From gitlab at gitlab.haskell.org Sat Jun 1 02:02:09 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Fri, 31 May 2024 22:02:09 -0400 Subject: [Git][ghc/ghc][wip/rip-stdcall] 3 commits: testsuite: adapt the testsuite for stdcall removal Message-ID: <665a8121127d4_1b206375687c8975b@gitlab.mail> Cheng Shao pushed to branch wip/rip-stdcall at Glasgow Haskell Compiler / GHC Commits: c422bc8f by Cheng Shao at 2024-06-01T02:01:26+00:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - 4cfbee50 by Cheng Shao at 2024-06-01T02:01:51+00:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 52c56d53 by Cheng Shao at 2024-06-01T02:01:51+00:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 30 changed files: - docs/users_guide/9.12.1-notes.rst - docs/users_guide/using-warnings.rst - docs/users_guide/win32-dlls.rst - testsuite/tests/concurrent/should_run/T5611.hs - testsuite/tests/concurrent/should_run/T5611a.hs - testsuite/tests/concurrent/should_run/conc036.hs - testsuite/tests/concurrent/should_run/conc037.hs - testsuite/tests/concurrent/should_run/conc038.hs - testsuite/tests/concurrent/should_run/foreignInterruptible.hs - testsuite/tests/diagnostic-codes/codes.stdout - testsuite/tests/ffi/should_compile/all.T - testsuite/tests/ffi/should_compile/cc004.hs - testsuite/tests/ffi/should_run/T1288.hs - testsuite/tests/ffi/should_run/T1288_c.c - testsuite/tests/ffi/should_run/T1288_ghci.hs - testsuite/tests/ffi/should_run/T1288_ghci_c.c - testsuite/tests/ffi/should_run/T22159.hs - testsuite/tests/ffi/should_run/T2276.hs - testsuite/tests/ffi/should_run/T2276_c.c - testsuite/tests/ffi/should_run/T2276_ghci.hs - testsuite/tests/ffi/should_run/T2276_ghci_c.c - testsuite/tests/ffi/should_run/all.T - + testsuite/tests/ffi/should_run/ffi012.ghc.stderr - testsuite/tests/rts/Makefile - testsuite/tests/rts/T12497.hs - testsuite/tests/rts/T7037_main.c - testsuite/tests/rts/all.T - testsuite/tests/rts/linker/T11223/all.T - testsuite/tests/th/T23309A.hs - testsuite/timeout/WinCBindings.hsc Changes: ===================================== docs/users_guide/9.12.1-notes.rst ===================================== @@ -60,6 +60,15 @@ Compiler - :ghc-flag:`-Wderiving-typeable` has been added to :ghc-flag:`-Wall`. +- i386 Windows support is now completely removed amid massive cleanup + of legacy code to pave way for Arm64 Windows support (`#24883 + `_). Rest + assured, this does not impact existing support for x86_64 Windows or + i386 Linux. For end users, the ``stdcall`` C calling convention is + now fully deprecated and GHC will unconditionally produce a warning + and treat it as ``ccall``. All C import/export declarations on + Windows should now use ``ccall``. + GHCi ~~~~ ===================================== docs/users_guide/using-warnings.rst ===================================== @@ -694,8 +694,7 @@ of ``-W(no-)*``. Causes a warning to be emitted for foreign declarations that use unsupported calling conventions. In particular, if the ``stdcall`` - calling convention is used on an architecture other than i386 then - it will be treated as ``ccall``. + calling convention is used then it will be treated as ``ccall``. .. ghc-flag:: -Wdodgy-foreign-imports :shortdesc: warn about dodgy foreign imports ===================================== docs/users_guide/win32-dlls.rst ===================================== @@ -319,7 +319,7 @@ to call from the outside. For example: adder :: Int -> Int -> IO Int -- gratuitous use of IO adder x y = return (x+y) - foreign export stdcall adder :: Int -> Int -> IO Int + foreign export ccall adder :: Int -> Int -> IO Int Add some helper code that starts up and shuts down the Haskell RTS: ===================================== testsuite/tests/concurrent/should_run/T5611.hs ===================================== @@ -7,7 +7,7 @@ import System.IO #if defined(mingw32_HOST_OS) sleep n = sleepBlock (n*1000) -foreign import stdcall safe "Sleep" sleepBlock :: Int -> IO () +foreign import ccall safe "Sleep" sleepBlock :: Int -> IO () #else sleep n = void $ sleepBlock n foreign import ccall safe "sleep" sleepBlock :: Int -> IO Int ===================================== testsuite/tests/concurrent/should_run/T5611a.hs ===================================== @@ -9,7 +9,7 @@ import System.IO #if defined(mingw32_HOST_OS) sleep n = sleepBlock (n*1000) -foreign import stdcall unsafe "Sleep" sleepBlock :: Int -> IO () +foreign import ccall unsafe "Sleep" sleepBlock :: Int -> IO () #else sleep n = void $ sleepBlock n foreign import ccall unsafe "sleep" sleepBlock :: Int -> IO Int ===================================== testsuite/tests/concurrent/should_run/conc036.hs ===================================== @@ -10,7 +10,7 @@ import System.IO #if defined(mingw32_HOST_OS) sleep n = sleepBlock (n*1000) -foreign import stdcall unsafe "Sleep" sleepBlock :: Int -> IO () +foreign import ccall unsafe "Sleep" sleepBlock :: Int -> IO () #else sleep n = sleepBlock n foreign import ccall unsafe "sleep" sleepBlock :: Int -> IO () ===================================== testsuite/tests/concurrent/should_run/conc037.hs ===================================== @@ -5,7 +5,7 @@ module Main where import Control.Concurrent #if defined(mingw32_HOST_OS) -foreign import stdcall safe "Sleep" _sleepBlock :: Int -> IO () +foreign import ccall safe "Sleep" _sleepBlock :: Int -> IO () sleepBlock n = _sleepBlock (n*1000) #else foreign import ccall safe "sleep" sleepBlock :: Int -> IO () @@ -24,4 +24,3 @@ main = do x <- takeMVar th putStrLn x putStrLn "\nshutting down" - ===================================== testsuite/tests/concurrent/should_run/conc038.hs ===================================== @@ -11,7 +11,7 @@ foreign export ccall "hFun" haskellFun :: Int -> IO () foreign import ccall safe "hFun" hFun :: Int -> IO () #if defined(mingw32_HOST_OS) -foreign import stdcall safe "Sleep" _sleepBlock :: Int -> IO () +foreign import ccall safe "Sleep" _sleepBlock :: Int -> IO () sleepBlock n = _sleepBlock (n*1000) #else foreign import ccall safe "sleep" sleepBlock :: Int -> IO () @@ -34,4 +34,3 @@ main = do x <- takeMVar th putStrLn x putStrLn "\nshutting down" - ===================================== testsuite/tests/concurrent/should_run/foreignInterruptible.hs ===================================== @@ -8,7 +8,7 @@ import System.IO #if defined(mingw32_HOST_OS) sleep n = sleepBlock (n*1000) -foreign import stdcall interruptible "Sleep" sleepBlock :: Int -> IO () +foreign import ccall interruptible "Sleep" sleepBlock :: Int -> IO () #else sleep n = sleepBlock n foreign import ccall interruptible "sleep" sleepBlock :: Int -> IO () ===================================== testsuite/tests/diagnostic-codes/codes.stdout ===================================== @@ -56,7 +56,6 @@ [GHC-63055] is untested (constructor = TcRnFieldUpdateInvalidType) [GHC-26133] is untested (constructor = TcRnForeignImportPrimSafeAnn) [GHC-03355] is untested (constructor = TcRnIllegalForeignDeclBackend) -[GHC-01245] is untested (constructor = TcRnUnsupportedCallConv) [GHC-01570] is untested (constructor = TcRnExpectedValueId) [GHC-96665] is untested (constructor = TcRnMultipleInlinePragmas) [GHC-88293] is untested (constructor = TcRnUnexpectedPragmas) @@ -119,5 +118,3 @@ [GHC-75721] is untested (constructor = CannotRepresentType) [GHC-17599] is untested (constructor = AddTopDeclsUnexpectedDeclarationSplice) [GHC-86934] is untested (constructor = ClassPE) - - ===================================== testsuite/tests/ffi/should_compile/all.T ===================================== @@ -6,13 +6,7 @@ setTestOpts(ffi) test('cc001', normal, compile, ['']) -# Non-static C call -# cc004 test also uses stdcall, so it only works on i386. -if config.platform.startswith('i386-'): - ways = normal -else: - ways = expect_fail -test('cc004', ways, compile, ['']) +test('cc004', expect_fail, compile, ['']) test('cc005', normal, compile, ['']) test('cc007', normal, compile, ['']) ===================================== testsuite/tests/ffi/should_compile/cc004.hs ===================================== @@ -9,15 +9,9 @@ import Data.Word -- importing functions --- We can't import the same function using both stdcall and ccall --- calling conventions in the same file when compiling via C (this is a --- restriction in the C backend caused by the need to emit a prototype --- for stdcall functions). foreign import stdcall "p" m_stdcall :: StablePtr a -> IO (StablePtr b) foreign import ccall unsafe "q" m_ccall :: ByteArray# -> IO Int --- We can't redefine the calling conventions of certain functions (those from --- math.h). foreign import stdcall "my_sin" my_sin :: Double -> IO Double foreign import stdcall "my_cos" my_cos :: Double -> IO Double @@ -65,4 +59,3 @@ type Sink2 b = Ptr b foreign import ccall unsafe "dynamic" sink2 :: Ptr (Sink2 b) -> Sink2 b - ===================================== testsuite/tests/ffi/should_run/T1288.hs ===================================== @@ -1,6 +1,6 @@ import Foreign import Foreign.C -foreign import stdcall "test" ctest :: CInt -> IO () +foreign import ccall "test" ctest :: CInt -> IO () main = ctest 3 ===================================== testsuite/tests/ffi/should_run/T1288_c.c ===================================== @@ -1,6 +1,6 @@ #include -void __attribute__((stdcall)) test(int arg) +void test(int arg) { printf("The argument passed was %i\n", arg ); } ===================================== testsuite/tests/ffi/should_run/T1288_ghci.hs ===================================== @@ -1,6 +1,6 @@ import Foreign import Foreign.C -foreign import stdcall "test" ctest :: CInt -> IO () +foreign import ccall "test" ctest :: CInt -> IO () main = ctest 3 ===================================== testsuite/tests/ffi/should_run/T1288_ghci_c.c ===================================== @@ -1,6 +1,6 @@ #include -void __attribute__((stdcall)) test(int arg) +void test(int arg) { printf("The argument passed was %i\n", arg ); } ===================================== testsuite/tests/ffi/should_run/T22159.hs ===================================== @@ -1,20 +1,12 @@ {-# LANGUAGE CPP #-} module Main (main) where -#if defined(i386_HOST_ARCH) -# define WINDOWS_CCONV stdcall -#elif defined(x86_64_HOST_ARCH) -# define WINDOWS_CCONV ccall -#else -# error Unknown mingw32 arch -#endif - import Foreign.C.String (peekCWString) import Foreign.C.Types (CWchar) import Foreign.Marshal.Alloc (allocaBytes) import Foreign.Ptr (Ptr) -foreign import WINDOWS_CCONV "hello" c_hello :: Ptr CWchar -> IO () +foreign import ccall "hello" c_hello :: Ptr CWchar -> IO () main :: IO () main = allocaBytes 12 $ \buf -> do ===================================== testsuite/tests/ffi/should_run/T2276.hs ===================================== @@ -1,7 +1,7 @@ import Foreign import Foreign.C -foreign import stdcall "&test" ptest :: FunPtr (CInt -> IO ()) -foreign import stdcall "dynamic" ctest :: FunPtr (CInt -> IO ()) -> CInt -> IO () +foreign import ccall "&test" ptest :: FunPtr (CInt -> IO ()) +foreign import ccall "dynamic" ctest :: FunPtr (CInt -> IO ()) -> CInt -> IO () main = ctest ptest 3 ===================================== testsuite/tests/ffi/should_run/T2276_c.c ===================================== @@ -1,6 +1,6 @@ #include -void __attribute__((stdcall)) test(int arg) +void test(int arg) { printf("The argument passed was %i\n", arg ); } ===================================== testsuite/tests/ffi/should_run/T2276_ghci.hs ===================================== @@ -1,7 +1,7 @@ import Foreign import Foreign.C -foreign import stdcall "&test" ptest :: FunPtr (CInt -> IO ()) -foreign import stdcall "dynamic" ctest :: FunPtr (CInt -> IO ()) -> CInt -> IO () +foreign import ccall "&test" ptest :: FunPtr (CInt -> IO ()) +foreign import ccall "dynamic" ctest :: FunPtr (CInt -> IO ()) -> CInt -> IO () main = ctest ptest 3 ===================================== testsuite/tests/ffi/should_run/T2276_ghci_c.c ===================================== @@ -1,6 +1,6 @@ #include -void __attribute__((stdcall)) test(int arg) +void test(int arg) { printf("The argument passed was %i\n", arg ); } ===================================== testsuite/tests/ffi/should_run/all.T ===================================== @@ -61,17 +61,7 @@ else: test('ffi010', normal, compile_and_run, ['']) test('ffi011', normal, compile_and_run, ['']) -# The stdcall calling convention works on Windows, and sometimes on -# Linux, and fails everywhhere else. For now, we test only on Windows, -# because it's difficult to discover whether a given Linux supports -# it. - -if config.os == 'mingw32': - skip_if_not_windows = normal -else: - skip_if_not_windows = skip - -test('ffi012', skip_if_not_windows, compile_and_run, ['']) +test('ffi012', normal, warn_and_run, ['']) test('ffi013', [normal, js_broken(22363)], compile_and_run, ['']) # threaded2 sometimes gives ffi014: Main_dDu: interrupted ===================================== testsuite/tests/ffi/should_run/ffi012.ghc.stderr ===================================== @@ -0,0 +1,52 @@ +[1 of 2] Compiling Main ( ffi012.hs, ffi012.o ) +ffi012.hs:11:1: warning: [GHC-01245] [-Wunsupported-calling-conventions (in -Wdefault)] + • the 'stdcall' calling convention is unsupported on this platform, + treating as ccall + • When checking declaration: + foreign import stdcall safe "wrapper" wrap_f :: F -> IO (FunPtr F) + +ffi012.hs:12:1: warning: [GHC-01245] [-Wunsupported-calling-conventions (in -Wdefault)] + • the 'stdcall' calling convention is unsupported on this platform, + treating as ccall + • When checking declaration: + foreign import stdcall safe "wrapper" wrap_f_io + :: IOF -> IO (FunPtr IOF) + +ffi012.hs:14:1: warning: [GHC-01245] [-Wunsupported-calling-conventions (in -Wdefault)] + • the 'stdcall' calling convention is unsupported on this platform, + treating as ccall + • When checking declaration: + foreign import stdcall safe "dynamic" f :: FunPtr F -> F + +ffi012.hs:15:1: warning: [GHC-01245] [-Wunsupported-calling-conventions (in -Wdefault)] + • the 'stdcall' calling convention is unsupported on this platform, + treating as ccall + • When checking declaration: + foreign import stdcall safe "dynamic" f_io :: FunPtr IOF -> IOF + +ffi012.hs:28:1: warning: [GHC-01245] [-Wunsupported-calling-conventions (in -Wdefault)] + • the 'stdcall' calling convention is unsupported on this platform, + treating as ccall + • When checking declaration: + foreign import stdcall safe "wrapper" wrap_d :: D -> IO (FunPtr D) + +ffi012.hs:29:1: warning: [GHC-01245] [-Wunsupported-calling-conventions (in -Wdefault)] + • the 'stdcall' calling convention is unsupported on this platform, + treating as ccall + • When checking declaration: + foreign import stdcall safe "wrapper" wrap_d_io + :: IOD -> IO (FunPtr IOD) + +ffi012.hs:31:1: warning: [GHC-01245] [-Wunsupported-calling-conventions (in -Wdefault)] + • the 'stdcall' calling convention is unsupported on this platform, + treating as ccall + • When checking declaration: + foreign import stdcall safe "dynamic" d :: FunPtr D -> D + +ffi012.hs:32:1: warning: [GHC-01245] [-Wunsupported-calling-conventions (in -Wdefault)] + • the 'stdcall' calling convention is unsupported on this platform, + treating as ccall + • When checking declaration: + foreign import stdcall safe "dynamic" d_io :: FunPtr IOD -> IOD + +[2 of 2] Linking ffi012 ===================================== testsuite/tests/rts/Makefile ===================================== @@ -64,16 +64,11 @@ T6006_setup : T8124_setup : '$(TEST_HC)' $(TEST_HC_OPTS) -c T8124.hs -ifeq "$(TARGETPLATFORM)" "i386-unknown-mingw32" -T7037_CONST = const -else -T7037_CONST = -endif .PHONY: T7037 T7037: $(RM) 7037.o 7037.hi 7037$(exeext) "$(TEST_HC)" $(TEST_HC_OPTS) T7037.hs -v0 - "$(TEST_HC)" -optc-DT7037_CONST=$(T7037_CONST) $(filter-out -rtsopts, $(TEST_HC_OPTS)) T7037_main.c -v0 -o T7037_main -no-hs-main + "$(TEST_HC)" $(filter-out -rtsopts, $(TEST_HC_OPTS)) T7037_main.c -v0 -o T7037_main -no-hs-main ./T7037_main T7040_ghci_setup : ===================================== testsuite/tests/rts/T12497.hs ===================================== @@ -1,17 +1,7 @@ -{-# LANGUAGE CPP #-} - -#if defined(i386_HOST_ARCH) -# define WINDOWS_CCONV stdcall -#elif defined(x86_64_HOST_ARCH) -# define WINDOWS_CCONV ccall -#else -# error Unknown mingw32 arch -#endif - import Foreign.C.String -foreign import WINDOWS_CCONV "_strdup" strdup :: CString -> IO CString -foreign import WINDOWS_CCONV "strdup" strdup2 :: CString -> IO CString +foreign import ccall "_strdup" strdup :: CString -> IO CString +foreign import ccall "strdup" strdup2 :: CString -> IO CString dupString :: String -> IO String dupString str = newCString str >>= strdup >>= peekCString ===================================== testsuite/tests/rts/T7037_main.c ===================================== @@ -2,6 +2,6 @@ #include int main(int argc, char *argv[]) { - char * T7037_CONST args[2] = {"T7037", NULL}; + char * args[2] = {"T7037", NULL}; execv("./T7037", args); } ===================================== testsuite/tests/rts/all.T ===================================== @@ -239,8 +239,6 @@ def config_T5250(name, opts): test('T5250', [extra_files(['spalign.c']), config_T5250, - # stack ptr is not 16-byte aligned on 32-bit Windows - when(platform('i386-unknown-mingw32'), expect_fail), when(platform('i386-unknown-linux'), expect_broken_for(4211,['llvm']))], compile_and_run, ['spalign.c']) ===================================== testsuite/tests/rts/linker/T11223/all.T ===================================== @@ -5,7 +5,7 @@ import re # Python normalization functions #-------------------------------------- def normalise_duplicate_errmsg( msg ): - return re.sub(r"((?:[a-z, A-Z]+):|)[\/\\\\]+(?:.+[\/\\\\]+?)?(.+?)[\/\\\\]+", " ", + return re.sub(r"((?:[a-z, A-Z]+):|)[\/\\\\]+(?:.+[\/\\\\]+?)?(.+?)[\/\\\\]+", " ", re.sub(r"version\s(\d+\.\d+\.\d+)\sfor\s[a-z,A-Z,0-9,_,-]+(?=\))", r"", msg)) #-------------------------------------- @@ -33,7 +33,6 @@ test('T11223_simple_duplicate', test('T11223_simple_duplicate_lib', [extra_files(['bar.c', 'foo.c', 'foo.hs']), - when(platform('i386-unknown-mingw32'), expect_broken(13515)), when(ghc_dynamic(), skip), normalise_errmsg_fun(normalise_duplicate_errmsg), req_c], makefile_test, ['t_11223_simple_duplicate_lib']) ===================================== testsuite/tests/th/T23309A.hs ===================================== @@ -1,19 +1,6 @@ -{-# LANGUAGE CPP #-} module T23309A (c_foo) where import Foreign.C.String import Foreign.C.Types -#if defined(mingw32_HOST_OS) -# if defined(i386_HOST_ARCH) -# define CALLCONV stdcall -# elif defined(x86_64_HOST_ARCH) -# define CALLCONV ccall -# else -# error Unknown mingw32 arch -# endif -#else -# define CALLCONV ccall -#endif - -foreign import CALLCONV unsafe "foo" c_foo :: CInt -> IO CString +foreign import ccall unsafe "foo" c_foo :: CInt -> IO CString ===================================== testsuite/timeout/WinCBindings.hsc ===================================== @@ -3,14 +3,6 @@ module WinCBindings where #if defined(mingw32_HOST_OS) -##if defined(i386_HOST_ARCH) -## define WINDOWS_CCONV stdcall -##elif defined(x86_64_HOST_ARCH) -## define WINDOWS_CCONV ccall -##else -## error Unknown mingw32 arch -##endif - import Foreign import Foreign.C.Types import System.Win32.File @@ -253,7 +245,7 @@ instance Storable JOBOBJECT_ASSOCIATE_COMPLETION_PORT where jacpCompletionPort = vCompletionPort} -foreign import WINDOWS_CCONV unsafe "windows.h WaitForSingleObject" +foreign import ccall unsafe "windows.h WaitForSingleObject" waitForSingleObject :: HANDLE -> DWORD -> IO DWORD type JOBOBJECTINFOCLASS = CInt @@ -294,22 +286,22 @@ cCREATE_SUSPENDED = #const CREATE_SUSPENDED cHANDLE_FLAG_INHERIT :: DWORD cHANDLE_FLAG_INHERIT = #const HANDLE_FLAG_INHERIT -foreign import WINDOWS_CCONV unsafe "windows.h GetExitCodeProcess" +foreign import ccall unsafe "windows.h GetExitCodeProcess" getExitCodeProcess :: HANDLE -> LPDWORD -> IO BOOL -foreign import WINDOWS_CCONV unsafe "windows.h CloseHandle" +foreign import ccall unsafe "windows.h CloseHandle" closeHandle :: HANDLE -> IO BOOL -foreign import WINDOWS_CCONV unsafe "windows.h TerminateJobObject" +foreign import ccall unsafe "windows.h TerminateJobObject" terminateJobObject :: HANDLE -> UINT -> IO BOOL -foreign import WINDOWS_CCONV unsafe "windows.h AssignProcessToJobObject" +foreign import ccall unsafe "windows.h AssignProcessToJobObject" assignProcessToJobObject :: HANDLE -> HANDLE -> IO BOOL -foreign import WINDOWS_CCONV unsafe "windows.h CreateJobObjectW" +foreign import ccall unsafe "windows.h CreateJobObjectW" createJobObjectW :: LPSECURITY_ATTRIBUTES -> LPCTSTR -> IO HANDLE -foreign import WINDOWS_CCONV unsafe "windows.h CreateProcessW" +foreign import ccall unsafe "windows.h CreateProcessW" createProcessW :: LPCTSTR -> LPTSTR -> LPSECURITY_ATTRIBUTES -> LPSECURITY_ATTRIBUTES -> BOOL -> DWORD -> LPVOID -> LPCTSTR -> LPSTARTUPINFO @@ -317,16 +309,16 @@ foreign import WINDOWS_CCONV unsafe "windows.h CreateProcessW" foreign import ccall unsafe "string.h" memset :: Ptr a -> CInt -> CSize -> IO (Ptr a) -foreign import WINDOWS_CCONV unsafe "windows.h SetInformationJobObject" +foreign import ccall unsafe "windows.h SetInformationJobObject" setInformationJobObject :: HANDLE -> JOBOBJECTINFOCLASS -> LPVOID -> DWORD -> IO BOOL -foreign import WINDOWS_CCONV unsafe "windows.h CreateIoCompletionPort" +foreign import ccall unsafe "windows.h CreateIoCompletionPort" createIoCompletionPort :: HANDLE -> HANDLE -> ULONG_PTR -> DWORD -> IO HANDLE -foreign import WINDOWS_CCONV unsafe "windows.h GetQueuedCompletionStatus" +foreign import ccall unsafe "windows.h GetQueuedCompletionStatus" getQueuedCompletionStatus :: HANDLE -> LPDWORD -> PULONG_PTR -> Ptr LPOVERLAPPED -> DWORD -> IO BOOL -foreign import WINDOWS_CCONV unsafe "windows.h SetHandleInformation" +foreign import ccall unsafe "windows.h SetHandleInformation" setHandleInformation :: HANDLE -> DWORD -> DWORD -> IO BOOL setJobParameters :: HANDLE -> IO BOOL @@ -394,4 +386,3 @@ waitForJobCompletion _hJob ioPort timeout then False -- Timeout occurred. *dark voice* YOU HAVE FAILED THIS TEST!. else True #endif - View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/efd3176cf386bd5ec2da8d07766ffb9f2871a48d...52c56d53b4ceecab7ee178497166be79b0b5918e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/efd3176cf386bd5ec2da8d07766ffb9f2871a48d...52c56d53b4ceecab7ee178497166be79b0b5918e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 04:25:09 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sat, 01 Jun 2024 00:25:09 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/rip-dead-adjustor Message-ID: <665aa2a597cad_1b206318253b092445@gitlab.mail> Cheng Shao pushed new branch wip/rip-dead-adjustor at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/rip-dead-adjustor You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 07:18:02 2024 From: gitlab at gitlab.haskell.org (Hannes Siebenhandl (@fendor)) Date: Sat, 01 Jun 2024 03:18:02 -0400 Subject: [Git][ghc/ghc][wip/fendor/os-string-modlocation] Migrate `Finder` component to `OsPath`, fixed #24616 Message-ID: <665acb2a85792_1b2063323cf8c11352f@gitlab.mail> Hannes Siebenhandl pushed to branch wip/fendor/os-string-modlocation at Glasgow Haskell Compiler / GHC Commits: b534a1a2 by Fendor at 2024-06-01T09:16:18+02:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 20 changed files: - compiler/GHC.hs - + compiler/GHC/Data/OsPath.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Config/Finder.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Iface/Errors.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Finder/Types.hs - compiler/GHC/Unit/Module/Location.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/ghc.cabal.in - ghc/ghc-bin.cabal.in - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -3,6 +3,7 @@ {-# LANGUAGE NondecreasingIndentation, ScopedTypeVariables #-} {-# LANGUAGE TupleSections, NamedFieldPuns #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE PatternSynonyms #-} -- ----------------------------------------------------------------------------- -- @@ -76,6 +77,7 @@ module GHC ( ModuleGraph, emptyMG, mapMG, mkModuleGraph, mgModSummaries, mgLookupModule, ModSummary(..), ms_mod_name, ModLocation(..), + pattern ModLocation, getModSummary, getModuleGraph, isLoaded, ===================================== compiler/GHC/Data/OsPath.hs ===================================== @@ -0,0 +1,29 @@ +module GHC.Data.OsPath + ( + -- * OsPath initialisation and transformation + OsPath + , OsString + , encodeUtf + , decodeUtf + , unsafeDecodeUtf + , unsafeEncodeUtf + , os + -- * Common utility functions + , () + , (<.>) + ) + where + +import GHC.Prelude + +import GHC.Utils.Misc (HasCallStack) +import GHC.Utils.Panic (panic) + +import System.OsPath +import System.Directory.Internal (os) + +-- | Decode an 'OsPath' to 'FilePath', throwing an 'error' if decoding failed. +-- Prefer 'decodeUtf' and gracious error handling. +unsafeDecodeUtf :: HasCallStack => OsPath -> FilePath +unsafeDecodeUtf p = + either (\err -> panic $ "Failed to decodeUtf \"" ++ show p ++ "\", because: " ++ show err) id (decodeUtf p) ===================================== compiler/GHC/Data/Strict.hs ===================================== @@ -9,8 +9,8 @@ module GHC.Data.Strict ( Maybe(Nothing, Just), fromMaybe, + GHC.Data.Strict.maybe, Pair(And), - -- Not used at the moment: -- -- Either(Left, Right), @@ -18,6 +18,7 @@ module GHC.Data.Strict ( ) where import GHC.Prelude hiding (Maybe(..), Either(..)) + import Control.Applicative import Data.Semigroup import Data.Data @@ -29,6 +30,10 @@ fromMaybe :: a -> Maybe a -> a fromMaybe d Nothing = d fromMaybe _ (Just x) = x +maybe :: b -> (a -> b) -> Maybe a -> b +maybe d _ Nothing = d +maybe _ f (Just x) = f x + apMaybe :: Maybe (a -> b) -> Maybe a -> Maybe b apMaybe (Just f) (Just x) = Just (f x) apMaybe _ _ = Nothing ===================================== compiler/GHC/Driver/Backpack.hs ===================================== @@ -74,6 +74,7 @@ import GHC.Linker.Types import qualified GHC.LanguageExtensions as LangExt import GHC.Data.Maybe +import GHC.Data.OsPath (unsafeEncodeUtf, os) import GHC.Data.StringBuffer import GHC.Data.FastString import qualified GHC.Data.EnumSet as EnumSet @@ -772,7 +773,7 @@ summariseRequirement pn mod_name = do let PackageName pn_fs = pn let location = mkHomeModLocation2 fopts mod_name - (unpackFS pn_fs moduleNameSlashes mod_name) "hsig" + (unsafeEncodeUtf $ unpackFS pn_fs moduleNameSlashes mod_name) (os "hsig") env <- getBkpEnv src_hash <- liftIO $ getFileHash (bkp_filename env) @@ -855,12 +856,12 @@ hsModuleToModSummary home_keys pn hsc_src modname -- these filenames to figure out where the hi files go. -- A travesty! let location0 = mkHomeModLocation2 fopts modname - (unpackFS unit_fs + (unsafeEncodeUtf $ unpackFS unit_fs moduleNameSlashes modname) (case hsc_src of - HsigFile -> "hsig" - HsBootFile -> "hs-boot" - HsSrcFile -> "hs") + HsigFile -> os "hsig" + HsBootFile -> os "hs-boot" + HsSrcFile -> os "hs") -- DANGEROUS: bootifying can POISON the module finder cache let location = case hsc_src of HsBootFile -> addBootSuffixLocnOut location0 ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -35,6 +35,7 @@ import GHC.Driver.LlvmConfigCache (LlvmConfigCache) import GHC.Driver.Ppr import GHC.Driver.Backend +import GHC.Data.OsPath import qualified GHC.Data.ShortText as ST import GHC.Data.Stream ( Stream ) import qualified GHC.Data.Stream as Stream @@ -259,7 +260,7 @@ outputForeignStubs Maybe FilePath) -- C file created outputForeignStubs logger tmpfs dflags unit_state mod location stubs = do - let stub_h = mkStubPaths (initFinderOpts dflags) (moduleName mod) location + let stub_h = unsafeDecodeUtf $ mkStubPaths (initFinderOpts dflags) (moduleName mod) location stub_c <- newTempName logger tmpfs (tmpDir dflags) TFL_CurrentModule "c" case stubs of ===================================== compiler/GHC/Driver/Config/Finder.hs ===================================== @@ -8,27 +8,27 @@ import GHC.Prelude import GHC.Driver.DynFlags import GHC.Unit.Finder.Types import GHC.Data.FastString - +import GHC.Data.OsPath -- | Create a new 'FinderOpts' from DynFlags. initFinderOpts :: DynFlags -> FinderOpts initFinderOpts flags = FinderOpts - { finder_importPaths = importPaths flags + { finder_importPaths = fmap unsafeEncodeUtf $ importPaths flags , finder_lookupHomeInterfaces = isOneShot (ghcMode flags) , finder_bypassHiFileCheck = MkDepend == (ghcMode flags) , finder_ways = ways flags , finder_enableSuggestions = gopt Opt_HelpfulErrors flags - , finder_workingDirectory = workingDirectory flags + , finder_workingDirectory = fmap unsafeEncodeUtf $ workingDirectory flags , finder_thisPackageName = mkFastString <$> thisPackageName flags , finder_hiddenModules = hiddenModules flags , finder_reexportedModules = reexportedModules flags - , finder_hieDir = hieDir flags - , finder_hieSuf = hieSuf flags - , finder_hiDir = hiDir flags - , finder_hiSuf = hiSuf_ flags - , finder_dynHiSuf = dynHiSuf_ flags - , finder_objectDir = objectDir flags - , finder_objectSuf = objectSuf_ flags - , finder_dynObjectSuf = dynObjectSuf_ flags - , finder_stubDir = stubDir flags + , finder_hieDir = fmap unsafeEncodeUtf $ hieDir flags + , finder_hieSuf = unsafeEncodeUtf $ hieSuf flags + , finder_hiDir = fmap unsafeEncodeUtf $ hiDir flags + , finder_hiSuf = unsafeEncodeUtf $ hiSuf_ flags + , finder_dynHiSuf = unsafeEncodeUtf $ dynHiSuf_ flags + , finder_objectDir = fmap unsafeEncodeUtf $ objectDir flags + , finder_objectSuf = unsafeEncodeUtf $ objectSuf_ flags + , finder_dynObjectSuf = unsafeEncodeUtf $ dynObjectSuf_ flags + , finder_stubDir = fmap unsafeEncodeUtf $ stubDir flags } ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -264,6 +264,7 @@ import qualified GHC.LanguageExtensions as LangExt import GHC.Data.FastString import GHC.Data.Bag +import GHC.Data.OsPath (unsafeEncodeUtf) import GHC.Data.StringBuffer import qualified GHC.Data.Stream as Stream import GHC.Data.Stream (Stream) @@ -2106,12 +2107,13 @@ hscCompileCmmFile hsc_env original_filename filename output_filename = runHsc hs rawCmms return stub_c_exists where - no_loc = ModLocation{ ml_hs_file = Just original_filename, - ml_hi_file = panic "hscCompileCmmFile: no hi file", - ml_obj_file = panic "hscCompileCmmFile: no obj file", - ml_dyn_obj_file = panic "hscCompileCmmFile: no dyn obj file", - ml_dyn_hi_file = panic "hscCompileCmmFile: no dyn obj file", - ml_hie_file = panic "hscCompileCmmFile: no hie file"} + no_loc = OsPathModLocation + { ml_hs_file_ospath = Just $ unsafeEncodeUtf original_filename, + ml_hi_file_ospath = panic "hscCompileCmmFile: no hi file", + ml_obj_file_ospath = panic "hscCompileCmmFile: no obj file", + ml_dyn_obj_file_ospath = panic "hscCompileCmmFile: no dyn obj file", + ml_dyn_hi_file_ospath = panic "hscCompileCmmFile: no dyn obj file", + ml_hie_file_ospath = panic "hscCompileCmmFile: no hie file"} -------------------- Stuff for new code gen --------------------- @@ -2346,12 +2348,13 @@ hscParsedDecls hsc_env decls = runInteractiveHsc hsc_env $ do {- Desugar it -} -- We use a basically null location for iNTERACTIVE - let iNTERACTIVELoc = ModLocation{ ml_hs_file = Nothing, - ml_hi_file = panic "hsDeclsWithLocation:ml_hi_file", - ml_obj_file = panic "hsDeclsWithLocation:ml_obj_file", - ml_dyn_obj_file = panic "hsDeclsWithLocation:ml_dyn_obj_file", - ml_dyn_hi_file = panic "hsDeclsWithLocation:ml_dyn_hi_file", - ml_hie_file = panic "hsDeclsWithLocation:ml_hie_file" } + let iNTERACTIVELoc = OsPathModLocation + { ml_hs_file_ospath = Nothing, + ml_hi_file_ospath = panic "hsDeclsWithLocation:ml_hi_file_ospath", + ml_obj_file_ospath = panic "hsDeclsWithLocation:ml_obj_file_ospath", + ml_dyn_obj_file_ospath = panic "hsDeclsWithLocation:ml_dyn_obj_file_ospath", + ml_dyn_hi_file_ospath = panic "hsDeclsWithLocation:ml_dyn_hi_file_ospath", + ml_hie_file_ospath = panic "hsDeclsWithLocation:ml_hie_file_ospath" } ds_result <- hscDesugar' iNTERACTIVELoc tc_gblenv {- Simplify -} @@ -2630,12 +2633,13 @@ hscCompileCoreExpr' hsc_env srcspan ds_expr = do {- Lint if necessary -} lintInteractiveExpr (text "hscCompileCoreExpr") hsc_env prepd_expr - let this_loc = ModLocation{ ml_hs_file = Nothing, - ml_hi_file = panic "hscCompileCoreExpr':ml_hi_file", - ml_obj_file = panic "hscCompileCoreExpr':ml_obj_file", - ml_dyn_obj_file = panic "hscCompileCoreExpr': ml_obj_file", - ml_dyn_hi_file = panic "hscCompileCoreExpr': ml_dyn_hi_file", - ml_hie_file = panic "hscCompileCoreExpr':ml_hie_file" } + let this_loc = OsPathModLocation + { ml_hs_file_ospath = Nothing, + ml_hi_file_ospath = panic "hscCompileCoreExpr':ml_hi_file_ospath", + ml_obj_file_ospath = panic "hscCompileCoreExpr':ml_obj_file_ospath", + ml_dyn_obj_file_ospath = panic "hscCompileCoreExpr': ml_obj_file_ospath", + ml_dyn_hi_file_ospath = panic "hscCompileCoreExpr': ml_dyn_hi_file_ospath", + ml_hie_file_ospath = panic "hscCompileCoreExpr':ml_hie_file_ospath" } -- Ensure module uniqueness by giving it a name like "GhciNNNN". -- This uniqueness is needed by the JS linker. Without it we break the 1-1 ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -76,6 +76,7 @@ import GHC.Data.Bag ( listToBag ) import GHC.Data.Graph.Directed import GHC.Data.FastString import GHC.Data.Maybe ( expectJust ) +import GHC.Data.OsPath ( unsafeEncodeUtf ) import GHC.Data.StringBuffer import qualified GHC.LanguageExtensions as LangExt @@ -1837,7 +1838,7 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = tn <- newTempName logger tmpfs (tmpDir dflags) staticLife suf let dyn_tn = tn -<.> dynsuf addFilesToClean tmpfs dynLife [dyn_tn] - return (tn, dyn_tn) + return (unsafeEncodeUtf tn, unsafeEncodeUtf dyn_tn) -- We don't want to create .o or .hi files unless we have been asked -- to by the user. But we need them, so we patch their locations in -- the ModSummary with temporary files. @@ -1846,8 +1847,8 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = -- If ``-fwrite-interface` is specified, then the .o and .hi files -- are written into `-odir` and `-hidir` respectively. #16670 if gopt Opt_WriteInterface dflags - then return ((ml_hi_file ms_location, ml_dyn_hi_file ms_location) - , (ml_obj_file ms_location, ml_dyn_obj_file ms_location)) + then return ((ml_hi_file_ospath ms_location, ml_dyn_hi_file_ospath ms_location) + , (ml_obj_file_ospath ms_location, ml_dyn_obj_file_ospath ms_location)) else (,) <$> (new_temp_file (hiSuf_ dflags) (dynHiSuf_ dflags)) <*> (new_temp_file (objectSuf_ dflags) (dynObjectSuf_ dflags)) let new_dflags = case enable_spec of @@ -1856,10 +1857,10 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = EnableByteCodeAndObject -> (gopt_set dflags Opt_ByteCodeAndObjectCode) { backend = defaultBackendOf ms} let ms' = ms { ms_location = - ms_location { ml_hi_file = hi_file - , ml_obj_file = o_file - , ml_dyn_hi_file = dyn_hi_file - , ml_dyn_obj_file = dyn_o_file } + ms_location { ml_hi_file_ospath = hi_file + , ml_obj_file_ospath = o_file + , ml_dyn_hi_file_ospath = dyn_hi_file + , ml_dyn_obj_file_ospath = dyn_o_file } , ms_hspp_opts = updOptLevel 0 $ new_dflags } -- Recursive call to catch the other cases @@ -2044,7 +2045,7 @@ summariseFile hsc_env' home_unit old_summaries src_fn mb_phase maybe_buf let fopts = initFinderOpts (hsc_dflags hsc_env) -- Make a ModLocation for this file - let location = mkHomeModLocation fopts pi_mod_name src_fn + let location = mkHomeModLocation fopts pi_mod_name (unsafeEncodeUtf src_fn) -- Tell the Finder cache where it is, so that subsequent calls -- to findModule will find it, even if it's not on any search path ===================================== compiler/GHC/Driver/MakeFile.hs ===================================== @@ -24,6 +24,7 @@ import GHC.Driver.Env import GHC.Driver.Errors.Types import qualified GHC.SysTools as SysTools import GHC.Data.Graph.Directed ( SCC(..) ) +import GHC.Data.OsPath (unsafeDecodeUtf) import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Types.SourceError @@ -252,7 +253,7 @@ processDeps dflags hsc_env excl_mods root hdl (AcyclicSCC (ModuleNode _ node)) -- files if the module has a corresponding .hs-boot file (#14482) ; when (isBootSummary node == IsBoot) $ do let hi_boot = msHiFilePath node - let obj = removeBootSuffix (msObjFilePath node) + let obj = unsafeDecodeUtf $ removeBootSuffix (msObjFileOsPath node) forM_ extra_suffixes $ \suff -> do let way_obj = insertSuffixes obj [suff] let way_hi_boot = insertSuffixes hi_boot [suff] @@ -297,7 +298,7 @@ findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps = do Found loc _ -- Home package: just depend on the .hi or hi-boot file | isJust (ml_hs_file loc) || include_pkg_deps - -> return (Just (addBootSuffix_maybe is_boot (ml_hi_file loc))) + -> return (Just (unsafeDecodeUtf $ addBootSuffix_maybe is_boot (ml_hi_file_ospath loc))) -- Not in this package: we don't need a dependency | otherwise ===================================== compiler/GHC/Driver/Pipeline/Execute.hs ===================================== @@ -58,6 +58,7 @@ import GHC.Iface.Make import GHC.Driver.Config.Parser import GHC.Parser.Header import GHC.Data.StringBuffer +import GHC.Data.OsPath (unsafeEncodeUtf) import GHC.Types.SourceError import GHC.Unit.Finder import Data.IORef @@ -759,7 +760,7 @@ mkOneShotModLocation :: PipeEnv -> DynFlags -> HscSource -> ModuleName -> IO Mod mkOneShotModLocation pipe_env dflags src_flavour mod_name = do let PipeEnv{ src_basename=basename, src_suffix=suff } = pipe_env - let location1 = mkHomeModLocation2 fopts mod_name basename suff + let location1 = mkHomeModLocation2 fopts mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf suff) -- Boot-ify it if necessary let location2 @@ -771,11 +772,11 @@ mkOneShotModLocation pipe_env dflags src_flavour mod_name = do -- This can't be done in mkHomeModuleLocation because -- it only applies to the module being compiles let ohi = outputHi dflags - location3 | Just fn <- ohi = location2{ ml_hi_file = fn } + location3 | Just fn <- ohi = location2{ ml_hi_file_ospath = unsafeEncodeUtf fn } | otherwise = location2 let dynohi = dynOutputHi dflags - location4 | Just fn <- dynohi = location3{ ml_dyn_hi_file = fn } + location4 | Just fn <- dynohi = location3{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn } | otherwise = location3 -- Take -o into account if present @@ -789,10 +790,10 @@ mkOneShotModLocation pipe_env dflags src_flavour mod_name = do location5 | Just ofile <- expl_o_file , let dyn_ofile = fromMaybe (ofile -<.> dynObjectSuf_ dflags) expl_dyn_o_file , isNoLink (ghcLink dflags) - = location4 { ml_obj_file = ofile - , ml_dyn_obj_file = dyn_ofile } + = location4 { ml_obj_file_ospath = unsafeEncodeUtf ofile + , ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile } | Just dyn_ofile <- expl_dyn_o_file - = location4 { ml_dyn_obj_file = dyn_ofile } + = location4 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile } | otherwise = location4 return location5 where ===================================== compiler/GHC/Iface/Errors.hs ===================================== @@ -14,6 +14,7 @@ import GHC.Utils.Panic.Plain import GHC.Driver.DynFlags import GHC.Driver.Env import GHC.Data.Maybe +import GHC.Data.OsPath import GHC.Prelude import GHC.Unit import GHC.Unit.Env @@ -55,13 +56,13 @@ cantFindInstalledErr unit_state mhome_unit profile mod_name find_result InstalledNotFound files mb_pkg | Just pkg <- mb_pkg , notHomeUnitId mhome_unit pkg - -> not_found_in_package pkg files + -> not_found_in_package pkg $ fmap unsafeDecodeUtf files | null files -> NotAModule | otherwise - -> CouldntFindInFiles files + -> CouldntFindInFiles $ fmap unsafeDecodeUtf files _ -> panic "cantFindInstalledErr" ===================================== compiler/GHC/Unit/Finder.hs ===================================== @@ -42,6 +42,9 @@ import GHC.Platform.Ways import GHC.Builtin.Names ( gHC_PRIM ) +import GHC.Data.Maybe ( expectJust ) +import GHC.Data.OsPath + import GHC.Unit.Env import GHC.Unit.Types import GHC.Unit.Module @@ -49,7 +52,6 @@ import GHC.Unit.Home import GHC.Unit.State import GHC.Unit.Finder.Types -import GHC.Data.Maybe ( expectJust ) import qualified GHC.Data.ShortText as ST import GHC.Utils.Misc @@ -61,8 +63,7 @@ import GHC.Types.PkgQual import GHC.Fingerprint import Data.IORef -import System.Directory -import System.FilePath +import System.Directory.OsPath import Control.Monad import Data.Time import qualified Data.Map as M @@ -70,9 +71,10 @@ import GHC.Driver.Env ( hsc_home_unit_maybe, HscEnv(hsc_FC, hsc_dflags, hsc_unit_env) ) import GHC.Driver.Config.Finder import qualified Data.Set as Set +import qualified System.OsPath as OsPath -type FileExt = String -- Filename extension -type BaseName = String -- Basename of file +type FileExt = OsString -- Filename extension +type BaseName = OsPath -- Basename of file -- ----------------------------------------------------------------------------- -- The Finder @@ -286,7 +288,7 @@ findLookupResult fc fopts r = case r of -- implicit locations from the instances InstalledFound loc _ -> return (Found loc m) InstalledNoPackage _ -> return (NoPackage (moduleUnit m)) - InstalledNotFound fp _ -> return (NotFound{ fr_paths = fp, fr_pkg = Just (moduleUnit m) + InstalledNotFound fp _ -> return (NotFound{ fr_paths = fmap unsafeDecodeUtf fp, fr_pkg = Just (moduleUnit m) , fr_pkgs_hidden = [] , fr_mods_hidden = [] , fr_unusables = [] @@ -357,7 +359,7 @@ findHomeModule fc fopts home_unit mod_name = do InstalledFound loc _ -> Found loc (mkHomeModule home_unit mod_name) InstalledNoPackage _ -> NoPackage uid -- impossible InstalledNotFound fps _ -> NotFound { - fr_paths = fps, + fr_paths = fmap unsafeDecodeUtf fps, fr_pkg = Just uid, fr_mods_hidden = [], fr_pkgs_hidden = [], @@ -382,7 +384,7 @@ findHomePackageModule fc fopts home_unit mod_name = do InstalledFound loc _ -> Found loc (mkModule uid mod_name) InstalledNoPackage _ -> NoPackage uid -- impossible InstalledNotFound fps _ -> NotFound { - fr_paths = fps, + fr_paths = fmap unsafeDecodeUtf fps, fr_pkg = Just uid, fr_mods_hidden = [], fr_pkgs_hidden = [], @@ -418,17 +420,17 @@ findInstalledHomeModule fc fopts home_unit mod_name = do hi_dir_path = case finder_hiDir fopts of Just hiDir -> case maybe_working_dir of - Nothing -> [hiDir] - Just fp -> [fp hiDir] + Nothing -> [hiDir] + Just fp -> [fp hiDir] Nothing -> home_path hisuf = finder_hiSuf fopts mod = mkModule home_unit mod_name source_exts = - [ ("hs", mkHomeModLocationSearched fopts mod_name "hs") - , ("lhs", mkHomeModLocationSearched fopts mod_name "lhs") - , ("hsig", mkHomeModLocationSearched fopts mod_name "hsig") - , ("lhsig", mkHomeModLocationSearched fopts mod_name "lhsig") + [ (os "hs", mkHomeModLocationSearched fopts mod_name $ os "hs") + , (os "lhs", mkHomeModLocationSearched fopts mod_name $ os "lhs") + , (os "hsig", mkHomeModLocationSearched fopts mod_name $ os "hsig") + , (os "lhsig", mkHomeModLocationSearched fopts mod_name $ os "lhsig") ] -- we use mkHomeModHiOnlyLocation instead of mkHiOnlyModLocation so that @@ -453,10 +455,11 @@ findInstalledHomeModule fc fopts home_unit mod_name = do else searchPathExts search_dirs mod exts -- | Prepend the working directory to the search path. -augmentImports :: FilePath -> [FilePath] -> [FilePath] +augmentImports :: OsPath -> [OsPath] -> [OsPath] augmentImports _work_dir [] = [] -augmentImports work_dir (fp:fps) | isAbsolute fp = fp : augmentImports work_dir fps - | otherwise = (work_dir fp) : augmentImports work_dir fps +augmentImports work_dir (fp:fps) + | OsPath.isAbsolute fp = fp : augmentImports work_dir fps + | otherwise = (work_dir fp) : augmentImports work_dir fps -- | Search for a module in external packages only. findPackageModule :: FinderCache -> UnitState -> FinderOpts -> InstalledModule -> IO InstalledFindResult @@ -488,14 +491,14 @@ findPackageModule_ fc fopts mod pkg_conf = do tag = waysBuildTag (finder_ways fopts) -- hi-suffix for packages depends on the build tag. - package_hisuf | null tag = "hi" - | otherwise = tag ++ "_hi" + package_hisuf | null tag = os "hi" + | otherwise = os (tag ++ "_hi") - package_dynhisuf = waysBuildTag (addWay WayDyn (finder_ways fopts)) ++ "_hi" + package_dynhisuf = os $ waysBuildTag (addWay WayDyn (finder_ways fopts)) ++ "_hi" mk_hi_loc = mkHiOnlyModLocation fopts package_hisuf package_dynhisuf - import_dirs = map ST.unpack $ unitImportDirs pkg_conf + import_dirs = map (unsafeEncodeUtf . ST.unpack) $ unitImportDirs pkg_conf -- we never look for a .hi-boot file in an external package; -- .hi-boot files only make sense for the home package. in @@ -503,7 +506,7 @@ findPackageModule_ fc fopts mod pkg_conf = do [one] | finder_bypassHiFileCheck fopts -> -- there's only one place that this .hi file can be, so -- don't bother looking for it. - let basename = moduleNameSlashes (moduleName mod) + let basename = unsafeEncodeUtf $ moduleNameSlashes (moduleName mod) loc = mk_hi_loc one basename in return $ InstalledFound loc mod _otherwise -> @@ -512,24 +515,24 @@ findPackageModule_ fc fopts mod pkg_conf = do -- ----------------------------------------------------------------------------- -- General path searching -searchPathExts :: [FilePath] -- paths to search +searchPathExts :: [OsPath] -- paths to search -> InstalledModule -- module name -> [ ( - FileExt, -- suffix - FilePath -> BaseName -> ModLocation -- action + FileExt, -- suffix + OsPath -> BaseName -> ModLocation -- action ) ] -> IO InstalledFindResult searchPathExts paths mod exts = search to_search where - basename = moduleNameSlashes (moduleName mod) + basename = unsafeEncodeUtf $ moduleNameSlashes (moduleName mod) - to_search :: [(FilePath, ModLocation)] + to_search :: [(OsPath, ModLocation)] to_search = [ (file, fn path basename) | path <- paths, (ext,fn) <- exts, - let base | path == "." = basename + let base | path == os "." = basename | otherwise = path basename file = base <.> ext ] @@ -543,7 +546,7 @@ searchPathExts paths mod exts = search to_search else search rest mkHomeModLocationSearched :: FinderOpts -> ModuleName -> FileExt - -> FilePath -> BaseName -> ModLocation + -> OsPath -> BaseName -> ModLocation mkHomeModLocationSearched fopts mod suff path basename = mkHomeModLocation2 fopts mod (path basename) suff @@ -581,18 +584,18 @@ mkHomeModLocationSearched fopts mod suff path basename = -- ext -- The filename extension of the source file (usually "hs" or "lhs"). -mkHomeModLocation :: FinderOpts -> ModuleName -> FilePath -> ModLocation +mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> ModLocation mkHomeModLocation dflags mod src_filename = - let (basename,extension) = splitExtension src_filename + let (basename,extension) = OsPath.splitExtension src_filename in mkHomeModLocation2 dflags mod basename extension mkHomeModLocation2 :: FinderOpts -> ModuleName - -> FilePath -- Of source module, without suffix - -> String -- Suffix + -> OsPath -- Of source module, without suffix + -> FileExt -- Suffix -> ModLocation mkHomeModLocation2 fopts mod src_basename ext = - let mod_basename = moduleNameSlashes mod + let mod_basename = unsafeEncodeUtf $ moduleNameSlashes mod obj_fn = mkObjPath fopts src_basename mod_basename dyn_obj_fn = mkDynObjPath fopts src_basename mod_basename @@ -600,51 +603,51 @@ mkHomeModLocation2 fopts mod src_basename ext = dyn_hi_fn = mkDynHiPath fopts src_basename mod_basename hie_fn = mkHiePath fopts src_basename mod_basename - in (ModLocation{ ml_hs_file = Just (src_basename <.> ext), - ml_hi_file = hi_fn, - ml_dyn_hi_file = dyn_hi_fn, - ml_obj_file = obj_fn, - ml_dyn_obj_file = dyn_obj_fn, - ml_hie_file = hie_fn }) + in (OsPathModLocation{ ml_hs_file_ospath = Just (src_basename <.> ext), + ml_hi_file_ospath = hi_fn, + ml_dyn_hi_file_ospath = dyn_hi_fn, + ml_obj_file_ospath = obj_fn, + ml_dyn_obj_file_ospath = dyn_obj_fn, + ml_hie_file_ospath = hie_fn }) mkHomeModHiOnlyLocation :: FinderOpts -> ModuleName - -> FilePath + -> OsPath -> BaseName -> ModLocation mkHomeModHiOnlyLocation fopts mod path basename = - let loc = mkHomeModLocation2 fopts mod (path basename) "" - in loc { ml_hs_file = Nothing } + let loc = mkHomeModLocation2 fopts mod (path basename) mempty + in loc { ml_hs_file_ospath = Nothing } -- This function is used to make a ModLocation for a package module. Hence why -- we explicitly pass in the interface file suffixes. -mkHiOnlyModLocation :: FinderOpts -> Suffix -> Suffix -> FilePath -> String +mkHiOnlyModLocation :: FinderOpts -> FileExt -> FileExt -> OsPath -> OsPath -> ModLocation mkHiOnlyModLocation fopts hisuf dynhisuf path basename = let full_basename = path basename obj_fn = mkObjPath fopts full_basename basename dyn_obj_fn = mkDynObjPath fopts full_basename basename hie_fn = mkHiePath fopts full_basename basename - in ModLocation{ ml_hs_file = Nothing, - ml_hi_file = full_basename <.> hisuf, - -- Remove the .hi-boot suffix from - -- hi_file, if it had one. We always - -- want the name of the real .hi file - -- in the ml_hi_file field. - ml_dyn_obj_file = dyn_obj_fn, - -- MP: TODO - ml_dyn_hi_file = full_basename <.> dynhisuf, - ml_obj_file = obj_fn, - ml_hie_file = hie_fn + in OsPathModLocation{ ml_hs_file_ospath = Nothing, + ml_hi_file_ospath = full_basename <.> hisuf, + -- Remove the .hi-boot suffix from + -- hi_file, if it had one. We always + -- want the name of the real .hi file + -- in the ml_hi_file field. + ml_dyn_obj_file_ospath = dyn_obj_fn, + -- MP: TODO + ml_dyn_hi_file_ospath = full_basename <.> dynhisuf, + ml_obj_file_ospath = obj_fn, + ml_hie_file_ospath = hie_fn } -- | Constructs the filename of a .o file for a given source file. -- Does /not/ check whether the .o file exists mkObjPath :: FinderOpts - -> FilePath -- the filename of the source file, minus the extension - -> String -- the module name with dots replaced by slashes - -> FilePath + -> OsPath -- the filename of the source file, minus the extension + -> OsPath -- the module name with dots replaced by slashes + -> OsPath mkObjPath fopts basename mod_basename = obj_basename <.> osuf where odir = finder_objectDir fopts @@ -657,9 +660,9 @@ mkObjPath fopts basename mod_basename = obj_basename <.> osuf -- Does /not/ check whether the .dyn_o file exists mkDynObjPath :: FinderOpts - -> FilePath -- the filename of the source file, minus the extension - -> String -- the module name with dots replaced by slashes - -> FilePath + -> OsPath -- the filename of the source file, minus the extension + -> OsPath -- the module name with dots replaced by slashes + -> OsPath mkDynObjPath fopts basename mod_basename = obj_basename <.> dynosuf where odir = finder_objectDir fopts @@ -673,9 +676,9 @@ mkDynObjPath fopts basename mod_basename = obj_basename <.> dynosuf -- Does /not/ check whether the .hi file exists mkHiPath :: FinderOpts - -> FilePath -- the filename of the source file, minus the extension - -> String -- the module name with dots replaced by slashes - -> FilePath + -> OsPath -- the filename of the source file, minus the extension + -> OsPath -- the module name with dots replaced by slashes + -> OsPath mkHiPath fopts basename mod_basename = hi_basename <.> hisuf where hidir = finder_hiDir fopts @@ -688,9 +691,9 @@ mkHiPath fopts basename mod_basename = hi_basename <.> hisuf -- Does /not/ check whether the .dyn_hi file exists mkDynHiPath :: FinderOpts - -> FilePath -- the filename of the source file, minus the extension - -> String -- the module name with dots replaced by slashes - -> FilePath + -> OsPath -- the filename of the source file, minus the extension + -> OsPath -- the module name with dots replaced by slashes + -> OsPath mkDynHiPath fopts basename mod_basename = hi_basename <.> dynhisuf where hidir = finder_hiDir fopts @@ -703,9 +706,9 @@ mkDynHiPath fopts basename mod_basename = hi_basename <.> dynhisuf -- Does /not/ check whether the .hie file exists mkHiePath :: FinderOpts - -> FilePath -- the filename of the source file, minus the extension - -> String -- the module name with dots replaced by slashes - -> FilePath + -> OsPath -- the filename of the source file, minus the extension + -> OsPath -- the module name with dots replaced by slashes + -> OsPath mkHiePath fopts basename mod_basename = hie_basename <.> hiesuf where hiedir = finder_hieDir fopts @@ -726,23 +729,23 @@ mkStubPaths :: FinderOpts -> ModuleName -> ModLocation - -> FilePath + -> OsPath mkStubPaths fopts mod location = let stubdir = finder_stubDir fopts - mod_basename = moduleNameSlashes mod - src_basename = dropExtension $ expectJust "mkStubPaths" - (ml_hs_file location) + mod_basename = unsafeEncodeUtf $ moduleNameSlashes mod + src_basename = OsPath.dropExtension $ expectJust "mkStubPaths" + (ml_hs_file_ospath location) stub_basename0 | Just dir <- stubdir = dir mod_basename | otherwise = src_basename - stub_basename = stub_basename0 ++ "_stub" + stub_basename = stub_basename0 `mappend` os "_stub" in - stub_basename <.> "h" + stub_basename <.> os "h" -- ----------------------------------------------------------------------------- -- findLinkable isn't related to the other stuff in here, ===================================== compiler/GHC/Unit/Finder/Types.hs ===================================== @@ -9,6 +9,7 @@ where import GHC.Prelude import GHC.Unit +import GHC.Data.OsPath import qualified Data.Map as M import GHC.Fingerprint import GHC.Platform.Ways @@ -31,7 +32,7 @@ data FinderCache = FinderCache { fcModuleCache :: (IORef FinderCacheState) data InstalledFindResult = InstalledFound ModLocation InstalledModule | InstalledNoPackage UnitId - | InstalledNotFound [FilePath] (Maybe UnitId) + | InstalledNotFound [OsPath] (Maybe UnitId) -- | The result of searching for an imported module. -- @@ -70,7 +71,7 @@ data FindResult -- -- Should be taken from 'DynFlags' via 'initFinderOpts'. data FinderOpts = FinderOpts - { finder_importPaths :: [FilePath] + { finder_importPaths :: [OsPath] -- ^ Where are we allowed to look for Modules and Source files , finder_lookupHomeInterfaces :: Bool -- ^ When looking up a home module: @@ -88,17 +89,17 @@ data FinderOpts = FinderOpts , finder_enableSuggestions :: Bool -- ^ If we encounter unknown modules, should we suggest modules -- that have a similar name. - , finder_workingDirectory :: Maybe FilePath + , finder_workingDirectory :: Maybe OsPath , finder_thisPackageName :: Maybe FastString , finder_hiddenModules :: Set.Set ModuleName , finder_reexportedModules :: Set.Set ModuleName - , finder_hieDir :: Maybe FilePath - , finder_hieSuf :: String - , finder_hiDir :: Maybe FilePath - , finder_hiSuf :: String - , finder_dynHiSuf :: String - , finder_objectDir :: Maybe FilePath - , finder_objectSuf :: String - , finder_dynObjectSuf :: String - , finder_stubDir :: Maybe FilePath + , finder_hieDir :: Maybe OsPath + , finder_hieSuf :: OsString + , finder_hiDir :: Maybe OsPath + , finder_hiSuf :: OsString + , finder_dynHiSuf :: OsString + , finder_objectDir :: Maybe OsPath + , finder_objectSuf :: OsString + , finder_dynObjectSuf :: OsString + , finder_stubDir :: Maybe OsPath } deriving Show ===================================== compiler/GHC/Unit/Module/Location.hs ===================================== @@ -1,6 +1,17 @@ +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE ViewPatterns #-} -- | Module location module GHC.Unit.Module.Location - ( ModLocation(..) + ( ModLocation + ( .. + , ml_hs_file + , ml_hi_file + , ml_dyn_hi_file + , ml_obj_file + , ml_dyn_obj_file + , ml_hie_file + ) + , pattern ModLocation , addBootSuffix , addBootSuffix_maybe , addBootSuffixLocn_maybe @@ -11,15 +22,19 @@ module GHC.Unit.Module.Location where import GHC.Prelude + +import GHC.Data.OsPath import GHC.Unit.Types import GHC.Utils.Outputable +import qualified System.OsString as OsString + -- | Module Location -- -- Where a module lives on the file system: the actual locations -- of the .hs, .hi, .dyn_hi, .o, .dyn_o and .hie files, if we have them. -- --- For a module in another unit, the ml_hs_file and ml_obj_file components of +-- For a module in another unit, the ml_hs_file_ospath and ml_obj_file_ospath components of -- ModLocation are undefined. -- -- The locations specified by a ModLocation may or may not @@ -38,31 +53,31 @@ import GHC.Utils.Outputable -- boot suffixes in mkOneShotModLocation. data ModLocation - = ModLocation { - ml_hs_file :: Maybe FilePath, + = OsPathModLocation { + ml_hs_file_ospath :: Maybe OsPath, -- ^ The source file, if we have one. Package modules -- probably don't have source files. - ml_hi_file :: FilePath, + ml_hi_file_ospath :: OsPath, -- ^ Where the .hi file is, whether or not it exists -- yet. Always of form foo.hi, even if there is an -- hi-boot file (we add the -boot suffix later) - ml_dyn_hi_file :: FilePath, + ml_dyn_hi_file_ospath :: OsPath, -- ^ Where the .dyn_hi file is, whether or not it exists -- yet. - ml_obj_file :: FilePath, + ml_obj_file_ospath :: OsPath, -- ^ Where the .o file is, whether or not it exists yet. -- (might not exist either because the module hasn't -- been compiled yet, or because it is part of a -- unit with a .a file) - ml_dyn_obj_file :: FilePath, + ml_dyn_obj_file_ospath :: OsPath, -- ^ Where the .dy file is, whether or not it exists -- yet. - ml_hie_file :: FilePath + ml_hie_file_ospath :: OsPath -- ^ Where the .hie file is, whether or not it exists -- yet. } deriving Show @@ -71,18 +86,18 @@ instance Outputable ModLocation where ppr = text . show -- | Add the @-boot@ suffix to .hs, .hi and .o files -addBootSuffix :: FilePath -> FilePath -addBootSuffix path = path ++ "-boot" +addBootSuffix :: OsPath -> OsPath +addBootSuffix path = path `mappend` os "-boot" -- | Remove the @-boot@ suffix to .hs, .hi and .o files -removeBootSuffix :: FilePath -> FilePath -removeBootSuffix "-boot" = [] -removeBootSuffix (x:xs) = x : removeBootSuffix xs -removeBootSuffix [] = error "removeBootSuffix: no -boot suffix" - +removeBootSuffix :: OsPath -> OsPath +removeBootSuffix pathWithBootSuffix = + case OsString.stripSuffix (os "-boot") pathWithBootSuffix of + Just path -> path + Nothing -> error "removeBootSuffix: no -boot suffix" -- | Add the @-boot@ suffix if the @Bool@ argument is @True@ -addBootSuffix_maybe :: IsBootInterface -> FilePath -> FilePath +addBootSuffix_maybe :: IsBootInterface -> OsPath -> OsPath addBootSuffix_maybe is_boot path = case is_boot of IsBoot -> addBootSuffix path NotBoot -> path @@ -95,22 +110,50 @@ addBootSuffixLocn_maybe is_boot locn = case is_boot of -- | Add the @-boot@ suffix to all file paths associated with the module addBootSuffixLocn :: ModLocation -> ModLocation addBootSuffixLocn locn - = locn { ml_hs_file = fmap addBootSuffix (ml_hs_file locn) - , ml_hi_file = addBootSuffix (ml_hi_file locn) - , ml_dyn_hi_file = addBootSuffix (ml_dyn_hi_file locn) - , ml_obj_file = addBootSuffix (ml_obj_file locn) - , ml_dyn_obj_file = addBootSuffix (ml_dyn_obj_file locn) - , ml_hie_file = addBootSuffix (ml_hie_file locn) } + = locn { ml_hs_file_ospath = fmap addBootSuffix (ml_hs_file_ospath locn) + , ml_hi_file_ospath = addBootSuffix (ml_hi_file_ospath locn) + , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn) + , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn) + , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn) + , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn) } -- | Add the @-boot@ suffix to all output file paths associated with the -- module, not including the input file itself addBootSuffixLocnOut :: ModLocation -> ModLocation addBootSuffixLocnOut locn - = locn { ml_hi_file = addBootSuffix (ml_hi_file locn) - , ml_dyn_hi_file = addBootSuffix (ml_dyn_hi_file locn) - , ml_obj_file = addBootSuffix (ml_obj_file locn) - , ml_dyn_obj_file = addBootSuffix (ml_dyn_obj_file locn) - , ml_hie_file = addBootSuffix (ml_hie_file locn) + = locn { ml_hi_file_ospath = addBootSuffix (ml_hi_file_ospath locn) + , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn) + , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn) + , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn) + , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn) } - +-- ---------------------------------------------------------------------------- +-- Helpers for backwards compatibility +-- ---------------------------------------------------------------------------- + +pattern ModLocation :: Maybe FilePath -> FilePath -> FilePath -> FilePath -> FilePath -> FilePath -> ModLocation +pattern ModLocation + { ml_hs_file + , ml_hi_file + , ml_dyn_hi_file + , ml_obj_file + , ml_dyn_obj_file + , ml_hie_file + } <- OsPathModLocation + { ml_hs_file_ospath = (fmap unsafeDecodeUtf -> ml_hs_file) + , ml_hi_file_ospath = (unsafeDecodeUtf -> ml_hi_file) + , ml_dyn_hi_file_ospath = (unsafeDecodeUtf -> ml_dyn_hi_file) + , ml_obj_file_ospath = (unsafeDecodeUtf -> ml_obj_file) + , ml_dyn_obj_file_ospath = (unsafeDecodeUtf -> ml_dyn_obj_file) + , ml_hie_file_ospath = (unsafeDecodeUtf -> ml_hie_file) + } where + ModLocation ml_hs_file ml_hi_file ml_dyn_hi_file ml_obj_file ml_dyn_obj_file ml_hie_file + = OsPathModLocation + { ml_hs_file_ospath = fmap unsafeEncodeUtf ml_hs_file + , ml_hi_file_ospath = unsafeEncodeUtf ml_hi_file + , ml_dyn_hi_file_ospath = unsafeEncodeUtf ml_dyn_hi_file + , ml_obj_file_ospath = unsafeEncodeUtf ml_obj_file + , ml_dyn_obj_file_ospath = unsafeEncodeUtf ml_dyn_obj_file + , ml_hie_file_ospath = unsafeEncodeUtf ml_hie_file + } ===================================== compiler/GHC/Unit/Module/ModSummary.hs ===================================== @@ -17,6 +17,11 @@ module GHC.Unit.Module.ModSummary , msHsFilePath , msObjFilePath , msDynObjFilePath + , msHsFileOsPath + , msHiFileOsPath + , msDynHiFileOsPath + , msObjFileOsPath + , msDynObjFileOsPath , msDeps , isBootSummary , findTarget @@ -38,6 +43,7 @@ import GHC.Types.Target import GHC.Types.PkgQual import GHC.Data.Maybe +import GHC.Data.OsPath (OsPath) import GHC.Data.StringBuffer ( StringBuffer ) import GHC.Utils.Fingerprint @@ -146,6 +152,13 @@ msDynHiFilePath ms = ml_dyn_hi_file (ms_location ms) msObjFilePath ms = ml_obj_file (ms_location ms) msDynObjFilePath ms = ml_dyn_obj_file (ms_location ms) +msHsFileOsPath, msDynHiFileOsPath, msHiFileOsPath, msObjFileOsPath, msDynObjFileOsPath :: ModSummary -> OsPath +msHsFileOsPath ms = expectJust "msHsFilePath" (ml_hs_file_ospath (ms_location ms)) +msHiFileOsPath ms = ml_hi_file_ospath (ms_location ms) +msDynHiFileOsPath ms = ml_dyn_hi_file_ospath (ms_location ms) +msObjFileOsPath ms = ml_obj_file_ospath (ms_location ms) +msDynObjFileOsPath ms = ml_dyn_obj_file_ospath (ms_location ms) + -- | Did this 'ModSummary' originate from a hs-boot file? isBootSummary :: ModSummary -> IsBootInterface isBootSummary ms = if ms_hsc_src ms == HsBootFile then IsBoot else NotBoot ===================================== compiler/ghc.cabal.in ===================================== @@ -123,7 +123,8 @@ Library time >= 1.4 && < 1.15, containers >= 0.6.2.1 && < 0.8, array >= 0.1 && < 0.6, - filepath >= 1 && < 1.6, + filepath >= 1.5 && < 1.6, + os-string >= 2.0.1 && < 2.1, hpc >= 0.6 && < 0.8, transformers >= 0.5 && < 0.7, exceptions == 0.10.*, @@ -444,6 +445,7 @@ Library GHC.Data.List.SetOps GHC.Data.Maybe GHC.Data.OrdList + GHC.Data.OsPath GHC.Data.Pair GHC.Data.SmallArray GHC.Data.Stream ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -36,7 +36,7 @@ Executable ghc bytestring >= 0.9 && < 0.13, directory >= 1 && < 1.4, process >= 1 && < 1.7, - filepath >= 1 && < 1.6, + filepath >= 1.5 && < 1.6, containers >= 0.5 && < 0.8, transformers >= 0.5 && < 0.7, ghc-boot == @ProjectVersionMunged@, ===================================== testsuite/tests/count-deps/CountDepsAst.stdout ===================================== @@ -70,6 +70,7 @@ GHC.Data.List.Infinite GHC.Data.List.SetOps GHC.Data.Maybe GHC.Data.OrdList +GHC.Data.OsPath GHC.Data.Pair GHC.Data.SmallArray GHC.Data.Strict ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -71,6 +71,7 @@ GHC.Data.List.Infinite GHC.Data.List.SetOps GHC.Data.Maybe GHC.Data.OrdList +GHC.Data.OsPath GHC.Data.Pair GHC.Data.SmallArray GHC.Data.Strict ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Create.hs ===================================== @@ -93,10 +93,7 @@ createInterface1 flags unit_state mod_sum mod_iface ifaces inst_ifaces (instance -- pragmas in the modules source code. Used to infer -- safety of module. ms_hspp_opts - , ms_location = - ModLocation - { ml_hie_file - } + , ms_location = modl } = mod_sum dflags = ms_hspp_opts @@ -228,7 +225,7 @@ createInterface1 flags unit_state mod_sum mod_iface ifaces inst_ifaces (instance Interface { ifaceMod = mdl , ifaceIsSig = is_sig - , ifaceHieFile = ml_hie_file + , ifaceHieFile = ml_hie_file modl , ifaceInfo = info , ifaceDoc = Documentation header_doc mod_warning , ifaceRnDoc = Documentation Nothing Nothing View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b534a1a2b1106dd208ff62d30ec3df615d8b4997 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b534a1a2b1106dd208ff62d30ec3df615d8b4997 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 07:28:33 2024 From: gitlab at gitlab.haskell.org (=?UTF-8?B?SmFrb2IgQnLDvG5rZXIgKEBKYWtvYkJydWVua2VyKQ==?=) Date: Sat, 01 Jun 2024 03:28:33 -0400 Subject: [Git][ghc/ghc][wip/jakobbruenker/23515] Draft: Type/data instances: require that the instantiation is determined by the LHS alone (#23515) Message-ID: <665acda1eba45_1b2063343fa2811819a@gitlab.mail> Jakob Brünker pushed to branch wip/jakobbruenker/23515 at Glasgow Haskell Compiler / GHC Commits: 9fcccb87 by Jakob Bruenker at 2024-06-01T08:26:24+02:00 Draft: Type/data instances: require that the instantiation is determined by the LHS alone (#23515) Co-authored-by: Andrei Borzenkov <andreyborzenkov2002 at gmail.com> - - - - - 30 changed files: - compiler/GHC/Tc/TyCl.hs - libraries/ghc-internal/src/GHC/Internal/Data/Type/Equality.hs - testsuite/tests/dependent/should_compile/RaeJobTalk.hs - testsuite/tests/dependent/should_compile/T14991.hs - testsuite/tests/dependent/should_compile/T15666.hs - testsuite/tests/dependent/should_fail/T11471.hs - testsuite/tests/dependent/should_fail/T15380.hs - testsuite/tests/dependent/should_fail/T15380.stderr - testsuite/tests/ghci/scripts/T6018ghci.script - testsuite/tests/ghci/scripts/T6018ghcifail.script - testsuite/tests/ghci/scripts/T6018ghcifail.stderr - testsuite/tests/ghci/should_fail/T16013.script - testsuite/tests/impredicative/T18126-nasty.hs - testsuite/tests/indexed-types/should_compile/ExplicitForAllFams2.hs - testsuite/tests/indexed-types/should_compile/GADT1.hs - testsuite/tests/indexed-types/should_compile/GADT11.hs - testsuite/tests/indexed-types/should_compile/Numerals.hs - testsuite/tests/indexed-types/should_compile/T11715b.hs - testsuite/tests/indexed-types/should_compile/T12522.hs - testsuite/tests/indexed-types/should_compile/T13705.hs - testsuite/tests/indexed-types/should_compile/T17405a.hs - testsuite/tests/indexed-types/should_compile/T17923.hs - testsuite/tests/indexed-types/should_compile/T18065.hs - testsuite/tests/indexed-types/should_compile/T2219.hs - testsuite/tests/indexed-types/should_compile/T2627.hs - testsuite/tests/indexed-types/should_fail/T12041.hs - testsuite/tests/indexed-types/should_fail/T13971.hs - testsuite/tests/indexed-types/should_fail/T13971.stderr - testsuite/tests/indexed-types/should_fail/T14246.hs - testsuite/tests/indexed-types/should_fail/T14246.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9fcccb8710a8d089d996425954cca4da569d40e4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9fcccb8710a8d089d996425954cca4da569d40e4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 07:48:27 2024 From: gitlab at gitlab.haskell.org (=?UTF-8?B?SmFrb2IgQnLDvG5rZXIgKEBKYWtvYkJydWVua2VyKQ==?=) Date: Sat, 01 Jun 2024 03:48:27 -0400 Subject: [Git][ghc/ghc][wip/jakobbruenker/23515] Draft: Type/data instances: require that the instantiation is determined by the LHS alone (#23515) Message-ID: <665ad24b26405_1b206336b41a0118394@gitlab.mail> Jakob Brünker pushed to branch wip/jakobbruenker/23515 at Glasgow Haskell Compiler / GHC Commits: 362cc8ce by Jakob Bruenker at 2024-06-01T09:47:51+02:00 Draft: Type/data instances: require that the instantiation is determined by the LHS alone (#23515) Fixes #23515 Co-authored-by: Andrei Borzenkov <andreyborzenkov2002 at gmail.com> - - - - - 30 changed files: - compiler/GHC/Tc/TyCl.hs - libraries/ghc-internal/src/GHC/Internal/Data/Type/Equality.hs - testsuite/tests/dependent/should_compile/RaeJobTalk.hs - testsuite/tests/dependent/should_compile/T14991.hs - testsuite/tests/dependent/should_compile/T15666.hs - testsuite/tests/dependent/should_fail/T11471.hs - testsuite/tests/dependent/should_fail/T15380.hs - testsuite/tests/dependent/should_fail/T15380.stderr - testsuite/tests/ghci/scripts/T6018ghci.script - testsuite/tests/ghci/scripts/T6018ghcifail.script - testsuite/tests/ghci/scripts/T6018ghcifail.stderr - testsuite/tests/ghci/should_fail/T16013.script - testsuite/tests/impredicative/T18126-nasty.hs - testsuite/tests/indexed-types/should_compile/ExplicitForAllFams2.hs - testsuite/tests/indexed-types/should_compile/GADT1.hs - testsuite/tests/indexed-types/should_compile/GADT11.hs - testsuite/tests/indexed-types/should_compile/Numerals.hs - testsuite/tests/indexed-types/should_compile/T11715b.hs - testsuite/tests/indexed-types/should_compile/T12522.hs - testsuite/tests/indexed-types/should_compile/T13705.hs - testsuite/tests/indexed-types/should_compile/T17405a.hs - testsuite/tests/indexed-types/should_compile/T17923.hs - testsuite/tests/indexed-types/should_compile/T18065.hs - testsuite/tests/indexed-types/should_compile/T2219.hs - testsuite/tests/indexed-types/should_compile/T2627.hs - testsuite/tests/indexed-types/should_fail/T12041.hs - testsuite/tests/indexed-types/should_fail/T13971.hs - testsuite/tests/indexed-types/should_fail/T13971.stderr - testsuite/tests/indexed-types/should_fail/T14246.hs - testsuite/tests/indexed-types/should_fail/T14246.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/362cc8ce1f544e7d36b43f7bc7d639f1c4dc8c79 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/362cc8ce1f544e7d36b43f7bc7d639f1c4dc8c79 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 08:13:00 2024 From: gitlab at gitlab.haskell.org (=?UTF-8?B?SmFrb2IgQnLDvG5rZXIgKEBKYWtvYkJydWVua2VyKQ==?=) Date: Sat, 01 Jun 2024 04:13:00 -0400 Subject: [Git][ghc/ghc][wip/jakobbruenker/23515] Draft: Type/data instances: require that the instantiation is determined by the LHS alone (#23515) Message-ID: <665ad80c8ccd1_1e8aa4136208859f0@gitlab.mail> Jakob Brünker pushed to branch wip/jakobbruenker/23515 at Glasgow Haskell Compiler / GHC Commits: bd5d159c by Jakob Bruenker at 2024-06-01T10:12:37+02:00 Draft: Type/data instances: require that the instantiation is determined by the LHS alone (#23515) Fixes #23515 Co-authored-by: Andrei Borzenkov <andreyborzenkov2002 at gmail.com> - - - - - 30 changed files: - compiler/GHC/Tc/TyCl.hs - docs/users_guide/exts/type_families.rst - libraries/ghc-internal/src/GHC/Internal/Data/Type/Equality.hs - testsuite/tests/dependent/should_compile/RaeJobTalk.hs - testsuite/tests/dependent/should_compile/T14991.hs - testsuite/tests/dependent/should_compile/T15666.hs - testsuite/tests/dependent/should_fail/T11471.hs - testsuite/tests/dependent/should_fail/T15380.hs - testsuite/tests/dependent/should_fail/T15380.stderr - testsuite/tests/ghci/scripts/T6018ghci.script - testsuite/tests/ghci/scripts/T6018ghcifail.script - testsuite/tests/ghci/scripts/T6018ghcifail.stderr - testsuite/tests/ghci/should_fail/T16013.script - testsuite/tests/impredicative/T18126-nasty.hs - testsuite/tests/indexed-types/should_compile/ExplicitForAllFams2.hs - testsuite/tests/indexed-types/should_compile/GADT1.hs - testsuite/tests/indexed-types/should_compile/GADT11.hs - testsuite/tests/indexed-types/should_compile/Numerals.hs - testsuite/tests/indexed-types/should_compile/T11715b.hs - testsuite/tests/indexed-types/should_compile/T12522.hs - testsuite/tests/indexed-types/should_compile/T13705.hs - testsuite/tests/indexed-types/should_compile/T17405a.hs - testsuite/tests/indexed-types/should_compile/T17923.hs - testsuite/tests/indexed-types/should_compile/T18065.hs - testsuite/tests/indexed-types/should_compile/T2219.hs - testsuite/tests/indexed-types/should_compile/T2627.hs - testsuite/tests/indexed-types/should_fail/T12041.hs - testsuite/tests/indexed-types/should_fail/T13971.hs - testsuite/tests/indexed-types/should_fail/T13971.stderr - testsuite/tests/indexed-types/should_fail/T14246.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bd5d159c1f36a646f35a6854815afcd460c416ab -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bd5d159c1f36a646f35a6854815afcd460c416ab You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 08:34:21 2024 From: gitlab at gitlab.haskell.org (=?UTF-8?B?SmFrb2IgQnLDvG5rZXIgKEBKYWtvYkJydWVua2VyKQ==?=) Date: Sat, 01 Jun 2024 04:34:21 -0400 Subject: [Git][ghc/ghc][wip/jakobbruenker/23515] Draft: Type/data instances: require that the instantiation is determined by the LHS alone (#23515) Message-ID: <665add0da2899_1e8aa437bcc0861e1@gitlab.mail> Jakob Brünker pushed to branch wip/jakobbruenker/23515 at Glasgow Haskell Compiler / GHC Commits: 192d70d0 by Jakob Bruenker at 2024-06-01T10:33:58+02:00 Draft: Type/data instances: require that the instantiation is determined by the LHS alone (#23515) Fixes #23515 Co-authored-by: Andrei Borzenkov <andreyborzenkov2002 at gmail.com> - - - - - 30 changed files: - compiler/GHC/Tc/TyCl.hs - docs/users_guide/9.12.1-notes.rst - docs/users_guide/exts/type_families.rst - libraries/ghc-internal/src/GHC/Internal/Data/Type/Equality.hs - testsuite/tests/dependent/should_compile/RaeJobTalk.hs - testsuite/tests/dependent/should_compile/T14991.hs - testsuite/tests/dependent/should_compile/T15666.hs - testsuite/tests/dependent/should_fail/T11471.hs - testsuite/tests/dependent/should_fail/T15380.hs - testsuite/tests/dependent/should_fail/T15380.stderr - testsuite/tests/ghci/scripts/T6018ghci.script - testsuite/tests/ghci/scripts/T6018ghcifail.script - testsuite/tests/ghci/scripts/T6018ghcifail.stderr - testsuite/tests/ghci/should_fail/T16013.script - testsuite/tests/impredicative/T18126-nasty.hs - testsuite/tests/indexed-types/should_compile/ExplicitForAllFams2.hs - testsuite/tests/indexed-types/should_compile/GADT1.hs - testsuite/tests/indexed-types/should_compile/GADT11.hs - testsuite/tests/indexed-types/should_compile/Numerals.hs - testsuite/tests/indexed-types/should_compile/T11715b.hs - testsuite/tests/indexed-types/should_compile/T12522.hs - testsuite/tests/indexed-types/should_compile/T13705.hs - testsuite/tests/indexed-types/should_compile/T17405a.hs - testsuite/tests/indexed-types/should_compile/T17923.hs - testsuite/tests/indexed-types/should_compile/T18065.hs - testsuite/tests/indexed-types/should_compile/T2219.hs - testsuite/tests/indexed-types/should_compile/T2627.hs - testsuite/tests/indexed-types/should_fail/T12041.hs - testsuite/tests/indexed-types/should_fail/T13971.hs - testsuite/tests/indexed-types/should_fail/T13971.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/192d70d05bf5f390d5570d9d8cd7513e555dba64 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/192d70d05bf5f390d5570d9d8cd7513e555dba64 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 08:45:47 2024 From: gitlab at gitlab.haskell.org (=?UTF-8?B?SmFrb2IgQnLDvG5rZXIgKEBKYWtvYkJydWVua2VyKQ==?=) Date: Sat, 01 Jun 2024 04:45:47 -0400 Subject: [Git][ghc/ghc][wip/jakobbruenker/23515] 32 commits: template-haskell: Move wired-ins to ghc-internal Message-ID: <665adfbba9054_1e8aa45698d49004a@gitlab.mail> Jakob Brünker pushed to branch wip/jakobbruenker/23515 at Glasgow Haskell Compiler / GHC Commits: 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - 4d296dfa by Jakob Bruenker at 2024-06-01T10:44:49+02:00 Draft: Type/data instances: require that the instantiation is determined by the LHS alone (#23515) Fixes #23515 Co-authored-by: Andrei Borzenkov <andreyborzenkov2002 at gmail.com> - - - - - 30 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/Word64Set/Internal.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Ext/Types.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/JS/JStg/Syntax.hs - compiler/GHC/JS/Syntax.hs - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Plugins.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/192d70d05bf5f390d5570d9d8cd7513e555dba64...4d296dfa26e6a52f80768484a0dab9b59340c3d0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/192d70d05bf5f390d5570d9d8cd7513e555dba64...4d296dfa26e6a52f80768484a0dab9b59340c3d0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 08:56:55 2024 From: gitlab at gitlab.haskell.org (=?UTF-8?B?SmFrb2IgQnLDvG5rZXIgKEBKYWtvYkJydWVua2VyKQ==?=) Date: Sat, 01 Jun 2024 04:56:55 -0400 Subject: [Git][ghc/ghc][wip/jakobbruenker/23515] Type/data instances: require that the instantiation is determined by the LHS alone (#23515) Message-ID: <665ae25715d14_1e8aa474f8ec919f9@gitlab.mail> Jakob Brünker pushed to branch wip/jakobbruenker/23515 at Glasgow Haskell Compiler / GHC Commits: 7104d463 by Jakob Bruenker at 2024-06-01T10:55:53+02:00 Type/data instances: require that the instantiation is determined by the LHS alone (#23515) Fixes #23515 Co-authored-by: Andrei Borzenkov <andreyborzenkov2002 at gmail.com> - - - - - 30 changed files: - compiler/GHC/Tc/TyCl.hs - docs/users_guide/9.12.1-notes.rst - docs/users_guide/exts/type_families.rst - libraries/ghc-internal/src/GHC/Internal/Data/Type/Equality.hs - testsuite/tests/dependent/should_compile/RaeJobTalk.hs - testsuite/tests/dependent/should_compile/T14991.hs - testsuite/tests/dependent/should_compile/T15666.hs - testsuite/tests/dependent/should_fail/T11471.hs - testsuite/tests/dependent/should_fail/T15380.hs - testsuite/tests/dependent/should_fail/T15380.stderr - testsuite/tests/ghci/scripts/T6018ghci.script - testsuite/tests/ghci/scripts/T6018ghcifail.script - testsuite/tests/ghci/scripts/T6018ghcifail.stderr - testsuite/tests/ghci/should_fail/T16013.script - testsuite/tests/impredicative/T18126-nasty.hs - testsuite/tests/indexed-types/should_compile/ExplicitForAllFams2.hs - testsuite/tests/indexed-types/should_compile/GADT1.hs - testsuite/tests/indexed-types/should_compile/GADT11.hs - testsuite/tests/indexed-types/should_compile/Numerals.hs - testsuite/tests/indexed-types/should_compile/T11715b.hs - testsuite/tests/indexed-types/should_compile/T12522.hs - testsuite/tests/indexed-types/should_compile/T13705.hs - testsuite/tests/indexed-types/should_compile/T17405a.hs - testsuite/tests/indexed-types/should_compile/T17923.hs - testsuite/tests/indexed-types/should_compile/T18065.hs - testsuite/tests/indexed-types/should_compile/T2219.hs - testsuite/tests/indexed-types/should_compile/T2627.hs - testsuite/tests/indexed-types/should_fail/T12041.hs - testsuite/tests/indexed-types/should_fail/T13971.hs - testsuite/tests/indexed-types/should_fail/T13971.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7104d463feeccb93db73e26a14413c28d78758c6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7104d463feeccb93db73e26a14413c28d78758c6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 13:36:27 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 01 Jun 2024 09:36:27 -0400 Subject: [Git][ghc/ghc][master] 2 commits: Bump max LLVM version to 19 (not inclusive) Message-ID: <665b23db49b5e_1e8aa4282f65c11579e@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - 2 changed files: - .gitlab-ci.yml - configure.ac Changes: ===================================== .gitlab-ci.yml ===================================== @@ -2,7 +2,7 @@ variables: GIT_SSL_NO_VERIFY: "1" # Commit of ghc/ci-images repository from which to pull Docker images - DOCKER_REV: dbbc0f6f5b73930ead052ca8161e969f1755eed7 + DOCKER_REV: 2e2497036a91104be281a0eb24b37889aaf98341 # Sequential version number of all cached things. # Bump to invalidate GitLab CI cache. ===================================== configure.ac ===================================== @@ -499,7 +499,7 @@ AC_SUBST(InstallNameToolCmd) # versions of LLVM simultaneously, but that stopped working around # 3.5/3.6 release of LLVM. LlvmMinVersion=13 # inclusive -LlvmMaxVersion=16 # not inclusive +LlvmMaxVersion=19 # not inclusive AC_SUBST([LlvmMinVersion]) AC_SUBST([LlvmMaxVersion]) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e0aa42b9eacd6c8ee4f25737306808abcbbea640...92aa65eab4111dc082e7b1c107f2727890dd60c1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e0aa42b9eacd6c8ee4f25737306808abcbbea640...92aa65eab4111dc082e7b1c107f2727890dd60c1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 13:37:06 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 01 Jun 2024 09:37:06 -0400 Subject: [Git][ghc/ghc][master] Unicode: make ucd2haskell build-able again Message-ID: <665b2401f154a_1e8aa429afc341190c8@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - 4 changed files: - libraries/ghc-internal/tools/ucd2haskell/README.md - libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs - libraries/ghc-internal/tools/ucd2haskell/ucd.sh - libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal Changes: ===================================== libraries/ghc-internal/tools/ucd2haskell/README.md ===================================== @@ -1,6 +1,6 @@ # Generating GHC’s Unicode modules -`GHC.Unicode.Internal.*` modules are generated with the internal tool `ucd2haskell`. +`GHC.Internal.Unicode.*` modules are generated with the internal tool `ucd2haskell`. ```bash cd ucd2haskell @@ -13,7 +13,7 @@ cd ucd2haskell 2. _Comment_ the line in `ucd.sh` with `VERIFY_CHECKSUM=y`. 3. Run `./ucd.sh download`. 4. Update the checksums in `ucd.sh` and _uncomment_ `VERIFY_CHECKSUM=y`. -5. Run `./ucd.sh generate`. This will generate the `GHC.Unicode.Internal.*` +5. Run `./ucd.sh generate`. This will generate the `GHC.Internal.Unicode.*` modules. 6. Check and update the output of the tests `base/tests/unicodeXXX.hs`. 7. Compare with Python (see hereinafter) and fix any error. @@ -32,7 +32,7 @@ __Warning:__ A Python version with the _exact same Unicode version_ is required. Check the properties of all the characters. ```bash -ghc -O2 tests/export_all_chars.hs +ghc -O2 tests/export_all_chars.hs ./tests/export_all_chars > tests/all_chars.csv python3 tests/check_all_chars.py tests/all_chars.csv ``` ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs ===================================== @@ -21,7 +21,6 @@ module Parser.Text (genModules) where import Control.Exception (catch, IOException) import Control.Monad (void) -import Control.Monad.IO.Class (MonadIO(liftIO)) import Data.Bits (Bits(..)) import Data.Word (Word8) import Data.Char (chr, ord, isSpace) @@ -31,19 +30,20 @@ import Data.List (intersperse, unfoldr) import Data.List.Split (splitWhen) import Numeric (showHex) import Streamly.Data.Fold (Fold) -import Streamly.Prelude (IsStream, SerialT) import System.Directory (createDirectoryIfMissing) import System.Environment (getEnv) import System.FilePath ((), (<.>)) -- import qualified Data.Set as Set -import qualified Streamly.Prelude as Stream +import Streamly.Data.Stream (Stream) +import qualified Streamly.Data.Stream.Prelude as Stream import qualified Streamly.Data.Fold as Fold import qualified Streamly.Internal.Data.Fold as Fold import qualified Streamly.Data.Unfold as Unfold import qualified Streamly.FileSystem.Handle as Handle -import qualified System.IO as Sys import qualified Streamly.Unicode.Stream as Unicode +import qualified Streamly.Internal.Unicode.Stream as Unicode +import qualified System.IO as Sys import Prelude hiding (pred) @@ -271,7 +271,7 @@ genUnicodeVersion outdir = do (\(_ :: IOException) -> return "") Stream.fold f (Stream.fromList (body version)) where - moduleName = "GHC.Unicode.Internal.Version" + moduleName = "GHC.Internal.Unicode.Version" f = moduleFileEmitter Nothing outdir (moduleName, \_ -> Fold.foldMap (<> "\n")) body :: String -> [String] @@ -284,12 +284,12 @@ genUnicodeVersion outdir = do , "(unicodeVersion)" , "where" , "" - , "import {-# SOURCE #-} Data.Version" + , "import {-# SOURCE #-} GHC.Internal.Data.Version" , "" , "-- | Version of Unicode standard used by @base@:" , "-- [" <> version <> "](https://www.unicode.org/versions/Unicode" <> version <> "/)." , "--" - , "-- @since 4.15.0.0" + , "-- @since base-4.15.0.0" , "unicodeVersion :: Version" , "unicodeVersion = makeVersion [" <> mkVersion version <> "]" ] mkVersion = foldr (\c acc -> case c of {'.' -> ',':' ':acc; _ -> c:acc}) mempty @@ -331,8 +331,8 @@ genGeneralCategoryModule moduleName = , "(generalCategory)" , "where" , "" - , "import GHC.Base (Char, Int, Ord(..), ord)" - , "import GHC.Unicode.Internal.Bits (lookupIntN)" + , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" + , "import GHC.Internal.Unicode.Bits (lookupIntN)" , "" , genEnumBitmap "generalCategory" Cn (reverse acc) ] @@ -415,7 +415,7 @@ genDecomposableModule moduleName dtype = , "where" , "" , "import Data.Char (ord)" - , "import GHC.Unicode.Internal.Bits (lookupBit64)" + , "import GHC.Internal.Unicode.Bits (lookupBit64)" , "" , genBitmap "isDecomposable" (reverse st) ] @@ -443,7 +443,7 @@ genCombiningClassModule moduleName = , "where" , "" , "import Data.Char (ord)" - , "import GHC.Unicode.Internal.Bits (lookupBit64)" + , "import GHC.Internal.Unicode.Bits (lookupBit64)" , "" , "combiningClass :: Char -> Int" , unlines (reverse st1) @@ -566,8 +566,8 @@ genCompositionsModule moduleName compExclu non0CC = , "(compose, composeStarters, isSecondStarter)" , "where" , "" - , "import GHC.Base (Char, ord)" - , "import GHC.Unicode.Internal.Bits (lookupBit64)" + , "import GHC.Internal.Base (Char, ord)" + , "import GHC.Internal.Unicode.Bits (lookupBit64)" , "" ] @@ -616,7 +616,7 @@ genSimpleCaseMappingModule moduleName funcName field = , "(" <> funcName <> ")" , "where" , "" - , "import GHC.Base (Char)" + , "import GHC.Internal.Base (Char)" , "" ] genSign = @@ -670,8 +670,8 @@ genCorePropertiesModule moduleName isProp = , "(" <> unwords (intersperse "," (map prop2FuncName exports)) <> ")" , "where" , "" - , "import GHC.Base (Bool, Char, Ord(..), (&&), ord)" - , "import GHC.Unicode.Internal.Bits (lookupBit64)" + , "import GHC.Internal.Base (Bool, Char, Ord(..), (&&), ord)" + , "import GHC.Internal.Unicode.Bits (lookupBit64)" , "" ] @@ -818,7 +818,7 @@ parsePropertyLine ln isDivider :: String -> Bool isDivider x = x == "# ================================================" -parsePropertyLines :: (IsStream t, Monad m) => t m String -> t m PropertyLine +parsePropertyLines :: (Monad m) => Stream m String -> Stream m PropertyLine parsePropertyLines = Stream.splitOn isDivider $ Fold.lmap parsePropertyLine @@ -843,11 +843,11 @@ Parse ranges according to https://www.unicode.org/reports/tr44/#Code_Point_Range __Note:__ this does /not/ fill missing char entries, i.e. entries with no explicit entry nor within a range. -} -parseUnicodeDataLines :: forall t m. (IsStream t, Monad m) => t m String -> t m DetailedChar +parseUnicodeDataLines :: forall m. (Monad m) => Stream m String -> Stream m DetailedChar parseUnicodeDataLines = Stream.unfoldMany (Unfold.unfoldr unitToRange) . Stream.foldMany ( Fold.lmap parseDetailedChar - $ Fold.mkFold_ step initial ) + $ Fold.foldt' step initial id) where @@ -913,19 +913,14 @@ parseDetailedChar line = case splitWhen (== ';') line of -- Generation ------------------------------------------------------------------------------- -readLinesFromFile :: String -> SerialT IO String +readLinesFromFile :: String -> Stream IO String readLinesFromFile file = withFile file Sys.ReadMode - $ \h -> - Stream.unfold Handle.read h & Unicode.decodeUtf8 - & unicodeLines Fold.toList + $ \h -> Handle.read h & Unicode.decodeUtf8 & Unicode.lines Fold.toList where - - unicodeLines = Stream.splitOnSuffix (== '\n') - withFile file_ mode = - Stream.bracket (liftIO $ Sys.openFile file_ mode) (liftIO . Sys.hClose) + Stream.bracketIO (Sys.openFile file_ mode) (Sys.hClose) moduleToFileName :: String -> String @@ -995,7 +990,7 @@ testOutputFileEmitter outdir (name, fldGen) = Fold.rmapM action fldGen runGenerator :: FilePath -> FilePath - -> (SerialT IO String -> SerialT IO a) + -> (Stream IO String -> Stream IO a) -> FilePath -> GeneratorRecipe a -> IO () @@ -1067,64 +1062,64 @@ genModules indir outdir props = do -- [NOTE] Disabled generator -- propList = - -- ("GHC.Unicode.Internal.Char.PropList" + -- ("GHC.Internal.Unicode.Char.PropList" -- , (`genCorePropertiesModule` (`elem` props))) derivedCoreProperties = - ("GHC.Unicode.Internal.Char.DerivedCoreProperties" + ("GHC.Internal.Unicode.Char.DerivedCoreProperties" , (`genCorePropertiesModule` (`elem` props))) -- [NOTE] Disabled generator -- compositions exc non0 = - -- ( "GHC.Unicode.Internal.Char.UnicodeData.Compositions" + -- ( "GHC.Internal.Unicode.Char.UnicodeData.Compositions" -- , \m -> genCompositionsModule m exc non0) -- [NOTE] Disabled generator -- combiningClass = - -- ( "GHC.Unicode.Internal.Char.UnicodeData.CombiningClass" + -- ( "GHC.Internal.Unicode.Char.UnicodeData.CombiningClass" -- , genCombiningClassModule) -- [NOTE] Disabled generator -- decomposable = - -- ( "GHC.Unicode.Internal.Char.UnicodeData.Decomposable" + -- ( "GHC.Internal.Unicode.Char.UnicodeData.Decomposable" -- , (`genDecomposableModule` Canonical)) -- [NOTE] Disabled generator -- decomposableK = - -- ( "GHC.Unicode.Internal.Char.UnicodeData.DecomposableK" + -- ( "GHC.Internal.Unicode.Char.UnicodeData.DecomposableK" -- , (`genDecomposableModule` Kompat)) -- [NOTE] Disabled generator -- decompositions = - -- ( "GHC.Unicode.Internal.Char.UnicodeData.Decompositions" + -- ( "GHC.Internal.Unicode.Char.UnicodeData.Decompositions" -- , \m -> genDecomposeDefModule m [] [] Canonical (const True)) -- [NOTE] Disabled generator -- decompositionsK2 = - -- ( "GHC.Unicode.Internal.Char.UnicodeData.DecompositionsK2" + -- ( "GHC.Internal.Unicode.Char.UnicodeData.DecompositionsK2" -- , \m -> genDecomposeDefModule m [] [] Kompat (>= 60000)) -- [NOTE] Disabled generator -- decompositionsK = -- let pre = ["import qualified " <> fst decompositionsK2 <> " as DK2", ""] -- post = ["decompose c = DK2.decompose c"] - -- in ( "GHC.Unicode.Internal.Char.UnicodeData.DecompositionsK" + -- in ( "GHC.Internal.Unicode.Char.UnicodeData.DecompositionsK" -- , \m -> genDecomposeDefModule m pre post Kompat (< 60000)) generalCategory = - ( "GHC.Unicode.Internal.Char.UnicodeData.GeneralCategory" + ( "GHC.Internal.Unicode.Char.UnicodeData.GeneralCategory" , genGeneralCategoryModule) simpleUpperCaseMapping = - ( "GHC.Unicode.Internal.Char.UnicodeData.SimpleUpperCaseMapping" + ( "GHC.Internal.Unicode.Char.UnicodeData.SimpleUpperCaseMapping" , \m -> genSimpleCaseMappingModule m "toSimpleUpperCase" _simpleUppercaseMapping) simpleLowerCaseMapping = - ( "GHC.Unicode.Internal.Char.UnicodeData.SimpleLowerCaseMapping" + ( "GHC.Internal.Unicode.Char.UnicodeData.SimpleLowerCaseMapping" , \m -> genSimpleCaseMappingModule m "toSimpleLowerCase" _simpleLowercaseMapping) simpleTitleCaseMapping = - ( "GHC.Unicode.Internal.Char.UnicodeData.SimpleTitleCaseMapping" + ( "GHC.Internal.Unicode.Char.UnicodeData.SimpleTitleCaseMapping" , \m -> genSimpleCaseMappingModule m "toSimpleTitleCase" _simpleTitlecaseMapping) -- unicode002Test = ===================================== libraries/ghc-internal/tools/ucd2haskell/ucd.sh ===================================== @@ -52,7 +52,7 @@ download_files() { done } -GHC_MODULE_PATH=$(realpath "$SCRIPT_DIR/../../") +GHC_MODULE_PATH=$(realpath "$SCRIPT_DIR/../../src") # Generate the Haskell files. run_generator() { @@ -63,7 +63,7 @@ run_generator() { --core-prop Uppercase \ --core-prop Lowercase # [NOTE] disabled generator - # --core-prop Alphabetic + # --core-prop Alphabetic # --core-prop White_Space \ # --core-prop ID_Start \ # --core-prop ID_Continue \ ===================================== libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal ===================================== @@ -52,10 +52,11 @@ executable ucd2haskell main-is: UCD2Haskell.hs other-modules: Parser.Text build-depends: - base >= 4.7 && < 4.18 - , streamly >= 0.8 && < 0.9 + base >= 4.7 && < 4.20 + , streamly-core >= 0.2.2 && < 0.3 + , streamly >= 0.10 && < 0.11 , split >= 0.2.3 && < 0.3 , getopt-generics >= 0.13 && < 0.14 , containers >= 0.5 && < 0.7 - , directory >= 1.3.6 && < 1.3.7 + , directory >= 1.3.6 && < 1.3.8 , filepath >= 1.4.2 && < 1.5 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/adb1fe42c00ceeddf6a4412550d8e34ac1b49ce9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/adb1fe42c00ceeddf6a4412550d8e34ac1b49ce9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 13:37:39 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 01 Jun 2024 09:37:39 -0400 Subject: [Git][ghc/ghc][master] Replace 'NB' with 'Note' in error messages Message-ID: <665b24232ba40_1e8aa429afc341221f1@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 30 changed files: - compiler/GHC/Tc/Errors/Ppr.hs - testsuite/tests/backpack/should_fail/bkpfail24.stderr - testsuite/tests/backpack/should_fail/bkpfail49.stderr - testsuite/tests/dependent/should_fail/BadTelescope4.stderr - testsuite/tests/dependent/should_fail/T14066g.stderr - testsuite/tests/dependent/should_fail/T15591b.stderr - testsuite/tests/dependent/should_fail/T15591c.stderr - testsuite/tests/dependent/should_fail/T15743c.stderr - testsuite/tests/dependent/should_fail/T15743d.stderr - testsuite/tests/deriving/should_fail/T1496.stderr - testsuite/tests/deriving/should_fail/T5498.stderr - testsuite/tests/deriving/should_fail/T8984.stderr - testsuite/tests/ghci/scripts/T2452.stderr - testsuite/tests/ghci/scripts/T8639.stderr - testsuite/tests/ghci/scripts/T8649.stderr - testsuite/tests/ghci/scripts/ghci036.stderr - testsuite/tests/ghci/scripts/ghci051.stderr - testsuite/tests/ghci/scripts/ghci052.stderr - testsuite/tests/ghci/scripts/ghci053.stderr - testsuite/tests/indexed-types/should_compile/T3208b.stderr - testsuite/tests/indexed-types/should_fail/NoMatchErr.stderr - testsuite/tests/indexed-types/should_fail/T14887.stderr - testsuite/tests/indexed-types/should_fail/T15764.stderr - testsuite/tests/indexed-types/should_fail/T1897b.stderr - testsuite/tests/indexed-types/should_fail/T1900.stderr - testsuite/tests/indexed-types/should_fail/T2544.stderr - testsuite/tests/indexed-types/should_fail/T4099.stderr - testsuite/tests/indexed-types/should_fail/T4179.stderr - testsuite/tests/indexed-types/should_fail/T9036.stderr - testsuite/tests/indexed-types/should_fail/T9171.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ad56fd846a829f0ae287defc37b84265f3d4af39 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ad56fd846a829f0ae287defc37b84265f3d4af39 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 13:38:17 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 01 Jun 2024 09:38:17 -0400 Subject: [Git][ghc/ghc][master] compiler: fix -ddump-cmm-raw when compiling .cmm Message-ID: <665b2449516ef_1e8aa42ccdfd8125468@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1 changed file: - compiler/GHC/Driver/Main.hs Changes: ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -2092,10 +2092,15 @@ hscCompileCmmFile hsc_env original_filename filename output_filename = runHsc hs putDumpFileMaybe logger Opt_D_dump_cmm "Output Cmm" FormatCMM (pdoc platform cmmgroup) - rawCmms <- case cmmToRawCmmHook hooks of + rawCmms0 <- case cmmToRawCmmHook hooks of Nothing -> cmmToRawCmm logger profile (Stream.yield cmmgroup) Just h -> h dflags Nothing (Stream.yield cmmgroup) + let dump a = do + unless (null a) $ putDumpFileMaybe logger Opt_D_dump_cmm_raw "Raw Cmm" FormatCMM (pdoc platform a) + return a + rawCmms = Stream.mapM dump rawCmms0 + let foreign_stubs _ | not $ null ipe_ents = let ip_init = ipInitCode do_info_table platform cmm_mod View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6346c669215c797abb977cf875da4e4238f5d064 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6346c669215c797abb977cf875da4e4238f5d064 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 13:38:54 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 01 Jun 2024 09:38:54 -0400 Subject: [Git][ghc/ghc][master] Print namespace specifiers in FixitySig's Outputable instance Message-ID: <665b246eb0491_1e8aa42d2f760128455@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - 5 changed files: - compiler/GHC/Hs/Binds.hs - testsuite/tests/rename/should_fail/T14032c.stderr - + testsuite/tests/th/T24911.hs - + testsuite/tests/th/T24911.stderr - testsuite/tests/th/all.T Changes: ===================================== compiler/GHC/Hs/Binds.hs ===================================== @@ -898,8 +898,13 @@ extractSpecPragName srcTxt = case (words $ show srcTxt) of instance OutputableBndrId p => Outputable (FixitySig (GhcPass p)) where - ppr (FixitySig _ names fixity) = sep [ppr fixity, pprops] + ppr (FixitySig ns_spec names fixity) = sep [ppr fixity, ppr_ns_spec, pprops] where + ppr_ns_spec = + case ghcPass @p of + GhcPs -> ppr ns_spec + GhcRn -> ppr ns_spec + GhcTc -> empty pprops = hsep $ punctuate comma (map (pprInfixOcc . unLoc) names) pragBrackets :: SDoc -> SDoc ===================================== testsuite/tests/rename/should_fail/T14032c.stderr ===================================== @@ -1,14 +1,14 @@ - T14032c.hs:1:1: error: [GHC-78534] Illegal use of the ‘type’ keyword: - infix 0 $ + infix 0 type $ in a fixity signature Suggested fix: Perhaps you intended to use the ‘ExplicitNamespaces’ extension (implied by ‘TypeFamilies’ and ‘TypeOperators’) T14032c.hs:1:1: error: [GHC-78534] Illegal use of the ‘data’ keyword: - infix 0 $ + infix 0 data $ in a fixity signature Suggested fix: Perhaps you intended to use the ‘ExplicitNamespaces’ extension (implied by ‘TypeFamilies’ and ‘TypeOperators’) + ===================================== testsuite/tests/th/T24911.hs ===================================== @@ -0,0 +1,12 @@ +{-# LANGUAGE ExplicitNamespaces #-} +{-# LANGUAGE TemplateHaskell #-} +module T24911 where + +$([d| infixl 4 data ### + (###) :: a -> a -> a + x ### y = x + + infixl 4 type ### + type (###) :: a -> a -> a + type x ### y = x + |]) ===================================== testsuite/tests/th/T24911.stderr ===================================== @@ -0,0 +1,17 @@ +T24911.hs:(5,2)-(12,7): Splicing declarations + [d| infixl 4 type ### + infixl 4 data ### + + (###) :: a -> a -> a + x ### y = x + + type (###) :: a -> a -> a + + type x ### y = x |] + ======> + infixl 4 data ### + (###) :: a -> a -> a + (###) x y = x + infixl 4 type ### + type (###) :: a -> a -> a + type (###) x y = x ===================================== testsuite/tests/th/all.T ===================================== @@ -615,3 +615,4 @@ test('T24557e', normal, compile, ['']) test('T24702a', normal, compile, ['']) test('T24702b', normal, compile, ['']) test('T24837', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques']) +test('T24911', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1c834ad41ff59713c421d95cd385aafd0e7416e5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1c834ad41ff59713c421d95cd385aafd0e7416e5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 13:39:19 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 01 Jun 2024 09:39:19 -0400 Subject: [Git][ghc/ghc][master] Configure: display C++ compiler path Message-ID: <665b2487a867a_1e8aa42f21bf413013b@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - 1 changed file: - configure.ac Changes: ===================================== configure.ac ===================================== @@ -1009,6 +1009,7 @@ echo "\ cmmcpp : $CmmCPPCmd cmmcpp-flags : $CmmCPPArgs cmmcpp-g0 : $CmmCPPSupportsG0 + c++ : $CXX ar : $ArCmd nm : $NmCmd objdump : $ObjdumpCmd View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cf49fb5f8c20ae97cca08a468f690503b517a4ef -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cf49fb5f8c20ae97cca08a468f690503b517a4ef You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 14:09:46 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 01 Jun 2024 10:09:46 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 12 commits: Bump max LLVM version to 19 (not inclusive) Message-ID: <665b2baa594e_3cfbe21cc488862a5@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - 0417901c by Fendor at 2024-06-01T10:09:36-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 562d2f31 by Fendor at 2024-06-01T10:09:36-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12234 T12425 T13035 T13701 T13719 T14697 T15703 T16875 T18730 T9198 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. - - - - - 2dea08ef by Cheng Shao at 2024-06-01T10:09:37-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - a91b56d8 by Cheng Shao at 2024-06-01T10:09:37-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 60d9a8f0 by Cheng Shao at 2024-06-01T10:09:37-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - configure.ac - hadrian/src/Settings/Builders/Configure.hs - libraries/ghc-internal/tools/ucd2haskell/README.md - libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs - libraries/ghc-internal/tools/ucd2haskell/ucd.sh - libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal - testsuite/tests/backpack/should_fail/bkpfail24.stderr - testsuite/tests/backpack/should_fail/bkpfail49.stderr - testsuite/tests/dependent/should_fail/BadTelescope4.stderr - testsuite/tests/dependent/should_fail/T14066g.stderr - testsuite/tests/dependent/should_fail/T15591b.stderr - testsuite/tests/dependent/should_fail/T15591c.stderr - testsuite/tests/dependent/should_fail/T15743c.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0307d3d53fd2454e76f75171af95121652dee6f3...60d9a8f0d8ef2de618ee37c8f140b8336af1ed50 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0307d3d53fd2454e76f75171af95121652dee6f3...60d9a8f0d8ef2de618ee37c8f140b8336af1ed50 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 14:44:20 2024 From: gitlab at gitlab.haskell.org (Ryan Scott (@RyanGlScott)) Date: Sat, 01 Jun 2024 10:44:20 -0400 Subject: [Git][ghc/ghc][wip/T24894] 39 commits: template-haskell: Move wired-ins to ghc-internal Message-ID: <665b33c48fd37_3cfbe2630d449476a@gitlab.mail> Ryan Scott pushed to branch wip/T24894 at Glasgow Haskell Compiler / GHC Commits: 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - a3a5485f by Ryan Scott at 2024-06-01T10:44:07-04:00 Add missing gParPat in cvtp's ViewP case When converting a `ViewP` using `cvtp`, we need to ensure that the view pattern is parenthesized so that the resulting code will parse correctly when roundtripped back through GHC's parser. Fixes #24894. - - - - - 30 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/Word64Set/Internal.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/HsToCore/Foreign/Call.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Ext/Types.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/JS/JStg/Syntax.hs - compiler/GHC/JS/Syntax.hs - compiler/GHC/Parser/Annotation.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1ffcb93b0214dab7d6f2a6a4954ea33de630aa0f...a3a5485f49736cf404e1354ea0529b0a52b7280e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1ffcb93b0214dab7d6f2a6a4954ea33de630aa0f...a3a5485f49736cf404e1354ea0529b0a52b7280e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 1 20:20:51 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 01 Jun 2024 16:20:51 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Improve sharing of duplicated values in `ModIface`, fixes #24723 Message-ID: <665b82a35fe9e_26e5f73c8dcc748@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: bd7595f6 by Fendor at 2024-06-01T16:20:03-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - e6dabe43 by Fendor at 2024-06-01T16:20:03-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12234 T12425 T13035 T13701 T13719 T14697 T15703 T16875 T18730 T9198 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. - - - - - e73ba28d by Cheng Shao at 2024-06-01T16:20:04-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 5b86d51d by Cheng Shao at 2024-06-01T16:20:04-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 534c8955 by Cheng Shao at 2024-06-01T16:20:04-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 16 changed files: - compiler/GHC.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - hadrian/src/Settings/Builders/Configure.hs - testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -3,6 +3,7 @@ {-# LANGUAGE NondecreasingIndentation, ScopedTypeVariables #-} {-# LANGUAGE TupleSections, NamedFieldPuns #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE PatternSynonyms #-} -- ----------------------------------------------------------------------------- -- @@ -96,7 +97,35 @@ module GHC ( lookupGlobalName, findGlobalAnns, mkNamePprCtxForModule, - ModIface, ModIface_(..), + ModIface, + ModIface_( + mi_module, + mi_sig_of, + mi_hsc_src, + mi_src_hash, + mi_hi_bytes, + mi_deps, + mi_usages, + mi_exports, + mi_used_th, + mi_fixities, + mi_warns, + mi_anns, + mi_insts, + mi_fam_insts, + mi_rules, + mi_decls, + mi_extra_decls, + mi_top_env, + mi_hpc, + mi_trust, + mi_trust_pkg, + mi_complete_matches, + mi_docs, + mi_final_exts, + mi_ext_fields + ), + pattern ModIface, SafeHaskellMode(..), -- * Printing ===================================== compiler/GHC/Iface/Binary.hs ===================================== @@ -18,6 +18,8 @@ module GHC.Iface.Binary ( getSymtabName, CheckHiWay(..), TraceBinIFace(..), + getIfaceWithExtFields, + putIfaceWithExtFields, getWithUserData, putWithUserData, @@ -61,6 +63,8 @@ import Data.Map.Strict (Map) import Data.Word import System.IO.Unsafe import Data.Typeable (Typeable) +import qualified GHC.Data.Strict as Strict +import Data.Function ((&)) -- --------------------------------------------------------------------------- @@ -169,17 +173,29 @@ readBinIface readBinIface profile name_cache checkHiWay traceBinIface hi_path = do (src_hash, bh) <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path - extFields_p <- get bh + mod_iface <- getIfaceWithExtFields name_cache bh - mod_iface <- getWithUserData name_cache bh + return $ mod_iface + & addSourceFingerprint src_hash - seekBinReader bh extFields_p - extFields <- get bh - return mod_iface - { mi_ext_fields = extFields - , mi_src_hash = src_hash - } +getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface +getIfaceWithExtFields name_cache bh = do + -- Start offset for the byte array that contains the serialised 'ModIface'. + start <- tellBinReader bh + extFields_p_rel <- getRelBin bh + + mod_iface <- getWithUserData name_cache bh + + seekBinReaderRel bh extFields_p_rel + extFields <- get bh + -- Store the 'ModIface' byte array, so that we can avoid serialisation if + -- the 'ModIface' isn't modified. + -- See Note [Sharing of ModIface] + modIfaceBinData <- freezeBinHandle bh start + pure $ mod_iface + & set_mi_ext_fields extFields + & set_mi_hi_bytes (FullIfaceBinHandle $ Strict.Just modIfaceBinData) -- | This performs a get action after reading the dictionary and symbol -- table. It is necessary to run this before trying to deserialise any @@ -209,7 +225,7 @@ getTables name_cache bh = do -- add it to the 'ReaderUserData' of 'ReadBinHandle'. decodeReaderTable :: Typeable a => ReaderTable a -> ReadBinHandle -> IO ReadBinHandle decodeReaderTable tbl bh0 = do - table <- Binary.forwardGet bh (getTable tbl bh0) + table <- Binary.forwardGetRel bh (getTable tbl bh0) let binaryReader = mkReaderFromTable tbl table pure $ addReaderToUserData binaryReader bh0 @@ -246,19 +262,24 @@ writeBinIface profile traceBinIface compressionLevel hi_path mod_iface = do put_ bh tag put_ bh (mi_src_hash mod_iface) - extFields_p_p <- tellBinWriter bh - put_ bh extFields_p_p - - putWithUserData traceBinIface compressionLevel bh mod_iface - - extFields_p <- tellBinWriter bh - putAt bh extFields_p_p extFields_p - seekBinWriter bh extFields_p - put_ bh (mi_ext_fields mod_iface) + putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface -- And send the result to the file writeBinMem bh hi_path +-- | Puts the 'ModIface' to the 'WriteBinHandle'. +-- +-- This avoids serialisation of the 'ModIface' if the fields 'mi_hi_bytes' contains a +-- 'Just' value. This field is populated by reading the 'ModIface' using +-- 'getIfaceWithExtFields' and not modifying it in any way afterwards. +putIfaceWithExtFields :: TraceBinIFace -> CompressionIFace -> WriteBinHandle -> ModIface -> IO () +putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface = + case mi_hi_bytes mod_iface of + FullIfaceBinHandle Strict.Nothing -> do + forwardPutRel_ bh (\_ -> put_ bh (mi_ext_fields mod_iface)) $ do + putWithUserData traceBinIface compressionLevel bh mod_iface + FullIfaceBinHandle (Strict.Just binData) -> putFullBinData bh binData + -- | Put a piece of data with an initialised `UserData` field. This -- is necessary if you want to serialise Names or FastStrings. -- It also writes a symbol table and the dictionary. @@ -332,7 +353,7 @@ putAllTables _ [] act = do a <- act pure ([], a) putAllTables bh (x : xs) act = do - (r, (res, a)) <- forwardPut bh (const $ putTable x bh) $ do + (r, (res, a)) <- forwardPutRel bh (const $ putTable x bh) $ do putAllTables bh xs act pure (r : res, a) @@ -484,7 +505,7 @@ to the table we need to deserialise first. What deduplication tables exist and the order of serialisation is currently statically specified in 'putWithTables'. 'putWithTables' also takes care of the serialisation of used deduplication tables. The deserialisation of the deduplication tables happens 'getTables', using 'Binary' utility -functions such as 'forwardGet'. +functions such as 'forwardGetRel'. Here, a visualisation of the table structure we currently have (ignoring 'ExtensibleFields'): @@ -585,7 +606,6 @@ initWriteIfaceType compressionLevel = do putGenericSymTab sym_tab bh ty _ -> putIfaceType bh ty - fullIfaceTypeSerialiser sym_tab bh ty = do put_ bh ifaceTypeSharedByte putGenericSymTab sym_tab bh ty ===================================== compiler/GHC/Iface/Ext/Binary.hs ===================================== @@ -228,7 +228,7 @@ readHieFileContents bh0 name_cache = do get bh1 where get_dictionary tbl bin_handle = do - fsTable <- Binary.forwardGet bin_handle (getTable tbl bin_handle) + fsTable <- Binary.forwardGetRel bin_handle (getTable tbl bin_handle) let fsReader = mkReaderFromTable tbl fsTable bhFs = addReaderToUserData fsReader bin_handle ===================================== compiler/GHC/Iface/Ext/Fields.hs ===================================== @@ -41,7 +41,7 @@ instance Binary ExtensibleFields where -- to point to the start of each payload: forM_ header_entries $ \(field_p_p, dat) -> do field_p <- tellBinWriter bh - putAt bh field_p_p field_p + putAtRel bh field_p_p field_p seekBinWriter bh field_p put_ bh dat @@ -50,11 +50,11 @@ instance Binary ExtensibleFields where -- Get the names and field pointers: header_entries <- replicateM n $ - (,) <$> get bh <*> get bh + (,) <$> get bh <*> getRelBin bh -- Seek to and get each field's payload: fields <- forM header_entries $ \(name, field_p) -> do - seekBinReader bh field_p + seekBinReaderRel bh field_p dat <- get bh return (name, dat) ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -117,6 +117,7 @@ import System.FilePath import System.Directory import GHC.Driver.Env.KnotVars import GHC.Iface.Errors.Types +import Data.Function ((&)) {- ************************************************************************ @@ -515,14 +516,12 @@ loadInterface doc_str mod from ; new_eps_anns <- tcIfaceAnnotations (mi_anns iface) ; new_eps_complete_matches <- tcIfaceCompleteMatches (mi_complete_matches iface) - ; let { final_iface = iface { - mi_decls = panic "No mi_decls in PIT", - mi_insts = panic "No mi_insts in PIT", - mi_fam_insts = panic "No mi_fam_insts in PIT", - mi_rules = panic "No mi_rules in PIT", - mi_anns = panic "No mi_anns in PIT" - } - } + ; let final_iface = iface + & set_mi_decls (panic "No mi_decls in PIT") + & set_mi_insts (panic "No mi_insts in PIT") + & set_mi_fam_insts (panic "No mi_fam_insts in PIT") + & set_mi_rules (panic "No mi_rules in PIT") + & set_mi_anns (panic "No mi_anns in PIT") ; let bad_boot = mi_boot iface == IsBoot && isJust (lookupKnotVars (if_rec_types gbl_env) mod) @@ -1018,13 +1017,13 @@ readIface dflags name_cache wanted_mod file_path = do -- See Note [GHC.Prim] in primops.txt.pp. ghcPrimIface :: ModIface ghcPrimIface - = empty_iface { - mi_exports = ghcPrimExports, - mi_decls = [], - mi_fixities = fixities, - mi_final_exts = (mi_final_exts empty_iface){ mi_fix_fn = mkIfaceFixCache fixities }, - mi_docs = Just ghcPrimDeclDocs -- See Note [GHC.Prim Docs] - } + = empty_iface + & set_mi_exports ghcPrimExports + & set_mi_decls [] + & set_mi_fixities fixities + & set_mi_final_exts ((mi_final_exts empty_iface){ mi_fix_fn = mkIfaceFixCache fixities }) + & set_mi_docs (Just ghcPrimDeclDocs) -- See Note [GHC.Prim Docs] + where empty_iface = emptyFullModIface gHC_PRIM @@ -1108,7 +1107,7 @@ pprModIfaceSimple unit_state iface = -- -- The UnitState is used to pretty-print units pprModIface :: UnitState -> ModIface -> SDoc -pprModIface unit_state iface at ModIface{ mi_final_exts = exts } +pprModIface unit_state iface = vcat [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) @@ -1149,6 +1148,7 @@ pprModIface unit_state iface at ModIface{ mi_final_exts = exts } , text "extensible fields:" $$ nest 2 (pprExtensibleFields (mi_ext_fields iface)) ] where + exts = mi_final_exts iface pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" pp_hsc_src HsSrcFile = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -69,10 +69,13 @@ import GHC.Types.HpcInfo import GHC.Types.CompleteMatch import GHC.Types.SourceText import GHC.Types.SrcLoc ( unLoc ) +import GHC.Types.Name.Cache import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Utils.Logger +import GHC.Utils.Binary +import GHC.Iface.Binary import GHC.Data.FastString import GHC.Data.Maybe @@ -142,14 +145,47 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos = do full_iface <- {-# SCC "addFingerprints" #-} - addFingerprints hsc_env partial_iface{ mi_decls = decls } + addFingerprints hsc_env (set_mi_decls decls partial_iface) -- Debug printing let unit_state = hsc_units hsc_env putDumpFileMaybe (hsc_logger hsc_env) Opt_D_dump_hi "FINAL INTERFACE" FormatText (pprModIface unit_state full_iface) + final_iface <- shareIface (hsc_NC hsc_env) (flagsToIfCompression $ hsc_dflags hsc_env) full_iface + return final_iface - return full_iface +-- | Compress an 'ModIface' and share as many values as possible, depending on the 'CompressionIFace' level. +-- See Note [Sharing of ModIface]. +-- +-- We compress the 'ModIface' by serialising the 'ModIface' to an in-memory byte array, and then deserialising it. +-- The deserialisation will deduplicate certain values depending on the 'CompressionIFace' level. +-- See Note [Deduplication during iface binary serialisation] for how we do that. +-- +-- Additionally, we cache the serialised byte array, so if the 'ModIface' is not modified +-- after calling 'shareIface', 'writeBinIface' will reuse that buffer without serialising the 'ModIface' again. +-- Modifying the 'ModIface' forces us to re-serialise it again. +shareIface :: NameCache -> CompressionIFace -> ModIface -> IO ModIface +shareIface _ NormalCompression mi = do + -- In 'NormalCompression', the sharing isn't reducing the memory usage, as 'Name's and 'FastString's are + -- already shared, and at this compression level, we don't compress/share anything else. + -- Thus, for a brief moment we simply double the memory residency for no reason. + -- Therefore, we only try to share expensive values if the compression mode is higher than + -- 'NormalCompression' + pure mi +shareIface nc compressionLevel mi = do + bh <- openBinMem initBinMemSize + start <- tellBinWriter bh + putIfaceWithExtFields QuietBinIFace compressionLevel bh mi + rbh <- shrinkBinBuffer bh + seekBinReader rbh start + res <- getIfaceWithExtFields nc rbh + let resiface = restoreFromOldModIface mi res + forceModIface resiface + return resiface + +-- | Initial ram buffer to allocate for writing interface files. +initBinMemSize :: Int +initBinMemSize = 1024 * 1024 -- 1 MB updateDecl :: [IfaceDecl] -> Maybe StgCgInfos -> Maybe CmmCgInfos -> [IfaceDecl] updateDecl decls Nothing Nothing = decls @@ -304,40 +340,40 @@ mkIface_ hsc_env icomplete_matches = map mkIfaceCompleteMatch complete_matches !rdrs = maybeGlobalRdrEnv rdr_env - ModIface { - mi_module = this_mod, + emptyPartialModIface this_mod -- Need to record this because it depends on the -instantiated-with flag -- which could change - mi_sig_of = if semantic_mod == this_mod - then Nothing - else Just semantic_mod, - mi_hsc_src = hsc_src, - mi_deps = deps, - mi_usages = usages, - mi_exports = mkIfaceExports exports, + & set_mi_sig_of (if semantic_mod == this_mod + then Nothing + else Just semantic_mod) + & set_mi_hsc_src hsc_src + & set_mi_deps deps + & set_mi_usages usages + & set_mi_exports (mkIfaceExports exports) -- Sort these lexicographically, so that -- the result is stable across compilations - mi_insts = sortBy cmp_inst iface_insts, - mi_fam_insts = sortBy cmp_fam_inst iface_fam_insts, - mi_rules = sortBy cmp_rule iface_rules, - - mi_fixities = fixities, - mi_warns = warns, - mi_anns = annotations, - mi_top_env = rdrs, - mi_used_th = used_th, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_hpc = isHpcUsed hpc_info, - mi_trust = trust_info, - mi_trust_pkg = pkg_trust_req, - mi_complete_matches = icomplete_matches, - mi_docs = docs, - mi_final_exts = (), - mi_ext_fields = emptyExtensibleFields, - mi_src_hash = ms_hs_hash mod_summary - } + & set_mi_insts (sortBy cmp_inst iface_insts) + & set_mi_fam_insts (sortBy cmp_fam_inst iface_fam_insts) + & set_mi_rules (sortBy cmp_rule iface_rules) + + & set_mi_fixities fixities + & set_mi_warns warns + & set_mi_anns annotations + & set_mi_top_env rdrs + & set_mi_used_th used_th + & set_mi_decls decls + & set_mi_extra_decls extra_decls + & set_mi_hpc (isHpcUsed hpc_info) + & set_mi_trust trust_info + & set_mi_trust_pkg pkg_trust_req + & set_mi_complete_matches (icomplete_matches) + & set_mi_docs docs + & set_mi_final_exts () + & set_mi_ext_fields emptyExtensibleFields + & set_mi_src_hash (ms_hs_hash mod_summary) + & set_mi_hi_bytes PartialIfaceBinHandle + where cmp_rule = lexicalCompareFS `on` ifRuleName -- Compare these lexicographically by OccName, *not* by unique, @@ -513,3 +549,22 @@ That is, in Y, In the result of mkIfaceExports, the names are grouped by defining module, so we may need to split up a single Avail into multiple ones. -} + +{- +Note [Sharing of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +A 'ModIface' contains many duplicated values such as 'Name', 'FastString' and 'IfaceType'. +'Name's and 'FastString's are already deduplicated by default using the 'NameCache' and +'FastStringTable' respectively. +However, 'IfaceType' can be quite expensive in terms of memory usage. +To improve the sharing of 'IfaceType', we introduced deduplication tables during +serialisation of 'ModIface', see Note [Deduplication during iface binary serialisation]. + +We can improve the sharing of 'ModIface' at run-time as well, by serialising the 'ModIface' to +an in-memory buffer, and then deserialising it again. +This implicitly shares duplicated values. + +To avoid re-serialising the 'ModIface' when writing it to disk, we save the serialised 'ModIface' buffer +in 'mi_hi_bytes_' field of said 'ModIface'. This buffer is written to disk directly in 'putIfaceWithExtFields'. +If we have to modify the 'ModIface' after 'shareIface' is called, the buffer needs to be discarded. +-} ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -1281,7 +1281,8 @@ addFingerprints hsc_env iface0 , mi_fix_fn = fix_fn , mi_hash_fn = lookupOccEnv local_env } - final_iface = iface0 { mi_decls = sorted_decls, mi_extra_decls = sorted_extra_decls, mi_final_exts = final_iface_exts } + final_iface = completePartialModIface iface0 + sorted_decls sorted_extra_decls final_iface_exts -- return final_iface ===================================== compiler/GHC/Iface/Rename.hs ===================================== @@ -44,6 +44,7 @@ import GHC.Utils.Panic import qualified Data.Traversable as T import Data.IORef +import Data.Function ((&)) tcRnMsgMaybe :: IO (Either (Messages TcRnMessage) a) -> TcM a tcRnMsgMaybe do_this = do @@ -108,13 +109,14 @@ rnModIface hsc_env insts nsubst iface = deps <- rnDependencies (mi_deps iface) -- TODO: -- mi_rules - return iface { mi_module = mod - , mi_sig_of = sig_of - , mi_insts = insts - , mi_fam_insts = fams - , mi_exports = exports - , mi_decls = decls - , mi_deps = deps } + return $ iface + & set_mi_module mod + & set_mi_sig_of sig_of + & set_mi_insts insts + & set_mi_fam_insts fams + & set_mi_exports exports + & set_mi_decls decls + & set_mi_deps deps -- | Rename just the exports of a 'ModIface'. Useful when we're doing -- shaping prior to signature merging. ===================================== compiler/GHC/Tc/Errors/Hole.hs ===================================== @@ -76,7 +76,7 @@ import GHC.Tc.Utils.Unify ( tcSubTypeSigma ) import GHC.HsToCore.Docs ( extractDocs ) import GHC.Hs.Doc -import GHC.Unit.Module.ModIface ( ModIface_(..) ) +import GHC.Unit.Module.ModIface ( mi_docs ) import GHC.Iface.Load ( loadInterfaceForName ) import GHC.Builtin.Utils (knownKeyNames) ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -1562,7 +1562,8 @@ lookupDeclDoc nm = do -- Wasn't in the current module. Try searching other external ones! mIface <- getExternalModIface nm case mIface of - Just ModIface { mi_docs = Just Docs{docs_decls = dmap} } -> + Just iface + | Just Docs{docs_decls = dmap} <- mi_docs iface -> pure $ renderHsDocStrings . map hsDocString <$> lookupUniqMap dmap nm _ -> pure Nothing @@ -1578,7 +1579,8 @@ lookupArgDoc i nm = do Nothing -> do mIface <- getExternalModIface nm case mIface of - Just ModIface { mi_docs = Just Docs{docs_args = amap} } -> + Just iface + | Just Docs{docs_args = amap} <- mi_docs iface-> pure $ renderHsDocString . hsDocString <$> (lookupUniqMap amap nm >>= IntMap.lookup i) _ -> pure Nothing ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -87,6 +87,7 @@ import Control.Monad import Data.List (find) import GHC.Iface.Errors.Types +import Data.Function ((&)) checkHsigDeclM :: ModIface -> TyThing -> TyThing -> TcRn () checkHsigDeclM sig_iface sig_thing real_thing = do @@ -369,8 +370,8 @@ tcRnMergeSignatures hsc_env hpm orig_tcg_env iface = thinModIface :: [AvailInfo] -> ModIface -> ModIface thinModIface avails iface = - iface { - mi_exports = avails, + iface + & set_mi_exports avails -- mi_fixities = ..., -- mi_warns = ..., -- mi_anns = ..., @@ -378,10 +379,9 @@ thinModIface avails iface = -- perhaps there might be two IfaceTopBndr that are the same -- OccName but different Name. Requires better understanding -- of invariants here. - mi_decls = exported_decls ++ non_exported_decls ++ dfun_decls + & set_mi_decls (exported_decls ++ non_exported_decls ++ dfun_decls) -- mi_insts = ..., -- mi_fam_insts = ..., - } where decl_pred occs decl = nameOccName (ifName decl) `elemOccSet` occs filter_decls occs = filter (decl_pred occs . snd) (mi_decls iface) ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -4,10 +4,68 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE PatternSynonyms #-} + module GHC.Unit.Module.ModIface ( ModIface - , ModIface_ (..) + , ModIface_ + ( mi_module + , mi_sig_of + , mi_hsc_src + , mi_deps + , mi_usages + , mi_exports + , mi_used_th + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_extra_decls + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_hpc + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_final_exts + , mi_ext_fields + , mi_src_hash + , mi_hi_bytes + ) + , pattern ModIface + , restoreFromOldModIface + , addSourceFingerprint + , set_mi_module + , set_mi_sig_of + , set_mi_hsc_src + , set_mi_src_hash + , set_mi_hi_bytes + , set_mi_deps + , set_mi_usages + , set_mi_exports + , set_mi_used_th + , set_mi_fixities + , set_mi_warns + , set_mi_anns + , set_mi_insts + , set_mi_fam_insts + , set_mi_rules + , set_mi_decls + , set_mi_extra_decls + , set_mi_top_env + , set_mi_hpc + , set_mi_trust + , set_mi_trust_pkg + , set_mi_complete_matches + , set_mi_docs + , set_mi_final_exts + , set_mi_ext_fields + , completePartialModIface + , IfaceBinHandle(..) , PartialModIface , ModIfaceBackend (..) , IfaceDeclExts @@ -47,6 +105,7 @@ import GHC.Types.Fixity import GHC.Types.Fixity.Env import GHC.Types.HpcInfo import GHC.Types.Name +import GHC.Types.Name.Reader (IfGlobalRdrEnv) import GHC.Types.SafeHaskell import GHC.Types.SourceFile import GHC.Types.Unique.DSet @@ -59,7 +118,7 @@ import GHC.Utils.Binary import Control.DeepSeq import Control.Exception -import GHC.Types.Name.Reader (IfGlobalRdrEnv) +import qualified GHC.Data.Strict as Strict {- Note [Interface file stages] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -141,7 +200,17 @@ type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where IfaceBackendExts 'ModIfaceCore = () IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend - +-- | In-memory byte array representation of a 'ModIface'. +-- +-- See Note [Sharing of ModIface] for why we need this. +data IfaceBinHandle (phase :: ModIfacePhase) where + -- | A partial 'ModIface' cannot be serialised to disk. + PartialIfaceBinHandle :: IfaceBinHandle 'ModIfaceCore + -- | Optional 'FullBinData' that can be serialised to disk directly. + -- + -- See Note [Private fields in ModIface] for when this fields needs to be cleared + -- (e.g., set to 'Nothing'). + FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal -- | A 'ModIface' plus a 'ModDetails' summarises everything we know -- about a compiled module. The 'ModIface' is the stuff *before* linking, @@ -155,62 +224,65 @@ type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where -- -- See Note [Strictness in ModIface] to learn about why some fields are -- strict and others are not. +-- +-- See Note [Private fields in ModIface] to learn why we don't export any of the +-- fields. data ModIface_ (phase :: ModIfacePhase) - = ModIface { - mi_module :: !Module, -- ^ Name of the module we are for - mi_sig_of :: !(Maybe Module), -- ^ Are we a sig of another mod? + = PrivateModIface { + mi_module_ :: !Module, -- ^ Name of the module we are for + mi_sig_of_ :: !(Maybe Module), -- ^ Are we a sig of another mod? - mi_hsc_src :: !HscSource, -- ^ Boot? Signature? + mi_hsc_src_ :: !HscSource, -- ^ Boot? Signature? - mi_deps :: Dependencies, + mi_deps_ :: Dependencies, -- ^ The dependencies of the module. This is -- consulted for directly-imported modules, but not -- for anything else (hence lazy) - mi_usages :: [Usage], + mi_usages_ :: [Usage], -- ^ Usages; kept sorted so that it's easy to decide -- whether to write a new iface file (changing usages -- doesn't affect the hash of this module) -- NOT STRICT! we read this field lazily from the interface file -- It is *only* consulted by the recompilation checker - mi_exports :: ![IfaceExport], + mi_exports_ :: ![IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier -- Records the modules that are the declaration points for things -- exported by this module, and the 'OccName's of those things - mi_used_th :: !Bool, + mi_used_th_ :: !Bool, -- ^ Module required TH splices when it was compiled. -- This disables recompilation avoidance (see #481). - mi_fixities :: [(OccName,Fixity)], + mi_fixities_ :: [(OccName,Fixity)], -- ^ Fixities -- NOT STRICT! we read this field lazily from the interface file - mi_warns :: IfaceWarnings, + mi_warns_ :: IfaceWarnings, -- ^ Warnings -- NOT STRICT! we read this field lazily from the interface file - mi_anns :: [IfaceAnnotation], + mi_anns_ :: [IfaceAnnotation], -- ^ Annotations -- NOT STRICT! we read this field lazily from the interface file - mi_decls :: [IfaceDeclExts phase], + mi_decls_ :: [IfaceDeclExts phase], -- ^ Type, class and variable declarations -- The hash of an Id changes if its fixity or deprecations change -- (as well as its type of course) -- Ditto data constructors, class operations, except that -- the hash of the parent class/tycon changes - mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], + mi_extra_decls_ :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], -- ^ Extra variable definitions which are **NOT** exposed but when -- combined with mi_decls allows us to restart code generation. -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] - mi_top_env :: !(Maybe IfaceTopEnv), + mi_top_env_ :: !(Maybe IfaceTopEnv), -- ^ Just enough information to reconstruct the top level environment in -- the /original source/ code for this module. which -- is NOT the same as mi_exports, nor mi_decls (which @@ -226,36 +298,36 @@ data ModIface_ (phase :: ModIfacePhase) -- 'HomeModInfo', but that leads to more plumbing. -- Instance declarations and rules - mi_insts :: [IfaceClsInst], -- ^ Sorted class instance - mi_fam_insts :: [IfaceFamInst], -- ^ Sorted family instances - mi_rules :: [IfaceRule], -- ^ Sorted rules + mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance + mi_fam_insts_ :: [IfaceFamInst], -- ^ Sorted family instances + mi_rules_ :: [IfaceRule], -- ^ Sorted rules - mi_hpc :: !AnyHpcUsage, + mi_hpc_ :: !AnyHpcUsage, -- ^ True if this program uses Hpc at any point in the program. - mi_trust :: !IfaceTrustInfo, + mi_trust_ :: !IfaceTrustInfo, -- ^ Safe Haskell Trust information for this module. - mi_trust_pkg :: !Bool, + mi_trust_pkg_ :: !Bool, -- ^ Do we require the package this module resides in be trusted -- to trust this module? This is used for the situation where a -- module is Safe (so doesn't require the package be trusted -- itself) but imports some trustworthy modules from its own -- package (which does require its own package be trusted). -- See Note [Trust Own Package] in GHC.Rename.Names - mi_complete_matches :: ![IfaceCompleteMatch], + mi_complete_matches_ :: ![IfaceCompleteMatch], - mi_docs :: !(Maybe Docs), + mi_docs_ :: !(Maybe Docs), -- ^ Docstrings and related data for use by haddock, the ghci -- @:doc@ command, and other tools. -- -- @Just _@ @<=>@ the module was built with @-haddock at . - mi_final_exts :: !(IfaceBackendExts phase), + mi_final_exts_ :: !(IfaceBackendExts phase), -- ^ Either `()` or `ModIfaceBackend` for -- a fully instantiated interface. - mi_ext_fields :: !ExtensibleFields, + mi_ext_fields_ :: !ExtensibleFields, -- ^ Additional optional fields, where the Map key represents -- the field name, resulting in a (size, serialized data) pair. -- Because the data is intended to be serialized through the @@ -264,8 +336,13 @@ data ModIface_ (phase :: ModIfacePhase) -- chosen over `ByteString`s. -- - mi_src_hash :: !Fingerprint + mi_src_hash_ :: !Fingerprint, -- ^ Hash of the .hs source, used for recompilation checking. + mi_hi_bytes_ :: !(IfaceBinHandle phase) + -- ^ A serialised in-memory buffer of this 'ModIface'. + -- If this handle is given, we can avoid serialising the 'ModIface' + -- when writing this 'ModIface' to disk, and write this buffer to disk instead. + -- See Note [Sharing of ModIface]. } -- Enough information to reconstruct the top level environment for a module @@ -354,34 +431,40 @@ renameFreeHoles fhs insts = -- See Note [Strictness in ModIface] about where we use lazyPut vs put instance Binary ModIface where - put_ bh (ModIface { - mi_module = mod, - mi_sig_of = sig_of, - mi_hsc_src = hsc_src, - mi_src_hash = _src_hash, -- Don't `put_` this in the instance + put_ bh (PrivateModIface { + mi_module_ = mod, + mi_sig_of_ = sig_of, + mi_hsc_src_ = hsc_src, + mi_src_hash_ = _src_hash, -- Don't `put_` this in the instance -- because we are going to write it -- out separately in the actual file - mi_deps = deps, - mi_usages = usages, - mi_exports = exports, - mi_used_th = used_th, - mi_fixities = fixities, - mi_warns = warns, - mi_anns = anns, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_insts = insts, - mi_fam_insts = fam_insts, - mi_rules = rules, - mi_hpc = hpc_info, - mi_trust = trust, - mi_trust_pkg = trust_pkg, - mi_complete_matches = complete_matches, - mi_docs = docs, - mi_ext_fields = _ext_fields, -- Don't `put_` this in the instance so we + mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself + -- may contain an in-memory byte array buffer for this + -- 'ModIface'. If we used 'put_' on this 'ModIface', then + -- we likely have a good reason, and do not want to reuse + -- the byte array. + -- See Note [Private fields in ModIface] + mi_deps_ = deps, + mi_usages_ = usages, + mi_exports_ = exports, + mi_used_th_ = used_th, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_anns_ = anns, + mi_decls_ = decls, + mi_extra_decls_ = extra_decls, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_hpc_ = hpc_info, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, + mi_complete_matches_ = complete_matches, + mi_docs_ = docs, + mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file - mi_final_exts = ModIfaceBackend { + mi_final_exts_ = ModIfaceBackend { mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, mi_flag_hash = flag_hash, @@ -455,34 +538,39 @@ instance Binary ModIface where trust_pkg <- get bh complete_matches <- get bh docs <- lazyGetMaybe bh - return (ModIface { - mi_module = mod, - mi_sig_of = sig_of, - mi_hsc_src = hsc_src, - mi_src_hash = fingerprint0, -- placeholder because this is dealt + return (PrivateModIface { + mi_module_ = mod, + mi_sig_of_ = sig_of, + mi_hsc_src_ = hsc_src, + mi_src_hash_ = fingerprint0, -- placeholder because this is dealt -- with specially when the file is read - mi_deps = deps, - mi_usages = usages, - mi_exports = exports, - mi_used_th = used_th, - mi_anns = anns, - mi_fixities = fixities, - mi_warns = warns, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_top_env = Nothing, - mi_insts = insts, - mi_fam_insts = fam_insts, - mi_rules = rules, - mi_hpc = hpc_info, - mi_trust = trust, - mi_trust_pkg = trust_pkg, + mi_hi_bytes_ = + -- We can't populate this field here, as we are + -- missing the 'mi_ext_fields_' field, which is + -- handled in 'getIfaceWithExtFields'. + FullIfaceBinHandle Strict.Nothing, + mi_deps_ = deps, + mi_usages_ = usages, + mi_exports_ = exports, + mi_used_th_ = used_th, + mi_anns_ = anns, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_decls_ = decls, + mi_extra_decls_ = extra_decls, + mi_top_env_ = Nothing, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_hpc_ = hpc_info, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, -- And build the cached values - mi_complete_matches = complete_matches, - mi_docs = docs, - mi_ext_fields = emptyExtensibleFields, -- placeholder because this is dealt + mi_complete_matches_ = complete_matches, + mi_docs_ = docs, + mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read - mi_final_exts = ModIfaceBackend { + mi_final_exts_ = ModIfaceBackend { mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, mi_flag_hash = flag_hash, @@ -499,42 +587,46 @@ instance Binary ModIface where mi_hash_fn = mkIfaceHashCache decls }}) + -- | The original names declared of a certain module that are exported type IfaceExport = AvailInfo emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod - = ModIface { mi_module = mod, - mi_sig_of = Nothing, - mi_hsc_src = HsSrcFile, - mi_src_hash = fingerprint0, - mi_deps = noDependencies, - mi_usages = [], - mi_exports = [], - mi_used_th = False, - mi_fixities = [], - mi_warns = IfWarnSome [] [], - mi_anns = [], - mi_insts = [], - mi_fam_insts = [], - mi_rules = [], - mi_decls = [], - mi_extra_decls = Nothing, - mi_top_env = Nothing, - mi_hpc = False, - mi_trust = noIfaceTrustInfo, - mi_trust_pkg = False, - mi_complete_matches = [], - mi_docs = Nothing, - mi_final_exts = (), - mi_ext_fields = emptyExtensibleFields - } + = PrivateModIface + { mi_module_ = mod, + mi_sig_of_ = Nothing, + mi_hsc_src_ = HsSrcFile, + mi_src_hash_ = fingerprint0, + mi_hi_bytes_ = PartialIfaceBinHandle, + mi_deps_ = noDependencies, + mi_usages_ = [], + mi_exports_ = [], + mi_used_th_ = False, + mi_fixities_ = [], + mi_warns_ = IfWarnSome [] [], + mi_anns_ = [], + mi_insts_ = [], + mi_fam_insts_ = [], + mi_rules_ = [], + mi_decls_ = [], + mi_extra_decls_ = Nothing, + mi_top_env_ = Nothing, + mi_hpc_ = False, + mi_trust_ = noIfaceTrustInfo, + mi_trust_pkg_ = False, + mi_complete_matches_ = [], + mi_docs_ = Nothing, + mi_final_exts_ = (), + mi_ext_fields_ = emptyExtensibleFields + } emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) - { mi_decls = [] - , mi_final_exts = ModIfaceBackend + { mi_decls_ = [] + , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + , mi_final_exts_ = ModIfaceBackend { mi_iface_hash = fingerprint0, mi_mod_hash = fingerprint0, mi_flag_hash = fingerprint0, @@ -569,36 +661,38 @@ emptyIfaceHashCache _occ = Nothing instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (ModIface{ mi_module, mi_sig_of, mi_hsc_src, mi_deps, mi_usages - , mi_exports, mi_used_th, mi_fixities, mi_warns, mi_anns - , mi_decls, mi_extra_decls, mi_top_env, mi_insts - , mi_fam_insts, mi_rules, mi_hpc, mi_trust, mi_trust_pkg - , mi_complete_matches, mi_docs, mi_final_exts - , mi_ext_fields, mi_src_hash }) - = rnf mi_module - `seq` rnf mi_sig_of - `seq` mi_hsc_src - `seq` mi_deps - `seq` mi_usages - `seq` mi_exports - `seq` rnf mi_used_th - `seq` mi_fixities - `seq` rnf mi_warns - `seq` rnf mi_anns - `seq` rnf mi_decls - `seq` rnf mi_extra_decls - `seq` rnf mi_top_env - `seq` rnf mi_insts - `seq` rnf mi_fam_insts - `seq` rnf mi_rules - `seq` rnf mi_hpc - `seq` mi_trust - `seq` rnf mi_trust_pkg - `seq` rnf mi_complete_matches - `seq` rnf mi_docs - `seq` mi_final_exts - `seq` mi_ext_fields - `seq` rnf mi_src_hash + rnf (PrivateModIface + { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_, mi_usages_ + , mi_exports_, mi_used_th_, mi_fixities_, mi_warns_, mi_anns_ + , mi_decls_, mi_extra_decls_, mi_top_env_, mi_insts_ + , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_ + , mi_complete_matches_, mi_docs_, mi_final_exts_ + , mi_ext_fields_, mi_src_hash_ }) + = rnf mi_module_ + `seq` rnf mi_sig_of_ + `seq` mi_hsc_src_ + `seq` mi_hi_bytes_ + `seq` mi_deps_ + `seq` mi_usages_ + `seq` mi_exports_ + `seq` rnf mi_used_th_ + `seq` mi_fixities_ + `seq` rnf mi_warns_ + `seq` rnf mi_anns_ + `seq` rnf mi_decls_ + `seq` rnf mi_extra_decls_ + `seq` rnf mi_top_env_ + `seq` rnf mi_insts_ + `seq` rnf mi_fam_insts_ + `seq` rnf mi_rules_ + `seq` rnf mi_hpc_ + `seq` mi_trust_ + `seq` rnf mi_trust_pkg_ + `seq` rnf mi_complete_matches_ + `seq` rnf mi_docs_ + `seq` mi_final_exts_ + `seq` mi_ext_fields_ + `seq` rnf mi_src_hash_ `seq` () instance NFData (ModIfaceBackend) where @@ -638,5 +732,286 @@ type WhetherHasOrphans = Bool -- | Does this module define family instances? type WhetherHasFamInst = Bool +-- ---------------------------------------------------------------------------- +-- Modify a 'ModIface'. +-- ---------------------------------------------------------------------------- + +{- +Note [Private fields in ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The fields of 'ModIface' are private, e.g., not exported, to make the API +impossible to misuse. A 'ModIface' can be "compressed" in-memory using +'shareIface', which serialises the 'ModIface' to an in-memory buffer. +This has the advantage of reducing memory usage of 'ModIface', reducing the +overall memory usage of GHC. +See Note [Sharing of ModIface]. + +This in-memory buffer can be reused, if and only if the 'ModIface' is not +modified after it has been "compressed"/shared via 'shareIface'. Instead of +serialising 'ModIface', we simply write the in-memory buffer to disk directly. + +However, we can't rely that a 'ModIface' isn't modified after 'shareIface' has +been called. Thus, we make all fields of 'ModIface' private and modification +only happens via exported update functions, such as 'set_mi_decls'. +These functions unconditionally clear any in-memory buffer if used, forcing us +to serialise the 'ModIface' to disk again. +-} + +-- | Given a 'PartialModIface', turn it into a 'ModIface' by completing +-- missing fields. +completePartialModIface :: PartialModIface + -> [(Fingerprint, IfaceDecl)] + -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] + -> ModIfaceBackend + -> ModIface +completePartialModIface partial decls extra_decls final_exts = partial + { mi_decls_ = decls + , mi_extra_decls_ = extra_decls + , mi_final_exts_ = final_exts + , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + } + +-- | Add a source fingerprint to a 'ModIface_' without invalidating the byte array +-- buffer 'mi_hi_bytes'. +-- This is a variant of 'set_mi_src_hash' which does invalidate the buffer. +-- +-- The 'mi_src_hash' is computed outside of 'ModIface_' based on the 'ModSummary'. +addSourceFingerprint :: Fingerprint -> ModIface_ phase -> ModIface_ phase +addSourceFingerprint val iface = iface { mi_src_hash_ = val } + +-- | Copy fields that aren't serialised to disk to the new 'ModIface_'. +-- This includes especially hashes that are usually stored in the interface +-- file header and 'mi_top_env'. +-- +-- We need this function after calling 'shareIface', to make sure the +-- 'ModIface_' doesn't lose any information. This function does not discard +-- the in-memory byte array buffer 'mi_hi_bytes'. +restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase +restoreFromOldModIface old new = new + { mi_top_env_ = mi_top_env_ old + , mi_hsc_src_ = mi_hsc_src_ old + , mi_src_hash_ = mi_src_hash_ old + } + +set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase +set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } + +set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase +set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } + +set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase +set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } + +set_mi_src_hash :: Fingerprint -> ModIface_ phase -> ModIface_ phase +set_mi_src_hash val iface = clear_mi_hi_bytes $ iface { mi_src_hash_ = val } + +set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase +set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } + +set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase +set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } + +set_mi_usages :: [Usage] -> ModIface_ phase -> ModIface_ phase +set_mi_usages val iface = clear_mi_hi_bytes $ iface { mi_usages_ = val } +set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase +set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } + +set_mi_used_th :: Bool -> ModIface_ phase -> ModIface_ phase +set_mi_used_th val iface = clear_mi_hi_bytes $ iface { mi_used_th_ = val } + +set_mi_fixities :: [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase +set_mi_fixities val iface = clear_mi_hi_bytes $ iface { mi_fixities_ = val } + +set_mi_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase +set_mi_warns val iface = clear_mi_hi_bytes $ iface { mi_warns_ = val } + +set_mi_anns :: [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase +set_mi_anns val iface = clear_mi_hi_bytes $ iface { mi_anns_ = val } + +set_mi_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase +set_mi_insts val iface = clear_mi_hi_bytes $ iface { mi_insts_ = val } + +set_mi_fam_insts :: [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase +set_mi_fam_insts val iface = clear_mi_hi_bytes $ iface { mi_fam_insts_ = val } + +set_mi_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase +set_mi_rules val iface = clear_mi_hi_bytes $ iface { mi_rules_ = val } + +set_mi_decls :: [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase +set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls_ = val } + +set_mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase +set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val } + +set_mi_top_env :: Maybe IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } + +set_mi_hpc :: AnyHpcUsage -> ModIface_ phase -> ModIface_ phase +set_mi_hpc val iface = clear_mi_hi_bytes $ iface { mi_hpc_ = val } + +set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase +set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val } + +set_mi_trust_pkg :: Bool -> ModIface_ phase -> ModIface_ phase +set_mi_trust_pkg val iface = clear_mi_hi_bytes $ iface { mi_trust_pkg_ = val } + +set_mi_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase +set_mi_complete_matches val iface = clear_mi_hi_bytes $ iface { mi_complete_matches_ = val } + +set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase +set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } + +set_mi_final_exts :: IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase +set_mi_final_exts val iface = clear_mi_hi_bytes $ iface { mi_final_exts_ = val } + +set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase +set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } + +-- | Invalidate any byte array buffer we might have. +clear_mi_hi_bytes :: ModIface_ phase -> ModIface_ phase +clear_mi_hi_bytes iface = iface + { mi_hi_bytes_ = case mi_hi_bytes iface of + PartialIfaceBinHandle -> PartialIfaceBinHandle + FullIfaceBinHandle _ -> FullIfaceBinHandle Strict.Nothing + } + +-- ---------------------------------------------------------------------------- +-- 'ModIface' pattern synonyms to keep breakage low. +-- ---------------------------------------------------------------------------- + +{- +Note [Inline Pattern synonym of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The introduction of the 'ModIface' pattern synonym originally caused an increase +in allocated bytes in multiple performance tests. +In some benchmarks, it was a 2~3% increase. + +Without {-# INLINE ModIface #-}, the generated core reveals the reason for this increase. +We show the core for the 'mi_module' record selector: + +@ + mi_module + = \ @phase iface -> $w$mModIface iface mi_module1 + + $w$mModIface + = \ @phase iface cont -> + case iface of + { PrivateModIface a b ... z -> + cont + a + b + ... + z + } + + mi_module1 + = \ @phase + a + _ + ... + _ -> + a +@ + +Thus, we can see the '$w$mModIface' is not inlined, leading to an increase in +the allocated bytes. + +However, with the pragma, the correct core is generated: + +@ + mi_module = mi_module_ +@ + +-} +-- See Note [Inline Pattern synonym of ModIface] for why we have all these +-- inline pragmas. +{-# INLINE ModIface #-} +{-# INLINE mi_module #-} +{-# INLINE mi_sig_of #-} +{-# INLINE mi_hsc_src #-} +{-# INLINE mi_deps #-} +{-# INLINE mi_usages #-} +{-# INLINE mi_exports #-} +{-# INLINE mi_used_th #-} +{-# INLINE mi_fixities #-} +{-# INLINE mi_warns #-} +{-# INLINE mi_anns #-} +{-# INLINE mi_decls #-} +{-# INLINE mi_extra_decls #-} +{-# INLINE mi_top_env #-} +{-# INLINE mi_insts #-} +{-# INLINE mi_fam_insts #-} +{-# INLINE mi_rules #-} +{-# INLINE mi_hpc #-} +{-# INLINE mi_trust #-} +{-# INLINE mi_trust_pkg #-} +{-# INLINE mi_complete_matches #-} +{-# INLINE mi_docs #-} +{-# INLINE mi_final_exts #-} +{-# INLINE mi_ext_fields #-} +{-# INLINE mi_src_hash #-} +{-# INLINE mi_hi_bytes #-} + +pattern ModIface :: + Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] -> + [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> + [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> + Maybe IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> + AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> + IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> + ModIface_ phase +pattern ModIface + { mi_module + , mi_sig_of + , mi_hsc_src + , mi_deps + , mi_usages + , mi_exports + , mi_used_th + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_extra_decls + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_hpc + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_final_exts + , mi_ext_fields + , mi_src_hash + , mi_hi_bytes + } <- PrivateModIface + { mi_module_ = mi_module + , mi_sig_of_ = mi_sig_of + , mi_hsc_src_ = mi_hsc_src + , mi_deps_ = mi_deps + , mi_usages_ = mi_usages + , mi_exports_ = mi_exports + , mi_used_th_ = mi_used_th + , mi_fixities_ = mi_fixities + , mi_warns_ = mi_warns + , mi_anns_ = mi_anns + , mi_decls_ = mi_decls + , mi_extra_decls_ = mi_extra_decls + , mi_top_env_ = mi_top_env + , mi_insts_ = mi_insts + , mi_fam_insts_ = mi_fam_insts + , mi_rules_ = mi_rules + , mi_hpc_ = mi_hpc + , mi_trust_ = mi_trust + , mi_trust_pkg_ = mi_trust_pkg + , mi_complete_matches_ = mi_complete_matches + , mi_docs_ = mi_docs + , mi_final_exts_ = mi_final_exts + , mi_ext_fields_ = mi_ext_fields + , mi_src_hash_ = mi_src_hash + , mi_hi_bytes_ = mi_hi_bytes + } ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -19,7 +19,7 @@ -- http://www.cs.york.ac.uk/fp/nhc98/ module GHC.Utils.Binary - ( {-type-} Bin, + ( {-type-} Bin, RelBin(..), getRelBin, {-class-} Binary(..), {-type-} ReadBinHandle, WriteBinHandle, SymbolTable, Dictionary, @@ -32,10 +32,14 @@ module GHC.Utils.Binary seekBinWriter, seekBinReader, + seekBinReaderRel, tellBinReader, tellBinWriter, castBin, withBinBuffer, + freezeWriteHandle, + shrinkBinBuffer, + thawReadHandle, foldGet, foldGet', @@ -44,7 +48,9 @@ module GHC.Utils.Binary readBinMemN, putAt, getAt, + putAtRel, forwardPut, forwardPut_, forwardGet, + forwardPutRel, forwardPutRel_, forwardGetRel, -- * For writing instances putByte, @@ -99,6 +105,8 @@ module GHC.Utils.Binary BindingName(..), simpleBindingNameWriter, simpleBindingNameReader, + FullBinData(..), freezeBinHandle, thawBinHandle, putFullBinData, + BinArray, ) where import GHC.Prelude @@ -107,6 +115,7 @@ import Language.Haskell.Syntax.Module.Name (ModuleName(..)) import {-# SOURCE #-} GHC.Types.Name (Name) import GHC.Data.FastString +import GHC.Data.TrieMap import GHC.Utils.Panic.Plain import GHC.Types.Unique.FM import GHC.Data.FastMutInt @@ -115,7 +124,6 @@ import GHC.Types.SrcLoc import GHC.Types.Unique import qualified GHC.Data.Strict as Strict import GHC.Utils.Outputable( JoinPointHood(..) ) -import GHC.Utils.Misc ( HasCallStack, HasDebugCallStack ) import Control.DeepSeq import Control.Monad ( when, (<$!>), unless, forM_, void ) @@ -123,7 +131,7 @@ import Foreign hiding (shiftL, shiftR, void) import Data.Array import Data.Array.IO import Data.Array.Unsafe -import Data.ByteString (ByteString) +import Data.ByteString (ByteString, copy) import Data.Coerce import qualified Data.ByteString.Internal as BS import qualified Data.ByteString.Unsafe as BS @@ -152,8 +160,6 @@ import GHC.ForeignPtr ( unsafeWithForeignPtr ) import Unsafe.Coerce (unsafeCoerce) -import GHC.Data.TrieMap - type BinArray = ForeignPtr Word8 #if !MIN_VERSION_base(4,15,0) @@ -193,6 +199,62 @@ dataHandle (BinData size bin) = do handleData :: WriteBinHandle -> IO BinData handleData (WriteBinMem _ ixr _ binr) = BinData <$> readFastMutInt ixr <*> readIORef binr +--------------------------------------------------------------- +-- FullBinData +--------------------------------------------------------------- + +-- | 'FullBinData' stores a slice to a 'BinArray'. +-- +-- It requires less memory than 'ReadBinHandle', and can be constructed from +-- a 'ReadBinHandle' via 'freezeBinHandle' and turned back into a +-- 'ReadBinHandle' using 'thawBinHandle'. +-- Additionally, the byte array slice can be put into a 'WriteBinHandle' without extra +-- conversions via 'putFullBinData'. +data FullBinData = FullBinData + { fbd_readerUserData :: ReaderUserData + -- ^ 'ReaderUserData' that can be used to resume reading. + , fbd_off_s :: {-# UNPACK #-} !Int + -- ^ start offset + , fbd_off_e :: {-# UNPACK #-} !Int + -- ^ end offset + , fbd_size :: {-# UNPACK #-} !Int + -- ^ total buffer size + , fbd_buffer :: {-# UNPACK #-} !BinArray + } + +-- Equality and Ord assume that two distinct buffers are different, even if they compare the same things. +instance Eq FullBinData where + (FullBinData _ b c d e) == (FullBinData _ b1 c1 d1 e1) = b == b1 && c == c1 && d == d1 && e == e1 + +instance Ord FullBinData where + compare (FullBinData _ b c d e) (FullBinData _ b1 c1 d1 e1) = + compare b b1 `mappend` compare c c1 `mappend` compare d d1 `mappend` compare e e1 + +-- | Write the 'FullBinData' slice into the 'WriteBinHandle'. +putFullBinData :: WriteBinHandle -> FullBinData -> IO () +putFullBinData bh (FullBinData _ o1 o2 _sz ba) = do + let sz = o2 - o1 + putPrim bh sz $ \dest -> + unsafeWithForeignPtr (ba `plusForeignPtr` o1) $ \orig -> + copyBytes dest orig sz + +-- | Freeze a 'ReadBinHandle' and a start index into a 'FullBinData'. +-- +-- 'FullBinData' stores a slice starting from the 'Bin a' location to the current +-- offset of the 'ReadBinHandle'. +freezeBinHandle :: ReadBinHandle -> Bin a -> IO FullBinData +freezeBinHandle (ReadBinMem user_data ixr sz binr) (BinPtr start) = do + ix <- readFastMutInt ixr + pure (FullBinData user_data start ix sz binr) + +-- | Turn the 'FullBinData' into a 'ReadBinHandle', setting the 'ReadBinHandle' +-- offset to the start of the 'FullBinData' and restore the 'ReaderUserData' that was +-- obtained from 'freezeBinHandle'. +thawBinHandle :: FullBinData -> IO ReadBinHandle +thawBinHandle (FullBinData user_data ix _end sz ba) = do + ixr <- newFastMutInt ix + return $ ReadBinMem user_data ixr sz ba + --------------------------------------------------------------- -- BinHandle --------------------------------------------------------------- @@ -286,9 +348,47 @@ unsafeUnpackBinBuffer (BS.BS arr len) = do newtype Bin a = BinPtr Int deriving (Eq, Ord, Show, Bounded) +-- | Like a 'Bin' but is used to store relative offset pointers. +-- Relative offset pointers store a relative location, but also contain an +-- anchor that allow to obtain the absolute offset. +data RelBin a = RelBin + { relBin_anchor :: {-# UNPACK #-} !(Bin a) + -- ^ Absolute position from where we read 'relBin_offset'. + , relBin_offset :: {-# UNPACK #-} !(RelBinPtr a) + -- ^ Relative offset to 'relBin_anchor'. + -- The absolute position of the 'RelBin' is @relBin_anchor + relBin_offset@ + } + deriving (Eq, Ord, Show, Bounded) + +-- | A 'RelBinPtr' is like a 'Bin', but contains a relative offset pointer +-- instead of an absolute offset. +newtype RelBinPtr a = RelBinPtr (Bin a) + deriving (Eq, Ord, Show, Bounded) + castBin :: Bin a -> Bin b castBin (BinPtr i) = BinPtr i +-- | Read a relative offset location and wrap it in 'RelBin'. +-- +-- The resulting 'RelBin' can be translated into an absolute offset location using +-- 'makeAbsoluteBin' +getRelBin :: ReadBinHandle -> IO (RelBin a) +getRelBin bh = do + start <- tellBinReader bh + off <- get bh + pure $ RelBin start off + +makeAbsoluteBin :: RelBin a -> Bin a +makeAbsoluteBin (RelBin (BinPtr !start) (RelBinPtr (BinPtr !offset))) = + BinPtr $ start + offset + +makeRelativeBin :: RelBin a -> RelBinPtr a +makeRelativeBin (RelBin _ offset) = offset + +toRelBin :: Bin (RelBinPtr a) -> Bin a -> RelBin a +toRelBin (BinPtr !start) (BinPtr !goal) = + RelBin (BinPtr start) (RelBinPtr $ BinPtr $ goal - start) + --------------------------------------------------------------- -- class Binary --------------------------------------------------------------- @@ -309,6 +409,9 @@ class Binary a where putAt :: Binary a => WriteBinHandle -> Bin a -> a -> IO () putAt bh p x = do seekBinWriter bh p; put_ bh x; return () +putAtRel :: WriteBinHandle -> Bin (RelBinPtr a) -> Bin a -> IO () +putAtRel bh from to = putAt bh from (makeRelativeBin $ toRelBin from to) + getAt :: Binary a => ReadBinHandle -> Bin a -> IO a getAt bh p = do seekBinReader bh p; get bh @@ -327,6 +430,44 @@ openBinMem size , wbm_arr_r = arr_r } +-- | Freeze the given 'WriteBinHandle' and turn it into an equivalent 'ReadBinHandle'. +-- +-- The current offset of the 'WriteBinHandle' is maintained in the new 'ReadBinHandle'. +freezeWriteHandle :: WriteBinHandle -> IO ReadBinHandle +freezeWriteHandle wbm = do + rbm_off_r <- newFastMutInt =<< readFastMutInt (wbm_off_r wbm) + rbm_sz_r <- readFastMutInt (wbm_sz_r wbm) + rbm_arr_r <- readIORef (wbm_arr_r wbm) + pure $ ReadBinMem + { rbm_userData = noReaderUserData + , rbm_off_r = rbm_off_r + , rbm_sz_r = rbm_sz_r + , rbm_arr_r = rbm_arr_r + } + +-- | Copy the BinBuffer to a new BinBuffer which is exactly the right size. +-- This performs a copy of the underlying buffer. +-- The buffer may be truncated if the offset is not at the end of the written +-- output. +-- +-- UserData is also discarded during the copy +-- You should just use this when translating a Put handle into a Get handle. +shrinkBinBuffer :: WriteBinHandle -> IO ReadBinHandle +shrinkBinBuffer bh = withBinBuffer bh $ \bs -> do + unsafeUnpackBinBuffer (copy bs) + +thawReadHandle :: ReadBinHandle -> IO WriteBinHandle +thawReadHandle rbm = do + wbm_off_r <- newFastMutInt =<< readFastMutInt (rbm_off_r rbm) + wbm_sz_r <- newFastMutInt (rbm_sz_r rbm) + wbm_arr_r <- newIORef (rbm_arr_r rbm) + pure $ WriteBinMem + { wbm_userData = noWriterUserData + , wbm_off_r = wbm_off_r + , wbm_sz_r = wbm_sz_r + , wbm_arr_r = wbm_arr_r + } + tellBinWriter :: WriteBinHandle -> IO (Bin a) tellBinWriter (WriteBinMem _ r _ _) = do ix <- readFastMutInt r; return (BinPtr ix) @@ -358,6 +499,13 @@ seekBinReader (ReadBinMem _ ix_r sz_r _) (BinPtr !p) = do then panic "seekBinReader: seek out of range" else writeFastMutInt ix_r p +seekBinReaderRel :: ReadBinHandle -> RelBin a -> IO () +seekBinReaderRel (ReadBinMem _ ix_r sz_r _) relBin = do + let (BinPtr !p) = makeAbsoluteBin relBin + if (p > sz_r) + then panic "seekBinReaderRel: seek out of range" + else writeFastMutInt ix_r p + writeBinMem :: WriteBinHandle -> FilePath -> IO () writeBinMem (WriteBinMem _ ix_r _ arr_r) fn = do h <- openBinaryFile fn WriteMode @@ -1078,12 +1226,17 @@ instance Binary (Bin a) where put_ bh (BinPtr i) = putWord32 bh (fromIntegral i :: Word32) get bh = do i <- getWord32 bh; return (BinPtr (fromIntegral (i :: Word32))) +-- Instance uses fixed-width encoding to allow inserting +-- Bin placeholders in the stream. +instance Binary (RelBinPtr a) where + put_ bh (RelBinPtr i) = put_ bh i + get bh = RelBinPtr <$> get bh -- ----------------------------------------------------------------------------- -- Forward reading/writing --- | "forwardPut put_A put_B" outputs A after B but allows A to be read before B --- by using a forward reference +-- | @'forwardPut' put_A put_B@ outputs A after B but allows A to be read before B +-- by using a forward reference. forwardPut :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a,b) forwardPut bh put_A put_B = do -- write placeholder pointer to A @@ -1106,6 +1259,8 @@ forwardPut_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () forwardPut_ bh put_A put_B = void $ forwardPut bh put_A put_B -- | Read a value stored using a forward reference +-- +-- The forward reference is expected to be an absolute offset. forwardGet :: ReadBinHandle -> IO a -> IO a forwardGet bh get_A = do -- read forward reference @@ -1118,6 +1273,48 @@ forwardGet bh get_A = do seekBinReader bh p_a pure r +-- | @'forwardPutRel' put_A put_B@ outputs A after B but allows A to be read before B +-- by using a forward reference. +-- +-- This forward reference is a relative offset that allows us to skip over the +-- result of 'put_A'. +forwardPutRel :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a,b) +forwardPutRel bh put_A put_B = do + -- write placeholder pointer to A + pre_a <- tellBinWriter bh + put_ bh pre_a + + -- write B + r_b <- put_B + + -- update A's pointer + a <- tellBinWriter bh + putAtRel bh pre_a a + seekBinNoExpandWriter bh a + + -- write A + r_a <- put_A r_b + pure (r_a,r_b) + +-- | Like 'forwardGetRel', but discard the result. +forwardPutRel_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () +forwardPutRel_ bh put_A put_B = void $ forwardPutRel bh put_A put_B + +-- | Read a value stored using a forward reference. +-- +-- The forward reference is expected to be a relative offset. +forwardGetRel :: ReadBinHandle -> IO a -> IO a +forwardGetRel bh get_A = do + -- read forward reference + p <- getRelBin bh + -- store current position + p_a <- tellBinReader bh + -- go read the forward value, then seek back + seekBinReader bh $ makeAbsoluteBin p + r <- get_A + seekBinReader bh p_a + pure r + -- ----------------------------------------------------------------------------- -- Lazy reading/writing @@ -1127,19 +1324,19 @@ lazyPut = lazyPut' put_ lazyGet :: Binary a => ReadBinHandle -> IO a lazyGet = lazyGet' get -lazyPut' :: HasDebugCallStack => (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO () +lazyPut' :: (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO () lazyPut' f bh a = do -- output the obj with a ptr to skip over it: pre_a <- tellBinWriter bh put_ bh pre_a -- save a slot for the ptr f bh a -- dump the object q <- tellBinWriter bh -- q = ptr to after object - putAt bh pre_a q -- fill in slot before a with ptr to q + putAtRel bh pre_a q -- fill in slot before a with ptr to q seekBinWriter bh q -- finally carry on writing at q -lazyGet' :: HasDebugCallStack => (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a +lazyGet' :: (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a lazyGet' f bh = do - p <- get bh -- a BinPtr + p <- getRelBin bh -- a BinPtr p_a <- tellBinReader bh a <- unsafeInterleaveIO $ do -- NB: Use a fresh rbm_off_r variable in the child thread, for thread @@ -1148,7 +1345,7 @@ lazyGet' f bh = do let bh' = bh { rbm_off_r = off_r } seekBinReader bh' p_a f bh' - seekBinReader bh p -- skip over the object for now + seekBinReader bh (makeAbsoluteBin p) -- skip over the object for now return a -- | Serialize the constructor strictly but lazily serialize a value inside a @@ -1284,7 +1481,7 @@ mkReader f = BinaryReader -- | Find the 'BinaryReader' for the 'Binary' instance for the type identified by 'Proxy a'. -- -- If no 'BinaryReader' has been configured before, this function will panic. -findUserDataReader :: forall a . (HasCallStack, Refl.Typeable a) => Proxy a -> ReadBinHandle -> BinaryReader a +findUserDataReader :: forall a . Refl.Typeable a => Proxy a -> ReadBinHandle -> BinaryReader a findUserDataReader query bh = case Map.lookup (Refl.someTypeRep query) (ud_reader_data $ getReaderUserData bh) of Nothing -> panic $ "Failed to find BinaryReader for the key: " ++ show (Refl.someTypeRep query) @@ -1306,7 +1503,7 @@ findUserDataReader query bh = -- | Find the 'BinaryWriter' for the 'Binary' instance for the type identified by 'Proxy a'. -- -- If no 'BinaryWriter' has been configured before, this function will panic. -findUserDataWriter :: forall a . (HasCallStack, Refl.Typeable a) => Proxy a -> WriteBinHandle -> BinaryWriter a +findUserDataWriter :: forall a . Refl.Typeable a => Proxy a -> WriteBinHandle -> BinaryWriter a findUserDataWriter query bh = case Map.lookup (Refl.someTypeRep query) (ud_writer_data $ getWriterUserData bh) of Nothing -> panic $ "Failed to find BinaryWriter for the key: " ++ show (Refl.someTypeRep query) @@ -1442,13 +1639,13 @@ putGenericSymbolTable gen_sym_tab serialiser bh = do mapM_ (\n -> serialiser bh n) (reverse todo) loop snd <$> - (forwardPut bh (const $ readFastMutInt symtab_next >>= put_ bh) $ + (forwardPutRel bh (const $ readFastMutInt symtab_next >>= put_ bh) $ loop) -- | Read the elements of a 'GenericSymbolTable' from disk into a 'SymbolTable'. getGenericSymbolTable :: forall a . (ReadBinHandle -> IO a) -> ReadBinHandle -> IO (SymbolTable a) getGenericSymbolTable deserialiser bh = do - sz <- forwardGet bh (get bh) :: IO Int + sz <- forwardGetRel bh (get bh) :: IO Int mut_arr <- newArray_ (0, sz-1) :: IO (IOArray Int a) forM_ [0..(sz-1)] $ \i -> do f <- deserialiser bh ===================================== hadrian/src/Settings/Builders/Configure.hs ===================================== @@ -15,16 +15,23 @@ configureBuilderArgs = do targetPlatform <- queryTarget targetPlatformTriple buildPlatform <- queryBuild targetPlatformTriple pure $ [ "--enable-shared=no" - , "--with-pic=yes" , "--host=" ++ targetPlatform -- GMP's host is our target , "--build=" ++ buildPlatform ] + -- Disable FFT logic on wasm32, sacrifice + -- performance of multiplying very large operands + -- to save code size + <> [ "--disable-fft" | targetArch == "wasm32" ] -- Disable GMP's alloca usage on wasm32, it may -- cause stack overflow (#22602) due to the -- rather small 64KB default stack size. See -- https://gmplib.org/manual/Build-Options for -- more detailed explanation of this configure -- option. - <> [ "--enable-alloca=malloc-reentrant" | targetArch == "wasm32" ] + <> [ "--enable-alloca=malloc-notreentrant" | targetArch == "wasm32" ] + -- Enable PIC unless target is wasm32, in which + -- case we don't want libgmp.a to be bloated due + -- to PIC overhead. + <> [ "--with-pic=yes" | targetArch /= "wasm32" ] , builder (Configure libffiPath) ? do top <- expr topDirectory ===================================== testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs ===================================== @@ -64,9 +64,10 @@ metaPlugin' _ meta = pprPanic "meta" (showAstData BlankSrcSpan BlankEpAnnotation interfaceLoadPlugin' :: [CommandLineOption] -> ModIface -> IfM lcl ModIface interfaceLoadPlugin' [name, "interface"] iface - = return $ iface { mi_exports = filter (availNotNamedAs name) - (mi_exports iface) - } + = return $ set_mi_exports (filter (availNotNamedAs name) + (mi_exports iface)) + iface + interfaceLoadPlugin' _ iface = return iface availNotNamedAs :: String -> AvailInfo -> Bool ===================================== utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs ===================================== @@ -56,7 +56,7 @@ import GHC.Types.Unique.FM import GHC.Unit.State import GHC.Utils.Binary -import GHC.Iface.Type (IfaceType, getIfaceType, putIfaceType) +import GHC.Iface.Type (IfaceType, putIfaceType) import Haddock.Options (Visibility (..)) @@ -200,7 +200,7 @@ writeInterfaceFile filename iface = do -- write the iface type pointer at the front of the file ifacetype_p <- tellBinWriter bh - putAt bh ifacetype_p_p ifacetype_p + putAtRel bh ifacetype_p_p ifacetype_p seekBinWriter bh ifacetype_p -- write the symbol table itself @@ -208,7 +208,7 @@ writeInterfaceFile filename iface = do -- write the symtab pointer at the front of the file symtab_p <- tellBinWriter bh - putAt bh symtab_p_p symtab_p + putAtRel bh symtab_p_p symtab_p seekBinWriter bh symtab_p -- write the symbol table itself @@ -218,7 +218,7 @@ writeInterfaceFile filename iface = do -- write the dictionary pointer at the fornt of the file dict_p <- tellBinWriter bh - putAt bh dict_p_p dict_p + putAtRel bh dict_p_p dict_p seekBinWriter bh dict_p -- write the dictionary itself View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/60d9a8f0d8ef2de618ee37c8f140b8336af1ed50...534c895517a4a1390a815084ed540d87bc0e384e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/60d9a8f0d8ef2de618ee37c8f140b8336af1ed50...534c895517a4a1390a815084ed540d87bc0e384e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 2 04:21:34 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sun, 02 Jun 2024 00:21:34 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Improve sharing of duplicated values in `ModIface`, fixes #24723 Message-ID: <665bf34e81f94_26e5f73c2e860336a2@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 0cc9b8aa by Fendor at 2024-06-02T00:21:01-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - ef0e1096 by Fendor at 2024-06-02T00:21:01-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12234 T12425 T13035 T13701 T13719 T14697 T15703 T16875 T18730 T9198 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. - - - - - d0675c6b by Cheng Shao at 2024-06-02T00:21:02-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 59a6e3f8 by Cheng Shao at 2024-06-02T00:21:02-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 6304030e by Cheng Shao at 2024-06-02T00:21:03-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 16 changed files: - compiler/GHC.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - hadrian/src/Settings/Builders/Configure.hs - testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -3,6 +3,7 @@ {-# LANGUAGE NondecreasingIndentation, ScopedTypeVariables #-} {-# LANGUAGE TupleSections, NamedFieldPuns #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE PatternSynonyms #-} -- ----------------------------------------------------------------------------- -- @@ -96,7 +97,35 @@ module GHC ( lookupGlobalName, findGlobalAnns, mkNamePprCtxForModule, - ModIface, ModIface_(..), + ModIface, + ModIface_( + mi_module, + mi_sig_of, + mi_hsc_src, + mi_src_hash, + mi_hi_bytes, + mi_deps, + mi_usages, + mi_exports, + mi_used_th, + mi_fixities, + mi_warns, + mi_anns, + mi_insts, + mi_fam_insts, + mi_rules, + mi_decls, + mi_extra_decls, + mi_top_env, + mi_hpc, + mi_trust, + mi_trust_pkg, + mi_complete_matches, + mi_docs, + mi_final_exts, + mi_ext_fields + ), + pattern ModIface, SafeHaskellMode(..), -- * Printing ===================================== compiler/GHC/Iface/Binary.hs ===================================== @@ -18,6 +18,8 @@ module GHC.Iface.Binary ( getSymtabName, CheckHiWay(..), TraceBinIFace(..), + getIfaceWithExtFields, + putIfaceWithExtFields, getWithUserData, putWithUserData, @@ -61,6 +63,8 @@ import Data.Map.Strict (Map) import Data.Word import System.IO.Unsafe import Data.Typeable (Typeable) +import qualified GHC.Data.Strict as Strict +import Data.Function ((&)) -- --------------------------------------------------------------------------- @@ -169,17 +173,29 @@ readBinIface readBinIface profile name_cache checkHiWay traceBinIface hi_path = do (src_hash, bh) <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path - extFields_p <- get bh + mod_iface <- getIfaceWithExtFields name_cache bh - mod_iface <- getWithUserData name_cache bh + return $ mod_iface + & addSourceFingerprint src_hash - seekBinReader bh extFields_p - extFields <- get bh - return mod_iface - { mi_ext_fields = extFields - , mi_src_hash = src_hash - } +getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface +getIfaceWithExtFields name_cache bh = do + -- Start offset for the byte array that contains the serialised 'ModIface'. + start <- tellBinReader bh + extFields_p_rel <- getRelBin bh + + mod_iface <- getWithUserData name_cache bh + + seekBinReaderRel bh extFields_p_rel + extFields <- get bh + -- Store the 'ModIface' byte array, so that we can avoid serialisation if + -- the 'ModIface' isn't modified. + -- See Note [Sharing of ModIface] + modIfaceBinData <- freezeBinHandle bh start + pure $ mod_iface + & set_mi_ext_fields extFields + & set_mi_hi_bytes (FullIfaceBinHandle $ Strict.Just modIfaceBinData) -- | This performs a get action after reading the dictionary and symbol -- table. It is necessary to run this before trying to deserialise any @@ -209,7 +225,7 @@ getTables name_cache bh = do -- add it to the 'ReaderUserData' of 'ReadBinHandle'. decodeReaderTable :: Typeable a => ReaderTable a -> ReadBinHandle -> IO ReadBinHandle decodeReaderTable tbl bh0 = do - table <- Binary.forwardGet bh (getTable tbl bh0) + table <- Binary.forwardGetRel bh (getTable tbl bh0) let binaryReader = mkReaderFromTable tbl table pure $ addReaderToUserData binaryReader bh0 @@ -246,19 +262,24 @@ writeBinIface profile traceBinIface compressionLevel hi_path mod_iface = do put_ bh tag put_ bh (mi_src_hash mod_iface) - extFields_p_p <- tellBinWriter bh - put_ bh extFields_p_p - - putWithUserData traceBinIface compressionLevel bh mod_iface - - extFields_p <- tellBinWriter bh - putAt bh extFields_p_p extFields_p - seekBinWriter bh extFields_p - put_ bh (mi_ext_fields mod_iface) + putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface -- And send the result to the file writeBinMem bh hi_path +-- | Puts the 'ModIface' to the 'WriteBinHandle'. +-- +-- This avoids serialisation of the 'ModIface' if the fields 'mi_hi_bytes' contains a +-- 'Just' value. This field is populated by reading the 'ModIface' using +-- 'getIfaceWithExtFields' and not modifying it in any way afterwards. +putIfaceWithExtFields :: TraceBinIFace -> CompressionIFace -> WriteBinHandle -> ModIface -> IO () +putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface = + case mi_hi_bytes mod_iface of + FullIfaceBinHandle Strict.Nothing -> do + forwardPutRel_ bh (\_ -> put_ bh (mi_ext_fields mod_iface)) $ do + putWithUserData traceBinIface compressionLevel bh mod_iface + FullIfaceBinHandle (Strict.Just binData) -> putFullBinData bh binData + -- | Put a piece of data with an initialised `UserData` field. This -- is necessary if you want to serialise Names or FastStrings. -- It also writes a symbol table and the dictionary. @@ -332,7 +353,7 @@ putAllTables _ [] act = do a <- act pure ([], a) putAllTables bh (x : xs) act = do - (r, (res, a)) <- forwardPut bh (const $ putTable x bh) $ do + (r, (res, a)) <- forwardPutRel bh (const $ putTable x bh) $ do putAllTables bh xs act pure (r : res, a) @@ -484,7 +505,7 @@ to the table we need to deserialise first. What deduplication tables exist and the order of serialisation is currently statically specified in 'putWithTables'. 'putWithTables' also takes care of the serialisation of used deduplication tables. The deserialisation of the deduplication tables happens 'getTables', using 'Binary' utility -functions such as 'forwardGet'. +functions such as 'forwardGetRel'. Here, a visualisation of the table structure we currently have (ignoring 'ExtensibleFields'): @@ -585,7 +606,6 @@ initWriteIfaceType compressionLevel = do putGenericSymTab sym_tab bh ty _ -> putIfaceType bh ty - fullIfaceTypeSerialiser sym_tab bh ty = do put_ bh ifaceTypeSharedByte putGenericSymTab sym_tab bh ty ===================================== compiler/GHC/Iface/Ext/Binary.hs ===================================== @@ -228,7 +228,7 @@ readHieFileContents bh0 name_cache = do get bh1 where get_dictionary tbl bin_handle = do - fsTable <- Binary.forwardGet bin_handle (getTable tbl bin_handle) + fsTable <- Binary.forwardGetRel bin_handle (getTable tbl bin_handle) let fsReader = mkReaderFromTable tbl fsTable bhFs = addReaderToUserData fsReader bin_handle ===================================== compiler/GHC/Iface/Ext/Fields.hs ===================================== @@ -41,7 +41,7 @@ instance Binary ExtensibleFields where -- to point to the start of each payload: forM_ header_entries $ \(field_p_p, dat) -> do field_p <- tellBinWriter bh - putAt bh field_p_p field_p + putAtRel bh field_p_p field_p seekBinWriter bh field_p put_ bh dat @@ -50,11 +50,11 @@ instance Binary ExtensibleFields where -- Get the names and field pointers: header_entries <- replicateM n $ - (,) <$> get bh <*> get bh + (,) <$> get bh <*> getRelBin bh -- Seek to and get each field's payload: fields <- forM header_entries $ \(name, field_p) -> do - seekBinReader bh field_p + seekBinReaderRel bh field_p dat <- get bh return (name, dat) ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -117,6 +117,7 @@ import System.FilePath import System.Directory import GHC.Driver.Env.KnotVars import GHC.Iface.Errors.Types +import Data.Function ((&)) {- ************************************************************************ @@ -515,14 +516,12 @@ loadInterface doc_str mod from ; new_eps_anns <- tcIfaceAnnotations (mi_anns iface) ; new_eps_complete_matches <- tcIfaceCompleteMatches (mi_complete_matches iface) - ; let { final_iface = iface { - mi_decls = panic "No mi_decls in PIT", - mi_insts = panic "No mi_insts in PIT", - mi_fam_insts = panic "No mi_fam_insts in PIT", - mi_rules = panic "No mi_rules in PIT", - mi_anns = panic "No mi_anns in PIT" - } - } + ; let final_iface = iface + & set_mi_decls (panic "No mi_decls in PIT") + & set_mi_insts (panic "No mi_insts in PIT") + & set_mi_fam_insts (panic "No mi_fam_insts in PIT") + & set_mi_rules (panic "No mi_rules in PIT") + & set_mi_anns (panic "No mi_anns in PIT") ; let bad_boot = mi_boot iface == IsBoot && isJust (lookupKnotVars (if_rec_types gbl_env) mod) @@ -1018,13 +1017,13 @@ readIface dflags name_cache wanted_mod file_path = do -- See Note [GHC.Prim] in primops.txt.pp. ghcPrimIface :: ModIface ghcPrimIface - = empty_iface { - mi_exports = ghcPrimExports, - mi_decls = [], - mi_fixities = fixities, - mi_final_exts = (mi_final_exts empty_iface){ mi_fix_fn = mkIfaceFixCache fixities }, - mi_docs = Just ghcPrimDeclDocs -- See Note [GHC.Prim Docs] - } + = empty_iface + & set_mi_exports ghcPrimExports + & set_mi_decls [] + & set_mi_fixities fixities + & set_mi_final_exts ((mi_final_exts empty_iface){ mi_fix_fn = mkIfaceFixCache fixities }) + & set_mi_docs (Just ghcPrimDeclDocs) -- See Note [GHC.Prim Docs] + where empty_iface = emptyFullModIface gHC_PRIM @@ -1108,7 +1107,7 @@ pprModIfaceSimple unit_state iface = -- -- The UnitState is used to pretty-print units pprModIface :: UnitState -> ModIface -> SDoc -pprModIface unit_state iface at ModIface{ mi_final_exts = exts } +pprModIface unit_state iface = vcat [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) @@ -1149,6 +1148,7 @@ pprModIface unit_state iface at ModIface{ mi_final_exts = exts } , text "extensible fields:" $$ nest 2 (pprExtensibleFields (mi_ext_fields iface)) ] where + exts = mi_final_exts iface pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" pp_hsc_src HsSrcFile = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -69,10 +69,13 @@ import GHC.Types.HpcInfo import GHC.Types.CompleteMatch import GHC.Types.SourceText import GHC.Types.SrcLoc ( unLoc ) +import GHC.Types.Name.Cache import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Utils.Logger +import GHC.Utils.Binary +import GHC.Iface.Binary import GHC.Data.FastString import GHC.Data.Maybe @@ -142,14 +145,47 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos = do full_iface <- {-# SCC "addFingerprints" #-} - addFingerprints hsc_env partial_iface{ mi_decls = decls } + addFingerprints hsc_env (set_mi_decls decls partial_iface) -- Debug printing let unit_state = hsc_units hsc_env putDumpFileMaybe (hsc_logger hsc_env) Opt_D_dump_hi "FINAL INTERFACE" FormatText (pprModIface unit_state full_iface) + final_iface <- shareIface (hsc_NC hsc_env) (flagsToIfCompression $ hsc_dflags hsc_env) full_iface + return final_iface - return full_iface +-- | Compress an 'ModIface' and share as many values as possible, depending on the 'CompressionIFace' level. +-- See Note [Sharing of ModIface]. +-- +-- We compress the 'ModIface' by serialising the 'ModIface' to an in-memory byte array, and then deserialising it. +-- The deserialisation will deduplicate certain values depending on the 'CompressionIFace' level. +-- See Note [Deduplication during iface binary serialisation] for how we do that. +-- +-- Additionally, we cache the serialised byte array, so if the 'ModIface' is not modified +-- after calling 'shareIface', 'writeBinIface' will reuse that buffer without serialising the 'ModIface' again. +-- Modifying the 'ModIface' forces us to re-serialise it again. +shareIface :: NameCache -> CompressionIFace -> ModIface -> IO ModIface +shareIface _ NormalCompression mi = do + -- In 'NormalCompression', the sharing isn't reducing the memory usage, as 'Name's and 'FastString's are + -- already shared, and at this compression level, we don't compress/share anything else. + -- Thus, for a brief moment we simply double the memory residency for no reason. + -- Therefore, we only try to share expensive values if the compression mode is higher than + -- 'NormalCompression' + pure mi +shareIface nc compressionLevel mi = do + bh <- openBinMem initBinMemSize + start <- tellBinWriter bh + putIfaceWithExtFields QuietBinIFace compressionLevel bh mi + rbh <- shrinkBinBuffer bh + seekBinReader rbh start + res <- getIfaceWithExtFields nc rbh + let resiface = restoreFromOldModIface mi res + forceModIface resiface + return resiface + +-- | Initial ram buffer to allocate for writing interface files. +initBinMemSize :: Int +initBinMemSize = 1024 * 1024 -- 1 MB updateDecl :: [IfaceDecl] -> Maybe StgCgInfos -> Maybe CmmCgInfos -> [IfaceDecl] updateDecl decls Nothing Nothing = decls @@ -304,40 +340,40 @@ mkIface_ hsc_env icomplete_matches = map mkIfaceCompleteMatch complete_matches !rdrs = maybeGlobalRdrEnv rdr_env - ModIface { - mi_module = this_mod, + emptyPartialModIface this_mod -- Need to record this because it depends on the -instantiated-with flag -- which could change - mi_sig_of = if semantic_mod == this_mod - then Nothing - else Just semantic_mod, - mi_hsc_src = hsc_src, - mi_deps = deps, - mi_usages = usages, - mi_exports = mkIfaceExports exports, + & set_mi_sig_of (if semantic_mod == this_mod + then Nothing + else Just semantic_mod) + & set_mi_hsc_src hsc_src + & set_mi_deps deps + & set_mi_usages usages + & set_mi_exports (mkIfaceExports exports) -- Sort these lexicographically, so that -- the result is stable across compilations - mi_insts = sortBy cmp_inst iface_insts, - mi_fam_insts = sortBy cmp_fam_inst iface_fam_insts, - mi_rules = sortBy cmp_rule iface_rules, - - mi_fixities = fixities, - mi_warns = warns, - mi_anns = annotations, - mi_top_env = rdrs, - mi_used_th = used_th, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_hpc = isHpcUsed hpc_info, - mi_trust = trust_info, - mi_trust_pkg = pkg_trust_req, - mi_complete_matches = icomplete_matches, - mi_docs = docs, - mi_final_exts = (), - mi_ext_fields = emptyExtensibleFields, - mi_src_hash = ms_hs_hash mod_summary - } + & set_mi_insts (sortBy cmp_inst iface_insts) + & set_mi_fam_insts (sortBy cmp_fam_inst iface_fam_insts) + & set_mi_rules (sortBy cmp_rule iface_rules) + + & set_mi_fixities fixities + & set_mi_warns warns + & set_mi_anns annotations + & set_mi_top_env rdrs + & set_mi_used_th used_th + & set_mi_decls decls + & set_mi_extra_decls extra_decls + & set_mi_hpc (isHpcUsed hpc_info) + & set_mi_trust trust_info + & set_mi_trust_pkg pkg_trust_req + & set_mi_complete_matches (icomplete_matches) + & set_mi_docs docs + & set_mi_final_exts () + & set_mi_ext_fields emptyExtensibleFields + & set_mi_src_hash (ms_hs_hash mod_summary) + & set_mi_hi_bytes PartialIfaceBinHandle + where cmp_rule = lexicalCompareFS `on` ifRuleName -- Compare these lexicographically by OccName, *not* by unique, @@ -513,3 +549,22 @@ That is, in Y, In the result of mkIfaceExports, the names are grouped by defining module, so we may need to split up a single Avail into multiple ones. -} + +{- +Note [Sharing of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +A 'ModIface' contains many duplicated values such as 'Name', 'FastString' and 'IfaceType'. +'Name's and 'FastString's are already deduplicated by default using the 'NameCache' and +'FastStringTable' respectively. +However, 'IfaceType' can be quite expensive in terms of memory usage. +To improve the sharing of 'IfaceType', we introduced deduplication tables during +serialisation of 'ModIface', see Note [Deduplication during iface binary serialisation]. + +We can improve the sharing of 'ModIface' at run-time as well, by serialising the 'ModIface' to +an in-memory buffer, and then deserialising it again. +This implicitly shares duplicated values. + +To avoid re-serialising the 'ModIface' when writing it to disk, we save the serialised 'ModIface' buffer +in 'mi_hi_bytes_' field of said 'ModIface'. This buffer is written to disk directly in 'putIfaceWithExtFields'. +If we have to modify the 'ModIface' after 'shareIface' is called, the buffer needs to be discarded. +-} ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -1281,7 +1281,8 @@ addFingerprints hsc_env iface0 , mi_fix_fn = fix_fn , mi_hash_fn = lookupOccEnv local_env } - final_iface = iface0 { mi_decls = sorted_decls, mi_extra_decls = sorted_extra_decls, mi_final_exts = final_iface_exts } + final_iface = completePartialModIface iface0 + sorted_decls sorted_extra_decls final_iface_exts -- return final_iface ===================================== compiler/GHC/Iface/Rename.hs ===================================== @@ -44,6 +44,7 @@ import GHC.Utils.Panic import qualified Data.Traversable as T import Data.IORef +import Data.Function ((&)) tcRnMsgMaybe :: IO (Either (Messages TcRnMessage) a) -> TcM a tcRnMsgMaybe do_this = do @@ -108,13 +109,14 @@ rnModIface hsc_env insts nsubst iface = deps <- rnDependencies (mi_deps iface) -- TODO: -- mi_rules - return iface { mi_module = mod - , mi_sig_of = sig_of - , mi_insts = insts - , mi_fam_insts = fams - , mi_exports = exports - , mi_decls = decls - , mi_deps = deps } + return $ iface + & set_mi_module mod + & set_mi_sig_of sig_of + & set_mi_insts insts + & set_mi_fam_insts fams + & set_mi_exports exports + & set_mi_decls decls + & set_mi_deps deps -- | Rename just the exports of a 'ModIface'. Useful when we're doing -- shaping prior to signature merging. ===================================== compiler/GHC/Tc/Errors/Hole.hs ===================================== @@ -76,7 +76,7 @@ import GHC.Tc.Utils.Unify ( tcSubTypeSigma ) import GHC.HsToCore.Docs ( extractDocs ) import GHC.Hs.Doc -import GHC.Unit.Module.ModIface ( ModIface_(..) ) +import GHC.Unit.Module.ModIface ( mi_docs ) import GHC.Iface.Load ( loadInterfaceForName ) import GHC.Builtin.Utils (knownKeyNames) ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -1562,7 +1562,8 @@ lookupDeclDoc nm = do -- Wasn't in the current module. Try searching other external ones! mIface <- getExternalModIface nm case mIface of - Just ModIface { mi_docs = Just Docs{docs_decls = dmap} } -> + Just iface + | Just Docs{docs_decls = dmap} <- mi_docs iface -> pure $ renderHsDocStrings . map hsDocString <$> lookupUniqMap dmap nm _ -> pure Nothing @@ -1578,7 +1579,8 @@ lookupArgDoc i nm = do Nothing -> do mIface <- getExternalModIface nm case mIface of - Just ModIface { mi_docs = Just Docs{docs_args = amap} } -> + Just iface + | Just Docs{docs_args = amap} <- mi_docs iface-> pure $ renderHsDocString . hsDocString <$> (lookupUniqMap amap nm >>= IntMap.lookup i) _ -> pure Nothing ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -87,6 +87,7 @@ import Control.Monad import Data.List (find) import GHC.Iface.Errors.Types +import Data.Function ((&)) checkHsigDeclM :: ModIface -> TyThing -> TyThing -> TcRn () checkHsigDeclM sig_iface sig_thing real_thing = do @@ -369,8 +370,8 @@ tcRnMergeSignatures hsc_env hpm orig_tcg_env iface = thinModIface :: [AvailInfo] -> ModIface -> ModIface thinModIface avails iface = - iface { - mi_exports = avails, + iface + & set_mi_exports avails -- mi_fixities = ..., -- mi_warns = ..., -- mi_anns = ..., @@ -378,10 +379,9 @@ thinModIface avails iface = -- perhaps there might be two IfaceTopBndr that are the same -- OccName but different Name. Requires better understanding -- of invariants here. - mi_decls = exported_decls ++ non_exported_decls ++ dfun_decls + & set_mi_decls (exported_decls ++ non_exported_decls ++ dfun_decls) -- mi_insts = ..., -- mi_fam_insts = ..., - } where decl_pred occs decl = nameOccName (ifName decl) `elemOccSet` occs filter_decls occs = filter (decl_pred occs . snd) (mi_decls iface) ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -4,10 +4,68 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE PatternSynonyms #-} + module GHC.Unit.Module.ModIface ( ModIface - , ModIface_ (..) + , ModIface_ + ( mi_module + , mi_sig_of + , mi_hsc_src + , mi_deps + , mi_usages + , mi_exports + , mi_used_th + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_extra_decls + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_hpc + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_final_exts + , mi_ext_fields + , mi_src_hash + , mi_hi_bytes + ) + , pattern ModIface + , restoreFromOldModIface + , addSourceFingerprint + , set_mi_module + , set_mi_sig_of + , set_mi_hsc_src + , set_mi_src_hash + , set_mi_hi_bytes + , set_mi_deps + , set_mi_usages + , set_mi_exports + , set_mi_used_th + , set_mi_fixities + , set_mi_warns + , set_mi_anns + , set_mi_insts + , set_mi_fam_insts + , set_mi_rules + , set_mi_decls + , set_mi_extra_decls + , set_mi_top_env + , set_mi_hpc + , set_mi_trust + , set_mi_trust_pkg + , set_mi_complete_matches + , set_mi_docs + , set_mi_final_exts + , set_mi_ext_fields + , completePartialModIface + , IfaceBinHandle(..) , PartialModIface , ModIfaceBackend (..) , IfaceDeclExts @@ -47,6 +105,7 @@ import GHC.Types.Fixity import GHC.Types.Fixity.Env import GHC.Types.HpcInfo import GHC.Types.Name +import GHC.Types.Name.Reader (IfGlobalRdrEnv) import GHC.Types.SafeHaskell import GHC.Types.SourceFile import GHC.Types.Unique.DSet @@ -59,7 +118,7 @@ import GHC.Utils.Binary import Control.DeepSeq import Control.Exception -import GHC.Types.Name.Reader (IfGlobalRdrEnv) +import qualified GHC.Data.Strict as Strict {- Note [Interface file stages] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -141,7 +200,17 @@ type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where IfaceBackendExts 'ModIfaceCore = () IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend - +-- | In-memory byte array representation of a 'ModIface'. +-- +-- See Note [Sharing of ModIface] for why we need this. +data IfaceBinHandle (phase :: ModIfacePhase) where + -- | A partial 'ModIface' cannot be serialised to disk. + PartialIfaceBinHandle :: IfaceBinHandle 'ModIfaceCore + -- | Optional 'FullBinData' that can be serialised to disk directly. + -- + -- See Note [Private fields in ModIface] for when this fields needs to be cleared + -- (e.g., set to 'Nothing'). + FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal -- | A 'ModIface' plus a 'ModDetails' summarises everything we know -- about a compiled module. The 'ModIface' is the stuff *before* linking, @@ -155,62 +224,65 @@ type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where -- -- See Note [Strictness in ModIface] to learn about why some fields are -- strict and others are not. +-- +-- See Note [Private fields in ModIface] to learn why we don't export any of the +-- fields. data ModIface_ (phase :: ModIfacePhase) - = ModIface { - mi_module :: !Module, -- ^ Name of the module we are for - mi_sig_of :: !(Maybe Module), -- ^ Are we a sig of another mod? + = PrivateModIface { + mi_module_ :: !Module, -- ^ Name of the module we are for + mi_sig_of_ :: !(Maybe Module), -- ^ Are we a sig of another mod? - mi_hsc_src :: !HscSource, -- ^ Boot? Signature? + mi_hsc_src_ :: !HscSource, -- ^ Boot? Signature? - mi_deps :: Dependencies, + mi_deps_ :: Dependencies, -- ^ The dependencies of the module. This is -- consulted for directly-imported modules, but not -- for anything else (hence lazy) - mi_usages :: [Usage], + mi_usages_ :: [Usage], -- ^ Usages; kept sorted so that it's easy to decide -- whether to write a new iface file (changing usages -- doesn't affect the hash of this module) -- NOT STRICT! we read this field lazily from the interface file -- It is *only* consulted by the recompilation checker - mi_exports :: ![IfaceExport], + mi_exports_ :: ![IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier -- Records the modules that are the declaration points for things -- exported by this module, and the 'OccName's of those things - mi_used_th :: !Bool, + mi_used_th_ :: !Bool, -- ^ Module required TH splices when it was compiled. -- This disables recompilation avoidance (see #481). - mi_fixities :: [(OccName,Fixity)], + mi_fixities_ :: [(OccName,Fixity)], -- ^ Fixities -- NOT STRICT! we read this field lazily from the interface file - mi_warns :: IfaceWarnings, + mi_warns_ :: IfaceWarnings, -- ^ Warnings -- NOT STRICT! we read this field lazily from the interface file - mi_anns :: [IfaceAnnotation], + mi_anns_ :: [IfaceAnnotation], -- ^ Annotations -- NOT STRICT! we read this field lazily from the interface file - mi_decls :: [IfaceDeclExts phase], + mi_decls_ :: [IfaceDeclExts phase], -- ^ Type, class and variable declarations -- The hash of an Id changes if its fixity or deprecations change -- (as well as its type of course) -- Ditto data constructors, class operations, except that -- the hash of the parent class/tycon changes - mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], + mi_extra_decls_ :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], -- ^ Extra variable definitions which are **NOT** exposed but when -- combined with mi_decls allows us to restart code generation. -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] - mi_top_env :: !(Maybe IfaceTopEnv), + mi_top_env_ :: !(Maybe IfaceTopEnv), -- ^ Just enough information to reconstruct the top level environment in -- the /original source/ code for this module. which -- is NOT the same as mi_exports, nor mi_decls (which @@ -226,36 +298,36 @@ data ModIface_ (phase :: ModIfacePhase) -- 'HomeModInfo', but that leads to more plumbing. -- Instance declarations and rules - mi_insts :: [IfaceClsInst], -- ^ Sorted class instance - mi_fam_insts :: [IfaceFamInst], -- ^ Sorted family instances - mi_rules :: [IfaceRule], -- ^ Sorted rules + mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance + mi_fam_insts_ :: [IfaceFamInst], -- ^ Sorted family instances + mi_rules_ :: [IfaceRule], -- ^ Sorted rules - mi_hpc :: !AnyHpcUsage, + mi_hpc_ :: !AnyHpcUsage, -- ^ True if this program uses Hpc at any point in the program. - mi_trust :: !IfaceTrustInfo, + mi_trust_ :: !IfaceTrustInfo, -- ^ Safe Haskell Trust information for this module. - mi_trust_pkg :: !Bool, + mi_trust_pkg_ :: !Bool, -- ^ Do we require the package this module resides in be trusted -- to trust this module? This is used for the situation where a -- module is Safe (so doesn't require the package be trusted -- itself) but imports some trustworthy modules from its own -- package (which does require its own package be trusted). -- See Note [Trust Own Package] in GHC.Rename.Names - mi_complete_matches :: ![IfaceCompleteMatch], + mi_complete_matches_ :: ![IfaceCompleteMatch], - mi_docs :: !(Maybe Docs), + mi_docs_ :: !(Maybe Docs), -- ^ Docstrings and related data for use by haddock, the ghci -- @:doc@ command, and other tools. -- -- @Just _@ @<=>@ the module was built with @-haddock at . - mi_final_exts :: !(IfaceBackendExts phase), + mi_final_exts_ :: !(IfaceBackendExts phase), -- ^ Either `()` or `ModIfaceBackend` for -- a fully instantiated interface. - mi_ext_fields :: !ExtensibleFields, + mi_ext_fields_ :: !ExtensibleFields, -- ^ Additional optional fields, where the Map key represents -- the field name, resulting in a (size, serialized data) pair. -- Because the data is intended to be serialized through the @@ -264,8 +336,13 @@ data ModIface_ (phase :: ModIfacePhase) -- chosen over `ByteString`s. -- - mi_src_hash :: !Fingerprint + mi_src_hash_ :: !Fingerprint, -- ^ Hash of the .hs source, used for recompilation checking. + mi_hi_bytes_ :: !(IfaceBinHandle phase) + -- ^ A serialised in-memory buffer of this 'ModIface'. + -- If this handle is given, we can avoid serialising the 'ModIface' + -- when writing this 'ModIface' to disk, and write this buffer to disk instead. + -- See Note [Sharing of ModIface]. } -- Enough information to reconstruct the top level environment for a module @@ -354,34 +431,40 @@ renameFreeHoles fhs insts = -- See Note [Strictness in ModIface] about where we use lazyPut vs put instance Binary ModIface where - put_ bh (ModIface { - mi_module = mod, - mi_sig_of = sig_of, - mi_hsc_src = hsc_src, - mi_src_hash = _src_hash, -- Don't `put_` this in the instance + put_ bh (PrivateModIface { + mi_module_ = mod, + mi_sig_of_ = sig_of, + mi_hsc_src_ = hsc_src, + mi_src_hash_ = _src_hash, -- Don't `put_` this in the instance -- because we are going to write it -- out separately in the actual file - mi_deps = deps, - mi_usages = usages, - mi_exports = exports, - mi_used_th = used_th, - mi_fixities = fixities, - mi_warns = warns, - mi_anns = anns, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_insts = insts, - mi_fam_insts = fam_insts, - mi_rules = rules, - mi_hpc = hpc_info, - mi_trust = trust, - mi_trust_pkg = trust_pkg, - mi_complete_matches = complete_matches, - mi_docs = docs, - mi_ext_fields = _ext_fields, -- Don't `put_` this in the instance so we + mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself + -- may contain an in-memory byte array buffer for this + -- 'ModIface'. If we used 'put_' on this 'ModIface', then + -- we likely have a good reason, and do not want to reuse + -- the byte array. + -- See Note [Private fields in ModIface] + mi_deps_ = deps, + mi_usages_ = usages, + mi_exports_ = exports, + mi_used_th_ = used_th, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_anns_ = anns, + mi_decls_ = decls, + mi_extra_decls_ = extra_decls, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_hpc_ = hpc_info, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, + mi_complete_matches_ = complete_matches, + mi_docs_ = docs, + mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file - mi_final_exts = ModIfaceBackend { + mi_final_exts_ = ModIfaceBackend { mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, mi_flag_hash = flag_hash, @@ -455,34 +538,39 @@ instance Binary ModIface where trust_pkg <- get bh complete_matches <- get bh docs <- lazyGetMaybe bh - return (ModIface { - mi_module = mod, - mi_sig_of = sig_of, - mi_hsc_src = hsc_src, - mi_src_hash = fingerprint0, -- placeholder because this is dealt + return (PrivateModIface { + mi_module_ = mod, + mi_sig_of_ = sig_of, + mi_hsc_src_ = hsc_src, + mi_src_hash_ = fingerprint0, -- placeholder because this is dealt -- with specially when the file is read - mi_deps = deps, - mi_usages = usages, - mi_exports = exports, - mi_used_th = used_th, - mi_anns = anns, - mi_fixities = fixities, - mi_warns = warns, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_top_env = Nothing, - mi_insts = insts, - mi_fam_insts = fam_insts, - mi_rules = rules, - mi_hpc = hpc_info, - mi_trust = trust, - mi_trust_pkg = trust_pkg, + mi_hi_bytes_ = + -- We can't populate this field here, as we are + -- missing the 'mi_ext_fields_' field, which is + -- handled in 'getIfaceWithExtFields'. + FullIfaceBinHandle Strict.Nothing, + mi_deps_ = deps, + mi_usages_ = usages, + mi_exports_ = exports, + mi_used_th_ = used_th, + mi_anns_ = anns, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_decls_ = decls, + mi_extra_decls_ = extra_decls, + mi_top_env_ = Nothing, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_hpc_ = hpc_info, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, -- And build the cached values - mi_complete_matches = complete_matches, - mi_docs = docs, - mi_ext_fields = emptyExtensibleFields, -- placeholder because this is dealt + mi_complete_matches_ = complete_matches, + mi_docs_ = docs, + mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read - mi_final_exts = ModIfaceBackend { + mi_final_exts_ = ModIfaceBackend { mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, mi_flag_hash = flag_hash, @@ -499,42 +587,46 @@ instance Binary ModIface where mi_hash_fn = mkIfaceHashCache decls }}) + -- | The original names declared of a certain module that are exported type IfaceExport = AvailInfo emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod - = ModIface { mi_module = mod, - mi_sig_of = Nothing, - mi_hsc_src = HsSrcFile, - mi_src_hash = fingerprint0, - mi_deps = noDependencies, - mi_usages = [], - mi_exports = [], - mi_used_th = False, - mi_fixities = [], - mi_warns = IfWarnSome [] [], - mi_anns = [], - mi_insts = [], - mi_fam_insts = [], - mi_rules = [], - mi_decls = [], - mi_extra_decls = Nothing, - mi_top_env = Nothing, - mi_hpc = False, - mi_trust = noIfaceTrustInfo, - mi_trust_pkg = False, - mi_complete_matches = [], - mi_docs = Nothing, - mi_final_exts = (), - mi_ext_fields = emptyExtensibleFields - } + = PrivateModIface + { mi_module_ = mod, + mi_sig_of_ = Nothing, + mi_hsc_src_ = HsSrcFile, + mi_src_hash_ = fingerprint0, + mi_hi_bytes_ = PartialIfaceBinHandle, + mi_deps_ = noDependencies, + mi_usages_ = [], + mi_exports_ = [], + mi_used_th_ = False, + mi_fixities_ = [], + mi_warns_ = IfWarnSome [] [], + mi_anns_ = [], + mi_insts_ = [], + mi_fam_insts_ = [], + mi_rules_ = [], + mi_decls_ = [], + mi_extra_decls_ = Nothing, + mi_top_env_ = Nothing, + mi_hpc_ = False, + mi_trust_ = noIfaceTrustInfo, + mi_trust_pkg_ = False, + mi_complete_matches_ = [], + mi_docs_ = Nothing, + mi_final_exts_ = (), + mi_ext_fields_ = emptyExtensibleFields + } emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) - { mi_decls = [] - , mi_final_exts = ModIfaceBackend + { mi_decls_ = [] + , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + , mi_final_exts_ = ModIfaceBackend { mi_iface_hash = fingerprint0, mi_mod_hash = fingerprint0, mi_flag_hash = fingerprint0, @@ -569,36 +661,38 @@ emptyIfaceHashCache _occ = Nothing instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (ModIface{ mi_module, mi_sig_of, mi_hsc_src, mi_deps, mi_usages - , mi_exports, mi_used_th, mi_fixities, mi_warns, mi_anns - , mi_decls, mi_extra_decls, mi_top_env, mi_insts - , mi_fam_insts, mi_rules, mi_hpc, mi_trust, mi_trust_pkg - , mi_complete_matches, mi_docs, mi_final_exts - , mi_ext_fields, mi_src_hash }) - = rnf mi_module - `seq` rnf mi_sig_of - `seq` mi_hsc_src - `seq` mi_deps - `seq` mi_usages - `seq` mi_exports - `seq` rnf mi_used_th - `seq` mi_fixities - `seq` rnf mi_warns - `seq` rnf mi_anns - `seq` rnf mi_decls - `seq` rnf mi_extra_decls - `seq` rnf mi_top_env - `seq` rnf mi_insts - `seq` rnf mi_fam_insts - `seq` rnf mi_rules - `seq` rnf mi_hpc - `seq` mi_trust - `seq` rnf mi_trust_pkg - `seq` rnf mi_complete_matches - `seq` rnf mi_docs - `seq` mi_final_exts - `seq` mi_ext_fields - `seq` rnf mi_src_hash + rnf (PrivateModIface + { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_, mi_usages_ + , mi_exports_, mi_used_th_, mi_fixities_, mi_warns_, mi_anns_ + , mi_decls_, mi_extra_decls_, mi_top_env_, mi_insts_ + , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_ + , mi_complete_matches_, mi_docs_, mi_final_exts_ + , mi_ext_fields_, mi_src_hash_ }) + = rnf mi_module_ + `seq` rnf mi_sig_of_ + `seq` mi_hsc_src_ + `seq` mi_hi_bytes_ + `seq` mi_deps_ + `seq` mi_usages_ + `seq` mi_exports_ + `seq` rnf mi_used_th_ + `seq` mi_fixities_ + `seq` rnf mi_warns_ + `seq` rnf mi_anns_ + `seq` rnf mi_decls_ + `seq` rnf mi_extra_decls_ + `seq` rnf mi_top_env_ + `seq` rnf mi_insts_ + `seq` rnf mi_fam_insts_ + `seq` rnf mi_rules_ + `seq` rnf mi_hpc_ + `seq` mi_trust_ + `seq` rnf mi_trust_pkg_ + `seq` rnf mi_complete_matches_ + `seq` rnf mi_docs_ + `seq` mi_final_exts_ + `seq` mi_ext_fields_ + `seq` rnf mi_src_hash_ `seq` () instance NFData (ModIfaceBackend) where @@ -638,5 +732,286 @@ type WhetherHasOrphans = Bool -- | Does this module define family instances? type WhetherHasFamInst = Bool +-- ---------------------------------------------------------------------------- +-- Modify a 'ModIface'. +-- ---------------------------------------------------------------------------- + +{- +Note [Private fields in ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The fields of 'ModIface' are private, e.g., not exported, to make the API +impossible to misuse. A 'ModIface' can be "compressed" in-memory using +'shareIface', which serialises the 'ModIface' to an in-memory buffer. +This has the advantage of reducing memory usage of 'ModIface', reducing the +overall memory usage of GHC. +See Note [Sharing of ModIface]. + +This in-memory buffer can be reused, if and only if the 'ModIface' is not +modified after it has been "compressed"/shared via 'shareIface'. Instead of +serialising 'ModIface', we simply write the in-memory buffer to disk directly. + +However, we can't rely that a 'ModIface' isn't modified after 'shareIface' has +been called. Thus, we make all fields of 'ModIface' private and modification +only happens via exported update functions, such as 'set_mi_decls'. +These functions unconditionally clear any in-memory buffer if used, forcing us +to serialise the 'ModIface' to disk again. +-} + +-- | Given a 'PartialModIface', turn it into a 'ModIface' by completing +-- missing fields. +completePartialModIface :: PartialModIface + -> [(Fingerprint, IfaceDecl)] + -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] + -> ModIfaceBackend + -> ModIface +completePartialModIface partial decls extra_decls final_exts = partial + { mi_decls_ = decls + , mi_extra_decls_ = extra_decls + , mi_final_exts_ = final_exts + , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + } + +-- | Add a source fingerprint to a 'ModIface_' without invalidating the byte array +-- buffer 'mi_hi_bytes'. +-- This is a variant of 'set_mi_src_hash' which does invalidate the buffer. +-- +-- The 'mi_src_hash' is computed outside of 'ModIface_' based on the 'ModSummary'. +addSourceFingerprint :: Fingerprint -> ModIface_ phase -> ModIface_ phase +addSourceFingerprint val iface = iface { mi_src_hash_ = val } + +-- | Copy fields that aren't serialised to disk to the new 'ModIface_'. +-- This includes especially hashes that are usually stored in the interface +-- file header and 'mi_top_env'. +-- +-- We need this function after calling 'shareIface', to make sure the +-- 'ModIface_' doesn't lose any information. This function does not discard +-- the in-memory byte array buffer 'mi_hi_bytes'. +restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase +restoreFromOldModIface old new = new + { mi_top_env_ = mi_top_env_ old + , mi_hsc_src_ = mi_hsc_src_ old + , mi_src_hash_ = mi_src_hash_ old + } + +set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase +set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } + +set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase +set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } + +set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase +set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } + +set_mi_src_hash :: Fingerprint -> ModIface_ phase -> ModIface_ phase +set_mi_src_hash val iface = clear_mi_hi_bytes $ iface { mi_src_hash_ = val } + +set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase +set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } + +set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase +set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } + +set_mi_usages :: [Usage] -> ModIface_ phase -> ModIface_ phase +set_mi_usages val iface = clear_mi_hi_bytes $ iface { mi_usages_ = val } +set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase +set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } + +set_mi_used_th :: Bool -> ModIface_ phase -> ModIface_ phase +set_mi_used_th val iface = clear_mi_hi_bytes $ iface { mi_used_th_ = val } + +set_mi_fixities :: [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase +set_mi_fixities val iface = clear_mi_hi_bytes $ iface { mi_fixities_ = val } + +set_mi_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase +set_mi_warns val iface = clear_mi_hi_bytes $ iface { mi_warns_ = val } + +set_mi_anns :: [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase +set_mi_anns val iface = clear_mi_hi_bytes $ iface { mi_anns_ = val } + +set_mi_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase +set_mi_insts val iface = clear_mi_hi_bytes $ iface { mi_insts_ = val } + +set_mi_fam_insts :: [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase +set_mi_fam_insts val iface = clear_mi_hi_bytes $ iface { mi_fam_insts_ = val } + +set_mi_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase +set_mi_rules val iface = clear_mi_hi_bytes $ iface { mi_rules_ = val } + +set_mi_decls :: [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase +set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls_ = val } + +set_mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase +set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val } + +set_mi_top_env :: Maybe IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } + +set_mi_hpc :: AnyHpcUsage -> ModIface_ phase -> ModIface_ phase +set_mi_hpc val iface = clear_mi_hi_bytes $ iface { mi_hpc_ = val } + +set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase +set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val } + +set_mi_trust_pkg :: Bool -> ModIface_ phase -> ModIface_ phase +set_mi_trust_pkg val iface = clear_mi_hi_bytes $ iface { mi_trust_pkg_ = val } + +set_mi_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase +set_mi_complete_matches val iface = clear_mi_hi_bytes $ iface { mi_complete_matches_ = val } + +set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase +set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } + +set_mi_final_exts :: IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase +set_mi_final_exts val iface = clear_mi_hi_bytes $ iface { mi_final_exts_ = val } + +set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase +set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } + +-- | Invalidate any byte array buffer we might have. +clear_mi_hi_bytes :: ModIface_ phase -> ModIface_ phase +clear_mi_hi_bytes iface = iface + { mi_hi_bytes_ = case mi_hi_bytes iface of + PartialIfaceBinHandle -> PartialIfaceBinHandle + FullIfaceBinHandle _ -> FullIfaceBinHandle Strict.Nothing + } + +-- ---------------------------------------------------------------------------- +-- 'ModIface' pattern synonyms to keep breakage low. +-- ---------------------------------------------------------------------------- + +{- +Note [Inline Pattern synonym of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The introduction of the 'ModIface' pattern synonym originally caused an increase +in allocated bytes in multiple performance tests. +In some benchmarks, it was a 2~3% increase. + +Without {-# INLINE ModIface #-}, the generated core reveals the reason for this increase. +We show the core for the 'mi_module' record selector: + +@ + mi_module + = \ @phase iface -> $w$mModIface iface mi_module1 + + $w$mModIface + = \ @phase iface cont -> + case iface of + { PrivateModIface a b ... z -> + cont + a + b + ... + z + } + + mi_module1 + = \ @phase + a + _ + ... + _ -> + a +@ + +Thus, we can see the '$w$mModIface' is not inlined, leading to an increase in +the allocated bytes. + +However, with the pragma, the correct core is generated: + +@ + mi_module = mi_module_ +@ + +-} +-- See Note [Inline Pattern synonym of ModIface] for why we have all these +-- inline pragmas. +{-# INLINE ModIface #-} +{-# INLINE mi_module #-} +{-# INLINE mi_sig_of #-} +{-# INLINE mi_hsc_src #-} +{-# INLINE mi_deps #-} +{-# INLINE mi_usages #-} +{-# INLINE mi_exports #-} +{-# INLINE mi_used_th #-} +{-# INLINE mi_fixities #-} +{-# INLINE mi_warns #-} +{-# INLINE mi_anns #-} +{-# INLINE mi_decls #-} +{-# INLINE mi_extra_decls #-} +{-# INLINE mi_top_env #-} +{-# INLINE mi_insts #-} +{-# INLINE mi_fam_insts #-} +{-# INLINE mi_rules #-} +{-# INLINE mi_hpc #-} +{-# INLINE mi_trust #-} +{-# INLINE mi_trust_pkg #-} +{-# INLINE mi_complete_matches #-} +{-# INLINE mi_docs #-} +{-# INLINE mi_final_exts #-} +{-# INLINE mi_ext_fields #-} +{-# INLINE mi_src_hash #-} +{-# INLINE mi_hi_bytes #-} + +pattern ModIface :: + Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] -> + [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> + [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> + Maybe IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> + AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> + IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> + ModIface_ phase +pattern ModIface + { mi_module + , mi_sig_of + , mi_hsc_src + , mi_deps + , mi_usages + , mi_exports + , mi_used_th + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_extra_decls + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_hpc + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_final_exts + , mi_ext_fields + , mi_src_hash + , mi_hi_bytes + } <- PrivateModIface + { mi_module_ = mi_module + , mi_sig_of_ = mi_sig_of + , mi_hsc_src_ = mi_hsc_src + , mi_deps_ = mi_deps + , mi_usages_ = mi_usages + , mi_exports_ = mi_exports + , mi_used_th_ = mi_used_th + , mi_fixities_ = mi_fixities + , mi_warns_ = mi_warns + , mi_anns_ = mi_anns + , mi_decls_ = mi_decls + , mi_extra_decls_ = mi_extra_decls + , mi_top_env_ = mi_top_env + , mi_insts_ = mi_insts + , mi_fam_insts_ = mi_fam_insts + , mi_rules_ = mi_rules + , mi_hpc_ = mi_hpc + , mi_trust_ = mi_trust + , mi_trust_pkg_ = mi_trust_pkg + , mi_complete_matches_ = mi_complete_matches + , mi_docs_ = mi_docs + , mi_final_exts_ = mi_final_exts + , mi_ext_fields_ = mi_ext_fields + , mi_src_hash_ = mi_src_hash + , mi_hi_bytes_ = mi_hi_bytes + } ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -19,7 +19,7 @@ -- http://www.cs.york.ac.uk/fp/nhc98/ module GHC.Utils.Binary - ( {-type-} Bin, + ( {-type-} Bin, RelBin(..), getRelBin, {-class-} Binary(..), {-type-} ReadBinHandle, WriteBinHandle, SymbolTable, Dictionary, @@ -32,10 +32,14 @@ module GHC.Utils.Binary seekBinWriter, seekBinReader, + seekBinReaderRel, tellBinReader, tellBinWriter, castBin, withBinBuffer, + freezeWriteHandle, + shrinkBinBuffer, + thawReadHandle, foldGet, foldGet', @@ -44,7 +48,9 @@ module GHC.Utils.Binary readBinMemN, putAt, getAt, + putAtRel, forwardPut, forwardPut_, forwardGet, + forwardPutRel, forwardPutRel_, forwardGetRel, -- * For writing instances putByte, @@ -99,6 +105,8 @@ module GHC.Utils.Binary BindingName(..), simpleBindingNameWriter, simpleBindingNameReader, + FullBinData(..), freezeBinHandle, thawBinHandle, putFullBinData, + BinArray, ) where import GHC.Prelude @@ -107,6 +115,7 @@ import Language.Haskell.Syntax.Module.Name (ModuleName(..)) import {-# SOURCE #-} GHC.Types.Name (Name) import GHC.Data.FastString +import GHC.Data.TrieMap import GHC.Utils.Panic.Plain import GHC.Types.Unique.FM import GHC.Data.FastMutInt @@ -115,7 +124,6 @@ import GHC.Types.SrcLoc import GHC.Types.Unique import qualified GHC.Data.Strict as Strict import GHC.Utils.Outputable( JoinPointHood(..) ) -import GHC.Utils.Misc ( HasCallStack, HasDebugCallStack ) import Control.DeepSeq import Control.Monad ( when, (<$!>), unless, forM_, void ) @@ -123,7 +131,7 @@ import Foreign hiding (shiftL, shiftR, void) import Data.Array import Data.Array.IO import Data.Array.Unsafe -import Data.ByteString (ByteString) +import Data.ByteString (ByteString, copy) import Data.Coerce import qualified Data.ByteString.Internal as BS import qualified Data.ByteString.Unsafe as BS @@ -152,8 +160,6 @@ import GHC.ForeignPtr ( unsafeWithForeignPtr ) import Unsafe.Coerce (unsafeCoerce) -import GHC.Data.TrieMap - type BinArray = ForeignPtr Word8 #if !MIN_VERSION_base(4,15,0) @@ -193,6 +199,62 @@ dataHandle (BinData size bin) = do handleData :: WriteBinHandle -> IO BinData handleData (WriteBinMem _ ixr _ binr) = BinData <$> readFastMutInt ixr <*> readIORef binr +--------------------------------------------------------------- +-- FullBinData +--------------------------------------------------------------- + +-- | 'FullBinData' stores a slice to a 'BinArray'. +-- +-- It requires less memory than 'ReadBinHandle', and can be constructed from +-- a 'ReadBinHandle' via 'freezeBinHandle' and turned back into a +-- 'ReadBinHandle' using 'thawBinHandle'. +-- Additionally, the byte array slice can be put into a 'WriteBinHandle' without extra +-- conversions via 'putFullBinData'. +data FullBinData = FullBinData + { fbd_readerUserData :: ReaderUserData + -- ^ 'ReaderUserData' that can be used to resume reading. + , fbd_off_s :: {-# UNPACK #-} !Int + -- ^ start offset + , fbd_off_e :: {-# UNPACK #-} !Int + -- ^ end offset + , fbd_size :: {-# UNPACK #-} !Int + -- ^ total buffer size + , fbd_buffer :: {-# UNPACK #-} !BinArray + } + +-- Equality and Ord assume that two distinct buffers are different, even if they compare the same things. +instance Eq FullBinData where + (FullBinData _ b c d e) == (FullBinData _ b1 c1 d1 e1) = b == b1 && c == c1 && d == d1 && e == e1 + +instance Ord FullBinData where + compare (FullBinData _ b c d e) (FullBinData _ b1 c1 d1 e1) = + compare b b1 `mappend` compare c c1 `mappend` compare d d1 `mappend` compare e e1 + +-- | Write the 'FullBinData' slice into the 'WriteBinHandle'. +putFullBinData :: WriteBinHandle -> FullBinData -> IO () +putFullBinData bh (FullBinData _ o1 o2 _sz ba) = do + let sz = o2 - o1 + putPrim bh sz $ \dest -> + unsafeWithForeignPtr (ba `plusForeignPtr` o1) $ \orig -> + copyBytes dest orig sz + +-- | Freeze a 'ReadBinHandle' and a start index into a 'FullBinData'. +-- +-- 'FullBinData' stores a slice starting from the 'Bin a' location to the current +-- offset of the 'ReadBinHandle'. +freezeBinHandle :: ReadBinHandle -> Bin a -> IO FullBinData +freezeBinHandle (ReadBinMem user_data ixr sz binr) (BinPtr start) = do + ix <- readFastMutInt ixr + pure (FullBinData user_data start ix sz binr) + +-- | Turn the 'FullBinData' into a 'ReadBinHandle', setting the 'ReadBinHandle' +-- offset to the start of the 'FullBinData' and restore the 'ReaderUserData' that was +-- obtained from 'freezeBinHandle'. +thawBinHandle :: FullBinData -> IO ReadBinHandle +thawBinHandle (FullBinData user_data ix _end sz ba) = do + ixr <- newFastMutInt ix + return $ ReadBinMem user_data ixr sz ba + --------------------------------------------------------------- -- BinHandle --------------------------------------------------------------- @@ -286,9 +348,47 @@ unsafeUnpackBinBuffer (BS.BS arr len) = do newtype Bin a = BinPtr Int deriving (Eq, Ord, Show, Bounded) +-- | Like a 'Bin' but is used to store relative offset pointers. +-- Relative offset pointers store a relative location, but also contain an +-- anchor that allow to obtain the absolute offset. +data RelBin a = RelBin + { relBin_anchor :: {-# UNPACK #-} !(Bin a) + -- ^ Absolute position from where we read 'relBin_offset'. + , relBin_offset :: {-# UNPACK #-} !(RelBinPtr a) + -- ^ Relative offset to 'relBin_anchor'. + -- The absolute position of the 'RelBin' is @relBin_anchor + relBin_offset@ + } + deriving (Eq, Ord, Show, Bounded) + +-- | A 'RelBinPtr' is like a 'Bin', but contains a relative offset pointer +-- instead of an absolute offset. +newtype RelBinPtr a = RelBinPtr (Bin a) + deriving (Eq, Ord, Show, Bounded) + castBin :: Bin a -> Bin b castBin (BinPtr i) = BinPtr i +-- | Read a relative offset location and wrap it in 'RelBin'. +-- +-- The resulting 'RelBin' can be translated into an absolute offset location using +-- 'makeAbsoluteBin' +getRelBin :: ReadBinHandle -> IO (RelBin a) +getRelBin bh = do + start <- tellBinReader bh + off <- get bh + pure $ RelBin start off + +makeAbsoluteBin :: RelBin a -> Bin a +makeAbsoluteBin (RelBin (BinPtr !start) (RelBinPtr (BinPtr !offset))) = + BinPtr $ start + offset + +makeRelativeBin :: RelBin a -> RelBinPtr a +makeRelativeBin (RelBin _ offset) = offset + +toRelBin :: Bin (RelBinPtr a) -> Bin a -> RelBin a +toRelBin (BinPtr !start) (BinPtr !goal) = + RelBin (BinPtr start) (RelBinPtr $ BinPtr $ goal - start) + --------------------------------------------------------------- -- class Binary --------------------------------------------------------------- @@ -309,6 +409,9 @@ class Binary a where putAt :: Binary a => WriteBinHandle -> Bin a -> a -> IO () putAt bh p x = do seekBinWriter bh p; put_ bh x; return () +putAtRel :: WriteBinHandle -> Bin (RelBinPtr a) -> Bin a -> IO () +putAtRel bh from to = putAt bh from (makeRelativeBin $ toRelBin from to) + getAt :: Binary a => ReadBinHandle -> Bin a -> IO a getAt bh p = do seekBinReader bh p; get bh @@ -327,6 +430,44 @@ openBinMem size , wbm_arr_r = arr_r } +-- | Freeze the given 'WriteBinHandle' and turn it into an equivalent 'ReadBinHandle'. +-- +-- The current offset of the 'WriteBinHandle' is maintained in the new 'ReadBinHandle'. +freezeWriteHandle :: WriteBinHandle -> IO ReadBinHandle +freezeWriteHandle wbm = do + rbm_off_r <- newFastMutInt =<< readFastMutInt (wbm_off_r wbm) + rbm_sz_r <- readFastMutInt (wbm_sz_r wbm) + rbm_arr_r <- readIORef (wbm_arr_r wbm) + pure $ ReadBinMem + { rbm_userData = noReaderUserData + , rbm_off_r = rbm_off_r + , rbm_sz_r = rbm_sz_r + , rbm_arr_r = rbm_arr_r + } + +-- | Copy the BinBuffer to a new BinBuffer which is exactly the right size. +-- This performs a copy of the underlying buffer. +-- The buffer may be truncated if the offset is not at the end of the written +-- output. +-- +-- UserData is also discarded during the copy +-- You should just use this when translating a Put handle into a Get handle. +shrinkBinBuffer :: WriteBinHandle -> IO ReadBinHandle +shrinkBinBuffer bh = withBinBuffer bh $ \bs -> do + unsafeUnpackBinBuffer (copy bs) + +thawReadHandle :: ReadBinHandle -> IO WriteBinHandle +thawReadHandle rbm = do + wbm_off_r <- newFastMutInt =<< readFastMutInt (rbm_off_r rbm) + wbm_sz_r <- newFastMutInt (rbm_sz_r rbm) + wbm_arr_r <- newIORef (rbm_arr_r rbm) + pure $ WriteBinMem + { wbm_userData = noWriterUserData + , wbm_off_r = wbm_off_r + , wbm_sz_r = wbm_sz_r + , wbm_arr_r = wbm_arr_r + } + tellBinWriter :: WriteBinHandle -> IO (Bin a) tellBinWriter (WriteBinMem _ r _ _) = do ix <- readFastMutInt r; return (BinPtr ix) @@ -358,6 +499,13 @@ seekBinReader (ReadBinMem _ ix_r sz_r _) (BinPtr !p) = do then panic "seekBinReader: seek out of range" else writeFastMutInt ix_r p +seekBinReaderRel :: ReadBinHandle -> RelBin a -> IO () +seekBinReaderRel (ReadBinMem _ ix_r sz_r _) relBin = do + let (BinPtr !p) = makeAbsoluteBin relBin + if (p > sz_r) + then panic "seekBinReaderRel: seek out of range" + else writeFastMutInt ix_r p + writeBinMem :: WriteBinHandle -> FilePath -> IO () writeBinMem (WriteBinMem _ ix_r _ arr_r) fn = do h <- openBinaryFile fn WriteMode @@ -1078,12 +1226,17 @@ instance Binary (Bin a) where put_ bh (BinPtr i) = putWord32 bh (fromIntegral i :: Word32) get bh = do i <- getWord32 bh; return (BinPtr (fromIntegral (i :: Word32))) +-- Instance uses fixed-width encoding to allow inserting +-- Bin placeholders in the stream. +instance Binary (RelBinPtr a) where + put_ bh (RelBinPtr i) = put_ bh i + get bh = RelBinPtr <$> get bh -- ----------------------------------------------------------------------------- -- Forward reading/writing --- | "forwardPut put_A put_B" outputs A after B but allows A to be read before B --- by using a forward reference +-- | @'forwardPut' put_A put_B@ outputs A after B but allows A to be read before B +-- by using a forward reference. forwardPut :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a,b) forwardPut bh put_A put_B = do -- write placeholder pointer to A @@ -1106,6 +1259,8 @@ forwardPut_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () forwardPut_ bh put_A put_B = void $ forwardPut bh put_A put_B -- | Read a value stored using a forward reference +-- +-- The forward reference is expected to be an absolute offset. forwardGet :: ReadBinHandle -> IO a -> IO a forwardGet bh get_A = do -- read forward reference @@ -1118,6 +1273,48 @@ forwardGet bh get_A = do seekBinReader bh p_a pure r +-- | @'forwardPutRel' put_A put_B@ outputs A after B but allows A to be read before B +-- by using a forward reference. +-- +-- This forward reference is a relative offset that allows us to skip over the +-- result of 'put_A'. +forwardPutRel :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a,b) +forwardPutRel bh put_A put_B = do + -- write placeholder pointer to A + pre_a <- tellBinWriter bh + put_ bh pre_a + + -- write B + r_b <- put_B + + -- update A's pointer + a <- tellBinWriter bh + putAtRel bh pre_a a + seekBinNoExpandWriter bh a + + -- write A + r_a <- put_A r_b + pure (r_a,r_b) + +-- | Like 'forwardGetRel', but discard the result. +forwardPutRel_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () +forwardPutRel_ bh put_A put_B = void $ forwardPutRel bh put_A put_B + +-- | Read a value stored using a forward reference. +-- +-- The forward reference is expected to be a relative offset. +forwardGetRel :: ReadBinHandle -> IO a -> IO a +forwardGetRel bh get_A = do + -- read forward reference + p <- getRelBin bh + -- store current position + p_a <- tellBinReader bh + -- go read the forward value, then seek back + seekBinReader bh $ makeAbsoluteBin p + r <- get_A + seekBinReader bh p_a + pure r + -- ----------------------------------------------------------------------------- -- Lazy reading/writing @@ -1127,19 +1324,19 @@ lazyPut = lazyPut' put_ lazyGet :: Binary a => ReadBinHandle -> IO a lazyGet = lazyGet' get -lazyPut' :: HasDebugCallStack => (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO () +lazyPut' :: (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO () lazyPut' f bh a = do -- output the obj with a ptr to skip over it: pre_a <- tellBinWriter bh put_ bh pre_a -- save a slot for the ptr f bh a -- dump the object q <- tellBinWriter bh -- q = ptr to after object - putAt bh pre_a q -- fill in slot before a with ptr to q + putAtRel bh pre_a q -- fill in slot before a with ptr to q seekBinWriter bh q -- finally carry on writing at q -lazyGet' :: HasDebugCallStack => (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a +lazyGet' :: (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a lazyGet' f bh = do - p <- get bh -- a BinPtr + p <- getRelBin bh -- a BinPtr p_a <- tellBinReader bh a <- unsafeInterleaveIO $ do -- NB: Use a fresh rbm_off_r variable in the child thread, for thread @@ -1148,7 +1345,7 @@ lazyGet' f bh = do let bh' = bh { rbm_off_r = off_r } seekBinReader bh' p_a f bh' - seekBinReader bh p -- skip over the object for now + seekBinReader bh (makeAbsoluteBin p) -- skip over the object for now return a -- | Serialize the constructor strictly but lazily serialize a value inside a @@ -1284,7 +1481,7 @@ mkReader f = BinaryReader -- | Find the 'BinaryReader' for the 'Binary' instance for the type identified by 'Proxy a'. -- -- If no 'BinaryReader' has been configured before, this function will panic. -findUserDataReader :: forall a . (HasCallStack, Refl.Typeable a) => Proxy a -> ReadBinHandle -> BinaryReader a +findUserDataReader :: forall a . Refl.Typeable a => Proxy a -> ReadBinHandle -> BinaryReader a findUserDataReader query bh = case Map.lookup (Refl.someTypeRep query) (ud_reader_data $ getReaderUserData bh) of Nothing -> panic $ "Failed to find BinaryReader for the key: " ++ show (Refl.someTypeRep query) @@ -1306,7 +1503,7 @@ findUserDataReader query bh = -- | Find the 'BinaryWriter' for the 'Binary' instance for the type identified by 'Proxy a'. -- -- If no 'BinaryWriter' has been configured before, this function will panic. -findUserDataWriter :: forall a . (HasCallStack, Refl.Typeable a) => Proxy a -> WriteBinHandle -> BinaryWriter a +findUserDataWriter :: forall a . Refl.Typeable a => Proxy a -> WriteBinHandle -> BinaryWriter a findUserDataWriter query bh = case Map.lookup (Refl.someTypeRep query) (ud_writer_data $ getWriterUserData bh) of Nothing -> panic $ "Failed to find BinaryWriter for the key: " ++ show (Refl.someTypeRep query) @@ -1442,13 +1639,13 @@ putGenericSymbolTable gen_sym_tab serialiser bh = do mapM_ (\n -> serialiser bh n) (reverse todo) loop snd <$> - (forwardPut bh (const $ readFastMutInt symtab_next >>= put_ bh) $ + (forwardPutRel bh (const $ readFastMutInt symtab_next >>= put_ bh) $ loop) -- | Read the elements of a 'GenericSymbolTable' from disk into a 'SymbolTable'. getGenericSymbolTable :: forall a . (ReadBinHandle -> IO a) -> ReadBinHandle -> IO (SymbolTable a) getGenericSymbolTable deserialiser bh = do - sz <- forwardGet bh (get bh) :: IO Int + sz <- forwardGetRel bh (get bh) :: IO Int mut_arr <- newArray_ (0, sz-1) :: IO (IOArray Int a) forM_ [0..(sz-1)] $ \i -> do f <- deserialiser bh ===================================== hadrian/src/Settings/Builders/Configure.hs ===================================== @@ -15,16 +15,23 @@ configureBuilderArgs = do targetPlatform <- queryTarget targetPlatformTriple buildPlatform <- queryBuild targetPlatformTriple pure $ [ "--enable-shared=no" - , "--with-pic=yes" , "--host=" ++ targetPlatform -- GMP's host is our target , "--build=" ++ buildPlatform ] + -- Disable FFT logic on wasm32, sacrifice + -- performance of multiplying very large operands + -- to save code size + <> [ "--disable-fft" | targetArch == "wasm32" ] -- Disable GMP's alloca usage on wasm32, it may -- cause stack overflow (#22602) due to the -- rather small 64KB default stack size. See -- https://gmplib.org/manual/Build-Options for -- more detailed explanation of this configure -- option. - <> [ "--enable-alloca=malloc-reentrant" | targetArch == "wasm32" ] + <> [ "--enable-alloca=malloc-notreentrant" | targetArch == "wasm32" ] + -- Enable PIC unless target is wasm32, in which + -- case we don't want libgmp.a to be bloated due + -- to PIC overhead. + <> [ "--with-pic=yes" | targetArch /= "wasm32" ] , builder (Configure libffiPath) ? do top <- expr topDirectory ===================================== testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs ===================================== @@ -64,9 +64,10 @@ metaPlugin' _ meta = pprPanic "meta" (showAstData BlankSrcSpan BlankEpAnnotation interfaceLoadPlugin' :: [CommandLineOption] -> ModIface -> IfM lcl ModIface interfaceLoadPlugin' [name, "interface"] iface - = return $ iface { mi_exports = filter (availNotNamedAs name) - (mi_exports iface) - } + = return $ set_mi_exports (filter (availNotNamedAs name) + (mi_exports iface)) + iface + interfaceLoadPlugin' _ iface = return iface availNotNamedAs :: String -> AvailInfo -> Bool ===================================== utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs ===================================== @@ -56,7 +56,7 @@ import GHC.Types.Unique.FM import GHC.Unit.State import GHC.Utils.Binary -import GHC.Iface.Type (IfaceType, getIfaceType, putIfaceType) +import GHC.Iface.Type (IfaceType, putIfaceType) import Haddock.Options (Visibility (..)) @@ -200,7 +200,7 @@ writeInterfaceFile filename iface = do -- write the iface type pointer at the front of the file ifacetype_p <- tellBinWriter bh - putAt bh ifacetype_p_p ifacetype_p + putAtRel bh ifacetype_p_p ifacetype_p seekBinWriter bh ifacetype_p -- write the symbol table itself @@ -208,7 +208,7 @@ writeInterfaceFile filename iface = do -- write the symtab pointer at the front of the file symtab_p <- tellBinWriter bh - putAt bh symtab_p_p symtab_p + putAtRel bh symtab_p_p symtab_p seekBinWriter bh symtab_p -- write the symbol table itself @@ -218,7 +218,7 @@ writeInterfaceFile filename iface = do -- write the dictionary pointer at the fornt of the file dict_p <- tellBinWriter bh - putAt bh dict_p_p dict_p + putAtRel bh dict_p_p dict_p seekBinWriter bh dict_p -- write the dictionary itself View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/534c895517a4a1390a815084ed540d87bc0e384e...6304030eacb0bd3acab5f8589dd25e3f286c65d9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/534c895517a4a1390a815084ed540d87bc0e384e...6304030eacb0bd3acab5f8589dd25e3f286c65d9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 2 06:27:32 2024 From: gitlab at gitlab.haskell.org (Brandon Chinn (@brandonchinn178)) Date: Sun, 02 Jun 2024 02:27:32 -0400 Subject: [Git][ghc/ghc][wip/multiline-strings] 99 commits: Add highlighting for inline-code snippets in haddock Message-ID: <665c10d4c6e90_26e5f74c0e76c50510@gitlab.mail> Brandon Chinn pushed to branch wip/multiline-strings at Glasgow Haskell Compiler / GHC Commits: 646d30ab by Jade at 2024-05-18T19:23:31+02:00 Add highlighting for inline-code snippets in haddock - - - - - 64459a3e by Hécate Moonlight at 2024-05-19T08:42:27-04:00 haddock: Add a .readthedocs.yml file for online documentation - - - - - 7d3d9bbf by Serge S. Gulin at 2024-05-19T18:47:05+00:00 Unicode: General Category size test (related #24789) Added trivial size performance test which involves unicode general category usage via `read`. The `read` itself uses general category to detect spaces. The purpose for this test is to measure outcome of applying improvements at General Category representation in code discussed at #24789. - - - - - 8e04efcf by Alan Zimmerman at 2024-05-19T21:29:34-04:00 EPA: Remove redundant code Remove unused epAnnAnns function various cases for showAstData that no longer exist - - - - - 071d7a1e by Rodrigo Mesquita at 2024-05-20T10:55:16-04:00 Improve docs on closed type families in hs-boots Fixes #24776 - - - - - d9e2c119 by Torsten Schmits at 2024-05-20T10:55:52-04:00 Use default deviation for large-project test This new performance test has the purpose of detecting regressions in complexity in relation to the number of modules in a project, so 1% deviation is way too small to avoid false positives. - - - - - 20b0136a by Ben Gamari at 2024-05-22T00:31:39-04:00 ghcup-metadata: Various fixes from 9.10.1 Use Debian 12/x86-64, Debian 10/aarch64, and Debian 11/aarch64 bindists where possible. - - - - - 6838a7c3 by Sylvain Henry at 2024-05-22T00:32:23-04:00 Reverse arguments to stgCallocBytes (fix #24828) - - - - - f50f46c3 by Fendor at 2024-05-22T00:32:59-04:00 Add log messages for Iface serialisation compression level Fix the label of the number of 'IfaceType' entries in the log message. Add log message for the compression level that is used to serialise a an interface file. Adds `Outputable` instance for 'CompressionIFace'. - - - - - 3bad5d55 by Hécate Moonlight at 2024-05-22T00:33:40-04:00 base: Update doctests outputs ghc-internal: Update doctests outputs - - - - - 9317c6fb by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix the testsuites of the haddock-library - Apply all the metadata revisions from Hackage to the cabal file. - Fix the `ParserSpec.hs` file in the `spec` testsuite of haddock-library. - Make `CHANGES.md` an extra-doc-file instead of an extra-source-file. - - - - - 54073b02 by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix parser of @since pragma The testsuite contained tests for annotations of the form `@since foo-bar-0.5.0`, but the parser was written incorrectly. - - - - - ede6ede3 by Matthew Pickering at 2024-05-22T00:34:57-04:00 Fix nightly pages job It seems likely broken by 9f99126a which moved `index.html` from the root folder into `docs/` folder. Fixes #24840 - - - - - b7bcf729 by Cheng Shao at 2024-05-22T00:35:32-04:00 autoconf: remove unused context diff check This patch removes redundant autoconf check for the context diff program given it isn't actually been used anywhere, especially since make removal. - - - - - ea2fe66e by Hécate Moonlight at 2024-05-22T00:36:13-04:00 haddock: Rework the contributing guide - - - - - 0f302a94 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 haddock: Add module relationships diagrams of haddock-api and haddock-library - - - - - d1a9f34f by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add instructions - - - - - b880ee80 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add SVG outputs - - - - - 6d7e6ad8 by Ben Gamari at 2024-05-22T13:40:05-04:00 rts: Fix size of StgOrigThunkInfo frames Previously the entry code of the `stg_orig_thunk` frame failed to account for the size of the profiling header as it hard-coded the frame size. Fix this. Fixes #24809. - - - - - c645fe40 by Fendor at 2024-05-22T13:40:05-04:00 Add regression test T24809 for stg_orig_thunk_info_frame size - - - - - 4181aa40 by Andreas Klebinger at 2024-05-22T13:40:42-04:00 bindists: Check for existence of share folder before trying to copy it. This folder isn't distributed in windows bindists A lack of doing so resulted us copying loads of files twice. - - - - - d216510e by Matthew Pickering at 2024-05-22T13:40:42-04:00 Remove ad-hoc installation of mingw toolchain in relocatable bindists This reverts 616ac30026e8dd7d2ebb98d92dde071eedf5d951 The choice about whether to install mingw is taken in the installation makefile. This is also broken on non-windows systems. The actual issue was the EnableDistroToolchain variable wasn't declared in mk/config.mk and therefore the check to install mingw was failing. - - - - - 7b4c1998 by Cheng Shao at 2024-05-22T21:52:52-04:00 testsuite: fix T17920 for wasm backend T17920 was marked as fragile on wasm before; it can be trivially fixed by avoiding calling variadic printf() in cmm. - - - - - c739383b by Cheng Shao at 2024-05-22T21:53:29-04:00 testsuite: bump T22744 timeout to 5x - - - - - c4c6d714 by Cheng Shao at 2024-05-22T21:54:06-04:00 testsuite: don't attempt to detect host cpu features when testing cross ghc The testsuite driver CPU feature detection logic only detects host CPU and only makes sense when we are not testing a cross GHC. - - - - - 3d9e4ce6 by Simon Peyton Jones at 2024-05-22T21:54:43-04:00 Better skolemisation As #24810 showed, it is (a little) better to skolemise en-bloc, so that Note [Let-bound skolems] fires more often. See Note [Skolemisation en bloc] in GHC.Tc.Utils.Instantiate. - - - - - a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00 Add missing parenthesizePat in cvtp We need to ensure that the output of `cvtp` is parenthesized (at precedence `sigPrec`) so that any pattern signatures with a surrounding pattern signature can parse correctly. Fixes #24837. - - - - - 4bb2a7cc by Hécate Moonlight at 2024-05-22T21:55:59-04:00 [base] Document the memory overhead of ByteArray Add a diagram that shows the constituent parts of a ByteArray and their memory overhead. - - - - - 8b2a016a by Hécate Moonlight at 2024-05-22T21:56:38-04:00 Haddock: Add MR template for Haddock - - - - - ead75532 by Peter Trommler at 2024-05-23T02:28:05-04:00 PPC: Support ELF v2 on powerpc64 big-endian Detect ELF v2 on PowerPC 64-bit systems. Check for `_CALL_ELF` preprocessor macro. Fixes #21191 - - - - - 9d4c10f2 by Hécate Kleidukos at 2024-05-23T02:28:44-04:00 gitlab: Add @Kleidukos to CODEOWNERS for utils/haddock - - - - - 28e64170 by Preetham Gujjula at 2024-05-23T07:20:48-04:00 haddock: Add cabal-fmt to tools for `make style` - - - - - 00126a89 by Andrei Borzenkov at 2024-05-23T07:21:24-04:00 haddock: fix verbosity option parsing - - - - - a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00 base: specify tie-breaking behavior of min, max, and related list/Foldable functions - - - - - bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00 cmm: add word <-> double/float bitcast - closes: #25331 This is the last step in the project plan described in #25331. This commit: - adds bitcast operands for x86_64, LLVM, aarch64 - For PPC and i386 we resort to using the cmm implementations - renames conversion MachOps from Conv to Round|Truncate - - - - - f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor Some functions in StgToByteCode were filtering out void arguments. However, StgToByteCode is called after unarisation: the void arguments should have been removed earlier. Instead of filtering out, we assert that the args are non-void. - - - - - 03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor `layoutNativeCall` was always called with a `primRepCmmType platform` callback. Hence we can put it inside of `layoutNativeCall` rather than repeat it. - - - - - 27c430f3 by David Binder at 2024-05-24T07:52:38-04:00 haddock: Remove compatibility shims for GHC < 8.4 from haddock-library - - - - - 8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00 compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs This patch makes the STG->Cmm backend avoid saving foreign call target to local when there are no caller-save GlobalRegs. Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a foreign call, we unconditionally save the foreign call target to a temporary local first, then rely on cmmSink to clean it up later, which only happens with -fcmm-sink (implied by -O) and not in unoptimized code. And this is troublesome for the wasm backend NCG, which needs to infer a foreign call target symbol's type signature from the Cmm call site. Previously, the NCG has been emitting incorrect type signatures for unoptimized code, which happens to work with `wasm-ld` most of the time, but this is never future-proof against upstream toolchain updates, and it causes horrible breakages when LTO objects are included in linker input. Hence this patch. - - - - - 986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00 testsuite: add callee-no-local regression test - - - - - 52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00 Fix HasCallStack leftovers from !12514 / #24726 - - - - - c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00 user_guide: Fix typo in MultiWayIf chapter Close #24829 - - - - - bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - 1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Fix changelog reference to setBacktraceMechanismState (cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d) - - - - - 43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00 Float/double unboxed literal support for HexFloatLiterals (fix #22155) - - - - - 4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00 Improve test labels for binary interface file size tests Test labels for binary interface file sizes are hard to read and overly verbose at the same time. Extend the name for the metric title, but shorten it in the actual comparison table. - - - - - 14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00 Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present" This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa. - - - - - f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00 Fix default hyperlinked sources pattern Previously this didn't include the `%M` token which manifested as broken links to the hyperlinked sources of reexports of declarations defined in other packages. Fixes haddock#1628. (cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36) - - - - - 42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00 Make DocPaths a proper data type (cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c) - - - - - 53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00 haddock: Bump version to 2.30 (cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602) - - - - - e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00 haddock-api: allow base 4.20 and ghc 9.11 - - - - - e294f7a2 by PHO at 2024-05-24T12:17:55-04:00 Add a flag "threaded" for building haddock with the threaded RTS GHC isn't guaranteed to have a threaded RTS. There should be a way to build it with the vanilla one. (cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d) - - - - - 51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00 Update ticky counter event docs. Add the info about the info table address and json fields. Fixes #23200 - - - - - 98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00 Export extractPromotedList (#24866) This can be useful in plugins. - - - - - 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - 2485a4ed by Brandon Chinn at 2024-06-01T23:27:20-07:00 Add MultilineStrings extension - - - - - 58a5edad by Brandon Chinn at 2024-06-01T23:27:21-07:00 Add test cases for MultilineStrings - - - - - 897542e8 by Brandon Chinn at 2024-06-01T23:27:21-07:00 Break out common lex_magic_hash logic for strings and chars - - - - - 94c5b05a by Brandon Chinn at 2024-06-01T23:27:21-07:00 Factor out string processing functions - - - - - e5dc408d by Brandon Chinn at 2024-06-01T23:27:21-07:00 Implement MultilineStrings (#24390) Updates haddock submodule for new ITmultiline constructor - - - - - 39805baf by Brandon Chinn at 2024-06-01T23:27:21-07:00 Add docs for MultilineStrings - - - - - 5209d145 by Brandon Chinn at 2024-06-01T23:27:21-07:00 Address feedback - - - - - 30 changed files: - .gitignore - .gitlab-ci.yml - + .gitlab/merge_request_templates/Haddock.md - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - CODEOWNERS - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a86f342e0f857dcb0fe42904cf7f590be7bc227d...5209d145f7f04def92091adb311a33cdbf7cf29a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a86f342e0f857dcb0fe42904cf7f590be7bc227d...5209d145f7f04def92091adb311a33cdbf7cf29a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 2 10:17:49 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sun, 02 Jun 2024 06:17:49 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T7773-fragile-wasm Message-ID: <665c46cd1c5ca_210f645cbc507742c@gitlab.mail> Cheng Shao pushed new branch wip/T7773-fragile-wasm at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T7773-fragile-wasm You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 2 11:01:51 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sun, 02 Jun 2024 07:01:51 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: hadrian: disable PIC for in-tree GMP on wasm32 Message-ID: <665c511f157ce_210f64b8257c84159@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 2dab6368 by Cheng Shao at 2024-06-02T07:01:38-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - b6c5b6ee by Cheng Shao at 2024-06-02T07:01:38-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 26bf70a8 by Cheng Shao at 2024-06-02T07:01:38-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - dd0c1732 by ARATA Mizuki at 2024-06-02T07:01:44-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 6 changed files: - compiler/GHC/Driver/Pipeline/Execute.hs - hadrian/src/Settings/Builders/Configure.hs - + testsuite/tests/driver/T24839.hs - + testsuite/tests/driver/T24839.stdout - testsuite/tests/driver/all.T - + testsuite/tests/driver/t24839_sub.S Changes: ===================================== compiler/GHC/Driver/Pipeline/Execute.hs ===================================== @@ -290,6 +290,7 @@ runGenericAsPhase :: (Logger -> DynFlags -> [Option] -> IO ()) -> [Option] -> Bo runGenericAsPhase run_as extra_opts with_cpp pipe_env hsc_env location input_fn = do let dflags = hsc_dflags hsc_env let logger = hsc_logger hsc_env + let unit_env = hsc_unit_env hsc_env let cmdline_include_paths = includePaths dflags let pic_c_flags = picCCOpts dflags @@ -300,16 +301,21 @@ runGenericAsPhase run_as extra_opts with_cpp pipe_env hsc_env location input_fn -- might be a hierarchical module. createDirectoryIfMissing True (takeDirectory output_fn) - let global_includes = [ GHC.SysTools.Option ("-I" ++ p) - | p <- includePathsGlobal cmdline_include_paths ] - let local_includes = [ GHC.SysTools.Option ("-iquote" ++ p) - | p <- includePathsQuote cmdline_include_paths ++ - includePathsQuoteImplicit cmdline_include_paths] + -- add package include paths + all_includes <- if not with_cpp + then pure [] + else do + pkg_include_dirs <- mayThrowUnitErr (collectIncludeDirs <$> preloadUnitsInfo unit_env) + let global_includes = [ GHC.SysTools.Option ("-I" ++ p) + | p <- includePathsGlobal cmdline_include_paths ++ pkg_include_dirs] + let local_includes = [ GHC.SysTools.Option ("-iquote" ++ p) + | p <- includePathsQuote cmdline_include_paths ++ includePathsQuoteImplicit cmdline_include_paths] + pure (local_includes ++ global_includes) let runAssembler inputFilename outputFilename = withAtomicRename outputFilename $ \temp_outputFilename -> run_as logger dflags - (local_includes ++ global_includes + (all_includes -- See Note [-fPIC for assembler] ++ map GHC.SysTools.Option pic_c_flags -- See Note [Produce big objects on Windows] ===================================== hadrian/src/Settings/Builders/Configure.hs ===================================== @@ -15,16 +15,23 @@ configureBuilderArgs = do targetPlatform <- queryTarget targetPlatformTriple buildPlatform <- queryBuild targetPlatformTriple pure $ [ "--enable-shared=no" - , "--with-pic=yes" , "--host=" ++ targetPlatform -- GMP's host is our target , "--build=" ++ buildPlatform ] + -- Disable FFT logic on wasm32, sacrifice + -- performance of multiplying very large operands + -- to save code size + <> [ "--disable-fft" | targetArch == "wasm32" ] -- Disable GMP's alloca usage on wasm32, it may -- cause stack overflow (#22602) due to the -- rather small 64KB default stack size. See -- https://gmplib.org/manual/Build-Options for -- more detailed explanation of this configure -- option. - <> [ "--enable-alloca=malloc-reentrant" | targetArch == "wasm32" ] + <> [ "--enable-alloca=malloc-notreentrant" | targetArch == "wasm32" ] + -- Enable PIC unless target is wasm32, in which + -- case we don't want libgmp.a to be bloated due + -- to PIC overhead. + <> [ "--with-pic=yes" | targetArch /= "wasm32" ] , builder (Configure libffiPath) ? do top <- expr topDirectory ===================================== testsuite/tests/driver/T24839.hs ===================================== @@ -0,0 +1,8 @@ +import Data.Int +import Foreign.Ptr +import Foreign.Storable + +foreign import ccall "&" foo :: Ptr Int64 + +main :: IO () +main = peek foo >>= print ===================================== testsuite/tests/driver/T24839.stdout ===================================== @@ -0,0 +1 @@ +24839 ===================================== testsuite/tests/driver/all.T ===================================== @@ -327,3 +327,4 @@ test('T23339B', [extra_files(['T23339.hs']), req_c], makefile_test, []) test('T23613', normal, compile_and_run, ['-this-unit-id=foo']) test('T23944', [unless(have_dynamic(), skip), extra_files(['T23944A.hs'])], multimod_compile, ['T23944 T23944A', '-fprefer-byte-code -fbyte-code -fno-code -dynamic-too -fwrite-interface']) test('T24286', [cxx_src, unless(have_profiling(), skip), extra_files(['T24286.cpp'])], compile, ['-prof -no-hs-main']) +test('T24839', [unless(arch('x86_64') or arch('aarch64'), skip), extra_files(["t24839_sub.S"])], compile_and_run, ['t24839_sub.S']) ===================================== testsuite/tests/driver/t24839_sub.S ===================================== @@ -0,0 +1,10 @@ +/* Note that the filename must begin with a lowercase letter, because GHC thinks it as a module name otherwise. */ +#include "ghcconfig.h" +#if LEADING_UNDERSCORE + .globl _foo +_foo: +#else + .globl foo +foo: +#endif + .quad 24839 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6304030eacb0bd3acab5f8589dd25e3f286c65d9...dd0c1732c5f51bd946ba7b79ad965af3e283e5bd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6304030eacb0bd3acab5f8589dd25e3f286c65d9...dd0c1732c5f51bd946ba7b79ad965af3e283e5bd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 2 15:09:21 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sun, 02 Jun 2024 11:09:21 -0400 Subject: [Git][ghc/ghc][wip/text-simdutf] 29 commits: rts: ensure gc_thread/gen_workspace is allocated with proper alignment Message-ID: <665c8b211186d_210f64278fb981083ca@gitlab.mail> Cheng Shao pushed to branch wip/text-simdutf at Glasgow Haskell Compiler / GHC Commits: 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - 3ccf4b82 by Cheng Shao at 2024-06-02T15:06:57+00:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 8442f707 by Cheng Shao at 2024-06-02T15:06:57+00:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Builtin/Types.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/Word64Set/Internal.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Ext/Types.hs - compiler/GHC/JS/JStg/Syntax.hs - compiler/GHC/JS/Syntax.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Types/FieldLabel.hs - compiler/GHC/Types/Unique/Set.hs - configure.ac - docs/users_guide/9.12.1-notes.rst The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/befd1dbc99b59c45733a36eb80131ad2c140100c...8442f707bd28d8de693b0bdd94c60a8c925e86c9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/befd1dbc99b59c45733a36eb80131ad2c140100c...8442f707bd28d8de693b0bdd94c60a8c925e86c9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 2 15:14:11 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sun, 02 Jun 2024 11:14:11 -0400 Subject: [Git][ghc/ghc][wip/text-simdutf] 2 commits: hadrian: add +text_simdutf flavour transformer to allow building text with simdutf Message-ID: <665c8c438834b_210f6428993f4110088@gitlab.mail> Cheng Shao pushed to branch wip/text-simdutf at Glasgow Haskell Compiler / GHC Commits: b492664c by Cheng Shao at 2024-06-02T15:13:55+00:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 45085756 by Cheng Shao at 2024-06-02T15:13:59+00:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - 8 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Flavour/Type.hs - hadrian/src/Rules/Register.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Packages.hs Changes: ===================================== .gitlab/generate-ci/gen_ci.hs ===================================== @@ -153,6 +153,7 @@ data BuildConfig , threadSanitiser :: Bool , noSplitSections :: Bool , validateNonmovingGc :: Bool + , textWithSIMDUTF :: Bool } -- Extra arguments to pass to ./configure due to the BuildConfig @@ -174,7 +175,8 @@ mkJobFlavour BuildConfig{..} = Flavour buildFlavour opts [FullyStatic | fullyStatic] ++ [ThreadSanitiser | threadSanitiser] ++ [NoSplitSections | noSplitSections, buildFlavour == Release ] ++ - [BootNonmovingGc | validateNonmovingGc ] + [BootNonmovingGc | validateNonmovingGc ] ++ + [TextWithSIMDUTF | textWithSIMDUTF] data Flavour = Flavour BaseFlavour [FlavourTrans] @@ -185,6 +187,7 @@ data FlavourTrans = | ThreadSanitiser | NoSplitSections | BootNonmovingGc + | TextWithSIMDUTF data BaseFlavour = Release | Validate | SlowValidate deriving Eq @@ -211,6 +214,7 @@ vanilla = BuildConfig , threadSanitiser = False , noSplitSections = False , validateNonmovingGc = False + , textWithSIMDUTF = False } splitSectionsBroken :: BuildConfig -> BuildConfig @@ -344,6 +348,7 @@ flavourString (Flavour base trans) = base_string base ++ concatMap (("+" ++) . f flavour_string ThreadSanitiser = "thread_sanitizer_cmm" flavour_string NoSplitSections = "no_split_sections" flavour_string BootNonmovingGc = "boot_nonmoving_gc" + flavour_string TextWithSIMDUTF = "text_simdutf" -- The path to the docker image (just for linux builders) dockerImage :: Arch -> Opsys -> Maybe String @@ -1057,6 +1062,7 @@ job_groups = { fullyStatic = True , buildFlavour = Release -- TODO: This needs to be validate but wasm backend doesn't pass yet + , textWithSIMDUTF = True } @@ -1082,10 +1088,10 @@ platform_mapping = Map.map go combined_result , "x86_64-linux-fedora33-release" , "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate" , "x86_64-windows-validate" - , "nightly-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static" + , "nightly-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf" , "nightly-x86_64-linux-deb11-validate" , "nightly-x86_64-linux-deb12-validate" - , "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static" + , "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf" , "x86_64-linux-deb12-validate+thread_sanitizer_cmm" , "nightly-aarch64-linux-deb10-validate" , "nightly-x86_64-linux-alpine3_12-validate" ===================================== .gitlab/jobs.yaml ===================================== @@ -951,7 +951,7 @@ "XZ_OPT": "-9" } }, - "nightly-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static": { + "nightly-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -962,7 +962,7 @@ "artifacts": { "expire_in": "8 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -1005,17 +1005,17 @@ ], "variables": { "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static", + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf", "XZ_OPT": "-9" } }, - "nightly-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static": { + "nightly-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -1026,7 +1026,7 @@ "artifacts": { "expire_in": "8 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -1069,17 +1069,17 @@ ], "variables": { "BIGNUM_BACKEND": "native", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static", + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf", "XZ_OPT": "-9" } }, - "nightly-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static": { + "nightly-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -1090,7 +1090,7 @@ "artifacts": { "expire_in": "8 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -1133,13 +1133,13 @@ ], "variables": { "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static", + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf", "XZ_OPT": "-9" } }, @@ -4465,7 +4465,7 @@ "TEST_ENV": "x86_64-linux-alpine3_12-validate+fully_static" } }, - "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static": { + "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -4476,7 +4476,7 @@ "artifacts": { "expire_in": "2 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -4519,16 +4519,16 @@ ], "variables": { "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static" + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf" } }, - "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static": { + "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -4539,7 +4539,7 @@ "artifacts": { "expire_in": "2 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -4583,16 +4583,16 @@ ], "variables": { "BIGNUM_BACKEND": "native", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static" + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf" } }, - "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static": { + "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -4603,7 +4603,7 @@ "artifacts": { "expire_in": "2 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -4647,13 +4647,13 @@ ], "variables": { "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static" + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf" } }, "x86_64-linux-deb10-int_native-validate": { ===================================== hadrian/doc/flavours.md ===================================== @@ -265,6 +265,10 @@ The supported transformers are listed below: native_bignum Use the native ghc-bignum backend. + + text_simdutf + Enable building the text package with simdutf support. + no_profiled_libs Disables building of libraries in profiled build ways. ===================================== hadrian/src/Flavour.hs ===================================== @@ -17,6 +17,7 @@ module Flavour , enableHaddock , enableHiCore , useNativeBignum + , enableTextWithSIMDUTF , omitPragmas , completeSetting @@ -53,6 +54,7 @@ flavourTransformers = M.fromList , "no_dynamic_ghc" =: disableDynamicGhcPrograms , "no_dynamic_libs" =: disableDynamicLibs , "native_bignum" =: useNativeBignum + , "text_simdutf" =: enableTextWithSIMDUTF , "no_profiled_libs" =: disableProfiledLibs , "omit_pragmas" =: omitPragmas , "ipe" =: enableIPE @@ -292,6 +294,12 @@ useNativeBignum flavour = flavour { bignumBackend = "native" } +-- | Enable building the @text@ package with @simdutf@ support. +enableTextWithSIMDUTF :: Flavour -> Flavour +enableTextWithSIMDUTF flavour = flavour { + textWithSIMDUTF = True +} + -- | Build stage2 compiler with -fomit-interface-pragmas to reduce -- recompilation. omitPragmas :: Flavour -> Flavour ===================================== hadrian/src/Flavour/Type.hs ===================================== @@ -23,6 +23,9 @@ data Flavour = Flavour { bignumBackend :: String, -- | Check selected bignum backend against native backend bignumCheck :: Bool, + -- | Build the @text@ package with @simdutf@ support. Disabled by + -- default due to packaging difficulties described in #20724. + textWithSIMDUTF :: Bool, -- | Build libraries these ways. libraryWays :: Ways, -- | Build RTS these ways. @@ -70,4 +73,3 @@ type DocTargets = Set DocTarget -- distribution. data DocTarget = Haddocks | SphinxHTML | SphinxPDFs | SphinxMan | SphinxInfo deriving (Eq, Ord, Show, Bounded, Enum) - ===================================== hadrian/src/Rules/Register.hs ===================================== @@ -7,6 +7,7 @@ module Rules.Register ( import Base import Context import Expression ( getContextData ) +import Flavour import Oracles.Setting import Hadrian.BuildPath import Hadrian.Expression @@ -51,6 +52,14 @@ configurePackageRules = do isGmp <- (== "gmp") <$> interpretInContext ctx getBignumBackend when isGmp $ need [buildP -/- "include/ghc-gmp.h"] + when (pkg == text) $ do + simdutf <- textWithSIMDUTF <$> flavour + when simdutf $ do + -- This is required, otherwise you get Error: hadrian: + -- Encountered missing or private dependencies: + -- system-cxx-std-lib ==1.0 + cxxStdLib <- systemCxxStdLibConfPath $ PackageDbLoc stage Inplace + need [cxxStdLib] Cabal.configurePackage ctx root -/- "**/autogen/cabal_macros.h" %> \out -> do ===================================== hadrian/src/Settings/Default.hs ===================================== @@ -267,6 +267,7 @@ defaultFlavour = Flavour , packages = defaultPackages , bignumBackend = defaultBignumBackend , bignumCheck = False + , textWithSIMDUTF = False , libraryWays = defaultLibraryWays , rtsWays = defaultRtsWays , dynamicGhcPrograms = defaultDynamicGhcPrograms ===================================== hadrian/src/Settings/Packages.hs ===================================== @@ -191,12 +191,10 @@ packageArgs = do builder (Cabal Flags) ? stage0 `cabalFlag` "bootstrap" ---------------------------------- text -------------------------------- - , package text ? mconcat - -- Disable SIMDUTF by default due to packaging difficulties - -- described in #20724. - [ builder (Cabal Flags) ? arg "-simdutf" - -- https://github.com/haskell/text/issues/415 - , builder Ghc ? input "**/Data/Text/Encoding.hs" ? arg "-Wno-unused-imports" ] + , package text ? + ifM (textWithSIMDUTF <$> expr flavour) + (builder (Cabal Flags) ? arg "+simdutf") + (builder (Cabal Flags) ? arg "-simdutf") ------------------------------- haskeline ------------------------------ -- Hadrian doesn't currently support packages containing both libraries View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8442f707bd28d8de693b0bdd94c60a8c925e86c9...45085756712ec43415874d94aea082dca30fd44f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8442f707bd28d8de693b0bdd94c60a8c925e86c9...45085756712ec43415874d94aea082dca30fd44f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 2 17:29:17 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 02 Jun 2024 13:29:17 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/supersven/ghc-9.10-riscv-ncg Message-ID: <665cabed99c27_2617cfcf6ad4247fe@gitlab.mail> Sven Tennie pushed new branch wip/supersven/ghc-9.10-riscv-ncg at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/supersven/ghc-9.10-riscv-ncg You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 2 18:02:22 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sun, 02 Jun 2024 14:02:22 -0400 Subject: [Git][ghc/ghc][master] 3 commits: hadrian: disable PIC for in-tree GMP on wasm32 Message-ID: <665cb3aebacab_2617cf126d95429730@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 1 changed file: - hadrian/src/Settings/Builders/Configure.hs Changes: ===================================== hadrian/src/Settings/Builders/Configure.hs ===================================== @@ -15,16 +15,23 @@ configureBuilderArgs = do targetPlatform <- queryTarget targetPlatformTriple buildPlatform <- queryBuild targetPlatformTriple pure $ [ "--enable-shared=no" - , "--with-pic=yes" , "--host=" ++ targetPlatform -- GMP's host is our target , "--build=" ++ buildPlatform ] + -- Disable FFT logic on wasm32, sacrifice + -- performance of multiplying very large operands + -- to save code size + <> [ "--disable-fft" | targetArch == "wasm32" ] -- Disable GMP's alloca usage on wasm32, it may -- cause stack overflow (#22602) due to the -- rather small 64KB default stack size. See -- https://gmplib.org/manual/Build-Options for -- more detailed explanation of this configure -- option. - <> [ "--enable-alloca=malloc-reentrant" | targetArch == "wasm32" ] + <> [ "--enable-alloca=malloc-notreentrant" | targetArch == "wasm32" ] + -- Enable PIC unless target is wasm32, in which + -- case we don't want libgmp.a to be bloated due + -- to PIC overhead. + <> [ "--with-pic=yes" | targetArch /= "wasm32" ] , builder (Configure libffiPath) ? do top <- expr topDirectory View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cf49fb5f8c20ae97cca08a468f690503b517a4ef...06277d56de91c8d21cbf71e8bc4096925b863acc -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cf49fb5f8c20ae97cca08a468f690503b517a4ef...06277d56de91c8d21cbf71e8bc4096925b863acc You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 2 18:03:15 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sun, 02 Jun 2024 14:03:15 -0400 Subject: [Git][ghc/ghc][master] Set package include paths when assembling .S files Message-ID: <665cb3e35b844_2617cf137c9f83709b@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 5 changed files: - compiler/GHC/Driver/Pipeline/Execute.hs - + testsuite/tests/driver/T24839.hs - + testsuite/tests/driver/T24839.stdout - testsuite/tests/driver/all.T - + testsuite/tests/driver/t24839_sub.S Changes: ===================================== compiler/GHC/Driver/Pipeline/Execute.hs ===================================== @@ -290,6 +290,7 @@ runGenericAsPhase :: (Logger -> DynFlags -> [Option] -> IO ()) -> [Option] -> Bo runGenericAsPhase run_as extra_opts with_cpp pipe_env hsc_env location input_fn = do let dflags = hsc_dflags hsc_env let logger = hsc_logger hsc_env + let unit_env = hsc_unit_env hsc_env let cmdline_include_paths = includePaths dflags let pic_c_flags = picCCOpts dflags @@ -300,16 +301,21 @@ runGenericAsPhase run_as extra_opts with_cpp pipe_env hsc_env location input_fn -- might be a hierarchical module. createDirectoryIfMissing True (takeDirectory output_fn) - let global_includes = [ GHC.SysTools.Option ("-I" ++ p) - | p <- includePathsGlobal cmdline_include_paths ] - let local_includes = [ GHC.SysTools.Option ("-iquote" ++ p) - | p <- includePathsQuote cmdline_include_paths ++ - includePathsQuoteImplicit cmdline_include_paths] + -- add package include paths + all_includes <- if not with_cpp + then pure [] + else do + pkg_include_dirs <- mayThrowUnitErr (collectIncludeDirs <$> preloadUnitsInfo unit_env) + let global_includes = [ GHC.SysTools.Option ("-I" ++ p) + | p <- includePathsGlobal cmdline_include_paths ++ pkg_include_dirs] + let local_includes = [ GHC.SysTools.Option ("-iquote" ++ p) + | p <- includePathsQuote cmdline_include_paths ++ includePathsQuoteImplicit cmdline_include_paths] + pure (local_includes ++ global_includes) let runAssembler inputFilename outputFilename = withAtomicRename outputFilename $ \temp_outputFilename -> run_as logger dflags - (local_includes ++ global_includes + (all_includes -- See Note [-fPIC for assembler] ++ map GHC.SysTools.Option pic_c_flags -- See Note [Produce big objects on Windows] ===================================== testsuite/tests/driver/T24839.hs ===================================== @@ -0,0 +1,8 @@ +import Data.Int +import Foreign.Ptr +import Foreign.Storable + +foreign import ccall "&" foo :: Ptr Int64 + +main :: IO () +main = peek foo >>= print ===================================== testsuite/tests/driver/T24839.stdout ===================================== @@ -0,0 +1 @@ +24839 ===================================== testsuite/tests/driver/all.T ===================================== @@ -327,3 +327,4 @@ test('T23339B', [extra_files(['T23339.hs']), req_c], makefile_test, []) test('T23613', normal, compile_and_run, ['-this-unit-id=foo']) test('T23944', [unless(have_dynamic(), skip), extra_files(['T23944A.hs'])], multimod_compile, ['T23944 T23944A', '-fprefer-byte-code -fbyte-code -fno-code -dynamic-too -fwrite-interface']) test('T24286', [cxx_src, unless(have_profiling(), skip), extra_files(['T24286.cpp'])], compile, ['-prof -no-hs-main']) +test('T24839', [unless(arch('x86_64') or arch('aarch64'), skip), extra_files(["t24839_sub.S"])], compile_and_run, ['t24839_sub.S']) ===================================== testsuite/tests/driver/t24839_sub.S ===================================== @@ -0,0 +1,10 @@ +/* Note that the filename must begin with a lowercase letter, because GHC thinks it as a module name otherwise. */ +#include "ghcconfig.h" +#if LEADING_UNDERSCORE + .globl _foo +_foo: +#else + .globl foo +foo: +#endif + .quad 24839 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f614270873135e9a3791085a486b665907a0d07 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f614270873135e9a3791085a486b665907a0d07 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 2 19:29:42 2024 From: gitlab at gitlab.haskell.org (Jade (@Jade)) Date: Sun, 02 Jun 2024 15:29:42 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/fine-grained-unused-warnings Message-ID: <665cc825ceca5_2617cf1e8106051890@gitlab.mail> Jade pushed new branch wip/fine-grained-unused-warnings at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fine-grained-unused-warnings You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 2 19:33:00 2024 From: gitlab at gitlab.haskell.org (Jade (@Jade)) Date: Sun, 02 Jun 2024 15:33:00 -0400 Subject: [Git][ghc/ghc][wip/fine-grained-unused-warnings] 4071 commits: [haddock @ 2002-04-04 16:23:43 by simonmar] Message-ID: <665cc8ec8f685_2617cf1f732c05405c@gitlab.mail> Jade pushed to branch wip/fine-grained-unused-warnings at Glasgow Haskell Compiler / GHC Commits: 2b39cd94 by Simon Marlow at 2002-04-04T16:23:43+00:00 [haddock @ 2002-04-04 16:23:43 by simonmar] This is Haddock, my stab at a Haskell documentation tool. It's not quite ready for release yet, but I'm putting it in the repository so others can take a look. It uses a locally modified version of the hssource parser, extended with support for GHC extensions and documentation annotations. - - - - - 99ede94f by Simon Marlow at 2002-04-04T16:24:10+00:00 [haddock @ 2002-04-04 16:24:10 by simonmar] forgot one file - - - - - 8363294c by Simon Marlow at 2002-04-05T13:58:15+00:00 [haddock @ 2002-04-05 13:58:15 by simonmar] Remap names in the exported declarations to be "closer" to the current module. eg. if an exported declaration mentions a type 'T' which is imported from module A then re-exported from the current module, then links from the type or indeed the documentation will point to the current module rather than module A. This is to support better hiding: module A won't be referred to in the generated output. - - - - - 1570cbc1 by Simon Marlow at 2002-04-05T13:58:23+00:00 [haddock @ 2002-04-05 13:58:23 by simonmar] update the TODO list - - - - - 3a62f96b by Simon Marlow at 2002-04-05T14:11:51+00:00 [haddock @ 2002-04-05 14:11:51 by simonmar] Fix the anchor for a class declaration - - - - - c5d9a471 by Simon Marlow at 2002-04-05T14:18:41+00:00 [haddock @ 2002-04-05 14:18:41 by simonmar] remove underlines on visited links - - - - - 97280525 by Simon Marlow at 2002-04-05T16:11:47+00:00 [haddock @ 2002-04-05 16:11:47 by simonmar] - Update to generate more correct HTML. - Use our own non-overloaded table combinators, as the overloaded versions were giving me a headache. The improved type safety caught several errors in the HTML generation. - - - - - 9acd3a4d by Simon Marlow at 2002-04-05T16:32:19+00:00 [haddock @ 2002-04-05 16:32:19 by simonmar] Add width property to the title, and add TD.children for the module contents page. - - - - - ec9a0847 by Simon Marlow at 2002-04-08T16:39:56+00:00 [haddock @ 2002-04-08 16:39:56 by simonmar] Fix a problem with exports of the form T(..). - - - - - e4627dc8 by Simon Marlow at 2002-04-08T16:41:38+00:00 [haddock @ 2002-04-08 16:41:37 by simonmar] - Add our own versions of Html & BlockTable for the time being. - Add support for generating an index to the HTML backend - - - - - 2d73fd75 by Simon Marlow at 2002-04-09T11:23:24+00:00 [haddock @ 2002-04-09 11:23:24 by simonmar] Add '-- /' as a synonym for '-- |', for compatibility with IDoc. - - - - - 3675464e by Simon Marlow at 2002-04-09T11:33:55+00:00 [haddock @ 2002-04-09 11:33:54 by simonmar] - add the <...> syntax for marking up URLs in documentation - Make the output for data & class declarations more compact when there aren't any documentation annotations on the individual methods or constructors respectively. - - - - - 5077f5b1 by Simon Marlow at 2002-04-09T11:36:04+00:00 [haddock @ 2002-04-09 11:36:04 by simonmar] Update the TODO list - - - - - 9e83c54d by Simon Marlow at 2002-04-10T10:50:06+00:00 [haddock @ 2002-04-10 10:50:06 by simonmar] Use explicit 'px' suffix on pixel sizes; IE seems to prefer them - - - - - 052de51c by Simon Marlow at 2002-04-10T13:23:13+00:00 [haddock @ 2002-04-10 13:23:13 by simonmar] Lex URLs as a single token to avoid having to escape special characters inside the URL string. - - - - - 47187edb by Simon Marlow at 2002-04-10T13:23:55+00:00 [haddock @ 2002-04-10 13:23:55 by simonmar] Not sure why I made the constructor name for a record declaration into a TyCls name, but change it back into a Var name anyhow. - - - - - 3dc6aa81 by Simon Marlow at 2002-04-10T13:26:10+00:00 [haddock @ 2002-04-10 13:26:09 by simonmar] Lots of changes, including: - add index support to the HTML backend - clean up the renamer, put it into a monad - propogate unresolved names to the top level and report them in a nicer way - various bugfixes - - - - - c2a70a72 by Simon Marlow at 2002-04-10T13:32:39+00:00 [haddock @ 2002-04-10 13:32:39 by simonmar] Skeleton documentation - - - - - 50c98d17 by Simon Marlow at 2002-04-10T13:37:23+00:00 [haddock @ 2002-04-10 13:37:23 by simonmar] Update the TODO list, separate into pre-1.0 and post-1.0 items - - - - - f3778be6 by Simon Marlow at 2002-04-10T14:30:58+00:00 [haddock @ 2002-04-10 14:30:58 by simonmar] Add an introduction - - - - - cfbaf9f7 by Simon Marlow at 2002-04-10T14:59:51+00:00 [haddock @ 2002-04-10 14:59:51 by simonmar] Sort the module tree - - - - - 76bd7b34 by Simon Marlow at 2002-04-10T15:50:11+00:00 [haddock @ 2002-04-10 15:50:10 by simonmar] Generate a little table of contents at the top of the module doc (only if the module actually contains some section headings, though). - - - - - bb8560a1 by Simon Marlow at 2002-04-10T16:10:26+00:00 [haddock @ 2002-04-10 16:10:26 by simonmar] Now we understand (or at least don't barf on) type signatures in patterns such as you might find when scoped type variables are in use. - - - - - 86c2a026 by Simon Marlow at 2002-04-10T16:10:49+00:00 [haddock @ 2002-04-10 16:10:49 by simonmar] more updates - - - - - 1c052b0e by Simon Marlow at 2002-04-10T16:28:05+00:00 [haddock @ 2002-04-10 16:28:05 by simonmar] Parse errors in doc strings are now reported as warnings rather that causing the whole thing to fall over. It still needs cleaning up (the warning is emitted with trace) but this will do for the time being. - - - - - ace03e8f by Simon Marlow at 2002-04-10T16:38:03+00:00 [haddock @ 2002-04-10 16:38:03 by simonmar] update again - - - - - 69006c3e by Simon Marlow at 2002-04-11T13:38:02+00:00 [haddock @ 2002-04-11 13:38:02 by simonmar] mention Opera - - - - - fe9b10f8 by Simon Marlow at 2002-04-11T13:40:31+00:00 [haddock @ 2002-04-11 13:40:30 by simonmar] - copy haddock.css into the same place as the generated HTML - new option: --css <file> specifies the style sheet to use - new option: -o <dir> specifies the directory in which to generate the output. - because Haddock now needs to know where to find its default stylesheet, we have to have a wrapper script and do the haddock-inplace thing (Makefile code copied largely from fptools/happy). - - - - - 106adbbe by Simon Marlow at 2002-04-24T15:12:41+00:00 [haddock @ 2002-04-24 15:12:41 by simonmar] Stop slurping comment lines when we see a row of dashes longer than length 2: these are useful as separators. - - - - - 995d3f9e by Simon Marlow at 2002-04-24T15:14:12+00:00 [haddock @ 2002-04-24 15:14:11 by simonmar] Grok the kind of module headers we use in fptools/libraries, and pass the "portability", "stability", and "maintainer" strings through into the generated HTML. If the module header doesn't match the pattern, then we don't include the info in the HTML. - - - - - e14da136 by Simon Marlow at 2002-04-24T15:16:57+00:00 [haddock @ 2002-04-24 15:16:57 by simonmar] Done module headers now. - - - - - 2ca8dfd4 by Simon Marlow at 2002-04-24T15:57:48+00:00 [haddock @ 2002-04-24 15:57:47 by simonmar] Handle gcons in export lists (a common extension). - - - - - 044cea81 by Simon Marlow at 2002-04-25T14:20:12+00:00 [haddock @ 2002-04-25 14:20:12 by simonmar] Add the little lambda icon - - - - - 63955027 by Simon Marlow at 2002-04-25T14:40:05+00:00 [haddock @ 2002-04-25 14:40:05 by simonmar] - Add support for named chunks of documentation which can be referenced from the export list. - Copy the icon from $libdir to the destination in HTML mode. - - - - - 36e3f913 by Simon Marlow at 2002-04-25T16:48:36+00:00 [haddock @ 2002-04-25 16:48:36 by simonmar] More keyboard bashing - - - - - 7ae18dd0 by Simon Marlow at 2002-04-26T08:43:33+00:00 [haddock @ 2002-04-26 08:43:33 by simonmar] Package util reqd. to compile with 4.08.2 - - - - - bbd5fbab by Simon Marlow at 2002-04-26T10:13:00+00:00 [haddock @ 2002-04-26 10:13:00 by simonmar] Include $(GHC_HAPPY_OPTS) when compiling HsParser - - - - - 31c53d79 by Simon Marlow at 2002-04-26T11:18:57+00:00 [haddock @ 2002-04-26 11:18:56 by simonmar] - support for fundeps (partially contributed by Brett Letner - thanks Brett). - make it build with GHC 4.08.2 - - - - - c415ce76 by Simon Marlow at 2002-04-26T13:15:02+00:00 [haddock @ 2002-04-26 13:15:02 by simonmar] Move the explicit formatting of the little table for the stability/portability/maintainer info from the HTML into the CSS, and remove the explicit table size (just right-align it). - - - - - 520ee21a by Simon Marlow at 2002-04-26T16:01:44+00:00 [haddock @ 2002-04-26 16:01:44 by simonmar] Yet more keyboard bashing - this is pretty much complete now. - - - - - 2ae37179 by Simon Marlow at 2002-04-26T16:02:14+00:00 [haddock @ 2002-04-26 16:02:14 by simonmar] Add a couple of things I forgot about - - - - - b7211e04 by Simon Marlow at 2002-04-29T15:28:12+00:00 [haddock @ 2002-04-29 15:28:12 by simonmar] bugfix for declBinders on a NewTypeDecl - - - - - 640c154a by Simon Marlow at 2002-04-29T15:28:54+00:00 [haddock @ 2002-04-29 15:28:54 by simonmar] Allow '-- |' style annotations on constructors and record fields. - - - - - 393f258a by Simon Marlow at 2002-04-29T15:37:32+00:00 [haddock @ 2002-04-29 15:37:32 by simonmar] syntax fix - - - - - 8a2c2549 by Simon Marlow at 2002-04-29T15:37:48+00:00 [haddock @ 2002-04-29 15:37:48 by simonmar] Add an example - - - - - db88f8a2 by Simon Marlow at 2002-04-29T15:55:46+00:00 [haddock @ 2002-04-29 15:55:46 by simonmar] remove a trace - - - - - 2b0248e0 by Simon Marlow at 2002-04-29T15:56:19+00:00 [haddock @ 2002-04-29 15:56:19 by simonmar] Fix for 'make install' - - - - - 120453a0 by Simon Marlow at 2002-04-29T15:56:39+00:00 [haddock @ 2002-04-29 15:56:39 by simonmar] Install the auxilliary bits - - - - - 950e6dbb by Simon Marlow at 2002-04-29T15:57:30+00:00 [haddock @ 2002-04-29 15:57:30 by simonmar] Add BinDist bits - - - - - 154b9d71 by Simon Marlow at 2002-05-01T11:02:52+00:00 [haddock @ 2002-05-01 11:02:52 by simonmar] update - - - - - ba6c39fa by Simon Marlow at 2002-05-01T11:03:26+00:00 [haddock @ 2002-05-01 11:03:26 by simonmar] Add another item - - - - - bacb5e33 by Simon Marlow at 2002-05-03T08:50:00+00:00 [haddock @ 2002-05-03 08:50:00 by simonmar] Fix some typos. - - - - - 54c87895 by Sven Panne at 2002-05-05T19:40:51+00:00 [haddock @ 2002-05-05 19:40:51 by panne] As a temporary hack/workaround for a bug in GHC's simplifier, don't pass Happy the -c option for generating the parsers in this subdir. Furthermore, disable -O for HaddocParse, too. - - - - - e6c08703 by Simon Marlow at 2002-05-06T09:51:10+00:00 [haddock @ 2002-05-06 09:51:10 by simonmar] Add RPM spec file (thanks to Tom Moertel <tom-rpms at moertel.com>) - - - - - 7b8fa8e7 by Simon Marlow at 2002-05-06T12:29:26+00:00 [haddock @ 2002-05-06 12:29:26 by simonmar] Add missing type signature (a different workaround for the bug in GHC's simplifier). - - - - - cd0e300d by Simon Marlow at 2002-05-06T12:30:09+00:00 [haddock @ 2002-05-06 12:30:09 by simonmar] Remove workaround for simplifier bug in previous revision. - - - - - 687e68fa by Simon Marlow at 2002-05-06T12:32:32+00:00 [haddock @ 2002-05-06 12:32:32 by simonmar] Allow empty data declarations (another GHC extension). - - - - - 8f29f696 by Simon Marlow at 2002-05-06T12:49:21+00:00 [haddock @ 2002-05-06 12:49:21 by simonmar] Fix silly bug in named documentation block lookup. - - - - - 8e0059af by Simon Marlow at 2002-05-06T13:02:42+00:00 [haddock @ 2002-05-06 13:02:42 by simonmar] Add another named chunk with a different name - - - - - 68f8a896 by Simon Marlow at 2002-05-06T13:32:32+00:00 [haddock @ 2002-05-06 13:32:32 by simonmar] Be more lenient about extra paragraph breaks - - - - - 65fc31db by Simon Marlow at 2002-05-07T15:36:36+00:00 [haddock @ 2002-05-07 15:36:36 by simonmar] DocEmpty is a right and left-unit of DocAppend (remove it in the smart constructor). - - - - - adc81078 by Simon Marlow at 2002-05-07T15:37:15+00:00 [haddock @ 2002-05-07 15:37:15 by simonmar] Allow code blocks to be denoted with bird-tracks in addition to [...]. - - - - - 1283a3c1 by Simon Marlow at 2002-05-08T11:21:56+00:00 [haddock @ 2002-05-08 11:21:56 by simonmar] Add a facility for specifying options that affect Haddock's treatment of the module. Options are given at the top of the module in a comma-separated list, beginning with '-- #'. eg. -- # prune, hide, ignore-exports Options currently available, with their meanings: prune: ignore declarations which have no documentation annotations ignore-exports: act as if the export list were not specified (i.e. export everything local to the module). hide: do not include this module in the generated documentation, but propagate any exported definitions to modules which re-export them. There's a slight change in the semantics for re-exporting a full module by giving 'module M' in the export list: if module M does not have the 'hide' option, then the documentation will now just contain a reference to module M rather than the full inlined contents of that module. These features, and some other changes in the pipeline, are the result of discussions between myself and Manuel Chakravarty <chak at cse.unsw.edu.au> (author of IDoc) yesterday. Also: some cleanups, use a Writer monad to collect error messages in some places instead of just printing them with trace. - - - - - a2239cf5 by Simon Marlow at 2002-05-08T11:22:30+00:00 [haddock @ 2002-05-08 11:22:30 by simonmar] Update to test new features. - - - - - 6add955f by Simon Marlow at 2002-05-08T13:37:25+00:00 [haddock @ 2002-05-08 13:37:25 by simonmar] Change the markup for typewriter-font from [...] to @... at . The reasoning is that the '@' symbol is much less likely to be needed than square brackets, and we don't want to have to escape square brackets in code fragments. This will be mildly painful in the short term, but it's better to get the change out of the way as early as possible. - - - - - cda06447 by Simon Marlow at 2002-05-08T13:39:56+00:00 [haddock @ 2002-05-08 13:39:56 by simonmar] Allow nested-style comments to be used as documentation annotations too. eg. {-| ... -} is equivalent to -- | ... An extra space can also be left after the comment opener: {- | ... -}. The only version that isn't allowed is {-# ... -}, because this syntax overlaps with Haskell pragmas; use {- # ... -} instead. - - - - - db23f65e by Simon Marlow at 2002-05-08T14:48:41+00:00 [haddock @ 2002-05-08 14:48:39 by simonmar] Add support for existential quantifiers on constructors. - - - - - adce3794 by Simon Marlow at 2002-05-08T15:43:25+00:00 [haddock @ 2002-05-08 15:43:25 by simonmar] update - - - - - 62a1f436 by Simon Marlow at 2002-05-08T15:44:10+00:00 [haddock @ 2002-05-08 15:44:10 by simonmar] Update to version 0.2 - - - - - f6a24ba3 by Simon Marlow at 2002-05-09T08:48:29+00:00 [haddock @ 2002-05-09 08:48:29 by simonmar] typo - - - - - 9f9522a4 by Simon Marlow at 2002-05-09T10:33:14+00:00 [haddock @ 2002-05-09 10:33:14 by simonmar] oops, left out '/' from the special characters in the last change. - - - - - 14abcb39 by Simon Marlow at 2002-05-09T10:34:44+00:00 [haddock @ 2002-05-09 10:34:44 by simonmar] Fix buglet - - - - - b8d878be by Simon Marlow at 2002-05-09T10:35:00+00:00 [haddock @ 2002-05-09 10:35:00 by simonmar] Give a more useful instance of Show for Module. - - - - - f7bfd626 by Simon Marlow at 2002-05-09T10:37:07+00:00 [haddock @ 2002-05-09 10:37:07 by simonmar] The last commit to Main.lhs broke the delicate balance of laziness which was being used to avoid computing the dependency graph of modules. So I finally bit the bullet and did a proper topological sort of the module graph, which turned out to be easy (stealing the Digraph module from GHC - this really ought to be in the libraries somewhere). - - - - - b481c1d0 by Simon Marlow at 2002-05-09T10:37:25+00:00 [haddock @ 2002-05-09 10:37:25 by simonmar] another item done - - - - - 032e2b42 by Simon Marlow at 2002-05-09T10:44:15+00:00 [haddock @ 2002-05-09 10:44:15 by simonmar] Don't consider a module re-export as having documentation, for the purposes of deciding whether we need a Synopsis section or not. - - - - - 5fb45e92 by Simon Marlow at 2002-05-09T11:10:55+00:00 [haddock @ 2002-05-09 11:10:55 by simonmar] Add a special case for list types in ppHsAType - - - - - 1937e428 by Simon Marlow at 2002-05-09T12:43:06+00:00 [haddock @ 2002-05-09 12:43:06 by simonmar] Type synonyms can accept a ctype on the RHS, to match GHC. - - - - - 0f16ce56 by Simon Marlow at 2002-05-09T12:45:19+00:00 [haddock @ 2002-05-09 12:45:19 by simonmar] Add 'stdcall' keyword - - - - - 29b0d7d2 by Simon Marlow at 2002-05-09T13:35:45+00:00 [haddock @ 2002-05-09 13:35:45 by simonmar] Add System Requirements section - - - - - bf14dddd by Simon Marlow at 2002-05-09T13:36:11+00:00 [haddock @ 2002-05-09 13:36:11 by simonmar] Test existential types, amongst other things - - - - - 502f8f6f by Simon Marlow at 2002-05-09T13:37:35+00:00 [haddock @ 2002-05-09 13:37:35 by simonmar] Print the module name in a doc-string parse error - - - - - ca1f8d49 by Simon Marlow at 2002-05-09T13:38:04+00:00 [haddock @ 2002-05-09 13:38:04 by simonmar] Add dependency - - - - - 8d3d91ff by Simon Marlow at 2002-05-09T15:37:57+00:00 [haddock @ 2002-05-09 15:37:57 by simonmar] Add the changelog/release notes - - - - - f3960959 by Simon Marlow at 2002-05-09T15:47:47+00:00 [haddock @ 2002-05-09 15:47:47 by simonmar] mention the backquote-style of markup - - - - - 089fb6e6 by Simon Marlow at 2002-05-09T15:59:45+00:00 [haddock @ 2002-05-09 15:59:45 by simonmar] update - - - - - bdd3be0b by Simon Marlow at 2002-05-09T15:59:56+00:00 [haddock @ 2002-05-09 15:59:56 by simonmar] Document changes since 0.1 - - - - - 00fc4af8 by Simon Marlow at 2002-05-10T08:22:48+00:00 [haddock @ 2002-05-10 08:22:48 by simonmar] oops, update to version 0.2 - - - - - a8a79041 by Simon Marlow at 2002-05-10T16:05:08+00:00 [haddock @ 2002-05-10 16:05:08 by simonmar] Only include a mini-contents if there are 2 or more sections - - - - - 06653319 by Simon Marlow at 2002-05-13T09:13:12+00:00 [haddock @ 2002-05-13 09:13:12 by simonmar] fix typos - - - - - 1402b19b by Simon Marlow at 2002-05-13T10:14:22+00:00 [haddock @ 2002-05-13 10:14:22 by simonmar] Allow backquote as the right-hand quote as well as the left-hand quote, as suggested by Dean Herrington. Clean up the grammar a litte. - - - - - dcd5320d by Simon Marlow at 2002-05-13T10:44:10+00:00 [haddock @ 2002-05-13 10:44:10 by simonmar] a couple more things, prioritise a bit - - - - - a90130c4 by Simon Marlow at 2002-05-13T15:19:03+00:00 [haddock @ 2002-05-13 15:19:03 by simonmar] Cope with datatypes which have documentation on the constructor but not the type itself, and records which have documentation on the fields but not the constructor. (Thanks to Ross Paterson for pointing out the bugs). - - - - - a774d432 by Simon Marlow at 2002-05-13T15:20:54+00:00 [haddock @ 2002-05-13 15:20:54 by simonmar] Fix one of the record examples - - - - - 2d1d5218 by Simon Marlow at 2002-05-15T12:44:35+00:00 [haddock @ 2002-05-15 12:44:35 by simonmar] Preserve the newline before a bird-track, but only within a paragraph. - - - - - 1554c09a by Simon Marlow at 2002-05-15T13:03:02+00:00 [haddock @ 2002-05-15 13:03:01 by simonmar] Reworking of the internals to support documenting function arguments (the Most Wanted new feature by the punters). The old method of keeping parsed documentation in a Name -> Doc mapping wasn't going to cut it for anntations on type components, where there's no name to attach the documentation to, so I've moved to storing all the documentation in the abstract syntax. Previously some of the documentation was left in the abstract syntax by the parser, but was later extracted into the mapping. In order to avoid having to parameterise the abstract syntax over the type of documentation stored in it, we have to parse the documentation at the same time as we parse the Haskell source (well, I suppose we could store 'Either String Doc' in the HsSyn, but that's clunky). One upshot is that documentation is now parsed eagerly, and documentation parse errors are fatal (but have better line numbers in the error message). The new story simplifies matters for the code that processes the source modules, because we don't have to maintain the extra Name->Doc mapping, and it should improve efficiency a little too. New features: - Function arguments and return values can now have doc annotations. - If you refer to a qualified name in a doc string, eg. 'IO.putStr', then Haddock will emit a hyperlink even if the identifier is not in scope, so you don't have to make sure everything referred to from the documentation is imported. - several bugs & minor infelicities fixed. - - - - - 57344dc3 by Simon Marlow at 2002-05-15T13:03:19+00:00 [haddock @ 2002-05-15 13:03:19 by simonmar] Bump to version 0.3 - - - - - b2791812 by Simon Marlow at 2002-05-15T13:03:41+00:00 [haddock @ 2002-05-15 13:03:41 by simonmar] update - - - - - fead183e by Simon Marlow at 2002-05-15T13:10:15+00:00 [haddock @ 2002-05-15 13:10:15 by simonmar] Rename Foo.hs to Test.hs, and add a Makefile - - - - - b0b1f89f by Simon Marlow at 2002-05-15T13:16:07+00:00 [haddock @ 2002-05-15 13:16:07 by simonmar] - Remove the note about function argument docs not being implemented - Note that qualified identifiers can be used to point to entities that aren't in scope. - - - - - 5665f31a by Simon Marlow at 2002-05-15T13:28:46+00:00 [haddock @ 2002-05-15 13:28:46 by simonmar] Patch to add support for GHC-style primitive strings ".."#, from Ross Paterson. - - - - - 0564505d by Simon Marlow at 2002-05-17T10:51:57+00:00 [haddock @ 2002-05-17 10:51:57 by simonmar] Fix bugs in qualified name handling (A.B.f was returned as B.f) - - - - - 10e7311c by Simon Marlow at 2002-05-21T10:24:52+00:00 [haddock @ 2002-05-21 10:24:52 by simonmar] - Use an alternate tabular layout for datatypes, which is more compact - Fix some problems with the function argument documentation - - - - - 2f91c2a6 by Simon Marlow at 2002-05-21T10:27:40+00:00 [haddock @ 2002-05-21 10:27:40 by simonmar] add a few more test cases - - - - - 01c2ddd2 by Simon Marlow at 2002-05-21T10:28:33+00:00 [haddock @ 2002-05-21 10:28:33 by simonmar] Rearrange a bit, and add support for tabular datatype rendering - - - - - a4e4c5f8 by Simon Marlow at 2002-05-27T09:03:52+00:00 [haddock @ 2002-05-27 09:03:51 by simonmar] Lots of changes: - instances of a class are listed with the class, and instances involving a datatype are listed with that type. Derived instances aren't included at the moment: the calculation to find the instance head for a derived instance is non-trivial. - some formatting changes; use rows with specified height rather than cellspacing in some places. - various fixes (source file links were wrong, amongst others) - - - - - 48722e68 by Simon Marlow at 2002-05-27T12:30:38+00:00 [haddock @ 2002-05-27 12:30:37 by simonmar] - Put function arguments *before* the doc for the function, as suggested by Sven Panne. This looks nicer when the function documentation is long. - Switch to using bold for binders at the definition site, and use underline for keywords. This makes the binder stand out more. - - - - - 657204d2 by Simon Marlow at 2002-05-27T13:19:49+00:00 [haddock @ 2002-05-27 13:19:49 by simonmar] Fix bug: we weren't renaming HsDocCommentNamed in renameDecl - - - - - 592aae66 by Simon Marlow at 2002-05-27T14:10:27+00:00 [haddock @ 2002-05-27 14:10:27 by simonmar] Fix some bugs in the rendering of qualified type signatures. - - - - - 69c8f763 by Simon Marlow at 2002-05-27T14:36:45+00:00 [haddock @ 2002-05-27 14:36:45 by simonmar] warning message tweak - - - - - 16e64e21 by Simon Marlow at 2002-05-27T14:53:53+00:00 [haddock @ 2002-05-27 14:53:53 by simonmar] hyperlinked identifiers should be in <tt> - - - - - 8d5e4783 by Simon Marlow at 2002-05-27T15:56:45+00:00 [haddock @ 2002-05-27 15:56:45 by simonmar] Do something sensible for modules which don't export anything (except instances). - - - - - 9d3ef811 by Simon Marlow at 2002-05-28T10:12:50+00:00 [haddock @ 2002-05-28 10:12:50 by simonmar] Rename the module documentation properly (bug reported by Sven Panne). - - - - - ef03a1cc by Simon Marlow at 2002-05-28T10:13:04+00:00 [haddock @ 2002-05-28 10:13:04 by simonmar] Add some more test cases - - - - - 92baa0e8 by Simon Marlow at 2002-05-28T11:17:55+00:00 [haddock @ 2002-05-28 11:17:55 by simonmar] If an identifier doesn't lex, then just replace it by a DocString. - - - - - a3156213 by Simon Marlow at 2002-05-28T16:16:19+00:00 [haddock @ 2002-05-28 16:16:19 by simonmar] Only link to names in the current module which are actually listed in the documentation. A name may be exported but not present in the documentation if it is exported as part of a 'module M' export specifier. - - - - - 31acf941 by Simon Marlow at 2002-05-28T16:17:11+00:00 [haddock @ 2002-05-28 16:17:11 by simonmar] update - - - - - 7e474ebf by Sigbjorn Finne at 2002-05-28T22:42:08+00:00 [haddock @ 2002-05-28 22:42:08 by sof] Handle lone occurrences of '/', e.g., -- | This/that. [did this in the lexer rather than in the parser, as I couldn't see a way not to introduce an S/R conflict that way.] - - - - - 093f7e53 by Simon Marlow at 2002-05-29T09:09:49+00:00 [haddock @ 2002-05-29 09:09:49 by simonmar] Back out previous change until we can find a better way to do this. - - - - - 9234389c by Simon Marlow at 2002-05-29T13:19:06+00:00 [haddock @ 2002-05-29 13:19:06 by simonmar] Make the markup syntax a little more friendly: - single quotes are now interpreted literally unless they surround a valid Haskell identifier. So for example now there's no need to escape a single quote used as an apostrophe. - text to the right of a bird track is now literal (if you want marked-up text in a code block, use @...@). - - - - - b3333526 by Simon Marlow at 2002-05-29T13:38:51+00:00 [haddock @ 2002-05-29 13:38:51 by simonmar] Document recent changes to markup syntax - - - - - f93641d6 by Simon Marlow at 2002-05-29T15:27:18+00:00 [haddock @ 2002-05-29 15:27:18 by simonmar] Include the instances in abstract data types too - - - - - 613f21e3 by Simon Marlow at 2002-06-03T13:05:58+00:00 [haddock @ 2002-06-03 13:05:57 by simonmar] Allow exporting of individual class methods and record selectors. For these we have to invent the correct type signature, which we do in the simplest possible way (i.e. no context reduction nonsense in the class case). - - - - - 14b36807 by Simon Marlow at 2002-06-03T13:20:00+00:00 [haddock @ 2002-06-03 13:20:00 by simonmar] Fix linking to qualified names again (thanks to Sven Panne for pointing out the bug). - - - - - 95b10eac by Simon Marlow at 2002-06-03T13:46:48+00:00 [haddock @ 2002-06-03 13:46:48 by simonmar] Fix for exporting record selectors from a newtype declaration - - - - - 272f932e by Simon Marlow at 2002-06-03T13:56:38+00:00 [haddock @ 2002-06-03 13:56:38 by simonmar] update to version 0.3 - - - - - 1c0a3bed by Simon Marlow at 2002-06-03T14:05:07+00:00 [haddock @ 2002-06-03 14:05:07 by simonmar] Add changes in version 0.3 - - - - - 145b4626 by Simon Marlow at 2002-06-03T14:12:38+00:00 [haddock @ 2002-06-03 14:12:38 by simonmar] Render class names as proper binders - - - - - 052106b3 by Simon Marlow at 2002-06-03T14:15:10+00:00 [haddock @ 2002-06-03 14:15:10 by simonmar] update, and separate into bugs, features, and cosmetic items. - - - - - 854f4914 by Simon Marlow at 2002-06-03T14:16:13+00:00 [haddock @ 2002-06-03 14:16:13 by simonmar] More test cases - - - - - 466922c8 by Simon Marlow at 2002-06-03T14:16:56+00:00 [haddock @ 2002-06-03 14:16:56 by simonmar] Example from the paper - - - - - 9962a045 by Simon Marlow at 2002-06-03T14:17:49+00:00 [haddock @ 2002-06-03 14:17:49 by simonmar] A debugging version of the style-sheet, which gives some tables coloured backgrounds so we can see what's going on. - - - - - f16b79db by Simon Marlow at 2002-06-03T14:19:46+00:00 [haddock @ 2002-06-03 14:19:46 by simonmar] typo - - - - - 620db27b by Simon Marlow at 2002-06-03T14:48:32+00:00 [haddock @ 2002-06-03 14:48:32 by simonmar] oops, fix markup bugs - - - - - 53fd105c by Simon Marlow at 2002-06-05T09:05:07+00:00 [haddock @ 2002-06-05 09:05:07 by simonmar] Keep foreign imports when there is no export list (bug reported by Sven Panne). - - - - - 6d98989c by Simon Marlow at 2002-06-05T09:12:02+00:00 [haddock @ 2002-06-05 09:12:02 by simonmar] Identifiers in single quotes can be symbol names too (bug reported by Hal Daume). - - - - - 001811e5 by Sven Panne at 2002-06-08T14:03:36+00:00 [haddock @ 2002-06-08 14:03:36 by panne] Tiny workaround for the fact that Haddock currently ignores HsImportSpecs: Let the local_orig_env take precedence. This is no real solution at all, but improves things sometimes, e.g. in my GLUT documentation. :-) - - - - - 504d19c9 by Simon Marlow at 2002-06-11T09:23:25+00:00 [haddock @ 2002-06-11 09:23:25 by simonmar] portability nit - - - - - e13b5af4 by Simon Marlow at 2002-06-20T12:38:07+00:00 [haddock @ 2002-06-20 12:38:07 by simonmar] Empty declaration fixes. - - - - - f467a9b6 by Simon Marlow at 2002-06-20T12:39:02+00:00 [haddock @ 2002-06-20 12:39:01 by simonmar] Add support for a "prologue" - a description for the whole library, placed on the contents page before the module list. - - - - - b8dbfe20 by Simon Marlow at 2002-06-21T12:43:06+00:00 [haddock @ 2002-06-21 12:43:06 by simonmar] When we have a single code block paragraph, don't place it in <pre>..</pre>, just use <tt>..</tt> to avoid generating extra vertical white space in some browsers. - - - - - 4831dbbd by Simon Marlow at 2002-06-21T15:50:42+00:00 [haddock @ 2002-06-21 15:50:42 by simonmar] Add support for reading and writing interface files(!) This turned out to be quite easy, and necessary to get decent hyperlinks between the documentation for separate packages in the libraries. The functionality isn't quite complete yet: for a given package of modules, you'd like to say "the HTML for these modules lives in directory <dir>" (currently they are assumed to be all in the same place). Two new flags: --dump-interface=FILE dump an interface file in FILE --read-interface=FILE read interface from FILE an interface file describes *all* the modules being processed. Only the exported names are kept in the interface: if you re-export a name from a module in another interface the signature won't be copied. This is a compromise to keep the size of the interfaces sensible. Also, I added another useful option: --no-implicit-prelude avoids trying to import the Prelude. Previously this was the default, but now importing the Prelude from elsewhere makes sense if you also read in an interface containing the Prelude module, so Haddock imports the Prelude implicitly according to the Haskell spec. - - - - - d3640a19 by Sven Panne at 2002-06-23T14:54:00+00:00 [haddock @ 2002-06-23 14:54:00 by panne] Make it compile with newer GHCs - - - - - 780c506b by Sven Panne at 2002-06-23T15:44:31+00:00 [haddock @ 2002-06-23 15:44:31 by panne] Cleaned up build root handling and added more docs - - - - - 45290d2e by Simon Marlow at 2002-06-24T14:37:43+00:00 [haddock @ 2002-06-24 14:37:42 by simonmar] When reading an interface, allow a file path offset to be specified which represents the path to the HTML files for the modules specified by that interface. The path may be either relative (to the location of the HTML for this package), or absolute. The syntax is --read-interface=PATH,FILE where PATH is the path to the HTML, and FILE is the filename containing the interface. - - - - - 4e2b9ae6 by Simon Marlow at 2002-07-03T16:01:08+00:00 [haddock @ 2002-07-03 16:01:07 by simonmar] Handle import specs properly, include 'hiding'. Haddock now has a complete implementation of the Haskell module system (more or less; I won't claim it's 100% correct). - - - - - 9a9aa1a8 by Simon Marlow at 2002-07-03T16:18:16+00:00 [haddock @ 2002-07-03 16:18:16 by simonmar] Update - - - - - 560c3026 by Simon Marlow at 2002-07-04T14:56:10+00:00 [haddock @ 2002-07-04 14:56:10 by simonmar] Clean up the code that constructs the exported declarations, and fix a couple of bugs along the way. Now if you import a class hiding one of the methods, then re-export the class, the version in the documentation will correctly have the appropriate method removed. - - - - - 2c26e77d by Simon Marlow at 2002-07-04T15:26:13+00:00 [haddock @ 2002-07-04 15:26:13 by simonmar] More bugfixes to the export handling - - - - - 03e0710d by Simon Marlow at 2002-07-09T10:12:10+00:00 [haddock @ 2002-07-09 10:12:10 by simonmar] Don't require that the list type comes from "Prelude" for it to be treated as special syntax (sometimes it comes from Data.List or maybe even GHC.Base). - - - - - 44f3891a by Simon Marlow at 2002-07-09T10:12:51+00:00 [haddock @ 2002-07-09 10:12:51 by simonmar] commented-out debugging code - - - - - 97280873 by Krasimir Angelov at 2002-07-09T16:33:33+00:00 [haddock @ 2002-07-09 16:33:31 by krasimir] 'Microsoft HTML Help' support - - - - - 3dc04655 by Simon Marlow at 2002-07-10T09:40:56+00:00 [haddock @ 2002-07-10 09:40:56 by simonmar] Fix for rendering of the (->) type constructor, from Ross Paterson. - - - - - c9f149c6 by Simon Marlow at 2002-07-10T10:26:11+00:00 [haddock @ 2002-07-10 10:26:11 by simonmar] Tweaks to the MS Help support: the extra files are now only generated if you ask for them (--ms-help). - - - - - e8acc1e6 by Simon Marlow at 2002-07-10T10:57:10+00:00 [haddock @ 2002-07-10 10:57:10 by simonmar] Document all the new options since 0.3 - - - - - 8bb85544 by Simon Marlow at 2002-07-10T10:58:31+00:00 [haddock @ 2002-07-10 10:58:31 by simonmar] Sort the options a bit - - - - - abc0dd59 by Simon Marlow at 2002-07-15T09:19:38+00:00 [haddock @ 2002-07-15 09:19:38 by simonmar] Fix a bug in mkExportItems when processing a module without an explicit export list. We were placing one copy of a declaration for each binder in the declaration, which for a data type would mean one copy of the whole declaration per constructor or record selector. - - - - - dde65bb9 by Simon Marlow at 2002-07-15T09:54:16+00:00 [haddock @ 2002-07-15 09:54:16 by simonmar] merge rev. 1.35 - - - - - bd7eb8c4 by Simon Marlow at 2002-07-15T10:14:31+00:00 [haddock @ 2002-07-15 10:14:30 by simonmar] Be a bit more liberal in the kind of commenting styles we allow, as suggested by Malcolm Wallace. Mostly this consists of allowing doc comments either side of a separator token. In an export list, a section heading is now allowed before the comma, as well as after it. eg. module M where ( T(..) -- * a section heading , f -- * another section heading , g ) In record fields, doc comments are allowed anywhere (previously a doc-next was allowed only after the comma, and a doc-before was allowed only before the comma). eg. data R = C { -- | describes 'f' f :: Int -- | describes 'g' , g :: Int } - - - - - 8f6dfe34 by Simon Marlow at 2002-07-15T10:21:56+00:00 [haddock @ 2002-07-15 10:21:56 by simonmar] Mention alternative commenting styles. - - - - - fc515bb7 by Simon Marlow at 2002-07-15T16:16:50+00:00 [haddock @ 2002-07-15 16:16:50 by simonmar] Allow multiple sections/subsections before and after a comma in the export list. Also at the same time I made the syntax a little stricter (multiple commas now aren't allowed between export specs). - - - - - 80a97e74 by Simon Marlow at 2002-07-19T09:13:10+00:00 [haddock @ 2002-07-19 09:13:10 by simonmar] Allow special id's ([], (), etc.) to be used in an import declaration. - - - - - a69d7378 by Simon Marlow at 2002-07-19T09:59:02+00:00 [haddock @ 2002-07-19 09:59:02 by simonmar] Allow special id's ([], (), etc.) to be used in an import declarations. - - - - - d205fa60 by Simon Marlow at 2002-07-19T10:00:16+00:00 [haddock @ 2002-07-19 10:00:16 by simonmar] Relax the restrictions which require doc comments to be followed by semi colons - in some cases this isn't necessary. Now you can write module M where { -- | some doc class C where {} } without needing to put a semicolon before the class declaration. - - - - - e9301e14 by Simon Marlow at 2002-07-23T08:24:09+00:00 [haddock @ 2002-07-23 08:24:09 by simonmar] A new TODO list item - - - - - e5d77586 by Simon Marlow at 2002-07-23T08:40:56+00:00 [haddock @ 2002-07-23 08:40:56 by simonmar] - update the acknowledgements - remove the paragraph that described how to use explicit layout with doc comments; it isn't relevant any more. - - - - - 78a94137 by Simon Marlow at 2002-07-23T08:43:02+00:00 [haddock @ 2002-07-23 08:43:02 by simonmar] more tests - - - - - 5c320927 by Simon Marlow at 2002-07-23T08:43:26+00:00 [haddock @ 2002-07-23 08:43:26 by simonmar] Updates for version 0.4 - - - - - 488e99ae by Simon Marlow at 2002-07-23T09:10:46+00:00 [haddock @ 2002-07-23 09:10:46 by simonmar] Fix the %changelog (rpm complained that it wasn't in the right order) - - - - - a77bb373 by Simon Marlow at 2002-07-23T09:12:38+00:00 [haddock @ 2002-07-23 09:12:38 by simonmar] Another item for the TODO list - - - - - f1ec1813 by Simon Marlow at 2002-07-23T10:18:46+00:00 [haddock @ 2002-07-23 10:18:46 by simonmar] Add a version banner when invoked with -v - - - - - 1d44cadf by Simon Marlow at 2002-07-24T09:28:19+00:00 [haddock @ 2002-07-24 09:28:19 by simonmar] Remove ^Ms - - - - - 4d8d5e94 by Simon Marlow at 2002-07-24T09:42:18+00:00 [haddock @ 2002-07-24 09:42:17 by simonmar] Patches to quieten ghc -Wall, from those nice folks at Galois. - - - - - d6edc43e by Simon Marlow at 2002-07-25T14:37:29+00:00 [haddock @ 2002-07-25 14:37:28 by simonmar] Patch to allow simple hyperlinking to an arbitrary location in another module's documentation, from Volker Stolz. Now in a doc comment: #foo# creates <a name="foo"></a> And you can use the form "M\#foo" to hyperlink to the label 'foo' in module 'M'. Note that the backslash is necessary for now. - - - - - b34d18fa by Simon Marlow at 2002-08-02T09:08:22+00:00 [haddock @ 2002-08-02 09:08:22 by simonmar] The <TT> and <PRE> environments seem to use a font that is a little too small in IE. Compensate. (suggestion from Daan Leijen). - - - - - 8106b086 by Simon Marlow at 2002-08-02T09:25:23+00:00 [haddock @ 2002-08-02 09:25:20 by simonmar] Remove <P>..</P> from around list items, to reduce excess whitespace between the items of bulleted and ordered lists. (Suggestion from Daan Leijen). - - - - - c1acff8f by Simon Marlow at 2002-08-05T09:03:49+00:00 [haddock @ 2002-08-05 09:03:49 by simonmar] update - - - - - f968661c by Simon Marlow at 2002-11-11T09:32:57+00:00 [haddock @ 2002-11-11 09:32:57 by simonmar] Fix cut-n-pasto - - - - - 12d02619 by Simon Marlow at 2002-11-13T09:49:46+00:00 [haddock @ 2002-11-13 09:49:46 by simonmar] Small bugfix in the --read-interface option parsing from Brett Letner. - - - - - 30e32d5e by Ross Paterson at 2003-01-16T15:07:57+00:00 [haddock @ 2003-01-16 15:07:57 by ross] Adjust for the new exception libraries (as well as the old ones). - - - - - 871f65df by Sven Panne at 2003-02-20T21:31:40+00:00 [haddock @ 2003-02-20 21:31:40 by panne] * Add varsyms and consyms to index * Exclude empty entries from index - - - - - bc42cc87 by Sven Panne at 2003-02-24T21:26:29+00:00 [haddock @ 2003-02-24 21:26:29 by panne] Don't convert a "newtype" to a single-constructor "data" for non-abstractly exported types, they are quite different regarding strictness/pattern matching. Now a "data" without any constructors is only emitted for an abstractly exported type, regardless if it is actually a "newtype" or a "data". - - - - - 0c2a1d99 by Sven Panne at 2003-03-08T19:02:38+00:00 [haddock @ 2003-03-08 19:02:38 by panne] Fixed some broken/redirected/canonicalized links found by a very picky link checker. - - - - - 25459269 by Sven Panne at 2003-03-09T21:13:43+00:00 [haddock @ 2003-03-09 21:13:43 by panne] Don't append a fragment to non-defining index entries, only documents with a defining occurrence have a name anchor. - - - - - 6be4db86 by Sven Panne at 2003-03-10T21:34:25+00:00 [haddock @ 2003-03-10 21:34:24 by panne] Escape fragments. This fixes e.g. links to operators. - - - - - eb12972c by Ross Paterson at 2003-04-25T10:50:06+00:00 [haddock @ 2003-04-25 10:50:05 by ross] An 80% solution to generating derived instances. A complete solution would duplicate the instance inference logic, but if a type variable occurs as a constructor argument, then we can just propagate the derived class to the variable. But we know nothing of the constraints on any type variables that occur elsewhere. For example, the declarations data Either a b = Left a | Right b deriving (Eq, Ord) data Ptr a = Ptr Addr# deriving (Eq, Ord) newtype IORef a = IORef (STRef RealWorld a) deriving Eq yield the instances (Eq a, Eq b) => Eq (Either a b) (Ord a, Ord b) => Ord (Either a b) Eq (Ptr a) Ord (Ptr a) (??? a) => Eq (IORef a) The last example shows the limits of this local analysis. Note that a type variable may be in both categories: then we know a constraint, but there may be more, or a stronger constraint, e.g. data Tree a = Node a [Tree a] deriving Eq yields (Eq a, ??? a) => Eq (Tree a) - - - - - de886f78 by Simon Marlow at 2003-04-25T11:17:55+00:00 [haddock @ 2003-04-25 11:17:55 by simonmar] Some updates, including moving the derived instance item down to the bottom of the list now that Ross has contributed some code that does the job for common cases. - - - - - 1b52cffd by Simon Marlow at 2003-04-30T14:02:32+00:00 [haddock @ 2003-04-30 14:02:32 by simonmar] When installing on Windows, run cygpath over $(HADDOCKLIB) so that haddock (a mingw program, built by GHC) can understand it. You still need to be in a cygwin environment to run Haddock, because of the shell script wrapper. - - - - - d4f638de by Simon Marlow at 2003-05-06T10:04:47+00:00 [haddock @ 2003-05-06 10:04:47 by simonmar] Catch another case of a paragraph containing just a DocMonospaced that should turn into a DocCodeBlock. - - - - - 4162b2b9 by Simon Marlow at 2003-05-06T10:11:44+00:00 [haddock @ 2003-05-06 10:11:44 by simonmar] Add some more code-block tests. - - - - - 4f5802c8 by Simon Marlow at 2003-05-06T10:14:52+00:00 [haddock @ 2003-05-06 10:14:52 by simonmar] Don't turn a single DocCodeBlock into a DocMonospaced, because that tends to remove the line breaks in the code. - - - - - ef8c45f7 by Simon Marlow at 2003-05-21T15:07:21+00:00 [haddock @ 2003-05-21 15:07:21 by simonmar] Only omit the module contents when there are no section headings at all. - - - - - bcee1e75 by Sigbjorn Finne at 2003-05-30T16:50:45+00:00 [haddock @ 2003-05-30 16:50:45 by sof] cygpath: for now, steer clear of --mixed - - - - - 30567af3 by Sigbjorn Finne at 2003-05-30T17:59:28+00:00 [haddock @ 2003-05-30 17:59:28 by sof] oops, drop test defn from prev commit - - - - - b0856e7d by Simon Marlow at 2003-06-03T09:55:26+00:00 [haddock @ 2003-06-03 09:55:26 by simonmar] Two small fixes to make the output valid HTML 4.01 (transitional). Thanks to Malcolm Wallace for pointing out the problems. - - - - - 70e137ea by Simon Marlow at 2003-07-28T13:30:35+00:00 [haddock @ 2003-07-28 13:30:35 by simonmar] Add tests for a couple of bugs. - - - - - 122bd578 by Simon Marlow at 2003-07-28T13:31:25+00:00 [haddock @ 2003-07-28 13:31:25 by simonmar] Add documentation for anchors. - - - - - 0bd27cb2 by Simon Marlow at 2003-07-28T13:31:46+00:00 [haddock @ 2003-07-28 13:31:46 by simonmar] Update - - - - - 08052d42 by Simon Marlow at 2003-07-28T13:32:12+00:00 [haddock @ 2003-07-28 13:32:12 by simonmar] layout tweak. - - - - - 13942749 by Simon Marlow at 2003-07-28T13:33:03+00:00 [haddock @ 2003-07-28 13:33:03 by simonmar] Differentiate links to types/classes from links to variables/constructors with a prefix ("t:" and "v:" respectively). - - - - - d7f493b9 by Simon Marlow at 2003-07-28T13:35:17+00:00 [haddock @ 2003-07-28 13:35:16 by simonmar] When a module A exports another module's contents via 'module B', then modules which import entities from B re-exported by A should link to B.foo rather than A.foo. See examples/Bug2.hs. - - - - - d94cf705 by Simon Marlow at 2003-07-28T13:36:14+00:00 [haddock @ 2003-07-28 13:36:14 by simonmar] Update to version 0.5 - - - - - dbb776cd by Sven Panne at 2003-07-28T14:02:43+00:00 [haddock @ 2003-07-28 14:02:43 by panne] * Updated to version 0.5 * Automagically generate configure if it is not there - - - - - 6cfeee53 by Simon Marlow at 2003-07-28T14:32:43+00:00 [haddock @ 2003-07-28 14:32:42 by simonmar] Update to avoid using hslibs with GHC >= 5.04 - - - - - a1ce838f by Simon Marlow at 2003-07-28T14:33:37+00:00 [haddock @ 2003-07-28 14:33:37 by simonmar] Update for 0.5 - - - - - c0fe6493 by Simon Marlow at 2003-07-28T14:53:22+00:00 [haddock @ 2003-07-28 14:53:22 by simonmar] Markup fix - - - - - 6ea31596 by Sven Panne at 2003-07-28T16:40:45+00:00 [haddock @ 2003-07-28 16:40:45 by panne] Make it compile with GHC >= 6.01 - - - - - afcd30fc by Simon Marlow at 2003-07-30T15:04:52+00:00 [haddock @ 2003-07-30 15:04:52 by simonmar] Pay attention to import specs when building the the import env, as well as the orig env. This may fix some wrong links in documentation when import specs are being used. - - - - - 17c3137f by Simon Marlow at 2003-07-30T16:05:41+00:00 [haddock @ 2003-07-30 16:05:40 by simonmar] Rename instances based on the import_env for the module in which they are to be displayed. This should give, in many cases, better links for the types and classes mentioned in the instance head. This involves keeping around the import_env in the iface until the end, because instances are not collected up until all the modules have been processed. Fortunately it doesn't seem to affect performance much. Instance heads are now attached to ExportDecls, rather than the HTML backend passing around a separate mapping for instances. This is a cleanup. - - - - - 3d3b5c87 by Sven Panne at 2003-08-04T10:18:24+00:00 [haddock @ 2003-08-04 10:18:24 by panne] Don't print parentheses around one-element contexts - - - - - 9e3f3f2d by Simon Marlow at 2003-08-04T12:59:47+00:00 [haddock @ 2003-08-04 12:59:47 by simonmar] A couple of TODOs. - - - - - e9d8085c by Simon Marlow at 2003-08-05T14:10:31+00:00 [haddock @ 2003-08-05 14:10:31 by simonmar] I'm not sure why, but it seems that the index entries for non-defining occurrences of entities did not have an anchor - the link just pointed to the module. This fixes it. - - - - - ff5c7d6d by Simon Marlow at 2003-08-15T14:42:59+00:00 [haddock @ 2003-08-15 14:42:59 by simonmar] Convert the lexer to Alex, and fix a bug in the process. - - - - - 1aa077bf by Simon Marlow at 2003-08-15T15:00:18+00:00 [haddock @ 2003-08-15 15:00:18 by simonmar] Update - - - - - d3de1e38 by Simon Marlow at 2003-08-15T15:01:03+00:00 [haddock @ 2003-08-15 15:01:03 by simonmar] wibbles - - - - - b40ece3b by Simon Marlow at 2003-08-18T10:04:47+00:00 [haddock @ 2003-08-18 10:04:47 by simonmar] Lex the 'mdo' keyword as 'do'. - - - - - 8f9a1146 by Simon Marlow at 2003-08-18T11:48:24+00:00 [haddock @ 2003-08-18 11:48:24 by simonmar] Two bugs from Sven. - - - - - ea54ebc0 by Simon Marlow at 2003-08-18T11:48:46+00:00 [haddock @ 2003-08-18 11:48:46 by simonmar] Fixes to the new lexer. - - - - - d5f6a4b5 by Simon Marlow at 2003-08-19T09:09:03+00:00 [haddock @ 2003-08-19 09:09:03 by simonmar] Further wibbles to the syntax. - - - - - 6bbdadb7 by Sven Panne at 2003-08-26T18:45:35+00:00 [haddock @ 2003-08-26 18:45:35 by panne] Use autoreconf instead of autoconf - - - - - 32e889cb by Sven Panne at 2003-08-26T19:01:19+00:00 [haddock @ 2003-08-26 19:01:18 by panne] Made option handling a bit more consistent with other tools, in particular: Every program in fptools should output * version info on stdout and terminate successfully when -V or --version * usage info on stdout and terminate successfully when -? or --help * usage info on stderr and terminate unsuccessfully when an unknown option is given. - - - - - 5d156a91 by Sven Panne at 2003-08-26T19:20:55+00:00 [haddock @ 2003-08-26 19:20:55 by panne] Make it *very* clear that we terminate when given a -V/--version flag - - - - - e6577265 by Sven Panne at 2003-08-27T07:50:03+00:00 [haddock @ 2003-08-27 07:50:02 by panne] * Made -D a short option for --dump-interface. * Made -m a short option for --ms-help. * Made -n a short option for --no-implicit-prelude. * Made -c a short option for --css. * Removed DocBook options from executable (they didn't do anything), but mark them as reserved in the docs. Note that the short option for DocBook output is now -S (from SGML) instead of -d. The latter is now a short option for --debug. * The order of the Options in the documentation now matches the order printed by Haddock itself. Note: Although changing the names of options is often a bad idea, I'd really like to make the options for the programs in fptools more consistent and compatible to the ones used in common GNU programs. - - - - - d303ff98 by Simon Marlow at 2003-09-10T08:23:48+00:00 [haddock @ 2003-09-10 08:23:48 by simonmar] Add doc subdir. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 9a70e46a by Simon Marlow at 2003-09-10T08:24:32+00:00 [haddock @ 2003-09-10 08:24:32 by simonmar] Install these files in $(datadir), not $(libdir), since they're architecture independent. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - bbb87e7a by Simon Marlow at 2003-09-10T08:25:31+00:00 [haddock @ 2003-09-10 08:25:31 by simonmar] Haddock's supplementary HTML bits now live in $(datadir), not $(libdir). Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 3587c24b by Simon Marlow at 2003-09-22T10:34:38+00:00 [haddock @ 2003-09-22 10:34:38 by simonmar] Allow installing of docs. - - - - - d510b517 by Sven Panne at 2003-10-11T08:10:44+00:00 [haddock @ 2003-10-11 08:10:44 by panne] Include architecture-independent files in file list - - - - - 187d7618 by Sigbjorn Finne at 2003-10-20T17:19:24+00:00 [haddock @ 2003-10-20 17:19:22 by sof] support for i-parameters + zip comprehensions - - - - - b6c7a273 by Simon Marlow at 2003-11-03T14:24:24+00:00 [haddock @ 2003-11-03 14:24:24 by simonmar] Update TODO file. - - - - - 58513e33 by Simon Marlow at 2003-11-05T11:22:04+00:00 [haddock @ 2003-11-05 11:22:04 by simonmar] Remove the last of the uses of 'trace' to emit warnings, and tidy up a couple of places where duplicate warnings were being emitted. - - - - - 33a78846 by Simon Marlow at 2003-11-05T11:30:53+00:00 [haddock @ 2003-11-05 11:30:52 by simonmar] - Suppress warnings about unknown imported modules by default. - Add a -v/--verbose flag to re-enable these warnings. The general idea is to suppress the "Warning: unknown module: Prelude" warnings which most Haddock users will see every time, and which aren't terribly useful. - - - - - a969de7f by Simon Marlow at 2003-11-05T12:30:28+00:00 [haddock @ 2003-11-05 12:30:28 by simonmar] - Remove the emboldening of index entries for defining locations. This isn't useful, and breaks abstractions. - If an entity is re-exported by a module but the module doesn't include documentation for that entity (perhaps because it is re-exported by 'module M'), then don't attempt to hyperlink to the documentation from the index. Instead, just list that module in the index, to indicate that the entity is exported from there. - - - - - f14ea82a by Simon Marlow at 2003-11-05T15:15:59+00:00 [haddock @ 2003-11-05 15:15:59 by simonmar] Index overhaul: - no more separate type/class and variable/function indices - the index now makes a distinction between different entities with the same name. One example is a type constructor with the same name as a data constructor, but another example is simply a function with the same name exported by two different modules. For example, the index entry for 'catch' now looks like this: catch 1 (Function) Control.Exception 2 (Function) GHC.Exception, Prelude, System.IO, System.IO.Error making it clear that there are two different 'catch'es, but one of them is exported by several modules. - Each index page now has the index contents (A B C ...) at the top. Please let me know if you really hate any of this. - - - - - 01a25ca6 by Simon Marlow at 2003-11-05T15:16:38+00:00 [haddock @ 2003-11-05 15:16:38 by simonmar] Update - - - - - 1a7ccb86 by Simon Marlow at 2003-11-05T17:16:05+00:00 [haddock @ 2003-11-05 17:16:04 by simonmar] Support for generating a single unified index for several packages. --use-index=URL turns off normal index generation, causes Index links to point to URL. --gen-index generates an combined index from the specified interfaces. Currently doesn't work exactly right, because the interfaces don't contain the iface_reexported info. I'll need to fix that up. - - - - - a2bca16d by Simon Marlow at 2003-11-06T10:44:52+00:00 [haddock @ 2003-11-06 10:44:52 by simonmar] Include iface_reexported in the .haddock file. This unfortunately bloats the file (40% for base). If this gets to be a problem we can always apply the dictionary trick that GHC uses for squashing .hi files. - - - - - 0a09c293 by Simon Marlow at 2003-11-06T12:39:47+00:00 [haddock @ 2003-11-06 12:39:46 by simonmar] - Add definition lists, marked up like this: -- | This is a definition list: -- -- [@foo@] The description of @foo at . -- -- [@bar@] The description of @bar at . Cunningly, the [] characters are not treated specially unless a [ is found at the beginning of a paragraph, in which case the ] becomes special in the following text. - Add --use-contents and --gen-contents, along the lines of --use-index and --gen-index added yesterday. Now we can generate a combined index and contents for the whole of the hierarchical libraries, and in theory the index/contents on the system could be updated as new packages are added. - - - - - fe1b3460 by Simon Marlow at 2003-11-06T14:47:36+00:00 [haddock @ 2003-11-06 14:47:36 by simonmar] Remove the 'Parent' button - it is of dubious use, and often points into thin air. - - - - - db6d762f by Simon Marlow at 2003-11-06T16:48:14+00:00 [haddock @ 2003-11-06 16:48:11 by simonmar] - Include the OptHide setting in the interface, so we don't include hidden modules in the combined index/contents. - Add a -k/--package flag to set the package name for the current set of modules. The package name for each module is now shown in the right-hand column of the contents, in a combined contents page. - - - - - 7d71718b by Simon Marlow at 2003-11-06T16:50:28+00:00 [haddock @ 2003-11-06 16:50:28 by simonmar] Add -k/--package docs - - - - - ef43949d by Simon Marlow at 2003-11-06T16:51:23+00:00 [haddock @ 2003-11-06 16:51:23 by simonmar] Bump to 0.6 - - - - - 1c419e06 by Simon Marlow at 2003-11-06T16:51:50+00:00 [haddock @ 2003-11-06 16:51:50 by simonmar] update - - - - - 69422327 by Simon Marlow at 2003-11-10T14:41:06+00:00 [haddock @ 2003-11-10 14:41:05 by simonmar] Re-exporting names from a different package is problematic, because we don't have access to the full documentation for the entity. Currently Haddock just ignores entities with no documentation, but this results in bogus-looking empty documentation for many of the modules in the haskell98 package. So: - the documentation will now just list the name, as a link pointing to the location of the actual documentation. - now we don't attempt to link to these re-exported entities if they are referred to by the current module. Additionally: - If there is no documentation in the current module, include just the Synopsis section (rather than just the documentation section, as it was before). This just looks nicer and was on the TODO list. - - - - - 3c3fc433 by Simon Marlow at 2003-11-10T14:51:59+00:00 [haddock @ 2003-11-10 14:51:59 by simonmar] Fix for getReExports: take into account names which are not visible because they are re-exported from a different package. - - - - - 31c8437b by Simon Marlow at 2003-11-10T15:10:53+00:00 [haddock @ 2003-11-10 15:10:53 by simonmar] Version 0.6 changes - - - - - a7c2430b by Simon Marlow at 2003-11-10T15:15:58+00:00 [haddock @ 2003-11-10 15:15:58 by simonmar] getReExports: one error case that isn't - - - - - 00cc459c by Simon Marlow at 2003-11-10T16:15:19+00:00 [haddock @ 2003-11-10 16:15:18 by simonmar] copyright update - - - - - ca62408d by Simon Marlow at 2003-11-11T09:57:25+00:00 [haddock @ 2003-11-11 09:57:25 by simonmar] Version 0.6 - - - - - 3acbf818 by Simon Marlow at 2003-11-11T12:10:44+00:00 [haddock @ 2003-11-11 12:10:44 by simonmar] Go back to producing just the documentation section, rather than just the synopsis section, for a module with no documentation annotations. One reason is that the synopsis section tries to link each entity to its documentation on the same page. Also, the doc section anchors each entity, and it lists instances which the synopsis doesn't. - - - - - 6c90abc2 by Simon Marlow at 2003-11-12T10:03:39+00:00 [haddock @ 2003-11-12 10:03:39 by simonmar] 2002 -> 2003 - - - - - 090bbc4c by Simon Marlow at 2003-11-28T12:08:00+00:00 [haddock @ 2003-11-28 12:08:00 by simonmar] update - - - - - 8096a832 by Simon Marlow at 2003-11-28T12:09:58+00:00 [haddock @ 2003-11-28 12:09:58 by simonmar] Fix some of the problems with Haddock generating pages that are too wide. Now we only specify 'nowrap' when it is necessary to avoid a code box getting squashed up by the text to the right of it. - - - - - 35294929 by Sven Panne at 2003-12-29T17:16:31+00:00 [haddock @ 2003-12-29 17:16:31 by panne] Updated my email address - - - - - cdb697bf by Simon Marlow at 2004-01-08T10:14:24+00:00 [haddock @ 2004-01-08 10:14:24 by simonmar] Add instructions for using GHC to pre-process source for feeding to Haddock. - - - - - 8dfc491f by Simon Marlow at 2004-01-09T12:45:46+00:00 [haddock @ 2004-01-09 12:45:46 by simonmar] Add -optP-P to example ghc command line. - - - - - ac41b820 by Simon Marlow at 2004-02-03T11:02:03+00:00 [haddock @ 2004-02-03 11:02:03 by simonmar] Fix bug in index generation - - - - - f4e7edcb by Simon Marlow at 2004-02-10T11:51:16+00:00 [haddock @ 2004-02-10 11:51:16 by simonmar] Don't throw away whitespace at the beginning of a line (experimental fix). - - - - - 68e212d2 by Simon Marlow at 2004-02-10T12:10:08+00:00 [haddock @ 2004-02-10 12:10:08 by simonmar] Fix for previous commit: I now realise why the whitespace was stripped from the beginning of the line. Work around it. - - - - - e7d7f2df by Sven Panne at 2004-02-10T18:38:45+00:00 [haddock @ 2004-02-10 18:38:45 by panne] Make Haddock link with the latest relocated monad transformer package - - - - - 992d4225 by Simon Marlow at 2004-02-16T10:21:35+00:00 [haddock @ 2004-02-16 10:21:35 by simonmar] Add a TODO - - - - - 1ac55326 by Simon Marlow at 2004-03-12T11:33:39+00:00 [haddock @ 2004-03-12 11:33:39 by simonmar] Add an item. - - - - - 0478e903 by Simon Marlow at 2004-03-15T12:24:05+00:00 [haddock @ 2004-03-15 12:24:05 by simonmar] Add an item. - - - - - 6f26d21a by Simon Marlow at 2004-03-18T14:21:29+00:00 [haddock @ 2004-03-18 14:21:29 by simonmar] Fix URL - - - - - 19b6bb99 by Simon Marlow at 2004-03-22T14:09:03+00:00 [haddock @ 2004-03-22 14:09:03 by simonmar] getReExports was bogus: we should really look in the import_env to find the documentation for an entity which we are re-exporting without documentation. Suggested by: Ross Paterson (patch modified by me). - - - - - 5c756031 by Simon Marlow at 2004-03-24T09:42:11+00:00 [haddock @ 2004-03-24 09:42:10 by simonmar] hiding bug from Ross Paterson (fixed in rev 1.59 of Main.hs) - - - - - 1b692e6c by Simon Marlow at 2004-03-24T10:10:50+00:00 [haddock @ 2004-03-24 10:10:50 by simonmar] mkExportItems fix & simplification: we should be looking at the actual exported names (calculated earlier) to figure out which subordinates of a declaration are exported. This means that if you export a record, and name its fields separately in the export list, the fields will still be visible in the documentation for the constructor. - - - - - 90e5e294 by Simon Marlow at 2004-03-24T10:12:08+00:00 [haddock @ 2004-03-24 10:12:08 by simonmar] Make restrictCons take into account record field names too (removing a ToDo). - - - - - 2600efa4 by Simon Marlow at 2004-03-24T10:16:17+00:00 [haddock @ 2004-03-24 10:16:17 by simonmar] Record export tests. - - - - - 6a8575c7 by Simon Marlow at 2004-03-25T09:35:14+00:00 [haddock @ 2004-03-25 09:35:14 by simonmar] restrictTo: fix for restricting a newtype with a record field. - - - - - dcf55a8d by Simon Marlow at 2004-03-25T10:01:42+00:00 [haddock @ 2004-03-25 10:01:42 by simonmar] Fix duplicate instance bug - - - - - f49aa758 by Simon Marlow at 2004-03-25T10:02:41+00:00 [haddock @ 2004-03-25 10:02:41 by simonmar] Duplicate instance bug. - - - - - 7b87344c by Simon Marlow at 2004-03-25T10:29:56+00:00 [haddock @ 2004-03-25 10:29:56 by simonmar] If a name is imported from two places, one hidden and one not, choose the unhidden one to link to. Also, when there's only a hidden module to link to, don't try linking to it. - - - - - 40f44d7b by Simon Marlow at 2004-03-25T15:17:24+00:00 [haddock @ 2004-03-25 15:17:23 by simonmar] Add support for collaspible parts of the page, with a +/- button and a bit of JavaScript. Make the instances collapsible, and collapse them by default. This makes documentation with long lists of instances (eg. the Prelude) much easier to read. Maybe we should give other documentation sections the same treatment. - - - - - 9b64dc0f by Simon Marlow at 2004-03-25T15:20:55+00:00 [haddock @ 2004-03-25 15:20:55 by simonmar] Update - - - - - c2fff7f2 by Simon Marlow at 2004-03-25T15:45:10+00:00 [haddock @ 2004-03-25 15:45:10 by simonmar] Eliminate some unnecessary spaces in the HTML rendering - - - - - b7948ff0 by Simon Marlow at 2004-03-25T16:00:37+00:00 [haddock @ 2004-03-25 16:00:36 by simonmar] Remove all that indentation in the generated HTML to keep the file sizes down. - - - - - da2bb4ca by Sven Panne at 2004-03-27T09:57:58+00:00 [haddock @ 2004-03-27 09:57:57 by panne] Added the new-born haddock.js to the build process and the documentation. - - - - - b99e6f8c by Sven Panne at 2004-03-27T10:32:20+00:00 [haddock @ 2004-03-27 10:32:20 by panne] "type" is a required attribute of the "script" element - - - - - 562b185a by Sven Panne at 2004-03-27T12:52:34+00:00 [haddock @ 2004-03-27 12:52:34 by panne] Add a doctype for the contents page, too. - - - - - f6a99c2d by Simon Marlow at 2004-04-14T10:03:25+00:00 [haddock @ 2004-04-14 10:03:25 by simonmar] fix for single-line comment syntax - - - - - de366303 by Simon Marlow at 2004-04-20T13:08:04+00:00 [haddock @ 2004-04-20 13:08:04 by simonmar] Allow a 'type' declaration to include documentation comments. These will be ignored by Haddock, but at least one user (Johannes Waldmann) finds this feature useful, and it's easy to add. - - - - - fd78f51e by Simon Marlow at 2004-05-07T15:14:56+00:00 [haddock @ 2004-05-07 15:14:56 by simonmar] - update copyright - add version to abstract - - - - - 59f53e32 by Sven Panne at 2004-05-09T14:39:53+00:00 [haddock @ 2004-05-09 14:39:53 by panne] Fix the fix for single-line comment syntax, ------------------------------------------- is now a valid comment line again. - - - - - 8b18f2fe by Simon Marlow at 2004-05-10T10:11:51+00:00 [haddock @ 2004-05-10 10:11:51 by simonmar] Update - - - - - 225a491d by Ross Paterson at 2004-05-19T13:10:23+00:00 [haddock @ 2004-05-19 13:10:23 by ross] Make the handling of "deriving" slightly smarter, by ignoring data constructor arguments that are identical to the lhs. Now handles things like data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving ... - - - - - 37588686 by Mike Thomas at 2004-05-21T06:38:14+00:00 [haddock @ 2004-05-21 06:38:14 by mthomas] Windows exe extensions (bin remains for Unix). - - - - - cf2b9152 by Simon Marlow at 2004-05-25T09:34:54+00:00 [haddock @ 2004-05-25 09:34:54 by simonmar] Add some TODO items - - - - - 4d29cdfc by Simon Marlow at 2004-05-25T10:41:46+00:00 [haddock @ 2004-05-25 10:41:46 by simonmar] Complain if -h is used with --gen-index or --gen-contents, because it'll overwrite the new index/contents. - - - - - 2e0771e0 by Mike Thomas at 2004-05-28T20:17:55+00:00 [haddock @ 2004-05-28 20:17:55 by mthomas] Windows: search for templates in executable directory. Unix: Haddock tries cwd first rather than error if no -l arg. - - - - - 8d10bde1 by Sven Panne at 2004-06-05T16:53:34+00:00 [haddock @ 2004-06-05 16:53:34 by panne] Misc. rpm spec file cleanup, including: * make BuildRoot handling more consistent * added default file attributes * consistent defines and tags - - - - - 59974349 by Sven Panne at 2004-06-05T18:01:00+00:00 [haddock @ 2004-06-05 18:01:00 by panne] More rpm spec file cleanup, including: * added some BuildRequires * changed packager to me, so people can complain at the right place :-] * consistently refer to haskell.org instead of www.haskell.org - - - - - b94d4903 by Simon Marlow at 2004-07-01T11:08:58+00:00 [haddock @ 2004-07-01 11:08:57 by simonmar] Update to the +/- buttons: use a resized image rather than a <button>. Still seeing some strange effects in Konqueror, so might need to use a fixed-size image instead. - - - - - d5278f67 by Sven Panne at 2004-07-04T15:15:55+00:00 [haddock @ 2004-07-04 15:15:55 by panne] Install pictures for +/- pictures, too (JPEG is a strange format for graphics like this, I would have expected GIF or PNG here.) Things look fine with Konqueror and Netscape on Linux now, the only downside is that the cursor doesn't change when positioned above the "button". - - - - - 46dec6c5 by Sven Panne at 2004-07-13T17:59:28+00:00 [haddock @ 2004-07-13 17:59:28 by panne] A quote is a valid part of a Haskell identifier, but it would interfere with an ECMA script string delimiter, so escape it there. - - - - - 1d7bc432 by Simon Marlow at 2004-07-22T08:54:06+00:00 [haddock @ 2004-07-22 08:54:06 by simonmar] Add single quote to $ident, so you can say eg. 'foldl'' to refer to foldl' (the longest match rule is our friend). Bug reported by Adrian Hey <ahey at iee.org> - - - - - f183618b by Krasimir Angelov at 2004-07-27T22:59:35+00:00 [haddock @ 2004-07-27 22:58:23 by krasimir] Add basic support for Microsoft HTML Help 2.0 - - - - - d515d0c2 by Krasimir Angelov at 2004-07-27T23:02:36+00:00 [haddock @ 2004-07-27 23:02:36 by krasimir] escape names in the index - - - - - a5f1be23 by Krasimir Angelov at 2004-07-27T23:05:21+00:00 [haddock @ 2004-07-27 23:05:21 by krasimir] Add jsFile, plusFile and minusFile to the file list - - - - - c4fb4881 by Krasimir Angelov at 2004-07-28T22:12:10+00:00 [haddock @ 2004-07-28 22:12:09 by krasimir] bugfix. Move contentsHtmlFile, indexHtmlFile and subIndexHtmlFile functions to HaddockUtil.hs module to make them accessible from HaddockHH2.hs - - - - - 64d30b1d by Krasimir Angelov at 2004-07-30T22:15:47+00:00 [haddock @ 2004-07-30 22:15:45 by krasimir] more stuffs - support for separated compilation of packages - the contents page now uses DHTML TreeView - fixed copyFile bug - - - - - 133c8c5c by Krasimir Angelov at 2004-07-31T12:04:38+00:00 [haddock @ 2004-07-31 12:04:37 by krasimir] make the DHtmlTree in contents page more portable. The +/- buttons are replaced with new images which looks more beatiful. - - - - - 79040963 by Krasimir Angelov at 2004-07-31T13:10:20+00:00 [haddock @ 2004-07-31 13:10:20 by krasimir] Make DHtmlTree compatible with Mozila browser - - - - - 1a55dc90 by Krasimir Angelov at 2004-07-31T14:52:55+00:00 [haddock @ 2004-07-31 14:52:55 by krasimir] fix - - - - - 85ce0237 by Krasimir Angelov at 2004-07-31T14:53:28+00:00 [haddock @ 2004-07-31 14:53:28 by krasimir] HtmlHelp 1.x - - - - - 3c0c53ba by Krasimir Angelov at 2004-07-31T20:35:21+00:00 [haddock @ 2004-07-31 20:35:21 by krasimir] Added support for DevHelp - - - - - d42b5af1 by Krasimir Angelov at 2004-07-31T21:17:51+00:00 [haddock @ 2004-07-31 21:17:51 by krasimir] Document new features in HtmlHelp - - - - - 790fe21e by Krasimir Angelov at 2004-08-01T15:14:02+00:00 [haddock @ 2004-08-01 15:14:02 by krasimir] add missing imports - - - - - fd7cc6bc by Krasimir Angelov at 2004-08-01T19:52:08+00:00 [haddock @ 2004-08-01 19:52:06 by krasimir] fix some bugs. Now I have got the entire libraries documentation in HtmlHelp 2.0 format. - - - - - 94ad7ac8 by Krasimir Angelov at 2004-08-01T19:53:50+00:00 [haddock @ 2004-08-01 19:53:50 by krasimir] I forgot to add the new +/- images - - - - - f0c65388 by Krasimir Angelov at 2004-08-02T16:25:53+00:00 [haddock @ 2004-08-02 16:25:53 by krasimir] Add root node to the table of contents. All modules in tree are not children of the root - - - - - f50bd85d by Sven Panne at 2004-08-02T18:17:46+00:00 [haddock @ 2004-08-02 18:17:46 by panne] Mainly DocBook fixes - - - - - 09527ce3 by Sven Panne at 2004-08-02T20:02:29+00:00 [haddock @ 2004-08-02 20:02:29 by panne] Fixed -o/--odir handling. Generating the output, especially the directory handling, is getting a bit convoluted nowadays... - - - - - c8fbacfa by Sven Panne at 2004-08-02T20:31:13+00:00 [haddock @ 2004-08-02 20:31:13 by panne] Warning police - - - - - 37830bff by Sven Panne at 2004-08-02T20:32:29+00:00 [haddock @ 2004-08-02 20:32:28 by panne] Nuked dead code - - - - - 13847171 by Sven Panne at 2004-08-02T21:12:27+00:00 [haddock @ 2004-08-02 21:12:25 by panne] Use pathJoin instead of low-level list-based manipulation for FilePaths - - - - - c711d61e by Sven Panne at 2004-08-02T21:16:02+00:00 [haddock @ 2004-08-02 21:16:02 by panne] Removed WinDoze CRs - - - - - b1f7dc88 by Sven Panne at 2004-08-03T19:35:59+00:00 [haddock @ 2004-08-03 19:35:59 by panne] Fixed spelling of "http-equiv" attribute - - - - - dd5f394e by Sven Panne at 2004-08-03T19:44:03+00:00 [haddock @ 2004-08-03 19:44:03 by panne] Pacify W3C validator: * Added document encoding (currently UTF-8, not sure if this is completely correct) * Fixed syntax of `id' attributes * Added necessary `alt' attribute for +/- images Small layout improvement: * Added space after +/- images (still not perfect, but better than before) - - - - - 919c47c6 by Sigbjorn Finne at 2004-08-03T19:45:11+00:00 [haddock @ 2004-08-03 19:45:11 by sof] make it compile with <= ghc-6.1 - - - - - 4d6f01d8 by Sigbjorn Finne at 2004-08-03T19:45:30+00:00 [haddock @ 2004-08-03 19:45:30 by sof] ffi wibble - - - - - 4770643a by Sven Panne at 2004-08-03T20:47:46+00:00 [haddock @ 2004-08-03 20:47:46 by panne] Fixed CSS for button style. Note that only "0" is a valid measure without a unit! - - - - - 14aaf2e5 by Sven Panne at 2004-08-03T21:07:59+00:00 [haddock @ 2004-08-03 21:07:58 by panne] Improved spacing of dynamic module tree - - - - - 97c3579a by Simon Marlow at 2004-08-09T11:03:04+00:00 [haddock @ 2004-08-09 11:03:04 by simonmar] Add FormatVersion Patch submitted by: George Russell <ger at informatik.uni-bremen.de> - - - - - af7f8c03 by Simon Marlow at 2004-08-09T11:55:07+00:00 [haddock @ 2004-08-09 11:55:05 by simonmar] Add support for a short description for each module, which is included in the contents. The short description should be given in a "Description: " field of the header. Included in this patch are changes that make the format of the header a little more flexible. From the comments: -- all fields in the header are optional and have the form -- -- [spaces1][field name][spaces] ":" -- [text]"\n" ([spaces2][space][text]"\n" | [spaces]"\n")* -- where each [spaces2] should have [spaces1] as a prefix. -- -- Thus for the key "Description", -- -- > Description : this is a -- > rather long -- > -- > description -- > -- > The module comment starts here -- -- the value will be "this is a .. description" and the rest will begin -- at "The module comment". The header fields must be in the following order: Module, Description, Copyright, License, Maintainer, Stability, Portability. Patches submitted by: George Russell <ger at informatik.uni-bremen.de>, with a few small changes be me, mostly to merge with other recent changes. ToDo: document the module header. - - - - - 7b865ad3 by Simon Marlow at 2004-08-10T14:09:57+00:00 [haddock @ 2004-08-10 14:09:57 by simonmar] Fixes for DevHelp/HtmlHelp following introduction of short module description. - - - - - 814766cd by Simon Marlow at 2004-08-10T14:33:46+00:00 [haddock @ 2004-08-10 14:33:45 by simonmar] Fixes to installation under Windows. - - - - - 39cf9ede by Simon Marlow at 2004-08-12T12:08:23+00:00 [haddock @ 2004-08-12 12:08:23 by simonmar] Avoid using string-gap tricks. - - - - - b6d78551 by Simon Marlow at 2004-08-13T10:53:21+00:00 [haddock @ 2004-08-13 10:53:21 by simonmar] Update - - - - - eaae7417 by Simon Marlow at 2004-08-13T10:53:50+00:00 [haddock @ 2004-08-13 10:53:50 by simonmar] Test for primes in quoted links - - - - - 68c34f06 by Sven Panne at 2004-08-16T19:59:38+00:00 [haddock @ 2004-08-16 19:59:36 by panne] XMLification - - - - - 7f45a6f9 by Sven Panne at 2004-08-18T16:42:54+00:00 [haddock @ 2004-08-18 16:42:54 by panne] Re-added indices + minor fixes - - - - - 8a5dd97c by Sigbjorn Finne at 2004-08-25T17:15:42+00:00 [haddock @ 2004-08-25 17:15:42 by sof] backquote HADDOCK_VERSION defn for <= ghc-6.0.x; believe this is only needed under mingw - - - - - 4b1b42ea by Sven Panne at 2004-08-26T20:08:50+00:00 [haddock @ 2004-08-26 20:08:49 by panne] SGML is dead, long live DocBook XML! Note: The BuildRequires tags in the spec files are still incomplete and the documentation about the DocBook tools needs to be updated, too. Stay tuned... - - - - - 8d52cedb by Sven Panne at 2004-08-26T21:03:19+00:00 [haddock @ 2004-08-26 21:03:19 by panne] Updated BuildRequires tags. Alas, there seems to be no real standard here, so your mileage may vary... At least the current specs should work on SuSE Linux. - - - - - e6982912 by Sigbjorn Finne at 2004-08-30T15:44:59+00:00 [haddock @ 2004-08-30 15:44:59 by sof] escape HADDOCK_VERSION double quotes on all platforms when compiling with <=6.0.x - - - - - b3fbc867 by Simon Marlow at 2004-08-31T13:09:42+00:00 [haddock @ 2004-08-31 13:09:42 by simonmar] Avoid GHC/shell versionitis and create Version.hs - - - - - c359e16a by Sven Panne at 2004-09-05T19:12:33+00:00 [haddock @ 2004-09-05 19:12:32 by panne] * HTML documentation for "foo.xml" goes into directory "foo" again, not "foo-html". This is nicer and consistent with the behaviour for building the docs from SGML. * Disabled building PostScript documentation in the spec files for now, there are some strange issues with the FO->PS conversion for some files which have to be clarified first. - - - - - c68b1eba by Sven Panne at 2004-09-24T07:04:38+00:00 [haddock @ 2004-09-24 07:04:38 by panne] Switched the default state for instances and the module hierarchy to non-collapsed. This can be reversed when we finally use cookies from JavaScript to have a more persistent state. Previously going back and forth in the documentation was simply too annoying because everything was collapsed again and therefore the documentation was not easily navigatable. - - - - - dfb32615 by Simon Marlow at 2004-09-30T08:21:29+00:00 [haddock @ 2004-09-30 08:21:29 by simonmar] Add a feature request - - - - - 45ff783c by Sven Panne at 2004-10-23T19:54:00+00:00 [haddock @ 2004-10-23 19:54:00 by panne] Improved the Cygwin/MinGW chaos a little bit. There is still confusion about host platform vs. target platform... - - - - - 5f644714 by Krasimir Angelov at 2004-10-28T16:01:51+00:00 [haddock @ 2004-10-28 16:01:51 by krasimir] update for ghc-6.3+ - - - - - 92d9753e by Sven Panne at 2004-11-01T16:39:01+00:00 [haddock @ 2004-11-01 16:39:01 by panne] Revert previous commit: It's Network.URI which should be changed, not Haddock. - - - - - 05f70f6e by Simon Marlow at 2005-01-04T16:15:51+00:00 [haddock @ 2005-01-04 16:15:51 by simonmar] parser fix: allow qualified specialids. - - - - - 47870837 by Simon Marlow at 2005-01-04T16:16:54+00:00 [haddock @ 2005-01-04 16:16:54 by simonmar] Add a test - - - - - ff11fc2c by Ross Paterson at 2005-01-10T19:18:22+00:00 [haddock @ 2005-01-10 19:18:22 by ross] Render non-ASCII characters using numeric character references, to simplify charset issues. There's a META tag saying the charset is UTF-8, but GHC outputs characters as raw bytes. Ideally we need an encoding on the input side too, primarily in comments, because source files containing non-ASCII characters aren't portable between locales. - - - - - eba2fc4e by Simon Marlow at 2005-01-11T10:44:37+00:00 [haddock @ 2005-01-11 10:44:37 by simonmar] Remove string gap - - - - - b899a381 by Ross Paterson at 2005-01-13T11:41:33+00:00 [haddock @ 2005-01-13 11:41:33 by ross] recognize SGML-style numeric character references &#ddd; or &#xhhhh; and translate them into Chars. - - - - - 106e3cf0 by Ross Paterson at 2005-01-13T14:43:41+00:00 [haddock @ 2005-01-13 14:43:41 by ross] also allow uppercase X in hexadecimal character references (like SGML) - - - - - e8f54f25 by Ross Paterson at 2005-01-13T14:44:24+00:00 [haddock @ 2005-01-13 14:44:24 by ross] Describe numeric character references. - - - - - 914ccdce by Sven Panne at 2005-01-15T18:44:48+00:00 [haddock @ 2005-01-15 18:44:45 by panne] Make Haddock compile again after the recent base package changed. The Map/Set legacy hell has been factored out, so that all modules can simply use the new non-deprecated interfaces. Probably a lot of things can be improved by a little bit of Map/Set/List algebra, this can be done later if needed. Small note: Currently the list of instances in HTML code is reversed. This will hopefully be fixed later. - - - - - 6ab20e84 by Sven Panne at 2005-01-16T12:18:26+00:00 [haddock @ 2005-01-16 12:18:26 by panne] Trim imports - - - - - efb81da9 by Sven Panne at 2005-01-16T12:58:08+00:00 [haddock @ 2005-01-16 12:58:03 by panne] Correctly handle the new order of arguments for the combining function given to fromListWith. - - - - - e27b5834 by Sven Panne at 2005-01-16T14:14:41+00:00 [haddock @ 2005-01-16 14:14:39 by panne] Data.Map.unions is left-biased. - - - - - dae3cc3e by Sven Panne at 2005-01-16T14:22:44+00:00 [haddock @ 2005-01-16 14:22:44 by panne] Added the last missing "flip" to get identical HTML output as previous versions. - - - - - 951d8408 by Sven Panne at 2005-01-16T14:37:10+00:00 [haddock @ 2005-01-16 14:37:10 by panne] Refactored Text.PrettyPrint legacy hell into a separate module. - - - - - f1c4b892 by Sven Panne at 2005-01-16T15:41:25+00:00 [haddock @ 2005-01-16 15:41:21 by panne] Cleaned up imports and dropped support for GHC < 5.03, it never worked, anyway. - - - - - 60824c6e by Simon Marlow at 2005-01-18T10:02:48+00:00 [haddock @ 2005-01-18 10:02:48 by simonmar] Add a TODO - - - - - a8c82f23 by Krasimir Angelov at 2005-01-28T23:19:39+00:00 [haddock @ 2005-01-28 23:19:39 by krasimir] import Foreign/Foreign.C are required for Windows - - - - - d8450a23 by Simon Marlow at 2005-02-02T16:23:04+00:00 [haddock @ 2005-02-02 16:23:00 by simonmar] Revamp the linking strategy in Haddock. Now name resolution is done in two phases: - first resolve everything to original names, like a Haskell compiler would. - then, figure out the "home" location for every entity, and point all the links to there. The home location is the lowest non-hidden module in the import hierarchy that documents the entity. If there are multiple candidates, one is chosen at random. Also: - Haddock should not generate any HTML with dangling links any more. Unlinked references are just rendered as plain text. - Error reporting is better: if we can't find a link destination for an entity reference, we now emit a warning. - - - - - 1cce71d0 by Simon Marlow at 2005-02-03T13:42:19+00:00 [haddock @ 2005-02-03 13:42:19 by simonmar] - add --ignore-all-exports flag, which behaves as if every module has the ignore-exports attribute (requested by Chris Ryder). - add --hide option to hide a module on the command line. - add --use-package option to get Haddock info for a package from ghc-pkg (largely untested). - remove reexports from the .haddock file, they aren't used any more. - - - - - 767123ef by Ross Paterson at 2005-02-03T16:17:37+00:00 [haddock @ 2005-02-03 16:17:37 by ross] fix typo for < 6.3 - - - - - 0c680c04 by Simon Marlow at 2005-02-04T12:03:31+00:00 [haddock @ 2005-02-04 12:03:31 by simonmar] Fix bug in renameExportItems that meant links in instances weren't being renamed properly. - - - - - ff7abe5f by Simon Marlow at 2005-02-04T12:15:53+00:00 [haddock @ 2005-02-04 12:15:52 by simonmar] Add attribute #not-home, to indicate that the current module should not be considered to be a home module for the each entity it exports, unless there is no other module that exports the entity. - - - - - fc2cfd27 by Simon Marlow at 2005-02-04T12:40:02+00:00 [haddock @ 2005-02-04 12:40:02 by simonmar] Update the documentation w.r.t. home modules and the not-home attribute. - - - - - 26b8ddf7 by Ross Paterson at 2005-02-04T13:36:06+00:00 [haddock @ 2005-02-04 13:36:05 by ross] sort lists of instances by - arity of the type constructors (so higher-kinded instances come first) - name of the class - argument types - - - - - 26bfb19c by Simon Marlow at 2005-02-23T15:57:12+00:00 [haddock @ 2005-02-23 15:57:12 by simonmar] Fix documentation regarding the module attributes. - - - - - 9c3afd02 by Simon Marlow at 2005-02-28T16:18:17+00:00 [haddock @ 2005-02-28 16:18:17 by simonmar] version 0.7 - - - - - a95fd63f by Simon Marlow at 2005-02-28T16:22:08+00:00 [haddock @ 2005-02-28 16:22:08 by simonmar] Attempt to fix the layout of the package names in the contents. Having tried just about everything, the only thing I can get to work reliably is to make the package names line up on a fixed offset from the left margin. This obviously isn't ideal, so anyone else that would like to have a go at improving it is welcome. One option is to remove the +/- buttons from the contents list and go back to a plain table. The contents page now uses CSS for layout rather than tables. It seems that most browsers have different interpretations of CSS layout, so only the simplest things lead to consistent results. - - - - - 905d42f7 by Simon Marlow at 2005-03-01T17:16:42+00:00 [haddock @ 2005-03-01 17:16:40 by simonmar] Another attempt at lining up the package names on the contents page. Now, they line up with Konqueror, and almost line up with Firefox & IE (different layout in each case). - - - - - a0e1d178 by Wolfgang Thaller at 2005-03-09T08:28:39+00:00 [haddock @ 2005-03-09 08:28:39 by wolfgang] Hack haddock's lexer to accept the output from Apple's broken version of cpp (Apple's cpp leaves #pragma set_debug_pwd directives in it's output). - - - - - 9e1eb784 by Simon Marlow at 2005-04-22T14:27:15+00:00 [haddock @ 2005-04-22 14:27:15 by simonmar] Add a TODO item - - - - - 23281f78 by Ross Paterson at 2005-05-18T12:41:59+00:00 [haddock @ 2005-05-18 12:41:59 by ross] fix 3 bugs in --use-package, and document it. - - - - - 00074a68 by Sven Panne at 2005-05-21T12:35:29+00:00 [haddock @ 2005-05-21 12:35:29 by panne] Warning/versionitis police - - - - - 341fa822 by Simon Marlow at 2005-06-15T15:43:21+00:00 [haddock @ 2005-06-15 15:43:21 by simonmar] Allow "licence" as an alternate spelling of "license" - - - - - 3b953f8b by Simon Marlow at 2005-06-16T08:14:12+00:00 [haddock @ 2005-06-16 08:14:12 by simonmar] wibble - - - - - abfd9826 by Simon Marlow at 2005-06-27T14:46:40+00:00 [haddock @ 2005-06-27 14:46:40 by simonmar] name hierarchical HTML files as A-B-C.html instead of A.B.C.html. The old way confused Apache because the extensions are sometimes interpreted as having special meanings. - - - - - a01eea00 by Simon Marlow at 2005-08-04T13:59:40+00:00 [haddock @ 2005-08-04 13:59:40 by simonmar] 0.7 changes - - - - - 170ef87e by Simon Marlow at 2005-08-04T15:08:03+00:00 [haddock @ 2005-08-04 15:08:03 by simonmar] spec file from Jens Peterson - - - - - 7621fde4 by Simon Marlow at 2005-08-04T15:59:30+00:00 [haddock @ 2005-08-04 15:59:30 by simonmar] replace mingw tests with $(Windows) - - - - - a20739bb by Sven Panne at 2005-08-05T07:01:12+00:00 [haddock @ 2005-08-05 07:01:12 by panne] Reverted to previous version (but with bumped version number), the last commit broke RPM building on SuSE systems due to differently named dependencies. As a clarification: All .spec files in the repository have to work at least on SuSE, because that's the system I'm using. And as "Mr. Building Police", I reserve me the right to keep them that way... >:-) It might very well be the case that we need different .spec files for different platforms, so packagers which are unhappy with the current .spec files should contact me, stating the actual problems. - - - - - 4afb15cf by Simon Marlow at 2005-10-05T10:51:45+00:00 [haddock @ 2005-10-05 10:51:45 by simonmar] Add a bug - - - - - 60f69f82 by Simon Marlow at 2005-10-05T12:52:03+00:00 [haddock @ 2005-10-05 12:52:03 by simonmar] Document new behaviour of -s option - - - - - f7e520ca by Simon Marlow at 2005-10-10T15:02:55+00:00 [haddock @ 2005-10-10 15:02:55 by simonmar] extractRecSel: ignore non-record constructors (fixes a crash when using datatypes with a mixture of record and non-record style constructors). - - - - - b2edbedb by Simon Marlow at 2005-10-14T09:44:21+00:00 Start CHANGES for 0.8 - - - - - 21c7ac8d by Simon Marlow at 2005-10-14T23:11:19+00:00 First cut of Cabal build system - - - - - 766cecdd by Simon Marlow at 2005-10-29T08:14:43+00:00 Add configure script and Makefile for the docs Add a separate configure script and build system for building the documentation. The configure and Makefile code is stolen from fptools. This is left as a separate build system so that the main Cabal setup doesn't require a Unix build environment or DocBook XML tools. - - - - - aa36c783 by Duncan Coutts at 2006-01-17T19:29:55+00:00 Add a --wiki=URL flag to add a per-module link to a correspondng wiki page. So each html page gets an extra link (placed next to the source code and contents links) to a corresponding wiki page. The idea is to let readers contribute their own notes, examples etc to the documentation. Also slightly tidy up the code for the --source option. - - - - - e06e2da2 by Simon Marlow at 2006-01-18T09:28:15+00:00 TODO: documnet --wiki - - - - - 17adfda9 by Duncan Coutts at 2006-01-19T20:17:59+00:00 Add an optional wiki link for each top level exported name. In each module, for each "top level" exported entity we add a hyper link to a corresponding wiki page. The link url gets the name of the exported entity as a '#'-style anchor, so if there is an anchor in the page with that name then the users browser should jump directly to it. By "top level" we mean functions, classes, class members and data types (data, type, newtype), but not data constructors, class instances or data type class membership. The link is added at the right of the page and in a small font. Hopefully this is the right balance of visibility/distraction. We also include a link to the wiki base url in the contents and index pages. - - - - - f52324bb by Duncan Coutts at 2006-01-19T20:28:27+00:00 Rewrite pathJoin to only add a path separator when necessary. When the path ends in a file seperator there is no need to add another. Now using "--wiki=http://blah.com/foo/" should do the right thing. (Code snippet adapted from Isaac's FilePath package.) - - - - - 43bb89fa by Duncan Coutts at 2006-01-21T17:15:27+00:00 Teach haddock about line pragmas and add accurate source code links Teach haddock about C and Haskell style line pragmas. Extend the lexer/parser's source location tracking to include the file name as well as line/column. This way each AST item that is tagged with a SrcLoc gets the original file name too. Use this original file name to add source links to each exported item, in the same visual style as the wiki links. Note that the per-export source links are to the defining module rather than whichever module haddock pretends it is exported from. This is what we want for source code links. The source code link URL can also contain the name of the export so one could implement jumping to the actual location of the function in the file if it were linked to an html version of the source rather than just plain text. The name can be selected with the %N wild card. So for linking to the raw source code one might use: --source=http://darcs/haskell.org/foo/%F Or for linking to html syntax highlighted code: --source=http://darcs/haskell.org/foo/%M.html#%N - - - - - edd9f229 by Duncan Coutts at 2006-01-22T00:02:00+00:00 Extend URL variable expansion syntax and add source links to the contents page Like the wiki link on the contents and index page, add a source code link too. Extend the wiki & source URL variable expansion syntax. The original syntax was: %F for the source file name (the .hs version only, not the .lhs or .hs.pp one) %M for the module name (with '.' replaced by '/') The new syntax is: %F or %{FILE} for the original source file name %M or %{MODULE} for the module name (no replacements) %N or %{NAME} for the function/type export name %K or %{KIND} for a type/value flag "t" or "v" with these extensions: %{MODULE/./c} to replace the '.' module seperator with any other char c %{VAR|some text with the % char in it} which means if the VAR is not in use in this URL context then "" else replace the given text with the '%' char replaced by the string value of the VAR. This extension allows us to construct URLs wit optional parts, since the module/file name is not available for the URL in the contents/index pages and the value/type name is not available for the URL at the top level of each module. - - - - - eb3c6ada by Duncan Coutts at 2006-01-23T13:42:34+00:00 Remove the complex substitutions and add more command line flags instead. Instead of incomprehensable URL substitutions like ${MODULE/./-|?m=%} we now use three seperate command line flags for the top level, per-module and per-entity source and wiki links. They are: --source-base, --source-module, --source-entity --comments-base, --comments-module, --comments-entity We leave -s, --source as an alias for --source-module which is how that option behaved previously. The long forms of the substitutions are still available, ${FILE} ${MODULE} etc and the only non-trivial substitution is ${MODULE/./c} to replace the '.' characters in the module name with any other character c. eg ${MODULE/./-} Seperating the source and wiki url flags has the added bonus that they can be turned on or off individually. So users can have per-module links for example without having to also have per-entity links.` - - - - - a2f0f2af by Duncan Coutts at 2006-01-23T13:54:52+00:00 Make the --help output fit in 80 columns. This is a purely cosmetic patch, feel free to ignore it. The only trickery going on is that we don't display the deprecated -s, --source flags in the help message, but we do still accept them. - - - - - 2d3a4b0c by Duncan Coutts at 2006-01-23T14:12:16+00:00 Add documentation for the new --source-* and --comments-* command line options - - - - - 1a82a297 by Simon Marlow at 2006-01-23T17:03:27+00:00 fix markup - - - - - 100d464a by Duncan Coutts at 2006-01-23T18:31:13+00:00 remove a couple TODO items that have been done The --wiki, or rather the --comment-* options are now documented. There is probably no need to have haddock invoke unlit or cpp itself since it can now pick up the line pragmas to get the source locations right. Tools like Cabal will arrange for preprocessors to be run so there is less of a need for tools like haddock to do it themselves. - - - - - 3162fa91 by Simon Marlow at 2006-01-24T14:21:56+00:00 add a test I had lying around - - - - - 98947063 by Simon Marlow at 2006-01-31T13:52:54+00:00 add scabal-version field - - - - - c41876e6 by Neil Mitchell at 2006-02-26T17:48:21+00:00 Add Hoogle output option - - - - - f86fb9c0 by Simon Marlow at 2006-03-08T09:15:20+00:00 add haskell.vim Contributed by Brad Bowman <bsb at bereft.net>, thanks! - - - - - 35d3c511 by benjamin.franksen at 2006-03-03T22:39:54+00:00 fixed libdir (/html was missing) - - - - - 4d08fd7d by Simon Marlow at 2006-03-10T11:13:31+00:00 add PatternGuards extension - - - - - 3f095e70 by Simon Marlow at 2006-03-13T11:40:42+00:00 bug fixes from Brad Bowman - - - - - 8610849d by Sven Panne at 2006-03-19T17:02:56+00:00 Fixed Cabal/RPM build - - - - - 34a994d6 by sven.panne at 2006-04-20T12:39:23+00:00 Avoid pattern guards Due to the use of pattern guards in Haddock, GHC was called with -fglasgow-exts. This in turn enables bang patterns, too, which broke the Haddock build. Removing some unnecessary pattern guards seemed to be the better way of fixing this instead of using a pragma to disable pattern guards. - - - - - bb523f51 by Ross Paterson at 2006-04-24T09:03:25+00:00 extend 'deriving' heuristic a little If an argument of a data constructor has a type variable head, it is irreducible and the same type class can be copied into the constraint. (Formerly we just did this for type variable arguments.) - - - - - dab9fe7a by Simon Marlow at 2006-04-26T10:02:31+00:00 record an idea - - - - - 748b7078 by Simon Marlow at 2006-05-08T08:28:53+00:00 add section about deriving - - - - - 11252ea1 by Simon Marlow at 2006-05-24T15:43:10+00:00 replace a fatal error in lexChar with a parseError - - - - - 382c9411 by Simon Marlow at 2006-05-24T15:45:47+00:00 add a bug - - - - - b79272f5 by Simon Marlow at 2006-05-24T15:46:29+00:00 add a bug report - - - - - 912edf65 by David Waern at 2006-07-10T19:09:23+00:00 Initial modifications -- doesn't compile - - - - - a3c7ba99 by David Waern at 2006-07-11T00:54:19+00:00 More porting work -- doesn't compile - - - - - 0a173d19 by David Waern at 2006-07-11T11:30:03+00:00 Make the repos temporarily compile and illustrate a problem - - - - - bad316de by David Waern at 2006-07-11T15:43:47+00:00 Progress on the porting process - - - - - bbf12d02 by David Waern at 2006-07-11T23:07:44+00:00 More progress on the porting -- first pass starting to shape up - - - - - de580ba2 by David Waern at 2006-07-20T17:48:30+00:00 More progress -- still on phase1 - - - - - 75a917a2 by David Waern at 2006-07-23T18:22:43+00:00 More work on pass1 -- mostly done - - - - - 6697b3f7 by David Waern at 2006-07-23T22:17:40+00:00 More work, started working on the renaming phase -- this code will need a cleanup soon :) - - - - - 82a5bcbb by David Waern at 2006-07-29T16:16:43+00:00 Add instances, build renaming environment, start on the renamer - - - - - c3f8f4f1 by David Waern at 2006-07-29T21:37:48+00:00 Complete the renamer - - - - - 7e00d464 by David Waern at 2006-07-30T21:01:57+00:00 Start porting the Html renderer - - - - - f04ce121 by David Waern at 2006-08-09T20:04:56+00:00 More Html rendering progress - - - - - 20c21b53 by David Waern at 2006-08-10T17:37:47+00:00 More progress - - - - - d7097e0d by David Waern at 2006-08-11T20:31:51+00:00 Cleanup - - - - - a7351e86 by David Waern at 2006-08-12T11:44:47+00:00 Render H98 Data declarations - - - - - 3fb2208e by David Waern at 2006-08-12T17:15:34+00:00 Perfect rendering of Test.hs - - - - - 454fd062 by David Waern at 2006-08-13T21:57:08+00:00 Misc fixes and interface load/save - - - - - 7ef7e7be by David Waern at 2006-08-14T00:56:07+00:00 Some refactoring - - - - - a7d3efef by David Waern at 2006-08-19T20:07:55+00:00 Adapt to latest GHC - - - - - 5fc3c0d7 by David Waern at 2006-08-20T21:28:11+00:00 Move interface read/write to its own module + some cleanup - - - - - 037e011c by David Waern at 2006-08-20T21:38:24+00:00 Small cleanup - - - - - da3a1023 by David Waern at 2006-09-03T16:05:22+00:00 Change mode to BatchCompile to avoid GHC API bug - - - - - 3cc9be3b by David Waern at 2006-09-03T16:06:59+00:00 Starting work on GADT rendering - - - - - 94506037 by David Waern at 2006-09-03T20:02:48+00:00 Compensate for change of export list order in GHC - - - - - c2cec4eb by David Waern at 2006-09-04T20:53:01+00:00 Rename a function - - - - - 9a9735ba by David Waern at 2006-09-05T15:51:21+00:00 Change version number to 2.0 - - - - - 3758a714 by David Waern at 2006-09-05T15:51:49+00:00 Align comment properly - - - - - 68478d9e by David Waern at 2006-09-15T18:03:00+00:00 Remove interface reading/writing code and use the GHC api for creating package environments instead - - - - - d2eedd95 by David Waern at 2006-09-15T18:05:29+00:00 Change the executable name to haddock-ghc-nolib - - - - - fcfbcf66 by David Waern at 2006-09-15T18:05:45+00:00 Small source code cleanup - - - - - d08eb017 by David Waern at 2006-09-15T18:06:21+00:00 Remove handling of --package flag - - - - - b8a4cf53 by David Waern at 2006-09-15T18:07:16+00:00 Remove commented-out code - - - - - bef0a684 by David Waern at 2006-09-15T18:37:57+00:00 Don't warn about missing links to () - - - - - e7d25fd7 by David Waern at 2006-09-15T19:50:49+00:00 Remove Interface and Binary2 modules - - - - - 9894f2a1 by David Waern at 2006-09-15T19:53:43+00:00 Remove debug printing from HaddockHtml - - - - - a0e7455d by David Waern at 2006-09-16T00:16:29+00:00 Comments only - - - - - d5b26fa7 by David Waern at 2006-09-16T00:16:57+00:00 Refactor PackageData creation code and start on building the doc env propery (unfinished) - - - - - 06aaa779 by David Waern at 2006-09-16T00:19:25+00:00 Better comments in Main.hs - - - - - 1a52d1b4 by David Waern at 2006-09-18T22:17:11+00:00 Comments and spacing change - - - - - e5a97767 by David Waern at 2006-09-21T17:02:45+00:00 Remove unnecessary fmapM import in Main - - - - - 9d0f9d3a by David Waern at 2006-09-22T18:07:07+00:00 Make import list in HaddockHtml prettier - - - - - 3452f662 by David Waern at 2006-09-22T18:08:47+00:00 Refactor context rendering - - - - - 12d0a6d0 by David Waern at 2006-09-22T18:09:52+00:00 Do proper HsType rendering (inser parentheses correctly) - - - - - 2c20c2f9 by David Waern at 2006-09-22T18:10:45+00:00 Fix a bug in Main.toHsType - - - - - c5396443 by David Waern at 2006-09-22T18:11:16+00:00 Skip external package modules sort for now - - - - - 3fb95547 by David Waern at 2006-09-22T20:35:40+00:00 Take away trailin "2" on all previously clashing type names - - - - - 2174755f by David Waern at 2006-09-22T20:51:43+00:00 Remove unused imports in Main - - - - - 1e9f7a39 by David Waern at 2006-09-22T20:52:11+00:00 Fix a comment in Main - - - - - 32d9e028 by David Waern at 2006-10-05T16:40:11+00:00 Merge with changes to ghc HEAD - - - - - 3058c8f5 by David Waern at 2006-10-05T16:41:02+00:00 Comment fixes - - - - - b9c217ec by David Waern at 2006-10-05T16:49:59+00:00 Filter out more builtin type constructors from warning messages - - - - - 67e7d252 by David Waern at 2006-10-05T19:38:22+00:00 Refactoring -- better structured pass1 - - - - - cd21c0c1 by David Waern at 2006-10-05T19:44:42+00:00 Remove read/dump interface flags - - - - - 313f9e69 by David Waern at 2006-10-05T19:49:26+00:00 Remove unused pretty printing - - - - - 480f09d1 by David Waern at 2006-12-28T13:22:24+00:00 Update to build with latest GHC HEAD - - - - - 63dccfcb by David Waern at 2007-01-05T01:38:45+00:00 Fixed a bug so that --ghc-flag works correctly - - - - - 3117dadc by David Waern at 2006-12-29T18:53:39+00:00 Automatically get the GHC lib dir - - - - - 9dc84a5c by David Waern at 2006-12-29T19:58:53+00:00 Comments - - - - - 0b0237cc by David Waern at 2007-01-05T16:48:30+00:00 Collect docs based on SrcLoc, syncing with removal of DeclEntity from GHC - - - - - a962c256 by David Waern at 2007-01-05T17:02:47+00:00 Add tabs in haddock.cabal - - - - - 0ca30c97 by David Waern at 2007-01-05T17:04:11+00:00 Add GHCUtils.hs - - - - - c0ab9abe by David Waern at 2007-01-10T11:43:08+00:00 Change package name to haddock-ghc, version 0.1 - - - - - 38e18b27 by David Waern at 2007-01-12T12:03:52+00:00 No binder name for foreign exports - - - - - d18587ab by David Waern at 2007-01-12T12:08:15+00:00 Temp record - - - - - ba6251a0 by David Waern at 2007-01-12T18:27:55+00:00 Remove read/dump-interface (again) - - - - - f4ba2b39 by David Waern at 2007-01-12T18:31:36+00:00 Remove DocOption, use the GHC type - - - - - 511be8bd by David Waern at 2007-01-12T18:32:41+00:00 Use exceptions instead of Either when loading package info - - - - - 0f2144d8 by David Waern at 2007-01-12T18:33:23+00:00 Small type change - - - - - 77507eb7 by David Waern at 2007-01-12T18:33:59+00:00 Remove interface file read/write - - - - - 0ea1e14f by David Waern at 2007-01-17T21:40:26+00:00 Add trace_ppr to GHCUtils - - - - - 3878b493 by David Waern at 2007-01-17T21:40:53+00:00 Sort external package modules and build a doc env - - - - - 8dc323fc by David Waern at 2007-01-17T21:42:41+00:00 Remove comment - - - - - f4c5b097 by David Waern at 2007-01-18T23:22:18+00:00 Add haddock-ghc.cabal and remove ghc option pragma in source file - - - - - da242b2c by David Waern at 2007-01-18T23:22:46+00:00 Remove some tabs - - - - - 288ed096 by David Waern at 2007-01-18T23:39:28+00:00 Moved the defaultErrorHandler to scope only over sortAndCheckModules for now - - - - - 4dd150fe by David Waern at 2007-02-03T21:23:56+00:00 Let restrictCons handle infix constructors - - - - - 97893442 by David Waern at 2007-02-04T16:26:00+00:00 Render infix data constructors - - - - - da89db72 by David Waern at 2007-02-04T16:26:33+00:00 CHange project name to Haddock-GHC - - - - - e93d48af by David Waern at 2007-02-04T16:59:08+00:00 Render infix type constructors properly - - - - - 357bc99b by David Waern at 2007-02-04T17:37:08+00:00 Insert spaces around infix function names - - - - - ab6cfc49 by David Waern at 2007-02-04T17:59:54+00:00 Do not list entities without documentation - - - - - 04249c7e by David Waern at 2007-02-04T19:16:25+00:00 Add GADT support (quite untested) - - - - - 2c223f8d by David Waern at 2007-02-04T19:25:10+00:00 Add package file write/save again! - - - - - b07ed218 by David Waern at 2007-02-04T19:33:02+00:00 Comment out minf_iface based stuff - - - - - 953d1fa7 by David Waern at 2007-02-05T00:12:23+00:00 Solve conflicts - - - - - 593247fc by David Waern at 2007-02-06T19:48:48+00:00 Remove -package flag, GHC's can be used instead - - - - - f658ded2 by David Waern at 2007-02-06T20:50:44+00:00 Start for support of ATs - - - - - 97f9e913 by David Waern at 2007-02-06T20:52:27+00:00 Wibble - - - - - 2ce8e4cf by David Waern at 2007-02-16T12:09:49+00:00 Add the DocOptions change - - - - - dee4a9b5 by David Waern at 2007-03-06T01:24:48+00:00 Wibble - - - - - 7cb99d18 by David Waern at 2007-03-06T01:24:58+00:00 Change version to 2.0 and executable name to haddock - - - - - c5aa02bc by David Waern at 2007-03-08T15:59:49+00:00 Go back to -B flag - - - - - 3a349201 by David Waern at 2007-03-09T13:31:59+00:00 Better exception handling and parsing of GHC flags - - - - - 05a69b71 by David Waern at 2007-03-09T17:45:44+00:00 Remove commented-out DocEntity printing - - - - - 755032cb by davve at dtek.chalmers.se at 2007-03-23T23:30:20+00:00 Remove a file that shouldn't be here - - - - - a7077e5f by davve at dtek.chalmers.se at 2007-03-24T03:58:48+00:00 Remove an import - - - - - 6f55aa8b by davve at dtek.chalmers.se at 2007-03-25T00:46:48+00:00 Start work on Haddock API - - - - - f0199480 by davve at dtek.chalmers.se at 2007-03-25T00:56:36+00:00 Prettify some comments - - - - - f952f9d1 by davve at dtek.chalmers.se at 2007-03-25T00:56:53+00:00 Remove ppr in HaddockTypes - - - - - bc594904 by davve at dtek.chalmers.se at 2007-03-25T00:57:53+00:00 Remove commented out doc env inference - - - - - 11ebf08d by davve at dtek.chalmers.se at 2007-03-25T01:23:25+00:00 De-flatten the namespace - - - - - f696b4bc by davve at dtek.chalmers.se at 2007-03-25T03:21:48+00:00 Add missing stuff to API - - - - - 9a2a04c3 by davve at dtek.chalmers.se at 2007-03-25T03:22:02+00:00 Wibble - - - - - 7d04a6d5 by davve at dtek.chalmers.se at 2007-03-25T03:22:08+00:00 Avoid a GHC bug with parseStaticFlags [] - - - - - 4d2820ba by davve at dtek.chalmers.se at 2007-03-26T04:57:01+00:00 Add fall-through case to mkExportItem - - - - - 6ebc8950 by Stefan O'Rear at 2007-03-26T04:14:53+00:00 Add shebang line to Setup.lhs - - - - - 80966ec5 by davve at dtek.chalmers.se at 2007-03-26T05:24:26+00:00 Fix stupid compile error - - - - - 1ea1385d by davve at dtek.chalmers.se at 2007-04-05T17:19:56+00:00 Do save/read of interface files properly - - - - - 0e4f6541 by David Waern at 2007-04-10T21:08:36+00:00 Add version to ghc dependency - - - - - b0499b63 by David Waern at 2007-04-10T21:37:08+00:00 Change package name to haddock - - - - - 9d50d27e by David Waern at 2007-04-24T00:22:14+00:00 Use filepath package instead of FilePath - - - - - 87c7fcdf by David Waern at 2007-07-10T21:03:04+00:00 Add new package dependencies - - - - - 4768709c by David Waern at 2007-07-11T20:37:11+00:00 Follow changes to record constructor representation - - - - - b9a02fee by Simon Marlow at 2007-05-30T14:00:48+00:00 update to compile with the latest GHC & Cabal - - - - - c0ebdc01 by David Waern at 2007-07-11T21:35:45+00:00 Fix conflicts - - - - - 97f7afd4 by David Waern at 2007-07-11T21:52:38+00:00 Follow changes to the GHC API - - - - - a5b7b58f by David Waern at 2007-07-12T20:36:48+00:00 Call parseStaticFlags before newSession - - - - - f7f50dbc by David Waern at 2007-08-01T21:52:58+00:00 Better indentation in haddock.cabal - - - - - d84e52ad by David Waern at 2007-08-02T00:08:18+00:00 Wibble - - - - - a23f494a by David Waern at 2007-08-02T00:08:24+00:00 Be better at trying to load all module dependencies (debugging) - - - - - ee917f13 by David Waern at 2007-08-03T18:48:08+00:00 Load all targets explicitly (checkModule doesn't chase dependencies anymore) - - - - - 5182d631 by David Waern at 2007-08-16T16:48:55+00:00 Finalize support for links to other packages - - - - - dfd1e3da by David Waern at 2007-08-16T16:51:11+00:00 Fix haddock comment errors in Haddock.Types - - - - - 50c0d83e by David Waern at 2007-08-16T16:51:37+00:00 Remove a debug import - - - - - d84b7c2b by David Waern at 2007-08-16T17:06:30+00:00 Rename PackageData to HaddockPackage - - - - - 3b52cb9f by David Waern at 2007-08-16T17:09:42+00:00 Simplify some comments - - - - - 66fa68d9 by David Waern at 2007-08-16T17:11:38+00:00 Comment the HaddockPackage definition - - - - - 8674c761 by David Waern at 2007-08-16T17:25:54+00:00 Improve code layout in Main - - - - - 571a3a0b by David Waern at 2007-08-16T17:32:13+00:00 Remove explict module imports in Main - - - - - d31b3cb0 by David Waern at 2007-08-16T17:36:23+00:00 Correct comments - - - - - 7f8a9f2b by David Waern at 2007-08-16T17:39:50+00:00 Fix layout problems in Haddock.Types - - - - - 9f421d7f by David Waern at 2007-08-17T11:16:48+00:00 Move options out of Main into Haddock.Options - - - - - 80042b63 by David Waern at 2007-08-17T11:26:59+00:00 Small comment/layout fixes - - - - - b141b982 by David Waern at 2007-08-17T11:28:28+00:00 Change project name from Haddock-GHC to Haddock - - - - - dbeb4a81 by David Waern at 2007-08-17T11:41:05+00:00 Add top module comment to all files - - - - - ce99cc9e by David Waern at 2007-08-17T14:53:04+00:00 Factor out typechecking phase into Haddock.Typecheck - - - - - 6bf75d9e by David Waern at 2007-08-17T16:55:35+00:00 Factor out package code to Haddock.Packages - - - - - b396db37 by David Waern at 2007-08-29T22:40:23+00:00 Major refactoring - - - - - 3d4f95ee by David Waern at 2007-08-29T23:26:24+00:00 Rename HaddockModule to Interface and a few more refactorings - - - - - c55326db by David Waern at 2007-08-29T23:48:03+00:00 Some comment cleanup - - - - - 9a84fc46 by David Waern at 2007-08-29T23:49:29+00:00 Add some modules that I forgot to add earlier - - - - - 4536dce2 by David Waern at 2007-08-29T23:55:24+00:00 Wibble - - - - - 9b7f0206 by David Waern at 2007-08-30T16:03:29+00:00 Wibble - - - - - c52c050a by David Waern at 2007-08-30T16:30:37+00:00 Rename HaddockModule to Interface - - - - - eae2995f by David Waern at 2007-08-30T16:42:59+00:00 Simplify createInterfaces - - - - - 53f99caa by David Waern at 2007-09-29T00:04:31+00:00 Add build-type: Simple to the cabal file - - - - - 0d3103a8 by David Waern at 2007-09-29T00:04:58+00:00 Add containers and array dependency - - - - - 6acf5f30 by David Waern at 2007-09-29T00:13:36+00:00 Prettify the cabal file - - - - - 87c1e378 by David Waern at 2007-09-29T13:16:39+00:00 FIX: consym data headers with more than two variables - - - - - b67fc16a by David Waern at 2007-09-29T14:01:32+00:00 FIX: prefix types used as operators should be quoted - - - - - a8f925bc by David Waern at 2007-09-29T14:02:26+00:00 Use isSymOcc from OccName instead of isConSym - - - - - fc330701 by David Waern at 2007-09-29T14:15:37+00:00 Use isLexConSym/isLexVarSym from OccName - - - - - e4f3dbad by David Waern at 2007-09-29T15:01:08+00:00 FIX: do not quote varsym type operators - - - - - 402207d2 by David Waern at 2007-09-29T15:01:50+00:00 Wibble - - - - - f9d89ef0 by David Waern at 2007-09-29T15:17:40+00:00 Take care when pp tyvars - add parens on syms - - - - - 849e2a77 by David Waern at 2007-10-01T21:56:39+00:00 Go back to using a ModuleMap instead of LookupMod - fixes a bug - - - - - 549dbac6 by David Waern at 2007-10-02T01:05:19+00:00 Improve parsing of doc options - - - - - a36021b8 by David Waern at 2007-10-02T23:05:00+00:00 FIX: double arrows in constructor contexts - - - - - d03bf347 by David Waern at 2007-10-09T16:14:05+00:00 Add a simple test suite - - - - - c252c140 by David Waern at 2007-10-17T16:02:28+00:00 Add --optghc=.. style flag passing to GHC - - - - - cce6c1b3 by David Waern at 2007-10-18T22:03:20+00:00 Add support for --read-interface again - - - - - 33d059c0 by David Waern at 2007-10-18T22:30:18+00:00 Refactoring -- get rid of Haddock.Packages - - - - - f9ed0a4c by David Waern at 2007-10-18T22:34:36+00:00 Name changes - - - - - 8a1c816f by David Waern at 2007-10-20T14:24:23+00:00 Add --ghc-version option - - - - - 4925aaa1 by David Waern at 2007-10-21T14:34:26+00:00 Add some Outputable utils - - - - - 69e7e47f by David Waern at 2007-10-21T14:35:49+00:00 FIX: Ord for OrdName was not comparing modules - - - - - 5a4ae535 by David Waern at 2007-10-21T21:18:48+00:00 Wibble - - - - - 03d48e20 by David Waern at 2007-10-24T15:52:56+00:00 Remove Main from "other modules" - - - - - c66f6d82 by David Waern at 2007-10-24T16:37:18+00:00 Make it possible to run haddock on itself - - - - - 21d156d8 by David Waern at 2007-10-25T14:02:14+00:00 Don't set boot modules as targets - - - - - f8bcf91c by David Waern at 2007-10-31T22:11:17+00:00 Add optimisation flags - - - - - 7ac758f2 by David Waern at 2007-11-04T09:48:28+00:00 Go back to loading only targets (seems to work now) - - - - - 4862aae1 by David Waern at 2007-11-05T22:24:57+00:00 Do full compilation of modules -- temporary fix for GHC API problem - - - - - 697e1517 by David Waern at 2007-11-05T22:25:50+00:00 Don't warn about not being able to link to wired/system/builtin-names - - - - - 892186da by David Waern at 2007-11-06T00:49:21+00:00 Filter out instances with TyCons that are not exported - - - - - 9548314c by David Waern at 2007-11-06T09:37:14+00:00 Wibble - - - - - 5cafd627 by David Waern at 2007-11-08T01:43:07+00:00 Filter out all non-vanilla type sigs - - - - - 04621830 by David Waern at 2007-11-08T01:45:13+00:00 Synch loading of names from .haddock files with GHC's name cache - - - - - 88d37f77 by David Waern at 2007-11-08T01:46:21+00:00 Remove commented-out code - - - - - 6409c911 by David Waern at 2007-11-08T01:56:00+00:00 Small bugfix and cleanup in getDeclFromTyCls - - - - - af59d9c2 by David Waern at 2007-11-08T02:08:44+00:00 Remove OrdName stuff - - - - - 3a615e2e by David Waern at 2007-11-08T02:13:41+00:00 Update runtests.hs following changes to haddock - - - - - 01f3314e by David Waern at 2007-11-08T02:33:01+00:00 Complain if we can't link to wired-in names - - - - - fcafb5d1 by David Waern at 2007-11-09T02:40:16+00:00 Don't exit when there are no file arguments - - - - - 194bc332 by David Waern at 2007-11-09T02:55:37+00:00 Wibble - - - - - dbe4cb55 by David Waern at 2007-11-09T02:56:14+00:00 Wibble - - - - - 82869fda by David Waern at 2007-11-10T17:01:43+00:00 Introduce InstalledInterface structure and add more stuff to the .haddock files We introduce InstalledInterface capturing the part of Interface that is stored in the interface files. We change the ppHtmlContents and ppHtmllIndex to take this structure instead of a partial Interface. We add stuff like the doc map and exported names to the .haddock file (via InstalledInterface). - - - - - d6bb57bf by David Waern at 2007-11-10T17:19:48+00:00 FIX: contents and index should include external package modules when --gen-contents/--gen-index - - - - - e8814716 by David Waern at 2007-11-11T00:29:27+00:00 Remove lDocLinkName and its use in Html backend - - - - - 6f9bd702 by David Waern at 2007-11-11T00:50:57+00:00 Do some refactoring in the html backend This also merges an old patch by Augustsson: Wed Jul 12 19:54:36 CEST 2006 lennart.augustsson at credit-suisse.com * Print type definitions like signatures if given arrows. - - - - - 09d0ce24 by Malcolm.Wallace at 2006-07-20T13:13:57+00:00 mention HsColour in the docs, next to option flags for linking to source code - - - - - 24da6c34 by Malcolm.Wallace at 2006-07-20T13:14:50+00:00 change doc references to CVS to give darcs repository location instead - - - - - 74d52cd6 by David Waern at 2007-11-11T00:55:33+00:00 Update copyright - - - - - fcaa3b4f by Duncan Coutts at 2006-09-08T13:41:00+00:00 Eliminate dep on network by doing a little cut'n'paste haddock depending on the network causes a circular dependency at least if you want to build the network lib with haddock docs. - - - - - 10cc9bda by David Waern at 2007-11-11T02:09:41+00:00 Fix conflicts - - - - - 4e3acd39 by David Waern at 2007-11-11T02:21:19+00:00 Manual merge of a patch from Duncan Coutts that removes the dependency on mtl - - - - - fa9070da by Neil Mitchell at 2006-09-29T15:52:03+00:00 Do not generate an empty table if there are no exports, this fixes a <table></table> tag being generated, which is not valid HTML 4.01 - - - - - d7431c85 by David Waern at 2007-11-11T02:28:50+00:00 Fix conflicts - - - - - f87e8f98 by Simon Marlow at 2006-10-10T11:37:16+00:00 changes for 0.8 - - - - - db929565 by Simon Marlow at 2006-10-10T12:07:12+00:00 fix the name of the source file - - - - - 8220aa4b by Simon Marlow at 2006-10-11T14:17:37+00:00 Rename haddock.js to haddock-util.js haddock.js will be run automatically by Windows when you type 'haddock' if it is found on the PATH, so rename to avoid confusion. Spotted by Adrian Hey. - - - - - 6bccdaa1 by sven.panne at 2006-10-12T15:28:23+00:00 Cabal's sdist does not generate "-src.tar.gz" files, but ".tar.gz" ones - - - - - d3f3fc19 by Simon Marlow at 2006-12-06T16:05:07+00:00 add todo item for --maintainer - - - - - 2da7e269 by Simon Marlow at 2006-12-15T15:52:00+00:00 TODO: do something better about re-exported symbols from another package - - - - - 42d85549 by David Waern at 2007-11-11T02:30:59+00:00 Fix conflicts - - - - - 5e7ef6e5 by Neil Mitchell at 2007-01-11T15:41:15+00:00 Never do spliting index files into many - - - - - f3d4aebe by Neil Mitchell at 2007-01-11T17:07:09+00:00 Add searching on the index page - - - - - bad3ab66 by Neil Mitchell at 2007-01-11T18:17:46+00:00 Delete dead code, now there is only one index page - - - - - cd09eedb by Neil Mitchell at 2007-01-11T18:21:19+00:00 Delete more stuff that is no longer required - - - - - e2806646 by David Waern at 2007-11-11T02:41:53+00:00 Fix conflicts - - - - - a872a823 by Neil Mitchell at 2007-01-11T18:51:43+00:00 Make the index be in case-insensitive alphabetic order - - - - - 8bddd9d7 by Neil Mitchell at 2007-02-06T17:49:12+00:00 Do not create empty tables for data declarations which don't have any constructors, instances or comments. Gets better HTML 4.01 compliance - - - - - 036b8120 by David Waern at 2007-11-11T02:56:58+00:00 Fix conflicts - - - - - f50c1639 by Conal Elliott at 2007-02-14T21:54:00+00:00 added substitution %{FILE///c} - - - - - 402e166a by David Waern at 2007-11-11T03:35:46+00:00 Manual merge of old patch: Sat Apr 21 04:36:43 CEST 2007 Roberto Zunino <zunrob at users.sf.net> * URL expansion for %%, %L, %{LINE} - - - - - 2f264fbd by David Waern at 2007-11-11T03:40:33+00:00 Manual merge of an old patch: Thu Apr 19 20:23:40 CEST 2007 Wolfgang Jeltsch <g9ks157k at acme.softbase.org> * bug fix When Haddock was invoked with the --ignore-all-exports flag but the ignore-exports module attribute wasn't used, hyperlinks weren't created for non-exported names. This fix might not be as clean as one would wish (since --ignore-all-exports now results in ignore_all_exports = True *and* an additional OptIgnoreExports option for every module) but at least the bug seems to be resolved now. - - - - - 7d7ae106 by sven.panne at 2007-09-02T12:18:02+00:00 Install LICENSE in the correct place - - - - - 66eaa924 by David Waern at 2007-11-11T19:02:46+00:00 Fix a bug that made haddock loop - - - - - 4ed47b58 by David Waern at 2007-11-11T19:03:09+00:00 Rename java-script file (this wasn't merge correctly) - - - - - d569534a by David Waern at 2007-11-11T19:06:44+00:00 Don't require -B <ghc-libdir> when no argument files Change readInterfaceFile to take a Maybe Session, to avoid having to pass -B <ghc-libdir> to Haddock when there're no source files to process. This is nice when computing contents/index for external packages. - - - - - 373368bc by Neil Mitchell at 2007-01-11T18:22:44+00:00 Change from tabs to spaces in the ppHtmlIndex function - - - - - 6b063a77 by Neil Mitchell at 2007-01-12T12:17:46+00:00 Rewrite much of the index searching code, previously was too slow to execute on the base library with IE, the new version guarantees less than O(log n) operations be performed, where n is the number in the list (before was always O(n)) - - - - - bfad00b7 by David Waern at 2007-11-11T23:33:53+00:00 Fix conflicts - - - - - cd2dcc09 by Neil Mitchell at 2007-01-12T12:25:01+00:00 Make the max number of results 75 instead of 50, to allow map searching in the base library to work - - - - - 3ae74764 by Neil Mitchell at 2007-01-12T12:58:17+00:00 Make the search box in a form so that enter does the default search - - - - - 142103e5 by David Waern at 2007-11-12T00:03:18+00:00 Merge patch from the old branch: Fri Aug 31 13:21:45 CEST 2007 Duncan Coutts <duncan at haskell.org> * Add category: Development to .cabal file Otherwise it appears on the hackage website in the "Unclassified" category. - - - - - 22ec2ddb by David Waern at 2007-11-25T01:55:29+00:00 A a list of small improvements to the TODO file - - - - - eb0129f4 by Wolfgang Jeltsch at 2007-12-03T23:47:55+00:00 addition of type equality support (at least for HTML generation) - - - - - 816a7e22 by David Waern at 2007-12-08T15:46:26+00:00 Handle class operators correctly when rendering predicates - - - - - 68baaad2 by David Waern at 2007-12-08T16:15:54+00:00 Code layout changes - - - - - 09b77fb4 by David Waern at 2007-12-08T16:16:03+00:00 Handle infix operators correctly in the Type -> HsType translation - - - - - 31c36da2 by David Waern at 2007-12-08T16:24:27+00:00 Add ppLParendTypes/ppLParendType - - - - - b17cc818 by David Waern at 2007-12-08T16:26:12+00:00 Use ppParendType when printing types args in predicates - - - - - ffd1f2cf by David Waern at 2007-12-08T16:45:06+00:00 Fix rendering of instance heads to handle infix operators This is also a refactoring to share this code for rendering predicates. - - - - - ff886d45 by David Waern at 2007-12-08T17:27:46+00:00 Fix rendering of class operators - - - - - e2fcbb9e by David Waern at 2007-12-08T17:59:28+00:00 Fix a bug (use ppTyName instead of ppName to print names in type apps) - - - - - 79a1056e by David Waern at 2007-12-08T21:25:18+00:00 Update tests - - - - - 867741ac by David Waern at 2007-12-08T21:25:49+00:00 Give a diff on test failure - - - - - 7e5eb274 by David Waern at 2008-01-05T14:33:45+00:00 Add DrIFT commands - - - - - 3656454d by David Waern at 2008-01-05T20:26:00+00:00 Add "cabal-version: >= 1.2" to the cabal file - - - - - 77974efc by Simon Marlow at 2007-12-20T09:52:44+00:00 add an item - - - - - f6ac1708 by Simon Marlow at 2007-12-06T14:00:10+00:00 Source links must point to the original module, not the referring module - - - - - eda1d5c9 by David Waern at 2008-01-06T14:40:52+00:00 Manual merge of a patch to the 0.8 branch Thu Dec 6 15:00:10 CET 2007 Simon Marlow <simonmar at microsoft.com> * Source links must point to the original module, not the referring module - - - - - 378f4085 by David Waern at 2008-01-06T16:03:45+00:00 Change stability from stable to experimental - - - - - 8bdafe44 by David Waern at 2008-01-06T16:14:22+00:00 Add haskell.vim (it had been removed somehow) - - - - - ea34d02e by David Waern at 2008-01-06T16:36:57+00:00 Change version to 2.0.0.0 - - - - - 34631ac0 by David Waern at 2008-01-06T16:44:57+00:00 Add missing modules to the cabal file - - - - - 9e142935 by David Waern at 2008-01-06T17:25:42+00:00 Depend on ghc >= 6.8.2 && < 6.9 - - - - - 59f9eeaa by Simon Marlow at 2007-12-20T10:43:04+00:00 add build scripts - - - - - 1c29ae30 by Simon Marlow at 2007-12-20T10:47:07+00:00 update version number - - - - - fe16a3e4 by Simon Marlow at 2007-12-20T10:48:03+00:00 update version - - - - - f688530f by Simon Marlow at 2007-12-20T10:48:29+00:00 doc updates - - - - - ce71b611 by David Waern at 2008-01-07T13:46:32+00:00 Change version in docs and spec - - - - - 03ab8d6f by David Waern at 2008-01-07T13:47:38+00:00 Manually merge over changes to CHANGES for 0.9 - - - - - 39f1b042 by David Waern at 2008-01-07T15:17:41+00:00 Remove the -use-package flag, we don't support it anyway - - - - - 7274a544 by David Waern at 2008-01-07T15:33:05+00:00 Update CHANGES for 2.0.0.0 - - - - - 96594f5d by David Waern at 2008-01-07T15:46:49+00:00 Wibble - - - - - f4c5a4c4 by David Waern at 2008-01-07T15:55:36+00:00 Change url to repo in documentation - - - - - 8a4c77f0 by David Waern at 2008-01-07T16:00:54+00:00 Update CHANGES - - - - - cb3a9288 by David Waern at 2008-01-07T16:02:55+00:00 Documentation fix - - - - - d8e45539 by David Waern at 2008-01-07T16:12:00+00:00 Update docs to say that Haddock accets .lhs files and module names - - - - - 4b5ce824 by David Waern at 2008-01-07T16:12:25+00:00 Document -B option - - - - - 47274262 by David Waern at 2008-01-07T16:23:07+00:00 Update CHANGES - - - - - 7ff314a9 by David Waern at 2008-01-07T16:23:20+00:00 Remove --use-package, --package & --no-implicit.. flags from docs - - - - - 6c3819c0 by David Waern at 2008-01-07T16:23:52+00:00 Remove --no-implicit-prelide flag - - - - - 1b14ae40 by David Waern at 2008-01-07T16:32:26+00:00 Update the "Using literate or pre-processed source" section - - - - - 0117f620 by David Waern at 2008-01-07T16:41:55+00:00 Document the --optghc flag - - - - - 087ab1cf by David Waern at 2008-01-07T16:42:10+00:00 Remove the documenation section on derived instances The problem mentioned there doesn't exist in Haddock 2.0.0.0 - - - - - 7253951e by David Waern at 2008-01-07T16:48:40+00:00 Document OPTIONS_HADDOCK - - - - - 3b6bdcf6 by David Waern at 2008-01-07T16:56:54+00:00 Wibble - - - - - 3025adf9 by David Waern at 2008-01-07T17:08:14+00:00 Wibble - - - - - 5f30f1a0 by David Waern at 2008-01-07T17:15:44+00:00 Change synopsis field to description - - - - - 1673f54b by David Waern at 2008-01-07T17:18:21+00:00 Change my email address in the cabal file - - - - - 55aa9808 by David Waern at 2008-01-07T18:18:02+00:00 Add documentation for readInterfaceFile - - - - - eaea417f by David Waern at 2008-01-07T18:21:30+00:00 Export necessary stuff from Distribution.Haddock - - - - - 7ea18759 by David Waern at 2008-01-07T18:31:49+00:00 Remove dep on Cabal - - - - - 7b79c74e by David Waern at 2008-01-07T18:33:49+00:00 Remove dep on process - - - - - ce3054e6 by David Waern at 2008-01-16T23:01:21+00:00 Add feature-requsts from Henning Thielemann to TODO - - - - - 0c08f1ec by David Waern at 2008-01-16T23:03:02+00:00 Record a bug in TODO - - - - - b04605f3 by David Waern at 2008-01-23T16:59:06+00:00 Add a bug reported by Ross to TODO - - - - - 5b17c030 by David Waern at 2008-01-23T18:05:53+00:00 A a bug report to TODO - - - - - 1c993b0d by David Waern at 2008-01-25T16:30:25+00:00 Accept test output - - - - - c22fc0d0 by David Waern at 2008-01-25T16:34:49+00:00 Accept test output - - - - - 4b795811 by David Waern at 2008-01-25T16:38:37+00:00 Change Hidden.hs (test) to use OPTIONS_HADDOCK - - - - - c124dbd9 by David Waern at 2008-01-25T16:39:23+00:00 Accept test output - - - - - ec6f6eea by David Waern at 2008-01-25T16:42:08+00:00 Add Hidden.html.ref to tests - - - - - 1dc9610c by David Waern at 2008-02-02T20:50:51+00:00 Add a comment about UNPACK bug in TODO - - - - - 2d3f7081 by David Waern at 2008-02-09T22:33:24+00:00 Change the representation of DocNames Ross Paterson reported a bug where links would point to the defining module instead of the "best" module for an identifier (e.g Int pointing to GHC.Base instead of Data.Int). This patch fixes this problem by refactoring the way renamed names are represented. Instead of representing them by: > data DocName = Link Name | NoLink Name they are now represented as such: > data DocName = Documented Name Module | Undocumented Name and the the link-env looks like this: > type LinkEnv = Map Name Module There are several reasons for this. First of all, the bug was caused by changing the module part of Names during the renaming process, without changing the Unique field. This caused names to be overwritten during the loading of .haddock files (which caches names using the NameCache of the GHC session). So we might create new Uniques during renaming to fix this (but I'm not sure that would be problem-free). Instead, we just keep the Name and add the Module where the name is best documented, since it can be useful to keep the original Name around (for e.g. source-code location info and for users of the Haddock API). Also, the names Link/NoLink don't really make sense, since wether to use links or not is entirely up to the users of DocName. In the process of following this change into H.Backends.Html I removed the assumption that binder names are Undocumented (which was just an unnecessary assumption, the OccName is the only thing needed to render these). This will probably make it possible to get rid of the renamer and replace it with a traversal from SYB or Uniplate. Since DocName has changed, InterfaceFile has changed so this patch also increments the file-format version. No backwards-compatibility is implemented. - - - - - 0f28c921 by David Waern at 2008-02-09T23:00:36+00:00 H.GHC.Utils: remove unused imports/exports - - - - - 0c44cad5 by David Waern at 2008-02-10T00:28:13+00:00 H.GHC.Utils: add some functions that were removed by mistake - - - - - e3452f49 by David Waern at 2008-02-10T00:28:48+00:00 Fix some trivial warnings in H.InterfaceFile - - - - - a6d74644 by David Waern at 2008-02-10T00:48:06+00:00 Update the version message to fit in small terminals - - - - - 76c9cd3e by David Waern at 2008-02-10T14:47:39+00:00 Remove bugs from TODO that don't apply anymore since the port - - - - - 5e10e090 by David Waern at 2008-02-10T15:22:47+00:00 Remove bugs from TODO that weren't actual bugs - - - - - fef70878 by David Waern at 2008-02-10T15:23:44+00:00 Remove yet another item from TODO that was not an actual bug - - - - - e1af47b8 by David Waern at 2008-02-11T10:25:57+00:00 Bump the version number to 2.1.0 Since the exported datatype DocName has changed, we need to bump the major version number. Let's also drop the fourth version component, it's not that useful. - - - - - e3be7825 by David Waern at 2008-04-11T14:29:04+00:00 Add a bug to TODO - - - - - cb6574be by David Waern at 2008-04-11T16:00:45+00:00 Use the in-place haddock when running tests - - - - - c6d7af0d by David Waern at 2008-04-11T16:09:16+00:00 Turn off GHC warnings when running tests - - - - - 7f61b546 by David Waern at 2008-04-11T17:24:00+00:00 Add a flag for turning off all warnings - - - - - 883b8422 by David Waern at 2008-04-12T14:02:18+00:00 Fix printing of data binders - - - - - 2a0db8fc by David Waern at 2008-04-12T18:52:46+00:00 Fix missing parenthesis in constructor args bug - - - - - 1b3ac3f9 by David Waern at 2008-04-12T18:57:23+00:00 Simplify test suite and add tests I move all tests into one single directory to simplify things, and add a test for the last bug that was fixed. - - - - - 8f178376 by David Waern at 2008-04-12T19:00:15+00:00 Add a script for copying test output to "expected" output - - - - - 193e3a03 by David Waern at 2008-04-12T19:16:37+00:00 Remove two fixed bugs from TODO - - - - - ddc9130c by David Waern at 2008-04-12T19:37:06+00:00 Update test README - - - - - 956069c0 by David Waern at 2008-05-01T12:16:14+00:00 Update version number in spec and docs - - - - - 5478621c by David Waern at 2008-05-01T12:28:12+00:00 Remove claim of backwards compatibility from docs for readInterfaceFile - - - - - 4a16dea9 by David Waern at 2008-05-01T12:33:04+00:00 Update CHANGES - - - - - 804216fb by David Waern at 2008-05-01T12:43:16+00:00 Add a synopsis - - - - - fd0c84d5 by David Waern at 2008-05-01T12:44:44+00:00 Add Haddock.DocName to the cabal file - - - - - 9f4a7439 by David Waern at 2008-05-01T12:45:53+00:00 Remove -fglasgow-exts and -fasm - - - - - aee7c145 by David Waern at 2008-05-01T12:54:01+00:00 Add LANGUAGE pragmas to source files - - - - - 9a58428b by David Waern at 2008-05-01T12:54:19+00:00 Add extensions to cabal file - - - - - 494f1bee by David Waern at 2008-05-01T13:12:09+00:00 Export DocName in the API - - - - - c938196b by David Waern at 2008-05-01T13:12:19+00:00 Add hide options to some source files - - - - - 236e86af by Neil Mitchell at 2008-06-07T20:45:10+00:00 Rewrite the --hoogle flag support - - - - - 6d910950 by Neil Mitchell at 2008-06-14T10:56:50+00:00 Simplify the newtype/data outputting in Hoogle, as haddock does it automatically - - - - - f87a95a8 by Neil Mitchell at 2008-06-14T12:10:18+00:00 Add initial structure for outputting documentation as well, but does not yet output anything - - - - - 7c3bce54 by Neil Mitchell at 2008-06-14T12:27:07+00:00 Remove <document comment> from the Hoogle output - - - - - 9504a325 by Neil Mitchell at 2008-06-16T06:33:21+00:00 Default to "main" if there is no package, otherwise will clobber hoogle's hoogle info - - - - - 4a794a79 by Neil Mitchell at 2008-06-16T06:53:29+00:00 Change packageName to packageStr, as it better reflects the information stored in it - - - - - 7abc9baf by Neil Mitchell at 2008-06-16T07:09:49+00:00 Add modulePkgInfo to Haddock.GHC.Utils, which gives back package name and version info - - - - - 8ca11514 by Neil Mitchell at 2008-06-16T07:13:48+00:00 Change Hoogle to take the package name and package version separately - - - - - a6da452d by Neil Mitchell at 2008-06-18T11:29:46+00:00 In Hoogle do not list things that are not local to this module - - - - - 974b76b7 by David Waern at 2008-06-19T18:40:13+00:00 Be more consistent with GHC API naming in H.GHC.Utils - - - - - 2facb4eb by David Waern at 2008-06-19T19:03:03+00:00 Update test output - - - - - c501de72 by David Waern at 2008-06-26T20:26:49+00:00 Use ghc-paths to get the lib dir The path can still be overridden using the -B flag. It's not longer required to pass the lib dir to the program that runs the test suite. - - - - - ac4c6836 by David Waern at 2008-06-26T20:33:08+00:00 Update CHANGES - - - - - 9d21c60a by David Waern at 2008-06-26T20:34:53+00:00 Update README - - - - - 741448f0 by David Waern at 2008-06-26T21:12:57+00:00 Improve wording in the help message - - - - - b1b42b11 by David Waern at 2008-06-30T10:16:17+00:00 Rename ForeignType - - - - - 6d6c2b34 by David Waern at 2008-06-30T10:25:09+00:00 Rename TyFamily - - - - - 8d1125ed by David Waern at 2008-06-30T10:37:21+00:00 Rename type patterns - - - - - 7610a4cb by David Waern at 2008-06-30T10:45:07+00:00 Rename associated types - - - - - 8eeba14c by David Waern at 2008-06-30T10:47:41+00:00 Remove the TODO file now that we have a trac - - - - - 1af5b25b by David Waern at 2008-07-02T18:19:28+00:00 Render type family declarations (untested) - - - - - ceb99797 by David Waern at 2008-07-02T18:24:06+00:00 Remove redundant check for summary when rendering data types - - - - - b36a58e0 by David Waern at 2008-07-02T22:01:38+00:00 More support for type families and associated types Now we just need to render the instances - - - - - 78784879 by David Waern at 2008-07-07T22:13:58+00:00 Remove filtering of instances We were filtering out all instances for types with unknown names. This was probably an attempt to filter out instances for internal types. I am removing the filtering for the moment, and will try to fix this properly later. - - - - - 3e758dad by David Waern at 2008-06-30T18:50:30+00:00 Run haddock in-place during testing - - - - - d9dab0ce by David Waern at 2008-07-08T21:04:32+00:00 Remove index.html and doc-index.html from output, they should not be versioned - - - - - 3e6c4681 by David Waern at 2008-07-08T21:06:42+00:00 Update test output following change to instance filtering - - - - - e34a3f14 by David Waern at 2008-07-12T16:48:28+00:00 Stop using the map from exported names to declarations During creation of the interface, we were using two maps: one from exported names to declarations, and one from all defined names in the module to declarations. The first contained subordinate names while the second one didn't. The first map was never used to look up names not defined in the associated module, so if we add subordinate names to the second map, we could use it everywhere. That's that this patch does. This simplifies code because we don't have to pass around two maps everywhere. We now store the map from locally defined things in the interface structure instead of the one from exported names. - - - - - 2e1d2766 by David Waern at 2008-07-12T16:55:21+00:00 Get the all locally defined names from GHC API We previously had some code to compute all locally defined names in a module including subordinate names. We don't need it since we can get the names from modInfoTyThings in the GHC API. - - - - - bf637994 by David Waern at 2008-07-13T13:09:16+00:00 Refactoring in H.Interface.Create We were creating a doc map, a declaration map and a list of entities separately by going through the HsGroup. These structures were all used to build the interface of a module. Instead of doing this, we can start by creating a list of declarations from the HsGroup, then collect the docs directly from this list (instead of using the list of entities), creating a documentation map. We no longer need the Entity data type, and we can store a single map from names to declarations and docs in the interface, instead of the declaration map and the doc map. This way, there is only one place where we filter out the declarations that we don't want, and we can remove a lot of code. Another advantage of this is that we can create the exports directly out of the list of declarations when we export the full module contents. (Previously we did a look up for each name to find the declarations). This is faster and removes another point where we depend on names to identify exported declarations, which is good because it eliminates problems with instances (which don't have names). - - - - - 547e410e by David Waern at 2008-07-13T13:34:51+00:00 Remove FastString import and FSLIT macro in H.I.Create -- they were unused - - - - - 693759d1 by David Waern at 2008-07-13T13:36:23+00:00 Remove unused import from H.I.Create - - - - - cde6e7fb by David Waern at 2008-07-13T13:51:54+00:00 Small touches - - - - - 96de8f1d by David Waern at 2008-07-20T11:21:46+00:00 Preparation for rendering instances as separate declarations We want to be able to render instances as separate declarations. So we remove the Name argument of ExportDecl, since instances are nameless. This patch also contains the first steps needed to gather type family instances and display them in the backend, but the implementation is far from complete. Because of this, we don't actually show the instances yet. - - - - - b0f824fb by David Waern at 2008-07-20T15:53:08+00:00 Follow changes to ExportDecl in Hoogle - - - - - 1192eff3 by Neil Mitchell at 2008-06-26T00:28:10+00:00 Change how the Hoogle backend outputs classes, adding the context in - - - - - 7a0d1464 by Neil Mitchell at 2008-06-26T00:28:46+00:00 Remove the indent utility function from Hoogle backend - - - - - 3361241b by Neil Mitchell at 2008-06-26T09:45:09+00:00 Add support for Hoogle writing ForeignImport/ForeignExport properly - - - - - 795ad3bf by Neil Mitchell at 2008-06-26T12:15:25+00:00 Flesh out the Hoogle code to render documentation - - - - - 23277995 by Neil Mitchell at 2008-06-26T14:56:41+00:00 Fix a bug in the Hoogle backend, unordered lists were being written out <ul>...</u> - - - - - db739b27 by Neil Mitchell at 2008-06-26T15:09:54+00:00 Remove any white space around a <li> element - - - - - f2e6bb8c by Neil Mitchell at 2008-07-10T15:30:47+00:00 Remove the TODO in the Hoogle HTML generation, was already done - - - - - 693ec9a3 by Neil Mitchell at 2008-07-10T15:53:00+00:00 Put brackets round operators in more places in the Hoogle output - - - - - 842313aa by Neil Mitchell at 2008-07-10T16:01:25+00:00 Print type signatures with brackets around the name - - - - - cf93deb0 by David Waern at 2008-07-20T17:04:22+00:00 Bump version number to 2.2.0 - - - - - 30e6a8d1 by David Waern at 2008-07-20T17:04:41+00:00 Resolve conflicts in H.B.Hoogle - - - - - 1f0071c9 by David Waern at 2008-07-23T23:05:01+00:00 Add "all" command to runtests.hs that runs all tests despite failures - - - - - f2723023 by David Waern at 2008-07-23T23:08:39+00:00 Update tests/README - - - - - c0304a11 by David Waern at 2008-07-23T23:21:15+00:00 Be compatible with GHC 6.8.3 The cabal file is converted to use the "new" syntax with explicit Library and Executable sections. We define the __GHC_PATCHLEVEL__ symbol using a conditinal cpp-options field in the cabal file. (Ideally, Cabal would define the symbol for us, like it does for __GLASGOW_HASKELL__). We use these symbols to #ifdef around a small difference between 6.8.2 and 6.8.3. Previously, we only supported GHC 6.8.2 officially but the dependencies field said "ghc <= 6.9". This was just for convenience when testing against the (then compatible) HEAD version of GHC, and was left in the release by mistake. Now, we support both GHC 6.8.2 and 6.8.3 and the dependencies field correctly reflects this. - - - - - 88a5fe71 by David Waern at 2008-07-23T23:54:16+00:00 Depend on the currently available ghc-paths versions only - - - - - 8738d97b by David Waern at 2008-07-24T10:50:44+00:00 FIX haskell/haddock#44: Propagate parenthesis level when printing documented types - - - - - 05339119 by David Waern at 2008-07-24T16:06:18+00:00 Drop unnecessary parenthesis in types, put in by the user We were putting in parenthesis were the user did. Let's remove this since it just clutters up the types. The types are readable anyway since we print parens around infix operators and do not rely on fixity levels. When doing this I discovered that we were relying on user parenthesis when printin types like (a `O` b) c. This patchs fixes this problem so that parenthesis are always inserted around an infix op application in case it is applied to further arguments, or if it's an arguments to a type constructor. Tests are updated. - - - - - b3a99828 by David Waern at 2008-07-24T10:19:43+00:00 Print parenthesis around non-atomic banged types Fixes half of haskell/haddock#44 - - - - - ab5238e0 by David Waern at 2008-07-24T22:07:49+00:00 Add a reference file for the TypeFamilies test - - - - - 1941cc11 by David Waern at 2008-07-25T17:15:53+00:00 Simplify definition of pretty and trace_ppr - - - - - e3bfa33c by David Waern at 2008-07-25T17:18:27+00:00 Warning messages Output a warning when filtering out data/type instances and associated types in instances. We don't show these in the documentation yet, and we need to let the user know. - - - - - 9b85fc89 by David Waern at 2008-07-25T17:45:40+00:00 Doc: Mention Hoogle in the Introduction - - - - - afb2dd60 by David Waern at 2008-07-25T17:49:00+00:00 Doc: update -B description - - - - - 584c0c91 by David Waern at 2008-07-25T18:11:38+00:00 Doc: describe -w flag - - - - - 77619c24 by David Waern at 2008-07-28T12:29:07+00:00 Remove TODO from cabal file - - - - - 96717d5f by David Waern at 2008-07-28T12:29:27+00:00 Support type equality predicates - - - - - c2fd2330 by David Waern at 2008-07-29T19:45:14+00:00 Move unL from H.B.Hoogle to H.GHC.Utils I like Neil's shorter unL better than unLoc from the GHC API. - - - - - c4c3bf6a by David Waern at 2008-07-29T19:47:36+00:00 Do not export ATs when not in list of subitems - - - - - bf9a7b85 by David Waern at 2008-08-03T11:42:59+00:00 Filter out ForeignExports - - - - - df59fcb0 by David Waern at 2008-08-03T14:02:51+00:00 Filter out more declarations The previous refactorings in H.I.Create introduced a few bugs. Filtering of some types of declarations that we don't handle was removed. This patch fixes this. - - - - - 2f8a958b by David Waern at 2008-08-03T15:24:07+00:00 Move reL to H.GHC.Utils so we can use it everywhere - - - - - 8ec15efd by David Waern at 2008-08-03T15:25:00+00:00 Use isVanillaLSig from GHC API instead of home brewn function - - - - - 300f93a2 by David Waern at 2008-08-03T15:25:27+00:00 Filter out separately exported ATs This is a quick and dirty hack to get rid of separately exported ATs. We haven't decided how to handle them yet. No warning message is given. - - - - - 8776d1ec by David Waern at 2008-08-03T16:21:21+00:00 Filter out more declarations and keep only vanilla type sigs in classes - - - - - ea07eada by David Waern at 2008-08-03T16:48:00+00:00 Fix layout - - - - - dd5e8199 by David Waern at 2008-08-03T16:50:52+00:00 Move some utility functions from H.I.Create to H.GHC.Utils - - - - - 4a1dbd72 by David Waern at 2008-08-03T17:39:55+00:00 Do not filter out doc declarations - - - - - 0bc8dca4 by David Waern at 2008-08-03T17:47:26+00:00 Filter out separately exported ATs (take two) - - - - - af970fe8 by David Waern at 2008-08-03T22:39:17+00:00 Update CHANGES - - - - - 5436ad24 by David Waern at 2008-08-03T22:40:20+00:00 Bump version number to 2.2.1 - - - - - d66de448 by David Waern at 2008-08-05T19:00:32+00:00 Remove version restriction on ghc-paths - - - - - 534b1364 by David Waern at 2008-08-05T19:04:35+00:00 Bump version to 2.2.2 and update CHANGES - - - - - 549188ff by David Waern at 2008-08-05T19:16:49+00:00 Fix CHANGES - - - - - 0d156bb4 by Luke Plant at 2008-08-11T15:20:59+00:00 invoking haddock clarification and help - - - - - 748295cc by David Waern at 2008-08-11T18:56:37+00:00 Doc: say that the --hoogle option is functional - - - - - 43301db4 by David Waern at 2008-08-05T19:26:08+00:00 Change ghc version dependency to >= 6.8.2 - - - - - 3e5a53b6 by David Waern at 2008-08-10T22:42:05+00:00 Make H.GHC.Utils build with GHC HEAD - - - - - 7568ace0 by David Waern at 2008-08-11T19:41:54+00:00 Import Control.OldException instead of C.Exception when using ghc >= 6.9 We should really test for base version instead, but I don't currently know which version to test for. - - - - - b71ae991 by David Waern at 2008-08-12T22:40:39+00:00 Make our .haddock file version number depend on the GHC version We need to do this, since our .haddock format can potentially change whenever GHC's version changes (even when only the patchlevel changes). - - - - - 6307ce3f by David Waern at 2008-08-12T22:49:57+00:00 Remove matching on NoteTy in AttachInstances, it has been removed - - - - - 2dbcfd5f by David Waern at 2008-08-12T23:02:02+00:00 Comment out H.GHC.loadPackages - it is unused and doesn't build with ghc >= 6.9 - - - - - c74db5c2 by David Waern at 2008-08-12T23:03:58+00:00 Hide <.> from GHC import in Hoogle only for ghc <= 6.8.3 - - - - - 69a44ebb by David Waern at 2008-08-12T23:11:12+00:00 Follow changes to parseDynamic/StaticFlags - - - - - 5881f3f0 by David Waern at 2008-08-13T21:43:58+00:00 Add __GHC_PATCHLEVEL__ symbol also when building the library - - - - - 8574dc11 by David Waern at 2008-08-13T21:44:17+00:00 Follow move of package string functions from PackageConfig to Module - - - - - c9baa77f by David Waern at 2008-08-13T21:45:29+00:00 Follow extensible exceptions changes - - - - - 9092de15 by David Waern at 2008-08-13T21:46:20+00:00 Update test following Haddock version change - - - - - ebe569a4 by David Waern at 2008-08-13T21:46:54+00:00 Follow changes to parseDynamic- parseStaticFlags in GHC - - - - - b8a5ffd3 by David Waern at 2008-08-13T21:47:36+00:00 Follow changes to Binary in GHC 6.9 - - - - - edfda1cc by David Waern at 2008-08-13T21:50:17+00:00 Change ghc version dependency to >= 6.8.2 && <= 6.9 - - - - - d59be1cf by Neil Mitchell at 2008-08-12T16:02:53+00:00 Output all items, even if they are not defined in this module - ensures map comes from Prelude, not just GHC.Base - - - - - dda93b9f by Neil Mitchell at 2008-08-12T21:37:32+00:00 Add support for type synonyms to Hoogle, was accidentally missing before (woops!) - - - - - b6ee795c by Neil Mitchell at 2008-08-13T14:03:24+00:00 Generalise Hoogle.doc and add a docWith - - - - - 415e1bb2 by Neil Mitchell at 2008-08-13T14:03:46+00:00 Make Hoogle add documentation to a package - - - - - 790a1202 by Neil Mitchell at 2008-08-18T12:52:43+00:00 Use the same method to put out signatures as class methods in the Hoogle backend - - - - - ded37eba by Neil Mitchell at 2008-08-18T12:53:04+00:00 Remove Explicit top-level forall's when pretty-printing signatures - - - - - 6468c722 by Neil Mitchell at 2008-08-20T07:59:13+00:00 Simplify the code by removing not-to-important use of <.> in the Hoogle back end - - - - - 788c3a8b by Neil Mitchell at 2008-08-21T18:20:24+00:00 In the hoogle back end, markup definition lists using <i>, not <b> - - - - - 77d4b000 by Ian Lynagh at 2008-08-14T10:49:14+00:00 Add a Makefile for GHC's build system. Still won't work yet, but we're closer - - - - - 920440d7 by Ian Lynagh at 2008-08-27T18:06:46+00:00 Add haddock.wrapper - - - - - bcda925f by Ian Lynagh at 2008-08-27T18:07:02+00:00 Add a manual Cabal flag to control the ghc-paths dependency - - - - - 04d194e2 by Ian Lynagh at 2008-08-27T20:41:27+00:00 Update extensions in Cabal file Use ScopedTypeVariables instead of PatternSignatures - - - - - 12480043 by Ian Lynagh at 2008-08-27T20:41:55+00:00 Increase the upper bound on the GHC version number - - - - - b1f809a5 by Ian Lynagh at 2008-08-27T21:32:22+00:00 Fix some warnings - - - - - aea0453d by Ian Lynagh at 2008-08-28T14:22:29+00:00 Fixes for using haddock in a GHC build tree - - - - - ad23bf86 by Ian Lynagh at 2008-08-28T21:14:27+00:00 Don't use Cabal wrappers on Windows - - - - - 35858e4c by Ian Lynagh at 2008-08-29T00:07:42+00:00 Fix in-tree haddock on Windows - - - - - c2642066 by Ian Lynagh at 2008-09-03T22:35:53+00:00 follow library changes - - - - - 2eb55d50 by Ian Lynagh at 2008-09-07T18:52:51+00:00 bindist fixes - - - - - 3daa5b59 by Ian Lynagh at 2008-09-10T16:58:18+00:00 We need to tell haddock that its datasubdir is . or it can't find package.conf - - - - - 388fd8c2 by Ian Lynagh at 2008-09-10T19:47:44+00:00 Fix haddock inplace on Windows - - - - - 70a641c1 by Ian Lynagh at 2008-09-10T22:15:44+00:00 Fix installed haddock on Windows - - - - - 83c1e997 by Neil Mitchell at 2008-09-11T10:48:55+00:00 Import GHC.Paths if not IN_GHC_TREE, seems to match the use of GHC.Paths functions much better - - - - - b452519b by Ian Lynagh at 2008-09-12T12:58:24+00:00 Add a LANGUAGE ForeignFunctionInterface pragma - - - - - afbd592c by Ian Lynagh at 2008-09-12T12:59:13+00:00 Wibble imports - - - - - 547ac4ad by Ian Lynagh at 2008-09-14T15:34:22+00:00 Add a "#!/bin/sh" to haddock.wrapper - - - - - f207a807 by Ian Lynagh at 2008-09-15T10:02:32+00:00 Use "exec" when calling haddock in the wrapper - - - - - 2ee68509 by Thomas Schilling at 2008-09-15T09:09:16+00:00 Port Haddock.Interface to new GHC API. This required one bigger change: 'readInterfaceFile' used to take an optional 'Session' argument. This was used to optionally update the name cache of an existing GHC session. This does not work with the new GHC API, because an active session requires the function to return a 'GhcMonad' action, but this is not possible if no session is provided. The solution is to use an argument of functions for reading and updating the name cache and to make the function work for any monad that embeds IO, so it's result type can adapt to the calling context. While refactoring, I tried to make the code a little more self-documenting, mostly turning comments into function names. - - - - - 3bb96431 by Thomas Schilling at 2008-09-15T09:09:37+00:00 Reflect GHC API changes. - - - - - 2e60f714 by Thomas Schilling at 2008-09-15T09:10:37+00:00 Port Haddock.GHC.Typecheck to new GHC API. - - - - - 9cfd4cff by Thomas Schilling at 2008-09-15T09:11:00+00:00 Port Haddock.GHC to new GHC API. - - - - - caffa003 by Thomas Schilling at 2008-09-15T09:11:25+00:00 Port Main to new GHC API. - - - - - 069a4608 by Ian Lynagh at 2008-09-21T11:19:00+00:00 Fix paths used on Windows frmo a GHC tree: There is no whare directory - - - - - 7ceee1f7 by Ian Lynagh at 2008-09-21T12:20:16+00:00 Fix the in-tree haddock on Windows - - - - - 0d486514 by Ian Lynagh at 2008-09-23T18:06:58+00:00 Increase the GHC upper bound from 6.11 to 6.13 - - - - - f092c414 by Neil Mitchell at 2008-09-11T14:56:07+00:00 Do not wrap __ in brackets - - - - - 036bdd13 by Ian Lynagh at 2008-09-28T01:42:35+00:00 Fix building haddock when GhcProfiled=YES - - - - - 01434a89 by David Waern at 2008-09-24T20:24:21+00:00 Add PatternSignatures LANGUAGE pragma to Main and Utils - - - - - 1671a750 by David Waern at 2008-10-02T22:57:25+00:00 For source links, get original module from declaration name instead of environment. Getting it from the environment must have been a remnant from the times when we were using unqualified names (versions 0.x). - - - - - a25dde99 by David Waern at 2008-10-02T22:59:57+00:00 Remove ifaceEnv from Interface - it's no longer used - - - - - 610993da by David Waern at 2008-10-02T23:04:58+00:00 Write a comment about source links for type instance declarations - - - - - 5a96b5d5 by Thomas Schilling at 2008-10-03T10:45:08+00:00 Follow GHC API change of parseModule. - - - - - 5a943ae5 by Ian Lynagh at 2008-10-03T15:56:58+00:00 TAG 2008-10-03 - - - - - 76cdd6ae by Thomas Schilling at 2008-10-08T12:29:50+00:00 Only load modules once when typechecking with GHC. This still doesn't fix the memory leak since the typechecked source is retained and then processed separately. To fix the leak, modules must be processed directly after typechecking. - - - - - 7074d251 by David Waern at 2008-10-09T23:53:54+00:00 Interleave typechecking with interface creation At the same time, we fix a bug where the list of interfaces were processed in the wrong order, when building the links and renaming the interfaces. - - - - - 4b9b2b2d by David Waern at 2008-10-09T23:54:49+00:00 Add some strictness annotations in Interface We add some strictness annotations to the fields of Interface, so that less GHC data is hold on to during processing. - - - - - 22035628 by David Waern at 2008-10-10T20:02:31+00:00 Remove typecheckFiles and MonadUtils import from H.GHC.Typeccheck - - - - - be637ad3 by David Waern at 2008-10-10T20:33:38+00:00 Make Haddock build with GHC 6.8.2 - - - - - 523b3404 by David Waern at 2008-10-10T21:08:09+00:00 Fix documentation for createInterfaces - - - - - e1556702 by David Waern at 2008-10-10T21:26:19+00:00 Hide H.Utils in library - - - - - a8e751c3 by David Waern at 2008-10-10T21:34:59+00:00 Add back .haddock file versioning based on GHC version It was accidentally removed in the patch for GHC 6.8.2 compatibility - - - - - 06fb3c01 by David Waern at 2008-10-10T21:47:15+00:00 Bump version number to 2.3.0 - - - - - ff087fce by David Waern at 2008-10-10T22:35:49+00:00 Add support for DocPic The support for DocPic was merged into the GHC source long ago, but the support in Haddock was forgotten. Thanks Peter Gavin for submitting this fix! - - - - - 3af85bf6 by David Waern at 2008-10-10T23:34:05+00:00 Update tests - - - - - 0966873c by Simon Marlow at 2008-10-10T14:43:04+00:00 no need for handleErrMsg now, we don't throw any ErrMsgs - - - - - f1870de3 by Clemens Fruhwirth at 2008-10-10T13:29:36+00:00 Compile with wrapper but remove it for dist-install - - - - - 7b440dc2 by David Waern at 2008-10-11T14:02:25+00:00 Remove interface from LinksInfo It was there to know the documentation home module when creating a wiki link, but we already know this since we have the DocName. - - - - - e5729e6a by David Waern at 2008-10-15T20:49:18+00:00 Wibble - - - - - b2a8e01a by David Waern at 2008-10-15T21:03:36+00:00 Use type synonyms for declarations and docs in H.I.Create - - - - - be71a15b by David Waern at 2008-10-15T21:12:17+00:00 Comment out unused type family stuff completely - - - - - 91aaf075 by David Waern at 2008-10-15T21:49:04+00:00 Wibble - - - - - 42ba4eb4 by David Waern at 2008-10-15T21:53:53+00:00 Move convenient type synonym to H.Types - - - - - db11b723 by David Waern at 2008-10-15T22:14:07+00:00 Add DeclInfo to H.Types - - - - - 193552b6 by David Waern at 2008-10-15T22:15:01+00:00 Add subordinates with docs to the declaration map The only place in the code where we want the subordinates for a declaration is right after having looked up the declaration in the map. And since we include subordinates in the map, we might as well take the opportunity to store those subordinates that belong to a particular declaration together with that declaration. We also store the documentation for each subordinate. - - - - - 31e6eebc by David Waern at 2008-10-16T17:18:47+00:00 Wibble - - - - - 0dcbd79f by David Waern at 2008-10-16T20:58:42+00:00 Fix haskell/haddock#61 We were not getting docs for re-exported class methods. This was because we were looking up the docs in a map made from the declarations in the current module being rendered. Obviously, re-exported class methods come from another module. Class methods and ATs were the only thing we were looking up using the doc map, everything else we found in the ExporItems. So now I've put subordinate docs in the ExportItem's directly, to make things a bit more consistent. To do this, I added subordinates to the the declarations in the declaration map. This was easy since we were computing subordinates anyway, to store stand-alone in the map. I added a new type synonym 'DeclInfo', which is what we call what is now stored in the map. This little refactoring removes duplicate code to retrieve subordinates and documentation from the HsGroup. - - - - - de47f20a by David Waern at 2008-10-16T22:06:35+00:00 Document function and improve its layout - - - - - e74e625a by Thomas Schilling at 2008-10-20T11:12:57+00:00 Force interface more aggressively. For running Haddock on GHC this reduces memory usage by about 50 MB on a 32 bit system. A heap profile shows total memory usage peak at about 100 MB, but actual usage is at around 300 MB even with compacting GC (+RTS -c). - - - - - b63ac9a1 by David Waern at 2008-10-20T20:25:50+00:00 Make renamer consistent Instead of explicitly making some binders Undocumented, treat all names the same way (that is, try to find a Documented name). - - - - - f6de0bb0 by Ian Lynagh at 2008-09-19T00:54:43+00:00 TAG GHC 6.10 fork - - - - - 74599cd0 by David Waern at 2008-10-20T21:13:24+00:00 Do not save hidden modules in the .haddock file We were saving interfaces of all processed modules including those hidden using {-# OPTIONS_HADDOCK hide #-} in the .haddock file. This caused broken links when generating the index for the libraries that come with GHC. This patch excludes modules with hidden documentation when writing .haddock files. It should fix the above problem. - - - - - 7b6742e9 by David Waern at 2008-10-21T19:54:52+00:00 Do not save hidden modules in the .haddock file (also for ghc >= 6.9) When writing the first patch, I forgot to do the fix in both branches of an #if macro. - - - - - b99b1951 by David Waern at 2008-10-22T20:04:18+00:00 Remove subordinate map and its usage It is not needed now that we store subordinate names in the DeclInfo map. - - - - - da97cddc by David Waern at 2008-10-22T20:11:46+00:00 Tidy up code in H.I.Create a little Remove commented out half-done type instance support, and remove DeclWithDoc synonym. - - - - - 6afa76f3 by David Waern at 2008-10-22T21:17:29+00:00 Fix warnings in H.GHC.Utils - - - - - 171ea1e8 by David Waern at 2008-10-22T21:35:04+00:00 Fix warnings in H.Utils - - - - - c8cb3b91 by David Waern at 2008-10-22T21:36:49+00:00 Wibble - - - - - 767fa06a by David Waern at 2008-10-27T19:59:04+00:00 Make named doc comments into ExportDoc instead of ExportDecl Fixes a crash when processing modules without export lists containing named docs. - - - - - e638bbc6 by David Waern at 2008-11-02T22:21:10+00:00 Add HCAR entry - - - - - 92b4ffcf by David Waern at 2008-11-02T22:44:19+00:00 Update CHANGES - - - - - 84d4da6e by David Waern at 2008-11-03T11:25:04+00:00 Add failing test for template haskell crash - - - - - 2a9cd2b1 by David Waern at 2008-11-04T21:13:44+00:00 Add tests/TH.hs - - - - - 8a59348e by David Waern at 2008-11-04T21:30:26+00:00 TAG 2.3.0 - - - - - 54f70d31 by Thomas Schilling at 2008-10-24T17:04:08+00:00 Enable framed view of the HTML documentation. This patch introduces: - A page that displays the documentation in a framed view. The left side will show a full module index. Clicking a module name will show it in the right frame. If Javascript is enabled, the left side is split again to show the modules at the top and a very short synopsis for the module currently displayed on the right. - Code to generate the mini-synopsis for each module and the mini module index ("index-frames.html"). - CSS rules for the mini-synopsis. - A very small amount of javascript to update the mini-synopsis (but only if inside a frame.) Some perhaps controversial things: - Sharing code was very difficult, so there is a small amount of code duplication. - The amount of generated pages has been doubled, since every module now also gets a mini-synopsis. The overhead should not be too much, but I haven't checked. Alternatively, the mini-synopsis could also be generated using Javascript if we properly annotate the actual synopsis. - - - - - 5d7ea5a6 by David Waern at 2008-11-04T23:20:17+00:00 Follow change to ExportDecl in frames code - - - - - 60e16308 by David Waern at 2008-11-04T23:35:26+00:00 Update CHANGES - - - - - d63fd26d by David Waern at 2008-11-04T23:37:43+00:00 Bump version number - - - - - c1660c39 by David Waern at 2008-11-04T23:44:46+00:00 Update CHANGES - - - - - 995ab384 by David Waern at 2008-11-04T23:55:21+00:00 Remove .ref files from tests/output/ - - - - - 1abbbe75 by David Waern at 2008-11-04T23:57:41+00:00 Output version info before running tests - - - - - 649b182f by David Waern at 2008-11-05T22:45:37+00:00 Add ANNOUNCE message - - - - - c36ae0bb by David Waern at 2008-11-05T23:15:35+00:00 Update ANNOUNCE - - - - - 9c4f3d40 by David Waern at 2008-11-05T23:18:30+00:00 Wibble - - - - - 5aac87ce by David Waern at 2008-11-06T21:07:48+00:00 Depend on base 4.* when using GHC >= 6.9, otherwise 3.* - - - - - b9796a74 by David Waern at 2008-11-06T21:13:40+00:00 Bump version to 2.4.1 and update CHANGES - - - - - d4b26baa by David Waern at 2008-11-06T21:26:33+00:00 Depend on base 4.0.* instead of 4.* - - - - - 2cb0903c by David Waern at 2008-11-06T21:46:53+00:00 Fix warnings in H.B.HH and H.B.HH2 - - - - - e568e89a by David Waern at 2008-11-06T21:47:12+00:00 Fix warnings in Haddock.ModuleTree - - - - - 9dc14fbd by David Waern at 2008-11-06T21:47:52+00:00 Fix warnings in Haddock.Version - - - - - 02ac197c by David Waern at 2008-11-06T21:51:31+00:00 Fix warnings in H.InterfaceFile and H.Options - - - - - 63e7439a by David Waern at 2008-11-06T21:59:45+00:00 Fix warnings in H.GHC.Typecheck - - - - - 4bca5b68 by David Waern at 2008-11-08T13:43:42+00:00 Set HscTarget to HscNothing instead of HscAsm There used to be a bug in the GHC API that prevented us from setting this value. - - - - - 07357aec by David Waern at 2008-11-09T22:27:00+00:00 Re-export NameCache and friends from Distribution.Haddock - - - - - ea554b5a by David Waern at 2008-11-09T23:14:10+00:00 Add Haddock.GHC.Utils to other-modules in library - - - - - 74aecfd7 by David Waern at 2008-11-10T01:18:57+00:00 Export DocName in the library - - - - - 241a58b3 by David Waern at 2008-11-10T01:19:18+00:00 Document the functions in H.DocName - - - - - edc2ef1b by David Waern at 2008-11-10T01:20:52+00:00 Export H.DocName in the library - - - - - 4f588d55 by David Waern at 2008-11-10T01:29:14+00:00 Make DocName an instance of NamedThing - - - - - b4647244 by David Waern at 2008-11-15T22:58:18+00:00 Reflect version bump in test suite - - - - - 4bee8ce2 by David Waern at 2008-11-15T22:58:45+00:00 Update tests For unknown reasons, test output for Bug1 and Test has changed for the better. - - - - - 1690e2f9 by David Waern at 2008-11-15T22:59:33+00:00 Store hidden modules in .haddock files We store documentation for an entity in the 'InstalledInterface' of the definition site module, and never in the same structure for a module which re-exports the entity. So when a client of the Haddock library wants to look up some documentation, he/she might need to access a hidden module. But we currently don't store hidden modules in the .haddock files. So we add the hidden modules and the Haddock options to the .haddock files. The options will be used to filter the module list to obtain the visible modules only, which is necessary for generating the contents and index for installed packages. - - - - - 8add6435 by David Waern at 2008-11-16T14:35:50+00:00 Bump major version number due to .haddock file format change - - - - - 48bfcf82 by David Waern at 2008-11-23T14:32:52+00:00 Update tests to account for version number bump - - - - - 0bbd1738 by David Waern at 2008-11-23T14:33:31+00:00 HADDOCK_DATA_DIR changed to haddock_datadir - - - - - 5088b78c by David Waern at 2008-11-23T17:13:21+00:00 FIX haskell/haddock#45: generate two anchors for each name We generate two anchor tags for each name, one where we don't escape the name and one where we URI-encode it. This is for compatibility between IE and Opera. Test output is updated. - - - - - 5ee5ca3b by Neil Mitchell at 2008-11-27T14:38:11+00:00 Drop HsDocTy annotations, they mess up pretty printing and also have a bracketing bug (#2584) - - - - - 51c014e9 by Roman Cheplyaka at 2008-11-27T22:27:36+00:00 Allow referring to a specific section within a module in a module link Fixes haskell/haddock#65 - - - - - 4094bdc5 by David Waern at 2008-11-28T21:13:33+00:00 Update tests following anchor change - - - - - f89552dd by Thomas Schilling at 2008-11-29T16:16:20+00:00 Haddock really shouldn't try to overwrite files. - - - - - 98127499 by David Waern at 2008-12-07T14:09:15+00:00 Solve conflict - - - - - 319356c5 by David Waern at 2008-10-22T21:16:55+00:00 Add -Wall -Werror to ghc-options - - - - - 3c4968c9 by David Waern at 2008-11-04T23:38:56+00:00 TAG 2.4.0 - - - - - 4b21e003 by David Waern at 2008-11-06T21:14:04+00:00 TAG 2.4.1 - - - - - 8e0cad5c by David Waern at 2008-12-07T14:12:54+00:00 Remove -Werror - - - - - 299d6deb by David Waern at 2008-12-07T14:25:18+00:00 Remove -Wall, we'll focus on warnings after 6.10.2 is out - - - - - 5f4216b6 by David Waern at 2008-12-07T20:58:05+00:00 Resolve conflict properly - - - - - 67d774e7 by Neil Mitchell at 2008-12-15T11:44:26+00:00 Make forall's in constructors explicit, i.e. data Foo = Foo {foo :: Eq a => a} - - - - - 61851792 by Neil Mitchell at 2008-12-18T15:39:39+00:00 Try and find a better package name than "main" for Hoogle, goes wrong when working on an executable rather than a library - - - - - 2fab8554 by David Waern at 2008-12-08T23:19:48+00:00 Make visible names from ExportItems Instead of a complicated calculation of visible names out of GHC's export items, we can get them straight out of the already calculated ExportItems. The ExportItems should represent exactly those items that are visible in an interface. If store all the exported sub-names in ExportDecl instead of only those with documentation, the calculation becomes very simple. So we do this change as well (should perhaps have been a separate patch). This should fix the problem with names from ghc-prim not appearing in the link environment. - - - - - 7caadd8c by Ian Lynagh at 2008-12-11T17:01:04+00:00 Wrap the GHC usage with defaultCleanupHandler This fixes a bug where haddock leaves /tmp/ghc* directories uncleaned. - - - - - 7c9fc9a5 by David Waern at 2009-01-02T21:38:27+00:00 Show re-exported names from external packages again This fixes GHC ticket 2746. In order to also link to the exported subordinate names of a declaration, we need to re-introduce the sub map in the .haddock files. - - - - - 119e4e05 by David Waern at 2009-01-06T23:34:17+00:00 Do not process boot modules We should of course not try to produce documentation for boot modules! The reason this has worked in the past is that the output of "real" modules overwrites the output of boot modules later in the process. However, this causes a subtle link environment problem. So let's get rid of this stupid behaviour. We avoid processing boot modules, but we continue to typecheck them. - - - - - c285b9d2 by David Waern at 2009-01-08T18:03:36+00:00 Export modules also when coming from external packages This seems to have regressed since a refactoring that was part of the 2.3.0 release. - - - - - 24031c17 by David Waern at 2009-01-10T15:26:26+00:00 Change version to 2.4.2 - no need to go to 2.5.0 - - - - - 864d1c3f by David Waern at 2009-01-10T15:35:20+00:00 Update tests to account for version number change - - - - - 524ba886 by David Waern at 2009-01-10T18:29:17+00:00 Add test for Template Haskell splicing - - - - - 05e6e003 by David Waern at 2009-01-10T19:35:42+00:00 Fix Trac haskell/haddock#68: Turn on compilation via C for Template Haskell packages We can't use HscNothing if we need to run code coming from modules inside the processed package during typechecking, which is the case for some packages using Template Haskell. This could be improved, to e.g. use HscInterpreted and HscNothing where possible, instead of using HscC for all modules in the package. - - - - - 2b2bafa1 by David Waern at 2009-01-10T20:22:25+00:00 Only use needsTemplateHaskell when compiling with GHC 6.10.2 or above - - - - - bedc3a93 by Ian Lynagh at 2009-01-11T14:58:41+00:00 Fix the location of INPLACE_PKG_CONF; fixes the build Spotted by Conal Elliott - - - - - 943107c8 by David Waern at 2009-01-20T19:27:39+00:00 Document H.I.Create.collectDocs better - - - - - c6252e37 by David Waern at 2009-01-20T19:29:51+00:00 Fix Trac haskell/haddock#59: TH-generated declarations disappearing This patch was contributed by Joachim Breitner (nomeata). - - - - - 3568a6af by David Waern at 2009-01-21T21:41:48+00:00 Do not indicate that a constructor argument is unboxed We only show the strictness annotation for an unboxed constructor argument. The fact that it is unboxed is an implementation detail and should not be part of the module interface. - - - - - 562a4523 by David Waern at 2009-01-22T18:53:49+00:00 Fix Trac haskell/haddock#50: do not attach docs to pragmas or other kinds of non-declarations We now filter out everything that is not a proper Haskell declaration before collecting the docs and attaching them to declarations. - - - - - 6fdf21c2 by David Waern at 2009-01-22T19:48:09+00:00 Add test for quasi quotation. No reference output yet. - - - - - dc4100fd by David Waern at 2009-01-22T19:57:47+00:00 Improve quasi-quotation test and add reference output - - - - - 908b74bb by David Waern at 2009-01-23T23:22:03+00:00 Filter out separately exported associated types in a smarter way - - - - - f6b42ecb by David Waern at 2009-01-24T16:54:39+00:00 Correct spelling mistake in error message - - - - - 24e4245d by David Waern at 2009-01-24T17:48:03+00:00 Correct comment - - - - - b5e8462f by David Waern at 2009-02-07T13:22:29+00:00 Do not show a subordinate at the top level if its parent is also exported See note in the source code for more info. - - - - - 4b09de57 by David Waern at 2009-02-07T13:53:53+00:00 Update test following change to top level subordinates - - - - - 76379896 by David Waern at 2009-02-07T13:58:04+00:00 Remove html files in the tests/output/ directory which have been accidentally added - - - - - 1a6d8b10 by Joachim Breitner at 2009-02-20T10:29:43+00:00 Typo in comment - - - - - fec367d0 by David Waern at 2009-02-24T20:21:17+00:00 Fix small bug The rule is to prefer type constructors to other things when an identifier in a doc string can refer to multiple things. This stopped working with newer GHC versions (due to a tiny change in the GHC renamer). We implement this rule in the HTML backend for now, instead of fixing it in GHC, since we will move renaming of doc strings to Haddock in the future anyway. - - - - - 9b4172eb by David Waern at 2009-02-25T20:04:38+00:00 Fix bad error handling with newer GHCs When support for GHC 6.10 was added, an error handler was installed only around the typechecking phase. This had the effect that errors thrown during dependency chasing were caught in the top-level exception handler and not printed with enough detail. With this patch we wrap the error handler around all our usage of the Ghc monad. - - - - - de2df363 by Simon Peyton Jones at 2009-02-02T16:47:42+00:00 Hide funTyConName, now exported by TypeRep - - - - - 4d40a29f by Ian Lynagh at 2009-02-12T18:57:49+00:00 Don't build the library when building in the GHC tree - - - - - 1cd0abe4 by Ian Lynagh at 2009-02-13T13:58:53+00:00 Add a ghc.mk - - - - - 3d814eeb by Ian Lynagh at 2009-02-13T18:50:28+00:00 do .depend generation for haddock with the stage1 compiler This is a bit of a hack. We mkdepend with stage1 as if .depend depends on the stage2 compiler then make goes wrong: haddock's .depend gets included, which means that make won't reload until it's built, but we can't build it without the stage2 compiler. We therefore build the stage2 compiler before its .depend file is available, and so compilation fails. - - - - - b55036a4 by Ian Lynagh at 2009-02-25T01:38:13+00:00 Give haddock a wrapper on unix in the new GHC build system - - - - - 9eabfe68 by Ian Lynagh at 2009-02-25T19:21:32+00:00 Create inplace/lib/html in the new GHC build system - - - - - 93af30c7 by Ian Lynagh at 2008-11-07T19:18:23+00:00 TAG GHC 6.10.1 release - - - - - 06e6e34a by Thomas Schilling at 2009-02-24T18:11:00+00:00 Define __GHC_PATCHLEVEL__ for recent version of GHC (stable). - - - - - 680e6ed8 by Thomas Schilling at 2009-02-24T18:12:26+00:00 'needsTemplateHaskell' is not defined in current stable GHC. - - - - - 6c5619df by David Waern at 2009-02-25T22:15:23+00:00 Hide fynTyConName only for recent GHC versions - - - - - 6b2344f1 by Ian Lynagh at 2009-02-26T00:49:56+00:00 Add the module to one of haddocks warnings - - - - - e5d11c70 by David Waern at 2009-02-27T21:37:20+00:00 Bug fix We tried to filter out subordinates that were already exported through their parent. This didn't work properly since we were in some cases looking at the grand-parent and not the parent. We now properly compute all the parent-child relations of a declaration, and use this information to get the parent of a subordinate. We also didn't consider record fields with multiple parents. This is now handled correctly. We don't currently support separately exported associated types. But when we do, they should be handled correctly by this process too. Also slightly improved the warning message that we give when filtering out subordinates. - - - - - 10a79a60 by David Waern at 2009-02-27T22:08:08+00:00 Fix error message conflict The module name is already written in the beginning of the message, as seems to be the convention in Haddock. Perhaps not so clear, but we should change it everywhere in that case. Leaving it as it is for now. - - - - - c5055c7f by David Waern at 2009-02-27T22:15:17+00:00 Shorten warning message - - - - - a72fed3a by David Waern at 2009-02-28T00:53:55+00:00 Do not show package name in warning message - - - - - a5daccb2 by Ian Lynagh at 2009-03-01T14:59:35+00:00 Install haddock in the new GHC build system - - - - - dfdb025c by Ian Lynagh at 2009-03-07T23:56:29+00:00 Relax base dependency to < 4.2, not < 4.1 - - - - - 5769c8b4 by David Waern at 2009-03-21T14:58:52+00:00 Bump .haddock file version number (due to change of format) - - - - - f1b8f67b by David Waern at 2009-03-21T14:59:26+00:00 Define __GHC_PATCHLEVEL__=1 when using ghc-6.10.1 - - - - - 23f78831 by David Waern at 2009-03-21T16:40:52+00:00 Update CHANGES - - - - - 7d2735e9 by David Waern at 2009-03-21T16:50:33+00:00 Update ANNOUNCE - - - - - 0771e00a by David Waern at 2009-03-21T16:54:40+00:00 Update ANNOUNCE, again - - - - - 81a6942a by David Waern at 2009-03-21T17:50:06+00:00 Don't be too verbose in CHANGES - - - - - 29861dcf by David Waern at 2009-03-21T18:03:31+00:00 TAG 2.4.2 - - - - - a585f285 by David Waern at 2009-03-21T19:20:29+00:00 Require Cabal >= 1.2.3 - - - - - 7c611662 by David Waern at 2009-03-21T19:21:48+00:00 TAG 2.4.2 with cabal-version >= 1.2.3 - - - - - 23b7deff by Simon Marlow at 2009-03-20T15:43:42+00:00 new GHC build system: use shell-wrappers macro - - - - - 25f8afe7 by Ian Lynagh at 2009-03-21T19:13:53+00:00 Fix (with a hack?) haddock in teh new build system - - - - - 6a29a37e by David Waern at 2009-03-24T22:10:15+00:00 Remove unnecessary LANGUAGE pragma - - - - - 954da57d by David Waern at 2009-03-24T22:21:23+00:00 Fix warnings in H.B.DevHelp - - - - - 1619f1df by David Waern at 2009-03-26T23:20:44+00:00 -Wall police in H.B.Html - - - - - b211e13b by Simon Marlow at 2009-03-24T13:00:56+00:00 install Haddock's html stuff - - - - - 78e0b107 by David Waern at 2008-12-07T19:58:53+00:00 Add verbosity flag and utils, remove "verbose" flag - - - - - 913dae06 by David Waern at 2008-12-07T20:01:05+00:00 Add some basic "verbose" mode logging in H.Interface - - - - - 1cbff3bf by David Waern at 2009-03-27T00:07:26+00:00 Fix conflicts - - - - - 22f82032 by David Waern at 2009-03-27T21:15:11+00:00 Remove H.GHC.Typecheck - - - - - 81557804 by David Waern at 2009-03-27T21:19:22+00:00 Remove docNameOrig and use getName everywhere instead - - - - - d8267213 by David Waern at 2009-03-27T21:21:46+00:00 Use docNameOcc instead of nameOccName . getName - - - - - 5d55deab by David Waern at 2009-03-27T21:33:04+00:00 Remove H.DocName and put DocName in H.Types - - - - - 8ba72611 by David Waern at 2009-03-27T22:06:26+00:00 Document DocName - - - - - 605f8ca5 by David Waern at 2009-03-27T22:45:21+00:00 -Wall police - - - - - e4da93ae by David Waern at 2009-03-27T23:12:53+00:00 -Wall police in H.B.Hoogle - - - - - bb255519 by David Waern at 2009-03-27T23:41:28+00:00 Define Foldable and Traversable instances for Located - - - - - f1195cfe by David Waern at 2009-03-27T23:51:34+00:00 Wibble - - - - - 23818d7c by David Waern at 2009-03-28T00:03:55+00:00 -Wall police in H.I.Rename - - - - - 0f050d67 by David Waern at 2009-03-28T00:15:15+00:00 -Wall police in H.I.AttachInstances - - - - - 0f3fe038 by David Waern at 2009-03-28T21:09:41+00:00 Wibble - - - - - 275d4865 by David Waern at 2009-03-28T21:27:06+00:00 Layout fix - - - - - 54ff0ef8 by David Waern at 2009-03-28T21:59:07+00:00 -Wall police in H.I.Create - - - - - 7f58b117 by David Waern at 2009-03-28T22:10:19+00:00 -Wall police in H.Interface - - - - - f0c03b44 by David Waern at 2009-03-28T22:22:59+00:00 -Wall police in Main - - - - - 29da355c by David Waern at 2009-03-28T22:23:39+00:00 Turn on -Wall -Werror - - - - - 446d3060 by David Waern at 2009-04-01T20:40:30+00:00 hlint police - - - - - 3867c9fc by David Waern at 2009-04-01T20:48:42+00:00 hlint police - - - - - bd1f1600 by David Waern at 2009-04-01T20:58:02+00:00 hlint police - - - - - e0e90866 by David Waern at 2009-04-05T12:42:53+00:00 Move H.GHC.Utils to H.GhcUtils - - - - - 9cbd426b by David Waern at 2009-04-05T12:57:21+00:00 Remove Haddock.GHC and move its (small) contents to Main - - - - - b5c2cbfd by David Waern at 2009-04-05T13:07:04+00:00 Fix whitespace and stylistic issues in Main - - - - - 3c04aa56 by porges at 2008-12-07T08:22:19+00:00 add unicode output - - - - - 607918da by David Waern at 2009-04-26T15:09:43+00:00 Resolve conflict - - - - - 4bec6b6b by Simon Marlow at 2009-05-13T10:00:31+00:00 fix markup - - - - - 436ad6f4 by Simon Marlow at 2009-03-23T11:54:45+00:00 clean up - - - - - bdcd1398 by Simon Marlow at 2009-03-24T10:36:45+00:00 new GHC build system: add $(exeext) - - - - - 9c0972f3 by Simon Marlow at 2009-03-24T11:04:31+00:00 update for new GHC build system layout - - - - - d0f3f83a by Ian Lynagh at 2009-03-29T15:31:43+00:00 GHC new build system fixes - - - - - 5a8245c2 by Ian Lynagh at 2009-04-04T20:44:23+00:00 Tweak new build system - - - - - 9c6f2d7b by Simon Marlow at 2009-05-13T10:01:27+00:00 add build instructions for GHC - - - - - 66d07c76 by Ian Lynagh at 2009-05-31T00:37:53+00:00 Quote program paths in ghc.mk - - - - - bb7de2cd by Ian Lynagh at 2009-06-03T22:57:55+00:00 Use a bang pattern on an unlifted binding - - - - - 3ad283fc by Ian Lynagh at 2009-06-13T16:17:50+00:00 Include haddock in GHC bindists - - - - - ac447ff4 by David Waern at 2009-06-24T21:07:50+00:00 Delete Haddock.Exception and move contents to Haddock.Types Only a few lines of code that mainly declares a type - why not just put it in Haddock.Types. - - - - - 4464fb9b by David Waern at 2009-06-24T22:23:23+00:00 Add Haddock module headers Add a proper Haddock module header to each module, with a more finegrained copyright. If you feel mis-accreditted, please correct any copyright notice! The maintainer field is set to haddock at projects.haskell.org. Next step is to add a brief description to each module. - - - - - 5f4c95dd by David Waern at 2009-06-24T22:39:44+00:00 Fix spelling error - - - - - 6d074cdb by David Waern at 2009-06-25T21:53:56+00:00 Document Interface and InstalledInterface better - - - - - d0cbd183 by David Waern at 2009-06-27T12:46:46+00:00 Remove misplaced whitespace in H.I.Rename - - - - - fa381c49 by David Waern at 2009-06-27T13:26:03+00:00 Fix haskell/haddock#104 - create output directory if missing - - - - - 91fb77ae by Ian Lynagh at 2009-06-25T15:59:50+00:00 TAG 2009-06-25 - - - - - 0d853f40 by Simon Peyton Jones at 2009-07-02T15:35:22+00:00 Follow extra field in ConDecl - - - - - b201735d by Ian Lynagh at 2009-07-05T16:50:35+00:00 Update Makefile for the new GHC build system - - - - - df6c0092 by Ian Lynagh at 2009-07-05T17:01:13+00:00 Resolve conflicts - - - - - 1066870a by Ian Lynagh at 2009-07-05T17:01:48+00:00 Remove the -Wwarn hack in the GHC build system - - - - - 7e856076 by Ian Lynagh at 2009-07-05T17:17:59+00:00 Fix warnings - - - - - 5d4cd958 by Ian Lynagh at 2009-07-05T19:35:40+00:00 Bump version number Cabal needs to distinguish between haddocks having a --verbose and --verbosity flag - - - - - 6ee07c99 by David Waern at 2009-07-06T20:14:57+00:00 Wibble - - - - - 2308b66f by David Waern at 2009-07-06T20:24:20+00:00 Clearer printing of versions by runtests.hs - - - - - d4b5d9ab by David Waern at 2009-07-06T21:22:42+00:00 Fix (invisible) bug introduced by unicode patch - - - - - 2caca8d8 by David Waern at 2009-07-06T21:44:10+00:00 Use HscAsm instead of HscC when using TH - - - - - 18f3b755 by David Waern at 2009-07-06T22:10:22+00:00 Update HCAR entry (by Janis) - - - - - a72ac9db by David Waern at 2009-07-06T23:01:35+00:00 Follow HsRecTy change with an #if __GLASGOW_HASKEL__ >= 611 - - - - - 549135d2 by David Waern at 2009-07-06T23:11:41+00:00 Remove unused functions from Haddock.Utils - - - - - b450134a by Isaac Dupree at 2009-07-11T14:59:00+00:00 revert to split-index for large indices - remove the search-box, because browsers have search-for-text abilities anyway. - pick 150 items in index as the arbitrary time at which to split it - notice the bug that identifiers starting with non-ASCII characters won't be listed in split-index, but don't bother to fix it yet (see ticket haskell/haddock#116, http://trac.haskell.org/haddock/ticket/116 ) - - - - - 78a5661e by Isaac Dupree at 2009-07-20T15:37:18+00:00 Implement GADT records in HTML backend - - - - - 4e163555 by Isaac Dupree at 2009-07-21T22:03:25+00:00 add test for GADT records - - - - - 79aa4d6e by David Waern at 2009-07-23T20:40:37+00:00 Update test suite following version bump - - - - - 5932c011 by David Waern at 2009-08-02T10:25:39+00:00 Fix documentation bug - - - - - a6970fca by David Waern at 2009-08-12T23:08:53+00:00 Remove support for ghc 6.8.* from .cabal file - - - - - c1695902 by Ian Lynagh at 2009-07-07T13:35:45+00:00 Fix unused import warnings - - - - - fb6df7f9 by Ian Lynagh at 2009-07-16T00:20:31+00:00 Use cProjectVersion directly rather than going through compilerInfo Fixes the build after changes in GHC - - - - - 548cdd66 by Simon Marlow at 2009-07-28T14:27:04+00:00 follow changes in GHC's ForeignType - - - - - 9395aaa0 by David Waern at 2009-08-13T22:17:33+00:00 Switch from PatternSignatures to ScopedTypeVariables in Main - - - - - eebf39bd by David Waern at 2009-08-14T17:14:28+00:00 Version .haddock files made with GHC 6.10.3/4 correclty - - - - - 58f3e735 by David Waern at 2009-08-14T17:19:37+00:00 Support GHC 6.10.* and 6.11.* only - - - - - 5f63cecc by David Waern at 2009-08-14T22:03:20+00:00 Do not version .haddock file based on GHC patchlevel version We require that the instances of Binary that we use from GHC will not change between patchlevel versions. - - - - - d519de9f by David Waern at 2009-08-14T23:50:00+00:00 Update CHANGES - - - - - 35dccf5c by David Waern at 2009-08-14T23:51:38+00:00 Update version number everywhere - - - - - 6d363fea by David Waern at 2009-08-15T09:46:49+00:00 Update ANNOUNCE - - - - - c7ee6bc2 by David Waern at 2009-08-15T09:47:13+00:00 Remove -Werror Forgot that Hackage doesn't like it. - - - - - a125c12b by David Waern at 2009-08-15T09:49:50+00:00 Require Cabal >= 1.6 - - - - - adb2f560 by Isaac Dupree at 2009-08-12T03:47:14+00:00 Cross-Package Documentation version 4 - - - - - 3d6dc04d by David Waern at 2009-08-15T23:42:57+00:00 Put all the IN_GHC_TREE stuff inside getGhcLibDir - - - - - 56624097 by David Waern at 2009-08-15T23:52:03+00:00 Add --print-ghc-libdir - - - - - f15d3ccb by David Waern at 2009-08-16T00:37:52+00:00 Read base.haddock when running tests We can now test cross-package docs. - - - - - 283f0fb9 by David Waern at 2009-08-16T00:50:59+00:00 Update test output - we now have more links - - - - - 673d1004 by David Waern at 2009-08-16T01:26:08+00:00 Read process.haddock when running tests - - - - - 0d127f82 by David Waern at 2009-08-16T01:43:04+00:00 Add a test for cross-package documentation - - - - - f94db967 by Ian Lynagh at 2009-08-16T18:42:44+00:00 Follow GHC build system changes - - - - - 5151278a by Isaac Dupree at 2009-08-16T19:58:05+00:00 make cross-package list types look nicer - - - - - c41e8228 by Isaac Dupree at 2009-08-18T01:47:47+00:00 Haddock.Convert: export more functions This lets us remove some code in Haddock.Interface.AttachInstances - - - - - 2e5fa398 by Isaac Dupree at 2009-08-18T02:11:05+00:00 switch AttachInstances to use synify code It changed an instance from showing ((,) a b) to (a, b) because my synify code is more sophisticated; I hope the latter is a good thing rather than a bad thing aesthetically, here. But this definitely reduces code duplication! - - - - - b8b07123 by Isaac Dupree at 2009-08-18T02:23:31+00:00 Find instances using GHC, which is more complete. In particular, it works cross-package. An intermediate patch also moved the instance-finding into createInterface, but that move turned out not to be necessary, so if we want to do that, it'd go in a separate patch. (Is that possible? Or will we need GHC to have loaded all the modules first, before we can go searching for the instances (e.g. if the modules are recursive or something)?) - - - - - 6959b451 by Isaac Dupree at 2009-08-17T00:37:18+00:00 fix preprocessor conditional sense - - - - - 942823af by Isaac Dupree at 2009-08-16T22:46:48+00:00 remove ghc 6.8 conditionals from Haddock.Interface - - - - - 4b3ad888 by Isaac Dupree at 2009-08-18T20:24:38+00:00 Fix GHC 6.11 build in Haddock.Convert - - - - - 0a89c5ab by Isaac Dupree at 2009-08-23T00:08:58+00:00 hacks to make it compile without fnArgDocsn - - - - - 7b3bed43 by Isaac Dupree at 2009-08-23T03:01:28+00:00 less big-Map-based proper extraction of constructor subdocs - - - - - b21c279a by Isaac Dupree at 2009-08-23T03:02:06+00:00 Html: remove unnecessary+troublesome GHC. qualifications - - - - - 96c97115 by Isaac Dupree at 2009-08-23T03:08:03+00:00 Move doc parsing/lexing into Haddock for ghc>=6.11 - - - - - e1cec02d by Isaac Dupree at 2009-08-23T05:08:14+00:00 get rid of unused DocMap parameter in Html - - - - - 66960c59 by Isaac Dupree at 2009-08-23T05:54:20+00:00 fix horrible named-docs-disappearing bug :-) - - - - - a9d7eff3 by Isaac Dupree at 2009-08-23T06:26:36+00:00 re-implement function-argument docs ..on top of the lexParseRn work. This patch doesn't change the InstalledInterface format, and thus, it does not work cross-package, but that will be easy to add subsequently. - - - - - 8bf6852c by Isaac Dupree at 2009-08-23T07:26:05+00:00 cross-package fnArgDocs. WARNING: changes .haddock binary format While breaking the format, I took the opportunity to unrename the DocMap that's saved to disk, because there's really no reason that we want to know what *another* package's favorite place to link a Name to was. (Is that true? Or might we want to know, someday?) Also, I added instance Binary Map in InterfaceFile. It makes the code a little simpler without changing anything of substance. Also it lets us add another Map hidden inside another Map (fnArgsDocs in instDocMap) without having really-convoluted serialization code. Instances are neat! I don't understand why this change to InterfaceFile seemed to subtly break binary compatibility all by itself, but no matter, I'll just roll it into the greater format-changing patch. Done! - - - - - 30115a64 by Isaac Dupree at 2009-08-23T18:22:47+00:00 Improve behavior for unfindable .haddock - - - - - aa364bda by Isaac Dupree at 2009-08-23T18:28:16+00:00 add comment for FnArgsDoc type - - - - - 49b23a99 by Isaac Dupree at 2009-08-23T21:52:48+00:00 bugfix: restore fnArgDocs for type-synonyms - - - - - f65f9467 by Isaac Dupree at 2009-08-23T22:06:55+00:00 Backends.Hoogle: eliminate warnings - - - - - a292d216 by Isaac Dupree at 2009-08-23T22:10:24+00:00 Haddock.Convert: eliminate warnings - - - - - 5546cd20 by Isaac Dupree at 2009-08-23T22:12:31+00:00 Haddock.Interface.Rename: eliminate warnings - - - - - 0a9798b6 by Isaac Dupree at 2009-08-23T22:18:47+00:00 Main.hs: remove ghc<6.9 conditionals - - - - - e8f9867f by Isaac Dupree at 2009-08-23T22:27:46+00:00 Main.hs: eliminate warnings (except for OldException) - - - - - 61c64247 by Isaac Dupree at 2009-08-23T22:41:01+00:00 move get*LibDir code in Main.hs, to +consistent code, -duplication - - - - - 948f1e69 by Isaac Dupree at 2009-08-23T23:14:26+00:00 Main.hs: OldException->Exception: which eliminates warnings - - - - - 3d5d5e03 by Isaac Dupree at 2009-08-23T23:20:11+00:00 GhcUtils: ghc >= 6.10 - - - - - 2771d657 by Isaac Dupree at 2009-08-23T23:21:55+00:00 InterfaceFile: ghc >= 6.10 - - - - - d9f2b9d1 by Isaac Dupree at 2009-08-23T23:22:58+00:00 Types: ghc >= 6.10 - - - - - ca39210e by Isaac Dupree at 2009-08-23T23:23:26+00:00 ModuleTree: ghc >= 6.10 - - - - - 883c4e59 by Isaac Dupree at 2009-08-23T23:24:04+00:00 Backends.DevHelp: ghc >= 6.10 - - - - - 04667df5 by Isaac Dupree at 2009-08-23T23:24:37+00:00 Backends.Html: ghc >= 6.10 - - - - - a9f7f25f by Isaac Dupree at 2009-08-23T23:25:24+00:00 Utils: ghc >= 6.10 - - - - - b7105022 by Isaac Dupree at 2009-08-23T23:37:47+00:00 eliminate haskell98 dependency, following GHC's example It turns out I/we already had, and it was only a matter of deleting it from the cabal file. - - - - - 292e0911 by Isaac Dupree at 2009-08-24T01:22:44+00:00 refactor out subordinatesWithNoDocs dep of inferenced-decls fix - - - - - c2ed46a2 by Isaac Dupree at 2009-08-24T01:24:03+00:00 Eradicate wrong runtime warning for type-inferenced exported-functions see the long comment in the patch for why I did it this way :-) - - - - - 4ac0b57c by David Waern at 2009-09-04T22:56:20+00:00 Clean up tyThingToHsSynSig a little Factor out noLoc and use the case construct. Also rename the function to tyThingToLHsDecl, since it doesn't just create type signatures. - - - - - 28ab9201 by David Waern at 2009-09-04T22:58:50+00:00 Wibble - - - - - 0d9fe6d0 by David Waern at 2009-09-06T18:39:30+00:00 Add more copyright owners to H.I.AttachInstances - - - - - 122441b1 by David Waern at 2009-09-06T18:44:12+00:00 Style police - - - - - 1fa79463 by David Waern at 2009-09-06T18:57:45+00:00 Move toHsInstHead to Haddock.Convert and call it synifyInstHead - - - - - 0d42a8aa by David Waern at 2009-09-06T21:11:38+00:00 Use colordiff to display test results if available - - - - - ea9d8e03 by Simon Marlow at 2009-08-24T08:46:14+00:00 Follow changes in GHC's interface file format Word32 instead of Int for FastString and Name offsets - - - - - 537e051e by Simon Marlow at 2009-07-29T14:16:53+00:00 define unpackPackageId (it was removed from GHC) - - - - - 50c63aa7 by David Waern at 2009-09-09T23:18:03+00:00 Remove commented-out code - - - - - 511631fe by David Waern at 2009-09-09T23:19:05+00:00 Correct copyright in H.I.ParseModuleHeader - - - - - 898ec768 by David Waern at 2009-09-11T11:22:29+00:00 Use Map.fromList/toList intead of fromAscList/toAscList when serializing Maps This fixes the missing docs problem. The Eq and Ord instances for Name uses the unique number in Name. This number is created at deserialization time by GHC's magic Binary instance for Name, and it is random. Thus, fromAscList can't be used at deserialization time, even though toAscList was used at serialization time. - - - - - 37bec0d5 by Simon Peyton Jones at 2009-09-11T08:28:04+00:00 Track change in HsType - - - - - eb3a97c3 by Ian Lynagh at 2009-09-11T16:07:09+00:00 Allow building with base 4.2 - - - - - bb4205ed by Ian Lynagh at 2009-09-22T13:50:02+00:00 Loosen the GHC dependency - - - - - 5c75deb2 by Ian Lynagh at 2009-09-22T14:08:39+00:00 Fix building with GHC >= 6.12 - - - - - fb131481 by David Waern at 2009-09-11T11:24:48+00:00 Update runtests.hs to work with GHC 6.11 - - - - - ac3a419d by David Waern at 2009-09-11T11:25:14+00:00 Update CrossPackageDocs test - - - - - ec65c3c6 by David Waern at 2009-09-11T11:25:40+00:00 Add reference output for CrossPackageDocs - - - - - 520c2758 by Ian Lynagh at 2009-10-25T17:26:40+00:00 Fix installation in the GHC build system - - - - - 28b3d7df by Ian Lynagh at 2009-11-05T15:57:27+00:00 GHC build system: Make *nix installation work in paths containing spaces - - - - - 5c9bb541 by David Waern at 2009-11-14T11:56:39+00:00 Track change in HsType for the right compiler version - - - - - 905097ce by David Waern at 2009-11-14T12:10:47+00:00 hlint police - - - - - 04920630 by Ian Lynagh at 2009-11-20T13:46:30+00:00 Use defaultObjectTarget rather than HscAsm This fixes haddock when we don't have a native code generator - - - - - 966eb079 by David Waern at 2009-11-15T12:32:21+00:00 Remove commented-out code - - - - - 37f00fc4 by David Waern at 2009-11-22T13:58:48+00:00 Make runtests.hs strip links before diffing Generates easier to read diffs when tests fail. The content of the links is not important anyway since it is not taken into account by the tests. - - - - - 3a9bb8ef by David Waern at 2009-11-22T14:05:06+00:00 Follow findProgramOnPath signature change in runtests.hs - - - - - b26b9e5a by David Waern at 2009-11-22T14:08:40+00:00 Follow removal of GHC.MVar from base in CrossPackageDocs - - - - - f4d90ae4 by David Waern at 2009-11-22T14:48:47+00:00 Make copy.hs strip link contents before copying No more updating of reference files when URLs in links changes. - - - - - 4c9c420d by David Waern at 2009-11-22T15:26:41+00:00 Update test reference output * More links (Int, Float etc) * Stripped link contents - - - - - a62b80e3 by David Waern at 2009-11-23T23:19:39+00:00 Update CrossPackageDocs reference output - Remove GHC.MVar import (removed from base) - Strip link contents - - - - - 43491394 by David Waern at 2009-11-23T23:20:00+00:00 Update test reference files with comments on instances - - - - - 0d370a0b by David Waern at 2009-11-23T23:25:16+00:00 Bump version number - - - - - 2293113e by David Waern at 2009-11-24T20:55:49+00:00 Comments on instances Implementing this was a little trickier than I thought, since we need to match up instances from the renamed syntax with instances represented by InstEnv.Instance. This is due to the current design of Haddock, which matches comments with declarations from the renamed syntax, while getting the list of instances of a class/family directly using the GHC API. - Works for class instances only (Haddock has no support for type family instances yet) - The comments are rendered to the right of the instance head in the HTML output - No change to the .haddock file format - Works for normal user-written instances only. No comments are added on derived or TH-generated instances - - - - - bf586f29 by David Waern at 2009-11-27T22:05:15+00:00 Whitespace police - - - - - b8f03afa by David Waern at 2009-11-27T22:11:46+00:00 Remove bad whitespace and commented-out pieces - - - - - 90b8ee90 by David Waern at 2009-11-27T22:15:04+00:00 Whitespace police - - - - - b5ede900 by David Waern at 2009-11-27T22:15:50+00:00 Whitespace police - - - - - e3fddbfe by David Waern at 2009-11-28T13:37:59+00:00 Remove Name from DocInstance It's not used. - - - - - 9502786c by David Waern at 2009-11-28T13:56:54+00:00 Require at least GHC 6.12 While regression testing Haddock, I found a bug that happens with GHC 6.10.3, but not with GHC 6.12-rc2 (haven't tried 6.10.4). I don't have time to track it down. I think we should just always require the latest major GHC version. The time spent on making Haddock work with older versions is too high compared to the time spent on bugfixing, refactoring and features. - - - - - 8fa688d8 by David Waern at 2009-11-28T15:05:03+00:00 Remove cruft due to compatibility with older GHCs - - - - - 46fbbe9d by David Waern at 2009-11-28T15:07:50+00:00 Add a documentation header to Haddock.Convert - - - - - c3d2cc4a by David Waern at 2009-11-28T15:10:14+00:00 Remove unused H.Utils.FastMutInt2 - - - - - 490aba80 by David Waern at 2009-11-28T15:36:36+00:00 Rename Distribution.Haddock into Documentation.Haddock - - - - - 33ee2397 by David Waern at 2009-11-28T15:36:47+00:00 Fix error message - - - - - a5a3b950 by David Waern at 2009-11-28T16:58:39+00:00 Add a test flag that brings in QuickCheck - - - - - fa049e13 by David Waern at 2009-11-28T19:32:18+00:00 Say that we want quickcheck 2 - - - - - f32b0d9b by David Waern at 2009-11-28T19:32:40+00:00 Add an Arbitrary instance for HsDoc - - - - - da9a8bd7 by David Waern at 2009-11-28T20:15:30+00:00 Rename HsDoc back into Doc - - - - - edb60101 by David Waern at 2009-11-28T22:16:16+00:00 Move H.Interface.Parse/Lex to H.Parse/Lex These are not just used to build Interfaces. - - - - - 0656a9b8 by David Waern at 2009-11-28T23:12:14+00:00 Update version number in test suite - - - - - 5e8c6f4a by David Waern at 2009-12-21T14:12:41+00:00 Improve doc of DocName - - - - - 7868e551 by Ian Lynagh at 2009-09-22T10:43:03+00:00 TAG GHC 6.12-branch created - - - - - 0452a3ea by Ian Lynagh at 2009-12-15T12:46:07+00:00 TAG GHC 6.12.1 release - - - - - 65e9be62 by David Waern at 2009-12-21T16:58:58+00:00 Update CHANGES - - - - - 145cee32 by David Waern at 2009-12-21T16:59:09+00:00 TAG 2.6.0 - - - - - 3c552008 by David Waern at 2009-12-22T17:11:14+00:00 Update ANNOUNCE - - - - - 931f9db4 by David Waern at 2010-01-22T19:57:17+00:00 Convert haddock.vim to use unix newlines - - - - - 4e56588f by David Waern at 2010-01-22T22:11:17+00:00 Remove unnecessary (and inexplicable) uses of nub - - - - - 744bb4d1 by David Waern at 2010-01-22T22:12:14+00:00 Follow move of parser and lexer - - - - - e34bab14 by David Waern at 2010-01-22T22:49:13+00:00 Use findProgramLocation instead of findProgramOnPath in runtests.hs - - - - - 8d39891b by Isaac Dupree at 2010-01-14T18:53:18+00:00 fix html arg-doc off-by-one and silliness - - - - - 9401f2e9 by David Waern at 2010-01-22T22:57:03+00:00 Create a test for function argument docs - - - - - 507a82d7 by David Waern at 2010-01-22T23:24:47+00:00 Put parenthesis around type signature arguments of function type - - - - - 8a305c28 by David Waern at 2010-01-23T17:26:59+00:00 Add reference file for the FunArgs test - - - - - 1309d5e1 by David Waern at 2010-01-24T16:05:08+00:00 Improve FunArg test and update Test.html.ref - - - - - 2990f055 by Yitzchak Gale at 2010-02-14T16:03:46+00:00 Do not generate illegal character in HTML ID attribute. - - - - - c5bcab7a by David Waern at 2010-02-22T22:10:30+00:00 Fix Haddock markup error in comment - - - - - c6416a73 by David Waern at 2010-02-24T22:55:08+00:00 Large additions to the Haddock API Also improved and added more doc comments. - - - - - 57d289d7 by David Waern at 2010-02-24T22:58:02+00:00 Remove unused ifaceLocals - - - - - 80528d93 by David Waern at 2010-02-25T21:05:09+00:00 Add HaddockModInfo to the API - - - - - 82806848 by David Waern at 2010-02-25T21:05:27+00:00 Wibble - - - - - 744cad4c by David Waern at 2010-02-25T23:30:59+00:00 Make it possible to run a single test - - - - - 6a806e4c by David Waern at 2010-03-14T14:19:39+00:00 Bump version number - - - - - a5a8e4a7 by David Waern at 2010-03-14T14:36:35+00:00 Update ANNOUNCE - - - - - 6f05435e by Simon Hengel at 2010-03-15T20:52:42+00:00 Add missing dependencies for 'library' in haddock.cabal - - - - - faefe2bd by David Waern at 2010-03-15T22:29:37+00:00 Solve conflicts - - - - - 9808ad52 by David Waern at 2010-03-15T22:51:21+00:00 Bump version number - - - - - eb0bf60b by David Waern at 2010-03-15T22:52:32+00:00 Update CHANGES - - - - - f95cd891 by David Waern at 2010-03-15T23:01:06+00:00 Add Paths_haddock to other-modules of library - - - - - 65997b0a by David Waern at 2010-03-15T23:14:59+00:00 Update CHANGES - - - - - 7e251731 by David Waern at 2010-03-15T23:15:30+00:00 Bump version number - - - - - c9cd0ddc by David Waern at 2010-03-16T00:28:34+00:00 Fix warning - - - - - 1cac2d93 by Simon Peyton Jones at 2010-01-04T15:22:16+00:00 Fix imports for new location of splitKindFunTys - - - - - 474f26f6 by Simon Peyton Jones at 2010-02-10T14:36:06+00:00 Update Haddock for quasiquotes - - - - - 0dcc06c0 by Simon Peyton Jones at 2010-02-10T10:59:45+00:00 Track changes in HsTyVarBndr - - - - - 2d84733a by Simon Peyton Jones at 2010-02-10T14:52:44+00:00 Track HsSyn chnages - - - - - 9e3adb8b by Ian Lynagh at 2010-02-20T17:09:42+00:00 Resolve conflicts - - - - - a3e72ff8 by Simon Peyton Jones at 2010-03-04T13:05:16+00:00 Track change in HsUtils; and use a nicer function not an internal one - - - - - 27994854 by David Waern at 2010-03-18T22:22:27+00:00 Fix build with GHC 6.12.1 - - - - - 11f6e488 by David Waern at 2010-03-18T22:24:09+00:00 Bump version in test reference files - - - - - 0ef2f11b by David Waern at 2010-03-20T00:56:30+00:00 Fix library part of cabal file when in ghc tree - - - - - 3f6146ff by Mark Lentczner at 2010-03-20T22:30:11+00:00 First, experimental XHTML rendering switch to using the xhtml package copied Html.hs to Xhtml.hs and split into sub-modules under Haddock/Backends/Xhtml and detabify moved footer into div, got ready for iface change headers converted to semantic markup contents in semantic markup summary as semantic markup description in semantic markup, info block in header fixed factored out rendering so during debug it can be readable (see renderToString) - - - - - b8ab329b by Mark Lentczner at 2010-03-20T22:54:01+00:00 apply changes to Html.hs to Xhtml/*.hs incorporate changes that were made between the time Html.hs was copied and split into Xhtml.hs and Xhtml/*.hs includes patchs after "Wibble" (!) through "Fix build with GHC 6.12.1" - - - - - 73df2433 by Ian Lynagh at 2010-03-20T21:56:37+00:00 Follow LazyUniqFM->UniqFM in GHC - - - - - db4f602b by David Waern at 2010-03-29T22:00:01+00:00 Fix build with GHC 6.12 - - - - - d8dca088 by Simon Hengel at 2010-04-02T16:39:55+00:00 Add missing dependencies to cabal file - - - - - e2adc437 by Simon Hengel at 2010-04-02T14:08:40+00:00 Add markup support for interactive examples - - - - - e882ac05 by Simon Hengel at 2010-04-02T14:11:53+00:00 Add tests for interactive examples - - - - - 5a07a6d3 by David Waern at 2010-04-07T17:05:20+00:00 Propagate source positions from Lex.x to Parse.y - - - - - 6493b46f by David Waern at 2010-04-07T21:48:57+00:00 Let runtests.hs die when haddock has not been built - - - - - 5e34423e by David Waern at 2010-04-07T22:01:13+00:00 Make runtests.hs slightly more readable - - - - - 321d59b3 by David Waern at 2010-04-07T22:13:27+00:00 Fix haskell/haddock#75 Add colons to the $ident character set. - - - - - 37b08b8d by David Waern at 2010-04-08T00:32:52+00:00 Fix haskell/haddock#118 Avoid being too greedy when lexing URL markup (<..>), in order to allow multiple URLs on the same line. Do the same thing with <<..>> and #..#. - - - - - df8feac9 by David Waern at 2010-04-08T00:57:33+00:00 Make it easier to add new package deps to test suite This is a hack - we should use Cabal to get the package details instead. - - - - - 1ca6f84b by David Waern at 2010-04-08T01:03:06+00:00 Add ghc-prim to test suite deps - - - - - 27371e3a by Simon Hengel at 2010-04-08T19:26:34+00:00 Let parsing fails on paragraphs that are immediately followed by an example This is more consistent with the way we treat code blocks. - - - - - 83096e4a by David Waern at 2010-04-08T21:20:00+00:00 Improve function name - - - - - 439983ce by David Waern at 2010-04-10T10:46:14+00:00 Fix haskell/haddock#112 No link was generated for 'Addr#' in a doc comment. The reason was simply that the identifier didn't parse. We were using parseIdentifier from the GHC API, with a parser state built from 'defaultDynFlags'. If we pass the dynflags of the module instead, the right options are turned on on while parsing the identifer (in this case -XMagicHash), and the parse succeeds. - - - - - 5c0d35d7 by David Waern at 2010-04-10T10:54:06+00:00 Rename startGhc into withGhc - - - - - dca081fa by Simon Hengel at 2010-04-12T19:09:16+00:00 Add documentation for interactive examples - - - - - c7f26bfa by David Waern at 2010-04-13T00:51:51+00:00 Slight fix to the documentation of examples - - - - - 06eb7c4c by David Waern at 2010-04-13T00:57:05+00:00 Rename Interactive Examples into Examples (and simplify explanation) - - - - - 264830cb by David Waern at 2010-05-10T20:07:27+00:00 Update CHANGES with info about 2.6.1 - - - - - 8e5d4514 by Simon Hengel at 2010-04-18T18:16:54+00:00 Add unit tests for parser - - - - - 68297f40 by David Waern at 2010-05-10T21:53:37+00:00 Improve testsuite README - - - - - f04eb6e4 by David Waern at 2010-05-11T19:14:31+00:00 Re-organise the testsuite structure - - - - - a360f710 by David Waern at 2010-05-11T19:18:03+00:00 Shorten function name - - - - - 1d5dd359 by David Waern at 2010-05-11T21:40:02+00:00 Update runtests.hs following testsuite re-organisation - - - - - ffebe217 by David Waern at 2010-05-11T21:40:10+00:00 Update runtests.hs to use base-4.2.0.1 - - - - - 635de402 by David Waern at 2010-05-11T21:41:11+00:00 Update runparsetests.hs following testsuite reorganisation - - - - - 72137910 by Ian Lynagh at 2010-05-06T20:43:06+00:00 Fix build - - - - - 1a80b76e by Ian Lynagh at 2010-05-06T22:25:29+00:00 Remove redundant import - - - - - 1031a80c by Simon Peyton Jones at 2010-05-07T13:21:09+00:00 Minor wibbles to HsBang stuff - - - - - dd8e7fe5 by Ian Lynagh at 2010-05-08T15:22:00+00:00 GHC build system: Follow "rm" variable changes - - - - - 7f5e6748 by David Waern at 2010-05-13T11:53:02+00:00 Fix build with GHC 6.12.2 - - - - - 7953d4d8 by David Waern at 2010-05-13T18:45:01+00:00 Fixes to comments only - - - - - 8ae8eb64 by David Waern at 2010-05-13T18:57:26+00:00 ModuleMap -> IfaceMap - - - - - 1c3eadc6 by David Waern at 2010-05-13T19:03:13+00:00 Fix whitespace style issues - - - - - e96783c0 by David Waern at 2010-05-13T19:08:53+00:00 Fix comment - - - - - c998a78b by David Waern at 2010-05-13T19:39:00+00:00 Position the module header the same way everywhere Silly, but nice with some consistency :-) - - - - - b48a714e by David Waern at 2010-05-13T19:41:32+00:00 Position of module header, this time in the HTML backends - - - - - f9bfb12e by David Waern at 2010-05-13T19:43:05+00:00 Two newlines between declarations in Main - - - - - 071d44c7 by David Waern at 2010-05-13T19:44:21+00:00 Newlines in Convert - - - - - 036346db by David Waern at 2010-05-13T19:46:47+00:00 Fix a few stylistic issues in H.InterfaceFile - - - - - f0b8379e by David Waern at 2010-05-13T19:47:53+00:00 Add newlines to H.ModuleTree - - - - - 27409f8e by David Waern at 2010-05-13T19:51:10+00:00 Fix stylistic issues in H.Utils - - - - - 24774a11 by David Waern at 2010-05-13T20:00:43+00:00 Structure H.Types better - - - - - 7b6f5e40 by David Waern at 2010-05-13T20:01:04+00:00 Remove bad Arbitrary instance - - - - - fac9f1f6 by David Waern at 2010-05-13T20:05:50+00:00 Get rid of H.Utils.pathJoin and use System.FilePath.joinPath instead - - - - - fe6d00c4 by David Waern at 2010-05-13T20:51:55+00:00 Export a couple of more types from the API - - - - - b2e33a5f by David Waern at 2010-05-13T21:27:51+00:00 Improve doc comment for Interface - - - - - c585f2ce by David Waern at 2010-05-13T21:30:14+00:00 Improve documentation of Haddock.Interface - - - - - e6791db2 by David Waern at 2010-05-13T22:07:35+00:00 Remove meaningless comments - - - - - 7801b390 by David Waern at 2010-05-14T17:53:33+00:00 Remove unused modules - - - - - f813e937 by David Waern at 2010-05-14T17:55:17+00:00 Re-direct compilation output to a temporary directory Also add a flag --no-tmp-comp-dir that can be used to get the old behaviour of writing compilation files to GHC's output directory (default "."). - - - - - e56737ec by David Waern at 2010-05-14T18:06:11+00:00 Wibble - - - - - e40b0447 by David Waern at 2010-05-14T19:01:52+00:00 Move flag evaluation code from Main to Haddock.Options Determining the value of "singular" flags (by e.g. taking the last occurrence of the flag) and other flag evaluation should done in Haddock.Options which is the module that is supposed to define the command line interface. This makes Main a bit easier on the eyes as well. - - - - - 27091f57 by David Waern at 2010-05-14T19:05:10+00:00 Wibble - - - - - c658cf61 by David Waern at 2010-05-14T19:06:49+00:00 Re-order things in Haddock.Options a bit - - - - - 8cfdd342 by David Waern at 2010-05-14T19:20:29+00:00 De-tabify Haddock.Options and fix other whitespace issues - - - - - 0df16b62 by David Waern at 2010-05-14T19:25:07+00:00 Improve comments - - - - - 80b38e2b by David Waern at 2010-05-14T19:26:42+00:00 Whitespace police - - - - - fe580255 by David Waern at 2010-05-14T19:31:23+00:00 Wibbles to comments - - - - - a2b43fad by David Waern at 2010-05-14T20:24:32+00:00 Move some more flag functions to Haddock.Options - - - - - 3f895547 by David Waern at 2010-05-14T20:37:12+00:00 Make renderStep a top-level function in Main - - - - - 5cdca11d by David Waern at 2010-05-14T20:39:27+00:00 Spelling in comment - - - - - ad98d14c by David Waern at 2010-05-14T20:40:26+00:00 Comment fixes - - - - - 0bb9218f by David Waern at 2010-05-14T20:49:01+00:00 Whitespace police - - - - - 0f0a533f by David Waern at 2010-05-15T16:42:29+00:00 Improve description of --dump-interface - - - - - 5b2833ac by David Waern at 2010-05-15T17:16:53+00:00 Document --no-tmp-comp-dir - - - - - 8160b170 by David Waern at 2010-05-15T17:18:59+00:00 Wibble - - - - - 570dbe33 by David Waern at 2010-05-18T21:15:38+00:00 HLint police - - - - - 204e425f by David Waern at 2010-05-18T21:16:30+00:00 HLint police - - - - - 6db657ac by David Waern at 2010-05-18T21:16:37+00:00 Wibble - - - - - b942ccd7 by Simon Marlow at 2010-06-02T08:27:30+00:00 Interrupted disappeared in GHC 6.13 (GHC ticket haskell/haddock#4100) - - - - - 3b94a819 by Simon Marlow at 2010-06-02T08:45:08+00:00 Allow base-4.3 - - - - - c5a1fb7c by Simon Marlow at 2010-06-02T09:03:04+00:00 Fix compilation with GHC 6.13 - - - - - 6181296c by David Waern at 2010-06-08T21:09:05+00:00 Display name of prologue file when parsing it fails - - - - - 7cbc6f60 by Ian Lynagh at 2010-06-13T16:20:25+00:00 Remove redundant imports - - - - - 980c804b by Simon Marlow at 2010-06-22T08:41:50+00:00 isLocalAndTypeInferenced: fix for local module names overlapping package modules - - - - - d74d4a12 by Simon Marlow at 2010-06-23T12:03:27+00:00 Unresolved identifiers in Doc get replaced with DocMonospaced rather than plain strings - - - - - d8546783 by Simon Marlow at 2010-06-30T12:45:17+00:00 LaTeX backend (new options: --latex, --latex-style=<style>) - - - - - 437afa9e by David Waern at 2010-07-01T12:02:44+00:00 Fix a few stylistic whitespace issues in LaTeX backend - - - - - 85bc1fae by David Waern at 2010-07-01T15:42:45+00:00 Make runtest.hs work with GHC 6.12.3 (we should really stop hard coding this) - - - - - 7d2eb86f by David Waern at 2010-07-01T15:43:33+00:00 Update test following Simon's patch to render unresolved names in monospaced font - - - - - 08fcbcd2 by David Waern at 2010-07-01T16:12:18+00:00 Warning police - - - - - d04a8d7a by David Waern at 2010-07-04T14:53:39+00:00 Fix a bug in attachInstances We didn't look for instance docs in all the interfaces of the package. This had the effect of instance docs not always showing up under a declaration. I took the opportunity to clean up the code in H.I.AttachInstances a bit as well. More cleanup is needed, however. - - - - - d10344eb by Simon Hengel at 2010-07-10T09:19:04+00:00 Add missing dependencies to cabal file - - - - - 24090531 by Mark Lentczner at 2010-03-21T04:51:16+00:00 add exports to Xhtml modules - - - - - 84f9a333 by Mark Lentczner at 2010-04-03T19:14:22+00:00 clean up Doc formatting code - add CSS for lists - renderToString now uses showHtml since prettyHtml messes up <pre> sections - - - - - bebccf52 by Mark Lentczner at 2010-04-04T04:51:08+00:00 tweak list css - - - - - 0c2aeb5e by Mark Lentczner at 2010-04-04T06:24:14+00:00 all decls now generate Html not HtmlTable - ppDecl return Html, and so now do all of the functions it calls - added some internal tables to some decls, which is wrong, and will have to be fixed - decl "Box" functions became "Elem" functions to make clear they aren't in a table anymore (see Layout.hs) - docBox went away, as only used in one place (and its days are numbered) - cleaned up logic in a number of places, removed dead code - added maybeDocToHtml which simplified a number of places in the code - - - - - dbf73e6e by Mark Lentczner at 2010-04-05T05:02:43+00:00 clean up processExport and place a div around each decl - - - - - e25b7e9f by Mark Lentczner at 2010-04-10T21:23:21+00:00 data decls are now a sequence of paragraphs, not a table - - - - - 89ee0294 by Mark Lentczner at 2010-04-10T21:29:16+00:00 removed commented out code that can't be maintained - - - - - d466f536 by Mark Lentczner at 2010-04-12T04:56:27+00:00 removed declWithDoc and cleaned up data decls in summary - - - - - ed755832 by Mark Lentczner at 2010-04-12T05:07:53+00:00 merge in markupExample changes - - - - - c36f51fd by Mark Lentczner at 2010-04-25T04:56:37+00:00 made record fields be an unordList, not a table - - - - - ed3a28d6 by Mark Lentczner at 2010-04-25T05:23:28+00:00 fixed surround of instance and constructor tables - - - - - 0e35bbc4 by Mark Lentczner at 2010-04-25T05:36:59+00:00 fix class member boxes in summary - - - - - 5041749b by Mark Lentczner at 2010-04-25T05:38:35+00:00 remove unused bodyBox - - - - - e91724db by Mark Lentczner at 2010-04-25T06:26:10+00:00 fixed javascript quoting/escpaing issue - - - - - f4abbb73 by Mark Lentczner at 2010-05-03T23:04:31+00:00 adjust css for current markup - - - - - e75fec4c by Mark Lentczner at 2010-05-04T06:14:34+00:00 added assoicated types and methods back into class decls - - - - - 84169323 by Mark Lentczner at 2010-05-24T13:13:42+00:00 merge in changes from the big-whitespace cleanup - - - - - 3c1c872e by Mark Lentczner at 2010-06-11T21:03:58+00:00 adjust synopsis and bottom bar spacing - - - - - 3c1f9ef7 by Mark Lentczner at 2010-06-11T21:14:44+00:00 fix missing space in "module" lines in synoposis - - - - - 9a137e6d by Mark Lentczner at 2010-06-11T21:34:08+00:00 changed tt elements to code elements - - - - - 50f71ef1 by Mark Lentczner at 2010-06-11T23:27:46+00:00 factored out ppInstances - - - - - 3b9a9de5 by Mark Lentczner at 2010-06-17T17:36:01+00:00 push single constructors (newtype) onto line with decl - - - - - e0f8f2ec by Mark Lentczner at 2010-06-17T22:20:56+00:00 remove <++> connector - - - - - 56c075dd by Mark Lentczner at 2010-07-13T05:26:21+00:00 change to new page structure - - - - - 04be6ca7 by Mark Lentczner at 2010-07-14T04:21:55+00:00 constructors and args as dl lists, built in Layout.hs - - - - - 65aeafc2 by Mark Lentczner at 2010-07-14T05:38:32+00:00 better interface to subDecls - - - - - 72032189 by Mark Lentczner at 2010-07-14T07:04:10+00:00 made subDecl tables looks just so - - - - - b782eca2 by Mark Lentczner at 2010-07-14T16:00:54+00:00 convert args to SubDecl format - - - - - cc75e98f by Mark Lentczner at 2010-07-14T16:28:53+00:00 convert instances to SubDecl - - - - - 34e2aa5a by Mark Lentczner at 2010-07-14T21:07:32+00:00 removing old table cruft from Layout.hs - - - - - d5810d95 by Mark Lentczner at 2010-07-14T21:54:58+00:00 methods and associated types in new layout scheme - - - - - 65ef9579 by Mark Lentczner at 2010-07-14T23:43:42+00:00 clean up synopsis lists - - - - - e523318f by Mark Lentczner at 2010-07-15T05:02:26+00:00 clean up of anchors - - - - - 1215dfc5 by Mark Lentczner at 2010-07-15T23:53:01+00:00 added two new themes and rough css switcher - - - - - 7f0fd36f by Mark Lentczner at 2010-07-16T04:57:38+00:00 fixed package catpion, added style menu - - - - - 0dd4999c by Mark Lentczner at 2010-07-16T20:12:39+00:00 new output for mini_ pages - - - - - 64b2810b by Mark Lentczner at 2010-07-16T20:58:41+00:00 reformat index-frames - - - - - 3173f555 by Mark Lentczner at 2010-07-16T22:41:53+00:00 convert index to new markup - - - - - b0a4b7c9 by Mark Lentczner at 2010-07-17T04:07:22+00:00 convert index.html to new markup, adjust module markup - - - - - 8261ae1e by Mark Lentczner at 2010-07-17T05:07:29+00:00 classing styling of ancillary pages - - - - - 2a4fb025 by Mark Lentczner at 2010-07-17T05:11:45+00:00 clean up Layout.hs: no more vanillaTable - - - - - 87eec685 by Mark Lentczner at 2010-07-17T05:35:16+00:00 clean up Util.hs - - - - - d304e9b0 by Mark Lentczner at 2010-07-17T05:38:50+00:00 qualify import of XHtml as XHtml - - - - - 7dc05807 by Mark Lentczner at 2010-07-17T06:17:53+00:00 factored out head element generation - - - - - 9cdaec9e by Mark Lentczner at 2010-07-17T06:44:54+00:00 refactored out main page body generation - - - - - 8a51019e by Mark Lentczner at 2010-07-17T06:48:20+00:00 moved footer into only place that used it - - - - - efa479da by Mark Lentczner at 2010-07-17T18:48:30+00:00 styling auxillary pages for tibbe and snappy themes - - - - - 81de5509 by Mark Lentczner at 2010-07-18T04:41:38+00:00 fixed alphabet on index page, and styling of it and packages in module lists - - - - - 20718c1a by Mark Lentczner at 2010-07-18T05:34:29+00:00 cleaned up div functions in Layout.hs - - - - - 60d50453 by Mark Lentczner at 2010-07-18T05:48:39+00:00 added content div to main pages - - - - - ed16561c by Mark Lentczner at 2010-07-18T06:12:22+00:00 add .doc class to documentation blocks - - - - - f5c781b0 by Mark Lentczner at 2010-07-19T05:20:53+00:00 refactoring of anchor ID and fragment handling - - - - - a69a93bf by Mark Lentczner at 2010-07-19T05:35:55+00:00 remove an explicit bold tag - replace with .def class - - - - - d76c7225 by Mark Lentczner at 2010-07-19T06:56:15+00:00 rename Haddock.Backends.Xhtml.Util to Utils - - - - - 5a58c0da by David Waern at 2010-07-21T13:30:54+00:00 Remove trailing whitespace in Haddock.Backends.Xhtml - - - - - 0652aa17 by David Waern at 2010-07-21T13:33:21+00:00 Align a few comments - - - - - 785776c3 by David Waern at 2010-07-21T13:39:04+00:00 Remove trailing whitespace in H.B.X.Decl - - - - - 71a30710 by David Waern at 2010-07-21T13:44:27+00:00 Remove more trailing whitespace - - - - - 38750394 by David Waern at 2010-07-21T13:50:43+00:00 Style police - - - - - 3023d940 by David Waern at 2010-07-21T14:01:22+00:00 Style police in H.B.X.Decl - - - - - df16e9e6 by David Waern at 2010-07-21T14:14:45+00:00 Style police in H.B.X.DocMarkup - - - - - 6020e321 by David Waern at 2010-07-21T14:17:32+00:00 More style police - - - - - 86ad8bf5 by David Waern at 2010-07-21T14:21:02+00:00 Style police in H.B.Xhtml - - - - - aea27d03 by David Waern at 2010-07-21T14:42:03+00:00 Fix warnings in LaTeX backend - - - - - 2aff34a9 by David Waern at 2010-07-21T14:50:46+00:00 Style police in LaTeX backend (mainly more newlines) - - - - - e517162d by David Waern at 2010-07-21T15:05:47+00:00 Doc sections in Main - - - - - b971aa0c by David Waern at 2010-07-21T15:06:17+00:00 Trailing whitespace in Documentation.Haddock - - - - - f11628fb by David Waern at 2010-07-21T15:07:06+00:00 Trailing whitespace in Haddock.Convert - - - - - cbaf284c by David Waern at 2010-07-21T15:08:11+00:00 Style police in Haddock.GhcUtils - - - - - 71feb77b by David Waern at 2010-07-21T15:09:06+00:00 Style police in Haddock.InterfaceFile - - - - - 0a9c80e6 by David Waern at 2010-07-21T15:11:33+00:00 Whitespace police - - - - - 6168376c by David Waern at 2010-07-21T15:16:35+00:00 Style police in Haddock.Utils - - - - - 9fe4dd90 by David Waern at 2010-07-21T15:19:31+00:00 Add -fwarn-tabs - - - - - a000d752 by Mark Lentczner at 2010-07-20T17:25:52+00:00 move CSS Theme functions into Themes.hs - - - - - b52b440f by Mark Lentczner at 2010-07-20T17:29:35+00:00 add Thomas Schilling's theme - - - - - e43fa7e8 by Mark Lentczner at 2010-07-21T04:49:34+00:00 correct icon used with Snappy theme - - - - - ba5092d3 by Mark Lentczner at 2010-07-21T04:56:47+00:00 apply Tibbe's updates to his theme - - - - - 7804eef6 by Mark Lentczner at 2010-07-21T05:15:49+00:00 space between "Style" and the downward triangle - - - - - 7131d4c6 by Mark Lentczner at 2010-07-21T17:43:35+00:00 merge with David's source cleanups - - - - - ee65f1cb by David Waern at 2010-07-22T16:50:46+00:00 Fix a bug where we allowed --hoogle, --latex, etc without input files - - - - - e413ff7a by David Waern at 2010-07-22T17:21:58+00:00 Improve function name - - - - - a0fd14f3 by Simon Marlow at 2010-06-30T15:34:32+00:00 fix warnings - - - - - 31f73d2a by David Waern at 2010-07-22T19:29:41+00:00 Solve conflicts - - - - - d563b4a5 by Simon Marlow at 2010-06-30T15:34:37+00:00 fix warning - - - - - 412b6469 by David Waern at 2010-07-22T19:31:28+00:00 Solve conflict - - - - - 35174b94 by Ian Lynagh at 2010-07-06T17:27:16+00:00 Follow mkPState argument order change - - - - - b5c3585c by Simon Marlow at 2010-07-14T08:49:21+00:00 common up code for instance rendering - - - - - d8009560 by Simon Marlow at 2010-07-14T12:37:11+00:00 fix warnings - - - - - a6d88695 by David Waern at 2010-07-24T15:33:33+00:00 Fix build with ghc < 6.13 - - - - - 94cf9de1 by David Waern at 2010-07-24T15:34:37+00:00 Remove conflict left-over - - - - - 313b15c0 by Mark Lentczner at 2010-07-21T22:09:04+00:00 reorganization of nhaddock.css with tibbe - - - - - 9defed80 by Mark Lentczner at 2010-07-21T22:42:14+00:00 further cleanup of nhaddock.css, float TOC, support aux. pages - - - - - 6d944c1b by Mark Lentczner at 2010-07-22T06:22:23+00:00 remove old HTML backend - - - - - b3e8cba5 by Mark Lentczner at 2010-07-22T06:43:32+00:00 remove --html-help support - it was old, out-of-date, and mostly missing - - - - - d2654a08 by Mark Lentczner at 2010-07-22T21:45:34+00:00 tweaks to nhaddock.css - - - - - f73b285c by Mark Lentczner at 2010-07-23T06:19:35+00:00 command like processing for theme selection The bulk of the change is threadnig the selected theme set through functions in Xhtml.hs so that the selected themes can be used when generating the page output. There isn't much going on in most of these changes, just passing it along. The real work is all done in Themes.hs. - - - - - 8bddc90d by Mark Lentczner at 2010-07-23T06:58:31+00:00 drop --themes support, add named theme support decided that --themes was silly - no one would do that, just use multiple --theme arguments made --theme a synonym for --css and -c made those arguments, if no file is found, look up the argument as the name of a built in theme all of this let's haddock be invoked with "--theme=classic" for example. - - - - - 20cafd4f by Mark Lentczner at 2010-07-23T17:44:29+00:00 rename --default-themes to --built-in-themes - - - - - 0fe41307 by Mark Lentczner at 2010-07-23T18:33:02+00:00 tweaks to theme for info table, headings, and tables - - - - - cba4fee0 by Mark Lentczner at 2010-07-23T19:13:59+00:00 tweaks for dl layout, though still not used - - - - - 463fa294 by Mark Lentczner at 2010-07-23T21:07:19+00:00 tweak look of mini pages, keywords, and preblocks - - - - - 5472fc02 by Mark Lentczner at 2010-07-24T05:36:15+00:00 slide out Synopsis drawer - - - - - 9d5d5de5 by Mark Lentczner at 2010-07-24T06:02:42+00:00 extend package header and footer to edges of page - - - - - a47c91a2 by Mark Lentczner at 2010-07-24T06:28:44+00:00 fields are def lists, tweak css for style menu, mini pages, arguments - - - - - ca20f23b by Mark Lentczner at 2010-07-24T16:55:22+00:00 excisting last vestiges of the --xhtml flag - - - - - 71fb012e by Mark Lentczner at 2010-07-25T18:47:49+00:00 change how collapsing sections are done make whole .caption be the target improve javascript for class toggling have plus/minus images come from .css, not img tags - - - - - c168c8d3 by Mark Lentczner at 2010-07-26T00:32:05+00:00 reorganize files in the html lib data dir - - - - - 93324301 by Mark Lentczner at 2010-07-26T01:27:42+00:00 cleaned up Themes.hs - - - - - ad3b5dd4 by Mark Lentczner at 2010-07-26T02:39:15+00:00 make module list use new collapsers - - - - - 1df9bfc6 by Mark Lentczner at 2010-07-27T19:09:25+00:00 remove Tibbe theme - - - - - 8b9b01b3 by Mark Lentczner at 2010-07-27T20:04:03+00:00 move themes into html dir with .theme and .std-theme extensions - - - - - a7beb965 by Mark Lentczner at 2010-07-27T21:06:34+00:00 give a class to empty dd elements so they can be hidden - - - - - a258c117 by Mark Lentczner at 2010-07-27T21:23:58+00:00 remove custom version of copyFile in Xhtml.hs - - - - - b70dba6e by Mark Lentczner at 2010-07-27T22:12:45+00:00 apply margin changes to pre and headings as per group decision, and small cleanups - - - - - e6f722a2 by Mark Lentczner at 2010-07-28T00:03:12+00:00 make info block and package bar links be floatable by placing them first in the dom tree - - - - - c8278867 by Mark Lentczner at 2010-07-28T19:01:18+00:00 styling source links on declarations - - - - - 88fdc399 by Mark Lentczner at 2010-07-29T01:12:46+00:00 styling tweaks don't generate an empty li for absent style menu in links area update css for Classic and Snappy to handle: dl lists links in package header and in declarations floating of links and info block in package and module headers - - - - - 8a75b213 by Ian Lynagh at 2010-07-30T20:21:46+00:00 Fix build in GHC tree - - - - - ce8e18b3 by Simon Hengel at 2010-08-03T18:37:26+00:00 Adapt paths to data files in cabal file - - - - - 9701a455 by Simon Hengel at 2010-08-07T13:20:27+00:00 Add missing dependency to cabal file - - - - - 01b838d1 by Mark Lentczner at 2010-07-30T20:19:40+00:00 improved synopsis drawer: on click, not hover - - - - - 7b6f3e59 by Mark Lentczner at 2010-07-30T23:38:55+00:00 put the synopsis back in the other themes - - - - - 7b2904c9 by Mark Lentczner at 2010-08-11T11:11:26+00:00 close arrows on expanded synopsis drawer - - - - - ea19e177 by Mark Lentczner at 2010-08-12T21:16:45+00:00 width and font changes removed the max width restrictions on the page as a whole and the synopsis made the main font size smaller (nominally 14pt) and then tweaked most font sizes (relative) to be more consistent - - - - - 5ced00c0 by Mark Lentczner at 2010-08-13T15:09:55+00:00 implemented YUI's CSS font approach - - - - - 2799c548 by Mark Lentczner at 2010-08-13T15:11:59+00:00 adjusted margin to 2em, 1 wasn't enough - - - - - 58f06893 by Mark Lentczner at 2010-08-13T15:48:44+00:00 removed underlining on hover for named anchors headings in interface lost thier a element, no need, just put id on heading css for a elements now only applies to those with href attribute - - - - - 7aced4c4 by Mark Lentczner at 2010-08-13T15:50:22+00:00 more space between elements - - - - - 5a3c1cce by Mark Lentczner at 2010-08-13T16:43:43+00:00 adjusted font sizes of auxilary pages per new scheme - - - - - 487539ef by Mark Lentczner at 2010-08-13T21:43:41+00:00 add Frames button and clean up frames.html - - - - - c1a140b6 by Mark Lentczner at 2010-08-13T22:17:48+00:00 move frames button to js - - - - - b0bdb68e by Mark Lentczner at 2010-08-14T03:44:46+00:00 build style menu in javascript moved to javascript, so as to not polute the content with the style menu removed menu building code in Themes.hs removed onclick in Utils.hs changed text of button in header from "Source code" to "Source" more consistent with links in rest of page - - - - - 43ab7120 by Mark Lentczner at 2010-08-16T15:15:37+00:00 font size and margin tweaks - - - - - c0b68652 by Mark Lentczner at 2010-08-17T18:19:52+00:00 clean up collapser logics javascript code for collapasble sections cleaned up rewrote class utilities in javascript to be more robust refactored utilities for generating collapsable sections made toc be same color as synopsis module list has needed clear attribute in CSS - - - - - 5d573427 by Mark Lentczner at 2010-08-17T23:06:02+00:00 don't collapse entries in module list when clicking on links - - - - - 8c307c4a by Mark Lentczner at 2010-08-17T23:21:43+00:00 add missing data file to .cabal - - - - - 414bcfcf by Mark Lentczner at 2010-08-17T23:28:47+00:00 remove synopsis when in frames - - - - - ba0fa98a by Mark Lentczner at 2010-08-18T16:16:11+00:00 layout tweeks - mini page font size, toc color, etc. - - - - - 63c1bed1 by Mark Lentczner at 2010-08-18T19:50:02+00:00 margin fiddling - - - - - c311c094 by Mark Lentczner at 2010-08-20T01:37:55+00:00 better synopsis handling logic - no flashing - - - - - f1fe5fa8 by Mark Lentczner at 2010-08-20T01:41:06+00:00 fix small layout issues mini frames should have same size top heading give info block dts some padding so they don't collide in some browsers - - - - - 0de84d77 by Mark Lentczner at 2010-08-20T02:13:09+00:00 made style changing and cookies storage robust - - - - - 1ef064f9 by Thomas Schilling at 2010-08-04T13:12:22+00:00 Make synopsis frame behave properly in Firefox. In Firefox, pressing the back button first reverted the synopsis frame, and only clicking the back button a second time would update the main frame. - - - - - dd1c9a94 by Mark Lentczner at 2010-08-21T01:46:19+00:00 remove Snappy theme - - - - - 2353a90d by Mark Lentczner at 2010-08-25T05:16:19+00:00 fix occasional v.scroll bars on pre blocks (I think) - - - - - 459b8bf1 by Simon Hengel at 2010-08-08T10:12:45+00:00 Add createInterfaces' (a more high-level alternative to createInterfaces) to Haddock API - - - - - b1b68675 by David Waern at 2010-08-26T20:31:58+00:00 Follow recent API additions with some refactorings Simon Hegel's patch prompted me to do some refactorings in Main, Haddock.Documentation and Haddock.Interface. - - - - - 264d4d67 by David Waern at 2010-08-26T21:40:59+00:00 Get rid of GhcModule and related cruft We can get everything we need directly from TypecheckedModule. - - - - - 0feacec2 by Mark Lentczner at 2010-08-26T23:44:13+00:00 fixed CSS for ordered lists and def lists in doc blocks - - - - - 2997e0c2 by Mark Lentczner at 2010-08-26T23:45:03+00:00 support both kinds of enumerated lists in doc markup The documentation for Haddock says enumerated lists can use either of (1) first item 2. second item The second form wasn't actually supported - - - - - 5d4ddeec by Mark Lentczner at 2010-08-27T21:29:48+00:00 fix broken header link margins - - - - - 614456ba by Mark Lentczner at 2010-08-27T22:16:19+00:00 fix table of contents CSS - - - - - 03f329a2 by David Waern at 2010-08-28T16:36:09+00:00 Update tests following switch to the Xhtml backend - - - - - ca689fa2 by Mark Lentczner at 2010-08-28T18:25:16+00:00 fix def lists - - - - - 18e1d3d2 by Mark Lentczner at 2010-08-28T18:26:18+00:00 push footer to bottom of window - - - - - b0ab8d82 by David Waern at 2010-08-28T22:04:32+00:00 Whitespace police - - - - - 2d217977 by David Waern at 2010-08-29T12:44:45+00:00 Remove Snappy data files - - - - - 01e27d5f by David Waern at 2010-08-29T13:03:28+00:00 Add source entity path to --read-interface You can now use this flag like this: --read-interface=<html path>,<source entity path>,<.haddock file> By "source entity path" I mean the same thing that is specified with the --source-entity flag. The purpose of this is to be able to specify the source entity path per package, to allow source links to work in the presence of cross-package documentation. When given two arguments or less the --read-interface flag behaves as before. - - - - - 20bf4aaa by David Waern at 2010-08-29T13:11:03+00:00 Naming wibbles - - - - - ad22463f by Mark Lentczner at 2010-08-29T15:14:54+00:00 make portability block be a table - solves layout issues - - - - - 97bd1ae6 by Mark Lentczner at 2010-08-29T15:17:42+00:00 update golden test for Test due to portability box change - - - - - d37e139e by Mark Lentczner at 2010-08-29T17:07:17+00:00 move TOC and Info blocks down 0.5em to improve layout issue w/Test.hs - - - - - acf52501 by David Waern at 2010-08-29T17:32:36+00:00 Allow building with ghc < 6.16 - - - - - 1cb34ed8 by Ian Lynagh at 2010-07-24T23:18:49+00:00 Flatten the dynflags before parsing - - - - - b36845b4 by Ian Lynagh at 2010-07-24T23:26:49+00:00 Follow flattenLanguageFlags -> flattenExtensionFlags rename - - - - - 7f7fcc7e by David Waern at 2010-08-29T17:46:23+00:00 Use flattenExtensionFlags with ghc >= 6.13 only - - - - - 13cf9411 by Ian Lynagh at 2010-08-01T18:09:54+00:00 Make the main haddock script versioned, and make plain "haddock" a symlink - - - - - 495cbff2 by Ian Lynagh at 2010-08-18T18:57:24+00:00 Fix installation in the GHC build system Data-files are now in subdirectories, so we need to handle that - - - - - 88ebab0a by Ian Lynagh at 2010-08-18T19:43:53+00:00 GHC build system: Add all the data files to BINDIST_EXTRAS - - - - - 65837172 by David Waern at 2010-08-29T20:12:34+00:00 Update Test - - - - - 094bbaa2 by David Waern at 2010-08-29T20:55:14+00:00 Revert update to Test - - - - - a881cfb3 by David Waern at 2010-08-31T18:24:15+00:00 Bump version number - - - - - 1fc8a3eb by David Waern at 2010-08-31T22:32:27+00:00 Update ANNOUNCE - - - - - ee1df9d0 by David Waern at 2010-08-31T22:33:11+00:00 Update CHANGES - - - - - 394cc854 by David Waern at 2010-08-31T22:33:23+00:00 Update interface file versioning to work with ghc 6.14/15 - - - - - 7d03b79b by David Waern at 2010-08-31T22:36:00+00:00 Update test output following version change - - - - - a48d82d1 by Mark Lentczner at 2010-09-01T04:29:35+00:00 sort options in doc to match --help output removed --html-help option, as it is no longer supported - - - - - 06561aeb by Mark Lentczner at 2010-09-01T05:29:32+00:00 update options documentation rewrote doc for --html added doc for --theme and --built-in-themes added --use-contents and --gen-contents - - - - - 57dea832 by Mark Lentczner at 2010-09-01T05:31:27+00:00 slight wording change about Frames mode - - - - - fa1f6da3 by David Waern at 2010-09-01T10:57:44+00:00 Update doc configure script to find docbook stylesheets on arch linux - - - - - addff770 by David Waern at 2010-09-01T11:02:29+00:00 Wibble - - - - - 8399006d by David Waern at 2010-09-01T11:19:21+00:00 Replace ghci> with >>> in example syntax - - - - - 35074cf8 by David Waern at 2010-09-01T19:03:27+00:00 Improve docs for --no-tmp-comp-dir - - - - - 0f8f8cfd by David Waern at 2010-09-02T11:22:27+00:00 Add a list of contributors to the user guide Break out everyone thanked in the `Acknowledgements` chapter into a separate contributor list and add everyone from `darcs show authors`. We consider everyone who is thanked to be a contributor as a conservative estimation :-) I have added some more contributors that I know about, who were not in the darcs history, but others may be missing. So please add anyone that you think is missing from the list. - - - - - 42ccf099 by David Waern at 2010-09-02T11:29:22+00:00 Update copyright years in license - - - - - 0d560479 by David Waern at 2010-09-02T11:38:52+00:00 Update release instructions - - - - - 72ab7796 by David Waern at 2010-09-02T19:27:08+00:00 Add a note to ANNOUNCE - - - - - bf9d9c5d by David Waern at 2010-09-02T19:27:48+00:00 H.Utils needs FFI on Win+MinGW - - - - - 048ae44a by Mark Lentczner at 2010-09-04T23:19:47+00:00 make TOC group header identifiers validate - - - - - 8c6faf36 by Simon Michael at 2010-09-22T07:12:34+00:00 add hints for cleaner darcs show authors output - - - - - 9909bd17 by Simon Michael at 2010-09-22T17:58:06+00:00 print haddock coverage info on stdout when generating docs A module's haddockable items are its exports and the module itself. The output is lightly formatted so you can align the :'s and sort for readability. - - - - - 6da72171 by David Waern at 2010-10-03T21:31:24+00:00 Style wibble - - - - - 2f8d8e4d by Tobias Brandt at 2010-08-27T07:01:21+00:00 adding the option to fully qualify identifiers - - - - - 833be6c6 by Tobias Brandt at 2010-08-27T15:50:28+00:00 adding support for local and relative name qualification - - - - - df15c4e9 by Tobias Brandt at 2010-08-27T15:56:37+00:00 corrected qualification help message - - - - - 449e9ce1 by David Waern at 2010-10-16T17:34:30+00:00 Solve conflicts - - - - - 3469bda5 by David Waern at 2010-10-16T18:42:40+00:00 Use "qual" as an abbreviation for qualification instead of "quali" for consistency - - - - - 97c2d728 by David Waern at 2010-10-16T18:47:07+00:00 Style police - - - - - ce14fbea by David Waern at 2010-10-16T21:15:25+00:00 Style police - - - - - fdf29e9d by David Waern at 2010-10-17T00:30:44+00:00 Add a pointer to the style guide - - - - - 8e6b44e8 by rrnewton at 2010-10-24T03:19:28+00:00 Change to index pages: include an 'All' option even when subdividing A-Z. - - - - - 755b131c by David Waern at 2010-11-14T19:39:36+00:00 Bump version - - - - - d0345a04 by David Waern at 2010-11-14T19:41:59+00:00 TAG 2.8.1 - - - - - f6221508 by Simon Peyton Jones at 2010-09-13T09:53:00+00:00 Adapt to minor changes in internal GHC functions - - - - - 1290713d by Ian Lynagh at 2010-09-15T10:37:18+00:00 Remove duplicate Outputable instance for Data.Map.Map - - - - - 87f69eef by Ian Lynagh at 2010-09-21T15:01:10+00:00 Bump GHC dep upper bound - - - - - af36e087 by Ian Lynagh at 2010-09-21T15:12:02+00:00 Fix up __GLASGOW_HASKELL__ tests - - - - - ad67716c by Ian Lynagh at 2010-09-21T20:31:35+00:00 Don't build haddock is HADDOCK_DOCS is NO - - - - - 63b3f1f5 by Ian Lynagh at 2010-09-21T21:39:51+00:00 Fixes for when HADDOCK_DOCS=NO - - - - - e92bfa42 by Ian Lynagh at 2010-09-29T21:15:38+00:00 Fix URL creation on Windows: Use / not \ in URLs. Fixes haskell/haddock#4353 - - - - - 66c55e05 by Ian Lynagh at 2010-09-30T17:03:34+00:00 Tidy up haddock symlink installation In particular, it now doesn't get created if we aren't installing haddock. - - - - - 549b5556 by Ian Lynagh at 2010-10-23T21:17:14+00:00 Follow extension-flattening change in GHC - - - - - d7c2f72b by David Waern at 2010-11-14T20:17:55+00:00 Bump version to 2.8.2 - - - - - 6989a3a9 by David Waern at 2010-11-14T20:26:01+00:00 Solve conflict - - - - - 055c6910 by Ian Lynagh at 2010-09-22T15:36:20+00:00 Bump GHC dep - - - - - c96c0763 by Simon Marlow at 2010-10-27T11:09:44+00:00 follow changes in the GHC API - - - - - 45907129 by David Waern at 2010-11-07T14:00:58+00:00 Update the HCAR entry - - - - - 61940b95 by David Waern at 2010-11-07T14:07:34+00:00 Make the HCAR entry smaller - - - - - aa590b7d by David Waern at 2010-11-14T21:30:59+00:00 Update HCAR entry with November 2010 version - - - - - 587f9847 by David Waern at 2010-11-14T23:48:17+00:00 Require ghc >= 7.0 - - - - - ff5c647c by David Waern at 2010-11-14T23:49:09+00:00 TAG 2.8.2 - - - - - 937fcb4f by David Waern at 2010-11-14T23:49:45+00:00 Solve conflict - - - - - 8e5d0c1a by David Waern at 2010-11-15T21:09:50+00:00 Remove code for ghc < 7 - - - - - 3d47b70a by David Waern at 2010-11-15T21:11:06+00:00 Fix bad merge - - - - - 7f4a0d8a by David Waern at 2010-11-15T21:13:57+00:00 Remove more ghc < 7 code - - - - - 9ee34b50 by David Waern at 2010-11-15T21:31:25+00:00 Match all AsyncExceptions in exception handler - - - - - 42849c70 by David Waern at 2010-11-15T21:35:31+00:00 Just say "internal error" instead of "internal Haddock or GHC error" - - - - - c88c809b by David Waern at 2010-11-15T21:44:19+00:00 Remove docNameOcc under the motto "don't name compositions" - - - - - b798fc7c by David Waern at 2010-11-15T23:27:13+00:00 Wibble - - - - - 2228197e by David Waern at 2010-11-15T23:28:24+00:00 Rename the HCAR entry file - - - - - 8a3f9090 by David Waern at 2010-11-16T00:05:29+00:00 Remove Haskell 2010 extensions from .cabal file - - - - - c7a0c597 by David Waern at 2010-11-16T00:10:28+00:00 Style wibbles - - - - - cde707a5 by David Waern at 2010-11-16T00:12:00+00:00 Remove LANGUAGE ForeignFunctionInterface pragmas - - - - - 1dbda8ed by David Waern at 2010-11-16T00:17:21+00:00 Make a little more use of DoAndIfThenElse - - - - - 4c45ff6e by David Waern at 2010-11-16T00:59:41+00:00 hlint police - - - - - d2feaf09 by David Waern at 2010-11-16T01:14:15+00:00 hlint police - - - - - 99876e97 by David Waern at 2010-11-20T19:06:00+00:00 Haddock documentation updates - - - - - 65ce6987 by David Waern at 2010-11-20T19:42:51+00:00 Follow the style guide closer in Haddock.Types and improve docs - - - - - 28ca304a by tob.brandt at 2010-11-20T17:04:40+00:00 add full qualification for undocumented names - - - - - d61341e3 by David Waern at 2010-11-20T20:04:15+00:00 Re-structure qualification code a little - - - - - 0057e4d6 by David Waern at 2010-11-20T20:07:55+00:00 Re-order functions - - - - - d7279afd by David Waern at 2010-11-21T03:39:54+00:00 Add BangPatterns to alex and happy source files - - - - - 629fe60e by tob.brandt at 2010-11-23T23:35:11+00:00 documentation for qualification - - - - - 37031cee by David Waern at 2010-11-23T21:06:44+00:00 Update CHANGES - don't mention 2.8.2, we won't release it - - - - - f2489e19 by David Waern at 2010-12-01T21:57:11+00:00 Update deps of runtests.hs to work with ghc 7.0.1 - - - - - d3657e9a by David Waern at 2010-12-01T22:04:57+00:00 Make tests compile with ghc 7.0.1 - - - - - a2f09d9b by David Waern at 2010-12-01T22:06:59+00:00 Update tests following version bump - - - - - 50883ebb by David Waern at 2010-12-06T14:09:18+00:00 Update tests following recent changes - - - - - fc2fadeb by David Waern at 2010-12-06T14:17:29+00:00 Add a flag --pretty-html for rendering indented html with newlines - - - - - 30832ef2 by David Waern at 2010-12-06T14:17:35+00:00 Use --pretty-html when running the test suite. Makes it easier to compare output - - - - - a0b81b31 by David Waern at 2010-12-06T14:18:27+00:00 Wibble - - - - - 3aaa23fe by David Waern at 2010-12-06T14:19:29+00:00 Haddockify ppHtml comments - - - - - 24bb24f0 by David Waern at 2010-12-06T14:23:15+00:00 Remove --debug. It was't used, and --verbosity should take its place - - - - - 6bc076e5 by David Waern at 2010-12-06T14:25:37+00:00 Rename golden-tests into html-tests. "golden tests" sounds strange - - - - - 53301e55 by David Waern at 2010-12-06T14:26:26+00:00 QUALI -> QUAL in the description --qual for consistency - - - - - 98b6affb by David Waern at 2010-12-06T21:54:02+00:00 Bump version - - - - - 371bf1b3 by David Waern at 2010-12-06T22:08:55+00:00 Update tests following version bump - - - - - 25be762d by David Waern at 2010-12-06T22:21:03+00:00 Update CHANGES - - - - - 7c7dac71 by David Waern at 2010-12-06T22:33:43+00:00 Update ANNOUNCE - - - - - 30d7a5f2 by Simon Peyton Jones at 2010-11-15T08:38:38+00:00 Alex generates BangPatterns, so make Lex.x accept them (It'd be better for Alex to generate this pragma.) - - - - - 605e8018 by Simon Marlow at 2010-11-17T11:37:24+00:00 Add {-# LANGUAGE BangPatterns #-} to mollify GHC - - - - - a46607ba by David Waern at 2010-12-07T14:08:10+00:00 Solve conflicts - - - - - b28cda66 by David Waern at 2010-12-09T20:41:35+00:00 Docs: Mention that \ is a special character in markup - - - - - a435bfdd by Ian Lynagh at 2010-11-17T14:01:19+00:00 TAG GHC 7.0.1 release - - - - - 5a15a05a by David Waern at 2010-12-11T17:51:19+00:00 Fix indentation problem - - - - - 4232289a by Lennart Kolmodin at 2010-12-17T18:32:03+00:00 Revise haddock.cabal given that we now require ghc-7 default-language should be Haskell2010, slight new semantics for extensions. Rewrite into clearer dependencies of base and Cabal. - - - - - a36302dc by David Waern at 2010-12-19T17:12:37+00:00 Update CHANGES - - - - - 7c8b85b3 by David Waern at 2010-12-19T17:14:24+00:00 Bump version - - - - - cff22813 by Ian Lynagh at 2011-01-05T18:24:27+00:00 Write hoogle output in utf8; fixes GHC build on Windows - - - - - c7e762ea by David Waern at 2011-01-22T00:00:35+00:00 Put title outside doc div when HTML:fying title+prologue Avoids indenting the title, and makes more sense since the title is not a doc string anyway. - - - - - 5f639054 by David Waern at 2011-01-22T16:09:44+00:00 Fix spelling error - contributed by Marco Silva - - - - - c11dce78 by Ian Lynagh at 2011-01-07T02:33:11+00:00 Follow GHC build system changes - - - - - 101cfaf5 by David Waern at 2011-01-08T14:06:44+00:00 Bump version - - - - - af62348b by David Waern at 2011-01-08T14:07:07+00:00 TAG 2.9.2 - - - - - 4d1f6461 by Ian Lynagh at 2011-01-07T23:06:57+00:00 Name the haddock script haddock-ghc-7.0.2 instead of haddock-7.0.2; haskell/haddock#4882 "7.0.2" looked like a haddock version number before - - - - - 8ee4d5d3 by Simon Peyton Jones at 2011-01-10T17:31:12+00:00 Update Haddock to reflect change in hs_tyclds field of HsGroup - - - - - 06f3e3db by Ian Lynagh at 2011-03-03T15:02:37+00:00 TAG GHC 7.0.2 release - - - - - 7de0667d by David Waern at 2011-03-10T22:47:13+00:00 Update CHANGES - - - - - 33a9f1c8 by David Waern at 2011-03-10T22:47:31+00:00 Fix build with ghc 7.0.1 - - - - - 4616f861 by David Waern at 2011-03-10T22:47:50+00:00 TAG 2.9.2-actual - - - - - 0dab5e3c by Simon Hengel at 2011-04-08T15:53:01+00:00 Set shell script for unit tests back to work - - - - - 85c54dee by Simon Hengel at 2011-04-08T16:01:24+00:00 Set unit tests back to work Here "ghci>" was still used instead of ">>>". - - - - - 1cea9b78 by Simon Hengel at 2011-04-08T16:25:36+00:00 Update runtests.hs for GHC 7.0.2 - - - - - 8e5b3bbb by Simon Hengel at 2011-04-08T16:28:49+00:00 Update Haddock version in *.html.ref - - - - - 2545e955 by Simon Hengel at 2011-04-08T17:09:28+00:00 Add support for blank lines in the result of examples Result lines that only contain the string "<BLANKLINE>" are treated as a blank line. - - - - - adf64d2e by Simon Hengel at 2011-04-08T17:36:50+00:00 Add documentation for "support for blank lines in the result of examples" - - - - - c51352ca by David Waern at 2011-05-21T23:57:56+00:00 Improve a haddock comment - - - - - 7419cf2c by David Waern at 2011-05-22T15:41:52+00:00 Use cabal's test suite support to run the test suite This gives up proper dependency tracking of the test script. - - - - - 7770070c by David Waern at 2011-05-22T01:45:44+00:00 We don't need to send DocOptions nor a flag to mkExportItems - - - - - 9d95b7b6 by David Waern at 2011-05-22T21:39:03+00:00 Fix a bug - - - - - 1f93699b by David Waern at 2011-05-22T21:40:21+00:00 Break out fullContentsOf, give it a better name and some documentation The documentation describes how we want this function to eventually behave, once we have fixed a few problems with the current implementation. - - - - - 9a86432f by David Waern at 2011-05-22T21:53:52+00:00 Fix some stylistic issues in mkExportItems - - - - - c271ff0c by David Waern at 2011-05-22T22:09:11+00:00 Indentation - - - - - 93e602b1 by David Waern at 2011-06-10T01:35:31+00:00 Add git commits since switchover: darcs format (followed by a conflict resolution): commit 6f92cdd12d1354dfbd80f8323ca333bea700896a Merge: f420cc4 28df3a1 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 19 17:54:34 2011 +0100 Merge remote branch 'origin/master' into ghc-generics commit 28df3a119f770fdfe85c687dd73d5f6712b8e7d0 Author: Max Bolingbroke <batterseapower at hotmail.com> Date: Sat May 14 22:37:02 2011 +0100 Unicode fix for getExecDir on Windows commit 89813e729be8bce26765b95419a171a7826f6d70 Merge: 6df3a04 797ab27 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 9 11:55:17 2011 +0100 Merge branch 'ghc-new-co' commit 6df3a040da3dbddee67c6e30a892f87e6b164383 Author: Ian Lynagh <igloo at earth.li> Date: Sun May 8 17:05:50 2011 +0100 Follow changes in SDoc commit f420cc48b9259f0b1afd2438b12f9a2bde57053d Author: Jose Pedro Magalhaes <jpm at cs.uu.nl> Date: Wed May 4 17:31:52 2011 +0200 Adapt haddock to the removal of HsNumTy and TypePat. commit 797ab27bdccf39c73ccad374fea265f124cb52ea Merge: 1d81436 5a91450 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:05:03 2011 +0100 Merge remote branch 'origin/master' into ghc-new-co commit 1d8143659a81cf9611668348e33fd0775c7ab1d2 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:03:46 2011 +0100 Wibbles for ghc-new-co branch commit 5a91450e2ea5a93c70bd3904b022445c9cc82488 Author: Ian Lynagh <igloo at earth.li> Date: Fri Apr 22 00:51:56 2011 +0100 Follow defaultDynFlags change in GHC - - - - - 498da5ae by David Waern at 2011-06-11T00:33:33+00:00 * Merge in git patch from Michal Terepeta >From 6fc71d067738ef4b7de159327bb6dc3d0596be29 Mon Sep 17 00:00:00 2001 From: Michal Terepeta <michal.terepeta at gmail.com> Date: Sat, 14 May 2011 19:18:22 +0200 Subject: [PATCH] Follow the change of TypeSig in GHC. This follows the change in GHC to make TypeSig take a list of names (instead of just one); GHC ticket haskell/haddock#1595. This should also improve the Haddock output in case the user writes a type signature that refers to many names: -- | Some comment.. foo, bar :: ... will now generate the expected output with one signature for both names. - - - - - 094607fe by Ian Lynagh at 2011-06-17T19:10:29+01:00 Fix build - - - - - 8fa35740 by Ian Lynagh at 2011-06-26T21:06:40+01:00 Bump GHC dep to allow 7.2 - - - - - e4d2ca3c by Ian Lynagh at 2011-07-07T23:06:28+01:00 Relax base dep - - - - - b948fde9 by Ian Lynagh at 2011-07-28T16:39:45+01:00 GHC build system: Don't install the datafiles twice - - - - - f82f6d70 by Simon Marlow at 2011-08-11T12:08:15+01:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - b341cc12 by Max Bolingbroke at 2011-08-22T20:25:27+01:00 Fix compilation with no-pred-ty GHC - - - - - 30494581 by Max Bolingbroke at 2011-08-23T10:20:54+01:00 Remaining fixes for PredTy removal - - - - - 0b197138 by Max Bolingbroke at 2011-08-26T08:27:45+01:00 Rename factKind to constraintKind - - - - - a379bec5 by Max Bolingbroke at 2011-09-04T12:54:47+01:00 Deal with change to IParam handling in GHC - - - - - f94e421b by Max Bolingbroke at 2011-09-06T17:34:31+01:00 Adapt Haddock for the ConstraintKind extension changes - - - - - 8821e5cc by Max Bolingbroke at 2011-09-09T08:24:59+01:00 Ignore associated type defaults (just as we ignore default methods) - - - - - 31a0afd4 by Max Bolingbroke at 2011-09-09T09:06:00+01:00 Merge branch 'no-pred-ty' of ssh://darcs.haskell.org/srv/darcs/haddock into no-pred-ty - - - - - dd3b530a by Max Bolingbroke at 2011-09-09T14:10:25+01:00 Merge branch 'no-pred-ty' Conflicts: src/Haddock/Convert.hs - - - - - 5f25ec96 by Max Bolingbroke at 2011-09-09T14:10:40+01:00 Replace FactTuple with ConstraintTuple - - - - - cd30b9cc by David Waern at 2011-09-26T02:17:55+02:00 Bump to version 2.9.3 - - - - - 4fbfd397 by Max Bolingbroke at 2011-09-27T14:55:21+01:00 Follow changes to BinIface Name serialization - - - - - 92257d90 by David Waern at 2011-09-30T23:45:07+02:00 Fix problem with test files not added to distribution tarball - - - - - 00255bda by David Waern at 2011-09-30T23:48:24+02:00 Merge branch 'development' - - - - - 5421264f by David Waern at 2011-10-01T01:25:39+02:00 Merge in darcs patch from Simon Meier: Wed Jun 1 19:41:16 CEST 2011 iridcode at gmail.com * prettier haddock coverage info The new coverage info rendering uses less horizontal space. This reduces the number of unnecessary line-wrappings. Moreover, the most important information, how much has been documented already, is now put up front. Hopefully, this makes it more likely that a library author is bothered by the low coverage of his modules and fixes that issue ;-) - - - - - 07d318ef by David Waern at 2011-10-01T01:34:10+02:00 Use printException instead of deprecated printExceptionAndWarnings - - - - - 40d52ee4 by David Waern at 2011-10-01T01:41:13+02:00 Merge in darcs pach: Mon Apr 11 18:09:54 JST 2011 Liyang HU <haddock at liyang.hu> * Remember collapsed sections in index.html / haddock-util.js - - - - - 279d6dd4 by David Waern at 2011-10-01T01:55:45+02:00 Merge in darcs patch: Joachim Breitner <mail at joachim-breitner.de>**20110619201645 Ignore-this: f6c51228205b0902ad5bfad5040b989a As reported on http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=578301, generating the global index takes much too long if type-level (with lots of auto-generated types) is installed. The patch avoids a quadratic runtime in the subfunction getIfaceIndex of ppHtmlIndex by using a temporary set. Runtime improvement observed here from 25.36s to 2.86s. - - - - - d1612383 by David Waern at 2011-10-01T01:56:48+02:00 Merge branch 'development' - - - - - 347520c1 by David Waern at 2011-10-01T01:56:54+02:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9a0c95e8 by David Waern at 2011-10-01T02:19:10+02:00 Improve .cabal file - - - - - 6967dc64 by Ian Lynagh at 2011-10-01T01:34:06+01:00 Follow changes to ForeignImport/ForeignExport in GHC - - - - - 565cb26b by Simon Marlow at 2011-10-04T00:15:04+02:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - 8b74f512 by David Waern at 2011-10-04T00:18:17+02:00 Requre ghc >= 7.2 - - - - - 271d360c by David Waern at 2011-10-04T00:22:50+02:00 Bump version to 2.9.4 - - - - - 37f3edb0 by David Waern at 2011-10-06T02:30:21+02:00 Add alex and happy to build-tools. - - - - - 7ac2bb6e by David Terei at 2011-10-12T14:02:55-07:00 Add safe haskell indication to haddock output - - - - - 42c91a47 by David Terei at 2011-10-12T14:06:03-07:00 Fix CSS issue with info table not being contained in module header - - - - - 0eddab6c by David Terei at 2011-10-12T14:06:58-07:00 Add safe haskell indication to haddock output - - - - - 3df058eb by David Terei at 2011-10-12T14:07:07-07:00 Fix CSS issue with info table not being contained in module header - - - - - a40a6c3f by David Waern at 2011-10-22T11:29:06+02:00 Bump .haddock file version since the format has changed recently - - - - - 8a6254be by David Waern at 2011-10-22T11:30:42+02:00 Merge branch 'development' - - - - - 642e3e02 by David Waern at 2011-10-23T21:23:39+02:00 Sort import list - - - - - 36371cf8 by David Waern at 2011-10-23T22:48:18+02:00 Remove NEW_GHC_LAYOUT conditional. - - - - - 5604b499 by David Waern at 2011-10-27T00:15:03+02:00 Add --print-ghc-path. - - - - - 463499fa by David Waern at 2011-10-27T00:16:22+02:00 Make testsuite able to find its dependencies automatically. - - - - - a3506172 by Ryan Newton at 2011-11-05T05:59:58-04:00 Improved declNames internal error. Added a case to handle DocD. - - - - - 001b8baf by David Waern at 2011-11-05T20:37:29+01:00 Rename copy.hs -> accept.hs. - - - - - 55d808d3 by David Waern at 2011-11-05T23:30:02+01:00 Fix build. - - - - - deb5c3be by David Waern at 2011-11-06T00:01:47+01:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9b663554 by David Waern at 2011-11-06T00:03:45+01:00 Merge https://github.com/rrnewton/haddock - - - - - 1abb0ff6 by David Waern at 2011-11-06T01:20:37+01:00 Use getDeclMainBinder instead of declNames. - - - - - 4b005c01 by David Waern at 2011-11-06T19:09:53+01:00 Fix build. - - - - - c2c51bc7 by Ian Lynagh at 2011-11-06T23:01:33+00:00 Remove -DNEW_GHC_LAYOUT in ghc.mk - - - - - f847d703 by Jose Pedro Magalhaes at 2011-11-11T09:07:39+00:00 New kind-polymorphic core This big patch implements a kind-polymorphic core for GHC. The current implementation focuses on making sure that all kind-monomorphic programs still work in the new core; it is not yet guaranteed that kind-polymorphic programs (using the new -XPolyKinds flag) will work. For more information, see http://haskell.org/haskellwiki/GHC/Kinds - - - - - 7d7c3b09 by Jose Pedro Magalhaes at 2011-11-16T21:42:22+01:00 Follow changes to tuple sorts in master - - - - - 8430e03e by Simon Peyton Jones at 2011-11-17T10:20:27+00:00 Remove redundant imports - - - - - d1b06832 by Ian Lynagh at 2011-11-19T01:33:21+00:00 Follow GHC build system change to the way we call rm - - - - - 9e2230ed by David Waern at 2011-11-24T15:00:24+01:00 Fix a bug in test runner and get rid of regex-compat dependency. - - - - - 52039b21 by David Waern at 2011-11-24T23:55:36+01:00 Avoid haskell98 dependency in test - - - - - 92e1220d by David Waern at 2011-11-25T00:03:33+01:00 Avoid depency on regex-compat also in accept.hs. - - - - - ddac6b6f by David Waern at 2011-11-25T02:13:38+01:00 Accept test output. - - - - - 5a720455 by David Waern at 2011-11-25T02:16:20+01:00 Some more changes to test scripts. - - - - - 170a9004 by David Waern at 2011-11-25T02:30:41+01:00 Add flag --interface-version. - - - - - d225576c by David Waern at 2011-11-25T02:39:26+01:00 Remove #ifs for older compiler versions. - - - - - f0d0a4f5 by David Waern at 2011-11-26T04:20:12+01:00 Give preference to type over data constructors for doc comment links at renaming time. Previously this was done in the backends. Also, warn when a doc comment refers to something that is in scope but which we don't have the .haddock file for. These changes mean we can make DocIdentifier [a] into DocIdentifier a. - - - - - eef0e776 by David Waern at 2011-11-26T17:01:06+01:00 Allow doc comments to link to out-of-scope things (#78). (A bug that should have been fixed long ago.) - - - - - 565ad529 by David Waern at 2011-11-26T19:56:21+01:00 Update tests. - - - - - fb3ce7b9 by David Waern at 2011-11-26T21:44:28+01:00 Cleanup. - - - - - d0328126 by David Waern at 2011-11-26T22:10:28+01:00 Fix module reference bug. - - - - - c03765f8 by David Waern at 2011-12-03T05:20:20+01:00 Slightly better behaviour on top-levels without type signatures. - Docs don't get attached to the next top-level with signature by mistake. - If there's an export list and the top-level is part of it, its doc comment shows up in the documentation. - - - - - 48461d31 by David Waern at 2011-12-03T05:38:10+01:00 Add a test for Unicode doc comments. - - - - - 549c4b4e by David Waern at 2011-12-03T19:07:55+01:00 Cleanup. - - - - - 7bfecf91 by David Waern at 2011-12-03T20:13:08+01:00 More cleanup. - - - - - 14fab722 by Ian Lynagh at 2011-12-12T21:21:35+00:00 Update dependencies and binaryInterfaceVersion - - - - - 469e6568 by Ian Lynagh at 2011-12-18T12:56:16+00:00 Fix (untested) building from source tarball without alex/happy haddock's .cabal file was declaring that it needed alex and happy to build, but in the GHC source tarballs it doesn't. - - - - - 895c9a8c by David Waern at 2011-12-27T12:57:43+01:00 Go back to having a doc, sub and decl map instead of one big decl map. This setup makes more sense since when we add value bindings to the processed declarations (for type inference), we will have multiple declarations which should share documentation. Also, we already have a separate doc map for instances which we can now merge into the main doc map. Another benefit is that we don't need the DeclInfo type any longer. - - - - - 736767d9 by David Waern at 2011-12-27T13:33:41+01:00 Merge ../../../haddock Conflicts: src/Haddock/InterfaceFile.hs - - - - - 20016f79 by David Waern at 2011-12-27T13:57:23+01:00 Bump version. - - - - - 31f276fb by David Waern at 2011-12-27T13:57:32+01:00 Merge ../ghc/utils/haddock - - - - - 95b367cd by David Waern at 2011-12-27T14:57:29+01:00 Update tests following version bump. - - - - - fa3c94cd by David Waern at 2011-12-27T14:57:51+01:00 Get rid of quite unnecessary use of different lists. - - - - - 9c4d3c54 by David Waern at 2011-12-27T15:26:42+01:00 Cleanup. - - - - - 2caf9f90 by David Waern at 2011-12-27T16:18:05+01:00 Wibbles. - - - - - 3757d09b by David Waern at 2011-12-27T20:50:26+01:00 Complete support for inferring types for top-level bindings. - - - - - 53418734 by David Waern at 2011-12-28T15:02:13+01:00 Minor fixes and cleanup. - - - - - 0c9d0385 by Ian Lynagh at 2012-01-03T18:31:29+00:00 Follow rename of Instance to ClsInst in GHC - - - - - c9bc969a by Simon Hengel at 2012-01-12T21:28:14+01:00 Make sure that generated xhtml is valid (close haskell/haddock#186) Thanks to Phyx. - - - - - 836a0b9a by David Waern at 2012-02-01T02:30:05+01:00 Fix bug introduced in my recent refactoring. - - - - - c7d733eb by David Waern at 2012-02-01T02:30:26+01:00 Cleanup mkMaps and avoid quadratic behaviour. - - - - - da3cda8f by David Waern at 2012-02-01T02:56:56+01:00 Require ghc >= 7.4. - - - - - 83a3287e by David Waern at 2012-02-01T02:57:36+01:00 Update CHANGES. - - - - - 93408f0b by Simon Hengel at 2012-02-04T00:48:04+01:00 Add reference renderings - - - - - 49d00d2c by Simon Hengel at 2012-02-04T00:48:25+01:00 Set unit tests for parser back to work - - - - - eb450980 by Simon Hengel at 2012-02-04T00:49:07+01:00 Add .gitignore - - - - - a841602c by Simon Hengel at 2012-02-04T00:49:16+01:00 Add .ghci file - - - - - 8861199d by Simon Hengel at 2012-02-04T00:49:29+01:00 tests/html-tests/copy.hs: Use mapM_ instead of mapM So we do net get a list of () on stdout when running with runhaskell. - - - - - b477d9b5 by Simon Hengel at 2012-02-04T00:49:46+01:00 Remove index files from golden tests - - - - - 9dbda34e by Simon Hengel at 2012-02-04T00:49:57+01:00 Add /tests/html-tests/tests/*index*.ref to .gitignore - - - - - a9434817 by Simon Hengel at 2012-02-04T00:50:04+01:00 Add DocWarning to Doc The Xhtml backend has special markup for that, Hoogle and LaTeX reuse what we have for DocEmphasis. - - - - - de2fb6fa by Simon Hengel at 2012-02-04T00:50:13+01:00 Add support for module warnings - - - - - 0640920e by Simon Hengel at 2012-02-04T00:50:21+01:00 Add tests for module warnings - - - - - 30ce0d77 by Simon Hengel at 2012-02-04T00:50:29+01:00 Add support for warnings - - - - - bb367960 by Simon Hengel at 2012-02-04T00:50:37+01:00 Add tests for warnings - - - - - 6af1dc2d by Simon Hengel at 2012-02-04T00:50:50+01:00 Expand type signatures in export list (fixes haskell/haddock#192) - - - - - a06cbf25 by Simon Hengel at 2012-02-04T00:51:04+01:00 Expand type signatures for modules without explicit export list - - - - - 57dda796 by Simon Hengel at 2012-02-04T00:51:15+01:00 Remove obsolete TODO - - - - - 270c3253 by David Waern at 2012-02-04T00:51:24+01:00 Fix issues in support for warnings. * Match against local names only. * Simplify (it's OK to map over the warnings). - - - - - 683634bd by David Waern at 2012-02-04T00:55:11+01:00 Some cleanup and make sure we filter warnings through exports. - - - - - 210cb4ca by David Waern at 2012-02-04T03:01:30+01:00 Merge branch 'fix-for-186' of https://github.com/sol/haddock into ghc-7.4 - - - - - e8db9031 by David Waern at 2012-02-04T03:07:51+01:00 Style police. - - - - - 261f9462 by David Waern at 2012-02-04T03:20:16+01:00 Update tests. - - - - - 823cfc7c by David Waern at 2012-02-04T03:21:12+01:00 Use mapM_ in accept.hs as well. - - - - - 873dd619 by David Waern at 2012-02-04T03:21:33+01:00 Remove copy.hs - use accept.hs instead. - - - - - 0e31a14a by David Waern at 2012-02-04T03:47:33+01:00 Use <> instead of mappend. - - - - - 2ff7544f by David Waern at 2012-02-04T03:48:55+01:00 Remove code for older ghc versions. - - - - - dacf2786 by David Waern at 2012-02-04T15:52:51+01:00 Clean up some code from last SoC project. - - - - - 00cbb117 by David Waern at 2012-02-04T21:43:49+01:00 Mostly hlint-inspired cleanup. - - - - - 7dc86cc2 by Simon Peyton Jones at 2012-02-06T09:14:41+00:00 Track changes in HsDecls - - - - - f91f82fe by Ian Lynagh at 2012-02-16T13:40:11+00:00 Follow changes in GHC caused by the CAPI CTYPE pragma - - - - - a0ea6b0b by Ian Lynagh at 2012-02-22T02:26:12+00:00 Follow changes in GHC - - - - - b23b07d1 by Simon Peyton Jones at 2012-03-02T16:36:41+00:00 Follow changes in data representation from the big PolyKinds commit - - - - - 43406022 by Simon Hengel at 2012-03-05T11:18:34+01:00 Save/restore global state for static flags when running GHC actions This is necessary if we want to run createInterfaces (from Documentation.Haddock) multiple times in the same process. - - - - - 9fba16fe by Paolo Capriotti at 2012-03-06T10:57:33+00:00 Update .gitignore. - - - - - a9325044 by Simon Peyton Jones at 2012-03-14T17:35:42+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - fd48065a by Iavor Diatchki at 2012-03-15T22:43:35-07:00 Add support for type-level literals. - - - - - 2e8206dd by Simon Peyton Jones at 2012-03-16T14:18:22+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - 93e13319 by Simon Peyton Jones at 2012-03-17T01:04:05+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock Conflicts: src/Haddock/Convert.hs - - - - - d253fa71 by Iavor Diatchki at 2012-03-19T20:12:18-07:00 Merge remote-tracking branch 'origin/master' into type-nats - - - - - fc40acc8 by Iavor Diatchki at 2012-03-19T20:31:27-07:00 Add a missing case for type literals. - - - - - fd2ad699 by Iavor Diatchki at 2012-03-24T13:28:29-07:00 Rename variable to avoid shadowing warning. - - - - - 9369dd3c by Simon Peyton Jones at 2012-03-26T09:14:23+01:00 Follow refactoring of TyClDecl/HsTyDefn - - - - - 38825ca5 by Simon Peyton Jones at 2012-03-26T09:14:37+01:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - 4324ac0f by David Waern at 2012-04-01T01:51:19+02:00 Disable unicode test. - - - - - 3165b750 by David Waern at 2012-04-01T01:51:34+02:00 Take reader environment directly from TypecheckedSource. - - - - - 213b644c by David Waern at 2012-04-01T01:55:20+02:00 Cleanup. - - - - - 3118b4ba by David Waern at 2012-04-01T02:16:15+02:00 Don't filter out unexported names from the four maps - fixes a regression. - - - - - d6524e17 by David Waern at 2012-04-01T02:40:34+02:00 Fix crash when using --qual. Naughty GHC API! - - - - - ea3c43d8 by Henning Thielemann at 2012-04-01T13:03:07+02:00 add QualOption type for distinction between qualification argument given by the user and the actual qualification for a concrete module - - - - - 5422ff05 by Henning Thielemann at 2012-04-01T16:25:02+02:00 emit an error message when the --qual option is used incorrectly - - - - - 026e3404 by David Waern at 2012-04-01T18:10:30+02:00 Don't crash on unicode strings in doc comments. - - - - - ce006632 by David Waern at 2012-04-01T20:13:35+02:00 Add test for --ignore-all-exports flag/ignore-exports pragma. - - - - - 6e4dd33c by David Waern at 2012-04-01T20:21:03+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.4 - - - - - 734ae124 by Henning Thielemann at 2012-04-01T20:22:10+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - 622f9ba5 by David Waern at 2012-04-01T21:26:13+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 55ce17cb by Henning Thielemann at 2012-04-01T22:03:25+02:00 'abbreviate' qualification style - basic support Currently we ignore the package a module is imported from. This means that a module import would shadow another one with the same module name from a different package. - - - - - c85314ef by David Waern at 2012-04-01T22:05:12+02:00 Check qualification option before processing modules. - - - - - ae4b626c by Henning Thielemann at 2012-04-02T00:19:36+02:00 abbreviated qualification: use Packages.lookupModuleInAllPackages for finding the package that a module belongs to - - - - - 60bdbcf5 by Henning Thielemann at 2012-04-02T00:25:31+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - df44301d by Henning Thielemann at 2012-04-02T00:29:05+02:00 qualification style 'abbreviated' -> 'aliased' - - - - - f4192a64 by David Waern at 2012-04-02T01:05:47+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 7ba09067 by David Terei at 2012-04-04T15:08:21-07:00 Fix reporting of modules safe haskell mode (#5989) - - - - - d0cc33d0 by David Terei at 2012-04-06T15:50:41+01:00 Fix reporting of modules safe haskell mode (#5989) - - - - - 6e3434c5 by Simon Peyton Jones at 2012-04-20T18:37:46+01:00 Track changes in HsSyn - - - - - 22014ed0 by Simon Peyton Jones at 2012-05-11T22:45:15+01:00 Follow changes to LHsTyVarBndrs - - - - - d9a07b24 by David Waern at 2012-05-15T01:46:35+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - a6c4ebc6 by David Waern at 2012-05-16T02:18:32+02:00 Update CHANGES. - - - - - 8e181d29 by David Waern at 2012-05-16T02:27:56+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - e358210d by David Waern at 2012-05-16T02:35:33+02:00 Mention the new aliased --qual mode in CHANGES. - - - - - efd36a28 by David Waern at 2012-05-16T21:33:13+02:00 Bump version number. - - - - - d6b3af14 by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for deprecated record field - - - - - 927f800e by Simon Hengel at 2012-05-17T19:08:20+02:00 Use >>= instead of fmap and join - - - - - 048b41d5 by Simon Hengel at 2012-05-17T19:08:20+02:00 newtype-wrap Doc nodes for things that may have warnings attached - - - - - e3a89fc3 by Simon Hengel at 2012-05-17T19:08:20+02:00 Attach warnings to `Documentation` type - - - - - 5d4cc43d by Simon Hengel at 2012-05-17T19:08:20+02:00 Simplify lookupWarning - - - - - cf8ae69d by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for haskell/haddock#205 - - - - - cb409b19 by Simon Peyton Jones at 2012-05-25T08:30:11+01:00 Follow changes in LHsTyVarBndrs - - - - - 2d5f4179 by Simon Hengel at 2012-05-26T19:21:29+02:00 Add Applicative instance for (GenRnM a) - - - - - e4373060 by Simon Hengel at 2012-05-26T19:21:33+02:00 Use a map for warnings, as suggested by @waern - - - - - 597a68c7 by Simon Hengel at 2012-05-27T08:48:24+02:00 Add an optional label to URLs - - - - - ef1ac7fe by Simon Hengel at 2012-05-27T08:48:24+02:00 Add support for hyperlink labels to parser - - - - - 41f2adce by Simon Hengel at 2012-05-27T08:48:24+02:00 Add golden test for hyperlinks - - - - - 83d5e764 by Simon Hengel at 2012-05-27T08:50:02+02:00 Use LANGUAGE pragmas instead of default-extensions in cabal file - - - - - ddb755e5 by Simon Hengel at 2012-05-27T08:50:02+02:00 Fix typo in comment - - - - - 110676b4 by Simon Hengel at 2012-05-27T08:50:02+02:00 Add a type signature for a where-binding - - - - - 7d9ba2a0 by Ian Lynagh at 2012-06-12T14:38:01+01:00 Follow changes in GHC - - - - - 47c704f2 by Ian Lynagh at 2012-06-12T18:52:16+01:00 Follow changes in GHC - - - - - e1efe1ab by Simon Peyton Jones at 2012-06-13T17:25:29+01:00 Follow changes for the implementation of implicit parameters - - - - - 69abc81c by Ian Lynagh at 2012-06-19T22:52:58+01:00 Follow changes in base - - - - - 9d074a21 by Paolo Capriotti at 2012-06-22T18:26:47+01:00 Use right docMap to get decl documentation. - - - - - e3292ef6 by Ian Lynagh at 2012-07-15T01:31:19+01:00 Follow changes in GHC - - - - - ceae56b0 by Ian Lynagh at 2012-07-16T21:22:48+01:00 Fix haddock following some GHC changes Passing _|_ as the Settings for defaultDynFlags no longer works well enough - - - - - 9df72735 by Paolo Capriotti at 2012-07-19T16:49:32+01:00 Forward port changes from stable. - - - - - 572f5fcf by Ian Lynagh at 2012-07-19T20:38:26+01:00 Merge branch 'master' of darcs.haskell.org:/srv/darcs//haddock - - - - - 9195aca4 by Paolo Capriotti at 2012-07-20T10:27:28+01:00 Update dependencies. - - - - - 33db3923 by Ian Lynagh at 2012-07-20T17:54:43+01:00 Build with GHC 7.7 - - - - - 925a2cea by David Waern at 2012-07-23T16:50:40+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.6 Conflicts: src/Haddock/InterfaceFile.hs - - - - - d710ef97 by David Waern at 2012-07-23T16:52:07+02:00 Bump version number. - - - - - eb0c2f83 by David Waern at 2012-07-23T16:57:58+02:00 Update CHANGES. - - - - - b3f56943 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Hide "internal" instances This fixes haskell/haddock#37 (http://trac.haskell.org/haddock/ticket/37) Precisely, we show an instance iff its class and all the types are exported by non-hidden modules. - - - - - a70aa412 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Tests for hiding instances (#37) - - - - - c0f4aa58 by Simon Hengel at 2012-07-27T13:00:13+03:00 Add an other test for hiding instances (#37) - - - - - a7ed6268 by Ian Lynagh at 2012-08-07T14:48:13+01:00 Follow changes in GHC - - - - - 0ab30d38 by Ian Lynagh at 2012-08-13T22:12:27+01:00 Improve haddock memory usage - - - - - 0eaa4e30 by Ian Lynagh at 2012-08-13T23:58:46+01:00 Improve haddock memory usage - - - - - 659d26cf by Ian Lynagh at 2012-08-14T13:16:48+01:00 Remove some temporary pragmas I accidentally recorded - - - - - d97fceb6 by Simon Hengel at 2012-08-25T13:19:34+02:00 Add missing dependency to library - - - - - 4c910697 by Simon Hengel at 2012-08-28T07:39:14+02:00 Move .ghci to project root - - - - - fc3c601a by Simon Hengel at 2012-08-28T07:39:14+02:00 accept.hs: Ignore some files - - - - - 1af9b984 by Simon Hengel at 2012-08-28T07:40:04+02:00 Update reference renderings (bump version) - - - - - 980dc253 by Simon Hengel at 2012-08-28T07:40:32+02:00 Update reference renderings (remove links for ()) - - - - - 33651dbf by Simon Hengel at 2012-08-28T07:41:50+02:00 Update documentation of `runInteractiveProcess` in reference rendering - - - - - 7ab25078 by David Waern at 2012-09-07T10:38:50+02:00 Merge branch 'hiddenInstances2' of http://github.com/feuerbach/haddock into ghc-7.6 - - - - - c3de3a4b by David Waern at 2012-09-07T14:29:27+02:00 Follow changes in GHC. - - - - - 298c43ac by David Waern at 2012-09-07T14:59:24+02:00 Update CHANGES. - - - - - e797993a by David Waern at 2012-09-07T15:21:30+02:00 Update ANNOUNCE. - - - - - d0b44790 by David Waern at 2012-09-07T15:22:43+02:00 Merge branch 'hidden-instances' into ghc-7.6 - - - - - 41a4adc8 by Simon Hengel at 2012-09-08T12:08:37+02:00 Update doc/README - - - - - 71ad1040 by Simon Hengel at 2012-09-08T12:17:17+02:00 Add documentation for URL labels - - - - - 9bb41afd by Simon Peyton Jones at 2012-09-20T18:14:26+01:00 Follow data type changes in the tc-untouchables branch Relating entirely to SynTyConRhs - - - - - b8139bfa by Simon Hengel at 2012-09-21T14:24:16+02:00 Disable Unicode test for now - - - - - a5fafdd7 by Simon Hengel at 2012-09-21T14:35:45+02:00 Update TypeOperators test for GHC 7.6.1 Type operators can't be used as type variables anymore! - - - - - 6ccf0025 by Simon Hengel at 2012-09-21T16:02:24+02:00 Remove (Monad (Either e)) instance from ref. rendering of CrossPackageDocs I do not really understand why the behavior changed, so I'll open a ticket, so that we can further investigate. - - - - - b5c6c138 by Ian Lynagh at 2012-09-27T02:00:57+01:00 Follow changes in GHC build system - - - - - b98eded0 by David Waern at 2012-09-27T15:37:02+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 76cc2051 by David Waern at 2012-09-27T15:48:19+02:00 Update hidden instances tests. - - - - - aeaa1c59 by David Waern at 2012-09-28T10:21:32+02:00 Make API buildable with GHC 7.6. - - - - - d76be1b0 by Simon Peyton Jones at 2012-09-28T15:57:05+01:00 Merge remote-tracking branch 'origin/master' into tc-untouchables - - - - - a1922af8 by David Waern at 2012-09-28T19:50:20+02:00 Fix spurious superclass constraints bug. - - - - - bc41bdbb by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove old examples - - - - - bed7d3dd by Simon Hengel at 2012-10-01T11:30:51+02:00 Adapt parsetests for GHC 7.6.1 - - - - - dcdb22bb by Simon Hengel at 2012-10-01T11:30:51+02:00 Add test-suite section for parsetests to cabal file + get rid of HUnit dependency - - - - - 1e5263c9 by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove test flag from cabal file This was not really used. - - - - - 4beee98b by David Waern at 2012-09-28T23:42:28+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 11dd2256 by Ian Lynagh at 2012-10-03T16:17:35+01:00 Follow change in GHC build system - - - - - fbd77962 by Simon Hengel at 2012-10-03T18:49:40+02:00 Remove redundant dependency from cabal file - - - - - 09218989 by Simon Hengel at 2012-10-04T16:03:05+02:00 Fix typo - - - - - 93a2d5f9 by Simon Hengel at 2012-10-04T16:11:41+02:00 Remove trailing whitespace from cabal file - - - - - c8b46cd3 by Simon Hengel at 2012-10-04T16:12:17+02:00 Export Haddock's main entry point from library - - - - - b411e77b by Simon Hengel at 2012-10-04T16:29:46+02:00 Depend on library for executable The main motivation for this is to increase build speed. In GHC's source tree the library is not build, but all modules are now required for the executable, so that GHC's validate will now detect build failures for the library. - - - - - f8f0979f by Simon Hengel at 2012-10-05T00:32:57+02:00 Set executable flag for Setup.lhs - - - - - dd045998 by Simon Hengel at 2012-10-07T16:44:06+02:00 Extend rather than set environment when running HTML tests On some platforms (e.g. ppc64) GHC requires gcc in the path. - - - - - 7b39c3ae by Simon Hengel at 2012-10-07T17:05:45+02:00 cross-package test: re-export IsString instead of Monad There is a monad instance for Q, which is not available on platforms that do not have GHCi support. This caused CrossPackageDocs to fail on those platforms. Re-exporting IsString should test the same thing, but it works on all platforms. - - - - - 0700c605 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Fix some warnings - - - - - f78eca79 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Make -Wall proof - - - - - 6beec041 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Use listToMaybe/fromMaybe instead of safeHead/maybe - - - - - 44b8ce86 by Ian Lynagh at 2012-10-08T21:59:46+01:00 Follow changes in GHC - - - - - 6da5f702 by Simon Hengel at 2012-10-09T11:16:19+02:00 Update .ghci - - - - - 9ac1a1b9 by Kazu Yamamoto at 2012-10-09T12:45:31+02:00 Add markup support for properties - - - - - 1944cb42 by Simon Hengel at 2012-10-09T12:45:31+02:00 Simplify lexing/parsing of properties In contrast to what we do for examples, we do not really need to capture the "prompt" here. - - - - - bffd8e62 by Simon Hengel at 2012-10-09T13:40:14+02:00 Add HTML test for properties - - - - - 2fe9c5cb by Simon Hengel at 2012-10-09T13:40:21+02:00 Add unit tests for properties - - - - - 874e361b by Simon Hengel at 2012-10-09T13:40:33+02:00 Bump interface version - - - - - 2506cc37 by Simon Hengel at 2012-10-09T15:15:04+02:00 Fix parser bug - - - - - 743d2b7d by Simon Hengel at 2012-10-09T15:31:06+02:00 Allow to load interface files with compatible versions - - - - - 981a1660 by Simon Hengel at 2012-10-10T10:32:05+02:00 Export more types from Documentation.Haddock (fixes haskell/haddock#216) - - - - - dff7dc76 by Simon Hengel at 2012-10-10T11:15:19+02:00 Update ANNOUNCE and CHANGES - - - - - edd2bb01 by Simon Hengel at 2012-10-10T11:22:50+02:00 Bump version - - - - - 5039163b by Simon Hengel at 2012-10-10T13:56:04+02:00 Fix typo in documentation - - - - - e4ce34da by Simon Hengel at 2012-10-10T14:28:35+02:00 Add documentation for properties - - - - - 9555ebca by Simon Hengel at 2012-10-11T10:49:04+02:00 Remove redundant if-defs, more source documentation - - - - - 87aa67e1 by Simon Hengel at 2012-10-11T12:32:51+02:00 Adapt cabal file - - - - - c44c1dee by Simon Hengel at 2012-10-11T12:41:58+02:00 Require ghc 7.6 - - - - - 8383bc34 by Simon Hengel at 2012-10-11T12:50:24+02:00 Bump version - - - - - 1030eb38 by Simon Hengel at 2012-10-11T12:55:44+02:00 Update ANNOUNCE and CHANGES - - - - - 74955088 by Simon Hengel at 2012-10-12T09:49:31+02:00 Improve note about `binaryInterfaceVersion` (thanks David) - - - - - ee30f6b7 by Simon Hengel at 2012-10-13T13:40:59+02:00 Update version in html tests, rpm spec file, and user manual - - - - - f2861f18 by Simon Hengel at 2012-10-13T14:40:33+02:00 Remove unused MonadFix constraint - - - - - dfdf1a74 by Simon Hengel at 2012-10-13T15:15:38+02:00 Minor code simplification - - - - - 4ecd1e70 by Simon Hengel at 2012-10-13T15:33:43+02:00 Increase code locality - - - - - f7df5cc9 by Simon Hengel at 2012-10-13T16:03:12+02:00 Minor code simplification - - - - - e737eb6e by Simon Hengel at 2012-10-13T19:03:04+02:00 Handle HsExplicitListTy in renameer (fixes haskell/haddock#213) - - - - - c2dc8f17 by Simon Hengel at 2012-10-13T20:46:31+02:00 Better error messages - - - - - 14d48b4c by Simon Hengel at 2012-10-14T00:21:07+02:00 Simplify RnM type - - - - - 6c2cc547 by Simon Hengel at 2012-10-14T00:23:35+02:00 Simplify lookupRn - - - - - bc77ce85 by Simon Hengel at 2012-10-14T01:51:32+02:00 Organize unite tests hierarchically - - - - - 2306d117 by Simon Hengel at 2012-10-14T10:34:58+02:00 Handle more cases in renameType - - - - - 8a864203 by Simon Hengel at 2012-10-14T11:47:59+02:00 Add mini_HiddenInstances.html.ref and mini_HiddenInstancesB.html.ref - - - - - 3a978eca by Simon Hengel at 2012-10-14T11:49:28+02:00 Add /tests/html-tests/output/ to .gitignore - - - - - db18888a by Simon Hengel at 2012-10-14T13:38:21+02:00 Allow haddock markup in deprecation messages - - - - - e7cfee9f by Simon Hengel at 2012-10-14T14:00:23+02:00 If parsing of deprecation message fails, include it verbatim - - - - - 242a85be by Simon Hengel at 2012-10-14T14:13:24+02:00 Add description for PruneWithWarning test - - - - - 43d33df1 by Simon Hengel at 2012-10-14T15:40:53+02:00 Minor formatting change - - - - - 22768c44 by Simon Hengel at 2012-10-14T16:03:43+02:00 Properly handle deprecation messages for re-exported things (fixes haskell/haddock#220) - - - - - cb4b9111 by Simon Hengel at 2012-10-14T17:30:28+02:00 Add build artifacts for documentation to .gitignore - - - - - 854cd8de by Simon Hengel at 2012-10-14T23:34:51+02:00 unit-tests: Improve readability Add IsString instance for (Doc RdrName) + use <> instead of DocAppend. - - - - - c4446d54 by Simon Hengel at 2012-10-14T23:37:21+02:00 unit-tests: Minor refactoring Rename parse to parseParas. - - - - - 04f2703c by Simon Hengel at 2012-10-15T00:36:42+02:00 Fix typo - - - - - 3d109e44 by Simon Hengel at 2012-10-15T10:30:07+02:00 Add description for DeprecatedReExport test - - - - - 84f0985c by Simon Hengel at 2012-10-15T14:54:19+02:00 Move resources to /resources directory - - - - - a5de7ca6 by Simon Hengel at 2012-10-15T15:46:18+02:00 Move HTML tests to directory /html-test/ - - - - - e21f727d by Simon Hengel at 2012-10-15T19:32:42+02:00 Move HTML reference renderings to /html-test/ref/ - - - - - 3a3c6c75 by Simon Hengel at 2012-10-15T19:32:42+02:00 Copy css, images, etc. on accept - - - - - 40ead6dc by Simon Hengel at 2012-10-15T19:32:42+02:00 Move unit tests to /test directory - - - - - 99a28231 by Simon Hengel at 2012-10-15T19:32:42+02:00 Fix Setup.lhs /usr/bin/runhaskell is not installed on all systems. - - - - - 95faf45e by Simon Hengel at 2012-10-15T19:32:42+02:00 Make test management scripts more robust * They are now independent from the current directory, and hence can be called from everywhere * On UNIX/Linux they can now be run as scripts - - - - - 027aaa2d by Simon Hengel at 2012-10-15T19:53:40+02:00 Add 'dev' flag to cabal file, that builds without -O2 That way --disable-optimization can be used, which decreases build time considerably. - - - - - e0266ede by Simon Hengel at 2012-10-15T20:03:43+02:00 Add test case for "spurious superclass constraints bug" - - - - - 52a2aa92 by Simon Hengel at 2012-10-15T20:28:55+02:00 Adapt accept.lhs, so that it ignores more index files - - - - - 53530781 by Simon Hengel at 2012-10-15T20:49:39+02:00 Rename html-test/runtests.lhs to html-test/run.lhs - - - - - 84518797 by Simon Hengel at 2012-10-15T20:49:39+02:00 Move source files for HTML tests to html-test/src - - - - - a911dc6c by Simon Hengel at 2012-10-15T20:49:39+02:00 Adapt output directory for HTML tests - - - - - d3c15857 by Ian Lynagh at 2012-10-16T16:54:43+01:00 Follow dopt->gopt rename - - - - - 956665a5 by Simon Hengel at 2012-10-18T08:42:48+02:00 Update html-test/README - - - - - 903b1029 by Simon Hengel at 2012-10-18T08:50:26+02:00 Use markdown for html-test/README - - - - - 150b4d63 by Ian Lynagh at 2012-10-18T16:36:00+01:00 Follow changes in GHC: 'flags' has been renamed 'generalFlags' - - - - - 41e04ff9 by Simon Hengel at 2012-11-28T09:54:35+01:00 Export missing types from Documentation.Haddock - - - - - 9be59237 by Ian Lynagh at 2012-11-30T23:20:47+00:00 Update dependencies - - - - - e06842f5 by Simon Hengel at 2012-12-07T20:58:05+01:00 Bump version - - - - - e3dbede0 by Simon Hengel at 2012-12-07T20:58:05+01:00 Add missing test files to cabal file (fixes haskell/haddock#230) - - - - - ee0dcca7 by Simon Hengel at 2012-12-07T20:58:05+01:00 Update CHANGES - - - - - 51601bdb by Simon Peyton Jones at 2012-12-19T17:28:35+00:00 Track changes in UNPACK pragma stuff - - - - - f2573bc1 by Richard Eisenberg at 2012-12-21T20:56:25-05:00 Implement overlapping type family instances. An ordered, overlapping type family instance is introduced by 'type instance where', followed by equations. See the new section in the user manual (7.7.2.2) for details. The canonical example is Boolean equality at the type level: type family Equals (a :: k) (b :: k) :: Bool type instance where Equals a a = True Equals a b = False A branched family instance, such as this one, checks its equations in order and applies only the first the matches. As explained in the note [Instance checking within groups] in FamInstEnv.lhs, we must be careful not to simplify, say, (Equals Int b) to False, because b might later unify with Int. This commit includes all of the commits on the overlapping-tyfams branch. SPJ requested that I combine all my commits over the past several months into one monolithic commit. The following GHC repos are affected: ghc, testsuite, utils/haddock, libraries/template-haskell, and libraries/dph. Here are some details for the interested: - The definition of CoAxiom has been moved from TyCon.lhs to a new file CoAxiom.lhs. I made this decision because of the number of definitions necessary to support BranchList. - BranchList is a GADT whose type tracks whether it is a singleton list or not-necessarily-a-singleton-list. The reason I introduced this type is to increase static checking of places where GHC code assumes that a FamInst or CoAxiom is indeed a singleton. This assumption takes place roughly 10 times throughout the code. I was worried that a future change to GHC would invalidate the assumption, and GHC might subtly fail to do the right thing. By explicitly labeling CoAxioms and FamInsts as being Unbranched (singleton) or Branched (not-necessarily-singleton), we make this assumption explicit and checkable. Furthermore, to enforce the accuracy of this label, the list of branches of a CoAxiom or FamInst is stored using a BranchList, whose constructors constrain its type index appropriately. I think that the decision to use BranchList is probably the most controversial decision I made from a code design point of view. Although I provide conversions to/from ordinary lists, it is more efficient to use the brList... functions provided in CoAxiom than always to convert. The use of these functions does not wander far from the core CoAxiom/FamInst logic. BranchLists are motivated and explained in the note [Branched axioms] in CoAxiom.lhs. - The CoAxiom type has changed significantly. You can see the new type in CoAxiom.lhs. It uses a CoAxBranch type to track branches of the CoAxiom. Correspondingly various functions producing and consuming CoAxioms had to change, including the binary layout of interface files. - To get branched axioms to work correctly, it is important to have a notion of type "apartness": two types are apart if they cannot unify, and no substitution of variables can ever get them to unify, even after type family simplification. (This is different than the normal failure to unify because of the type family bit.) This notion in encoded in tcApartTys, in Unify.lhs. Because apartness is finer-grained than unification, the tcUnifyTys now calls tcApartTys. - CoreLinting axioms has been updated, both to reflect the new form of CoAxiom and to enforce the apartness rules of branch application. The formalization of the new rules is in docs/core-spec/core-spec.pdf. - The FamInst type (in types/FamInstEnv.lhs) has changed significantly, paralleling the changes to CoAxiom. Of course, this forced minor changes in many files. - There are several new Notes in FamInstEnv.lhs, including one discussing confluent overlap and why we're not doing it. - lookupFamInstEnv, lookupFamInstEnvConflicts, and lookup_fam_inst_env' (the function that actually does the work) have all been more-or-less completely rewritten. There is a Note [lookup_fam_inst_env' implementation] describing the implementation. One of the changes that affects other files is to change the type of matches from a pair of (FamInst, [Type]) to a new datatype (which now includes the index of the matching branch). This seemed a better design. - The TySynInstD constructor in Template Haskell was updated to use the new datatype TySynEqn. I also bumped the TH version number, requiring changes to DPH cabal files. (That's why the DPH repo has an overlapping-tyfams branch.) - As SPJ requested, I refactored some of the code in HsDecls: * splitting up TyDecl into SynDecl and DataDecl, correspondingly changing HsTyDefn to HsDataDefn (with only one constructor) * splitting FamInstD into TyFamInstD and DataFamInstD and splitting FamInstDecl into DataFamInstDecl and TyFamInstDecl * making the ClsInstD take a ClsInstDecl, for parallelism with InstDecl's other constructors * changing constructor TyFamily into FamDecl * creating a FamilyDecl type that stores the details for a family declaration; this is useful because FamilyDecls can appear in classes but other decls cannot * restricting the associated types and associated type defaults for a * class to be the new, more restrictive types * splitting cid_fam_insts into cid_tyfam_insts and cid_datafam_insts, according to the new types * perhaps one or two more that I'm overlooking None of these changes has far-reaching implications. - The user manual, section 7.7.2.2, is updated to describe the new type family instances. - - - - - f788d0fb by Simon Peyton Jones at 2012-12-23T15:49:58+00:00 Track changes in HsBang - - - - - ca460a0c by Simon Peyton Jones at 2012-12-23T15:50:28+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - f078fea6 by Simon Peyton Jones at 2013-01-02T08:33:13+00:00 Use InstEnv.instanceSig rather than instanceHead (name change) - - - - - 88e41305 by Simon Peyton Jones at 2013-01-14T17:10:27+00:00 Track change to HsBang type - - - - - e1ad4e19 by Kazu Yamamoto at 2013-02-01T11:59:24+09:00 Merge branch 'ghc-7.6' into ghc-7.6-merge-2 Conflicts: haddock.cabal src/Haddock/Interface/AttachInstances.hs src/Haddock/Interface/Create.hs src/Haddock/Interface/LexParseRn.hs src/Haddock/InterfaceFile.hs src/Haddock/Types.hs Only GHC HEAD can compile this. GHC 7.6.x cannot compile this. Some test fail. - - - - - 62bec012 by Kazu Yamamoto at 2013-02-06T11:12:28+09:00 Using tcSplitSigmaTy in instanceHead' (FIXME is resolved.) - - - - - 013fd2e4 by Kazu Yamamoto at 2013-02-06T17:56:21+09:00 Refactoring instanceHead'. - - - - - 3148ce0e by Kazu Yamamoto at 2013-02-07T17:45:10+09:00 Using new syntax in html-test/src/GADTRecords.hs. - - - - - 626dabe7 by Gabor Greif at 2013-02-15T22:42:01+01:00 Typo - - - - - 1eb667ae by Ian Lynagh at 2013-02-16T17:02:07+00:00 Follow changes in base - - - - - 3ef8253a by Ian Lynagh at 2013-03-01T23:23:57+00:00 Follow changes in GHC's build system - - - - - 1a265a3c by Ian Lynagh at 2013-03-03T23:12:07+00:00 Follow changes in GHC build system - - - - - 69941c79 by Max Bolingbroke at 2013-03-10T09:38:28-07:00 Use Alex 3's Unicode support to properly lex source files as UTF-8 Signed-off-by: David Waern <david.waern at gmail.com> - - - - - ea687dad by Simon Peyton Jones at 2013-03-15T14:16:10+00:00 Adapt to tcRnGetInfo returning family instances too This API change was part of the fix to Trac haskell/haddock#4175. But it offers new information to Haddock: the type-family instances, as well as the class instances, of this type. This patch just drops the new information on the floor, but there's an open opportunity to use it in the information that Haddock displays. - - - - - 971a30b0 by Andreas Voellmy at 2013-05-19T20:47:39+01:00 Fix for haskell/haddock#7879. Changed copy of utils/haddock/html/resources/html to use "cp -RL" rather than "cp -R". This allows users to run validate in a build tree, where the build tree was setup using lndir with a relative path to the source directory. - - - - - 31fb7694 by Ian Lynagh at 2013-05-19T20:47:49+01:00 Use "cp -L" when making $(INPLACE_LIB)/latex too - - - - - e9952233 by Simon Hengel at 2013-06-01T18:06:50+02:00 Add -itest to .ghci - - - - - b06873b3 by Mateusz Kowalczyk at 2013-06-01T18:06:50+02:00 Workaround for a failing build with --enable-tests. - - - - - e7858d16 by Simon Hengel at 2013-06-01T19:29:28+02:00 Fix broken test - - - - - 0690acb1 by Richard Eisenberg at 2013-06-21T14:08:25+01:00 Updates to reflect changes in HsDecls to support closed type families. - - - - - 7fd347ec by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 53ed81b6 by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 931c4f4f by Richard Eisenberg at 2013-07-24T13:15:59+01:00 Remove (error "synifyKind") to use WithinType, to allow haddock to process base. - - - - - 55a9c804 by Richard Eisenberg at 2013-08-02T15:54:55+01:00 Changes to reflect changes in GHC's type HsTyVarBndr - - - - - b6e9226c by Mathieu Boespflug at 2013-08-04T10:39:43-07:00 Output Copright and License keys in Xhtml backend. This information is as relevant in the documentation as it is in the source files themselves. Signed-off-by: David Waern <david.waern at gmail.com> - - - - - 4c66028a by David Waern at 2013-08-04T15:27:36-07:00 Bump interface file version. - - - - - 67340163 by David Waern at 2013-08-09T16:12:51-07:00 Update tests. - - - - - 2087569b by Mateusz Kowalczyk at 2013-08-25T09:24:13+02:00 Add spec tests. This adds tests for all elements we can create during regular parsing. This also adds tests for text with unicode in it. - - - - - 97f36a11 by Mateusz Kowalczyk at 2013-08-27T06:59:12+01:00 Fix ticket haskell/haddock#247. I do the same thing that the XHTML backend does: give these no special treatment and just act as if they are regular functions. - - - - - 60681b4f by Mateusz Kowalczyk at 2013-08-27T21:22:48+02:00 LaTeX tests setup - - - - - fa4c27b2 by Mateusz Kowalczyk at 2013-09-02T23:21:43+01:00 Fixes haskell/haddock#253 - - - - - 1a202490 by Mateusz Kowalczyk at 2013-09-03T01:12:50+01:00 Use Hspec instead of nanospec This is motivated by the fact that Haddock tests are not ran by the GHC's ‘validate’ script so we're pretty liberal on dependencies in that area. Full Hspec gives us some nice features such as Quickcheck integration. - - - - - 8cde3b20 by David Luposchainsky at 2013-09-08T07:27:28-05:00 Fix AMP warnings Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - d10661f2 by Herbert Valerio Riedel at 2013-09-11T15:15:01+02:00 Update Git repo URL in `.cabal` file - - - - - 16a44eb5 by Richard Eisenberg at 2013-09-17T09:34:26-04:00 Revision to reflect new role annotation syntax in GHC. - - - - - 4b9833b9 by Herbert Valerio Riedel at 2013-09-18T10:15:28+02:00 Add missing `traverse` method for `GenLocated` As `Traversable` needs at least one of `traverse` or `sequenceA` to be overridden. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - b71fed5d by Simon Hengel at 2013-09-18T22:43:34+02:00 Add test helper - - - - - 4fc1ea86 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#231 - - - - - 435872f6 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#256 We inject -dynamic-too into flags before we run all our actions in the GHC monad. - - - - - b8b24abb by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Add new field to DynFlags - - - - - 49558795 by Simon Hengel at 2013-09-18T22:43:35+02:00 Fallback to ./resources when Cabal data is not found (so that themes are found during development) - - - - - bf79d05c by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Fixes haskell/haddock#5 - - - - - e1baebc2 by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Print missing documentation. Fixes haskell/haddock#258. - - - - - 02ea74de by Austin Seipp at 2013-10-09T10:52:22-05:00 Don't consider StaticFlags when parsing arguments. Instead, discard any static flags before parsing the command line using GHC's DynFlags parser. See http://ghc.haskell.org/trac/ghc/ticket/8276 Based off a patch from Simon Hengel. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 704fd5bb by Simon Hengel at 2013-11-09T00:15:13+01:00 Update HTML tests - - - - - f9fed49e by Simon Hengel at 2013-11-10T18:43:58+01:00 Bump version - - - - - 97ae1999 by Simon Peyton Jones at 2013-11-25T17:25:14+00:00 Track changes in HsSpliceTy data constructor - - - - - 59ad8268 by Simon Peyton Jones at 2014-01-10T18:17:43+00:00 Adapt to small change in Pretty's exports - - - - - 8b12e6aa by Simon Hengel at 2014-01-12T14:48:35-06:00 Some code simplification by using traverse - - - - - fc5ea9a2 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix warnings in test helper - - - - - 6dbb3ba5 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Add ByteString version of Attoparsec - - - - - 968d7774 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 One pass parser and tests. We remove the HTML test as it is no longer necessary. We cover the test case in spec tests and other HTML tests but keeping this around fails: this is because the new parser has different semantics there. In fact, I suspect the original behaviour was a bug that wasn't caught/fixed but simply included as-is during the testing. - - - - - 37a07c9c by Simon Hengel at 2014-01-12T14:48:35-06:00 Rename Haddock.ParseSpec to Haddock.ParserSpec - - - - - f0f68fe9 by Simon Hengel at 2014-01-12T14:48:35-06:00 Don't append newline to parseString input We also check that we have parsed everything with endOfInput. - - - - - 95d60093 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix totality, unicode, examples, paragraph parsing Also simplify specs and parsers while we're at it. Some parsers were made more generic. This commit is a part of GHC pre-merge squash, email fuuzetsu at fuuzetsu.co.uk if you need the full commit history. - - - - - 7d99108c by Simon Hengel at 2014-01-12T14:48:35-06:00 Update acceptance tests - - - - - d1b59640 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Support for bold. Conflicts: src/Haddock/Backends/Hoogle.hs src/Haddock/Interface/Rename.hs src/Haddock/Parser.hs - - - - - 4b412b39 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Allow for headings inside function documentation. LaTeX will treat the h3-h6 headings the same as we'd have to hack the style file heavily otherwise and it would make the headings tiny anyway. Hoogle upstream said they will put in the functionality on their end. Conflicts: src/Haddock/Interface/Rename.hs src/Haddock/Types.hs test/Haddock/ParserSpec.hs - - - - - fdcca428 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Per-module extension flags and language listing. Any extensions that are not enabled by a used language (Haskell2010 &c) will be shown. Furthermore, any implicitly enabled are also going to be shown. While we could eliminate this either by using the GHC API or a dirty hack, I opted not to: if a user doesn't want the implied flags to show, they are recommended to use enable extensions more carefully or individually. Perhaps this will encourage users to not enable the most powerful flags needlessly. Enabled with show-extensions. Conflicts: src/Haddock/InterfaceFile.hs - - - - - 368942a2 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Bump interface version There were some breaking changes over the last few patches so we bump the interface version. This causes a big problem with testing: 1. To generate cross package docs, we first need to generate docs for the package used. 2. To generate package docs with new interface version, we need to use Haddock which has the version bumped. 3. To get Haddock with the version bump, we first need to test cross package docs 4. GOTO 1 So the problem is the chicken and the egg problem. It seems that the only solution would be to generate some interface files on the fly but it is non-trivial. To run this test, you'll have to: * build Haddock without the test (make sure everything else passes) * rebuild the packages used in the test with your shiny new binary making sure they are visible to Haddock * remove the ‘_hidden’ suffix and re-run the tests Note: because the packages currently used for this test are those provided by GHC, it's probably non-trivial to just re-build them. Preferably something less tedious to rebuild should be used and something that is not subject to change. - - - - - 124ae7a9 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow for nesting of paragraphs under lists. The nesting rules are similar to Markdown's with the exception that we can not simply indent the first line of a hard wrapped indented paragraph and have it treated as if it was fully indented. The reason is differences in markup as some of our constructs care about whitespace while others just swallow everything up so it's just a lot easier to not bother with it rather than making arbitrary rules. Note that we now drop trailing for string entities inside of lists. They weren't needed and it makes the output look uniform whether we use a single or double newline between list elements. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - c7913535 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow escaping in URLs and pictures. Some tests were moved under parseString as they weren't about paragraph level markup. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - 32326680 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update documentation. - - - - - fbef6406 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update maintainer - - - - - b40e82f4 by Mateusz Kowalczyk at 2014-01-13T02:39:25-06:00 Fixes haskell/haddock#271 Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - f4eafbf8 by Gergő Érdi at 2014-01-19T15:35:16-06:00 Support for -XPatternSynonyms Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - a8939591 by Austin Seipp at 2014-01-29T08:09:04-06:00 Update CPP check for __GLASGOW_HASKELL__ Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 30d7e9d5 by Gergő Érdi at 2014-01-31T00:15:01+08:00 <+>: Don't insert a space when concatenating empty nodes - - - - - a25ccd4d by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Fix @ code blocks In cases where we had some horizontal space before the closing ‘@’, the parser would not accept the block as a code block and we'd get ugly output. - - - - - 0f67305a by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Update tests This updates tests due to Haddock Trac haskell/haddock#271 fix and due to removal of TypeHoles as an extension from GHC. - - - - - 157322a7 by Gergő Érdi at 2014-01-31T01:03:17+08:00 Handle infix vs prefix names correctly everywhere, by explicitly specifying the context The basic idea is that "a" and "+" are either pretty-printed as "a" and "(+)" or "`a`" and "+" - - - - - aa6d9685 by Mateusz Kowalczyk at 2014-01-30T17:21:50+00:00 Correct whitespace in ‘hidden’ test for <+> change - - - - - 121872f0 by Mateusz Kowalczyk at 2014-02-09T17:59:12+00:00 Document module header. Fixes Haddock Trac haskell/haddock#270. - - - - - e3253746 by Mateusz Kowalczyk at 2014-02-10T21:37:48+00:00 Insert a space between module link and description Fixes Haddock Trac haskell/haddock#277. - - - - - 771d2384 by Mateusz Kowalczyk at 2014-02-10T23:27:21+00:00 Ensure a space between type signature and ‘Source’ This is briefly related to Haddock Trac haskell/haddock#249 and employs effectively the suggested fix _but_ it doesn't actually fix the reported issue. This commit simply makes copying the full line a bit less of a pain. - - - - - 8cda9eff by nand at 2014-02-11T15:48:30+00:00 Add support for type/data families This adds support for type/data families with their respective instances, as well as closed type families and associated type/data families. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 3f22c510 by nand at 2014-02-11T15:53:50+00:00 Improve display of poly-kinded type operators This now displays them as (==) k a b c ... to mirror GHC's behavior, instead of the old (k == a) b c ... which was just wrong. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - effb2d6b by nand at 2014-02-11T15:56:50+00:00 Add test case for PatternSynonyms This just tests various stuff including poly-kinded patterns and operator patterns to make sure the rendering isn't broken. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - b38faf0d by Niklas Haas at 2014-02-13T21:53:32+00:00 Get rid of re-implementation of sortBy I have no idea what this was doing lying around here, and due to the usage of tuples it's actually slower, too. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - ac1e0413 by Mateusz Kowalczyk at 2014-02-13T23:57:16+00:00 Only warn about missing docs when docs are missing This fixes the ‘Missing documentation for…’ message for modules with 100% coverage. - - - - - cae2e36a by Niklas Haas at 2014-02-15T21:56:18+00:00 Add test case for inter-module type/data family instances These should show up in every place where the class is visible, and indeed they do right now. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 8bea5c3a by Mateusz Kowalczyk at 2014-02-19T05:11:34+00:00 Use a bespoke data type to indicate fixity This deals with what I imagine was an ancient TODO and makes it much clearer what the argument actually does rather than having the user chase down the comment. - - - - - 5b52d57c by Niklas Haas at 2014-02-22T21:31:03+01:00 Strip a single leading space from bird tracks (#201) This makes bird tracks in the form > foo > bar > bat parse as if they had been written as >foo >bar >bat ie. without the leading whitespace in front of every line. Ideally we also want to look into how leading whitespace affects code blocks written using the @ @ syntax, which are currently unaffected by this patch. - - - - - 5a1315a5 by Simon Hengel at 2014-02-22T21:55:35+01:00 Turn a source code comment into specs - - - - - 784cfe58 by Mateusz Kowalczyk at 2014-02-23T05:02:22+00:00 Update test case for lifted GADT type rendering The parsing of these seems to have been fixed by GHC folk and it now renders differently. IMHO it now renders in a better way so I'm updating the test to reflect this. - - - - - c3c88c2f by Mateusz Kowalczyk at 2014-02-23T06:37:14+00:00 Don't shadow ‘strip’. -Wall complains - - - - - 293031d8 by Niklas Haas at 2014-02-23T15:21:52+01:00 Make ImplicitParams render correctly (#260) This introduces a new precedence level for single contexts (because implicit param contexts always need parens around them, but other types of contexts don't necessarily, even when alone) - - - - - 4200842d by Niklas Haas at 2014-02-23T15:37:13+01:00 Lower precedence of equality constraints This drops them to the new precedence pREC_CTX, which makes single eqaulity constraints show up as (a ~ b) => ty, in line with GHC's rendering. Additional tests added to make sure other type operators render as intended. Current behavior matches GHC - - - - - b59e3227 by Niklas Haas at 2014-02-23T16:11:22+01:00 Add RankNTypes test case to ImplicitParams.hs This test actually tests what haskell/haddock#260 originally reported - I omitted the RankNTypes scenario from the original fix because I realized it's not relevant to the underlying issue and indeed, this renders as intended now. Still good to have more tests. - - - - - c373dbf7 by Mateusz Kowalczyk at 2014-02-24T06:09:54+00:00 Fix rendering of Contents when links are present Fixes Haddock Trac haskell/haddock#267. - - - - - 9ecb0e56 by Mateusz Kowalczyk at 2014-02-24T06:26:50+00:00 Fix wording in the docs - - - - - 4f4dcd8e by Mateusz Kowalczyk at 2014-02-27T03:00:33+00:00 Change rendering of duplicate record field docs See Haddock Trac haskell/haddock#195. We now change this behaviour to only rendering the documentation attached to the first instance of a duplicate field. Perhaps we could improve this by rendering the first instance that has documentation attached to it but for now, we'll stick with this. - - - - - ad8aa609 by Niklas Haas at 2014-03-08T09:43:26+01:00 Render fixity information Affects functions, type synonyms, type families, class names, data type names, constructors, data families, associated TFs/DFs, type synonyms, pattern synonyms and everything else I could think of. - - - - - 6a39c917 by Niklas Haas at 2014-03-09T07:43:39+01:00 Reorder topDeclElem to move the source/wiki links to the top They appear in the same position due to the float: right attribute but now they're always at the top of the box instead of at the bottom. - - - - - 2d34b3b4 by Niklas Haas at 2014-03-09T07:53:46+01:00 Use optLast instead of listToMaybe for sourceUrls/wikiUrls This lets you override them using eg. cabal haddock --haddock-options, which can come in handy if you want to use a different layout or URL for your source code links than cabal-install generates. - - - - - 0eff4624 by Niklas Haas at 2014-03-09T07:53:46+01:00 Differentiate between TH splices (line-links) and regular names This adds a new type of source code link, to a specific line rather than a specific declaration/name - this is used to link to the location of a TH splice that defines a certain name. Rather hefty changes throughout and still one unresolved issue (the line URLs aren't parsed from the third form of --read-interface which means they're currently restricted to same-interface links). Not sure if this issue is really worth all the hassle, especially since we could just use line links in general. This commit also contains some cleanup/clarification of the types in Haddock.Backends.Xhtml.Decl and shortens some overlong lines in the process. Notably, the Bool parameter was replaced by a Unicode type synonym to help clarify its presence in type signatures. - - - - - 66d6f77b by Niklas Haas at 2014-03-09T20:02:43+01:00 Group similar fixities together Identical fixities declared for the same line should now render using syntax like: infix 4 <, >=, >, <= - - - - - 6587f9f5 by Mateusz Kowalczyk at 2014-03-10T04:24:18+00:00 Update changelog - - - - - 7387ddad by Niklas Haas at 2014-03-11T10:26:04+01:00 Include fixity information in the Interface file This resolves fixity information not appearing across package borders. The binary file version has been increased accordingly. - - - - - ab46ef44 by Niklas Haas at 2014-03-11T10:26:04+01:00 Update changelog - - - - - 565cab6f by Niklas Haas at 2014-03-11T10:26:04+01:00 Update appearance of fixity annotations This moves them in-line with their corresponding lines, similar to a presentation envision by @hvr and described in #ghc. Redundant operator names are also omitted when no ambiguity is present. - - - - - 5d7afd67 by Niklas Haas at 2014-03-11T10:26:05+01:00 Filter family instances of hidden types Currently, this check does not extend to hidden right hand sides, although it probably should hide them in that case. - - - - - ec291b0c by Niklas Haas at 2014-03-11T10:26:05+01:00 Add documentation for --source-entity-line - - - - - 0922e581 by Niklas Haas at 2014-03-11T10:37:32+01:00 Revert "Reorder topDeclElem to move the source/wiki links to the top" This reverts commit 843c42c4179526a2ad3526e4c7d38cbf4d50001d. This change is no longer needed with the new rendering style, and it messes with copy/pasting lines. - - - - - 30618e8b by Mateusz Kowalczyk at 2014-03-11T09:41:07+00:00 Bump version to 2.15.0 - - - - - adf3f1bb by Mateusz Kowalczyk at 2014-03-11T09:41:09+00:00 Fix up some whitespace - - - - - 8905f57d by Niklas Haas at 2014-03-13T19:18:06+00:00 Hide RHS of TFs with non-exported right hand sides Not sure what to do about data families yet, since technically it would not make a lot of sense to display constructors that cannot be used by the user. - - - - - 5c44d5c2 by Niklas Haas at 2014-03-13T19:18:08+00:00 Add UnicodeSyntax alternatives for * and -> I could not find a cleaner way to do this other than checking for string equality with the given built-in types. But seeing as it's actually equivalent to string rewriting in GHC's implementation of UnicodeSyntax, it's probably fitting. - - - - - b04a63e6 by Niklas Haas at 2014-03-13T19:18:10+00:00 Display minimal complete definitions for type classes This corresponds to the new {-# MINIMAL #-} pragma present in GHC 7.8+. I also cleaned up some of the places in which ExportDecl is used to make adding fields easier in the future. Lots of test cases have been updated since they now render with minimality information. - - - - - a4a20b16 by Niklas Haas at 2014-03-13T19:18:12+00:00 Strip links from recently added html tests These were accidentally left there when the tests were originally added - - - - - d624f315 by Mateusz Kowalczyk at 2014-03-13T19:19:31+00:00 Update changelog - - - - - d27a21ac by Mateusz Kowalczyk at 2014-03-13T21:19:07+00:00 Always read in prologue files as UTF8 (#286). - - - - - 54b2fd78 by Mateusz Kowalczyk at 2014-03-13T21:28:09+00:00 Style only - - - - - fa4fe650 by Simon Hengel at 2014-03-15T09:04:18+01:00 Add Fuuzetsu maintainers field in cabal file - - - - - f83484b7 by Niklas Haas at 2014-03-15T18:20:24+00:00 Hide minimal definition for only-method classes Previously this was not covered by the All xs check since here it is not actually an All, rather a single Var n. This also adds the previously missing html-test/src/Minimal.hs. - - - - - 0099d276 by Niklas Haas at 2014-03-15T18:20:26+00:00 Fix issue haskell/haddock#281 This is a regression from the data family instances change. Data instances are now distinguished from regular lists by usage of the new class "inst", and the style has been updated to only apply to those. I've also updated the appropriate test case to test this a bit better, including GADT instances with GADT-style records. - - - - - 1f9687bd by Mateusz Kowalczyk at 2014-03-21T17:48:37+00:00 Please cabal sdist - - - - - 75542693 by Mateusz Kowalczyk at 2014-03-22T16:36:16+00:00 Drop needless --split-objs which slows us down. Involves tiny cleanup of all the dynflag bindings. Fixes haskell/haddock#292. - - - - - 31214dc3 by Herbert Valerio Riedel at 2014-03-23T18:01:01+01:00 Fix a few typos Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 0b73e638 by Mateusz Kowalczyk at 2014-03-31T05:34:36+01:00 Print kind signatures on GADTs - - - - - 2bab42f3 by Mateusz Kowalczyk at 2014-03-31T16:53:25+01:00 Add default for new PlatformConstraints field - - - - - 42647c5f by Mateusz Kowalczyk at 2014-03-31T18:29:04+01:00 Drop leading whitespace in @-style blocks. Fixes haskell/haddock#201. - - - - - 98208294 by Niklas Haas at 2014-03-31T20:09:58+02:00 Crash when exporting record selectors of data family instances This fixes bug haskell/haddock#294. This also fixes a related but never-before-mentioned bug about the display of GADT record selectors with non-polymorphic type signatures. Note: Associated data type constructors fail to show up if nothing is exported that they could be attached to. Exporting any of the data types in the instance head, or the class + data family itself, causes them to show up, but in the absence of either of these, exporting just the associated data type with the constructor itself will result in it being hidden. The only scenario I can come up that would involve this kind of situation involved OverlappingInstances, and even then it can be mitigated by just exporting the class itself, so I'm not going to solve it since the logic would most likely be very complicated. - - - - - 3832d171 by Mateusz Kowalczyk at 2014-04-01T19:07:33+01:00 Make CHANGES consistent with what's now in 2.14.2 - - - - - c386ae89 by Mateusz Kowalczyk at 2014-04-01T19:18:36+01:00 Actually bundle extra spec tests in sdist - - - - - bd57a6d3 by Mateusz Kowalczyk at 2014-04-03T21:13:48+01:00 Update test cases for GHC bug haskell/haddock#8945, Haddock haskell/haddock#188 The order of signature groups has been corrected upstream. Here we add a test case and update some existing test-cases to reflect this change. We remove grouped signature in test cases that we can (Minimal, BugDeprecated &c) so that the test is as self-contained as possible. - - - - - 708b88b1 by Mateusz Kowalczyk at 2014-04-03T21:16:07+01:00 Enforce strict GHC version in cabal file This stops people with 7.6.3 trying to install 2.15.x which clearly won't work. Unfortunately we shipped 2.14.x without realising this. - - - - - 60334f7c by Mateusz Kowalczyk at 2014-04-03T21:19:24+01:00 Initialise some new PlatformConstants fields - - - - - ea77f668 by Mateusz Kowalczyk at 2014-04-11T16:52:23+01:00 We don't actually want unicode here - - - - - 0b651cae by Mateusz Kowalczyk at 2014-04-11T18:13:30+01:00 Parse identifiers with ^ and ⋆ in them. Fixes haskell/haddock#298. - - - - - e8ad0f5f by Mateusz Kowalczyk at 2014-04-11T18:47:41+01:00 Ignore version string during HTML tests. - - - - - de489089 by Mateusz Kowalczyk at 2014-04-11T18:59:30+01:00 Update CHANGES to follow 2.14.3 - - - - - beb464a9 by Gergő Érdi at 2014-04-13T16:31:10+08:00 remove Origin flag from LHsBindsLR - - - - - cb16f07c by Herbert Valerio Riedel at 2014-04-21T17:16:50+02:00 Replace local `die` by new `System.Exit.die` Starting with GHC 7.10, System.Exit exports the new `die` which is essentially the same as Haddock.Util.die, so this commit changes Haddock.Util.die to be a simple re-export of System.Exit.die. See also https://ghc.haskell.org/trac/ghc/ticket/9016 for more details. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 9b9b23c7 by Mateusz Kowalczyk at 2014-05-03T15:40:11+02:00 Disambiguate ‘die’ in test runners. - - - - - 5d28a2b8 by Mateusz Kowalczyk at 2014-05-05T09:19:49+02:00 Prepare modules for parser split. We have to generalise the Doc (now DocH) slightly to remove the dependency on GHC-supplied type. - - - - - d3967ff3 by Mateusz Kowalczyk at 2014-05-05T11:00:41+02:00 Move parser + parser tests out to own package. We move some types out that are necessary as well and then re-export and specialise them in the core Haddock. Reason for moving out spec tests is that if we're working on the parser, we can simply work on that and we can ignore the rest of Haddock. The downside is that it's a little inconvenient if at the end of the day we want to see that everything passes. - - - - - 522a448d by Mateusz Kowalczyk at 2014-05-05T11:14:47+02:00 Move out Show and Eq instances to Types They are much more useful to the users here. - - - - - 11a6f0f2 by Mateusz Kowalczyk at 2014-05-06T13:50:31+02:00 Remove no longer necessary parser error handling. We can now drop some Maybe tests and even lets us strip an error handling monad away in a few places. - - - - - 6992c924 by Mateusz Kowalczyk at 2014-05-14T02:23:55+02:00 Please the GHC build-system. As I can not figure out how to do this properly, if we're in GHC tree, we treat the library as being the same package. If we're not in the tree, we require that the library be installed separately. - - - - - 7a8ad763 by Mateusz Kowalczyk at 2014-05-14T14:50:25+02:00 Update issue tracker URL - - - - - f616c521 by Mateusz Kowalczyk at 2014-05-14T14:53:32+02:00 Update issue tracker URL for haddock-library - - - - - 66580ded by Gergő Érdi at 2014-05-25T14:24:16+08:00 Accomodate change in PatSyn representation - - - - - 0e43b988 by Mateusz Kowalczyk at 2014-05-29T03:15:29+02:00 Revert "Accomodate change in PatSyn representation" This reverts commit 57aa591362d7c8ba21285fccd6a958629a422091. I am reverting this because I pushed it to master when it was meant to stay on a wip-branch. Sorry Gergo and everyone who had trouble due to this. - - - - - e10d7ec8 by Mateusz Kowalczyk at 2014-05-29T03:24:11+02:00 Revert "Revert "Accomodate change in PatSyn representation"" This reverts commit e110e6e70e40eed06c06676fd2e62578da01d295. Apparently as per GHC commit ac2796e6ddbd54c5762c53e2fcf29f20ea162fd5 this was actually intended. Embarrasing for me. - - - - - 5861aca9 by Mateusz Kowalczyk at 2014-06-05T19:49:27+02:00 Clear up highlighting of identifiers with ‘'’s. - - - - - d7cc420f by Simon Peyton Jones at 2014-06-06T12:41:09+01:00 Follow change in patSynSig - - - - - 938b4fd8 by Mateusz Kowalczyk at 2014-06-12T07:24:29+02:00 Slightly update the readme. Style-sheets are no longer a recent thing, dead links, old maintainers, different formats. - - - - - c7799dea by Mateusz Kowalczyk at 2014-06-18T00:05:56+02:00 Update cabal files Update repository urls, use subdir property for haddock-library and use a separate versioning scheme for haddock-library in preparation for release. - - - - - a2750b6a by Simon Hengel at 2014-06-18T11:01:18+08:00 Compatibility with older versions of base and bytestring - - - - - 009b4b03 by Simon Hengel at 2014-06-18T11:14:01+08:00 Enable travis-ci for haddock-library - - - - - 9b5862eb by Simon Hengel at 2014-06-18T11:14:01+08:00 haddock-library: Do not depend on haddock-library in test suite I think you either add src to hs-source-dirs or the library to build-depends. But doing both does not make sense (AFAICT). - - - - - fb1f3279 by Simon Hengel at 2014-06-18T11:49:05+08:00 haddock-library: Use -Wall for specs - - - - - 649340e1 by Mateusz Kowalczyk at 2014-06-18T06:58:54+02:00 Use Travis with multiple GHC versions When using HEAD, we build haddock-library directly from repository as a dependency (and thanks to --enable-tests, the tests get ran anyway). In all other cases, we manually run the tests on haddock-library only and don't test the main project. - - - - - d7eeeec2 by Mateusz Kowalczyk at 2014-06-18T07:49:04+02:00 Comment improvements + few words in cabal file - - - - - 0f8db914 by Simon Hengel at 2014-06-18T13:52:23+08:00 Use doctest to check examples in documentation - - - - - 2888a8dc by Simon Hengel at 2014-06-18T14:16:48+08:00 Remove doctest dependency (so that we can use haddock-library with doctest) - - - - - 626d5e85 by Mateusz Kowalczyk at 2014-06-18T08:41:25+02:00 Travis tweaks - - - - - 41d4f9cc by Mateusz Kowalczyk at 2014-06-18T08:58:43+02:00 Don't actually forget to install specified GHC. - - - - - c6aa512a by John MacFarlane at 2014-06-18T10:43:57-07:00 Removed reliance on LambdaCase (which breaks build with ghc 7.4). - - - - - b9b93b6f by John MacFarlane at 2014-06-18T10:54:56-07:00 Fixed haddock warnings. - - - - - a41b0ab5 by Mateusz Kowalczyk at 2014-06-19T01:20:10+02:00 Update Travis, bump version - - - - - 864bf62a by Mateusz Kowalczyk at 2014-06-25T10:36:54+02:00 Fix anchors. Closes haskell/haddock#308. - - - - - 53df91bb by Mateusz Kowalczyk at 2014-06-25T15:04:49+02:00 Drop DocParagraph from front of headers I can not remember why they were wrapped in paragraphs to begin with and it seems unnecessary now that I test it. Closes haskell/haddock#307. - - - - - 29b5f2fa by Mateusz Kowalczyk at 2014-06-25T15:17:20+02:00 Don't mangle append order for nested lists. The benefit of this is that the ‘top-level’ element of such lists is properly wrapped in <p> tags so any CSS working with these will be applied properly. It also just makes more sense. Pointed out at jgm/pandoc#1346. - - - - - 05cb6e9c by Mateusz Kowalczyk at 2014-06-25T15:19:45+02:00 Bump haddock-library to 1.1.0 for release - - - - - 70feab15 by Iavor Diatchki at 2014-07-01T03:37:07-07:00 Propagate overloading-mode for instance declarations in haddock (#9242) - - - - - d4ca34a7 by Simon Peyton Jones at 2014-07-14T16:23:15+01:00 Adapt to new definition of HsDecls.TyFamEqn This is a knock-on from the refactoring from Trac haskell/haddock#9063. I'll push the corresponding changes to GHC shortly. - - - - - f91e2276 by Edward Z. Yang at 2014-07-21T08:14:19-07:00 Track GHC PackageId to PackageKey renaming. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - b010f9ef by Edward Z. Yang at 2014-07-25T16:28:46-07:00 Track changes for module reexports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - 8b85f9f9 by Mateusz Kowalczyk at 2014-07-28T13:25:43+02:00 Catch mid-line URLs. Fixes haskell/haddock#314. - - - - - 4c613a78 by Edward Z. Yang at 2014-08-05T03:11:00-07:00 Track type signature change of lookupModuleInAllPackages Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - e80b051c by Edward Z. Yang at 2014-08-05T17:34:26+01:00 If GhcProfiled, also build Haddock profiled. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f9cccd29 by Edward Z. Yang at 2014-08-07T14:23:35+01:00 Ignore TAGS files. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 00b3af52 by Mateusz Kowalczyk at 2014-08-08T04:58:19+02:00 Update to attoparsec-0.12.1.1 There seems to be memory and speed improvement. - - - - - 5457dc71 by Mateusz Kowalczyk at 2014-08-08T18:24:02+02:00 Fix forgotten src - - - - - 3520cb04 by Mateusz Kowalczyk at 2014-08-14T20:19:07+01:00 Bump down the version for master to 2.14.4 - - - - - dc98c21b by Mateusz Kowalczyk at 2014-08-14T20:23:27+01:00 Revert "Track type signature change of lookupModuleInAllPackages" This reverts commit d59fec2c9551b5662a3507c0011e32a09a9c118f. - - - - - 3f2038c0 by Mateusz Kowalczyk at 2014-08-14T20:23:31+01:00 Revert "Track changes for module reexports." This reverts commit b99b57c0df072d12b67816b45eca2a03cb1da96d. - - - - - 56d4e49e by Mateusz Kowalczyk at 2014-08-14T20:23:42+01:00 Revert "Track GHC PackageId to PackageKey renaming." This reverts commit 8ac42d3327473939c013551750425cac191ff0fd. - - - - - 726ea3cb by Mateusz Kowalczyk at 2014-08-14T20:23:47+01:00 Revert "Adapt to new definition of HsDecls.TyFamEqn" This reverts commit cb96b4f1ed0462b4a394b9fda6612c3bea9886bd. - - - - - 61a88ff0 by Mateusz Kowalczyk at 2014-08-14T20:23:52+01:00 Revert "Propagate overloading-mode for instance declarations in haddock (#9242)" This reverts commit 8d20ca8d5a9bee73252ff2035ec45f9c03d0820c. - - - - - a32ba674 by Mateusz Kowalczyk at 2014-08-14T20:26:03+01:00 Revert "Disambiguate ‘die’ in test runners." This reverts commit dba02d6df32534aac5d257f2d28596238d248942. - - - - - f335820f by Mateusz Kowalczyk at 2014-08-14T20:26:09+01:00 Revert "Replace local `die` by new `System.Exit.die`" This reverts commit 08aa509ebac58bfb202ea79c7c41291ec280a1c5. - - - - - 107078e4 by Mateusz Kowalczyk at 2014-08-14T20:27:34+01:00 Merge branch 'reverts' This reverts any changes that were made to have Haddock compile with 7.9. When 7.10 release comes, we can simply re-apply all the patches and any patches that occur on ghc-head branch from now on. This allows us to build master with 7.8.3 - - - - - b44b3871 by Mateusz Kowalczyk at 2014-08-15T02:47:40+01:00 Fix haskell/haddock#313 by doing some list munging. I get rid of the Monoid instance because we weren't satisfying the laws. Convenience of having <> didn't outweigh the shock-factor of having it behave badly. - - - - - e1a62cde by Mateusz Kowalczyk at 2014-08-15T02:52:56+01:00 Stop testing haskell/haddock#188. Because the change is in GHC 7.9 and we now work against 7.8.3, this test no longer makes sense. We revert it until 7.10 becomes the standard version. If anything, there should be a test for this in GHC itself. - - - - - 54e8286d by Mateusz Kowalczyk at 2014-08-15T05:31:57+01:00 Add haskell/haddock#313 to CHANGES - - - - - 9df7ad5d by Simon Hengel at 2014-08-20T11:25:32+08:00 Fix warning - - - - - ee2574d6 by Simon Hengel at 2014-08-20T12:07:01+08:00 Fix travis builds - - - - - 384cf2e6 by Simon Hengel at 2014-08-20T12:14:31+08:00 Require GHC 7.8.3 - - - - - d4779863 by Simon Hengel at 2014-08-22T12:14:16+08:00 Move Haddock API to a separate package - - - - - 80f3e0e1 by Simon Hengel at 2014-08-22T14:57:38+08:00 Bump version to 2.15.0 and add version constraints - - - - - 309a94ce by Simon Hengel at 2014-08-22T15:18:06+08:00 Add deprecated compatibility module - - - - - 4d1e4e3f by Luite Stegeman at 2014-08-22T20:46:45+02:00 export things to allow customizing how the Ghc session is run - - - - - 47884591 by Luite Stegeman at 2014-08-22T20:46:51+02:00 ghc 7.8.2 compatibility - - - - - 5ea94e2c by Luite Stegeman at 2014-08-22T22:08:58+02:00 install dependencies for haddock-api on travis - - - - - 9fb845b2 by Mateusz Kowalczyk at 2014-08-23T10:09:34+01:00 Move sources under haddock-api/src - - - - - 85817dc4 by Mateusz Kowalczyk at 2014-08-23T10:10:48+01:00 Remove compat stuff - - - - - 151c6169 by Niklas Haas at 2014-08-24T08:14:10+02:00 Fix extra whitespace on signatures and update all test cases This was long overdue, now running ./accept.lhs on a clean test from master will not generate a bunch of changes. - - - - - d320e0d2 by Niklas Haas at 2014-08-24T08:14:35+02:00 Omit unnecessary foralls and fix haskell/haddock#315 This also fixes haskell/haddock#86. - - - - - bdafe108 by Mateusz Kowalczyk at 2014-08-24T15:06:46+01:00 Update CHANGES - - - - - fafa6d6e by Mateusz Kowalczyk at 2014-08-24T15:14:23+01:00 Delete few unused/irrelevant/badly-place files. - - - - - 3634923d by Duncan Coutts at 2014-08-27T13:49:31+01:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. - - - - - 539a7e70 by Herbert Valerio Riedel at 2014-08-31T11:36:32+02:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 9e3a0e5b by Mateusz Kowalczyk at 2014-08-31T12:54:43+01:00 Bump version in doc - - - - - 4a177525 by Mateusz Kowalczyk at 2014-08-31T13:01:23+01:00 Bump haddock-library version - - - - - f99c1384 by Mateusz Kowalczyk at 2014-08-31T13:05:25+01:00 Remove references to deleted files - - - - - 5e51a247 by Mateusz Kowalczyk at 2014-08-31T14:18:44+01:00 Make the doc parser not complain - - - - - 2cedb49a by Mateusz Kowalczyk at 2014-09-03T03:33:15+01:00 CONTRIBUTING file for issues - - - - - 88027143 by Mateusz Kowalczyk at 2014-09-04T00:46:59+01:00 Mention --print-missing-docs - - - - - 42f6754f by Alan Zimmerman at 2014-09-05T18:13:24-05:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e712719e by Austin Seipp at 2014-09-09T01:03:27-05:00 Fix import of 'empty' due to AMP. Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 71c29755 by Herbert Valerio Riedel at 2014-09-09T17:35:20+02:00 Bump `base` constraint for AMP - - - - - 0bf9f3ed by Mateusz Kowalczyk at 2014-09-12T19:18:32+01:00 Delete stale ANNOUNCE - - - - - cac89ee6 by Krzysztof Gogolewski at 2014-09-14T17:17:09+02:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 4d683426 by Edward Z. Yang at 2014-09-18T13:38:11-07:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 80697fd5 by Herbert Valerio Riedel at 2014-09-19T00:07:52+02:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. - - - - - c015eb70 by Herbert Valerio Riedel at 2014-09-19T00:10:36+02:00 Revert "Followup changes to addition of -fwarn-context-quantification" This reverts commit 4023817d7c0e46db012ba2eea28022626841ca9b temporarily as the respective feature hasn't landed in GHC HEAD yet, but this commit blocks later commits from being referenced in GHC HEAD. - - - - - 38ded784 by Edward Z. Yang at 2014-09-18T15:32:15-07:00 Revert "Revert "Followup changes to addition of -fwarn-context-quantification"" This reverts commit db14fd8ab4fab43694139bc203808b814eafb2dc. It's in HEAD now. - - - - - f55d59c9 by Herbert Valerio Riedel at 2014-09-26T19:18:28+02:00 Revert "Fix import of 'empty' due to AMP." This reverts commit 0cc5bc85e9fca92ab712b68a2ba2c0dd9d3d79f4 since it turns out we don't need to re-export `empty` from Control.Monad after all. - - - - - 467050f1 by David Feuer at 2014-10-09T20:07:36-04:00 Fix improper lazy IO use Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. - - - - - cc47b699 by Edward Z. Yang at 2014-10-09T21:38:19-07:00 Fix use-after-close lazy IO bug Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. Signed-off-by: David Feuer <David.Feuer at gmail.com> Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 87babcbe by Austin Seipp at 2014-10-20T20:05:27-05:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - ab259516 by Austin Seipp at 2014-10-20T20:07:01-05:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - b918093c by Mateusz Kowalczyk at 2014-10-29T03:59:39+00:00 Experimental support for collapsable headers Closes haskell/haddock#335 - - - - - 849db129 by Mateusz Kowalczyk at 2014-10-29T10:07:26+01:00 Experimental support for collapsable headers (cherry picked from commit e2ed3b9d8dfab09f1b1861dbc8e74f08e137ebcc) - - - - - a4cc4789 by Herbert Valerio Riedel at 2014-10-31T11:08:26+01:00 Collapse user-defined section by default (re haskell/haddock#335) - - - - - 9da1b33e by Yuras Shumovich at 2014-10-31T16:11:04-05:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - c625aefc by Austin Seipp at 2014-10-31T19:34:10-05:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - c7738e5e by Simon Hengel at 2014-11-02T07:25:30+08:00 Remove -fobject-code from .ghci (this slows down reloads on modifications) - - - - - d4a86e95 by Simon Hengel at 2014-11-03T09:26:11+08:00 Get rid of StandaloneDeriving - - - - - a974e311 by Simon Hengel at 2014-11-03T09:26:11+08:00 Derive more instances - - - - - 8aa0c4d7 by Simon Hengel at 2014-11-03T09:27:08+08:00 Remove unused language extensions - - - - - 3052d46a by Simon Hengel at 2014-11-03T09:30:46+08:00 Minor refactoring - - - - - 4281d3cb by Simon Hengel at 2014-11-03T09:30:46+08:00 parser: Try to parse definition lists right before text paragraphs - - - - - 8ba12bf9 by Simon Hengel at 2014-11-03T09:34:19+08:00 Add support for markdown links (closes haskell/haddock#336) - - - - - a2f8d747 by Simon Hengel at 2014-11-03T09:34:19+08:00 Allow markdown links at the beginning of a paragraph - - - - - 53b11207 by Simon Hengel at 2014-11-03T09:34:20+08:00 Update documentation - - - - - 652267c6 by Simon Hengel at 2014-11-03T09:34:20+08:00 Add support for markdown images - - - - - 9d667502 by Simon Hengel at 2014-11-03T09:34:20+08:00 Allow an optional colon after the closing bracket of definition lists This is to disambiguate them from markdown links and will be require with a future release. - - - - - 8167fc32 by Mateusz Kowalczyk at 2014-11-04T01:16:51+00:00 whitespace only - - - - - 3da62981 by Mateusz Kowalczyk at 2014-11-04T01:17:31+00:00 Fix re-exports of built-in type families Fixes haskell/haddock#310 - - - - - edc76b34 by Mateusz Kowalczyk at 2014-11-04T02:54:28+00:00 Turn some uses of error into recoverable warnings This should at the very least not abort when something weird happens. It does feel like we should have a type that carries these errors until the end however as the user might not see them unless they are printed at the end. - - - - - 0a137400 by Mateusz Kowalczyk at 2014-11-04T04:09:44+00:00 Fix warnings - - - - - d068fc21 by Mateusz Kowalczyk at 2014-11-04T21:04:07+00:00 Fix parsing of identifiers written in infix way - - - - - 1a9f2f3d by Simon Hengel at 2014-11-08T11:32:42+08:00 Minor code simplification - - - - - 6475e9b1 by Simon Hengel at 2014-11-08T17:28:33+08:00 newtype-wrap parser monad - - - - - dc1ea105 by Herbert Valerio Riedel at 2014-11-15T11:55:43+01:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - fbb1aca4 by Simon Hengel at 2014-11-16T08:51:38+08:00 State intention rather than implementation details in Haddock comment - - - - - 97851ab2 by Simon Hengel at 2014-11-16T10:20:19+08:00 (wip) Add support for @since (closes haskell/haddock#26) - - - - - 34bcd18e by Gergő Érdi at 2014-11-20T22:35:38+08:00 Update Haddock to new pattern synonym type signature syntax - - - - - 304b7dc3 by Jan Stolarek at 2014-11-20T17:48:43+01:00 Follow changes from haskell/haddock#9812 - - - - - 920f9b03 by Richard Eisenberg at 2014-11-20T16:52:50-05:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 0bfe4e78 by Alan Zimmerman at 2014-11-21T11:23:09-06:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 356ed45a by Thomas Winant at 2014-11-28T16:11:22-06:00 Support for PartialTypeSignatures - - - - - 5dc8f3b1 by Gergő Érdi at 2014-11-29T15:39:09+08:00 For pattern synonyms, render "pattern" as a keyword - - - - - fe704480 by Mateusz Kowalczyk at 2014-12-09T03:38:32+00:00 List new module in cabal file - - - - - b9ad5a29 by Mateusz Kowalczyk at 2014-12-10T00:58:24+00:00 Allow the parser to spit out meta-info Currently we only use it only for ‘since’ annotations but with these patches it should be fairly simple to add new attributes if we wish to. Closes haskell/haddock#26. It seems to work fine but due to 7.10 rush I don't have the chance to do more exhaustive testing right now. The way the meta is output (emphasis at the end of the whole comment) is fairly arbitrary and subject to bikeshedding. Note that this makes test for Bug310 fail due to interface version bump: it can't find the docs for base with this interface version so it fails. There is not much we can do to help this because it tests for ’built-in’ identifier, not something we can provide ourselves. - - - - - 765af0e3 by Mateusz Kowalczyk at 2014-12-10T01:17:19+00:00 Update doctest parts of comments - - - - - 8670272b by jpmoresmau at 2014-12-10T01:35:31+00:00 header could contain several lines Closes haskell/haddock#348 - - - - - 4f9ae4f3 by Mateusz Kowalczyk at 2014-12-12T06:22:31+00:00 Revert "Merge branch 'reverts'" This reverts commit 5c93cc347773c7634321edd5f808d5b55b46301f, reversing changes made to 5b81a9e53894d2ae591ca0c6c96199632d39eb06. Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - e974ac94 by Duncan Coutts at 2014-12-12T06:26:11+00:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. Conflicts: haddock-api/src/Haddock.hs - - - - - 2f3a2365 by Herbert Valerio Riedel at 2014-12-12T06:26:51+00:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 1dbd6390 by Alan Zimmerman at 2014-12-12T06:32:07+00:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - bb6ff1f4 by Mateusz Kowalczyk at 2014-12-12T06:35:07+00:00 Bump ‘base’ constraint Follows the similar commit made on ghc-head branch - - - - - 466fe4ab by Krzysztof Gogolewski at 2014-12-12T06:37:42+00:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 97e080c9 by Edward Z. Yang at 2014-12-12T06:39:35+00:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: haddock-api/src/Haddock/ModuleTree.hs - - - - - 20b2af56 by Herbert Valerio Riedel at 2014-12-12T06:42:50+00:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. Conflicts: haddock-library/src/Documentation/Haddock/Parser.hs - - - - - b3ad269d by Austin Seipp at 2014-12-12T06:44:14+00:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 072df0dd by Austin Seipp at 2014-12-12T06:45:01+00:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - dbb9294a by Herbert Valerio Riedel at 2014-12-12T06:46:17+00:00 Collapse user-defined section by default (re haskell/haddock#335) Conflicts: haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs - - - - - f23ab545 by Yuras Shumovich at 2014-12-12T06:46:41+00:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - 753a4b67 by Austin Seipp at 2014-12-12T06:46:51+00:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8954e8f5 by Herbert Valerio Riedel at 2014-12-12T06:50:53+00:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - d2b06d61 by Gergő Érdi at 2014-12-12T07:07:30+00:00 Update Haddock to new pattern synonym type signature syntax Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 1ff02426 by Jan Stolarek at 2014-12-12T07:13:24+00:00 Follow changes from haskell/haddock#9812 Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - 06ad7600 by Richard Eisenberg at 2014-12-12T07:13:43+00:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 8fd2aa8b by Alan Zimmerman at 2014-12-12T07:22:25+00:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Backends/LaTeX.hs haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 95c3db98 by Thomas Winant at 2014-12-12T07:35:49+00:00 Support for PartialTypeSignatures Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs haddock-api/src/Haddock/Interface/Create.hs - - - - - 45494428 by Gergő Érdi at 2014-12-12T07:36:18+00:00 For pattern synonyms, render "pattern" as a keyword - - - - - a237e3eb by Mateusz Kowalczyk at 2014-12-12T12:27:13+00:00 Various fixups and bumps for next release - - - - - 22918bcd by Herbert Valerio Riedel at 2014-12-14T10:11:47+01:00 Remove redundant wild-card pattern match (this would otherwise cause a build-failure with `-Werror`) - - - - - 1d6ce947 by Herbert Valerio Riedel at 2014-12-14T10:17:06+01:00 Treat GHC 7.10 the same as GHC 7.9 ...since the current GHC 7.9 is going to become GHC 7.10 real-soon-now anyway - - - - - f434ea89 by Herbert Valerio Riedel at 2014-12-14T18:26:50+01:00 Fixup ghc.mk (follow-up to 1739375eb23342) This makes the GHC build-system aware of the data-files to be copied into the bindist (as haddock.cabal doesn't list those anymore) - - - - - 6fb839eb by Mateusz Kowalczyk at 2014-12-17T09:28:59+00:00 Only keep one Version instead of blindly appending - - - - - 40645489 by Mateusz Kowalczyk at 2014-12-18T07:09:44+00:00 Fix dependency version - - - - - 8b3b927b by Mateusz Kowalczyk at 2014-12-18T07:14:23+00:00 Print missing docs by default Adds --no-print-missing-docs - - - - - 59666694 by Mateusz Kowalczyk at 2014-12-18T07:21:37+00:00 update changelog - - - - - aa6d168e by Mateusz Kowalczyk at 2014-12-18T07:30:58+00:00 Update docs for @since - - - - - 2d7043ee by Luite Stegeman at 2014-12-19T18:29:35-06:00 hide projectVersion from DynFlags since it clashes with Haddock.Version.projectVersion - - - - - aaa70fc0 by Luite Stegeman at 2014-12-22T15:58:43+01:00 Add missing import for standalone haddock-api package - - - - - 9ce01269 by Herbert Valerio Riedel at 2014-12-22T17:48:45+01:00 Reset ghc-head with master's tree (this is an overwriting git merge of master into ghc-head) - - - - - fcd6fec1 by Herbert Valerio Riedel at 2014-12-22T17:51:52+01:00 Bump versions for ghc-7.11 - - - - - 525ec900 by Mateusz Kowalczyk at 2014-12-23T13:36:24+00:00 travis-ci: test with HEAD - - - - - cbf494b5 by Simon Peyton Jones at 2014-12-23T15:22:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 50e01c99 by Mateusz Kowalczyk at 2014-12-29T15:28:47+00:00 Make travis use 7.10.x - - - - - 475e60b0 by Njagi Mwaniki at 2014-12-29T15:30:44+00:00 Turn the README into GitHub Markdown format. Closes haskell/haddock#354 - - - - - 8cacf48e by Luite Stegeman at 2015-01-05T16:25:37+01:00 bump haddock-api ghc dependency to allow release candidate and first release - - - - - 6ed6cf1f by Simon Peyton Jones at 2015-01-06T16:37:47+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 8b484f33 by Simon Peyton Jones at 2015-01-08T15:50:22+00:00 Track naming change in DataCon - - - - - 23c5c0b5 by Alan Zimmerman at 2015-01-16T10:15:11-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e7a5532c by JP Moresmau at 2015-01-22T17:19:03+00:00 Ignore warnings, install Cabal 1.22 - - - - - 86942c84 by jpmoresmau at 2015-01-22T17:19:04+00:00 solve dataDir ambiguity - - - - - 5ceb743e by jpmoresmau at 2015-01-22T19:17:32+00:00 support GHC 7.10: no Safe-Inferred, Foldable instance - - - - - 6a3b3fb5 by Mateusz Kowalczyk at 2015-01-22T19:32:10+00:00 Update test files Test: a correct behaviour for fields comma-separating values. I'm surprised we had no bug open for this. Maybe it affects how haskell/haddock#301 renders now but I doubt. Operators: Seems GHC is giving us a new order for operators, something must have changed on their side again. cc @haasn , this makes the fixity to the side not match the order on the LHS which is a bit unpleasant. Maybe the fixity can be made to match the GHC order? Bug335: We expand examples by default now. Bug310: Now inferred safe. - - - - - 708f8b2f by jpmoresmau at 2015-01-22T19:36:59+00:00 Links to source location of class instance definitions - - - - - 5cf8a6da by Vincent Berthoux at 2015-01-22T19:59:58+00:00 Filter '\r' from comments due to Windows problems. On Windows this was causing newline to be rendered twice in code blocks. Closes haskell/haddock#359, fixes haskell/haddock#356. - - - - - 1749e6f0 by Mateusz Kowalczyk at 2015-01-22T20:31:27+00:00 Changelog only - - - - - c8145f90 by Mateusz Kowalczyk at 2015-01-22T23:34:05+00:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. - - - - - 14248254 by Mateusz Kowalczyk at 2015-01-22T23:43:18+00:00 Sort out some module import warnings - - - - - d8a38989 by Simon Peyton Jones at 2015-01-23T07:10:16-06:00 Track naming change in DataCon (cherry picked from commit 04cf63d0195837ed52075ed7d2676e71831e8a0b) - - - - - d3ac6ae4 by Alan Zimmerman at 2015-01-23T07:17:19-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit d61bbc75890e4eb0ad508b9c2a27b91f691213e6) - - - - - 4c1ffeb0 by Simon Peyton Jones at 2015-02-10T12:10:33+00:00 Track changes in HsSyn for quasi-quotes - - - - - 775d20f7 by Mateusz Kowalczyk at 2015-03-15T08:11:48+01:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. (cherry picked from commit 8e06728afb0784128ab2df0be7a5d7a191d30ff4) - - - - - f9245e72 by Phil Ruffwind at 2015-03-16T04:32:01-04:00 Prevent Synopsis from using up too much horizontal space When long type signatures occur in the Synopsis, the element is stretched beyond the width of the window. Scrollbars don't appear, so it's impossible to read anything when this happens. - - - - - cd8fa415 by Mateusz Kowalczyk at 2015-03-17T21:59:39+00:00 Update changelog Closes haskell/haddock#151 due to 71170fc77962f10d7d001e3b8bc8b92bfeda99bc - - - - - b5248b47 by Ben Gamari at 2015-03-25T17:12:17+00:00 Make the error encountered when a package can't be found more user-friendly Closes haskell/haddock#369 - - - - - b756b772 by Mateusz Kowalczyk at 2015-03-26T16:31:40+00:00 Remove now redundant imports - - - - - 5ea5e8dd by Mateusz Kowalczyk at 2015-03-26T16:45:52+00:00 Update test to account for \r filtering - - - - - 6539bfb3 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Test for anchor defaulting I delete the old tests because it turns out that: * test runner would never put them in scope of each other even with imports so just one would suffice * test runner actually needed some hacking to keep links so in the end we would end up with no anchors making them useless - - - - - 1a01d950 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Clearly default to variables in out of scope case - - - - - 7943abe8 by Mateusz Kowalczyk at 2015-03-27T01:14:11+00:00 Fix Hoogle display of constructors Fixes haskell/haddock#361 - - - - - 6d6e587e by Mateusz Kowalczyk at 2015-03-27T01:45:18+00:00 Fully qualify names in Hoogle instances output Closes haskell/haddock#263 - - - - - 52dac365 by Mateusz Kowalczyk at 2015-03-27T01:55:01+00:00 Update changelog - - - - - ca5af9a8 by Mateusz Kowalczyk at 2015-03-27T02:43:55+00:00 Output method documentation in Hoogle backend One thing of note is that we no longer preserve grouping of methods and print each method on its own line. We could preserve it if no documentation is present for any methods in the group if someone asks for it though. Fixes haskell/haddock#259 - - - - - a33f0c10 by Mateusz Kowalczyk at 2015-03-27T03:04:21+00:00 Don't print instance safety information in Hoogle Fixes haskell/haddock#168 - - - - - df6c935a by Mateusz Kowalczyk at 2015-03-28T00:11:47+00:00 Post-release version bumps and changelog - - - - - dde8f7c0 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Loosen bounds on haddock-* - - - - - de93bf89 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Expand response files in arguments Closes haskell/haddock#285 - - - - - 1f0b0856 by Zejun Wu at 2015-04-26T16:35:35-07:00 Do not insert anchor for section headings in contents box - - - - - 860439d7 by Simon Peyton Jones at 2015-05-01T09:36:47+01:00 Track change in API of TyCon - - - - - a32f3e5f by Adam Gundry at 2015-05-04T15:32:59+01:00 Track API changes to support empty closed type familes - - - - - 77e98bee by Ben Gamari at 2015-05-06T20:17:08+01:00 Ignore doc/haddock.{ps,pdf} - - - - - 663d0204 by Murray Campbell at 2015-05-11T04:47:37-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8bb0dcf5 by Murray Campbell at 2015-05-11T06:35:06-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit 2380f07c430c525b205ce2eae6dab23c8388d899) - - - - - bad900ea by Adam Bergmark at 2015-05-11T15:29:39+01:00 haddock-library: require GHC >= 7.4 `Data.Monoid.<>` was added in base-4.5/GHC-7.4 Closes haskell/haddock#394 Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - daceff85 by Simon Peyton Jones at 2015-05-13T12:04:21+01:00 Track the new location of setRdrNameSpace - - - - - 1937d1c4 by Alan Zimmerman at 2015-05-25T21:27:15+02:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - ee0fb6c2 by Łukasz Hanuszczak at 2015-05-27T11:51:31+02:00 Create simple method for indentation parsing. - - - - - 7d6fcad5 by Łukasz Hanuszczak at 2015-05-27T21:36:13+02:00 Make nested lists count indentation according to first item. - - - - - d6819398 by Łukasz Hanuszczak at 2015-05-27T22:46:13+02:00 Add simple test case for arbitrary-depth list nesting. - - - - - 2929c54d by Łukasz Hanuszczak at 2015-06-03T02:11:31+02:00 Add arbitrary-indent spec test for parser. - - - - - 9a0a9bb0 by Mateusz Kowalczyk at 2015-06-03T05:25:29+01:00 Update docs with info on new list nesting rule Fixes haskell/haddock#278 through commits from PR haskell/haddock#401 - - - - - 12efc92c by Mateusz Kowalczyk at 2015-06-03T05:29:26+01:00 Update some meta data at the top of the docs - - - - - 765ee49f by Bartosz Nitka at 2015-06-07T08:40:59-07:00 Add some Hacking docs for getting started - - - - - 19aaf851 by Bartosz Nitka at 2015-06-07T08:44:30-07:00 Fix markdown - - - - - 2a90cb70 by Mateusz Kowalczyk at 2015-06-08T15:08:36+01:00 Refine hacking instructions slightly - - - - - 0894da6e by Thomas Winant at 2015-06-08T23:47:28-05:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 10a9bb76 by Emanuel Borsboom at 2015-06-12T02:46:23+01:00 Build executable with '-threaded' (fixes haskell/haddock#399) - - - - - 7696b94f by Mateusz Kowalczyk at 2015-06-12T02:59:19+01:00 Update changelog for -threaded Closes haskell/haddock#400 - - - - - d3c118ec by Bartosz Nitka at 2015-06-12T03:00:58+01:00 Fix haddock: internal error: spliceURL UnhelpfulSpan (#207) Inferred type signatures don't have SrcSpans, so let's use the one from the declaration. I've tested this manually on the test-case from haskell/haddock#207, but I got stuck at trying to run the test-suite. - - - - - b67e843b by Mateusz Kowalczyk at 2015-06-12T03:01:50+01:00 Changelog for haskell/haddock#207 Fixes haskell/haddock#207, closes haskell/haddock#402 - - - - - 841d785e by jpmoresmau at 2015-06-12T16:03:16+01:00 Attach to instance location the name that has the same location file Fixes haskell/haddock#383 - - - - - 98791cae by Mateusz Kowalczyk at 2015-06-12T16:08:27+01:00 Update changelog Closes haskell/haddock#398 - - - - - 7c0b5a87 by Phil Ruffwind at 2015-06-12T13:07:25-04:00 Fix alignment of Source links in instance table in Firefox Due to a Firefox bug [1], a combination of 'whitespace: nowrap' on the parent element with 'float: right' on the inner element can cause the floated element to be displaced downwards for no apparent reason. To work around this, the left side is wrapped in its own <span> and set to 'float: left'. As a precautionary measure to prevent the parent element from collapsing entirely, we also add the classic "clearfix" hack. The latter is not strictly needed but it helps prevent bugs if the layout is altered again in the future. Fixes haskell/haddock#384. Remark: line 159 of src/Haddock/Backends/Xhtml/Layout.hs was indented to prevent confusion over the operator precedence of (<+>) vs (<<). [1]: https://bugzilla.mozilla.org/show_bug.cgi?id=488725 - - - - - cfe86e73 by Mateusz Kowalczyk at 2015-06-14T10:49:01+01:00 Update tests for the CSS changes - - - - - 2d4983c1 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding for Haskell source parser module. - - - - - 29548785 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement function for tagging parsed chunks with source spans. - - - - - 6a5e4074 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement simple string chunking based on HsColour library. - - - - - 6e52291f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create basic token classification method. - - - - - da971a27 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Adapt source span tagging to work with current whitespace handling. - - - - - 4feb5a22 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add record accessors to exports of hyperlinker parser module. - - - - - a8cc4e39 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Make parser module export all types and associated accessors. - - - - - fb8d468f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple HTML renderer for parsed source file. - - - - - 80747822 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for specifying the CSS file path in HTML source renderer. - - - - - 994dc1f5 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix identifier recognition in Haskell source parser. - - - - - b1bd0430 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix comment recognition in Haskell source parser. - - - - - 11db85ae by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for recognizing compiler pragmas in source parser. - - - - - 736c7bd3 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding of module for associating tokens with AST names. - - - - - 7e149bc2 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement utility method for extracting variable identifiers from AST. - - - - - 32eb640a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple mechanism for associating tokens with AST names. - - - - - d4eba5bc by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add dummy support for hyperlinking named tokens. - - - - - 2b76141f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matcher bug causing wrong items being hyperlinked. - - - - - 2d48002e by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Constrain elements exported by hyperlinker modules. - - - - - 9715eec6 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for type token recognition. - - - - - 8fa401cb by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for binding token recognition. - - - - - d062400b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement go-to-definition mechanism for local bindings. - - - - - f4dc229b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement module export- and import-list item hyperlinking. - - - - - c9a46d58 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matching to allow parenthesized operators hyperlinking. - - - - - 03aad95a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix weird hyperlinking of parenthesized operators. - - - - - b4694a7d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for type declaration anchors. - - - - - 7358d2d2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for top-level function declaration anchors. - - - - - dfc24b24 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix external anchors to contain HTML file extension. - - - - - a045926c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Refactor the way AST names are handled within detailed tokens. - - - - - c76049b4 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement hyperlinking of imported module names. - - - - - 2d2a1572 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix parsing of single line comments with broken up newlines. - - - - - 11afdcf2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix bug with improper newline handling. - - - - - 8137f104 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issues with escaped newlines in comments. - - - - - 34759b19 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for parsing C preprocessor macros. - - - - - 09f0f847 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for parser module of source hyperlinker. - - - - - 709a8389 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for AST module of source hyperlinker. - - - - - 4df5c227 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add command line option for generating hyperlinked source. - - - - - 7a755ea2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Extend module interface with rich source token stream field. - - - - - 494f4ab1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement source tokenization during interface creation process. - - - - - 5f21c953 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create hyperlinker module and plug it into the Haddock pipeline. - - - - - 0cc8a216 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for providing custom CSS files for hyperlinked source. - - - - - a32bbdc1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for fancy highlighting upon hovering over identifier. - - - - - d16d642a by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make source hyperlinker generate output in apropriate directory. - - - - - ae12953d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create module with hyperlinker utility functions. - - - - - 6d4952c5 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make external hyperlinks point to locations specified by source URLs. - - - - - 8417555d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Rewrite source generation to fixed links and directory structure. - - - - - ce9cec01 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add basic support for cross-package hyperlink generation. - - - - - 7eaf025c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Disable generating hyperlinks for module references. - - - - - a50bf92e by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make Haddock generate source for all interfaces (also hidden ones). - - - - - f5ae2838 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Prevent source parser from throwing exception when lexing fails. - - - - - db9ffbe0 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement workaround for Chrome highlighting issues. - - - - - 0b6b453b by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate correct anchors for data constructors. - - - - - c86d38bc by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate anchors for record field declarations. - - - - - 063abf7f by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issue with hyperlink highlight styling in Chrome browser. - - - - - 880fc611 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking constructor names in patters. - - - - - c9e89b95 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record patterns. - - - - - 17a11996 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record expressions. - - - - - 0eef932d by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Make hyperlinker respect pretty-printer flag and add documentation. - - - - - f87c1776 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Unexpose hyperlinker modules in Cabal configuration. - - - - - 4c9e2b06 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Setup HSpec framework for Haddock API package. - - - - - 4b20cb30 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add basic tests related to comment parsing. - - - - - 6842e919 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add tests related to parsing basic language constructs. - - - - - 87bffb35 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add simple tests for do-notation parsing. - - - - - e7af1841 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add very simple QuickCheck properties for source parser spec. - - - - - c84efcf1 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Create simple test runner for hyperlinker tests. - - - - - 76b90447 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for basic identifier hyperlinking. - - - - - 0fbf4df6 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for operator hyperlinking. - - - - - 731aa039 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for constructor hyperlinking. - - - - - 995a78a2 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for record expressions and patterns hyperlinking. - - - - - 3566875a by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for literal syntax highlighting. - - - - - 68469a35 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add hyperlinker test runner to .cabal and .gitignore files. - - - - - aa946c93 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Adapt hyperlinker test runner to have the same interface as HTML one. - - - - - ce34da16 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Fix hyperlinker test runner file paths and add pretty-printing option. - - - - - 0d7dd65e by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add reference files for hyperlinker test cases. - - - - - efa4a1e0 by Łukasz Hanuszczak at 2015-07-01T00:47:32+02:00 Make hyperlinker test runner strip local links from generated source. - - - - - 3e96e584 by Łukasz Hanuszczak at 2015-07-01T01:14:59+02:00 Create simple script for accepting hyperlinker test case references. - - - - - 526fe610 by Łukasz Hanuszczak at 2015-07-01T01:16:41+02:00 Re-accept hyperlinker test cases with local references stripped out. - - - - - 892e2cb3 by Łukasz Hanuszczak at 2015-07-01T01:22:09+02:00 Fix bug with diffing wrong files in hyperlinker test runner. - - - - - 9ff46039 by Łukasz Hanuszczak at 2015-07-01T18:04:46+02:00 Remove unused dependencies in Haddock API spec configuration. - - - - - 47969c07 by Łukasz Hanuszczak at 2015-07-01T18:32:19+02:00 Add support for hyperlinking synonyms in patterns. - - - - - a73449e0 by Łukasz Hanuszczak at 2015-07-01T18:33:44+02:00 Create test case for hyperlinking @-patterns. - - - - - c2077ed8 by Łukasz Hanuszczak at 2015-07-01T19:06:04+02:00 Add support for hyperlinking universally quantified type variables. - - - - - 68017342 by Łukasz Hanuszczak at 2015-07-01T19:28:32+02:00 Create hyperlinker test case with quantified type variables. - - - - - 51c01a78 by Łukasz Hanuszczak at 2015-07-01T19:34:22+02:00 Add scoped type variables test for polymorphism test case. - - - - - 13181ae2 by Łukasz Hanuszczak at 2015-07-01T19:56:27+02:00 Add record wildcards test for records hyperlinking test case. - - - - - 991b81dd by Łukasz Hanuszczak at 2015-07-01T21:01:42+02:00 Document some functions in XHTML utlity module. - - - - - 98c8dfe5 by Łukasz Hanuszczak at 2015-07-01T22:25:21+02:00 Make hyperlinker render qualified names as one entity. - - - - - 75e13b9b by Łukasz Hanuszczak at 2015-07-01T22:27:38+02:00 Add qualified name test for identifiers hyperlinking test case. - - - - - de1e143f by Łukasz Hanuszczak at 2015-07-02T12:32:59+02:00 Fix crash happening when hyperlinking type family declarations. - - - - - 7a8fb175 by Łukasz Hanuszczak at 2015-07-02T12:47:03+02:00 Add support for anchoring data family constructor declarations. - - - - - 3b404e49 by Łukasz Hanuszczak at 2015-07-02T13:31:05+02:00 Improve support for hyperlinking type families. - - - - - 59eb7143 by Łukasz Hanuszczak at 2015-07-02T13:33:34+02:00 Add hyperlinker test case for checking type and type family declarations. - - - - - d1cda0c0 by Łukasz Hanuszczak at 2015-07-02T13:41:38+02:00 Fix issue with operators being recognized as preprocessor directives. - - - - - da206c9d by Łukasz Hanuszczak at 2015-07-02T17:18:12+02:00 Fix broken tests for parsing and hyperlinking hash operators. - - - - - 53750d1b by Łukasz Hanuszczak at 2015-07-02T18:53:28+02:00 Add support for anchoring signatures in type class declarations. - - - - - 1fa5bb10 by Łukasz Hanuszczak at 2015-07-02T19:04:47+02:00 Make hyperlinker generate anchors only to top-level value bindings. - - - - - a542305c by Łukasz Hanuszczak at 2015-07-02T19:05:58+02:00 Create hyperlinker test case for type classes. - - - - - b0dd4581 by Łukasz Hanuszczak at 2015-07-04T16:28:26+02:00 Update docs with information about source hyperlinking. - - - - - 9795302a by Łukasz Hanuszczak at 2015-07-04T16:52:15+02:00 Update docs on using `--read-interface` option. - - - - - 9acdc002 by Łukasz Hanuszczak at 2015-07-04T17:15:26+02:00 Remove potentially dangerous record access in hyperlinker AST module. - - - - - fb3ab7be by Łukasz Hanuszczak at 2015-07-04T17:40:10+02:00 Make Haddock generate warnings about potential misuse of hyperlinker. - - - - - a324c504 by Łukasz Hanuszczak at 2015-07-04T17:43:22+02:00 Fix incorrect specification of source style option in doc file. - - - - - 3f01a8e4 by Łukasz Hanuszczak at 2015-07-05T17:06:36+02:00 Refactor source path mapping to use modules as indices. - - - - - ac70f5b1 by Łukasz Hanuszczak at 2015-07-05T17:47:34+02:00 Fix bug where not all module interfaces were added to source mapping. - - - - - f5e57da9 by Łukasz Hanuszczak at 2015-07-06T16:39:57+02:00 Extract main hyperlinker types to separate module. - - - - - 43974905 by Łukasz Hanuszczak at 2015-07-06T16:52:13+02:00 Move source paths types to hyperlinker types module. - - - - - 3e236055 by Łukasz Hanuszczak at 2015-07-06T17:06:19+02:00 Add support for hyperlinking modules in import lists. - - - - - 58233d9f by Łukasz Hanuszczak at 2015-07-06T17:26:49+02:00 Add short documentation for hyperlinker source map type. - - - - - 14da016d by Łukasz Hanuszczak at 2015-07-06T18:07:20+02:00 Fix bug with module name being hyperlinked to `Prelude`. - - - - - 8f79db52 by Łukasz Hanuszczak at 2015-07-06T18:23:47+02:00 Fix problem with spec build in Haddock API configuration. - - - - - e7cc056c by Adam Sandberg Eriksson at 2015-07-07T23:22:21+01:00 StrictData: print correct strictness marks - - - - - e8253ca8 by Mateusz Kowalczyk at 2015-07-07T23:58:28+01:00 Update changelog - - - - - 0aba676b by Mateusz Kowalczyk at 2015-07-07T23:58:33+01:00 Relax upper bound on GHC a bit - - - - - 7a595381 by Mateusz Kowalczyk at 2015-07-07T23:58:52+01:00 Delete trailing whitespace - - - - - 50976d5e by Adam Sandberg Eriksson at 2015-07-08T15:03:04+02:00 StrictData: changes in HsBang type - - - - - 83b045fa by Mateusz Kowalczyk at 2015-07-11T14:35:18+01:00 Fix expansion icon for user-collapsible sections Closes haskell/haddock#412 - - - - - b2a3b0d1 by Mateusz Kowalczyk at 2015-07-22T22:03:21+01:00 Make some version changes after 2.16.1 release - - - - - a8294423 by Ben Gamari at 2015-07-27T13:16:07+02:00 Merge pull request haskell/haddock#422 from adamse/adamse-D1033 Merge for GHC D1033 - - - - - c0173f17 by randen at 2015-07-30T14:49:08-07:00 Break the response file by line termination rather than spaces, since spaces may be within the parameters. This simple approach avoids having the need for any quoting and/or escaping (although a newline char will not be possible in a parameter and has no escape mechanism to allow it). - - - - - 47c0ca14 by Alan Zimmerman at 2015-07-31T10:41:52+02:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - 45a9d770 by Mateusz Kowalczyk at 2015-07-31T09:47:43+01:00 Update changelog - - - - - 347a20a3 by Phil Ruffwind at 2015-08-02T23:15:26+01:00 Avoid JavaScript error during page load in non-frame mode In non-frame mode, parent.window.synopsis refers to the synopsis div rather than the nonexistent frame. Unfortunately, the script wrongly assumes that if it exists it must be a frame, leading to an error where it tries to access the nonexistent attribute 'replace' of an undefined value (synopsis.location). Closes haskell/haddock#406 - - - - - 54ebd519 by Phil Ruffwind at 2015-08-02T23:27:10+01:00 Link to the definitions to themselves Currently, the definitions already have an anchor tag that allows URLs with fragment identifiers to locate them, but it is rather inconvenient to obtain such a URL (so-called "permalink") as it would require finding the a link to the corresponding item in the Synopsis or elsewhere. This commit adds hyperlinks to the definitions themselves, allowing users to obtain links to them easily. To preserve the original aesthetics of the definitions, we alter the color of the link so as to be identical to what it was, except it now has a hover effect indicating that it is clickable. Additionally, the anchor now uses the 'id' attribute instead of the (obsolete) 'name' attribute. Closes haskell/haddock#407 - - - - - 02cc8bb7 by Phil Ruffwind at 2015-08-02T23:28:02+01:00 Fix typo in Haddock.Backends.Xhtml.Layout: divSynposis -> divSynopsis Closes haskell/haddock#408 - - - - - 2eb0a458 by Phil Ruffwind at 2015-08-02T23:30:07+01:00 Fix record field alignment when name is too long Change <dl> to <ul> and use display:table rather than floats to layout the record fields. This avoids bug haskell/haddock#301 that occurs whenever the field name gets too long. Slight aesthetic change: the entire cell of the field's source code is now shaded gray rather than just the area where text exists. Fixes haskell/haddock#301. Closes haskell/haddock#421 - - - - - 7abb3402 by Łukasz Hanuszczak at 2015-08-02T23:32:14+01:00 Add some utility definitions for generating line anchors. - - - - - e0b1d79b by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Make hyperlinked source renderer generate line anchors. - - - - - 24dd4c9f by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Re-accept test cases after adding line anchors for each of them. - - - - - 0372cfcb by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Override source line flags when source hyperlinker is enabled. - - - - - a81bcd07 by Mateusz Kowalczyk at 2015-08-02T23:58:25+01:00 Update tests to follow HTML changes - - - - - d2d7426f by Łukasz Hanuszczak at 2015-08-06T20:54:59+02:00 Fix quote syntax for promoted types. - - - - - 668cf029 by Łukasz Hanuszczak at 2015-08-06T21:12:00+02:00 Apply promoted type quoting to type-level consing. - - - - - 89f8e7c6 by Łukasz Hanuszczak at 2015-08-06T21:17:10+02:00 Extend advanced types test case with other examples. - - - - - 86494bca by Łukasz Hanuszczak at 2015-08-06T21:22:06+02:00 Rename advanced types test case and accept new output. - - - - - dbb7c7c0 by Adam Sandberg Eriksson at 2015-08-09T23:01:05+02:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 2a7704fa by Ben Gamari at 2015-08-10T13:18:05+02:00 Merge pull request haskell/haddock#433 from adamse/split-hsbang HsBang is split into HsSrcBang and HsImplBang - - - - - 891954bc by Thomas Miedema at 2015-08-15T14:51:18+02:00 Follow changes in GHC build system - - - - - b55d32ab by Mateusz Kowalczyk at 2015-08-21T18:06:09+01:00 Make Travis use 7.10.2 - - - - - 97348b51 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Move SYB utilities to standalone module. - - - - - 748ec081 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement `everywhere` transformation in SYB module. - - - - - 011cc543 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement generic transformation constructor. - - - - - b9510db2 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Create simple utility module for type specialization. - - - - - 43229fa6 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Make type of type specialization function more general. - - - - - fd844e90 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Add basic HTML test case for checking instance specialization. - - - - - 6ea0ad04 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Make HTML class instance printer take optional signature argument. - - - - - 65aa41b6 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Refactor instance head type to record instead of a meaningless tuple. - - - - - 3fc3bede by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add expandable method section for each class instance declaration. - - - - - 99ceb107 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Move dummy post-family instances for `DocName` to `Types` module. - - - - - e98f4708 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create convenience functions for type specialization module. - - - - - b947552f by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Hook type specialization logic with HTML pretty-printer. - - - - - dcaa8030 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create stub functions for sugaring specialized types. - - - - - fa84bc65 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement list syntax sugaring logic for specialized types. - - - - - e8b05b07 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement tuple syntax sugaring logic for specialized types. - - - - - 68a2e5bc by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Get rid of code duplication in type specialization module. - - - - - 4721c336 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create scaffolding of a framework for renaming specialized types. - - - - - 271b488d by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in missing cases in specialized type renaming function. - - - - - bfa5f2a4 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Remove code duplication in specialized type renamer. - - - - - ea6bd0e8 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Change state of the type renaming monad. - - - - - 77c5496e by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement simple mechanism for generating new type names. - - - - - 91bfb48b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in stub behaviour with actual environment renaming. - - - - - d244517b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix logic behind binder type renaming. - - - - - f3c5e360 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add SYB-like utility function for performing stateful queries. - - - - - eb3f9154 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create function for retrieving free variables from given type. - - - - - a94561d3 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix compilation error caused by incorrect type signature. - - - - - 8bb707cf by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Move `SetName` class definition to types module. - - - - - 5800b13b by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Hook type renamer with instance method HTML pretty-printer. - - - - - 6a480164 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some test cases for type renamer. - - - - - 839842f7 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized signatures refer to original signature declaration. - - - - - 4880f7c9 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized methods be nicely formatted again. - - - - - ab5a6a2e by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Attach source locations to the specialized class methods. - - - - - 43f8a559 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Extend instances test case to also test multi-name type signatures. - - - - - 59bc751c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix tab-based indentation in instances test case. - - - - - c2126815 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Improve placement of instance methods expander button. - - - - - 0a32e287 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add new data type declaration to instance specialization test case. - - - - - 5281af1f by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make type renamer first try single-letter names as alternatives. - - - - - 7d509475 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix type renamer bug with incorrect names being generated. - - - - - 0f35bf7c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some documentation and refactor type specialization module. - - - - - da1d0803 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix another bug where type renamer was generating incorrect names. - - - - - cd39b5cb by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Refactor type renamer to rebinding and pure renaming phases. - - - - - 850251f4 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix unwitting compilation bug. - - - - - e5e9fc01 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Integrate instance specification type into class instance definition. - - - - - 825b0ea0 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer neccessary instance specification type. - - - - - cdba44eb by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix declaration converter to use more appropriate mode for methods. - - - - - bc45c309 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug with types not being specialized at all. - - - - - 5d8e5d89 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug where instance expander was opening wrong section. - - - - - 6001ee41 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix another type renamer bug where not all names were rebound. - - - - - 5f58ce2a by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix yet another renamer bug where some names were not unique. - - - - - 8265e521 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split instance subsection layout method to top-level declarations. - - - - - e5e66298 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Rearrange layout of instance methods in generated documentation. - - - - - a50b4eea by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer used layout method. - - - - - 2ff36ec2 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach section title to the instance methods block. - - - - - 7ac15300 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Add basic tests for associated types in instances test case. - - - - - db0ea2f9 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach associated types information to instance header. - - - - - 71cad4d5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details section contain associated types information. - - - - - deee2809 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Improve look of rendered associated families in instance details. - - - - - 839d13a5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Introduce alternative type for family declarations. - - - - - d397f03f by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details record use new type for family declarations. - - - - - 2b23fe97 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split printer of type family header to separate functions. - - - - - c3498cdc by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Implement HTML renderer for pseudo-family declarations. - - - - - c12bbb04 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Apply type specializer to associated type family declarations. - - - - - 2fd69ff2 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Create helper method for specializing type signatures. - - - - - 475826e7 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Refactor specializer module to be independent from XHTML backend. - - - - - f00b431c by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add some documentation for instance head specializer. - - - - - a9fef2dc by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix bug with missing space in documentation for associated types. - - - - - 50e29056 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with incorrect instance details sections being expanded. - - - - - e6dfdd03 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by adding instance details section. - - - - - 75565b2a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make section identifier of instance details more GHC-independent. - - - - - add0c23e by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Re-accept tests after applying deterministic section identifiers. - - - - - 878f2534 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make identifier generation also architecture-independent. - - - - - 48be69f8 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with instance expander hijacking type hyperlink click. - - - - - 47830c1f by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Get rid of dreadful hashing function for generating identifiers. - - - - - 956cd5af by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Move `InstOrigin` type declaration to more appropriate module. - - - - - bf672ed3 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by changes related to instance expander. - - - - - 8f2a949a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add examples with type operators to the instances test case. - - - - - 64600a84 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add basic support for sugaring infix type operators. - - - - - 747d71b8 by Łukasz Hanuszczak at 2015-08-21T18:22:34+01:00 Add support for sugaring built-in function syntax. - - - - - d4696ffb by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Remove default methods from Hoogle class output. - - - - - bf0e09d7 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add fixity declarations in Hoogle backend output. - - - - - 90e91a51 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix bug with incorrect fixities being generated in Hoogle backend. - - - - - 48f11d35 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve class type family declarations output in Hoogle backend. - - - - - 661e8e8f by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add missing default family equations in Hoogle output. - - - - - e2d64103 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve formatting of class details output in Hoogle backend. - - - - - 490fc377 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix weird-looking Hoogle output for familyless classes. - - - - - ea115b64 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create script file for new HTML test runner. - - - - - 609913d3 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Set default behaviour if no arguments given. - - - - - dc115f67 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for providing optional arguments for test runner. - - - - - d93ec867 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve output of test runner error messages. - - - - - 0be9fe12 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for executing Haddock process in test runner. - - - - - 4e4d00d9 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add GHC path to test runner configuration. - - - - - d67a2086 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make GHC path a test runner command-line argument. - - - - - c810079a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Extend test runner configuration with Haddock arguments. - - - - - fee18845 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor test runner and create stub functions. - - - - - ff7c161f by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make test runner actually run Haddock executable. - - - - - 391f73e6 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with test runner not producing any output files. - - - - - 81a74e2d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Setup skeleton of framework for running tests. - - - - - f8a79ec4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with modules not being found in global search mode. - - - - - 7e700b4d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make Haddock standard output redirection be more configurable. - - - - - 53b4c17a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Incorporate old, ugly functions for comparing output files. - - - - - 8277c8aa by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor architecture of test runner output checking functions. - - - - - 587bb414 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement actual diffing mechanism. - - - - - 9ed2b5e4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve code style to match popular guidelines. - - - - - 14bffaf8 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make it possible to choose alternative diff tool. - - - - - 5cdfb005 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create stub methods for processing test output as XML documents. - - - - - 7ef8e12e by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement link-stripping logic as simple SYB transformation. - - - - - 8a1fcd4f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Incorporate link stripping to output diffing mechanism. - - - - - 37dba2bc by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement footer-stripping logic. - - - - - 9cd52120 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Add missing dependencies in Cabal configuration file. - - - - - e0f83c6e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix issue with output being printed in incorrect order. - - - - - 0a94fbb0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to run tests without generating diff. - - - - - 76a58c6f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor HTML test suite boilerplate to external package. - - - - - af41e6b0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utilities for storing directory configuration. - - - - - d8f0698f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move IO-dependent config of HTML test suite to test package. - - - - - 17369fa0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Enable all compiler warnings in Haddock test package configuration. - - - - - 9d03b47a by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move Haddock runner of HTML test suite to Haddock test package. - - - - - 4b3483c5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 03754194 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience wrappers to simplify in test entry points. - - - - - 27476ab7 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adjust module visibility and items they export. - - - - - c40002ba by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Remove no longer useful test option. - - - - - 55ab2541 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Change extension of test files used for diffing. - - - - - 136bf4e4 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor and simplify XHTML helper module of test package. - - - - - 69f7e3df by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix typo in link stripper of HTML test suite runner. - - - - - 0c3c1c6b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience script for running specific HTML tests. - - - - - 489e1b05 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement utility functions for conditional link stripping. - - - - - 0f985dc3 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt `hypsrc-test` module to work with new testing framework. - - - - - 927406f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement output accepting mechanism in test package. - - - - - 8545715e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utility function for recursive obtaining directory contents. - - - - - cb70381f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 019599b5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix path handling in test runner. - - - - - 399b985b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to specify ignored files for test output. - - - - - 41b3d93d by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt HTML test runner to use new ignoring functionality. - - - - - e2091c8b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix bug with not all test output files being checked. - - - - - b22134f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Specify ignored files for hyperlinker source test runner. - - - - - 3301dfa1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Copy test runner script for hyperlinked source case. - - - - - d39a6dfa by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner invoking Haddock in incorrect mode. - - - - - f32c8ff3 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix path handling in test module loader. - - - - - 10f94ee9 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make test runner ignore test packages with no modules. - - - - - 5dc4239c by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create test runner entry points for LaTeX test suite. - - - - - 58d1f7cf by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with unnecessary checking old test output. - - - - - c7ce76e1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Re-implement test acceptance functionality. - - - - - 13bbabe8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix warning about no longer needed definition. - - - - - 958a99b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Adapt Cabal configuration to execute LaTeX suite with new runner. - - - - - 550ff663 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Setup test suite for Hoogle backend. - - - - - 3aa969c4 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make Hoogle backend create output directory if needed. - - - - - eb085b02 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Add appropriate .gitignore entry and configure Hoogle test suite. - - - - - a50bf915 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner failing when run on multiple test packages. - - - - - bf5368b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create simple test cases for Hoogle backend. - - - - - 6121ba4b by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create helper function for conversion between XML and XHTML. - - - - - cb516061 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Refactor existing code to use XHTML printer instead of XML one. - - - - - e2de8c82 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Improve portability of test runner scripts. - - - - - 9563e774 by Łukasz Hanuszczak at 2015-08-22T23:43:16+02:00 Remove redundant import statement. - - - - - 55353df1 by Łukasz Hanuszczak at 2015-08-24T23:09:20+02:00 Fix bug with accepting to non-existing directory. - - - - - 00a334ca by Łukasz Hanuszczak at 2015-08-24T23:09:47+02:00 Accept output for Hoogle and LaTeX backends. - - - - - 29191d8b by Łukasz Hanuszczak at 2015-08-24T23:14:18+02:00 Get rid of obsolete testing utilities. - - - - - bbb25db3 by Łukasz Hanuszczak at 2015-08-24T23:18:50+02:00 Update sandbox setup guide to work with Haddock test package. - - - - - cfd45248 by Łukasz Hanuszczak at 2015-08-24T23:51:30+02:00 Make Travis aware of Haddock test package. - - - - - 74185b7a by Łukasz Hanuszczak at 2015-08-25T17:41:59+02:00 Fix test suite failure when used with Stack. - - - - - 18769697 by Łukasz Hanuszczak at 2015-08-25T18:02:09+02:00 Add sample Stack setup to the hacking guide. - - - - - 22715eeb by Łukasz Hanuszczak at 2015-08-25T18:04:47+02:00 Fix Markdown formatting of README file. - - - - - b49ec386 by Łukasz Hanuszczak at 2015-08-25T18:13:36+02:00 Setup Haddock executable path in Travis configuration. - - - - - 5d29eb03 by Eric Seidel at 2015-08-30T09:55:58-07:00 account for changes to ipClass - - - - - f111740a by Ben Gamari at 2015-09-02T13:20:37+02:00 Merge pull request haskell/haddock#443 from bgamari/ghc-head account for changes to ipClass - - - - - a2654bf6 by Jan Stolarek at 2015-09-03T01:32:57+02:00 Follow changes from haskell/haddock#6018 - - - - - 2678bafe by Richard Eisenberg at 2015-09-21T12:00:47-04:00 React to refactoring CoAxiom branch lists. - - - - - ebc56e24 by Edward Z. Yang at 2015-09-21T11:53:46-07:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4a8c4198 by Tamar Christina at 2015-09-27T13:59:08+02:00 Create Process: removed PhaseFailed - - - - - 7e99b790 by Oleg Grenrus at 2015-09-27T20:52:10+03:00 Generate docs for orphan instances - - - - - 32e932e2 by Oleg Grenrus at 2015-09-28T07:21:11+03:00 Have source links for orphan instances - - - - - c2eb9f4f by Oleg Grenrus at 2015-09-28T07:24:58+03:00 Print orphan instances header only if required - - - - - ff96f978 by Oleg Grenrus at 2015-09-28T07:40:54+03:00 Add orphan instances link to contents box - - - - - d72490a6 by Oleg Grenrus at 2015-09-28T16:37:44+03:00 Fix orphan instance collapsing - - - - - 25d3dfe5 by Ben Gamari at 2015-10-03T12:38:09+02:00 Merge pull request haskell/haddock#448 from Mistuke/fix-silent-death-of-runInteractive Remove PhaseFailed - - - - - 1e45e43b by Edward Z. Yang at 2015-10-11T13:10:10-07:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b1370ac1 by Adam Gundry at 2015-10-16T16:26:42+01:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 60bef421 by Simon Peyton Jones at 2015-10-26T12:52:36+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 4c1898ca by Simon Peyton Jones at 2015-10-27T14:24:56+00:00 Track change to PatSyn.patSynSig - - - - - 25108e85 by Simon Peyton Jones at 2015-10-27T17:34:18+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - 693643ac by Ben Gamari at 2015-10-28T14:33:06+01:00 Account for Typeable changes The treatment of type families changed. - - - - - cd7c2221 by Simon Peyton Jones at 2015-10-30T13:03:51+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - 712032cb by Herbert Valerio Riedel at 2015-10-31T11:01:45+01:00 Relax upper bound on `base` to allow base-4.9 - - - - - 0bfa0475 by Simon Peyton Jones at 2015-10-31T19:08:13+00:00 More adaption to wildcard-refactor - - - - - 0a3c0cb7 by Simon Peyton Jones at 2015-10-31T22:14:43+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - c4fd4ec9 by Alan Zimmerman at 2015-11-01T11:16:34+01:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 42cdd882 by Matthew Pickering at 2015-11-06T20:02:16+00:00 Change for IEThingWith - - - - - f368b7be by Ben Gamari at 2015-11-11T11:35:51+01:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - e32965b8 by Simon Peyton Jones at 2015-11-13T12:18:17+00:00 Merge with origin/head - - - - - ebcf795a by Edward Z. Yang at 2015-11-13T21:56:27-08:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4e23989f by Simon Peyton Jones at 2015-11-18T11:32:54+00:00 Wibbles to Haddock - - - - - 2289cd4a by Simon Peyton Jones at 2015-11-20T23:12:49+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor - - - - - 695975a6 by Alan Zimmerman at 2015-11-21T21:16:12+02:00 Update to match GHC wip/T11019 - - - - - bbba21e7 by Simon Peyton Jones at 2015-11-23T13:54:31+00:00 merge with origin/ghc-head - - - - - 3d664258 by Simon Peyton Jones at 2015-11-23T17:17:18+00:00 Wibble - - - - - e64cf586 by Herbert Valerio Riedel at 2015-12-05T00:29:55+01:00 Canonicalise Monad instances - - - - - a2de15a7 by Alan Zimmerman at 2015-12-05T17:33:52+02:00 Matching changes for haskell/haddock#11028 - - - - - cc29a3e4 by Alan Zimmerman at 2015-12-05T19:45:33+02:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 95dd15d1 by Richard Eisenberg at 2015-12-11T17:33:39-06:00 Update for type=kinds - - - - - cb5fd9ed by Herbert Valerio Riedel at 2015-12-14T15:07:30+00:00 Bump versions for ghc-7.11 - - - - - 4f286d96 by Simon Peyton Jones at 2015-12-14T15:10:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 13ea2733 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 098df8b8 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track changes in HsSyn for quasi-quotes - - - - - 716a64de by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track change in API of TyCon - - - - - 77a66bca by Adam Gundry at 2015-12-14T15:10:58+00:00 Track API changes to support empty closed type familes - - - - - f2808305 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track the new location of setRdrNameSpace - - - - - ba8b08a4 by Alan Zimmerman at 2015-12-14T15:10:59+00:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - a4ded87e by Thomas Winant at 2015-12-14T15:14:05+00:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 25c78107 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: print correct strictness marks - - - - - 6cbc41c4 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: changes in HsBang type - - - - - ad46821a by Alan Zimmerman at 2015-12-14T15:14:06+00:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - abc0ae5b by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 3308d06c by Thomas Miedema at 2015-12-14T15:14:07+00:00 Follow changes in GHC build system - - - - - 6c763deb by Eric Seidel at 2015-12-14T15:14:07+00:00 account for changes to ipClass - - - - - ae5b4eac by Jan Stolarek at 2015-12-14T15:17:00+00:00 Follow changes from haskell/haddock#6018 - - - - - ffbc40e0 by Richard Eisenberg at 2015-12-14T15:17:02+00:00 React to refactoring CoAxiom branch lists. - - - - - d1f531e9 by Edward Z. Yang at 2015-12-14T15:17:02+00:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 79f73754 by Tamar Christina at 2015-12-14T15:17:02+00:00 Create Process: removed PhaseFailed - - - - - 3d37bebb by Edward Z. Yang at 2015-12-14T15:20:46+00:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 5f8a9e44 by Adam Gundry at 2015-12-14T15:20:48+00:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 79dda70f by Simon Peyton Jones at 2015-12-14T15:26:02+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 959930fb by Simon Peyton Jones at 2015-12-14T15:37:50+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - e18a8df5 by Simon Peyton Jones at 2015-12-14T15:37:52+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - aa35ab52 by Simon Peyton Jones at 2015-12-14T15:40:18+00:00 More adaption to wildcard-refactor - - - - - 8ceef94b by Simon Peyton Jones at 2015-12-14T15:46:04+00:00 Track change to PatSyn.patSynSig - - - - - cd81e83d by Ben Gamari at 2015-12-14T15:46:06+00:00 Account for Typeable changes The treatment of type families changed. - - - - - 63c9117c by Herbert Valerio Riedel at 2015-12-14T15:46:34+00:00 Relax upper bound on `base` to allow base-4.9 - - - - - a484c613 by Alan Zimmerman at 2015-12-14T15:47:46+00:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 2c26fa51 by Matthew Pickering at 2015-12-14T15:47:47+00:00 Change for IEThingWith - - - - - 593baa0f by Ben Gamari at 2015-12-14T15:49:21+00:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - b6b5ca78 by Edward Z. Yang at 2015-12-14T15:49:54+00:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b5b0e072 by Alan Zimmerman at 2015-12-14T15:54:20+00:00 Update to match GHC wip/T11019 - - - - - 14ddeb68 by Simon Peyton Jones at 2015-12-14T15:54:22+00:00 Wibble - - - - - 10a90ad8 by Herbert Valerio Riedel at 2015-12-14T15:54:22+00:00 Canonicalise Monad instances - - - - - ed68ac50 by Alan Zimmerman at 2015-12-14T15:55:48+00:00 Matching changes for haskell/haddock#11028 - - - - - 3f7e5a2d by Alan Zimmerman at 2015-12-14T15:55:49+00:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 6543a73f by Richard Eisenberg at 2015-12-14T15:59:55+00:00 Update for type=kinds - - - - - 193a5c48 by Matthew Pickering at 2015-12-14T18:17:00+00:00 Changes to compile with 8.0 - - - - - add669ec by Matthew Pickering at 2015-12-14T18:47:12+00:00 Warnings - - - - - 223f3fb4 by Ben Gamari at 2015-12-15T23:45:05+01:00 Update for D1200 - - - - - d058388f by Ben Gamari at 2015-12-16T05:40:17-05:00 Types: Add Outputable[Bndr] DocName instances - - - - - 62ecd7fb by Ben Gamari at 2015-12-16T09:23:09-05:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ddbc187a by Ben Gamari at 2015-12-16T17:54:55+01:00 Update for D1200 - - - - - cec83b52 by Ben Gamari at 2015-12-16T17:54:55+01:00 Types: Add Outputable[Bndr] DocName instances - - - - - d12ecc98 by Ben Gamari at 2015-12-16T17:54:55+01:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ada1616f by Ben Gamari at 2015-12-16T17:54:58+01:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a4f0383d by Ben Gamari at 2015-12-16T23:32:38+01:00 Fix Hyperlinker GHC.con_names is now GHC.getConNames - - - - - a10e6849 by Ben Gamari at 2015-12-20T00:54:11+01:00 Merge remote-tracking branch 'mrhania/testing-framework-improvements' into ghc-head - - - - - f078b4fd by Ben Gamari at 2015-12-20T00:59:51+01:00 test: Compatibility with Cabal 1.23 - - - - - 88a511a9 by Ben Gamari at 2015-12-20T01:14:35+01:00 Merge remote-tracking branch 'phadej/orphans' into ghc-head - - - - - 4e250f36 by Ben Gamari at 2015-12-20T01:14:52+01:00 Add html-test for orphan instances output - - - - - 87fffbad by Alan Zimmerman at 2015-12-20T09:50:42+02:00 Update for GHC trac#11258 Adding locations to RdrName in FieldOcc and AmbiguousFieldOcc - - - - - 6b7e51c9 by idontgetoutmuch at 2015-12-20T21:01:47+00:00 Merge pull request haskell/haddock#1 from haskell/ghc-head Ghc head - - - - - 229c1fb5 by Dominic Steinitz at 2015-12-21T07:19:16+00:00 Handle inline math with mathjax. - - - - - 57902d66 by Dominic Steinitz at 2015-12-21T08:07:11+00:00 Fix the documentation for haddock itself. Change notation and add support for inline math. Allow newlines in display math. Add a command line option for the mathjax url (you might want to use a locally installed version). Rebase tests because of extra url and version change. Respond to (some of the) comments. Fix warnings in InterfaceFile.hs - - - - - 0e69f236 by Herbert Valerio Riedel at 2015-12-21T18:30:43+01:00 Fix-up left-over assumptions of GHC 7.12 into GHC 8.0 - - - - - c67f8444 by Simon Peyton Jones at 2015-12-22T16:26:56+00:00 Follow removal of NamedWildCard from HsType - - - - - da40327a by Ben Gamari at 2015-12-23T14:15:28+01:00 html-test/Operators: Clear up ambiguous types For reasons that aren't entirely clear a class with ambiguous types was accepted by GHC <8.0. I've added a functional dependency to clear up this ambiguity. - - - - - 541b7fa4 by Ben Gamari at 2015-12-23T14:18:51+01:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 0febc947 by Ben Gamari at 2015-12-24T00:30:20+01:00 hoogle-test/AssocTypes: Allow AmbiguousTypes GHC 8.0 complains otherwise - - - - - 25810841 by Ben Gamari at 2015-12-24T00:33:18+01:00 OrphanInstances: Accept test output - - - - - 841987f3 by Ben Gamari at 2015-12-25T11:03:11+01:00 Merge remote-tracking branch 'idontgetoutmuch/ghc-head' into ghc-head - - - - - 358391f0 by Ben Gamari at 2015-12-26T10:44:50+01:00 Add missing import - - - - - a8896885 by Ben Gamari at 2015-12-26T10:45:27+01:00 travis: Use Travis containers - - - - - 85e82134 by Herbert Valerio Riedel at 2015-12-30T17:25:39+01:00 tweak version bounds for GHC-8.1 - - - - - 672a5f75 by randen at 2016-01-01T23:45:25-08:00 The Haddock part for fully gcc-like response files " driver/Main.hs * Moved the response file handling into ResponseFile.hs, updating import section as appropriate. * driver/ResponseFile.hs * New file. In anticipation that maybe some day this could be provided by another library, and to make it possible to unit test, this functionality is pulled out of the Main.hs module, and expanded to support the style/format of response files which gcc uses. * The specification for the format of response files which gcc generates and consumes, seems to be best derived from the gcc code itself (libiberty/argv.c), so that is what has been done here. * This is intended to fix haskell/haddock#379 * driver-test/Main.hs * New file for testing code in the driver source tree * driver-test/ResponseFileSpec.hs * Tests, adapted/adopted from the same gcc code where the escaping/unescaping is from, in the hspec style of unit tests * haddock.cabal * Add the driver-test test-suite. Introduces a new library dependency (upon hspec) for the haddock driver target in the haddock.cabal file, but practically, this should not be a problem as the haddock-api tests already depend on hspec. - - - - - 498781df by Ben Gamari at 2016-01-06T13:41:04+01:00 Version bumps and changelog - - - - - 8451e46a by Ben Gamari at 2016-01-06T13:47:17+01:00 Merge remote-tracking branch 'randen/bug468' - - - - - fb2d9181 by Ben Gamari at 2016-01-06T08:14:42-05:00 Add ResponseFile to OtherModules - - - - - 2cb2d2e3 by Ben Gamari at 2016-01-06T14:35:00+01:00 Merge branch 'master' into ghc-head - - - - - 913477d4 by Eric Seidel at 2016-01-11T14:57:57-08:00 deal with un-wiring of IP class - - - - - c557a4b3 by Alan Zimmerman at 2016-01-15T11:14:35+02:00 Update to match wip/T11430 in GHC - - - - - 3e135093 by Alan Zimmerman at 2016-01-16T18:21:59+01:00 Update to match wip/T11430 in GHC - - - - - c48ef2f9 by Ben Gamari at 2016-01-18T09:50:06+01:00 Merge remote-tracking branch 'gridaphobe/ghc-head' into ghc-head - - - - - 9138a1b0 by Eric Seidel at 2016-01-18T12:50:15+01:00 deal with un-wiring of IP class (cherry picked from commit 17388b0f0029d969d79353be7737eb01c7b8dc5f) - - - - - b48c172e by Joachim Breitner at 2016-01-19T00:11:38+01:00 Make sure --mathjax affects all written HTML files This fixes haskell/haddock#475. - - - - - af61fe63 by Ryan Scott at 2016-02-07T23:25:57+01:00 Render */# instead of TYPE 'Lifted/TYPE 'Unlifted (fixes haskell/haddock#473) - - - - - b6458693 by Ben Gamari at 2016-02-07T23:29:27+01:00 Merge pull request haskell/haddock#477 from haskell/issue-475 Make sure --mathjax affects all written HTML files - - - - - adcc0071 by Ben Gamari at 2016-02-07T23:34:52+01:00 Merge branch 'master' into ghc-head - - - - - d0404e61 by Ben Gamari at 2016-02-08T12:46:49+01:00 doc: Switch to Sphinx - - - - - acb153b3 by Ben Gamari at 2016-02-08T12:46:56+01:00 Document --use-unicode flag - - - - - c20bdf1d by Ben Gamari at 2016-02-08T13:41:24+01:00 Fix GHC and haddock-library dependency bounds - - - - - 8d946801 by Ben Gamari at 2016-02-08T14:54:56+01:00 testsuite: Rework handling of output sanitization Previously un-cleaned artifacts were kept as reference output, making it difficult to tell what has changed and causing spurious changes in the version control history. Here we rework this, cleaning the output during acceptance. To accomplish this it was necessary to move to strict I/O to ensure the reference handle was closed before accept attempts to open the reference file. - - - - - c465705d by Ben Gamari at 2016-02-08T15:36:05+01:00 test: Compare on dump For reasons I don't understand the Xml representations differ despite their textual representations being identical. - - - - - 1ec0227a by Ben Gamari at 2016-02-08T15:36:05+01:00 html-test: Accept test output - - - - - eefbd63a by Ben Gamari at 2016-02-08T15:36:08+01:00 hypsrc-test: Accept test output And fix impredicative Polymorphism testcase. - - - - - d1df4372 by Ben Gamari at 2016-02-08T15:40:44+01:00 Merge branch 'fix-up-testsuite' - - - - - 206a3859 by Phil Ruffwind at 2016-02-08T17:51:21+01:00 Move the permalinks to "#" on the right side Since pull request haskell/haddock#407, the identifiers have been permalinked to themselves, but this makes it difficult to copy the identifier by double-clicking. To work around this usability problem, the permalinks are now placed on the far right adjacent to "Source", indicated by "#". Also, 'namedAnchor' now uses 'id' instead of 'name' (which is obsolete). - - - - - 6c89fa03 by Phil Ruffwind at 2016-02-08T17:54:44+01:00 Update tests for previous commit - - - - - effaa832 by Ben Gamari at 2016-02-08T17:56:17+01:00 Merge branch 'anchors-redux' - - - - - 9a2bec90 by Ben Gamari at 2016-02-08T17:58:40+01:00 Use -fprint-unicode-syntax when --use-unicode is enabled This allows GHC to render `*` as its Unicode representation, among other things. - - - - - 28ecac5b by Ben Gamari at 2016-02-11T18:53:03+01:00 Merge pull request haskell/haddock#480 from bgamari/sphinx Move documentation to ReStructuredText - - - - - 222e5920 by Ryan Scott at 2016-02-11T15:42:42-05:00 Collapse type/data family instances by default - - - - - a80ac03b by Ryan Scott at 2016-02-11T20:17:09-05:00 Ensure expanded family instances render correctly - - - - - 7f985231 by Ben Gamari at 2016-02-12T10:04:22+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - d4eda086 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Various cleanups - - - - - 79bee48d by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show kind signatures for type family variables Addresses GHC haskell/haddock#11588. - - - - - b2981d98 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show 'where ...' after closed type family Seems like we should ideally show the actual equations as well but that seems like it would be a fair amount of work - - - - - cfc0e621 by Ben Gamari at 2016-02-18T22:48:12+01:00 Merge pull request haskell/haddock#483 from bgamari/T11588 Fix GHC haskell/haddock#11588 This fixes GHC haskell/haddock#11588: * Show where ... after closed type families * Show kind signatures on type family type variables - - - - - 256e8a0d by Ben Gamari at 2016-02-18T23:15:39+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 32402036 by Richard Eisenberg at 2016-02-24T13:21:44-05:00 Follow-on changes to support RuntimeRep - - - - - 2b1c572d by Matthew Pickering at 2016-03-04T21:04:02+00:00 Remove unused functions - - - - - eb906f50 by Richard Eisenberg at 2016-03-13T21:17:20+01:00 Follow-on changes to support RuntimeRep (cherry picked from commit ab954263a793d8ced734459d6194a5d89214b66c) - - - - - 8c34ef34 by Richard Eisenberg at 2016-03-14T23:47:23-04:00 Changes due to fix for GHC#11648. - - - - - 0e022014 by Richard Eisenberg at 2016-03-15T14:06:45+01:00 Changes due to fix for GHC#11648. (cherry picked from commit bb994de1ab0c76d1aaf1e39c54158db2526d31f1) - - - - - ed3f78ab by Rik Steenkamp at 2016-04-02T22:20:36+01:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 - - - - - d3210042 by Rik Steenkamp at 2016-04-04T15:43:32+02:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 (cherry picked from commit 3ddcbd6b8e6884bd95028381176eb33bee6896fb) - - - - - 236eec90 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 692ee7e0 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. - - - - - 79619f57 by Ben Gamari at 2016-04-10T23:46:22+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. (cherry picked from commit c6d6a18d85e5e2d9bb5904e6919e8a8d7e31c4c5) - - - - - 3358ccb4 by Ben Gamari at 2016-04-10T23:47:27+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 264949b1 by Ben Gamari at 2016-04-16T17:50:23+02:00 Merge pull request haskell/haddock#482 from RyanGlScott/ghc-head Collapse type/data family instances by default - - - - - 478c483a by Ben Gamari at 2016-04-16T17:51:09+02:00 Merge pull request haskell/haddock#489 from mpickering/unused-functions Remove some unused functions - - - - - c94e55f0 by Ryan Scott at 2016-04-16T17:57:54+02:00 Collapse type/data family instances by default (cherry picked from commit 2da130a8db8f995c119b544fad807533236cf088) - - - - - 31e633d3 by Ryan Scott at 2016-04-16T17:58:06+02:00 Ensure expanded family instances render correctly (cherry picked from commit 1338b5d7c32939de6bbc31af0049477e4f847103) - - - - - 03e4d197 by Matthew Pickering at 2016-04-16T17:58:21+02:00 Remove unused functions (cherry picked from commit b89d1c2456bdb2d4208d94ded56155f7088a37d0) - - - - - ed4116f6 by Ben Gamari at 2016-04-20T10:46:57+02:00 ghc: Install files for needed --hyperlinked-source - - - - - 0be999c4 by Ben Gamari at 2016-04-20T11:37:54+02:00 ghc: Install files for needed --hyperlinked-source (cherry picked from commit 5c82c9fc2d21ddaae4a2470f1c375426968f19c6) - - - - - 4d17544c by Simon Peyton Jones at 2016-04-20T12:42:28+01:00 Track change to HsGroup This relates to a big GHC patch for Trac haskell/haddock#11348 - - - - - 1700a50d by Ben Gamari at 2016-05-01T13:19:27+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. - - - - - 0b7c8125 by Ben Gamari at 2016-05-01T13:21:43+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. (cherry picked from commit 609018dd09c4ffe27f9248b2d8b50f6196cd42b9) - - - - - af115ce0 by Ryan Scott at 2016-05-04T22:15:50-04:00 Render Haddocks for derived instances Currently, one can document top-level instance declarations, but derived instances (both those in `deriving` clauses and standalone `deriving` instances) do not enjoy the same privilege. This makes the necessary changes to the Haddock API to enable rendering Haddock comments for derived instances. This is part of a fix for Trac haskell/haddock#11768. - - - - - 76fa1edc by Ben Gamari at 2016-05-10T18:13:25+02:00 haddock-test: A bit of refactoring for debuggability - - - - - 7d4c4b20 by Ben Gamari at 2016-05-10T18:13:25+02:00 Create: Mark a comment as TODO - - - - - 2a6d0c90 by Ben Gamari at 2016-05-10T18:13:25+02:00 html-test: Update reference output - - - - - bd60913d by Ben Gamari at 2016-05-10T18:13:25+02:00 hypsrc-test: Fix reference file path in cabal file It appears the haddock insists on prefixing --hyperlinked-sourcer output with directory which the source appeared in. - - - - - c1548057 by Ben Gamari at 2016-05-10T18:22:12+02:00 doc: Update extra-source-files in Cabal file - - - - - 41d5bae3 by Ben Gamari at 2016-05-10T18:29:21+02:00 Bump versions - - - - - ca75b779 by Ben Gamari at 2016-05-11T16:03:44+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 4e3cfd62 by Ben Gamari at 2016-05-11T16:06:45+02:00 Merge remote-tracking branch 'RyanGlScott/ghc-head' into ghc-head - - - - - a2379970 by Ben Gamari at 2016-05-11T23:15:11+02:00 doc: Add clean targets - - - - - f275212e by Ben Gamari at 2016-05-11T23:15:14+02:00 doc: Add html as an all-target for ghc Otherwise the html documentation won't be installed for binary-dist. - - - - - 388fc0af by Ben Gamari at 2016-05-12T09:49:12+02:00 Update CHANGES - - - - - bad81ad5 by Ben Gamari at 2016-05-12T09:49:38+02:00 Version bump - - - - - c01688a7 by Ben Gamari at 2016-05-12T10:04:58+02:00 Revert "Version bump" This bump was a bit premature. This reverts commit 7b238d9c5be9b07aa2d10df323b5c7b8d1634dc8. - - - - - 7ed05724 by Ben Gamari at 2016-05-12T10:05:33+02:00 doc: Fix GHC clean rule Apparently GHC's build system doesn't permit wildcards in clean paths. - - - - - 5d9611f4 by Ben Gamari at 2016-05-12T17:43:50+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 653566b2 by Ben Gamari at 2016-05-14T09:57:31+02:00 Version bump to 2.17.2 - - - - - b355c439 by Ben Gamari at 2016-05-14T09:57:51+02:00 doc: Use `$(MAKE)` instead of `make` This is necessary to ensure we use gmake. - - - - - 8a18537d by Ben Gamari at 2016-05-14T10:15:45+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - b3290ef1 by Sebastian Meric de Bellefon at 2016-05-14T11:29:47-04:00 Fix haskell/haddock#303. Hide footer when printing The "Produced by Haddock" footer was overlapping the page's body when printing. This patch hides the footer with a css media rule. - - - - - b4a76f89 by Sebastian Meric de Bellefon at 2016-05-15T02:12:46-04:00 Fix haskell/haddock#280. Parsing of module header The initial newlines were counted as indentation spaces, thus disturbing the parsing of next lines - - - - - ba797c9e by Ben Gamari at 2016-05-16T14:53:46+02:00 doc: Vendorize alabaster Sphinx theme Alabaster is now the default sphinx theme and is a significant improvement over the previous default that it's worthproviding it when unavailable (e.g. Sphinx <1.3). - - - - - c9283e44 by Ben Gamari at 2016-05-16T14:55:17+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 1c9ea198 by Sebastian Méric de Bellefon at 2016-05-16T12:30:40-04:00 Merge pull request haskell/haddock#502 from Helkafen/master Fix haskell/haddock#303. Hide footer when printing - - - - - 33631016 by Ben Gamari at 2016-05-16T19:56:11+02:00 Revert "doc: Vendorize alabaster Sphinx theme" This ended up causes far too many issues to be worthwhile. We'll just have to live with inconsistent haddock documentation. This reverts commit cec21957001143794e71bcd9420283df18e7de40. - - - - - 93317d26 by Ben Gamari at 2016-05-16T19:56:11+02:00 cabal: Fix README path - - - - - c8695b22 by Ben Gamari at 2016-05-16T19:58:51+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 0b50eaaa by Ben Gamari at 2016-05-16T21:02:08+02:00 doc: Use whichever theme sphinx deems appropriate - - - - - 857c1c9c by Ben Gamari at 2016-05-16T21:07:08+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 15fc5637 by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Remove redundant imports - - - - - 132ddc6a by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Better debug output For tracking down haskell/haddock#505 - - - - - 2252a149 by Ben Gamari at 2016-05-22T12:43:59+02:00 Don't consider default class ops when looking for decls When we are looking for an operation within a class we don't care about `default`-type declarations. This was the cause of haskell/haddock#505. - - - - - 4886b2ec by Oleg Grenrus at 2016-05-24T16:19:48+03:00 UnfelpfulSpan line number omitted Kind of resolves https://github.com/haskell/haddock/issues/508 - - - - - a4befd36 by Oleg Grenrus at 2016-05-24T16:53:35+03:00 Change Hyperlinked lexer to know about DataKinds ticks - - - - - f45cb52e by David Feuer at 2016-05-24T18:48:53-04:00 Make parser state a newtype Previously, it was `data` wrapping a `Maybe`, which seems a bit silly. Obviously, this can be changed back if anyone wants to add more fields some day. - - - - - 05013dd7 by Sebastian Meric de Bellefon at 2016-05-24T22:03:55-04:00 remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) Frames are a bit broken, ignored by Hackage, and considered obsolete in general. This patch disables frames generation. The mini_*.html files are still used in the synopsis. - - - - - b8163a88 by Ben Gamari at 2016-05-25T14:44:15+02:00 Merge pull request haskell/haddock#507 from bgamari/T505 Fix haskell/haddock#505 - - - - - ea1b30c6 by Sebastian Meric de Bellefon at 2016-05-25T14:17:00-04:00 Update CHANGES - - - - - eddfc258 by Sebastian Méric de Bellefon at 2016-05-25T15:17:40-04:00 Merge pull request haskell/haddock#514 from Helkafen/frames remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) - - - - - 0e506818 by Alex Biehl at 2016-05-26T12:43:09+02:00 Remove misplaced haddock comment - - - - - a07d28c0 by Ben Gamari at 2016-05-27T11:34:59+02:00 Merge pull request haskell/haddock#515 from alexbiehl/master Remove misplaced haddock comment - - - - - 9001d267 by Ben Gamari at 2016-05-27T11:35:46+02:00 Merge pull request haskell/haddock#513 from treeowl/newtype-since Make parser state a newtype - - - - - 74e1a018 by Sebastian Méric de Bellefon at 2016-05-28T17:28:15-04:00 Merge pull request haskell/haddock#504 from Helkafen/issue-280 Fix haskell/haddock#280. Parsing of module header - - - - - 37557f4f by Alan Zimmerman at 2016-05-29T23:36:50+02:00 Matching changes for haskell/haddock#12105 - - - - - 7d09e5d6 by Sebastian Meric de Bellefon at 2016-06-03T18:07:48-04:00 Version bumps (2.17.3, 1.4.2) - - - - - 85b4bc15 by Sebastian Méric de Bellefon at 2016-06-06T18:35:13-04:00 Merge pull request haskell/haddock#521 from Helkafen/master Version bumps (2.17.3, 1.4.2) - - - - - e95f0dee by Sebastian Meric de Bellefon at 2016-06-06T19:11:35-04:00 publish haddock-test library - - - - - 4de40586 by Sebastian Méric de Bellefon at 2016-06-06T20:26:30-04:00 Merge pull request haskell/haddock#512 from phadej/oleg-fixes Fixes for haskell/haddock#508 and haskell/haddock#510 - - - - - ddfd0789 by Dominic Steinitz at 2016-06-09T09:27:28+01:00 Documentation for LaTeX markup. - - - - - 697a503a by Dominic Steinitz at 2016-06-09T09:33:59+01:00 Fix spelling mistake. - - - - - 246f6fff by Dominic Steinitz at 2016-06-09T09:37:15+01:00 Camel case MathJax. - - - - - 4684bd23 by Dominic Steinitz at 2016-06-09T09:44:53+01:00 Fix math typo and add link. - - - - - f20c037c by Simon Peyton Jones at 2016-06-13T18:26:03+01:00 Follow changes to LHsSigWcType - - - - - 0c58996d by Simon Peyton Jones at 2016-06-15T12:56:01+01:00 Follow GHC re-adding FunTy - - - - - 401b5ca7 by Sebastian Méric de Bellefon at 2016-06-15T12:16:47-04:00 Merge pull request haskell/haddock#525 from idontgetoutmuch/master Documentation for LaTeX markup. - - - - - 92d263b7 by Sebastian Méric de Bellefon at 2016-06-15T12:17:29-04:00 Merge pull request haskell/haddock#522 from Helkafen/master publish haddock-test library - - - - - 0953a2ca by Sebastian Meric de Bellefon at 2016-06-16T00:46:46-04:00 Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 65453e14 by Ben Gamari at 2016-06-16T11:16:32+02:00 ocean: Ensure that synopsis fully covers other content Previously MathJax content was being rendered on top of the synopsis due to ambiguous z-ordering. Here we explicitly give the synopsis block a higher z-index to ensure it is rendered on top. Fixes haskell/haddock#531. - - - - - 68e411a1 by Sebastian Méric de Bellefon at 2016-06-16T23:34:39-04:00 Merge pull request haskell/haddock#534 from bgamari/T531 ocean: Ensure that synopsis fully covers other content - - - - - fad6491b by Sebastian Méric de Bellefon at 2016-06-18T23:57:20-04:00 Merge pull request haskell/haddock#533 from Helkafen/master Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 6108e21b by Sebastian Meric de Bellefon at 2016-06-22T23:08:28-04:00 do not create empty src directory Fix haskell/haddock#536. - - - - - 1ef23823 by Sebastian Méric de Bellefon at 2016-06-24T00:04:48-04:00 Merge pull request haskell/haddock#537 from Helkafen/master do not create empty src directory - - - - - 966baa96 by Omari Norman at 2016-06-29T21:59:34-04:00 Add $ as a special character If this character is not escaped, documentation built with Haddock 2.17.2 will fail. This was not an issue with 2.16 series, which causes builds to fail and there is nothing in the docs or error message giving a clue about why builds that used to succeed now don't. - - - - - 324adb60 by Ben Gamari at 2016-07-01T12:18:51+02:00 GhcUtils: Changes for multi-pattern signatures - - - - - d7571675 by Ömer Sinan Ağacan at 2016-07-21T13:30:47+02:00 Add support for unboxed sums - - - - - 29d0907b by Simon Marlow at 2016-07-22T13:55:48+01:00 Disable NFData instances for GHC types when GHC >= 8.2 - - - - - 702d95f3 by Simon Marlow at 2016-08-02T15:57:30+02:00 Disable NFData instances for GHC types when GHC >= 8.0.2 (cherry picked from commit a3309e797c42dae9bccdeb17ce52fcababbaff8a) - - - - - f4fa79c3 by Ben Gamari at 2016-08-07T13:51:18+02:00 ghc.mk: Don't attempt to install html/frames.html The frames business has been removed. - - - - - 9cd63daf by Ben Gamari at 2016-08-07T13:51:40+02:00 Haddock.Types: More precise version guard This allows haddock to be built with GHC 8.0.2 pre-releases. - - - - - f3d7e03f by Mateusz Kowalczyk at 2016-08-29T20:47:45+01:00 Merge pull request haskell/haddock#538 from massysett/master Add $ as a special character - - - - - 16dbf7fd by Bartosz Nitka at 2016-09-20T19:44:04+01:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 - - - - - 7c31c1ff by Bartosz Nitka at 2016-09-27T17:32:22-04:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 (cherry picked from commit 073d899a8f94ddec698f617a38d3420160a7fd0b) - - - - - 33a90dce by Ryan Scott at 2016-09-30T20:53:41-04:00 Haddock changes for T10598 See https://ghc.haskell.org/trac/ghc/ticket/10598 - - - - - 1f32f7cb by Ben Gamari at 2016-10-13T20:01:26-04:00 Update for refactoring of NameCache - - - - - 1678ff2e by Ben Gamari at 2016-11-15T17:42:48-05:00 Bump upper bound on base - - - - - 9262a7c5 by Alan Zimmerman at 2016-12-07T21:14:28+02:00 Match changes in GHC wip/T3384 branch - - - - - ac0eaf1a by Ben Gamari at 2016-12-09T09:48:41-05:00 haddock-api: Don't use stdcall calling convention on 64-bit Windows See GHC haskell/haddock#12890. - - - - - 04afe4f7 by Alan Zimmerman at 2016-12-12T20:07:21+02:00 Matching changes for GHC wip/T12942 - - - - - e1d1701d by Ben Gamari at 2016-12-13T16:50:41-05:00 Bump base upper bound - - - - - 3d3eacd1 by Alan Zimmerman at 2017-01-10T16:59:38+02:00 HsIParamTy now has a Located name - - - - - 7dbceefd by Kyrill Briantsev at 2017-01-12T13:23:50+03:00 Prevent GHC API from doing optimization passes. - - - - - d48d1e33 by Richard Eisenberg at 2017-01-19T08:41:41-05:00 Upstream changes re levity polymorphism - - - - - 40c25ed6 by Alan Zimmerman at 2017-01-26T15:16:18+02:00 Changes to match haskell/haddock#13163 in GHC - - - - - 504f586d by Ben Gamari at 2017-02-02T17:19:37-05:00 Kill remaining static flags - - - - - 49147ea0 by Justus Adam at 2017-03-02T15:33:34+01:00 Adding MDoc to exports of Documentation.Haddock - - - - - 1cfba9b4 by Justus Adam at 2017-03-09T11:41:44+01:00 Also exposing toInstalledIface - - - - - 53f0c0dd by Ben Gamari at 2017-03-09T13:10:08-05:00 Bump for GHC 8.3 - - - - - c7902d2e by Ben Gamari at 2017-03-09T23:46:02-05:00 Bump for GHC 8.2 - - - - - 4f3a74f8 by Ben Gamari at 2017-03-10T10:21:55-05:00 Merge branch 'ghc-head' - - - - - e273b72f by Richard Eisenberg at 2017-03-14T13:34:04-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - 6ec3d436 by Richard Eisenberg at 2017-03-14T15:15:52-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - eee3cda1 by Ben Gamari at 2017-03-15T15:19:59-04:00 Adapt to EnumSet - - - - - 017cf58e by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 736d6773 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 475f84a0 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 13240b53 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - cd16d529 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 3bea97ae by Edward Z. Yang at 2017-03-15T22:50:46-07:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b2b051ce by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 0f082795 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 20ef63c9 by Edward Z. Yang at 2017-03-22T13:48:12-07:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 45692dcb by Edward Z. Yang at 2017-03-22T14:11:25-07:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4eae8caf by Ben Gamari at 2017-03-23T09:25:33-04:00 Merge commit '240bc38b94ed2d0af27333b23392d03eeb615e82' into HEAD - - - - - 0bbe03f5 by Ben Gamari at 2017-03-23T09:27:28-04:00 haddock-api: Bump bound on GHC - - - - - 65f3ac9d by Alex Biehl at 2017-03-23T17:36:11+01:00 Merge pull request haskell/haddock#581 from JustusAdam/master Adding more exports to Documentation.Haddock - - - - - 37d49a47 by Alex Biehl at 2017-03-23T17:39:14+01:00 Merge pull request haskell/haddock#568 from awson/ghc-head Prevent GHC API from doing optimization passes. - - - - - 1ed047e4 by Brian Huffman at 2017-03-23T17:45:58+01:00 Print any user-supplied kind signatures on type parameters. This applies to type parameters on data, newtype, type, and class declarations, and also to forall-bound type vars in type signatures. - - - - - 1b78ca5c by Brian Huffman at 2017-03-23T17:45:58+01:00 Update test suite to expect kind annotations on type parameters. - - - - - a856b162 by Alex Biehl at 2017-03-23T17:49:32+01:00 Include travis build indication badge - - - - - 8e2e2c56 by Ben Gamari at 2017-03-23T17:20:08-04:00 haddock-api: Bump bound on GHC - - - - - 4d2d9995 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 26d6c150b31bc4580ab17cfd07b6e7f9afe10737) - - - - - a650e20f by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 930cfbe58e2e87f5a4d431d89a3c204934e6e858) - - - - - caa282c2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 2067a2d0afa9cef381d26fb7140b67c62f433fc0) - - - - - 49684884 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 0671abfe7e8ceae2269467a30b77ed9d9656e2cc) - - - - - 4dcfeb1a by Edward Z. Yang at 2017-03-23T17:20:08-04:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 3d77b373dd5807d5d956719dd7c849a11534fa6a) - - - - - 74dd19d2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 94610e9b446324f4231fa6ad4c6ac51e4eba8c0e) - - - - - a9b19a23 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 6cc832dfb1de6088a4abcaae62b25a7e944d55c3) - - - - - d3631064 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit bf3c4d72a0fda38561376eac7eda216158783267) - - - - - ef2148fc by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 07b88c5d4e79b87a319fbb08f8ea01dbb41063c1) - - - - - 2f29518b by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 4eb765ca4205c79539d60b7afa9b7e261a4a49fe) - - - - - 37de047d by Phil Ruffwind at 2017-04-03T11:57:14+02:00 Update MathJax URL MathJax is shutting down their CDN: https://www.mathjax.org/cdn-shutting-down/ They recommend migrating to cdnjs. - - - - - e9d24ba8 by David C. Turner at 2017-04-03T14:58:01+02:00 Add highlight for :target to ocean.css - - - - - 4819a202 by Alex Biehl at 2017-04-11T19:36:48+02:00 Allow base-4.10 for haddock-test - - - - - 44cec69c by Alex Biehl at 2017-04-11T19:39:22+02:00 cabal.project for haddock-api, haddock-library and haddock-test - - - - - 935d0f6a by Alex Biehl at 2017-04-11T19:46:29+02:00 Move dist scripts to scripts/ - - - - - 128e150c by Alex Biehl at 2017-04-11T20:34:46+02:00 Add haddock to cabal.project - - - - - cc8e08ea by Alex Biehl at 2017-04-11T20:35:08+02:00 Read files for hyperlinker eagerly This also exposes Documentation.Haddock.Utf8 - - - - - 152dda78 by Alex Biehl at 2017-04-11T20:37:06+02:00 Explicit import list ofr Control.DeepSeq in Haddock.Interface.Create - - - - - 501b33c4 by Kyrill Briantsev at 2017-04-11T21:01:42+02:00 Prevent GHC API from doing optimization passes. - - - - - c9f3f5ff by Alexander Biehl at 2017-04-12T16:36:53+02:00 Add @alexbiehl as maintaner - - - - - 76f214cc by Alex Biehl at 2017-04-13T07:27:18+02:00 Disable doctest with ghc-8.3 Currently doctest doesn't support ghc-head - - - - - 46b4f5fc by Edward Z. Yang at 2017-04-22T20:38:26-07:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f0555235 by Alex Biehl at 2017-04-25T10:08:48+02:00 Travis: Use ghc-8.2.1 on master - - - - - 966ea348 by Alex Biehl at 2017-04-25T10:32:01+02:00 Travis: Verbose cabal output cf. https://travis-ci.org/haskell/haddock/jobs/225512194#L377 - - - - - 36972bcd by Alex Biehl at 2017-04-25T10:40:43+02:00 Use travis_retry for cabal invocations - - - - - b3a09d2c by Alex Biehl at 2017-04-25T17:02:20+02:00 Use new MathJax URL in html-test 18ed871afb82560d5433b2f53e31b4db9353a74e switched to a new MathJax URL but didn't update the tests. - - - - - ae331e5f by Alexander Biehl at 2017-04-25T17:02:20+02:00 Expand signatures for class declarations - - - - - e573c65a by Alexander Biehl at 2017-04-25T17:02:20+02:00 Hoogle: Correctly print classes with associated data types - - - - - 3fc6be9b by Edward Z. Yang at 2017-04-25T17:02:20+02:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit a0c4790e15a2d3fab8d830eee8fcd639fe6d39c9) - - - - - 6725c060 by Herbert Valerio Riedel at 2017-04-25T17:02:20+02:00 `html-test --accept` deltas to reference samples - - - - - 7d444d61 by Alex Biehl at 2017-04-26T07:13:50+02:00 Remove anything related to obsolete frames mode - - - - - b888972c by Alex Biehl at 2017-04-26T07:49:10+02:00 Cherry-picked remaining commits from haddock-2.17.4-release (#603) * Release haddock/haddock-api 2.17.4 and haddock-library 1.4.3 * Set version bounds for haddock-library NB: This allows GHC 8.2.1's base * Set version bounds for haddock & haddock-api The version bounds support GHC 8.2 * Merge (temporary) v2.17.3 branch into v2.17 This allows us to delete the v2.17.3 branch * Fixup changelog * Pin down haddock-api to a single version as otherwise `haddock`'s package version has no proper meaning * fix source-repo spec for haddock-api - - - - - 4161099b by Alex Biehl at 2017-04-26T11:11:20+02:00 Update changelog to reflect news in HEAD - - - - - eed72cb8 by Alex Biehl at 2017-04-26T11:11:20+02:00 Markdownify changelog - - - - - 5815cea1 by Alex Biehl at 2017-04-26T11:32:33+02:00 Bump to 2.18.0 (#605) - - - - - a551d558 by Alex Biehl at 2017-04-29T22:00:25+02:00 Update attoparsec-0.12.1.1 to attoparsec-0.13.1.0 - - - - - ea164a8d by Sergey Vinokurov at 2017-04-29T22:42:36+02:00 Improve error message - - - - - 2e10122f by Alex Biehl at 2017-04-30T10:07:46+02:00 Correctly remember collapsed sections (#608) Now the "collapsed" cookie stores which sections have changed state instead of which are collapsed. - - - - - f9b24d99 by Alex Biehl at 2017-05-01T17:40:36+02:00 Lazily decode docMap and argMap (#610) These are only used in case of a doc reexport so most of the time decoding these is wasted work. - - - - - 2372af62 by Alex Biehl at 2017-05-01T21:59:23+02:00 Fix Binary instance for InstalledInterface (#611) (#610) introduced lazy decoding for docs from InstalledInterface but forgot to remove the original calls to get and put_ - - - - - 6c633c13 by Nathan Collins at 2017-05-11T11:47:55+02:00 Improve documenation of Haddock markup (#614) * Improve documentation of Haddock markup. - document that Haddock supports inferring types top-level functions with without type signatures, but also explain why using this feature is discouraged. Looks like this feature has been around since version 2.0.0.0 in 2008! - rework the "Module description" section: - move the general discussion of field formatting to the section intro and add examples illustrating the prose for multiline fields. - mention that newlines are preserved in some multiline fields, but not in others (I also noticed that commas in the `Copyright` field are not preserved; I'll look into this bug later). - add a subsection for the module description fields documentation, and put the field keywords in code formatting (double back ticks) instead of double quotes, to be consistent with the typesetting of keywords in other parts of the documentation. - mention that "Named chunks" are not supported in the long-form "Module description" documentation. - fix formatting of keywords in the "Module attributes" section. Perhaps these errors were left over from an automatic translation to ReST from some other format as part of the transition to using Sphinx for Haddock documentation? Also, add a missing reference here; it just said "See ?"! - update footnote about special treatment for re-exporting partially imported modules not being implemented. In my tests it's not implemented at all -- I tried re-exporting both `import B hiding (f)` and `import B (a, b)` style partial imports, and in both cases got the same result as with full imports `import B`: I only get a module reference. * Rework the `Controlling the documentation structure` section. My main goal was to better explain how to use Haddock without an export list, since that's my most common use case, but I hope I improved the section overall: - remove the incomplete `Omitting the export list` section and fold it into the other sections. In particular, summarize the differences between using and not using an export list -- i.e. control over what and in what order is documented -- in the section lead. - add "realistic" examples that use the structure markup, both with and without an export list. I wanted a realistic example here to capture how it can be useful to explain the relationship between a group of functions in a section, in addition to documenting their individual APIs. - make it clear that you can associate documentation chunks with documentation sections when you aren't using an export list, and that doing it in the most obvious way -- i.e. with `-- |`, as you can in the export list -- doesn't work without an export list. It took me a while to figure this out the first time, since the docs didn't explain it at all before. - add a "no export list" example to the section header section. - add more cross references. * Add examples of gotchas for markup in `@...@`. I'm not sure this will help anyone, since I think most people first learn about `@...@` by reading other people's Haddocks, but I've documented the mistakes which I've made and then gotten confused by. * Use consistent Capitalization of Titles. Some titles were in usual title caps, and others only had the first word capitalized. I chose making them all use title caps because that seems to make the cross references look better. - - - - - d4734f45 by Ben Gamari at 2017-05-12T20:36:08+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 93883f37 by Alex Biehl at 2017-05-12T21:02:33+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 5b8f179c by Alex Biehl at 2017-05-13T12:48:10+02:00 Consequently use inClass and notInClass in haddock-library (#617) These allow attoparsec to do some clever lookup optimization - - - - - 77984b82 by Doug Wilson at 2017-05-27T17:37:38+02:00 Don't enable compilation for template haskell (#624) This is no longer necessary after ghc commit 53c78be0aab76a3107c4dacbb1d177afacdd37fa - - - - - 5a3de2b4 by Doug Wilson at 2017-05-27T19:54:53+02:00 Improve Syb code (#621) Specialize.hs and Ast.hs are modified to have their Syb code not recurse into Name or Id in HsSyn types. Specialize.hs is refactored to have fewer calls to Syb functions. Syb.hs has some foldl calls replaced with foldl' calls. There is still a lot of performance on the floor of Ast.hs. The RenamedSource is traversed many times, and lookupBySpan is very inefficient. everywhereBut and lookupBySpan dominate the runtime whenever --hyperlinked-source is passed. - - - - - 3d35a949 by Alex Biehl at 2017-05-30T19:01:37+02:00 Clear fixme comment (#625) - - - - - 2a44bd0c by Alex Biehl at 2017-05-30T19:02:12+02:00 Make haddock-library and haddock-api warning free (#626) - - - - - bd1a0e42 by Alex Biehl at 2017-06-01T10:40:33+02:00 Include `driver-test/*.hs` sdist (#630) This lead to haskell/haddock#629. - - - - - 184a3ab6 by Doug Wilson at 2017-06-03T12:02:08+02:00 Disable pattern match warnings (#628) This disables the pattern match checker which can be very expensive in some cases. The disabled warnings include: * Opt_WarnIncompletePatterns * Opt_WarnIncompleteUniPatterns * Opt_WarnIncompletePatternsRecUpd * Opt_WarnOverlappingPatterns - - - - - 0cf68004 by Alex Biehl at 2017-06-03T20:37:28+02:00 Allow user defined signatures for pattern synonyms (#631) - - - - - 7f51a58a by Alex Biehl at 2017-06-04T11:56:38+02:00 Use NameSet for isExported check (#632) - - - - - d8f044a9 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Match new AST as per GHC wip/new-tree-one-param See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow - - - - - da1254e3 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Rename extension index tags - - - - - 538c7514 by Christiaan Baaij at 2017-06-09T08:26:43+02:00 Haddock support for bundled pattern synonyms (#627) * Haddock support for bundled pattern synonyms * Add fixities to bundled pattern synonyms * Add bundled pattern synonyms to the synopsis * Store bundled pattern fixities in expItemFixities * Add test for bundled pattern synonyms * Stop threading fixities * Include bundled pattern synonyms for re-exported data types Sadly, fixity information isn't found for re-exported data types * Support for pattern synonyms * Modify tests after haskell/haddock#631 * Test some reexport variations * Also lookup bundled pattern synonyms from `InstalledInterface`s * Check isExported for bundled pattern synonyms * Pattern synonym is exported check * Always look for pattern synonyms in the current module Another overlooked cornercase * Account for types named twice in export lists Also introduce a fast function for nubbing on a `Name` and use it throughout the code base. * correct fixities for reexported pattern synonyms * Fuse concatMap and map * Remove obsolete import * Add pattern synonyms to visible exports * Fix test * Remove corner case - - - - - a050bffd by Doug Wilson at 2017-06-21T09:27:33+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#636) There is some performance improvement. GHC compiler: | version | bytes allocated | cpu_seconds --------------------------------- | before | 56057108648 | 41.0 | after | 51592019560 | 35.1 base: | version | bytes allocated | cpu_seconds --------------------------------- | before | 25174011784 | 14.6 | after | 23712637272 | 13.1 Cabal: | version | bytes allocated | cpu_seconds --------------------------------- | before | 18754966920 | 12.6 | after | 18198208864 | 11.6 - - - - - 5d06b871 by Doug Wilson at 2017-06-22T20:23:29+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#639) * Use new function getNameToInstancesIndex instead of tcRnGetInfo There is some significant performance improvement in the ghc testsuite. haddock.base: -23.3% haddock.Cabal: -16.7% haddock.compiler: -19.8% * Remove unused imports - - - - - b11bb73a by Alex Biehl at 2017-06-23T14:44:41+02:00 Lookup fixities for reexports without subordinates (#642) So we agree that reexported declarations which do not have subordinates (for example top-level functions) shouldn't have gotten fixities reexported according to the current logic. I wondered why for example Prelude.($) which is obviously reexported from GHC.Base has fixities attached (c.f. http://hackage.haskell.org/package/base-4.9.1.0/docs/Prelude.html#v:-36-). The reason is this: In mkMaps we lookup all the subordinates of top-level declarations, of course top-level functions don't have subordinates so for them the resulting list is empty. In haskell/haddock#644 I established the invariant that there won't be any empty lists in the subordinate map. Without the patch from haskell/haddock#642 top-level functions now started to fail reexporting their fixities. - - - - - d2a6dad6 by Alex Biehl at 2017-06-23T18:30:45+02:00 Don't include names with empty subordinates in maps (#644) These are unecessary anyway and just blow up interface size - - - - - 69c2aac4 by Alex Biehl at 2017-06-29T19:54:49+02:00 Make per-argument docs for class methods work again (#648) * Make per-argument docs for class methods work again * Test case - - - - - c9448d54 by Bartosz Nitka at 2017-07-02T12:12:01+02:00 Fix haddock: internal error: links: UnhelpfulSpan (#561) * Fix haddock: internal error: links: UnhelpfulSpan This fixes haskell/haddock#554 for me. I believe this is another fall out of `wildcard-refactor`, like haskell/haddock#549. * Comment to clarify why we take the methods name location - - - - - d4f29eb7 by Alex Biehl at 2017-07-03T19:43:04+02:00 Document record fields when DuplicateRecordFields is enabled (#649) - - - - - 9d6e3423 by Yuji Yamamoto at 2017-07-03T22:37:58+02:00 Fix test failures on Windows (#564) * Ignore .stack-work * Fix for windows: use nul instead of /dev/null * Fix for windows: canonicalize line separator * Also normalize osx line endings - - - - - 7d81e8b3 by Yuji Yamamoto at 2017-07-04T16:13:12+02:00 Avoid errors on non UTF-8 Windows (#566) * Avoid errors on non UTF-8 Windows Problem ==== haddock exits with errors like below: `(1)` ``` haddock: internal error: <stderr>: hPutChar: invalid argument (invalid character) ``` `(2)` ``` haddock: internal error: Language\Haskell\HsColour\Anchors.hs: hGetContents: invalid argument (invalid byte sequence) ``` `(1)` is caused by printing [the "bullet" character](http://www.fileformat.info/info/unicode/char/2022/index.htm) onto stderr. For example, this warning contains it: ``` Language\Haskell\HsColour\ANSI.hs:62:10: warning: [-Wmissing-methods] • No explicit implementation for ‘toEnum’ • In the instance declaration for ‘Enum Highlight’ ``` `(2)` is caused when the input file of `readFile` contains some Unicode characters. In the case above, '⇒' is the cause. Environment ---- OS: Windows 10 haddock: 2.17.3 GHC: 8.0.1 Solution ==== Add `hSetEncoding handle utf8` to avoid the errors. Note ==== - I found the detailed causes by these changes for debugging: - https://github.com/haskell/haddock/commit/8f29edb6b02691c1cf4c479f6c6f3f922b35a55b - https://github.com/haskell/haddock/commit/1dd23bf2065a1e1f2c14d0f4abd847c906b4ecb4 - These errors happen even after executing `chcp 65001` on the console. According to the debug code, `hGetEncoding stderr` returns `CP932` regardless of the console encoding. * Avoid 'internal error: <stderr>: hPutChar: invalid argument (invalid character)' non UTF-8 Windows Better solution for 59411754a6db41d17820733c076e6a72bcdbd82b's (1) - - - - - eded67d2 by Alex Biehl at 2017-07-07T19:17:15+02:00 Remove redudant import warning (#651) - - - - - 05114757 by Alex Biehl at 2017-07-08T00:33:12+02:00 Avoid missing home module warning (#652) * Avoid missing home module warning * Update haddock-library.cabal - - - - - e9cfc902 by Bryn Edwards at 2017-07-17T07:51:20+02:00 Fix haskell/haddock#249 (#655) - - - - - eb02792b by Herbert Valerio Riedel at 2017-07-20T09:09:15+02:00 Fix compilation of lib:haddock-library w/ GHC < 8 - - - - - 9200bfbc by Alex Biehl at 2017-07-20T09:20:38+02:00 Prepare 2.18.1 release (#657) - - - - - 46ddd22c by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Tweak haddock-api.cabal for pending release - - - - - 85e33d29 by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Avoid trivial use of LambdaCase otherwise we can't test w/ e.g. GHC 7.4.2 - - - - - 3afb4bfe by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Refactor .cabal to use sub-lib for vendored lib A practical benefit is that we can control the build-depends and also avoid some recompilation between library and test-suite. - - - - - e56a552e by Herbert Valerio Riedel at 2017-07-20T10:17:48+02:00 haddock-api: add changelog pointing to haddock's changelog This addresses https://github.com/haskell/haddock/issues/638#issuecomment-309283297 - - - - - 2222ff0d by Herbert Valerio Riedel at 2017-07-20T10:19:56+02:00 Drop obsolete/misleading `stability: experimental` This .cabal property has long been considered obsolete - - - - - 9b882905 by Alex Biehl at 2017-07-20T11:25:54+02:00 Beef up haddock description (#658) * Beef up haddock description * Handle empty lines - - - - - bb60e95c by Herbert Valerio Riedel at 2017-07-20T12:08:53+02:00 Import @aisamanra's Haddock cheatsheet from https://github.com/aisamanra/haddock-cheatsheet - - - - - 0761e456 by Herbert Valerio Riedel at 2017-07-20T12:12:55+02:00 Add cheatsheet to haddock.cabal - - - - - 2ece0f0f by Herbert Valerio Riedel at 2017-07-20T12:18:38+02:00 Mention new-build in README - - - - - 947b7865 by Herbert Valerio Riedel at 2017-07-20T12:32:16+02:00 Update README Also improves markup and removes/fixes redundant/obsolete parts [skip ci] - - - - - 785e09ad by Alex Biehl at 2017-07-27T07:28:57+02:00 Bump haddock to 2.18.2, haddock-library to 1.4.5 - - - - - e3ff1ca3 by Alex Biehl at 2017-07-31T20:15:32+02:00 Move `DocMarkup` from haddock-api to haddock-library (#659) * Move `DocMarkup` from haddock-api to haddock-library * Move more markup related functions * Markup module * CHANGELOG - - - - - cda7c20c by Alex Biehl at 2017-07-31T20:35:49+02:00 Fixup haddock - - - - - 583b6812 by Alex Biehl at 2017-07-31T21:20:45+02:00 Changelog for haddock-library - - - - - bac6a0eb by Alex Biehl at 2017-07-31T21:50:24+02:00 Prepare haddock-library-1.4.5 release - - - - - 58ce6877 by Moritz Drexl at 2017-08-05T16:44:40+02:00 Fix renaming after instance signature specializing (#660) * rework rename * Add regression test for Bug 613 * update tests * update changelog - - - - - b8137ec8 by Tim Baumann at 2017-08-06T11:33:38+02:00 Fix: Generate pattern signatures for constructors exported as patterns (#663) * Fix pretty-printing of pattern signatures Pattern synonyms can have up to two contexts, both having a different semantic meaning: The first holds the constraints required to perform the matching, the second contains the constraints provided by a successful pattern match. When the first context is empty but the second is not it is necessary to render the first, empty context. * Generate pattern synonym signatures for ctors exported as patterns This fixes haskell/haddock#653. * Simplify extractPatternSyn It is not necessary to generate the simplest type signature since it will be simplified when pretty-printed. * Add changelog entries for PR haskell/haddock#663 * Fix extractPatternSyn error message - - - - - d037086b by Alex Biehl at 2017-08-06T12:43:25+02:00 Bump haddock-library - - - - - 99d7e792 by Alex Biehl at 2017-08-06T12:44:07+02:00 Bump haddock-library in haddock-api - - - - - 94802a5b by Alex Biehl at 2017-08-06T13:18:02+02:00 Provide --show-interface option to dump interfaces (#645) * WIP: Provide --show-interface option to dump interfaces Like ghcs own --show-iface this flag dumps a binary interface file to stdout in a human (and machine) readable fashion. Currently it uses json as output format. * Fill all the jsonNull stubs * Rework Bifunctor instance of DocH, update changelog and documentation * replace changelog, bring DocMarkupH doc back * Update CHANGES.md * Update CHANGES.md * Move Control.Arrow up It would result in unused import if the Bifunctor instance is not generated. - - - - - c662e476 by Ryan Scott at 2017-08-14T21:00:21-04:00 Adapt to haskell/haddock#14060 - - - - - b891eb73 by Alex Biehl at 2017-08-16T08:24:48+02:00 Bifoldable and Bitraversable for DocH and MetaDoc - - - - - 021bb56c by Alex Biehl at 2017-08-16T09:06:40+02:00 Refactoring: Make doc renaming monadic This allows us to later throw warnings if can't find an identifier - - - - - 39fbf022 by Alex Biehl at 2017-08-19T20:35:27+02:00 Hyperlinker: Avoid linear lookup in enrichToken (#669) * Make Span strict in Position * Hyperlinker: Use a proper map to enrich tokens - - - - - e13baedd by Alex Biehl at 2017-08-21T20:05:42+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 27dd6e87 by Alex Biehl at 2017-08-21T22:06:35+02:00 Drop Avails from export list - - - - - 86b247e2 by Alex Biehl at 2017-08-22T08:44:22+02:00 Bump ghc version for haddock-api tests - - - - - d4607ca0 by Alex Biehl at 2017-08-22T08:45:17+02:00 Revert "Drop Avails from export list" This reverts commit a850ba86d88a4fb9c0bd175453a2580e544e3def. - - - - - c9c54c30 by Alex Biehl at 2017-08-22T09:26:01+02:00 IntefaceFile version - - - - - a85b7c02 by Ben Gamari at 2017-08-22T09:29:52-04:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 34e976f5 by Ben Gamari at 2017-08-22T17:40:06+02:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 577abf06 by Ryan Scott at 2017-08-23T14:47:29-04:00 Update for haskell/haddock#14131 - - - - - da68fc55 by Florian Eggenhofer at 2017-08-27T18:21:56+02:00 Generate an index for package content search (#662) Generate an index for package content search - - - - - 39e62302 by Alex Biehl at 2017-08-27T18:50:16+02:00 Content search for haddock html doc - - - - - 91fd6fb2 by Alex Biehl at 2017-08-28T18:39:58+02:00 Fix tests for content search - - - - - b4a3798a by Alex Biehl at 2017-08-28T18:44:08+02:00 Add search button to #page-menu - - - - - 25a7ca65 by Alex Biehl at 2017-08-28T18:47:43+02:00 Load javascript below the fold - - - - - 8d323c1a by Alex Biehl at 2017-08-28T18:49:22+02:00 Accept tests - - - - - c5dac557 by Alex Biehl at 2017-08-28T19:14:55+02:00 Content search css - - - - - 89a5af57 by Paolo Veronelli at 2017-08-29T07:42:13+02:00 Removed `nowrap` for interface method sigs (#674) with nowrap the interfaces method sigs would expand at libitum - - - - - a505f6f7 by Alex Biehl at 2017-08-29T08:05:33+02:00 Include subordinates in content index - - - - - 4bb698c4 by Alexander Biehl at 2017-08-29T11:40:19+02:00 QuickNav: Make docbase configurable - - - - - c783bf44 by Alexander Biehl at 2017-08-29T11:48:36+02:00 QuickNav: Also use baseUrl for doc-index.json request - - - - - 47017510 by Alex Biehl at 2017-08-29T17:56:47+02:00 Fix test fallout (again) - - - - - 924fc318 by Alex Biehl at 2017-08-30T09:24:56+02:00 Write meta.json when generating html output (#676) - - - - - 717dea52 by Alex Biehl at 2017-09-01T09:20:34+02:00 Use relative URL when no docBaseUrl given - - - - - e5d85f3b by Alex Biehl at 2017-09-01T09:35:19+02:00 Add missing js files to data-files (#677) - - - - - 95b9231a by Alex Biehl at 2017-09-01T11:01:36+02:00 Rename "Search" tab to "Quick Jump" - - - - - da0ead0b by Alex Biehl at 2017-09-01T13:03:49+02:00 Make trigger link configurable (#678) QuickNav: Configurable show/hide trigger - - - - - de7da594 by Ben Gamari at 2017-09-05T06:49:55-04:00 Account for "Remember the AvailInfo for each IE" As of GHC commit f609374a55bdcf3b79f3a299104767aae2ffbf21 GHC retains the AvailInfo associated with each IE. @alexbiehl has a patch making proper use of this change, but this is just to keep things building. - - - - - b05cd3b3 by Ben Gamari at 2017-09-14T07:55:07-04:00 Bump upper bound on base - - - - - 79db899e by Herbert Valerio Riedel at 2017-09-21T23:27:52+02:00 Make compatible with Prelude.<> export in GHC 8.4/base-4.11 - - - - - 3405dd52 by Tim Baumann at 2017-09-23T22:02:01+02:00 Add compile step that bundles and compresses JS files (#684) * Add compile step that bundles and compresses JS files Also, manage dependencies on third-party JS libraries using NPM. * Compile JS from TypeScript * Enable 'noImplicitAny' in TypeScript * QuickJump: use JSX syntax * Generate source maps from TypeScript for easier debugging * TypeScript: more accurate type * Separate quick jump css file from ocean theme - - - - - df0b5742 by Alex Biehl at 2017-09-29T21:15:40+02:00 Bump base for haddock-library and haddock-test - - - - - 62b12ea0 by Merijn Verstraaten at 2017-10-04T16:03:13+02:00 Inhibit output of coverage information for hidden modules. (#687) * Inhibit output of coverage information for hidden modules. * Add changelog entry. - - - - - 8daf8bc1 by Alexander Biehl at 2017-10-05T11:27:05+02:00 Don't use subMap in attachInstances - - - - - ad75114e by Alexander Biehl at 2017-10-05T11:27:58+02:00 Revert "Don't use subMap in attachInstances" This reverts commit 3adf5bcb1a6c5326ab33dc77b4aa229a91d91ce9. - - - - - 7d4aa02f by Alex Biehl at 2017-10-08T15:32:28+02:00 Precise Haddock: Use Avails for export resolution (#688) * Use Avails for export resolution * Support reexported modules * Factor out availExportItem * Use avails for fullModuleExports * Don't use subMap in attachInstances * lookupDocs without subMap * Completely remove subMap * Only calculate unqualified modules when explicit export list is given * Refactor * Refine comment * return * Fix * Refactoring * Split avail if declaration is not exported itself * Move avail splitting - - - - - b9b4faa8 by Alex Biehl at 2017-10-08T19:38:21+02:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 43325295 by Alex Biehl at 2017-10-08T20:18:46+02:00 Fix merge fallout - - - - - c6423cc0 by Alex Biehl at 2017-10-08T20:36:12+02:00 Copy QuickJump files over - - - - - 1db587c3 by Tim Baumann at 2017-10-09T18:33:09+02:00 Use <details> element for collapsibles (#690) * Remove unnecessary call to 'collapseSection' The call is unnecessary since there is no corresponding toggle for hiding the section of orphan instances. * Use <details> for collapsibles This makes them work even when JS is disabled. Closes haskell/haddock#560. - - - - - 1b54c64b by Tim Baumann at 2017-10-10T09:50:59+02:00 Quick Jump: Show error when loading 'doc-index.json' failed (#691) - - - - - 910f716d by Veronika Romashkina at 2017-10-24T07:36:20+02:00 Fix tiny typo in docs (#693) - - - - - b21de7e5 by Ryan Scott at 2017-10-24T13:07:15+02:00 Overhaul Haddock's rendering of kind signatures (#681) * Overhaul Haddock's rendering of kind signatures * Strip off kind signatures when specializing As an added bonus, this lets us remove an ugly hack specifically for `(->)`. Yay! * Update due to 0390e4a0f61e37bd1dcc24a36d499e92f2561b67 * @alexbiehl's suggestions * Import injectiveVarsOfBinder from GHC - - - - - 6704405c by Ryan Scott at 2017-10-28T07:10:27+02:00 Fix Haddock rendering of kind-indexed data family instances (#694) - - - - - 470f6b9c by Alex Biehl at 2017-10-30T08:45:51+01:00 Add QuickJump version to meta.json (#696) - - - - - b89eccdf by Alex Biehl at 2017-10-30T10:15:49+01:00 Put Quickjump behind --quickjump flag (#697) - - - - - 3095fb58 by Alex Biehl at 2017-10-30T19:09:06+01:00 Add build command to package.json - - - - - f223fda9 by Alex Biehl at 2017-10-30T19:10:39+01:00 Decrease threshold for fuzzy matching - - - - - 80245dda by Edward Z. Yang at 2017-10-31T20:35:05+01:00 Supported reexported-modules via --reexport flag. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 7e389742 by Alex Biehl at 2017-10-31T20:37:56+01:00 Correct missing title in changelog - - - - - 1a2a1c03 by Alex Biehl at 2017-10-31T20:59:07+01:00 Copy quickjump.css for nicer error messages - - - - - db234bb9 by Alex Biehl at 2017-10-31T21:31:18+01:00 Reexported modules: Report warnings if argument cannot be parsed or ... module cannot be found - - - - - eea8a205 by Carlo Hamalainen at 2017-10-31T21:43:14+01:00 More general type for nameCacheFromGhc. (#539) - - - - - 580eb42a by Alex Biehl at 2017-10-31T21:46:52+01:00 Remote tab - - - - - 0e599498 by Alex Biehl at 2017-10-31T21:48:55+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 7b8539bb by Alex Biehl at 2017-10-31T22:28:34+01:00 fullModuleContents traverses exports in declaration order - - - - - 0c91fbf2 by Alex Biehl at 2017-10-31T22:32:31+01:00 Remove excessive use of list comprehensions - - - - - f7356e02 by Alex Biehl at 2017-11-01T19:11:03+01:00 Make better use of AvailInfo - - - - - f3e512d5 by Alex Biehl at 2017-11-02T12:16:22+01:00 Always return documentation for exported subordinates ... event if they have no documentation (e.g. noDocForDecl) By using the information in the AvailInfo we don't need additional export checks. - - - - - 7cf58898 by Alan Zimmerman at 2017-11-07T08:28:03+02:00 Match changes for Trees that Grow in GHC - - - - - e5105a41 by Alan Zimmerman at 2017-11-08T17:21:58+02:00 Match Trees That Grow - - - - - 55178266 by Alan Zimmerman at 2017-11-11T22:20:31+02:00 Match Trees that Grow in GHC for HsExpr - - - - - 2082ab02 by Ryan Scott at 2017-11-14T15:27:03+01:00 Actually render infix type operators as infix (#703) * Actually render infix type operators as infix * Account for things like `(f :*: g) p`, too - - - - - c52ab7d0 by Alan Zimmerman at 2017-11-14T23:14:26+02:00 Clean up use of PlaceHolder, to match TTG - - - - - 81cc9851 by Moritz Angermann at 2017-11-20T07:52:49+01:00 Declare use of `Paths_haddock` module in other-modules (#705) This was detected by `-Wmissing-home-modules` - - - - - f9d27598 by Moritz Angermann at 2017-11-20T12:47:34+01:00 Drop Paths_haddock from ghc.mk (#707) With haskell/haddock#705 and haskell/haddock#706, the custom addition should not be necessary any more. # Conflicts: # ghc.mk - - - - - f34818dc by Moritz Angermann at 2017-11-20T12:47:59+01:00 Add autogen-modules (#706) > Packages using 'cabal-version: >= 1.25' and the autogenerated module Paths_* must include it also on the 'autogen-modules' field besides 'exposed-modules' and 'other-modules'. This specifies that the module does not come with the package and is generated on setup. Modules built with a custom Setup.hs script also go here to ensure that commands like sdist don't fail. # Conflicts: # haddock.cabal - - - - - bb43a0aa by Ben Gamari at 2017-11-21T15:50:12-05:00 Revert "Clean up use of PlaceHolder, to match TTG" This reverts commit 134a7bb054ea730b13c8629a76232d73e3ace049. - - - - - af9ebb2b by Ben Gamari at 2017-11-21T15:50:14-05:00 Revert "Match Trees that Grow in GHC for HsExpr" This reverts commit 9f054dc365379c66668de6719840918190ae6e44. - - - - - 5d35c3af by Ben Gamari at 2017-11-21T15:50:15-05:00 Revert "Match Trees That Grow" This reverts commit 73a26af844ac50b8bec39de11d64452a6286b00c. - - - - - 99a8e43b by Ben Gamari at 2017-11-21T16:36:06-05:00 Revert "Match changes for Trees that Grow in GHC" This reverts commit 01eeeb048acd2dd05ff6471ae148a97cf0720547. - - - - - c4d650c2 by Ben Gamari at 2017-12-04T15:06:07-05:00 Bump GHC version - - - - - 027b2274 by Ben Gamari at 2017-12-04T17:06:31-05:00 Bump GHC bound to 8.4.* - - - - - 58eaf755 by Alex Biehl at 2017-12-06T15:44:24+01:00 Update changelog - - - - - d68f5584 by Simon Peyton Jones at 2017-12-07T14:39:56+00:00 Track changes to follow Trac haskell/haddock#14529 This tracks the refactoring of HsDecl.ConDecl. - - - - - dc519d6b by Alec Theriault at 2018-01-06T08:20:43-08:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - 8285118c by Alec Theriault at 2018-01-13T12:12:37+01:00 Constructor and pattern synonym argument docs (#709) * Support Haddocks on constructor arguments This is in conjunction with https://phabricator.haskell.org/D4094. Adds support for rendering Haddock's on (non-record) constructor arguments, both for regular and GADT constructors. * Support haddocks on pattern synonym arguments It appears that GHC already parsed these - we just weren't using them. In the process of doing this, I tried to deduplicate some code around handling patterns. * Update the markup guide Add some information about the new support for commenting constructor arguments, and mention pattern synonyms and GADT-style constructors. * Overhaul LaTeX support for data/pattern decls This includes at least * fixing several bugs that resulted in invalid LaTeX * fixing GADT data declaration headers * overhaul handling of record fields * overhaul handling of GADT constructors * overhaul handling of bundled patterns * add support for constructor argument docs * Support GADT record constructors This means changes what existing HTML docs look like. As for LaTeX, looks like GADT records were never even supported. Now they are. * Clean up code/comments Made code/comments consistent between the LaTeX and XHTML backend when possible. * Update changelog * Patch post-rebase regressions * Another post-rebase change We want return values to be documentable on record GADT constructors. - - - - - ca4fabb4 by Alec Theriault at 2018-01-15T17:12:18-08:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 4c472fea by Ryan Scott at 2018-01-19T10:44:02+01:00 Fix haskell/haddock#732 (#733) - - - - - bff14dbd by Alex Biehl at 2018-01-19T15:33:30+01:00 extractDecl: Extract associated types correctly (#736) - - - - - a2a94a73 by Alex Biehl at 2018-01-19T15:34:40+01:00 extractDecl: Extract associated types correctly (#736) - - - - - 26df93dc by Alex Biehl at 2018-01-20T10:18:22+01:00 haddock-api: bump ghc to ^>= 8.4 - - - - - f65aeb1d by Alex Biehl at 2018-01-20T19:18:20+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - 0e721b97 by Alex Biehl at 2018-01-20T19:20:19+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - cb6234f6 by Ben Gamari at 2018-01-26T13:40:55-05:00 Merge remote-tracking branch 'harpocrates/fix/missing-orphan-instances' into ghc-head - - - - - 0fc28554 by Alec Theriault at 2018-02-01T14:58:18+01:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - b9123772 by Alec Theriault at 2018-02-01T14:58:18+01:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 0c12e274 by Ryan Scott at 2018-02-01T14:58:18+01:00 Fix haskell/haddock#548 by rendering datatype kinds more carefully (#702) - - - - - 8876d20b by Alec Theriault at 2018-02-01T14:58:18+01:00 Use the GHC lexer for the Hyperlinker backend (#714) * Start changing to use GHC lexer * better cpp * Change SrcSpan to RealSrcSpan * Remove error * Try to stop too many open files * wip * wip * Revert "wip" This reverts commit b605510a195f26315e3d8ca90e6d95a6737553e1. Conflicts: haddock-api/haddock-api.cabal haddock-api/src/Haddock/Interface.hs * Remove pointless 'caching' * Use dlist rather than lists when finding vars * Use a map rather than list * Delete bogus comment * Rebase followup Things now run using the GHC lexer. There are still - stray debug statements - unnecessary changes w.r.t. master * Cleaned up differences w.r.t. current Haddock HEAD Things are looking good. quasiquotes in particular look beautiful: the TH ones (with Haskell source inside) colour/link their contents too! Haven't yet begun to check for possible performance problems. * Support CPP and top-level pragmas The support for these is hackier - but no more hacky than the existing support. * Tests pass, CPP is better recognized The tests were in some cases altered: I consider the new output to be more correct than the old one.... * Fix shrinking of source without tabs in test * Replace 'Position'/'Span' with GHC counterparts Replaces 'Position' -> 'GHC.RealSrcLoc' and 'Span' -> 'GHC.RealSrcSpan'. * Nits * Forgot entry in .cabal * Update changelog - - - - - 95c6a771 by Alec Theriault at 2018-02-01T14:58:18+01:00 Clickable anchors for headings (#716) See haskell/haddock#579. This just adds an <a> tag around the heading, pointing to the heading itself. - - - - - 21463d28 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump: Matches on function names weight more than matches in ... module names. - - - - - 8023af39 by Alex Biehl at 2018-02-01T14:58:18+01:00 Treat escaped \] better in definition lists (#717) This fixes haskell/haddock#546. - - - - - e4866dc1 by Alex Biehl at 2018-02-01T14:58:18+01:00 Remove scanner, takeWhile1_ already takes care of escaping - - - - - 9bcaa49d by Alex Biehl at 2018-02-01T14:58:18+01:00 Take until line feed - - - - - 01d2af93 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Add simple framework for running parser fixtures (#668) * Add simple framework for running parser fixtures * Compatible with tree-diff-0.0.0.1 * Use parseParas to parse fixtures This allows to test all syntactic constructs available in haddock markup. - - - - - 31128417 by Alec Theriault at 2018-02-01T14:58:18+01:00 Patch flaky parser test (#720) * Patch flaky parser test This test was a great idea, but it doesn't port over too well to using the GHC lexer. GHC rewrites its input a bit - nothing surprising, but we need to guard against those cases for the test. * Change instance head * Change use site - - - - - 9704f214 by Herbert Valerio Riedel at 2018-02-01T14:58:18+01:00 Include secondary LICENSE file in source dist - - - - - 51f25074 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Grid Tables (#718) * Add table examples * Add table types and adopt simple parser Simple parser is done by Giovanni Cappellotto (@potomak) in https://github.com/haskell/haddock/pull/577 It seems to support single fine full tables, so far from full RST-grid tables, but it's good start. Table type support row- and colspans, but obviously parser is lacking. Still TODO: - Latex backend. Should we use multirow package https://ctan.org/pkg/multirow?lang=en? - Hoogle backend: ? * Implement grid-tables * Refactor table parser * Add two ill-examples * Update CHANGES.md * Basic documentation for tables * Fix documentation example - - - - - 670d6200 by Alex Biehl at 2018-02-01T14:58:18+01:00 Add grid table example to cheatsheet (pdf and svg need to be regenerated thought) - - - - - 4262dec9 by Alec Theriault at 2018-02-01T14:58:18+01:00 Fix infinite loop when specializing instance heads (#723) * Fix infinite loop when specializing instance heads The bug can only be triggered from TH, hence why it went un-noticed for so long. * Add test for haskell/haddock#679 and haskell/haddock#710 - - - - - 67ecd803 by Alec Theriault at 2018-02-01T14:58:18+01:00 Filter RTS arguments from 'ghc-options' arguments (#725) This fixes haskell/haddock#666. - - - - - 7db26992 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump Scrollable overlay - - - - - da9ff634 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Hyperlinker: Adjust parser to new PFailed constructor - - - - - 7b7cf8cb by Alexander Biehl at 2018-02-01T14:58:18+01:00 Specialize: Add missing IdP annotations - - - - - 78cd7231 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Convert: Correct pass type - - - - - a2d0f590 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Warning free compilation - - - - - cd861cf3 by Alexander Biehl at 2018-02-01T14:58:18+01:00 hadock-2.19.0 / haddock-api-2.19.0 / haddock-library-1.5.0 - - - - - c6651b72 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Adjust changelogs - - - - - 1e93da0b by Alexander Biehl at 2018-02-01T14:58:18+01:00 haddock-library: Info about breaking changes - - - - - f9b11db8 by Alec Theriault at 2018-02-02T12:36:02+01:00 Properly color pragma contents in hyperlinker The hyperlinker backend now classifies the content of pragmas as 'TkPragma'. That means that in something like '{-# INLINE foo #-}', 'foo' still gets classified as a pragma token. - - - - - c40b0043 by Alec Theriault at 2018-02-02T12:36:02+01:00 Support the new 'ITcolumn_prag' token - - - - - 4a2a4d39 by Alex Biehl at 2018-02-03T12:11:55+01:00 QuickJump: Mitigate encoding problems on Windows - - - - - bb34503a by Alex Biehl at 2018-02-04T18:39:31+01:00 Use withBinaryFile - - - - - 637605bf by Herbert Valerio Riedel at 2018-02-05T09:48:32+01:00 Try GHC 8.4.1 for Travis CI job - - - - - 7abb67e4 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 try harder to build w/ GHC 8.4.1 - - - - - 8255cc98 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 Add `SPDX-License-Identifier` as alised for "license" module header tokens C.f. SPDX 2.1 - Appendix V https://spdx.org/spdx-specification-21-web-version#h.twlc0ztnng3b The tag should appear on its own line in the source file, generally as part of a comment. SPDX-License-Identifier: <SPDX License Expression> Cherry-picked from haskell/haddock#743 - - - - - 267cd23d by Herbert Valerio Riedel at 2018-02-05T10:24:34+01:00 Make test-suite SMP compatible - - - - - 95d4bf40 by Alec Theriault at 2018-02-05T22:01:04+01:00 Hyperlink pattern synonyms and 'module' imports (#744) Links to pattern synonyms are now generated, as well as links from modules in import lists. Fixes haskell/haddock#731. - - - - - 67838dcd by Alec Theriault at 2018-02-06T08:23:36+01:00 Don't warn about missing '~' (#746) This manually filters out '~' from the list of things to warn about. It truly makes no sense to warn on this since '~' has nothing it could link to - it is magical. This fixes haskell/haddock#532. - - - - - ab6c3f9f by Alec Theriault at 2018-02-06T08:24:47+01:00 Don't barf on 'HsSpliceTy' (#745) This handles 'HsSpliceTy's by replacing them with what they expand to. IIUC everything that is happening, 'renameHsSpliceTy' should not be able to fail for the inputs we feed it from GHC. This fixes haskell/haddock#574. - - - - - 92bf95ad by Alex Biehl at 2018-02-06T08:28:23+01:00 Rename: renameHsSpliceTy ttg - - - - - 3130b1e1 by Alex Biehl at 2018-02-06T09:02:14+01:00 Expand SigDs - - - - - c72adae5 by Alex Biehl at 2018-02-06T09:20:51+01:00 fullModuleContents: support named docs - - - - - de2e4dbf by Alex Biehl at 2018-02-06T13:56:17+01:00 Hyperlinker: Also link pattern synonym arguments - - - - - b7c98237 by Alex Biehl at 2018-02-09T18:44:23+01:00 Expand SigD in a better place In https://github.com/haskell/haddock/issues/287 we found that haddock-2.19.0 would miss documentation on class methods with multiples names. This patch uses expandSigDecls in a more sensible place. - - - - - 8f598b27 by Alec Theriault at 2018-02-11T12:29:56+01:00 Add module tooltips to linked identifiers (#753) No more clicking to figure out whether your bytestring is strict or lazy! - - - - - d812e65d by Alec Theriault at 2018-02-11T12:31:44+01:00 Add 'show' option to complement 'hide' (#752) * Add 'show' option to complement 'hide' The behaviour is for flags passed in the command line to override flags in file headers. In the command line, later flags override earlier ones. Fixes haskell/haddock#751 and haskell/haddock#266. * Add a '--show-all' option - - - - - 6676cecb by Alex Biehl at 2018-02-18T11:07:15-05:00 QuickJump: Mitigate encoding problems on Windows (cherry picked from commit 86292c54bfee2343aee84559ec01f1fc68f52231) - - - - - e753dd88 by Alex Biehl at 2018-02-18T17:59:54+01:00 Use withBinaryFile - - - - - 724dc881 by Tamar Christina at 2018-02-19T05:34:49+01:00 Haddock: support splitted include paths. (#689) - - - - - 9b6d6f50 by Alex Biehl at 2018-02-19T05:57:02+01:00 Teach the HTML backend how to render methods with multiple names - - - - - a74aa754 by Alexander Biehl at 2018-02-19T10:04:34+01:00 Hoogle/Latex: Remove use of partial function - - - - - 66d8bb0e by Alec Theriault at 2018-02-25T16:04:01+01:00 Fix file handle leak (#763) (#764) Brought back some mistakenly deleted code for handling encoding and eager reading of files from e0ada1743cb722d2f82498a95b201f3ffb303137. - - - - - bb92d03d by Alex Biehl at 2018-03-02T14:21:23+01:00 Enable running test suite with stock haddock and ghc using ``` $ cabal new-run -- html-test --haddock-path=$(which haddock) --ghc-path=$(which ghc) ``` - - - - - dddb3cb2 by Alex Biehl at 2018-03-02T15:43:21+01:00 Make testsuite work with haddock-1.19.0 release (#766) - - - - - f38636ed by Alec Theriault at 2018-03-02T15:48:36+01:00 Support unicode operators, proper modules Unicode operators are a pretty big thing in Haskell, so supporting linking them seems like it outweighs the cost of the extra machinery to force Attoparsec to look for unicode. Fixes haskell/haddock#458. - - - - - 09d89f7c by Alec Theriault at 2018-03-02T15:48:43+01:00 Remove bang pattern - - - - - d150a687 by Alex Biehl at 2018-03-02T15:48:48+01:00 fix test - - - - - d6fd71a5 by Alex Biehl at 2018-03-02T16:22:38+01:00 haddock-test: Be more explicit which packages to pass We now pass `-hide-all-packages` to haddock when invoking the testsuite. This ensures we don't accidentally pick up any dependencies up through ghc.env files. - - - - - 0932c78c by Alex Biehl at 2018-03-02T17:50:38+01:00 Revert "fix test" This reverts commit 1ac2f9569242f6cb074ba6e577285a4c33ae1197. - - - - - 52516029 by Alex Biehl at 2018-03-02T18:16:50+01:00 Fix Bug548 for real - - - - - 89df9eb5 by Alex Biehl at 2018-03-05T18:28:19+01:00 Hyperlinker: Links for TyOps, class methods and associated types - - - - - d019a4cb by Ryan Scott at 2018-03-06T13:43:56-05:00 Updates for haskell/haddock#13324 - - - - - 6d5a42ce by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump haddock-2.19.0.1, haddock-api-2.19.0.1, haddock-library-1.5.0.1 - - - - - c0e6f380 by Alex Biehl at 2018-03-10T18:25:57+01:00 Update changelogs for haddock-2.19.0.1 and haddock-library-1.5.0.1 - - - - - 500da489 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Update to QC 2.11 - - - - - ce8362e9 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Restore backward-compat with base-4.5 through base-4.8 - - - - - baae4435 by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump lower bound for haddock-library - - - - - 10b7a73e by Alex Biehl at 2018-03-10T18:25:57+01:00 Haddock: Straighten out base bound - - - - - a6096f7b by Alex Biehl at 2018-03-13T08:45:06+01:00 extractDecl: Extract constructor patterns from data family instances (#776) * extractDecl: Allow extraction of data family instance constructors * extractDecl: extract data family instance constructors - - - - - ba4a0744 by Simon Jakobi at 2018-03-14T08:26:42+01:00 Readme: Update GHC version (#778) - - - - - 8de157d4 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for definition lists - - - - - 425b46f9 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for links - - - - - d53945d8 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for inline links - - - - - f1dc7c99 by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Slightly unmangle output - - - - - 0879d31c by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Prevent stdout buffering - - - - - 1f9e5f1b by Simon Jakobi at 2018-03-14T20:39:29+01:00 haddock-library.cabal: Clean up GHC options - - - - - 066b891a by Simon Jakobi at 2018-03-14T20:39:29+01:00 Make a proper definition for the <link> parser - - - - - 573d6ba7 by Alec Theriault at 2018-03-21T09:16:57+01:00 Show where instances are defined (#748) * Indicate source module of instances Above instance, we now also display a link to the module where the instance was defined. This is sometimes helpful in figuring out what to import. * Source module for type/data families too * Remove parens * Accept tests - - - - - 99b5d28b by Alex Biehl at 2018-03-21T09:20:36+01:00 Prepare changelog for next release - - - - - 482d3a93 by Alex Biehl at 2018-03-23T15:57:36+01:00 Useful cost centres, timers and allocation counters (#785) * Add some useful cost-centres for profiling * Add withTiming for each haddock phase Invoking haddock with `--optghc=-ddump-timings` now shows the amount of time spent and the number of allocated bytes for each phase. - - - - - 773b41bb by Alec Theriault at 2018-03-27T08:35:59+02:00 @since includes package name (#749) * Metadoc stores a package name This means that '@since' annotations can be package aware. * Get the package name the right way This should extract the package name for `@since` annotations the right way. I had to move `modulePackageInfo` around to do this and, in the process, I took the liberty to update it. Since it appears that finding the package name is something that can fail, I added a warning for this case. * Silence warnings * Hide package for local 'since' annotations As discussed, this is still the usual case (and we should avoid being noisy for it). Although this commit is large, it is basically only about threading a 'Maybe Package' from 'Haddock.render' all the way to 'Haddock.Backends.Xhtml.DocMarkup.renderMeta'. * Bump binary interface version * Add a '--since-qual' option This controls when to qualify since annotations with the package they come from. The default is always, but I've left an 'external' variant where only those annotations coming from outside of the current package are qualified. * Make ParserSpec work * Make Fixtures work * Use package name even if package version is not available The @since stuff needs only the package name passed in, so it makes sense to not be forced to pass in a version too. - - - - - e42c57bc by Alex Biehl at 2018-03-27T08:42:50+02:00 haddock-2.19.1, haddock-api-2.19.1, haddock-library-1.6.0 - - - - - 8373a529 by Alex Biehl at 2018-03-28T10:17:11+02:00 Bump haddock and haddock-api to 2.20.0 - - - - - 5038eddd by Jack Henahan at 2018-04-03T13:28:12+02:00 Clear search string on hide for haskell/haddock#781 (#789) - - - - - 920ca1eb by Alex Biehl at 2018-04-03T16:35:50+02:00 Travis: Build with ghc-8.4.2 (#793) - - - - - a232f0eb by Alan Zimmerman at 2018-04-07T14:14:32+02:00 Match changes in GHC for D4199 Removing HasSourceText and SourceTextX classes. - - - - - ab85060b by Alan Zimmerman at 2018-04-09T21:20:24+02:00 Match GHC changes for TTG - - - - - 739302b6 by Alan Zimmerman at 2018-04-13T13:31:44+02:00 Match GHC for TTG implemented on HsBinds, D4581 - - - - - 2f56d3cb by Ryan Scott at 2018-04-19T11:42:58-04:00 Bump upper bound on base to < 4.13 See https://ghc.haskell.org/trac/ghc/ticket/15018. - - - - - a49df92a by Alex Biehl at 2018-04-20T07:31:44+02:00 Don't treat fixity signatures like declarations - - - - - d02c103b by Ryan Scott at 2018-04-24T11:20:11-04:00 Add regression test for haskell/haddock#413 Fixes haskell/haddock#413. - - - - - c7577f52 by Ryan Scott at 2018-04-24T13:51:06-07:00 Improve the Hoogle backend's treatment of type families (#808) Fixes parts 1 and 2 of haskell/haddock#806. - - - - - d88f85b1 by Alec Theriault at 2018-04-25T11:24:07-07:00 Replace 'attoparsec' with 'parsec' (#799) * Remove attoparsec with parsec and start fixing failed parses * Make tests pass * Fix encoding issues The Haddock parser no longer needs to worry about bytestrings. All the internal parsing work in haddock-library happens over 'Text'. * Remove attoparsec vendor * Fix stuff broken in 'attoparsec' -> 'parsec' * hyperlinks * codeblocks * examples Pretty much all issues are due to attoparsec's backtracking failure behaviour vs. parsec's non-backtracking failure behaviour. * Fix small TODOs * Missing quote + Haddocks * Better handle spaces before/after paragraphs * Address review comments - - - - - fc25e2fe by Alan Zimmerman at 2018-04-27T15:36:53+02:00 Match changes in GHC for TTG - - - - - 06175f91 by Herbert Valerio Riedel at 2018-05-01T18:11:09+02:00 Merge branch 'ghc-head' with 'ghc-8.4' - - - - - 879caaa8 by Alec Theriault at 2018-05-07T18:53:15-07:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 3e0120cb by Simon Jakobi at 2018-05-07T19:00:18-07:00 Add docs for some DocH constructors (#814) - - - - - 0a32c6db by Alec Theriault at 2018-05-08T02:15:45-07:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 8816e783 by Simon Jakobi at 2018-05-08T10:48:11-07:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - ad60366f by Ryan Scott at 2018-05-10T11:19:47-04:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - 03b7cc3b by Ryan Scott at 2018-05-10T11:24:38-04:00 Wibbles - - - - - b03dd563 by Chaitanya Koparkar at 2018-05-10T11:44:58-04:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 9f298a40 by Ben Gamari at 2018-05-13T17:36:04-04:00 Account for refactoring of LitString - - - - - ea3dabe7 by Ryan Scott at 2018-05-16T09:21:43-04:00 Merge pull request haskell/haddock#826 from haskell/T825 Remove Hoogle backend hack that butchers infix datatype names - - - - - 0d234f7c by Alec Theriault at 2018-05-23T11:29:05+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 15fc9712 by Simon Jakobi at 2018-05-31T04:17:47+02:00 Adjust to new HsDocString internals - - - - - 6f1e19a8 by Ben Gamari at 2018-06-02T16:18:58-04:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 0d0355d9 by Ryan Scott at 2018-06-04T21:26:59-04:00 DerivingVia changes - - - - - 0d93475a by Simon Jakobi at 2018-06-05T19:47:05+02:00 Bump a few dependency bounds (#845) - - - - - 5cbef804 by Alec Theriault at 2018-06-05T19:47:16+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 9094c56f by Alec Theriault at 2018-06-05T22:53:25+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 70188719 by Simon Jakobi at 2018-06-08T22:20:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - 495cd1fc by Chaitanya Koparkar at 2018-06-13T23:01:34+02:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 81088732 by Ben Gamari at 2018-06-13T23:01:34+02:00 Account for refactoring of LitString - - - - - 7baf6587 by Simon Jakobi at 2018-06-13T23:05:08+02:00 Adjust to new HsDocString internals - - - - - bb61464d by Ben Gamari at 2018-06-13T23:05:22+02:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 5d8cb87f by Ryan Scott at 2018-06-13T23:39:30+02:00 DerivingVia changes - - - - - 73d373a3 by Alec Theriault at 2018-06-13T23:39:30+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 4865e254 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Remove `ITtildehsh` token - - - - - b867db54 by Alec Theriault at 2018-06-13T23:39:30+02:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 9598e392 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Add docs for some DocH constructors (#814) - - - - - 8a59035b by Alec Theriault at 2018-06-13T23:39:30+02:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 29350fc8 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - 2590bbd9 by Ryan Scott at 2018-06-13T23:39:30+02:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - a9939fdc by Ryan Scott at 2018-06-13T23:39:30+02:00 Wibbles - - - - - a22f7df4 by Alec Theriault at 2018-06-13T23:39:30+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 8741015d by Simon Jakobi at 2018-06-13T23:39:30+02:00 Bump a few dependency bounds (#845) - - - - - 4791e1cc by Alec Theriault at 2018-06-13T23:39:30+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 311d3216 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - d0577817 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Complete FixitySig and FamilyDecl pattern matches - - - - - 055b3aa7 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Fix redundant import warnings - - - - - f9ce19b1 by Simon Jakobi at 2018-06-13T23:49:52+02:00 html-test: Accept output - - - - - 04604ea7 by Simon Jakobi at 2018-06-13T23:54:37+02:00 Bump bounds on Cabal - - - - - 0713b692 by Simon Jakobi at 2018-06-14T00:00:12+02:00 Merge branch 'ghc-head' into ghc-head-update-3 - - - - - c6a56bfd by Simon Jakobi at 2018-06-14T02:33:27+02:00 Bump ghc bound for haddock-api spec test-suite - - - - - 119d04b2 by Simon Jakobi at 2018-06-14T12:37:48+02:00 Travis: `--allow-newer` for all packages - - - - - 0e876e2c by Alex Biehl at 2018-06-14T15:28:52+02:00 Merge pull request haskell/haddock#857 from sjakobi/ghc-head-update-3 Update ghc-head - - - - - 5be46454 by Alec Theriault at 2018-06-14T21:42:45+02:00 Improved handling of interfaces in 'haddock-test' (#851) This should now work with an inplace GHC where (for instance) HTML directories may not be properly recorded in the package DB. - - - - - 96ab1387 by Vladislav Zavialov at 2018-06-14T17:06:21-04:00 Handle -XStarIsType - - - - - e518f8c4 by Ben Gamari at 2018-06-14T17:48:00-04:00 Revert unintentional reversion of fix of haskell/haddock#548 - - - - - 01b9f96d by Alan Zimmerman at 2018-06-19T11:52:22+02:00 Match changes in GHC for haskell/haddock#14259 - - - - - 7f8c8298 by Ben Gamari at 2018-06-19T18:14:27-04:00 Bump GHC version to 8.6 - - - - - 11c6b5d2 by Ryan Scott at 2018-06-19T23:17:31-04:00 Remove HsEqTy and XEqTy - - - - - b33347c2 by Herbert Valerio Riedel at 2018-06-20T23:14:52+02:00 Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. - - - - - f0d2460e by Herbert Valerio Riedel at 2018-06-20T23:28:46+02:00 Update Travis CI job - - - - - ef239223 by Herbert Valerio Riedel at 2018-06-20T23:32:41+02:00 Drop GHC HEAD from CI and update GHC to 8.4.3 It's a waste of resource to even try to build this branch w/ ghc-head; so let's not do that... - - - - - 41c4a9fa by Ben Gamari at 2018-06-20T18:26:20-04:00 Bump GHC version to 8.7 - - - - - 8be593dc by Herbert Valerio Riedel at 2018-06-21T22:32:15+02:00 Update CI job to use GHC 8.7.* - - - - - b91d334a by Simon Jakobi at 2018-06-30T13:41:38+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section - - - - - f707d848 by Alec Theriault at 2018-07-05T10:43:35-04:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. - - - - - a6d2b8dc by Alec Theriault at 2018-07-06T10:06:32-04:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case - - - - - 13819f71 by Alan Zimmerman at 2018-07-15T19:33:51+02:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 - - - - - c346aa78 by Simon Jakobi at 2018-07-19T12:29:32+02:00 haddock-library: Bump bounds for containers - - - - - 722e733c by Simon Jakobi at 2018-07-19T13:36:45+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] - - - - - f0bd83fd by Alec Theriault at 2018-07-19T14:39:57+02:00 Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. - - - - - 394053a8 by Simon Jakobi at 2018-07-19T14:58:07+02:00 haddock-library: Bump bounds for containers - - - - - 1bda11a2 by Alec Theriault at 2018-07-20T09:04:03+02:00 Add HEAD.hackage overlay (#887) * Add HEAD.hackage overlay * Add HCPKG variable - - - - - c7b4ab45 by Alec Theriault at 2018-07-20T12:01:16+02:00 Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test - - - - - c05d32ad by Alec Theriault at 2018-07-20T12:01:49+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output - - - - - 24b39ee4 by Alec Theriault at 2018-07-20T12:02:16+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. - - - - - cb9d2099 by Simon Jakobi at 2018-07-20T13:39:29+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) - - - - - 133f24f5 by Alec Theriault at 2018-07-20T13:39:29+02:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) - - - - - 11024149 by Alec Theriault at 2018-07-20T13:39:29+02:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) - - - - - de0c139e by Simon Jakobi at 2018-07-20T13:39:29+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) - - - - - 6435e952 by Alec Theriault at 2018-07-20T13:39:29+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) - - - - - 1461af39 by Alec Theriault at 2018-07-20T13:39:29+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) - - - - - 69d3bde1 by Alec Theriault at 2018-07-20T13:49:47+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) - - - - - 6a5c73c7 by Alec Theriault at 2018-07-20T13:50:00+02:00 Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests - - - - - 92ca94c6 by Alec Theriault at 2018-07-20T13:55:36+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) - - - - - 981bc7fa by Simon Jakobi at 2018-07-20T15:06:06+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers - - - - - 27e7c0c5 by Simon Jakobi at 2018-07-20T15:09:05+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 49e1a415 by Simon Jakobi at 2018-07-20T16:02:02+02:00 Update the ghc-8.6 branch (#889) * Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. * README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) * Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) * Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) * tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) * Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. * Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test * Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) * Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) * Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) * Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests * Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 5ca14bed by Simon Jakobi at 2018-07-20T16:05:47+02:00 Revert "Revert "Bump GHC version to 8.6"" That commit didn't belong onto the ghc-8.6 branch. This reverts commit acbaef3b9daf1d2dea10017964bf886e77a8e967. - - - - - 2dd600dd by Simon Jakobi at 2018-07-20T16:18:21+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. - - - - - fceb2422 by Simon Jakobi at 2018-07-20T16:18:21+02:00 outOfScope: Recommend qualifying the identifier - - - - - acea5d23 by Simon Jakobi at 2018-07-20T16:19:35+02:00 outOfScope: Recommend qualifying the identifier (cherry picked from commit 73707ed58d879cc04cb644c5dab88c39ca1465b7) - - - - - 1a83ca55 by Simon Jakobi at 2018-07-20T16:19:35+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. (cherry picked from commit d504a2864a4e1982e142cf88c023e7caeea3b76f) - - - - - 48374451 by Masahiro Sakai at 2018-07-20T17:06:42+02:00 Add # as a special character (#884) '#' has special meaning used for anchors and can be escaped using backslash. Therefore it would be nice to be listed as special characters. - - - - - 5e1a5275 by Alec Theriault at 2018-07-20T23:37:24+02:00 Let `haddock-test` bypass interface version check (#890) This means `haddock-test` might * crash during deserialization * deserialize incorrectly Still - it means things _might_ work where they were previously sure not to. - - - - - 27286754 by Yuji Yamamoto at 2018-07-23T08:16:01+02:00 Avoid "invalid argument (invalid character)" on non-unicode Windows (#892) Steps to reproduce and the error message ==== ``` > stack haddock basement ... snip ... Warning: 'A' is out of scope. Warning: 'haddock: internal error: <stdout>: commitBuffer: invalid argument (invalid character) ``` Environment ==== OS: Windows 10 ver. 1709 haddock: [HEAD of ghc-8.4 when I reproduce the error](https://github.com/haskell/haddock/commit/532b209d127e4cecdbf7e9e3dcf4f653a5605b5a). (I had to use this version to avoid another probrem already fixed in HEAD) GHC: 8.4.3 stack: Version 1.7.1, Git revision 681c800873816c022739ca7ed14755e85a579565 (5807 commits) x86_64 hpack-0.28.2 Related pull request ==== https://github.com/haskell/haddock/pull/566 - - - - - 6729d361 by Alec Theriault at 2018-07-23T13:52:56-07:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). - - - - - 8cf4e6b5 by Ryan Scott at 2018-07-27T11:28:03-04:00 eqTyCon_RDR now lives in TysWiredIn After GHC commit http://git.haskell.org/ghc.git/commit/f265008fb6f70830e7e92ce563f6d83833cef071 - - - - - 1ad251a6 by Alan Zimmerman at 2018-07-30T13:28:09-04:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 (cherry picked from commit e3926b50ab8a7269fd6904b06e881745f08bc5d6) - - - - - 8aea2492 by Richard Eisenberg at 2018-08-02T10:54:17-04:00 Update against new HsImplicitBndrs - - - - - e42cada9 by Alec Theriault at 2018-08-04T17:51:30+02:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 0e852512 by Alex Biehl at 2018-08-06T13:04:02+02:00 Make --package-version optional for --hoogle generation (#899) * Make --package-version optional for --hoogle generation * Import mkVersion * It's makeVersion not mkVersion - - - - - d2abd684 by Noel Bourke at 2018-08-21T09:34:18+02:00 Remove unnecessary backslashes from docs (#908) On https://haskell-haddock.readthedocs.io/en/latest/markup.html#special-characters the backslash and backtick special characters showed up with an extra backslash before them – I think the escaping is not (or no longer) needed for those characters in rst. - - - - - 7a578a9e by Matthew Pickering at 2018-08-21T09:34:50+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - aa3d4db3 by Matthew Pickering at 2018-08-21T09:37:34+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - ede91744 by Alec Theriault at 2018-08-21T09:42:52+02:00 Better test output when Haddock crashes on a test (#902) In particular: we report the tests that crashed seperately from the tests that produced incorrect output. In order for tests to pass (and exit 0), they must not crash and must produce the right output. - - - - - 4a872b84 by Guillaume Bouchard at 2018-08-21T09:45:57+02:00 Fix a typo (#878) - - - - - 4dbf7595 by Ben Sklaroff at 2018-08-21T12:04:09-04:00 Add ITcomment_line_prag token to Hyperlinker Parser This token is necessary for parsing #line pragmas inside nested comments. Reviewers: bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D4935 - - - - - 9170b2a9 by Ben Gamari at 2018-08-21T17:55:15-04:00 Merge pull request haskell/haddock#893 from harpocrates/get-name-to-instances Accumulate explicitly which modules to load for 'attachInstances' - - - - - d57b57cc by Ben Gamari at 2018-08-21T17:59:13-04:00 Merge branch 'ghc-head' of github.com:haskell/haddock into ghc-head - - - - - 14601ca2 by Alec Theriault at 2018-08-21T19:09:37-04:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). (cherry picked from commit 5c7c596c51d69b92164e9ba920157b36ce2b2ec1) - - - - - 438c645e by Matthew Pickering at 2018-08-21T19:12:39-04:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 (cherry picked from commit e6aa8fb47b9477cc5ef5e46097524fe83e080f6d) - - - - - a80c5161 by Alec Theriault at 2018-08-21T22:06:40-07:00 Better rendering of unboxed sums/tuples * adds space after/before the '#' marks * properly reify 'HsSumTy' in 'synifyType' - - - - - 88456cc1 by Alec Theriault at 2018-08-21T22:06:40-07:00 Handle promoted tuples in 'synifyType' When we have a fully applied promoted tuple, we can expand it out properly. - - - - - fd1c1094 by Alec Theriault at 2018-08-21T22:19:34-07:00 Accept test cases - - - - - 6e80d9e0 by Alec Theriault at 2018-08-21T22:24:03-07:00 Merge pull request haskell/haddock#914 from harpocrates/feature/unboxed-stuff Better rendering of unboxed sums, unboxed tuples, promoted tuples. - - - - - 181a23f1 by Ben Gamari at 2018-08-23T15:53:48-04:00 Merge remote-tracking branch 'origin/ghc-8.6' into ghc-8.6 - - - - - 3a18c1d8 by Alec Theriault at 2018-08-27T14:15:25-07:00 Properly synify promoted list types We reconstruct promoted list literals whenever possible. That means that 'synifyType' produces '[Int, Bool, ()] instead of (Int ': (() ': (Bool ': ([] :: [Type])))) - - - - - b4794946 by Alec Theriault at 2018-09-03T07:19:55-07:00 Only look at visible types when synifying a 'HsListTy' The other types are still looked at when considering whether to make a kind signature or not. - - - - - a231fce2 by Alec Theriault at 2018-09-03T07:38:10-07:00 Merge pull request haskell/haddock#922 from harpocrates/promoted-lists Properly synify promoted list types - - - - - 0fdf044e by Ningning Xie at 2018-09-15T10:25:58-04:00 Update according to GHC Core changes - - - - - 7379b115 by Ningning Xie at 2018-09-15T15:40:18-04:00 update dataFullSig to work with Co Quantification This should have been in the previous patch, but wasn't. - - - - - cf84a046 by Alec Theriault at 2018-09-17T20:12:18-07:00 Fix/add to various docs * Add documentation for a bunch of previously undocumented options (fixes haskell/haddock#870) * Extend the documentation of `--hoogle` considerably (see haskell/haddock#807) * Describe how to add docs to `deriving` clauses (fixes haskell/haddock#912) * Fix inaccurate docs about hyperlinking infix identifiers (fixes haskell/haddock#780) - - - - - ae017935 by Alec Theriault at 2018-09-22T08:32:16-07:00 Update Travis - - - - - d95ae753 by Alec Theriault at 2018-09-22T09:34:10-07:00 Accept failing tests Also silence orphan warnings. - - - - - f3e67024 by Alec Theriault at 2018-09-22T09:41:23-07:00 Bump haddock-api-2.21.0, haddock-library-1.7.0 * Update CHANGELOGS * Update new versions in Cabal files * Purge references to ghc-8.4/master branches in README - - - - - 3f136d4a by Alec Theriault at 2018-09-22T10:53:31-07:00 Turn haddock-library into a minor release Fix some version bounds in haddock-library too. - - - - - b9def006 by Alec Theriault at 2018-09-22T13:07:35-07:00 keep cabal.project file - - - - - 4909aca7 by Alec Theriault at 2018-10-16T09:36:30-07:00 Build on 7.4 and 7.8 - - - - - 99d20a28 by Herbert Valerio Riedel at 2018-10-16T18:45:52+02:00 Minor tweak to package description - - - - - a8059618 by Herbert Valerio Riedel at 2018-10-16T18:47:24+02:00 Merge pull request haskell/haddock#945 haddock-api 2.21.0 and haddock-library 1.6.1 release - - - - - 2d9bdfc1 by Alec Theriault at 2018-10-16T10:54:21-07:00 Bump haddock-library to 1.7.0 The 1.6.1 release should've been a major bump, since types in the `Documentation.Haddock.Parser.Monad` module changed. This version makes that module internal (as it morally should be). - - - - - ed340cef by Alec Theriault at 2018-10-16T14:59:13-07:00 Merge branch 'ghc-8.4' into ghc-8.6 - - - - - 2821a8df by Alec Theriault at 2018-10-16T15:14:48-07:00 Merge branch 'ghc-8.6' into ghc-head - - - - - a722dc84 by Alec Theriault at 2018-10-16T16:28:55-07:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 63377496 by Alec Theriault at 2018-10-16T16:39:07-07:00 Update changelog - - - - - 099a0110 by Alec Theriault at 2018-10-16T16:49:28-07:00 Merge pull request haskell/haddock#942 from harpocrates/update-docs Fix & add to documentation - - - - - 0927416f by Alec Theriault at 2018-10-16T16:50:14-07:00 Set UTF-8 encoding before writing files (#934) This should fix haskell/haddock#929, as well as guard against future problems of this sort in other places. Basically replaces 'writeFile' (which selects the users default locale) with 'writeUtf8File' (which always uses utf8). - - - - - 83b7b017 by Alec Theriault at 2018-10-16T17:42:05-07:00 Output pattern synonyms in Hoogle backend (#947) * Output pattern synonyms in Hoogle backend We were previously weren't outputting _any_ pattern synonyms, bundled or not. Now, we output both. Fixes haskell/haddock#946. * Update changelog - - - - - 81e5033d by Alec Theriault at 2018-10-16T18:04:40-07:00 Release `haddock{,-api}-2.22.0` This version will accompany ghc-8.6.2 - - - - - 9661744e by Alex Biehl at 2018-10-18T08:14:32-07:00 Add NewOcean theme And make it the default theme. - - - - - 7ae6d722 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Improve appearance and readability These changes include: - use latest Haskell's logo colors - decrease #content width to improve readability - use nicer font - improve sizes and distances - - - - - 37f8703d by NunoAlexandre at 2018-10-18T08:14:32-07:00 Include custom font in the html head - - - - - 1d5e1d79 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Update html test reference files - - - - - 53b7651f by NunoAlexandre at 2018-10-18T08:14:32-07:00 Make it responsive - It makes small screens taking more space than larger ones - fixes a few issues present in small screens currently - make it look good across different screen sizes. - - - - - 6aa1aeb1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make the style consistent with hackage Several things are addressed here: - better responsive behaviour on the header - better space usage - consistent colors overall - other nit PR comments - - - - - 3a250c5c by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Place the package name before the menu links This supports the expected responsive menu design, where the package name appears above the menu links. - - - - - cae699b3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update html-test reference files The package name element in the package-header is now a div instead of a paragraph, and it is now above the menu ul.links instead of below. - - - - - 2ec7fd2d by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve synopsis style and code - Use CSS3 instead of loading pictures to show "+" and "-" symbols - Drop redundant code - - - - - 0c874c01 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Decrease space between code blocks There was too much space between code blocks as pointed out by reviewers. - - - - - 85568ce2 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Add an initial-scale property to all haddock pages This solves an issue reported about the content looking incredibly small on mobile devices. - - - - - c1538926 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Address several PR comments - Darken text color like done for hackage - Move synopsis to left side - Make table of contents stick to the left on wide screens - Wrap links to avoid page overflow - Improve expand/collapse buttons - Fix issue with content size on mobile devices - Fix issue with font-size on landscape mode - Increase width of the content - Change colors of table of contents and synopsis - Etc - - - - - e6639e5f by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make synopsis scrollable on wide screens When the synopsis is longer than the screen, you can’t see its end and you can't scroll down either, making the content unreachable. - - - - - 1f0591ff by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve information density - Reduce font size - Improve space between and within code blocks - Improve alignments - Improve spacing within sub-blocks - - - - - bf083097 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Minor adjustments Bring in some adjustments made to hackage: - link colors - page header show everything when package title is too long - - - - - 10375fc7 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix responsive triggers overlap issue The min and max width triggers have the same values, which caused the style resolution to take an intersection of both style declarations when the screen resolution had the size of the limts (say 1280px), causing an odd behaviour and look. - - - - - 95ff2f95 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix issue with menu alignment on firefox Reported and described here: https://github.com/haskell/haddock/pull/721#issuecomment-374668869 - - - - - dc86587e by Alex Biehl at 2018-10-18T08:14:32-07:00 Changelog entry for NewOcean - - - - - 27195e47 by Herbert Valerio Riedel at 2018-10-18T08:14:32-07:00 html-test --accept - - - - - 83f4f9c0 by Alex Biehl at 2018-10-18T08:14:32-07:00 Avoid name shadowing - - - - - 231487f1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font to PT Sans Also migrate some general text related changes from hackage. - - - - - 313db81a by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Use 'flex' to fix header alignment - - - - - 5087367b by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Misc of tweaks - Update link colors to hackage scheme - Tune spacing between content elements - Update footer style - Fix and improve code blocks identation - - - - - b08020df by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font in Xhtml.hs to PT Sans - - - - - 78ce06e3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve code blocks styling - Fix and improve spacing - Improve colors and borders - - - - - 81262d20 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make package-header caption backward-compatible The current html generator of this branch wraps the package-header caption as a div, which does not work (without style adjustments) with the old themes. Changing it from div to span does the trick, without needing to adjust the old stylesheets. - - - - - dc4475cb by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update test-suite reference html pages - - - - - 393d35d8 by Alec Theriault at 2018-10-18T08:25:36-07:00 Accept tests - - - - - a94484ba by Alec Theriault at 2018-10-21T10:29:29-07:00 Fix CHANGELOG - - - - - 8797eca3 by Alec Theriault at 2018-10-21T10:36:19-07:00 Update 'data-files' to include NewOcean stuff - - - - - 1ae51e4a by Simon Jakobi at 2018-10-23T11:29:14+02:00 Fix typo in a warning - - - - - 009ad8e8 by Alec Theriault at 2018-10-24T12:47:47-07:00 Update JS dependencies This was done via `npm audit fix`. I think this fixes haskell/haddock#903 along with some more serious vulnerabilities that nobody seems to have noticed. - - - - - 051994db by Alec Theriault at 2018-10-24T17:31:09-07:00 Resurrect the style-switcher This fixes haskell/haddock#810. Looks like things were broken during the quickjump refactor of the JS. For the (git) record: I do not think the style switcher is a good idea. I'm fixing it for the same reason @mzero added it; as an answer to "rumblings from some that they didn't want their pixels changed on bit" - - - - - 2a1d620f by Alec Theriault at 2018-10-24T17:38:07-07:00 Fix copy-pasta error in data-files - - - - - ed5bfb7f by Alec Theriault at 2018-10-24T20:42:14-07:00 Fix the synopsis button Here's these changes are supposed to do: * put the synopsis back on the right side * properly have it on the edge of the screen on wide screens * adjust the background of the synopsis to match the button (otherwise the grey blends in with what is underneath) * get rid of the dotted purple line * the synopsis contents are now scrollable even when in wide screens (this has been a long-standing bug) - - - - - 883fd74b by Alec Theriault at 2018-10-25T20:16:46-07:00 Avoid more conflicts in generated ids (#954) This fixes haskell/haddock#953 by passing more names into the generated ids. - - - - - ea54e331 by Alec Theriault at 2018-10-25T21:07:12-07:00 Don't hide bullets in method docs I think thst CSS was meant only to deal with fields and the effect on bullets was accidental. Fixes haskell/haddock#926. - - - - - 9a14ef4a by Alec Theriault at 2018-10-25T22:02:07-07:00 Indent more things + slightly smaller font - - - - - b9f17e29 by Alec Theriault at 2018-10-25T22:10:01-07:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 096a3cfa by Alec Theriault at 2018-10-25T22:24:38-07:00 Accept HTML output - - - - - 2669517d by Alec Theriault at 2018-10-26T09:02:35-07:00 User manual + stuff for building GHC docs - - - - - 46b27687 by Alec Theriault at 2018-10-26T09:10:59-07:00 Make 'Contents' in NewOcean scrollable This only happens if the contents block on the left is so big that it doesn't fit (vertically) on the page. If that happens, we want it to be scrollable. - - - - - 3443dd94 by Alec Theriault at 2018-10-26T09:36:46-07:00 Revert "Make 'Contents' in NewOcean scrollable" This reverts commit f909ffd8353d6463fd5dd184998a32aa98d5c922. I missed the fact this also forces the 'Contents' to always go down to the bottom of the page. - - - - - ed081424 by Alec Theriault at 2018-10-26T14:22:23-07:00 Avoid some partiality AFAICT this wasn't causing any crashes, but that's mostly because we happen not to be forcing `pkgStr` when it would diverge. We come dangerously close to doing that in `ppHtmlIndex`. Fixes haskell/haddock#569. - - - - - 6a5bec41 by Alec Theriault at 2018-10-27T10:05:04-07:00 Fix documentation in `haddock-api` (#957) * Fix misplaced Haddocks in Haddock itself Haddock should be able to generate documentation for 'haddock-api' again. * Make CI check that documentation can be built. * Add back a doc that is OK - - - - - 5100450a by Matthew Yacavone at 2018-10-27T14:51:38-04:00 More explicit foralls (GHC Proposal 0007) - - - - - 8771a6b0 by Alec Theriault at 2018-11-05T13:58:11-08:00 Only run MathJax on entities with "mathjax" class (#960) Correspondingly, we wrap all inline/diplay math in <span class="mathjax"> ... the math .... </span> This fixes haskell/haddock#959. - - - - - bd7ff5c5 by Alec Theriault at 2018-11-05T15:54:22-08:00 Deduplicate some work in 'AttachInstances' Perf only change: * avoid needlessly union-ing maps * avoid synify-ing instances twice Took this opportunity to add some docs too - - - - - cf99fd8f by Alec Theriault at 2018-11-05T15:54:22-08:00 Specialize some SYB functions Perf only change: * Add a 'SPECIALIZE' pragma to help GHC optimize a 'Data a =>' constraint * Manually specialize the needlessly general type of 'specializeTyVarBndrs' - - - - - 4f91c473 by Alec Theriault at 2018-11-05T15:54:22-08:00 Improve perf of renaming Perf only change: * don't look up type variable names (they're never in the environment) * use a difference list for accumulating missing names * more efficient 'Functor'/'Applicative' instances for 'RnM' - - - - - 4bbab0d4 by Alec Theriault at 2018-11-05T15:54:22-08:00 Faster 'Text' driven parser combinators Perf only change: * use 'getParserState'/'setParserState' to make 'Text'-optimized parser combinators * minimize uses of 'Data.Text.{pack,unpack,cons,snoc}' - - - - - fa430c02 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support hyperlink labels with inline markup The parser for pictures hasn't been properly adjusted yet. - - - - - c1431035 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support (and flatten) inline markup in image links Inline markup is supported in image links but, as per the [commonmark recommendation][0], it is stripped back to a plain text representation. [0]: https://spec.commonmark.org/0.28/#example-547 - - - - - d4ee1ba5 by Alec Theriault at 2018-11-06T12:03:24-08:00 Accept test case - - - - - 8088aeb1 by Alec Theriault at 2018-11-06T12:03:24-08:00 Fix/add to haddock-library test suite - - - - - e78f644d by Alec Theriault at 2018-11-06T13:26:31-08:00 Bump version bounds - - - - - 644335eb by Alec Theriault at 2018-11-06T13:53:30-08:00 Merge pull request haskell/haddock#875 from harpocrates/feature/markup-in-hyperlinks Inline markup in markdown-style links and images - - - - - e173ed0d by Alec Theriault at 2018-11-07T12:37:18-08:00 Fix issues around plus/minus * swap the minimize unicode to something more intuitive * use new unicode expander/collapser for instance lists * address some alignment issues in the "index" page - - - - - b2d92df7 by Alec Theriault at 2018-11-07T13:41:57-08:00 Allow "Contents" summary to scroll in a fixed div In the unfortunate event that the "Contents" summary doesn't fit vertically (like in the "Prelude"), it will be scrollable. - - - - - ca704c23 by Alec Theriault at 2018-11-07T13:45:15-08:00 Accept HTML output changes - - - - - 82c0ec6d by Alec Theriault at 2018-11-07T18:12:54-08:00 overflow-y 'scroll' -> 'auto' - - - - - 571d7657 by Alec Theriault at 2018-11-08T19:44:12-08:00 Clicking on "Contents" navigates to top of page - - - - - 8065a012 by Alec Theriault at 2018-11-08T19:44:17-08:00 Space out functions more Also, functions and data decls now have the same space before and after them. - - - - - cc650ede by Alec Theriault at 2018-11-09T08:13:35-08:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 65f8c17f by Alec Theriault at 2018-11-10T14:04:06-08:00 Update changelog - - - - - 20473847 by Alec Theriault at 2018-11-10T14:21:40-08:00 Replace oplus/ominus expander/collapser icons with triangles - - - - - 16592957 by Alec Theriault at 2018-11-10T14:35:10-08:00 Merge pull request haskell/haddock#949 from haskell/wip/new-ocean Introduce NewOcean theme. - - - - - 357cefe1 by Alec Theriault at 2018-11-10T16:02:13-08:00 Merge branch 'ghc-8.6' into ghc-head - - - - - de612267 by Alec Theriault at 2018-11-11T20:01:21-08:00 Rename 'NewOcean' theme to 'Linuwial' - - - - - 954b5baa by Alec Theriault at 2018-11-12T08:33:18-08:00 Add blockquote styling Matches b71da1feabf33efbbc517ac376bb690b5a604c2f from hackage-server. Fixes haskell/haddock#967. - - - - - d32c0b0b by Fangyi Zhou at 2018-11-12T10:24:13-08:00 Fix some broken links (#15733) Summary: For links in subpackages as well. https://phabricator.haskell.org/D5257 Test Plan: Manually verify links Reviewers: mpickering, bgamari, osa1 Reviewed By: osa1 GHC Trac Issues: haskell/haddock#15733 Differential Revision: https://phabricator.haskell.org/D5262 - - - - - 41098b1f by Alp Mestanogullari at 2018-11-15T22:40:09+01:00 Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change It got introduced in ghc/ghc at ae2c9b40f5b6bf272251d1f4107c60003f541b62. - - - - - c5c1c7e0 by Alec Theriault at 2018-11-15T13:48:13-08:00 Merge pull request haskell/haddock#970 from alpmestan/alp/fix-promotionflag Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change - - - - - 6473d3a4 by Shayan-Najd at 2018-11-23T01:38:49+01:00 [TTG: Handling Source Locations] Foundation and Pat Trac Issues haskell/haddock#15495 This patch removes the ping-pong style from HsPat (only, for now), using the plan laid out at https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/HandlingSourceLocations (solution A). - the class `HasSrcSpan`, and its functions (e.g., `cL` and `dL`), are introduced - some instances of `HasSrcSpan` are introduced - some constructors `L` are replaced with `cL` - some patterns `L` are replaced with `dL->L` view pattern - some type annotation are necessarily updated (e.g., `Pat p` --> `Pat (GhcPass p)`) - - - - - 7a088dfe by Alec Theriault at 2018-11-26T11:11:28-08:00 More uniform handling of `forall`'s in HTML/LaTeX * don't forget to print explicit `forall`'s when there are arg docs * when printing an explicit `forall`, print all tyvars Fixes haskell/haddock#973 - - - - - d735e570 by Alec Theriault at 2018-12-12T08:42:09-08:00 Fix warnings, accept output * remove redundant imports (only brought to light due to recent work for improving redundant import detection) * fix a bug that was casuing exports to appear in reverse order * fix something in haddock-library that prevented compilation on old GHC's - - - - - a3852f8a by Zejun Wu at 2018-12-14T09:37:47-05:00 Output better debug infromation on internal error in extractDecl This will make investigation of haskell/haddock#979 easier - - - - - 2eccb5b9 by Alec Theriault at 2018-12-17T09:25:10-05:00 Refactor names + unused functions (#982) This commit should not introduce any change in functionality! * consistently use `getOccString` to convert `Name`s to strings * compare names directly when possible (instead of comparing strings) * get rid of unused utility functions - - - - - e82e4df8 by Alec Theriault at 2018-12-20T16:16:30-05:00 Load plugins when compiling each module (#983) * WIP: Load (typechecker) plugins from language pragmas * Revert "Load plugins when starting a GHC session (#905)" This reverts commit 72d82e52f2a6225686d9668790ac33c1d1743193. * Simplify plugin initialization code - - - - - 96e86f38 by Alec Theriault at 2018-12-23T10:23:20-05:00 Properly synify and render promoted type variables (#985) * Synify and render properly promoted type variables Fixes haskell/haddock#923. * Accept output - - - - - 23343345 by Alec Theriault at 2018-12-27T16:39:38-05:00 Remove `haddock-test`'s dep. on `syb` (#987) The functionality is easily inlined into one short function: `gmapEverywhere`. This doesn't warrant pulling in another package. - - - - - d0734f21 by Alec Theriault at 2018-12-27T16:39:52-05:00 Address deprecation warnings in `haddock-test` (#988) Fixes haskell/haddock#885. - - - - - 4d9f144e by mynguyen at 2018-12-30T23:42:26-05:00 Visible kind application haddock update - - - - - ffe0e9ed by Alec Theriault at 2019-01-07T13:55:22-08:00 Print kinded tyvars in constructors for Hoogle (#993) Fixes haskell/haddock#992 - - - - - 2e18b55d by Alec Theriault at 2019-01-10T16:42:45-08:00 Accept new output `GHC.Maybe` -> `Data.Maybe` (#996) Since 53874834b779ad0dfbcde6650069c37926da1b79 in GHC, "GHC.Maybe" is marked as `not-home`. That changes around some test output. - - - - - 055da666 by Gabor Greif at 2019-01-22T14:41:51+01:00 Lone typofix - - - - - 01bb71c9 by Alec Theriault at 2019-01-23T11:46:46-08:00 Keep forall on H98 existential data constructors (#1003) The information about whether or not there is a source-level `forall` is already available on a `ConDecl` (as `con_forall`), so we should use it instead of always assuming `False`! Fixes haskell/haddock#1002. - - - - - f9b9bc0e by Ryan Scott at 2019-01-27T09:28:12-08:00 Fix haskell/haddock#1004 with a pinch of dropForAlls - - - - - 5cfcdd0a by Alec Theriault at 2019-01-28T16:49:57-08:00 Loosen 'QuickCheck' and 'hspec' bounds It looks like the new versions don't cause any breakage and loosening the bounds helps deps fit in one stack resolver. - - - - - 3545d3dd by Alec Theriault at 2019-01-31T01:37:25-08:00 Use `.hie` files for the Hyperlinker backend (#977) # Summary This is a large architectural change to the Hyperlinker. * extract link (and now also type) information from `.hie` instead of doing ad-hoc SYB traversals of the `RenamedSource`. Also adds a superb type-on-hover feature (#715). * re-engineer the lexer to avoid needless string conversions. By going directly through GHC's `P` monad and taking bytestring slices, we avoid a ton of allocation and have better handling of position pragmas and CPP. In terms of performance, the Haddock side of things has gotten _much_ more efficient. Unfortunately, much of this is cancelled out by the increased GHC workload for generating `.hie` files. For the full set of boot libs (including `ghc`-the-library) * the sum of total time went down by 9-10% overall * the sum of total allocations went down by 6-7% # Motivation Haddock is moving towards working entirely over `.hi` and `.hie` files. This change means we no longer need the `RenamedSource` from `TypecheckedModule` (something which is _not_ in `.hi` files). # Details Along the way a bunch of things were fixed: * Cross package (and other) links are now more reliable (#496) * The lexer tries to recover from errors on every line (instead of at CPP boundaries) * `LINE`/`COLUMN` pragmas are taken into account * filter out zero length tokens before rendering * avoid recomputing the `ModuleName`-based `SrcMap` * remove the last use of `Documentation.Haddock.Utf8` (see haskell/haddock#998) * restructure temporary folder logic for `.hi`/`.hie` model - - - - - 2ded3359 by Herbert Valerio Riedel at 2019-02-02T12:06:12+01:00 Update/modernise haddock-library.cabal file - - - - - 62b93451 by Herbert Valerio Riedel at 2019-02-02T12:19:31+01:00 Tentatively declare support for unreleased base-4.13/ghc-8.8 - - - - - 6041e767 by Herbert Valerio Riedel at 2019-02-02T16:04:32+01:00 Normalise LICENSE text w/ cabal's BSD2 template Also, correct the `.cabal` files to advertise `BSD2` instead of the incorrect `BSD3` license. - - - - - 0b459d7f by Alec Theriault at 2019-02-02T18:06:12-08:00 CI: fetch GHC from validate artifact Should help make CI be less broken - - - - - 6b5c07cf by Alec Theriault at 2019-02-02T18:06:12-08:00 Fix some Hyperlinker test suite fallout * Amend `ParserSpec` to match new Hyperlinker API - pass in compiler info - strip out null tokens * Make `hypsrc-test` pass reliably - strip out `local-*` ids - strip out `line-*` ids from the `ClangCppBug` test - re-accept output - - - - - ded34791 by Nathan Collins at 2019-02-02T18:31:23-08:00 Update README instructions for Stack No need to `stack install` Haddock to test it. Indeed, `stack install` changes the `haddock` on user's `PATH` if `~/.local/bin` is on user's `PATH` which may not be desirable when hacking on Haddock. - - - - - 723298c9 by Alec Theriault at 2019-02-03T09:11:05-08:00 Remove `Documentation.Haddock.Utf8` The circumstances under which this module appeared are completely gone. The Hyperlinker backend no longer needs this module (it uses the more efficient `Encoding` module from `ghc`). Why no deprecation? Because this module really shouldn't exist! - It isn't used in `haddock-library`/`haddock-api` anymore - It was copy pasted directly from `utf8-string` - Folks seeking a boot-lib only solution can use `ghc`'s `Encoding` - - - - - 51050006 by Alec Theriault at 2019-02-03T22:58:58-08:00 Miscellaneous improvements to `Convert` (#1020) Now that Haddock is moving towards working entirely over `.hi` and `.hie` files, all declarations and types are going to be synthesized via the `Convert` module. In preparation for this change, here are a bunch of fixes to this module: * Add kind annotations to type variables in `forall`'s whose kind is not `Type`, unless the kind can be inferred from some later use of the variable. See `implicitForAll` and `noKindTyVars` in particular if you wish to dive into this. * Properly detect `HsQualTy` in `synifyType`. This is done by following suit with what GHC's `toIfaceTypeX` does and checking the first argument of `FunTy{} :: Type` to see if it classified as a given/wanted in the typechecker (see `isPredTy`). * Beef up the logic around figuring out when an explicit `forall` is needed. This includes: observing if any of the type variables will need kind signatures, if the inferred type variable order _without_ a forall will still match the one GHC claims, and some other small things. * Add some (not yet used) functionality for default levity polymorphic type signatures. This functionality similar to `fprint-explicit-runtime-reps`. Couple other smaller fixes only worth mentioning: * Show the family result signature only when it isn't `Type` * Fix rendering of implicit parameters in the LaTeX and Hoogle backends * Better handling of the return kind of polykinded H98 data declarations * Class decls produced by `tyThingToLHsDecl` now contain associated type defaults and default method signatures when appropriate * Filter out more `forall`'s in pattern synonyms - - - - - 841980c4 by Oleg Grenrus at 2019-02-04T08:44:25-08:00 Make a fixture of weird parsing of lists (#997) The second example is interesting. If there's a list directly after the header, and that list has deeper structure, the parser is confused: It finds two lists: - One with the first nested element, - everything after it I'm not trying to fix this, as I'm not even sure this is a bug, and not a feature. - - - - - 7315c0c8 by Ryan Scott at 2019-02-04T12:17:56-08:00 Fix haskell/haddock#1015 with dataConUserTyVars (#1022) The central trick in this patch is to use `dataConUserTyVars` instead of `univ_tvs ++ ex_tvs`, which displays the foralls in a GADT constructor in a way that's more faithful to how the user originally wrote it. Fixes haskell/haddock#1015. - - - - - ee0b49a3 by Ryan Scott at 2019-02-04T15:25:17-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. - - - - - 1c850dc8 by Alan Zimmerman at 2019-02-05T21:54:18+02:00 Matching changes in GHC for haskell/haddock#16236 - - - - - ab03c38e by Simon Marlow at 2019-02-06T08:07:33+00:00 Merge pull request haskell/haddock#1014 from hvr/pr/bsd2-normalise Normalise LICENSE text w/ cabal's BSD2 template - - - - - 5a92ccae by Alec Theriault at 2019-02-10T06:21:55-05:00 Merge remote-tracking branch 'gitlab/wip/T16236-2' into ghc-head - - - - - c0485a1d by Alec Theriault at 2019-02-10T03:32:52-08:00 Removes `haddock-test`s dependency on `xml`/`xhtml` (#1027) This means that `html-test`, `latex-test`, `hoogle-test`, and `hypsrc-test` now only depend on GHC boot libs. So we should now be able to build and run these as part of GHC's testsuite. \o/ The reference output has changed very slightly, in three ways: * we don't convert quotes back into `&quot;` as the `xml` lib did * we don't add extra `&nbsp;` as the `xml` lib did * we now remove the entire footer `div` (instead of just emptying it) - - - - - 65a448e3 by Alec Theriault at 2019-02-11T12:27:41-05:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - 360ca937 by Alec Theriault at 2019-02-13T11:36:11-05:00 Clean up logic for guessing `-B` and `--lib` (#1026) Haddock built with the `in-ghc-tree` flag tries harder to find the GHC lib folder and its own resources. This should make it possible to use `in-ghc-tree`-built Haddock without having to specify the `-B` and `--lib` options (just how you can use in-tree GHC without always specifying the `-B` option). The logic to do this relies on `getExecutablePath`, so we only get this auto-detection on platforms where this function works. - - - - - d583e364 by Alec Theriault at 2019-02-16T10:41:22-05:00 Fix tests broken by GHC Changes in 19626218566ea709b5f6f287d3c296b0c4021de2 affected some of the hyperlinker output. Accepted the new output (hovering over a `..` now shows you what that wildcard binds). Also fixed some stray deprecation warnings. - - - - - da0c42cc by Vladislav Zavialov at 2019-02-17T11:39:19+03:00 Parser changes to match !380 - - - - - ab96bed7 by Ryan Scott at 2019-02-18T04:44:08-05:00 Bump ghc version to 8.9 - - - - - 44b7c714 by Alec Theriault at 2019-02-22T05:49:43-08:00 Match GHC changes for T16185 `FunTy` now has an `AnonArgFlag` that indicates whether the arrow is a `t1 => t2` or `t1 -> t2`. This commit shouldn't change any functionality in Haddock. - - - - - 2ee653b1 by Alec Theriault at 2019-02-24T18:53:33-08:00 Update .travis.yml Points to the new GHC CI artifact. - - - - - 90939d71 by Alec Theriault at 2019-02-25T00:42:41-08:00 Support value/type namespaces on identifier links Identifier links can be prefixed with a 'v' or 't' to indicate the value or type namespace of the desired identifier. For example: -- | Some link to a value: v'Data.Functor.Identity' -- -- Some link to a type: t'Data.Functor.Identity' The default is still the type (with a warning about the ambiguity) - - - - - d6ed496c by Alec Theriault at 2019-02-25T00:42:46-08:00 Better identifier parsing * '(<|>)' and '`elem`' now get parsed and rendered properly as links * 'DbModule'/'DbUnitId' now properly get split apart into two links * tuple names now get parsed properly * some more small niceties... The identifier parsing code is more precise and more efficient (although to be fair: it is also longer and in its own module). On the rendering side, we need to pipe through information about backticks/parens/neither all the way through from renaming to the backends. In terms of impact: a total of 35 modules in the entirety of the bootlib + ghc lib docs change. The only "regression" is things like '\0'. These should be changed to @\\0@ (the path by which this previously worked seems accidental). - - - - - 3c3b404c by Alec Theriault at 2019-02-25T22:12:11-08:00 Fix standalone deriving docs Docs on standalone deriving decls for classes with associated types should be associated with the class instance, not the associated type instance. Fixes haskell/haddock#1033 - - - - - d51ef69e by Alec Theriault at 2019-02-26T19:14:59-08:00 Fix bogus identifier defaulting This avoids a situation in which an identifier would get defaulted to a completely different identifier. Prior to this commit, the 'Bug1035' test case would hyperlink 'Foo' into 'Bar'! Fixes haskell/haddock#1035. - - - - - 88cbbdc7 by Ryan Scott at 2019-02-27T10:14:03-05:00 Visible dependent quantification (#16326) changes - - - - - 0dcf6cee by Xia Li-yao at 2019-02-27T21:53:27-05:00 Menu item controlling which instances are expanded/collapsed (#1007) Adds a menu item (like "Quick Jump") for options related to displaying instances. This provides functionality for: * expanding/collapsing all instances on the currently opened page * controlling whether instances are expanded/collapsed by default * controlling whether the state of instances should be "remembered" This new functionality is implemented in Typescript in `details-helper`. The built-in-themes style switcher also got a revamp so that all three of QuickJump, the style switcher, and instance preferences now have the same style and implementation structure. See also: https://mail.haskell.org/pipermail/haskell-cafe/2019-January/130495.html Fixes haskell/haddock#698. Co-authored-by: Lysxia <lysxia at gmail.com> Co-authored-by: Nathan Collins <conathan at galois.com> - - - - - 3828c0fb by Alec Theriault at 2019-02-28T12:42:49-05:00 `--show-interface` should output to stdout. (#1040) Fixes haskell/haddock#864. - - - - - a50f4cda by gbaz at 2019-03-01T07:43:16-08:00 Increase contrast of Linuwal theme (#1037) This is to address the concern that, on less nice and older screens, some of the shades of grey blend in too easily with the white background. * darken the font slightly * darken slightly the grey behind type signatures and such * add a border and round the corners on code blocks * knock the font down by one point - - - - - ab4d41de by Alec Theriault at 2019-03-03T09:23:26-08:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 12f509eb by Ben Gamari at 2019-03-04T22:13:20-05:00 Remove reference to Opt_SplitObjs flag Split-objects has been removed. - - - - - 5b3e4c9a by Ryan Scott at 2019-03-06T19:16:24-05:00 Update html-test output to reflect haskell/haddock#16391 changes - - - - - fc228af1 by Alec Theriault at 2019-03-09T08:29:23-08:00 Match changes for "Stop inferring over-polymorphic kinds" The `hsq_ext` field of `HsQTvs` is now just the implicit variables (instead of also including information about which of these variables are dependent). This commit shouldn't change any functionality in Haddock. - - - - - 6ac109eb by Alec Theriault at 2019-03-09T11:22:55-08:00 Add .hi, .dyn_hi, etc files to .gitignore Fixes haskell/haddock#1030. - - - - - b55f0c05 by Alec Theriault at 2019-03-09T11:22:55-08:00 Better support for default methods in classes * default methods now get rendered differently * default associated types get rendered * fix a forgotten `s/TypeSig/ClassOpSig/` refactor in LaTeX backend * LaTeX backend now renders default method signatures NB: there is still no way to document default class members and the NB: LaTeX backend still crashes on associated types - - - - - 10aea0cf by Alec Theriault at 2019-03-09T11:22:55-08:00 Avoid multi-line `emph` in LaTeX backend `markupWarning` often processes inputs which span across paragraphs. Unfortunately, LaTeX's `emph` is not made to handle this (and will crash). Fixes haskell/haddock#936. - - - - - d22dc2c9 by Alec Theriault at 2019-03-09T11:22:55-08:00 Many LaTeX backend fixes After this commit, we can run with `--latex` on all boot libraries without crashing (although the generated LaTeX still fails to compile in a handful of larger packages like `ghc` and `base`). * Add newlines after all block elements in LaTeX. This is important to prevent the final output from being more an more indented. See the `latext-test/src/Example` test case for a sample of this. * Support associated types in class declarations (but not yet defaults) * Several small issues for producing compiling LaTeX; - avoid empy `\haddockbeginargs` lists (ex: `type family Any`) - properly escape identifiers depending on context (ex: `Int#`) - add `vbox` around `itemize`/`enumerate` (so they can be in tables) * Several spacing fixes: - limit the width of `Pretty`-arranged monospaced code - cut out extra space characters in export lists - only escape spaces if there are _multiple_ spaces - allow type signatures to be multiline (even without docs) * Remove uninteresting and repetitive `main.tex`/`haddock.sty` files from `latex-test` test reference output. Fixes haskell/haddock#935, haskell/haddock#929 (LaTeX docs for `text` build & compile) Fixes haskell/haddock#727, haskell/haddock#930 (I think both are really about type families...) - - - - - 0e6cee00 by Alec Theriault at 2019-03-29T12:11:56-07:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - ce05434d by Alan Zimmerman at 2019-03-29T12:12:11-07:00 Matching changes in GHC for haskell/haddock#16236 (cherry picked from commit 3ee6526d4ae7bf4deb7cd1caf24b3d7355573576) - - - - - d85766b2 by Ben Gamari at 2019-03-29T12:14:04-07:00 Bump GHC to 8.8 - - - - - 5a82cbaf by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Redo ParseModuleHeader - - - - - b9033348 by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - bb55c8f4 by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove outdated `.ghci` files and `scripts` The `.ghci` files are actively annoying when trying to `cabal v2-repl`. As for the `scripts`, the distribution workflow is completely different. - - - - - 5ee244dc by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove obsolete arcanist files + STYLE Now that GHC is hosted on Gitlab, the arcanist files don't make sense anymore. The STYLE file contains nothing more than a dead link too. - - - - - d07c1928 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Redo ParseModuleHeader - - - - - 492762d2 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - af2ac773 by Ryan Scott at 2019-05-14T17:22:13-04:00 Changes for haskell/haddock#16110/#16356 - - - - - 6820ed0d by Alec Theriault at 2019-05-17T08:51:27-07:00 Unbreak haskell/haddock#1004 test case `fail` is no longer part of `Monad`. - - - - - 6bf7be98 by Alec Theriault at 2019-05-17T08:51:27-07:00 Fix haskell/haddock#1063 with better parenthesization logic for contexts The only other change in html/hoogle/hyperlinker output for the boot libraries that this caused is a fix to some Hoogle output for implicit params. ``` $ diff -r _build/docs/ old_docs diff -r _build/docs/html/libraries/base/base.txt old_docs/html/libraries/base/base.txt 13296c13296 < assertError :: (?callStack :: CallStack) => Bool -> a -> a --- > assertError :: ?callStack :: CallStack => Bool -> a -> a ``` - - - - - b5716b61 by Ryan Scott at 2019-05-22T17:24:32-04:00 Match changes with haskell/haddock#14332 - - - - - c115abf6 by Alec Theriault at 2019-05-26T16:01:58-04:00 Remove Haddock's dependency on `Cabal` At this point, Haddock depended on Cabal-the-library solely for a verbosity parser (which misleadingly accepts all sorts of verbosity options that Haddock never uses). Now, the only dependency on Cabal is for `haddock-test` (which uses Cabal to locate the Haddock interface files of a couple boot libraries). - - - - - e5b2d4a3 by Alec Theriault at 2019-05-26T16:16:25-04:00 Regression test: promoted lists in associated types When possible, associated types with promoted lists should use the promoted list literal syntax (instead of repeated applications of ': and '[]). This was fixed in 2122de5473fd5b434af690ff9ccb1a2e58491f8c. Closes haskell/haddock#466, - - - - - cc5ad5d3 by Alec Theriault at 2019-05-26T17:55:54-04:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 4b3301a6 by Alec Theriault at 2019-05-26T17:57:52-04:00 Release haddock-2.23, haddock-library-1.8.0 Tentatively adjust bounds and changelogs for the release to be bundled with GHC 8.8.1. - - - - - 69c7cfce by Matthew Pickering at 2019-05-30T10:54:27+01:00 Update hyperlinker tests for new types in .hie files - - - - - 29b7e738 by Zubin Duggal at 2019-05-30T10:57:51+01:00 update for new way to store hiefile headers - - - - - aeca5d5f by Zubin Duggal at 2019-06-04T18:57:42-04:00 update for new way to store hiefile headers - - - - - ba2ca518 by Ben Gamari at 2019-06-07T23:11:14+00:00 Update test output for introduction of Safe-Inferred - - - - - 3a975a6c by Ryan Scott at 2019-07-03T12:06:27-04:00 Changes for haskell/haddock#15247 - - - - - 0df46555 by Zubin Duggal at 2019-07-22T10:52:50+01:00 Fix haddockHypsrcTest - - - - - 2688686b by Sylvain Henry at 2019-09-12T23:19:39+02:00 Fix for GHC module renaming - - - - - 9ec0f3fc by Alec Theriault at 2019-09-20T03:21:00-04:00 Fix Travis CI, loosen .cabal bounds (#1089) Tentatively for the 2.23 release: * updated Travis CI to work again * tweaked bounds in the `.cabal` files * adjusted `extra-source-files` to properly identify test files - - - - - ca559beb by Matthías Páll Gissurarson at 2019-09-28T12:14:40-04:00 Small change in to facilitate extended typed-holes (#1090) This change has no functional effect on haddock itself, it just changes one pattern to use `_ (` rather than `_(`, so that we may use `_(` as a token for extended typed-holes later. - - - - - 02e28976 by Vladislav Zavialov at 2019-09-28T12:17:45-04:00 Remove spaces around @-patterns (#1093) This is needed to compile `haddock` when [GHC Proposal haskell/haddock#229](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0229-whitespace-bang-patterns.rst) is implemented. - - - - - 83cbbf55 by Alexis King at 2019-09-30T21:12:42-04:00 Fix the ignore-exports option (#1082) The `ignore-exports` option has been broken since haskell/haddock#688, as mentioned in https://github.com/haskell/haddock/pull/766#issue-172505043. This PR fixes it. - - - - - e127e0ab by Ben Gamari at 2019-10-06T15:12:06-04:00 Fix a few haddock issues - - - - - 3a0f5c89 by Zubin Duggal at 2019-10-07T17:56:13-04:00 Fix crash when there are no srcspans in the file due to CPP - - - - - 339c5ff8 by Alec Theriault at 2019-10-07T17:56:13-04:00 Prefer un-hyperlinked sources to no sources It is possible to fail to extract an HIE ast. This is however not a reason to produce _no_ output - we should still make a colorized HTML page. - - - - - d47ef478 by Alec Theriault at 2019-10-07T17:56:13-04:00 Add a regression test for haskell/haddock#1091 Previously, this input would crash Haddock. - - - - - ed7c8b0f by Alec Theriault at 2019-10-07T20:56:48-04:00 Add Hyperlinker test cases for TH-related stuff Hopefully this will guard against regressions around quasiquotes, TH quotes, and TH splices. - - - - - d00436ab by Andreas Klebinger at 2019-10-21T15:53:03+02:00 Refactor for withTiming changes. - - - - - 4230e712 by Ben Gamari at 2019-10-22T09:36:37-04:00 Merge pull request haskell/haddock#1101 from AndreasPK/withTimingRefactor Refactor for withTiming changes. - - - - - d155c5f4 by Ryan Scott at 2019-10-23T10:37:17-04:00 Reify oversaturated data family instances correctly (#1103) This fixes haskell/haddock#1103 by adapting the corresponding patch for GHC (see https://gitlab.haskell.org/ghc/ghc/issues/17296 and https://gitlab.haskell.org/ghc/ghc/merge_requests/1877). - - - - - 331a5adf by Sebastian Graf at 2019-10-25T17:14:40+02:00 Refactor for OutputableBndrId changes - - - - - 48a490e0 by Ben Gamari at 2019-10-27T10:16:16-04:00 Merge pull request haskell/haddock#1105 from sgraf812/wip/flexible-outputable Refactor for OutputableBndrId changes - - - - - f62a7dfc by Sebastian Graf at 2019-11-01T11:54:16+00:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - d9b242ed by Ryan Scott at 2019-11-03T13:20:03-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. (cherry picked from commit cfd682c5fd03b099a3d78c44f9279faf56a0ac70) - - - - - dfd42406 by Sebastian Graf at 2019-11-04T07:02:14-05:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - 0b15be7c by Ben Gamari at 2019-11-09T13:21:33-05:00 Import isRuntimeRepVar from Type rather than TyCoRep isRuntimeRepVar is not longer exported from TyCoRep due to ghc#17441. - - - - - 091f7283 by Ben Gamari at 2019-11-10T12:47:06-05:00 Bump to GHC 8.10 - - - - - e88c71f2 by Ben Gamari at 2019-11-14T00:22:24-05:00 Merge pull request haskell/haddock#1110 from haskell/wip/T17441 Import isRuntimeRepVar from Type rather than TyCoRep - - - - - 4e0bbc17 by Ben Gamari at 2019-11-14T00:22:45-05:00 Version bumps for GHC 8.11 - - - - - 0e85ceb4 by Ben Gamari at 2019-11-15T11:59:45-05:00 Bump to GHC 8.10 - - - - - 00d6d68b by Ben Gamari at 2019-11-16T18:35:58-05:00 Bump ghc version to 8.11 - - - - - dde1fc3f by Ben Gamari at 2019-11-16T20:40:37-05:00 Drop support for base 4.13 - - - - - f52e331d by Vladislav Zavialov at 2019-11-24T13:02:28+03:00 Update Hyperlinker.Parser.classify to use ITdollar - - - - - 1ad96198 by Vladislav Zavialov at 2019-11-28T16:12:33+03:00 Remove HasSrcSpan (#17494) - - - - - 651afd70 by Herbert Valerio Riedel at 2019-12-08T12:08:16+01:00 Document error-prone conditional definition of instances This can easily trip up people if one isn't aware of it. Usually it's better to avoid this kind of conditionality especially for typeclasses for which there's an compat-package as conditional instances like these tend to fragment the ecosystem into those packages that go the extra mile to provide backward compat via those compat-packages and those that fail to do so. - - - - - b521af56 by Herbert Valerio Riedel at 2019-12-08T12:09:54+01:00 Fix build-failure regression for base < 4.7 The `$>` operator definition is available only since base-4.7 which unfortunately wasn't caught before release to Hackage (but has been fixed up by a metadata-revision) This commit introduces a `CompatPrelude` module which allows to reduce the amount of CPP by ousting it to a central location, i.e. the new `CompatPrelude` module. This pattern also tends to reduce the tricks needed to silence unused import warnings. Addresses haskell/haddock#1119 - - - - - 556c375d by Sylvain Henry at 2020-01-02T19:01:55+01:00 Fix after Iface modules renaming - - - - - bd6c53e5 by Sylvain Henry at 2020-01-07T00:48:48+01:00 hsyl20-modules-renamer - - - - - fb23713b by Ryan Scott at 2020-01-08T07:41:13-05:00 Changes for GHC#17608 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2372 - - - - - 4a4dd382 by Ryan Scott at 2020-01-25T08:08:26-05:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - e782a44d by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename PackageConfig into UnitInfo - - - - - ba3c9f05 by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename lookupPackage - - - - - ab37f9b3 by Ben Gamari at 2020-01-29T13:00:44-05:00 Merge pull request haskell/haddock#1125 from haskell/wip/T17566-take-two Changes for GHC#17566 - - - - - 3ebd5ae0 by Ryan Scott at 2020-01-31T05:56:50-05:00 Merge branch 'wip-hsyl20-package-refactor' into ghc-head - - - - - 602a747e by Richard Eisenberg at 2020-02-04T09:05:43+00:00 Echo GHC's removal of PlaceHolder module This goes with GHC's !2083. - - - - - ccfe5679 by Sylvain Henry at 2020-02-10T10:13:56+01:00 Module hierarchy: runtime (cf haskell/haddock#13009) - - - - - 554914ce by Cale Gibbard at 2020-02-10T16:10:39-05:00 Fix build of haddock in stage1 We have to use the correct version of the GHC API, but the version of the compiler itself doesn't matter. - - - - - 5b6fa2a7 by John Ericson at 2020-02-10T16:18:07-05:00 Noramlize `tested-with` fields in cabal files - - - - - e6eb3ebe by Vladislav Zavialov at 2020-02-16T13:25:26+03:00 No MonadFail/Alternative for P - - - - - 90e181f7 by Ben Gamari at 2020-02-18T14:13:47-05:00 Merge pull request haskell/haddock#1129 from obsidiansystems/wip/fix-stage1-build Fix build of haddock in stage1 - - - - - 93b64636 by Sylvain Henry at 2020-02-19T11:20:27+01:00 Modules: Driver (#13009) - - - - - da4f6c7b by Vladislav Zavialov at 2020-02-22T15:33:02+03:00 Use RealSrcSpan in InstMap - - - - - 479b1b50 by Ben Gamari at 2020-02-23T10:28:13-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 55ecacf0 by Sylvain Henry at 2020-02-25T15:18:27+01:00 Modules: Core (#13009) - - - - - 60867b3b by Vladislav Zavialov at 2020-02-28T15:53:52+03:00 Ignore the BufLoc/BufSpan added in GHC's !2516 - - - - - 1e5506d3 by Sylvain Henry at 2020-03-02T12:32:43+01:00 Modules: Core (#13009) - - - - - 6fb53177 by Richard Eisenberg at 2020-03-09T14:49:40+00:00 Changes in GHC's !1913. - - - - - 30b792ea by Ben Gamari at 2020-03-16T12:45:02-04:00 Merge pull request haskell/haddock#1130 from hsyl20/wip/hsyl20-modules-core2 Modules: Core (#13009) - - - - - cd761ffa by Sylvain Henry at 2020-03-18T15:24:00+01:00 Modules: Types - - - - - b6646486 by Ben Gamari at 2020-03-18T14:42:43-04:00 Merge pull request haskell/haddock#1133 from hsyl20/wip/hsyl20/modules/types Modules: Types - - - - - 9325d734 by Kleidukos at 2020-03-19T12:38:31-04:00 Replace the 'caption' class so that the collapsible sections are shown - - - - - 5e2bb555 by Kleidukos at 2020-03-19T12:38:31-04:00 Force ghc-8.8.3 - - - - - c6fcd0aa by Kleidukos at 2020-03-19T12:38:31-04:00 Update test fixtures - - - - - 5c849cb1 by Sylvain Henry at 2020-03-20T09:34:39+01:00 Modules: Types - - - - - 7f439155 by Alec Theriault at 2020-03-20T20:17:01-04:00 Merge branch 'ghc-8.8' into ghc-8.10 - - - - - b7904e5c by Alina Banerjee at 2020-03-20T20:24:17-04:00 Update parsing to strip whitespace from table cells (#1074) * Update parsing to strip leading & trailing whitespace from table cells * Update fixture data to disallow whitespaces at both ends in table cells * Add test case for whitespaces stripped from both ends of table cells * Update table reference test data for html tests - - - - - b9d60a59 by Alec Theriault at 2020-03-22T11:46:42-04:00 Clean up warnings * unused imports * imports of `Data.List` without import lists * missing `CompatPrelude` file in `.cabal` - - - - - 0c317dbe by Alec Theriault at 2020-03-22T18:46:54-04:00 Fix NPM security warnings This was done by calling `npm audit fix`. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. - - - - - 6e306242 by Alec Theriault at 2020-03-22T20:10:52-04:00 Tentative 2.24 release Adjusted changelogs and versions in `.cabal` files in preparation for the upcoming release bundled with GHC 8.10. - - - - - 1bfb4645 by Ben Gamari at 2020-03-23T16:40:54-04:00 Merge commit '3c2944c037263b426c4fe60a3424c27b852ea71c' into HEAD More changes from the GHC types module refactoring. - - - - - be8c6f3d by Alec Theriault at 2020-03-26T20:10:53-04:00 Update `.travis.yml` to work with GHC 8.10.1 * Regenerated the Travis file with `haskell-ci` * Beef up `.cabal` files with more `tested-with` information - - - - - b025a9c6 by Alec Theriault at 2020-03-26T20:10:53-04:00 Update README Removed some out of date links/info, added some more useful links. * badge to Hackage * update old trac link * `ghc-head` => `ghc-8.10` * `cabal new-*` is now `cabal v2-*` and it should Just Work * `--test-option='--accept'` is the way to accept testsuite output - - - - - 564d889a by Alec Theriault at 2020-03-27T20:34:33-04:00 Fix crash in `haddock-library` on unicode space Our quickcheck tests for `haddock-library` stumbled across an edge case input that was causing Haddock to crash: it was a unicode space character. The root cause of the crash is that we were implicitly assuming that if a space character was not " \t\f\v\r", it would have to be "\n". We fix this by instead defining horizontal space as: any space character that is not '\n'. Fixes haskell/haddock#1142 - - - - - 2d360ba1 by Alec Theriault at 2020-03-27T21:57:32-04:00 Disallow qualified uses of reserved identifiers This a GHC bug (https://gitlab.haskell.org/ghc/ghc/issues/14109) too, but it is a relatively easy fix in Haddock. Note that the fix must live in `haddock-api` instead of `haddock-library` because we can only really decide if an identifier is a reserved one by asking the GHC lexer. Fixes haskell/haddock#952 - - - - - 47ae22ed by Alec Theriault at 2020-03-28T13:36:25-04:00 Remove unused `Haddock.Utils` functions * removed functions in `Haddock.Utils` that were not used anywhere (or exported from the `haddock-api` package) * moved GHC-specific utils from `Haddock.Utils` to `Haddock.GhcUtils` - - - - - c0291245 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use TTG empty extensions to remove some `error`'s None of these error cases should ever have been reachable, so this is just a matter of leveraging the type system to assert this. * Use the `NoExtCon` and `noExtCon` to handle case matches for no extension constructors, instead of throwing an `error`. * Use the extension field of `HsSpliceTy` to ensure that this variant of `HsType` cannot exist in an `HsType DocNameI`. - - - - - 0aff8dc4 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use `unLoc`/`noLoc` from GHC instead of `unL`/`reL` * `unL` is already defined by GHC as `unLoc` * `reL` is already defined by GHC as `noLoc` (in a safer way too!) * Condense `setOutputDir` and add a about exporting from GHC Fixes haskell/haddock#978 - - - - - bf6f2fb7 by Alec Theriault at 2020-03-28T13:36:25-04:00 Cleanup up GHC flags in `.cabal` files * enable more useful warning flags in `haddock-api`, handle the new warnings generated * remove `-fwarn-tabs` (now we'd use `-Wtabs`, but this has been in `-Wall` for a while now) - - - - - c576fbf1 by Alec Theriault at 2020-03-28T13:36:25-04:00 `haddock-library` document header level Document the fact the header level is going to always be between 1 and 6 inclusive. Along the way, I also optimized the parsing code a bit. - - - - - 71bce0ee by Alec Theriault at 2020-03-28T14:26:27-04:00 Disallow links in section headers This is quite straightforward to implement, since we already had a function `docToHtmlNoAnchors` (which we used to generate the link in the sidebar "Contents"). This breaks test `Bug387`, but that test case has aged badly: we now automatically generate anchors for all headings, so manually adding an anchor in a section makes no sense. Nested anchors are, as pointed out in haskell/haddock#1054, disallowed by the HTML standard. Fixes haskell/haddock#1054 - - - - - b461b0ed by Sylvain Henry at 2020-03-30T10:34:23+02:00 Modules: type checker - - - - - cd8cd1ee by Ben Gamari at 2020-03-31T12:45:02-04:00 Merge pull request haskell/haddock#1152 from hsyl20/wip/hsyl20/modules/tc Module renaming - - - - - 5e8f8ea7 by Felix Yan at 2020-04-01T17:58:06-07:00 Allow QuickCheck 2.14 Builds fine and all tests pass. - - - - - dc6b1633 by Sylvain Henry at 2020-04-05T16:43:44+02:00 Module renaming: amend previous patch - - - - - eee2f4ae by Ryan Scott at 2020-04-05T09:04:43-07:00 Fix haskell/haddock#1050 by filtering out invisible AppTy arguments This makes the `synifyType` case for `AppTy` more intelligent by taking into consideration the visibilities of each `AppTy` argument and filtering out any invisible arguments, as they aren't intended to be displayed in the source code. (See haskell/haddock#1050 for an example of what can happen if you fail to filter these out.) Along the way, I noticed that a special `synifyType` case for `AppTy t1 (CoercionTy {})` could be consolidated with the case below it, so I took the opportunity to tidy this up. - - - - - 23eb99e8 by Ben Gamari at 2020-04-07T11:19:58-04:00 Merge pull request haskell/haddock#1154 from hsyl20/wip/hsyl20/modules/tc Module renaming: amend previous patch - - - - - 072d994d by Ryan Scott at 2020-04-07T19:32:47-04:00 Make NoExtCon fields strict These changes are a part of a fix for [GHC#17992](https://gitlab.haskell.org/ghc/ghc/issues/17992). - - - - - d8ebf6c8 by Ignat Insarov at 2020-04-09T21:15:01-04:00 Recode Doc to Json. (#1159) * Recode Doc to Json. * More descriptive field labels. - - - - - 52df4b4e by Sylvain Henry at 2020-04-10T12:39:18+02:00 Module renaming - - - - - d9ab8ec8 by Cale Gibbard at 2020-04-14T11:43:34-04:00 Add instance of XCollectPat for DocNameI - - - - - 323d221d by Cale Gibbard at 2020-04-14T11:43:34-04:00 Rename XCollectPat -> CollectPass - - - - - 2df80867 by Alec Theriault at 2020-04-15T07:30:51-07:00 Prune docstrings that are never rendered When first creating a Haddock interface, trim `ifaceDocMap` and `ifaceArgMap` to not include docstrings that can never appear in the final output. Besides checking with GHC which names are exported, we also need to keep all the docs attached to instance declarations (it is much tougher to detect when an instance is fully private). This change means: * slightly smaller interface files (7% reduction on boot libs) * slightly less work to do processing docstrings that aren't used * no warnings in Haddock's output about private docstrings (see haskell/haddock#1070) I've tested manually that this does not affect any of the boot library generated docs (the only change in output was some small re-ordering in a handful of instance lists). This should mean no docstrings have been incorrectly dropped. - - - - - f49c90cc by Alec Theriault at 2020-04-15T07:30:51-07:00 Don't warn about missing links in miminal sigs When renaming the Haddock interface, never emit warnings when renaming a minimal signature. Also added some documention around `renameInterface`. Minimal signatures intentionally include references to potentially un-exported methods (see the discussion in haskell/haddock#330), so it is expected that they will not always have a link destination. On the principle that warnings should always be resolvable, this shouldn't produce a warning. See haskell/haddock#1070. - - - - - a9eda64d by Ben Gamari at 2020-04-17T09:27:35-04:00 Merge pull request haskell/haddock#1160 from hsyl20/wip/hsyl20/modules/systools Module renaming - - - - - f40d7879 by Cale Gibbard at 2020-04-20T11:30:38-04:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ttg-con-pat - - - - - a50e7753 by Ben Gamari at 2020-04-20T11:36:10-04:00 Merge pull request haskell/haddock#1165 from obsidiansystems/wip/ttg-con-pat Trees that Grow refactor (GHC !2553) - - - - - 6a24795c by Alec Theriault at 2020-04-21T08:06:45-07:00 Fallback to `hiDecl` when `extractDecl` fails Sometimes, the declaration being exported is a subdecl (for instance, a record accessor getting exported at the top-level). For these cases, Haddock has to find a way to produce some synthetic sensible top-level declaration. This is done with `extractDecl`. As is shown by haskell/haddock#1067, this is sometimes impossible to do just at a syntactic level (for instance when the subdecl is re-exported). In these cases, the only sensible thing to do is to try to reify a declaration based on a GHC `TyThing` via `hiDecl`. - - - - - eee1a8b7 by Sylvain Henry at 2020-04-24T15:46:05+02:00 Module structure - - - - - 50b9259c by Iñaki at 2020-04-25T18:38:11-04:00 Add support for custom section anchors (#1179) This allows to have stable anchors for groups, even if the set of groups in the documentation is altered. The syntax for setting the anchor of a group is -- * Group name #desiredAnchor# Which will produce an html anchor of the form '#g:desiredAnchor' Co-authored-by: Iñaki García Etxebarria <git at inaki.blueleaf.cc> - - - - - 4003c97a by Ben Gamari at 2020-04-26T09:35:15-04:00 Merge pull request haskell/haddock#1166 from hsyl20/wip/hsyl20/modules/utils Module structure - - - - - 5206ab60 by Sylvain Henry at 2020-04-27T16:47:39+02:00 Renamed UnitInfo fields - - - - - c32c333b by Sylvain Henry at 2020-04-27T17:32:58+02:00 UnitId has been renamed into Unit - - - - - 3e87db64 by Sylvain Henry at 2020-04-27T17:36:00+02:00 Fix for GHC.Unit.* modules - - - - - ae3323a7 by Ben Gamari at 2020-04-29T12:36:37-04:00 Merge pull request haskell/haddock#1183 from hsyl20/wip/hsyl20/unitid Refactoring of Unit code - - - - - b105564a by Artem Pelenitsyn at 2020-05-03T08:14:10+01:00 add dependency on exceptions because GHC.Exception was boiled down (ghc haskell/haddock#18075) - - - - - 9857eff3 by Zubin Duggal at 2020-05-04T18:48:25+01:00 Atomic update of NameCache in readHieFile - - - - - 86bbb226 by Sylvain Henry at 2020-05-14T16:36:27+02:00 Fix after Config module renaming - - - - - a4bbdbc2 by Gert-Jan Bottu at 2020-05-15T22:09:44+02:00 Explicit Specificity Support for Haddock - - - - - 46199daf by Ben Gamari at 2020-05-19T09:59:56-04:00 Merge pull request haskell/haddock#1192 from hsyl20/hsyl20/modules-config Fix after Config module renaming - - - - - f9a9d2ba by Gert-Jan Bottu at 2020-05-20T16:48:38-04:00 Explicit Specificity Support for Haddock - - - - - 55c5b7ea by Ben Gamari at 2020-05-21T00:32:02-04:00 Merge commit 'a8d7e66da4dcc3b242103271875261604be42d6e' into ghc-head - - - - - a566557f by Cale Gibbard at 2020-05-21T16:02:06-04:00 isBootSummary now produces a result of type IsBootInterface - - - - - ea52f905 by Zubin Duggal at 2020-05-24T17:55:48+01:00 update for hiefile-typeclass-info - - - - - 49ba7a67 by Willem Van Onsem at 2020-05-25T12:23:01-04:00 Use floor over round to calculate the percentage (#1195) If we compile documentation where only a small fraction is undocumented, it is misleading to see 100% coverage - 99% is more intuitive. Fixes haskell/haddock#1194 - - - - - c025ebf1 by Ben Gamari at 2020-05-29T14:32:42-04:00 Merge pull request haskell/haddock#1185 from obsidiansystems/boot-disambig isBootSummary now produces a result of type IsBootInterface - - - - - 74ab9415 by Ben Gamari at 2020-05-29T20:23:39-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - b40be944 by Ben Gamari at 2020-06-03T17:02:31-04:00 testsuite: Update expected output for simplified subsumption - - - - - 624be71c by Ryan Scott at 2020-06-05T12:43:23-04:00 Changes for GHC#18191 See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3337. - - - - - fbd8f7ce by Sylvain Henry at 2020-06-08T15:31:47+02:00 Fix after unit refactoring - - - - - 743fda4d by Ben Gamari at 2020-06-09T12:09:58-04:00 Merge pull request haskell/haddock#1202 from hsyl20/wip/hsyl20/unitid-ii Fix after unit refactoring - - - - - d07a06a9 by Ryan Scott at 2020-06-13T07:16:55-04:00 Use HsForAllTelescope (GHC#18235) - - - - - 389bb60d by Ben Gamari at 2020-06-13T15:30:52-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - 7a377f5f by Ben Gamari at 2020-06-17T14:53:16-04:00 Merge pull request haskell/haddock#1199 from bgamari/wip/ghc-8.12 haddock: Bounds bumps for GHC 8.12 - - - - - 9fd9e586 by Krzysztof Gogolewski at 2020-06-17T16:09:07-04:00 Adapt Haddock to LinearTypes See ghc/ghc!852. - - - - - 46fe7636 by Ben Gamari at 2020-06-18T14:20:02-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 35a3c9e2 by Zubin Duggal at 2020-06-21T21:19:18+05:30 Use functions exported from HsToCore - - - - - 8abe3928 by Ben Gamari at 2020-06-24T13:53:39-04:00 Merge pull request haskell/haddock#1204 from wz1000/wip/haddock-hstocore Use functions exported from GHC.HsToCore.Docs - - - - - 22f2c937 by Matthías Páll Gissurarson at 2020-06-26T19:07:03+02:00 Adapt Haddock for QualifiedDo - - - - - 3f6208d7 by Vladislav Zavialov at 2020-06-28T14:28:16+03:00 Handle LexicalNegation's ITprefixminus - - - - - 03a19f41 by Sylvain Henry at 2020-07-02T09:37:38+02:00 Rename hsctarget into backend - - - - - ea17ff23 by Andreas Klebinger at 2020-07-02T17:44:18+02:00 Update for UniqFM changes. - - - - - 9872f2f3 by Ben Gamari at 2020-07-09T10:39:19-04:00 Merge pull request haskell/haddock#1209 from AndreasPK/wip/typed_uniqfm Update for UniqFM changes. - - - - - 68f7b668 by Krzysztof Gogolewski at 2020-07-12T18:16:57+02:00 Sync with GHC removing {-# CORE #-} pragma See ghc ticket haskell/haddock#18048 - - - - - eb372681 by Sylvain Henry at 2020-07-20T11:41:30+02:00 Rename hscTarget into backend - - - - - fb7f78bf by Ben Gamari at 2020-07-21T12:15:25-04:00 Merge pull request haskell/haddock#1214 from hsyl20/wip/hsyl20/hadrian/ncg Rename hscTarget into backend - - - - - 1e8f5b56 by Ben Gamari at 2020-07-23T09:11:50-04:00 Merge commit '904dce0cafe0a241dd3ef355775db47fc12f434d' into ghc-head - - - - - d8fd1775 by Zubin Duggal at 2020-07-23T18:46:40+05:30 Update for modular ping pong - - - - - 8416f872 by Ben Gamari at 2020-07-23T09:35:03-04:00 Merge pull request haskell/haddock#1200 from wz1000/wip/wz1000-modular-ping-pong Modular ping pong - - - - - a24a8577 by Ben Gamari at 2020-07-28T15:23:36-04:00 Bump GHC version to 9.0 - - - - - 6a51c9dd by Sylvain Henry at 2020-08-05T18:47:05+02:00 Fix after Outputable refactoring - - - - - c05e1c99 by Ben Gamari at 2020-08-10T14:41:41-04:00 Merge pull request haskell/haddock#1223 from hsyl20/wip/hsyl20/dynflags/exception Fix after Outputable refactoring - - - - - d964f15b by Sylvain Henry at 2020-08-12T11:58:49+02:00 Fix after HomeUnit - - - - - 8e6d5b23 by Ben Gamari at 2020-08-12T14:25:30-04:00 Merge pull request haskell/haddock#1225 from hsyl20/wip/hsyl20/plugins/homeunit Fix after HomeUnit - - - - - 8c7880fe by Sylvain Henry at 2020-08-17T14:13:29+02:00 Remove Ord FastString instance - - - - - 8ea410db by Alex Biehl at 2020-08-19T10:56:32+02:00 Another round of `npm audit fix` (#1228) This should shut down the warnings on Github. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. Last NPM dependency audit happend in d576b2327e2bc117f912fe0a9d595e9ae62614e0 Co-authored-by: Alex Biehl <alex.biehl at target.com> - - - - - 7af6e2a8 by Ben Gamari at 2020-08-31T13:59:34-04:00 Merge pull request haskell/haddock#1226 from hsyl20/wip/hsyl20/fs_ord Remove Ord FastString instance - - - - - ffbc8702 by Alan Zimmerman at 2020-09-07T21:47:41+01:00 Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - a93f1268 by Alan Zimmerman at 2020-09-07T23:11:38+01:00 Merge pull request haskell/haddock#1232 from haskell/wip/T18639-remove-generated-pragma, Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - 1f605d50 by Ben Gamari at 2020-09-14T18:30:01-04:00 Bump GHC version to 9.1 - - - - - 6599df62 by Vladislav Zavialov at 2020-09-18T14:05:15+03:00 Bump base upper bound to 4.16 - - - - - a01b3c43 by Ben Gamari at 2020-09-22T15:41:48-04:00 Update hypsrc-test for QuickLook This appears to be a spurious change. - - - - - e9cc6cac by Vladislav Zavialov at 2020-09-26T21:00:12+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 30e3ca7c by Sylvain Henry at 2020-09-29T11:18:32-04:00 Update for parser (#1234) - - - - - b172f3e3 by Vladislav Zavialov at 2020-09-30T01:01:30+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 0b9c08d3 by Sylvain Henry at 2020-09-30T11:02:33+02:00 Adapt to GHC parser changes - - - - - b9540b7a by Sylvain Henry at 2020-10-12T09:13:38-04:00 Don't pass the HomeUnitId (#1239) - - - - - 34762e80 by HaskellMouse at 2020-10-13T12:58:04+03:00 Changed tests due to unification of `Nat` and `Natural` in the follwing merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3583 - - - - - 256f86b6 by Vladislav Zavialov at 2020-10-15T10:48:03+03:00 Add whitespace in: map ($ v) - - - - - 4a3f711b by Alan Zimmerman at 2020-10-19T08:57:27+01:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled - - - - - 072cdd21 by Alan Zimmerman at 2020-10-21T14:48:28-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 9e09a445 by Alan Zimmerman at 2020-10-21T23:53:34-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 636d7de3 by Sylvain Henry at 2020-10-26T14:31:54-04:00 GHC.Driver.Types refactoring (#1242) - - - - - a597f000 by Ryan Scott at 2020-10-29T04:18:05-04:00 Adapt to the removal of Hs{Boxed,Constraint}Tuple See ghc/ghc!4097 and GHC#18723. - - - - - b96660fb by Ryan Scott at 2020-10-30T04:53:05-04:00 Adapt to HsConDecl{H98,GADT}Details split Needed for GHC#18844. - - - - - c287d82c by Ryan Scott at 2020-10-30T19:35:59-04:00 Adapt to HsOuterTyVarBndrs These changes accompany ghc/ghc!4107, which aims to be a fix for haskell/haddock#16762. - - - - - a34c31a1 by Ryan Scott at 2020-11-13T13:38:34-05:00 Adapt to splitPiTysInvisible being renamed to splitInvisPiTys This is a part of !4434, a fix for GHC#18939. - - - - - 66ea459d by Sylvain Henry at 2020-11-16T10:59:30+01:00 Fix after Plugins moved into HscEnv - - - - - 508556d8 by Ben Gamari at 2020-11-18T15:47:40-05:00 Merge pull request haskell/haddock#1253 from hsyl20/wip/hsyl20/plugins/hscenv Fix after Plugins moved into HscEnv - - - - - 620fec1a by Andreas Klebinger at 2020-11-24T20:51:59+01:00 Update for changes in GHC's Pretty - - - - - 01cc13ab by Richard Eisenberg at 2020-11-25T23:18:35-05:00 Avoid GHC#18932. - - - - - 8d29ba21 by Cale Gibbard at 2020-11-25T23:18:35-05:00 Add type arguments to PrefixCon - - - - - 414d5f87 by Sylvain Henry at 2020-11-30T17:06:04+01:00 DynFlags's unit fields moved to HscEnv - - - - - e356668c by Ben Gamari at 2020-11-30T11:11:37-05:00 Merge pull request haskell/haddock#1258 from hsyl20/wip/hsyl20/hscenv/unitstate Unit fields moved from DynFlags to HscEnv - - - - - 7cf552f1 by Ben Gamari at 2020-12-03T10:31:27-05:00 Merge pull request haskell/haddock#1257 from AndreasPK/wip/andreask/opt_dumps Update for changes in GHC's Pretty - - - - - fc0871c3 by Veronika Romashkina at 2020-12-08T16:35:33+01:00 Fix docs links from Darcs to GitHub in intro (#1262) - - - - - 7059e808 by Veronika Romashkina at 2020-12-08T16:36:16+01:00 Use gender neutral word in docs (#1260) - - - - - 1b16e5ee by Maximilian Tagher at 2020-12-08T16:40:03+01:00 Allow scrolling search results (#1235) Closes https://github.com/haskell/haddock/issues/1231 - - - - - 8a118c01 by dependabot[bot] at 2020-12-08T16:40:25+01:00 Bump bl from 1.2.2 to 1.2.3 in /haddock-api/resources/html (#1255) Bumps [bl](https://github.com/rvagg/bl) from 1.2.2 to 1.2.3. - [Release notes](https://github.com/rvagg/bl/releases) - [Commits](https://github.com/rvagg/bl/compare/v1.2.2...v1.2.3) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - c89ff587 by Xia Li-yao at 2020-12-08T16:42:17+01:00 Allow more characters in anchor following module reference (#1220) - - - - - 14af7d64 by Xia Li-yao at 2020-12-08T16:43:05+01:00 Add dangling changes from branches ghc-8.6 and ghc-8.8 (#1243) * Fix multiple typos and inconsistencies in doc/markup.rst Note: I noticed some overlap with haskell/haddock#1112 from @wygulmage and haskell/haddock#1081 from @parsonsmatt after creating these proposed changes - mea culpa for not looking at the open PRs sooner. * Fix haskell/haddock#1113 If no Signatures, no section of index.html * Change the formatting of missing link destinations The current formatting of the missing link destination does not really help user to understand the reasons of the missing link. To address this, I've changed the formatting in two ways: - the missing link symbol name is now fully qualified. This way you immediately know which haskell module cannot be linked. It is then easier to understand why this module does not have documentation (hidden module or broken documentation). - one line per missing link, that's more readable now that symbol name can be longer due to qualification. For example, before haddock was listing missing symbol such as: ``` could not find link destinations for: Word8 Word16 mapMaybe ``` Now it is listed as: ``` could not find link destinations for: - Data.Word.Word8 - Data.Word.Word16 - Data.Maybe.mapMaybe ``` * Add `--ignore-link-symbol` command line argument This argument can be used multiples time. A missing link to a symbol listed by `--ignore-link-symbol` won't trigger "missing link" warning. * Forbid spaces in anchors (#1148) * Improve error messages with context information (#1060) Co-authored-by: Matt Audesse <matt at mattaudesse.com> Co-authored-by: Mike Pilgrem <mpilgrem at users.noreply.github.com> Co-authored-by: Guillaume Bouchard <guillaume.bouchard at tweag.io> Co-authored-by: Pepe Iborra <pepeiborra at gmail.com> - - - - - 89e3af13 by tomjaguarpaw at 2020-12-08T18:00:04+01:00 Enable two warnings (#1245) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - c3320f8d by Willem Van Onsem at 2020-12-08T18:26:55+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 685df308 by Alex Biehl at 2020-12-08T20:06:26+01:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - be3ec3c0 by Alex Biehl at 2020-12-08T20:06:26+01:00 Import intercalate - - - - - 32c33912 by Matthías Páll Gissurarson at 2020-12-08T21:15:30+01:00 Adapt Haddock for QualifiedDo - - - - - 31696088 by Alex Biehl at 2020-12-08T22:06:02+01:00 Fix haddock-library tests - - - - - fbc0998a by Alex Biehl at 2020-12-08T23:08:23+01:00 Move to GitHub CI (#1266) * Initial version of ci.yml This is a straight copy from Dmitrii Kovanikov's blog post at https://kodimensional.dev/github-actions. Will adapt to haddock in successive commits. * Delete .travis.yml * Modify to only test on ghc-8.10.{1,2} * Use actions/setup-haskell at v1.1.4 * Relax QuickCheck bound on haddock-api * Remove stack matrix for now * Nail down to ghc-8.10 branch for now * Pin index state to 2020-12-08T20:13:44Z for now * Disable macOS and Windows tests for now for speed up - - - - - 5b946b9a by tomjaguarpaw at 2020-12-10T19:01:41+01:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - bc5a408f by dependabot[bot] at 2020-12-10T19:02:16+01:00 Bump ini from 1.3.5 to 1.3.7 in /haddock-api/resources/html (#1269) Bumps [ini](https://github.com/isaacs/ini) from 1.3.5 to 1.3.7. - [Release notes](https://github.com/isaacs/ini/releases) - [Commits](https://github.com/isaacs/ini/compare/v1.3.5...v1.3.7) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - d02995f1 by Andrew Martin at 2020-12-14T16:48:40-05:00 Update for boxed rep - - - - - a381aeff by Ben Gamari at 2020-12-15T15:13:30-05:00 Revert "Enable two warnings (#1245) (#1268)" As this does not build on GHC `master`. This reverts commit 7936692badfe38f23ae95b51fb7bd7c2ff7e9bce. - - - - - a63c0a9e by Ben Gamari at 2020-12-15T15:17:59-05:00 Revert "Update for boxed rep" This reverts commit 4ffb30d8b637ccebecc81ce610f0af451ac8088d. - - - - - 53bfbb29 by Ben Gamari at 2020-12-15T15:37:24-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - bae76a30 by Ben Gamari at 2020-12-16T02:44:42+00:00 Update output for nullary TyConApp optimisation (ghc/ghc!2952) - - - - - 4b733b57 by Krzysztof Gogolewski at 2020-12-16T20:03:14+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. - - - - - ee463bd3 by Ryan Scott at 2020-12-16T16:55:23-05:00 Adapt to HsCoreTy (formerly NewHsTypeX) becoming a type synonym Needed for !4417, the fix for GHC#15706 and GHC#18914. - - - - - ed0b02f8 by tomjaguarpaw at 2020-12-19T10:17:19+00:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - d80bf8f5 by Sylvain Henry at 2020-12-21T10:09:25+01:00 Fix after binder collect changes - - - - - bf4c9d32 by Adam Gundry at 2020-12-23T21:35:01+00:00 Adapt to changes to GlobalRdrElt and AvailInfo Needed for ghc/ghc!4467 - - - - - 37736c4c by John Ericson at 2020-12-28T12:27:02-05:00 Support a new ghc --make node type for parallel backpack upsweep - - - - - 717bdeac by Vladislav Zavialov at 2020-12-29T10:50:02+03:00 Inline and fix getGADTConTypeG The getGADTConTypeG used HsRecTy, which is at odds with GHC issue haskell/haddock#18782. I noticed that getGADTConTypeG was only used in the Hoogle backend. Interestingly, when handling H98 constructors, Hoogle converts RecCon to PrefixCon (see Haddock.Backends.Hoogle.ppCtor). So I changed getGADTConTypeG to handle RecConGADT in the same manner as PrefixConGADT, and after this simplification moved it into the 'where' clause of ppCtor, to the only place where it is used. The practical effect of this change is as follows. Consider this example: data TestH98 = T98 { bar::Int } data TestGADT where TG :: { foo :: Int } -> TestGADT Before this patch, haddock --hoogle used to produce: T98 :: Int -> TestH98 [TG] :: {foo :: Int} -> TestGADT Notice how the record syntax was discarded in T98 but not TG. With this patch, we always produce signatures without record syntax: T98 :: Int -> TestH98 [TG] :: Int -> TestGADT I suspect this might also be a bugfix, as currently Hoogle doesn't seem to render GADT record constructors properly. - - - - - cb1b8c56 by Andreas Abel at 2020-12-30T21:12:37+01:00 Build instructions: haddock-library and -api first! - - - - - b947f6ad by Ben Gamari at 2020-12-31T13:04:19-05:00 Merge pull request haskell/haddock#1281 from obsidiansystems/wip/backpack-j Changes to support -j with backpack - - - - - 120e1cfd by Hécate Moonlight at 2021-01-04T19:54:58+01:00 Merge pull request haskell/haddock#1282 from andreasabel/master Build instructions: haddock-library and -api first! - - - - - fd45e41a by Ben Gamari at 2021-01-05T16:14:31-05:00 Merge remote-tracking branch 'origin/ghc-8.10' into ghc-9.0 - - - - - b471bdec by Ben Gamari at 2021-01-05T16:23:02-05:00 Merge commit '1e56f63c3197e7ca1c1e506e083c2bad25d08793' into ghc-9.0 - - - - - 81cdbc41 by Alex Biehl at 2021-01-09T12:14:41+01:00 Prepare Haddock for being a GHC Plugin - - - - - b646d952 by Alex Biehl at 2021-01-09T12:14:41+01:00 Make Haddock a GHC Plugin - - - - - cc044674 by Alex Biehl at 2021-01-09T12:14:41+01:00 Add -j[n] CLI param to Haddock executable It translates to `--ghcopt=-j[n]` - - - - - 84a04073 by Alex Biehl at 2021-01-09T12:14:41+01:00 Abstract Monad for interface creation I found that when running as a plugin the lookupName function (which runs in Ghc monad) does not work correctly from the typeCheckResultAction hook. Instead, we abstracted the monad used when creating interfaces, so that access to GHC session specific parts is explicit and so that the TcM can provide their (correct) implementation of lookupName. - - - - - 5be2c4f7 by Alex Biehl at 2021-01-09T12:14:41+01:00 Accept tests - - - - - 8cefee9d by Alex Biehl at 2021-01-09T16:10:47+01:00 Add missing dependency for mtl - - - - - 3681f919 by Ben Gamari at 2021-01-13T18:39:25-05:00 Merge remote-tracking branch 'origin/ghc-9.0' into ghc-head - - - - - 33c6b152 by Hécate Moonlight at 2021-01-14T16:04:20+01:00 Merge pull request haskell/haddock#1273 from hsyl20/wip/hsyl20/arrows Fix after binder collect changes - - - - - 70d13e8e by Joachim Breitner at 2021-01-22T19:03:45+01:00 Make haddock more robust to changes to the `Language` data type With the introduction of GHC2021, the `Languages` data type in GHC will grow. In preparation of that (and to avoid changing haddock with each new language), this change makes the code handle extensions to that data type gracefully. (cherry picked from commit c341dd7c9c3fc5ebc83a2d577c5a726f3eb152a5) - - - - - 7d6dd57a by John Ericson at 2021-01-22T22:02:02+00:00 Add `NoGhcTc` instance now that it's not closed - - - - - e5fdaf0a by Alan Zimmerman at 2021-01-23T22:57:44+00:00 Merge pull request haskell/haddock#1293 from obsidiansystems/wip/fix-18936 Add `NoGhcTc` instance now that it's not closed - - - - - 989a1e05 by Oleg Grenrus at 2021-01-24T16:11:46+03:00 Add import list to Data.List - - - - - 368e144a by Ben Gamari at 2021-01-28T22:15:48+01:00 Adapt to "Make PatSyn immutable" - - - - - abe66c21 by Alfredo Di Napoli at 2021-02-01T08:05:35+01:00 Rename pprLogErrMsg to new name - - - - - e600e75c by Hécate Moonlight at 2021-02-05T14:53:00+01:00 Move CI to ghc-9.0 - - - - - dd492961 by Vladislav Zavialov at 2021-02-05T14:53:00+01:00 Update cabal.project and README build instructions - - - - - 31bd292a by Hécate Moonlight at 2021-02-05T15:03:56+01:00 Merge pull request haskell/haddock#1296 from Kleidukos/ghc-9.0 Merge the late additions to ghc-8.10 into ghc-9.0 - - - - - 6388989e by Vladislav Zavialov at 2021-02-05T17:41:57+03:00 Cleanup: fix build warnings - - - - - f99407ef by Daniel Rogozin at 2021-02-05T18:11:48+03:00 type level characters support for haddock (required for haskell/haddock#11342) - - - - - d8c6b26f by Hécate Moonlight at 2021-02-05T17:44:50+01:00 Add a CONTRIBUTING.md file - - - - - 6a01ad98 by Hécate Moonlight at 2021-02-05T17:58:16+01:00 Merge pull request haskell/haddock#1312 from Kleidukos/proper-branch-etiquette Add a CONTRIBUTING.md file - - - - - 955eecc4 by Vladislav Zavialov at 2021-02-05T20:29:00+03:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into ghc-head - - - - - 47b3d6ab by Hécate Moonlight at 2021-02-05T19:09:38+01:00 Amend the CONTRIBUTING.md file - - - - - 23de6137 by Hécate Moonlight at 2021-02-05T19:16:49+01:00 Merge pull request haskell/haddock#1313 from Kleidukos/amend-contributing Amend the CONTRIBUTING.md file - - - - - 69026b59 by Krzysztof Gogolewski at 2021-02-05T23:05:56+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. (cherry picked from commit b4b4d896d2d68d6c48e7db7bfe95c185ca0709cb) - - - - - ea026b78 by Oleg Grenrus at 2021-02-06T17:14:45+01:00 Add import list to Data.List - - - - - 5204326f by Hécate Moonlight at 2021-02-06T17:15:44+01:00 Merge pull request haskell/haddock#1316 from Kleidukos/explicit-imports-to-data-list Add import list to Data.List - - - - - 1f4d2136 by Ben Gamari at 2021-02-06T11:53:31-05:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ghc-head-merge - - - - - 13f0d09a by Ben Gamari at 2021-02-06T11:53:45-05:00 Fix partial record selector warning - - - - - 5c115f7e by Ben Gamari at 2021-02-06T11:55:52-05:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into wip/ghc-head-merge - - - - - b6fd8b75 by Ben Gamari at 2021-02-06T12:01:31-05:00 Merge commit '41964cb2fd54b5a10f8c0f28147015b7d5ad2c02' into wip/ghc-head-merge - - - - - a967194c by Ben Gamari at 2021-02-06T18:30:35-05:00 Merge branch 'wip/ghc-head-merge' into ghc-head - - - - - 1f4c3a91 by MorrowM at 2021-02-07T01:52:33+02:00 Fix search div not scrolling - - - - - 684b1287 by Iñaki García Etxebarria at 2021-02-07T16:13:04+01:00 Add support for labeled module references Support a markdown-style way of annotating module references. For instance -- | [label]("Module.Name#anchor") will create a link that points to the same place as the module reference "Module.Name#anchor" but the text displayed on the link will be "label". - - - - - bdb55a5d by Hécate Moonlight at 2021-02-07T16:18:10+01:00 Merge pull request haskell/haddock#1319 from alexbiehl/alex/compat Backward compat: Add support for labeled module references - - - - - 6ca70991 by Hécate Moonlight at 2021-02-07T16:21:29+01:00 Merge pull request haskell/haddock#1314 from tweag/show-linear-backport Backport haskell/haddock#1238 (linear types) to ghc-9.0 - - - - - d9d73298 by Alex Biehl at 2021-02-07T17:46:25+01:00 Remove dubious parseModLink Instead construct the ModLink value directly when parsing. - - - - - 33b4d020 by Hécate Moonlight at 2021-02-07T17:52:05+01:00 Merge pull request haskell/haddock#1320 from haskell/alex/fix Remove dubious parseModLink - - - - - 54211316 by Hécate Moonlight at 2021-02-07T18:12:07+01:00 Merge pull request haskell/haddock#1318 from MorrowM/ghc-9.0 Fix search div not scrolling - - - - - 19db679e by alexbiehl-gc at 2021-02-07T18:14:46+01:00 Merge pull request haskell/haddock#1317 from bgamari/wip/ghc-head-merge Merge ghc-8.10 into ghc-head - - - - - 6bc1e9e4 by Willem Van Onsem at 2021-02-07T18:25:30+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - c8537cf8 by alexbiehl-gc at 2021-02-07T18:30:40+01:00 Merge pull request haskell/haddock#1322 from haskell/alex/forward-port simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 2d47ae4e by alexbiehl-gc at 2021-02-07T18:39:59+01:00 Merge branch 'ghc-head' into ghc-9.0 - - - - - 849e4733 by Hécate Moonlight at 2021-02-07T18:43:19+01:00 Merge pull request haskell/haddock#1321 from Kleidukos/ghc-9.0 Merge ghc-9.0 into ghc-head - - - - - ee6095d7 by Sylvain Henry at 2021-02-08T11:36:38+01:00 Update for Logger - - - - - 4ad688c9 by Alex Biehl at 2021-02-08T18:11:24+01:00 Merge pull request haskell/haddock#1310 from hsyl20/wip/hsyl20/logger2 Logger refactoring - - - - - 922a9e0e by Ben Gamari at 2021-02-08T12:54:33-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - 991649d2 by Sylvain Henry at 2021-02-09T10:55:17+01:00 Fix to build with HEAD - - - - - a8348dc2 by Hécate Moonlight at 2021-02-09T10:58:51+01:00 Merge pull request haskell/haddock#1327 from hsyl20/wip/hsyl20/logger2 Fix to build with HEAD - - - - - 0abdbca6 by Fendor at 2021-02-09T20:06:15+01:00 Add UnitId to Target record - - - - - d5790a0e by Alex Biehl at 2021-02-11T10:32:32+01:00 Stable sort for (data/newtype) instances - - - - - 8e6036f5 by Alex Biehl at 2021-02-11T10:32:32+01:00 Also make TyLit deterministic - - - - - f76d2945 by Hécate Moonlight at 2021-02-11T11:00:31+01:00 Merge pull request haskell/haddock#1329 from hsyl20/hsyl20/stabe_iface Stable sort for instances - - - - - 5e0469ea by Oleg Grenrus at 2021-02-14T15:28:15+02:00 Add import list to Data.List in Haddock.Interface.Create - - - - - fa57cd24 by Hécate Moonlight at 2021-02-14T17:19:27+01:00 Merge pull request haskell/haddock#1331 from phadej/more-explicit-data-list-imports Add import list to Data.List in Haddock.Interface.Create - - - - - f0cd629c by Hécate Moonlight at 2021-02-21T00:22:01+01:00 Merge pull request haskell/haddock#1311 from fendor/wip/add-targetUnitId-to-target Add UnitId to Target record - - - - - 674ef723 by Joachim Breitner at 2021-02-22T10:39:18+01:00 html-test: Always set language from ghc-9.2 on, the “default” langauge of GHC is expected to change more wildly. To prepare for that (and unblock https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4853), this sets the language for all the test files to `Haskell2010`. This should insolate this test suite against changes to the default. Cherry-picked from https://github.com/haskell/haddock/pull/1341 - - - - - f072d623 by Hécate Moonlight at 2021-02-22T10:56:51+01:00 Merge pull request haskell/haddock#1342 from nomeata/joachim/haskell2010-in-tests-ghc-head html-test: Always set language - - - - - caebbfca by Hécate Moonlight at 2021-02-22T11:53:07+01:00 Clean-up of Interface and Interface.Create's imports and pragmata - - - - - f6caa89d by Hécate Moonlight at 2021-02-22T11:54:58+01:00 Merge pull request haskell/haddock#1345 from Kleidukos/head/fix-interface-imports [ghc-head] Clean-up of Interface and Interface.Create's imports and pragmata - - - - - 7395c9cb by Hécate Moonlight at 2021-02-22T18:44:57+01:00 Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 6e9fb5d5 by Hécate Moonlight at 2021-02-22T18:45:28+01:00 Merge pull request haskell/haddock#1348 from Kleidukos/head/explicit-imports-interface Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 9198b118 by Alan Zimmerman at 2021-02-22T20:04:24+00:00 Context becomes a Maybe in the GHC AST This prevents noLoc's appearing in the ParsedSource. Match the change in GHC. - - - - - 0af20f64 by Hécate Moonlight at 2021-02-23T12:36:12+01:00 Fix the call-site of guessTarget in Interface.hs Explicit the imports from GHC.HsToCore.Docs - - - - - b7886885 by Hécate Moonlight at 2021-02-23T12:37:54+01:00 Merge pull request haskell/haddock#1349 from Kleidukos/fix-interface-guesstarget-call Fix the call-site of guessTarget in Interface.hs - - - - - 9cf041ba by Sylvain Henry at 2021-02-24T11:08:20+01:00 Fix haddockHypsrcTest output in ghc-head - - - - - b194182a by Hécate Moonlight at 2021-02-24T11:12:36+01:00 Merge pull request haskell/haddock#1351 from hsyl20/wip/hsyl20/fix-head Fix haddockHypsrcTest output in ghc-head - - - - - 3ce8b375 by Shayne Fletcher at 2021-03-06T09:55:03-05:00 Add ITproj to parser - - - - - d2abf762 by Ben Gamari at 2021-03-06T19:26:49-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a0f6047d by Andrew Martin at 2021-03-07T11:25:23-05:00 Update for boxed rep - - - - - 6f63c99e by Ben Gamari at 2021-03-10T13:20:21-05:00 Update for "FastString: Use FastMutInt instead of IORef Int" - - - - - e13f01df by Luke Lau at 2021-03-10T15:38:40-05:00 Implement template-haskell's putDoc This catches up to GHC using the new extractTHDocs function, which returns documentation added via the putDoc function (provided it was compiled with Opt_Haddock). Since it's already a map from names -> docs, there's no need to do traversal etc. It also matches the change from the argument map being made an IntMap rather than a Map Int - - - - - 89263d94 by Alan Zimmerman at 2021-03-15T17:15:26+00:00 Match changes in GHC AST for in-tree API Annotations As landed via https://gitlab.haskell.org/ghc/ghc/-/merge_requests/2418 - - - - - 28db1934 by Alan Zimmerman at 2021-03-15T20:40:09+00:00 Change some type family test results. It is not clear to me whether the original was printing incorrectly (since we did not have the TopLevel flag before now), or if this behaviour is expected. For the time being I am assuming the former. - - - - - 7c11c989 by Sylvain Henry at 2021-03-22T10:05:19+01:00 Fix after NameCache changes - - - - - addbde15 by Sylvain Henry at 2021-03-22T10:05:19+01:00 NameCache doesn't store a UniqSupply anymore - - - - - 15ec6cec by Ben Gamari at 2021-03-22T17:53:44-04:00 Bump GHC version to 9.2 - - - - - dbd6aa63 by Hécate Moonlight at 2021-03-24T14:28:36+01:00 Merge pull request haskell/haddock#1365 from hsyl20/wip/hsyl20/iface1 NameCache refactoring - - - - - 2d32da7e by Oleg Grenrus at 2021-03-27T01:12:00+02:00 Specialization of Data.List - - - - - 32b84fa6 by Fendor at 2021-03-27T10:50:17+01:00 Add UnitId to Target record This way we always know to which home-unit a given target belongs to. So far, there only exists a single home-unit at a time, but it enables having multiple home-units at the same time. - - - - - 54bf9f0e by Hécate Moonlight at 2021-03-28T14:08:35+02:00 Merge pull request haskell/haddock#1368 from fendor/target-unit-id-revert Add UnitId to Target record - - - - - 7dea168a by Alan Zimmerman at 2021-03-29T08:45:52+01:00 EPA : Rename ApiAnn to EpAnn - - - - - 72967f65 by Alfredo Di Napoli at 2021-03-29T09:47:01+02:00 pprError changed name in GHC - - - - - 4bc61035 by Alan Zimmerman at 2021-03-29T16:16:27-04:00 EPA : Rename ApiAnn to EpAnn - - - - - 108d031d by Ben Gamari at 2021-03-29T18:49:36-04:00 Merge commit '36418c4f70d7d2b179a77925b3ad5caedb08c9b5' into HEAD - - - - - 1444f700 by Ben Gamari at 2021-03-31T09:18:39-04:00 Merge pull request haskell/haddock#1370 from adinapoli/wip/adinapoli-diag-reason-severity Rename pprError to mkParserErr - - - - - d3087b79 by Ben Gamari at 2021-03-31T11:34:17-04:00 Merge commit 'd8d8024ad6796549a8d3b5512dabf3288d14e30f' into ghc-head - - - - - 170b79e9 by Ben Gamari at 2021-03-31T12:24:56-04:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - db0d6bae by Ben Gamari at 2021-04-10T09:34:35-04:00 Bump GHC version to 9.3 - - - - - a9f2c421 by Alan Zimmerman at 2021-04-19T18:26:46-04:00 Update for EPA changes in GHC (cherry picked from commit cafb48118f7c111020663776845897e225607b41) - - - - - 1ee4b7c7 by Sylvain Henry at 2021-05-11T10:00:06+02:00 Removal of HsVersions.h (#1388) * Update for EPA changes in GHC * Account for HsVersions.h removal Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 79e819e9 by Hécate Moonlight at 2021-05-11T10:14:47+02:00 Revert "Removal of HsVersions.h (#1388)" This reverts commit 72118896464f94d81f10c52f5d9261efcacc57a6. - - - - - 3dbd3f8b by Alan Zimmerman at 2021-05-11T10:15:17+02:00 Update for EPA changes in GHC - - - - - 2ce80c17 by Sylvain Henry at 2021-05-11T10:15:19+02:00 Account for HsVersions.h removal - - - - - 00e4c918 by Christiaan Baaij at 2021-05-13T08:21:56+02:00 Add Haddock support for the OPAQUE pragma (#1380) - - - - - 8f9049b2 by Hécate Moonlight at 2021-05-13T08:40:22+02:00 fixup! Use GHC 9.2 in CI runner - - - - - 27ddec38 by Alan Zimmerman at 2021-05-13T22:51:20+01:00 EPA: match changes from GHC T19834 - - - - - f8a1d714 by Felix Yan at 2021-05-14T17:10:04+02:00 Allow hspec 2.8 (#1389) All tests are passing. - - - - - df44453b by Divam Narula at 2021-05-20T15:42:42+02:00 Update ref, the variables got renamed. (#1391) This is due to ghc/ghc!5555 which caused a change in ModDetails in case of NoBackend. Now the initModDetails is used to recreate the ModDetails from interface and in-memory ModDetails is not used. - - - - - e46bfc87 by Alan Zimmerman at 2021-05-20T19:05:09+01:00 Remove Maybe from HsQualTy Match changes in GHC for haskell/haddock#19845 - - - - - 79bd7b62 by Shayne Fletcher at 2021-05-22T08:20:39+10:00 FieldOcc: rename extFieldOcc to foExt - - - - - 6ed68c74 by Ben Gamari at 2021-05-21T22:29:30-04:00 Merge commit '3b6a8774bdb543dad59b2618458b07feab8a55e9' into ghc-head - - - - - f9a02d34 by Alfredo Di Napoli at 2021-05-24T13:53:00+02:00 New Parser diagnostics interface - - - - - 392807d0 by Ben Gamari at 2021-05-24T09:57:40-04:00 Merge pull request haskell/haddock#1394 from adinapoli/wip/adinapoli-align-ps-messages Align Haddock to use the new Parser diagnostics interface - - - - - 33023cd8 by Ben Gamari at 2021-05-24T11:19:16-04:00 Revert "Add Haddock support for the OPAQUE pragma (#1380)" This reverts commit a1337c599ef7720b0482a25c55f11794112496dc. The GHC patch associated with this change is not yet ready to be merged. - - - - - 8c005af7 by Ben Simms at 2021-05-28T07:56:20+02:00 CI configuration for ghc-head (#1395) - - - - - 1e947612 by Hécate Moonlight at 2021-05-28T12:27:35+02:00 Use GHC 9.2 in CI runner (#1378) - - - - - e6fa10ab by CGenie at 2021-05-31T09:02:13+02:00 Add page about common errors (#1396) * Update index.rst Common errors page * Create common-errors.rst * Update common-errors.rst * Use GHC 9.2 in CI runner (#1378) * [haddock-api] remove .hspec-failures Co-authored-by: Hécate Moonlight <Kleidukos at users.noreply.github.com> - - - - - abc72a8d by Sylvain Henry at 2021-06-01T10:02:06+02:00 Adapt Haddock to Logger and Parser changes (#1399) - - - - - 91373656 by Zubin Duggal at 2021-06-01T20:45:10+02:00 Update haddockHypSrc tests since we now compute slighly more type info (#1397) - - - - - ed712822 by Marcin Szamotulski at 2021-06-02T08:54:33+02:00 Added myself to contributors - - - - - 49fdbcb7 by Marcin Szamotulski at 2021-06-02T08:57:24+02:00 Document multi component support - - - - - 9ddc8d7d by Hécate Moonlight at 2021-06-02T09:35:55+02:00 Merge pull request haskell/haddock#1379 from coot/coot/document-multi-component-support Document multi component support - - - - - 585b5c5e by Ben Simms at 2021-06-02T19:46:54+02:00 Update CONTRIBUTING.md (#1402) - - - - - 1df4a605 by Ben Simms at 2021-06-02T19:47:14+02:00 Update CONTRIBUTING.md (#1403) - - - - - 58ea43d2 by sheaf at 2021-06-02T22:09:06+02:00 Update Haddock Bug873 to account for renaming - - - - - c5d0ab23 by Vladislav Zavialov at 2021-06-10T13:35:42+03:00 HsToken in FunTy, RecConGADT - - - - - 1ae2f40c by Hécate Moonlight at 2021-06-11T11:19:09+02:00 Update the CI badges - - - - - 6fdc4de2 by Sylvain Henry at 2021-06-28T19:21:17+02:00 Fix mkParserOpts (#1411) - - - - - 18201670 by Alfredo Di Napoli at 2021-07-05T07:55:12+02:00 Rename getErrorMessages Lexer import This commit renames the Lexer import in `Hyperlinker.Parser` from `getErrorMessages` to `getPsErrorMessages` to eliminate the ambiguity with the `getErrorMessages` function defined in `GHC.Types.Error`. - - - - - 23173ca3 by Ben Gamari at 2021-07-07T11:31:44-04:00 Merge pull request haskell/haddock#1413 from adinapoli/wip/adinapoli-issue-19920 Rename getErrorMessages Lexer import - - - - - b3dc4ed8 by Alan Zimmerman at 2021-07-28T22:30:59+01:00 EPA: match changes from GHC T19834 (cherry picked from commit 2fec1b44e0ee7e263286709aa528b4ecb99ac6c2) - - - - - 5f177278 by Ben Gamari at 2021-08-06T01:17:37-04:00 Merge commit '2a966c8ca37' into HEAD - - - - - cdd81d08 by Marcin Szamotulski at 2021-08-08T17:19:06+02:00 coot/multiple packages (ghc-9.2) (#1418) - - - - - be0d71f1 by Marcin Szamotulski at 2021-08-16T08:46:03+02:00 coot/multiple package (ghc-head) (#1419) * FromJSON class Aeson style FromJSON class with Parsec based json parser. * doc-index.json file for multiple packages When creating haddock summary page for multiple packages render doc-index.json file using contents of all found 'doc-index.json' files. * Render doc-index.json When rendering html, render doc-index.json file independently of maybe_index_url option. doc-index.json file is useful now even if maybe_index_url is not `Nothing`. * base url option New `Flag_BaseURL` which configures from where static files are loaded (--base-url). If given and not equal "." static files are not coppied, as this indicates that they are not read from the the directory where we'd copy them. The default value is ".". - - - - - 3b09dbdf by Hécate Moonlight at 2021-10-07T23:26:03+02:00 Update GHC 9.2 to latest pre-release in CI - - - - - 7ac55417 by Zubin Duggal at 2021-10-11T12:10:19+02:00 Enable Haddock tests in GHC windows CI (#1428) * testsuite: strip windows line endings for haddock * hyperlinker: Work around double escaping (#19236) * deterministic SCC - - - - - 1cb81f25 by Andrew Lelechenko at 2021-10-12T15:23:19+02:00 haddock-library does not depend on bytestring or transformers (#1426) - - - - - a890b9aa by sheaf at 2021-10-15T22:19:42+02:00 update haddockHypsrcTest for GHC MR !6705 (#1430) - - - - - 42a55c6c by Sylvain Henry at 2021-10-15T22:20:10+02:00 Fix after PkgQual refactoring (#1429) - - - - - 91659238 by Alan Zimmerman at 2021-10-28T18:57:10+01:00 Update for changes in GHC for branch wip/az/no-srcspan-anno-instances - - - - - acf23e60 by Vladislav Zavialov at 2021-11-05T02:09:47+03:00 Do not use forall as an identifier See GHC ticket haskell/haddock#20609 - - - - - c565db0e by Krzysztof Gogolewski at 2021-11-27T02:42:35+01:00 Update after NoExtCon -> DataConCantHappen rename - - - - - b5f55590 by Artem Pelenitsyn at 2021-11-27T11:14:17+01:00 fix CI for 9.2 (#1436) - - - - - 25cd621e by Matthew Pickering at 2021-12-02T11:46:54+00:00 Update html-test for Data.List revert - - - - - 1d5ff85f by malteneuss at 2021-12-15T07:56:55+01:00 Add hint about inline link issue (#1444) - - - - - 791fde81 by Sylvain Henry at 2021-12-16T09:29:51+01:00 Bump ghc-head (#1445) * Update after NoExtCon -> DataConCantHappen rename * Update html-test for Data.List revert * Fix for new Plugins datatype Co-authored-by: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 44236317 by Sylvain Henry at 2021-12-17T09:39:00+01:00 Fix for new Plugins datatype - - - - - 80ada0fa by Hécate Moonlight at 2021-12-17T17:28:48+01:00 Remove ghc-head workflow (#1446) Contributions of GHC glue code are now done on the GHC gitlab, not in the GitHub repo anymore. - - - - - 49e171cd by Matthew Pickering at 2021-12-28T09:47:09+00:00 Remove use of ExtendedModSummary - - - - - 0e91b5ea by askeblad at 2022-01-04T09:18:35+01:00 update URLs - - - - - 9f13c212 by Hécate Moonlight at 2022-02-25T10:19:46+01:00 Fix solver for GHC 9.2 - - - - - 386751a1 by Meng Weng Wong at 2022-02-25T19:19:11+01:00 IDoc link has bitrotted; replaced with web.archive.org cache. (#1454) - - - - - d877cbe6 by Hécate Moonlight at 2022-02-25T19:21:58+01:00 Fix haddock user guide (#1456) - - - - - cc47f036 by Andrew Lelechenko at 2022-03-04T17:29:36+01:00 Allow text-2.0 in haddock-library (#1459) - - - - - 7b3685a3 by malteneuss at 2022-03-07T19:27:24+01:00 Add multi-line style hint to style section (#1460) - - - - - c51088b8 by John Ericson at 2022-03-11T16:46:26+01:00 Fix CollectPass instance to match TTG refactor Companion to GHC !7614 (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7614) - - - - - b882195b by Vladislav Zavialov at 2022-03-14T20:32:30+01:00 Link to (~) - - - - - 877349b8 by Christiaan Baaij at 2022-03-16T09:20:43+01:00 Add Haddock support for the OPAQUE pragma - - - - - 0ea22721 by askeblad at 2022-03-16T09:44:27+01:00 typos (#1464) - - - - - a6d13da1 by Matthew Pickering at 2022-03-22T13:41:17+00:00 Minimum changes needed for compilation with hi-haddock With hi-haddock, of course there is a much large refactoring of haddock which could be achieved but that is left for a future patch which can implemented at any time independently of GHC. - - - - - e7ac9129 by Matthew Pickering at 2022-03-22T21:17:50+00:00 Update test output - - - - - 6d916214 by Matthew Pickering at 2022-03-24T15:06:26+00:00 Merge branch 'wip/opaque_pragma' into 'ghc-head' Add Haddock support for the OPAQUE pragma See merge request ghc/haddock!2 - - - - - 42208183 by Steve Hart at 2022-03-25T20:43:50+01:00 Fix CI (#1467) * CI: Reinstall GHC with docs CI tests were failing because the GHC preinstalled to the CI environment does not include documentation, which is required for running the Haddock tests. This commit causes the CI workflow to reinstall GHC with docs so that tests can succeed. - - - - - 9676fd79 by Steve Hart at 2022-03-25T21:33:34+01:00 Make links in Synopsis functional again (#1458) Commit e41c1cbe9f0476997eac7b4a3f17cbc6b2262faf added a call to e.preventDefault() when handling click events that reach a toggle element. This prevents the browser from following hyperlinks within the Synopsis section when they are clicked by a user. This commit restores functioning hyperlinks within the Synopsis section by removing the call to e.preventDefault(), as it does not appear to be necessary, and removing it increases the flexibility of the details-helper code. - - - - - d1edd637 by sheaf at 2022-04-01T12:02:02+02:00 Keep track of promotion ticks in HsOpTy Keeping track of promotion ticks in HsOpTy allows us to properly pretty-print promoted constructors such as lists. - - - - - 9dcb2dfc by Jakob Brünker at 2022-04-01T15:46:22+00:00 Add support for \cases See merge request ghc/ghc!7873 - - - - - b0412ee5 by askeblad at 2022-04-06T17:47:57+02:00 spelling errors (#1471) - - - - - 6b18829b by Vladislav Zavialov at 2022-04-06T18:53:58+02:00 Rename [] to List - - - - - 2d046691 by Vladislav Zavialov at 2022-04-07T20:25:54+03:00 HsToken ConDeclGADT con_dcolon - - - - - 90b43da4 by Steve Hart at 2022-04-12T13:29:46+02:00 Parse Markdown links at beginning of line within a paragraph (#1470) * Catch Markdown links at beginning of line within paragraph Per Issue haskell/haddock#774, Markdown links were being parsed as ordinary text when they occurred at the beginning of a line other than the first line of the paragraph. This occurred because the parser was not interpreting a left square bracket as a special character that could delimit special markup. A space character was considered a special character, so, if a space occurred at the beginning of the new line, then the parser would interpret the space by itself and then continue parsing, thereby catching the Markdown link. '\n' was not treated as a special character, so the parser did not catch a Markdown link that may have followed. Note that this will allow for Markdown links that are not surrounded by spaces. For example, the following text includes a Markdown link that will be parsed: Hello, world[label](url) This is consistent with how the parser handles other types of markup. * Remove obsolete documentation hint Commit 6b9aeafddf20efc65d3725c16e3fc43a20aac343 should eliminate the need for the workaround suggested in the documentation. - - - - - 5b08312d by Hécate Moonlight at 2022-04-12T13:36:38+02:00 Force ghc-9.2 in the cabal.project - - - - - 0d0ea349 by dependabot[bot] at 2022-04-12T13:57:41+02:00 Bump path-parse from 1.0.5 to 1.0.7 in /haddock-api/resources/html (#1469) Bumps [path-parse](https://github.com/jbgutierrez/path-parse) from 1.0.5 to 1.0.7. - [Release notes](https://github.com/jbgutierrez/path-parse/releases) - [Commits](https://github.com/jbgutierrez/path-parse/commits/v1.0.7) --- updated-dependencies: - dependency-name: path-parse dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 2b9fc65e by dependabot[bot] at 2022-04-12T13:57:54+02:00 Bump copy-props from 2.0.4 to 2.0.5 in /haddock-api/resources/html (#1468) Bumps [copy-props](https://github.com/gulpjs/copy-props) from 2.0.4 to 2.0.5. - [Release notes](https://github.com/gulpjs/copy-props/releases) - [Changelog](https://github.com/gulpjs/copy-props/blob/master/CHANGELOG.md) - [Commits](https://github.com/gulpjs/copy-props/compare/2.0.4...2.0.5) --- updated-dependencies: - dependency-name: copy-props dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - ea98a6fb by Ben Gamari at 2022-04-23T22:54:37-04:00 Update for GHC 9.4 - - - - - 9e11864f by Ben Gamari at 2022-04-25T16:24:31-04:00 Merge remote-tracking branch 'upstream/ghc-9.2' into ghc-head - - - - - f83cc506 by Ben Gamari at 2022-04-25T17:00:25-04:00 Bump ghc version to 9.5 - - - - - e01c2e7d by Ben Gamari at 2022-04-28T16:19:04-04:00 Revert "Bump ghc-head (#1445)" This reverts commit b29a78ef6926101338f62e84f456dac8659dc9d2. This should not have been merged. - - - - - a2b5ee8c by Ben Gamari at 2022-04-28T16:19:24-04:00 Merge commit '2627a86c' into ghc-head - - - - - 0c6fe4f9 by Ben Gamari at 2022-04-29T10:05:54-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-9.4 - - - - - b6e5cb0a by Ben Gamari at 2022-04-29T11:46:06-04:00 Revert "HsToken ConDeclGADT con_dcolon" This reverts commit 24208496649a02d5f87373052c430ea4a97842c5. - - - - - 15a62888 by Ben Gamari at 2022-04-29T15:12:55-04:00 Bump base upper bound - - - - - 165b9031 by Ben Gamari at 2022-04-29T23:58:38-04:00 Update test output - - - - - e0c3e5da by Phil de Joux at 2022-05-02T14:46:38+02:00 Add hlint action .hlint.yaml with ignores & CPP. (#1475) - - - - - ead1158d by Raphael Das Gupta at 2022-05-02T14:46:48+02:00 fix grammar in docs: "can the" → "can be" (#1477) - - - - - cff97944 by Ben Gamari at 2022-05-02T18:38:56-04:00 Allow base-4.17 - - - - - e4ecb201 by Phil de Joux at 2022-05-03T13:14:55+02:00 Remove unused imports that GHC warned about. (#1480) - - - - - 222890b1 by Phil de Joux at 2022-05-03T13:15:46+02:00 Follow hlint suggestion to remove redundant bang. (#1479) - - - - - 058b671f by Phil de Joux at 2022-05-03T13:34:04+02:00 Follow hlint, remove language pragmas in libs. (#1478) - - - - - 0a645049 by Ben Simms at 2022-05-03T14:19:24+02:00 Keep track of ordered list indexes and render them (#1407) * Keep track of ordered list indexes and render them * Rename some identifiers to clarify - - - - - f0433304 by Norman Ramsey at 2022-05-04T15:13:34-04:00 update for changes in GHC API - - - - - 3740cf71 by Emily Martins at 2022-05-06T18:23:48+02:00 Add link to the readthedocs in cabal description to show on hackage. (cherry picked from commit 52e2d40d47295c02d3181aac0c53028e730f1e3b) - - - - - 5d754f1e by Hécate Moonlight at 2022-05-06T18:44:57+02:00 remove Bug873 - - - - - 968fc267 by Hécate Moonlight at 2022-05-06T18:48:28+02:00 Ignore "Use second" HLint suggestion. It increases laziness. - - - - - 02d14e97 by Jade Lovelace at 2022-05-07T17:42:08+02:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` - - - - - b22b87ed by Artem Pelenitsyn at 2022-05-08T16:19:47+02:00 fix parsing trailing quotes in backticked identifiers (#1408) (#1483) - - - - - 80ae107b by Alex Biehl at 2022-05-08T16:37:16+02:00 Fix "Defined by not used" error (cherry picked from commit 6e02a620a26c3a44f98675dd1b93b08070c36c0a) - - - - - 4c838e84 by Hécate Moonlight at 2022-05-08T16:37:16+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - fc9827b4 by Hécate Moonlight at 2022-05-08T16:40:40+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - b153b555 by Xia Li-yao at 2022-05-20T17:52:42+02:00 Hide synopsis from search when hidden (#1486) Fix haskell/haddock#1451 - - - - - f3e38b85 by Marcin Szamotulski at 2022-05-21T23:32:31+02:00 Allow to hide interfaces when rendering multiple components (#1487) This is useful when one wishes to `--gen-contents` when rendering multiple components, but one does not want to render all modules. This is in particular useful when adding base package. - - - - - f942863b by Marcin Szamotulski at 2022-05-24T08:29:59+02:00 Check if doc-index.json exists before reading it (#1488) - - - - - 31e92982 by Marcin Szamotulski at 2022-05-25T16:22:13+02:00 Version bump 2.26.1 (#1489) * Version bump 2.26.1 We extended format accepted by `--read-interface` option, which requires updating the minor version. * Update documentation of --read-interface option - - - - - 7cc873e0 by sheaf at 2022-05-25T16:42:31+02:00 Updated HaddockHypsrcTest output for record update changes (MR !7981) - - - - - cd196942 by Marcin Szamotulski at 2022-05-25T20:28:47+02:00 Use visibility to decide which interfaces are included in quickjump (#1490) This is also consistent with how html index is build. See haskell/cabal#7669 for rationale behind this decision. - - - - - 00c713c5 by Hécate Moonlight at 2022-05-26T17:09:15+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 2f3039f1 by Hécate Moonlight at 2022-05-26T17:10:59+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 63a5650c by romes at 2022-05-31T12:43:22+01:00 TTG: Match new GHC AST - - - - - dd7d1617 by romes at 2022-06-02T16:11:00+01:00 Update for IE changes in !8228 - - - - - c23aaab7 by cydparser at 2022-06-06T08:48:14+02:00 Fix and improve CI (#1495) * Pin GHC version before creating the freeze file * Use newest action versions * Improve caching * Avoid unnecessarily reinstalling GHC * Use GHC 9.2.2 for CI Co-authored-by: Cyd Wise <cwise at tripshot.com> - - - - - c156fa77 by Hécate Moonlight at 2022-06-06T11:59:35+02:00 Add Mergify configuration (#1496) - - - - - 2dba4188 by Hécate Moonlight at 2022-06-06T16:12:50+02:00 Bump haddock's version in cabal file to 2.26.1 (#1497) - - - - - d7d4b8b9 by Marcin Szamotulski at 2022-06-07T06:09:40+00:00 Render module tree per package in the content page (#1492) * Render module tree per package in the content page When rendering content page for multiple packages it is useful to split the module tree per package. Package names in this patch are inferred from haddock's interface file names. * Write PackageInfo into interface file To keep interface file format backward compatible, instead of using `Binary` instance for `InterfaceFile` we introduce functions to serialise and deserialise, which depends on the interface file version. - - - - - 77765665 by Mike Pilgrem at 2022-06-12T21:57:19+01:00 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - b0e079b0 by mergify[bot] at 2022-06-13T11:49:37+00:00 Merge pull request haskell/haddock#1108 from mpilgrem/fix783 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - 6c0292b1 by Hécate Moonlight at 2022-06-21T17:21:08+02:00 Update the contribution guide - - - - - e413b9fa by dependabot[bot] at 2022-06-21T23:38:19+02:00 Bump shell-quote from 1.6.1 to 1.7.3 in /haddock-api/resources/html (#1500) Bumps [shell-quote](https://github.com/substack/node-shell-quote) from 1.6.1 to 1.7.3. - [Release notes](https://github.com/substack/node-shell-quote/releases) - [Changelog](https://github.com/substack/node-shell-quote/blob/master/CHANGELOG.md) - [Commits](https://github.com/substack/node-shell-quote/compare/1.6.1...1.7.3) --- updated-dependencies: - dependency-name: shell-quote dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 29d0ef70 by romes at 2022-07-06T11:29:39+02:00 TTG: AST Updates for !8308 - - - - - 1bae7c87 by Alan Zimmerman at 2022-07-06T22:50:43+01:00 Match GHC changes for T21805 This brings in a newtype for FieldLabelString - - - - - 6fe8b988 by Phil de Joux at 2022-07-16T20:54:26+00:00 Bump hlint version to 3.4.1, the version with counts. (#1503) Redo the counts available with the --default option. - - - - - 48fb43af by Phil de Joux at 2022-07-19T09:32:55+02:00 Follow hlint suggestion: unused LANGUAGE pragma. (#1504) * Follow hlint suggestion: unused LANGUAGE pragma. * Ignore within modules to pass linting and pass tests. - - - - - c1cf1fa7 by Phil de Joux at 2022-07-24T13:45:59+02:00 Follow hlint suggestion: redundant $. (#1505) * Follow hlint suggestion: redundant $. * Remove $ and surplus blank lines in Operators. - - - - - 74777eb2 by Jade Lovelace at 2022-07-29T11:02:41+01:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` (cherry picked from commit ab53ccf089ea703b767581ac14be0f6c78a7678a) - - - - - faa4cfcf by Hécate Moonlight at 2022-07-29T20:31:20+02:00 Merge pull request haskell/haddock#1516 from duog/9-4-backport-fix-hyperlinks Backport 9-4: Fix hyperlinks to external items and modules (#1482) - - - - - 5d2450f3 by Ben Gamari at 2022-08-05T17:41:15-04:00 Merge remote-tracking branch 'origin/ghc-9.4' - - - - - 63954f73 by Ben Gamari at 2022-08-05T19:08:36-04:00 Clean up build and testsuite for GHC 9.4 - - - - - d4568cb8 by Hécate Moonlight at 2022-08-05T19:10:49-04:00 Bump the versions - - - - - 505583a4 by Ben Gamari at 2022-08-06T13:58:27-04:00 Merge pull request haskell/haddock#1518 from bgamari/wip/ghc-9.4-merge Merge GHC 9.4 into `main` - - - - - 5706f6a4 by Ben Gamari at 2022-08-06T22:57:21-04:00 html-test: Testsuite changes for GHC 9.4.1 - - - - - 5f2a45a2 by Ben Gamari at 2022-08-15T14:33:05-04:00 doc: Fix a few minor ReST issues Sphinx was complaining about too-short title underlines. - - - - - 220e6410 by Ben Gamari at 2022-08-15T14:41:24-04:00 Merge branch 'main' into ghc-head - - - - - fbeb1b02 by Ben Gamari at 2022-08-15T14:45:16-04:00 Updates for GHC 9.5 - - - - - eee562eb by Vladislav Zavialov at 2022-08-15T14:46:13-04:00 HsToken ConDeclGADT con_dcolon - - - - - c5f073db by Ben Gamari at 2022-08-15T16:55:35-04:00 Updates for GHC 9.5 - - - - - 3f7ab242 by Vladislav Zavialov at 2022-08-15T16:55:35-04:00 HsToken ConDeclGADT con_dcolon - - - - - a18e473d by Ben Gamari at 2022-08-16T08:35:19-04:00 Merge branch 'wip/ghc-head-bump' into ghc-head - - - - - af0ff3a4 by M Farkas-Dyck at 2022-09-15T21:16:05+00:00 Disuse `mapLoc`. - - - - - a748fc38 by Matthew Farkas-Dyck at 2022-09-17T10:44:18+00:00 Scrub partiality about `NewOrData`. - - - - - 2758fb6c by John Ericson at 2022-09-18T03:27:37+02:00 Test output changed because of change to `base` Spooky, but I guess that is intended? - - - - - a7eec128 by Torsten Schmits at 2022-09-21T11:06:55+02:00 update tests for the move of tuples to GHC.Tuple.Prim - - - - - 461e7b9d by Ross Paterson at 2022-09-24T22:01:25+00:00 match implementation of GHC proposal haskell/haddock#106 (Define Kinds Without Promotion) - - - - - f7fd77ef by sheaf at 2022-10-17T14:53:01+02:00 Update Haddock for GHC MR !8563 (configuration of diagnostics) - - - - - 3d3e85ab by Vladislav Zavialov at 2022-10-22T23:04:06+03:00 Class layout info - - - - - cbde4cb0 by Simon Peyton Jones at 2022-10-25T23:19:18+01:00 Adapt to Constraint-vs-Type See haskell/haddock#21623 and !8750 - - - - - 7108ba96 by Tom Smeding at 2022-11-01T22:33:23+01:00 Remove outdated footnote about module re-exports The footnote is invalid with GHC 9.2.4 (and possibly earlier): the described behaviour in the main text works fine. - - - - - 206c6bc7 by Hécate Moonlight at 2022-11-01T23:00:46+01:00 Merge pull request haskell/haddock#1534 from tomsmeding/patch-1 - - - - - a57b4c4b by Andrew Lelechenko at 2022-11-21T00:39:52+00:00 Support mtl-2.3 - - - - - e9d62453 by Simon Peyton Jones at 2022-11-25T13:49:12+01:00 Track small API change in TyCon.hs - - - - - eb1c73f7 by Ben Gamari at 2022-12-07T08:46:21-05:00 Update for GhC 9.6 - - - - - 063268dd by Ben Gamari at 2022-12-07T11:26:32-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 4ca722fe by Ben Gamari at 2022-12-08T14:43:26-05:00 Bump bounds to accomodate base-4.18 - - - - - 340b7511 by Vladislav Zavialov at 2022-12-10T12:31:28+00:00 HsToken in HsAppKindTy - - - - - 946226ec by Ben Gamari at 2022-12-13T20:12:56-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - fd8faa66 by Ben Gamari at 2022-12-22T13:44:28-05:00 Bump GHC version to 9.7 - - - - - 2958aa9c by Ben Gamari at 2022-12-22T14:49:16-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 9e0fefd8 by Andrei Borzenkov at 2023-01-30T14:02:04+04:00 Rename () to Unit, Rename (,,...,,) to Tuple<n> - - - - - eb3968b5 by Ben Gamari at 2023-03-10T02:32:43-05:00 Bump versions for ghc-9.6 release - - - - - 4aeead36 by Adam Gundry at 2023-03-23T13:53:47+01:00 Adapt to warning categories changes - - - - - 642d8d60 by sheaf at 2023-03-29T13:35:56+02:00 Adapt to record field refactor This commit adapts to the changes in GHC MR !8686, which overhauls the treatment of record fields in the renamer, adding separate record field namespaces and entirely removing the GreName datatype. - - - - - ac8d4333 by doyougnu at 2023-03-29T11:11:44-04:00 Update UniqMap API - - - - - 7866fc86 by Ben Orchard at 2023-04-20T11:29:33+02:00 update classify with new tokens - - - - - ffcdd683 by Finley McIlwaine at 2023-04-24T09:36:18-06:00 Remove index-state - - - - - 05b70982 by Finley McIlwaine at 2023-04-26T08:16:31-06:00 `renameInterface` space leak fixes - Change logic for accumulation of names for which link warnings will be generated - Change handling of `--ignore-link-symbol` to allow qualified and unqualified names. Added to CHANGES.md - Some formatting changes and comments here and there - - - - - e5697d7c by Finley McIlwaine at 2023-04-27T18:46:36-06:00 Messy things - ghc-debug dependency and instrumentation - cabal.project custom with-compiler - hie.yaml files - traces and such - - - - - 0b8ef80b by Finley McIlwaine at 2023-05-02T18:08:52-06:00 Stop retaining GRE closures GRE closures should never be necessary to Haddock, so we never want to keep them on the heap. Despite that, they are retained by a lot of the data structures that Haddock makes use of. - Attempt to fix that situation by adding strictness to various computations and pruning the `ifaceInstances` field of `Interface` to a much thinner data type. - Removes the `ifaceFamInstances` field, as it was never used. - Move some of the attach instances types (e.g. `SimpleType`) to the types module - - - - - 8bda991b by Finley McIlwaine at 2023-05-08T16:07:51-06:00 Memory usage fixes - Refactor `ifaceDeclMap` to drastically reduce memory footprint. We no longer store all declarations associated with a given name, since we only cared to determine if the only declaration associated with a name was a value declaration. Change the `DeclMap` type to better reflect this. - Drop pre-renaming export items after the renaming step. Since the Hoogle backend used the pre-renamed export items, this isn't trivial. We now generate Hoogle output for exported declarations during the renaming step (if Hoogle output /should/ be generated), and store that with the renamed export item. - Slightly refactor Hoogle backend to handle the above change and allow for early generation of Hoogle output. - Remove the `ifaceRnDocMap` and `ifaceRnArgMap` fields of the `Interface` type, as they were never used. - Remove some unnecessary strictness - Remove a lot of dead code from `Syb` module - - - - - 1611ac0c by Finley McIlwaine at 2023-05-09T11:51:57-06:00 Unify ErrMsgM and IfM - Delete ErrMsgM, stop accumulating warnings in a writer - Make IfM a state monad, print warnings directly to stdout, move IfM type into types module - Drop ErrMsg = String synonym - Unset IORefs from plugin after they are read, preventing unnecessary retention of interfaces - - - - - 42d696ab by Finley McIlwaine at 2023-05-11T15:52:07-06:00 Thunk leak fixes The strictness introduced in this commit was motivated by observing thunk leaks in the eventlog2html output. - Refactor attach instances list comprehension to avoid large intermediate thunks - Refactor some HTML backend list comprehensions to avoid large intermediate thunks - Avoid thunks accumulating in documentation types or documentation parser - A lot of orphan NFData instances to allow us to force documentation values - - - - - 68561cf6 by Finley McIlwaine at 2023-05-11T17:02:10-06:00 Remove GHC debug dep - - - - - 10519e3d by Finley McIlwaine at 2023-05-15T12:40:48-06:00 Force HIE file path Removes a potential retainer of `ModSummary`s - - - - - 1e4a6ec6 by Finley McIlwaine at 2023-05-15T14:20:34-06:00 Re-add index-state, with-compiler, delete hie.yamls - - - - - a2363fe9 by Hécate Moonlight at 2023-05-15T22:45:16+02:00 Merge pull request haskell/haddock#1594 from FinleyMcIlwaine/finley/ghc-9.6-mem-fixes Reduce memory usage - - - - - e8a78383 by Finley McIlwaine at 2023-05-17T12:19:16-06:00 Merge branch ghc-9.6 into ghc-head - - - - - 22e25581 by Finley McIlwaine at 2023-05-17T12:20:23-06:00 Merge branch 'ghc-head' of gitlab.haskell.org:ghc/haddock into ghc-head - - - - - 41bbf0df by Bartłomiej Cieślar at 2023-05-24T08:57:58+02:00 changes to the WarningTxt cases Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - c686ba9b by Hécate Moonlight at 2023-06-01T14:03:02-06:00 Port the remains of Hi-Haddock - - - - - 9d8a85fd by Hécate Moonlight at 2023-06-01T14:03:06-06:00 Stdout for tests - - - - - 36331d07 by Finley McIlwaine at 2023-06-01T14:06:02-06:00 Formatting, organize imports - - - - - a06059b1 by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix empty context confusion in Convert module - - - - - 379346ae by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix associated type families in Hoogle output - - - - - fc6ea7ed by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix test refs Accept several changes in Hoogle tests: Pretty printing logic no longer prints the `(Proxy (Proxy (...))` chain in Bug806 with parentheses. Since this test was only meant to verify that line breaks do not occur, accept the change. `tyThingToLHsDecl` is called for class and data declarations, which ends up "synifying" the type variables and giving unlifted types kind signatures. As a result, type variables of kind `Type -> Type` are now printed with kind signatures in Hoogle output. This could be changed by manually drop kind signatures from class variables in the Hoogle backend if the behavior is deemed unacceptable. Sometimes subordinate declarations are exported separate from their parent declarations (e.g. record selectors). In this case, a type signature is cobbled together for the export item in `extractDecl`. Since this type signature is very manually constructed, it may lack kind signatures of decls constructed from `tyThingToLHsDecl`. An example of this is the `type-sigs` Hoogle test. Change `*` to `Type` in Hoogle test refs. I don't think this will break Hoogle behavior, since it appears to not consider type signatures in search. I have not fully verified this. - - - - - e14b7e58 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix LaTeX backend test refs Changes to GHC pretty printing code have resulted in some differences to Haddock's LaTeX output. - Type variables are printed explicitly quantified in the LinearTypes test - Wildcard types in type family equations are now printed numbered, e.g. _1 _2, in the TypeFamilies3 test - Combined signatures in DefaultSignatures test are now documented as separate signatures - - - - - 41b5b296 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and test source updates - Stop using kind `*` in html test sources - Add TypeOperators where necessary to avoid warnings and future errors - Rename some test modules to match their module names - - - - - c640e2a2 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix missing deprecation warnings on record fields `lookupOccEnv` was used to resolve `OccNames` with warnings attached, but it doesn't look in the record field namespace. Thus, if a record field had a warning attached, it would not resolve and the warning map would not include it. This commit fixes by using `lookupOccEnv_WithFields` instead. - - - - - fad0c462 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and some comments - - - - - 751fd023 by Finley McIlwaine at 2023-06-01T14:11:41-06:00 Accept HTML test diffs All diffs now boil down to the expected differences resulting from declarations being reified from TyThings in hi-haddock. Surface syntax now has much less control over the syntax used in the documentation. - - - - - d835c845 by Finley McIlwaine at 2023-06-01T14:11:45-06:00 Adapt to new load' type - - - - - dcf776c4 by Finley McIlwaine at 2023-06-01T14:13:13-06:00 Update mkWarningMap and moduleWarning - - - - - 8e8432fd by Finley McIlwaine at 2023-06-01T14:28:54-06:00 Revert load' changes - - - - - aeb2982c by Finley McIlwaine at 2023-06-01T14:40:24-06:00 Accept change to Instances test in html-test Link to Data.Tuple instead of GHC.Tuple.Prim - - - - - 8adfdbac by Finley McIlwaine at 2023-06-01T15:53:17-06:00 Reset ghc dep to ^>= 9.6 - - - - - 2b1ce93d by Finley McIlwaine at 2023-06-06T07:50:04-06:00 Update CHANGES.md, user guide, recomp avoidance * Add --trace-args flag for tracing arguments received to standard output * Avoid recompiling due to changes in optimization flags * Update users guide and changes.md - - - - - f3da6676 by Finley McIlwaine at 2023-06-06T14:12:56-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - bf36c467 by Matthew Pickering at 2023-06-07T10:16:09+01:00 Revert back to e16e20d592a6f5d9ed1af17b77fafd6495242345 Neither of these MRs are ready to land yet which causes issues with other MRs which are ready to land and need haddock changes. - - - - - 421510a9 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 atSign has no unicode variant Prior to this change, atSign was defined as follows: atSign unicode = text (if unicode then "@" else "@") Yes, this is the same symbol '\64' and not your font playing tricks on you. Now we define: atSign = char '@' Both the LaTeX and the Xhtml backend are updated accordingly. - - - - - 3785c276 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 LaTeX: fix printing of type variable bindings Consider this type signature: kindOf :: forall {k} (a :: k). Proxy a -> Proxy k Prior to this fix, the LaTeX backend rendered it like this: kindOf :: forall k a. Proxy a -> Proxy k Now we preserve explicit specificity and kind annotations. - - - - - 0febf3a8 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 Add support for invisible binders in type declarations - - - - - 13e33bb3 by Finley McIlwaine at 2023-06-08T07:51:59-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - 3e5340ce by Finley McIlwaine at 2023-06-08T07:54:27-06:00 Add note about stubdir to recompilation docs - - - - - db7e84dc by Finley at 2023-06-08T08:11:03-06:00 Merge pull request haskell/haddock#1597 from haskell/finley/hi-haddock-9.6 hi-haddock for ghc 9.6 - - - - - 4e085d17 by Finley McIlwaine at 2023-06-14T13:41:06-06:00 Replace SYB traversals - - - - - 7b39aec5 by Finley McIlwaine at 2023-06-14T14:20:17-06:00 Test ref accepts, remove unused HaddockClsInst - - - - - df9c2090 by Finley McIlwaine at 2023-06-15T08:02:51-06:00 Use batchMsg for progress reporting during load With hi-haddock as is, there is an awkward silence during the load operation. This commit makes haddock use the default `batchMsg` Messager for progress reporting, and makes the default GHC verbosity level 1, so the user can see what GHC is doing. - - - - - f23679a8 by Hécate Moonlight at 2023-06-15T20:31:53+02:00 Merge pull request haskell/haddock#1600 from haskell/finley/hi-haddock-optim - - - - - a7982192 by Finley McIlwaine at 2023-06-15T15:02:16-06:00 hi-haddock squashed - - - - - c34f0c8d by Finley McIlwaine at 2023-06-15T16:22:03-06:00 Merge remote-tracking branch 'origin/ghc-9.6' into finley/hi-haddock-squashed - - - - - 40452797 by Bartłomiej Cieślar at 2023-06-16T12:26:04+02:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - e58673bf by Ben Gamari at 2023-06-16T09:33:35-04:00 Bump GHC version to 9.8 - - - - - 74bdf972 by Ben Gamari at 2023-06-16T09:36:18-04:00 Merge commit 'fcaaad06770a26d35d4aafd65772dedadf17669c' into ghc-head - - - - - 418ee3dc by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Remove NFData SourceText, IfaceWarnings updates The NFData SourceText instance is now available in GHC Handle mod_iface mi_warns now being IfaceWarnings - - - - - 62f31380 by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Accept Instances.hs test output Due to ghc!10469. - - - - - a8f2fc0e by Ben Gamari at 2023-06-20T15:48:08-04:00 Test fixes for "Fix associated data family doc structure items" Associated data families were being given their own export DocStructureItems, which resulted in them being documented separately from their classes in haddocks. This commit fixes it. - - - - - cb1ac33e by Bartłomiej Cieślar at 2023-06-21T12:56:02-04:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - 9933e10b by Ben Gamari at 2023-06-21T12:56:02-04:00 Bump GHC version to 9.8 - - - - - fe8c18b6 by Ben Gamari at 2023-06-21T15:36:29-04:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - c61a0d5b by Ben Gamari at 2023-06-21T16:10:51-04:00 Bump GHC version to 9.9 - - - - - 0c2a756e by sheaf at 2023-07-07T13:45:12+02:00 Avoid incomplete record update in Haddock Hoogle This commit avoids running into an incomplete record update warning in the Hoogle backend of Haddock. This was only noticed now, because incomplete record updates were broken in GHC 9.6. Now that they are fixed, we have to avoid running into them! - - - - - f9b952a7 by Ben Gamari at 2023-07-21T11:58:05-04:00 Bump base bound to <4.20 For GHC 9.8. - - - - - 1b27e151 by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Check for puns (see ghc#23368) - - - - - 457341fd by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Remove fake exports for (~), List, and Tuple<n> The old reasoning no longer applies, nowadays those names can be mentioned in export lists. - - - - - bf3dcddf by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Fix pretty-printing of Solo and MkSolo - - - - - 495b2241 by Matthew Pickering at 2023-09-01T13:02:07+02:00 Fix issue with duplicate reexported definitions (T23616) When a class method was reexported, it's default methods were also showing up in the generated html page. The simplest and most non-invasive fix is to not look for the default method if we are just exporting the class method.. because the backends are just showing default methods when the whole class is exported. In general it would be worthwhile to rewrite this bit of code I think as the logic and what gets included is split over `lookupDocs` and `availExportDecl` it would be clearer to combine the two. The result of lookupDocs is always just passed to availExportDecl so it seems simpler and more obvious to just write the function directly. - - - - - 6551824d by Finley McIlwaine at 2023-09-05T13:06:57-07:00 Remove fake export of `FUN` from Prelude This prevents `data FUN` from being shown at the top of the Prelude docs. Fixes \#23920 on GHC. - - - - - 9ab5a448 by Alan Zimmerman at 2023-09-08T18:26:53+01:00 Match changes in wip/az/T23885-unicode-funtycon - - - - - 4d08364e by Alan Zimmerman at 2023-10-31T19:46:45+00:00 EPA: match changes in GHC - EPA: Comments in AnchorOperation - EPA: Remove EpaEofComment - - - - - e7da0d25 by Alan Zimmerman at 2023-11-05T11:20:31+00:00 EPA: match changes in GHC, l2l cleanup - - - - - 4ceac14d by Alan Zimmerman at 2023-11-11T15:16:41+00:00 EPA: Replace Anchor with EpaLocation Match GHC - - - - - 94fb8d47 by Alan Zimmerman at 2023-11-29T18:10:26+00:00 Match GHC, No comments in EpaDelta for comments - - - - - 32d208e1 by Vladislav Zavialov at 2023-12-12T20:41:36+03:00 EPA: Match changes to LHsToken removal - - - - - eebdd316 by Apoorv Ingle at 2024-01-23T13:49:12+00:00 Changes for haskell/haddock#18324 - - - - - ae856a82 by Matthew Pickering at 2024-02-05T12:22:39+00:00 ghc-internals fallout - - - - - f8429266 by Jade at 2024-02-08T14:56:50+01:00 Adjust test for ghc MR !10993 - - - - - 6d1e2386 by Alan Zimmerman at 2024-02-13T22:00:28+03:00 EPA: Match changes to HsParTy and HsFunTy - - - - - 9c588f19 by Fendor at 2024-02-14T11:05:36+01:00 Adapt to GHC giving better Name's for linking - - - - - 778e1db3 by Andrei Borzenkov at 2024-02-16T16:12:07+03:00 Namespace specifiers for fixity signatures - - - - - 826c5b47 by Torsten Schmits at 2024-02-21T13:17:05+01:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 2cff14d5 by Ben Gamari at 2024-02-22T09:35:56-05:00 Bump bounds - - - - - f49376b3 by Ben Gamari at 2024-02-22T09:35:56-05:00 Allow `@since` annotations in export lists Here we extend Haddock to admit `@since` annotations in export lists. These can be attached to most export list items (although not subordinate lists). These annotations supercede the declaration's `@since` annotation in produced Haddocks. - - - - - b5aa93df by Ben Gamari at 2024-02-22T12:09:06-05:00 Allow package-qualified @since declarations - - - - - 8f5957f2 by Ben Gamari at 2024-02-22T13:55:19-05:00 Documentation changes from ghc-internal restructuring Previously many declarations (e.g. `Int`) were declared to have a "home" in `Prelude`. However, now Haddock instead chooses to put these in more specific homes (e.g. `Data.Int`). Given that the "home" decision is driven by heuristics and in general these changes seem quite reasonable I am accepting them: * `Int` moved from `Prelude` to `Data.Int` * `(~)` moved from `Prelude` to `Data.Type.Equality` * `Type` moved from `GHC.Types` to `Data.Kind` * `Maybe` moved from `Prelude` to `Data.Maybe` * `Bool` moved from `Prelude` to `Data.Bool` * `Ordering` moved from `Prelude` to `Data.Ord` As well, more identifiers are now hyperlinked; it's not immediately clear *why*, but it is an improvement nevertheless. - - - - - ec33fec3 by Ben Gamari at 2024-02-22T20:36:24-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 30cfd251 by Torsten Schmits at 2024-02-24T13:00:42-05:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 732db81d by Ben Gamari at 2024-02-24T19:12:18-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 86bf7010 by Ben Gamari at 2024-02-27T19:28:10-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 4b6e76b5 by Patrick at 2024-03-07T22:09:30+08:00 fix haskell/haddock#24493, with module name introduced in hieAst The accompanies haddoc PR with GHC PR https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12153 Two things have been done: 1. Link is introduced to every `X` in `module X where`, since we introduce the module name to HieAst, 2. `{-# LINE 4 "hypsrc-test/src/PositionPragmas.hs" #-}` is added before the `module PositionPragmas where` in ` hypsrc-test/ref/src/PositionPragmas.html `.It ensures only a single hieAst for file `hypsrc-test/src/PositionPragmas.hs` is generated. - - - - - 635abccc by Ben Gamari at 2024-03-08T17:09:06-05:00 Bump ghc version to 9.10 - - - - - 5b934048 by Ben Gamari at 2024-03-08T18:50:12-05:00 Bump base upper bound - - - - - b30d134e by Ben Gamari at 2024-03-08T18:50:44-05:00 Testsuite output update - - - - - 9bdf3586 by Ben Gamari at 2024-03-09T21:37:44-05:00 Merge branch 'ghc-9.10' into ghc-head - - - - - cec76981 by Ben Gamari at 2024-03-09T21:54:00-05:00 Bump GHC version to 9.11 - - - - - 4c59feb7 by Ben Gamari at 2024-03-09T22:15:01-05:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - bee54c24 by Krzysztof Gogolewski at 2024-04-19T11:13:00+02:00 Update quantification order following GHC haskell/haddock#23764 - - - - - 2814eb89 by Ben Gamari at 2024-04-19T18:57:05+02:00 hypsrc-test: Fix output of PositionPragmas.html - - - - - a27c6a49 by Fendor at 2024-04-22T10:13:03+02:00 Adapt to UserData split - - - - - 1efc5a7a by Fendor at 2024-04-22T10:13:03+02:00 Adapt to BinHandle split - - - - - c62239b7 by Sylvain Henry at 2024-04-29T10:35:00+02:00 Fix tests for T22229 - - - - - adba68e7 by John Ericson at 2024-05-05T19:35:56-04:00 Substitute bindist files with Hadrian not configure The `ghc-toolchain` overhaul will eventually replace all this stuff with something much more cleaned up, but I think it is still worth making this sort of cleanup in the meantime so other untanglings and dead code cleaning can procede. I was able to delete a fair amount of dead code doing this too. `LLVMTarget_CPP` is renamed to / merged with `LLVMTarget` because it wasn't actually turned into a valid CPP identifier. (Original to 1345c7cc42c45e63ab1726a8fd24a7e4d4222467, actually.) Progress on #23966 Co-Authored-By: Sylvain Henry <hsyl20 at gmail.com> - - - - - 18f4ff84 by Alan Zimmerman at 2024-05-05T19:36:32-04:00 EPA: fix mkHsOpTyPV duplicating comments Closes #24753 - - - - - a19201d4 by Matthew Craven at 2024-05-06T19:54:29-04:00 Add test cases for #24664 ...since none are present in the original MR !12463 fixing this issue. - - - - - 46328a49 by Alan Zimmerman at 2024-05-06T19:55:05-04:00 EPA: preserve comments in data decls Closes #24771 - - - - - 3b51995c by Andrei Borzenkov at 2024-05-07T14:39:40-04:00 Rename Solo# data constructor to MkSolo# (#24673) - data Solo# a = (# a #) + data Solo# a = MkSolo# a And `(# foo #)` syntax now becomes just a syntactic sugar for `MkSolo# a`. - - - - - 4d59abf2 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Add the cmm_cpp_is_gcc predicate to the testsuite A future C-- test called T24474-cmm-override-g0 relies on the GCC-specific behaviour of -g3 implying -dD, which, in turn, leads to it emitting #defines past the preprocessing stage. Clang, at least, does not do this, so the test would fail if ran on Clang. As the behaviour here being tested is ``-optCmmP-g3'' undoing effects of the workaround we apply as a fix for bug #24474, and the workaround was for GCC-specific behaviour, the test needs to be marked as fragile on other compilers. - - - - - 25b0b404 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Split out the C-- preprocessor, and make it pass -g0 Previously, C-- was processed with the C preprocessor program. This means that it inherited flags passed via -optc. A flag that is somewhat often passed through -optc is -g. At certain -g levels (>=2), GCC starts emitting defines *after* preprocessing, for the purposes of debug info generation. This is not useful for the C-- compiler, and, in fact, causes lexer errors. We can suppress this effect (safely, if supported) via -g0. As a workaround, in older versions of GCC (<=10), GCC only emitted defines if a certain set of -g*3 flags was passed. Newer versions check the debug level. For the former, we filter out those -g*3 flags and, for the latter, we specify -g0 on top of that. As a compatible and effective solution, this change adds a C-- preprocessor distinct from the C compiler and preprocessor, but that keeps its flags. The command line produced for C-- preprocessing now looks like: $pgmCmmP $optCs_without_g3 $g0_if_supported $optCmmP Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/24474 - - - - - 9b4129a5 by Andreas Klebinger at 2024-05-08T13:24:20-04:00 -fprof-late: Only insert cost centres on functions/non-workfree cafs. They are usually useless and doing so for data values comes with a large compile time/code size overhead. Fixes #24103 - - - - - 259b63d3 by Sebastian Graf at 2024-05-08T13:24:57-04:00 Simplifier: Preserve OccInfo on DataAlt fields when case binder is dead (#24770) See the adjusted `Note [DataAlt occ info]`. This change also has a positive repercussion on `Note [Combine case alts: awkward corner]`. Fixes #24770. We now try not to call `dataConRepStrictness` in `adjustFieldsIdInfo` when all fields are lazy anyway, leading to a 2% ghc/alloc decrease in T9675. Metric Decrease: T9675 - - - - - 31b28cdb by Sebastian Graf at 2024-05-08T13:24:57-04:00 Kill seqRule, discard dead seq# in Prep (#24334) Discarding seq#s in Core land via `seqRule` was problematic; see #24334. So instead we discard certain dead, discardable seq#s in Prep now. See the updated `Note [seq# magic]`. This fixes the symptoms of #24334. - - - - - b2682534 by Rodrigo Mesquita at 2024-05-10T01:47:51-04:00 Document NcgImpl methods Fixes #19914 - - - - - 4d3acbcf by Zejun Wu at 2024-05-10T01:48:28-04:00 Make renamer to be more flexible with parens in the LHS of the rules We used to reject LHS like `(f a) b` in RULES and requires it to be written as `f a b`. It will be handy to allow both as the expression may be more readable with extra parens in some cases when infix operator is involved. Espceially when TemplateHaskell is used, extra parens may be added out of user's control and result in "valid" rules being rejected and there are not always ways to workaround it. Fixes #24621 - - - - - ab840ce6 by Ben Gamari at 2024-05-10T01:49:04-04:00 IPE: Eliminate dependency on Read Instead of encoding the closure type as decimal string we now simply represent it as an integer, eliminating the need for `Read` in `GHC.Internal.InfoProv.Types.peekInfoProv`. Closes #24504. ------------------------- Metric Decrease: T24602_perf_size size_hello_artifact ------------------------- - - - - - a9979f55 by Cheng Shao at 2024-05-10T01:49:43-04:00 testsuite: fix testwsdeque with recent clang This patch fixes compilation of testwsdeque.c with recent versions of clang, which will fail with the error below: ``` testwsdeque.c:95:33: error: warning: format specifies type 'long' but the argument has type 'void *' [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~~ ^ testwsdeque.c:95:39: error: warning: format specifies type 'int' but the argument has type 'StgWord' (aka 'unsigned long') [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~ ^~~ | %lu testwsdeque.c:133:42: error: error: incompatible function pointer types passing 'void (void *)' to parameter of type 'OSThreadProc *' (aka 'void *(*)(void *)') [-Wincompatible-function-pointer-types] 133 | createOSThread(&ids[n], "thief", thief, (void*)(StgWord)n); | ^~~~~ /workspace/ghc/_build/stage1/lib/../lib/x86_64-linux-ghc-9.11.20240502/rts-1.0.2/include/rts/OSThreads.h:193:51: error: note: passing argument to parameter 'startProc' here 193 | OSThreadProc *startProc, void *param); | ^ 2 warnings and 1 error generated. ``` - - - - - c2b33fc9 by Rodrigo Mesquita at 2024-05-10T01:50:20-04:00 Rename pre-processor invocation args Small clean up. Uses proper names for the various groups of arguments that make up the pre-processor invocation. - - - - - 2b1af08b by Cheng Shao at 2024-05-10T01:50:55-04:00 ghc-heap: fix typo in ghc-heap cbits - - - - - fc2d6de1 by Jade at 2024-05-10T21:07:16-04:00 Improve performance of Data.List.sort(By) This patch improves the algorithm to sort lists in base. It does so using two strategies: 1) Use a four-way-merge instead of the 'default' two-way-merge. This is able to save comparisons and allocations. 2) Use `(>) a b` over `compare a b == GT` and allow inlining and specialization. This mainly benefits types with a fast (>). Note that this *may* break instances with a *malformed* Ord instance where `a > b` is *not* equal to `compare a b == GT`. CLC proposal: https://github.com/haskell/core-libraries-committee/issues/236 Fixes #24280 ------------------------- Metric Decrease: MultiLayerModulesTH_Make T10421 T13719 T15164 T18698a T18698b T1969 T9872a T9961 T18730 WWRec T12425 T15703 ------------------------- - - - - - 1012e8aa by Matthew Pickering at 2024-05-10T21:07:52-04:00 Revert "ghcup-metadata: Drop output_name field" This reverts commit ecbf22a6ac397a791204590f94c0afa82e29e79f. This breaks the ghcup metadata generation on the nightly jobs. - - - - - daff1e30 by Jannis at 2024-05-12T13:38:35-04:00 Division by constants optimization - - - - - 413217ba by Andreas Klebinger at 2024-05-12T13:39:11-04:00 Tidy: Add flag to expose unfoldings if they take dictionary arguments. Add the flag `-fexpose-overloaded-unfoldings` to be able to control this behaviour. For ghc's boot libraries file size grew by less than 1% when it was enabled. However I refrained from enabling it by default for now. I've also added a section on specialization more broadly to the users guide. ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot Metric Increase: T12425 T13386 hard_hole_fits ------------------------- - - - - - c5d89412 by Zubin Duggal at 2024-05-13T22:19:53-04:00 Don't store a GlobalRdrEnv in `mi_globals` for GHCi. GHCi only needs the `mi_globals` field for modules imported with :module +*SomeModule. It uses this field to make the top level environment in `SomeModule` available to the repl. By default, only the first target in the command line parameters is "star" loaded into GHCi. Other modules have to be manually "star" loaded into the repl. Storing the top level GlobalRdrEnv for each module is very wasteful, especially given that we will most likely never need most of these environments. Instead we store only the information needed to reconstruct the top level environment in a module, which is the `IfaceTopEnv` data structure, consisting of all import statements as well as all top level symbols defined in the module (not taking export lists into account) When a particular module is "star-loaded" into GHCi (as the first commandline target, or via an explicit `:module +*SomeModule`, we reconstruct the top level environment on demand using the `IfaceTopEnv`. - - - - - d65bf4a2 by Fendor at 2024-05-13T22:20:30-04:00 Add perf regression test for `-fwrite-if-simplified-core` - - - - - 2c0f8ddb by Andrei Borzenkov at 2024-05-13T22:21:07-04:00 Improve pattern to type pattern transformation (23739) `pat_to_type_pat` function now can handle more patterns: - TuplePat - ListPat - LitPat - NPat - ConPat Allowing these new constructors in type patterns significantly increases possible shapes of type patterns without `type` keyword. This patch also changes how lookups in `lookupOccRnConstr` are performed, because we need to fall back into types when we didn't find a constructor on data level to perform `ConPat` to type transformation properly. - - - - - be514bb4 by Cheng Shao at 2024-05-13T22:21:43-04:00 hadrian: fix hadrian building with ghc-9.10.1 - - - - - ad38e954 by Cheng Shao at 2024-05-13T22:21:43-04:00 linters: fix lint-whitespace compilation with ghc-9.10.1 - - - - - a593f284 by Andreas Klebinger at 2024-05-15T07:32:10-04:00 Expand the `inline` rule to look through casts/ticks. Fixes #24808 - - - - - b1e0c313 by Cheng Shao at 2024-05-15T07:32:46-04:00 testsuite: bump PartialDownSweep timeout to 5x on wasm32 - - - - - b2227487 by Fendor at 2024-05-15T17:14:06-04:00 Add Eq and Ord instance to `IfaceType` We add an `Ord` instance so that we can store `IfaceType` in a `Data.Map` container. This is required to deduplicate `IfaceType` while writing `.hi` files to disk. Deduplication has many beneficial consequences to both file size and memory usage, as the deduplication enables implicit sharing of values. See issue #24540 for more motivation. The `Ord` instance would be unnecessary if we used a `TrieMap` instead of `Data.Map` for the deduplication process. While in theory this is clerarly the better option, experiments on the agda code base showed that a `TrieMap` implementation has worse run-time performance characteristics. To the change itself, we mostly derive `Eq` and `Ord`. This requires us to change occurrences of `FastString` with `LexicalFastString`, since `FastString` has no `Ord` instance. We change the definition of `IfLclName` to a newtype of `LexicalFastString`, to make such changes in the future easier. Bump haddock submodule for IfLclName changes - - - - - d368f9a6 by Fendor at 2024-05-15T17:14:06-04:00 Move out LiteralMap to avoid cyclic module dependencies - - - - - 2fcc09fd by Fendor at 2024-05-15T17:14:06-04:00 Add deduplication table for `IfaceType` The type `IfaceType` is a highly redundant, tree-like data structure. While benchmarking, we realised that the high redundancy of `IfaceType` causes high memory consumption in GHCi sessions when byte code is embedded into the `.hi` file via `-fwrite-if-simplified-core` or `-fbyte-code-and-object-code`. Loading such `.hi` files from disk introduces many duplicates of memory expensive values in `IfaceType`, such as `IfaceTyCon`, `IfaceTyConApp`, `IA_Arg` and many more. We improve the memory behaviour of GHCi by adding an additional deduplication table for `IfaceType` to the serialisation of `ModIface`, similar to how we deduplicate `Name`s and `FastString`s. When reading the interface file back, the table allows us to automatically share identical values of `IfaceType`. To provide some numbers, we evaluated this patch on the agda code base. We loaded the full library from the `.hi` files, which contained the embedded core expressions (`-fwrite-if-simplified-core`). Before this patch: * Load time: 11.7 s, 2.5 GB maximum residency. After this patch: * Load time: 7.3 s, 1.7 GB maximum residency. This deduplication has the beneficial side effect to additionally reduce the size of the on-disk interface files tremendously. For example, on agda, we reduce the size of `.hi` files (with `-fwrite-if-simplified-core`): * Before: 101 MB on disk * Now: 24 MB on disk This has even a beneficial side effect on the cabal store. We reduce the size of the store on disk: * Before: 341 MB on disk * Now: 310 MB on disk Note, none of the dependencies have been compiled with `-fwrite-if-simplified-core`, but `IfaceType` occurs in multiple locations in a `ModIface`. We also add IfaceType deduplication table to .hie serialisation and refactor .hie file serialisation to use the same infrastrucutre as `putWithTables`. Bump haddock submodule to accomodate for changes to the deduplication table layout and binary interface. - - - - - 36aa7cf1 by Fendor at 2024-05-15T17:14:06-04:00 Add run-time configurability of `.hi` file compression Introduce the flag `-fwrite-if-compression=<n>` which allows to configure the compression level of writing .hi files. The motivation is that some deduplication operations are too expensive for the average use case. Hence, we introduce multiple compression levels with variable impact on performance, but still reduce the memory residency and `.hi` file size on disk considerably. We introduce three compression levels: * `1`: `Normal` mode. This is the least amount of compression. It deduplicates only `Name` and `FastString`s, and is naturally the fastest compression mode. * `2`: `Safe` mode. It has a noticeable impact on .hi file size and is marginally slower than `Normal` mode. In general, it should be safe to always use `Safe` mode. * `3`: `Full` deduplication mode. Deduplicate as much as we can, resulting in minimal .hi files, but at the cost of additional compilation time. Reading .hi files doesn't need to know the initial compression level, and can always deserialise a `ModIface`, as we write out a byte that indicates the next value has been deduplicated. This allows users to experiment with different compression levels for packages, without recompilation of dependencies. Note, the deduplication also has an additional side effect of reduced memory consumption to implicit sharing of deduplicated elements. See https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for example where that matters. ------------------------- Metric Decrease: MultiLayerModulesDefsGhciWithCore T16875 T21839c T24471 hard_hole_fits libdir ------------------------- - - - - - 1e63a6fb by Matthew Pickering at 2024-05-15T17:14:07-04:00 Introduce regression tests for `.hi` file sizes Add regression tests to track how `-fwrite-if-compression` levels affect the size of `.hi` files. - - - - - 639d742b by M Farkas-Dyck at 2024-05-15T17:14:49-04:00 TTG: ApplicativeStatement exist only in Rn and Tc Co-Authored-By: romes <rodrigo.m.mesquita at gmail.com> - - - - - aa7b336b by Jade at 2024-05-15T23:06:17-04:00 Documentation: Improve documentation for symbols exported from System.IO - - - - - c561de8f by Jade at 2024-05-15T23:06:54-04:00 Improve suggestions for language extensions - When suggesting Language extensions, also suggest Extensions which imply them - Suggest ExplicitForAll and GADTSyntax instead of more specific extensions - Rephrase suggestion to include the term 'Extension' - Also moves some flag specific definitions out of Session.hs into Flags.hs (#24478) Fixes: #24477 Fixes: #24448 Fixes: #10893 - - - - - 4c7ae2a1 by Andreas Klebinger at 2024-05-15T23:07:30-04:00 Testsuite: Check if llvm assembler is available for have_llvm - - - - - bc672166 by Torsten Schmits at 2024-05-15T23:08:06-04:00 refactor quadratic search in warnMissingHomeModules - - - - - 7875e8cb by Torsten Schmits at 2024-05-15T23:08:06-04:00 add test that runs MakeDepend on thousands of modules - - - - - b84b91f5 by Adam Gundry at 2024-05-16T15:32:06-04:00 Representation-polymorphic HasField (fixes #22156) This generalises the HasField class to support representation polymorphism, so that instead of type HasField :: forall {k} . k -> Type -> Type -> Constraint we have type HasField :: forall {k} {r_rep} {a_rep} . k -> TYPE r_rep -> TYPE a_rep -> Constraint - - - - - 05285090 by Matthew Pickering at 2024-05-16T15:32:43-04:00 Bump os-string submodule to 2.0.2.2 Closes #24786 - - - - - 886ab43a by Cheng Shao at 2024-05-17T01:34:50-04:00 rts: do not prefetch mark_closure bdescr in non-moving gc when ASSERTS_ENABLED This commit fixes a small an oversight in !12148: the prefetch logic in non-moving GC may trap in debug RTS because it calls Bdescr() for mark_closure which may be a static one. It's fine in non-debug RTS because even invalid bdescr addresses are prefetched, they will not cause segfaults, so this commit implements the most straightforward fix: don't prefetch mark_closure bdescr when assertions are enabled. - - - - - b38dcf39 by Teo Camarasu at 2024-05-17T01:34:50-04:00 rts: Allocate non-moving segments with megablocks Non-moving segments are 8 blocks long and need to be aligned. Previously we serviced allocations by grabbing 15 blocks, finding an aligned 8 block group in it and returning the rest. This proved to lead to high levels of fragmentation as a de-allocating a segment caused an 8 block gap to form, and this could not be reused for allocation. This patch introduces a segment allocator based around using entire megablocks to service segment allocations in bulk. When there are no free segments, we grab an entire megablock and fill it with aligned segments. As the megablock is free, we can easily guarantee alignment. Any unused segments are placed on a free list. It only makes sense to free segments in bulk when all of the segments in a megablock are freeable. After sweeping, we grab the free list, sort it, and find all groups of segments where they cover the megablock and free them. This introduces a period of time when free segments are not available to the mutator, but the risk that this would lead to excessive allocation is low. Right after sweep, we should have an abundance of partially full segments, and this pruning step is relatively quick. In implementing this we drop the logic that kept NONMOVING_MAX_FREE segments on the free list. We also introduce an eventlog event to log the amount of pruned/retained free segments. See Note [Segment allocation strategy] Resolves #24150 ------------------------- Metric Decrease: T13253 T19695 ------------------------- - - - - - 710665bd by Cheng Shao at 2024-05-17T01:35:30-04:00 rts: fix I/O manager compilation errors for win32 target This patch fixes I/O manager compilation errors for win32 target discovered when cross-compiling to win32 using recent clang: ``` rts/win32/ThrIOManager.c:117:7: error: error: call to undeclared function 'is_io_mng_native_p'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 117 | if (is_io_mng_native_p ()) { | ^ | 117 | if (is_io_mng_native_p ()) { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/fs.c:143:28: error: error: a function declaration without a prototype is deprecated in all versions of C [-Werror,-Wstrict-prototypes] 143 | int setErrNoFromWin32Error () { | ^ | void | 143 | int setErrNoFromWin32Error () { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:227:9: error: error: call to undeclared function 'interruptIOManagerEvent'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 227 | interruptIOManagerEvent (); | ^ | 227 | interruptIOManagerEvent (); | ^ rts/win32/ConsoleHandler.c:227:9: error: note: did you mean 'getIOManagerEvent'? | 227 | interruptIOManagerEvent (); | ^ rts/include/rts/IOInterface.h:27:10: error: note: 'getIOManagerEvent' declared here 27 | void * getIOManagerEvent (void); | ^ | 27 | void * getIOManagerEvent (void); | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:196:9: error: error: call to undeclared function 'setThreadLabel'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/win32/ConsoleHandler.c:196:9: error: note: did you mean 'postThreadLabel'? | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/eventlog/EventLog.h:118:6: error: note: 'postThreadLabel' declared here 118 | void postThreadLabel(Capability *cap, | ^ | 118 | void postThreadLabel(Capability *cap, | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) ``` - - - - - 28b9cee0 by Rodrigo Mesquita at 2024-05-17T01:36:05-04:00 configure: Check C99-compat for Cmm preprocessor Fixes #24815 - - - - - 8927e0c3 by Andreas Klebinger at 2024-05-17T01:36:41-04:00 Ensure `tcHasFixedRuntimeRep (# #)` returns True. - - - - - 04179044 by doyougnu at 2024-05-17T09:00:32-04:00 testsuite: make find_so regex less general Closes #24759 Background. In MR !12372 we began tracking shared object files and directories sizes for dependencies. However, this broke release builds because release builds alter the filenames swapping "in-place" for a hash. This was not considered in the MR and thus broke release pipelines. Furthermore, the rts_so test was found to be wildly varying and was therefore disabled in !12561. This commit fixes both of these issues: - fix the rts_so test by making the regex less general, now the rts_so test and all other foo.so tests must match "libHS<some-lib>-<version>-<hash|'in-place>-<ghc>". This prevents the rts_so test from accidentally matching different rts variants such as rts_threaded, which was the cause of the wild swings after !12372. - add logic to match either a hash or the string in-place. This should make the find_so function build agnostic. - - - - - 0962b50d by Andreas Klebinger at 2024-05-17T09:01:08-04:00 TagAnalysis: Treat all bottom ids as tagged during analysis. Ticket #24806 showed that we also need to treat dead end thunks as tagged during the analysis. - - - - - 7eb9f184 by Ben Gamari at 2024-05-17T11:23:37-04:00 Remove haddock submodule In preparation for merge into the GHC, as proposed in #23178. - - - - - 47b14dcc by Fendor at 2024-05-17T11:28:17-04:00 Adapt to `IfLclName` newtype changes (cherry picked from commit a711607e29b925f3d69e27c5fde4ba655c711ff1) - - - - - 6cc6681d by Fendor at 2024-05-17T11:28:17-04:00 Add IfaceType deduplication table to interface file serialisation Although we do not really need it in the interface file serialisation, as the deserialisation uses `getWithUserData`, we need to mirror the structure `getWithUserData` expects. Thus, we write essentially an empty `IfaceType` table at the end of the file, as the interface file doesn't reference `IfaceType`. (cherry picked from commit c9bc29c6a708483d2abc3d8ec9262510ce87ca61) - - - - - b9721206 by Ben Gamari at 2024-05-17T11:30:22-04:00 ghc-tags.yaml: Initial commit - - - - - 074e7d8f by Ben Gamari at 2024-05-17T11:31:29-04:00 fourmolu: Add configuration - - - - - 151b1736 by Ben Gamari at 2024-05-17T11:32:52-04:00 Makefile: Rework for use by haddock developers Previously the Makefile was present only for GHC's old make-based build system. Now since the make-based build system is gone we can use it for more useful ends. - - - - - a7dcf13b by Ben Gamari at 2024-05-17T11:36:14-04:00 Reformat with fourmolu Using previously-added configuration and `fourmolu -i .` Note that we exclude the test-cases (`./{hoogle,html-hypsrc,latex}-test`) as they are sensitive to formatting. - - - - - 0ea6017b by Ben Gamari at 2024-05-17T11:40:04-04:00 Add 'utils/haddock/' from commit 'a7dcf13bfbb97b20e75cc8ce650e2bb628db4660' git-subtree-dir: utils/haddock git-subtree-mainline: 7eb9f1849b1c72a1c61dee88462b4244550406f3 git-subtree-split: a7dcf13bfbb97b20e75cc8ce650e2bb628db4660 - - - - - aba1d304 by Hécate Moonlight at 2024-05-17T11:40:48-04:00 Add exceptions to the dangling notes list - - - - - 527bfbfb by Hécate Moonlight at 2024-05-17T11:40:52-04:00 Add haddock to the whitespace lint ignore list - - - - - 43274677 by Ben Gamari at 2024-05-17T11:41:20-04:00 git-blame-ignore-revs: Ignore haddock reformatting - - - - - 0e679e37 by Fendor at 2024-05-18T00:27:24-04:00 Pass cpp options to the CC builder in hadrian - - - - - bb40244e by Sylvain Henry at 2024-05-18T00:28:06-04:00 JS: fix allocation constant (fix #24746) - - - - - 646d30ab by Jade at 2024-05-18T19:23:31+02:00 Add highlighting for inline-code snippets in haddock - - - - - 64459a3e by Hécate Moonlight at 2024-05-19T08:42:27-04:00 haddock: Add a .readthedocs.yml file for online documentation - - - - - 7d3d9bbf by Serge S. Gulin at 2024-05-19T18:47:05+00:00 Unicode: General Category size test (related #24789) Added trivial size performance test which involves unicode general category usage via `read`. The `read` itself uses general category to detect spaces. The purpose for this test is to measure outcome of applying improvements at General Category representation in code discussed at #24789. - - - - - 8e04efcf by Alan Zimmerman at 2024-05-19T21:29:34-04:00 EPA: Remove redundant code Remove unused epAnnAnns function various cases for showAstData that no longer exist - - - - - 071d7a1e by Rodrigo Mesquita at 2024-05-20T10:55:16-04:00 Improve docs on closed type families in hs-boots Fixes #24776 - - - - - d9e2c119 by Torsten Schmits at 2024-05-20T10:55:52-04:00 Use default deviation for large-project test This new performance test has the purpose of detecting regressions in complexity in relation to the number of modules in a project, so 1% deviation is way too small to avoid false positives. - - - - - 20b0136a by Ben Gamari at 2024-05-22T00:31:39-04:00 ghcup-metadata: Various fixes from 9.10.1 Use Debian 12/x86-64, Debian 10/aarch64, and Debian 11/aarch64 bindists where possible. - - - - - 6838a7c3 by Sylvain Henry at 2024-05-22T00:32:23-04:00 Reverse arguments to stgCallocBytes (fix #24828) - - - - - f50f46c3 by Fendor at 2024-05-22T00:32:59-04:00 Add log messages for Iface serialisation compression level Fix the label of the number of 'IfaceType' entries in the log message. Add log message for the compression level that is used to serialise a an interface file. Adds `Outputable` instance for 'CompressionIFace'. - - - - - 3bad5d55 by Hécate Moonlight at 2024-05-22T00:33:40-04:00 base: Update doctests outputs ghc-internal: Update doctests outputs - - - - - 9317c6fb by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix the testsuites of the haddock-library - Apply all the metadata revisions from Hackage to the cabal file. - Fix the `ParserSpec.hs` file in the `spec` testsuite of haddock-library. - Make `CHANGES.md` an extra-doc-file instead of an extra-source-file. - - - - - 54073b02 by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix parser of @since pragma The testsuite contained tests for annotations of the form `@since foo-bar-0.5.0`, but the parser was written incorrectly. - - - - - ede6ede3 by Matthew Pickering at 2024-05-22T00:34:57-04:00 Fix nightly pages job It seems likely broken by 9f99126a which moved `index.html` from the root folder into `docs/` folder. Fixes #24840 - - - - - b7bcf729 by Cheng Shao at 2024-05-22T00:35:32-04:00 autoconf: remove unused context diff check This patch removes redundant autoconf check for the context diff program given it isn't actually been used anywhere, especially since make removal. - - - - - ea2fe66e by Hécate Moonlight at 2024-05-22T00:36:13-04:00 haddock: Rework the contributing guide - - - - - 0f302a94 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 haddock: Add module relationships diagrams of haddock-api and haddock-library - - - - - d1a9f34f by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add instructions - - - - - b880ee80 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add SVG outputs - - - - - 6d7e6ad8 by Ben Gamari at 2024-05-22T13:40:05-04:00 rts: Fix size of StgOrigThunkInfo frames Previously the entry code of the `stg_orig_thunk` frame failed to account for the size of the profiling header as it hard-coded the frame size. Fix this. Fixes #24809. - - - - - c645fe40 by Fendor at 2024-05-22T13:40:05-04:00 Add regression test T24809 for stg_orig_thunk_info_frame size - - - - - 4181aa40 by Andreas Klebinger at 2024-05-22T13:40:42-04:00 bindists: Check for existence of share folder before trying to copy it. This folder isn't distributed in windows bindists A lack of doing so resulted us copying loads of files twice. - - - - - d216510e by Matthew Pickering at 2024-05-22T13:40:42-04:00 Remove ad-hoc installation of mingw toolchain in relocatable bindists This reverts 616ac30026e8dd7d2ebb98d92dde071eedf5d951 The choice about whether to install mingw is taken in the installation makefile. This is also broken on non-windows systems. The actual issue was the EnableDistroToolchain variable wasn't declared in mk/config.mk and therefore the check to install mingw was failing. - - - - - 7b4c1998 by Cheng Shao at 2024-05-22T21:52:52-04:00 testsuite: fix T17920 for wasm backend T17920 was marked as fragile on wasm before; it can be trivially fixed by avoiding calling variadic printf() in cmm. - - - - - c739383b by Cheng Shao at 2024-05-22T21:53:29-04:00 testsuite: bump T22744 timeout to 5x - - - - - c4c6d714 by Cheng Shao at 2024-05-22T21:54:06-04:00 testsuite: don't attempt to detect host cpu features when testing cross ghc The testsuite driver CPU feature detection logic only detects host CPU and only makes sense when we are not testing a cross GHC. - - - - - 3d9e4ce6 by Simon Peyton Jones at 2024-05-22T21:54:43-04:00 Better skolemisation As #24810 showed, it is (a little) better to skolemise en-bloc, so that Note [Let-bound skolems] fires more often. See Note [Skolemisation en bloc] in GHC.Tc.Utils.Instantiate. - - - - - a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00 Add missing parenthesizePat in cvtp We need to ensure that the output of `cvtp` is parenthesized (at precedence `sigPrec`) so that any pattern signatures with a surrounding pattern signature can parse correctly. Fixes #24837. - - - - - 4bb2a7cc by Hécate Moonlight at 2024-05-22T21:55:59-04:00 [base] Document the memory overhead of ByteArray Add a diagram that shows the constituent parts of a ByteArray and their memory overhead. - - - - - 8b2a016a by Hécate Moonlight at 2024-05-22T21:56:38-04:00 Haddock: Add MR template for Haddock - - - - - ead75532 by Peter Trommler at 2024-05-23T02:28:05-04:00 PPC: Support ELF v2 on powerpc64 big-endian Detect ELF v2 on PowerPC 64-bit systems. Check for `_CALL_ELF` preprocessor macro. Fixes #21191 - - - - - 9d4c10f2 by Hécate Kleidukos at 2024-05-23T02:28:44-04:00 gitlab: Add @Kleidukos to CODEOWNERS for utils/haddock - - - - - 28e64170 by Preetham Gujjula at 2024-05-23T07:20:48-04:00 haddock: Add cabal-fmt to tools for `make style` - - - - - 00126a89 by Andrei Borzenkov at 2024-05-23T07:21:24-04:00 haddock: fix verbosity option parsing - - - - - a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00 base: specify tie-breaking behavior of min, max, and related list/Foldable functions - - - - - bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00 cmm: add word <-> double/float bitcast - closes: #25331 This is the last step in the project plan described in #25331. This commit: - adds bitcast operands for x86_64, LLVM, aarch64 - For PPC and i386 we resort to using the cmm implementations - renames conversion MachOps from Conv to Round|Truncate - - - - - f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor Some functions in StgToByteCode were filtering out void arguments. However, StgToByteCode is called after unarisation: the void arguments should have been removed earlier. Instead of filtering out, we assert that the args are non-void. - - - - - 03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor `layoutNativeCall` was always called with a `primRepCmmType platform` callback. Hence we can put it inside of `layoutNativeCall` rather than repeat it. - - - - - 27c430f3 by David Binder at 2024-05-24T07:52:38-04:00 haddock: Remove compatibility shims for GHC < 8.4 from haddock-library - - - - - 8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00 compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs This patch makes the STG->Cmm backend avoid saving foreign call target to local when there are no caller-save GlobalRegs. Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a foreign call, we unconditionally save the foreign call target to a temporary local first, then rely on cmmSink to clean it up later, which only happens with -fcmm-sink (implied by -O) and not in unoptimized code. And this is troublesome for the wasm backend NCG, which needs to infer a foreign call target symbol's type signature from the Cmm call site. Previously, the NCG has been emitting incorrect type signatures for unoptimized code, which happens to work with `wasm-ld` most of the time, but this is never future-proof against upstream toolchain updates, and it causes horrible breakages when LTO objects are included in linker input. Hence this patch. - - - - - 986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00 testsuite: add callee-no-local regression test - - - - - 52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00 Fix HasCallStack leftovers from !12514 / #24726 - - - - - c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00 user_guide: Fix typo in MultiWayIf chapter Close #24829 - - - - - bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - 1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Fix changelog reference to setBacktraceMechanismState (cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d) - - - - - 43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00 Float/double unboxed literal support for HexFloatLiterals (fix #22155) - - - - - 4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00 Improve test labels for binary interface file size tests Test labels for binary interface file sizes are hard to read and overly verbose at the same time. Extend the name for the metric title, but shorten it in the actual comparison table. - - - - - 14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00 Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present" This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa. - - - - - f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00 Fix default hyperlinked sources pattern Previously this didn't include the `%M` token which manifested as broken links to the hyperlinked sources of reexports of declarations defined in other packages. Fixes haddock#1628. (cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36) - - - - - 42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00 Make DocPaths a proper data type (cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c) - - - - - 53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00 haddock: Bump version to 2.30 (cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602) - - - - - e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00 haddock-api: allow base 4.20 and ghc 9.11 - - - - - e294f7a2 by PHO at 2024-05-24T12:17:55-04:00 Add a flag "threaded" for building haddock with the threaded RTS GHC isn't guaranteed to have a threaded RTS. There should be a way to build it with the vanilla one. (cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d) - - - - - 51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00 Update ticky counter event docs. Add the info about the info table address and json fields. Fixes #23200 - - - - - 98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00 Export extractPromotedList (#24866) This can be useful in plugins. - - - - - 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - b1d77716 by Jade at 2024-06-02T21:31:48+02:00 wip - - - - - 30 changed files: - + .git-blame-ignore-revs - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - + .gitlab/merge_request_templates/Haddock.md - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitmodules - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Config.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/AArch64/RegInfo.hs - compiler/GHC/CmmToAsm/Monad.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3b26aa6d337b541ac23d9dc6c92f0c4bbca9af23...b1d77716e8588c88168a63fee48da190337943a2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3b26aa6d337b541ac23d9dc6c92f0c4bbca9af23...b1d77716e8588c88168a63fee48da190337943a2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 2 20:18:15 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sun, 02 Jun 2024 16:18:15 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/fix-alignmentspec Message-ID: <665cd38790fe7_2bf3ff12395050a9@gitlab.mail> Cheng Shao pushed new branch wip/fix-alignmentspec at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-alignmentspec You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 2 21:16:18 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sun, 02 Jun 2024 17:16:18 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/hadrian-fix-docs Message-ID: <665ce12291e88_2bf3ff95734c10716@gitlab.mail> Cheng Shao pushed new branch wip/hadrian-fix-docs at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/hadrian-fix-docs You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 2 22:09:31 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Sun, 02 Jun 2024 18:09:31 -0400 Subject: [Git][ghc/ghc][wip/T24868] More substantial wibbles Message-ID: <665ced9b44b10_2bf3fffa68ec154e5@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24868 at Glasgow Haskell Compiler / GHC Commits: b092070b by Simon Peyton Jones at 2024-06-02T23:08:21+01:00 More substantial wibbles In particular see tidyType on ForAllTy Also error recovery for type arguments. - - - - - 30 changed files: - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Types/Name/Occurrence.hs - testsuite/tests/dependent/should_compile/T15743e.stderr - testsuite/tests/dependent/should_fail/T16326_Fail4.stderr - testsuite/tests/dependent/should_fail/T16326_Fail5.stderr - testsuite/tests/ghci/scripts/T8959.stdout - testsuite/tests/indexed-types/should_fail/T13877.stderr - testsuite/tests/indexed-types/should_fail/T14369.stderr - testsuite/tests/patsyn/should_fail/T15695.stderr - testsuite/tests/polykinds/T11520.stderr - testsuite/tests/polykinds/T14846.stderr - testsuite/tests/polykinds/T15787.stderr - testsuite/tests/polykinds/T7278.stderr - testsuite/tests/rename/should_fail/rnfail055.stderr - testsuite/tests/rep-poly/RepPolyNPlusK.stderr - testsuite/tests/th/T21050.stderr - testsuite/tests/typecheck/no_skolem_info/T13499.stderr - testsuite/tests/typecheck/no_skolem_info/T20063.stderr - testsuite/tests/typecheck/should_compile/T9834.stderr - testsuite/tests/typecheck/should_compile/tc214.stderr - testsuite/tests/typecheck/should_fail/GivenForallLoop.stderr - testsuite/tests/typecheck/should_fail/T10709.stderr - testsuite/tests/typecheck/should_fail/T10709b.stderr - testsuite/tests/typecheck/should_fail/T13909.stderr - testsuite/tests/typecheck/should_fail/T16059c.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b092070b87134f9be65e2ca81216653d7f55c43f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b092070b87134f9be65e2ca81216653d7f55c43f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 03:39:26 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sun, 02 Jun 2024 23:39:26 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: hadrian: disable PIC for in-tree GMP on wasm32 Message-ID: <665d3aee7522c_2bf3ff378ffac2737c@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 7a814245 by Alex Mason at 2024-06-02T23:39:15-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - 8303b6fd by Cheng Shao at 2024-06-02T23:39:15-04:00 testsuite: mark T7773 as fragile on wasm - - - - - 10 changed files: - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/StgToCmm/Prim.hs - hadrian/src/Settings/Builders/Configure.hs - libraries/base/tests/all.T - + testsuite/tests/driver/T24839.hs - + testsuite/tests/driver/T24839.stdout - testsuite/tests/driver/all.T - + testsuite/tests/driver/t24839_sub.S - testsuite/tests/numeric/should_run/all.T - + testsuite/tests/numeric/should_run/quotRem2Large.hs Changes: ===================================== compiler/GHC/Driver/Pipeline/Execute.hs ===================================== @@ -290,6 +290,7 @@ runGenericAsPhase :: (Logger -> DynFlags -> [Option] -> IO ()) -> [Option] -> Bo runGenericAsPhase run_as extra_opts with_cpp pipe_env hsc_env location input_fn = do let dflags = hsc_dflags hsc_env let logger = hsc_logger hsc_env + let unit_env = hsc_unit_env hsc_env let cmdline_include_paths = includePaths dflags let pic_c_flags = picCCOpts dflags @@ -300,16 +301,21 @@ runGenericAsPhase run_as extra_opts with_cpp pipe_env hsc_env location input_fn -- might be a hierarchical module. createDirectoryIfMissing True (takeDirectory output_fn) - let global_includes = [ GHC.SysTools.Option ("-I" ++ p) - | p <- includePathsGlobal cmdline_include_paths ] - let local_includes = [ GHC.SysTools.Option ("-iquote" ++ p) - | p <- includePathsQuote cmdline_include_paths ++ - includePathsQuoteImplicit cmdline_include_paths] + -- add package include paths + all_includes <- if not with_cpp + then pure [] + else do + pkg_include_dirs <- mayThrowUnitErr (collectIncludeDirs <$> preloadUnitsInfo unit_env) + let global_includes = [ GHC.SysTools.Option ("-I" ++ p) + | p <- includePathsGlobal cmdline_include_paths ++ pkg_include_dirs] + let local_includes = [ GHC.SysTools.Option ("-iquote" ++ p) + | p <- includePathsQuote cmdline_include_paths ++ includePathsQuoteImplicit cmdline_include_paths] + pure (local_includes ++ global_includes) let runAssembler inputFilename outputFilename = withAtomicRename outputFilename $ \temp_outputFilename -> run_as logger dflags - (local_includes ++ global_includes + (all_includes -- See Note [-fPIC for assembler] ++ map GHC.SysTools.Option pic_c_flags -- See Note [Produce big objects on Windows] ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1894,53 +1894,179 @@ genericWordQuotRemOp width [res_q, res_r] [arg_x, arg_y] (CmmMachOp (MO_U_Rem width) [arg_x, arg_y]) genericWordQuotRemOp _ _ _ = panic "genericWordQuotRemOp" +-- Based on the algorithm from LLVM's compiler-rt: +-- https://github.com/llvm/llvm-project/blob/7339f7ba3053db7595ece1ca5f49bd2e4c3c8305/compiler-rt/lib/builtins/udivmodti4.c#L23 +-- See that file for licensing and copyright. genericWordQuotRem2Op :: Platform -> GenericOp -genericWordQuotRem2Op platform [res_q, res_r] [arg_x_high, arg_x_low, arg_y] - = emit =<< f (widthInBits (wordWidth platform)) zero arg_x_high arg_x_low - where ty = cmmExprType platform arg_x_high - shl x i = CmmMachOp (MO_Shl (wordWidth platform)) [x, i] - shr x i = CmmMachOp (MO_U_Shr (wordWidth platform)) [x, i] - or x y = CmmMachOp (MO_Or (wordWidth platform)) [x, y] - ge x y = CmmMachOp (MO_U_Ge (wordWidth platform)) [x, y] - ne x y = CmmMachOp (MO_Ne (wordWidth platform)) [x, y] - minus x y = CmmMachOp (MO_Sub (wordWidth platform)) [x, y] - times x y = CmmMachOp (MO_Mul (wordWidth platform)) [x, y] - zero = lit 0 - one = lit 1 - negone = lit (fromIntegral (platformWordSizeInBits platform) - 1) - lit i = CmmLit (CmmInt i (wordWidth platform)) - - f :: Int -> CmmExpr -> CmmExpr -> CmmExpr -> FCode CmmAGraph - f 0 acc high _ = return (mkAssign (CmmLocal res_q) acc <*> - mkAssign (CmmLocal res_r) high) - f i acc high low = - do roverflowedBit <- newTemp ty - rhigh' <- newTemp ty - rhigh'' <- newTemp ty - rlow' <- newTemp ty - risge <- newTemp ty - racc' <- newTemp ty - let high' = CmmReg (CmmLocal rhigh') - isge = CmmReg (CmmLocal risge) - overflowedBit = CmmReg (CmmLocal roverflowedBit) - let this = catAGraphs - [mkAssign (CmmLocal roverflowedBit) - (shr high negone), - mkAssign (CmmLocal rhigh') - (or (shl high one) (shr low negone)), - mkAssign (CmmLocal rlow') - (shl low one), - mkAssign (CmmLocal risge) - (or (overflowedBit `ne` zero) - (high' `ge` arg_y)), - mkAssign (CmmLocal rhigh'') - (high' `minus` (arg_y `times` isge)), - mkAssign (CmmLocal racc') - (or (shl acc one) isge)] - rest <- f (i - 1) (CmmReg (CmmLocal racc')) - (CmmReg (CmmLocal rhigh'')) - (CmmReg (CmmLocal rlow')) - return (this <*> rest) +genericWordQuotRem2Op platform [res_q, res_r] [arg_u1, arg_u0, arg_v] + = do + -- v gets modified below based on clz v + v <- newTemp ty + emit $ mkAssign (CmmLocal v) arg_v + go arg_u1 arg_u0 v + where ty = cmmExprType platform arg_u1 + shl x i = CmmMachOp (MO_Shl (wordWidth platform)) [x, i] + shr x i = CmmMachOp (MO_U_Shr (wordWidth platform)) [x, i] + or x y = CmmMachOp (MO_Or (wordWidth platform)) [x, y] + ge x y = CmmMachOp (MO_U_Ge (wordWidth platform)) [x, y] + le x y = CmmMachOp (MO_U_Le (wordWidth platform)) [x, y] + eq x y = CmmMachOp (MO_Eq (wordWidth platform)) [x, y] + plus x y = CmmMachOp (MO_Add (wordWidth platform)) [x, y] + minus x y = CmmMachOp (MO_Sub (wordWidth platform)) [x, y] + times x y = CmmMachOp (MO_Mul (wordWidth platform)) [x, y] + udiv x y = CmmMachOp (MO_U_Quot (wordWidth platform)) [x, y] + and x y = CmmMachOp (MO_And (wordWidth platform)) [x, y] + lit i = CmmLit (CmmInt i (wordWidth platform)) + one = lit 1 + zero = lit 0 + masklow = lit ((1 `shiftL` (platformWordSizeInBits platform `div` 2)) - 1) + gotoIf pred target = emit =<< mkCmmIfGoto pred target + mkTmp ty = do + t <- newTemp ty + pure (t, CmmReg (CmmLocal t)) + infixr 8 .= + r .= e = emit $ mkAssign (CmmLocal r) e + + go :: CmmActual -> CmmActual -> LocalReg -> FCode () + go u1 u0 v = do + -- Computes (ret,r) = (u1< 0) { + -- actually if (s > 0 && s /= wordSizeInBits) { + gotoIf (s' `eq` zero) if_else + gotoIf (s' `eq` lit n_udword_bits) if_else + do + -- // Normalize the divisor. + -- v = v << s; + v .= shl v' s' + -- un64 = (u1 << s) | (u0 >> (n_udword_bits - s)); + un64 .= (u1 `shl` s') `or` (u0 `shr` (lit n_udword_bits `minus` s')) + -- un10 = u0 << s; // Shift dividend left + un10 .= shl u0 s' + emit $ mkBranch if_done + -- } else { + do + -- // Avoid undefined behavior of (u0 >> 64). + emitLabel if_else + -- un64 = u1; + un64 .= u1 + -- un10 = u0; + un10 .= u0 + s .= lit 0 -- Otherwise leads to >>/<< 64 + -- } + emitLabel if_done + + -- // Break divisor up into two 32-bit digits. + -- vn1 = v >> (n_udword_bits / 2); + vn1 .= v' `shr` lit (n_udword_bits `div` 2) + -- vn0 = v & 0xFFFFFFFF; + vn0 .= v' `and` masklow + + -- // Break right half of dividend into two digits. + -- un1 = un10 >> (n_udword_bits / 2); + un1 .= un10' `shr` lit (n_udword_bits `div` 2) + -- un0 = un10 & 0xFFFFFFFF; + un0 .= un10' `and` masklow + + -- // Compute the first quotient digit, q1. + -- q1 = un64 / vn1; + q1 .= un64' `udiv` vn1' + -- rhat = un64 - q1 * vn1; + rhat .= un64' `minus` times q1' vn1' + + while_1_entry <- newBlockId + while_1_body <- newBlockId + while_1_done <- newBlockId + -- // q1 has at most error 2. No more than 2 iterations. + -- while (q1 >= b || q1 * vn0 > b * rhat + un1) { + emitLabel while_1_entry + gotoIf (q1' `ge` lit b) while_1_body + gotoIf (le (times q1' vn0') + (times (lit b) rhat' `plus` un1')) + while_1_done + do + emitLabel while_1_body + -- q1 = q1 - 1; + q1 .= q1' `minus` one + -- rhat = rhat + vn1; + rhat .= rhat' `plus` vn1' + -- if (rhat >= b) + -- break; + gotoIf (rhat' `ge` lit b) + while_1_done + emit $ mkBranch while_1_entry + -- } + emitLabel while_1_done + + -- un21 = un64 * b + un1 - q1 * v; + un21 .= (times un64' (lit b) `plus` un1') `minus` times q1' v' + + -- // Compute the second quotient digit. + -- q0 = un21 / vn1; + q0 .= un21' `udiv` vn1' + -- rhat = un21 - q0 * vn1; + rhat .= un21' `minus` times q0' vn1' + + -- // q0 has at most error 2. No more than 2 iterations. + while_2_entry <- newBlockId + while_2_body <- newBlockId + while_2_done <- newBlockId + emitLabel while_2_entry + -- while (q0 >= b || q0 * vn0 > b * rhat + un0) { + gotoIf (q0' `ge` lit b) + while_2_body + gotoIf (le (times q0' vn0') + (times (lit b) rhat' `plus` un0')) + while_2_done + do + emitLabel while_2_body + -- q0 = q0 - 1; + q0 .= q0' `minus` one + -- rhat = rhat + vn1; + rhat .= rhat' `plus` vn1' + -- if (rhat >= b) + -- break; + gotoIf (rhat' `ge` lit b) while_2_done + emit $ mkBranch while_2_entry + -- } + emitLabel while_2_done + + -- r = (un21 * b + un0 - q0 * v) >> s; + res_r .= ((times un21' (lit b) `plus` un0') `minus` times q0' v') `shr` s' + -- return q1 * b + q0; + res_q .= times q1' (lit b) `plus` q0' genericWordQuotRem2Op _ _ _ = panic "genericWordQuotRem2Op" genericWordAdd2Op :: GenericOp ===================================== hadrian/src/Settings/Builders/Configure.hs ===================================== @@ -15,16 +15,23 @@ configureBuilderArgs = do targetPlatform <- queryTarget targetPlatformTriple buildPlatform <- queryBuild targetPlatformTriple pure $ [ "--enable-shared=no" - , "--with-pic=yes" , "--host=" ++ targetPlatform -- GMP's host is our target , "--build=" ++ buildPlatform ] + -- Disable FFT logic on wasm32, sacrifice + -- performance of multiplying very large operands + -- to save code size + <> [ "--disable-fft" | targetArch == "wasm32" ] -- Disable GMP's alloca usage on wasm32, it may -- cause stack overflow (#22602) due to the -- rather small 64KB default stack size. See -- https://gmplib.org/manual/Build-Options for -- more detailed explanation of this configure -- option. - <> [ "--enable-alloca=malloc-reentrant" | targetArch == "wasm32" ] + <> [ "--enable-alloca=malloc-notreentrant" | targetArch == "wasm32" ] + -- Enable PIC unless target is wasm32, in which + -- case we don't want libgmp.a to be bloated due + -- to PIC overhead. + <> [ "--with-pic=yes" | targetArch /= "wasm32" ] , builder (Configure libffiPath) ? do top <- expr topDirectory ===================================== libraries/base/tests/all.T ===================================== @@ -176,6 +176,7 @@ test('T7457', normal, compile_and_run, ['']) test('T7773', [when(opsys('mingw32'), skip), js_broken(22261), + when(arch('wasm32'), fragile(24928)), expect_broken_for(23272, ['ghci-opt']) # unclear ], compile_and_run, ===================================== testsuite/tests/driver/T24839.hs ===================================== @@ -0,0 +1,8 @@ +import Data.Int +import Foreign.Ptr +import Foreign.Storable + +foreign import ccall "&" foo :: Ptr Int64 + +main :: IO () +main = peek foo >>= print ===================================== testsuite/tests/driver/T24839.stdout ===================================== @@ -0,0 +1 @@ +24839 ===================================== testsuite/tests/driver/all.T ===================================== @@ -327,3 +327,4 @@ test('T23339B', [extra_files(['T23339.hs']), req_c], makefile_test, []) test('T23613', normal, compile_and_run, ['-this-unit-id=foo']) test('T23944', [unless(have_dynamic(), skip), extra_files(['T23944A.hs'])], multimod_compile, ['T23944 T23944A', '-fprefer-byte-code -fbyte-code -fno-code -dynamic-too -fwrite-interface']) test('T24286', [cxx_src, unless(have_profiling(), skip), extra_files(['T24286.cpp'])], compile, ['-prof -no-hs-main']) +test('T24839', [unless(arch('x86_64') or arch('aarch64'), skip), extra_files(["t24839_sub.S"])], compile_and_run, ['t24839_sub.S']) ===================================== testsuite/tests/driver/t24839_sub.S ===================================== @@ -0,0 +1,10 @@ +/* Note that the filename must begin with a lowercase letter, because GHC thinks it as a module name otherwise. */ +#include "ghcconfig.h" +#if LEADING_UNDERSCORE + .globl _foo +_foo: +#else + .globl foo +foo: +#endif + .quad 24839 ===================================== testsuite/tests/numeric/should_run/all.T ===================================== @@ -52,6 +52,7 @@ test('add2', normal, compile_and_run, ['-fobject-code']) test('mul2', normal, compile_and_run, ['-fobject-code']) test('mul2int', normal, compile_and_run, ['-fobject-code']) test('quotRem2', normal, compile_and_run, ['-fobject-code']) +test('quotRem2Large', normal, compile_and_run, ['-fobject-code']) test('T5863', normal, compile_and_run, ['']) test('T7014', js_skip, makefile_test, []) ===================================== testsuite/tests/numeric/should_run/quotRem2Large.hs ===================================== The diff for this file was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dd0c1732c5f51bd946ba7b79ad965af3e283e5bd...8303b6fda3e0daa15c76b7bcece977a2cd63ed60 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dd0c1732c5f51bd946ba7b79ad965af3e283e5bd...8303b6fda3e0daa15c76b7bcece977a2cd63ed60 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 06:10:56 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 03 Jun 2024 02:10:56 -0400 Subject: [Git][ghc/ghc][master] Improve performance of genericWordQuotRem2Op (#22966) Message-ID: <665d5e7020994_2bf3ff4d6840043447@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - 3 changed files: - compiler/GHC/StgToCmm/Prim.hs - testsuite/tests/numeric/should_run/all.T - + testsuite/tests/numeric/should_run/quotRem2Large.hs Changes: ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1894,53 +1894,179 @@ genericWordQuotRemOp width [res_q, res_r] [arg_x, arg_y] (CmmMachOp (MO_U_Rem width) [arg_x, arg_y]) genericWordQuotRemOp _ _ _ = panic "genericWordQuotRemOp" +-- Based on the algorithm from LLVM's compiler-rt: +-- https://github.com/llvm/llvm-project/blob/7339f7ba3053db7595ece1ca5f49bd2e4c3c8305/compiler-rt/lib/builtins/udivmodti4.c#L23 +-- See that file for licensing and copyright. genericWordQuotRem2Op :: Platform -> GenericOp -genericWordQuotRem2Op platform [res_q, res_r] [arg_x_high, arg_x_low, arg_y] - = emit =<< f (widthInBits (wordWidth platform)) zero arg_x_high arg_x_low - where ty = cmmExprType platform arg_x_high - shl x i = CmmMachOp (MO_Shl (wordWidth platform)) [x, i] - shr x i = CmmMachOp (MO_U_Shr (wordWidth platform)) [x, i] - or x y = CmmMachOp (MO_Or (wordWidth platform)) [x, y] - ge x y = CmmMachOp (MO_U_Ge (wordWidth platform)) [x, y] - ne x y = CmmMachOp (MO_Ne (wordWidth platform)) [x, y] - minus x y = CmmMachOp (MO_Sub (wordWidth platform)) [x, y] - times x y = CmmMachOp (MO_Mul (wordWidth platform)) [x, y] - zero = lit 0 - one = lit 1 - negone = lit (fromIntegral (platformWordSizeInBits platform) - 1) - lit i = CmmLit (CmmInt i (wordWidth platform)) - - f :: Int -> CmmExpr -> CmmExpr -> CmmExpr -> FCode CmmAGraph - f 0 acc high _ = return (mkAssign (CmmLocal res_q) acc <*> - mkAssign (CmmLocal res_r) high) - f i acc high low = - do roverflowedBit <- newTemp ty - rhigh' <- newTemp ty - rhigh'' <- newTemp ty - rlow' <- newTemp ty - risge <- newTemp ty - racc' <- newTemp ty - let high' = CmmReg (CmmLocal rhigh') - isge = CmmReg (CmmLocal risge) - overflowedBit = CmmReg (CmmLocal roverflowedBit) - let this = catAGraphs - [mkAssign (CmmLocal roverflowedBit) - (shr high negone), - mkAssign (CmmLocal rhigh') - (or (shl high one) (shr low negone)), - mkAssign (CmmLocal rlow') - (shl low one), - mkAssign (CmmLocal risge) - (or (overflowedBit `ne` zero) - (high' `ge` arg_y)), - mkAssign (CmmLocal rhigh'') - (high' `minus` (arg_y `times` isge)), - mkAssign (CmmLocal racc') - (or (shl acc one) isge)] - rest <- f (i - 1) (CmmReg (CmmLocal racc')) - (CmmReg (CmmLocal rhigh'')) - (CmmReg (CmmLocal rlow')) - return (this <*> rest) +genericWordQuotRem2Op platform [res_q, res_r] [arg_u1, arg_u0, arg_v] + = do + -- v gets modified below based on clz v + v <- newTemp ty + emit $ mkAssign (CmmLocal v) arg_v + go arg_u1 arg_u0 v + where ty = cmmExprType platform arg_u1 + shl x i = CmmMachOp (MO_Shl (wordWidth platform)) [x, i] + shr x i = CmmMachOp (MO_U_Shr (wordWidth platform)) [x, i] + or x y = CmmMachOp (MO_Or (wordWidth platform)) [x, y] + ge x y = CmmMachOp (MO_U_Ge (wordWidth platform)) [x, y] + le x y = CmmMachOp (MO_U_Le (wordWidth platform)) [x, y] + eq x y = CmmMachOp (MO_Eq (wordWidth platform)) [x, y] + plus x y = CmmMachOp (MO_Add (wordWidth platform)) [x, y] + minus x y = CmmMachOp (MO_Sub (wordWidth platform)) [x, y] + times x y = CmmMachOp (MO_Mul (wordWidth platform)) [x, y] + udiv x y = CmmMachOp (MO_U_Quot (wordWidth platform)) [x, y] + and x y = CmmMachOp (MO_And (wordWidth platform)) [x, y] + lit i = CmmLit (CmmInt i (wordWidth platform)) + one = lit 1 + zero = lit 0 + masklow = lit ((1 `shiftL` (platformWordSizeInBits platform `div` 2)) - 1) + gotoIf pred target = emit =<< mkCmmIfGoto pred target + mkTmp ty = do + t <- newTemp ty + pure (t, CmmReg (CmmLocal t)) + infixr 8 .= + r .= e = emit $ mkAssign (CmmLocal r) e + + go :: CmmActual -> CmmActual -> LocalReg -> FCode () + go u1 u0 v = do + -- Computes (ret,r) = (u1< 0) { + -- actually if (s > 0 && s /= wordSizeInBits) { + gotoIf (s' `eq` zero) if_else + gotoIf (s' `eq` lit n_udword_bits) if_else + do + -- // Normalize the divisor. + -- v = v << s; + v .= shl v' s' + -- un64 = (u1 << s) | (u0 >> (n_udword_bits - s)); + un64 .= (u1 `shl` s') `or` (u0 `shr` (lit n_udword_bits `minus` s')) + -- un10 = u0 << s; // Shift dividend left + un10 .= shl u0 s' + emit $ mkBranch if_done + -- } else { + do + -- // Avoid undefined behavior of (u0 >> 64). + emitLabel if_else + -- un64 = u1; + un64 .= u1 + -- un10 = u0; + un10 .= u0 + s .= lit 0 -- Otherwise leads to >>/<< 64 + -- } + emitLabel if_done + + -- // Break divisor up into two 32-bit digits. + -- vn1 = v >> (n_udword_bits / 2); + vn1 .= v' `shr` lit (n_udword_bits `div` 2) + -- vn0 = v & 0xFFFFFFFF; + vn0 .= v' `and` masklow + + -- // Break right half of dividend into two digits. + -- un1 = un10 >> (n_udword_bits / 2); + un1 .= un10' `shr` lit (n_udword_bits `div` 2) + -- un0 = un10 & 0xFFFFFFFF; + un0 .= un10' `and` masklow + + -- // Compute the first quotient digit, q1. + -- q1 = un64 / vn1; + q1 .= un64' `udiv` vn1' + -- rhat = un64 - q1 * vn1; + rhat .= un64' `minus` times q1' vn1' + + while_1_entry <- newBlockId + while_1_body <- newBlockId + while_1_done <- newBlockId + -- // q1 has at most error 2. No more than 2 iterations. + -- while (q1 >= b || q1 * vn0 > b * rhat + un1) { + emitLabel while_1_entry + gotoIf (q1' `ge` lit b) while_1_body + gotoIf (le (times q1' vn0') + (times (lit b) rhat' `plus` un1')) + while_1_done + do + emitLabel while_1_body + -- q1 = q1 - 1; + q1 .= q1' `minus` one + -- rhat = rhat + vn1; + rhat .= rhat' `plus` vn1' + -- if (rhat >= b) + -- break; + gotoIf (rhat' `ge` lit b) + while_1_done + emit $ mkBranch while_1_entry + -- } + emitLabel while_1_done + + -- un21 = un64 * b + un1 - q1 * v; + un21 .= (times un64' (lit b) `plus` un1') `minus` times q1' v' + + -- // Compute the second quotient digit. + -- q0 = un21 / vn1; + q0 .= un21' `udiv` vn1' + -- rhat = un21 - q0 * vn1; + rhat .= un21' `minus` times q0' vn1' + + -- // q0 has at most error 2. No more than 2 iterations. + while_2_entry <- newBlockId + while_2_body <- newBlockId + while_2_done <- newBlockId + emitLabel while_2_entry + -- while (q0 >= b || q0 * vn0 > b * rhat + un0) { + gotoIf (q0' `ge` lit b) + while_2_body + gotoIf (le (times q0' vn0') + (times (lit b) rhat' `plus` un0')) + while_2_done + do + emitLabel while_2_body + -- q0 = q0 - 1; + q0 .= q0' `minus` one + -- rhat = rhat + vn1; + rhat .= rhat' `plus` vn1' + -- if (rhat >= b) + -- break; + gotoIf (rhat' `ge` lit b) while_2_done + emit $ mkBranch while_2_entry + -- } + emitLabel while_2_done + + -- r = (un21 * b + un0 - q0 * v) >> s; + res_r .= ((times un21' (lit b) `plus` un0') `minus` times q0' v') `shr` s' + -- return q1 * b + q0; + res_q .= times q1' (lit b) `plus` q0' genericWordQuotRem2Op _ _ _ = panic "genericWordQuotRem2Op" genericWordAdd2Op :: GenericOp ===================================== testsuite/tests/numeric/should_run/all.T ===================================== @@ -52,6 +52,7 @@ test('add2', normal, compile_and_run, ['-fobject-code']) test('mul2', normal, compile_and_run, ['-fobject-code']) test('mul2int', normal, compile_and_run, ['-fobject-code']) test('quotRem2', normal, compile_and_run, ['-fobject-code']) +test('quotRem2Large', normal, compile_and_run, ['-fobject-code']) test('T5863', normal, compile_and_run, ['']) test('T7014', js_skip, makefile_test, []) ===================================== testsuite/tests/numeric/should_run/quotRem2Large.hs ===================================== The diff for this file was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4998a6edb61d3c3f5542106322cee56105b88f91 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4998a6edb61d3c3f5542106322cee56105b88f91 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 06:11:07 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 03 Jun 2024 02:11:07 -0400 Subject: [Git][ghc/ghc][master] testsuite: mark T7773 as fragile on wasm Message-ID: <665d5e7bce0fb_2bf3ff4daa97c43614@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - 1 changed file: - libraries/base/tests/all.T Changes: ===================================== libraries/base/tests/all.T ===================================== @@ -176,6 +176,7 @@ test('T7457', normal, compile_and_run, ['']) test('T7773', [when(opsys('mingw32'), skip), js_broken(22261), + when(arch('wasm32'), fragile(24928)), expect_broken_for(23272, ['ghci-opt']) # unclear ], compile_and_run, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ae50a8eb73a21decf3f6aa6cd9e4f236d11bdc3f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ae50a8eb73a21decf3f6aa6cd9e4f236d11bdc3f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 06:44:10 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Mon, 03 Jun 2024 02:44:10 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/fix-mingw-distro-toolchain Message-ID: <665d663a14b2c_32af32cc7e844513@gitlab.mail> Cheng Shao pushed new branch wip/fix-mingw-distro-toolchain at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-mingw-distro-toolchain You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 07:48:25 2024 From: gitlab at gitlab.haskell.org (Hannes Siebenhandl (@fendor)) Date: Mon, 03 Jun 2024 03:48:25 -0400 Subject: [Git][ghc/ghc][wip/fendor/ghc-iface-sharing-avoid-reserialisation] Avoid unneccessarily re-serialising the `ModIface` Message-ID: <665d7549a9a53_32af3a3497c53817@gitlab.mail> Hannes Siebenhandl pushed to branch wip/fendor/ghc-iface-sharing-avoid-reserialisation at Glasgow Haskell Compiler / GHC Commits: 7fcf829e by Fendor at 2024-06-03T09:39:15+02:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. - - - - - 15 changed files: - compiler/GHC.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -3,6 +3,7 @@ {-# LANGUAGE NondecreasingIndentation, ScopedTypeVariables #-} {-# LANGUAGE TupleSections, NamedFieldPuns #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE PatternSynonyms #-} -- ----------------------------------------------------------------------------- -- @@ -96,7 +97,35 @@ module GHC ( lookupGlobalName, findGlobalAnns, mkNamePprCtxForModule, - ModIface, ModIface_(..), + ModIface, + ModIface_( + mi_module, + mi_sig_of, + mi_hsc_src, + mi_src_hash, + mi_hi_bytes, + mi_deps, + mi_usages, + mi_exports, + mi_used_th, + mi_fixities, + mi_warns, + mi_anns, + mi_insts, + mi_fam_insts, + mi_rules, + mi_decls, + mi_extra_decls, + mi_top_env, + mi_hpc, + mi_trust, + mi_trust_pkg, + mi_complete_matches, + mi_docs, + mi_final_exts, + mi_ext_fields + ), + pattern ModIface, SafeHaskellMode(..), -- * Printing ===================================== compiler/GHC/Iface/Binary.hs ===================================== @@ -63,6 +63,8 @@ import Data.Map.Strict (Map) import Data.Word import System.IO.Unsafe import Data.Typeable (Typeable) +import qualified GHC.Data.Strict as Strict +import Data.Function ((&)) -- --------------------------------------------------------------------------- @@ -173,22 +175,27 @@ readBinIface profile name_cache checkHiWay traceBinIface hi_path = do mod_iface <- getIfaceWithExtFields name_cache bh - return mod_iface - { mi_src_hash = src_hash - } + return $ mod_iface + & addSourceFingerprint src_hash + getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface getIfaceWithExtFields name_cache bh = do - extFields_p <- get bh + -- Start offset for the byte array that contains the serialised 'ModIface'. + start <- tellBinReader bh + extFields_p_rel <- getRelBin bh mod_iface <- getWithUserData name_cache bh - seekBinReader bh extFields_p + seekBinReaderRel bh extFields_p_rel extFields <- get bh - pure mod_iface - { mi_ext_fields = extFields - } - + -- Store the 'ModIface' byte array, so that we can avoid serialisation if + -- the 'ModIface' isn't modified. + -- See Note [Sharing of ModIface] + modIfaceBinData <- freezeBinHandle bh start + pure $ mod_iface + & set_mi_ext_fields extFields + & set_mi_hi_bytes (FullIfaceBinHandle $ Strict.Just modIfaceBinData) -- | This performs a get action after reading the dictionary and symbol -- table. It is necessary to run this before trying to deserialise any @@ -218,7 +225,7 @@ getTables name_cache bh = do -- add it to the 'ReaderUserData' of 'ReadBinHandle'. decodeReaderTable :: Typeable a => ReaderTable a -> ReadBinHandle -> IO ReadBinHandle decodeReaderTable tbl bh0 = do - table <- Binary.forwardGet bh (getTable tbl bh0) + table <- Binary.forwardGetRel bh (getTable tbl bh0) let binaryReader = mkReaderFromTable tbl table pure $ addReaderToUserData binaryReader bh0 @@ -260,11 +267,18 @@ writeBinIface profile traceBinIface compressionLevel hi_path mod_iface = do -- And send the result to the file writeBinMem bh hi_path --- | Puts the 'ModIface' +-- | Puts the 'ModIface' to the 'WriteBinHandle'. +-- +-- This avoids serialisation of the 'ModIface' if the fields 'mi_hi_bytes' contains a +-- 'Just' value. This field is populated by reading the 'ModIface' using +-- 'getIfaceWithExtFields' and not modifying it in any way afterwards. putIfaceWithExtFields :: TraceBinIFace -> CompressionIFace -> WriteBinHandle -> ModIface -> IO () putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface = - forwardPut_ bh (\_ -> put_ bh (mi_ext_fields mod_iface)) $ do - putWithUserData traceBinIface compressionLevel bh mod_iface + case mi_hi_bytes mod_iface of + FullIfaceBinHandle Strict.Nothing -> do + forwardPutRel_ bh (\_ -> put_ bh (mi_ext_fields mod_iface)) $ do + putWithUserData traceBinIface compressionLevel bh mod_iface + FullIfaceBinHandle (Strict.Just binData) -> putFullBinData bh binData -- | Put a piece of data with an initialised `UserData` field. This -- is necessary if you want to serialise Names or FastStrings. @@ -339,7 +353,7 @@ putAllTables _ [] act = do a <- act pure ([], a) putAllTables bh (x : xs) act = do - (r, (res, a)) <- forwardPut bh (const $ putTable x bh) $ do + (r, (res, a)) <- forwardPutRel bh (const $ putTable x bh) $ do putAllTables bh xs act pure (r : res, a) @@ -491,7 +505,7 @@ to the table we need to deserialise first. What deduplication tables exist and the order of serialisation is currently statically specified in 'putWithTables'. 'putWithTables' also takes care of the serialisation of used deduplication tables. The deserialisation of the deduplication tables happens 'getTables', using 'Binary' utility -functions such as 'forwardGet'. +functions such as 'forwardGetRel'. Here, a visualisation of the table structure we currently have (ignoring 'ExtensibleFields'): @@ -592,7 +606,6 @@ initWriteIfaceType compressionLevel = do putGenericSymTab sym_tab bh ty _ -> putIfaceType bh ty - fullIfaceTypeSerialiser sym_tab bh ty = do put_ bh ifaceTypeSharedByte putGenericSymTab sym_tab bh ty ===================================== compiler/GHC/Iface/Ext/Binary.hs ===================================== @@ -228,7 +228,7 @@ readHieFileContents bh0 name_cache = do get bh1 where get_dictionary tbl bin_handle = do - fsTable <- Binary.forwardGet bin_handle (getTable tbl bin_handle) + fsTable <- Binary.forwardGetRel bin_handle (getTable tbl bin_handle) let fsReader = mkReaderFromTable tbl fsTable bhFs = addReaderToUserData fsReader bin_handle ===================================== compiler/GHC/Iface/Ext/Fields.hs ===================================== @@ -41,7 +41,7 @@ instance Binary ExtensibleFields where -- to point to the start of each payload: forM_ header_entries $ \(field_p_p, dat) -> do field_p <- tellBinWriter bh - putAt bh field_p_p field_p + putAtRel bh field_p_p field_p seekBinWriter bh field_p put_ bh dat @@ -50,11 +50,11 @@ instance Binary ExtensibleFields where -- Get the names and field pointers: header_entries <- replicateM n $ - (,) <$> get bh <*> get bh + (,) <$> get bh <*> getRelBin bh -- Seek to and get each field's payload: fields <- forM header_entries $ \(name, field_p) -> do - seekBinReader bh field_p + seekBinReaderRel bh field_p dat <- get bh return (name, dat) ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -117,6 +117,7 @@ import System.FilePath import System.Directory import GHC.Driver.Env.KnotVars import GHC.Iface.Errors.Types +import Data.Function ((&)) {- ************************************************************************ @@ -515,14 +516,12 @@ loadInterface doc_str mod from ; new_eps_anns <- tcIfaceAnnotations (mi_anns iface) ; new_eps_complete_matches <- tcIfaceCompleteMatches (mi_complete_matches iface) - ; let { final_iface = iface { - mi_decls = panic "No mi_decls in PIT", - mi_insts = panic "No mi_insts in PIT", - mi_fam_insts = panic "No mi_fam_insts in PIT", - mi_rules = panic "No mi_rules in PIT", - mi_anns = panic "No mi_anns in PIT" - } - } + ; let final_iface = iface + & set_mi_decls (panic "No mi_decls in PIT") + & set_mi_insts (panic "No mi_insts in PIT") + & set_mi_fam_insts (panic "No mi_fam_insts in PIT") + & set_mi_rules (panic "No mi_rules in PIT") + & set_mi_anns (panic "No mi_anns in PIT") ; let bad_boot = mi_boot iface == IsBoot && isJust (lookupKnotVars (if_rec_types gbl_env) mod) @@ -1018,13 +1017,13 @@ readIface dflags name_cache wanted_mod file_path = do -- See Note [GHC.Prim] in primops.txt.pp. ghcPrimIface :: ModIface ghcPrimIface - = empty_iface { - mi_exports = ghcPrimExports, - mi_decls = [], - mi_fixities = fixities, - mi_final_exts = (mi_final_exts empty_iface){ mi_fix_fn = mkIfaceFixCache fixities }, - mi_docs = Just ghcPrimDeclDocs -- See Note [GHC.Prim Docs] - } + = empty_iface + & set_mi_exports ghcPrimExports + & set_mi_decls [] + & set_mi_fixities fixities + & set_mi_final_exts ((mi_final_exts empty_iface){ mi_fix_fn = mkIfaceFixCache fixities }) + & set_mi_docs (Just ghcPrimDeclDocs) -- See Note [GHC.Prim Docs] + where empty_iface = emptyFullModIface gHC_PRIM @@ -1108,7 +1107,7 @@ pprModIfaceSimple unit_state iface = -- -- The UnitState is used to pretty-print units pprModIface :: UnitState -> ModIface -> SDoc -pprModIface unit_state iface at ModIface{ mi_final_exts = exts } +pprModIface unit_state iface = vcat [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) @@ -1149,6 +1148,7 @@ pprModIface unit_state iface at ModIface{ mi_final_exts = exts } , text "extensible fields:" $$ nest 2 (pprExtensibleFields (mi_ext_fields iface)) ] where + exts = mi_final_exts iface pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" pp_hsc_src HsSrcFile = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -145,7 +145,7 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos = do full_iface <- {-# SCC "addFingerprints" #-} - addFingerprints hsc_env partial_iface{ mi_decls = decls } + addFingerprints hsc_env (set_mi_decls decls partial_iface) -- Debug printing let unit_state = hsc_units hsc_env @@ -154,8 +154,24 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos = do final_iface <- shareIface (hsc_NC hsc_env) (flagsToIfCompression $ hsc_dflags hsc_env) full_iface return final_iface +-- | Compress an 'ModIface' and share as many values as possible, depending on the 'CompressionIFace' level. +-- See Note [Sharing of ModIface]. +-- +-- We compress the 'ModIface' by serialising the 'ModIface' to an in-memory byte array, and then deserialising it. +-- The deserialisation will deduplicate certain values depending on the 'CompressionIFace' level. +-- See Note [Deduplication during iface binary serialisation] for how we do that. +-- +-- Additionally, we cache the serialised byte array, so if the 'ModIface' is not modified +-- after calling 'shareIface', 'writeBinIface' will reuse that buffer without serialising the 'ModIface' again. +-- Modifying the 'ModIface' forces us to re-serialise it again. shareIface :: NameCache -> CompressionIFace -> ModIface -> IO ModIface -shareIface _ NormalCompression mi = pure mi +shareIface _ NormalCompression mi = do + -- In 'NormalCompression', the sharing isn't reducing the memory usage, as 'Name's and 'FastString's are + -- already shared, and at this compression level, we don't compress/share anything else. + -- Thus, for a brief moment we simply double the memory residency for no reason. + -- Therefore, we only try to share expensive values if the compression mode is higher than + -- 'NormalCompression' + pure mi shareIface nc compressionLevel mi = do bh <- openBinMem initBinMemSize start <- tellBinWriter bh @@ -163,10 +179,7 @@ shareIface nc compressionLevel mi = do rbh <- shrinkBinBuffer bh seekBinReader rbh start res <- getIfaceWithExtFields nc rbh - let resiface = res - { mi_src_hash = mi_src_hash mi - , mi_globals = mi_globals mi - } + let resiface = restoreFromOldModIface mi res forceModIface resiface return resiface @@ -327,40 +340,40 @@ mkIface_ hsc_env icomplete_matches = map mkIfaceCompleteMatch complete_matches !rdrs = maybeGlobalRdrEnv rdr_env - ModIface { - mi_module = this_mod, + emptyPartialModIface this_mod -- Need to record this because it depends on the -instantiated-with flag -- which could change - mi_sig_of = if semantic_mod == this_mod - then Nothing - else Just semantic_mod, - mi_hsc_src = hsc_src, - mi_deps = deps, - mi_usages = usages, - mi_exports = mkIfaceExports exports, + & set_mi_sig_of (if semantic_mod == this_mod + then Nothing + else Just semantic_mod) + & set_mi_hsc_src hsc_src + & set_mi_deps deps + & set_mi_usages usages + & set_mi_exports (mkIfaceExports exports) -- Sort these lexicographically, so that -- the result is stable across compilations - mi_insts = sortBy cmp_inst iface_insts, - mi_fam_insts = sortBy cmp_fam_inst iface_fam_insts, - mi_rules = sortBy cmp_rule iface_rules, - - mi_fixities = fixities, - mi_warns = warns, - mi_anns = annotations, - mi_top_env = rdrs, - mi_used_th = used_th, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_hpc = isHpcUsed hpc_info, - mi_trust = trust_info, - mi_trust_pkg = pkg_trust_req, - mi_complete_matches = icomplete_matches, - mi_docs = docs, - mi_final_exts = (), - mi_ext_fields = emptyExtensibleFields, - mi_src_hash = ms_hs_hash mod_summary - } + & set_mi_insts (sortBy cmp_inst iface_insts) + & set_mi_fam_insts (sortBy cmp_fam_inst iface_fam_insts) + & set_mi_rules (sortBy cmp_rule iface_rules) + + & set_mi_fixities fixities + & set_mi_warns warns + & set_mi_anns annotations + & set_mi_top_env rdrs + & set_mi_used_th used_th + & set_mi_decls decls + & set_mi_extra_decls extra_decls + & set_mi_hpc (isHpcUsed hpc_info) + & set_mi_trust trust_info + & set_mi_trust_pkg pkg_trust_req + & set_mi_complete_matches (icomplete_matches) + & set_mi_docs docs + & set_mi_final_exts () + & set_mi_ext_fields emptyExtensibleFields + & set_mi_src_hash (ms_hs_hash mod_summary) + & set_mi_hi_bytes PartialIfaceBinHandle + where cmp_rule = lexicalCompareFS `on` ifRuleName -- Compare these lexicographically by OccName, *not* by unique, @@ -536,3 +549,22 @@ That is, in Y, In the result of mkIfaceExports, the names are grouped by defining module, so we may need to split up a single Avail into multiple ones. -} + +{- +Note [Sharing of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +A 'ModIface' contains many duplicated values such as 'Name', 'FastString' and 'IfaceType'. +'Name's and 'FastString's are already deduplicated by default using the 'NameCache' and +'FastStringTable' respectively. +However, 'IfaceType' can be quite expensive in terms of memory usage. +To improve the sharing of 'IfaceType', we introduced deduplication tables during +serialisation of 'ModIface', see Note [Deduplication during iface binary serialisation]. + +We can improve the sharing of 'ModIface' at run-time as well, by serialising the 'ModIface' to +an in-memory buffer, and then deserialising it again. +This implicitly shares duplicated values. + +To avoid re-serialising the 'ModIface' when writing it to disk, we save the serialised 'ModIface' buffer +in 'mi_hi_bytes_' field of said 'ModIface'. This buffer is written to disk directly in 'putIfaceWithExtFields'. +If we have to modify the 'ModIface' after 'shareIface' is called, the buffer needs to be discarded. +-} ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -1281,7 +1281,8 @@ addFingerprints hsc_env iface0 , mi_fix_fn = fix_fn , mi_hash_fn = lookupOccEnv local_env } - final_iface = iface0 { mi_decls = sorted_decls, mi_extra_decls = sorted_extra_decls, mi_final_exts = final_iface_exts } + final_iface = completePartialModIface iface0 + sorted_decls sorted_extra_decls final_iface_exts -- return final_iface ===================================== compiler/GHC/Iface/Rename.hs ===================================== @@ -44,6 +44,7 @@ import GHC.Utils.Panic import qualified Data.Traversable as T import Data.IORef +import Data.Function ((&)) tcRnMsgMaybe :: IO (Either (Messages TcRnMessage) a) -> TcM a tcRnMsgMaybe do_this = do @@ -108,13 +109,14 @@ rnModIface hsc_env insts nsubst iface = deps <- rnDependencies (mi_deps iface) -- TODO: -- mi_rules - return iface { mi_module = mod - , mi_sig_of = sig_of - , mi_insts = insts - , mi_fam_insts = fams - , mi_exports = exports - , mi_decls = decls - , mi_deps = deps } + return $ iface + & set_mi_module mod + & set_mi_sig_of sig_of + & set_mi_insts insts + & set_mi_fam_insts fams + & set_mi_exports exports + & set_mi_decls decls + & set_mi_deps deps -- | Rename just the exports of a 'ModIface'. Useful when we're doing -- shaping prior to signature merging. ===================================== compiler/GHC/Tc/Errors/Hole.hs ===================================== @@ -76,7 +76,7 @@ import GHC.Tc.Utils.Unify ( tcSubTypeSigma ) import GHC.HsToCore.Docs ( extractDocs ) import GHC.Hs.Doc -import GHC.Unit.Module.ModIface ( ModIface_(..) ) +import GHC.Unit.Module.ModIface ( mi_docs ) import GHC.Iface.Load ( loadInterfaceForName ) import GHC.Builtin.Utils (knownKeyNames) ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -1562,7 +1562,8 @@ lookupDeclDoc nm = do -- Wasn't in the current module. Try searching other external ones! mIface <- getExternalModIface nm case mIface of - Just ModIface { mi_docs = Just Docs{docs_decls = dmap} } -> + Just iface + | Just Docs{docs_decls = dmap} <- mi_docs iface -> pure $ renderHsDocStrings . map hsDocString <$> lookupUniqMap dmap nm _ -> pure Nothing @@ -1578,7 +1579,8 @@ lookupArgDoc i nm = do Nothing -> do mIface <- getExternalModIface nm case mIface of - Just ModIface { mi_docs = Just Docs{docs_args = amap} } -> + Just iface + | Just Docs{docs_args = amap} <- mi_docs iface-> pure $ renderHsDocString . hsDocString <$> (lookupUniqMap amap nm >>= IntMap.lookup i) _ -> pure Nothing ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -87,6 +87,7 @@ import Control.Monad import Data.List (find) import GHC.Iface.Errors.Types +import Data.Function ((&)) checkHsigDeclM :: ModIface -> TyThing -> TyThing -> TcRn () checkHsigDeclM sig_iface sig_thing real_thing = do @@ -369,8 +370,8 @@ tcRnMergeSignatures hsc_env hpm orig_tcg_env iface = thinModIface :: [AvailInfo] -> ModIface -> ModIface thinModIface avails iface = - iface { - mi_exports = avails, + iface + & set_mi_exports avails -- mi_fixities = ..., -- mi_warns = ..., -- mi_anns = ..., @@ -378,10 +379,9 @@ thinModIface avails iface = -- perhaps there might be two IfaceTopBndr that are the same -- OccName but different Name. Requires better understanding -- of invariants here. - mi_decls = exported_decls ++ non_exported_decls ++ dfun_decls + & set_mi_decls (exported_decls ++ non_exported_decls ++ dfun_decls) -- mi_insts = ..., -- mi_fam_insts = ..., - } where decl_pred occs decl = nameOccName (ifName decl) `elemOccSet` occs filter_decls occs = filter (decl_pred occs . snd) (mi_decls iface) ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -4,10 +4,68 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE PatternSynonyms #-} + module GHC.Unit.Module.ModIface ( ModIface - , ModIface_ (..) + , ModIface_ + ( mi_module + , mi_sig_of + , mi_hsc_src + , mi_deps + , mi_usages + , mi_exports + , mi_used_th + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_extra_decls + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_hpc + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_final_exts + , mi_ext_fields + , mi_src_hash + , mi_hi_bytes + ) + , pattern ModIface + , restoreFromOldModIface + , addSourceFingerprint + , set_mi_module + , set_mi_sig_of + , set_mi_hsc_src + , set_mi_src_hash + , set_mi_hi_bytes + , set_mi_deps + , set_mi_usages + , set_mi_exports + , set_mi_used_th + , set_mi_fixities + , set_mi_warns + , set_mi_anns + , set_mi_insts + , set_mi_fam_insts + , set_mi_rules + , set_mi_decls + , set_mi_extra_decls + , set_mi_top_env + , set_mi_hpc + , set_mi_trust + , set_mi_trust_pkg + , set_mi_complete_matches + , set_mi_docs + , set_mi_final_exts + , set_mi_ext_fields + , completePartialModIface + , IfaceBinHandle(..) , PartialModIface , ModIfaceBackend (..) , IfaceDeclExts @@ -47,6 +105,7 @@ import GHC.Types.Fixity import GHC.Types.Fixity.Env import GHC.Types.HpcInfo import GHC.Types.Name +import GHC.Types.Name.Reader (IfGlobalRdrEnv) import GHC.Types.SafeHaskell import GHC.Types.SourceFile import GHC.Types.Unique.DSet @@ -59,7 +118,7 @@ import GHC.Utils.Binary import Control.DeepSeq import Control.Exception -import GHC.Types.Name.Reader (IfGlobalRdrEnv) +import qualified GHC.Data.Strict as Strict {- Note [Interface file stages] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -141,7 +200,17 @@ type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where IfaceBackendExts 'ModIfaceCore = () IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend - +-- | In-memory byte array representation of a 'ModIface'. +-- +-- See Note [Sharing of ModIface] for why we need this. +data IfaceBinHandle (phase :: ModIfacePhase) where + -- | A partial 'ModIface' cannot be serialised to disk. + PartialIfaceBinHandle :: IfaceBinHandle 'ModIfaceCore + -- | Optional 'FullBinData' that can be serialised to disk directly. + -- + -- See Note [Private fields in ModIface] for when this fields needs to be cleared + -- (e.g., set to 'Nothing'). + FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal -- | A 'ModIface' plus a 'ModDetails' summarises everything we know -- about a compiled module. The 'ModIface' is the stuff *before* linking, @@ -155,62 +224,65 @@ type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where -- -- See Note [Strictness in ModIface] to learn about why some fields are -- strict and others are not. +-- +-- See Note [Private fields in ModIface] to learn why we don't export any of the +-- fields. data ModIface_ (phase :: ModIfacePhase) - = ModIface { - mi_module :: !Module, -- ^ Name of the module we are for - mi_sig_of :: !(Maybe Module), -- ^ Are we a sig of another mod? + = PrivateModIface { + mi_module_ :: !Module, -- ^ Name of the module we are for + mi_sig_of_ :: !(Maybe Module), -- ^ Are we a sig of another mod? - mi_hsc_src :: !HscSource, -- ^ Boot? Signature? + mi_hsc_src_ :: !HscSource, -- ^ Boot? Signature? - mi_deps :: Dependencies, + mi_deps_ :: Dependencies, -- ^ The dependencies of the module. This is -- consulted for directly-imported modules, but not -- for anything else (hence lazy) - mi_usages :: [Usage], + mi_usages_ :: [Usage], -- ^ Usages; kept sorted so that it's easy to decide -- whether to write a new iface file (changing usages -- doesn't affect the hash of this module) -- NOT STRICT! we read this field lazily from the interface file -- It is *only* consulted by the recompilation checker - mi_exports :: ![IfaceExport], + mi_exports_ :: ![IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier -- Records the modules that are the declaration points for things -- exported by this module, and the 'OccName's of those things - mi_used_th :: !Bool, + mi_used_th_ :: !Bool, -- ^ Module required TH splices when it was compiled. -- This disables recompilation avoidance (see #481). - mi_fixities :: [(OccName,Fixity)], + mi_fixities_ :: [(OccName,Fixity)], -- ^ Fixities -- NOT STRICT! we read this field lazily from the interface file - mi_warns :: IfaceWarnings, + mi_warns_ :: IfaceWarnings, -- ^ Warnings -- NOT STRICT! we read this field lazily from the interface file - mi_anns :: [IfaceAnnotation], + mi_anns_ :: [IfaceAnnotation], -- ^ Annotations -- NOT STRICT! we read this field lazily from the interface file - mi_decls :: [IfaceDeclExts phase], + mi_decls_ :: [IfaceDeclExts phase], -- ^ Type, class and variable declarations -- The hash of an Id changes if its fixity or deprecations change -- (as well as its type of course) -- Ditto data constructors, class operations, except that -- the hash of the parent class/tycon changes - mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], + mi_extra_decls_ :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], -- ^ Extra variable definitions which are **NOT** exposed but when -- combined with mi_decls allows us to restart code generation. -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] - mi_top_env :: !(Maybe IfaceTopEnv), + mi_top_env_ :: !(Maybe IfaceTopEnv), -- ^ Just enough information to reconstruct the top level environment in -- the /original source/ code for this module. which -- is NOT the same as mi_exports, nor mi_decls (which @@ -226,36 +298,36 @@ data ModIface_ (phase :: ModIfacePhase) -- 'HomeModInfo', but that leads to more plumbing. -- Instance declarations and rules - mi_insts :: [IfaceClsInst], -- ^ Sorted class instance - mi_fam_insts :: [IfaceFamInst], -- ^ Sorted family instances - mi_rules :: [IfaceRule], -- ^ Sorted rules + mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance + mi_fam_insts_ :: [IfaceFamInst], -- ^ Sorted family instances + mi_rules_ :: [IfaceRule], -- ^ Sorted rules - mi_hpc :: !AnyHpcUsage, + mi_hpc_ :: !AnyHpcUsage, -- ^ True if this program uses Hpc at any point in the program. - mi_trust :: !IfaceTrustInfo, + mi_trust_ :: !IfaceTrustInfo, -- ^ Safe Haskell Trust information for this module. - mi_trust_pkg :: !Bool, + mi_trust_pkg_ :: !Bool, -- ^ Do we require the package this module resides in be trusted -- to trust this module? This is used for the situation where a -- module is Safe (so doesn't require the package be trusted -- itself) but imports some trustworthy modules from its own -- package (which does require its own package be trusted). -- See Note [Trust Own Package] in GHC.Rename.Names - mi_complete_matches :: ![IfaceCompleteMatch], + mi_complete_matches_ :: ![IfaceCompleteMatch], - mi_docs :: !(Maybe Docs), + mi_docs_ :: !(Maybe Docs), -- ^ Docstrings and related data for use by haddock, the ghci -- @:doc@ command, and other tools. -- -- @Just _@ @<=>@ the module was built with @-haddock at . - mi_final_exts :: !(IfaceBackendExts phase), + mi_final_exts_ :: !(IfaceBackendExts phase), -- ^ Either `()` or `ModIfaceBackend` for -- a fully instantiated interface. - mi_ext_fields :: !ExtensibleFields, + mi_ext_fields_ :: !ExtensibleFields, -- ^ Additional optional fields, where the Map key represents -- the field name, resulting in a (size, serialized data) pair. -- Because the data is intended to be serialized through the @@ -264,8 +336,13 @@ data ModIface_ (phase :: ModIfacePhase) -- chosen over `ByteString`s. -- - mi_src_hash :: !Fingerprint + mi_src_hash_ :: !Fingerprint, -- ^ Hash of the .hs source, used for recompilation checking. + mi_hi_bytes_ :: !(IfaceBinHandle phase) + -- ^ A serialised in-memory buffer of this 'ModIface'. + -- If this handle is given, we can avoid serialising the 'ModIface' + -- when writing this 'ModIface' to disk, and write this buffer to disk instead. + -- See Note [Sharing of ModIface]. } -- Enough information to reconstruct the top level environment for a module @@ -354,34 +431,40 @@ renameFreeHoles fhs insts = -- See Note [Strictness in ModIface] about where we use lazyPut vs put instance Binary ModIface where - put_ bh (ModIface { - mi_module = mod, - mi_sig_of = sig_of, - mi_hsc_src = hsc_src, - mi_src_hash = _src_hash, -- Don't `put_` this in the instance + put_ bh (PrivateModIface { + mi_module_ = mod, + mi_sig_of_ = sig_of, + mi_hsc_src_ = hsc_src, + mi_src_hash_ = _src_hash, -- Don't `put_` this in the instance -- because we are going to write it -- out separately in the actual file - mi_deps = deps, - mi_usages = usages, - mi_exports = exports, - mi_used_th = used_th, - mi_fixities = fixities, - mi_warns = warns, - mi_anns = anns, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_insts = insts, - mi_fam_insts = fam_insts, - mi_rules = rules, - mi_hpc = hpc_info, - mi_trust = trust, - mi_trust_pkg = trust_pkg, - mi_complete_matches = complete_matches, - mi_docs = docs, - mi_ext_fields = _ext_fields, -- Don't `put_` this in the instance so we + mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself + -- may contain an in-memory byte array buffer for this + -- 'ModIface'. If we used 'put_' on this 'ModIface', then + -- we likely have a good reason, and do not want to reuse + -- the byte array. + -- See Note [Private fields in ModIface] + mi_deps_ = deps, + mi_usages_ = usages, + mi_exports_ = exports, + mi_used_th_ = used_th, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_anns_ = anns, + mi_decls_ = decls, + mi_extra_decls_ = extra_decls, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_hpc_ = hpc_info, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, + mi_complete_matches_ = complete_matches, + mi_docs_ = docs, + mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file - mi_final_exts = ModIfaceBackend { + mi_final_exts_ = ModIfaceBackend { mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, mi_flag_hash = flag_hash, @@ -455,34 +538,39 @@ instance Binary ModIface where trust_pkg <- get bh complete_matches <- get bh docs <- lazyGetMaybe bh - return (ModIface { - mi_module = mod, - mi_sig_of = sig_of, - mi_hsc_src = hsc_src, - mi_src_hash = fingerprint0, -- placeholder because this is dealt + return (PrivateModIface { + mi_module_ = mod, + mi_sig_of_ = sig_of, + mi_hsc_src_ = hsc_src, + mi_src_hash_ = fingerprint0, -- placeholder because this is dealt -- with specially when the file is read - mi_deps = deps, - mi_usages = usages, - mi_exports = exports, - mi_used_th = used_th, - mi_anns = anns, - mi_fixities = fixities, - mi_warns = warns, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_top_env = Nothing, - mi_insts = insts, - mi_fam_insts = fam_insts, - mi_rules = rules, - mi_hpc = hpc_info, - mi_trust = trust, - mi_trust_pkg = trust_pkg, + mi_hi_bytes_ = + -- We can't populate this field here, as we are + -- missing the 'mi_ext_fields_' field, which is + -- handled in 'getIfaceWithExtFields'. + FullIfaceBinHandle Strict.Nothing, + mi_deps_ = deps, + mi_usages_ = usages, + mi_exports_ = exports, + mi_used_th_ = used_th, + mi_anns_ = anns, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_decls_ = decls, + mi_extra_decls_ = extra_decls, + mi_top_env_ = Nothing, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_hpc_ = hpc_info, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, -- And build the cached values - mi_complete_matches = complete_matches, - mi_docs = docs, - mi_ext_fields = emptyExtensibleFields, -- placeholder because this is dealt + mi_complete_matches_ = complete_matches, + mi_docs_ = docs, + mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read - mi_final_exts = ModIfaceBackend { + mi_final_exts_ = ModIfaceBackend { mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, mi_flag_hash = flag_hash, @@ -499,42 +587,46 @@ instance Binary ModIface where mi_hash_fn = mkIfaceHashCache decls }}) + -- | The original names declared of a certain module that are exported type IfaceExport = AvailInfo emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod - = ModIface { mi_module = mod, - mi_sig_of = Nothing, - mi_hsc_src = HsSrcFile, - mi_src_hash = fingerprint0, - mi_deps = noDependencies, - mi_usages = [], - mi_exports = [], - mi_used_th = False, - mi_fixities = [], - mi_warns = IfWarnSome [] [], - mi_anns = [], - mi_insts = [], - mi_fam_insts = [], - mi_rules = [], - mi_decls = [], - mi_extra_decls = Nothing, - mi_top_env = Nothing, - mi_hpc = False, - mi_trust = noIfaceTrustInfo, - mi_trust_pkg = False, - mi_complete_matches = [], - mi_docs = Nothing, - mi_final_exts = (), - mi_ext_fields = emptyExtensibleFields - } + = PrivateModIface + { mi_module_ = mod, + mi_sig_of_ = Nothing, + mi_hsc_src_ = HsSrcFile, + mi_src_hash_ = fingerprint0, + mi_hi_bytes_ = PartialIfaceBinHandle, + mi_deps_ = noDependencies, + mi_usages_ = [], + mi_exports_ = [], + mi_used_th_ = False, + mi_fixities_ = [], + mi_warns_ = IfWarnSome [] [], + mi_anns_ = [], + mi_insts_ = [], + mi_fam_insts_ = [], + mi_rules_ = [], + mi_decls_ = [], + mi_extra_decls_ = Nothing, + mi_top_env_ = Nothing, + mi_hpc_ = False, + mi_trust_ = noIfaceTrustInfo, + mi_trust_pkg_ = False, + mi_complete_matches_ = [], + mi_docs_ = Nothing, + mi_final_exts_ = (), + mi_ext_fields_ = emptyExtensibleFields + } emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) - { mi_decls = [] - , mi_final_exts = ModIfaceBackend + { mi_decls_ = [] + , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + , mi_final_exts_ = ModIfaceBackend { mi_iface_hash = fingerprint0, mi_mod_hash = fingerprint0, mi_flag_hash = fingerprint0, @@ -569,36 +661,38 @@ emptyIfaceHashCache _occ = Nothing instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (ModIface{ mi_module, mi_sig_of, mi_hsc_src, mi_deps, mi_usages - , mi_exports, mi_used_th, mi_fixities, mi_warns, mi_anns - , mi_decls, mi_extra_decls, mi_top_env, mi_insts - , mi_fam_insts, mi_rules, mi_hpc, mi_trust, mi_trust_pkg - , mi_complete_matches, mi_docs, mi_final_exts - , mi_ext_fields, mi_src_hash }) - = rnf mi_module - `seq` rnf mi_sig_of - `seq` mi_hsc_src - `seq` mi_deps - `seq` mi_usages - `seq` mi_exports - `seq` rnf mi_used_th - `seq` mi_fixities - `seq` rnf mi_warns - `seq` rnf mi_anns - `seq` rnf mi_decls - `seq` rnf mi_extra_decls - `seq` rnf mi_top_env - `seq` rnf mi_insts - `seq` rnf mi_fam_insts - `seq` rnf mi_rules - `seq` rnf mi_hpc - `seq` mi_trust - `seq` rnf mi_trust_pkg - `seq` rnf mi_complete_matches - `seq` rnf mi_docs - `seq` mi_final_exts - `seq` mi_ext_fields - `seq` rnf mi_src_hash + rnf (PrivateModIface + { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_, mi_usages_ + , mi_exports_, mi_used_th_, mi_fixities_, mi_warns_, mi_anns_ + , mi_decls_, mi_extra_decls_, mi_top_env_, mi_insts_ + , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_ + , mi_complete_matches_, mi_docs_, mi_final_exts_ + , mi_ext_fields_, mi_src_hash_ }) + = rnf mi_module_ + `seq` rnf mi_sig_of_ + `seq` mi_hsc_src_ + `seq` mi_hi_bytes_ + `seq` mi_deps_ + `seq` mi_usages_ + `seq` mi_exports_ + `seq` rnf mi_used_th_ + `seq` mi_fixities_ + `seq` rnf mi_warns_ + `seq` rnf mi_anns_ + `seq` rnf mi_decls_ + `seq` rnf mi_extra_decls_ + `seq` rnf mi_top_env_ + `seq` rnf mi_insts_ + `seq` rnf mi_fam_insts_ + `seq` rnf mi_rules_ + `seq` rnf mi_hpc_ + `seq` mi_trust_ + `seq` rnf mi_trust_pkg_ + `seq` rnf mi_complete_matches_ + `seq` rnf mi_docs_ + `seq` mi_final_exts_ + `seq` mi_ext_fields_ + `seq` rnf mi_src_hash_ `seq` () instance NFData (ModIfaceBackend) where @@ -638,5 +732,286 @@ type WhetherHasOrphans = Bool -- | Does this module define family instances? type WhetherHasFamInst = Bool +-- ---------------------------------------------------------------------------- +-- Modify a 'ModIface'. +-- ---------------------------------------------------------------------------- + +{- +Note [Private fields in ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The fields of 'ModIface' are private, e.g., not exported, to make the API +impossible to misuse. A 'ModIface' can be "compressed" in-memory using +'shareIface', which serialises the 'ModIface' to an in-memory buffer. +This has the advantage of reducing memory usage of 'ModIface', reducing the +overall memory usage of GHC. +See Note [Sharing of ModIface]. + +This in-memory buffer can be reused, if and only if the 'ModIface' is not +modified after it has been "compressed"/shared via 'shareIface'. Instead of +serialising 'ModIface', we simply write the in-memory buffer to disk directly. + +However, we can't rely that a 'ModIface' isn't modified after 'shareIface' has +been called. Thus, we make all fields of 'ModIface' private and modification +only happens via exported update functions, such as 'set_mi_decls'. +These functions unconditionally clear any in-memory buffer if used, forcing us +to serialise the 'ModIface' to disk again. +-} + +-- | Given a 'PartialModIface', turn it into a 'ModIface' by completing +-- missing fields. +completePartialModIface :: PartialModIface + -> [(Fingerprint, IfaceDecl)] + -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] + -> ModIfaceBackend + -> ModIface +completePartialModIface partial decls extra_decls final_exts = partial + { mi_decls_ = decls + , mi_extra_decls_ = extra_decls + , mi_final_exts_ = final_exts + , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + } + +-- | Add a source fingerprint to a 'ModIface_' without invalidating the byte array +-- buffer 'mi_hi_bytes'. +-- This is a variant of 'set_mi_src_hash' which does invalidate the buffer. +-- +-- The 'mi_src_hash' is computed outside of 'ModIface_' based on the 'ModSummary'. +addSourceFingerprint :: Fingerprint -> ModIface_ phase -> ModIface_ phase +addSourceFingerprint val iface = iface { mi_src_hash_ = val } + +-- | Copy fields that aren't serialised to disk to the new 'ModIface_'. +-- This includes especially hashes that are usually stored in the interface +-- file header and 'mi_top_env'. +-- +-- We need this function after calling 'shareIface', to make sure the +-- 'ModIface_' doesn't lose any information. This function does not discard +-- the in-memory byte array buffer 'mi_hi_bytes'. +restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase +restoreFromOldModIface old new = new + { mi_top_env_ = mi_top_env_ old + , mi_hsc_src_ = mi_hsc_src_ old + , mi_src_hash_ = mi_src_hash_ old + } + +set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase +set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } + +set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase +set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } + +set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase +set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } + +set_mi_src_hash :: Fingerprint -> ModIface_ phase -> ModIface_ phase +set_mi_src_hash val iface = clear_mi_hi_bytes $ iface { mi_src_hash_ = val } + +set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase +set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } + +set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase +set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } + +set_mi_usages :: [Usage] -> ModIface_ phase -> ModIface_ phase +set_mi_usages val iface = clear_mi_hi_bytes $ iface { mi_usages_ = val } +set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase +set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } + +set_mi_used_th :: Bool -> ModIface_ phase -> ModIface_ phase +set_mi_used_th val iface = clear_mi_hi_bytes $ iface { mi_used_th_ = val } + +set_mi_fixities :: [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase +set_mi_fixities val iface = clear_mi_hi_bytes $ iface { mi_fixities_ = val } + +set_mi_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase +set_mi_warns val iface = clear_mi_hi_bytes $ iface { mi_warns_ = val } + +set_mi_anns :: [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase +set_mi_anns val iface = clear_mi_hi_bytes $ iface { mi_anns_ = val } + +set_mi_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase +set_mi_insts val iface = clear_mi_hi_bytes $ iface { mi_insts_ = val } + +set_mi_fam_insts :: [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase +set_mi_fam_insts val iface = clear_mi_hi_bytes $ iface { mi_fam_insts_ = val } + +set_mi_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase +set_mi_rules val iface = clear_mi_hi_bytes $ iface { mi_rules_ = val } + +set_mi_decls :: [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase +set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls_ = val } + +set_mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase +set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val } + +set_mi_top_env :: Maybe IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } + +set_mi_hpc :: AnyHpcUsage -> ModIface_ phase -> ModIface_ phase +set_mi_hpc val iface = clear_mi_hi_bytes $ iface { mi_hpc_ = val } + +set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase +set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val } + +set_mi_trust_pkg :: Bool -> ModIface_ phase -> ModIface_ phase +set_mi_trust_pkg val iface = clear_mi_hi_bytes $ iface { mi_trust_pkg_ = val } + +set_mi_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase +set_mi_complete_matches val iface = clear_mi_hi_bytes $ iface { mi_complete_matches_ = val } + +set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase +set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } + +set_mi_final_exts :: IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase +set_mi_final_exts val iface = clear_mi_hi_bytes $ iface { mi_final_exts_ = val } + +set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase +set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } + +-- | Invalidate any byte array buffer we might have. +clear_mi_hi_bytes :: ModIface_ phase -> ModIface_ phase +clear_mi_hi_bytes iface = iface + { mi_hi_bytes_ = case mi_hi_bytes iface of + PartialIfaceBinHandle -> PartialIfaceBinHandle + FullIfaceBinHandle _ -> FullIfaceBinHandle Strict.Nothing + } + +-- ---------------------------------------------------------------------------- +-- 'ModIface' pattern synonyms to keep breakage low. +-- ---------------------------------------------------------------------------- + +{- +Note [Inline Pattern synonym of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The introduction of the 'ModIface' pattern synonym originally caused an increase +in allocated bytes in multiple performance tests. +In some benchmarks, it was a 2~3% increase. + +Without {-# INLINE ModIface #-}, the generated core reveals the reason for this increase. +We show the core for the 'mi_module' record selector: + +@ + mi_module + = \ @phase iface -> $w$mModIface iface mi_module1 + + $w$mModIface + = \ @phase iface cont -> + case iface of + { PrivateModIface a b ... z -> + cont + a + b + ... + z + } + + mi_module1 + = \ @phase + a + _ + ... + _ -> + a +@ + +Thus, we can see the '$w$mModIface' is not inlined, leading to an increase in +the allocated bytes. + +However, with the pragma, the correct core is generated: + +@ + mi_module = mi_module_ +@ + +-} +-- See Note [Inline Pattern synonym of ModIface] for why we have all these +-- inline pragmas. +{-# INLINE ModIface #-} +{-# INLINE mi_module #-} +{-# INLINE mi_sig_of #-} +{-# INLINE mi_hsc_src #-} +{-# INLINE mi_deps #-} +{-# INLINE mi_usages #-} +{-# INLINE mi_exports #-} +{-# INLINE mi_used_th #-} +{-# INLINE mi_fixities #-} +{-# INLINE mi_warns #-} +{-# INLINE mi_anns #-} +{-# INLINE mi_decls #-} +{-# INLINE mi_extra_decls #-} +{-# INLINE mi_top_env #-} +{-# INLINE mi_insts #-} +{-# INLINE mi_fam_insts #-} +{-# INLINE mi_rules #-} +{-# INLINE mi_hpc #-} +{-# INLINE mi_trust #-} +{-# INLINE mi_trust_pkg #-} +{-# INLINE mi_complete_matches #-} +{-# INLINE mi_docs #-} +{-# INLINE mi_final_exts #-} +{-# INLINE mi_ext_fields #-} +{-# INLINE mi_src_hash #-} +{-# INLINE mi_hi_bytes #-} + +pattern ModIface :: + Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] -> + [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> + [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> + Maybe IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> + AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> + IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> + ModIface_ phase +pattern ModIface + { mi_module + , mi_sig_of + , mi_hsc_src + , mi_deps + , mi_usages + , mi_exports + , mi_used_th + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_extra_decls + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_hpc + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_final_exts + , mi_ext_fields + , mi_src_hash + , mi_hi_bytes + } <- PrivateModIface + { mi_module_ = mi_module + , mi_sig_of_ = mi_sig_of + , mi_hsc_src_ = mi_hsc_src + , mi_deps_ = mi_deps + , mi_usages_ = mi_usages + , mi_exports_ = mi_exports + , mi_used_th_ = mi_used_th + , mi_fixities_ = mi_fixities + , mi_warns_ = mi_warns + , mi_anns_ = mi_anns + , mi_decls_ = mi_decls + , mi_extra_decls_ = mi_extra_decls + , mi_top_env_ = mi_top_env + , mi_insts_ = mi_insts + , mi_fam_insts_ = mi_fam_insts + , mi_rules_ = mi_rules + , mi_hpc_ = mi_hpc + , mi_trust_ = mi_trust + , mi_trust_pkg_ = mi_trust_pkg + , mi_complete_matches_ = mi_complete_matches + , mi_docs_ = mi_docs + , mi_final_exts_ = mi_final_exts + , mi_ext_fields_ = mi_ext_fields + , mi_src_hash_ = mi_src_hash + , mi_hi_bytes_ = mi_hi_bytes + } ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -19,7 +19,7 @@ -- http://www.cs.york.ac.uk/fp/nhc98/ module GHC.Utils.Binary - ( {-type-} Bin, + ( {-type-} Bin, RelBin(..), getRelBin, {-class-} Binary(..), {-type-} ReadBinHandle, WriteBinHandle, SymbolTable, Dictionary, @@ -32,6 +32,7 @@ module GHC.Utils.Binary seekBinWriter, seekBinReader, + seekBinReaderRel, tellBinReader, tellBinWriter, castBin, @@ -47,7 +48,9 @@ module GHC.Utils.Binary readBinMemN, putAt, getAt, + putAtRel, forwardPut, forwardPut_, forwardGet, + forwardPutRel, forwardPutRel_, forwardGetRel, -- * For writing instances putByte, @@ -102,6 +105,8 @@ module GHC.Utils.Binary BindingName(..), simpleBindingNameWriter, simpleBindingNameReader, + FullBinData(..), freezeBinHandle, thawBinHandle, putFullBinData, + BinArray, ) where import GHC.Prelude @@ -119,7 +124,6 @@ import GHC.Types.SrcLoc import GHC.Types.Unique import qualified GHC.Data.Strict as Strict import GHC.Utils.Outputable( JoinPointHood(..) ) -import GHC.Utils.Misc ( HasCallStack, HasDebugCallStack ) import Control.DeepSeq import Control.Monad ( when, (<$!>), unless, forM_, void ) @@ -195,6 +199,62 @@ dataHandle (BinData size bin) = do handleData :: WriteBinHandle -> IO BinData handleData (WriteBinMem _ ixr _ binr) = BinData <$> readFastMutInt ixr <*> readIORef binr +--------------------------------------------------------------- +-- FullBinData +--------------------------------------------------------------- + +-- | 'FullBinData' stores a slice to a 'BinArray'. +-- +-- It requires less memory than 'ReadBinHandle', and can be constructed from +-- a 'ReadBinHandle' via 'freezeBinHandle' and turned back into a +-- 'ReadBinHandle' using 'thawBinHandle'. +-- Additionally, the byte array slice can be put into a 'WriteBinHandle' without extra +-- conversions via 'putFullBinData'. +data FullBinData = FullBinData + { fbd_readerUserData :: ReaderUserData + -- ^ 'ReaderUserData' that can be used to resume reading. + , fbd_off_s :: {-# UNPACK #-} !Int + -- ^ start offset + , fbd_off_e :: {-# UNPACK #-} !Int + -- ^ end offset + , fbd_size :: {-# UNPACK #-} !Int + -- ^ total buffer size + , fbd_buffer :: {-# UNPACK #-} !BinArray + } + +-- Equality and Ord assume that two distinct buffers are different, even if they compare the same things. +instance Eq FullBinData where + (FullBinData _ b c d e) == (FullBinData _ b1 c1 d1 e1) = b == b1 && c == c1 && d == d1 && e == e1 + +instance Ord FullBinData where + compare (FullBinData _ b c d e) (FullBinData _ b1 c1 d1 e1) = + compare b b1 `mappend` compare c c1 `mappend` compare d d1 `mappend` compare e e1 + +-- | Write the 'FullBinData' slice into the 'WriteBinHandle'. +putFullBinData :: WriteBinHandle -> FullBinData -> IO () +putFullBinData bh (FullBinData _ o1 o2 _sz ba) = do + let sz = o2 - o1 + putPrim bh sz $ \dest -> + unsafeWithForeignPtr (ba `plusForeignPtr` o1) $ \orig -> + copyBytes dest orig sz + +-- | Freeze a 'ReadBinHandle' and a start index into a 'FullBinData'. +-- +-- 'FullBinData' stores a slice starting from the 'Bin a' location to the current +-- offset of the 'ReadBinHandle'. +freezeBinHandle :: ReadBinHandle -> Bin a -> IO FullBinData +freezeBinHandle (ReadBinMem user_data ixr sz binr) (BinPtr start) = do + ix <- readFastMutInt ixr + pure (FullBinData user_data start ix sz binr) + +-- | Turn the 'FullBinData' into a 'ReadBinHandle', setting the 'ReadBinHandle' +-- offset to the start of the 'FullBinData' and restore the 'ReaderUserData' that was +-- obtained from 'freezeBinHandle'. +thawBinHandle :: FullBinData -> IO ReadBinHandle +thawBinHandle (FullBinData user_data ix _end sz ba) = do + ixr <- newFastMutInt ix + return $ ReadBinMem user_data ixr sz ba + --------------------------------------------------------------- -- BinHandle --------------------------------------------------------------- @@ -288,9 +348,47 @@ unsafeUnpackBinBuffer (BS.BS arr len) = do newtype Bin a = BinPtr Int deriving (Eq, Ord, Show, Bounded) +-- | Like a 'Bin' but is used to store relative offset pointers. +-- Relative offset pointers store a relative location, but also contain an +-- anchor that allow to obtain the absolute offset. +data RelBin a = RelBin + { relBin_anchor :: {-# UNPACK #-} !(Bin a) + -- ^ Absolute position from where we read 'relBin_offset'. + , relBin_offset :: {-# UNPACK #-} !(RelBinPtr a) + -- ^ Relative offset to 'relBin_anchor'. + -- The absolute position of the 'RelBin' is @relBin_anchor + relBin_offset@ + } + deriving (Eq, Ord, Show, Bounded) + +-- | A 'RelBinPtr' is like a 'Bin', but contains a relative offset pointer +-- instead of an absolute offset. +newtype RelBinPtr a = RelBinPtr (Bin a) + deriving (Eq, Ord, Show, Bounded) + castBin :: Bin a -> Bin b castBin (BinPtr i) = BinPtr i +-- | Read a relative offset location and wrap it in 'RelBin'. +-- +-- The resulting 'RelBin' can be translated into an absolute offset location using +-- 'makeAbsoluteBin' +getRelBin :: ReadBinHandle -> IO (RelBin a) +getRelBin bh = do + start <- tellBinReader bh + off <- get bh + pure $ RelBin start off + +makeAbsoluteBin :: RelBin a -> Bin a +makeAbsoluteBin (RelBin (BinPtr !start) (RelBinPtr (BinPtr !offset))) = + BinPtr $ start + offset + +makeRelativeBin :: RelBin a -> RelBinPtr a +makeRelativeBin (RelBin _ offset) = offset + +toRelBin :: Bin (RelBinPtr a) -> Bin a -> RelBin a +toRelBin (BinPtr !start) (BinPtr !goal) = + RelBin (BinPtr start) (RelBinPtr $ BinPtr $ goal - start) + --------------------------------------------------------------- -- class Binary --------------------------------------------------------------- @@ -311,6 +409,9 @@ class Binary a where putAt :: Binary a => WriteBinHandle -> Bin a -> a -> IO () putAt bh p x = do seekBinWriter bh p; put_ bh x; return () +putAtRel :: WriteBinHandle -> Bin (RelBinPtr a) -> Bin a -> IO () +putAtRel bh from to = putAt bh from (makeRelativeBin $ toRelBin from to) + getAt :: Binary a => ReadBinHandle -> Bin a -> IO a getAt bh p = do seekBinReader bh p; get bh @@ -344,7 +445,7 @@ freezeWriteHandle wbm = do , rbm_arr_r = rbm_arr_r } --- Copy the BinBuffer to a new BinBuffer which is exactly the right size. +-- | Copy the BinBuffer to a new BinBuffer which is exactly the right size. -- This performs a copy of the underlying buffer. -- The buffer may be truncated if the offset is not at the end of the written -- output. @@ -398,6 +499,13 @@ seekBinReader (ReadBinMem _ ix_r sz_r _) (BinPtr !p) = do then panic "seekBinReader: seek out of range" else writeFastMutInt ix_r p +seekBinReaderRel :: ReadBinHandle -> RelBin a -> IO () +seekBinReaderRel (ReadBinMem _ ix_r sz_r _) relBin = do + let (BinPtr !p) = makeAbsoluteBin relBin + if (p > sz_r) + then panic "seekBinReaderRel: seek out of range" + else writeFastMutInt ix_r p + writeBinMem :: WriteBinHandle -> FilePath -> IO () writeBinMem (WriteBinMem _ ix_r _ arr_r) fn = do h <- openBinaryFile fn WriteMode @@ -1118,12 +1226,17 @@ instance Binary (Bin a) where put_ bh (BinPtr i) = putWord32 bh (fromIntegral i :: Word32) get bh = do i <- getWord32 bh; return (BinPtr (fromIntegral (i :: Word32))) +-- Instance uses fixed-width encoding to allow inserting +-- Bin placeholders in the stream. +instance Binary (RelBinPtr a) where + put_ bh (RelBinPtr i) = put_ bh i + get bh = RelBinPtr <$> get bh -- ----------------------------------------------------------------------------- -- Forward reading/writing --- | "forwardPut put_A put_B" outputs A after B but allows A to be read before B --- by using a forward reference +-- | @'forwardPut' put_A put_B@ outputs A after B but allows A to be read before B +-- by using a forward reference. forwardPut :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a,b) forwardPut bh put_A put_B = do -- write placeholder pointer to A @@ -1146,6 +1259,8 @@ forwardPut_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () forwardPut_ bh put_A put_B = void $ forwardPut bh put_A put_B -- | Read a value stored using a forward reference +-- +-- The forward reference is expected to be an absolute offset. forwardGet :: ReadBinHandle -> IO a -> IO a forwardGet bh get_A = do -- read forward reference @@ -1158,6 +1273,48 @@ forwardGet bh get_A = do seekBinReader bh p_a pure r +-- | @'forwardPutRel' put_A put_B@ outputs A after B but allows A to be read before B +-- by using a forward reference. +-- +-- This forward reference is a relative offset that allows us to skip over the +-- result of 'put_A'. +forwardPutRel :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a,b) +forwardPutRel bh put_A put_B = do + -- write placeholder pointer to A + pre_a <- tellBinWriter bh + put_ bh pre_a + + -- write B + r_b <- put_B + + -- update A's pointer + a <- tellBinWriter bh + putAtRel bh pre_a a + seekBinNoExpandWriter bh a + + -- write A + r_a <- put_A r_b + pure (r_a,r_b) + +-- | Like 'forwardGetRel', but discard the result. +forwardPutRel_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () +forwardPutRel_ bh put_A put_B = void $ forwardPutRel bh put_A put_B + +-- | Read a value stored using a forward reference. +-- +-- The forward reference is expected to be a relative offset. +forwardGetRel :: ReadBinHandle -> IO a -> IO a +forwardGetRel bh get_A = do + -- read forward reference + p <- getRelBin bh + -- store current position + p_a <- tellBinReader bh + -- go read the forward value, then seek back + seekBinReader bh $ makeAbsoluteBin p + r <- get_A + seekBinReader bh p_a + pure r + -- ----------------------------------------------------------------------------- -- Lazy reading/writing @@ -1167,19 +1324,19 @@ lazyPut = lazyPut' put_ lazyGet :: Binary a => ReadBinHandle -> IO a lazyGet = lazyGet' get -lazyPut' :: HasDebugCallStack => (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO () +lazyPut' :: (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO () lazyPut' f bh a = do -- output the obj with a ptr to skip over it: pre_a <- tellBinWriter bh put_ bh pre_a -- save a slot for the ptr f bh a -- dump the object q <- tellBinWriter bh -- q = ptr to after object - putAt bh pre_a q -- fill in slot before a with ptr to q + putAtRel bh pre_a q -- fill in slot before a with ptr to q seekBinWriter bh q -- finally carry on writing at q -lazyGet' :: HasDebugCallStack => (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a +lazyGet' :: (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a lazyGet' f bh = do - p <- get bh -- a BinPtr + p <- getRelBin bh -- a BinPtr p_a <- tellBinReader bh a <- unsafeInterleaveIO $ do -- NB: Use a fresh rbm_off_r variable in the child thread, for thread @@ -1188,7 +1345,7 @@ lazyGet' f bh = do let bh' = bh { rbm_off_r = off_r } seekBinReader bh' p_a f bh' - seekBinReader bh p -- skip over the object for now + seekBinReader bh (makeAbsoluteBin p) -- skip over the object for now return a -- | Serialize the constructor strictly but lazily serialize a value inside a @@ -1324,7 +1481,7 @@ mkReader f = BinaryReader -- | Find the 'BinaryReader' for the 'Binary' instance for the type identified by 'Proxy a'. -- -- If no 'BinaryReader' has been configured before, this function will panic. -findUserDataReader :: forall a . (HasCallStack, Refl.Typeable a) => Proxy a -> ReadBinHandle -> BinaryReader a +findUserDataReader :: forall a . Refl.Typeable a => Proxy a -> ReadBinHandle -> BinaryReader a findUserDataReader query bh = case Map.lookup (Refl.someTypeRep query) (ud_reader_data $ getReaderUserData bh) of Nothing -> panic $ "Failed to find BinaryReader for the key: " ++ show (Refl.someTypeRep query) @@ -1346,7 +1503,7 @@ findUserDataReader query bh = -- | Find the 'BinaryWriter' for the 'Binary' instance for the type identified by 'Proxy a'. -- -- If no 'BinaryWriter' has been configured before, this function will panic. -findUserDataWriter :: forall a . (HasCallStack, Refl.Typeable a) => Proxy a -> WriteBinHandle -> BinaryWriter a +findUserDataWriter :: forall a . Refl.Typeable a => Proxy a -> WriteBinHandle -> BinaryWriter a findUserDataWriter query bh = case Map.lookup (Refl.someTypeRep query) (ud_writer_data $ getWriterUserData bh) of Nothing -> panic $ "Failed to find BinaryWriter for the key: " ++ show (Refl.someTypeRep query) @@ -1482,13 +1639,13 @@ putGenericSymbolTable gen_sym_tab serialiser bh = do mapM_ (\n -> serialiser bh n) (reverse todo) loop snd <$> - (forwardPut bh (const $ readFastMutInt symtab_next >>= put_ bh) $ + (forwardPutRel bh (const $ readFastMutInt symtab_next >>= put_ bh) $ loop) -- | Read the elements of a 'GenericSymbolTable' from disk into a 'SymbolTable'. getGenericSymbolTable :: forall a . (ReadBinHandle -> IO a) -> ReadBinHandle -> IO (SymbolTable a) getGenericSymbolTable deserialiser bh = do - sz <- forwardGet bh (get bh) :: IO Int + sz <- forwardGetRel bh (get bh) :: IO Int mut_arr <- newArray_ (0, sz-1) :: IO (IOArray Int a) forM_ [0..(sz-1)] $ \i -> do f <- deserialiser bh ===================================== testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs ===================================== @@ -64,9 +64,10 @@ metaPlugin' _ meta = pprPanic "meta" (showAstData BlankSrcSpan BlankEpAnnotation interfaceLoadPlugin' :: [CommandLineOption] -> ModIface -> IfM lcl ModIface interfaceLoadPlugin' [name, "interface"] iface - = return $ iface { mi_exports = filter (availNotNamedAs name) - (mi_exports iface) - } + = return $ set_mi_exports (filter (availNotNamedAs name) + (mi_exports iface)) + iface + interfaceLoadPlugin' _ iface = return iface availNotNamedAs :: String -> AvailInfo -> Bool ===================================== utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs ===================================== @@ -56,7 +56,7 @@ import GHC.Types.Unique.FM import GHC.Unit.State import GHC.Utils.Binary -import GHC.Iface.Type (IfaceType, getIfaceType, putIfaceType) +import GHC.Iface.Type (IfaceType, putIfaceType) import Haddock.Options (Visibility (..)) @@ -200,7 +200,7 @@ writeInterfaceFile filename iface = do -- write the iface type pointer at the front of the file ifacetype_p <- tellBinWriter bh - putAt bh ifacetype_p_p ifacetype_p + putAtRel bh ifacetype_p_p ifacetype_p seekBinWriter bh ifacetype_p -- write the symbol table itself @@ -208,7 +208,7 @@ writeInterfaceFile filename iface = do -- write the symtab pointer at the front of the file symtab_p <- tellBinWriter bh - putAt bh symtab_p_p symtab_p + putAtRel bh symtab_p_p symtab_p seekBinWriter bh symtab_p -- write the symbol table itself @@ -218,7 +218,7 @@ writeInterfaceFile filename iface = do -- write the dictionary pointer at the fornt of the file dict_p <- tellBinWriter bh - putAt bh dict_p_p dict_p + putAtRel bh dict_p_p dict_p seekBinWriter bh dict_p -- write the dictionary itself View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7fcf829eef2b90ceb41f9e5e64b019d8614d2201 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7fcf829eef2b90ceb41f9e5e64b019d8614d2201 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 08:42:02 2024 From: gitlab at gitlab.haskell.org (Hannes Siebenhandl (@fendor)) Date: Mon, 03 Jun 2024 04:42:02 -0400 Subject: [Git][ghc/ghc][wip/fendor/ghc-iface-sharing-avoid-reserialisation] Avoid unneccessarily re-serialising the `ModIface` Message-ID: <665d81da8fb3a_32af311731d46447e@gitlab.mail> Hannes Siebenhandl pushed to branch wip/fendor/ghc-iface-sharing-avoid-reserialisation at Glasgow Haskell Compiler / GHC Commits: 1cc28d23 by Fendor at 2024-06-03T10:41:18+02:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-linux job, where the number of allocated bytes seems to be lower than in other jobs. - - - - - 15 changed files: - compiler/GHC.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -3,6 +3,7 @@ {-# LANGUAGE NondecreasingIndentation, ScopedTypeVariables #-} {-# LANGUAGE TupleSections, NamedFieldPuns #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE PatternSynonyms #-} -- ----------------------------------------------------------------------------- -- @@ -96,7 +97,35 @@ module GHC ( lookupGlobalName, findGlobalAnns, mkNamePprCtxForModule, - ModIface, ModIface_(..), + ModIface, + ModIface_( + mi_module, + mi_sig_of, + mi_hsc_src, + mi_src_hash, + mi_hi_bytes, + mi_deps, + mi_usages, + mi_exports, + mi_used_th, + mi_fixities, + mi_warns, + mi_anns, + mi_insts, + mi_fam_insts, + mi_rules, + mi_decls, + mi_extra_decls, + mi_top_env, + mi_hpc, + mi_trust, + mi_trust_pkg, + mi_complete_matches, + mi_docs, + mi_final_exts, + mi_ext_fields + ), + pattern ModIface, SafeHaskellMode(..), -- * Printing ===================================== compiler/GHC/Iface/Binary.hs ===================================== @@ -63,6 +63,8 @@ import Data.Map.Strict (Map) import Data.Word import System.IO.Unsafe import Data.Typeable (Typeable) +import qualified GHC.Data.Strict as Strict +import Data.Function ((&)) -- --------------------------------------------------------------------------- @@ -173,22 +175,27 @@ readBinIface profile name_cache checkHiWay traceBinIface hi_path = do mod_iface <- getIfaceWithExtFields name_cache bh - return mod_iface - { mi_src_hash = src_hash - } + return $ mod_iface + & addSourceFingerprint src_hash + getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface getIfaceWithExtFields name_cache bh = do - extFields_p <- get bh + -- Start offset for the byte array that contains the serialised 'ModIface'. + start <- tellBinReader bh + extFields_p_rel <- getRelBin bh mod_iface <- getWithUserData name_cache bh - seekBinReader bh extFields_p + seekBinReaderRel bh extFields_p_rel extFields <- get bh - pure mod_iface - { mi_ext_fields = extFields - } - + -- Store the 'ModIface' byte array, so that we can avoid serialisation if + -- the 'ModIface' isn't modified. + -- See Note [Sharing of ModIface] + modIfaceBinData <- freezeBinHandle bh start + pure $ mod_iface + & set_mi_ext_fields extFields + & set_mi_hi_bytes (FullIfaceBinHandle $ Strict.Just modIfaceBinData) -- | This performs a get action after reading the dictionary and symbol -- table. It is necessary to run this before trying to deserialise any @@ -218,7 +225,7 @@ getTables name_cache bh = do -- add it to the 'ReaderUserData' of 'ReadBinHandle'. decodeReaderTable :: Typeable a => ReaderTable a -> ReadBinHandle -> IO ReadBinHandle decodeReaderTable tbl bh0 = do - table <- Binary.forwardGet bh (getTable tbl bh0) + table <- Binary.forwardGetRel bh (getTable tbl bh0) let binaryReader = mkReaderFromTable tbl table pure $ addReaderToUserData binaryReader bh0 @@ -260,11 +267,18 @@ writeBinIface profile traceBinIface compressionLevel hi_path mod_iface = do -- And send the result to the file writeBinMem bh hi_path --- | Puts the 'ModIface' +-- | Puts the 'ModIface' to the 'WriteBinHandle'. +-- +-- This avoids serialisation of the 'ModIface' if the fields 'mi_hi_bytes' contains a +-- 'Just' value. This field is populated by reading the 'ModIface' using +-- 'getIfaceWithExtFields' and not modifying it in any way afterwards. putIfaceWithExtFields :: TraceBinIFace -> CompressionIFace -> WriteBinHandle -> ModIface -> IO () putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface = - forwardPut_ bh (\_ -> put_ bh (mi_ext_fields mod_iface)) $ do - putWithUserData traceBinIface compressionLevel bh mod_iface + case mi_hi_bytes mod_iface of + FullIfaceBinHandle Strict.Nothing -> do + forwardPutRel_ bh (\_ -> put_ bh (mi_ext_fields mod_iface)) $ do + putWithUserData traceBinIface compressionLevel bh mod_iface + FullIfaceBinHandle (Strict.Just binData) -> putFullBinData bh binData -- | Put a piece of data with an initialised `UserData` field. This -- is necessary if you want to serialise Names or FastStrings. @@ -339,7 +353,7 @@ putAllTables _ [] act = do a <- act pure ([], a) putAllTables bh (x : xs) act = do - (r, (res, a)) <- forwardPut bh (const $ putTable x bh) $ do + (r, (res, a)) <- forwardPutRel bh (const $ putTable x bh) $ do putAllTables bh xs act pure (r : res, a) @@ -491,7 +505,7 @@ to the table we need to deserialise first. What deduplication tables exist and the order of serialisation is currently statically specified in 'putWithTables'. 'putWithTables' also takes care of the serialisation of used deduplication tables. The deserialisation of the deduplication tables happens 'getTables', using 'Binary' utility -functions such as 'forwardGet'. +functions such as 'forwardGetRel'. Here, a visualisation of the table structure we currently have (ignoring 'ExtensibleFields'): @@ -592,7 +606,6 @@ initWriteIfaceType compressionLevel = do putGenericSymTab sym_tab bh ty _ -> putIfaceType bh ty - fullIfaceTypeSerialiser sym_tab bh ty = do put_ bh ifaceTypeSharedByte putGenericSymTab sym_tab bh ty ===================================== compiler/GHC/Iface/Ext/Binary.hs ===================================== @@ -228,7 +228,7 @@ readHieFileContents bh0 name_cache = do get bh1 where get_dictionary tbl bin_handle = do - fsTable <- Binary.forwardGet bin_handle (getTable tbl bin_handle) + fsTable <- Binary.forwardGetRel bin_handle (getTable tbl bin_handle) let fsReader = mkReaderFromTable tbl fsTable bhFs = addReaderToUserData fsReader bin_handle ===================================== compiler/GHC/Iface/Ext/Fields.hs ===================================== @@ -41,7 +41,7 @@ instance Binary ExtensibleFields where -- to point to the start of each payload: forM_ header_entries $ \(field_p_p, dat) -> do field_p <- tellBinWriter bh - putAt bh field_p_p field_p + putAtRel bh field_p_p field_p seekBinWriter bh field_p put_ bh dat @@ -50,11 +50,11 @@ instance Binary ExtensibleFields where -- Get the names and field pointers: header_entries <- replicateM n $ - (,) <$> get bh <*> get bh + (,) <$> get bh <*> getRelBin bh -- Seek to and get each field's payload: fields <- forM header_entries $ \(name, field_p) -> do - seekBinReader bh field_p + seekBinReaderRel bh field_p dat <- get bh return (name, dat) ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -117,6 +117,7 @@ import System.FilePath import System.Directory import GHC.Driver.Env.KnotVars import GHC.Iface.Errors.Types +import Data.Function ((&)) {- ************************************************************************ @@ -515,14 +516,12 @@ loadInterface doc_str mod from ; new_eps_anns <- tcIfaceAnnotations (mi_anns iface) ; new_eps_complete_matches <- tcIfaceCompleteMatches (mi_complete_matches iface) - ; let { final_iface = iface { - mi_decls = panic "No mi_decls in PIT", - mi_insts = panic "No mi_insts in PIT", - mi_fam_insts = panic "No mi_fam_insts in PIT", - mi_rules = panic "No mi_rules in PIT", - mi_anns = panic "No mi_anns in PIT" - } - } + ; let final_iface = iface + & set_mi_decls (panic "No mi_decls in PIT") + & set_mi_insts (panic "No mi_insts in PIT") + & set_mi_fam_insts (panic "No mi_fam_insts in PIT") + & set_mi_rules (panic "No mi_rules in PIT") + & set_mi_anns (panic "No mi_anns in PIT") ; let bad_boot = mi_boot iface == IsBoot && isJust (lookupKnotVars (if_rec_types gbl_env) mod) @@ -1018,13 +1017,13 @@ readIface dflags name_cache wanted_mod file_path = do -- See Note [GHC.Prim] in primops.txt.pp. ghcPrimIface :: ModIface ghcPrimIface - = empty_iface { - mi_exports = ghcPrimExports, - mi_decls = [], - mi_fixities = fixities, - mi_final_exts = (mi_final_exts empty_iface){ mi_fix_fn = mkIfaceFixCache fixities }, - mi_docs = Just ghcPrimDeclDocs -- See Note [GHC.Prim Docs] - } + = empty_iface + & set_mi_exports ghcPrimExports + & set_mi_decls [] + & set_mi_fixities fixities + & set_mi_final_exts ((mi_final_exts empty_iface){ mi_fix_fn = mkIfaceFixCache fixities }) + & set_mi_docs (Just ghcPrimDeclDocs) -- See Note [GHC.Prim Docs] + where empty_iface = emptyFullModIface gHC_PRIM @@ -1108,7 +1107,7 @@ pprModIfaceSimple unit_state iface = -- -- The UnitState is used to pretty-print units pprModIface :: UnitState -> ModIface -> SDoc -pprModIface unit_state iface at ModIface{ mi_final_exts = exts } +pprModIface unit_state iface = vcat [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) @@ -1149,6 +1148,7 @@ pprModIface unit_state iface at ModIface{ mi_final_exts = exts } , text "extensible fields:" $$ nest 2 (pprExtensibleFields (mi_ext_fields iface)) ] where + exts = mi_final_exts iface pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" pp_hsc_src HsSrcFile = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -145,7 +145,7 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos = do full_iface <- {-# SCC "addFingerprints" #-} - addFingerprints hsc_env partial_iface{ mi_decls = decls } + addFingerprints hsc_env (set_mi_decls decls partial_iface) -- Debug printing let unit_state = hsc_units hsc_env @@ -154,8 +154,24 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos = do final_iface <- shareIface (hsc_NC hsc_env) (flagsToIfCompression $ hsc_dflags hsc_env) full_iface return final_iface +-- | Compress an 'ModIface' and share as many values as possible, depending on the 'CompressionIFace' level. +-- See Note [Sharing of ModIface]. +-- +-- We compress the 'ModIface' by serialising the 'ModIface' to an in-memory byte array, and then deserialising it. +-- The deserialisation will deduplicate certain values depending on the 'CompressionIFace' level. +-- See Note [Deduplication during iface binary serialisation] for how we do that. +-- +-- Additionally, we cache the serialised byte array, so if the 'ModIface' is not modified +-- after calling 'shareIface', 'writeBinIface' will reuse that buffer without serialising the 'ModIface' again. +-- Modifying the 'ModIface' forces us to re-serialise it again. shareIface :: NameCache -> CompressionIFace -> ModIface -> IO ModIface -shareIface _ NormalCompression mi = pure mi +shareIface _ NormalCompression mi = do + -- In 'NormalCompression', the sharing isn't reducing the memory usage, as 'Name's and 'FastString's are + -- already shared, and at this compression level, we don't compress/share anything else. + -- Thus, for a brief moment we simply double the memory residency for no reason. + -- Therefore, we only try to share expensive values if the compression mode is higher than + -- 'NormalCompression' + pure mi shareIface nc compressionLevel mi = do bh <- openBinMem initBinMemSize start <- tellBinWriter bh @@ -163,10 +179,7 @@ shareIface nc compressionLevel mi = do rbh <- shrinkBinBuffer bh seekBinReader rbh start res <- getIfaceWithExtFields nc rbh - let resiface = res - { mi_src_hash = mi_src_hash mi - , mi_globals = mi_globals mi - } + let resiface = restoreFromOldModIface mi res forceModIface resiface return resiface @@ -327,40 +340,40 @@ mkIface_ hsc_env icomplete_matches = map mkIfaceCompleteMatch complete_matches !rdrs = maybeGlobalRdrEnv rdr_env - ModIface { - mi_module = this_mod, + emptyPartialModIface this_mod -- Need to record this because it depends on the -instantiated-with flag -- which could change - mi_sig_of = if semantic_mod == this_mod - then Nothing - else Just semantic_mod, - mi_hsc_src = hsc_src, - mi_deps = deps, - mi_usages = usages, - mi_exports = mkIfaceExports exports, + & set_mi_sig_of (if semantic_mod == this_mod + then Nothing + else Just semantic_mod) + & set_mi_hsc_src hsc_src + & set_mi_deps deps + & set_mi_usages usages + & set_mi_exports (mkIfaceExports exports) -- Sort these lexicographically, so that -- the result is stable across compilations - mi_insts = sortBy cmp_inst iface_insts, - mi_fam_insts = sortBy cmp_fam_inst iface_fam_insts, - mi_rules = sortBy cmp_rule iface_rules, - - mi_fixities = fixities, - mi_warns = warns, - mi_anns = annotations, - mi_top_env = rdrs, - mi_used_th = used_th, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_hpc = isHpcUsed hpc_info, - mi_trust = trust_info, - mi_trust_pkg = pkg_trust_req, - mi_complete_matches = icomplete_matches, - mi_docs = docs, - mi_final_exts = (), - mi_ext_fields = emptyExtensibleFields, - mi_src_hash = ms_hs_hash mod_summary - } + & set_mi_insts (sortBy cmp_inst iface_insts) + & set_mi_fam_insts (sortBy cmp_fam_inst iface_fam_insts) + & set_mi_rules (sortBy cmp_rule iface_rules) + + & set_mi_fixities fixities + & set_mi_warns warns + & set_mi_anns annotations + & set_mi_top_env rdrs + & set_mi_used_th used_th + & set_mi_decls decls + & set_mi_extra_decls extra_decls + & set_mi_hpc (isHpcUsed hpc_info) + & set_mi_trust trust_info + & set_mi_trust_pkg pkg_trust_req + & set_mi_complete_matches (icomplete_matches) + & set_mi_docs docs + & set_mi_final_exts () + & set_mi_ext_fields emptyExtensibleFields + & set_mi_src_hash (ms_hs_hash mod_summary) + & set_mi_hi_bytes PartialIfaceBinHandle + where cmp_rule = lexicalCompareFS `on` ifRuleName -- Compare these lexicographically by OccName, *not* by unique, @@ -536,3 +549,22 @@ That is, in Y, In the result of mkIfaceExports, the names are grouped by defining module, so we may need to split up a single Avail into multiple ones. -} + +{- +Note [Sharing of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +A 'ModIface' contains many duplicated values such as 'Name', 'FastString' and 'IfaceType'. +'Name's and 'FastString's are already deduplicated by default using the 'NameCache' and +'FastStringTable' respectively. +However, 'IfaceType' can be quite expensive in terms of memory usage. +To improve the sharing of 'IfaceType', we introduced deduplication tables during +serialisation of 'ModIface', see Note [Deduplication during iface binary serialisation]. + +We can improve the sharing of 'ModIface' at run-time as well, by serialising the 'ModIface' to +an in-memory buffer, and then deserialising it again. +This implicitly shares duplicated values. + +To avoid re-serialising the 'ModIface' when writing it to disk, we save the serialised 'ModIface' buffer +in 'mi_hi_bytes_' field of said 'ModIface'. This buffer is written to disk directly in 'putIfaceWithExtFields'. +If we have to modify the 'ModIface' after 'shareIface' is called, the buffer needs to be discarded. +-} ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -1281,7 +1281,8 @@ addFingerprints hsc_env iface0 , mi_fix_fn = fix_fn , mi_hash_fn = lookupOccEnv local_env } - final_iface = iface0 { mi_decls = sorted_decls, mi_extra_decls = sorted_extra_decls, mi_final_exts = final_iface_exts } + final_iface = completePartialModIface iface0 + sorted_decls sorted_extra_decls final_iface_exts -- return final_iface ===================================== compiler/GHC/Iface/Rename.hs ===================================== @@ -44,6 +44,7 @@ import GHC.Utils.Panic import qualified Data.Traversable as T import Data.IORef +import Data.Function ((&)) tcRnMsgMaybe :: IO (Either (Messages TcRnMessage) a) -> TcM a tcRnMsgMaybe do_this = do @@ -108,13 +109,14 @@ rnModIface hsc_env insts nsubst iface = deps <- rnDependencies (mi_deps iface) -- TODO: -- mi_rules - return iface { mi_module = mod - , mi_sig_of = sig_of - , mi_insts = insts - , mi_fam_insts = fams - , mi_exports = exports - , mi_decls = decls - , mi_deps = deps } + return $ iface + & set_mi_module mod + & set_mi_sig_of sig_of + & set_mi_insts insts + & set_mi_fam_insts fams + & set_mi_exports exports + & set_mi_decls decls + & set_mi_deps deps -- | Rename just the exports of a 'ModIface'. Useful when we're doing -- shaping prior to signature merging. ===================================== compiler/GHC/Tc/Errors/Hole.hs ===================================== @@ -76,7 +76,7 @@ import GHC.Tc.Utils.Unify ( tcSubTypeSigma ) import GHC.HsToCore.Docs ( extractDocs ) import GHC.Hs.Doc -import GHC.Unit.Module.ModIface ( ModIface_(..) ) +import GHC.Unit.Module.ModIface ( mi_docs ) import GHC.Iface.Load ( loadInterfaceForName ) import GHC.Builtin.Utils (knownKeyNames) ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -1562,7 +1562,8 @@ lookupDeclDoc nm = do -- Wasn't in the current module. Try searching other external ones! mIface <- getExternalModIface nm case mIface of - Just ModIface { mi_docs = Just Docs{docs_decls = dmap} } -> + Just iface + | Just Docs{docs_decls = dmap} <- mi_docs iface -> pure $ renderHsDocStrings . map hsDocString <$> lookupUniqMap dmap nm _ -> pure Nothing @@ -1578,7 +1579,8 @@ lookupArgDoc i nm = do Nothing -> do mIface <- getExternalModIface nm case mIface of - Just ModIface { mi_docs = Just Docs{docs_args = amap} } -> + Just iface + | Just Docs{docs_args = amap} <- mi_docs iface-> pure $ renderHsDocString . hsDocString <$> (lookupUniqMap amap nm >>= IntMap.lookup i) _ -> pure Nothing ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -87,6 +87,7 @@ import Control.Monad import Data.List (find) import GHC.Iface.Errors.Types +import Data.Function ((&)) checkHsigDeclM :: ModIface -> TyThing -> TyThing -> TcRn () checkHsigDeclM sig_iface sig_thing real_thing = do @@ -369,8 +370,8 @@ tcRnMergeSignatures hsc_env hpm orig_tcg_env iface = thinModIface :: [AvailInfo] -> ModIface -> ModIface thinModIface avails iface = - iface { - mi_exports = avails, + iface + & set_mi_exports avails -- mi_fixities = ..., -- mi_warns = ..., -- mi_anns = ..., @@ -378,10 +379,9 @@ thinModIface avails iface = -- perhaps there might be two IfaceTopBndr that are the same -- OccName but different Name. Requires better understanding -- of invariants here. - mi_decls = exported_decls ++ non_exported_decls ++ dfun_decls + & set_mi_decls (exported_decls ++ non_exported_decls ++ dfun_decls) -- mi_insts = ..., -- mi_fam_insts = ..., - } where decl_pred occs decl = nameOccName (ifName decl) `elemOccSet` occs filter_decls occs = filter (decl_pred occs . snd) (mi_decls iface) ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -4,10 +4,68 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE PatternSynonyms #-} + module GHC.Unit.Module.ModIface ( ModIface - , ModIface_ (..) + , ModIface_ + ( mi_module + , mi_sig_of + , mi_hsc_src + , mi_deps + , mi_usages + , mi_exports + , mi_used_th + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_extra_decls + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_hpc + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_final_exts + , mi_ext_fields + , mi_src_hash + , mi_hi_bytes + ) + , pattern ModIface + , restoreFromOldModIface + , addSourceFingerprint + , set_mi_module + , set_mi_sig_of + , set_mi_hsc_src + , set_mi_src_hash + , set_mi_hi_bytes + , set_mi_deps + , set_mi_usages + , set_mi_exports + , set_mi_used_th + , set_mi_fixities + , set_mi_warns + , set_mi_anns + , set_mi_insts + , set_mi_fam_insts + , set_mi_rules + , set_mi_decls + , set_mi_extra_decls + , set_mi_top_env + , set_mi_hpc + , set_mi_trust + , set_mi_trust_pkg + , set_mi_complete_matches + , set_mi_docs + , set_mi_final_exts + , set_mi_ext_fields + , completePartialModIface + , IfaceBinHandle(..) , PartialModIface , ModIfaceBackend (..) , IfaceDeclExts @@ -47,6 +105,7 @@ import GHC.Types.Fixity import GHC.Types.Fixity.Env import GHC.Types.HpcInfo import GHC.Types.Name +import GHC.Types.Name.Reader (IfGlobalRdrEnv) import GHC.Types.SafeHaskell import GHC.Types.SourceFile import GHC.Types.Unique.DSet @@ -59,7 +118,7 @@ import GHC.Utils.Binary import Control.DeepSeq import Control.Exception -import GHC.Types.Name.Reader (IfGlobalRdrEnv) +import qualified GHC.Data.Strict as Strict {- Note [Interface file stages] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -141,7 +200,17 @@ type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where IfaceBackendExts 'ModIfaceCore = () IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend - +-- | In-memory byte array representation of a 'ModIface'. +-- +-- See Note [Sharing of ModIface] for why we need this. +data IfaceBinHandle (phase :: ModIfacePhase) where + -- | A partial 'ModIface' cannot be serialised to disk. + PartialIfaceBinHandle :: IfaceBinHandle 'ModIfaceCore + -- | Optional 'FullBinData' that can be serialised to disk directly. + -- + -- See Note [Private fields in ModIface] for when this fields needs to be cleared + -- (e.g., set to 'Nothing'). + FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal -- | A 'ModIface' plus a 'ModDetails' summarises everything we know -- about a compiled module. The 'ModIface' is the stuff *before* linking, @@ -155,62 +224,65 @@ type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where -- -- See Note [Strictness in ModIface] to learn about why some fields are -- strict and others are not. +-- +-- See Note [Private fields in ModIface] to learn why we don't export any of the +-- fields. data ModIface_ (phase :: ModIfacePhase) - = ModIface { - mi_module :: !Module, -- ^ Name of the module we are for - mi_sig_of :: !(Maybe Module), -- ^ Are we a sig of another mod? + = PrivateModIface { + mi_module_ :: !Module, -- ^ Name of the module we are for + mi_sig_of_ :: !(Maybe Module), -- ^ Are we a sig of another mod? - mi_hsc_src :: !HscSource, -- ^ Boot? Signature? + mi_hsc_src_ :: !HscSource, -- ^ Boot? Signature? - mi_deps :: Dependencies, + mi_deps_ :: Dependencies, -- ^ The dependencies of the module. This is -- consulted for directly-imported modules, but not -- for anything else (hence lazy) - mi_usages :: [Usage], + mi_usages_ :: [Usage], -- ^ Usages; kept sorted so that it's easy to decide -- whether to write a new iface file (changing usages -- doesn't affect the hash of this module) -- NOT STRICT! we read this field lazily from the interface file -- It is *only* consulted by the recompilation checker - mi_exports :: ![IfaceExport], + mi_exports_ :: ![IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier -- Records the modules that are the declaration points for things -- exported by this module, and the 'OccName's of those things - mi_used_th :: !Bool, + mi_used_th_ :: !Bool, -- ^ Module required TH splices when it was compiled. -- This disables recompilation avoidance (see #481). - mi_fixities :: [(OccName,Fixity)], + mi_fixities_ :: [(OccName,Fixity)], -- ^ Fixities -- NOT STRICT! we read this field lazily from the interface file - mi_warns :: IfaceWarnings, + mi_warns_ :: IfaceWarnings, -- ^ Warnings -- NOT STRICT! we read this field lazily from the interface file - mi_anns :: [IfaceAnnotation], + mi_anns_ :: [IfaceAnnotation], -- ^ Annotations -- NOT STRICT! we read this field lazily from the interface file - mi_decls :: [IfaceDeclExts phase], + mi_decls_ :: [IfaceDeclExts phase], -- ^ Type, class and variable declarations -- The hash of an Id changes if its fixity or deprecations change -- (as well as its type of course) -- Ditto data constructors, class operations, except that -- the hash of the parent class/tycon changes - mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], + mi_extra_decls_ :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], -- ^ Extra variable definitions which are **NOT** exposed but when -- combined with mi_decls allows us to restart code generation. -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] - mi_top_env :: !(Maybe IfaceTopEnv), + mi_top_env_ :: !(Maybe IfaceTopEnv), -- ^ Just enough information to reconstruct the top level environment in -- the /original source/ code for this module. which -- is NOT the same as mi_exports, nor mi_decls (which @@ -226,36 +298,36 @@ data ModIface_ (phase :: ModIfacePhase) -- 'HomeModInfo', but that leads to more plumbing. -- Instance declarations and rules - mi_insts :: [IfaceClsInst], -- ^ Sorted class instance - mi_fam_insts :: [IfaceFamInst], -- ^ Sorted family instances - mi_rules :: [IfaceRule], -- ^ Sorted rules + mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance + mi_fam_insts_ :: [IfaceFamInst], -- ^ Sorted family instances + mi_rules_ :: [IfaceRule], -- ^ Sorted rules - mi_hpc :: !AnyHpcUsage, + mi_hpc_ :: !AnyHpcUsage, -- ^ True if this program uses Hpc at any point in the program. - mi_trust :: !IfaceTrustInfo, + mi_trust_ :: !IfaceTrustInfo, -- ^ Safe Haskell Trust information for this module. - mi_trust_pkg :: !Bool, + mi_trust_pkg_ :: !Bool, -- ^ Do we require the package this module resides in be trusted -- to trust this module? This is used for the situation where a -- module is Safe (so doesn't require the package be trusted -- itself) but imports some trustworthy modules from its own -- package (which does require its own package be trusted). -- See Note [Trust Own Package] in GHC.Rename.Names - mi_complete_matches :: ![IfaceCompleteMatch], + mi_complete_matches_ :: ![IfaceCompleteMatch], - mi_docs :: !(Maybe Docs), + mi_docs_ :: !(Maybe Docs), -- ^ Docstrings and related data for use by haddock, the ghci -- @:doc@ command, and other tools. -- -- @Just _@ @<=>@ the module was built with @-haddock at . - mi_final_exts :: !(IfaceBackendExts phase), + mi_final_exts_ :: !(IfaceBackendExts phase), -- ^ Either `()` or `ModIfaceBackend` for -- a fully instantiated interface. - mi_ext_fields :: !ExtensibleFields, + mi_ext_fields_ :: !ExtensibleFields, -- ^ Additional optional fields, where the Map key represents -- the field name, resulting in a (size, serialized data) pair. -- Because the data is intended to be serialized through the @@ -264,8 +336,13 @@ data ModIface_ (phase :: ModIfacePhase) -- chosen over `ByteString`s. -- - mi_src_hash :: !Fingerprint + mi_src_hash_ :: !Fingerprint, -- ^ Hash of the .hs source, used for recompilation checking. + mi_hi_bytes_ :: !(IfaceBinHandle phase) + -- ^ A serialised in-memory buffer of this 'ModIface'. + -- If this handle is given, we can avoid serialising the 'ModIface' + -- when writing this 'ModIface' to disk, and write this buffer to disk instead. + -- See Note [Sharing of ModIface]. } -- Enough information to reconstruct the top level environment for a module @@ -354,34 +431,40 @@ renameFreeHoles fhs insts = -- See Note [Strictness in ModIface] about where we use lazyPut vs put instance Binary ModIface where - put_ bh (ModIface { - mi_module = mod, - mi_sig_of = sig_of, - mi_hsc_src = hsc_src, - mi_src_hash = _src_hash, -- Don't `put_` this in the instance + put_ bh (PrivateModIface { + mi_module_ = mod, + mi_sig_of_ = sig_of, + mi_hsc_src_ = hsc_src, + mi_src_hash_ = _src_hash, -- Don't `put_` this in the instance -- because we are going to write it -- out separately in the actual file - mi_deps = deps, - mi_usages = usages, - mi_exports = exports, - mi_used_th = used_th, - mi_fixities = fixities, - mi_warns = warns, - mi_anns = anns, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_insts = insts, - mi_fam_insts = fam_insts, - mi_rules = rules, - mi_hpc = hpc_info, - mi_trust = trust, - mi_trust_pkg = trust_pkg, - mi_complete_matches = complete_matches, - mi_docs = docs, - mi_ext_fields = _ext_fields, -- Don't `put_` this in the instance so we + mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself + -- may contain an in-memory byte array buffer for this + -- 'ModIface'. If we used 'put_' on this 'ModIface', then + -- we likely have a good reason, and do not want to reuse + -- the byte array. + -- See Note [Private fields in ModIface] + mi_deps_ = deps, + mi_usages_ = usages, + mi_exports_ = exports, + mi_used_th_ = used_th, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_anns_ = anns, + mi_decls_ = decls, + mi_extra_decls_ = extra_decls, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_hpc_ = hpc_info, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, + mi_complete_matches_ = complete_matches, + mi_docs_ = docs, + mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file - mi_final_exts = ModIfaceBackend { + mi_final_exts_ = ModIfaceBackend { mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, mi_flag_hash = flag_hash, @@ -455,34 +538,39 @@ instance Binary ModIface where trust_pkg <- get bh complete_matches <- get bh docs <- lazyGetMaybe bh - return (ModIface { - mi_module = mod, - mi_sig_of = sig_of, - mi_hsc_src = hsc_src, - mi_src_hash = fingerprint0, -- placeholder because this is dealt + return (PrivateModIface { + mi_module_ = mod, + mi_sig_of_ = sig_of, + mi_hsc_src_ = hsc_src, + mi_src_hash_ = fingerprint0, -- placeholder because this is dealt -- with specially when the file is read - mi_deps = deps, - mi_usages = usages, - mi_exports = exports, - mi_used_th = used_th, - mi_anns = anns, - mi_fixities = fixities, - mi_warns = warns, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_top_env = Nothing, - mi_insts = insts, - mi_fam_insts = fam_insts, - mi_rules = rules, - mi_hpc = hpc_info, - mi_trust = trust, - mi_trust_pkg = trust_pkg, + mi_hi_bytes_ = + -- We can't populate this field here, as we are + -- missing the 'mi_ext_fields_' field, which is + -- handled in 'getIfaceWithExtFields'. + FullIfaceBinHandle Strict.Nothing, + mi_deps_ = deps, + mi_usages_ = usages, + mi_exports_ = exports, + mi_used_th_ = used_th, + mi_anns_ = anns, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_decls_ = decls, + mi_extra_decls_ = extra_decls, + mi_top_env_ = Nothing, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_hpc_ = hpc_info, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, -- And build the cached values - mi_complete_matches = complete_matches, - mi_docs = docs, - mi_ext_fields = emptyExtensibleFields, -- placeholder because this is dealt + mi_complete_matches_ = complete_matches, + mi_docs_ = docs, + mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read - mi_final_exts = ModIfaceBackend { + mi_final_exts_ = ModIfaceBackend { mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, mi_flag_hash = flag_hash, @@ -499,42 +587,46 @@ instance Binary ModIface where mi_hash_fn = mkIfaceHashCache decls }}) + -- | The original names declared of a certain module that are exported type IfaceExport = AvailInfo emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod - = ModIface { mi_module = mod, - mi_sig_of = Nothing, - mi_hsc_src = HsSrcFile, - mi_src_hash = fingerprint0, - mi_deps = noDependencies, - mi_usages = [], - mi_exports = [], - mi_used_th = False, - mi_fixities = [], - mi_warns = IfWarnSome [] [], - mi_anns = [], - mi_insts = [], - mi_fam_insts = [], - mi_rules = [], - mi_decls = [], - mi_extra_decls = Nothing, - mi_top_env = Nothing, - mi_hpc = False, - mi_trust = noIfaceTrustInfo, - mi_trust_pkg = False, - mi_complete_matches = [], - mi_docs = Nothing, - mi_final_exts = (), - mi_ext_fields = emptyExtensibleFields - } + = PrivateModIface + { mi_module_ = mod, + mi_sig_of_ = Nothing, + mi_hsc_src_ = HsSrcFile, + mi_src_hash_ = fingerprint0, + mi_hi_bytes_ = PartialIfaceBinHandle, + mi_deps_ = noDependencies, + mi_usages_ = [], + mi_exports_ = [], + mi_used_th_ = False, + mi_fixities_ = [], + mi_warns_ = IfWarnSome [] [], + mi_anns_ = [], + mi_insts_ = [], + mi_fam_insts_ = [], + mi_rules_ = [], + mi_decls_ = [], + mi_extra_decls_ = Nothing, + mi_top_env_ = Nothing, + mi_hpc_ = False, + mi_trust_ = noIfaceTrustInfo, + mi_trust_pkg_ = False, + mi_complete_matches_ = [], + mi_docs_ = Nothing, + mi_final_exts_ = (), + mi_ext_fields_ = emptyExtensibleFields + } emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) - { mi_decls = [] - , mi_final_exts = ModIfaceBackend + { mi_decls_ = [] + , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + , mi_final_exts_ = ModIfaceBackend { mi_iface_hash = fingerprint0, mi_mod_hash = fingerprint0, mi_flag_hash = fingerprint0, @@ -569,36 +661,38 @@ emptyIfaceHashCache _occ = Nothing instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (ModIface{ mi_module, mi_sig_of, mi_hsc_src, mi_deps, mi_usages - , mi_exports, mi_used_th, mi_fixities, mi_warns, mi_anns - , mi_decls, mi_extra_decls, mi_top_env, mi_insts - , mi_fam_insts, mi_rules, mi_hpc, mi_trust, mi_trust_pkg - , mi_complete_matches, mi_docs, mi_final_exts - , mi_ext_fields, mi_src_hash }) - = rnf mi_module - `seq` rnf mi_sig_of - `seq` mi_hsc_src - `seq` mi_deps - `seq` mi_usages - `seq` mi_exports - `seq` rnf mi_used_th - `seq` mi_fixities - `seq` rnf mi_warns - `seq` rnf mi_anns - `seq` rnf mi_decls - `seq` rnf mi_extra_decls - `seq` rnf mi_top_env - `seq` rnf mi_insts - `seq` rnf mi_fam_insts - `seq` rnf mi_rules - `seq` rnf mi_hpc - `seq` mi_trust - `seq` rnf mi_trust_pkg - `seq` rnf mi_complete_matches - `seq` rnf mi_docs - `seq` mi_final_exts - `seq` mi_ext_fields - `seq` rnf mi_src_hash + rnf (PrivateModIface + { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_, mi_usages_ + , mi_exports_, mi_used_th_, mi_fixities_, mi_warns_, mi_anns_ + , mi_decls_, mi_extra_decls_, mi_top_env_, mi_insts_ + , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_ + , mi_complete_matches_, mi_docs_, mi_final_exts_ + , mi_ext_fields_, mi_src_hash_ }) + = rnf mi_module_ + `seq` rnf mi_sig_of_ + `seq` mi_hsc_src_ + `seq` mi_hi_bytes_ + `seq` mi_deps_ + `seq` mi_usages_ + `seq` mi_exports_ + `seq` rnf mi_used_th_ + `seq` mi_fixities_ + `seq` rnf mi_warns_ + `seq` rnf mi_anns_ + `seq` rnf mi_decls_ + `seq` rnf mi_extra_decls_ + `seq` rnf mi_top_env_ + `seq` rnf mi_insts_ + `seq` rnf mi_fam_insts_ + `seq` rnf mi_rules_ + `seq` rnf mi_hpc_ + `seq` mi_trust_ + `seq` rnf mi_trust_pkg_ + `seq` rnf mi_complete_matches_ + `seq` rnf mi_docs_ + `seq` mi_final_exts_ + `seq` mi_ext_fields_ + `seq` rnf mi_src_hash_ `seq` () instance NFData (ModIfaceBackend) where @@ -638,5 +732,286 @@ type WhetherHasOrphans = Bool -- | Does this module define family instances? type WhetherHasFamInst = Bool +-- ---------------------------------------------------------------------------- +-- Modify a 'ModIface'. +-- ---------------------------------------------------------------------------- + +{- +Note [Private fields in ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The fields of 'ModIface' are private, e.g., not exported, to make the API +impossible to misuse. A 'ModIface' can be "compressed" in-memory using +'shareIface', which serialises the 'ModIface' to an in-memory buffer. +This has the advantage of reducing memory usage of 'ModIface', reducing the +overall memory usage of GHC. +See Note [Sharing of ModIface]. + +This in-memory buffer can be reused, if and only if the 'ModIface' is not +modified after it has been "compressed"/shared via 'shareIface'. Instead of +serialising 'ModIface', we simply write the in-memory buffer to disk directly. + +However, we can't rely that a 'ModIface' isn't modified after 'shareIface' has +been called. Thus, we make all fields of 'ModIface' private and modification +only happens via exported update functions, such as 'set_mi_decls'. +These functions unconditionally clear any in-memory buffer if used, forcing us +to serialise the 'ModIface' to disk again. +-} + +-- | Given a 'PartialModIface', turn it into a 'ModIface' by completing +-- missing fields. +completePartialModIface :: PartialModIface + -> [(Fingerprint, IfaceDecl)] + -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] + -> ModIfaceBackend + -> ModIface +completePartialModIface partial decls extra_decls final_exts = partial + { mi_decls_ = decls + , mi_extra_decls_ = extra_decls + , mi_final_exts_ = final_exts + , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + } + +-- | Add a source fingerprint to a 'ModIface_' without invalidating the byte array +-- buffer 'mi_hi_bytes'. +-- This is a variant of 'set_mi_src_hash' which does invalidate the buffer. +-- +-- The 'mi_src_hash' is computed outside of 'ModIface_' based on the 'ModSummary'. +addSourceFingerprint :: Fingerprint -> ModIface_ phase -> ModIface_ phase +addSourceFingerprint val iface = iface { mi_src_hash_ = val } + +-- | Copy fields that aren't serialised to disk to the new 'ModIface_'. +-- This includes especially hashes that are usually stored in the interface +-- file header and 'mi_top_env'. +-- +-- We need this function after calling 'shareIface', to make sure the +-- 'ModIface_' doesn't lose any information. This function does not discard +-- the in-memory byte array buffer 'mi_hi_bytes'. +restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase +restoreFromOldModIface old new = new + { mi_top_env_ = mi_top_env_ old + , mi_hsc_src_ = mi_hsc_src_ old + , mi_src_hash_ = mi_src_hash_ old + } + +set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase +set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } + +set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase +set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } + +set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase +set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } + +set_mi_src_hash :: Fingerprint -> ModIface_ phase -> ModIface_ phase +set_mi_src_hash val iface = clear_mi_hi_bytes $ iface { mi_src_hash_ = val } + +set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase +set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } + +set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase +set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } + +set_mi_usages :: [Usage] -> ModIface_ phase -> ModIface_ phase +set_mi_usages val iface = clear_mi_hi_bytes $ iface { mi_usages_ = val } +set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase +set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } + +set_mi_used_th :: Bool -> ModIface_ phase -> ModIface_ phase +set_mi_used_th val iface = clear_mi_hi_bytes $ iface { mi_used_th_ = val } + +set_mi_fixities :: [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase +set_mi_fixities val iface = clear_mi_hi_bytes $ iface { mi_fixities_ = val } + +set_mi_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase +set_mi_warns val iface = clear_mi_hi_bytes $ iface { mi_warns_ = val } + +set_mi_anns :: [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase +set_mi_anns val iface = clear_mi_hi_bytes $ iface { mi_anns_ = val } + +set_mi_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase +set_mi_insts val iface = clear_mi_hi_bytes $ iface { mi_insts_ = val } + +set_mi_fam_insts :: [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase +set_mi_fam_insts val iface = clear_mi_hi_bytes $ iface { mi_fam_insts_ = val } + +set_mi_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase +set_mi_rules val iface = clear_mi_hi_bytes $ iface { mi_rules_ = val } + +set_mi_decls :: [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase +set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls_ = val } + +set_mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase +set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val } + +set_mi_top_env :: Maybe IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } + +set_mi_hpc :: AnyHpcUsage -> ModIface_ phase -> ModIface_ phase +set_mi_hpc val iface = clear_mi_hi_bytes $ iface { mi_hpc_ = val } + +set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase +set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val } + +set_mi_trust_pkg :: Bool -> ModIface_ phase -> ModIface_ phase +set_mi_trust_pkg val iface = clear_mi_hi_bytes $ iface { mi_trust_pkg_ = val } + +set_mi_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase +set_mi_complete_matches val iface = clear_mi_hi_bytes $ iface { mi_complete_matches_ = val } + +set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase +set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } + +set_mi_final_exts :: IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase +set_mi_final_exts val iface = clear_mi_hi_bytes $ iface { mi_final_exts_ = val } + +set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase +set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } + +-- | Invalidate any byte array buffer we might have. +clear_mi_hi_bytes :: ModIface_ phase -> ModIface_ phase +clear_mi_hi_bytes iface = iface + { mi_hi_bytes_ = case mi_hi_bytes iface of + PartialIfaceBinHandle -> PartialIfaceBinHandle + FullIfaceBinHandle _ -> FullIfaceBinHandle Strict.Nothing + } + +-- ---------------------------------------------------------------------------- +-- 'ModIface' pattern synonyms to keep breakage low. +-- ---------------------------------------------------------------------------- + +{- +Note [Inline Pattern synonym of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The introduction of the 'ModIface' pattern synonym originally caused an increase +in allocated bytes in multiple performance tests. +In some benchmarks, it was a 2~3% increase. + +Without {-# INLINE ModIface #-}, the generated core reveals the reason for this increase. +We show the core for the 'mi_module' record selector: + +@ + mi_module + = \ @phase iface -> $w$mModIface iface mi_module1 + + $w$mModIface + = \ @phase iface cont -> + case iface of + { PrivateModIface a b ... z -> + cont + a + b + ... + z + } + + mi_module1 + = \ @phase + a + _ + ... + _ -> + a +@ + +Thus, we can see the '$w$mModIface' is not inlined, leading to an increase in +the allocated bytes. + +However, with the pragma, the correct core is generated: + +@ + mi_module = mi_module_ +@ + +-} +-- See Note [Inline Pattern synonym of ModIface] for why we have all these +-- inline pragmas. +{-# INLINE ModIface #-} +{-# INLINE mi_module #-} +{-# INLINE mi_sig_of #-} +{-# INLINE mi_hsc_src #-} +{-# INLINE mi_deps #-} +{-# INLINE mi_usages #-} +{-# INLINE mi_exports #-} +{-# INLINE mi_used_th #-} +{-# INLINE mi_fixities #-} +{-# INLINE mi_warns #-} +{-# INLINE mi_anns #-} +{-# INLINE mi_decls #-} +{-# INLINE mi_extra_decls #-} +{-# INLINE mi_top_env #-} +{-# INLINE mi_insts #-} +{-# INLINE mi_fam_insts #-} +{-# INLINE mi_rules #-} +{-# INLINE mi_hpc #-} +{-# INLINE mi_trust #-} +{-# INLINE mi_trust_pkg #-} +{-# INLINE mi_complete_matches #-} +{-# INLINE mi_docs #-} +{-# INLINE mi_final_exts #-} +{-# INLINE mi_ext_fields #-} +{-# INLINE mi_src_hash #-} +{-# INLINE mi_hi_bytes #-} + +pattern ModIface :: + Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] -> + [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> + [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> + Maybe IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> + AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> + IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> + ModIface_ phase +pattern ModIface + { mi_module + , mi_sig_of + , mi_hsc_src + , mi_deps + , mi_usages + , mi_exports + , mi_used_th + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_extra_decls + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_hpc + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_final_exts + , mi_ext_fields + , mi_src_hash + , mi_hi_bytes + } <- PrivateModIface + { mi_module_ = mi_module + , mi_sig_of_ = mi_sig_of + , mi_hsc_src_ = mi_hsc_src + , mi_deps_ = mi_deps + , mi_usages_ = mi_usages + , mi_exports_ = mi_exports + , mi_used_th_ = mi_used_th + , mi_fixities_ = mi_fixities + , mi_warns_ = mi_warns + , mi_anns_ = mi_anns + , mi_decls_ = mi_decls + , mi_extra_decls_ = mi_extra_decls + , mi_top_env_ = mi_top_env + , mi_insts_ = mi_insts + , mi_fam_insts_ = mi_fam_insts + , mi_rules_ = mi_rules + , mi_hpc_ = mi_hpc + , mi_trust_ = mi_trust + , mi_trust_pkg_ = mi_trust_pkg + , mi_complete_matches_ = mi_complete_matches + , mi_docs_ = mi_docs + , mi_final_exts_ = mi_final_exts + , mi_ext_fields_ = mi_ext_fields + , mi_src_hash_ = mi_src_hash + , mi_hi_bytes_ = mi_hi_bytes + } ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -19,7 +19,7 @@ -- http://www.cs.york.ac.uk/fp/nhc98/ module GHC.Utils.Binary - ( {-type-} Bin, + ( {-type-} Bin, RelBin(..), getRelBin, {-class-} Binary(..), {-type-} ReadBinHandle, WriteBinHandle, SymbolTable, Dictionary, @@ -32,6 +32,7 @@ module GHC.Utils.Binary seekBinWriter, seekBinReader, + seekBinReaderRel, tellBinReader, tellBinWriter, castBin, @@ -47,7 +48,9 @@ module GHC.Utils.Binary readBinMemN, putAt, getAt, + putAtRel, forwardPut, forwardPut_, forwardGet, + forwardPutRel, forwardPutRel_, forwardGetRel, -- * For writing instances putByte, @@ -102,6 +105,8 @@ module GHC.Utils.Binary BindingName(..), simpleBindingNameWriter, simpleBindingNameReader, + FullBinData(..), freezeBinHandle, thawBinHandle, putFullBinData, + BinArray, ) where import GHC.Prelude @@ -119,7 +124,6 @@ import GHC.Types.SrcLoc import GHC.Types.Unique import qualified GHC.Data.Strict as Strict import GHC.Utils.Outputable( JoinPointHood(..) ) -import GHC.Utils.Misc ( HasCallStack, HasDebugCallStack ) import Control.DeepSeq import Control.Monad ( when, (<$!>), unless, forM_, void ) @@ -195,6 +199,62 @@ dataHandle (BinData size bin) = do handleData :: WriteBinHandle -> IO BinData handleData (WriteBinMem _ ixr _ binr) = BinData <$> readFastMutInt ixr <*> readIORef binr +--------------------------------------------------------------- +-- FullBinData +--------------------------------------------------------------- + +-- | 'FullBinData' stores a slice to a 'BinArray'. +-- +-- It requires less memory than 'ReadBinHandle', and can be constructed from +-- a 'ReadBinHandle' via 'freezeBinHandle' and turned back into a +-- 'ReadBinHandle' using 'thawBinHandle'. +-- Additionally, the byte array slice can be put into a 'WriteBinHandle' without extra +-- conversions via 'putFullBinData'. +data FullBinData = FullBinData + { fbd_readerUserData :: ReaderUserData + -- ^ 'ReaderUserData' that can be used to resume reading. + , fbd_off_s :: {-# UNPACK #-} !Int + -- ^ start offset + , fbd_off_e :: {-# UNPACK #-} !Int + -- ^ end offset + , fbd_size :: {-# UNPACK #-} !Int + -- ^ total buffer size + , fbd_buffer :: {-# UNPACK #-} !BinArray + } + +-- Equality and Ord assume that two distinct buffers are different, even if they compare the same things. +instance Eq FullBinData where + (FullBinData _ b c d e) == (FullBinData _ b1 c1 d1 e1) = b == b1 && c == c1 && d == d1 && e == e1 + +instance Ord FullBinData where + compare (FullBinData _ b c d e) (FullBinData _ b1 c1 d1 e1) = + compare b b1 `mappend` compare c c1 `mappend` compare d d1 `mappend` compare e e1 + +-- | Write the 'FullBinData' slice into the 'WriteBinHandle'. +putFullBinData :: WriteBinHandle -> FullBinData -> IO () +putFullBinData bh (FullBinData _ o1 o2 _sz ba) = do + let sz = o2 - o1 + putPrim bh sz $ \dest -> + unsafeWithForeignPtr (ba `plusForeignPtr` o1) $ \orig -> + copyBytes dest orig sz + +-- | Freeze a 'ReadBinHandle' and a start index into a 'FullBinData'. +-- +-- 'FullBinData' stores a slice starting from the 'Bin a' location to the current +-- offset of the 'ReadBinHandle'. +freezeBinHandle :: ReadBinHandle -> Bin a -> IO FullBinData +freezeBinHandle (ReadBinMem user_data ixr sz binr) (BinPtr start) = do + ix <- readFastMutInt ixr + pure (FullBinData user_data start ix sz binr) + +-- | Turn the 'FullBinData' into a 'ReadBinHandle', setting the 'ReadBinHandle' +-- offset to the start of the 'FullBinData' and restore the 'ReaderUserData' that was +-- obtained from 'freezeBinHandle'. +thawBinHandle :: FullBinData -> IO ReadBinHandle +thawBinHandle (FullBinData user_data ix _end sz ba) = do + ixr <- newFastMutInt ix + return $ ReadBinMem user_data ixr sz ba + --------------------------------------------------------------- -- BinHandle --------------------------------------------------------------- @@ -288,9 +348,47 @@ unsafeUnpackBinBuffer (BS.BS arr len) = do newtype Bin a = BinPtr Int deriving (Eq, Ord, Show, Bounded) +-- | Like a 'Bin' but is used to store relative offset pointers. +-- Relative offset pointers store a relative location, but also contain an +-- anchor that allow to obtain the absolute offset. +data RelBin a = RelBin + { relBin_anchor :: {-# UNPACK #-} !(Bin a) + -- ^ Absolute position from where we read 'relBin_offset'. + , relBin_offset :: {-# UNPACK #-} !(RelBinPtr a) + -- ^ Relative offset to 'relBin_anchor'. + -- The absolute position of the 'RelBin' is @relBin_anchor + relBin_offset@ + } + deriving (Eq, Ord, Show, Bounded) + +-- | A 'RelBinPtr' is like a 'Bin', but contains a relative offset pointer +-- instead of an absolute offset. +newtype RelBinPtr a = RelBinPtr (Bin a) + deriving (Eq, Ord, Show, Bounded) + castBin :: Bin a -> Bin b castBin (BinPtr i) = BinPtr i +-- | Read a relative offset location and wrap it in 'RelBin'. +-- +-- The resulting 'RelBin' can be translated into an absolute offset location using +-- 'makeAbsoluteBin' +getRelBin :: ReadBinHandle -> IO (RelBin a) +getRelBin bh = do + start <- tellBinReader bh + off <- get bh + pure $ RelBin start off + +makeAbsoluteBin :: RelBin a -> Bin a +makeAbsoluteBin (RelBin (BinPtr !start) (RelBinPtr (BinPtr !offset))) = + BinPtr $ start + offset + +makeRelativeBin :: RelBin a -> RelBinPtr a +makeRelativeBin (RelBin _ offset) = offset + +toRelBin :: Bin (RelBinPtr a) -> Bin a -> RelBin a +toRelBin (BinPtr !start) (BinPtr !goal) = + RelBin (BinPtr start) (RelBinPtr $ BinPtr $ goal - start) + --------------------------------------------------------------- -- class Binary --------------------------------------------------------------- @@ -311,6 +409,9 @@ class Binary a where putAt :: Binary a => WriteBinHandle -> Bin a -> a -> IO () putAt bh p x = do seekBinWriter bh p; put_ bh x; return () +putAtRel :: WriteBinHandle -> Bin (RelBinPtr a) -> Bin a -> IO () +putAtRel bh from to = putAt bh from (makeRelativeBin $ toRelBin from to) + getAt :: Binary a => ReadBinHandle -> Bin a -> IO a getAt bh p = do seekBinReader bh p; get bh @@ -344,7 +445,7 @@ freezeWriteHandle wbm = do , rbm_arr_r = rbm_arr_r } --- Copy the BinBuffer to a new BinBuffer which is exactly the right size. +-- | Copy the BinBuffer to a new BinBuffer which is exactly the right size. -- This performs a copy of the underlying buffer. -- The buffer may be truncated if the offset is not at the end of the written -- output. @@ -398,6 +499,13 @@ seekBinReader (ReadBinMem _ ix_r sz_r _) (BinPtr !p) = do then panic "seekBinReader: seek out of range" else writeFastMutInt ix_r p +seekBinReaderRel :: ReadBinHandle -> RelBin a -> IO () +seekBinReaderRel (ReadBinMem _ ix_r sz_r _) relBin = do + let (BinPtr !p) = makeAbsoluteBin relBin + if (p > sz_r) + then panic "seekBinReaderRel: seek out of range" + else writeFastMutInt ix_r p + writeBinMem :: WriteBinHandle -> FilePath -> IO () writeBinMem (WriteBinMem _ ix_r _ arr_r) fn = do h <- openBinaryFile fn WriteMode @@ -1118,12 +1226,17 @@ instance Binary (Bin a) where put_ bh (BinPtr i) = putWord32 bh (fromIntegral i :: Word32) get bh = do i <- getWord32 bh; return (BinPtr (fromIntegral (i :: Word32))) +-- Instance uses fixed-width encoding to allow inserting +-- Bin placeholders in the stream. +instance Binary (RelBinPtr a) where + put_ bh (RelBinPtr i) = put_ bh i + get bh = RelBinPtr <$> get bh -- ----------------------------------------------------------------------------- -- Forward reading/writing --- | "forwardPut put_A put_B" outputs A after B but allows A to be read before B --- by using a forward reference +-- | @'forwardPut' put_A put_B@ outputs A after B but allows A to be read before B +-- by using a forward reference. forwardPut :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a,b) forwardPut bh put_A put_B = do -- write placeholder pointer to A @@ -1146,6 +1259,8 @@ forwardPut_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () forwardPut_ bh put_A put_B = void $ forwardPut bh put_A put_B -- | Read a value stored using a forward reference +-- +-- The forward reference is expected to be an absolute offset. forwardGet :: ReadBinHandle -> IO a -> IO a forwardGet bh get_A = do -- read forward reference @@ -1158,6 +1273,48 @@ forwardGet bh get_A = do seekBinReader bh p_a pure r +-- | @'forwardPutRel' put_A put_B@ outputs A after B but allows A to be read before B +-- by using a forward reference. +-- +-- This forward reference is a relative offset that allows us to skip over the +-- result of 'put_A'. +forwardPutRel :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a,b) +forwardPutRel bh put_A put_B = do + -- write placeholder pointer to A + pre_a <- tellBinWriter bh + put_ bh pre_a + + -- write B + r_b <- put_B + + -- update A's pointer + a <- tellBinWriter bh + putAtRel bh pre_a a + seekBinNoExpandWriter bh a + + -- write A + r_a <- put_A r_b + pure (r_a,r_b) + +-- | Like 'forwardGetRel', but discard the result. +forwardPutRel_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () +forwardPutRel_ bh put_A put_B = void $ forwardPutRel bh put_A put_B + +-- | Read a value stored using a forward reference. +-- +-- The forward reference is expected to be a relative offset. +forwardGetRel :: ReadBinHandle -> IO a -> IO a +forwardGetRel bh get_A = do + -- read forward reference + p <- getRelBin bh + -- store current position + p_a <- tellBinReader bh + -- go read the forward value, then seek back + seekBinReader bh $ makeAbsoluteBin p + r <- get_A + seekBinReader bh p_a + pure r + -- ----------------------------------------------------------------------------- -- Lazy reading/writing @@ -1167,19 +1324,19 @@ lazyPut = lazyPut' put_ lazyGet :: Binary a => ReadBinHandle -> IO a lazyGet = lazyGet' get -lazyPut' :: HasDebugCallStack => (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO () +lazyPut' :: (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO () lazyPut' f bh a = do -- output the obj with a ptr to skip over it: pre_a <- tellBinWriter bh put_ bh pre_a -- save a slot for the ptr f bh a -- dump the object q <- tellBinWriter bh -- q = ptr to after object - putAt bh pre_a q -- fill in slot before a with ptr to q + putAtRel bh pre_a q -- fill in slot before a with ptr to q seekBinWriter bh q -- finally carry on writing at q -lazyGet' :: HasDebugCallStack => (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a +lazyGet' :: (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a lazyGet' f bh = do - p <- get bh -- a BinPtr + p <- getRelBin bh -- a BinPtr p_a <- tellBinReader bh a <- unsafeInterleaveIO $ do -- NB: Use a fresh rbm_off_r variable in the child thread, for thread @@ -1188,7 +1345,7 @@ lazyGet' f bh = do let bh' = bh { rbm_off_r = off_r } seekBinReader bh' p_a f bh' - seekBinReader bh p -- skip over the object for now + seekBinReader bh (makeAbsoluteBin p) -- skip over the object for now return a -- | Serialize the constructor strictly but lazily serialize a value inside a @@ -1324,7 +1481,7 @@ mkReader f = BinaryReader -- | Find the 'BinaryReader' for the 'Binary' instance for the type identified by 'Proxy a'. -- -- If no 'BinaryReader' has been configured before, this function will panic. -findUserDataReader :: forall a . (HasCallStack, Refl.Typeable a) => Proxy a -> ReadBinHandle -> BinaryReader a +findUserDataReader :: forall a . Refl.Typeable a => Proxy a -> ReadBinHandle -> BinaryReader a findUserDataReader query bh = case Map.lookup (Refl.someTypeRep query) (ud_reader_data $ getReaderUserData bh) of Nothing -> panic $ "Failed to find BinaryReader for the key: " ++ show (Refl.someTypeRep query) @@ -1346,7 +1503,7 @@ findUserDataReader query bh = -- | Find the 'BinaryWriter' for the 'Binary' instance for the type identified by 'Proxy a'. -- -- If no 'BinaryWriter' has been configured before, this function will panic. -findUserDataWriter :: forall a . (HasCallStack, Refl.Typeable a) => Proxy a -> WriteBinHandle -> BinaryWriter a +findUserDataWriter :: forall a . Refl.Typeable a => Proxy a -> WriteBinHandle -> BinaryWriter a findUserDataWriter query bh = case Map.lookup (Refl.someTypeRep query) (ud_writer_data $ getWriterUserData bh) of Nothing -> panic $ "Failed to find BinaryWriter for the key: " ++ show (Refl.someTypeRep query) @@ -1482,13 +1639,13 @@ putGenericSymbolTable gen_sym_tab serialiser bh = do mapM_ (\n -> serialiser bh n) (reverse todo) loop snd <$> - (forwardPut bh (const $ readFastMutInt symtab_next >>= put_ bh) $ + (forwardPutRel bh (const $ readFastMutInt symtab_next >>= put_ bh) $ loop) -- | Read the elements of a 'GenericSymbolTable' from disk into a 'SymbolTable'. getGenericSymbolTable :: forall a . (ReadBinHandle -> IO a) -> ReadBinHandle -> IO (SymbolTable a) getGenericSymbolTable deserialiser bh = do - sz <- forwardGet bh (get bh) :: IO Int + sz <- forwardGetRel bh (get bh) :: IO Int mut_arr <- newArray_ (0, sz-1) :: IO (IOArray Int a) forM_ [0..(sz-1)] $ \i -> do f <- deserialiser bh ===================================== testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs ===================================== @@ -64,9 +64,10 @@ metaPlugin' _ meta = pprPanic "meta" (showAstData BlankSrcSpan BlankEpAnnotation interfaceLoadPlugin' :: [CommandLineOption] -> ModIface -> IfM lcl ModIface interfaceLoadPlugin' [name, "interface"] iface - = return $ iface { mi_exports = filter (availNotNamedAs name) - (mi_exports iface) - } + = return $ set_mi_exports (filter (availNotNamedAs name) + (mi_exports iface)) + iface + interfaceLoadPlugin' _ iface = return iface availNotNamedAs :: String -> AvailInfo -> Bool ===================================== utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs ===================================== @@ -56,7 +56,7 @@ import GHC.Types.Unique.FM import GHC.Unit.State import GHC.Utils.Binary -import GHC.Iface.Type (IfaceType, getIfaceType, putIfaceType) +import GHC.Iface.Type (IfaceType, putIfaceType) import Haddock.Options (Visibility (..)) @@ -200,7 +200,7 @@ writeInterfaceFile filename iface = do -- write the iface type pointer at the front of the file ifacetype_p <- tellBinWriter bh - putAt bh ifacetype_p_p ifacetype_p + putAtRel bh ifacetype_p_p ifacetype_p seekBinWriter bh ifacetype_p -- write the symbol table itself @@ -208,7 +208,7 @@ writeInterfaceFile filename iface = do -- write the symtab pointer at the front of the file symtab_p <- tellBinWriter bh - putAt bh symtab_p_p symtab_p + putAtRel bh symtab_p_p symtab_p seekBinWriter bh symtab_p -- write the symbol table itself @@ -218,7 +218,7 @@ writeInterfaceFile filename iface = do -- write the dictionary pointer at the fornt of the file dict_p <- tellBinWriter bh - putAt bh dict_p_p dict_p + putAtRel bh dict_p_p dict_p seekBinWriter bh dict_p -- write the dictionary itself View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1cc28d23030a41115ea77b62aa96dc98cb756e62 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1cc28d23030a41115ea77b62aa96dc98cb756e62 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 08:58:34 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Mon, 03 Jun 2024 04:58:34 -0400 Subject: [Git][ghc/ghc][wip/fix-mingw-distro-toolchain] autoconf: normalize paths of some build-time dependencies on Windows Message-ID: <665d85bab375b_32af314b2cf07021d@gitlab.mail> Cheng Shao pushed to branch wip/fix-mingw-distro-toolchain at Glasgow Haskell Compiler / GHC Commits: 5926c86d by Cheng Shao at 2024-06-03T10:55:41+02:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 3 changed files: - configure.ac - m4/fp_find_nm.m4 - m4/fp_prog_ar_args.m4 Changes: ===================================== configure.ac ===================================== @@ -314,6 +314,8 @@ else AC_CHECK_TARGET_TOOL([WindresCmd],[windres]) AC_CHECK_TARGET_TOOL([OBJDUMP],[objdump]) + WindresCmd="$(cygpath -m $WindresCmd)" + if test "$Genlib" != ""; then GenlibCmd="$(cygpath -m $Genlib)" fi @@ -464,7 +466,12 @@ case $HostOS_CPP in ;; esac -ObjdumpCmd="$OBJDUMP" +if test "$HostOS" = "mingw32" +then + ObjdumpCmd=$(cygpath -m "$OBJDUMP") +else + ObjdumpCmd="$OBJDUMP" +fi AC_SUBST([ObjdumpCmd]) dnl ** Which ranlib to use? @@ -473,7 +480,12 @@ AC_PROG_RANLIB if test "$RANLIB" = ":"; then AC_MSG_ERROR([cannot find ranlib in your PATH]) fi -RanlibCmd="$RANLIB" +if test "$HostOS" = "mingw32" +then + RanlibCmd=$(cygpath -m "$RANLIB") +else + RanlibCmd="$RANLIB" +fi AC_SUBST([RanlibCmd]) dnl ** which strip to use? ===================================== m4/fp_find_nm.m4 ===================================== @@ -9,7 +9,12 @@ AC_DEFUN([FP_FIND_NM], AC_MSG_ERROR([cannot find nm in your PATH]) fi fi - NmCmd="$NM" + if test "$HostOS" = "mingw32" + then + NmCmd=$(cygpath -m "$NM") + else + NmCmd="$NM" + fi AC_SUBST([NmCmd]) if test "$TargetOS_CPP" = "darwin" @@ -37,4 +42,3 @@ AC_DEFUN([FP_FIND_NM], esac fi ]) - ===================================== m4/fp_prog_ar_args.m4 ===================================== @@ -30,7 +30,13 @@ else fi fi]) fp_prog_ar_args=$fp_cv_prog_ar_args -AC_SUBST([ArCmd], ["$fp_prog_ar"]) +if test "$HostOS" = "mingw32" +then + ArCmd=$(cygpath -m "$fp_prog_ar") +else + ArCmd="$fp_prog_ar" +fi +AC_SUBST([ArCmd]) AC_SUBST([ArArgs], ["$fp_prog_ar_args"]) ])# FP_PROG_AR_ARGS View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5926c86d221a7f749525de1a9e0e6e941aff4f57 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5926c86d221a7f749525de1a9e0e6e941aff4f57 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 10:13:35 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 03 Jun 2024 06:13:35 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Improve performance of genericWordQuotRem2Op (#22966) Message-ID: <665d974ef2c45_3658d174b22451562@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - 26c13ceb by Fendor at 2024-06-03T06:13:03-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 6c3a5604 by Cheng Shao at 2024-06-03T06:13:06-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 24 changed files: - compiler/GHC.hs - + compiler/GHC/Data/OsPath.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Config/Finder.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Iface/Errors.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Finder/Types.hs - compiler/GHC/Unit/Module/Location.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/ghc.cabal.in - ghc/ghc-bin.cabal.in - libraries/base/tests/all.T - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/numeric/should_run/all.T - + testsuite/tests/numeric/should_run/quotRem2Large.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -3,6 +3,7 @@ {-# LANGUAGE NondecreasingIndentation, ScopedTypeVariables #-} {-# LANGUAGE TupleSections, NamedFieldPuns #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE PatternSynonyms #-} -- ----------------------------------------------------------------------------- -- @@ -76,6 +77,7 @@ module GHC ( ModuleGraph, emptyMG, mapMG, mkModuleGraph, mgModSummaries, mgLookupModule, ModSummary(..), ms_mod_name, ModLocation(..), + pattern ModLocation, getModSummary, getModuleGraph, isLoaded, ===================================== compiler/GHC/Data/OsPath.hs ===================================== @@ -0,0 +1,29 @@ +module GHC.Data.OsPath + ( + -- * OsPath initialisation and transformation + OsPath + , OsString + , encodeUtf + , decodeUtf + , unsafeDecodeUtf + , unsafeEncodeUtf + , os + -- * Common utility functions + , () + , (<.>) + ) + where + +import GHC.Prelude + +import GHC.Utils.Misc (HasCallStack) +import GHC.Utils.Panic (panic) + +import System.OsPath +import System.Directory.Internal (os) + +-- | Decode an 'OsPath' to 'FilePath', throwing an 'error' if decoding failed. +-- Prefer 'decodeUtf' and gracious error handling. +unsafeDecodeUtf :: HasCallStack => OsPath -> FilePath +unsafeDecodeUtf p = + either (\err -> panic $ "Failed to decodeUtf \"" ++ show p ++ "\", because: " ++ show err) id (decodeUtf p) ===================================== compiler/GHC/Data/Strict.hs ===================================== @@ -9,8 +9,8 @@ module GHC.Data.Strict ( Maybe(Nothing, Just), fromMaybe, + GHC.Data.Strict.maybe, Pair(And), - -- Not used at the moment: -- -- Either(Left, Right), @@ -18,6 +18,7 @@ module GHC.Data.Strict ( ) where import GHC.Prelude hiding (Maybe(..), Either(..)) + import Control.Applicative import Data.Semigroup import Data.Data @@ -29,6 +30,10 @@ fromMaybe :: a -> Maybe a -> a fromMaybe d Nothing = d fromMaybe _ (Just x) = x +maybe :: b -> (a -> b) -> Maybe a -> b +maybe d _ Nothing = d +maybe _ f (Just x) = f x + apMaybe :: Maybe (a -> b) -> Maybe a -> Maybe b apMaybe (Just f) (Just x) = Just (f x) apMaybe _ _ = Nothing ===================================== compiler/GHC/Driver/Backpack.hs ===================================== @@ -74,6 +74,7 @@ import GHC.Linker.Types import qualified GHC.LanguageExtensions as LangExt import GHC.Data.Maybe +import GHC.Data.OsPath (unsafeEncodeUtf, os) import GHC.Data.StringBuffer import GHC.Data.FastString import qualified GHC.Data.EnumSet as EnumSet @@ -772,7 +773,7 @@ summariseRequirement pn mod_name = do let PackageName pn_fs = pn let location = mkHomeModLocation2 fopts mod_name - (unpackFS pn_fs moduleNameSlashes mod_name) "hsig" + (unsafeEncodeUtf $ unpackFS pn_fs moduleNameSlashes mod_name) (os "hsig") env <- getBkpEnv src_hash <- liftIO $ getFileHash (bkp_filename env) @@ -855,12 +856,12 @@ hsModuleToModSummary home_keys pn hsc_src modname -- these filenames to figure out where the hi files go. -- A travesty! let location0 = mkHomeModLocation2 fopts modname - (unpackFS unit_fs + (unsafeEncodeUtf $ unpackFS unit_fs moduleNameSlashes modname) (case hsc_src of - HsigFile -> "hsig" - HsBootFile -> "hs-boot" - HsSrcFile -> "hs") + HsigFile -> os "hsig" + HsBootFile -> os "hs-boot" + HsSrcFile -> os "hs") -- DANGEROUS: bootifying can POISON the module finder cache let location = case hsc_src of HsBootFile -> addBootSuffixLocnOut location0 ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -35,6 +35,7 @@ import GHC.Driver.LlvmConfigCache (LlvmConfigCache) import GHC.Driver.Ppr import GHC.Driver.Backend +import GHC.Data.OsPath import qualified GHC.Data.ShortText as ST import GHC.Data.Stream ( Stream ) import qualified GHC.Data.Stream as Stream @@ -259,7 +260,7 @@ outputForeignStubs Maybe FilePath) -- C file created outputForeignStubs logger tmpfs dflags unit_state mod location stubs = do - let stub_h = mkStubPaths (initFinderOpts dflags) (moduleName mod) location + let stub_h = unsafeDecodeUtf $ mkStubPaths (initFinderOpts dflags) (moduleName mod) location stub_c <- newTempName logger tmpfs (tmpDir dflags) TFL_CurrentModule "c" case stubs of ===================================== compiler/GHC/Driver/Config/Finder.hs ===================================== @@ -8,27 +8,27 @@ import GHC.Prelude import GHC.Driver.DynFlags import GHC.Unit.Finder.Types import GHC.Data.FastString - +import GHC.Data.OsPath -- | Create a new 'FinderOpts' from DynFlags. initFinderOpts :: DynFlags -> FinderOpts initFinderOpts flags = FinderOpts - { finder_importPaths = importPaths flags + { finder_importPaths = fmap unsafeEncodeUtf $ importPaths flags , finder_lookupHomeInterfaces = isOneShot (ghcMode flags) , finder_bypassHiFileCheck = MkDepend == (ghcMode flags) , finder_ways = ways flags , finder_enableSuggestions = gopt Opt_HelpfulErrors flags - , finder_workingDirectory = workingDirectory flags + , finder_workingDirectory = fmap unsafeEncodeUtf $ workingDirectory flags , finder_thisPackageName = mkFastString <$> thisPackageName flags , finder_hiddenModules = hiddenModules flags , finder_reexportedModules = reexportedModules flags - , finder_hieDir = hieDir flags - , finder_hieSuf = hieSuf flags - , finder_hiDir = hiDir flags - , finder_hiSuf = hiSuf_ flags - , finder_dynHiSuf = dynHiSuf_ flags - , finder_objectDir = objectDir flags - , finder_objectSuf = objectSuf_ flags - , finder_dynObjectSuf = dynObjectSuf_ flags - , finder_stubDir = stubDir flags + , finder_hieDir = fmap unsafeEncodeUtf $ hieDir flags + , finder_hieSuf = unsafeEncodeUtf $ hieSuf flags + , finder_hiDir = fmap unsafeEncodeUtf $ hiDir flags + , finder_hiSuf = unsafeEncodeUtf $ hiSuf_ flags + , finder_dynHiSuf = unsafeEncodeUtf $ dynHiSuf_ flags + , finder_objectDir = fmap unsafeEncodeUtf $ objectDir flags + , finder_objectSuf = unsafeEncodeUtf $ objectSuf_ flags + , finder_dynObjectSuf = unsafeEncodeUtf $ dynObjectSuf_ flags + , finder_stubDir = fmap unsafeEncodeUtf $ stubDir flags } ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -264,6 +264,7 @@ import qualified GHC.LanguageExtensions as LangExt import GHC.Data.FastString import GHC.Data.Bag +import GHC.Data.OsPath (unsafeEncodeUtf) import GHC.Data.StringBuffer import qualified GHC.Data.Stream as Stream import GHC.Data.Stream (Stream) @@ -2111,12 +2112,13 @@ hscCompileCmmFile hsc_env original_filename filename output_filename = runHsc hs rawCmms return stub_c_exists where - no_loc = ModLocation{ ml_hs_file = Just original_filename, - ml_hi_file = panic "hscCompileCmmFile: no hi file", - ml_obj_file = panic "hscCompileCmmFile: no obj file", - ml_dyn_obj_file = panic "hscCompileCmmFile: no dyn obj file", - ml_dyn_hi_file = panic "hscCompileCmmFile: no dyn obj file", - ml_hie_file = panic "hscCompileCmmFile: no hie file"} + no_loc = OsPathModLocation + { ml_hs_file_ospath = Just $ unsafeEncodeUtf original_filename, + ml_hi_file_ospath = panic "hscCompileCmmFile: no hi file", + ml_obj_file_ospath = panic "hscCompileCmmFile: no obj file", + ml_dyn_obj_file_ospath = panic "hscCompileCmmFile: no dyn obj file", + ml_dyn_hi_file_ospath = panic "hscCompileCmmFile: no dyn obj file", + ml_hie_file_ospath = panic "hscCompileCmmFile: no hie file"} -------------------- Stuff for new code gen --------------------- @@ -2351,12 +2353,13 @@ hscParsedDecls hsc_env decls = runInteractiveHsc hsc_env $ do {- Desugar it -} -- We use a basically null location for iNTERACTIVE - let iNTERACTIVELoc = ModLocation{ ml_hs_file = Nothing, - ml_hi_file = panic "hsDeclsWithLocation:ml_hi_file", - ml_obj_file = panic "hsDeclsWithLocation:ml_obj_file", - ml_dyn_obj_file = panic "hsDeclsWithLocation:ml_dyn_obj_file", - ml_dyn_hi_file = panic "hsDeclsWithLocation:ml_dyn_hi_file", - ml_hie_file = panic "hsDeclsWithLocation:ml_hie_file" } + let iNTERACTIVELoc = OsPathModLocation + { ml_hs_file_ospath = Nothing, + ml_hi_file_ospath = panic "hsDeclsWithLocation:ml_hi_file_ospath", + ml_obj_file_ospath = panic "hsDeclsWithLocation:ml_obj_file_ospath", + ml_dyn_obj_file_ospath = panic "hsDeclsWithLocation:ml_dyn_obj_file_ospath", + ml_dyn_hi_file_ospath = panic "hsDeclsWithLocation:ml_dyn_hi_file_ospath", + ml_hie_file_ospath = panic "hsDeclsWithLocation:ml_hie_file_ospath" } ds_result <- hscDesugar' iNTERACTIVELoc tc_gblenv {- Simplify -} @@ -2635,12 +2638,13 @@ hscCompileCoreExpr' hsc_env srcspan ds_expr = do {- Lint if necessary -} lintInteractiveExpr (text "hscCompileCoreExpr") hsc_env prepd_expr - let this_loc = ModLocation{ ml_hs_file = Nothing, - ml_hi_file = panic "hscCompileCoreExpr':ml_hi_file", - ml_obj_file = panic "hscCompileCoreExpr':ml_obj_file", - ml_dyn_obj_file = panic "hscCompileCoreExpr': ml_obj_file", - ml_dyn_hi_file = panic "hscCompileCoreExpr': ml_dyn_hi_file", - ml_hie_file = panic "hscCompileCoreExpr':ml_hie_file" } + let this_loc = OsPathModLocation + { ml_hs_file_ospath = Nothing, + ml_hi_file_ospath = panic "hscCompileCoreExpr':ml_hi_file_ospath", + ml_obj_file_ospath = panic "hscCompileCoreExpr':ml_obj_file_ospath", + ml_dyn_obj_file_ospath = panic "hscCompileCoreExpr': ml_obj_file_ospath", + ml_dyn_hi_file_ospath = panic "hscCompileCoreExpr': ml_dyn_hi_file_ospath", + ml_hie_file_ospath = panic "hscCompileCoreExpr':ml_hie_file_ospath" } -- Ensure module uniqueness by giving it a name like "GhciNNNN". -- This uniqueness is needed by the JS linker. Without it we break the 1-1 ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -76,6 +76,7 @@ import GHC.Data.Bag ( listToBag ) import GHC.Data.Graph.Directed import GHC.Data.FastString import GHC.Data.Maybe ( expectJust ) +import GHC.Data.OsPath ( unsafeEncodeUtf ) import GHC.Data.StringBuffer import qualified GHC.LanguageExtensions as LangExt @@ -1837,7 +1838,7 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = tn <- newTempName logger tmpfs (tmpDir dflags) staticLife suf let dyn_tn = tn -<.> dynsuf addFilesToClean tmpfs dynLife [dyn_tn] - return (tn, dyn_tn) + return (unsafeEncodeUtf tn, unsafeEncodeUtf dyn_tn) -- We don't want to create .o or .hi files unless we have been asked -- to by the user. But we need them, so we patch their locations in -- the ModSummary with temporary files. @@ -1846,8 +1847,8 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = -- If ``-fwrite-interface` is specified, then the .o and .hi files -- are written into `-odir` and `-hidir` respectively. #16670 if gopt Opt_WriteInterface dflags - then return ((ml_hi_file ms_location, ml_dyn_hi_file ms_location) - , (ml_obj_file ms_location, ml_dyn_obj_file ms_location)) + then return ((ml_hi_file_ospath ms_location, ml_dyn_hi_file_ospath ms_location) + , (ml_obj_file_ospath ms_location, ml_dyn_obj_file_ospath ms_location)) else (,) <$> (new_temp_file (hiSuf_ dflags) (dynHiSuf_ dflags)) <*> (new_temp_file (objectSuf_ dflags) (dynObjectSuf_ dflags)) let new_dflags = case enable_spec of @@ -1856,10 +1857,10 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = EnableByteCodeAndObject -> (gopt_set dflags Opt_ByteCodeAndObjectCode) { backend = defaultBackendOf ms} let ms' = ms { ms_location = - ms_location { ml_hi_file = hi_file - , ml_obj_file = o_file - , ml_dyn_hi_file = dyn_hi_file - , ml_dyn_obj_file = dyn_o_file } + ms_location { ml_hi_file_ospath = hi_file + , ml_obj_file_ospath = o_file + , ml_dyn_hi_file_ospath = dyn_hi_file + , ml_dyn_obj_file_ospath = dyn_o_file } , ms_hspp_opts = updOptLevel 0 $ new_dflags } -- Recursive call to catch the other cases @@ -2044,7 +2045,7 @@ summariseFile hsc_env' home_unit old_summaries src_fn mb_phase maybe_buf let fopts = initFinderOpts (hsc_dflags hsc_env) -- Make a ModLocation for this file - let location = mkHomeModLocation fopts pi_mod_name src_fn + let location = mkHomeModLocation fopts pi_mod_name (unsafeEncodeUtf src_fn) -- Tell the Finder cache where it is, so that subsequent calls -- to findModule will find it, even if it's not on any search path ===================================== compiler/GHC/Driver/MakeFile.hs ===================================== @@ -24,6 +24,7 @@ import GHC.Driver.Env import GHC.Driver.Errors.Types import qualified GHC.SysTools as SysTools import GHC.Data.Graph.Directed ( SCC(..) ) +import GHC.Data.OsPath (unsafeDecodeUtf) import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Types.SourceError @@ -252,7 +253,7 @@ processDeps dflags hsc_env excl_mods root hdl (AcyclicSCC (ModuleNode _ node)) -- files if the module has a corresponding .hs-boot file (#14482) ; when (isBootSummary node == IsBoot) $ do let hi_boot = msHiFilePath node - let obj = removeBootSuffix (msObjFilePath node) + let obj = unsafeDecodeUtf $ removeBootSuffix (msObjFileOsPath node) forM_ extra_suffixes $ \suff -> do let way_obj = insertSuffixes obj [suff] let way_hi_boot = insertSuffixes hi_boot [suff] @@ -297,7 +298,7 @@ findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps = do Found loc _ -- Home package: just depend on the .hi or hi-boot file | isJust (ml_hs_file loc) || include_pkg_deps - -> return (Just (addBootSuffix_maybe is_boot (ml_hi_file loc))) + -> return (Just (unsafeDecodeUtf $ addBootSuffix_maybe is_boot (ml_hi_file_ospath loc))) -- Not in this package: we don't need a dependency | otherwise ===================================== compiler/GHC/Driver/Pipeline/Execute.hs ===================================== @@ -58,6 +58,7 @@ import GHC.Iface.Make import GHC.Driver.Config.Parser import GHC.Parser.Header import GHC.Data.StringBuffer +import GHC.Data.OsPath (unsafeEncodeUtf) import GHC.Types.SourceError import GHC.Unit.Finder import Data.IORef @@ -772,7 +773,7 @@ mkOneShotModLocation :: PipeEnv -> DynFlags -> HscSource -> ModuleName -> IO Mod mkOneShotModLocation pipe_env dflags src_flavour mod_name = do let PipeEnv{ src_basename=basename, src_suffix=suff } = pipe_env - let location1 = mkHomeModLocation2 fopts mod_name basename suff + let location1 = mkHomeModLocation2 fopts mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf suff) -- Boot-ify it if necessary let location2 @@ -784,11 +785,11 @@ mkOneShotModLocation pipe_env dflags src_flavour mod_name = do -- This can't be done in mkHomeModuleLocation because -- it only applies to the module being compiles let ohi = outputHi dflags - location3 | Just fn <- ohi = location2{ ml_hi_file = fn } + location3 | Just fn <- ohi = location2{ ml_hi_file_ospath = unsafeEncodeUtf fn } | otherwise = location2 let dynohi = dynOutputHi dflags - location4 | Just fn <- dynohi = location3{ ml_dyn_hi_file = fn } + location4 | Just fn <- dynohi = location3{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn } | otherwise = location3 -- Take -o into account if present @@ -802,10 +803,10 @@ mkOneShotModLocation pipe_env dflags src_flavour mod_name = do location5 | Just ofile <- expl_o_file , let dyn_ofile = fromMaybe (ofile -<.> dynObjectSuf_ dflags) expl_dyn_o_file , isNoLink (ghcLink dflags) - = location4 { ml_obj_file = ofile - , ml_dyn_obj_file = dyn_ofile } + = location4 { ml_obj_file_ospath = unsafeEncodeUtf ofile + , ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile } | Just dyn_ofile <- expl_dyn_o_file - = location4 { ml_dyn_obj_file = dyn_ofile } + = location4 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile } | otherwise = location4 return location5 where ===================================== compiler/GHC/Iface/Errors.hs ===================================== @@ -14,6 +14,7 @@ import GHC.Utils.Panic.Plain import GHC.Driver.DynFlags import GHC.Driver.Env import GHC.Data.Maybe +import GHC.Data.OsPath import GHC.Prelude import GHC.Unit import GHC.Unit.Env @@ -55,13 +56,13 @@ cantFindInstalledErr unit_state mhome_unit profile mod_name find_result InstalledNotFound files mb_pkg | Just pkg <- mb_pkg , notHomeUnitId mhome_unit pkg - -> not_found_in_package pkg files + -> not_found_in_package pkg $ fmap unsafeDecodeUtf files | null files -> NotAModule | otherwise - -> CouldntFindInFiles files + -> CouldntFindInFiles $ fmap unsafeDecodeUtf files _ -> panic "cantFindInstalledErr" ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1894,53 +1894,179 @@ genericWordQuotRemOp width [res_q, res_r] [arg_x, arg_y] (CmmMachOp (MO_U_Rem width) [arg_x, arg_y]) genericWordQuotRemOp _ _ _ = panic "genericWordQuotRemOp" +-- Based on the algorithm from LLVM's compiler-rt: +-- https://github.com/llvm/llvm-project/blob/7339f7ba3053db7595ece1ca5f49bd2e4c3c8305/compiler-rt/lib/builtins/udivmodti4.c#L23 +-- See that file for licensing and copyright. genericWordQuotRem2Op :: Platform -> GenericOp -genericWordQuotRem2Op platform [res_q, res_r] [arg_x_high, arg_x_low, arg_y] - = emit =<< f (widthInBits (wordWidth platform)) zero arg_x_high arg_x_low - where ty = cmmExprType platform arg_x_high - shl x i = CmmMachOp (MO_Shl (wordWidth platform)) [x, i] - shr x i = CmmMachOp (MO_U_Shr (wordWidth platform)) [x, i] - or x y = CmmMachOp (MO_Or (wordWidth platform)) [x, y] - ge x y = CmmMachOp (MO_U_Ge (wordWidth platform)) [x, y] - ne x y = CmmMachOp (MO_Ne (wordWidth platform)) [x, y] - minus x y = CmmMachOp (MO_Sub (wordWidth platform)) [x, y] - times x y = CmmMachOp (MO_Mul (wordWidth platform)) [x, y] - zero = lit 0 - one = lit 1 - negone = lit (fromIntegral (platformWordSizeInBits platform) - 1) - lit i = CmmLit (CmmInt i (wordWidth platform)) - - f :: Int -> CmmExpr -> CmmExpr -> CmmExpr -> FCode CmmAGraph - f 0 acc high _ = return (mkAssign (CmmLocal res_q) acc <*> - mkAssign (CmmLocal res_r) high) - f i acc high low = - do roverflowedBit <- newTemp ty - rhigh' <- newTemp ty - rhigh'' <- newTemp ty - rlow' <- newTemp ty - risge <- newTemp ty - racc' <- newTemp ty - let high' = CmmReg (CmmLocal rhigh') - isge = CmmReg (CmmLocal risge) - overflowedBit = CmmReg (CmmLocal roverflowedBit) - let this = catAGraphs - [mkAssign (CmmLocal roverflowedBit) - (shr high negone), - mkAssign (CmmLocal rhigh') - (or (shl high one) (shr low negone)), - mkAssign (CmmLocal rlow') - (shl low one), - mkAssign (CmmLocal risge) - (or (overflowedBit `ne` zero) - (high' `ge` arg_y)), - mkAssign (CmmLocal rhigh'') - (high' `minus` (arg_y `times` isge)), - mkAssign (CmmLocal racc') - (or (shl acc one) isge)] - rest <- f (i - 1) (CmmReg (CmmLocal racc')) - (CmmReg (CmmLocal rhigh'')) - (CmmReg (CmmLocal rlow')) - return (this <*> rest) +genericWordQuotRem2Op platform [res_q, res_r] [arg_u1, arg_u0, arg_v] + = do + -- v gets modified below based on clz v + v <- newTemp ty + emit $ mkAssign (CmmLocal v) arg_v + go arg_u1 arg_u0 v + where ty = cmmExprType platform arg_u1 + shl x i = CmmMachOp (MO_Shl (wordWidth platform)) [x, i] + shr x i = CmmMachOp (MO_U_Shr (wordWidth platform)) [x, i] + or x y = CmmMachOp (MO_Or (wordWidth platform)) [x, y] + ge x y = CmmMachOp (MO_U_Ge (wordWidth platform)) [x, y] + le x y = CmmMachOp (MO_U_Le (wordWidth platform)) [x, y] + eq x y = CmmMachOp (MO_Eq (wordWidth platform)) [x, y] + plus x y = CmmMachOp (MO_Add (wordWidth platform)) [x, y] + minus x y = CmmMachOp (MO_Sub (wordWidth platform)) [x, y] + times x y = CmmMachOp (MO_Mul (wordWidth platform)) [x, y] + udiv x y = CmmMachOp (MO_U_Quot (wordWidth platform)) [x, y] + and x y = CmmMachOp (MO_And (wordWidth platform)) [x, y] + lit i = CmmLit (CmmInt i (wordWidth platform)) + one = lit 1 + zero = lit 0 + masklow = lit ((1 `shiftL` (platformWordSizeInBits platform `div` 2)) - 1) + gotoIf pred target = emit =<< mkCmmIfGoto pred target + mkTmp ty = do + t <- newTemp ty + pure (t, CmmReg (CmmLocal t)) + infixr 8 .= + r .= e = emit $ mkAssign (CmmLocal r) e + + go :: CmmActual -> CmmActual -> LocalReg -> FCode () + go u1 u0 v = do + -- Computes (ret,r) = (u1< 0) { + -- actually if (s > 0 && s /= wordSizeInBits) { + gotoIf (s' `eq` zero) if_else + gotoIf (s' `eq` lit n_udword_bits) if_else + do + -- // Normalize the divisor. + -- v = v << s; + v .= shl v' s' + -- un64 = (u1 << s) | (u0 >> (n_udword_bits - s)); + un64 .= (u1 `shl` s') `or` (u0 `shr` (lit n_udword_bits `minus` s')) + -- un10 = u0 << s; // Shift dividend left + un10 .= shl u0 s' + emit $ mkBranch if_done + -- } else { + do + -- // Avoid undefined behavior of (u0 >> 64). + emitLabel if_else + -- un64 = u1; + un64 .= u1 + -- un10 = u0; + un10 .= u0 + s .= lit 0 -- Otherwise leads to >>/<< 64 + -- } + emitLabel if_done + + -- // Break divisor up into two 32-bit digits. + -- vn1 = v >> (n_udword_bits / 2); + vn1 .= v' `shr` lit (n_udword_bits `div` 2) + -- vn0 = v & 0xFFFFFFFF; + vn0 .= v' `and` masklow + + -- // Break right half of dividend into two digits. + -- un1 = un10 >> (n_udword_bits / 2); + un1 .= un10' `shr` lit (n_udword_bits `div` 2) + -- un0 = un10 & 0xFFFFFFFF; + un0 .= un10' `and` masklow + + -- // Compute the first quotient digit, q1. + -- q1 = un64 / vn1; + q1 .= un64' `udiv` vn1' + -- rhat = un64 - q1 * vn1; + rhat .= un64' `minus` times q1' vn1' + + while_1_entry <- newBlockId + while_1_body <- newBlockId + while_1_done <- newBlockId + -- // q1 has at most error 2. No more than 2 iterations. + -- while (q1 >= b || q1 * vn0 > b * rhat + un1) { + emitLabel while_1_entry + gotoIf (q1' `ge` lit b) while_1_body + gotoIf (le (times q1' vn0') + (times (lit b) rhat' `plus` un1')) + while_1_done + do + emitLabel while_1_body + -- q1 = q1 - 1; + q1 .= q1' `minus` one + -- rhat = rhat + vn1; + rhat .= rhat' `plus` vn1' + -- if (rhat >= b) + -- break; + gotoIf (rhat' `ge` lit b) + while_1_done + emit $ mkBranch while_1_entry + -- } + emitLabel while_1_done + + -- un21 = un64 * b + un1 - q1 * v; + un21 .= (times un64' (lit b) `plus` un1') `minus` times q1' v' + + -- // Compute the second quotient digit. + -- q0 = un21 / vn1; + q0 .= un21' `udiv` vn1' + -- rhat = un21 - q0 * vn1; + rhat .= un21' `minus` times q0' vn1' + + -- // q0 has at most error 2. No more than 2 iterations. + while_2_entry <- newBlockId + while_2_body <- newBlockId + while_2_done <- newBlockId + emitLabel while_2_entry + -- while (q0 >= b || q0 * vn0 > b * rhat + un0) { + gotoIf (q0' `ge` lit b) + while_2_body + gotoIf (le (times q0' vn0') + (times (lit b) rhat' `plus` un0')) + while_2_done + do + emitLabel while_2_body + -- q0 = q0 - 1; + q0 .= q0' `minus` one + -- rhat = rhat + vn1; + rhat .= rhat' `plus` vn1' + -- if (rhat >= b) + -- break; + gotoIf (rhat' `ge` lit b) while_2_done + emit $ mkBranch while_2_entry + -- } + emitLabel while_2_done + + -- r = (un21 * b + un0 - q0 * v) >> s; + res_r .= ((times un21' (lit b) `plus` un0') `minus` times q0' v') `shr` s' + -- return q1 * b + q0; + res_q .= times q1' (lit b) `plus` q0' genericWordQuotRem2Op _ _ _ = panic "genericWordQuotRem2Op" genericWordAdd2Op :: GenericOp @@ -2176,8 +2302,8 @@ alignmentFromTypes :: CmmType -- ^ element type -> CmmType -- ^ index type -> AlignmentSpec alignmentFromTypes ty idx_ty - | typeWidth ty < typeWidth idx_ty = NaturallyAligned - | otherwise = Unaligned + | typeWidth ty <= typeWidth idx_ty = NaturallyAligned + | otherwise = Unaligned doIndexOffAddrOp :: Maybe MachOp -> CmmType ===================================== compiler/GHC/Unit/Finder.hs ===================================== @@ -42,6 +42,9 @@ import GHC.Platform.Ways import GHC.Builtin.Names ( gHC_PRIM ) +import GHC.Data.Maybe ( expectJust ) +import GHC.Data.OsPath + import GHC.Unit.Env import GHC.Unit.Types import GHC.Unit.Module @@ -49,7 +52,6 @@ import GHC.Unit.Home import GHC.Unit.State import GHC.Unit.Finder.Types -import GHC.Data.Maybe ( expectJust ) import qualified GHC.Data.ShortText as ST import GHC.Utils.Misc @@ -61,8 +63,7 @@ import GHC.Types.PkgQual import GHC.Fingerprint import Data.IORef -import System.Directory -import System.FilePath +import System.Directory.OsPath import Control.Monad import Data.Time import qualified Data.Map as M @@ -70,9 +71,10 @@ import GHC.Driver.Env ( hsc_home_unit_maybe, HscEnv(hsc_FC, hsc_dflags, hsc_unit_env) ) import GHC.Driver.Config.Finder import qualified Data.Set as Set +import qualified System.OsPath as OsPath -type FileExt = String -- Filename extension -type BaseName = String -- Basename of file +type FileExt = OsString -- Filename extension +type BaseName = OsPath -- Basename of file -- ----------------------------------------------------------------------------- -- The Finder @@ -286,7 +288,7 @@ findLookupResult fc fopts r = case r of -- implicit locations from the instances InstalledFound loc _ -> return (Found loc m) InstalledNoPackage _ -> return (NoPackage (moduleUnit m)) - InstalledNotFound fp _ -> return (NotFound{ fr_paths = fp, fr_pkg = Just (moduleUnit m) + InstalledNotFound fp _ -> return (NotFound{ fr_paths = fmap unsafeDecodeUtf fp, fr_pkg = Just (moduleUnit m) , fr_pkgs_hidden = [] , fr_mods_hidden = [] , fr_unusables = [] @@ -357,7 +359,7 @@ findHomeModule fc fopts home_unit mod_name = do InstalledFound loc _ -> Found loc (mkHomeModule home_unit mod_name) InstalledNoPackage _ -> NoPackage uid -- impossible InstalledNotFound fps _ -> NotFound { - fr_paths = fps, + fr_paths = fmap unsafeDecodeUtf fps, fr_pkg = Just uid, fr_mods_hidden = [], fr_pkgs_hidden = [], @@ -382,7 +384,7 @@ findHomePackageModule fc fopts home_unit mod_name = do InstalledFound loc _ -> Found loc (mkModule uid mod_name) InstalledNoPackage _ -> NoPackage uid -- impossible InstalledNotFound fps _ -> NotFound { - fr_paths = fps, + fr_paths = fmap unsafeDecodeUtf fps, fr_pkg = Just uid, fr_mods_hidden = [], fr_pkgs_hidden = [], @@ -418,17 +420,17 @@ findInstalledHomeModule fc fopts home_unit mod_name = do hi_dir_path = case finder_hiDir fopts of Just hiDir -> case maybe_working_dir of - Nothing -> [hiDir] - Just fp -> [fp hiDir] + Nothing -> [hiDir] + Just fp -> [fp hiDir] Nothing -> home_path hisuf = finder_hiSuf fopts mod = mkModule home_unit mod_name source_exts = - [ ("hs", mkHomeModLocationSearched fopts mod_name "hs") - , ("lhs", mkHomeModLocationSearched fopts mod_name "lhs") - , ("hsig", mkHomeModLocationSearched fopts mod_name "hsig") - , ("lhsig", mkHomeModLocationSearched fopts mod_name "lhsig") + [ (os "hs", mkHomeModLocationSearched fopts mod_name $ os "hs") + , (os "lhs", mkHomeModLocationSearched fopts mod_name $ os "lhs") + , (os "hsig", mkHomeModLocationSearched fopts mod_name $ os "hsig") + , (os "lhsig", mkHomeModLocationSearched fopts mod_name $ os "lhsig") ] -- we use mkHomeModHiOnlyLocation instead of mkHiOnlyModLocation so that @@ -453,10 +455,11 @@ findInstalledHomeModule fc fopts home_unit mod_name = do else searchPathExts search_dirs mod exts -- | Prepend the working directory to the search path. -augmentImports :: FilePath -> [FilePath] -> [FilePath] +augmentImports :: OsPath -> [OsPath] -> [OsPath] augmentImports _work_dir [] = [] -augmentImports work_dir (fp:fps) | isAbsolute fp = fp : augmentImports work_dir fps - | otherwise = (work_dir fp) : augmentImports work_dir fps +augmentImports work_dir (fp:fps) + | OsPath.isAbsolute fp = fp : augmentImports work_dir fps + | otherwise = (work_dir fp) : augmentImports work_dir fps -- | Search for a module in external packages only. findPackageModule :: FinderCache -> UnitState -> FinderOpts -> InstalledModule -> IO InstalledFindResult @@ -488,14 +491,14 @@ findPackageModule_ fc fopts mod pkg_conf = do tag = waysBuildTag (finder_ways fopts) -- hi-suffix for packages depends on the build tag. - package_hisuf | null tag = "hi" - | otherwise = tag ++ "_hi" + package_hisuf | null tag = os "hi" + | otherwise = os (tag ++ "_hi") - package_dynhisuf = waysBuildTag (addWay WayDyn (finder_ways fopts)) ++ "_hi" + package_dynhisuf = os $ waysBuildTag (addWay WayDyn (finder_ways fopts)) ++ "_hi" mk_hi_loc = mkHiOnlyModLocation fopts package_hisuf package_dynhisuf - import_dirs = map ST.unpack $ unitImportDirs pkg_conf + import_dirs = map (unsafeEncodeUtf . ST.unpack) $ unitImportDirs pkg_conf -- we never look for a .hi-boot file in an external package; -- .hi-boot files only make sense for the home package. in @@ -503,7 +506,7 @@ findPackageModule_ fc fopts mod pkg_conf = do [one] | finder_bypassHiFileCheck fopts -> -- there's only one place that this .hi file can be, so -- don't bother looking for it. - let basename = moduleNameSlashes (moduleName mod) + let basename = unsafeEncodeUtf $ moduleNameSlashes (moduleName mod) loc = mk_hi_loc one basename in return $ InstalledFound loc mod _otherwise -> @@ -512,24 +515,24 @@ findPackageModule_ fc fopts mod pkg_conf = do -- ----------------------------------------------------------------------------- -- General path searching -searchPathExts :: [FilePath] -- paths to search +searchPathExts :: [OsPath] -- paths to search -> InstalledModule -- module name -> [ ( - FileExt, -- suffix - FilePath -> BaseName -> ModLocation -- action + FileExt, -- suffix + OsPath -> BaseName -> ModLocation -- action ) ] -> IO InstalledFindResult searchPathExts paths mod exts = search to_search where - basename = moduleNameSlashes (moduleName mod) + basename = unsafeEncodeUtf $ moduleNameSlashes (moduleName mod) - to_search :: [(FilePath, ModLocation)] + to_search :: [(OsPath, ModLocation)] to_search = [ (file, fn path basename) | path <- paths, (ext,fn) <- exts, - let base | path == "." = basename + let base | path == os "." = basename | otherwise = path basename file = base <.> ext ] @@ -543,7 +546,7 @@ searchPathExts paths mod exts = search to_search else search rest mkHomeModLocationSearched :: FinderOpts -> ModuleName -> FileExt - -> FilePath -> BaseName -> ModLocation + -> OsPath -> BaseName -> ModLocation mkHomeModLocationSearched fopts mod suff path basename = mkHomeModLocation2 fopts mod (path basename) suff @@ -581,18 +584,18 @@ mkHomeModLocationSearched fopts mod suff path basename = -- ext -- The filename extension of the source file (usually "hs" or "lhs"). -mkHomeModLocation :: FinderOpts -> ModuleName -> FilePath -> ModLocation +mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> ModLocation mkHomeModLocation dflags mod src_filename = - let (basename,extension) = splitExtension src_filename + let (basename,extension) = OsPath.splitExtension src_filename in mkHomeModLocation2 dflags mod basename extension mkHomeModLocation2 :: FinderOpts -> ModuleName - -> FilePath -- Of source module, without suffix - -> String -- Suffix + -> OsPath -- Of source module, without suffix + -> FileExt -- Suffix -> ModLocation mkHomeModLocation2 fopts mod src_basename ext = - let mod_basename = moduleNameSlashes mod + let mod_basename = unsafeEncodeUtf $ moduleNameSlashes mod obj_fn = mkObjPath fopts src_basename mod_basename dyn_obj_fn = mkDynObjPath fopts src_basename mod_basename @@ -600,51 +603,51 @@ mkHomeModLocation2 fopts mod src_basename ext = dyn_hi_fn = mkDynHiPath fopts src_basename mod_basename hie_fn = mkHiePath fopts src_basename mod_basename - in (ModLocation{ ml_hs_file = Just (src_basename <.> ext), - ml_hi_file = hi_fn, - ml_dyn_hi_file = dyn_hi_fn, - ml_obj_file = obj_fn, - ml_dyn_obj_file = dyn_obj_fn, - ml_hie_file = hie_fn }) + in (OsPathModLocation{ ml_hs_file_ospath = Just (src_basename <.> ext), + ml_hi_file_ospath = hi_fn, + ml_dyn_hi_file_ospath = dyn_hi_fn, + ml_obj_file_ospath = obj_fn, + ml_dyn_obj_file_ospath = dyn_obj_fn, + ml_hie_file_ospath = hie_fn }) mkHomeModHiOnlyLocation :: FinderOpts -> ModuleName - -> FilePath + -> OsPath -> BaseName -> ModLocation mkHomeModHiOnlyLocation fopts mod path basename = - let loc = mkHomeModLocation2 fopts mod (path basename) "" - in loc { ml_hs_file = Nothing } + let loc = mkHomeModLocation2 fopts mod (path basename) mempty + in loc { ml_hs_file_ospath = Nothing } -- This function is used to make a ModLocation for a package module. Hence why -- we explicitly pass in the interface file suffixes. -mkHiOnlyModLocation :: FinderOpts -> Suffix -> Suffix -> FilePath -> String +mkHiOnlyModLocation :: FinderOpts -> FileExt -> FileExt -> OsPath -> OsPath -> ModLocation mkHiOnlyModLocation fopts hisuf dynhisuf path basename = let full_basename = path basename obj_fn = mkObjPath fopts full_basename basename dyn_obj_fn = mkDynObjPath fopts full_basename basename hie_fn = mkHiePath fopts full_basename basename - in ModLocation{ ml_hs_file = Nothing, - ml_hi_file = full_basename <.> hisuf, - -- Remove the .hi-boot suffix from - -- hi_file, if it had one. We always - -- want the name of the real .hi file - -- in the ml_hi_file field. - ml_dyn_obj_file = dyn_obj_fn, - -- MP: TODO - ml_dyn_hi_file = full_basename <.> dynhisuf, - ml_obj_file = obj_fn, - ml_hie_file = hie_fn + in OsPathModLocation{ ml_hs_file_ospath = Nothing, + ml_hi_file_ospath = full_basename <.> hisuf, + -- Remove the .hi-boot suffix from + -- hi_file, if it had one. We always + -- want the name of the real .hi file + -- in the ml_hi_file field. + ml_dyn_obj_file_ospath = dyn_obj_fn, + -- MP: TODO + ml_dyn_hi_file_ospath = full_basename <.> dynhisuf, + ml_obj_file_ospath = obj_fn, + ml_hie_file_ospath = hie_fn } -- | Constructs the filename of a .o file for a given source file. -- Does /not/ check whether the .o file exists mkObjPath :: FinderOpts - -> FilePath -- the filename of the source file, minus the extension - -> String -- the module name with dots replaced by slashes - -> FilePath + -> OsPath -- the filename of the source file, minus the extension + -> OsPath -- the module name with dots replaced by slashes + -> OsPath mkObjPath fopts basename mod_basename = obj_basename <.> osuf where odir = finder_objectDir fopts @@ -657,9 +660,9 @@ mkObjPath fopts basename mod_basename = obj_basename <.> osuf -- Does /not/ check whether the .dyn_o file exists mkDynObjPath :: FinderOpts - -> FilePath -- the filename of the source file, minus the extension - -> String -- the module name with dots replaced by slashes - -> FilePath + -> OsPath -- the filename of the source file, minus the extension + -> OsPath -- the module name with dots replaced by slashes + -> OsPath mkDynObjPath fopts basename mod_basename = obj_basename <.> dynosuf where odir = finder_objectDir fopts @@ -673,9 +676,9 @@ mkDynObjPath fopts basename mod_basename = obj_basename <.> dynosuf -- Does /not/ check whether the .hi file exists mkHiPath :: FinderOpts - -> FilePath -- the filename of the source file, minus the extension - -> String -- the module name with dots replaced by slashes - -> FilePath + -> OsPath -- the filename of the source file, minus the extension + -> OsPath -- the module name with dots replaced by slashes + -> OsPath mkHiPath fopts basename mod_basename = hi_basename <.> hisuf where hidir = finder_hiDir fopts @@ -688,9 +691,9 @@ mkHiPath fopts basename mod_basename = hi_basename <.> hisuf -- Does /not/ check whether the .dyn_hi file exists mkDynHiPath :: FinderOpts - -> FilePath -- the filename of the source file, minus the extension - -> String -- the module name with dots replaced by slashes - -> FilePath + -> OsPath -- the filename of the source file, minus the extension + -> OsPath -- the module name with dots replaced by slashes + -> OsPath mkDynHiPath fopts basename mod_basename = hi_basename <.> dynhisuf where hidir = finder_hiDir fopts @@ -703,9 +706,9 @@ mkDynHiPath fopts basename mod_basename = hi_basename <.> dynhisuf -- Does /not/ check whether the .hie file exists mkHiePath :: FinderOpts - -> FilePath -- the filename of the source file, minus the extension - -> String -- the module name with dots replaced by slashes - -> FilePath + -> OsPath -- the filename of the source file, minus the extension + -> OsPath -- the module name with dots replaced by slashes + -> OsPath mkHiePath fopts basename mod_basename = hie_basename <.> hiesuf where hiedir = finder_hieDir fopts @@ -726,23 +729,23 @@ mkStubPaths :: FinderOpts -> ModuleName -> ModLocation - -> FilePath + -> OsPath mkStubPaths fopts mod location = let stubdir = finder_stubDir fopts - mod_basename = moduleNameSlashes mod - src_basename = dropExtension $ expectJust "mkStubPaths" - (ml_hs_file location) + mod_basename = unsafeEncodeUtf $ moduleNameSlashes mod + src_basename = OsPath.dropExtension $ expectJust "mkStubPaths" + (ml_hs_file_ospath location) stub_basename0 | Just dir <- stubdir = dir mod_basename | otherwise = src_basename - stub_basename = stub_basename0 ++ "_stub" + stub_basename = stub_basename0 `mappend` os "_stub" in - stub_basename <.> "h" + stub_basename <.> os "h" -- ----------------------------------------------------------------------------- -- findLinkable isn't related to the other stuff in here, ===================================== compiler/GHC/Unit/Finder/Types.hs ===================================== @@ -9,6 +9,7 @@ where import GHC.Prelude import GHC.Unit +import GHC.Data.OsPath import qualified Data.Map as M import GHC.Fingerprint import GHC.Platform.Ways @@ -31,7 +32,7 @@ data FinderCache = FinderCache { fcModuleCache :: (IORef FinderCacheState) data InstalledFindResult = InstalledFound ModLocation InstalledModule | InstalledNoPackage UnitId - | InstalledNotFound [FilePath] (Maybe UnitId) + | InstalledNotFound [OsPath] (Maybe UnitId) -- | The result of searching for an imported module. -- @@ -70,7 +71,7 @@ data FindResult -- -- Should be taken from 'DynFlags' via 'initFinderOpts'. data FinderOpts = FinderOpts - { finder_importPaths :: [FilePath] + { finder_importPaths :: [OsPath] -- ^ Where are we allowed to look for Modules and Source files , finder_lookupHomeInterfaces :: Bool -- ^ When looking up a home module: @@ -88,17 +89,17 @@ data FinderOpts = FinderOpts , finder_enableSuggestions :: Bool -- ^ If we encounter unknown modules, should we suggest modules -- that have a similar name. - , finder_workingDirectory :: Maybe FilePath + , finder_workingDirectory :: Maybe OsPath , finder_thisPackageName :: Maybe FastString , finder_hiddenModules :: Set.Set ModuleName , finder_reexportedModules :: Set.Set ModuleName - , finder_hieDir :: Maybe FilePath - , finder_hieSuf :: String - , finder_hiDir :: Maybe FilePath - , finder_hiSuf :: String - , finder_dynHiSuf :: String - , finder_objectDir :: Maybe FilePath - , finder_objectSuf :: String - , finder_dynObjectSuf :: String - , finder_stubDir :: Maybe FilePath + , finder_hieDir :: Maybe OsPath + , finder_hieSuf :: OsString + , finder_hiDir :: Maybe OsPath + , finder_hiSuf :: OsString + , finder_dynHiSuf :: OsString + , finder_objectDir :: Maybe OsPath + , finder_objectSuf :: OsString + , finder_dynObjectSuf :: OsString + , finder_stubDir :: Maybe OsPath } deriving Show ===================================== compiler/GHC/Unit/Module/Location.hs ===================================== @@ -1,6 +1,17 @@ +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE ViewPatterns #-} -- | Module location module GHC.Unit.Module.Location - ( ModLocation(..) + ( ModLocation + ( .. + , ml_hs_file + , ml_hi_file + , ml_dyn_hi_file + , ml_obj_file + , ml_dyn_obj_file + , ml_hie_file + ) + , pattern ModLocation , addBootSuffix , addBootSuffix_maybe , addBootSuffixLocn_maybe @@ -11,15 +22,19 @@ module GHC.Unit.Module.Location where import GHC.Prelude + +import GHC.Data.OsPath import GHC.Unit.Types import GHC.Utils.Outputable +import qualified System.OsString as OsString + -- | Module Location -- -- Where a module lives on the file system: the actual locations -- of the .hs, .hi, .dyn_hi, .o, .dyn_o and .hie files, if we have them. -- --- For a module in another unit, the ml_hs_file and ml_obj_file components of +-- For a module in another unit, the ml_hs_file_ospath and ml_obj_file_ospath components of -- ModLocation are undefined. -- -- The locations specified by a ModLocation may or may not @@ -38,31 +53,31 @@ import GHC.Utils.Outputable -- boot suffixes in mkOneShotModLocation. data ModLocation - = ModLocation { - ml_hs_file :: Maybe FilePath, + = OsPathModLocation { + ml_hs_file_ospath :: Maybe OsPath, -- ^ The source file, if we have one. Package modules -- probably don't have source files. - ml_hi_file :: FilePath, + ml_hi_file_ospath :: OsPath, -- ^ Where the .hi file is, whether or not it exists -- yet. Always of form foo.hi, even if there is an -- hi-boot file (we add the -boot suffix later) - ml_dyn_hi_file :: FilePath, + ml_dyn_hi_file_ospath :: OsPath, -- ^ Where the .dyn_hi file is, whether or not it exists -- yet. - ml_obj_file :: FilePath, + ml_obj_file_ospath :: OsPath, -- ^ Where the .o file is, whether or not it exists yet. -- (might not exist either because the module hasn't -- been compiled yet, or because it is part of a -- unit with a .a file) - ml_dyn_obj_file :: FilePath, + ml_dyn_obj_file_ospath :: OsPath, -- ^ Where the .dy file is, whether or not it exists -- yet. - ml_hie_file :: FilePath + ml_hie_file_ospath :: OsPath -- ^ Where the .hie file is, whether or not it exists -- yet. } deriving Show @@ -71,18 +86,18 @@ instance Outputable ModLocation where ppr = text . show -- | Add the @-boot@ suffix to .hs, .hi and .o files -addBootSuffix :: FilePath -> FilePath -addBootSuffix path = path ++ "-boot" +addBootSuffix :: OsPath -> OsPath +addBootSuffix path = path `mappend` os "-boot" -- | Remove the @-boot@ suffix to .hs, .hi and .o files -removeBootSuffix :: FilePath -> FilePath -removeBootSuffix "-boot" = [] -removeBootSuffix (x:xs) = x : removeBootSuffix xs -removeBootSuffix [] = error "removeBootSuffix: no -boot suffix" - +removeBootSuffix :: OsPath -> OsPath +removeBootSuffix pathWithBootSuffix = + case OsString.stripSuffix (os "-boot") pathWithBootSuffix of + Just path -> path + Nothing -> error "removeBootSuffix: no -boot suffix" -- | Add the @-boot@ suffix if the @Bool@ argument is @True@ -addBootSuffix_maybe :: IsBootInterface -> FilePath -> FilePath +addBootSuffix_maybe :: IsBootInterface -> OsPath -> OsPath addBootSuffix_maybe is_boot path = case is_boot of IsBoot -> addBootSuffix path NotBoot -> path @@ -95,22 +110,50 @@ addBootSuffixLocn_maybe is_boot locn = case is_boot of -- | Add the @-boot@ suffix to all file paths associated with the module addBootSuffixLocn :: ModLocation -> ModLocation addBootSuffixLocn locn - = locn { ml_hs_file = fmap addBootSuffix (ml_hs_file locn) - , ml_hi_file = addBootSuffix (ml_hi_file locn) - , ml_dyn_hi_file = addBootSuffix (ml_dyn_hi_file locn) - , ml_obj_file = addBootSuffix (ml_obj_file locn) - , ml_dyn_obj_file = addBootSuffix (ml_dyn_obj_file locn) - , ml_hie_file = addBootSuffix (ml_hie_file locn) } + = locn { ml_hs_file_ospath = fmap addBootSuffix (ml_hs_file_ospath locn) + , ml_hi_file_ospath = addBootSuffix (ml_hi_file_ospath locn) + , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn) + , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn) + , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn) + , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn) } -- | Add the @-boot@ suffix to all output file paths associated with the -- module, not including the input file itself addBootSuffixLocnOut :: ModLocation -> ModLocation addBootSuffixLocnOut locn - = locn { ml_hi_file = addBootSuffix (ml_hi_file locn) - , ml_dyn_hi_file = addBootSuffix (ml_dyn_hi_file locn) - , ml_obj_file = addBootSuffix (ml_obj_file locn) - , ml_dyn_obj_file = addBootSuffix (ml_dyn_obj_file locn) - , ml_hie_file = addBootSuffix (ml_hie_file locn) + = locn { ml_hi_file_ospath = addBootSuffix (ml_hi_file_ospath locn) + , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn) + , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn) + , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn) + , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn) } - +-- ---------------------------------------------------------------------------- +-- Helpers for backwards compatibility +-- ---------------------------------------------------------------------------- + +pattern ModLocation :: Maybe FilePath -> FilePath -> FilePath -> FilePath -> FilePath -> FilePath -> ModLocation +pattern ModLocation + { ml_hs_file + , ml_hi_file + , ml_dyn_hi_file + , ml_obj_file + , ml_dyn_obj_file + , ml_hie_file + } <- OsPathModLocation + { ml_hs_file_ospath = (fmap unsafeDecodeUtf -> ml_hs_file) + , ml_hi_file_ospath = (unsafeDecodeUtf -> ml_hi_file) + , ml_dyn_hi_file_ospath = (unsafeDecodeUtf -> ml_dyn_hi_file) + , ml_obj_file_ospath = (unsafeDecodeUtf -> ml_obj_file) + , ml_dyn_obj_file_ospath = (unsafeDecodeUtf -> ml_dyn_obj_file) + , ml_hie_file_ospath = (unsafeDecodeUtf -> ml_hie_file) + } where + ModLocation ml_hs_file ml_hi_file ml_dyn_hi_file ml_obj_file ml_dyn_obj_file ml_hie_file + = OsPathModLocation + { ml_hs_file_ospath = fmap unsafeEncodeUtf ml_hs_file + , ml_hi_file_ospath = unsafeEncodeUtf ml_hi_file + , ml_dyn_hi_file_ospath = unsafeEncodeUtf ml_dyn_hi_file + , ml_obj_file_ospath = unsafeEncodeUtf ml_obj_file + , ml_dyn_obj_file_ospath = unsafeEncodeUtf ml_dyn_obj_file + , ml_hie_file_ospath = unsafeEncodeUtf ml_hie_file + } ===================================== compiler/GHC/Unit/Module/ModSummary.hs ===================================== @@ -17,6 +17,11 @@ module GHC.Unit.Module.ModSummary , msHsFilePath , msObjFilePath , msDynObjFilePath + , msHsFileOsPath + , msHiFileOsPath + , msDynHiFileOsPath + , msObjFileOsPath + , msDynObjFileOsPath , msDeps , isBootSummary , findTarget @@ -38,6 +43,7 @@ import GHC.Types.Target import GHC.Types.PkgQual import GHC.Data.Maybe +import GHC.Data.OsPath (OsPath) import GHC.Data.StringBuffer ( StringBuffer ) import GHC.Utils.Fingerprint @@ -146,6 +152,13 @@ msDynHiFilePath ms = ml_dyn_hi_file (ms_location ms) msObjFilePath ms = ml_obj_file (ms_location ms) msDynObjFilePath ms = ml_dyn_obj_file (ms_location ms) +msHsFileOsPath, msDynHiFileOsPath, msHiFileOsPath, msObjFileOsPath, msDynObjFileOsPath :: ModSummary -> OsPath +msHsFileOsPath ms = expectJust "msHsFilePath" (ml_hs_file_ospath (ms_location ms)) +msHiFileOsPath ms = ml_hi_file_ospath (ms_location ms) +msDynHiFileOsPath ms = ml_dyn_hi_file_ospath (ms_location ms) +msObjFileOsPath ms = ml_obj_file_ospath (ms_location ms) +msDynObjFileOsPath ms = ml_dyn_obj_file_ospath (ms_location ms) + -- | Did this 'ModSummary' originate from a hs-boot file? isBootSummary :: ModSummary -> IsBootInterface isBootSummary ms = if ms_hsc_src ms == HsBootFile then IsBoot else NotBoot ===================================== compiler/ghc.cabal.in ===================================== @@ -123,7 +123,8 @@ Library time >= 1.4 && < 1.15, containers >= 0.6.2.1 && < 0.8, array >= 0.1 && < 0.6, - filepath >= 1 && < 1.6, + filepath >= 1.5 && < 1.6, + os-string >= 2.0.1 && < 2.1, hpc >= 0.6 && < 0.8, transformers >= 0.5 && < 0.7, exceptions == 0.10.*, @@ -444,6 +445,7 @@ Library GHC.Data.List.SetOps GHC.Data.Maybe GHC.Data.OrdList + GHC.Data.OsPath GHC.Data.Pair GHC.Data.SmallArray GHC.Data.Stream ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -36,7 +36,7 @@ Executable ghc bytestring >= 0.9 && < 0.13, directory >= 1 && < 1.4, process >= 1 && < 1.7, - filepath >= 1 && < 1.6, + filepath >= 1.5 && < 1.6, containers >= 0.5 && < 0.8, transformers >= 0.5 && < 0.7, ghc-boot == @ProjectVersionMunged@, ===================================== libraries/base/tests/all.T ===================================== @@ -176,6 +176,7 @@ test('T7457', normal, compile_and_run, ['']) test('T7773', [when(opsys('mingw32'), skip), js_broken(22261), + when(arch('wasm32'), fragile(24928)), expect_broken_for(23272, ['ghci-opt']) # unclear ], compile_and_run, ===================================== testsuite/tests/count-deps/CountDepsAst.stdout ===================================== @@ -70,6 +70,7 @@ GHC.Data.List.Infinite GHC.Data.List.SetOps GHC.Data.Maybe GHC.Data.OrdList +GHC.Data.OsPath GHC.Data.Pair GHC.Data.SmallArray GHC.Data.Strict ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -71,6 +71,7 @@ GHC.Data.List.Infinite GHC.Data.List.SetOps GHC.Data.Maybe GHC.Data.OrdList +GHC.Data.OsPath GHC.Data.Pair GHC.Data.SmallArray GHC.Data.Strict ===================================== testsuite/tests/numeric/should_run/all.T ===================================== @@ -52,6 +52,7 @@ test('add2', normal, compile_and_run, ['-fobject-code']) test('mul2', normal, compile_and_run, ['-fobject-code']) test('mul2int', normal, compile_and_run, ['-fobject-code']) test('quotRem2', normal, compile_and_run, ['-fobject-code']) +test('quotRem2Large', normal, compile_and_run, ['-fobject-code']) test('T5863', normal, compile_and_run, ['']) test('T7014', js_skip, makefile_test, []) ===================================== testsuite/tests/numeric/should_run/quotRem2Large.hs ===================================== The diff for this file was not included because it is too large. ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Create.hs ===================================== @@ -93,10 +93,7 @@ createInterface1 flags unit_state mod_sum mod_iface ifaces inst_ifaces (instance -- pragmas in the modules source code. Used to infer -- safety of module. ms_hspp_opts - , ms_location = - ModLocation - { ml_hie_file - } + , ms_location = modl } = mod_sum dflags = ms_hspp_opts @@ -228,7 +225,7 @@ createInterface1 flags unit_state mod_sum mod_iface ifaces inst_ifaces (instance Interface { ifaceMod = mdl , ifaceIsSig = is_sig - , ifaceHieFile = ml_hie_file + , ifaceHieFile = ml_hie_file modl , ifaceInfo = info , ifaceDoc = Documentation header_doc mod_warning , ifaceRnDoc = Documentation Nothing Nothing View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8303b6fda3e0daa15c76b7bcece977a2cd63ed60...6c3a56046193bca66ca43fa4f9c63801a019852d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8303b6fda3e0daa15c76b7bcece977a2cd63ed60...6c3a56046193bca66ca43fa4f9c63801a019852d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 10:18:53 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 03 Jun 2024 06:18:53 -0400 Subject: [Git][ghc/ghc][wip/T24359] 95 commits: rts: Fix size of StgOrigThunkInfo frames Message-ID: <665d988daa11d_3658d1917328546d8@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24359 at Glasgow Haskell Compiler / GHC Commits: 6d7e6ad8 by Ben Gamari at 2024-05-22T13:40:05-04:00 rts: Fix size of StgOrigThunkInfo frames Previously the entry code of the `stg_orig_thunk` frame failed to account for the size of the profiling header as it hard-coded the frame size. Fix this. Fixes #24809. - - - - - c645fe40 by Fendor at 2024-05-22T13:40:05-04:00 Add regression test T24809 for stg_orig_thunk_info_frame size - - - - - 4181aa40 by Andreas Klebinger at 2024-05-22T13:40:42-04:00 bindists: Check for existence of share folder before trying to copy it. This folder isn't distributed in windows bindists A lack of doing so resulted us copying loads of files twice. - - - - - d216510e by Matthew Pickering at 2024-05-22T13:40:42-04:00 Remove ad-hoc installation of mingw toolchain in relocatable bindists This reverts 616ac30026e8dd7d2ebb98d92dde071eedf5d951 The choice about whether to install mingw is taken in the installation makefile. This is also broken on non-windows systems. The actual issue was the EnableDistroToolchain variable wasn't declared in mk/config.mk and therefore the check to install mingw was failing. - - - - - 7b4c1998 by Cheng Shao at 2024-05-22T21:52:52-04:00 testsuite: fix T17920 for wasm backend T17920 was marked as fragile on wasm before; it can be trivially fixed by avoiding calling variadic printf() in cmm. - - - - - c739383b by Cheng Shao at 2024-05-22T21:53:29-04:00 testsuite: bump T22744 timeout to 5x - - - - - c4c6d714 by Cheng Shao at 2024-05-22T21:54:06-04:00 testsuite: don't attempt to detect host cpu features when testing cross ghc The testsuite driver CPU feature detection logic only detects host CPU and only makes sense when we are not testing a cross GHC. - - - - - 3d9e4ce6 by Simon Peyton Jones at 2024-05-22T21:54:43-04:00 Better skolemisation As #24810 showed, it is (a little) better to skolemise en-bloc, so that Note [Let-bound skolems] fires more often. See Note [Skolemisation en bloc] in GHC.Tc.Utils.Instantiate. - - - - - a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00 Add missing parenthesizePat in cvtp We need to ensure that the output of `cvtp` is parenthesized (at precedence `sigPrec`) so that any pattern signatures with a surrounding pattern signature can parse correctly. Fixes #24837. - - - - - 4bb2a7cc by Hécate Moonlight at 2024-05-22T21:55:59-04:00 [base] Document the memory overhead of ByteArray Add a diagram that shows the constituent parts of a ByteArray and their memory overhead. - - - - - 8b2a016a by Hécate Moonlight at 2024-05-22T21:56:38-04:00 Haddock: Add MR template for Haddock - - - - - ead75532 by Peter Trommler at 2024-05-23T02:28:05-04:00 PPC: Support ELF v2 on powerpc64 big-endian Detect ELF v2 on PowerPC 64-bit systems. Check for `_CALL_ELF` preprocessor macro. Fixes #21191 - - - - - 9d4c10f2 by Hécate Kleidukos at 2024-05-23T02:28:44-04:00 gitlab: Add @Kleidukos to CODEOWNERS for utils/haddock - - - - - 28e64170 by Preetham Gujjula at 2024-05-23T07:20:48-04:00 haddock: Add cabal-fmt to tools for `make style` - - - - - 00126a89 by Andrei Borzenkov at 2024-05-23T07:21:24-04:00 haddock: fix verbosity option parsing - - - - - a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00 base: specify tie-breaking behavior of min, max, and related list/Foldable functions - - - - - bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00 cmm: add word <-> double/float bitcast - closes: #25331 This is the last step in the project plan described in #25331. This commit: - adds bitcast operands for x86_64, LLVM, aarch64 - For PPC and i386 we resort to using the cmm implementations - renames conversion MachOps from Conv to Round|Truncate - - - - - f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor Some functions in StgToByteCode were filtering out void arguments. However, StgToByteCode is called after unarisation: the void arguments should have been removed earlier. Instead of filtering out, we assert that the args are non-void. - - - - - 03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor `layoutNativeCall` was always called with a `primRepCmmType platform` callback. Hence we can put it inside of `layoutNativeCall` rather than repeat it. - - - - - 27c430f3 by David Binder at 2024-05-24T07:52:38-04:00 haddock: Remove compatibility shims for GHC < 8.4 from haddock-library - - - - - 8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00 compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs This patch makes the STG->Cmm backend avoid saving foreign call target to local when there are no caller-save GlobalRegs. Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a foreign call, we unconditionally save the foreign call target to a temporary local first, then rely on cmmSink to clean it up later, which only happens with -fcmm-sink (implied by -O) and not in unoptimized code. And this is troublesome for the wasm backend NCG, which needs to infer a foreign call target symbol's type signature from the Cmm call site. Previously, the NCG has been emitting incorrect type signatures for unoptimized code, which happens to work with `wasm-ld` most of the time, but this is never future-proof against upstream toolchain updates, and it causes horrible breakages when LTO objects are included in linker input. Hence this patch. - - - - - 986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00 testsuite: add callee-no-local regression test - - - - - 52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00 Fix HasCallStack leftovers from !12514 / #24726 - - - - - c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00 user_guide: Fix typo in MultiWayIf chapter Close #24829 - - - - - bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - 1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Fix changelog reference to setBacktraceMechanismState (cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d) - - - - - 43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00 Float/double unboxed literal support for HexFloatLiterals (fix #22155) - - - - - 4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00 Improve test labels for binary interface file size tests Test labels for binary interface file sizes are hard to read and overly verbose at the same time. Extend the name for the metric title, but shorten it in the actual comparison table. - - - - - 14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00 Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present" This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa. - - - - - f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00 Fix default hyperlinked sources pattern Previously this didn't include the `%M` token which manifested as broken links to the hyperlinked sources of reexports of declarations defined in other packages. Fixes haddock#1628. (cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36) - - - - - 42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00 Make DocPaths a proper data type (cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c) - - - - - 53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00 haddock: Bump version to 2.30 (cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602) - - - - - e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00 haddock-api: allow base 4.20 and ghc 9.11 - - - - - e294f7a2 by PHO at 2024-05-24T12:17:55-04:00 Add a flag "threaded" for building haddock with the threaded RTS GHC isn't guaranteed to have a threaded RTS. There should be a way to build it with the vanilla one. (cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d) - - - - - 51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00 Update ticky counter event docs. Add the info about the info table address and json fields. Fixes #23200 - - - - - 98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00 Export extractPromotedList (#24866) This can be useful in plugins. - - - - - 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - 606fb59d by Simon Peyton Jones at 2024-06-03T10:44:29+01:00 Just a start on specialising expressions Addresses #24359. Just a start, does not compile. - - - - - b99b20fa by Simon Peyton Jones at 2024-06-03T10:44:29+01:00 More progress (Still does not compile.) - - - - - b0e6290a by Simon Peyton Jones at 2024-06-03T10:44:29+01:00 More progress - - - - - 75af0cf7 by Simon Peyton Jones at 2024-06-03T10:44:29+01:00 Wibble - - - - - cfc24b5a by Simon Peyton Jones at 2024-06-03T10:44:29+01:00 More progress - - - - - 0e1dd1e2 by Simon Peyton Jones at 2024-06-03T10:44:29+01:00 More progress - - - - - 50d1da38 by Simon Peyton Jones at 2024-06-03T10:44:29+01:00 Finally runnable! - - - - - 66ed6431 by Simon Peyton Jones at 2024-06-03T10:44:29+01:00 Progress - - - - - 1067eb65 by Simon Peyton Jones at 2024-06-03T10:44:29+01:00 Working I think - - - - - ad588459 by Andrei Borzenkov at 2024-06-03T10:44:29+01:00 Fix derivations conflict in parser, disambiguate them in post-process - - - - - fd9334d8 by Alan Zimmerman at 2024-06-03T10:44:29+01:00 Fix exact printing for RuleBndrs This puts the exact print annotations inside a TTG extension point in RuleBndrs. It also adds an exact print case for SpecSigE - - - - - fbc86d8f by Simon Peyton Jones at 2024-06-03T10:44:29+01:00 Wibble imports - - - - - 9133c781 by Simon Peyton Jones at 2024-06-03T10:44:29+01:00 Typo in comments - - - - - 84483095 by Simon Peyton Jones at 2024-06-03T10:44:29+01:00 Wibbles - - - - - 559e86ce by Simon Peyton Jones at 2024-06-03T11:18:25+01:00 Go via new route for simple SPECIALISE pragmas - - - - - 30 changed files: - .gitignore - .gitlab-ci.yml - + .gitlab/merge_request_templates/Haddock.md - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - CODEOWNERS - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCon.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e764367be29d6a571c13fdf26f49b331748b38bc...559e86ce0b41c8e1b0b669824ba3b02e0c9c632e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e764367be29d6a571c13fdf26f49b331748b38bc...559e86ce0b41c8e1b0b669824ba3b02e0c9c632e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 10:20:27 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 03 Jun 2024 06:20:27 -0400 Subject: [Git][ghc/ghc][wip/T24887] Put all nominal equalities in eqs_N Message-ID: <665d98ebd1dce_3658d1a1c3f4553e7@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24887 at Glasgow Haskell Compiler / GHC Commits: bcb05c05 by Simon Peyton Jones at 2024-06-03T11:20:01+01:00 Put all nominal equalities in eqs_N - - - - - 2 changed files: - compiler/GHC/Core/Predicate.hs - compiler/GHC/Tc/Solver/InertSet.hs Changes: ===================================== compiler/GHC/Core/Predicate.hs ===================================== @@ -12,7 +12,7 @@ module GHC.Core.Predicate ( -- Equality predicates EqRel(..), eqRelRole, - isEqPrimPred, isNomEqPrimPred, isReprEqPrimPred, isEqPred, isCoVarType, + isEqPrimPred, isNomEqPred, isReprEqPrimPred, isEqPred, isCoVarType, getEqPredTys, getEqPredTys_maybe, getEqPredRole, predTypeEqRel, mkPrimEqPred, mkReprPrimEqPred, mkPrimEqPredRole, @@ -189,11 +189,11 @@ getEqPredTys_maybe ty _ -> Nothing getEqPredRole :: PredType -> Role --- Precondition: the PredType is (a ~#N b) or (a ~#R b) +-- Precondition: the PredType is (s ~#N t) or (s ~#R t) getEqPredRole ty = eqRelRole (predTypeEqRel ty) -- | Get the equality relation relevant for a pred type. --- Precondition: the PredType is (a ~#N b) or (a ~#R b) +-- Precondition: the PredType is (s ~#N t) or (s ~#R t) predTypeEqRel :: HasDebugCallStack => PredType -> EqRel predTypeEqRel ty = case splitTyConApp_maybe ty of @@ -232,21 +232,21 @@ isCoVarType :: Type -> Bool -- ToDo: should we check saturation? isCoVarType ty = isEqPrimPred ty +isEvVarType :: Type -> Bool +-- True of (a) predicates, of kind Constraint, such as (Eq t), and (s ~ t) +-- (b) coercion types, such as (s ~# t) or (s ~R# t) +-- See Note [Types for coercions, predicates, and evidence] in GHC.Core.TyCo.Rep +-- See Note [Evidence for quantified constraints] +isEvVarType ty = isCoVarType ty || isPredTy ty + isEqPrimPred :: PredType -> Bool --- True of (a ~# b) (a ~R# b) +-- True of (s ~# t) (s ~R# t) isEqPrimPred ty | Just tc <- tyConAppTyCon_maybe ty = tc `hasKey` eqPrimTyConKey || tc `hasKey` eqReprPrimTyConKey | otherwise = False -isNomEqPrimPred :: PredType -> Bool -isNomEqPrimPred ty - | Just tc <- tyConAppTyCon_maybe ty - = tc `hasKey` eqPrimTyConKey - | otherwise - = False - isReprEqPrimPred :: PredType -> Bool isReprEqPrimPred ty | Just tc <- tyConAppTyCon_maybe ty @@ -254,12 +254,13 @@ isReprEqPrimPred ty | otherwise = False -isEvVarType :: Type -> Bool --- True of (a) predicates, of kind Constraint, such as (Eq a), and (a ~ b) --- (b) coercion types, such as (t1 ~# t2) or (t1 ~R# t2) --- See Note [Types for coercions, predicates, and evidence] in GHC.Core.TyCo.Rep --- See Note [Evidence for quantified constraints] -isEvVarType ty = isCoVarType ty || isPredTy ty +isNomEqPred :: PredType -> Bool +-- A nominal equality, primitive or not (s ~# t), (s ~ t), or (s ~~ t) +isNomEqPred ty + | Just tc <- tyConAppTyCon_maybe ty + = tc `hasKey` eqPrimTyConKey || tc `hasKey` heqTyConKey || tc `hasKey` eqTyConKey + | otherwise + = False isClassPred :: PredType -> Bool isClassPred ty = case tyConAppTyCon_maybe ty of @@ -267,7 +268,7 @@ isClassPred ty = case tyConAppTyCon_maybe ty of _ -> False isEqPred :: PredType -> Bool -isEqPred ty -- True of (a ~ b) and (a ~~ b) +isEqPred ty -- True of (s ~ t) and (s ~~ t) -- ToDo: should we check saturation? | Just tc <- tyConAppTyCon_maybe ty , Just cls <- tyConClass_maybe tc ===================================== compiler/GHC/Tc/Solver/InertSet.hs ===================================== @@ -175,7 +175,7 @@ See GHC.Tc.Solver.Monad.deferTcSForAllEq -- See Note [WorkList priorities] data WorkList - = WL { wl_eqs_N :: [Ct] -- Primitive /nominal/ equalities (a ~#N b) + = WL { wl_eqs_N :: [Ct] -- /Nominal/ equalities (s ~#N t), (s ~ t), (s ~~ t) -- with empty rewriter set , wl_eqs_X :: [Ct] -- CEqCan, CDictCan, CIrredCan -- with empty rewriter set @@ -218,7 +218,7 @@ extendWorkListEq rewriters ct | isEmptyRewriterSet rewriters -- A wanted that has not been rewritten -- isEmptyRewriterSet: see Note [Prioritise Wanteds with empty RewriterSet] -- in GHC.Tc.Types.Constraint - = if isNomEqPrimPred (ctPred ct) + = if isNomEqPred (ctPred ct) then wl { wl_eqs_N = ct : eqs_N } else wl { wl_eqs_X = ct : eqs_X } @@ -253,7 +253,7 @@ extendWorkListEqs rewriters new_eqs -- push_on_front puts the new equlities on the front of the queue push_on_front new_eqs eqs = foldr (:) eqs new_eqs - is_nominal ct = isNomEqPrimPred (ctPred ct) + is_nominal ct = isNomEqPred (ctPred ct) extendWorkListNonEq :: Ct -> WorkList -> WorkList -- Extension by non equality View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bcb05c055cc594b1f9d739700e3b2474b8a019dd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bcb05c055cc594b1f9d739700e3b2474b8a019dd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 13:46:58 2024 From: gitlab at gitlab.haskell.org (Hannes Siebenhandl (@fendor)) Date: Mon, 03 Jun 2024 09:46:58 -0400 Subject: [Git][ghc/ghc][wip/fendor/ghc-iface-sharing-avoid-reserialisation] 20 commits: utils: add hie.yaml config file for ghc-config Message-ID: <665dc952e5f8b_3d9c926c251487952@gitlab.mail> Hannes Siebenhandl pushed to branch wip/fendor/ghc-iface-sharing-avoid-reserialisation at Glasgow Haskell Compiler / GHC Commits: 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - d68edf97 by Fendor at 2024-06-03T15:46:44+02:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 12d59b3b by Fendor at 2024-06-03T15:46:44+02:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-linux job, where the number of allocated bytes seems to be lower than in other jobs. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Data/Word64Set/Internal.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Types/Unique/Set.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1cc28d23030a41115ea77b62aa96dc98cb756e62...12d59b3b208ca8a88eecc88e9b4fa5fc651e55bc -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1cc28d23030a41115ea77b62aa96dc98cb756e62...12d59b3b208ca8a88eecc88e9b4fa5fc651e55bc You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 13:59:49 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Mon, 03 Jun 2024 09:59:49 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/rip-compilerinfo Message-ID: <665dcc557a120_3d9c929952649411@gitlab.mail> Cheng Shao pushed new branch wip/rip-compilerinfo at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/rip-compilerinfo You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 14:02:20 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Mon, 03 Jun 2024 10:02:20 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/cc-is-clang Message-ID: <665dccec3e4e6_3d9c92a45fec960ea@gitlab.mail> Cheng Shao pushed new branch wip/cc-is-clang at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/cc-is-clang You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 15:48:23 2024 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Mon, 03 Jun 2024 11:48:23 -0400 Subject: [Git][ghc/ghc][wip/andreask/bytecode_tagging] GHCi interpreter: Tag constructor closures when possible. Message-ID: <665de5c7d9503_3d9c9219a7760124861@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/bytecode_tagging at Glasgow Haskell Compiler / GHC Commits: 6da2946a by Andreas Klebinger at 2024-06-03T17:32:42+02:00 GHCi interpreter: Tag constructor closures when possible. When evaluating PUSH_G try to tag the reference we are pushing if it's a constructor or function. This is potentially helpful for performance and required to fix #24870. - - - - - 6 changed files: - compiler/GHC/ByteCode/Instr.hs - rts/Interpreter.c - + testsuite/tests/th/should_compile/T24870/Def.hs - + testsuite/tests/th/should_compile/T24870/T24870.stderr - + testsuite/tests/th/should_compile/T24870/Use.hs - + testsuite/tests/th/should_compile/T24870/all.T Changes: ===================================== compiler/GHC/ByteCode/Instr.hs ===================================== @@ -83,7 +83,7 @@ data BCInstr | PUSH16_W !ByteOff | PUSH32_W !ByteOff - -- Push a ptr (these all map to PUSH_G really) + -- Push a (heap) ptr (these all map to PUSH_G really) | PUSH_G Name | PUSH_PRIMOP PrimOp | PUSH_BCO (ProtoBCO Name) ===================================== rts/Interpreter.c ===================================== @@ -4,6 +4,30 @@ * Copyright (c) The GHC Team, 1994-2002. * ---------------------------------------------------------------------------*/ +/* +Note [CBV Functions and the interpreter] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +When the byte code interpreter loads a reference to a value it often +ends up as a non-tagged pointers *especially* if we already know a value +is a certain constructor and therefore don't perform an eval on the reference. +This causes friction with CBV functions which assume +their value arguments are properly tagged by the caller. + +In order to ensure CBV functions still get passed tagged functions we have +three options: +a) Special case the interpreter behaviour into the tag inference analysis. + If we assume the interpreter can't properly tag value references the STG passes + would then wrap such calls in appropriate evals which are executed at runtime. + This would ensure tags by doing additional evals at runtime. +b) When the interpreter pushes references for known constructors instead of + pushing the objects address add the tag to the value pushed. This is what + the NCG backends do. +c) When the interpreter pushes a reference inspect the closure of the object + and apply the appropriate tag at runtime. + +For now we use approach c). Mostly because it's easiest to implement. We also don't +tag functions as tag inference currently doesn't rely on those being properly tagged. +*/ #include "rts/PosixSource.h" #include "Rts.h" @@ -292,6 +316,18 @@ STATIC_INLINE StgClosure *tagConstr(StgClosure *con) { return TAG_CLOSURE(stg_min(TAG_MASK, 1 + GET_TAG(con)), con); } +// Compute the pointer tag for the function and tag the pointer; +STATIC_INLINE StgClosure *tagFun(StgClosure *fun) { + StgHalfWord tag = GET_TAG(fun); + if(tag > TAG_MASK) { return fun; } + else { + return TAG_CLOSURE(tag, fun); + } + + +} + + static StgWord app_ptrs_itbl[] = { (W_)&stg_ap_p_info, (W_)&stg_ap_pp_info, @@ -1306,7 +1342,52 @@ run_BCO: case bci_PUSH_G: { W_ o1 = BCO_GET_LARGE_ARG; - SpW(-1) = BCO_PTR(o1); + StgClosure *tagged_obj = (StgClosure*) BCO_PTR(o1); + + tag_push_g: + ASSERT(LOOKS_LIKE_CLOSURE_PTR((StgClosure*) tagged_obj)); + // Here we make sure references we push are tagged. + // See Note [CBV Functions and the interpreter] in Info.hs + + //Safe some memory reads if we already have a tag. + if(GET_CLOSURE_TAG(tagged_obj) == 0) { + StgClosure *obj = UNTAG_CLOSURE(tagged_obj); + switch ( get_itbl(obj)->type ) { + case IND: + case IND_STATIC: + { + tagged_obj = ACQUIRE_LOAD(&((StgInd*)obj)->indirectee); + goto tag_push_g; + } + case CONSTR: + case CONSTR_1_0: + case CONSTR_0_1: + case CONSTR_2_0: + case CONSTR_1_1: + case CONSTR_0_2: + case CONSTR_NOCAF: + // The value is already evaluated, so we can just return it. However, + // before we do, we MUST ensure that the pointer is tagged, because we + // might return to a native `case` expression, which assumes the returned + // pointer is tagged so it can use the tag to select an alternative. + tagged_obj = tagConstr(obj); + break; + case FUN: + case FUN_1_0: + case FUN_0_1: + case FUN_2_0: + case FUN_1_1: + case FUN_0_2: + case FUN_STATIC: + // Purely for performance since we already hit memory anyway. + tagged_obj = tagFun(obj); + break; + default: + break; + } + } + + SpW(-1) = (W_) tagged_obj; Sp_subW(1); goto nextInsn; } ===================================== testsuite/tests/th/should_compile/T24870/Def.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE TemplateHaskell #-} + +module SDef where + +{-# NOINLINE aValue #-} +aValue = True + +{-# NOINLINE aStrictFunction #-} +aStrictFunction !x = [| x |] ===================================== testsuite/tests/th/should_compile/T24870/T24870.stderr ===================================== @@ -0,0 +1,2 @@ +[1 of 2] Compiling SDef ( Def.hs, Def.o, Def.dyn_o ) +[2 of 2] Compiling SUse ( Use.hs, Use.o ) ===================================== testsuite/tests/th/should_compile/T24870/Use.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE TemplateHaskell #-} + +module SUse where + +import qualified Language.Haskell.TH.Syntax as TH +import SDef +import GHC.Exts + +bar = $( inline aStrictFunction aValue ) ===================================== testsuite/tests/th/should_compile/T24870/all.T ===================================== @@ -0,0 +1,6 @@ +# The interpreter must uphold tagging invariants, and failed to do so in #24870 +# We test this here by having the interpreter calls a strict worker function +# with a reference to a value it constructed. +# See also Note [CBV Functions and the interpreter] +test('T24870', [extra_files(['Def.hs', 'Use.hs']), req_th], + multimod_compile, ['Def Use', '-dtag-inference-checks']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6da2946a0895f6e87fe604a6330570ac4fc4d258 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6da2946a0895f6e87fe604a6330570ac4fc4d258 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 16:20:22 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 03 Jun 2024 12:20:22 -0400 Subject: [Git][ghc/ghc][wip/T24676] Wibbles Message-ID: <665ded465c4c9_3d9c921ff61c01303c0@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24676 at Glasgow Haskell Compiler / GHC Commits: 6f90e5d0 by Simon Peyton Jones at 2024-06-03T17:20:00+01:00 Wibbles - - - - - 3 changed files: - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/Unify.hs Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -1858,11 +1858,14 @@ which has no free instantiation variables, so we can QL-unify --------------------- qlUnify :: TcType -> TcType -> TcM () --- Unify ty1 with ty2, unifying /only/ instantiation variables in delta --- (it /never/ unifies ordinary unification variables) --- It never produces errors, even for mis-matched types --- It may return without having made the types equal, of course; --- it just makes best efforts. +-- Unify ty1 with ty2: +-- * It unifies /only/ instantiation variables; +-- it /never/ unifies ordinary unification variables +-- * It never produces errors, even for mis-matched types +-- * It does not return a coercion (unlike unifyType); it is called +-- for the sole purpose of unifying instantiation variables +-- * It may return without having made the argument types equal, of course; +-- it just makes best efforts. qlUnify ty1 ty2 = go (emptyVarSet,emptyVarSet) ty1 ty2 where ===================================== compiler/GHC/Tc/Utils/Instantiate.hs ===================================== @@ -401,25 +401,38 @@ instCallConstraints orig preds = return idHsWrapper | otherwise = do { evs <- mapM (emitWanted orig) preds + -- See Note [Possible fast path for equality constraints] ; traceTc "instCallConstraints" (ppr evs) ; return (mkWpEvApps evs) } -{- --- ToDo: explain why we don't short-cut here; Quick Look - where - go :: TcPredType -> TcM EvTerm - go pred - | Just (Nominal, ty1, ty2) <- getEqPredTys_maybe pred -- Try short-cut #1 - = do { co <- unifyType Nothing ty1 ty2 - ; return (evCoercion co) } - - -- Try short-cut #2 - | Just (tc, args@[_, _, ty1, ty2]) <- splitTyConApp_maybe pred - , tc `hasKey` heqTyConKey - = do { co <- unifyType Nothing ty1 ty2 - ; return (evDFunApp (dataConWrapId heqDataCon) args [Coercion co]) } - | otherwise - = emitWanted orig pred +{- Note [Possible fast path for equality constraints] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Given f :: forall a b. (a ~ [b]) => a -> b -> blah +rather than emitting ([W] alpha ~ [beta]) we could imagine calling unifyType +right here. But note + +* Often such constraints look like (F a ~ G b), in which case unification would end up + spitting out a wanted-equality anyway. + +* So perhaps the main fast-path would be where the LHS or RHS was an instantiation + variable. But note that this could, perhaps, impact on Quick Look: + + - The first arg of `f` changes from the naked `a` to the guarded `[b]` (or would do so + if we zonked it). That might affect typing under Quick Look. + + - We might imagine using the let-bound skolems trick: + g :: forall a b. (a ~ forall c. c->c) => a -> [a] -> [a] + Here we are just using `a` as a local abreviation for (forall c. c->c) + See Note [Let-bound skolems] in GHC.Tc.Solver.InertSet. + + If we substitute aggressively (including zonking) that abbreviation could work. But + again it affects what is typeable. + +* There is little point in trying to optimise for + - (s ~# t), because few functions have primitive equalities in their context + - (s ~~ t), becaues heterogeneous equality is rare, and more complicated. + +Anyway, for now we don't take advantage of these potential effects. -} instDFunType :: DFunId -> [DFunInstType] ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -2894,14 +2894,13 @@ simpleUnifyCheck :: Bool -- True <=> called from constraint solver simpleUnifyCheck called_from_solver lhs_tv rhs = go rhs where - fam_ok = called_from_solver || is_ql_inst_tv !(occ_in_ty, occ_in_co) = mkOccFolders lhs_tv lhs_tv_lvl = tcTyVarLevel lhs_tv lhs_tv_is_concrete = isConcreteTyVar lhs_tv - is_ql_inst_tv = isQLInstTyVar lhs_tv - forall_ok = is_ql_inst_tv || isRuntimeUnkTyVar lhs_tv + forall_ok = isRuntimeUnkTyVar lhs_tv + fam_ok = called_from_solver go (TyVarTy tv) | lhs_tv == tv = False View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6f90e5d0f831b99ef47048294ccadf8313988071 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6f90e5d0f831b99ef47048294ccadf8313988071 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 16:35:03 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 03 Jun 2024 12:35:03 -0400 Subject: [Git][ghc/ghc][wip/T24887] Wibble test Message-ID: <665df0b772a6e_3d9c92226eefc133164@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24887 at Glasgow Haskell Compiler / GHC Commits: 60d573e7 by Simon Peyton Jones at 2024-06-03T17:34:48+01:00 Wibble test - - - - - 1 changed file: - testsuite/tests/typecheck/should_compile/T24887.hs Changes: ===================================== testsuite/tests/typecheck/should_compile/T24887.hs ===================================== @@ -1,6 +1,7 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE ScopedTypeVariables, TypeAbstractions #-} + module Data.Array.Nested.Internal where import Data.Coerce (coerce) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/60d573e7ae0f1d1d924d2dca9067715a3a05de73 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/60d573e7ae0f1d1d924d2dca9067715a3a05de73 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 16:35:55 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 03 Jun 2024 12:35:55 -0400 Subject: [Git][ghc/ghc][wip/T24887] 34 commits: rts: ensure gc_thread/gen_workspace is allocated with proper alignment Message-ID: <665df0eb594d_3d9c922316f301339a1@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24887 at Glasgow Haskell Compiler / GHC Commits: 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - cb61d384 by Simon Peyton Jones at 2024-06-03T17:35:46+01:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Builtin/Types.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Data/Word64Set/Internal.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/HsToCore/Pmc/Solver.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Ext/Types.hs - compiler/GHC/JS/JStg/Syntax.hs - compiler/GHC/JS/Syntax.hs - compiler/GHC/StgToCmm/Prim.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/60d573e7ae0f1d1d924d2dca9067715a3a05de73...cb61d38413529de5a41a5d57fb4a4b80fb2b8d4a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/60d573e7ae0f1d1d924d2dca9067715a3a05de73...cb61d38413529de5a41a5d57fb4a4b80fb2b8d4a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 16:47:02 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 03 Jun 2024 12:47:02 -0400 Subject: [Git][ghc/ghc][wip/T24868] Add hack for #24623 Message-ID: <665df38695c89_3d9c92252d940134337@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24868 at Glasgow Haskell Compiler / GHC Commits: 28cdc083 by Simon Peyton Jones at 2024-06-03T17:45:52+01:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 1 changed file: - compiler/GHC/Core/Lint.hs Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -634,11 +634,16 @@ lintLetBind top_lvl rec_flag binder rhs rhs_ty -- in GHC.Core.Opt.DmdAnal ; case splitDmdSig (idDmdSig binder) of (demands, result_info) | isDeadEndDiv result_info -> - checkL (demands `lengthAtLeast` idArity binder) - (text "idArity" <+> ppr (idArity binder) <+> - text "exceeds arity imposed by the strictness signature" <+> - ppr (idDmdSig binder) <> colon <+> - ppr binder) + if (demands `lengthAtLeast` idArity binder) + then return () + else pprTrace "Hack alert: lintLetBind #24623" + (ppr (idArity binder) $$ ppr (idDmdSig binder)) $ + return () +-- checkL (demands `lengthAtLeast` idArity binder) +-- (text "idArity" <+> ppr (idArity binder) <+> +-- text "exceeds arity imposed by the strictness signature" <+> +-- ppr (idDmdSig binder) <> colon <+> +-- ppr binder) _ -> return () View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/28cdc083dc584de5388c51bbcebb57b85e434b1a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/28cdc083dc584de5388c51bbcebb57b85e434b1a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 19:05:48 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 03 Jun 2024 15:05:48 -0400 Subject: [Git][ghc/ghc][wip/T24676] Add notes Message-ID: <665e140cd9a0c_3d9c9235f48c81422d@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24676 at Glasgow Haskell Compiler / GHC Commits: 6d030891 by Simon Peyton Jones at 2024-06-03T20:05:17+01:00 Add notes - - - - - 3 changed files: - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Utils/TcType.hs - compiler/GHC/Tc/Zonk/TcType.hs Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -82,8 +82,8 @@ import GHC.Prelude * * ********************************************************************* -} -{- Note [Quick Look] -~~~~~~~~~~~~~~~~~~~~ +{- Note [Quick Look overview] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The implementation of Quick Look closely follows the QL paper A quick look at impredicativity, Serrano et al, ICFP 2020 https://www.microsoft.com/en-us/research/publication/a-quick-look-at-impredicativity/ @@ -121,6 +121,7 @@ Note [Instantiation variables are short lived] * By the time QL is done, all filled-in occurrences of instantiation variables have been zonked away with `qlZonkTcType` (see "Crucial step" in tcValArgs). + See also Note [QuickLook zonking] in GHC.Tc.Zonk.TcType See Section 4.3 "Applications and instantiation" of the paper. @@ -396,6 +397,7 @@ finishApp :: QLFlag -> HsExpr GhcRn -> TcM (HsExpr GhcTc) finishApp do_ql rn_expr tc_head@(tc_fun,_) inst_args app_res_rho exp_res_ty = do { -- Step 6: qlZonk the type of the result of the call + -- See Note [QuickLook zonking] in GHC.Tc.Zonk.TcType traceTc "finishApp" $ vcat [ ppr app_res_rho, ppr exp_res_ty ] ; app_res_rho <- case do_ql of DoQL -> liftZonkM $ qlZonkTcType app_res_rho @@ -508,6 +510,7 @@ tcValArg do_ql (EValArg { ea_ctxt = ctxt -- Then Theta = [p :-> forall a. a->a], and we want -- to check 'e' with expected type (forall a. a->a) -- See Note [Instantiation variables are short lived] + -- and Note [QuickLook zonking] in GHC.Tc.Zonk.TcType ; Scaled mult exp_arg_ty <- case do_ql of DoQL -> liftZonkM $ qlZonkScaledTcType sc_arg_ty NoQL -> return sc_arg_ty @@ -540,9 +543,15 @@ tcValArg _ (EValArgQL { eaql_wanted = wanted ; (wrap, arg') <- tcScalingUsage mult $ tcSkolemise ds_flag GenSigCtxt exp_arg_ty $ \ exp_arg_rho -> - do { emitConstraints wanted + do { -- Emit saved-up constraints, /under/ the tcSkolemise + -- See (QLA4) in Note [Quick Look at value arguments] + emitConstraints wanted + + -- Unify with context if we have no already done so + -- See (QLA4) in Note [Quick Look at value arguments] ; unless arg_influences_enclosing_call $ -- Don't repeat qlUnify app_res_rho exp_arg_rho -- the qlUnify + ; finishApp DoQL rn_expr tc_head inst_args app_res_rho (mkCheckExpType exp_arg_rho) } @@ -764,7 +773,7 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args -- Fill in kappa := nu_1 -> .. -> nu_n -> res_nu -- NB: kappa is uninstantiated ('go' already checked that) ; kind_co <- unifyKind Nothing liftedTypeKind (tyVarKind kappa) - -- unifyKind: see (UQL3) in Note [Actual unification during QuickLook] + -- unifyKind: see (UQL3) in Note [QuickLook unification] ; liftZonkM (writeMetaTyVar kappa (mkCastTy fun_ty' kind_co)) ; let co_wrap = mkWpCastN (mkGReflLeftCo Nominal fun_ty' kind_co) @@ -1561,59 +1570,18 @@ This turned out to be more subtle than I expected. Wrinkles: (QLA4) When we resume typechecking an argument, in `tcValArg` on `EValArgQL` - - quickLookArg has not yet done `qlUnify` with the calling context. We - must do so now. Example: choose [] ids, + - Calling `tcInstFun` on the argument may have emitted some constraints, which + we carefully captured in `quickLookArg` and stored in the EValArgQL. We must + now emit them with `emitConstraints`. + + - quickLookArg may or may not have done `qlUnify` with the calling context. + If not (eaql_encl = False) must do so now. Example: choose [] ids, where ids :: [forall a. a->a] choose :: a -> a -> a We instantiate choose with `kappa` and discover from `ids` that (kappa = [forall a. a->a]). Now we resume typechecking argument [], and we must take advantage of what we have now discovered about `kappa`, to typecheck [] :: [forall a. a->a] - - - Calling `tcInstFun` on the argument may have emitted some constraints, which - we carefully captured in `quickLookArg` and stored in the EValArgQL. We must - now emit them with `emitConstraints`. - -(QLA5) When we resume typechecking the argument (in the `EValArgQL` case of - `tcValArg`), we may now know that the arg is a polytype. - E.g. suppose f :: a -> [a], and we are checking that - f (g (h x)) :: [forall b. b->b] - We will end up instantiating `f` at (forall b. b->b), and hence we need to - check (g (h x)) :: forall b. b -> b - The `tcSkolemise` in `tcValArg` for EValArgQL skolemises that forall b; but - we are now at a deeper level, and those carefully-preserved kappas are from - the /outer/ level. We want it to be /as if/ we had always known that we were - checking (g (h x)) :: forall b. b -> b - so we must instantiate g with type variables whose level numbers are inside - the skolemise. - - We call `demoteQLDelta` to do this. Demotion seems like an unusual thing to - do, and indeed we need to carefully avoid calling `writeMetaTyVar` in order - to skip the check that we never unify with a type at a deeper level. But - the key insight is this: - - We should think of instantiation variables - as not having a level number at all. - - They don't need a level number (see next para), and in fact only have one - because we use normal unification variables as instantiation variables for - convenience. So `demoteQLDelta` should really be seen as creating fresh - unification variables (at the current, correct level), and then - substituting the instantiation variables to these fresh unification - variables. So it's not really a demotion at all, but rather a substitution - from unleveled instantiation variables to fresh, leveled, unification - variables. - -(QLA6) Why do instantiation variables not need a level? Because their lifetime is - short; see Note [Instantiation variables are short lived]. They must /all/ - be substituted by types (possibly with regular unification variables) before - we are done. Now, it happens that a very common case is that we want to substitute - an instantiate variable with a fresh unification variable at the same level as - the original `tcApp` call. - - By using a (levelled) unification variable as the implementation for an - (unlevelled) instantiation variable, we can make this common case into a - no-op; see the `when` short-cut in `demoteQLDelta`. -} quickLookArg :: QLFlag -> AppCtxt @@ -1743,64 +1711,18 @@ quickLookArg1 ctxt larg@(L _ arg) sc_arg_ty@(Scaled _ orig_arg_rho) * * ********************************************************************* -} -{- Note [Monomorphise instantiation variables] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -`monomorphiseQLInstVars` turns /instantiation/ variables into regular -/unification/ variables. It does so by looking at the arguments and -result type of the call, seaching for free instatiation variables. -This is the lower-case 'theta' (a mono-substitution) in the APP-DOWN rule -of Fig 5 of the Quick Look paper. - -(MIV1) When monomorphising an instantiation variable, don't forget to - monomorphise its kind. It might have type (a :: TYPE k), where both - `a` and `k` are instantiation variables. - -(MIV2) In `qlUnify`, `make_kinds_ok` may unify - a :: k1 ~ b :: k2 - making a cast - a := b |> (co :: k1 ~ k2) - But now suppose k1 is an instantiation variable. Then that coercion hole - `co` is the only place that `k1` will show up in the traversal, and yet - we want to monomrphise it. Hence the do_hole in `foldQLInstTyVars` - --} - -{- -monomorphiseQLInstVars :: [HsExprArg 'TcpInst] -> TcRhoType -> TcM () -monomorphiseQLInstVars inst_args res_rho - = do { traceTc "monomorphiseQLInstVars {" $ - vcat [ text "inst_args:" <+> vcat (map pprArgInst inst_args) - , text "res_rho:" <+> ppr res_rho ] - ; go_val_arg_ql inst_args res_rho - ; traceTc "monomorphiseQLInstVars }" empty } - where - go_val_arg_ql :: [HsExprArg 'TcpInst] -> TcRhoType -> TcM () - go_val_arg_ql inst_args rho = do { mapM_ go_arg inst_args; go_ty rho } - - go_arg :: HsExprArg 'TcpInst -> TcM () - go_arg (EValArg { ea_arg_ty = arg_ty }) = go_ty (scaledThing arg_ty) - go_arg (EValArgQL { eaql_arg_ty = arg_ty }) = go_ty (scaledThing arg_ty) - go_arg _ = return () - - go_ty :: TcType -> TcM () - go_ty ty = unTcMUnit (foldQLInstVars go_tv ty) - - go_tv :: TcTyVar -> TcMUnit - go_tv tv = assertPpr (isQLInstTyVar tv) (ppr tv) $ - TCMU $ do { traceTc "momomorphiseQLInstVar" (ppr tv) - ; info <- readMetaTyVar tv - ; case info of - Indirect ty -> go_ty ty - Flexi -> do { go_ty (tyVarKind tv) - ; monomorphiseQLInstVar tv } } - -- For the tyVarKind see (MIV1) in Note [Monomorphise instantiation variables] - - -newtype TcMUnit = TCMU { unTcMUnit :: TcM () } -instance Semigroup TcMUnit where - TCMU ml <> TCMU mr = TCMU (ml >> mr) -instance Monoid TcMUnit where - mempty = TCMU (return ()) +{- Note [The fiv test in quickLookArg] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +In rule APP-lightning-bolt in Fig 5 of the paper, we have to test rho_r +for having no free instantiation variables. We do this in Step 3 of quickLookArg1, +using anyFreeKappa. Example: + Suppose ids :: [forall a. a->a] + and consider Just (ids++ids) +We will instantiate Just with kappa, say, and then call + quickLookArg1 False {kappa} (ids ++ ids) kappa +The call to tcInstFun will return with app_res_rho = [forall a. a->a] +which has no free instantiation variables, so we can QL-unify + kappa ~ [Forall a. a->a] -} anyFreeKappa :: TcType -> TcM Bool @@ -1841,22 +1763,12 @@ foldQLInstVars check_tv ty do_tv _ tv | isQLInstTyVar tv = check_tv tv | otherwise = mempty ----------------- -{- Note [The fiv test in quickLookArg] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -In rule APP-lightning-bolt in Fig 5 of the paper, we have to test rho_r -for having no free instantiation variables. We do this in Step 3 of quickLookArg1, -using anyFreeKappa. Example: - Suppose ids :: [forall a. a->a] - and consider Just (ids++ids) -We will instantiate Just with kappa, say, and then call - quickLookArg1 False {kappa} (ids ++ ids) kappa -The call to tcInstFun will return with app_res_rho = [forall a. a->a] -which has no free instantiation variables, so we can QL-unify - kappa ~ [Forall a. a->a] --} +{- ********************************************************************* +* * + QuickLook unification +* * +********************************************************************* -} ---------------------- qlUnify :: TcType -> TcType -> TcM () -- Unify ty1 with ty2: -- * It unifies /only/ instantiation variables; @@ -1876,7 +1788,8 @@ qlUnify ty1 ty2 -- for the corresponding type. Don't unify with these. go bvs (TyVarTy tv) ty2 | isQLInstTyVar tv = go_kappa bvs tv ty2 - + -- Only unify QL instantiation variables + -- See (UQL3) in Note [QuickLook unification] go (bvs1, bvs2) ty1 (TyVarTy tv) | isQLInstTyVar tv = go_kappa (bvs2,bvs1) tv ty1 @@ -1950,7 +1863,7 @@ qlUnify ty1 ty2 = go_flexi1 bvs kappa ty2 go_flexi1 (_,bvs2) kappa ty2 -- ty2 is zonked - | -- See Note [Actual unification during QuickLook] (UQL1) + | -- See Note [QuickLook unification] (UQL1) let ty2_tvs = shallowTyCoVarsOfType ty2 , not (ty2_tvs `intersectsVarSet` bvs2) -- Can't instantiate a delta-var to a forall-bound variable @@ -1958,55 +1871,21 @@ qlUnify ty1 ty2 -- Passes the occurs check , not (isConcreteTyVar kappa) || isConcreteType ty2 -- Don't unify a concrete instantiatiation variable with a non-concrete type - = do { ty2' <- make_kinds_ok kappa ty2 + = do { co <- unifyKind (Just (TypeThing ty2)) ty2_kind kappa_kind + -- unifyKind: see (UQL2) in Note [QuickLook unification] + ; let ty2' = mkCastTy ty2 co ; traceTc "qlUnify:update" $ ppr kappa <+> text ":=" <+> ppr ty2 ; liftZonkM $ writeMetaTyVar kappa ty2' } | otherwise = return () -- Occurs-check or forall-bound variable - - make_kinds_ok :: TcTyVar -> TcType -> TcM TcType - -- Don't call unifyKind! Instead try to make the kinds equal with - -- unifyKind; and if that fails just emit an equality - -- See Note [Actual unification during QuickLook] (UQL2) - make_kinds_ok kappa ty2 - = do { co <- unifyKind (Just (TypeThing ty2)) ty2_kind kappa_kind - -- unifyKind: see Note [Actual unification during QuickLook] - ; return (mkCastTy ty2 co) } where kappa_kind = tyVarKind kappa ty2_kind = typeKind ty2 -{- - | kind1 `tcEqType` kind2 - = return ty2 - | otherwise - = do { qlUnify kind1 kind2 - ; (kind1, kind2) <- liftZonkM $ - do { kind1 <- zonkTcType kind1 - ; kind2 <- zonkTcType kind2 - ; return (kind1, kind2) } - ; if (kind1 `tcEqType` kind2) - then return ty2 - else - do { co <- emitWantedEq orig KindLevel Nominal kind2 kind1 - ; traceTc "make_kinds_ok" $ - vcat [ hang (ppr kappa <+> dcolon <+> ppr kind1 <+> text ":=") - 2 (ppr ty2 <+> dcolon <+> ppr kind2) - , text "co:" <+> ppr co ] - ; return (mkCastTy ty2 co) } } - where - kind1 = tyVarKind kappa - kind2 = typeKind ty2 - orig = TypeEqOrigin { uo_actual = kind2 - , uo_expected = kind1 - , uo_thing = Just (TypeThing ty2) - , uo_visible = True } --} - -{- Note [Actual unification during QuickLook] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +{- Note [QuickLook unification] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ In qlUnify, if we find (kappa ~ ty), we are going to update kappa := ty. That is the entire point of qlUnify! Wrinkles: @@ -2028,38 +1907,30 @@ That is the entire point of qlUnify! Wrinkles: - type families; relates to a very specific and exotic performance question, that is unlikely to bite here -(UQL2) What if kappa and ty have different kinds? So we: - * Check to see if the kinds are already the same - * If not, use qlUnify to unify them, and - * Then check again for equality - We insist on actual equality, without any casts. The whole point of +(UQL2) What if kappa and ty have different kinds? We simply call the + ordinary unifier and use the coercion to connect the two. + + If that coercion is not Refl, it is all in vain: The whole point of qlUnify is to impredicatively unify (kappa := forall a. blah). It is no good to unify (kappa := (forall a.blah) |> co) because we can't use that casted polytype. - There is a small worry that we might have - qlUnify( (kappa :: alpha), (forall a. a->a :: Type) ) - where `alpha` is a regular unification variable, not an instantiation - variable; so qlUnify won't unify it, and hence won't unify `kappa`. - But maybe `alpha` turns out to be Type anyway, so it'd be fine. But - we are very wary about unifying non-instantiation variables here; see - wrinkle (UQL3). So there is a remote danger of order dependence; whether - Quick Look succeeds depends on when `alpha` gets unified. + BUT: the kind-unifer has emitted constraint(s) so we may as well use + them. (An alternative; use uType directly, and discard constraints + if the result is not Refl.) (UQL3) qlUnify (and Quick Look generally) is very careful only to unify instantiation variables, not regular unification variables. Why? Because instantiation variables don't really have a settled level yet; - see Note [Quick Look at value arguments] wrinkle (QLA6). So we should be - worried that we might unify - alpha[1] := Maybe kappa[??] + they have level QLInstVar (see Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. + So we should be worried that we might unify + alpha[1] := Maybe kappa[qlinst] and later this kappa turns out to be a level-2 variable, and we have committed a skolem-escape error. Boo! - Solution: Quick Look only unifies instantiation variables. - - Small exception: In the IVAR rule we want (tyVarKind kappa ~ liftedTypeKind), - and that cannot possibly cause skolem escape, so do allow regular unification - for this case, via the call to `unifyKind`. + Solution: Quick Look only unifies instantiation variables, and the regular + unifier wont' do this unification because QL instantiation variables have + level infinity. -} {- ********************************************************************* ===================================== compiler/GHC/Tc/Utils/TcType.hs ===================================== @@ -699,6 +699,7 @@ data TcLevel = TcLevel Int# | QLInstVar -- See Note [TcLevel invariants] for what this Int is -- See also Note [TcLevel assignment] + -- See also Note [The TcLevel QLInstVar] {- Note [TcLevel invariants] @@ -733,14 +734,35 @@ Note [TcLevel invariants] The level of a MetaTyVar also governs its untouchability. See Note [Unification preconditions] in GHC.Tc.Utils.Unify. + -- See also Note [The TcLevel QLInstVar] + Note [TcLevel assignment] ~~~~~~~~~~~~~~~~~~~~~~~~~ We arrange the TcLevels like this - 0 Top level - 1 First-level implication constraints - 2 Second-level implication constraints + 0 Top level + 1 First-level implication constraints + 2 Second-level implication constraints ...etc... + QLInstVar The level for QuickLook instantiation variables + See Note [The QLInstVar TcLevel] + +Note [The QLInstVar TcLevel] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +QuickLook instantiation variables are identified by having a TcLevel +of QLInstVar. See Note [Quick Look overview] in GHC.Tc.Gen.App. + +The QLInstVar level behaves like infinity: it is greater than any +other TcLevel. See `strictlyDeeperThan` and friends in this module. +That ensures that we never unify an ordinary unification variable +with a QL instantiation variable, e.g. + alpha[tau:3] := Maybe beta[tau:qlinstvar] +(This is an immediate consequence of our general rule that we never +unify a variable with a type mentioning deeper variables; the skolem +escape check. + +QL instantation variables are eventually turned into ordinary unificaiton +variables; see (QL3) in Note [Quick Look overview]. Note [GivenInv] ~~~~~~~~~~~~~~~ @@ -818,12 +840,14 @@ pushTcLevel (TcLevel us) = TcLevel (us +# 1#) pushTcLevel QLInstVar = QLInstVar strictlyDeeperThan :: TcLevel -> TcLevel -> Bool +-- See Note [The QLInstVar TcLevel] strictlyDeeperThan (TcLevel tv_tclvl) (TcLevel ctxt_tclvl) = isTrue# (tv_tclvl ># ctxt_tclvl) strictlyDeeperThan QLInstVar (TcLevel {}) = True strictlyDeeperThan _ _ = False deeperThanOrSame :: TcLevel -> TcLevel -> Bool +-- See Note [The QLInstVar TcLevel] deeperThanOrSame (TcLevel tv_tclvl) (TcLevel ctxt_tclvl) = isTrue# (tv_tclvl >=# ctxt_tclvl) deeperThanOrSame (TcLevel {}) QLInstVar = False ===================================== compiler/GHC/Tc/Zonk/TcType.hs ===================================== @@ -199,17 +199,35 @@ See for example test T5631, which regresses without this change. {- ************************************************************************ * * - Zonking -- the main work-horses: zonkTcType, zonkTcTyVar + QuickLook zonking * * ************************************************************************ -} +{- Note [QuickLook zonking] +~~~~~~~~~~~~~~~~~~~~~~~~~~~ +When we are done with the QuickLook, we must +* Expose the polytypes hidden inside now-unified instantiation + variables, by zonking the types involved. +* Turn any still-un-unified QL instantiation variables into regular + unification variables, with a now-known level. + +These tasks are performed simultaneously by `qlZonkTcType`. It behaves very +similarly to the regular `zonkTcType`, except that /in addition/ it turns any +un-filled-in instantiation variable kappa into a monotype, using +`monomorphiseQLInstVar`. The latter creates a fresh unification variable, say +alpha[lvl], and unifiying kappa := alpha. + +It is very simple and satisfying that the two tasks can be done as one. +-} + qlZonkScaledTcType :: Scaled TcType -> ZonkM (Scaled TcType) qlZonkScaledTcType (Scaled m ty) = Scaled <$> qlZonkTcType m <*> qlZonkTcType ty qlZonkTcType :: TcType -> ZonkM TcType qlZonkCo :: Coercion -> ZonkM Coercion +-- See Note [QuickLook zonking] (qlZonkTcType, _, qlZonkCo, _) = mapTyCo mapper where @@ -274,6 +292,15 @@ monomorphiseQLInstTyVar tv info new_tv = mkTcTyVar (tyVarName tv) kind details ; return (mkTyVarTy new_tv) } + +{- +************************************************************************ +* * + Zonking -- the main work-horses: zonkTcType, zonkTcTyVar +* * +************************************************************************ +-} + -- For unbound, mutable tyvars, zonkType uses the function given to it -- For tyvars bound at a for-all, zonkType zonks them to an immutable -- type variable and zonks the kind too View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6d030891a12aa0a8af4afea64d142dcde956b5e9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6d030891a12aa0a8af4afea64d142dcde956b5e9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 20:30:49 2024 From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim)) Date: Mon, 03 Jun 2024 16:30:49 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/representation-polymorphic-flip Message-ID: <665e27f98d2fd_3d9c92408e1d015712a@gitlab.mail> Bodigrim pushed new branch wip/representation-polymorphic-flip at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/representation-polymorphic-flip You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 21:25:41 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 03 Jun 2024 17:25:41 -0400 Subject: [Git][ghc/ghc][wip/T24676] More wibbles Message-ID: <665e34d5bec8d_3d9c9247b66b01593a2@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24676 at Glasgow Haskell Compiler / GHC Commits: 801075df by Simon Peyton Jones at 2024-06-03T22:25:02+01:00 More wibbles - - - - - 3 changed files: - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Zonk/TcType.hs Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -51,7 +51,6 @@ import GHC.Core.Coercion import GHC.Builtin.Types ( multiplicityTy ) import GHC.Builtin.PrimOps( tagToEnumKey ) import GHC.Builtin.Names -import GHC.Driver.DynFlags import GHC.Types.Var import GHC.Types.Name @@ -167,7 +166,7 @@ tcInferSigma inst (L loc rn_expr) ; do_ql <- wantQuickLook rn_fun ; (tc_fun, fun_sigma) <- tcInferAppHead fun ; (inst_args, app_res_sigma) <- tcInstFun do_ql inst (tc_fun, fun_ctxt) fun_sigma rn_args - ; mapM_ (tcValArg do_ql) inst_args + ; _ <- tcValArgs do_ql inst_args ; return app_res_sigma } {- ********************************************************************* @@ -275,24 +274,41 @@ tcApp works like this: /its/ argument(s), in this case (h x). And so on recursively. Key point: all these instantiations make instantiation variables. -4. Use quickLookResultType to take a quick look at the result type, - when in checking mode. This is the shaded part of APP-Downarrow - in Fig 5. +Now we split into two cases: -5. Then we call finishApp to finish the job +4. Case NoQL: no Quick Look -6. finishApp uses qlZonkTcType to expose what we have learned from - Quick Look (if Quick Look is being used for this application) + 4.1 Use checkResultTy to connect the the result type. + Do this /before/ checking the arguments; see + Note [Unify with expected type before typechecking arguments] -7. Then call checkResultTy to match up the result type of the call - with that expected by the context. See Note [Unify with - expected type before typechecking arguments] + 4.2 Check the arguments with `tcValArgs`. -8. Use tcValArgs to typecheck the value arguments + 4.3 Use `finishApp` to wrap up. -9. Horrible newtype check +5. Case DoQL: use Quick Look + + 5.1 Use `quickLookResultType` to take a quick look at the result type, + when in checking mode. This is the shaded part of APP-Downarrow + in Fig 5. It also implements the key part of + Note [Unify with expected type before typechecking arguments] + + 5.2 Check the arguments with `tcValArgs`. Importantly, this will monomorphise + all the instantiation variables of the call. See Note [qlMonoTcType] + + 5.3 Use `zonkTcType` to expose the polymophism hidden under instantiation + variables in `app_res_rho`, and the monomorphic versions of any + un-unified instantiation variables. + + 5.4 Use `checkResTy` to do the subsumption check as usual + + 5.4 Use `finishApp` to wrap up + +The funcion `finishApp` mainly calls `rebuildHsApps` to rebuild the +application; but it also does a couple of gruesome final checks: + * Horrible newtype check + * Special case for tagToEnum -10. After a gruesome special case for tagToEnum, rebuild the result. Some cases that /won't/ work: @@ -373,65 +389,56 @@ tcApp rn_expr exp_res_ty -- Note [tcApp: typechecking applications] tcInstFun do_ql True tc_head fun_sigma rn_args - -- Step 3: Take a quick look at the result type - ; quickLookResultType do_ql app_res_rho exp_res_ty - - -- Finish up - ; finishApp do_ql rn_expr tc_head inst_args app_res_rho exp_res_ty } + ; case do_ql of + NoQL -> do { -- Step 4.1: subsumption check against expecte result type + -- See Note [Unify with expected type before typechecking arguments] + res_wrap <- checkResultTy rn_expr tc_head inst_args + app_res_rho exp_res_ty + -- Step 4.2: typecheck the arguments + ; tc_args <- tcValArgs NoQL inst_args + -- Step 4.3: wrap up + ; finishApp tc_head tc_args app_res_rho res_wrap } + + DoQL -> do { -- Step 5.1: Take a quick look at the result type + quickLookResultType app_res_rho exp_res_ty + -- Step 5.2: typecheck the arguments, and monomorphise + -- any un-unified instantiation variables + ; tc_args <- tcValArgs DoQL inst_args + -- Step 5.3: typecheck the arguments + ; app_res_rho <- liftZonkM $ zonkTcType app_res_rho + -- Step 5.4: subsumption check against the expected type + ; res_wrap <- checkResultTy rn_expr tc_head inst_args + app_res_rho exp_res_ty + -- Step 5.5: wrap up + ; finishApp tc_head tc_args app_res_rho res_wrap } } setQLInstLevel :: QLFlag -> TcM a -> TcM a setQLInstLevel DoQL thing_inside = setTcLevel QLInstVar thing_inside setQLInstLevel NoQL thing_inside = thing_inside -quickLookResultType :: QLFlag -> TcRhoType -> ExpRhoType -> TcM () +quickLookResultType :: TcRhoType -> ExpRhoType -> TcM () -- This function implements the shaded bit of rule APP-Downarrow in -- Fig 5 of the QL paper: "A quick look at impredicativity" (ICFP'20). -quickLookResultType DoQL app_res_rho (Check exp_rho) = qlUnify app_res_rho exp_rho -quickLookResultType _ _ _ = return () - -finishApp :: QLFlag -> HsExpr GhcRn - -> (HsExpr GhcTc, AppCtxt) -- Head of the application - -> [HsExprArg 'TcpInst] -- Args of the application - -> TcRhoType -- Inferred type of the application - -> ExpRhoType -- Expected type; this is deeply skolemised +quickLookResultType app_res_rho (Check exp_rho) = qlUnify app_res_rho exp_rho +quickLookResultType _ _ = return () + +finishApp :: (HsExpr GhcTc, AppCtxt) -> [HsExprArg 'TcpTc] + -> TcRhoType -> HsWrapper -> TcM (HsExpr GhcTc) -finishApp do_ql rn_expr tc_head@(tc_fun,_) inst_args app_res_rho exp_res_ty - = do { -- Step 6: qlZonk the type of the result of the call - -- See Note [QuickLook zonking] in GHC.Tc.Zonk.TcType - traceTc "finishApp" $ vcat [ ppr app_res_rho, ppr exp_res_ty ] - ; app_res_rho <- case do_ql of - DoQL -> liftZonkM $ qlZonkTcType app_res_rho - NoQL -> return app_res_rho - - -- Step 7: check the result type - ; res_wrap <- checkResultTy rn_expr tc_head inst_args - app_res_rho exp_res_ty - - -- step 8: Typecheck the value arguments - ; tc_args <- mapM (tcValArg do_ql) inst_args - - -- Step 9: Horrible newtype check +-- Do final checks and wrap up the result +finishApp tc_head@(tc_fun,_) tc_args app_res_rho res_wrap + = do { -- Horrible newtype check ; rejectRepPolyNewtypes tc_head app_res_rho - -- Step 10: econstruct, with a special case for tagToEnum#. - ; tc_expr <- if isTagToEnum tc_fun - then tcTagToEnum tc_head tc_args app_res_rho - else return (rebuildHsApps tc_head tc_args) - - ; whenDOptM Opt_D_dump_tc_trace $ - do { inst_args <- liftZonkM $ mapM zonkArg inst_args -- Only when tracing - ; traceTc "tcApp }" (vcat [ text "inst_args" <+> brackets (pprWithCommas pprArgInst inst_args) - , text "app_res_rho:" <+> ppr app_res_rho - , text "tc_fun:" <+> ppr tc_fun - , text "tc_args:" <+> ppr tc_args - , text "tc_expr:" <+> ppr tc_expr ]) } - - ; return (mkHsWrap res_wrap tc_expr) } - + -- Reconstruct, with a horrible special case for tagToEnum#. + ; res_expr <- if isTagToEnum tc_fun + then tcTagToEnum tc_head tc_args app_res_rho + else return (rebuildHsApps tc_head tc_args) + ; return (mkHsWrap res_wrap res_expr) } checkResultTy :: HsExpr GhcRn -> (HsExpr GhcTc, AppCtxt) -- Head - -> [HsExprArg p] -- Arguments + -> [HsExprArg p] -- Arguments, just error messages -> TcRhoType -- Inferred type of the application; zonked to -- expose foralls, but maybe not deeply instantiated -> ExpRhoType -- Expected type; this is deeply skolemised @@ -486,11 +493,20 @@ checkResultTy rn_expr (tc_fun, fun_ctxt) inst_args app_res_rho (Check res_ty) thing_inside ---------------- +tcValArgs :: QLFlag -> [HsExprArg 'TcpInst] -> TcM [HsExprArg 'TcpTc] +-- Importantly, tcValArgs works left-to-right, so that by the time we +-- encounter an argument, we have monomorphised all the instantiation +-- variables that its type contains. All that is left to do is an ordinary +-- zonkTcType. See Note [Monomorphise instantiation variables]. +tcValArgs do_ql args = mapM (tcValArg do_ql) args + tcValArg :: QLFlag -> HsExprArg 'TcpInst -- Actual argument -> TcM (HsExprArg 'TcpTc) -- Resulting argument -tcValArg _ (EPrag l p) = return (EPrag l (tcExprPrag p)) -tcValArg _ (EWrap w) = return (EWrap w) -tcValArg _ (ETypeArg l hs_ty ty) = return (ETypeArg l hs_ty ty) +tcValArg _ (EPrag l p) = return (EPrag l (tcExprPrag p)) +tcValArg _ (ETypeArg l hty ty) = return (ETypeArg l hty ty) +tcValArg do_ql (EWrap (EHsWrap w)) = do { whenQL do_ql $ qlMonoHsWrapper w + ; return (EWrap (EHsWrap w)) } +tcValArg _ (EWrap ew) = return (EWrap ew) tcValArg do_ql (EValArg { ea_ctxt = ctxt , ea_arg = larg@(L arg_loc arg) @@ -512,7 +528,7 @@ tcValArg do_ql (EValArg { ea_ctxt = ctxt -- See Note [Instantiation variables are short lived] -- and Note [QuickLook zonking] in GHC.Tc.Zonk.TcType ; Scaled mult exp_arg_ty <- case do_ql of - DoQL -> liftZonkM $ qlZonkScaledTcType sc_arg_ty + DoQL -> liftZonkM $ zonkScaledTcType sc_arg_ty NoQL -> return sc_arg_ty -- Now check the argument @@ -533,7 +549,7 @@ tcValArg _ (EValArgQL { eaql_wanted = wanted , eaql_res_rho = app_res_rho }) = addArgCtxt ctxt larg $ do { -- Expose QL results to tcSkolemise, as in EValArg case - Scaled mult exp_arg_ty <- liftZonkM $ qlZonkScaledTcType sc_arg_ty + Scaled mult exp_arg_ty <- liftZonkM $ zonkScaledTcType sc_arg_ty ; traceTc "tcEValArgQL {" (vcat [ text "app_res_rho:" <+> ppr app_res_rho , text "exp_arg_ty:" <+> ppr exp_arg_ty @@ -547,13 +563,16 @@ tcValArg _ (EValArgQL { eaql_wanted = wanted -- See (QLA4) in Note [Quick Look at value arguments] emitConstraints wanted - -- Unify with context if we have no already done so + -- Unify with context if we have not already done so -- See (QLA4) in Note [Quick Look at value arguments] ; unless arg_influences_enclosing_call $ -- Don't repeat qlUnify app_res_rho exp_arg_rho -- the qlUnify - ; finishApp DoQL rn_expr tc_head inst_args - app_res_rho (mkCheckExpType exp_arg_rho) } + ; tc_args <- tcValArgs DoQL inst_args + ; app_res_rho <- liftZonkM $ zonkTcType app_res_rho + ; res_wrap <- checkResultTy rn_expr tc_head inst_args + app_res_rho (mkCheckExpType exp_arg_rho) + ; finishApp tc_head tc_args app_res_rho res_wrap } ; traceTc "tcEValArgQL }" $ vcat [ text "app_res_rho:" <+> ppr app_res_rho ] @@ -574,6 +593,7 @@ quickLookKeys :: [Unique] -- See Note [Quick Look for particular Ids] quickLookKeys = [dollarIdKey, leftSectionKey, rightSectionKey] +{- -- zonkArg is used *only* during debug-tracing, to make it easier to -- see what is going on. For that reason, it is not a full zonk: add -- more if you need it. @@ -582,6 +602,7 @@ zonkArg eva@(EValArg { ea_arg_ty = Scaled m ty }) = do { ty' <- zonkTcType ty ; return (eva { ea_arg_ty = Scaled m ty' }) } zonkArg arg = return arg +-} {- ********************************************************************* * * @@ -1530,19 +1551,17 @@ at its arguments. This is quadratic in the nesting depth of the arguments. Instead, after the quick look, we /save/ the work we have done in an EValArgQL record, and /resume/ it later. The way to think of it is this: - * `tcApp` typechecks an application. It is strutured into two: - - the "initial" part, especially `tcInstFun` - - the "finish" part, `finishApp`, which completes the job + * `tcApp` typechecks an application. It uses `tcInstFun`, which in turn + calls `quickLookArg` on each value argument. - * quickLookArg (which takes a quick look at the argument) + * `quickLookArg` (which takes a quick look at the argument) - Does the "initial" part of `tcApp`, especially `tcInstFun` - Captures the result in an EValArgQL record - Later, `tcValArg` starts from the EValArgQL record, and - completes the job of tpyechecking the appication by calling - `finishApp` + completes the job of typechecking the application This turned out to be more subtle than I expected. Wrinkles: @@ -1609,7 +1628,10 @@ skipQuickLook ctxt larg arg_ty = return (EValArg { ea_ctxt = ctxt , ea_arg = larg , ea_arg_ty = arg_ty }) - -- do_ql <=> remember to zonk this argument in tcValArg + +whenQL :: QLFlag -> ZonkM () -> TcM () +whenQL DoQL thing_inside = liftZonkM thing_inside +whenQL NoQL _ = return () tcIsDeepRho :: TcType -> TcM Bool -- This top-level zonk step, which is the reason we need a local 'go' loop, @@ -1711,6 +1733,87 @@ quickLookArg1 ctxt larg@(L _ arg) sc_arg_ty@(Scaled _ orig_arg_rho) * * ********************************************************************* -} +{- Note [Monomorphise instantiation variables] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +When we are done with Quick Look on a call, we must turn any un-unified +/instantiation/ variables into regular /unification/ variables. This is the +lower-case 'theta' (a mono-substitution) in the APP-DOWN rule of Fig 5 of the +Quick Look paper. + +We so this by look at the arguments, left to right, monomorphising the free +instantiation variables of the /type/ arguments of the call. Those type +arguments appear (only) in + * the `WpTyApp` components of + * the `HsWrapper` of + * a `EWrap` argument +See `qlMonoHsWrapper`. + +By going left to right, we are sure to monomorphise instantiation variables +before we encounter them in an argument type (in `tcValArg`). + +To monomorphise the free QL instantiation variables of a type, we use +`foldQLInstVars`. + +Wrinkles: + +(MIV1) When monomorphising an instantiation variable, don't forget to + monomorphise its kind. It might have type (a :: TYPE k), where both + `a` and `k` are instantiation variables. + +(MIV2) In `qlUnify`, `make_kinds_ok` may unify + a :: k1 ~ b :: k2 + making a cast + a := b |> (co :: k1 ~ k2) + But now suppose k1 is an instantiation variable. Then that coercion hole + `co` is the only place that `k1` will show up in the traversal, and yet + we want to monomrphise it. Hence the do_hole in `foldQLInstTyVars` +-} + +qlMonoHsWrapper :: HsWrapper -> ZonkM () +qlMonoHsWrapper (WpCompose w1 w2) = qlMonoHsWrapper w1 >> qlMonoHsWrapper w2 +qlMonoHsWrapper (WpTyApp ty) = qlMonoTcType ty +qlMonoHsWrapper _ = return () + +qlMonoTcType :: TcType -> ZonkM () +qlMonoTcType ty + = do { traceZonk "monomorphiseQLInstVars {" (ppr ty) + ; go_ty ty + ; traceZonk "monomorphiseQLInstVars }" empty } + where + go_ty :: TcType -> ZonkM () + go_ty ty = unTcMUnit (foldQLInstVars go_tv ty) + + go_tv :: TcTyVar -> TcMUnit + -- Precondition: tv is a QL instantiation variable + -- If it is already unified, look through it and carry on + -- If not, monomorphise it, by making a fresh unification variable, + -- at the ambient level + go_tv tv + | MetaTv { mtv_ref = ref, mtv_tclvl = lvl, mtv_info = info } <- tcTyVarDetails tv + = assertPpr (case lvl of QLInstVar -> True; _ -> False) (ppr tv) $ + TCMU $ do { traceZonk "qlMonoTcType" (ppr tv) + ; flex <- readTcRef ref + ; case flex of { + Indirect ty -> go_ty ty ; + Flexi -> + do { let kind = tyVarKind tv + ; go_ty kind -- See (MIV1) in Note [Monomorphise instantiation variables] + ; ref2 <- newTcRef Flexi + ; lvl2 <- getZonkTcLevel + ; let details = MetaTv { mtv_info = info + , mtv_ref = ref2 + , mtv_tclvl = lvl2 } + tv2 = mkTcTyVar (tyVarName tv) kind details + ; writeTcRef ref (Indirect (mkTyVarTy tv2)) }}} + | otherwise + = pprPanic "qlMonoTcType" (ppr tv) + +newtype TcMUnit = TCMU { unTcMUnit :: ZonkM () } +instance Semigroup TcMUnit where + TCMU ml <> TCMU mr = TCMU (ml >> mr) +instance Monoid TcMUnit where + mempty = TCMU (return ()) + {- Note [The fiv test in quickLookArg] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ In rule APP-lightning-bolt in Fig 5 of the paper, we have to test rho_r ===================================== compiler/GHC/Tc/Gen/Head.hs ===================================== @@ -16,7 +16,7 @@ -} module GHC.Tc.Gen.Head - ( HsExprArg(..), TcPass(..), QLFlag(..) + ( HsExprArg(..), TcPass(..), QLFlag(..), EWrap(..) , AppCtxt(..), appCtxtLoc, insideExpansion , splitHsApps, rebuildHsApps , addArgWrap, isHsValArg ===================================== compiler/GHC/Tc/Zonk/TcType.hs ===================================== @@ -15,15 +15,12 @@ module GHC.Tc.Zonk.TcType module GHC.Tc.Zonk.Monad -- ** Zonking types - , zonkTcType, zonkTcTypes + , zonkTcType, zonkTcTypes, zonkScaledTcType , zonkTcTyVar, zonkTcTyVars , zonkTcTyVarToTcTyVar, zonkTcTyVarsToTcTyVars , zonkInvisTVBinder , zonkCo - -- ** Quick-look zonking - , qlZonkTcType, qlZonkScaledTcType - -- ** Zonking 'TyCon's , zonkTcTyCon @@ -196,103 +193,6 @@ These functions just wrap writeTcRef, with some extra tracing See for example test T5631, which regresses without this change. -} -{- -************************************************************************ -* * - QuickLook zonking -* * -************************************************************************ --} - -{- Note [QuickLook zonking] -~~~~~~~~~~~~~~~~~~~~~~~~~~~ -When we are done with the QuickLook, we must -* Expose the polytypes hidden inside now-unified instantiation - variables, by zonking the types involved. -* Turn any still-un-unified QL instantiation variables into regular - unification variables, with a now-known level. - -These tasks are performed simultaneously by `qlZonkTcType`. It behaves very -similarly to the regular `zonkTcType`, except that /in addition/ it turns any -un-filled-in instantiation variable kappa into a monotype, using -`monomorphiseQLInstVar`. The latter creates a fresh unification variable, say -alpha[lvl], and unifiying kappa := alpha. - -It is very simple and satisfying that the two tasks can be done as one. --} - -qlZonkScaledTcType :: Scaled TcType -> ZonkM (Scaled TcType) -qlZonkScaledTcType (Scaled m ty) - = Scaled <$> qlZonkTcType m <*> qlZonkTcType ty - -qlZonkTcType :: TcType -> ZonkM TcType -qlZonkCo :: Coercion -> ZonkM Coercion --- See Note [QuickLook zonking] -(qlZonkTcType, _, qlZonkCo, _) - = mapTyCo mapper - where - mapper :: TyCoMapper () ZonkM - mapper = TyCoMapper - { tcm_tyvar = const qlzonk_tc_tyvar - , tcm_covar = const (\cv -> mkCoVarCo <$> qlzonk_tcv cv) - , tcm_hole = qlzonk_hole - , tcm_tycobinder = \ _env tcv _vis k -> qlzonk_tcv tcv >>= k () - , tcm_tycon = return } - - qlzonk_hole :: () -> CoercionHole -> ZonkM Coercion - qlzonk_hole _ hole@(CoercionHole { ch_ref = ref, ch_co_var = cv }) - = do { contents <- readTcRef ref - ; case contents of - Just co -> qlZonkCo co - Nothing -> do { cv' <- qlzonk_tcv cv - ; return $ HoleCo (hole { ch_co_var = cv' }) } } - - qlzonk_tcv :: TyCoVar -> ZonkM TyCoVar - qlzonk_tcv tcv = do { kind' <- qlZonkTcType (varType tcv) - ; return (setVarType tcv kind') } - - qlzonk_tc_tyvar :: TcTyVar -> ZonkM TcType - qlzonk_tc_tyvar tv - | isTcTyVar tv - = case tcTyVarDetails tv of - SkolemTv {} -> qlzonk_kind_and_return tv - RuntimeUnk {} -> qlzonk_kind_and_return tv - MetaTv { mtv_ref = ref, mtv_tclvl = lvl, mtv_info = info } - -> do { cts <- readTcRef ref - ; case cts of - Indirect ty -> do { ty' <- qlZonkTcType ty - ; writeTcRef ref (Indirect ty') - -- See Note [Sharing in zonking] - ; return ty' } - Flexi | QLInstVar <- lvl - -> do { ty' <- monomorphiseQLInstTyVar tv info - ; writeTcRef ref (Indirect ty') - ; return ty' } - | otherwise - -> qlzonk_kind_and_return tv } - - | otherwise -- coercion variable - = qlzonk_kind_and_return tv - where - - qlzonk_kind_and_return :: TcTyVar -> ZonkM TcType - qlzonk_kind_and_return tv - = do { tv' <- qlzonk_tcv tv - ; return (mkTyVarTy tv') } - -monomorphiseQLInstTyVar :: TcTyVar -> MetaInfo -> ZonkM TcType --- Make a fresh ordinary unification variable, with the same --- Name and MetaInfo as the current one --- Precondition: the MetaInfo argument is that of the TcTyVar -monomorphiseQLInstTyVar tv info - = do { ref <- newTcRef Flexi - ; lvl <- getZonkTcLevel - ; kind <- qlZonkTcType (tyVarKind tv) - ; let details = MetaTv {mtv_info = info, mtv_ref = ref, mtv_tclvl = lvl } - new_tv = mkTcTyVar (tyVarName tv) kind details - ; return (mkTyVarTy new_tv) } - - {- ************************************************************************ * * @@ -301,6 +201,10 @@ monomorphiseQLInstTyVar tv info ************************************************************************ -} +zonkScaledTcType :: Scaled TcType -> ZonkM (Scaled TcType) +zonkScaledTcType (Scaled m ty) + = Scaled <$> zonkTcType m <*> zonkTcType ty + -- For unbound, mutable tyvars, zonkType uses the function given to it -- For tyvars bound at a for-all, zonkType zonks them to an immutable -- type variable and zonks the kind too View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/801075dff6202767a9f300ec0b0a5af587afd49c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/801075dff6202767a9f300ec0b0a5af587afd49c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 23:44:02 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 03 Jun 2024 19:44:02 -0400 Subject: [Git][ghc/ghc][master] Migrate `Finder` component to `OsPath`, fixed #24616 Message-ID: <665e5542155f4_16e7cdcf0eb836584@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 20 changed files: - compiler/GHC.hs - + compiler/GHC/Data/OsPath.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Config/Finder.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Iface/Errors.hs - compiler/GHC/Unit/Finder.hs - compiler/GHC/Unit/Finder/Types.hs - compiler/GHC/Unit/Module/Location.hs - compiler/GHC/Unit/Module/ModSummary.hs - compiler/ghc.cabal.in - ghc/ghc-bin.cabal.in - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -3,6 +3,7 @@ {-# LANGUAGE NondecreasingIndentation, ScopedTypeVariables #-} {-# LANGUAGE TupleSections, NamedFieldPuns #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE PatternSynonyms #-} -- ----------------------------------------------------------------------------- -- @@ -76,6 +77,7 @@ module GHC ( ModuleGraph, emptyMG, mapMG, mkModuleGraph, mgModSummaries, mgLookupModule, ModSummary(..), ms_mod_name, ModLocation(..), + pattern ModLocation, getModSummary, getModuleGraph, isLoaded, ===================================== compiler/GHC/Data/OsPath.hs ===================================== @@ -0,0 +1,29 @@ +module GHC.Data.OsPath + ( + -- * OsPath initialisation and transformation + OsPath + , OsString + , encodeUtf + , decodeUtf + , unsafeDecodeUtf + , unsafeEncodeUtf + , os + -- * Common utility functions + , () + , (<.>) + ) + where + +import GHC.Prelude + +import GHC.Utils.Misc (HasCallStack) +import GHC.Utils.Panic (panic) + +import System.OsPath +import System.Directory.Internal (os) + +-- | Decode an 'OsPath' to 'FilePath', throwing an 'error' if decoding failed. +-- Prefer 'decodeUtf' and gracious error handling. +unsafeDecodeUtf :: HasCallStack => OsPath -> FilePath +unsafeDecodeUtf p = + either (\err -> panic $ "Failed to decodeUtf \"" ++ show p ++ "\", because: " ++ show err) id (decodeUtf p) ===================================== compiler/GHC/Data/Strict.hs ===================================== @@ -9,8 +9,8 @@ module GHC.Data.Strict ( Maybe(Nothing, Just), fromMaybe, + GHC.Data.Strict.maybe, Pair(And), - -- Not used at the moment: -- -- Either(Left, Right), @@ -18,6 +18,7 @@ module GHC.Data.Strict ( ) where import GHC.Prelude hiding (Maybe(..), Either(..)) + import Control.Applicative import Data.Semigroup import Data.Data @@ -29,6 +30,10 @@ fromMaybe :: a -> Maybe a -> a fromMaybe d Nothing = d fromMaybe _ (Just x) = x +maybe :: b -> (a -> b) -> Maybe a -> b +maybe d _ Nothing = d +maybe _ f (Just x) = f x + apMaybe :: Maybe (a -> b) -> Maybe a -> Maybe b apMaybe (Just f) (Just x) = Just (f x) apMaybe _ _ = Nothing ===================================== compiler/GHC/Driver/Backpack.hs ===================================== @@ -74,6 +74,7 @@ import GHC.Linker.Types import qualified GHC.LanguageExtensions as LangExt import GHC.Data.Maybe +import GHC.Data.OsPath (unsafeEncodeUtf, os) import GHC.Data.StringBuffer import GHC.Data.FastString import qualified GHC.Data.EnumSet as EnumSet @@ -772,7 +773,7 @@ summariseRequirement pn mod_name = do let PackageName pn_fs = pn let location = mkHomeModLocation2 fopts mod_name - (unpackFS pn_fs moduleNameSlashes mod_name) "hsig" + (unsafeEncodeUtf $ unpackFS pn_fs moduleNameSlashes mod_name) (os "hsig") env <- getBkpEnv src_hash <- liftIO $ getFileHash (bkp_filename env) @@ -855,12 +856,12 @@ hsModuleToModSummary home_keys pn hsc_src modname -- these filenames to figure out where the hi files go. -- A travesty! let location0 = mkHomeModLocation2 fopts modname - (unpackFS unit_fs + (unsafeEncodeUtf $ unpackFS unit_fs moduleNameSlashes modname) (case hsc_src of - HsigFile -> "hsig" - HsBootFile -> "hs-boot" - HsSrcFile -> "hs") + HsigFile -> os "hsig" + HsBootFile -> os "hs-boot" + HsSrcFile -> os "hs") -- DANGEROUS: bootifying can POISON the module finder cache let location = case hsc_src of HsBootFile -> addBootSuffixLocnOut location0 ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -35,6 +35,7 @@ import GHC.Driver.LlvmConfigCache (LlvmConfigCache) import GHC.Driver.Ppr import GHC.Driver.Backend +import GHC.Data.OsPath import qualified GHC.Data.ShortText as ST import GHC.Data.Stream ( Stream ) import qualified GHC.Data.Stream as Stream @@ -259,7 +260,7 @@ outputForeignStubs Maybe FilePath) -- C file created outputForeignStubs logger tmpfs dflags unit_state mod location stubs = do - let stub_h = mkStubPaths (initFinderOpts dflags) (moduleName mod) location + let stub_h = unsafeDecodeUtf $ mkStubPaths (initFinderOpts dflags) (moduleName mod) location stub_c <- newTempName logger tmpfs (tmpDir dflags) TFL_CurrentModule "c" case stubs of ===================================== compiler/GHC/Driver/Config/Finder.hs ===================================== @@ -8,27 +8,27 @@ import GHC.Prelude import GHC.Driver.DynFlags import GHC.Unit.Finder.Types import GHC.Data.FastString - +import GHC.Data.OsPath -- | Create a new 'FinderOpts' from DynFlags. initFinderOpts :: DynFlags -> FinderOpts initFinderOpts flags = FinderOpts - { finder_importPaths = importPaths flags + { finder_importPaths = fmap unsafeEncodeUtf $ importPaths flags , finder_lookupHomeInterfaces = isOneShot (ghcMode flags) , finder_bypassHiFileCheck = MkDepend == (ghcMode flags) , finder_ways = ways flags , finder_enableSuggestions = gopt Opt_HelpfulErrors flags - , finder_workingDirectory = workingDirectory flags + , finder_workingDirectory = fmap unsafeEncodeUtf $ workingDirectory flags , finder_thisPackageName = mkFastString <$> thisPackageName flags , finder_hiddenModules = hiddenModules flags , finder_reexportedModules = reexportedModules flags - , finder_hieDir = hieDir flags - , finder_hieSuf = hieSuf flags - , finder_hiDir = hiDir flags - , finder_hiSuf = hiSuf_ flags - , finder_dynHiSuf = dynHiSuf_ flags - , finder_objectDir = objectDir flags - , finder_objectSuf = objectSuf_ flags - , finder_dynObjectSuf = dynObjectSuf_ flags - , finder_stubDir = stubDir flags + , finder_hieDir = fmap unsafeEncodeUtf $ hieDir flags + , finder_hieSuf = unsafeEncodeUtf $ hieSuf flags + , finder_hiDir = fmap unsafeEncodeUtf $ hiDir flags + , finder_hiSuf = unsafeEncodeUtf $ hiSuf_ flags + , finder_dynHiSuf = unsafeEncodeUtf $ dynHiSuf_ flags + , finder_objectDir = fmap unsafeEncodeUtf $ objectDir flags + , finder_objectSuf = unsafeEncodeUtf $ objectSuf_ flags + , finder_dynObjectSuf = unsafeEncodeUtf $ dynObjectSuf_ flags + , finder_stubDir = fmap unsafeEncodeUtf $ stubDir flags } ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -264,6 +264,7 @@ import qualified GHC.LanguageExtensions as LangExt import GHC.Data.FastString import GHC.Data.Bag +import GHC.Data.OsPath (unsafeEncodeUtf) import GHC.Data.StringBuffer import qualified GHC.Data.Stream as Stream import GHC.Data.Stream (Stream) @@ -2111,12 +2112,13 @@ hscCompileCmmFile hsc_env original_filename filename output_filename = runHsc hs rawCmms return stub_c_exists where - no_loc = ModLocation{ ml_hs_file = Just original_filename, - ml_hi_file = panic "hscCompileCmmFile: no hi file", - ml_obj_file = panic "hscCompileCmmFile: no obj file", - ml_dyn_obj_file = panic "hscCompileCmmFile: no dyn obj file", - ml_dyn_hi_file = panic "hscCompileCmmFile: no dyn obj file", - ml_hie_file = panic "hscCompileCmmFile: no hie file"} + no_loc = OsPathModLocation + { ml_hs_file_ospath = Just $ unsafeEncodeUtf original_filename, + ml_hi_file_ospath = panic "hscCompileCmmFile: no hi file", + ml_obj_file_ospath = panic "hscCompileCmmFile: no obj file", + ml_dyn_obj_file_ospath = panic "hscCompileCmmFile: no dyn obj file", + ml_dyn_hi_file_ospath = panic "hscCompileCmmFile: no dyn obj file", + ml_hie_file_ospath = panic "hscCompileCmmFile: no hie file"} -------------------- Stuff for new code gen --------------------- @@ -2351,12 +2353,13 @@ hscParsedDecls hsc_env decls = runInteractiveHsc hsc_env $ do {- Desugar it -} -- We use a basically null location for iNTERACTIVE - let iNTERACTIVELoc = ModLocation{ ml_hs_file = Nothing, - ml_hi_file = panic "hsDeclsWithLocation:ml_hi_file", - ml_obj_file = panic "hsDeclsWithLocation:ml_obj_file", - ml_dyn_obj_file = panic "hsDeclsWithLocation:ml_dyn_obj_file", - ml_dyn_hi_file = panic "hsDeclsWithLocation:ml_dyn_hi_file", - ml_hie_file = panic "hsDeclsWithLocation:ml_hie_file" } + let iNTERACTIVELoc = OsPathModLocation + { ml_hs_file_ospath = Nothing, + ml_hi_file_ospath = panic "hsDeclsWithLocation:ml_hi_file_ospath", + ml_obj_file_ospath = panic "hsDeclsWithLocation:ml_obj_file_ospath", + ml_dyn_obj_file_ospath = panic "hsDeclsWithLocation:ml_dyn_obj_file_ospath", + ml_dyn_hi_file_ospath = panic "hsDeclsWithLocation:ml_dyn_hi_file_ospath", + ml_hie_file_ospath = panic "hsDeclsWithLocation:ml_hie_file_ospath" } ds_result <- hscDesugar' iNTERACTIVELoc tc_gblenv {- Simplify -} @@ -2635,12 +2638,13 @@ hscCompileCoreExpr' hsc_env srcspan ds_expr = do {- Lint if necessary -} lintInteractiveExpr (text "hscCompileCoreExpr") hsc_env prepd_expr - let this_loc = ModLocation{ ml_hs_file = Nothing, - ml_hi_file = panic "hscCompileCoreExpr':ml_hi_file", - ml_obj_file = panic "hscCompileCoreExpr':ml_obj_file", - ml_dyn_obj_file = panic "hscCompileCoreExpr': ml_obj_file", - ml_dyn_hi_file = panic "hscCompileCoreExpr': ml_dyn_hi_file", - ml_hie_file = panic "hscCompileCoreExpr':ml_hie_file" } + let this_loc = OsPathModLocation + { ml_hs_file_ospath = Nothing, + ml_hi_file_ospath = panic "hscCompileCoreExpr':ml_hi_file_ospath", + ml_obj_file_ospath = panic "hscCompileCoreExpr':ml_obj_file_ospath", + ml_dyn_obj_file_ospath = panic "hscCompileCoreExpr': ml_obj_file_ospath", + ml_dyn_hi_file_ospath = panic "hscCompileCoreExpr': ml_dyn_hi_file_ospath", + ml_hie_file_ospath = panic "hscCompileCoreExpr':ml_hie_file_ospath" } -- Ensure module uniqueness by giving it a name like "GhciNNNN". -- This uniqueness is needed by the JS linker. Without it we break the 1-1 ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -76,6 +76,7 @@ import GHC.Data.Bag ( listToBag ) import GHC.Data.Graph.Directed import GHC.Data.FastString import GHC.Data.Maybe ( expectJust ) +import GHC.Data.OsPath ( unsafeEncodeUtf ) import GHC.Data.StringBuffer import qualified GHC.LanguageExtensions as LangExt @@ -1837,7 +1838,7 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = tn <- newTempName logger tmpfs (tmpDir dflags) staticLife suf let dyn_tn = tn -<.> dynsuf addFilesToClean tmpfs dynLife [dyn_tn] - return (tn, dyn_tn) + return (unsafeEncodeUtf tn, unsafeEncodeUtf dyn_tn) -- We don't want to create .o or .hi files unless we have been asked -- to by the user. But we need them, so we patch their locations in -- the ModSummary with temporary files. @@ -1846,8 +1847,8 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = -- If ``-fwrite-interface` is specified, then the .o and .hi files -- are written into `-odir` and `-hidir` respectively. #16670 if gopt Opt_WriteInterface dflags - then return ((ml_hi_file ms_location, ml_dyn_hi_file ms_location) - , (ml_obj_file ms_location, ml_dyn_obj_file ms_location)) + then return ((ml_hi_file_ospath ms_location, ml_dyn_hi_file_ospath ms_location) + , (ml_obj_file_ospath ms_location, ml_dyn_obj_file_ospath ms_location)) else (,) <$> (new_temp_file (hiSuf_ dflags) (dynHiSuf_ dflags)) <*> (new_temp_file (objectSuf_ dflags) (dynObjectSuf_ dflags)) let new_dflags = case enable_spec of @@ -1856,10 +1857,10 @@ enableCodeGenWhen logger tmpfs staticLife dynLife unit_env mod_graph = EnableByteCodeAndObject -> (gopt_set dflags Opt_ByteCodeAndObjectCode) { backend = defaultBackendOf ms} let ms' = ms { ms_location = - ms_location { ml_hi_file = hi_file - , ml_obj_file = o_file - , ml_dyn_hi_file = dyn_hi_file - , ml_dyn_obj_file = dyn_o_file } + ms_location { ml_hi_file_ospath = hi_file + , ml_obj_file_ospath = o_file + , ml_dyn_hi_file_ospath = dyn_hi_file + , ml_dyn_obj_file_ospath = dyn_o_file } , ms_hspp_opts = updOptLevel 0 $ new_dflags } -- Recursive call to catch the other cases @@ -2044,7 +2045,7 @@ summariseFile hsc_env' home_unit old_summaries src_fn mb_phase maybe_buf let fopts = initFinderOpts (hsc_dflags hsc_env) -- Make a ModLocation for this file - let location = mkHomeModLocation fopts pi_mod_name src_fn + let location = mkHomeModLocation fopts pi_mod_name (unsafeEncodeUtf src_fn) -- Tell the Finder cache where it is, so that subsequent calls -- to findModule will find it, even if it's not on any search path ===================================== compiler/GHC/Driver/MakeFile.hs ===================================== @@ -24,6 +24,7 @@ import GHC.Driver.Env import GHC.Driver.Errors.Types import qualified GHC.SysTools as SysTools import GHC.Data.Graph.Directed ( SCC(..) ) +import GHC.Data.OsPath (unsafeDecodeUtf) import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Types.SourceError @@ -252,7 +253,7 @@ processDeps dflags hsc_env excl_mods root hdl (AcyclicSCC (ModuleNode _ node)) -- files if the module has a corresponding .hs-boot file (#14482) ; when (isBootSummary node == IsBoot) $ do let hi_boot = msHiFilePath node - let obj = removeBootSuffix (msObjFilePath node) + let obj = unsafeDecodeUtf $ removeBootSuffix (msObjFileOsPath node) forM_ extra_suffixes $ \suff -> do let way_obj = insertSuffixes obj [suff] let way_hi_boot = insertSuffixes hi_boot [suff] @@ -297,7 +298,7 @@ findDependency hsc_env srcloc pkg imp is_boot include_pkg_deps = do Found loc _ -- Home package: just depend on the .hi or hi-boot file | isJust (ml_hs_file loc) || include_pkg_deps - -> return (Just (addBootSuffix_maybe is_boot (ml_hi_file loc))) + -> return (Just (unsafeDecodeUtf $ addBootSuffix_maybe is_boot (ml_hi_file_ospath loc))) -- Not in this package: we don't need a dependency | otherwise ===================================== compiler/GHC/Driver/Pipeline/Execute.hs ===================================== @@ -58,6 +58,7 @@ import GHC.Iface.Make import GHC.Driver.Config.Parser import GHC.Parser.Header import GHC.Data.StringBuffer +import GHC.Data.OsPath (unsafeEncodeUtf) import GHC.Types.SourceError import GHC.Unit.Finder import Data.IORef @@ -772,7 +773,7 @@ mkOneShotModLocation :: PipeEnv -> DynFlags -> HscSource -> ModuleName -> IO Mod mkOneShotModLocation pipe_env dflags src_flavour mod_name = do let PipeEnv{ src_basename=basename, src_suffix=suff } = pipe_env - let location1 = mkHomeModLocation2 fopts mod_name basename suff + let location1 = mkHomeModLocation2 fopts mod_name (unsafeEncodeUtf basename) (unsafeEncodeUtf suff) -- Boot-ify it if necessary let location2 @@ -784,11 +785,11 @@ mkOneShotModLocation pipe_env dflags src_flavour mod_name = do -- This can't be done in mkHomeModuleLocation because -- it only applies to the module being compiles let ohi = outputHi dflags - location3 | Just fn <- ohi = location2{ ml_hi_file = fn } + location3 | Just fn <- ohi = location2{ ml_hi_file_ospath = unsafeEncodeUtf fn } | otherwise = location2 let dynohi = dynOutputHi dflags - location4 | Just fn <- dynohi = location3{ ml_dyn_hi_file = fn } + location4 | Just fn <- dynohi = location3{ ml_dyn_hi_file_ospath = unsafeEncodeUtf fn } | otherwise = location3 -- Take -o into account if present @@ -802,10 +803,10 @@ mkOneShotModLocation pipe_env dflags src_flavour mod_name = do location5 | Just ofile <- expl_o_file , let dyn_ofile = fromMaybe (ofile -<.> dynObjectSuf_ dflags) expl_dyn_o_file , isNoLink (ghcLink dflags) - = location4 { ml_obj_file = ofile - , ml_dyn_obj_file = dyn_ofile } + = location4 { ml_obj_file_ospath = unsafeEncodeUtf ofile + , ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile } | Just dyn_ofile <- expl_dyn_o_file - = location4 { ml_dyn_obj_file = dyn_ofile } + = location4 { ml_dyn_obj_file_ospath = unsafeEncodeUtf dyn_ofile } | otherwise = location4 return location5 where ===================================== compiler/GHC/Iface/Errors.hs ===================================== @@ -14,6 +14,7 @@ import GHC.Utils.Panic.Plain import GHC.Driver.DynFlags import GHC.Driver.Env import GHC.Data.Maybe +import GHC.Data.OsPath import GHC.Prelude import GHC.Unit import GHC.Unit.Env @@ -55,13 +56,13 @@ cantFindInstalledErr unit_state mhome_unit profile mod_name find_result InstalledNotFound files mb_pkg | Just pkg <- mb_pkg , notHomeUnitId mhome_unit pkg - -> not_found_in_package pkg files + -> not_found_in_package pkg $ fmap unsafeDecodeUtf files | null files -> NotAModule | otherwise - -> CouldntFindInFiles files + -> CouldntFindInFiles $ fmap unsafeDecodeUtf files _ -> panic "cantFindInstalledErr" ===================================== compiler/GHC/Unit/Finder.hs ===================================== @@ -42,6 +42,9 @@ import GHC.Platform.Ways import GHC.Builtin.Names ( gHC_PRIM ) +import GHC.Data.Maybe ( expectJust ) +import GHC.Data.OsPath + import GHC.Unit.Env import GHC.Unit.Types import GHC.Unit.Module @@ -49,7 +52,6 @@ import GHC.Unit.Home import GHC.Unit.State import GHC.Unit.Finder.Types -import GHC.Data.Maybe ( expectJust ) import qualified GHC.Data.ShortText as ST import GHC.Utils.Misc @@ -61,8 +63,7 @@ import GHC.Types.PkgQual import GHC.Fingerprint import Data.IORef -import System.Directory -import System.FilePath +import System.Directory.OsPath import Control.Monad import Data.Time import qualified Data.Map as M @@ -70,9 +71,10 @@ import GHC.Driver.Env ( hsc_home_unit_maybe, HscEnv(hsc_FC, hsc_dflags, hsc_unit_env) ) import GHC.Driver.Config.Finder import qualified Data.Set as Set +import qualified System.OsPath as OsPath -type FileExt = String -- Filename extension -type BaseName = String -- Basename of file +type FileExt = OsString -- Filename extension +type BaseName = OsPath -- Basename of file -- ----------------------------------------------------------------------------- -- The Finder @@ -286,7 +288,7 @@ findLookupResult fc fopts r = case r of -- implicit locations from the instances InstalledFound loc _ -> return (Found loc m) InstalledNoPackage _ -> return (NoPackage (moduleUnit m)) - InstalledNotFound fp _ -> return (NotFound{ fr_paths = fp, fr_pkg = Just (moduleUnit m) + InstalledNotFound fp _ -> return (NotFound{ fr_paths = fmap unsafeDecodeUtf fp, fr_pkg = Just (moduleUnit m) , fr_pkgs_hidden = [] , fr_mods_hidden = [] , fr_unusables = [] @@ -357,7 +359,7 @@ findHomeModule fc fopts home_unit mod_name = do InstalledFound loc _ -> Found loc (mkHomeModule home_unit mod_name) InstalledNoPackage _ -> NoPackage uid -- impossible InstalledNotFound fps _ -> NotFound { - fr_paths = fps, + fr_paths = fmap unsafeDecodeUtf fps, fr_pkg = Just uid, fr_mods_hidden = [], fr_pkgs_hidden = [], @@ -382,7 +384,7 @@ findHomePackageModule fc fopts home_unit mod_name = do InstalledFound loc _ -> Found loc (mkModule uid mod_name) InstalledNoPackage _ -> NoPackage uid -- impossible InstalledNotFound fps _ -> NotFound { - fr_paths = fps, + fr_paths = fmap unsafeDecodeUtf fps, fr_pkg = Just uid, fr_mods_hidden = [], fr_pkgs_hidden = [], @@ -418,17 +420,17 @@ findInstalledHomeModule fc fopts home_unit mod_name = do hi_dir_path = case finder_hiDir fopts of Just hiDir -> case maybe_working_dir of - Nothing -> [hiDir] - Just fp -> [fp hiDir] + Nothing -> [hiDir] + Just fp -> [fp hiDir] Nothing -> home_path hisuf = finder_hiSuf fopts mod = mkModule home_unit mod_name source_exts = - [ ("hs", mkHomeModLocationSearched fopts mod_name "hs") - , ("lhs", mkHomeModLocationSearched fopts mod_name "lhs") - , ("hsig", mkHomeModLocationSearched fopts mod_name "hsig") - , ("lhsig", mkHomeModLocationSearched fopts mod_name "lhsig") + [ (os "hs", mkHomeModLocationSearched fopts mod_name $ os "hs") + , (os "lhs", mkHomeModLocationSearched fopts mod_name $ os "lhs") + , (os "hsig", mkHomeModLocationSearched fopts mod_name $ os "hsig") + , (os "lhsig", mkHomeModLocationSearched fopts mod_name $ os "lhsig") ] -- we use mkHomeModHiOnlyLocation instead of mkHiOnlyModLocation so that @@ -453,10 +455,11 @@ findInstalledHomeModule fc fopts home_unit mod_name = do else searchPathExts search_dirs mod exts -- | Prepend the working directory to the search path. -augmentImports :: FilePath -> [FilePath] -> [FilePath] +augmentImports :: OsPath -> [OsPath] -> [OsPath] augmentImports _work_dir [] = [] -augmentImports work_dir (fp:fps) | isAbsolute fp = fp : augmentImports work_dir fps - | otherwise = (work_dir fp) : augmentImports work_dir fps +augmentImports work_dir (fp:fps) + | OsPath.isAbsolute fp = fp : augmentImports work_dir fps + | otherwise = (work_dir fp) : augmentImports work_dir fps -- | Search for a module in external packages only. findPackageModule :: FinderCache -> UnitState -> FinderOpts -> InstalledModule -> IO InstalledFindResult @@ -488,14 +491,14 @@ findPackageModule_ fc fopts mod pkg_conf = do tag = waysBuildTag (finder_ways fopts) -- hi-suffix for packages depends on the build tag. - package_hisuf | null tag = "hi" - | otherwise = tag ++ "_hi" + package_hisuf | null tag = os "hi" + | otherwise = os (tag ++ "_hi") - package_dynhisuf = waysBuildTag (addWay WayDyn (finder_ways fopts)) ++ "_hi" + package_dynhisuf = os $ waysBuildTag (addWay WayDyn (finder_ways fopts)) ++ "_hi" mk_hi_loc = mkHiOnlyModLocation fopts package_hisuf package_dynhisuf - import_dirs = map ST.unpack $ unitImportDirs pkg_conf + import_dirs = map (unsafeEncodeUtf . ST.unpack) $ unitImportDirs pkg_conf -- we never look for a .hi-boot file in an external package; -- .hi-boot files only make sense for the home package. in @@ -503,7 +506,7 @@ findPackageModule_ fc fopts mod pkg_conf = do [one] | finder_bypassHiFileCheck fopts -> -- there's only one place that this .hi file can be, so -- don't bother looking for it. - let basename = moduleNameSlashes (moduleName mod) + let basename = unsafeEncodeUtf $ moduleNameSlashes (moduleName mod) loc = mk_hi_loc one basename in return $ InstalledFound loc mod _otherwise -> @@ -512,24 +515,24 @@ findPackageModule_ fc fopts mod pkg_conf = do -- ----------------------------------------------------------------------------- -- General path searching -searchPathExts :: [FilePath] -- paths to search +searchPathExts :: [OsPath] -- paths to search -> InstalledModule -- module name -> [ ( - FileExt, -- suffix - FilePath -> BaseName -> ModLocation -- action + FileExt, -- suffix + OsPath -> BaseName -> ModLocation -- action ) ] -> IO InstalledFindResult searchPathExts paths mod exts = search to_search where - basename = moduleNameSlashes (moduleName mod) + basename = unsafeEncodeUtf $ moduleNameSlashes (moduleName mod) - to_search :: [(FilePath, ModLocation)] + to_search :: [(OsPath, ModLocation)] to_search = [ (file, fn path basename) | path <- paths, (ext,fn) <- exts, - let base | path == "." = basename + let base | path == os "." = basename | otherwise = path basename file = base <.> ext ] @@ -543,7 +546,7 @@ searchPathExts paths mod exts = search to_search else search rest mkHomeModLocationSearched :: FinderOpts -> ModuleName -> FileExt - -> FilePath -> BaseName -> ModLocation + -> OsPath -> BaseName -> ModLocation mkHomeModLocationSearched fopts mod suff path basename = mkHomeModLocation2 fopts mod (path basename) suff @@ -581,18 +584,18 @@ mkHomeModLocationSearched fopts mod suff path basename = -- ext -- The filename extension of the source file (usually "hs" or "lhs"). -mkHomeModLocation :: FinderOpts -> ModuleName -> FilePath -> ModLocation +mkHomeModLocation :: FinderOpts -> ModuleName -> OsPath -> ModLocation mkHomeModLocation dflags mod src_filename = - let (basename,extension) = splitExtension src_filename + let (basename,extension) = OsPath.splitExtension src_filename in mkHomeModLocation2 dflags mod basename extension mkHomeModLocation2 :: FinderOpts -> ModuleName - -> FilePath -- Of source module, without suffix - -> String -- Suffix + -> OsPath -- Of source module, without suffix + -> FileExt -- Suffix -> ModLocation mkHomeModLocation2 fopts mod src_basename ext = - let mod_basename = moduleNameSlashes mod + let mod_basename = unsafeEncodeUtf $ moduleNameSlashes mod obj_fn = mkObjPath fopts src_basename mod_basename dyn_obj_fn = mkDynObjPath fopts src_basename mod_basename @@ -600,51 +603,51 @@ mkHomeModLocation2 fopts mod src_basename ext = dyn_hi_fn = mkDynHiPath fopts src_basename mod_basename hie_fn = mkHiePath fopts src_basename mod_basename - in (ModLocation{ ml_hs_file = Just (src_basename <.> ext), - ml_hi_file = hi_fn, - ml_dyn_hi_file = dyn_hi_fn, - ml_obj_file = obj_fn, - ml_dyn_obj_file = dyn_obj_fn, - ml_hie_file = hie_fn }) + in (OsPathModLocation{ ml_hs_file_ospath = Just (src_basename <.> ext), + ml_hi_file_ospath = hi_fn, + ml_dyn_hi_file_ospath = dyn_hi_fn, + ml_obj_file_ospath = obj_fn, + ml_dyn_obj_file_ospath = dyn_obj_fn, + ml_hie_file_ospath = hie_fn }) mkHomeModHiOnlyLocation :: FinderOpts -> ModuleName - -> FilePath + -> OsPath -> BaseName -> ModLocation mkHomeModHiOnlyLocation fopts mod path basename = - let loc = mkHomeModLocation2 fopts mod (path basename) "" - in loc { ml_hs_file = Nothing } + let loc = mkHomeModLocation2 fopts mod (path basename) mempty + in loc { ml_hs_file_ospath = Nothing } -- This function is used to make a ModLocation for a package module. Hence why -- we explicitly pass in the interface file suffixes. -mkHiOnlyModLocation :: FinderOpts -> Suffix -> Suffix -> FilePath -> String +mkHiOnlyModLocation :: FinderOpts -> FileExt -> FileExt -> OsPath -> OsPath -> ModLocation mkHiOnlyModLocation fopts hisuf dynhisuf path basename = let full_basename = path basename obj_fn = mkObjPath fopts full_basename basename dyn_obj_fn = mkDynObjPath fopts full_basename basename hie_fn = mkHiePath fopts full_basename basename - in ModLocation{ ml_hs_file = Nothing, - ml_hi_file = full_basename <.> hisuf, - -- Remove the .hi-boot suffix from - -- hi_file, if it had one. We always - -- want the name of the real .hi file - -- in the ml_hi_file field. - ml_dyn_obj_file = dyn_obj_fn, - -- MP: TODO - ml_dyn_hi_file = full_basename <.> dynhisuf, - ml_obj_file = obj_fn, - ml_hie_file = hie_fn + in OsPathModLocation{ ml_hs_file_ospath = Nothing, + ml_hi_file_ospath = full_basename <.> hisuf, + -- Remove the .hi-boot suffix from + -- hi_file, if it had one. We always + -- want the name of the real .hi file + -- in the ml_hi_file field. + ml_dyn_obj_file_ospath = dyn_obj_fn, + -- MP: TODO + ml_dyn_hi_file_ospath = full_basename <.> dynhisuf, + ml_obj_file_ospath = obj_fn, + ml_hie_file_ospath = hie_fn } -- | Constructs the filename of a .o file for a given source file. -- Does /not/ check whether the .o file exists mkObjPath :: FinderOpts - -> FilePath -- the filename of the source file, minus the extension - -> String -- the module name with dots replaced by slashes - -> FilePath + -> OsPath -- the filename of the source file, minus the extension + -> OsPath -- the module name with dots replaced by slashes + -> OsPath mkObjPath fopts basename mod_basename = obj_basename <.> osuf where odir = finder_objectDir fopts @@ -657,9 +660,9 @@ mkObjPath fopts basename mod_basename = obj_basename <.> osuf -- Does /not/ check whether the .dyn_o file exists mkDynObjPath :: FinderOpts - -> FilePath -- the filename of the source file, minus the extension - -> String -- the module name with dots replaced by slashes - -> FilePath + -> OsPath -- the filename of the source file, minus the extension + -> OsPath -- the module name with dots replaced by slashes + -> OsPath mkDynObjPath fopts basename mod_basename = obj_basename <.> dynosuf where odir = finder_objectDir fopts @@ -673,9 +676,9 @@ mkDynObjPath fopts basename mod_basename = obj_basename <.> dynosuf -- Does /not/ check whether the .hi file exists mkHiPath :: FinderOpts - -> FilePath -- the filename of the source file, minus the extension - -> String -- the module name with dots replaced by slashes - -> FilePath + -> OsPath -- the filename of the source file, minus the extension + -> OsPath -- the module name with dots replaced by slashes + -> OsPath mkHiPath fopts basename mod_basename = hi_basename <.> hisuf where hidir = finder_hiDir fopts @@ -688,9 +691,9 @@ mkHiPath fopts basename mod_basename = hi_basename <.> hisuf -- Does /not/ check whether the .dyn_hi file exists mkDynHiPath :: FinderOpts - -> FilePath -- the filename of the source file, minus the extension - -> String -- the module name with dots replaced by slashes - -> FilePath + -> OsPath -- the filename of the source file, minus the extension + -> OsPath -- the module name with dots replaced by slashes + -> OsPath mkDynHiPath fopts basename mod_basename = hi_basename <.> dynhisuf where hidir = finder_hiDir fopts @@ -703,9 +706,9 @@ mkDynHiPath fopts basename mod_basename = hi_basename <.> dynhisuf -- Does /not/ check whether the .hie file exists mkHiePath :: FinderOpts - -> FilePath -- the filename of the source file, minus the extension - -> String -- the module name with dots replaced by slashes - -> FilePath + -> OsPath -- the filename of the source file, minus the extension + -> OsPath -- the module name with dots replaced by slashes + -> OsPath mkHiePath fopts basename mod_basename = hie_basename <.> hiesuf where hiedir = finder_hieDir fopts @@ -726,23 +729,23 @@ mkStubPaths :: FinderOpts -> ModuleName -> ModLocation - -> FilePath + -> OsPath mkStubPaths fopts mod location = let stubdir = finder_stubDir fopts - mod_basename = moduleNameSlashes mod - src_basename = dropExtension $ expectJust "mkStubPaths" - (ml_hs_file location) + mod_basename = unsafeEncodeUtf $ moduleNameSlashes mod + src_basename = OsPath.dropExtension $ expectJust "mkStubPaths" + (ml_hs_file_ospath location) stub_basename0 | Just dir <- stubdir = dir mod_basename | otherwise = src_basename - stub_basename = stub_basename0 ++ "_stub" + stub_basename = stub_basename0 `mappend` os "_stub" in - stub_basename <.> "h" + stub_basename <.> os "h" -- ----------------------------------------------------------------------------- -- findLinkable isn't related to the other stuff in here, ===================================== compiler/GHC/Unit/Finder/Types.hs ===================================== @@ -9,6 +9,7 @@ where import GHC.Prelude import GHC.Unit +import GHC.Data.OsPath import qualified Data.Map as M import GHC.Fingerprint import GHC.Platform.Ways @@ -31,7 +32,7 @@ data FinderCache = FinderCache { fcModuleCache :: (IORef FinderCacheState) data InstalledFindResult = InstalledFound ModLocation InstalledModule | InstalledNoPackage UnitId - | InstalledNotFound [FilePath] (Maybe UnitId) + | InstalledNotFound [OsPath] (Maybe UnitId) -- | The result of searching for an imported module. -- @@ -70,7 +71,7 @@ data FindResult -- -- Should be taken from 'DynFlags' via 'initFinderOpts'. data FinderOpts = FinderOpts - { finder_importPaths :: [FilePath] + { finder_importPaths :: [OsPath] -- ^ Where are we allowed to look for Modules and Source files , finder_lookupHomeInterfaces :: Bool -- ^ When looking up a home module: @@ -88,17 +89,17 @@ data FinderOpts = FinderOpts , finder_enableSuggestions :: Bool -- ^ If we encounter unknown modules, should we suggest modules -- that have a similar name. - , finder_workingDirectory :: Maybe FilePath + , finder_workingDirectory :: Maybe OsPath , finder_thisPackageName :: Maybe FastString , finder_hiddenModules :: Set.Set ModuleName , finder_reexportedModules :: Set.Set ModuleName - , finder_hieDir :: Maybe FilePath - , finder_hieSuf :: String - , finder_hiDir :: Maybe FilePath - , finder_hiSuf :: String - , finder_dynHiSuf :: String - , finder_objectDir :: Maybe FilePath - , finder_objectSuf :: String - , finder_dynObjectSuf :: String - , finder_stubDir :: Maybe FilePath + , finder_hieDir :: Maybe OsPath + , finder_hieSuf :: OsString + , finder_hiDir :: Maybe OsPath + , finder_hiSuf :: OsString + , finder_dynHiSuf :: OsString + , finder_objectDir :: Maybe OsPath + , finder_objectSuf :: OsString + , finder_dynObjectSuf :: OsString + , finder_stubDir :: Maybe OsPath } deriving Show ===================================== compiler/GHC/Unit/Module/Location.hs ===================================== @@ -1,6 +1,17 @@ +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE ViewPatterns #-} -- | Module location module GHC.Unit.Module.Location - ( ModLocation(..) + ( ModLocation + ( .. + , ml_hs_file + , ml_hi_file + , ml_dyn_hi_file + , ml_obj_file + , ml_dyn_obj_file + , ml_hie_file + ) + , pattern ModLocation , addBootSuffix , addBootSuffix_maybe , addBootSuffixLocn_maybe @@ -11,15 +22,19 @@ module GHC.Unit.Module.Location where import GHC.Prelude + +import GHC.Data.OsPath import GHC.Unit.Types import GHC.Utils.Outputable +import qualified System.OsString as OsString + -- | Module Location -- -- Where a module lives on the file system: the actual locations -- of the .hs, .hi, .dyn_hi, .o, .dyn_o and .hie files, if we have them. -- --- For a module in another unit, the ml_hs_file and ml_obj_file components of +-- For a module in another unit, the ml_hs_file_ospath and ml_obj_file_ospath components of -- ModLocation are undefined. -- -- The locations specified by a ModLocation may or may not @@ -38,31 +53,31 @@ import GHC.Utils.Outputable -- boot suffixes in mkOneShotModLocation. data ModLocation - = ModLocation { - ml_hs_file :: Maybe FilePath, + = OsPathModLocation { + ml_hs_file_ospath :: Maybe OsPath, -- ^ The source file, if we have one. Package modules -- probably don't have source files. - ml_hi_file :: FilePath, + ml_hi_file_ospath :: OsPath, -- ^ Where the .hi file is, whether or not it exists -- yet. Always of form foo.hi, even if there is an -- hi-boot file (we add the -boot suffix later) - ml_dyn_hi_file :: FilePath, + ml_dyn_hi_file_ospath :: OsPath, -- ^ Where the .dyn_hi file is, whether or not it exists -- yet. - ml_obj_file :: FilePath, + ml_obj_file_ospath :: OsPath, -- ^ Where the .o file is, whether or not it exists yet. -- (might not exist either because the module hasn't -- been compiled yet, or because it is part of a -- unit with a .a file) - ml_dyn_obj_file :: FilePath, + ml_dyn_obj_file_ospath :: OsPath, -- ^ Where the .dy file is, whether or not it exists -- yet. - ml_hie_file :: FilePath + ml_hie_file_ospath :: OsPath -- ^ Where the .hie file is, whether or not it exists -- yet. } deriving Show @@ -71,18 +86,18 @@ instance Outputable ModLocation where ppr = text . show -- | Add the @-boot@ suffix to .hs, .hi and .o files -addBootSuffix :: FilePath -> FilePath -addBootSuffix path = path ++ "-boot" +addBootSuffix :: OsPath -> OsPath +addBootSuffix path = path `mappend` os "-boot" -- | Remove the @-boot@ suffix to .hs, .hi and .o files -removeBootSuffix :: FilePath -> FilePath -removeBootSuffix "-boot" = [] -removeBootSuffix (x:xs) = x : removeBootSuffix xs -removeBootSuffix [] = error "removeBootSuffix: no -boot suffix" - +removeBootSuffix :: OsPath -> OsPath +removeBootSuffix pathWithBootSuffix = + case OsString.stripSuffix (os "-boot") pathWithBootSuffix of + Just path -> path + Nothing -> error "removeBootSuffix: no -boot suffix" -- | Add the @-boot@ suffix if the @Bool@ argument is @True@ -addBootSuffix_maybe :: IsBootInterface -> FilePath -> FilePath +addBootSuffix_maybe :: IsBootInterface -> OsPath -> OsPath addBootSuffix_maybe is_boot path = case is_boot of IsBoot -> addBootSuffix path NotBoot -> path @@ -95,22 +110,50 @@ addBootSuffixLocn_maybe is_boot locn = case is_boot of -- | Add the @-boot@ suffix to all file paths associated with the module addBootSuffixLocn :: ModLocation -> ModLocation addBootSuffixLocn locn - = locn { ml_hs_file = fmap addBootSuffix (ml_hs_file locn) - , ml_hi_file = addBootSuffix (ml_hi_file locn) - , ml_dyn_hi_file = addBootSuffix (ml_dyn_hi_file locn) - , ml_obj_file = addBootSuffix (ml_obj_file locn) - , ml_dyn_obj_file = addBootSuffix (ml_dyn_obj_file locn) - , ml_hie_file = addBootSuffix (ml_hie_file locn) } + = locn { ml_hs_file_ospath = fmap addBootSuffix (ml_hs_file_ospath locn) + , ml_hi_file_ospath = addBootSuffix (ml_hi_file_ospath locn) + , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn) + , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn) + , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn) + , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn) } -- | Add the @-boot@ suffix to all output file paths associated with the -- module, not including the input file itself addBootSuffixLocnOut :: ModLocation -> ModLocation addBootSuffixLocnOut locn - = locn { ml_hi_file = addBootSuffix (ml_hi_file locn) - , ml_dyn_hi_file = addBootSuffix (ml_dyn_hi_file locn) - , ml_obj_file = addBootSuffix (ml_obj_file locn) - , ml_dyn_obj_file = addBootSuffix (ml_dyn_obj_file locn) - , ml_hie_file = addBootSuffix (ml_hie_file locn) + = locn { ml_hi_file_ospath = addBootSuffix (ml_hi_file_ospath locn) + , ml_dyn_hi_file_ospath = addBootSuffix (ml_dyn_hi_file_ospath locn) + , ml_obj_file_ospath = addBootSuffix (ml_obj_file_ospath locn) + , ml_dyn_obj_file_ospath = addBootSuffix (ml_dyn_obj_file_ospath locn) + , ml_hie_file_ospath = addBootSuffix (ml_hie_file_ospath locn) } - +-- ---------------------------------------------------------------------------- +-- Helpers for backwards compatibility +-- ---------------------------------------------------------------------------- + +pattern ModLocation :: Maybe FilePath -> FilePath -> FilePath -> FilePath -> FilePath -> FilePath -> ModLocation +pattern ModLocation + { ml_hs_file + , ml_hi_file + , ml_dyn_hi_file + , ml_obj_file + , ml_dyn_obj_file + , ml_hie_file + } <- OsPathModLocation + { ml_hs_file_ospath = (fmap unsafeDecodeUtf -> ml_hs_file) + , ml_hi_file_ospath = (unsafeDecodeUtf -> ml_hi_file) + , ml_dyn_hi_file_ospath = (unsafeDecodeUtf -> ml_dyn_hi_file) + , ml_obj_file_ospath = (unsafeDecodeUtf -> ml_obj_file) + , ml_dyn_obj_file_ospath = (unsafeDecodeUtf -> ml_dyn_obj_file) + , ml_hie_file_ospath = (unsafeDecodeUtf -> ml_hie_file) + } where + ModLocation ml_hs_file ml_hi_file ml_dyn_hi_file ml_obj_file ml_dyn_obj_file ml_hie_file + = OsPathModLocation + { ml_hs_file_ospath = fmap unsafeEncodeUtf ml_hs_file + , ml_hi_file_ospath = unsafeEncodeUtf ml_hi_file + , ml_dyn_hi_file_ospath = unsafeEncodeUtf ml_dyn_hi_file + , ml_obj_file_ospath = unsafeEncodeUtf ml_obj_file + , ml_dyn_obj_file_ospath = unsafeEncodeUtf ml_dyn_obj_file + , ml_hie_file_ospath = unsafeEncodeUtf ml_hie_file + } ===================================== compiler/GHC/Unit/Module/ModSummary.hs ===================================== @@ -17,6 +17,11 @@ module GHC.Unit.Module.ModSummary , msHsFilePath , msObjFilePath , msDynObjFilePath + , msHsFileOsPath + , msHiFileOsPath + , msDynHiFileOsPath + , msObjFileOsPath + , msDynObjFileOsPath , msDeps , isBootSummary , findTarget @@ -38,6 +43,7 @@ import GHC.Types.Target import GHC.Types.PkgQual import GHC.Data.Maybe +import GHC.Data.OsPath (OsPath) import GHC.Data.StringBuffer ( StringBuffer ) import GHC.Utils.Fingerprint @@ -146,6 +152,13 @@ msDynHiFilePath ms = ml_dyn_hi_file (ms_location ms) msObjFilePath ms = ml_obj_file (ms_location ms) msDynObjFilePath ms = ml_dyn_obj_file (ms_location ms) +msHsFileOsPath, msDynHiFileOsPath, msHiFileOsPath, msObjFileOsPath, msDynObjFileOsPath :: ModSummary -> OsPath +msHsFileOsPath ms = expectJust "msHsFilePath" (ml_hs_file_ospath (ms_location ms)) +msHiFileOsPath ms = ml_hi_file_ospath (ms_location ms) +msDynHiFileOsPath ms = ml_dyn_hi_file_ospath (ms_location ms) +msObjFileOsPath ms = ml_obj_file_ospath (ms_location ms) +msDynObjFileOsPath ms = ml_dyn_obj_file_ospath (ms_location ms) + -- | Did this 'ModSummary' originate from a hs-boot file? isBootSummary :: ModSummary -> IsBootInterface isBootSummary ms = if ms_hsc_src ms == HsBootFile then IsBoot else NotBoot ===================================== compiler/ghc.cabal.in ===================================== @@ -123,7 +123,8 @@ Library time >= 1.4 && < 1.15, containers >= 0.6.2.1 && < 0.8, array >= 0.1 && < 0.6, - filepath >= 1 && < 1.6, + filepath >= 1.5 && < 1.6, + os-string >= 2.0.1 && < 2.1, hpc >= 0.6 && < 0.8, transformers >= 0.5 && < 0.7, exceptions == 0.10.*, @@ -444,6 +445,7 @@ Library GHC.Data.List.SetOps GHC.Data.Maybe GHC.Data.OrdList + GHC.Data.OsPath GHC.Data.Pair GHC.Data.SmallArray GHC.Data.Stream ===================================== ghc/ghc-bin.cabal.in ===================================== @@ -36,7 +36,7 @@ Executable ghc bytestring >= 0.9 && < 0.13, directory >= 1 && < 1.4, process >= 1 && < 1.7, - filepath >= 1 && < 1.6, + filepath >= 1.5 && < 1.6, containers >= 0.5 && < 0.8, transformers >= 0.5 && < 0.7, ghc-boot == @ProjectVersionMunged@, ===================================== testsuite/tests/count-deps/CountDepsAst.stdout ===================================== @@ -70,6 +70,7 @@ GHC.Data.List.Infinite GHC.Data.List.SetOps GHC.Data.Maybe GHC.Data.OrdList +GHC.Data.OsPath GHC.Data.Pair GHC.Data.SmallArray GHC.Data.Strict ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -71,6 +71,7 @@ GHC.Data.List.Infinite GHC.Data.List.SetOps GHC.Data.Maybe GHC.Data.OrdList +GHC.Data.OsPath GHC.Data.Pair GHC.Data.SmallArray GHC.Data.Strict ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Create.hs ===================================== @@ -93,10 +93,7 @@ createInterface1 flags unit_state mod_sum mod_iface ifaces inst_ifaces (instance -- pragmas in the modules source code. Used to infer -- safety of module. ms_hspp_opts - , ms_location = - ModLocation - { ml_hie_file - } + , ms_location = modl } = mod_sum dflags = ms_hspp_opts @@ -228,7 +225,7 @@ createInterface1 flags unit_state mod_sum mod_iface ifaces inst_ifaces (instance Interface { ifaceMod = mdl , ifaceIsSig = is_sig - , ifaceHieFile = ml_hie_file + , ifaceHieFile = ml_hie_file modl , ifaceInfo = info , ifaceDoc = Documentation header_doc mod_warning , ifaceRnDoc = Documentation Nothing Nothing View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c8ece0df3316b9f1934f3f059437bc055f5cfae2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c8ece0df3316b9f1934f3f059437bc055f5cfae2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 3 23:44:50 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 03 Jun 2024 19:44:50 -0400 Subject: [Git][ghc/ghc][master] compiler: emit NaturallyAligned when element type & index type are the same width Message-ID: <665e557213ac9_16e7cdef274841256@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 1 changed file: - compiler/GHC/StgToCmm/Prim.hs Changes: ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -2302,8 +2302,8 @@ alignmentFromTypes :: CmmType -- ^ element type -> CmmType -- ^ index type -> AlignmentSpec alignmentFromTypes ty idx_ty - | typeWidth ty < typeWidth idx_ty = NaturallyAligned - | otherwise = Unaligned + | typeWidth ty <= typeWidth idx_ty = NaturallyAligned + | otherwise = Unaligned doIndexOffAddrOp :: Maybe MachOp -> CmmType View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0cff083abb24701530974872b21cf897c9955a9a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0cff083abb24701530974872b21cf897c9955a9a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 00:15:26 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 03 Jun 2024 20:15:26 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 13 commits: Migrate `Finder` component to `OsPath`, fixed #24616 Message-ID: <665e5c9e32c2_16e7cd13752d44270@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 0bce5abf by Sebastian Graf at 2024-06-03T20:15:11-04:00 Parser: Remove unused `apats` rule - - - - - 7fe5b7fc by David Knothe at 2024-06-03T20:15:11-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - ce8fb51e by Cheng Shao at 2024-06-03T20:15:14-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - 4e0fea20 by Cheng Shao at 2024-06-03T20:15:14-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - 74c7d647 by Cheng Shao at 2024-06-03T20:15:14-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - c1ba0d8d by Cheng Shao at 2024-06-03T20:15:14-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 25430bf2 by Cheng Shao at 2024-06-03T20:15:14-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - 0d33f8f6 by Cheng Shao at 2024-06-03T20:15:14-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - 999637df by Cheng Shao at 2024-06-03T20:15:14-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - ba9d4e42 by Cheng Shao at 2024-06-03T20:15:14-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 28de59e0 by Cheng Shao at 2024-06-03T20:15:15-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - + compiler/GHC/Data/OsPath.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Config/Finder.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6c3a56046193bca66ca43fa4f9c63801a019852d...28de59e030d258f55f6aa93bae6672605a9df144 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6c3a56046193bca66ca43fa4f9c63801a019852d...28de59e030d258f55f6aa93bae6672605a9df144 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 09:05:56 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Jun 2024 05:05:56 -0400 Subject: [Git][ghc/ghc][master] 2 commits: Parser: Remove unused `apats` rule Message-ID: <665ed8f490782_27a8357c9e3011518e@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 30 changed files: - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Check.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Types.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Utils.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Error/Codes.hs - compiler/GHC/Utils/Outputable.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0cff083abb24701530974872b21cf897c9955a9a...38757c305e96a1db93cc48a3d7bea4277433f97f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0cff083abb24701530974872b21cf897c9955a9a...38757c305e96a1db93cc48a3d7bea4277433f97f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 09:06:29 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Jun 2024 05:06:29 -0400 Subject: [Git][ghc/ghc][master] 8 commits: compiler/ghci/rts: remove stdcall support completely Message-ID: <665ed9157510c_27a83591f08c1183ad@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 30 changed files: - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/StgToCmm/Bind.hs - compiler/GHC/StgToCmm/Foreign.hs - compiler/GHC/StgToCmm/Lit.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/SysTools/Terminal.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/Literal.hs - compiler/Language/Haskell/Syntax/Decls.hs - docs/users_guide/9.12.1-notes.rst - docs/users_guide/using-warnings.rst - docs/users_guide/win32-dlls.rst - − libraries/ghc-internal/include/windows_cconv.h The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/38757c305e96a1db93cc48a3d7bea4277433f97f...54332437da3177ad987a8352bd60c3591676aa69 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/38757c305e96a1db93cc48a3d7bea4277433f97f...54332437da3177ad987a8352bd60c3591676aa69 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 09:07:10 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Jun 2024 05:07:10 -0400 Subject: [Git][ghc/ghc][master] hadrian: improve user settings documentation Message-ID: <665ed93e366aa_27a835b1bd0412143a@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 1 changed file: - hadrian/doc/user-settings.md Changes: ===================================== hadrian/doc/user-settings.md ===================================== @@ -119,22 +119,22 @@ the right names for them: * `ghc` refers to GHC commands; the final slot refers to how GHC is invoked: * `c.opts` for commands that build C files with GHC - * `hs.opts` for commands that compile Haskell modules with GHC + * `cpp.opts` for commands that build C++ files with GHC + * `hs.opts` for commands that compile Haskell modules with GHC * `link.opts` for GHC linking command * `deps.opts` for commands that figure out dependencies between Haskell modules (with `ghc -M`) * `toolargs.opts` for GHC commands that are used to generate the right ghci argument for `hadrian/ghci` to work - * `cc` refers to C compiler commands - * `cxx` refers to C++ compiler commands + * `cc` refers to C/C++ compiler commands - * `c.opts` for commands that call the C compiler on some C files - * `deps.opts` for commands that call the C compiler for figuring out - dependencies between C files + * `c.opts` for commands that call the C compiler on some C/C++ files + * `deps.opts` for commands that call the C compiler for figuring out + dependencies between C files. Note that this doesn't work for C++ files yet. * `cabal.configure.opts` refers to Cabal configure command line. Note that - package flags can be given by adding `--flags=...` arguments. + package flags can be given by adding `--flags=...` arguments. Also, for packages with `build-type: Configure`, you can pass additional arguments to the `configure` script like this: `stage1.rts.cabal.configure.opts+=--configure-option=--enable-asserts-all-ways` * `hsc2hs.run.opts` allows passing options to `Hsc2Hs` invocations. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2aaea8a1f135bda24604bd9ae3bf5ac2fd03133a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2aaea8a1f135bda24604bd9ae3bf5ac2fd03133a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 10:05:52 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Tue, 04 Jun 2024 06:05:52 -0400 Subject: [Git][ghc/ghc][wip/rip-dead-adjustor] 27 commits: Bump max LLVM version to 19 (not inclusive) Message-ID: <665ee700152be_27a83512a19d41332f7@gitlab.mail> Cheng Shao pushed to branch wip/rip-dead-adjustor at Glasgow Haskell Compiler / GHC Commits: ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 41db0122 by Cheng Shao at 2024-06-04T10:05:31+00:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 30 changed files: - .gitlab-ci.yml - compiler/GHC.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - + compiler/GHC/Data/OsPath.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Config/Finder.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Pipeline/Execute.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9eed5b08f2ca8fff4a8e597a06571b07fd25e7a1...41db0122547f12fea143ea312c57763e2f44d66f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9eed5b08f2ca8fff4a8e597a06571b07fd25e7a1...41db0122547f12fea143ea312c57763e2f44d66f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 11:09:02 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Jun 2024 07:09:02 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 14 commits: Parser: Remove unused `apats` rule Message-ID: <665ef5ce4e1a4_27a8351aa32e0155872@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 07e3ab5a by Alex Mason at 2024-06-04T07:08:53-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 580c27a7 by Cheng Shao at 2024-06-04T07:08:54-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 789846b4 by Cheng Shao at 2024-06-04T07:08:54-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - 30 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Foreign/Decl.hs - compiler/GHC/HsToCore/Foreign/JavaScript.hs - compiler/GHC/HsToCore/Foreign/Wasm.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Check.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/28de59e030d258f55f6aa93bae6672605a9df144...789846b41e08c4d65affc9422205c6b38941ffb1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/28de59e030d258f55f6aa93bae6672605a9df144...789846b41e08c4d65affc9422205c6b38941ffb1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 12:48:02 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Tue, 04 Jun 2024 08:48:02 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/rip-32bit-apple Message-ID: <665f0d02a77b6_27a835287fc2418057@gitlab.mail> Cheng Shao pushed new branch wip/rip-32bit-apple at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/rip-32bit-apple You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 12:55:48 2024 From: gitlab at gitlab.haskell.org (Jaro Reinders (@jaro)) Date: Tue, 04 Jun 2024 08:55:48 -0400 Subject: [Git][ghc/ghc][wip/T24880] Replace fold/build by stream fusion WIP Message-ID: <665f0ed41ff00_27a8352a21b90184388@gitlab.mail> Jaro Reinders pushed to branch wip/T24880 at Glasgow Haskell Compiler / GHC Commits: 3e0b4233 by Jaro Reinders at 2024-06-04T14:55:12+02:00 Replace fold/build by stream fusion WIP - - - - - 10 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/HsToCore/ListComp.hs - libraries/ghc-internal/src/GHC/Internal/Base.hs - libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs - libraries/ghc-internal/src/GHC/Internal/List.hs - libraries/ghc-internal/src/GHC/Internal/System/Posix/Internals.hs Changes: ===================================== compiler/GHC/Builtin/Names.hs ===================================== @@ -356,6 +356,7 @@ basicKnownKeyNames -- List operations concatName, filterName, mapName, zipName, foldrName, buildName, augmentName, appendName, + concatMapName, -- FFI primitive types that are not wired-in. stablePtrTyConName, ptrTyConName, funPtrTyConName, constPtrConName, @@ -746,13 +747,14 @@ map_RDR, append_RDR :: RdrName map_RDR = nameRdrName mapName append_RDR = nameRdrName appendName -foldr_RDR, build_RDR, returnM_RDR, bindM_RDR, failM_RDR +foldr_RDR, build_RDR, returnM_RDR, bindM_RDR, failM_RDR, concatMap_RDR :: RdrName foldr_RDR = nameRdrName foldrName build_RDR = nameRdrName buildName returnM_RDR = nameRdrName returnMName bindM_RDR = nameRdrName bindMName failM_RDR = nameRdrName failMName +concatMap_RDR = nameRdrName concatMapName left_RDR, right_RDR :: RdrName left_RDR = nameRdrName leftDataConName @@ -1123,7 +1125,7 @@ considerAccessibleName = varQual gHC_INTERNAL_EXTS (fsLit "considerAccessible") -- Random GHC.Internal.Base functions fromStringName, otherwiseIdName, foldrName, buildName, augmentName, - mapName, appendName, assertName, + mapName, concatMapName, appendName, assertName, dollarName :: Name dollarName = varQual gHC_INTERNAL_BASE (fsLit "$") dollarIdKey otherwiseIdName = varQual gHC_INTERNAL_BASE (fsLit "otherwise") otherwiseIdKey @@ -1131,6 +1133,7 @@ foldrName = varQual gHC_INTERNAL_BASE (fsLit "foldr") foldrIdKey buildName = varQual gHC_INTERNAL_BASE (fsLit "build") buildIdKey augmentName = varQual gHC_INTERNAL_BASE (fsLit "augment") augmentIdKey mapName = varQual gHC_INTERNAL_BASE (fsLit "map") mapIdKey +concatMapName = varQual gHC_INTERNAL_BASE (fsLit "concatMap") concatMapIdKey appendName = varQual gHC_INTERNAL_BASE (fsLit "++") appendIdKey assertName = varQual gHC_INTERNAL_BASE (fsLit "assert") assertIdKey fromStringName = varQual gHC_INTERNAL_DATA_STRING (fsLit "fromString") fromStringClassOpKey @@ -2376,6 +2379,9 @@ leftSectionKey, rightSectionKey :: Unique leftSectionKey = mkPreludeMiscIdUnique 45 rightSectionKey = mkPreludeMiscIdUnique 46 +concatMapIdKey :: Unique +concatMapIdKey = mkPreludeMiscIdUnique 47 + rootMainKey, runMainKey :: Unique rootMainKey = mkPreludeMiscIdUnique 101 runMainKey = mkPreludeMiscIdUnique 102 ===================================== compiler/GHC/Core/Make.hs ===================================== @@ -37,7 +37,7 @@ module GHC.Core.Make ( -- * Constructing list expressions mkNilExpr, mkConsExpr, mkListExpr, - mkFoldrExpr, mkBuildExpr, + mkFoldrExpr, mkBuildExpr, mkConcatMapExpr, -- * Constructing Maybe expressions mkNothingExpr, mkJustExpr, @@ -796,6 +796,11 @@ mkFoldrExpr elt_ty result_ty c n list = do `App` n `App` list) +mkConcatMapExpr :: MonadThings m => Type -> Type -> CoreExpr -> CoreExpr -> m CoreExpr +mkConcatMapExpr src_ty tgt_ty f xs = do + concatMap_id <- lookupId concatMapName + return (Var concatMap_id `App` Type src_ty `App` Type tgt_ty `App` f `App` xs) + -- | Make a 'build' expression applied to a locally-bound worker function mkBuildExpr :: (MonadFail m, MonadThings m, MonadUnique m) => Type -- ^ Type of list elements to be built ===================================== compiler/GHC/Core/Rules.hs ===================================== @@ -56,7 +56,7 @@ import GHC.Core.Ppr ( pprRules ) import GHC.Core.Unify as Unify ( ruleMatchTyKiX ) import GHC.Core.Type as Type ( Type, extendTvSubst, extendCvSubst - , substTy, getTyVar_maybe ) + , substTy, getTyVar_maybe, tyCoVarsOfType ) import GHC.Core.TyCo.Ppr( pprParendType ) import GHC.Core.Coercion as Coercion import GHC.Core.Tidy ( tidyRules ) @@ -696,12 +696,16 @@ matchRule opts rule_env _is_active fn args _rough_args Nothing -> Nothing Just expr -> Just expr -matchRule _ rule_env is_active _ args rough_args +matchRule _ rule_env is_active _fn args rough_args (Rule { ru_name = rule_name, ru_act = act, ru_rough = tpl_tops , ru_bndrs = tpl_vars, ru_args = tpl_args, ru_rhs = rhs }) | not (is_active act) = Nothing | ruleCantMatch tpl_tops rough_args = Nothing - | otherwise = matchN rule_env rule_name tpl_vars tpl_args args rhs + | otherwise = + case matchN rule_env rule_name tpl_vars tpl_args args rhs of + Just x -> -- pprTrace "match found:" (ppr rule_name <+> ppr _fn <+> ppr args) True + Just x + Nothing -> Nothing --------------------------------------- @@ -1046,9 +1050,9 @@ tryFloatIn :: CoreExpr -> Maybe CoreExpr tryFloatIn = go emptyVarSet False id where go vs _ c (Let bind e) = go (extendVarSetList vs (bindersOf bind)) True (c . Let bind) e go vs _ c (Case scrut case_bndr ty [Alt con alt_bndrs rhs]) = go (extendVarSetList vs alt_bndrs) True (c . (\x -> Case scrut case_bndr (exprType x) [Alt con alt_bndrs x])) rhs - go vs True c (App e1 e2) = App <$> go vs True c e1 <*> pure (c e2) - go vs True c e@(Var v) | not (v `elemVarSet` vs) = Just e - go vs True _ e at Type{} = Just e + go vs True c (App e1 e2) = App <$> go vs True c e1 <*> Just (c e2) + go vs True _ e@(Var v) | not (v `elemVarSet` vs) = Just e + go vs True _ e@(Type ty) | isEmptyVarSet (tyCoVarsOfType ty `intersectVarSet` vs) = Just e go vs True _ e at Lit{} = Just e go _ _ _ _ = Nothing ===================================== compiler/GHC/HsToCore/ListComp.hs ===================================== @@ -61,7 +61,7 @@ dsListComp lquals res_ty = do || isParallelComp quals -- Foldr-style desugaring can't handle parallel list comprehensions then deListComp quals (mkNilExpr elt_ty) - else mkBuildExpr elt_ty (\(c, _) (n, _) -> dfListComp c n quals) + else dfListComp elt_ty quals -- Foldr/build should be enabled, so desugar -- into foldrs and builds @@ -305,78 +305,73 @@ deBindComp pat core_list1 quals core_list2 = do @dfListComp@ are the rules used with foldr/build turned on: \begin{verbatim} -TE[ e | ] c n = c e n -TE[ e | b , q ] c n = if b then TE[ e | q ] c n else n -TE[ e | p <- l , q ] c n = let - f = \ x b -> case x of - p -> TE[ e | q ] c b - _ -> b - in - foldr f n l +TE[ e | ] = [e] +TE[ e | b , q ] = if b then TE[ e | q ] else [] +TE[ e | p <- l , q ] = concatMap (\x -> case x of + p -> TE[ e | q ] + _ -> []) l \end{verbatim} -} -dfListComp :: Id -> Id -- 'c' and 'n' +dfListComp :: Type -- element type -> [ExprStmt GhcTc] -- the rest of the qual's -> DsM CoreExpr -dfListComp _ _ [] = panic "dfListComp" +dfListComp _ [] = panic "dfListComp" -dfListComp c_id n_id (LastStmt _ body _ _ : quals) +dfListComp elt_ty (LastStmt _ body _ _ : quals) = assert (null quals) $ do { core_body <- dsLExpr body - ; return (mkApps (Var c_id) [core_body, Var n_id]) } + ; return (mkListExpr elt_ty [core_body]) } -- Non-last: must be a guard -dfListComp c_id n_id (BodyStmt _ guard _ _ : quals) = do +dfListComp elt_ty (BodyStmt _ guard _ _ : quals) = do core_guard <- dsLExpr guard - core_rest <- dfListComp c_id n_id quals - return (mkIfThenElse core_guard core_rest (Var n_id)) + core_rest <- dfListComp elt_ty quals + return (mkIfThenElse core_guard core_rest (mkListExpr elt_ty [])) -dfListComp c_id n_id (LetStmt _ binds : quals) = do +dfListComp elt_ty (LetStmt _ binds : quals) = do -- new in 1.3, local bindings - core_rest <- dfListComp c_id n_id quals + core_rest <- dfListComp elt_ty quals dsLocalBinds binds core_rest -dfListComp c_id n_id (stmt@(TransStmt {}) : quals) = do +dfListComp elt_ty (stmt@(TransStmt {}) : quals) = do (inner_list_expr, pat) <- dsTransStmt stmt -- Anyway, we bind the newly grouped list via the generic binding function - dfBindComp c_id n_id (pat, inner_list_expr) quals + dfBindComp elt_ty (pat, inner_list_expr) quals -dfListComp c_id n_id (BindStmt _ pat list1 : quals) = do +dfListComp elt_ty (BindStmt _ pat list1 : quals) = do -- evaluate the two lists core_list1 <- dsLExpr list1 -- Do the rest of the work in the generic binding builder - dfBindComp c_id n_id (pat, core_list1) quals + dfBindComp elt_ty (pat, core_list1) quals -dfListComp _ _ (ParStmt {} : _) = panic "dfListComp ParStmt" -dfListComp _ _ (RecStmt {} : _) = panic "dfListComp RecStmt" -dfListComp _ _ (XStmtLR ApplicativeStmt {} : _) = +dfListComp _ (ParStmt {} : _) = panic "dfListComp ParStmt" +dfListComp _ (RecStmt {} : _) = panic "dfListComp RecStmt" +dfListComp _ (XStmtLR ApplicativeStmt {} : _) = panic "dfListComp ApplicativeStmt" -dfBindComp :: Id -> Id -- 'c' and 'n' +dfBindComp :: Type -- element type -> (LPat GhcTc, CoreExpr) -> [ExprStmt GhcTc] -- the rest of the qual's -> DsM CoreExpr -dfBindComp c_id n_id (pat, core_list1) quals = do +dfBindComp elt_ty (pat, core_list1) quals = do -- find the required type let x_ty = hsLPatType pat - let b_ty = idType n_id -- create some new local id's - b <- newSysLocalDs ManyTy b_ty x <- newSysLocalDs ManyTy x_ty -- build rest of the comprehension - core_rest <- dfListComp c_id b quals + core_rest <- dfListComp elt_ty quals -- build the pattern match core_expr <- matchSimply (Var x) (StmtCtxt (HsDoStmt ListComp)) ManyTy - pat core_rest (Var b) + pat core_rest (mkListExpr elt_ty []) -- now build the outermost foldr, and return - mkFoldrExpr x_ty b_ty (mkLams [x, b] core_expr) (Var n_id) core_list1 + mkConcatMapExpr x_ty elt_ty (mkLams [x] core_expr) core_list1 {- ************************************************************************ ===================================== libraries/ghc-internal/src/GHC/Internal/Base.hs ===================================== @@ -346,6 +346,229 @@ infixl 4 <*>, <*, *>, <**> default () -- Double isn't available yet +data Stream a = forall s. Stream (s -> Step s a) !s +data Step s a = Yield a !s | Skip !s | Done + +unstream :: Stream a -> [a] +unstream (Stream next s0) = go s0 where + go !s = case next s of + Yield x s' -> x : go s' + Skip s' -> go s' + Done -> [] +{-# INLINE [1] unstream #-} + +-- This changes an unstream into a cheapUnstream, which means GHC will be free +-- to duplicate the list producing stream. +cheap :: [a] -> [a] +cheap x = x +{-# INLINE [1] cheap #-} + +{-# RULES "cheap/unstream" forall x. cheap (unstream x) = cheapUnstream x #-} + +cheapUnstream :: Stream a -> [a] +cheapUnstream (Stream next s0) = go s0 where + go !s = case next s of + Yield x s' -> x : go s' + Skip s' -> go s' + Done -> [] +{-# INLINE CONLIKE [1] cheapUnstream #-} + +data Lazy a = L a + +streamNext :: Lazy [a] -> Step (Lazy [a]) a +streamNext (L []) = Done +streamNext (L (x:xs)) = Yield x (L xs) + +stream :: [a] -> Stream a +stream = Stream streamNext . L where +{-# INLINE [1] stream #-} + +{-# RULES +"unstream/stream" forall xs. unstream (stream xs) = xs +"cheapUnstream/stream" forall xs. cheapUnstream (stream xs) = xs +"stream/unstream" forall xs. stream (unstream xs) = xs +"stream/cheapUnstream" forall xs. stream (cheapUnstream xs) = xs +"stream/build" forall (f :: forall b. (a -> b -> b) -> b -> b). + stream (build f) = Stream streamNext (L (f (:) [])) + #-} + +data AppendState s1 s2 = AS1 !s1 | AS2 !s2 + +appendS :: Stream a -> Stream a -> Stream a +appendS (Stream next1 s01) (Stream next2 s02) = Stream next' (AS1 s01) where + next' (AS1 s1) = + case next1 s1 of + Yield x s1' -> Yield x (AS1 s1') + Skip s1' -> Skip (AS1 s1') + Done -> Skip (AS2 s02) + next' (AS2 s2) = + case next2 s2 of + Yield x s2' -> Yield x (AS2 s2') + Skip s2' -> Skip (AS2 s2') + Done -> Done + {-# INLINE next' #-} +{-# INLINE appendS #-} + +append1S :: Stream a -> [a] -> [a] +append1S (Stream next s0) xs = go s0 where + go !s = + case next s of + Yield x s' -> x : go s' + Skip s' -> go s' + Done -> xs +{-# INLINE [0] append1S #-} + +(++) :: [a] -> [a] -> [a] +(++) [] ys = ys +(++) (x:xs) ys = x : xs ++ ys +{-# NOINLINE [1] (++) #-} + +-- NOTE: This is quite subtle as we do not want to copy the last list in +-- +-- xs1 ++ xs2 ++ ... ++ xsn +-- +-- Indeed, we don't really want to fuse the above at all unless at least +-- one of the arguments has the form (unstream s) or the result of the +-- concatenation is streamed. The rules below do precisely that. Note they +-- really fuse instead of just rewriting things into a fusible form so there +-- is no need to rewrite back. + +{-# RULES +"++ -> fused on 1st arg" [~1] forall xs ys. + unstream xs ++ ys = append1S xs ys +"++ -> fused on 2nd arg" [~1] forall xs ys. + append1S xs (unstream ys) = unstream (appendS xs ys) +"++ -> fused (1)" [~1] forall xs ys. + stream (xs ++ ys) = appendS (stream xs) (stream ys) +"++ -> fused (2)" [~1] forall xs ys. + stream (append1S xs ys) = appendS xs (stream ys) + +"++ -> 1st arg empty" forall xs. + [] ++ xs = xs +"++ -> 2nd arg empty" forall xs. + xs ++ [] = xs +"++ / :" forall x xs ys. + (x:xs) ++ ys = x : (xs ++ ys) + #-} + +foldrS :: (a -> b -> b) -> b -> Stream a -> b +foldrS k z (Stream next s0) = go s0 where + go !s = + case next s of + Yield x s' -> k x (go s') + Skip s' -> go s' + Done -> z +{-# INLINE foldrS #-} + +foldr :: (a -> b -> b) -> b -> [a] -> b +foldr k z = foldrS k z . stream +{-# INLINE foldr #-} + +mapS :: (a -> b) -> Stream a -> Stream b +mapS f (Stream next s0) = Stream next' s0 where + next' !s = + case next s of + Yield x s' -> Yield (f x) s' + Skip s' -> Skip s' + Done -> Done + {-# INLINE next' #-} +{-# INLINE mapS #-} + +map :: (a -> b) -> [a] -> [b] +map f = unstream . mapS f . stream +{-# INLINE map #-} + +data ConcatMapState s a = ConcatMapState1 !s | forall is. ConcatMapState2 !s (is -> Step is a) !is + +concatMapS :: (a -> Stream b) -> Stream a -> Stream b +concatMapS f (Stream next s0) = Stream next' (ConcatMapState1 s0) + where + {-# INLINE next' #-} + next' (ConcatMapState1 s) = case next s of + Done -> Done + Skip s' -> Skip (ConcatMapState1 s') + Yield x s' -> + case f x of + Stream inext is0 -> Skip (ConcatMapState2 s' inext is0) + + next' (ConcatMapState2 s inext is) = case inext is of + Done -> Skip (ConcatMapState1 s) + Skip is' -> Skip (ConcatMapState2 s inext is') + Yield x is' -> Yield x (ConcatMapState2 s inext is') +{-# INLINE [0] concatMapS #-} + +-- {-# RULES +-- "concatMapS/singleton" forall f. concatMapS (\x -> stream [f x]) = mapS f +-- #-} + +data ConcatMap'State s1 a s2 = CM'S1 !s1 | CM'S2 !s1 a !s2 + +concatMapS' :: (a -> s -> Step s b) -> (a -> s) -> Stream a -> Stream b +concatMapS' next2 f (Stream next1 s0) = Stream next' (CM'S1 s0) + where + {-# INLINE next' #-} + next' (CM'S1 s) = case next1 s of + Done -> Done + Skip s' -> Skip (CM'S1 s') + Yield x s' -> Skip (CM'S2 s' x (f x)) + + next' (CM'S2 s a t) = case next2 a t of + Done -> Skip (CM'S1 s) + Skip t' -> Skip (CM'S2 s a t') + Yield x t' -> Yield x (CM'S2 s a t') +{-# INLINE concatMapS' #-} + +-- data ConcatMap''State s1 a s2 = CM''S1 !s1 | CM''S2 !s1 !s2 +-- +-- concatMapS'' :: (s -> Step s b) -> (a -> s) -> Stream a -> Stream b +-- concatMapS'' next2 f (Stream next1 s0) = Stream next (CM''S1 s0) +-- where +-- {-# INLINE next #-} +-- next (CM''S1 s) = case next1 s of +-- Done -> Done +-- Skip s' -> Skip (CM''S1 s') +-- Yield x s' -> Skip (CM''S2 s' (f x)) +-- +-- next (CM''S2 s t) = case next2 t of +-- Done -> Skip (CM''S1 s) +-- Skip t' -> Skip (CM''S2 s t') +-- Yield x t' -> Yield x (CM''S2 s t') +-- {-# INLINE concatMapS'' #-} + +-- {-# RULES +-- "concatMap" forall step f. concatMapS (\x -> Stream (step x) (f x)) = concatMapS' step f +-- #-} + +-- Shouldn't be necessary, because stream gets inlined anyway in phase 1 +-- "concatMap/stream" [1] forall f. concatMapS (\x -> stream (f x)) = concatMapS' (\_ -> streamStep) f + +-- | Map a function returning a list over a list and concatenate the results. +-- 'concatMap' can be seen as the composition of 'concat' and 'map'. +-- +-- > concatMap f xs == (concat . map f) xs +-- +-- ==== __Examples__ +-- +-- >>> concatMap (\i -> [-i,i]) [] +-- [] +-- +-- >>> concatMap (\i -> [-i, i]) [1, 2, 3] +-- [-1,1,-2,2,-3,3] +-- +-- >>> concatMap ('replicate' 3) [0, 2, 4] +-- [0,0,0,2,2,2,4,4,4] +concatMap :: (a -> [b]) -> [a] -> [b] +concatMap f = foldr ((++) . f) [] + +{-# NOINLINE [1] concatMap #-} + +{-# RULES +"concatMap" forall f . concatMap f = unstream . concatMapS (stream . f) . stream +-- "concatMap" forall f xs . concatMap f xs = +-- build (\c n -> foldr (\x b -> foldr c b (f x)) n xs) + #-} + + {- Note [Tracking dependencies on primitives] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1780,17 +2003,17 @@ The rest of the prelude list functions are in GHC.List. -- -- > foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...) -foldr :: (a -> b -> b) -> b -> [a] -> b --- foldr _ z [] = z --- foldr f z (x:xs) = f x (foldr f z xs) -{-# INLINE [0] foldr #-} --- Inline only in the final stage, after the foldr/cons rule has had a chance --- Also note that we inline it when it has *two* parameters, which are the --- ones we are keen about specialising! -foldr k z = go - where - go [] = z - go (y:ys) = y `k` go ys +-- foldr :: (a -> b -> b) -> b -> [a] -> b +-- -- foldr _ z [] = z +-- -- foldr f z (x:xs) = f x (foldr f z xs) +-- {-# INLINE [0] foldr #-} +-- -- Inline only in the final stage, after the foldr/cons rule has had a chance +-- -- Also note that we inline it when it has *two* parameters, which are the +-- -- ones we are keen about specialising! +-- foldr k z = go +-- where +-- go [] = z +-- go (y:ys) = y `k` go ys -- | A list producer that can be fused with 'foldr'. -- This function is merely @@ -1825,38 +2048,38 @@ augment :: forall a. (forall b. (a->b->b) -> b -> b) -> [a] -> [a] {-# INLINE [1] augment #-} augment g xs = g (:) xs -{-# RULES -"fold/build" forall k z (g::forall b. (a->b->b) -> b -> b) . - foldr k z (build g) = g k z - -"foldr/augment" forall k z xs (g::forall b. (a->b->b) -> b -> b) . - foldr k z (augment g xs) = g k (foldr k z xs) - -"foldr/id" foldr (:) [] = \x -> x -"foldr/app" [1] forall ys. foldr (:) ys = \xs -> xs ++ ys - -- Only activate this from phase 1, because that's - -- when we disable the rule that expands (++) into foldr - --- The foldr/cons rule looks nice, but it can give disastrously --- bloated code when compiling --- array (a,b) [(1,2), (2,2), (3,2), ...very long list... ] --- i.e. when there are very very long literal lists --- So I've disabled it for now. We could have special cases --- for short lists, I suppose. --- "foldr/cons" forall k z x xs. foldr k z (x:xs) = k x (foldr k z xs) - -"foldr/single" forall k z x. foldr k z [x] = k x z -"foldr/nil" forall k z. foldr k z [] = z - -"foldr/cons/build" forall k z x (g::forall b. (a->b->b) -> b -> b) . - foldr k z (x:build g) = k x (g k z) - -"augment/build" forall (g::forall b. (a->b->b) -> b -> b) - (h::forall b. (a->b->b) -> b -> b) . - augment g (build h) = build (\c n -> g c (h c n)) -"augment/nil" forall (g::forall b. (a->b->b) -> b -> b) . - augment g [] = build g - #-} +-- {-# RULES +-- "fold/build" forall k z (g::forall b. (a->b->b) -> b -> b) . +-- foldr k z (build g) = g k z +-- +-- "foldr/augment" forall k z xs (g::forall b. (a->b->b) -> b -> b) . +-- foldr k z (augment g xs) = g k (foldr k z xs) +-- +-- "foldr/id" foldr (:) [] = \x -> x +-- "foldr/app" [1] forall ys. foldr (:) ys = \xs -> xs ++ ys +-- -- Only activate this from phase 1, because that's +-- -- when we disable the rule that expands (++) into foldr +-- +-- -- The foldr/cons rule looks nice, but it can give disastrously +-- -- bloated code when compiling +-- -- array (a,b) [(1,2), (2,2), (3,2), ...very long list... ] +-- -- i.e. when there are very very long literal lists +-- -- So I've disabled it for now. We could have special cases +-- -- for short lists, I suppose. +-- -- "foldr/cons" forall k z x xs. foldr k z (x:xs) = k x (foldr k z xs) +-- +-- "foldr/single" forall k z x. foldr k z [x] = k x z +-- "foldr/nil" forall k z. foldr k z [] = z +-- +-- "foldr/cons/build" forall k z x (g::forall b. (a->b->b) -> b -> b) . +-- foldr k z (x:build g) = k x (g k z) +-- +-- "augment/build" forall (g::forall b. (a->b->b) -> b -> b) +-- (h::forall b. (a->b->b) -> b -> b) . +-- augment g (build h) = build (\c n -> g c (h c n)) +-- "augment/nil" forall (g::forall b. (a->b->b) -> b -> b) . +-- augment g [] = build g +-- #-} -- This rule is true, but not (I think) useful: -- augment g (augment h t) = augment (\cn -> g c (h c n)) t @@ -1883,13 +2106,13 @@ augment g xs = g (:) xs -- -- >>> map (\n -> 3 * n + 1) [1, 2, 3] -- [4,7,10] -map :: (a -> b) -> [a] -> [b] -{-# NOINLINE [0] map #-} - -- We want the RULEs "map" and "map/coerce" to fire first. - -- map is recursive, so won't inline anyway, - -- but saying so is more explicit, and silences warnings -map _ [] = [] -map f (x:xs) = f x : map f xs +-- map :: (a -> b) -> [a] -> [b] +-- {-# NOINLINE [0] map #-} +-- -- We want the RULEs "map" and "map/coerce" to fire first. +-- -- map is recursive, so won't inline anyway, +-- -- but saying so is more explicit, and silences warnings +-- map _ [] = [] +-- map f (x:xs) = f x : map f xs -- Note eta expanded mapFB :: (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst @@ -1931,12 +2154,12 @@ The rules for map work like this. * Any similarity to the Functor laws for [] is expected. -} -{-# RULES -"map" [~1] forall f xs. map f xs = build (\c n -> foldr (mapFB c f) n xs) -"mapList" [1] forall f. foldr (mapFB (:) f) [] = map f -"mapFB" forall c f g. mapFB (mapFB c f) g = mapFB c (f.g) -"mapFB/id" forall c. mapFB c (\x -> x) = c - #-} +-- {-# RULES +-- "map" [~1] forall f xs. map f xs = build (\c n -> foldr (mapFB c f) n xs) +-- "mapList" [1] forall f. foldr (mapFB (:) f) [] = map f +-- "mapFB" forall c f g. mapFB (mapFB c f) g = mapFB c (f.g) +-- "mapFB/id" forall c. mapFB c (\x -> x) = c +-- #-} -- See Breitner, Eisenberg, Peyton Jones, and Weirich, "Safe Zero-cost -- Coercions for Haskell", section 6.5: @@ -1976,21 +2199,21 @@ The rules for map work like this. -- -- >>> [3, 2, 1] ++ [] -- [3,2,1] -(++) :: [a] -> [a] -> [a] -{-# NOINLINE [2] (++) #-} - -- Give time for the RULEs for (++) to fire in InitialPhase - -- It's recursive, so won't inline anyway, - -- but saying so is more explicit -(++) [] ys = ys -(++) (x:xs) ys = x : xs ++ ys +-- (++) :: [a] -> [a] -> [a] +-- {-# NOINLINE [2] (++) #-} +-- -- Give time for the RULEs for (++) to fire in InitialPhase +-- -- It's recursive, so won't inline anyway, +-- -- but saying so is more explicit +-- (++) [] ys = ys +-- (++) (x:xs) ys = x : xs ++ ys -{-# RULES -"++/literal" forall x. (++) (unpackCString# x) = unpackAppendCString# x -"++/literal_utf8" forall x. (++) (unpackCStringUtf8# x) = unpackAppendCStringUtf8# x #-} - -{-# RULES -"++" [~1] forall xs ys. xs ++ ys = augment (\c n -> foldr c n xs) ys - #-} +-- {-# RULES +-- "++/literal" forall x. (++) (unpackCString# x) = unpackAppendCString# x +-- "++/literal_utf8" forall x. (++) (unpackCStringUtf8# x) = unpackAppendCStringUtf8# x #-} +-- +-- {-# RULES +-- "++" [~1] forall xs ys. xs ++ ys = augment (\c n -> foldr c n xs) ys +-- #-} -- |'otherwise' is defined as the value 'True'. It helps to make @@ -2512,20 +2735,20 @@ iShiftRL# :: Int# -> Int# -> Int# a `iShiftRL#` b = (a `uncheckedIShiftRL#` b) `andI#` shift_mask WORD_SIZE_IN_BITS# b -- Rules for C strings (the functions themselves are now in GHC.CString) -{-# RULES -"unpack" [~1] forall a . unpackCString# a = build (unpackFoldrCString# a) -"unpack-list" [1] forall a . unpackFoldrCString# a (:) [] = unpackCString# a -"unpack-append" forall a n . unpackFoldrCString# a (:) n = unpackAppendCString# a n -"unpack-append-nil" forall a . unpackAppendCString# a [] = unpackCString# a - -"unpack-utf8" [~1] forall a . unpackCStringUtf8# a = build (unpackFoldrCStringUtf8# a) -"unpack-list-utf8" [1] forall a . unpackFoldrCStringUtf8# a (:) [] = unpackCStringUtf8# a -"unpack-append-utf8" forall a n . unpackFoldrCStringUtf8# a (:) n = unpackAppendCStringUtf8# a n -"unpack-append-nil-utf8" forall a . unpackAppendCStringUtf8# a [] = unpackCStringUtf8# a - --- There's a built-in rule (in GHC.Core.Op.ConstantFold) for --- unpackFoldr "foo" c (unpackFoldr "baz" c n) = unpackFoldr "foobaz" c n - --- See also the Note [String literals in GHC] in CString.hs - - #-} +-- {-# RULES +-- "unpack" [~1] forall a . unpackCString# a = build (unpackFoldrCString# a) +-- "unpack-list" [1] forall a . unpackFoldrCString# a (:) [] = unpackCString# a +-- "unpack-append" forall a n . unpackFoldrCString# a (:) n = unpackAppendCString# a n +-- "unpack-append-nil" forall a . unpackAppendCString# a [] = unpackCString# a +-- +-- "unpack-utf8" [~1] forall a . unpackCStringUtf8# a = build (unpackFoldrCStringUtf8# a) +-- "unpack-list-utf8" [1] forall a . unpackFoldrCStringUtf8# a (:) [] = unpackCStringUtf8# a +-- "unpack-append-utf8" forall a n . unpackFoldrCStringUtf8# a (:) n = unpackAppendCStringUtf8# a n +-- "unpack-append-nil-utf8" forall a . unpackAppendCStringUtf8# a [] = unpackCStringUtf8# a +-- +-- -- There's a built-in rule (in GHC.Core.Op.ConstantFold) for +-- -- unpackFoldr "foo" c (unpackFoldr "baz" c n) = unpackFoldr "foobaz" c n +-- +-- -- See also the Note [String literals in GHC] in CString.hs +-- +-- #-} ===================================== libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs ===================================== @@ -64,7 +64,7 @@ import GHC.Internal.Arr ( Array(..), elems, numElements, foldlElems, foldrElems, foldlElems', foldrElems', foldl1Elems, foldr1Elems) -import GHC.Internal.Base hiding ( foldr ) +import GHC.Internal.Base hiding ( foldr , concatMap ) import GHC.Internal.Generics import GHC.Tuple (Solo (..)) import GHC.Internal.Num ( Num(..) ) ===================================== libraries/ghc-internal/src/GHC/Internal/Enum.hs ===================================== @@ -32,6 +32,7 @@ module GHC.Internal.Enum( ) where import GHC.Internal.Base hiding ( many ) +import GHC.Internal.List (eftInt) import GHC.Internal.Char import GHC.Num.Integer import GHC.Internal.Num @@ -610,15 +611,15 @@ instance Enum Int where * Phase 0: optionally inline eftInt -} -{-# NOINLINE [1] eftInt #-} -eftInt :: Int# -> Int# -> [Int] --- [x1..x2] -eftInt x0 y | isTrue# (x0 ># y) = [] - | otherwise = go x0 - where - go x = I# x : if isTrue# (x ==# y) - then [] - else go (x +# 1#) +-- {-# NOINLINE [1] eftInt #-} +-- eftInt :: Int# -> Int# -> [Int] +-- -- [x1..x2] +-- eftInt x0 y | isTrue# (x0 ># y) = [] +-- | otherwise = go x0 +-- where +-- go x = I# x : if isTrue# (x ==# y) +-- then [] +-- else go (x +# 1#) {-# INLINE [0] eftIntFB #-} -- See Note [Inline FB functions] in GHC.Internal.List eftIntFB :: (Int -> r -> r) -> r -> Int# -> Int# -> r ===================================== libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs ===================================== @@ -25,7 +25,7 @@ module GHC.Internal.IO.Handle.FD ( mkHandleFromFD, fdToHandle, fdToHandle', handleToFd ) where -import GHC.Internal.Base +import GHC.Internal.Base hiding (Stream) import GHC.Internal.Show import GHC.Internal.Control.Exception (try) import GHC.Internal.Data.Maybe ===================================== libraries/ghc-internal/src/GHC/Internal/List.hs ===================================== @@ -1,6 +1,6 @@ {-# LANGUAGE Trustworthy #-} -{-# LANGUAGE CPP, NoImplicitPrelude, ScopedTypeVariables #-} -{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE CPP, NoImplicitPrelude, ScopedTypeVariables, ExistentialQuantification #-} +{-# LANGUAGE BangPatterns, MagicHash #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} ----------------------------------------------------------------------------- @@ -41,6 +41,9 @@ module GHC.Internal.List ( -- * GHC List fusion augment, build, + -- * Enumeration + eftInt, + ) where import GHC.Internal.Data.Maybe @@ -52,6 +55,927 @@ import GHC.Internal.Stack.Types (HasCallStack) infixl 9 !?, !! infix 4 `elem`, `notElem` +data Tuple a b = !a :!: !b +data Option a = None | Some !a + +eftIntS :: Int# -> Int# -> Stream Int +eftIntS x y = Stream next (I# x) where + next !s + | s <= I# y = Yield s (s + 1) + | otherwise = Done + {-# INLINE next #-} +{-# INLINE eftIntS #-} + +eftInt :: Int# -> Int# -> [Int] +eftInt = \x y -> cheapUnstream (eftIntS x y) +{-# INLINE eftInt #-} + +-- unfoldrS :: (a -> Maybe (a, b)) -> a -> Stream b +-- unfoldrS f x0 = Stream next x0 where +-- next s = +-- case f s of +-- Just (s', x) -> Yield x s' +-- Nothing -> Done +-- {-# INLINE next #-} +-- {-# INLINE unfoldrS #-} + +data ZipState s1 a s2 + = ZipState1 !s1 !s2 + | ZipState2 !s1 a !s2 + +zipS :: Stream a -> Stream b -> Stream (a, b) +zipS (Stream next1 s01) (Stream next2 s02) = Stream next' (ZipState1 s01 s02) where + next' (ZipState1 s1 s2) = + case next1 s1 of + Yield x s1' -> + case next2 s2 of + Yield y s2' -> + Yield (x, y) (ZipState1 s1' s2') + Skip s2' -> Skip (ZipState2 s1' x s2') + Done -> Done + Skip s1' -> Skip (ZipState1 s1' s2) + Done -> Done + next' (ZipState2 s1' x s2) = + case next2 s2 of + Yield y s2' -> Yield (x, y) (ZipState1 s1' s2') + Skip s2' -> Skip (ZipState2 s1' x s2') + Done -> Done + {-# INLINE next' #-} +{-# INLINE zipS #-} + +data Zip3State s1 a s2 b s3 + = Zip3State1 !s1 !s2 !s3 + | Zip3State2 !s1 a !s2 !s3 + | Zip3State3 !s1 a !s2 b !s3 + +zip3S :: Stream a -> Stream b -> Stream c -> Stream (a, b, c) +zip3S (Stream next1 s01) (Stream next2 s02) (Stream next3 s03) = Stream next' (Zip3State1 s01 s02 s03) where + next' (Zip3State1 s1 s2 s3) = + case next1 s1 of + Yield x s1' -> + case next2 s2 of + Yield y s2' -> + case next3 s3 of + Yield z s3' -> Yield (x, y, z) (Zip3State1 s1' s2' s3') + Skip s3' -> Skip (Zip3State3 s1' x s2' y s3') + Done -> Done + Skip s2' -> Skip (Zip3State2 s1' x s2' s3) + Done -> Done + Skip s1' -> Skip (Zip3State1 s1' s2 s3) + Done -> Done + next' (Zip3State2 s1' x s2 s3) = + case next2 s2 of + Yield y s2' -> + case next3 s3 of + Yield z s3' -> Yield (x,y,z) (Zip3State1 s1' s2' s3') + Skip s3' -> Skip (Zip3State3 s1' x s2' y s3') + Done -> Done + Skip s2' -> Skip (Zip3State2 s1' x s2' s3) + Done -> Done + next' (Zip3State3 s1' x s2' y s3) = + case next3 s3 of + Yield z s3' -> Yield (x,y,z) (Zip3State1 s1' s2' s3') + Skip s3' -> Skip (Zip3State3 s1' x s2' y s3') + Done -> Done + {-# INLINE next' #-} +{-# INLINE zip3S #-} + +zipWithS :: (a -> b -> c) -> Stream a -> Stream b -> Stream c +zipWithS f (Stream next1 s01) (Stream next2 s02) = Stream next' (ZipState1 s01 s02) where + next' (ZipState1 s1 s2) = + case next1 s1 of + Yield x s1' -> + case next2 s2 of + Yield y s2' -> + Yield (f x y) (ZipState1 s1' s2') + Skip s2' -> Skip (ZipState2 s1' x s2') + Done -> Done + Skip s1' -> Skip (ZipState1 s1' s2) + Done -> Done + next' (ZipState2 s1' x s2) = + case next2 s2 of + Yield y s2' -> Yield (f x y) (ZipState1 s1' s2') + Skip s2' -> Skip (ZipState2 s1' x s2') + Done -> Done + {-# INLINE next' #-} +{-# INLINE zipWithS #-} + +zipWith3S :: (a -> b -> c -> d) -> Stream a -> Stream b -> Stream c -> Stream d +zipWith3S f (Stream next1 s01) (Stream next2 s02) (Stream next3 s03) = Stream next' (Zip3State1 s01 s02 s03) where + next' (Zip3State1 s1 s2 s3) = + case next1 s1 of + Yield x s1' -> + case next2 s2 of + Yield y s2' -> + case next3 s3 of + Yield z s3' -> Yield (f x y z) (Zip3State1 s1' s2' s3') + Skip s3' -> Skip (Zip3State3 s1' x s2' y s3') + Done -> Done + Skip s2' -> Skip (Zip3State2 s1' x s2' s3) + Done -> Done + Skip s1' -> Skip (Zip3State1 s1' s2 s3) + Done -> Done + next' (Zip3State2 s1' x s2 s3) = + case next2 s2 of + Yield y s2' -> + case next3 s3 of + Yield z s3' -> Yield (f x y z) (Zip3State1 s1' s2' s3') + Skip s3' -> Skip (Zip3State3 s1' x s2' y s3') + Done -> Done + Skip s2' -> Skip (Zip3State2 s1' x s2' s3) + Done -> Done + next' (Zip3State3 s1' x s2' y s3) = + case next3 s3 of + Yield z s3' -> Yield (f x y z) (Zip3State1 s1' s2' s3') + Skip s3' -> Skip (Zip3State3 s1' x s2' y s3') + Done -> Done + {-# INLINE next' #-} +{-# INLINE zipWith3S #-} + +-- unzipS :: Stream (a, b) -> (Stream a, Stream b) +-- unzipS s = (mapS fst s, mapS snd s) +-- {-# INLINE unzipS #-} + +unzipS :: Stream (a, b) -> ([a], [b]) +unzipS (Stream next s0) = go s0 where + go s = + case next s of + Yield (x, y) s' -> let (xs, ys) = go s' in (x:xs, y:ys) + Skip s' -> go s' + Done -> ([], []) +{-# INLINE unzipS #-} + +-- unzip3S :: Stream (a, b, c) -> (Stream a, Stream b, Stream c) +-- unzip3S s = (mapS (\(x,_,_) -> x) s, mapS (\(_,x,_) -> x) s, mapS (\(_,_,x) -> x) s) +-- {-# INLINE unzip3S #-} + +unzip3S :: Stream (a, b, c) -> ([a], [b], [c]) +unzip3S (Stream next s0) = go s0 where + go !s = + case next s of + Yield (x, y, z) s' -> let (xs, ys, zs) = go s' in (x:xs, y:ys, z:zs) + Skip s' -> go s' + Done -> ([], [], []) +{-# INLINE unzip3S #-} + +foldrS' :: (a -> b -> b) -> b -> Stream a -> b +foldrS' k z (Stream next s0) = go s0 where + go !s = + case next s of + Yield x s' -> k x $! go s' + Skip s' -> go s' + Done -> z +{-# INLINE foldrS' #-} + +foldr1S :: (a -> a -> a) -> Stream a -> a +foldr1S f (Stream next s0) = go1 s0 where + go1 !s = + case next s of + Yield x s' -> go2 x s' + Skip s' -> go1 s' + Done -> errorEmptyList "foldr1" + go2 x !s = + case next s of + Yield y s' -> f x (go2 y s') + Skip s' -> go2 x s' + Done -> x +{-# INLINE foldr1S #-} + +nullS :: Stream a -> Bool +nullS (Stream next s0) = go s0 where + go !s = + case next s of + Yield{} -> False + Skip s' -> go s' + Done -> True +{-# INLINE nullS #-} + +lengthS :: Stream a -> Int +lengthS (Stream next s0) = go 0 s0 where + go !n !s = + case next s of + Yield _ s' -> go (n + 1) s' + Skip s' -> go n s' + Done -> n +{-# INLINE lengthS #-} + +elemS :: Eq a => a -> Stream a -> Bool +elemS x0 (Stream next s0) = go s0 where + go s = + case next s of + Yield x s' -> x == x0 || go s' + Skip s' -> go s' + Done -> False +{-# INLINE elemS #-} + +notElemS :: Eq a => a -> Stream a -> Bool +notElemS x0 (Stream next s0) = go s0 where + go s = + case next s of + Yield x s' -> x /= x0 && go s' + Skip s' -> go s' + Done -> True +{-# INLINE notElemS #-} + +maximumS :: Ord a => Stream a -> a +maximumS (Stream next s0) = go1 s0 where + go1 !s = + case next s of + Yield x s' -> go2 x s' + Skip s' -> go1 s' + Done -> errorEmptyList "maximum" + go2 x !s = + case next s of + Yield y s' + | y > x -> go2 y s' + | otherwise -> go2 x s' + Skip s' -> go2 x s' + Done -> x +{-# INLINE maximumS #-} + +minimumS :: Ord a => Stream a -> a +minimumS (Stream next s0) = go1 s0 where + go1 !s = + case next s of + Yield x s' -> go2 x s' + Skip s' -> go1 s' + Done -> errorEmptyList "minimum" + go2 x !s = + case next s of + Yield y s' + | y < x -> go2 y s' + | otherwise -> go2 x s' + Skip s' -> go2 x s' + Done -> x +{-# INLINE minimumS #-} + +takeS :: Int -> Stream a -> Stream a +takeS n (Stream next s0) = Stream next' (s0 :!: n) where + next' (_ :!: 0) = Done + next' (s :!: i) = + case next s of + Yield x s' -> Yield x (s' :!: (i - 1)) + Skip s' -> Skip (s' :!: i) + Done -> Done + {-# INLINE next' #-} +{-# INLINE takeS #-} + +-- dropS :: Int -> Stream a -> Stream a +-- dropS n (Stream next s0) = Stream next (f n s0) where +-- f i s +-- | i <= 0 = s +-- | otherwise = +-- case next s of +-- Yield _ s' -> f (i - 1) s' +-- Skip s' -> f i s' +-- Done -> s +-- {-# INLINE dropS #-} + +dropS :: Int -> Stream a -> Stream a +dropS n (Stream next s0) = Stream next' (n :!: s0) where + next' (i :!: s) + | i > 0 = + case next s of + Yield _ s' -> Skip ((i - 1) :!: s') + Skip s' -> Skip (i :!: s') + Done -> Done + | otherwise = + case next s of + Yield x s' -> Yield x (i :!: s') + Skip s' -> Skip (i :!: s') + Done -> Done + {-# INLINE next' #-} +{-# INLINE dropS #-} + +cheapSplitAtS :: Int -> Stream a -> ([a], [a]) +cheapSplitAtS n s = (cheapUnstream (takeS n s), cheapUnstream (dropS n s)) +{-# INLINE cheapSplitAtS #-} + +splitAtS :: Int -> Stream a -> ([a], [a]) +splitAtS n (Stream next s0) = go1 n s0 where + go1 !i !s + | i > 0 = + case next s of + Yield x s' -> let (xs,ys) = go1 (i - 1) s' in (x : xs, ys) + Skip s' -> go1 i s' + Done -> ([], []) + | otherwise = ([], go2 s) + go2 !s = + case next s of + Yield x s' -> x : go2 s' + Skip s' -> go2 s' + Done -> [] +{-# INLINE splitAtS #-} + +takeWhileS :: (a -> Bool) -> Stream a -> Stream a +takeWhileS p (Stream next s0) = Stream next' s0 where + next' !s = + case next s of + Yield x s' + | p x -> Yield x s' + | otherwise -> Done + Skip s' -> Skip s' + Done -> Done +{-# INLINE takeWhileS #-} + +dropWhileS :: (a -> Bool) -> Stream a -> Stream a +dropWhileS p (Stream next s0) = Stream next' (True :!: s0) where + next' (True :!: s) = + case next s of + Yield x s' + | p x -> Skip (True :!: s') + | otherwise -> Yield x (False :!: s') + Skip s' -> Skip (True :!: s') + Done -> Done + next' (False :!: s) = + case next s of + Yield x s' -> Yield x (False :!: s') + Skip s' -> Skip (False :!: s') + Done -> Done + {-# INLINE next' #-} +{-# INLINE dropWhileS #-} + +-- nubS :: Eq a => Stream a -> Stream a +-- nubS (Stream next s0) = Stream next' ([] :!: s0) where +-- next' (xs :!: s) = +-- case next s of +-- Yield x s' +-- | x `elem` xs -> Skip (xs :!: s') +-- | otherwise -> Yield x ((x : xs) :!: s') +-- Skip s' -> Skip (xs :!: s') +-- Done -> Done +-- {-# INLINE next' #-} +-- {-# INLINE nubS #-} + +-- spanS :: (a -> Bool) -> Stream a -> (Stream a, Stream a) +-- spanS f s = (takeWhileS f s, dropWhileS f s) +-- {-# INLINE spanS #-} + +spanS :: (a -> Bool) -> Stream a -> ([a], [a]) +spanS p (Stream next s0) = go1 s0 where + go1 !s = + case next s of + Yield x s' + | p x -> let (xs, ys) = go1 s' in (x : xs, ys) + | otherwise -> ([], x : go2 s') + Skip s' -> go1 s' + Done -> ([],[]) + go2 !s = + case next s of + Yield x s' -> x : go2 s' + Skip s' -> go2 s' + Done -> [] +{-# INLINE spanS #-} + +breakS :: (a -> Bool) -> Stream a -> ([a], [a]) +breakS f = spanS (not . f) +{-# INLINE breakS #-} + +reverseS :: Stream a -> [a] +reverseS = foldlS' (flip (:)) [] +{-# INLINE reverseS #-} + +foldlS :: (b -> a -> b) -> b -> Stream a -> b +foldlS k z (Stream next s0) = go z s0 where + go acc !s = + case next s of + Yield x s' -> go (k acc x) s' + Skip s' -> go acc s' + Done -> acc +{-# INLINE foldlS #-} + +foldlS' :: (b -> a -> b) -> b -> Stream a -> b +foldlS' k z (Stream next s0) = go z s0 where + go !acc !s = + case next s of + Yield x s' -> go (k acc x) s' + Skip s' -> go acc s' + Done -> acc +{-# INLINE foldlS' #-} + +foldl1S :: (a -> a -> a) -> Stream a -> a +foldl1S f (Stream next s0) = go1 s0 where + go1 !s = + case next s of + Yield x s' -> go2 x s' + Skip s' -> go1 s' + Done -> errorEmptyList "foldl1" + go2 acc !s = + case next s of + Yield x s' -> go2 (f acc x) s' + Skip s' -> go2 acc s' + Done -> acc +{-# INLINE foldl1S #-} + +-- consumer +sumS :: Num a => Stream a -> a +sumS (Stream next s0) = go 0 s0 where + go !acc !s = case next s of + Done -> acc + Skip s' -> go acc s' + Yield x s' -> go (acc + x) s' +{-# INLINE sumS #-} + +productS :: Num a => Stream a -> a +productS (Stream next s0) = go 1 s0 where + go !acc !s = case next s of + Done -> acc + Skip s' -> go acc s' + Yield x s' -> go (acc * x) s' +{-# INLINE productS #-} + +andS :: Stream Bool -> Bool +andS (Stream next s0) = go True s0 where + go !acc !s = case next s of + Done -> acc + Skip s' -> go acc s' + Yield x s' -> go (acc && x) s' +{-# INLINE andS #-} + +orS :: Stream Bool -> Bool +orS (Stream next s0) = go False s0 where + go !acc !s = case next s of + Done -> acc + Skip s' -> go acc s' + Yield x s' -> go (acc || x) s' +{-# INLINE orS #-} + +anyS :: (a -> Bool) -> Stream a -> Bool +anyS p (Stream next s0) = go False s0 where + go !acc !s = case next s of + Done -> acc + Skip s' -> go acc s' + Yield x s' -> go (acc || p x) s' +{-# INLINE anyS #-} + +allS :: (a -> Bool) -> Stream a -> Bool +allS f (Stream next s0) = go True s0 where + go !acc !s = case next s of + Done -> acc + Skip s' -> go acc s' + Yield x s' -> go (acc && f x) s' +{-# INLINE allS #-} + +foldl1S' :: (a -> a -> a) -> Stream a -> a +foldl1S' f (Stream next s0) = go1 s0 where + go1 !s = + case next s of + Yield x s' -> go2 x s' + Skip s' -> go1 s' + Done -> errorEmptyList "foldl1" + go2 !acc !s = + case next s of + Yield x s' -> go2 (f acc x) s' + Skip s' -> go2 acc s' + Done -> acc +{-# INLINE foldl1S' #-} + +filterS :: (a -> Bool) -> Stream a -> Stream a +filterS p (Stream next s0) = Stream next' s0 where + next' !s = + case next s of + Yield x s' + | p x -> Yield x s' + | otherwise -> Skip s' + Skip s' -> Skip s' + Done -> Done + {-# INLINE next' #-} +{-# INLINE filterS #-} + +lookupS :: Eq a => a -> Stream (a, b) -> Maybe b +lookupS x0 (Stream next s0) = go s0 where + go !s = + case next s of + Yield (x,y) s' + | x0 == x -> Just y + | otherwise -> go s' + Skip s' -> go s' + Done -> Nothing +{-# INLINE lookupS #-} + +-- findS :: (a -> Bool) -> Stream a -> Maybe a +-- findS p (Stream next s0) = go s0 where +-- go !s = +-- case next s of +-- Yield x s' +-- | p x -> Just x +-- | otherwise -> go s' +-- Skip s' -> go s' +-- Done -> Nothing +-- {-# INLINE findS #-} +-- +-- findIndexS :: (a -> Bool) -> Stream a -> Maybe Int +-- findIndexS p (Stream next s0) = go 0 s0 where +-- go !i !s = +-- case next s of +-- Yield x s' +-- | p x -> Just i +-- | otherwise -> go (i + 1) s' +-- Skip s' -> go i s' +-- Done -> Nothing +-- {-# INLINE findIndexS #-} + +headS :: Stream a -> a +headS (Stream next s0) = go s0 where + go !s = + case next s of + Yield x _ -> x + Skip s' -> go s' + Done -> errorEmptyList "head" +{-# INLINE headS #-} + +lastS :: Stream a -> a +lastS (Stream next s0) = go1 s0 where + go1 !s = + case next s of + Yield x s' -> go2 x s' + Skip s' -> go1 s' + Done -> errorEmptyList "last" + go2 x !s = + case next s of + Yield x' s' -> go2 x' s' + Skip s' -> go2 x s' + Done -> x +{-# INLINE lastS #-} + +-- tailS :: Stream a -> Stream a +-- tailS (Stream next s0) = Stream next (tailF s0) where +-- tailF !s = +-- case next s of +-- Yield _ s' -> s' +-- Skip s' -> tailF s' +-- Done -> errorEmptyList "tail" +-- +-- initS1 :: Stream a -> Stream a +-- initS1 (Stream next s0) = Stream next' (f s0) where +-- f !s = +-- case next s of +-- Yield x s' -> x :!: s' +-- Skip s' -> f s' +-- Done -> errorEmptyList "init" +-- next' (x :!: s) = +-- case next s of +-- Yield y s' -> Yield x (y :!: s') +-- Skip s' -> Skip (x :!: s') +-- Done -> Done +-- {-# INLINE initS1 #-} + +initS :: Stream a -> Stream a +initS (Stream next s0) = Stream next' (Nothing :!: s0) where + next' (Nothing :!: s) = + case next s of + Yield x s' -> Skip (Just x :!: s') + Skip s' -> Skip (Nothing :!: s') + Done -> errorEmptyList "init" + next' (Just x :!: s) = + case next s of + Yield y s' -> Yield x (Just y :!: s') + Skip s' -> Skip (Just x :!: s') + Done -> Done +{-# INLINE initS #-} + +unconsS :: Stream a -> Maybe (a, [a]) +unconsS (Stream next s0) = go1 s0 where + go1 !s = + case next s of + Yield x s' -> Just (x, go2 s') + Skip s' -> go1 s' + Done -> Nothing + go2 !s = + case next s of + Yield x s' -> x : go2 s' + Skip s' -> go2 s' + Done -> [] +{-# INLINE unconsS #-} + +unsnocS :: Stream a -> Maybe ([a], a) +-- duplicates work: +-- unsnocS s = if nullS s then Nothing else Just (unstream (initS s), lastS s) +unsnocS = foldrS (\x xs -> case xs of Nothing -> Just ([], x); Just (ys,y) -> Just (x:ys,y)) Nothing +{-# INLINE unsnocS #-} + +indexHelperS :: Stream a -> Int -> Maybe a +indexHelperS (Stream next s0) i0 = go i0 s0 + where + go 0 !s = + case next s of + Yield x _ -> Just x + Skip s' -> go 0 s' + Done -> Nothing + go !i !s = + case next s of + Yield _ s' -> go (i - 1) s' + Skip s' -> go i s' + Done -> Nothing +{-# INLINE indexHelperS #-} + +unsafeIndexHelperS :: Stream a -> Int -> a +unsafeIndexHelperS (Stream next s0) i0 = go i0 s0 + where + go !i !s = + case next s of + Yield x s' -> if i == 0 then x else go (i - 1) s' + Skip s' -> go i s' + Done -> tooLarge i +{-# INLINE unsafeIndexHelperS #-} + +scanlS :: (b -> a -> b) -> b -> Stream a -> Stream b +scanlS k z (Stream next s0) = Stream next' (Just z :!: s0) where + next' (Just x :!: s) = + case next s of + Yield y s' -> Yield x (Just (k x y) :!: s') + Skip s' -> Skip (Just x :!: s') + Done -> Yield x (Nothing :!: s) + next' (Nothing :!: _) = Done + {-# INLINE next' #-} +{-# INLINE scanlS #-} + +data Scanl1State a s = Scanl1State1 !s | Scanl1State2 a !s | Scanl1State3 + +scanl1S :: (a -> a -> a) -> Stream a -> Stream a +scanl1S k (Stream next s0) = Stream next' (Scanl1State1 s0) where + next' (Scanl1State1 s) = + case next s of + Yield x s' -> Skip (Scanl1State2 x s') + Skip s' -> Skip (Scanl1State1 s') + Done -> errorEmptyList "scanl1" + next' (Scanl1State2 x s) = + case next s of + Yield y s' -> Yield x (Scanl1State2 (k x y) s') + Skip s' -> Skip (Scanl1State2 x s') + Done -> Yield x Scanl1State3 + next' Scanl1State3 = Done + {-# INLINE next' #-} +{-# INLINE scanl1S #-} + +scanlS' :: (b -> a -> b) -> b -> Stream a -> Stream b +scanlS' k z (Stream next s0) = Stream next' (Some (z :!: s0)) where + next' (Some (x :!: s)) = + case next s of + Yield y s' -> Yield x (Some (k x y :!: s')) + Skip s' -> Skip (Some (x :!: s')) + Done -> Yield x None + next' None = Done + {-# INLINE next' #-} +{-# INLINE scanlS' #-} + +iterateS :: (a -> a) -> a -> Stream a +iterateS f = Stream next . L where + next (L s) = Yield s (L (f s)) + {-# INLINE next #-} +{-# INLINE iterateS #-} + +iterateS' :: (a -> a) -> a -> Stream a +iterateS' f = Stream next where + next s = Yield s (f s) + {-# INLINE next #-} +{-# INLINE iterateS' #-} + +-- repeatS :: a -> Stream a +-- repeatS = Stream next . L where +-- next (L s) = Yield s (L s) +-- {-# INLINE next #-} +-- {-# INLINE repeatS #-} + +replicateS :: Int -> a -> Stream a +replicateS n x = Stream next n where + next s | s <= 0 = Done + | otherwise = Yield x (s - 1) + {-# INLINE next #-} +{-# INLINE replicateS #-} + +-- cycleS :: Stream a -> Stream a +-- cycleS (Stream next s0) = Stream next' s0 where +-- next' !s = +-- case next s of +-- Yield x s' -> Yield x s' +-- Skip s' -> Skip s' +-- Done -> Skip s0 +-- {-# INLINE cycleS #-} + +concatS :: Stream [a] -> Stream a +concatS (Stream next s0) = Stream next' (s0 :!: L []) where + next' (s :!: L []) = + case next s of + Yield [] s' -> Skip (s' :!: L []) + Yield (x:xs) s' -> Yield x (s' :!: L xs) + Skip s' -> Skip (s' :!: L []) + Done -> Done + next' (s :!: L (x:xs)) = Yield x (s :!: L xs) +{-# INLINE concatS #-} + +scanrS :: (a -> b -> b) -> b -> Stream a -> [b] +scanrS f q0 = foldrS (\x qs@(q:_) -> f x q : qs) [q0] +{-# INLINE scanrS #-} +scanr1S :: (a -> a -> a) -> Stream a -> [a] +scanr1S f = foldrS (\x qs -> case qs of [] -> [x]; (q:_) -> f x q : qs) [] +{-# INLINE scanr1S #-} + + +-- foldr' :: (a -> b -> b) -> b -> [a] -> b +-- foldr' k z = foldrS' k z . stream +-- {-# INLINE foldr' #-} +-- foldr1 :: (a -> a -> a) -> [a] -> a +-- foldr1 k = foldr1S k . stream +-- {-# INLINE foldr1 #-} +-- +-- foldl :: (b -> a -> b) -> b -> [a] -> b +-- foldl k z = foldlS k z . stream +-- {-# INLINE foldl #-} +-- foldl' :: (b -> a -> b) -> b -> [a] -> b +-- foldl' k z = foldlS' k z . stream +-- {-# INLINE foldl' #-} +-- foldl1 :: (a -> a -> a) -> [a] -> a +-- foldl1 k = foldl1S k . stream +-- {-# INLINE foldl1 #-} +-- +-- null :: [a] -> Bool +-- null = nullS . stream +-- {-# INLINE null #-} +-- length :: [a] -> Int +-- length = lengthS . stream +-- {-# INLINE length #-} +-- elem :: Eq a => a -> [a] -> Bool +-- elem x = elemS x . stream +-- {-# INLINE elem #-} +-- notElem :: Eq a => a -> [a] -> Bool +-- notElem x = notElemS x . stream +-- {-# INLINE notElem #-} +-- +-- maximum :: Ord a => [a] -> a +-- maximum = maximumS . stream +-- {-# INLINE maximum #-} +-- minimum :: Ord a => [a] -> a +-- minimum = minimumS . stream +-- {-# INLINE minimum #-} +-- sum :: Num a => [a] -> a +-- sum = sumS . stream +-- {-# INLINE sum #-} +-- product :: Num a => [a] -> a +-- product = productS . stream +-- {-# INLINE product #-} +-- and :: [Bool] -> Bool +-- and = andS . stream +-- {-# INLINE and #-} +-- or :: [Bool] -> Bool +-- or = orS . stream +-- {-# INLINE or #-} +-- any :: (a -> Bool) -> [a] -> Bool +-- any p = anyS p . stream +-- {-# INLINE any #-} +-- all :: (a -> Bool) -> [a] -> Bool +-- all p = allS p . stream +-- {-# INLINE all #-} +-- +-- foldl1' :: (a -> a -> a) -> [a] -> a +-- foldl1' f = foldl1S' f . stream +-- {-# INLINE foldl1' #-} +-- concat :: [[a]] -> [a] +-- concat = unstream . concatS . stream +-- {-# INLINE concat #-} +-- concatMap :: (a -> [b]) -> [a] -> [b] +-- concatMap f = unstream . concatMapS (stream . f) . stream +-- {-# INLINE concatMap #-} +-- +-- filter :: (a -> Bool) -> [a] -> [a] +-- filter p = unstream . filterS p . stream +-- {-# INLINE filter #-} +-- lookup :: Eq a => a -> [(a, b)] -> Maybe b +-- lookup x = lookupS x . stream +-- {-# INLINE lookup #-} +-- +-- head :: [a] -> a +-- head = headS . stream +-- {-# INLINE head #-} +-- last :: [a] -> a +-- last = lastS . stream +-- {-# INLINE last #-} +-- tail :: [a] -> [a] +-- -- destoys sharing: +-- -- tail = unstream . tailS . stream +-- tail [] = errorEmptyList "tail" +-- tail (_:xs) = xs +-- {-# INLINE tail #-} +-- init :: [a] -> [a] +-- init = unstream . initS . stream +-- {-# INLINE init #-} +-- uncons :: [a] -> Maybe (a, [a]) +-- uncons [] = Nothing +-- uncons (x:xs) = Just (x, xs) +-- {-# NOINLINE [1] uncons #-} +-- -- {-# RULES "uncons/stream" forall s. uncons (unstream s) = unconsS s #-} +-- -- {-# RULES "uncons/stream" forall s. uncons (cheapUnstream s) = unconsS s #-} +-- unsnoc :: [a] -> Maybe ([a], a) +-- unsnoc = unsnocS . stream +-- {-# INLINE unsnoc #-} +-- (!?) :: [a] -> Int -> Maybe a +-- xs !? i = indexS (stream xs) i +-- {-# INLINE (!?) #-} +-- (!!) :: [a] -> Int -> a +-- xs !! i = unsafeIndexS (stream xs) i +-- {-# INLINE (!!) #-} +-- +-- scanl :: (b -> a -> b) -> b -> [a] -> [b] +-- scanl k z = unstream . scanlS k z . stream +-- {-# INLINE scanl #-} +-- scanl1 :: (a -> a -> a) -> [a] -> [a] +-- scanl1 k = unstream . scanl1S k . stream +-- {-# INLINE scanl1 #-} +-- scanl' :: (b -> a -> b) -> b -> [a] -> [b] +-- scanl' k z = unstream . scanlS' k z . stream +-- {-# INLINE scanl' #-} +-- scanr :: (a -> b -> b) -> b -> [a] -> [b] +-- scanr f q0 = foldrS (\x qs@(q:_) -> f x q : qs) [q0] . stream +-- {-# INLINE scanr #-} +-- scanr1 :: (a -> a -> a) -> [a] -> [a] +-- scanr1 f = foldrS (\x qs -> case qs of [] -> [x]; (q:_) -> f x q : qs) [] . stream +-- {-# INLINE scanr1 #-} +-- +-- iterate :: (a -> a) -> a -> [a] +-- iterate f x = cheapUnstream (iterateS f x) +-- {-# INLINE iterate #-} +-- iterate' :: (a -> a) -> a -> [a] +-- iterate' f x = unstream (iterateS' f x) +-- {-# INLINE iterate' #-} +-- repeat :: a -> [a] +-- repeat x = let xs = x : xs in xs +-- -- repeat = cheapUnstream . repeatS +-- {-# INLINE repeat #-} +-- replicate :: Int -> a -> [a] +-- replicate n x = cheapUnstream (replicateS n x) +-- {-# INLINE replicate #-} +-- cycle :: [a] -> [a] +-- cycle xs = ys where ys = foldrS (:) ys (stream xs) +-- -- cycle = unstream . cycleS . stream +-- {-# INLINE cycle #-} +-- +-- take :: Int -> [a] -> [a] +-- take n = unstream . takeS n . stream +-- {-# INLINE take #-} +-- drop :: Int -> [a] -> [a] +-- drop 0 xs = xs +-- drop _ [] = [] +-- drop n (_:xs) = drop (n - 1) xs +-- {-# NOINLINE [1] drop #-} +-- -- {-# RULES "drop/stream" forall n s. drop n (unstream s) = unstream (dropS n s) #-} +-- -- {-# RULES "drop/stream" forall n s. drop n (cheapUnstream s) = cheapUnstream (dropS n s) #-} +-- +-- splitAt :: Int -> [a] -> ([a], [a]) +-- splitAt 0 xs = ([], xs) +-- splitAt _ [] = ([],[]) +-- splitAt n (x:xs) = let (xs',ys') = splitAt (n - 1) xs in (x : xs', ys') +-- {-# NOINLINE [1] splitAt #-} +-- -- {-# RULES "splitAt/stream" forall n s. splitAt n (unstream s) = splitAtS n s #-} +-- -- {-# RULES "splitAt/stream" forall n s. splitAt n (cheapUnstream s) = cheapSplitAtS n s #-} +-- takeWhile :: (a -> Bool) -> [a] -> [a] +-- takeWhile p = unstream . takeWhileS p . stream +-- {-# INLINE takeWhile #-} +-- dropWhile :: (a -> Bool) -> [a] -> [a] +-- dropWhile _ [] = [] +-- dropWhile p xs@(x:xs') +-- | p x = dropWhile p xs' +-- | otherwise = xs +-- {-# NOINLINE [1] dropWhile #-} +-- -- {-# RULES "dropWhile/stream" forall p s. dropWhile p (unstream s) = unstream (dropWhileS p s) #-} +-- -- {-# RULES "dropWhile/stream" forall p s. dropWhile p (cheapUnstream s) = unstream (dropWhileS p s) #-} +-- span :: (a -> Bool) -> [a] -> ([a], [a]) +-- -- destroys sharing and duplicates work: +-- -- span p xs = (unstream (takeWhileS p (stream xs)), unstream (dropWhileS p (stream xs))) +-- span _ [] = ([], []) +-- span p xs@(x:xs') +-- | p x = let (ys,zs) = span p xs' in (x:ys,zs) +-- | otherwise = ([], xs) +-- {-# NOINLINE [1] span #-} +-- -- {-# RULES "span/stream" forall p s. span p (unstream s) = spanS p s #-} +-- -- {-# RULES "span/stream" forall p s. span p (cheapUnstream s) = spanS p s #-} +-- break :: (a -> Bool) -> [a] -> ([a], [a]) +-- break p = span (not . p) +-- {-# INLINE break #-} +-- reverse :: [a] -> [a] +-- reverse = reverseS . stream +-- {-# INLINE reverse #-} +-- +-- zip :: [a] -> [b] -> [(a,b)] +-- zip xs ys = unstream (zipS (stream xs) (stream ys)) +-- {-# INLINE zip #-} +-- zip3 :: [a] -> [b] -> [c] -> [(a,b,c)] +-- zip3 xs ys zs = unstream (zip3S (stream xs) (stream ys) (stream zs)) +-- {-# INLINE zip3 #-} +-- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] +-- zipWith f xs ys = unstream (zipWithS f (stream xs) (stream ys)) +-- {-# INLINE zipWith #-} +-- zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] +-- zipWith3 f xs ys zs = unstream (zipWith3S f (stream xs) (stream ys) (stream zs)) +-- {-# INLINE zipWith3 #-} +-- +-- unzip :: [(a,b)] -> ([a], [b]) +-- unzip = unzipS . stream +-- {-# INLINE unzip #-} +-- unzip3 :: [(a,b,c)] -> ([a], [b], [c]) +-- unzip3 = unzip3S . stream +-- {-# INLINE unzip3 #-} + + -- $setup -- >>> import GHC.Internal.Base -- >>> import Prelude (Num (..), Ord (..), Int, Double, odd, not, undefined) @@ -98,10 +1022,12 @@ badHead = errorEmptyList "head" -- This rule is useful in cases like -- head [y | (x,y) <- ps, x==t] {-# RULES -"head/build" forall (g::forall b.(a->b->b)->b->b) . - head (build g) = g (\x _ -> x) badHead -"head/augment" forall xs (g::forall b. (a->b->b) -> b -> b) . - head (augment g xs) = g (\x _ -> x) (head xs) +"head/unstream" forall s. head (unstream s) = headS s +"head/cheapUnstream" forall s. head (cheapUnstream s) = headS s +-- "head/build" forall (g::forall b.(a->b->b)->b->b) . +-- head (build g) = g (\x _ -> x) badHead +-- "head/augment" forall xs (g::forall b. (a->b->b) -> b -> b) . +-- head (augment g xs) = g (\x _ -> x) (head xs) #-} -- | \(\mathcal{O}(1)\). Decompose a list into its 'head' and 'tail'. @@ -283,8 +1209,9 @@ lenAcc [] n = n lenAcc (_:ys) n = lenAcc ys (n+1) {-# RULES -"length" [~1] forall xs . length xs = foldr lengthFB idLength xs 0 -"lengthList" [1] foldr lengthFB idLength = lenAcc +"length" length = lengthS . stream +-- "length" [~1] forall xs . length xs = foldr lengthFB idLength xs 0 +-- "lengthList" [1] foldr lengthFB idLength = lenAcc #-} -- The lambda form turns out to be necessary to make this inline @@ -325,9 +1252,10 @@ filterFB c p x r | p x = x `c` r | otherwise = r {-# RULES -"filter" [~1] forall p xs. filter p xs = build (\c n -> foldr (filterFB c p) n xs) -"filterList" [1] forall p. foldr (filterFB (:) p) [] = filter p -"filterFB" forall c p q. filterFB (filterFB c p) q = filterFB c (\x -> q x && p x) +"filter" forall p. filter p = unstream . filterS p . stream +-- "filter" [~1] forall p xs. filter p xs = build (\c n -> foldr (filterFB c p) n xs) +-- "filterList" [1] forall p. foldr (filterFB (:) p) [] = filter p +-- "filterFB" forall c p q. filterFB (filterFB c p) q = filterFB c (\x -> q x && p x) #-} -- Note the filterFB rule, which has p and q the "wrong way round" in the RHS. @@ -359,10 +1287,13 @@ filterFB c p x r | p x = x `c` r -- >>> foldl (+) 0 [1..] -- * Hangs forever * foldl :: forall a b. (b -> a -> b) -> b -> [a] -> b -{-# INLINE foldl #-} -foldl k z0 xs = - foldr (\(v::a) (fn::b->b) -> oneShot (\(z::b) -> fn (k z v))) (id :: b -> b) xs z0 - -- See Note [Left folds via right fold] +foldl k z0 [] = z0 +foldl k z0 (x:xs) = foldl k (k z0 x) xs +{-# NOINLINE [0] foldl #-} + +{-# RULES +"foldl" forall k z . foldl k z = foldlS k z . stream + #-} {- Note [Left folds via right fold] @@ -405,9 +1336,14 @@ allocation-free. Also see #13001. -- | A strict version of 'foldl'. foldl' :: forall a b . (b -> a -> b) -> b -> [a] -> b -{-# INLINE foldl' #-} -foldl' k z0 = \xs -> - foldr (\(v::a) (fn::b->b) -> oneShot (\(z::b) -> z `seq` fn (k z v))) (id :: b -> b) xs z0 +foldl' k !z0 [] = z0 +foldl' k !z0 (x:xs) = foldl' k (k z0 x) xs + +{-# NOINLINE [0] foldl' #-} +{-# RULES +"foldl'" forall k z. foldl' k z = foldlS' k z . stream + #-} + {- Note [Definition of foldl'] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -551,10 +1487,11 @@ scanl = scanlGo -- See Note [scanl rewrite rules] {-# RULES -"scanl" [~1] forall f a bs . scanl f a bs = - build (\c n -> a `c` foldr (scanlFB f c) (constScanl n) bs a) -"scanlList" [1] forall f (a::a) bs . - foldr (scanlFB f (:)) (constScanl []) bs a = tail (scanl f a bs) +"scanl" forall f a. scanl f a = unstream . scanlS f a . stream +-- "scanl" [~1] forall f a bs . scanl f a bs = +-- build (\c n -> a `c` foldr (scanlFB f c) (constScanl n) bs a) +-- "scanlList" [1] forall f (a::a) bs . +-- foldr (scanlFB f (:)) (constScanl []) bs a = tail (scanl f a bs) #-} {-# INLINE [0] scanlFB #-} -- See Note [Inline FB functions] @@ -612,10 +1549,11 @@ scanl' = scanlGo' -- See Note [scanl rewrite rules] {-# RULES -"scanl'" [~1] forall f a bs . scanl' f a bs = - build (\c n -> a `c` foldr (scanlFB' f c) (flipSeq n) bs a) -"scanlList'" [1] forall f a bs . - foldr (scanlFB' f (:)) (flipSeq []) bs a = tail (scanl' f a bs) +"scanl'" forall f a. scanl' f a = unstream . scanlS' f a . stream +-- "scanl'" [~1] forall f a bs . scanl' f a bs = +-- build (\c n -> a `c` foldr (scanlFB' f c) (flipSeq n) bs a) +-- "scanlList'" [1] forall f a bs . +-- foldr (scanlFB' f (:)) (flipSeq []) bs a = tail (scanl' f a bs) #-} {-# INLINE [0] scanlFB' #-} -- See Note [Inline FB functions] @@ -680,6 +1618,7 @@ match on everything past the :, which is just the tail of scanl. -- >>> foldr' (||) [False, False, True, True] -- Use foldr instead! -- True foldr' :: (a -> b -> b) -> b -> [a] -> b +{-# INLINE foldr' #-} foldr' f z0 xs = foldl f' id xs z0 where f' k x z = k $! f x z @@ -704,6 +1643,9 @@ foldr1 f = go go (x:xs) = f x (go xs) go [] = errorEmptyList "foldr1" {-# INLINE [0] foldr1 #-} +{-# RULES +"foldr1" forall f . foldr1 f = foldr1S f . stream + #-} -- | \(\mathcal{O}(n)\). 'scanr' is the right-to-left dual of 'scanl'. Note that the order of parameters on the accumulating function are reversed compared to 'scanl'. -- Also note that @@ -746,11 +1688,12 @@ scanrFB f c = \x ~(r, est) -> (f x r, r `c` est) -- See Note [scanrFB and evaluation] below {-# RULES -"scanr" [~1] forall f q0 ls . scanr f q0 ls = - build (\c n -> strictUncurryScanr c (foldr (scanrFB f c) (q0,n) ls)) -"scanrList" [1] forall f q0 ls . - strictUncurryScanr (:) (foldr (scanrFB f (:)) (q0,[]) ls) = - scanr f q0 ls +"scanr" forall f q0. scanr f q0 = scanrS f q0 . stream +-- "scanr" [~1] forall f q0 ls . scanr f q0 ls = +-- build (\c n -> strictUncurryScanr c (foldr (scanrFB f c) (q0,n) ls)) +-- "scanrList" [1] forall f q0 ls . +-- strictUncurryScanr (:) (foldr (scanrFB f (:)) (q0,[]) ls) = +-- scanr f q0 ls #-} {- @@ -805,6 +1748,10 @@ scanr1 _ [] = [] scanr1 _ [x] = [x] scanr1 f (x:xs) = f x q : qs where qs@(q:_) = scanr1 f xs +{-# NOINLINE [0] scanr1 #-} +{-# RULES +"scanr1" forall f. scanr1 f = scanr1S f . stream + #-} -- | 'maximum' returns the maximum value from a list, -- which must be non-empty, finite, and of an ordered type. @@ -888,8 +1835,9 @@ iterateFB c f x0 = go x0 where go x = x `c` go (f x) {-# RULES -"iterate" [~1] forall f x. iterate f x = build (\c _n -> iterateFB c f x) -"iterateFB" [1] iterateFB (:) = iterate +"iterate" forall f x. iterate f x = unstream (iterateS f x) +-- "iterate" [~1] forall f x. iterate f x = build (\c _n -> iterateFB c f x) +-- "iterateFB" [1] iterateFB (:) = iterate #-} @@ -915,8 +1863,9 @@ iterate'FB c f x0 = go x0 in x' `seq` (x `c` go x') {-# RULES -"iterate'" [~1] forall f x. iterate' f x = build (\c _n -> iterate'FB c f x) -"iterate'FB" [1] iterate'FB (:) = iterate' +"iterate'" forall f x. iterate' f x = unstream (iterateS' f x) +-- "iterate'" [~1] forall f x. iterate' f x = build (\c _n -> iterate'FB c f x) +-- "iterate'FB" [1] iterate'FB (:) = iterate' #-} @@ -939,10 +1888,10 @@ repeatFB :: (a -> b -> b) -> a -> b repeatFB c x = xs where xs = x `c` xs -{-# RULES -"repeat" [~1] forall x. repeat x = build (\c _n -> repeatFB c x) -"repeatFB" [1] repeatFB (:) = repeat - #-} +-- {-# RULES +-- "repeat" [~1] forall x. repeat x = build (\c _n -> repeatFB c x) +-- "repeatFB" [1] repeatFB (:) = repeat +-- #-} -- | 'replicate' @n x@ is a list of length @n@ with @x@ the value of -- every element. @@ -959,9 +1908,12 @@ repeatFB c x = xs where xs = x `c` xs -- -- >>> replicate 4 True -- [True,True,True,True] -{-# INLINE replicate #-} +{-# NOINLINE [0] replicate #-} replicate :: Int -> a -> [a] replicate n x = take n (repeat x) +{-# RULES +"replicate" forall n x . replicate n x = cheapUnstream (replicateS n x) +#-} -- | 'cycle' ties a finite list into a circular one, or equivalently, -- the infinite repetition of the original list. It is the identity @@ -1027,11 +1979,12 @@ takeWhileFB p c n = \x r -> if p x then x `c` r else n -- \x r -> if q x && p x then x `c` r else n = -- takeWhileFB (\x -> q x && p x) c n {-# RULES -"takeWhile" [~1] forall p xs. takeWhile p xs = - build (\c n -> foldr (takeWhileFB p c n) n xs) -"takeWhileList" [1] forall p. foldr (takeWhileFB p (:) []) [] = takeWhile p -"takeWhileFB" forall c n p q. takeWhileFB q (takeWhileFB p c n) n = - takeWhileFB (\x -> q x && p x) c n +"takeWhile" forall p. takeWhile p = unstream . takeWhileS p . stream +-- "takeWhile" [~1] forall p xs. takeWhile p xs = +-- build (\c n -> foldr (takeWhileFB p c n) n xs) +-- "takeWhileList" [1] forall p. foldr (takeWhileFB p (:) []) [] = takeWhile p +-- "takeWhileFB" forall c n p q. takeWhileFB q (takeWhileFB p c n) n = +-- takeWhileFB (\x -> q x && p x) c n #-} -- | 'dropWhile' @p xs@ returns the suffix remaining after 'takeWhile' @p xs at . @@ -1051,6 +2004,12 @@ dropWhile _ [] = [] dropWhile p xs@(x:xs') | p x = dropWhile p xs' | otherwise = xs +{-# NOINLINE [0] dropWhile #-} + +{-# RULES +"dropWhile/unstream" forall p s. dropWhile p (unstream s) = unstream (dropWhileS p s) +"dropWhile/cheapUnstream" forall p s. dropWhile p (cheapUnstream s) = cheapUnstream (dropWhileS p s) + #-} -- | 'take' @n@, applied to a list @xs@, returns the prefix of @xs@ -- of length @n@, or @xs@ itself if @n >= 'length' xs at . @@ -1109,12 +2068,13 @@ unsafeTake 1 (x: _) = [x] unsafeTake m (x:xs) = x : unsafeTake (m - 1) xs {-# RULES -"take" [~1] forall n xs . take n xs = - build (\c nil -> if 0 < n - then foldr (takeFB c nil) (flipSeq nil) xs n - else nil) -"unsafeTakeList" [1] forall n xs . foldr (takeFB (:) []) (flipSeq []) xs n - = unsafeTake n xs +"take" forall n. take n = unstream . takeS n . stream +-- "take" [~1] forall n xs . take n xs = +-- build (\c nil -> if 0 < n +-- then foldr (takeFB c nil) (flipSeq nil) xs n +-- else nil) +-- "unsafeTakeList" [1] forall n xs . foldr (takeFB (:) []) (flipSeq []) xs n +-- = unsafeTake n xs #-} {-# INLINE [0] flipSeq #-} @@ -1168,7 +2128,7 @@ drop n xs | n <= 0 = xs drop _ [] = [] drop n (_:xs) = drop (n-1) xs #else /* hack away */ -{-# INLINE drop #-} +{-# INLINE [1] drop #-} drop n ls | n <= 0 = ls | otherwise = unsafeDrop n ls @@ -1179,6 +2139,10 @@ drop n ls unsafeDrop !_ [] = [] unsafeDrop 1 (_:xs) = xs unsafeDrop m (_:xs) = unsafeDrop (m - 1) xs +{-# RULES +"drop/unstream" forall n s . drop n (unstream s) = unstream (dropS n s) +"drop/cheapUnstream" forall n s. drop n (cheapUnstream s) = cheapUnstream (dropS n s) + #-} #endif -- | 'splitAt' @n xs@ returns a tuple where first element is @xs@ prefix of @@ -1238,6 +2202,11 @@ splitAt n ls splitAt' m (x:xs) = (x:xs', xs'') where (xs', xs'') = splitAt' (m - 1) xs +{-# NOINLINE [0] splitAt #-} +{-# RULES +"splitAt/unstream" forall n s. splitAt n (unstream s) = splitAtS n s +"splitAt/cheapUnstream" forall n s. splitAt n (cheapUnstream s) = cheapSplitAtS n s + #-} #endif /* USE_REPORT_PRELUDE */ -- | 'span', applied to a predicate @p@ and a list @xs@, returns a tuple where @@ -1394,8 +2363,9 @@ and (x:xs) = x && and xs {-# NOINLINE [1] and #-} {-# RULES -"and/build" forall (g::forall b.(Bool->b->b)->b->b) . - and (build g) = g (&&) True +"and" and = andS . stream +-- "and/build" forall (g::forall b.(Bool->b->b)->b->b) . +-- and (build g) = g (&&) True #-} #endif @@ -1431,8 +2401,9 @@ or (x:xs) = x || or xs {-# NOINLINE [1] or #-} {-# RULES -"or/build" forall (g::forall b.(Bool->b->b)->b->b) . - or (build g) = g (||) False +"or" or = orS . stream +-- "or/build" forall (g::forall b.(Bool->b->b)->b->b) . +-- or (build g) = g (||) False #-} #endif @@ -1468,8 +2439,9 @@ any p (x:xs) = p x || any p xs {-# NOINLINE [1] any #-} {-# RULES -"any/build" forall p (g::forall b.(a->b->b)->b->b) . - any p (build g) = g ((||) . p) False +"any" forall p . any p = anyS p . stream +-- "any/build" forall p (g::forall b.(a->b->b)->b->b) . +-- any p (build g) = g ((||) . p) False #-} #endif @@ -1505,8 +2477,9 @@ all p (x:xs) = p x && all p xs {-# NOINLINE [1] all #-} {-# RULES -"all/build" forall p (g::forall b.(a->b->b)->b->b) . - all p (build g) = g ((&&) . p) True +"all" forall p . all p = allS p . stream +-- "all/build" forall p (g::forall b.(a->b->b)->b->b) . +-- all p (build g) = g ((&&) . p) True #-} #endif @@ -1539,8 +2512,9 @@ elem _ [] = False elem x (y:ys) = x==y || elem x ys {-# NOINLINE [1] elem #-} {-# RULES -"elem/build" forall x (g :: forall b . (a -> b -> b) -> b -> b) - . elem x (build g) = g (\ y r -> (x == y) || r) False +"elem" forall x. elem x = elemS x . stream +-- "elem/build" forall x (g :: forall b . (a -> b -> b) -> b -> b) +-- . elem x (build g) = g (\ y r -> (x == y) || r) False #-} #endif @@ -1570,8 +2544,9 @@ notElem _ [] = True notElem x (y:ys)= x /= y && notElem x ys {-# NOINLINE [1] notElem #-} {-# RULES -"notElem/build" forall x (g :: forall b . (a -> b -> b) -> b -> b) - . notElem x (build g) = g (\ y r -> (x /= y) && r) True +"notElem" forall x. notElem x = notElemS x . stream +-- "notElem/build" forall x (g :: forall b . (a -> b -> b) -> b -> b) +-- . notElem x (build g) = g (\ y r -> (x /= y) && r) True #-} #endif @@ -1596,35 +2571,11 @@ lookup key ((x,y):xys) | otherwise = lookup key xys {-# NOINLINE [1] lookup #-} -- see Note [Fusion for lookup] {-# RULES -"lookup/build" forall x (g :: forall b. ((k, a) -> b -> b) -> b -> b). - lookup x (build g) = g (\(k, v) r -> if x == k then Just v else r) Nothing +"lookup" forall x. lookup x = lookupS x . stream +-- "lookup/build" forall x (g :: forall b. ((k, a) -> b -> b) -> b -> b). +-- lookup x (build g) = g (\(k, v) r -> if x == k then Just v else r) Nothing #-} --- | Map a function returning a list over a list and concatenate the results. --- 'concatMap' can be seen as the composition of 'concat' and 'map'. --- --- > concatMap f xs == (concat . map f) xs --- --- ==== __Examples__ --- --- >>> concatMap (\i -> [-i,i]) [] --- [] --- --- >>> concatMap (\i -> [-i, i]) [1, 2, 3] --- [-1,1,-2,2,-3,3] --- --- >>> concatMap ('replicate' 3) [0, 2, 4] --- [0,0,0,2,2,2,4,4,4] -concatMap :: (a -> [b]) -> [a] -> [b] -concatMap f = foldr ((++) . f) [] - -{-# NOINLINE [1] concatMap #-} - -{-# RULES -"concatMap" forall f xs . concatMap f xs = - build (\c n -> foldr (\x b -> foldr c b (f x)) n xs) - #-} - -- | Concatenate a list of lists. -- @@ -1644,8 +2595,9 @@ concat = foldr (++) [] {-# NOINLINE [1] concat #-} {-# RULES - "concat" forall xs. concat xs = - build (\c n -> foldr (\x y -> foldr c y x) n xs) +"concat" concat = unstream . concatS . stream +-- "concat" forall xs. concat xs = +-- build (\c n -> foldr (\x y -> foldr c y x) n xs) -- We don't bother to turn non-fusible applications of concat back into concat #-} @@ -1694,9 +2646,17 @@ negIndex = error $ prel_list_str ++ "!!: negative index" {-# INLINABLE (!!) #-} xs !! n | n < 0 = negIndex - | otherwise = foldr (\x r k -> case k of - 0 -> x - _ -> r (k-1)) tooLarge xs n + | otherwise = unsafeIndexHelper xs n + +unsafeIndexHelper :: [a] -> Int -> a +unsafeIndexHelper [] i = tooLarge i +unsafeIndexHelper (x:xs) 0 = x +unsafeIndexHelper (x:xs) n = unsafeIndexHelper xs (n - 1) +{-# NOINLINE [1] unsafeIndexHelper #-} + +{-# RULES +"unsafeIndexHelper" forall xs. unsafeIndexHelper xs = unsafeIndexHelperS (stream xs) + #-} #endif -- | List index (subscript) operator, starting from 0. Returns 'Nothing' @@ -1724,9 +2684,16 @@ xs !! n {-# INLINABLE (!?) #-} xs !? n | n < 0 = Nothing - | otherwise = foldr (\x r k -> case k of - 0 -> Just x - _ -> r (k-1)) (const Nothing) xs n + | otherwise = indexHelper xs n + +indexHelper :: [a] -> Int -> Maybe a +indexHelper [] _ = Nothing +indexHelper (x:_) 0 = Just x +indexHelper (_:xs) n = indexHelper xs (n - 1) +{-# NOINLINE [1] indexHelper #-} +{-# RULES +"indexHelper" forall xs n . indexHelper xs n = indexHelperS (stream xs) n + #-} -------------------------------------------------------------- -- The zip family @@ -1879,8 +2846,9 @@ zipFB :: ((a, b) -> c -> d) -> a -> b -> c -> d zipFB c = \x y r -> (x,y) `c` r {-# RULES -- See Note [Fusion for zipN/zipWithN] -"zip" [~1] forall xs ys. zip xs ys = build (\c n -> foldr2 (zipFB c) n xs ys) -"zipList" [1] foldr2 (zipFB (:)) [] = zip +"zip" forall xs ys. zip xs ys = unstream (zipS (stream xs) (stream ys)) +-- "zip" [~1] forall xs ys. zip xs ys = build (\c n -> foldr2 (zipFB c) n xs ys) +-- "zipList" [1] foldr2 (zipFB (:)) [] = zip #-} ---------------------------------------------- @@ -1900,8 +2868,9 @@ zip3FB :: ((a,b,c) -> xs -> xs') -> a -> b -> c -> xs -> xs' zip3FB cons = \a b c r -> (a,b,c) `cons` r {-# RULES -- See Note [Fusion for zipN/zipWithN] -"zip3" [~1] forall as bs cs. zip3 as bs cs = build (\c n -> foldr3 (zip3FB c) n as bs cs) -"zip3List" [1] foldr3 (zip3FB (:)) [] = zip3 +"zip3" forall xs ys zs . zip3 xs ys zs = unstream (zip3S (stream xs) (stream ys) (stream zs)) +-- "zip3" [~1] forall as bs cs. zip3 as bs cs = build (\c n -> foldr3 (zip3FB c) n as bs cs) +-- "zip3List" [1] foldr3 (zip3FB (:)) [] = zip3 #-} -- The zipWith family generalises the zip family by zipping with the @@ -1949,8 +2918,9 @@ zipWithFB :: (a -> b -> c) -> (d -> e -> a) -> d -> e -> b -> c zipWithFB c f = \x y r -> (x `f` y) `c` r {-# RULES -- See Note [Fusion for zipN/zipWithN] -"zipWith" [~1] forall f xs ys. zipWith f xs ys = build (\c n -> foldr2 (zipWithFB c f) n xs ys) -"zipWithList" [1] forall f. foldr2 (zipWithFB (:) f) [] = zipWith f +"zipWith" forall f xs ys. zipWith f xs ys = unstream (zipWithS f (stream xs) (stream ys)) +-- "zipWith" [~1] forall f xs ys. zipWith f xs ys = build (\c n -> foldr2 (zipWithFB c f) n xs ys) +-- "zipWithList" [1] forall f. foldr2 (zipWithFB (:) f) [] = zipWith f #-} -- | \(\mathcal{O}(\min(l,m,n))\). The 'zipWith3' function takes a function which combines three @@ -1981,8 +2951,9 @@ zipWith3FB :: (d -> xs -> xs') -> (a -> b -> c -> d) -> a -> b -> c -> xs -> xs' zipWith3FB cons func = \a b c r -> (func a b c) `cons` r {-# RULES -"zipWith3" [~1] forall f as bs cs. zipWith3 f as bs cs = build (\c n -> foldr3 (zipWith3FB c f) n as bs cs) -"zipWith3List" [1] forall f. foldr3 (zipWith3FB (:) f) [] = zipWith3 f +"zipWith3" forall f xs ys zs . zipWith3 f xs ys zs = unstream (zipWith3S f (stream xs) (stream ys) (stream zs)) +-- "zipWith3" [~1] forall f as bs cs. zipWith3 f as bs cs = build (\c n -> foldr3 (zipWith3FB c f) n as bs cs) +-- "zipWith3List" [1] forall f. foldr3 (zipWith3FB (:) f) [] = zipWith3 f #-} -- | 'unzip' transforms a list of pairs into a list of first components ===================================== libraries/ghc-internal/src/GHC/Internal/System/Posix/Internals.hs ===================================== @@ -48,7 +48,7 @@ import GHC.Internal.Data.Maybe import GHC.Internal.System.IO.Error #endif -import GHC.Internal.Base +import GHC.Internal.Base hiding (Stream) import GHC.Internal.Bits import GHC.Internal.Num import GHC.Internal.Real View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3e0b4233f722dedd7ebcfb0be0ca0adef8de0574 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3e0b4233f722dedd7ebcfb0be0ca0adef8de0574 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 12:57:57 2024 From: gitlab at gitlab.haskell.org (Jaro Reinders (@jaro)) Date: Tue, 04 Jun 2024 08:57:57 -0400 Subject: [Git][ghc/ghc][wip/T24880] Deleted 1 commit: Replace fold/build by stream fusion WIP Message-ID: <665f0f55cf5d3_27a8352b458f01846d0@gitlab.mail> Jaro Reinders pushed to branch wip/T24880 at Glasgow Haskell Compiler / GHC WARNING: The push did not contain any new commits, but force pushed to delete the commits and changes below. Deleted commits: 3e0b4233 by Jaro Reinders at 2024-06-04T14:55:12+02:00 Replace fold/build by stream fusion WIP - - - - - 10 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/HsToCore/ListComp.hs - libraries/ghc-internal/src/GHC/Internal/Base.hs - libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs - libraries/ghc-internal/src/GHC/Internal/Enum.hs - libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs - libraries/ghc-internal/src/GHC/Internal/List.hs - libraries/ghc-internal/src/GHC/Internal/System/Posix/Internals.hs Changes: ===================================== compiler/GHC/Builtin/Names.hs ===================================== @@ -356,6 +356,7 @@ basicKnownKeyNames -- List operations concatName, filterName, mapName, zipName, foldrName, buildName, augmentName, appendName, + concatMapName, -- FFI primitive types that are not wired-in. stablePtrTyConName, ptrTyConName, funPtrTyConName, constPtrConName, @@ -746,13 +747,14 @@ map_RDR, append_RDR :: RdrName map_RDR = nameRdrName mapName append_RDR = nameRdrName appendName -foldr_RDR, build_RDR, returnM_RDR, bindM_RDR, failM_RDR +foldr_RDR, build_RDR, returnM_RDR, bindM_RDR, failM_RDR, concatMap_RDR :: RdrName foldr_RDR = nameRdrName foldrName build_RDR = nameRdrName buildName returnM_RDR = nameRdrName returnMName bindM_RDR = nameRdrName bindMName failM_RDR = nameRdrName failMName +concatMap_RDR = nameRdrName concatMapName left_RDR, right_RDR :: RdrName left_RDR = nameRdrName leftDataConName @@ -1123,7 +1125,7 @@ considerAccessibleName = varQual gHC_INTERNAL_EXTS (fsLit "considerAccessible") -- Random GHC.Internal.Base functions fromStringName, otherwiseIdName, foldrName, buildName, augmentName, - mapName, appendName, assertName, + mapName, concatMapName, appendName, assertName, dollarName :: Name dollarName = varQual gHC_INTERNAL_BASE (fsLit "$") dollarIdKey otherwiseIdName = varQual gHC_INTERNAL_BASE (fsLit "otherwise") otherwiseIdKey @@ -1131,6 +1133,7 @@ foldrName = varQual gHC_INTERNAL_BASE (fsLit "foldr") foldrIdKey buildName = varQual gHC_INTERNAL_BASE (fsLit "build") buildIdKey augmentName = varQual gHC_INTERNAL_BASE (fsLit "augment") augmentIdKey mapName = varQual gHC_INTERNAL_BASE (fsLit "map") mapIdKey +concatMapName = varQual gHC_INTERNAL_BASE (fsLit "concatMap") concatMapIdKey appendName = varQual gHC_INTERNAL_BASE (fsLit "++") appendIdKey assertName = varQual gHC_INTERNAL_BASE (fsLit "assert") assertIdKey fromStringName = varQual gHC_INTERNAL_DATA_STRING (fsLit "fromString") fromStringClassOpKey @@ -2376,6 +2379,9 @@ leftSectionKey, rightSectionKey :: Unique leftSectionKey = mkPreludeMiscIdUnique 45 rightSectionKey = mkPreludeMiscIdUnique 46 +concatMapIdKey :: Unique +concatMapIdKey = mkPreludeMiscIdUnique 47 + rootMainKey, runMainKey :: Unique rootMainKey = mkPreludeMiscIdUnique 101 runMainKey = mkPreludeMiscIdUnique 102 ===================================== compiler/GHC/Core/Make.hs ===================================== @@ -37,7 +37,7 @@ module GHC.Core.Make ( -- * Constructing list expressions mkNilExpr, mkConsExpr, mkListExpr, - mkFoldrExpr, mkBuildExpr, + mkFoldrExpr, mkBuildExpr, mkConcatMapExpr, -- * Constructing Maybe expressions mkNothingExpr, mkJustExpr, @@ -796,6 +796,11 @@ mkFoldrExpr elt_ty result_ty c n list = do `App` n `App` list) +mkConcatMapExpr :: MonadThings m => Type -> Type -> CoreExpr -> CoreExpr -> m CoreExpr +mkConcatMapExpr src_ty tgt_ty f xs = do + concatMap_id <- lookupId concatMapName + return (Var concatMap_id `App` Type src_ty `App` Type tgt_ty `App` f `App` xs) + -- | Make a 'build' expression applied to a locally-bound worker function mkBuildExpr :: (MonadFail m, MonadThings m, MonadUnique m) => Type -- ^ Type of list elements to be built ===================================== compiler/GHC/Core/Rules.hs ===================================== @@ -56,7 +56,7 @@ import GHC.Core.Ppr ( pprRules ) import GHC.Core.Unify as Unify ( ruleMatchTyKiX ) import GHC.Core.Type as Type ( Type, extendTvSubst, extendCvSubst - , substTy, getTyVar_maybe ) + , substTy, getTyVar_maybe, tyCoVarsOfType ) import GHC.Core.TyCo.Ppr( pprParendType ) import GHC.Core.Coercion as Coercion import GHC.Core.Tidy ( tidyRules ) @@ -696,12 +696,16 @@ matchRule opts rule_env _is_active fn args _rough_args Nothing -> Nothing Just expr -> Just expr -matchRule _ rule_env is_active _ args rough_args +matchRule _ rule_env is_active _fn args rough_args (Rule { ru_name = rule_name, ru_act = act, ru_rough = tpl_tops , ru_bndrs = tpl_vars, ru_args = tpl_args, ru_rhs = rhs }) | not (is_active act) = Nothing | ruleCantMatch tpl_tops rough_args = Nothing - | otherwise = matchN rule_env rule_name tpl_vars tpl_args args rhs + | otherwise = + case matchN rule_env rule_name tpl_vars tpl_args args rhs of + Just x -> -- pprTrace "match found:" (ppr rule_name <+> ppr _fn <+> ppr args) True + Just x + Nothing -> Nothing --------------------------------------- @@ -1046,9 +1050,9 @@ tryFloatIn :: CoreExpr -> Maybe CoreExpr tryFloatIn = go emptyVarSet False id where go vs _ c (Let bind e) = go (extendVarSetList vs (bindersOf bind)) True (c . Let bind) e go vs _ c (Case scrut case_bndr ty [Alt con alt_bndrs rhs]) = go (extendVarSetList vs alt_bndrs) True (c . (\x -> Case scrut case_bndr (exprType x) [Alt con alt_bndrs x])) rhs - go vs True c (App e1 e2) = App <$> go vs True c e1 <*> pure (c e2) - go vs True c e@(Var v) | not (v `elemVarSet` vs) = Just e - go vs True _ e at Type{} = Just e + go vs True c (App e1 e2) = App <$> go vs True c e1 <*> Just (c e2) + go vs True _ e@(Var v) | not (v `elemVarSet` vs) = Just e + go vs True _ e@(Type ty) | isEmptyVarSet (tyCoVarsOfType ty `intersectVarSet` vs) = Just e go vs True _ e at Lit{} = Just e go _ _ _ _ = Nothing ===================================== compiler/GHC/HsToCore/ListComp.hs ===================================== @@ -61,7 +61,7 @@ dsListComp lquals res_ty = do || isParallelComp quals -- Foldr-style desugaring can't handle parallel list comprehensions then deListComp quals (mkNilExpr elt_ty) - else mkBuildExpr elt_ty (\(c, _) (n, _) -> dfListComp c n quals) + else dfListComp elt_ty quals -- Foldr/build should be enabled, so desugar -- into foldrs and builds @@ -305,78 +305,73 @@ deBindComp pat core_list1 quals core_list2 = do @dfListComp@ are the rules used with foldr/build turned on: \begin{verbatim} -TE[ e | ] c n = c e n -TE[ e | b , q ] c n = if b then TE[ e | q ] c n else n -TE[ e | p <- l , q ] c n = let - f = \ x b -> case x of - p -> TE[ e | q ] c b - _ -> b - in - foldr f n l +TE[ e | ] = [e] +TE[ e | b , q ] = if b then TE[ e | q ] else [] +TE[ e | p <- l , q ] = concatMap (\x -> case x of + p -> TE[ e | q ] + _ -> []) l \end{verbatim} -} -dfListComp :: Id -> Id -- 'c' and 'n' +dfListComp :: Type -- element type -> [ExprStmt GhcTc] -- the rest of the qual's -> DsM CoreExpr -dfListComp _ _ [] = panic "dfListComp" +dfListComp _ [] = panic "dfListComp" -dfListComp c_id n_id (LastStmt _ body _ _ : quals) +dfListComp elt_ty (LastStmt _ body _ _ : quals) = assert (null quals) $ do { core_body <- dsLExpr body - ; return (mkApps (Var c_id) [core_body, Var n_id]) } + ; return (mkListExpr elt_ty [core_body]) } -- Non-last: must be a guard -dfListComp c_id n_id (BodyStmt _ guard _ _ : quals) = do +dfListComp elt_ty (BodyStmt _ guard _ _ : quals) = do core_guard <- dsLExpr guard - core_rest <- dfListComp c_id n_id quals - return (mkIfThenElse core_guard core_rest (Var n_id)) + core_rest <- dfListComp elt_ty quals + return (mkIfThenElse core_guard core_rest (mkListExpr elt_ty [])) -dfListComp c_id n_id (LetStmt _ binds : quals) = do +dfListComp elt_ty (LetStmt _ binds : quals) = do -- new in 1.3, local bindings - core_rest <- dfListComp c_id n_id quals + core_rest <- dfListComp elt_ty quals dsLocalBinds binds core_rest -dfListComp c_id n_id (stmt@(TransStmt {}) : quals) = do +dfListComp elt_ty (stmt@(TransStmt {}) : quals) = do (inner_list_expr, pat) <- dsTransStmt stmt -- Anyway, we bind the newly grouped list via the generic binding function - dfBindComp c_id n_id (pat, inner_list_expr) quals + dfBindComp elt_ty (pat, inner_list_expr) quals -dfListComp c_id n_id (BindStmt _ pat list1 : quals) = do +dfListComp elt_ty (BindStmt _ pat list1 : quals) = do -- evaluate the two lists core_list1 <- dsLExpr list1 -- Do the rest of the work in the generic binding builder - dfBindComp c_id n_id (pat, core_list1) quals + dfBindComp elt_ty (pat, core_list1) quals -dfListComp _ _ (ParStmt {} : _) = panic "dfListComp ParStmt" -dfListComp _ _ (RecStmt {} : _) = panic "dfListComp RecStmt" -dfListComp _ _ (XStmtLR ApplicativeStmt {} : _) = +dfListComp _ (ParStmt {} : _) = panic "dfListComp ParStmt" +dfListComp _ (RecStmt {} : _) = panic "dfListComp RecStmt" +dfListComp _ (XStmtLR ApplicativeStmt {} : _) = panic "dfListComp ApplicativeStmt" -dfBindComp :: Id -> Id -- 'c' and 'n' +dfBindComp :: Type -- element type -> (LPat GhcTc, CoreExpr) -> [ExprStmt GhcTc] -- the rest of the qual's -> DsM CoreExpr -dfBindComp c_id n_id (pat, core_list1) quals = do +dfBindComp elt_ty (pat, core_list1) quals = do -- find the required type let x_ty = hsLPatType pat - let b_ty = idType n_id -- create some new local id's - b <- newSysLocalDs ManyTy b_ty x <- newSysLocalDs ManyTy x_ty -- build rest of the comprehension - core_rest <- dfListComp c_id b quals + core_rest <- dfListComp elt_ty quals -- build the pattern match core_expr <- matchSimply (Var x) (StmtCtxt (HsDoStmt ListComp)) ManyTy - pat core_rest (Var b) + pat core_rest (mkListExpr elt_ty []) -- now build the outermost foldr, and return - mkFoldrExpr x_ty b_ty (mkLams [x, b] core_expr) (Var n_id) core_list1 + mkConcatMapExpr x_ty elt_ty (mkLams [x] core_expr) core_list1 {- ************************************************************************ ===================================== libraries/ghc-internal/src/GHC/Internal/Base.hs ===================================== @@ -346,6 +346,229 @@ infixl 4 <*>, <*, *>, <**> default () -- Double isn't available yet +data Stream a = forall s. Stream (s -> Step s a) !s +data Step s a = Yield a !s | Skip !s | Done + +unstream :: Stream a -> [a] +unstream (Stream next s0) = go s0 where + go !s = case next s of + Yield x s' -> x : go s' + Skip s' -> go s' + Done -> [] +{-# INLINE [1] unstream #-} + +-- This changes an unstream into a cheapUnstream, which means GHC will be free +-- to duplicate the list producing stream. +cheap :: [a] -> [a] +cheap x = x +{-# INLINE [1] cheap #-} + +{-# RULES "cheap/unstream" forall x. cheap (unstream x) = cheapUnstream x #-} + +cheapUnstream :: Stream a -> [a] +cheapUnstream (Stream next s0) = go s0 where + go !s = case next s of + Yield x s' -> x : go s' + Skip s' -> go s' + Done -> [] +{-# INLINE CONLIKE [1] cheapUnstream #-} + +data Lazy a = L a + +streamNext :: Lazy [a] -> Step (Lazy [a]) a +streamNext (L []) = Done +streamNext (L (x:xs)) = Yield x (L xs) + +stream :: [a] -> Stream a +stream = Stream streamNext . L where +{-# INLINE [1] stream #-} + +{-# RULES +"unstream/stream" forall xs. unstream (stream xs) = xs +"cheapUnstream/stream" forall xs. cheapUnstream (stream xs) = xs +"stream/unstream" forall xs. stream (unstream xs) = xs +"stream/cheapUnstream" forall xs. stream (cheapUnstream xs) = xs +"stream/build" forall (f :: forall b. (a -> b -> b) -> b -> b). + stream (build f) = Stream streamNext (L (f (:) [])) + #-} + +data AppendState s1 s2 = AS1 !s1 | AS2 !s2 + +appendS :: Stream a -> Stream a -> Stream a +appendS (Stream next1 s01) (Stream next2 s02) = Stream next' (AS1 s01) where + next' (AS1 s1) = + case next1 s1 of + Yield x s1' -> Yield x (AS1 s1') + Skip s1' -> Skip (AS1 s1') + Done -> Skip (AS2 s02) + next' (AS2 s2) = + case next2 s2 of + Yield x s2' -> Yield x (AS2 s2') + Skip s2' -> Skip (AS2 s2') + Done -> Done + {-# INLINE next' #-} +{-# INLINE appendS #-} + +append1S :: Stream a -> [a] -> [a] +append1S (Stream next s0) xs = go s0 where + go !s = + case next s of + Yield x s' -> x : go s' + Skip s' -> go s' + Done -> xs +{-# INLINE [0] append1S #-} + +(++) :: [a] -> [a] -> [a] +(++) [] ys = ys +(++) (x:xs) ys = x : xs ++ ys +{-# NOINLINE [1] (++) #-} + +-- NOTE: This is quite subtle as we do not want to copy the last list in +-- +-- xs1 ++ xs2 ++ ... ++ xsn +-- +-- Indeed, we don't really want to fuse the above at all unless at least +-- one of the arguments has the form (unstream s) or the result of the +-- concatenation is streamed. The rules below do precisely that. Note they +-- really fuse instead of just rewriting things into a fusible form so there +-- is no need to rewrite back. + +{-# RULES +"++ -> fused on 1st arg" [~1] forall xs ys. + unstream xs ++ ys = append1S xs ys +"++ -> fused on 2nd arg" [~1] forall xs ys. + append1S xs (unstream ys) = unstream (appendS xs ys) +"++ -> fused (1)" [~1] forall xs ys. + stream (xs ++ ys) = appendS (stream xs) (stream ys) +"++ -> fused (2)" [~1] forall xs ys. + stream (append1S xs ys) = appendS xs (stream ys) + +"++ -> 1st arg empty" forall xs. + [] ++ xs = xs +"++ -> 2nd arg empty" forall xs. + xs ++ [] = xs +"++ / :" forall x xs ys. + (x:xs) ++ ys = x : (xs ++ ys) + #-} + +foldrS :: (a -> b -> b) -> b -> Stream a -> b +foldrS k z (Stream next s0) = go s0 where + go !s = + case next s of + Yield x s' -> k x (go s') + Skip s' -> go s' + Done -> z +{-# INLINE foldrS #-} + +foldr :: (a -> b -> b) -> b -> [a] -> b +foldr k z = foldrS k z . stream +{-# INLINE foldr #-} + +mapS :: (a -> b) -> Stream a -> Stream b +mapS f (Stream next s0) = Stream next' s0 where + next' !s = + case next s of + Yield x s' -> Yield (f x) s' + Skip s' -> Skip s' + Done -> Done + {-# INLINE next' #-} +{-# INLINE mapS #-} + +map :: (a -> b) -> [a] -> [b] +map f = unstream . mapS f . stream +{-# INLINE map #-} + +data ConcatMapState s a = ConcatMapState1 !s | forall is. ConcatMapState2 !s (is -> Step is a) !is + +concatMapS :: (a -> Stream b) -> Stream a -> Stream b +concatMapS f (Stream next s0) = Stream next' (ConcatMapState1 s0) + where + {-# INLINE next' #-} + next' (ConcatMapState1 s) = case next s of + Done -> Done + Skip s' -> Skip (ConcatMapState1 s') + Yield x s' -> + case f x of + Stream inext is0 -> Skip (ConcatMapState2 s' inext is0) + + next' (ConcatMapState2 s inext is) = case inext is of + Done -> Skip (ConcatMapState1 s) + Skip is' -> Skip (ConcatMapState2 s inext is') + Yield x is' -> Yield x (ConcatMapState2 s inext is') +{-# INLINE [0] concatMapS #-} + +-- {-# RULES +-- "concatMapS/singleton" forall f. concatMapS (\x -> stream [f x]) = mapS f +-- #-} + +data ConcatMap'State s1 a s2 = CM'S1 !s1 | CM'S2 !s1 a !s2 + +concatMapS' :: (a -> s -> Step s b) -> (a -> s) -> Stream a -> Stream b +concatMapS' next2 f (Stream next1 s0) = Stream next' (CM'S1 s0) + where + {-# INLINE next' #-} + next' (CM'S1 s) = case next1 s of + Done -> Done + Skip s' -> Skip (CM'S1 s') + Yield x s' -> Skip (CM'S2 s' x (f x)) + + next' (CM'S2 s a t) = case next2 a t of + Done -> Skip (CM'S1 s) + Skip t' -> Skip (CM'S2 s a t') + Yield x t' -> Yield x (CM'S2 s a t') +{-# INLINE concatMapS' #-} + +-- data ConcatMap''State s1 a s2 = CM''S1 !s1 | CM''S2 !s1 !s2 +-- +-- concatMapS'' :: (s -> Step s b) -> (a -> s) -> Stream a -> Stream b +-- concatMapS'' next2 f (Stream next1 s0) = Stream next (CM''S1 s0) +-- where +-- {-# INLINE next #-} +-- next (CM''S1 s) = case next1 s of +-- Done -> Done +-- Skip s' -> Skip (CM''S1 s') +-- Yield x s' -> Skip (CM''S2 s' (f x)) +-- +-- next (CM''S2 s t) = case next2 t of +-- Done -> Skip (CM''S1 s) +-- Skip t' -> Skip (CM''S2 s t') +-- Yield x t' -> Yield x (CM''S2 s t') +-- {-# INLINE concatMapS'' #-} + +-- {-# RULES +-- "concatMap" forall step f. concatMapS (\x -> Stream (step x) (f x)) = concatMapS' step f +-- #-} + +-- Shouldn't be necessary, because stream gets inlined anyway in phase 1 +-- "concatMap/stream" [1] forall f. concatMapS (\x -> stream (f x)) = concatMapS' (\_ -> streamStep) f + +-- | Map a function returning a list over a list and concatenate the results. +-- 'concatMap' can be seen as the composition of 'concat' and 'map'. +-- +-- > concatMap f xs == (concat . map f) xs +-- +-- ==== __Examples__ +-- +-- >>> concatMap (\i -> [-i,i]) [] +-- [] +-- +-- >>> concatMap (\i -> [-i, i]) [1, 2, 3] +-- [-1,1,-2,2,-3,3] +-- +-- >>> concatMap ('replicate' 3) [0, 2, 4] +-- [0,0,0,2,2,2,4,4,4] +concatMap :: (a -> [b]) -> [a] -> [b] +concatMap f = foldr ((++) . f) [] + +{-# NOINLINE [1] concatMap #-} + +{-# RULES +"concatMap" forall f . concatMap f = unstream . concatMapS (stream . f) . stream +-- "concatMap" forall f xs . concatMap f xs = +-- build (\c n -> foldr (\x b -> foldr c b (f x)) n xs) + #-} + + {- Note [Tracking dependencies on primitives] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1780,17 +2003,17 @@ The rest of the prelude list functions are in GHC.List. -- -- > foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...) -foldr :: (a -> b -> b) -> b -> [a] -> b --- foldr _ z [] = z --- foldr f z (x:xs) = f x (foldr f z xs) -{-# INLINE [0] foldr #-} --- Inline only in the final stage, after the foldr/cons rule has had a chance --- Also note that we inline it when it has *two* parameters, which are the --- ones we are keen about specialising! -foldr k z = go - where - go [] = z - go (y:ys) = y `k` go ys +-- foldr :: (a -> b -> b) -> b -> [a] -> b +-- -- foldr _ z [] = z +-- -- foldr f z (x:xs) = f x (foldr f z xs) +-- {-# INLINE [0] foldr #-} +-- -- Inline only in the final stage, after the foldr/cons rule has had a chance +-- -- Also note that we inline it when it has *two* parameters, which are the +-- -- ones we are keen about specialising! +-- foldr k z = go +-- where +-- go [] = z +-- go (y:ys) = y `k` go ys -- | A list producer that can be fused with 'foldr'. -- This function is merely @@ -1825,38 +2048,38 @@ augment :: forall a. (forall b. (a->b->b) -> b -> b) -> [a] -> [a] {-# INLINE [1] augment #-} augment g xs = g (:) xs -{-# RULES -"fold/build" forall k z (g::forall b. (a->b->b) -> b -> b) . - foldr k z (build g) = g k z - -"foldr/augment" forall k z xs (g::forall b. (a->b->b) -> b -> b) . - foldr k z (augment g xs) = g k (foldr k z xs) - -"foldr/id" foldr (:) [] = \x -> x -"foldr/app" [1] forall ys. foldr (:) ys = \xs -> xs ++ ys - -- Only activate this from phase 1, because that's - -- when we disable the rule that expands (++) into foldr - --- The foldr/cons rule looks nice, but it can give disastrously --- bloated code when compiling --- array (a,b) [(1,2), (2,2), (3,2), ...very long list... ] --- i.e. when there are very very long literal lists --- So I've disabled it for now. We could have special cases --- for short lists, I suppose. --- "foldr/cons" forall k z x xs. foldr k z (x:xs) = k x (foldr k z xs) - -"foldr/single" forall k z x. foldr k z [x] = k x z -"foldr/nil" forall k z. foldr k z [] = z - -"foldr/cons/build" forall k z x (g::forall b. (a->b->b) -> b -> b) . - foldr k z (x:build g) = k x (g k z) - -"augment/build" forall (g::forall b. (a->b->b) -> b -> b) - (h::forall b. (a->b->b) -> b -> b) . - augment g (build h) = build (\c n -> g c (h c n)) -"augment/nil" forall (g::forall b. (a->b->b) -> b -> b) . - augment g [] = build g - #-} +-- {-# RULES +-- "fold/build" forall k z (g::forall b. (a->b->b) -> b -> b) . +-- foldr k z (build g) = g k z +-- +-- "foldr/augment" forall k z xs (g::forall b. (a->b->b) -> b -> b) . +-- foldr k z (augment g xs) = g k (foldr k z xs) +-- +-- "foldr/id" foldr (:) [] = \x -> x +-- "foldr/app" [1] forall ys. foldr (:) ys = \xs -> xs ++ ys +-- -- Only activate this from phase 1, because that's +-- -- when we disable the rule that expands (++) into foldr +-- +-- -- The foldr/cons rule looks nice, but it can give disastrously +-- -- bloated code when compiling +-- -- array (a,b) [(1,2), (2,2), (3,2), ...very long list... ] +-- -- i.e. when there are very very long literal lists +-- -- So I've disabled it for now. We could have special cases +-- -- for short lists, I suppose. +-- -- "foldr/cons" forall k z x xs. foldr k z (x:xs) = k x (foldr k z xs) +-- +-- "foldr/single" forall k z x. foldr k z [x] = k x z +-- "foldr/nil" forall k z. foldr k z [] = z +-- +-- "foldr/cons/build" forall k z x (g::forall b. (a->b->b) -> b -> b) . +-- foldr k z (x:build g) = k x (g k z) +-- +-- "augment/build" forall (g::forall b. (a->b->b) -> b -> b) +-- (h::forall b. (a->b->b) -> b -> b) . +-- augment g (build h) = build (\c n -> g c (h c n)) +-- "augment/nil" forall (g::forall b. (a->b->b) -> b -> b) . +-- augment g [] = build g +-- #-} -- This rule is true, but not (I think) useful: -- augment g (augment h t) = augment (\cn -> g c (h c n)) t @@ -1883,13 +2106,13 @@ augment g xs = g (:) xs -- -- >>> map (\n -> 3 * n + 1) [1, 2, 3] -- [4,7,10] -map :: (a -> b) -> [a] -> [b] -{-# NOINLINE [0] map #-} - -- We want the RULEs "map" and "map/coerce" to fire first. - -- map is recursive, so won't inline anyway, - -- but saying so is more explicit, and silences warnings -map _ [] = [] -map f (x:xs) = f x : map f xs +-- map :: (a -> b) -> [a] -> [b] +-- {-# NOINLINE [0] map #-} +-- -- We want the RULEs "map" and "map/coerce" to fire first. +-- -- map is recursive, so won't inline anyway, +-- -- but saying so is more explicit, and silences warnings +-- map _ [] = [] +-- map f (x:xs) = f x : map f xs -- Note eta expanded mapFB :: (elt -> lst -> lst) -> (a -> elt) -> a -> lst -> lst @@ -1931,12 +2154,12 @@ The rules for map work like this. * Any similarity to the Functor laws for [] is expected. -} -{-# RULES -"map" [~1] forall f xs. map f xs = build (\c n -> foldr (mapFB c f) n xs) -"mapList" [1] forall f. foldr (mapFB (:) f) [] = map f -"mapFB" forall c f g. mapFB (mapFB c f) g = mapFB c (f.g) -"mapFB/id" forall c. mapFB c (\x -> x) = c - #-} +-- {-# RULES +-- "map" [~1] forall f xs. map f xs = build (\c n -> foldr (mapFB c f) n xs) +-- "mapList" [1] forall f. foldr (mapFB (:) f) [] = map f +-- "mapFB" forall c f g. mapFB (mapFB c f) g = mapFB c (f.g) +-- "mapFB/id" forall c. mapFB c (\x -> x) = c +-- #-} -- See Breitner, Eisenberg, Peyton Jones, and Weirich, "Safe Zero-cost -- Coercions for Haskell", section 6.5: @@ -1976,21 +2199,21 @@ The rules for map work like this. -- -- >>> [3, 2, 1] ++ [] -- [3,2,1] -(++) :: [a] -> [a] -> [a] -{-# NOINLINE [2] (++) #-} - -- Give time for the RULEs for (++) to fire in InitialPhase - -- It's recursive, so won't inline anyway, - -- but saying so is more explicit -(++) [] ys = ys -(++) (x:xs) ys = x : xs ++ ys +-- (++) :: [a] -> [a] -> [a] +-- {-# NOINLINE [2] (++) #-} +-- -- Give time for the RULEs for (++) to fire in InitialPhase +-- -- It's recursive, so won't inline anyway, +-- -- but saying so is more explicit +-- (++) [] ys = ys +-- (++) (x:xs) ys = x : xs ++ ys -{-# RULES -"++/literal" forall x. (++) (unpackCString# x) = unpackAppendCString# x -"++/literal_utf8" forall x. (++) (unpackCStringUtf8# x) = unpackAppendCStringUtf8# x #-} - -{-# RULES -"++" [~1] forall xs ys. xs ++ ys = augment (\c n -> foldr c n xs) ys - #-} +-- {-# RULES +-- "++/literal" forall x. (++) (unpackCString# x) = unpackAppendCString# x +-- "++/literal_utf8" forall x. (++) (unpackCStringUtf8# x) = unpackAppendCStringUtf8# x #-} +-- +-- {-# RULES +-- "++" [~1] forall xs ys. xs ++ ys = augment (\c n -> foldr c n xs) ys +-- #-} -- |'otherwise' is defined as the value 'True'. It helps to make @@ -2512,20 +2735,20 @@ iShiftRL# :: Int# -> Int# -> Int# a `iShiftRL#` b = (a `uncheckedIShiftRL#` b) `andI#` shift_mask WORD_SIZE_IN_BITS# b -- Rules for C strings (the functions themselves are now in GHC.CString) -{-# RULES -"unpack" [~1] forall a . unpackCString# a = build (unpackFoldrCString# a) -"unpack-list" [1] forall a . unpackFoldrCString# a (:) [] = unpackCString# a -"unpack-append" forall a n . unpackFoldrCString# a (:) n = unpackAppendCString# a n -"unpack-append-nil" forall a . unpackAppendCString# a [] = unpackCString# a - -"unpack-utf8" [~1] forall a . unpackCStringUtf8# a = build (unpackFoldrCStringUtf8# a) -"unpack-list-utf8" [1] forall a . unpackFoldrCStringUtf8# a (:) [] = unpackCStringUtf8# a -"unpack-append-utf8" forall a n . unpackFoldrCStringUtf8# a (:) n = unpackAppendCStringUtf8# a n -"unpack-append-nil-utf8" forall a . unpackAppendCStringUtf8# a [] = unpackCStringUtf8# a - --- There's a built-in rule (in GHC.Core.Op.ConstantFold) for --- unpackFoldr "foo" c (unpackFoldr "baz" c n) = unpackFoldr "foobaz" c n - --- See also the Note [String literals in GHC] in CString.hs - - #-} +-- {-# RULES +-- "unpack" [~1] forall a . unpackCString# a = build (unpackFoldrCString# a) +-- "unpack-list" [1] forall a . unpackFoldrCString# a (:) [] = unpackCString# a +-- "unpack-append" forall a n . unpackFoldrCString# a (:) n = unpackAppendCString# a n +-- "unpack-append-nil" forall a . unpackAppendCString# a [] = unpackCString# a +-- +-- "unpack-utf8" [~1] forall a . unpackCStringUtf8# a = build (unpackFoldrCStringUtf8# a) +-- "unpack-list-utf8" [1] forall a . unpackFoldrCStringUtf8# a (:) [] = unpackCStringUtf8# a +-- "unpack-append-utf8" forall a n . unpackFoldrCStringUtf8# a (:) n = unpackAppendCStringUtf8# a n +-- "unpack-append-nil-utf8" forall a . unpackAppendCStringUtf8# a [] = unpackCStringUtf8# a +-- +-- -- There's a built-in rule (in GHC.Core.Op.ConstantFold) for +-- -- unpackFoldr "foo" c (unpackFoldr "baz" c n) = unpackFoldr "foobaz" c n +-- +-- -- See also the Note [String literals in GHC] in CString.hs +-- +-- #-} ===================================== libraries/ghc-internal/src/GHC/Internal/Data/Foldable.hs ===================================== @@ -64,7 +64,7 @@ import GHC.Internal.Arr ( Array(..), elems, numElements, foldlElems, foldrElems, foldlElems', foldrElems', foldl1Elems, foldr1Elems) -import GHC.Internal.Base hiding ( foldr ) +import GHC.Internal.Base hiding ( foldr , concatMap ) import GHC.Internal.Generics import GHC.Tuple (Solo (..)) import GHC.Internal.Num ( Num(..) ) ===================================== libraries/ghc-internal/src/GHC/Internal/Enum.hs ===================================== @@ -32,6 +32,7 @@ module GHC.Internal.Enum( ) where import GHC.Internal.Base hiding ( many ) +import GHC.Internal.List (eftInt) import GHC.Internal.Char import GHC.Num.Integer import GHC.Internal.Num @@ -610,15 +611,15 @@ instance Enum Int where * Phase 0: optionally inline eftInt -} -{-# NOINLINE [1] eftInt #-} -eftInt :: Int# -> Int# -> [Int] --- [x1..x2] -eftInt x0 y | isTrue# (x0 ># y) = [] - | otherwise = go x0 - where - go x = I# x : if isTrue# (x ==# y) - then [] - else go (x +# 1#) +-- {-# NOINLINE [1] eftInt #-} +-- eftInt :: Int# -> Int# -> [Int] +-- -- [x1..x2] +-- eftInt x0 y | isTrue# (x0 ># y) = [] +-- | otherwise = go x0 +-- where +-- go x = I# x : if isTrue# (x ==# y) +-- then [] +-- else go (x +# 1#) {-# INLINE [0] eftIntFB #-} -- See Note [Inline FB functions] in GHC.Internal.List eftIntFB :: (Int -> r -> r) -> r -> Int# -> Int# -> r ===================================== libraries/ghc-internal/src/GHC/Internal/IO/Handle/FD.hs ===================================== @@ -25,7 +25,7 @@ module GHC.Internal.IO.Handle.FD ( mkHandleFromFD, fdToHandle, fdToHandle', handleToFd ) where -import GHC.Internal.Base +import GHC.Internal.Base hiding (Stream) import GHC.Internal.Show import GHC.Internal.Control.Exception (try) import GHC.Internal.Data.Maybe ===================================== libraries/ghc-internal/src/GHC/Internal/List.hs ===================================== @@ -1,6 +1,6 @@ {-# LANGUAGE Trustworthy #-} -{-# LANGUAGE CPP, NoImplicitPrelude, ScopedTypeVariables #-} -{-# LANGUAGE BangPatterns #-} +{-# LANGUAGE CPP, NoImplicitPrelude, ScopedTypeVariables, ExistentialQuantification #-} +{-# LANGUAGE BangPatterns, MagicHash #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} ----------------------------------------------------------------------------- @@ -41,6 +41,9 @@ module GHC.Internal.List ( -- * GHC List fusion augment, build, + -- * Enumeration + eftInt, + ) where import GHC.Internal.Data.Maybe @@ -52,6 +55,927 @@ import GHC.Internal.Stack.Types (HasCallStack) infixl 9 !?, !! infix 4 `elem`, `notElem` +data Tuple a b = !a :!: !b +data Option a = None | Some !a + +eftIntS :: Int# -> Int# -> Stream Int +eftIntS x y = Stream next (I# x) where + next !s + | s <= I# y = Yield s (s + 1) + | otherwise = Done + {-# INLINE next #-} +{-# INLINE eftIntS #-} + +eftInt :: Int# -> Int# -> [Int] +eftInt = \x y -> cheapUnstream (eftIntS x y) +{-# INLINE eftInt #-} + +-- unfoldrS :: (a -> Maybe (a, b)) -> a -> Stream b +-- unfoldrS f x0 = Stream next x0 where +-- next s = +-- case f s of +-- Just (s', x) -> Yield x s' +-- Nothing -> Done +-- {-# INLINE next #-} +-- {-# INLINE unfoldrS #-} + +data ZipState s1 a s2 + = ZipState1 !s1 !s2 + | ZipState2 !s1 a !s2 + +zipS :: Stream a -> Stream b -> Stream (a, b) +zipS (Stream next1 s01) (Stream next2 s02) = Stream next' (ZipState1 s01 s02) where + next' (ZipState1 s1 s2) = + case next1 s1 of + Yield x s1' -> + case next2 s2 of + Yield y s2' -> + Yield (x, y) (ZipState1 s1' s2') + Skip s2' -> Skip (ZipState2 s1' x s2') + Done -> Done + Skip s1' -> Skip (ZipState1 s1' s2) + Done -> Done + next' (ZipState2 s1' x s2) = + case next2 s2 of + Yield y s2' -> Yield (x, y) (ZipState1 s1' s2') + Skip s2' -> Skip (ZipState2 s1' x s2') + Done -> Done + {-# INLINE next' #-} +{-# INLINE zipS #-} + +data Zip3State s1 a s2 b s3 + = Zip3State1 !s1 !s2 !s3 + | Zip3State2 !s1 a !s2 !s3 + | Zip3State3 !s1 a !s2 b !s3 + +zip3S :: Stream a -> Stream b -> Stream c -> Stream (a, b, c) +zip3S (Stream next1 s01) (Stream next2 s02) (Stream next3 s03) = Stream next' (Zip3State1 s01 s02 s03) where + next' (Zip3State1 s1 s2 s3) = + case next1 s1 of + Yield x s1' -> + case next2 s2 of + Yield y s2' -> + case next3 s3 of + Yield z s3' -> Yield (x, y, z) (Zip3State1 s1' s2' s3') + Skip s3' -> Skip (Zip3State3 s1' x s2' y s3') + Done -> Done + Skip s2' -> Skip (Zip3State2 s1' x s2' s3) + Done -> Done + Skip s1' -> Skip (Zip3State1 s1' s2 s3) + Done -> Done + next' (Zip3State2 s1' x s2 s3) = + case next2 s2 of + Yield y s2' -> + case next3 s3 of + Yield z s3' -> Yield (x,y,z) (Zip3State1 s1' s2' s3') + Skip s3' -> Skip (Zip3State3 s1' x s2' y s3') + Done -> Done + Skip s2' -> Skip (Zip3State2 s1' x s2' s3) + Done -> Done + next' (Zip3State3 s1' x s2' y s3) = + case next3 s3 of + Yield z s3' -> Yield (x,y,z) (Zip3State1 s1' s2' s3') + Skip s3' -> Skip (Zip3State3 s1' x s2' y s3') + Done -> Done + {-# INLINE next' #-} +{-# INLINE zip3S #-} + +zipWithS :: (a -> b -> c) -> Stream a -> Stream b -> Stream c +zipWithS f (Stream next1 s01) (Stream next2 s02) = Stream next' (ZipState1 s01 s02) where + next' (ZipState1 s1 s2) = + case next1 s1 of + Yield x s1' -> + case next2 s2 of + Yield y s2' -> + Yield (f x y) (ZipState1 s1' s2') + Skip s2' -> Skip (ZipState2 s1' x s2') + Done -> Done + Skip s1' -> Skip (ZipState1 s1' s2) + Done -> Done + next' (ZipState2 s1' x s2) = + case next2 s2 of + Yield y s2' -> Yield (f x y) (ZipState1 s1' s2') + Skip s2' -> Skip (ZipState2 s1' x s2') + Done -> Done + {-# INLINE next' #-} +{-# INLINE zipWithS #-} + +zipWith3S :: (a -> b -> c -> d) -> Stream a -> Stream b -> Stream c -> Stream d +zipWith3S f (Stream next1 s01) (Stream next2 s02) (Stream next3 s03) = Stream next' (Zip3State1 s01 s02 s03) where + next' (Zip3State1 s1 s2 s3) = + case next1 s1 of + Yield x s1' -> + case next2 s2 of + Yield y s2' -> + case next3 s3 of + Yield z s3' -> Yield (f x y z) (Zip3State1 s1' s2' s3') + Skip s3' -> Skip (Zip3State3 s1' x s2' y s3') + Done -> Done + Skip s2' -> Skip (Zip3State2 s1' x s2' s3) + Done -> Done + Skip s1' -> Skip (Zip3State1 s1' s2 s3) + Done -> Done + next' (Zip3State2 s1' x s2 s3) = + case next2 s2 of + Yield y s2' -> + case next3 s3 of + Yield z s3' -> Yield (f x y z) (Zip3State1 s1' s2' s3') + Skip s3' -> Skip (Zip3State3 s1' x s2' y s3') + Done -> Done + Skip s2' -> Skip (Zip3State2 s1' x s2' s3) + Done -> Done + next' (Zip3State3 s1' x s2' y s3) = + case next3 s3 of + Yield z s3' -> Yield (f x y z) (Zip3State1 s1' s2' s3') + Skip s3' -> Skip (Zip3State3 s1' x s2' y s3') + Done -> Done + {-# INLINE next' #-} +{-# INLINE zipWith3S #-} + +-- unzipS :: Stream (a, b) -> (Stream a, Stream b) +-- unzipS s = (mapS fst s, mapS snd s) +-- {-# INLINE unzipS #-} + +unzipS :: Stream (a, b) -> ([a], [b]) +unzipS (Stream next s0) = go s0 where + go s = + case next s of + Yield (x, y) s' -> let (xs, ys) = go s' in (x:xs, y:ys) + Skip s' -> go s' + Done -> ([], []) +{-# INLINE unzipS #-} + +-- unzip3S :: Stream (a, b, c) -> (Stream a, Stream b, Stream c) +-- unzip3S s = (mapS (\(x,_,_) -> x) s, mapS (\(_,x,_) -> x) s, mapS (\(_,_,x) -> x) s) +-- {-# INLINE unzip3S #-} + +unzip3S :: Stream (a, b, c) -> ([a], [b], [c]) +unzip3S (Stream next s0) = go s0 where + go !s = + case next s of + Yield (x, y, z) s' -> let (xs, ys, zs) = go s' in (x:xs, y:ys, z:zs) + Skip s' -> go s' + Done -> ([], [], []) +{-# INLINE unzip3S #-} + +foldrS' :: (a -> b -> b) -> b -> Stream a -> b +foldrS' k z (Stream next s0) = go s0 where + go !s = + case next s of + Yield x s' -> k x $! go s' + Skip s' -> go s' + Done -> z +{-# INLINE foldrS' #-} + +foldr1S :: (a -> a -> a) -> Stream a -> a +foldr1S f (Stream next s0) = go1 s0 where + go1 !s = + case next s of + Yield x s' -> go2 x s' + Skip s' -> go1 s' + Done -> errorEmptyList "foldr1" + go2 x !s = + case next s of + Yield y s' -> f x (go2 y s') + Skip s' -> go2 x s' + Done -> x +{-# INLINE foldr1S #-} + +nullS :: Stream a -> Bool +nullS (Stream next s0) = go s0 where + go !s = + case next s of + Yield{} -> False + Skip s' -> go s' + Done -> True +{-# INLINE nullS #-} + +lengthS :: Stream a -> Int +lengthS (Stream next s0) = go 0 s0 where + go !n !s = + case next s of + Yield _ s' -> go (n + 1) s' + Skip s' -> go n s' + Done -> n +{-# INLINE lengthS #-} + +elemS :: Eq a => a -> Stream a -> Bool +elemS x0 (Stream next s0) = go s0 where + go s = + case next s of + Yield x s' -> x == x0 || go s' + Skip s' -> go s' + Done -> False +{-# INLINE elemS #-} + +notElemS :: Eq a => a -> Stream a -> Bool +notElemS x0 (Stream next s0) = go s0 where + go s = + case next s of + Yield x s' -> x /= x0 && go s' + Skip s' -> go s' + Done -> True +{-# INLINE notElemS #-} + +maximumS :: Ord a => Stream a -> a +maximumS (Stream next s0) = go1 s0 where + go1 !s = + case next s of + Yield x s' -> go2 x s' + Skip s' -> go1 s' + Done -> errorEmptyList "maximum" + go2 x !s = + case next s of + Yield y s' + | y > x -> go2 y s' + | otherwise -> go2 x s' + Skip s' -> go2 x s' + Done -> x +{-# INLINE maximumS #-} + +minimumS :: Ord a => Stream a -> a +minimumS (Stream next s0) = go1 s0 where + go1 !s = + case next s of + Yield x s' -> go2 x s' + Skip s' -> go1 s' + Done -> errorEmptyList "minimum" + go2 x !s = + case next s of + Yield y s' + | y < x -> go2 y s' + | otherwise -> go2 x s' + Skip s' -> go2 x s' + Done -> x +{-# INLINE minimumS #-} + +takeS :: Int -> Stream a -> Stream a +takeS n (Stream next s0) = Stream next' (s0 :!: n) where + next' (_ :!: 0) = Done + next' (s :!: i) = + case next s of + Yield x s' -> Yield x (s' :!: (i - 1)) + Skip s' -> Skip (s' :!: i) + Done -> Done + {-# INLINE next' #-} +{-# INLINE takeS #-} + +-- dropS :: Int -> Stream a -> Stream a +-- dropS n (Stream next s0) = Stream next (f n s0) where +-- f i s +-- | i <= 0 = s +-- | otherwise = +-- case next s of +-- Yield _ s' -> f (i - 1) s' +-- Skip s' -> f i s' +-- Done -> s +-- {-# INLINE dropS #-} + +dropS :: Int -> Stream a -> Stream a +dropS n (Stream next s0) = Stream next' (n :!: s0) where + next' (i :!: s) + | i > 0 = + case next s of + Yield _ s' -> Skip ((i - 1) :!: s') + Skip s' -> Skip (i :!: s') + Done -> Done + | otherwise = + case next s of + Yield x s' -> Yield x (i :!: s') + Skip s' -> Skip (i :!: s') + Done -> Done + {-# INLINE next' #-} +{-# INLINE dropS #-} + +cheapSplitAtS :: Int -> Stream a -> ([a], [a]) +cheapSplitAtS n s = (cheapUnstream (takeS n s), cheapUnstream (dropS n s)) +{-# INLINE cheapSplitAtS #-} + +splitAtS :: Int -> Stream a -> ([a], [a]) +splitAtS n (Stream next s0) = go1 n s0 where + go1 !i !s + | i > 0 = + case next s of + Yield x s' -> let (xs,ys) = go1 (i - 1) s' in (x : xs, ys) + Skip s' -> go1 i s' + Done -> ([], []) + | otherwise = ([], go2 s) + go2 !s = + case next s of + Yield x s' -> x : go2 s' + Skip s' -> go2 s' + Done -> [] +{-# INLINE splitAtS #-} + +takeWhileS :: (a -> Bool) -> Stream a -> Stream a +takeWhileS p (Stream next s0) = Stream next' s0 where + next' !s = + case next s of + Yield x s' + | p x -> Yield x s' + | otherwise -> Done + Skip s' -> Skip s' + Done -> Done +{-# INLINE takeWhileS #-} + +dropWhileS :: (a -> Bool) -> Stream a -> Stream a +dropWhileS p (Stream next s0) = Stream next' (True :!: s0) where + next' (True :!: s) = + case next s of + Yield x s' + | p x -> Skip (True :!: s') + | otherwise -> Yield x (False :!: s') + Skip s' -> Skip (True :!: s') + Done -> Done + next' (False :!: s) = + case next s of + Yield x s' -> Yield x (False :!: s') + Skip s' -> Skip (False :!: s') + Done -> Done + {-# INLINE next' #-} +{-# INLINE dropWhileS #-} + +-- nubS :: Eq a => Stream a -> Stream a +-- nubS (Stream next s0) = Stream next' ([] :!: s0) where +-- next' (xs :!: s) = +-- case next s of +-- Yield x s' +-- | x `elem` xs -> Skip (xs :!: s') +-- | otherwise -> Yield x ((x : xs) :!: s') +-- Skip s' -> Skip (xs :!: s') +-- Done -> Done +-- {-# INLINE next' #-} +-- {-# INLINE nubS #-} + +-- spanS :: (a -> Bool) -> Stream a -> (Stream a, Stream a) +-- spanS f s = (takeWhileS f s, dropWhileS f s) +-- {-# INLINE spanS #-} + +spanS :: (a -> Bool) -> Stream a -> ([a], [a]) +spanS p (Stream next s0) = go1 s0 where + go1 !s = + case next s of + Yield x s' + | p x -> let (xs, ys) = go1 s' in (x : xs, ys) + | otherwise -> ([], x : go2 s') + Skip s' -> go1 s' + Done -> ([],[]) + go2 !s = + case next s of + Yield x s' -> x : go2 s' + Skip s' -> go2 s' + Done -> [] +{-# INLINE spanS #-} + +breakS :: (a -> Bool) -> Stream a -> ([a], [a]) +breakS f = spanS (not . f) +{-# INLINE breakS #-} + +reverseS :: Stream a -> [a] +reverseS = foldlS' (flip (:)) [] +{-# INLINE reverseS #-} + +foldlS :: (b -> a -> b) -> b -> Stream a -> b +foldlS k z (Stream next s0) = go z s0 where + go acc !s = + case next s of + Yield x s' -> go (k acc x) s' + Skip s' -> go acc s' + Done -> acc +{-# INLINE foldlS #-} + +foldlS' :: (b -> a -> b) -> b -> Stream a -> b +foldlS' k z (Stream next s0) = go z s0 where + go !acc !s = + case next s of + Yield x s' -> go (k acc x) s' + Skip s' -> go acc s' + Done -> acc +{-# INLINE foldlS' #-} + +foldl1S :: (a -> a -> a) -> Stream a -> a +foldl1S f (Stream next s0) = go1 s0 where + go1 !s = + case next s of + Yield x s' -> go2 x s' + Skip s' -> go1 s' + Done -> errorEmptyList "foldl1" + go2 acc !s = + case next s of + Yield x s' -> go2 (f acc x) s' + Skip s' -> go2 acc s' + Done -> acc +{-# INLINE foldl1S #-} + +-- consumer +sumS :: Num a => Stream a -> a +sumS (Stream next s0) = go 0 s0 where + go !acc !s = case next s of + Done -> acc + Skip s' -> go acc s' + Yield x s' -> go (acc + x) s' +{-# INLINE sumS #-} + +productS :: Num a => Stream a -> a +productS (Stream next s0) = go 1 s0 where + go !acc !s = case next s of + Done -> acc + Skip s' -> go acc s' + Yield x s' -> go (acc * x) s' +{-# INLINE productS #-} + +andS :: Stream Bool -> Bool +andS (Stream next s0) = go True s0 where + go !acc !s = case next s of + Done -> acc + Skip s' -> go acc s' + Yield x s' -> go (acc && x) s' +{-# INLINE andS #-} + +orS :: Stream Bool -> Bool +orS (Stream next s0) = go False s0 where + go !acc !s = case next s of + Done -> acc + Skip s' -> go acc s' + Yield x s' -> go (acc || x) s' +{-# INLINE orS #-} + +anyS :: (a -> Bool) -> Stream a -> Bool +anyS p (Stream next s0) = go False s0 where + go !acc !s = case next s of + Done -> acc + Skip s' -> go acc s' + Yield x s' -> go (acc || p x) s' +{-# INLINE anyS #-} + +allS :: (a -> Bool) -> Stream a -> Bool +allS f (Stream next s0) = go True s0 where + go !acc !s = case next s of + Done -> acc + Skip s' -> go acc s' + Yield x s' -> go (acc && f x) s' +{-# INLINE allS #-} + +foldl1S' :: (a -> a -> a) -> Stream a -> a +foldl1S' f (Stream next s0) = go1 s0 where + go1 !s = + case next s of + Yield x s' -> go2 x s' + Skip s' -> go1 s' + Done -> errorEmptyList "foldl1" + go2 !acc !s = + case next s of + Yield x s' -> go2 (f acc x) s' + Skip s' -> go2 acc s' + Done -> acc +{-# INLINE foldl1S' #-} + +filterS :: (a -> Bool) -> Stream a -> Stream a +filterS p (Stream next s0) = Stream next' s0 where + next' !s = + case next s of + Yield x s' + | p x -> Yield x s' + | otherwise -> Skip s' + Skip s' -> Skip s' + Done -> Done + {-# INLINE next' #-} +{-# INLINE filterS #-} + +lookupS :: Eq a => a -> Stream (a, b) -> Maybe b +lookupS x0 (Stream next s0) = go s0 where + go !s = + case next s of + Yield (x,y) s' + | x0 == x -> Just y + | otherwise -> go s' + Skip s' -> go s' + Done -> Nothing +{-# INLINE lookupS #-} + +-- findS :: (a -> Bool) -> Stream a -> Maybe a +-- findS p (Stream next s0) = go s0 where +-- go !s = +-- case next s of +-- Yield x s' +-- | p x -> Just x +-- | otherwise -> go s' +-- Skip s' -> go s' +-- Done -> Nothing +-- {-# INLINE findS #-} +-- +-- findIndexS :: (a -> Bool) -> Stream a -> Maybe Int +-- findIndexS p (Stream next s0) = go 0 s0 where +-- go !i !s = +-- case next s of +-- Yield x s' +-- | p x -> Just i +-- | otherwise -> go (i + 1) s' +-- Skip s' -> go i s' +-- Done -> Nothing +-- {-# INLINE findIndexS #-} + +headS :: Stream a -> a +headS (Stream next s0) = go s0 where + go !s = + case next s of + Yield x _ -> x + Skip s' -> go s' + Done -> errorEmptyList "head" +{-# INLINE headS #-} + +lastS :: Stream a -> a +lastS (Stream next s0) = go1 s0 where + go1 !s = + case next s of + Yield x s' -> go2 x s' + Skip s' -> go1 s' + Done -> errorEmptyList "last" + go2 x !s = + case next s of + Yield x' s' -> go2 x' s' + Skip s' -> go2 x s' + Done -> x +{-# INLINE lastS #-} + +-- tailS :: Stream a -> Stream a +-- tailS (Stream next s0) = Stream next (tailF s0) where +-- tailF !s = +-- case next s of +-- Yield _ s' -> s' +-- Skip s' -> tailF s' +-- Done -> errorEmptyList "tail" +-- +-- initS1 :: Stream a -> Stream a +-- initS1 (Stream next s0) = Stream next' (f s0) where +-- f !s = +-- case next s of +-- Yield x s' -> x :!: s' +-- Skip s' -> f s' +-- Done -> errorEmptyList "init" +-- next' (x :!: s) = +-- case next s of +-- Yield y s' -> Yield x (y :!: s') +-- Skip s' -> Skip (x :!: s') +-- Done -> Done +-- {-# INLINE initS1 #-} + +initS :: Stream a -> Stream a +initS (Stream next s0) = Stream next' (Nothing :!: s0) where + next' (Nothing :!: s) = + case next s of + Yield x s' -> Skip (Just x :!: s') + Skip s' -> Skip (Nothing :!: s') + Done -> errorEmptyList "init" + next' (Just x :!: s) = + case next s of + Yield y s' -> Yield x (Just y :!: s') + Skip s' -> Skip (Just x :!: s') + Done -> Done +{-# INLINE initS #-} + +unconsS :: Stream a -> Maybe (a, [a]) +unconsS (Stream next s0) = go1 s0 where + go1 !s = + case next s of + Yield x s' -> Just (x, go2 s') + Skip s' -> go1 s' + Done -> Nothing + go2 !s = + case next s of + Yield x s' -> x : go2 s' + Skip s' -> go2 s' + Done -> [] +{-# INLINE unconsS #-} + +unsnocS :: Stream a -> Maybe ([a], a) +-- duplicates work: +-- unsnocS s = if nullS s then Nothing else Just (unstream (initS s), lastS s) +unsnocS = foldrS (\x xs -> case xs of Nothing -> Just ([], x); Just (ys,y) -> Just (x:ys,y)) Nothing +{-# INLINE unsnocS #-} + +indexHelperS :: Stream a -> Int -> Maybe a +indexHelperS (Stream next s0) i0 = go i0 s0 + where + go 0 !s = + case next s of + Yield x _ -> Just x + Skip s' -> go 0 s' + Done -> Nothing + go !i !s = + case next s of + Yield _ s' -> go (i - 1) s' + Skip s' -> go i s' + Done -> Nothing +{-# INLINE indexHelperS #-} + +unsafeIndexHelperS :: Stream a -> Int -> a +unsafeIndexHelperS (Stream next s0) i0 = go i0 s0 + where + go !i !s = + case next s of + Yield x s' -> if i == 0 then x else go (i - 1) s' + Skip s' -> go i s' + Done -> tooLarge i +{-# INLINE unsafeIndexHelperS #-} + +scanlS :: (b -> a -> b) -> b -> Stream a -> Stream b +scanlS k z (Stream next s0) = Stream next' (Just z :!: s0) where + next' (Just x :!: s) = + case next s of + Yield y s' -> Yield x (Just (k x y) :!: s') + Skip s' -> Skip (Just x :!: s') + Done -> Yield x (Nothing :!: s) + next' (Nothing :!: _) = Done + {-# INLINE next' #-} +{-# INLINE scanlS #-} + +data Scanl1State a s = Scanl1State1 !s | Scanl1State2 a !s | Scanl1State3 + +scanl1S :: (a -> a -> a) -> Stream a -> Stream a +scanl1S k (Stream next s0) = Stream next' (Scanl1State1 s0) where + next' (Scanl1State1 s) = + case next s of + Yield x s' -> Skip (Scanl1State2 x s') + Skip s' -> Skip (Scanl1State1 s') + Done -> errorEmptyList "scanl1" + next' (Scanl1State2 x s) = + case next s of + Yield y s' -> Yield x (Scanl1State2 (k x y) s') + Skip s' -> Skip (Scanl1State2 x s') + Done -> Yield x Scanl1State3 + next' Scanl1State3 = Done + {-# INLINE next' #-} +{-# INLINE scanl1S #-} + +scanlS' :: (b -> a -> b) -> b -> Stream a -> Stream b +scanlS' k z (Stream next s0) = Stream next' (Some (z :!: s0)) where + next' (Some (x :!: s)) = + case next s of + Yield y s' -> Yield x (Some (k x y :!: s')) + Skip s' -> Skip (Some (x :!: s')) + Done -> Yield x None + next' None = Done + {-# INLINE next' #-} +{-# INLINE scanlS' #-} + +iterateS :: (a -> a) -> a -> Stream a +iterateS f = Stream next . L where + next (L s) = Yield s (L (f s)) + {-# INLINE next #-} +{-# INLINE iterateS #-} + +iterateS' :: (a -> a) -> a -> Stream a +iterateS' f = Stream next where + next s = Yield s (f s) + {-# INLINE next #-} +{-# INLINE iterateS' #-} + +-- repeatS :: a -> Stream a +-- repeatS = Stream next . L where +-- next (L s) = Yield s (L s) +-- {-# INLINE next #-} +-- {-# INLINE repeatS #-} + +replicateS :: Int -> a -> Stream a +replicateS n x = Stream next n where + next s | s <= 0 = Done + | otherwise = Yield x (s - 1) + {-# INLINE next #-} +{-# INLINE replicateS #-} + +-- cycleS :: Stream a -> Stream a +-- cycleS (Stream next s0) = Stream next' s0 where +-- next' !s = +-- case next s of +-- Yield x s' -> Yield x s' +-- Skip s' -> Skip s' +-- Done -> Skip s0 +-- {-# INLINE cycleS #-} + +concatS :: Stream [a] -> Stream a +concatS (Stream next s0) = Stream next' (s0 :!: L []) where + next' (s :!: L []) = + case next s of + Yield [] s' -> Skip (s' :!: L []) + Yield (x:xs) s' -> Yield x (s' :!: L xs) + Skip s' -> Skip (s' :!: L []) + Done -> Done + next' (s :!: L (x:xs)) = Yield x (s :!: L xs) +{-# INLINE concatS #-} + +scanrS :: (a -> b -> b) -> b -> Stream a -> [b] +scanrS f q0 = foldrS (\x qs@(q:_) -> f x q : qs) [q0] +{-# INLINE scanrS #-} +scanr1S :: (a -> a -> a) -> Stream a -> [a] +scanr1S f = foldrS (\x qs -> case qs of [] -> [x]; (q:_) -> f x q : qs) [] +{-# INLINE scanr1S #-} + + +-- foldr' :: (a -> b -> b) -> b -> [a] -> b +-- foldr' k z = foldrS' k z . stream +-- {-# INLINE foldr' #-} +-- foldr1 :: (a -> a -> a) -> [a] -> a +-- foldr1 k = foldr1S k . stream +-- {-# INLINE foldr1 #-} +-- +-- foldl :: (b -> a -> b) -> b -> [a] -> b +-- foldl k z = foldlS k z . stream +-- {-# INLINE foldl #-} +-- foldl' :: (b -> a -> b) -> b -> [a] -> b +-- foldl' k z = foldlS' k z . stream +-- {-# INLINE foldl' #-} +-- foldl1 :: (a -> a -> a) -> [a] -> a +-- foldl1 k = foldl1S k . stream +-- {-# INLINE foldl1 #-} +-- +-- null :: [a] -> Bool +-- null = nullS . stream +-- {-# INLINE null #-} +-- length :: [a] -> Int +-- length = lengthS . stream +-- {-# INLINE length #-} +-- elem :: Eq a => a -> [a] -> Bool +-- elem x = elemS x . stream +-- {-# INLINE elem #-} +-- notElem :: Eq a => a -> [a] -> Bool +-- notElem x = notElemS x . stream +-- {-# INLINE notElem #-} +-- +-- maximum :: Ord a => [a] -> a +-- maximum = maximumS . stream +-- {-# INLINE maximum #-} +-- minimum :: Ord a => [a] -> a +-- minimum = minimumS . stream +-- {-# INLINE minimum #-} +-- sum :: Num a => [a] -> a +-- sum = sumS . stream +-- {-# INLINE sum #-} +-- product :: Num a => [a] -> a +-- product = productS . stream +-- {-# INLINE product #-} +-- and :: [Bool] -> Bool +-- and = andS . stream +-- {-# INLINE and #-} +-- or :: [Bool] -> Bool +-- or = orS . stream +-- {-# INLINE or #-} +-- any :: (a -> Bool) -> [a] -> Bool +-- any p = anyS p . stream +-- {-# INLINE any #-} +-- all :: (a -> Bool) -> [a] -> Bool +-- all p = allS p . stream +-- {-# INLINE all #-} +-- +-- foldl1' :: (a -> a -> a) -> [a] -> a +-- foldl1' f = foldl1S' f . stream +-- {-# INLINE foldl1' #-} +-- concat :: [[a]] -> [a] +-- concat = unstream . concatS . stream +-- {-# INLINE concat #-} +-- concatMap :: (a -> [b]) -> [a] -> [b] +-- concatMap f = unstream . concatMapS (stream . f) . stream +-- {-# INLINE concatMap #-} +-- +-- filter :: (a -> Bool) -> [a] -> [a] +-- filter p = unstream . filterS p . stream +-- {-# INLINE filter #-} +-- lookup :: Eq a => a -> [(a, b)] -> Maybe b +-- lookup x = lookupS x . stream +-- {-# INLINE lookup #-} +-- +-- head :: [a] -> a +-- head = headS . stream +-- {-# INLINE head #-} +-- last :: [a] -> a +-- last = lastS . stream +-- {-# INLINE last #-} +-- tail :: [a] -> [a] +-- -- destoys sharing: +-- -- tail = unstream . tailS . stream +-- tail [] = errorEmptyList "tail" +-- tail (_:xs) = xs +-- {-# INLINE tail #-} +-- init :: [a] -> [a] +-- init = unstream . initS . stream +-- {-# INLINE init #-} +-- uncons :: [a] -> Maybe (a, [a]) +-- uncons [] = Nothing +-- uncons (x:xs) = Just (x, xs) +-- {-# NOINLINE [1] uncons #-} +-- -- {-# RULES "uncons/stream" forall s. uncons (unstream s) = unconsS s #-} +-- -- {-# RULES "uncons/stream" forall s. uncons (cheapUnstream s) = unconsS s #-} +-- unsnoc :: [a] -> Maybe ([a], a) +-- unsnoc = unsnocS . stream +-- {-# INLINE unsnoc #-} +-- (!?) :: [a] -> Int -> Maybe a +-- xs !? i = indexS (stream xs) i +-- {-# INLINE (!?) #-} +-- (!!) :: [a] -> Int -> a +-- xs !! i = unsafeIndexS (stream xs) i +-- {-# INLINE (!!) #-} +-- +-- scanl :: (b -> a -> b) -> b -> [a] -> [b] +-- scanl k z = unstream . scanlS k z . stream +-- {-# INLINE scanl #-} +-- scanl1 :: (a -> a -> a) -> [a] -> [a] +-- scanl1 k = unstream . scanl1S k . stream +-- {-# INLINE scanl1 #-} +-- scanl' :: (b -> a -> b) -> b -> [a] -> [b] +-- scanl' k z = unstream . scanlS' k z . stream +-- {-# INLINE scanl' #-} +-- scanr :: (a -> b -> b) -> b -> [a] -> [b] +-- scanr f q0 = foldrS (\x qs@(q:_) -> f x q : qs) [q0] . stream +-- {-# INLINE scanr #-} +-- scanr1 :: (a -> a -> a) -> [a] -> [a] +-- scanr1 f = foldrS (\x qs -> case qs of [] -> [x]; (q:_) -> f x q : qs) [] . stream +-- {-# INLINE scanr1 #-} +-- +-- iterate :: (a -> a) -> a -> [a] +-- iterate f x = cheapUnstream (iterateS f x) +-- {-# INLINE iterate #-} +-- iterate' :: (a -> a) -> a -> [a] +-- iterate' f x = unstream (iterateS' f x) +-- {-# INLINE iterate' #-} +-- repeat :: a -> [a] +-- repeat x = let xs = x : xs in xs +-- -- repeat = cheapUnstream . repeatS +-- {-# INLINE repeat #-} +-- replicate :: Int -> a -> [a] +-- replicate n x = cheapUnstream (replicateS n x) +-- {-# INLINE replicate #-} +-- cycle :: [a] -> [a] +-- cycle xs = ys where ys = foldrS (:) ys (stream xs) +-- -- cycle = unstream . cycleS . stream +-- {-# INLINE cycle #-} +-- +-- take :: Int -> [a] -> [a] +-- take n = unstream . takeS n . stream +-- {-# INLINE take #-} +-- drop :: Int -> [a] -> [a] +-- drop 0 xs = xs +-- drop _ [] = [] +-- drop n (_:xs) = drop (n - 1) xs +-- {-# NOINLINE [1] drop #-} +-- -- {-# RULES "drop/stream" forall n s. drop n (unstream s) = unstream (dropS n s) #-} +-- -- {-# RULES "drop/stream" forall n s. drop n (cheapUnstream s) = cheapUnstream (dropS n s) #-} +-- +-- splitAt :: Int -> [a] -> ([a], [a]) +-- splitAt 0 xs = ([], xs) +-- splitAt _ [] = ([],[]) +-- splitAt n (x:xs) = let (xs',ys') = splitAt (n - 1) xs in (x : xs', ys') +-- {-# NOINLINE [1] splitAt #-} +-- -- {-# RULES "splitAt/stream" forall n s. splitAt n (unstream s) = splitAtS n s #-} +-- -- {-# RULES "splitAt/stream" forall n s. splitAt n (cheapUnstream s) = cheapSplitAtS n s #-} +-- takeWhile :: (a -> Bool) -> [a] -> [a] +-- takeWhile p = unstream . takeWhileS p . stream +-- {-# INLINE takeWhile #-} +-- dropWhile :: (a -> Bool) -> [a] -> [a] +-- dropWhile _ [] = [] +-- dropWhile p xs@(x:xs') +-- | p x = dropWhile p xs' +-- | otherwise = xs +-- {-# NOINLINE [1] dropWhile #-} +-- -- {-# RULES "dropWhile/stream" forall p s. dropWhile p (unstream s) = unstream (dropWhileS p s) #-} +-- -- {-# RULES "dropWhile/stream" forall p s. dropWhile p (cheapUnstream s) = unstream (dropWhileS p s) #-} +-- span :: (a -> Bool) -> [a] -> ([a], [a]) +-- -- destroys sharing and duplicates work: +-- -- span p xs = (unstream (takeWhileS p (stream xs)), unstream (dropWhileS p (stream xs))) +-- span _ [] = ([], []) +-- span p xs@(x:xs') +-- | p x = let (ys,zs) = span p xs' in (x:ys,zs) +-- | otherwise = ([], xs) +-- {-# NOINLINE [1] span #-} +-- -- {-# RULES "span/stream" forall p s. span p (unstream s) = spanS p s #-} +-- -- {-# RULES "span/stream" forall p s. span p (cheapUnstream s) = spanS p s #-} +-- break :: (a -> Bool) -> [a] -> ([a], [a]) +-- break p = span (not . p) +-- {-# INLINE break #-} +-- reverse :: [a] -> [a] +-- reverse = reverseS . stream +-- {-# INLINE reverse #-} +-- +-- zip :: [a] -> [b] -> [(a,b)] +-- zip xs ys = unstream (zipS (stream xs) (stream ys)) +-- {-# INLINE zip #-} +-- zip3 :: [a] -> [b] -> [c] -> [(a,b,c)] +-- zip3 xs ys zs = unstream (zip3S (stream xs) (stream ys) (stream zs)) +-- {-# INLINE zip3 #-} +-- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] +-- zipWith f xs ys = unstream (zipWithS f (stream xs) (stream ys)) +-- {-# INLINE zipWith #-} +-- zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] +-- zipWith3 f xs ys zs = unstream (zipWith3S f (stream xs) (stream ys) (stream zs)) +-- {-# INLINE zipWith3 #-} +-- +-- unzip :: [(a,b)] -> ([a], [b]) +-- unzip = unzipS . stream +-- {-# INLINE unzip #-} +-- unzip3 :: [(a,b,c)] -> ([a], [b], [c]) +-- unzip3 = unzip3S . stream +-- {-# INLINE unzip3 #-} + + -- $setup -- >>> import GHC.Internal.Base -- >>> import Prelude (Num (..), Ord (..), Int, Double, odd, not, undefined) @@ -98,10 +1022,12 @@ badHead = errorEmptyList "head" -- This rule is useful in cases like -- head [y | (x,y) <- ps, x==t] {-# RULES -"head/build" forall (g::forall b.(a->b->b)->b->b) . - head (build g) = g (\x _ -> x) badHead -"head/augment" forall xs (g::forall b. (a->b->b) -> b -> b) . - head (augment g xs) = g (\x _ -> x) (head xs) +"head/unstream" forall s. head (unstream s) = headS s +"head/cheapUnstream" forall s. head (cheapUnstream s) = headS s +-- "head/build" forall (g::forall b.(a->b->b)->b->b) . +-- head (build g) = g (\x _ -> x) badHead +-- "head/augment" forall xs (g::forall b. (a->b->b) -> b -> b) . +-- head (augment g xs) = g (\x _ -> x) (head xs) #-} -- | \(\mathcal{O}(1)\). Decompose a list into its 'head' and 'tail'. @@ -283,8 +1209,9 @@ lenAcc [] n = n lenAcc (_:ys) n = lenAcc ys (n+1) {-# RULES -"length" [~1] forall xs . length xs = foldr lengthFB idLength xs 0 -"lengthList" [1] foldr lengthFB idLength = lenAcc +"length" length = lengthS . stream +-- "length" [~1] forall xs . length xs = foldr lengthFB idLength xs 0 +-- "lengthList" [1] foldr lengthFB idLength = lenAcc #-} -- The lambda form turns out to be necessary to make this inline @@ -325,9 +1252,10 @@ filterFB c p x r | p x = x `c` r | otherwise = r {-# RULES -"filter" [~1] forall p xs. filter p xs = build (\c n -> foldr (filterFB c p) n xs) -"filterList" [1] forall p. foldr (filterFB (:) p) [] = filter p -"filterFB" forall c p q. filterFB (filterFB c p) q = filterFB c (\x -> q x && p x) +"filter" forall p. filter p = unstream . filterS p . stream +-- "filter" [~1] forall p xs. filter p xs = build (\c n -> foldr (filterFB c p) n xs) +-- "filterList" [1] forall p. foldr (filterFB (:) p) [] = filter p +-- "filterFB" forall c p q. filterFB (filterFB c p) q = filterFB c (\x -> q x && p x) #-} -- Note the filterFB rule, which has p and q the "wrong way round" in the RHS. @@ -359,10 +1287,13 @@ filterFB c p x r | p x = x `c` r -- >>> foldl (+) 0 [1..] -- * Hangs forever * foldl :: forall a b. (b -> a -> b) -> b -> [a] -> b -{-# INLINE foldl #-} -foldl k z0 xs = - foldr (\(v::a) (fn::b->b) -> oneShot (\(z::b) -> fn (k z v))) (id :: b -> b) xs z0 - -- See Note [Left folds via right fold] +foldl k z0 [] = z0 +foldl k z0 (x:xs) = foldl k (k z0 x) xs +{-# NOINLINE [0] foldl #-} + +{-# RULES +"foldl" forall k z . foldl k z = foldlS k z . stream + #-} {- Note [Left folds via right fold] @@ -405,9 +1336,14 @@ allocation-free. Also see #13001. -- | A strict version of 'foldl'. foldl' :: forall a b . (b -> a -> b) -> b -> [a] -> b -{-# INLINE foldl' #-} -foldl' k z0 = \xs -> - foldr (\(v::a) (fn::b->b) -> oneShot (\(z::b) -> z `seq` fn (k z v))) (id :: b -> b) xs z0 +foldl' k !z0 [] = z0 +foldl' k !z0 (x:xs) = foldl' k (k z0 x) xs + +{-# NOINLINE [0] foldl' #-} +{-# RULES +"foldl'" forall k z. foldl' k z = foldlS' k z . stream + #-} + {- Note [Definition of foldl'] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -551,10 +1487,11 @@ scanl = scanlGo -- See Note [scanl rewrite rules] {-# RULES -"scanl" [~1] forall f a bs . scanl f a bs = - build (\c n -> a `c` foldr (scanlFB f c) (constScanl n) bs a) -"scanlList" [1] forall f (a::a) bs . - foldr (scanlFB f (:)) (constScanl []) bs a = tail (scanl f a bs) +"scanl" forall f a. scanl f a = unstream . scanlS f a . stream +-- "scanl" [~1] forall f a bs . scanl f a bs = +-- build (\c n -> a `c` foldr (scanlFB f c) (constScanl n) bs a) +-- "scanlList" [1] forall f (a::a) bs . +-- foldr (scanlFB f (:)) (constScanl []) bs a = tail (scanl f a bs) #-} {-# INLINE [0] scanlFB #-} -- See Note [Inline FB functions] @@ -612,10 +1549,11 @@ scanl' = scanlGo' -- See Note [scanl rewrite rules] {-# RULES -"scanl'" [~1] forall f a bs . scanl' f a bs = - build (\c n -> a `c` foldr (scanlFB' f c) (flipSeq n) bs a) -"scanlList'" [1] forall f a bs . - foldr (scanlFB' f (:)) (flipSeq []) bs a = tail (scanl' f a bs) +"scanl'" forall f a. scanl' f a = unstream . scanlS' f a . stream +-- "scanl'" [~1] forall f a bs . scanl' f a bs = +-- build (\c n -> a `c` foldr (scanlFB' f c) (flipSeq n) bs a) +-- "scanlList'" [1] forall f a bs . +-- foldr (scanlFB' f (:)) (flipSeq []) bs a = tail (scanl' f a bs) #-} {-# INLINE [0] scanlFB' #-} -- See Note [Inline FB functions] @@ -680,6 +1618,7 @@ match on everything past the :, which is just the tail of scanl. -- >>> foldr' (||) [False, False, True, True] -- Use foldr instead! -- True foldr' :: (a -> b -> b) -> b -> [a] -> b +{-# INLINE foldr' #-} foldr' f z0 xs = foldl f' id xs z0 where f' k x z = k $! f x z @@ -704,6 +1643,9 @@ foldr1 f = go go (x:xs) = f x (go xs) go [] = errorEmptyList "foldr1" {-# INLINE [0] foldr1 #-} +{-# RULES +"foldr1" forall f . foldr1 f = foldr1S f . stream + #-} -- | \(\mathcal{O}(n)\). 'scanr' is the right-to-left dual of 'scanl'. Note that the order of parameters on the accumulating function are reversed compared to 'scanl'. -- Also note that @@ -746,11 +1688,12 @@ scanrFB f c = \x ~(r, est) -> (f x r, r `c` est) -- See Note [scanrFB and evaluation] below {-# RULES -"scanr" [~1] forall f q0 ls . scanr f q0 ls = - build (\c n -> strictUncurryScanr c (foldr (scanrFB f c) (q0,n) ls)) -"scanrList" [1] forall f q0 ls . - strictUncurryScanr (:) (foldr (scanrFB f (:)) (q0,[]) ls) = - scanr f q0 ls +"scanr" forall f q0. scanr f q0 = scanrS f q0 . stream +-- "scanr" [~1] forall f q0 ls . scanr f q0 ls = +-- build (\c n -> strictUncurryScanr c (foldr (scanrFB f c) (q0,n) ls)) +-- "scanrList" [1] forall f q0 ls . +-- strictUncurryScanr (:) (foldr (scanrFB f (:)) (q0,[]) ls) = +-- scanr f q0 ls #-} {- @@ -805,6 +1748,10 @@ scanr1 _ [] = [] scanr1 _ [x] = [x] scanr1 f (x:xs) = f x q : qs where qs@(q:_) = scanr1 f xs +{-# NOINLINE [0] scanr1 #-} +{-# RULES +"scanr1" forall f. scanr1 f = scanr1S f . stream + #-} -- | 'maximum' returns the maximum value from a list, -- which must be non-empty, finite, and of an ordered type. @@ -888,8 +1835,9 @@ iterateFB c f x0 = go x0 where go x = x `c` go (f x) {-# RULES -"iterate" [~1] forall f x. iterate f x = build (\c _n -> iterateFB c f x) -"iterateFB" [1] iterateFB (:) = iterate +"iterate" forall f x. iterate f x = unstream (iterateS f x) +-- "iterate" [~1] forall f x. iterate f x = build (\c _n -> iterateFB c f x) +-- "iterateFB" [1] iterateFB (:) = iterate #-} @@ -915,8 +1863,9 @@ iterate'FB c f x0 = go x0 in x' `seq` (x `c` go x') {-# RULES -"iterate'" [~1] forall f x. iterate' f x = build (\c _n -> iterate'FB c f x) -"iterate'FB" [1] iterate'FB (:) = iterate' +"iterate'" forall f x. iterate' f x = unstream (iterateS' f x) +-- "iterate'" [~1] forall f x. iterate' f x = build (\c _n -> iterate'FB c f x) +-- "iterate'FB" [1] iterate'FB (:) = iterate' #-} @@ -939,10 +1888,10 @@ repeatFB :: (a -> b -> b) -> a -> b repeatFB c x = xs where xs = x `c` xs -{-# RULES -"repeat" [~1] forall x. repeat x = build (\c _n -> repeatFB c x) -"repeatFB" [1] repeatFB (:) = repeat - #-} +-- {-# RULES +-- "repeat" [~1] forall x. repeat x = build (\c _n -> repeatFB c x) +-- "repeatFB" [1] repeatFB (:) = repeat +-- #-} -- | 'replicate' @n x@ is a list of length @n@ with @x@ the value of -- every element. @@ -959,9 +1908,12 @@ repeatFB c x = xs where xs = x `c` xs -- -- >>> replicate 4 True -- [True,True,True,True] -{-# INLINE replicate #-} +{-# NOINLINE [0] replicate #-} replicate :: Int -> a -> [a] replicate n x = take n (repeat x) +{-# RULES +"replicate" forall n x . replicate n x = cheapUnstream (replicateS n x) +#-} -- | 'cycle' ties a finite list into a circular one, or equivalently, -- the infinite repetition of the original list. It is the identity @@ -1027,11 +1979,12 @@ takeWhileFB p c n = \x r -> if p x then x `c` r else n -- \x r -> if q x && p x then x `c` r else n = -- takeWhileFB (\x -> q x && p x) c n {-# RULES -"takeWhile" [~1] forall p xs. takeWhile p xs = - build (\c n -> foldr (takeWhileFB p c n) n xs) -"takeWhileList" [1] forall p. foldr (takeWhileFB p (:) []) [] = takeWhile p -"takeWhileFB" forall c n p q. takeWhileFB q (takeWhileFB p c n) n = - takeWhileFB (\x -> q x && p x) c n +"takeWhile" forall p. takeWhile p = unstream . takeWhileS p . stream +-- "takeWhile" [~1] forall p xs. takeWhile p xs = +-- build (\c n -> foldr (takeWhileFB p c n) n xs) +-- "takeWhileList" [1] forall p. foldr (takeWhileFB p (:) []) [] = takeWhile p +-- "takeWhileFB" forall c n p q. takeWhileFB q (takeWhileFB p c n) n = +-- takeWhileFB (\x -> q x && p x) c n #-} -- | 'dropWhile' @p xs@ returns the suffix remaining after 'takeWhile' @p xs at . @@ -1051,6 +2004,12 @@ dropWhile _ [] = [] dropWhile p xs@(x:xs') | p x = dropWhile p xs' | otherwise = xs +{-# NOINLINE [0] dropWhile #-} + +{-# RULES +"dropWhile/unstream" forall p s. dropWhile p (unstream s) = unstream (dropWhileS p s) +"dropWhile/cheapUnstream" forall p s. dropWhile p (cheapUnstream s) = cheapUnstream (dropWhileS p s) + #-} -- | 'take' @n@, applied to a list @xs@, returns the prefix of @xs@ -- of length @n@, or @xs@ itself if @n >= 'length' xs at . @@ -1109,12 +2068,13 @@ unsafeTake 1 (x: _) = [x] unsafeTake m (x:xs) = x : unsafeTake (m - 1) xs {-# RULES -"take" [~1] forall n xs . take n xs = - build (\c nil -> if 0 < n - then foldr (takeFB c nil) (flipSeq nil) xs n - else nil) -"unsafeTakeList" [1] forall n xs . foldr (takeFB (:) []) (flipSeq []) xs n - = unsafeTake n xs +"take" forall n. take n = unstream . takeS n . stream +-- "take" [~1] forall n xs . take n xs = +-- build (\c nil -> if 0 < n +-- then foldr (takeFB c nil) (flipSeq nil) xs n +-- else nil) +-- "unsafeTakeList" [1] forall n xs . foldr (takeFB (:) []) (flipSeq []) xs n +-- = unsafeTake n xs #-} {-# INLINE [0] flipSeq #-} @@ -1168,7 +2128,7 @@ drop n xs | n <= 0 = xs drop _ [] = [] drop n (_:xs) = drop (n-1) xs #else /* hack away */ -{-# INLINE drop #-} +{-# INLINE [1] drop #-} drop n ls | n <= 0 = ls | otherwise = unsafeDrop n ls @@ -1179,6 +2139,10 @@ drop n ls unsafeDrop !_ [] = [] unsafeDrop 1 (_:xs) = xs unsafeDrop m (_:xs) = unsafeDrop (m - 1) xs +{-# RULES +"drop/unstream" forall n s . drop n (unstream s) = unstream (dropS n s) +"drop/cheapUnstream" forall n s. drop n (cheapUnstream s) = cheapUnstream (dropS n s) + #-} #endif -- | 'splitAt' @n xs@ returns a tuple where first element is @xs@ prefix of @@ -1238,6 +2202,11 @@ splitAt n ls splitAt' m (x:xs) = (x:xs', xs'') where (xs', xs'') = splitAt' (m - 1) xs +{-# NOINLINE [0] splitAt #-} +{-# RULES +"splitAt/unstream" forall n s. splitAt n (unstream s) = splitAtS n s +"splitAt/cheapUnstream" forall n s. splitAt n (cheapUnstream s) = cheapSplitAtS n s + #-} #endif /* USE_REPORT_PRELUDE */ -- | 'span', applied to a predicate @p@ and a list @xs@, returns a tuple where @@ -1394,8 +2363,9 @@ and (x:xs) = x && and xs {-# NOINLINE [1] and #-} {-# RULES -"and/build" forall (g::forall b.(Bool->b->b)->b->b) . - and (build g) = g (&&) True +"and" and = andS . stream +-- "and/build" forall (g::forall b.(Bool->b->b)->b->b) . +-- and (build g) = g (&&) True #-} #endif @@ -1431,8 +2401,9 @@ or (x:xs) = x || or xs {-# NOINLINE [1] or #-} {-# RULES -"or/build" forall (g::forall b.(Bool->b->b)->b->b) . - or (build g) = g (||) False +"or" or = orS . stream +-- "or/build" forall (g::forall b.(Bool->b->b)->b->b) . +-- or (build g) = g (||) False #-} #endif @@ -1468,8 +2439,9 @@ any p (x:xs) = p x || any p xs {-# NOINLINE [1] any #-} {-# RULES -"any/build" forall p (g::forall b.(a->b->b)->b->b) . - any p (build g) = g ((||) . p) False +"any" forall p . any p = anyS p . stream +-- "any/build" forall p (g::forall b.(a->b->b)->b->b) . +-- any p (build g) = g ((||) . p) False #-} #endif @@ -1505,8 +2477,9 @@ all p (x:xs) = p x && all p xs {-# NOINLINE [1] all #-} {-# RULES -"all/build" forall p (g::forall b.(a->b->b)->b->b) . - all p (build g) = g ((&&) . p) True +"all" forall p . all p = allS p . stream +-- "all/build" forall p (g::forall b.(a->b->b)->b->b) . +-- all p (build g) = g ((&&) . p) True #-} #endif @@ -1539,8 +2512,9 @@ elem _ [] = False elem x (y:ys) = x==y || elem x ys {-# NOINLINE [1] elem #-} {-# RULES -"elem/build" forall x (g :: forall b . (a -> b -> b) -> b -> b) - . elem x (build g) = g (\ y r -> (x == y) || r) False +"elem" forall x. elem x = elemS x . stream +-- "elem/build" forall x (g :: forall b . (a -> b -> b) -> b -> b) +-- . elem x (build g) = g (\ y r -> (x == y) || r) False #-} #endif @@ -1570,8 +2544,9 @@ notElem _ [] = True notElem x (y:ys)= x /= y && notElem x ys {-# NOINLINE [1] notElem #-} {-# RULES -"notElem/build" forall x (g :: forall b . (a -> b -> b) -> b -> b) - . notElem x (build g) = g (\ y r -> (x /= y) && r) True +"notElem" forall x. notElem x = notElemS x . stream +-- "notElem/build" forall x (g :: forall b . (a -> b -> b) -> b -> b) +-- . notElem x (build g) = g (\ y r -> (x /= y) && r) True #-} #endif @@ -1596,35 +2571,11 @@ lookup key ((x,y):xys) | otherwise = lookup key xys {-# NOINLINE [1] lookup #-} -- see Note [Fusion for lookup] {-# RULES -"lookup/build" forall x (g :: forall b. ((k, a) -> b -> b) -> b -> b). - lookup x (build g) = g (\(k, v) r -> if x == k then Just v else r) Nothing +"lookup" forall x. lookup x = lookupS x . stream +-- "lookup/build" forall x (g :: forall b. ((k, a) -> b -> b) -> b -> b). +-- lookup x (build g) = g (\(k, v) r -> if x == k then Just v else r) Nothing #-} --- | Map a function returning a list over a list and concatenate the results. --- 'concatMap' can be seen as the composition of 'concat' and 'map'. --- --- > concatMap f xs == (concat . map f) xs --- --- ==== __Examples__ --- --- >>> concatMap (\i -> [-i,i]) [] --- [] --- --- >>> concatMap (\i -> [-i, i]) [1, 2, 3] --- [-1,1,-2,2,-3,3] --- --- >>> concatMap ('replicate' 3) [0, 2, 4] --- [0,0,0,2,2,2,4,4,4] -concatMap :: (a -> [b]) -> [a] -> [b] -concatMap f = foldr ((++) . f) [] - -{-# NOINLINE [1] concatMap #-} - -{-# RULES -"concatMap" forall f xs . concatMap f xs = - build (\c n -> foldr (\x b -> foldr c b (f x)) n xs) - #-} - -- | Concatenate a list of lists. -- @@ -1644,8 +2595,9 @@ concat = foldr (++) [] {-# NOINLINE [1] concat #-} {-# RULES - "concat" forall xs. concat xs = - build (\c n -> foldr (\x y -> foldr c y x) n xs) +"concat" concat = unstream . concatS . stream +-- "concat" forall xs. concat xs = +-- build (\c n -> foldr (\x y -> foldr c y x) n xs) -- We don't bother to turn non-fusible applications of concat back into concat #-} @@ -1694,9 +2646,17 @@ negIndex = error $ prel_list_str ++ "!!: negative index" {-# INLINABLE (!!) #-} xs !! n | n < 0 = negIndex - | otherwise = foldr (\x r k -> case k of - 0 -> x - _ -> r (k-1)) tooLarge xs n + | otherwise = unsafeIndexHelper xs n + +unsafeIndexHelper :: [a] -> Int -> a +unsafeIndexHelper [] i = tooLarge i +unsafeIndexHelper (x:xs) 0 = x +unsafeIndexHelper (x:xs) n = unsafeIndexHelper xs (n - 1) +{-# NOINLINE [1] unsafeIndexHelper #-} + +{-# RULES +"unsafeIndexHelper" forall xs. unsafeIndexHelper xs = unsafeIndexHelperS (stream xs) + #-} #endif -- | List index (subscript) operator, starting from 0. Returns 'Nothing' @@ -1724,9 +2684,16 @@ xs !! n {-# INLINABLE (!?) #-} xs !? n | n < 0 = Nothing - | otherwise = foldr (\x r k -> case k of - 0 -> Just x - _ -> r (k-1)) (const Nothing) xs n + | otherwise = indexHelper xs n + +indexHelper :: [a] -> Int -> Maybe a +indexHelper [] _ = Nothing +indexHelper (x:_) 0 = Just x +indexHelper (_:xs) n = indexHelper xs (n - 1) +{-# NOINLINE [1] indexHelper #-} +{-# RULES +"indexHelper" forall xs n . indexHelper xs n = indexHelperS (stream xs) n + #-} -------------------------------------------------------------- -- The zip family @@ -1879,8 +2846,9 @@ zipFB :: ((a, b) -> c -> d) -> a -> b -> c -> d zipFB c = \x y r -> (x,y) `c` r {-# RULES -- See Note [Fusion for zipN/zipWithN] -"zip" [~1] forall xs ys. zip xs ys = build (\c n -> foldr2 (zipFB c) n xs ys) -"zipList" [1] foldr2 (zipFB (:)) [] = zip +"zip" forall xs ys. zip xs ys = unstream (zipS (stream xs) (stream ys)) +-- "zip" [~1] forall xs ys. zip xs ys = build (\c n -> foldr2 (zipFB c) n xs ys) +-- "zipList" [1] foldr2 (zipFB (:)) [] = zip #-} ---------------------------------------------- @@ -1900,8 +2868,9 @@ zip3FB :: ((a,b,c) -> xs -> xs') -> a -> b -> c -> xs -> xs' zip3FB cons = \a b c r -> (a,b,c) `cons` r {-# RULES -- See Note [Fusion for zipN/zipWithN] -"zip3" [~1] forall as bs cs. zip3 as bs cs = build (\c n -> foldr3 (zip3FB c) n as bs cs) -"zip3List" [1] foldr3 (zip3FB (:)) [] = zip3 +"zip3" forall xs ys zs . zip3 xs ys zs = unstream (zip3S (stream xs) (stream ys) (stream zs)) +-- "zip3" [~1] forall as bs cs. zip3 as bs cs = build (\c n -> foldr3 (zip3FB c) n as bs cs) +-- "zip3List" [1] foldr3 (zip3FB (:)) [] = zip3 #-} -- The zipWith family generalises the zip family by zipping with the @@ -1949,8 +2918,9 @@ zipWithFB :: (a -> b -> c) -> (d -> e -> a) -> d -> e -> b -> c zipWithFB c f = \x y r -> (x `f` y) `c` r {-# RULES -- See Note [Fusion for zipN/zipWithN] -"zipWith" [~1] forall f xs ys. zipWith f xs ys = build (\c n -> foldr2 (zipWithFB c f) n xs ys) -"zipWithList" [1] forall f. foldr2 (zipWithFB (:) f) [] = zipWith f +"zipWith" forall f xs ys. zipWith f xs ys = unstream (zipWithS f (stream xs) (stream ys)) +-- "zipWith" [~1] forall f xs ys. zipWith f xs ys = build (\c n -> foldr2 (zipWithFB c f) n xs ys) +-- "zipWithList" [1] forall f. foldr2 (zipWithFB (:) f) [] = zipWith f #-} -- | \(\mathcal{O}(\min(l,m,n))\). The 'zipWith3' function takes a function which combines three @@ -1981,8 +2951,9 @@ zipWith3FB :: (d -> xs -> xs') -> (a -> b -> c -> d) -> a -> b -> c -> xs -> xs' zipWith3FB cons func = \a b c r -> (func a b c) `cons` r {-# RULES -"zipWith3" [~1] forall f as bs cs. zipWith3 f as bs cs = build (\c n -> foldr3 (zipWith3FB c f) n as bs cs) -"zipWith3List" [1] forall f. foldr3 (zipWith3FB (:) f) [] = zipWith3 f +"zipWith3" forall f xs ys zs . zipWith3 f xs ys zs = unstream (zipWith3S f (stream xs) (stream ys) (stream zs)) +-- "zipWith3" [~1] forall f as bs cs. zipWith3 f as bs cs = build (\c n -> foldr3 (zipWith3FB c f) n as bs cs) +-- "zipWith3List" [1] forall f. foldr3 (zipWith3FB (:) f) [] = zipWith3 f #-} -- | 'unzip' transforms a list of pairs into a list of first components ===================================== libraries/ghc-internal/src/GHC/Internal/System/Posix/Internals.hs ===================================== @@ -48,7 +48,7 @@ import GHC.Internal.Data.Maybe import GHC.Internal.System.IO.Error #endif -import GHC.Internal.Base +import GHC.Internal.Base hiding (Stream) import GHC.Internal.Bits import GHC.Internal.Num import GHC.Internal.Real View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3e0b4233f722dedd7ebcfb0be0ca0adef8de0574 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3e0b4233f722dedd7ebcfb0be0ca0adef8de0574 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 12:58:08 2024 From: gitlab at gitlab.haskell.org (Jaro Reinders (@jaro)) Date: Tue, 04 Jun 2024 08:58:08 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/stream-fusion Message-ID: <665f0f605e237_27a8352b7a6681848d5@gitlab.mail> Jaro Reinders pushed new branch wip/stream-fusion at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/stream-fusion You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 13:46:35 2024 From: gitlab at gitlab.haskell.org (Zubin (@wz1000)) Date: Tue, 04 Jun 2024 09:46:35 -0400 Subject: [Git][ghc/ghc][ghc-9.10] 14 commits: Bump version to 9.10.1 Message-ID: <665f1abb336fe_27a8353303fc4223461@gitlab.mail> Zubin pushed to branch ghc-9.10 at Glasgow Haskell Compiler / GHC Commits: 017c52b7 by Ben Gamari at 2024-05-09T18:39:46-04:00 Bump version to 9.10.1 - - - - - d07219d8 by Ben Gamari at 2024-05-09T22:52:06-04:00 generate_bootstrap_plans: Update - - - - - 6d779c0f by Ben Gamari at 2024-05-10T00:36:54-04:00 base: Fix release date in changelog - - - - - 0d2160de by Ben Gamari at 2024-05-13T11:54:20-04:00 releng/uploads: .gz files are release artifacts - - - - - b63f7ba0 by Ben Gamari at 2024-05-23T17:33:27-04:00 base: Fix changelog reference to setBacktraceMechanismState - - - - - 6ccd1c03 by Ben Gamari at 2024-05-23T17:33:27-04:00 ghcup-metadata: update to reflect upstream preferences - - - - - a5325ded by Ben Gamari at 2024-05-23T17:33:27-04:00 Bump haddock version Somehow the submodule bump which performed the version increment of `haddock` and friends in was lost in the pre-release shuffle. Fix this. Closes #24827. - - - - - 559e73fb by Ben Gamari at 2024-05-28T09:37:46-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - e6b940c3 by Ben Gamari at 2024-05-28T14:31:42-04:00 Bump haddock submodule with fix to #24853 It appears that this reversion was not merged to ghc-9.10, again breaking quick-jump in `base`'s Haddocks. Also bump version to 2.31 Fixes #24853. - - - - - c453ac59 by Ben Gamari at 2024-05-29T07:28:32-04:00 base: Bump version We are bumping the version by a patch-level to upload to Hackage to fix Haddock issues with the 9.10 release. See #24875. - - - - - 1b157ab3 by Ben Gamari at 2024-05-29T10:41:50-04:00 testsuite: Normalize version of base in T19847a - - - - - 2fe96b6e by Zubin Duggal at 2024-05-30T18:06:57+05:30 Bump haddock submodule to fix #24907 - - - - - 0c301d33 by Zubin Duggal at 2024-05-31T13:01:18+05:30 Bump haddock submodule to fix #24912 - - - - - 934a8bb9 by Zubin Duggal at 2024-05-31T13:01:18+05:30 base: Add changelog entry for 4.20.0.1 - - - - - 9 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitlab/rel_eng/upload.sh - configure.ac - hadrian/bootstrap/generate_bootstrap_plans - − hadrian/bootstrap/plan-9_4_2.json - − hadrian/bootstrap/plan-9_4_3.json - − hadrian/bootstrap/plan-9_4_4.json - − hadrian/bootstrap/plan-9_4_6.json - − hadrian/bootstrap/plan-9_4_7.json The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2cc6968a0e70967a0fe906ff27957030eab40889...934a8bb930390d5db1e5613ddfeafc8c80dd9b96 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2cc6968a0e70967a0fe906ff27957030eab40889...934a8bb930390d5db1e5613ddfeafc8c80dd9b96 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 13:49:06 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 04 Jun 2024 09:49:06 -0400 Subject: [Git][ghc/ghc][wip/T24676] Wibbles Message-ID: <665f1b52861af_27a83533ac2782266b4@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24676 at Glasgow Haskell Compiler / GHC Commits: b6a7f3de by Simon Peyton Jones at 2024-06-04T14:48:35+01:00 Wibbles - - - - - 4 changed files: - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Utils/TcType.hs - testsuite/tests/typecheck/should_fail/T8450.hs - testsuite/tests/typecheck/should_fail/T8450.stderr Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -119,8 +119,7 @@ Note [Instantiation variables are short lived] variables can be unified with a polytype (by `qlUnify`). * By the time QL is done, all filled-in occurrences of instantiation variables - have been zonked away with `qlZonkTcType` (see "Crucial step" in tcValArgs). - See also Note [QuickLook zonking] in GHC.Tc.Zonk.TcType + have been zonked away with `zonkTcType` (see "Crucial step" in tcValArgs). See Section 4.3 "Applications and instantiation" of the paper. @@ -294,7 +293,8 @@ Now we split into two cases: Note [Unify with expected type before typechecking arguments] 5.2 Check the arguments with `tcValArgs`. Importantly, this will monomorphise - all the instantiation variables of the call. See Note [qlMonoTcType] + all the instantiation variables of the call. + See Note [Monomorphise instantiation variables]. 5.3 Use `zonkTcType` to expose the polymophism hidden under instantiation variables in `app_res_rho`, and the monomorphic versions of any @@ -526,7 +526,6 @@ tcValArg do_ql (EValArg { ea_ctxt = ctxt -- Then Theta = [p :-> forall a. a->a], and we want -- to check 'e' with expected type (forall a. a->a) -- See Note [Instantiation variables are short lived] - -- and Note [QuickLook zonking] in GHC.Tc.Zonk.TcType ; Scaled mult exp_arg_ty <- case do_ql of DoQL -> liftZonkM $ zonkScaledTcType sc_arg_ty NoQL -> return sc_arg_ty ===================================== compiler/GHC/Tc/Utils/TcType.hs ===================================== @@ -699,7 +699,7 @@ data TcLevel = TcLevel Int# | QLInstVar -- See Note [TcLevel invariants] for what this Int is -- See also Note [TcLevel assignment] - -- See also Note [The TcLevel QLInstVar] + -- See also Note [The QLInstVar TcLevel] {- Note [TcLevel invariants] @@ -734,7 +734,7 @@ Note [TcLevel invariants] The level of a MetaTyVar also governs its untouchability. See Note [Unification preconditions] in GHC.Tc.Utils.Unify. - -- See also Note [The TcLevel QLInstVar] + -- See also Note [The QLInstVar TcLevel] Note [TcLevel assignment] ~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== testsuite/tests/typecheck/should_fail/T8450.hs ===================================== @@ -7,5 +7,8 @@ runEffect = undefined run :: forall a. a run = runEffect $ (undefined :: Either a ()) -{- Either a () ~ Either Bool alpha - a ~ alpha -} \ No newline at end of file +{- +r:=a +Expected: Either Bool a +Actual: Either a () +-} ===================================== testsuite/tests/typecheck/should_fail/T8450.stderr ===================================== @@ -1,11 +1,15 @@ - -T8450.hs:8:7: error: [GHC-25897] - • Couldn't match expected type ‘a’ with actual type ‘()’ +T8450.hs:8:18: error: [GHC-25897] + • Couldn't match type ‘a’ with ‘Bool’ + Expected: Either Bool a + Actual: Either a () ‘a’ is a rigid type variable bound by the type signature for: run :: forall a. a at T8450.hs:7:1-18 - • In the expression: runEffect $ (undefined :: Either a ()) + • In the first argument of ‘runEffect’, namely + ‘(undefined :: Either a ())’ + In the expression: runEffect (undefined :: Either a ()) In an equation for ‘run’: - run = runEffect $ (undefined :: Either a ()) + run = runEffect (undefined :: Either a ()) • Relevant bindings include run :: a (bound at T8450.hs:8:1) + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b6a7f3de755306e5188e420f0d4f38b6a1bebab5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b6a7f3de755306e5188e420f0d4f38b6a1bebab5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 14:15:51 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Tue, 04 Jun 2024 10:15:51 -0400 Subject: [Git][ghc/ghc][wip/rip-32bit-apple] 5 commits: compiler: remove 32-bit darwin logic Message-ID: <665f21976c6c_201618147bd46854@gitlab.mail> Cheng Shao pushed to branch wip/rip-32bit-apple at Glasgow Haskell Compiler / GHC Commits: e0534ea1 by Cheng Shao at 2024-06-04T14:15:31+00:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 62fea527 by Cheng Shao at 2024-06-04T14:15:36+00:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 8b666f9a by Cheng Shao at 2024-06-04T14:15:36+00:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - 04742db9 by Cheng Shao at 2024-06-04T14:15:36+00:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 235e496b by Cheng Shao at 2024-06-04T14:15:36+00:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 19 changed files: - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Linker/Static.hs - docs/users_guide/9.12.1-notes.rst - llvm-targets - rts/RtsSymbols.c - rts/StgCRun.c - testsuite/tests/driver/objc/all.T - testsuite/tests/ffi/should_run/Makefile - testsuite/tests/ffi/should_run/all.T - testsuite/tests/numeric/should_run/all.T - testsuite/tests/rts/T10672/Makefile - testsuite/tests/rts/T10672/all.T - testsuite/tests/rts/all.T - utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs - utils/llvm-targets/gen-data-layout.sh Changes: ===================================== compiler/GHC/Cmm/CLabel.hs ===================================== @@ -1659,11 +1659,7 @@ pprDynamicLinkerAsmLabel !platform dllInfo ppLbl = GotSymbolPtr -> ppLbl <> text "@GOTPCREL" GotSymbolOffset -> ppLbl | platformArch platform == ArchAArch64 -> ppLbl - | otherwise -> - case dllInfo of - CodeStub -> char 'L' <> ppLbl <> text "$stub" - SymbolPtr -> char 'L' <> ppLbl <> text "$non_lazy_ptr" - _ -> panic "pprDynamicLinkerAsmLabel" + | otherwise -> panic "pprDynamicLinkerAsmLabel" OSAIX -> case dllInfo of ===================================== compiler/GHC/CmmToAsm/PIC.hs ===================================== @@ -303,25 +303,15 @@ howToAccessLabel config arch OSDarwin DataReference lbl | otherwise = AccessDirectly -howToAccessLabel config arch OSDarwin JumpReference lbl +howToAccessLabel config _ OSDarwin JumpReference lbl -- dyld code stubs don't work for tailcalls because the -- stack alignment is only right for regular calls. -- Therefore, we have to go via a symbol pointer: - | arch == ArchX86 || arch == ArchX86_64 || arch == ArchAArch64 - , ncgLabelDynamic config lbl + | ncgLabelDynamic config lbl = AccessViaSymbolPtr -howToAccessLabel config arch OSDarwin _kind lbl - -- Code stubs are the usual method of choice for imported code; - -- not needed on x86_64 because Apple's new linker, ld64, generates - -- them automatically, neither on Aarch64 (arm64). - | arch /= ArchX86_64 - , arch /= ArchAArch64 - , ncgLabelDynamic config lbl - = AccessViaStub - - | otherwise +howToAccessLabel _ _ OSDarwin _ _ = AccessDirectly ---------------------------------------------------------------------------- @@ -534,16 +524,6 @@ gotLabel -- However, for PIC on x86, we need a small helper function. pprGotDeclaration :: NCGConfig -> HDoc pprGotDeclaration config = case (arch,os) of - (ArchX86, OSDarwin) - | ncgPIC config - -> lines_ [ - text ".section __TEXT,__textcoal_nt,coalesced,no_toc", - text ".weak_definition ___i686.get_pc_thunk.ax", - text ".private_extern ___i686.get_pc_thunk.ax", - text "___i686.get_pc_thunk.ax:", - text "\tmovl (%esp), %eax", - text "\tret" ] - (_, OSDarwin) -> empty -- Emit XCOFF TOC section @@ -597,59 +577,6 @@ pprGotDeclaration config = case (arch,os) of pprImportedSymbol :: NCGConfig -> CLabel -> HDoc pprImportedSymbol config importedLbl = case (arch,os) of - (ArchX86, OSDarwin) - | Just (CodeStub, lbl) <- dynamicLinkerLabelInfo importedLbl - -> if not pic - then - lines_ [ - text ".symbol_stub", - text "L" <> ppr_lbl lbl <> text "$stub:", - text "\t.indirect_symbol" <+> ppr_lbl lbl, - text "\tjmp *L" <> ppr_lbl lbl - <> text "$lazy_ptr", - text "L" <> ppr_lbl lbl - <> text "$stub_binder:", - text "\tpushl $L" <> ppr_lbl lbl - <> text "$lazy_ptr", - text "\tjmp dyld_stub_binding_helper" - ] - else - lines_ [ - text ".section __TEXT,__picsymbolstub2," - <> text "symbol_stubs,pure_instructions,25", - text "L" <> ppr_lbl lbl <> text "$stub:", - text "\t.indirect_symbol" <+> ppr_lbl lbl, - text "\tcall ___i686.get_pc_thunk.ax", - text "1:", - text "\tmovl L" <> ppr_lbl lbl - <> text "$lazy_ptr-1b(%eax),%edx", - text "\tjmp *%edx", - text "L" <> ppr_lbl lbl - <> text "$stub_binder:", - text "\tlea L" <> ppr_lbl lbl - <> text "$lazy_ptr-1b(%eax),%eax", - text "\tpushl %eax", - text "\tjmp dyld_stub_binding_helper" - ] - $$ lines_ [ - text ".section __DATA, __la_sym_ptr" - <> (if pic then int 2 else int 3) - <> text ",lazy_symbol_pointers", - text "L" <> ppr_lbl lbl <> text "$lazy_ptr:", - text "\t.indirect_symbol" <+> ppr_lbl lbl, - text "\t.long L" <> ppr_lbl lbl - <> text "$stub_binder"] - - | Just (SymbolPtr, lbl) <- dynamicLinkerLabelInfo importedLbl - -> lines_ [ - text ".non_lazy_symbol_pointer", - char 'L' <> ppr_lbl lbl <> text "$non_lazy_ptr:", - text "\t.indirect_symbol" <+> ppr_lbl lbl, - text "\t.long\t0"] - - | otherwise - -> empty - (ArchAArch64, OSDarwin) -> empty @@ -734,7 +661,6 @@ pprImportedSymbol config importedLbl = case (arch,os) of ppr_lbl = pprAsmLabel platform arch = platformArch platform os = platformOS platform - pic = ncgPIC config -------------------------------------------------------------------------------- -- Generate code to calculate the address that should be put in the @@ -840,11 +766,11 @@ initializePicBase_ppc _ _ _ _ -- (See PprMach.hs) initializePicBase_x86 - :: Arch -> OS -> Reg + :: OS -> Reg -> [NatCmmDecl (Alignment, RawCmmStatics) X86.Instr] -> NatM [NatCmmDecl (Alignment, RawCmmStatics) X86.Instr] -initializePicBase_x86 ArchX86 os picReg +initializePicBase_x86 os picReg (CmmProc info lab live (ListGraph blocks) : statics) | osElfTarget os = return (CmmProc info lab live (ListGraph blocks') : statics) @@ -862,12 +788,12 @@ initializePicBase_x86 ArchX86 os picReg fetchGOT (BasicBlock bID insns) = BasicBlock bID (X86.FETCHGOT picReg : insns) -initializePicBase_x86 ArchX86 OSDarwin picReg +initializePicBase_x86 OSDarwin picReg (CmmProc info lab live (ListGraph (entry:blocks)) : statics) = return (CmmProc info lab live (ListGraph (block':blocks)) : statics) where BasicBlock bID insns = entry block' = BasicBlock bID (X86.FETCHPC picReg : insns) -initializePicBase_x86 _ _ _ _ +initializePicBase_x86 _ _ _ = panic "initializePicBase_x86: not needed" ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -124,7 +124,7 @@ cmmTopCodeGen (CmmProc info lab live graph) = do os = platformOS platform case picBaseMb of - Just picBase -> initializePicBase_x86 ArchX86 os picBase tops + Just picBase -> initializePicBase_x86 os picBase tops Nothing -> return tops cmmTopCodeGen (CmmData sec dat) = ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -883,7 +883,6 @@ needs_probe_call :: Platform -> Int -> Bool needs_probe_call platform amount = case platformOS platform of OSMinGW32 -> case platformArch platform of - ArchX86 -> amount > (4 * 1024) ArchX86_64 -> amount > (4 * 1024) _ -> False _ -> False @@ -913,15 +912,6 @@ mkStackAllocInstr platform amount -- function dropping the stack more than a page. -- See Note [Windows stack layout] case platformArch platform of - ArchX86 | needs_probe_call platform amount -> - [ MOV II32 (OpImm (ImmInt amount)) (OpReg eax) - , CALL (Left $ strImmLit (fsLit "___chkstk_ms")) [eax] - , SUB II32 (OpReg eax) (OpReg esp) - ] - | otherwise -> - [ SUB II32 (OpImm (ImmInt amount)) (OpReg esp) - , TEST II32 (OpReg esp) (OpReg esp) - ] ArchX86_64 | needs_probe_call platform amount -> [ MOV II64 (OpImm (ImmInt amount)) (OpReg rax) , CALL (Left $ strImmLit (fsLit "___chkstk_ms")) [rax] ===================================== compiler/GHC/Driver/Config/Cmm.hs ===================================== @@ -24,15 +24,10 @@ initCmmConfig dflags = CmmConfig , cmmDoCmmSwitchPlans = not (backendHasNativeSwitch (backend dflags)) , cmmSplitProcPoints = not (backendSupportsUnsplitProcPoints (backend dflags)) || not (platformTablesNextToCode platform) - || usingInconsistentPicReg , cmmAllowMul2 = (ncg && x86ish) || llvm , cmmOptConstDivision = not llvm } where platform = targetPlatform dflags - usingInconsistentPicReg = - case (platformArch platform, platformOS platform, positionIndependent dflags) - of (ArchX86, OSDarwin, pic) -> pic - _ -> False -- Copied from StgToCmm (ncg, llvm) = case backendPrimitiveImplementation (backend dflags) of GenericPrimitives -> (False, False) ===================================== compiler/GHC/Linker/Static.hs ===================================== @@ -219,25 +219,12 @@ linkBinary' staticLink logger tmpfs dflags unit_env o_files dep_units = do toolSettings_ldSupportsCompactUnwind toolSettings' && (platformOS platform == OSDarwin) && case platformArch platform of - ArchX86 -> True ArchX86_64 -> True - ArchARM {} -> True ArchAArch64 -> True _ -> False then ["-Wl,-no_compact_unwind"] else []) - -- '-Wl,-read_only_relocs,suppress' - -- ld gives loads of warnings like: - -- ld: warning: text reloc in _base_GHCziArr_unsafeArray_info to _base_GHCziArr_unsafeArray_closure - -- when linking any program. We're not sure - -- whether this is something we ought to fix, but - -- for now this flags silences them. - ++ (if platformOS platform == OSDarwin && - platformArch platform == ArchX86 - then ["-Wl,-read_only_relocs,suppress"] - else []) - -- We should rather be asking does it support --gc-sections? ++ (if toolSettings_ldIsGnuLd toolSettings' && not (gopt Opt_WholeArchiveHsLibs dflags) ===================================== docs/users_guide/9.12.1-notes.rst ===================================== @@ -69,6 +69,10 @@ Compiler and treat it as ``ccall``. All C import/export declarations on Windows should now use ``ccall``. +- 32-bit macOS/iOS support has also been completely removed (`#24921 + `_). This does + not affect existing support of apple systems on x86_64/aarch64. + GHCi ~~~~ ===================================== llvm-targets ===================================== @@ -43,12 +43,9 @@ ,("riscv64-unknown-linux", ("e-m:e-p:64:64-i64:64-i128:128-n64-S128", "", "+m +a +f +d +c +relax")) ,("loongarch64-unknown-linux-gnu", ("e-m:e-p:64:64-i64:64-i128:128-n64-S128", "", "+f +d")) ,("loongarch64-unknown-linux", ("e-m:e-p:64:64-i64:64-i128:128-n64-S128", "", "+f +d")) -,("i386-apple-darwin", ("e-m:o-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:128-n8:16:32-S128", "penryn", "")) ,("x86_64-apple-darwin", ("e-m:o-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "penryn", "")) ,("arm64-apple-darwin", ("e-m:o-i64:64-i128:128-n32:64-S128", "generic", "+v8.3a +fp-armv8 +neon +crc +crypto +fullfp16 +ras +lse +rdm +rcpc +zcm +zcz +sha2 +aes")) -,("armv7-apple-ios", ("e-m:o-p:32:32-Fi8-f64:32:64-v64:32:64-v128:32:128-a:0:32-n32-S32", "generic", "")) ,("aarch64-apple-ios", ("e-m:o-i64:64-i128:128-n32:64-S128", "apple-a7", "+fp-armv8 +neon +crypto +zcm +zcz +sha2 +aes")) -,("i386-apple-ios", ("e-m:o-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:128-n8:16:32-S128", "yonah", "")) ,("x86_64-apple-ios", ("e-m:o-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "core2", "")) ,("amd64-portbld-freebsd", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) ,("x86_64-unknown-freebsd", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) ===================================== rts/RtsSymbols.c ===================================== @@ -1073,11 +1073,5 @@ RtsSymbolVal rtsSyms[] = { RTS_LIBFFI_SYMBOLS RTS_ARM_OUTLINE_ATOMIC_SYMBOLS SymI_HasDataProto(nonmoving_write_barrier_enabled) -#if defined(darwin_HOST_OS) && defined(i386_HOST_ARCH) - // dyld stub code contains references to this, - // but it should never be called because we treat - // lazy pointers as nonlazy. - { "dyld_stub_binding_helper", (void*)0xDEADBEEF, STRENGTH_NORMAL }, -#endif { 0, 0, STRENGTH_NORMAL, SYM_TYPE_CODE } /* sentinel */ }; ===================================== rts/StgCRun.c ===================================== @@ -102,13 +102,8 @@ StgFunPtr StgReturn(void) #if defined(i386_HOST_ARCH) -#if defined(darwin_HOST_OS) || defined(ios_HOST_OS) -#define STG_GLOBAL ".globl " -#define STG_HIDDEN ".private_extern " -#else #define STG_GLOBAL ".global " #define STG_HIDDEN ".hidden " -#endif /* * Note [Stack Alignment on X86] ===================================== testsuite/tests/driver/objc/all.T ===================================== @@ -1,19 +1,11 @@ -def if_not_platform(platforms, f): - if not (config.platform in platforms): - return f - else: - return normal - -skip_if_not_osx = if_not_platform(['i386-apple-darwin','x86_64-apple-darwin'], skip) - test('objc-hi', - [ skip_if_not_osx, + [ unless(opsys('darwin'), skip), objc_src, expect_fail_for(['ghci']) ], compile_and_run, ['-framework Foundation']) test('objcxx-hi', - [ skip_if_not_osx, + [ unless(opsys('darwin'), skip), objcxx_src, expect_fail_for(['ghci']) ], compile_and_run, ['-framework Foundation -lc++']) ===================================== testsuite/tests/ffi/should_run/Makefile ===================================== @@ -6,12 +6,10 @@ ffi018_ghci_setup : '$(TEST_HC)' $(TEST_HC_OPTS) -c ffi018_ghci_c.c T1288_ghci_setup : - # Don't show gcc warning: 'stdcall' attribute ignored [-Wattributes] - '$(TEST_HC)' $(TEST_HC_OPTS) $(ghciWayFlags) -c -optc=-Wno-attributes T1288_ghci_c.c + '$(TEST_HC)' $(TEST_HC_OPTS) $(ghciWayFlags) -c T1288_ghci_c.c T2276_ghci_setup : - # Don't show gcc warning: 'stdcall' attribute ignored [-Wattributes] - '$(TEST_HC)' $(TEST_HC_OPTS) $(ghciWayFlags) -c -optc=-Wno-attributes T2276_ghci_c.c + '$(TEST_HC)' $(TEST_HC_OPTS) $(ghciWayFlags) -c T2276_ghci_c.c ffi002_setup : '$(TEST_HC)' $(TEST_HC_OPTS) -c ffi002.hs ===================================== testsuite/tests/ffi/should_run/all.T ===================================== @@ -33,7 +33,6 @@ test('ffi004', skip, compile_and_run, ['']) # test('ffi005', [ omit_ways(prof_ways), when(arch('i386'), skip), - when(platform('i386-apple-darwin'), expect_broken(4105)), exit_code(3), req_c ], compile_and_run, ['ffi005_c.c']) @@ -101,7 +100,6 @@ test('T1288_ghci', test('T2276', [req_c], compile_and_run, ['T2276_c.c']) test('T2276_ghci', [ only_ghci, - when(opsys('darwin'), skip), # stdcall not supported on OS X pre_cmd('$MAKE -s --no-print-directory T2276_ghci_setup') ], compile_and_run, ['-fobject-code T2276_ghci_c.o']) ===================================== testsuite/tests/numeric/should_run/all.T ===================================== @@ -7,7 +7,7 @@ test('arith001', normal, compile_and_run, ['']) test('arith002', normal, compile_and_run, ['']) test('arith003', normal, compile_and_run, ['']) test('arith004', normal, compile_and_run, ['']) -test('arith005', when(platform('i386-apple-darwin'), expect_broken_for(7043, ['ghci'])), compile_and_run, ['']) +test('arith005', normal, compile_and_run, ['']) test('arith006', normal, compile_and_run, ['']) test('arith007', normal, compile_and_run, ['']) ===================================== testsuite/tests/rts/T10672/Makefile ===================================== @@ -5,7 +5,3 @@ include $(TOP)/mk/test.mk T10672_x64: '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -rtsopts=none -fforce-recomp -lgcc_s_seh-1 -package system-cxx-std-lib Main.hs Printf.hs cxxy.cpp - -T10672_x86: - '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -rtsopts=none -fforce-recomp -lgcc_s_dw2-1 -package system-cxx-std-lib \ - Main.hs Printf.hs cxxy.cpp ===================================== testsuite/tests/rts/T10672/all.T ===================================== @@ -3,9 +3,3 @@ test('T10672_x64', unless(opsys('mingw32'), skip), unless(arch('x86_64'), skip), when(opsys('mingw32'), expect_broken(16390))], makefile_test, ['T10672_x64']) - -test('T10672_x86', - [extra_files(['Main.hs', 'Printf.hs', 'cxxy.cpp']), - unless(opsys('mingw32'), skip), unless(arch('i386'), skip), - when(opsys('mingw32'), expect_broken(16390))], - makefile_test, ['T10672_x86']) ===================================== testsuite/tests/rts/all.T ===================================== @@ -38,7 +38,6 @@ test('derefnull', when(opsys('openbsd'), ignore_stderr), # SIGBUS on OX X (PPC and x86 only; amd64 gives SEGV) # The output under OS X is too unstable to readily compare - when(platform('i386-apple-darwin'), [ignore_stderr, exit_code(139)]), when(platform('x86_64-apple-darwin'), [ignore_stderr, exit_code(139)]), when(platform('aarch64-apple-darwin'), [ignore_stderr, exit_code(139)]), when(opsys('mingw32'), [ignore_stderr, exit_code(11)]), @@ -80,7 +79,6 @@ test('divbyzero', when(opsys('mingw32'), [ignore_stderr, exit_code(8)]), when(opsys('mingw32'), [fragile(18548)]), # The output under OS X is too unstable to readily compare - when(platform('i386-apple-darwin'), [ignore_stderr, exit_code(136)]), when(platform('x86_64-apple-darwin'), [ignore_stderr, exit_code(136)]), # ThreadSanitizer changes the output when(have_thread_sanitizer(), skip), ===================================== utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs ===================================== @@ -148,8 +148,6 @@ addPlatformDepCcFlags archOs cc0 = do let cc1 = addWorkaroundFor7799 archOs cc0 -- As per FPTOOLS_SET_C_LD_FLAGS case archOs of - ArchOS ArchX86 OSMinGW32 -> - return $ cc1 & _ccFlags %++ "-march=i686" ArchOS ArchX86 OSFreeBSD -> return $ cc1 & _ccFlags %++ "-march=i686" ArchOS ArchX86_64 OSSolaris2 -> @@ -183,4 +181,3 @@ addWorkaroundFor7799 :: ArchOS -> Cc -> Cc addWorkaroundFor7799 archOs cc | ArchX86 <- archOS_arch archOs = cc & _ccFlags %++ "-U__i686" | otherwise = cc - ===================================== utils/llvm-targets/gen-data-layout.sh ===================================== @@ -89,13 +89,10 @@ TARGETS=( ######################### # macOS - "i386-apple-darwin" "x86_64-apple-darwin" "arm64-apple-darwin" # iOS - "armv7-apple-ios" "arm64-apple-ios" - "i386-apple-ios" "x86_64-apple-ios" ######################### View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f75241e50c1496f43f215480ee1bafa210f4c278...235e496b9094c9aaf1df77b47aa5c0891767b6d1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f75241e50c1496f43f215480ee1bafa210f4c278...235e496b9094c9aaf1df77b47aa5c0891767b6d1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 14:16:51 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 04 Jun 2024 10:16:51 -0400 Subject: [Git][ghc/ghc][wip/T24676] Instantiation variables can leak into the constraint solver, just Message-ID: <665f21d378e0a_2016182259707193@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24676 at Glasgow Haskell Compiler / GHC Commits: 6d024220 by Simon Peyton Jones at 2024-06-04T15:16:26+01:00 Instantiation variables can leak into the constraint solver, just - - - - - 3 changed files: - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Solver/Equality.hs - testsuite/tests/typecheck/should_fail/VisFlag1_ql.stderr Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -123,7 +123,8 @@ Note [Instantiation variables are short lived] See Section 4.3 "Applications and instantiation" of the paper. -* The constraint solver never sees an instantiation variable. +* The constraint solver never sees an instantiation variable [not quite true; + see below] However, the constraint solver can see a meta-type-variable filled in with a polytype (#18987). Suppose @@ -145,6 +146,21 @@ Note [Instantiation variables are short lived] Since the constraint solver does not do implicit instantiation (as the constraint generator does), the fact that a unification variable might stand for a polytype does not matter. + +* Actually, sadly the constraint solver /can/ see an instantiation variable. + Consider this from test VisFlag1_ql: + f :: forall {k} {a :: k} (hk :: forall j. j -> Type). hk a -> () + + bad_wild :: () + bad_wild = f @_ MkV + In tcInstFun instantiate f with [k:=k0, a:=a0], and then encounter the `@_`, + expecting it to have kind (forall j. j->Type). We make a fresh variable (it'll + be an instantiation variable since we are in tcInstFun) for the `_`, thus + (_ : k0) and do `checkExpectedKind` to match up `k0` with `forall j. j->Type`. + The unifier doesn't solve it (it does not unify instantiation variables) so + it leaves it for the constraint solver. Yuk. It's hard to see what to do + about this, but it seems to do no harm for the constraint solver to see the + occasional instantiation variable. -} ===================================== compiler/GHC/Tc/Solver/Equality.hs ===================================== @@ -1821,9 +1821,6 @@ canEqCanLHSFinish ev eq_rel swapped lhs rhs , text "lhs:" <+> ppr lhs , text "rhs:" <+> ppr rhs ] - -- Assertion: no QL instantiation tyvars - ; massertPpr (not (ql_inst_tv lhs)) (ppr lhs) - -- Assertion: (TyEq:K) is already satisfied ; massert (canEqLHSKind lhs `eqType` typeKind rhs) @@ -1835,9 +1832,6 @@ canEqCanLHSFinish ev eq_rel swapped lhs rhs ; canEqCanLHSFinish_try_unification ev eq_rel swapped lhs rhs } where - ql_inst_tv (TyVarLHS tv) = isQLInstTyVar tv - ql_inst_tv (TyFamLHS {}) = False - -- This is about (TyEq:N): check that we don't have a saturated application -- of a newtype TyCon at the top level of the RHS, if the constructor -- of the newtype is in scope. ===================================== testsuite/tests/typecheck/should_fail/VisFlag1_ql.stderr ===================================== @@ -6,12 +6,11 @@ VisFlag1_ql.hs:14:16: error: [GHC-83865] In the expression: f @V MkV In an equation for ‘bad_tyapp’: bad_tyapp = f @V MkV -VisFlag1_ql.hs:17:17: error: [GHC-83865] - • Expecting one more argument to ‘V’ - Expected kind ‘forall j. j -> *’, - but ‘V’ has kind ‘forall k -> k -> *’ - • In the second argument of ‘f’, namely ‘MkV’ - In the expression: f @_ MkV +VisFlag1_ql.hs:17:15: error: [GHC-91028] + • Expected kind ‘forall j. j -> *’, but ‘_’ has kind ‘k0’ + Cannot instantiate unification variable ‘k0’ + with a kind involving polytypes: forall j. j -> * + • In the expression: f @_ MkV In an equation for ‘bad_wild’: bad_wild = f @_ MkV VisFlag1_ql.hs:20:15: error: [GHC-83865] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6d0242204ede318af23ff74b324b3399a6ec5415 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6d0242204ede318af23ff74b324b3399a6ec5415 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 14:59:08 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 04 Jun 2024 10:59:08 -0400 Subject: [Git][ghc/ghc][wip/T24868] Undo recovery code Message-ID: <665f2bbc12f27_2016187995f01351c@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24868 at Glasgow Haskell Compiler / GHC Commits: dd833da4 by Simon Peyton Jones at 2024-06-04T15:58:33+01:00 Undo recovery code .. it caused a cascade of follow on errors - - - - - 1 changed file: - compiler/GHC/Tc/Gen/App.hs Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -532,6 +532,8 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args , text "fun_ctxt" <+> ppr fun_ctxt , text "args:" <+> ppr rn_args , text "do_ql" <+> ppr do_ql ]) + -- Recover from fatal failures in kind-checking type arguments + -- which are fatal ; go emptyVarSet [] [] fun_sigma rn_args } where fun_orig @@ -662,14 +664,9 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args -- Rule ITYARG from Fig 4 of the QL paper go1 delta acc so_far fun_ty ( ETypeArg { eva_ctxt = ctxt, eva_hs_ty = hs_ty } : rest_args ) - = do { mb_res <- attemptM $ tcVTA fun_conc_tvs fun_ty hs_ty - ; case mb_res of { - Nothing -> -- Failure to kind-check the type, or fun_ty is not a forall; - -- just ignore it the type argument and carry on - go delta acc so_far fun_ty rest_args ; - Just (ty_arg, inst_ty) -> - do { let arg' = ETypeArg { eva_ctxt = ctxt, eva_hs_ty = hs_ty, eva_ty = ty_arg } - ; go delta (arg' : acc) so_far inst_ty rest_args } } } + = do { (ty_arg, inst_ty) <- tcVTA fun_conc_tvs fun_ty hs_ty + ; let arg' = ETypeArg { eva_ctxt = ctxt, eva_hs_ty = hs_ty, eva_ty = ty_arg } + ; go delta (arg' : acc) so_far inst_ty rest_args } -- Rule IVAR from Fig 4 of the QL paper: go1 delta acc so_far fun_ty args@(EValArg {} : _) @@ -851,24 +848,11 @@ tcVTA conc_tvs fun_ty hs_ty ; failWith $ TcRnInvalidTypeApplication fun_ty hs_ty } -- See Note [Visible type application and abstraction] -tcVDQ, tcVDQ' - :: ConcreteTyVars -- See Note [Representation-polymorphism checking built-ins] +tcVDQ :: ConcreteTyVars -- See Note [Representation-polymorphism checking built-ins] -> (ForAllTyBinder, TcType) -- Function type -> LHsExpr GhcRn -- Argument type -> TcM (TcType, TcType) tcVDQ conc_tvs (tvb,inner_ty) arg - = do { mb_res <- attemptM $ tcVDQ' conc_tvs (tvb,inner_ty) arg - ; case mb_res of { - Just res -> return res ; - Nothing -> - do { -- Recovery code. Pretend the type arg is just a meta-tyvar - ; let tv = binderVar tvb - ; fake_ty_arg <- newFlexiTyVarTy (tyVarKind tv) - ; let in_scope = mkInScopeSet (tyCoVarsOfTypes [mkForAllTy tvb inner_ty,fake_ty_arg]) - insted_ty = substTyWithInScope in_scope [tv] [fake_ty_arg] inner_ty - ; return (fake_ty_arg, insted_ty) } } } - -tcVDQ' conc_tvs (tvb, inner_ty) arg = do { hs_wc_ty <- expr_to_type arg ; tc_inst_forall_arg conc_tvs (tvb, inner_ty) hs_wc_ty } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dd833da4687e7783fc5c2bb073207bca5abe0474 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/dd833da4687e7783fc5c2bb073207bca5abe0474 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 15:02:01 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 04 Jun 2024 11:02:01 -0400 Subject: [Git][ghc/ghc][wip/T24676] Remove dead Delta Message-ID: <665f2c69ac0a3_20161894f110174c1@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24676 at Glasgow Haskell Compiler / GHC Commits: 820c9b16 by Simon Peyton Jones at 2024-06-04T16:01:42+01:00 Remove dead Delta - - - - - 1 changed file: - compiler/GHC/Tc/Gen/App.hs Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -625,8 +625,6 @@ zonkArg arg = return arg * * ********************************************************************* -} -type Delta = Bool -- True <=> at least one instantiation variable - tcInstFun :: QLFlag -> Bool -- False <=> Instantiate only /inferred/ variables at the end -- so may return a sigma-type @@ -649,9 +647,7 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args , text "fun_ctxt" <+> ppr fun_ctxt , text "args:" <+> ppr rn_args , text "do_ql" <+> ppr do_ql ]) - ; (_delta, inst_args, res_rho) <- go 1 False [] fun_sigma rn_args - -- ToDo: remove delta from go - ; return (inst_args, res_rho) } + ; go 1 [] fun_sigma rn_args } where fun_orig = case fun_ctxt of VAExpansion (OrigStmt{}) _ _ -> DoOrigin @@ -695,34 +691,33 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args ----------- go, go1 :: Int -- Value-argument position of next arg - -> Delta -- True <=> at least one instantiation variable -> [HsExprArg 'TcpInst] -- Accumulator, reversed -> TcSigmaType -> [HsExprArg 'TcpRn] - -> TcM (Delta, [HsExprArg 'TcpInst], TcSigmaType) + -> TcM ([HsExprArg 'TcpInst], TcSigmaType) -- go: If fun_ty=kappa, look it up in Theta - go pos delta acc fun_ty args + go pos acc fun_ty args | Just kappa <- getTyVar_maybe fun_ty , isQLInstTyVar kappa = do { cts <- readMetaTyVar kappa ; case cts of - Indirect fun_ty' -> go pos delta acc fun_ty' args - Flexi -> go1 pos delta acc fun_ty args } + Indirect fun_ty' -> go pos acc fun_ty' args + Flexi -> go1 pos acc fun_ty args } | otherwise - = go1 pos delta acc fun_ty args + = go1 pos acc fun_ty args -- go1: fun_ty is not filled-in instantiation variable -- ('go' dealt with that case) -- Handle out-of-scope functions gracefully - go1 pos delta acc fun_ty (arg : rest_args) + go1 pos acc fun_ty (arg : rest_args) | fun_is_out_of_scope, looks_like_type_arg arg -- See Note [VTA for out-of-scope functions] - = go pos delta acc fun_ty rest_args + = go pos acc fun_ty rest_args -- Rule IALL from Fig 4 of the QL paper; applies even if args = [] -- Instantiate invisible foralls and dictionaries. -- c.f. GHC.Tc.Utils.Instantiate.topInstantiate - go1 pos delta acc fun_ty args + go1 pos acc fun_ty args | (tvs, body1) <- tcSplitSomeForAllTyVars (inst_fun args) fun_ty , (theta, body2) <- if inst_fun args Inferred then tcSplitPhiTy body1 @@ -750,41 +745,40 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args -- argument of (#,#) to @LiftedRep, but want to rule out the -- second instantiation @r. - ; go pos (delta || not no_tvs) - (addArgWrap wrap acc) fun_rho args } + ; go pos (addArgWrap wrap acc) fun_rho args } -- Going around again means we deal easily with -- nested forall a. Eq a => forall b. Show b => blah -- Rule IRESULT from Fig 4 of the QL paper; no more arguments - go1 _pos delta acc fun_ty [] + go1 _pos acc fun_ty [] = do { traceTc "tcInstFun:ret" (ppr fun_ty) - ; return (delta, reverse acc, fun_ty) } + ; return (reverse acc, fun_ty) } -- Rule ITVDQ from the GHC Proposal #281 - go1 pos delta acc fun_ty ((EValArg { ea_arg = arg }) : rest_args) + go1 pos acc fun_ty ((EValArg { ea_arg = arg }) : rest_args) | Just (tvb, body) <- tcSplitForAllTyVarBinder_maybe fun_ty = assertPpr (binderFlag tvb == Required) (ppr fun_ty $$ ppr arg) $ -- Any invisible binders have been instantiated by IALL above, -- so this forall must be visible (i.e. Required) do { (ty_arg, inst_body) <- tcVDQ fun_conc_tvs (tvb, body) arg ; let wrap = mkWpTyApps [ty_arg] - ; go (pos+1) delta (addArgWrap wrap acc) inst_body rest_args } + ; go (pos+1) (addArgWrap wrap acc) inst_body rest_args } - go1 pos delta acc fun_ty (EWrap w : args) - = go1 pos delta (EWrap w : acc) fun_ty args + go1 pos acc fun_ty (EWrap w : args) + = go1 pos (EWrap w : acc) fun_ty args - go1 pos delta acc fun_ty (EPrag sp prag : args) - = go1 pos delta (EPrag sp prag : acc) fun_ty args + go1 pos acc fun_ty (EPrag sp prag : args) + = go1 pos (EPrag sp prag : acc) fun_ty args -- Rule ITYARG from Fig 4 of the QL paper - go1 pos delta acc fun_ty ( ETypeArg { ea_ctxt = ctxt, ea_hs_ty = hs_ty } + go1 pos acc fun_ty ( ETypeArg { ea_ctxt = ctxt, ea_hs_ty = hs_ty } : rest_args ) = do { (ty_arg, inst_ty) <- tcVTA fun_conc_tvs fun_ty hs_ty ; let arg' = ETypeArg { ea_ctxt = ctxt, ea_hs_ty = hs_ty, ea_ty_arg = ty_arg } - ; go pos delta (arg' : acc) inst_ty rest_args } + ; go pos (arg' : acc) inst_ty rest_args } -- Rule IVAR from Fig 4 of the QL paper: - go1 pos _ acc fun_ty args@(EValArg {} : _) + go1 pos acc fun_ty args@(EValArg {} : _) | Just kappa <- getTyVar_maybe fun_ty , isQLInstTyVar kappa = -- Function type was of form f :: forall a b. t1 -> t2 -> b @@ -799,8 +793,6 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args -- matchActualFunTys is much more general, has a loop, etc. -- - We must be sure to actually update the variable right now, -- not defer in any way, because this is a QL instantiation variable. - -- - We need the freshly allocated unification variables, to extend - -- delta with. -- It's easier just to do the job directly here. do { arg_tys <- zipWithM new_arg_ty (leadingValArgs args) [pos..] ; res_ty <- newOpenFlexiTyVarTy @@ -818,10 +810,10 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args -- Then fun_ty :: kk, fun_ty' :: Type, kind_co :: Type ~ kk -- co_wrap :: (fun_ty' |> kind_co) ~ fun_ty' - ; go pos True acc' fun_ty' args } + ; go pos acc' fun_ty' args } -- Rule IARG from Fig 4 of the QL paper: - go1 pos delta acc fun_ty + go1 pos acc fun_ty (EValArg { ea_arg = arg, ea_ctxt = ctxt } : rest_args) = do { let herald = case fun_ctxt of VAExpansion (OrigStmt{}) _ _ -> ExpectedFunTySyntaxOp DoOrigin tc_fun @@ -838,7 +830,7 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args ; arg' <- quickLookArg do_ql ctxt arg arg_ty ; let acc' = arg' : addArgWrap wrap acc - ; go (pos+1) delta acc' res_ty rest_args } + ; go (pos+1) acc' res_ty rest_args } new_arg_ty :: LHsExpr GhcRn -> Int -> TcM (Scaled TcType) -- Make a fresh nus for each argument in rule IVAR @@ -1623,11 +1615,6 @@ quickLookArg :: QLFlag -> AppCtxt -> Scaled TcSigmaTypeFRR -- ^ Type expected by the function -> TcM (HsExprArg 'TcpInst) -- See Note [Quick Look at value arguments] --- --- The returned Delta is a superset of the one passed in --- with added instantiation variables from --- (a) the call itself --- (b) the arguments of the call quickLookArg NoQL ctxt larg orig_arg_ty = skipQuickLook ctxt larg orig_arg_ty quickLookArg DoQL ctxt larg orig_arg_ty @@ -1844,7 +1831,7 @@ which has no free instantiation variables, so we can QL-unify -} anyFreeKappa :: TcType -> TcM Bool --- True if there is a free instantiation variable (member of Delta) +-- True if there is a free instantiation variable -- in the argument type, after zonking -- See Note [The fiv test in quickLookArg] anyFreeKappa ty = unTcMBool (foldQLInstVars go_tv ty) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/820c9b16ee0cf4f6b299d074048430ee4d815be1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/820c9b16ee0cf4f6b299d074048430ee4d815be1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 16:09:46 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Jun 2024 12:09:46 -0400 Subject: [Git][ghc/ghc][master] Add AArch64 CLZ, CTZ, RBIT primop implementations. Message-ID: <665f3c4ae46e9_201618123f0a43171@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 5 changed files: - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - + testsuite/tests/codeGen/should_run/CtzClz0.hs - testsuite/tests/codeGen/should_run/all.T Changes: ===================================== compiler/GHC/CmmToAsm/AArch64/CodeGen.hs ===================================== @@ -1757,6 +1757,137 @@ genCCall target dest_regs arg_regs bid = do truncateReg W64 w lo , Nothing) | otherwise -> unsupported (MO_U_Mul2 w) + PrimTarget (MO_Clz w) + | w == W64 || w == W32 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst_reg = getRegisterReg platform (CmmLocal dst) + return ( + code_x `snocOL` + CLZ (OpReg w dst_reg) (OpReg w reg_a) + , Nothing) + | w == W16 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst' = getRegisterReg platform (CmmLocal dst) + r n = OpReg W32 n + imm n = OpImm (ImmInt n) + {- dst = clz(x << 16 | 0x0000_8000) -} + return ( + code_x `appOL` toOL + [ LSL (r dst') (r reg_a) (imm 16) + , ORR (r dst') (r dst') (imm 0x00008000) + , CLZ (r dst') (r dst') + ] + , Nothing) + | w == W8 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst' = getRegisterReg platform (CmmLocal dst) + r n = OpReg W32 n + imm n = OpImm (ImmInt n) + {- dst = clz(x << 24 | 0x0080_0000) -} + return ( + code_x `appOL` toOL + [ LSL (r dst') (r reg_a) (imm 24) + , ORR (r dst') (r dst') (imm 0x00800000) + , CLZ (r dst') (r dst') + ] + , Nothing) + | otherwise -> unsupported (MO_Clz w) + PrimTarget (MO_Ctz w) + | w == W64 || w == W32 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst_reg = getRegisterReg platform (CmmLocal dst) + return ( + code_x `snocOL` + RBIT (OpReg w dst_reg) (OpReg w reg_a) `snocOL` + CLZ (OpReg w dst_reg) (OpReg w dst_reg) + , Nothing) + | w == W16 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst' = getRegisterReg platform (CmmLocal dst) + r n = OpReg W32 n + imm n = OpImm (ImmInt n) + {- dst = clz(reverseBits(x) | 0x0000_8000) -} + return ( + code_x `appOL` toOL + [ RBIT (r dst') (r reg_a) + , ORR (r dst') (r dst') (imm 0x00008000) + , CLZ (r dst') (r dst') + ] + , Nothing) + | w == W8 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst' = getRegisterReg platform (CmmLocal dst) + r n = OpReg W32 n + imm n = OpImm (ImmInt n) + {- dst = clz(reverseBits(x) | 0x0080_0000) -} + return ( + code_x `appOL` toOL + [ RBIT (r dst') (r reg_a) + , ORR (r dst') (r dst') (imm 0x00800000) + , CLZ (r dst') (r dst') + ] + , Nothing) + | otherwise -> unsupported (MO_Ctz w) + PrimTarget (MO_BRev w) + | w == W64 || w == W32 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst_reg = getRegisterReg platform (CmmLocal dst) + return ( + code_x `snocOL` + RBIT (OpReg w dst_reg) (OpReg w reg_a) + , Nothing) + | w == W16 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst' = getRegisterReg platform (CmmLocal dst) + r n = OpReg W32 n + imm n = OpImm (ImmInt n) + {- dst = reverseBits32(x << 16) -} + return ( + code_x `appOL` toOL + [ LSL (r dst') (r reg_a) (imm 16) + , RBIT (r dst') (r dst') + ] + , Nothing) + | w == W8 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst' = getRegisterReg platform (CmmLocal dst) + r n = OpReg W32 n + imm n = OpImm (ImmInt n) + {- dst = reverseBits32(x << 24) -} + return ( + code_x `appOL` toOL + [ LSL (r dst') (r reg_a) (imm 24) + , RBIT (r dst') (r dst') + ] + , Nothing) + | otherwise -> unsupported (MO_BRev w) -- or a possibly side-effecting machine operation @@ -1883,10 +2014,7 @@ genCCall target dest_regs arg_regs bid = do MO_PopCnt w -> mkCCall (popCntLabel w) MO_Pdep w -> mkCCall (pdepLabel w) MO_Pext w -> mkCCall (pextLabel w) - MO_Clz w -> mkCCall (clzLabel w) - MO_Ctz w -> mkCCall (ctzLabel w) MO_BSwap w -> mkCCall (bSwapLabel w) - MO_BRev w -> mkCCall (bRevLabel w) -- -- Atomic read-modify-write. MO_AtomicRead w ord ===================================== compiler/GHC/CmmToAsm/AArch64/Instr.hs ===================================== @@ -100,6 +100,8 @@ regUsageOfInstr platform instr = case instr of UXTB dst src -> usage (regOp src, regOp dst) SXTH dst src -> usage (regOp src, regOp dst) UXTH dst src -> usage (regOp src, regOp dst) + CLZ dst src -> usage (regOp src, regOp dst) + RBIT dst src -> usage (regOp src, regOp dst) -- 3. Logical and Move Instructions ------------------------------------------ AND dst src1 src2 -> usage (regOp src1 ++ regOp src2, regOp dst) ASR dst src1 src2 -> usage (regOp src1 ++ regOp src2, regOp dst) @@ -140,7 +142,8 @@ regUsageOfInstr platform instr = case instr of FMA _ dst src1 src2 src3 -> usage (regOp src1 ++ regOp src2 ++ regOp src3, regOp dst) - _ -> panic $ "regUsageOfInstr: " ++ instrCon instr + LOCATION{} -> panic $ "regUsageOfInstr: " ++ instrCon instr + NEWBLOCK{} -> panic $ "regUsageOfInstr: " ++ instrCon instr where -- filtering the usage is necessary, otherwise the register @@ -234,6 +237,8 @@ patchRegsOfInstr instr env = case instr of UXTB o1 o2 -> UXTB (patchOp o1) (patchOp o2) SXTH o1 o2 -> SXTH (patchOp o1) (patchOp o2) UXTH o1 o2 -> UXTH (patchOp o1) (patchOp o2) + CLZ o1 o2 -> CLZ (patchOp o1) (patchOp o2) + RBIT o1 o2 -> RBIT (patchOp o1) (patchOp o2) -- 3. Logical and Move Instructions ---------------------------------------- AND o1 o2 o3 -> AND (patchOp o1) (patchOp o2) (patchOp o3) @@ -276,7 +281,8 @@ patchRegsOfInstr instr env = case instr of FMA s o1 o2 o3 o4 -> FMA s (patchOp o1) (patchOp o2) (patchOp o3) (patchOp o4) - _ -> panic $ "patchRegsOfInstr: " ++ instrCon instr + NEWBLOCK{} -> panic $ "patchRegsOfInstr: " ++ instrCon instr + LOCATION{} -> panic $ "patchRegsOfInstr: " ++ instrCon instr where patchOp :: Operand -> Operand patchOp (OpReg w r) = OpReg w (env r) @@ -591,6 +597,8 @@ data Instr -- Signed/Unsigned bitfield extract | SBFX Operand Operand Operand Operand -- rd = rn[i,j] | UBFX Operand Operand Operand Operand -- rd = rn[i,j] + | CLZ Operand Operand -- rd = countLeadingZeros(rn) + | RBIT Operand Operand -- rd = reverseBits(rn) -- 3. Logical and Move Instructions ---------------------------------------- | AND Operand Operand Operand -- rd = rn & op2 @@ -676,6 +684,8 @@ instrCon i = UBFM{} -> "UBFM" SBFX{} -> "SBFX" UBFX{} -> "UBFX" + CLZ{} -> "CLZ" + RBIT{} -> "RBIT" AND{} -> "AND" ASR{} -> "ASR" EOR{} -> "EOR" ===================================== compiler/GHC/CmmToAsm/AArch64/Ppr.hs ===================================== @@ -396,6 +396,8 @@ pprInstr platform instr = case instr of -- 2. Bit Manipulation Instructions ------------------------------------------ SBFM o1 o2 o3 o4 -> op4 (text "\tsbfm") o1 o2 o3 o4 UBFM o1 o2 o3 o4 -> op4 (text "\tubfm") o1 o2 o3 o4 + CLZ o1 o2 -> op2 (text "\tclz") o1 o2 + RBIT o1 o2 -> op2 (text "\trbit") o1 o2 -- signed and unsigned bitfield extract SBFX o1 o2 o3 o4 -> op4 (text "\tsbfx") o1 o2 o3 o4 UBFX o1 o2 o3 o4 -> op4 (text "\tubfx") o1 o2 o3 o4 ===================================== testsuite/tests/codeGen/should_run/CtzClz0.hs ===================================== @@ -0,0 +1,27 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE MagicHash #-} + +module Main where + +import GHC.Exts +import Control.Monad + +#include + +{-# OPAQUE x #-} -- needed to avoid triggering constant folding +x :: Word +x = 0 + +main :: IO () +main = do + let !(W# w) = x + + guard (W# (ctz# w) == WORD_SIZE_IN_BITS) + guard (W# (ctz8# w) == 8) + guard (W# (ctz16# w) == 16) + guard (W# (ctz32# w) == 32) + + guard (W# (clz# w) == WORD_SIZE_IN_BITS) + guard (W# (clz8# w) == 8) + guard (W# (clz16# w) == 16) + guard (W# (clz32# w) == 32) ===================================== testsuite/tests/codeGen/should_run/all.T ===================================== @@ -246,3 +246,4 @@ test('T24295a', normal, compile_and_run, ['-O -floopification']) test('T24295b', normal, compile_and_run, ['-O -floopification -fpedantic-bottoms']) test('T24664a', normal, compile_and_run, ['-O']) test('T24664b', normal, compile_and_run, ['-O']) +test('CtzClz0', normal, compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/71010381f4270966de334193ab2bfc67f8524212 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/71010381f4270966de334193ab2bfc67f8524212 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 16:10:48 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Jun 2024 12:10:48 -0400 Subject: [Git][ghc/ghc][master] 2 commits: hadrian: add +text_simdutf flavour transformer to allow building text with simdutf Message-ID: <665f3c881a1_20161813bf30c34833@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - 8 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Flavour/Type.hs - hadrian/src/Rules/Register.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Packages.hs Changes: ===================================== .gitlab/generate-ci/gen_ci.hs ===================================== @@ -153,6 +153,7 @@ data BuildConfig , threadSanitiser :: Bool , noSplitSections :: Bool , validateNonmovingGc :: Bool + , textWithSIMDUTF :: Bool } -- Extra arguments to pass to ./configure due to the BuildConfig @@ -174,7 +175,8 @@ mkJobFlavour BuildConfig{..} = Flavour buildFlavour opts [FullyStatic | fullyStatic] ++ [ThreadSanitiser | threadSanitiser] ++ [NoSplitSections | noSplitSections, buildFlavour == Release ] ++ - [BootNonmovingGc | validateNonmovingGc ] + [BootNonmovingGc | validateNonmovingGc ] ++ + [TextWithSIMDUTF | textWithSIMDUTF] data Flavour = Flavour BaseFlavour [FlavourTrans] @@ -185,6 +187,7 @@ data FlavourTrans = | ThreadSanitiser | NoSplitSections | BootNonmovingGc + | TextWithSIMDUTF data BaseFlavour = Release | Validate | SlowValidate deriving Eq @@ -211,6 +214,7 @@ vanilla = BuildConfig , threadSanitiser = False , noSplitSections = False , validateNonmovingGc = False + , textWithSIMDUTF = False } splitSectionsBroken :: BuildConfig -> BuildConfig @@ -344,6 +348,7 @@ flavourString (Flavour base trans) = base_string base ++ concatMap (("+" ++) . f flavour_string ThreadSanitiser = "thread_sanitizer_cmm" flavour_string NoSplitSections = "no_split_sections" flavour_string BootNonmovingGc = "boot_nonmoving_gc" + flavour_string TextWithSIMDUTF = "text_simdutf" -- The path to the docker image (just for linux builders) dockerImage :: Arch -> Opsys -> Maybe String @@ -1057,6 +1062,7 @@ job_groups = { fullyStatic = True , buildFlavour = Release -- TODO: This needs to be validate but wasm backend doesn't pass yet + , textWithSIMDUTF = True } @@ -1082,10 +1088,10 @@ platform_mapping = Map.map go combined_result , "x86_64-linux-fedora33-release" , "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate" , "x86_64-windows-validate" - , "nightly-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static" + , "nightly-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf" , "nightly-x86_64-linux-deb11-validate" , "nightly-x86_64-linux-deb12-validate" - , "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static" + , "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf" , "x86_64-linux-deb12-validate+thread_sanitizer_cmm" , "nightly-aarch64-linux-deb10-validate" , "nightly-x86_64-linux-alpine3_12-validate" ===================================== .gitlab/jobs.yaml ===================================== @@ -951,7 +951,7 @@ "XZ_OPT": "-9" } }, - "nightly-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static": { + "nightly-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -962,7 +962,7 @@ "artifacts": { "expire_in": "8 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -1005,17 +1005,17 @@ ], "variables": { "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static", + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf", "XZ_OPT": "-9" } }, - "nightly-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static": { + "nightly-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -1026,7 +1026,7 @@ "artifacts": { "expire_in": "8 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -1069,17 +1069,17 @@ ], "variables": { "BIGNUM_BACKEND": "native", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static", + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf", "XZ_OPT": "-9" } }, - "nightly-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static": { + "nightly-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -1090,7 +1090,7 @@ "artifacts": { "expire_in": "8 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -1133,13 +1133,13 @@ ], "variables": { "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static", + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf", "XZ_OPT": "-9" } }, @@ -4465,7 +4465,7 @@ "TEST_ENV": "x86_64-linux-alpine3_12-validate+fully_static" } }, - "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static": { + "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -4476,7 +4476,7 @@ "artifacts": { "expire_in": "2 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -4519,16 +4519,16 @@ ], "variables": { "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static" + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf" } }, - "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static": { + "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -4539,7 +4539,7 @@ "artifacts": { "expire_in": "2 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -4583,16 +4583,16 @@ ], "variables": { "BIGNUM_BACKEND": "native", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static" + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf" } }, - "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static": { + "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -4603,7 +4603,7 @@ "artifacts": { "expire_in": "2 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -4647,13 +4647,13 @@ ], "variables": { "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static" + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf" } }, "x86_64-linux-deb10-int_native-validate": { ===================================== hadrian/doc/flavours.md ===================================== @@ -265,6 +265,10 @@ The supported transformers are listed below: native_bignum Use the native ghc-bignum backend. + + text_simdutf + Enable building the text package with simdutf support. + no_profiled_libs Disables building of libraries in profiled build ways. ===================================== hadrian/src/Flavour.hs ===================================== @@ -17,6 +17,7 @@ module Flavour , enableHaddock , enableHiCore , useNativeBignum + , enableTextWithSIMDUTF , omitPragmas , completeSetting @@ -53,6 +54,7 @@ flavourTransformers = M.fromList , "no_dynamic_ghc" =: disableDynamicGhcPrograms , "no_dynamic_libs" =: disableDynamicLibs , "native_bignum" =: useNativeBignum + , "text_simdutf" =: enableTextWithSIMDUTF , "no_profiled_libs" =: disableProfiledLibs , "omit_pragmas" =: omitPragmas , "ipe" =: enableIPE @@ -292,6 +294,12 @@ useNativeBignum flavour = flavour { bignumBackend = "native" } +-- | Enable building the @text@ package with @simdutf@ support. +enableTextWithSIMDUTF :: Flavour -> Flavour +enableTextWithSIMDUTF flavour = flavour { + textWithSIMDUTF = True +} + -- | Build stage2 compiler with -fomit-interface-pragmas to reduce -- recompilation. omitPragmas :: Flavour -> Flavour ===================================== hadrian/src/Flavour/Type.hs ===================================== @@ -23,6 +23,9 @@ data Flavour = Flavour { bignumBackend :: String, -- | Check selected bignum backend against native backend bignumCheck :: Bool, + -- | Build the @text@ package with @simdutf@ support. Disabled by + -- default due to packaging difficulties described in #20724. + textWithSIMDUTF :: Bool, -- | Build libraries these ways. libraryWays :: Ways, -- | Build RTS these ways. @@ -70,4 +73,3 @@ type DocTargets = Set DocTarget -- distribution. data DocTarget = Haddocks | SphinxHTML | SphinxPDFs | SphinxMan | SphinxInfo deriving (Eq, Ord, Show, Bounded, Enum) - ===================================== hadrian/src/Rules/Register.hs ===================================== @@ -7,6 +7,7 @@ module Rules.Register ( import Base import Context import Expression ( getContextData ) +import Flavour import Oracles.Setting import Hadrian.BuildPath import Hadrian.Expression @@ -51,6 +52,14 @@ configurePackageRules = do isGmp <- (== "gmp") <$> interpretInContext ctx getBignumBackend when isGmp $ need [buildP -/- "include/ghc-gmp.h"] + when (pkg == text) $ do + simdutf <- textWithSIMDUTF <$> flavour + when simdutf $ do + -- This is required, otherwise you get Error: hadrian: + -- Encountered missing or private dependencies: + -- system-cxx-std-lib ==1.0 + cxxStdLib <- systemCxxStdLibConfPath $ PackageDbLoc stage Inplace + need [cxxStdLib] Cabal.configurePackage ctx root -/- "**/autogen/cabal_macros.h" %> \out -> do ===================================== hadrian/src/Settings/Default.hs ===================================== @@ -267,6 +267,7 @@ defaultFlavour = Flavour , packages = defaultPackages , bignumBackend = defaultBignumBackend , bignumCheck = False + , textWithSIMDUTF = False , libraryWays = defaultLibraryWays , rtsWays = defaultRtsWays , dynamicGhcPrograms = defaultDynamicGhcPrograms ===================================== hadrian/src/Settings/Packages.hs ===================================== @@ -191,12 +191,10 @@ packageArgs = do builder (Cabal Flags) ? stage0 `cabalFlag` "bootstrap" ---------------------------------- text -------------------------------- - , package text ? mconcat - -- Disable SIMDUTF by default due to packaging difficulties - -- described in #20724. - [ builder (Cabal Flags) ? arg "-simdutf" - -- https://github.com/haskell/text/issues/415 - , builder Ghc ? input "**/Data/Text/Encoding.hs" ? arg "-Wno-unused-imports" ] + , package text ? + ifM (textWithSIMDUTF <$> expr flavour) + (builder (Cabal Flags) ? arg "+simdutf") + (builder (Cabal Flags) ? arg "-simdutf") ------------------------------- haskeline ------------------------------ -- Hadrian doesn't currently support packages containing both libraries View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/71010381f4270966de334193ab2bfc67f8524212...077cb2e11fa81076e8c9c5f8dd3bdfa99c8aaf8d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/71010381f4270966de334193ab2bfc67f8524212...077cb2e11fa81076e8c9c5f8dd3bdfa99c8aaf8d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 16:40:53 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Jun 2024 12:40:53 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: Add AArch64 CLZ, CTZ, RBIT primop implementations. Message-ID: <665f4395b0bd3_20161817b8f084681d@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - 08026887 by Teo Camarasu at 2024-06-04T12:40:36-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - fad1c253 by Teo Camarasu at 2024-06-04T12:40:36-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 7541e204 by Cheng Shao at 2024-06-04T12:40:37-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 16 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Session.hs - hadrian/doc/flavours.md - hadrian/src/Flavour.hs - hadrian/src/Flavour/Type.hs - hadrian/src/Rules/Register.hs - hadrian/src/Settings/Default.hs - hadrian/src/Settings/Packages.hs - libraries/base/src/Data/Array/Byte.hs - + testsuite/tests/codeGen/should_run/CtzClz0.hs - testsuite/tests/codeGen/should_run/all.T Changes: ===================================== .gitlab/generate-ci/gen_ci.hs ===================================== @@ -153,6 +153,7 @@ data BuildConfig , threadSanitiser :: Bool , noSplitSections :: Bool , validateNonmovingGc :: Bool + , textWithSIMDUTF :: Bool } -- Extra arguments to pass to ./configure due to the BuildConfig @@ -174,7 +175,8 @@ mkJobFlavour BuildConfig{..} = Flavour buildFlavour opts [FullyStatic | fullyStatic] ++ [ThreadSanitiser | threadSanitiser] ++ [NoSplitSections | noSplitSections, buildFlavour == Release ] ++ - [BootNonmovingGc | validateNonmovingGc ] + [BootNonmovingGc | validateNonmovingGc ] ++ + [TextWithSIMDUTF | textWithSIMDUTF] data Flavour = Flavour BaseFlavour [FlavourTrans] @@ -185,6 +187,7 @@ data FlavourTrans = | ThreadSanitiser | NoSplitSections | BootNonmovingGc + | TextWithSIMDUTF data BaseFlavour = Release | Validate | SlowValidate deriving Eq @@ -211,6 +214,7 @@ vanilla = BuildConfig , threadSanitiser = False , noSplitSections = False , validateNonmovingGc = False + , textWithSIMDUTF = False } splitSectionsBroken :: BuildConfig -> BuildConfig @@ -344,6 +348,7 @@ flavourString (Flavour base trans) = base_string base ++ concatMap (("+" ++) . f flavour_string ThreadSanitiser = "thread_sanitizer_cmm" flavour_string NoSplitSections = "no_split_sections" flavour_string BootNonmovingGc = "boot_nonmoving_gc" + flavour_string TextWithSIMDUTF = "text_simdutf" -- The path to the docker image (just for linux builders) dockerImage :: Arch -> Opsys -> Maybe String @@ -1057,6 +1062,7 @@ job_groups = { fullyStatic = True , buildFlavour = Release -- TODO: This needs to be validate but wasm backend doesn't pass yet + , textWithSIMDUTF = True } @@ -1082,10 +1088,10 @@ platform_mapping = Map.map go combined_result , "x86_64-linux-fedora33-release" , "x86_64-linux-deb11-cross_aarch64-linux-gnu-validate" , "x86_64-windows-validate" - , "nightly-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static" + , "nightly-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf" , "nightly-x86_64-linux-deb11-validate" , "nightly-x86_64-linux-deb12-validate" - , "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static" + , "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf" , "x86_64-linux-deb12-validate+thread_sanitizer_cmm" , "nightly-aarch64-linux-deb10-validate" , "nightly-x86_64-linux-alpine3_12-validate" ===================================== .gitlab/jobs.yaml ===================================== @@ -951,7 +951,7 @@ "XZ_OPT": "-9" } }, - "nightly-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static": { + "nightly-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -962,7 +962,7 @@ "artifacts": { "expire_in": "8 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -1005,17 +1005,17 @@ ], "variables": { "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static", + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf", "XZ_OPT": "-9" } }, - "nightly-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static": { + "nightly-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -1026,7 +1026,7 @@ "artifacts": { "expire_in": "8 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -1069,17 +1069,17 @@ ], "variables": { "BIGNUM_BACKEND": "native", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static", + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf", "XZ_OPT": "-9" } }, - "nightly-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static": { + "nightly-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -1090,7 +1090,7 @@ "artifacts": { "expire_in": "8 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -1133,13 +1133,13 @@ ], "variables": { "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static", + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf", "XZ_OPT": "-9" } }, @@ -4465,7 +4465,7 @@ "TEST_ENV": "x86_64-linux-alpine3_12-validate+fully_static" } }, - "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static": { + "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -4476,7 +4476,7 @@ "artifacts": { "expire_in": "2 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -4519,16 +4519,16 @@ ], "variables": { "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static" + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-cross_wasm32-wasi-release+fully_static+text_simdutf" } }, - "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static": { + "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -4539,7 +4539,7 @@ "artifacts": { "expire_in": "2 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -4583,16 +4583,16 @@ ], "variables": { "BIGNUM_BACKEND": "native", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static" + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-int_native-cross_wasm32-wasi-release+fully_static+text_simdutf" } }, - "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static": { + "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf": { "after_script": [ ".gitlab/ci.sh save_cache", ".gitlab/ci.sh save_test_output", @@ -4603,7 +4603,7 @@ "artifacts": { "expire_in": "2 weeks", "paths": [ - "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static.tar.xz", + "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf.tar.xz", "junit.xml", "unexpected-test-output.tar.gz" ], @@ -4647,13 +4647,13 @@ ], "variables": { "BIGNUM_BACKEND": "gmp", - "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static", - "BUILD_FLAVOUR": "release+fully_static", + "BIN_DIST_NAME": "ghc-x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf", + "BUILD_FLAVOUR": "release+fully_static+text_simdutf", "CONFIGURE_ARGS": "--enable-unregisterised --with-intree-gmp --with-system-libffi --enable-strict-ghc-toolchain-check", "CROSS_TARGET": "wasm32-wasi", "HADRIAN_ARGS": "--docs=none", "RUNTEST_ARGS": "", - "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static" + "TEST_ENV": "x86_64-linux-alpine3_18-wasm-unreg-cross_wasm32-wasi-release+fully_static+text_simdutf" } }, "x86_64-linux-deb10-int_native-validate": { ===================================== compiler/GHC/CmmToAsm/AArch64/CodeGen.hs ===================================== @@ -1757,6 +1757,137 @@ genCCall target dest_regs arg_regs bid = do truncateReg W64 w lo , Nothing) | otherwise -> unsupported (MO_U_Mul2 w) + PrimTarget (MO_Clz w) + | w == W64 || w == W32 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst_reg = getRegisterReg platform (CmmLocal dst) + return ( + code_x `snocOL` + CLZ (OpReg w dst_reg) (OpReg w reg_a) + , Nothing) + | w == W16 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst' = getRegisterReg platform (CmmLocal dst) + r n = OpReg W32 n + imm n = OpImm (ImmInt n) + {- dst = clz(x << 16 | 0x0000_8000) -} + return ( + code_x `appOL` toOL + [ LSL (r dst') (r reg_a) (imm 16) + , ORR (r dst') (r dst') (imm 0x00008000) + , CLZ (r dst') (r dst') + ] + , Nothing) + | w == W8 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst' = getRegisterReg platform (CmmLocal dst) + r n = OpReg W32 n + imm n = OpImm (ImmInt n) + {- dst = clz(x << 24 | 0x0080_0000) -} + return ( + code_x `appOL` toOL + [ LSL (r dst') (r reg_a) (imm 24) + , ORR (r dst') (r dst') (imm 0x00800000) + , CLZ (r dst') (r dst') + ] + , Nothing) + | otherwise -> unsupported (MO_Clz w) + PrimTarget (MO_Ctz w) + | w == W64 || w == W32 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst_reg = getRegisterReg platform (CmmLocal dst) + return ( + code_x `snocOL` + RBIT (OpReg w dst_reg) (OpReg w reg_a) `snocOL` + CLZ (OpReg w dst_reg) (OpReg w dst_reg) + , Nothing) + | w == W16 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst' = getRegisterReg platform (CmmLocal dst) + r n = OpReg W32 n + imm n = OpImm (ImmInt n) + {- dst = clz(reverseBits(x) | 0x0000_8000) -} + return ( + code_x `appOL` toOL + [ RBIT (r dst') (r reg_a) + , ORR (r dst') (r dst') (imm 0x00008000) + , CLZ (r dst') (r dst') + ] + , Nothing) + | w == W8 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst' = getRegisterReg platform (CmmLocal dst) + r n = OpReg W32 n + imm n = OpImm (ImmInt n) + {- dst = clz(reverseBits(x) | 0x0080_0000) -} + return ( + code_x `appOL` toOL + [ RBIT (r dst') (r reg_a) + , ORR (r dst') (r dst') (imm 0x00800000) + , CLZ (r dst') (r dst') + ] + , Nothing) + | otherwise -> unsupported (MO_Ctz w) + PrimTarget (MO_BRev w) + | w == W64 || w == W32 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst_reg = getRegisterReg platform (CmmLocal dst) + return ( + code_x `snocOL` + RBIT (OpReg w dst_reg) (OpReg w reg_a) + , Nothing) + | w == W16 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst' = getRegisterReg platform (CmmLocal dst) + r n = OpReg W32 n + imm n = OpImm (ImmInt n) + {- dst = reverseBits32(x << 16) -} + return ( + code_x `appOL` toOL + [ LSL (r dst') (r reg_a) (imm 16) + , RBIT (r dst') (r dst') + ] + , Nothing) + | w == W8 + , [src] <- arg_regs + , [dst] <- dest_regs + -> do + (reg_a, _format_x, code_x) <- getSomeReg src + let dst' = getRegisterReg platform (CmmLocal dst) + r n = OpReg W32 n + imm n = OpImm (ImmInt n) + {- dst = reverseBits32(x << 24) -} + return ( + code_x `appOL` toOL + [ LSL (r dst') (r reg_a) (imm 24) + , RBIT (r dst') (r dst') + ] + , Nothing) + | otherwise -> unsupported (MO_BRev w) -- or a possibly side-effecting machine operation @@ -1883,10 +2014,7 @@ genCCall target dest_regs arg_regs bid = do MO_PopCnt w -> mkCCall (popCntLabel w) MO_Pdep w -> mkCCall (pdepLabel w) MO_Pext w -> mkCCall (pextLabel w) - MO_Clz w -> mkCCall (clzLabel w) - MO_Ctz w -> mkCCall (ctzLabel w) MO_BSwap w -> mkCCall (bSwapLabel w) - MO_BRev w -> mkCCall (bRevLabel w) -- -- Atomic read-modify-write. MO_AtomicRead w ord ===================================== compiler/GHC/CmmToAsm/AArch64/Instr.hs ===================================== @@ -100,6 +100,8 @@ regUsageOfInstr platform instr = case instr of UXTB dst src -> usage (regOp src, regOp dst) SXTH dst src -> usage (regOp src, regOp dst) UXTH dst src -> usage (regOp src, regOp dst) + CLZ dst src -> usage (regOp src, regOp dst) + RBIT dst src -> usage (regOp src, regOp dst) -- 3. Logical and Move Instructions ------------------------------------------ AND dst src1 src2 -> usage (regOp src1 ++ regOp src2, regOp dst) ASR dst src1 src2 -> usage (regOp src1 ++ regOp src2, regOp dst) @@ -140,7 +142,8 @@ regUsageOfInstr platform instr = case instr of FMA _ dst src1 src2 src3 -> usage (regOp src1 ++ regOp src2 ++ regOp src3, regOp dst) - _ -> panic $ "regUsageOfInstr: " ++ instrCon instr + LOCATION{} -> panic $ "regUsageOfInstr: " ++ instrCon instr + NEWBLOCK{} -> panic $ "regUsageOfInstr: " ++ instrCon instr where -- filtering the usage is necessary, otherwise the register @@ -234,6 +237,8 @@ patchRegsOfInstr instr env = case instr of UXTB o1 o2 -> UXTB (patchOp o1) (patchOp o2) SXTH o1 o2 -> SXTH (patchOp o1) (patchOp o2) UXTH o1 o2 -> UXTH (patchOp o1) (patchOp o2) + CLZ o1 o2 -> CLZ (patchOp o1) (patchOp o2) + RBIT o1 o2 -> RBIT (patchOp o1) (patchOp o2) -- 3. Logical and Move Instructions ---------------------------------------- AND o1 o2 o3 -> AND (patchOp o1) (patchOp o2) (patchOp o3) @@ -276,7 +281,8 @@ patchRegsOfInstr instr env = case instr of FMA s o1 o2 o3 o4 -> FMA s (patchOp o1) (patchOp o2) (patchOp o3) (patchOp o4) - _ -> panic $ "patchRegsOfInstr: " ++ instrCon instr + NEWBLOCK{} -> panic $ "patchRegsOfInstr: " ++ instrCon instr + LOCATION{} -> panic $ "patchRegsOfInstr: " ++ instrCon instr where patchOp :: Operand -> Operand patchOp (OpReg w r) = OpReg w (env r) @@ -591,6 +597,8 @@ data Instr -- Signed/Unsigned bitfield extract | SBFX Operand Operand Operand Operand -- rd = rn[i,j] | UBFX Operand Operand Operand Operand -- rd = rn[i,j] + | CLZ Operand Operand -- rd = countLeadingZeros(rn) + | RBIT Operand Operand -- rd = reverseBits(rn) -- 3. Logical and Move Instructions ---------------------------------------- | AND Operand Operand Operand -- rd = rn & op2 @@ -676,6 +684,8 @@ instrCon i = UBFM{} -> "UBFM" SBFX{} -> "SBFX" UBFX{} -> "UBFX" + CLZ{} -> "CLZ" + RBIT{} -> "RBIT" AND{} -> "AND" ASR{} -> "ASR" EOR{} -> "EOR" ===================================== compiler/GHC/CmmToAsm/AArch64/Ppr.hs ===================================== @@ -396,6 +396,8 @@ pprInstr platform instr = case instr of -- 2. Bit Manipulation Instructions ------------------------------------------ SBFM o1 o2 o3 o4 -> op4 (text "\tsbfm") o1 o2 o3 o4 UBFM o1 o2 o3 o4 -> op4 (text "\tubfm") o1 o2 o3 o4 + CLZ o1 o2 -> op2 (text "\tclz") o1 o2 + RBIT o1 o2 -> op2 (text "\trbit") o1 o2 -- signed and unsigned bitfield extract SBFX o1 o2 o3 o4 -> op4 (text "\tsbfx") o1 o2 o3 o4 UBFX o1 o2 o3 o4 -> op4 (text "\tubfx") o1 o2 o3 o4 ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -60,10 +60,6 @@ module GHC.Driver.DynFlags ( versionedAppDir, versionedFilePath, extraGccViaCFlags, globalPackageDatabasePath, - -- * Linker/compiler information - LinkerInfo(..), - CompilerInfo(..), - -- * Include specifications IncludeSpecs(..), addGlobalInclude, addQuoteInclude, flattenIncludes, addImplicitQuoteInclude, @@ -758,31 +754,6 @@ data ParMakeCount -- | Use the specific semaphore @@ to control parallelism (@-jsem @ flag). | ParMakeSemaphore FilePath --- ----------------------------------------------------------------------------- --- Linker/compiler information - --- LinkerInfo contains any extra options needed by the system linker. -data LinkerInfo - = GnuLD [Option] - | Mold [Option] - | GnuGold [Option] - | LlvmLLD [Option] - | DarwinLD [Option] - | SolarisLD [Option] - | AixLD [Option] - | UnknownLD - deriving Eq - --- CompilerInfo tells us which C compiler we're using -data CompilerInfo - = GCC - | Clang - | AppleClang - | AppleClang51 - | Emscripten - | UnknownCC - deriving Eq - -- | The 'GhcMode' tells us whether we're doing multi-module -- compilation (controlled via the "GHC" API) or one-shot -- (single-module) compilation. This makes a difference primarily to ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -215,8 +215,6 @@ module GHC.Driver.Session ( isFmaEnabled, -- * Linker/compiler information - LinkerInfo(..), - CompilerInfo(..), useXLinkerRPath, -- * Include specifications ===================================== hadrian/doc/flavours.md ===================================== @@ -265,6 +265,10 @@ The supported transformers are listed below: native_bignum Use the native ghc-bignum backend. + + text_simdutf + Enable building the text package with simdutf support. + no_profiled_libs Disables building of libraries in profiled build ways. ===================================== hadrian/src/Flavour.hs ===================================== @@ -17,6 +17,7 @@ module Flavour , enableHaddock , enableHiCore , useNativeBignum + , enableTextWithSIMDUTF , omitPragmas , completeSetting @@ -53,6 +54,7 @@ flavourTransformers = M.fromList , "no_dynamic_ghc" =: disableDynamicGhcPrograms , "no_dynamic_libs" =: disableDynamicLibs , "native_bignum" =: useNativeBignum + , "text_simdutf" =: enableTextWithSIMDUTF , "no_profiled_libs" =: disableProfiledLibs , "omit_pragmas" =: omitPragmas , "ipe" =: enableIPE @@ -292,6 +294,12 @@ useNativeBignum flavour = flavour { bignumBackend = "native" } +-- | Enable building the @text@ package with @simdutf@ support. +enableTextWithSIMDUTF :: Flavour -> Flavour +enableTextWithSIMDUTF flavour = flavour { + textWithSIMDUTF = True +} + -- | Build stage2 compiler with -fomit-interface-pragmas to reduce -- recompilation. omitPragmas :: Flavour -> Flavour ===================================== hadrian/src/Flavour/Type.hs ===================================== @@ -23,6 +23,9 @@ data Flavour = Flavour { bignumBackend :: String, -- | Check selected bignum backend against native backend bignumCheck :: Bool, + -- | Build the @text@ package with @simdutf@ support. Disabled by + -- default due to packaging difficulties described in #20724. + textWithSIMDUTF :: Bool, -- | Build libraries these ways. libraryWays :: Ways, -- | Build RTS these ways. @@ -70,4 +73,3 @@ type DocTargets = Set DocTarget -- distribution. data DocTarget = Haddocks | SphinxHTML | SphinxPDFs | SphinxMan | SphinxInfo deriving (Eq, Ord, Show, Bounded, Enum) - ===================================== hadrian/src/Rules/Register.hs ===================================== @@ -7,6 +7,7 @@ module Rules.Register ( import Base import Context import Expression ( getContextData ) +import Flavour import Oracles.Setting import Hadrian.BuildPath import Hadrian.Expression @@ -51,6 +52,14 @@ configurePackageRules = do isGmp <- (== "gmp") <$> interpretInContext ctx getBignumBackend when isGmp $ need [buildP -/- "include/ghc-gmp.h"] + when (pkg == text) $ do + simdutf <- textWithSIMDUTF <$> flavour + when simdutf $ do + -- This is required, otherwise you get Error: hadrian: + -- Encountered missing or private dependencies: + -- system-cxx-std-lib ==1.0 + cxxStdLib <- systemCxxStdLibConfPath $ PackageDbLoc stage Inplace + need [cxxStdLib] Cabal.configurePackage ctx root -/- "**/autogen/cabal_macros.h" %> \out -> do ===================================== hadrian/src/Settings/Default.hs ===================================== @@ -267,6 +267,7 @@ defaultFlavour = Flavour , packages = defaultPackages , bignumBackend = defaultBignumBackend , bignumCheck = False + , textWithSIMDUTF = False , libraryWays = defaultLibraryWays , rtsWays = defaultRtsWays , dynamicGhcPrograms = defaultDynamicGhcPrograms ===================================== hadrian/src/Settings/Packages.hs ===================================== @@ -191,12 +191,10 @@ packageArgs = do builder (Cabal Flags) ? stage0 `cabalFlag` "bootstrap" ---------------------------------- text -------------------------------- - , package text ? mconcat - -- Disable SIMDUTF by default due to packaging difficulties - -- described in #20724. - [ builder (Cabal Flags) ? arg "-simdutf" - -- https://github.com/haskell/text/issues/415 - , builder Ghc ? input "**/Data/Text/Encoding.hs" ? arg "-Wno-unused-imports" ] + , package text ? + ifM (textWithSIMDUTF <$> expr flavour) + (builder (Cabal Flags) ? arg "+simdutf") + (builder (Cabal Flags) ? arg "-simdutf") ------------------------------- haskeline ------------------------------ -- Hadrian doesn't currently support packages containing both libraries ===================================== libraries/base/src/Data/Array/Byte.hs ===================================== @@ -201,10 +201,11 @@ instance Show ByteArray where | otherwise = showString ", " instance Lift ByteArray where - liftTyped x = unsafeCodeCoerce (lift x) - lift (ByteArray b) = return - (AppE (AppE (VarE addrToByteArrayName) (LitE (IntegerL (fromIntegral len)))) - (LitE (BytesPrimL (Bytes ptr 0 (fromIntegral len))))) + liftTyped = unsafeCodeCoerce . lift + lift (ByteArray b) = + [| addrToByteArray $(lift len) + $(pure . LitE . BytesPrimL $ Bytes ptr 0 (fromIntegral len)) + |] where len# = sizeofByteArray# b len = I# len# @@ -219,9 +220,7 @@ instance Lift ByteArray where ptr :: ForeignPtr Word8 ptr = ForeignPtr (byteArrayContents# pb) (PlainPtr (unsafeCoerce# pb)) -addrToByteArrayName :: Name -addrToByteArrayName = 'addrToByteArray - +{-# NOINLINE addrToByteArray #-} addrToByteArray :: Int -> Addr# -> ByteArray addrToByteArray (I# len) addr = runST $ ST $ \s -> case newByteArray# len s of ===================================== testsuite/tests/codeGen/should_run/CtzClz0.hs ===================================== @@ -0,0 +1,27 @@ +{-# LANGUAGE CPP #-} +{-# LANGUAGE MagicHash #-} + +module Main where + +import GHC.Exts +import Control.Monad + +#include + +{-# OPAQUE x #-} -- needed to avoid triggering constant folding +x :: Word +x = 0 + +main :: IO () +main = do + let !(W# w) = x + + guard (W# (ctz# w) == WORD_SIZE_IN_BITS) + guard (W# (ctz8# w) == 8) + guard (W# (ctz16# w) == 16) + guard (W# (ctz32# w) == 32) + + guard (W# (clz# w) == WORD_SIZE_IN_BITS) + guard (W# (clz8# w) == 8) + guard (W# (clz16# w) == 16) + guard (W# (clz32# w) == 32) ===================================== testsuite/tests/codeGen/should_run/all.T ===================================== @@ -246,3 +246,4 @@ test('T24295a', normal, compile_and_run, ['-O -floopification']) test('T24295b', normal, compile_and_run, ['-O -floopification -fpedantic-bottoms']) test('T24664a', normal, compile_and_run, ['-O']) test('T24664b', normal, compile_and_run, ['-O']) +test('CtzClz0', normal, compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/789846b41e08c4d65affc9422205c6b38941ffb1...7541e2046e24ed1abf1066689ec2a0f4ea3ec9b2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/789846b41e08c4d65affc9422205c6b38941ffb1...7541e2046e24ed1abf1066689ec2a0f4ea3ec9b2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 4 22:37:19 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 04 Jun 2024 18:37:19 -0400 Subject: [Git][ghc/ghc][wip/T24676] One more error message change Message-ID: <665f971f17f8b_28ddc13c4fb4853d1@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24676 at Glasgow Haskell Compiler / GHC Commits: f60ff66c by Simon Peyton Jones at 2024-06-04T23:36:54+01:00 One more error message change - - - - - 1 changed file: - testsuite/tests/typecheck/should_fail/T8450.stderr Changes: ===================================== testsuite/tests/typecheck/should_fail/T8450.stderr ===================================== @@ -1,15 +1,15 @@ -T8450.hs:8:18: error: [GHC-25897] +T8450.hs:8:19: error: [GHC-25897] • Couldn't match type ‘a’ with ‘Bool’ - Expected: Either Bool a + Expected: Either Bool () Actual: Either a () ‘a’ is a rigid type variable bound by the type signature for: run :: forall a. a at T8450.hs:7:1-18 - • In the first argument of ‘runEffect’, namely + • In the second argument of ‘($)’, namely ‘(undefined :: Either a ())’ - In the expression: runEffect (undefined :: Either a ()) + In the expression: runEffect $ (undefined :: Either a ()) In an equation for ‘run’: - run = runEffect (undefined :: Either a ()) + run = runEffect $ (undefined :: Either a ()) • Relevant bindings include run :: a (bound at T8450.hs:8:1) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f60ff66ce2e68cbbe0c4672140534265d1178f17 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f60ff66ce2e68cbbe0c4672140534265d1178f17 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 02:51:23 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Jun 2024 22:51:23 -0400 Subject: [Git][ghc/ghc][master] 2 commits: base: Use TemplateHaskellQuotes in instance Lift ByteArray Message-ID: <665fd2ab3ee59_28ddc33fbb98103128@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 1 changed file: - libraries/base/src/Data/Array/Byte.hs Changes: ===================================== libraries/base/src/Data/Array/Byte.hs ===================================== @@ -201,10 +201,11 @@ instance Show ByteArray where | otherwise = showString ", " instance Lift ByteArray where - liftTyped x = unsafeCodeCoerce (lift x) - lift (ByteArray b) = return - (AppE (AppE (VarE addrToByteArrayName) (LitE (IntegerL (fromIntegral len)))) - (LitE (BytesPrimL (Bytes ptr 0 (fromIntegral len))))) + liftTyped = unsafeCodeCoerce . lift + lift (ByteArray b) = + [| addrToByteArray $(lift len) + $(pure . LitE . BytesPrimL $ Bytes ptr 0 (fromIntegral len)) + |] where len# = sizeofByteArray# b len = I# len# @@ -219,9 +220,7 @@ instance Lift ByteArray where ptr :: ForeignPtr Word8 ptr = ForeignPtr (byteArrayContents# pb) (PlainPtr (unsafeCoerce# pb)) -addrToByteArrayName :: Name -addrToByteArrayName = 'addrToByteArray - +{-# NOINLINE addrToByteArray #-} addrToByteArray :: Int -> Addr# -> ByteArray addrToByteArray (I# len) addr = runST $ ST $ \s -> case newByteArray# len s of View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/077cb2e11fa81076e8c9c5f8dd3bdfa99c8aaf8d...3fd25743ea14c9c99efc9e1da66ee35371d1fc93 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/077cb2e11fa81076e8c9c5f8dd3bdfa99c8aaf8d...3fd25743ea14c9c99efc9e1da66ee35371d1fc93 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 02:51:54 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Jun 2024 22:51:54 -0400 Subject: [Git][ghc/ghc][master] compiler: remove unused CompilerInfo/LinkerInfo types Message-ID: <665fd2ca51df4_28ddc35a95bc1062ab@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 2 changed files: - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Session.hs Changes: ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -60,10 +60,6 @@ module GHC.Driver.DynFlags ( versionedAppDir, versionedFilePath, extraGccViaCFlags, globalPackageDatabasePath, - -- * Linker/compiler information - LinkerInfo(..), - CompilerInfo(..), - -- * Include specifications IncludeSpecs(..), addGlobalInclude, addQuoteInclude, flattenIncludes, addImplicitQuoteInclude, @@ -758,31 +754,6 @@ data ParMakeCount -- | Use the specific semaphore @@ to control parallelism (@-jsem @ flag). | ParMakeSemaphore FilePath --- ----------------------------------------------------------------------------- --- Linker/compiler information - --- LinkerInfo contains any extra options needed by the system linker. -data LinkerInfo - = GnuLD [Option] - | Mold [Option] - | GnuGold [Option] - | LlvmLLD [Option] - | DarwinLD [Option] - | SolarisLD [Option] - | AixLD [Option] - | UnknownLD - deriving Eq - --- CompilerInfo tells us which C compiler we're using -data CompilerInfo - = GCC - | Clang - | AppleClang - | AppleClang51 - | Emscripten - | UnknownCC - deriving Eq - -- | The 'GhcMode' tells us whether we're doing multi-module -- compilation (controlled via the "GHC" API) or one-shot -- (single-module) compilation. This makes a difference primarily to ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -215,8 +215,6 @@ module GHC.Driver.Session ( isFmaEnabled, -- * Linker/compiler information - LinkerInfo(..), - CompilerInfo(..), useXLinkerRPath, -- * Include specifications View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/98ad1ea5ea9f113335df591cab362d841ee7b96b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/98ad1ea5ea9f113335df591cab362d841ee7b96b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 03:53:22 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 04 Jun 2024 23:53:22 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: base: Use TemplateHaskellQuotes in instance Lift ByteArray Message-ID: <665fe132e81c_28ddc3dd0de410809f@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 32e89ba6 by Cheng Shao at 2024-06-04T23:52:57-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 848d5160 by Sylvain Henry at 2024-06-04T23:53:09-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - 9 changed files: - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Session.hs - libraries/base/src/Data/Array/Byte.hs - − rts/AdjustorAsm.S - rts/RtsFlags.h - − rts/adjustor/NativeIA64.c - − rts/adjustor/NativePowerPC.c - rts/include/rts/storage/ClosureMacros.h - rts/rts.cabal Changes: ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -60,10 +60,6 @@ module GHC.Driver.DynFlags ( versionedAppDir, versionedFilePath, extraGccViaCFlags, globalPackageDatabasePath, - -- * Linker/compiler information - LinkerInfo(..), - CompilerInfo(..), - -- * Include specifications IncludeSpecs(..), addGlobalInclude, addQuoteInclude, flattenIncludes, addImplicitQuoteInclude, @@ -758,31 +754,6 @@ data ParMakeCount -- | Use the specific semaphore @@ to control parallelism (@-jsem @ flag). | ParMakeSemaphore FilePath --- ----------------------------------------------------------------------------- --- Linker/compiler information - --- LinkerInfo contains any extra options needed by the system linker. -data LinkerInfo - = GnuLD [Option] - | Mold [Option] - | GnuGold [Option] - | LlvmLLD [Option] - | DarwinLD [Option] - | SolarisLD [Option] - | AixLD [Option] - | UnknownLD - deriving Eq - --- CompilerInfo tells us which C compiler we're using -data CompilerInfo - = GCC - | Clang - | AppleClang - | AppleClang51 - | Emscripten - | UnknownCC - deriving Eq - -- | The 'GhcMode' tells us whether we're doing multi-module -- compilation (controlled via the "GHC" API) or one-shot -- (single-module) compilation. This makes a difference primarily to ===================================== compiler/GHC/Driver/Session.hs ===================================== @@ -215,8 +215,6 @@ module GHC.Driver.Session ( isFmaEnabled, -- * Linker/compiler information - LinkerInfo(..), - CompilerInfo(..), useXLinkerRPath, -- * Include specifications ===================================== libraries/base/src/Data/Array/Byte.hs ===================================== @@ -201,10 +201,11 @@ instance Show ByteArray where | otherwise = showString ", " instance Lift ByteArray where - liftTyped x = unsafeCodeCoerce (lift x) - lift (ByteArray b) = return - (AppE (AppE (VarE addrToByteArrayName) (LitE (IntegerL (fromIntegral len)))) - (LitE (BytesPrimL (Bytes ptr 0 (fromIntegral len))))) + liftTyped = unsafeCodeCoerce . lift + lift (ByteArray b) = + [| addrToByteArray $(lift len) + $(pure . LitE . BytesPrimL $ Bytes ptr 0 (fromIntegral len)) + |] where len# = sizeofByteArray# b len = I# len# @@ -219,9 +220,7 @@ instance Lift ByteArray where ptr :: ForeignPtr Word8 ptr = ForeignPtr (byteArrayContents# pb) (PlainPtr (unsafeCoerce# pb)) -addrToByteArrayName :: Name -addrToByteArrayName = 'addrToByteArray - +{-# NOINLINE addrToByteArray #-} addrToByteArray :: Int -> Addr# -> ByteArray addrToByteArray (I# len) addr = runST $ ST $ \s -> case newByteArray# len s of ===================================== rts/AdjustorAsm.S deleted ===================================== @@ -1,125 +0,0 @@ -#include "include/ghcconfig.h" - -/* ******************************** PowerPC ******************************** */ - -#if defined(powerpc_HOST_ARCH) && defined(aix_HOST_OS) || defined(powerpc64_HOST_ARCH) && defined(__ELF__) && (!defined(_CALL_ELF) || _CALL_ELF == 1) - /* The following code applies, with some differences, - to all powerpc platforms except for powerpc32-linux, - whose calling convention is annoyingly complex. - */ - - - /* The code is "almost" the same for - 32-bit and for 64-bit - */ -#if defined(powerpc64_HOST_ARCH) -#define WS 8 -#define LOAD ld -#define STORE std -#else -#define WS 4 -#define LOAD lwz -#define STORE stw -#endif /* defined(powerpc64_HOST_ARCH) */ - - /* Some info about stack frame layout */ -#define LINK_SLOT (2*WS) -#define LINKAGE_AREA_SIZE (6*WS) - - /* The following defines mirror struct AdjustorStub - from Adjustor.c. Make sure to keep these in sync. - */ -#define HEADER_WORDS 3 - -#define HPTR_OFF ((HEADER_WORDS )*WS) -#define WPTR_OFF ((HEADER_WORDS + 1)*WS) -#define FRAMESIZE_OFF ((HEADER_WORDS + 2)*WS) -#define EXTRA_WORDS_OFF ((HEADER_WORDS + 3)*WS) - -#if defined(aix_HOST_OS) -/* IBM's assembler needs a different pseudo-op to declare a .text section */ -.csect .text[PR] -#else -.text -#endif /* defined(aix_HOST_OS) */ - -#if LEADING_UNDERSCORE - .globl _adjustorCode -_adjustorCode: -#else - .globl adjustorCode - /* Note that we don't build a function descriptor - for AIX-derived ABIs here. This will happen at runtime - in createAdjustor(). - */ -adjustorCode: -#endif /* LEADING_UNDERSCORE */ - /* On entry, r2 will point to the AdjustorStub data structure. */ - - /* save the link */ - mflr 0 - STORE 0, LINK_SLOT(1) - - /* set up stack frame */ - LOAD 12, FRAMESIZE_OFF(2) -#if defined(powerpc64_HOST_ARCH) - stdux 1, 1, 12 -#else - stwux 1, 1, 12 -#endif /* defined(powerpc64_HOST_ARCH) */ - - /* Save some regs so that we can use them. - Note that we use the "Red Zone" below the stack pointer. - */ - STORE 31, -WS(1) - STORE 30, -2*WS(1) - - mr 31, 1 - subf 30, 12, 31 - - LOAD 12, EXTRA_WORDS_OFF(2) - mtctr 12 - b L2 -L1: - LOAD 0, LINKAGE_AREA_SIZE + 8*WS(30) - STORE 0, LINKAGE_AREA_SIZE + 10*WS(31) - addi 30, 30, WS - addi 31, 31, WS -L2: - bdnz L1 - - /* Restore r30 and r31 now. - */ - LOAD 31, -WS(1) - LOAD 30, -2*WS(1) - - STORE 10, LINKAGE_AREA_SIZE + 9*WS(1) - STORE 9, LINKAGE_AREA_SIZE + 8*WS(1) - mr 10, 8 - mr 9, 7 - mr 8, 6 - mr 7, 5 - mr 6, 4 - mr 5, 3 - - LOAD 3, HPTR_OFF(2) - - LOAD 12, WPTR_OFF(2) - LOAD 0, 0(12) - /* The function we're calling will never be a nested function, - so we don't load r11. - */ - mtctr 0 - LOAD 2, WS(12) - bctrl - - LOAD 1, 0(1) - LOAD 0, LINK_SLOT(1) - mtlr 0 - blr -#endif - -/* mark stack as nonexecutable */ -#if defined(__linux__) && defined(__ELF__) -.section .note.GNU-stack,"", at progbits -#endif ===================================== rts/RtsFlags.h ===================================== @@ -23,7 +23,12 @@ char** getUTF8Args(int* argc); void initRtsFlagsDefaults (void); void setupRtsFlags (int *argc, char *argv[], RtsConfig rtsConfig); void freeRtsArgs (void); -#if defined(PROFILING) + +/* These prototypes may also be defined by ClosureMacros.h. We don't want to + * define them twice (#24918). + */ +#if defined(PROFILING) && !defined(RTS_FLAGS_DOING_PROFILING) +#define RTS_FLAGS_DOING_PROFILING 1 bool doingLDVProfiling (void); bool doingRetainerProfiling(void); bool doingErasProfiling(void); ===================================== rts/adjustor/NativeIA64.c deleted ===================================== @@ -1,154 +0,0 @@ -/* ----------------------------------------------------------------------------- - * IA64 architecture adjustor thunk logic. - * ---------------------------------------------------------------------------*/ - -#include "rts/PosixSource.h" -#include "Rts.h" - -#include "RtsUtils.h" -#include "StablePtr.h" - -/* Layout of a function descriptor */ -typedef struct _IA64FunDesc { - StgWord64 ip; - StgWord64 gp; -} IA64FunDesc; - -static void * -stgAllocStable(size_t size_in_bytes, StgStablePtr *stable) -{ - StgArrBytes* arr; - uint32_t data_size_in_words, total_size_in_words; - - /* round up to a whole number of words */ - data_size_in_words = ROUNDUP_BYTES_TO_WDS(size_in_bytes); - total_size_in_words = sizeofW(StgArrBytes) + data_size_in_words; - - /* allocate and fill it in */ - arr = (StgArrBytes *)allocate(total_size_in_words); - SET_ARR_HDR(arr, &stg_ARR_WORDS_info, CCCS, size_in_bytes); - - /* obtain a stable ptr */ - *stable = getStablePtr((StgPtr)arr); - - /* and return a ptr to the goods inside the array */ - return(&(arr->payload)); -} - -void initAdjustors(void) { } - -void* -createAdjustor(StgStablePtr hptr, - StgFunPtr wptr, - char *typeString -#if !defined(powerpc_HOST_ARCH) && !defined(powerpc64_HOST_ARCH) && !defined(x86_64_HOST_ARCH) - STG_UNUSED -#endif - ) -{ - void *adjustor = NULL; - void *code = NULL; - -/* - Up to 8 inputs are passed in registers. We flush the last two inputs to - the stack, initially into the 16-byte scratch region left by the caller. - We then shuffle the others along by 4 (taking 2 registers for ourselves - to save return address and previous function state - we need to come back - here on the way out to restore the stack, so this is a real function - rather than just a trampoline). - - The function descriptor we create contains the gp of the target function - so gp is already loaded correctly. - - [MLX] alloc r16=ar.pfs,10,2,0 - movl r17=wptr - [MII] st8.spill [r12]=r38,8 // spill in6 (out4) - mov r41=r37 // out7 = in5 (out3) - mov r40=r36;; // out6 = in4 (out2) - [MII] st8.spill [r12]=r39 // spill in7 (out5) - mov.sptk b6=r17,50 - mov r38=r34;; // out4 = in2 (out0) - [MII] mov r39=r35 // out5 = in3 (out1) - mov r37=r33 // out3 = in1 (loc1) - mov r36=r32 // out2 = in0 (loc0) - [MLX] adds r12=-24,r12 // update sp - movl r34=hptr;; // out0 = hptr - [MIB] mov r33=r16 // loc1 = ar.pfs - mov r32=b0 // loc0 = retaddr - br.call.sptk.many b0=b6;; - - [MII] adds r12=-16,r12 - mov b0=r32 - mov.i ar.pfs=r33 - [MFB] nop.m 0x0 - nop.f 0x0 - br.ret.sptk.many b0;; -*/ - -/* These macros distribute a long constant into the two words of an MLX bundle */ -#define BITS(val,start,count) (((val) >> (start)) & ((1 << (count))-1)) -#define MOVL_LOWORD(val) (BITS(val,22,18) << 46) -#define MOVL_HIWORD(val) ( (BITS(val,0,7) << 36) \ - | (BITS(val,7,9) << 50) \ - | (BITS(val,16,5) << 45) \ - | (BITS(val,21,1) << 44) \ - | (BITS(val,40,23)) \ - | (BITS(val,63,1) << 59)) - - StgStablePtr stable; - IA64FunDesc *wdesc = (IA64FunDesc *)wptr; - StgWord64 wcode = wdesc->ip; - IA64FunDesc *fdesc; - StgWord64 *code; - - /* we allocate on the Haskell heap since malloc'd memory isn't - * executable - argh */ - /* Allocated memory is word-aligned (8 bytes) but functions on ia64 - * must be aligned to 16 bytes. We allocate an extra 8 bytes of - * wiggle room so that we can put the code on a 16 byte boundary. */ - adjustor = stgAllocStable(sizeof(IA64FunDesc)+18*8+8, &stable); - - fdesc = (IA64FunDesc *)adjustor; - code = (StgWord64 *)(fdesc + 1); - /* add 8 bytes to code if needed to align to a 16-byte boundary */ - if ((StgWord64)code & 15) code++; - fdesc->ip = (StgWord64)code; - fdesc->gp = wdesc->gp; - - code[0] = 0x0000058004288004 | MOVL_LOWORD(wcode); - code[1] = 0x6000000220000000 | MOVL_HIWORD(wcode); - code[2] = 0x029015d818984001; - code[3] = 0x8401200500420094; - code[4] = 0x886011d8189c0001; - code[5] = 0x84011004c00380c0; - code[6] = 0x0250210046013800; - code[7] = 0x8401000480420084; - code[8] = 0x0000233f19a06005 | MOVL_LOWORD((StgWord64)hptr); - code[9] = 0x6000000440000000 | MOVL_HIWORD((StgWord64)hptr); - code[10] = 0x0200210020010811; - code[11] = 0x1080006800006200; - code[12] = 0x0000210018406000; - code[13] = 0x00aa021000038005; - code[14] = 0x000000010000001d; - code[15] = 0x0084000880000200; - - /* save stable pointers in convenient form */ - code[16] = (StgWord64)hptr; - code[17] = (StgWord64)stable; - - return code; -} - -void -freeHaskellFunctionPtr(void* ptr) -{ - IA64FunDesc *fdesc = (IA64FunDesc *)ptr; - StgWord64 *code = (StgWord64 *)(fdesc+1); - - if (fdesc->ip != (StgWord64)code) { - errorBelch("freeHaskellFunctionPtr: not for me, guv! %p\n", ptr); - return; - } - freeStablePtr((StgStablePtr)code[16]); - freeStablePtr((StgStablePtr)code[17]); -} ===================================== rts/adjustor/NativePowerPC.c deleted ===================================== @@ -1,401 +0,0 @@ -/* ----------------------------------------------------------------------------- - * PowerPC architecture adjustor thunk logic. - * ---------------------------------------------------------------------------*/ - -#include "rts/PosixSource.h" -#include "Rts.h" - -#include "RtsUtils.h" -#include "StablePtr.h" -#include "Adjustor.h" - -/* Adjustor logic for PowerPC and PowerPC64 */ - -#if defined(linux_HOST_OS) -#include -#endif - -// from AdjustorAsm.s -// not declared as a function so that AIX-style -// fundescs can never get in the way. -extern void *adjustorCode; - -#if defined(linux_HOST_OS) -__asm__("obscure_ccall_ret_code:\n\t" - "lwz 1,0(1)\n\t" - "lwz 0,4(1)\n\t" - "mtlr 0\n\t" - "blr"); -extern void obscure_ccall_ret_code(void); -#endif /* defined(linux_HOST_OS) */ - -#if defined(powerpc_HOST_ARCH) && defined(aix_HOST_OS) || defined(powerpc64_HOST_ARCH) && defined(__ELF__) && (!defined(_CALL_ELF) || _CALL_ELF == 1) - -/* !!! !!! WARNING: !!! !!! - * This structure is accessed from AdjustorAsm.s - * Any changes here have to be mirrored in the offsets there. - */ - -typedef struct AdjustorStub { - /* fundesc-based ABIs */ -#define FUNDESCS - StgFunPtr code; - struct AdjustorStub - *toc; - void *env; - StgStablePtr hptr; - StgFunPtr wptr; - StgInt negative_framesize; - StgInt extrawords_plus_one; -} AdjustorStub; - -#endif - -void initAdjustors(void) { } - -void* -createAdjustor(StgStablePtr hptr, - StgFunPtr wptr, - char *typeString - ) -{ -#if defined(linux_HOST_OS) - -#define OP_LO(op,lo) ((((unsigned)(op)) << 16) | (((unsigned)(lo)) & 0xFFFF)) -#define OP_HI(op,hi) ((((unsigned)(op)) << 16) | (((unsigned)(hi)) >> 16)) - /* The PowerPC Linux (32-bit) calling convention is annoyingly complex. - We need to calculate all the details of the stack frame layout, - taking into account the types of all the arguments, and then - generate code on the fly. */ - - int src_gpr = 3, dst_gpr = 5; - int fpr = 3; - int src_offset = 0, dst_offset = 0; - int n = strlen(typeString),i; - int src_locs[n], dst_locs[n]; - int frameSize; - - /* Step 1: - Calculate where the arguments should go. - src_locs[] will contain the locations of the arguments in the - original stack frame passed to the adjustor. - dst_locs[] will contain the locations of the arguments after the - adjustor runs, on entry to the wrapper proc pointed to by wptr. - - This algorithm is based on the one described on page 3-19 of the - System V ABI PowerPC Processor Supplement. - */ - for(i=0;typeString[i];i++) - { - char t = typeString[i]; - if((t == 'f' || t == 'd') && fpr <= 8) - src_locs[i] = dst_locs[i] = -32-(fpr++); - else - { - if((t == 'l' || t == 'L') && src_gpr <= 9) - { - if((src_gpr & 1) == 0) - src_gpr++; - src_locs[i] = -src_gpr; - src_gpr += 2; - } - else if((t == 'w' || t == 'W') && src_gpr <= 10) - { - src_locs[i] = -(src_gpr++); - } - else - { - if(t == 'l' || t == 'L' || t == 'd') - { - if(src_offset % 8) - src_offset += 4; - } - src_locs[i] = src_offset; - src_offset += (t == 'l' || t == 'L' || t == 'd') ? 8 : 4; - } - - if((t == 'l' || t == 'L') && dst_gpr <= 9) - { - if((dst_gpr & 1) == 0) - dst_gpr++; - dst_locs[i] = -dst_gpr; - dst_gpr += 2; - } - else if((t == 'w' || t == 'W') && dst_gpr <= 10) - { - dst_locs[i] = -(dst_gpr++); - } - else - { - if(t == 'l' || t == 'L' || t == 'd') - { - if(dst_offset % 8) - dst_offset += 4; - } - dst_locs[i] = dst_offset; - dst_offset += (t == 'l' || t == 'L' || t == 'd') ? 8 : 4; - } - } - } - - frameSize = dst_offset + 8; - frameSize = (frameSize+15) & ~0xF; - - /* Step 2: - Build the adjustor. - */ - // allocate space for at most 4 insns per parameter - // plus 14 more instructions. - ExecPage *page = allocateExecPage(); - if (page == NULL) { - barf("createAdjustor: failed to allocate executable page\n"); - } - unsigned *code = adjustor; - - *code++ = 0x48000008; // b *+8 - // * Put the hptr in a place where freeHaskellFunctionPtr - // can get at it. - *code++ = (unsigned) hptr; - - // * save the link register - *code++ = 0x7c0802a6; // mflr r0; - *code++ = 0x90010004; // stw r0, 4(r1); - // * and build a new stack frame - *code++ = OP_LO(0x9421, -frameSize); // stwu r1, -frameSize(r1) - - // * now generate instructions to copy arguments - // from the old stack frame into the new stack frame. - for(i=n-1;i>=0;i--) - { - if(src_locs[i] < -32) - ASSERT(dst_locs[i] == src_locs[i]); - else if(src_locs[i] < 0) - { - // source in GPR. - ASSERT(typeString[i] != 'f' && typeString[i] != 'd'); - if(dst_locs[i] < 0) - { - ASSERT(dst_locs[i] > -32); - // dst is in GPR, too. - - if(typeString[i] == 'l' || typeString[i] == 'L') - { - // mr dst+1, src+1 - *code++ = 0x7c000378 - | ((-dst_locs[i]+1) << 16) - | ((-src_locs[i]+1) << 11) - | ((-src_locs[i]+1) << 21); - } - // mr dst, src - *code++ = 0x7c000378 - | ((-dst_locs[i]) << 16) - | ((-src_locs[i]) << 11) - | ((-src_locs[i]) << 21); - } - else - { - if(typeString[i] == 'l' || typeString[i] == 'L') - { - // stw src+1, dst_offset+4(r1) - *code++ = 0x90010000 - | ((-src_locs[i]+1) << 21) - | (dst_locs[i] + 4); - } - - // stw src, dst_offset(r1) - *code++ = 0x90010000 - | ((-src_locs[i]) << 21) - | (dst_locs[i] + 8); - } - } - else - { - ASSERT(dst_locs[i] >= 0); - ASSERT(typeString[i] != 'f' && typeString[i] != 'd'); - - if(typeString[i] == 'l' || typeString[i] == 'L') - { - // lwz r0, src_offset(r1) - *code++ = 0x80010000 - | (src_locs[i] + frameSize + 8 + 4); - // stw r0, dst_offset(r1) - *code++ = 0x90010000 - | (dst_locs[i] + 8 + 4); - } - // lwz r0, src_offset(r1) - *code++ = 0x80010000 - | (src_locs[i] + frameSize + 8); - // stw r0, dst_offset(r1) - *code++ = 0x90010000 - | (dst_locs[i] + 8); - } - } - - // * hptr will be the new first argument. - // lis r3, hi(hptr) - *code++ = OP_HI(0x3c60, hptr); - // ori r3,r3,lo(hptr) - *code++ = OP_LO(0x6063, hptr); - - // * we need to return to a piece of code - // which will tear down the stack frame. - // lis r11,hi(obscure_ccall_ret_code) - *code++ = OP_HI(0x3d60, obscure_ccall_ret_code); - // ori r11,r11,lo(obscure_ccall_ret_code) - *code++ = OP_LO(0x616b, obscure_ccall_ret_code); - // mtlr r11 - *code++ = 0x7d6803a6; - - // * jump to wptr - // lis r11,hi(wptr) - *code++ = OP_HI(0x3d60, wptr); - // ori r11,r11,lo(wptr) - *code++ = OP_LO(0x616b, wptr); - // mtctr r11 - *code++ = 0x7d6903a6; - // bctr - *code++ = 0x4e800420; - - freezeExecPage(page); - - // Flush the Instruction cache: - { - unsigned *p = adjustor; - while(p < code) - { - __asm__ volatile ("dcbf 0,%0\n\tsync\n\ticbi 0,%0" - : : "r" (p)); - p++; - } - __asm__ volatile ("sync\n\tisync"); - } - -#else - -#define OP_LO(op,lo) ((((unsigned)(op)) << 16) | (((unsigned)(lo)) & 0xFFFF)) -#define OP_HI(op,hi) ((((unsigned)(op)) << 16) | (((unsigned)(hi)) >> 16)) - /* The following code applies to all PowerPC and PowerPC64 platforms - whose stack layout is based on the AIX ABI. - - Besides (obviously) AIX, this includes - Mac OS 9 and BeOS/PPC and Mac OS X PPC (may they rest in peace), - which use the 32-bit AIX ABI - powerpc64-linux, - which uses the 64-bit AIX ABI. - - The actual stack-frame shuffling is implemented out-of-line - in the function adjustorCode, in AdjustorAsm.S. - Here, we set up an AdjustorStub structure, which - is a function descriptor with a pointer to the AdjustorStub - struct in the position of the TOC that is loaded - into register r2. - - One nice thing about this is that there is _no_ code generated at - runtime on the platforms that have function descriptors. - */ - AdjustorStub *adjustorStub; - int sz = 0, extra_sz, total_sz; - -#if defined(FUNDESCS) - adjustorStub = stgMallocBytes(sizeof(AdjustorStub), "createAdjustor"); -#else - ExecPage *page = allocateExecPage(); - if (page == NULL) { - barf("createAdjustor: failed to allocate executable page\n"); - } - adjustorStub = (AdjustorStub *) page; -#endif /* defined(FUNDESCS) */ - adjustor = adjustorStub; - - adjustorStub->code = (void*) &adjustorCode; - -#if defined(FUNDESCS) - // function descriptors are a cool idea. - // We don't need to generate any code at runtime. - adjustorStub->toc = adjustorStub; -#else - - // no function descriptors :-( - // We need to do things "by hand". -#if defined(powerpc_HOST_ARCH) - // lis r2, hi(adjustorStub) - adjustorStub->lis = OP_HI(0x3c40, adjustorStub); - // ori r2, r2, lo(adjustorStub) - adjustorStub->ori = OP_LO(0x6042, adjustorStub); - // lwz r0, code(r2) - adjustorStub->lwz = OP_LO(0x8002, (char*)(&adjustorStub->code) - - (char*)adjustorStub); - // mtctr r0 - adjustorStub->mtctr = 0x7c0903a6; - // bctr - adjustorStub->bctr = 0x4e800420; - - freezeExecPage(page); -#else - barf("adjustor creation not supported on this platform"); -#endif /* defined(powerpc_HOST_ARCH) */ - - // Flush the Instruction cache: - { - int n = sizeof(AdjustorStub)/sizeof(unsigned); - unsigned *p = (unsigned*)adjustor; - while(n--) - { - __asm__ volatile ("dcbf 0,%0\n\tsync\n\ticbi 0,%0" - : : "r" (p)); - p++; - } - __asm__ volatile ("sync\n\tisync"); - } -#endif /* defined(FUNDESCS) */ - - // Calculate the size of the stack frame, in words. - sz = totalArgumentSize(typeString); - - // The first eight words of the parameter area - // are just "backing store" for the parameters passed in - // the GPRs. extra_sz is the number of words beyond those first - // 8 words. - extra_sz = sz - 8; - if(extra_sz < 0) - extra_sz = 0; - - // Calculate the total size of the stack frame. - total_sz = (6 /* linkage area */ - + 8 /* minimum parameter area */ - + 2 /* two extra arguments */ - + extra_sz)*sizeof(StgWord); - - // align to 16 bytes. - // AIX only requires 8 bytes, but who cares? - total_sz = (total_sz+15) & ~0xF; - - // Fill in the information that adjustorCode in AdjustorAsm.S - // will use to create a new stack frame with the additional args. - adjustorStub->hptr = hptr; - adjustorStub->wptr = wptr; - adjustorStub->negative_framesize = -total_sz; - adjustorStub->extrawords_plus_one = extra_sz + 1; - - return code; -} - -void -freeHaskellFunctionPtr(void* ptr) -{ -#if defined(linux_HOST_OS) - if ( *(StgWord*)ptr != 0x48000008 ) { - errorBelch("freeHaskellFunctionPtr: not for me, guv! %p\n", ptr); - return; - } - freeStablePtr(((StgStablePtr*)ptr)[1]); -#else - if ( ((AdjustorStub*)ptr)->code != (StgFunPtr) &adjustorCode ) { - errorBelch("freeHaskellFunctionPtr: not for me, guv! %p\n", ptr); - return; - } - freeStablePtr(((AdjustorStub*)ptr)->hptr); -#endif - - freeExecPage(ptr); -} ===================================== rts/include/rts/storage/ClosureMacros.h ===================================== @@ -152,10 +152,16 @@ EXTERN_INLINE StgHalfWord GET_TAG(const StgClosure *con) be duplicated here, otherwise there will be some -Wimplicit-function-declaration compilation errors. Especially when GHC compiles out-of-tree cbits that rely on SET_HDR in RTS API. + + However when RtsFlags.h is imported, we don't want to redefine them to avoid + spurious warnings (#24918). */ +#if !defined(RTS_FLAGS_DOING_PROFILING) +#define RTS_FLAGS_DOING_PROFILING 1 bool doingLDVProfiling(void); bool doingRetainerProfiling(void); bool doingErasProfiling(void); +#endif /* The following macro works for both retainer profiling and LDV profiling. For ===================================== rts/rts.cabal ===================================== @@ -362,11 +362,6 @@ library else asm-sources: adjustor/NativeAmd64Asm.S c-sources: adjustor/NativeAmd64.c - if arch(ppc) || arch(ppc64) - asm-sources: AdjustorAsm.S - c-sources: adjustor/NativePowerPC.c - if arch(ia64) - c-sources: adjustor/NativeIA64.c -- Use assembler STG entrypoint on architectures where it is used if arch(ppc) || arch(ppc64) || arch(s390x) || arch(riscv64) || arch(loongarch64) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7541e2046e24ed1abf1066689ec2a0f4ea3ec9b2...848d5160f6b84d36ba15cea83bad82641138bbb2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7541e2046e24ed1abf1066689ec2a0f4ea3ec9b2...848d5160f6b84d36ba15cea83bad82641138bbb2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 07:24:20 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Wed, 05 Jun 2024 03:24:20 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/or-pats-release-notes Message-ID: <666012a42768a_282c23bbe38556d8@gitlab.mail> Sebastian Graf pushed new branch wip/or-pats-release-notes at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/or-pats-release-notes You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 10:33:49 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 05 Jun 2024 06:33:49 -0400 Subject: [Git][ghc/ghc][master] rts: remove unused PowerPC/IA64 native adjustor code Message-ID: <66603f0d15820_146dbfef5884145d@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 4 changed files: - − rts/AdjustorAsm.S - − rts/adjustor/NativeIA64.c - − rts/adjustor/NativePowerPC.c - rts/rts.cabal Changes: ===================================== rts/AdjustorAsm.S deleted ===================================== @@ -1,125 +0,0 @@ -#include "include/ghcconfig.h" - -/* ******************************** PowerPC ******************************** */ - -#if defined(powerpc_HOST_ARCH) && defined(aix_HOST_OS) || defined(powerpc64_HOST_ARCH) && defined(__ELF__) && (!defined(_CALL_ELF) || _CALL_ELF == 1) - /* The following code applies, with some differences, - to all powerpc platforms except for powerpc32-linux, - whose calling convention is annoyingly complex. - */ - - - /* The code is "almost" the same for - 32-bit and for 64-bit - */ -#if defined(powerpc64_HOST_ARCH) -#define WS 8 -#define LOAD ld -#define STORE std -#else -#define WS 4 -#define LOAD lwz -#define STORE stw -#endif /* defined(powerpc64_HOST_ARCH) */ - - /* Some info about stack frame layout */ -#define LINK_SLOT (2*WS) -#define LINKAGE_AREA_SIZE (6*WS) - - /* The following defines mirror struct AdjustorStub - from Adjustor.c. Make sure to keep these in sync. - */ -#define HEADER_WORDS 3 - -#define HPTR_OFF ((HEADER_WORDS )*WS) -#define WPTR_OFF ((HEADER_WORDS + 1)*WS) -#define FRAMESIZE_OFF ((HEADER_WORDS + 2)*WS) -#define EXTRA_WORDS_OFF ((HEADER_WORDS + 3)*WS) - -#if defined(aix_HOST_OS) -/* IBM's assembler needs a different pseudo-op to declare a .text section */ -.csect .text[PR] -#else -.text -#endif /* defined(aix_HOST_OS) */ - -#if LEADING_UNDERSCORE - .globl _adjustorCode -_adjustorCode: -#else - .globl adjustorCode - /* Note that we don't build a function descriptor - for AIX-derived ABIs here. This will happen at runtime - in createAdjustor(). - */ -adjustorCode: -#endif /* LEADING_UNDERSCORE */ - /* On entry, r2 will point to the AdjustorStub data structure. */ - - /* save the link */ - mflr 0 - STORE 0, LINK_SLOT(1) - - /* set up stack frame */ - LOAD 12, FRAMESIZE_OFF(2) -#if defined(powerpc64_HOST_ARCH) - stdux 1, 1, 12 -#else - stwux 1, 1, 12 -#endif /* defined(powerpc64_HOST_ARCH) */ - - /* Save some regs so that we can use them. - Note that we use the "Red Zone" below the stack pointer. - */ - STORE 31, -WS(1) - STORE 30, -2*WS(1) - - mr 31, 1 - subf 30, 12, 31 - - LOAD 12, EXTRA_WORDS_OFF(2) - mtctr 12 - b L2 -L1: - LOAD 0, LINKAGE_AREA_SIZE + 8*WS(30) - STORE 0, LINKAGE_AREA_SIZE + 10*WS(31) - addi 30, 30, WS - addi 31, 31, WS -L2: - bdnz L1 - - /* Restore r30 and r31 now. - */ - LOAD 31, -WS(1) - LOAD 30, -2*WS(1) - - STORE 10, LINKAGE_AREA_SIZE + 9*WS(1) - STORE 9, LINKAGE_AREA_SIZE + 8*WS(1) - mr 10, 8 - mr 9, 7 - mr 8, 6 - mr 7, 5 - mr 6, 4 - mr 5, 3 - - LOAD 3, HPTR_OFF(2) - - LOAD 12, WPTR_OFF(2) - LOAD 0, 0(12) - /* The function we're calling will never be a nested function, - so we don't load r11. - */ - mtctr 0 - LOAD 2, WS(12) - bctrl - - LOAD 1, 0(1) - LOAD 0, LINK_SLOT(1) - mtlr 0 - blr -#endif - -/* mark stack as nonexecutable */ -#if defined(__linux__) && defined(__ELF__) -.section .note.GNU-stack,"", at progbits -#endif ===================================== rts/adjustor/NativeIA64.c deleted ===================================== @@ -1,154 +0,0 @@ -/* ----------------------------------------------------------------------------- - * IA64 architecture adjustor thunk logic. - * ---------------------------------------------------------------------------*/ - -#include "rts/PosixSource.h" -#include "Rts.h" - -#include "RtsUtils.h" -#include "StablePtr.h" - -/* Layout of a function descriptor */ -typedef struct _IA64FunDesc { - StgWord64 ip; - StgWord64 gp; -} IA64FunDesc; - -static void * -stgAllocStable(size_t size_in_bytes, StgStablePtr *stable) -{ - StgArrBytes* arr; - uint32_t data_size_in_words, total_size_in_words; - - /* round up to a whole number of words */ - data_size_in_words = ROUNDUP_BYTES_TO_WDS(size_in_bytes); - total_size_in_words = sizeofW(StgArrBytes) + data_size_in_words; - - /* allocate and fill it in */ - arr = (StgArrBytes *)allocate(total_size_in_words); - SET_ARR_HDR(arr, &stg_ARR_WORDS_info, CCCS, size_in_bytes); - - /* obtain a stable ptr */ - *stable = getStablePtr((StgPtr)arr); - - /* and return a ptr to the goods inside the array */ - return(&(arr->payload)); -} - -void initAdjustors(void) { } - -void* -createAdjustor(StgStablePtr hptr, - StgFunPtr wptr, - char *typeString -#if !defined(powerpc_HOST_ARCH) && !defined(powerpc64_HOST_ARCH) && !defined(x86_64_HOST_ARCH) - STG_UNUSED -#endif - ) -{ - void *adjustor = NULL; - void *code = NULL; - -/* - Up to 8 inputs are passed in registers. We flush the last two inputs to - the stack, initially into the 16-byte scratch region left by the caller. - We then shuffle the others along by 4 (taking 2 registers for ourselves - to save return address and previous function state - we need to come back - here on the way out to restore the stack, so this is a real function - rather than just a trampoline). - - The function descriptor we create contains the gp of the target function - so gp is already loaded correctly. - - [MLX] alloc r16=ar.pfs,10,2,0 - movl r17=wptr - [MII] st8.spill [r12]=r38,8 // spill in6 (out4) - mov r41=r37 // out7 = in5 (out3) - mov r40=r36;; // out6 = in4 (out2) - [MII] st8.spill [r12]=r39 // spill in7 (out5) - mov.sptk b6=r17,50 - mov r38=r34;; // out4 = in2 (out0) - [MII] mov r39=r35 // out5 = in3 (out1) - mov r37=r33 // out3 = in1 (loc1) - mov r36=r32 // out2 = in0 (loc0) - [MLX] adds r12=-24,r12 // update sp - movl r34=hptr;; // out0 = hptr - [MIB] mov r33=r16 // loc1 = ar.pfs - mov r32=b0 // loc0 = retaddr - br.call.sptk.many b0=b6;; - - [MII] adds r12=-16,r12 - mov b0=r32 - mov.i ar.pfs=r33 - [MFB] nop.m 0x0 - nop.f 0x0 - br.ret.sptk.many b0;; -*/ - -/* These macros distribute a long constant into the two words of an MLX bundle */ -#define BITS(val,start,count) (((val) >> (start)) & ((1 << (count))-1)) -#define MOVL_LOWORD(val) (BITS(val,22,18) << 46) -#define MOVL_HIWORD(val) ( (BITS(val,0,7) << 36) \ - | (BITS(val,7,9) << 50) \ - | (BITS(val,16,5) << 45) \ - | (BITS(val,21,1) << 44) \ - | (BITS(val,40,23)) \ - | (BITS(val,63,1) << 59)) - - StgStablePtr stable; - IA64FunDesc *wdesc = (IA64FunDesc *)wptr; - StgWord64 wcode = wdesc->ip; - IA64FunDesc *fdesc; - StgWord64 *code; - - /* we allocate on the Haskell heap since malloc'd memory isn't - * executable - argh */ - /* Allocated memory is word-aligned (8 bytes) but functions on ia64 - * must be aligned to 16 bytes. We allocate an extra 8 bytes of - * wiggle room so that we can put the code on a 16 byte boundary. */ - adjustor = stgAllocStable(sizeof(IA64FunDesc)+18*8+8, &stable); - - fdesc = (IA64FunDesc *)adjustor; - code = (StgWord64 *)(fdesc + 1); - /* add 8 bytes to code if needed to align to a 16-byte boundary */ - if ((StgWord64)code & 15) code++; - fdesc->ip = (StgWord64)code; - fdesc->gp = wdesc->gp; - - code[0] = 0x0000058004288004 | MOVL_LOWORD(wcode); - code[1] = 0x6000000220000000 | MOVL_HIWORD(wcode); - code[2] = 0x029015d818984001; - code[3] = 0x8401200500420094; - code[4] = 0x886011d8189c0001; - code[5] = 0x84011004c00380c0; - code[6] = 0x0250210046013800; - code[7] = 0x8401000480420084; - code[8] = 0x0000233f19a06005 | MOVL_LOWORD((StgWord64)hptr); - code[9] = 0x6000000440000000 | MOVL_HIWORD((StgWord64)hptr); - code[10] = 0x0200210020010811; - code[11] = 0x1080006800006200; - code[12] = 0x0000210018406000; - code[13] = 0x00aa021000038005; - code[14] = 0x000000010000001d; - code[15] = 0x0084000880000200; - - /* save stable pointers in convenient form */ - code[16] = (StgWord64)hptr; - code[17] = (StgWord64)stable; - - return code; -} - -void -freeHaskellFunctionPtr(void* ptr) -{ - IA64FunDesc *fdesc = (IA64FunDesc *)ptr; - StgWord64 *code = (StgWord64 *)(fdesc+1); - - if (fdesc->ip != (StgWord64)code) { - errorBelch("freeHaskellFunctionPtr: not for me, guv! %p\n", ptr); - return; - } - freeStablePtr((StgStablePtr)code[16]); - freeStablePtr((StgStablePtr)code[17]); -} ===================================== rts/adjustor/NativePowerPC.c deleted ===================================== @@ -1,401 +0,0 @@ -/* ----------------------------------------------------------------------------- - * PowerPC architecture adjustor thunk logic. - * ---------------------------------------------------------------------------*/ - -#include "rts/PosixSource.h" -#include "Rts.h" - -#include "RtsUtils.h" -#include "StablePtr.h" -#include "Adjustor.h" - -/* Adjustor logic for PowerPC and PowerPC64 */ - -#if defined(linux_HOST_OS) -#include -#endif - -// from AdjustorAsm.s -// not declared as a function so that AIX-style -// fundescs can never get in the way. -extern void *adjustorCode; - -#if defined(linux_HOST_OS) -__asm__("obscure_ccall_ret_code:\n\t" - "lwz 1,0(1)\n\t" - "lwz 0,4(1)\n\t" - "mtlr 0\n\t" - "blr"); -extern void obscure_ccall_ret_code(void); -#endif /* defined(linux_HOST_OS) */ - -#if defined(powerpc_HOST_ARCH) && defined(aix_HOST_OS) || defined(powerpc64_HOST_ARCH) && defined(__ELF__) && (!defined(_CALL_ELF) || _CALL_ELF == 1) - -/* !!! !!! WARNING: !!! !!! - * This structure is accessed from AdjustorAsm.s - * Any changes here have to be mirrored in the offsets there. - */ - -typedef struct AdjustorStub { - /* fundesc-based ABIs */ -#define FUNDESCS - StgFunPtr code; - struct AdjustorStub - *toc; - void *env; - StgStablePtr hptr; - StgFunPtr wptr; - StgInt negative_framesize; - StgInt extrawords_plus_one; -} AdjustorStub; - -#endif - -void initAdjustors(void) { } - -void* -createAdjustor(StgStablePtr hptr, - StgFunPtr wptr, - char *typeString - ) -{ -#if defined(linux_HOST_OS) - -#define OP_LO(op,lo) ((((unsigned)(op)) << 16) | (((unsigned)(lo)) & 0xFFFF)) -#define OP_HI(op,hi) ((((unsigned)(op)) << 16) | (((unsigned)(hi)) >> 16)) - /* The PowerPC Linux (32-bit) calling convention is annoyingly complex. - We need to calculate all the details of the stack frame layout, - taking into account the types of all the arguments, and then - generate code on the fly. */ - - int src_gpr = 3, dst_gpr = 5; - int fpr = 3; - int src_offset = 0, dst_offset = 0; - int n = strlen(typeString),i; - int src_locs[n], dst_locs[n]; - int frameSize; - - /* Step 1: - Calculate where the arguments should go. - src_locs[] will contain the locations of the arguments in the - original stack frame passed to the adjustor. - dst_locs[] will contain the locations of the arguments after the - adjustor runs, on entry to the wrapper proc pointed to by wptr. - - This algorithm is based on the one described on page 3-19 of the - System V ABI PowerPC Processor Supplement. - */ - for(i=0;typeString[i];i++) - { - char t = typeString[i]; - if((t == 'f' || t == 'd') && fpr <= 8) - src_locs[i] = dst_locs[i] = -32-(fpr++); - else - { - if((t == 'l' || t == 'L') && src_gpr <= 9) - { - if((src_gpr & 1) == 0) - src_gpr++; - src_locs[i] = -src_gpr; - src_gpr += 2; - } - else if((t == 'w' || t == 'W') && src_gpr <= 10) - { - src_locs[i] = -(src_gpr++); - } - else - { - if(t == 'l' || t == 'L' || t == 'd') - { - if(src_offset % 8) - src_offset += 4; - } - src_locs[i] = src_offset; - src_offset += (t == 'l' || t == 'L' || t == 'd') ? 8 : 4; - } - - if((t == 'l' || t == 'L') && dst_gpr <= 9) - { - if((dst_gpr & 1) == 0) - dst_gpr++; - dst_locs[i] = -dst_gpr; - dst_gpr += 2; - } - else if((t == 'w' || t == 'W') && dst_gpr <= 10) - { - dst_locs[i] = -(dst_gpr++); - } - else - { - if(t == 'l' || t == 'L' || t == 'd') - { - if(dst_offset % 8) - dst_offset += 4; - } - dst_locs[i] = dst_offset; - dst_offset += (t == 'l' || t == 'L' || t == 'd') ? 8 : 4; - } - } - } - - frameSize = dst_offset + 8; - frameSize = (frameSize+15) & ~0xF; - - /* Step 2: - Build the adjustor. - */ - // allocate space for at most 4 insns per parameter - // plus 14 more instructions. - ExecPage *page = allocateExecPage(); - if (page == NULL) { - barf("createAdjustor: failed to allocate executable page\n"); - } - unsigned *code = adjustor; - - *code++ = 0x48000008; // b *+8 - // * Put the hptr in a place where freeHaskellFunctionPtr - // can get at it. - *code++ = (unsigned) hptr; - - // * save the link register - *code++ = 0x7c0802a6; // mflr r0; - *code++ = 0x90010004; // stw r0, 4(r1); - // * and build a new stack frame - *code++ = OP_LO(0x9421, -frameSize); // stwu r1, -frameSize(r1) - - // * now generate instructions to copy arguments - // from the old stack frame into the new stack frame. - for(i=n-1;i>=0;i--) - { - if(src_locs[i] < -32) - ASSERT(dst_locs[i] == src_locs[i]); - else if(src_locs[i] < 0) - { - // source in GPR. - ASSERT(typeString[i] != 'f' && typeString[i] != 'd'); - if(dst_locs[i] < 0) - { - ASSERT(dst_locs[i] > -32); - // dst is in GPR, too. - - if(typeString[i] == 'l' || typeString[i] == 'L') - { - // mr dst+1, src+1 - *code++ = 0x7c000378 - | ((-dst_locs[i]+1) << 16) - | ((-src_locs[i]+1) << 11) - | ((-src_locs[i]+1) << 21); - } - // mr dst, src - *code++ = 0x7c000378 - | ((-dst_locs[i]) << 16) - | ((-src_locs[i]) << 11) - | ((-src_locs[i]) << 21); - } - else - { - if(typeString[i] == 'l' || typeString[i] == 'L') - { - // stw src+1, dst_offset+4(r1) - *code++ = 0x90010000 - | ((-src_locs[i]+1) << 21) - | (dst_locs[i] + 4); - } - - // stw src, dst_offset(r1) - *code++ = 0x90010000 - | ((-src_locs[i]) << 21) - | (dst_locs[i] + 8); - } - } - else - { - ASSERT(dst_locs[i] >= 0); - ASSERT(typeString[i] != 'f' && typeString[i] != 'd'); - - if(typeString[i] == 'l' || typeString[i] == 'L') - { - // lwz r0, src_offset(r1) - *code++ = 0x80010000 - | (src_locs[i] + frameSize + 8 + 4); - // stw r0, dst_offset(r1) - *code++ = 0x90010000 - | (dst_locs[i] + 8 + 4); - } - // lwz r0, src_offset(r1) - *code++ = 0x80010000 - | (src_locs[i] + frameSize + 8); - // stw r0, dst_offset(r1) - *code++ = 0x90010000 - | (dst_locs[i] + 8); - } - } - - // * hptr will be the new first argument. - // lis r3, hi(hptr) - *code++ = OP_HI(0x3c60, hptr); - // ori r3,r3,lo(hptr) - *code++ = OP_LO(0x6063, hptr); - - // * we need to return to a piece of code - // which will tear down the stack frame. - // lis r11,hi(obscure_ccall_ret_code) - *code++ = OP_HI(0x3d60, obscure_ccall_ret_code); - // ori r11,r11,lo(obscure_ccall_ret_code) - *code++ = OP_LO(0x616b, obscure_ccall_ret_code); - // mtlr r11 - *code++ = 0x7d6803a6; - - // * jump to wptr - // lis r11,hi(wptr) - *code++ = OP_HI(0x3d60, wptr); - // ori r11,r11,lo(wptr) - *code++ = OP_LO(0x616b, wptr); - // mtctr r11 - *code++ = 0x7d6903a6; - // bctr - *code++ = 0x4e800420; - - freezeExecPage(page); - - // Flush the Instruction cache: - { - unsigned *p = adjustor; - while(p < code) - { - __asm__ volatile ("dcbf 0,%0\n\tsync\n\ticbi 0,%0" - : : "r" (p)); - p++; - } - __asm__ volatile ("sync\n\tisync"); - } - -#else - -#define OP_LO(op,lo) ((((unsigned)(op)) << 16) | (((unsigned)(lo)) & 0xFFFF)) -#define OP_HI(op,hi) ((((unsigned)(op)) << 16) | (((unsigned)(hi)) >> 16)) - /* The following code applies to all PowerPC and PowerPC64 platforms - whose stack layout is based on the AIX ABI. - - Besides (obviously) AIX, this includes - Mac OS 9 and BeOS/PPC and Mac OS X PPC (may they rest in peace), - which use the 32-bit AIX ABI - powerpc64-linux, - which uses the 64-bit AIX ABI. - - The actual stack-frame shuffling is implemented out-of-line - in the function adjustorCode, in AdjustorAsm.S. - Here, we set up an AdjustorStub structure, which - is a function descriptor with a pointer to the AdjustorStub - struct in the position of the TOC that is loaded - into register r2. - - One nice thing about this is that there is _no_ code generated at - runtime on the platforms that have function descriptors. - */ - AdjustorStub *adjustorStub; - int sz = 0, extra_sz, total_sz; - -#if defined(FUNDESCS) - adjustorStub = stgMallocBytes(sizeof(AdjustorStub), "createAdjustor"); -#else - ExecPage *page = allocateExecPage(); - if (page == NULL) { - barf("createAdjustor: failed to allocate executable page\n"); - } - adjustorStub = (AdjustorStub *) page; -#endif /* defined(FUNDESCS) */ - adjustor = adjustorStub; - - adjustorStub->code = (void*) &adjustorCode; - -#if defined(FUNDESCS) - // function descriptors are a cool idea. - // We don't need to generate any code at runtime. - adjustorStub->toc = adjustorStub; -#else - - // no function descriptors :-( - // We need to do things "by hand". -#if defined(powerpc_HOST_ARCH) - // lis r2, hi(adjustorStub) - adjustorStub->lis = OP_HI(0x3c40, adjustorStub); - // ori r2, r2, lo(adjustorStub) - adjustorStub->ori = OP_LO(0x6042, adjustorStub); - // lwz r0, code(r2) - adjustorStub->lwz = OP_LO(0x8002, (char*)(&adjustorStub->code) - - (char*)adjustorStub); - // mtctr r0 - adjustorStub->mtctr = 0x7c0903a6; - // bctr - adjustorStub->bctr = 0x4e800420; - - freezeExecPage(page); -#else - barf("adjustor creation not supported on this platform"); -#endif /* defined(powerpc_HOST_ARCH) */ - - // Flush the Instruction cache: - { - int n = sizeof(AdjustorStub)/sizeof(unsigned); - unsigned *p = (unsigned*)adjustor; - while(n--) - { - __asm__ volatile ("dcbf 0,%0\n\tsync\n\ticbi 0,%0" - : : "r" (p)); - p++; - } - __asm__ volatile ("sync\n\tisync"); - } -#endif /* defined(FUNDESCS) */ - - // Calculate the size of the stack frame, in words. - sz = totalArgumentSize(typeString); - - // The first eight words of the parameter area - // are just "backing store" for the parameters passed in - // the GPRs. extra_sz is the number of words beyond those first - // 8 words. - extra_sz = sz - 8; - if(extra_sz < 0) - extra_sz = 0; - - // Calculate the total size of the stack frame. - total_sz = (6 /* linkage area */ - + 8 /* minimum parameter area */ - + 2 /* two extra arguments */ - + extra_sz)*sizeof(StgWord); - - // align to 16 bytes. - // AIX only requires 8 bytes, but who cares? - total_sz = (total_sz+15) & ~0xF; - - // Fill in the information that adjustorCode in AdjustorAsm.S - // will use to create a new stack frame with the additional args. - adjustorStub->hptr = hptr; - adjustorStub->wptr = wptr; - adjustorStub->negative_framesize = -total_sz; - adjustorStub->extrawords_plus_one = extra_sz + 1; - - return code; -} - -void -freeHaskellFunctionPtr(void* ptr) -{ -#if defined(linux_HOST_OS) - if ( *(StgWord*)ptr != 0x48000008 ) { - errorBelch("freeHaskellFunctionPtr: not for me, guv! %p\n", ptr); - return; - } - freeStablePtr(((StgStablePtr*)ptr)[1]); -#else - if ( ((AdjustorStub*)ptr)->code != (StgFunPtr) &adjustorCode ) { - errorBelch("freeHaskellFunctionPtr: not for me, guv! %p\n", ptr); - return; - } - freeStablePtr(((AdjustorStub*)ptr)->hptr); -#endif - - freeExecPage(ptr); -} ===================================== rts/rts.cabal ===================================== @@ -362,11 +362,6 @@ library else asm-sources: adjustor/NativeAmd64Asm.S c-sources: adjustor/NativeAmd64.c - if arch(ppc) || arch(ppc64) - asm-sources: AdjustorAsm.S - c-sources: adjustor/NativePowerPC.c - if arch(ia64) - c-sources: adjustor/NativeIA64.c -- Use assembler STG entrypoint on architectures where it is used if arch(ppc) || arch(ppc64) || arch(s390x) || arch(riscv64) || arch(loongarch64) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1179524475f697692286b7486339ce72dcc52606 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1179524475f697692286b7486339ce72dcc52606 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 10:34:27 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 05 Jun 2024 06:34:27 -0400 Subject: [Git][ghc/ghc][master] RTS: fix warnings with doing*Profiling (#24918) Message-ID: <66603f336dc7f_146db11bffe8447bd@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - 2 changed files: - rts/RtsFlags.h - rts/include/rts/storage/ClosureMacros.h Changes: ===================================== rts/RtsFlags.h ===================================== @@ -23,7 +23,12 @@ char** getUTF8Args(int* argc); void initRtsFlagsDefaults (void); void setupRtsFlags (int *argc, char *argv[], RtsConfig rtsConfig); void freeRtsArgs (void); -#if defined(PROFILING) + +/* These prototypes may also be defined by ClosureMacros.h. We don't want to + * define them twice (#24918). + */ +#if defined(PROFILING) && !defined(RTS_FLAGS_DOING_PROFILING) +#define RTS_FLAGS_DOING_PROFILING 1 bool doingLDVProfiling (void); bool doingRetainerProfiling(void); bool doingErasProfiling(void); ===================================== rts/include/rts/storage/ClosureMacros.h ===================================== @@ -152,10 +152,16 @@ EXTERN_INLINE StgHalfWord GET_TAG(const StgClosure *con) be duplicated here, otherwise there will be some -Wimplicit-function-declaration compilation errors. Especially when GHC compiles out-of-tree cbits that rely on SET_HDR in RTS API. + + However when RtsFlags.h is imported, we don't want to redefine them to avoid + spurious warnings (#24918). */ +#if !defined(RTS_FLAGS_DOING_PROFILING) +#define RTS_FLAGS_DOING_PROFILING 1 bool doingLDVProfiling(void); bool doingRetainerProfiling(void); bool doingErasProfiling(void); +#endif /* The following macro works for both retainer profiling and LDV profiling. For View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5132754b80d468e0c24e39b63eea525dc1ee3a5b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5132754b80d468e0c24e39b63eea525dc1ee3a5b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 11:21:00 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Wed, 05 Jun 2024 07:21:00 -0400 Subject: [Git][ghc/ghc][wip/T24899] 66 commits: template-haskell: Move wired-ins to ghc-internal Message-ID: <66604a1c72d61_286991042a884661@gitlab.mail> Cheng Shao pushed to branch wip/T24899 at Glasgow Haskell Compiler / GHC Commits: 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - 1d499c18 by Ben Gamari at 2024-06-05T11:19:38+00:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 30 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCon.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fe9890127f957cb3d7f81ad702d5fdf7c6b330a6...1d499c18cc739e2fce5a4a3b679f125411111bb0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fe9890127f957cb3d7f81ad702d5fdf7c6b330a6...1d499c18cc739e2fce5a4a3b679f125411111bb0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 11:35:53 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 05 Jun 2024 07:35:53 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 10 commits: rts: remove unused PowerPC/IA64 native adjustor code Message-ID: <66604d99482d9_286993f8194949cb@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - 333bbab3 by Cheng Shao at 2024-06-05T07:35:30-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 1e34af01 by Cheng Shao at 2024-06-05T07:35:30-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 2ee13ed2 by Cheng Shao at 2024-06-05T07:35:30-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - e83849b0 by Cheng Shao at 2024-06-05T07:35:30-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 3f73769f by Cheng Shao at 2024-06-05T07:35:30-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - a138e1b8 by Cheng Shao at 2024-06-05T07:35:30-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - de075099 by Cheng Shao at 2024-06-05T07:35:30-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - a27ed449 by Cheng Shao at 2024-06-05T07:35:30-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 30 changed files: - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Linker/Static.hs - configure.ac - docs/users_guide/9.12.1-notes.rst - hadrian/src/Builder.hs - hadrian/src/Settings/Packages.hs - llvm-targets - m4/fp_find_nm.m4 - m4/fp_prog_ar_args.m4 - − rts/AdjustorAsm.S - rts/RtsFlags.h - rts/RtsSymbols.c - rts/StgCRun.c - − rts/adjustor/NativeIA64.c - − rts/adjustor/NativePowerPC.c - rts/include/rts/storage/ClosureMacros.h - rts/rts.cabal - testsuite/tests/driver/objc/all.T - testsuite/tests/ffi/should_run/Makefile - testsuite/tests/ffi/should_run/all.T - testsuite/tests/numeric/should_run/all.T - testsuite/tests/rts/T10672/Makefile - testsuite/tests/rts/T10672/all.T - testsuite/tests/rts/all.T - utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs - utils/llvm-targets/gen-data-layout.sh Changes: ===================================== compiler/GHC/Cmm/CLabel.hs ===================================== @@ -1659,11 +1659,7 @@ pprDynamicLinkerAsmLabel !platform dllInfo ppLbl = GotSymbolPtr -> ppLbl <> text "@GOTPCREL" GotSymbolOffset -> ppLbl | platformArch platform == ArchAArch64 -> ppLbl - | otherwise -> - case dllInfo of - CodeStub -> char 'L' <> ppLbl <> text "$stub" - SymbolPtr -> char 'L' <> ppLbl <> text "$non_lazy_ptr" - _ -> panic "pprDynamicLinkerAsmLabel" + | otherwise -> panic "pprDynamicLinkerAsmLabel" OSAIX -> case dllInfo of ===================================== compiler/GHC/CmmToAsm/PIC.hs ===================================== @@ -303,25 +303,15 @@ howToAccessLabel config arch OSDarwin DataReference lbl | otherwise = AccessDirectly -howToAccessLabel config arch OSDarwin JumpReference lbl +howToAccessLabel config _ OSDarwin JumpReference lbl -- dyld code stubs don't work for tailcalls because the -- stack alignment is only right for regular calls. -- Therefore, we have to go via a symbol pointer: - | arch == ArchX86 || arch == ArchX86_64 || arch == ArchAArch64 - , ncgLabelDynamic config lbl + | ncgLabelDynamic config lbl = AccessViaSymbolPtr -howToAccessLabel config arch OSDarwin _kind lbl - -- Code stubs are the usual method of choice for imported code; - -- not needed on x86_64 because Apple's new linker, ld64, generates - -- them automatically, neither on Aarch64 (arm64). - | arch /= ArchX86_64 - , arch /= ArchAArch64 - , ncgLabelDynamic config lbl - = AccessViaStub - - | otherwise +howToAccessLabel _ _ OSDarwin _ _ = AccessDirectly ---------------------------------------------------------------------------- @@ -534,16 +524,6 @@ gotLabel -- However, for PIC on x86, we need a small helper function. pprGotDeclaration :: NCGConfig -> HDoc pprGotDeclaration config = case (arch,os) of - (ArchX86, OSDarwin) - | ncgPIC config - -> lines_ [ - text ".section __TEXT,__textcoal_nt,coalesced,no_toc", - text ".weak_definition ___i686.get_pc_thunk.ax", - text ".private_extern ___i686.get_pc_thunk.ax", - text "___i686.get_pc_thunk.ax:", - text "\tmovl (%esp), %eax", - text "\tret" ] - (_, OSDarwin) -> empty -- Emit XCOFF TOC section @@ -597,59 +577,6 @@ pprGotDeclaration config = case (arch,os) of pprImportedSymbol :: NCGConfig -> CLabel -> HDoc pprImportedSymbol config importedLbl = case (arch,os) of - (ArchX86, OSDarwin) - | Just (CodeStub, lbl) <- dynamicLinkerLabelInfo importedLbl - -> if not pic - then - lines_ [ - text ".symbol_stub", - text "L" <> ppr_lbl lbl <> text "$stub:", - text "\t.indirect_symbol" <+> ppr_lbl lbl, - text "\tjmp *L" <> ppr_lbl lbl - <> text "$lazy_ptr", - text "L" <> ppr_lbl lbl - <> text "$stub_binder:", - text "\tpushl $L" <> ppr_lbl lbl - <> text "$lazy_ptr", - text "\tjmp dyld_stub_binding_helper" - ] - else - lines_ [ - text ".section __TEXT,__picsymbolstub2," - <> text "symbol_stubs,pure_instructions,25", - text "L" <> ppr_lbl lbl <> text "$stub:", - text "\t.indirect_symbol" <+> ppr_lbl lbl, - text "\tcall ___i686.get_pc_thunk.ax", - text "1:", - text "\tmovl L" <> ppr_lbl lbl - <> text "$lazy_ptr-1b(%eax),%edx", - text "\tjmp *%edx", - text "L" <> ppr_lbl lbl - <> text "$stub_binder:", - text "\tlea L" <> ppr_lbl lbl - <> text "$lazy_ptr-1b(%eax),%eax", - text "\tpushl %eax", - text "\tjmp dyld_stub_binding_helper" - ] - $$ lines_ [ - text ".section __DATA, __la_sym_ptr" - <> (if pic then int 2 else int 3) - <> text ",lazy_symbol_pointers", - text "L" <> ppr_lbl lbl <> text "$lazy_ptr:", - text "\t.indirect_symbol" <+> ppr_lbl lbl, - text "\t.long L" <> ppr_lbl lbl - <> text "$stub_binder"] - - | Just (SymbolPtr, lbl) <- dynamicLinkerLabelInfo importedLbl - -> lines_ [ - text ".non_lazy_symbol_pointer", - char 'L' <> ppr_lbl lbl <> text "$non_lazy_ptr:", - text "\t.indirect_symbol" <+> ppr_lbl lbl, - text "\t.long\t0"] - - | otherwise - -> empty - (ArchAArch64, OSDarwin) -> empty @@ -734,7 +661,6 @@ pprImportedSymbol config importedLbl = case (arch,os) of ppr_lbl = pprAsmLabel platform arch = platformArch platform os = platformOS platform - pic = ncgPIC config -------------------------------------------------------------------------------- -- Generate code to calculate the address that should be put in the @@ -840,11 +766,11 @@ initializePicBase_ppc _ _ _ _ -- (See PprMach.hs) initializePicBase_x86 - :: Arch -> OS -> Reg + :: OS -> Reg -> [NatCmmDecl (Alignment, RawCmmStatics) X86.Instr] -> NatM [NatCmmDecl (Alignment, RawCmmStatics) X86.Instr] -initializePicBase_x86 ArchX86 os picReg +initializePicBase_x86 os picReg (CmmProc info lab live (ListGraph blocks) : statics) | osElfTarget os = return (CmmProc info lab live (ListGraph blocks') : statics) @@ -862,12 +788,12 @@ initializePicBase_x86 ArchX86 os picReg fetchGOT (BasicBlock bID insns) = BasicBlock bID (X86.FETCHGOT picReg : insns) -initializePicBase_x86 ArchX86 OSDarwin picReg +initializePicBase_x86 OSDarwin picReg (CmmProc info lab live (ListGraph (entry:blocks)) : statics) = return (CmmProc info lab live (ListGraph (block':blocks)) : statics) where BasicBlock bID insns = entry block' = BasicBlock bID (X86.FETCHPC picReg : insns) -initializePicBase_x86 _ _ _ _ +initializePicBase_x86 _ _ _ = panic "initializePicBase_x86: not needed" ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -124,7 +124,7 @@ cmmTopCodeGen (CmmProc info lab live graph) = do os = platformOS platform case picBaseMb of - Just picBase -> initializePicBase_x86 ArchX86 os picBase tops + Just picBase -> initializePicBase_x86 os picBase tops Nothing -> return tops cmmTopCodeGen (CmmData sec dat) = ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -883,7 +883,6 @@ needs_probe_call :: Platform -> Int -> Bool needs_probe_call platform amount = case platformOS platform of OSMinGW32 -> case platformArch platform of - ArchX86 -> amount > (4 * 1024) ArchX86_64 -> amount > (4 * 1024) _ -> False _ -> False @@ -913,15 +912,6 @@ mkStackAllocInstr platform amount -- function dropping the stack more than a page. -- See Note [Windows stack layout] case platformArch platform of - ArchX86 | needs_probe_call platform amount -> - [ MOV II32 (OpImm (ImmInt amount)) (OpReg eax) - , CALL (Left $ strImmLit (fsLit "___chkstk_ms")) [eax] - , SUB II32 (OpReg eax) (OpReg esp) - ] - | otherwise -> - [ SUB II32 (OpImm (ImmInt amount)) (OpReg esp) - , TEST II32 (OpReg esp) (OpReg esp) - ] ArchX86_64 | needs_probe_call platform amount -> [ MOV II64 (OpImm (ImmInt amount)) (OpReg rax) , CALL (Left $ strImmLit (fsLit "___chkstk_ms")) [rax] ===================================== compiler/GHC/Driver/Config/Cmm.hs ===================================== @@ -24,15 +24,10 @@ initCmmConfig dflags = CmmConfig , cmmDoCmmSwitchPlans = not (backendHasNativeSwitch (backend dflags)) , cmmSplitProcPoints = not (backendSupportsUnsplitProcPoints (backend dflags)) || not (platformTablesNextToCode platform) - || usingInconsistentPicReg , cmmAllowMul2 = (ncg && x86ish) || llvm , cmmOptConstDivision = not llvm } where platform = targetPlatform dflags - usingInconsistentPicReg = - case (platformArch platform, platformOS platform, positionIndependent dflags) - of (ArchX86, OSDarwin, pic) -> pic - _ -> False -- Copied from StgToCmm (ncg, llvm) = case backendPrimitiveImplementation (backend dflags) of GenericPrimitives -> (False, False) ===================================== compiler/GHC/Linker/Static.hs ===================================== @@ -219,25 +219,12 @@ linkBinary' staticLink logger tmpfs dflags unit_env o_files dep_units = do toolSettings_ldSupportsCompactUnwind toolSettings' && (platformOS platform == OSDarwin) && case platformArch platform of - ArchX86 -> True ArchX86_64 -> True - ArchARM {} -> True ArchAArch64 -> True _ -> False then ["-Wl,-no_compact_unwind"] else []) - -- '-Wl,-read_only_relocs,suppress' - -- ld gives loads of warnings like: - -- ld: warning: text reloc in _base_GHCziArr_unsafeArray_info to _base_GHCziArr_unsafeArray_closure - -- when linking any program. We're not sure - -- whether this is something we ought to fix, but - -- for now this flags silences them. - ++ (if platformOS platform == OSDarwin && - platformArch platform == ArchX86 - then ["-Wl,-read_only_relocs,suppress"] - else []) - -- We should rather be asking does it support --gc-sections? ++ (if toolSettings_ldIsGnuLd toolSettings' && not (gopt Opt_WholeArchiveHsLibs dflags) ===================================== configure.ac ===================================== @@ -314,6 +314,8 @@ else AC_CHECK_TARGET_TOOL([WindresCmd],[windres]) AC_CHECK_TARGET_TOOL([OBJDUMP],[objdump]) + WindresCmd="$(cygpath -m $WindresCmd)" + if test "$Genlib" != ""; then GenlibCmd="$(cygpath -m $Genlib)" fi @@ -464,7 +466,12 @@ case $HostOS_CPP in ;; esac -ObjdumpCmd="$OBJDUMP" +if test "$HostOS" = "mingw32" +then + ObjdumpCmd=$(cygpath -m "$OBJDUMP") +else + ObjdumpCmd="$OBJDUMP" +fi AC_SUBST([ObjdumpCmd]) dnl ** Which ranlib to use? @@ -473,7 +480,12 @@ AC_PROG_RANLIB if test "$RANLIB" = ":"; then AC_MSG_ERROR([cannot find ranlib in your PATH]) fi -RanlibCmd="$RANLIB" +if test "$HostOS" = "mingw32" +then + RanlibCmd=$(cygpath -m "$RANLIB") +else + RanlibCmd="$RANLIB" +fi AC_SUBST([RanlibCmd]) dnl ** which strip to use? ===================================== docs/users_guide/9.12.1-notes.rst ===================================== @@ -69,6 +69,10 @@ Compiler and treat it as ``ccall``. All C import/export declarations on Windows should now use ``ccall``. +- 32-bit macOS/iOS support has also been completely removed (`#24921 + `_). This does + not affect existing support of apple systems on x86_64/aarch64. + GHCi ~~~~ ===================================== hadrian/src/Builder.hs ===================================== @@ -34,6 +34,7 @@ import Base import Context import Oracles.Flag import Oracles.Setting (setting, Setting(..)) +import Oracles.Setting (settingsFileSetting, ToolchainSetting(..)) import Packages import GHC.IO.Encoding (getFileSystemEncoding) @@ -239,9 +240,10 @@ instance H.Builder Builder where Ghc {} -> do root <- buildRoot unlitPath <- builderPath Unlit + distro_mingw <- settingsFileSetting ToolchainSetting_DistroMinGW return $ [ unlitPath ] - ++ [ root -/- mingwStamp | windowsHost ] + ++ [ root -/- mingwStamp | windowsHost, distro_mingw == "NO" ] -- proxy for the entire mingw toolchain that -- we have in inplace/mingw initially, and then at -- root -/- mingw. ===================================== hadrian/src/Settings/Packages.hs ===================================== @@ -480,7 +480,7 @@ rtsPackageArgs = package rts ? do speedHack :: Action Bool speedHack = do i386 <- anyTargetArch [ArchX86] - goodOS <- not <$> anyTargetOs [OSDarwin, OSSolaris2] + goodOS <- not <$> anyTargetOs [OSSolaris2] return $ i386 && goodOS -- See @rts/ghc.mk at . ===================================== llvm-targets ===================================== @@ -43,12 +43,9 @@ ,("riscv64-unknown-linux", ("e-m:e-p:64:64-i64:64-i128:128-n64-S128", "", "+m +a +f +d +c +relax")) ,("loongarch64-unknown-linux-gnu", ("e-m:e-p:64:64-i64:64-i128:128-n64-S128", "", "+f +d")) ,("loongarch64-unknown-linux", ("e-m:e-p:64:64-i64:64-i128:128-n64-S128", "", "+f +d")) -,("i386-apple-darwin", ("e-m:o-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:128-n8:16:32-S128", "penryn", "")) ,("x86_64-apple-darwin", ("e-m:o-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "penryn", "")) ,("arm64-apple-darwin", ("e-m:o-i64:64-i128:128-n32:64-S128", "generic", "+v8.3a +fp-armv8 +neon +crc +crypto +fullfp16 +ras +lse +rdm +rcpc +zcm +zcz +sha2 +aes")) -,("armv7-apple-ios", ("e-m:o-p:32:32-Fi8-f64:32:64-v64:32:64-v128:32:128-a:0:32-n32-S32", "generic", "")) ,("aarch64-apple-ios", ("e-m:o-i64:64-i128:128-n32:64-S128", "apple-a7", "+fp-armv8 +neon +crypto +zcm +zcz +sha2 +aes")) -,("i386-apple-ios", ("e-m:o-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:128-n8:16:32-S128", "yonah", "")) ,("x86_64-apple-ios", ("e-m:o-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "core2", "")) ,("amd64-portbld-freebsd", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) ,("x86_64-unknown-freebsd", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) ===================================== m4/fp_find_nm.m4 ===================================== @@ -9,7 +9,12 @@ AC_DEFUN([FP_FIND_NM], AC_MSG_ERROR([cannot find nm in your PATH]) fi fi - NmCmd="$NM" + if test "$HostOS" = "mingw32" + then + NmCmd=$(cygpath -m "$NM") + else + NmCmd="$NM" + fi AC_SUBST([NmCmd]) if test "$TargetOS_CPP" = "darwin" @@ -37,4 +42,3 @@ AC_DEFUN([FP_FIND_NM], esac fi ]) - ===================================== m4/fp_prog_ar_args.m4 ===================================== @@ -30,7 +30,13 @@ else fi fi]) fp_prog_ar_args=$fp_cv_prog_ar_args -AC_SUBST([ArCmd], ["$fp_prog_ar"]) +if test "$HostOS" = "mingw32" +then + ArCmd=$(cygpath -m "$fp_prog_ar") +else + ArCmd="$fp_prog_ar" +fi +AC_SUBST([ArCmd]) AC_SUBST([ArArgs], ["$fp_prog_ar_args"]) ])# FP_PROG_AR_ARGS ===================================== rts/AdjustorAsm.S deleted ===================================== @@ -1,125 +0,0 @@ -#include "include/ghcconfig.h" - -/* ******************************** PowerPC ******************************** */ - -#if defined(powerpc_HOST_ARCH) && defined(aix_HOST_OS) || defined(powerpc64_HOST_ARCH) && defined(__ELF__) && (!defined(_CALL_ELF) || _CALL_ELF == 1) - /* The following code applies, with some differences, - to all powerpc platforms except for powerpc32-linux, - whose calling convention is annoyingly complex. - */ - - - /* The code is "almost" the same for - 32-bit and for 64-bit - */ -#if defined(powerpc64_HOST_ARCH) -#define WS 8 -#define LOAD ld -#define STORE std -#else -#define WS 4 -#define LOAD lwz -#define STORE stw -#endif /* defined(powerpc64_HOST_ARCH) */ - - /* Some info about stack frame layout */ -#define LINK_SLOT (2*WS) -#define LINKAGE_AREA_SIZE (6*WS) - - /* The following defines mirror struct AdjustorStub - from Adjustor.c. Make sure to keep these in sync. - */ -#define HEADER_WORDS 3 - -#define HPTR_OFF ((HEADER_WORDS )*WS) -#define WPTR_OFF ((HEADER_WORDS + 1)*WS) -#define FRAMESIZE_OFF ((HEADER_WORDS + 2)*WS) -#define EXTRA_WORDS_OFF ((HEADER_WORDS + 3)*WS) - -#if defined(aix_HOST_OS) -/* IBM's assembler needs a different pseudo-op to declare a .text section */ -.csect .text[PR] -#else -.text -#endif /* defined(aix_HOST_OS) */ - -#if LEADING_UNDERSCORE - .globl _adjustorCode -_adjustorCode: -#else - .globl adjustorCode - /* Note that we don't build a function descriptor - for AIX-derived ABIs here. This will happen at runtime - in createAdjustor(). - */ -adjustorCode: -#endif /* LEADING_UNDERSCORE */ - /* On entry, r2 will point to the AdjustorStub data structure. */ - - /* save the link */ - mflr 0 - STORE 0, LINK_SLOT(1) - - /* set up stack frame */ - LOAD 12, FRAMESIZE_OFF(2) -#if defined(powerpc64_HOST_ARCH) - stdux 1, 1, 12 -#else - stwux 1, 1, 12 -#endif /* defined(powerpc64_HOST_ARCH) */ - - /* Save some regs so that we can use them. - Note that we use the "Red Zone" below the stack pointer. - */ - STORE 31, -WS(1) - STORE 30, -2*WS(1) - - mr 31, 1 - subf 30, 12, 31 - - LOAD 12, EXTRA_WORDS_OFF(2) - mtctr 12 - b L2 -L1: - LOAD 0, LINKAGE_AREA_SIZE + 8*WS(30) - STORE 0, LINKAGE_AREA_SIZE + 10*WS(31) - addi 30, 30, WS - addi 31, 31, WS -L2: - bdnz L1 - - /* Restore r30 and r31 now. - */ - LOAD 31, -WS(1) - LOAD 30, -2*WS(1) - - STORE 10, LINKAGE_AREA_SIZE + 9*WS(1) - STORE 9, LINKAGE_AREA_SIZE + 8*WS(1) - mr 10, 8 - mr 9, 7 - mr 8, 6 - mr 7, 5 - mr 6, 4 - mr 5, 3 - - LOAD 3, HPTR_OFF(2) - - LOAD 12, WPTR_OFF(2) - LOAD 0, 0(12) - /* The function we're calling will never be a nested function, - so we don't load r11. - */ - mtctr 0 - LOAD 2, WS(12) - bctrl - - LOAD 1, 0(1) - LOAD 0, LINK_SLOT(1) - mtlr 0 - blr -#endif - -/* mark stack as nonexecutable */ -#if defined(__linux__) && defined(__ELF__) -.section .note.GNU-stack,"", at progbits -#endif ===================================== rts/RtsFlags.h ===================================== @@ -23,7 +23,12 @@ char** getUTF8Args(int* argc); void initRtsFlagsDefaults (void); void setupRtsFlags (int *argc, char *argv[], RtsConfig rtsConfig); void freeRtsArgs (void); -#if defined(PROFILING) + +/* These prototypes may also be defined by ClosureMacros.h. We don't want to + * define them twice (#24918). + */ +#if defined(PROFILING) && !defined(RTS_FLAGS_DOING_PROFILING) +#define RTS_FLAGS_DOING_PROFILING 1 bool doingLDVProfiling (void); bool doingRetainerProfiling(void); bool doingErasProfiling(void); ===================================== rts/RtsSymbols.c ===================================== @@ -1073,11 +1073,5 @@ RtsSymbolVal rtsSyms[] = { RTS_LIBFFI_SYMBOLS RTS_ARM_OUTLINE_ATOMIC_SYMBOLS SymI_HasDataProto(nonmoving_write_barrier_enabled) -#if defined(darwin_HOST_OS) && defined(i386_HOST_ARCH) - // dyld stub code contains references to this, - // but it should never be called because we treat - // lazy pointers as nonlazy. - { "dyld_stub_binding_helper", (void*)0xDEADBEEF, STRENGTH_NORMAL }, -#endif { 0, 0, STRENGTH_NORMAL, SYM_TYPE_CODE } /* sentinel */ }; ===================================== rts/StgCRun.c ===================================== @@ -102,13 +102,8 @@ StgFunPtr StgReturn(void) #if defined(i386_HOST_ARCH) -#if defined(darwin_HOST_OS) || defined(ios_HOST_OS) -#define STG_GLOBAL ".globl " -#define STG_HIDDEN ".private_extern " -#else #define STG_GLOBAL ".global " #define STG_HIDDEN ".hidden " -#endif /* * Note [Stack Alignment on X86] ===================================== rts/adjustor/NativeIA64.c deleted ===================================== @@ -1,154 +0,0 @@ -/* ----------------------------------------------------------------------------- - * IA64 architecture adjustor thunk logic. - * ---------------------------------------------------------------------------*/ - -#include "rts/PosixSource.h" -#include "Rts.h" - -#include "RtsUtils.h" -#include "StablePtr.h" - -/* Layout of a function descriptor */ -typedef struct _IA64FunDesc { - StgWord64 ip; - StgWord64 gp; -} IA64FunDesc; - -static void * -stgAllocStable(size_t size_in_bytes, StgStablePtr *stable) -{ - StgArrBytes* arr; - uint32_t data_size_in_words, total_size_in_words; - - /* round up to a whole number of words */ - data_size_in_words = ROUNDUP_BYTES_TO_WDS(size_in_bytes); - total_size_in_words = sizeofW(StgArrBytes) + data_size_in_words; - - /* allocate and fill it in */ - arr = (StgArrBytes *)allocate(total_size_in_words); - SET_ARR_HDR(arr, &stg_ARR_WORDS_info, CCCS, size_in_bytes); - - /* obtain a stable ptr */ - *stable = getStablePtr((StgPtr)arr); - - /* and return a ptr to the goods inside the array */ - return(&(arr->payload)); -} - -void initAdjustors(void) { } - -void* -createAdjustor(StgStablePtr hptr, - StgFunPtr wptr, - char *typeString -#if !defined(powerpc_HOST_ARCH) && !defined(powerpc64_HOST_ARCH) && !defined(x86_64_HOST_ARCH) - STG_UNUSED -#endif - ) -{ - void *adjustor = NULL; - void *code = NULL; - -/* - Up to 8 inputs are passed in registers. We flush the last two inputs to - the stack, initially into the 16-byte scratch region left by the caller. - We then shuffle the others along by 4 (taking 2 registers for ourselves - to save return address and previous function state - we need to come back - here on the way out to restore the stack, so this is a real function - rather than just a trampoline). - - The function descriptor we create contains the gp of the target function - so gp is already loaded correctly. - - [MLX] alloc r16=ar.pfs,10,2,0 - movl r17=wptr - [MII] st8.spill [r12]=r38,8 // spill in6 (out4) - mov r41=r37 // out7 = in5 (out3) - mov r40=r36;; // out6 = in4 (out2) - [MII] st8.spill [r12]=r39 // spill in7 (out5) - mov.sptk b6=r17,50 - mov r38=r34;; // out4 = in2 (out0) - [MII] mov r39=r35 // out5 = in3 (out1) - mov r37=r33 // out3 = in1 (loc1) - mov r36=r32 // out2 = in0 (loc0) - [MLX] adds r12=-24,r12 // update sp - movl r34=hptr;; // out0 = hptr - [MIB] mov r33=r16 // loc1 = ar.pfs - mov r32=b0 // loc0 = retaddr - br.call.sptk.many b0=b6;; - - [MII] adds r12=-16,r12 - mov b0=r32 - mov.i ar.pfs=r33 - [MFB] nop.m 0x0 - nop.f 0x0 - br.ret.sptk.many b0;; -*/ - -/* These macros distribute a long constant into the two words of an MLX bundle */ -#define BITS(val,start,count) (((val) >> (start)) & ((1 << (count))-1)) -#define MOVL_LOWORD(val) (BITS(val,22,18) << 46) -#define MOVL_HIWORD(val) ( (BITS(val,0,7) << 36) \ - | (BITS(val,7,9) << 50) \ - | (BITS(val,16,5) << 45) \ - | (BITS(val,21,1) << 44) \ - | (BITS(val,40,23)) \ - | (BITS(val,63,1) << 59)) - - StgStablePtr stable; - IA64FunDesc *wdesc = (IA64FunDesc *)wptr; - StgWord64 wcode = wdesc->ip; - IA64FunDesc *fdesc; - StgWord64 *code; - - /* we allocate on the Haskell heap since malloc'd memory isn't - * executable - argh */ - /* Allocated memory is word-aligned (8 bytes) but functions on ia64 - * must be aligned to 16 bytes. We allocate an extra 8 bytes of - * wiggle room so that we can put the code on a 16 byte boundary. */ - adjustor = stgAllocStable(sizeof(IA64FunDesc)+18*8+8, &stable); - - fdesc = (IA64FunDesc *)adjustor; - code = (StgWord64 *)(fdesc + 1); - /* add 8 bytes to code if needed to align to a 16-byte boundary */ - if ((StgWord64)code & 15) code++; - fdesc->ip = (StgWord64)code; - fdesc->gp = wdesc->gp; - - code[0] = 0x0000058004288004 | MOVL_LOWORD(wcode); - code[1] = 0x6000000220000000 | MOVL_HIWORD(wcode); - code[2] = 0x029015d818984001; - code[3] = 0x8401200500420094; - code[4] = 0x886011d8189c0001; - code[5] = 0x84011004c00380c0; - code[6] = 0x0250210046013800; - code[7] = 0x8401000480420084; - code[8] = 0x0000233f19a06005 | MOVL_LOWORD((StgWord64)hptr); - code[9] = 0x6000000440000000 | MOVL_HIWORD((StgWord64)hptr); - code[10] = 0x0200210020010811; - code[11] = 0x1080006800006200; - code[12] = 0x0000210018406000; - code[13] = 0x00aa021000038005; - code[14] = 0x000000010000001d; - code[15] = 0x0084000880000200; - - /* save stable pointers in convenient form */ - code[16] = (StgWord64)hptr; - code[17] = (StgWord64)stable; - - return code; -} - -void -freeHaskellFunctionPtr(void* ptr) -{ - IA64FunDesc *fdesc = (IA64FunDesc *)ptr; - StgWord64 *code = (StgWord64 *)(fdesc+1); - - if (fdesc->ip != (StgWord64)code) { - errorBelch("freeHaskellFunctionPtr: not for me, guv! %p\n", ptr); - return; - } - freeStablePtr((StgStablePtr)code[16]); - freeStablePtr((StgStablePtr)code[17]); -} ===================================== rts/adjustor/NativePowerPC.c deleted ===================================== @@ -1,401 +0,0 @@ -/* ----------------------------------------------------------------------------- - * PowerPC architecture adjustor thunk logic. - * ---------------------------------------------------------------------------*/ - -#include "rts/PosixSource.h" -#include "Rts.h" - -#include "RtsUtils.h" -#include "StablePtr.h" -#include "Adjustor.h" - -/* Adjustor logic for PowerPC and PowerPC64 */ - -#if defined(linux_HOST_OS) -#include -#endif - -// from AdjustorAsm.s -// not declared as a function so that AIX-style -// fundescs can never get in the way. -extern void *adjustorCode; - -#if defined(linux_HOST_OS) -__asm__("obscure_ccall_ret_code:\n\t" - "lwz 1,0(1)\n\t" - "lwz 0,4(1)\n\t" - "mtlr 0\n\t" - "blr"); -extern void obscure_ccall_ret_code(void); -#endif /* defined(linux_HOST_OS) */ - -#if defined(powerpc_HOST_ARCH) && defined(aix_HOST_OS) || defined(powerpc64_HOST_ARCH) && defined(__ELF__) && (!defined(_CALL_ELF) || _CALL_ELF == 1) - -/* !!! !!! WARNING: !!! !!! - * This structure is accessed from AdjustorAsm.s - * Any changes here have to be mirrored in the offsets there. - */ - -typedef struct AdjustorStub { - /* fundesc-based ABIs */ -#define FUNDESCS - StgFunPtr code; - struct AdjustorStub - *toc; - void *env; - StgStablePtr hptr; - StgFunPtr wptr; - StgInt negative_framesize; - StgInt extrawords_plus_one; -} AdjustorStub; - -#endif - -void initAdjustors(void) { } - -void* -createAdjustor(StgStablePtr hptr, - StgFunPtr wptr, - char *typeString - ) -{ -#if defined(linux_HOST_OS) - -#define OP_LO(op,lo) ((((unsigned)(op)) << 16) | (((unsigned)(lo)) & 0xFFFF)) -#define OP_HI(op,hi) ((((unsigned)(op)) << 16) | (((unsigned)(hi)) >> 16)) - /* The PowerPC Linux (32-bit) calling convention is annoyingly complex. - We need to calculate all the details of the stack frame layout, - taking into account the types of all the arguments, and then - generate code on the fly. */ - - int src_gpr = 3, dst_gpr = 5; - int fpr = 3; - int src_offset = 0, dst_offset = 0; - int n = strlen(typeString),i; - int src_locs[n], dst_locs[n]; - int frameSize; - - /* Step 1: - Calculate where the arguments should go. - src_locs[] will contain the locations of the arguments in the - original stack frame passed to the adjustor. - dst_locs[] will contain the locations of the arguments after the - adjustor runs, on entry to the wrapper proc pointed to by wptr. - - This algorithm is based on the one described on page 3-19 of the - System V ABI PowerPC Processor Supplement. - */ - for(i=0;typeString[i];i++) - { - char t = typeString[i]; - if((t == 'f' || t == 'd') && fpr <= 8) - src_locs[i] = dst_locs[i] = -32-(fpr++); - else - { - if((t == 'l' || t == 'L') && src_gpr <= 9) - { - if((src_gpr & 1) == 0) - src_gpr++; - src_locs[i] = -src_gpr; - src_gpr += 2; - } - else if((t == 'w' || t == 'W') && src_gpr <= 10) - { - src_locs[i] = -(src_gpr++); - } - else - { - if(t == 'l' || t == 'L' || t == 'd') - { - if(src_offset % 8) - src_offset += 4; - } - src_locs[i] = src_offset; - src_offset += (t == 'l' || t == 'L' || t == 'd') ? 8 : 4; - } - - if((t == 'l' || t == 'L') && dst_gpr <= 9) - { - if((dst_gpr & 1) == 0) - dst_gpr++; - dst_locs[i] = -dst_gpr; - dst_gpr += 2; - } - else if((t == 'w' || t == 'W') && dst_gpr <= 10) - { - dst_locs[i] = -(dst_gpr++); - } - else - { - if(t == 'l' || t == 'L' || t == 'd') - { - if(dst_offset % 8) - dst_offset += 4; - } - dst_locs[i] = dst_offset; - dst_offset += (t == 'l' || t == 'L' || t == 'd') ? 8 : 4; - } - } - } - - frameSize = dst_offset + 8; - frameSize = (frameSize+15) & ~0xF; - - /* Step 2: - Build the adjustor. - */ - // allocate space for at most 4 insns per parameter - // plus 14 more instructions. - ExecPage *page = allocateExecPage(); - if (page == NULL) { - barf("createAdjustor: failed to allocate executable page\n"); - } - unsigned *code = adjustor; - - *code++ = 0x48000008; // b *+8 - // * Put the hptr in a place where freeHaskellFunctionPtr - // can get at it. - *code++ = (unsigned) hptr; - - // * save the link register - *code++ = 0x7c0802a6; // mflr r0; - *code++ = 0x90010004; // stw r0, 4(r1); - // * and build a new stack frame - *code++ = OP_LO(0x9421, -frameSize); // stwu r1, -frameSize(r1) - - // * now generate instructions to copy arguments - // from the old stack frame into the new stack frame. - for(i=n-1;i>=0;i--) - { - if(src_locs[i] < -32) - ASSERT(dst_locs[i] == src_locs[i]); - else if(src_locs[i] < 0) - { - // source in GPR. - ASSERT(typeString[i] != 'f' && typeString[i] != 'd'); - if(dst_locs[i] < 0) - { - ASSERT(dst_locs[i] > -32); - // dst is in GPR, too. - - if(typeString[i] == 'l' || typeString[i] == 'L') - { - // mr dst+1, src+1 - *code++ = 0x7c000378 - | ((-dst_locs[i]+1) << 16) - | ((-src_locs[i]+1) << 11) - | ((-src_locs[i]+1) << 21); - } - // mr dst, src - *code++ = 0x7c000378 - | ((-dst_locs[i]) << 16) - | ((-src_locs[i]) << 11) - | ((-src_locs[i]) << 21); - } - else - { - if(typeString[i] == 'l' || typeString[i] == 'L') - { - // stw src+1, dst_offset+4(r1) - *code++ = 0x90010000 - | ((-src_locs[i]+1) << 21) - | (dst_locs[i] + 4); - } - - // stw src, dst_offset(r1) - *code++ = 0x90010000 - | ((-src_locs[i]) << 21) - | (dst_locs[i] + 8); - } - } - else - { - ASSERT(dst_locs[i] >= 0); - ASSERT(typeString[i] != 'f' && typeString[i] != 'd'); - - if(typeString[i] == 'l' || typeString[i] == 'L') - { - // lwz r0, src_offset(r1) - *code++ = 0x80010000 - | (src_locs[i] + frameSize + 8 + 4); - // stw r0, dst_offset(r1) - *code++ = 0x90010000 - | (dst_locs[i] + 8 + 4); - } - // lwz r0, src_offset(r1) - *code++ = 0x80010000 - | (src_locs[i] + frameSize + 8); - // stw r0, dst_offset(r1) - *code++ = 0x90010000 - | (dst_locs[i] + 8); - } - } - - // * hptr will be the new first argument. - // lis r3, hi(hptr) - *code++ = OP_HI(0x3c60, hptr); - // ori r3,r3,lo(hptr) - *code++ = OP_LO(0x6063, hptr); - - // * we need to return to a piece of code - // which will tear down the stack frame. - // lis r11,hi(obscure_ccall_ret_code) - *code++ = OP_HI(0x3d60, obscure_ccall_ret_code); - // ori r11,r11,lo(obscure_ccall_ret_code) - *code++ = OP_LO(0x616b, obscure_ccall_ret_code); - // mtlr r11 - *code++ = 0x7d6803a6; - - // * jump to wptr - // lis r11,hi(wptr) - *code++ = OP_HI(0x3d60, wptr); - // ori r11,r11,lo(wptr) - *code++ = OP_LO(0x616b, wptr); - // mtctr r11 - *code++ = 0x7d6903a6; - // bctr - *code++ = 0x4e800420; - - freezeExecPage(page); - - // Flush the Instruction cache: - { - unsigned *p = adjustor; - while(p < code) - { - __asm__ volatile ("dcbf 0,%0\n\tsync\n\ticbi 0,%0" - : : "r" (p)); - p++; - } - __asm__ volatile ("sync\n\tisync"); - } - -#else - -#define OP_LO(op,lo) ((((unsigned)(op)) << 16) | (((unsigned)(lo)) & 0xFFFF)) -#define OP_HI(op,hi) ((((unsigned)(op)) << 16) | (((unsigned)(hi)) >> 16)) - /* The following code applies to all PowerPC and PowerPC64 platforms - whose stack layout is based on the AIX ABI. - - Besides (obviously) AIX, this includes - Mac OS 9 and BeOS/PPC and Mac OS X PPC (may they rest in peace), - which use the 32-bit AIX ABI - powerpc64-linux, - which uses the 64-bit AIX ABI. - - The actual stack-frame shuffling is implemented out-of-line - in the function adjustorCode, in AdjustorAsm.S. - Here, we set up an AdjustorStub structure, which - is a function descriptor with a pointer to the AdjustorStub - struct in the position of the TOC that is loaded - into register r2. - - One nice thing about this is that there is _no_ code generated at - runtime on the platforms that have function descriptors. - */ - AdjustorStub *adjustorStub; - int sz = 0, extra_sz, total_sz; - -#if defined(FUNDESCS) - adjustorStub = stgMallocBytes(sizeof(AdjustorStub), "createAdjustor"); -#else - ExecPage *page = allocateExecPage(); - if (page == NULL) { - barf("createAdjustor: failed to allocate executable page\n"); - } - adjustorStub = (AdjustorStub *) page; -#endif /* defined(FUNDESCS) */ - adjustor = adjustorStub; - - adjustorStub->code = (void*) &adjustorCode; - -#if defined(FUNDESCS) - // function descriptors are a cool idea. - // We don't need to generate any code at runtime. - adjustorStub->toc = adjustorStub; -#else - - // no function descriptors :-( - // We need to do things "by hand". -#if defined(powerpc_HOST_ARCH) - // lis r2, hi(adjustorStub) - adjustorStub->lis = OP_HI(0x3c40, adjustorStub); - // ori r2, r2, lo(adjustorStub) - adjustorStub->ori = OP_LO(0x6042, adjustorStub); - // lwz r0, code(r2) - adjustorStub->lwz = OP_LO(0x8002, (char*)(&adjustorStub->code) - - (char*)adjustorStub); - // mtctr r0 - adjustorStub->mtctr = 0x7c0903a6; - // bctr - adjustorStub->bctr = 0x4e800420; - - freezeExecPage(page); -#else - barf("adjustor creation not supported on this platform"); -#endif /* defined(powerpc_HOST_ARCH) */ - - // Flush the Instruction cache: - { - int n = sizeof(AdjustorStub)/sizeof(unsigned); - unsigned *p = (unsigned*)adjustor; - while(n--) - { - __asm__ volatile ("dcbf 0,%0\n\tsync\n\ticbi 0,%0" - : : "r" (p)); - p++; - } - __asm__ volatile ("sync\n\tisync"); - } -#endif /* defined(FUNDESCS) */ - - // Calculate the size of the stack frame, in words. - sz = totalArgumentSize(typeString); - - // The first eight words of the parameter area - // are just "backing store" for the parameters passed in - // the GPRs. extra_sz is the number of words beyond those first - // 8 words. - extra_sz = sz - 8; - if(extra_sz < 0) - extra_sz = 0; - - // Calculate the total size of the stack frame. - total_sz = (6 /* linkage area */ - + 8 /* minimum parameter area */ - + 2 /* two extra arguments */ - + extra_sz)*sizeof(StgWord); - - // align to 16 bytes. - // AIX only requires 8 bytes, but who cares? - total_sz = (total_sz+15) & ~0xF; - - // Fill in the information that adjustorCode in AdjustorAsm.S - // will use to create a new stack frame with the additional args. - adjustorStub->hptr = hptr; - adjustorStub->wptr = wptr; - adjustorStub->negative_framesize = -total_sz; - adjustorStub->extrawords_plus_one = extra_sz + 1; - - return code; -} - -void -freeHaskellFunctionPtr(void* ptr) -{ -#if defined(linux_HOST_OS) - if ( *(StgWord*)ptr != 0x48000008 ) { - errorBelch("freeHaskellFunctionPtr: not for me, guv! %p\n", ptr); - return; - } - freeStablePtr(((StgStablePtr*)ptr)[1]); -#else - if ( ((AdjustorStub*)ptr)->code != (StgFunPtr) &adjustorCode ) { - errorBelch("freeHaskellFunctionPtr: not for me, guv! %p\n", ptr); - return; - } - freeStablePtr(((AdjustorStub*)ptr)->hptr); -#endif - - freeExecPage(ptr); -} ===================================== rts/include/rts/storage/ClosureMacros.h ===================================== @@ -152,10 +152,16 @@ EXTERN_INLINE StgHalfWord GET_TAG(const StgClosure *con) be duplicated here, otherwise there will be some -Wimplicit-function-declaration compilation errors. Especially when GHC compiles out-of-tree cbits that rely on SET_HDR in RTS API. + + However when RtsFlags.h is imported, we don't want to redefine them to avoid + spurious warnings (#24918). */ +#if !defined(RTS_FLAGS_DOING_PROFILING) +#define RTS_FLAGS_DOING_PROFILING 1 bool doingLDVProfiling(void); bool doingRetainerProfiling(void); bool doingErasProfiling(void); +#endif /* The following macro works for both retainer profiling and LDV profiling. For ===================================== rts/rts.cabal ===================================== @@ -362,11 +362,6 @@ library else asm-sources: adjustor/NativeAmd64Asm.S c-sources: adjustor/NativeAmd64.c - if arch(ppc) || arch(ppc64) - asm-sources: AdjustorAsm.S - c-sources: adjustor/NativePowerPC.c - if arch(ia64) - c-sources: adjustor/NativeIA64.c -- Use assembler STG entrypoint on architectures where it is used if arch(ppc) || arch(ppc64) || arch(s390x) || arch(riscv64) || arch(loongarch64) ===================================== testsuite/tests/driver/objc/all.T ===================================== @@ -1,19 +1,11 @@ -def if_not_platform(platforms, f): - if not (config.platform in platforms): - return f - else: - return normal - -skip_if_not_osx = if_not_platform(['i386-apple-darwin','x86_64-apple-darwin'], skip) - test('objc-hi', - [ skip_if_not_osx, + [ unless(opsys('darwin'), skip), objc_src, expect_fail_for(['ghci']) ], compile_and_run, ['-framework Foundation']) test('objcxx-hi', - [ skip_if_not_osx, + [ unless(opsys('darwin'), skip), objcxx_src, expect_fail_for(['ghci']) ], compile_and_run, ['-framework Foundation -lc++']) ===================================== testsuite/tests/ffi/should_run/Makefile ===================================== @@ -6,12 +6,10 @@ ffi018_ghci_setup : '$(TEST_HC)' $(TEST_HC_OPTS) -c ffi018_ghci_c.c T1288_ghci_setup : - # Don't show gcc warning: 'stdcall' attribute ignored [-Wattributes] - '$(TEST_HC)' $(TEST_HC_OPTS) $(ghciWayFlags) -c -optc=-Wno-attributes T1288_ghci_c.c + '$(TEST_HC)' $(TEST_HC_OPTS) $(ghciWayFlags) -c T1288_ghci_c.c T2276_ghci_setup : - # Don't show gcc warning: 'stdcall' attribute ignored [-Wattributes] - '$(TEST_HC)' $(TEST_HC_OPTS) $(ghciWayFlags) -c -optc=-Wno-attributes T2276_ghci_c.c + '$(TEST_HC)' $(TEST_HC_OPTS) $(ghciWayFlags) -c T2276_ghci_c.c ffi002_setup : '$(TEST_HC)' $(TEST_HC_OPTS) -c ffi002.hs ===================================== testsuite/tests/ffi/should_run/all.T ===================================== @@ -33,7 +33,6 @@ test('ffi004', skip, compile_and_run, ['']) # test('ffi005', [ omit_ways(prof_ways), when(arch('i386'), skip), - when(platform('i386-apple-darwin'), expect_broken(4105)), exit_code(3), req_c ], compile_and_run, ['ffi005_c.c']) @@ -101,7 +100,6 @@ test('T1288_ghci', test('T2276', [req_c], compile_and_run, ['T2276_c.c']) test('T2276_ghci', [ only_ghci, - when(opsys('darwin'), skip), # stdcall not supported on OS X pre_cmd('$MAKE -s --no-print-directory T2276_ghci_setup') ], compile_and_run, ['-fobject-code T2276_ghci_c.o']) ===================================== testsuite/tests/numeric/should_run/all.T ===================================== @@ -7,7 +7,7 @@ test('arith001', normal, compile_and_run, ['']) test('arith002', normal, compile_and_run, ['']) test('arith003', normal, compile_and_run, ['']) test('arith004', normal, compile_and_run, ['']) -test('arith005', when(platform('i386-apple-darwin'), expect_broken_for(7043, ['ghci'])), compile_and_run, ['']) +test('arith005', normal, compile_and_run, ['']) test('arith006', normal, compile_and_run, ['']) test('arith007', normal, compile_and_run, ['']) ===================================== testsuite/tests/rts/T10672/Makefile ===================================== @@ -5,7 +5,3 @@ include $(TOP)/mk/test.mk T10672_x64: '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -rtsopts=none -fforce-recomp -lgcc_s_seh-1 -package system-cxx-std-lib Main.hs Printf.hs cxxy.cpp - -T10672_x86: - '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -rtsopts=none -fforce-recomp -lgcc_s_dw2-1 -package system-cxx-std-lib \ - Main.hs Printf.hs cxxy.cpp ===================================== testsuite/tests/rts/T10672/all.T ===================================== @@ -3,9 +3,3 @@ test('T10672_x64', unless(opsys('mingw32'), skip), unless(arch('x86_64'), skip), when(opsys('mingw32'), expect_broken(16390))], makefile_test, ['T10672_x64']) - -test('T10672_x86', - [extra_files(['Main.hs', 'Printf.hs', 'cxxy.cpp']), - unless(opsys('mingw32'), skip), unless(arch('i386'), skip), - when(opsys('mingw32'), expect_broken(16390))], - makefile_test, ['T10672_x86']) ===================================== testsuite/tests/rts/all.T ===================================== @@ -38,7 +38,6 @@ test('derefnull', when(opsys('openbsd'), ignore_stderr), # SIGBUS on OX X (PPC and x86 only; amd64 gives SEGV) # The output under OS X is too unstable to readily compare - when(platform('i386-apple-darwin'), [ignore_stderr, exit_code(139)]), when(platform('x86_64-apple-darwin'), [ignore_stderr, exit_code(139)]), when(platform('aarch64-apple-darwin'), [ignore_stderr, exit_code(139)]), when(opsys('mingw32'), [ignore_stderr, exit_code(11)]), @@ -80,7 +79,6 @@ test('divbyzero', when(opsys('mingw32'), [ignore_stderr, exit_code(8)]), when(opsys('mingw32'), [fragile(18548)]), # The output under OS X is too unstable to readily compare - when(platform('i386-apple-darwin'), [ignore_stderr, exit_code(136)]), when(platform('x86_64-apple-darwin'), [ignore_stderr, exit_code(136)]), # ThreadSanitizer changes the output when(have_thread_sanitizer(), skip), ===================================== utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs ===================================== @@ -148,8 +148,6 @@ addPlatformDepCcFlags archOs cc0 = do let cc1 = addWorkaroundFor7799 archOs cc0 -- As per FPTOOLS_SET_C_LD_FLAGS case archOs of - ArchOS ArchX86 OSMinGW32 -> - return $ cc1 & _ccFlags %++ "-march=i686" ArchOS ArchX86 OSFreeBSD -> return $ cc1 & _ccFlags %++ "-march=i686" ArchOS ArchX86_64 OSSolaris2 -> @@ -183,4 +181,3 @@ addWorkaroundFor7799 :: ArchOS -> Cc -> Cc addWorkaroundFor7799 archOs cc | ArchX86 <- archOS_arch archOs = cc & _ccFlags %++ "-U__i686" | otherwise = cc - ===================================== utils/llvm-targets/gen-data-layout.sh ===================================== @@ -89,13 +89,10 @@ TARGETS=( ######################### # macOS - "i386-apple-darwin" "x86_64-apple-darwin" "arm64-apple-darwin" # iOS - "armv7-apple-ios" "arm64-apple-ios" - "i386-apple-ios" "x86_64-apple-ios" ######################### View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/848d5160f6b84d36ba15cea83bad82641138bbb2...a27ed449621487cc121c765da0d721c88651890b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/848d5160f6b84d36ba15cea83bad82641138bbb2...a27ed449621487cc121c765da0d721c88651890b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 13:16:36 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Wed, 05 Jun 2024 09:16:36 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/bump-T7653 Message-ID: <66606534c9a55_28699f34a801083fc@gitlab.mail> Cheng Shao pushed new branch wip/bump-T7653 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/bump-T7653 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 15:36:04 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 05 Jun 2024 11:36:04 -0400 Subject: [Git][ghc/ghc][master] 2 commits: hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows Message-ID: <666085e4cec81_28699202dc4c132563@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 4 changed files: - configure.ac - hadrian/src/Builder.hs - m4/fp_find_nm.m4 - m4/fp_prog_ar_args.m4 Changes: ===================================== configure.ac ===================================== @@ -314,6 +314,8 @@ else AC_CHECK_TARGET_TOOL([WindresCmd],[windres]) AC_CHECK_TARGET_TOOL([OBJDUMP],[objdump]) + WindresCmd="$(cygpath -m $WindresCmd)" + if test "$Genlib" != ""; then GenlibCmd="$(cygpath -m $Genlib)" fi @@ -464,7 +466,12 @@ case $HostOS_CPP in ;; esac -ObjdumpCmd="$OBJDUMP" +if test "$HostOS" = "mingw32" +then + ObjdumpCmd=$(cygpath -m "$OBJDUMP") +else + ObjdumpCmd="$OBJDUMP" +fi AC_SUBST([ObjdumpCmd]) dnl ** Which ranlib to use? @@ -473,7 +480,12 @@ AC_PROG_RANLIB if test "$RANLIB" = ":"; then AC_MSG_ERROR([cannot find ranlib in your PATH]) fi -RanlibCmd="$RANLIB" +if test "$HostOS" = "mingw32" +then + RanlibCmd=$(cygpath -m "$RANLIB") +else + RanlibCmd="$RANLIB" +fi AC_SUBST([RanlibCmd]) dnl ** which strip to use? ===================================== hadrian/src/Builder.hs ===================================== @@ -34,6 +34,7 @@ import Base import Context import Oracles.Flag import Oracles.Setting (setting, Setting(..)) +import Oracles.Setting (settingsFileSetting, ToolchainSetting(..)) import Packages import GHC.IO.Encoding (getFileSystemEncoding) @@ -239,9 +240,10 @@ instance H.Builder Builder where Ghc {} -> do root <- buildRoot unlitPath <- builderPath Unlit + distro_mingw <- settingsFileSetting ToolchainSetting_DistroMinGW return $ [ unlitPath ] - ++ [ root -/- mingwStamp | windowsHost ] + ++ [ root -/- mingwStamp | windowsHost, distro_mingw == "NO" ] -- proxy for the entire mingw toolchain that -- we have in inplace/mingw initially, and then at -- root -/- mingw. ===================================== m4/fp_find_nm.m4 ===================================== @@ -9,7 +9,12 @@ AC_DEFUN([FP_FIND_NM], AC_MSG_ERROR([cannot find nm in your PATH]) fi fi - NmCmd="$NM" + if test "$HostOS" = "mingw32" + then + NmCmd=$(cygpath -m "$NM") + else + NmCmd="$NM" + fi AC_SUBST([NmCmd]) if test "$TargetOS_CPP" = "darwin" @@ -37,4 +42,3 @@ AC_DEFUN([FP_FIND_NM], esac fi ]) - ===================================== m4/fp_prog_ar_args.m4 ===================================== @@ -30,7 +30,13 @@ else fi fi]) fp_prog_ar_args=$fp_cv_prog_ar_args -AC_SUBST([ArCmd], ["$fp_prog_ar"]) +if test "$HostOS" = "mingw32" +then + ArCmd=$(cygpath -m "$fp_prog_ar") +else + ArCmd="$fp_prog_ar" +fi +AC_SUBST([ArCmd]) AC_SUBST([ArArgs], ["$fp_prog_ar_args"]) ])# FP_PROG_AR_ARGS View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5132754b80d468e0c24e39b63eea525dc1ee3a5b...6ffbd678836775f9ea77335ef0086feaa94dc515 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5132754b80d468e0c24e39b63eea525dc1ee3a5b...6ffbd678836775f9ea77335ef0086feaa94dc515 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 15:36:50 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 05 Jun 2024 11:36:50 -0400 Subject: [Git][ghc/ghc][master] 6 commits: hadrian: remove OSDarwin mention from speedHack Message-ID: <6660861275dd5_28699219e20c135693@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 20 changed files: - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Linker/Static.hs - docs/users_guide/9.12.1-notes.rst - hadrian/src/Settings/Packages.hs - llvm-targets - rts/RtsSymbols.c - rts/StgCRun.c - testsuite/tests/driver/objc/all.T - testsuite/tests/ffi/should_run/Makefile - testsuite/tests/ffi/should_run/all.T - testsuite/tests/numeric/should_run/all.T - testsuite/tests/rts/T10672/Makefile - testsuite/tests/rts/T10672/all.T - testsuite/tests/rts/all.T - utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs - utils/llvm-targets/gen-data-layout.sh Changes: ===================================== compiler/GHC/Cmm/CLabel.hs ===================================== @@ -1659,11 +1659,7 @@ pprDynamicLinkerAsmLabel !platform dllInfo ppLbl = GotSymbolPtr -> ppLbl <> text "@GOTPCREL" GotSymbolOffset -> ppLbl | platformArch platform == ArchAArch64 -> ppLbl - | otherwise -> - case dllInfo of - CodeStub -> char 'L' <> ppLbl <> text "$stub" - SymbolPtr -> char 'L' <> ppLbl <> text "$non_lazy_ptr" - _ -> panic "pprDynamicLinkerAsmLabel" + | otherwise -> panic "pprDynamicLinkerAsmLabel" OSAIX -> case dllInfo of ===================================== compiler/GHC/CmmToAsm/PIC.hs ===================================== @@ -303,25 +303,15 @@ howToAccessLabel config arch OSDarwin DataReference lbl | otherwise = AccessDirectly -howToAccessLabel config arch OSDarwin JumpReference lbl +howToAccessLabel config _ OSDarwin JumpReference lbl -- dyld code stubs don't work for tailcalls because the -- stack alignment is only right for regular calls. -- Therefore, we have to go via a symbol pointer: - | arch == ArchX86 || arch == ArchX86_64 || arch == ArchAArch64 - , ncgLabelDynamic config lbl + | ncgLabelDynamic config lbl = AccessViaSymbolPtr -howToAccessLabel config arch OSDarwin _kind lbl - -- Code stubs are the usual method of choice for imported code; - -- not needed on x86_64 because Apple's new linker, ld64, generates - -- them automatically, neither on Aarch64 (arm64). - | arch /= ArchX86_64 - , arch /= ArchAArch64 - , ncgLabelDynamic config lbl - = AccessViaStub - - | otherwise +howToAccessLabel _ _ OSDarwin _ _ = AccessDirectly ---------------------------------------------------------------------------- @@ -534,16 +524,6 @@ gotLabel -- However, for PIC on x86, we need a small helper function. pprGotDeclaration :: NCGConfig -> HDoc pprGotDeclaration config = case (arch,os) of - (ArchX86, OSDarwin) - | ncgPIC config - -> lines_ [ - text ".section __TEXT,__textcoal_nt,coalesced,no_toc", - text ".weak_definition ___i686.get_pc_thunk.ax", - text ".private_extern ___i686.get_pc_thunk.ax", - text "___i686.get_pc_thunk.ax:", - text "\tmovl (%esp), %eax", - text "\tret" ] - (_, OSDarwin) -> empty -- Emit XCOFF TOC section @@ -597,59 +577,6 @@ pprGotDeclaration config = case (arch,os) of pprImportedSymbol :: NCGConfig -> CLabel -> HDoc pprImportedSymbol config importedLbl = case (arch,os) of - (ArchX86, OSDarwin) - | Just (CodeStub, lbl) <- dynamicLinkerLabelInfo importedLbl - -> if not pic - then - lines_ [ - text ".symbol_stub", - text "L" <> ppr_lbl lbl <> text "$stub:", - text "\t.indirect_symbol" <+> ppr_lbl lbl, - text "\tjmp *L" <> ppr_lbl lbl - <> text "$lazy_ptr", - text "L" <> ppr_lbl lbl - <> text "$stub_binder:", - text "\tpushl $L" <> ppr_lbl lbl - <> text "$lazy_ptr", - text "\tjmp dyld_stub_binding_helper" - ] - else - lines_ [ - text ".section __TEXT,__picsymbolstub2," - <> text "symbol_stubs,pure_instructions,25", - text "L" <> ppr_lbl lbl <> text "$stub:", - text "\t.indirect_symbol" <+> ppr_lbl lbl, - text "\tcall ___i686.get_pc_thunk.ax", - text "1:", - text "\tmovl L" <> ppr_lbl lbl - <> text "$lazy_ptr-1b(%eax),%edx", - text "\tjmp *%edx", - text "L" <> ppr_lbl lbl - <> text "$stub_binder:", - text "\tlea L" <> ppr_lbl lbl - <> text "$lazy_ptr-1b(%eax),%eax", - text "\tpushl %eax", - text "\tjmp dyld_stub_binding_helper" - ] - $$ lines_ [ - text ".section __DATA, __la_sym_ptr" - <> (if pic then int 2 else int 3) - <> text ",lazy_symbol_pointers", - text "L" <> ppr_lbl lbl <> text "$lazy_ptr:", - text "\t.indirect_symbol" <+> ppr_lbl lbl, - text "\t.long L" <> ppr_lbl lbl - <> text "$stub_binder"] - - | Just (SymbolPtr, lbl) <- dynamicLinkerLabelInfo importedLbl - -> lines_ [ - text ".non_lazy_symbol_pointer", - char 'L' <> ppr_lbl lbl <> text "$non_lazy_ptr:", - text "\t.indirect_symbol" <+> ppr_lbl lbl, - text "\t.long\t0"] - - | otherwise - -> empty - (ArchAArch64, OSDarwin) -> empty @@ -734,7 +661,6 @@ pprImportedSymbol config importedLbl = case (arch,os) of ppr_lbl = pprAsmLabel platform arch = platformArch platform os = platformOS platform - pic = ncgPIC config -------------------------------------------------------------------------------- -- Generate code to calculate the address that should be put in the @@ -840,11 +766,11 @@ initializePicBase_ppc _ _ _ _ -- (See PprMach.hs) initializePicBase_x86 - :: Arch -> OS -> Reg + :: OS -> Reg -> [NatCmmDecl (Alignment, RawCmmStatics) X86.Instr] -> NatM [NatCmmDecl (Alignment, RawCmmStatics) X86.Instr] -initializePicBase_x86 ArchX86 os picReg +initializePicBase_x86 os picReg (CmmProc info lab live (ListGraph blocks) : statics) | osElfTarget os = return (CmmProc info lab live (ListGraph blocks') : statics) @@ -862,12 +788,12 @@ initializePicBase_x86 ArchX86 os picReg fetchGOT (BasicBlock bID insns) = BasicBlock bID (X86.FETCHGOT picReg : insns) -initializePicBase_x86 ArchX86 OSDarwin picReg +initializePicBase_x86 OSDarwin picReg (CmmProc info lab live (ListGraph (entry:blocks)) : statics) = return (CmmProc info lab live (ListGraph (block':blocks)) : statics) where BasicBlock bID insns = entry block' = BasicBlock bID (X86.FETCHPC picReg : insns) -initializePicBase_x86 _ _ _ _ +initializePicBase_x86 _ _ _ = panic "initializePicBase_x86: not needed" ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -124,7 +124,7 @@ cmmTopCodeGen (CmmProc info lab live graph) = do os = platformOS platform case picBaseMb of - Just picBase -> initializePicBase_x86 ArchX86 os picBase tops + Just picBase -> initializePicBase_x86 os picBase tops Nothing -> return tops cmmTopCodeGen (CmmData sec dat) = ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -883,7 +883,6 @@ needs_probe_call :: Platform -> Int -> Bool needs_probe_call platform amount = case platformOS platform of OSMinGW32 -> case platformArch platform of - ArchX86 -> amount > (4 * 1024) ArchX86_64 -> amount > (4 * 1024) _ -> False _ -> False @@ -913,15 +912,6 @@ mkStackAllocInstr platform amount -- function dropping the stack more than a page. -- See Note [Windows stack layout] case platformArch platform of - ArchX86 | needs_probe_call platform amount -> - [ MOV II32 (OpImm (ImmInt amount)) (OpReg eax) - , CALL (Left $ strImmLit (fsLit "___chkstk_ms")) [eax] - , SUB II32 (OpReg eax) (OpReg esp) - ] - | otherwise -> - [ SUB II32 (OpImm (ImmInt amount)) (OpReg esp) - , TEST II32 (OpReg esp) (OpReg esp) - ] ArchX86_64 | needs_probe_call platform amount -> [ MOV II64 (OpImm (ImmInt amount)) (OpReg rax) , CALL (Left $ strImmLit (fsLit "___chkstk_ms")) [rax] ===================================== compiler/GHC/Driver/Config/Cmm.hs ===================================== @@ -24,15 +24,10 @@ initCmmConfig dflags = CmmConfig , cmmDoCmmSwitchPlans = not (backendHasNativeSwitch (backend dflags)) , cmmSplitProcPoints = not (backendSupportsUnsplitProcPoints (backend dflags)) || not (platformTablesNextToCode platform) - || usingInconsistentPicReg , cmmAllowMul2 = (ncg && x86ish) || llvm , cmmOptConstDivision = not llvm } where platform = targetPlatform dflags - usingInconsistentPicReg = - case (platformArch platform, platformOS platform, positionIndependent dflags) - of (ArchX86, OSDarwin, pic) -> pic - _ -> False -- Copied from StgToCmm (ncg, llvm) = case backendPrimitiveImplementation (backend dflags) of GenericPrimitives -> (False, False) ===================================== compiler/GHC/Linker/Static.hs ===================================== @@ -219,25 +219,12 @@ linkBinary' staticLink logger tmpfs dflags unit_env o_files dep_units = do toolSettings_ldSupportsCompactUnwind toolSettings' && (platformOS platform == OSDarwin) && case platformArch platform of - ArchX86 -> True ArchX86_64 -> True - ArchARM {} -> True ArchAArch64 -> True _ -> False then ["-Wl,-no_compact_unwind"] else []) - -- '-Wl,-read_only_relocs,suppress' - -- ld gives loads of warnings like: - -- ld: warning: text reloc in _base_GHCziArr_unsafeArray_info to _base_GHCziArr_unsafeArray_closure - -- when linking any program. We're not sure - -- whether this is something we ought to fix, but - -- for now this flags silences them. - ++ (if platformOS platform == OSDarwin && - platformArch platform == ArchX86 - then ["-Wl,-read_only_relocs,suppress"] - else []) - -- We should rather be asking does it support --gc-sections? ++ (if toolSettings_ldIsGnuLd toolSettings' && not (gopt Opt_WholeArchiveHsLibs dflags) ===================================== docs/users_guide/9.12.1-notes.rst ===================================== @@ -69,6 +69,10 @@ Compiler and treat it as ``ccall``. All C import/export declarations on Windows should now use ``ccall``. +- 32-bit macOS/iOS support has also been completely removed (`#24921 + `_). This does + not affect existing support of apple systems on x86_64/aarch64. + GHCi ~~~~ ===================================== hadrian/src/Settings/Packages.hs ===================================== @@ -480,7 +480,7 @@ rtsPackageArgs = package rts ? do speedHack :: Action Bool speedHack = do i386 <- anyTargetArch [ArchX86] - goodOS <- not <$> anyTargetOs [OSDarwin, OSSolaris2] + goodOS <- not <$> anyTargetOs [OSSolaris2] return $ i386 && goodOS -- See @rts/ghc.mk at . ===================================== llvm-targets ===================================== @@ -43,12 +43,9 @@ ,("riscv64-unknown-linux", ("e-m:e-p:64:64-i64:64-i128:128-n64-S128", "", "+m +a +f +d +c +relax")) ,("loongarch64-unknown-linux-gnu", ("e-m:e-p:64:64-i64:64-i128:128-n64-S128", "", "+f +d")) ,("loongarch64-unknown-linux", ("e-m:e-p:64:64-i64:64-i128:128-n64-S128", "", "+f +d")) -,("i386-apple-darwin", ("e-m:o-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:128-n8:16:32-S128", "penryn", "")) ,("x86_64-apple-darwin", ("e-m:o-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "penryn", "")) ,("arm64-apple-darwin", ("e-m:o-i64:64-i128:128-n32:64-S128", "generic", "+v8.3a +fp-armv8 +neon +crc +crypto +fullfp16 +ras +lse +rdm +rcpc +zcm +zcz +sha2 +aes")) -,("armv7-apple-ios", ("e-m:o-p:32:32-Fi8-f64:32:64-v64:32:64-v128:32:128-a:0:32-n32-S32", "generic", "")) ,("aarch64-apple-ios", ("e-m:o-i64:64-i128:128-n32:64-S128", "apple-a7", "+fp-armv8 +neon +crypto +zcm +zcz +sha2 +aes")) -,("i386-apple-ios", ("e-m:o-p:32:32-p270:32:32-p271:32:32-p272:64:64-f64:32:64-f80:128-n8:16:32-S128", "yonah", "")) ,("x86_64-apple-ios", ("e-m:o-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "core2", "")) ,("amd64-portbld-freebsd", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) ,("x86_64-unknown-freebsd", ("e-m:e-p270:32:32-p271:32:32-p272:64:64-i64:64-f80:128-n8:16:32:64-S128", "x86-64", "")) ===================================== rts/RtsSymbols.c ===================================== @@ -1073,11 +1073,5 @@ RtsSymbolVal rtsSyms[] = { RTS_LIBFFI_SYMBOLS RTS_ARM_OUTLINE_ATOMIC_SYMBOLS SymI_HasDataProto(nonmoving_write_barrier_enabled) -#if defined(darwin_HOST_OS) && defined(i386_HOST_ARCH) - // dyld stub code contains references to this, - // but it should never be called because we treat - // lazy pointers as nonlazy. - { "dyld_stub_binding_helper", (void*)0xDEADBEEF, STRENGTH_NORMAL }, -#endif { 0, 0, STRENGTH_NORMAL, SYM_TYPE_CODE } /* sentinel */ }; ===================================== rts/StgCRun.c ===================================== @@ -102,13 +102,8 @@ StgFunPtr StgReturn(void) #if defined(i386_HOST_ARCH) -#if defined(darwin_HOST_OS) || defined(ios_HOST_OS) -#define STG_GLOBAL ".globl " -#define STG_HIDDEN ".private_extern " -#else #define STG_GLOBAL ".global " #define STG_HIDDEN ".hidden " -#endif /* * Note [Stack Alignment on X86] ===================================== testsuite/tests/driver/objc/all.T ===================================== @@ -1,19 +1,11 @@ -def if_not_platform(platforms, f): - if not (config.platform in platforms): - return f - else: - return normal - -skip_if_not_osx = if_not_platform(['i386-apple-darwin','x86_64-apple-darwin'], skip) - test('objc-hi', - [ skip_if_not_osx, + [ unless(opsys('darwin'), skip), objc_src, expect_fail_for(['ghci']) ], compile_and_run, ['-framework Foundation']) test('objcxx-hi', - [ skip_if_not_osx, + [ unless(opsys('darwin'), skip), objcxx_src, expect_fail_for(['ghci']) ], compile_and_run, ['-framework Foundation -lc++']) ===================================== testsuite/tests/ffi/should_run/Makefile ===================================== @@ -6,12 +6,10 @@ ffi018_ghci_setup : '$(TEST_HC)' $(TEST_HC_OPTS) -c ffi018_ghci_c.c T1288_ghci_setup : - # Don't show gcc warning: 'stdcall' attribute ignored [-Wattributes] - '$(TEST_HC)' $(TEST_HC_OPTS) $(ghciWayFlags) -c -optc=-Wno-attributes T1288_ghci_c.c + '$(TEST_HC)' $(TEST_HC_OPTS) $(ghciWayFlags) -c T1288_ghci_c.c T2276_ghci_setup : - # Don't show gcc warning: 'stdcall' attribute ignored [-Wattributes] - '$(TEST_HC)' $(TEST_HC_OPTS) $(ghciWayFlags) -c -optc=-Wno-attributes T2276_ghci_c.c + '$(TEST_HC)' $(TEST_HC_OPTS) $(ghciWayFlags) -c T2276_ghci_c.c ffi002_setup : '$(TEST_HC)' $(TEST_HC_OPTS) -c ffi002.hs ===================================== testsuite/tests/ffi/should_run/all.T ===================================== @@ -33,7 +33,6 @@ test('ffi004', skip, compile_and_run, ['']) # test('ffi005', [ omit_ways(prof_ways), when(arch('i386'), skip), - when(platform('i386-apple-darwin'), expect_broken(4105)), exit_code(3), req_c ], compile_and_run, ['ffi005_c.c']) @@ -101,7 +100,6 @@ test('T1288_ghci', test('T2276', [req_c], compile_and_run, ['T2276_c.c']) test('T2276_ghci', [ only_ghci, - when(opsys('darwin'), skip), # stdcall not supported on OS X pre_cmd('$MAKE -s --no-print-directory T2276_ghci_setup') ], compile_and_run, ['-fobject-code T2276_ghci_c.o']) ===================================== testsuite/tests/numeric/should_run/all.T ===================================== @@ -7,7 +7,7 @@ test('arith001', normal, compile_and_run, ['']) test('arith002', normal, compile_and_run, ['']) test('arith003', normal, compile_and_run, ['']) test('arith004', normal, compile_and_run, ['']) -test('arith005', when(platform('i386-apple-darwin'), expect_broken_for(7043, ['ghci'])), compile_and_run, ['']) +test('arith005', normal, compile_and_run, ['']) test('arith006', normal, compile_and_run, ['']) test('arith007', normal, compile_and_run, ['']) ===================================== testsuite/tests/rts/T10672/Makefile ===================================== @@ -5,7 +5,3 @@ include $(TOP)/mk/test.mk T10672_x64: '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -rtsopts=none -fforce-recomp -lgcc_s_seh-1 -package system-cxx-std-lib Main.hs Printf.hs cxxy.cpp - -T10672_x86: - '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -rtsopts=none -fforce-recomp -lgcc_s_dw2-1 -package system-cxx-std-lib \ - Main.hs Printf.hs cxxy.cpp ===================================== testsuite/tests/rts/T10672/all.T ===================================== @@ -3,9 +3,3 @@ test('T10672_x64', unless(opsys('mingw32'), skip), unless(arch('x86_64'), skip), when(opsys('mingw32'), expect_broken(16390))], makefile_test, ['T10672_x64']) - -test('T10672_x86', - [extra_files(['Main.hs', 'Printf.hs', 'cxxy.cpp']), - unless(opsys('mingw32'), skip), unless(arch('i386'), skip), - when(opsys('mingw32'), expect_broken(16390))], - makefile_test, ['T10672_x86']) ===================================== testsuite/tests/rts/all.T ===================================== @@ -38,7 +38,6 @@ test('derefnull', when(opsys('openbsd'), ignore_stderr), # SIGBUS on OX X (PPC and x86 only; amd64 gives SEGV) # The output under OS X is too unstable to readily compare - when(platform('i386-apple-darwin'), [ignore_stderr, exit_code(139)]), when(platform('x86_64-apple-darwin'), [ignore_stderr, exit_code(139)]), when(platform('aarch64-apple-darwin'), [ignore_stderr, exit_code(139)]), when(opsys('mingw32'), [ignore_stderr, exit_code(11)]), @@ -80,7 +79,6 @@ test('divbyzero', when(opsys('mingw32'), [ignore_stderr, exit_code(8)]), when(opsys('mingw32'), [fragile(18548)]), # The output under OS X is too unstable to readily compare - when(platform('i386-apple-darwin'), [ignore_stderr, exit_code(136)]), when(platform('x86_64-apple-darwin'), [ignore_stderr, exit_code(136)]), # ThreadSanitizer changes the output when(have_thread_sanitizer(), skip), ===================================== utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs ===================================== @@ -148,8 +148,6 @@ addPlatformDepCcFlags archOs cc0 = do let cc1 = addWorkaroundFor7799 archOs cc0 -- As per FPTOOLS_SET_C_LD_FLAGS case archOs of - ArchOS ArchX86 OSMinGW32 -> - return $ cc1 & _ccFlags %++ "-march=i686" ArchOS ArchX86 OSFreeBSD -> return $ cc1 & _ccFlags %++ "-march=i686" ArchOS ArchX86_64 OSSolaris2 -> @@ -183,4 +181,3 @@ addWorkaroundFor7799 :: ArchOS -> Cc -> Cc addWorkaroundFor7799 archOs cc | ArchX86 <- archOS_arch archOs = cc & _ccFlags %++ "-U__i686" | otherwise = cc - ===================================== utils/llvm-targets/gen-data-layout.sh ===================================== @@ -89,13 +89,10 @@ TARGETS=( ######################### # macOS - "i386-apple-darwin" "x86_64-apple-darwin" "arm64-apple-darwin" # iOS - "armv7-apple-ios" "arm64-apple-ios" - "i386-apple-ios" "x86_64-apple-ios" ######################### View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6ffbd678836775f9ea77335ef0086feaa94dc515...11d661c47652339d5552b18940f876cca380e1bf -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6ffbd678836775f9ea77335ef0086feaa94dc515...11d661c47652339d5552b18940f876cca380e1bf You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 16:07:19 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 05 Jun 2024 12:07:19 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 11 commits: hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows Message-ID: <66608d36e6ed6_286992668d641383ba@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - fab30940 by Georgi Lyubenov at 2024-06-05T12:07:08-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - eb4e3b95 by Ben Gamari at 2024-06-05T12:07:11-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - d6940e46 by Sebastian Graf at 2024-06-05T12:07:11-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 30 changed files: - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Linker/Static.hs - configure.ac - docs/users_guide/9.12.1-notes.rst - hadrian/src/Builder.hs - hadrian/src/Settings/Packages.hs - libraries/base/base.cabal - libraries/base/changelog.md - libraries/base/src/Data/Bitraversable.hs - llvm-targets - m4/fp_find_nm.m4 - m4/fp_prog_ar_args.m4 - rts/RtsSymbols.c - rts/StgCRun.c - testsuite/tests/driver/objc/all.T - testsuite/tests/ffi/should_run/Makefile - testsuite/tests/ffi/should_run/all.T - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/numeric/should_run/all.T - testsuite/tests/rts/T10672/Makefile - testsuite/tests/rts/T10672/all.T - testsuite/tests/rts/all.T - utils/ghc-toolchain/src/GHC/Toolchain/Tools/Cc.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a27ed449621487cc121c765da0d721c88651890b...d6940e46a2ee323966b66a9d01b53f6bddd59eb0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a27ed449621487cc121c765da0d721c88651890b...d6940e46a2ee323966b66a9d01b53f6bddd59eb0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 16:48:22 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 05 Jun 2024 12:48:22 -0400 Subject: [Git][ghc/ghc][wip/T24868] More wibbles Message-ID: <666096d6bd313_286992c55cf415327d@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24868 at Glasgow Haskell Compiler / GHC Commits: f2e10a2c by Simon Peyton Jones at 2024-06-05T17:48:02+01:00 More wibbles - - - - - 19 changed files: - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/TcType.hs - testsuite/tests/typecheck/should_compile/tc214.stderr - testsuite/tests/typecheck/should_fail/T10709.stderr - testsuite/tests/typecheck/should_fail/T10709b.stderr - testsuite/tests/typecheck/should_fail/T13909.stderr - testsuite/tests/typecheck/should_fail/tcfail201.stderr Changes: ===================================== compiler/GHC/Core/TyCo/FVs.hs ===================================== @@ -290,16 +290,19 @@ runTyCoVars f = appEndo f emptyVarSet ********************************************************************* -} tyCoVarsOfType :: Type -> TyCoVarSet +-- The "deep" TyCoVars of the the type tyCoVarsOfType ty = runTyCoVars (deep_ty ty) -- Alternative: -- tyCoVarsOfType ty = closeOverKinds (shallowTyCoVarsOfType ty) tyCoVarsOfTypes :: [Type] -> TyCoVarSet +-- The "deep" TyCoVars of the the type tyCoVarsOfTypes tys = runTyCoVars (deep_tys tys) -- Alternative: -- tyCoVarsOfTypes tys = closeOverKinds (shallowTyCoVarsOfTypes tys) tyCoVarsOfCo :: Coercion -> TyCoVarSet +-- The "deep" TyCoVars of the the coercion -- See Note [Free variables of types] tyCoVarsOfCo co = runTyCoVars (deep_co co) ===================================== compiler/GHC/Core/TyCo/Ppr.hs ===================================== @@ -93,6 +93,13 @@ pprPrecTypeX env prec ty -- NB: debug-style is used for -dppr-debug -- dump-style is used for -ddump-tc-trace etc +tidyToIfaceTypeStyX :: TidyEnv -> Type -> PprStyle -> IfaceType +tidyToIfaceTypeStyX env ty sty + | userStyle sty = tidyToIfaceTypeX env ty + | otherwise = toIfaceTypeX (tyCoVarsOfType ty) ty + -- in latter case, don't tidy, as we'll be printing uniques. + + pprTyLit :: TyLit -> SDoc pprTyLit = pprIfaceTyLit . toIfaceTyLit @@ -100,12 +107,6 @@ pprKind, pprParendKind :: Kind -> SDoc pprKind = pprType pprParendKind = pprParendType -tidyToIfaceTypeStyX :: TidyEnv -> Type -> PprStyle -> IfaceType -tidyToIfaceTypeStyX env ty sty - | userStyle sty = tidyToIfaceTypeX env ty - | otherwise = toIfaceTypeX (tyCoVarsOfType ty) ty - -- in latter case, don't tidy, as we'll be printing uniques. - tidyToIfaceType :: Type -> IfaceType tidyToIfaceType = tidyToIfaceTypeX emptyTidyEnv ===================================== compiler/GHC/Core/TyCo/Tidy.hs ===================================== @@ -4,14 +4,18 @@ module GHC.Core.TyCo.Tidy ( -- * Tidying type related things up for printing - tidyType, tidyTypes, - tidyOpenType, tidyOpenTypes, - tidyVarBndr, tidyVarBndrs, tidyFreeTyCoVars, avoidNameClashes, - tidyOpenTyCoVar, tidyOpenTyCoVars, tidyAvoiding, - tidyTyCoVarOcc, + tidyType, tidyTypes, + tidyCo, tidyCos, tidyTopType, - tidyCo, tidyCos, - tidyForAllTyBinder, tidyForAllTyBinders + + tidyOpenType, tidyOpenTypes, + tidyOpenTypeX, tidyOpenTypesX, + tidyFreeTyCoVars, tidyFreeTyCoVarX, tidyFreeTyCoVarsX, + + tidyAvoiding, + tidyVarBndr, tidyVarBndrs, avoidNameClashes, + tidyForAllTyBinder, tidyForAllTyBinders, + tidyTyCoVarOcc ) where import GHC.Prelude @@ -94,24 +98,27 @@ tidyForAllTyBinders tidy_env tvbs tidyFreeTyCoVars :: TidyEnv -> [TyCoVar] -> TidyEnv -- ^ Add the free 'TyVar's to the env in tidy form, -- so that we can tidy the type they are free in -tidyFreeTyCoVars tidy_env tyvars - = fst (tidyOpenTyCoVars tidy_env tyvars) +-- Precondition: input free vars are +-- (a) closed over kinds and +-- (b) scope-sorted +tidyFreeTyCoVars tidy_env tyvars = fst (tidyFreeTyCoVarsX tidy_env tyvars) --------------- -tidyOpenTyCoVars :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar]) -tidyOpenTyCoVars env tyvars = mapAccumL tidyOpenTyCoVar env tyvars +tidyFreeTyCoVarsX :: TidyEnv -> [TyCoVar] -> (TidyEnv, [TyCoVar]) +-- Precondition: input free vars are +-- (a) closed over kinds and +-- (b) scope-sorted +tidyFreeTyCoVarsX env tyvars = mapAccumL tidyFreeTyCoVarX env tyvars --------------- -tidyOpenTyCoVar :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar) +tidyFreeTyCoVarX :: TidyEnv -> TyCoVar -> (TidyEnv, TyCoVar) -- ^ Treat a new 'TyCoVar' as a binder, and give it a fresh tidy name -- using the environment if one has not already been allocated. See -- also 'tidyVarBndr' -tidyOpenTyCoVar env@(_, subst) tyvar +tidyFreeTyCoVarX env@(_, subst) tyvar = case lookupVarEnv subst tyvar of - Just tyvar' -> (env, tyvar') -- Already substituted - Nothing -> - let env' = tidyFreeTyCoVars env (tyCoVarsOfTypeList (tyVarKind tyvar)) - in tidyVarBndr env' tyvar -- Treat it as a binder + Just tyvar' -> (env, tyvar') -- Already substituted + Nothing -> tidyVarBndr env tyvar -- Treat it as a binder --------------- tidyTyCoVarOcc :: TidyEnv -> TyCoVar -> TyCoVar @@ -171,8 +178,13 @@ tidyType env (ty@(ForAllTy{})) = tidyForAllType env ty tidyForAllType :: TidyEnv -> Type -> Type -tidyForAllType (occ_env, var_env) ty +tidyForAllType env ty = (mkForAllTys' $! (zip tcvs' vis)) $! tidyType body_env body_ty + where + (tcvs, vis, body_ty) = splitForAllTyCoVars' ty + (body_env, tcvs') = tidyVarBndrs env tcvs + +{- where (tcvs, vis, body_ty) = splitForAllTyCoVars' ty free_tcvs = tyCoVarsOfType ty @@ -188,7 +200,7 @@ tidyForAllType (occ_env, var_env) ty occ = case lookupVarEnv var_env var of Just var' -> getOccName var' Nothing -> getOccName var - +-} -- The following two functions differ from mkForAllTys and splitForAllTyCoVars in that -- they expect/preserve the ForAllTyFlag argument. These belong to "GHC.Core.Type", but @@ -258,23 +270,39 @@ We can see: Ideally we'd like to do this at every forall, but we make do with doing it once at the top level of `tidyOpenTypes`, and that turns out quite well. -} +--------------- +trimTidyEnv :: TidyEnv -> [TyCoVar] -> TidyEnv +trimTidyEnv (occ_env, var_env) tcvs + = (trimTidyOccEnv occ_env (map getOccName tcvs), var_env) + --------------- -- | Grabs the free type variables, tidies them -- and then uses 'tidyType' to work over the type itself -tidyOpenTypes :: TidyEnv -> [Type] -> (TidyEnv, [Type]) -tidyOpenTypes env tys - = (env', tidyTypes inner_env tys) +tidyOpenTypesX :: TidyEnv -> [Type] -> (TidyEnv, [Type]) +tidyOpenTypesX env tys + = (env1, tidyTypes inner_env tys) where - free_tvs = tyCoVarsOfTypesWellScoped tys - (env'@(occ_env, var_env), _) = tidyOpenTyCoVars env free_tvs - trimmed_occ_env = trimTidyOccEnv occ_env (map getOccName free_tvs) - inner_env = (trimmed_occ_env, var_env) + free_tcvs :: [TyCoVar] -- Closed over kinds, scope-sorted + free_tcvs = tyCoVarsOfTypesWellScoped tys + (env1, free_tcvs') = tidyFreeTyCoVarsX env free_tcvs + inner_env = trimTidyEnv env1 free_tcvs' -- inner_env: see Note [Tidying open types] --------------- -tidyOpenType :: TidyEnv -> Type -> (TidyEnv, Type) -tidyOpenType env ty = let (env', [ty']) = tidyOpenTypes env [ty] in - (env', ty') +tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) +tidyOpenTypeX env ty + = (env1, tidyType inner_env ty) + where + free_tcvs = tyCoVarsOfTypeWellScoped ty + (env1, free_tcvs') = tidyFreeTyCoVarsX env free_tcvs + inner_env = trimTidyEnv env1 free_tcvs' + +--------------- +tidyOpenTypes :: TidyEnv -> [Type] -> [Type] +tidyOpenTypes env ty = snd (tidyOpenTypesX env ty) + +tidyOpenType :: TidyEnv -> Type -> Type +tidyOpenType env ty = snd (tidyOpenTypeX env ty) --------------- -- | Calls 'tidyType' on a top-level type (i.e. with an empty tidying environment) ===================================== compiler/GHC/Core/Type.hs ===================================== @@ -226,8 +226,10 @@ module GHC.Core.Type ( -- * Tidying type related things up for printing tidyType, tidyTypes, tidyOpenType, tidyOpenTypes, - tidyVarBndr, tidyVarBndrs, tidyFreeTyCoVars, - tidyOpenTyCoVar, tidyOpenTyCoVars, + tidyOpenTypeX, tidyOpenTypesX, + tidyVarBndr, tidyVarBndrs, + tidyFreeTyCoVars, + tidyFreeTyCoVarX, tidyFreeTyCoVarsX, tidyTyCoVarOcc, tidyTopType, tidyForAllTyBinder, tidyForAllTyBinders, ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -1758,7 +1758,7 @@ warnMissingSignatures gbl_env add_binding_warn id = when (not_ghc_generated name) $ do { env <- liftZonkM $ tcInitTidyEnv -- Why not use emptyTidyEnv? - ; let (_, ty) = tidyOpenType env (idType id) + ; let ty = tidyOpenType env (idType id) missing = MissingTopLevelBindingSig name ty diag = TcRnMissingSignature missing exported ; addDiagnosticAt (getSrcSpan name) diag } ===================================== compiler/GHC/Runtime/Debugger.hs ===================================== @@ -138,7 +138,7 @@ pprintClosureCommand bindThings force str = do -- It's OK to use nonDetEltsUniqSet here because initTidyOccEnv -- forgets the ordering immediately by creating an env , getUniqSet $ env_tvs `intersectVarSet` my_tvs) - return $ mapTermType (snd . tidyOpenType tidyEnv) t + return $ mapTermType (tidyOpenType tidyEnv) t -- | Give names, and bind in the interactive environment, to all the suspensions -- included (inductively) in a term ===================================== compiler/GHC/Runtime/Eval.hs ===================================== @@ -597,8 +597,8 @@ bindLocalsAtBreakpoint hsc_env apStack_fhv (Just ibi) = do let tv_subst = newTyVars us free_tvs (filtered_ids, occs'') = unzip -- again, sync the occ-names [ (id, occ) | (id, Just _hv, occ) <- zip3 ids mb_hValues occs' ] - (_,tidy_tys) = tidyOpenTypes emptyTidyEnv $ - map (substTy tv_subst . idType) filtered_ids + tidy_tys = tidyOpenTypes emptyTidyEnv $ + map (substTy tv_subst . idType) filtered_ids new_ids <- zipWith3M mkNewId occs'' tidy_tys filtered_ids result_name <- newInteractiveBinder hsc_env (mkVarOccFS result_fs) span ===================================== compiler/GHC/Tc/Errors/Ppr.hs ===================================== @@ -3393,7 +3393,7 @@ format_frr_err :: Type -- ^ the type which doesn't have a fixed runtime represe format_frr_err ty = (bullet <+> ppr tidy_ty <+> dcolon <+> ppr tidy_ki) where - (tidy_env, tidy_ty) = tidyOpenType emptyTidyEnv ty + (tidy_env, tidy_ty) = tidyOpenTypeX emptyTidyEnv ty tidy_ki = tidyType tidy_env (typeKind ty) pprField :: (FieldLabelString, TcType) -> SDoc ===================================== compiler/GHC/Tc/Gen/Bind.hs ===================================== @@ -59,7 +59,7 @@ import GHC.Core.Multiplicity import GHC.Core.FamInstEnv( normaliseType ) import GHC.Core.Class ( Class ) import GHC.Core.Coercion( mkSymCo ) -import GHC.Core.Type (mkStrLitTy, tidyOpenType, mkCastTy) +import GHC.Core.Type (mkStrLitTy, tidyOpenTypeX, mkCastTy) import GHC.Core.TyCo.Ppr( pprTyVars ) import GHC.Builtin.Types ( mkConstraintTupleTy, multiplicityTy, oneDataConTy ) @@ -1179,7 +1179,7 @@ localSigWarn id mb_sig warnMissingSignatures :: Id -> TcM () warnMissingSignatures id = do { env0 <- liftZonkM $ tcInitTidyEnv - ; let (env1, tidy_ty) = tidyOpenType env0 (idType id) + ; let (env1, tidy_ty) = tidyOpenTypeX env0 (idType id) ; let dia = TcRnPolymorphicBinderMissingSig (idName id) tidy_ty ; addDiagnosticTcM (env1, dia) } ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -1889,8 +1889,8 @@ solverDepthError loc ty do { ty <- TcM.zonkTcType ty ; env0 <- TcM.tcInitTidyEnv ; return (ty, env0) } - ; let tidy_env = tidyFreeTyCoVars env0 (tyCoVarsOfTypeList ty) - tidy_ty = tidyType tidy_env ty + ; let tidy_env = tidyFreeTyCoVars env0 (tyCoVarsOfTypeList ty) + tidy_ty = tidyType tidy_env ty msg = TcRnSolverDepthError tidy_ty depth ; TcM.failWithTcM (tidy_env, msg) } where ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -392,7 +392,8 @@ pprSigSkolInfo :: UserTypeCtxt -> TcType -> SDoc -- The type is already tidied pprSigSkolInfo ctxt ty = case ctxt of - FunSigCtxt f _ -> vcat [ text "the type signature for:" + FunSigCtxt f _ -> pprTrace "ppse" (ppr (tyCoVarsOfType ty)) $ + vcat [ text "the type signature for:" , nest 2 (pprPrefixOcc f <+> dcolon <+> ppr ty) ] PatSynCtxt {} -> pprUserTypeCtxt ctxt -- See Note [Skolem info for pattern synonyms] _ -> vcat [ pprUserTypeCtxt ctxt <> colon ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -1914,7 +1914,8 @@ defaultTyVar def_strat tv ; liftZonkM $ writeMetaTyVar kv liftedTypeKind ; return True } | otherwise - = do { addErr $ TcRnCannotDefaultKindVar kv' (tyVarKind kv') + = do { let (tidy_env, kv') = tidyFreeTyCoVarX emptyTidyEnv kv + ; addErrTcM $ (tidy_env, TcRnCannotDefaultKindVar kv' (tyVarKind kv')) -- We failed to default it, so return False to say so. -- Hence, it'll get skolemised. That might seem odd, but we must either -- promote, skolemise, or zap-to-Any, to satisfy GHC.Tc.Gen.HsType @@ -1923,8 +1924,6 @@ defaultTyVar def_strat tv -- because we are in an error situation anyway. ; return False } - where - (_, kv') = tidyOpenTyCoVar emptyTidyEnv kv -- | Default some unconstrained type variables, as specified -- by the defaulting options: @@ -2130,7 +2129,7 @@ doNotQuantifyTyVars dvs where_found -- are OK ; let leftover_metas = filter isMetaTyVar undefaulted ; unless (null leftover_metas) $ - do { let (tidy_env1, tidied_tvs) = tidyOpenTyCoVars emptyTidyEnv leftover_metas + do { let (tidy_env1, tidied_tvs) = tidyFreeTyCoVarsX emptyTidyEnv leftover_metas ; (tidy_env2, where_doc) <- liftZonkM $ where_found tidy_env1 ; let msg = TcRnUninferrableTyVar tidied_tvs where_doc ; failWithTcM (tidy_env2, msg) } ===================================== compiler/GHC/Tc/Validity.hs ===================================== @@ -290,7 +290,7 @@ checkUserTypeError ctxt ty | Just msg <- deepUserTypeError_maybe ty = do { env0 <- liftZonkM tcInitTidyEnv - ; let (env1, tidy_msg) = tidyOpenType env0 msg + ; let (env1, tidy_msg) = tidyOpenTypeX env0 msg ; failWithTcM (env1, TcRnUserTypeError tidy_msg) } | otherwise = return () @@ -793,7 +793,9 @@ check_type ve@(ValidityEnv{ ve_tidy_env = env , ve_rank = rank, ve_expand = expand }) ty | not (null tvbs && null theta) = do { traceTc "check_type" (ppr ty $$ ppr rank) - ; checkTcM (forAllAllowed rank) (env, TcRnForAllRankErr rank (tidyType env ty)) + ; checkTcM (forAllAllowed rank) $ + let (env1, tidy_ty) = tidyOpenTypeX env ty + in (env1, TcRnForAllRankErr rank tidy_ty) -- Reject e.g. (Maybe (?x::Int => Int)), -- with a decent error message ===================================== compiler/GHC/Tc/Zonk/TcType.hs ===================================== @@ -560,12 +560,11 @@ tcInitTidyEnv tcInitOpenTidyEnv :: [TyCoVar] -> ZonkM TidyEnv tcInitOpenTidyEnv tvs = do { env1 <- tcInitTidyEnv - ; let env2 = tidyFreeTyCoVars env1 tvs - ; return env2 } + ; return (tidyFreeTyCoVars env1 tvs) } zonkTidyTcType :: TidyEnv -> TcType -> ZonkM (TidyEnv, TcType) zonkTidyTcType env ty = do { ty' <- zonkTcType ty - ; return (tidyOpenType env ty') } + ; return (tidyOpenTypeX env ty') } zonkTidyTcTypes :: TidyEnv -> [TcType] -> ZonkM (TidyEnv, [TcType]) zonkTidyTcTypes = zonkTidyTcTypes' [] @@ -642,7 +641,7 @@ zonkTidyFRRInfos = go [] go_mb_not_conc env Nothing = return (env, Nothing) go_mb_not_conc env (Just (tv, ty)) - = do { (env, tv) <- return $ tidyOpenTyCoVar env tv + = do { (env, tv) <- return $ tidyFreeTyCoVarX env tv ; (env, ty) <- zonkTidyTcType env ty ; return (env, Just (tv, ty)) } @@ -654,12 +653,12 @@ tidyCt env = updCtEvidence (tidyCtEvidence env) tidyCtEvidence :: TidyEnv -> CtEvidence -> CtEvidence -- NB: we do not tidy the ctev_evar field because we don't -- show it in error messages -tidyCtEvidence env ctev = ctev { ctev_pred = tidyType env ty } +tidyCtEvidence env ctev = ctev { ctev_pred = tidyOpenType env ty } where ty = ctev_pred ctev tidyHole :: TidyEnv -> Hole -> Hole -tidyHole env h@(Hole { hole_ty = ty }) = h { hole_ty = tidyType env ty } +tidyHole env h@(Hole { hole_ty = ty }) = h { hole_ty = tidyOpenType env ty } tidyDelayedError :: TidyEnv -> DelayedError -> DelayedError tidyDelayedError env (DE_Hole hole) ===================================== testsuite/tests/typecheck/should_compile/tc214.stderr ===================================== @@ -6,9 +6,9 @@ tc214.hs:19:7: warning: [GHC-40564] [-Winaccessible-code (in -Wdefault)] • Inaccessible code in a pattern with constructor: F2 :: forall a. a -> Foo2 [a], in an equation for ‘bar2’ - Couldn't match type ‘a’ with ‘forall a. a’ + Couldn't match type ‘a’ with ‘forall a1. a1’ Cannot equate type variable ‘a’ - with a type involving polytypes: forall a. a + with a type involving polytypes: forall a1. a1 ‘a’ is a rigid type variable bound by a pattern with constructor: F2 :: forall a. a -> Foo2 [a], in an equation for ‘bar2’ ===================================== testsuite/tests/typecheck/should_fail/T10709.stderr ===================================== @@ -14,22 +14,26 @@ T10709.hs:6:21: error: [GHC-91028] x1 :: a2 -> IO [a3] (bound at T10709.hs:6:1) T10709.hs:7:22: error: [GHC-91028] - • Couldn't match type ‘a1’ with ‘(forall a. IO a -> IO a) -> IO a’ + • Couldn't match type ‘a1’ + with ‘(forall a2. IO a2 -> IO a2) -> IO a’ Expected: a1 -> IO a - Actual: ((forall a. IO a -> IO a) -> IO a) -> IO a + Actual: ((forall a1. IO a1 -> IO a1) -> IO a) -> IO a Cannot instantiate unification variable ‘a1’ - with a type involving polytypes: (forall a. IO a -> IO a) -> IO a + with a type involving polytypes: + (forall a2. IO a2 -> IO a2) -> IO a • In the second argument of ‘(.)’, namely ‘mask’ In the expression: (replicateM 2 . mask) undefined In an equation for ‘x2’: x2 = (replicateM 2 . mask) undefined • Relevant bindings include x2 :: IO [a] (bound at T10709.hs:7:1) T10709.hs:8:22: error: [GHC-91028] - • Couldn't match type ‘a0’ with ‘(forall a. IO a -> IO a) -> IO a’ + • Couldn't match type ‘a0’ + with ‘(forall a1. IO a1 -> IO a1) -> IO a’ Expected: a0 -> IO a - Actual: ((forall a. IO a -> IO a) -> IO a) -> IO a + Actual: ((forall a1. IO a1 -> IO a1) -> IO a) -> IO a Cannot instantiate unification variable ‘a0’ - with a type involving polytypes: (forall a. IO a -> IO a) -> IO a + with a type involving polytypes: + (forall a1. IO a1 -> IO a1) -> IO a • In the second argument of ‘(.)’, namely ‘mask’ In the first argument of ‘($)’, namely ‘(replicateM 2 . mask)’ In the expression: (replicateM 2 . mask) $ undefined ===================================== testsuite/tests/typecheck/should_fail/T10709b.stderr ===================================== @@ -12,7 +12,7 @@ T10709b.hs:6:22: error: [GHC-91028] T10709b.hs:7:22: error: [GHC-91028] • Couldn't match type ‘t1’ with ‘forall a. IO a -> IO a’ Expected: (t1 -> IO a) -> IO a - Actual: ((forall a. IO a -> IO a) -> IO a) -> IO a + Actual: ((forall a1. IO a1 -> IO a1) -> IO a) -> IO a Cannot instantiate unification variable ‘t1’ with a type involving polytypes: forall a. IO a -> IO a • In the second argument of ‘(.)’, namely ‘mask’ @@ -23,7 +23,7 @@ T10709b.hs:7:22: error: [GHC-91028] T10709b.hs:8:22: error: [GHC-91028] • Couldn't match type ‘t0’ with ‘forall a. IO a -> IO a’ Expected: (t0 -> IO a) -> IO a - Actual: ((forall a. IO a -> IO a) -> IO a) -> IO a + Actual: ((forall a1. IO a1 -> IO a1) -> IO a) -> IO a Cannot instantiate unification variable ‘t0’ with a type involving polytypes: forall a. IO a -> IO a • In the second argument of ‘(.)’, namely ‘mask’ @@ -34,7 +34,7 @@ T10709b.hs:8:22: error: [GHC-91028] T10709b.hs:9:22: error: [GHC-91028] • Couldn't match type ‘b0’ with ‘forall a. IO a -> IO a’ Expected: (b0 -> IO a) -> IO a - Actual: ((forall a. IO a -> IO a) -> IO a) -> IO a + Actual: ((forall a1. IO a1 -> IO a1) -> IO a) -> IO a Cannot instantiate unification variable ‘b0’ with a type involving polytypes: forall a. IO a -> IO a • In the second argument of ‘(.)’, namely ‘mask’ @@ -45,7 +45,7 @@ T10709b.hs:9:22: error: [GHC-91028] T10709b.hs:10:22: error: [GHC-91028] • Couldn't match type ‘a0’ with ‘forall a. IO a -> IO a’ Expected: (a0 -> IO a) -> IO a - Actual: ((forall a. IO a -> IO a) -> IO a) -> IO a + Actual: ((forall a1. IO a1 -> IO a1) -> IO a) -> IO a Cannot instantiate unification variable ‘a0’ with a type involving polytypes: forall a. IO a -> IO a • In the second argument of ‘(.)’, namely ‘mask’ ===================================== testsuite/tests/typecheck/should_fail/T13909.stderr ===================================== @@ -2,7 +2,7 @@ T13909.hs:11:18: error: [GHC-91028] • Expecting two more arguments to ‘Hm’ Expected kind ‘k’, but ‘Hm’ has kind ‘forall k -> k -> *’ Cannot equate type variable ‘k’ - with a kind involving polytypes: forall k -> k -> * + with a kind involving polytypes: forall k1 -> k1 -> * ‘k’ is a rigid type variable bound by an instance declaration at T13909.hs:11:10-19 ===================================== testsuite/tests/typecheck/should_fail/tcfail201.stderr ===================================== @@ -3,7 +3,7 @@ tcfail201.hs:17:27: error: [GHC-25897] ‘a’ is a rigid type variable bound by the type signature for: gfoldl' :: forall (c :: * -> *) a. - (forall a b. c (a -> b) -> a -> c b) + (forall a1 b. c (a1 -> b) -> a1 -> c b) -> (forall g. g -> c g) -> a -> c a at tcfail201.hs:15:1-85 • In the pattern: DocEmpty @@ -11,7 +11,7 @@ tcfail201.hs:17:27: error: [GHC-25897] In the expression: case hsDoc of DocEmpty -> z DocEmpty • Relevant bindings include hsDoc :: a (bound at tcfail201.hs:16:13) - gfoldl' :: (forall a b. c (a -> b) -> a -> c b) + gfoldl' :: (forall a1 b. c (a1 -> b) -> a1 -> c b) -> (forall g. g -> c g) -> a -> c a (bound at tcfail201.hs:16:1) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f2e10a2ca9132a1670256a1ca9ab6eb2d1177e50 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f2e10a2ca9132a1670256a1ca9ab6eb2d1177e50 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 17:56:52 2024 From: gitlab at gitlab.haskell.org (Torsten Schmits (@torsten.schmits)) Date: Wed, 05 Jun 2024 13:56:52 -0400 Subject: [Git][ghc/ghc][wip/torsten.schmits/cross-package-objects] make type env available to hydrator Message-ID: <6660a6e46d271_2869934bb2a4159452@gitlab.mail> Torsten Schmits pushed to branch wip/torsten.schmits/cross-package-objects at Glasgow Haskell Compiler / GHC Commits: b7451e99 by Torsten Schmits at 2024-06-05T19:56:36+02:00 make type env available to hydrator - - - - - 5 changed files: - compiler/GHC/Driver/Main.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Linker/Loader.hs - testsuite/tests/th/cross-package/CrossDep.hs - testsuite/tests/th/cross-package/CrossLocal.hs Changes: ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -161,7 +161,7 @@ import GHC.StgToJS.Ids import GHC.StgToJS.Types import GHC.JS.Syntax -import GHC.IfaceToCore ( typecheckIface, typecheckWholeCoreBindings ) +import GHC.IfaceToCore ( typecheckIface, typecheckWholeCoreBindings, tcIfaceDecls ) import GHC.Iface.Load ( ifaceStats, writeIface, flagsToIfCompression ) import GHC.Iface.Make @@ -1004,6 +1004,20 @@ initWholeCoreBindings hsc_env mod_iface details (LM utc_time this_mod uls) = LM generateByteCode hsc_env cgi_guts (wcb_mod_location fi)) go ul = return ul +hydrateOpaqueMinimal :: HscEnv -> ModIface -> Linkable -> IO Linkable +hydrateOpaqueMinimal hsc_env mod_iface linkable = do + names_w_things <- initIfaceCheck (text "hydrate") hsc_env $ + initIfaceLcl (mi_semantic_module mod_iface) (text "typecheckIface") (mi_boot mod_iface) $ + tcIfaceDecls False (mi_decls mod_iface) + let type_env = mkNameEnv names_w_things + det = emptyModDetails {md_types = type_env} + initWholeCoreBindings hsc_env mod_iface det linkable + +hydrateOpaque :: HscEnv -> ModIface -> Linkable -> IO Linkable +hydrateOpaque hsc_env mod_iface linkable = do + det <- initModDetails hsc_env mod_iface + initWholeCoreBindings hsc_env mod_iface det linkable + {- Note [ModDetails and --make mode] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -2676,7 +2690,7 @@ hscCompileCoreExpr' hsc_env srcspan ds_expr = do [] Nothing {- load it -} - (fv_hvs, mods_needed, units_needed) <- loadDecls interp hsc_env (initWholeCoreBindings hsc_env) srcspan bcos + (fv_hvs, mods_needed, units_needed) <- loadDecls interp hsc_env (hydrateOpaque hsc_env) srcspan bcos {- Get the HValue for the root -} return (expectJust "hscCompileCoreExpr'" $ lookup (idName binding_id) fv_hvs, mods_needed, units_needed) ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -515,14 +515,7 @@ loadInterface doc_str mod from ; new_eps_anns <- tcIfaceAnnotations (mi_anns iface) ; new_eps_complete_matches <- tcIfaceCompleteMatches (mi_complete_matches iface) - ; let { final_iface = iface { - mi_decls = panic "No mi_decls in PIT", - mi_insts = panic "No mi_insts in PIT", - mi_fam_insts = panic "No mi_fam_insts in PIT", - mi_rules = panic "No mi_rules in PIT", - mi_anns = panic "No mi_anns in PIT" - } - } + ; let final_iface = iface ; let bad_boot = mi_boot iface == IsBoot && isJust (lookupKnotVars (if_rec_types gbl_env) mod) ===================================== compiler/GHC/Linker/Loader.hs ===================================== @@ -111,7 +111,7 @@ import System.Win32.Info (getSystemDirectory) import GHC.Utils.Exception import GHC.Unit.Module.ModIface (ModIface, ModIface_ (..)) -import GHC.Unit.Module.ModDetails (ModDetails (..), emptyModDetails) +import GHC.Unit.Module.ModDetails (ModDetails (..)) import GHC.Unit.Finder (FindResult(..), findImportedModule) import qualified GHC.Data.Maybe as ME import GHC.Unit.Module.ModSummary (ModSummary(..)) @@ -229,7 +229,7 @@ loadDependencies :: Interp -> HscEnv -> LoaderState - -> (ModIface -> ModDetails -> Linkable -> IO Linkable) + -> (ModIface -> Linkable -> IO Linkable) -> SrcSpan -> [Module] -> IO (LoaderState, SuccessFlag, [Linkable], PkgsLoaded) -- ^ returns the set of linkables required @@ -728,32 +728,27 @@ loadByteCode loc iface mod_sum = do loadIfaceByteCode :: Interp -> HscEnv -> - (ModIface -> ModDetails -> Linkable -> IO Linkable) -> + (ModIface -> Linkable -> IO Linkable) -> LoaderState -> Module -> IO ([Linkable], LoaderState) loadIfaceByteCode interp hsc_env hydrate pls mod = do - mb_iface <- run_ifg $ loadInterface (text "blarkh") mod (ImportByUser NotBoot) + iface <- run_ifg $ loadSysInterface (text "blarkh") mod imp_mod <- findImportedModule hsc_env (moduleName mod) (OtherPkg (moduleUnitId mod)) - let pprI = - case mb_iface of - ME.Succeeded iface -> ppr (mi_module iface) - ME.Failed _ -> text "missing" dbg "loadIfaceByteCode" [ ("mod", ppr mod), - ("iface", ppr pprI) + ("iface", ppr (mi_module iface)) ] - case (imp_mod, mb_iface) of - (Found loc _, ME.Succeeded iface) -> do - let det = emptyModDetails + case imp_mod of + (Found loc _) -> do summ <- mod_summary mod loc iface l <- loadByteCode loc iface summ - lh <- maybeToList <$> traverse (hydrate iface det) l - dbg "loadIfaceByteCode found" [("loc", ppr loc), ("loaded", ppr lh)] + lh <- maybeToList <$> traverse (hydrate iface) l + dbg "loadIfaceByteCode found" [("hi", text (ml_hi_file loc)), ("loaded", ppr lh)] pls1 <- dynLinkBCOs interp pls lh pure (lh, pls1) - (fr, _) -> do - dbg "loadIfaceByteCode not found" [("result", pprI), ("impo", debugFr fr)] + fr -> do + dbg "loadIfaceByteCode not found" [("impo", debugFr fr)] pure ([], pls) where run_ifg :: forall a . IfG a -> IO a @@ -774,7 +769,7 @@ loadIfaceByteCode interp hsc_env hydrate pls mod = do loadIfacesByteCode :: Interp -> HscEnv -> - (ModIface -> ModDetails -> Linkable -> IO Linkable) -> + (ModIface -> Linkable -> IO Linkable) -> LoaderState -> [Linkable] -> IO (LoaderState, [Linkable]) @@ -803,7 +798,7 @@ loadIfacesByteCode interp hsc_env hydrate pls lnks = do loadDecls :: Interp -> HscEnv -> - (ModIface -> ModDetails -> Linkable -> IO Linkable) -> + (ModIface -> Linkable -> IO Linkable) -> SrcSpan -> CompiledByteCode -> IO ([(Name, ForeignHValue)], [Linkable], PkgsLoaded) ===================================== testsuite/tests/th/cross-package/CrossDep.hs ===================================== @@ -1,4 +1,6 @@ module CrossDep where -dep :: Int -dep = 9681 +data A = A Int + +dep :: A +dep = A 9681 ===================================== testsuite/tests/th/cross-package/CrossLocal.hs ===================================== @@ -5,8 +5,10 @@ module CrossLocal where import Language.Haskell.TH (ExpQ) import Language.Haskell.TH.Syntax (lift) -- just to be sure that the file isn't accidentally picked up locally -import "dep" CrossDep (dep) +import "dep" CrossDep (dep, A (A)) import CrossNum (num) splc :: ExpQ -splc = lift @_ @Int (num + dep) +splc = lift @_ @Int (num + d) + where + A d = dep View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b7451e99f56251adc8ab94fc30f5687ad56f4456 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b7451e99f56251adc8ab94fc30f5687ad56f4456 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 19:17:55 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 05 Jun 2024 15:17:55 -0400 Subject: [Git][ghc/ghc][master] Add firstA and secondA to Data.Bitraversable Message-ID: <6660b9e35bd95_286993eee7f816630@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 6 changed files: - libraries/base/changelog.md - libraries/base/src/Data/Bitraversable.hs - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 Changes: ===================================== libraries/base/changelog.md ===================================== @@ -6,6 +6,7 @@ * The `HasField` class now supports representation polymorphism ([CLC proposal #194](https://github.com/haskell/core-libraries-committee/issues/194)) * Make `read` accept binary integer notation ([CLC proposal #177](https://github.com/haskell/core-libraries-committee/issues/177)) * Improve the performance of `Data.List.sort` using an improved merging strategy. Instead of `compare`, `sort` now uses `(>)` which may break *malformed* `Ord` instances ([CLC proposal #236](https://github.com/haskell/core-libraries-committee/issues/236)) + * Add `firstA` and `secondA` to `Data.Bitraversable`. ([CLC proposal #172](https://github.com/haskell/core-libraries-committee/issues/172)) ## 4.20.0.0 *TBA* * Deprecate `GHC.Pack` ([#21461](https://gitlab.haskell.org/ghc/ghc/-/issues/21461)) ===================================== libraries/base/src/Data/Bitraversable.hs ===================================== @@ -18,6 +18,8 @@ module Data.Bitraversable , bisequenceA , bisequence , bimapM + , firstA + , secondA , bifor , biforM , bimapAccumL @@ -172,6 +174,60 @@ bimapM = bitraverse bisequence :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b) bisequence = bitraverse id id +-- | Traverses only over the first argument. +-- +-- @'firstA' f ≡ 'bitraverse' f 'pure'@ + +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> firstA listToMaybe (Left []) +-- Nothing +-- +-- >>> firstA listToMaybe (Left [1, 2, 3]) +-- Just (Left 1) +-- +-- >>> firstA listToMaybe (Right [4, 5]) +-- Just (Right [4, 5]) +-- +-- >>> firstA listToMaybe ([1, 2, 3], [4, 5]) +-- Just (1,[4, 5]) +-- +-- >>> firstA listToMaybe ([], [4, 5]) +-- Nothing + +-- @since 4.21.0.0 +firstA :: Bitraversable t => Applicative f => (a -> f c) -> t a b -> f (t c b) +firstA f = bitraverse f pure + +-- | Traverses only over the second argument. +-- +-- @'secondA' f ≡ 'bitraverse' 'pure' f@ +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> secondA (find odd) (Left []) +-- Just (Left []) +-- +-- >>> secondA (find odd) (Left [1, 2, 3]) +-- Just (Left [1,2,3]) +-- +-- >>> secondA (find odd) (Right [4, 5]) +-- Just (Right 5) +-- +-- >>> secondA (find odd) ([1, 2, 3], [4, 5]) +-- Just ([1,2,3],5) +-- +-- >>> secondA (find odd) ([1,2,3], [4]) +-- Nothing +-- +-- @since 4.21.0.0 +secondA :: Bitraversable t => Applicative f => (b -> f c) -> t a b -> f (t a c) +secondA f = bitraverse pure f + -- | Class laws for tuples hold only up to laziness. The -- Bitraversable methods are lazier than their Traversable counterparts. -- For example the law @'bitraverse' 'pure' ≡ 'traverse'@ does ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -679,6 +679,8 @@ module Data.Bitraversable where bimapM :: forall (t :: * -> * -> *) (f :: * -> *) a c b d. (Bitraversable t, GHC.Internal.Base.Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d) bisequence :: forall (t :: * -> * -> *) (f :: * -> *) a b. (Bitraversable t, GHC.Internal.Base.Applicative f) => t (f a) (f b) -> f (t a b) bisequenceA :: forall (t :: * -> * -> *) (f :: * -> *) a b. (Bitraversable t, GHC.Internal.Base.Applicative f) => t (f a) (f b) -> f (t a b) + firstA :: forall (t :: * -> * -> *) (f :: * -> *) a c b. (Bitraversable t, GHC.Internal.Base.Applicative f) => (a -> f c) -> t a b -> f (t c b) + secondA :: forall (t :: * -> * -> *) (f :: * -> *) b c a. (Bitraversable t, GHC.Internal.Base.Applicative f) => (b -> f c) -> t a b -> f (t a c) module Data.Bits where -- Safety: Safe ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -679,6 +679,8 @@ module Data.Bitraversable where bimapM :: forall (t :: * -> * -> *) (f :: * -> *) a c b d. (Bitraversable t, GHC.Internal.Base.Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d) bisequence :: forall (t :: * -> * -> *) (f :: * -> *) a b. (Bitraversable t, GHC.Internal.Base.Applicative f) => t (f a) (f b) -> f (t a b) bisequenceA :: forall (t :: * -> * -> *) (f :: * -> *) a b. (Bitraversable t, GHC.Internal.Base.Applicative f) => t (f a) (f b) -> f (t a b) + firstA :: forall (t :: * -> * -> *) (f :: * -> *) a c b. (Bitraversable t, GHC.Internal.Base.Applicative f) => (a -> f c) -> t a b -> f (t c b) + secondA :: forall (t :: * -> * -> *) (f :: * -> *) b c a. (Bitraversable t, GHC.Internal.Base.Applicative f) => (b -> f c) -> t a b -> f (t a c) module Data.Bits where -- Safety: Safe ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -679,6 +679,8 @@ module Data.Bitraversable where bimapM :: forall (t :: * -> * -> *) (f :: * -> *) a c b d. (Bitraversable t, GHC.Internal.Base.Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d) bisequence :: forall (t :: * -> * -> *) (f :: * -> *) a b. (Bitraversable t, GHC.Internal.Base.Applicative f) => t (f a) (f b) -> f (t a b) bisequenceA :: forall (t :: * -> * -> *) (f :: * -> *) a b. (Bitraversable t, GHC.Internal.Base.Applicative f) => t (f a) (f b) -> f (t a b) + firstA :: forall (t :: * -> * -> *) (f :: * -> *) a c b. (Bitraversable t, GHC.Internal.Base.Applicative f) => (a -> f c) -> t a b -> f (t c b) + secondA :: forall (t :: * -> * -> *) (f :: * -> *) b c a. (Bitraversable t, GHC.Internal.Base.Applicative f) => (b -> f c) -> t a b -> f (t a c) module Data.Bits where -- Safety: Safe ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -679,6 +679,8 @@ module Data.Bitraversable where bimapM :: forall (t :: * -> * -> *) (f :: * -> *) a c b d. (Bitraversable t, GHC.Internal.Base.Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d) bisequence :: forall (t :: * -> * -> *) (f :: * -> *) a b. (Bitraversable t, GHC.Internal.Base.Applicative f) => t (f a) (f b) -> f (t a b) bisequenceA :: forall (t :: * -> * -> *) (f :: * -> *) a b. (Bitraversable t, GHC.Internal.Base.Applicative f) => t (f a) (f b) -> f (t a b) + firstA :: forall (t :: * -> * -> *) (f :: * -> *) a c b. (Bitraversable t, GHC.Internal.Base.Applicative f) => (a -> f c) -> t a b -> f (t c b) + secondA :: forall (t :: * -> * -> *) (f :: * -> *) b c a. (Bitraversable t, GHC.Internal.Base.Applicative f) => (b -> f c) -> t a b -> f (t a c) module Data.Bits where -- Safety: Safe View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7c173310a82e796d0be262c629c9048becd50d50 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7c173310a82e796d0be262c629c9048becd50d50 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 19:18:35 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 05 Jun 2024 15:18:35 -0400 Subject: [Git][ghc/ghc][master] base: Fix name of changelog Message-ID: <6660ba0b8462e_2869940b6b8017166c@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1 changed file: - libraries/base/base.cabal Changes: ===================================== libraries/base/base.cabal ===================================== @@ -19,8 +19,8 @@ description: Haskell's base library provides, among other things, core types [Set](https://hackage.haskell.org/package/containers/docs/Data-Set.html) are available in the [containers](https://hackage.haskell.org/package/containers) library. To work with textual data, use the [text](https://hackage.haskell.org/package/text/docs/Data-Text.html) library. -extra-source-files: - CHANGELOG.md +extra-doc-files: + changelog.md Library default-language: Haskell2010 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3b6f9fd15f0fae8cc4c4c1bff5006397903f8580 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3b6f9fd15f0fae8cc4c4c1bff5006397903f8580 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 19:19:19 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 05 Jun 2024 15:19:19 -0400 Subject: [Git][ghc/ghc][master] Announce Or-patterns in the release notes for GHC 9.12 (#22596) Message-ID: <6660ba379a237_286994200e64174970@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 1 changed file: - docs/users_guide/9.12.1-notes.rst Changes: ===================================== docs/users_guide/9.12.1-notes.rst ===================================== @@ -11,6 +11,8 @@ for specific guidance on migrating programs to this release. Language ~~~~~~~~ +- New language extension: :extension:`OrPatterns` implements `GHC Proposal #522 + `_). - The ordering of variables used for visible type application has been changed in two cases. It is supposed to be left-to-right, but due to an oversight, it was wrong: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1f4d2ef7f080535f9cc7af08edb5e12c62ce9509 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1f4d2ef7f080535f9cc7af08edb5e12c62ce9509 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 21:33:07 2024 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Wed, 05 Jun 2024 17:33:07 -0400 Subject: [Git][ghc/ghc][wip/andreask/bytecode_tagging] GHCi interpreter: Tag constructor closures when possible. Message-ID: <6660d9935cd44_28699539c45c1870a2@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/bytecode_tagging at Glasgow Haskell Compiler / GHC Commits: 3c487956 by Andreas Klebinger at 2024-06-05T23:32:30+02:00 GHCi interpreter: Tag constructor closures when possible. When evaluating PUSH_G try to tag the reference we are pushing if it's a constructor or function. This is potentially helpful for performance and required to fix #24870. - - - - - 7 changed files: - compiler/GHC/ByteCode/Instr.hs - rts/Interpreter.c - + testsuite/tests/th/should_compile/T24870/Def.hs - + testsuite/tests/th/should_compile/T24870/T24870.stderr - + testsuite/tests/th/should_compile/T24870/T24870.stderr-mingw32 - + testsuite/tests/th/should_compile/T24870/Use.hs - + testsuite/tests/th/should_compile/T24870/all.T Changes: ===================================== compiler/GHC/ByteCode/Instr.hs ===================================== @@ -83,7 +83,7 @@ data BCInstr | PUSH16_W !ByteOff | PUSH32_W !ByteOff - -- Push a ptr (these all map to PUSH_G really) + -- Push a (heap) ptr (these all map to PUSH_G really) | PUSH_G Name | PUSH_PRIMOP PrimOp | PUSH_BCO (ProtoBCO Name) ===================================== rts/Interpreter.c ===================================== @@ -4,6 +4,30 @@ * Copyright (c) The GHC Team, 1994-2002. * ---------------------------------------------------------------------------*/ +/* +Note [CBV Functions and the interpreter] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +When the byte code interpreter loads a reference to a value it often +ends up as a non-tagged pointers *especially* if we already know a value +is a certain constructor and therefore don't perform an eval on the reference. +This causes friction with CBV functions which assume +their value arguments are properly tagged by the caller. + +In order to ensure CBV functions still get passed tagged functions we have +three options: +a) Special case the interpreter behaviour into the tag inference analysis. + If we assume the interpreter can't properly tag value references the STG passes + would then wrap such calls in appropriate evals which are executed at runtime. + This would ensure tags by doing additional evals at runtime. +b) When the interpreter pushes references for known constructors instead of + pushing the objects address add the tag to the value pushed. This is what + the NCG backends do. +c) When the interpreter pushes a reference inspect the closure of the object + and apply the appropriate tag at runtime. + +For now we use approach c). Mostly because it's easiest to implement. We also don't +tag functions as tag inference currently doesn't rely on those being properly tagged. +*/ #include "rts/PosixSource.h" #include "Rts.h" @@ -292,6 +316,18 @@ STATIC_INLINE StgClosure *tagConstr(StgClosure *con) { return TAG_CLOSURE(stg_min(TAG_MASK, 1 + GET_TAG(con)), con); } +// Compute the pointer tag for the function and tag the pointer; +STATIC_INLINE StgClosure *tagFun(StgClosure *fun) { + StgHalfWord tag = GET_TAG(fun); + if(tag > TAG_MASK) { return fun; } + else { + return TAG_CLOSURE(tag, fun); + } + + +} + + static StgWord app_ptrs_itbl[] = { (W_)&stg_ap_p_info, (W_)&stg_ap_pp_info, @@ -1306,7 +1342,52 @@ run_BCO: case bci_PUSH_G: { W_ o1 = BCO_GET_LARGE_ARG; - SpW(-1) = BCO_PTR(o1); + StgClosure *tagged_obj = (StgClosure*) BCO_PTR(o1); + + tag_push_g: + ASSERT(LOOKS_LIKE_CLOSURE_PTR((StgClosure*) tagged_obj)); + // Here we make sure references we push are tagged. + // See Note [CBV Functions and the interpreter] in Info.hs + + //Safe some memory reads if we already have a tag. + if(GET_CLOSURE_TAG(tagged_obj) == 0) { + StgClosure *obj = UNTAG_CLOSURE(tagged_obj); + switch ( get_itbl(obj)->type ) { + case IND: + case IND_STATIC: + { + tagged_obj = ACQUIRE_LOAD(&((StgInd*)obj)->indirectee); + goto tag_push_g; + } + case CONSTR: + case CONSTR_1_0: + case CONSTR_0_1: + case CONSTR_2_0: + case CONSTR_1_1: + case CONSTR_0_2: + case CONSTR_NOCAF: + // The value is already evaluated, so we can just return it. However, + // before we do, we MUST ensure that the pointer is tagged, because we + // might return to a native `case` expression, which assumes the returned + // pointer is tagged so it can use the tag to select an alternative. + tagged_obj = tagConstr(obj); + break; + case FUN: + case FUN_1_0: + case FUN_0_1: + case FUN_2_0: + case FUN_1_1: + case FUN_0_2: + case FUN_STATIC: + // Purely for performance since we already hit memory anyway. + tagged_obj = tagFun(obj); + break; + default: + break; + } + } + + SpW(-1) = (W_) tagged_obj; Sp_subW(1); goto nextInsn; } ===================================== testsuite/tests/th/should_compile/T24870/Def.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE TemplateHaskell #-} + +module SDef where + +{-# NOINLINE aValue #-} +aValue = True + +{-# NOINLINE aStrictFunction #-} +aStrictFunction !x = [| x |] ===================================== testsuite/tests/th/should_compile/T24870/T24870.stderr ===================================== @@ -0,0 +1,2 @@ +[1 of 2] Compiling SDef ( Def.hs, Def.o, Def.dyn_o ) +[2 of 2] Compiling SUse ( Use.hs, Use.o ) ===================================== testsuite/tests/th/should_compile/T24870/T24870.stderr-mingw32 ===================================== @@ -0,0 +1,2 @@ +[1 of 2] Compiling SDef ( Def.hs, Def.o ) +[2 of 2] Compiling SUse ( Use.hs, Use.o ) ===================================== testsuite/tests/th/should_compile/T24870/Use.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE TemplateHaskell #-} + +module SUse where + +import qualified Language.Haskell.TH.Syntax as TH +import SDef +import GHC.Exts + +bar = $( inline aStrictFunction aValue ) ===================================== testsuite/tests/th/should_compile/T24870/all.T ===================================== @@ -0,0 +1,6 @@ +# The interpreter must uphold tagging invariants, and failed to do so in #24870 +# We test this here by having the interpreter calls a strict worker function +# with a reference to a value it constructed. +# See also Note [CBV Functions and the interpreter] +test('T24870', [extra_files(['Def.hs', 'Use.hs']), req_th], + multimod_compile, ['Def Use', '-dtag-inference-checks']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3c48795654f7ea643b5a90b7de9db87b8d044f51 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3c48795654f7ea643b5a90b7de9db87b8d044f51 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 5 22:08:25 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Wed, 05 Jun 2024 18:08:25 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/fix-small-addr-space Message-ID: <6660e1d9eb4fe_1852392ff8c8404db@gitlab.mail> Cheng Shao pushed new branch wip/fix-small-addr-space at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-small-addr-space You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 02:42:59 2024 From: gitlab at gitlab.haskell.org (=?UTF-8?B?SmFrb2IgQnLDvG5rZXIgKEBKYWtvYkJydWVua2VyKQ==?=) Date: Wed, 05 Jun 2024 22:42:59 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/jakobbruenker/T24909 Message-ID: <66612233dea69_1852392186dc846017@gitlab.mail> Jakob Brünker pushed new branch wip/jakobbruenker/T24909 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/jakobbruenker/T24909 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 03:14:18 2024 From: gitlab at gitlab.haskell.org (=?UTF-8?B?SmFrb2IgQnLDvG5rZXIgKEBKYWtvYkJydWVua2VyKQ==?=) Date: Wed, 05 Jun 2024 23:14:18 -0400 Subject: [Git][ghc/ghc][wip/jakobbruenker/T24909] docs: Update mention of ($) type in user guide Message-ID: <6661298a6985d_185239268e3845166f@gitlab.mail> Jakob Brünker pushed to branch wip/jakobbruenker/T24909 at Glasgow Haskell Compiler / GHC Commits: 6ca9ed0e by Jakob Bruenker at 2024-06-06T05:13:57+02:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 1 changed file: - docs/users_guide/exts/representation_polymorphism.rst Changes: ===================================== docs/users_guide/exts/representation_polymorphism.rst ===================================== @@ -79,14 +79,26 @@ representation-polymorphic type. However, not all is lost. We can still do this: :: - ($) :: forall r (a :: Type) (b :: TYPE r). + good :: forall r (a :: Type) (b :: TYPE r). (a -> b) -> a -> b - f $ x = f x + good f x = f x Here, only ``b`` is representation-polymorphic. There are no variables with a representation-polymorphic type. And the code generator has no -trouble with this. Indeed, this is the true type of GHC's ``$`` operator, -slightly more general than the Haskell 98 version. +trouble with this. Nonetheless, there is a way to write a definition with +``bad``'s type: :: + + + ($) :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) + (a :: TYPE r1) (b :: TYPE r2). + (a -> b) -> a -> b + ($) f = f + +By eta-reducing, we got rid of ``x``, and thus have no variable with a +representation-polymorphic type. Indeed, this is the true type of GHC's ``$`` +operator, slightly more general than the Haskell 98 version. However, it's +strictness properties are different: ``(good undefined) `seq` ()`` is equivalent +to ``()``, whereas ``(($) undefined) `seq` ()`` diverges. Because the code generator must store and move arguments as well as variables, the logic above applies equally well to function arguments, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ca9ed0e90d57b142e29e7cc9ba9dbb25457c25d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ca9ed0e90d57b142e29e7cc9ba9dbb25457c25d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 03:15:51 2024 From: gitlab at gitlab.haskell.org (=?UTF-8?B?SmFrb2IgQnLDvG5rZXIgKEBKYWtvYkJydWVua2VyKQ==?=) Date: Wed, 05 Jun 2024 23:15:51 -0400 Subject: [Git][ghc/ghc][wip/jakobbruenker/T24909] docs: Update mention of ($) type in user guide Message-ID: <666129e7958a8_185239279f1105195d@gitlab.mail> Jakob Brünker pushed to branch wip/jakobbruenker/T24909 at Glasgow Haskell Compiler / GHC Commits: 5d55f178 by Jakob Bruenker at 2024-06-06T05:14:44+02:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 1 changed file: - docs/users_guide/exts/representation_polymorphism.rst Changes: ===================================== docs/users_guide/exts/representation_polymorphism.rst ===================================== @@ -79,14 +79,26 @@ representation-polymorphic type. However, not all is lost. We can still do this: :: - ($) :: forall r (a :: Type) (b :: TYPE r). + good :: forall r (a :: Type) (b :: TYPE r). (a -> b) -> a -> b - f $ x = f x + good f x = f x Here, only ``b`` is representation-polymorphic. There are no variables with a representation-polymorphic type. And the code generator has no -trouble with this. Indeed, this is the true type of GHC's ``$`` operator, -slightly more general than the Haskell 98 version. +trouble with this. Nonetheless, there is a way to write a definition with +``bad``'s type: :: + + + ($) :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) + (a :: TYPE r1) (b :: TYPE r2). + (a -> b) -> a -> b + ($) f = f + +By eta-reducing, we got rid of ``x``, and thus have no variable with a +representation-polymorphic type. Indeed, this is the true type of GHC's ``$`` +operator, slightly more general than the Haskell 98 version. However, its +strictness properties are different: ``(good undefined) `seq` ()`` is equivalent +to ``()``, whereas ``(($) undefined) `seq` ()`` diverges. Because the code generator must store and move arguments as well as variables, the logic above applies equally well to function arguments, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5d55f178e9e35ac78307e6be8a0021f221f253f3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5d55f178e9e35ac78307e6be8a0021f221f253f3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 11:59:29 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 06 Jun 2024 07:59:29 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Add firstA and secondA to Data.Bitraversable Message-ID: <6661a4a119996_12ae2117507a0487ce@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 3d8ecd2e by Jan Hrček at 2024-06-06T07:59:16-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 058a7c77 by Cheng Shao at 2024-06-06T07:59:16-04:00 testsuite: bump T7653 timeout for wasm - - - - - 10 changed files: - compiler/Language/Haskell/Syntax/Pat.hs - docs/users_guide/9.12.1-notes.rst - libraries/base/base.cabal - libraries/base/changelog.md - libraries/base/src/Data/Bitraversable.hs - libraries/base/tests/all.T - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 Changes: ===================================== compiler/Language/Haskell/Syntax/Pat.hs ===================================== @@ -57,62 +57,73 @@ import Data.List.NonEmpty (NonEmpty) type LPat p = XRec p (Pat p) -- | Pattern --- --- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang' - --- For details on above see Note [exact print annotations] in GHC.Parser.Annotation data Pat p = ------------ Simple patterns --------------- - WildPat (XWildPat p) -- ^ Wildcard Pattern - -- The sole reason for a type on a WildPat is to - -- support hsPatType :: Pat Id -> Type - - -- AZ:TODO above comment needs to be updated + WildPat (XWildPat p) + -- ^ Wildcard Pattern (@_@) | VarPat (XVarPat p) - (LIdP p) -- ^ Variable Pattern + (LIdP p) + -- ^ Variable Pattern, e.g. @x@ - -- See Note [Located RdrNames] in GHC.Hs.Expr + -- See Note [Located RdrNames] in GHC.Hs.Expr | LazyPat (XLazyPat p) - (LPat p) -- ^ Lazy Pattern - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnTilde' + (LPat p) + -- ^ Lazy Pattern, e.g. @~x@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnTilde' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | AsPat (XAsPat p) (LIdP p) - (LPat p) -- ^ As pattern - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnAt' + (LPat p) + -- ^ As pattern, e.g. @x\@pat@ + -- + -- - Location of '@' is captured by 'GHC.Parser.Annotation.EpToken' @"\@"@ -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | ParPat (XParPat p) - (LPat p) -- ^ Parenthesised pattern - -- See Note [Parens in HsSyn] in GHC.Hs.Expr - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'('@, - -- 'GHC.Parser.Annotation.AnnClose' @')'@ + (LPat p) + -- ^ Parenthesised pattern, e.g. @(x)@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : + -- 'GHC.Parser.Annotation.AnnOpen' @'('@, + -- 'GHC.Parser.Annotation.AnnClose' @')'@ + + -- See Note [Parens in HsSyn] in GHC.Hs.Expr -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | BangPat (XBangPat p) - (LPat p) -- ^ Bang pattern - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang' + (LPat p) + -- ^ Bang pattern, e.g. @!x@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation ------------ Lists, tuples, arrays --------------- | ListPat (XListPat p) [LPat p] + -- ^ Syntactic List, e.g. @[x]@ or @[x,y]@ (but not @[]@ nor @(x:xs)@ which are represented using 'ConPat') + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : + -- 'GHC.Parser.Annotation.AnnOpen' @'['@, + -- 'GHC.Parser.Annotation.AnnClose' @']'@ - -- ^ Syntactic List + -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation + + | -- | Tuple pattern, e.g. @(x, y)@ -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'['@, - -- 'GHC.Parser.Annotation.AnnClose' @']'@ + -- - 'GHC.Parser.Annotation.AnnKeywordId' : + -- 'GHC.Parser.Annotation.AnnOpen' @'('@ or @'(#'@, + -- 'GHC.Parser.Annotation.AnnClose' @')'@ or @'#)'@ -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation + TuplePat (XTuplePat p) -- ^ After typechecking, holds the types of the tuple components + [LPat p] -- ^ Tuple sub-patterns + Boxity -- ^ UnitPat is TuplePat [] - | TuplePat (XTuplePat p) - -- after typechecking, holds the types of the tuple components - [LPat p] -- Tuple sub-patterns - Boxity -- UnitPat is TuplePat [] -- You might think that the post typechecking Type was redundant, -- because we can get the pattern type by getting the types of the -- sub-patterns. @@ -129,11 +140,6 @@ data Pat p -- of the tuple is of type 'a' not Int. See selectMatchVar -- (June 14: I'm not sure this comment is right; the sub-patterns -- will be wrapped in CoPats, no?) - -- ^ Tuple sub-patterns - -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : - -- 'GHC.Parser.Annotation.AnnOpen' @'('@ or @'(#'@, - -- 'GHC.Parser.Annotation.AnnClose' @')'@ or @'#)'@ | OrPat (XOrPat p) (NonEmpty (LPat p)) @@ -143,7 +149,8 @@ data Pat p (LPat p) -- Sum sub-pattern ConTag -- Alternative (one-based) SumWidth -- Arity (INVARIANT: ≥ 2) - -- ^ Anonymous sum pattern + + -- ^ Anonymous sum pattern, e.g. @(# x | #)@. Used by @-XUnboxedSums@ -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : -- 'GHC.Parser.Annotation.AnnOpen' @'(#'@, @@ -157,35 +164,40 @@ data Pat p pat_con :: XRec p (ConLikeP p), pat_args :: HsConPatDetails p } - -- ^ Constructor Pattern + -- ^ Constructor Pattern, e.g. @[]@ or @Nothing@ ------------ View patterns --------------- - -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnRarrow' - -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | ViewPat (XViewPat p) (LHsExpr p) (LPat p) - -- ^ View Pattern + -- ^ View Pattern, e.g. @someFun -> pat at . Used by @-XViewPatterns@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnRarrow' + + -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation ------------ Pattern splices --------------- - -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'$('@ - -- 'GHC.Parser.Annotation.AnnClose' @')'@ - -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | SplicePat (XSplicePat p) - (HsUntypedSplice p) -- ^ Splice Pattern (Includes quasi-quotes) + (HsUntypedSplice p) + -- ^ Splice Pattern (Includes quasi-quotes @$(...)@) + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId': + -- 'GHC.Parser.Annotation.AnnOpen' @'$('@ + -- 'GHC.Parser.Annotation.AnnClose' @')'@ + + -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation ------------ Literal and n+k patterns --------------- | LitPat (XLitPat p) - (HsLit p) -- ^ Literal Pattern - -- Used for *non-overloaded* literal patterns: - -- Int#, Char#, Int, Char, String, etc. - - | NPat -- Natural Pattern - -- Used for all overloaded literals, - -- including overloaded strings with -XOverloadedStrings - (XNPat p) -- Overall type of pattern. Might be + (HsLit p) + -- ^ Literal Pattern + -- + -- Used for __non-overloaded__ literal patterns: + -- Int#, Char#, Int, Char, String, etc. + + | NPat (XNPat p) -- Overall type of pattern. Might be -- different than the literal's type -- if (==) or negate changes the type (XRec p (HsOverLit p)) -- ALWAYS positive @@ -194,7 +206,8 @@ data Pat p -- otherwise (SyntaxExpr p) -- Equality checker, of type t->t->Bool - -- ^ Natural Pattern + -- ^ Natural Pattern, used for all overloaded literals, including overloaded Strings + -- with @-XOverloadedStrings@ -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnVal' @'+'@ @@ -208,30 +221,35 @@ data Pat p (SyntaxExpr p) -- (>=) function, of type t1->t2->Bool (SyntaxExpr p) -- Name of '-' (see GHC.Rename.Env.lookupSyntax) - -- ^ n+k pattern + -- ^ n+k pattern, e.g. @n+1@, enabled by @-XNPlusKPatterns@ extension ------------ Pattern type signatures --------------- - -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' - -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | SigPat (XSigPat p) -- After typechecker: Type (LPat p) -- Pattern with a type signature (HsPatSigType (NoGhcTc p)) -- Signature can bind both -- kind and type vars - -- ^ Pattern with a type signature + -- ^ Pattern with a type signature, e.g. @x :: Int@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' + + -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation - -- Embed the syntax of types into patterns. - -- Used with RequiredTypeArguments, e.g. fn (type t) = rhs - | EmbTyPat (XEmbTyPat p) + | -- | Embed the syntax of types into patterns. + -- Used with @-XRequiredTypeArguments@, e.g. @fn (type t) = rhs@ + EmbTyPat (XEmbTyPat p) (HsTyPat (NoGhcTc p)) - -- See Note [Invisible binders in functions] in GHC.Hs.Pat | InvisPat (XInvisPat p) (HsTyPat (NoGhcTc p)) + -- ^ Type abstraction which brings into scope type variables associated with invisible forall. Used by @-XTypeAbstractions at . + -- + -- The location of @\@@ is captured by 'GHC.Parser.Annotation.EpToken' @"\@"@ + + -- See Note [Invisible binders in functions] in GHC.Hs.Pat - -- Extension point; see Note [Trees That Grow] in Language.Haskell.Syntax.Extension - | XPat - !(XXPat p) + | -- | TTG Extension point; see Note [Trees That Grow] in Language.Haskell.Syntax.Extension + XPat !(XXPat p) type family ConLikeP x @@ -311,7 +329,7 @@ type HsRecUpdField p q = HsFieldBind (LAmbiguousFieldOcc p) (LHsExpr q) -- | Haskell Field Binding -- --- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnEqual', +-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnEqual' -- -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation data HsFieldBind lhs rhs = HsFieldBind { ===================================== docs/users_guide/9.12.1-notes.rst ===================================== @@ -11,6 +11,8 @@ for specific guidance on migrating programs to this release. Language ~~~~~~~~ +- New language extension: :extension:`OrPatterns` implements `GHC Proposal #522 + `_). - The ordering of variables used for visible type application has been changed in two cases. It is supposed to be left-to-right, but due to an oversight, it was wrong: ===================================== libraries/base/base.cabal ===================================== @@ -19,8 +19,8 @@ description: Haskell's base library provides, among other things, core types [Set](https://hackage.haskell.org/package/containers/docs/Data-Set.html) are available in the [containers](https://hackage.haskell.org/package/containers) library. To work with textual data, use the [text](https://hackage.haskell.org/package/text/docs/Data-Text.html) library. -extra-source-files: - CHANGELOG.md +extra-doc-files: + changelog.md Library default-language: Haskell2010 ===================================== libraries/base/changelog.md ===================================== @@ -6,6 +6,7 @@ * The `HasField` class now supports representation polymorphism ([CLC proposal #194](https://github.com/haskell/core-libraries-committee/issues/194)) * Make `read` accept binary integer notation ([CLC proposal #177](https://github.com/haskell/core-libraries-committee/issues/177)) * Improve the performance of `Data.List.sort` using an improved merging strategy. Instead of `compare`, `sort` now uses `(>)` which may break *malformed* `Ord` instances ([CLC proposal #236](https://github.com/haskell/core-libraries-committee/issues/236)) + * Add `firstA` and `secondA` to `Data.Bitraversable`. ([CLC proposal #172](https://github.com/haskell/core-libraries-committee/issues/172)) ## 4.20.0.0 *TBA* * Deprecate `GHC.Pack` ([#21461](https://gitlab.haskell.org/ghc/ghc/-/issues/21461)) ===================================== libraries/base/src/Data/Bitraversable.hs ===================================== @@ -18,6 +18,8 @@ module Data.Bitraversable , bisequenceA , bisequence , bimapM + , firstA + , secondA , bifor , biforM , bimapAccumL @@ -172,6 +174,60 @@ bimapM = bitraverse bisequence :: (Bitraversable t, Applicative f) => t (f a) (f b) -> f (t a b) bisequence = bitraverse id id +-- | Traverses only over the first argument. +-- +-- @'firstA' f ≡ 'bitraverse' f 'pure'@ + +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> firstA listToMaybe (Left []) +-- Nothing +-- +-- >>> firstA listToMaybe (Left [1, 2, 3]) +-- Just (Left 1) +-- +-- >>> firstA listToMaybe (Right [4, 5]) +-- Just (Right [4, 5]) +-- +-- >>> firstA listToMaybe ([1, 2, 3], [4, 5]) +-- Just (1,[4, 5]) +-- +-- >>> firstA listToMaybe ([], [4, 5]) +-- Nothing + +-- @since 4.21.0.0 +firstA :: Bitraversable t => Applicative f => (a -> f c) -> t a b -> f (t c b) +firstA f = bitraverse f pure + +-- | Traverses only over the second argument. +-- +-- @'secondA' f ≡ 'bitraverse' 'pure' f@ +-- +-- ==== __Examples__ +-- +-- Basic usage: +-- +-- >>> secondA (find odd) (Left []) +-- Just (Left []) +-- +-- >>> secondA (find odd) (Left [1, 2, 3]) +-- Just (Left [1,2,3]) +-- +-- >>> secondA (find odd) (Right [4, 5]) +-- Just (Right 5) +-- +-- >>> secondA (find odd) ([1, 2, 3], [4, 5]) +-- Just ([1,2,3],5) +-- +-- >>> secondA (find odd) ([1,2,3], [4]) +-- Nothing +-- +-- @since 4.21.0.0 +secondA :: Bitraversable t => Applicative f => (b -> f c) -> t a b -> f (t a c) +secondA f = bitraverse pure f + -- | Class laws for tuples hold only up to laziness. The -- Bitraversable methods are lazier than their Traversable counterparts. -- For example the law @'bitraverse' 'pure' ≡ 'traverse'@ does ===================================== libraries/base/tests/all.T ===================================== @@ -189,6 +189,7 @@ test('CatEntail', normal, compile, ['']) # When running with WAY=ghci and profiled ways, T7653 uses a lot of memory. test('T7653', [when(opsys('mingw32'), skip), + when(arch('wasm32'), run_timeout_multiplier(5)), omit_ways(prof_ways + ghci_ways)], compile_and_run, ['']) test('T7787', normal, compile_and_run, ['']) ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -679,6 +679,8 @@ module Data.Bitraversable where bimapM :: forall (t :: * -> * -> *) (f :: * -> *) a c b d. (Bitraversable t, GHC.Internal.Base.Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d) bisequence :: forall (t :: * -> * -> *) (f :: * -> *) a b. (Bitraversable t, GHC.Internal.Base.Applicative f) => t (f a) (f b) -> f (t a b) bisequenceA :: forall (t :: * -> * -> *) (f :: * -> *) a b. (Bitraversable t, GHC.Internal.Base.Applicative f) => t (f a) (f b) -> f (t a b) + firstA :: forall (t :: * -> * -> *) (f :: * -> *) a c b. (Bitraversable t, GHC.Internal.Base.Applicative f) => (a -> f c) -> t a b -> f (t c b) + secondA :: forall (t :: * -> * -> *) (f :: * -> *) b c a. (Bitraversable t, GHC.Internal.Base.Applicative f) => (b -> f c) -> t a b -> f (t a c) module Data.Bits where -- Safety: Safe ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -679,6 +679,8 @@ module Data.Bitraversable where bimapM :: forall (t :: * -> * -> *) (f :: * -> *) a c b d. (Bitraversable t, GHC.Internal.Base.Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d) bisequence :: forall (t :: * -> * -> *) (f :: * -> *) a b. (Bitraversable t, GHC.Internal.Base.Applicative f) => t (f a) (f b) -> f (t a b) bisequenceA :: forall (t :: * -> * -> *) (f :: * -> *) a b. (Bitraversable t, GHC.Internal.Base.Applicative f) => t (f a) (f b) -> f (t a b) + firstA :: forall (t :: * -> * -> *) (f :: * -> *) a c b. (Bitraversable t, GHC.Internal.Base.Applicative f) => (a -> f c) -> t a b -> f (t c b) + secondA :: forall (t :: * -> * -> *) (f :: * -> *) b c a. (Bitraversable t, GHC.Internal.Base.Applicative f) => (b -> f c) -> t a b -> f (t a c) module Data.Bits where -- Safety: Safe ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -679,6 +679,8 @@ module Data.Bitraversable where bimapM :: forall (t :: * -> * -> *) (f :: * -> *) a c b d. (Bitraversable t, GHC.Internal.Base.Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d) bisequence :: forall (t :: * -> * -> *) (f :: * -> *) a b. (Bitraversable t, GHC.Internal.Base.Applicative f) => t (f a) (f b) -> f (t a b) bisequenceA :: forall (t :: * -> * -> *) (f :: * -> *) a b. (Bitraversable t, GHC.Internal.Base.Applicative f) => t (f a) (f b) -> f (t a b) + firstA :: forall (t :: * -> * -> *) (f :: * -> *) a c b. (Bitraversable t, GHC.Internal.Base.Applicative f) => (a -> f c) -> t a b -> f (t c b) + secondA :: forall (t :: * -> * -> *) (f :: * -> *) b c a. (Bitraversable t, GHC.Internal.Base.Applicative f) => (b -> f c) -> t a b -> f (t a c) module Data.Bits where -- Safety: Safe ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -679,6 +679,8 @@ module Data.Bitraversable where bimapM :: forall (t :: * -> * -> *) (f :: * -> *) a c b d. (Bitraversable t, GHC.Internal.Base.Applicative f) => (a -> f c) -> (b -> f d) -> t a b -> f (t c d) bisequence :: forall (t :: * -> * -> *) (f :: * -> *) a b. (Bitraversable t, GHC.Internal.Base.Applicative f) => t (f a) (f b) -> f (t a b) bisequenceA :: forall (t :: * -> * -> *) (f :: * -> *) a b. (Bitraversable t, GHC.Internal.Base.Applicative f) => t (f a) (f b) -> f (t a b) + firstA :: forall (t :: * -> * -> *) (f :: * -> *) a c b. (Bitraversable t, GHC.Internal.Base.Applicative f) => (a -> f c) -> t a b -> f (t c b) + secondA :: forall (t :: * -> * -> *) (f :: * -> *) b c a. (Bitraversable t, GHC.Internal.Base.Applicative f) => (b -> f c) -> t a b -> f (t a c) module Data.Bits where -- Safety: Safe View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d6940e46a2ee323966b66a9d01b53f6bddd59eb0...058a7c774aee9eb53563c110e88795d499874cf8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d6940e46a2ee323966b66a9d01b53f6bddd59eb0...058a7c774aee9eb53563c110e88795d499874cf8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 12:28:29 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Thu, 06 Jun 2024 08:28:29 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T24945 Message-ID: <6661ab6d8fa4_12ae211b890d858746@gitlab.mail> Cheng Shao pushed new branch wip/T24945 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T24945 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 12:31:48 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 06 Jun 2024 08:31:48 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] SIMD NCG WIP: fix stack spilling Message-ID: <6661ac349da86_12ae211c77ee0608ee@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 2b451078 by sheaf at 2024-06-06T14:26:29+02:00 SIMD NCG WIP: fix stack spilling - - - - - 9 changed files: - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs - compiler/GHC/CmmToAsm/Reg/Linear/State.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Platform/Reg.hs - compiler/GHC/Platform/Reg/Class.hs Changes: ===================================== compiler/GHC/CmmToAsm/Instr.hs ===================================== @@ -97,8 +97,8 @@ class Instruction instr where :: NCGConfig -> Reg -- ^ the reg to spill -> Int -- ^ the current stack delta - -> Int -- ^ spill slot to use - -> [instr] -- ^ instructions + -> Int -- ^ spill slots to use + -> [instr] -- ^ instructions -- | An instruction to reload a register from a spill slot. ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -719,7 +719,7 @@ saveClobberedTemps clobbered dying -- (2) no free registers: spill the value [] -> do - (spill, slot) <- spillR (RegReal reg) temp + (spill, slot) <- spillR (RegReal reg) regclass temp -- record why this reg was spilled for profiling recordSpill (SpillClobber temp) @@ -869,7 +869,8 @@ allocRegsAndSpill_spill :: (FR freeRegs, Instruction instr) allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc = do platform <- getPlatform freeRegs <- getFreeRegsR - let freeRegs_thisClass = frGetFreeRegs platform (classOfVirtualReg r) freeRegs :: [RealReg] + let regclass = classOfVirtualReg r + freeRegs_thisClass = frGetFreeRegs platform regclass freeRegs :: [RealReg] -- Can we put the variable into a register it already was? pref_reg <- findPrefRealReg r @@ -938,7 +939,7 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc | (temp_to_push_out, (my_reg :: RealReg)) : _ <- candidates_inReg = do - (spill_store, slot) <- spillR (RegReal my_reg) temp_to_push_out + (spill_store, slot) <- spillR (RegReal my_reg) regclass temp_to_push_out -- record that this temp was spilled recordSpill (SpillAlloc temp_to_push_out) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/Base.hs ===================================== @@ -96,11 +96,11 @@ data Loc -- | vreg is in a register = InReg !RealReg - -- | vreg is held in a stack slot + -- | vreg is held in stack slots | InMem {-# UNPACK #-} !StackSlot - -- | vreg is held in both a register and a stack slot + -- | vreg is held in both a register and stack slots | InBoth !RealReg {-# UNPACK #-} !StackSlot deriving (Eq, Show, Ord) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs ===================================== @@ -32,6 +32,7 @@ import GHC.Types.Unique.FM import GHC.Types.Unique.Set import GHC.Utils.Outputable +import GHC.CmmToAsm.Reg.Target (targetClassOfRealReg) -- | For a jump instruction at the end of a block, generate fixup code so its -- vregs are in the correct regs for its destination. @@ -330,9 +331,10 @@ handleComponent delta instr (CyclicSCC ((DigraphNode vreg (InReg sreg) ((InReg dreg: _))) : rest)) -- dest list may have more than one element, if the reg is also InMem. = do + platform <- getPlatform -- spill the source into its slot (instrSpill, slot) - <- spillR (RegReal sreg) vreg + <- spillR (RegReal sreg) (targetClassOfRealReg platform sreg) vreg -- reload into destination reg instrLoad <- loadR (RegReal dreg) slot ===================================== compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs ===================================== @@ -22,6 +22,7 @@ where import GHC.Prelude +import GHC.Platform.Reg.Class import GHC.Types.Unique.FM import GHC.Types.Unique @@ -47,13 +48,20 @@ emptyStackMap = StackMap 0 emptyUFM -- | If this vreg unique already has a stack assignment then return the slot number, -- otherwise allocate a new slot, and update the map. -- -getStackSlotFor :: StackMap -> Unique -> (StackMap, Int) - -getStackSlotFor fs@(StackMap _ reserved) reg - | Just slot <- lookupUFM reserved reg = (fs, slot) - -getStackSlotFor (StackMap freeSlot reserved) reg = - (StackMap (freeSlot+1) (addToUFM reserved reg freeSlot), freeSlot) +getStackSlotFor :: StackMap -> RegClass -> Unique -> (StackMap, Int) + +getStackSlotFor fs@(StackMap _ reserved) _regUse regUnique + | Just slot <- lookupUFM reserved regUnique = (fs, slot) + +getStackSlotFor (StackMap freeSlot reserved) regClass regUnique = + let + nbSlots = case regClass of + RcInteger -> 1 + RcFloat -> 1 + RcDouble -> 1 + RcVector128 -> 2 + in + (StackMap (freeSlot+nbSlots) (addToUFM reserved regUnique freeSlot), freeSlot) -- | Return the number of stack slots that were allocated getStackUse :: StackMap -> Int ===================================== compiler/GHC/CmmToAsm/Reg/Linear/State.hs ===================================== @@ -48,6 +48,7 @@ import GHC.Platform.Reg import GHC.Cmm.BlockId import GHC.Platform +import GHC.Platform.Reg.Class import GHC.Types.Unique import GHC.Types.Unique.Supply import GHC.Exts (oneShot) @@ -121,13 +122,13 @@ makeRAStats state spillR :: Instruction instr - => Reg -> Unique -> RegM freeRegs ([instr], Int) + => Reg -> RegClass -> Unique -> RegM freeRegs ([instr], Int) -spillR reg temp = mkRegM $ \s -> - let (stack1,slot) = getStackSlotFor (ra_stack s) temp - instr = mkSpillInstr (ra_config s) reg (ra_delta s) slot +spillR reg regClass temp = mkRegM $ \s -> + let (stack1,slots) = getStackSlotFor (ra_stack s) regClass temp + instr = mkSpillInstr (ra_config s) reg (ra_delta s) slots in - RA_Result s{ra_stack=stack1} (instr,slot) + RA_Result s{ra_stack=stack1} (instr,slots) loadR :: Instruction instr ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -380,6 +380,8 @@ data Instr | VSHUFPS Format Imm Operand Reg | SHUFPD Format Imm Operand Reg | VSHUFPD Format Imm Operand Reg + -- SIMD NCG TODO: don't store the Format (or only what we need) + -- in order to emit these instructions. -- Shift | PSLLDQ Format Operand Reg @@ -822,13 +824,20 @@ mkSpillInstr -> [Instr] mkSpillInstr config reg delta slot - = let off = spillSlotToOffset platform slot - delta + = let off s = spillSlotToOffset platform s - delta in case targetClassOfReg platform reg of RcInteger -> [MOV (archWordFormat is32Bit) - (OpReg reg) (OpAddr (spRel platform off))] - RcDouble -> [MOV FF64 (OpReg reg) (OpAddr (spRel platform off))] - _ -> panic "X86.mkSpillInstr: no match" + (OpReg reg) (OpAddr (spRel platform $ off slot))] + RcDouble -> [MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off slot))] + RcFloat -> panic "X86_mkSpillInstr: RcFloat" + RcVector128 -> [MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off slot)) + -- Now shuffle the register, putting the high half into the lower half. + ,SHUFPD (VecFormat 2 FmtDouble W64) (ImmInt 0b00) (OpReg reg) reg + -- NB: this format doesn't matter, we emit the same instruction + -- regardless of what is stored... + -- SIMD NCG TODO: avoid using MOV by using SHUFPD with an OpAddr argument? + ,MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off (slot + 1)))] where platform = ncgPlatform config is32Bit = target32Bit platform @@ -841,13 +850,24 @@ mkLoadInstr -> [Instr] mkLoadInstr config reg delta slot - = let off = spillSlotToOffset platform slot - delta + = let off s = spillSlotToOffset platform s - delta in case targetClassOfReg platform reg of RcInteger -> ([MOV (archWordFormat is32Bit) - (OpAddr (spRel platform off)) (OpReg reg)]) - RcDouble -> ([MOV FF64 (OpAddr (spRel platform off)) (OpReg reg)]) - _ -> panic "X86.mkLoadInstr" + (OpAddr (spRel platform $ off slot)) (OpReg reg)]) + RcDouble -> ([MOV FF64 (OpAddr (spRel platform $ off slot)) (OpReg reg)]) + RcFloat -> panic "X86.mkLoadInstr RcFloat" + RcVector128 -> + -- Load the higher half into the lower part of register from the second stack slot, + -- shuffle it into the higher part of the register, + -- and load then lower half into the lower part of the register. + [MOV FF64 (OpAddr (spRel platform $ off (slot + 1))) (OpReg reg) + ,SHUFPD (VecFormat 2 FmtDouble W64) (ImmInt 0b01) (OpReg reg) reg + -- SIMD NCG TODO: not sure about this immediate + -- SIMD NCG TODO: can we avoid the MOV instructions and directly + -- use SHUFPD for an Addr to Reg move? + ,MOV FF64 (OpAddr (spRel platform $ off slot)) (OpReg reg)] + where platform = ncgPlatform config is32Bit = target32Bit platform ===================================== compiler/GHC/Platform/Reg.hs ===================================== @@ -116,17 +116,12 @@ renameVirtualReg u r classOfVirtualReg :: VirtualReg -> RegClass classOfVirtualReg vr - = case vr of + = case vr of VirtualRegI{} -> RcInteger VirtualRegHi{} -> RcInteger VirtualRegF{} -> RcFloat VirtualRegD{} -> RcDouble - -- Below is an awful, largely x86-specific hack - VirtualRegVec{} -> RcDouble - -- SIMD NCG TODO: this seems very wrong and potentially the source of - -- bug #16927, because we use this function to determine how to spill - -- the contents of a virtual register - -- (see e.g. GHC.CmmToAsm.X86.Instr.mkSpillInstr). + VirtualRegVec{} -> RcVector128 -- Determine the upper-half vreg for a 64-bit quantity on a 32-bit platform ===================================== compiler/GHC/Platform/Reg/Class.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE LambdaCase #-} -- | An architecture independent description of a register's class. module GHC.Platform.Reg.Class ( RegClass (..) @@ -18,21 +19,26 @@ import GHC.Builtin.Uniques -- We treat all registers in a class as being interchangeable. -- data RegClass - = RcInteger - | RcFloat - | RcDouble - deriving (Eq, Show) + = RcInteger + | RcFloat + | RcDouble + | RcVector128 + deriving (Eq, Ord, Show) allRegClasses :: [RegClass] allRegClasses = - [RcInteger, RcFloat, RcDouble] + [ RcInteger, RcFloat, RcDouble, RcVector128 ] instance Uniquable RegClass where - getUnique RcInteger = mkRegClassUnique 0 - getUnique RcFloat = mkRegClassUnique 1 - getUnique RcDouble = mkRegClassUnique 2 + getUnique = \case + RcInteger -> mkRegClassUnique 0 + RcFloat -> mkRegClassUnique 1 + RcDouble -> mkRegClassUnique 2 + RcVector128 -> mkRegClassUnique 3 instance Outputable RegClass where - ppr RcInteger = Outputable.text "I" - ppr RcFloat = Outputable.text "F" - ppr RcDouble = Outputable.text "D" + ppr = \case + RcInteger -> Outputable.text "I" + RcFloat -> Outputable.text "F" + RcDouble -> Outputable.text "D" + RcVector128 -> Outputable.text "V" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2b451078203820b4f3a55c02935a01fa7382631e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2b451078203820b4f3a55c02935a01fa7382631e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 13:17:44 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 06 Jun 2024 09:17:44 -0400 Subject: [Git][ghc/ghc][wip/romes/faststring-is-shortbytestring] 7351 commits: [haddock @ 2002-04-04 16:23:43 by simonmar] Message-ID: <6661b6f885b62_12ae21241bfd4622a3@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/faststring-is-shortbytestring at Glasgow Haskell Compiler / GHC Commits: 2b39cd94 by Simon Marlow at 2002-04-04T16:23:43+00:00 [haddock @ 2002-04-04 16:23:43 by simonmar] This is Haddock, my stab at a Haskell documentation tool. It's not quite ready for release yet, but I'm putting it in the repository so others can take a look. It uses a locally modified version of the hssource parser, extended with support for GHC extensions and documentation annotations. - - - - - 99ede94f by Simon Marlow at 2002-04-04T16:24:10+00:00 [haddock @ 2002-04-04 16:24:10 by simonmar] forgot one file - - - - - 8363294c by Simon Marlow at 2002-04-05T13:58:15+00:00 [haddock @ 2002-04-05 13:58:15 by simonmar] Remap names in the exported declarations to be "closer" to the current module. eg. if an exported declaration mentions a type 'T' which is imported from module A then re-exported from the current module, then links from the type or indeed the documentation will point to the current module rather than module A. This is to support better hiding: module A won't be referred to in the generated output. - - - - - 1570cbc1 by Simon Marlow at 2002-04-05T13:58:23+00:00 [haddock @ 2002-04-05 13:58:23 by simonmar] update the TODO list - - - - - 3a62f96b by Simon Marlow at 2002-04-05T14:11:51+00:00 [haddock @ 2002-04-05 14:11:51 by simonmar] Fix the anchor for a class declaration - - - - - c5d9a471 by Simon Marlow at 2002-04-05T14:18:41+00:00 [haddock @ 2002-04-05 14:18:41 by simonmar] remove underlines on visited links - - - - - 97280525 by Simon Marlow at 2002-04-05T16:11:47+00:00 [haddock @ 2002-04-05 16:11:47 by simonmar] - Update to generate more correct HTML. - Use our own non-overloaded table combinators, as the overloaded versions were giving me a headache. The improved type safety caught several errors in the HTML generation. - - - - - 9acd3a4d by Simon Marlow at 2002-04-05T16:32:19+00:00 [haddock @ 2002-04-05 16:32:19 by simonmar] Add width property to the title, and add TD.children for the module contents page. - - - - - ec9a0847 by Simon Marlow at 2002-04-08T16:39:56+00:00 [haddock @ 2002-04-08 16:39:56 by simonmar] Fix a problem with exports of the form T(..). - - - - - e4627dc8 by Simon Marlow at 2002-04-08T16:41:38+00:00 [haddock @ 2002-04-08 16:41:37 by simonmar] - Add our own versions of Html & BlockTable for the time being. - Add support for generating an index to the HTML backend - - - - - 2d73fd75 by Simon Marlow at 2002-04-09T11:23:24+00:00 [haddock @ 2002-04-09 11:23:24 by simonmar] Add '-- /' as a synonym for '-- |', for compatibility with IDoc. - - - - - 3675464e by Simon Marlow at 2002-04-09T11:33:55+00:00 [haddock @ 2002-04-09 11:33:54 by simonmar] - add the <...> syntax for marking up URLs in documentation - Make the output for data & class declarations more compact when there aren't any documentation annotations on the individual methods or constructors respectively. - - - - - 5077f5b1 by Simon Marlow at 2002-04-09T11:36:04+00:00 [haddock @ 2002-04-09 11:36:04 by simonmar] Update the TODO list - - - - - 9e83c54d by Simon Marlow at 2002-04-10T10:50:06+00:00 [haddock @ 2002-04-10 10:50:06 by simonmar] Use explicit 'px' suffix on pixel sizes; IE seems to prefer them - - - - - 052de51c by Simon Marlow at 2002-04-10T13:23:13+00:00 [haddock @ 2002-04-10 13:23:13 by simonmar] Lex URLs as a single token to avoid having to escape special characters inside the URL string. - - - - - 47187edb by Simon Marlow at 2002-04-10T13:23:55+00:00 [haddock @ 2002-04-10 13:23:55 by simonmar] Not sure why I made the constructor name for a record declaration into a TyCls name, but change it back into a Var name anyhow. - - - - - 3dc6aa81 by Simon Marlow at 2002-04-10T13:26:10+00:00 [haddock @ 2002-04-10 13:26:09 by simonmar] Lots of changes, including: - add index support to the HTML backend - clean up the renamer, put it into a monad - propogate unresolved names to the top level and report them in a nicer way - various bugfixes - - - - - c2a70a72 by Simon Marlow at 2002-04-10T13:32:39+00:00 [haddock @ 2002-04-10 13:32:39 by simonmar] Skeleton documentation - - - - - 50c98d17 by Simon Marlow at 2002-04-10T13:37:23+00:00 [haddock @ 2002-04-10 13:37:23 by simonmar] Update the TODO list, separate into pre-1.0 and post-1.0 items - - - - - f3778be6 by Simon Marlow at 2002-04-10T14:30:58+00:00 [haddock @ 2002-04-10 14:30:58 by simonmar] Add an introduction - - - - - cfbaf9f7 by Simon Marlow at 2002-04-10T14:59:51+00:00 [haddock @ 2002-04-10 14:59:51 by simonmar] Sort the module tree - - - - - 76bd7b34 by Simon Marlow at 2002-04-10T15:50:11+00:00 [haddock @ 2002-04-10 15:50:10 by simonmar] Generate a little table of contents at the top of the module doc (only if the module actually contains some section headings, though). - - - - - bb8560a1 by Simon Marlow at 2002-04-10T16:10:26+00:00 [haddock @ 2002-04-10 16:10:26 by simonmar] Now we understand (or at least don't barf on) type signatures in patterns such as you might find when scoped type variables are in use. - - - - - 86c2a026 by Simon Marlow at 2002-04-10T16:10:49+00:00 [haddock @ 2002-04-10 16:10:49 by simonmar] more updates - - - - - 1c052b0e by Simon Marlow at 2002-04-10T16:28:05+00:00 [haddock @ 2002-04-10 16:28:05 by simonmar] Parse errors in doc strings are now reported as warnings rather that causing the whole thing to fall over. It still needs cleaning up (the warning is emitted with trace) but this will do for the time being. - - - - - ace03e8f by Simon Marlow at 2002-04-10T16:38:03+00:00 [haddock @ 2002-04-10 16:38:03 by simonmar] update again - - - - - 69006c3e by Simon Marlow at 2002-04-11T13:38:02+00:00 [haddock @ 2002-04-11 13:38:02 by simonmar] mention Opera - - - - - fe9b10f8 by Simon Marlow at 2002-04-11T13:40:31+00:00 [haddock @ 2002-04-11 13:40:30 by simonmar] - copy haddock.css into the same place as the generated HTML - new option: --css <file> specifies the style sheet to use - new option: -o <dir> specifies the directory in which to generate the output. - because Haddock now needs to know where to find its default stylesheet, we have to have a wrapper script and do the haddock-inplace thing (Makefile code copied largely from fptools/happy). - - - - - 106adbbe by Simon Marlow at 2002-04-24T15:12:41+00:00 [haddock @ 2002-04-24 15:12:41 by simonmar] Stop slurping comment lines when we see a row of dashes longer than length 2: these are useful as separators. - - - - - 995d3f9e by Simon Marlow at 2002-04-24T15:14:12+00:00 [haddock @ 2002-04-24 15:14:11 by simonmar] Grok the kind of module headers we use in fptools/libraries, and pass the "portability", "stability", and "maintainer" strings through into the generated HTML. If the module header doesn't match the pattern, then we don't include the info in the HTML. - - - - - e14da136 by Simon Marlow at 2002-04-24T15:16:57+00:00 [haddock @ 2002-04-24 15:16:57 by simonmar] Done module headers now. - - - - - 2ca8dfd4 by Simon Marlow at 2002-04-24T15:57:48+00:00 [haddock @ 2002-04-24 15:57:47 by simonmar] Handle gcons in export lists (a common extension). - - - - - 044cea81 by Simon Marlow at 2002-04-25T14:20:12+00:00 [haddock @ 2002-04-25 14:20:12 by simonmar] Add the little lambda icon - - - - - 63955027 by Simon Marlow at 2002-04-25T14:40:05+00:00 [haddock @ 2002-04-25 14:40:05 by simonmar] - Add support for named chunks of documentation which can be referenced from the export list. - Copy the icon from $libdir to the destination in HTML mode. - - - - - 36e3f913 by Simon Marlow at 2002-04-25T16:48:36+00:00 [haddock @ 2002-04-25 16:48:36 by simonmar] More keyboard bashing - - - - - 7ae18dd0 by Simon Marlow at 2002-04-26T08:43:33+00:00 [haddock @ 2002-04-26 08:43:33 by simonmar] Package util reqd. to compile with 4.08.2 - - - - - bbd5fbab by Simon Marlow at 2002-04-26T10:13:00+00:00 [haddock @ 2002-04-26 10:13:00 by simonmar] Include $(GHC_HAPPY_OPTS) when compiling HsParser - - - - - 31c53d79 by Simon Marlow at 2002-04-26T11:18:57+00:00 [haddock @ 2002-04-26 11:18:56 by simonmar] - support for fundeps (partially contributed by Brett Letner - thanks Brett). - make it build with GHC 4.08.2 - - - - - c415ce76 by Simon Marlow at 2002-04-26T13:15:02+00:00 [haddock @ 2002-04-26 13:15:02 by simonmar] Move the explicit formatting of the little table for the stability/portability/maintainer info from the HTML into the CSS, and remove the explicit table size (just right-align it). - - - - - 520ee21a by Simon Marlow at 2002-04-26T16:01:44+00:00 [haddock @ 2002-04-26 16:01:44 by simonmar] Yet more keyboard bashing - this is pretty much complete now. - - - - - 2ae37179 by Simon Marlow at 2002-04-26T16:02:14+00:00 [haddock @ 2002-04-26 16:02:14 by simonmar] Add a couple of things I forgot about - - - - - b7211e04 by Simon Marlow at 2002-04-29T15:28:12+00:00 [haddock @ 2002-04-29 15:28:12 by simonmar] bugfix for declBinders on a NewTypeDecl - - - - - 640c154a by Simon Marlow at 2002-04-29T15:28:54+00:00 [haddock @ 2002-04-29 15:28:54 by simonmar] Allow '-- |' style annotations on constructors and record fields. - - - - - 393f258a by Simon Marlow at 2002-04-29T15:37:32+00:00 [haddock @ 2002-04-29 15:37:32 by simonmar] syntax fix - - - - - 8a2c2549 by Simon Marlow at 2002-04-29T15:37:48+00:00 [haddock @ 2002-04-29 15:37:48 by simonmar] Add an example - - - - - db88f8a2 by Simon Marlow at 2002-04-29T15:55:46+00:00 [haddock @ 2002-04-29 15:55:46 by simonmar] remove a trace - - - - - 2b0248e0 by Simon Marlow at 2002-04-29T15:56:19+00:00 [haddock @ 2002-04-29 15:56:19 by simonmar] Fix for 'make install' - - - - - 120453a0 by Simon Marlow at 2002-04-29T15:56:39+00:00 [haddock @ 2002-04-29 15:56:39 by simonmar] Install the auxilliary bits - - - - - 950e6dbb by Simon Marlow at 2002-04-29T15:57:30+00:00 [haddock @ 2002-04-29 15:57:30 by simonmar] Add BinDist bits - - - - - 154b9d71 by Simon Marlow at 2002-05-01T11:02:52+00:00 [haddock @ 2002-05-01 11:02:52 by simonmar] update - - - - - ba6c39fa by Simon Marlow at 2002-05-01T11:03:26+00:00 [haddock @ 2002-05-01 11:03:26 by simonmar] Add another item - - - - - bacb5e33 by Simon Marlow at 2002-05-03T08:50:00+00:00 [haddock @ 2002-05-03 08:50:00 by simonmar] Fix some typos. - - - - - 54c87895 by Sven Panne at 2002-05-05T19:40:51+00:00 [haddock @ 2002-05-05 19:40:51 by panne] As a temporary hack/workaround for a bug in GHC's simplifier, don't pass Happy the -c option for generating the parsers in this subdir. Furthermore, disable -O for HaddocParse, too. - - - - - e6c08703 by Simon Marlow at 2002-05-06T09:51:10+00:00 [haddock @ 2002-05-06 09:51:10 by simonmar] Add RPM spec file (thanks to Tom Moertel <tom-rpms at moertel.com>) - - - - - 7b8fa8e7 by Simon Marlow at 2002-05-06T12:29:26+00:00 [haddock @ 2002-05-06 12:29:26 by simonmar] Add missing type signature (a different workaround for the bug in GHC's simplifier). - - - - - cd0e300d by Simon Marlow at 2002-05-06T12:30:09+00:00 [haddock @ 2002-05-06 12:30:09 by simonmar] Remove workaround for simplifier bug in previous revision. - - - - - 687e68fa by Simon Marlow at 2002-05-06T12:32:32+00:00 [haddock @ 2002-05-06 12:32:32 by simonmar] Allow empty data declarations (another GHC extension). - - - - - 8f29f696 by Simon Marlow at 2002-05-06T12:49:21+00:00 [haddock @ 2002-05-06 12:49:21 by simonmar] Fix silly bug in named documentation block lookup. - - - - - 8e0059af by Simon Marlow at 2002-05-06T13:02:42+00:00 [haddock @ 2002-05-06 13:02:42 by simonmar] Add another named chunk with a different name - - - - - 68f8a896 by Simon Marlow at 2002-05-06T13:32:32+00:00 [haddock @ 2002-05-06 13:32:32 by simonmar] Be more lenient about extra paragraph breaks - - - - - 65fc31db by Simon Marlow at 2002-05-07T15:36:36+00:00 [haddock @ 2002-05-07 15:36:36 by simonmar] DocEmpty is a right and left-unit of DocAppend (remove it in the smart constructor). - - - - - adc81078 by Simon Marlow at 2002-05-07T15:37:15+00:00 [haddock @ 2002-05-07 15:37:15 by simonmar] Allow code blocks to be denoted with bird-tracks in addition to [...]. - - - - - 1283a3c1 by Simon Marlow at 2002-05-08T11:21:56+00:00 [haddock @ 2002-05-08 11:21:56 by simonmar] Add a facility for specifying options that affect Haddock's treatment of the module. Options are given at the top of the module in a comma-separated list, beginning with '-- #'. eg. -- # prune, hide, ignore-exports Options currently available, with their meanings: prune: ignore declarations which have no documentation annotations ignore-exports: act as if the export list were not specified (i.e. export everything local to the module). hide: do not include this module in the generated documentation, but propagate any exported definitions to modules which re-export them. There's a slight change in the semantics for re-exporting a full module by giving 'module M' in the export list: if module M does not have the 'hide' option, then the documentation will now just contain a reference to module M rather than the full inlined contents of that module. These features, and some other changes in the pipeline, are the result of discussions between myself and Manuel Chakravarty <chak at cse.unsw.edu.au> (author of IDoc) yesterday. Also: some cleanups, use a Writer monad to collect error messages in some places instead of just printing them with trace. - - - - - a2239cf5 by Simon Marlow at 2002-05-08T11:22:30+00:00 [haddock @ 2002-05-08 11:22:30 by simonmar] Update to test new features. - - - - - 6add955f by Simon Marlow at 2002-05-08T13:37:25+00:00 [haddock @ 2002-05-08 13:37:25 by simonmar] Change the markup for typewriter-font from [...] to @... at . The reasoning is that the '@' symbol is much less likely to be needed than square brackets, and we don't want to have to escape square brackets in code fragments. This will be mildly painful in the short term, but it's better to get the change out of the way as early as possible. - - - - - cda06447 by Simon Marlow at 2002-05-08T13:39:56+00:00 [haddock @ 2002-05-08 13:39:56 by simonmar] Allow nested-style comments to be used as documentation annotations too. eg. {-| ... -} is equivalent to -- | ... An extra space can also be left after the comment opener: {- | ... -}. The only version that isn't allowed is {-# ... -}, because this syntax overlaps with Haskell pragmas; use {- # ... -} instead. - - - - - db23f65e by Simon Marlow at 2002-05-08T14:48:41+00:00 [haddock @ 2002-05-08 14:48:39 by simonmar] Add support for existential quantifiers on constructors. - - - - - adce3794 by Simon Marlow at 2002-05-08T15:43:25+00:00 [haddock @ 2002-05-08 15:43:25 by simonmar] update - - - - - 62a1f436 by Simon Marlow at 2002-05-08T15:44:10+00:00 [haddock @ 2002-05-08 15:44:10 by simonmar] Update to version 0.2 - - - - - f6a24ba3 by Simon Marlow at 2002-05-09T08:48:29+00:00 [haddock @ 2002-05-09 08:48:29 by simonmar] typo - - - - - 9f9522a4 by Simon Marlow at 2002-05-09T10:33:14+00:00 [haddock @ 2002-05-09 10:33:14 by simonmar] oops, left out '/' from the special characters in the last change. - - - - - 14abcb39 by Simon Marlow at 2002-05-09T10:34:44+00:00 [haddock @ 2002-05-09 10:34:44 by simonmar] Fix buglet - - - - - b8d878be by Simon Marlow at 2002-05-09T10:35:00+00:00 [haddock @ 2002-05-09 10:35:00 by simonmar] Give a more useful instance of Show for Module. - - - - - f7bfd626 by Simon Marlow at 2002-05-09T10:37:07+00:00 [haddock @ 2002-05-09 10:37:07 by simonmar] The last commit to Main.lhs broke the delicate balance of laziness which was being used to avoid computing the dependency graph of modules. So I finally bit the bullet and did a proper topological sort of the module graph, which turned out to be easy (stealing the Digraph module from GHC - this really ought to be in the libraries somewhere). - - - - - b481c1d0 by Simon Marlow at 2002-05-09T10:37:25+00:00 [haddock @ 2002-05-09 10:37:25 by simonmar] another item done - - - - - 032e2b42 by Simon Marlow at 2002-05-09T10:44:15+00:00 [haddock @ 2002-05-09 10:44:15 by simonmar] Don't consider a module re-export as having documentation, for the purposes of deciding whether we need a Synopsis section or not. - - - - - 5fb45e92 by Simon Marlow at 2002-05-09T11:10:55+00:00 [haddock @ 2002-05-09 11:10:55 by simonmar] Add a special case for list types in ppHsAType - - - - - 1937e428 by Simon Marlow at 2002-05-09T12:43:06+00:00 [haddock @ 2002-05-09 12:43:06 by simonmar] Type synonyms can accept a ctype on the RHS, to match GHC. - - - - - 0f16ce56 by Simon Marlow at 2002-05-09T12:45:19+00:00 [haddock @ 2002-05-09 12:45:19 by simonmar] Add 'stdcall' keyword - - - - - 29b0d7d2 by Simon Marlow at 2002-05-09T13:35:45+00:00 [haddock @ 2002-05-09 13:35:45 by simonmar] Add System Requirements section - - - - - bf14dddd by Simon Marlow at 2002-05-09T13:36:11+00:00 [haddock @ 2002-05-09 13:36:11 by simonmar] Test existential types, amongst other things - - - - - 502f8f6f by Simon Marlow at 2002-05-09T13:37:35+00:00 [haddock @ 2002-05-09 13:37:35 by simonmar] Print the module name in a doc-string parse error - - - - - ca1f8d49 by Simon Marlow at 2002-05-09T13:38:04+00:00 [haddock @ 2002-05-09 13:38:04 by simonmar] Add dependency - - - - - 8d3d91ff by Simon Marlow at 2002-05-09T15:37:57+00:00 [haddock @ 2002-05-09 15:37:57 by simonmar] Add the changelog/release notes - - - - - f3960959 by Simon Marlow at 2002-05-09T15:47:47+00:00 [haddock @ 2002-05-09 15:47:47 by simonmar] mention the backquote-style of markup - - - - - 089fb6e6 by Simon Marlow at 2002-05-09T15:59:45+00:00 [haddock @ 2002-05-09 15:59:45 by simonmar] update - - - - - bdd3be0b by Simon Marlow at 2002-05-09T15:59:56+00:00 [haddock @ 2002-05-09 15:59:56 by simonmar] Document changes since 0.1 - - - - - 00fc4af8 by Simon Marlow at 2002-05-10T08:22:48+00:00 [haddock @ 2002-05-10 08:22:48 by simonmar] oops, update to version 0.2 - - - - - a8a79041 by Simon Marlow at 2002-05-10T16:05:08+00:00 [haddock @ 2002-05-10 16:05:08 by simonmar] Only include a mini-contents if there are 2 or more sections - - - - - 06653319 by Simon Marlow at 2002-05-13T09:13:12+00:00 [haddock @ 2002-05-13 09:13:12 by simonmar] fix typos - - - - - 1402b19b by Simon Marlow at 2002-05-13T10:14:22+00:00 [haddock @ 2002-05-13 10:14:22 by simonmar] Allow backquote as the right-hand quote as well as the left-hand quote, as suggested by Dean Herrington. Clean up the grammar a litte. - - - - - dcd5320d by Simon Marlow at 2002-05-13T10:44:10+00:00 [haddock @ 2002-05-13 10:44:10 by simonmar] a couple more things, prioritise a bit - - - - - a90130c4 by Simon Marlow at 2002-05-13T15:19:03+00:00 [haddock @ 2002-05-13 15:19:03 by simonmar] Cope with datatypes which have documentation on the constructor but not the type itself, and records which have documentation on the fields but not the constructor. (Thanks to Ross Paterson for pointing out the bugs). - - - - - a774d432 by Simon Marlow at 2002-05-13T15:20:54+00:00 [haddock @ 2002-05-13 15:20:54 by simonmar] Fix one of the record examples - - - - - 2d1d5218 by Simon Marlow at 2002-05-15T12:44:35+00:00 [haddock @ 2002-05-15 12:44:35 by simonmar] Preserve the newline before a bird-track, but only within a paragraph. - - - - - 1554c09a by Simon Marlow at 2002-05-15T13:03:02+00:00 [haddock @ 2002-05-15 13:03:01 by simonmar] Reworking of the internals to support documenting function arguments (the Most Wanted new feature by the punters). The old method of keeping parsed documentation in a Name -> Doc mapping wasn't going to cut it for anntations on type components, where there's no name to attach the documentation to, so I've moved to storing all the documentation in the abstract syntax. Previously some of the documentation was left in the abstract syntax by the parser, but was later extracted into the mapping. In order to avoid having to parameterise the abstract syntax over the type of documentation stored in it, we have to parse the documentation at the same time as we parse the Haskell source (well, I suppose we could store 'Either String Doc' in the HsSyn, but that's clunky). One upshot is that documentation is now parsed eagerly, and documentation parse errors are fatal (but have better line numbers in the error message). The new story simplifies matters for the code that processes the source modules, because we don't have to maintain the extra Name->Doc mapping, and it should improve efficiency a little too. New features: - Function arguments and return values can now have doc annotations. - If you refer to a qualified name in a doc string, eg. 'IO.putStr', then Haddock will emit a hyperlink even if the identifier is not in scope, so you don't have to make sure everything referred to from the documentation is imported. - several bugs & minor infelicities fixed. - - - - - 57344dc3 by Simon Marlow at 2002-05-15T13:03:19+00:00 [haddock @ 2002-05-15 13:03:19 by simonmar] Bump to version 0.3 - - - - - b2791812 by Simon Marlow at 2002-05-15T13:03:41+00:00 [haddock @ 2002-05-15 13:03:41 by simonmar] update - - - - - fead183e by Simon Marlow at 2002-05-15T13:10:15+00:00 [haddock @ 2002-05-15 13:10:15 by simonmar] Rename Foo.hs to Test.hs, and add a Makefile - - - - - b0b1f89f by Simon Marlow at 2002-05-15T13:16:07+00:00 [haddock @ 2002-05-15 13:16:07 by simonmar] - Remove the note about function argument docs not being implemented - Note that qualified identifiers can be used to point to entities that aren't in scope. - - - - - 5665f31a by Simon Marlow at 2002-05-15T13:28:46+00:00 [haddock @ 2002-05-15 13:28:46 by simonmar] Patch to add support for GHC-style primitive strings ".."#, from Ross Paterson. - - - - - 0564505d by Simon Marlow at 2002-05-17T10:51:57+00:00 [haddock @ 2002-05-17 10:51:57 by simonmar] Fix bugs in qualified name handling (A.B.f was returned as B.f) - - - - - 10e7311c by Simon Marlow at 2002-05-21T10:24:52+00:00 [haddock @ 2002-05-21 10:24:52 by simonmar] - Use an alternate tabular layout for datatypes, which is more compact - Fix some problems with the function argument documentation - - - - - 2f91c2a6 by Simon Marlow at 2002-05-21T10:27:40+00:00 [haddock @ 2002-05-21 10:27:40 by simonmar] add a few more test cases - - - - - 01c2ddd2 by Simon Marlow at 2002-05-21T10:28:33+00:00 [haddock @ 2002-05-21 10:28:33 by simonmar] Rearrange a bit, and add support for tabular datatype rendering - - - - - a4e4c5f8 by Simon Marlow at 2002-05-27T09:03:52+00:00 [haddock @ 2002-05-27 09:03:51 by simonmar] Lots of changes: - instances of a class are listed with the class, and instances involving a datatype are listed with that type. Derived instances aren't included at the moment: the calculation to find the instance head for a derived instance is non-trivial. - some formatting changes; use rows with specified height rather than cellspacing in some places. - various fixes (source file links were wrong, amongst others) - - - - - 48722e68 by Simon Marlow at 2002-05-27T12:30:38+00:00 [haddock @ 2002-05-27 12:30:37 by simonmar] - Put function arguments *before* the doc for the function, as suggested by Sven Panne. This looks nicer when the function documentation is long. - Switch to using bold for binders at the definition site, and use underline for keywords. This makes the binder stand out more. - - - - - 657204d2 by Simon Marlow at 2002-05-27T13:19:49+00:00 [haddock @ 2002-05-27 13:19:49 by simonmar] Fix bug: we weren't renaming HsDocCommentNamed in renameDecl - - - - - 592aae66 by Simon Marlow at 2002-05-27T14:10:27+00:00 [haddock @ 2002-05-27 14:10:27 by simonmar] Fix some bugs in the rendering of qualified type signatures. - - - - - 69c8f763 by Simon Marlow at 2002-05-27T14:36:45+00:00 [haddock @ 2002-05-27 14:36:45 by simonmar] warning message tweak - - - - - 16e64e21 by Simon Marlow at 2002-05-27T14:53:53+00:00 [haddock @ 2002-05-27 14:53:53 by simonmar] hyperlinked identifiers should be in <tt> - - - - - 8d5e4783 by Simon Marlow at 2002-05-27T15:56:45+00:00 [haddock @ 2002-05-27 15:56:45 by simonmar] Do something sensible for modules which don't export anything (except instances). - - - - - 9d3ef811 by Simon Marlow at 2002-05-28T10:12:50+00:00 [haddock @ 2002-05-28 10:12:50 by simonmar] Rename the module documentation properly (bug reported by Sven Panne). - - - - - ef03a1cc by Simon Marlow at 2002-05-28T10:13:04+00:00 [haddock @ 2002-05-28 10:13:04 by simonmar] Add some more test cases - - - - - 92baa0e8 by Simon Marlow at 2002-05-28T11:17:55+00:00 [haddock @ 2002-05-28 11:17:55 by simonmar] If an identifier doesn't lex, then just replace it by a DocString. - - - - - a3156213 by Simon Marlow at 2002-05-28T16:16:19+00:00 [haddock @ 2002-05-28 16:16:19 by simonmar] Only link to names in the current module which are actually listed in the documentation. A name may be exported but not present in the documentation if it is exported as part of a 'module M' export specifier. - - - - - 31acf941 by Simon Marlow at 2002-05-28T16:17:11+00:00 [haddock @ 2002-05-28 16:17:11 by simonmar] update - - - - - 7e474ebf by Sigbjorn Finne at 2002-05-28T22:42:08+00:00 [haddock @ 2002-05-28 22:42:08 by sof] Handle lone occurrences of '/', e.g., -- | This/that. [did this in the lexer rather than in the parser, as I couldn't see a way not to introduce an S/R conflict that way.] - - - - - 093f7e53 by Simon Marlow at 2002-05-29T09:09:49+00:00 [haddock @ 2002-05-29 09:09:49 by simonmar] Back out previous change until we can find a better way to do this. - - - - - 9234389c by Simon Marlow at 2002-05-29T13:19:06+00:00 [haddock @ 2002-05-29 13:19:06 by simonmar] Make the markup syntax a little more friendly: - single quotes are now interpreted literally unless they surround a valid Haskell identifier. So for example now there's no need to escape a single quote used as an apostrophe. - text to the right of a bird track is now literal (if you want marked-up text in a code block, use @...@). - - - - - b3333526 by Simon Marlow at 2002-05-29T13:38:51+00:00 [haddock @ 2002-05-29 13:38:51 by simonmar] Document recent changes to markup syntax - - - - - f93641d6 by Simon Marlow at 2002-05-29T15:27:18+00:00 [haddock @ 2002-05-29 15:27:18 by simonmar] Include the instances in abstract data types too - - - - - 613f21e3 by Simon Marlow at 2002-06-03T13:05:58+00:00 [haddock @ 2002-06-03 13:05:57 by simonmar] Allow exporting of individual class methods and record selectors. For these we have to invent the correct type signature, which we do in the simplest possible way (i.e. no context reduction nonsense in the class case). - - - - - 14b36807 by Simon Marlow at 2002-06-03T13:20:00+00:00 [haddock @ 2002-06-03 13:20:00 by simonmar] Fix linking to qualified names again (thanks to Sven Panne for pointing out the bug). - - - - - 95b10eac by Simon Marlow at 2002-06-03T13:46:48+00:00 [haddock @ 2002-06-03 13:46:48 by simonmar] Fix for exporting record selectors from a newtype declaration - - - - - 272f932e by Simon Marlow at 2002-06-03T13:56:38+00:00 [haddock @ 2002-06-03 13:56:38 by simonmar] update to version 0.3 - - - - - 1c0a3bed by Simon Marlow at 2002-06-03T14:05:07+00:00 [haddock @ 2002-06-03 14:05:07 by simonmar] Add changes in version 0.3 - - - - - 145b4626 by Simon Marlow at 2002-06-03T14:12:38+00:00 [haddock @ 2002-06-03 14:12:38 by simonmar] Render class names as proper binders - - - - - 052106b3 by Simon Marlow at 2002-06-03T14:15:10+00:00 [haddock @ 2002-06-03 14:15:10 by simonmar] update, and separate into bugs, features, and cosmetic items. - - - - - 854f4914 by Simon Marlow at 2002-06-03T14:16:13+00:00 [haddock @ 2002-06-03 14:16:13 by simonmar] More test cases - - - - - 466922c8 by Simon Marlow at 2002-06-03T14:16:56+00:00 [haddock @ 2002-06-03 14:16:56 by simonmar] Example from the paper - - - - - 9962a045 by Simon Marlow at 2002-06-03T14:17:49+00:00 [haddock @ 2002-06-03 14:17:49 by simonmar] A debugging version of the style-sheet, which gives some tables coloured backgrounds so we can see what's going on. - - - - - f16b79db by Simon Marlow at 2002-06-03T14:19:46+00:00 [haddock @ 2002-06-03 14:19:46 by simonmar] typo - - - - - 620db27b by Simon Marlow at 2002-06-03T14:48:32+00:00 [haddock @ 2002-06-03 14:48:32 by simonmar] oops, fix markup bugs - - - - - 53fd105c by Simon Marlow at 2002-06-05T09:05:07+00:00 [haddock @ 2002-06-05 09:05:07 by simonmar] Keep foreign imports when there is no export list (bug reported by Sven Panne). - - - - - 6d98989c by Simon Marlow at 2002-06-05T09:12:02+00:00 [haddock @ 2002-06-05 09:12:02 by simonmar] Identifiers in single quotes can be symbol names too (bug reported by Hal Daume). - - - - - 001811e5 by Sven Panne at 2002-06-08T14:03:36+00:00 [haddock @ 2002-06-08 14:03:36 by panne] Tiny workaround for the fact that Haddock currently ignores HsImportSpecs: Let the local_orig_env take precedence. This is no real solution at all, but improves things sometimes, e.g. in my GLUT documentation. :-) - - - - - 504d19c9 by Simon Marlow at 2002-06-11T09:23:25+00:00 [haddock @ 2002-06-11 09:23:25 by simonmar] portability nit - - - - - e13b5af4 by Simon Marlow at 2002-06-20T12:38:07+00:00 [haddock @ 2002-06-20 12:38:07 by simonmar] Empty declaration fixes. - - - - - f467a9b6 by Simon Marlow at 2002-06-20T12:39:02+00:00 [haddock @ 2002-06-20 12:39:01 by simonmar] Add support for a "prologue" - a description for the whole library, placed on the contents page before the module list. - - - - - b8dbfe20 by Simon Marlow at 2002-06-21T12:43:06+00:00 [haddock @ 2002-06-21 12:43:06 by simonmar] When we have a single code block paragraph, don't place it in <pre>..</pre>, just use <tt>..</tt> to avoid generating extra vertical white space in some browsers. - - - - - 4831dbbd by Simon Marlow at 2002-06-21T15:50:42+00:00 [haddock @ 2002-06-21 15:50:42 by simonmar] Add support for reading and writing interface files(!) This turned out to be quite easy, and necessary to get decent hyperlinks between the documentation for separate packages in the libraries. The functionality isn't quite complete yet: for a given package of modules, you'd like to say "the HTML for these modules lives in directory <dir>" (currently they are assumed to be all in the same place). Two new flags: --dump-interface=FILE dump an interface file in FILE --read-interface=FILE read interface from FILE an interface file describes *all* the modules being processed. Only the exported names are kept in the interface: if you re-export a name from a module in another interface the signature won't be copied. This is a compromise to keep the size of the interfaces sensible. Also, I added another useful option: --no-implicit-prelude avoids trying to import the Prelude. Previously this was the default, but now importing the Prelude from elsewhere makes sense if you also read in an interface containing the Prelude module, so Haddock imports the Prelude implicitly according to the Haskell spec. - - - - - d3640a19 by Sven Panne at 2002-06-23T14:54:00+00:00 [haddock @ 2002-06-23 14:54:00 by panne] Make it compile with newer GHCs - - - - - 780c506b by Sven Panne at 2002-06-23T15:44:31+00:00 [haddock @ 2002-06-23 15:44:31 by panne] Cleaned up build root handling and added more docs - - - - - 45290d2e by Simon Marlow at 2002-06-24T14:37:43+00:00 [haddock @ 2002-06-24 14:37:42 by simonmar] When reading an interface, allow a file path offset to be specified which represents the path to the HTML files for the modules specified by that interface. The path may be either relative (to the location of the HTML for this package), or absolute. The syntax is --read-interface=PATH,FILE where PATH is the path to the HTML, and FILE is the filename containing the interface. - - - - - 4e2b9ae6 by Simon Marlow at 2002-07-03T16:01:08+00:00 [haddock @ 2002-07-03 16:01:07 by simonmar] Handle import specs properly, include 'hiding'. Haddock now has a complete implementation of the Haskell module system (more or less; I won't claim it's 100% correct). - - - - - 9a9aa1a8 by Simon Marlow at 2002-07-03T16:18:16+00:00 [haddock @ 2002-07-03 16:18:16 by simonmar] Update - - - - - 560c3026 by Simon Marlow at 2002-07-04T14:56:10+00:00 [haddock @ 2002-07-04 14:56:10 by simonmar] Clean up the code that constructs the exported declarations, and fix a couple of bugs along the way. Now if you import a class hiding one of the methods, then re-export the class, the version in the documentation will correctly have the appropriate method removed. - - - - - 2c26e77d by Simon Marlow at 2002-07-04T15:26:13+00:00 [haddock @ 2002-07-04 15:26:13 by simonmar] More bugfixes to the export handling - - - - - 03e0710d by Simon Marlow at 2002-07-09T10:12:10+00:00 [haddock @ 2002-07-09 10:12:10 by simonmar] Don't require that the list type comes from "Prelude" for it to be treated as special syntax (sometimes it comes from Data.List or maybe even GHC.Base). - - - - - 44f3891a by Simon Marlow at 2002-07-09T10:12:51+00:00 [haddock @ 2002-07-09 10:12:51 by simonmar] commented-out debugging code - - - - - 97280873 by Krasimir Angelov at 2002-07-09T16:33:33+00:00 [haddock @ 2002-07-09 16:33:31 by krasimir] 'Microsoft HTML Help' support - - - - - 3dc04655 by Simon Marlow at 2002-07-10T09:40:56+00:00 [haddock @ 2002-07-10 09:40:56 by simonmar] Fix for rendering of the (->) type constructor, from Ross Paterson. - - - - - c9f149c6 by Simon Marlow at 2002-07-10T10:26:11+00:00 [haddock @ 2002-07-10 10:26:11 by simonmar] Tweaks to the MS Help support: the extra files are now only generated if you ask for them (--ms-help). - - - - - e8acc1e6 by Simon Marlow at 2002-07-10T10:57:10+00:00 [haddock @ 2002-07-10 10:57:10 by simonmar] Document all the new options since 0.3 - - - - - 8bb85544 by Simon Marlow at 2002-07-10T10:58:31+00:00 [haddock @ 2002-07-10 10:58:31 by simonmar] Sort the options a bit - - - - - abc0dd59 by Simon Marlow at 2002-07-15T09:19:38+00:00 [haddock @ 2002-07-15 09:19:38 by simonmar] Fix a bug in mkExportItems when processing a module without an explicit export list. We were placing one copy of a declaration for each binder in the declaration, which for a data type would mean one copy of the whole declaration per constructor or record selector. - - - - - dde65bb9 by Simon Marlow at 2002-07-15T09:54:16+00:00 [haddock @ 2002-07-15 09:54:16 by simonmar] merge rev. 1.35 - - - - - bd7eb8c4 by Simon Marlow at 2002-07-15T10:14:31+00:00 [haddock @ 2002-07-15 10:14:30 by simonmar] Be a bit more liberal in the kind of commenting styles we allow, as suggested by Malcolm Wallace. Mostly this consists of allowing doc comments either side of a separator token. In an export list, a section heading is now allowed before the comma, as well as after it. eg. module M where ( T(..) -- * a section heading , f -- * another section heading , g ) In record fields, doc comments are allowed anywhere (previously a doc-next was allowed only after the comma, and a doc-before was allowed only before the comma). eg. data R = C { -- | describes 'f' f :: Int -- | describes 'g' , g :: Int } - - - - - 8f6dfe34 by Simon Marlow at 2002-07-15T10:21:56+00:00 [haddock @ 2002-07-15 10:21:56 by simonmar] Mention alternative commenting styles. - - - - - fc515bb7 by Simon Marlow at 2002-07-15T16:16:50+00:00 [haddock @ 2002-07-15 16:16:50 by simonmar] Allow multiple sections/subsections before and after a comma in the export list. Also at the same time I made the syntax a little stricter (multiple commas now aren't allowed between export specs). - - - - - 80a97e74 by Simon Marlow at 2002-07-19T09:13:10+00:00 [haddock @ 2002-07-19 09:13:10 by simonmar] Allow special id's ([], (), etc.) to be used in an import declaration. - - - - - a69d7378 by Simon Marlow at 2002-07-19T09:59:02+00:00 [haddock @ 2002-07-19 09:59:02 by simonmar] Allow special id's ([], (), etc.) to be used in an import declarations. - - - - - d205fa60 by Simon Marlow at 2002-07-19T10:00:16+00:00 [haddock @ 2002-07-19 10:00:16 by simonmar] Relax the restrictions which require doc comments to be followed by semi colons - in some cases this isn't necessary. Now you can write module M where { -- | some doc class C where {} } without needing to put a semicolon before the class declaration. - - - - - e9301e14 by Simon Marlow at 2002-07-23T08:24:09+00:00 [haddock @ 2002-07-23 08:24:09 by simonmar] A new TODO list item - - - - - e5d77586 by Simon Marlow at 2002-07-23T08:40:56+00:00 [haddock @ 2002-07-23 08:40:56 by simonmar] - update the acknowledgements - remove the paragraph that described how to use explicit layout with doc comments; it isn't relevant any more. - - - - - 78a94137 by Simon Marlow at 2002-07-23T08:43:02+00:00 [haddock @ 2002-07-23 08:43:02 by simonmar] more tests - - - - - 5c320927 by Simon Marlow at 2002-07-23T08:43:26+00:00 [haddock @ 2002-07-23 08:43:26 by simonmar] Updates for version 0.4 - - - - - 488e99ae by Simon Marlow at 2002-07-23T09:10:46+00:00 [haddock @ 2002-07-23 09:10:46 by simonmar] Fix the %changelog (rpm complained that it wasn't in the right order) - - - - - a77bb373 by Simon Marlow at 2002-07-23T09:12:38+00:00 [haddock @ 2002-07-23 09:12:38 by simonmar] Another item for the TODO list - - - - - f1ec1813 by Simon Marlow at 2002-07-23T10:18:46+00:00 [haddock @ 2002-07-23 10:18:46 by simonmar] Add a version banner when invoked with -v - - - - - 1d44cadf by Simon Marlow at 2002-07-24T09:28:19+00:00 [haddock @ 2002-07-24 09:28:19 by simonmar] Remove ^Ms - - - - - 4d8d5e94 by Simon Marlow at 2002-07-24T09:42:18+00:00 [haddock @ 2002-07-24 09:42:17 by simonmar] Patches to quieten ghc -Wall, from those nice folks at Galois. - - - - - d6edc43e by Simon Marlow at 2002-07-25T14:37:29+00:00 [haddock @ 2002-07-25 14:37:28 by simonmar] Patch to allow simple hyperlinking to an arbitrary location in another module's documentation, from Volker Stolz. Now in a doc comment: #foo# creates <a name="foo"></a> And you can use the form "M\#foo" to hyperlink to the label 'foo' in module 'M'. Note that the backslash is necessary for now. - - - - - b34d18fa by Simon Marlow at 2002-08-02T09:08:22+00:00 [haddock @ 2002-08-02 09:08:22 by simonmar] The <TT> and <PRE> environments seem to use a font that is a little too small in IE. Compensate. (suggestion from Daan Leijen). - - - - - 8106b086 by Simon Marlow at 2002-08-02T09:25:23+00:00 [haddock @ 2002-08-02 09:25:20 by simonmar] Remove <P>..</P> from around list items, to reduce excess whitespace between the items of bulleted and ordered lists. (Suggestion from Daan Leijen). - - - - - c1acff8f by Simon Marlow at 2002-08-05T09:03:49+00:00 [haddock @ 2002-08-05 09:03:49 by simonmar] update - - - - - f968661c by Simon Marlow at 2002-11-11T09:32:57+00:00 [haddock @ 2002-11-11 09:32:57 by simonmar] Fix cut-n-pasto - - - - - 12d02619 by Simon Marlow at 2002-11-13T09:49:46+00:00 [haddock @ 2002-11-13 09:49:46 by simonmar] Small bugfix in the --read-interface option parsing from Brett Letner. - - - - - 30e32d5e by Ross Paterson at 2003-01-16T15:07:57+00:00 [haddock @ 2003-01-16 15:07:57 by ross] Adjust for the new exception libraries (as well as the old ones). - - - - - 871f65df by Sven Panne at 2003-02-20T21:31:40+00:00 [haddock @ 2003-02-20 21:31:40 by panne] * Add varsyms and consyms to index * Exclude empty entries from index - - - - - bc42cc87 by Sven Panne at 2003-02-24T21:26:29+00:00 [haddock @ 2003-02-24 21:26:29 by panne] Don't convert a "newtype" to a single-constructor "data" for non-abstractly exported types, they are quite different regarding strictness/pattern matching. Now a "data" without any constructors is only emitted for an abstractly exported type, regardless if it is actually a "newtype" or a "data". - - - - - 0c2a1d99 by Sven Panne at 2003-03-08T19:02:38+00:00 [haddock @ 2003-03-08 19:02:38 by panne] Fixed some broken/redirected/canonicalized links found by a very picky link checker. - - - - - 25459269 by Sven Panne at 2003-03-09T21:13:43+00:00 [haddock @ 2003-03-09 21:13:43 by panne] Don't append a fragment to non-defining index entries, only documents with a defining occurrence have a name anchor. - - - - - 6be4db86 by Sven Panne at 2003-03-10T21:34:25+00:00 [haddock @ 2003-03-10 21:34:24 by panne] Escape fragments. This fixes e.g. links to operators. - - - - - eb12972c by Ross Paterson at 2003-04-25T10:50:06+00:00 [haddock @ 2003-04-25 10:50:05 by ross] An 80% solution to generating derived instances. A complete solution would duplicate the instance inference logic, but if a type variable occurs as a constructor argument, then we can just propagate the derived class to the variable. But we know nothing of the constraints on any type variables that occur elsewhere. For example, the declarations data Either a b = Left a | Right b deriving (Eq, Ord) data Ptr a = Ptr Addr# deriving (Eq, Ord) newtype IORef a = IORef (STRef RealWorld a) deriving Eq yield the instances (Eq a, Eq b) => Eq (Either a b) (Ord a, Ord b) => Ord (Either a b) Eq (Ptr a) Ord (Ptr a) (??? a) => Eq (IORef a) The last example shows the limits of this local analysis. Note that a type variable may be in both categories: then we know a constraint, but there may be more, or a stronger constraint, e.g. data Tree a = Node a [Tree a] deriving Eq yields (Eq a, ??? a) => Eq (Tree a) - - - - - de886f78 by Simon Marlow at 2003-04-25T11:17:55+00:00 [haddock @ 2003-04-25 11:17:55 by simonmar] Some updates, including moving the derived instance item down to the bottom of the list now that Ross has contributed some code that does the job for common cases. - - - - - 1b52cffd by Simon Marlow at 2003-04-30T14:02:32+00:00 [haddock @ 2003-04-30 14:02:32 by simonmar] When installing on Windows, run cygpath over $(HADDOCKLIB) so that haddock (a mingw program, built by GHC) can understand it. You still need to be in a cygwin environment to run Haddock, because of the shell script wrapper. - - - - - d4f638de by Simon Marlow at 2003-05-06T10:04:47+00:00 [haddock @ 2003-05-06 10:04:47 by simonmar] Catch another case of a paragraph containing just a DocMonospaced that should turn into a DocCodeBlock. - - - - - 4162b2b9 by Simon Marlow at 2003-05-06T10:11:44+00:00 [haddock @ 2003-05-06 10:11:44 by simonmar] Add some more code-block tests. - - - - - 4f5802c8 by Simon Marlow at 2003-05-06T10:14:52+00:00 [haddock @ 2003-05-06 10:14:52 by simonmar] Don't turn a single DocCodeBlock into a DocMonospaced, because that tends to remove the line breaks in the code. - - - - - ef8c45f7 by Simon Marlow at 2003-05-21T15:07:21+00:00 [haddock @ 2003-05-21 15:07:21 by simonmar] Only omit the module contents when there are no section headings at all. - - - - - bcee1e75 by Sigbjorn Finne at 2003-05-30T16:50:45+00:00 [haddock @ 2003-05-30 16:50:45 by sof] cygpath: for now, steer clear of --mixed - - - - - 30567af3 by Sigbjorn Finne at 2003-05-30T17:59:28+00:00 [haddock @ 2003-05-30 17:59:28 by sof] oops, drop test defn from prev commit - - - - - b0856e7d by Simon Marlow at 2003-06-03T09:55:26+00:00 [haddock @ 2003-06-03 09:55:26 by simonmar] Two small fixes to make the output valid HTML 4.01 (transitional). Thanks to Malcolm Wallace for pointing out the problems. - - - - - 70e137ea by Simon Marlow at 2003-07-28T13:30:35+00:00 [haddock @ 2003-07-28 13:30:35 by simonmar] Add tests for a couple of bugs. - - - - - 122bd578 by Simon Marlow at 2003-07-28T13:31:25+00:00 [haddock @ 2003-07-28 13:31:25 by simonmar] Add documentation for anchors. - - - - - 0bd27cb2 by Simon Marlow at 2003-07-28T13:31:46+00:00 [haddock @ 2003-07-28 13:31:46 by simonmar] Update - - - - - 08052d42 by Simon Marlow at 2003-07-28T13:32:12+00:00 [haddock @ 2003-07-28 13:32:12 by simonmar] layout tweak. - - - - - 13942749 by Simon Marlow at 2003-07-28T13:33:03+00:00 [haddock @ 2003-07-28 13:33:03 by simonmar] Differentiate links to types/classes from links to variables/constructors with a prefix ("t:" and "v:" respectively). - - - - - d7f493b9 by Simon Marlow at 2003-07-28T13:35:17+00:00 [haddock @ 2003-07-28 13:35:16 by simonmar] When a module A exports another module's contents via 'module B', then modules which import entities from B re-exported by A should link to B.foo rather than A.foo. See examples/Bug2.hs. - - - - - d94cf705 by Simon Marlow at 2003-07-28T13:36:14+00:00 [haddock @ 2003-07-28 13:36:14 by simonmar] Update to version 0.5 - - - - - dbb776cd by Sven Panne at 2003-07-28T14:02:43+00:00 [haddock @ 2003-07-28 14:02:43 by panne] * Updated to version 0.5 * Automagically generate configure if it is not there - - - - - 6cfeee53 by Simon Marlow at 2003-07-28T14:32:43+00:00 [haddock @ 2003-07-28 14:32:42 by simonmar] Update to avoid using hslibs with GHC >= 5.04 - - - - - a1ce838f by Simon Marlow at 2003-07-28T14:33:37+00:00 [haddock @ 2003-07-28 14:33:37 by simonmar] Update for 0.5 - - - - - c0fe6493 by Simon Marlow at 2003-07-28T14:53:22+00:00 [haddock @ 2003-07-28 14:53:22 by simonmar] Markup fix - - - - - 6ea31596 by Sven Panne at 2003-07-28T16:40:45+00:00 [haddock @ 2003-07-28 16:40:45 by panne] Make it compile with GHC >= 6.01 - - - - - afcd30fc by Simon Marlow at 2003-07-30T15:04:52+00:00 [haddock @ 2003-07-30 15:04:52 by simonmar] Pay attention to import specs when building the the import env, as well as the orig env. This may fix some wrong links in documentation when import specs are being used. - - - - - 17c3137f by Simon Marlow at 2003-07-30T16:05:41+00:00 [haddock @ 2003-07-30 16:05:40 by simonmar] Rename instances based on the import_env for the module in which they are to be displayed. This should give, in many cases, better links for the types and classes mentioned in the instance head. This involves keeping around the import_env in the iface until the end, because instances are not collected up until all the modules have been processed. Fortunately it doesn't seem to affect performance much. Instance heads are now attached to ExportDecls, rather than the HTML backend passing around a separate mapping for instances. This is a cleanup. - - - - - 3d3b5c87 by Sven Panne at 2003-08-04T10:18:24+00:00 [haddock @ 2003-08-04 10:18:24 by panne] Don't print parentheses around one-element contexts - - - - - 9e3f3f2d by Simon Marlow at 2003-08-04T12:59:47+00:00 [haddock @ 2003-08-04 12:59:47 by simonmar] A couple of TODOs. - - - - - e9d8085c by Simon Marlow at 2003-08-05T14:10:31+00:00 [haddock @ 2003-08-05 14:10:31 by simonmar] I'm not sure why, but it seems that the index entries for non-defining occurrences of entities did not have an anchor - the link just pointed to the module. This fixes it. - - - - - ff5c7d6d by Simon Marlow at 2003-08-15T14:42:59+00:00 [haddock @ 2003-08-15 14:42:59 by simonmar] Convert the lexer to Alex, and fix a bug in the process. - - - - - 1aa077bf by Simon Marlow at 2003-08-15T15:00:18+00:00 [haddock @ 2003-08-15 15:00:18 by simonmar] Update - - - - - d3de1e38 by Simon Marlow at 2003-08-15T15:01:03+00:00 [haddock @ 2003-08-15 15:01:03 by simonmar] wibbles - - - - - b40ece3b by Simon Marlow at 2003-08-18T10:04:47+00:00 [haddock @ 2003-08-18 10:04:47 by simonmar] Lex the 'mdo' keyword as 'do'. - - - - - 8f9a1146 by Simon Marlow at 2003-08-18T11:48:24+00:00 [haddock @ 2003-08-18 11:48:24 by simonmar] Two bugs from Sven. - - - - - ea54ebc0 by Simon Marlow at 2003-08-18T11:48:46+00:00 [haddock @ 2003-08-18 11:48:46 by simonmar] Fixes to the new lexer. - - - - - d5f6a4b5 by Simon Marlow at 2003-08-19T09:09:03+00:00 [haddock @ 2003-08-19 09:09:03 by simonmar] Further wibbles to the syntax. - - - - - 6bbdadb7 by Sven Panne at 2003-08-26T18:45:35+00:00 [haddock @ 2003-08-26 18:45:35 by panne] Use autoreconf instead of autoconf - - - - - 32e889cb by Sven Panne at 2003-08-26T19:01:19+00:00 [haddock @ 2003-08-26 19:01:18 by panne] Made option handling a bit more consistent with other tools, in particular: Every program in fptools should output * version info on stdout and terminate successfully when -V or --version * usage info on stdout and terminate successfully when -? or --help * usage info on stderr and terminate unsuccessfully when an unknown option is given. - - - - - 5d156a91 by Sven Panne at 2003-08-26T19:20:55+00:00 [haddock @ 2003-08-26 19:20:55 by panne] Make it *very* clear that we terminate when given a -V/--version flag - - - - - e6577265 by Sven Panne at 2003-08-27T07:50:03+00:00 [haddock @ 2003-08-27 07:50:02 by panne] * Made -D a short option for --dump-interface. * Made -m a short option for --ms-help. * Made -n a short option for --no-implicit-prelude. * Made -c a short option for --css. * Removed DocBook options from executable (they didn't do anything), but mark them as reserved in the docs. Note that the short option for DocBook output is now -S (from SGML) instead of -d. The latter is now a short option for --debug. * The order of the Options in the documentation now matches the order printed by Haddock itself. Note: Although changing the names of options is often a bad idea, I'd really like to make the options for the programs in fptools more consistent and compatible to the ones used in common GNU programs. - - - - - d303ff98 by Simon Marlow at 2003-09-10T08:23:48+00:00 [haddock @ 2003-09-10 08:23:48 by simonmar] Add doc subdir. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 9a70e46a by Simon Marlow at 2003-09-10T08:24:32+00:00 [haddock @ 2003-09-10 08:24:32 by simonmar] Install these files in $(datadir), not $(libdir), since they're architecture independent. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - bbb87e7a by Simon Marlow at 2003-09-10T08:25:31+00:00 [haddock @ 2003-09-10 08:25:31 by simonmar] Haddock's supplementary HTML bits now live in $(datadir), not $(libdir). Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 3587c24b by Simon Marlow at 2003-09-22T10:34:38+00:00 [haddock @ 2003-09-22 10:34:38 by simonmar] Allow installing of docs. - - - - - d510b517 by Sven Panne at 2003-10-11T08:10:44+00:00 [haddock @ 2003-10-11 08:10:44 by panne] Include architecture-independent files in file list - - - - - 187d7618 by Sigbjorn Finne at 2003-10-20T17:19:24+00:00 [haddock @ 2003-10-20 17:19:22 by sof] support for i-parameters + zip comprehensions - - - - - b6c7a273 by Simon Marlow at 2003-11-03T14:24:24+00:00 [haddock @ 2003-11-03 14:24:24 by simonmar] Update TODO file. - - - - - 58513e33 by Simon Marlow at 2003-11-05T11:22:04+00:00 [haddock @ 2003-11-05 11:22:04 by simonmar] Remove the last of the uses of 'trace' to emit warnings, and tidy up a couple of places where duplicate warnings were being emitted. - - - - - 33a78846 by Simon Marlow at 2003-11-05T11:30:53+00:00 [haddock @ 2003-11-05 11:30:52 by simonmar] - Suppress warnings about unknown imported modules by default. - Add a -v/--verbose flag to re-enable these warnings. The general idea is to suppress the "Warning: unknown module: Prelude" warnings which most Haddock users will see every time, and which aren't terribly useful. - - - - - a969de7f by Simon Marlow at 2003-11-05T12:30:28+00:00 [haddock @ 2003-11-05 12:30:28 by simonmar] - Remove the emboldening of index entries for defining locations. This isn't useful, and breaks abstractions. - If an entity is re-exported by a module but the module doesn't include documentation for that entity (perhaps because it is re-exported by 'module M'), then don't attempt to hyperlink to the documentation from the index. Instead, just list that module in the index, to indicate that the entity is exported from there. - - - - - f14ea82a by Simon Marlow at 2003-11-05T15:15:59+00:00 [haddock @ 2003-11-05 15:15:59 by simonmar] Index overhaul: - no more separate type/class and variable/function indices - the index now makes a distinction between different entities with the same name. One example is a type constructor with the same name as a data constructor, but another example is simply a function with the same name exported by two different modules. For example, the index entry for 'catch' now looks like this: catch 1 (Function) Control.Exception 2 (Function) GHC.Exception, Prelude, System.IO, System.IO.Error making it clear that there are two different 'catch'es, but one of them is exported by several modules. - Each index page now has the index contents (A B C ...) at the top. Please let me know if you really hate any of this. - - - - - 01a25ca6 by Simon Marlow at 2003-11-05T15:16:38+00:00 [haddock @ 2003-11-05 15:16:38 by simonmar] Update - - - - - 1a7ccb86 by Simon Marlow at 2003-11-05T17:16:05+00:00 [haddock @ 2003-11-05 17:16:04 by simonmar] Support for generating a single unified index for several packages. --use-index=URL turns off normal index generation, causes Index links to point to URL. --gen-index generates an combined index from the specified interfaces. Currently doesn't work exactly right, because the interfaces don't contain the iface_reexported info. I'll need to fix that up. - - - - - a2bca16d by Simon Marlow at 2003-11-06T10:44:52+00:00 [haddock @ 2003-11-06 10:44:52 by simonmar] Include iface_reexported in the .haddock file. This unfortunately bloats the file (40% for base). If this gets to be a problem we can always apply the dictionary trick that GHC uses for squashing .hi files. - - - - - 0a09c293 by Simon Marlow at 2003-11-06T12:39:47+00:00 [haddock @ 2003-11-06 12:39:46 by simonmar] - Add definition lists, marked up like this: -- | This is a definition list: -- -- [@foo@] The description of @foo at . -- -- [@bar@] The description of @bar at . Cunningly, the [] characters are not treated specially unless a [ is found at the beginning of a paragraph, in which case the ] becomes special in the following text. - Add --use-contents and --gen-contents, along the lines of --use-index and --gen-index added yesterday. Now we can generate a combined index and contents for the whole of the hierarchical libraries, and in theory the index/contents on the system could be updated as new packages are added. - - - - - fe1b3460 by Simon Marlow at 2003-11-06T14:47:36+00:00 [haddock @ 2003-11-06 14:47:36 by simonmar] Remove the 'Parent' button - it is of dubious use, and often points into thin air. - - - - - db6d762f by Simon Marlow at 2003-11-06T16:48:14+00:00 [haddock @ 2003-11-06 16:48:11 by simonmar] - Include the OptHide setting in the interface, so we don't include hidden modules in the combined index/contents. - Add a -k/--package flag to set the package name for the current set of modules. The package name for each module is now shown in the right-hand column of the contents, in a combined contents page. - - - - - 7d71718b by Simon Marlow at 2003-11-06T16:50:28+00:00 [haddock @ 2003-11-06 16:50:28 by simonmar] Add -k/--package docs - - - - - ef43949d by Simon Marlow at 2003-11-06T16:51:23+00:00 [haddock @ 2003-11-06 16:51:23 by simonmar] Bump to 0.6 - - - - - 1c419e06 by Simon Marlow at 2003-11-06T16:51:50+00:00 [haddock @ 2003-11-06 16:51:50 by simonmar] update - - - - - 69422327 by Simon Marlow at 2003-11-10T14:41:06+00:00 [haddock @ 2003-11-10 14:41:05 by simonmar] Re-exporting names from a different package is problematic, because we don't have access to the full documentation for the entity. Currently Haddock just ignores entities with no documentation, but this results in bogus-looking empty documentation for many of the modules in the haskell98 package. So: - the documentation will now just list the name, as a link pointing to the location of the actual documentation. - now we don't attempt to link to these re-exported entities if they are referred to by the current module. Additionally: - If there is no documentation in the current module, include just the Synopsis section (rather than just the documentation section, as it was before). This just looks nicer and was on the TODO list. - - - - - 3c3fc433 by Simon Marlow at 2003-11-10T14:51:59+00:00 [haddock @ 2003-11-10 14:51:59 by simonmar] Fix for getReExports: take into account names which are not visible because they are re-exported from a different package. - - - - - 31c8437b by Simon Marlow at 2003-11-10T15:10:53+00:00 [haddock @ 2003-11-10 15:10:53 by simonmar] Version 0.6 changes - - - - - a7c2430b by Simon Marlow at 2003-11-10T15:15:58+00:00 [haddock @ 2003-11-10 15:15:58 by simonmar] getReExports: one error case that isn't - - - - - 00cc459c by Simon Marlow at 2003-11-10T16:15:19+00:00 [haddock @ 2003-11-10 16:15:18 by simonmar] copyright update - - - - - ca62408d by Simon Marlow at 2003-11-11T09:57:25+00:00 [haddock @ 2003-11-11 09:57:25 by simonmar] Version 0.6 - - - - - 3acbf818 by Simon Marlow at 2003-11-11T12:10:44+00:00 [haddock @ 2003-11-11 12:10:44 by simonmar] Go back to producing just the documentation section, rather than just the synopsis section, for a module with no documentation annotations. One reason is that the synopsis section tries to link each entity to its documentation on the same page. Also, the doc section anchors each entity, and it lists instances which the synopsis doesn't. - - - - - 6c90abc2 by Simon Marlow at 2003-11-12T10:03:39+00:00 [haddock @ 2003-11-12 10:03:39 by simonmar] 2002 -> 2003 - - - - - 090bbc4c by Simon Marlow at 2003-11-28T12:08:00+00:00 [haddock @ 2003-11-28 12:08:00 by simonmar] update - - - - - 8096a832 by Simon Marlow at 2003-11-28T12:09:58+00:00 [haddock @ 2003-11-28 12:09:58 by simonmar] Fix some of the problems with Haddock generating pages that are too wide. Now we only specify 'nowrap' when it is necessary to avoid a code box getting squashed up by the text to the right of it. - - - - - 35294929 by Sven Panne at 2003-12-29T17:16:31+00:00 [haddock @ 2003-12-29 17:16:31 by panne] Updated my email address - - - - - cdb697bf by Simon Marlow at 2004-01-08T10:14:24+00:00 [haddock @ 2004-01-08 10:14:24 by simonmar] Add instructions for using GHC to pre-process source for feeding to Haddock. - - - - - 8dfc491f by Simon Marlow at 2004-01-09T12:45:46+00:00 [haddock @ 2004-01-09 12:45:46 by simonmar] Add -optP-P to example ghc command line. - - - - - ac41b820 by Simon Marlow at 2004-02-03T11:02:03+00:00 [haddock @ 2004-02-03 11:02:03 by simonmar] Fix bug in index generation - - - - - f4e7edcb by Simon Marlow at 2004-02-10T11:51:16+00:00 [haddock @ 2004-02-10 11:51:16 by simonmar] Don't throw away whitespace at the beginning of a line (experimental fix). - - - - - 68e212d2 by Simon Marlow at 2004-02-10T12:10:08+00:00 [haddock @ 2004-02-10 12:10:08 by simonmar] Fix for previous commit: I now realise why the whitespace was stripped from the beginning of the line. Work around it. - - - - - e7d7f2df by Sven Panne at 2004-02-10T18:38:45+00:00 [haddock @ 2004-02-10 18:38:45 by panne] Make Haddock link with the latest relocated monad transformer package - - - - - 992d4225 by Simon Marlow at 2004-02-16T10:21:35+00:00 [haddock @ 2004-02-16 10:21:35 by simonmar] Add a TODO - - - - - 1ac55326 by Simon Marlow at 2004-03-12T11:33:39+00:00 [haddock @ 2004-03-12 11:33:39 by simonmar] Add an item. - - - - - 0478e903 by Simon Marlow at 2004-03-15T12:24:05+00:00 [haddock @ 2004-03-15 12:24:05 by simonmar] Add an item. - - - - - 6f26d21a by Simon Marlow at 2004-03-18T14:21:29+00:00 [haddock @ 2004-03-18 14:21:29 by simonmar] Fix URL - - - - - 19b6bb99 by Simon Marlow at 2004-03-22T14:09:03+00:00 [haddock @ 2004-03-22 14:09:03 by simonmar] getReExports was bogus: we should really look in the import_env to find the documentation for an entity which we are re-exporting without documentation. Suggested by: Ross Paterson (patch modified by me). - - - - - 5c756031 by Simon Marlow at 2004-03-24T09:42:11+00:00 [haddock @ 2004-03-24 09:42:10 by simonmar] hiding bug from Ross Paterson (fixed in rev 1.59 of Main.hs) - - - - - 1b692e6c by Simon Marlow at 2004-03-24T10:10:50+00:00 [haddock @ 2004-03-24 10:10:50 by simonmar] mkExportItems fix & simplification: we should be looking at the actual exported names (calculated earlier) to figure out which subordinates of a declaration are exported. This means that if you export a record, and name its fields separately in the export list, the fields will still be visible in the documentation for the constructor. - - - - - 90e5e294 by Simon Marlow at 2004-03-24T10:12:08+00:00 [haddock @ 2004-03-24 10:12:08 by simonmar] Make restrictCons take into account record field names too (removing a ToDo). - - - - - 2600efa4 by Simon Marlow at 2004-03-24T10:16:17+00:00 [haddock @ 2004-03-24 10:16:17 by simonmar] Record export tests. - - - - - 6a8575c7 by Simon Marlow at 2004-03-25T09:35:14+00:00 [haddock @ 2004-03-25 09:35:14 by simonmar] restrictTo: fix for restricting a newtype with a record field. - - - - - dcf55a8d by Simon Marlow at 2004-03-25T10:01:42+00:00 [haddock @ 2004-03-25 10:01:42 by simonmar] Fix duplicate instance bug - - - - - f49aa758 by Simon Marlow at 2004-03-25T10:02:41+00:00 [haddock @ 2004-03-25 10:02:41 by simonmar] Duplicate instance bug. - - - - - 7b87344c by Simon Marlow at 2004-03-25T10:29:56+00:00 [haddock @ 2004-03-25 10:29:56 by simonmar] If a name is imported from two places, one hidden and one not, choose the unhidden one to link to. Also, when there's only a hidden module to link to, don't try linking to it. - - - - - 40f44d7b by Simon Marlow at 2004-03-25T15:17:24+00:00 [haddock @ 2004-03-25 15:17:23 by simonmar] Add support for collaspible parts of the page, with a +/- button and a bit of JavaScript. Make the instances collapsible, and collapse them by default. This makes documentation with long lists of instances (eg. the Prelude) much easier to read. Maybe we should give other documentation sections the same treatment. - - - - - 9b64dc0f by Simon Marlow at 2004-03-25T15:20:55+00:00 [haddock @ 2004-03-25 15:20:55 by simonmar] Update - - - - - c2fff7f2 by Simon Marlow at 2004-03-25T15:45:10+00:00 [haddock @ 2004-03-25 15:45:10 by simonmar] Eliminate some unnecessary spaces in the HTML rendering - - - - - b7948ff0 by Simon Marlow at 2004-03-25T16:00:37+00:00 [haddock @ 2004-03-25 16:00:36 by simonmar] Remove all that indentation in the generated HTML to keep the file sizes down. - - - - - da2bb4ca by Sven Panne at 2004-03-27T09:57:58+00:00 [haddock @ 2004-03-27 09:57:57 by panne] Added the new-born haddock.js to the build process and the documentation. - - - - - b99e6f8c by Sven Panne at 2004-03-27T10:32:20+00:00 [haddock @ 2004-03-27 10:32:20 by panne] "type" is a required attribute of the "script" element - - - - - 562b185a by Sven Panne at 2004-03-27T12:52:34+00:00 [haddock @ 2004-03-27 12:52:34 by panne] Add a doctype for the contents page, too. - - - - - f6a99c2d by Simon Marlow at 2004-04-14T10:03:25+00:00 [haddock @ 2004-04-14 10:03:25 by simonmar] fix for single-line comment syntax - - - - - de366303 by Simon Marlow at 2004-04-20T13:08:04+00:00 [haddock @ 2004-04-20 13:08:04 by simonmar] Allow a 'type' declaration to include documentation comments. These will be ignored by Haddock, but at least one user (Johannes Waldmann) finds this feature useful, and it's easy to add. - - - - - fd78f51e by Simon Marlow at 2004-05-07T15:14:56+00:00 [haddock @ 2004-05-07 15:14:56 by simonmar] - update copyright - add version to abstract - - - - - 59f53e32 by Sven Panne at 2004-05-09T14:39:53+00:00 [haddock @ 2004-05-09 14:39:53 by panne] Fix the fix for single-line comment syntax, ------------------------------------------- is now a valid comment line again. - - - - - 8b18f2fe by Simon Marlow at 2004-05-10T10:11:51+00:00 [haddock @ 2004-05-10 10:11:51 by simonmar] Update - - - - - 225a491d by Ross Paterson at 2004-05-19T13:10:23+00:00 [haddock @ 2004-05-19 13:10:23 by ross] Make the handling of "deriving" slightly smarter, by ignoring data constructor arguments that are identical to the lhs. Now handles things like data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving ... - - - - - 37588686 by Mike Thomas at 2004-05-21T06:38:14+00:00 [haddock @ 2004-05-21 06:38:14 by mthomas] Windows exe extensions (bin remains for Unix). - - - - - cf2b9152 by Simon Marlow at 2004-05-25T09:34:54+00:00 [haddock @ 2004-05-25 09:34:54 by simonmar] Add some TODO items - - - - - 4d29cdfc by Simon Marlow at 2004-05-25T10:41:46+00:00 [haddock @ 2004-05-25 10:41:46 by simonmar] Complain if -h is used with --gen-index or --gen-contents, because it'll overwrite the new index/contents. - - - - - 2e0771e0 by Mike Thomas at 2004-05-28T20:17:55+00:00 [haddock @ 2004-05-28 20:17:55 by mthomas] Windows: search for templates in executable directory. Unix: Haddock tries cwd first rather than error if no -l arg. - - - - - 8d10bde1 by Sven Panne at 2004-06-05T16:53:34+00:00 [haddock @ 2004-06-05 16:53:34 by panne] Misc. rpm spec file cleanup, including: * make BuildRoot handling more consistent * added default file attributes * consistent defines and tags - - - - - 59974349 by Sven Panne at 2004-06-05T18:01:00+00:00 [haddock @ 2004-06-05 18:01:00 by panne] More rpm spec file cleanup, including: * added some BuildRequires * changed packager to me, so people can complain at the right place :-] * consistently refer to haskell.org instead of www.haskell.org - - - - - b94d4903 by Simon Marlow at 2004-07-01T11:08:58+00:00 [haddock @ 2004-07-01 11:08:57 by simonmar] Update to the +/- buttons: use a resized image rather than a <button>. Still seeing some strange effects in Konqueror, so might need to use a fixed-size image instead. - - - - - d5278f67 by Sven Panne at 2004-07-04T15:15:55+00:00 [haddock @ 2004-07-04 15:15:55 by panne] Install pictures for +/- pictures, too (JPEG is a strange format for graphics like this, I would have expected GIF or PNG here.) Things look fine with Konqueror and Netscape on Linux now, the only downside is that the cursor doesn't change when positioned above the "button". - - - - - 46dec6c5 by Sven Panne at 2004-07-13T17:59:28+00:00 [haddock @ 2004-07-13 17:59:28 by panne] A quote is a valid part of a Haskell identifier, but it would interfere with an ECMA script string delimiter, so escape it there. - - - - - 1d7bc432 by Simon Marlow at 2004-07-22T08:54:06+00:00 [haddock @ 2004-07-22 08:54:06 by simonmar] Add single quote to $ident, so you can say eg. 'foldl'' to refer to foldl' (the longest match rule is our friend). Bug reported by Adrian Hey <ahey at iee.org> - - - - - f183618b by Krasimir Angelov at 2004-07-27T22:59:35+00:00 [haddock @ 2004-07-27 22:58:23 by krasimir] Add basic support for Microsoft HTML Help 2.0 - - - - - d515d0c2 by Krasimir Angelov at 2004-07-27T23:02:36+00:00 [haddock @ 2004-07-27 23:02:36 by krasimir] escape names in the index - - - - - a5f1be23 by Krasimir Angelov at 2004-07-27T23:05:21+00:00 [haddock @ 2004-07-27 23:05:21 by krasimir] Add jsFile, plusFile and minusFile to the file list - - - - - c4fb4881 by Krasimir Angelov at 2004-07-28T22:12:10+00:00 [haddock @ 2004-07-28 22:12:09 by krasimir] bugfix. Move contentsHtmlFile, indexHtmlFile and subIndexHtmlFile functions to HaddockUtil.hs module to make them accessible from HaddockHH2.hs - - - - - 64d30b1d by Krasimir Angelov at 2004-07-30T22:15:47+00:00 [haddock @ 2004-07-30 22:15:45 by krasimir] more stuffs - support for separated compilation of packages - the contents page now uses DHTML TreeView - fixed copyFile bug - - - - - 133c8c5c by Krasimir Angelov at 2004-07-31T12:04:38+00:00 [haddock @ 2004-07-31 12:04:37 by krasimir] make the DHtmlTree in contents page more portable. The +/- buttons are replaced with new images which looks more beatiful. - - - - - 79040963 by Krasimir Angelov at 2004-07-31T13:10:20+00:00 [haddock @ 2004-07-31 13:10:20 by krasimir] Make DHtmlTree compatible with Mozila browser - - - - - 1a55dc90 by Krasimir Angelov at 2004-07-31T14:52:55+00:00 [haddock @ 2004-07-31 14:52:55 by krasimir] fix - - - - - 85ce0237 by Krasimir Angelov at 2004-07-31T14:53:28+00:00 [haddock @ 2004-07-31 14:53:28 by krasimir] HtmlHelp 1.x - - - - - 3c0c53ba by Krasimir Angelov at 2004-07-31T20:35:21+00:00 [haddock @ 2004-07-31 20:35:21 by krasimir] Added support for DevHelp - - - - - d42b5af1 by Krasimir Angelov at 2004-07-31T21:17:51+00:00 [haddock @ 2004-07-31 21:17:51 by krasimir] Document new features in HtmlHelp - - - - - 790fe21e by Krasimir Angelov at 2004-08-01T15:14:02+00:00 [haddock @ 2004-08-01 15:14:02 by krasimir] add missing imports - - - - - fd7cc6bc by Krasimir Angelov at 2004-08-01T19:52:08+00:00 [haddock @ 2004-08-01 19:52:06 by krasimir] fix some bugs. Now I have got the entire libraries documentation in HtmlHelp 2.0 format. - - - - - 94ad7ac8 by Krasimir Angelov at 2004-08-01T19:53:50+00:00 [haddock @ 2004-08-01 19:53:50 by krasimir] I forgot to add the new +/- images - - - - - f0c65388 by Krasimir Angelov at 2004-08-02T16:25:53+00:00 [haddock @ 2004-08-02 16:25:53 by krasimir] Add root node to the table of contents. All modules in tree are not children of the root - - - - - f50bd85d by Sven Panne at 2004-08-02T18:17:46+00:00 [haddock @ 2004-08-02 18:17:46 by panne] Mainly DocBook fixes - - - - - 09527ce3 by Sven Panne at 2004-08-02T20:02:29+00:00 [haddock @ 2004-08-02 20:02:29 by panne] Fixed -o/--odir handling. Generating the output, especially the directory handling, is getting a bit convoluted nowadays... - - - - - c8fbacfa by Sven Panne at 2004-08-02T20:31:13+00:00 [haddock @ 2004-08-02 20:31:13 by panne] Warning police - - - - - 37830bff by Sven Panne at 2004-08-02T20:32:29+00:00 [haddock @ 2004-08-02 20:32:28 by panne] Nuked dead code - - - - - 13847171 by Sven Panne at 2004-08-02T21:12:27+00:00 [haddock @ 2004-08-02 21:12:25 by panne] Use pathJoin instead of low-level list-based manipulation for FilePaths - - - - - c711d61e by Sven Panne at 2004-08-02T21:16:02+00:00 [haddock @ 2004-08-02 21:16:02 by panne] Removed WinDoze CRs - - - - - b1f7dc88 by Sven Panne at 2004-08-03T19:35:59+00:00 [haddock @ 2004-08-03 19:35:59 by panne] Fixed spelling of "http-equiv" attribute - - - - - dd5f394e by Sven Panne at 2004-08-03T19:44:03+00:00 [haddock @ 2004-08-03 19:44:03 by panne] Pacify W3C validator: * Added document encoding (currently UTF-8, not sure if this is completely correct) * Fixed syntax of `id' attributes * Added necessary `alt' attribute for +/- images Small layout improvement: * Added space after +/- images (still not perfect, but better than before) - - - - - 919c47c6 by Sigbjorn Finne at 2004-08-03T19:45:11+00:00 [haddock @ 2004-08-03 19:45:11 by sof] make it compile with <= ghc-6.1 - - - - - 4d6f01d8 by Sigbjorn Finne at 2004-08-03T19:45:30+00:00 [haddock @ 2004-08-03 19:45:30 by sof] ffi wibble - - - - - 4770643a by Sven Panne at 2004-08-03T20:47:46+00:00 [haddock @ 2004-08-03 20:47:46 by panne] Fixed CSS for button style. Note that only "0" is a valid measure without a unit! - - - - - 14aaf2e5 by Sven Panne at 2004-08-03T21:07:59+00:00 [haddock @ 2004-08-03 21:07:58 by panne] Improved spacing of dynamic module tree - - - - - 97c3579a by Simon Marlow at 2004-08-09T11:03:04+00:00 [haddock @ 2004-08-09 11:03:04 by simonmar] Add FormatVersion Patch submitted by: George Russell <ger at informatik.uni-bremen.de> - - - - - af7f8c03 by Simon Marlow at 2004-08-09T11:55:07+00:00 [haddock @ 2004-08-09 11:55:05 by simonmar] Add support for a short description for each module, which is included in the contents. The short description should be given in a "Description: " field of the header. Included in this patch are changes that make the format of the header a little more flexible. From the comments: -- all fields in the header are optional and have the form -- -- [spaces1][field name][spaces] ":" -- [text]"\n" ([spaces2][space][text]"\n" | [spaces]"\n")* -- where each [spaces2] should have [spaces1] as a prefix. -- -- Thus for the key "Description", -- -- > Description : this is a -- > rather long -- > -- > description -- > -- > The module comment starts here -- -- the value will be "this is a .. description" and the rest will begin -- at "The module comment". The header fields must be in the following order: Module, Description, Copyright, License, Maintainer, Stability, Portability. Patches submitted by: George Russell <ger at informatik.uni-bremen.de>, with a few small changes be me, mostly to merge with other recent changes. ToDo: document the module header. - - - - - 7b865ad3 by Simon Marlow at 2004-08-10T14:09:57+00:00 [haddock @ 2004-08-10 14:09:57 by simonmar] Fixes for DevHelp/HtmlHelp following introduction of short module description. - - - - - 814766cd by Simon Marlow at 2004-08-10T14:33:46+00:00 [haddock @ 2004-08-10 14:33:45 by simonmar] Fixes to installation under Windows. - - - - - 39cf9ede by Simon Marlow at 2004-08-12T12:08:23+00:00 [haddock @ 2004-08-12 12:08:23 by simonmar] Avoid using string-gap tricks. - - - - - b6d78551 by Simon Marlow at 2004-08-13T10:53:21+00:00 [haddock @ 2004-08-13 10:53:21 by simonmar] Update - - - - - eaae7417 by Simon Marlow at 2004-08-13T10:53:50+00:00 [haddock @ 2004-08-13 10:53:50 by simonmar] Test for primes in quoted links - - - - - 68c34f06 by Sven Panne at 2004-08-16T19:59:38+00:00 [haddock @ 2004-08-16 19:59:36 by panne] XMLification - - - - - 7f45a6f9 by Sven Panne at 2004-08-18T16:42:54+00:00 [haddock @ 2004-08-18 16:42:54 by panne] Re-added indices + minor fixes - - - - - 8a5dd97c by Sigbjorn Finne at 2004-08-25T17:15:42+00:00 [haddock @ 2004-08-25 17:15:42 by sof] backquote HADDOCK_VERSION defn for <= ghc-6.0.x; believe this is only needed under mingw - - - - - 4b1b42ea by Sven Panne at 2004-08-26T20:08:50+00:00 [haddock @ 2004-08-26 20:08:49 by panne] SGML is dead, long live DocBook XML! Note: The BuildRequires tags in the spec files are still incomplete and the documentation about the DocBook tools needs to be updated, too. Stay tuned... - - - - - 8d52cedb by Sven Panne at 2004-08-26T21:03:19+00:00 [haddock @ 2004-08-26 21:03:19 by panne] Updated BuildRequires tags. Alas, there seems to be no real standard here, so your mileage may vary... At least the current specs should work on SuSE Linux. - - - - - e6982912 by Sigbjorn Finne at 2004-08-30T15:44:59+00:00 [haddock @ 2004-08-30 15:44:59 by sof] escape HADDOCK_VERSION double quotes on all platforms when compiling with <=6.0.x - - - - - b3fbc867 by Simon Marlow at 2004-08-31T13:09:42+00:00 [haddock @ 2004-08-31 13:09:42 by simonmar] Avoid GHC/shell versionitis and create Version.hs - - - - - c359e16a by Sven Panne at 2004-09-05T19:12:33+00:00 [haddock @ 2004-09-05 19:12:32 by panne] * HTML documentation for "foo.xml" goes into directory "foo" again, not "foo-html". This is nicer and consistent with the behaviour for building the docs from SGML. * Disabled building PostScript documentation in the spec files for now, there are some strange issues with the FO->PS conversion for some files which have to be clarified first. - - - - - c68b1eba by Sven Panne at 2004-09-24T07:04:38+00:00 [haddock @ 2004-09-24 07:04:38 by panne] Switched the default state for instances and the module hierarchy to non-collapsed. This can be reversed when we finally use cookies from JavaScript to have a more persistent state. Previously going back and forth in the documentation was simply too annoying because everything was collapsed again and therefore the documentation was not easily navigatable. - - - - - dfb32615 by Simon Marlow at 2004-09-30T08:21:29+00:00 [haddock @ 2004-09-30 08:21:29 by simonmar] Add a feature request - - - - - 45ff783c by Sven Panne at 2004-10-23T19:54:00+00:00 [haddock @ 2004-10-23 19:54:00 by panne] Improved the Cygwin/MinGW chaos a little bit. There is still confusion about host platform vs. target platform... - - - - - 5f644714 by Krasimir Angelov at 2004-10-28T16:01:51+00:00 [haddock @ 2004-10-28 16:01:51 by krasimir] update for ghc-6.3+ - - - - - 92d9753e by Sven Panne at 2004-11-01T16:39:01+00:00 [haddock @ 2004-11-01 16:39:01 by panne] Revert previous commit: It's Network.URI which should be changed, not Haddock. - - - - - 05f70f6e by Simon Marlow at 2005-01-04T16:15:51+00:00 [haddock @ 2005-01-04 16:15:51 by simonmar] parser fix: allow qualified specialids. - - - - - 47870837 by Simon Marlow at 2005-01-04T16:16:54+00:00 [haddock @ 2005-01-04 16:16:54 by simonmar] Add a test - - - - - ff11fc2c by Ross Paterson at 2005-01-10T19:18:22+00:00 [haddock @ 2005-01-10 19:18:22 by ross] Render non-ASCII characters using numeric character references, to simplify charset issues. There's a META tag saying the charset is UTF-8, but GHC outputs characters as raw bytes. Ideally we need an encoding on the input side too, primarily in comments, because source files containing non-ASCII characters aren't portable between locales. - - - - - eba2fc4e by Simon Marlow at 2005-01-11T10:44:37+00:00 [haddock @ 2005-01-11 10:44:37 by simonmar] Remove string gap - - - - - b899a381 by Ross Paterson at 2005-01-13T11:41:33+00:00 [haddock @ 2005-01-13 11:41:33 by ross] recognize SGML-style numeric character references &#ddd; or &#xhhhh; and translate them into Chars. - - - - - 106e3cf0 by Ross Paterson at 2005-01-13T14:43:41+00:00 [haddock @ 2005-01-13 14:43:41 by ross] also allow uppercase X in hexadecimal character references (like SGML) - - - - - e8f54f25 by Ross Paterson at 2005-01-13T14:44:24+00:00 [haddock @ 2005-01-13 14:44:24 by ross] Describe numeric character references. - - - - - 914ccdce by Sven Panne at 2005-01-15T18:44:48+00:00 [haddock @ 2005-01-15 18:44:45 by panne] Make Haddock compile again after the recent base package changed. The Map/Set legacy hell has been factored out, so that all modules can simply use the new non-deprecated interfaces. Probably a lot of things can be improved by a little bit of Map/Set/List algebra, this can be done later if needed. Small note: Currently the list of instances in HTML code is reversed. This will hopefully be fixed later. - - - - - 6ab20e84 by Sven Panne at 2005-01-16T12:18:26+00:00 [haddock @ 2005-01-16 12:18:26 by panne] Trim imports - - - - - efb81da9 by Sven Panne at 2005-01-16T12:58:08+00:00 [haddock @ 2005-01-16 12:58:03 by panne] Correctly handle the new order of arguments for the combining function given to fromListWith. - - - - - e27b5834 by Sven Panne at 2005-01-16T14:14:41+00:00 [haddock @ 2005-01-16 14:14:39 by panne] Data.Map.unions is left-biased. - - - - - dae3cc3e by Sven Panne at 2005-01-16T14:22:44+00:00 [haddock @ 2005-01-16 14:22:44 by panne] Added the last missing "flip" to get identical HTML output as previous versions. - - - - - 951d8408 by Sven Panne at 2005-01-16T14:37:10+00:00 [haddock @ 2005-01-16 14:37:10 by panne] Refactored Text.PrettyPrint legacy hell into a separate module. - - - - - f1c4b892 by Sven Panne at 2005-01-16T15:41:25+00:00 [haddock @ 2005-01-16 15:41:21 by panne] Cleaned up imports and dropped support for GHC < 5.03, it never worked, anyway. - - - - - 60824c6e by Simon Marlow at 2005-01-18T10:02:48+00:00 [haddock @ 2005-01-18 10:02:48 by simonmar] Add a TODO - - - - - a8c82f23 by Krasimir Angelov at 2005-01-28T23:19:39+00:00 [haddock @ 2005-01-28 23:19:39 by krasimir] import Foreign/Foreign.C are required for Windows - - - - - d8450a23 by Simon Marlow at 2005-02-02T16:23:04+00:00 [haddock @ 2005-02-02 16:23:00 by simonmar] Revamp the linking strategy in Haddock. Now name resolution is done in two phases: - first resolve everything to original names, like a Haskell compiler would. - then, figure out the "home" location for every entity, and point all the links to there. The home location is the lowest non-hidden module in the import hierarchy that documents the entity. If there are multiple candidates, one is chosen at random. Also: - Haddock should not generate any HTML with dangling links any more. Unlinked references are just rendered as plain text. - Error reporting is better: if we can't find a link destination for an entity reference, we now emit a warning. - - - - - 1cce71d0 by Simon Marlow at 2005-02-03T13:42:19+00:00 [haddock @ 2005-02-03 13:42:19 by simonmar] - add --ignore-all-exports flag, which behaves as if every module has the ignore-exports attribute (requested by Chris Ryder). - add --hide option to hide a module on the command line. - add --use-package option to get Haddock info for a package from ghc-pkg (largely untested). - remove reexports from the .haddock file, they aren't used any more. - - - - - 767123ef by Ross Paterson at 2005-02-03T16:17:37+00:00 [haddock @ 2005-02-03 16:17:37 by ross] fix typo for < 6.3 - - - - - 0c680c04 by Simon Marlow at 2005-02-04T12:03:31+00:00 [haddock @ 2005-02-04 12:03:31 by simonmar] Fix bug in renameExportItems that meant links in instances weren't being renamed properly. - - - - - ff7abe5f by Simon Marlow at 2005-02-04T12:15:53+00:00 [haddock @ 2005-02-04 12:15:52 by simonmar] Add attribute #not-home, to indicate that the current module should not be considered to be a home module for the each entity it exports, unless there is no other module that exports the entity. - - - - - fc2cfd27 by Simon Marlow at 2005-02-04T12:40:02+00:00 [haddock @ 2005-02-04 12:40:02 by simonmar] Update the documentation w.r.t. home modules and the not-home attribute. - - - - - 26b8ddf7 by Ross Paterson at 2005-02-04T13:36:06+00:00 [haddock @ 2005-02-04 13:36:05 by ross] sort lists of instances by - arity of the type constructors (so higher-kinded instances come first) - name of the class - argument types - - - - - 26bfb19c by Simon Marlow at 2005-02-23T15:57:12+00:00 [haddock @ 2005-02-23 15:57:12 by simonmar] Fix documentation regarding the module attributes. - - - - - 9c3afd02 by Simon Marlow at 2005-02-28T16:18:17+00:00 [haddock @ 2005-02-28 16:18:17 by simonmar] version 0.7 - - - - - a95fd63f by Simon Marlow at 2005-02-28T16:22:08+00:00 [haddock @ 2005-02-28 16:22:08 by simonmar] Attempt to fix the layout of the package names in the contents. Having tried just about everything, the only thing I can get to work reliably is to make the package names line up on a fixed offset from the left margin. This obviously isn't ideal, so anyone else that would like to have a go at improving it is welcome. One option is to remove the +/- buttons from the contents list and go back to a plain table. The contents page now uses CSS for layout rather than tables. It seems that most browsers have different interpretations of CSS layout, so only the simplest things lead to consistent results. - - - - - 905d42f7 by Simon Marlow at 2005-03-01T17:16:42+00:00 [haddock @ 2005-03-01 17:16:40 by simonmar] Another attempt at lining up the package names on the contents page. Now, they line up with Konqueror, and almost line up with Firefox & IE (different layout in each case). - - - - - a0e1d178 by Wolfgang Thaller at 2005-03-09T08:28:39+00:00 [haddock @ 2005-03-09 08:28:39 by wolfgang] Hack haddock's lexer to accept the output from Apple's broken version of cpp (Apple's cpp leaves #pragma set_debug_pwd directives in it's output). - - - - - 9e1eb784 by Simon Marlow at 2005-04-22T14:27:15+00:00 [haddock @ 2005-04-22 14:27:15 by simonmar] Add a TODO item - - - - - 23281f78 by Ross Paterson at 2005-05-18T12:41:59+00:00 [haddock @ 2005-05-18 12:41:59 by ross] fix 3 bugs in --use-package, and document it. - - - - - 00074a68 by Sven Panne at 2005-05-21T12:35:29+00:00 [haddock @ 2005-05-21 12:35:29 by panne] Warning/versionitis police - - - - - 341fa822 by Simon Marlow at 2005-06-15T15:43:21+00:00 [haddock @ 2005-06-15 15:43:21 by simonmar] Allow "licence" as an alternate spelling of "license" - - - - - 3b953f8b by Simon Marlow at 2005-06-16T08:14:12+00:00 [haddock @ 2005-06-16 08:14:12 by simonmar] wibble - - - - - abfd9826 by Simon Marlow at 2005-06-27T14:46:40+00:00 [haddock @ 2005-06-27 14:46:40 by simonmar] name hierarchical HTML files as A-B-C.html instead of A.B.C.html. The old way confused Apache because the extensions are sometimes interpreted as having special meanings. - - - - - a01eea00 by Simon Marlow at 2005-08-04T13:59:40+00:00 [haddock @ 2005-08-04 13:59:40 by simonmar] 0.7 changes - - - - - 170ef87e by Simon Marlow at 2005-08-04T15:08:03+00:00 [haddock @ 2005-08-04 15:08:03 by simonmar] spec file from Jens Peterson - - - - - 7621fde4 by Simon Marlow at 2005-08-04T15:59:30+00:00 [haddock @ 2005-08-04 15:59:30 by simonmar] replace mingw tests with $(Windows) - - - - - a20739bb by Sven Panne at 2005-08-05T07:01:12+00:00 [haddock @ 2005-08-05 07:01:12 by panne] Reverted to previous version (but with bumped version number), the last commit broke RPM building on SuSE systems due to differently named dependencies. As a clarification: All .spec files in the repository have to work at least on SuSE, because that's the system I'm using. And as "Mr. Building Police", I reserve me the right to keep them that way... >:-) It might very well be the case that we need different .spec files for different platforms, so packagers which are unhappy with the current .spec files should contact me, stating the actual problems. - - - - - 4afb15cf by Simon Marlow at 2005-10-05T10:51:45+00:00 [haddock @ 2005-10-05 10:51:45 by simonmar] Add a bug - - - - - 60f69f82 by Simon Marlow at 2005-10-05T12:52:03+00:00 [haddock @ 2005-10-05 12:52:03 by simonmar] Document new behaviour of -s option - - - - - f7e520ca by Simon Marlow at 2005-10-10T15:02:55+00:00 [haddock @ 2005-10-10 15:02:55 by simonmar] extractRecSel: ignore non-record constructors (fixes a crash when using datatypes with a mixture of record and non-record style constructors). - - - - - b2edbedb by Simon Marlow at 2005-10-14T09:44:21+00:00 Start CHANGES for 0.8 - - - - - 21c7ac8d by Simon Marlow at 2005-10-14T23:11:19+00:00 First cut of Cabal build system - - - - - 766cecdd by Simon Marlow at 2005-10-29T08:14:43+00:00 Add configure script and Makefile for the docs Add a separate configure script and build system for building the documentation. The configure and Makefile code is stolen from fptools. This is left as a separate build system so that the main Cabal setup doesn't require a Unix build environment or DocBook XML tools. - - - - - aa36c783 by Duncan Coutts at 2006-01-17T19:29:55+00:00 Add a --wiki=URL flag to add a per-module link to a correspondng wiki page. So each html page gets an extra link (placed next to the source code and contents links) to a corresponding wiki page. The idea is to let readers contribute their own notes, examples etc to the documentation. Also slightly tidy up the code for the --source option. - - - - - e06e2da2 by Simon Marlow at 2006-01-18T09:28:15+00:00 TODO: documnet --wiki - - - - - 17adfda9 by Duncan Coutts at 2006-01-19T20:17:59+00:00 Add an optional wiki link for each top level exported name. In each module, for each "top level" exported entity we add a hyper link to a corresponding wiki page. The link url gets the name of the exported entity as a '#'-style anchor, so if there is an anchor in the page with that name then the users browser should jump directly to it. By "top level" we mean functions, classes, class members and data types (data, type, newtype), but not data constructors, class instances or data type class membership. The link is added at the right of the page and in a small font. Hopefully this is the right balance of visibility/distraction. We also include a link to the wiki base url in the contents and index pages. - - - - - f52324bb by Duncan Coutts at 2006-01-19T20:28:27+00:00 Rewrite pathJoin to only add a path separator when necessary. When the path ends in a file seperator there is no need to add another. Now using "--wiki=http://blah.com/foo/" should do the right thing. (Code snippet adapted from Isaac's FilePath package.) - - - - - 43bb89fa by Duncan Coutts at 2006-01-21T17:15:27+00:00 Teach haddock about line pragmas and add accurate source code links Teach haddock about C and Haskell style line pragmas. Extend the lexer/parser's source location tracking to include the file name as well as line/column. This way each AST item that is tagged with a SrcLoc gets the original file name too. Use this original file name to add source links to each exported item, in the same visual style as the wiki links. Note that the per-export source links are to the defining module rather than whichever module haddock pretends it is exported from. This is what we want for source code links. The source code link URL can also contain the name of the export so one could implement jumping to the actual location of the function in the file if it were linked to an html version of the source rather than just plain text. The name can be selected with the %N wild card. So for linking to the raw source code one might use: --source=http://darcs/haskell.org/foo/%F Or for linking to html syntax highlighted code: --source=http://darcs/haskell.org/foo/%M.html#%N - - - - - edd9f229 by Duncan Coutts at 2006-01-22T00:02:00+00:00 Extend URL variable expansion syntax and add source links to the contents page Like the wiki link on the contents and index page, add a source code link too. Extend the wiki & source URL variable expansion syntax. The original syntax was: %F for the source file name (the .hs version only, not the .lhs or .hs.pp one) %M for the module name (with '.' replaced by '/') The new syntax is: %F or %{FILE} for the original source file name %M or %{MODULE} for the module name (no replacements) %N or %{NAME} for the function/type export name %K or %{KIND} for a type/value flag "t" or "v" with these extensions: %{MODULE/./c} to replace the '.' module seperator with any other char c %{VAR|some text with the % char in it} which means if the VAR is not in use in this URL context then "" else replace the given text with the '%' char replaced by the string value of the VAR. This extension allows us to construct URLs wit optional parts, since the module/file name is not available for the URL in the contents/index pages and the value/type name is not available for the URL at the top level of each module. - - - - - eb3c6ada by Duncan Coutts at 2006-01-23T13:42:34+00:00 Remove the complex substitutions and add more command line flags instead. Instead of incomprehensable URL substitutions like ${MODULE/./-|?m=%} we now use three seperate command line flags for the top level, per-module and per-entity source and wiki links. They are: --source-base, --source-module, --source-entity --comments-base, --comments-module, --comments-entity We leave -s, --source as an alias for --source-module which is how that option behaved previously. The long forms of the substitutions are still available, ${FILE} ${MODULE} etc and the only non-trivial substitution is ${MODULE/./c} to replace the '.' characters in the module name with any other character c. eg ${MODULE/./-} Seperating the source and wiki url flags has the added bonus that they can be turned on or off individually. So users can have per-module links for example without having to also have per-entity links.` - - - - - a2f0f2af by Duncan Coutts at 2006-01-23T13:54:52+00:00 Make the --help output fit in 80 columns. This is a purely cosmetic patch, feel free to ignore it. The only trickery going on is that we don't display the deprecated -s, --source flags in the help message, but we do still accept them. - - - - - 2d3a4b0c by Duncan Coutts at 2006-01-23T14:12:16+00:00 Add documentation for the new --source-* and --comments-* command line options - - - - - 1a82a297 by Simon Marlow at 2006-01-23T17:03:27+00:00 fix markup - - - - - 100d464a by Duncan Coutts at 2006-01-23T18:31:13+00:00 remove a couple TODO items that have been done The --wiki, or rather the --comment-* options are now documented. There is probably no need to have haddock invoke unlit or cpp itself since it can now pick up the line pragmas to get the source locations right. Tools like Cabal will arrange for preprocessors to be run so there is less of a need for tools like haddock to do it themselves. - - - - - 3162fa91 by Simon Marlow at 2006-01-24T14:21:56+00:00 add a test I had lying around - - - - - 98947063 by Simon Marlow at 2006-01-31T13:52:54+00:00 add scabal-version field - - - - - c41876e6 by Neil Mitchell at 2006-02-26T17:48:21+00:00 Add Hoogle output option - - - - - f86fb9c0 by Simon Marlow at 2006-03-08T09:15:20+00:00 add haskell.vim Contributed by Brad Bowman <bsb at bereft.net>, thanks! - - - - - 35d3c511 by benjamin.franksen at 2006-03-03T22:39:54+00:00 fixed libdir (/html was missing) - - - - - 4d08fd7d by Simon Marlow at 2006-03-10T11:13:31+00:00 add PatternGuards extension - - - - - 3f095e70 by Simon Marlow at 2006-03-13T11:40:42+00:00 bug fixes from Brad Bowman - - - - - 8610849d by Sven Panne at 2006-03-19T17:02:56+00:00 Fixed Cabal/RPM build - - - - - 34a994d6 by sven.panne at 2006-04-20T12:39:23+00:00 Avoid pattern guards Due to the use of pattern guards in Haddock, GHC was called with -fglasgow-exts. This in turn enables bang patterns, too, which broke the Haddock build. Removing some unnecessary pattern guards seemed to be the better way of fixing this instead of using a pragma to disable pattern guards. - - - - - bb523f51 by Ross Paterson at 2006-04-24T09:03:25+00:00 extend 'deriving' heuristic a little If an argument of a data constructor has a type variable head, it is irreducible and the same type class can be copied into the constraint. (Formerly we just did this for type variable arguments.) - - - - - dab9fe7a by Simon Marlow at 2006-04-26T10:02:31+00:00 record an idea - - - - - 748b7078 by Simon Marlow at 2006-05-08T08:28:53+00:00 add section about deriving - - - - - 11252ea1 by Simon Marlow at 2006-05-24T15:43:10+00:00 replace a fatal error in lexChar with a parseError - - - - - 382c9411 by Simon Marlow at 2006-05-24T15:45:47+00:00 add a bug - - - - - b79272f5 by Simon Marlow at 2006-05-24T15:46:29+00:00 add a bug report - - - - - 912edf65 by David Waern at 2006-07-10T19:09:23+00:00 Initial modifications -- doesn't compile - - - - - a3c7ba99 by David Waern at 2006-07-11T00:54:19+00:00 More porting work -- doesn't compile - - - - - 0a173d19 by David Waern at 2006-07-11T11:30:03+00:00 Make the repos temporarily compile and illustrate a problem - - - - - bad316de by David Waern at 2006-07-11T15:43:47+00:00 Progress on the porting process - - - - - bbf12d02 by David Waern at 2006-07-11T23:07:44+00:00 More progress on the porting -- first pass starting to shape up - - - - - de580ba2 by David Waern at 2006-07-20T17:48:30+00:00 More progress -- still on phase1 - - - - - 75a917a2 by David Waern at 2006-07-23T18:22:43+00:00 More work on pass1 -- mostly done - - - - - 6697b3f7 by David Waern at 2006-07-23T22:17:40+00:00 More work, started working on the renaming phase -- this code will need a cleanup soon :) - - - - - 82a5bcbb by David Waern at 2006-07-29T16:16:43+00:00 Add instances, build renaming environment, start on the renamer - - - - - c3f8f4f1 by David Waern at 2006-07-29T21:37:48+00:00 Complete the renamer - - - - - 7e00d464 by David Waern at 2006-07-30T21:01:57+00:00 Start porting the Html renderer - - - - - f04ce121 by David Waern at 2006-08-09T20:04:56+00:00 More Html rendering progress - - - - - 20c21b53 by David Waern at 2006-08-10T17:37:47+00:00 More progress - - - - - d7097e0d by David Waern at 2006-08-11T20:31:51+00:00 Cleanup - - - - - a7351e86 by David Waern at 2006-08-12T11:44:47+00:00 Render H98 Data declarations - - - - - 3fb2208e by David Waern at 2006-08-12T17:15:34+00:00 Perfect rendering of Test.hs - - - - - 454fd062 by David Waern at 2006-08-13T21:57:08+00:00 Misc fixes and interface load/save - - - - - 7ef7e7be by David Waern at 2006-08-14T00:56:07+00:00 Some refactoring - - - - - a7d3efef by David Waern at 2006-08-19T20:07:55+00:00 Adapt to latest GHC - - - - - 5fc3c0d7 by David Waern at 2006-08-20T21:28:11+00:00 Move interface read/write to its own module + some cleanup - - - - - 037e011c by David Waern at 2006-08-20T21:38:24+00:00 Small cleanup - - - - - da3a1023 by David Waern at 2006-09-03T16:05:22+00:00 Change mode to BatchCompile to avoid GHC API bug - - - - - 3cc9be3b by David Waern at 2006-09-03T16:06:59+00:00 Starting work on GADT rendering - - - - - 94506037 by David Waern at 2006-09-03T20:02:48+00:00 Compensate for change of export list order in GHC - - - - - c2cec4eb by David Waern at 2006-09-04T20:53:01+00:00 Rename a function - - - - - 9a9735ba by David Waern at 2006-09-05T15:51:21+00:00 Change version number to 2.0 - - - - - 3758a714 by David Waern at 2006-09-05T15:51:49+00:00 Align comment properly - - - - - 68478d9e by David Waern at 2006-09-15T18:03:00+00:00 Remove interface reading/writing code and use the GHC api for creating package environments instead - - - - - d2eedd95 by David Waern at 2006-09-15T18:05:29+00:00 Change the executable name to haddock-ghc-nolib - - - - - fcfbcf66 by David Waern at 2006-09-15T18:05:45+00:00 Small source code cleanup - - - - - d08eb017 by David Waern at 2006-09-15T18:06:21+00:00 Remove handling of --package flag - - - - - b8a4cf53 by David Waern at 2006-09-15T18:07:16+00:00 Remove commented-out code - - - - - bef0a684 by David Waern at 2006-09-15T18:37:57+00:00 Don't warn about missing links to () - - - - - e7d25fd7 by David Waern at 2006-09-15T19:50:49+00:00 Remove Interface and Binary2 modules - - - - - 9894f2a1 by David Waern at 2006-09-15T19:53:43+00:00 Remove debug printing from HaddockHtml - - - - - a0e7455d by David Waern at 2006-09-16T00:16:29+00:00 Comments only - - - - - d5b26fa7 by David Waern at 2006-09-16T00:16:57+00:00 Refactor PackageData creation code and start on building the doc env propery (unfinished) - - - - - 06aaa779 by David Waern at 2006-09-16T00:19:25+00:00 Better comments in Main.hs - - - - - 1a52d1b4 by David Waern at 2006-09-18T22:17:11+00:00 Comments and spacing change - - - - - e5a97767 by David Waern at 2006-09-21T17:02:45+00:00 Remove unnecessary fmapM import in Main - - - - - 9d0f9d3a by David Waern at 2006-09-22T18:07:07+00:00 Make import list in HaddockHtml prettier - - - - - 3452f662 by David Waern at 2006-09-22T18:08:47+00:00 Refactor context rendering - - - - - 12d0a6d0 by David Waern at 2006-09-22T18:09:52+00:00 Do proper HsType rendering (inser parentheses correctly) - - - - - 2c20c2f9 by David Waern at 2006-09-22T18:10:45+00:00 Fix a bug in Main.toHsType - - - - - c5396443 by David Waern at 2006-09-22T18:11:16+00:00 Skip external package modules sort for now - - - - - 3fb95547 by David Waern at 2006-09-22T20:35:40+00:00 Take away trailin "2" on all previously clashing type names - - - - - 2174755f by David Waern at 2006-09-22T20:51:43+00:00 Remove unused imports in Main - - - - - 1e9f7a39 by David Waern at 2006-09-22T20:52:11+00:00 Fix a comment in Main - - - - - 32d9e028 by David Waern at 2006-10-05T16:40:11+00:00 Merge with changes to ghc HEAD - - - - - 3058c8f5 by David Waern at 2006-10-05T16:41:02+00:00 Comment fixes - - - - - b9c217ec by David Waern at 2006-10-05T16:49:59+00:00 Filter out more builtin type constructors from warning messages - - - - - 67e7d252 by David Waern at 2006-10-05T19:38:22+00:00 Refactoring -- better structured pass1 - - - - - cd21c0c1 by David Waern at 2006-10-05T19:44:42+00:00 Remove read/dump interface flags - - - - - 313f9e69 by David Waern at 2006-10-05T19:49:26+00:00 Remove unused pretty printing - - - - - 480f09d1 by David Waern at 2006-12-28T13:22:24+00:00 Update to build with latest GHC HEAD - - - - - 63dccfcb by David Waern at 2007-01-05T01:38:45+00:00 Fixed a bug so that --ghc-flag works correctly - - - - - 3117dadc by David Waern at 2006-12-29T18:53:39+00:00 Automatically get the GHC lib dir - - - - - 9dc84a5c by David Waern at 2006-12-29T19:58:53+00:00 Comments - - - - - 0b0237cc by David Waern at 2007-01-05T16:48:30+00:00 Collect docs based on SrcLoc, syncing with removal of DeclEntity from GHC - - - - - a962c256 by David Waern at 2007-01-05T17:02:47+00:00 Add tabs in haddock.cabal - - - - - 0ca30c97 by David Waern at 2007-01-05T17:04:11+00:00 Add GHCUtils.hs - - - - - c0ab9abe by David Waern at 2007-01-10T11:43:08+00:00 Change package name to haddock-ghc, version 0.1 - - - - - 38e18b27 by David Waern at 2007-01-12T12:03:52+00:00 No binder name for foreign exports - - - - - d18587ab by David Waern at 2007-01-12T12:08:15+00:00 Temp record - - - - - ba6251a0 by David Waern at 2007-01-12T18:27:55+00:00 Remove read/dump-interface (again) - - - - - f4ba2b39 by David Waern at 2007-01-12T18:31:36+00:00 Remove DocOption, use the GHC type - - - - - 511be8bd by David Waern at 2007-01-12T18:32:41+00:00 Use exceptions instead of Either when loading package info - - - - - 0f2144d8 by David Waern at 2007-01-12T18:33:23+00:00 Small type change - - - - - 77507eb7 by David Waern at 2007-01-12T18:33:59+00:00 Remove interface file read/write - - - - - 0ea1e14f by David Waern at 2007-01-17T21:40:26+00:00 Add trace_ppr to GHCUtils - - - - - 3878b493 by David Waern at 2007-01-17T21:40:53+00:00 Sort external package modules and build a doc env - - - - - 8dc323fc by David Waern at 2007-01-17T21:42:41+00:00 Remove comment - - - - - f4c5b097 by David Waern at 2007-01-18T23:22:18+00:00 Add haddock-ghc.cabal and remove ghc option pragma in source file - - - - - da242b2c by David Waern at 2007-01-18T23:22:46+00:00 Remove some tabs - - - - - 288ed096 by David Waern at 2007-01-18T23:39:28+00:00 Moved the defaultErrorHandler to scope only over sortAndCheckModules for now - - - - - 4dd150fe by David Waern at 2007-02-03T21:23:56+00:00 Let restrictCons handle infix constructors - - - - - 97893442 by David Waern at 2007-02-04T16:26:00+00:00 Render infix data constructors - - - - - da89db72 by David Waern at 2007-02-04T16:26:33+00:00 CHange project name to Haddock-GHC - - - - - e93d48af by David Waern at 2007-02-04T16:59:08+00:00 Render infix type constructors properly - - - - - 357bc99b by David Waern at 2007-02-04T17:37:08+00:00 Insert spaces around infix function names - - - - - ab6cfc49 by David Waern at 2007-02-04T17:59:54+00:00 Do not list entities without documentation - - - - - 04249c7e by David Waern at 2007-02-04T19:16:25+00:00 Add GADT support (quite untested) - - - - - 2c223f8d by David Waern at 2007-02-04T19:25:10+00:00 Add package file write/save again! - - - - - b07ed218 by David Waern at 2007-02-04T19:33:02+00:00 Comment out minf_iface based stuff - - - - - 953d1fa7 by David Waern at 2007-02-05T00:12:23+00:00 Solve conflicts - - - - - 593247fc by David Waern at 2007-02-06T19:48:48+00:00 Remove -package flag, GHC's can be used instead - - - - - f658ded2 by David Waern at 2007-02-06T20:50:44+00:00 Start for support of ATs - - - - - 97f9e913 by David Waern at 2007-02-06T20:52:27+00:00 Wibble - - - - - 2ce8e4cf by David Waern at 2007-02-16T12:09:49+00:00 Add the DocOptions change - - - - - dee4a9b5 by David Waern at 2007-03-06T01:24:48+00:00 Wibble - - - - - 7cb99d18 by David Waern at 2007-03-06T01:24:58+00:00 Change version to 2.0 and executable name to haddock - - - - - c5aa02bc by David Waern at 2007-03-08T15:59:49+00:00 Go back to -B flag - - - - - 3a349201 by David Waern at 2007-03-09T13:31:59+00:00 Better exception handling and parsing of GHC flags - - - - - 05a69b71 by David Waern at 2007-03-09T17:45:44+00:00 Remove commented-out DocEntity printing - - - - - 755032cb by davve at dtek.chalmers.se at 2007-03-23T23:30:20+00:00 Remove a file that shouldn't be here - - - - - a7077e5f by davve at dtek.chalmers.se at 2007-03-24T03:58:48+00:00 Remove an import - - - - - 6f55aa8b by davve at dtek.chalmers.se at 2007-03-25T00:46:48+00:00 Start work on Haddock API - - - - - f0199480 by davve at dtek.chalmers.se at 2007-03-25T00:56:36+00:00 Prettify some comments - - - - - f952f9d1 by davve at dtek.chalmers.se at 2007-03-25T00:56:53+00:00 Remove ppr in HaddockTypes - - - - - bc594904 by davve at dtek.chalmers.se at 2007-03-25T00:57:53+00:00 Remove commented out doc env inference - - - - - 11ebf08d by davve at dtek.chalmers.se at 2007-03-25T01:23:25+00:00 De-flatten the namespace - - - - - f696b4bc by davve at dtek.chalmers.se at 2007-03-25T03:21:48+00:00 Add missing stuff to API - - - - - 9a2a04c3 by davve at dtek.chalmers.se at 2007-03-25T03:22:02+00:00 Wibble - - - - - 7d04a6d5 by davve at dtek.chalmers.se at 2007-03-25T03:22:08+00:00 Avoid a GHC bug with parseStaticFlags [] - - - - - 4d2820ba by davve at dtek.chalmers.se at 2007-03-26T04:57:01+00:00 Add fall-through case to mkExportItem - - - - - 6ebc8950 by Stefan O'Rear at 2007-03-26T04:14:53+00:00 Add shebang line to Setup.lhs - - - - - 80966ec5 by davve at dtek.chalmers.se at 2007-03-26T05:24:26+00:00 Fix stupid compile error - - - - - 1ea1385d by davve at dtek.chalmers.se at 2007-04-05T17:19:56+00:00 Do save/read of interface files properly - - - - - 0e4f6541 by David Waern at 2007-04-10T21:08:36+00:00 Add version to ghc dependency - - - - - b0499b63 by David Waern at 2007-04-10T21:37:08+00:00 Change package name to haddock - - - - - 9d50d27e by David Waern at 2007-04-24T00:22:14+00:00 Use filepath package instead of FilePath - - - - - 87c7fcdf by David Waern at 2007-07-10T21:03:04+00:00 Add new package dependencies - - - - - 4768709c by David Waern at 2007-07-11T20:37:11+00:00 Follow changes to record constructor representation - - - - - b9a02fee by Simon Marlow at 2007-05-30T14:00:48+00:00 update to compile with the latest GHC & Cabal - - - - - c0ebdc01 by David Waern at 2007-07-11T21:35:45+00:00 Fix conflicts - - - - - 97f7afd4 by David Waern at 2007-07-11T21:52:38+00:00 Follow changes to the GHC API - - - - - a5b7b58f by David Waern at 2007-07-12T20:36:48+00:00 Call parseStaticFlags before newSession - - - - - f7f50dbc by David Waern at 2007-08-01T21:52:58+00:00 Better indentation in haddock.cabal - - - - - d84e52ad by David Waern at 2007-08-02T00:08:18+00:00 Wibble - - - - - a23f494a by David Waern at 2007-08-02T00:08:24+00:00 Be better at trying to load all module dependencies (debugging) - - - - - ee917f13 by David Waern at 2007-08-03T18:48:08+00:00 Load all targets explicitly (checkModule doesn't chase dependencies anymore) - - - - - 5182d631 by David Waern at 2007-08-16T16:48:55+00:00 Finalize support for links to other packages - - - - - dfd1e3da by David Waern at 2007-08-16T16:51:11+00:00 Fix haddock comment errors in Haddock.Types - - - - - 50c0d83e by David Waern at 2007-08-16T16:51:37+00:00 Remove a debug import - - - - - d84b7c2b by David Waern at 2007-08-16T17:06:30+00:00 Rename PackageData to HaddockPackage - - - - - 3b52cb9f by David Waern at 2007-08-16T17:09:42+00:00 Simplify some comments - - - - - 66fa68d9 by David Waern at 2007-08-16T17:11:38+00:00 Comment the HaddockPackage definition - - - - - 8674c761 by David Waern at 2007-08-16T17:25:54+00:00 Improve code layout in Main - - - - - 571a3a0b by David Waern at 2007-08-16T17:32:13+00:00 Remove explict module imports in Main - - - - - d31b3cb0 by David Waern at 2007-08-16T17:36:23+00:00 Correct comments - - - - - 7f8a9f2b by David Waern at 2007-08-16T17:39:50+00:00 Fix layout problems in Haddock.Types - - - - - 9f421d7f by David Waern at 2007-08-17T11:16:48+00:00 Move options out of Main into Haddock.Options - - - - - 80042b63 by David Waern at 2007-08-17T11:26:59+00:00 Small comment/layout fixes - - - - - b141b982 by David Waern at 2007-08-17T11:28:28+00:00 Change project name from Haddock-GHC to Haddock - - - - - dbeb4a81 by David Waern at 2007-08-17T11:41:05+00:00 Add top module comment to all files - - - - - ce99cc9e by David Waern at 2007-08-17T14:53:04+00:00 Factor out typechecking phase into Haddock.Typecheck - - - - - 6bf75d9e by David Waern at 2007-08-17T16:55:35+00:00 Factor out package code to Haddock.Packages - - - - - b396db37 by David Waern at 2007-08-29T22:40:23+00:00 Major refactoring - - - - - 3d4f95ee by David Waern at 2007-08-29T23:26:24+00:00 Rename HaddockModule to Interface and a few more refactorings - - - - - c55326db by David Waern at 2007-08-29T23:48:03+00:00 Some comment cleanup - - - - - 9a84fc46 by David Waern at 2007-08-29T23:49:29+00:00 Add some modules that I forgot to add earlier - - - - - 4536dce2 by David Waern at 2007-08-29T23:55:24+00:00 Wibble - - - - - 9b7f0206 by David Waern at 2007-08-30T16:03:29+00:00 Wibble - - - - - c52c050a by David Waern at 2007-08-30T16:30:37+00:00 Rename HaddockModule to Interface - - - - - eae2995f by David Waern at 2007-08-30T16:42:59+00:00 Simplify createInterfaces - - - - - 53f99caa by David Waern at 2007-09-29T00:04:31+00:00 Add build-type: Simple to the cabal file - - - - - 0d3103a8 by David Waern at 2007-09-29T00:04:58+00:00 Add containers and array dependency - - - - - 6acf5f30 by David Waern at 2007-09-29T00:13:36+00:00 Prettify the cabal file - - - - - 87c1e378 by David Waern at 2007-09-29T13:16:39+00:00 FIX: consym data headers with more than two variables - - - - - b67fc16a by David Waern at 2007-09-29T14:01:32+00:00 FIX: prefix types used as operators should be quoted - - - - - a8f925bc by David Waern at 2007-09-29T14:02:26+00:00 Use isSymOcc from OccName instead of isConSym - - - - - fc330701 by David Waern at 2007-09-29T14:15:37+00:00 Use isLexConSym/isLexVarSym from OccName - - - - - e4f3dbad by David Waern at 2007-09-29T15:01:08+00:00 FIX: do not quote varsym type operators - - - - - 402207d2 by David Waern at 2007-09-29T15:01:50+00:00 Wibble - - - - - f9d89ef0 by David Waern at 2007-09-29T15:17:40+00:00 Take care when pp tyvars - add parens on syms - - - - - 849e2a77 by David Waern at 2007-10-01T21:56:39+00:00 Go back to using a ModuleMap instead of LookupMod - fixes a bug - - - - - 549dbac6 by David Waern at 2007-10-02T01:05:19+00:00 Improve parsing of doc options - - - - - a36021b8 by David Waern at 2007-10-02T23:05:00+00:00 FIX: double arrows in constructor contexts - - - - - d03bf347 by David Waern at 2007-10-09T16:14:05+00:00 Add a simple test suite - - - - - c252c140 by David Waern at 2007-10-17T16:02:28+00:00 Add --optghc=.. style flag passing to GHC - - - - - cce6c1b3 by David Waern at 2007-10-18T22:03:20+00:00 Add support for --read-interface again - - - - - 33d059c0 by David Waern at 2007-10-18T22:30:18+00:00 Refactoring -- get rid of Haddock.Packages - - - - - f9ed0a4c by David Waern at 2007-10-18T22:34:36+00:00 Name changes - - - - - 8a1c816f by David Waern at 2007-10-20T14:24:23+00:00 Add --ghc-version option - - - - - 4925aaa1 by David Waern at 2007-10-21T14:34:26+00:00 Add some Outputable utils - - - - - 69e7e47f by David Waern at 2007-10-21T14:35:49+00:00 FIX: Ord for OrdName was not comparing modules - - - - - 5a4ae535 by David Waern at 2007-10-21T21:18:48+00:00 Wibble - - - - - 03d48e20 by David Waern at 2007-10-24T15:52:56+00:00 Remove Main from "other modules" - - - - - c66f6d82 by David Waern at 2007-10-24T16:37:18+00:00 Make it possible to run haddock on itself - - - - - 21d156d8 by David Waern at 2007-10-25T14:02:14+00:00 Don't set boot modules as targets - - - - - f8bcf91c by David Waern at 2007-10-31T22:11:17+00:00 Add optimisation flags - - - - - 7ac758f2 by David Waern at 2007-11-04T09:48:28+00:00 Go back to loading only targets (seems to work now) - - - - - 4862aae1 by David Waern at 2007-11-05T22:24:57+00:00 Do full compilation of modules -- temporary fix for GHC API problem - - - - - 697e1517 by David Waern at 2007-11-05T22:25:50+00:00 Don't warn about not being able to link to wired/system/builtin-names - - - - - 892186da by David Waern at 2007-11-06T00:49:21+00:00 Filter out instances with TyCons that are not exported - - - - - 9548314c by David Waern at 2007-11-06T09:37:14+00:00 Wibble - - - - - 5cafd627 by David Waern at 2007-11-08T01:43:07+00:00 Filter out all non-vanilla type sigs - - - - - 04621830 by David Waern at 2007-11-08T01:45:13+00:00 Synch loading of names from .haddock files with GHC's name cache - - - - - 88d37f77 by David Waern at 2007-11-08T01:46:21+00:00 Remove commented-out code - - - - - 6409c911 by David Waern at 2007-11-08T01:56:00+00:00 Small bugfix and cleanup in getDeclFromTyCls - - - - - af59d9c2 by David Waern at 2007-11-08T02:08:44+00:00 Remove OrdName stuff - - - - - 3a615e2e by David Waern at 2007-11-08T02:13:41+00:00 Update runtests.hs following changes to haddock - - - - - 01f3314e by David Waern at 2007-11-08T02:33:01+00:00 Complain if we can't link to wired-in names - - - - - fcafb5d1 by David Waern at 2007-11-09T02:40:16+00:00 Don't exit when there are no file arguments - - - - - 194bc332 by David Waern at 2007-11-09T02:55:37+00:00 Wibble - - - - - dbe4cb55 by David Waern at 2007-11-09T02:56:14+00:00 Wibble - - - - - 82869fda by David Waern at 2007-11-10T17:01:43+00:00 Introduce InstalledInterface structure and add more stuff to the .haddock files We introduce InstalledInterface capturing the part of Interface that is stored in the interface files. We change the ppHtmlContents and ppHtmllIndex to take this structure instead of a partial Interface. We add stuff like the doc map and exported names to the .haddock file (via InstalledInterface). - - - - - d6bb57bf by David Waern at 2007-11-10T17:19:48+00:00 FIX: contents and index should include external package modules when --gen-contents/--gen-index - - - - - e8814716 by David Waern at 2007-11-11T00:29:27+00:00 Remove lDocLinkName and its use in Html backend - - - - - 6f9bd702 by David Waern at 2007-11-11T00:50:57+00:00 Do some refactoring in the html backend This also merges an old patch by Augustsson: Wed Jul 12 19:54:36 CEST 2006 lennart.augustsson at credit-suisse.com * Print type definitions like signatures if given arrows. - - - - - 09d0ce24 by Malcolm.Wallace at 2006-07-20T13:13:57+00:00 mention HsColour in the docs, next to option flags for linking to source code - - - - - 24da6c34 by Malcolm.Wallace at 2006-07-20T13:14:50+00:00 change doc references to CVS to give darcs repository location instead - - - - - 74d52cd6 by David Waern at 2007-11-11T00:55:33+00:00 Update copyright - - - - - fcaa3b4f by Duncan Coutts at 2006-09-08T13:41:00+00:00 Eliminate dep on network by doing a little cut'n'paste haddock depending on the network causes a circular dependency at least if you want to build the network lib with haddock docs. - - - - - 10cc9bda by David Waern at 2007-11-11T02:09:41+00:00 Fix conflicts - - - - - 4e3acd39 by David Waern at 2007-11-11T02:21:19+00:00 Manual merge of a patch from Duncan Coutts that removes the dependency on mtl - - - - - fa9070da by Neil Mitchell at 2006-09-29T15:52:03+00:00 Do not generate an empty table if there are no exports, this fixes a <table></table> tag being generated, which is not valid HTML 4.01 - - - - - d7431c85 by David Waern at 2007-11-11T02:28:50+00:00 Fix conflicts - - - - - f87e8f98 by Simon Marlow at 2006-10-10T11:37:16+00:00 changes for 0.8 - - - - - db929565 by Simon Marlow at 2006-10-10T12:07:12+00:00 fix the name of the source file - - - - - 8220aa4b by Simon Marlow at 2006-10-11T14:17:37+00:00 Rename haddock.js to haddock-util.js haddock.js will be run automatically by Windows when you type 'haddock' if it is found on the PATH, so rename to avoid confusion. Spotted by Adrian Hey. - - - - - 6bccdaa1 by sven.panne at 2006-10-12T15:28:23+00:00 Cabal's sdist does not generate "-src.tar.gz" files, but ".tar.gz" ones - - - - - d3f3fc19 by Simon Marlow at 2006-12-06T16:05:07+00:00 add todo item for --maintainer - - - - - 2da7e269 by Simon Marlow at 2006-12-15T15:52:00+00:00 TODO: do something better about re-exported symbols from another package - - - - - 42d85549 by David Waern at 2007-11-11T02:30:59+00:00 Fix conflicts - - - - - 5e7ef6e5 by Neil Mitchell at 2007-01-11T15:41:15+00:00 Never do spliting index files into many - - - - - f3d4aebe by Neil Mitchell at 2007-01-11T17:07:09+00:00 Add searching on the index page - - - - - bad3ab66 by Neil Mitchell at 2007-01-11T18:17:46+00:00 Delete dead code, now there is only one index page - - - - - cd09eedb by Neil Mitchell at 2007-01-11T18:21:19+00:00 Delete more stuff that is no longer required - - - - - e2806646 by David Waern at 2007-11-11T02:41:53+00:00 Fix conflicts - - - - - a872a823 by Neil Mitchell at 2007-01-11T18:51:43+00:00 Make the index be in case-insensitive alphabetic order - - - - - 8bddd9d7 by Neil Mitchell at 2007-02-06T17:49:12+00:00 Do not create empty tables for data declarations which don't have any constructors, instances or comments. Gets better HTML 4.01 compliance - - - - - 036b8120 by David Waern at 2007-11-11T02:56:58+00:00 Fix conflicts - - - - - f50c1639 by Conal Elliott at 2007-02-14T21:54:00+00:00 added substitution %{FILE///c} - - - - - 402e166a by David Waern at 2007-11-11T03:35:46+00:00 Manual merge of old patch: Sat Apr 21 04:36:43 CEST 2007 Roberto Zunino <zunrob at users.sf.net> * URL expansion for %%, %L, %{LINE} - - - - - 2f264fbd by David Waern at 2007-11-11T03:40:33+00:00 Manual merge of an old patch: Thu Apr 19 20:23:40 CEST 2007 Wolfgang Jeltsch <g9ks157k at acme.softbase.org> * bug fix When Haddock was invoked with the --ignore-all-exports flag but the ignore-exports module attribute wasn't used, hyperlinks weren't created for non-exported names. This fix might not be as clean as one would wish (since --ignore-all-exports now results in ignore_all_exports = True *and* an additional OptIgnoreExports option for every module) but at least the bug seems to be resolved now. - - - - - 7d7ae106 by sven.panne at 2007-09-02T12:18:02+00:00 Install LICENSE in the correct place - - - - - 66eaa924 by David Waern at 2007-11-11T19:02:46+00:00 Fix a bug that made haddock loop - - - - - 4ed47b58 by David Waern at 2007-11-11T19:03:09+00:00 Rename java-script file (this wasn't merge correctly) - - - - - d569534a by David Waern at 2007-11-11T19:06:44+00:00 Don't require -B <ghc-libdir> when no argument files Change readInterfaceFile to take a Maybe Session, to avoid having to pass -B <ghc-libdir> to Haddock when there're no source files to process. This is nice when computing contents/index for external packages. - - - - - 373368bc by Neil Mitchell at 2007-01-11T18:22:44+00:00 Change from tabs to spaces in the ppHtmlIndex function - - - - - 6b063a77 by Neil Mitchell at 2007-01-12T12:17:46+00:00 Rewrite much of the index searching code, previously was too slow to execute on the base library with IE, the new version guarantees less than O(log n) operations be performed, where n is the number in the list (before was always O(n)) - - - - - bfad00b7 by David Waern at 2007-11-11T23:33:53+00:00 Fix conflicts - - - - - cd2dcc09 by Neil Mitchell at 2007-01-12T12:25:01+00:00 Make the max number of results 75 instead of 50, to allow map searching in the base library to work - - - - - 3ae74764 by Neil Mitchell at 2007-01-12T12:58:17+00:00 Make the search box in a form so that enter does the default search - - - - - 142103e5 by David Waern at 2007-11-12T00:03:18+00:00 Merge patch from the old branch: Fri Aug 31 13:21:45 CEST 2007 Duncan Coutts <duncan at haskell.org> * Add category: Development to .cabal file Otherwise it appears on the hackage website in the "Unclassified" category. - - - - - 22ec2ddb by David Waern at 2007-11-25T01:55:29+00:00 A a list of small improvements to the TODO file - - - - - eb0129f4 by Wolfgang Jeltsch at 2007-12-03T23:47:55+00:00 addition of type equality support (at least for HTML generation) - - - - - 816a7e22 by David Waern at 2007-12-08T15:46:26+00:00 Handle class operators correctly when rendering predicates - - - - - 68baaad2 by David Waern at 2007-12-08T16:15:54+00:00 Code layout changes - - - - - 09b77fb4 by David Waern at 2007-12-08T16:16:03+00:00 Handle infix operators correctly in the Type -> HsType translation - - - - - 31c36da2 by David Waern at 2007-12-08T16:24:27+00:00 Add ppLParendTypes/ppLParendType - - - - - b17cc818 by David Waern at 2007-12-08T16:26:12+00:00 Use ppParendType when printing types args in predicates - - - - - ffd1f2cf by David Waern at 2007-12-08T16:45:06+00:00 Fix rendering of instance heads to handle infix operators This is also a refactoring to share this code for rendering predicates. - - - - - ff886d45 by David Waern at 2007-12-08T17:27:46+00:00 Fix rendering of class operators - - - - - e2fcbb9e by David Waern at 2007-12-08T17:59:28+00:00 Fix a bug (use ppTyName instead of ppName to print names in type apps) - - - - - 79a1056e by David Waern at 2007-12-08T21:25:18+00:00 Update tests - - - - - 867741ac by David Waern at 2007-12-08T21:25:49+00:00 Give a diff on test failure - - - - - 7e5eb274 by David Waern at 2008-01-05T14:33:45+00:00 Add DrIFT commands - - - - - 3656454d by David Waern at 2008-01-05T20:26:00+00:00 Add "cabal-version: >= 1.2" to the cabal file - - - - - 77974efc by Simon Marlow at 2007-12-20T09:52:44+00:00 add an item - - - - - f6ac1708 by Simon Marlow at 2007-12-06T14:00:10+00:00 Source links must point to the original module, not the referring module - - - - - eda1d5c9 by David Waern at 2008-01-06T14:40:52+00:00 Manual merge of a patch to the 0.8 branch Thu Dec 6 15:00:10 CET 2007 Simon Marlow <simonmar at microsoft.com> * Source links must point to the original module, not the referring module - - - - - 378f4085 by David Waern at 2008-01-06T16:03:45+00:00 Change stability from stable to experimental - - - - - 8bdafe44 by David Waern at 2008-01-06T16:14:22+00:00 Add haskell.vim (it had been removed somehow) - - - - - ea34d02e by David Waern at 2008-01-06T16:36:57+00:00 Change version to 2.0.0.0 - - - - - 34631ac0 by David Waern at 2008-01-06T16:44:57+00:00 Add missing modules to the cabal file - - - - - 9e142935 by David Waern at 2008-01-06T17:25:42+00:00 Depend on ghc >= 6.8.2 && < 6.9 - - - - - 59f9eeaa by Simon Marlow at 2007-12-20T10:43:04+00:00 add build scripts - - - - - 1c29ae30 by Simon Marlow at 2007-12-20T10:47:07+00:00 update version number - - - - - fe16a3e4 by Simon Marlow at 2007-12-20T10:48:03+00:00 update version - - - - - f688530f by Simon Marlow at 2007-12-20T10:48:29+00:00 doc updates - - - - - ce71b611 by David Waern at 2008-01-07T13:46:32+00:00 Change version in docs and spec - - - - - 03ab8d6f by David Waern at 2008-01-07T13:47:38+00:00 Manually merge over changes to CHANGES for 0.9 - - - - - 39f1b042 by David Waern at 2008-01-07T15:17:41+00:00 Remove the -use-package flag, we don't support it anyway - - - - - 7274a544 by David Waern at 2008-01-07T15:33:05+00:00 Update CHANGES for 2.0.0.0 - - - - - 96594f5d by David Waern at 2008-01-07T15:46:49+00:00 Wibble - - - - - f4c5a4c4 by David Waern at 2008-01-07T15:55:36+00:00 Change url to repo in documentation - - - - - 8a4c77f0 by David Waern at 2008-01-07T16:00:54+00:00 Update CHANGES - - - - - cb3a9288 by David Waern at 2008-01-07T16:02:55+00:00 Documentation fix - - - - - d8e45539 by David Waern at 2008-01-07T16:12:00+00:00 Update docs to say that Haddock accets .lhs files and module names - - - - - 4b5ce824 by David Waern at 2008-01-07T16:12:25+00:00 Document -B option - - - - - 47274262 by David Waern at 2008-01-07T16:23:07+00:00 Update CHANGES - - - - - 7ff314a9 by David Waern at 2008-01-07T16:23:20+00:00 Remove --use-package, --package & --no-implicit.. flags from docs - - - - - 6c3819c0 by David Waern at 2008-01-07T16:23:52+00:00 Remove --no-implicit-prelide flag - - - - - 1b14ae40 by David Waern at 2008-01-07T16:32:26+00:00 Update the "Using literate or pre-processed source" section - - - - - 0117f620 by David Waern at 2008-01-07T16:41:55+00:00 Document the --optghc flag - - - - - 087ab1cf by David Waern at 2008-01-07T16:42:10+00:00 Remove the documenation section on derived instances The problem mentioned there doesn't exist in Haddock 2.0.0.0 - - - - - 7253951e by David Waern at 2008-01-07T16:48:40+00:00 Document OPTIONS_HADDOCK - - - - - 3b6bdcf6 by David Waern at 2008-01-07T16:56:54+00:00 Wibble - - - - - 3025adf9 by David Waern at 2008-01-07T17:08:14+00:00 Wibble - - - - - 5f30f1a0 by David Waern at 2008-01-07T17:15:44+00:00 Change synopsis field to description - - - - - 1673f54b by David Waern at 2008-01-07T17:18:21+00:00 Change my email address in the cabal file - - - - - 55aa9808 by David Waern at 2008-01-07T18:18:02+00:00 Add documentation for readInterfaceFile - - - - - eaea417f by David Waern at 2008-01-07T18:21:30+00:00 Export necessary stuff from Distribution.Haddock - - - - - 7ea18759 by David Waern at 2008-01-07T18:31:49+00:00 Remove dep on Cabal - - - - - 7b79c74e by David Waern at 2008-01-07T18:33:49+00:00 Remove dep on process - - - - - ce3054e6 by David Waern at 2008-01-16T23:01:21+00:00 Add feature-requsts from Henning Thielemann to TODO - - - - - 0c08f1ec by David Waern at 2008-01-16T23:03:02+00:00 Record a bug in TODO - - - - - b04605f3 by David Waern at 2008-01-23T16:59:06+00:00 Add a bug reported by Ross to TODO - - - - - 5b17c030 by David Waern at 2008-01-23T18:05:53+00:00 A a bug report to TODO - - - - - 1c993b0d by David Waern at 2008-01-25T16:30:25+00:00 Accept test output - - - - - c22fc0d0 by David Waern at 2008-01-25T16:34:49+00:00 Accept test output - - - - - 4b795811 by David Waern at 2008-01-25T16:38:37+00:00 Change Hidden.hs (test) to use OPTIONS_HADDOCK - - - - - c124dbd9 by David Waern at 2008-01-25T16:39:23+00:00 Accept test output - - - - - ec6f6eea by David Waern at 2008-01-25T16:42:08+00:00 Add Hidden.html.ref to tests - - - - - 1dc9610c by David Waern at 2008-02-02T20:50:51+00:00 Add a comment about UNPACK bug in TODO - - - - - 2d3f7081 by David Waern at 2008-02-09T22:33:24+00:00 Change the representation of DocNames Ross Paterson reported a bug where links would point to the defining module instead of the "best" module for an identifier (e.g Int pointing to GHC.Base instead of Data.Int). This patch fixes this problem by refactoring the way renamed names are represented. Instead of representing them by: > data DocName = Link Name | NoLink Name they are now represented as such: > data DocName = Documented Name Module | Undocumented Name and the the link-env looks like this: > type LinkEnv = Map Name Module There are several reasons for this. First of all, the bug was caused by changing the module part of Names during the renaming process, without changing the Unique field. This caused names to be overwritten during the loading of .haddock files (which caches names using the NameCache of the GHC session). So we might create new Uniques during renaming to fix this (but I'm not sure that would be problem-free). Instead, we just keep the Name and add the Module where the name is best documented, since it can be useful to keep the original Name around (for e.g. source-code location info and for users of the Haddock API). Also, the names Link/NoLink don't really make sense, since wether to use links or not is entirely up to the users of DocName. In the process of following this change into H.Backends.Html I removed the assumption that binder names are Undocumented (which was just an unnecessary assumption, the OccName is the only thing needed to render these). This will probably make it possible to get rid of the renamer and replace it with a traversal from SYB or Uniplate. Since DocName has changed, InterfaceFile has changed so this patch also increments the file-format version. No backwards-compatibility is implemented. - - - - - 0f28c921 by David Waern at 2008-02-09T23:00:36+00:00 H.GHC.Utils: remove unused imports/exports - - - - - 0c44cad5 by David Waern at 2008-02-10T00:28:13+00:00 H.GHC.Utils: add some functions that were removed by mistake - - - - - e3452f49 by David Waern at 2008-02-10T00:28:48+00:00 Fix some trivial warnings in H.InterfaceFile - - - - - a6d74644 by David Waern at 2008-02-10T00:48:06+00:00 Update the version message to fit in small terminals - - - - - 76c9cd3e by David Waern at 2008-02-10T14:47:39+00:00 Remove bugs from TODO that don't apply anymore since the port - - - - - 5e10e090 by David Waern at 2008-02-10T15:22:47+00:00 Remove bugs from TODO that weren't actual bugs - - - - - fef70878 by David Waern at 2008-02-10T15:23:44+00:00 Remove yet another item from TODO that was not an actual bug - - - - - e1af47b8 by David Waern at 2008-02-11T10:25:57+00:00 Bump the version number to 2.1.0 Since the exported datatype DocName has changed, we need to bump the major version number. Let's also drop the fourth version component, it's not that useful. - - - - - e3be7825 by David Waern at 2008-04-11T14:29:04+00:00 Add a bug to TODO - - - - - cb6574be by David Waern at 2008-04-11T16:00:45+00:00 Use the in-place haddock when running tests - - - - - c6d7af0d by David Waern at 2008-04-11T16:09:16+00:00 Turn off GHC warnings when running tests - - - - - 7f61b546 by David Waern at 2008-04-11T17:24:00+00:00 Add a flag for turning off all warnings - - - - - 883b8422 by David Waern at 2008-04-12T14:02:18+00:00 Fix printing of data binders - - - - - 2a0db8fc by David Waern at 2008-04-12T18:52:46+00:00 Fix missing parenthesis in constructor args bug - - - - - 1b3ac3f9 by David Waern at 2008-04-12T18:57:23+00:00 Simplify test suite and add tests I move all tests into one single directory to simplify things, and add a test for the last bug that was fixed. - - - - - 8f178376 by David Waern at 2008-04-12T19:00:15+00:00 Add a script for copying test output to "expected" output - - - - - 193e3a03 by David Waern at 2008-04-12T19:16:37+00:00 Remove two fixed bugs from TODO - - - - - ddc9130c by David Waern at 2008-04-12T19:37:06+00:00 Update test README - - - - - 956069c0 by David Waern at 2008-05-01T12:16:14+00:00 Update version number in spec and docs - - - - - 5478621c by David Waern at 2008-05-01T12:28:12+00:00 Remove claim of backwards compatibility from docs for readInterfaceFile - - - - - 4a16dea9 by David Waern at 2008-05-01T12:33:04+00:00 Update CHANGES - - - - - 804216fb by David Waern at 2008-05-01T12:43:16+00:00 Add a synopsis - - - - - fd0c84d5 by David Waern at 2008-05-01T12:44:44+00:00 Add Haddock.DocName to the cabal file - - - - - 9f4a7439 by David Waern at 2008-05-01T12:45:53+00:00 Remove -fglasgow-exts and -fasm - - - - - aee7c145 by David Waern at 2008-05-01T12:54:01+00:00 Add LANGUAGE pragmas to source files - - - - - 9a58428b by David Waern at 2008-05-01T12:54:19+00:00 Add extensions to cabal file - - - - - 494f1bee by David Waern at 2008-05-01T13:12:09+00:00 Export DocName in the API - - - - - c938196b by David Waern at 2008-05-01T13:12:19+00:00 Add hide options to some source files - - - - - 236e86af by Neil Mitchell at 2008-06-07T20:45:10+00:00 Rewrite the --hoogle flag support - - - - - 6d910950 by Neil Mitchell at 2008-06-14T10:56:50+00:00 Simplify the newtype/data outputting in Hoogle, as haddock does it automatically - - - - - f87a95a8 by Neil Mitchell at 2008-06-14T12:10:18+00:00 Add initial structure for outputting documentation as well, but does not yet output anything - - - - - 7c3bce54 by Neil Mitchell at 2008-06-14T12:27:07+00:00 Remove <document comment> from the Hoogle output - - - - - 9504a325 by Neil Mitchell at 2008-06-16T06:33:21+00:00 Default to "main" if there is no package, otherwise will clobber hoogle's hoogle info - - - - - 4a794a79 by Neil Mitchell at 2008-06-16T06:53:29+00:00 Change packageName to packageStr, as it better reflects the information stored in it - - - - - 7abc9baf by Neil Mitchell at 2008-06-16T07:09:49+00:00 Add modulePkgInfo to Haddock.GHC.Utils, which gives back package name and version info - - - - - 8ca11514 by Neil Mitchell at 2008-06-16T07:13:48+00:00 Change Hoogle to take the package name and package version separately - - - - - a6da452d by Neil Mitchell at 2008-06-18T11:29:46+00:00 In Hoogle do not list things that are not local to this module - - - - - 974b76b7 by David Waern at 2008-06-19T18:40:13+00:00 Be more consistent with GHC API naming in H.GHC.Utils - - - - - 2facb4eb by David Waern at 2008-06-19T19:03:03+00:00 Update test output - - - - - c501de72 by David Waern at 2008-06-26T20:26:49+00:00 Use ghc-paths to get the lib dir The path can still be overridden using the -B flag. It's not longer required to pass the lib dir to the program that runs the test suite. - - - - - ac4c6836 by David Waern at 2008-06-26T20:33:08+00:00 Update CHANGES - - - - - 9d21c60a by David Waern at 2008-06-26T20:34:53+00:00 Update README - - - - - 741448f0 by David Waern at 2008-06-26T21:12:57+00:00 Improve wording in the help message - - - - - b1b42b11 by David Waern at 2008-06-30T10:16:17+00:00 Rename ForeignType - - - - - 6d6c2b34 by David Waern at 2008-06-30T10:25:09+00:00 Rename TyFamily - - - - - 8d1125ed by David Waern at 2008-06-30T10:37:21+00:00 Rename type patterns - - - - - 7610a4cb by David Waern at 2008-06-30T10:45:07+00:00 Rename associated types - - - - - 8eeba14c by David Waern at 2008-06-30T10:47:41+00:00 Remove the TODO file now that we have a trac - - - - - 1af5b25b by David Waern at 2008-07-02T18:19:28+00:00 Render type family declarations (untested) - - - - - ceb99797 by David Waern at 2008-07-02T18:24:06+00:00 Remove redundant check for summary when rendering data types - - - - - b36a58e0 by David Waern at 2008-07-02T22:01:38+00:00 More support for type families and associated types Now we just need to render the instances - - - - - 78784879 by David Waern at 2008-07-07T22:13:58+00:00 Remove filtering of instances We were filtering out all instances for types with unknown names. This was probably an attempt to filter out instances for internal types. I am removing the filtering for the moment, and will try to fix this properly later. - - - - - 3e758dad by David Waern at 2008-06-30T18:50:30+00:00 Run haddock in-place during testing - - - - - d9dab0ce by David Waern at 2008-07-08T21:04:32+00:00 Remove index.html and doc-index.html from output, they should not be versioned - - - - - 3e6c4681 by David Waern at 2008-07-08T21:06:42+00:00 Update test output following change to instance filtering - - - - - e34a3f14 by David Waern at 2008-07-12T16:48:28+00:00 Stop using the map from exported names to declarations During creation of the interface, we were using two maps: one from exported names to declarations, and one from all defined names in the module to declarations. The first contained subordinate names while the second one didn't. The first map was never used to look up names not defined in the associated module, so if we add subordinate names to the second map, we could use it everywhere. That's that this patch does. This simplifies code because we don't have to pass around two maps everywhere. We now store the map from locally defined things in the interface structure instead of the one from exported names. - - - - - 2e1d2766 by David Waern at 2008-07-12T16:55:21+00:00 Get the all locally defined names from GHC API We previously had some code to compute all locally defined names in a module including subordinate names. We don't need it since we can get the names from modInfoTyThings in the GHC API. - - - - - bf637994 by David Waern at 2008-07-13T13:09:16+00:00 Refactoring in H.Interface.Create We were creating a doc map, a declaration map and a list of entities separately by going through the HsGroup. These structures were all used to build the interface of a module. Instead of doing this, we can start by creating a list of declarations from the HsGroup, then collect the docs directly from this list (instead of using the list of entities), creating a documentation map. We no longer need the Entity data type, and we can store a single map from names to declarations and docs in the interface, instead of the declaration map and the doc map. This way, there is only one place where we filter out the declarations that we don't want, and we can remove a lot of code. Another advantage of this is that we can create the exports directly out of the list of declarations when we export the full module contents. (Previously we did a look up for each name to find the declarations). This is faster and removes another point where we depend on names to identify exported declarations, which is good because it eliminates problems with instances (which don't have names). - - - - - 547e410e by David Waern at 2008-07-13T13:34:51+00:00 Remove FastString import and FSLIT macro in H.I.Create -- they were unused - - - - - 693759d1 by David Waern at 2008-07-13T13:36:23+00:00 Remove unused import from H.I.Create - - - - - cde6e7fb by David Waern at 2008-07-13T13:51:54+00:00 Small touches - - - - - 96de8f1d by David Waern at 2008-07-20T11:21:46+00:00 Preparation for rendering instances as separate declarations We want to be able to render instances as separate declarations. So we remove the Name argument of ExportDecl, since instances are nameless. This patch also contains the first steps needed to gather type family instances and display them in the backend, but the implementation is far from complete. Because of this, we don't actually show the instances yet. - - - - - b0f824fb by David Waern at 2008-07-20T15:53:08+00:00 Follow changes to ExportDecl in Hoogle - - - - - 1192eff3 by Neil Mitchell at 2008-06-26T00:28:10+00:00 Change how the Hoogle backend outputs classes, adding the context in - - - - - 7a0d1464 by Neil Mitchell at 2008-06-26T00:28:46+00:00 Remove the indent utility function from Hoogle backend - - - - - 3361241b by Neil Mitchell at 2008-06-26T09:45:09+00:00 Add support for Hoogle writing ForeignImport/ForeignExport properly - - - - - 795ad3bf by Neil Mitchell at 2008-06-26T12:15:25+00:00 Flesh out the Hoogle code to render documentation - - - - - 23277995 by Neil Mitchell at 2008-06-26T14:56:41+00:00 Fix a bug in the Hoogle backend, unordered lists were being written out <ul>...</u> - - - - - db739b27 by Neil Mitchell at 2008-06-26T15:09:54+00:00 Remove any white space around a <li> element - - - - - f2e6bb8c by Neil Mitchell at 2008-07-10T15:30:47+00:00 Remove the TODO in the Hoogle HTML generation, was already done - - - - - 693ec9a3 by Neil Mitchell at 2008-07-10T15:53:00+00:00 Put brackets round operators in more places in the Hoogle output - - - - - 842313aa by Neil Mitchell at 2008-07-10T16:01:25+00:00 Print type signatures with brackets around the name - - - - - cf93deb0 by David Waern at 2008-07-20T17:04:22+00:00 Bump version number to 2.2.0 - - - - - 30e6a8d1 by David Waern at 2008-07-20T17:04:41+00:00 Resolve conflicts in H.B.Hoogle - - - - - 1f0071c9 by David Waern at 2008-07-23T23:05:01+00:00 Add "all" command to runtests.hs that runs all tests despite failures - - - - - f2723023 by David Waern at 2008-07-23T23:08:39+00:00 Update tests/README - - - - - c0304a11 by David Waern at 2008-07-23T23:21:15+00:00 Be compatible with GHC 6.8.3 The cabal file is converted to use the "new" syntax with explicit Library and Executable sections. We define the __GHC_PATCHLEVEL__ symbol using a conditinal cpp-options field in the cabal file. (Ideally, Cabal would define the symbol for us, like it does for __GLASGOW_HASKELL__). We use these symbols to #ifdef around a small difference between 6.8.2 and 6.8.3. Previously, we only supported GHC 6.8.2 officially but the dependencies field said "ghc <= 6.9". This was just for convenience when testing against the (then compatible) HEAD version of GHC, and was left in the release by mistake. Now, we support both GHC 6.8.2 and 6.8.3 and the dependencies field correctly reflects this. - - - - - 88a5fe71 by David Waern at 2008-07-23T23:54:16+00:00 Depend on the currently available ghc-paths versions only - - - - - 8738d97b by David Waern at 2008-07-24T10:50:44+00:00 FIX haskell/haddock#44: Propagate parenthesis level when printing documented types - - - - - 05339119 by David Waern at 2008-07-24T16:06:18+00:00 Drop unnecessary parenthesis in types, put in by the user We were putting in parenthesis were the user did. Let's remove this since it just clutters up the types. The types are readable anyway since we print parens around infix operators and do not rely on fixity levels. When doing this I discovered that we were relying on user parenthesis when printin types like (a `O` b) c. This patchs fixes this problem so that parenthesis are always inserted around an infix op application in case it is applied to further arguments, or if it's an arguments to a type constructor. Tests are updated. - - - - - b3a99828 by David Waern at 2008-07-24T10:19:43+00:00 Print parenthesis around non-atomic banged types Fixes half of haskell/haddock#44 - - - - - ab5238e0 by David Waern at 2008-07-24T22:07:49+00:00 Add a reference file for the TypeFamilies test - - - - - 1941cc11 by David Waern at 2008-07-25T17:15:53+00:00 Simplify definition of pretty and trace_ppr - - - - - e3bfa33c by David Waern at 2008-07-25T17:18:27+00:00 Warning messages Output a warning when filtering out data/type instances and associated types in instances. We don't show these in the documentation yet, and we need to let the user know. - - - - - 9b85fc89 by David Waern at 2008-07-25T17:45:40+00:00 Doc: Mention Hoogle in the Introduction - - - - - afb2dd60 by David Waern at 2008-07-25T17:49:00+00:00 Doc: update -B description - - - - - 584c0c91 by David Waern at 2008-07-25T18:11:38+00:00 Doc: describe -w flag - - - - - 77619c24 by David Waern at 2008-07-28T12:29:07+00:00 Remove TODO from cabal file - - - - - 96717d5f by David Waern at 2008-07-28T12:29:27+00:00 Support type equality predicates - - - - - c2fd2330 by David Waern at 2008-07-29T19:45:14+00:00 Move unL from H.B.Hoogle to H.GHC.Utils I like Neil's shorter unL better than unLoc from the GHC API. - - - - - c4c3bf6a by David Waern at 2008-07-29T19:47:36+00:00 Do not export ATs when not in list of subitems - - - - - bf9a7b85 by David Waern at 2008-08-03T11:42:59+00:00 Filter out ForeignExports - - - - - df59fcb0 by David Waern at 2008-08-03T14:02:51+00:00 Filter out more declarations The previous refactorings in H.I.Create introduced a few bugs. Filtering of some types of declarations that we don't handle was removed. This patch fixes this. - - - - - 2f8a958b by David Waern at 2008-08-03T15:24:07+00:00 Move reL to H.GHC.Utils so we can use it everywhere - - - - - 8ec15efd by David Waern at 2008-08-03T15:25:00+00:00 Use isVanillaLSig from GHC API instead of home brewn function - - - - - 300f93a2 by David Waern at 2008-08-03T15:25:27+00:00 Filter out separately exported ATs This is a quick and dirty hack to get rid of separately exported ATs. We haven't decided how to handle them yet. No warning message is given. - - - - - 8776d1ec by David Waern at 2008-08-03T16:21:21+00:00 Filter out more declarations and keep only vanilla type sigs in classes - - - - - ea07eada by David Waern at 2008-08-03T16:48:00+00:00 Fix layout - - - - - dd5e8199 by David Waern at 2008-08-03T16:50:52+00:00 Move some utility functions from H.I.Create to H.GHC.Utils - - - - - 4a1dbd72 by David Waern at 2008-08-03T17:39:55+00:00 Do not filter out doc declarations - - - - - 0bc8dca4 by David Waern at 2008-08-03T17:47:26+00:00 Filter out separately exported ATs (take two) - - - - - af970fe8 by David Waern at 2008-08-03T22:39:17+00:00 Update CHANGES - - - - - 5436ad24 by David Waern at 2008-08-03T22:40:20+00:00 Bump version number to 2.2.1 - - - - - d66de448 by David Waern at 2008-08-05T19:00:32+00:00 Remove version restriction on ghc-paths - - - - - 534b1364 by David Waern at 2008-08-05T19:04:35+00:00 Bump version to 2.2.2 and update CHANGES - - - - - 549188ff by David Waern at 2008-08-05T19:16:49+00:00 Fix CHANGES - - - - - 0d156bb4 by Luke Plant at 2008-08-11T15:20:59+00:00 invoking haddock clarification and help - - - - - 748295cc by David Waern at 2008-08-11T18:56:37+00:00 Doc: say that the --hoogle option is functional - - - - - 43301db4 by David Waern at 2008-08-05T19:26:08+00:00 Change ghc version dependency to >= 6.8.2 - - - - - 3e5a53b6 by David Waern at 2008-08-10T22:42:05+00:00 Make H.GHC.Utils build with GHC HEAD - - - - - 7568ace0 by David Waern at 2008-08-11T19:41:54+00:00 Import Control.OldException instead of C.Exception when using ghc >= 6.9 We should really test for base version instead, but I don't currently know which version to test for. - - - - - b71ae991 by David Waern at 2008-08-12T22:40:39+00:00 Make our .haddock file version number depend on the GHC version We need to do this, since our .haddock format can potentially change whenever GHC's version changes (even when only the patchlevel changes). - - - - - 6307ce3f by David Waern at 2008-08-12T22:49:57+00:00 Remove matching on NoteTy in AttachInstances, it has been removed - - - - - 2dbcfd5f by David Waern at 2008-08-12T23:02:02+00:00 Comment out H.GHC.loadPackages - it is unused and doesn't build with ghc >= 6.9 - - - - - c74db5c2 by David Waern at 2008-08-12T23:03:58+00:00 Hide <.> from GHC import in Hoogle only for ghc <= 6.8.3 - - - - - 69a44ebb by David Waern at 2008-08-12T23:11:12+00:00 Follow changes to parseDynamic/StaticFlags - - - - - 5881f3f0 by David Waern at 2008-08-13T21:43:58+00:00 Add __GHC_PATCHLEVEL__ symbol also when building the library - - - - - 8574dc11 by David Waern at 2008-08-13T21:44:17+00:00 Follow move of package string functions from PackageConfig to Module - - - - - c9baa77f by David Waern at 2008-08-13T21:45:29+00:00 Follow extensible exceptions changes - - - - - 9092de15 by David Waern at 2008-08-13T21:46:20+00:00 Update test following Haddock version change - - - - - ebe569a4 by David Waern at 2008-08-13T21:46:54+00:00 Follow changes to parseDynamic- parseStaticFlags in GHC - - - - - b8a5ffd3 by David Waern at 2008-08-13T21:47:36+00:00 Follow changes to Binary in GHC 6.9 - - - - - edfda1cc by David Waern at 2008-08-13T21:50:17+00:00 Change ghc version dependency to >= 6.8.2 && <= 6.9 - - - - - d59be1cf by Neil Mitchell at 2008-08-12T16:02:53+00:00 Output all items, even if they are not defined in this module - ensures map comes from Prelude, not just GHC.Base - - - - - dda93b9f by Neil Mitchell at 2008-08-12T21:37:32+00:00 Add support for type synonyms to Hoogle, was accidentally missing before (woops!) - - - - - b6ee795c by Neil Mitchell at 2008-08-13T14:03:24+00:00 Generalise Hoogle.doc and add a docWith - - - - - 415e1bb2 by Neil Mitchell at 2008-08-13T14:03:46+00:00 Make Hoogle add documentation to a package - - - - - 790a1202 by Neil Mitchell at 2008-08-18T12:52:43+00:00 Use the same method to put out signatures as class methods in the Hoogle backend - - - - - ded37eba by Neil Mitchell at 2008-08-18T12:53:04+00:00 Remove Explicit top-level forall's when pretty-printing signatures - - - - - 6468c722 by Neil Mitchell at 2008-08-20T07:59:13+00:00 Simplify the code by removing not-to-important use of <.> in the Hoogle back end - - - - - 788c3a8b by Neil Mitchell at 2008-08-21T18:20:24+00:00 In the hoogle back end, markup definition lists using <i>, not <b> - - - - - 77d4b000 by Ian Lynagh at 2008-08-14T10:49:14+00:00 Add a Makefile for GHC's build system. Still won't work yet, but we're closer - - - - - 920440d7 by Ian Lynagh at 2008-08-27T18:06:46+00:00 Add haddock.wrapper - - - - - bcda925f by Ian Lynagh at 2008-08-27T18:07:02+00:00 Add a manual Cabal flag to control the ghc-paths dependency - - - - - 04d194e2 by Ian Lynagh at 2008-08-27T20:41:27+00:00 Update extensions in Cabal file Use ScopedTypeVariables instead of PatternSignatures - - - - - 12480043 by Ian Lynagh at 2008-08-27T20:41:55+00:00 Increase the upper bound on the GHC version number - - - - - b1f809a5 by Ian Lynagh at 2008-08-27T21:32:22+00:00 Fix some warnings - - - - - aea0453d by Ian Lynagh at 2008-08-28T14:22:29+00:00 Fixes for using haddock in a GHC build tree - - - - - ad23bf86 by Ian Lynagh at 2008-08-28T21:14:27+00:00 Don't use Cabal wrappers on Windows - - - - - 35858e4c by Ian Lynagh at 2008-08-29T00:07:42+00:00 Fix in-tree haddock on Windows - - - - - c2642066 by Ian Lynagh at 2008-09-03T22:35:53+00:00 follow library changes - - - - - 2eb55d50 by Ian Lynagh at 2008-09-07T18:52:51+00:00 bindist fixes - - - - - 3daa5b59 by Ian Lynagh at 2008-09-10T16:58:18+00:00 We need to tell haddock that its datasubdir is . or it can't find package.conf - - - - - 388fd8c2 by Ian Lynagh at 2008-09-10T19:47:44+00:00 Fix haddock inplace on Windows - - - - - 70a641c1 by Ian Lynagh at 2008-09-10T22:15:44+00:00 Fix installed haddock on Windows - - - - - 83c1e997 by Neil Mitchell at 2008-09-11T10:48:55+00:00 Import GHC.Paths if not IN_GHC_TREE, seems to match the use of GHC.Paths functions much better - - - - - b452519b by Ian Lynagh at 2008-09-12T12:58:24+00:00 Add a LANGUAGE ForeignFunctionInterface pragma - - - - - afbd592c by Ian Lynagh at 2008-09-12T12:59:13+00:00 Wibble imports - - - - - 547ac4ad by Ian Lynagh at 2008-09-14T15:34:22+00:00 Add a "#!/bin/sh" to haddock.wrapper - - - - - f207a807 by Ian Lynagh at 2008-09-15T10:02:32+00:00 Use "exec" when calling haddock in the wrapper - - - - - 2ee68509 by Thomas Schilling at 2008-09-15T09:09:16+00:00 Port Haddock.Interface to new GHC API. This required one bigger change: 'readInterfaceFile' used to take an optional 'Session' argument. This was used to optionally update the name cache of an existing GHC session. This does not work with the new GHC API, because an active session requires the function to return a 'GhcMonad' action, but this is not possible if no session is provided. The solution is to use an argument of functions for reading and updating the name cache and to make the function work for any monad that embeds IO, so it's result type can adapt to the calling context. While refactoring, I tried to make the code a little more self-documenting, mostly turning comments into function names. - - - - - 3bb96431 by Thomas Schilling at 2008-09-15T09:09:37+00:00 Reflect GHC API changes. - - - - - 2e60f714 by Thomas Schilling at 2008-09-15T09:10:37+00:00 Port Haddock.GHC.Typecheck to new GHC API. - - - - - 9cfd4cff by Thomas Schilling at 2008-09-15T09:11:00+00:00 Port Haddock.GHC to new GHC API. - - - - - caffa003 by Thomas Schilling at 2008-09-15T09:11:25+00:00 Port Main to new GHC API. - - - - - 069a4608 by Ian Lynagh at 2008-09-21T11:19:00+00:00 Fix paths used on Windows frmo a GHC tree: There is no whare directory - - - - - 7ceee1f7 by Ian Lynagh at 2008-09-21T12:20:16+00:00 Fix the in-tree haddock on Windows - - - - - 0d486514 by Ian Lynagh at 2008-09-23T18:06:58+00:00 Increase the GHC upper bound from 6.11 to 6.13 - - - - - f092c414 by Neil Mitchell at 2008-09-11T14:56:07+00:00 Do not wrap __ in brackets - - - - - 036bdd13 by Ian Lynagh at 2008-09-28T01:42:35+00:00 Fix building haddock when GhcProfiled=YES - - - - - 01434a89 by David Waern at 2008-09-24T20:24:21+00:00 Add PatternSignatures LANGUAGE pragma to Main and Utils - - - - - 1671a750 by David Waern at 2008-10-02T22:57:25+00:00 For source links, get original module from declaration name instead of environment. Getting it from the environment must have been a remnant from the times when we were using unqualified names (versions 0.x). - - - - - a25dde99 by David Waern at 2008-10-02T22:59:57+00:00 Remove ifaceEnv from Interface - it's no longer used - - - - - 610993da by David Waern at 2008-10-02T23:04:58+00:00 Write a comment about source links for type instance declarations - - - - - 5a96b5d5 by Thomas Schilling at 2008-10-03T10:45:08+00:00 Follow GHC API change of parseModule. - - - - - 5a943ae5 by Ian Lynagh at 2008-10-03T15:56:58+00:00 TAG 2008-10-03 - - - - - 76cdd6ae by Thomas Schilling at 2008-10-08T12:29:50+00:00 Only load modules once when typechecking with GHC. This still doesn't fix the memory leak since the typechecked source is retained and then processed separately. To fix the leak, modules must be processed directly after typechecking. - - - - - 7074d251 by David Waern at 2008-10-09T23:53:54+00:00 Interleave typechecking with interface creation At the same time, we fix a bug where the list of interfaces were processed in the wrong order, when building the links and renaming the interfaces. - - - - - 4b9b2b2d by David Waern at 2008-10-09T23:54:49+00:00 Add some strictness annotations in Interface We add some strictness annotations to the fields of Interface, so that less GHC data is hold on to during processing. - - - - - 22035628 by David Waern at 2008-10-10T20:02:31+00:00 Remove typecheckFiles and MonadUtils import from H.GHC.Typeccheck - - - - - be637ad3 by David Waern at 2008-10-10T20:33:38+00:00 Make Haddock build with GHC 6.8.2 - - - - - 523b3404 by David Waern at 2008-10-10T21:08:09+00:00 Fix documentation for createInterfaces - - - - - e1556702 by David Waern at 2008-10-10T21:26:19+00:00 Hide H.Utils in library - - - - - a8e751c3 by David Waern at 2008-10-10T21:34:59+00:00 Add back .haddock file versioning based on GHC version It was accidentally removed in the patch for GHC 6.8.2 compatibility - - - - - 06fb3c01 by David Waern at 2008-10-10T21:47:15+00:00 Bump version number to 2.3.0 - - - - - ff087fce by David Waern at 2008-10-10T22:35:49+00:00 Add support for DocPic The support for DocPic was merged into the GHC source long ago, but the support in Haddock was forgotten. Thanks Peter Gavin for submitting this fix! - - - - - 3af85bf6 by David Waern at 2008-10-10T23:34:05+00:00 Update tests - - - - - 0966873c by Simon Marlow at 2008-10-10T14:43:04+00:00 no need for handleErrMsg now, we don't throw any ErrMsgs - - - - - f1870de3 by Clemens Fruhwirth at 2008-10-10T13:29:36+00:00 Compile with wrapper but remove it for dist-install - - - - - 7b440dc2 by David Waern at 2008-10-11T14:02:25+00:00 Remove interface from LinksInfo It was there to know the documentation home module when creating a wiki link, but we already know this since we have the DocName. - - - - - e5729e6a by David Waern at 2008-10-15T20:49:18+00:00 Wibble - - - - - b2a8e01a by David Waern at 2008-10-15T21:03:36+00:00 Use type synonyms for declarations and docs in H.I.Create - - - - - be71a15b by David Waern at 2008-10-15T21:12:17+00:00 Comment out unused type family stuff completely - - - - - 91aaf075 by David Waern at 2008-10-15T21:49:04+00:00 Wibble - - - - - 42ba4eb4 by David Waern at 2008-10-15T21:53:53+00:00 Move convenient type synonym to H.Types - - - - - db11b723 by David Waern at 2008-10-15T22:14:07+00:00 Add DeclInfo to H.Types - - - - - 193552b6 by David Waern at 2008-10-15T22:15:01+00:00 Add subordinates with docs to the declaration map The only place in the code where we want the subordinates for a declaration is right after having looked up the declaration in the map. And since we include subordinates in the map, we might as well take the opportunity to store those subordinates that belong to a particular declaration together with that declaration. We also store the documentation for each subordinate. - - - - - 31e6eebc by David Waern at 2008-10-16T17:18:47+00:00 Wibble - - - - - 0dcbd79f by David Waern at 2008-10-16T20:58:42+00:00 Fix haskell/haddock#61 We were not getting docs for re-exported class methods. This was because we were looking up the docs in a map made from the declarations in the current module being rendered. Obviously, re-exported class methods come from another module. Class methods and ATs were the only thing we were looking up using the doc map, everything else we found in the ExporItems. So now I've put subordinate docs in the ExportItem's directly, to make things a bit more consistent. To do this, I added subordinates to the the declarations in the declaration map. This was easy since we were computing subordinates anyway, to store stand-alone in the map. I added a new type synonym 'DeclInfo', which is what we call what is now stored in the map. This little refactoring removes duplicate code to retrieve subordinates and documentation from the HsGroup. - - - - - de47f20a by David Waern at 2008-10-16T22:06:35+00:00 Document function and improve its layout - - - - - e74e625a by Thomas Schilling at 2008-10-20T11:12:57+00:00 Force interface more aggressively. For running Haddock on GHC this reduces memory usage by about 50 MB on a 32 bit system. A heap profile shows total memory usage peak at about 100 MB, but actual usage is at around 300 MB even with compacting GC (+RTS -c). - - - - - b63ac9a1 by David Waern at 2008-10-20T20:25:50+00:00 Make renamer consistent Instead of explicitly making some binders Undocumented, treat all names the same way (that is, try to find a Documented name). - - - - - f6de0bb0 by Ian Lynagh at 2008-09-19T00:54:43+00:00 TAG GHC 6.10 fork - - - - - 74599cd0 by David Waern at 2008-10-20T21:13:24+00:00 Do not save hidden modules in the .haddock file We were saving interfaces of all processed modules including those hidden using {-# OPTIONS_HADDOCK hide #-} in the .haddock file. This caused broken links when generating the index for the libraries that come with GHC. This patch excludes modules with hidden documentation when writing .haddock files. It should fix the above problem. - - - - - 7b6742e9 by David Waern at 2008-10-21T19:54:52+00:00 Do not save hidden modules in the .haddock file (also for ghc >= 6.9) When writing the first patch, I forgot to do the fix in both branches of an #if macro. - - - - - b99b1951 by David Waern at 2008-10-22T20:04:18+00:00 Remove subordinate map and its usage It is not needed now that we store subordinate names in the DeclInfo map. - - - - - da97cddc by David Waern at 2008-10-22T20:11:46+00:00 Tidy up code in H.I.Create a little Remove commented out half-done type instance support, and remove DeclWithDoc synonym. - - - - - 6afa76f3 by David Waern at 2008-10-22T21:17:29+00:00 Fix warnings in H.GHC.Utils - - - - - 171ea1e8 by David Waern at 2008-10-22T21:35:04+00:00 Fix warnings in H.Utils - - - - - c8cb3b91 by David Waern at 2008-10-22T21:36:49+00:00 Wibble - - - - - 767fa06a by David Waern at 2008-10-27T19:59:04+00:00 Make named doc comments into ExportDoc instead of ExportDecl Fixes a crash when processing modules without export lists containing named docs. - - - - - e638bbc6 by David Waern at 2008-11-02T22:21:10+00:00 Add HCAR entry - - - - - 92b4ffcf by David Waern at 2008-11-02T22:44:19+00:00 Update CHANGES - - - - - 84d4da6e by David Waern at 2008-11-03T11:25:04+00:00 Add failing test for template haskell crash - - - - - 2a9cd2b1 by David Waern at 2008-11-04T21:13:44+00:00 Add tests/TH.hs - - - - - 8a59348e by David Waern at 2008-11-04T21:30:26+00:00 TAG 2.3.0 - - - - - 54f70d31 by Thomas Schilling at 2008-10-24T17:04:08+00:00 Enable framed view of the HTML documentation. This patch introduces: - A page that displays the documentation in a framed view. The left side will show a full module index. Clicking a module name will show it in the right frame. If Javascript is enabled, the left side is split again to show the modules at the top and a very short synopsis for the module currently displayed on the right. - Code to generate the mini-synopsis for each module and the mini module index ("index-frames.html"). - CSS rules for the mini-synopsis. - A very small amount of javascript to update the mini-synopsis (but only if inside a frame.) Some perhaps controversial things: - Sharing code was very difficult, so there is a small amount of code duplication. - The amount of generated pages has been doubled, since every module now also gets a mini-synopsis. The overhead should not be too much, but I haven't checked. Alternatively, the mini-synopsis could also be generated using Javascript if we properly annotate the actual synopsis. - - - - - 5d7ea5a6 by David Waern at 2008-11-04T23:20:17+00:00 Follow change to ExportDecl in frames code - - - - - 60e16308 by David Waern at 2008-11-04T23:35:26+00:00 Update CHANGES - - - - - d63fd26d by David Waern at 2008-11-04T23:37:43+00:00 Bump version number - - - - - c1660c39 by David Waern at 2008-11-04T23:44:46+00:00 Update CHANGES - - - - - 995ab384 by David Waern at 2008-11-04T23:55:21+00:00 Remove .ref files from tests/output/ - - - - - 1abbbe75 by David Waern at 2008-11-04T23:57:41+00:00 Output version info before running tests - - - - - 649b182f by David Waern at 2008-11-05T22:45:37+00:00 Add ANNOUNCE message - - - - - c36ae0bb by David Waern at 2008-11-05T23:15:35+00:00 Update ANNOUNCE - - - - - 9c4f3d40 by David Waern at 2008-11-05T23:18:30+00:00 Wibble - - - - - 5aac87ce by David Waern at 2008-11-06T21:07:48+00:00 Depend on base 4.* when using GHC >= 6.9, otherwise 3.* - - - - - b9796a74 by David Waern at 2008-11-06T21:13:40+00:00 Bump version to 2.4.1 and update CHANGES - - - - - d4b26baa by David Waern at 2008-11-06T21:26:33+00:00 Depend on base 4.0.* instead of 4.* - - - - - 2cb0903c by David Waern at 2008-11-06T21:46:53+00:00 Fix warnings in H.B.HH and H.B.HH2 - - - - - e568e89a by David Waern at 2008-11-06T21:47:12+00:00 Fix warnings in Haddock.ModuleTree - - - - - 9dc14fbd by David Waern at 2008-11-06T21:47:52+00:00 Fix warnings in Haddock.Version - - - - - 02ac197c by David Waern at 2008-11-06T21:51:31+00:00 Fix warnings in H.InterfaceFile and H.Options - - - - - 63e7439a by David Waern at 2008-11-06T21:59:45+00:00 Fix warnings in H.GHC.Typecheck - - - - - 4bca5b68 by David Waern at 2008-11-08T13:43:42+00:00 Set HscTarget to HscNothing instead of HscAsm There used to be a bug in the GHC API that prevented us from setting this value. - - - - - 07357aec by David Waern at 2008-11-09T22:27:00+00:00 Re-export NameCache and friends from Distribution.Haddock - - - - - ea554b5a by David Waern at 2008-11-09T23:14:10+00:00 Add Haddock.GHC.Utils to other-modules in library - - - - - 74aecfd7 by David Waern at 2008-11-10T01:18:57+00:00 Export DocName in the library - - - - - 241a58b3 by David Waern at 2008-11-10T01:19:18+00:00 Document the functions in H.DocName - - - - - edc2ef1b by David Waern at 2008-11-10T01:20:52+00:00 Export H.DocName in the library - - - - - 4f588d55 by David Waern at 2008-11-10T01:29:14+00:00 Make DocName an instance of NamedThing - - - - - b4647244 by David Waern at 2008-11-15T22:58:18+00:00 Reflect version bump in test suite - - - - - 4bee8ce2 by David Waern at 2008-11-15T22:58:45+00:00 Update tests For unknown reasons, test output for Bug1 and Test has changed for the better. - - - - - 1690e2f9 by David Waern at 2008-11-15T22:59:33+00:00 Store hidden modules in .haddock files We store documentation for an entity in the 'InstalledInterface' of the definition site module, and never in the same structure for a module which re-exports the entity. So when a client of the Haddock library wants to look up some documentation, he/she might need to access a hidden module. But we currently don't store hidden modules in the .haddock files. So we add the hidden modules and the Haddock options to the .haddock files. The options will be used to filter the module list to obtain the visible modules only, which is necessary for generating the contents and index for installed packages. - - - - - 8add6435 by David Waern at 2008-11-16T14:35:50+00:00 Bump major version number due to .haddock file format change - - - - - 48bfcf82 by David Waern at 2008-11-23T14:32:52+00:00 Update tests to account for version number bump - - - - - 0bbd1738 by David Waern at 2008-11-23T14:33:31+00:00 HADDOCK_DATA_DIR changed to haddock_datadir - - - - - 5088b78c by David Waern at 2008-11-23T17:13:21+00:00 FIX haskell/haddock#45: generate two anchors for each name We generate two anchor tags for each name, one where we don't escape the name and one where we URI-encode it. This is for compatibility between IE and Opera. Test output is updated. - - - - - 5ee5ca3b by Neil Mitchell at 2008-11-27T14:38:11+00:00 Drop HsDocTy annotations, they mess up pretty printing and also have a bracketing bug (#2584) - - - - - 51c014e9 by Roman Cheplyaka at 2008-11-27T22:27:36+00:00 Allow referring to a specific section within a module in a module link Fixes haskell/haddock#65 - - - - - 4094bdc5 by David Waern at 2008-11-28T21:13:33+00:00 Update tests following anchor change - - - - - f89552dd by Thomas Schilling at 2008-11-29T16:16:20+00:00 Haddock really shouldn't try to overwrite files. - - - - - 98127499 by David Waern at 2008-12-07T14:09:15+00:00 Solve conflict - - - - - 319356c5 by David Waern at 2008-10-22T21:16:55+00:00 Add -Wall -Werror to ghc-options - - - - - 3c4968c9 by David Waern at 2008-11-04T23:38:56+00:00 TAG 2.4.0 - - - - - 4b21e003 by David Waern at 2008-11-06T21:14:04+00:00 TAG 2.4.1 - - - - - 8e0cad5c by David Waern at 2008-12-07T14:12:54+00:00 Remove -Werror - - - - - 299d6deb by David Waern at 2008-12-07T14:25:18+00:00 Remove -Wall, we'll focus on warnings after 6.10.2 is out - - - - - 5f4216b6 by David Waern at 2008-12-07T20:58:05+00:00 Resolve conflict properly - - - - - 67d774e7 by Neil Mitchell at 2008-12-15T11:44:26+00:00 Make forall's in constructors explicit, i.e. data Foo = Foo {foo :: Eq a => a} - - - - - 61851792 by Neil Mitchell at 2008-12-18T15:39:39+00:00 Try and find a better package name than "main" for Hoogle, goes wrong when working on an executable rather than a library - - - - - 2fab8554 by David Waern at 2008-12-08T23:19:48+00:00 Make visible names from ExportItems Instead of a complicated calculation of visible names out of GHC's export items, we can get them straight out of the already calculated ExportItems. The ExportItems should represent exactly those items that are visible in an interface. If store all the exported sub-names in ExportDecl instead of only those with documentation, the calculation becomes very simple. So we do this change as well (should perhaps have been a separate patch). This should fix the problem with names from ghc-prim not appearing in the link environment. - - - - - 7caadd8c by Ian Lynagh at 2008-12-11T17:01:04+00:00 Wrap the GHC usage with defaultCleanupHandler This fixes a bug where haddock leaves /tmp/ghc* directories uncleaned. - - - - - 7c9fc9a5 by David Waern at 2009-01-02T21:38:27+00:00 Show re-exported names from external packages again This fixes GHC ticket 2746. In order to also link to the exported subordinate names of a declaration, we need to re-introduce the sub map in the .haddock files. - - - - - 119e4e05 by David Waern at 2009-01-06T23:34:17+00:00 Do not process boot modules We should of course not try to produce documentation for boot modules! The reason this has worked in the past is that the output of "real" modules overwrites the output of boot modules later in the process. However, this causes a subtle link environment problem. So let's get rid of this stupid behaviour. We avoid processing boot modules, but we continue to typecheck them. - - - - - c285b9d2 by David Waern at 2009-01-08T18:03:36+00:00 Export modules also when coming from external packages This seems to have regressed since a refactoring that was part of the 2.3.0 release. - - - - - 24031c17 by David Waern at 2009-01-10T15:26:26+00:00 Change version to 2.4.2 - no need to go to 2.5.0 - - - - - 864d1c3f by David Waern at 2009-01-10T15:35:20+00:00 Update tests to account for version number change - - - - - 524ba886 by David Waern at 2009-01-10T18:29:17+00:00 Add test for Template Haskell splicing - - - - - 05e6e003 by David Waern at 2009-01-10T19:35:42+00:00 Fix Trac haskell/haddock#68: Turn on compilation via C for Template Haskell packages We can't use HscNothing if we need to run code coming from modules inside the processed package during typechecking, which is the case for some packages using Template Haskell. This could be improved, to e.g. use HscInterpreted and HscNothing where possible, instead of using HscC for all modules in the package. - - - - - 2b2bafa1 by David Waern at 2009-01-10T20:22:25+00:00 Only use needsTemplateHaskell when compiling with GHC 6.10.2 or above - - - - - bedc3a93 by Ian Lynagh at 2009-01-11T14:58:41+00:00 Fix the location of INPLACE_PKG_CONF; fixes the build Spotted by Conal Elliott - - - - - 943107c8 by David Waern at 2009-01-20T19:27:39+00:00 Document H.I.Create.collectDocs better - - - - - c6252e37 by David Waern at 2009-01-20T19:29:51+00:00 Fix Trac haskell/haddock#59: TH-generated declarations disappearing This patch was contributed by Joachim Breitner (nomeata). - - - - - 3568a6af by David Waern at 2009-01-21T21:41:48+00:00 Do not indicate that a constructor argument is unboxed We only show the strictness annotation for an unboxed constructor argument. The fact that it is unboxed is an implementation detail and should not be part of the module interface. - - - - - 562a4523 by David Waern at 2009-01-22T18:53:49+00:00 Fix Trac haskell/haddock#50: do not attach docs to pragmas or other kinds of non-declarations We now filter out everything that is not a proper Haskell declaration before collecting the docs and attaching them to declarations. - - - - - 6fdf21c2 by David Waern at 2009-01-22T19:48:09+00:00 Add test for quasi quotation. No reference output yet. - - - - - dc4100fd by David Waern at 2009-01-22T19:57:47+00:00 Improve quasi-quotation test and add reference output - - - - - 908b74bb by David Waern at 2009-01-23T23:22:03+00:00 Filter out separately exported associated types in a smarter way - - - - - f6b42ecb by David Waern at 2009-01-24T16:54:39+00:00 Correct spelling mistake in error message - - - - - 24e4245d by David Waern at 2009-01-24T17:48:03+00:00 Correct comment - - - - - b5e8462f by David Waern at 2009-02-07T13:22:29+00:00 Do not show a subordinate at the top level if its parent is also exported See note in the source code for more info. - - - - - 4b09de57 by David Waern at 2009-02-07T13:53:53+00:00 Update test following change to top level subordinates - - - - - 76379896 by David Waern at 2009-02-07T13:58:04+00:00 Remove html files in the tests/output/ directory which have been accidentally added - - - - - 1a6d8b10 by Joachim Breitner at 2009-02-20T10:29:43+00:00 Typo in comment - - - - - fec367d0 by David Waern at 2009-02-24T20:21:17+00:00 Fix small bug The rule is to prefer type constructors to other things when an identifier in a doc string can refer to multiple things. This stopped working with newer GHC versions (due to a tiny change in the GHC renamer). We implement this rule in the HTML backend for now, instead of fixing it in GHC, since we will move renaming of doc strings to Haddock in the future anyway. - - - - - 9b4172eb by David Waern at 2009-02-25T20:04:38+00:00 Fix bad error handling with newer GHCs When support for GHC 6.10 was added, an error handler was installed only around the typechecking phase. This had the effect that errors thrown during dependency chasing were caught in the top-level exception handler and not printed with enough detail. With this patch we wrap the error handler around all our usage of the Ghc monad. - - - - - de2df363 by Simon Peyton Jones at 2009-02-02T16:47:42+00:00 Hide funTyConName, now exported by TypeRep - - - - - 4d40a29f by Ian Lynagh at 2009-02-12T18:57:49+00:00 Don't build the library when building in the GHC tree - - - - - 1cd0abe4 by Ian Lynagh at 2009-02-13T13:58:53+00:00 Add a ghc.mk - - - - - 3d814eeb by Ian Lynagh at 2009-02-13T18:50:28+00:00 do .depend generation for haddock with the stage1 compiler This is a bit of a hack. We mkdepend with stage1 as if .depend depends on the stage2 compiler then make goes wrong: haddock's .depend gets included, which means that make won't reload until it's built, but we can't build it without the stage2 compiler. We therefore build the stage2 compiler before its .depend file is available, and so compilation fails. - - - - - b55036a4 by Ian Lynagh at 2009-02-25T01:38:13+00:00 Give haddock a wrapper on unix in the new GHC build system - - - - - 9eabfe68 by Ian Lynagh at 2009-02-25T19:21:32+00:00 Create inplace/lib/html in the new GHC build system - - - - - 93af30c7 by Ian Lynagh at 2008-11-07T19:18:23+00:00 TAG GHC 6.10.1 release - - - - - 06e6e34a by Thomas Schilling at 2009-02-24T18:11:00+00:00 Define __GHC_PATCHLEVEL__ for recent version of GHC (stable). - - - - - 680e6ed8 by Thomas Schilling at 2009-02-24T18:12:26+00:00 'needsTemplateHaskell' is not defined in current stable GHC. - - - - - 6c5619df by David Waern at 2009-02-25T22:15:23+00:00 Hide fynTyConName only for recent GHC versions - - - - - 6b2344f1 by Ian Lynagh at 2009-02-26T00:49:56+00:00 Add the module to one of haddocks warnings - - - - - e5d11c70 by David Waern at 2009-02-27T21:37:20+00:00 Bug fix We tried to filter out subordinates that were already exported through their parent. This didn't work properly since we were in some cases looking at the grand-parent and not the parent. We now properly compute all the parent-child relations of a declaration, and use this information to get the parent of a subordinate. We also didn't consider record fields with multiple parents. This is now handled correctly. We don't currently support separately exported associated types. But when we do, they should be handled correctly by this process too. Also slightly improved the warning message that we give when filtering out subordinates. - - - - - 10a79a60 by David Waern at 2009-02-27T22:08:08+00:00 Fix error message conflict The module name is already written in the beginning of the message, as seems to be the convention in Haddock. Perhaps not so clear, but we should change it everywhere in that case. Leaving it as it is for now. - - - - - c5055c7f by David Waern at 2009-02-27T22:15:17+00:00 Shorten warning message - - - - - a72fed3a by David Waern at 2009-02-28T00:53:55+00:00 Do not show package name in warning message - - - - - a5daccb2 by Ian Lynagh at 2009-03-01T14:59:35+00:00 Install haddock in the new GHC build system - - - - - dfdb025c by Ian Lynagh at 2009-03-07T23:56:29+00:00 Relax base dependency to < 4.2, not < 4.1 - - - - - 5769c8b4 by David Waern at 2009-03-21T14:58:52+00:00 Bump .haddock file version number (due to change of format) - - - - - f1b8f67b by David Waern at 2009-03-21T14:59:26+00:00 Define __GHC_PATCHLEVEL__=1 when using ghc-6.10.1 - - - - - 23f78831 by David Waern at 2009-03-21T16:40:52+00:00 Update CHANGES - - - - - 7d2735e9 by David Waern at 2009-03-21T16:50:33+00:00 Update ANNOUNCE - - - - - 0771e00a by David Waern at 2009-03-21T16:54:40+00:00 Update ANNOUNCE, again - - - - - 81a6942a by David Waern at 2009-03-21T17:50:06+00:00 Don't be too verbose in CHANGES - - - - - 29861dcf by David Waern at 2009-03-21T18:03:31+00:00 TAG 2.4.2 - - - - - a585f285 by David Waern at 2009-03-21T19:20:29+00:00 Require Cabal >= 1.2.3 - - - - - 7c611662 by David Waern at 2009-03-21T19:21:48+00:00 TAG 2.4.2 with cabal-version >= 1.2.3 - - - - - 23b7deff by Simon Marlow at 2009-03-20T15:43:42+00:00 new GHC build system: use shell-wrappers macro - - - - - 25f8afe7 by Ian Lynagh at 2009-03-21T19:13:53+00:00 Fix (with a hack?) haddock in teh new build system - - - - - 6a29a37e by David Waern at 2009-03-24T22:10:15+00:00 Remove unnecessary LANGUAGE pragma - - - - - 954da57d by David Waern at 2009-03-24T22:21:23+00:00 Fix warnings in H.B.DevHelp - - - - - 1619f1df by David Waern at 2009-03-26T23:20:44+00:00 -Wall police in H.B.Html - - - - - b211e13b by Simon Marlow at 2009-03-24T13:00:56+00:00 install Haddock's html stuff - - - - - 78e0b107 by David Waern at 2008-12-07T19:58:53+00:00 Add verbosity flag and utils, remove "verbose" flag - - - - - 913dae06 by David Waern at 2008-12-07T20:01:05+00:00 Add some basic "verbose" mode logging in H.Interface - - - - - 1cbff3bf by David Waern at 2009-03-27T00:07:26+00:00 Fix conflicts - - - - - 22f82032 by David Waern at 2009-03-27T21:15:11+00:00 Remove H.GHC.Typecheck - - - - - 81557804 by David Waern at 2009-03-27T21:19:22+00:00 Remove docNameOrig and use getName everywhere instead - - - - - d8267213 by David Waern at 2009-03-27T21:21:46+00:00 Use docNameOcc instead of nameOccName . getName - - - - - 5d55deab by David Waern at 2009-03-27T21:33:04+00:00 Remove H.DocName and put DocName in H.Types - - - - - 8ba72611 by David Waern at 2009-03-27T22:06:26+00:00 Document DocName - - - - - 605f8ca5 by David Waern at 2009-03-27T22:45:21+00:00 -Wall police - - - - - e4da93ae by David Waern at 2009-03-27T23:12:53+00:00 -Wall police in H.B.Hoogle - - - - - bb255519 by David Waern at 2009-03-27T23:41:28+00:00 Define Foldable and Traversable instances for Located - - - - - f1195cfe by David Waern at 2009-03-27T23:51:34+00:00 Wibble - - - - - 23818d7c by David Waern at 2009-03-28T00:03:55+00:00 -Wall police in H.I.Rename - - - - - 0f050d67 by David Waern at 2009-03-28T00:15:15+00:00 -Wall police in H.I.AttachInstances - - - - - 0f3fe038 by David Waern at 2009-03-28T21:09:41+00:00 Wibble - - - - - 275d4865 by David Waern at 2009-03-28T21:27:06+00:00 Layout fix - - - - - 54ff0ef8 by David Waern at 2009-03-28T21:59:07+00:00 -Wall police in H.I.Create - - - - - 7f58b117 by David Waern at 2009-03-28T22:10:19+00:00 -Wall police in H.Interface - - - - - f0c03b44 by David Waern at 2009-03-28T22:22:59+00:00 -Wall police in Main - - - - - 29da355c by David Waern at 2009-03-28T22:23:39+00:00 Turn on -Wall -Werror - - - - - 446d3060 by David Waern at 2009-04-01T20:40:30+00:00 hlint police - - - - - 3867c9fc by David Waern at 2009-04-01T20:48:42+00:00 hlint police - - - - - bd1f1600 by David Waern at 2009-04-01T20:58:02+00:00 hlint police - - - - - e0e90866 by David Waern at 2009-04-05T12:42:53+00:00 Move H.GHC.Utils to H.GhcUtils - - - - - 9cbd426b by David Waern at 2009-04-05T12:57:21+00:00 Remove Haddock.GHC and move its (small) contents to Main - - - - - b5c2cbfd by David Waern at 2009-04-05T13:07:04+00:00 Fix whitespace and stylistic issues in Main - - - - - 3c04aa56 by porges at 2008-12-07T08:22:19+00:00 add unicode output - - - - - 607918da by David Waern at 2009-04-26T15:09:43+00:00 Resolve conflict - - - - - 4bec6b6b by Simon Marlow at 2009-05-13T10:00:31+00:00 fix markup - - - - - 436ad6f4 by Simon Marlow at 2009-03-23T11:54:45+00:00 clean up - - - - - bdcd1398 by Simon Marlow at 2009-03-24T10:36:45+00:00 new GHC build system: add $(exeext) - - - - - 9c0972f3 by Simon Marlow at 2009-03-24T11:04:31+00:00 update for new GHC build system layout - - - - - d0f3f83a by Ian Lynagh at 2009-03-29T15:31:43+00:00 GHC new build system fixes - - - - - 5a8245c2 by Ian Lynagh at 2009-04-04T20:44:23+00:00 Tweak new build system - - - - - 9c6f2d7b by Simon Marlow at 2009-05-13T10:01:27+00:00 add build instructions for GHC - - - - - 66d07c76 by Ian Lynagh at 2009-05-31T00:37:53+00:00 Quote program paths in ghc.mk - - - - - bb7de2cd by Ian Lynagh at 2009-06-03T22:57:55+00:00 Use a bang pattern on an unlifted binding - - - - - 3ad283fc by Ian Lynagh at 2009-06-13T16:17:50+00:00 Include haddock in GHC bindists - - - - - ac447ff4 by David Waern at 2009-06-24T21:07:50+00:00 Delete Haddock.Exception and move contents to Haddock.Types Only a few lines of code that mainly declares a type - why not just put it in Haddock.Types. - - - - - 4464fb9b by David Waern at 2009-06-24T22:23:23+00:00 Add Haddock module headers Add a proper Haddock module header to each module, with a more finegrained copyright. If you feel mis-accreditted, please correct any copyright notice! The maintainer field is set to haddock at projects.haskell.org. Next step is to add a brief description to each module. - - - - - 5f4c95dd by David Waern at 2009-06-24T22:39:44+00:00 Fix spelling error - - - - - 6d074cdb by David Waern at 2009-06-25T21:53:56+00:00 Document Interface and InstalledInterface better - - - - - d0cbd183 by David Waern at 2009-06-27T12:46:46+00:00 Remove misplaced whitespace in H.I.Rename - - - - - fa381c49 by David Waern at 2009-06-27T13:26:03+00:00 Fix haskell/haddock#104 - create output directory if missing - - - - - 91fb77ae by Ian Lynagh at 2009-06-25T15:59:50+00:00 TAG 2009-06-25 - - - - - 0d853f40 by Simon Peyton Jones at 2009-07-02T15:35:22+00:00 Follow extra field in ConDecl - - - - - b201735d by Ian Lynagh at 2009-07-05T16:50:35+00:00 Update Makefile for the new GHC build system - - - - - df6c0092 by Ian Lynagh at 2009-07-05T17:01:13+00:00 Resolve conflicts - - - - - 1066870a by Ian Lynagh at 2009-07-05T17:01:48+00:00 Remove the -Wwarn hack in the GHC build system - - - - - 7e856076 by Ian Lynagh at 2009-07-05T17:17:59+00:00 Fix warnings - - - - - 5d4cd958 by Ian Lynagh at 2009-07-05T19:35:40+00:00 Bump version number Cabal needs to distinguish between haddocks having a --verbose and --verbosity flag - - - - - 6ee07c99 by David Waern at 2009-07-06T20:14:57+00:00 Wibble - - - - - 2308b66f by David Waern at 2009-07-06T20:24:20+00:00 Clearer printing of versions by runtests.hs - - - - - d4b5d9ab by David Waern at 2009-07-06T21:22:42+00:00 Fix (invisible) bug introduced by unicode patch - - - - - 2caca8d8 by David Waern at 2009-07-06T21:44:10+00:00 Use HscAsm instead of HscC when using TH - - - - - 18f3b755 by David Waern at 2009-07-06T22:10:22+00:00 Update HCAR entry (by Janis) - - - - - a72ac9db by David Waern at 2009-07-06T23:01:35+00:00 Follow HsRecTy change with an #if __GLASGOW_HASKEL__ >= 611 - - - - - 549135d2 by David Waern at 2009-07-06T23:11:41+00:00 Remove unused functions from Haddock.Utils - - - - - b450134a by Isaac Dupree at 2009-07-11T14:59:00+00:00 revert to split-index for large indices - remove the search-box, because browsers have search-for-text abilities anyway. - pick 150 items in index as the arbitrary time at which to split it - notice the bug that identifiers starting with non-ASCII characters won't be listed in split-index, but don't bother to fix it yet (see ticket haskell/haddock#116, http://trac.haskell.org/haddock/ticket/116 ) - - - - - 78a5661e by Isaac Dupree at 2009-07-20T15:37:18+00:00 Implement GADT records in HTML backend - - - - - 4e163555 by Isaac Dupree at 2009-07-21T22:03:25+00:00 add test for GADT records - - - - - 79aa4d6e by David Waern at 2009-07-23T20:40:37+00:00 Update test suite following version bump - - - - - 5932c011 by David Waern at 2009-08-02T10:25:39+00:00 Fix documentation bug - - - - - a6970fca by David Waern at 2009-08-12T23:08:53+00:00 Remove support for ghc 6.8.* from .cabal file - - - - - c1695902 by Ian Lynagh at 2009-07-07T13:35:45+00:00 Fix unused import warnings - - - - - fb6df7f9 by Ian Lynagh at 2009-07-16T00:20:31+00:00 Use cProjectVersion directly rather than going through compilerInfo Fixes the build after changes in GHC - - - - - 548cdd66 by Simon Marlow at 2009-07-28T14:27:04+00:00 follow changes in GHC's ForeignType - - - - - 9395aaa0 by David Waern at 2009-08-13T22:17:33+00:00 Switch from PatternSignatures to ScopedTypeVariables in Main - - - - - eebf39bd by David Waern at 2009-08-14T17:14:28+00:00 Version .haddock files made with GHC 6.10.3/4 correclty - - - - - 58f3e735 by David Waern at 2009-08-14T17:19:37+00:00 Support GHC 6.10.* and 6.11.* only - - - - - 5f63cecc by David Waern at 2009-08-14T22:03:20+00:00 Do not version .haddock file based on GHC patchlevel version We require that the instances of Binary that we use from GHC will not change between patchlevel versions. - - - - - d519de9f by David Waern at 2009-08-14T23:50:00+00:00 Update CHANGES - - - - - 35dccf5c by David Waern at 2009-08-14T23:51:38+00:00 Update version number everywhere - - - - - 6d363fea by David Waern at 2009-08-15T09:46:49+00:00 Update ANNOUNCE - - - - - c7ee6bc2 by David Waern at 2009-08-15T09:47:13+00:00 Remove -Werror Forgot that Hackage doesn't like it. - - - - - a125c12b by David Waern at 2009-08-15T09:49:50+00:00 Require Cabal >= 1.6 - - - - - adb2f560 by Isaac Dupree at 2009-08-12T03:47:14+00:00 Cross-Package Documentation version 4 - - - - - 3d6dc04d by David Waern at 2009-08-15T23:42:57+00:00 Put all the IN_GHC_TREE stuff inside getGhcLibDir - - - - - 56624097 by David Waern at 2009-08-15T23:52:03+00:00 Add --print-ghc-libdir - - - - - f15d3ccb by David Waern at 2009-08-16T00:37:52+00:00 Read base.haddock when running tests We can now test cross-package docs. - - - - - 283f0fb9 by David Waern at 2009-08-16T00:50:59+00:00 Update test output - we now have more links - - - - - 673d1004 by David Waern at 2009-08-16T01:26:08+00:00 Read process.haddock when running tests - - - - - 0d127f82 by David Waern at 2009-08-16T01:43:04+00:00 Add a test for cross-package documentation - - - - - f94db967 by Ian Lynagh at 2009-08-16T18:42:44+00:00 Follow GHC build system changes - - - - - 5151278a by Isaac Dupree at 2009-08-16T19:58:05+00:00 make cross-package list types look nicer - - - - - c41e8228 by Isaac Dupree at 2009-08-18T01:47:47+00:00 Haddock.Convert: export more functions This lets us remove some code in Haddock.Interface.AttachInstances - - - - - 2e5fa398 by Isaac Dupree at 2009-08-18T02:11:05+00:00 switch AttachInstances to use synify code It changed an instance from showing ((,) a b) to (a, b) because my synify code is more sophisticated; I hope the latter is a good thing rather than a bad thing aesthetically, here. But this definitely reduces code duplication! - - - - - b8b07123 by Isaac Dupree at 2009-08-18T02:23:31+00:00 Find instances using GHC, which is more complete. In particular, it works cross-package. An intermediate patch also moved the instance-finding into createInterface, but that move turned out not to be necessary, so if we want to do that, it'd go in a separate patch. (Is that possible? Or will we need GHC to have loaded all the modules first, before we can go searching for the instances (e.g. if the modules are recursive or something)?) - - - - - 6959b451 by Isaac Dupree at 2009-08-17T00:37:18+00:00 fix preprocessor conditional sense - - - - - 942823af by Isaac Dupree at 2009-08-16T22:46:48+00:00 remove ghc 6.8 conditionals from Haddock.Interface - - - - - 4b3ad888 by Isaac Dupree at 2009-08-18T20:24:38+00:00 Fix GHC 6.11 build in Haddock.Convert - - - - - 0a89c5ab by Isaac Dupree at 2009-08-23T00:08:58+00:00 hacks to make it compile without fnArgDocsn - - - - - 7b3bed43 by Isaac Dupree at 2009-08-23T03:01:28+00:00 less big-Map-based proper extraction of constructor subdocs - - - - - b21c279a by Isaac Dupree at 2009-08-23T03:02:06+00:00 Html: remove unnecessary+troublesome GHC. qualifications - - - - - 96c97115 by Isaac Dupree at 2009-08-23T03:08:03+00:00 Move doc parsing/lexing into Haddock for ghc>=6.11 - - - - - e1cec02d by Isaac Dupree at 2009-08-23T05:08:14+00:00 get rid of unused DocMap parameter in Html - - - - - 66960c59 by Isaac Dupree at 2009-08-23T05:54:20+00:00 fix horrible named-docs-disappearing bug :-) - - - - - a9d7eff3 by Isaac Dupree at 2009-08-23T06:26:36+00:00 re-implement function-argument docs ..on top of the lexParseRn work. This patch doesn't change the InstalledInterface format, and thus, it does not work cross-package, but that will be easy to add subsequently. - - - - - 8bf6852c by Isaac Dupree at 2009-08-23T07:26:05+00:00 cross-package fnArgDocs. WARNING: changes .haddock binary format While breaking the format, I took the opportunity to unrename the DocMap that's saved to disk, because there's really no reason that we want to know what *another* package's favorite place to link a Name to was. (Is that true? Or might we want to know, someday?) Also, I added instance Binary Map in InterfaceFile. It makes the code a little simpler without changing anything of substance. Also it lets us add another Map hidden inside another Map (fnArgsDocs in instDocMap) without having really-convoluted serialization code. Instances are neat! I don't understand why this change to InterfaceFile seemed to subtly break binary compatibility all by itself, but no matter, I'll just roll it into the greater format-changing patch. Done! - - - - - 30115a64 by Isaac Dupree at 2009-08-23T18:22:47+00:00 Improve behavior for unfindable .haddock - - - - - aa364bda by Isaac Dupree at 2009-08-23T18:28:16+00:00 add comment for FnArgsDoc type - - - - - 49b23a99 by Isaac Dupree at 2009-08-23T21:52:48+00:00 bugfix: restore fnArgDocs for type-synonyms - - - - - f65f9467 by Isaac Dupree at 2009-08-23T22:06:55+00:00 Backends.Hoogle: eliminate warnings - - - - - a292d216 by Isaac Dupree at 2009-08-23T22:10:24+00:00 Haddock.Convert: eliminate warnings - - - - - 5546cd20 by Isaac Dupree at 2009-08-23T22:12:31+00:00 Haddock.Interface.Rename: eliminate warnings - - - - - 0a9798b6 by Isaac Dupree at 2009-08-23T22:18:47+00:00 Main.hs: remove ghc<6.9 conditionals - - - - - e8f9867f by Isaac Dupree at 2009-08-23T22:27:46+00:00 Main.hs: eliminate warnings (except for OldException) - - - - - 61c64247 by Isaac Dupree at 2009-08-23T22:41:01+00:00 move get*LibDir code in Main.hs, to +consistent code, -duplication - - - - - 948f1e69 by Isaac Dupree at 2009-08-23T23:14:26+00:00 Main.hs: OldException->Exception: which eliminates warnings - - - - - 3d5d5e03 by Isaac Dupree at 2009-08-23T23:20:11+00:00 GhcUtils: ghc >= 6.10 - - - - - 2771d657 by Isaac Dupree at 2009-08-23T23:21:55+00:00 InterfaceFile: ghc >= 6.10 - - - - - d9f2b9d1 by Isaac Dupree at 2009-08-23T23:22:58+00:00 Types: ghc >= 6.10 - - - - - ca39210e by Isaac Dupree at 2009-08-23T23:23:26+00:00 ModuleTree: ghc >= 6.10 - - - - - 883c4e59 by Isaac Dupree at 2009-08-23T23:24:04+00:00 Backends.DevHelp: ghc >= 6.10 - - - - - 04667df5 by Isaac Dupree at 2009-08-23T23:24:37+00:00 Backends.Html: ghc >= 6.10 - - - - - a9f7f25f by Isaac Dupree at 2009-08-23T23:25:24+00:00 Utils: ghc >= 6.10 - - - - - b7105022 by Isaac Dupree at 2009-08-23T23:37:47+00:00 eliminate haskell98 dependency, following GHC's example It turns out I/we already had, and it was only a matter of deleting it from the cabal file. - - - - - 292e0911 by Isaac Dupree at 2009-08-24T01:22:44+00:00 refactor out subordinatesWithNoDocs dep of inferenced-decls fix - - - - - c2ed46a2 by Isaac Dupree at 2009-08-24T01:24:03+00:00 Eradicate wrong runtime warning for type-inferenced exported-functions see the long comment in the patch for why I did it this way :-) - - - - - 4ac0b57c by David Waern at 2009-09-04T22:56:20+00:00 Clean up tyThingToHsSynSig a little Factor out noLoc and use the case construct. Also rename the function to tyThingToLHsDecl, since it doesn't just create type signatures. - - - - - 28ab9201 by David Waern at 2009-09-04T22:58:50+00:00 Wibble - - - - - 0d9fe6d0 by David Waern at 2009-09-06T18:39:30+00:00 Add more copyright owners to H.I.AttachInstances - - - - - 122441b1 by David Waern at 2009-09-06T18:44:12+00:00 Style police - - - - - 1fa79463 by David Waern at 2009-09-06T18:57:45+00:00 Move toHsInstHead to Haddock.Convert and call it synifyInstHead - - - - - 0d42a8aa by David Waern at 2009-09-06T21:11:38+00:00 Use colordiff to display test results if available - - - - - ea9d8e03 by Simon Marlow at 2009-08-24T08:46:14+00:00 Follow changes in GHC's interface file format Word32 instead of Int for FastString and Name offsets - - - - - 537e051e by Simon Marlow at 2009-07-29T14:16:53+00:00 define unpackPackageId (it was removed from GHC) - - - - - 50c63aa7 by David Waern at 2009-09-09T23:18:03+00:00 Remove commented-out code - - - - - 511631fe by David Waern at 2009-09-09T23:19:05+00:00 Correct copyright in H.I.ParseModuleHeader - - - - - 898ec768 by David Waern at 2009-09-11T11:22:29+00:00 Use Map.fromList/toList intead of fromAscList/toAscList when serializing Maps This fixes the missing docs problem. The Eq and Ord instances for Name uses the unique number in Name. This number is created at deserialization time by GHC's magic Binary instance for Name, and it is random. Thus, fromAscList can't be used at deserialization time, even though toAscList was used at serialization time. - - - - - 37bec0d5 by Simon Peyton Jones at 2009-09-11T08:28:04+00:00 Track change in HsType - - - - - eb3a97c3 by Ian Lynagh at 2009-09-11T16:07:09+00:00 Allow building with base 4.2 - - - - - bb4205ed by Ian Lynagh at 2009-09-22T13:50:02+00:00 Loosen the GHC dependency - - - - - 5c75deb2 by Ian Lynagh at 2009-09-22T14:08:39+00:00 Fix building with GHC >= 6.12 - - - - - fb131481 by David Waern at 2009-09-11T11:24:48+00:00 Update runtests.hs to work with GHC 6.11 - - - - - ac3a419d by David Waern at 2009-09-11T11:25:14+00:00 Update CrossPackageDocs test - - - - - ec65c3c6 by David Waern at 2009-09-11T11:25:40+00:00 Add reference output for CrossPackageDocs - - - - - 520c2758 by Ian Lynagh at 2009-10-25T17:26:40+00:00 Fix installation in the GHC build system - - - - - 28b3d7df by Ian Lynagh at 2009-11-05T15:57:27+00:00 GHC build system: Make *nix installation work in paths containing spaces - - - - - 5c9bb541 by David Waern at 2009-11-14T11:56:39+00:00 Track change in HsType for the right compiler version - - - - - 905097ce by David Waern at 2009-11-14T12:10:47+00:00 hlint police - - - - - 04920630 by Ian Lynagh at 2009-11-20T13:46:30+00:00 Use defaultObjectTarget rather than HscAsm This fixes haddock when we don't have a native code generator - - - - - 966eb079 by David Waern at 2009-11-15T12:32:21+00:00 Remove commented-out code - - - - - 37f00fc4 by David Waern at 2009-11-22T13:58:48+00:00 Make runtests.hs strip links before diffing Generates easier to read diffs when tests fail. The content of the links is not important anyway since it is not taken into account by the tests. - - - - - 3a9bb8ef by David Waern at 2009-11-22T14:05:06+00:00 Follow findProgramOnPath signature change in runtests.hs - - - - - b26b9e5a by David Waern at 2009-11-22T14:08:40+00:00 Follow removal of GHC.MVar from base in CrossPackageDocs - - - - - f4d90ae4 by David Waern at 2009-11-22T14:48:47+00:00 Make copy.hs strip link contents before copying No more updating of reference files when URLs in links changes. - - - - - 4c9c420d by David Waern at 2009-11-22T15:26:41+00:00 Update test reference output * More links (Int, Float etc) * Stripped link contents - - - - - a62b80e3 by David Waern at 2009-11-23T23:19:39+00:00 Update CrossPackageDocs reference output - Remove GHC.MVar import (removed from base) - Strip link contents - - - - - 43491394 by David Waern at 2009-11-23T23:20:00+00:00 Update test reference files with comments on instances - - - - - 0d370a0b by David Waern at 2009-11-23T23:25:16+00:00 Bump version number - - - - - 2293113e by David Waern at 2009-11-24T20:55:49+00:00 Comments on instances Implementing this was a little trickier than I thought, since we need to match up instances from the renamed syntax with instances represented by InstEnv.Instance. This is due to the current design of Haddock, which matches comments with declarations from the renamed syntax, while getting the list of instances of a class/family directly using the GHC API. - Works for class instances only (Haddock has no support for type family instances yet) - The comments are rendered to the right of the instance head in the HTML output - No change to the .haddock file format - Works for normal user-written instances only. No comments are added on derived or TH-generated instances - - - - - bf586f29 by David Waern at 2009-11-27T22:05:15+00:00 Whitespace police - - - - - b8f03afa by David Waern at 2009-11-27T22:11:46+00:00 Remove bad whitespace and commented-out pieces - - - - - 90b8ee90 by David Waern at 2009-11-27T22:15:04+00:00 Whitespace police - - - - - b5ede900 by David Waern at 2009-11-27T22:15:50+00:00 Whitespace police - - - - - e3fddbfe by David Waern at 2009-11-28T13:37:59+00:00 Remove Name from DocInstance It's not used. - - - - - 9502786c by David Waern at 2009-11-28T13:56:54+00:00 Require at least GHC 6.12 While regression testing Haddock, I found a bug that happens with GHC 6.10.3, but not with GHC 6.12-rc2 (haven't tried 6.10.4). I don't have time to track it down. I think we should just always require the latest major GHC version. The time spent on making Haddock work with older versions is too high compared to the time spent on bugfixing, refactoring and features. - - - - - 8fa688d8 by David Waern at 2009-11-28T15:05:03+00:00 Remove cruft due to compatibility with older GHCs - - - - - 46fbbe9d by David Waern at 2009-11-28T15:07:50+00:00 Add a documentation header to Haddock.Convert - - - - - c3d2cc4a by David Waern at 2009-11-28T15:10:14+00:00 Remove unused H.Utils.FastMutInt2 - - - - - 490aba80 by David Waern at 2009-11-28T15:36:36+00:00 Rename Distribution.Haddock into Documentation.Haddock - - - - - 33ee2397 by David Waern at 2009-11-28T15:36:47+00:00 Fix error message - - - - - a5a3b950 by David Waern at 2009-11-28T16:58:39+00:00 Add a test flag that brings in QuickCheck - - - - - fa049e13 by David Waern at 2009-11-28T19:32:18+00:00 Say that we want quickcheck 2 - - - - - f32b0d9b by David Waern at 2009-11-28T19:32:40+00:00 Add an Arbitrary instance for HsDoc - - - - - da9a8bd7 by David Waern at 2009-11-28T20:15:30+00:00 Rename HsDoc back into Doc - - - - - edb60101 by David Waern at 2009-11-28T22:16:16+00:00 Move H.Interface.Parse/Lex to H.Parse/Lex These are not just used to build Interfaces. - - - - - 0656a9b8 by David Waern at 2009-11-28T23:12:14+00:00 Update version number in test suite - - - - - 5e8c6f4a by David Waern at 2009-12-21T14:12:41+00:00 Improve doc of DocName - - - - - 7868e551 by Ian Lynagh at 2009-09-22T10:43:03+00:00 TAG GHC 6.12-branch created - - - - - 0452a3ea by Ian Lynagh at 2009-12-15T12:46:07+00:00 TAG GHC 6.12.1 release - - - - - 65e9be62 by David Waern at 2009-12-21T16:58:58+00:00 Update CHANGES - - - - - 145cee32 by David Waern at 2009-12-21T16:59:09+00:00 TAG 2.6.0 - - - - - 3c552008 by David Waern at 2009-12-22T17:11:14+00:00 Update ANNOUNCE - - - - - 931f9db4 by David Waern at 2010-01-22T19:57:17+00:00 Convert haddock.vim to use unix newlines - - - - - 4e56588f by David Waern at 2010-01-22T22:11:17+00:00 Remove unnecessary (and inexplicable) uses of nub - - - - - 744bb4d1 by David Waern at 2010-01-22T22:12:14+00:00 Follow move of parser and lexer - - - - - e34bab14 by David Waern at 2010-01-22T22:49:13+00:00 Use findProgramLocation instead of findProgramOnPath in runtests.hs - - - - - 8d39891b by Isaac Dupree at 2010-01-14T18:53:18+00:00 fix html arg-doc off-by-one and silliness - - - - - 9401f2e9 by David Waern at 2010-01-22T22:57:03+00:00 Create a test for function argument docs - - - - - 507a82d7 by David Waern at 2010-01-22T23:24:47+00:00 Put parenthesis around type signature arguments of function type - - - - - 8a305c28 by David Waern at 2010-01-23T17:26:59+00:00 Add reference file for the FunArgs test - - - - - 1309d5e1 by David Waern at 2010-01-24T16:05:08+00:00 Improve FunArg test and update Test.html.ref - - - - - 2990f055 by Yitzchak Gale at 2010-02-14T16:03:46+00:00 Do not generate illegal character in HTML ID attribute. - - - - - c5bcab7a by David Waern at 2010-02-22T22:10:30+00:00 Fix Haddock markup error in comment - - - - - c6416a73 by David Waern at 2010-02-24T22:55:08+00:00 Large additions to the Haddock API Also improved and added more doc comments. - - - - - 57d289d7 by David Waern at 2010-02-24T22:58:02+00:00 Remove unused ifaceLocals - - - - - 80528d93 by David Waern at 2010-02-25T21:05:09+00:00 Add HaddockModInfo to the API - - - - - 82806848 by David Waern at 2010-02-25T21:05:27+00:00 Wibble - - - - - 744cad4c by David Waern at 2010-02-25T23:30:59+00:00 Make it possible to run a single test - - - - - 6a806e4c by David Waern at 2010-03-14T14:19:39+00:00 Bump version number - - - - - a5a8e4a7 by David Waern at 2010-03-14T14:36:35+00:00 Update ANNOUNCE - - - - - 6f05435e by Simon Hengel at 2010-03-15T20:52:42+00:00 Add missing dependencies for 'library' in haddock.cabal - - - - - faefe2bd by David Waern at 2010-03-15T22:29:37+00:00 Solve conflicts - - - - - 9808ad52 by David Waern at 2010-03-15T22:51:21+00:00 Bump version number - - - - - eb0bf60b by David Waern at 2010-03-15T22:52:32+00:00 Update CHANGES - - - - - f95cd891 by David Waern at 2010-03-15T23:01:06+00:00 Add Paths_haddock to other-modules of library - - - - - 65997b0a by David Waern at 2010-03-15T23:14:59+00:00 Update CHANGES - - - - - 7e251731 by David Waern at 2010-03-15T23:15:30+00:00 Bump version number - - - - - c9cd0ddc by David Waern at 2010-03-16T00:28:34+00:00 Fix warning - - - - - 1cac2d93 by Simon Peyton Jones at 2010-01-04T15:22:16+00:00 Fix imports for new location of splitKindFunTys - - - - - 474f26f6 by Simon Peyton Jones at 2010-02-10T14:36:06+00:00 Update Haddock for quasiquotes - - - - - 0dcc06c0 by Simon Peyton Jones at 2010-02-10T10:59:45+00:00 Track changes in HsTyVarBndr - - - - - 2d84733a by Simon Peyton Jones at 2010-02-10T14:52:44+00:00 Track HsSyn chnages - - - - - 9e3adb8b by Ian Lynagh at 2010-02-20T17:09:42+00:00 Resolve conflicts - - - - - a3e72ff8 by Simon Peyton Jones at 2010-03-04T13:05:16+00:00 Track change in HsUtils; and use a nicer function not an internal one - - - - - 27994854 by David Waern at 2010-03-18T22:22:27+00:00 Fix build with GHC 6.12.1 - - - - - 11f6e488 by David Waern at 2010-03-18T22:24:09+00:00 Bump version in test reference files - - - - - 0ef2f11b by David Waern at 2010-03-20T00:56:30+00:00 Fix library part of cabal file when in ghc tree - - - - - 3f6146ff by Mark Lentczner at 2010-03-20T22:30:11+00:00 First, experimental XHTML rendering switch to using the xhtml package copied Html.hs to Xhtml.hs and split into sub-modules under Haddock/Backends/Xhtml and detabify moved footer into div, got ready for iface change headers converted to semantic markup contents in semantic markup summary as semantic markup description in semantic markup, info block in header fixed factored out rendering so during debug it can be readable (see renderToString) - - - - - b8ab329b by Mark Lentczner at 2010-03-20T22:54:01+00:00 apply changes to Html.hs to Xhtml/*.hs incorporate changes that were made between the time Html.hs was copied and split into Xhtml.hs and Xhtml/*.hs includes patchs after "Wibble" (!) through "Fix build with GHC 6.12.1" - - - - - 73df2433 by Ian Lynagh at 2010-03-20T21:56:37+00:00 Follow LazyUniqFM->UniqFM in GHC - - - - - db4f602b by David Waern at 2010-03-29T22:00:01+00:00 Fix build with GHC 6.12 - - - - - d8dca088 by Simon Hengel at 2010-04-02T16:39:55+00:00 Add missing dependencies to cabal file - - - - - e2adc437 by Simon Hengel at 2010-04-02T14:08:40+00:00 Add markup support for interactive examples - - - - - e882ac05 by Simon Hengel at 2010-04-02T14:11:53+00:00 Add tests for interactive examples - - - - - 5a07a6d3 by David Waern at 2010-04-07T17:05:20+00:00 Propagate source positions from Lex.x to Parse.y - - - - - 6493b46f by David Waern at 2010-04-07T21:48:57+00:00 Let runtests.hs die when haddock has not been built - - - - - 5e34423e by David Waern at 2010-04-07T22:01:13+00:00 Make runtests.hs slightly more readable - - - - - 321d59b3 by David Waern at 2010-04-07T22:13:27+00:00 Fix haskell/haddock#75 Add colons to the $ident character set. - - - - - 37b08b8d by David Waern at 2010-04-08T00:32:52+00:00 Fix haskell/haddock#118 Avoid being too greedy when lexing URL markup (<..>), in order to allow multiple URLs on the same line. Do the same thing with <<..>> and #..#. - - - - - df8feac9 by David Waern at 2010-04-08T00:57:33+00:00 Make it easier to add new package deps to test suite This is a hack - we should use Cabal to get the package details instead. - - - - - 1ca6f84b by David Waern at 2010-04-08T01:03:06+00:00 Add ghc-prim to test suite deps - - - - - 27371e3a by Simon Hengel at 2010-04-08T19:26:34+00:00 Let parsing fails on paragraphs that are immediately followed by an example This is more consistent with the way we treat code blocks. - - - - - 83096e4a by David Waern at 2010-04-08T21:20:00+00:00 Improve function name - - - - - 439983ce by David Waern at 2010-04-10T10:46:14+00:00 Fix haskell/haddock#112 No link was generated for 'Addr#' in a doc comment. The reason was simply that the identifier didn't parse. We were using parseIdentifier from the GHC API, with a parser state built from 'defaultDynFlags'. If we pass the dynflags of the module instead, the right options are turned on on while parsing the identifer (in this case -XMagicHash), and the parse succeeds. - - - - - 5c0d35d7 by David Waern at 2010-04-10T10:54:06+00:00 Rename startGhc into withGhc - - - - - dca081fa by Simon Hengel at 2010-04-12T19:09:16+00:00 Add documentation for interactive examples - - - - - c7f26bfa by David Waern at 2010-04-13T00:51:51+00:00 Slight fix to the documentation of examples - - - - - 06eb7c4c by David Waern at 2010-04-13T00:57:05+00:00 Rename Interactive Examples into Examples (and simplify explanation) - - - - - 264830cb by David Waern at 2010-05-10T20:07:27+00:00 Update CHANGES with info about 2.6.1 - - - - - 8e5d4514 by Simon Hengel at 2010-04-18T18:16:54+00:00 Add unit tests for parser - - - - - 68297f40 by David Waern at 2010-05-10T21:53:37+00:00 Improve testsuite README - - - - - f04eb6e4 by David Waern at 2010-05-11T19:14:31+00:00 Re-organise the testsuite structure - - - - - a360f710 by David Waern at 2010-05-11T19:18:03+00:00 Shorten function name - - - - - 1d5dd359 by David Waern at 2010-05-11T21:40:02+00:00 Update runtests.hs following testsuite re-organisation - - - - - ffebe217 by David Waern at 2010-05-11T21:40:10+00:00 Update runtests.hs to use base-4.2.0.1 - - - - - 635de402 by David Waern at 2010-05-11T21:41:11+00:00 Update runparsetests.hs following testsuite reorganisation - - - - - 72137910 by Ian Lynagh at 2010-05-06T20:43:06+00:00 Fix build - - - - - 1a80b76e by Ian Lynagh at 2010-05-06T22:25:29+00:00 Remove redundant import - - - - - 1031a80c by Simon Peyton Jones at 2010-05-07T13:21:09+00:00 Minor wibbles to HsBang stuff - - - - - dd8e7fe5 by Ian Lynagh at 2010-05-08T15:22:00+00:00 GHC build system: Follow "rm" variable changes - - - - - 7f5e6748 by David Waern at 2010-05-13T11:53:02+00:00 Fix build with GHC 6.12.2 - - - - - 7953d4d8 by David Waern at 2010-05-13T18:45:01+00:00 Fixes to comments only - - - - - 8ae8eb64 by David Waern at 2010-05-13T18:57:26+00:00 ModuleMap -> IfaceMap - - - - - 1c3eadc6 by David Waern at 2010-05-13T19:03:13+00:00 Fix whitespace style issues - - - - - e96783c0 by David Waern at 2010-05-13T19:08:53+00:00 Fix comment - - - - - c998a78b by David Waern at 2010-05-13T19:39:00+00:00 Position the module header the same way everywhere Silly, but nice with some consistency :-) - - - - - b48a714e by David Waern at 2010-05-13T19:41:32+00:00 Position of module header, this time in the HTML backends - - - - - f9bfb12e by David Waern at 2010-05-13T19:43:05+00:00 Two newlines between declarations in Main - - - - - 071d44c7 by David Waern at 2010-05-13T19:44:21+00:00 Newlines in Convert - - - - - 036346db by David Waern at 2010-05-13T19:46:47+00:00 Fix a few stylistic issues in H.InterfaceFile - - - - - f0b8379e by David Waern at 2010-05-13T19:47:53+00:00 Add newlines to H.ModuleTree - - - - - 27409f8e by David Waern at 2010-05-13T19:51:10+00:00 Fix stylistic issues in H.Utils - - - - - 24774a11 by David Waern at 2010-05-13T20:00:43+00:00 Structure H.Types better - - - - - 7b6f5e40 by David Waern at 2010-05-13T20:01:04+00:00 Remove bad Arbitrary instance - - - - - fac9f1f6 by David Waern at 2010-05-13T20:05:50+00:00 Get rid of H.Utils.pathJoin and use System.FilePath.joinPath instead - - - - - fe6d00c4 by David Waern at 2010-05-13T20:51:55+00:00 Export a couple of more types from the API - - - - - b2e33a5f by David Waern at 2010-05-13T21:27:51+00:00 Improve doc comment for Interface - - - - - c585f2ce by David Waern at 2010-05-13T21:30:14+00:00 Improve documentation of Haddock.Interface - - - - - e6791db2 by David Waern at 2010-05-13T22:07:35+00:00 Remove meaningless comments - - - - - 7801b390 by David Waern at 2010-05-14T17:53:33+00:00 Remove unused modules - - - - - f813e937 by David Waern at 2010-05-14T17:55:17+00:00 Re-direct compilation output to a temporary directory Also add a flag --no-tmp-comp-dir that can be used to get the old behaviour of writing compilation files to GHC's output directory (default "."). - - - - - e56737ec by David Waern at 2010-05-14T18:06:11+00:00 Wibble - - - - - e40b0447 by David Waern at 2010-05-14T19:01:52+00:00 Move flag evaluation code from Main to Haddock.Options Determining the value of "singular" flags (by e.g. taking the last occurrence of the flag) and other flag evaluation should done in Haddock.Options which is the module that is supposed to define the command line interface. This makes Main a bit easier on the eyes as well. - - - - - 27091f57 by David Waern at 2010-05-14T19:05:10+00:00 Wibble - - - - - c658cf61 by David Waern at 2010-05-14T19:06:49+00:00 Re-order things in Haddock.Options a bit - - - - - 8cfdd342 by David Waern at 2010-05-14T19:20:29+00:00 De-tabify Haddock.Options and fix other whitespace issues - - - - - 0df16b62 by David Waern at 2010-05-14T19:25:07+00:00 Improve comments - - - - - 80b38e2b by David Waern at 2010-05-14T19:26:42+00:00 Whitespace police - - - - - fe580255 by David Waern at 2010-05-14T19:31:23+00:00 Wibbles to comments - - - - - a2b43fad by David Waern at 2010-05-14T20:24:32+00:00 Move some more flag functions to Haddock.Options - - - - - 3f895547 by David Waern at 2010-05-14T20:37:12+00:00 Make renderStep a top-level function in Main - - - - - 5cdca11d by David Waern at 2010-05-14T20:39:27+00:00 Spelling in comment - - - - - ad98d14c by David Waern at 2010-05-14T20:40:26+00:00 Comment fixes - - - - - 0bb9218f by David Waern at 2010-05-14T20:49:01+00:00 Whitespace police - - - - - 0f0a533f by David Waern at 2010-05-15T16:42:29+00:00 Improve description of --dump-interface - - - - - 5b2833ac by David Waern at 2010-05-15T17:16:53+00:00 Document --no-tmp-comp-dir - - - - - 8160b170 by David Waern at 2010-05-15T17:18:59+00:00 Wibble - - - - - 570dbe33 by David Waern at 2010-05-18T21:15:38+00:00 HLint police - - - - - 204e425f by David Waern at 2010-05-18T21:16:30+00:00 HLint police - - - - - 6db657ac by David Waern at 2010-05-18T21:16:37+00:00 Wibble - - - - - b942ccd7 by Simon Marlow at 2010-06-02T08:27:30+00:00 Interrupted disappeared in GHC 6.13 (GHC ticket haskell/haddock#4100) - - - - - 3b94a819 by Simon Marlow at 2010-06-02T08:45:08+00:00 Allow base-4.3 - - - - - c5a1fb7c by Simon Marlow at 2010-06-02T09:03:04+00:00 Fix compilation with GHC 6.13 - - - - - 6181296c by David Waern at 2010-06-08T21:09:05+00:00 Display name of prologue file when parsing it fails - - - - - 7cbc6f60 by Ian Lynagh at 2010-06-13T16:20:25+00:00 Remove redundant imports - - - - - 980c804b by Simon Marlow at 2010-06-22T08:41:50+00:00 isLocalAndTypeInferenced: fix for local module names overlapping package modules - - - - - d74d4a12 by Simon Marlow at 2010-06-23T12:03:27+00:00 Unresolved identifiers in Doc get replaced with DocMonospaced rather than plain strings - - - - - d8546783 by Simon Marlow at 2010-06-30T12:45:17+00:00 LaTeX backend (new options: --latex, --latex-style=<style>) - - - - - 437afa9e by David Waern at 2010-07-01T12:02:44+00:00 Fix a few stylistic whitespace issues in LaTeX backend - - - - - 85bc1fae by David Waern at 2010-07-01T15:42:45+00:00 Make runtest.hs work with GHC 6.12.3 (we should really stop hard coding this) - - - - - 7d2eb86f by David Waern at 2010-07-01T15:43:33+00:00 Update test following Simon's patch to render unresolved names in monospaced font - - - - - 08fcbcd2 by David Waern at 2010-07-01T16:12:18+00:00 Warning police - - - - - d04a8d7a by David Waern at 2010-07-04T14:53:39+00:00 Fix a bug in attachInstances We didn't look for instance docs in all the interfaces of the package. This had the effect of instance docs not always showing up under a declaration. I took the opportunity to clean up the code in H.I.AttachInstances a bit as well. More cleanup is needed, however. - - - - - d10344eb by Simon Hengel at 2010-07-10T09:19:04+00:00 Add missing dependencies to cabal file - - - - - 24090531 by Mark Lentczner at 2010-03-21T04:51:16+00:00 add exports to Xhtml modules - - - - - 84f9a333 by Mark Lentczner at 2010-04-03T19:14:22+00:00 clean up Doc formatting code - add CSS for lists - renderToString now uses showHtml since prettyHtml messes up <pre> sections - - - - - bebccf52 by Mark Lentczner at 2010-04-04T04:51:08+00:00 tweak list css - - - - - 0c2aeb5e by Mark Lentczner at 2010-04-04T06:24:14+00:00 all decls now generate Html not HtmlTable - ppDecl return Html, and so now do all of the functions it calls - added some internal tables to some decls, which is wrong, and will have to be fixed - decl "Box" functions became "Elem" functions to make clear they aren't in a table anymore (see Layout.hs) - docBox went away, as only used in one place (and its days are numbered) - cleaned up logic in a number of places, removed dead code - added maybeDocToHtml which simplified a number of places in the code - - - - - dbf73e6e by Mark Lentczner at 2010-04-05T05:02:43+00:00 clean up processExport and place a div around each decl - - - - - e25b7e9f by Mark Lentczner at 2010-04-10T21:23:21+00:00 data decls are now a sequence of paragraphs, not a table - - - - - 89ee0294 by Mark Lentczner at 2010-04-10T21:29:16+00:00 removed commented out code that can't be maintained - - - - - d466f536 by Mark Lentczner at 2010-04-12T04:56:27+00:00 removed declWithDoc and cleaned up data decls in summary - - - - - ed755832 by Mark Lentczner at 2010-04-12T05:07:53+00:00 merge in markupExample changes - - - - - c36f51fd by Mark Lentczner at 2010-04-25T04:56:37+00:00 made record fields be an unordList, not a table - - - - - ed3a28d6 by Mark Lentczner at 2010-04-25T05:23:28+00:00 fixed surround of instance and constructor tables - - - - - 0e35bbc4 by Mark Lentczner at 2010-04-25T05:36:59+00:00 fix class member boxes in summary - - - - - 5041749b by Mark Lentczner at 2010-04-25T05:38:35+00:00 remove unused bodyBox - - - - - e91724db by Mark Lentczner at 2010-04-25T06:26:10+00:00 fixed javascript quoting/escpaing issue - - - - - f4abbb73 by Mark Lentczner at 2010-05-03T23:04:31+00:00 adjust css for current markup - - - - - e75fec4c by Mark Lentczner at 2010-05-04T06:14:34+00:00 added assoicated types and methods back into class decls - - - - - 84169323 by Mark Lentczner at 2010-05-24T13:13:42+00:00 merge in changes from the big-whitespace cleanup - - - - - 3c1c872e by Mark Lentczner at 2010-06-11T21:03:58+00:00 adjust synopsis and bottom bar spacing - - - - - 3c1f9ef7 by Mark Lentczner at 2010-06-11T21:14:44+00:00 fix missing space in "module" lines in synoposis - - - - - 9a137e6d by Mark Lentczner at 2010-06-11T21:34:08+00:00 changed tt elements to code elements - - - - - 50f71ef1 by Mark Lentczner at 2010-06-11T23:27:46+00:00 factored out ppInstances - - - - - 3b9a9de5 by Mark Lentczner at 2010-06-17T17:36:01+00:00 push single constructors (newtype) onto line with decl - - - - - e0f8f2ec by Mark Lentczner at 2010-06-17T22:20:56+00:00 remove <++> connector - - - - - 56c075dd by Mark Lentczner at 2010-07-13T05:26:21+00:00 change to new page structure - - - - - 04be6ca7 by Mark Lentczner at 2010-07-14T04:21:55+00:00 constructors and args as dl lists, built in Layout.hs - - - - - 65aeafc2 by Mark Lentczner at 2010-07-14T05:38:32+00:00 better interface to subDecls - - - - - 72032189 by Mark Lentczner at 2010-07-14T07:04:10+00:00 made subDecl tables looks just so - - - - - b782eca2 by Mark Lentczner at 2010-07-14T16:00:54+00:00 convert args to SubDecl format - - - - - cc75e98f by Mark Lentczner at 2010-07-14T16:28:53+00:00 convert instances to SubDecl - - - - - 34e2aa5a by Mark Lentczner at 2010-07-14T21:07:32+00:00 removing old table cruft from Layout.hs - - - - - d5810d95 by Mark Lentczner at 2010-07-14T21:54:58+00:00 methods and associated types in new layout scheme - - - - - 65ef9579 by Mark Lentczner at 2010-07-14T23:43:42+00:00 clean up synopsis lists - - - - - e523318f by Mark Lentczner at 2010-07-15T05:02:26+00:00 clean up of anchors - - - - - 1215dfc5 by Mark Lentczner at 2010-07-15T23:53:01+00:00 added two new themes and rough css switcher - - - - - 7f0fd36f by Mark Lentczner at 2010-07-16T04:57:38+00:00 fixed package catpion, added style menu - - - - - 0dd4999c by Mark Lentczner at 2010-07-16T20:12:39+00:00 new output for mini_ pages - - - - - 64b2810b by Mark Lentczner at 2010-07-16T20:58:41+00:00 reformat index-frames - - - - - 3173f555 by Mark Lentczner at 2010-07-16T22:41:53+00:00 convert index to new markup - - - - - b0a4b7c9 by Mark Lentczner at 2010-07-17T04:07:22+00:00 convert index.html to new markup, adjust module markup - - - - - 8261ae1e by Mark Lentczner at 2010-07-17T05:07:29+00:00 classing styling of ancillary pages - - - - - 2a4fb025 by Mark Lentczner at 2010-07-17T05:11:45+00:00 clean up Layout.hs: no more vanillaTable - - - - - 87eec685 by Mark Lentczner at 2010-07-17T05:35:16+00:00 clean up Util.hs - - - - - d304e9b0 by Mark Lentczner at 2010-07-17T05:38:50+00:00 qualify import of XHtml as XHtml - - - - - 7dc05807 by Mark Lentczner at 2010-07-17T06:17:53+00:00 factored out head element generation - - - - - 9cdaec9e by Mark Lentczner at 2010-07-17T06:44:54+00:00 refactored out main page body generation - - - - - 8a51019e by Mark Lentczner at 2010-07-17T06:48:20+00:00 moved footer into only place that used it - - - - - efa479da by Mark Lentczner at 2010-07-17T18:48:30+00:00 styling auxillary pages for tibbe and snappy themes - - - - - 81de5509 by Mark Lentczner at 2010-07-18T04:41:38+00:00 fixed alphabet on index page, and styling of it and packages in module lists - - - - - 20718c1a by Mark Lentczner at 2010-07-18T05:34:29+00:00 cleaned up div functions in Layout.hs - - - - - 60d50453 by Mark Lentczner at 2010-07-18T05:48:39+00:00 added content div to main pages - - - - - ed16561c by Mark Lentczner at 2010-07-18T06:12:22+00:00 add .doc class to documentation blocks - - - - - f5c781b0 by Mark Lentczner at 2010-07-19T05:20:53+00:00 refactoring of anchor ID and fragment handling - - - - - a69a93bf by Mark Lentczner at 2010-07-19T05:35:55+00:00 remove an explicit bold tag - replace with .def class - - - - - d76c7225 by Mark Lentczner at 2010-07-19T06:56:15+00:00 rename Haddock.Backends.Xhtml.Util to Utils - - - - - 5a58c0da by David Waern at 2010-07-21T13:30:54+00:00 Remove trailing whitespace in Haddock.Backends.Xhtml - - - - - 0652aa17 by David Waern at 2010-07-21T13:33:21+00:00 Align a few comments - - - - - 785776c3 by David Waern at 2010-07-21T13:39:04+00:00 Remove trailing whitespace in H.B.X.Decl - - - - - 71a30710 by David Waern at 2010-07-21T13:44:27+00:00 Remove more trailing whitespace - - - - - 38750394 by David Waern at 2010-07-21T13:50:43+00:00 Style police - - - - - 3023d940 by David Waern at 2010-07-21T14:01:22+00:00 Style police in H.B.X.Decl - - - - - df16e9e6 by David Waern at 2010-07-21T14:14:45+00:00 Style police in H.B.X.DocMarkup - - - - - 6020e321 by David Waern at 2010-07-21T14:17:32+00:00 More style police - - - - - 86ad8bf5 by David Waern at 2010-07-21T14:21:02+00:00 Style police in H.B.Xhtml - - - - - aea27d03 by David Waern at 2010-07-21T14:42:03+00:00 Fix warnings in LaTeX backend - - - - - 2aff34a9 by David Waern at 2010-07-21T14:50:46+00:00 Style police in LaTeX backend (mainly more newlines) - - - - - e517162d by David Waern at 2010-07-21T15:05:47+00:00 Doc sections in Main - - - - - b971aa0c by David Waern at 2010-07-21T15:06:17+00:00 Trailing whitespace in Documentation.Haddock - - - - - f11628fb by David Waern at 2010-07-21T15:07:06+00:00 Trailing whitespace in Haddock.Convert - - - - - cbaf284c by David Waern at 2010-07-21T15:08:11+00:00 Style police in Haddock.GhcUtils - - - - - 71feb77b by David Waern at 2010-07-21T15:09:06+00:00 Style police in Haddock.InterfaceFile - - - - - 0a9c80e6 by David Waern at 2010-07-21T15:11:33+00:00 Whitespace police - - - - - 6168376c by David Waern at 2010-07-21T15:16:35+00:00 Style police in Haddock.Utils - - - - - 9fe4dd90 by David Waern at 2010-07-21T15:19:31+00:00 Add -fwarn-tabs - - - - - a000d752 by Mark Lentczner at 2010-07-20T17:25:52+00:00 move CSS Theme functions into Themes.hs - - - - - b52b440f by Mark Lentczner at 2010-07-20T17:29:35+00:00 add Thomas Schilling's theme - - - - - e43fa7e8 by Mark Lentczner at 2010-07-21T04:49:34+00:00 correct icon used with Snappy theme - - - - - ba5092d3 by Mark Lentczner at 2010-07-21T04:56:47+00:00 apply Tibbe's updates to his theme - - - - - 7804eef6 by Mark Lentczner at 2010-07-21T05:15:49+00:00 space between "Style" and the downward triangle - - - - - 7131d4c6 by Mark Lentczner at 2010-07-21T17:43:35+00:00 merge with David's source cleanups - - - - - ee65f1cb by David Waern at 2010-07-22T16:50:46+00:00 Fix a bug where we allowed --hoogle, --latex, etc without input files - - - - - e413ff7a by David Waern at 2010-07-22T17:21:58+00:00 Improve function name - - - - - a0fd14f3 by Simon Marlow at 2010-06-30T15:34:32+00:00 fix warnings - - - - - 31f73d2a by David Waern at 2010-07-22T19:29:41+00:00 Solve conflicts - - - - - d563b4a5 by Simon Marlow at 2010-06-30T15:34:37+00:00 fix warning - - - - - 412b6469 by David Waern at 2010-07-22T19:31:28+00:00 Solve conflict - - - - - 35174b94 by Ian Lynagh at 2010-07-06T17:27:16+00:00 Follow mkPState argument order change - - - - - b5c3585c by Simon Marlow at 2010-07-14T08:49:21+00:00 common up code for instance rendering - - - - - d8009560 by Simon Marlow at 2010-07-14T12:37:11+00:00 fix warnings - - - - - a6d88695 by David Waern at 2010-07-24T15:33:33+00:00 Fix build with ghc < 6.13 - - - - - 94cf9de1 by David Waern at 2010-07-24T15:34:37+00:00 Remove conflict left-over - - - - - 313b15c0 by Mark Lentczner at 2010-07-21T22:09:04+00:00 reorganization of nhaddock.css with tibbe - - - - - 9defed80 by Mark Lentczner at 2010-07-21T22:42:14+00:00 further cleanup of nhaddock.css, float TOC, support aux. pages - - - - - 6d944c1b by Mark Lentczner at 2010-07-22T06:22:23+00:00 remove old HTML backend - - - - - b3e8cba5 by Mark Lentczner at 2010-07-22T06:43:32+00:00 remove --html-help support - it was old, out-of-date, and mostly missing - - - - - d2654a08 by Mark Lentczner at 2010-07-22T21:45:34+00:00 tweaks to nhaddock.css - - - - - f73b285c by Mark Lentczner at 2010-07-23T06:19:35+00:00 command like processing for theme selection The bulk of the change is threadnig the selected theme set through functions in Xhtml.hs so that the selected themes can be used when generating the page output. There isn't much going on in most of these changes, just passing it along. The real work is all done in Themes.hs. - - - - - 8bddc90d by Mark Lentczner at 2010-07-23T06:58:31+00:00 drop --themes support, add named theme support decided that --themes was silly - no one would do that, just use multiple --theme arguments made --theme a synonym for --css and -c made those arguments, if no file is found, look up the argument as the name of a built in theme all of this let's haddock be invoked with "--theme=classic" for example. - - - - - 20cafd4f by Mark Lentczner at 2010-07-23T17:44:29+00:00 rename --default-themes to --built-in-themes - - - - - 0fe41307 by Mark Lentczner at 2010-07-23T18:33:02+00:00 tweaks to theme for info table, headings, and tables - - - - - cba4fee0 by Mark Lentczner at 2010-07-23T19:13:59+00:00 tweaks for dl layout, though still not used - - - - - 463fa294 by Mark Lentczner at 2010-07-23T21:07:19+00:00 tweak look of mini pages, keywords, and preblocks - - - - - 5472fc02 by Mark Lentczner at 2010-07-24T05:36:15+00:00 slide out Synopsis drawer - - - - - 9d5d5de5 by Mark Lentczner at 2010-07-24T06:02:42+00:00 extend package header and footer to edges of page - - - - - a47c91a2 by Mark Lentczner at 2010-07-24T06:28:44+00:00 fields are def lists, tweak css for style menu, mini pages, arguments - - - - - ca20f23b by Mark Lentczner at 2010-07-24T16:55:22+00:00 excisting last vestiges of the --xhtml flag - - - - - 71fb012e by Mark Lentczner at 2010-07-25T18:47:49+00:00 change how collapsing sections are done make whole .caption be the target improve javascript for class toggling have plus/minus images come from .css, not img tags - - - - - c168c8d3 by Mark Lentczner at 2010-07-26T00:32:05+00:00 reorganize files in the html lib data dir - - - - - 93324301 by Mark Lentczner at 2010-07-26T01:27:42+00:00 cleaned up Themes.hs - - - - - ad3b5dd4 by Mark Lentczner at 2010-07-26T02:39:15+00:00 make module list use new collapsers - - - - - 1df9bfc6 by Mark Lentczner at 2010-07-27T19:09:25+00:00 remove Tibbe theme - - - - - 8b9b01b3 by Mark Lentczner at 2010-07-27T20:04:03+00:00 move themes into html dir with .theme and .std-theme extensions - - - - - a7beb965 by Mark Lentczner at 2010-07-27T21:06:34+00:00 give a class to empty dd elements so they can be hidden - - - - - a258c117 by Mark Lentczner at 2010-07-27T21:23:58+00:00 remove custom version of copyFile in Xhtml.hs - - - - - b70dba6e by Mark Lentczner at 2010-07-27T22:12:45+00:00 apply margin changes to pre and headings as per group decision, and small cleanups - - - - - e6f722a2 by Mark Lentczner at 2010-07-28T00:03:12+00:00 make info block and package bar links be floatable by placing them first in the dom tree - - - - - c8278867 by Mark Lentczner at 2010-07-28T19:01:18+00:00 styling source links on declarations - - - - - 88fdc399 by Mark Lentczner at 2010-07-29T01:12:46+00:00 styling tweaks don't generate an empty li for absent style menu in links area update css for Classic and Snappy to handle: dl lists links in package header and in declarations floating of links and info block in package and module headers - - - - - 8a75b213 by Ian Lynagh at 2010-07-30T20:21:46+00:00 Fix build in GHC tree - - - - - ce8e18b3 by Simon Hengel at 2010-08-03T18:37:26+00:00 Adapt paths to data files in cabal file - - - - - 9701a455 by Simon Hengel at 2010-08-07T13:20:27+00:00 Add missing dependency to cabal file - - - - - 01b838d1 by Mark Lentczner at 2010-07-30T20:19:40+00:00 improved synopsis drawer: on click, not hover - - - - - 7b6f3e59 by Mark Lentczner at 2010-07-30T23:38:55+00:00 put the synopsis back in the other themes - - - - - 7b2904c9 by Mark Lentczner at 2010-08-11T11:11:26+00:00 close arrows on expanded synopsis drawer - - - - - ea19e177 by Mark Lentczner at 2010-08-12T21:16:45+00:00 width and font changes removed the max width restrictions on the page as a whole and the synopsis made the main font size smaller (nominally 14pt) and then tweaked most font sizes (relative) to be more consistent - - - - - 5ced00c0 by Mark Lentczner at 2010-08-13T15:09:55+00:00 implemented YUI's CSS font approach - - - - - 2799c548 by Mark Lentczner at 2010-08-13T15:11:59+00:00 adjusted margin to 2em, 1 wasn't enough - - - - - 58f06893 by Mark Lentczner at 2010-08-13T15:48:44+00:00 removed underlining on hover for named anchors headings in interface lost thier a element, no need, just put id on heading css for a elements now only applies to those with href attribute - - - - - 7aced4c4 by Mark Lentczner at 2010-08-13T15:50:22+00:00 more space between elements - - - - - 5a3c1cce by Mark Lentczner at 2010-08-13T16:43:43+00:00 adjusted font sizes of auxilary pages per new scheme - - - - - 487539ef by Mark Lentczner at 2010-08-13T21:43:41+00:00 add Frames button and clean up frames.html - - - - - c1a140b6 by Mark Lentczner at 2010-08-13T22:17:48+00:00 move frames button to js - - - - - b0bdb68e by Mark Lentczner at 2010-08-14T03:44:46+00:00 build style menu in javascript moved to javascript, so as to not polute the content with the style menu removed menu building code in Themes.hs removed onclick in Utils.hs changed text of button in header from "Source code" to "Source" more consistent with links in rest of page - - - - - 43ab7120 by Mark Lentczner at 2010-08-16T15:15:37+00:00 font size and margin tweaks - - - - - c0b68652 by Mark Lentczner at 2010-08-17T18:19:52+00:00 clean up collapser logics javascript code for collapasble sections cleaned up rewrote class utilities in javascript to be more robust refactored utilities for generating collapsable sections made toc be same color as synopsis module list has needed clear attribute in CSS - - - - - 5d573427 by Mark Lentczner at 2010-08-17T23:06:02+00:00 don't collapse entries in module list when clicking on links - - - - - 8c307c4a by Mark Lentczner at 2010-08-17T23:21:43+00:00 add missing data file to .cabal - - - - - 414bcfcf by Mark Lentczner at 2010-08-17T23:28:47+00:00 remove synopsis when in frames - - - - - ba0fa98a by Mark Lentczner at 2010-08-18T16:16:11+00:00 layout tweeks - mini page font size, toc color, etc. - - - - - 63c1bed1 by Mark Lentczner at 2010-08-18T19:50:02+00:00 margin fiddling - - - - - c311c094 by Mark Lentczner at 2010-08-20T01:37:55+00:00 better synopsis handling logic - no flashing - - - - - f1fe5fa8 by Mark Lentczner at 2010-08-20T01:41:06+00:00 fix small layout issues mini frames should have same size top heading give info block dts some padding so they don't collide in some browsers - - - - - 0de84d77 by Mark Lentczner at 2010-08-20T02:13:09+00:00 made style changing and cookies storage robust - - - - - 1ef064f9 by Thomas Schilling at 2010-08-04T13:12:22+00:00 Make synopsis frame behave properly in Firefox. In Firefox, pressing the back button first reverted the synopsis frame, and only clicking the back button a second time would update the main frame. - - - - - dd1c9a94 by Mark Lentczner at 2010-08-21T01:46:19+00:00 remove Snappy theme - - - - - 2353a90d by Mark Lentczner at 2010-08-25T05:16:19+00:00 fix occasional v.scroll bars on pre blocks (I think) - - - - - 459b8bf1 by Simon Hengel at 2010-08-08T10:12:45+00:00 Add createInterfaces' (a more high-level alternative to createInterfaces) to Haddock API - - - - - b1b68675 by David Waern at 2010-08-26T20:31:58+00:00 Follow recent API additions with some refactorings Simon Hegel's patch prompted me to do some refactorings in Main, Haddock.Documentation and Haddock.Interface. - - - - - 264d4d67 by David Waern at 2010-08-26T21:40:59+00:00 Get rid of GhcModule and related cruft We can get everything we need directly from TypecheckedModule. - - - - - 0feacec2 by Mark Lentczner at 2010-08-26T23:44:13+00:00 fixed CSS for ordered lists and def lists in doc blocks - - - - - 2997e0c2 by Mark Lentczner at 2010-08-26T23:45:03+00:00 support both kinds of enumerated lists in doc markup The documentation for Haddock says enumerated lists can use either of (1) first item 2. second item The second form wasn't actually supported - - - - - 5d4ddeec by Mark Lentczner at 2010-08-27T21:29:48+00:00 fix broken header link margins - - - - - 614456ba by Mark Lentczner at 2010-08-27T22:16:19+00:00 fix table of contents CSS - - - - - 03f329a2 by David Waern at 2010-08-28T16:36:09+00:00 Update tests following switch to the Xhtml backend - - - - - ca689fa2 by Mark Lentczner at 2010-08-28T18:25:16+00:00 fix def lists - - - - - 18e1d3d2 by Mark Lentczner at 2010-08-28T18:26:18+00:00 push footer to bottom of window - - - - - b0ab8d82 by David Waern at 2010-08-28T22:04:32+00:00 Whitespace police - - - - - 2d217977 by David Waern at 2010-08-29T12:44:45+00:00 Remove Snappy data files - - - - - 01e27d5f by David Waern at 2010-08-29T13:03:28+00:00 Add source entity path to --read-interface You can now use this flag like this: --read-interface=<html path>,<source entity path>,<.haddock file> By "source entity path" I mean the same thing that is specified with the --source-entity flag. The purpose of this is to be able to specify the source entity path per package, to allow source links to work in the presence of cross-package documentation. When given two arguments or less the --read-interface flag behaves as before. - - - - - 20bf4aaa by David Waern at 2010-08-29T13:11:03+00:00 Naming wibbles - - - - - ad22463f by Mark Lentczner at 2010-08-29T15:14:54+00:00 make portability block be a table - solves layout issues - - - - - 97bd1ae6 by Mark Lentczner at 2010-08-29T15:17:42+00:00 update golden test for Test due to portability box change - - - - - d37e139e by Mark Lentczner at 2010-08-29T17:07:17+00:00 move TOC and Info blocks down 0.5em to improve layout issue w/Test.hs - - - - - acf52501 by David Waern at 2010-08-29T17:32:36+00:00 Allow building with ghc < 6.16 - - - - - 1cb34ed8 by Ian Lynagh at 2010-07-24T23:18:49+00:00 Flatten the dynflags before parsing - - - - - b36845b4 by Ian Lynagh at 2010-07-24T23:26:49+00:00 Follow flattenLanguageFlags -> flattenExtensionFlags rename - - - - - 7f7fcc7e by David Waern at 2010-08-29T17:46:23+00:00 Use flattenExtensionFlags with ghc >= 6.13 only - - - - - 13cf9411 by Ian Lynagh at 2010-08-01T18:09:54+00:00 Make the main haddock script versioned, and make plain "haddock" a symlink - - - - - 495cbff2 by Ian Lynagh at 2010-08-18T18:57:24+00:00 Fix installation in the GHC build system Data-files are now in subdirectories, so we need to handle that - - - - - 88ebab0a by Ian Lynagh at 2010-08-18T19:43:53+00:00 GHC build system: Add all the data files to BINDIST_EXTRAS - - - - - 65837172 by David Waern at 2010-08-29T20:12:34+00:00 Update Test - - - - - 094bbaa2 by David Waern at 2010-08-29T20:55:14+00:00 Revert update to Test - - - - - a881cfb3 by David Waern at 2010-08-31T18:24:15+00:00 Bump version number - - - - - 1fc8a3eb by David Waern at 2010-08-31T22:32:27+00:00 Update ANNOUNCE - - - - - ee1df9d0 by David Waern at 2010-08-31T22:33:11+00:00 Update CHANGES - - - - - 394cc854 by David Waern at 2010-08-31T22:33:23+00:00 Update interface file versioning to work with ghc 6.14/15 - - - - - 7d03b79b by David Waern at 2010-08-31T22:36:00+00:00 Update test output following version change - - - - - a48d82d1 by Mark Lentczner at 2010-09-01T04:29:35+00:00 sort options in doc to match --help output removed --html-help option, as it is no longer supported - - - - - 06561aeb by Mark Lentczner at 2010-09-01T05:29:32+00:00 update options documentation rewrote doc for --html added doc for --theme and --built-in-themes added --use-contents and --gen-contents - - - - - 57dea832 by Mark Lentczner at 2010-09-01T05:31:27+00:00 slight wording change about Frames mode - - - - - fa1f6da3 by David Waern at 2010-09-01T10:57:44+00:00 Update doc configure script to find docbook stylesheets on arch linux - - - - - addff770 by David Waern at 2010-09-01T11:02:29+00:00 Wibble - - - - - 8399006d by David Waern at 2010-09-01T11:19:21+00:00 Replace ghci> with >>> in example syntax - - - - - 35074cf8 by David Waern at 2010-09-01T19:03:27+00:00 Improve docs for --no-tmp-comp-dir - - - - - 0f8f8cfd by David Waern at 2010-09-02T11:22:27+00:00 Add a list of contributors to the user guide Break out everyone thanked in the `Acknowledgements` chapter into a separate contributor list and add everyone from `darcs show authors`. We consider everyone who is thanked to be a contributor as a conservative estimation :-) I have added some more contributors that I know about, who were not in the darcs history, but others may be missing. So please add anyone that you think is missing from the list. - - - - - 42ccf099 by David Waern at 2010-09-02T11:29:22+00:00 Update copyright years in license - - - - - 0d560479 by David Waern at 2010-09-02T11:38:52+00:00 Update release instructions - - - - - 72ab7796 by David Waern at 2010-09-02T19:27:08+00:00 Add a note to ANNOUNCE - - - - - bf9d9c5d by David Waern at 2010-09-02T19:27:48+00:00 H.Utils needs FFI on Win+MinGW - - - - - 048ae44a by Mark Lentczner at 2010-09-04T23:19:47+00:00 make TOC group header identifiers validate - - - - - 8c6faf36 by Simon Michael at 2010-09-22T07:12:34+00:00 add hints for cleaner darcs show authors output - - - - - 9909bd17 by Simon Michael at 2010-09-22T17:58:06+00:00 print haddock coverage info on stdout when generating docs A module's haddockable items are its exports and the module itself. The output is lightly formatted so you can align the :'s and sort for readability. - - - - - 6da72171 by David Waern at 2010-10-03T21:31:24+00:00 Style wibble - - - - - 2f8d8e4d by Tobias Brandt at 2010-08-27T07:01:21+00:00 adding the option to fully qualify identifiers - - - - - 833be6c6 by Tobias Brandt at 2010-08-27T15:50:28+00:00 adding support for local and relative name qualification - - - - - df15c4e9 by Tobias Brandt at 2010-08-27T15:56:37+00:00 corrected qualification help message - - - - - 449e9ce1 by David Waern at 2010-10-16T17:34:30+00:00 Solve conflicts - - - - - 3469bda5 by David Waern at 2010-10-16T18:42:40+00:00 Use "qual" as an abbreviation for qualification instead of "quali" for consistency - - - - - 97c2d728 by David Waern at 2010-10-16T18:47:07+00:00 Style police - - - - - ce14fbea by David Waern at 2010-10-16T21:15:25+00:00 Style police - - - - - fdf29e9d by David Waern at 2010-10-17T00:30:44+00:00 Add a pointer to the style guide - - - - - 8e6b44e8 by rrnewton at 2010-10-24T03:19:28+00:00 Change to index pages: include an 'All' option even when subdividing A-Z. - - - - - 755b131c by David Waern at 2010-11-14T19:39:36+00:00 Bump version - - - - - d0345a04 by David Waern at 2010-11-14T19:41:59+00:00 TAG 2.8.1 - - - - - f6221508 by Simon Peyton Jones at 2010-09-13T09:53:00+00:00 Adapt to minor changes in internal GHC functions - - - - - 1290713d by Ian Lynagh at 2010-09-15T10:37:18+00:00 Remove duplicate Outputable instance for Data.Map.Map - - - - - 87f69eef by Ian Lynagh at 2010-09-21T15:01:10+00:00 Bump GHC dep upper bound - - - - - af36e087 by Ian Lynagh at 2010-09-21T15:12:02+00:00 Fix up __GLASGOW_HASKELL__ tests - - - - - ad67716c by Ian Lynagh at 2010-09-21T20:31:35+00:00 Don't build haddock is HADDOCK_DOCS is NO - - - - - 63b3f1f5 by Ian Lynagh at 2010-09-21T21:39:51+00:00 Fixes for when HADDOCK_DOCS=NO - - - - - e92bfa42 by Ian Lynagh at 2010-09-29T21:15:38+00:00 Fix URL creation on Windows: Use / not \ in URLs. Fixes haskell/haddock#4353 - - - - - 66c55e05 by Ian Lynagh at 2010-09-30T17:03:34+00:00 Tidy up haddock symlink installation In particular, it now doesn't get created if we aren't installing haddock. - - - - - 549b5556 by Ian Lynagh at 2010-10-23T21:17:14+00:00 Follow extension-flattening change in GHC - - - - - d7c2f72b by David Waern at 2010-11-14T20:17:55+00:00 Bump version to 2.8.2 - - - - - 6989a3a9 by David Waern at 2010-11-14T20:26:01+00:00 Solve conflict - - - - - 055c6910 by Ian Lynagh at 2010-09-22T15:36:20+00:00 Bump GHC dep - - - - - c96c0763 by Simon Marlow at 2010-10-27T11:09:44+00:00 follow changes in the GHC API - - - - - 45907129 by David Waern at 2010-11-07T14:00:58+00:00 Update the HCAR entry - - - - - 61940b95 by David Waern at 2010-11-07T14:07:34+00:00 Make the HCAR entry smaller - - - - - aa590b7d by David Waern at 2010-11-14T21:30:59+00:00 Update HCAR entry with November 2010 version - - - - - 587f9847 by David Waern at 2010-11-14T23:48:17+00:00 Require ghc >= 7.0 - - - - - ff5c647c by David Waern at 2010-11-14T23:49:09+00:00 TAG 2.8.2 - - - - - 937fcb4f by David Waern at 2010-11-14T23:49:45+00:00 Solve conflict - - - - - 8e5d0c1a by David Waern at 2010-11-15T21:09:50+00:00 Remove code for ghc < 7 - - - - - 3d47b70a by David Waern at 2010-11-15T21:11:06+00:00 Fix bad merge - - - - - 7f4a0d8a by David Waern at 2010-11-15T21:13:57+00:00 Remove more ghc < 7 code - - - - - 9ee34b50 by David Waern at 2010-11-15T21:31:25+00:00 Match all AsyncExceptions in exception handler - - - - - 42849c70 by David Waern at 2010-11-15T21:35:31+00:00 Just say "internal error" instead of "internal Haddock or GHC error" - - - - - c88c809b by David Waern at 2010-11-15T21:44:19+00:00 Remove docNameOcc under the motto "don't name compositions" - - - - - b798fc7c by David Waern at 2010-11-15T23:27:13+00:00 Wibble - - - - - 2228197e by David Waern at 2010-11-15T23:28:24+00:00 Rename the HCAR entry file - - - - - 8a3f9090 by David Waern at 2010-11-16T00:05:29+00:00 Remove Haskell 2010 extensions from .cabal file - - - - - c7a0c597 by David Waern at 2010-11-16T00:10:28+00:00 Style wibbles - - - - - cde707a5 by David Waern at 2010-11-16T00:12:00+00:00 Remove LANGUAGE ForeignFunctionInterface pragmas - - - - - 1dbda8ed by David Waern at 2010-11-16T00:17:21+00:00 Make a little more use of DoAndIfThenElse - - - - - 4c45ff6e by David Waern at 2010-11-16T00:59:41+00:00 hlint police - - - - - d2feaf09 by David Waern at 2010-11-16T01:14:15+00:00 hlint police - - - - - 99876e97 by David Waern at 2010-11-20T19:06:00+00:00 Haddock documentation updates - - - - - 65ce6987 by David Waern at 2010-11-20T19:42:51+00:00 Follow the style guide closer in Haddock.Types and improve docs - - - - - 28ca304a by tob.brandt at 2010-11-20T17:04:40+00:00 add full qualification for undocumented names - - - - - d61341e3 by David Waern at 2010-11-20T20:04:15+00:00 Re-structure qualification code a little - - - - - 0057e4d6 by David Waern at 2010-11-20T20:07:55+00:00 Re-order functions - - - - - d7279afd by David Waern at 2010-11-21T03:39:54+00:00 Add BangPatterns to alex and happy source files - - - - - 629fe60e by tob.brandt at 2010-11-23T23:35:11+00:00 documentation for qualification - - - - - 37031cee by David Waern at 2010-11-23T21:06:44+00:00 Update CHANGES - don't mention 2.8.2, we won't release it - - - - - f2489e19 by David Waern at 2010-12-01T21:57:11+00:00 Update deps of runtests.hs to work with ghc 7.0.1 - - - - - d3657e9a by David Waern at 2010-12-01T22:04:57+00:00 Make tests compile with ghc 7.0.1 - - - - - a2f09d9b by David Waern at 2010-12-01T22:06:59+00:00 Update tests following version bump - - - - - 50883ebb by David Waern at 2010-12-06T14:09:18+00:00 Update tests following recent changes - - - - - fc2fadeb by David Waern at 2010-12-06T14:17:29+00:00 Add a flag --pretty-html for rendering indented html with newlines - - - - - 30832ef2 by David Waern at 2010-12-06T14:17:35+00:00 Use --pretty-html when running the test suite. Makes it easier to compare output - - - - - a0b81b31 by David Waern at 2010-12-06T14:18:27+00:00 Wibble - - - - - 3aaa23fe by David Waern at 2010-12-06T14:19:29+00:00 Haddockify ppHtml comments - - - - - 24bb24f0 by David Waern at 2010-12-06T14:23:15+00:00 Remove --debug. It was't used, and --verbosity should take its place - - - - - 6bc076e5 by David Waern at 2010-12-06T14:25:37+00:00 Rename golden-tests into html-tests. "golden tests" sounds strange - - - - - 53301e55 by David Waern at 2010-12-06T14:26:26+00:00 QUALI -> QUAL in the description --qual for consistency - - - - - 98b6affb by David Waern at 2010-12-06T21:54:02+00:00 Bump version - - - - - 371bf1b3 by David Waern at 2010-12-06T22:08:55+00:00 Update tests following version bump - - - - - 25be762d by David Waern at 2010-12-06T22:21:03+00:00 Update CHANGES - - - - - 7c7dac71 by David Waern at 2010-12-06T22:33:43+00:00 Update ANNOUNCE - - - - - 30d7a5f2 by Simon Peyton Jones at 2010-11-15T08:38:38+00:00 Alex generates BangPatterns, so make Lex.x accept them (It'd be better for Alex to generate this pragma.) - - - - - 605e8018 by Simon Marlow at 2010-11-17T11:37:24+00:00 Add {-# LANGUAGE BangPatterns #-} to mollify GHC - - - - - a46607ba by David Waern at 2010-12-07T14:08:10+00:00 Solve conflicts - - - - - b28cda66 by David Waern at 2010-12-09T20:41:35+00:00 Docs: Mention that \ is a special character in markup - - - - - a435bfdd by Ian Lynagh at 2010-11-17T14:01:19+00:00 TAG GHC 7.0.1 release - - - - - 5a15a05a by David Waern at 2010-12-11T17:51:19+00:00 Fix indentation problem - - - - - 4232289a by Lennart Kolmodin at 2010-12-17T18:32:03+00:00 Revise haddock.cabal given that we now require ghc-7 default-language should be Haskell2010, slight new semantics for extensions. Rewrite into clearer dependencies of base and Cabal. - - - - - a36302dc by David Waern at 2010-12-19T17:12:37+00:00 Update CHANGES - - - - - 7c8b85b3 by David Waern at 2010-12-19T17:14:24+00:00 Bump version - - - - - cff22813 by Ian Lynagh at 2011-01-05T18:24:27+00:00 Write hoogle output in utf8; fixes GHC build on Windows - - - - - c7e762ea by David Waern at 2011-01-22T00:00:35+00:00 Put title outside doc div when HTML:fying title+prologue Avoids indenting the title, and makes more sense since the title is not a doc string anyway. - - - - - 5f639054 by David Waern at 2011-01-22T16:09:44+00:00 Fix spelling error - contributed by Marco Silva - - - - - c11dce78 by Ian Lynagh at 2011-01-07T02:33:11+00:00 Follow GHC build system changes - - - - - 101cfaf5 by David Waern at 2011-01-08T14:06:44+00:00 Bump version - - - - - af62348b by David Waern at 2011-01-08T14:07:07+00:00 TAG 2.9.2 - - - - - 4d1f6461 by Ian Lynagh at 2011-01-07T23:06:57+00:00 Name the haddock script haddock-ghc-7.0.2 instead of haddock-7.0.2; haskell/haddock#4882 "7.0.2" looked like a haddock version number before - - - - - 8ee4d5d3 by Simon Peyton Jones at 2011-01-10T17:31:12+00:00 Update Haddock to reflect change in hs_tyclds field of HsGroup - - - - - 06f3e3db by Ian Lynagh at 2011-03-03T15:02:37+00:00 TAG GHC 7.0.2 release - - - - - 7de0667d by David Waern at 2011-03-10T22:47:13+00:00 Update CHANGES - - - - - 33a9f1c8 by David Waern at 2011-03-10T22:47:31+00:00 Fix build with ghc 7.0.1 - - - - - 4616f861 by David Waern at 2011-03-10T22:47:50+00:00 TAG 2.9.2-actual - - - - - 0dab5e3c by Simon Hengel at 2011-04-08T15:53:01+00:00 Set shell script for unit tests back to work - - - - - 85c54dee by Simon Hengel at 2011-04-08T16:01:24+00:00 Set unit tests back to work Here "ghci>" was still used instead of ">>>". - - - - - 1cea9b78 by Simon Hengel at 2011-04-08T16:25:36+00:00 Update runtests.hs for GHC 7.0.2 - - - - - 8e5b3bbb by Simon Hengel at 2011-04-08T16:28:49+00:00 Update Haddock version in *.html.ref - - - - - 2545e955 by Simon Hengel at 2011-04-08T17:09:28+00:00 Add support for blank lines in the result of examples Result lines that only contain the string "<BLANKLINE>" are treated as a blank line. - - - - - adf64d2e by Simon Hengel at 2011-04-08T17:36:50+00:00 Add documentation for "support for blank lines in the result of examples" - - - - - c51352ca by David Waern at 2011-05-21T23:57:56+00:00 Improve a haddock comment - - - - - 7419cf2c by David Waern at 2011-05-22T15:41:52+00:00 Use cabal's test suite support to run the test suite This gives up proper dependency tracking of the test script. - - - - - 7770070c by David Waern at 2011-05-22T01:45:44+00:00 We don't need to send DocOptions nor a flag to mkExportItems - - - - - 9d95b7b6 by David Waern at 2011-05-22T21:39:03+00:00 Fix a bug - - - - - 1f93699b by David Waern at 2011-05-22T21:40:21+00:00 Break out fullContentsOf, give it a better name and some documentation The documentation describes how we want this function to eventually behave, once we have fixed a few problems with the current implementation. - - - - - 9a86432f by David Waern at 2011-05-22T21:53:52+00:00 Fix some stylistic issues in mkExportItems - - - - - c271ff0c by David Waern at 2011-05-22T22:09:11+00:00 Indentation - - - - - 93e602b1 by David Waern at 2011-06-10T01:35:31+00:00 Add git commits since switchover: darcs format (followed by a conflict resolution): commit 6f92cdd12d1354dfbd80f8323ca333bea700896a Merge: f420cc4 28df3a1 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 19 17:54:34 2011 +0100 Merge remote branch 'origin/master' into ghc-generics commit 28df3a119f770fdfe85c687dd73d5f6712b8e7d0 Author: Max Bolingbroke <batterseapower at hotmail.com> Date: Sat May 14 22:37:02 2011 +0100 Unicode fix for getExecDir on Windows commit 89813e729be8bce26765b95419a171a7826f6d70 Merge: 6df3a04 797ab27 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 9 11:55:17 2011 +0100 Merge branch 'ghc-new-co' commit 6df3a040da3dbddee67c6e30a892f87e6b164383 Author: Ian Lynagh <igloo at earth.li> Date: Sun May 8 17:05:50 2011 +0100 Follow changes in SDoc commit f420cc48b9259f0b1afd2438b12f9a2bde57053d Author: Jose Pedro Magalhaes <jpm at cs.uu.nl> Date: Wed May 4 17:31:52 2011 +0200 Adapt haddock to the removal of HsNumTy and TypePat. commit 797ab27bdccf39c73ccad374fea265f124cb52ea Merge: 1d81436 5a91450 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:05:03 2011 +0100 Merge remote branch 'origin/master' into ghc-new-co commit 1d8143659a81cf9611668348e33fd0775c7ab1d2 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:03:46 2011 +0100 Wibbles for ghc-new-co branch commit 5a91450e2ea5a93c70bd3904b022445c9cc82488 Author: Ian Lynagh <igloo at earth.li> Date: Fri Apr 22 00:51:56 2011 +0100 Follow defaultDynFlags change in GHC - - - - - 498da5ae by David Waern at 2011-06-11T00:33:33+00:00 * Merge in git patch from Michal Terepeta >From 6fc71d067738ef4b7de159327bb6dc3d0596be29 Mon Sep 17 00:00:00 2001 From: Michal Terepeta <michal.terepeta at gmail.com> Date: Sat, 14 May 2011 19:18:22 +0200 Subject: [PATCH] Follow the change of TypeSig in GHC. This follows the change in GHC to make TypeSig take a list of names (instead of just one); GHC ticket haskell/haddock#1595. This should also improve the Haddock output in case the user writes a type signature that refers to many names: -- | Some comment.. foo, bar :: ... will now generate the expected output with one signature for both names. - - - - - 094607fe by Ian Lynagh at 2011-06-17T19:10:29+01:00 Fix build - - - - - 8fa35740 by Ian Lynagh at 2011-06-26T21:06:40+01:00 Bump GHC dep to allow 7.2 - - - - - e4d2ca3c by Ian Lynagh at 2011-07-07T23:06:28+01:00 Relax base dep - - - - - b948fde9 by Ian Lynagh at 2011-07-28T16:39:45+01:00 GHC build system: Don't install the datafiles twice - - - - - f82f6d70 by Simon Marlow at 2011-08-11T12:08:15+01:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - b341cc12 by Max Bolingbroke at 2011-08-22T20:25:27+01:00 Fix compilation with no-pred-ty GHC - - - - - 30494581 by Max Bolingbroke at 2011-08-23T10:20:54+01:00 Remaining fixes for PredTy removal - - - - - 0b197138 by Max Bolingbroke at 2011-08-26T08:27:45+01:00 Rename factKind to constraintKind - - - - - a379bec5 by Max Bolingbroke at 2011-09-04T12:54:47+01:00 Deal with change to IParam handling in GHC - - - - - f94e421b by Max Bolingbroke at 2011-09-06T17:34:31+01:00 Adapt Haddock for the ConstraintKind extension changes - - - - - 8821e5cc by Max Bolingbroke at 2011-09-09T08:24:59+01:00 Ignore associated type defaults (just as we ignore default methods) - - - - - 31a0afd4 by Max Bolingbroke at 2011-09-09T09:06:00+01:00 Merge branch 'no-pred-ty' of ssh://darcs.haskell.org/srv/darcs/haddock into no-pred-ty - - - - - dd3b530a by Max Bolingbroke at 2011-09-09T14:10:25+01:00 Merge branch 'no-pred-ty' Conflicts: src/Haddock/Convert.hs - - - - - 5f25ec96 by Max Bolingbroke at 2011-09-09T14:10:40+01:00 Replace FactTuple with ConstraintTuple - - - - - cd30b9cc by David Waern at 2011-09-26T02:17:55+02:00 Bump to version 2.9.3 - - - - - 4fbfd397 by Max Bolingbroke at 2011-09-27T14:55:21+01:00 Follow changes to BinIface Name serialization - - - - - 92257d90 by David Waern at 2011-09-30T23:45:07+02:00 Fix problem with test files not added to distribution tarball - - - - - 00255bda by David Waern at 2011-09-30T23:48:24+02:00 Merge branch 'development' - - - - - 5421264f by David Waern at 2011-10-01T01:25:39+02:00 Merge in darcs patch from Simon Meier: Wed Jun 1 19:41:16 CEST 2011 iridcode at gmail.com * prettier haddock coverage info The new coverage info rendering uses less horizontal space. This reduces the number of unnecessary line-wrappings. Moreover, the most important information, how much has been documented already, is now put up front. Hopefully, this makes it more likely that a library author is bothered by the low coverage of his modules and fixes that issue ;-) - - - - - 07d318ef by David Waern at 2011-10-01T01:34:10+02:00 Use printException instead of deprecated printExceptionAndWarnings - - - - - 40d52ee4 by David Waern at 2011-10-01T01:41:13+02:00 Merge in darcs pach: Mon Apr 11 18:09:54 JST 2011 Liyang HU <haddock at liyang.hu> * Remember collapsed sections in index.html / haddock-util.js - - - - - 279d6dd4 by David Waern at 2011-10-01T01:55:45+02:00 Merge in darcs patch: Joachim Breitner <mail at joachim-breitner.de>**20110619201645 Ignore-this: f6c51228205b0902ad5bfad5040b989a As reported on http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=578301, generating the global index takes much too long if type-level (with lots of auto-generated types) is installed. The patch avoids a quadratic runtime in the subfunction getIfaceIndex of ppHtmlIndex by using a temporary set. Runtime improvement observed here from 25.36s to 2.86s. - - - - - d1612383 by David Waern at 2011-10-01T01:56:48+02:00 Merge branch 'development' - - - - - 347520c1 by David Waern at 2011-10-01T01:56:54+02:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9a0c95e8 by David Waern at 2011-10-01T02:19:10+02:00 Improve .cabal file - - - - - 6967dc64 by Ian Lynagh at 2011-10-01T01:34:06+01:00 Follow changes to ForeignImport/ForeignExport in GHC - - - - - 565cb26b by Simon Marlow at 2011-10-04T00:15:04+02:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - 8b74f512 by David Waern at 2011-10-04T00:18:17+02:00 Requre ghc >= 7.2 - - - - - 271d360c by David Waern at 2011-10-04T00:22:50+02:00 Bump version to 2.9.4 - - - - - 37f3edb0 by David Waern at 2011-10-06T02:30:21+02:00 Add alex and happy to build-tools. - - - - - 7ac2bb6e by David Terei at 2011-10-12T14:02:55-07:00 Add safe haskell indication to haddock output - - - - - 42c91a47 by David Terei at 2011-10-12T14:06:03-07:00 Fix CSS issue with info table not being contained in module header - - - - - 0eddab6c by David Terei at 2011-10-12T14:06:58-07:00 Add safe haskell indication to haddock output - - - - - 3df058eb by David Terei at 2011-10-12T14:07:07-07:00 Fix CSS issue with info table not being contained in module header - - - - - a40a6c3f by David Waern at 2011-10-22T11:29:06+02:00 Bump .haddock file version since the format has changed recently - - - - - 8a6254be by David Waern at 2011-10-22T11:30:42+02:00 Merge branch 'development' - - - - - 642e3e02 by David Waern at 2011-10-23T21:23:39+02:00 Sort import list - - - - - 36371cf8 by David Waern at 2011-10-23T22:48:18+02:00 Remove NEW_GHC_LAYOUT conditional. - - - - - 5604b499 by David Waern at 2011-10-27T00:15:03+02:00 Add --print-ghc-path. - - - - - 463499fa by David Waern at 2011-10-27T00:16:22+02:00 Make testsuite able to find its dependencies automatically. - - - - - a3506172 by Ryan Newton at 2011-11-05T05:59:58-04:00 Improved declNames internal error. Added a case to handle DocD. - - - - - 001b8baf by David Waern at 2011-11-05T20:37:29+01:00 Rename copy.hs -> accept.hs. - - - - - 55d808d3 by David Waern at 2011-11-05T23:30:02+01:00 Fix build. - - - - - deb5c3be by David Waern at 2011-11-06T00:01:47+01:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9b663554 by David Waern at 2011-11-06T00:03:45+01:00 Merge https://github.com/rrnewton/haddock - - - - - 1abb0ff6 by David Waern at 2011-11-06T01:20:37+01:00 Use getDeclMainBinder instead of declNames. - - - - - 4b005c01 by David Waern at 2011-11-06T19:09:53+01:00 Fix build. - - - - - c2c51bc7 by Ian Lynagh at 2011-11-06T23:01:33+00:00 Remove -DNEW_GHC_LAYOUT in ghc.mk - - - - - f847d703 by Jose Pedro Magalhaes at 2011-11-11T09:07:39+00:00 New kind-polymorphic core This big patch implements a kind-polymorphic core for GHC. The current implementation focuses on making sure that all kind-monomorphic programs still work in the new core; it is not yet guaranteed that kind-polymorphic programs (using the new -XPolyKinds flag) will work. For more information, see http://haskell.org/haskellwiki/GHC/Kinds - - - - - 7d7c3b09 by Jose Pedro Magalhaes at 2011-11-16T21:42:22+01:00 Follow changes to tuple sorts in master - - - - - 8430e03e by Simon Peyton Jones at 2011-11-17T10:20:27+00:00 Remove redundant imports - - - - - d1b06832 by Ian Lynagh at 2011-11-19T01:33:21+00:00 Follow GHC build system change to the way we call rm - - - - - 9e2230ed by David Waern at 2011-11-24T15:00:24+01:00 Fix a bug in test runner and get rid of regex-compat dependency. - - - - - 52039b21 by David Waern at 2011-11-24T23:55:36+01:00 Avoid haskell98 dependency in test - - - - - 92e1220d by David Waern at 2011-11-25T00:03:33+01:00 Avoid depency on regex-compat also in accept.hs. - - - - - ddac6b6f by David Waern at 2011-11-25T02:13:38+01:00 Accept test output. - - - - - 5a720455 by David Waern at 2011-11-25T02:16:20+01:00 Some more changes to test scripts. - - - - - 170a9004 by David Waern at 2011-11-25T02:30:41+01:00 Add flag --interface-version. - - - - - d225576c by David Waern at 2011-11-25T02:39:26+01:00 Remove #ifs for older compiler versions. - - - - - f0d0a4f5 by David Waern at 2011-11-26T04:20:12+01:00 Give preference to type over data constructors for doc comment links at renaming time. Previously this was done in the backends. Also, warn when a doc comment refers to something that is in scope but which we don't have the .haddock file for. These changes mean we can make DocIdentifier [a] into DocIdentifier a. - - - - - eef0e776 by David Waern at 2011-11-26T17:01:06+01:00 Allow doc comments to link to out-of-scope things (#78). (A bug that should have been fixed long ago.) - - - - - 565ad529 by David Waern at 2011-11-26T19:56:21+01:00 Update tests. - - - - - fb3ce7b9 by David Waern at 2011-11-26T21:44:28+01:00 Cleanup. - - - - - d0328126 by David Waern at 2011-11-26T22:10:28+01:00 Fix module reference bug. - - - - - c03765f8 by David Waern at 2011-12-03T05:20:20+01:00 Slightly better behaviour on top-levels without type signatures. - Docs don't get attached to the next top-level with signature by mistake. - If there's an export list and the top-level is part of it, its doc comment shows up in the documentation. - - - - - 48461d31 by David Waern at 2011-12-03T05:38:10+01:00 Add a test for Unicode doc comments. - - - - - 549c4b4e by David Waern at 2011-12-03T19:07:55+01:00 Cleanup. - - - - - 7bfecf91 by David Waern at 2011-12-03T20:13:08+01:00 More cleanup. - - - - - 14fab722 by Ian Lynagh at 2011-12-12T21:21:35+00:00 Update dependencies and binaryInterfaceVersion - - - - - 469e6568 by Ian Lynagh at 2011-12-18T12:56:16+00:00 Fix (untested) building from source tarball without alex/happy haddock's .cabal file was declaring that it needed alex and happy to build, but in the GHC source tarballs it doesn't. - - - - - 895c9a8c by David Waern at 2011-12-27T12:57:43+01:00 Go back to having a doc, sub and decl map instead of one big decl map. This setup makes more sense since when we add value bindings to the processed declarations (for type inference), we will have multiple declarations which should share documentation. Also, we already have a separate doc map for instances which we can now merge into the main doc map. Another benefit is that we don't need the DeclInfo type any longer. - - - - - 736767d9 by David Waern at 2011-12-27T13:33:41+01:00 Merge ../../../haddock Conflicts: src/Haddock/InterfaceFile.hs - - - - - 20016f79 by David Waern at 2011-12-27T13:57:23+01:00 Bump version. - - - - - 31f276fb by David Waern at 2011-12-27T13:57:32+01:00 Merge ../ghc/utils/haddock - - - - - 95b367cd by David Waern at 2011-12-27T14:57:29+01:00 Update tests following version bump. - - - - - fa3c94cd by David Waern at 2011-12-27T14:57:51+01:00 Get rid of quite unnecessary use of different lists. - - - - - 9c4d3c54 by David Waern at 2011-12-27T15:26:42+01:00 Cleanup. - - - - - 2caf9f90 by David Waern at 2011-12-27T16:18:05+01:00 Wibbles. - - - - - 3757d09b by David Waern at 2011-12-27T20:50:26+01:00 Complete support for inferring types for top-level bindings. - - - - - 53418734 by David Waern at 2011-12-28T15:02:13+01:00 Minor fixes and cleanup. - - - - - 0c9d0385 by Ian Lynagh at 2012-01-03T18:31:29+00:00 Follow rename of Instance to ClsInst in GHC - - - - - c9bc969a by Simon Hengel at 2012-01-12T21:28:14+01:00 Make sure that generated xhtml is valid (close haskell/haddock#186) Thanks to Phyx. - - - - - 836a0b9a by David Waern at 2012-02-01T02:30:05+01:00 Fix bug introduced in my recent refactoring. - - - - - c7d733eb by David Waern at 2012-02-01T02:30:26+01:00 Cleanup mkMaps and avoid quadratic behaviour. - - - - - da3cda8f by David Waern at 2012-02-01T02:56:56+01:00 Require ghc >= 7.4. - - - - - 83a3287e by David Waern at 2012-02-01T02:57:36+01:00 Update CHANGES. - - - - - 93408f0b by Simon Hengel at 2012-02-04T00:48:04+01:00 Add reference renderings - - - - - 49d00d2c by Simon Hengel at 2012-02-04T00:48:25+01:00 Set unit tests for parser back to work - - - - - eb450980 by Simon Hengel at 2012-02-04T00:49:07+01:00 Add .gitignore - - - - - a841602c by Simon Hengel at 2012-02-04T00:49:16+01:00 Add .ghci file - - - - - 8861199d by Simon Hengel at 2012-02-04T00:49:29+01:00 tests/html-tests/copy.hs: Use mapM_ instead of mapM So we do net get a list of () on stdout when running with runhaskell. - - - - - b477d9b5 by Simon Hengel at 2012-02-04T00:49:46+01:00 Remove index files from golden tests - - - - - 9dbda34e by Simon Hengel at 2012-02-04T00:49:57+01:00 Add /tests/html-tests/tests/*index*.ref to .gitignore - - - - - a9434817 by Simon Hengel at 2012-02-04T00:50:04+01:00 Add DocWarning to Doc The Xhtml backend has special markup for that, Hoogle and LaTeX reuse what we have for DocEmphasis. - - - - - de2fb6fa by Simon Hengel at 2012-02-04T00:50:13+01:00 Add support for module warnings - - - - - 0640920e by Simon Hengel at 2012-02-04T00:50:21+01:00 Add tests for module warnings - - - - - 30ce0d77 by Simon Hengel at 2012-02-04T00:50:29+01:00 Add support for warnings - - - - - bb367960 by Simon Hengel at 2012-02-04T00:50:37+01:00 Add tests for warnings - - - - - 6af1dc2d by Simon Hengel at 2012-02-04T00:50:50+01:00 Expand type signatures in export list (fixes haskell/haddock#192) - - - - - a06cbf25 by Simon Hengel at 2012-02-04T00:51:04+01:00 Expand type signatures for modules without explicit export list - - - - - 57dda796 by Simon Hengel at 2012-02-04T00:51:15+01:00 Remove obsolete TODO - - - - - 270c3253 by David Waern at 2012-02-04T00:51:24+01:00 Fix issues in support for warnings. * Match against local names only. * Simplify (it's OK to map over the warnings). - - - - - 683634bd by David Waern at 2012-02-04T00:55:11+01:00 Some cleanup and make sure we filter warnings through exports. - - - - - 210cb4ca by David Waern at 2012-02-04T03:01:30+01:00 Merge branch 'fix-for-186' of https://github.com/sol/haddock into ghc-7.4 - - - - - e8db9031 by David Waern at 2012-02-04T03:07:51+01:00 Style police. - - - - - 261f9462 by David Waern at 2012-02-04T03:20:16+01:00 Update tests. - - - - - 823cfc7c by David Waern at 2012-02-04T03:21:12+01:00 Use mapM_ in accept.hs as well. - - - - - 873dd619 by David Waern at 2012-02-04T03:21:33+01:00 Remove copy.hs - use accept.hs instead. - - - - - 0e31a14a by David Waern at 2012-02-04T03:47:33+01:00 Use <> instead of mappend. - - - - - 2ff7544f by David Waern at 2012-02-04T03:48:55+01:00 Remove code for older ghc versions. - - - - - dacf2786 by David Waern at 2012-02-04T15:52:51+01:00 Clean up some code from last SoC project. - - - - - 00cbb117 by David Waern at 2012-02-04T21:43:49+01:00 Mostly hlint-inspired cleanup. - - - - - 7dc86cc2 by Simon Peyton Jones at 2012-02-06T09:14:41+00:00 Track changes in HsDecls - - - - - f91f82fe by Ian Lynagh at 2012-02-16T13:40:11+00:00 Follow changes in GHC caused by the CAPI CTYPE pragma - - - - - a0ea6b0b by Ian Lynagh at 2012-02-22T02:26:12+00:00 Follow changes in GHC - - - - - b23b07d1 by Simon Peyton Jones at 2012-03-02T16:36:41+00:00 Follow changes in data representation from the big PolyKinds commit - - - - - 43406022 by Simon Hengel at 2012-03-05T11:18:34+01:00 Save/restore global state for static flags when running GHC actions This is necessary if we want to run createInterfaces (from Documentation.Haddock) multiple times in the same process. - - - - - 9fba16fe by Paolo Capriotti at 2012-03-06T10:57:33+00:00 Update .gitignore. - - - - - a9325044 by Simon Peyton Jones at 2012-03-14T17:35:42+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - fd48065a by Iavor Diatchki at 2012-03-15T22:43:35-07:00 Add support for type-level literals. - - - - - 2e8206dd by Simon Peyton Jones at 2012-03-16T14:18:22+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - 93e13319 by Simon Peyton Jones at 2012-03-17T01:04:05+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock Conflicts: src/Haddock/Convert.hs - - - - - d253fa71 by Iavor Diatchki at 2012-03-19T20:12:18-07:00 Merge remote-tracking branch 'origin/master' into type-nats - - - - - fc40acc8 by Iavor Diatchki at 2012-03-19T20:31:27-07:00 Add a missing case for type literals. - - - - - fd2ad699 by Iavor Diatchki at 2012-03-24T13:28:29-07:00 Rename variable to avoid shadowing warning. - - - - - 9369dd3c by Simon Peyton Jones at 2012-03-26T09:14:23+01:00 Follow refactoring of TyClDecl/HsTyDefn - - - - - 38825ca5 by Simon Peyton Jones at 2012-03-26T09:14:37+01:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - 4324ac0f by David Waern at 2012-04-01T01:51:19+02:00 Disable unicode test. - - - - - 3165b750 by David Waern at 2012-04-01T01:51:34+02:00 Take reader environment directly from TypecheckedSource. - - - - - 213b644c by David Waern at 2012-04-01T01:55:20+02:00 Cleanup. - - - - - 3118b4ba by David Waern at 2012-04-01T02:16:15+02:00 Don't filter out unexported names from the four maps - fixes a regression. - - - - - d6524e17 by David Waern at 2012-04-01T02:40:34+02:00 Fix crash when using --qual. Naughty GHC API! - - - - - ea3c43d8 by Henning Thielemann at 2012-04-01T13:03:07+02:00 add QualOption type for distinction between qualification argument given by the user and the actual qualification for a concrete module - - - - - 5422ff05 by Henning Thielemann at 2012-04-01T16:25:02+02:00 emit an error message when the --qual option is used incorrectly - - - - - 026e3404 by David Waern at 2012-04-01T18:10:30+02:00 Don't crash on unicode strings in doc comments. - - - - - ce006632 by David Waern at 2012-04-01T20:13:35+02:00 Add test for --ignore-all-exports flag/ignore-exports pragma. - - - - - 6e4dd33c by David Waern at 2012-04-01T20:21:03+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.4 - - - - - 734ae124 by Henning Thielemann at 2012-04-01T20:22:10+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - 622f9ba5 by David Waern at 2012-04-01T21:26:13+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 55ce17cb by Henning Thielemann at 2012-04-01T22:03:25+02:00 'abbreviate' qualification style - basic support Currently we ignore the package a module is imported from. This means that a module import would shadow another one with the same module name from a different package. - - - - - c85314ef by David Waern at 2012-04-01T22:05:12+02:00 Check qualification option before processing modules. - - - - - ae4b626c by Henning Thielemann at 2012-04-02T00:19:36+02:00 abbreviated qualification: use Packages.lookupModuleInAllPackages for finding the package that a module belongs to - - - - - 60bdbcf5 by Henning Thielemann at 2012-04-02T00:25:31+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - df44301d by Henning Thielemann at 2012-04-02T00:29:05+02:00 qualification style 'abbreviated' -> 'aliased' - - - - - f4192a64 by David Waern at 2012-04-02T01:05:47+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 7ba09067 by David Terei at 2012-04-04T15:08:21-07:00 Fix reporting of modules safe haskell mode (#5989) - - - - - d0cc33d0 by David Terei at 2012-04-06T15:50:41+01:00 Fix reporting of modules safe haskell mode (#5989) - - - - - 6e3434c5 by Simon Peyton Jones at 2012-04-20T18:37:46+01:00 Track changes in HsSyn - - - - - 22014ed0 by Simon Peyton Jones at 2012-05-11T22:45:15+01:00 Follow changes to LHsTyVarBndrs - - - - - d9a07b24 by David Waern at 2012-05-15T01:46:35+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - a6c4ebc6 by David Waern at 2012-05-16T02:18:32+02:00 Update CHANGES. - - - - - 8e181d29 by David Waern at 2012-05-16T02:27:56+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - e358210d by David Waern at 2012-05-16T02:35:33+02:00 Mention the new aliased --qual mode in CHANGES. - - - - - efd36a28 by David Waern at 2012-05-16T21:33:13+02:00 Bump version number. - - - - - d6b3af14 by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for deprecated record field - - - - - 927f800e by Simon Hengel at 2012-05-17T19:08:20+02:00 Use >>= instead of fmap and join - - - - - 048b41d5 by Simon Hengel at 2012-05-17T19:08:20+02:00 newtype-wrap Doc nodes for things that may have warnings attached - - - - - e3a89fc3 by Simon Hengel at 2012-05-17T19:08:20+02:00 Attach warnings to `Documentation` type - - - - - 5d4cc43d by Simon Hengel at 2012-05-17T19:08:20+02:00 Simplify lookupWarning - - - - - cf8ae69d by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for haskell/haddock#205 - - - - - cb409b19 by Simon Peyton Jones at 2012-05-25T08:30:11+01:00 Follow changes in LHsTyVarBndrs - - - - - 2d5f4179 by Simon Hengel at 2012-05-26T19:21:29+02:00 Add Applicative instance for (GenRnM a) - - - - - e4373060 by Simon Hengel at 2012-05-26T19:21:33+02:00 Use a map for warnings, as suggested by @waern - - - - - 597a68c7 by Simon Hengel at 2012-05-27T08:48:24+02:00 Add an optional label to URLs - - - - - ef1ac7fe by Simon Hengel at 2012-05-27T08:48:24+02:00 Add support for hyperlink labels to parser - - - - - 41f2adce by Simon Hengel at 2012-05-27T08:48:24+02:00 Add golden test for hyperlinks - - - - - 83d5e764 by Simon Hengel at 2012-05-27T08:50:02+02:00 Use LANGUAGE pragmas instead of default-extensions in cabal file - - - - - ddb755e5 by Simon Hengel at 2012-05-27T08:50:02+02:00 Fix typo in comment - - - - - 110676b4 by Simon Hengel at 2012-05-27T08:50:02+02:00 Add a type signature for a where-binding - - - - - 7d9ba2a0 by Ian Lynagh at 2012-06-12T14:38:01+01:00 Follow changes in GHC - - - - - 47c704f2 by Ian Lynagh at 2012-06-12T18:52:16+01:00 Follow changes in GHC - - - - - e1efe1ab by Simon Peyton Jones at 2012-06-13T17:25:29+01:00 Follow changes for the implementation of implicit parameters - - - - - 69abc81c by Ian Lynagh at 2012-06-19T22:52:58+01:00 Follow changes in base - - - - - 9d074a21 by Paolo Capriotti at 2012-06-22T18:26:47+01:00 Use right docMap to get decl documentation. - - - - - e3292ef6 by Ian Lynagh at 2012-07-15T01:31:19+01:00 Follow changes in GHC - - - - - ceae56b0 by Ian Lynagh at 2012-07-16T21:22:48+01:00 Fix haddock following some GHC changes Passing _|_ as the Settings for defaultDynFlags no longer works well enough - - - - - 9df72735 by Paolo Capriotti at 2012-07-19T16:49:32+01:00 Forward port changes from stable. - - - - - 572f5fcf by Ian Lynagh at 2012-07-19T20:38:26+01:00 Merge branch 'master' of darcs.haskell.org:/srv/darcs//haddock - - - - - 9195aca4 by Paolo Capriotti at 2012-07-20T10:27:28+01:00 Update dependencies. - - - - - 33db3923 by Ian Lynagh at 2012-07-20T17:54:43+01:00 Build with GHC 7.7 - - - - - 925a2cea by David Waern at 2012-07-23T16:50:40+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.6 Conflicts: src/Haddock/InterfaceFile.hs - - - - - d710ef97 by David Waern at 2012-07-23T16:52:07+02:00 Bump version number. - - - - - eb0c2f83 by David Waern at 2012-07-23T16:57:58+02:00 Update CHANGES. - - - - - b3f56943 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Hide "internal" instances This fixes haskell/haddock#37 (http://trac.haskell.org/haddock/ticket/37) Precisely, we show an instance iff its class and all the types are exported by non-hidden modules. - - - - - a70aa412 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Tests for hiding instances (#37) - - - - - c0f4aa58 by Simon Hengel at 2012-07-27T13:00:13+03:00 Add an other test for hiding instances (#37) - - - - - a7ed6268 by Ian Lynagh at 2012-08-07T14:48:13+01:00 Follow changes in GHC - - - - - 0ab30d38 by Ian Lynagh at 2012-08-13T22:12:27+01:00 Improve haddock memory usage - - - - - 0eaa4e30 by Ian Lynagh at 2012-08-13T23:58:46+01:00 Improve haddock memory usage - - - - - 659d26cf by Ian Lynagh at 2012-08-14T13:16:48+01:00 Remove some temporary pragmas I accidentally recorded - - - - - d97fceb6 by Simon Hengel at 2012-08-25T13:19:34+02:00 Add missing dependency to library - - - - - 4c910697 by Simon Hengel at 2012-08-28T07:39:14+02:00 Move .ghci to project root - - - - - fc3c601a by Simon Hengel at 2012-08-28T07:39:14+02:00 accept.hs: Ignore some files - - - - - 1af9b984 by Simon Hengel at 2012-08-28T07:40:04+02:00 Update reference renderings (bump version) - - - - - 980dc253 by Simon Hengel at 2012-08-28T07:40:32+02:00 Update reference renderings (remove links for ()) - - - - - 33651dbf by Simon Hengel at 2012-08-28T07:41:50+02:00 Update documentation of `runInteractiveProcess` in reference rendering - - - - - 7ab25078 by David Waern at 2012-09-07T10:38:50+02:00 Merge branch 'hiddenInstances2' of http://github.com/feuerbach/haddock into ghc-7.6 - - - - - c3de3a4b by David Waern at 2012-09-07T14:29:27+02:00 Follow changes in GHC. - - - - - 298c43ac by David Waern at 2012-09-07T14:59:24+02:00 Update CHANGES. - - - - - e797993a by David Waern at 2012-09-07T15:21:30+02:00 Update ANNOUNCE. - - - - - d0b44790 by David Waern at 2012-09-07T15:22:43+02:00 Merge branch 'hidden-instances' into ghc-7.6 - - - - - 41a4adc8 by Simon Hengel at 2012-09-08T12:08:37+02:00 Update doc/README - - - - - 71ad1040 by Simon Hengel at 2012-09-08T12:17:17+02:00 Add documentation for URL labels - - - - - 9bb41afd by Simon Peyton Jones at 2012-09-20T18:14:26+01:00 Follow data type changes in the tc-untouchables branch Relating entirely to SynTyConRhs - - - - - b8139bfa by Simon Hengel at 2012-09-21T14:24:16+02:00 Disable Unicode test for now - - - - - a5fafdd7 by Simon Hengel at 2012-09-21T14:35:45+02:00 Update TypeOperators test for GHC 7.6.1 Type operators can't be used as type variables anymore! - - - - - 6ccf0025 by Simon Hengel at 2012-09-21T16:02:24+02:00 Remove (Monad (Either e)) instance from ref. rendering of CrossPackageDocs I do not really understand why the behavior changed, so I'll open a ticket, so that we can further investigate. - - - - - b5c6c138 by Ian Lynagh at 2012-09-27T02:00:57+01:00 Follow changes in GHC build system - - - - - b98eded0 by David Waern at 2012-09-27T15:37:02+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 76cc2051 by David Waern at 2012-09-27T15:48:19+02:00 Update hidden instances tests. - - - - - aeaa1c59 by David Waern at 2012-09-28T10:21:32+02:00 Make API buildable with GHC 7.6. - - - - - d76be1b0 by Simon Peyton Jones at 2012-09-28T15:57:05+01:00 Merge remote-tracking branch 'origin/master' into tc-untouchables - - - - - a1922af8 by David Waern at 2012-09-28T19:50:20+02:00 Fix spurious superclass constraints bug. - - - - - bc41bdbb by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove old examples - - - - - bed7d3dd by Simon Hengel at 2012-10-01T11:30:51+02:00 Adapt parsetests for GHC 7.6.1 - - - - - dcdb22bb by Simon Hengel at 2012-10-01T11:30:51+02:00 Add test-suite section for parsetests to cabal file + get rid of HUnit dependency - - - - - 1e5263c9 by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove test flag from cabal file This was not really used. - - - - - 4beee98b by David Waern at 2012-09-28T23:42:28+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 11dd2256 by Ian Lynagh at 2012-10-03T16:17:35+01:00 Follow change in GHC build system - - - - - fbd77962 by Simon Hengel at 2012-10-03T18:49:40+02:00 Remove redundant dependency from cabal file - - - - - 09218989 by Simon Hengel at 2012-10-04T16:03:05+02:00 Fix typo - - - - - 93a2d5f9 by Simon Hengel at 2012-10-04T16:11:41+02:00 Remove trailing whitespace from cabal file - - - - - c8b46cd3 by Simon Hengel at 2012-10-04T16:12:17+02:00 Export Haddock's main entry point from library - - - - - b411e77b by Simon Hengel at 2012-10-04T16:29:46+02:00 Depend on library for executable The main motivation for this is to increase build speed. In GHC's source tree the library is not build, but all modules are now required for the executable, so that GHC's validate will now detect build failures for the library. - - - - - f8f0979f by Simon Hengel at 2012-10-05T00:32:57+02:00 Set executable flag for Setup.lhs - - - - - dd045998 by Simon Hengel at 2012-10-07T16:44:06+02:00 Extend rather than set environment when running HTML tests On some platforms (e.g. ppc64) GHC requires gcc in the path. - - - - - 7b39c3ae by Simon Hengel at 2012-10-07T17:05:45+02:00 cross-package test: re-export IsString instead of Monad There is a monad instance for Q, which is not available on platforms that do not have GHCi support. This caused CrossPackageDocs to fail on those platforms. Re-exporting IsString should test the same thing, but it works on all platforms. - - - - - 0700c605 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Fix some warnings - - - - - f78eca79 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Make -Wall proof - - - - - 6beec041 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Use listToMaybe/fromMaybe instead of safeHead/maybe - - - - - 44b8ce86 by Ian Lynagh at 2012-10-08T21:59:46+01:00 Follow changes in GHC - - - - - 6da5f702 by Simon Hengel at 2012-10-09T11:16:19+02:00 Update .ghci - - - - - 9ac1a1b9 by Kazu Yamamoto at 2012-10-09T12:45:31+02:00 Add markup support for properties - - - - - 1944cb42 by Simon Hengel at 2012-10-09T12:45:31+02:00 Simplify lexing/parsing of properties In contrast to what we do for examples, we do not really need to capture the "prompt" here. - - - - - bffd8e62 by Simon Hengel at 2012-10-09T13:40:14+02:00 Add HTML test for properties - - - - - 2fe9c5cb by Simon Hengel at 2012-10-09T13:40:21+02:00 Add unit tests for properties - - - - - 874e361b by Simon Hengel at 2012-10-09T13:40:33+02:00 Bump interface version - - - - - 2506cc37 by Simon Hengel at 2012-10-09T15:15:04+02:00 Fix parser bug - - - - - 743d2b7d by Simon Hengel at 2012-10-09T15:31:06+02:00 Allow to load interface files with compatible versions - - - - - 981a1660 by Simon Hengel at 2012-10-10T10:32:05+02:00 Export more types from Documentation.Haddock (fixes haskell/haddock#216) - - - - - dff7dc76 by Simon Hengel at 2012-10-10T11:15:19+02:00 Update ANNOUNCE and CHANGES - - - - - edd2bb01 by Simon Hengel at 2012-10-10T11:22:50+02:00 Bump version - - - - - 5039163b by Simon Hengel at 2012-10-10T13:56:04+02:00 Fix typo in documentation - - - - - e4ce34da by Simon Hengel at 2012-10-10T14:28:35+02:00 Add documentation for properties - - - - - 9555ebca by Simon Hengel at 2012-10-11T10:49:04+02:00 Remove redundant if-defs, more source documentation - - - - - 87aa67e1 by Simon Hengel at 2012-10-11T12:32:51+02:00 Adapt cabal file - - - - - c44c1dee by Simon Hengel at 2012-10-11T12:41:58+02:00 Require ghc 7.6 - - - - - 8383bc34 by Simon Hengel at 2012-10-11T12:50:24+02:00 Bump version - - - - - 1030eb38 by Simon Hengel at 2012-10-11T12:55:44+02:00 Update ANNOUNCE and CHANGES - - - - - 74955088 by Simon Hengel at 2012-10-12T09:49:31+02:00 Improve note about `binaryInterfaceVersion` (thanks David) - - - - - ee30f6b7 by Simon Hengel at 2012-10-13T13:40:59+02:00 Update version in html tests, rpm spec file, and user manual - - - - - f2861f18 by Simon Hengel at 2012-10-13T14:40:33+02:00 Remove unused MonadFix constraint - - - - - dfdf1a74 by Simon Hengel at 2012-10-13T15:15:38+02:00 Minor code simplification - - - - - 4ecd1e70 by Simon Hengel at 2012-10-13T15:33:43+02:00 Increase code locality - - - - - f7df5cc9 by Simon Hengel at 2012-10-13T16:03:12+02:00 Minor code simplification - - - - - e737eb6e by Simon Hengel at 2012-10-13T19:03:04+02:00 Handle HsExplicitListTy in renameer (fixes haskell/haddock#213) - - - - - c2dc8f17 by Simon Hengel at 2012-10-13T20:46:31+02:00 Better error messages - - - - - 14d48b4c by Simon Hengel at 2012-10-14T00:21:07+02:00 Simplify RnM type - - - - - 6c2cc547 by Simon Hengel at 2012-10-14T00:23:35+02:00 Simplify lookupRn - - - - - bc77ce85 by Simon Hengel at 2012-10-14T01:51:32+02:00 Organize unite tests hierarchically - - - - - 2306d117 by Simon Hengel at 2012-10-14T10:34:58+02:00 Handle more cases in renameType - - - - - 8a864203 by Simon Hengel at 2012-10-14T11:47:59+02:00 Add mini_HiddenInstances.html.ref and mini_HiddenInstancesB.html.ref - - - - - 3a978eca by Simon Hengel at 2012-10-14T11:49:28+02:00 Add /tests/html-tests/output/ to .gitignore - - - - - db18888a by Simon Hengel at 2012-10-14T13:38:21+02:00 Allow haddock markup in deprecation messages - - - - - e7cfee9f by Simon Hengel at 2012-10-14T14:00:23+02:00 If parsing of deprecation message fails, include it verbatim - - - - - 242a85be by Simon Hengel at 2012-10-14T14:13:24+02:00 Add description for PruneWithWarning test - - - - - 43d33df1 by Simon Hengel at 2012-10-14T15:40:53+02:00 Minor formatting change - - - - - 22768c44 by Simon Hengel at 2012-10-14T16:03:43+02:00 Properly handle deprecation messages for re-exported things (fixes haskell/haddock#220) - - - - - cb4b9111 by Simon Hengel at 2012-10-14T17:30:28+02:00 Add build artifacts for documentation to .gitignore - - - - - 854cd8de by Simon Hengel at 2012-10-14T23:34:51+02:00 unit-tests: Improve readability Add IsString instance for (Doc RdrName) + use <> instead of DocAppend. - - - - - c4446d54 by Simon Hengel at 2012-10-14T23:37:21+02:00 unit-tests: Minor refactoring Rename parse to parseParas. - - - - - 04f2703c by Simon Hengel at 2012-10-15T00:36:42+02:00 Fix typo - - - - - 3d109e44 by Simon Hengel at 2012-10-15T10:30:07+02:00 Add description for DeprecatedReExport test - - - - - 84f0985c by Simon Hengel at 2012-10-15T14:54:19+02:00 Move resources to /resources directory - - - - - a5de7ca6 by Simon Hengel at 2012-10-15T15:46:18+02:00 Move HTML tests to directory /html-test/ - - - - - e21f727d by Simon Hengel at 2012-10-15T19:32:42+02:00 Move HTML reference renderings to /html-test/ref/ - - - - - 3a3c6c75 by Simon Hengel at 2012-10-15T19:32:42+02:00 Copy css, images, etc. on accept - - - - - 40ead6dc by Simon Hengel at 2012-10-15T19:32:42+02:00 Move unit tests to /test directory - - - - - 99a28231 by Simon Hengel at 2012-10-15T19:32:42+02:00 Fix Setup.lhs /usr/bin/runhaskell is not installed on all systems. - - - - - 95faf45e by Simon Hengel at 2012-10-15T19:32:42+02:00 Make test management scripts more robust * They are now independent from the current directory, and hence can be called from everywhere * On UNIX/Linux they can now be run as scripts - - - - - 027aaa2d by Simon Hengel at 2012-10-15T19:53:40+02:00 Add 'dev' flag to cabal file, that builds without -O2 That way --disable-optimization can be used, which decreases build time considerably. - - - - - e0266ede by Simon Hengel at 2012-10-15T20:03:43+02:00 Add test case for "spurious superclass constraints bug" - - - - - 52a2aa92 by Simon Hengel at 2012-10-15T20:28:55+02:00 Adapt accept.lhs, so that it ignores more index files - - - - - 53530781 by Simon Hengel at 2012-10-15T20:49:39+02:00 Rename html-test/runtests.lhs to html-test/run.lhs - - - - - 84518797 by Simon Hengel at 2012-10-15T20:49:39+02:00 Move source files for HTML tests to html-test/src - - - - - a911dc6c by Simon Hengel at 2012-10-15T20:49:39+02:00 Adapt output directory for HTML tests - - - - - d3c15857 by Ian Lynagh at 2012-10-16T16:54:43+01:00 Follow dopt->gopt rename - - - - - 956665a5 by Simon Hengel at 2012-10-18T08:42:48+02:00 Update html-test/README - - - - - 903b1029 by Simon Hengel at 2012-10-18T08:50:26+02:00 Use markdown for html-test/README - - - - - 150b4d63 by Ian Lynagh at 2012-10-18T16:36:00+01:00 Follow changes in GHC: 'flags' has been renamed 'generalFlags' - - - - - 41e04ff9 by Simon Hengel at 2012-11-28T09:54:35+01:00 Export missing types from Documentation.Haddock - - - - - 9be59237 by Ian Lynagh at 2012-11-30T23:20:47+00:00 Update dependencies - - - - - e06842f5 by Simon Hengel at 2012-12-07T20:58:05+01:00 Bump version - - - - - e3dbede0 by Simon Hengel at 2012-12-07T20:58:05+01:00 Add missing test files to cabal file (fixes haskell/haddock#230) - - - - - ee0dcca7 by Simon Hengel at 2012-12-07T20:58:05+01:00 Update CHANGES - - - - - 51601bdb by Simon Peyton Jones at 2012-12-19T17:28:35+00:00 Track changes in UNPACK pragma stuff - - - - - f2573bc1 by Richard Eisenberg at 2012-12-21T20:56:25-05:00 Implement overlapping type family instances. An ordered, overlapping type family instance is introduced by 'type instance where', followed by equations. See the new section in the user manual (7.7.2.2) for details. The canonical example is Boolean equality at the type level: type family Equals (a :: k) (b :: k) :: Bool type instance where Equals a a = True Equals a b = False A branched family instance, such as this one, checks its equations in order and applies only the first the matches. As explained in the note [Instance checking within groups] in FamInstEnv.lhs, we must be careful not to simplify, say, (Equals Int b) to False, because b might later unify with Int. This commit includes all of the commits on the overlapping-tyfams branch. SPJ requested that I combine all my commits over the past several months into one monolithic commit. The following GHC repos are affected: ghc, testsuite, utils/haddock, libraries/template-haskell, and libraries/dph. Here are some details for the interested: - The definition of CoAxiom has been moved from TyCon.lhs to a new file CoAxiom.lhs. I made this decision because of the number of definitions necessary to support BranchList. - BranchList is a GADT whose type tracks whether it is a singleton list or not-necessarily-a-singleton-list. The reason I introduced this type is to increase static checking of places where GHC code assumes that a FamInst or CoAxiom is indeed a singleton. This assumption takes place roughly 10 times throughout the code. I was worried that a future change to GHC would invalidate the assumption, and GHC might subtly fail to do the right thing. By explicitly labeling CoAxioms and FamInsts as being Unbranched (singleton) or Branched (not-necessarily-singleton), we make this assumption explicit and checkable. Furthermore, to enforce the accuracy of this label, the list of branches of a CoAxiom or FamInst is stored using a BranchList, whose constructors constrain its type index appropriately. I think that the decision to use BranchList is probably the most controversial decision I made from a code design point of view. Although I provide conversions to/from ordinary lists, it is more efficient to use the brList... functions provided in CoAxiom than always to convert. The use of these functions does not wander far from the core CoAxiom/FamInst logic. BranchLists are motivated and explained in the note [Branched axioms] in CoAxiom.lhs. - The CoAxiom type has changed significantly. You can see the new type in CoAxiom.lhs. It uses a CoAxBranch type to track branches of the CoAxiom. Correspondingly various functions producing and consuming CoAxioms had to change, including the binary layout of interface files. - To get branched axioms to work correctly, it is important to have a notion of type "apartness": two types are apart if they cannot unify, and no substitution of variables can ever get them to unify, even after type family simplification. (This is different than the normal failure to unify because of the type family bit.) This notion in encoded in tcApartTys, in Unify.lhs. Because apartness is finer-grained than unification, the tcUnifyTys now calls tcApartTys. - CoreLinting axioms has been updated, both to reflect the new form of CoAxiom and to enforce the apartness rules of branch application. The formalization of the new rules is in docs/core-spec/core-spec.pdf. - The FamInst type (in types/FamInstEnv.lhs) has changed significantly, paralleling the changes to CoAxiom. Of course, this forced minor changes in many files. - There are several new Notes in FamInstEnv.lhs, including one discussing confluent overlap and why we're not doing it. - lookupFamInstEnv, lookupFamInstEnvConflicts, and lookup_fam_inst_env' (the function that actually does the work) have all been more-or-less completely rewritten. There is a Note [lookup_fam_inst_env' implementation] describing the implementation. One of the changes that affects other files is to change the type of matches from a pair of (FamInst, [Type]) to a new datatype (which now includes the index of the matching branch). This seemed a better design. - The TySynInstD constructor in Template Haskell was updated to use the new datatype TySynEqn. I also bumped the TH version number, requiring changes to DPH cabal files. (That's why the DPH repo has an overlapping-tyfams branch.) - As SPJ requested, I refactored some of the code in HsDecls: * splitting up TyDecl into SynDecl and DataDecl, correspondingly changing HsTyDefn to HsDataDefn (with only one constructor) * splitting FamInstD into TyFamInstD and DataFamInstD and splitting FamInstDecl into DataFamInstDecl and TyFamInstDecl * making the ClsInstD take a ClsInstDecl, for parallelism with InstDecl's other constructors * changing constructor TyFamily into FamDecl * creating a FamilyDecl type that stores the details for a family declaration; this is useful because FamilyDecls can appear in classes but other decls cannot * restricting the associated types and associated type defaults for a * class to be the new, more restrictive types * splitting cid_fam_insts into cid_tyfam_insts and cid_datafam_insts, according to the new types * perhaps one or two more that I'm overlooking None of these changes has far-reaching implications. - The user manual, section 7.7.2.2, is updated to describe the new type family instances. - - - - - f788d0fb by Simon Peyton Jones at 2012-12-23T15:49:58+00:00 Track changes in HsBang - - - - - ca460a0c by Simon Peyton Jones at 2012-12-23T15:50:28+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - f078fea6 by Simon Peyton Jones at 2013-01-02T08:33:13+00:00 Use InstEnv.instanceSig rather than instanceHead (name change) - - - - - 88e41305 by Simon Peyton Jones at 2013-01-14T17:10:27+00:00 Track change to HsBang type - - - - - e1ad4e19 by Kazu Yamamoto at 2013-02-01T11:59:24+09:00 Merge branch 'ghc-7.6' into ghc-7.6-merge-2 Conflicts: haddock.cabal src/Haddock/Interface/AttachInstances.hs src/Haddock/Interface/Create.hs src/Haddock/Interface/LexParseRn.hs src/Haddock/InterfaceFile.hs src/Haddock/Types.hs Only GHC HEAD can compile this. GHC 7.6.x cannot compile this. Some test fail. - - - - - 62bec012 by Kazu Yamamoto at 2013-02-06T11:12:28+09:00 Using tcSplitSigmaTy in instanceHead' (FIXME is resolved.) - - - - - 013fd2e4 by Kazu Yamamoto at 2013-02-06T17:56:21+09:00 Refactoring instanceHead'. - - - - - 3148ce0e by Kazu Yamamoto at 2013-02-07T17:45:10+09:00 Using new syntax in html-test/src/GADTRecords.hs. - - - - - 626dabe7 by Gabor Greif at 2013-02-15T22:42:01+01:00 Typo - - - - - 1eb667ae by Ian Lynagh at 2013-02-16T17:02:07+00:00 Follow changes in base - - - - - 3ef8253a by Ian Lynagh at 2013-03-01T23:23:57+00:00 Follow changes in GHC's build system - - - - - 1a265a3c by Ian Lynagh at 2013-03-03T23:12:07+00:00 Follow changes in GHC build system - - - - - 69941c79 by Max Bolingbroke at 2013-03-10T09:38:28-07:00 Use Alex 3's Unicode support to properly lex source files as UTF-8 Signed-off-by: David Waern <david.waern at gmail.com> - - - - - ea687dad by Simon Peyton Jones at 2013-03-15T14:16:10+00:00 Adapt to tcRnGetInfo returning family instances too This API change was part of the fix to Trac haskell/haddock#4175. But it offers new information to Haddock: the type-family instances, as well as the class instances, of this type. This patch just drops the new information on the floor, but there's an open opportunity to use it in the information that Haddock displays. - - - - - 971a30b0 by Andreas Voellmy at 2013-05-19T20:47:39+01:00 Fix for haskell/haddock#7879. Changed copy of utils/haddock/html/resources/html to use "cp -RL" rather than "cp -R". This allows users to run validate in a build tree, where the build tree was setup using lndir with a relative path to the source directory. - - - - - 31fb7694 by Ian Lynagh at 2013-05-19T20:47:49+01:00 Use "cp -L" when making $(INPLACE_LIB)/latex too - - - - - e9952233 by Simon Hengel at 2013-06-01T18:06:50+02:00 Add -itest to .ghci - - - - - b06873b3 by Mateusz Kowalczyk at 2013-06-01T18:06:50+02:00 Workaround for a failing build with --enable-tests. - - - - - e7858d16 by Simon Hengel at 2013-06-01T19:29:28+02:00 Fix broken test - - - - - 0690acb1 by Richard Eisenberg at 2013-06-21T14:08:25+01:00 Updates to reflect changes in HsDecls to support closed type families. - - - - - 7fd347ec by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 53ed81b6 by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 931c4f4f by Richard Eisenberg at 2013-07-24T13:15:59+01:00 Remove (error "synifyKind") to use WithinType, to allow haddock to process base. - - - - - 55a9c804 by Richard Eisenberg at 2013-08-02T15:54:55+01:00 Changes to reflect changes in GHC's type HsTyVarBndr - - - - - b6e9226c by Mathieu Boespflug at 2013-08-04T10:39:43-07:00 Output Copright and License keys in Xhtml backend. This information is as relevant in the documentation as it is in the source files themselves. Signed-off-by: David Waern <david.waern at gmail.com> - - - - - 4c66028a by David Waern at 2013-08-04T15:27:36-07:00 Bump interface file version. - - - - - 67340163 by David Waern at 2013-08-09T16:12:51-07:00 Update tests. - - - - - 2087569b by Mateusz Kowalczyk at 2013-08-25T09:24:13+02:00 Add spec tests. This adds tests for all elements we can create during regular parsing. This also adds tests for text with unicode in it. - - - - - 97f36a11 by Mateusz Kowalczyk at 2013-08-27T06:59:12+01:00 Fix ticket haskell/haddock#247. I do the same thing that the XHTML backend does: give these no special treatment and just act as if they are regular functions. - - - - - 60681b4f by Mateusz Kowalczyk at 2013-08-27T21:22:48+02:00 LaTeX tests setup - - - - - fa4c27b2 by Mateusz Kowalczyk at 2013-09-02T23:21:43+01:00 Fixes haskell/haddock#253 - - - - - 1a202490 by Mateusz Kowalczyk at 2013-09-03T01:12:50+01:00 Use Hspec instead of nanospec This is motivated by the fact that Haddock tests are not ran by the GHC's ‘validate’ script so we're pretty liberal on dependencies in that area. Full Hspec gives us some nice features such as Quickcheck integration. - - - - - 8cde3b20 by David Luposchainsky at 2013-09-08T07:27:28-05:00 Fix AMP warnings Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - d10661f2 by Herbert Valerio Riedel at 2013-09-11T15:15:01+02:00 Update Git repo URL in `.cabal` file - - - - - 16a44eb5 by Richard Eisenberg at 2013-09-17T09:34:26-04:00 Revision to reflect new role annotation syntax in GHC. - - - - - 4b9833b9 by Herbert Valerio Riedel at 2013-09-18T10:15:28+02:00 Add missing `traverse` method for `GenLocated` As `Traversable` needs at least one of `traverse` or `sequenceA` to be overridden. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - b71fed5d by Simon Hengel at 2013-09-18T22:43:34+02:00 Add test helper - - - - - 4fc1ea86 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#231 - - - - - 435872f6 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#256 We inject -dynamic-too into flags before we run all our actions in the GHC monad. - - - - - b8b24abb by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Add new field to DynFlags - - - - - 49558795 by Simon Hengel at 2013-09-18T22:43:35+02:00 Fallback to ./resources when Cabal data is not found (so that themes are found during development) - - - - - bf79d05c by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Fixes haskell/haddock#5 - - - - - e1baebc2 by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Print missing documentation. Fixes haskell/haddock#258. - - - - - 02ea74de by Austin Seipp at 2013-10-09T10:52:22-05:00 Don't consider StaticFlags when parsing arguments. Instead, discard any static flags before parsing the command line using GHC's DynFlags parser. See http://ghc.haskell.org/trac/ghc/ticket/8276 Based off a patch from Simon Hengel. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 704fd5bb by Simon Hengel at 2013-11-09T00:15:13+01:00 Update HTML tests - - - - - f9fed49e by Simon Hengel at 2013-11-10T18:43:58+01:00 Bump version - - - - - 97ae1999 by Simon Peyton Jones at 2013-11-25T17:25:14+00:00 Track changes in HsSpliceTy data constructor - - - - - 59ad8268 by Simon Peyton Jones at 2014-01-10T18:17:43+00:00 Adapt to small change in Pretty's exports - - - - - 8b12e6aa by Simon Hengel at 2014-01-12T14:48:35-06:00 Some code simplification by using traverse - - - - - fc5ea9a2 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix warnings in test helper - - - - - 6dbb3ba5 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Add ByteString version of Attoparsec - - - - - 968d7774 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 One pass parser and tests. We remove the HTML test as it is no longer necessary. We cover the test case in spec tests and other HTML tests but keeping this around fails: this is because the new parser has different semantics there. In fact, I suspect the original behaviour was a bug that wasn't caught/fixed but simply included as-is during the testing. - - - - - 37a07c9c by Simon Hengel at 2014-01-12T14:48:35-06:00 Rename Haddock.ParseSpec to Haddock.ParserSpec - - - - - f0f68fe9 by Simon Hengel at 2014-01-12T14:48:35-06:00 Don't append newline to parseString input We also check that we have parsed everything with endOfInput. - - - - - 95d60093 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix totality, unicode, examples, paragraph parsing Also simplify specs and parsers while we're at it. Some parsers were made more generic. This commit is a part of GHC pre-merge squash, email fuuzetsu at fuuzetsu.co.uk if you need the full commit history. - - - - - 7d99108c by Simon Hengel at 2014-01-12T14:48:35-06:00 Update acceptance tests - - - - - d1b59640 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Support for bold. Conflicts: src/Haddock/Backends/Hoogle.hs src/Haddock/Interface/Rename.hs src/Haddock/Parser.hs - - - - - 4b412b39 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Allow for headings inside function documentation. LaTeX will treat the h3-h6 headings the same as we'd have to hack the style file heavily otherwise and it would make the headings tiny anyway. Hoogle upstream said they will put in the functionality on their end. Conflicts: src/Haddock/Interface/Rename.hs src/Haddock/Types.hs test/Haddock/ParserSpec.hs - - - - - fdcca428 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Per-module extension flags and language listing. Any extensions that are not enabled by a used language (Haskell2010 &c) will be shown. Furthermore, any implicitly enabled are also going to be shown. While we could eliminate this either by using the GHC API or a dirty hack, I opted not to: if a user doesn't want the implied flags to show, they are recommended to use enable extensions more carefully or individually. Perhaps this will encourage users to not enable the most powerful flags needlessly. Enabled with show-extensions. Conflicts: src/Haddock/InterfaceFile.hs - - - - - 368942a2 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Bump interface version There were some breaking changes over the last few patches so we bump the interface version. This causes a big problem with testing: 1. To generate cross package docs, we first need to generate docs for the package used. 2. To generate package docs with new interface version, we need to use Haddock which has the version bumped. 3. To get Haddock with the version bump, we first need to test cross package docs 4. GOTO 1 So the problem is the chicken and the egg problem. It seems that the only solution would be to generate some interface files on the fly but it is non-trivial. To run this test, you'll have to: * build Haddock without the test (make sure everything else passes) * rebuild the packages used in the test with your shiny new binary making sure they are visible to Haddock * remove the ‘_hidden’ suffix and re-run the tests Note: because the packages currently used for this test are those provided by GHC, it's probably non-trivial to just re-build them. Preferably something less tedious to rebuild should be used and something that is not subject to change. - - - - - 124ae7a9 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow for nesting of paragraphs under lists. The nesting rules are similar to Markdown's with the exception that we can not simply indent the first line of a hard wrapped indented paragraph and have it treated as if it was fully indented. The reason is differences in markup as some of our constructs care about whitespace while others just swallow everything up so it's just a lot easier to not bother with it rather than making arbitrary rules. Note that we now drop trailing for string entities inside of lists. They weren't needed and it makes the output look uniform whether we use a single or double newline between list elements. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - c7913535 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow escaping in URLs and pictures. Some tests were moved under parseString as they weren't about paragraph level markup. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - 32326680 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update documentation. - - - - - fbef6406 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update maintainer - - - - - b40e82f4 by Mateusz Kowalczyk at 2014-01-13T02:39:25-06:00 Fixes haskell/haddock#271 Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - f4eafbf8 by Gergő Érdi at 2014-01-19T15:35:16-06:00 Support for -XPatternSynonyms Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - a8939591 by Austin Seipp at 2014-01-29T08:09:04-06:00 Update CPP check for __GLASGOW_HASKELL__ Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 30d7e9d5 by Gergő Érdi at 2014-01-31T00:15:01+08:00 <+>: Don't insert a space when concatenating empty nodes - - - - - a25ccd4d by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Fix @ code blocks In cases where we had some horizontal space before the closing ‘@’, the parser would not accept the block as a code block and we'd get ugly output. - - - - - 0f67305a by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Update tests This updates tests due to Haddock Trac haskell/haddock#271 fix and due to removal of TypeHoles as an extension from GHC. - - - - - 157322a7 by Gergő Érdi at 2014-01-31T01:03:17+08:00 Handle infix vs prefix names correctly everywhere, by explicitly specifying the context The basic idea is that "a" and "+" are either pretty-printed as "a" and "(+)" or "`a`" and "+" - - - - - aa6d9685 by Mateusz Kowalczyk at 2014-01-30T17:21:50+00:00 Correct whitespace in ‘hidden’ test for <+> change - - - - - 121872f0 by Mateusz Kowalczyk at 2014-02-09T17:59:12+00:00 Document module header. Fixes Haddock Trac haskell/haddock#270. - - - - - e3253746 by Mateusz Kowalczyk at 2014-02-10T21:37:48+00:00 Insert a space between module link and description Fixes Haddock Trac haskell/haddock#277. - - - - - 771d2384 by Mateusz Kowalczyk at 2014-02-10T23:27:21+00:00 Ensure a space between type signature and ‘Source’ This is briefly related to Haddock Trac haskell/haddock#249 and employs effectively the suggested fix _but_ it doesn't actually fix the reported issue. This commit simply makes copying the full line a bit less of a pain. - - - - - 8cda9eff by nand at 2014-02-11T15:48:30+00:00 Add support for type/data families This adds support for type/data families with their respective instances, as well as closed type families and associated type/data families. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 3f22c510 by nand at 2014-02-11T15:53:50+00:00 Improve display of poly-kinded type operators This now displays them as (==) k a b c ... to mirror GHC's behavior, instead of the old (k == a) b c ... which was just wrong. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - effb2d6b by nand at 2014-02-11T15:56:50+00:00 Add test case for PatternSynonyms This just tests various stuff including poly-kinded patterns and operator patterns to make sure the rendering isn't broken. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - b38faf0d by Niklas Haas at 2014-02-13T21:53:32+00:00 Get rid of re-implementation of sortBy I have no idea what this was doing lying around here, and due to the usage of tuples it's actually slower, too. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - ac1e0413 by Mateusz Kowalczyk at 2014-02-13T23:57:16+00:00 Only warn about missing docs when docs are missing This fixes the ‘Missing documentation for…’ message for modules with 100% coverage. - - - - - cae2e36a by Niklas Haas at 2014-02-15T21:56:18+00:00 Add test case for inter-module type/data family instances These should show up in every place where the class is visible, and indeed they do right now. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 8bea5c3a by Mateusz Kowalczyk at 2014-02-19T05:11:34+00:00 Use a bespoke data type to indicate fixity This deals with what I imagine was an ancient TODO and makes it much clearer what the argument actually does rather than having the user chase down the comment. - - - - - 5b52d57c by Niklas Haas at 2014-02-22T21:31:03+01:00 Strip a single leading space from bird tracks (#201) This makes bird tracks in the form > foo > bar > bat parse as if they had been written as >foo >bar >bat ie. without the leading whitespace in front of every line. Ideally we also want to look into how leading whitespace affects code blocks written using the @ @ syntax, which are currently unaffected by this patch. - - - - - 5a1315a5 by Simon Hengel at 2014-02-22T21:55:35+01:00 Turn a source code comment into specs - - - - - 784cfe58 by Mateusz Kowalczyk at 2014-02-23T05:02:22+00:00 Update test case for lifted GADT type rendering The parsing of these seems to have been fixed by GHC folk and it now renders differently. IMHO it now renders in a better way so I'm updating the test to reflect this. - - - - - c3c88c2f by Mateusz Kowalczyk at 2014-02-23T06:37:14+00:00 Don't shadow ‘strip’. -Wall complains - - - - - 293031d8 by Niklas Haas at 2014-02-23T15:21:52+01:00 Make ImplicitParams render correctly (#260) This introduces a new precedence level for single contexts (because implicit param contexts always need parens around them, but other types of contexts don't necessarily, even when alone) - - - - - 4200842d by Niklas Haas at 2014-02-23T15:37:13+01:00 Lower precedence of equality constraints This drops them to the new precedence pREC_CTX, which makes single eqaulity constraints show up as (a ~ b) => ty, in line with GHC's rendering. Additional tests added to make sure other type operators render as intended. Current behavior matches GHC - - - - - b59e3227 by Niklas Haas at 2014-02-23T16:11:22+01:00 Add RankNTypes test case to ImplicitParams.hs This test actually tests what haskell/haddock#260 originally reported - I omitted the RankNTypes scenario from the original fix because I realized it's not relevant to the underlying issue and indeed, this renders as intended now. Still good to have more tests. - - - - - c373dbf7 by Mateusz Kowalczyk at 2014-02-24T06:09:54+00:00 Fix rendering of Contents when links are present Fixes Haddock Trac haskell/haddock#267. - - - - - 9ecb0e56 by Mateusz Kowalczyk at 2014-02-24T06:26:50+00:00 Fix wording in the docs - - - - - 4f4dcd8e by Mateusz Kowalczyk at 2014-02-27T03:00:33+00:00 Change rendering of duplicate record field docs See Haddock Trac haskell/haddock#195. We now change this behaviour to only rendering the documentation attached to the first instance of a duplicate field. Perhaps we could improve this by rendering the first instance that has documentation attached to it but for now, we'll stick with this. - - - - - ad8aa609 by Niklas Haas at 2014-03-08T09:43:26+01:00 Render fixity information Affects functions, type synonyms, type families, class names, data type names, constructors, data families, associated TFs/DFs, type synonyms, pattern synonyms and everything else I could think of. - - - - - 6a39c917 by Niklas Haas at 2014-03-09T07:43:39+01:00 Reorder topDeclElem to move the source/wiki links to the top They appear in the same position due to the float: right attribute but now they're always at the top of the box instead of at the bottom. - - - - - 2d34b3b4 by Niklas Haas at 2014-03-09T07:53:46+01:00 Use optLast instead of listToMaybe for sourceUrls/wikiUrls This lets you override them using eg. cabal haddock --haddock-options, which can come in handy if you want to use a different layout or URL for your source code links than cabal-install generates. - - - - - 0eff4624 by Niklas Haas at 2014-03-09T07:53:46+01:00 Differentiate between TH splices (line-links) and regular names This adds a new type of source code link, to a specific line rather than a specific declaration/name - this is used to link to the location of a TH splice that defines a certain name. Rather hefty changes throughout and still one unresolved issue (the line URLs aren't parsed from the third form of --read-interface which means they're currently restricted to same-interface links). Not sure if this issue is really worth all the hassle, especially since we could just use line links in general. This commit also contains some cleanup/clarification of the types in Haddock.Backends.Xhtml.Decl and shortens some overlong lines in the process. Notably, the Bool parameter was replaced by a Unicode type synonym to help clarify its presence in type signatures. - - - - - 66d6f77b by Niklas Haas at 2014-03-09T20:02:43+01:00 Group similar fixities together Identical fixities declared for the same line should now render using syntax like: infix 4 <, >=, >, <= - - - - - 6587f9f5 by Mateusz Kowalczyk at 2014-03-10T04:24:18+00:00 Update changelog - - - - - 7387ddad by Niklas Haas at 2014-03-11T10:26:04+01:00 Include fixity information in the Interface file This resolves fixity information not appearing across package borders. The binary file version has been increased accordingly. - - - - - ab46ef44 by Niklas Haas at 2014-03-11T10:26:04+01:00 Update changelog - - - - - 565cab6f by Niklas Haas at 2014-03-11T10:26:04+01:00 Update appearance of fixity annotations This moves them in-line with their corresponding lines, similar to a presentation envision by @hvr and described in #ghc. Redundant operator names are also omitted when no ambiguity is present. - - - - - 5d7afd67 by Niklas Haas at 2014-03-11T10:26:05+01:00 Filter family instances of hidden types Currently, this check does not extend to hidden right hand sides, although it probably should hide them in that case. - - - - - ec291b0c by Niklas Haas at 2014-03-11T10:26:05+01:00 Add documentation for --source-entity-line - - - - - 0922e581 by Niklas Haas at 2014-03-11T10:37:32+01:00 Revert "Reorder topDeclElem to move the source/wiki links to the top" This reverts commit 843c42c4179526a2ad3526e4c7d38cbf4d50001d. This change is no longer needed with the new rendering style, and it messes with copy/pasting lines. - - - - - 30618e8b by Mateusz Kowalczyk at 2014-03-11T09:41:07+00:00 Bump version to 2.15.0 - - - - - adf3f1bb by Mateusz Kowalczyk at 2014-03-11T09:41:09+00:00 Fix up some whitespace - - - - - 8905f57d by Niklas Haas at 2014-03-13T19:18:06+00:00 Hide RHS of TFs with non-exported right hand sides Not sure what to do about data families yet, since technically it would not make a lot of sense to display constructors that cannot be used by the user. - - - - - 5c44d5c2 by Niklas Haas at 2014-03-13T19:18:08+00:00 Add UnicodeSyntax alternatives for * and -> I could not find a cleaner way to do this other than checking for string equality with the given built-in types. But seeing as it's actually equivalent to string rewriting in GHC's implementation of UnicodeSyntax, it's probably fitting. - - - - - b04a63e6 by Niklas Haas at 2014-03-13T19:18:10+00:00 Display minimal complete definitions for type classes This corresponds to the new {-# MINIMAL #-} pragma present in GHC 7.8+. I also cleaned up some of the places in which ExportDecl is used to make adding fields easier in the future. Lots of test cases have been updated since they now render with minimality information. - - - - - a4a20b16 by Niklas Haas at 2014-03-13T19:18:12+00:00 Strip links from recently added html tests These were accidentally left there when the tests were originally added - - - - - d624f315 by Mateusz Kowalczyk at 2014-03-13T19:19:31+00:00 Update changelog - - - - - d27a21ac by Mateusz Kowalczyk at 2014-03-13T21:19:07+00:00 Always read in prologue files as UTF8 (#286). - - - - - 54b2fd78 by Mateusz Kowalczyk at 2014-03-13T21:28:09+00:00 Style only - - - - - fa4fe650 by Simon Hengel at 2014-03-15T09:04:18+01:00 Add Fuuzetsu maintainers field in cabal file - - - - - f83484b7 by Niklas Haas at 2014-03-15T18:20:24+00:00 Hide minimal definition for only-method classes Previously this was not covered by the All xs check since here it is not actually an All, rather a single Var n. This also adds the previously missing html-test/src/Minimal.hs. - - - - - 0099d276 by Niklas Haas at 2014-03-15T18:20:26+00:00 Fix issue haskell/haddock#281 This is a regression from the data family instances change. Data instances are now distinguished from regular lists by usage of the new class "inst", and the style has been updated to only apply to those. I've also updated the appropriate test case to test this a bit better, including GADT instances with GADT-style records. - - - - - 1f9687bd by Mateusz Kowalczyk at 2014-03-21T17:48:37+00:00 Please cabal sdist - - - - - 75542693 by Mateusz Kowalczyk at 2014-03-22T16:36:16+00:00 Drop needless --split-objs which slows us down. Involves tiny cleanup of all the dynflag bindings. Fixes haskell/haddock#292. - - - - - 31214dc3 by Herbert Valerio Riedel at 2014-03-23T18:01:01+01:00 Fix a few typos Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 0b73e638 by Mateusz Kowalczyk at 2014-03-31T05:34:36+01:00 Print kind signatures on GADTs - - - - - 2bab42f3 by Mateusz Kowalczyk at 2014-03-31T16:53:25+01:00 Add default for new PlatformConstraints field - - - - - 42647c5f by Mateusz Kowalczyk at 2014-03-31T18:29:04+01:00 Drop leading whitespace in @-style blocks. Fixes haskell/haddock#201. - - - - - 98208294 by Niklas Haas at 2014-03-31T20:09:58+02:00 Crash when exporting record selectors of data family instances This fixes bug haskell/haddock#294. This also fixes a related but never-before-mentioned bug about the display of GADT record selectors with non-polymorphic type signatures. Note: Associated data type constructors fail to show up if nothing is exported that they could be attached to. Exporting any of the data types in the instance head, or the class + data family itself, causes them to show up, but in the absence of either of these, exporting just the associated data type with the constructor itself will result in it being hidden. The only scenario I can come up that would involve this kind of situation involved OverlappingInstances, and even then it can be mitigated by just exporting the class itself, so I'm not going to solve it since the logic would most likely be very complicated. - - - - - 3832d171 by Mateusz Kowalczyk at 2014-04-01T19:07:33+01:00 Make CHANGES consistent with what's now in 2.14.2 - - - - - c386ae89 by Mateusz Kowalczyk at 2014-04-01T19:18:36+01:00 Actually bundle extra spec tests in sdist - - - - - bd57a6d3 by Mateusz Kowalczyk at 2014-04-03T21:13:48+01:00 Update test cases for GHC bug haskell/haddock#8945, Haddock haskell/haddock#188 The order of signature groups has been corrected upstream. Here we add a test case and update some existing test-cases to reflect this change. We remove grouped signature in test cases that we can (Minimal, BugDeprecated &c) so that the test is as self-contained as possible. - - - - - 708b88b1 by Mateusz Kowalczyk at 2014-04-03T21:16:07+01:00 Enforce strict GHC version in cabal file This stops people with 7.6.3 trying to install 2.15.x which clearly won't work. Unfortunately we shipped 2.14.x without realising this. - - - - - 60334f7c by Mateusz Kowalczyk at 2014-04-03T21:19:24+01:00 Initialise some new PlatformConstants fields - - - - - ea77f668 by Mateusz Kowalczyk at 2014-04-11T16:52:23+01:00 We don't actually want unicode here - - - - - 0b651cae by Mateusz Kowalczyk at 2014-04-11T18:13:30+01:00 Parse identifiers with ^ and ⋆ in them. Fixes haskell/haddock#298. - - - - - e8ad0f5f by Mateusz Kowalczyk at 2014-04-11T18:47:41+01:00 Ignore version string during HTML tests. - - - - - de489089 by Mateusz Kowalczyk at 2014-04-11T18:59:30+01:00 Update CHANGES to follow 2.14.3 - - - - - beb464a9 by Gergő Érdi at 2014-04-13T16:31:10+08:00 remove Origin flag from LHsBindsLR - - - - - cb16f07c by Herbert Valerio Riedel at 2014-04-21T17:16:50+02:00 Replace local `die` by new `System.Exit.die` Starting with GHC 7.10, System.Exit exports the new `die` which is essentially the same as Haddock.Util.die, so this commit changes Haddock.Util.die to be a simple re-export of System.Exit.die. See also https://ghc.haskell.org/trac/ghc/ticket/9016 for more details. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 9b9b23c7 by Mateusz Kowalczyk at 2014-05-03T15:40:11+02:00 Disambiguate ‘die’ in test runners. - - - - - 5d28a2b8 by Mateusz Kowalczyk at 2014-05-05T09:19:49+02:00 Prepare modules for parser split. We have to generalise the Doc (now DocH) slightly to remove the dependency on GHC-supplied type. - - - - - d3967ff3 by Mateusz Kowalczyk at 2014-05-05T11:00:41+02:00 Move parser + parser tests out to own package. We move some types out that are necessary as well and then re-export and specialise them in the core Haddock. Reason for moving out spec tests is that if we're working on the parser, we can simply work on that and we can ignore the rest of Haddock. The downside is that it's a little inconvenient if at the end of the day we want to see that everything passes. - - - - - 522a448d by Mateusz Kowalczyk at 2014-05-05T11:14:47+02:00 Move out Show and Eq instances to Types They are much more useful to the users here. - - - - - 11a6f0f2 by Mateusz Kowalczyk at 2014-05-06T13:50:31+02:00 Remove no longer necessary parser error handling. We can now drop some Maybe tests and even lets us strip an error handling monad away in a few places. - - - - - 6992c924 by Mateusz Kowalczyk at 2014-05-14T02:23:55+02:00 Please the GHC build-system. As I can not figure out how to do this properly, if we're in GHC tree, we treat the library as being the same package. If we're not in the tree, we require that the library be installed separately. - - - - - 7a8ad763 by Mateusz Kowalczyk at 2014-05-14T14:50:25+02:00 Update issue tracker URL - - - - - f616c521 by Mateusz Kowalczyk at 2014-05-14T14:53:32+02:00 Update issue tracker URL for haddock-library - - - - - 66580ded by Gergő Érdi at 2014-05-25T14:24:16+08:00 Accomodate change in PatSyn representation - - - - - 0e43b988 by Mateusz Kowalczyk at 2014-05-29T03:15:29+02:00 Revert "Accomodate change in PatSyn representation" This reverts commit 57aa591362d7c8ba21285fccd6a958629a422091. I am reverting this because I pushed it to master when it was meant to stay on a wip-branch. Sorry Gergo and everyone who had trouble due to this. - - - - - e10d7ec8 by Mateusz Kowalczyk at 2014-05-29T03:24:11+02:00 Revert "Revert "Accomodate change in PatSyn representation"" This reverts commit e110e6e70e40eed06c06676fd2e62578da01d295. Apparently as per GHC commit ac2796e6ddbd54c5762c53e2fcf29f20ea162fd5 this was actually intended. Embarrasing for me. - - - - - 5861aca9 by Mateusz Kowalczyk at 2014-06-05T19:49:27+02:00 Clear up highlighting of identifiers with ‘'’s. - - - - - d7cc420f by Simon Peyton Jones at 2014-06-06T12:41:09+01:00 Follow change in patSynSig - - - - - 938b4fd8 by Mateusz Kowalczyk at 2014-06-12T07:24:29+02:00 Slightly update the readme. Style-sheets are no longer a recent thing, dead links, old maintainers, different formats. - - - - - c7799dea by Mateusz Kowalczyk at 2014-06-18T00:05:56+02:00 Update cabal files Update repository urls, use subdir property for haddock-library and use a separate versioning scheme for haddock-library in preparation for release. - - - - - a2750b6a by Simon Hengel at 2014-06-18T11:01:18+08:00 Compatibility with older versions of base and bytestring - - - - - 009b4b03 by Simon Hengel at 2014-06-18T11:14:01+08:00 Enable travis-ci for haddock-library - - - - - 9b5862eb by Simon Hengel at 2014-06-18T11:14:01+08:00 haddock-library: Do not depend on haddock-library in test suite I think you either add src to hs-source-dirs or the library to build-depends. But doing both does not make sense (AFAICT). - - - - - fb1f3279 by Simon Hengel at 2014-06-18T11:49:05+08:00 haddock-library: Use -Wall for specs - - - - - 649340e1 by Mateusz Kowalczyk at 2014-06-18T06:58:54+02:00 Use Travis with multiple GHC versions When using HEAD, we build haddock-library directly from repository as a dependency (and thanks to --enable-tests, the tests get ran anyway). In all other cases, we manually run the tests on haddock-library only and don't test the main project. - - - - - d7eeeec2 by Mateusz Kowalczyk at 2014-06-18T07:49:04+02:00 Comment improvements + few words in cabal file - - - - - 0f8db914 by Simon Hengel at 2014-06-18T13:52:23+08:00 Use doctest to check examples in documentation - - - - - 2888a8dc by Simon Hengel at 2014-06-18T14:16:48+08:00 Remove doctest dependency (so that we can use haddock-library with doctest) - - - - - 626d5e85 by Mateusz Kowalczyk at 2014-06-18T08:41:25+02:00 Travis tweaks - - - - - 41d4f9cc by Mateusz Kowalczyk at 2014-06-18T08:58:43+02:00 Don't actually forget to install specified GHC. - - - - - c6aa512a by John MacFarlane at 2014-06-18T10:43:57-07:00 Removed reliance on LambdaCase (which breaks build with ghc 7.4). - - - - - b9b93b6f by John MacFarlane at 2014-06-18T10:54:56-07:00 Fixed haddock warnings. - - - - - a41b0ab5 by Mateusz Kowalczyk at 2014-06-19T01:20:10+02:00 Update Travis, bump version - - - - - 864bf62a by Mateusz Kowalczyk at 2014-06-25T10:36:54+02:00 Fix anchors. Closes haskell/haddock#308. - - - - - 53df91bb by Mateusz Kowalczyk at 2014-06-25T15:04:49+02:00 Drop DocParagraph from front of headers I can not remember why they were wrapped in paragraphs to begin with and it seems unnecessary now that I test it. Closes haskell/haddock#307. - - - - - 29b5f2fa by Mateusz Kowalczyk at 2014-06-25T15:17:20+02:00 Don't mangle append order for nested lists. The benefit of this is that the ‘top-level’ element of such lists is properly wrapped in <p> tags so any CSS working with these will be applied properly. It also just makes more sense. Pointed out at jgm/pandoc#1346. - - - - - 05cb6e9c by Mateusz Kowalczyk at 2014-06-25T15:19:45+02:00 Bump haddock-library to 1.1.0 for release - - - - - 70feab15 by Iavor Diatchki at 2014-07-01T03:37:07-07:00 Propagate overloading-mode for instance declarations in haddock (#9242) - - - - - d4ca34a7 by Simon Peyton Jones at 2014-07-14T16:23:15+01:00 Adapt to new definition of HsDecls.TyFamEqn This is a knock-on from the refactoring from Trac haskell/haddock#9063. I'll push the corresponding changes to GHC shortly. - - - - - f91e2276 by Edward Z. Yang at 2014-07-21T08:14:19-07:00 Track GHC PackageId to PackageKey renaming. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - b010f9ef by Edward Z. Yang at 2014-07-25T16:28:46-07:00 Track changes for module reexports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - 8b85f9f9 by Mateusz Kowalczyk at 2014-07-28T13:25:43+02:00 Catch mid-line URLs. Fixes haskell/haddock#314. - - - - - 4c613a78 by Edward Z. Yang at 2014-08-05T03:11:00-07:00 Track type signature change of lookupModuleInAllPackages Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - e80b051c by Edward Z. Yang at 2014-08-05T17:34:26+01:00 If GhcProfiled, also build Haddock profiled. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f9cccd29 by Edward Z. Yang at 2014-08-07T14:23:35+01:00 Ignore TAGS files. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 00b3af52 by Mateusz Kowalczyk at 2014-08-08T04:58:19+02:00 Update to attoparsec-0.12.1.1 There seems to be memory and speed improvement. - - - - - 5457dc71 by Mateusz Kowalczyk at 2014-08-08T18:24:02+02:00 Fix forgotten src - - - - - 3520cb04 by Mateusz Kowalczyk at 2014-08-14T20:19:07+01:00 Bump down the version for master to 2.14.4 - - - - - dc98c21b by Mateusz Kowalczyk at 2014-08-14T20:23:27+01:00 Revert "Track type signature change of lookupModuleInAllPackages" This reverts commit d59fec2c9551b5662a3507c0011e32a09a9c118f. - - - - - 3f2038c0 by Mateusz Kowalczyk at 2014-08-14T20:23:31+01:00 Revert "Track changes for module reexports." This reverts commit b99b57c0df072d12b67816b45eca2a03cb1da96d. - - - - - 56d4e49e by Mateusz Kowalczyk at 2014-08-14T20:23:42+01:00 Revert "Track GHC PackageId to PackageKey renaming." This reverts commit 8ac42d3327473939c013551750425cac191ff0fd. - - - - - 726ea3cb by Mateusz Kowalczyk at 2014-08-14T20:23:47+01:00 Revert "Adapt to new definition of HsDecls.TyFamEqn" This reverts commit cb96b4f1ed0462b4a394b9fda6612c3bea9886bd. - - - - - 61a88ff0 by Mateusz Kowalczyk at 2014-08-14T20:23:52+01:00 Revert "Propagate overloading-mode for instance declarations in haddock (#9242)" This reverts commit 8d20ca8d5a9bee73252ff2035ec45f9c03d0820c. - - - - - a32ba674 by Mateusz Kowalczyk at 2014-08-14T20:26:03+01:00 Revert "Disambiguate ‘die’ in test runners." This reverts commit dba02d6df32534aac5d257f2d28596238d248942. - - - - - f335820f by Mateusz Kowalczyk at 2014-08-14T20:26:09+01:00 Revert "Replace local `die` by new `System.Exit.die`" This reverts commit 08aa509ebac58bfb202ea79c7c41291ec280a1c5. - - - - - 107078e4 by Mateusz Kowalczyk at 2014-08-14T20:27:34+01:00 Merge branch 'reverts' This reverts any changes that were made to have Haddock compile with 7.9. When 7.10 release comes, we can simply re-apply all the patches and any patches that occur on ghc-head branch from now on. This allows us to build master with 7.8.3 - - - - - b44b3871 by Mateusz Kowalczyk at 2014-08-15T02:47:40+01:00 Fix haskell/haddock#313 by doing some list munging. I get rid of the Monoid instance because we weren't satisfying the laws. Convenience of having <> didn't outweigh the shock-factor of having it behave badly. - - - - - e1a62cde by Mateusz Kowalczyk at 2014-08-15T02:52:56+01:00 Stop testing haskell/haddock#188. Because the change is in GHC 7.9 and we now work against 7.8.3, this test no longer makes sense. We revert it until 7.10 becomes the standard version. If anything, there should be a test for this in GHC itself. - - - - - 54e8286d by Mateusz Kowalczyk at 2014-08-15T05:31:57+01:00 Add haskell/haddock#313 to CHANGES - - - - - 9df7ad5d by Simon Hengel at 2014-08-20T11:25:32+08:00 Fix warning - - - - - ee2574d6 by Simon Hengel at 2014-08-20T12:07:01+08:00 Fix travis builds - - - - - 384cf2e6 by Simon Hengel at 2014-08-20T12:14:31+08:00 Require GHC 7.8.3 - - - - - d4779863 by Simon Hengel at 2014-08-22T12:14:16+08:00 Move Haddock API to a separate package - - - - - 80f3e0e1 by Simon Hengel at 2014-08-22T14:57:38+08:00 Bump version to 2.15.0 and add version constraints - - - - - 309a94ce by Simon Hengel at 2014-08-22T15:18:06+08:00 Add deprecated compatibility module - - - - - 4d1e4e3f by Luite Stegeman at 2014-08-22T20:46:45+02:00 export things to allow customizing how the Ghc session is run - - - - - 47884591 by Luite Stegeman at 2014-08-22T20:46:51+02:00 ghc 7.8.2 compatibility - - - - - 5ea94e2c by Luite Stegeman at 2014-08-22T22:08:58+02:00 install dependencies for haddock-api on travis - - - - - 9fb845b2 by Mateusz Kowalczyk at 2014-08-23T10:09:34+01:00 Move sources under haddock-api/src - - - - - 85817dc4 by Mateusz Kowalczyk at 2014-08-23T10:10:48+01:00 Remove compat stuff - - - - - 151c6169 by Niklas Haas at 2014-08-24T08:14:10+02:00 Fix extra whitespace on signatures and update all test cases This was long overdue, now running ./accept.lhs on a clean test from master will not generate a bunch of changes. - - - - - d320e0d2 by Niklas Haas at 2014-08-24T08:14:35+02:00 Omit unnecessary foralls and fix haskell/haddock#315 This also fixes haskell/haddock#86. - - - - - bdafe108 by Mateusz Kowalczyk at 2014-08-24T15:06:46+01:00 Update CHANGES - - - - - fafa6d6e by Mateusz Kowalczyk at 2014-08-24T15:14:23+01:00 Delete few unused/irrelevant/badly-place files. - - - - - 3634923d by Duncan Coutts at 2014-08-27T13:49:31+01:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. - - - - - 539a7e70 by Herbert Valerio Riedel at 2014-08-31T11:36:32+02:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 9e3a0e5b by Mateusz Kowalczyk at 2014-08-31T12:54:43+01:00 Bump version in doc - - - - - 4a177525 by Mateusz Kowalczyk at 2014-08-31T13:01:23+01:00 Bump haddock-library version - - - - - f99c1384 by Mateusz Kowalczyk at 2014-08-31T13:05:25+01:00 Remove references to deleted files - - - - - 5e51a247 by Mateusz Kowalczyk at 2014-08-31T14:18:44+01:00 Make the doc parser not complain - - - - - 2cedb49a by Mateusz Kowalczyk at 2014-09-03T03:33:15+01:00 CONTRIBUTING file for issues - - - - - 88027143 by Mateusz Kowalczyk at 2014-09-04T00:46:59+01:00 Mention --print-missing-docs - - - - - 42f6754f by Alan Zimmerman at 2014-09-05T18:13:24-05:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e712719e by Austin Seipp at 2014-09-09T01:03:27-05:00 Fix import of 'empty' due to AMP. Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 71c29755 by Herbert Valerio Riedel at 2014-09-09T17:35:20+02:00 Bump `base` constraint for AMP - - - - - 0bf9f3ed by Mateusz Kowalczyk at 2014-09-12T19:18:32+01:00 Delete stale ANNOUNCE - - - - - cac89ee6 by Krzysztof Gogolewski at 2014-09-14T17:17:09+02:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 4d683426 by Edward Z. Yang at 2014-09-18T13:38:11-07:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 80697fd5 by Herbert Valerio Riedel at 2014-09-19T00:07:52+02:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. - - - - - c015eb70 by Herbert Valerio Riedel at 2014-09-19T00:10:36+02:00 Revert "Followup changes to addition of -fwarn-context-quantification" This reverts commit 4023817d7c0e46db012ba2eea28022626841ca9b temporarily as the respective feature hasn't landed in GHC HEAD yet, but this commit blocks later commits from being referenced in GHC HEAD. - - - - - 38ded784 by Edward Z. Yang at 2014-09-18T15:32:15-07:00 Revert "Revert "Followup changes to addition of -fwarn-context-quantification"" This reverts commit db14fd8ab4fab43694139bc203808b814eafb2dc. It's in HEAD now. - - - - - f55d59c9 by Herbert Valerio Riedel at 2014-09-26T19:18:28+02:00 Revert "Fix import of 'empty' due to AMP." This reverts commit 0cc5bc85e9fca92ab712b68a2ba2c0dd9d3d79f4 since it turns out we don't need to re-export `empty` from Control.Monad after all. - - - - - 467050f1 by David Feuer at 2014-10-09T20:07:36-04:00 Fix improper lazy IO use Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. - - - - - cc47b699 by Edward Z. Yang at 2014-10-09T21:38:19-07:00 Fix use-after-close lazy IO bug Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. Signed-off-by: David Feuer <David.Feuer at gmail.com> Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 87babcbe by Austin Seipp at 2014-10-20T20:05:27-05:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - ab259516 by Austin Seipp at 2014-10-20T20:07:01-05:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - b918093c by Mateusz Kowalczyk at 2014-10-29T03:59:39+00:00 Experimental support for collapsable headers Closes haskell/haddock#335 - - - - - 849db129 by Mateusz Kowalczyk at 2014-10-29T10:07:26+01:00 Experimental support for collapsable headers (cherry picked from commit e2ed3b9d8dfab09f1b1861dbc8e74f08e137ebcc) - - - - - a4cc4789 by Herbert Valerio Riedel at 2014-10-31T11:08:26+01:00 Collapse user-defined section by default (re haskell/haddock#335) - - - - - 9da1b33e by Yuras Shumovich at 2014-10-31T16:11:04-05:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - c625aefc by Austin Seipp at 2014-10-31T19:34:10-05:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - c7738e5e by Simon Hengel at 2014-11-02T07:25:30+08:00 Remove -fobject-code from .ghci (this slows down reloads on modifications) - - - - - d4a86e95 by Simon Hengel at 2014-11-03T09:26:11+08:00 Get rid of StandaloneDeriving - - - - - a974e311 by Simon Hengel at 2014-11-03T09:26:11+08:00 Derive more instances - - - - - 8aa0c4d7 by Simon Hengel at 2014-11-03T09:27:08+08:00 Remove unused language extensions - - - - - 3052d46a by Simon Hengel at 2014-11-03T09:30:46+08:00 Minor refactoring - - - - - 4281d3cb by Simon Hengel at 2014-11-03T09:30:46+08:00 parser: Try to parse definition lists right before text paragraphs - - - - - 8ba12bf9 by Simon Hengel at 2014-11-03T09:34:19+08:00 Add support for markdown links (closes haskell/haddock#336) - - - - - a2f8d747 by Simon Hengel at 2014-11-03T09:34:19+08:00 Allow markdown links at the beginning of a paragraph - - - - - 53b11207 by Simon Hengel at 2014-11-03T09:34:20+08:00 Update documentation - - - - - 652267c6 by Simon Hengel at 2014-11-03T09:34:20+08:00 Add support for markdown images - - - - - 9d667502 by Simon Hengel at 2014-11-03T09:34:20+08:00 Allow an optional colon after the closing bracket of definition lists This is to disambiguate them from markdown links and will be require with a future release. - - - - - 8167fc32 by Mateusz Kowalczyk at 2014-11-04T01:16:51+00:00 whitespace only - - - - - 3da62981 by Mateusz Kowalczyk at 2014-11-04T01:17:31+00:00 Fix re-exports of built-in type families Fixes haskell/haddock#310 - - - - - edc76b34 by Mateusz Kowalczyk at 2014-11-04T02:54:28+00:00 Turn some uses of error into recoverable warnings This should at the very least not abort when something weird happens. It does feel like we should have a type that carries these errors until the end however as the user might not see them unless they are printed at the end. - - - - - 0a137400 by Mateusz Kowalczyk at 2014-11-04T04:09:44+00:00 Fix warnings - - - - - d068fc21 by Mateusz Kowalczyk at 2014-11-04T21:04:07+00:00 Fix parsing of identifiers written in infix way - - - - - 1a9f2f3d by Simon Hengel at 2014-11-08T11:32:42+08:00 Minor code simplification - - - - - 6475e9b1 by Simon Hengel at 2014-11-08T17:28:33+08:00 newtype-wrap parser monad - - - - - dc1ea105 by Herbert Valerio Riedel at 2014-11-15T11:55:43+01:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - fbb1aca4 by Simon Hengel at 2014-11-16T08:51:38+08:00 State intention rather than implementation details in Haddock comment - - - - - 97851ab2 by Simon Hengel at 2014-11-16T10:20:19+08:00 (wip) Add support for @since (closes haskell/haddock#26) - - - - - 34bcd18e by Gergő Érdi at 2014-11-20T22:35:38+08:00 Update Haddock to new pattern synonym type signature syntax - - - - - 304b7dc3 by Jan Stolarek at 2014-11-20T17:48:43+01:00 Follow changes from haskell/haddock#9812 - - - - - 920f9b03 by Richard Eisenberg at 2014-11-20T16:52:50-05:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 0bfe4e78 by Alan Zimmerman at 2014-11-21T11:23:09-06:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 356ed45a by Thomas Winant at 2014-11-28T16:11:22-06:00 Support for PartialTypeSignatures - - - - - 5dc8f3b1 by Gergő Érdi at 2014-11-29T15:39:09+08:00 For pattern synonyms, render "pattern" as a keyword - - - - - fe704480 by Mateusz Kowalczyk at 2014-12-09T03:38:32+00:00 List new module in cabal file - - - - - b9ad5a29 by Mateusz Kowalczyk at 2014-12-10T00:58:24+00:00 Allow the parser to spit out meta-info Currently we only use it only for ‘since’ annotations but with these patches it should be fairly simple to add new attributes if we wish to. Closes haskell/haddock#26. It seems to work fine but due to 7.10 rush I don't have the chance to do more exhaustive testing right now. The way the meta is output (emphasis at the end of the whole comment) is fairly arbitrary and subject to bikeshedding. Note that this makes test for Bug310 fail due to interface version bump: it can't find the docs for base with this interface version so it fails. There is not much we can do to help this because it tests for ’built-in’ identifier, not something we can provide ourselves. - - - - - 765af0e3 by Mateusz Kowalczyk at 2014-12-10T01:17:19+00:00 Update doctest parts of comments - - - - - 8670272b by jpmoresmau at 2014-12-10T01:35:31+00:00 header could contain several lines Closes haskell/haddock#348 - - - - - 4f9ae4f3 by Mateusz Kowalczyk at 2014-12-12T06:22:31+00:00 Revert "Merge branch 'reverts'" This reverts commit 5c93cc347773c7634321edd5f808d5b55b46301f, reversing changes made to 5b81a9e53894d2ae591ca0c6c96199632d39eb06. Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - e974ac94 by Duncan Coutts at 2014-12-12T06:26:11+00:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. Conflicts: haddock-api/src/Haddock.hs - - - - - 2f3a2365 by Herbert Valerio Riedel at 2014-12-12T06:26:51+00:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 1dbd6390 by Alan Zimmerman at 2014-12-12T06:32:07+00:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - bb6ff1f4 by Mateusz Kowalczyk at 2014-12-12T06:35:07+00:00 Bump ‘base’ constraint Follows the similar commit made on ghc-head branch - - - - - 466fe4ab by Krzysztof Gogolewski at 2014-12-12T06:37:42+00:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 97e080c9 by Edward Z. Yang at 2014-12-12T06:39:35+00:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: haddock-api/src/Haddock/ModuleTree.hs - - - - - 20b2af56 by Herbert Valerio Riedel at 2014-12-12T06:42:50+00:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. Conflicts: haddock-library/src/Documentation/Haddock/Parser.hs - - - - - b3ad269d by Austin Seipp at 2014-12-12T06:44:14+00:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 072df0dd by Austin Seipp at 2014-12-12T06:45:01+00:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - dbb9294a by Herbert Valerio Riedel at 2014-12-12T06:46:17+00:00 Collapse user-defined section by default (re haskell/haddock#335) Conflicts: haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs - - - - - f23ab545 by Yuras Shumovich at 2014-12-12T06:46:41+00:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - 753a4b67 by Austin Seipp at 2014-12-12T06:46:51+00:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8954e8f5 by Herbert Valerio Riedel at 2014-12-12T06:50:53+00:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - d2b06d61 by Gergő Érdi at 2014-12-12T07:07:30+00:00 Update Haddock to new pattern synonym type signature syntax Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 1ff02426 by Jan Stolarek at 2014-12-12T07:13:24+00:00 Follow changes from haskell/haddock#9812 Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - 06ad7600 by Richard Eisenberg at 2014-12-12T07:13:43+00:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 8fd2aa8b by Alan Zimmerman at 2014-12-12T07:22:25+00:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Backends/LaTeX.hs haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 95c3db98 by Thomas Winant at 2014-12-12T07:35:49+00:00 Support for PartialTypeSignatures Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs haddock-api/src/Haddock/Interface/Create.hs - - - - - 45494428 by Gergő Érdi at 2014-12-12T07:36:18+00:00 For pattern synonyms, render "pattern" as a keyword - - - - - a237e3eb by Mateusz Kowalczyk at 2014-12-12T12:27:13+00:00 Various fixups and bumps for next release - - - - - 22918bcd by Herbert Valerio Riedel at 2014-12-14T10:11:47+01:00 Remove redundant wild-card pattern match (this would otherwise cause a build-failure with `-Werror`) - - - - - 1d6ce947 by Herbert Valerio Riedel at 2014-12-14T10:17:06+01:00 Treat GHC 7.10 the same as GHC 7.9 ...since the current GHC 7.9 is going to become GHC 7.10 real-soon-now anyway - - - - - f434ea89 by Herbert Valerio Riedel at 2014-12-14T18:26:50+01:00 Fixup ghc.mk (follow-up to 1739375eb23342) This makes the GHC build-system aware of the data-files to be copied into the bindist (as haddock.cabal doesn't list those anymore) - - - - - 6fb839eb by Mateusz Kowalczyk at 2014-12-17T09:28:59+00:00 Only keep one Version instead of blindly appending - - - - - 40645489 by Mateusz Kowalczyk at 2014-12-18T07:09:44+00:00 Fix dependency version - - - - - 8b3b927b by Mateusz Kowalczyk at 2014-12-18T07:14:23+00:00 Print missing docs by default Adds --no-print-missing-docs - - - - - 59666694 by Mateusz Kowalczyk at 2014-12-18T07:21:37+00:00 update changelog - - - - - aa6d168e by Mateusz Kowalczyk at 2014-12-18T07:30:58+00:00 Update docs for @since - - - - - 2d7043ee by Luite Stegeman at 2014-12-19T18:29:35-06:00 hide projectVersion from DynFlags since it clashes with Haddock.Version.projectVersion - - - - - aaa70fc0 by Luite Stegeman at 2014-12-22T15:58:43+01:00 Add missing import for standalone haddock-api package - - - - - 9ce01269 by Herbert Valerio Riedel at 2014-12-22T17:48:45+01:00 Reset ghc-head with master's tree (this is an overwriting git merge of master into ghc-head) - - - - - fcd6fec1 by Herbert Valerio Riedel at 2014-12-22T17:51:52+01:00 Bump versions for ghc-7.11 - - - - - 525ec900 by Mateusz Kowalczyk at 2014-12-23T13:36:24+00:00 travis-ci: test with HEAD - - - - - cbf494b5 by Simon Peyton Jones at 2014-12-23T15:22:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 50e01c99 by Mateusz Kowalczyk at 2014-12-29T15:28:47+00:00 Make travis use 7.10.x - - - - - 475e60b0 by Njagi Mwaniki at 2014-12-29T15:30:44+00:00 Turn the README into GitHub Markdown format. Closes haskell/haddock#354 - - - - - 8cacf48e by Luite Stegeman at 2015-01-05T16:25:37+01:00 bump haddock-api ghc dependency to allow release candidate and first release - - - - - 6ed6cf1f by Simon Peyton Jones at 2015-01-06T16:37:47+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 8b484f33 by Simon Peyton Jones at 2015-01-08T15:50:22+00:00 Track naming change in DataCon - - - - - 23c5c0b5 by Alan Zimmerman at 2015-01-16T10:15:11-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e7a5532c by JP Moresmau at 2015-01-22T17:19:03+00:00 Ignore warnings, install Cabal 1.22 - - - - - 86942c84 by jpmoresmau at 2015-01-22T17:19:04+00:00 solve dataDir ambiguity - - - - - 5ceb743e by jpmoresmau at 2015-01-22T19:17:32+00:00 support GHC 7.10: no Safe-Inferred, Foldable instance - - - - - 6a3b3fb5 by Mateusz Kowalczyk at 2015-01-22T19:32:10+00:00 Update test files Test: a correct behaviour for fields comma-separating values. I'm surprised we had no bug open for this. Maybe it affects how haskell/haddock#301 renders now but I doubt. Operators: Seems GHC is giving us a new order for operators, something must have changed on their side again. cc @haasn , this makes the fixity to the side not match the order on the LHS which is a bit unpleasant. Maybe the fixity can be made to match the GHC order? Bug335: We expand examples by default now. Bug310: Now inferred safe. - - - - - 708f8b2f by jpmoresmau at 2015-01-22T19:36:59+00:00 Links to source location of class instance definitions - - - - - 5cf8a6da by Vincent Berthoux at 2015-01-22T19:59:58+00:00 Filter '\r' from comments due to Windows problems. On Windows this was causing newline to be rendered twice in code blocks. Closes haskell/haddock#359, fixes haskell/haddock#356. - - - - - 1749e6f0 by Mateusz Kowalczyk at 2015-01-22T20:31:27+00:00 Changelog only - - - - - c8145f90 by Mateusz Kowalczyk at 2015-01-22T23:34:05+00:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. - - - - - 14248254 by Mateusz Kowalczyk at 2015-01-22T23:43:18+00:00 Sort out some module import warnings - - - - - d8a38989 by Simon Peyton Jones at 2015-01-23T07:10:16-06:00 Track naming change in DataCon (cherry picked from commit 04cf63d0195837ed52075ed7d2676e71831e8a0b) - - - - - d3ac6ae4 by Alan Zimmerman at 2015-01-23T07:17:19-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit d61bbc75890e4eb0ad508b9c2a27b91f691213e6) - - - - - 4c1ffeb0 by Simon Peyton Jones at 2015-02-10T12:10:33+00:00 Track changes in HsSyn for quasi-quotes - - - - - 775d20f7 by Mateusz Kowalczyk at 2015-03-15T08:11:48+01:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. (cherry picked from commit 8e06728afb0784128ab2df0be7a5d7a191d30ff4) - - - - - f9245e72 by Phil Ruffwind at 2015-03-16T04:32:01-04:00 Prevent Synopsis from using up too much horizontal space When long type signatures occur in the Synopsis, the element is stretched beyond the width of the window. Scrollbars don't appear, so it's impossible to read anything when this happens. - - - - - cd8fa415 by Mateusz Kowalczyk at 2015-03-17T21:59:39+00:00 Update changelog Closes haskell/haddock#151 due to 71170fc77962f10d7d001e3b8bc8b92bfeda99bc - - - - - b5248b47 by Ben Gamari at 2015-03-25T17:12:17+00:00 Make the error encountered when a package can't be found more user-friendly Closes haskell/haddock#369 - - - - - b756b772 by Mateusz Kowalczyk at 2015-03-26T16:31:40+00:00 Remove now redundant imports - - - - - 5ea5e8dd by Mateusz Kowalczyk at 2015-03-26T16:45:52+00:00 Update test to account for \r filtering - - - - - 6539bfb3 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Test for anchor defaulting I delete the old tests because it turns out that: * test runner would never put them in scope of each other even with imports so just one would suffice * test runner actually needed some hacking to keep links so in the end we would end up with no anchors making them useless - - - - - 1a01d950 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Clearly default to variables in out of scope case - - - - - 7943abe8 by Mateusz Kowalczyk at 2015-03-27T01:14:11+00:00 Fix Hoogle display of constructors Fixes haskell/haddock#361 - - - - - 6d6e587e by Mateusz Kowalczyk at 2015-03-27T01:45:18+00:00 Fully qualify names in Hoogle instances output Closes haskell/haddock#263 - - - - - 52dac365 by Mateusz Kowalczyk at 2015-03-27T01:55:01+00:00 Update changelog - - - - - ca5af9a8 by Mateusz Kowalczyk at 2015-03-27T02:43:55+00:00 Output method documentation in Hoogle backend One thing of note is that we no longer preserve grouping of methods and print each method on its own line. We could preserve it if no documentation is present for any methods in the group if someone asks for it though. Fixes haskell/haddock#259 - - - - - a33f0c10 by Mateusz Kowalczyk at 2015-03-27T03:04:21+00:00 Don't print instance safety information in Hoogle Fixes haskell/haddock#168 - - - - - df6c935a by Mateusz Kowalczyk at 2015-03-28T00:11:47+00:00 Post-release version bumps and changelog - - - - - dde8f7c0 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Loosen bounds on haddock-* - - - - - de93bf89 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Expand response files in arguments Closes haskell/haddock#285 - - - - - 1f0b0856 by Zejun Wu at 2015-04-26T16:35:35-07:00 Do not insert anchor for section headings in contents box - - - - - 860439d7 by Simon Peyton Jones at 2015-05-01T09:36:47+01:00 Track change in API of TyCon - - - - - a32f3e5f by Adam Gundry at 2015-05-04T15:32:59+01:00 Track API changes to support empty closed type familes - - - - - 77e98bee by Ben Gamari at 2015-05-06T20:17:08+01:00 Ignore doc/haddock.{ps,pdf} - - - - - 663d0204 by Murray Campbell at 2015-05-11T04:47:37-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8bb0dcf5 by Murray Campbell at 2015-05-11T06:35:06-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit 2380f07c430c525b205ce2eae6dab23c8388d899) - - - - - bad900ea by Adam Bergmark at 2015-05-11T15:29:39+01:00 haddock-library: require GHC >= 7.4 `Data.Monoid.<>` was added in base-4.5/GHC-7.4 Closes haskell/haddock#394 Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - daceff85 by Simon Peyton Jones at 2015-05-13T12:04:21+01:00 Track the new location of setRdrNameSpace - - - - - 1937d1c4 by Alan Zimmerman at 2015-05-25T21:27:15+02:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - ee0fb6c2 by Łukasz Hanuszczak at 2015-05-27T11:51:31+02:00 Create simple method for indentation parsing. - - - - - 7d6fcad5 by Łukasz Hanuszczak at 2015-05-27T21:36:13+02:00 Make nested lists count indentation according to first item. - - - - - d6819398 by Łukasz Hanuszczak at 2015-05-27T22:46:13+02:00 Add simple test case for arbitrary-depth list nesting. - - - - - 2929c54d by Łukasz Hanuszczak at 2015-06-03T02:11:31+02:00 Add arbitrary-indent spec test for parser. - - - - - 9a0a9bb0 by Mateusz Kowalczyk at 2015-06-03T05:25:29+01:00 Update docs with info on new list nesting rule Fixes haskell/haddock#278 through commits from PR haskell/haddock#401 - - - - - 12efc92c by Mateusz Kowalczyk at 2015-06-03T05:29:26+01:00 Update some meta data at the top of the docs - - - - - 765ee49f by Bartosz Nitka at 2015-06-07T08:40:59-07:00 Add some Hacking docs for getting started - - - - - 19aaf851 by Bartosz Nitka at 2015-06-07T08:44:30-07:00 Fix markdown - - - - - 2a90cb70 by Mateusz Kowalczyk at 2015-06-08T15:08:36+01:00 Refine hacking instructions slightly - - - - - 0894da6e by Thomas Winant at 2015-06-08T23:47:28-05:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 10a9bb76 by Emanuel Borsboom at 2015-06-12T02:46:23+01:00 Build executable with '-threaded' (fixes haskell/haddock#399) - - - - - 7696b94f by Mateusz Kowalczyk at 2015-06-12T02:59:19+01:00 Update changelog for -threaded Closes haskell/haddock#400 - - - - - d3c118ec by Bartosz Nitka at 2015-06-12T03:00:58+01:00 Fix haddock: internal error: spliceURL UnhelpfulSpan (#207) Inferred type signatures don't have SrcSpans, so let's use the one from the declaration. I've tested this manually on the test-case from haskell/haddock#207, but I got stuck at trying to run the test-suite. - - - - - b67e843b by Mateusz Kowalczyk at 2015-06-12T03:01:50+01:00 Changelog for haskell/haddock#207 Fixes haskell/haddock#207, closes haskell/haddock#402 - - - - - 841d785e by jpmoresmau at 2015-06-12T16:03:16+01:00 Attach to instance location the name that has the same location file Fixes haskell/haddock#383 - - - - - 98791cae by Mateusz Kowalczyk at 2015-06-12T16:08:27+01:00 Update changelog Closes haskell/haddock#398 - - - - - 7c0b5a87 by Phil Ruffwind at 2015-06-12T13:07:25-04:00 Fix alignment of Source links in instance table in Firefox Due to a Firefox bug [1], a combination of 'whitespace: nowrap' on the parent element with 'float: right' on the inner element can cause the floated element to be displaced downwards for no apparent reason. To work around this, the left side is wrapped in its own <span> and set to 'float: left'. As a precautionary measure to prevent the parent element from collapsing entirely, we also add the classic "clearfix" hack. The latter is not strictly needed but it helps prevent bugs if the layout is altered again in the future. Fixes haskell/haddock#384. Remark: line 159 of src/Haddock/Backends/Xhtml/Layout.hs was indented to prevent confusion over the operator precedence of (<+>) vs (<<). [1]: https://bugzilla.mozilla.org/show_bug.cgi?id=488725 - - - - - cfe86e73 by Mateusz Kowalczyk at 2015-06-14T10:49:01+01:00 Update tests for the CSS changes - - - - - 2d4983c1 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding for Haskell source parser module. - - - - - 29548785 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement function for tagging parsed chunks with source spans. - - - - - 6a5e4074 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement simple string chunking based on HsColour library. - - - - - 6e52291f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create basic token classification method. - - - - - da971a27 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Adapt source span tagging to work with current whitespace handling. - - - - - 4feb5a22 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add record accessors to exports of hyperlinker parser module. - - - - - a8cc4e39 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Make parser module export all types and associated accessors. - - - - - fb8d468f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple HTML renderer for parsed source file. - - - - - 80747822 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for specifying the CSS file path in HTML source renderer. - - - - - 994dc1f5 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix identifier recognition in Haskell source parser. - - - - - b1bd0430 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix comment recognition in Haskell source parser. - - - - - 11db85ae by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for recognizing compiler pragmas in source parser. - - - - - 736c7bd3 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding of module for associating tokens with AST names. - - - - - 7e149bc2 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement utility method for extracting variable identifiers from AST. - - - - - 32eb640a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple mechanism for associating tokens with AST names. - - - - - d4eba5bc by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add dummy support for hyperlinking named tokens. - - - - - 2b76141f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matcher bug causing wrong items being hyperlinked. - - - - - 2d48002e by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Constrain elements exported by hyperlinker modules. - - - - - 9715eec6 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for type token recognition. - - - - - 8fa401cb by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for binding token recognition. - - - - - d062400b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement go-to-definition mechanism for local bindings. - - - - - f4dc229b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement module export- and import-list item hyperlinking. - - - - - c9a46d58 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matching to allow parenthesized operators hyperlinking. - - - - - 03aad95a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix weird hyperlinking of parenthesized operators. - - - - - b4694a7d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for type declaration anchors. - - - - - 7358d2d2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for top-level function declaration anchors. - - - - - dfc24b24 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix external anchors to contain HTML file extension. - - - - - a045926c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Refactor the way AST names are handled within detailed tokens. - - - - - c76049b4 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement hyperlinking of imported module names. - - - - - 2d2a1572 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix parsing of single line comments with broken up newlines. - - - - - 11afdcf2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix bug with improper newline handling. - - - - - 8137f104 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issues with escaped newlines in comments. - - - - - 34759b19 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for parsing C preprocessor macros. - - - - - 09f0f847 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for parser module of source hyperlinker. - - - - - 709a8389 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for AST module of source hyperlinker. - - - - - 4df5c227 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add command line option for generating hyperlinked source. - - - - - 7a755ea2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Extend module interface with rich source token stream field. - - - - - 494f4ab1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement source tokenization during interface creation process. - - - - - 5f21c953 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create hyperlinker module and plug it into the Haddock pipeline. - - - - - 0cc8a216 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for providing custom CSS files for hyperlinked source. - - - - - a32bbdc1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for fancy highlighting upon hovering over identifier. - - - - - d16d642a by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make source hyperlinker generate output in apropriate directory. - - - - - ae12953d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create module with hyperlinker utility functions. - - - - - 6d4952c5 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make external hyperlinks point to locations specified by source URLs. - - - - - 8417555d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Rewrite source generation to fixed links and directory structure. - - - - - ce9cec01 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add basic support for cross-package hyperlink generation. - - - - - 7eaf025c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Disable generating hyperlinks for module references. - - - - - a50bf92e by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make Haddock generate source for all interfaces (also hidden ones). - - - - - f5ae2838 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Prevent source parser from throwing exception when lexing fails. - - - - - db9ffbe0 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement workaround for Chrome highlighting issues. - - - - - 0b6b453b by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate correct anchors for data constructors. - - - - - c86d38bc by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate anchors for record field declarations. - - - - - 063abf7f by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issue with hyperlink highlight styling in Chrome browser. - - - - - 880fc611 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking constructor names in patters. - - - - - c9e89b95 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record patterns. - - - - - 17a11996 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record expressions. - - - - - 0eef932d by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Make hyperlinker respect pretty-printer flag and add documentation. - - - - - f87c1776 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Unexpose hyperlinker modules in Cabal configuration. - - - - - 4c9e2b06 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Setup HSpec framework for Haddock API package. - - - - - 4b20cb30 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add basic tests related to comment parsing. - - - - - 6842e919 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add tests related to parsing basic language constructs. - - - - - 87bffb35 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add simple tests for do-notation parsing. - - - - - e7af1841 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add very simple QuickCheck properties for source parser spec. - - - - - c84efcf1 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Create simple test runner for hyperlinker tests. - - - - - 76b90447 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for basic identifier hyperlinking. - - - - - 0fbf4df6 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for operator hyperlinking. - - - - - 731aa039 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for constructor hyperlinking. - - - - - 995a78a2 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for record expressions and patterns hyperlinking. - - - - - 3566875a by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for literal syntax highlighting. - - - - - 68469a35 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add hyperlinker test runner to .cabal and .gitignore files. - - - - - aa946c93 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Adapt hyperlinker test runner to have the same interface as HTML one. - - - - - ce34da16 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Fix hyperlinker test runner file paths and add pretty-printing option. - - - - - 0d7dd65e by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add reference files for hyperlinker test cases. - - - - - efa4a1e0 by Łukasz Hanuszczak at 2015-07-01T00:47:32+02:00 Make hyperlinker test runner strip local links from generated source. - - - - - 3e96e584 by Łukasz Hanuszczak at 2015-07-01T01:14:59+02:00 Create simple script for accepting hyperlinker test case references. - - - - - 526fe610 by Łukasz Hanuszczak at 2015-07-01T01:16:41+02:00 Re-accept hyperlinker test cases with local references stripped out. - - - - - 892e2cb3 by Łukasz Hanuszczak at 2015-07-01T01:22:09+02:00 Fix bug with diffing wrong files in hyperlinker test runner. - - - - - 9ff46039 by Łukasz Hanuszczak at 2015-07-01T18:04:46+02:00 Remove unused dependencies in Haddock API spec configuration. - - - - - 47969c07 by Łukasz Hanuszczak at 2015-07-01T18:32:19+02:00 Add support for hyperlinking synonyms in patterns. - - - - - a73449e0 by Łukasz Hanuszczak at 2015-07-01T18:33:44+02:00 Create test case for hyperlinking @-patterns. - - - - - c2077ed8 by Łukasz Hanuszczak at 2015-07-01T19:06:04+02:00 Add support for hyperlinking universally quantified type variables. - - - - - 68017342 by Łukasz Hanuszczak at 2015-07-01T19:28:32+02:00 Create hyperlinker test case with quantified type variables. - - - - - 51c01a78 by Łukasz Hanuszczak at 2015-07-01T19:34:22+02:00 Add scoped type variables test for polymorphism test case. - - - - - 13181ae2 by Łukasz Hanuszczak at 2015-07-01T19:56:27+02:00 Add record wildcards test for records hyperlinking test case. - - - - - 991b81dd by Łukasz Hanuszczak at 2015-07-01T21:01:42+02:00 Document some functions in XHTML utlity module. - - - - - 98c8dfe5 by Łukasz Hanuszczak at 2015-07-01T22:25:21+02:00 Make hyperlinker render qualified names as one entity. - - - - - 75e13b9b by Łukasz Hanuszczak at 2015-07-01T22:27:38+02:00 Add qualified name test for identifiers hyperlinking test case. - - - - - de1e143f by Łukasz Hanuszczak at 2015-07-02T12:32:59+02:00 Fix crash happening when hyperlinking type family declarations. - - - - - 7a8fb175 by Łukasz Hanuszczak at 2015-07-02T12:47:03+02:00 Add support for anchoring data family constructor declarations. - - - - - 3b404e49 by Łukasz Hanuszczak at 2015-07-02T13:31:05+02:00 Improve support for hyperlinking type families. - - - - - 59eb7143 by Łukasz Hanuszczak at 2015-07-02T13:33:34+02:00 Add hyperlinker test case for checking type and type family declarations. - - - - - d1cda0c0 by Łukasz Hanuszczak at 2015-07-02T13:41:38+02:00 Fix issue with operators being recognized as preprocessor directives. - - - - - da206c9d by Łukasz Hanuszczak at 2015-07-02T17:18:12+02:00 Fix broken tests for parsing and hyperlinking hash operators. - - - - - 53750d1b by Łukasz Hanuszczak at 2015-07-02T18:53:28+02:00 Add support for anchoring signatures in type class declarations. - - - - - 1fa5bb10 by Łukasz Hanuszczak at 2015-07-02T19:04:47+02:00 Make hyperlinker generate anchors only to top-level value bindings. - - - - - a542305c by Łukasz Hanuszczak at 2015-07-02T19:05:58+02:00 Create hyperlinker test case for type classes. - - - - - b0dd4581 by Łukasz Hanuszczak at 2015-07-04T16:28:26+02:00 Update docs with information about source hyperlinking. - - - - - 9795302a by Łukasz Hanuszczak at 2015-07-04T16:52:15+02:00 Update docs on using `--read-interface` option. - - - - - 9acdc002 by Łukasz Hanuszczak at 2015-07-04T17:15:26+02:00 Remove potentially dangerous record access in hyperlinker AST module. - - - - - fb3ab7be by Łukasz Hanuszczak at 2015-07-04T17:40:10+02:00 Make Haddock generate warnings about potential misuse of hyperlinker. - - - - - a324c504 by Łukasz Hanuszczak at 2015-07-04T17:43:22+02:00 Fix incorrect specification of source style option in doc file. - - - - - 3f01a8e4 by Łukasz Hanuszczak at 2015-07-05T17:06:36+02:00 Refactor source path mapping to use modules as indices. - - - - - ac70f5b1 by Łukasz Hanuszczak at 2015-07-05T17:47:34+02:00 Fix bug where not all module interfaces were added to source mapping. - - - - - f5e57da9 by Łukasz Hanuszczak at 2015-07-06T16:39:57+02:00 Extract main hyperlinker types to separate module. - - - - - 43974905 by Łukasz Hanuszczak at 2015-07-06T16:52:13+02:00 Move source paths types to hyperlinker types module. - - - - - 3e236055 by Łukasz Hanuszczak at 2015-07-06T17:06:19+02:00 Add support for hyperlinking modules in import lists. - - - - - 58233d9f by Łukasz Hanuszczak at 2015-07-06T17:26:49+02:00 Add short documentation for hyperlinker source map type. - - - - - 14da016d by Łukasz Hanuszczak at 2015-07-06T18:07:20+02:00 Fix bug with module name being hyperlinked to `Prelude`. - - - - - 8f79db52 by Łukasz Hanuszczak at 2015-07-06T18:23:47+02:00 Fix problem with spec build in Haddock API configuration. - - - - - e7cc056c by Adam Sandberg Eriksson at 2015-07-07T23:22:21+01:00 StrictData: print correct strictness marks - - - - - e8253ca8 by Mateusz Kowalczyk at 2015-07-07T23:58:28+01:00 Update changelog - - - - - 0aba676b by Mateusz Kowalczyk at 2015-07-07T23:58:33+01:00 Relax upper bound on GHC a bit - - - - - 7a595381 by Mateusz Kowalczyk at 2015-07-07T23:58:52+01:00 Delete trailing whitespace - - - - - 50976d5e by Adam Sandberg Eriksson at 2015-07-08T15:03:04+02:00 StrictData: changes in HsBang type - - - - - 83b045fa by Mateusz Kowalczyk at 2015-07-11T14:35:18+01:00 Fix expansion icon for user-collapsible sections Closes haskell/haddock#412 - - - - - b2a3b0d1 by Mateusz Kowalczyk at 2015-07-22T22:03:21+01:00 Make some version changes after 2.16.1 release - - - - - a8294423 by Ben Gamari at 2015-07-27T13:16:07+02:00 Merge pull request haskell/haddock#422 from adamse/adamse-D1033 Merge for GHC D1033 - - - - - c0173f17 by randen at 2015-07-30T14:49:08-07:00 Break the response file by line termination rather than spaces, since spaces may be within the parameters. This simple approach avoids having the need for any quoting and/or escaping (although a newline char will not be possible in a parameter and has no escape mechanism to allow it). - - - - - 47c0ca14 by Alan Zimmerman at 2015-07-31T10:41:52+02:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - 45a9d770 by Mateusz Kowalczyk at 2015-07-31T09:47:43+01:00 Update changelog - - - - - 347a20a3 by Phil Ruffwind at 2015-08-02T23:15:26+01:00 Avoid JavaScript error during page load in non-frame mode In non-frame mode, parent.window.synopsis refers to the synopsis div rather than the nonexistent frame. Unfortunately, the script wrongly assumes that if it exists it must be a frame, leading to an error where it tries to access the nonexistent attribute 'replace' of an undefined value (synopsis.location). Closes haskell/haddock#406 - - - - - 54ebd519 by Phil Ruffwind at 2015-08-02T23:27:10+01:00 Link to the definitions to themselves Currently, the definitions already have an anchor tag that allows URLs with fragment identifiers to locate them, but it is rather inconvenient to obtain such a URL (so-called "permalink") as it would require finding the a link to the corresponding item in the Synopsis or elsewhere. This commit adds hyperlinks to the definitions themselves, allowing users to obtain links to them easily. To preserve the original aesthetics of the definitions, we alter the color of the link so as to be identical to what it was, except it now has a hover effect indicating that it is clickable. Additionally, the anchor now uses the 'id' attribute instead of the (obsolete) 'name' attribute. Closes haskell/haddock#407 - - - - - 02cc8bb7 by Phil Ruffwind at 2015-08-02T23:28:02+01:00 Fix typo in Haddock.Backends.Xhtml.Layout: divSynposis -> divSynopsis Closes haskell/haddock#408 - - - - - 2eb0a458 by Phil Ruffwind at 2015-08-02T23:30:07+01:00 Fix record field alignment when name is too long Change <dl> to <ul> and use display:table rather than floats to layout the record fields. This avoids bug haskell/haddock#301 that occurs whenever the field name gets too long. Slight aesthetic change: the entire cell of the field's source code is now shaded gray rather than just the area where text exists. Fixes haskell/haddock#301. Closes haskell/haddock#421 - - - - - 7abb3402 by Łukasz Hanuszczak at 2015-08-02T23:32:14+01:00 Add some utility definitions for generating line anchors. - - - - - e0b1d79b by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Make hyperlinked source renderer generate line anchors. - - - - - 24dd4c9f by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Re-accept test cases after adding line anchors for each of them. - - - - - 0372cfcb by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Override source line flags when source hyperlinker is enabled. - - - - - a81bcd07 by Mateusz Kowalczyk at 2015-08-02T23:58:25+01:00 Update tests to follow HTML changes - - - - - d2d7426f by Łukasz Hanuszczak at 2015-08-06T20:54:59+02:00 Fix quote syntax for promoted types. - - - - - 668cf029 by Łukasz Hanuszczak at 2015-08-06T21:12:00+02:00 Apply promoted type quoting to type-level consing. - - - - - 89f8e7c6 by Łukasz Hanuszczak at 2015-08-06T21:17:10+02:00 Extend advanced types test case with other examples. - - - - - 86494bca by Łukasz Hanuszczak at 2015-08-06T21:22:06+02:00 Rename advanced types test case and accept new output. - - - - - dbb7c7c0 by Adam Sandberg Eriksson at 2015-08-09T23:01:05+02:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 2a7704fa by Ben Gamari at 2015-08-10T13:18:05+02:00 Merge pull request haskell/haddock#433 from adamse/split-hsbang HsBang is split into HsSrcBang and HsImplBang - - - - - 891954bc by Thomas Miedema at 2015-08-15T14:51:18+02:00 Follow changes in GHC build system - - - - - b55d32ab by Mateusz Kowalczyk at 2015-08-21T18:06:09+01:00 Make Travis use 7.10.2 - - - - - 97348b51 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Move SYB utilities to standalone module. - - - - - 748ec081 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement `everywhere` transformation in SYB module. - - - - - 011cc543 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement generic transformation constructor. - - - - - b9510db2 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Create simple utility module for type specialization. - - - - - 43229fa6 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Make type of type specialization function more general. - - - - - fd844e90 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Add basic HTML test case for checking instance specialization. - - - - - 6ea0ad04 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Make HTML class instance printer take optional signature argument. - - - - - 65aa41b6 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Refactor instance head type to record instead of a meaningless tuple. - - - - - 3fc3bede by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add expandable method section for each class instance declaration. - - - - - 99ceb107 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Move dummy post-family instances for `DocName` to `Types` module. - - - - - e98f4708 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create convenience functions for type specialization module. - - - - - b947552f by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Hook type specialization logic with HTML pretty-printer. - - - - - dcaa8030 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create stub functions for sugaring specialized types. - - - - - fa84bc65 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement list syntax sugaring logic for specialized types. - - - - - e8b05b07 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement tuple syntax sugaring logic for specialized types. - - - - - 68a2e5bc by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Get rid of code duplication in type specialization module. - - - - - 4721c336 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create scaffolding of a framework for renaming specialized types. - - - - - 271b488d by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in missing cases in specialized type renaming function. - - - - - bfa5f2a4 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Remove code duplication in specialized type renamer. - - - - - ea6bd0e8 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Change state of the type renaming monad. - - - - - 77c5496e by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement simple mechanism for generating new type names. - - - - - 91bfb48b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in stub behaviour with actual environment renaming. - - - - - d244517b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix logic behind binder type renaming. - - - - - f3c5e360 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add SYB-like utility function for performing stateful queries. - - - - - eb3f9154 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create function for retrieving free variables from given type. - - - - - a94561d3 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix compilation error caused by incorrect type signature. - - - - - 8bb707cf by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Move `SetName` class definition to types module. - - - - - 5800b13b by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Hook type renamer with instance method HTML pretty-printer. - - - - - 6a480164 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some test cases for type renamer. - - - - - 839842f7 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized signatures refer to original signature declaration. - - - - - 4880f7c9 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized methods be nicely formatted again. - - - - - ab5a6a2e by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Attach source locations to the specialized class methods. - - - - - 43f8a559 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Extend instances test case to also test multi-name type signatures. - - - - - 59bc751c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix tab-based indentation in instances test case. - - - - - c2126815 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Improve placement of instance methods expander button. - - - - - 0a32e287 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add new data type declaration to instance specialization test case. - - - - - 5281af1f by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make type renamer first try single-letter names as alternatives. - - - - - 7d509475 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix type renamer bug with incorrect names being generated. - - - - - 0f35bf7c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some documentation and refactor type specialization module. - - - - - da1d0803 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix another bug where type renamer was generating incorrect names. - - - - - cd39b5cb by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Refactor type renamer to rebinding and pure renaming phases. - - - - - 850251f4 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix unwitting compilation bug. - - - - - e5e9fc01 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Integrate instance specification type into class instance definition. - - - - - 825b0ea0 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer neccessary instance specification type. - - - - - cdba44eb by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix declaration converter to use more appropriate mode for methods. - - - - - bc45c309 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug with types not being specialized at all. - - - - - 5d8e5d89 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug where instance expander was opening wrong section. - - - - - 6001ee41 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix another type renamer bug where not all names were rebound. - - - - - 5f58ce2a by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix yet another renamer bug where some names were not unique. - - - - - 8265e521 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split instance subsection layout method to top-level declarations. - - - - - e5e66298 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Rearrange layout of instance methods in generated documentation. - - - - - a50b4eea by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer used layout method. - - - - - 2ff36ec2 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach section title to the instance methods block. - - - - - 7ac15300 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Add basic tests for associated types in instances test case. - - - - - db0ea2f9 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach associated types information to instance header. - - - - - 71cad4d5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details section contain associated types information. - - - - - deee2809 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Improve look of rendered associated families in instance details. - - - - - 839d13a5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Introduce alternative type for family declarations. - - - - - d397f03f by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details record use new type for family declarations. - - - - - 2b23fe97 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split printer of type family header to separate functions. - - - - - c3498cdc by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Implement HTML renderer for pseudo-family declarations. - - - - - c12bbb04 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Apply type specializer to associated type family declarations. - - - - - 2fd69ff2 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Create helper method for specializing type signatures. - - - - - 475826e7 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Refactor specializer module to be independent from XHTML backend. - - - - - f00b431c by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add some documentation for instance head specializer. - - - - - a9fef2dc by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix bug with missing space in documentation for associated types. - - - - - 50e29056 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with incorrect instance details sections being expanded. - - - - - e6dfdd03 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by adding instance details section. - - - - - 75565b2a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make section identifier of instance details more GHC-independent. - - - - - add0c23e by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Re-accept tests after applying deterministic section identifiers. - - - - - 878f2534 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make identifier generation also architecture-independent. - - - - - 48be69f8 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with instance expander hijacking type hyperlink click. - - - - - 47830c1f by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Get rid of dreadful hashing function for generating identifiers. - - - - - 956cd5af by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Move `InstOrigin` type declaration to more appropriate module. - - - - - bf672ed3 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by changes related to instance expander. - - - - - 8f2a949a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add examples with type operators to the instances test case. - - - - - 64600a84 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add basic support for sugaring infix type operators. - - - - - 747d71b8 by Łukasz Hanuszczak at 2015-08-21T18:22:34+01:00 Add support for sugaring built-in function syntax. - - - - - d4696ffb by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Remove default methods from Hoogle class output. - - - - - bf0e09d7 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add fixity declarations in Hoogle backend output. - - - - - 90e91a51 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix bug with incorrect fixities being generated in Hoogle backend. - - - - - 48f11d35 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve class type family declarations output in Hoogle backend. - - - - - 661e8e8f by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add missing default family equations in Hoogle output. - - - - - e2d64103 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve formatting of class details output in Hoogle backend. - - - - - 490fc377 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix weird-looking Hoogle output for familyless classes. - - - - - ea115b64 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create script file for new HTML test runner. - - - - - 609913d3 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Set default behaviour if no arguments given. - - - - - dc115f67 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for providing optional arguments for test runner. - - - - - d93ec867 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve output of test runner error messages. - - - - - 0be9fe12 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for executing Haddock process in test runner. - - - - - 4e4d00d9 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add GHC path to test runner configuration. - - - - - d67a2086 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make GHC path a test runner command-line argument. - - - - - c810079a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Extend test runner configuration with Haddock arguments. - - - - - fee18845 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor test runner and create stub functions. - - - - - ff7c161f by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make test runner actually run Haddock executable. - - - - - 391f73e6 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with test runner not producing any output files. - - - - - 81a74e2d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Setup skeleton of framework for running tests. - - - - - f8a79ec4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with modules not being found in global search mode. - - - - - 7e700b4d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make Haddock standard output redirection be more configurable. - - - - - 53b4c17a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Incorporate old, ugly functions for comparing output files. - - - - - 8277c8aa by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor architecture of test runner output checking functions. - - - - - 587bb414 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement actual diffing mechanism. - - - - - 9ed2b5e4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve code style to match popular guidelines. - - - - - 14bffaf8 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make it possible to choose alternative diff tool. - - - - - 5cdfb005 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create stub methods for processing test output as XML documents. - - - - - 7ef8e12e by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement link-stripping logic as simple SYB transformation. - - - - - 8a1fcd4f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Incorporate link stripping to output diffing mechanism. - - - - - 37dba2bc by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement footer-stripping logic. - - - - - 9cd52120 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Add missing dependencies in Cabal configuration file. - - - - - e0f83c6e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix issue with output being printed in incorrect order. - - - - - 0a94fbb0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to run tests without generating diff. - - - - - 76a58c6f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor HTML test suite boilerplate to external package. - - - - - af41e6b0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utilities for storing directory configuration. - - - - - d8f0698f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move IO-dependent config of HTML test suite to test package. - - - - - 17369fa0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Enable all compiler warnings in Haddock test package configuration. - - - - - 9d03b47a by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move Haddock runner of HTML test suite to Haddock test package. - - - - - 4b3483c5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 03754194 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience wrappers to simplify in test entry points. - - - - - 27476ab7 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adjust module visibility and items they export. - - - - - c40002ba by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Remove no longer useful test option. - - - - - 55ab2541 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Change extension of test files used for diffing. - - - - - 136bf4e4 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor and simplify XHTML helper module of test package. - - - - - 69f7e3df by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix typo in link stripper of HTML test suite runner. - - - - - 0c3c1c6b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience script for running specific HTML tests. - - - - - 489e1b05 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement utility functions for conditional link stripping. - - - - - 0f985dc3 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt `hypsrc-test` module to work with new testing framework. - - - - - 927406f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement output accepting mechanism in test package. - - - - - 8545715e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utility function for recursive obtaining directory contents. - - - - - cb70381f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 019599b5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix path handling in test runner. - - - - - 399b985b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to specify ignored files for test output. - - - - - 41b3d93d by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt HTML test runner to use new ignoring functionality. - - - - - e2091c8b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix bug with not all test output files being checked. - - - - - b22134f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Specify ignored files for hyperlinker source test runner. - - - - - 3301dfa1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Copy test runner script for hyperlinked source case. - - - - - d39a6dfa by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner invoking Haddock in incorrect mode. - - - - - f32c8ff3 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix path handling in test module loader. - - - - - 10f94ee9 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make test runner ignore test packages with no modules. - - - - - 5dc4239c by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create test runner entry points for LaTeX test suite. - - - - - 58d1f7cf by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with unnecessary checking old test output. - - - - - c7ce76e1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Re-implement test acceptance functionality. - - - - - 13bbabe8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix warning about no longer needed definition. - - - - - 958a99b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Adapt Cabal configuration to execute LaTeX suite with new runner. - - - - - 550ff663 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Setup test suite for Hoogle backend. - - - - - 3aa969c4 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make Hoogle backend create output directory if needed. - - - - - eb085b02 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Add appropriate .gitignore entry and configure Hoogle test suite. - - - - - a50bf915 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner failing when run on multiple test packages. - - - - - bf5368b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create simple test cases for Hoogle backend. - - - - - 6121ba4b by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create helper function for conversion between XML and XHTML. - - - - - cb516061 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Refactor existing code to use XHTML printer instead of XML one. - - - - - e2de8c82 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Improve portability of test runner scripts. - - - - - 9563e774 by Łukasz Hanuszczak at 2015-08-22T23:43:16+02:00 Remove redundant import statement. - - - - - 55353df1 by Łukasz Hanuszczak at 2015-08-24T23:09:20+02:00 Fix bug with accepting to non-existing directory. - - - - - 00a334ca by Łukasz Hanuszczak at 2015-08-24T23:09:47+02:00 Accept output for Hoogle and LaTeX backends. - - - - - 29191d8b by Łukasz Hanuszczak at 2015-08-24T23:14:18+02:00 Get rid of obsolete testing utilities. - - - - - bbb25db3 by Łukasz Hanuszczak at 2015-08-24T23:18:50+02:00 Update sandbox setup guide to work with Haddock test package. - - - - - cfd45248 by Łukasz Hanuszczak at 2015-08-24T23:51:30+02:00 Make Travis aware of Haddock test package. - - - - - 74185b7a by Łukasz Hanuszczak at 2015-08-25T17:41:59+02:00 Fix test suite failure when used with Stack. - - - - - 18769697 by Łukasz Hanuszczak at 2015-08-25T18:02:09+02:00 Add sample Stack setup to the hacking guide. - - - - - 22715eeb by Łukasz Hanuszczak at 2015-08-25T18:04:47+02:00 Fix Markdown formatting of README file. - - - - - b49ec386 by Łukasz Hanuszczak at 2015-08-25T18:13:36+02:00 Setup Haddock executable path in Travis configuration. - - - - - 5d29eb03 by Eric Seidel at 2015-08-30T09:55:58-07:00 account for changes to ipClass - - - - - f111740a by Ben Gamari at 2015-09-02T13:20:37+02:00 Merge pull request haskell/haddock#443 from bgamari/ghc-head account for changes to ipClass - - - - - a2654bf6 by Jan Stolarek at 2015-09-03T01:32:57+02:00 Follow changes from haskell/haddock#6018 - - - - - 2678bafe by Richard Eisenberg at 2015-09-21T12:00:47-04:00 React to refactoring CoAxiom branch lists. - - - - - ebc56e24 by Edward Z. Yang at 2015-09-21T11:53:46-07:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4a8c4198 by Tamar Christina at 2015-09-27T13:59:08+02:00 Create Process: removed PhaseFailed - - - - - 7e99b790 by Oleg Grenrus at 2015-09-27T20:52:10+03:00 Generate docs for orphan instances - - - - - 32e932e2 by Oleg Grenrus at 2015-09-28T07:21:11+03:00 Have source links for orphan instances - - - - - c2eb9f4f by Oleg Grenrus at 2015-09-28T07:24:58+03:00 Print orphan instances header only if required - - - - - ff96f978 by Oleg Grenrus at 2015-09-28T07:40:54+03:00 Add orphan instances link to contents box - - - - - d72490a6 by Oleg Grenrus at 2015-09-28T16:37:44+03:00 Fix orphan instance collapsing - - - - - 25d3dfe5 by Ben Gamari at 2015-10-03T12:38:09+02:00 Merge pull request haskell/haddock#448 from Mistuke/fix-silent-death-of-runInteractive Remove PhaseFailed - - - - - 1e45e43b by Edward Z. Yang at 2015-10-11T13:10:10-07:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b1370ac1 by Adam Gundry at 2015-10-16T16:26:42+01:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 60bef421 by Simon Peyton Jones at 2015-10-26T12:52:36+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 4c1898ca by Simon Peyton Jones at 2015-10-27T14:24:56+00:00 Track change to PatSyn.patSynSig - - - - - 25108e85 by Simon Peyton Jones at 2015-10-27T17:34:18+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - 693643ac by Ben Gamari at 2015-10-28T14:33:06+01:00 Account for Typeable changes The treatment of type families changed. - - - - - cd7c2221 by Simon Peyton Jones at 2015-10-30T13:03:51+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - 712032cb by Herbert Valerio Riedel at 2015-10-31T11:01:45+01:00 Relax upper bound on `base` to allow base-4.9 - - - - - 0bfa0475 by Simon Peyton Jones at 2015-10-31T19:08:13+00:00 More adaption to wildcard-refactor - - - - - 0a3c0cb7 by Simon Peyton Jones at 2015-10-31T22:14:43+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - c4fd4ec9 by Alan Zimmerman at 2015-11-01T11:16:34+01:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 42cdd882 by Matthew Pickering at 2015-11-06T20:02:16+00:00 Change for IEThingWith - - - - - f368b7be by Ben Gamari at 2015-11-11T11:35:51+01:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - e32965b8 by Simon Peyton Jones at 2015-11-13T12:18:17+00:00 Merge with origin/head - - - - - ebcf795a by Edward Z. Yang at 2015-11-13T21:56:27-08:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4e23989f by Simon Peyton Jones at 2015-11-18T11:32:54+00:00 Wibbles to Haddock - - - - - 2289cd4a by Simon Peyton Jones at 2015-11-20T23:12:49+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor - - - - - 695975a6 by Alan Zimmerman at 2015-11-21T21:16:12+02:00 Update to match GHC wip/T11019 - - - - - bbba21e7 by Simon Peyton Jones at 2015-11-23T13:54:31+00:00 merge with origin/ghc-head - - - - - 3d664258 by Simon Peyton Jones at 2015-11-23T17:17:18+00:00 Wibble - - - - - e64cf586 by Herbert Valerio Riedel at 2015-12-05T00:29:55+01:00 Canonicalise Monad instances - - - - - a2de15a7 by Alan Zimmerman at 2015-12-05T17:33:52+02:00 Matching changes for haskell/haddock#11028 - - - - - cc29a3e4 by Alan Zimmerman at 2015-12-05T19:45:33+02:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 95dd15d1 by Richard Eisenberg at 2015-12-11T17:33:39-06:00 Update for type=kinds - - - - - cb5fd9ed by Herbert Valerio Riedel at 2015-12-14T15:07:30+00:00 Bump versions for ghc-7.11 - - - - - 4f286d96 by Simon Peyton Jones at 2015-12-14T15:10:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 13ea2733 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 098df8b8 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track changes in HsSyn for quasi-quotes - - - - - 716a64de by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track change in API of TyCon - - - - - 77a66bca by Adam Gundry at 2015-12-14T15:10:58+00:00 Track API changes to support empty closed type familes - - - - - f2808305 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track the new location of setRdrNameSpace - - - - - ba8b08a4 by Alan Zimmerman at 2015-12-14T15:10:59+00:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - a4ded87e by Thomas Winant at 2015-12-14T15:14:05+00:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 25c78107 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: print correct strictness marks - - - - - 6cbc41c4 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: changes in HsBang type - - - - - ad46821a by Alan Zimmerman at 2015-12-14T15:14:06+00:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - abc0ae5b by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 3308d06c by Thomas Miedema at 2015-12-14T15:14:07+00:00 Follow changes in GHC build system - - - - - 6c763deb by Eric Seidel at 2015-12-14T15:14:07+00:00 account for changes to ipClass - - - - - ae5b4eac by Jan Stolarek at 2015-12-14T15:17:00+00:00 Follow changes from haskell/haddock#6018 - - - - - ffbc40e0 by Richard Eisenberg at 2015-12-14T15:17:02+00:00 React to refactoring CoAxiom branch lists. - - - - - d1f531e9 by Edward Z. Yang at 2015-12-14T15:17:02+00:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 79f73754 by Tamar Christina at 2015-12-14T15:17:02+00:00 Create Process: removed PhaseFailed - - - - - 3d37bebb by Edward Z. Yang at 2015-12-14T15:20:46+00:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 5f8a9e44 by Adam Gundry at 2015-12-14T15:20:48+00:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 79dda70f by Simon Peyton Jones at 2015-12-14T15:26:02+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 959930fb by Simon Peyton Jones at 2015-12-14T15:37:50+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - e18a8df5 by Simon Peyton Jones at 2015-12-14T15:37:52+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - aa35ab52 by Simon Peyton Jones at 2015-12-14T15:40:18+00:00 More adaption to wildcard-refactor - - - - - 8ceef94b by Simon Peyton Jones at 2015-12-14T15:46:04+00:00 Track change to PatSyn.patSynSig - - - - - cd81e83d by Ben Gamari at 2015-12-14T15:46:06+00:00 Account for Typeable changes The treatment of type families changed. - - - - - 63c9117c by Herbert Valerio Riedel at 2015-12-14T15:46:34+00:00 Relax upper bound on `base` to allow base-4.9 - - - - - a484c613 by Alan Zimmerman at 2015-12-14T15:47:46+00:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 2c26fa51 by Matthew Pickering at 2015-12-14T15:47:47+00:00 Change for IEThingWith - - - - - 593baa0f by Ben Gamari at 2015-12-14T15:49:21+00:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - b6b5ca78 by Edward Z. Yang at 2015-12-14T15:49:54+00:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b5b0e072 by Alan Zimmerman at 2015-12-14T15:54:20+00:00 Update to match GHC wip/T11019 - - - - - 14ddeb68 by Simon Peyton Jones at 2015-12-14T15:54:22+00:00 Wibble - - - - - 10a90ad8 by Herbert Valerio Riedel at 2015-12-14T15:54:22+00:00 Canonicalise Monad instances - - - - - ed68ac50 by Alan Zimmerman at 2015-12-14T15:55:48+00:00 Matching changes for haskell/haddock#11028 - - - - - 3f7e5a2d by Alan Zimmerman at 2015-12-14T15:55:49+00:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 6543a73f by Richard Eisenberg at 2015-12-14T15:59:55+00:00 Update for type=kinds - - - - - 193a5c48 by Matthew Pickering at 2015-12-14T18:17:00+00:00 Changes to compile with 8.0 - - - - - add669ec by Matthew Pickering at 2015-12-14T18:47:12+00:00 Warnings - - - - - 223f3fb4 by Ben Gamari at 2015-12-15T23:45:05+01:00 Update for D1200 - - - - - d058388f by Ben Gamari at 2015-12-16T05:40:17-05:00 Types: Add Outputable[Bndr] DocName instances - - - - - 62ecd7fb by Ben Gamari at 2015-12-16T09:23:09-05:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ddbc187a by Ben Gamari at 2015-12-16T17:54:55+01:00 Update for D1200 - - - - - cec83b52 by Ben Gamari at 2015-12-16T17:54:55+01:00 Types: Add Outputable[Bndr] DocName instances - - - - - d12ecc98 by Ben Gamari at 2015-12-16T17:54:55+01:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ada1616f by Ben Gamari at 2015-12-16T17:54:58+01:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a4f0383d by Ben Gamari at 2015-12-16T23:32:38+01:00 Fix Hyperlinker GHC.con_names is now GHC.getConNames - - - - - a10e6849 by Ben Gamari at 2015-12-20T00:54:11+01:00 Merge remote-tracking branch 'mrhania/testing-framework-improvements' into ghc-head - - - - - f078b4fd by Ben Gamari at 2015-12-20T00:59:51+01:00 test: Compatibility with Cabal 1.23 - - - - - 88a511a9 by Ben Gamari at 2015-12-20T01:14:35+01:00 Merge remote-tracking branch 'phadej/orphans' into ghc-head - - - - - 4e250f36 by Ben Gamari at 2015-12-20T01:14:52+01:00 Add html-test for orphan instances output - - - - - 87fffbad by Alan Zimmerman at 2015-12-20T09:50:42+02:00 Update for GHC trac#11258 Adding locations to RdrName in FieldOcc and AmbiguousFieldOcc - - - - - 6b7e51c9 by idontgetoutmuch at 2015-12-20T21:01:47+00:00 Merge pull request haskell/haddock#1 from haskell/ghc-head Ghc head - - - - - 229c1fb5 by Dominic Steinitz at 2015-12-21T07:19:16+00:00 Handle inline math with mathjax. - - - - - 57902d66 by Dominic Steinitz at 2015-12-21T08:07:11+00:00 Fix the documentation for haddock itself. Change notation and add support for inline math. Allow newlines in display math. Add a command line option for the mathjax url (you might want to use a locally installed version). Rebase tests because of extra url and version change. Respond to (some of the) comments. Fix warnings in InterfaceFile.hs - - - - - 0e69f236 by Herbert Valerio Riedel at 2015-12-21T18:30:43+01:00 Fix-up left-over assumptions of GHC 7.12 into GHC 8.0 - - - - - c67f8444 by Simon Peyton Jones at 2015-12-22T16:26:56+00:00 Follow removal of NamedWildCard from HsType - - - - - da40327a by Ben Gamari at 2015-12-23T14:15:28+01:00 html-test/Operators: Clear up ambiguous types For reasons that aren't entirely clear a class with ambiguous types was accepted by GHC <8.0. I've added a functional dependency to clear up this ambiguity. - - - - - 541b7fa4 by Ben Gamari at 2015-12-23T14:18:51+01:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 0febc947 by Ben Gamari at 2015-12-24T00:30:20+01:00 hoogle-test/AssocTypes: Allow AmbiguousTypes GHC 8.0 complains otherwise - - - - - 25810841 by Ben Gamari at 2015-12-24T00:33:18+01:00 OrphanInstances: Accept test output - - - - - 841987f3 by Ben Gamari at 2015-12-25T11:03:11+01:00 Merge remote-tracking branch 'idontgetoutmuch/ghc-head' into ghc-head - - - - - 358391f0 by Ben Gamari at 2015-12-26T10:44:50+01:00 Add missing import - - - - - a8896885 by Ben Gamari at 2015-12-26T10:45:27+01:00 travis: Use Travis containers - - - - - 85e82134 by Herbert Valerio Riedel at 2015-12-30T17:25:39+01:00 tweak version bounds for GHC-8.1 - - - - - 672a5f75 by randen at 2016-01-01T23:45:25-08:00 The Haddock part for fully gcc-like response files " driver/Main.hs * Moved the response file handling into ResponseFile.hs, updating import section as appropriate. * driver/ResponseFile.hs * New file. In anticipation that maybe some day this could be provided by another library, and to make it possible to unit test, this functionality is pulled out of the Main.hs module, and expanded to support the style/format of response files which gcc uses. * The specification for the format of response files which gcc generates and consumes, seems to be best derived from the gcc code itself (libiberty/argv.c), so that is what has been done here. * This is intended to fix haskell/haddock#379 * driver-test/Main.hs * New file for testing code in the driver source tree * driver-test/ResponseFileSpec.hs * Tests, adapted/adopted from the same gcc code where the escaping/unescaping is from, in the hspec style of unit tests * haddock.cabal * Add the driver-test test-suite. Introduces a new library dependency (upon hspec) for the haddock driver target in the haddock.cabal file, but practically, this should not be a problem as the haddock-api tests already depend on hspec. - - - - - 498781df by Ben Gamari at 2016-01-06T13:41:04+01:00 Version bumps and changelog - - - - - 8451e46a by Ben Gamari at 2016-01-06T13:47:17+01:00 Merge remote-tracking branch 'randen/bug468' - - - - - fb2d9181 by Ben Gamari at 2016-01-06T08:14:42-05:00 Add ResponseFile to OtherModules - - - - - 2cb2d2e3 by Ben Gamari at 2016-01-06T14:35:00+01:00 Merge branch 'master' into ghc-head - - - - - 913477d4 by Eric Seidel at 2016-01-11T14:57:57-08:00 deal with un-wiring of IP class - - - - - c557a4b3 by Alan Zimmerman at 2016-01-15T11:14:35+02:00 Update to match wip/T11430 in GHC - - - - - 3e135093 by Alan Zimmerman at 2016-01-16T18:21:59+01:00 Update to match wip/T11430 in GHC - - - - - c48ef2f9 by Ben Gamari at 2016-01-18T09:50:06+01:00 Merge remote-tracking branch 'gridaphobe/ghc-head' into ghc-head - - - - - 9138a1b0 by Eric Seidel at 2016-01-18T12:50:15+01:00 deal with un-wiring of IP class (cherry picked from commit 17388b0f0029d969d79353be7737eb01c7b8dc5f) - - - - - b48c172e by Joachim Breitner at 2016-01-19T00:11:38+01:00 Make sure --mathjax affects all written HTML files This fixes haskell/haddock#475. - - - - - af61fe63 by Ryan Scott at 2016-02-07T23:25:57+01:00 Render */# instead of TYPE 'Lifted/TYPE 'Unlifted (fixes haskell/haddock#473) - - - - - b6458693 by Ben Gamari at 2016-02-07T23:29:27+01:00 Merge pull request haskell/haddock#477 from haskell/issue-475 Make sure --mathjax affects all written HTML files - - - - - adcc0071 by Ben Gamari at 2016-02-07T23:34:52+01:00 Merge branch 'master' into ghc-head - - - - - d0404e61 by Ben Gamari at 2016-02-08T12:46:49+01:00 doc: Switch to Sphinx - - - - - acb153b3 by Ben Gamari at 2016-02-08T12:46:56+01:00 Document --use-unicode flag - - - - - c20bdf1d by Ben Gamari at 2016-02-08T13:41:24+01:00 Fix GHC and haddock-library dependency bounds - - - - - 8d946801 by Ben Gamari at 2016-02-08T14:54:56+01:00 testsuite: Rework handling of output sanitization Previously un-cleaned artifacts were kept as reference output, making it difficult to tell what has changed and causing spurious changes in the version control history. Here we rework this, cleaning the output during acceptance. To accomplish this it was necessary to move to strict I/O to ensure the reference handle was closed before accept attempts to open the reference file. - - - - - c465705d by Ben Gamari at 2016-02-08T15:36:05+01:00 test: Compare on dump For reasons I don't understand the Xml representations differ despite their textual representations being identical. - - - - - 1ec0227a by Ben Gamari at 2016-02-08T15:36:05+01:00 html-test: Accept test output - - - - - eefbd63a by Ben Gamari at 2016-02-08T15:36:08+01:00 hypsrc-test: Accept test output And fix impredicative Polymorphism testcase. - - - - - d1df4372 by Ben Gamari at 2016-02-08T15:40:44+01:00 Merge branch 'fix-up-testsuite' - - - - - 206a3859 by Phil Ruffwind at 2016-02-08T17:51:21+01:00 Move the permalinks to "#" on the right side Since pull request haskell/haddock#407, the identifiers have been permalinked to themselves, but this makes it difficult to copy the identifier by double-clicking. To work around this usability problem, the permalinks are now placed on the far right adjacent to "Source", indicated by "#". Also, 'namedAnchor' now uses 'id' instead of 'name' (which is obsolete). - - - - - 6c89fa03 by Phil Ruffwind at 2016-02-08T17:54:44+01:00 Update tests for previous commit - - - - - effaa832 by Ben Gamari at 2016-02-08T17:56:17+01:00 Merge branch 'anchors-redux' - - - - - 9a2bec90 by Ben Gamari at 2016-02-08T17:58:40+01:00 Use -fprint-unicode-syntax when --use-unicode is enabled This allows GHC to render `*` as its Unicode representation, among other things. - - - - - 28ecac5b by Ben Gamari at 2016-02-11T18:53:03+01:00 Merge pull request haskell/haddock#480 from bgamari/sphinx Move documentation to ReStructuredText - - - - - 222e5920 by Ryan Scott at 2016-02-11T15:42:42-05:00 Collapse type/data family instances by default - - - - - a80ac03b by Ryan Scott at 2016-02-11T20:17:09-05:00 Ensure expanded family instances render correctly - - - - - 7f985231 by Ben Gamari at 2016-02-12T10:04:22+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - d4eda086 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Various cleanups - - - - - 79bee48d by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show kind signatures for type family variables Addresses GHC haskell/haddock#11588. - - - - - b2981d98 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show 'where ...' after closed type family Seems like we should ideally show the actual equations as well but that seems like it would be a fair amount of work - - - - - cfc0e621 by Ben Gamari at 2016-02-18T22:48:12+01:00 Merge pull request haskell/haddock#483 from bgamari/T11588 Fix GHC haskell/haddock#11588 This fixes GHC haskell/haddock#11588: * Show where ... after closed type families * Show kind signatures on type family type variables - - - - - 256e8a0d by Ben Gamari at 2016-02-18T23:15:39+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 32402036 by Richard Eisenberg at 2016-02-24T13:21:44-05:00 Follow-on changes to support RuntimeRep - - - - - 2b1c572d by Matthew Pickering at 2016-03-04T21:04:02+00:00 Remove unused functions - - - - - eb906f50 by Richard Eisenberg at 2016-03-13T21:17:20+01:00 Follow-on changes to support RuntimeRep (cherry picked from commit ab954263a793d8ced734459d6194a5d89214b66c) - - - - - 8c34ef34 by Richard Eisenberg at 2016-03-14T23:47:23-04:00 Changes due to fix for GHC#11648. - - - - - 0e022014 by Richard Eisenberg at 2016-03-15T14:06:45+01:00 Changes due to fix for GHC#11648. (cherry picked from commit bb994de1ab0c76d1aaf1e39c54158db2526d31f1) - - - - - ed3f78ab by Rik Steenkamp at 2016-04-02T22:20:36+01:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 - - - - - d3210042 by Rik Steenkamp at 2016-04-04T15:43:32+02:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 (cherry picked from commit 3ddcbd6b8e6884bd95028381176eb33bee6896fb) - - - - - 236eec90 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 692ee7e0 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. - - - - - 79619f57 by Ben Gamari at 2016-04-10T23:46:22+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. (cherry picked from commit c6d6a18d85e5e2d9bb5904e6919e8a8d7e31c4c5) - - - - - 3358ccb4 by Ben Gamari at 2016-04-10T23:47:27+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 264949b1 by Ben Gamari at 2016-04-16T17:50:23+02:00 Merge pull request haskell/haddock#482 from RyanGlScott/ghc-head Collapse type/data family instances by default - - - - - 478c483a by Ben Gamari at 2016-04-16T17:51:09+02:00 Merge pull request haskell/haddock#489 from mpickering/unused-functions Remove some unused functions - - - - - c94e55f0 by Ryan Scott at 2016-04-16T17:57:54+02:00 Collapse type/data family instances by default (cherry picked from commit 2da130a8db8f995c119b544fad807533236cf088) - - - - - 31e633d3 by Ryan Scott at 2016-04-16T17:58:06+02:00 Ensure expanded family instances render correctly (cherry picked from commit 1338b5d7c32939de6bbc31af0049477e4f847103) - - - - - 03e4d197 by Matthew Pickering at 2016-04-16T17:58:21+02:00 Remove unused functions (cherry picked from commit b89d1c2456bdb2d4208d94ded56155f7088a37d0) - - - - - ed4116f6 by Ben Gamari at 2016-04-20T10:46:57+02:00 ghc: Install files for needed --hyperlinked-source - - - - - 0be999c4 by Ben Gamari at 2016-04-20T11:37:54+02:00 ghc: Install files for needed --hyperlinked-source (cherry picked from commit 5c82c9fc2d21ddaae4a2470f1c375426968f19c6) - - - - - 4d17544c by Simon Peyton Jones at 2016-04-20T12:42:28+01:00 Track change to HsGroup This relates to a big GHC patch for Trac haskell/haddock#11348 - - - - - 1700a50d by Ben Gamari at 2016-05-01T13:19:27+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. - - - - - 0b7c8125 by Ben Gamari at 2016-05-01T13:21:43+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. (cherry picked from commit 609018dd09c4ffe27f9248b2d8b50f6196cd42b9) - - - - - af115ce0 by Ryan Scott at 2016-05-04T22:15:50-04:00 Render Haddocks for derived instances Currently, one can document top-level instance declarations, but derived instances (both those in `deriving` clauses and standalone `deriving` instances) do not enjoy the same privilege. This makes the necessary changes to the Haddock API to enable rendering Haddock comments for derived instances. This is part of a fix for Trac haskell/haddock#11768. - - - - - 76fa1edc by Ben Gamari at 2016-05-10T18:13:25+02:00 haddock-test: A bit of refactoring for debuggability - - - - - 7d4c4b20 by Ben Gamari at 2016-05-10T18:13:25+02:00 Create: Mark a comment as TODO - - - - - 2a6d0c90 by Ben Gamari at 2016-05-10T18:13:25+02:00 html-test: Update reference output - - - - - bd60913d by Ben Gamari at 2016-05-10T18:13:25+02:00 hypsrc-test: Fix reference file path in cabal file It appears the haddock insists on prefixing --hyperlinked-sourcer output with directory which the source appeared in. - - - - - c1548057 by Ben Gamari at 2016-05-10T18:22:12+02:00 doc: Update extra-source-files in Cabal file - - - - - 41d5bae3 by Ben Gamari at 2016-05-10T18:29:21+02:00 Bump versions - - - - - ca75b779 by Ben Gamari at 2016-05-11T16:03:44+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 4e3cfd62 by Ben Gamari at 2016-05-11T16:06:45+02:00 Merge remote-tracking branch 'RyanGlScott/ghc-head' into ghc-head - - - - - a2379970 by Ben Gamari at 2016-05-11T23:15:11+02:00 doc: Add clean targets - - - - - f275212e by Ben Gamari at 2016-05-11T23:15:14+02:00 doc: Add html as an all-target for ghc Otherwise the html documentation won't be installed for binary-dist. - - - - - 388fc0af by Ben Gamari at 2016-05-12T09:49:12+02:00 Update CHANGES - - - - - bad81ad5 by Ben Gamari at 2016-05-12T09:49:38+02:00 Version bump - - - - - c01688a7 by Ben Gamari at 2016-05-12T10:04:58+02:00 Revert "Version bump" This bump was a bit premature. This reverts commit 7b238d9c5be9b07aa2d10df323b5c7b8d1634dc8. - - - - - 7ed05724 by Ben Gamari at 2016-05-12T10:05:33+02:00 doc: Fix GHC clean rule Apparently GHC's build system doesn't permit wildcards in clean paths. - - - - - 5d9611f4 by Ben Gamari at 2016-05-12T17:43:50+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 653566b2 by Ben Gamari at 2016-05-14T09:57:31+02:00 Version bump to 2.17.2 - - - - - b355c439 by Ben Gamari at 2016-05-14T09:57:51+02:00 doc: Use `$(MAKE)` instead of `make` This is necessary to ensure we use gmake. - - - - - 8a18537d by Ben Gamari at 2016-05-14T10:15:45+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - b3290ef1 by Sebastian Meric de Bellefon at 2016-05-14T11:29:47-04:00 Fix haskell/haddock#303. Hide footer when printing The "Produced by Haddock" footer was overlapping the page's body when printing. This patch hides the footer with a css media rule. - - - - - b4a76f89 by Sebastian Meric de Bellefon at 2016-05-15T02:12:46-04:00 Fix haskell/haddock#280. Parsing of module header The initial newlines were counted as indentation spaces, thus disturbing the parsing of next lines - - - - - ba797c9e by Ben Gamari at 2016-05-16T14:53:46+02:00 doc: Vendorize alabaster Sphinx theme Alabaster is now the default sphinx theme and is a significant improvement over the previous default that it's worthproviding it when unavailable (e.g. Sphinx <1.3). - - - - - c9283e44 by Ben Gamari at 2016-05-16T14:55:17+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 1c9ea198 by Sebastian Méric de Bellefon at 2016-05-16T12:30:40-04:00 Merge pull request haskell/haddock#502 from Helkafen/master Fix haskell/haddock#303. Hide footer when printing - - - - - 33631016 by Ben Gamari at 2016-05-16T19:56:11+02:00 Revert "doc: Vendorize alabaster Sphinx theme" This ended up causes far too many issues to be worthwhile. We'll just have to live with inconsistent haddock documentation. This reverts commit cec21957001143794e71bcd9420283df18e7de40. - - - - - 93317d26 by Ben Gamari at 2016-05-16T19:56:11+02:00 cabal: Fix README path - - - - - c8695b22 by Ben Gamari at 2016-05-16T19:58:51+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 0b50eaaa by Ben Gamari at 2016-05-16T21:02:08+02:00 doc: Use whichever theme sphinx deems appropriate - - - - - 857c1c9c by Ben Gamari at 2016-05-16T21:07:08+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 15fc5637 by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Remove redundant imports - - - - - 132ddc6a by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Better debug output For tracking down haskell/haddock#505 - - - - - 2252a149 by Ben Gamari at 2016-05-22T12:43:59+02:00 Don't consider default class ops when looking for decls When we are looking for an operation within a class we don't care about `default`-type declarations. This was the cause of haskell/haddock#505. - - - - - 4886b2ec by Oleg Grenrus at 2016-05-24T16:19:48+03:00 UnfelpfulSpan line number omitted Kind of resolves https://github.com/haskell/haddock/issues/508 - - - - - a4befd36 by Oleg Grenrus at 2016-05-24T16:53:35+03:00 Change Hyperlinked lexer to know about DataKinds ticks - - - - - f45cb52e by David Feuer at 2016-05-24T18:48:53-04:00 Make parser state a newtype Previously, it was `data` wrapping a `Maybe`, which seems a bit silly. Obviously, this can be changed back if anyone wants to add more fields some day. - - - - - 05013dd7 by Sebastian Meric de Bellefon at 2016-05-24T22:03:55-04:00 remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) Frames are a bit broken, ignored by Hackage, and considered obsolete in general. This patch disables frames generation. The mini_*.html files are still used in the synopsis. - - - - - b8163a88 by Ben Gamari at 2016-05-25T14:44:15+02:00 Merge pull request haskell/haddock#507 from bgamari/T505 Fix haskell/haddock#505 - - - - - ea1b30c6 by Sebastian Meric de Bellefon at 2016-05-25T14:17:00-04:00 Update CHANGES - - - - - eddfc258 by Sebastian Méric de Bellefon at 2016-05-25T15:17:40-04:00 Merge pull request haskell/haddock#514 from Helkafen/frames remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) - - - - - 0e506818 by Alex Biehl at 2016-05-26T12:43:09+02:00 Remove misplaced haddock comment - - - - - a07d28c0 by Ben Gamari at 2016-05-27T11:34:59+02:00 Merge pull request haskell/haddock#515 from alexbiehl/master Remove misplaced haddock comment - - - - - 9001d267 by Ben Gamari at 2016-05-27T11:35:46+02:00 Merge pull request haskell/haddock#513 from treeowl/newtype-since Make parser state a newtype - - - - - 74e1a018 by Sebastian Méric de Bellefon at 2016-05-28T17:28:15-04:00 Merge pull request haskell/haddock#504 from Helkafen/issue-280 Fix haskell/haddock#280. Parsing of module header - - - - - 37557f4f by Alan Zimmerman at 2016-05-29T23:36:50+02:00 Matching changes for haskell/haddock#12105 - - - - - 7d09e5d6 by Sebastian Meric de Bellefon at 2016-06-03T18:07:48-04:00 Version bumps (2.17.3, 1.4.2) - - - - - 85b4bc15 by Sebastian Méric de Bellefon at 2016-06-06T18:35:13-04:00 Merge pull request haskell/haddock#521 from Helkafen/master Version bumps (2.17.3, 1.4.2) - - - - - e95f0dee by Sebastian Meric de Bellefon at 2016-06-06T19:11:35-04:00 publish haddock-test library - - - - - 4de40586 by Sebastian Méric de Bellefon at 2016-06-06T20:26:30-04:00 Merge pull request haskell/haddock#512 from phadej/oleg-fixes Fixes for haskell/haddock#508 and haskell/haddock#510 - - - - - ddfd0789 by Dominic Steinitz at 2016-06-09T09:27:28+01:00 Documentation for LaTeX markup. - - - - - 697a503a by Dominic Steinitz at 2016-06-09T09:33:59+01:00 Fix spelling mistake. - - - - - 246f6fff by Dominic Steinitz at 2016-06-09T09:37:15+01:00 Camel case MathJax. - - - - - 4684bd23 by Dominic Steinitz at 2016-06-09T09:44:53+01:00 Fix math typo and add link. - - - - - f20c037c by Simon Peyton Jones at 2016-06-13T18:26:03+01:00 Follow changes to LHsSigWcType - - - - - 0c58996d by Simon Peyton Jones at 2016-06-15T12:56:01+01:00 Follow GHC re-adding FunTy - - - - - 401b5ca7 by Sebastian Méric de Bellefon at 2016-06-15T12:16:47-04:00 Merge pull request haskell/haddock#525 from idontgetoutmuch/master Documentation for LaTeX markup. - - - - - 92d263b7 by Sebastian Méric de Bellefon at 2016-06-15T12:17:29-04:00 Merge pull request haskell/haddock#522 from Helkafen/master publish haddock-test library - - - - - 0953a2ca by Sebastian Meric de Bellefon at 2016-06-16T00:46:46-04:00 Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 65453e14 by Ben Gamari at 2016-06-16T11:16:32+02:00 ocean: Ensure that synopsis fully covers other content Previously MathJax content was being rendered on top of the synopsis due to ambiguous z-ordering. Here we explicitly give the synopsis block a higher z-index to ensure it is rendered on top. Fixes haskell/haddock#531. - - - - - 68e411a1 by Sebastian Méric de Bellefon at 2016-06-16T23:34:39-04:00 Merge pull request haskell/haddock#534 from bgamari/T531 ocean: Ensure that synopsis fully covers other content - - - - - fad6491b by Sebastian Méric de Bellefon at 2016-06-18T23:57:20-04:00 Merge pull request haskell/haddock#533 from Helkafen/master Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 6108e21b by Sebastian Meric de Bellefon at 2016-06-22T23:08:28-04:00 do not create empty src directory Fix haskell/haddock#536. - - - - - 1ef23823 by Sebastian Méric de Bellefon at 2016-06-24T00:04:48-04:00 Merge pull request haskell/haddock#537 from Helkafen/master do not create empty src directory - - - - - 966baa96 by Omari Norman at 2016-06-29T21:59:34-04:00 Add $ as a special character If this character is not escaped, documentation built with Haddock 2.17.2 will fail. This was not an issue with 2.16 series, which causes builds to fail and there is nothing in the docs or error message giving a clue about why builds that used to succeed now don't. - - - - - 324adb60 by Ben Gamari at 2016-07-01T12:18:51+02:00 GhcUtils: Changes for multi-pattern signatures - - - - - d7571675 by Ömer Sinan Ağacan at 2016-07-21T13:30:47+02:00 Add support for unboxed sums - - - - - 29d0907b by Simon Marlow at 2016-07-22T13:55:48+01:00 Disable NFData instances for GHC types when GHC >= 8.2 - - - - - 702d95f3 by Simon Marlow at 2016-08-02T15:57:30+02:00 Disable NFData instances for GHC types when GHC >= 8.0.2 (cherry picked from commit a3309e797c42dae9bccdeb17ce52fcababbaff8a) - - - - - f4fa79c3 by Ben Gamari at 2016-08-07T13:51:18+02:00 ghc.mk: Don't attempt to install html/frames.html The frames business has been removed. - - - - - 9cd63daf by Ben Gamari at 2016-08-07T13:51:40+02:00 Haddock.Types: More precise version guard This allows haddock to be built with GHC 8.0.2 pre-releases. - - - - - f3d7e03f by Mateusz Kowalczyk at 2016-08-29T20:47:45+01:00 Merge pull request haskell/haddock#538 from massysett/master Add $ as a special character - - - - - 16dbf7fd by Bartosz Nitka at 2016-09-20T19:44:04+01:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 - - - - - 7c31c1ff by Bartosz Nitka at 2016-09-27T17:32:22-04:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 (cherry picked from commit 073d899a8f94ddec698f617a38d3420160a7fd0b) - - - - - 33a90dce by Ryan Scott at 2016-09-30T20:53:41-04:00 Haddock changes for T10598 See https://ghc.haskell.org/trac/ghc/ticket/10598 - - - - - 1f32f7cb by Ben Gamari at 2016-10-13T20:01:26-04:00 Update for refactoring of NameCache - - - - - 1678ff2e by Ben Gamari at 2016-11-15T17:42:48-05:00 Bump upper bound on base - - - - - 9262a7c5 by Alan Zimmerman at 2016-12-07T21:14:28+02:00 Match changes in GHC wip/T3384 branch - - - - - ac0eaf1a by Ben Gamari at 2016-12-09T09:48:41-05:00 haddock-api: Don't use stdcall calling convention on 64-bit Windows See GHC haskell/haddock#12890. - - - - - 04afe4f7 by Alan Zimmerman at 2016-12-12T20:07:21+02:00 Matching changes for GHC wip/T12942 - - - - - e1d1701d by Ben Gamari at 2016-12-13T16:50:41-05:00 Bump base upper bound - - - - - 3d3eacd1 by Alan Zimmerman at 2017-01-10T16:59:38+02:00 HsIParamTy now has a Located name - - - - - 7dbceefd by Kyrill Briantsev at 2017-01-12T13:23:50+03:00 Prevent GHC API from doing optimization passes. - - - - - d48d1e33 by Richard Eisenberg at 2017-01-19T08:41:41-05:00 Upstream changes re levity polymorphism - - - - - 40c25ed6 by Alan Zimmerman at 2017-01-26T15:16:18+02:00 Changes to match haskell/haddock#13163 in GHC - - - - - 504f586d by Ben Gamari at 2017-02-02T17:19:37-05:00 Kill remaining static flags - - - - - 49147ea0 by Justus Adam at 2017-03-02T15:33:34+01:00 Adding MDoc to exports of Documentation.Haddock - - - - - 1cfba9b4 by Justus Adam at 2017-03-09T11:41:44+01:00 Also exposing toInstalledIface - - - - - 53f0c0dd by Ben Gamari at 2017-03-09T13:10:08-05:00 Bump for GHC 8.3 - - - - - c7902d2e by Ben Gamari at 2017-03-09T23:46:02-05:00 Bump for GHC 8.2 - - - - - 4f3a74f8 by Ben Gamari at 2017-03-10T10:21:55-05:00 Merge branch 'ghc-head' - - - - - e273b72f by Richard Eisenberg at 2017-03-14T13:34:04-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - 6ec3d436 by Richard Eisenberg at 2017-03-14T15:15:52-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - eee3cda1 by Ben Gamari at 2017-03-15T15:19:59-04:00 Adapt to EnumSet - - - - - 017cf58e by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 736d6773 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 475f84a0 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 13240b53 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - cd16d529 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 3bea97ae by Edward Z. Yang at 2017-03-15T22:50:46-07:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b2b051ce by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 0f082795 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 20ef63c9 by Edward Z. Yang at 2017-03-22T13:48:12-07:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 45692dcb by Edward Z. Yang at 2017-03-22T14:11:25-07:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4eae8caf by Ben Gamari at 2017-03-23T09:25:33-04:00 Merge commit '240bc38b94ed2d0af27333b23392d03eeb615e82' into HEAD - - - - - 0bbe03f5 by Ben Gamari at 2017-03-23T09:27:28-04:00 haddock-api: Bump bound on GHC - - - - - 65f3ac9d by Alex Biehl at 2017-03-23T17:36:11+01:00 Merge pull request haskell/haddock#581 from JustusAdam/master Adding more exports to Documentation.Haddock - - - - - 37d49a47 by Alex Biehl at 2017-03-23T17:39:14+01:00 Merge pull request haskell/haddock#568 from awson/ghc-head Prevent GHC API from doing optimization passes. - - - - - 1ed047e4 by Brian Huffman at 2017-03-23T17:45:58+01:00 Print any user-supplied kind signatures on type parameters. This applies to type parameters on data, newtype, type, and class declarations, and also to forall-bound type vars in type signatures. - - - - - 1b78ca5c by Brian Huffman at 2017-03-23T17:45:58+01:00 Update test suite to expect kind annotations on type parameters. - - - - - a856b162 by Alex Biehl at 2017-03-23T17:49:32+01:00 Include travis build indication badge - - - - - 8e2e2c56 by Ben Gamari at 2017-03-23T17:20:08-04:00 haddock-api: Bump bound on GHC - - - - - 4d2d9995 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 26d6c150b31bc4580ab17cfd07b6e7f9afe10737) - - - - - a650e20f by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 930cfbe58e2e87f5a4d431d89a3c204934e6e858) - - - - - caa282c2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 2067a2d0afa9cef381d26fb7140b67c62f433fc0) - - - - - 49684884 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 0671abfe7e8ceae2269467a30b77ed9d9656e2cc) - - - - - 4dcfeb1a by Edward Z. Yang at 2017-03-23T17:20:08-04:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 3d77b373dd5807d5d956719dd7c849a11534fa6a) - - - - - 74dd19d2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 94610e9b446324f4231fa6ad4c6ac51e4eba8c0e) - - - - - a9b19a23 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 6cc832dfb1de6088a4abcaae62b25a7e944d55c3) - - - - - d3631064 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit bf3c4d72a0fda38561376eac7eda216158783267) - - - - - ef2148fc by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 07b88c5d4e79b87a319fbb08f8ea01dbb41063c1) - - - - - 2f29518b by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 4eb765ca4205c79539d60b7afa9b7e261a4a49fe) - - - - - 37de047d by Phil Ruffwind at 2017-04-03T11:57:14+02:00 Update MathJax URL MathJax is shutting down their CDN: https://www.mathjax.org/cdn-shutting-down/ They recommend migrating to cdnjs. - - - - - e9d24ba8 by David C. Turner at 2017-04-03T14:58:01+02:00 Add highlight for :target to ocean.css - - - - - 4819a202 by Alex Biehl at 2017-04-11T19:36:48+02:00 Allow base-4.10 for haddock-test - - - - - 44cec69c by Alex Biehl at 2017-04-11T19:39:22+02:00 cabal.project for haddock-api, haddock-library and haddock-test - - - - - 935d0f6a by Alex Biehl at 2017-04-11T19:46:29+02:00 Move dist scripts to scripts/ - - - - - 128e150c by Alex Biehl at 2017-04-11T20:34:46+02:00 Add haddock to cabal.project - - - - - cc8e08ea by Alex Biehl at 2017-04-11T20:35:08+02:00 Read files for hyperlinker eagerly This also exposes Documentation.Haddock.Utf8 - - - - - 152dda78 by Alex Biehl at 2017-04-11T20:37:06+02:00 Explicit import list ofr Control.DeepSeq in Haddock.Interface.Create - - - - - 501b33c4 by Kyrill Briantsev at 2017-04-11T21:01:42+02:00 Prevent GHC API from doing optimization passes. - - - - - c9f3f5ff by Alexander Biehl at 2017-04-12T16:36:53+02:00 Add @alexbiehl as maintaner - - - - - 76f214cc by Alex Biehl at 2017-04-13T07:27:18+02:00 Disable doctest with ghc-8.3 Currently doctest doesn't support ghc-head - - - - - 46b4f5fc by Edward Z. Yang at 2017-04-22T20:38:26-07:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f0555235 by Alex Biehl at 2017-04-25T10:08:48+02:00 Travis: Use ghc-8.2.1 on master - - - - - 966ea348 by Alex Biehl at 2017-04-25T10:32:01+02:00 Travis: Verbose cabal output cf. https://travis-ci.org/haskell/haddock/jobs/225512194#L377 - - - - - 36972bcd by Alex Biehl at 2017-04-25T10:40:43+02:00 Use travis_retry for cabal invocations - - - - - b3a09d2c by Alex Biehl at 2017-04-25T17:02:20+02:00 Use new MathJax URL in html-test 18ed871afb82560d5433b2f53e31b4db9353a74e switched to a new MathJax URL but didn't update the tests. - - - - - ae331e5f by Alexander Biehl at 2017-04-25T17:02:20+02:00 Expand signatures for class declarations - - - - - e573c65a by Alexander Biehl at 2017-04-25T17:02:20+02:00 Hoogle: Correctly print classes with associated data types - - - - - 3fc6be9b by Edward Z. Yang at 2017-04-25T17:02:20+02:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit a0c4790e15a2d3fab8d830eee8fcd639fe6d39c9) - - - - - 6725c060 by Herbert Valerio Riedel at 2017-04-25T17:02:20+02:00 `html-test --accept` deltas to reference samples - - - - - 7d444d61 by Alex Biehl at 2017-04-26T07:13:50+02:00 Remove anything related to obsolete frames mode - - - - - b888972c by Alex Biehl at 2017-04-26T07:49:10+02:00 Cherry-picked remaining commits from haddock-2.17.4-release (#603) * Release haddock/haddock-api 2.17.4 and haddock-library 1.4.3 * Set version bounds for haddock-library NB: This allows GHC 8.2.1's base * Set version bounds for haddock & haddock-api The version bounds support GHC 8.2 * Merge (temporary) v2.17.3 branch into v2.17 This allows us to delete the v2.17.3 branch * Fixup changelog * Pin down haddock-api to a single version as otherwise `haddock`'s package version has no proper meaning * fix source-repo spec for haddock-api - - - - - 4161099b by Alex Biehl at 2017-04-26T11:11:20+02:00 Update changelog to reflect news in HEAD - - - - - eed72cb8 by Alex Biehl at 2017-04-26T11:11:20+02:00 Markdownify changelog - - - - - 5815cea1 by Alex Biehl at 2017-04-26T11:32:33+02:00 Bump to 2.18.0 (#605) - - - - - a551d558 by Alex Biehl at 2017-04-29T22:00:25+02:00 Update attoparsec-0.12.1.1 to attoparsec-0.13.1.0 - - - - - ea164a8d by Sergey Vinokurov at 2017-04-29T22:42:36+02:00 Improve error message - - - - - 2e10122f by Alex Biehl at 2017-04-30T10:07:46+02:00 Correctly remember collapsed sections (#608) Now the "collapsed" cookie stores which sections have changed state instead of which are collapsed. - - - - - f9b24d99 by Alex Biehl at 2017-05-01T17:40:36+02:00 Lazily decode docMap and argMap (#610) These are only used in case of a doc reexport so most of the time decoding these is wasted work. - - - - - 2372af62 by Alex Biehl at 2017-05-01T21:59:23+02:00 Fix Binary instance for InstalledInterface (#611) (#610) introduced lazy decoding for docs from InstalledInterface but forgot to remove the original calls to get and put_ - - - - - 6c633c13 by Nathan Collins at 2017-05-11T11:47:55+02:00 Improve documenation of Haddock markup (#614) * Improve documentation of Haddock markup. - document that Haddock supports inferring types top-level functions with without type signatures, but also explain why using this feature is discouraged. Looks like this feature has been around since version 2.0.0.0 in 2008! - rework the "Module description" section: - move the general discussion of field formatting to the section intro and add examples illustrating the prose for multiline fields. - mention that newlines are preserved in some multiline fields, but not in others (I also noticed that commas in the `Copyright` field are not preserved; I'll look into this bug later). - add a subsection for the module description fields documentation, and put the field keywords in code formatting (double back ticks) instead of double quotes, to be consistent with the typesetting of keywords in other parts of the documentation. - mention that "Named chunks" are not supported in the long-form "Module description" documentation. - fix formatting of keywords in the "Module attributes" section. Perhaps these errors were left over from an automatic translation to ReST from some other format as part of the transition to using Sphinx for Haddock documentation? Also, add a missing reference here; it just said "See ?"! - update footnote about special treatment for re-exporting partially imported modules not being implemented. In my tests it's not implemented at all -- I tried re-exporting both `import B hiding (f)` and `import B (a, b)` style partial imports, and in both cases got the same result as with full imports `import B`: I only get a module reference. * Rework the `Controlling the documentation structure` section. My main goal was to better explain how to use Haddock without an export list, since that's my most common use case, but I hope I improved the section overall: - remove the incomplete `Omitting the export list` section and fold it into the other sections. In particular, summarize the differences between using and not using an export list -- i.e. control over what and in what order is documented -- in the section lead. - add "realistic" examples that use the structure markup, both with and without an export list. I wanted a realistic example here to capture how it can be useful to explain the relationship between a group of functions in a section, in addition to documenting their individual APIs. - make it clear that you can associate documentation chunks with documentation sections when you aren't using an export list, and that doing it in the most obvious way -- i.e. with `-- |`, as you can in the export list -- doesn't work without an export list. It took me a while to figure this out the first time, since the docs didn't explain it at all before. - add a "no export list" example to the section header section. - add more cross references. * Add examples of gotchas for markup in `@...@`. I'm not sure this will help anyone, since I think most people first learn about `@...@` by reading other people's Haddocks, but I've documented the mistakes which I've made and then gotten confused by. * Use consistent Capitalization of Titles. Some titles were in usual title caps, and others only had the first word capitalized. I chose making them all use title caps because that seems to make the cross references look better. - - - - - d4734f45 by Ben Gamari at 2017-05-12T20:36:08+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 93883f37 by Alex Biehl at 2017-05-12T21:02:33+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 5b8f179c by Alex Biehl at 2017-05-13T12:48:10+02:00 Consequently use inClass and notInClass in haddock-library (#617) These allow attoparsec to do some clever lookup optimization - - - - - 77984b82 by Doug Wilson at 2017-05-27T17:37:38+02:00 Don't enable compilation for template haskell (#624) This is no longer necessary after ghc commit 53c78be0aab76a3107c4dacbb1d177afacdd37fa - - - - - 5a3de2b4 by Doug Wilson at 2017-05-27T19:54:53+02:00 Improve Syb code (#621) Specialize.hs and Ast.hs are modified to have their Syb code not recurse into Name or Id in HsSyn types. Specialize.hs is refactored to have fewer calls to Syb functions. Syb.hs has some foldl calls replaced with foldl' calls. There is still a lot of performance on the floor of Ast.hs. The RenamedSource is traversed many times, and lookupBySpan is very inefficient. everywhereBut and lookupBySpan dominate the runtime whenever --hyperlinked-source is passed. - - - - - 3d35a949 by Alex Biehl at 2017-05-30T19:01:37+02:00 Clear fixme comment (#625) - - - - - 2a44bd0c by Alex Biehl at 2017-05-30T19:02:12+02:00 Make haddock-library and haddock-api warning free (#626) - - - - - bd1a0e42 by Alex Biehl at 2017-06-01T10:40:33+02:00 Include `driver-test/*.hs` sdist (#630) This lead to haskell/haddock#629. - - - - - 184a3ab6 by Doug Wilson at 2017-06-03T12:02:08+02:00 Disable pattern match warnings (#628) This disables the pattern match checker which can be very expensive in some cases. The disabled warnings include: * Opt_WarnIncompletePatterns * Opt_WarnIncompleteUniPatterns * Opt_WarnIncompletePatternsRecUpd * Opt_WarnOverlappingPatterns - - - - - 0cf68004 by Alex Biehl at 2017-06-03T20:37:28+02:00 Allow user defined signatures for pattern synonyms (#631) - - - - - 7f51a58a by Alex Biehl at 2017-06-04T11:56:38+02:00 Use NameSet for isExported check (#632) - - - - - d8f044a9 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Match new AST as per GHC wip/new-tree-one-param See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow - - - - - da1254e3 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Rename extension index tags - - - - - 538c7514 by Christiaan Baaij at 2017-06-09T08:26:43+02:00 Haddock support for bundled pattern synonyms (#627) * Haddock support for bundled pattern synonyms * Add fixities to bundled pattern synonyms * Add bundled pattern synonyms to the synopsis * Store bundled pattern fixities in expItemFixities * Add test for bundled pattern synonyms * Stop threading fixities * Include bundled pattern synonyms for re-exported data types Sadly, fixity information isn't found for re-exported data types * Support for pattern synonyms * Modify tests after haskell/haddock#631 * Test some reexport variations * Also lookup bundled pattern synonyms from `InstalledInterface`s * Check isExported for bundled pattern synonyms * Pattern synonym is exported check * Always look for pattern synonyms in the current module Another overlooked cornercase * Account for types named twice in export lists Also introduce a fast function for nubbing on a `Name` and use it throughout the code base. * correct fixities for reexported pattern synonyms * Fuse concatMap and map * Remove obsolete import * Add pattern synonyms to visible exports * Fix test * Remove corner case - - - - - a050bffd by Doug Wilson at 2017-06-21T09:27:33+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#636) There is some performance improvement. GHC compiler: | version | bytes allocated | cpu_seconds --------------------------------- | before | 56057108648 | 41.0 | after | 51592019560 | 35.1 base: | version | bytes allocated | cpu_seconds --------------------------------- | before | 25174011784 | 14.6 | after | 23712637272 | 13.1 Cabal: | version | bytes allocated | cpu_seconds --------------------------------- | before | 18754966920 | 12.6 | after | 18198208864 | 11.6 - - - - - 5d06b871 by Doug Wilson at 2017-06-22T20:23:29+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#639) * Use new function getNameToInstancesIndex instead of tcRnGetInfo There is some significant performance improvement in the ghc testsuite. haddock.base: -23.3% haddock.Cabal: -16.7% haddock.compiler: -19.8% * Remove unused imports - - - - - b11bb73a by Alex Biehl at 2017-06-23T14:44:41+02:00 Lookup fixities for reexports without subordinates (#642) So we agree that reexported declarations which do not have subordinates (for example top-level functions) shouldn't have gotten fixities reexported according to the current logic. I wondered why for example Prelude.($) which is obviously reexported from GHC.Base has fixities attached (c.f. http://hackage.haskell.org/package/base-4.9.1.0/docs/Prelude.html#v:-36-). The reason is this: In mkMaps we lookup all the subordinates of top-level declarations, of course top-level functions don't have subordinates so for them the resulting list is empty. In haskell/haddock#644 I established the invariant that there won't be any empty lists in the subordinate map. Without the patch from haskell/haddock#642 top-level functions now started to fail reexporting their fixities. - - - - - d2a6dad6 by Alex Biehl at 2017-06-23T18:30:45+02:00 Don't include names with empty subordinates in maps (#644) These are unecessary anyway and just blow up interface size - - - - - 69c2aac4 by Alex Biehl at 2017-06-29T19:54:49+02:00 Make per-argument docs for class methods work again (#648) * Make per-argument docs for class methods work again * Test case - - - - - c9448d54 by Bartosz Nitka at 2017-07-02T12:12:01+02:00 Fix haddock: internal error: links: UnhelpfulSpan (#561) * Fix haddock: internal error: links: UnhelpfulSpan This fixes haskell/haddock#554 for me. I believe this is another fall out of `wildcard-refactor`, like haskell/haddock#549. * Comment to clarify why we take the methods name location - - - - - d4f29eb7 by Alex Biehl at 2017-07-03T19:43:04+02:00 Document record fields when DuplicateRecordFields is enabled (#649) - - - - - 9d6e3423 by Yuji Yamamoto at 2017-07-03T22:37:58+02:00 Fix test failures on Windows (#564) * Ignore .stack-work * Fix for windows: use nul instead of /dev/null * Fix for windows: canonicalize line separator * Also normalize osx line endings - - - - - 7d81e8b3 by Yuji Yamamoto at 2017-07-04T16:13:12+02:00 Avoid errors on non UTF-8 Windows (#566) * Avoid errors on non UTF-8 Windows Problem ==== haddock exits with errors like below: `(1)` ``` haddock: internal error: <stderr>: hPutChar: invalid argument (invalid character) ``` `(2)` ``` haddock: internal error: Language\Haskell\HsColour\Anchors.hs: hGetContents: invalid argument (invalid byte sequence) ``` `(1)` is caused by printing [the "bullet" character](http://www.fileformat.info/info/unicode/char/2022/index.htm) onto stderr. For example, this warning contains it: ``` Language\Haskell\HsColour\ANSI.hs:62:10: warning: [-Wmissing-methods] • No explicit implementation for ‘toEnum’ • In the instance declaration for ‘Enum Highlight’ ``` `(2)` is caused when the input file of `readFile` contains some Unicode characters. In the case above, '⇒' is the cause. Environment ---- OS: Windows 10 haddock: 2.17.3 GHC: 8.0.1 Solution ==== Add `hSetEncoding handle utf8` to avoid the errors. Note ==== - I found the detailed causes by these changes for debugging: - https://github.com/haskell/haddock/commit/8f29edb6b02691c1cf4c479f6c6f3f922b35a55b - https://github.com/haskell/haddock/commit/1dd23bf2065a1e1f2c14d0f4abd847c906b4ecb4 - These errors happen even after executing `chcp 65001` on the console. According to the debug code, `hGetEncoding stderr` returns `CP932` regardless of the console encoding. * Avoid 'internal error: <stderr>: hPutChar: invalid argument (invalid character)' non UTF-8 Windows Better solution for 59411754a6db41d17820733c076e6a72bcdbd82b's (1) - - - - - eded67d2 by Alex Biehl at 2017-07-07T19:17:15+02:00 Remove redudant import warning (#651) - - - - - 05114757 by Alex Biehl at 2017-07-08T00:33:12+02:00 Avoid missing home module warning (#652) * Avoid missing home module warning * Update haddock-library.cabal - - - - - e9cfc902 by Bryn Edwards at 2017-07-17T07:51:20+02:00 Fix haskell/haddock#249 (#655) - - - - - eb02792b by Herbert Valerio Riedel at 2017-07-20T09:09:15+02:00 Fix compilation of lib:haddock-library w/ GHC < 8 - - - - - 9200bfbc by Alex Biehl at 2017-07-20T09:20:38+02:00 Prepare 2.18.1 release (#657) - - - - - 46ddd22c by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Tweak haddock-api.cabal for pending release - - - - - 85e33d29 by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Avoid trivial use of LambdaCase otherwise we can't test w/ e.g. GHC 7.4.2 - - - - - 3afb4bfe by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Refactor .cabal to use sub-lib for vendored lib A practical benefit is that we can control the build-depends and also avoid some recompilation between library and test-suite. - - - - - e56a552e by Herbert Valerio Riedel at 2017-07-20T10:17:48+02:00 haddock-api: add changelog pointing to haddock's changelog This addresses https://github.com/haskell/haddock/issues/638#issuecomment-309283297 - - - - - 2222ff0d by Herbert Valerio Riedel at 2017-07-20T10:19:56+02:00 Drop obsolete/misleading `stability: experimental` This .cabal property has long been considered obsolete - - - - - 9b882905 by Alex Biehl at 2017-07-20T11:25:54+02:00 Beef up haddock description (#658) * Beef up haddock description * Handle empty lines - - - - - bb60e95c by Herbert Valerio Riedel at 2017-07-20T12:08:53+02:00 Import @aisamanra's Haddock cheatsheet from https://github.com/aisamanra/haddock-cheatsheet - - - - - 0761e456 by Herbert Valerio Riedel at 2017-07-20T12:12:55+02:00 Add cheatsheet to haddock.cabal - - - - - 2ece0f0f by Herbert Valerio Riedel at 2017-07-20T12:18:38+02:00 Mention new-build in README - - - - - 947b7865 by Herbert Valerio Riedel at 2017-07-20T12:32:16+02:00 Update README Also improves markup and removes/fixes redundant/obsolete parts [skip ci] - - - - - 785e09ad by Alex Biehl at 2017-07-27T07:28:57+02:00 Bump haddock to 2.18.2, haddock-library to 1.4.5 - - - - - e3ff1ca3 by Alex Biehl at 2017-07-31T20:15:32+02:00 Move `DocMarkup` from haddock-api to haddock-library (#659) * Move `DocMarkup` from haddock-api to haddock-library * Move more markup related functions * Markup module * CHANGELOG - - - - - cda7c20c by Alex Biehl at 2017-07-31T20:35:49+02:00 Fixup haddock - - - - - 583b6812 by Alex Biehl at 2017-07-31T21:20:45+02:00 Changelog for haddock-library - - - - - bac6a0eb by Alex Biehl at 2017-07-31T21:50:24+02:00 Prepare haddock-library-1.4.5 release - - - - - 58ce6877 by Moritz Drexl at 2017-08-05T16:44:40+02:00 Fix renaming after instance signature specializing (#660) * rework rename * Add regression test for Bug 613 * update tests * update changelog - - - - - b8137ec8 by Tim Baumann at 2017-08-06T11:33:38+02:00 Fix: Generate pattern signatures for constructors exported as patterns (#663) * Fix pretty-printing of pattern signatures Pattern synonyms can have up to two contexts, both having a different semantic meaning: The first holds the constraints required to perform the matching, the second contains the constraints provided by a successful pattern match. When the first context is empty but the second is not it is necessary to render the first, empty context. * Generate pattern synonym signatures for ctors exported as patterns This fixes haskell/haddock#653. * Simplify extractPatternSyn It is not necessary to generate the simplest type signature since it will be simplified when pretty-printed. * Add changelog entries for PR haskell/haddock#663 * Fix extractPatternSyn error message - - - - - d037086b by Alex Biehl at 2017-08-06T12:43:25+02:00 Bump haddock-library - - - - - 99d7e792 by Alex Biehl at 2017-08-06T12:44:07+02:00 Bump haddock-library in haddock-api - - - - - 94802a5b by Alex Biehl at 2017-08-06T13:18:02+02:00 Provide --show-interface option to dump interfaces (#645) * WIP: Provide --show-interface option to dump interfaces Like ghcs own --show-iface this flag dumps a binary interface file to stdout in a human (and machine) readable fashion. Currently it uses json as output format. * Fill all the jsonNull stubs * Rework Bifunctor instance of DocH, update changelog and documentation * replace changelog, bring DocMarkupH doc back * Update CHANGES.md * Update CHANGES.md * Move Control.Arrow up It would result in unused import if the Bifunctor instance is not generated. - - - - - c662e476 by Ryan Scott at 2017-08-14T21:00:21-04:00 Adapt to haskell/haddock#14060 - - - - - b891eb73 by Alex Biehl at 2017-08-16T08:24:48+02:00 Bifoldable and Bitraversable for DocH and MetaDoc - - - - - 021bb56c by Alex Biehl at 2017-08-16T09:06:40+02:00 Refactoring: Make doc renaming monadic This allows us to later throw warnings if can't find an identifier - - - - - 39fbf022 by Alex Biehl at 2017-08-19T20:35:27+02:00 Hyperlinker: Avoid linear lookup in enrichToken (#669) * Make Span strict in Position * Hyperlinker: Use a proper map to enrich tokens - - - - - e13baedd by Alex Biehl at 2017-08-21T20:05:42+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 27dd6e87 by Alex Biehl at 2017-08-21T22:06:35+02:00 Drop Avails from export list - - - - - 86b247e2 by Alex Biehl at 2017-08-22T08:44:22+02:00 Bump ghc version for haddock-api tests - - - - - d4607ca0 by Alex Biehl at 2017-08-22T08:45:17+02:00 Revert "Drop Avails from export list" This reverts commit a850ba86d88a4fb9c0bd175453a2580e544e3def. - - - - - c9c54c30 by Alex Biehl at 2017-08-22T09:26:01+02:00 IntefaceFile version - - - - - a85b7c02 by Ben Gamari at 2017-08-22T09:29:52-04:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 34e976f5 by Ben Gamari at 2017-08-22T17:40:06+02:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 577abf06 by Ryan Scott at 2017-08-23T14:47:29-04:00 Update for haskell/haddock#14131 - - - - - da68fc55 by Florian Eggenhofer at 2017-08-27T18:21:56+02:00 Generate an index for package content search (#662) Generate an index for package content search - - - - - 39e62302 by Alex Biehl at 2017-08-27T18:50:16+02:00 Content search for haddock html doc - - - - - 91fd6fb2 by Alex Biehl at 2017-08-28T18:39:58+02:00 Fix tests for content search - - - - - b4a3798a by Alex Biehl at 2017-08-28T18:44:08+02:00 Add search button to #page-menu - - - - - 25a7ca65 by Alex Biehl at 2017-08-28T18:47:43+02:00 Load javascript below the fold - - - - - 8d323c1a by Alex Biehl at 2017-08-28T18:49:22+02:00 Accept tests - - - - - c5dac557 by Alex Biehl at 2017-08-28T19:14:55+02:00 Content search css - - - - - 89a5af57 by Paolo Veronelli at 2017-08-29T07:42:13+02:00 Removed `nowrap` for interface method sigs (#674) with nowrap the interfaces method sigs would expand at libitum - - - - - a505f6f7 by Alex Biehl at 2017-08-29T08:05:33+02:00 Include subordinates in content index - - - - - 4bb698c4 by Alexander Biehl at 2017-08-29T11:40:19+02:00 QuickNav: Make docbase configurable - - - - - c783bf44 by Alexander Biehl at 2017-08-29T11:48:36+02:00 QuickNav: Also use baseUrl for doc-index.json request - - - - - 47017510 by Alex Biehl at 2017-08-29T17:56:47+02:00 Fix test fallout (again) - - - - - 924fc318 by Alex Biehl at 2017-08-30T09:24:56+02:00 Write meta.json when generating html output (#676) - - - - - 717dea52 by Alex Biehl at 2017-09-01T09:20:34+02:00 Use relative URL when no docBaseUrl given - - - - - e5d85f3b by Alex Biehl at 2017-09-01T09:35:19+02:00 Add missing js files to data-files (#677) - - - - - 95b9231a by Alex Biehl at 2017-09-01T11:01:36+02:00 Rename "Search" tab to "Quick Jump" - - - - - da0ead0b by Alex Biehl at 2017-09-01T13:03:49+02:00 Make trigger link configurable (#678) QuickNav: Configurable show/hide trigger - - - - - de7da594 by Ben Gamari at 2017-09-05T06:49:55-04:00 Account for "Remember the AvailInfo for each IE" As of GHC commit f609374a55bdcf3b79f3a299104767aae2ffbf21 GHC retains the AvailInfo associated with each IE. @alexbiehl has a patch making proper use of this change, but this is just to keep things building. - - - - - b05cd3b3 by Ben Gamari at 2017-09-14T07:55:07-04:00 Bump upper bound on base - - - - - 79db899e by Herbert Valerio Riedel at 2017-09-21T23:27:52+02:00 Make compatible with Prelude.<> export in GHC 8.4/base-4.11 - - - - - 3405dd52 by Tim Baumann at 2017-09-23T22:02:01+02:00 Add compile step that bundles and compresses JS files (#684) * Add compile step that bundles and compresses JS files Also, manage dependencies on third-party JS libraries using NPM. * Compile JS from TypeScript * Enable 'noImplicitAny' in TypeScript * QuickJump: use JSX syntax * Generate source maps from TypeScript for easier debugging * TypeScript: more accurate type * Separate quick jump css file from ocean theme - - - - - df0b5742 by Alex Biehl at 2017-09-29T21:15:40+02:00 Bump base for haddock-library and haddock-test - - - - - 62b12ea0 by Merijn Verstraaten at 2017-10-04T16:03:13+02:00 Inhibit output of coverage information for hidden modules. (#687) * Inhibit output of coverage information for hidden modules. * Add changelog entry. - - - - - 8daf8bc1 by Alexander Biehl at 2017-10-05T11:27:05+02:00 Don't use subMap in attachInstances - - - - - ad75114e by Alexander Biehl at 2017-10-05T11:27:58+02:00 Revert "Don't use subMap in attachInstances" This reverts commit 3adf5bcb1a6c5326ab33dc77b4aa229a91d91ce9. - - - - - 7d4aa02f by Alex Biehl at 2017-10-08T15:32:28+02:00 Precise Haddock: Use Avails for export resolution (#688) * Use Avails for export resolution * Support reexported modules * Factor out availExportItem * Use avails for fullModuleExports * Don't use subMap in attachInstances * lookupDocs without subMap * Completely remove subMap * Only calculate unqualified modules when explicit export list is given * Refactor * Refine comment * return * Fix * Refactoring * Split avail if declaration is not exported itself * Move avail splitting - - - - - b9b4faa8 by Alex Biehl at 2017-10-08T19:38:21+02:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 43325295 by Alex Biehl at 2017-10-08T20:18:46+02:00 Fix merge fallout - - - - - c6423cc0 by Alex Biehl at 2017-10-08T20:36:12+02:00 Copy QuickJump files over - - - - - 1db587c3 by Tim Baumann at 2017-10-09T18:33:09+02:00 Use <details> element for collapsibles (#690) * Remove unnecessary call to 'collapseSection' The call is unnecessary since there is no corresponding toggle for hiding the section of orphan instances. * Use <details> for collapsibles This makes them work even when JS is disabled. Closes haskell/haddock#560. - - - - - 1b54c64b by Tim Baumann at 2017-10-10T09:50:59+02:00 Quick Jump: Show error when loading 'doc-index.json' failed (#691) - - - - - 910f716d by Veronika Romashkina at 2017-10-24T07:36:20+02:00 Fix tiny typo in docs (#693) - - - - - b21de7e5 by Ryan Scott at 2017-10-24T13:07:15+02:00 Overhaul Haddock's rendering of kind signatures (#681) * Overhaul Haddock's rendering of kind signatures * Strip off kind signatures when specializing As an added bonus, this lets us remove an ugly hack specifically for `(->)`. Yay! * Update due to 0390e4a0f61e37bd1dcc24a36d499e92f2561b67 * @alexbiehl's suggestions * Import injectiveVarsOfBinder from GHC - - - - - 6704405c by Ryan Scott at 2017-10-28T07:10:27+02:00 Fix Haddock rendering of kind-indexed data family instances (#694) - - - - - 470f6b9c by Alex Biehl at 2017-10-30T08:45:51+01:00 Add QuickJump version to meta.json (#696) - - - - - b89eccdf by Alex Biehl at 2017-10-30T10:15:49+01:00 Put Quickjump behind --quickjump flag (#697) - - - - - 3095fb58 by Alex Biehl at 2017-10-30T19:09:06+01:00 Add build command to package.json - - - - - f223fda9 by Alex Biehl at 2017-10-30T19:10:39+01:00 Decrease threshold for fuzzy matching - - - - - 80245dda by Edward Z. Yang at 2017-10-31T20:35:05+01:00 Supported reexported-modules via --reexport flag. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 7e389742 by Alex Biehl at 2017-10-31T20:37:56+01:00 Correct missing title in changelog - - - - - 1a2a1c03 by Alex Biehl at 2017-10-31T20:59:07+01:00 Copy quickjump.css for nicer error messages - - - - - db234bb9 by Alex Biehl at 2017-10-31T21:31:18+01:00 Reexported modules: Report warnings if argument cannot be parsed or ... module cannot be found - - - - - eea8a205 by Carlo Hamalainen at 2017-10-31T21:43:14+01:00 More general type for nameCacheFromGhc. (#539) - - - - - 580eb42a by Alex Biehl at 2017-10-31T21:46:52+01:00 Remote tab - - - - - 0e599498 by Alex Biehl at 2017-10-31T21:48:55+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 7b8539bb by Alex Biehl at 2017-10-31T22:28:34+01:00 fullModuleContents traverses exports in declaration order - - - - - 0c91fbf2 by Alex Biehl at 2017-10-31T22:32:31+01:00 Remove excessive use of list comprehensions - - - - - f7356e02 by Alex Biehl at 2017-11-01T19:11:03+01:00 Make better use of AvailInfo - - - - - f3e512d5 by Alex Biehl at 2017-11-02T12:16:22+01:00 Always return documentation for exported subordinates ... event if they have no documentation (e.g. noDocForDecl) By using the information in the AvailInfo we don't need additional export checks. - - - - - 7cf58898 by Alan Zimmerman at 2017-11-07T08:28:03+02:00 Match changes for Trees that Grow in GHC - - - - - e5105a41 by Alan Zimmerman at 2017-11-08T17:21:58+02:00 Match Trees That Grow - - - - - 55178266 by Alan Zimmerman at 2017-11-11T22:20:31+02:00 Match Trees that Grow in GHC for HsExpr - - - - - 2082ab02 by Ryan Scott at 2017-11-14T15:27:03+01:00 Actually render infix type operators as infix (#703) * Actually render infix type operators as infix * Account for things like `(f :*: g) p`, too - - - - - c52ab7d0 by Alan Zimmerman at 2017-11-14T23:14:26+02:00 Clean up use of PlaceHolder, to match TTG - - - - - 81cc9851 by Moritz Angermann at 2017-11-20T07:52:49+01:00 Declare use of `Paths_haddock` module in other-modules (#705) This was detected by `-Wmissing-home-modules` - - - - - f9d27598 by Moritz Angermann at 2017-11-20T12:47:34+01:00 Drop Paths_haddock from ghc.mk (#707) With haskell/haddock#705 and haskell/haddock#706, the custom addition should not be necessary any more. # Conflicts: # ghc.mk - - - - - f34818dc by Moritz Angermann at 2017-11-20T12:47:59+01:00 Add autogen-modules (#706) > Packages using 'cabal-version: >= 1.25' and the autogenerated module Paths_* must include it also on the 'autogen-modules' field besides 'exposed-modules' and 'other-modules'. This specifies that the module does not come with the package and is generated on setup. Modules built with a custom Setup.hs script also go here to ensure that commands like sdist don't fail. # Conflicts: # haddock.cabal - - - - - bb43a0aa by Ben Gamari at 2017-11-21T15:50:12-05:00 Revert "Clean up use of PlaceHolder, to match TTG" This reverts commit 134a7bb054ea730b13c8629a76232d73e3ace049. - - - - - af9ebb2b by Ben Gamari at 2017-11-21T15:50:14-05:00 Revert "Match Trees that Grow in GHC for HsExpr" This reverts commit 9f054dc365379c66668de6719840918190ae6e44. - - - - - 5d35c3af by Ben Gamari at 2017-11-21T15:50:15-05:00 Revert "Match Trees That Grow" This reverts commit 73a26af844ac50b8bec39de11d64452a6286b00c. - - - - - 99a8e43b by Ben Gamari at 2017-11-21T16:36:06-05:00 Revert "Match changes for Trees that Grow in GHC" This reverts commit 01eeeb048acd2dd05ff6471ae148a97cf0720547. - - - - - c4d650c2 by Ben Gamari at 2017-12-04T15:06:07-05:00 Bump GHC version - - - - - 027b2274 by Ben Gamari at 2017-12-04T17:06:31-05:00 Bump GHC bound to 8.4.* - - - - - 58eaf755 by Alex Biehl at 2017-12-06T15:44:24+01:00 Update changelog - - - - - d68f5584 by Simon Peyton Jones at 2017-12-07T14:39:56+00:00 Track changes to follow Trac haskell/haddock#14529 This tracks the refactoring of HsDecl.ConDecl. - - - - - dc519d6b by Alec Theriault at 2018-01-06T08:20:43-08:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - 8285118c by Alec Theriault at 2018-01-13T12:12:37+01:00 Constructor and pattern synonym argument docs (#709) * Support Haddocks on constructor arguments This is in conjunction with https://phabricator.haskell.org/D4094. Adds support for rendering Haddock's on (non-record) constructor arguments, both for regular and GADT constructors. * Support haddocks on pattern synonym arguments It appears that GHC already parsed these - we just weren't using them. In the process of doing this, I tried to deduplicate some code around handling patterns. * Update the markup guide Add some information about the new support for commenting constructor arguments, and mention pattern synonyms and GADT-style constructors. * Overhaul LaTeX support for data/pattern decls This includes at least * fixing several bugs that resulted in invalid LaTeX * fixing GADT data declaration headers * overhaul handling of record fields * overhaul handling of GADT constructors * overhaul handling of bundled patterns * add support for constructor argument docs * Support GADT record constructors This means changes what existing HTML docs look like. As for LaTeX, looks like GADT records were never even supported. Now they are. * Clean up code/comments Made code/comments consistent between the LaTeX and XHTML backend when possible. * Update changelog * Patch post-rebase regressions * Another post-rebase change We want return values to be documentable on record GADT constructors. - - - - - ca4fabb4 by Alec Theriault at 2018-01-15T17:12:18-08:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 4c472fea by Ryan Scott at 2018-01-19T10:44:02+01:00 Fix haskell/haddock#732 (#733) - - - - - bff14dbd by Alex Biehl at 2018-01-19T15:33:30+01:00 extractDecl: Extract associated types correctly (#736) - - - - - a2a94a73 by Alex Biehl at 2018-01-19T15:34:40+01:00 extractDecl: Extract associated types correctly (#736) - - - - - 26df93dc by Alex Biehl at 2018-01-20T10:18:22+01:00 haddock-api: bump ghc to ^>= 8.4 - - - - - f65aeb1d by Alex Biehl at 2018-01-20T19:18:20+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - 0e721b97 by Alex Biehl at 2018-01-20T19:20:19+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - cb6234f6 by Ben Gamari at 2018-01-26T13:40:55-05:00 Merge remote-tracking branch 'harpocrates/fix/missing-orphan-instances' into ghc-head - - - - - 0fc28554 by Alec Theriault at 2018-02-01T14:58:18+01:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - b9123772 by Alec Theriault at 2018-02-01T14:58:18+01:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 0c12e274 by Ryan Scott at 2018-02-01T14:58:18+01:00 Fix haskell/haddock#548 by rendering datatype kinds more carefully (#702) - - - - - 8876d20b by Alec Theriault at 2018-02-01T14:58:18+01:00 Use the GHC lexer for the Hyperlinker backend (#714) * Start changing to use GHC lexer * better cpp * Change SrcSpan to RealSrcSpan * Remove error * Try to stop too many open files * wip * wip * Revert "wip" This reverts commit b605510a195f26315e3d8ca90e6d95a6737553e1. Conflicts: haddock-api/haddock-api.cabal haddock-api/src/Haddock/Interface.hs * Remove pointless 'caching' * Use dlist rather than lists when finding vars * Use a map rather than list * Delete bogus comment * Rebase followup Things now run using the GHC lexer. There are still - stray debug statements - unnecessary changes w.r.t. master * Cleaned up differences w.r.t. current Haddock HEAD Things are looking good. quasiquotes in particular look beautiful: the TH ones (with Haskell source inside) colour/link their contents too! Haven't yet begun to check for possible performance problems. * Support CPP and top-level pragmas The support for these is hackier - but no more hacky than the existing support. * Tests pass, CPP is better recognized The tests were in some cases altered: I consider the new output to be more correct than the old one.... * Fix shrinking of source without tabs in test * Replace 'Position'/'Span' with GHC counterparts Replaces 'Position' -> 'GHC.RealSrcLoc' and 'Span' -> 'GHC.RealSrcSpan'. * Nits * Forgot entry in .cabal * Update changelog - - - - - 95c6a771 by Alec Theriault at 2018-02-01T14:58:18+01:00 Clickable anchors for headings (#716) See haskell/haddock#579. This just adds an <a> tag around the heading, pointing to the heading itself. - - - - - 21463d28 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump: Matches on function names weight more than matches in ... module names. - - - - - 8023af39 by Alex Biehl at 2018-02-01T14:58:18+01:00 Treat escaped \] better in definition lists (#717) This fixes haskell/haddock#546. - - - - - e4866dc1 by Alex Biehl at 2018-02-01T14:58:18+01:00 Remove scanner, takeWhile1_ already takes care of escaping - - - - - 9bcaa49d by Alex Biehl at 2018-02-01T14:58:18+01:00 Take until line feed - - - - - 01d2af93 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Add simple framework for running parser fixtures (#668) * Add simple framework for running parser fixtures * Compatible with tree-diff-0.0.0.1 * Use parseParas to parse fixtures This allows to test all syntactic constructs available in haddock markup. - - - - - 31128417 by Alec Theriault at 2018-02-01T14:58:18+01:00 Patch flaky parser test (#720) * Patch flaky parser test This test was a great idea, but it doesn't port over too well to using the GHC lexer. GHC rewrites its input a bit - nothing surprising, but we need to guard against those cases for the test. * Change instance head * Change use site - - - - - 9704f214 by Herbert Valerio Riedel at 2018-02-01T14:58:18+01:00 Include secondary LICENSE file in source dist - - - - - 51f25074 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Grid Tables (#718) * Add table examples * Add table types and adopt simple parser Simple parser is done by Giovanni Cappellotto (@potomak) in https://github.com/haskell/haddock/pull/577 It seems to support single fine full tables, so far from full RST-grid tables, but it's good start. Table type support row- and colspans, but obviously parser is lacking. Still TODO: - Latex backend. Should we use multirow package https://ctan.org/pkg/multirow?lang=en? - Hoogle backend: ? * Implement grid-tables * Refactor table parser * Add two ill-examples * Update CHANGES.md * Basic documentation for tables * Fix documentation example - - - - - 670d6200 by Alex Biehl at 2018-02-01T14:58:18+01:00 Add grid table example to cheatsheet (pdf and svg need to be regenerated thought) - - - - - 4262dec9 by Alec Theriault at 2018-02-01T14:58:18+01:00 Fix infinite loop when specializing instance heads (#723) * Fix infinite loop when specializing instance heads The bug can only be triggered from TH, hence why it went un-noticed for so long. * Add test for haskell/haddock#679 and haskell/haddock#710 - - - - - 67ecd803 by Alec Theriault at 2018-02-01T14:58:18+01:00 Filter RTS arguments from 'ghc-options' arguments (#725) This fixes haskell/haddock#666. - - - - - 7db26992 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump Scrollable overlay - - - - - da9ff634 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Hyperlinker: Adjust parser to new PFailed constructor - - - - - 7b7cf8cb by Alexander Biehl at 2018-02-01T14:58:18+01:00 Specialize: Add missing IdP annotations - - - - - 78cd7231 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Convert: Correct pass type - - - - - a2d0f590 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Warning free compilation - - - - - cd861cf3 by Alexander Biehl at 2018-02-01T14:58:18+01:00 hadock-2.19.0 / haddock-api-2.19.0 / haddock-library-1.5.0 - - - - - c6651b72 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Adjust changelogs - - - - - 1e93da0b by Alexander Biehl at 2018-02-01T14:58:18+01:00 haddock-library: Info about breaking changes - - - - - f9b11db8 by Alec Theriault at 2018-02-02T12:36:02+01:00 Properly color pragma contents in hyperlinker The hyperlinker backend now classifies the content of pragmas as 'TkPragma'. That means that in something like '{-# INLINE foo #-}', 'foo' still gets classified as a pragma token. - - - - - c40b0043 by Alec Theriault at 2018-02-02T12:36:02+01:00 Support the new 'ITcolumn_prag' token - - - - - 4a2a4d39 by Alex Biehl at 2018-02-03T12:11:55+01:00 QuickJump: Mitigate encoding problems on Windows - - - - - bb34503a by Alex Biehl at 2018-02-04T18:39:31+01:00 Use withBinaryFile - - - - - 637605bf by Herbert Valerio Riedel at 2018-02-05T09:48:32+01:00 Try GHC 8.4.1 for Travis CI job - - - - - 7abb67e4 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 try harder to build w/ GHC 8.4.1 - - - - - 8255cc98 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 Add `SPDX-License-Identifier` as alised for "license" module header tokens C.f. SPDX 2.1 - Appendix V https://spdx.org/spdx-specification-21-web-version#h.twlc0ztnng3b The tag should appear on its own line in the source file, generally as part of a comment. SPDX-License-Identifier: <SPDX License Expression> Cherry-picked from haskell/haddock#743 - - - - - 267cd23d by Herbert Valerio Riedel at 2018-02-05T10:24:34+01:00 Make test-suite SMP compatible - - - - - 95d4bf40 by Alec Theriault at 2018-02-05T22:01:04+01:00 Hyperlink pattern synonyms and 'module' imports (#744) Links to pattern synonyms are now generated, as well as links from modules in import lists. Fixes haskell/haddock#731. - - - - - 67838dcd by Alec Theriault at 2018-02-06T08:23:36+01:00 Don't warn about missing '~' (#746) This manually filters out '~' from the list of things to warn about. It truly makes no sense to warn on this since '~' has nothing it could link to - it is magical. This fixes haskell/haddock#532. - - - - - ab6c3f9f by Alec Theriault at 2018-02-06T08:24:47+01:00 Don't barf on 'HsSpliceTy' (#745) This handles 'HsSpliceTy's by replacing them with what they expand to. IIUC everything that is happening, 'renameHsSpliceTy' should not be able to fail for the inputs we feed it from GHC. This fixes haskell/haddock#574. - - - - - 92bf95ad by Alex Biehl at 2018-02-06T08:28:23+01:00 Rename: renameHsSpliceTy ttg - - - - - 3130b1e1 by Alex Biehl at 2018-02-06T09:02:14+01:00 Expand SigDs - - - - - c72adae5 by Alex Biehl at 2018-02-06T09:20:51+01:00 fullModuleContents: support named docs - - - - - de2e4dbf by Alex Biehl at 2018-02-06T13:56:17+01:00 Hyperlinker: Also link pattern synonym arguments - - - - - b7c98237 by Alex Biehl at 2018-02-09T18:44:23+01:00 Expand SigD in a better place In https://github.com/haskell/haddock/issues/287 we found that haddock-2.19.0 would miss documentation on class methods with multiples names. This patch uses expandSigDecls in a more sensible place. - - - - - 8f598b27 by Alec Theriault at 2018-02-11T12:29:56+01:00 Add module tooltips to linked identifiers (#753) No more clicking to figure out whether your bytestring is strict or lazy! - - - - - d812e65d by Alec Theriault at 2018-02-11T12:31:44+01:00 Add 'show' option to complement 'hide' (#752) * Add 'show' option to complement 'hide' The behaviour is for flags passed in the command line to override flags in file headers. In the command line, later flags override earlier ones. Fixes haskell/haddock#751 and haskell/haddock#266. * Add a '--show-all' option - - - - - 6676cecb by Alex Biehl at 2018-02-18T11:07:15-05:00 QuickJump: Mitigate encoding problems on Windows (cherry picked from commit 86292c54bfee2343aee84559ec01f1fc68f52231) - - - - - e753dd88 by Alex Biehl at 2018-02-18T17:59:54+01:00 Use withBinaryFile - - - - - 724dc881 by Tamar Christina at 2018-02-19T05:34:49+01:00 Haddock: support splitted include paths. (#689) - - - - - 9b6d6f50 by Alex Biehl at 2018-02-19T05:57:02+01:00 Teach the HTML backend how to render methods with multiple names - - - - - a74aa754 by Alexander Biehl at 2018-02-19T10:04:34+01:00 Hoogle/Latex: Remove use of partial function - - - - - 66d8bb0e by Alec Theriault at 2018-02-25T16:04:01+01:00 Fix file handle leak (#763) (#764) Brought back some mistakenly deleted code for handling encoding and eager reading of files from e0ada1743cb722d2f82498a95b201f3ffb303137. - - - - - bb92d03d by Alex Biehl at 2018-03-02T14:21:23+01:00 Enable running test suite with stock haddock and ghc using ``` $ cabal new-run -- html-test --haddock-path=$(which haddock) --ghc-path=$(which ghc) ``` - - - - - dddb3cb2 by Alex Biehl at 2018-03-02T15:43:21+01:00 Make testsuite work with haddock-1.19.0 release (#766) - - - - - f38636ed by Alec Theriault at 2018-03-02T15:48:36+01:00 Support unicode operators, proper modules Unicode operators are a pretty big thing in Haskell, so supporting linking them seems like it outweighs the cost of the extra machinery to force Attoparsec to look for unicode. Fixes haskell/haddock#458. - - - - - 09d89f7c by Alec Theriault at 2018-03-02T15:48:43+01:00 Remove bang pattern - - - - - d150a687 by Alex Biehl at 2018-03-02T15:48:48+01:00 fix test - - - - - d6fd71a5 by Alex Biehl at 2018-03-02T16:22:38+01:00 haddock-test: Be more explicit which packages to pass We now pass `-hide-all-packages` to haddock when invoking the testsuite. This ensures we don't accidentally pick up any dependencies up through ghc.env files. - - - - - 0932c78c by Alex Biehl at 2018-03-02T17:50:38+01:00 Revert "fix test" This reverts commit 1ac2f9569242f6cb074ba6e577285a4c33ae1197. - - - - - 52516029 by Alex Biehl at 2018-03-02T18:16:50+01:00 Fix Bug548 for real - - - - - 89df9eb5 by Alex Biehl at 2018-03-05T18:28:19+01:00 Hyperlinker: Links for TyOps, class methods and associated types - - - - - d019a4cb by Ryan Scott at 2018-03-06T13:43:56-05:00 Updates for haskell/haddock#13324 - - - - - 6d5a42ce by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump haddock-2.19.0.1, haddock-api-2.19.0.1, haddock-library-1.5.0.1 - - - - - c0e6f380 by Alex Biehl at 2018-03-10T18:25:57+01:00 Update changelogs for haddock-2.19.0.1 and haddock-library-1.5.0.1 - - - - - 500da489 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Update to QC 2.11 - - - - - ce8362e9 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Restore backward-compat with base-4.5 through base-4.8 - - - - - baae4435 by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump lower bound for haddock-library - - - - - 10b7a73e by Alex Biehl at 2018-03-10T18:25:57+01:00 Haddock: Straighten out base bound - - - - - a6096f7b by Alex Biehl at 2018-03-13T08:45:06+01:00 extractDecl: Extract constructor patterns from data family instances (#776) * extractDecl: Allow extraction of data family instance constructors * extractDecl: extract data family instance constructors - - - - - ba4a0744 by Simon Jakobi at 2018-03-14T08:26:42+01:00 Readme: Update GHC version (#778) - - - - - 8de157d4 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for definition lists - - - - - 425b46f9 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for links - - - - - d53945d8 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for inline links - - - - - f1dc7c99 by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Slightly unmangle output - - - - - 0879d31c by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Prevent stdout buffering - - - - - 1f9e5f1b by Simon Jakobi at 2018-03-14T20:39:29+01:00 haddock-library.cabal: Clean up GHC options - - - - - 066b891a by Simon Jakobi at 2018-03-14T20:39:29+01:00 Make a proper definition for the <link> parser - - - - - 573d6ba7 by Alec Theriault at 2018-03-21T09:16:57+01:00 Show where instances are defined (#748) * Indicate source module of instances Above instance, we now also display a link to the module where the instance was defined. This is sometimes helpful in figuring out what to import. * Source module for type/data families too * Remove parens * Accept tests - - - - - 99b5d28b by Alex Biehl at 2018-03-21T09:20:36+01:00 Prepare changelog for next release - - - - - 482d3a93 by Alex Biehl at 2018-03-23T15:57:36+01:00 Useful cost centres, timers and allocation counters (#785) * Add some useful cost-centres for profiling * Add withTiming for each haddock phase Invoking haddock with `--optghc=-ddump-timings` now shows the amount of time spent and the number of allocated bytes for each phase. - - - - - 773b41bb by Alec Theriault at 2018-03-27T08:35:59+02:00 @since includes package name (#749) * Metadoc stores a package name This means that '@since' annotations can be package aware. * Get the package name the right way This should extract the package name for `@since` annotations the right way. I had to move `modulePackageInfo` around to do this and, in the process, I took the liberty to update it. Since it appears that finding the package name is something that can fail, I added a warning for this case. * Silence warnings * Hide package for local 'since' annotations As discussed, this is still the usual case (and we should avoid being noisy for it). Although this commit is large, it is basically only about threading a 'Maybe Package' from 'Haddock.render' all the way to 'Haddock.Backends.Xhtml.DocMarkup.renderMeta'. * Bump binary interface version * Add a '--since-qual' option This controls when to qualify since annotations with the package they come from. The default is always, but I've left an 'external' variant where only those annotations coming from outside of the current package are qualified. * Make ParserSpec work * Make Fixtures work * Use package name even if package version is not available The @since stuff needs only the package name passed in, so it makes sense to not be forced to pass in a version too. - - - - - e42c57bc by Alex Biehl at 2018-03-27T08:42:50+02:00 haddock-2.19.1, haddock-api-2.19.1, haddock-library-1.6.0 - - - - - 8373a529 by Alex Biehl at 2018-03-28T10:17:11+02:00 Bump haddock and haddock-api to 2.20.0 - - - - - 5038eddd by Jack Henahan at 2018-04-03T13:28:12+02:00 Clear search string on hide for haskell/haddock#781 (#789) - - - - - 920ca1eb by Alex Biehl at 2018-04-03T16:35:50+02:00 Travis: Build with ghc-8.4.2 (#793) - - - - - a232f0eb by Alan Zimmerman at 2018-04-07T14:14:32+02:00 Match changes in GHC for D4199 Removing HasSourceText and SourceTextX classes. - - - - - ab85060b by Alan Zimmerman at 2018-04-09T21:20:24+02:00 Match GHC changes for TTG - - - - - 739302b6 by Alan Zimmerman at 2018-04-13T13:31:44+02:00 Match GHC for TTG implemented on HsBinds, D4581 - - - - - 2f56d3cb by Ryan Scott at 2018-04-19T11:42:58-04:00 Bump upper bound on base to < 4.13 See https://ghc.haskell.org/trac/ghc/ticket/15018. - - - - - a49df92a by Alex Biehl at 2018-04-20T07:31:44+02:00 Don't treat fixity signatures like declarations - - - - - d02c103b by Ryan Scott at 2018-04-24T11:20:11-04:00 Add regression test for haskell/haddock#413 Fixes haskell/haddock#413. - - - - - c7577f52 by Ryan Scott at 2018-04-24T13:51:06-07:00 Improve the Hoogle backend's treatment of type families (#808) Fixes parts 1 and 2 of haskell/haddock#806. - - - - - d88f85b1 by Alec Theriault at 2018-04-25T11:24:07-07:00 Replace 'attoparsec' with 'parsec' (#799) * Remove attoparsec with parsec and start fixing failed parses * Make tests pass * Fix encoding issues The Haddock parser no longer needs to worry about bytestrings. All the internal parsing work in haddock-library happens over 'Text'. * Remove attoparsec vendor * Fix stuff broken in 'attoparsec' -> 'parsec' * hyperlinks * codeblocks * examples Pretty much all issues are due to attoparsec's backtracking failure behaviour vs. parsec's non-backtracking failure behaviour. * Fix small TODOs * Missing quote + Haddocks * Better handle spaces before/after paragraphs * Address review comments - - - - - fc25e2fe by Alan Zimmerman at 2018-04-27T15:36:53+02:00 Match changes in GHC for TTG - - - - - 06175f91 by Herbert Valerio Riedel at 2018-05-01T18:11:09+02:00 Merge branch 'ghc-head' with 'ghc-8.4' - - - - - 879caaa8 by Alec Theriault at 2018-05-07T18:53:15-07:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 3e0120cb by Simon Jakobi at 2018-05-07T19:00:18-07:00 Add docs for some DocH constructors (#814) - - - - - 0a32c6db by Alec Theriault at 2018-05-08T02:15:45-07:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 8816e783 by Simon Jakobi at 2018-05-08T10:48:11-07:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - ad60366f by Ryan Scott at 2018-05-10T11:19:47-04:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - 03b7cc3b by Ryan Scott at 2018-05-10T11:24:38-04:00 Wibbles - - - - - b03dd563 by Chaitanya Koparkar at 2018-05-10T11:44:58-04:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 9f298a40 by Ben Gamari at 2018-05-13T17:36:04-04:00 Account for refactoring of LitString - - - - - ea3dabe7 by Ryan Scott at 2018-05-16T09:21:43-04:00 Merge pull request haskell/haddock#826 from haskell/T825 Remove Hoogle backend hack that butchers infix datatype names - - - - - 0d234f7c by Alec Theriault at 2018-05-23T11:29:05+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 15fc9712 by Simon Jakobi at 2018-05-31T04:17:47+02:00 Adjust to new HsDocString internals - - - - - 6f1e19a8 by Ben Gamari at 2018-06-02T16:18:58-04:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 0d0355d9 by Ryan Scott at 2018-06-04T21:26:59-04:00 DerivingVia changes - - - - - 0d93475a by Simon Jakobi at 2018-06-05T19:47:05+02:00 Bump a few dependency bounds (#845) - - - - - 5cbef804 by Alec Theriault at 2018-06-05T19:47:16+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 9094c56f by Alec Theriault at 2018-06-05T22:53:25+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 70188719 by Simon Jakobi at 2018-06-08T22:20:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - 495cd1fc by Chaitanya Koparkar at 2018-06-13T23:01:34+02:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 81088732 by Ben Gamari at 2018-06-13T23:01:34+02:00 Account for refactoring of LitString - - - - - 7baf6587 by Simon Jakobi at 2018-06-13T23:05:08+02:00 Adjust to new HsDocString internals - - - - - bb61464d by Ben Gamari at 2018-06-13T23:05:22+02:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 5d8cb87f by Ryan Scott at 2018-06-13T23:39:30+02:00 DerivingVia changes - - - - - 73d373a3 by Alec Theriault at 2018-06-13T23:39:30+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 4865e254 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Remove `ITtildehsh` token - - - - - b867db54 by Alec Theriault at 2018-06-13T23:39:30+02:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 9598e392 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Add docs for some DocH constructors (#814) - - - - - 8a59035b by Alec Theriault at 2018-06-13T23:39:30+02:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 29350fc8 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - 2590bbd9 by Ryan Scott at 2018-06-13T23:39:30+02:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - a9939fdc by Ryan Scott at 2018-06-13T23:39:30+02:00 Wibbles - - - - - a22f7df4 by Alec Theriault at 2018-06-13T23:39:30+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 8741015d by Simon Jakobi at 2018-06-13T23:39:30+02:00 Bump a few dependency bounds (#845) - - - - - 4791e1cc by Alec Theriault at 2018-06-13T23:39:30+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 311d3216 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - d0577817 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Complete FixitySig and FamilyDecl pattern matches - - - - - 055b3aa7 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Fix redundant import warnings - - - - - f9ce19b1 by Simon Jakobi at 2018-06-13T23:49:52+02:00 html-test: Accept output - - - - - 04604ea7 by Simon Jakobi at 2018-06-13T23:54:37+02:00 Bump bounds on Cabal - - - - - 0713b692 by Simon Jakobi at 2018-06-14T00:00:12+02:00 Merge branch 'ghc-head' into ghc-head-update-3 - - - - - c6a56bfd by Simon Jakobi at 2018-06-14T02:33:27+02:00 Bump ghc bound for haddock-api spec test-suite - - - - - 119d04b2 by Simon Jakobi at 2018-06-14T12:37:48+02:00 Travis: `--allow-newer` for all packages - - - - - 0e876e2c by Alex Biehl at 2018-06-14T15:28:52+02:00 Merge pull request haskell/haddock#857 from sjakobi/ghc-head-update-3 Update ghc-head - - - - - 5be46454 by Alec Theriault at 2018-06-14T21:42:45+02:00 Improved handling of interfaces in 'haddock-test' (#851) This should now work with an inplace GHC where (for instance) HTML directories may not be properly recorded in the package DB. - - - - - 96ab1387 by Vladislav Zavialov at 2018-06-14T17:06:21-04:00 Handle -XStarIsType - - - - - e518f8c4 by Ben Gamari at 2018-06-14T17:48:00-04:00 Revert unintentional reversion of fix of haskell/haddock#548 - - - - - 01b9f96d by Alan Zimmerman at 2018-06-19T11:52:22+02:00 Match changes in GHC for haskell/haddock#14259 - - - - - 7f8c8298 by Ben Gamari at 2018-06-19T18:14:27-04:00 Bump GHC version to 8.6 - - - - - 11c6b5d2 by Ryan Scott at 2018-06-19T23:17:31-04:00 Remove HsEqTy and XEqTy - - - - - b33347c2 by Herbert Valerio Riedel at 2018-06-20T23:14:52+02:00 Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. - - - - - f0d2460e by Herbert Valerio Riedel at 2018-06-20T23:28:46+02:00 Update Travis CI job - - - - - ef239223 by Herbert Valerio Riedel at 2018-06-20T23:32:41+02:00 Drop GHC HEAD from CI and update GHC to 8.4.3 It's a waste of resource to even try to build this branch w/ ghc-head; so let's not do that... - - - - - 41c4a9fa by Ben Gamari at 2018-06-20T18:26:20-04:00 Bump GHC version to 8.7 - - - - - 8be593dc by Herbert Valerio Riedel at 2018-06-21T22:32:15+02:00 Update CI job to use GHC 8.7.* - - - - - b91d334a by Simon Jakobi at 2018-06-30T13:41:38+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section - - - - - f707d848 by Alec Theriault at 2018-07-05T10:43:35-04:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. - - - - - a6d2b8dc by Alec Theriault at 2018-07-06T10:06:32-04:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case - - - - - 13819f71 by Alan Zimmerman at 2018-07-15T19:33:51+02:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 - - - - - c346aa78 by Simon Jakobi at 2018-07-19T12:29:32+02:00 haddock-library: Bump bounds for containers - - - - - 722e733c by Simon Jakobi at 2018-07-19T13:36:45+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] - - - - - f0bd83fd by Alec Theriault at 2018-07-19T14:39:57+02:00 Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. - - - - - 394053a8 by Simon Jakobi at 2018-07-19T14:58:07+02:00 haddock-library: Bump bounds for containers - - - - - 1bda11a2 by Alec Theriault at 2018-07-20T09:04:03+02:00 Add HEAD.hackage overlay (#887) * Add HEAD.hackage overlay * Add HCPKG variable - - - - - c7b4ab45 by Alec Theriault at 2018-07-20T12:01:16+02:00 Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test - - - - - c05d32ad by Alec Theriault at 2018-07-20T12:01:49+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output - - - - - 24b39ee4 by Alec Theriault at 2018-07-20T12:02:16+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. - - - - - cb9d2099 by Simon Jakobi at 2018-07-20T13:39:29+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) - - - - - 133f24f5 by Alec Theriault at 2018-07-20T13:39:29+02:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) - - - - - 11024149 by Alec Theriault at 2018-07-20T13:39:29+02:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) - - - - - de0c139e by Simon Jakobi at 2018-07-20T13:39:29+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) - - - - - 6435e952 by Alec Theriault at 2018-07-20T13:39:29+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) - - - - - 1461af39 by Alec Theriault at 2018-07-20T13:39:29+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) - - - - - 69d3bde1 by Alec Theriault at 2018-07-20T13:49:47+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) - - - - - 6a5c73c7 by Alec Theriault at 2018-07-20T13:50:00+02:00 Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests - - - - - 92ca94c6 by Alec Theriault at 2018-07-20T13:55:36+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) - - - - - 981bc7fa by Simon Jakobi at 2018-07-20T15:06:06+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers - - - - - 27e7c0c5 by Simon Jakobi at 2018-07-20T15:09:05+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 49e1a415 by Simon Jakobi at 2018-07-20T16:02:02+02:00 Update the ghc-8.6 branch (#889) * Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. * README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) * Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) * Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) * tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) * Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. * Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test * Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) * Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) * Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) * Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests * Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 5ca14bed by Simon Jakobi at 2018-07-20T16:05:47+02:00 Revert "Revert "Bump GHC version to 8.6"" That commit didn't belong onto the ghc-8.6 branch. This reverts commit acbaef3b9daf1d2dea10017964bf886e77a8e967. - - - - - 2dd600dd by Simon Jakobi at 2018-07-20T16:18:21+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. - - - - - fceb2422 by Simon Jakobi at 2018-07-20T16:18:21+02:00 outOfScope: Recommend qualifying the identifier - - - - - acea5d23 by Simon Jakobi at 2018-07-20T16:19:35+02:00 outOfScope: Recommend qualifying the identifier (cherry picked from commit 73707ed58d879cc04cb644c5dab88c39ca1465b7) - - - - - 1a83ca55 by Simon Jakobi at 2018-07-20T16:19:35+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. (cherry picked from commit d504a2864a4e1982e142cf88c023e7caeea3b76f) - - - - - 48374451 by Masahiro Sakai at 2018-07-20T17:06:42+02:00 Add # as a special character (#884) '#' has special meaning used for anchors and can be escaped using backslash. Therefore it would be nice to be listed as special characters. - - - - - 5e1a5275 by Alec Theriault at 2018-07-20T23:37:24+02:00 Let `haddock-test` bypass interface version check (#890) This means `haddock-test` might * crash during deserialization * deserialize incorrectly Still - it means things _might_ work where they were previously sure not to. - - - - - 27286754 by Yuji Yamamoto at 2018-07-23T08:16:01+02:00 Avoid "invalid argument (invalid character)" on non-unicode Windows (#892) Steps to reproduce and the error message ==== ``` > stack haddock basement ... snip ... Warning: 'A' is out of scope. Warning: 'haddock: internal error: <stdout>: commitBuffer: invalid argument (invalid character) ``` Environment ==== OS: Windows 10 ver. 1709 haddock: [HEAD of ghc-8.4 when I reproduce the error](https://github.com/haskell/haddock/commit/532b209d127e4cecdbf7e9e3dcf4f653a5605b5a). (I had to use this version to avoid another probrem already fixed in HEAD) GHC: 8.4.3 stack: Version 1.7.1, Git revision 681c800873816c022739ca7ed14755e85a579565 (5807 commits) x86_64 hpack-0.28.2 Related pull request ==== https://github.com/haskell/haddock/pull/566 - - - - - 6729d361 by Alec Theriault at 2018-07-23T13:52:56-07:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). - - - - - 8cf4e6b5 by Ryan Scott at 2018-07-27T11:28:03-04:00 eqTyCon_RDR now lives in TysWiredIn After GHC commit http://git.haskell.org/ghc.git/commit/f265008fb6f70830e7e92ce563f6d83833cef071 - - - - - 1ad251a6 by Alan Zimmerman at 2018-07-30T13:28:09-04:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 (cherry picked from commit e3926b50ab8a7269fd6904b06e881745f08bc5d6) - - - - - 8aea2492 by Richard Eisenberg at 2018-08-02T10:54:17-04:00 Update against new HsImplicitBndrs - - - - - e42cada9 by Alec Theriault at 2018-08-04T17:51:30+02:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 0e852512 by Alex Biehl at 2018-08-06T13:04:02+02:00 Make --package-version optional for --hoogle generation (#899) * Make --package-version optional for --hoogle generation * Import mkVersion * It's makeVersion not mkVersion - - - - - d2abd684 by Noel Bourke at 2018-08-21T09:34:18+02:00 Remove unnecessary backslashes from docs (#908) On https://haskell-haddock.readthedocs.io/en/latest/markup.html#special-characters the backslash and backtick special characters showed up with an extra backslash before them – I think the escaping is not (or no longer) needed for those characters in rst. - - - - - 7a578a9e by Matthew Pickering at 2018-08-21T09:34:50+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - aa3d4db3 by Matthew Pickering at 2018-08-21T09:37:34+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - ede91744 by Alec Theriault at 2018-08-21T09:42:52+02:00 Better test output when Haddock crashes on a test (#902) In particular: we report the tests that crashed seperately from the tests that produced incorrect output. In order for tests to pass (and exit 0), they must not crash and must produce the right output. - - - - - 4a872b84 by Guillaume Bouchard at 2018-08-21T09:45:57+02:00 Fix a typo (#878) - - - - - 4dbf7595 by Ben Sklaroff at 2018-08-21T12:04:09-04:00 Add ITcomment_line_prag token to Hyperlinker Parser This token is necessary for parsing #line pragmas inside nested comments. Reviewers: bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D4935 - - - - - 9170b2a9 by Ben Gamari at 2018-08-21T17:55:15-04:00 Merge pull request haskell/haddock#893 from harpocrates/get-name-to-instances Accumulate explicitly which modules to load for 'attachInstances' - - - - - d57b57cc by Ben Gamari at 2018-08-21T17:59:13-04:00 Merge branch 'ghc-head' of github.com:haskell/haddock into ghc-head - - - - - 14601ca2 by Alec Theriault at 2018-08-21T19:09:37-04:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). (cherry picked from commit 5c7c596c51d69b92164e9ba920157b36ce2b2ec1) - - - - - 438c645e by Matthew Pickering at 2018-08-21T19:12:39-04:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 (cherry picked from commit e6aa8fb47b9477cc5ef5e46097524fe83e080f6d) - - - - - a80c5161 by Alec Theriault at 2018-08-21T22:06:40-07:00 Better rendering of unboxed sums/tuples * adds space after/before the '#' marks * properly reify 'HsSumTy' in 'synifyType' - - - - - 88456cc1 by Alec Theriault at 2018-08-21T22:06:40-07:00 Handle promoted tuples in 'synifyType' When we have a fully applied promoted tuple, we can expand it out properly. - - - - - fd1c1094 by Alec Theriault at 2018-08-21T22:19:34-07:00 Accept test cases - - - - - 6e80d9e0 by Alec Theriault at 2018-08-21T22:24:03-07:00 Merge pull request haskell/haddock#914 from harpocrates/feature/unboxed-stuff Better rendering of unboxed sums, unboxed tuples, promoted tuples. - - - - - 181a23f1 by Ben Gamari at 2018-08-23T15:53:48-04:00 Merge remote-tracking branch 'origin/ghc-8.6' into ghc-8.6 - - - - - 3a18c1d8 by Alec Theriault at 2018-08-27T14:15:25-07:00 Properly synify promoted list types We reconstruct promoted list literals whenever possible. That means that 'synifyType' produces '[Int, Bool, ()] instead of (Int ': (() ': (Bool ': ([] :: [Type])))) - - - - - b4794946 by Alec Theriault at 2018-09-03T07:19:55-07:00 Only look at visible types when synifying a 'HsListTy' The other types are still looked at when considering whether to make a kind signature or not. - - - - - a231fce2 by Alec Theriault at 2018-09-03T07:38:10-07:00 Merge pull request haskell/haddock#922 from harpocrates/promoted-lists Properly synify promoted list types - - - - - 0fdf044e by Ningning Xie at 2018-09-15T10:25:58-04:00 Update according to GHC Core changes - - - - - 7379b115 by Ningning Xie at 2018-09-15T15:40:18-04:00 update dataFullSig to work with Co Quantification This should have been in the previous patch, but wasn't. - - - - - cf84a046 by Alec Theriault at 2018-09-17T20:12:18-07:00 Fix/add to various docs * Add documentation for a bunch of previously undocumented options (fixes haskell/haddock#870) * Extend the documentation of `--hoogle` considerably (see haskell/haddock#807) * Describe how to add docs to `deriving` clauses (fixes haskell/haddock#912) * Fix inaccurate docs about hyperlinking infix identifiers (fixes haskell/haddock#780) - - - - - ae017935 by Alec Theriault at 2018-09-22T08:32:16-07:00 Update Travis - - - - - d95ae753 by Alec Theriault at 2018-09-22T09:34:10-07:00 Accept failing tests Also silence orphan warnings. - - - - - f3e67024 by Alec Theriault at 2018-09-22T09:41:23-07:00 Bump haddock-api-2.21.0, haddock-library-1.7.0 * Update CHANGELOGS * Update new versions in Cabal files * Purge references to ghc-8.4/master branches in README - - - - - 3f136d4a by Alec Theriault at 2018-09-22T10:53:31-07:00 Turn haddock-library into a minor release Fix some version bounds in haddock-library too. - - - - - b9def006 by Alec Theriault at 2018-09-22T13:07:35-07:00 keep cabal.project file - - - - - 4909aca7 by Alec Theriault at 2018-10-16T09:36:30-07:00 Build on 7.4 and 7.8 - - - - - 99d20a28 by Herbert Valerio Riedel at 2018-10-16T18:45:52+02:00 Minor tweak to package description - - - - - a8059618 by Herbert Valerio Riedel at 2018-10-16T18:47:24+02:00 Merge pull request haskell/haddock#945 haddock-api 2.21.0 and haddock-library 1.6.1 release - - - - - 2d9bdfc1 by Alec Theriault at 2018-10-16T10:54:21-07:00 Bump haddock-library to 1.7.0 The 1.6.1 release should've been a major bump, since types in the `Documentation.Haddock.Parser.Monad` module changed. This version makes that module internal (as it morally should be). - - - - - ed340cef by Alec Theriault at 2018-10-16T14:59:13-07:00 Merge branch 'ghc-8.4' into ghc-8.6 - - - - - 2821a8df by Alec Theriault at 2018-10-16T15:14:48-07:00 Merge branch 'ghc-8.6' into ghc-head - - - - - a722dc84 by Alec Theriault at 2018-10-16T16:28:55-07:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 63377496 by Alec Theriault at 2018-10-16T16:39:07-07:00 Update changelog - - - - - 099a0110 by Alec Theriault at 2018-10-16T16:49:28-07:00 Merge pull request haskell/haddock#942 from harpocrates/update-docs Fix & add to documentation - - - - - 0927416f by Alec Theriault at 2018-10-16T16:50:14-07:00 Set UTF-8 encoding before writing files (#934) This should fix haskell/haddock#929, as well as guard against future problems of this sort in other places. Basically replaces 'writeFile' (which selects the users default locale) with 'writeUtf8File' (which always uses utf8). - - - - - 83b7b017 by Alec Theriault at 2018-10-16T17:42:05-07:00 Output pattern synonyms in Hoogle backend (#947) * Output pattern synonyms in Hoogle backend We were previously weren't outputting _any_ pattern synonyms, bundled or not. Now, we output both. Fixes haskell/haddock#946. * Update changelog - - - - - 81e5033d by Alec Theriault at 2018-10-16T18:04:40-07:00 Release `haddock{,-api}-2.22.0` This version will accompany ghc-8.6.2 - - - - - 9661744e by Alex Biehl at 2018-10-18T08:14:32-07:00 Add NewOcean theme And make it the default theme. - - - - - 7ae6d722 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Improve appearance and readability These changes include: - use latest Haskell's logo colors - decrease #content width to improve readability - use nicer font - improve sizes and distances - - - - - 37f8703d by NunoAlexandre at 2018-10-18T08:14:32-07:00 Include custom font in the html head - - - - - 1d5e1d79 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Update html test reference files - - - - - 53b7651f by NunoAlexandre at 2018-10-18T08:14:32-07:00 Make it responsive - It makes small screens taking more space than larger ones - fixes a few issues present in small screens currently - make it look good across different screen sizes. - - - - - 6aa1aeb1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make the style consistent with hackage Several things are addressed here: - better responsive behaviour on the header - better space usage - consistent colors overall - other nit PR comments - - - - - 3a250c5c by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Place the package name before the menu links This supports the expected responsive menu design, where the package name appears above the menu links. - - - - - cae699b3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update html-test reference files The package name element in the package-header is now a div instead of a paragraph, and it is now above the menu ul.links instead of below. - - - - - 2ec7fd2d by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve synopsis style and code - Use CSS3 instead of loading pictures to show "+" and "-" symbols - Drop redundant code - - - - - 0c874c01 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Decrease space between code blocks There was too much space between code blocks as pointed out by reviewers. - - - - - 85568ce2 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Add an initial-scale property to all haddock pages This solves an issue reported about the content looking incredibly small on mobile devices. - - - - - c1538926 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Address several PR comments - Darken text color like done for hackage - Move synopsis to left side - Make table of contents stick to the left on wide screens - Wrap links to avoid page overflow - Improve expand/collapse buttons - Fix issue with content size on mobile devices - Fix issue with font-size on landscape mode - Increase width of the content - Change colors of table of contents and synopsis - Etc - - - - - e6639e5f by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make synopsis scrollable on wide screens When the synopsis is longer than the screen, you can’t see its end and you can't scroll down either, making the content unreachable. - - - - - 1f0591ff by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve information density - Reduce font size - Improve space between and within code blocks - Improve alignments - Improve spacing within sub-blocks - - - - - bf083097 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Minor adjustments Bring in some adjustments made to hackage: - link colors - page header show everything when package title is too long - - - - - 10375fc7 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix responsive triggers overlap issue The min and max width triggers have the same values, which caused the style resolution to take an intersection of both style declarations when the screen resolution had the size of the limts (say 1280px), causing an odd behaviour and look. - - - - - 95ff2f95 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix issue with menu alignment on firefox Reported and described here: https://github.com/haskell/haddock/pull/721#issuecomment-374668869 - - - - - dc86587e by Alex Biehl at 2018-10-18T08:14:32-07:00 Changelog entry for NewOcean - - - - - 27195e47 by Herbert Valerio Riedel at 2018-10-18T08:14:32-07:00 html-test --accept - - - - - 83f4f9c0 by Alex Biehl at 2018-10-18T08:14:32-07:00 Avoid name shadowing - - - - - 231487f1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font to PT Sans Also migrate some general text related changes from hackage. - - - - - 313db81a by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Use 'flex' to fix header alignment - - - - - 5087367b by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Misc of tweaks - Update link colors to hackage scheme - Tune spacing between content elements - Update footer style - Fix and improve code blocks identation - - - - - b08020df by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font in Xhtml.hs to PT Sans - - - - - 78ce06e3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve code blocks styling - Fix and improve spacing - Improve colors and borders - - - - - 81262d20 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make package-header caption backward-compatible The current html generator of this branch wraps the package-header caption as a div, which does not work (without style adjustments) with the old themes. Changing it from div to span does the trick, without needing to adjust the old stylesheets. - - - - - dc4475cb by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update test-suite reference html pages - - - - - 393d35d8 by Alec Theriault at 2018-10-18T08:25:36-07:00 Accept tests - - - - - a94484ba by Alec Theriault at 2018-10-21T10:29:29-07:00 Fix CHANGELOG - - - - - 8797eca3 by Alec Theriault at 2018-10-21T10:36:19-07:00 Update 'data-files' to include NewOcean stuff - - - - - 1ae51e4a by Simon Jakobi at 2018-10-23T11:29:14+02:00 Fix typo in a warning - - - - - 009ad8e8 by Alec Theriault at 2018-10-24T12:47:47-07:00 Update JS dependencies This was done via `npm audit fix`. I think this fixes haskell/haddock#903 along with some more serious vulnerabilities that nobody seems to have noticed. - - - - - 051994db by Alec Theriault at 2018-10-24T17:31:09-07:00 Resurrect the style-switcher This fixes haskell/haddock#810. Looks like things were broken during the quickjump refactor of the JS. For the (git) record: I do not think the style switcher is a good idea. I'm fixing it for the same reason @mzero added it; as an answer to "rumblings from some that they didn't want their pixels changed on bit" - - - - - 2a1d620f by Alec Theriault at 2018-10-24T17:38:07-07:00 Fix copy-pasta error in data-files - - - - - ed5bfb7f by Alec Theriault at 2018-10-24T20:42:14-07:00 Fix the synopsis button Here's these changes are supposed to do: * put the synopsis back on the right side * properly have it on the edge of the screen on wide screens * adjust the background of the synopsis to match the button (otherwise the grey blends in with what is underneath) * get rid of the dotted purple line * the synopsis contents are now scrollable even when in wide screens (this has been a long-standing bug) - - - - - 883fd74b by Alec Theriault at 2018-10-25T20:16:46-07:00 Avoid more conflicts in generated ids (#954) This fixes haskell/haddock#953 by passing more names into the generated ids. - - - - - ea54e331 by Alec Theriault at 2018-10-25T21:07:12-07:00 Don't hide bullets in method docs I think thst CSS was meant only to deal with fields and the effect on bullets was accidental. Fixes haskell/haddock#926. - - - - - 9a14ef4a by Alec Theriault at 2018-10-25T22:02:07-07:00 Indent more things + slightly smaller font - - - - - b9f17e29 by Alec Theriault at 2018-10-25T22:10:01-07:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 096a3cfa by Alec Theriault at 2018-10-25T22:24:38-07:00 Accept HTML output - - - - - 2669517d by Alec Theriault at 2018-10-26T09:02:35-07:00 User manual + stuff for building GHC docs - - - - - 46b27687 by Alec Theriault at 2018-10-26T09:10:59-07:00 Make 'Contents' in NewOcean scrollable This only happens if the contents block on the left is so big that it doesn't fit (vertically) on the page. If that happens, we want it to be scrollable. - - - - - 3443dd94 by Alec Theriault at 2018-10-26T09:36:46-07:00 Revert "Make 'Contents' in NewOcean scrollable" This reverts commit f909ffd8353d6463fd5dd184998a32aa98d5c922. I missed the fact this also forces the 'Contents' to always go down to the bottom of the page. - - - - - ed081424 by Alec Theriault at 2018-10-26T14:22:23-07:00 Avoid some partiality AFAICT this wasn't causing any crashes, but that's mostly because we happen not to be forcing `pkgStr` when it would diverge. We come dangerously close to doing that in `ppHtmlIndex`. Fixes haskell/haddock#569. - - - - - 6a5bec41 by Alec Theriault at 2018-10-27T10:05:04-07:00 Fix documentation in `haddock-api` (#957) * Fix misplaced Haddocks in Haddock itself Haddock should be able to generate documentation for 'haddock-api' again. * Make CI check that documentation can be built. * Add back a doc that is OK - - - - - 5100450a by Matthew Yacavone at 2018-10-27T14:51:38-04:00 More explicit foralls (GHC Proposal 0007) - - - - - 8771a6b0 by Alec Theriault at 2018-11-05T13:58:11-08:00 Only run MathJax on entities with "mathjax" class (#960) Correspondingly, we wrap all inline/diplay math in <span class="mathjax"> ... the math .... </span> This fixes haskell/haddock#959. - - - - - bd7ff5c5 by Alec Theriault at 2018-11-05T15:54:22-08:00 Deduplicate some work in 'AttachInstances' Perf only change: * avoid needlessly union-ing maps * avoid synify-ing instances twice Took this opportunity to add some docs too - - - - - cf99fd8f by Alec Theriault at 2018-11-05T15:54:22-08:00 Specialize some SYB functions Perf only change: * Add a 'SPECIALIZE' pragma to help GHC optimize a 'Data a =>' constraint * Manually specialize the needlessly general type of 'specializeTyVarBndrs' - - - - - 4f91c473 by Alec Theriault at 2018-11-05T15:54:22-08:00 Improve perf of renaming Perf only change: * don't look up type variable names (they're never in the environment) * use a difference list for accumulating missing names * more efficient 'Functor'/'Applicative' instances for 'RnM' - - - - - 4bbab0d4 by Alec Theriault at 2018-11-05T15:54:22-08:00 Faster 'Text' driven parser combinators Perf only change: * use 'getParserState'/'setParserState' to make 'Text'-optimized parser combinators * minimize uses of 'Data.Text.{pack,unpack,cons,snoc}' - - - - - fa430c02 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support hyperlink labels with inline markup The parser for pictures hasn't been properly adjusted yet. - - - - - c1431035 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support (and flatten) inline markup in image links Inline markup is supported in image links but, as per the [commonmark recommendation][0], it is stripped back to a plain text representation. [0]: https://spec.commonmark.org/0.28/#example-547 - - - - - d4ee1ba5 by Alec Theriault at 2018-11-06T12:03:24-08:00 Accept test case - - - - - 8088aeb1 by Alec Theriault at 2018-11-06T12:03:24-08:00 Fix/add to haddock-library test suite - - - - - e78f644d by Alec Theriault at 2018-11-06T13:26:31-08:00 Bump version bounds - - - - - 644335eb by Alec Theriault at 2018-11-06T13:53:30-08:00 Merge pull request haskell/haddock#875 from harpocrates/feature/markup-in-hyperlinks Inline markup in markdown-style links and images - - - - - e173ed0d by Alec Theriault at 2018-11-07T12:37:18-08:00 Fix issues around plus/minus * swap the minimize unicode to something more intuitive * use new unicode expander/collapser for instance lists * address some alignment issues in the "index" page - - - - - b2d92df7 by Alec Theriault at 2018-11-07T13:41:57-08:00 Allow "Contents" summary to scroll in a fixed div In the unfortunate event that the "Contents" summary doesn't fit vertically (like in the "Prelude"), it will be scrollable. - - - - - ca704c23 by Alec Theriault at 2018-11-07T13:45:15-08:00 Accept HTML output changes - - - - - 82c0ec6d by Alec Theriault at 2018-11-07T18:12:54-08:00 overflow-y 'scroll' -> 'auto' - - - - - 571d7657 by Alec Theriault at 2018-11-08T19:44:12-08:00 Clicking on "Contents" navigates to top of page - - - - - 8065a012 by Alec Theriault at 2018-11-08T19:44:17-08:00 Space out functions more Also, functions and data decls now have the same space before and after them. - - - - - cc650ede by Alec Theriault at 2018-11-09T08:13:35-08:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 65f8c17f by Alec Theriault at 2018-11-10T14:04:06-08:00 Update changelog - - - - - 20473847 by Alec Theriault at 2018-11-10T14:21:40-08:00 Replace oplus/ominus expander/collapser icons with triangles - - - - - 16592957 by Alec Theriault at 2018-11-10T14:35:10-08:00 Merge pull request haskell/haddock#949 from haskell/wip/new-ocean Introduce NewOcean theme. - - - - - 357cefe1 by Alec Theriault at 2018-11-10T16:02:13-08:00 Merge branch 'ghc-8.6' into ghc-head - - - - - de612267 by Alec Theriault at 2018-11-11T20:01:21-08:00 Rename 'NewOcean' theme to 'Linuwial' - - - - - 954b5baa by Alec Theriault at 2018-11-12T08:33:18-08:00 Add blockquote styling Matches b71da1feabf33efbbc517ac376bb690b5a604c2f from hackage-server. Fixes haskell/haddock#967. - - - - - d32c0b0b by Fangyi Zhou at 2018-11-12T10:24:13-08:00 Fix some broken links (#15733) Summary: For links in subpackages as well. https://phabricator.haskell.org/D5257 Test Plan: Manually verify links Reviewers: mpickering, bgamari, osa1 Reviewed By: osa1 GHC Trac Issues: haskell/haddock#15733 Differential Revision: https://phabricator.haskell.org/D5262 - - - - - 41098b1f by Alp Mestanogullari at 2018-11-15T22:40:09+01:00 Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change It got introduced in ghc/ghc at ae2c9b40f5b6bf272251d1f4107c60003f541b62. - - - - - c5c1c7e0 by Alec Theriault at 2018-11-15T13:48:13-08:00 Merge pull request haskell/haddock#970 from alpmestan/alp/fix-promotionflag Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change - - - - - 6473d3a4 by Shayan-Najd at 2018-11-23T01:38:49+01:00 [TTG: Handling Source Locations] Foundation and Pat Trac Issues haskell/haddock#15495 This patch removes the ping-pong style from HsPat (only, for now), using the plan laid out at https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/HandlingSourceLocations (solution A). - the class `HasSrcSpan`, and its functions (e.g., `cL` and `dL`), are introduced - some instances of `HasSrcSpan` are introduced - some constructors `L` are replaced with `cL` - some patterns `L` are replaced with `dL->L` view pattern - some type annotation are necessarily updated (e.g., `Pat p` --> `Pat (GhcPass p)`) - - - - - 7a088dfe by Alec Theriault at 2018-11-26T11:11:28-08:00 More uniform handling of `forall`'s in HTML/LaTeX * don't forget to print explicit `forall`'s when there are arg docs * when printing an explicit `forall`, print all tyvars Fixes haskell/haddock#973 - - - - - d735e570 by Alec Theriault at 2018-12-12T08:42:09-08:00 Fix warnings, accept output * remove redundant imports (only brought to light due to recent work for improving redundant import detection) * fix a bug that was casuing exports to appear in reverse order * fix something in haddock-library that prevented compilation on old GHC's - - - - - a3852f8a by Zejun Wu at 2018-12-14T09:37:47-05:00 Output better debug infromation on internal error in extractDecl This will make investigation of haskell/haddock#979 easier - - - - - 2eccb5b9 by Alec Theriault at 2018-12-17T09:25:10-05:00 Refactor names + unused functions (#982) This commit should not introduce any change in functionality! * consistently use `getOccString` to convert `Name`s to strings * compare names directly when possible (instead of comparing strings) * get rid of unused utility functions - - - - - e82e4df8 by Alec Theriault at 2018-12-20T16:16:30-05:00 Load plugins when compiling each module (#983) * WIP: Load (typechecker) plugins from language pragmas * Revert "Load plugins when starting a GHC session (#905)" This reverts commit 72d82e52f2a6225686d9668790ac33c1d1743193. * Simplify plugin initialization code - - - - - 96e86f38 by Alec Theriault at 2018-12-23T10:23:20-05:00 Properly synify and render promoted type variables (#985) * Synify and render properly promoted type variables Fixes haskell/haddock#923. * Accept output - - - - - 23343345 by Alec Theriault at 2018-12-27T16:39:38-05:00 Remove `haddock-test`'s dep. on `syb` (#987) The functionality is easily inlined into one short function: `gmapEverywhere`. This doesn't warrant pulling in another package. - - - - - d0734f21 by Alec Theriault at 2018-12-27T16:39:52-05:00 Address deprecation warnings in `haddock-test` (#988) Fixes haskell/haddock#885. - - - - - 4d9f144e by mynguyen at 2018-12-30T23:42:26-05:00 Visible kind application haddock update - - - - - ffe0e9ed by Alec Theriault at 2019-01-07T13:55:22-08:00 Print kinded tyvars in constructors for Hoogle (#993) Fixes haskell/haddock#992 - - - - - 2e18b55d by Alec Theriault at 2019-01-10T16:42:45-08:00 Accept new output `GHC.Maybe` -> `Data.Maybe` (#996) Since 53874834b779ad0dfbcde6650069c37926da1b79 in GHC, "GHC.Maybe" is marked as `not-home`. That changes around some test output. - - - - - 055da666 by Gabor Greif at 2019-01-22T14:41:51+01:00 Lone typofix - - - - - 01bb71c9 by Alec Theriault at 2019-01-23T11:46:46-08:00 Keep forall on H98 existential data constructors (#1003) The information about whether or not there is a source-level `forall` is already available on a `ConDecl` (as `con_forall`), so we should use it instead of always assuming `False`! Fixes haskell/haddock#1002. - - - - - f9b9bc0e by Ryan Scott at 2019-01-27T09:28:12-08:00 Fix haskell/haddock#1004 with a pinch of dropForAlls - - - - - 5cfcdd0a by Alec Theriault at 2019-01-28T16:49:57-08:00 Loosen 'QuickCheck' and 'hspec' bounds It looks like the new versions don't cause any breakage and loosening the bounds helps deps fit in one stack resolver. - - - - - 3545d3dd by Alec Theriault at 2019-01-31T01:37:25-08:00 Use `.hie` files for the Hyperlinker backend (#977) # Summary This is a large architectural change to the Hyperlinker. * extract link (and now also type) information from `.hie` instead of doing ad-hoc SYB traversals of the `RenamedSource`. Also adds a superb type-on-hover feature (#715). * re-engineer the lexer to avoid needless string conversions. By going directly through GHC's `P` monad and taking bytestring slices, we avoid a ton of allocation and have better handling of position pragmas and CPP. In terms of performance, the Haddock side of things has gotten _much_ more efficient. Unfortunately, much of this is cancelled out by the increased GHC workload for generating `.hie` files. For the full set of boot libs (including `ghc`-the-library) * the sum of total time went down by 9-10% overall * the sum of total allocations went down by 6-7% # Motivation Haddock is moving towards working entirely over `.hi` and `.hie` files. This change means we no longer need the `RenamedSource` from `TypecheckedModule` (something which is _not_ in `.hi` files). # Details Along the way a bunch of things were fixed: * Cross package (and other) links are now more reliable (#496) * The lexer tries to recover from errors on every line (instead of at CPP boundaries) * `LINE`/`COLUMN` pragmas are taken into account * filter out zero length tokens before rendering * avoid recomputing the `ModuleName`-based `SrcMap` * remove the last use of `Documentation.Haddock.Utf8` (see haskell/haddock#998) * restructure temporary folder logic for `.hi`/`.hie` model - - - - - 2ded3359 by Herbert Valerio Riedel at 2019-02-02T12:06:12+01:00 Update/modernise haddock-library.cabal file - - - - - 62b93451 by Herbert Valerio Riedel at 2019-02-02T12:19:31+01:00 Tentatively declare support for unreleased base-4.13/ghc-8.8 - - - - - 6041e767 by Herbert Valerio Riedel at 2019-02-02T16:04:32+01:00 Normalise LICENSE text w/ cabal's BSD2 template Also, correct the `.cabal` files to advertise `BSD2` instead of the incorrect `BSD3` license. - - - - - 0b459d7f by Alec Theriault at 2019-02-02T18:06:12-08:00 CI: fetch GHC from validate artifact Should help make CI be less broken - - - - - 6b5c07cf by Alec Theriault at 2019-02-02T18:06:12-08:00 Fix some Hyperlinker test suite fallout * Amend `ParserSpec` to match new Hyperlinker API - pass in compiler info - strip out null tokens * Make `hypsrc-test` pass reliably - strip out `local-*` ids - strip out `line-*` ids from the `ClangCppBug` test - re-accept output - - - - - ded34791 by Nathan Collins at 2019-02-02T18:31:23-08:00 Update README instructions for Stack No need to `stack install` Haddock to test it. Indeed, `stack install` changes the `haddock` on user's `PATH` if `~/.local/bin` is on user's `PATH` which may not be desirable when hacking on Haddock. - - - - - 723298c9 by Alec Theriault at 2019-02-03T09:11:05-08:00 Remove `Documentation.Haddock.Utf8` The circumstances under which this module appeared are completely gone. The Hyperlinker backend no longer needs this module (it uses the more efficient `Encoding` module from `ghc`). Why no deprecation? Because this module really shouldn't exist! - It isn't used in `haddock-library`/`haddock-api` anymore - It was copy pasted directly from `utf8-string` - Folks seeking a boot-lib only solution can use `ghc`'s `Encoding` - - - - - 51050006 by Alec Theriault at 2019-02-03T22:58:58-08:00 Miscellaneous improvements to `Convert` (#1020) Now that Haddock is moving towards working entirely over `.hi` and `.hie` files, all declarations and types are going to be synthesized via the `Convert` module. In preparation for this change, here are a bunch of fixes to this module: * Add kind annotations to type variables in `forall`'s whose kind is not `Type`, unless the kind can be inferred from some later use of the variable. See `implicitForAll` and `noKindTyVars` in particular if you wish to dive into this. * Properly detect `HsQualTy` in `synifyType`. This is done by following suit with what GHC's `toIfaceTypeX` does and checking the first argument of `FunTy{} :: Type` to see if it classified as a given/wanted in the typechecker (see `isPredTy`). * Beef up the logic around figuring out when an explicit `forall` is needed. This includes: observing if any of the type variables will need kind signatures, if the inferred type variable order _without_ a forall will still match the one GHC claims, and some other small things. * Add some (not yet used) functionality for default levity polymorphic type signatures. This functionality similar to `fprint-explicit-runtime-reps`. Couple other smaller fixes only worth mentioning: * Show the family result signature only when it isn't `Type` * Fix rendering of implicit parameters in the LaTeX and Hoogle backends * Better handling of the return kind of polykinded H98 data declarations * Class decls produced by `tyThingToLHsDecl` now contain associated type defaults and default method signatures when appropriate * Filter out more `forall`'s in pattern synonyms - - - - - 841980c4 by Oleg Grenrus at 2019-02-04T08:44:25-08:00 Make a fixture of weird parsing of lists (#997) The second example is interesting. If there's a list directly after the header, and that list has deeper structure, the parser is confused: It finds two lists: - One with the first nested element, - everything after it I'm not trying to fix this, as I'm not even sure this is a bug, and not a feature. - - - - - 7315c0c8 by Ryan Scott at 2019-02-04T12:17:56-08:00 Fix haskell/haddock#1015 with dataConUserTyVars (#1022) The central trick in this patch is to use `dataConUserTyVars` instead of `univ_tvs ++ ex_tvs`, which displays the foralls in a GADT constructor in a way that's more faithful to how the user originally wrote it. Fixes haskell/haddock#1015. - - - - - ee0b49a3 by Ryan Scott at 2019-02-04T15:25:17-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. - - - - - 1c850dc8 by Alan Zimmerman at 2019-02-05T21:54:18+02:00 Matching changes in GHC for haskell/haddock#16236 - - - - - ab03c38e by Simon Marlow at 2019-02-06T08:07:33+00:00 Merge pull request haskell/haddock#1014 from hvr/pr/bsd2-normalise Normalise LICENSE text w/ cabal's BSD2 template - - - - - 5a92ccae by Alec Theriault at 2019-02-10T06:21:55-05:00 Merge remote-tracking branch 'gitlab/wip/T16236-2' into ghc-head - - - - - c0485a1d by Alec Theriault at 2019-02-10T03:32:52-08:00 Removes `haddock-test`s dependency on `xml`/`xhtml` (#1027) This means that `html-test`, `latex-test`, `hoogle-test`, and `hypsrc-test` now only depend on GHC boot libs. So we should now be able to build and run these as part of GHC's testsuite. \o/ The reference output has changed very slightly, in three ways: * we don't convert quotes back into `&quot;` as the `xml` lib did * we don't add extra `&nbsp;` as the `xml` lib did * we now remove the entire footer `div` (instead of just emptying it) - - - - - 65a448e3 by Alec Theriault at 2019-02-11T12:27:41-05:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - 360ca937 by Alec Theriault at 2019-02-13T11:36:11-05:00 Clean up logic for guessing `-B` and `--lib` (#1026) Haddock built with the `in-ghc-tree` flag tries harder to find the GHC lib folder and its own resources. This should make it possible to use `in-ghc-tree`-built Haddock without having to specify the `-B` and `--lib` options (just how you can use in-tree GHC without always specifying the `-B` option). The logic to do this relies on `getExecutablePath`, so we only get this auto-detection on platforms where this function works. - - - - - d583e364 by Alec Theriault at 2019-02-16T10:41:22-05:00 Fix tests broken by GHC Changes in 19626218566ea709b5f6f287d3c296b0c4021de2 affected some of the hyperlinker output. Accepted the new output (hovering over a `..` now shows you what that wildcard binds). Also fixed some stray deprecation warnings. - - - - - da0c42cc by Vladislav Zavialov at 2019-02-17T11:39:19+03:00 Parser changes to match !380 - - - - - ab96bed7 by Ryan Scott at 2019-02-18T04:44:08-05:00 Bump ghc version to 8.9 - - - - - 44b7c714 by Alec Theriault at 2019-02-22T05:49:43-08:00 Match GHC changes for T16185 `FunTy` now has an `AnonArgFlag` that indicates whether the arrow is a `t1 => t2` or `t1 -> t2`. This commit shouldn't change any functionality in Haddock. - - - - - 2ee653b1 by Alec Theriault at 2019-02-24T18:53:33-08:00 Update .travis.yml Points to the new GHC CI artifact. - - - - - 90939d71 by Alec Theriault at 2019-02-25T00:42:41-08:00 Support value/type namespaces on identifier links Identifier links can be prefixed with a 'v' or 't' to indicate the value or type namespace of the desired identifier. For example: -- | Some link to a value: v'Data.Functor.Identity' -- -- Some link to a type: t'Data.Functor.Identity' The default is still the type (with a warning about the ambiguity) - - - - - d6ed496c by Alec Theriault at 2019-02-25T00:42:46-08:00 Better identifier parsing * '(<|>)' and '`elem`' now get parsed and rendered properly as links * 'DbModule'/'DbUnitId' now properly get split apart into two links * tuple names now get parsed properly * some more small niceties... The identifier parsing code is more precise and more efficient (although to be fair: it is also longer and in its own module). On the rendering side, we need to pipe through information about backticks/parens/neither all the way through from renaming to the backends. In terms of impact: a total of 35 modules in the entirety of the bootlib + ghc lib docs change. The only "regression" is things like '\0'. These should be changed to @\\0@ (the path by which this previously worked seems accidental). - - - - - 3c3b404c by Alec Theriault at 2019-02-25T22:12:11-08:00 Fix standalone deriving docs Docs on standalone deriving decls for classes with associated types should be associated with the class instance, not the associated type instance. Fixes haskell/haddock#1033 - - - - - d51ef69e by Alec Theriault at 2019-02-26T19:14:59-08:00 Fix bogus identifier defaulting This avoids a situation in which an identifier would get defaulted to a completely different identifier. Prior to this commit, the 'Bug1035' test case would hyperlink 'Foo' into 'Bar'! Fixes haskell/haddock#1035. - - - - - 88cbbdc7 by Ryan Scott at 2019-02-27T10:14:03-05:00 Visible dependent quantification (#16326) changes - - - - - 0dcf6cee by Xia Li-yao at 2019-02-27T21:53:27-05:00 Menu item controlling which instances are expanded/collapsed (#1007) Adds a menu item (like "Quick Jump") for options related to displaying instances. This provides functionality for: * expanding/collapsing all instances on the currently opened page * controlling whether instances are expanded/collapsed by default * controlling whether the state of instances should be "remembered" This new functionality is implemented in Typescript in `details-helper`. The built-in-themes style switcher also got a revamp so that all three of QuickJump, the style switcher, and instance preferences now have the same style and implementation structure. See also: https://mail.haskell.org/pipermail/haskell-cafe/2019-January/130495.html Fixes haskell/haddock#698. Co-authored-by: Lysxia <lysxia at gmail.com> Co-authored-by: Nathan Collins <conathan at galois.com> - - - - - 3828c0fb by Alec Theriault at 2019-02-28T12:42:49-05:00 `--show-interface` should output to stdout. (#1040) Fixes haskell/haddock#864. - - - - - a50f4cda by gbaz at 2019-03-01T07:43:16-08:00 Increase contrast of Linuwal theme (#1037) This is to address the concern that, on less nice and older screens, some of the shades of grey blend in too easily with the white background. * darken the font slightly * darken slightly the grey behind type signatures and such * add a border and round the corners on code blocks * knock the font down by one point - - - - - ab4d41de by Alec Theriault at 2019-03-03T09:23:26-08:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 12f509eb by Ben Gamari at 2019-03-04T22:13:20-05:00 Remove reference to Opt_SplitObjs flag Split-objects has been removed. - - - - - 5b3e4c9a by Ryan Scott at 2019-03-06T19:16:24-05:00 Update html-test output to reflect haskell/haddock#16391 changes - - - - - fc228af1 by Alec Theriault at 2019-03-09T08:29:23-08:00 Match changes for "Stop inferring over-polymorphic kinds" The `hsq_ext` field of `HsQTvs` is now just the implicit variables (instead of also including information about which of these variables are dependent). This commit shouldn't change any functionality in Haddock. - - - - - 6ac109eb by Alec Theriault at 2019-03-09T11:22:55-08:00 Add .hi, .dyn_hi, etc files to .gitignore Fixes haskell/haddock#1030. - - - - - b55f0c05 by Alec Theriault at 2019-03-09T11:22:55-08:00 Better support for default methods in classes * default methods now get rendered differently * default associated types get rendered * fix a forgotten `s/TypeSig/ClassOpSig/` refactor in LaTeX backend * LaTeX backend now renders default method signatures NB: there is still no way to document default class members and the NB: LaTeX backend still crashes on associated types - - - - - 10aea0cf by Alec Theriault at 2019-03-09T11:22:55-08:00 Avoid multi-line `emph` in LaTeX backend `markupWarning` often processes inputs which span across paragraphs. Unfortunately, LaTeX's `emph` is not made to handle this (and will crash). Fixes haskell/haddock#936. - - - - - d22dc2c9 by Alec Theriault at 2019-03-09T11:22:55-08:00 Many LaTeX backend fixes After this commit, we can run with `--latex` on all boot libraries without crashing (although the generated LaTeX still fails to compile in a handful of larger packages like `ghc` and `base`). * Add newlines after all block elements in LaTeX. This is important to prevent the final output from being more an more indented. See the `latext-test/src/Example` test case for a sample of this. * Support associated types in class declarations (but not yet defaults) * Several small issues for producing compiling LaTeX; - avoid empy `\haddockbeginargs` lists (ex: `type family Any`) - properly escape identifiers depending on context (ex: `Int#`) - add `vbox` around `itemize`/`enumerate` (so they can be in tables) * Several spacing fixes: - limit the width of `Pretty`-arranged monospaced code - cut out extra space characters in export lists - only escape spaces if there are _multiple_ spaces - allow type signatures to be multiline (even without docs) * Remove uninteresting and repetitive `main.tex`/`haddock.sty` files from `latex-test` test reference output. Fixes haskell/haddock#935, haskell/haddock#929 (LaTeX docs for `text` build & compile) Fixes haskell/haddock#727, haskell/haddock#930 (I think both are really about type families...) - - - - - 0e6cee00 by Alec Theriault at 2019-03-29T12:11:56-07:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - ce05434d by Alan Zimmerman at 2019-03-29T12:12:11-07:00 Matching changes in GHC for haskell/haddock#16236 (cherry picked from commit 3ee6526d4ae7bf4deb7cd1caf24b3d7355573576) - - - - - d85766b2 by Ben Gamari at 2019-03-29T12:14:04-07:00 Bump GHC to 8.8 - - - - - 5a82cbaf by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Redo ParseModuleHeader - - - - - b9033348 by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - bb55c8f4 by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove outdated `.ghci` files and `scripts` The `.ghci` files are actively annoying when trying to `cabal v2-repl`. As for the `scripts`, the distribution workflow is completely different. - - - - - 5ee244dc by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove obsolete arcanist files + STYLE Now that GHC is hosted on Gitlab, the arcanist files don't make sense anymore. The STYLE file contains nothing more than a dead link too. - - - - - d07c1928 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Redo ParseModuleHeader - - - - - 492762d2 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - af2ac773 by Ryan Scott at 2019-05-14T17:22:13-04:00 Changes for haskell/haddock#16110/#16356 - - - - - 6820ed0d by Alec Theriault at 2019-05-17T08:51:27-07:00 Unbreak haskell/haddock#1004 test case `fail` is no longer part of `Monad`. - - - - - 6bf7be98 by Alec Theriault at 2019-05-17T08:51:27-07:00 Fix haskell/haddock#1063 with better parenthesization logic for contexts The only other change in html/hoogle/hyperlinker output for the boot libraries that this caused is a fix to some Hoogle output for implicit params. ``` $ diff -r _build/docs/ old_docs diff -r _build/docs/html/libraries/base/base.txt old_docs/html/libraries/base/base.txt 13296c13296 < assertError :: (?callStack :: CallStack) => Bool -> a -> a --- > assertError :: ?callStack :: CallStack => Bool -> a -> a ``` - - - - - b5716b61 by Ryan Scott at 2019-05-22T17:24:32-04:00 Match changes with haskell/haddock#14332 - - - - - c115abf6 by Alec Theriault at 2019-05-26T16:01:58-04:00 Remove Haddock's dependency on `Cabal` At this point, Haddock depended on Cabal-the-library solely for a verbosity parser (which misleadingly accepts all sorts of verbosity options that Haddock never uses). Now, the only dependency on Cabal is for `haddock-test` (which uses Cabal to locate the Haddock interface files of a couple boot libraries). - - - - - e5b2d4a3 by Alec Theriault at 2019-05-26T16:16:25-04:00 Regression test: promoted lists in associated types When possible, associated types with promoted lists should use the promoted list literal syntax (instead of repeated applications of ': and '[]). This was fixed in 2122de5473fd5b434af690ff9ccb1a2e58491f8c. Closes haskell/haddock#466, - - - - - cc5ad5d3 by Alec Theriault at 2019-05-26T17:55:54-04:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 4b3301a6 by Alec Theriault at 2019-05-26T17:57:52-04:00 Release haddock-2.23, haddock-library-1.8.0 Tentatively adjust bounds and changelogs for the release to be bundled with GHC 8.8.1. - - - - - 69c7cfce by Matthew Pickering at 2019-05-30T10:54:27+01:00 Update hyperlinker tests for new types in .hie files - - - - - 29b7e738 by Zubin Duggal at 2019-05-30T10:57:51+01:00 update for new way to store hiefile headers - - - - - aeca5d5f by Zubin Duggal at 2019-06-04T18:57:42-04:00 update for new way to store hiefile headers - - - - - ba2ca518 by Ben Gamari at 2019-06-07T23:11:14+00:00 Update test output for introduction of Safe-Inferred - - - - - 3a975a6c by Ryan Scott at 2019-07-03T12:06:27-04:00 Changes for haskell/haddock#15247 - - - - - 0df46555 by Zubin Duggal at 2019-07-22T10:52:50+01:00 Fix haddockHypsrcTest - - - - - 2688686b by Sylvain Henry at 2019-09-12T23:19:39+02:00 Fix for GHC module renaming - - - - - 9ec0f3fc by Alec Theriault at 2019-09-20T03:21:00-04:00 Fix Travis CI, loosen .cabal bounds (#1089) Tentatively for the 2.23 release: * updated Travis CI to work again * tweaked bounds in the `.cabal` files * adjusted `extra-source-files` to properly identify test files - - - - - ca559beb by Matthías Páll Gissurarson at 2019-09-28T12:14:40-04:00 Small change in to facilitate extended typed-holes (#1090) This change has no functional effect on haddock itself, it just changes one pattern to use `_ (` rather than `_(`, so that we may use `_(` as a token for extended typed-holes later. - - - - - 02e28976 by Vladislav Zavialov at 2019-09-28T12:17:45-04:00 Remove spaces around @-patterns (#1093) This is needed to compile `haddock` when [GHC Proposal haskell/haddock#229](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0229-whitespace-bang-patterns.rst) is implemented. - - - - - 83cbbf55 by Alexis King at 2019-09-30T21:12:42-04:00 Fix the ignore-exports option (#1082) The `ignore-exports` option has been broken since haskell/haddock#688, as mentioned in https://github.com/haskell/haddock/pull/766#issue-172505043. This PR fixes it. - - - - - e127e0ab by Ben Gamari at 2019-10-06T15:12:06-04:00 Fix a few haddock issues - - - - - 3a0f5c89 by Zubin Duggal at 2019-10-07T17:56:13-04:00 Fix crash when there are no srcspans in the file due to CPP - - - - - 339c5ff8 by Alec Theriault at 2019-10-07T17:56:13-04:00 Prefer un-hyperlinked sources to no sources It is possible to fail to extract an HIE ast. This is however not a reason to produce _no_ output - we should still make a colorized HTML page. - - - - - d47ef478 by Alec Theriault at 2019-10-07T17:56:13-04:00 Add a regression test for haskell/haddock#1091 Previously, this input would crash Haddock. - - - - - ed7c8b0f by Alec Theriault at 2019-10-07T20:56:48-04:00 Add Hyperlinker test cases for TH-related stuff Hopefully this will guard against regressions around quasiquotes, TH quotes, and TH splices. - - - - - d00436ab by Andreas Klebinger at 2019-10-21T15:53:03+02:00 Refactor for withTiming changes. - - - - - 4230e712 by Ben Gamari at 2019-10-22T09:36:37-04:00 Merge pull request haskell/haddock#1101 from AndreasPK/withTimingRefactor Refactor for withTiming changes. - - - - - d155c5f4 by Ryan Scott at 2019-10-23T10:37:17-04:00 Reify oversaturated data family instances correctly (#1103) This fixes haskell/haddock#1103 by adapting the corresponding patch for GHC (see https://gitlab.haskell.org/ghc/ghc/issues/17296 and https://gitlab.haskell.org/ghc/ghc/merge_requests/1877). - - - - - 331a5adf by Sebastian Graf at 2019-10-25T17:14:40+02:00 Refactor for OutputableBndrId changes - - - - - 48a490e0 by Ben Gamari at 2019-10-27T10:16:16-04:00 Merge pull request haskell/haddock#1105 from sgraf812/wip/flexible-outputable Refactor for OutputableBndrId changes - - - - - f62a7dfc by Sebastian Graf at 2019-11-01T11:54:16+00:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - d9b242ed by Ryan Scott at 2019-11-03T13:20:03-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. (cherry picked from commit cfd682c5fd03b099a3d78c44f9279faf56a0ac70) - - - - - dfd42406 by Sebastian Graf at 2019-11-04T07:02:14-05:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - 0b15be7c by Ben Gamari at 2019-11-09T13:21:33-05:00 Import isRuntimeRepVar from Type rather than TyCoRep isRuntimeRepVar is not longer exported from TyCoRep due to ghc#17441. - - - - - 091f7283 by Ben Gamari at 2019-11-10T12:47:06-05:00 Bump to GHC 8.10 - - - - - e88c71f2 by Ben Gamari at 2019-11-14T00:22:24-05:00 Merge pull request haskell/haddock#1110 from haskell/wip/T17441 Import isRuntimeRepVar from Type rather than TyCoRep - - - - - 4e0bbc17 by Ben Gamari at 2019-11-14T00:22:45-05:00 Version bumps for GHC 8.11 - - - - - 0e85ceb4 by Ben Gamari at 2019-11-15T11:59:45-05:00 Bump to GHC 8.10 - - - - - 00d6d68b by Ben Gamari at 2019-11-16T18:35:58-05:00 Bump ghc version to 8.11 - - - - - dde1fc3f by Ben Gamari at 2019-11-16T20:40:37-05:00 Drop support for base 4.13 - - - - - f52e331d by Vladislav Zavialov at 2019-11-24T13:02:28+03:00 Update Hyperlinker.Parser.classify to use ITdollar - - - - - 1ad96198 by Vladislav Zavialov at 2019-11-28T16:12:33+03:00 Remove HasSrcSpan (#17494) - - - - - 651afd70 by Herbert Valerio Riedel at 2019-12-08T12:08:16+01:00 Document error-prone conditional definition of instances This can easily trip up people if one isn't aware of it. Usually it's better to avoid this kind of conditionality especially for typeclasses for which there's an compat-package as conditional instances like these tend to fragment the ecosystem into those packages that go the extra mile to provide backward compat via those compat-packages and those that fail to do so. - - - - - b521af56 by Herbert Valerio Riedel at 2019-12-08T12:09:54+01:00 Fix build-failure regression for base < 4.7 The `$>` operator definition is available only since base-4.7 which unfortunately wasn't caught before release to Hackage (but has been fixed up by a metadata-revision) This commit introduces a `CompatPrelude` module which allows to reduce the amount of CPP by ousting it to a central location, i.e. the new `CompatPrelude` module. This pattern also tends to reduce the tricks needed to silence unused import warnings. Addresses haskell/haddock#1119 - - - - - 556c375d by Sylvain Henry at 2020-01-02T19:01:55+01:00 Fix after Iface modules renaming - - - - - bd6c53e5 by Sylvain Henry at 2020-01-07T00:48:48+01:00 hsyl20-modules-renamer - - - - - fb23713b by Ryan Scott at 2020-01-08T07:41:13-05:00 Changes for GHC#17608 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2372 - - - - - 4a4dd382 by Ryan Scott at 2020-01-25T08:08:26-05:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - e782a44d by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename PackageConfig into UnitInfo - - - - - ba3c9f05 by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename lookupPackage - - - - - ab37f9b3 by Ben Gamari at 2020-01-29T13:00:44-05:00 Merge pull request haskell/haddock#1125 from haskell/wip/T17566-take-two Changes for GHC#17566 - - - - - 3ebd5ae0 by Ryan Scott at 2020-01-31T05:56:50-05:00 Merge branch 'wip-hsyl20-package-refactor' into ghc-head - - - - - 602a747e by Richard Eisenberg at 2020-02-04T09:05:43+00:00 Echo GHC's removal of PlaceHolder module This goes with GHC's !2083. - - - - - ccfe5679 by Sylvain Henry at 2020-02-10T10:13:56+01:00 Module hierarchy: runtime (cf haskell/haddock#13009) - - - - - 554914ce by Cale Gibbard at 2020-02-10T16:10:39-05:00 Fix build of haddock in stage1 We have to use the correct version of the GHC API, but the version of the compiler itself doesn't matter. - - - - - 5b6fa2a7 by John Ericson at 2020-02-10T16:18:07-05:00 Noramlize `tested-with` fields in cabal files - - - - - e6eb3ebe by Vladislav Zavialov at 2020-02-16T13:25:26+03:00 No MonadFail/Alternative for P - - - - - 90e181f7 by Ben Gamari at 2020-02-18T14:13:47-05:00 Merge pull request haskell/haddock#1129 from obsidiansystems/wip/fix-stage1-build Fix build of haddock in stage1 - - - - - 93b64636 by Sylvain Henry at 2020-02-19T11:20:27+01:00 Modules: Driver (#13009) - - - - - da4f6c7b by Vladislav Zavialov at 2020-02-22T15:33:02+03:00 Use RealSrcSpan in InstMap - - - - - 479b1b50 by Ben Gamari at 2020-02-23T10:28:13-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 55ecacf0 by Sylvain Henry at 2020-02-25T15:18:27+01:00 Modules: Core (#13009) - - - - - 60867b3b by Vladislav Zavialov at 2020-02-28T15:53:52+03:00 Ignore the BufLoc/BufSpan added in GHC's !2516 - - - - - 1e5506d3 by Sylvain Henry at 2020-03-02T12:32:43+01:00 Modules: Core (#13009) - - - - - 6fb53177 by Richard Eisenberg at 2020-03-09T14:49:40+00:00 Changes in GHC's !1913. - - - - - 30b792ea by Ben Gamari at 2020-03-16T12:45:02-04:00 Merge pull request haskell/haddock#1130 from hsyl20/wip/hsyl20-modules-core2 Modules: Core (#13009) - - - - - cd761ffa by Sylvain Henry at 2020-03-18T15:24:00+01:00 Modules: Types - - - - - b6646486 by Ben Gamari at 2020-03-18T14:42:43-04:00 Merge pull request haskell/haddock#1133 from hsyl20/wip/hsyl20/modules/types Modules: Types - - - - - 9325d734 by Kleidukos at 2020-03-19T12:38:31-04:00 Replace the 'caption' class so that the collapsible sections are shown - - - - - 5e2bb555 by Kleidukos at 2020-03-19T12:38:31-04:00 Force ghc-8.8.3 - - - - - c6fcd0aa by Kleidukos at 2020-03-19T12:38:31-04:00 Update test fixtures - - - - - 5c849cb1 by Sylvain Henry at 2020-03-20T09:34:39+01:00 Modules: Types - - - - - 7f439155 by Alec Theriault at 2020-03-20T20:17:01-04:00 Merge branch 'ghc-8.8' into ghc-8.10 - - - - - b7904e5c by Alina Banerjee at 2020-03-20T20:24:17-04:00 Update parsing to strip whitespace from table cells (#1074) * Update parsing to strip leading & trailing whitespace from table cells * Update fixture data to disallow whitespaces at both ends in table cells * Add test case for whitespaces stripped from both ends of table cells * Update table reference test data for html tests - - - - - b9d60a59 by Alec Theriault at 2020-03-22T11:46:42-04:00 Clean up warnings * unused imports * imports of `Data.List` without import lists * missing `CompatPrelude` file in `.cabal` - - - - - 0c317dbe by Alec Theriault at 2020-03-22T18:46:54-04:00 Fix NPM security warnings This was done by calling `npm audit fix`. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. - - - - - 6e306242 by Alec Theriault at 2020-03-22T20:10:52-04:00 Tentative 2.24 release Adjusted changelogs and versions in `.cabal` files in preparation for the upcoming release bundled with GHC 8.10. - - - - - 1bfb4645 by Ben Gamari at 2020-03-23T16:40:54-04:00 Merge commit '3c2944c037263b426c4fe60a3424c27b852ea71c' into HEAD More changes from the GHC types module refactoring. - - - - - be8c6f3d by Alec Theriault at 2020-03-26T20:10:53-04:00 Update `.travis.yml` to work with GHC 8.10.1 * Regenerated the Travis file with `haskell-ci` * Beef up `.cabal` files with more `tested-with` information - - - - - b025a9c6 by Alec Theriault at 2020-03-26T20:10:53-04:00 Update README Removed some out of date links/info, added some more useful links. * badge to Hackage * update old trac link * `ghc-head` => `ghc-8.10` * `cabal new-*` is now `cabal v2-*` and it should Just Work * `--test-option='--accept'` is the way to accept testsuite output - - - - - 564d889a by Alec Theriault at 2020-03-27T20:34:33-04:00 Fix crash in `haddock-library` on unicode space Our quickcheck tests for `haddock-library` stumbled across an edge case input that was causing Haddock to crash: it was a unicode space character. The root cause of the crash is that we were implicitly assuming that if a space character was not " \t\f\v\r", it would have to be "\n". We fix this by instead defining horizontal space as: any space character that is not '\n'. Fixes haskell/haddock#1142 - - - - - 2d360ba1 by Alec Theriault at 2020-03-27T21:57:32-04:00 Disallow qualified uses of reserved identifiers This a GHC bug (https://gitlab.haskell.org/ghc/ghc/issues/14109) too, but it is a relatively easy fix in Haddock. Note that the fix must live in `haddock-api` instead of `haddock-library` because we can only really decide if an identifier is a reserved one by asking the GHC lexer. Fixes haskell/haddock#952 - - - - - 47ae22ed by Alec Theriault at 2020-03-28T13:36:25-04:00 Remove unused `Haddock.Utils` functions * removed functions in `Haddock.Utils` that were not used anywhere (or exported from the `haddock-api` package) * moved GHC-specific utils from `Haddock.Utils` to `Haddock.GhcUtils` - - - - - c0291245 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use TTG empty extensions to remove some `error`'s None of these error cases should ever have been reachable, so this is just a matter of leveraging the type system to assert this. * Use the `NoExtCon` and `noExtCon` to handle case matches for no extension constructors, instead of throwing an `error`. * Use the extension field of `HsSpliceTy` to ensure that this variant of `HsType` cannot exist in an `HsType DocNameI`. - - - - - 0aff8dc4 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use `unLoc`/`noLoc` from GHC instead of `unL`/`reL` * `unL` is already defined by GHC as `unLoc` * `reL` is already defined by GHC as `noLoc` (in a safer way too!) * Condense `setOutputDir` and add a about exporting from GHC Fixes haskell/haddock#978 - - - - - bf6f2fb7 by Alec Theriault at 2020-03-28T13:36:25-04:00 Cleanup up GHC flags in `.cabal` files * enable more useful warning flags in `haddock-api`, handle the new warnings generated * remove `-fwarn-tabs` (now we'd use `-Wtabs`, but this has been in `-Wall` for a while now) - - - - - c576fbf1 by Alec Theriault at 2020-03-28T13:36:25-04:00 `haddock-library` document header level Document the fact the header level is going to always be between 1 and 6 inclusive. Along the way, I also optimized the parsing code a bit. - - - - - 71bce0ee by Alec Theriault at 2020-03-28T14:26:27-04:00 Disallow links in section headers This is quite straightforward to implement, since we already had a function `docToHtmlNoAnchors` (which we used to generate the link in the sidebar "Contents"). This breaks test `Bug387`, but that test case has aged badly: we now automatically generate anchors for all headings, so manually adding an anchor in a section makes no sense. Nested anchors are, as pointed out in haskell/haddock#1054, disallowed by the HTML standard. Fixes haskell/haddock#1054 - - - - - b461b0ed by Sylvain Henry at 2020-03-30T10:34:23+02:00 Modules: type checker - - - - - cd8cd1ee by Ben Gamari at 2020-03-31T12:45:02-04:00 Merge pull request haskell/haddock#1152 from hsyl20/wip/hsyl20/modules/tc Module renaming - - - - - 5e8f8ea7 by Felix Yan at 2020-04-01T17:58:06-07:00 Allow QuickCheck 2.14 Builds fine and all tests pass. - - - - - dc6b1633 by Sylvain Henry at 2020-04-05T16:43:44+02:00 Module renaming: amend previous patch - - - - - eee2f4ae by Ryan Scott at 2020-04-05T09:04:43-07:00 Fix haskell/haddock#1050 by filtering out invisible AppTy arguments This makes the `synifyType` case for `AppTy` more intelligent by taking into consideration the visibilities of each `AppTy` argument and filtering out any invisible arguments, as they aren't intended to be displayed in the source code. (See haskell/haddock#1050 for an example of what can happen if you fail to filter these out.) Along the way, I noticed that a special `synifyType` case for `AppTy t1 (CoercionTy {})` could be consolidated with the case below it, so I took the opportunity to tidy this up. - - - - - 23eb99e8 by Ben Gamari at 2020-04-07T11:19:58-04:00 Merge pull request haskell/haddock#1154 from hsyl20/wip/hsyl20/modules/tc Module renaming: amend previous patch - - - - - 072d994d by Ryan Scott at 2020-04-07T19:32:47-04:00 Make NoExtCon fields strict These changes are a part of a fix for [GHC#17992](https://gitlab.haskell.org/ghc/ghc/issues/17992). - - - - - d8ebf6c8 by Ignat Insarov at 2020-04-09T21:15:01-04:00 Recode Doc to Json. (#1159) * Recode Doc to Json. * More descriptive field labels. - - - - - 52df4b4e by Sylvain Henry at 2020-04-10T12:39:18+02:00 Module renaming - - - - - d9ab8ec8 by Cale Gibbard at 2020-04-14T11:43:34-04:00 Add instance of XCollectPat for DocNameI - - - - - 323d221d by Cale Gibbard at 2020-04-14T11:43:34-04:00 Rename XCollectPat -> CollectPass - - - - - 2df80867 by Alec Theriault at 2020-04-15T07:30:51-07:00 Prune docstrings that are never rendered When first creating a Haddock interface, trim `ifaceDocMap` and `ifaceArgMap` to not include docstrings that can never appear in the final output. Besides checking with GHC which names are exported, we also need to keep all the docs attached to instance declarations (it is much tougher to detect when an instance is fully private). This change means: * slightly smaller interface files (7% reduction on boot libs) * slightly less work to do processing docstrings that aren't used * no warnings in Haddock's output about private docstrings (see haskell/haddock#1070) I've tested manually that this does not affect any of the boot library generated docs (the only change in output was some small re-ordering in a handful of instance lists). This should mean no docstrings have been incorrectly dropped. - - - - - f49c90cc by Alec Theriault at 2020-04-15T07:30:51-07:00 Don't warn about missing links in miminal sigs When renaming the Haddock interface, never emit warnings when renaming a minimal signature. Also added some documention around `renameInterface`. Minimal signatures intentionally include references to potentially un-exported methods (see the discussion in haskell/haddock#330), so it is expected that they will not always have a link destination. On the principle that warnings should always be resolvable, this shouldn't produce a warning. See haskell/haddock#1070. - - - - - a9eda64d by Ben Gamari at 2020-04-17T09:27:35-04:00 Merge pull request haskell/haddock#1160 from hsyl20/wip/hsyl20/modules/systools Module renaming - - - - - f40d7879 by Cale Gibbard at 2020-04-20T11:30:38-04:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ttg-con-pat - - - - - a50e7753 by Ben Gamari at 2020-04-20T11:36:10-04:00 Merge pull request haskell/haddock#1165 from obsidiansystems/wip/ttg-con-pat Trees that Grow refactor (GHC !2553) - - - - - 6a24795c by Alec Theriault at 2020-04-21T08:06:45-07:00 Fallback to `hiDecl` when `extractDecl` fails Sometimes, the declaration being exported is a subdecl (for instance, a record accessor getting exported at the top-level). For these cases, Haddock has to find a way to produce some synthetic sensible top-level declaration. This is done with `extractDecl`. As is shown by haskell/haddock#1067, this is sometimes impossible to do just at a syntactic level (for instance when the subdecl is re-exported). In these cases, the only sensible thing to do is to try to reify a declaration based on a GHC `TyThing` via `hiDecl`. - - - - - eee1a8b7 by Sylvain Henry at 2020-04-24T15:46:05+02:00 Module structure - - - - - 50b9259c by Iñaki at 2020-04-25T18:38:11-04:00 Add support for custom section anchors (#1179) This allows to have stable anchors for groups, even if the set of groups in the documentation is altered. The syntax for setting the anchor of a group is -- * Group name #desiredAnchor# Which will produce an html anchor of the form '#g:desiredAnchor' Co-authored-by: Iñaki García Etxebarria <git at inaki.blueleaf.cc> - - - - - 4003c97a by Ben Gamari at 2020-04-26T09:35:15-04:00 Merge pull request haskell/haddock#1166 from hsyl20/wip/hsyl20/modules/utils Module structure - - - - - 5206ab60 by Sylvain Henry at 2020-04-27T16:47:39+02:00 Renamed UnitInfo fields - - - - - c32c333b by Sylvain Henry at 2020-04-27T17:32:58+02:00 UnitId has been renamed into Unit - - - - - 3e87db64 by Sylvain Henry at 2020-04-27T17:36:00+02:00 Fix for GHC.Unit.* modules - - - - - ae3323a7 by Ben Gamari at 2020-04-29T12:36:37-04:00 Merge pull request haskell/haddock#1183 from hsyl20/wip/hsyl20/unitid Refactoring of Unit code - - - - - b105564a by Artem Pelenitsyn at 2020-05-03T08:14:10+01:00 add dependency on exceptions because GHC.Exception was boiled down (ghc haskell/haddock#18075) - - - - - 9857eff3 by Zubin Duggal at 2020-05-04T18:48:25+01:00 Atomic update of NameCache in readHieFile - - - - - 86bbb226 by Sylvain Henry at 2020-05-14T16:36:27+02:00 Fix after Config module renaming - - - - - a4bbdbc2 by Gert-Jan Bottu at 2020-05-15T22:09:44+02:00 Explicit Specificity Support for Haddock - - - - - 46199daf by Ben Gamari at 2020-05-19T09:59:56-04:00 Merge pull request haskell/haddock#1192 from hsyl20/hsyl20/modules-config Fix after Config module renaming - - - - - f9a9d2ba by Gert-Jan Bottu at 2020-05-20T16:48:38-04:00 Explicit Specificity Support for Haddock - - - - - 55c5b7ea by Ben Gamari at 2020-05-21T00:32:02-04:00 Merge commit 'a8d7e66da4dcc3b242103271875261604be42d6e' into ghc-head - - - - - a566557f by Cale Gibbard at 2020-05-21T16:02:06-04:00 isBootSummary now produces a result of type IsBootInterface - - - - - ea52f905 by Zubin Duggal at 2020-05-24T17:55:48+01:00 update for hiefile-typeclass-info - - - - - 49ba7a67 by Willem Van Onsem at 2020-05-25T12:23:01-04:00 Use floor over round to calculate the percentage (#1195) If we compile documentation where only a small fraction is undocumented, it is misleading to see 100% coverage - 99% is more intuitive. Fixes haskell/haddock#1194 - - - - - c025ebf1 by Ben Gamari at 2020-05-29T14:32:42-04:00 Merge pull request haskell/haddock#1185 from obsidiansystems/boot-disambig isBootSummary now produces a result of type IsBootInterface - - - - - 74ab9415 by Ben Gamari at 2020-05-29T20:23:39-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - b40be944 by Ben Gamari at 2020-06-03T17:02:31-04:00 testsuite: Update expected output for simplified subsumption - - - - - 624be71c by Ryan Scott at 2020-06-05T12:43:23-04:00 Changes for GHC#18191 See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3337. - - - - - fbd8f7ce by Sylvain Henry at 2020-06-08T15:31:47+02:00 Fix after unit refactoring - - - - - 743fda4d by Ben Gamari at 2020-06-09T12:09:58-04:00 Merge pull request haskell/haddock#1202 from hsyl20/wip/hsyl20/unitid-ii Fix after unit refactoring - - - - - d07a06a9 by Ryan Scott at 2020-06-13T07:16:55-04:00 Use HsForAllTelescope (GHC#18235) - - - - - 389bb60d by Ben Gamari at 2020-06-13T15:30:52-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - 7a377f5f by Ben Gamari at 2020-06-17T14:53:16-04:00 Merge pull request haskell/haddock#1199 from bgamari/wip/ghc-8.12 haddock: Bounds bumps for GHC 8.12 - - - - - 9fd9e586 by Krzysztof Gogolewski at 2020-06-17T16:09:07-04:00 Adapt Haddock to LinearTypes See ghc/ghc!852. - - - - - 46fe7636 by Ben Gamari at 2020-06-18T14:20:02-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 35a3c9e2 by Zubin Duggal at 2020-06-21T21:19:18+05:30 Use functions exported from HsToCore - - - - - 8abe3928 by Ben Gamari at 2020-06-24T13:53:39-04:00 Merge pull request haskell/haddock#1204 from wz1000/wip/haddock-hstocore Use functions exported from GHC.HsToCore.Docs - - - - - 22f2c937 by Matthías Páll Gissurarson at 2020-06-26T19:07:03+02:00 Adapt Haddock for QualifiedDo - - - - - 3f6208d7 by Vladislav Zavialov at 2020-06-28T14:28:16+03:00 Handle LexicalNegation's ITprefixminus - - - - - 03a19f41 by Sylvain Henry at 2020-07-02T09:37:38+02:00 Rename hsctarget into backend - - - - - ea17ff23 by Andreas Klebinger at 2020-07-02T17:44:18+02:00 Update for UniqFM changes. - - - - - 9872f2f3 by Ben Gamari at 2020-07-09T10:39:19-04:00 Merge pull request haskell/haddock#1209 from AndreasPK/wip/typed_uniqfm Update for UniqFM changes. - - - - - 68f7b668 by Krzysztof Gogolewski at 2020-07-12T18:16:57+02:00 Sync with GHC removing {-# CORE #-} pragma See ghc ticket haskell/haddock#18048 - - - - - eb372681 by Sylvain Henry at 2020-07-20T11:41:30+02:00 Rename hscTarget into backend - - - - - fb7f78bf by Ben Gamari at 2020-07-21T12:15:25-04:00 Merge pull request haskell/haddock#1214 from hsyl20/wip/hsyl20/hadrian/ncg Rename hscTarget into backend - - - - - 1e8f5b56 by Ben Gamari at 2020-07-23T09:11:50-04:00 Merge commit '904dce0cafe0a241dd3ef355775db47fc12f434d' into ghc-head - - - - - d8fd1775 by Zubin Duggal at 2020-07-23T18:46:40+05:30 Update for modular ping pong - - - - - 8416f872 by Ben Gamari at 2020-07-23T09:35:03-04:00 Merge pull request haskell/haddock#1200 from wz1000/wip/wz1000-modular-ping-pong Modular ping pong - - - - - a24a8577 by Ben Gamari at 2020-07-28T15:23:36-04:00 Bump GHC version to 9.0 - - - - - 6a51c9dd by Sylvain Henry at 2020-08-05T18:47:05+02:00 Fix after Outputable refactoring - - - - - c05e1c99 by Ben Gamari at 2020-08-10T14:41:41-04:00 Merge pull request haskell/haddock#1223 from hsyl20/wip/hsyl20/dynflags/exception Fix after Outputable refactoring - - - - - d964f15b by Sylvain Henry at 2020-08-12T11:58:49+02:00 Fix after HomeUnit - - - - - 8e6d5b23 by Ben Gamari at 2020-08-12T14:25:30-04:00 Merge pull request haskell/haddock#1225 from hsyl20/wip/hsyl20/plugins/homeunit Fix after HomeUnit - - - - - 8c7880fe by Sylvain Henry at 2020-08-17T14:13:29+02:00 Remove Ord FastString instance - - - - - 8ea410db by Alex Biehl at 2020-08-19T10:56:32+02:00 Another round of `npm audit fix` (#1228) This should shut down the warnings on Github. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. Last NPM dependency audit happend in d576b2327e2bc117f912fe0a9d595e9ae62614e0 Co-authored-by: Alex Biehl <alex.biehl at target.com> - - - - - 7af6e2a8 by Ben Gamari at 2020-08-31T13:59:34-04:00 Merge pull request haskell/haddock#1226 from hsyl20/wip/hsyl20/fs_ord Remove Ord FastString instance - - - - - ffbc8702 by Alan Zimmerman at 2020-09-07T21:47:41+01:00 Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - a93f1268 by Alan Zimmerman at 2020-09-07T23:11:38+01:00 Merge pull request haskell/haddock#1232 from haskell/wip/T18639-remove-generated-pragma, Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - 1f605d50 by Ben Gamari at 2020-09-14T18:30:01-04:00 Bump GHC version to 9.1 - - - - - 6599df62 by Vladislav Zavialov at 2020-09-18T14:05:15+03:00 Bump base upper bound to 4.16 - - - - - a01b3c43 by Ben Gamari at 2020-09-22T15:41:48-04:00 Update hypsrc-test for QuickLook This appears to be a spurious change. - - - - - e9cc6cac by Vladislav Zavialov at 2020-09-26T21:00:12+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 30e3ca7c by Sylvain Henry at 2020-09-29T11:18:32-04:00 Update for parser (#1234) - - - - - b172f3e3 by Vladislav Zavialov at 2020-09-30T01:01:30+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 0b9c08d3 by Sylvain Henry at 2020-09-30T11:02:33+02:00 Adapt to GHC parser changes - - - - - b9540b7a by Sylvain Henry at 2020-10-12T09:13:38-04:00 Don't pass the HomeUnitId (#1239) - - - - - 34762e80 by HaskellMouse at 2020-10-13T12:58:04+03:00 Changed tests due to unification of `Nat` and `Natural` in the follwing merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3583 - - - - - 256f86b6 by Vladislav Zavialov at 2020-10-15T10:48:03+03:00 Add whitespace in: map ($ v) - - - - - 4a3f711b by Alan Zimmerman at 2020-10-19T08:57:27+01:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled - - - - - 072cdd21 by Alan Zimmerman at 2020-10-21T14:48:28-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 9e09a445 by Alan Zimmerman at 2020-10-21T23:53:34-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 636d7de3 by Sylvain Henry at 2020-10-26T14:31:54-04:00 GHC.Driver.Types refactoring (#1242) - - - - - a597f000 by Ryan Scott at 2020-10-29T04:18:05-04:00 Adapt to the removal of Hs{Boxed,Constraint}Tuple See ghc/ghc!4097 and GHC#18723. - - - - - b96660fb by Ryan Scott at 2020-10-30T04:53:05-04:00 Adapt to HsConDecl{H98,GADT}Details split Needed for GHC#18844. - - - - - c287d82c by Ryan Scott at 2020-10-30T19:35:59-04:00 Adapt to HsOuterTyVarBndrs These changes accompany ghc/ghc!4107, which aims to be a fix for haskell/haddock#16762. - - - - - a34c31a1 by Ryan Scott at 2020-11-13T13:38:34-05:00 Adapt to splitPiTysInvisible being renamed to splitInvisPiTys This is a part of !4434, a fix for GHC#18939. - - - - - 66ea459d by Sylvain Henry at 2020-11-16T10:59:30+01:00 Fix after Plugins moved into HscEnv - - - - - 508556d8 by Ben Gamari at 2020-11-18T15:47:40-05:00 Merge pull request haskell/haddock#1253 from hsyl20/wip/hsyl20/plugins/hscenv Fix after Plugins moved into HscEnv - - - - - 620fec1a by Andreas Klebinger at 2020-11-24T20:51:59+01:00 Update for changes in GHC's Pretty - - - - - 01cc13ab by Richard Eisenberg at 2020-11-25T23:18:35-05:00 Avoid GHC#18932. - - - - - 8d29ba21 by Cale Gibbard at 2020-11-25T23:18:35-05:00 Add type arguments to PrefixCon - - - - - 414d5f87 by Sylvain Henry at 2020-11-30T17:06:04+01:00 DynFlags's unit fields moved to HscEnv - - - - - e356668c by Ben Gamari at 2020-11-30T11:11:37-05:00 Merge pull request haskell/haddock#1258 from hsyl20/wip/hsyl20/hscenv/unitstate Unit fields moved from DynFlags to HscEnv - - - - - 7cf552f1 by Ben Gamari at 2020-12-03T10:31:27-05:00 Merge pull request haskell/haddock#1257 from AndreasPK/wip/andreask/opt_dumps Update for changes in GHC's Pretty - - - - - fc0871c3 by Veronika Romashkina at 2020-12-08T16:35:33+01:00 Fix docs links from Darcs to GitHub in intro (#1262) - - - - - 7059e808 by Veronika Romashkina at 2020-12-08T16:36:16+01:00 Use gender neutral word in docs (#1260) - - - - - 1b16e5ee by Maximilian Tagher at 2020-12-08T16:40:03+01:00 Allow scrolling search results (#1235) Closes https://github.com/haskell/haddock/issues/1231 - - - - - 8a118c01 by dependabot[bot] at 2020-12-08T16:40:25+01:00 Bump bl from 1.2.2 to 1.2.3 in /haddock-api/resources/html (#1255) Bumps [bl](https://github.com/rvagg/bl) from 1.2.2 to 1.2.3. - [Release notes](https://github.com/rvagg/bl/releases) - [Commits](https://github.com/rvagg/bl/compare/v1.2.2...v1.2.3) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - c89ff587 by Xia Li-yao at 2020-12-08T16:42:17+01:00 Allow more characters in anchor following module reference (#1220) - - - - - 14af7d64 by Xia Li-yao at 2020-12-08T16:43:05+01:00 Add dangling changes from branches ghc-8.6 and ghc-8.8 (#1243) * Fix multiple typos and inconsistencies in doc/markup.rst Note: I noticed some overlap with haskell/haddock#1112 from @wygulmage and haskell/haddock#1081 from @parsonsmatt after creating these proposed changes - mea culpa for not looking at the open PRs sooner. * Fix haskell/haddock#1113 If no Signatures, no section of index.html * Change the formatting of missing link destinations The current formatting of the missing link destination does not really help user to understand the reasons of the missing link. To address this, I've changed the formatting in two ways: - the missing link symbol name is now fully qualified. This way you immediately know which haskell module cannot be linked. It is then easier to understand why this module does not have documentation (hidden module or broken documentation). - one line per missing link, that's more readable now that symbol name can be longer due to qualification. For example, before haddock was listing missing symbol such as: ``` could not find link destinations for: Word8 Word16 mapMaybe ``` Now it is listed as: ``` could not find link destinations for: - Data.Word.Word8 - Data.Word.Word16 - Data.Maybe.mapMaybe ``` * Add `--ignore-link-symbol` command line argument This argument can be used multiples time. A missing link to a symbol listed by `--ignore-link-symbol` won't trigger "missing link" warning. * Forbid spaces in anchors (#1148) * Improve error messages with context information (#1060) Co-authored-by: Matt Audesse <matt at mattaudesse.com> Co-authored-by: Mike Pilgrem <mpilgrem at users.noreply.github.com> Co-authored-by: Guillaume Bouchard <guillaume.bouchard at tweag.io> Co-authored-by: Pepe Iborra <pepeiborra at gmail.com> - - - - - 89e3af13 by tomjaguarpaw at 2020-12-08T18:00:04+01:00 Enable two warnings (#1245) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - c3320f8d by Willem Van Onsem at 2020-12-08T18:26:55+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 685df308 by Alex Biehl at 2020-12-08T20:06:26+01:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - be3ec3c0 by Alex Biehl at 2020-12-08T20:06:26+01:00 Import intercalate - - - - - 32c33912 by Matthías Páll Gissurarson at 2020-12-08T21:15:30+01:00 Adapt Haddock for QualifiedDo - - - - - 31696088 by Alex Biehl at 2020-12-08T22:06:02+01:00 Fix haddock-library tests - - - - - fbc0998a by Alex Biehl at 2020-12-08T23:08:23+01:00 Move to GitHub CI (#1266) * Initial version of ci.yml This is a straight copy from Dmitrii Kovanikov's blog post at https://kodimensional.dev/github-actions. Will adapt to haddock in successive commits. * Delete .travis.yml * Modify to only test on ghc-8.10.{1,2} * Use actions/setup-haskell at v1.1.4 * Relax QuickCheck bound on haddock-api * Remove stack matrix for now * Nail down to ghc-8.10 branch for now * Pin index state to 2020-12-08T20:13:44Z for now * Disable macOS and Windows tests for now for speed up - - - - - 5b946b9a by tomjaguarpaw at 2020-12-10T19:01:41+01:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - bc5a408f by dependabot[bot] at 2020-12-10T19:02:16+01:00 Bump ini from 1.3.5 to 1.3.7 in /haddock-api/resources/html (#1269) Bumps [ini](https://github.com/isaacs/ini) from 1.3.5 to 1.3.7. - [Release notes](https://github.com/isaacs/ini/releases) - [Commits](https://github.com/isaacs/ini/compare/v1.3.5...v1.3.7) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - d02995f1 by Andrew Martin at 2020-12-14T16:48:40-05:00 Update for boxed rep - - - - - a381aeff by Ben Gamari at 2020-12-15T15:13:30-05:00 Revert "Enable two warnings (#1245) (#1268)" As this does not build on GHC `master`. This reverts commit 7936692badfe38f23ae95b51fb7bd7c2ff7e9bce. - - - - - a63c0a9e by Ben Gamari at 2020-12-15T15:17:59-05:00 Revert "Update for boxed rep" This reverts commit 4ffb30d8b637ccebecc81ce610f0af451ac8088d. - - - - - 53bfbb29 by Ben Gamari at 2020-12-15T15:37:24-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - bae76a30 by Ben Gamari at 2020-12-16T02:44:42+00:00 Update output for nullary TyConApp optimisation (ghc/ghc!2952) - - - - - 4b733b57 by Krzysztof Gogolewski at 2020-12-16T20:03:14+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. - - - - - ee463bd3 by Ryan Scott at 2020-12-16T16:55:23-05:00 Adapt to HsCoreTy (formerly NewHsTypeX) becoming a type synonym Needed for !4417, the fix for GHC#15706 and GHC#18914. - - - - - ed0b02f8 by tomjaguarpaw at 2020-12-19T10:17:19+00:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - d80bf8f5 by Sylvain Henry at 2020-12-21T10:09:25+01:00 Fix after binder collect changes - - - - - bf4c9d32 by Adam Gundry at 2020-12-23T21:35:01+00:00 Adapt to changes to GlobalRdrElt and AvailInfo Needed for ghc/ghc!4467 - - - - - 37736c4c by John Ericson at 2020-12-28T12:27:02-05:00 Support a new ghc --make node type for parallel backpack upsweep - - - - - 717bdeac by Vladislav Zavialov at 2020-12-29T10:50:02+03:00 Inline and fix getGADTConTypeG The getGADTConTypeG used HsRecTy, which is at odds with GHC issue haskell/haddock#18782. I noticed that getGADTConTypeG was only used in the Hoogle backend. Interestingly, when handling H98 constructors, Hoogle converts RecCon to PrefixCon (see Haddock.Backends.Hoogle.ppCtor). So I changed getGADTConTypeG to handle RecConGADT in the same manner as PrefixConGADT, and after this simplification moved it into the 'where' clause of ppCtor, to the only place where it is used. The practical effect of this change is as follows. Consider this example: data TestH98 = T98 { bar::Int } data TestGADT where TG :: { foo :: Int } -> TestGADT Before this patch, haddock --hoogle used to produce: T98 :: Int -> TestH98 [TG] :: {foo :: Int} -> TestGADT Notice how the record syntax was discarded in T98 but not TG. With this patch, we always produce signatures without record syntax: T98 :: Int -> TestH98 [TG] :: Int -> TestGADT I suspect this might also be a bugfix, as currently Hoogle doesn't seem to render GADT record constructors properly. - - - - - cb1b8c56 by Andreas Abel at 2020-12-30T21:12:37+01:00 Build instructions: haddock-library and -api first! - - - - - b947f6ad by Ben Gamari at 2020-12-31T13:04:19-05:00 Merge pull request haskell/haddock#1281 from obsidiansystems/wip/backpack-j Changes to support -j with backpack - - - - - 120e1cfd by Hécate Moonlight at 2021-01-04T19:54:58+01:00 Merge pull request haskell/haddock#1282 from andreasabel/master Build instructions: haddock-library and -api first! - - - - - fd45e41a by Ben Gamari at 2021-01-05T16:14:31-05:00 Merge remote-tracking branch 'origin/ghc-8.10' into ghc-9.0 - - - - - b471bdec by Ben Gamari at 2021-01-05T16:23:02-05:00 Merge commit '1e56f63c3197e7ca1c1e506e083c2bad25d08793' into ghc-9.0 - - - - - 81cdbc41 by Alex Biehl at 2021-01-09T12:14:41+01:00 Prepare Haddock for being a GHC Plugin - - - - - b646d952 by Alex Biehl at 2021-01-09T12:14:41+01:00 Make Haddock a GHC Plugin - - - - - cc044674 by Alex Biehl at 2021-01-09T12:14:41+01:00 Add -j[n] CLI param to Haddock executable It translates to `--ghcopt=-j[n]` - - - - - 84a04073 by Alex Biehl at 2021-01-09T12:14:41+01:00 Abstract Monad for interface creation I found that when running as a plugin the lookupName function (which runs in Ghc monad) does not work correctly from the typeCheckResultAction hook. Instead, we abstracted the monad used when creating interfaces, so that access to GHC session specific parts is explicit and so that the TcM can provide their (correct) implementation of lookupName. - - - - - 5be2c4f7 by Alex Biehl at 2021-01-09T12:14:41+01:00 Accept tests - - - - - 8cefee9d by Alex Biehl at 2021-01-09T16:10:47+01:00 Add missing dependency for mtl - - - - - 3681f919 by Ben Gamari at 2021-01-13T18:39:25-05:00 Merge remote-tracking branch 'origin/ghc-9.0' into ghc-head - - - - - 33c6b152 by Hécate Moonlight at 2021-01-14T16:04:20+01:00 Merge pull request haskell/haddock#1273 from hsyl20/wip/hsyl20/arrows Fix after binder collect changes - - - - - 70d13e8e by Joachim Breitner at 2021-01-22T19:03:45+01:00 Make haddock more robust to changes to the `Language` data type With the introduction of GHC2021, the `Languages` data type in GHC will grow. In preparation of that (and to avoid changing haddock with each new language), this change makes the code handle extensions to that data type gracefully. (cherry picked from commit c341dd7c9c3fc5ebc83a2d577c5a726f3eb152a5) - - - - - 7d6dd57a by John Ericson at 2021-01-22T22:02:02+00:00 Add `NoGhcTc` instance now that it's not closed - - - - - e5fdaf0a by Alan Zimmerman at 2021-01-23T22:57:44+00:00 Merge pull request haskell/haddock#1293 from obsidiansystems/wip/fix-18936 Add `NoGhcTc` instance now that it's not closed - - - - - 989a1e05 by Oleg Grenrus at 2021-01-24T16:11:46+03:00 Add import list to Data.List - - - - - 368e144a by Ben Gamari at 2021-01-28T22:15:48+01:00 Adapt to "Make PatSyn immutable" - - - - - abe66c21 by Alfredo Di Napoli at 2021-02-01T08:05:35+01:00 Rename pprLogErrMsg to new name - - - - - e600e75c by Hécate Moonlight at 2021-02-05T14:53:00+01:00 Move CI to ghc-9.0 - - - - - dd492961 by Vladislav Zavialov at 2021-02-05T14:53:00+01:00 Update cabal.project and README build instructions - - - - - 31bd292a by Hécate Moonlight at 2021-02-05T15:03:56+01:00 Merge pull request haskell/haddock#1296 from Kleidukos/ghc-9.0 Merge the late additions to ghc-8.10 into ghc-9.0 - - - - - 6388989e by Vladislav Zavialov at 2021-02-05T17:41:57+03:00 Cleanup: fix build warnings - - - - - f99407ef by Daniel Rogozin at 2021-02-05T18:11:48+03:00 type level characters support for haddock (required for haskell/haddock#11342) - - - - - d8c6b26f by Hécate Moonlight at 2021-02-05T17:44:50+01:00 Add a CONTRIBUTING.md file - - - - - 6a01ad98 by Hécate Moonlight at 2021-02-05T17:58:16+01:00 Merge pull request haskell/haddock#1312 from Kleidukos/proper-branch-etiquette Add a CONTRIBUTING.md file - - - - - 955eecc4 by Vladislav Zavialov at 2021-02-05T20:29:00+03:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into ghc-head - - - - - 47b3d6ab by Hécate Moonlight at 2021-02-05T19:09:38+01:00 Amend the CONTRIBUTING.md file - - - - - 23de6137 by Hécate Moonlight at 2021-02-05T19:16:49+01:00 Merge pull request haskell/haddock#1313 from Kleidukos/amend-contributing Amend the CONTRIBUTING.md file - - - - - 69026b59 by Krzysztof Gogolewski at 2021-02-05T23:05:56+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. (cherry picked from commit b4b4d896d2d68d6c48e7db7bfe95c185ca0709cb) - - - - - ea026b78 by Oleg Grenrus at 2021-02-06T17:14:45+01:00 Add import list to Data.List - - - - - 5204326f by Hécate Moonlight at 2021-02-06T17:15:44+01:00 Merge pull request haskell/haddock#1316 from Kleidukos/explicit-imports-to-data-list Add import list to Data.List - - - - - 1f4d2136 by Ben Gamari at 2021-02-06T11:53:31-05:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ghc-head-merge - - - - - 13f0d09a by Ben Gamari at 2021-02-06T11:53:45-05:00 Fix partial record selector warning - - - - - 5c115f7e by Ben Gamari at 2021-02-06T11:55:52-05:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into wip/ghc-head-merge - - - - - b6fd8b75 by Ben Gamari at 2021-02-06T12:01:31-05:00 Merge commit '41964cb2fd54b5a10f8c0f28147015b7d5ad2c02' into wip/ghc-head-merge - - - - - a967194c by Ben Gamari at 2021-02-06T18:30:35-05:00 Merge branch 'wip/ghc-head-merge' into ghc-head - - - - - 1f4c3a91 by MorrowM at 2021-02-07T01:52:33+02:00 Fix search div not scrolling - - - - - 684b1287 by Iñaki García Etxebarria at 2021-02-07T16:13:04+01:00 Add support for labeled module references Support a markdown-style way of annotating module references. For instance -- | [label]("Module.Name#anchor") will create a link that points to the same place as the module reference "Module.Name#anchor" but the text displayed on the link will be "label". - - - - - bdb55a5d by Hécate Moonlight at 2021-02-07T16:18:10+01:00 Merge pull request haskell/haddock#1319 from alexbiehl/alex/compat Backward compat: Add support for labeled module references - - - - - 6ca70991 by Hécate Moonlight at 2021-02-07T16:21:29+01:00 Merge pull request haskell/haddock#1314 from tweag/show-linear-backport Backport haskell/haddock#1238 (linear types) to ghc-9.0 - - - - - d9d73298 by Alex Biehl at 2021-02-07T17:46:25+01:00 Remove dubious parseModLink Instead construct the ModLink value directly when parsing. - - - - - 33b4d020 by Hécate Moonlight at 2021-02-07T17:52:05+01:00 Merge pull request haskell/haddock#1320 from haskell/alex/fix Remove dubious parseModLink - - - - - 54211316 by Hécate Moonlight at 2021-02-07T18:12:07+01:00 Merge pull request haskell/haddock#1318 from MorrowM/ghc-9.0 Fix search div not scrolling - - - - - 19db679e by alexbiehl-gc at 2021-02-07T18:14:46+01:00 Merge pull request haskell/haddock#1317 from bgamari/wip/ghc-head-merge Merge ghc-8.10 into ghc-head - - - - - 6bc1e9e4 by Willem Van Onsem at 2021-02-07T18:25:30+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - c8537cf8 by alexbiehl-gc at 2021-02-07T18:30:40+01:00 Merge pull request haskell/haddock#1322 from haskell/alex/forward-port simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 2d47ae4e by alexbiehl-gc at 2021-02-07T18:39:59+01:00 Merge branch 'ghc-head' into ghc-9.0 - - - - - 849e4733 by Hécate Moonlight at 2021-02-07T18:43:19+01:00 Merge pull request haskell/haddock#1321 from Kleidukos/ghc-9.0 Merge ghc-9.0 into ghc-head - - - - - ee6095d7 by Sylvain Henry at 2021-02-08T11:36:38+01:00 Update for Logger - - - - - 4ad688c9 by Alex Biehl at 2021-02-08T18:11:24+01:00 Merge pull request haskell/haddock#1310 from hsyl20/wip/hsyl20/logger2 Logger refactoring - - - - - 922a9e0e by Ben Gamari at 2021-02-08T12:54:33-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - 991649d2 by Sylvain Henry at 2021-02-09T10:55:17+01:00 Fix to build with HEAD - - - - - a8348dc2 by Hécate Moonlight at 2021-02-09T10:58:51+01:00 Merge pull request haskell/haddock#1327 from hsyl20/wip/hsyl20/logger2 Fix to build with HEAD - - - - - 0abdbca6 by Fendor at 2021-02-09T20:06:15+01:00 Add UnitId to Target record - - - - - d5790a0e by Alex Biehl at 2021-02-11T10:32:32+01:00 Stable sort for (data/newtype) instances - - - - - 8e6036f5 by Alex Biehl at 2021-02-11T10:32:32+01:00 Also make TyLit deterministic - - - - - f76d2945 by Hécate Moonlight at 2021-02-11T11:00:31+01:00 Merge pull request haskell/haddock#1329 from hsyl20/hsyl20/stabe_iface Stable sort for instances - - - - - 5e0469ea by Oleg Grenrus at 2021-02-14T15:28:15+02:00 Add import list to Data.List in Haddock.Interface.Create - - - - - fa57cd24 by Hécate Moonlight at 2021-02-14T17:19:27+01:00 Merge pull request haskell/haddock#1331 from phadej/more-explicit-data-list-imports Add import list to Data.List in Haddock.Interface.Create - - - - - f0cd629c by Hécate Moonlight at 2021-02-21T00:22:01+01:00 Merge pull request haskell/haddock#1311 from fendor/wip/add-targetUnitId-to-target Add UnitId to Target record - - - - - 674ef723 by Joachim Breitner at 2021-02-22T10:39:18+01:00 html-test: Always set language from ghc-9.2 on, the “default” langauge of GHC is expected to change more wildly. To prepare for that (and unblock https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4853), this sets the language for all the test files to `Haskell2010`. This should insolate this test suite against changes to the default. Cherry-picked from https://github.com/haskell/haddock/pull/1341 - - - - - f072d623 by Hécate Moonlight at 2021-02-22T10:56:51+01:00 Merge pull request haskell/haddock#1342 from nomeata/joachim/haskell2010-in-tests-ghc-head html-test: Always set language - - - - - caebbfca by Hécate Moonlight at 2021-02-22T11:53:07+01:00 Clean-up of Interface and Interface.Create's imports and pragmata - - - - - f6caa89d by Hécate Moonlight at 2021-02-22T11:54:58+01:00 Merge pull request haskell/haddock#1345 from Kleidukos/head/fix-interface-imports [ghc-head] Clean-up of Interface and Interface.Create's imports and pragmata - - - - - 7395c9cb by Hécate Moonlight at 2021-02-22T18:44:57+01:00 Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 6e9fb5d5 by Hécate Moonlight at 2021-02-22T18:45:28+01:00 Merge pull request haskell/haddock#1348 from Kleidukos/head/explicit-imports-interface Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 9198b118 by Alan Zimmerman at 2021-02-22T20:04:24+00:00 Context becomes a Maybe in the GHC AST This prevents noLoc's appearing in the ParsedSource. Match the change in GHC. - - - - - 0af20f64 by Hécate Moonlight at 2021-02-23T12:36:12+01:00 Fix the call-site of guessTarget in Interface.hs Explicit the imports from GHC.HsToCore.Docs - - - - - b7886885 by Hécate Moonlight at 2021-02-23T12:37:54+01:00 Merge pull request haskell/haddock#1349 from Kleidukos/fix-interface-guesstarget-call Fix the call-site of guessTarget in Interface.hs - - - - - 9cf041ba by Sylvain Henry at 2021-02-24T11:08:20+01:00 Fix haddockHypsrcTest output in ghc-head - - - - - b194182a by Hécate Moonlight at 2021-02-24T11:12:36+01:00 Merge pull request haskell/haddock#1351 from hsyl20/wip/hsyl20/fix-head Fix haddockHypsrcTest output in ghc-head - - - - - 3ce8b375 by Shayne Fletcher at 2021-03-06T09:55:03-05:00 Add ITproj to parser - - - - - d2abf762 by Ben Gamari at 2021-03-06T19:26:49-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a0f6047d by Andrew Martin at 2021-03-07T11:25:23-05:00 Update for boxed rep - - - - - 6f63c99e by Ben Gamari at 2021-03-10T13:20:21-05:00 Update for "FastString: Use FastMutInt instead of IORef Int" - - - - - e13f01df by Luke Lau at 2021-03-10T15:38:40-05:00 Implement template-haskell's putDoc This catches up to GHC using the new extractTHDocs function, which returns documentation added via the putDoc function (provided it was compiled with Opt_Haddock). Since it's already a map from names -> docs, there's no need to do traversal etc. It also matches the change from the argument map being made an IntMap rather than a Map Int - - - - - 89263d94 by Alan Zimmerman at 2021-03-15T17:15:26+00:00 Match changes in GHC AST for in-tree API Annotations As landed via https://gitlab.haskell.org/ghc/ghc/-/merge_requests/2418 - - - - - 28db1934 by Alan Zimmerman at 2021-03-15T20:40:09+00:00 Change some type family test results. It is not clear to me whether the original was printing incorrectly (since we did not have the TopLevel flag before now), or if this behaviour is expected. For the time being I am assuming the former. - - - - - 7c11c989 by Sylvain Henry at 2021-03-22T10:05:19+01:00 Fix after NameCache changes - - - - - addbde15 by Sylvain Henry at 2021-03-22T10:05:19+01:00 NameCache doesn't store a UniqSupply anymore - - - - - 15ec6cec by Ben Gamari at 2021-03-22T17:53:44-04:00 Bump GHC version to 9.2 - - - - - dbd6aa63 by Hécate Moonlight at 2021-03-24T14:28:36+01:00 Merge pull request haskell/haddock#1365 from hsyl20/wip/hsyl20/iface1 NameCache refactoring - - - - - 2d32da7e by Oleg Grenrus at 2021-03-27T01:12:00+02:00 Specialization of Data.List - - - - - 32b84fa6 by Fendor at 2021-03-27T10:50:17+01:00 Add UnitId to Target record This way we always know to which home-unit a given target belongs to. So far, there only exists a single home-unit at a time, but it enables having multiple home-units at the same time. - - - - - 54bf9f0e by Hécate Moonlight at 2021-03-28T14:08:35+02:00 Merge pull request haskell/haddock#1368 from fendor/target-unit-id-revert Add UnitId to Target record - - - - - 7dea168a by Alan Zimmerman at 2021-03-29T08:45:52+01:00 EPA : Rename ApiAnn to EpAnn - - - - - 72967f65 by Alfredo Di Napoli at 2021-03-29T09:47:01+02:00 pprError changed name in GHC - - - - - 4bc61035 by Alan Zimmerman at 2021-03-29T16:16:27-04:00 EPA : Rename ApiAnn to EpAnn - - - - - 108d031d by Ben Gamari at 2021-03-29T18:49:36-04:00 Merge commit '36418c4f70d7d2b179a77925b3ad5caedb08c9b5' into HEAD - - - - - 1444f700 by Ben Gamari at 2021-03-31T09:18:39-04:00 Merge pull request haskell/haddock#1370 from adinapoli/wip/adinapoli-diag-reason-severity Rename pprError to mkParserErr - - - - - d3087b79 by Ben Gamari at 2021-03-31T11:34:17-04:00 Merge commit 'd8d8024ad6796549a8d3b5512dabf3288d14e30f' into ghc-head - - - - - 170b79e9 by Ben Gamari at 2021-03-31T12:24:56-04:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - db0d6bae by Ben Gamari at 2021-04-10T09:34:35-04:00 Bump GHC version to 9.3 - - - - - a9f2c421 by Alan Zimmerman at 2021-04-19T18:26:46-04:00 Update for EPA changes in GHC (cherry picked from commit cafb48118f7c111020663776845897e225607b41) - - - - - 1ee4b7c7 by Sylvain Henry at 2021-05-11T10:00:06+02:00 Removal of HsVersions.h (#1388) * Update for EPA changes in GHC * Account for HsVersions.h removal Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 79e819e9 by Hécate Moonlight at 2021-05-11T10:14:47+02:00 Revert "Removal of HsVersions.h (#1388)" This reverts commit 72118896464f94d81f10c52f5d9261efcacc57a6. - - - - - 3dbd3f8b by Alan Zimmerman at 2021-05-11T10:15:17+02:00 Update for EPA changes in GHC - - - - - 2ce80c17 by Sylvain Henry at 2021-05-11T10:15:19+02:00 Account for HsVersions.h removal - - - - - 00e4c918 by Christiaan Baaij at 2021-05-13T08:21:56+02:00 Add Haddock support for the OPAQUE pragma (#1380) - - - - - 8f9049b2 by Hécate Moonlight at 2021-05-13T08:40:22+02:00 fixup! Use GHC 9.2 in CI runner - - - - - 27ddec38 by Alan Zimmerman at 2021-05-13T22:51:20+01:00 EPA: match changes from GHC T19834 - - - - - f8a1d714 by Felix Yan at 2021-05-14T17:10:04+02:00 Allow hspec 2.8 (#1389) All tests are passing. - - - - - df44453b by Divam Narula at 2021-05-20T15:42:42+02:00 Update ref, the variables got renamed. (#1391) This is due to ghc/ghc!5555 which caused a change in ModDetails in case of NoBackend. Now the initModDetails is used to recreate the ModDetails from interface and in-memory ModDetails is not used. - - - - - e46bfc87 by Alan Zimmerman at 2021-05-20T19:05:09+01:00 Remove Maybe from HsQualTy Match changes in GHC for haskell/haddock#19845 - - - - - 79bd7b62 by Shayne Fletcher at 2021-05-22T08:20:39+10:00 FieldOcc: rename extFieldOcc to foExt - - - - - 6ed68c74 by Ben Gamari at 2021-05-21T22:29:30-04:00 Merge commit '3b6a8774bdb543dad59b2618458b07feab8a55e9' into ghc-head - - - - - f9a02d34 by Alfredo Di Napoli at 2021-05-24T13:53:00+02:00 New Parser diagnostics interface - - - - - 392807d0 by Ben Gamari at 2021-05-24T09:57:40-04:00 Merge pull request haskell/haddock#1394 from adinapoli/wip/adinapoli-align-ps-messages Align Haddock to use the new Parser diagnostics interface - - - - - 33023cd8 by Ben Gamari at 2021-05-24T11:19:16-04:00 Revert "Add Haddock support for the OPAQUE pragma (#1380)" This reverts commit a1337c599ef7720b0482a25c55f11794112496dc. The GHC patch associated with this change is not yet ready to be merged. - - - - - 8c005af7 by Ben Simms at 2021-05-28T07:56:20+02:00 CI configuration for ghc-head (#1395) - - - - - 1e947612 by Hécate Moonlight at 2021-05-28T12:27:35+02:00 Use GHC 9.2 in CI runner (#1378) - - - - - e6fa10ab by CGenie at 2021-05-31T09:02:13+02:00 Add page about common errors (#1396) * Update index.rst Common errors page * Create common-errors.rst * Update common-errors.rst * Use GHC 9.2 in CI runner (#1378) * [haddock-api] remove .hspec-failures Co-authored-by: Hécate Moonlight <Kleidukos at users.noreply.github.com> - - - - - abc72a8d by Sylvain Henry at 2021-06-01T10:02:06+02:00 Adapt Haddock to Logger and Parser changes (#1399) - - - - - 91373656 by Zubin Duggal at 2021-06-01T20:45:10+02:00 Update haddockHypSrc tests since we now compute slighly more type info (#1397) - - - - - ed712822 by Marcin Szamotulski at 2021-06-02T08:54:33+02:00 Added myself to contributors - - - - - 49fdbcb7 by Marcin Szamotulski at 2021-06-02T08:57:24+02:00 Document multi component support - - - - - 9ddc8d7d by Hécate Moonlight at 2021-06-02T09:35:55+02:00 Merge pull request haskell/haddock#1379 from coot/coot/document-multi-component-support Document multi component support - - - - - 585b5c5e by Ben Simms at 2021-06-02T19:46:54+02:00 Update CONTRIBUTING.md (#1402) - - - - - 1df4a605 by Ben Simms at 2021-06-02T19:47:14+02:00 Update CONTRIBUTING.md (#1403) - - - - - 58ea43d2 by sheaf at 2021-06-02T22:09:06+02:00 Update Haddock Bug873 to account for renaming - - - - - c5d0ab23 by Vladislav Zavialov at 2021-06-10T13:35:42+03:00 HsToken in FunTy, RecConGADT - - - - - 1ae2f40c by Hécate Moonlight at 2021-06-11T11:19:09+02:00 Update the CI badges - - - - - 6fdc4de2 by Sylvain Henry at 2021-06-28T19:21:17+02:00 Fix mkParserOpts (#1411) - - - - - 18201670 by Alfredo Di Napoli at 2021-07-05T07:55:12+02:00 Rename getErrorMessages Lexer import This commit renames the Lexer import in `Hyperlinker.Parser` from `getErrorMessages` to `getPsErrorMessages` to eliminate the ambiguity with the `getErrorMessages` function defined in `GHC.Types.Error`. - - - - - 23173ca3 by Ben Gamari at 2021-07-07T11:31:44-04:00 Merge pull request haskell/haddock#1413 from adinapoli/wip/adinapoli-issue-19920 Rename getErrorMessages Lexer import - - - - - b3dc4ed8 by Alan Zimmerman at 2021-07-28T22:30:59+01:00 EPA: match changes from GHC T19834 (cherry picked from commit 2fec1b44e0ee7e263286709aa528b4ecb99ac6c2) - - - - - 5f177278 by Ben Gamari at 2021-08-06T01:17:37-04:00 Merge commit '2a966c8ca37' into HEAD - - - - - cdd81d08 by Marcin Szamotulski at 2021-08-08T17:19:06+02:00 coot/multiple packages (ghc-9.2) (#1418) - - - - - be0d71f1 by Marcin Szamotulski at 2021-08-16T08:46:03+02:00 coot/multiple package (ghc-head) (#1419) * FromJSON class Aeson style FromJSON class with Parsec based json parser. * doc-index.json file for multiple packages When creating haddock summary page for multiple packages render doc-index.json file using contents of all found 'doc-index.json' files. * Render doc-index.json When rendering html, render doc-index.json file independently of maybe_index_url option. doc-index.json file is useful now even if maybe_index_url is not `Nothing`. * base url option New `Flag_BaseURL` which configures from where static files are loaded (--base-url). If given and not equal "." static files are not coppied, as this indicates that they are not read from the the directory where we'd copy them. The default value is ".". - - - - - 3b09dbdf by Hécate Moonlight at 2021-10-07T23:26:03+02:00 Update GHC 9.2 to latest pre-release in CI - - - - - 7ac55417 by Zubin Duggal at 2021-10-11T12:10:19+02:00 Enable Haddock tests in GHC windows CI (#1428) * testsuite: strip windows line endings for haddock * hyperlinker: Work around double escaping (#19236) * deterministic SCC - - - - - 1cb81f25 by Andrew Lelechenko at 2021-10-12T15:23:19+02:00 haddock-library does not depend on bytestring or transformers (#1426) - - - - - a890b9aa by sheaf at 2021-10-15T22:19:42+02:00 update haddockHypsrcTest for GHC MR !6705 (#1430) - - - - - 42a55c6c by Sylvain Henry at 2021-10-15T22:20:10+02:00 Fix after PkgQual refactoring (#1429) - - - - - 91659238 by Alan Zimmerman at 2021-10-28T18:57:10+01:00 Update for changes in GHC for branch wip/az/no-srcspan-anno-instances - - - - - acf23e60 by Vladislav Zavialov at 2021-11-05T02:09:47+03:00 Do not use forall as an identifier See GHC ticket haskell/haddock#20609 - - - - - c565db0e by Krzysztof Gogolewski at 2021-11-27T02:42:35+01:00 Update after NoExtCon -> DataConCantHappen rename - - - - - b5f55590 by Artem Pelenitsyn at 2021-11-27T11:14:17+01:00 fix CI for 9.2 (#1436) - - - - - 25cd621e by Matthew Pickering at 2021-12-02T11:46:54+00:00 Update html-test for Data.List revert - - - - - 1d5ff85f by malteneuss at 2021-12-15T07:56:55+01:00 Add hint about inline link issue (#1444) - - - - - 791fde81 by Sylvain Henry at 2021-12-16T09:29:51+01:00 Bump ghc-head (#1445) * Update after NoExtCon -> DataConCantHappen rename * Update html-test for Data.List revert * Fix for new Plugins datatype Co-authored-by: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 44236317 by Sylvain Henry at 2021-12-17T09:39:00+01:00 Fix for new Plugins datatype - - - - - 80ada0fa by Hécate Moonlight at 2021-12-17T17:28:48+01:00 Remove ghc-head workflow (#1446) Contributions of GHC glue code are now done on the GHC gitlab, not in the GitHub repo anymore. - - - - - 49e171cd by Matthew Pickering at 2021-12-28T09:47:09+00:00 Remove use of ExtendedModSummary - - - - - 0e91b5ea by askeblad at 2022-01-04T09:18:35+01:00 update URLs - - - - - 9f13c212 by Hécate Moonlight at 2022-02-25T10:19:46+01:00 Fix solver for GHC 9.2 - - - - - 386751a1 by Meng Weng Wong at 2022-02-25T19:19:11+01:00 IDoc link has bitrotted; replaced with web.archive.org cache. (#1454) - - - - - d877cbe6 by Hécate Moonlight at 2022-02-25T19:21:58+01:00 Fix haddock user guide (#1456) - - - - - cc47f036 by Andrew Lelechenko at 2022-03-04T17:29:36+01:00 Allow text-2.0 in haddock-library (#1459) - - - - - 7b3685a3 by malteneuss at 2022-03-07T19:27:24+01:00 Add multi-line style hint to style section (#1460) - - - - - c51088b8 by John Ericson at 2022-03-11T16:46:26+01:00 Fix CollectPass instance to match TTG refactor Companion to GHC !7614 (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7614) - - - - - b882195b by Vladislav Zavialov at 2022-03-14T20:32:30+01:00 Link to (~) - - - - - 877349b8 by Christiaan Baaij at 2022-03-16T09:20:43+01:00 Add Haddock support for the OPAQUE pragma - - - - - 0ea22721 by askeblad at 2022-03-16T09:44:27+01:00 typos (#1464) - - - - - a6d13da1 by Matthew Pickering at 2022-03-22T13:41:17+00:00 Minimum changes needed for compilation with hi-haddock With hi-haddock, of course there is a much large refactoring of haddock which could be achieved but that is left for a future patch which can implemented at any time independently of GHC. - - - - - e7ac9129 by Matthew Pickering at 2022-03-22T21:17:50+00:00 Update test output - - - - - 6d916214 by Matthew Pickering at 2022-03-24T15:06:26+00:00 Merge branch 'wip/opaque_pragma' into 'ghc-head' Add Haddock support for the OPAQUE pragma See merge request ghc/haddock!2 - - - - - 42208183 by Steve Hart at 2022-03-25T20:43:50+01:00 Fix CI (#1467) * CI: Reinstall GHC with docs CI tests were failing because the GHC preinstalled to the CI environment does not include documentation, which is required for running the Haddock tests. This commit causes the CI workflow to reinstall GHC with docs so that tests can succeed. - - - - - 9676fd79 by Steve Hart at 2022-03-25T21:33:34+01:00 Make links in Synopsis functional again (#1458) Commit e41c1cbe9f0476997eac7b4a3f17cbc6b2262faf added a call to e.preventDefault() when handling click events that reach a toggle element. This prevents the browser from following hyperlinks within the Synopsis section when they are clicked by a user. This commit restores functioning hyperlinks within the Synopsis section by removing the call to e.preventDefault(), as it does not appear to be necessary, and removing it increases the flexibility of the details-helper code. - - - - - d1edd637 by sheaf at 2022-04-01T12:02:02+02:00 Keep track of promotion ticks in HsOpTy Keeping track of promotion ticks in HsOpTy allows us to properly pretty-print promoted constructors such as lists. - - - - - 9dcb2dfc by Jakob Brünker at 2022-04-01T15:46:22+00:00 Add support for \cases See merge request ghc/ghc!7873 - - - - - b0412ee5 by askeblad at 2022-04-06T17:47:57+02:00 spelling errors (#1471) - - - - - 6b18829b by Vladislav Zavialov at 2022-04-06T18:53:58+02:00 Rename [] to List - - - - - 2d046691 by Vladislav Zavialov at 2022-04-07T20:25:54+03:00 HsToken ConDeclGADT con_dcolon - - - - - 90b43da4 by Steve Hart at 2022-04-12T13:29:46+02:00 Parse Markdown links at beginning of line within a paragraph (#1470) * Catch Markdown links at beginning of line within paragraph Per Issue haskell/haddock#774, Markdown links were being parsed as ordinary text when they occurred at the beginning of a line other than the first line of the paragraph. This occurred because the parser was not interpreting a left square bracket as a special character that could delimit special markup. A space character was considered a special character, so, if a space occurred at the beginning of the new line, then the parser would interpret the space by itself and then continue parsing, thereby catching the Markdown link. '\n' was not treated as a special character, so the parser did not catch a Markdown link that may have followed. Note that this will allow for Markdown links that are not surrounded by spaces. For example, the following text includes a Markdown link that will be parsed: Hello, world[label](url) This is consistent with how the parser handles other types of markup. * Remove obsolete documentation hint Commit 6b9aeafddf20efc65d3725c16e3fc43a20aac343 should eliminate the need for the workaround suggested in the documentation. - - - - - 5b08312d by Hécate Moonlight at 2022-04-12T13:36:38+02:00 Force ghc-9.2 in the cabal.project - - - - - 0d0ea349 by dependabot[bot] at 2022-04-12T13:57:41+02:00 Bump path-parse from 1.0.5 to 1.0.7 in /haddock-api/resources/html (#1469) Bumps [path-parse](https://github.com/jbgutierrez/path-parse) from 1.0.5 to 1.0.7. - [Release notes](https://github.com/jbgutierrez/path-parse/releases) - [Commits](https://github.com/jbgutierrez/path-parse/commits/v1.0.7) --- updated-dependencies: - dependency-name: path-parse dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 2b9fc65e by dependabot[bot] at 2022-04-12T13:57:54+02:00 Bump copy-props from 2.0.4 to 2.0.5 in /haddock-api/resources/html (#1468) Bumps [copy-props](https://github.com/gulpjs/copy-props) from 2.0.4 to 2.0.5. - [Release notes](https://github.com/gulpjs/copy-props/releases) - [Changelog](https://github.com/gulpjs/copy-props/blob/master/CHANGELOG.md) - [Commits](https://github.com/gulpjs/copy-props/compare/2.0.4...2.0.5) --- updated-dependencies: - dependency-name: copy-props dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - ea98a6fb by Ben Gamari at 2022-04-23T22:54:37-04:00 Update for GHC 9.4 - - - - - 9e11864f by Ben Gamari at 2022-04-25T16:24:31-04:00 Merge remote-tracking branch 'upstream/ghc-9.2' into ghc-head - - - - - f83cc506 by Ben Gamari at 2022-04-25T17:00:25-04:00 Bump ghc version to 9.5 - - - - - e01c2e7d by Ben Gamari at 2022-04-28T16:19:04-04:00 Revert "Bump ghc-head (#1445)" This reverts commit b29a78ef6926101338f62e84f456dac8659dc9d2. This should not have been merged. - - - - - a2b5ee8c by Ben Gamari at 2022-04-28T16:19:24-04:00 Merge commit '2627a86c' into ghc-head - - - - - 0c6fe4f9 by Ben Gamari at 2022-04-29T10:05:54-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-9.4 - - - - - b6e5cb0a by Ben Gamari at 2022-04-29T11:46:06-04:00 Revert "HsToken ConDeclGADT con_dcolon" This reverts commit 24208496649a02d5f87373052c430ea4a97842c5. - - - - - 15a62888 by Ben Gamari at 2022-04-29T15:12:55-04:00 Bump base upper bound - - - - - 165b9031 by Ben Gamari at 2022-04-29T23:58:38-04:00 Update test output - - - - - e0c3e5da by Phil de Joux at 2022-05-02T14:46:38+02:00 Add hlint action .hlint.yaml with ignores & CPP. (#1475) - - - - - ead1158d by Raphael Das Gupta at 2022-05-02T14:46:48+02:00 fix grammar in docs: "can the" → "can be" (#1477) - - - - - cff97944 by Ben Gamari at 2022-05-02T18:38:56-04:00 Allow base-4.17 - - - - - e4ecb201 by Phil de Joux at 2022-05-03T13:14:55+02:00 Remove unused imports that GHC warned about. (#1480) - - - - - 222890b1 by Phil de Joux at 2022-05-03T13:15:46+02:00 Follow hlint suggestion to remove redundant bang. (#1479) - - - - - 058b671f by Phil de Joux at 2022-05-03T13:34:04+02:00 Follow hlint, remove language pragmas in libs. (#1478) - - - - - 0a645049 by Ben Simms at 2022-05-03T14:19:24+02:00 Keep track of ordered list indexes and render them (#1407) * Keep track of ordered list indexes and render them * Rename some identifiers to clarify - - - - - f0433304 by Norman Ramsey at 2022-05-04T15:13:34-04:00 update for changes in GHC API - - - - - 3740cf71 by Emily Martins at 2022-05-06T18:23:48+02:00 Add link to the readthedocs in cabal description to show on hackage. (cherry picked from commit 52e2d40d47295c02d3181aac0c53028e730f1e3b) - - - - - 5d754f1e by Hécate Moonlight at 2022-05-06T18:44:57+02:00 remove Bug873 - - - - - 968fc267 by Hécate Moonlight at 2022-05-06T18:48:28+02:00 Ignore "Use second" HLint suggestion. It increases laziness. - - - - - 02d14e97 by Jade Lovelace at 2022-05-07T17:42:08+02:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` - - - - - b22b87ed by Artem Pelenitsyn at 2022-05-08T16:19:47+02:00 fix parsing trailing quotes in backticked identifiers (#1408) (#1483) - - - - - 80ae107b by Alex Biehl at 2022-05-08T16:37:16+02:00 Fix "Defined by not used" error (cherry picked from commit 6e02a620a26c3a44f98675dd1b93b08070c36c0a) - - - - - 4c838e84 by Hécate Moonlight at 2022-05-08T16:37:16+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - fc9827b4 by Hécate Moonlight at 2022-05-08T16:40:40+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - b153b555 by Xia Li-yao at 2022-05-20T17:52:42+02:00 Hide synopsis from search when hidden (#1486) Fix haskell/haddock#1451 - - - - - f3e38b85 by Marcin Szamotulski at 2022-05-21T23:32:31+02:00 Allow to hide interfaces when rendering multiple components (#1487) This is useful when one wishes to `--gen-contents` when rendering multiple components, but one does not want to render all modules. This is in particular useful when adding base package. - - - - - f942863b by Marcin Szamotulski at 2022-05-24T08:29:59+02:00 Check if doc-index.json exists before reading it (#1488) - - - - - 31e92982 by Marcin Szamotulski at 2022-05-25T16:22:13+02:00 Version bump 2.26.1 (#1489) * Version bump 2.26.1 We extended format accepted by `--read-interface` option, which requires updating the minor version. * Update documentation of --read-interface option - - - - - 7cc873e0 by sheaf at 2022-05-25T16:42:31+02:00 Updated HaddockHypsrcTest output for record update changes (MR !7981) - - - - - cd196942 by Marcin Szamotulski at 2022-05-25T20:28:47+02:00 Use visibility to decide which interfaces are included in quickjump (#1490) This is also consistent with how html index is build. See haskell/cabal#7669 for rationale behind this decision. - - - - - 00c713c5 by Hécate Moonlight at 2022-05-26T17:09:15+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 2f3039f1 by Hécate Moonlight at 2022-05-26T17:10:59+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 63a5650c by romes at 2022-05-31T12:43:22+01:00 TTG: Match new GHC AST - - - - - dd7d1617 by romes at 2022-06-02T16:11:00+01:00 Update for IE changes in !8228 - - - - - ce9f986b by John Ericson at 2022-06-02T15:42:59+00:00 HsToCore.Coverage: Improve haddocks - - - - - f065804e by John Ericson at 2022-06-02T15:42:59+00:00 Hoist auto `mkModBreaks` and `writeMixEntries` conditions to caller No need to inline traversing a maybe for `mkModBreaks`. And better to make each function do one thing and let the caller deside when than scatter the decision making and make the caller seem more imperative. - - - - - d550d907 by John Ericson at 2022-06-02T15:42:59+00:00 Rename `HsToCore.{Coverage -> Ticks}` The old name made it confusing why disabling HPC didn't disable the entire pass. The name makes it clear --- there are other reasons to add ticks in addition. - - - - - 6520da95 by John Ericson at 2022-06-02T15:42:59+00:00 Split out `GHC.HsToCore.{Breakpoints,Coverage}` and use `SizedSeq` As proposed in https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7508#note_432877 and https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7508#note_434676, `GHC.HsToCore.Ticks` is about ticks, breakpoints are separate and backend-specific (only for the bytecode interpreter), and mix entry writing is just for HPC. With this split we separate out those interpreter- and HPC-specific its, and keep the main `GHC.HsToCore.Ticks` agnostic. Also, instead of passing the reversed list and count around, we use `SizedSeq` which abstracts over the algorithm. This is much nicer to avoid noise and prevents bugs. (The bugs are not just hypothetical! I missed up the reverses on an earlier draft of this commit.) - - - - - 1838c3d8 by Sylvain Henry at 2022-06-02T15:43:14+00:00 GHC.HsToCore.Breakpoints: Slightly improve perf We have the length already, so we might as well use that rather than O(n) recomputing it. - - - - - 5a3fdcfd by John Ericson at 2022-06-02T15:43:59+00:00 HsToCore.Coverage: Purge DynFlags Finishes what !7467 (closed) started. Progress towards #17957 - - - - - c23aaab7 by cydparser at 2022-06-06T08:48:14+02:00 Fix and improve CI (#1495) * Pin GHC version before creating the freeze file * Use newest action versions * Improve caching * Avoid unnecessarily reinstalling GHC * Use GHC 9.2.2 for CI Co-authored-by: Cyd Wise <cwise at tripshot.com> - - - - - c156fa77 by Hécate Moonlight at 2022-06-06T11:59:35+02:00 Add Mergify configuration (#1496) - - - - - 9ce9ea50 by HaskellMouse at 2022-06-06T09:50:00-04:00 Deprecate TypeInType extension This commit fixes #20312 It deprecates "TypeInType" extension according to the following proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0083-no-type-in-type.rst It has been already implemented. The migration strategy: 1. Disable TypeInType 2. Enable both DataKinds and PolyKinds extensions Metric Decrease: T16875 - - - - - f2e037fd by Aaron Allen at 2022-06-06T09:50:39-04:00 Diagnostics conversions, part 6 (#20116) Replaces uses of `TcRnUnknownMessage` with proper diagnostics constructors in `GHC.Tc.Gen.Match`, `GHC.Tc.Gen.Pat`, and `GHC.Tc.Gen.Sig`. - - - - - 04209f2a by Simon Peyton Jones at 2022-06-06T09:51:15-04:00 Ensure floated dictionaries are in scope (again) In the Specialiser, we missed one more call to bringFloatedDictsIntoScope (see #21391). This omission led to #21689. The problem is that the call to `rewriteClassOps` needs to have in scope any dictionaries floated out of the arguments we have just specialised. Easy fix. - - - - - 2dba4188 by Hécate Moonlight at 2022-06-06T16:12:50+02:00 Bump haddock's version in cabal file to 2.26.1 (#1497) - - - - - a7fece19 by John Ericson at 2022-06-07T05:04:22+00:00 Don't print the number of deps in count-deps tests It is redundant information and a source of needless version control conflicts when multiple MRs are changing the deps list. Just printing the list and not also its length is fine. - - - - - a1651a3a by John Ericson at 2022-06-07T05:06:38+00:00 Core.Lint: Reduce `DynFlags` and `HscEnv` Co-Authored-By: Andre Marianiello <andremarianiello at users.noreply.github.com> - - - - - d7d4b8b9 by Marcin Szamotulski at 2022-06-07T06:09:40+00:00 Render module tree per package in the content page (#1492) * Render module tree per package in the content page When rendering content page for multiple packages it is useful to split the module tree per package. Package names in this patch are inferred from haddock's interface file names. * Write PackageInfo into interface file To keep interface file format backward compatible, instead of using `Binary` instance for `InterfaceFile` we introduce functions to serialise and deserialise, which depends on the interface file version. - - - - - 56ebf9a5 by Andreas Klebinger at 2022-06-09T09:11:43-04:00 Fix a CSE shadowing bug. We used to process the rhs of non-recursive bindings and their body using the same env. If we had something like let x = ... x ... this caused trouble because the two xs refer to different binders but we would substitute both for a new binder x2 causing out of scope errors. We now simply use two different envs for the rhs and body in cse_bind. It's all explained in the Note [Separate envs for let rhs and body] Fixes #21685 - - - - - 28880828 by sheaf at 2022-06-09T09:12:19-04:00 Typecheck remaining ValArgs in rebuildHsApps This patch refactors hasFixedRuntimeRep_remainingValArgs, renaming it to tcRemainingValArgs. The logic is moved to rebuildHsApps, which ensures consistent behaviour across tcApp and quickLookArg1/tcEValArg. This patch also refactors the treatment of stupid theta for data constructors, changing the place we drop stupid theta arguments from dsConLike to mkDataConRep (now the datacon wrapper drops these arguments). We decided not to implement PHASE 2 of the FixedRuntimeRep plan for these remaining ValArgs. Future directions are outlined on the wiki: https://gitlab.haskell.org/ghc/ghc/-/wikis/Remaining-ValArgs Fixes #21544 and #21650 - - - - - 1fbba97b by Matthew Pickering at 2022-06-09T09:12:54-04:00 Add test for T21682 Fixes #21682 - - - - - 8727be73 by Andreas Klebinger at 2022-06-09T09:13:29-04:00 Document dataToTag# primop - - - - - 7eab75bb by uhbif19 at 2022-06-09T20:22:47+03:00 Remove TcRnUnknownMessage usage from GHC.Rename.Env #20115 - - - - - 46d2fc65 by uhbif19 at 2022-06-09T20:24:40+03:00 Fix TcRnPragmaWarning meaning - - - - - 69e72ecd by Matthew Pickering at 2022-06-09T19:07:01-04:00 getProcessCPUTime: Fix the getrusage fallback to account for system CPU time clock_gettime reports the combined total or user AND system time so in order to replicate it with getrusage we need to add both system and user time together. See https://stackoverflow.com/questions/7622371/getrusage-vs-clock-gettime Some sample measurements when building Cabal with this patch t1: rusage t2: clock_gettime t1: 62347518000; t2: 62347520873 t1: 62395687000; t2: 62395690171 t1: 62432435000; t2: 62432437313 t1: 62478489000; t2: 62478492465 t1: 62514990000; t2: 62514992534 t1: 62515479000; t2: 62515480327 t1: 62515485000; t2: 62515486344 Fixes #21656 - - - - - 722814ba by Yiyun Liu at 2022-06-10T21:23:03-04:00 Use <br> instead of newline character - - - - - 77765665 by Mike Pilgrem at 2022-06-12T21:57:19+01:00 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - b0e079b0 by mergify[bot] at 2022-06-13T11:49:37+00:00 Merge pull request haskell/haddock#1108 from mpilgrem/fix783 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - dc202080 by Matthew Craven at 2022-06-13T14:07:12-04:00 Use (fixed_lev = True) in mkDataTyConRhs - - - - - ad70c621 by Matthew Pickering at 2022-06-14T08:40:53-04:00 hadrian: Fix testing stage1 compiler There were various issues with testing the stage1 compiler.. 1. The wrapper was not being built 2. The wrapper was picking up the stage0 package database and trying to load prelude from that. 3. The wrappers never worked on windows so just don't support that for now. Fixes #21072 - - - - - ac83899d by Ben Gamari at 2022-06-14T08:41:30-04:00 validate: Ensure that $make variable is set Currently the `$make` variable is used without being set in `validate`'s Hadrian path, which uses make to install the binary distribution. Fix this. Fixes #21687. - - - - - 59bc6008 by John Ericson at 2022-06-15T18:05:35+00:00 CoreToStg.Prep: Get rid of `DynFlags` and `HscEnv` The call sites in `Driver.Main` are duplicative, but this is good, because the next step is to remove `InteractiveContext` from `Core.Lint` into `Core.Lint.Interactive`. Also further clean up `Core.Lint` to use a better configuration record than the one we initially added. - - - - - aa9d9381 by Ben Gamari at 2022-06-15T20:33:04-04:00 hadrian: Run xattr -rc . on bindist tarball Fixes #21506. - - - - - cdc75a1f by Ben Gamari at 2022-06-15T20:33:04-04:00 configure: Hide spurious warning from ld Previously the check_for_gold_t22266 configure check could result in spurious warnings coming from the linker being blurted to stderr. Suppress these by piping stderr to /dev/null. - - - - - e128b7b8 by Ben Gamari at 2022-06-15T20:33:40-04:00 cmm: Add surface syntax for MO_MulMayOflo - - - - - bde65ea9 by Ben Gamari at 2022-06-15T20:34:16-04:00 configure: Don't attempt to override linker on Darwin Configure's --enable-ld-override functionality is intended to ensure that we don't rely on ld.bfd, which tends to be slow and buggy, on Linux and Windows. However, on Darwin the lack of sensible package management makes it extremely easy for users to have awkward mixtures of toolchain components from, e.g., XCode, the Apple Command-Line Tools package, and homebrew. This leads to extremely confusing problems like #21712. Here we avoid this by simply giving up on linker selection on Darwin altogether. This isn't so bad since the Apple ld64 linker has decent performance and AFAICT fairly reliable. Closes #21712. - - - - - 25b510c3 by Torsten Schmits at 2022-06-16T12:37:45-04:00 replace quadratic nub to fight byte code gen perf explosion Despite this code having been present in the core-to-bytecode implementation, I have observed it in the wild starting with 9.2, causing enormous slowdown in certain situations. My test case produces the following profiles: Before: ``` total time = 559.77 secs (559766 ticks @ 1000 us, 1 processor) total alloc = 513,985,665,640 bytes (excludes profiling overheads) COST CENTRE MODULE SRC %time %alloc ticks bytes elem_by Data.OldList libraries/base/Data/OldList.hs:429:1-7 67.6 92.9 378282 477447404296 eqInt GHC.Classes libraries/ghc-prim/GHC/Classes.hs:275:8-14 12.4 0.0 69333 32 $c>>= GHC.Data.IOEnv <no location info> 6.9 0.6 38475 3020371232 ``` After: ``` total time = 89.83 secs (89833 ticks @ 1000 us, 1 processor) total alloc = 39,365,306,360 bytes (excludes profiling overheads) COST CENTRE MODULE SRC %time %alloc ticks bytes $c>>= GHC.Data.IOEnv <no location info> 43.6 7.7 39156 3020403424 doCase GHC.StgToByteCode compiler/GHC/StgToByteCode.hs:(805,1)-(1054,53) 2.5 7.4 2246 2920777088 ``` - - - - - aa7e1f20 by Matthew Pickering at 2022-06-16T12:38:21-04:00 hadrian: Don't install `include/` directory in bindist. The install_includes for the RTS package used to be put in the top-level ./include folder but this would lead to confusing things happening if you installed multiple GHC versions side-by-side. We don't need this folder anymore because install-includes is honoured properly by cabal and the relevant header files already copied in by the cabal installation process. If you want to depend on the header files for the RTS in a Haskell project then you just have to depend on the `rts` package and the correct include directories will be provided for you. If you want to depend on the header files in a standard C project then you should query ghc-pkg to get the right paths. ``` ghc-pkg field rts include-dirs --simple-output ``` Fixes #21609 - - - - - 03172116 by Bryan Richter at 2022-06-16T12:38:57-04:00 Enable eventlogs on nightly perf job - - - - - ecbf8685 by Hécate Moonlight at 2022-06-16T16:30:00-04:00 Repair dead link in TH haddocks Closes #21724 - - - - - 99ff3818 by sheaf at 2022-06-16T16:30:39-04:00 Hadrian: allow configuring Hsc2Hs This patch adds the ability to pass options to Hsc2Hs as Hadrian key/value settings, in the same way as cabal configure options, using the syntax: *.*.hsc2hs.run.opts += ... - - - - - 9c575f24 by sheaf at 2022-06-16T16:30:39-04:00 Hadrian bootstrap: look up hsc2hs Hadrian bootstrapping looks up where to find ghc_pkg, but the same logic was not in place for hsc2hs which meant we could fail to find the appropriate hsc2hs executabe when bootstrapping Hadrian. This patch adds that missing logic. - - - - - 229d741f by Ben Gamari at 2022-06-18T10:42:54-04:00 ghc-heap: Add (broken) test for #21622 - - - - - cadd7753 by Ben Gamari at 2022-06-18T10:42:54-04:00 ghc-heap: Don't Box NULL pointers Previously we could construct a `Box` of a NULL pointer from the `link` field of `StgWeak`. Now we take care to avoid ever introducing such pointers in `collect_pointers` and ensure that the `link` field is represented as a `Maybe` in the `Closure` type. Fixes #21622 - - - - - 31c214cc by Tamar Christina at 2022-06-18T10:43:34-04:00 winio: Add support to console handles to handleToHANDLE - - - - - 711cb417 by Ben Gamari at 2022-06-18T10:44:11-04:00 CmmToAsm/AArch64: Add SMUL[LH] instructions These will be needed to fix #21624. - - - - - d05d90d2 by Ben Gamari at 2022-06-18T10:44:11-04:00 CmmToAsm/AArch64: Fix syntax of OpRegShift operands Previously this produced invalid assembly containing a redundant comma. - - - - - a1e1d8ee by Ben Gamari at 2022-06-18T10:44:11-04:00 ncg/aarch64: Fix implementation of IntMulMayOflo The code generated for IntMulMayOflo was previously wrong as it depended upon the overflow flag, which the AArch64 MUL instruction does not set. Fix this. Fixes #21624. - - - - - 26745006 by Ben Gamari at 2022-06-18T10:44:11-04:00 testsuite: Add test for #21624 Ensuring that mulIntMayOflo# behaves as expected. - - - - - 94f2e92a by Sebastian Graf at 2022-06-20T09:40:58+02:00 CprAnal: Set signatures of DFuns to top The recursive DFun in the reproducer for #20836 also triggered a bug in CprAnal that is observable in a debug build. The CPR signature of a recursive DFunId was never updated and hence the optimistic arity 0 bottom signature triggered a mismatch with the arity 1 of the binding in WorkWrap. We never miscompiled any code because WW doesn't exploit bottom CPR signatures. - - - - - b570da84 by Sebastian Graf at 2022-06-20T09:43:29+02:00 CorePrep: Don't speculatively evaluate recursive calls (#20836) In #20836 we have optimised a terminating program into an endless loop, because we speculated the self-recursive call of a recursive DFun. Now we track the set of enclosing recursive binders in CorePrep to prevent speculation of such self-recursive calls. See the updates to Note [Speculative evaluation] for details. Fixes #20836. - - - - - 49fb2f9b by Sebastian Graf at 2022-06-20T09:43:32+02:00 Simplify: Take care with eta reduction in recursive RHSs (#21652) Similar to the fix to #20836 in CorePrep, we now track the set of enclosing recursive binders in the SimplEnv and SimpleOptEnv. See Note [Eta reduction in recursive RHSs] for details. I also updated Note [Arity robustness] with the insights Simon and I had in a call discussing the issue. Fixes #21652. Unfortunately, we get a 5% ghc/alloc regression in T16577. That is due to additional eta reduction in GHC.Read.choose1 and the resulting ANF-isation of a large list literal at the top-level that didn't happen before (presumably because it was too interesting to float to the top-level). There's not much we can do about that. Metric Increase: T16577 - - - - - 2563b95c by Sebastian Graf at 2022-06-20T09:45:09+02:00 Ignore .hie-bios - - - - - e4e44d8d by Simon Peyton Jones at 2022-06-20T12:31:45-04:00 Instantiate top level foralls in partial type signatures The main fix for #21667 is the new call to tcInstTypeBnders in tcHsPartialSigType. It was really a simple omission before. I also moved the decision about whether we need to apply the Monomorphism Restriction, from `decideGeneralisationPlan` to `tcPolyInfer`. That removes a flag from the InferGen constructor, which is good. But more importantly, it allows the new function, checkMonomorphismRestriction called from `tcPolyInfer`, to "see" the `Types` involved rather than the `HsTypes`. And that in turn matters because we invoke the MR for partial signatures if none of the partial signatures in the group have any overloading context; and we can't answer that question for HsTypes. See Note [Partial type signatures and the monomorphism restriction] in GHC.Tc.Gen.Bind. This latter is really a pre-existing bug. - - - - - 262a9f93 by Winston Hartnett at 2022-06-20T12:32:23-04:00 Make Outputable instance for InlineSig print the InlineSpec Fix ghc/ghc#21739 Squash fix ghc/ghc#21739 - - - - - b5590fff by Matthew Pickering at 2022-06-20T12:32:59-04:00 Add NO_BOOT to hackage_doc_tarball job We were attempting to boot a src-tarball which doesn't work as ./boot is not included in the source tarball. This slipped through as the job is only run on nightly. - - - - - d24afd9d by Vladislav Zavialov at 2022-06-20T17:34:44-04:00 HsToken for @-patterns and TypeApplications (#19623) One more step towards the new design of EPA. - - - - - 159b7628 by Tamar Christina at 2022-06-20T17:35:23-04:00 linker: only keep rtl exception tables if they have been relocated - - - - - da5ff105 by Andreas Klebinger at 2022-06-21T17:04:12+02:00 Ticky:Make json info a separate field. - - - - - 6c0292b1 by Hécate Moonlight at 2022-06-21T17:21:08+02:00 Update the contribution guide - - - - - e413b9fa by dependabot[bot] at 2022-06-21T23:38:19+02:00 Bump shell-quote from 1.6.1 to 1.7.3 in /haddock-api/resources/html (#1500) Bumps [shell-quote](https://github.com/substack/node-shell-quote) from 1.6.1 to 1.7.3. - [Release notes](https://github.com/substack/node-shell-quote/releases) - [Changelog](https://github.com/substack/node-shell-quote/blob/master/CHANGELOG.md) - [Commits](https://github.com/substack/node-shell-quote/compare/1.6.1...1.7.3) --- updated-dependencies: - dependency-name: shell-quote dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 1a4ce4b2 by Matthew Pickering at 2022-06-22T09:49:22+01:00 Revert "Ticky:Make json info a separate field." This reverts commit da5ff10503e683e2148c62e36f8fe2f819328862. This was pushed directly without review. - - - - - f89bf85f by Vanessa McHale at 2022-06-22T08:21:32-04:00 Flags to disable local let-floating; -flocal-float-out, -flocal-float-out-top-level CLI flags These flags affect the behaviour of local let floating. If `-flocal-float-out` is disabled (the default) then we disable all local floating. ``` …(let x = let y = e in (a,b) in body)... ===> …(let y = e; x = (a,b) in body)... ``` Further to this, top-level local floating can be disabled on it's own by passing -fno-local-float-out-top-level. ``` x = let y = e in (a,b) ===> y = e; x = (a,b) ``` Note that this is only about local floating, ie, floating two adjacent lets past each other and doesn't say anything about the global floating pass which is controlled by `-fno-float`. Fixes #13663 - - - - - 4ccefc6e by Matthew Craven at 2022-06-22T08:22:12-04:00 Check for Int overflows in Data.Array.Byte - - - - - 2004e3c8 by Matthew Craven at 2022-06-22T08:22:12-04:00 Add a basic test for ByteArray's Monoid instance - - - - - fb36770c by Matthew Craven at 2022-06-22T08:22:12-04:00 Rename `copyByteArray` to `unsafeCopyByteArray` - - - - - ecc9aedc by Ben Gamari at 2022-06-22T08:22:48-04:00 testsuite: Add test for #21719 Happily, this has been fixed since 9.2. - - - - - 19606c42 by Brandon Chinn at 2022-06-22T08:23:28-04:00 Use lookupNameCache instead of lookupOrigIO - - - - - 4c9dfd69 by Brandon Chinn at 2022-06-22T08:23:28-04:00 Break out thNameToGhcNameIO (ref. #21730) - - - - - eb4fb849 by Michael Peyton Jones at 2022-06-22T08:24:07-04:00 Add laws for 'toInteger' and 'toRational' CLC discussion here: https://github.com/haskell/core-libraries-committee/issues/58 - - - - - c1a950c1 by Alexander Esgen at 2022-06-22T12:36:13+00:00 Correct documentation of defaults of the `-V` RTS option - - - - - b7b7d90d by Matthew Pickering at 2022-06-22T21:58:12-04:00 Transcribe discussion from #21483 into a Note In #21483 I had a discussion with Simon Marlow about the memory retention behaviour of -Fd. I have just transcribed that conversation here as it elucidates the potentially subtle assumptions which led to the design of the memory retention behaviours of -Fd. Fixes #21483 - - - - - 980d1954 by Ben Gamari at 2022-06-22T21:58:48-04:00 eventlog: Don't leave dangling pointers hanging around Previously we failed to reset pointers to various eventlog buffers to NULL after freeing them. In principle we shouldn't look at them after they are freed but nevertheless it is good practice to set them to a well-defined value. - - - - - 575ec846 by Eric Lindblad at 2022-06-22T21:59:28-04:00 runhaskell - - - - - e6a69337 by Artem Pelenitsyn at 2022-06-22T22:00:07-04:00 re-export GHC.Natural.minusNaturalMaybe from Numeric.Natural CLC proposal: https://github.com/haskell/core-libraries-committee/issues/45 - - - - - 5d45aa97 by Gergő Érdi at 2022-06-22T22:00:46-04:00 When specialising, look through floatable ticks. Fixes #21697. - - - - - 531205ac by Andreas Klebinger at 2022-06-22T22:01:22-04:00 TagCheck.hs: Properly check if arguments are boxed types. For one by mistake I had been checking against the kind of runtime rep instead of the boxity. This uncovered another bug, namely that we tried to generate the checking code before we had associated the function arguments with a register, so this could never have worked to begin with. This fixes #21729 and both of the above issues. - - - - - c7f9f6b5 by Gleb Popov at 2022-06-22T22:02:00-04:00 Use correct arch for the FreeBSD triple in gen-data-layout.sh Downstream bug for reference: https://bugs.freebsd.org/bugzilla/show_bug.cgi?id=261798 Relevant upstream issue: #15718 - - - - - 75f0091b by Andreas Klebinger at 2022-06-22T22:02:35-04:00 Bump nofib submodule. Allows the shake runner to build with 9.2.3 among other things. Fixes #21772 - - - - - 0aa0ce69 by Ben Gamari at 2022-06-27T08:01:03-04:00 Bump ghc-prim and base versions To 0.9.0 and 4.17.0 respectively. Bumps array, deepseq, directory, filepath, haskeline, hpc, parsec, stm, terminfo, text, unix, haddock, and hsc2hs submodules. (cherry picked from commit ba47b95122b7b336ce1cc00896a47b584ad24095) - - - - - 4713abc2 by Ben Gamari at 2022-06-27T08:01:03-04:00 testsuite: Use normalise_version more consistently Previously several tests' output were unnecessarily dependent on version numbers, particularly of `base`. Fix this. - - - - - d7b0642b by Matthew Pickering at 2022-06-27T08:01:03-04:00 linters: Fix lint-submodule-refs when crashing trying to find plausible branches - - - - - 38378be3 by Andreas Klebinger at 2022-06-27T08:01:39-04:00 hadrian: Improve haddocks for ghcDebugAssertions - - - - - ac7a7fc8 by Andreas Klebinger at 2022-06-27T08:01:39-04:00 Don't mark lambda binders as OtherCon We used to put OtherCon unfoldings on lambda binders of workers and sometimes also join points/specializations with with the assumption that since the wrapper would force these arguments once we execute the RHS they would indeed be in WHNF. This was wrong for reasons detailed in #21472. So now we purge evaluated unfoldings from *all* lambda binders. This fixes #21472, but at the cost of sometimes not using as efficient a calling convention. It can also change inlining behaviour as some occurances will no longer look like value arguments when they did before. As consequence we also change how we compute CBV information for arguments slightly. We now *always* determine the CBV convention for arguments during tidy. Earlier in the pipeline we merely mark functions as candidates for having their arguments treated as CBV. As before the process is described in the relevant notes: Note [CBV Function Ids] Note [Attaching CBV Marks to ids] Note [Never put `OtherCon` unfoldigns on lambda binders] ------------------------- Metric Decrease: T12425 T13035 T18223 T18223 T18923 MultiLayerModulesTH_OneShot Metric Increase: WWRec ------------------------- - - - - - 06cf6f4a by Tony Zorman at 2022-06-27T08:02:18-04:00 Add suggestions for unrecognised pragmas (#21589) In case of a misspelled pragma, offer possible corrections as to what the user could have meant. Fixes: https://gitlab.haskell.org/ghc/ghc/-/issues/21589 - - - - - 3fbab757 by Greg Steuck at 2022-06-27T08:02:56-04:00 Remove the traces of i386-*-openbsd, long live amd64 OpenBSD will not ship any ghc packages on i386 starting with 7.2 release. This means there will not be a bootstrap compiler easily available. The last available binaries are ghc-8.10.6 which is already not supported as bootstrap for HEAD. See here for more information: https://marc.info/?l=openbsd-ports&m=165060700222580&w=2 - - - - - 58530271 by Andrew Lelechenko at 2022-06-27T08:03:34-04:00 Add Foldable1 and Bifoldable1 type classes Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/9 Instances roughly follow https://hackage.haskell.org/package/semigroupoids-5.3.7/docs/Data-Semigroup-Foldable-Class.html#t:Foldable1 but the API of `Foldable1` was expanded in comparison to `semigroupoids`. Compatibility shim is available from https://github.com/phadej/foldable1 (to be released). Closes #13573. - - - - - a51f4ecc by Naomi Liu at 2022-06-27T08:04:13-04:00 add levity polymorphism to addrToAny# - - - - - f4edcdc4 by Naomi Liu at 2022-06-27T08:04:13-04:00 add tests for addrToAny# levity - - - - - 07016fc9 by Matthew Pickering at 2022-06-27T08:04:49-04:00 hadrian: Update main README page This README had some quite out-of-date content about the build system so I did a complete pass deleting old material. I also made the section about flavours more prominent and mentioned flavour transformers. - - - - - 79ae2d89 by Ben Gamari at 2022-06-27T08:05:24-04:00 testsuite: Hide output from test compilations with verbosity==2 Previously the output from test compilations used to determine whether, e.g., profiling libraries are available was shown with verbosity levels >= 2. However, the default level is 2, meaning that most users were often spammed with confusing errors. Fix this by bumping the verbosity threshold for this output to >=3. Fixes #21760. - - - - - 995ea44d by Ben Gamari at 2022-06-27T08:06:00-04:00 configure: Only probe for LD in FIND_LD Since 6be2c5a7e9187fc14d51e1ec32ca235143bb0d8b we would probe for LD rather early in `configure`. However, it turns out that this breaks `configure`'s `ld`-override logic, which assumes that `LD` was set by the user and aborts. Fixes #21778. - - - - - b43d140b by Sergei Trofimovich at 2022-06-27T08:06:39-04:00 `.hs-boot` make rules: add missing order-only dependency on target directory Noticed missing target directory dependency as a build failure in `make --shuffle` mode (added in https://savannah.gnu.org/bugs/index.php?62100): "cp" libraries/base/./GHC/Stack/CCS.hs-boot libraries/base/dist-install/build/GHC/Stack/CCS.hs-boot cp: cannot create regular file 'libraries/base/dist-install/build/GHC/Stack/CCS.hs-boot': No such file or directory libraries/haskeline/ghc.mk:4: libraries/haskeline/dist-install/build/.depend-v-p-dyn.haskell: No such file or directory make[1]: *** [libraries/base/ghc.mk:4: libraries/base/dist-install/build/GHC/Stack/CCS.hs-boot] Error 1 shuffle=1656129254 make: *** [Makefile:128: all] Error 2 shuffle=1656129254 Note that `cp` complains about inability to create target file. The change adds order-only dependency on a target directory (similar to the rest of rules in that file). The bug is lurking there since 2009 commit 34cc75e1a (`GHC new build system megapatch`.) where upfront directory creation was never added to `.hs-boot` files. - - - - - 57a5f88c by Ben Gamari at 2022-06-28T03:24:24-04:00 Mark AArch64/Darwin as requiring sign-extension Apple's AArch64 ABI requires that the caller sign-extend small integer arguments. Set platformCConvNeedsExtension to reflect this fact. Fixes #21773. - - - - - df762ae9 by Ben Gamari at 2022-06-28T03:24:24-04:00 -ddump-llvm shouldn't imply -fllvm Previously -ddump-llvm would change the backend used, which contrasts with all other dump flags. This is quite surprising and cost me quite a bit of time. Dump flags should not change compiler behavior. Fixes #21776. - - - - - 70f0c1f8 by Ben Gamari at 2022-06-28T03:24:24-04:00 CmmToAsm/AArch64: Re-format argument handling logic Previously there were very long, hard to parse lines. Fix this. - - - - - 696d64c3 by Ben Gamari at 2022-06-28T03:24:24-04:00 CmmToAsm/AArch64: Sign-extend narrow C arguments The AArch64/Darwin ABI requires that function arguments narrower than 32-bits must be sign-extended by the caller. We neglected to do this, resulting in #20735. Fixes #20735. - - - - - c006ac0d by Ben Gamari at 2022-06-28T03:24:24-04:00 testsuite: Add test for #20735 - - - - - 16b9100c by Ben Gamari at 2022-06-28T03:24:59-04:00 integer-gmp: Fix cabal file Evidently fields may not come after sections in a cabal file. - - - - - 03cc5d02 by Sergei Trofimovich at 2022-06-28T15:20:45-04:00 ghc.mk: fix 'make install' (`mk/system-cxx-std-lib-1.0.conf.install` does not exist) before the change `make install` was failing as: ``` "mv" "/<<NIX>>/ghc-9.3.20220406/lib/ghc-9.5.20220625/bin/ghc-stage2" "/<<NIX>>/ghc-9.3.20220406/lib/ghc-9.5.20220625/bin/ghc" make[1]: *** No rule to make target 'mk/system-cxx-std-lib-1.0.conf.install', needed by 'install_packages'. Stop. ``` I think it's a recent regression caused by 0ef249aa where `system-cxx-std-lib-1.0.conf` is created (somewhat manually), but not the .install varianlt of it. The fix is to consistently use `mk/system-cxx-std-lib-1.0.conf` everywhere. Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/21784 - - - - - eecab8f9 by Simon Peyton Jones at 2022-06-28T15:21:21-04:00 Comments only, about join points This MR just adds some documentation about why casts destroy join points, following #21716. - - - - - 251471e7 by Matthew Pickering at 2022-06-28T19:02:41-04:00 Cleanup BuiltInSyntax vs UserSyntax There was some confusion about whether FUN/TYPE/One/Many should be BuiltInSyntax or UserSyntax. The answer is certainly UserSyntax as BuiltInSyntax is for things which are directly constructed by the parser rather than going through normal renaming channels. I fixed all the obviously wrong places I could find and added a test for the original bug which was caused by this (#21752) Fixes #21752 #20695 #18302 - - - - - 0e22f16c by Ben Gamari at 2022-06-28T19:03:16-04:00 template-haskell: Bump version to 2.19.0.0 Bumps text and exceptions submodules due to bounds. - - - - - bbe6f10e by Emily Bourke at 2022-06-29T08:23:13+00:00 Tiny tweak to `IOPort#` documentation The exclamation mark and bracket don’t seem to make sense here. I’ve looked through the history, and I don’t think they’re deliberate – possibly a copy-and-paste error. - - - - - 70e47489 by Dominik Peteler at 2022-06-29T19:26:31-04:00 Remove `CoreOccurAnal` constructor of the `CoreToDo` type It was dead code since the last occurence in an expression context got removed in 71916e1c018dded2e68d6769a2dbb8777da12664. - - - - - d0722170 by nineonine at 2022-07-01T08:15:56-04:00 Fix panic with UnliftedFFITypes+CApiFFI (#14624) When declaring foreign import using CAPI calling convention, using unlifted unboxed types would result in compiler panic. There was an attempt to fix the situation in #9274, however it only addressed some of the ByteArray cases. This patch fixes other missed cases for all prims that may be used as basic foreign types. - - - - - eb043148 by Douglas Wilson at 2022-07-01T08:16:32-04:00 rts: gc stats: account properly for copied bytes in sequential collections We were not updating the [copied,any_work,scav_find_work, max_n_todo_overflow] counters during sequential collections. As well, we were double counting for parallel collections. To fix this we add an `else` clause to the `if (is_par_gc())`. The par_* counters do not need to be updated in the sequential case because they must be 0. - - - - - f95edea9 by Matthew Pickering at 2022-07-01T19:21:55-04:00 desugar: Look through ticks when warning about possible literal overflow Enabling `-fhpc` or `-finfo-table-map` would case a tick to end up between the appliation of `neg` to its argument. This defeated the special logic which looks for `NegApp ... (HsOverLit` to warn about possible overflow if a user writes a negative literal (without out NegativeLiterals) in their code. Fixes #21701 - - - - - f25c8d03 by Matthew Pickering at 2022-07-01T19:22:31-04:00 ci: Fix definition of slow-validate flavour (so that -dlint) is passed In this embarassing sequence of events we were running slow-validate without -dlint. - - - - - bf7991b0 by Mike Pilgrem at 2022-07-02T10:12:04-04:00 Identify the extistence of the `runhaskell` command and that it is equivalent to the `runghc` command. Add an entry to the index for `runhaskell`. See https://gitlab.haskell.org/ghc/ghc/-/issues/21411 - - - - - 9e79f6d0 by Simon Jakobi at 2022-07-02T10:12:39-04:00 Data.Foldable1: Remove references to Foldable-specific note ...as discussed in https://gitlab.haskell.org/ghc/ghc/-/merge_requests/8495#note_439455. - - - - - 3a8970ac by romes at 2022-07-03T14:11:31-04:00 TTG: Move HsModule to L.H.S Move the definition of HsModule defined in GHC.Hs to Language.Haskell.Syntax with an added TTG parameter and corresponding extension fields. This is progress towards having the haskell-syntax package, as described in #21592 - - - - - f9f80995 by romes at 2022-07-03T14:11:31-04:00 TTG: Move ImpExp client-independent bits to L.H.S.ImpExp Move the GHC-independent definitions from GHC.Hs.ImpExp to Language.Haskell.Syntax.ImpExp with the required TTG extension fields such as to keep the AST independent from GHC. This is progress towards having the haskell-syntax package, as described in #21592 Bumps haddock submodule - - - - - c43dbac0 by romes at 2022-07-03T14:11:31-04:00 Refactor ModuleName to L.H.S.Module.Name ModuleName used to live in GHC.Unit.Module.Name. In this commit, the definition of ModuleName and its associated functions are moved to Language.Haskell.Syntax.Module.Name according to the current plan towards making the AST GHC-independent. The instances for ModuleName for Outputable, Uniquable and Binary were moved to the module in which the class is defined because these instances depend on GHC. The instance of Eq for ModuleName is slightly changed to no longer depend on unique explicitly and instead uses FastString's instance of Eq. - - - - - 2635c6f2 by konsumlamm at 2022-07-03T14:12:11-04:00 Expand `Ord` instance for `Down` Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/23#issuecomment-1172932610 - - - - - 36fba0df by Anselm Schüler at 2022-07-04T05:06:42+00:00 Add applyWhen to Data.Function per CLC prop Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/71#issuecomment-1165830233 - - - - - 3b13aab1 by Matthew Pickering at 2022-07-04T15:15:00-04:00 hadrian: Don't read package environments in ghc-stage1 wrapper The stage1 compiler may be on the brink of existence and not have even a working base library. You may have installed packages globally with a similar stage2 compiler which will then lead to arguments such as --show-iface not even working because you are passing too many package flags. The solution is simple, don't read these implicit files. Fixes #21803 - - - - - aba482ea by Andreas Klebinger at 2022-07-04T17:55:55-04:00 Ticky:Make json info a separate field. Fixes #21233 - - - - - 74f3867d by Matthew Pickering at 2022-07-04T17:56:30-04:00 Add docs:<pkg> command to hadrian to build docs for just one package - - - - - 418afaf1 by Matthew Pickering at 2022-07-04T17:56:30-04:00 upload-docs: propagate publish correctly in upload_sdist - - - - - ed793d7a by Matthew Pickering at 2022-07-04T17:56:30-04:00 docs-upload: Fix upload script when no packages are listed - - - - - d002c6e0 by Matthew Pickering at 2022-07-04T17:56:30-04:00 hadrian: Add --haddock-base-url option for specifying base-url when generating docs The motiviation for this flag is to be able to produce documentation which is suitable for uploading for hackage, ie, the cross-package links work correctly. There are basically three values you want to set this to: * off - default, base_url = ../%pkg% which works for local browsing * on - no argument , base_url = https:://hackage.haskell.org/package/%pkg%/docs - for hackage docs upload * on - argument, for example, base_url = http://localhost:8080/package/%pkg%/docs for testing the documentation. The `%pkg%` string is a template variable which is replaced with the package identifier for the relevant package. This is one step towards fixing #21749 - - - - - 41eb749a by Matthew Pickering at 2022-07-04T17:56:31-04:00 Add nightly job for generating docs suitable for hackage upload - - - - - 620ee7ed by Matthew Pickering at 2022-07-04T17:57:05-04:00 ghci: Support :set prompt in multi repl This adds supports for various :set commands apart from `:set <FLAG>` in multi repl, this includes `:set prompt` and so-on. Fixes #21796 - - - - - b151b65e by Matthew Pickering at 2022-07-05T16:32:31-04:00 Vendor filepath inside template-haskell Adding filepath as a dependency of template-haskell means that it can't be reinstalled if any build-plan depends on template-haskell. This is a temporary solution for the 9.4 release. A longer term solution is to split-up the template-haskell package into the wired-in part and a non-wired-in part which can be reinstalled. This was deemed quite risky on the 9.4 release timescale. Fixes #21738 - - - - - c9347ecf by John Ericson at 2022-07-05T16:33:07-04:00 Factor fields of `CoreDoSimplify` into separate data type This avoids some partiality. The work @mmhat is doing cleaning up and modularizing `Core.Opt` will build on this nicely. - - - - - d0e74992 by Eric Lindblad at 2022-07-06T01:35:48-04:00 https urls - - - - - 803e965c by Eric Lindblad at 2022-07-06T01:35:48-04:00 options and typos - - - - - 5519baa5 by Eric Lindblad at 2022-07-06T01:35:48-04:00 grammar - - - - - 4ddc1d3e by Eric Lindblad at 2022-07-06T01:35:48-04:00 sources - - - - - c95c2026 by Matthew Pickering at 2022-07-06T01:35:48-04:00 Fix lint warnings in bootstrap.py - - - - - 86ced2ad by romes at 2022-07-06T01:36:23-04:00 Restore Eq instance of ImportDeclQualifiedStyle Fixes #21819 - - - - - 29d0ef70 by romes at 2022-07-06T11:29:39+02:00 TTG: AST Updates for !8308 - - - - - 3547e264 by romes at 2022-07-06T13:50:27-04:00 Prune L.H.S modules of GHC dependencies Move around datatypes, functions and instances that are GHC-specific out of the `Language.Haskell.Syntax.*` modules to reduce the GHC dependencies in them -- progressing towards #21592 Creates a module `Language.Haskell.Syntax.Basic` to hold basic definitions required by the other L.H.S modules (and don't belong in any of them) - - - - - e4eea07b by romes at 2022-07-06T13:50:27-04:00 TTG: Move CoreTickish out of LHS.Binds Remove the `[CoreTickish]` fields from datatype `HsBindLR idL idR` and move them to the extension point instance, according to the plan outlined in #21592 to separate the base AST from the GHC specific bits. - - - - - acc1816b by romes at 2022-07-06T13:50:27-04:00 TTG for ForeignImport/Export Add a TTG parameter to both `ForeignImport` and `ForeignExport` and, according to #21592, move the GHC-specific bits in them and in the other AST data types related to foreign imports and exports to the TTG extension point. - - - - - 371c5ecf by romes at 2022-07-06T13:50:27-04:00 TTG for HsTyLit Add TTG parameter to `HsTyLit` to move the GHC-specific `SourceText` fields to the extension point and out of the base AST. Progress towards #21592 - - - - - fd379d1b by romes at 2022-07-06T13:50:27-04:00 Remove many GHC dependencies from L.H.S Continue to prune the `Language.Haskell.Syntax.*` modules out of GHC imports according to the plan in the linked issue. Moves more GHC-specific declarations to `GHC.*` and brings more required GHC-independent declarations to `Language.Haskell.Syntax.*` (extending e.g. `Language.Haskell.Syntax.Basic`). Progress towards #21592 Bump haddock submodule for !8308 ------------------------- Metric Decrease: hard_hole_fits ------------------------- - - - - - c5415bc5 by Alan Zimmerman at 2022-07-06T13:50:27-04:00 Fix exact printing of the HsRule name Prior to this branch, the HsRule name was XRec pass (SourceText,RuleName) and there is an ExactPrint instance for (SourceText, RuleName). The SourceText has moved to a different location, so synthesise the original to trigger the correct instance when printing. We need both the SourceText and RuleName when exact printing, as it is possible to have a NoSourceText variant, in which case we fall back to the FastString. - - - - - 665fa5a7 by Matthew Pickering at 2022-07-06T13:51:03-04:00 driver: Fix issue with module loops and multiple home units We were attempting to rehydrate all dependencies of a particular module, but we actually only needed to rehydrate those of the current package (as those are the ones participating in the loop). This fixes loading GHC into a multi-unit session. Fixes #21814 - - - - - bbcaba6a by Andreas Klebinger at 2022-07-06T13:51:39-04:00 Remove a bogus #define from ClosureMacros.h - - - - - 1bae7c87 by Alan Zimmerman at 2022-07-06T22:50:43+01:00 Match GHC changes for T21805 This brings in a newtype for FieldLabelString - - - - - fa59223b by Tamar Christina at 2022-07-07T23:23:57-04:00 winio: make consoleReadNonBlocking not wait for any events at all. - - - - - 42c917df by Adam Sandberg Ericsson at 2022-07-07T23:24:34-04:00 rts: allow NULL to be used as an invalid StgStablePtr - - - - - 3739e565 by Andreas Schwab at 2022-07-07T23:25:10-04:00 RTS: Add stack marker to StgCRunAsm.S Every object file must be properly marked for non-executable stack, even if it contains no code. - - - - - a889bc05 by Ben Gamari at 2022-07-07T23:25:45-04:00 Bump unix submodule Adds `config.sub` to unix's `.gitignore`, fixing #19574. - - - - - 3609a478 by Matthew Pickering at 2022-07-09T11:11:58-04:00 ghci: Fix most calls to isLoaded to work in multi-mode The most egrarious thing this fixes is the report about the total number of loaded modules after starting a session. Ticket #20889 - - - - - fc183c90 by Matthew Pickering at 2022-07-09T11:11:58-04:00 Enable :edit command in ghci multi-mode. This works after the last change to isLoaded. Ticket #20888 - - - - - 46050534 by Simon Peyton Jones at 2022-07-09T11:12:34-04:00 Fix a scoping bug in the Specialiser In the call to `specLookupRule` in `already_covered`, in `specCalls`, we need an in-scope set that includes the free vars of the arguments. But we simply were not guaranteeing that: did not include the `rule_bndrs`. Easily fixed. I'm not sure how how this bug has lain for quite so long without biting us. Fixes #21828. - - - - - 6e8d9056 by Simon Peyton Jones at 2022-07-12T13:26:52+00:00 Edit Note [idArity varies independently of dmdTypeDepth] ...and refer to it in GHC.Core.Lint.lintLetBind. Fixes #21452 - - - - - 89ba4655 by Simon Peyton Jones at 2022-07-12T13:26:52+00:00 Tiny documentation wibbles (comments only) - - - - - 61a46c6d by Eric Lindblad at 2022-07-13T08:28:29-04:00 fix readme - - - - - 61babb5e by Eric Lindblad at 2022-07-13T08:28:29-04:00 fix bootstrap - - - - - 8b417ad5 by Eric Lindblad at 2022-07-13T08:28:29-04:00 tarball - - - - - e9d9f078 by Zubin Duggal at 2022-07-13T14:00:18-04:00 hie-files: Fix scopes for deriving clauses and instance signatures (#18425) - - - - - c4989131 by Zubin Duggal at 2022-07-13T14:00:18-04:00 hie-files: Record location of filled in default method bindings This is useful for hie files to reconstruct the evidence that default methods depend on. - - - - - 9c52e7fc by Zubin Duggal at 2022-07-13T14:00:18-04:00 testsuite: Factor out common parts from hiefile tests - - - - - 6a9e4493 by sheaf at 2022-07-13T14:00:56-04:00 Hadrian: update documentation of settings The documentation for key-value settings was a bit out of date. This patch updates it to account for `cabal.configure.opts` and `hsc2hs.run.opts`. The user-settings document was also re-arranged, to make the key-value settings more prominent (as it doesn't involve changing the Hadrian source code, and thus doesn't require any recompilation of Hadrian). - - - - - a2f142f8 by Zubin Duggal at 2022-07-13T20:43:32-04:00 Fix potential space leak that arise from ModuleGraphs retaining references to previous ModuleGraphs, in particular the lazy `mg_non_boot` field. This manifests in `extendMG`. Solution: Delete `mg_non_boot` as it is only used for `mgLookupModule`, which is only called in two places in the compiler, and should only be called at most once for every home unit: GHC.Driver.Make: mainModuleSrcPath :: Maybe String mainModuleSrcPath = do ms <- mgLookupModule mod_graph (mainModIs hue) ml_hs_file (ms_location ms) GHCI.UI: listModuleLine modl line = do graph <- GHC.getModuleGraph let this = GHC.mgLookupModule graph modl Instead `mgLookupModule` can be a linear function that looks through the entire list of `ModuleGraphNodes` Fixes #21816 - - - - - dcf8b30a by Ben Gamari at 2022-07-13T20:44:08-04:00 rts: Fix AdjustorPool bitmap manipulation Previously the implementation of bitmap_first_unset assumed that `__builtin_clz` would accept `uint8_t` however it apparently rather extends its argument to `unsigned int`. To fix this we simply revert to a naive implementation since handling the various corner cases with `clz` is quite tricky. This should be fine given that AdjustorPool isn't particularly hot. Ideally we would have a single, optimised bitmap implementation in the RTS but I'll leave this for future work. Fixes #21838. - - - - - ad8f3e15 by Luite Stegeman at 2022-07-16T07:20:36-04:00 Change GHCi bytecode return convention for unlifted datatypes. This changes the bytecode return convention for unlifted algebraic datatypes to be the same as for lifted types, i.e. ENTER/PUSH_ALTS instead of RETURN_UNLIFTED/PUSH_ALTS_UNLIFTED Fixes #20849 - - - - - 5434d1a3 by Colten Webb at 2022-07-16T07:21:15-04:00 Compute record-dot-syntax types Ensures type information for record-dot-syntax is included in HieASTs. See #21797 - - - - - 89d169ec by Colten Webb at 2022-07-16T07:21:15-04:00 Add record-dot-syntax test - - - - - 4beb9f3c by Ben Gamari at 2022-07-16T07:21:51-04:00 Document RuntimeRep polymorphism limitations of catch#, et al As noted in #21868, several primops accepting continuations producing RuntimeRep-polymorphic results aren't nearly as polymorphic as their types suggest. Document this limitation and adapt the `UnliftedWeakPtr` test to avoid breaking this limitation in `keepAlive#`. - - - - - 4ef1c65d by Ben Gamari at 2022-07-16T07:21:51-04:00 Make keepAlive# out-of-line This is a naive approach to fixing the unsoundness noticed in #21708. Specifically, we remove the lowering of `keepAlive#` via CorePrep and instead turn it into an out-of-line primop. This is simple, inefficient (since the continuation must now be heap allocated), but good enough for 9.4.1. We will revisit this (particiularly via #16098) in a future release. Metric Increase: T4978 T7257 T9203 - - - - - 1bbff35d by Greg Steuck at 2022-07-16T07:22:29-04:00 Suppress extra output from configure check for c++ libraries - - - - - 3acbd7ad by Ben Gamari at 2022-07-16T07:23:04-04:00 rel-notes: Drop mention of #21745 fix Since we have backported the fix to 9.4.1. - - - - - b27c2774 by Dominik Peteler at 2022-07-16T07:23:43-04:00 Align the behaviour of `dopt` and `log_dopt` Before the behaviour of `dopt` and `logHasDumpFlag` (and the underlying function `log_dopt`) were different as the latter did not take the verbosity level into account. This led to problems during the refactoring as we cannot simply replace calls to `dopt` with calls to `logHasDumpFlag`. In addition to that a subtle bug in the GHC module was fixed: `setSessionDynFlags` did not update the logger and as a consequence the verbosity value of the logger was not set appropriately. Fixes #21861 - - - - - 28347d71 by Douglas Wilson at 2022-07-16T13:25:06-04:00 rts: forkOn context switches the target capability Fixes #21824 - - - - - f1c44991 by Ben Gamari at 2022-07-16T13:25:41-04:00 cmm: Eliminate orphan Outputable instances Here we reorganize `GHC.Cmm` to eliminate the orphan `Outputable` and `OutputableP` instances for the Cmm AST. This makes it significantly easier to use the Cmm pretty-printers in tracing output without incurring module import cycles. - - - - - f2e5e763 by Ben Gamari at 2022-07-16T13:25:41-04:00 cmm: Move toBlockList to GHC.Cmm - - - - - fa092745 by Ben Gamari at 2022-07-16T13:25:41-04:00 compiler: Add haddock sections to GHC.Utils.Panic - - - - - 097759f9 by Ben Gamari at 2022-07-16T13:26:17-04:00 configure: Don't override Windows CXXFLAGS At some point we used the clang distribution from msys2's `MINGW64` environment for our Windows toolchain. This defaulted to using libgcc and libstdc++ for its runtime library. However, we found for a variety of reasons that compiler-rt, libunwind, and libc++ were more reliable, consequently we explicitly overrode the CXXFLAGS to use these. However, since then we have switched to use the `CLANG64` packaging, which default to these already. Consequently we can drop these arguments, silencing some redundant argument warnings from clang. Fixes #21669. - - - - - 6fe8b988 by Phil de Joux at 2022-07-16T20:54:26+00:00 Bump hlint version to 3.4.1, the version with counts. (#1503) Redo the counts available with the --default option. - - - - - e38a2684 by Ben Gamari at 2022-07-16T23:50:36-04:00 rts/linker/Elf: Check that there are no NULL ctors - - - - - 616365b0 by Ben Gamari at 2022-07-16T23:50:36-04:00 rts/linker/Elf: Introduce support for invoking finalizers on unload Addresses #20494. - - - - - cdd3be20 by Ben Gamari at 2022-07-16T23:50:36-04:00 testsuite: Add T20494 - - - - - 03c69d8d by Ben Gamari at 2022-07-16T23:50:36-04:00 rts/linker/PEi386: Rename finit field to fini fini is short for "finalizer", which does not contain a "t". - - - - - 033580bc by Ben Gamari at 2022-07-16T23:50:36-04:00 rts/linker/PEi386: Refactor handling of oc->info Previously we would free oc->info after running initializers. However, we can't do this is we want to also run finalizers. Moreover, freeing oc->info so early was wrong for another reason: we will need it in order to unregister the exception tables (see the call to `RtlDeleteFunctionTable`). In service of #20494. - - - - - f17912e4 by Ben Gamari at 2022-07-16T23:50:36-04:00 rts/linker/PEi386: Add finalization support This implements #20494 for the PEi386 linker. Happily, this also appears to fix `T9405`, resolving #21361. - - - - - 2cd75550 by Ben Gamari at 2022-07-16T23:50:36-04:00 Loader: Implement gnu-style -l:$path syntax Gnu ld allows `-l` to be passed an absolute file path, signalled by a `:` prefix. Implement this in the GHC's loader search logic. - - - - - 5781a360 by Ben Gamari at 2022-07-16T23:50:36-04:00 Statically-link against libc++ on Windows Unfortunately on Windows we have no RPATH-like facility, making dynamic linking extremely fragile. Since we cannot assume that the user will add their GHC installation to `$PATH` (and therefore their DLL search path) we cannot assume that the loader will be able to locate our `libc++.dll`. To avoid this, we instead statically link against `libc++.a` on Windows. Fixes #21435. - - - - - 8e2e883b by Ben Gamari at 2022-07-16T23:50:36-04:00 rts/linker/PEi386: Ensure that all .ctors/.dtors sections are run It turns out that PE objects may have multiple `.ctors`/`.dtors` sections but the RTS linker had assumed that there was only one. Fix this. Fixes #21618. - - - - - fba04387 by Ben Gamari at 2022-07-16T23:50:36-04:00 rts/linker/PEi386: Respect dtor/ctor priority Previously we would run constructors and destructors in arbitrary order despite explicit priorities. Fixes #21847. - - - - - 1001952f by Ben Gamari at 2022-07-16T23:50:36-04:00 testsuite: Add test for #21618 and #21847 - - - - - 6f3816af by Ben Gamari at 2022-07-16T23:50:36-04:00 rts/linker/PEi386: Fix exception unwind unregistration RtlDeleteFunctionTable expects a pointer to the .pdata section yet we passed it the .xdata section. Happily, this fixes #21354. - - - - - d9bff44c by Ben Gamari at 2022-07-16T23:50:36-04:00 rts/linker/MachO: Drop dead code - - - - - d161e6bc by Ben Gamari at 2022-07-16T23:50:36-04:00 rts/linker/MachO: Use section flags to identify initializers - - - - - fbb17110 by Ben Gamari at 2022-07-16T23:50:36-04:00 rts/linker/MachO: Introduce finalizer support - - - - - 5b0ed8a8 by Ben Gamari at 2022-07-16T23:50:37-04:00 testsuite: Use system-cxx-std-lib instead of config.stdcxx_impl - - - - - 6c476e1a by Ben Gamari at 2022-07-16T23:50:37-04:00 rts/linker/Elf: Work around GCC 6 init/fini behavior It appears that GCC 6t (at least on i386) fails to give init_array/fini_array sections the correct SHT_INIT_ARRAY/SHT_FINI_ARRAY section types, instead marking them as SHT_PROGBITS. This caused T20494 to fail on Debian. - - - - - 5f8203b8 by Ben Gamari at 2022-07-16T23:50:37-04:00 testsuite: Mark T13366Cxx as unbroken on Darwin - - - - - 1fd2f851 by Ben Gamari at 2022-07-16T23:50:37-04:00 rts/linker: Fix resolution of __dso_handle on Darwin Darwin expects a leading underscore. - - - - - a2dc00f3 by Ben Gamari at 2022-07-16T23:50:37-04:00 rts/linker: Clean up section kinds - - - - - aeb1a7c3 by Ben Gamari at 2022-07-16T23:50:37-04:00 rts/linker: Ensure that __cxa_finalize is called on code unload - - - - - 028f081e by Ben Gamari at 2022-07-16T23:51:12-04:00 testsuite: Fix T11829 on Centos 7 It appears that Centos 7 has a more strict C++ compiler than most distributions since std::runtime_error is defined in <stdexcept> rather than <exception>. In T11829 we mistakenly imported the latter. - - - - - a10584e8 by Ben Gamari at 2022-07-17T22:30:32-04:00 hadrian: Rename documentation directories for consistency with make * Rename `docs` to `doc` * Place pdf documentation in `doc/` instead of `doc/pdfs/` Fixes #21164. - - - - - b27c5947 by Anselm Schüler at 2022-07-17T22:31:11-04:00 Fix incorrect proof of applyWhen’s properties - - - - - eb031a5b by Matthew Pickering at 2022-07-18T08:04:47-04:00 hadrian: Add multi:<pkg> and multi targets for starting a multi-repl This patch adds support to hadrian for starting a multi-repl containing all the packages which stage0 can build. In particular, there is the new user-facing command: ``` ./hadrian/ghci-multi ``` which when executed will start a multi-repl containing the `ghc` package and all it's dependencies. This is implemented by two new hadrian targets: ``` ./hadrian/build multi:<pkg> ``` Construct the arguments for a multi-repl session where the top-level package is <pkg>. For example, `./hadrian/ghci-multi` is implemented using `multi:ghc` target. There is also the `multi` command which constructs a repl for everything in stage0 which we can build. - - - - - 19e7cac9 by Eric Lindblad at 2022-07-18T08:05:27-04:00 changelog typo - - - - - af6731a4 by Eric Lindblad at 2022-07-18T08:05:27-04:00 typos - - - - - 415468fe by Simon Peyton Jones at 2022-07-18T16:36:54-04:00 Refactor SpecConstr to use treat bindings uniformly This patch, provoked by #21457, simplifies SpecConstr by treating top-level and nested bindings uniformly (see the new scBind). * Eliminates the mysterious scTopBindEnv * Refactors scBind to handle top-level and nested definitions uniformly. * But, for now at least, continues the status quo of not doing SpecConstr for top-level non-recursive bindings. (In contrast we do specialise nested non-recursive bindings, although the original paper did not; see Note [Local let bindings].) I tried the effect of specialising top-level non-recursive bindings (which is now dead easy to switch on, unlike before) but found some regressions, so I backed off. See !8135. It's a pure refactoring. I think it'll do a better job in a few cases, but there is no regression test. - - - - - d4d3fe6e by Andreas Klebinger at 2022-07-18T16:37:29-04:00 Rule matching: Don't compute the FVs if we don't look at them. - - - - - 5f907371 by Simon Peyton Jones at 2022-07-18T16:38:04-04:00 White space only in FamInstEnv - - - - - ae3b3b62 by Simon Peyton Jones at 2022-07-18T16:38:04-04:00 Make transferPolyIdInfo work for CPR I don't know why this hasn't bitten us before, but it was plain wrong. - - - - - 9bdfdd98 by Simon Peyton Jones at 2022-07-18T16:38:04-04:00 Inline mapAccumLM This function is called in inner loops in the compiler, and it's overloaded and higher order. Best just to inline it. This popped up when I was looking at something else. I think perhaps GHC is delicately balanced on the cusp of inlining this automatically. - - - - - d0b806ff by Simon Peyton Jones at 2022-07-18T16:38:04-04:00 Make SetLevels honour floatConsts This fix, in the definition of profitableFloat, is just for consistency. `floatConsts` should do what it says! I don't think it'll affect anything much, though. - - - - - d1c25a48 by Simon Peyton Jones at 2022-07-18T16:38:04-04:00 Refactor wantToUnboxArg a bit * Rename GHC.Core.Opt.WorkWrap.Utils.wantToUnboxArg to canUnboxArg and similarly wantToUnboxResult to canUnboxResult. * Add GHC.Core.Opt.DmdAnal.wantToUnboxArg as a wrapper for the (new) GHC.Core.Opt.WorkWrap.Utils.canUnboxArg, avoiding some yukky duplication. I decided it was clearer to give it a new data type for its return type, because I nedeed the FD_RecBox case which was not otherwise readiliy expressible. * Add dcpc_args to WorkWrap.Utils.DataConPatContext for the payload * Get rid of the Unlift constructor of UnboxingDecision, eliminate two panics, and two arguments to canUnboxArg (new name). Much nicer now. - - - - - 6d8a715e by Teo Camarasu at 2022-07-18T16:38:44-04:00 Allow running memInventory when the concurrent nonmoving gc is enabled If the nonmoving gc is enabled and we are using a threaded RTS, we now try to grab the collector mutex to avoid memInventory and the collection racing. Before memInventory was disabled. - - - - - aa75bbde by Ben Gamari at 2022-07-18T16:39:20-04:00 gitignore: don't ignore all aclocal.m4 files While GHC's own aclocal.m4 is generated by the aclocal tool, other packages' aclocal.m4 are committed in the repository. Previously `.gitignore` included an entry which covered *any* file named `aclocal.m4`, which lead to quite some confusion (e.g. see #21740). Fix this by modifying GHC's `.gitignore` to only cover GHC's own `aclocal.m4`. - - - - - 4b98c5ce by Boris Lykah at 2022-07-19T02:34:12-04:00 Add mapAccumM, forAccumM to Data.Traversable Approved by Core Libraries Committee in https://github.com/haskell/core-libraries-committee/issues/65#issuecomment-1186275433 - - - - - bd92182c by Ben Gamari at 2022-07-19T02:34:47-04:00 configure: Use AC_PATH_TOOL to detect tools Previously we used AC_PATH_PROG which, as noted by #21601, does not look for tools with a target prefix, breaking cross-compilation. Fixes #21601. - - - - - 48fb43af by Phil de Joux at 2022-07-19T09:32:55+02:00 Follow hlint suggestion: unused LANGUAGE pragma. (#1504) * Follow hlint suggestion: unused LANGUAGE pragma. * Ignore within modules to pass linting and pass tests. - - - - - e8c07aa9 by Matthew Pickering at 2022-07-19T10:07:53-04:00 driver: Fix implementation of -S We were failing to stop before running the assembler so the object file was also created. Fixes #21869 - - - - - e2f0094c by Ben Gamari at 2022-07-19T10:08:28-04:00 rts/ProfHeap: Ensure new Censuses are zeroed When growing the Census array ProfHeap previously neglected to zero the new part of the array. Consequently `freeEra` would attempt to free random words that often looked suspiciously like pointers. Fixes #21880. - - - - - 81d65f7f by sheaf at 2022-07-21T15:37:22+02:00 Make withDict opaque to the specialiser As pointed out in #21575, it is not sufficient to set withDict to inline after the typeclass specialiser, because we might inline withDict in one module and then import it in another, and we run into the same problem. This means we could still end up with incorrect runtime results because the typeclass specialiser would assume that distinct typeclass evidence terms at the same type are equal, when this is not necessarily the case when using withDict. Instead, this patch introduces a new magicId, 'nospec', which is only inlined in CorePrep. We make use of it in the definition of withDict to ensure that the typeclass specialiser does not common up distinct typeclass evidence terms. Fixes #21575 - - - - - 9a3e1f31 by Dominik Peteler at 2022-07-22T08:18:40-04:00 Refactored Simplify pass * Removed references to driver from GHC.Core.LateCC, GHC.Core.Simplify namespace and GHC.Core.Opt.Stats. Also removed services from configuration records. * Renamed GHC.Core.Opt.Simplify to GHC.Core.Opt.Simplify.Iteration. * Inlined `simplifyPgm` and renamed `simplifyPgmIO` to `simplifyPgm` and moved the Simplify driver to GHC.Core.Opt.Simplify. * Moved `SimplMode` and `FloatEnable` to GHC.Core.Opt.Simplify.Env. * Added a configuration record `TopEnvConfig` for the `SimplTopEnv` environment in GHC.Core.Opt.Simplify.Monad. * Added `SimplifyOpts` and `SimplifyExprOpts`. Provide initialization functions for those in a new module GHC.Driver.Config.Core.Opt.Simplify. Also added initialization functions for `SimplMode` to that module. * Moved `CoreToDo` and friends to a new module GHC.Core.Pipeline.Types and the counting types and functions (`SimplCount` and `Tick`) to new module GHC.Core.Opt.Stats. * Added getter functions for the fields of `SimplMode`. The pedantic bottoms option and the platform are retrieved from the ArityOpts and RuleOpts and the getter functions allow us to retrieve values from `SpecEnv` without the knowledge where the data is stored exactly. * Moved the coercion optimization options from the top environment to `SimplMode`. This way the values left in the top environment are those dealing with monadic functionality, namely logging, IO related stuff and counting. Added a note "The environments of the Simplify pass". * Removed `CoreToDo` from GHC.Core.Lint and GHC.CoreToStg.Prep and got rid of `CoreDoSimplify`. Pass `SimplifyOpts` in the `CoreToDo` type instead. * Prep work before removing `InteractiveContext` from `HscEnv`. - - - - - 2c5991cc by Simon Peyton Jones at 2022-07-22T08:18:41-04:00 Make the specialiser deal better with specialised methods This patch fixes #21848, by being more careful to update unfoldings in the type-class specialiser. See the new Note [Update unfolding after specialisation] Now that we are being so much more careful about unfoldings, it turned out that I could dispense with se_interesting, and all its tricky corners. Hooray. This fixes #21368. - - - - - ae166635 by Ben Gamari at 2022-07-22T08:18:41-04:00 ghc-boot: Clean up UTF-8 codecs In preparation for moving the UTF-8 codecs into `base`: * Move them to GHC.Utils.Encoding.UTF8 * Make names more consistent * Add some Haddocks - - - - - e8ac91db by Ben Gamari at 2022-07-22T08:18:41-04:00 base: Introduce GHC.Encoding.UTF8 Here we copy a subset of the UTF-8 implementation living in `ghc-boot` into `base`, with the intent of dropping the former in the future. For this reason, the `ghc-boot` copy is now CPP-guarded on `MIN_VERSION_base(4,18,0)`. Naturally, we can't copy *all* of the functions defined by `ghc-boot` as some depend upon `bytestring`; we rather just copy those which only depend upon `base` and `ghc-prim`. Further consolidation? ---------------------- Currently GHC ships with at least five UTF-8 implementations: * the implementation used by GHC in `ghc-boot:GHC.Utils.Encoding`; this can be used at a number of types including `Addr#`, `ByteArray#`, `ForeignPtr`, `Ptr`, `ShortByteString`, and `ByteString`. Most of this can be removed in GHC 9.6+2, when the copies in `base` will become available to `ghc-boot`. * the copy of the `ghc-boot` definition now exported by `base:GHC.Encoding.UTF8`. This can be used at `Addr#`, `Ptr`, `ByteArray#`, and `ForeignPtr` * the decoder used by `unpackCStringUtf8#` in `ghc-prim:GHC.CString`; this is specialised at `Addr#`. * the codec used by the IO subsystem in `base:GHC.IO.Encoding.UTF8`; this is specialised at `Addr#` but, unlike the above, supports recovery in the presence of partial codepoints (since in IO contexts codepoints may be broken across buffers) * the implementation provided by the `text` library This does seem a tad silly. On the other hand, these implementations *do* materially differ from one another (e.g. in the types they support, the detail in errors they can report, and the ability to recover from partial codepoints). Consequently, it's quite unclear that further consolidate would be worthwhile. - - - - - f9ad8025 by Ben Gamari at 2022-07-22T08:18:41-04:00 Add a Note summarising GHC's UTF-8 implementations GHC has a somewhat dizzying array of UTF-8 implementations. This note describes why this is the case. - - - - - 72dfad3d by Ben Gamari at 2022-07-22T08:18:42-04:00 upload_ghc_libs: Fix path to documentation The documentation was moved in a10584e8df9b346cecf700b23187044742ce0b35 but this one occurrence was note updated. Finally closes #21164. - - - - - a8b150e7 by sheaf at 2022-07-22T08:18:44-04:00 Add test for #21871 This adds a test for #21871, which was fixed by the No Skolem Info rework (MR !7105). Fixes #21871 - - - - - 6379f942 by sheaf at 2022-07-22T08:18:46-04:00 Add test for #21360 The way record updates are typechecked/desugared changed in MR !7981. Because we desugar in the typechecker to a simple case expression, the pattern match checker becomes able to spot the long-distance information and avoid emitting an incorrect pattern match warning. Fixes #21360 - - - - - ce0cd12c by sheaf at 2022-07-22T08:18:47-04:00 Hadrian: don't try to build "unix" on Windows - - - - - c1cf1fa7 by Phil de Joux at 2022-07-24T13:45:59+02:00 Follow hlint suggestion: redundant $. (#1505) * Follow hlint suggestion: redundant $. * Remove $ and surplus blank lines in Operators. - - - - - dc27e15a by Simon Peyton Jones at 2022-07-25T09:42:01-04:00 Implement DeepSubsumption This MR adds the language extension -XDeepSubsumption, implementing GHC proposal #511. This change mitigates the impact of GHC proposal The changes are highly localised, by design. See Note [Deep subsumption] in GHC.Tc.Utils.Unify. The main changes are: * Add -XDeepSubsumption, which is on by default in Haskell98 and Haskell2010, but off in Haskell2021. -XDeepSubsumption largely restores the behaviour before the "simple subsumption" change. -XDeepSubsumpition has a similar flavour as -XNoMonoLocalBinds: it makes type inference more complicated and less predictable, but it may be convenient in practice. * The main changes are in: * GHC.Tc.Utils.Unify.tcSubType, which does deep susumption and eta-expanansion * GHC.Tc.Utils.Unify.tcSkolemiseET, which does deep skolemisation * In GHC.Tc.Gen.App.tcApp we call tcSubTypeNC to match the result type. Without deep subsumption, unifyExpectedType would be sufficent. See Note [Deep subsumption] in GHC.Tc.Utils.Unify. * There are no changes to Quick Look at all. * The type of `withDict` becomes ambiguous; so add -XAllowAmbiguousTypes to GHC.Magic.Dict * I fixed a small but egregious bug in GHC.Core.FVs.varTypeTyCoFVs, where we'd forgotten to take the free vars of the multiplicity of an Id. * I also had to fix tcSplitNestedSigmaTys When I did the shallow-subsumption patch commit 2b792facab46f7cdd09d12e79499f4e0dcd4293f Date: Sun Feb 2 18:23:11 2020 +0000 Simple subsumption I changed tcSplitNestedSigmaTys to not look through function arrows any more. But that was actually an un-forced change. This function is used only in * Improving error messages in GHC.Tc.Gen.Head.addFunResCtxt * Validity checking for default methods: GHC.Tc.TyCl.checkValidClass * A couple of calls in the GHCi debugger: GHC.Runtime.Heap.Inspect All to do with validity checking and error messages. Acutally its fine to look under function arrows here, and quite useful a test DeepSubsumption05 (a test motivated by a build failure in the `lens` package) shows. The fix is easy. I added Note [tcSplitNestedSigmaTys]. - - - - - e31ead39 by Matthew Pickering at 2022-07-25T09:42:01-04:00 Add tests that -XHaskell98 and -XHaskell2010 enable DeepSubsumption - - - - - 67189985 by Matthew Pickering at 2022-07-25T09:42:01-04:00 Add DeepSubsumption08 - - - - - 5e93a952 by Simon Peyton Jones at 2022-07-25T09:42:01-04:00 Fix the interaction of operator sections and deep subsumption Fixes DeepSubsumption08 - - - - - 918620d9 by Zubin Duggal at 2022-07-25T09:42:01-04:00 Add DeepSubsumption09 - - - - - 2a773259 by Gabriella Gonzalez at 2022-07-25T09:42:40-04:00 Default implementation for mempty/(<>) Approved by: https://github.com/haskell/core-libraries-committee/issues/61 This adds a default implementation for `mempty` and `(<>)` along with a matching `MINIMAL` pragma so that `Semigroup` and `Monoid` instances can be defined in terms of `sconcat` / `mconcat`. The description for each class has also been updated to include the equivalent set of laws for the `sconcat`-only / `mconcat`-only instances. - - - - - 73836fc8 by Bryan Richter at 2022-07-25T09:43:16-04:00 ci: Disable (broken) perf-nofib See #21859 - - - - - c24ca5c3 by sheaf at 2022-07-25T09:43:58-04:00 Docs: clarify ConstraintKinds infelicity GHC doesn't consistently require the ConstraintKinds extension to be enabled, as it allows programs such as type families returning a constraint without this extension. MR !7784 fixes this infelicity, but breaking user programs was deemed to not be worth it, so we document it instead. Fixes #21061. - - - - - 5f2fbd5e by Simon Peyton Jones at 2022-07-25T09:44:34-04:00 More improvements to worker/wrapper This patch fixes #21888, and simplifies finaliseArgBoxities by eliminating the (recently introduced) data type FinalDecision. A delicate interaction meant that this patch commit d1c25a48154236861a413e058ea38d1b8320273f Date: Tue Jul 12 16:33:46 2022 +0100 Refactor wantToUnboxArg a bit make worker/wrapper go into an infinite loop. This patch fixes it by narrowing the handling of case (B) of Note [Boxity for bottoming functions], to deal only the arguemnts that are type variables. Only then do we drop the trimBoxity call, which is what caused the bug. I also * Added documentation of case (B), which was previously completely un-mentioned. And a regression test, T21888a, to test it. * Made unboxDeeplyDmd stop at lazy demands. It's rare anyway for a bottoming function to have a lazy argument (mainly when the data type is recursive and then we don't want to unbox deeply). Plus there is Note [No lazy, Unboxed demands in demand signature] * Refactored the Case equation for dmdAnal a bit, to do less redundant pattern matching. - - - - - b77d95f8 by Simon Peyton Jones at 2022-07-25T09:45:09-04:00 Fix a small buglet in tryEtaReduce Gergo points out (#21801) that GHC.Core.Opt.Arity.tryEtaReduce was making an ill-formed cast. It didn't matter, because the subsequent guard discarded it; but still worth fixing. Spurious warnings are distracting. - - - - - 3bbde957 by Zubin Duggal at 2022-07-25T09:45:45-04:00 Fix #21889, GHCi misbehaves with Ctrl-C on Windows On Windows, we create multiple levels of wrappers for GHCi which ultimately execute ghc --interactive. In order to handle console events properly, each of these wrappers must call FreeConsole() in order to hand off event processing to the child process. See #14150. In addition to this, FreeConsole must only be called from interactive processes (#13411). This commit makes two changes to fix this situation: 1. The hadrian wrappers generated using `hadrian/bindist/cwrappers/version-wrapper.c` call `FreeConsole` if the CPP flag INTERACTIVE_PROCESS is set, which is set when we are generating a wrapper for GHCi. 2. The GHCi wrapper in `driver/ghci/` calls the `ghc-$VER.exe` executable which is not wrapped rather than calling `ghc.exe` is is wrapped on windows (and usually non-interactive, so can't call `FreeConsole`: Before: ghci-$VER.exe calls ghci.exe which calls ghc.exe which calls ghc-$VER.exe After: ghci-$VER.exe calls ghci.exe which calls ghc-$VER.exe - - - - - 79f1b021 by Simon Jakobi at 2022-07-25T09:46:21-04:00 docs: Fix documentation of \cases Fixes #21902. - - - - - e4bf9592 by sternenseemann at 2022-07-25T09:47:01-04:00 ghc-cabal: allow Cabal 3.8 to unbreak make build When bootstrapping GHC 9.4.*, the build will fail when configuring ghc-cabal as part of the make based build system due to this upper bound, as Cabal has been updated to a 3.8 release. Reference #21914, see especially https://gitlab.haskell.org/ghc/ghc/-/issues/21914#note_444699 - - - - - 726d938e by Simon Peyton Jones at 2022-07-25T14:38:14-04:00 Fix isEvaldUnfolding and isValueUnfolding This fixes (1) in #21831. Easy, obviously correct. - - - - - 5d26c321 by Simon Peyton Jones at 2022-07-25T14:38:14-04:00 Switch off eta-expansion in rules and unfoldings I think this change will make little difference except to reduce clutter. But that's it -- if it causes problems we can switch it on again. - - - - - d4fe2f4e by Simon Peyton Jones at 2022-07-25T14:38:14-04:00 Teach SpecConstr about typeDeterminesValue This patch addresses #21831, point 2. See Note [generaliseDictPats] in SpecConstr I took the opportunity to refactor the construction of specialisation rules a bit, so that the rule name says what type we are specialising at. Surprisingly, there's a 20% decrease in compile time for test perf/compiler/T18223. I took a look at it, and the code size seems the same throughout. I did a quick ticky profile which seemed to show a bit less substitution going on. Hmm. Maybe it's the "don't do eta-expansion in stable unfoldings" patch, which is part of the same MR as this patch. Anyway, since it's a move in the right direction, I didn't think it was worth looking into further. Metric Decrease: T18223 - - - - - 65f7838a by Simon Peyton Jones at 2022-07-25T14:38:14-04:00 Add a 'notes' file in testsuite/tests/perf/compiler This file is just a place to accumlate notes about particular benchmarks, so that I don't keep re-inventing the wheel. - - - - - 61faff40 by Simon Peyton Jones at 2022-07-25T14:38:50-04:00 Get the in-scope set right in FamInstEnv.injectiveBranches There was an assert error, as Gergo pointed out in #21896. I fixed this by adding an InScopeSet argument to tcUnifyTyWithTFs. And also to GHC.Core.Unify.niFixTCvSubst. I also took the opportunity to get a couple more InScopeSets right, and to change some substTyUnchecked into substTy. This MR touches a lot of other files, but only because I also took the opportunity to introduce mkInScopeSetList, and use it. - - - - - 4a7256a7 by Cheng Shao at 2022-07-25T20:41:55+00:00 Add location to cc phase - - - - - 96811ba4 by Cheng Shao at 2022-07-25T20:41:55+00:00 Avoid as pipeline when compiling c - - - - - 2869b66d by Cheng Shao at 2022-07-25T20:42:20+00:00 testsuite: Skip test cases involving -S when testing unregisterised GHC We no longer generate .s files anyway. Metric Decrease: MultiLayerModules T10421 T13035 T13701 T14697 T16875 T18140 T18304 T18923 T9198 - - - - - 82a0991a by Ben Gamari at 2022-07-25T23:32:05-04:00 testsuite: introduce nonmoving_thread_sanity way (cherry picked from commit 19f8fce3659de3d72046bea9c61d1a82904bc4ae) - - - - - 4b087973 by Ben Gamari at 2022-07-25T23:32:06-04:00 rts/nonmoving: Track segment state It can often be useful during debugging to be able to determine the state of a nonmoving segment. Introduce some state, enabled by DEBUG, to track this. (cherry picked from commit 40e797ef591ae3122ccc98ab0cc3cfcf9d17bd7f) - - - - - 54a5c32d by Ben Gamari at 2022-07-25T23:32:06-04:00 rts/nonmoving: Don't scavenge objects which weren't evacuated This fixes a rather subtle bug in the logic responsible for scavenging objects evacuated to the non-moving generation. In particular, objects can be allocated into the non-moving generation by two ways: a. evacuation out of from-space by the garbage collector b. direct allocation by the mutator Like all evacuation, objects moved by (a) must be scavenged, since they may contain references to other objects located in from-space. To accomplish this we have the following scheme: * each nonmoving segment's block descriptor has a scan pointer which points to the first object which has yet to be scavenged * the GC tracks a set of "todo" segments which have pending scavenging work * to scavenge a segment, we scavenge each of the unmarked blocks between the scan pointer and segment's `next_free` pointer. We skip marked blocks since we know the allocator wouldn't have allocated into marked blocks (since they contain presumably live data). We can stop at `next_free` since, by definition, the GC could not have evacuated any objects to blocks above `next_free` (otherwise `next_free wouldn't be the first free block). However, this neglected to consider objects allocated by path (b). In short, the problem is that objects directly allocated by the mutator may become unreachable (but not swept, since the containing segment is not yet full), at which point they may contain references to swept objects. Specifically, we observed this in #21885 in the following way: 1. the mutator (specifically in #21885, a `lockCAF`) allocates an object (specifically a blackhole, which here we will call `blkh`; see Note [Static objects under the nonmoving collector] for the reason why) on the non-moving heap. The bitmap of the allocated block remains 0 (since allocation doesn't affect the bitmap) and the containing segment's (which we will call `blkh_seg`) `next_free` is advanced. 2. We enter the blackhole, evaluating the blackhole to produce a result (specificaly a cons cell) in the nursery 3. The blackhole gets updated into an indirection pointing to the cons cell; it is pushed to the generational remembered set 4. we perform a GC, the cons cell is evacuated into the nonmoving heap (into segment `cons_seg`) 5. the cons cell is marked 6. the GC concludes 7. the CAF and blackhole become unreachable 8. `cons_seg` is filled 9. we start another GC; the cons cell is swept 10. we start a new GC 11. something is evacuated into `blkh_seg`, adding it to the "todo" list 12. we attempt to scavenge `blkh_seg` (namely, all unmarked blocks between `scan` and `next_free`, which includes `blkh`). We attempt to evacuate `blkh`'s indirectee, which is the previously-swept cons cell. This is unsafe, since the indirectee is no longer a valid heap object. The problem here was that the scavenging logic *assumed* that (a) was the only source of allocations into the non-moving heap and therefore *all* unmarked blocks between `scan` and `next_free` were evacuated. However, due to (b) this is not true. The solution is to ensure that that the scanned region only encompasses the region of objects allocated during evacuation. We do this by updating `scan` as we push the segment to the todo-segment list to point to the block which was evacuated into. Doing this required changing the nonmoving scavenging implementation's update of the `scan` pointer to bump it *once*, instead of after scavenging each block as was done previously. This is because we may end up evacuating into the segment being scavenged as we scavenge it. This was quite tricky to discover but the result is quite simple, demonstrating yet again that global mutable state should be used exceedingly sparingly. Fixes #21885 (cherry picked from commit 0b27ea23efcb08639309293faf13fdfef03f1060) - - - - - 25c24535 by Ben Gamari at 2022-07-25T23:32:06-04:00 testsuite: Skip a few tests as in the nonmoving collector Residency monitoring under the non-moving collector is quite conservative (e.g. the reported value is larger than reality) since otherwise we would need to block on concurrent collection. Skip a few tests that are sensitive to residency. (cherry picked from commit 6880e4fbf728c04e8ce83e725bfc028fcb18cd70) - - - - - 42147534 by sternenseemann at 2022-07-26T16:26:53-04:00 hadrian: add flag disabling selftest rules which require QuickCheck The hadrian executable depends on QuickCheck for building, meaning this library (and its dependencies) will need to be built for bootstrapping GHC in the future. Building QuickCheck, however, can require TemplateHaskell. When building a statically linking GHC toolchain, TemplateHaskell can be tricky to get to work, and cross-compiling TemplateHaskell doesn't work at all without -fexternal-interpreter, so QuickCheck introduces an element of fragility to GHC's bootstrap. Since the selftest rules are the only part of hadrian that need QuickCheck, we can easily eliminate this bootstrap dependency when required by introducing a `selftest` flag guarding the rules' inclusion. Closes #8699. - - - - - 9ea29d47 by Simon Peyton Jones at 2022-07-26T16:27:28-04:00 Regression test for #21848 - - - - - ef30e215 by Matthew Pickering at 2022-07-28T13:56:59-04:00 driver: Don't create LinkNodes when -no-link is enabled Fixes #21866 - - - - - fc23b5ed by sheaf at 2022-07-28T13:57:38-04:00 Docs: fix mistaken claim about kind signatures This patch fixes #21806 by rectifying an incorrect claim about the usage of kind variables in the header of a data declaration with a standalone kind signature. It also adds some clarifications about the number of parameters expected in GADT declarations and in type family declarations. - - - - - 74777eb2 by Jade Lovelace at 2022-07-29T11:02:41+01:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` (cherry picked from commit ab53ccf089ea703b767581ac14be0f6c78a7678a) - - - - - faa4cfcf by Hécate Moonlight at 2022-07-29T20:31:20+02:00 Merge pull request haskell/haddock#1516 from duog/9-4-backport-fix-hyperlinks Backport 9-4: Fix hyperlinks to external items and modules (#1482) - - - - - 2df92ee1 by Matthew Pickering at 2022-08-02T05:20:01-04:00 testsuite: Correctly set withNativeCodeGen Fixes #21918 - - - - - f2912143 by Matthew Pickering at 2022-08-02T05:20:45-04:00 Fix since annotations in GHC.Stack.CloneStack Fixes #21894 - - - - - aeb8497d by Andreas Klebinger at 2022-08-02T19:26:51-04:00 Add -dsuppress-coercion-types to make coercions even smaller. Instead of `` `cast` <Co:11> :: (Some -> Really -> Large Type)`` simply print `` `cast` <Co:11> :: ... `` - - - - - 97655ad8 by sheaf at 2022-08-02T19:27:29-04:00 User's guide: fix typo in hasfield.rst Fixes #21950 - - - - - 35aef18d by Yiyun Liu at 2022-08-04T02:55:07-04:00 Remove TCvSubst and use Subst for both term and type-level subst This patch removes the TCvSubst data type and instead uses Subst as the environment for both term and type level substitution. This change is partially motivated by the existential type proposal, which will introduce types that contain expressions and therefore forces us to carry around an "IdSubstEnv" even when substituting for types. It also reduces the amount of code because "Subst" and "TCvSubst" share a lot of common operations. There isn't any noticeable impact on performance (geo. mean for ghc/alloc is around 0.0% but we have -94 loc and one less data type to worry abount). Currently, the "TCvSubst" data type for substitution on types is identical to the "Subst" data type except the former doesn't store "IdSubstEnv". Using "Subst" for type-level substitution means there will be a redundant field stored in the data type. However, in cases where the substitution starts from the expression, using "Subst" for type-level substitution saves us from having to project "Subst" into a "TCvSubst". This probably explains why the allocation is mostly even despite the redundant field. The patch deletes "TCvSubst" and moves "Subst" and its relevant functions from "GHC.Core.Subst" into "GHC.Core.TyCo.Subst". Substitution on expressions is still defined in "GHC.Core.Subst" so we don't have to expose the definition of "Expr" in the hs-boot file that "GHC.Core.TyCo.Subst" must import to refer to "IdSubstEnv" (whose codomain is "CoreExpr"). Most functions named fooTCvSubst are renamed into fooSubst with a few exceptions (e.g. "isEmptyTCvSubst" is a distinct function from "isEmptySubst"; the former ignores the emptiness of "IdSubstEnv"). These exceptions mainly exist for performance reasons and will go away when "Expr" and "Type" are mutually recursively defined (we won't be able to take those shortcuts if we can't make the assumption that expressions don't appear in types). - - - - - b99819bd by Krzysztof Gogolewski at 2022-08-04T02:55:43-04:00 Fix TH + defer-type-errors interaction (#21920) Previously, we had to disable defer-type-errors in splices because of #7276. But this fix is no longer necessary, the test T7276 no longer segfaults and is now correctly deferred. - - - - - fb529cae by Andreas Klebinger at 2022-08-04T13:57:25-04:00 Add a note about about W/W for unlifting strict arguments This fixes #21236. - - - - - fffc75a9 by Matthew Pickering at 2022-08-04T13:58:01-04:00 Force safeInferred to avoid retaining extra copy of DynFlags This will only have a (very) modest impact on memory but we don't want to retain old copies of DynFlags hanging around so best to force this value. - - - - - 0f43837f by Matthew Pickering at 2022-08-04T13:58:01-04:00 Force name selectors to ensure no reference to Ids enter the NameCache I observed some unforced thunks in the NameCache which were retaining a whole Id, which ends up retaining a Type.. which ends up retaining old copies of HscEnv containing stale HomeModInfo. - - - - - 0b1f5fd1 by Matthew Pickering at 2022-08-04T13:58:01-04:00 Fix leaks in --make mode when there are module loops This patch fixes quite a tricky leak where we would end up retaining stale ModDetails due to rehydrating modules against non-finalised interfaces. == Loops with multiple boot files It is possible for a module graph to have a loop (SCC, when ignoring boot files) which requires multiple boot files to break. In this case we must perform the necessary hydration steps before and after compiling modules which have boot files which are described above for corectness but also perform an additional hydration step at the end of the SCC to remove space leaks. Consider the following example: ┌───────┐ ┌───────┐ │ │ │ │ │ A │ │ B │ │ │ │ │ └─────┬─┘ └───┬───┘ │ │ ┌────▼─────────▼──┐ │ │ │ C │ └────┬─────────┬──┘ │ │ ┌────▼──┐ ┌───▼───┐ │ │ │ │ │ A-boot│ │ B-boot│ │ │ │ │ └───────┘ └───────┘ A, B and C live together in a SCC. Say we compile the modules in order A-boot, B-boot, C, A, B then when we compile A we will perform the hydration steps (because A has a boot file). Therefore C will be hydrated relative to A, and the ModDetails for A will reference C/A. Then when B is compiled C will be rehydrated again, and so B will reference C/A,B, its interface will be hydrated relative to both A and B. Now there is a space leak because say C is a very big module, there are now two different copies of ModDetails kept alive by modules A and B. The way to avoid this space leak is to rehydrate an entire SCC together at the end of compilation so that all the ModDetails point to interfaces for .hs files. In this example, when we hydrate A, B and C together then both A and B will refer to C/A,B. See #21900 for some more discussion. ------------------------------------------------------- In addition to this simple case, there is also the potential for a leak during parallel upsweep which is also fixed by this patch. Transcibed is Note [ModuleNameSet, efficiency and space leaks] Note [ModuleNameSet, efficiency and space leaks] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ During unsweep the results of compiling modules are placed into a MVar, to find the environment the module needs to compile itself in the MVar is consulted and the HomeUnitGraph is set accordingly. The reason we do this is that precisely tracking module dependencies and recreating the HUG from scratch each time is very expensive. In serial mode (-j1), this all works out fine because a module can only be compiled after its dependencies have finished compiling and not interleaved with compiling module loops. Therefore when we create the finalised or no loop interfaces, the HUG only contains finalised interfaces. In parallel mode, we have to be more careful because the HUG variable can contain non-finalised interfaces which have been started by another thread. In order to avoid a space leak where a finalised interface is compiled against a HPT which contains a non-finalised interface we have to restrict the HUG to only the visible modules. The visible modules is recording in the ModuleNameSet, this is propagated upwards whilst compiling and explains which transitive modules are visible from a certain point. This set is then used to restrict the HUG before the module is compiled to only the visible modules and thus avoiding this tricky space leak. Efficiency of the ModuleNameSet is of utmost importance because a union occurs for each edge in the module graph. Therefore the set is represented directly as an IntSet which provides suitable performance, even using a UniqSet (which is backed by an IntMap) is too slow. The crucial test of performance here is the time taken to a do a no-op build in --make mode. See test "jspace" for an example which used to trigger this problem. Fixes #21900 - - - - - 1d94a59f by Matthew Pickering at 2022-08-04T13:58:01-04:00 Store interfaces in ModIfaceCache more directly I realised hydration was completely irrelavant for this cache because the ModDetails are pruned from the result. So now it simplifies things a lot to just store the ModIface and Linkable, which we can put into the cache straight away rather than wait for the final version of a HomeModInfo to appear. - - - - - 6c7cd50f by Cheng Shao at 2022-08-04T23:01:45-04:00 cmm: Remove unused ReadOnlyData16 We don't actually emit rodata16 sections anywhere. - - - - - 16333ad7 by Andreas Klebinger at 2022-08-04T23:02:20-04:00 findExternalRules: Don't needlessly traverse the list of rules. - - - - - 52c15674 by Krzysztof Gogolewski at 2022-08-05T12:47:05-04:00 Remove backported items from 9.6 release notes They have been backported to 9.4 in commits 5423d84bd9a28f, 13c81cb6be95c5, 67ccbd6b2d4b9b. - - - - - 78d232f5 by Matthew Pickering at 2022-08-05T12:47:40-04:00 ci: Fix pages job The job has been failing because we don't bundle haddock docs anymore in the docs dist created by hadrian. Fixes #21789 - - - - - 5d2450f3 by Ben Gamari at 2022-08-05T17:41:15-04:00 Merge remote-tracking branch 'origin/ghc-9.4' - - - - - 63954f73 by Ben Gamari at 2022-08-05T19:08:36-04:00 Clean up build and testsuite for GHC 9.4 - - - - - d4568cb8 by Hécate Moonlight at 2022-08-05T19:10:49-04:00 Bump the versions - - - - - 037bc9c9 by Ben Gamari at 2022-08-05T22:00:29-04:00 codeGen/X86: Don't clobber switch variable in switch generation Previously ce8745952f99174ad9d3bdc7697fd086b47cdfb5 assumed that it was safe to clobber the switch variable when generating code for a jump table since we were at the end of a block. However, this assumption is wrong; the register could be live in the jump target. Fixes #21968. - - - - - 50c8e1c5 by Matthew Pickering at 2022-08-05T22:01:04-04:00 Fix equality operator in jspace test - - - - - e9c77a22 by Andreas Klebinger at 2022-08-06T06:13:17-04:00 Improve BUILD_PAP comments - - - - - 41234147 by Andreas Klebinger at 2022-08-06T06:13:17-04:00 Make dropTail comment a haddock comment - - - - - ff11d579 by Andreas Klebinger at 2022-08-06T06:13:17-04:00 Add one more sanity check in stg_restore_cccs - - - - - 1f6c56ae by Andreas Klebinger at 2022-08-06T06:13:17-04:00 StgToCmm: Fix isSimpleScrut when profiling is enabled. When profiling is enabled we must enter functions that might represent thunks in order for their sccs to show up in the profile. We might allocate even if the function is already evaluated in this case. So we can't consider any potential function thunk to be a simple scrut when profiling. Not doing so caused profiled binaries to segfault. - - - - - fab0ee93 by Andreas Klebinger at 2022-08-06T06:13:17-04:00 Change `-fprof-late` to insert cost centres after unfolding creation. The former behaviour of adding cost centres after optimization but before unfoldings are created is not available via the flag `prof-late-inline` instead. I also reduced the overhead of -fprof-late* by pushing the cost centres into lambdas. This means the cost centres will only account for execution of functions and not their partial application. Further I made LATE_CC cost centres it's own CC flavour so they now won't clash with user defined ones if a user uses the same string for a custom scc. LateCC: Don't put cost centres inside constructor workers. With -fprof-late they are rarely useful as the worker is usually inlined. Even if the worker is not inlined or we use -fprof-late-linline they are generally not helpful but bloat compile and run time significantly. So we just don't add sccs inside constructor workers. ------------------------- Metric Decrease: T13701 ------------------------- - - - - - f8bec4e3 by Ben Gamari at 2022-08-06T06:13:53-04:00 gitlab-ci: Fix hadrian bootstrapping of release pipelines Previously we would attempt to test hadrian bootstrapping in the `validate` build flavour. However, `ci.sh` refuses to run validation builds during release pipelines, resulting in job failures. Fix this by testing bootstrapping in the `release` flavour during release pipelines. We also attempted to record perf notes for these builds, which is redundant work and undesirable now since we no longer build in a consistent flavour. - - - - - c0348865 by Ben Gamari at 2022-08-06T11:45:17-04:00 compiler: Eliminate two uses of foldr in favor of foldl' These two uses constructed maps, which is a case where foldl' is generally more efficient since we avoid constructing an intermediate O(n)-depth stack. - - - - - d2e4e123 by Ben Gamari at 2022-08-06T11:45:17-04:00 rts: Fix code style - - - - - 57f530d3 by Ben Gamari at 2022-08-06T11:45:17-04:00 genprimopcode: Drop ArrayArray# references As ArrayArray# no longer exists - - - - - 7267cd52 by Ben Gamari at 2022-08-06T11:45:17-04:00 base: Organize Haddocks in GHC.Conc.Sync - - - - - aa818a9f by Ben Gamari at 2022-08-06T11:48:50-04:00 Add primop to list threads A user came to #ghc yesterday wondering how best to check whether they were leaking threads. We ended up using the eventlog but it seems to me like it would be generally useful if Haskell programs could query their own threads. - - - - - 6d1700b6 by Ben Gamari at 2022-08-06T11:51:35-04:00 rts: Move thread labels into TSO This eliminates the thread label HashTable and instead tracks this information in the TSO, allowing us to use proper StgArrBytes arrays for backing the label and greatly simplifying management of object lifetimes when we expose them to the user with the coming `threadLabel#` primop. - - - - - 1472044b by Ben Gamari at 2022-08-06T11:54:52-04:00 Add a primop to query the label of a thread - - - - - 43f2b271 by Ben Gamari at 2022-08-06T11:55:14-04:00 base: Share finalization thread label For efficiency's sake we float the thread label assigned to the finalization thread to the top-level, ensuring that we only need to encode the label once. - - - - - 1d63b4fb by Ben Gamari at 2022-08-06T11:57:11-04:00 users-guide: Add release notes entry for thread introspection support - - - - - 505583a4 by Ben Gamari at 2022-08-06T13:58:27-04:00 Merge pull request haskell/haddock#1518 from bgamari/wip/ghc-9.4-merge Merge GHC 9.4 into `main` - - - - - 5706f6a4 by Ben Gamari at 2022-08-06T22:57:21-04:00 html-test: Testsuite changes for GHC 9.4.1 - - - - - 09bca1de by Ben Gamari at 2022-08-07T01:19:35-04:00 hadrian: Fix binary distribution install attributes Previously we would use plain `cp` to install various parts of the binary distribution. However, `cp`'s behavior w.r.t. file attributes is quite unclear; for this reason it is much better to rather use `install`. Fixes #21965. - - - - - 2b8ea16d by Ben Gamari at 2022-08-07T01:19:35-04:00 hadrian: Fix installation of system-cxx-std-lib package conf - - - - - 7b514848 by Ben Gamari at 2022-08-07T01:20:10-04:00 gitlab-ci: Bump Docker images To give the ARMv7 job access to lld, fixing #21875. - - - - - afa584a3 by Ben Gamari at 2022-08-07T05:08:52-04:00 hadrian: Don't use mk/config.mk.in Ultimately we want to drop mk/config.mk so here I extract the bits needed by the Hadrian bindist installation logic into a Hadrian-specific file. While doing this I fixed binary distribution installation, #21901. - - - - - b9bb45d7 by Ben Gamari at 2022-08-07T05:08:52-04:00 hadrian: Fix naming of cross-compiler wrappers - - - - - 78d04cfa by Ben Gamari at 2022-08-07T11:44:58-04:00 hadrian: Extend xattr Darwin hack to cover /lib As noted in #21506, it is now necessary to remove extended attributes from `/lib` as well as `/bin` to avoid SIP issues on Darwin. Fixes #21506. - - - - - 20457d77 by Andreas Klebinger at 2022-08-08T14:42:26+02:00 NCG(x86): Compile add+shift as lea if possible. - - - - - 742292e4 by Andreas Klebinger at 2022-08-08T16:46:37-04:00 dataToTag#: Skip runtime tag check if argument is infered tagged This addresses one part of #21710. - - - - - 1504a93e by Cheng Shao at 2022-08-08T16:47:14-04:00 rts: remove redundant stg_traceCcszh This out-of-line primop has no Haskell wrapper and hasn't been used anywhere in the tree. Furthermore, the code gets in the way of !7632, so it should be garbage collected. - - - - - a52de3cb by Andreas Klebinger at 2022-08-08T16:47:50-04:00 Document a divergence from the report in parsing function lhss. GHC is happy to parse `(f) x y = x + y` when it should be a parse error based on the Haskell report. Seems harmless enough so we won't fix it but it's documented now. Fixes #19788 - - - - - 5765e133 by Ben Gamari at 2022-08-08T16:48:25-04:00 gitlab-ci: Add release job for aarch64/debian 11 - - - - - 5b26f324 by Ben Gamari at 2022-08-08T19:39:20-04:00 gitlab-ci: Introduce validation job for aarch64 cross-compilation Begins to address #11958. - - - - - e866625c by Ben Gamari at 2022-08-08T19:39:20-04:00 Bump process submodule - - - - - ae707762 by Ben Gamari at 2022-08-08T19:39:20-04:00 gitlab-ci: Add basic support for cross-compiler testiing Here we add a simple qemu-based test for cross-compilers. - - - - - 50912d68 by Ben Gamari at 2022-08-08T19:39:57-04:00 rts: Ensure that Array# card arrays are initialized In #19143 I noticed that newArray# failed to initialize the card table of newly-allocated arrays. However, embarrassingly, I then only fixed the issue in newArrayArray# and, in so doing, introduced the potential for an integer underflow on zero-length arrays (#21962). Here I fix the issue in newArray#, this time ensuring that we do not underflow in pathological cases. Fixes #19143. - - - - - e5ceff56 by Ben Gamari at 2022-08-08T19:39:57-04:00 testsuite: Add test for #21962 - - - - - c1c08bd8 by Ben Gamari at 2022-08-09T02:31:14-04:00 gitlab-ci: Don't use coreutils on Darwin In general we want to ensure that the tested environment is as similar as possible to the environment the user will use. In the case of Darwin, this means we want to use the system's BSD command-line utilities, not coreutils. This would have caught #21974. - - - - - 1c582f44 by Ben Gamari at 2022-08-09T02:31:14-04:00 hadrian: Fix bindist installation on Darwin It turns out that `cp -P` on Darwin does not always copy a symlink as a symlink. In order to get these semantics one must pass `-RP`. It's not entirely clear whether this is valid under POSIX, but it is nevertheless what Apple does. - - - - - 681aa076 by Ben Gamari at 2022-08-09T02:31:49-04:00 hadrian: Fix access mode of installed package registration files Previously hadrian's bindist Makefile would modify package registrations placed by `install` via a shell pipeline and `mv`. However, the use of `mv` means that if umask is set then the user may otherwise end up with package registrations which are inaccessible. Fix this by ensuring that the mode is 0644. - - - - - e9dfd26a by Krzysztof Gogolewski at 2022-08-09T02:32:24-04:00 Cleanups around pretty-printing * Remove hack when printing OccNames. No longer needed since e3dcc0d5 * Remove unused `pprCmms` and `instance Outputable Instr` * Simplify `pprCLabel` (no need to pass platform) * Remove evil `Show`/`Eq` instances for `SDoc`. They were needed by ImmLit, but that can take just a String instead. * Remove instance `Outputable CLabel` - proper output of labels needs a platform, and is done by the `OutputableP` instance - - - - - 66d2e927 by Ben Gamari at 2022-08-09T13:46:48-04:00 rts/linker: Resolve iconv_* on FreeBSD FreeBSD's libiconv includes an implementation of the iconv_* functions in libc. Unfortunately these can only be resolved using dlvsym, which is how the RTS linker usually resolves such functions. To fix this we include an ad-hoc special case for iconv_*. Fixes #20354. - - - - - 5d66a0ce by Ben Gamari at 2022-08-09T13:46:48-04:00 system-cxx-std-lib: Add support for FreeBSD libcxxrt - - - - - ea90e61d by Ben Gamari at 2022-08-09T13:46:48-04:00 gitlab-ci: Bump to use freebsd13 runners - - - - - d71a2051 by sheaf at 2022-08-09T13:47:28-04:00 Fix size_up_alloc to account for UnliftedDatatypes The size_up_alloc function mistakenly considered any type that isn't lifted to not allocate anything, which is wrong. What we want instead is to check the type isn't boxed. This accounts for (BoxedRep Unlifted). Fixes #21939 - - - - - 76b52cf0 by Douglas Wilson at 2022-08-10T06:01:53-04:00 testsuite: 21651 add test for closeFdWith + setNumCapabilities This bug does not affect windows, which does not use the base module GHC.Event.Thread. - - - - - 7589ee72 by Douglas Wilson at 2022-08-10T06:01:53-04:00 base: Fix races in IOManager (setNumCapabilities,closeFdWith) Fix for #21651 Fixes three bugs: - writes to eventManager should be atomic. It is accessed concurrently by ioManagerCapabilitiesChanged and closeFdWith. - The race in closeFdWith described in the ticket. - A race in getSystemEventManager where it accesses the 'IOArray' in 'eventManager' before 'ioManagerCapabilitiesChanged' has written to 'eventManager', causing an Array Index exception. The fix here is to 'yield' and retry. - - - - - dc76439d by Trevis Elser at 2022-08-10T06:02:28-04:00 Updates language extension documentation Adding a 'Status' field with a few values: - Deprecated - Experimental - InternalUseOnly - Noting if included in 'GHC2021', 'Haskell2010' or 'Haskell98' Those values are pulled from the existing descriptions or elsewhere in the documentation. While at it, include the :implied by: where appropriate, to provide more detail. Fixes #21475 - - - - - 823fe5b5 by Jens Petersen at 2022-08-10T06:03:07-04:00 hadrian RunRest: add type signature for stageNumber avoids warning seen on 9.4.1: src/Settings/Builders/RunTest.hs:264:53: warning: [-Wtype-defaults] • Defaulting the following constraints to type ‘Integer’ (Show a0) arising from a use of ‘show’ at src/Settings/Builders/RunTest.hs:264:53-84 (Num a0) arising from a use of ‘stageNumber’ at src/Settings/Builders/RunTest.hs:264:59-83 • In the second argument of ‘(++)’, namely ‘show (stageNumber (C.stage ctx))’ In the second argument of ‘($)’, namely ‘"config.stage=" ++ show (stageNumber (C.stage ctx))’ In the expression: arg $ "config.stage=" ++ show (stageNumber (C.stage ctx)) | 264 | , arg "-e", arg $ "config.stage=" ++ show (stageNumber (C.stage ctx)) | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ compilation tested locally - - - - - f95bbdca by Sylvain Henry at 2022-08-10T09:44:46-04:00 Add support for external static plugins (#20964) This patch adds a new command-line flag: -fplugin-library=<file-path>;<unit-id>;<module>;<args> used like this: -fplugin-library=path/to/plugin.so;package-123;Plugin.Module;["Argument","List"] It allows a plugin to be loaded directly from a shared library. With this approach, GHC doesn't compile anything for the plugin and doesn't load any .hi file for the plugin and its dependencies. As such GHC doesn't need to support two environments (one for plugins, one for target code), which was the more ambitious approach tracked in #14335. Fix #20964 Co-authored-by: Josh Meredith <joshmeredith2008 at gmail.com> - - - - - 5bc489ca by Ben Gamari at 2022-08-10T09:45:22-04:00 gitlab-ci: Fix ARMv7 build It appears that the CI refactoring carried out in 5ff690b8474c74e9c968ef31e568c1ad0fe719a1 failed to carry over some critical configuration: setting the build/host/target platforms and forcing use of a non-broken linker. - - - - - 596db9a5 by Ben Gamari at 2022-08-10T09:45:22-04:00 gitlab-ci: Run ARMv7 jobs when ~ARM label is used - - - - - 7cabea7c by Ben Gamari at 2022-08-10T15:37:58-04:00 hadrian: Don't attempt to install documentation if doc/ doesn't exist Previously we would attempt to install documentation even if the `doc` directory doesn't exist (e.g. due to `--docs=none`). This would result in the surprising side-effect of the entire contents of the bindist being installed in the destination documentation directory. Fix this. Fixes #21976. - - - - - 67575f20 by normalcoder at 2022-08-10T15:38:34-04:00 ncg/aarch64: Don't use x18 register on AArch64/Darwin Apple's ABI documentation [1] says: "The platforms reserve register x18. Don’t use this register." While this wasn't problematic in previous Darwin releases, macOS 13 appears to start zeroing this register periodically. See #21964. [1] https://developer.apple.com/documentation/xcode/writing-arm64-code-for-apple-platforms - - - - - 45eb4cbe by Andreas Klebinger at 2022-08-10T22:41:12-04:00 Note [Trimming auto-rules]: State that this improves compiler perf. - - - - - 5c24b1b3 by Andrew Lelechenko at 2022-08-10T22:41:50-04:00 Document that threadDelay / timeout are susceptible to overflows on 32-bit machines - - - - - ff67c79e by Alan Zimmerman at 2022-08-11T16:19:57-04:00 EPA: DotFieldOcc does not have exact print annotations For the code {-# LANGUAGE OverloadedRecordUpdate #-} operatorUpdate f = f{(+) = 1} There are no exact print annotations for the parens around the + symbol, nor does normal ppr print them. This MR fixes that. Closes #21805 Updates haddock submodule - - - - - dca43a04 by Matthew Pickering at 2022-08-11T16:20:33-04:00 Revert "gitlab-ci: Add release job for aarch64/debian 11" This reverts commit 5765e13370634979eb6a0d9f67aa9afa797bee46. The job was not tested before being merged and fails CI (https://gitlab.haskell.org/ghc/ghc/-/jobs/1139392) Ticket #22005 - - - - - 5f2a45a2 by Ben Gamari at 2022-08-15T14:33:05-04:00 doc: Fix a few minor ReST issues Sphinx was complaining about too-short title underlines. - - - - - 220e6410 by Ben Gamari at 2022-08-15T14:41:24-04:00 Merge branch 'main' into ghc-head - - - - - fbeb1b02 by Ben Gamari at 2022-08-15T14:45:16-04:00 Updates for GHC 9.5 - - - - - eee562eb by Vladislav Zavialov at 2022-08-15T14:46:13-04:00 HsToken ConDeclGADT con_dcolon - - - - - c5f073db by Ben Gamari at 2022-08-15T16:55:35-04:00 Updates for GHC 9.5 - - - - - 3f7ab242 by Vladislav Zavialov at 2022-08-15T16:55:35-04:00 HsToken ConDeclGADT con_dcolon - - - - - a18e473d by Ben Gamari at 2022-08-16T08:35:19-04:00 Merge branch 'wip/ghc-head-bump' into ghc-head - - - - - ffc9116e by Eric Lindblad at 2022-08-16T09:01:26-04:00 typo - - - - - cd6f5bfd by Ben Gamari at 2022-08-16T09:02:02-04:00 CmmToLlvm: Don't aliasify builtin LLVM variables Our aliasification logic would previously turn builtin LLVM variables into aliases, which apparently confuses LLVM. This manifested in initializers failing to be emitted, resulting in many profiling failures with the LLVM backend. Fixes #22019. - - - - - dc7da356 by Bryan Richter at 2022-08-16T09:02:38-04:00 run_ci: remove monoidal-containers Fixes #21492 MonoidalMap is inlined and used to implement Variables, as before. The top-level value "jobs" is reimplemented as a regular Map, since it doesn't use the monoidal union anyway. - - - - - 64110544 by Cheng Shao at 2022-08-16T09:03:15-04:00 CmmToAsm/AArch64: correct a typo - - - - - f6a5524a by Andreas Klebinger at 2022-08-16T14:34:11-04:00 Fix #21979 - compact-share failing with -O I don't have good reason to believe the optimization level should affect if sharing works or not here. So limit the test to the normal way. - - - - - 68154a9d by Ben Gamari at 2022-08-16T14:34:47-04:00 users-guide: Fix reference to dead llvm-version substitution Fixes #22052. - - - - - 28c60d26 by Ben Gamari at 2022-08-16T14:34:47-04:00 users-guide: Fix incorrect reference to `:extension: role - - - - - 71102c8f by Ben Gamari at 2022-08-16T14:34:47-04:00 users-guide: Add :ghc-flag: reference - - - - - 385f420b by Ben Gamari at 2022-08-16T14:34:47-04:00 hadrian: Place manpage in docroot This relocates it from docs/ to doc/ - - - - - 84598f2e by Ben Gamari at 2022-08-16T14:34:47-04:00 Bump haddock submodule Includes merge of `main` into `ghc-head` as well as some Haddock users guide fixes. - - - - - 59ce787c by Ben Gamari at 2022-08-16T14:34:47-04:00 base: Add changelog entries from ghc-9.2 Closes #21922. - - - - - a14e6ae3 by Ben Gamari at 2022-08-16T14:34:47-04:00 relnotes: Add "included libraries" section As noted in #21988, some users rely on this. - - - - - a4212edc by Ben Gamari at 2022-08-16T14:34:47-04:00 users-guide: Rephrase the rewrite rule documentation Previously the wording was a tad unclear. Fix this. Closes #21114. - - - - - 3e493dfd by Peter Becich at 2022-08-17T08:43:21+01:00 Implement Response File support for HPC This is an improvement to HPC authored by Richard Wallace (https://github.com/purefn) and myself. I have received permission from him to attempt to upstream it. This improvement was originally implemented as a patch to HPC via input-output-hk/haskell.nix: https://github.com/input-output-hk/haskell.nix/pull/1464 Paraphrasing Richard, HPC currently requires all inputs as command line arguments. With large projects this can result in an argument list too long error. I have only seen this error in Nix, but I assume it can occur is a plain Unix environment. This MR adds the standard response file syntax support to HPC. For example you can now pass a file to the command line which contains the arguments. ``` hpc @response_file_1 @response_file_2 ... The contents of a Response File must have this format: COMMAND ... example: report my_library.tix --include=ModuleA --include=ModuleB ``` Updates hpc submodule Co-authored-by: Richard Wallace <rwallace at thewallacepack.net> Fixes #22050 - - - - - 436867d6 by Matthew Pickering at 2022-08-18T09:24:08-04:00 ghc-heap: Fix decoding of TSO closures An extra field was added to the TSO structure in 6d1700b6 but the decoding logic in ghc-heap was not updated for this new field. Fixes #22046 - - - - - a740a4c5 by Matthew Pickering at 2022-08-18T09:24:44-04:00 driver: Honour -x option The -x option is used to manually specify which phase a file should be started to be compiled from (even if it lacks the correct extension). I just failed to implement this when refactoring the driver. In particular Cabal calls GHC with `-E -cpp -x hs Foo.cpphs` to preprocess source files using GHC. I added a test to exercise this case. Fixes #22044 - - - - - e293029d by Simon Peyton Jones at 2022-08-18T09:25:19-04:00 Be more careful in chooseInferredQuantifiers This fixes #22065. We were failing to retain a quantifier that was mentioned in the kind of another retained quantifier. Easy to fix. - - - - - 714c936f by Bryan Richter at 2022-08-18T18:37:21-04:00 testsuite: Add test for #21583 - - - - - 989b844d by Ben Gamari at 2022-08-18T18:37:57-04:00 compiler: Drop --build-id=none hack Since 2011 the object-joining implementation has had a hack to pass `--build-id=none` to `ld` when supported, seemingly to work around a linker bug. This hack is now unnecessary and may break downstream users who expect objects to have valid build-ids. Remove it. Closes #22060. - - - - - 519c712e by Matthew Pickering at 2022-08-19T00:09:11-04:00 Make ru_fn field strict to avoid retaining Ids It's better to perform this projection from Id to Name strictly so we don't retain an old Id (hence IdInfo, hence Unfolding, hence everything etc) - - - - - 7dda04b0 by Matthew Pickering at 2022-08-19T00:09:11-04:00 Force `getOccFS bndr` to avoid retaining reference to Bndr. This is another symptom of #19619 - - - - - 4303acba by Matthew Pickering at 2022-08-19T00:09:11-04:00 Force unfoldings when they are cleaned-up in Tidy and CorePrep If these thunks are not forced then the entire unfolding for the binding is live throughout the whole of CodeGen despite the fact it should have been discarded. Fixes #22071 - - - - - 2361b3bc by Matthew Pickering at 2022-08-19T00:09:47-04:00 haddock docs: Fix links from identifiers to dependent packages When implementing the base_url changes I made the pretty bad mistake of zipping together two lists which were in different orders. The simpler thing to do is just modify `haddockDependencies` to also return the package identifier so that everything stays in sync. Fixes #22001 - - - - - 9a7e2ea1 by Matthew Pickering at 2022-08-19T00:10:23-04:00 Revert "Refactor SpecConstr to use treat bindings uniformly" This reverts commit 415468fef8a3e9181b7eca86de0e05c0cce31729. This refactoring introduced quite a severe residency regression (900MB live from 650MB live when compiling mmark), see #21993 for a reproducer and more discussion. Ticket #21993 - - - - - 9789e845 by Zachary Wood at 2022-08-19T14:17:28-04:00 tc: warn about lazy annotations on unlifted arguments (fixes #21951) - - - - - e5567289 by Andreas Klebinger at 2022-08-19T14:18:03-04:00 Fix #22048 where we failed to drop rules for -fomit-interface-pragmas. Now we also filter the local rules (again) which fixes the issue. - - - - - 51ffd009 by Swann Moreau at 2022-08-19T18:29:21-04:00 Print constraints in quotes (#21167) This patch improves the uniformity of error message formatting by printing constraints in quotes, as we do for types. Fix #21167 - - - - - ab3e0f5a by Sasha Bogicevic at 2022-08-19T18:29:57-04:00 19217 Implicitly quantify type variables in :kind command - - - - - 9939e95f by MorrowM at 2022-08-21T16:51:38-04:00 Recognize file-header pragmas in GHCi (#21507) - - - - - fb7c2d99 by Matthew Pickering at 2022-08-21T16:52:13-04:00 hadrian: Fix bootstrapping with ghc-9.4 The error was that we were trying to link together containers from boot package library (which depends template-haskell in boot package library) template-haskell from in-tree package database So the fix is to build containers in stage0 (and link against template-haskell built in stage0). Fixes #21981 - - - - - b946232c by Mario Blažević at 2022-08-22T22:06:21-04:00 Added pprType with precedence argument, as a prerequisite to fix issues #21723 and #21942. * refines the precedence levels, adding `qualPrec` and `funPrec` to better control parenthesization * `pprParendType`, `pprFunArgType`, and `instance Ppr Type` all just call `pprType` with proper precedence * `ParensT` constructor is now always printed parenthesized * adds the precedence argument to `pprTyApp` as well, as it needs to keep track and pass it down * using `>=` instead of former `>` to match the Core type printing logic * some test outputs have changed, losing extraneous parentheses - - - - - fe4ff0f7 by Mario Blažević at 2022-08-22T22:06:21-04:00 Fix and test for issue #21723 - - - - - 33968354 by Mario Blažević at 2022-08-22T22:06:21-04:00 Test for issue #21942 - - - - - c9655251 by Mario Blažević at 2022-08-22T22:06:21-04:00 Updated the changelog - - - - - 80102356 by Ben Gamari at 2022-08-22T22:06:57-04:00 hadrian: Don't duplicate binaries on installation Previously we used `install` on symbolic links, which ended up copying the target file rather than installing a symbolic link. Fixes #22062. - - - - - b929063e by Matthew Farkas-Dyck at 2022-08-24T02:37:01-04:00 Unbreak Haddock comments in `GHC.Core.Opt.WorkWrap.Utils`. Closes #22092. - - - - - 112e4f9c by Cheng Shao at 2022-08-24T02:37:38-04:00 driver: don't actually merge objects when ar -L works - - - - - a9f0e68e by Ben Gamari at 2022-08-24T02:38:13-04:00 rts: Consistently use MiB in stats output Previously we would say `MB` even where we meant `MiB`. - - - - - a90298cc by Simon Peyton Jones at 2022-08-25T08:38:16+01:00 Fix arityType: -fpedantic-bottoms, join points, etc This MR fixes #21694, #21755. It also makes sure that #21948 and fix to #21694. * For #21694 the underlying problem was that we were calling arityType on an expression that had free join points. This is a Bad Bad Idea. See Note [No free join points in arityType]. * To make "no free join points in arityType" work out I had to avoid trying to use eta-expansion for runRW#. This entailed a few changes in the Simplifier's treatment of runRW#. See GHC.Core.Opt.Simplify.Iteration Note [No eta-expansion in runRW#] * I also made andArityType work correctly with -fpedantic-bottoms; see Note [Combining case branches: andWithTail]. * Rewrote Note [Combining case branches: optimistic one-shot-ness] * arityType previously treated join points differently to other let-bindings. This patch makes them unform; arityType analyses the RHS of all bindings to get its ArityType, and extends am_sigs. I realised that, now we have am_sigs giving the ArityType for let-bound Ids, we don't need the (pre-dating) special code in arityType for join points. But instead we need to extend the env for Rec bindings, which weren't doing before. More uniform now. See Note [arityType for let-bindings]. This meant we could get rid of ae_joins, and in fact get rid of EtaExpandArity altogether. Simpler. * And finally, it was the strange treatment of join-point Ids in arityType (involving a fake ABot type) that led to a serious bug: #21755. Fixed by this refactoring, which treats them uniformly; but without breaking #18328. In fact, the arity for recursive join bindings is pretty tricky; see the long Note [Arity for recursive join bindings] in GHC.Core.Opt.Simplify.Utils. That led to more refactoring, including deciding that an Id could have an Arity that is bigger than its JoinArity; see Note [Invariants on join points], item 2(b) in GHC.Core * Make sure that the "demand threshold" for join points in DmdAnal is no bigger than the join-arity. In GHC.Core.Opt.DmdAnal see Note [Demand signatures are computed for a threshold arity based on idArity] * I moved GHC.Core.Utils.exprIsDeadEnd into GHC.Core.Opt.Arity, where it more properly belongs. * Remove an old, redundant hack in FloatOut. The old Note was Note [Bottoming floats: eta expansion] in GHC.Core.Opt.SetLevels. Compile time improves very slightly on average: Metrics: compile_time/bytes allocated --------------------------------------------------------------------------------------- T18223(normal) ghc/alloc 725,808,720 747,839,216 +3.0% BAD T6048(optasm) ghc/alloc 105,006,104 101,599,472 -3.2% GOOD geo. mean -0.2% minimum -3.2% maximum +3.0% For some reason Windows was better T10421(normal) ghc/alloc 125,888,360 124,129,168 -1.4% GOOD T18140(normal) ghc/alloc 85,974,520 83,884,224 -2.4% GOOD T18698b(normal) ghc/alloc 236,764,568 234,077,288 -1.1% GOOD T18923(normal) ghc/alloc 75,660,528 73,994,512 -2.2% GOOD T6048(optasm) ghc/alloc 112,232,512 108,182,520 -3.6% GOOD geo. mean -0.6% I had a quick look at T18223 but it is knee deep in coercions and the size of everything looks similar before and after. I decided to accept that 3% increase in exchange for goodness elsewhere. Metric Decrease: T10421 T18140 T18698b T18923 T6048 Metric Increase: T18223 - - - - - 909edcfc by Ben Gamari at 2022-08-25T10:03:34-04:00 upload_ghc_libs: Add means of passing Hackage credentials - - - - - 28402eed by M Farkas-Dyck at 2022-08-25T10:04:17-04:00 Scrub some partiality in `CommonBlockElim`. - - - - - 54affbfa by Ben Gamari at 2022-08-25T20:05:31-04:00 hadrian: Fix whitespace Previously this region of Settings.Packages was incorrectly indented. - - - - - c4bba0f0 by Ben Gamari at 2022-08-25T20:05:31-04:00 validate: Drop --legacy flag In preparation for removal of the legacy `make`-based build system. - - - - - 822b0302 by Ben Gamari at 2022-08-25T20:05:31-04:00 gitlab-ci: Drop make build validation jobs In preparation for removal of the `make`-based build system - - - - - 6fd9b0a1 by Ben Gamari at 2022-08-25T20:05:31-04:00 Drop make build system Here we at long last remove the `make`-based build system, it having been replaced with the Shake-based Hadrian build system. Users are encouraged to refer to the documentation in `hadrian/doc` and this [1] blog post for details on using Hadrian. Closes #17527. [1] https://www.haskell.org/ghc/blog/20220805-make-to-hadrian.html - - - - - dbb004b0 by Ben Gamari at 2022-08-25T20:05:31-04:00 Remove testsuite/tests/perf/haddock/.gitignore As noted in #16802, this is no longer needed. Closes #16802. - - - - - fe9d824d by Ben Gamari at 2022-08-25T20:05:31-04:00 Drop hc-build script This has not worked for many, many years and relied on the now-removed `make`-based build system. - - - - - 659502bc by Ben Gamari at 2022-08-25T20:05:31-04:00 Drop mkdirhier This is only used by nofib's dead `dist` target - - - - - 4a426924 by Ben Gamari at 2022-08-25T20:05:31-04:00 Drop mk/{build,install,config}.mk.in - - - - - 46924b75 by Ben Gamari at 2022-08-25T20:05:31-04:00 compiler: Drop comment references to make - - - - - d387f687 by Harry Garrood at 2022-08-25T20:06:10-04:00 Add inits1 and tails1 to Data.List.NonEmpty See https://github.com/haskell/core-libraries-committee/issues/67 - - - - - 8603c921 by Harry Garrood at 2022-08-25T20:06:10-04:00 Add since annotations and changelog entries - - - - - 6b47aa1c by Krzysztof Gogolewski at 2022-08-25T20:06:46-04:00 Fix redundant import This fixes a build error on x86_64-linux-alpine3_12-validate. See the function 'loadExternalPlugins' defined in this file. - - - - - 4786acf7 by sheaf at 2022-08-26T15:05:23-04:00 Pmc: consider any 2 dicts of the same type equal This patch massages the keys used in the `TmOracle` `CoreMap` to ensure that dictionaries of coherent classes give the same key. That is, whenever we have an expression we want to insert or lookup in the `TmOracle` `CoreMap`, we first replace any dictionary `$dict_abcd :: ct` with a value of the form `error @ct`. This allows us to common-up view pattern functions with required constraints whose arguments differed only in the uniques of the dictionaries they were provided, thus fixing #21662. This is a rather ad-hoc change to the keys used in the `TmOracle` `CoreMap`. In the long run, we would probably want to use a different representation for the keys instead of simply using `CoreExpr` as-is. This more ambitious plan is outlined in #19272. Fixes #21662 Updates unix submodule - - - - - f5e0f086 by Krzysztof Gogolewski at 2022-08-26T15:06:01-04:00 Remove label style from printing context Previously, the SDocContext used for code generation contained information whether the labels should use Asm or C style. However, at every individual call site, this is known statically. This removes the parameter to 'PprCode' and replaces every 'pdoc' used to print a label in code style with 'pprCLabel' or 'pprAsmLabel'. The OutputableP instance is now used only for dumps. The output of T15155 changes, it now uses the Asm style (which is faithful to what actually happens). - - - - - 1007829b by Cheng Shao at 2022-08-26T15:06:40-04:00 boot: cleanup legacy args Cleanup legacy boot script args, following removal of the legacy make build system. - - - - - 95fe09da by Simon Peyton Jones at 2022-08-27T00:29:02-04:00 Improve SpecConstr for evals As #21763 showed, we were over-specialising in some cases, when the function involved was doing a simple 'eval', but not taking the value apart, or branching on it. This MR fixes the problem. See Note [Do not specialise evals]. Nofib barely budges, except that spectral/cichelli allocates about 3% less. Compiler bytes-allocated improves a bit geo. mean -0.1% minimum -0.5% maximum +0.0% The -0.5% is on T11303b, for what it's worth. - - - - - 565a8ec8 by Matthew Pickering at 2022-08-27T00:29:39-04:00 Revert "Revert "Refactor SpecConstr to use treat bindings uniformly"" This reverts commit 851d8dd89a7955864b66a3da8b25f1dd88a503f8. This commit was originally reverted due to an increase in space usage. This was diagnosed as because the SCE increased in size and that was being retained by another leak. See #22102 - - - - - 82ce1654 by Matthew Pickering at 2022-08-27T00:29:39-04:00 Avoid retaining bindings via ModGuts held on the stack It's better to overwrite the bindings fields of the ModGuts before starting an iteration as then all the old bindings can be collected as soon as the simplifier has processed them. Otherwise we end up with the old bindings being alive until right at the end of the simplifier pass as the mg_binds field is only modified right at the end. - - - - - 64779dcd by Matthew Pickering at 2022-08-27T00:29:39-04:00 Force imposs_deflt_cons in filterAlts This fixes a pretty serious space leak as the forced thunk would retain `Alt b` values which would then contain reference to a lot of old bindings and other simplifier gunk. The OtherCon unfolding was not forced on subsequent simplifier runs so more and more old stuff would be retained until the end of simplification. Fixing this has a drastic effect on maximum residency for the mmark package which goes from ``` 45,005,401,056 bytes allocated in the heap 17,227,721,856 bytes copied during GC 818,281,720 bytes maximum residency (33 sample(s)) 9,659,144 bytes maximum slop 2245 MiB total memory in use (0 MB lost due to fragmentation) ``` to ``` 45,039,453,304 bytes allocated in the heap 13,128,181,400 bytes copied during GC 331,546,608 bytes maximum residency (40 sample(s)) 7,471,120 bytes maximum slop 916 MiB total memory in use (0 MB lost due to fragmentation) ``` See #21993 for some more discussion. - - - - - a3b23a33 by Matthew Pickering at 2022-08-27T00:29:39-04:00 Use Solo to avoid retaining the SCE but to avoid performing the substitution The use of Solo here allows us to force the selection into the SCE to obtain the Subst but without forcing the substitution to be applied. The resulting thunk is placed into a lazy field which is rarely forced, so forcing it regresses peformance. - - - - - 161a6f1f by Simon Peyton Jones at 2022-08-27T00:30:14-04:00 Fix a nasty loop in Tidy As the remarkably-simple #22112 showed, we were making a black hole in the unfolding of a self-recursive binding. Boo! It's a bit tricky. Documented in GHC.Iface.Tidy, Note [tidyTopUnfolding: avoiding black holes] - - - - - 68e6786f by Giles Anderson at 2022-08-29T00:01:35+02:00 Use TcRnDiagnostic in GHC.Tc.TyCl.Class (#20117) The following `TcRnDiagnostic` messages have been introduced: TcRnIllegalHsigDefaultMethods TcRnBadGenericMethod TcRnWarningMinimalDefIncomplete TcRnDefaultMethodForPragmaLacksBinding TcRnIgnoreSpecialisePragmaOnDefMethod TcRnBadMethodErr TcRnNoExplicitAssocTypeOrDefaultDeclaration - - - - - cbe51ac5 by Simon Peyton Jones at 2022-08-29T04:18:57-04:00 Fix a bug in anyInRnEnvR This bug was a subtle error in anyInRnEnvR, introduced by commit d4d3fe6e02c0eb2117dbbc9df72ae394edf50f06 Author: Andreas Klebinger <klebinger.andreas at gmx.at> Date: Sat Jul 9 01:19:52 2022 +0200 Rule matching: Don't compute the FVs if we don't look at them. The net result was #22028, where a rewrite rule would wrongly match on a lambda. The fix to that function is easy. - - - - - 0154bc80 by sheaf at 2022-08-30T06:05:41-04:00 Various Hadrian bootstrapping fixes - Don't always produce a distribution archive (#21629) - Use correct executable names for ghc-pkg and hsc2hs on windows (we were missing the .exe file extension) - Fix a bug where we weren't using the right archive format on Windows when unpacking the bootstrap sources. Fixes #21629 - - - - - 451b1d90 by Matthew Pickering at 2022-08-30T06:06:16-04:00 ci: Attempt using normal submodule cloning strategy We do not use any recursively cloned submodules, and this protects us from flaky upstream remotes. Fixes #22121 - - - - - 9d5ad7c4 by Pi Delport at 2022-08-30T22:40:46+00:00 Fix typo in Any docs: stray "--" - - - - - 3a002632 by Pi Delport at 2022-08-30T22:40:46+00:00 Fix typo in Any docs: syntatic -> syntactic - - - - - 7f490b13 by Simon Peyton Jones at 2022-08-31T03:53:54-04:00 Add a missing trimArityType This buglet was exposed by #22114, a consequence of my earlier refactoring of arity for join points. - - - - - e6fc820f by Ben Gamari at 2022-08-31T13:16:01+01:00 Bump binary submodule to 0.8.9.1 - - - - - 4c1e7b22 by Ben Gamari at 2022-08-31T13:16:01+01:00 Bump stm submodule to 2.5.1.0 - - - - - 837472b4 by Ben Gamari at 2022-08-31T13:16:01+01:00 users-guide: Document system-cxx-std-lib - - - - - f7a9947a by Douglas Wilson at 2022-08-31T13:16:01+01:00 Update submodule containers to 0.6.6 - - - - - 4ab1c2ca by Douglas Wilson at 2022-08-31T13:16:02+01:00 Update submodule process to 1.6.15.0 - - - - - 1309ea1e by Ben Gamari at 2022-08-31T13:16:02+01:00 Bump directory submodule to 1.3.7.1 - - - - - 7962a33a by Douglas Wilson at 2022-08-31T13:16:02+01:00 Bump text submodule to 2.0.1 - - - - - fd8d80c3 by Ben Gamari at 2022-08-31T13:26:52+01:00 Bump deepseq submodule to 1.4.8.0 - - - - - a9baafac by Ben Gamari at 2022-08-31T13:26:52+01:00 Add dates to base, ghc-prim changelogs - - - - - 2cee323c by Ben Gamari at 2022-08-31T13:26:52+01:00 Update autoconf scripts Scripts taken from autoconf 02ba26b218d3d3db6c56e014655faf463cefa983 - - - - - e62705ff by Ben Gamari at 2022-08-31T13:26:53+01:00 Bump bytestring submodule to 0.11.3.1 - - - - - f7b4dcbd by Douglas Wilson at 2022-08-31T13:26:53+01:00 Update submodule Cabal to tag Cabal-v3.8.1.0 closes #21931 - - - - - e8eaf807 by Matthew Pickering at 2022-08-31T18:27:57-04:00 Refine in-tree compiler args for --test-compiler=stage1 Some of the logic to calculate in-tree arguments was not correct for the stage1 compiler. Namely we were not correctly reporting whether we were building static or dynamic executables and whether debug assertions were enabled. Fixes #22096 - - - - - 6b2f7ffe by Matthew Pickering at 2022-08-31T18:27:57-04:00 Make ghcDebugAssertions into a Stage predicate (Stage -> Bool) We also care whether we have debug assertions enabled for a stage one compiler, but the way which we turned on the assertions was quite different from the stage2 compiler. This makes the logic for turning on consistent across both and has the advantage of being able to correct determine in in-tree args whether a flavour enables assertions or not. Ticket #22096 - - - - - 15111af6 by Zubin Duggal at 2022-09-01T01:18:50-04:00 Add regression test for #21550 This was fixed by ca90ffa321a31842a32be1b5b6e26743cd677ec5 "Use local instances with least superclass depth" - - - - - 7d3a055d by Krzysztof Gogolewski at 2022-09-01T01:19:26-04:00 Minor cleanup - Remove mkHeteroCoercionType, sdocImpredicativeTypes, isStateType (unused), isCoVar_maybe (duplicated by getCoVar_maybe) - Replace a few occurrences of voidPrimId with (# #). void# is a deprecated synonym for the unboxed tuple. - Use showSDoc in :show linker. This makes it consistent with the other :show commands - - - - - 31a8989a by Tommy Bidne at 2022-09-01T12:01:20-04:00 Change Ord defaults per CLC proposal Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/24#issuecomment-1233331267 - - - - - 7f527f01 by Matthew Pickering at 2022-09-01T12:01:56-04:00 Fix bootstrap with ghc-9.0 It turns out Solo is a very recent addition to base, so for older GHC versions we just defined it inline here the one place we use it in the compiler. - - - - - d2be80fd by Sebastian Graf at 2022-09-05T23:12:14-04:00 DmdAnal: Don't panic in addCaseBndrDmd (#22039) Rather conservatively return Top. See Note [Untyped demand on case-alternative binders]. I also factored `addCaseBndrDmd` into two separate functions `scrutSubDmd` and `fieldBndrDmds`. Fixes #22039. - - - - - 25f68ace by Ben Gamari at 2022-09-05T23:12:50-04:00 gitlab-ci: Ensure that ghc derivation is in scope Previously the lint-ci job attempted to use cabal-install (specifically `cabal update`) without a GHC in PATH. However, cabal-install-3.8 appears to want GHC, even for `cabal update`. - - - - - f37b621f by sheaf at 2022-09-06T11:51:53+00:00 Update instances.rst, clarifying InstanceSigs Fixes #22103 - - - - - d4f908f7 by Jan Hrček at 2022-09-06T15:36:58-04:00 Fix :add docs in user guide - - - - - 808bb793 by Cheng Shao at 2022-09-06T15:37:35-04:00 ci: remove unused build_make/test_make in ci script - - - - - d0a2efb2 by Eric Lindblad at 2022-09-07T16:42:45-04:00 typo - - - - - fac0098b by Eric Lindblad at 2022-09-07T16:42:45-04:00 typos - - - - - a581186f by Eric Lindblad at 2022-09-07T16:42:45-04:00 whitespace - - - - - 04a738cb by Cheng Shao at 2022-09-07T16:43:22-04:00 CmmToAsm: remove unused ModLocation from NatM_State - - - - - ee1cfaa9 by Krzysztof Gogolewski at 2022-09-07T16:43:58-04:00 Minor SDoc cleanup Change calls to renderWithContext with showSDocOneLine; it's more efficient and explanatory. Remove polyPatSig (unused) - - - - - 7918265d by Krzysztof Gogolewski at 2022-09-07T16:43:58-04:00 Remove Outputable Char instance Use 'text' instead of 'ppr'. Using 'ppr' on the list "hello" rendered as "h,e,l,l,o". - - - - - 77209ab3 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00 Export liftA2 from Prelude Changes: In order to be warning free and compatible, we hide Applicative(..) from Prelude in a few places and instead import it directly from Control.Applicative. Please see the migration guide at https://github.com/haskell/core-libraries-committee/blob/main/guides/export-lifta2-prelude.md for more details. This means that Applicative is now exported in its entirety from Prelude. Motivation: This change is motivated by a few things: * liftA2 is an often used function, even more so than (<*>) for some people. * When implementing Applicative, the compiler will prompt you for either an implementation of (<*>) or of liftA2, but trying to use the latter ends with an error, without further imports. This could be confusing for newbies. * For teaching, it is often times easier to introduce liftA2 first, as it is a natural generalisation of fmap. * This change seems to have been unanimously and enthusiastically accepted by the CLC members, possibly indicating a lot of love for it. * This change causes very limited breakage, see the linked issue below for an investigation on this. See https://github.com/haskell/core-libraries-committee/issues/50 for the surrounding discussion and more details. - - - - - 442a94e8 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00 Add changelog entry for liftA2 export from Prelude - - - - - fb968680 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00 Bump submodule containers to one with liftA2 warnings fixed - - - - - f54ff818 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00 Bump submodule Cabal to one with liftA2 warnings fixed - - - - - a4b34808 by Georgi Lyubenov at 2022-09-08T17:14:36+03:00 Isolate some Applicative hidings to GHC.Prelude By reexporting the entirety of Applicative from GHC.Prelude, we can save ourselves some `hiding` and importing of `Applicative` in consumers of GHC.Prelude. This also has the benefit of isolating this type of change to GHC.Prelude, so that people in the future don't have to think about it. - - - - - 9c4ea90c by Cheng Shao at 2022-09-08T17:49:47-04:00 CmmToC: enable 64-bit CallishMachOp on 32-bit targets Normally, the unregisterised builds avoid generating 64-bit CallishMachOp in StgToCmm, so CmmToC doesn't support these. However, there do exist cases where we'd like to invoke cmmToC for other cmm inputs which may contain such CallishMachOps, and it's a rather low effort to add support for these since they only require calling into existing ghc-prim cbits. - - - - - 04062510 by Alexis King at 2022-09-11T11:30:32+02:00 Add native delimited continuations to the RTS This patch implements GHC proposal 313, "Delimited continuation primops", by adding native support for delimited continuations to the GHC RTS. All things considered, the patch is relatively small. It almost exclusively consists of changes to the RTS; the compiler itself is essentially unaffected. The primops come with fairly extensive Haddock documentation, and an overview of the implementation strategy is given in the Notes in rts/Continuation.c. This first stab at the implementation prioritizes simplicity over performance. Most notably, every continuation is always stored as a single, contiguous chunk of stack. If one of these chunks is particularly large, it can result in poor performance, as the current implementation does not attempt to cleverly squeeze a subset of the stack frames into the existing stack: it must fit all at once. If this proves to be a performance issue in practice, a cleverer strategy would be a worthwhile target for future improvements. - - - - - ee471dfb by Cheng Shao at 2022-09-12T07:07:33-04:00 rts: fix missing dirty_MVAR argument in stg_writeIOPortzh - - - - - a5f9c35f by Cheng Shao at 2022-09-12T13:29:05-04:00 ci: enable parallel compression for xz - - - - - 3a815f30 by Ryan Scott at 2022-09-12T13:29:41-04:00 Windows: Always define _UCRT when compiling C code As seen in #22159, this is required to ensure correct behavior when MinGW-w64 headers are in the `C_INCLUDE_PATH`. Fixes #22159. - - - - - 65a0bd69 by sheaf at 2022-09-13T10:27:52-04:00 Add diagnostic codes This MR adds diagnostic codes, assigning unique numeric codes to error and warnings, e.g. error: [GHC-53633] Pattern match is redundant This is achieved as follows: - a type family GhcDiagnosticCode that gives the diagnostic code for each diagnostic constructor, - a type family ConRecursInto that specifies whether to recur into an argument of the constructor to obtain a more fine-grained code (e.g. different error codes for different 'deriving' errors), - generics machinery to generate the value-level function assigning each diagnostic its error code; see Note [Diagnostic codes using generics] in GHC.Types.Error.Codes. The upshot is that, to add a new diagnostic code, contributors only need to modify the two type families mentioned above. All logic relating to diagnostic codes is thus contained to the GHC.Types.Error.Codes module, with no code duplication. This MR also refactors error message datatypes a bit, ensuring we can derive Generic for them, and cleans up the logic around constraint solver reports by splitting up 'TcSolverReportInfo' into separate datatypes (see #20772). Fixes #21684 - - - - - 362cca13 by sheaf at 2022-09-13T10:27:53-04:00 Diagnostic codes: acccept test changes The testsuite output now contains diagnostic codes, so many tests need to be updated at once. We decided it was best to keep the diagnostic codes in the testsuite output, so that contributors don't inadvertently make changes to the diagnostic codes. - - - - - 08f6730c by Adam Gundry at 2022-09-13T10:28:29-04:00 Allow imports to reference multiple fields with the same name (#21625) If a module `M` exports two fields `f` (using DuplicateRecordFields), we can still accept import M (f) import M hiding (f) and treat `f` as referencing both of them. This was accepted in GHC 9.0, but gave rise to an ambiguity error in GHC 9.2. See #21625. This patch also documents this behaviour in the user's guide, and updates the test for #16745 which is now treated differently. - - - - - c14370d7 by Cheng Shao at 2022-09-13T10:29:07-04:00 ci: remove unused appveyor config - - - - - dc6af9ed by Cheng Shao at 2022-09-13T10:29:45-04:00 compiler: remove unused lazy state monad - - - - - 646d15ad by Eric Lindblad at 2022-09-14T03:13:56-04:00 Fix typos This fixes various typos and spelling mistakes in the compiler. Fixes #21891 - - - - - 7d7e71b0 by Matthew Pickering at 2022-09-14T03:14:32-04:00 hadrian: Bump index state This bumps the index state so a build plan can also be found when booting with 9.4. Fixes #22165 - - - - - 98b62871 by Matthew Pickering at 2022-09-14T17:17:04-04:00 hadrian: Use a stamp file to record when a package is built in a certain way Before this patch which library ways we had built wasn't recorded directly. So you would run into issues if you build the .conf file with some library ways before switching the library ways which you wanted to build. Now there is one stamp file for each way, so in order to build a specific way you can need that specific stamp file rather than going indirectly via the .conf file. - - - - - b42cedbe by Matthew Pickering at 2022-09-14T17:17:04-04:00 hadrian: Inplace/Final package databases There are now two different package databases per stage. An inplace package database contains .conf files which point directly into the build directories. The final package database contains .conf files which point into the installed locations. The inplace .conf files are created before any building happens and have fake ABI hash values. The final .conf files are created after a package finished building and contains the proper ABI has. The motivation for this is to make the dependency structure more fine-grained when building modules. Now a module depends just depends directly on M.o from package p rather than the .conf file depend on the .conf file for package p. So when all of a modules direct dependencies have finished building we can start building it rather than waiting for the whole package to finish. The secondary motivation is that the multi-repl doesn't need to build everything before starting the multi-repl session. We can just configure the inplace package-db and use that in order to start the repl. - - - - - 6515c32b by Matthew Pickering at 2022-09-14T17:17:04-04:00 hadrian: Add some more packages to multi-cradle The main improvement here is to pass `-this-unit-id` for executables so that they can be added to the multi-cradle if desired as well as normal library packages. - - - - - e470e91f by Matthew Pickering at 2022-09-14T17:17:04-04:00 hadrian: Need builders needed by Cabal Configure in parallel Because of the use of withStaged (which needs the necessary builder) when configuring a package, the builds of stage1:exe:ghc-bin and stage1:exe:ghc-pkg where being linearised when building a specific target like `binary-dist-dir`. Thankfully the fix is quite local, to supply all the `withStaged` arguments together so the needs can be batched together and hence performed in parallel. Fixes #22093 - - - - - c4438347 by Matthew Pickering at 2022-09-14T17:17:04-04:00 Remove stage1:exe:ghc-bin pre-build from CI script CI builds stage1:exe:ghc-bin before the binary-dist target which introduces some quite bad linearisation (see #22093) because we don't build stage1 compiler in parallel with anything. Then when the binary-dist target is started we have to build stage1:exe:ghc-pkg before doing anything. Fixes #22094 - - - - - 71d8db86 by Matthew Pickering at 2022-09-14T17:17:04-04:00 hadrian: Add extra implicit dependencies from DeriveLift ghc -M should know that modules which use DeriveLift (or TemplateHaskellQuotes) need TH.Lib.Internal but until it does, we have to add these extra edges manually or the modules will be compiled before TH.Lib.Internal is compiled which leads to a desugarer error. - - - - - 43e574f0 by Greg Steuck at 2022-09-14T17:17:43-04:00 Repair c++ probing on OpenBSD Failure without this change: ``` checking C++ standard library flavour... libc++ checking for linkage against 'c++ c++abi'... failed checking for linkage against 'c++ cxxrt'... failed configure: error: Failed to find C++ standard library ``` - - - - - 534b39ee by Douglas Wilson at 2022-09-14T17:18:21-04:00 libraries: template-haskell: vendor filepath differently Vendoring with ../ in hs-source-dirs prevents upload to hackage. (cherry picked from commit 1446be7586ba70f9136496f9b67f792955447842) - - - - - bdd61cd6 by M Farkas-Dyck at 2022-09-14T22:39:34-04:00 Unbreak Hadrian with Cabal 3.8. - - - - - df04d6ec by Krzysztof Gogolewski at 2022-09-14T22:40:09-04:00 Fix typos - - - - - d6ea8356 by Andreas Klebinger at 2022-09-15T10:12:41+02:00 Tag inference: Fix #21954 by retaining tagsigs of vars in function position. For an expression like: case x of y Con z -> z If we also retain the tag sig for z we can generate code to immediately return it rather than calling out to stg_ap_0_fast. - - - - - 7cce7007 by Andreas Klebinger at 2022-09-15T10:12:42+02:00 Stg.InferTags.Rewrite - Avoid some thunks. - - - - - af0ff3a4 by M Farkas-Dyck at 2022-09-15T21:16:05+00:00 Disuse `mapLoc`. - - - - - 88c4cbdb by Cheng Shao at 2022-09-16T13:57:56-04:00 hadrian: enable -fprof-late only for profiling ways - - - - - d7235831 by Cheng Shao at 2022-09-16T13:57:56-04:00 hadrian: add late_ccs flavour transformer - - - - - ce203753 by Cheng Shao at 2022-09-16T13:58:34-04:00 configure: remove unused program checks - - - - - 9b4c1056 by Pierre Le Marre at 2022-09-16T13:59:16-04:00 Update to Unicode 15.0 - - - - - c6e9b89a by Andrew Lelechenko at 2022-09-16T13:59:55-04:00 Avoid partial head and tail in ghc-heap; replace with total pattern-matching - - - - - 616afde3 by Cheng Shao at 2022-09-16T14:00:33-04:00 hadrian: relax Cabal upper bound to allow building with Cabal-3.8 A follow up of !8910. - - - - - df35d994 by Alexis King at 2022-09-16T14:01:11-04:00 Add links to the continuations haddocks in the docs for each primop fixes #22176 - - - - - 383f7549 by Matthew Pickering at 2022-09-16T21:42:10-04:00 -Wunused-pattern-binds: Recurse into patterns to check whether there's a splice See the examples in #22057 which show we have to traverse deeply into a pattern to determine whether it contains a splice or not. The original implementation pointed this out but deemed this very shallow traversal "too expensive". Fixes #22057 I also fixed an oversight in !7821 which meant we lost a warning which was present in 9.2.2. Fixes #22067 - - - - - 5031bf49 by sheaf at 2022-09-16T21:42:49-04:00 Hadrian: Don't try to build terminfo on Windows Commit b42cedbe introduced a dependency on terminfo on Windows, but that package isn't available on Windows. - - - - - a748fc38 by Matthew Farkas-Dyck at 2022-09-17T10:44:18+00:00 Scrub partiality about `NewOrData`. - - - - - c9afe221 by M Farkas-Dyck at 2022-09-17T06:44:47-04:00 Clean up some. In particular: • Delete some dead code, largely under `GHC.Utils`. • Clean up a few definitions in `GHC.Utils.(Misc, Monad)`. • Clean up `GHC.Types.SrcLoc`. • Derive stock `Functor, Foldable, Traversable` for more types. • Derive more instances for newtypes. Bump haddock submodule. - - - - - 85431ac3 by Cheng Shao at 2022-09-17T06:45:25-04:00 driver: pass original Cmm filename in ModLocation When compiling Cmm, the ml_hs_file field is used to indicate Cmm filename when later generating DWARF information. We should pass the original filename here, otherwise for preprocessed Cmm files, the filename will be a temporary filename which is confusing. - - - - - 63aa0069 by Cheng Shao at 2022-09-17T06:46:04-04:00 rts: remove legacy logging cabal flag - - - - - bd0f4184 by Cheng Shao at 2022-09-17T06:46:04-04:00 rts: make threaded ways optional For certain targets (e.g. wasm32-wasi), the threaded rts is known not to work. This patch adds a "threaded" cabal flag to rts to make threaded rts ways optional. Hadrian enables this flag iff the flavour rtsWays contains threaded ways. - - - - - 2758fb6c by John Ericson at 2022-09-18T03:27:37+02:00 Test output changed because of change to `base` Spooky, but I guess that is intended? - - - - - 8a666ad2 by Ryan Scott at 2022-09-18T08:00:44-04:00 DeriveFunctor: Check for last type variables using dataConUnivTyVars Previously, derived instances of `Functor` (as well as the related classes `Foldable`, `Traversable`, and `Generic1`) would determine which constraints to infer by checking for fields that contain the last type variable. The problem was that this last type variable was taken from `tyConTyVars`. For GADTs, the type variables in each data constructor are _not_ the same type variables as in `tyConTyVars`, leading to #22167. This fixes the issue by instead checking for the last type variable using `dataConUnivTyVars`. (This is very similar in spirit to the fix for #21185, which also replaced an errant use of `tyConTyVars` with type variables from each data constructor.) Fixes #22167. - - - - - 78037167 by Vladislav Zavialov at 2022-09-18T08:01:20-04:00 Lexer: pass updated buffer to actions (#22201) In the lexer, predicates have the following type: { ... } :: user -- predicate state -> AlexInput -- input stream before the token -> Int -- length of the token -> AlexInput -- input stream after the token -> Bool -- True <=> accept the token This is documented in the Alex manual. There is access to the input stream both before and after the token. But when the time comes to construct the token, GHC passes only the initial string buffer to the lexer action. This patch fixes it: - type Action = PsSpan -> StringBuffer -> Int -> P (PsLocated Token) + type Action = PsSpan -> StringBuffer -> Int -> StringBuffer -> P (PsLocated Token) Now lexer actions have access to the string buffer both before and after the token, just like the predicates. It's just a matter of passing an additional function parameter throughout the lexer. - - - - - 75746594 by Vladislav Zavialov at 2022-09-18T08:01:20-04:00 Lexer: define varsym without predicates (#22201) Before this patch, the varsym lexing rules were defined as follows: <0> { @varsym / { precededByClosingToken `alexAndPred` followedByOpeningToken } { varsym_tight_infix } @varsym / { followedByOpeningToken } { varsym_prefix } @varsym / { precededByClosingToken } { varsym_suffix } @varsym { varsym_loose_infix } } Unfortunately, this meant that the predicates 'precededByClosingToken' and 'followedByOpeningToken' were recomputed several times before we could figure out the whitespace context. With this patch, we check for whitespace context directly in the lexer action: <0> { @varsym { with_op_ws varsym } } The checking for opening/closing tokens happens in 'with_op_ws' now, which is part of the lexer action rather than the lexer predicate. - - - - - c1f81b38 by Matthew Farkas-Dyck at 2022-09-19T09:07:05-04:00 Scrub partiality about `NewOrData`. Rather than a list of constructors and a `NewOrData` flag, we define `data DataDefnCons a = NewTypeCon a | DataTypeCons [a]`, which enforces a newtype to have exactly one constructor. Closes #22070. Bump haddock submodule. - - - - - 1e1ed8c5 by Cheng Shao at 2022-09-19T09:07:43-04:00 CmmToC: emit __builtin_unreachable() after noreturn ccalls Emit a __builtin_unreachable() call after a foreign call marked as CmmNeverReturns. This is crucial to generate correctly typed code for wasm; as for other archs, this is also beneficial for the C compiler optimizations. - - - - - 19f45a25 by Jan Hrček at 2022-09-20T03:49:29-04:00 Document :unadd GHCi command in user guide - - - - - 545ff490 by sheaf at 2022-09-20T03:50:06-04:00 Hadrian: merge archives even in stage 0 We now always merge .a archives when ar supports -L. This change is necessary in order to bootstrap GHC using GHC 9.4 on Windows, as nested archives aren't supported. Not doing so triggered bug #21990 when trying to use the Win32 package, with errors such as: Not a x86_64 PE+ file. Unknown COFF 4 type in getHeaderInfo. ld.lld: error: undefined symbol: Win32zm2zi12zi0zi0_SystemziWin32ziConsoleziCtrlHandler_withConsoleCtrlHandler1_info We have to be careful about which ar is meant: in stage 0, the check should be done on the system ar (system-ar in system.config). - - - - - 59fe128c by Vladislav Zavialov at 2022-09-20T03:50:42-04:00 Fix -Woperator-whitespace for consym (part of #19372) Due to an oversight, the initial specification and implementation of -Woperator-whitespace focused on varsym exclusively and completely ignored consym. This meant that expressions such as "x+ y" would produce a warning, while "x:+ y" would not. The specification was corrected in ghc-proposals pull request #404, and this patch updates the implementation accordingly. Regression test included. - - - - - c4c2cca0 by John Ericson at 2022-09-20T13:11:49-04:00 Add `Eq` and `Ord` instances for `Generically1` These are needed so the subsequent commit overhauling the `*1` classes type-checks. - - - - - 7beb356e by John Ericson at 2022-09-20T13:11:50-04:00 Relax instances for Functor combinators; put superclass on Class1 and Class2 to make non-breaking This change is approved by the Core Libraries commitee in https://github.com/haskell/core-libraries-committee/issues/10 The first change makes the `Eq`, `Ord`, `Show`, and `Read` instances for `Sum`, `Product`, and `Compose` match those for `:+:`, `:*:`, and `:.:`. These have the proper flexible contexts that are exactly what the instance needs: For example, instead of ```haskell instance (Eq1 f, Eq1 g, Eq a) => Eq (Compose f g a) where (==) = eq1 ``` we do ```haskell deriving instance Eq (f (g a)) => Eq (Compose f g a) ``` But, that change alone is rather breaking, because until now `Eq (f a)` and `Eq1 f` (and respectively the other classes and their `*1` equivalents too) are *incomparable* constraints. This has always been an annoyance of working with the `*1` classes, and now it would rear it's head one last time as an pesky migration. Instead, we give the `*1` classes superclasses, like so: ```haskell (forall a. Eq a => Eq (f a)) => Eq1 f ``` along with some laws that canonicity is preserved, like: ```haskell liftEq (==) = (==) ``` and likewise for `*2` classes: ```haskell (forall a. Eq a => Eq1 (f a)) => Eq2 f ``` and laws: ```haskell liftEq2 (==) = liftEq1 ``` The `*1` classes also have default methods using the `*2` classes where possible. What this means, as explained in the docs, is that `*1` classes really are generations of the regular classes, indicating that the methods can be split into a canonical lifting combined with a canonical inner, with the super class "witnessing" the laws[1] in a fashion. Circling back to the pragmatics of migrating, note that the superclass means evidence for the old `Sum`, `Product`, and `Compose` instances is (more than) sufficient, so breakage is less likely --- as long no instances are "missing", existing polymorphic code will continue to work. Breakage can occur when a datatype implements the `*1` class but not the corresponding regular class, but this is almost certainly an oversight. For example, containers made that mistake for `Tree` and `Ord`, which I fixed in https://github.com/haskell/containers/pull/761, but fixing the issue by adding `Ord1` was extremely *un*controversial. `Generically1` was also missing `Eq`, `Ord`, `Read,` and `Show` instances. It is unlikely this would have been caught without implementing this change. ----- [1]: In fact, someday, when the laws are part of the language and not only documentation, we might be able to drop the superclass field of the dictionary by using the laws to recover the superclass in an instance-agnostic manner, e.g. with a *non*-overloaded function with type: ```haskell DictEq1 f -> DictEq a -> DictEq (f a) ``` But I don't wish to get into optomizations now, just demonstrate the close relationship between the law and the superclass. Bump haddock submodule because of test output changing. - - - - - 6a8c6b5e by Tom Ellis at 2022-09-20T13:12:27-04:00 Add notes to ghc-prim Haddocks that users should not import it - - - - - ee9d0f5c by matoro at 2022-09-20T13:13:06-04:00 docs: clarify that LLVM codegen is not available in unregisterised mode The current docs are misleading and suggest that it is possible to use LLVM codegen from an unregisterised build. This is not the case; attempting to pass `-fllvm` to an unregisterised build warns: ``` when making flags consistent: warning: Target platform uses unregisterised ABI, so compiling via C ``` and uses the C codegen anyway. - - - - - 854224ed by Nicolas Trangez at 2022-09-20T20:14:29-04:00 rts: remove copy-paste error from `cabal.rts.in` This was, likely accidentally, introduced in 4bf542bf1c. See: 4bf542bf1cdf2fa468457fc0af21333478293476 - - - - - c8ae3add by Matthew Pickering at 2022-09-20T20:15:04-04:00 hadrian: Add extra_dependencies edges for all different ways The hack to add extra dependencies needed by DeriveLift extension missed the cases for profiles and dynamic ways. For the profiled way this leads to errors like: ``` GHC error in desugarer lookup in Data.IntSet.Internal: Failed to load interface for ‘Language.Haskell.TH.Lib.Internal’ Perhaps you haven't installed the profiling libraries for package ‘template-haskell’? Use -v (or `:set -v` in ghci) to see a list of the files searched for. ghc: panic! (the 'impossible' happened) GHC version 9.5.20220916: initDs ``` Therefore the fix is to add these extra edges in. Fixes #22197 - - - - - a971657d by Mon Aaraj at 2022-09-21T06:41:24+03:00 users-guide: fix incorrect ghcappdata folder for unix and windows - - - - - a7eec128 by Torsten Schmits at 2022-09-21T11:06:55+02:00 update tests for the move of tuples to GHC.Tuple.Prim - - - - - 06ccad0d by sheaf at 2022-09-21T08:28:49-04:00 Don't use isUnliftedType in isTagged The function GHC.Stg.InferTags.Rewrite.isTagged can be given the Id of a join point, which might be representation polymorphic. This would cause the call to isUnliftedType to crash. It's better to use typeLevity_maybe instead. Fixes #22212 - - - - - c0ba775d by Teo Camarasu at 2022-09-21T14:30:37-04:00 Add fragmentation statistic to GHC.Stats Implements #21537 - - - - - 2463df2f by Torsten Schmits at 2022-09-21T14:31:24-04:00 Rename Solo[constructor] to MkSolo Part of proposal 475 (https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0475-tuple-syntax.rst) Moves all tuples to GHC.Tuple.Prim Updates ghc-prim version (and bumps bounds in dependents) updates haddock submodule updates deepseq submodule updates text submodule - - - - - 9034fada by Matthew Pickering at 2022-09-22T09:25:29-04:00 Update filepath to filepath-1.4.100.0 Updates submodule * Always rely on vendored filepath * filepath must be built as stage0 dependency because it uses template-haskell. Towards #22098 - - - - - 615e2278 by Krzysztof Gogolewski at 2022-09-22T09:26:05-04:00 Minor refactor around Outputable * Replace 'text . show' and 'ppr' with 'int'. * Remove Outputable.hs-boot, no longer needed * Use pprWithCommas * Factor out instructions in AArch64 codegen - - - - - 461e7b9d by Ross Paterson at 2022-09-24T22:01:25+00:00 match implementation of GHC proposal haskell/haddock#106 (Define Kinds Without Promotion) - - - - - aeafdba5 by Sebastian Graf at 2022-09-27T15:14:54+02:00 Demand: Clear distinction between Call SubDmd and eval Dmd (#21717) In #21717 we saw a reportedly unsound strictness signature due to an unsound definition of plusSubDmd on Calls. This patch contains a description and the fix to the unsoundness as outlined in `Note [Call SubDemand vs. evaluation Demand]`. This fix means we also get rid of the special handling of `-fpedantic-bottoms` in eta-reduction. Thanks to less strict and actually sound strictness results, we will no longer eta-reduce the problematic cases in the first place, even without `-fpedantic-bottoms`. So fixing the unsoundness also makes our eta-reduction code simpler with less hacks to explain. But there is another, more unfortunate side-effect: We *unfix* #21085, but fortunately we have a new fix ready: See `Note [mkCall and plusSubDmd]`. There's another change: I decided to make `Note [SubDemand denotes at least one evaluation]` a lot simpler by using `plusSubDmd` (instead of `lubPlusSubDmd`) even if both argument demands are lazy. That leads to less precise results, but in turn rids ourselves from the need for 4 different `OpMode`s and the complication of `Note [Manual specialisation of lub*Dmd/plus*Dmd]`. The result is simpler code that is in line with the paper draft on Demand Analysis. I left the abandoned idea in `Note [Unrealised opportunity in plusDmd]` for posterity. The fallout in terms of regressions is negligible, as the testsuite and NoFib shows. ``` Program Allocs Instrs -------------------------------------------------------------------------------- hidden +0.2% -0.2% linear -0.0% -0.7% -------------------------------------------------------------------------------- Min -0.0% -0.7% Max +0.2% +0.0% Geometric Mean +0.0% -0.0% ``` Fixes #21717. - - - - - 9b1595c8 by Ross Paterson at 2022-09-27T14:12:01-04:00 implement proposal 106 (Define Kinds Without Promotion) (fixes #6024) includes corresponding changes to haddock submodule - - - - - c2d73cb4 by Andreas Klebinger at 2022-09-28T15:07:30-04:00 Apply some tricks to speed up core lint. Below are the noteworthy changes and if given their impact on compiler allocations for a type heavy module: * Use the oneShot trick on LintM * Use a unboxed tuple for the result of LintM: ~6% reduction * Avoid a thunk for the result of typeKind in lintType: ~5% reduction * lint_app: Don't allocate the error msg in the hot code path: ~4% reduction * lint_app: Eagerly force the in scope set: ~4% * nonDetCmpType: Try to short cut using reallyUnsafePtrEquality#: ~2% * lintM: Use a unboxed maybe for the `a` result: ~12% * lint_app: make go_app tail recursive to avoid allocating the go function as heap closure: ~7% * expandSynTyCon_maybe: Use a specialized data type For a less type heavy module like nofib/spectral/simple compiled with -O -dcore-lint allocations went down by ~24% and compile time by ~9%. ------------------------- Metric Decrease: T1969 ------------------------- - - - - - b74b6191 by sheaf at 2022-09-28T15:08:10-04:00 matchLocalInst: do domination analysis When multiple Given quantified constraints match a Wanted, and there is a quantified constraint that dominates all others, we now pick it to solve the Wanted. See Note [Use only the best matching quantified constraint]. For example: [G] d1: forall a b. ( Eq a, Num b, C a b ) => D a b [G] d2: forall a . C a Int => D a Int [W] {w}: D a Int When solving the Wanted, we find that both Givens match, but we pick the second, because it has a weaker precondition, C a Int, compared to (Eq a, Num Int, C a Int). We thus say that d2 dominates d1; see Note [When does a quantified instance dominate another?]. This domination test is done purely in terms of superclass expansion, in the function GHC.Tc.Solver.Interact.impliedBySCs. We don't attempt to do a full round of constraint solving; this simple check suffices for now. Fixes #22216 and #22223 - - - - - 2a53ac18 by Simon Peyton Jones at 2022-09-28T17:49:09-04:00 Improve aggressive specialisation This patch fixes #21286, by not unboxing dictionaries in worker/wrapper (ever). The main payload is tiny: * In `GHC.Core.Opt.DmdAnal.finaliseArgBoxities`, do not unbox dictionaries in `get_dmd`. See Note [Do not unbox class dictionaries] in that module * I also found that imported wrappers were being fruitlessly specialised, so I fixed that too, in canSpecImport. See Note [Specialising imported functions] point (2). In doing due diligence in the testsuite I fixed a number of other things: * Improve Note [Specialising unfoldings] in GHC.Core.Unfold.Make, and Note [Inline specialisations] in GHC.Core.Opt.Specialise, and remove duplication between the two. The new Note describes how we specialise functions with an INLINABLE pragma. And simplify the defn of `spec_unf` in `GHC.Core.Opt.Specialise.specCalls`. * Improve Note [Worker/wrapper for INLINABLE functions] in GHC.Core.Opt.WorkWrap. And (critially) make an actual change which is to propagate the user-written pragma from the original function to the wrapper; see `mkStrWrapperInlinePrag`. * Write new Note [Specialising imported functions] in GHC.Core.Opt.Specialise All this has a big effect on some compile times. This is compiler/perf, showing only changes over 1%: Metrics: compile_time/bytes allocated ------------------------------------- LargeRecord(normal) -50.2% GOOD ManyConstructors(normal) +1.0% MultiLayerModulesTH_OneShot(normal) +2.6% PmSeriesG(normal) -1.1% T10547(normal) -1.2% T11195(normal) -1.2% T11276(normal) -1.0% T11303b(normal) -1.6% T11545(normal) -1.4% T11822(normal) -1.3% T12150(optasm) -1.0% T12234(optasm) -1.2% T13056(optasm) -9.3% GOOD T13253(normal) -3.8% GOOD T15164(normal) -3.6% GOOD T16190(normal) -2.1% T16577(normal) -2.8% GOOD T16875(normal) -1.6% T17836(normal) +2.2% T17977b(normal) -1.0% T18223(normal) -33.3% GOOD T18282(normal) -3.4% GOOD T18304(normal) -1.4% T18698a(normal) -1.4% GOOD T18698b(normal) -1.3% GOOD T19695(normal) -2.5% GOOD T5837(normal) -2.3% T9630(normal) -33.0% GOOD WWRec(normal) -9.7% GOOD hard_hole_fits(normal) -2.1% GOOD hie002(normal) +1.6% geo. mean -2.2% minimum -50.2% maximum +2.6% I diligently investigated some of the big drops. * Caused by not doing w/w for dictionaries: T13056, T15164, WWRec, T18223 * Caused by not fruitlessly specialising wrappers LargeRecord, T9630 For runtimes, here is perf/should+_run: Metrics: runtime/bytes allocated -------------------------------- T12990(normal) -3.8% T5205(normal) -1.3% T9203(normal) -10.7% GOOD haddock.Cabal(normal) +0.1% haddock.base(normal) -1.1% haddock.compiler(normal) -0.3% lazy-bs-alloc(normal) -0.2% ------------------------------------------ geo. mean -0.3% minimum -10.7% maximum +0.1% I did not investigate exactly what happens in T9203. Nofib is a wash: +-------------------------------++--+-----------+-----------+ | || | tsv (rel) | std. err. | +===============================++==+===========+===========+ | real/anna || | -0.13% | 0.0% | | real/fem || | +0.13% | 0.0% | | real/fulsom || | -0.16% | 0.0% | | real/lift || | -1.55% | 0.0% | | real/reptile || | -0.11% | 0.0% | | real/smallpt || | +0.51% | 0.0% | | spectral/constraints || | +0.20% | 0.0% | | spectral/dom-lt || | +1.80% | 0.0% | | spectral/expert || | +0.33% | 0.0% | +===============================++==+===========+===========+ | geom mean || | | | +-------------------------------++--+-----------+-----------+ I spent quite some time investigating dom-lt, but it's pretty complicated. See my note on !7847. Conclusion: it's just a delicate inlining interaction, and we have plenty of those. Metric Decrease: LargeRecord T13056 T13253 T15164 T16577 T18223 T18282 T18698a T18698b T19695 T9630 WWRec hard_hole_fits T9203 - - - - - addeefc0 by Simon Peyton Jones at 2022-09-28T17:49:09-04:00 Refactor UnfoldingSource and IfaceUnfolding I finally got tired of the way that IfaceUnfolding reflected a previous structure of unfoldings, not the current one. This MR refactors UnfoldingSource and IfaceUnfolding to be simpler and more consistent. It's largely just a refactor, but in UnfoldingSource (which moves to GHC.Types.Basic, since it is now used in IfaceSyn too), I distinguish between /user-specified/ and /system-generated/ stable unfoldings. data UnfoldingSource = VanillaSrc | StableUserSrc -- From a user-specified pragma | StableSystemSrc -- From a system-generated unfolding | CompulsorySrc This has a minor effect in CSE (see the use of isisStableUserUnfolding in GHC.Core.Opt.CSE), which I tripped over when working on specialisation, but it seems like a Good Thing to know anyway. - - - - - 7be6f9a4 by Simon Peyton Jones at 2022-09-28T17:49:09-04:00 INLINE/INLINEABLE pragmas in Foreign.Marshal.Array Foreign.Marshal.Array contains many small functions, all of which are overloaded, and which are critical for performance. Yet none of them had pragmas, so it was a fluke whether or not they got inlined. This patch makes them all either INLINE (small ones) or INLINEABLE and hence specialisable (larger ones). See Note [Specialising array operations] in that module. - - - - - b0c89dfa by Jade Lovelace at 2022-09-28T17:49:49-04:00 Export OnOff from GHC.Driver.Session I was working on fixing an issue where HLS was trying to pass its DynFlags to HLint, but didn't pass any of the disabled language extensions, which HLint would then assume are on because of their default values. Currently it's not possible to get any of the "No" flags because the `DynFlags.extensions` field can't really be used since it is [OnOff Extension] and OnOff is not exported. So let's export it. - - - - - 2f050687 by Andrew Lelechenko at 2022-09-28T17:50:28-04:00 Avoid Data.List.group; prefer Data.List.NonEmpty.group This allows to avoid further partiality, e. g., map head . group is replaced by map NE.head . NE.group, and there are less panic calls. - - - - - bc0020fa by M Farkas-Dyck at 2022-09-28T22:51:59-04:00 Clean up `findWiredInUnit`. In particular, avoid `head`. - - - - - 6a2eec98 by Andrew Lelechenko at 2022-09-28T22:52:38-04:00 Eliminate headFS, use unconsFS instead A small step towards #22185 to avoid partial functions + safe implementation of `startsWithUnderscore`. - - - - - 5a535172 by Sebastian Graf at 2022-09-29T17:04:20+02:00 Demand: Format Call SubDemands `Cn(sd)` as `C(n,sd)` (#22231) Justification in #22231. Short form: In a demand like `1C1(C1(L))` it was too easy to confuse which `1` belongs to which `C`. Now that should be more obvious. Fixes #22231 - - - - - ea0083bf by Bryan Richter at 2022-09-29T15:48:38-04:00 Revert "ci: enable parallel compression for xz" Combined wxth XZ_OPT=9, this blew the memory capacity of CI runners. This reverts commit a5f9c35f5831ef5108e87813a96eac62803852ab. - - - - - f5e8f493 by Sebastian Graf at 2022-09-30T18:42:13+02:00 Boxity: Don't update Boxity unless worker/wrapper follows (#21754) A small refactoring in our Core Opt pipeline and some new functions for transfering argument boxities from one signature to another to facilitate `Note [Don't change boxity without worker/wrapper]`. Fixes #21754. - - - - - 4baf7b1c by M Farkas-Dyck at 2022-09-30T17:45:47-04:00 Scrub various partiality involving empty lists. Avoids some uses of `head` and `tail`, and some panics when an argument is null. - - - - - 95ead839 by Alexis King at 2022-10-01T00:37:43-04:00 Fix a bug in continuation capture across multiple stack chunks - - - - - 22096652 by Andrew Lelechenko at 2022-10-01T00:38:22-04:00 Enforce internal invariant of OrdList and fix bugs in viewCons / viewSnoc `viewCons` used to ignore `Many` constructor completely, returning `VNothing`. `viewSnoc` violated internal invariant of `Many` being a non-empty list. - - - - - 48ab9ca5 by Nicolas Trangez at 2022-10-04T20:34:10-04:00 chore: extend `.editorconfig` for C files - - - - - b8df5c72 by Brandon Chinn at 2022-10-04T20:34:46-04:00 Fix docs for pattern synonyms - - - - - 463ffe02 by Oleg Grenrus at 2022-10-04T20:35:24-04:00 Use sameByteArray# in sameByteArray - - - - - fbe1e86e by Pierre Le Marre at 2022-10-05T15:58:43+02:00 Minor fixes following Unicode 15.0.0 update - Fix changelog for Unicode 15.0.0 - Fix the checksums of the downloaded Unicode files, in base's tool: "ucd2haskell". - - - - - 8a31d02e by Cheng Shao at 2022-10-05T20:40:41-04:00 rts: don't enforce aligned((8)) on 32-bit targets We simply need to align to the word size for pointer tagging to work. On 32-bit targets, aligned((8)) is wasteful. - - - - - 532de368 by Ryan Scott at 2022-10-06T07:45:46-04:00 Export symbolSing, SSymbol, and friends (CLC#85) This implements this Core Libraries Proposal: https://github.com/haskell/core-libraries-committee/issues/85 In particular, it: 1. Exposes the `symbolSing` method of `KnownSymbol`, 2. Exports the abstract `SSymbol` type used in `symbolSing`, and 3. Defines an API for interacting with `SSymbol`. This also makes corresponding changes for `natSing`/`KnownNat`/`SNat` and `charSing`/`KnownChar`/`SChar`. This fixes #15183 and addresses part (2) of #21568. - - - - - d83a92e6 by sheaf at 2022-10-07T07:36:30-04:00 Remove mention of make from README.md - - - - - 945e8e49 by Andrew Lelechenko at 2022-10-10T17:13:31-04:00 Add a newline before since pragma in Data.Array.Byte - - - - - 44fcdb04 by Vladislav Zavialov at 2022-10-10T17:14:06-04:00 Parser/PostProcess: rename failOp* functions There are three functions named failOp* in the parser: failOpNotEnabledImportQualifiedPost failOpImportQualifiedTwice failOpFewArgs Only the last one has anything to do with operators. The other two were named this way either by mistake or due to a misunderstanding of what "op" stands for. This small patch corrects this. - - - - - 96d32ff2 by Simon Peyton Jones at 2022-10-10T22:30:21+01:00 Make rewrite rules "win" over inlining If a rewrite rule and a rewrite rule compete in the simplifier, this patch makes sure that the rewrite rule "win". That is, in general a bit fragile, but it's a huge help when making specialisation work reliably, as #21851 and #22097 showed. The change is fairly straightforwad, and documented in Note [Rewrite rules and inlining] in GHC.Core.Opt.Simplify.Iteration. Compile-times change, up and down a bit -- in some cases because we get better specialisation. But the payoff (more reliable specialisation) is large. Metrics: compile_time/bytes allocated ----------------------------------------------- T10421(normal) +3.7% BAD T10421a(normal) +5.5% T13253(normal) +1.3% T14052(ghci) +1.8% T15304(normal) -1.4% T16577(normal) +3.1% BAD T17516(normal) +2.3% T17836(normal) -1.9% T18223(normal) -1.8% T8095(normal) -1.3% T9961(normal) +2.5% BAD geo. mean +0.0% minimum -1.9% maximum +5.5% Nofib results are (bytes allocated) +-------------------------------++----------+ | ||tsv (rel) | +===============================++==========+ | imaginary/paraffins || +0.27% | | imaginary/rfib || -0.04% | | real/anna || +0.02% | | real/fem || -0.04% | | real/fluid || +1.68% | | real/gamteb || -0.34% | | real/gg || +1.54% | | real/hidden || -0.01% | | real/hpg || -0.03% | | real/infer || -0.03% | | real/prolog || +0.02% | | real/veritas || -0.47% | | shootout/fannkuch-redux || -0.03% | | shootout/k-nucleotide || -0.02% | | shootout/n-body || -0.06% | | shootout/spectral-norm || -0.01% | | spectral/cryptarithm2 || +1.25% | | spectral/fibheaps || +18.33% | | spectral/last-piece || -0.34% | +===============================++==========+ | geom mean || +0.17% | There are extensive notes in !8897 about the regressions. Briefly * fibheaps: there was a very delicately balanced inlining that tipped over the wrong way after this change. * cryptarithm2 and paraffins are caused by #22274, which is a separate issue really. (I.e. the right fix is *not* to make inlining "win" over rules.) So I'm accepting these changes Metric Increase: T10421 T16577 T9961 - - - - - ed4b5885 by Joachim Breitner at 2022-10-10T23:16:11-04:00 Utils.JSON: do not escapeJsonString in ToJson String instance as `escapeJsonString` is used in `renderJSON`, so the `JSString` constructor is meant to carry the unescaped string. - - - - - fbb88740 by Matthew Pickering at 2022-10-11T12:48:45-04:00 Tidy implicit binds We want to put implicit binds into fat interface files, so the easiest thing to do seems to be to treat them uniformly with other binders. - - - - - e058b138 by Matthew Pickering at 2022-10-11T12:48:45-04:00 Interface Files with Core Definitions This commit adds three new flags * -fwrite-if-simplified-core: Writes the whole core program into an interface file * -fbyte-code-and-object-code: Generate both byte code and object code when compiling a file * -fprefer-byte-code: Prefer to use byte-code if it's available when running TH splices. The goal for including the core bindings in an interface file is to be able to restart the compiler pipeline at the point just after simplification and before code generation. Once compilation is restarted then code can be created for the byte code backend. This can significantly speed up start-times for projects in GHCi. HLS already implements its own version of these extended interface files for this reason. Preferring to use byte-code means that we can avoid some potentially expensive code generation steps (see #21700) * Producing object code is much slower than producing bytecode, and normally you need to compile with `-dynamic-too` to produce code in the static and dynamic way, the dynamic way just for Template Haskell execution when using a dynamically linked compiler. * Linking many large object files, which happens once per splice, can be quite expensive compared to linking bytecode. And you can get GHC to compile the necessary byte code so `-fprefer-byte-code` has access to it by using `-fbyte-code-and-object-code`. Fixes #21067 - - - - - 9789ea8e by Matthew Pickering at 2022-10-11T12:48:45-04:00 Teach -fno-code about -fprefer-byte-code This patch teachs the code generation logic of -fno-code about -fprefer-byte-code, so that if we need to generate code for a module which prefers byte code, then we generate byte code rather than object code. We keep track separately which modules need object code and which byte code and then enable the relevant code generation for each. Typically the option will be enabled globally so one of these sets should be empty and we will just turn on byte code or object code generation. We also fix the bug where we would generate code for a module which enables Template Haskell despite the fact it was unecessary. Fixes #22016 - - - - - caced757 by Simon Peyton Jones at 2022-10-11T12:49:21-04:00 Don't keep exit join points so much We were religiously keeping exit join points throughout, which had some bad effects (#21148, #22084). This MR does two things: * Arranges that exit join points are inhibited from inlining only in /one/ Simplifier pass (right after Exitification). See Note [Be selective about not-inlining exit join points] in GHC.Core.Opt.Exitify It's not a big deal, but it shaves 0.1% off compile times. * Inline used-once non-recursive join points very aggressively Given join j x = rhs in joinrec k y = ....j x.... where this is the only occurrence of `j`, we want to inline `j`. (Unless sm_keep_exits is on.) See Note [Inline used-once non-recursive join points] in GHC.Core.Opt.Simplify.Utils This is just a tidy-up really. It doesn't change allocation, but getting rid of a binding is always good. Very effect on nofib -- some up and down. - - - - - 284cf387 by Simon Peyton Jones at 2022-10-11T12:49:21-04:00 Make SpecConstr bale out less often When doing performance debugging on #22084 / !8901, I found that the algorithm in SpecConstr.decreaseSpecCount was so aggressive that if there were /more/ specialisations available for an outer function, that could more or less kill off specialisation for an /inner/ function. (An example was in nofib/spectral/fibheaps.) This patch makes it a bit more aggressive, by dividing by 2, rather than by the number of outer specialisations. This makes the program bigger, temporarily: T19695(normal) ghc/alloc +11.3% BAD because we get more specialisation. But lots of other programs compile a bit faster and the geometric mean in perf/compiler is 0.0%. Metric Increase: T19695 - - - - - 66af1399 by Cheng Shao at 2022-10-11T12:49:59-04:00 CmmToC: emit explicit tail calls when the C compiler supports it Clang 13+ supports annotating a return statement using the musttail attribute, which guarantees that it lowers to a tail call if compilation succeeds. This patch takes advantage of that feature for the unregisterised code generator. The configure script tests availability of the musttail attribute, if it's available, the Cmm tail calls will become C tail calls that avoids the mini interpreter trampoline overhead. Nothing is affected if the musttail attribute is not supported. Clang documentation: https://clang.llvm.org/docs/AttributeReference.html#musttail - - - - - 7f0decd5 by Matthew Pickering at 2022-10-11T12:50:40-04:00 Don't include BufPos in interface files Ticket #22162 pointed out that the build directory was leaking into the ABI hash of a module because the BufPos depended on the location of the build tree. BufPos is only used in GHC.Parser.PostProcess.Haddock, and the information doesn't need to be propagated outside the context of a module. Fixes #22162 - - - - - dce9f320 by Cheng Shao at 2022-10-11T12:51:19-04:00 CLabel: fix isInfoTableLabel isInfoTableLabel does not take Cmm info table into account. This patch is required for data section layout of wasm32 NCG to work. - - - - - da679f2e by Andrew Lelechenko at 2022-10-11T18:02:59-04:00 Extend documentation for Data.List, mostly wrt infinite lists - - - - - 9c099387 by jwaldmann at 2022-10-11T18:02:59-04:00 Expand comment for Data.List.permutations - - - - - d3863cb7 by Andrew Lelechenko at 2022-10-11T18:03:37-04:00 ByteArray# is unlifted, not unboxed - - - - - f6260e8b by Ben Gamari at 2022-10-11T23:45:10-04:00 rts: Add missing declaration of stg_noDuplicate - - - - - 69ccec2c by Ben Gamari at 2022-10-11T23:45:10-04:00 base: Move CString, CStringLen to GHC.Foreign - - - - - f6e8feb4 by Ben Gamari at 2022-10-11T23:45:10-04:00 base: Move IPE helpers to GHC.InfoProv - - - - - 866c736e by Ben Gamari at 2022-10-11T23:45:10-04:00 rts: Refactor IPE tracing support - - - - - 6b0d2022 by Ben Gamari at 2022-10-11T23:45:10-04:00 Refactor IPE initialization Here we refactor the representation of info table provenance information in object code to significantly reduce its size and link-time impact. Specifically, we deduplicate strings and represent them as 32-bit offsets into a common string table. In addition, we rework the registration logic to eliminate allocation from the registration path, which is run from a static initializer where things like allocation are technically undefined behavior (although it did previously seem to work). For similar reasons we eliminate lock usage from registration path, instead relying on atomic CAS. Closes #22077. - - - - - 9b572d54 by Ben Gamari at 2022-10-11T23:45:10-04:00 Separate IPE source file from span The source file name can very often be shared across many IPE entries whereas the source coordinates are generally unique. Separate the two to exploit sharing of the former. - - - - - 27978ceb by Krzysztof Gogolewski at 2022-10-11T23:45:46-04:00 Make Cmm Lint messages use dump style Lint errors indicate an internal error in GHC, so it makes sense to use it instead of the user style. This is consistent with Core Lint and STG Lint: https://gitlab.haskell.org/ghc/ghc/-/blob/22096652/compiler/GHC/Core/Lint.hs#L429 https://gitlab.haskell.org/ghc/ghc/-/blob/22096652/compiler/GHC/Stg/Lint.hs#L144 Fixes #22218. - - - - - 64a390d9 by Bryan Richter at 2022-10-12T09:52:51+03:00 Mark T7919 as fragile On x86_64-linux, T7919 timed out ~30 times during July 2022. And again ~30 times in September 2022. - - - - - 481467a5 by Ben Gamari at 2022-10-12T08:08:37-04:00 rts: Don't hint inlining of appendToRunQueue These hints have resulted in compile-time warnings due to failed inlinings for quite some time. Moreover, it's quite unlikely that inlining them is all that beneficial given that they are rather sizeable functions. Resolves #22280. - - - - - 81915089 by Curran McConnell at 2022-10-12T16:32:26-04:00 remove name shadowing - - - - - 626652f7 by Tamar Christina at 2022-10-12T16:33:13-04:00 winio: do not re-translate input when handle is uncooked - - - - - 5172789a by Charles Taylor at 2022-10-12T16:33:57-04:00 Unrestricted OverloadedLabels (#11671) Implements GHC proposal: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0170-unrestricted-overloadedlabels.rst - - - - - ce293908 by Andreas Klebinger at 2022-10-13T05:58:19-04:00 Add a perf test for the generics code pattern from #21839. This code showed a strong shift between compile time (got worse) and run time (got a lot better) recently which is perfectly acceptable. However it wasn't clear why the compile time regression was happening initially so I'm adding this test to make it easier to track such changes in the future. - - - - - 78ab7afe by Ben Gamari at 2022-10-13T05:58:56-04:00 rts/linker: Consolidate initializer/finalizer handling Here we extend our treatment of initializer/finalizer priorities to include ELF and in so doing refactor things to share the implementation with PEi386. As well, I fix a subtle misconception of the ordering behavior for `.ctors`. Fixes #21847. - - - - - 44692713 by Ben Gamari at 2022-10-13T05:58:56-04:00 rts/linker: Add support for .fini sections - - - - - beebf546 by Simon Hengel at 2022-10-13T05:59:37-04:00 Update phases.rst (the name of the original source file is $1, not $2) - - - - - eda6c05e by Finley McIlwaine at 2022-10-13T06:00:17-04:00 Clearer error msg for newtype GADTs with defaulted kind When a newtype introduces GADT eq_specs due to a defaulted RuntimeRep, we detect this and print the error message with explicit kinds. This also refactors newtype type checking to use the new diagnostic infra. Fixes #21447 - - - - - 43ab435a by Pierre Le Marre at 2022-10-14T07:45:43-04:00 Add standard Unicode case predicates isUpperCase and isLowerCase. These predicates use the standard Unicode case properties and are more intuitive than isUpper and isLower. Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/90#issuecomment-1276649403. Fixes #14589 - - - - - aec5a443 by Andrew Lelechenko at 2022-10-14T07:46:21-04:00 Add type signatures in where-clause of Data.List.permutations The type of interleave' is very much revealing, otherwise it's extremely tough to decipher. - - - - - ee0deb80 by Ben Gamari at 2022-10-14T18:29:20-04:00 rts: Use pthread_setname_np correctly on Darwin As noted in #22206, pthread_setname_np on Darwin only supports setting the name of the calling thread. Consequently we must introduce a trampoline which first sets the thread name before entering the thread entrypoint. - - - - - 8eff62a4 by Ben Gamari at 2022-10-14T18:29:57-04:00 testsuite: Add test for #22282 This will complement mpickering's more general port of foundation's numerical testsuite, providing a test for the specific case found in #22282. - - - - - 62a55001 by Ben Gamari at 2022-10-14T18:29:57-04:00 ncg/aarch64: Fix sub-word sign extension yet again In adc7f108141a973b6dcb02a7836eed65d61230e8 we fixed a number of issues to do with sign extension in the AArch64 NCG found by ghc/test-primops>. However, this patch made a critical error, assuming that getSomeReg would allocate a fresh register for the result of its evaluation. However, this is not the case as `getSomeReg (CmmReg r) == r`. Consequently, any mutation of the register returned by `getSomeReg` may have unwanted side-effects on other expressions also mentioning `r`. In the fix listed above, this manifested as the registers containing the operands of binary arithmetic operations being incorrectly sign-extended. This resulted in #22282. Sadly, the rather simple structure of the tests generated by `test-primops` meant that this particular case was not exercised. Even more surprisingly, none of our testsuite caught this case. Here we fix this by ensuring that intermediate sign extension is performed in a fresh register. Fixes #22282. - - - - - 54e41b16 by Teo Camarasu at 2022-10-15T18:09:24+01:00 rts: ensure we are below maxHeapSize after returning megablocks When the heap is heavily block fragmented the live byte size might be low while the memory usage is high. We want to ensure that heap overflow triggers in these cases. We do so by checking that we can return enough megablocks to under maxHeapSize at the end of GC. - - - - - 29bb90db by Teo Camarasu at 2022-10-15T18:09:24+01:00 rts: trigger a major collection if megablock usage exceeds maxHeapSize When the heap is suffering from block fragmentation, live bytes might be low while megablock usage is high. If megablock usage exceeds maxHeapSize, we want to trigger a major GC to try to recover some memory otherwise we will die from a heapOverflow at the end of the GC. Fixes #21927 - - - - - 4a4641ca by Teo Camarasu at 2022-10-15T18:11:29+01:00 Add realease note for #21927 - - - - - f7fd77ef by sheaf at 2022-10-17T14:53:01+02:00 Update Haddock for GHC MR !8563 (configuration of diagnostics) - - - - - c1e5719a by Sebastian Graf at 2022-10-17T11:58:46-04:00 DmdAnal: Look through unfoldings of DataCon wrappers (#22241) Previously, the demand signature we computed upfront for a DataCon wrapper lacked boxity information and was much less precise than the demand transformer for the DataCon worker. In this patch we adopt the solution to look through unfoldings of DataCon wrappers during Demand Analysis, but still attach a demand signature for other passes such as the Simplifier. See `Note [DmdAnal for DataCon wrappers]` for more details. Fixes #22241. - - - - - 8c72411d by Gergő Érdi at 2022-10-17T19:20:04-04:00 Add `Enum (Down a)` instance that swaps `succ` and `pred` See https://github.com/haskell/core-libraries-committee/issues/51 for discussion. The key points driving the implementation are the following two ideas: * For the `Int` type, `comparing (complement @Int)` behaves exactly as an order-swapping `compare @Int`. * `enumFrom @(Down a)` can be implemented in terms of `enumFromThen @a`, if only the corner case of starting at the very end is handled specially - - - - - d80ad2f4 by Alan Zimmerman at 2022-10-17T19:20:40-04:00 Update the check-exact infrastructure to match ghc-exactprint GHC tests the exact print annotations using the contents of utils/check-exact. The same functionality is provided via https://github.com/alanz/ghc-exactprint The latter was updated to ensure it works with all of the files on hackage when 9.2 was released, as well as updated to ensure users of the library could work properly (apply-refact, retrie, etc). This commit brings the changes from ghc-exactprint into GHC/utils/check-exact, adapting for the changes to master. Once it lands, it will form the basis for the 9.4 version of ghc-exactprint. See also discussion around this process at #21355 - - - - - 08ab5419 by Andreas Klebinger at 2022-10-17T19:21:15-04:00 Avoid allocating intermediate lists for non recursive bindings. We do so by having an explicit folding function that doesn't need to allocate intermediate lists first. Fixes #22196 - - - - - ff6275ef by Andreas Klebinger at 2022-10-17T19:21:52-04:00 Testsuite: Add a new tables_next_to_code predicate. And use it to avoid T21710a failing on non-tntc archs. Fixes #22169 - - - - - abb82f38 by Eric Lindblad at 2022-10-17T19:22:33-04:00 example rewrite - - - - - 39beb801 by Eric Lindblad at 2022-10-17T19:22:33-04:00 remove redirect - - - - - 0d9fb651 by Eric Lindblad at 2022-10-17T19:22:33-04:00 use heredoc - - - - - 0fa2d185 by Matthew Pickering at 2022-10-17T19:23:10-04:00 testsuite: Fix typo when setting llvm_ways Since 2014 llvm_ways has been set to [] so none of the tests which use only_ways(llvm_ways) have worked as expected. Hopefully the tests still pass with this typo fix! - - - - - ced664a2 by Krzysztof Gogolewski at 2022-10-17T19:23:10-04:00 Fix T15155l not getting -fllvm - - - - - 0ac60423 by Andreas Klebinger at 2022-10-18T03:34:47-04:00 Fix GHCis interaction with tag inference. I had assumed that wrappers were not inlined in interactive mode. Meaning we would always execute the compiled wrapper which properly takes care of upholding the strict field invariant. This turned out to be wrong. So instead we now run tag inference even when we generate bytecode. In that case only for correctness not performance reasons although it will be still beneficial for runtime in some cases. I further fixed a bug where GHCi didn't tag nullary constructors properly when used as arguments. Which caused segfaults when calling into compiled functions which expect the strict field invariant to be upheld. Fixes #22042 and #21083 ------------------------- Metric Increase: T4801 Metric Decrease: T13035 ------------------------- - - - - - 9ecd1ac0 by M Farkas-Dyck at 2022-10-18T03:35:38-04:00 Make `Functor` a superclass of `TrieMap`, which lets us derive the `map` functions. - - - - - f60244d7 by Ben Gamari at 2022-10-18T03:36:15-04:00 configure: Bump minimum bootstrap GHC version Fixes #22245 - - - - - ba4bd4a4 by Matthew Pickering at 2022-10-18T03:36:55-04:00 Build System: Remove out-of-date comment about make build system Both make and hadrian interleave compilation of modules of different modules and don't respect the package boundaries. Therefore I just remove this comment which points out this "difference". Fixes #22253 - - - - - e1bbd368 by Matthew Pickering at 2022-10-18T16:15:49+02:00 Allow configuration of error message printing This MR implements the idea of #21731 that the printing of a diagnostic method should be configurable at the printing time. The interface of the `Diagnostic` class is modified from: ``` class Diagnostic a where diagnosticMessage :: a -> DecoratedSDoc diagnosticReason :: a -> DiagnosticReason diagnosticHints :: a -> [GhcHint] ``` to ``` class Diagnostic a where type DiagnosticOpts a defaultDiagnosticOpts :: DiagnosticOpts a diagnosticMessage :: DiagnosticOpts a -> a -> DecoratedSDoc diagnosticReason :: a -> DiagnosticReason diagnosticHints :: a -> [GhcHint] ``` and so each `Diagnostic` can implement their own configuration record which can then be supplied by a client in order to dictate how to print out the error message. At the moment this only allows us to implement #21722 nicely but in future it is more natural to separate the configuration of how much information we put into an error message and how much we decide to print out of it. Updates Haddock submodule - - - - - 99dc3e3d by Matthew Pickering at 2022-10-18T16:15:53+02:00 Add -fsuppress-error-contexts to disable printing error contexts in errors In many development environments, the source span is the primary means of seeing what an error message relates to, and the In the expression: and In an equation for: clauses are not particularly relevant. However, they can grow to be quite long, which can make the message itself both feel overwhelming and interact badly with limited-space areas. It's simple to implement this flag so we might as well do it and give the user control about how they see their messages. Fixes #21722 - - - - - 5b3a992f by Dai at 2022-10-19T10:45:45-04:00 Add VecSlot for unboxed sums of SIMD vectors This patch adds the missing `VecRep` case to `primRepSlot` function and all the necessary machinery to carry this new `VecSlot` through code generation. This allows programs involving unboxed sums of SIMD vectors to be written and compiled. Fixes #22187 - - - - - 6d7d9181 by sheaf at 2022-10-19T10:45:45-04:00 Remove SIMD conversions This patch makes it so that packing/unpacking SIMD vectors always uses the right sized types, e.g. unpacking a Word16X4# will give a tuple of Word16#s. As a result, we can get rid of the conversion instructions that were previously required. Fixes #22296 - - - - - 3be48877 by sheaf at 2022-10-19T10:45:45-04:00 Cmm Lint: relax SIMD register assignment check As noted in #22297, SIMD vector registers can be used to store different kinds of values, e.g. xmm1 can be used both to store integer and floating point values. The Cmm type system doesn't properly account for this, so we weaken the Cmm register assignment lint check to only compare widths when comparing a vector type with its allocated vector register. - - - - - f7b7a312 by sheaf at 2022-10-19T10:45:45-04:00 Disable some SIMD tests on non-X86 architectures - - - - - 83638dce by M Farkas-Dyck at 2022-10-19T10:46:29-04:00 Scrub various partiality involving lists (again). Lets us avoid some use of `head` and `tail`, and some panics. - - - - - c3732c62 by M Farkas-Dyck at 2022-10-19T10:47:13-04:00 Enforce invariant of `ListBag` constructor. - - - - - 488d3631 by Andrew Lelechenko at 2022-10-19T10:47:52-04:00 More precise types for fields of OverlappingInstances and UnsafeOverlap in TcSolverReportMsg It's clear from asserts in `GHC.Tc.Errors` that `overlappingInstances_matches` and `unsafeOverlapped` are supposed to be non-empty, and `unsafeOverlap_matches` contains a single instance, but these invariants are immediately lost afterwards and not encoded in types. This patch enforces the invariants by pattern matching and makes types more precise, avoiding asserts and partial functions such as `head`. - - - - - 607ce263 by sheaf at 2022-10-19T10:47:52-04:00 Rename unsafeOverlap_matches -> unsafeOverlap_match in UnsafeOverlap - - - - - 1fab9598 by Matthew Pickering at 2022-10-19T10:48:29-04:00 Add SpliceTypes test for hie files This test checks that typed splices and quotes get the right type information when used in hiefiles. See #21619 - - - - - a8b52786 by Jan Hrček at 2022-10-19T10:49:09-04:00 Small language fixes in 'Using GHC' - - - - - 1dab1167 by Gergő Érdi at 2022-10-19T10:49:51-04:00 Fix typo in `Opt_WriteIfSimplifiedCore`'s name - - - - - b17cfc9c by sheaf at 2022-10-19T10:50:37-04:00 TyEq:N assertion: only for saturated applications The assertion that checked TyEq:N in canEqCanLHSFinish incorrectly triggered in the case of an unsaturated newtype TyCon heading the RHS, even though we can't unwrap such an application. Now, we only trigger an assertion failure in case of a saturated application of a newtype TyCon. Fixes #22310 - - - - - ff6f2228 by M Farkas-Dyck at 2022-10-20T16:15:51-04:00 CoreToStg: purge `DynFlags`. - - - - - 1ebd521f by Matthew Pickering at 2022-10-20T16:16:27-04:00 ci: Make fat014 test robust For some reason I implemented this as a makefile test rather than a ghci_script test. Hopefully making it a ghci_script test makes it more robust. Fixes #22313 - - - - - 8cd6f435 by Curran McConnell at 2022-10-21T02:58:01-04:00 remove a no-warn directive from GHC.Cmm.ContFlowOpt This patch is motivated by the desire to remove the {-# OPTIONS_GHC -fno-warn-incomplete-patterns #-} directive at the top of GHC.Cmm.ContFlowOpt. (Based on the text in this coding standards doc, I understand it's a goal of the project to remove such directives.) I chose this task because I'm a new contributor to GHC, and it seemed like a good way to get acquainted with the patching process. In order to address the warning that arose when I removed the no-warn directive, I added a case to removeUnreachableBlocksProc to handle the CmmData constructor. Clearly, since this partial function has not been erroring out in the wild, its inputs are always in practice wrapped by the CmmProc constructor. Therefore the CmmData case is handled by a precise panic (which is an improvement over the partial pattern match from before). - - - - - a2af7c4c by Nicolas Trangez at 2022-10-21T02:58:39-04:00 build: get rid of `HAVE_TIME_H` As advertized by `autoreconf`: > All current systems provide time.h; it need not be checked for. Hence, remove the check for it in `configure.ac` and remove conditional inclusion of the header in `HAVE_TIME_H` blocks where applicable. The `time.h` header was being included in various source files without a `HAVE_TIME_H` guard already anyway. - - - - - 25cdc630 by Nicolas Trangez at 2022-10-21T02:58:39-04:00 rts: remove use of `TIME_WITH_SYS_TIME` `autoreconf` will insert an `m4_warning` when the obsolescent `AC_HEADER_TIME` macro is used: > Update your code to rely only on HAVE_SYS_TIME_H, > then remove this warning and the obsolete code below it. > All current systems provide time.h; it need not be checked for. > Not all systems provide sys/time.h, but those that do, all allow > you to include it and time.h simultaneously. Presence of `sys/time.h` was already checked in an earlier `AC_CHECK_HEADERS` invocation, so `AC_HEADER_TIME` can be dropped and guards relying on `TIME_WITH_SYS_TIME` can be reworked to (unconditionally) include `time.h` and include `sys/time.h` based on `HAVE_SYS_TIME_H`. Note the documentation of `AC_HEADER_TIME` in (at least) Autoconf 2.67 says > This macro is obsolescent, as current systems can include both files > when they exist. New programs need not use this macro. - - - - - 1fe7921c by Eric Lindblad at 2022-10-21T02:59:21-04:00 runhaskell - - - - - e3b3986e by David Feuer at 2022-10-21T03:00:00-04:00 Document how to quote certain names with spaces Quoting a name for Template Haskell is a bit tricky if the second character of that name is a single quote. The User's Guide falsely claimed that it was impossible. Document how to do it. Fixes #22236 - - - - - 0eba81e8 by Krzysztof Gogolewski at 2022-10-21T03:00:00-04:00 Fix syntax - - - - - a4dbd102 by Ben Gamari at 2022-10-21T09:11:12-04:00 Fix manifest filename when writing Windows .rc files As noted in #12971, we previously used `show` which resulted in inappropriate escaping of non-ASCII characters. - - - - - 30f0d9a9 by Ben Gamari at 2022-10-21T09:11:12-04:00 Write response files in UTF-8 on Windows This reverts the workaround introduced in f63c8ef33ec9666688163abe4ccf2d6c0428a7e7, which taught our response file logic to write response files with the `latin1` encoding to workaround `gcc`'s lacking Unicode support. This is now no longer necessary (and in fact actively unhelpful) since we rather use Clang. - - - - - b8304648 by Matthew Farkas-Dyck at 2022-10-21T09:11:56-04:00 Scrub some partiality in `GHC.Core.Opt.Simplify.Utils`. - - - - - 09ec7de2 by Teo Camarasu at 2022-10-21T13:23:07-04:00 template-haskell: Improve documentation of strictness annotation types Before it was undocumentated that DecidedLazy can be returned by reifyConStrictness for strict fields. This can happen when a field has an unlifted type or its the single field of a newtype constructor. Fixes #21380 - - - - - 88172069 by M Farkas-Dyck at 2022-10-21T13:23:51-04:00 Delete `eqExpr`, since GHC 9.4 has been released. - - - - - 86e6549e by Ömer Sinan Ağacan at 2022-10-22T07:41:30-04:00 Introduce a standard thunk for allocating strings Currently for a top-level closure in the form hey = unpackCString# x we generate code like this: Main.hey_entry() // [R1] { info_tbls: [(c2T4, label: Main.hey_info rep: HeapRep static { Thunk } srt: Nothing)] stack_info: arg_space: 8 updfr_space: Just 8 } {offset c2T4: // global _rqm::P64 = R1; if ((Sp + 8) - 24 < SpLim) (likely: False) goto c2T5; else goto c2T6; c2T5: // global R1 = _rqm::P64; call (stg_gc_enter_1)(R1) args: 8, res: 0, upd: 8; c2T6: // global (_c2T1::I64) = call "ccall" arg hints: [PtrHint, PtrHint] result hints: [PtrHint] newCAF(BaseReg, _rqm::P64); if (_c2T1::I64 == 0) goto c2T3; else goto c2T2; c2T3: // global call (I64[_rqm::P64])() args: 8, res: 0, upd: 8; c2T2: // global I64[Sp - 16] = stg_bh_upd_frame_info; I64[Sp - 8] = _c2T1::I64; R2 = hey1_r2Gg_bytes; Sp = Sp - 16; call GHC.CString.unpackCString#_info(R2) args: 24, res: 0, upd: 24; } } This code is generated for every string literal. Only difference between top-level closures like this is the argument for the bytes of the string (hey1_r2Gg_bytes in the code above). With this patch we introduce a standard thunk in the RTS, called stg_MK_STRING_info, that does what `unpackCString# x` does, except it gets the bytes address from the payload. Using this, for the closure above, we generate this: Main.hey_closure" { Main.hey_closure: const stg_MK_STRING_info; const 0; // padding for indirectee const 0; // static link const 0; // saved info const hey1_r1Gg_bytes; // the payload } This is much smaller in code. Metric Decrease: T10421 T11195 T12150 T12425 T16577 T18282 T18698a T18698b Co-Authored By: Ben Gamari <ben at well-typed.com> - - - - - 1937016b by Andreas Klebinger at 2022-10-22T07:42:06-04:00 hadrian: Improve error for wrong key/value errors. - - - - - 3d3e85ab by Vladislav Zavialov at 2022-10-22T23:04:06+03:00 Class layout info - - - - - 11fe42d8 by Vladislav Zavialov at 2022-10-23T00:11:50+03:00 Class layout info (#19623) Updates the haddock submodule. - - - - - f0a90c11 by Sven Tennie at 2022-10-24T00:12:51-04:00 Pin used way for test cloneMyStack (#21977) cloneMyStack checks the order of closures on the cloned stack. This may change for different ways. Thus we limit this test to one way (normal). - - - - - 0614e74d by Aaron Allen at 2022-10-24T17:11:21+02:00 Convert Diagnostics in GHC.Tc.Gen.Splice (#20116) Replaces uses of `TcRnUnknownMessage` in `GHC.Tc.Gen.Splice` with structured diagnostics. closes #20116 - - - - - 8d2dbe2d by Andreas Klebinger at 2022-10-24T15:59:41-04:00 Improve stg lint for unboxed sums. It now properly lints cases where sums end up distributed over multiple args after unarise. Fixes #22026. - - - - - 41406da5 by Simon Peyton Jones at 2022-10-25T18:07:03-04:00 Fix binder-swap bug This patch fixes #21229 properly, by avoiding doing a binder-swap on dictionary Ids. This is pretty subtle, and explained in Note [Care with binder-swap on dictionaries]. Test is already in simplCore/should_run/T21229 This allows us to restore a feature to the specialiser that we had to revert: see Note [Specialising polymorphic dictionaries]. (This is done in a separate patch.) I also modularised things, using a new function scrutBinderSwap_maybe in all the places where we are (effectively) doing a binder-swap, notably * Simplify.Iteration.addAltUnfoldings * SpecConstr.extendCaseBndrs In Simplify.Iteration.addAltUnfoldings I also eliminated a guard Many <- idMult case_bndr because we concluded, in #22123, that it was doing no good. - - - - - 5a997e16 by Simon Peyton Jones at 2022-10-25T18:07:03-04:00 Make the specialiser handle polymorphic specialisation Ticket #13873 unexpectedly showed that a SPECIALISE pragma made a program run (a lot) slower, because less specialisation took place overall. It turned out that the specialiser was missing opportunities because of quantified type variables. It was quite easy to fix. The story is given in Note [Specialising polymorphic dictionaries] Two other minor fixes in the specialiser * There is no benefit in specialising data constructor /wrappers/. (They can appear overloaded because they are given a dictionary to store in the constructor.) Small guard in canSpecImport. * There was a buglet in the UnspecArg case of specHeader, in the case where there is a dead binder. We need a LitRubbish filler for the specUnfolding stuff. I expanded Note [Drop dead args from specialisations] to explain. There is a 4% increase in compile time for T15164, because we generate more specialised code. This seems OK. Metric Increase: T15164 - - - - - 7f203d00 by Sylvain Henry at 2022-10-25T18:07:43-04:00 Numeric exceptions: replace FFI calls with primops ghc-bignum needs a way to raise numerical exceptions defined in base package. At the time we used FFI calls into primops defined in the RTS. These FFI calls had to be wrapped into hacky bottoming functions because "foreign import prim" syntax doesn't support giving a bottoming demand to the foreign call (cf #16929). These hacky wrapper functions trip up the JavaScript backend (#21078) because they are polymorphic in their return type. This commit replaces them with primops very similar to raise# but raising predefined exceptions. - - - - - 0988a23d by Sylvain Henry at 2022-10-25T18:08:24-04:00 Enable popcount rewrite rule when cross-compiling The comment applies only when host's word size < target's word size. So we can relax the guard. - - - - - a2f53ac8 by Sylvain Henry at 2022-10-25T18:09:05-04:00 Add GHC.SysTools.Cpp module Move doCpp out of the driver to be able to use it in the upcoming JS backend. - - - - - 1fd7f201 by Ben Gamari at 2022-10-25T18:09:42-04:00 llvm-targets: Add datalayouts for big-endian AArch64 targets Fixes #22311. Thanks to @zeldin for the patch. - - - - - f5a486eb by Krzysztof Gogolewski at 2022-10-25T18:10:19-04:00 Cleanup String/FastString conversions Remove unused mkPtrString and isUnderscoreFS. We no longer use mkPtrString since 1d03d8bef96. Remove unnecessary conversions between FastString and String and back. - - - - - cbde4cb0 by Simon Peyton Jones at 2022-10-25T23:19:18+01:00 Adapt to Constraint-vs-Type See haskell/haddock#21623 and !8750 - - - - - f7bfb40c by Ryan Scott at 2022-10-26T00:01:24-04:00 Broaden the in-scope sets for liftEnvSubst and composeTCvSubst This patch fixes two distinct (but closely related) buglets that were uncovered in #22235: * `liftEnvSubst` used an empty in-scope set, which was not wide enough to cover the variables in the range of the substitution. This patch fixes this by populating the in-scope set from the free variables in the range of the substitution. * `composeTCvSubst` applied the first substitution argument to the range of the second substitution argument, but the first substitution's in-scope set was not wide enough to cover the range of the second substutition. We similarly fix this issue in this patch by widening the first substitution's in-scope set before applying it. Fixes #22235. - - - - - 0270cc54 by Vladislav Zavialov at 2022-10-26T00:02:01-04:00 Introduce TcRnWithHsDocContext (#22346) Before this patch, GHC used withHsDocContext to attach an HsDocContext to an error message: addErr $ mkTcRnUnknownMessage $ mkPlainError noHints (withHsDocContext ctxt msg) The problem with this approach is that it only works with TcRnUnknownMessage. But could we attach an HsDocContext to a structured error message in a generic way? This patch solves the problem by introducing a new constructor to TcRnMessage: data TcRnMessage where ... TcRnWithHsDocContext :: !HsDocContext -> !TcRnMessage -> TcRnMessage ... - - - - - 9ab31f42 by Sylvain Henry at 2022-10-26T09:32:20+02:00 Testsuite: more precise test options Necessary for newer cross-compiling backends (JS, Wasm) that don't support TH yet. - - - - - f60a1a62 by Vladislav Zavialov at 2022-10-26T12:17:14-04:00 Use TcRnVDQInTermType in noNestedForallsContextsErr (#20115) When faced with VDQ in the type of a term, GHC generates the following error message: Illegal visible, dependent quantification in the type of a term (GHC does not yet support this) Prior to this patch, there were two ways this message could have been generated and represented: 1. with the dedicated constructor TcRnVDQInTermType (see check_type in GHC.Tc.Validity) 2. with the transitional constructor TcRnUnknownMessage (see noNestedForallsContextsErr in GHC.Rename.Utils) Not only this led to duplication of code generating the final SDoc, it also made it tricky to track the origin of the error message. This patch fixes the problem by using TcRnVDQInTermType exclusively. - - - - - 223e159d by Owen Shepherd at 2022-10-27T13:54:33-04:00 Remove source location information from interface files This change aims to minimize source location information leaking into interface files, which makes ABI hashes dependent on the build location. The `Binary (Located a)` instance has been removed completely. It seems that the HIE interface still needs the ability to serialize SrcSpans, but by wrapping the instances, it should be a lot more difficult to inadvertently add source location information. - - - - - 22e3deb9 by Simon Peyton Jones at 2022-10-27T13:55:37-04:00 Add missing dict binds to specialiser I had forgotten to add the auxiliary dict bindings to the /unfolding/ of a specialised function. This caused #22358, which reports failures when compiling Hackage packages fixed-vector indexed-traversable Regression test T22357 is snarfed from indexed-traversable - - - - - a8ed36f9 by Evan Relf at 2022-10-27T13:56:36-04:00 Fix broken link to `async` package - - - - - 750846cd by Zubin Duggal at 2022-10-28T00:49:22-04:00 Pass correct package db when testing stage1. It used to pick the db for stage-2 which obviously didn't work. - - - - - ad612f55 by Krzysztof Gogolewski at 2022-10-28T00:50:00-04:00 Minor SDoc-related cleanup * Rename pprCLabel to pprCLabelStyle, and use the name pprCLabel for a function using CStyle (analogous to pprAsmLabel) * Move LabelStyle to the CLabel module, it no longer needs to be in Outputable. * Move calls to 'text' right next to literals, to make sure the text/str rule is triggered. * Remove FastString/String roundtrip in Tc.Deriv.Generate * Introduce showSDocForUser', which abstracts over a pattern in GHCi.UI - - - - - c2872f3f by Bryan Richter at 2022-10-28T11:36:34+03:00 CI: Don't run lint-submods on nightly Fixes #22325 - - - - - 270037fa by Hécate Moonlight at 2022-10-28T19:46:12-04:00 Start the deprecation process for GHC.Pack - - - - - d45d8cb3 by M Farkas-Dyck at 2022-11-01T12:47:21-04:00 Drop a kludge for binutils<2.17, which is now over 10 years old. - - - - - 8ee8b418 by Nicolas Trangez at 2022-11-01T12:47:58-04:00 rts: `name` argument of `createOSThread` can be `const` Since we don't intend to ever change the incoming string, declare this to be true. Also, in the POSIX implementation, the argument is no longer `STG_UNUSED` (since ee0deb8054da2a597fc5624469b4c44fd769ada2) in any code path. See: https://gitlab.haskell.org/ghc/ghc/-/commit/ee0deb8054da2a597fc5624469b4c44fd769ada2#note_460080 - - - - - 13b5f102 by Nicolas Trangez at 2022-11-01T12:47:58-04:00 rts: fix lifetime of `start_thread`s `name` value Since, unlike the code in ee0deb8054da2^, usage of the `name` value passed to `createOSThread` now outlives said function's lifetime, and could hence be released by the caller by the time the new thread runs `start_thread`, it needs to be copied. See: https://gitlab.haskell.org/ghc/ghc/-/commit/ee0deb8054da2a597fc5624469b4c44fd769ada2#note_460080 See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/9066 - - - - - edd175c9 by Nicolas Trangez at 2022-11-01T12:47:58-04:00 rts: fix OS thread naming in ticker Since ee0deb805, the use of `pthread_setname_np` on Darwin was fixed when invoking `createOSThread`. However, the 'ticker' has some thread-creation code which doesn't rely on `createOSThread`, yet also uses `pthread_setname_np`. This patch enforces all thread creation to go through a single function, which uses the (correct) thread-naming code introduced in ee0deb805. See: https://gitlab.haskell.org/ghc/ghc/-/commit/ee0deb8054da2a597fc5624469b4c44fd769ada2 See: https://gitlab.haskell.org/ghc/ghc/-/issues/22206 See: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/9066 - - - - - b7a00113 by Krzysztof Gogolewski at 2022-11-01T12:48:35-04:00 Typo: rename -fwrite-if-simplfied-core to -fwrite-if-simplified-core - - - - - 30e625e6 by Vladislav Zavialov at 2022-11-01T12:49:10-04:00 ThToHs: fix overzealous parenthesization Before this patch, when converting from TH.Exp to LHsExpr GhcPs, the compiler inserted more parentheses than required: ((f a) (b + c)) d This was happening because the LHS of the function application was parenthesized as if it was the RHS. Now we use funPrec and appPrec appropriately and produce sensibly parenthesized expressions: f a (b + c) d I also took the opportunity to remove the special case for LamE, which was not special at all and simply duplicated code. - - - - - 0560821f by Simon Peyton Jones at 2022-11-01T12:49:47-04:00 Add accurate skolem info when quantifying Ticket #22379 revealed that skolemiseQuantifiedTyVar was dropping the passed-in skol_info on the floor when it encountered a SkolemTv. Bad! Several TyCons thereby share a single SkolemInfo on their binders, which lead to bogus error reports. - - - - - 38d19668 by Fendor at 2022-11-01T12:50:25-04:00 Expose UnitEnvGraphKey for user-code - - - - - 77e24902 by Simon Peyton Jones at 2022-11-01T12:51:00-04:00 Shrink test case for #22357 Ryan Scott offered a cut-down repro case (60 lines instead of more than 700 lines) - - - - - 4521f649 by Simon Peyton Jones at 2022-11-01T12:51:00-04:00 Add two tests for #17366 - - - - - 7108ba96 by Tom Smeding at 2022-11-01T22:33:23+01:00 Remove outdated footnote about module re-exports The footnote is invalid with GHC 9.2.4 (and possibly earlier): the described behaviour in the main text works fine. - - - - - 206c6bc7 by Hécate Moonlight at 2022-11-01T23:00:46+01:00 Merge pull request haskell/haddock#1534 from tomsmeding/patch-1 - - - - - 6b400d26 by Nicolas Trangez at 2022-11-02T12:06:48-04:00 rts: introduce (and use) `STG_NORETURN` Instead of sprinkling the codebase with `GNU(C3)_ATTRIBUTE(__noreturn__)`, add a `STG_NORETURN` macro (for, basically, the same thing) similar to `STG_UNUSED` and others, and update the code to use this macro where applicable. - - - - - f9638654 by Nicolas Trangez at 2022-11-02T12:06:48-04:00 rts: consistently use `STG_UNUSED` - - - - - 81a58433 by Nicolas Trangez at 2022-11-02T12:06:48-04:00 rts: introduce (and use) `STG_USED` Similar to `STG_UNUSED`, have a specific macro for `__attribute__(used)`. - - - - - 41e1f748 by Nicolas Trangez at 2022-11-02T12:06:48-04:00 rts: introduce (and use) `STG_MALLOC` Instead of using `GNUC3_ATTRIBUTE(__malloc__)`, provide a `STG_MALLOC` macro definition and use it instead. - - - - - 3a9a8bde by Nicolas Trangez at 2022-11-02T12:06:48-04:00 rts: use `STG_UNUSED` - - - - - 9ab999de by Nicolas Trangez at 2022-11-02T12:06:48-04:00 rts: specify deallocator of allocating functions This patch adds a new `STG_MALLOC1` macro (and its counterpart `STG_MALLOC2` for completeness) which allows to specify the deallocation function to be used with allocations of allocating functions, and applies it to `stg*allocBytes`. It also fixes a case where `free` was used to free up an `stgMallocBytes` allocation, found by the above change. See: https://gcc.gnu.org/onlinedocs/gcc/Common-Function-Attributes.html#index-malloc-function-attribute See: https://gitlab.haskell.org/ghc/ghc/-/issues/22381 - - - - - 81c0c7c9 by Nicolas Trangez at 2022-11-02T12:06:48-04:00 rts: use `alloc_size` attribute This patch adds the `STG_ALLOC_SIZE1` and `STG_ALLOC_SIZE2` macros which allow to set the `alloc_size` attribute on functions, when available. See: https://gcc.gnu.org/onlinedocs/gcc/Common-Function-Attributes.html#index-alloc_005fsize-function-attribute See: https://gitlab.haskell.org/ghc/ghc/-/issues/22381 - - - - - 99a1d896 by Nicolas Trangez at 2022-11-02T12:06:48-04:00 rts: add and use `STG_RETURNS_NONNULL` See: https://gcc.gnu.org/onlinedocs/gcc/Common-Function-Attributes.html#index-returns_005fnonnull-function-attribute See: https://gitlab.haskell.org/ghc/ghc/-/issues/22381 - - - - - c235b399 by Nicolas Trangez at 2022-11-02T12:06:48-04:00 rts: tag `stgStrndup` as `STG_MALLOC` See: https://gitlab.haskell.org/ghc/ghc/-/issues/22381 - - - - - ed81b448 by Oleg Grenrus at 2022-11-02T12:07:27-04:00 Move Symbol implementation note out of public haddock - - - - - 284fd39c by Ben Gamari at 2022-11-03T01:58:54-04:00 gen-dll: Drop it Currently it is only used by the make build system, which is soon to be retired, and it has not built since 41cf758b. We may need to reintroduce it when dynamic-linking support is introduced on Windows, but we will cross that bridge once we get there. Fixes #21753. - - - - - 24f4f54f by Matthew Pickering at 2022-11-03T01:59:30-04:00 Port foundation numeric tests to GHC testsuite This commit ports the numeric tests which found a regression in GHC-9.4. https://github.com/haskell-foundation/foundation/issues/571 Included in the commit is a simple random number generator and simplified QuickCheck implementation. In future these could be factored out of this standalone file and reused as a general purpose library which could be used for other QuickCheck style tests in the testsuite. See #22282 - - - - - d51bf7bd by M Farkas-Dyck at 2022-11-03T02:00:13-04:00 git: ignore HIE files. Cleans up git status if one sets -fwrite-ide-info in hadrian/ghci. - - - - - a9fc15b1 by Matthew Pickering at 2022-11-03T02:00:49-04:00 Clarify status of bindings in WholeCoreBindings Gergo points out that these bindings are tidied, rather than prepd as the variable claims. Therefore we update the name of the variable to reflect reality and add a comment to the data type to try to erase any future confusion. Fixes #22307 - - - - - 634da448 by Andrew Lelechenko at 2022-11-03T21:25:02+00:00 Fix haddocks for GHC.IORef - - - - - 31125154 by Andreas Klebinger at 2022-11-03T23:08:09-04:00 Export pprTrace and friends from GHC.Prelude. Introduces GHC.Prelude.Basic which can be used in modules which are a dependency of the ppr code. - - - - - bdc8cbb3 by Bryan Richter at 2022-11-04T10:27:37+02:00 CI: Allow hadrian-ghc-in-ghci to run in nightlies Since lint-submods doesn't run in nightlies, hadrian-ghc-in-ghci needs to mark it as "optional" so it can run if the job doesn't exist. Fixes #22396. - - - - - 3c0e3793 by Krzysztof Gogolewski at 2022-11-05T00:29:57-04:00 Minor refactor around FastStrings Pass FastStrings to functions directly, to make sure the rule for fsLit "literal" fires. Remove SDoc indirection in GHCi.UI.Tags and GHC.Unit.Module.Graph. - - - - - e41b2f55 by Matthew Pickering at 2022-11-05T14:18:10+00:00 Bump unix submodule to 2.8.0.0 Also bumps process and ghc-boot bounds on unix. For hadrian, when cross-compiling, we add -Wwarn=unused-imports -Wwarn=unused-top-binds to validation flavour. Further fixes in unix and/or hsc2hs is needed to make it completely free of warnings; for the time being, this change is needed to unblock other cross-compilation related work. - - - - - 42938a58 by Matthew Pickering at 2022-11-05T14:18:10+00:00 Bump Win32 submodule to 2.13.4.0 Fixes #22098 - - - - - e7372bc5 by Cheng Shao at 2022-11-06T13:15:22+00:00 Bump ci-images revision ci-images has recently been updated, including changes needed for wasm32-wasi CI. - - - - - 88cb9492 by Cheng Shao at 2022-11-06T13:15:22+00:00 Bump gmp-tarballs submodule Includes a fix for wasm support, doesn't impact other targets. - - - - - 69427ce9 by Cheng Shao at 2022-11-06T13:15:22+00:00 Bump haskeline submodule Includes a fix for wasm support, doesn't impact other targets. - - - - - 5fe11fe6 by Carter Schonwald at 2022-11-07T13:22:14-05:00 bump llvm upper bound - - - - - 68f49874 by M Farkas-Dyck at 2022-11-08T12:53:55-05:00 Define `Infinite` list and use where appropriate. Also add perf test for infinite list fusion. In particular, in `GHC.Core`, often we deal with infinite lists of roles. Also in a few locations we deal with infinite lists of names. Thanks to simonpj for helping to write the Note [Fusion for `Infinite` lists]. - - - - - ce726cd2 by Ross Paterson at 2022-11-08T12:54:34-05:00 Fix TypeData issues (fixes #22315 and #22332) There were two bugs here: 1. Treating type-level constructors as PromotedDataCon doesn't always work, in particular because constructors promoted via DataKinds are called both T and 'T. (Tests T22332a, T22332b, T22315a, T22315b) Fix: guard these cases with isDataKindsPromotedDataCon. 2. Type-level constructors were sent to the code generator, producing things like constructor wrappers. (Tests T22332a, T22332b) Fix: test for them in isDataTyCon. Other changes: * changed the marking of "type data" DataCon's as suggested by SPJ. * added a test TDGADT for a type-level GADT. * comment tweaks * change tcIfaceTyCon to ignore IfaceTyConInfo, so that IfaceTyConInfo is used only for pretty printing, not for typechecking. (SPJ) - - - - - 132f8908 by Jade Lovelace at 2022-11-08T12:55:18-05:00 Clarify msum/asum documentation - - - - - bb5888c5 by Jade Lovelace at 2022-11-08T12:55:18-05:00 Add example for (<$) - - - - - 080fffa1 by Jade Lovelace at 2022-11-08T12:55:18-05:00 Document what Alternative/MonadPlus instances actually do - - - - - 92ccb8de by Giles Anderson at 2022-11-09T09:27:52-05:00 Use TcRnDiagnostic in GHC.Tc.TyCl.Instance (#20117) The following `TcRnDiagnostic` messages have been introduced: TcRnWarnUnsatisfiedMinimalDefinition TcRnMisplacedInstSig TcRnBadBootFamInstDeclErr TcRnIllegalFamilyInstance TcRnAssocInClassErr TcRnBadFamInstDecl TcRnNotOpenFamily - - - - - 90c5abd4 by Hécate Moonlight at 2022-11-09T09:28:30-05:00 GHCi tags generation phase 2 see #19884 - - - - - f9f17b68 by Simon Peyton Jones at 2022-11-10T12:20:03+00:00 Fire RULES in the Specialiser The Specialiser has, for some time, fires class-op RULES in the specialiser itself: see Note [Specialisation modulo dictionary selectors] This MR beefs it up a bit, so that it fires /all/ RULES in the specialiser, not just class-op rules. See Note [Fire rules in the specialiser] The result is a bit more specialisation; see test simplCore/should_compile/T21851_2 This pushed me into a bit of refactoring. I made a new data types GHC.Core.Rules.RuleEnv, which combines - the several source of rules (local, home-package, external) - the orphan-module dependencies in a single record for `getRules` to consult. That drove a bunch of follow-on refactoring, including allowing me to remove cr_visible_orphan_mods from the CoreReader data type. I moved some of the RuleBase/RuleEnv stuff into GHC.Core.Rule. The reorganisation in the Simplifier improve compile times a bit (geom mean -0.1%), but T9961 is an outlier Metric Decrease: T9961 - - - - - 2b3d0bee by Simon Peyton Jones at 2022-11-10T12:21:13+00:00 Make indexError work better The problem here is described at some length in Note [Boxity for bottoming functions] and Note [Reboxed crud for bottoming calls] in GHC.Core.Opt.DmdAnal. This patch adds a SPECIALISE pragma for indexError, which makes it much less vulnerable to the problem described in these Notes. (This came up in another line of work, where a small change made indexError do reboxing (in nofib/spectral/simple/table_sort) that didn't happen before my change. I've opened #22404 to document the fagility. - - - - - 399e921b by Simon Peyton Jones at 2022-11-10T12:21:14+00:00 Fix DsUselessSpecialiseForClassMethodSelector msg The error message for DsUselessSpecialiseForClassMethodSelector was just wrong (a typo in some earlier work); trivial fix - - - - - dac0682a by Sebastian Graf at 2022-11-10T21:16:01-05:00 WorkWrap: Unboxing unboxed tuples is not always useful (#22388) See Note [Unboxing through unboxed tuples]. Fixes #22388. - - - - - 1230c268 by Sebastian Graf at 2022-11-10T21:16:01-05:00 Boxity: Handle argument budget of unboxed tuples correctly (#21737) Now Budget roughly tracks the combined width of all arguments after unarisation. See the changes to `Note [Worker argument budgets]`. Fixes #21737. - - - - - 2829fd92 by Cheng Shao at 2022-11-11T00:26:54-05:00 autoconf: check getpid getuid raise This patch adds checks for getpid, getuid and raise in autoconf. These functions are absent in wasm32-wasi and thus needs to be checked. - - - - - f5dfd1b4 by Cheng Shao at 2022-11-11T00:26:55-05:00 hadrian: add -Wwarn only for cross-compiling unix - - - - - 2e6ab453 by Cheng Shao at 2022-11-11T00:26:55-05:00 hadrian: add targetSupportsThreadedRts flag This patch adds a targetSupportsThreadedRts flag to indicate whether the target supports the threaded rts at all, different from existing targetSupportsSMP that checks whether -N is supported by the RTS. All existing flavours have also been updated accordingly to respect this flags. Some targets (e.g. wasm32-wasi) does not support the threaded rts, therefore this flag is needed for the default flavours to work. It makes more sense to have proper autoconf logic to check for threading support, but for the time being, we just set the flag to False iff the target is wasm32. - - - - - 8104f6f5 by Cheng Shao at 2022-11-11T00:26:55-05:00 Fix Cmm symbol kind - - - - - b2035823 by Norman Ramsey at 2022-11-11T00:26:55-05:00 add the two key graph modules from Martin Erwig's FGL Martin Erwig's FGL (Functional Graph Library) provides an "inductive" representation of graphs. A general graph has labeled nodes and labeled edges. The key operation on a graph is to decompose it by removing one node, together with the edges that connect the node to the rest of the graph. There is also an inverse composition operation. The decomposition and composition operations make this representation of graphs exceptionally well suited to implement graph algorithms in which the graph is continually changing, as alluded to in #21259. This commit adds `GHC.Data.Graph.Inductive.Graph`, which defines the interface, and `GHC.Data.Graph.Inductive.PatriciaTree`, which provides an implementation. Both modules are taken from `fgl-5.7.0.3` on Hackage, with these changes: - Copyright and license text have been copied into the files themselves, not stored separately. - Some calls to `error` have been replaced with calls to `panic`. - Conditional-compilation support for older versions of GHC, `containers`, and `base` has been removed. - - - - - 3633a5f5 by Norman Ramsey at 2022-11-11T00:26:55-05:00 add new modules for reducibility and WebAssembly translation - - - - - df7bfef8 by Cheng Shao at 2022-11-11T00:26:55-05:00 Add support for the wasm32-wasi target tuple This patch adds the wasm32-wasi tuple support to various places in the tree: autoconf, hadrian, ghc-boot and also the compiler. The codegen logic will come in subsequent commits. - - - - - 32ae62e6 by Cheng Shao at 2022-11-11T00:26:55-05:00 deriveConstants: parse .ll output for wasm32 due to broken nm This patch makes deriveConstants emit and parse an .ll file when targeting wasm. It's a necessary workaround for broken llvm-nm on wasm, which isn't capable of reporting correct constant values when parsing an object. - - - - - 07e92c92 by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: workaround cmm's improper variadic ccall breaking wasm32 typechecking Unlike other targets, wasm requires the function signature of the call site and callee to strictly match. So in Cmm, when we call a C function that actually returns a value, we need to add an _unused local variable to receive it, otherwise type error awaits. An even bigger problem is calling variadic functions like barf() and such. Cmm doesn't support CAPI calling convention yet, so calls to variadic functions just happen to work in some cases with some target's ABI. But again, it doesn't work with wasm. Fortunately, the wasm C ABI lowers varargs to a stack pointer argument, and it can be passed NULL when no other arguments are expected to be passed. So we also add the additional unused NULL arguments to those functions, so to fix wasm, while not affecting behavior on other targets. - - - - - 00124d12 by Cheng Shao at 2022-11-11T00:26:55-05:00 testsuite: correct sleep() signature in T5611 In libc, sleep() returns an integer. The ccall type signature should match the libc definition, otherwise it causes linker error on wasm. - - - - - d72466a9 by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: prefer ffi_type_void over FFI_TYPE_VOID This patch uses ffi_type_void instead of FFI_TYPE_VOID in the interpreter code, since the FFI_TYPE_* macros are not available in libffi-wasm32 yet. The libffi public documentation also only mentions the lower-case ffi_type_* symbols, so we should prefer the lower-case API here. - - - - - 4d36a1d3 by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: don't define RTS_USER_SIGNALS when signal.h is not present In the rts, we have a RTS_USER_SIGNALS macro, and most signal-related logic is guarded with RTS_USER_SIGNALS. This patch extends the range of code guarded with RTS_USER_SIGNALS, and define RTS_USER_SIGNALS iff signal.h is actually detected by autoconf. This is required for wasm32-wasi to work, which lacks signals. - - - - - 3f1e164f by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: use HAVE_GETPID to guard subprocess related logic We've previously added detection of getpid() in autoconf. This patch uses HAVE_GETPID to guard some subprocess related logic in the RTS. This is required for certain targets like wasm32-wasi, where there isn't a process model at all. - - - - - 50bf5e77 by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: IPE.c: don't do mutex stuff when THREADED_RTS is not defined This patch adds the missing THREADED_RTS CPP guard to mutex logic in IPE.c. - - - - - ed3b3da0 by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: genericRaise: use exit() instead when not HAVE_RAISE We check existence of raise() in autoconf, and here, if not HAVE_RAISE, we should use exit() instead in genericRaise. - - - - - c0ba1547 by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: checkSuid: don't do it when not HAVE_GETUID When getuid() is not present, don't do checkSuid since it doesn't make sense anyway on that target. - - - - - d2d6dfd2 by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: wasm32 placeholder linker This patch adds minimal placeholder linker logic for wasm32, just enough to unblock compiling rts on wasm32. RTS linker functionality is not properly implemented yet for wasm32. - - - - - 65ba3285 by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: RtsStartup: chdir to PWD on wasm32 This patch adds a wasm32-specific behavior to RtsStartup logic. When the PWD environment variable is present, we chdir() to it first. The point is to workaround an issue in wasi-libc: it's currently not possible to specify the initial working directory, it always defaults to / (in the virtual filesystem mapped from some host directory). For some use cases this is sufficient, but there are some other cases (e.g. in the testsuite) where the program needs to access files outside. - - - - - 65b82542 by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: no timer for wasm32 Due to the lack of threads, on wasm32 there can't be a background timer that periodically resets the context switch flag. This patch disables timer for wasm32, and also makes the scheduler default to -C0 on wasm32 to avoid starving threads. - - - - - e007586f by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: RtsSymbols: empty RTS_POSIX_ONLY_SYMBOLS for wasm32 The default RTS_POSIX_ONLY_SYMBOLS doesn't make sense on wasm32. - - - - - 0e33f667 by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: Schedule: no FORKPROCESS_PRIMOP_SUPPORTED on wasm32 On wasm32 there isn't a process model at all, so no FORKPROCESS_PRIMOP_SUPPORTED. - - - - - 88bbdb31 by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: LibffiAdjustor: adapt to ffi_alloc_prep_closure interface for wasm32 libffi-wasm32 only supports non-standard libffi closure api via ffi_alloc_prep_closure(). This patch implements ffi_alloc_prep_closure() via standard libffi closure api on other targets, and uses it to implement adjustor functionality. - - - - - 15138746 by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: don't return memory to OS on wasm32 This patch makes the storage manager not return any memory on wasm32. The detailed reason is described in Note [Megablock allocator on wasm]. - - - - - 631af3cc by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: make flushExec a no-op on wasm32 This patch makes flushExec a no-op on wasm32, since there's no such thing as executable memory on wasm32 in the first place. - - - - - 654a3d46 by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: RtsStartup: don't call resetTerminalSettings, freeThreadingResources on wasm32 This patch prevents resetTerminalSettings and freeThreadingResources to be called on wasm32, since there is no TTY or threading on wasm32 at all. - - - - - f271e7ca by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: OSThreads.h: stub types for wasm32 This patch defines stub Condition/Mutex/OSThreadId/ThreadLocalKey types for wasm32, just enough to unblock compiling RTS. Any threading-related functionality has been patched to be disabled on wasm32. - - - - - a6ac67b0 by Cheng Shao at 2022-11-11T00:26:55-05:00 Add register mapping for wasm32 This patch adds register mapping logic for wasm32. See Note [Register mapping on WebAssembly] in wasm32 NCG for more description. - - - - - d7b33982 by Cheng Shao at 2022-11-11T00:26:55-05:00 rts: wasm32 specific logic This patch adds the rest of wasm32 specific logic in rts. - - - - - 7f59b0f3 by Cheng Shao at 2022-11-11T00:26:55-05:00 base: fall back to using monotonic clock to emulate cputime on wasm32 On wasm32, we have to fall back to using monotonic clock to emulate cputime, since there's no native support for cputime as a clock id. - - - - - 5fcbae0b by Cheng Shao at 2022-11-11T00:26:55-05:00 base: more autoconf checks for wasm32 This patch adds more autoconf checks to base, since those functions and headers may exist on other POSIX systems but don't exist on wasm32. - - - - - 00a9359f by Cheng Shao at 2022-11-11T00:26:55-05:00 base: avoid using unsupported posix functionality on wasm32 This base patch avoids using unsupported posix functionality on wasm32. - - - - - 34b8f611 by Cheng Shao at 2022-11-11T00:26:55-05:00 autoconf: set CrossCompiling=YES in cross bindist configure This patch fixes the bindist autoconf logic to properly set CrossCompiling=YES when it's a cross GHC bindist. - - - - - 5ebeaa45 by Cheng Shao at 2022-11-11T00:26:55-05:00 compiler: add util functions for UniqFM and UniqMap This patch adds addToUFM_L (backed by insertLookupWithKey), addToUniqMap_L and intersectUniqMap_C. These UniqFM/UniqMap util functions are used by the wasm32 NCG. - - - - - 177c56c1 by Cheng Shao at 2022-11-11T00:26:55-05:00 driver: avoid -Wl,--no-as-needed for wasm32 The driver used to pass -Wl,--no-as-needed for LLD linking. This is actually only supported for ELF targets, and must be avoided when linking for wasm32. - - - - - 06f01c74 by Cheng Shao at 2022-11-11T00:26:55-05:00 compiler: allow big arith for wasm32 This patch enables Cmm big arithmetic on wasm32, since 64-bit arithmetic can be efficiently lowered to wasm32 opcodes. - - - - - df6bb112 by Cheng Shao at 2022-11-11T00:26:55-05:00 driver: pass -Wa,--no-type-check for wasm32 when runAsPhase This patch passes -Wa,--no-type-check for wasm32 when compiling assembly. See the added note for more detailed explanation. - - - - - c1fe4ab6 by Cheng Shao at 2022-11-11T00:26:55-05:00 compiler: enforce cmm switch planning for wasm32 This patch forcibly enable Cmm switch planning for wasm32, since otherwise the switch tables we generate may exceed the br_table maximum allowed size. - - - - - a8adc71e by Cheng Shao at 2022-11-11T00:26:55-05:00 compiler: annotate CmmFileEmbed with blob length This patch adds the blob length field to CmmFileEmbed. The wasm32 NCG needs to know the precise size of each data segment. - - - - - 36340328 by Cheng Shao at 2022-11-11T00:26:55-05:00 compiler: wasm32 NCG This patch adds the wasm32 NCG. - - - - - 435f42ea by Cheng Shao at 2022-11-11T00:26:55-05:00 ci: add wasm32-wasi release bindist job - - - - - d8262fdc by Cheng Shao at 2022-11-11T00:26:55-05:00 ci: add a stronger test for cross bindists This commit adds a simple GHC API program that parses and reprints the original hello world program used for basic testing of cross bindists. Before there's full cross-compilation support in the test suite driver, this provides better coverage than the original test. - - - - - 8e6ae882 by Cheng Shao at 2022-11-11T00:26:55-05:00 CODEOWNERS: add wasm-specific maintainers - - - - - 707d5651 by Zubin Duggal at 2022-11-11T00:27:31-05:00 Clarify that LLVM upper bound is non-inclusive during configure (#22411) - - - - - 430eccef by Ben Gamari at 2022-11-11T13:16:45-05:00 rts: Check for program_invocation_short_name via autoconf Instead of assuming support on all Linuxes. - - - - - 6dab0046 by Matthew Pickering at 2022-11-11T13:17:22-05:00 driver: Fix -fdefer-diagnostics flag The `withDeferredDiagnostics` wrapper wasn't doing anything because the session it was modifying wasn't used in hsc_env. Therefore the fix is simple, just push the `getSession` call into the scope of `withDeferredDiagnostics`. Fixes #22391 - - - - - d0c691b6 by Simon Peyton Jones at 2022-11-11T13:18:07-05:00 Add a fast path for data constructor workers See Note [Fast path for data constructors] in GHC.Core.Opt.Simplify.Iteration This bypasses lots of expensive logic, in the special case of applications of data constructors. It is a surprisingly worthwhile improvement, as you can see in the figures below. Metrics: compile_time/bytes allocated ------------------------------------------------ CoOpt_Read(normal) -2.0% CoOpt_Singletons(normal) -2.0% ManyConstructors(normal) -1.3% T10421(normal) -1.9% GOOD T10421a(normal) -1.5% T10858(normal) -1.6% T11545(normal) -1.7% T12234(optasm) -1.3% T12425(optasm) -1.9% GOOD T13035(normal) -1.0% GOOD T13056(optasm) -1.8% T13253(normal) -3.3% GOOD T15164(normal) -1.7% T15304(normal) -3.4% T15630(normal) -2.8% T16577(normal) -4.3% GOOD T17096(normal) -1.1% T17516(normal) -3.1% T18282(normal) -1.9% T18304(normal) -1.2% T18698a(normal) -1.2% GOOD T18698b(normal) -1.5% GOOD T18923(normal) -1.3% T1969(normal) -1.3% GOOD T19695(normal) -4.4% GOOD T21839c(normal) -2.7% GOOD T21839r(normal) -2.7% GOOD T4801(normal) -3.8% GOOD T5642(normal) -3.1% GOOD T6048(optasm) -2.5% GOOD T9020(optasm) -2.7% GOOD T9630(normal) -2.1% GOOD T9961(normal) -11.7% GOOD WWRec(normal) -1.0% geo. mean -1.1% minimum -11.7% maximum +0.1% Metric Decrease: T10421 T12425 T13035 T13253 T16577 T18698a T18698b T1969 T19695 T21839c T21839r T4801 T5642 T6048 T9020 T9630 T9961 - - - - - 3c37d30b by Krzysztof Gogolewski at 2022-11-11T19:18:39+01:00 Use a more efficient printer for code generation (#21853) The changes in `GHC.Utils.Outputable` are the bulk of the patch and drive the rest. The types `HLine` and `HDoc` in Outputable can be used instead of `SDoc` and support printing directly to a handle with `bPutHDoc`. See Note [SDoc versus HDoc] and Note [HLine versus HDoc]. The classes `IsLine` and `IsDoc` are used to make the existing code polymorphic over `HLine`/`HDoc` and `SDoc`. This is done for X86, PPC, AArch64, DWARF and dependencies (printing module names, labels etc.). Co-authored-by: Alexis King <lexi.lambda at gmail.com> Metric Decrease: CoOpt_Read ManyAlternatives ManyConstructors T10421 T12425 T12707 T13035 T13056 T13253 T13379 T18140 T18282 T18698a T18698b T1969 T20049 T21839c T21839r T3064 T3294 T4801 T5321FD T5321Fun T5631 T6048 T783 T9198 T9233 - - - - - 6b92b47f by Matthew Craven at 2022-11-11T18:32:14-05:00 Weaken wrinkle 1 of Note [Scrutinee Constant Folding] Fixes #22375. Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> - - - - - 154c70f6 by Simon Peyton Jones at 2022-11-11T23:40:10+00:00 Fix fragile RULE setup in GHC.Float In testing my type-vs-constraint patch I found that the handling of Natural literals was very fragile -- and I somehow tripped that fragility in my work. So this patch fixes the fragility. See Note [realToFrac natural-to-float] This made a big (9%) difference in one existing test in perf/should_run/T1-359 Metric Decrease: T10359 - - - - - 778c6adc by Simon Peyton Jones at 2022-11-11T23:40:10+00:00 Type vs Constraint: finally nailed This big patch addresses the rats-nest of issues that have plagued us for years, about the relationship between Type and Constraint. See #11715/#21623. The main payload of the patch is: * To introduce CONSTRAINT :: RuntimeRep -> Type * To make TYPE and CONSTRAINT distinct throughout the compiler Two overview Notes in GHC.Builtin.Types.Prim * Note [TYPE and CONSTRAINT] * Note [Type and Constraint are not apart] This is the main complication. The specifics * New primitive types (GHC.Builtin.Types.Prim) - CONSTRAINT - ctArrowTyCon (=>) - tcArrowTyCon (-=>) - ccArrowTyCon (==>) - funTyCon FUN -- Not new See Note [Function type constructors and FunTy] and Note [TYPE and CONSTRAINT] * GHC.Builtin.Types: - New type Constraint = CONSTRAINT LiftedRep - I also stopped nonEmptyTyCon being built-in; it only needs to be wired-in * Exploit the fact that Type and Constraint are distinct throughout GHC - Get rid of tcView in favour of coreView. - Many tcXX functions become XX functions. e.g. tcGetCastedTyVar --> getCastedTyVar * Kill off Note [ForAllTy and typechecker equality], in (old) GHC.Tc.Solver.Canonical. It said that typechecker-equality should ignore the specified/inferred distinction when comparein two ForAllTys. But that wsa only weakly supported and (worse) implies that we need a separate typechecker equality, different from core equality. No no no. * GHC.Core.TyCon: kill off FunTyCon in data TyCon. There was no need for it, and anyway now we have four of them! * GHC.Core.TyCo.Rep: add two FunTyFlags to FunCo See Note [FunCo] in that module. * GHC.Core.Type. Lots and lots of changes driven by adding CONSTRAINT. The key new function is sORTKind_maybe; most other changes are built on top of that. See also `funTyConAppTy_maybe` and `tyConAppFun_maybe`. * Fix a longstanding bug in GHC.Core.Type.typeKind, and Core Lint, in kinding ForAllTys. See new tules (FORALL1) and (FORALL2) in GHC.Core.Type. (The bug was that before (forall (cv::t1 ~# t2). blah), where blah::TYPE IntRep, would get kind (TYPE IntRep), but it should be (TYPE LiftedRep). See Note [Kinding rules for types] in GHC.Core.Type. * GHC.Core.TyCo.Compare is a new module in which we do eqType and cmpType. Of course, no tcEqType any more. * GHC.Core.TyCo.FVs. I moved some free-var-like function into this module: tyConsOfType, visVarsOfType, and occCheckExpand. Refactoring only. * GHC.Builtin.Types. Compiletely re-engineer boxingDataCon_maybe to have one for each /RuntimeRep/, rather than one for each /Type/. This dramatically widens the range of types we can auto-box. See Note [Boxing constructors] in GHC.Builtin.Types The boxing types themselves are declared in library ghc-prim:GHC.Types. GHC.Core.Make. Re-engineer the treatment of "big" tuples (mkBigCoreVarTup etc) GHC.Core.Make, so that it auto-boxes unboxed values and (crucially) types of kind Constraint. That allows the desugaring for arrows to work; it gathers up free variables (including dictionaries) into tuples. See Note [Big tuples] in GHC.Core.Make. There is still work to do here: #22336. But things are better than before. * GHC.Core.Make. We need two absent-error Ids, aBSENT_ERROR_ID for types of kind Type, and aBSENT_CONSTRAINT_ERROR_ID for vaues of kind Constraint. Ditto noInlineId vs noInlieConstraintId in GHC.Types.Id.Make; see Note [inlineId magic]. * GHC.Core.TyCo.Rep. Completely refactor the NthCo coercion. It is now called SelCo, and its fields are much more descriptive than the single Int we used to have. A great improvement. See Note [SelCo] in GHC.Core.TyCo.Rep. * GHC.Core.RoughMap.roughMatchTyConName. Collapse TYPE and CONSTRAINT to a single TyCon, so that the rough-map does not distinguish them. * GHC.Core.DataCon - Mainly just improve documentation * Some significant renamings: GHC.Core.Multiplicity: Many --> ManyTy (easier to grep for) One --> OneTy GHC.Core.TyCo.Rep TyCoBinder --> GHC.Core.Var.PiTyBinder GHC.Core.Var TyCoVarBinder --> ForAllTyBinder AnonArgFlag --> FunTyFlag ArgFlag --> ForAllTyFlag GHC.Core.TyCon TyConTyCoBinder --> TyConPiTyBinder Many functions are renamed in consequence e.g. isinvisibleArgFlag becomes isInvisibleForAllTyFlag, etc * I refactored FunTyFlag (was AnonArgFlag) into a simple, flat data type data FunTyFlag = FTF_T_T -- (->) Type -> Type | FTF_T_C -- (-=>) Type -> Constraint | FTF_C_T -- (=>) Constraint -> Type | FTF_C_C -- (==>) Constraint -> Constraint * GHC.Tc.Errors.Ppr. Some significant refactoring in the TypeEqMisMatch case of pprMismatchMsg. * I made the tyConUnique field of TyCon strict, because I saw code with lots of silly eval's. That revealed that GHC.Settings.Constants.mAX_SUM_SIZE can only be 63, because we pack the sum tag into a 6-bit field. (Lurking bug squashed.) Fixes * #21530 Updates haddock submodule slightly. Performance changes ~~~~~~~~~~~~~~~~~~~ I was worried that compile times would get worse, but after some careful profiling we are down to a geometric mean 0.1% increase in allocation (in perf/compiler). That seems fine. There is a big runtime improvement in T10359 Metric Decrease: LargeRecord MultiLayerModulesTH_OneShot T13386 T13719 Metric Increase: T8095 - - - - - 360f5fec by Simon Peyton Jones at 2022-11-11T23:40:11+00:00 Indent closing "#-}" to silence HLint - - - - - e160cf47 by Krzysztof Gogolewski at 2022-11-12T08:05:28-05:00 Fix merge conflict in T18355.stderr Fixes #22446 - - - - - 294f9073 by Simon Peyton Jones at 2022-11-12T23:14:13+00:00 Fix a trivial typo in dataConNonlinearType Fixes #22416 - - - - - 268a3ce9 by Ben Gamari at 2022-11-14T09:36:57-05:00 eventlog: Ensure that IPE output contains actual info table pointers The refactoring in 866c736e introduced a rather subtle change in the semantics of the IPE eventlog output, changing the eventlog field from encoding info table pointers to "TNTC pointers" (which point to entry code when tables-next-to-code is enabled). Fix this. Fixes #22452. - - - - - d91db679 by Matthew Pickering at 2022-11-14T16:48:10-05:00 testsuite: Add tests for T22347 These are fixed in recent versions but might as well add regression tests. See #22347 - - - - - 8f6c576b by Matthew Pickering at 2022-11-14T16:48:45-05:00 testsuite: Improve output from tests which have failing pre_cmd There are two changes: * If a pre_cmd fails, then don't attempt to run the test. * If a pre_cmd fails, then print the stdout and stderr from running that command (which hopefully has a nice error message). For example: ``` =====> 1 of 1 [0, 0, 0] *** framework failure for test-defaulting-plugin(normal) pre_cmd failed: 2 ** pre_cmd was "$MAKE -s --no-print-directory -C defaulting-plugin package.test-defaulting-plugin TOP={top}". stdout: stderr: DefaultLifted.hs:19:13: error: [GHC-76037] Not in scope: type constructor or class ‘Typ’ Suggested fix: Perhaps use one of these: ‘Type’ (imported from GHC.Tc.Utils.TcType), data constructor ‘Type’ (imported from GHC.Plugins) | 19 | instance Eq Typ where | ^^^ make: *** [Makefile:17: package.test-defaulting-plugin] Error 1 Performance Metrics (test environment: local): ``` Fixes #22329 - - - - - 2b7d5ccc by Madeline Haraj at 2022-11-14T22:44:17+00:00 Implement UNPACK support for sum types. This is based on osa's unpack_sums PR from ages past. The meat of the patch is implemented in dataConArgUnpackSum and described in Note [UNPACK for sum types]. - - - - - 78f7ecb0 by Andreas Klebinger at 2022-11-14T22:20:29-05:00 Expand on the need to clone local binders. Fixes #22402. - - - - - 65ce43cc by Krzysztof Gogolewski at 2022-11-14T22:21:05-05:00 Fix :i Constraint printing "type Constraint = Constraint" Since Constraint became a synonym for CONSTRAINT 'LiftedRep, we need the same code for handling printing as for the synonym Type = TYPE 'LiftedRep. This addresses the same bug as #18594, so I'm reusing the test. - - - - - 94549f8f by ARATA Mizuki at 2022-11-15T21:36:03-05:00 configure: Don't check for an unsupported version of LLVM The upper bound is not inclusive. Fixes #22449 - - - - - 02d3511b by Andrew Lelechenko at 2022-11-15T21:36:41-05:00 Fix capitalization in haddock for TestEquality - - - - - 08bf2881 by Cheng Shao at 2022-11-16T09:16:29+00:00 base: make Foreign.Marshal.Pool use RTS internal arena for allocation `Foreign.Marshal.Pool` used to call `malloc` once for each allocation request. Each `Pool` maintained a list of allocated pointers, and traverses the list to `free` each one of those pointers. The extra O(n) overhead is apparently bad for a `Pool` that serves a lot of small allocation requests. This patch uses the RTS internal arena to implement `Pool`, with these benefits: - Gets rid of the extra O(n) overhead. - The RTS arena is simply a bump allocator backed by the block allocator, each allocation request is likely faster than a libc `malloc` call. Closes #14762 #18338. - - - - - 37cfe3c0 by Krzysztof Gogolewski at 2022-11-16T14:50:06-05:00 Misc cleanup * Replace catMaybes . map f with mapMaybe f * Use concatFS to concatenate multiple FastStrings * Fix documentation of -exclude-module * Cleanup getIgnoreCount in GHCi.UI - - - - - b0ac3813 by Lawton Nichols at 2022-11-19T03:22:14-05:00 Give better errors for code corrupted by Unicode smart quotes (#21843) Previously, we emitted a generic and potentially confusing error during lexical analysis on programs containing smart quotes (“/”/‘/’). This commit adds smart quote-aware lexer errors. - - - - - cb8430f8 by Sebastian Graf at 2022-11-19T03:22:49-05:00 Make OpaqueNo* tests less noisy to unrelated changes - - - - - b1a8af69 by Sebastian Graf at 2022-11-19T03:22:49-05:00 Simplifier: Consider `seq` as a `BoringCtxt` (#22317) See `Note [Seq is boring]` for the rationale. Fixes #22317. - - - - - 9fd11585 by Sebastian Graf at 2022-11-19T03:22:49-05:00 Make T21839c's ghc/max threshold more forgiving - - - - - 4b6251ab by Simon Peyton Jones at 2022-11-19T03:23:24-05:00 Be more careful when reporting unbound RULE binders See Note [Variables unbound on the LHS] in GHC.HsToCore.Binds. Fixes #22471. - - - - - e8f2b80d by Peter Trommler at 2022-11-19T03:23:59-05:00 PPC NCG: Fix generating assembler code Fixes #22479 - - - - - f2f9ef07 by Andrew Lelechenko at 2022-11-20T18:39:30-05:00 Extend documentation for Data.IORef - - - - - ef511b23 by Simon Peyton Jones at 2022-11-20T18:40:05-05:00 Buglet in GHC.Tc.Module.checkBootTyCon This lurking bug used the wrong function to compare two types in GHC.Tc.Module.checkBootTyCon It's hard to trigger the bug, which only came up during !9343, so there's no regression test in this MR. - - - - - 451aeac3 by Andrew Lelechenko at 2022-11-20T18:40:44-05:00 Add since pragmas for c_interruptible_open and hostIsThreaded - - - - - a57b4c4b by Andrew Lelechenko at 2022-11-21T00:39:52+00:00 Support mtl-2.3 - - - - - 8d6aaa49 by Duncan Coutts at 2022-11-22T02:06:16-05:00 Introduce CapIOManager as the per-cap I/O mangager state Rather than each I/O manager adding things into the Capability structure ad-hoc, we should have a common CapIOManager iomgr member of the Capability structure, with a common interface to initialise etc. The content of the CapIOManager struct will be defined differently for each I/O manager implementation. Eventually we should be able to have the CapIOManager be opaque to the rest of the RTS, and known just to the I/O manager implementation. We plan for that by making the Capability contain a pointer to the CapIOManager rather than containing the structure directly. Initially just move the Unix threaded I/O manager's control FD. - - - - - 8901285e by Duncan Coutts at 2022-11-22T02:06:17-05:00 Add hook markCapabilityIOManager To allow I/O managers to have GC roots in the Capability, within the CapIOManager structure. Not yet used in this patch. - - - - - 5cf709c5 by Duncan Coutts at 2022-11-22T02:06:17-05:00 Move APPEND_TO_BLOCKED_QUEUE from cmm to C The I/O and delay blocking primitives for the non-threaded way currently access the blocked_queue and sleeping_queue directly. We want to move where those queues are to make their ownership clearer: to have them clearly belong to the I/O manager impls rather than to the scheduler. Ultimately we will want to change their representation too. It's inconvenient to do that if these queues are accessed directly from cmm code. So as a first step, replace the APPEND_TO_BLOCKED_QUEUE with a C version appendToIOBlockedQueue(), and replace the open-coded sleeping_queue insertion with insertIntoSleepingQueue(). - - - - - ced9acdb by Duncan Coutts at 2022-11-22T02:06:17-05:00 Move {blocked,sleeping}_queue from scheduler global vars to CapIOManager The blocked_queue_{hd,tl} and the sleeping_queue are currently cooperatively managed between the scheduler and (some but not all of) the non-threaded I/O manager implementations. They lived as global vars with the scheduler, but are poked by I/O primops and the I/O manager backends. This patch is a step on the path towards making the management of I/O or timer blocking belong to the I/O managers and not the scheduler. Specifically, this patch moves the {blocked,sleeping}_queue from being global vars in the scheduler to being members of the CapIOManager struct within each Capability. They are not yet exclusively used by the I/O managers: they are still poked from a couple other places, notably in the scheduler before calling awaitEvent. - - - - - 0f68919e by Duncan Coutts at 2022-11-22T02:06:17-05:00 Remove the now-unused markScheduler The global vars {blocked,sleeping}_queue are now in the Capability and so get marked there via markCapabilityIOManager. - - - - - 39a91f60 by Duncan Coutts at 2022-11-22T02:06:17-05:00 Move macros for checking for pending IO or timers from Schedule.h to Schedule.c and IOManager.h This is just moving, the next step will be to rejig them slightly. For the non-threaded RTS the scheduler needs to be able to test for there being pending I/O operation or pending timers. The implementation of these tests should really be considered to be part of the I/O managers and not part of the scheduler. - - - - - 664b034b by Duncan Coutts at 2022-11-22T02:06:17-05:00 Replace EMPTY_{BLOCKED,SLEEPING}_QUEUE macros by function These are the macros originaly from Scheduler.h, previously moved to IOManager.h, and now replaced with a single inline function anyPendingTimeoutsOrIO(). We can use a single function since the two macros were always checked together. Note that since anyPendingTimeoutsOrIO is defined for all IO manager cases, including threaded, we do not need to guard its use by cpp #if !defined(THREADED_RTS) - - - - - 32946220 by Duncan Coutts at 2022-11-22T02:06:17-05:00 Expand emptyThreadQueues inline for clarity It was not really adding anything. The name no longer meant anything since those I/O and timeout queues do not belong to the scheuler. In one of the two places it was used, the comments already had to explain what it did, whereas now the code matches the comment nicely. - - - - - 9943baf9 by Duncan Coutts at 2022-11-22T02:06:17-05:00 Move the awaitEvent declaration into IOManager.h And add or adjust comments at the use sites of awaitEvent. - - - - - 054dcc9d by Duncan Coutts at 2022-11-22T02:06:17-05:00 Pass the Capability *cap explicitly to awaitEvent It is currently only used in the non-threaded RTS so it works to use MainCapability, but it's a bit nicer to pass the cap anyway. It's certainly shorter. - - - - - 667fe5a4 by Duncan Coutts at 2022-11-22T02:06:17-05:00 Pass the Capability *cap explicitly to appendToIOBlockedQueue And to insertIntoSleepingQueue. Again, it's a bit cleaner and simpler though not strictly necessary given that these primops are currently only used in the non-threaded RTS. - - - - - 7181b074 by Duncan Coutts at 2022-11-22T02:06:17-05:00 Reveiew feedback: improve one of the TODO comments The one about the nonsense (const False) test on WinIO for there being any IO or timers pending, leading to unnecessary complication later in the scheduler. - - - - - e5b68183 by Andreas Klebinger at 2022-11-22T02:06:52-05:00 Optimize getLevity. Avoid the intermediate data structures allocated by splitTyConApp. This avoids ~0.5% of allocations for a build using -O2. Fixes #22254 - - - - - de5fb348 by Andreas Klebinger at 2022-11-22T02:07:28-05:00 hadrian:Set TNTC when running testsuite. - - - - - 9d61c182 by Oleg Grenrus at 2022-11-22T15:59:34-05:00 Add unsafePtrEquality# restricted to UnliftedTypes - - - - - e817c871 by Jonathan Dowland at 2022-11-22T16:00:14-05:00 utils/unlit: adjust parser to match Report spec The Haskell 2010 Report says that, for Latex-style Literate format, "Program code begins on the first line following a line that begins \begin{code}". (This is unchanged from the 98 Report) However the unlit.c implementation only matches a line that contains "\begin{code}" and nothing else. One consequence of this is that one cannot suffix Latex options to the code environment. I.e., this does not work: \begin{code}[label=foo,caption=Foo Code] Adjust the matcher to conform to the specification from the Report. The Haskell Wiki currently recommends suffixing a '%' to \begin{code} in order to deliberately hide a code block from Haskell. This is bad advice, as it's relying on an implementation quirk rather than specified behaviour. None-the-less, some people have tried to use it, c.f. <https://mail.haskell.org/pipermail/haskell-cafe/2009-September/066780.html> An alternative solution is to define a separate, equivalent Latex environment to "code", that is functionally identical in Latex but ignored by unlit. This should not be a burden: users are required to manually define the code environment anyway, as it is not provided by the Latex verbatim or lstlistings packages usually used for presenting code in documents. Fixes #3549. - - - - - 0b7fef11 by Teo Camarasu at 2022-11-23T12:44:33-05:00 Fix eventlog all option Previously it didn't enable/disable nonmoving_gc and ticky event types Fixes #21813 - - - - - 04d0618c by Arnaud Spiwack at 2022-11-23T12:45:14-05:00 Expand Note [Linear types] with the stance on linting linearity Per the discussion on #22123 - - - - - e1538516 by Lawton Nichols at 2022-11-23T12:45:55-05:00 Add documentation on custom Prelude modules (#22228) Specifically, custom Prelude modules that are named `Prelude`. - - - - - b5c71454 by Sylvain Henry at 2022-11-23T12:46:35-05:00 Don't let configure perform trivial substitutions (#21846) Hadrian now performs substitutions, especially to generate .cabal files from .cabal.in files. Two benefits: 1. We won't have to re-configure when we modify thing.cabal.in. Hadrian will take care of this for us. 2. It paves the way to allow the same package to be configured differently by Hadrian in the same session. This will be useful to fix #19174: we want to build a stage2 cross-compiler for the host platform and a stage1 compiler for the cross target platform in the same Hadrian session. - - - - - 99aca26b by nineonine at 2022-11-23T12:47:11-05:00 CApiFFI: add ConstPtr for encoding const-qualified pointer return types (#22043) Previously, when using `capi` calling convention in foreign declarations, code generator failed to handle const-cualified pointer return types. This resulted in CC toolchain throwing `-Wincompatible-pointer-types-discards-qualifiers` warning. `Foreign.C.Types.ConstPtr` newtype was introduced to handle these cases - special treatment was put in place to generate appropritetly qualified C wrapper that no longer triggers the above mentioned warning. Fixes #22043 - - - - - 040bfdc3 by M Farkas-Dyck at 2022-11-23T21:59:03-05:00 Scrub some no-warning pragmas. - - - - - 178c1fd8 by Vladislav Zavialov at 2022-11-23T21:59:39-05:00 Check if the SDoc starts with a single quote (#22488) This patch fixes pretty-printing of character literals inside promoted lists and tuples. When we pretty-print a promoted list or tuple whose first element starts with a single quote, we want to add a space between the opening bracket and the element: '[True] -- ok '[ 'True] -- ok '['True] -- not ok If we don't add the space, we accidentally produce a character literal '['. Before this patch, pprSpaceIfPromotedTyCon inspected the type as an AST and tried to guess if it would be rendered with a single quote. However, it missed the case when the inner type was itself a character literal: '[ 'x'] -- ok '['x'] -- not ok Instead of adding this particular case, I opted for a more future-proof solution: check the SDoc directly. This way we can detect if the single quote is actually there instead of trying to predict it from the AST. The new function is called spaceIfSingleQuote. - - - - - 11627c42 by Matthew Pickering at 2022-11-23T22:00:15-05:00 notes: Fix references to HPT space leak note Updating this note was missed when updating the HPT to the HUG. Fixes #22477 - - - - - 86ff1523 by Andrei Borzenkov at 2022-11-24T17:24:51-05:00 Convert diagnostics in GHC.Rename.Expr to proper TcRnMessage (#20115) Problem: avoid usage of TcRnMessageUnknown Solution: The following `TcRnMessage` messages has been introduced: TcRnNoRebindableSyntaxRecordDot TcRnNoFieldPunsRecordDot TcRnIllegalStaticExpression TcRnIllegalStaticFormInSplice TcRnListComprehensionDuplicateBinding TcRnEmptyStmtsGroup TcRnLastStmtNotExpr TcRnUnexpectedStatementInContext TcRnIllegalTupleSection TcRnIllegalImplicitParameterBindings TcRnSectionWithoutParentheses Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - d198a19a by Cheng Shao at 2022-11-24T17:25:29-05:00 rts: fix missing Arena.h symbols in RtsSymbols.c It was an unfortunate oversight in !8961 and broke devel2 builds. - - - - - 5943e739 by Andrew Lelechenko at 2022-11-25T04:38:28-05:00 Assorted fixes to avoid Data.List.{head,tail} - - - - - 1f1b99b8 by sheaf at 2022-11-25T04:38:28-05:00 Review suggestions for assorted fixes to avoid Data.List.{head,tail} - - - - - 13d627bb by Vladislav Zavialov at 2022-11-25T04:39:04-05:00 Print unticked promoted data constructors (#20531) Before this patch, GHC unconditionally printed ticks before promoted data constructors: ghci> type T = True -- unticked (user-written) ghci> :kind! T T :: Bool = 'True -- ticked (compiler output) After this patch, GHC prints ticks only when necessary: ghci> type F = False -- unticked (user-written) ghci> :kind! F F :: Bool = False -- unticked (compiler output) ghci> data False -- introduce ambiguity ghci> :kind! F F :: Bool = 'False -- ticked by necessity (compiler output) The old behavior can be enabled by -fprint-redundant-promotion-ticks. Summary of changes: * Rename PrintUnqualified to NamePprCtx * Add QueryPromotionTick to it * Consult the GlobalRdrEnv to decide whether to print a tick (see mkPromTick) * Introduce -fprint-redundant-promotion-ticks Co-authored-by: Artyom Kuznetsov <hi at wzrd.ht> - - - - - e9d62453 by Simon Peyton Jones at 2022-11-25T13:49:12+01:00 Track small API change in TyCon.hs - - - - - d10dc6bd by Simon Peyton Jones at 2022-11-25T22:31:27+00:00 Fix decomposition of TyConApps Ticket #22331 showed that we were being too eager to decompose a Wanted TyConApp, leading to incompleteness in the solver. To understand all this I ended up doing a substantial rewrite of the old Note [Decomposing equalities], now reborn as Note [Decomposing TyConApp equalities]. Plus rewrites of other related Notes. The actual fix is very minor and actually simplifies the code: in `can_decompose` in `GHC.Tc.Solver.Canonical.canTyConApp`, we now call `noMatchableIrreds`. A closely related refactor: we stop trying to use the same "no matchable givens" function here as in `matchClassInst`. Instead split into two much simpler functions. - - - - - 2da5c38a by Will Hawkins at 2022-11-26T04:05:04-05:00 Redirect output of musttail attribute test Compilation output from test for support of musttail attribute leaked to the console. - - - - - 0eb1c331 by Cheng Shao at 2022-11-28T08:55:53+00:00 Move hs_mulIntMayOflo cbits to ghc-prim It's only used by wasm NCG at the moment, but ghc-prim is a more reasonable place for hosting out-of-line primops. Also, we only need a single version of hs_mulIntMayOflo. - - - - - 36b53a9d by Cheng Shao at 2022-11-28T09:05:57+00:00 compiler: generate ccalls for clz/ctz/popcnt in wasm NCG We used to generate a single wasm clz/ctz/popcnt opcode, but it's wrong when it comes to subwords, so might as well generate ccalls for them. See #22470 for details. - - - - - d4134e92 by Cheng Shao at 2022-11-28T23:48:14-05:00 compiler: remove unused MO_U_MulMayOflo We actually only emit MO_S_MulMayOflo and never emit MO_U_MulMayOflo anywhere. - - - - - 8d15eadc by Apoorv Ingle at 2022-11-29T03:09:31-05:00 Killing cc_fundeps, streamlining kind equality orientation, and type equality processing order Fixes: #217093 Associated to #19415 This change * Flips the orientation of the the generated kind equality coercion in canEqLHSHetero; * Removes `cc_fundeps` in CDictCan as the check was incomplete; * Changes `canDecomposableTyConAppOk` to ensure we process kind equalities before type equalities and avoiding a call to `canEqLHSHetero` while processing wanted TyConApp equalities * Adds 2 new tests for validating the change - testsuites/typecheck/should_compile/T21703.hs and - testsuites/typecheck/should_fail/T19415b.hs (a simpler version of T19415.hs) * Misc: Due to the change in the equality direction some error messages now have flipped type mismatch errors * Changes in Notes: - Note [Fundeps with instances, and equality orientation] supercedes Note [Fundeps with instances] - Added Note [Kind Equality Orientation] to visualize the kind flipping - Added Note [Decomposing Dependent TyCons and Processing Wanted Equalties] - - - - - 646969d4 by Krzysztof Gogolewski at 2022-11-29T03:10:13-05:00 Change printing of sized literals to match the proposal Literals in Core were printed as e.g. 0xFF#16 :: Int16#. The proposal 451 now specifies syntax 0xFF#Int16. This change affects the Core printer only - more to be done later. Part of #21422. - - - - - 02e282ec by Simon Peyton Jones at 2022-11-29T03:10:48-05:00 Be a bit more selective about floating bottoming expressions This MR arranges to float a bottoming expression to the top only if it escapes a value lambda. See #22494 and Note [Floating to the top] in SetLevels. This has a generally beneficial effect in nofib +-------------------------------++----------+ | ||tsv (rel) | +===============================++==========+ | imaginary/paraffins || -0.93% | | imaginary/rfib || -0.05% | | real/fem || -0.03% | | real/fluid || -0.01% | | real/fulsom || +0.05% | | real/gamteb || -0.27% | | real/gg || -0.10% | | real/hidden || -0.01% | | real/hpg || -0.03% | | real/scs || -11.13% | | shootout/k-nucleotide || -0.01% | | shootout/n-body || -0.08% | | shootout/reverse-complement || -0.00% | | shootout/spectral-norm || -0.02% | | spectral/fibheaps || -0.20% | | spectral/hartel/fft || -1.04% | | spectral/hartel/solid || +0.33% | | spectral/hartel/wave4main || -0.35% | | spectral/mate || +0.76% | +===============================++==========+ | geom mean || -0.12% | The effect on compile time is generally slightly beneficial Metrics: compile_time/bytes allocated ---------------------------------------------- MultiLayerModulesTH_OneShot(normal) +0.3% PmSeriesG(normal) -0.2% PmSeriesT(normal) -0.1% T10421(normal) -0.1% T10421a(normal) -0.1% T10858(normal) -0.1% T11276(normal) -0.1% T11303b(normal) -0.2% T11545(normal) -0.1% T11822(normal) -0.1% T12150(optasm) -0.1% T12234(optasm) -0.3% T13035(normal) -0.2% T16190(normal) -0.1% T16875(normal) -0.4% T17836b(normal) -0.2% T17977(normal) -0.2% T17977b(normal) -0.2% T18140(normal) -0.1% T18282(normal) -0.1% T18304(normal) -0.2% T18698a(normal) -0.1% T18923(normal) -0.1% T20049(normal) -0.1% T21839r(normal) -0.1% T5837(normal) -0.4% T6048(optasm) +3.2% BAD T9198(normal) -0.2% T9630(normal) -0.1% TcPlugin_RewritePerf(normal) -0.4% hard_hole_fits(normal) -0.1% geo. mean -0.0% minimum -0.4% maximum +3.2% The T6048 outlier is hard to pin down, but it may be the effect of reading in more interface files definitions. It's a small program for which compile time is very short, so I'm not bothered about it. Metric Increase: T6048 - - - - - ab23dc5e by Ben Gamari at 2022-11-29T03:11:25-05:00 testsuite: Mark unpack_sums_6 as fragile due to #22504 This test is explicitly dependent upon runtime, which is generally not appropriate given that the testsuite is run in parallel and generally saturates the CPU. - - - - - def47dd3 by Ben Gamari at 2022-11-29T03:11:25-05:00 testsuite: Don't use grep -q in unpack_sums_7 `grep -q` closes stdin as soon as it finds the pattern it is looking for, resulting in #22484. - - - - - cc25d52e by Sylvain Henry at 2022-11-29T09:44:31+01:00 Add Javascript backend Add JS backend adapted from the GHCJS project by Luite Stegeman. Some features haven't been ported or implemented yet. Tests for these features have been disabled with an associated gitlab ticket. Bump array submodule Work funded by IOG. Co-authored-by: Jeffrey Young <jeffrey.young at iohk.io> Co-authored-by: Luite Stegeman <stegeman at gmail.com> Co-authored-by: Josh Meredith <joshmeredith2008 at gmail.com> - - - - - 68c966cd by sheaf at 2022-11-30T09:31:25-05:00 Fix @since annotations on WithDict and Coercible Fixes #22453 - - - - - a3a8e9e9 by Simon Peyton Jones at 2022-11-30T09:32:03-05:00 Be more careful in GHC.Tc.Solver.Interact.solveOneFromTheOther We were failing to account for the cc_pend_sc flag in this important function, with the result that we expanded superclasses forever. Fixes #22516. - - - - - a9d9b8c0 by Simon Peyton Jones at 2022-11-30T09:32:03-05:00 Use mkNakedFunTy in tcPatSynSig As #22521 showed, in tcPatSynSig we make a "fake type" to kind-generalise; and that type has unzonked type variables in it. So we must not use `mkFunTy` (which checks FunTy's invariants) via `mkPhiTy` when building this type. Instead we need to use `mkNakedFunTy`. Easy fix. - - - - - 31462d98 by Andreas Klebinger at 2022-11-30T14:50:58-05:00 Properly cast values when writing/reading unboxed sums. Unboxed sums might store a Int8# value as Int64#. This patch makes sure we keep track of the actual value type. See Note [Casting slot arguments] for the details. - - - - - 10a2a7de by Oleg Grenrus at 2022-11-30T14:51:39-05:00 Move Void to GHC.Base... This change would allow `Void` to be used deeper in module graph. For example exported from `Prelude` (though that might be already possible). Also this change includes a change `stimes @Void _ x = x`, https://github.com/haskell/core-libraries-committee/issues/95 While the above is not required, maintaining old stimes behavior would be tricky as `GHC.Base` doesn't know about `Num` or `Integral`, which would require more hs-boot files. - - - - - b4cfa8e2 by Sebastian Graf at 2022-11-30T14:52:24-05:00 DmdAnal: Reflect the `seq` of strict fields of a DataCon worker (#22475) See the updated `Note [Data-con worker strictness]` and the new `Note [Demand transformer for data constructors]`. Fixes #22475. - - - - - d87f28d8 by Baldur Blöndal at 2022-11-30T21:16:36+01:00 Make Functor a quantified superclass of Bifunctor. See https://github.com/haskell/core-libraries-committee/issues/91 for discussion. This change relates Bifunctor with Functor by requiring second = fmap. Moreover this change is a step towards unblocking the major version bump of bifunctors and profunctors to major version 6. This paves the way to move the Profunctor class into base. For that Functor first similarly becomes a superclass of Profunctor in the new major version 6. - - - - - 72cf4c5d by doyougnu at 2022-12-01T12:36:44-05:00 FastString: SAT bucket_match Metric Decrease: MultiLayerModulesTH_OneShot - - - - - afc2540d by Simon Peyton Jones at 2022-12-01T12:37:20-05:00 Add a missing varToCoreExpr in etaBodyForJoinPoint This subtle bug showed up when compiling a library with 9.4. See #22491. The bug is present in master, but it is hard to trigger; the new regression test T22491 fails in 9.4. The fix was easy: just add a missing varToCoreExpr in etaBodyForJoinPoint. The fix is definitely right though! I also did some other minor refatoring: * Moved the preInlineUnconditionally test in simplExprF1 to before the call to joinPointBinding_maybe, to avoid fruitless eta-expansion. * Added a boolean from_lam flag to simplNonRecE, to avoid two fruitless tests, and commented it a bit better. These refactorings seem to save 0.1% on compile-time allocation in perf/compiler; with a max saving of 1.4% in T9961 Metric Decrease: T9961 - - - - - 81eeec7f by M Farkas-Dyck at 2022-12-01T12:37:56-05:00 CI: Forbid the fully static build on Alpine to fail. To do so, we mark some tests broken in this configuration. - - - - - c5d1bf29 by Bryan Richter at 2022-12-01T12:37:56-05:00 CI: Remove ARMv7 jobs These jobs fail (and are allowed to fail) nearly every time. Soon they won't even be able to run at all, as we won't currently have runners that can run them. Fixing the latter problem is tracked in #22409. I went ahead and removed all settings and configurations. - - - - - d82992fd by Bryan Richter at 2022-12-01T12:37:56-05:00 CI: Fix CI lint Failure was introduced by conflicting changes to gen_ci.hs that did *not* trigger git conflicts. - - - - - ce126993 by Simon Peyton Jones at 2022-12-02T01:22:12-05:00 Refactor TyCon to have a top-level product This patch changes the representation of TyCon so that it has a top-level product type, with a field that gives the details (newtype, type family etc), #22458. Not much change in allocation, but execution seems to be a bit faster. Includes a change to the haddock submodule to adjust for API changes. - - - - - 74c767df by Matthew Pickering at 2022-12-02T01:22:48-05:00 ApplicativeDo: Set pattern location before running exhaustiveness checker This improves the error messages of the exhaustiveness checker when checking statements which have been moved around with ApplicativeDo. Before: Test.hs:2:3: warning: [GHC-62161] [-Wincomplete-uni-patterns] Pattern match(es) are non-exhaustive In a pattern binding: Patterns of type ‘Maybe ()’ not matched: Nothing | 2 | let x = () | ^^^^^^^^^^ After: Test.hs:4:3: warning: [GHC-62161] [-Wincomplete-uni-patterns] Pattern match(es) are non-exhaustive In a pattern binding: Patterns of type ‘Maybe ()’ not matched: Nothing | 4 | ~(Just res1) <- seq x (pure $ Nothing @()) | Fixes #22483 - - - - - 85ecc1a0 by Matthew Pickering at 2022-12-02T19:46:43-05:00 Add special case for :Main module in `GHC.IfaceToCore.mk_top_id` See Note [Root-main Id] The `:Main` special binding is actually defined in the current module (hence don't go looking for it externally) but the module name is rOOT_MAIN rather than the current module so we need this special case. There was already some similar logic in `GHC.Rename.Env` for External Core, but now the "External Core" is in interface files it needs to be moved here instead. Fixes #22405 - - - - - 108c319f by Krzysztof Gogolewski at 2022-12-02T19:47:18-05:00 Fix linearity checking in Lint Lint was not able to see that x*y <= x*y, because this inequality was decomposed to x <= x*y && y <= x*y, but there was no rule to see that x <= x*y. Fixes #22546. - - - - - bb674262 by Bryan Richter at 2022-12-03T04:38:46-05:00 Mark T16916 fragile See https://gitlab.haskell.org/ghc/ghc/-/issues/16966 - - - - - 5d267d46 by Vladislav Zavialov at 2022-12-03T04:39:22-05:00 Refactor: FreshOrReuse instead of addTyClTyVarBinds This is a refactoring that should have no effect on observable behavior. Prior to this change, GHC.HsToCore.Quote contained a few closely related functions to process type variable bindings: addSimpleTyVarBinds, addHsTyVarBinds, addQTyVarBinds, and addTyClTyVarBinds. We can classify them by their input type and name generation strategy: Fresh names only Reuse bound names +---------------------+-------------------+ [Name] | addSimpleTyVarBinds | | [LHsTyVarBndr flag GhcRn] | addHsTyVarBinds | | LHsQTyVars GhcRn | addQTyVarBinds | addTyClTyVarBinds | +---------------------+-------------------+ Note how two functions are missing. Because of this omission, there were two places where a LHsQTyVars value was constructed just to be able to pass it to addTyClTyVarBinds: 1. mk_qtvs in addHsOuterFamEqnTyVarBinds -- bad 2. mkHsQTvs in repFamilyDecl -- bad This prevented me from making other changes to LHsQTyVars, so the main goal of this refactoring is to get rid of those workarounds. The most direct solution would be to define the missing functions. But that would lead to a certain amount of code duplication. To avoid code duplication, I factored out the name generation strategy into a function parameter: data FreshOrReuse = FreshNamesOnly | ReuseBoundNames addSimpleTyVarBinds :: FreshOrReuse -> ... addHsTyVarBinds :: FreshOrReuse -> ... addQTyVarBinds :: FreshOrReuse -> ... - - - - - c189b831 by Vladislav Zavialov at 2022-12-03T04:39:22-05:00 addHsOuterFamEqnTyVarBinds: use FreshNamesOnly for explicit binders Consider this example: [d| instance forall a. C [a] where type forall b. G [a] b = Proxy b |] When we process "forall b." in the associated type instance, it is unambiguously the binding site for "b" and we want a fresh name for it. Therefore, FreshNamesOnly is more fitting than ReuseBoundNames. This should not have any observable effect but it avoids pointless lookups in the MetaEnv. - - - - - 42512264 by Ross Paterson at 2022-12-03T10:32:45+00:00 Handle type data declarations in Template Haskell quotations and splices (fixes #22500) This adds a TypeDataD constructor to the Template Haskell Dec type, and ensures that the constructors it contains go in the TyCls namespace. - - - - - 1a767fa3 by Vladislav Zavialov at 2022-12-05T05:18:50-05:00 Add BufSpan to EpaLocation (#22319, #22558) The key part of this patch is the change to mkTokenLocation: - mkTokenLocation (RealSrcSpan r _) = TokenLoc (EpaSpan r) + mkTokenLocation (RealSrcSpan r mb) = TokenLoc (EpaSpan r mb) mkTokenLocation used to discard the BufSpan, but now it is saved and can be retrieved from LHsToken or LHsUniToken. This is made possible by the following change to EpaLocation: - data EpaLocation = EpaSpan !RealSrcSpan + data EpaLocation = EpaSpan !RealSrcSpan !(Strict.Maybe BufSpan) | ... The end goal is to make use of the BufSpan in Parser/PostProcess/Haddock. - - - - - cd31acad by sheaf at 2022-12-06T15:45:58-05:00 Hadrian: fix ghcDebugAssertions off-by-one error Commit 6b2f7ffe changed the logic that decided whether to enable debug assertions. However, it had an off-by-one error, as the stage parameter to the function inconsistently referred to the stage of the compiler being used to build or the stage of the compiler we are building. This patch makes it consistent. Now the parameter always refers to the the compiler which is being built. In particular, this patch re-enables assertions in the stage 2 compiler when building with devel2 flavour, and disables assertions in the stage 2 compiler when building with validate flavour. Some extra performance tests are now run in the "validate" jobs because the stage2 compiler no longer contains assertions. ------------------------- Metric Decrease: CoOpt_Singletons MultiComponentModules MultiComponentModulesRecomp MultiLayerModulesTH_OneShot T11374 T12227 T12234 T13253-spj T13701 T14683 T14697 T15703 T17096 T17516 T18304 T18478 T18923 T5030 T9872b TcPlugin_RewritePerf Metric Increase: MultiComponentModules MultiComponentModulesRecomp MultiLayerModules MultiLayerModulesRecomp MultiLayerModulesTH_Make T13386 T13719 T3294 T9233 T9675 parsing001 ------------------------- - - - - - 21d66db1 by mrkun at 2022-12-06T15:46:38-05:00 Push DynFlags out of runInstallNameTool - - - - - aaaaa79b by mrkun at 2022-12-06T15:46:38-05:00 Push DynFlags out of askOtool - - - - - 4e28f49e by mrkun at 2022-12-06T15:46:38-05:00 Push DynFlags out of runInjectRPaths - - - - - a7422580 by mrkun at 2022-12-06T15:46:38-05:00 Push DynFlags out of Linker.MacOS - - - - - eb1c73f7 by Ben Gamari at 2022-12-07T08:46:21-05:00 Update for GhC 9.6 - - - - - 063268dd by Ben Gamari at 2022-12-07T11:26:32-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - e902d771 by Matthew Craven at 2022-12-08T08:30:23-05:00 Fix bounds-checking buglet in Data.Array.Byte ...another manifestation of #20851 which I unfortunately missed in my first pass. - - - - - 8d36c0c6 by Gergő Érdi at 2022-12-08T08:31:03-05:00 Remove copy-pasted definitions of `graphFromEdgedVertices*` - - - - - c5d8ed3a by Gergő Érdi at 2022-12-08T08:31:03-05:00 Add version of `reachableGraph` that avoids loop for cyclic inputs by building its result connected component by component Fixes #22512 - - - - - 90cd5396 by Krzysztof Gogolewski at 2022-12-08T08:31:39-05:00 Mark Type.Reflection.Unsafe as Unsafe This module can be used to construct ill-formed TypeReps, so it should be Unsafe. - - - - - 2057c77d by Ian-Woo Kim at 2022-12-08T08:32:19-05:00 Truncate eventlog event for large payload (#20221) RTS eventlog events for postCapsetVecEvent are truncated if payload is larger than EVENT_PAYLOAD_SIZE_MAX Previously, postCapsetVecEvent records eventlog event with payload of variable size larger than EVENT_PAYLOAD_SIZE_MAX (2^16) without any validation, resulting in corrupted data. For example, this happens when a Haskell binary is invoked with very long command line arguments exceeding 2^16 bytes (see #20221). Now we check the size of accumulated payload messages incrementally, and truncate the message just before the payload size exceeds EVENT_PAYLOAD_SIZE_MAX. RTS will warn the user with a message showing how many arguments are truncated. - - - - - 9ec76f61 by Cheng Shao at 2022-12-08T08:32:59-05:00 hadrian: don't add debug info to non-debug ways of rts Hadrian used to pass -g when building all ways of rts. It makes output binaries larger (especially so for wasm backend), and isn't needed by most users out there, so this patch removes that flag. In case the debug info is desired, we still pass -g3 when building the debug way, and there's also the debug_info flavour transformer which ensures -g3 is passed for all rts ways. - - - - - 7658cdd4 by Krzysztof Gogolewski at 2022-12-08T08:33:36-05:00 Restore show (typeRep @[]) == "[]" The Show instance for TypeRep [] has changed in 9.5 to output "List" because the name of the type constructor changed. This seems to be accidental and is inconsistent with TypeReps of saturated lists, which are printed as e.g. "[Int]". For now, I'm restoring the old behavior; in the future, maybe we should show TypeReps without puns (List, Tuple, Type). - - - - - 4ca722fe by Ben Gamari at 2022-12-08T14:43:26-05:00 Bump bounds to accomodate base-4.18 - - - - - 216deefd by Matthew Pickering at 2022-12-08T22:45:27-05:00 Add test for #22162 - - - - - 5d0a311f by Matthew Pickering at 2022-12-08T22:45:27-05:00 ci: Add job to test interface file determinism guarantees In this job we can run on every commit we add a test which builds the Cabal library twice and checks that the ABI hash and interface hash is stable across the two builds. * We run the test 20 times to try to weed out any race conditions due to `-j` * We run the builds in different temporary directories to try to weed out anything related to build directory affecting ABI or interface file hash. Fixes #22180 - - - - - 0a76d7d4 by Matthew Pickering at 2022-12-08T22:45:27-05:00 ci: Add job for testing interface stability across builds The idea is that both the bindists should product libraries with the same ABI and interface hash. So the job checks with ghc-pkg to make sure the computed ABI is the same. In future this job can be extended to check for the other facets of interface determinism. Fixes #22180 - - - - - 74c9bf91 by Matthew Pickering at 2022-12-08T22:45:27-05:00 backpack: Be more careful when adding together ImportAvails There was some code in the signature merging logic which added together the ImportAvails of the signature and the signature which was merged into it. This had the side-effect of making the merged signature depend on the signature (via a normal module dependency). The intention was to propagate orphan instances through the merge but this also messed up recompilation logic because we shouldn't be attempting to load B.hi when mergeing it. The fix is to just combine the part of ImportAvails that we intended to (transitive info, orphan instances and type family instances) rather than the whole thing. - - - - - d122e022 by Matthew Pickering at 2022-12-08T22:45:27-05:00 Fix mk_mod_usage_info if the interface file is not already loaded In #22217 it was observed that the order modules are compiled in affects the contents of an interface file. This was because a module dependended on another module indirectly, via a re-export but the interface file for this module was never loaded because the symbol was never used in the file. If we decide that we depend on a module then we jolly well ought to record this fact in the interface file! Otherwise it could lead to very subtle recompilation bugs if the dependency is not tracked and the module is updated. Therefore the best thing to do is just to make sure the file is loaded by calling the `loadSysInterface` function. This first checks the caches (like we did before) but then actually goes to find the interface on disk if it wasn't loaded. Fixes #22217 - - - - - ea25088d by lrzlin at 2022-12-08T22:46:06-05:00 Add initial support for LoongArch Architecture. - - - - - 9eb9d2f4 by Andrew Lelechenko at 2022-12-08T22:46:47-05:00 Update submodule mtl to 2.3.1, parsec to 3.1.15.1, haddock and Cabal to HEAD - - - - - 08d8fe2a by Andrew Lelechenko at 2022-12-08T22:46:47-05:00 Allow mtl-2.3 in hadrian - - - - - 3807a46c by Andrew Lelechenko at 2022-12-08T22:46:47-05:00 Support mtl-2.3 in check-exact - - - - - ef702a18 by Andrew Lelechenko at 2022-12-08T22:46:47-05:00 Fix tests - - - - - 3144e8ff by Sebastian Graf at 2022-12-08T22:47:22-05:00 Make (^) INLINE (#22324) So that we get to cancel away the allocation for the lazily used base. We can move `powImpl` (which *is* strict in the base) to the top-level so that we don't duplicate too much code and move the SPECIALISATION pragmas onto `powImpl`. The net effect of this change is that `(^)` plays along much better with inlining thresholds and loopification (#22227), for example in `x2n1`. Fixes #22324. - - - - - 1d3a8b8e by Matthew Pickering at 2022-12-08T22:47:59-05:00 Typeable: Fix module locations of some definitions in GHC.Types There was some confusion in Data.Typeable about which module certain wired-in things were defined in. Just because something is wired-in doesn't mean it comes from GHC.Prim, in particular things like LiftedRep and RuntimeRep are defined in GHC.Types and that's the end of the story. Things like Int#, Float# etc are defined in GHC.Prim as they have no Haskell definition site at all so we need to generate type representations for them (which live in GHC.Types). Fixes #22510 - - - - - 0f7588b5 by Sebastian Graf at 2022-12-08T22:48:34-05:00 Make `drop` and `dropWhile` fuse (#18964) I copied the fusion framework we have in place for `take`. T18964 asserts that we regress neither when fusion fires nor when it doesn't. Fixes #18964. - - - - - 26e71562 by Sebastian Graf at 2022-12-08T22:49:10-05:00 Do not strictify a DFun's parameter dictionaries (#22549) ... thus fixing #22549. The details are in the refurbished and no longer dead `Note [Do not strictify a DFun's parameter dictionaries]`. There's a regression test in T22549. - - - - - 36093407 by John Ericson at 2022-12-08T22:49:45-05:00 Delete `rts/package.conf.in` It is a relic of the Make build system. The RTS now uses a `package.conf` file generated the usual way by Cabal. - - - - - b0cc2fcf by Krzysztof Gogolewski at 2022-12-08T22:50:21-05:00 Fixes around primitive literals * The SourceText of primitive characters 'a'# did not include the #, unlike for other primitive literals 1#, 1##, 1.0#, 1.0##, "a"#. We can now remove the function pp_st_suffix, which was a hack to add the # back. * Negative primitive literals shouldn't use parentheses, as described in Note [Printing of literals in Core]. Added a testcase to T14681. - - - - - aacf616d by Bryan Richter at 2022-12-08T22:50:56-05:00 testsuite: Mark conc024 fragile on Windows - - - - - ed239a24 by Ryan Scott at 2022-12-09T09:42:16-05:00 Document TH splices' interaction with INCOHERENT instances Top-level declaration splices can having surprising interactions with `INCOHERENT` instances, as observed in #22492. This patch resolves #22492 by documenting this strange interaction in the GHC User's Guide. [ci skip] - - - - - 1023b432 by Mike Pilgrem at 2022-12-09T09:42:56-05:00 Fix #22300 Document GHC's extensions to valid whitespace - - - - - 79b0cec0 by Luite Stegeman at 2022-12-09T09:43:38-05:00 Add support for environments that don't have setImmediate - - - - - 5b007ec5 by Luite Stegeman at 2022-12-09T09:43:38-05:00 Fix bound thread status - - - - - 65335d10 by Matthew Pickering at 2022-12-09T20:15:45-05:00 Update containers submodule This contains a fix necessary for the multi-repl to work on GHC's code base where we try to load containers and template-haskell into the same session. - - - - - 4937c0bb by Matthew Pickering at 2022-12-09T20:15:45-05:00 hadrian-multi: Put interface files in separate directories Before we were putting all the interface files in the same directory which was leading to collisions if the files were called the same thing. - - - - - 8acb5b7b by Matthew Pickering at 2022-12-09T20:15:45-05:00 hadrian-toolargs: Add filepath to allowed repl targets - - - - - 5949d927 by Matthew Pickering at 2022-12-09T20:15:45-05:00 driver: Set correct UnitId when rehydrating modules We were not setting the UnitId before rehydrating modules which just led to us attempting to find things in the wrong HPT. The test for this is the hadrian-multi command (which is now added as a CI job). Fixes #22222 - - - - - ab06c0f0 by Matthew Pickering at 2022-12-09T20:15:45-05:00 ci: Add job to test hadrian-multi command I am not sure this job is good because it requires booting HEAD with HEAD, but it should be fine. - - - - - fac3e568 by Matthew Pickering at 2022-12-09T20:16:20-05:00 hadrian: Update bootstrap plans to 9.2.* series and 9.4.* series. This updates the build plans for the most recent compiler versions, as well as fixing the hadrian-bootstrap-gen script to a specific GHC version. - - - - - 195b08b4 by Matthew Pickering at 2022-12-09T20:16:20-05:00 ci: Bump boot images to use ghc-9.4.3 Also updates the bootstrap jobs to test booting 9.2 and 9.4. - - - - - c658c580 by Matthew Pickering at 2022-12-09T20:16:20-05:00 hlint: Removed redundant UnboxedSums pragmas UnboxedSums is quite confusingly implied by UnboxedTuples, alas, just the way it is. See #22485 - - - - - 340b7511 by Vladislav Zavialov at 2022-12-10T12:31:28+00:00 HsToken in HsAppKindTy - - - - - b3e98a92 by Oleg Grenrus at 2022-12-11T12:26:17-05:00 Add heqT, a kind-heterogeneous variant of heq CLC proposal https://github.com/haskell/core-libraries-committee/issues/99 - - - - - bfd7c1e6 by Andrew Lelechenko at 2022-12-11T12:26:55-05:00 Document that Bifunctor instances for tuples are lawful only up to laziness - - - - - 5d1a1881 by Bryan Richter at 2022-12-12T16:22:36-05:00 Mark T21336a fragile - - - - - c30accc2 by Matthew Pickering at 2022-12-12T16:23:11-05:00 Add test for #21476 This issues seems to have been fixed since the ticket was made, so let's add a test and move on. Fixes #21476 - - - - - 946226ec by Ben Gamari at 2022-12-13T20:12:56-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - e9d74a3e by Sebastian Graf at 2022-12-13T22:18:39-05:00 Respect -XStrict in the pattern-match checker (#21761) We were missing a call to `decideBangHood` in the pattern-match checker. There is another call in `matchWrapper.mk_eqn_info` which seems redundant but really is not; see `Note [Desugaring -XStrict matches in Pmc]`. Fixes #21761. - - - - - 884790e2 by Gergő Érdi at 2022-12-13T22:19:14-05:00 Fix loop in the interface representation of some `Unfolding` fields As discovered in #22272, dehydration of the unfolding info of a recursive definition used to involve a traversal of the definition itself, which in turn involves traversing the unfolding info. Hence, a loop. Instead, we now store enough data in the interface that we can produce the unfolding info without this traversal. See Note [Tying the 'CoreUnfolding' knot] for details. Fixes #22272 Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> - - - - - 9f301189 by Alan Zimmerman at 2022-12-13T22:19:50-05:00 EPA: When splitting out header comments, keep ones for first decl Any comments immediately preceding the first declaration are no longer kept as header comments, but attach to the first declaration instead. - - - - - 8b1f1b45 by Sylvain Henry at 2022-12-13T22:20:28-05:00 JS: fix object file name comparison (#22578) - - - - - e9e161bb by Bryan Richter at 2022-12-13T22:21:03-05:00 configure: Bump min bootstrap GHC version to 9.2 - - - - - 75855643 by Ben Gamari at 2022-12-15T03:54:02-05:00 hadrian: Don't enable TSAN in stage0 build - - - - - da7b51d8 by Ben Gamari at 2022-12-15T03:54:02-05:00 cmm: Introduce blockConcat - - - - - 34f6b09c by Ben Gamari at 2022-12-15T03:54:02-05:00 cmm: Introduce MemoryOrderings - - - - - 43beaa7b by Ben Gamari at 2022-12-15T03:54:02-05:00 llvm: Respect memory specified orderings - - - - - 8faf74fc by Ben Gamari at 2022-12-15T03:54:02-05:00 Codegen/x86: Eliminate barrier for relaxed accesses - - - - - 6cc3944a by Ben Gamari at 2022-12-15T03:54:02-05:00 cmm/Parser: Reduce some repetition - - - - - 6c9862c4 by Ben Gamari at 2022-12-15T03:54:02-05:00 cmm/Parser: Add syntax for ordered loads and stores - - - - - 748490d2 by Ben Gamari at 2022-12-15T03:54:02-05:00 cmm/Parser: Atomic load syntax Originally I had thought I would just use the `prim` call syntax instead of introducing new syntax for atomic loads. However, it turns out that `prim` call syntax tends to make things quite unreadable. This new syntax seems quite natural. - - - - - 28c6781a by Ben Gamari at 2022-12-15T03:54:02-05:00 codeGen: Introduce ThreadSanitizer instrumentation This introduces a new Cmm pass which instruments the program with ThreadSanitizer annotations, allowing full tracking of mutator memory accesses via TSAN. - - - - - d97aa311 by Ben Gamari at 2022-12-15T03:54:02-05:00 Hadrian: Drop TSAN_ENABLED define from flavour This is redundant since the TSANUtils.h already defines it. - - - - - 86974ef1 by Ben Gamari at 2022-12-15T03:54:02-05:00 hadrian: Enable Cmm instrumentation in TSAN flavour - - - - - 93723290 by Ben Gamari at 2022-12-15T03:54:02-05:00 rts: Ensure that global regs are never passed as fun call args This is in general unsafe as they may be clobbered if they are mapped to caller-saved machine registers. See Note [Register parameter passing]. - - - - - 2eb0fb87 by Matthew Pickering at 2022-12-15T03:54:39-05:00 Package Imports: Get candidate packages also from re-exported modules Previously we were just looking at the direct imports to try and work out what a package qualifier could apply to but #22333 pointed out we also needed to look for reexported modules. Fixes #22333 - - - - - 552b7908 by Ben Gamari at 2022-12-15T03:55:15-05:00 compiler: Ensure that MutVar operations have necessary barriers Here we add acquire and release barriers in readMutVar# and writeMutVar#, which are necessary for soundness. Fixes #22468. - - - - - 933d61a4 by Simon Peyton Jones at 2022-12-15T03:55:51-05:00 Fix bogus test in Lint The Lint check for branch compatiblity within an axiom, in GHC.Core.Lint.compatible_branches was subtly different to the check made when contructing an axiom, in GHC.Core.FamInstEnv.compatibleBranches. The latter is correct, so I killed the former and am now using the latter. On the way I did some improvements to pretty-printing and documentation. - - - - - 03ed0b95 by Ryan Scott at 2022-12-15T03:56:26-05:00 checkValidInst: Don't expand synonyms when splitting sigma types Previously, the `checkValidInst` function (used when checking that an instance declaration is headed by an actual type class, not a type synonym) was using `tcSplitSigmaTy` to split apart the `forall`s and instance context. This is incorrect, however, as `tcSplitSigmaTy` expands type synonyms, which can cause instances headed by quantified constraint type synonyms to be accepted erroneously. This patch introduces `splitInstTyForValidity`, a variant of `tcSplitSigmaTy` specialized for validity checking that does _not_ expand type synonyms, and uses it in `checkValidInst`. Fixes #22570. - - - - - ed056bc3 by Ben Gamari at 2022-12-16T16:12:44-05:00 rts/Messages: Refactor This doesn't change behavior but makes the code a bit easier to follow. - - - - - 7356f8e0 by Ben Gamari at 2022-12-16T16:12:44-05:00 rts/ThreadPaused: Ordering fixes - - - - - 914f0025 by Ben Gamari at 2022-12-16T16:12:44-05:00 eventlog: Silence spurious data race - - - - - fbc84244 by Ben Gamari at 2022-12-16T16:12:44-05:00 Introduce SET_INFO_RELEASE for Cmm - - - - - 821b5472 by Ben Gamari at 2022-12-16T16:12:44-05:00 rts: Use fences instead of explicit barriers - - - - - 2228c999 by Ben Gamari at 2022-12-16T16:12:44-05:00 rts/stm: Fix memory ordering in readTVarIO# See #22421. - - - - - 99269b9f by Ben Gamari at 2022-12-16T16:12:44-05:00 Improve heap memory barrier Note Also introduce MUT_FIELD marker in Closures.h to document mutable fields. - - - - - 70999283 by Ben Gamari at 2022-12-16T16:12:44-05:00 rts: Introduce getNumCapabilities And ensure accesses to n_capabilities are atomic (although with relaxed ordering). This is necessary as RTS API callers may concurrently call into the RTS without holding a capability. - - - - - 98689f77 by Ben Gamari at 2022-12-16T16:12:44-05:00 ghc: Fix data race in dump file handling Previously the dump filename cache would use a non-atomic update which could potentially result in lost dump contents. Note that this is still a bit racy since the first writer may lag behind a later appending writer. - - - - - 605d9547 by Ben Gamari at 2022-12-16T16:12:45-05:00 rts: Always use atomics for context_switch and interrupt Since these are modified by the timer handler. - - - - - 86f20258 by Ben Gamari at 2022-12-16T16:12:45-05:00 rts/Timer: Always use atomic operations As noted in #22447, the existence of the pthread-based ITimer implementation means that we cannot assume that the program is single-threaded. - - - - - f8e901dc by Ben Gamari at 2022-12-16T16:12:45-05:00 rts: Encapsulate recent_activity access This makes it easier to ensure that it is accessed using the necessary atomic operations. - - - - - e0affaa9 by Ben Gamari at 2022-12-16T16:12:45-05:00 rts: Encapsulate access to capabilities array - - - - - 7ca683e4 by Ben Gamari at 2022-12-16T16:12:45-05:00 rts: Encapsulate sched_state - - - - - 1cf13bd0 by Ben Gamari at 2022-12-16T16:12:45-05:00 PrimOps: Fix benign MutVar race Relaxed ordering is fine here since the later CAS implies a release. - - - - - 3d2a7e08 by Ben Gamari at 2022-12-16T16:12:45-05:00 rts: Style fix - - - - - 82c62074 by Ben Gamari at 2022-12-16T16:12:45-05:00 compiler: Use release store in eager blackholing - - - - - eb1a0136 by Ben Gamari at 2022-12-16T16:12:45-05:00 rts: Fix ordering of makeStableName - - - - - ad0e260a by Ben Gamari at 2022-12-16T16:12:45-05:00 rts: Use ordered accesses instead of explicit barriers - - - - - a3eccf06 by Ben Gamari at 2022-12-16T16:12:45-05:00 rts: Statically allocate capabilities This is a rather simplistic way of solving #17289. - - - - - 287fa3fb by Ben Gamari at 2022-12-16T16:12:45-05:00 rts: Ensure that all accesses to pending_sync are atomic - - - - - 351eae58 by Ben Gamari at 2022-12-16T16:12:45-05:00 rts: Note race with wakeBlockingQueue - - - - - 5acf33dd by Andrew Lelechenko at 2022-12-16T16:13:22-05:00 Bump submodule directory to 1.3.8.0 and hpc to HEAD - - - - - 0dd95421 by Andrew Lelechenko at 2022-12-16T16:13:22-05:00 Accept allocations increase on Windows This is because of `filepath-1.4.100.0` and AFPP, causing increasing round-trips between lists and ByteArray. See #22625 for discussion. Metric Increase: MultiComponentModules MultiComponentModulesRecomp MultiLayerModules MultiLayerModulesRecomp T10421 T10547 T12150 T12227 T12234 T12425 T13035 T13253 T13253-spj T13701 T13719 T15703 T16875 T18140 T18282 T18304 T18698a T18698b T18923 T20049 T21839c T21839r T5837 T6048 T9198 T9961 TcPlugin_RewritePerf hard_hole_fits - - - - - ef9ac9d2 by Cheng Shao at 2022-12-16T16:13:59-05:00 testsuite: Mark T9405 as fragile instead of broken on Windows It's starting to pass again, and the unexpected pass blocks CI. - - - - - 1f3abd85 by Cheng Shao at 2022-12-16T21:16:28+00:00 compiler: remove obsolete commented code in wasm NCG It was just a temporary hack to workaround a bug in the relooper, that bug has been fixed long before the wasm backend is merged. - - - - - e3104eab by Cheng Shao at 2022-12-16T21:16:28+00:00 compiler: add missing export list of GHC.CmmToAsm.Wasm.FromCmm Also removes some unreachable code here. - - - - - 1c6930bf by Cheng Shao at 2022-12-16T21:16:28+00:00 compiler: change fallback function signature to Cmm function signature in wasm NCG In the wasm NCG, when handling a `CLabel` of undefined function without knowing its function signature, we used to fallback to `() -> ()` which is accepted by `wasm-ld`. This patch changes it to the signature of Cmm functions, which equally works, but would be required when we emit tail call instructions. - - - - - 8a81d9d9 by Cheng Shao at 2022-12-16T21:16:28+00:00 compiler: add optional tail-call support in wasm NCG When the `-mtail-call` clang flag is passed at configure time, wasm tail-call extension is enabled, and the wasm NCG will emit `return_call`/`return_call_indirect` instructions to take advantage of it and avoid the `StgRun` trampoline overhead. Closes #22461. - - - - - d1431cc0 by Cheng Shao at 2022-12-17T08:07:15-05:00 base: add missing autoconf checks for waitpid/umask These are not present in wasi-libc. Required for fixing #22589 - - - - - da3f1e91 by Cheng Shao at 2022-12-17T08:07:51-05:00 compiler: make .wasm the default executable extension on wasm32 Following convention as in other wasm toolchains. Fixes #22594. - - - - - ad21f4ef by Cheng Shao at 2022-12-17T08:07:51-05:00 ci: support hello.wasm in ci.sh cross testing logic - - - - - 6fe2d778 by amesgen at 2022-12-18T19:33:49-05:00 Correct `exitWith` Haddocks The `IOError`-specific `catch` in the Prelude is long gone. - - - - - b3eacd64 by Ben Gamari at 2022-12-18T19:34:24-05:00 rts: Drop racy assertion 0e274c39bf836d5bb846f5fa08649c75f85326ac added an assertion in `dirty_MUT_VAR` checking that the MUT_VAR being dirtied was clean. However, this isn't necessarily the case since another thread may have raced us to dirty the object. - - - - - 761c1f49 by Ben Gamari at 2022-12-18T19:35:00-05:00 rts/libdw: Silence uninitialized usage warnings As noted in #22538, previously some GCC versions warned that various locals in Libdw.c may be used uninitialized. Although this wasn't strictly true (since they were initialized in an inline assembler block) we fix this by providing explicit empty initializers. Fixes #22538 - - - - - 5e047eff by Matthew Pickering at 2022-12-20T15:12:04+00:00 testsuite: Mark T16392 as fragile on windows See #22649 - - - - - 703a4665 by M Farkas-Dyck at 2022-12-20T21:14:46-05:00 Scrub some partiality in `GHC.Cmm.Info.Build`: `doSRTs` takes a `[(CAFSet, CmmDecl)]` but truly wants a `[(CAFSet, CmmStatics)]`. - - - - - 9736ab74 by Matthew Pickering at 2022-12-20T21:15:22-05:00 packaging: Fix upload_ghc_libs.py script This change reflects the changes where .cabal files are now generated by hadrian rather than ./configure. Fixes #22518 - - - - - 7c6de18d by Ben Gamari at 2022-12-20T21:15:57-05:00 configure: Drop uses of AC_PROG_CC_C99 As noted in #22566, this macro is deprecated as of autoconf-2.70 `AC_PROG_CC` now sets `ac_cv_prog_cc_c99` itself. Closes #22566. - - - - - 36c5d98e by Ben Gamari at 2022-12-20T21:15:57-05:00 configure: Use AS_HELP_STRING instead of AC_HELP_STRING The latter has been deprecated. See #22566. - - - - - befe6ff8 by Andrew Lelechenko at 2022-12-20T21:16:37-05:00 GHCi.UI: fix various usages of head and tail - - - - - 666d0ba7 by Andrew Lelechenko at 2022-12-20T21:16:37-05:00 GHCi.UI: avoid head and tail in parseCallEscape and around - - - - - 5d96fd50 by Andrew Lelechenko at 2022-12-20T21:16:37-05:00 Make GHC.Driver.Main.hscTcRnLookupRdrName to return NonEmpty - - - - - 3ce2ab94 by Andrew Lelechenko at 2022-12-21T06:17:56-05:00 Allow transformers-0.6 in ghc, ghci, ghc-bin and hadrian - - - - - 954de93a by Andrew Lelechenko at 2022-12-21T06:17:56-05:00 Update submodule haskeline to HEAD (to allow transformers-0.6) - - - - - cefbeec3 by Andrew Lelechenko at 2022-12-21T06:17:56-05:00 Update submodule transformers to 0.6.0.4 - - - - - b4730b62 by Andrew Lelechenko at 2022-12-21T06:17:56-05:00 Fix tests T13253 imports MonadTrans, which acquired a quantified constraint in transformers-0.6, thus increase in allocations Metric Increase: T13253 - - - - - 0be75261 by Simon Peyton Jones at 2022-12-21T06:18:32-05:00 Abstract over the right free vars Fix #22459, in two ways: (1) Make the Specialiser not create a bogus specialisation if it is presented by strangely polymorphic dictionary. See Note [Weird special case in SpecDict] in GHC.Core.Opt.Specialise (2) Be more careful in abstractFloats See Note [Which type variables to abstract over] in GHC.Core.Opt.Simplify.Utils. So (2) stops creating the excessively polymorphic dictionary in abstractFloats, while (1) stops crashing if some other pass should nevertheless create a weirdly polymorphic dictionary. - - - - - df7bc6b3 by Ying-Ruei Liang (TheKK) at 2022-12-21T14:31:54-05:00 rts: explicitly store return value of ccall checkClosure to prevent type error (#22617) - - - - - e193e537 by Simon Peyton Jones at 2022-12-21T14:32:30-05:00 Fix shadowing lacuna in OccurAnal Issue #22623 demonstrated another lacuna in the implementation of wrinkle (BS3) in Note [The binder-swap substitution] in the occurrence analyser. I was failing to add TyVar lambda binders using addInScope/addOneInScope and that led to a totally bogus binder-swap transformation. Very easy to fix. - - - - - 3d55d8ab by Simon Peyton Jones at 2022-12-21T14:32:30-05:00 Fix an assertion check in addToEqualCtList The old assertion saw that a constraint ct could rewrite itself (of course it can) and complained (stupid). Fixes #22645 - - - - - ceb2e9b9 by Ben Gamari at 2022-12-21T15:26:08-05:00 configure: Bump version to 9.6 - - - - - fb4d36c4 by Ben Gamari at 2022-12-21T15:27:49-05:00 base: Bump version to 4.18 Requires various submodule bumps. - - - - - 93ee7e90 by Ben Gamari at 2022-12-21T15:27:49-05:00 ghc-boot: Fix bootstrapping - - - - - fd8faa66 by Ben Gamari at 2022-12-22T13:44:28-05:00 Bump GHC version to 9.7 - - - - - fc3a2232 by Ben Gamari at 2022-12-22T13:45:06-05:00 Bump GHC version to 9.7 - - - - - 2958aa9c by Ben Gamari at 2022-12-22T14:49:16-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 914f7fe3 by Andreas Klebinger at 2022-12-22T23:36:10-05:00 Don't consider large byte arrays/compact regions pinned. Workaround for #22255 which showed how treating large/compact regions as pinned could cause segfaults. - - - - - 32b32d7f by Matthew Pickering at 2022-12-22T23:36:46-05:00 hadrian bindist: Install manpages to share/man/man1/ghc.1 When the installation makefile was copied over the manpages were no longer installed in the correct place. Now we install it into share/man/man1/ghc.1 as the make build system did. Fixes #22371 - - - - - b3ddf803 by Ben Gamari at 2022-12-22T23:37:23-05:00 rts: Drop paths from configure from cabal file A long time ago we would rely on substitutions from the configure script to inject paths of the include and library directories of libffi and libdw. However, now these are instead handled inside Hadrian when calling Cabal's `configure` (see the uses of `cabalExtraDirs` in Hadrian's `Settings.Packages.packageArgs`). While the occurrences in the cabal file were redundant, they did no harm. However, since b5c714545abc5f75a1ffdcc39b4bfdc7cd5e64b4 they have no longer been interpolated. @mpickering noticed the suspicious uninterpolated occurrence of `@FFIIncludeDir@` in #22595, prompting this commit to finally remove them. - - - - - b2c7523d by Ben Gamari at 2022-12-22T23:37:59-05:00 Bump libffi-tarballs submodule We will now use libffi-3.4.4. - - - - - 3699a554 by Alan Zimmerman at 2022-12-22T23:38:35-05:00 EPA: Make EOF position part of AnnsModule Closes #20951 Closes #19697 - - - - - 99757ce8 by Sylvain Henry at 2022-12-22T23:39:13-05:00 JS: fix support for -outputdir (#22641) The `-outputdir` option wasn't correctly handled with the JS backend because the same code path was used to handle both objects produced by the JS backend and foreign .js files. Now we clearly distinguish the two in the pipeline, fixing the bug. - - - - - 02ed7d78 by Simon Peyton Jones at 2022-12-22T23:39:49-05:00 Refactor mkRuntimeError This patch fixes #22634. Because we don't have TYPE/CONSTRAINT polymorphism, we need two error functions rather than one. I took the opportunity to rname runtimeError to impossibleError, to line up with mkImpossibleExpr, and avoid confusion with the genuine runtime-error-constructing functions. - - - - - 35267f07 by Ben Gamari at 2022-12-22T23:40:32-05:00 base: Fix event manager shutdown race on non-Linux platforms During shutdown it's possible that we will attempt to use a closed fd to wakeup another capability's event manager. On the Linux eventfd path we were careful to handle this. However on the non-Linux path we failed to do so. Fix this. - - - - - 317f45c1 by Simon Peyton Jones at 2022-12-22T23:41:07-05:00 Fix unifier bug: failing to decompose over-saturated type family This simple patch fixes #22647 - - - - - 14b2e3d3 by Ben Gamari at 2022-12-22T23:41:42-05:00 rts/m32: Fix sanity checking Previously we would attempt to clear pages which were marked as read-only. Fix this. - - - - - 16a1bcd1 by Matthew Pickering at 2022-12-23T09:15:24+00:00 ci: Move wasm pipelines into nightly rather than master See #22664 for the changes which need to be made to bring one of these back to the validate pipeline. - - - - - 18d2acd2 by Ben Gamari at 2022-12-23T19:09:30-05:00 nonmoving: Fix race in marking of blackholes We must use an acquire-fence when marking to ensure that the indirectee is visible. - - - - - 11241efa by Ben Gamari at 2022-12-23T19:09:30-05:00 nonmoving: Fix segment list races - - - - - 602455c9 by Ben Gamari at 2022-12-23T19:09:30-05:00 nonmoving: Use atomic when looking at bd->gen Since it may have been mutated by a moving GC. - - - - - 9d63b160 by Ben Gamari at 2022-12-23T19:09:30-05:00 nonmoving: Eliminate race in bump_static_flag To ensure that we don't race with a mutator entering a new CAF we take the SM mutex before touching static_flag. The other option here would be to instead modify newCAF to use a CAS but the present approach is a bit safer. - - - - - 26837523 by Ben Gamari at 2022-12-23T19:09:30-05:00 nonmoving: Ensure that mutable fields have acquire barrier - - - - - 8093264a by Ben Gamari at 2022-12-23T19:09:30-05:00 nonmoving: Fix races in collector status tracking Mark a number of accesses to do with tracking of the status of the concurrent collection thread as atomic. No interesting races here, merely necessary to satisfy TSAN. - - - - - 387d4fcc by Ben Gamari at 2022-12-23T19:09:30-05:00 nonmoving: Make segment state updates atomic - - - - - 543cae00 by Ben Gamari at 2022-12-23T19:09:30-05:00 nonmoving: Refactor update remembered set initialization This avoids a lock inversion between the storage manager mutex and the stable pointer table mutex by not dropping the SM_MUTEX in nonmovingCollect. This requires quite a bit of rejiggering but it does seem like a better strategy. - - - - - c9936718 by Ben Gamari at 2022-12-23T19:09:30-05:00 nonmoving: Ensure that we aren't holding locks when closing them TSAN complains about this sort of thing. - - - - - 0cd31f7d by Ben Gamari at 2022-12-23T19:09:30-05:00 nonmoving: Make bitmap accesses atomic This is a benign race on any sensible hard since these are byte accesses. Nevertheless, atomic accesses are necessary to satisfy TSAN. - - - - - d3fe110a by Ben Gamari at 2022-12-23T19:09:30-05:00 nonmoving: Fix benign race in update remembered set check Relaxed load is fine here since we will take the lock before looking at the list. - - - - - ab6cf893 by Ben Gamari at 2022-12-23T19:09:30-05:00 nonmoving: Fix race in shortcutting We must use an acquire load to read the info table pointer since if we find an indirection we must be certain that we see the indirectee. - - - - - 36c9f23c by Ben Gamari at 2022-12-23T19:09:30-05:00 nonmoving: Make free list counter accesses atomic Since these may race with the allocator(s). - - - - - aebef31c by doyougnu at 2022-12-23T19:10:09-05:00 add GHC.Utils.Binary.foldGet' and use for Iface A minor optimization to remove lazy IO and a lazy accumulator strictify foldGet' IFace.Binary: use strict foldGet' remove superfluous bang - - - - - 5eb357d9 by Ben Gamari at 2022-12-24T00:41:05-05:00 compiler: Ensure that GHC toolchain is first in search path As noted in #22561, it is important that GHC's toolchain look first for its own headers and libraries to ensure that the system's are not found instead. If this happens things can break in surprising ways (e.g. see #22561). - - - - - cbaebfb9 by Matthew Pickering at 2022-12-24T00:41:40-05:00 head.hackage: Use slow-validate bindist for linting jobs This enables the SLOW_VALIDATE env var for the linting head.hackage jobs, namely the jobs enabled manually, by the label or on the nightly build now use the deb10-numa-slow-validate bindist which has assertions enabled. See #22623 for a ticket which was found by using this configuration already! The head.hackage jobs triggered by upstream CI are now thusly: hackage-lint: Can be triggered on any MR, normal validate pipeline or nightly build. Runs head.hackage with -dlint and a slow-validate bindist hackage-label-lint: Trigged on MRs with "user-facing" label, runs the slow-validate head.hackage build with -dlint. nightly-hackage-lint: Runs automatically on nightly pipelines with slow-validate + dlint config. nightly-hackage-perf: Runs automaticaly on nightly pipelines with release build and eventlogging enabled. release-hackage-lint: Runs automatically on release pipelines with -dlint on a release bindist. - - - - - f4850f36 by Matthew Pickering at 2022-12-24T00:41:40-05:00 ci: Don't run abi-test-nightly on release jobs The test is not configured to get the correct dependencies for the release pipelines (and indeed stops the release pipeline being run at all) - - - - - c264b06b by Matthew Pickering at 2022-12-24T00:41:40-05:00 ci: Run head.hackage jobs on upstream-testing branch rather than master This change allows less priviledged users to trigger head.hackage jobs because less permissions are needed to trigger jobs on the upstream-testing branch, which is not protected. There is a CI job which updates upstream-testing each hour to the state of the master branch so it should always be relatively up-to-date. - - - - - 63b97430 by Ben Gamari at 2022-12-24T00:42:16-05:00 llvmGen: Fix relaxed ordering Previously I used LLVM's `unordered` ordering for the C11 `relaxed` ordering. However, this is wrong and should rather use the LLVM `monotonic` ordering. Fixes #22640 - - - - - f42ba88f by Ben Gamari at 2022-12-24T00:42:16-05:00 gitlab-ci: Introduce aarch64-linux-llvm job This nightly job will ensure that we don't break the LLVM backend on AArch64/Linux by bootstrapping GHC. This would have caught #22640. - - - - - 6d62f6bf by Matthew Pickering at 2022-12-24T00:42:51-05:00 Store RdrName rather than OccName in Holes In #20472 it was pointed out that you couldn't defer out of scope but the implementation collapsed a RdrName into an OccName to stuff it into a Hole. This leads to the error message for a deferred qualified name dropping the qualification which affects the quality of the error message. This commit adds a bit more structure to a hole, so a hole can replace a RdrName without losing information about what that RdrName was. This is important when printing error messages. I also added a test which checks the Template Haskell deferral of out of scope qualified names works properly. Fixes #22130 - - - - - 3c3060e4 by Richard Eisenberg at 2022-12-24T17:34:19+00:00 Drop support for kind constraints. This implements proposal 547 and closes ticket #22298. See the proposal and ticket for motivation. Compiler perf improves a bit Metrics: compile_time/bytes allocated ------------------------------------- CoOpt_Singletons(normal) -2.4% GOOD T12545(normal) +1.0% T13035(normal) -13.5% GOOD T18478(normal) +0.9% T9872d(normal) -2.2% GOOD geo. mean -0.2% minimum -13.5% maximum +1.0% Metric Decrease: CoOpt_Singletons T13035 T9872d - - - - - 6d7d4393 by Ben Gamari at 2022-12-24T21:09:56-05:00 hadrian: Ensure that linker scripts are used when merging objects In #22527 @rui314 inadvertantly pointed out a glaring bug in Hadrian's implementation of the object merging rules: unlike the old `make` build system we utterly failed to pass the needed linker scripts. Fix this. - - - - - a5bd0eb8 by Andrew Lelechenko at 2022-12-24T21:10:34-05:00 Document infelicities of instance Ord Double and workarounds - - - - - 62b9a7b2 by Zubin Duggal at 2023-01-03T12:22:11+00:00 Force the Docs structure to prevent leaks in GHCi with -haddock without -fwrite-interface Involves adding many new NFData instances. Without forcing Docs, references to the TcGblEnv for each module are retained by the Docs structure. Usually these are forced when the ModIface is serialised but not when we aren't writing the interface. - - - - - 21bedd84 by Facundo Domínguez at 2023-01-03T23:27:30-05:00 Explain the auxiliary functions of permutations - - - - - 32255d05 by Matthew Pickering at 2023-01-04T11:58:42+00:00 compiler: Add -f[no-]split-sections flags Here we add a `-fsplit-sections` flag which may some day replace `-split-sections`. This has the advantage of automatically providing a `-fno-split-sections` flag, which is useful for our packaging because we enable `-split-sections` by default but want to disable it in certain configurations. - - - - - e640940c by Matthew Pickering at 2023-01-04T11:58:42+00:00 hadrian: Fix computation of tables_next_to_code for outOfTreeCompiler This copy-pasto was introduced in de5fb3489f2a9bd6dc75d0cb8925a27fe9b9084b - - - - - 15bee123 by Matthew Pickering at 2023-01-04T11:58:42+00:00 hadrian: Add test:all_deps to build just testsuite dependencies Fixes #22534 - - - - - fec6638e by Matthew Pickering at 2023-01-04T11:58:42+00:00 hadrian: Add no_split_sections tranformer This transformer reverts the effect of `split_sections`, which we intend to use for platforms which don't support split sections. In order to achieve this we have to modify the implemntation of the split_sections transformer to store whether we are enabling split_sections directly in the `Flavour` definition. This is because otherwise there's no convenient way to turn off split_sections due to having to pass additional linker scripts when merging objects. - - - - - 3dc05726 by Matthew Pickering at 2023-01-04T11:58:42+00:00 check-exact: Fix build with -Werror - - - - - 53a6ae7a by Matthew Pickering at 2023-01-04T11:58:42+00:00 ci: Build all test dependencies with in-tree compiler This means that these executables will honour flavour transformers such as "werror". Fixes #22555 - - - - - 32e264c1 by Matthew Pickering at 2023-01-04T11:58:42+00:00 hadrian: Document using GHC environment variable to select boot compiler Fixes #22340 - - - - - be9dd9b0 by Matthew Pickering at 2023-01-04T11:58:42+00:00 packaging: Build perf builds with -split-sections In 8f71d958 the make build system was made to use split-sections on linux systems but it appears this logic never made it to hadrian. There is the split_sections flavour transformer but this doesn't appear to be used for perf builds on linux. This is disbled on deb9 and windows due to #21670 Closes #21135 - - - - - 00dc5106 by Matthew Pickering at 2023-01-04T14:32:45-05:00 sphinx: Use modern syntax for extlinks This fixes the following build error: ``` Command line: /opt/homebrew/opt/sphinx-doc/bin/sphinx-build -b man -d /private/tmp/extra-dir-55768274273/.doctrees-man -n -w /private/tmp/extra-dir-55768274273/.log docs/users_guide /private/tmp/extra-dir-55768274273 ===> Command failed with error code: 2 Exception occurred: File "/opt/homebrew/Cellar/sphinx-doc/6.0.0/libexec/lib/python3.11/site-packages/sphinx/ext/extlinks.py", line 101, in role title = caption % part ~~~~~~~~^~~~~~ TypeError: not all arguments converted during string formatting ``` I tested on Sphinx-5.1.1 and Sphinx-6.0.0 Thanks for sterni for providing instructions about how to test using sphinx-6.0.0. Fixes #22690 - - - - - 541aedcd by Krzysztof Gogolewski at 2023-01-05T10:48:34-05:00 Misc cleanup - Remove unused uniques and hs-boot declarations - Fix types of seq and unsafeCoerce# - Remove FastString/String roundtrip in JS - Use TTG to enforce totality - Remove enumeration in Heap/Inspect; the 'otherwise' clause serves the primitive types well. - - - - - 22bb8998 by Alan Zimmerman at 2023-01-05T10:49:09-05:00 EPA: Do not collect comments from end of file In Parser.y semis1 production triggers for the virtual semi at the end of the file. This is detected by it being zero length. In this case, do not extend the span being used to gather comments, so any final comments are allocated at the module level instead. - - - - - 9e077999 by Vladislav Zavialov at 2023-01-05T23:01:55-05:00 HsToken in TypeArg (#19623) Updates the haddock submodule. - - - - - b2a2db04 by Matthew Pickering at 2023-01-05T23:02:30-05:00 Revert "configure: Drop uses of AC_PROG_CC_C99" This reverts commit 7c6de18dd3151ead954c210336728e8686c91de6. Centos7 using a very old version of the toolchain (autotools-2.69) where the behaviour of these macros has not yet changed. I am reverting this without haste as it is blocking the 9.6 branch. Fixes #22704 - - - - - 28f8c0eb by Luite Stegeman at 2023-01-06T18:16:24+09:00 Add support for sized literals in the bytecode interpreter. The bytecode interpreter only has branching instructions for word-sized values. These are used for pattern matching. Branching instructions for other types (e.g. Int16# or Word8#) weren't needed, since unoptimized Core or STG never requires branching on types like this. It's now possible for optimized STG to reach the bytecode generator (e.g. fat interface files or certain compiler flag combinations), which requires dealing with various sized literals in branches. This patch improves support for generating bytecode from optimized STG by adding the following new bytecode instructions: TESTLT_I64 TESTEQ_I64 TESTLT_I32 TESTEQ_I32 TESTLT_I16 TESTEQ_I16 TESTLT_I8 TESTEQ_I8 TESTLT_W64 TESTEQ_W64 TESTLT_W32 TESTEQ_W32 TESTLT_W16 TESTEQ_W16 TESTLT_W8 TESTEQ_W8 Fixes #21945 - - - - - ac39e8e9 by Matthew Pickering at 2023-01-06T13:47:00-05:00 Only store Name in FunRhs rather than Id with knot-tied fields All the issues here have been caused by #18758. The goal of the ticket is to be able to talk about things like `LTyClDecl GhcTc`. In the case of HsMatchContext, the correct "context" is whatever we want, and in fact storing just a `Name` is sufficient and correct context, even if the rest of the AST is storing typechecker Ids. So this reverts (#20415, !5579) which intended to get closed to #18758 but didn't really and introduced a few subtle bugs. Printing of an error message in #22695 would just hang, because we would attempt to print the `Id` in debug mode to assertain whether it was empty or not. Printing the Name is fine for the error message. Another consequence is that when `-dppr-debug` was enabled the compiler would hang because the debug printing of the Id would try and print fields which were not populated yet. This also led to 32070e6c2e1b4b7c32530a9566fe14543791f9a6 having to add a workaround for the `checkArgs` function which was probably a very similar bug to #22695. Fixes #22695 - - - - - c306d939 by Matthew Pickering at 2023-01-06T22:08:53-05:00 ci: Upgrade darwin, windows and freebsd CI to use GHC-9.4.3 Fixes #22599 - - - - - 0db496ff by Matthew Pickering at 2023-01-06T22:08:53-05:00 darwin ci: Explicitly pass desired build triple to configure On the zw3rk machines for some reason the build machine was inferred to be arm64. Setting the build triple appropiately resolve this confusion and we produce x86 binaries. - - - - - 2459c358 by Ben Gamari at 2023-01-06T22:09:29-05:00 rts: MUT_VAR is not a StgMutArrPtrs There was previously a comment claiming that the MUT_VAR closure type had the layout of StgMutArrPtrs. - - - - - 6206cb92 by Simon Peyton Jones at 2023-01-07T12:14:40-05:00 Make FloatIn robust to shadowing This MR fixes #22622. See the new Note [Shadowing and name capture] I did a bit of refactoring in sepBindsByDropPoint too. The bug doesn't manifest in HEAD, but it did show up in 9.4, so we should backport this patch to 9.4 - - - - - a960ca81 by Matthew Pickering at 2023-01-07T12:15:15-05:00 T10955: Set DYLD_LIBRARY_PATH for darwin The correct path to direct the dynamic linker on darwin is DYLD_LIBRARY_PATH rather than LD_LIBRARY_PATH. On recent versions of OSX using LD_LIBRARY_PATH seems to have stopped working. For more reading see: https://stackoverflow.com/questions/3146274/is-it-ok-to-use-dyld-library-path-on-mac-os-x-and-whats-the-dynamic-library-s - - - - - 73484710 by Matthew Pickering at 2023-01-07T12:15:15-05:00 Skip T18623 on darwin (to add to the long list of OSs) On recent versions of OSX, running `ulimit -v` results in ``` ulimit: setrlimit failed: invalid argument ``` Time is too short to work out what random stuff Apple has been doing with ulimit, so just skip the test like we do for other platforms. - - - - - 8c0ea25f by Matthew Pickering at 2023-01-07T12:15:15-05:00 Pass -Wl,-no_fixup_chains to ld64 when appropiate Recent versions of MacOS use a version of ld where `-fixup_chains` is on by default. This is incompatible with our usage of `-undefined dynamic_lookup`. Therefore we explicitly disable `fixup-chains` by passing `-no_fixup_chains` to the linker on darwin. This results in a warning of the form: ld: warning: -undefined dynamic_lookup may not work with chained fixups The manual explains the incompatible nature of these two flags: -undefined treatment Specifies how undefined symbols are to be treated. Options are: error, warning, suppress, or dynamic_lookup. The default is error. Note: dynamic_lookup that depends on lazy binding will not work with chained fixups. A relevant ticket is #22429 Here are also a few other links which are relevant to the issue: Official comment: https://developer.apple.com/forums/thread/719961 More relevant links: https://openradar.appspot.com/radar?id=5536824084660224 https://github.com/python/cpython/issues/97524 Note in release notes: https://developer.apple.com/documentation/xcode-release-notes/xcode-13-releas e-notes - - - - - 365b3045 by Matthew Pickering at 2023-01-09T02:36:20-05:00 Disable split sections on aarch64-deb10 build See #22722 Failure on this job: https://gitlab.haskell.org/ghc/ghc/-/jobs/1287852 ``` Unexpected failures: /builds/ghc/ghc/tmp/ghctest-s3d8g1hj/test spaces/testsuite/tests/th/T10828.run T10828 [exit code non-0] (ext-interp) /builds/ghc/ghc/tmp/ghctest-s3d8g1hj/test spaces/testsuite/tests/th/T13123.run T13123 [exit code non-0] (ext-interp) /builds/ghc/ghc/tmp/ghctest-s3d8g1hj/test spaces/testsuite/tests/th/T20590.run T20590 [exit code non-0] (ext-interp) Appending 232 stats to file: /builds/ghc/ghc/performance-metrics.tsv ``` ``` Compile failed (exit code 1) errors were: data family D_0 a_1 :: * -> * data instance D_0 GHC.Types.Int GHC.Types.Bool :: * where DInt_2 :: D_0 GHC.Types.Int GHC.Types.Bool data E_3 where MkE_4 :: a_5 -> E_3 data Foo_6 a_7 b_8 where MkFoo_9, MkFoo'_10 :: a_11 -> Foo_6 a_11 b_12 newtype Bar_13 :: * -> GHC.Types.Bool -> * where MkBar_14 :: a_15 -> Bar_13 a_15 b_16 data T10828.T (a_0 :: *) where T10828.MkT :: forall (a_1 :: *) . a_1 -> a_1 -> T10828.T a_1 T10828.MkC :: forall (a_2 :: *) (b_3 :: *) . (GHC.Types.~) a_2 GHC.Types.Int => {T10828.foo :: a_2, T10828.bar :: b_3} -> T10828.T GHC.Types.Int T10828.hs:1:1: error: [GHC-87897] Exception when trying to run compile-time code: ghc-iserv terminated (-4) Code: (do TyConI dec <- runQ $ reify (mkName "T") runIO $ putStrLn (pprint dec) >> hFlush stdout d <- runQ $ [d| data T' a :: Type where MkT' :: a -> a -> T' a MkC' :: forall a b. (a ~ Int) => {foo :: a, bar :: b} -> T' Int |] runIO $ putStrLn (pprint d) >> hFlush stdout ....) *** unexpected failure for T10828(ext-interp) =====> 7000 of 9215 [0, 1, 0] =====> 7000 of 9215 [0, 1, 0] =====> 7000 of 9215 [0, 1, 0] =====> 7000 of 9215 [0, 1, 0] Compile failed (exit code 1) errors were: T13123.hs:1:1: error: [GHC-87897] Exception when trying to run compile-time code: ghc-iserv terminated (-4) Code: ([d| data GADT where MkGADT :: forall k proxy (a :: k). proxy a -> GADT |]) *** unexpected failure for T13123(ext-interp) =====> 7100 of 9215 [0, 2, 0] =====> 7100 of 9215 [0, 2, 0] =====> 7200 of 9215 [0, 2, 0] Compile failed (exit code 1) errors were: T20590.hs:1:1: error: [GHC-87897] Exception when trying to run compile-time code: ghc-iserv terminated (-4) Code: ([d| data T where MkT :: forall a. a -> T |]) *** unexpected failure for T20590(ext-interp) ``` Looks fairly worrying to me. - - - - - 965a2735 by Alan Zimmerman at 2023-01-09T02:36:20-05:00 EPA: exact print HsDocTy To match ghc-exactprint https://github.com/alanz/ghc-exactprint/pull/121 - - - - - 5d65773e by John Ericson at 2023-01-09T20:39:27-05:00 Remove RTS hack for configuring See the brand new Note [Undefined symbols in the RTS] for additional details. - - - - - e3fff751 by Sebastian Graf at 2023-01-09T20:40:02-05:00 Handle shadowing in DmdAnal (#22718) Previously, when we had a shadowing situation like ```hs f x = ... -- demand signature <1L><1L> main = ... \f -> f 1 ... ``` we'd happily use the shadowed demand signature at the call site inside the lambda. Of course, that's wrong and solution is simply to remove the demand signature from the `AnalEnv` when we enter the lambda. This patch does so for all binding constructs Core. In #22718 the issue was caused by LetUp not shadowing away the existing demand signature for the let binder in the let body. The resulting absent error is fickle to reproduce; hence no reproduction test case. #17478 would help. Fixes #22718. It appears that TcPlugin_Rewrite regresses by ~40% on Darwin. It is likely that DmdAnal was exploiting ill-scoped analysis results. Metric increase ['bytes allocated'] (test_env=x86_64-darwin-validate): TcPlugin_Rewrite - - - - - d53f6f4d by Oleg Grenrus at 2023-01-09T21:11:02-05:00 Add safe list indexing operator: !? With Joachim's amendments. Implements https://github.com/haskell/core-libraries-committee/issues/110 - - - - - cfaf1ad7 by Nicolas Trangez at 2023-01-09T21:11:03-05:00 rts, tests: limit thread name length to 15 bytes On Linux, `pthread_setname_np` (or rather, the kernel) only allows for thread names up to 16 bytes, including the terminating null byte. This commit adds a note pointing this out in `createOSThread`, and fixes up two instances where a thread name of more than 15 characters long was used (in the RTS, and in a test-case). Fixes: #22366 Fixes: https://gitlab.haskell.org/ghc/ghc/-/issues/22366 See: https://gitlab.haskell.org/ghc/ghc/-/issues/22366#note_460796 - - - - - 64286132 by Matthew Pickering at 2023-01-09T21:11:03-05:00 Store bootstrap_llvm_target and use it to set LlvmTarget in bindists This mirrors some existing logic for the bootstrap_target which influences how TargetPlatform is set. As described on #21970 not storing this led to `LlvmTarget` being set incorrectly and hence the wrong `--target` flag being passed to the C compiler. Towards #21970 - - - - - 4724e8d1 by Matthew Pickering at 2023-01-09T21:11:04-05:00 Check for FP_LD_NO_FIXUP_CHAINS in installation configure script Otherwise, when installing from a bindist the C flag isn't passed to the C compiler. This completes the fix for #22429 - - - - - 2e926b88 by Georgi Lyubenov at 2023-01-09T21:11:07-05:00 Fix outdated link to Happy section on sequences - - - - - 146a1458 by Matthew Pickering at 2023-01-09T21:11:07-05:00 Revert "NCG(x86): Compile add+shift as lea if possible." This reverts commit 20457d775885d6c3df020d204da9a7acfb3c2e5a. See #22666 and #21777 - - - - - 6e6adbe3 by Jade Lovelace at 2023-01-11T00:55:30-05:00 Fix tcPluginRewrite example - - - - - faa57138 by Jade Lovelace at 2023-01-11T00:55:31-05:00 fix missing haddock pipe - - - - - 0470ea7c by Florian Weimer at 2023-01-11T00:56:10-05:00 m4/fp_leading_underscore.m4: Avoid implicit exit function declaration And switch to a new-style function definition. Fixes build issues with compilers that do not accept implicit function declarations. - - - - - b2857df4 by HaskellMouse at 2023-01-11T00:56:52-05:00 Added a new warning about compatibility with RequiredTypeArguments This commit introduces a new warning that indicates code incompatible with future extension: RequiredTypeArguments. Enabling this extension may break some code and the warning will help to make it compatible in advance. - - - - - 5f17e21a by Ben Gamari at 2023-01-11T00:57:27-05:00 testsuite: Drop testheapalloced.c As noted in #22414, this file (which appears to be a benchmark for characterising the one-step allocator's MBlock cache) is currently unreferenced. Remove it. Closes #22414. - - - - - bc125775 by Vladislav Zavialov at 2023-01-11T00:58:03-05:00 Introduce the TypeAbstractions language flag GHC Proposals #448 "Modern scoped type variables" and #425 "Invisible binders in type declarations" introduce a new language extension flag: TypeAbstractions. Part of the functionality guarded by this flag has already been implemented, namely type abstractions in constructor patterns, but it was guarded by a combination of TypeApplications and ScopedTypeVariables instead of a dedicated language extension flag. This patch does the following: * introduces a new language extension flag TypeAbstractions * requires TypeAbstractions for @a-syntax in constructor patterns instead of TypeApplications and ScopedTypeVariables * creates a User's Guide page for TypeAbstractions and moves the "Type Applications in Patterns" section there To avoid a breaking change, the new flag is implied by ScopedTypeVariables and is retroactively added to GHC2021. Metric Decrease: MultiLayerModulesTH_OneShot - - - - - 083f7015 by Krzysztof Gogolewski at 2023-01-11T00:58:38-05:00 Misc cleanup - Remove unused mkWildEvBinder - Use typeTypeOrConstraint - more symmetric and asserts that that the type is Type or Constraint - Fix escape sequences in Python; they raise a deprecation warning with -Wdefault - - - - - aed1974e by Richard Eisenberg at 2023-01-11T08:30:42+00:00 Refactor the treatment of loopy superclass dicts This patch completely re-engineers how we deal with loopy superclass dictionaries in instance declarations. It fixes #20666 and #19690 The highlights are * Recognise that the loopy-superclass business should use precisely the Paterson conditions. This is much much nicer. See Note [Recursive superclasses] in GHC.Tc.TyCl.Instance * With that in mind, define "Paterson-smaller" in Note [Paterson conditions] in GHC.Tc.Validity, and the new data type `PatersonSize` in GHC.Tc.Utils.TcType, along with functions to compute and compare PatsonSizes * Use the new PatersonSize stuff when solving superclass constraints See Note [Solving superclass constraints] in GHC.Tc.TyCl.Instance * In GHC.Tc.Solver.Monad.lookupInInerts, add a missing call to prohibitedSuperClassSolve. This was the original cause of #20666. * Treat (TypeError "stuff") as having PatersonSize zero. See Note [Paterson size for type family applications] in GHC.Tc.Utils.TcType. * Treat the head of a Wanted quantified constraint in the same way as the superclass of an instance decl; this is what fixes #19690. See GHC.Tc.Solver.Canonical Note [Solving a Wanted forall-constraint] (Thanks to Matthew Craven for this insight.) This entailed refactoring the GivenSc constructor of CtOrigin a bit, to say whether it comes from an instance decl or quantified constraint. * Some refactoring way in which redundant constraints are reported; we don't want to complain about the extra, apparently-redundant constraints that we must add to an instance decl because of the loopy-superclass thing. I moved some work from GHC.Tc.Errors to GHC.Tc.Solver. * Add a new section to the user manual to describe the loopy superclass issue and what rules it follows. - - - - - 300bcc15 by HaskellMouse at 2023-01-11T13:43:36-05:00 Parse qualified terms in type signatures This commit allows qualified terms in type signatures to pass the parser and to be cathced by renamer with more informative error message. Adds a few tests. Fixes #21605 - - - - - 964284fc by Simon Peyton Jones at 2023-01-11T13:44:12-05:00 Fix void-arg-adding mechanism for worker/wrapper As #22725 shows, in worker/wrapper we must add the void argument /last/, not first. See GHC.Core.Opt.WorkWrap.Utils Note [Worker/wrapper needs to add void arg last]. That led me to to study GHC.Core.Opt.SpecConstr Note [SpecConstr needs to add void args first] which suggests the opposite! And indeed I think it's the other way round for SpecConstr -- or more precisely the void arg must precede the "extra_bndrs". That led me to some refactoring of GHC.Core.Opt.SpecConstr.calcSpecInfo. - - - - - f7ceafc9 by Krzysztof Gogolewski at 2023-01-11T22:36:59-05:00 Add 'docWithStyle' to improve codegen This new combinator docWithStyle :: IsOutput doc => doc -> (PprStyle -> SDoc) -> doc let us remove the need for code to be polymorphic in HDoc when not used in code style. Metric Decrease: ManyConstructors T13035 T1969 - - - - - b3be0d18 by Simon Peyton Jones at 2023-01-11T22:37:35-05:00 Fix finaliseArgBoxities for OPAQUE function We never do worker wrapper for OPAQUE functions, so we must zap the unboxing info during strictness analysis. This patch fixes #22502 - - - - - db11f358 by Ben Gamari at 2023-01-12T07:49:04-05:00 Revert "rts: Drop racy assertion" The logic here was inverted. Reverting the commit to avoid confusion when examining the commit history. This reverts commit b3eacd64fb36724ed6c5d2d24a81211a161abef1. - - - - - 3242139f by Ben Gamari at 2023-01-12T07:49:04-05:00 rts: Drop racy assertion 0e274c39bf836d5bb846f5fa08649c75f85326ac added an assertion in `dirty_MUT_VAR` checking that the MUT_VAR being dirtied was clean. However, this isn't necessarily the case since another thread may have raced us to dirty the object. - - - - - 9ffd5d57 by Ben Gamari at 2023-01-12T07:49:41-05:00 configure: Fix escaping of `$tooldir` In !9547 I introduced `$tooldir` directories into GHC's default link and compilation flags to ensure that our C toolchain finds its own headers and libraries before others on the system. However, the patch was subtly wrong in the escaping of `$tooldir`. Fix this. Fixes #22561. - - - - - 905d0b6e by Sebastian Graf at 2023-01-12T15:51:47-05:00 Fix contification with stable unfoldings (#22428) Many functions now return a `TailUsageDetails` that adorns a `UsageDetails` with a `JoinArity` that reflects the number of join point binders around the body for which the `UsageDetails` was computed. `TailUsageDetails` is now returned by `occAnalLamTail` as well as `occAnalUnfolding` and `occAnalRules`. I adjusted `Note [Join points and unfoldings/rules]` and `Note [Adjusting right-hand sides]` to account for the new machinery. I also wrote a new `Note [Join arity prediction based on joinRhsArity]` and refer to it when we combine `TailUsageDetails` for a recursive RHS. I also renamed * `occAnalLam` to `occAnalLamTail` * `adjustRhsUsage` to `adjustTailUsage` * a few other less important functions and properly documented the that each call of `occAnalLamTail` must pair up with `adjustTailUsage`. I removed `Note [Unfoldings and join points]` because it was redundant with `Note [Occurrences in stable unfoldings]`. While in town, I refactored `mkLoopBreakerNodes` so that it returns a condensed `NodeDetails` called `SimpleNodeDetails`. Fixes #22428. The refactoring seems to have quite beneficial effect on ghc/alloc performance: ``` CoOpt_Read(normal) ghc/alloc 784,778,420 768,091,176 -2.1% GOOD T12150(optasm) ghc/alloc 77,762,270 75,986,720 -2.3% GOOD T12425(optasm) ghc/alloc 85,740,186 84,641,712 -1.3% GOOD T13056(optasm) ghc/alloc 306,104,656 299,811,632 -2.1% GOOD T13253(normal) ghc/alloc 350,233,952 346,004,008 -1.2% T14683(normal) ghc/alloc 2,800,514,792 2,754,651,360 -1.6% T15304(normal) ghc/alloc 1,230,883,318 1,215,978,336 -1.2% T15630(normal) ghc/alloc 153,379,590 151,796,488 -1.0% T16577(normal) ghc/alloc 7,356,797,056 7,244,194,416 -1.5% T17516(normal) ghc/alloc 1,718,941,448 1,692,157,288 -1.6% T19695(normal) ghc/alloc 1,485,794,632 1,458,022,112 -1.9% T21839c(normal) ghc/alloc 437,562,314 431,295,896 -1.4% GOOD T21839r(normal) ghc/alloc 446,927,580 440,615,776 -1.4% GOOD geo. mean -0.6% minimum -2.4% maximum -0.0% ``` Metric Decrease: CoOpt_Read T10421 T12150 T12425 T13056 T18698a T18698b T21839c T21839r T9961 - - - - - a1491c87 by Andreas Klebinger at 2023-01-12T15:52:23-05:00 Only gc sparks locally when we can ensure marking is done. When performing GC without work stealing there was no guarantee that spark pruning was happening after marking of the sparks. This could cause us to GC live sparks under certain circumstances. Fixes #22528. - - - - - 8acfe930 by Cheng Shao at 2023-01-12T15:53:00-05:00 Change MSYSTEM to CLANG64 uniformly - - - - - 73bc162b by M Farkas-Dyck at 2023-01-12T15:53:42-05:00 Make `GHC.Tc.Errors.Reporter` take `NonEmpty ErrorItem` rather than `[ErrorItem]`, which lets us drop some panics. Also use the `BasicMismatch` constructor rather than `mkBasicMismatchMsg`, which lets us drop the "-Wno-incomplete-record-updates" flag. - - - - - 1b812b69 by Oleg Grenrus at 2023-01-12T15:54:21-05:00 Fix #22728: Not all diagnostics in safe check are fatal Also add tests for the issue and -Winferred-safe-imports in general - - - - - c79b2b65 by Matthew Pickering at 2023-01-12T15:54:58-05:00 Don't run hadrian-multi on fast-ci label Fixes #22667 - - - - - 9a3d6add by Andrew Lelechenko at 2023-01-13T00:46:36-05:00 Bump submodule bytestring to 0.11.4.0 Metric Decrease: T21839c T21839r - - - - - df33c13c by Ben Gamari at 2023-01-13T00:47:12-05:00 gitlab-ci: Bump Darwin bootstrap toolchain This updates the bootstrap compiler on Darwin from 8.10.7 to 9.2.5, ensuring that we have the fix for #21964. - - - - - 756a66ec by Ben Gamari at 2023-01-13T00:47:12-05:00 gitlab-ci: Pass -w to cabal update Due to cabal#8447, cabal-install 3.8.1.0 requires a compiler to run `cabal update`. - - - - - 1142f858 by Cheng Shao at 2023-01-13T11:04:00+00:00 Bump hsc2hs submodule - - - - - d4686729 by Cheng Shao at 2023-01-13T11:04:00+00:00 Bump process submodule - - - - - 84ae6573 by Cheng Shao at 2023-01-13T11:06:58+00:00 ci: Bump DOCKER_REV - - - - - d53598c5 by Cheng Shao at 2023-01-13T11:06:58+00:00 ci: enable xz parallel compression for x64 jobs - - - - - d31fcbca by Cheng Shao at 2023-01-13T11:06:58+00:00 ci: use in-image emsdk for js jobs - - - - - 93b9bbc1 by Cheng Shao at 2023-01-13T11:47:17+00:00 ci: improve nix-shell for gen_ci.hs and fix some ghc/hlint warnings - Add a ghc environment including prebuilt dependencies to the nix-shell. Get rid of the ad hoc cabal cache and all dependencies are now downloaded from the nixos binary cache. - Make gen_ci.hs a cabal package with HLS integration, to make future hacking of gen_ci.hs easier. - Fix some ghc/hlint warnings after I got HLS to work. - For the lint-ci-config job, do a shallow clone to save a few minutes of unnecessary git checkout time. - - - - - 8acc56c7 by Cheng Shao at 2023-01-13T11:47:17+00:00 ci: source the toolchain env file in wasm jobs - - - - - 87194df0 by Cheng Shao at 2023-01-13T11:47:17+00:00 ci: add wasm ci jobs via gen_ci.hs - There is one regular wasm job run in validate pipelines - Additionally, int-native/unreg wasm jobs run in nightly/release pipelines Also, remove the legacy handwritten wasm ci jobs in .gitlab-ci.yml. - - - - - b6eb9bcc by Matthew Pickering at 2023-01-13T11:52:16+00:00 wasm ci: Remove wasm release jobs This removes the wasm release jobs, as we do not yet intend to distribute these binaries. - - - - - 496607fd by Simon Peyton Jones at 2023-01-13T16:52:07-05:00 Add a missing checkEscapingKind Ticket #22743 pointed out that there is a missing check, for type-inferred bindings, that the inferred type doesn't have an escaping kind. The fix is easy. - - - - - 7a9a1042 by Andreas Klebinger at 2023-01-16T20:48:19-05:00 Separate core inlining logic from `Unfolding` type. This seems like a good idea either way, but is mostly motivated by a patch where this avoids a module loop. - - - - - 33b58f77 by sheaf at 2023-01-16T20:48:57-05:00 Hadrian: generalise &%> to avoid warnings This patch introduces a more general version of &%> that works with general traversable shapes, instead of lists. This allows us to pass along the information that the length of the list of filepaths passed to the function exactly matches the length of the input list of filepath patterns, avoiding pattern match warnings. Fixes #22430 - - - - - 8c7a991c by Andreas Klebinger at 2023-01-16T20:49:34-05:00 Add regression test for #22611. A case were a function used to fail to specialize, but now does. - - - - - 6abea760 by Andreas Klebinger at 2023-01-16T20:50:10-05:00 Mark maximumBy/minimumBy as INLINE. The RHS was too large to inline which often prevented the overhead of the Maybe from being optimized away. By marking it as INLINE we can eliminate the overhead of both the maybe and are able to unpack the accumulator when possible. Fixes #22609 - - - - - 99d151bb by Matthew Pickering at 2023-01-16T20:50:50-05:00 ci: Bump CACHE_REV so that ghc-9.6 branch and HEAD have different caches Having the same CACHE_REV on both branches leads to issues where the darwin toolchain is different on ghc-9.6 and HEAD which leads to long darwin build times. In general we should ensure that each branch has a different CACHE_REV. - - - - - 6a5845fb by Matthew Pickering at 2023-01-16T20:51:25-05:00 ci: Change owner of files in source-tarball job This fixes errors of the form: ``` fatal: detected dubious ownership in repository at '/builds/ghc/ghc' To add an exception for this directory, call: git config --global --add safe.directory /builds/ghc/ghc inferred 9.7.20230113 checking for GHC Git commit id... fatal: detected dubious ownership in repository at '/builds/ghc/ghc' To add an exception for this directory, call: git config --global --add safe.directory /builds/ghc/ghc ``` - - - - - 4afb952c by Matthew Pickering at 2023-01-16T20:51:25-05:00 ci: Don't build aarch64-deb10-llvm job on release pipelines Closes #22721 - - - - - 8039feb9 by Matthew Pickering at 2023-01-16T20:51:25-05:00 ci: Change owner of files in test-bootstrap job - - - - - 0b358d0c by Matthew Pickering at 2023-01-16T20:51:25-05:00 rel_eng: Add release engineering scripts into ghc tree It is better to keep these scripts in the tree as they depend on the CI configuration and so on. By keeping them in tree we can keep them up-to-date as the CI config changes and also makes it easier to backport changes to the release script between release branches in future. The final motivation is that it makes generating GHCUp metadata possible. - - - - - 28cb2ed0 by Matthew Pickering at 2023-01-16T20:51:25-05:00 ci: Don't use complicated image or clone in not-interruptible job This job exists only for the meta-reason of not allowing nightly pipelines to be cancelled. It was taking two minutes to run as in order to run "true" we would also clone the whole GHC repo. - - - - - eeea59bb by Matthew Pickering at 2023-01-16T20:51:26-05:00 Add scripts to generate ghcup metadata on nightly and release pipelines 1. A python script in .gitlab/rel_eng/mk-ghcup-metadata which generates suitable metadata for consumption by GHCUp for the relevant pipelines. - The script generates the metadata just as the ghcup maintainers want, without taking into account platform/library combinations. It is updated manually when the mapping changes. - The script downloads the bindists which ghcup wants to distribute, calculates the hash and generates the yaml in the correct structure. - The script is documented in the .gitlab/rel_eng/mk-ghcup-metadata/README.mk file 1a. The script requires us to understand the mapping from platform -> job. To choose the preferred bindist for each platform the .gitlab/gen_ci.hs script is modified to allow outputting a metadata file which answers the question about which job produces the bindist which we want to distribute to users for a specific platform. 2. Pipelines to run on nightly and release jobs to generate metadata - ghcup-metadata-nightly: Generates metadata which points directly to artifacts in the nightly job. - ghcup-metadata-release: Generates metadata suitable for inclusion directly in ghcup by pointing to the downloads folder where the bindist will be uploaded to. 2a. Trigger jobs which test the generated metadata in the downstream `ghccup-ci` repo. See that repo for documentation about what is tested and how but essentially we test in a variety of clean images that ghcup can download and install the bindists we say exist in our metadata. - - - - - 97bd4d8c by Andrew Lelechenko at 2023-01-16T20:52:04-05:00 Bump submodule parsec to 3.1.16.1 - - - - - 97ac8230 by Alan Zimmerman at 2023-01-16T20:52:39-05:00 EPA: Add annotation for 'type' in DataDecl Closes #22765 - - - - - dbbab95d by Ben Gamari at 2023-01-17T06:36:06-05:00 compiler: Small optimisation of assertM In #22739 @AndreasK noticed that assertM performed the action to compute the asserted predicate regardless of whether DEBUG is enabled. This is inconsistent with the other assertion operations and general convention. Fix this. Closes #22739. - - - - - fc02f3bb by Viktor Dukhovni at 2023-01-17T06:36:47-05:00 Avoid unnecessary printf warnings in EventLog.c Fixes #22778 - - - - - 003b6d44 by Simon Peyton Jones at 2023-01-17T16:33:05-05:00 Document the semantics of pattern bindings a bit better This MR is in response to the discussion on #22719 - - - - - f4d50baf by Vladislav Zavialov at 2023-01-17T16:33:41-05:00 Hadrian: fix warnings (#22783) This change fixes the following warnings when building Hadrian: src/Hadrian/Expression.hs:38:10: warning: [-Wredundant-constraints] src/Hadrian/Expression.hs:84:13: warning: [-Wtype-equality-requires-operators] src/Hadrian/Expression.hs:84:21: warning: [-Wtype-equality-requires-operators] src/Hadrian/Haskell/Cabal/Parse.hs:67:1: warning: [-Wunused-imports] - - - - - 06036d93 by Sylvain Henry at 2023-01-18T01:55:10-05:00 testsuite: req_smp --> req_target_smp, req_ghc_smp See #22630 and !9552 This commit: - splits req_smp into req_target_smp and req_ghc_smp - changes the testsuite driver to calculate req_ghc_smp - changes a handful of tests to use req_target_smp instead of req_smp - changes a handful of tests to use req_host_smp when needed The problem: - the problem this solves is the ambiguity surrounding req_smp - on master req_smp was used to express the constraint that the program being compiled supports smp _and_ that the host RTS (i.e., the RTS used to compile the program) supported smp. Normally that is fine, but in cross compilation this is not always the case as was discovered in #22630. The solution: - Differentiate the two constraints: - use req_target_smp to say the RTS the compiled program is linked with (and the platform) supports smp - use req_host_smp to say the RTS the host is linked with supports smp WIP: fix req_smp (target vs ghc) add flag to separate bootstrapper split req_smp -> req_target_smp and req_ghc_smp update tests smp flags cleanup and add some docstrings only set ghc_with_smp to bootstrapper on S1 or CC Only set ghc_with_smp to bootstrapperWithSMP of when testing stage 1 and cross compiling test the RTS in config/ghc not hadrian re-add ghc_with_smp fix and align req names fix T11760 to use req_host_smp test the rts directly, avoid python 3.5 limitation test the compiler in a try block align out of tree and in tree withSMP flags mark failing tests as host req smp testsuite: req_host_smp --> req_ghc_smp Fix ghc vs host, fix ghc_with_smp leftover - - - - - ee9b78aa by Krzysztof Gogolewski at 2023-01-18T01:55:45-05:00 Use -Wdefault when running Python testdriver (#22727) - - - - - e9c0537c by Vladislav Zavialov at 2023-01-18T01:56:22-05:00 Enable -Wstar-is-type by default (#22759) Following the plan in GHC Proposal #143 "Remove the * kind syntax", which states: In the next release (or 3 years in), enable -fwarn-star-is-type by default. The "next release" happens to be 9.6.1 I also moved the T21583 test case from should_fail to should_compile, because the only reason it was failing was -Werror=compat in our test suite configuration. - - - - - 4efee43d by Ryan Scott at 2023-01-18T01:56:59-05:00 Add missing parenthesizeHsType in cvtSigTypeKind We need to ensure that the output of `cvtSigTypeKind` is parenthesized (at precedence `sigPrec`) so that any type signatures with an outermost, explicit kind signature can parse correctly. Fixes #22784. - - - - - f891a442 by Ben Gamari at 2023-01-18T07:28:00-05:00 Bump ghc-tarballs to fix #22497 It turns out that gmp 6.2.1 uses the platform-reserved `x18` register on AArch64/Darwin. This was fixed in upstream changeset 18164:5f32dbc41afc, which was merged in 2020. Here I backport this patch although I do hope that a new release is forthcoming soon. Bumps gmp-tarballs submodule. Fixes #22497. - - - - - b13c6ea5 by Ben Gamari at 2023-01-18T07:28:00-05:00 Bump gmp-tarballs submodule This backports the upstream fix for CVE-2021-43618, fixing #22789. - - - - - c45a5fff by Cheng Shao at 2023-01-18T07:28:37-05:00 Fix typo in recent darwin tests fix Corrects a typo in !9647. Otherwise T18623 will still fail on darwin and stall other people's work. - - - - - b4c14c4b by Luite Stegeman at 2023-01-18T14:21:42-05:00 Add PrimCallConv support to GHCi This adds support for calling Cmm code from bytecode using the native calling convention, allowing modules that use `foreign import prim` to be loaded and debugged in GHCi. This patch introduces a new `PRIMCALL` bytecode instruction and a helper stack frame `stg_primcall`. The code is based on the existing functionality for dealing with unboxed tuples in bytecode, which has been generalised to handle arbitrary calls. Fixes #22051 - - - - - d0a63ef8 by Adam Gundry at 2023-01-18T14:22:26-05:00 Refactor warning flag parsing to add missing flags This adds `-Werror=<group>` and `-fwarn-<group>` flags for warning groups as well as individual warnings. Previously these were defined on an ad hoc basis so for example we had `-Werror=compat` but not `-Werror=unused-binds`, whereas we had `-fwarn-unused-binds` but not `-fwarn-compat`. Fixes #22182. - - - - - 7ed1b8ef by Adam Gundry at 2023-01-18T14:22:26-05:00 Minor corrections to comments - - - - - 5389681e by Adam Gundry at 2023-01-18T14:22:26-05:00 Revise warnings documentation in user's guide - - - - - ab0d5cda by Adam Gundry at 2023-01-18T14:22:26-05:00 Move documentation of deferred type error flags out of warnings section - - - - - eb5a6b91 by John Ericson at 2023-01-18T22:24:10-05:00 Give the RTS it's own configure script Currently it doesn't do much anything, we are just trying to introduce it without breaking the build. Later, we will move functionality from the top-level configure script over to it. We need to bump Cabal for https://github.com/haskell/cabal/pull/8649; to facilitate and existing hack of skipping some configure checks for the RTS we now need to skip just *part* not *all* of the "post configure" hook, as running the configure script (which we definitely want to do) is also implemented as part of the "post configure" hook. But doing this requires exposing functionality that wasn't exposed before. - - - - - 32ab07bf by Andrew Lelechenko at 2023-01-18T22:24:51-05:00 ghc package does not have to depend on terminfo - - - - - 981ff7c4 by Andrew Lelechenko at 2023-01-18T22:24:51-05:00 ghc-pkg does not have to depend on terminfo - - - - - f058e367 by Ben Gamari at 2023-01-18T22:25:27-05:00 nativeGen/X86: MFENCE is unnecessary for release semantics In #22764 a user noticed that a program implementing a simple atomic counter via an STRef regressed significantly due to the introduction of necessary atomic operations in the MutVar# primops (#22468). This regression was caused by a bug in the NCG, which emitted an unnecessary MFENCE instruction for a release-ordered atomic write. MFENCE is rather only needed to achieve sequentially consistent ordering. Fixes #22764. - - - - - 154889db by Ryan Scott at 2023-01-18T22:26:03-05:00 Add regression test for #22151 Issue #22151 was coincidentally fixed in commit aed1974e92366ab8e117734f308505684f70cddf (`Refactor the treatment of loopy superclass dicts`). This adds a regression test to ensure that the issue remains fixed. Fixes #22151. - - - - - 14b5982a by Andrei Borzenkov at 2023-01-18T22:26:43-05:00 Fix printing of promoted MkSolo datacon (#22785) Problem: In 2463df2f, the Solo data constructor was renamed to MkSolo, and Solo was turned into a pattern synonym for backwards compatibility. Since pattern synonyms can not be promoted, the old code that pretty-printed promoted single-element tuples started producing ill-typed code: t :: Proxy ('Solo Int) This fails with "Pattern synonym ‘Solo’ used as a type" The solution is to track the distinction between type constructors and data constructors more carefully when printing single-element tuples. - - - - - 1fe806d3 by Cheng Shao at 2023-01-23T04:48:47-05:00 hadrian: add hi_core flavour transformer The hi_core flavour transformer enables -fwrite-if-simplified-core for stage1 libraries, which emit core into interface files to make it possible to restart code generation. Building boot libs with it makes it easier to use GHC API to prototype experimental backends that needs core/stg at link time. - - - - - 317cad26 by Cheng Shao at 2023-01-23T04:48:47-05:00 hadrian: add missing docs for recently added flavour transformers - - - - - 658f4446 by Ben Gamari at 2023-01-23T04:49:23-05:00 gitlab-ci: Add Rocky8 jobs Addresses #22268. - - - - - a83ec778 by Vladislav Zavialov at 2023-01-23T04:49:58-05:00 Set "since: 9.8" for TypeAbstractions and -Wterm-variable-capture These flags did not make it into the 9.6 release series, so the "since" annotations must be corrected. - - - - - fec7c2ea by Alan Zimmerman at 2023-01-23T04:50:33-05:00 EPA: Add SourceText to HsOverLabel To be able to capture string literals with possible escape codes as labels. Close #22771 - - - - - 3efd1e99 by Ben Gamari at 2023-01-23T04:51:08-05:00 template-haskell: Bump version to 2.20.0.0 Updates `text` and `exceptions` submodules for bounds bumps. Addresses #22767. - - - - - 0900b584 by Cheng Shao at 2023-01-23T04:51:45-05:00 hadrian: disable alloca for in-tree GMP on wasm32 When building in-tree GMP for wasm32, disable its alloca usage, since it may potentially cause stack overflow (e.g. #22602). - - - - - db0f1bfd by Cheng Shao at 2023-01-23T04:52:21-05:00 Bump process submodule Includes a critical fix for wasm32, see https://github.com/haskell/process/pull/272 for details. Also changes the existing cross test to include process stuff and avoid future regression here. - - - - - 9222b167 by Matthew Pickering at 2023-01-23T04:52:57-05:00 ghcup metadata: Fix subdir for windows bindist - - - - - 9a9bec57 by Matthew Pickering at 2023-01-23T04:52:57-05:00 ghcup metadata: Remove viPostRemove field from generated metadata This has been removed from the downstream metadata. - - - - - 82884ce0 by Simon Peyton Jones at 2023-01-23T04:53:32-05:00 Fix #22742 runtimeRepLevity_maybe was panicing unnecessarily; and the error printing code made use of the case when it should return Nothing rather than panicing. For some bizarre reason perf/compiler/T21839r shows a 10% bump in runtime peak-megagbytes-used, on a single architecture (alpine). See !9753 for commentary, but I'm going to accept it. Metric Increase: T21839r - - - - - 2c6deb18 by Bryan Richter at 2023-01-23T14:12:22+02:00 codeowners: Add Ben, Matt, and Bryan to CI - - - - - eee3bf05 by Matthew Craven at 2023-01-23T21:46:41-05:00 Do not collect compile-time metrics for T21839r ...the testsuite doesn't handle this properly since it also collects run-time metrics. Compile-time metrics for this test are already tracked via T21839c. Metric Decrease: T21839r - - - - - 1d1dd3fb by Matthew Pickering at 2023-01-24T05:37:52-05:00 Fix recompilation checking for multiple home units The key part of this change is to store a UnitId in the `UsageHomeModule` and `UsageHomeModuleInterface`. * Fine-grained dependency tracking is used if the dependency comes from any home unit. * We actually look up the right module when checking whether we need to recompile in the `UsageHomeModuleInterface` case. These scenarios are both checked by the new tests ( multipleHomeUnits_recomp and multipleHomeUnits_recomp_th ) Fixes #22675 - - - - - 7bfb30f9 by Matthew Pickering at 2023-01-24T05:37:52-05:00 Augment target filepath by working directory when checking if module satisfies target This fixes a spurious warning in -Wmissing-home-modules. This is a simple oversight where when looking for the target in the first place we augment the search by the -working-directory flag but then fail to do so when checking this warning. Fixes #22676 - - - - - 69500dd4 by Matthew Pickering at 2023-01-24T05:37:52-05:00 Use NodeKey rather than ModuleName in pruneCache The `pruneCache` function assumes that the list of `CachedInfo` all have unique `ModuleName`, this is not true: * In normal compilation, the same module name can appear for a file and it's boot file. * In multiple home unit compilation the same ModuleName can appear in different units The fix is to use a `NodeKey` as the actual key for the interfaces which includes `ModuleName`, `IsBoot` and `UnitId`. Fixes #22677 - - - - - 336b2b1c by Matthew Pickering at 2023-01-24T05:37:52-05:00 Recompilation checking: Don't try to find artefacts for Interactive & hs-boot combo In interactive mode we don't produce any linkables for hs-boot files. So we also need to not going looking for them when we check to see if we have all the right objects needed for recompilation. Ticket #22669 - - - - - 6469fea7 by Matthew Pickering at 2023-01-24T05:37:52-05:00 Don't write o-boot files in Interactive mode We should not be producing object files when in interactive mode but we still produced the dummy o-boot files. These never made it into a `Linkable` but then confused the recompilation checker. Fixes #22669 - - - - - 06cc0a95 by Matthew Pickering at 2023-01-24T05:37:52-05:00 Improve driver diagnostic messages by including UnitId in message Currently the driver diagnostics don't give any indication about which unit they correspond to. For example `-Wmissing-home-modules` can fire multiple times for each different home unit and gives no indication about which unit it's actually reporting about. Perhaps a longer term fix is to generalise the providence information away from a SrcSpan so that these kind of whole project errors can be reported with an accurate provenance. For now we can just include the `UnitId` in the error message. Fixes #22678 - - - - - 4fe9eaff by Matthew Pickering at 2023-01-24T05:37:52-05:00 Key ModSummary cache by UnitId as well as FilePath Multiple units can refer to the same files without any problem. Just another assumption which needs to be updated when we may have multiple home units. However, there is the invariant that within each unit each file only maps to one module, so as long as we also key the cache by UnitId then we are all good. This led to some confusing behaviour in GHCi when reloading, multipleHomeUnits_shared distils the essence of what can go wrong. Fixes #22679 - - - - - ada29f5c by Matthew Pickering at 2023-01-24T05:37:52-05:00 Finder: Look in current unit before looking in any home package dependencies In order to preserve existing behaviour it's important to look within the current component before consideirng a module might come from an external component. This already happened by accident in `downsweep`, (because roots are used to repopulated the cache) but in the `Finder` the logic was the wrong way around. Fixes #22680 ------------------------- Metric Decrease: MultiComponentModules MultiComponentModulesRecomp -------------------------p - - - - - be701cc6 by Matthew Pickering at 2023-01-24T05:37:52-05:00 Debug: Print full NodeKey when pretty printing ModuleGraphNode This is helpful when debugging multiple component issues. - - - - - 34d2d463 by Krzysztof Gogolewski at 2023-01-24T05:38:32-05:00 Fix Lint check for duplicate external names Lint was checking for duplicate external names by calling removeDups, which needs a comparison function that is passed to Data.List.sortBy. But the comparison was not a valid ordering - it returned LT if one of the names was not external. For example, the previous implementation won't find a duplicate in [M.x, y, M.x]. Instead, we filter out non-external names before looking for duplicates. - - - - - 1c050ed2 by Matthew Pickering at 2023-01-24T05:39:08-05:00 Add test for T22671 This was fixed by b13c6ea5 Closes #22671 - - - - - 05e6a2d9 by Tom Ellis at 2023-01-24T12:10:52-05:00 Clarify where `f` is defined - - - - - d151546e by Cheng Shao at 2023-01-24T12:11:29-05:00 CmmToC: fix CmmRegOff for 64-bit register on a 32-bit target We used to print the offset value to a platform word sized integer. This is incorrect when the offset is negative (e.g. output of cmm constant folding) and the register is 64-bit but on a 32-bit target, and may lead to incorrect runtime result (e.g. #22607). The fix is simple: just treat it as a proper MO_Add, with the correct width info inferred from the register itself. Metric Increase: T12707 T13379 T4801 T5321FD T5321Fun - - - - - e5383a29 by Wander Hillen at 2023-01-24T20:02:26-05:00 Allow waiting for timerfd to be interrupted during rts shutdown - - - - - 1957eda1 by Ryan Scott at 2023-01-24T20:03:01-05:00 Restore Compose's Read/Show behavior to match Read1/Show1 instances Fixes #22816. - - - - - 30972827 by Matthew Pickering at 2023-01-25T03:54:14-05:00 docs: Update INSTALL.md Removes references to make. Fixes #22480 - - - - - bc038c3b by Cheng Shao at 2023-01-25T03:54:50-05:00 compiler: fix handling of MO_F_Neg in wasm NCG In the wasm NCG, we used to compile MO_F_Neg to 0.0-x. It was an oversight, there actually exists f32.neg/f64.neg opcodes in the wasm spec and those should be used instead! The old behavior almost works, expect when GHC compiles the -0.0 literal, which will incorrectly become 0.0. - - - - - e987e345 by Sylvain Henry at 2023-01-25T14:47:41-05:00 Hadrian: correctly detect AR at-file support Stage0's ar may not support at-files. Take it into account. Found while cross-compiling from Darwin to Windows. - - - - - 48131ee2 by Sylvain Henry at 2023-01-25T14:47:41-05:00 Hadrian: fix Windows cross-compilation Decision to build either unix or Win32 package must be stage specific for cross-compilation to be supported. - - - - - 288fa017 by Sylvain Henry at 2023-01-25T14:47:41-05:00 Fix RTS build on Windows This change fixes a cross-compilation issue from ArchLinux to Windows because these symbols weren't found. - - - - - 2fdf22ae by Sylvain Henry at 2023-01-25T14:47:41-05:00 configure: support "windows" as an OS - - - - - 13a0566b by Simon Peyton Jones at 2023-01-25T14:48:16-05:00 Fix in-scope set in specImports Nothing deep here; I had failed to bring some floated dictionary binders into scope. Exposed by -fspecialise-aggressively Fixes #22715. - - - - - b7efdb24 by Matthew Pickering at 2023-01-25T14:48:51-05:00 ci: Disable HLint job due to excessive runtime The HLint jobs takes much longer to run (20 minutes) after "Give the RTS it's own configure script" eb5a6b91 Now the CI job will build the stage0 compiler before it generates the necessary RTS headers. We either need to: * Fix the linting rules so they take much less time * Revert the commit * Remove the linting of base from the hlint job * Remove the hlint job This is highest priority as it is affecting all CI pipelines. For now I am just disabling the job because there are many more pressing matters at hand. Ticket #22830 - - - - - 1bd32a35 by Sylvain Henry at 2023-01-26T12:34:21-05:00 Factorize hptModulesBelow Create and use moduleGraphModulesBelow in GHC.Unit.Module.Graph that doesn't need anything from the driver to be used. - - - - - 1262d3f8 by Matthew Pickering at 2023-01-26T12:34:56-05:00 Store dehydrated data structures in CgModBreaks This fixes a tricky leak in GHCi where we were retaining old copies of HscEnvs when reloading. If not all modules were recompiled then these hydrated fields in break points would retain a reference to the old HscEnv which could double memory usage. Fixes #22530 - - - - - e27eb80c by Matthew Pickering at 2023-01-26T12:34:56-05:00 Force more in NFData Name instance Doesn't force the lazy `OccName` field (#19619) which is already known as a really bad source of leaks. When we slam the hammer storing Names on disk (in interface files or the like), all this should be forced as otherwise a `Name` can easily retain an `Id` and hence the entire world. Fixes #22833 - - - - - 3d004d5a by Matthew Pickering at 2023-01-26T12:34:56-05:00 Force OccName in tidyTopName This occname has just been derived from an `Id`, so need to force it promptly so we can release the Id back to the world. Another symptom of the bug caused by #19619 - - - - - f2a0fea0 by Matthew Pickering at 2023-01-26T12:34:56-05:00 Strict fields in ModNodeKey (otherwise retains HomeModInfo) Towards #22530 - - - - - 5640cb1d by Sylvain Henry at 2023-01-26T12:35:36-05:00 Hadrian: fix doc generation Was missing dependencies on files generated by templates (e.g. ghc.cabal) - - - - - 3e827c3f by Richard Eisenberg at 2023-01-26T20:06:53-05:00 Do newtype unwrapping in the canonicaliser and rewriter See Note [Unwrap newtypes first], which has the details. Close #22519. - - - - - b3ef5c89 by doyougnu at 2023-01-26T20:07:48-05:00 tryFillBuffer: strictify more speculative bangs - - - - - d0d7ba0f by Vladislav Zavialov at 2023-01-26T20:08:25-05:00 base: NoImplicitPrelude in Data.Void and Data.Kind This change removes an unnecessary dependency on Prelude from two modules in the base package. - - - - - fa1db923 by Matthew Pickering at 2023-01-26T20:09:00-05:00 ci: Add ubuntu18_04 nightly and release jobs This adds release jobs for ubuntu18_04 which uses glibc 2.27 which is older than the 2.28 which is used by Rocky8 bindists. Ticket #22268 - - - - - 807310a1 by Matthew Pickering at 2023-01-26T20:09:00-05:00 rel-eng: Add missing rocky8 bindist We intend to release rocky8 bindist so the fetching script needs to know about them. - - - - - c7116b10 by Ben Gamari at 2023-01-26T20:09:35-05:00 base: Make changelog proposal references more consistent Addresses #22773. - - - - - 6932cfc7 by Sylvain Henry at 2023-01-26T20:10:27-05:00 Fix spurious change from !9568 - - - - - e480fbc2 by Ben Gamari at 2023-01-27T05:01:24-05:00 rts: Use C11-compliant static assertion syntax Previously we used `static_assert` which is only available in C23. By contrast, C11 only provides `_Static_assert`. Fixes #22777 - - - - - 2648c09c by Andrei Borzenkov at 2023-01-27T05:02:07-05:00 Replace errors from badOrigBinding with new one (#22839) Problem: in 02279a9c the type-level [] syntax was changed from a built-in name to an alias for the GHC.Types.List constructor. badOrigBinding assumes that if a name is not built-in then it must have come from TH quotation, but this is not necessarily the case with []. The outdated assumption in badOrigBinding leads to incorrect error messages. This code: data [] Fails with "Cannot redefine a Name retrieved by a Template Haskell quote: []" Unfortunately, there is not enough information in RdrName to directly determine if the name was constructed via TH or by the parser, so this patch changes the error message instead. It unifies TcRnIllegalBindingOfBuiltIn and TcRnNameByTemplateHaskellQuote into a new error TcRnBindingOfExistingName and changes its wording to avoid guessing the origin of the name. - - - - - 545bf8cf by Matthew Pickering at 2023-01-27T14:58:53+00:00 Revert "base: NoImplicitPrelude in Data.Void and Data.Kind" Fixes CI errors of the form. ``` ===> Command failed with error code: 1 ghc: panic! (the 'impossible' happened) GHC version 9.7.20230127: lookupGlobal Failed to load interface for ‘GHC.Num.BigNat’ There are files missing in the ‘ghc-bignum’ package, try running 'ghc-pkg check'. Use -v (or `:set -v` in ghci) to see a list of the files searched for. Call stack: CallStack (from HasCallStack): callStackDoc, called at compiler/GHC/Utils/Panic.hs:189:37 in ghc:GHC.Utils.Panic pprPanic, called at compiler/GHC/Tc/Utils/Env.hs:154:32 in ghc:GHC.Tc.Utils.Env CallStack (from HasCallStack): panic, called at compiler/GHC/Utils/Error.hs:454:29 in ghc:GHC.Utils.Error Please report this as a GHC bug: https://www.haskell.org/ghc/reportabug ``` This reverts commit d0d7ba0fb053ebe7f919a5932066fbc776301ccd. The module now lacks a dependency on GHC.Num.BigNat which it implicitly depends on. It is causing all CI jobs to fail so we revert without haste whilst the patch can be fixed. Fixes #22848 - - - - - 638277ba by Simon Peyton Jones at 2023-01-27T23:54:55-05:00 Detect family instance orphans correctly We were treating a type-family instance as a non-orphan if there was a type constructor on its /right-hand side/ that was local. Boo! Utterly wrong. With this patch, we correctly check the /left-hand side/ instead! Fixes #22717 - - - - - 46a53bb2 by Simon Peyton Jones at 2023-01-27T23:54:55-05:00 Report family instance orphans correctly This fixes the fact that we were not reporting orphan family instances at all. The fix here is easy, but touches a bit of code. I refactored the code to be much more similar to the way that class instances are done: - Add a fi_orphan field to FamInst, like the is_orphan field in ClsInst - Make newFamInst initialise this field, just like newClsInst - And make newFamInst report a warning for an orphan, just like newClsInst - I moved newFamInst from GHC.Tc.Instance.Family to GHC.Tc.Utils.Instantiate, just like newClsInst. - I added mkLocalFamInst to FamInstEnv, just like mkLocalClsInst in InstEnv - TcRnOrphanInstance and SuggestFixOrphanInstance are now parametrised over class instances vs type/data family instances. Fixes #19773 - - - - - faa300fb by Simon Peyton Jones at 2023-01-27T23:54:55-05:00 Avoid orphans in STG This patch removes some orphan instances in the STG namespace by introducing the GHC.Stg.Lift.Types module, which allows various type family instances to be moved to GHC.Stg.Syntax, avoiding orphan instances. - - - - - 0f25a13b by Simon Peyton Jones at 2023-01-27T23:54:55-05:00 Avoid orphans in the parser This moves Anno instances for PatBuilder from GHC.Parser.PostProcess to GHC.Parser.Types to avoid orphans. - - - - - 15750d33 by Simon Peyton Jones at 2023-01-27T23:54:55-05:00 Accept an orphan declaration (sadly) This accepts the orphan type family instance type instance DsForeignHook = ... in GHC.HsToCore.Types. See Note [The Decoupling Abstract Data Hack] in GHC.Driver.Hooks - - - - - c9967d13 by Zubin Duggal at 2023-01-27T23:55:31-05:00 bindist configure: Fail if find not found (#22691) - - - - - ad8cfed4 by John Ericson at 2023-01-27T23:56:06-05:00 Put hadrian bootstrap plans through `jq` This makes it possible to review changes with conventional diffing tools. - - - - - d0ddc01b by Ben Gamari at 2023-01-27T23:56:42-05:00 testsuite: Introduce threaded2_sanity way Incredibly, we previously did not have a single way which would test the threaded RTS with multiple capabilities and the sanity-checker enabled. - - - - - 38ad8351 by Ben Gamari at 2023-01-27T23:56:42-05:00 rts: Relax Messages assertion `doneWithMsgThrowTo` was previously too strict in asserting that the `Message` is locked. Specifically, it failed to consider that the `Message` may not be locked if we are deleting all threads during RTS shutdown. - - - - - a9fe81af by Ben Gamari at 2023-01-27T23:56:42-05:00 testsuite: Fix race in UnliftedTVar2 Previously UnliftedTVar2 would fail when run with multiple capabilities (and possibly even with one capability) as it would assume that `killThread#` would immediately kill the "increment" thread. Also, refactor the the executable to now succeed with no output and fails with an exit code. - - - - - 8519af60 by Ben Gamari at 2023-01-27T23:56:42-05:00 testsuite: Make listThreads more robust Previously it was sensitive to the labels of threads which it did not create (e.g. the IO manager event loop threads). Fix this. - - - - - 55a81995 by Ben Gamari at 2023-01-27T23:56:43-05:00 rts: Fix non-atomic mutation of enabled_capabilities - - - - - b5c75f1d by Ben Gamari at 2023-01-27T23:56:43-05:00 rts: Fix C++ compilation issues Make the RTS compilable with a C++ compiler by inserting necessary casts. - - - - - c261b62f by Ben Gamari at 2023-01-27T23:56:43-05:00 rts: Fix typo "tracingAddCapabilities" was mis-named - - - - - 77fdbd3f by Ben Gamari at 2023-01-27T23:56:43-05:00 rts: Drop long-dead fallback definitions for INFINITY & NAN These are no longer necessary since we now compile as C99. - - - - - 56c1bd98 by Ben Gamari at 2023-01-28T02:57:59-05:00 Revert "CApiFFI: add ConstPtr for encoding const-qualified pointer return types (#22043)" This reverts commit 99aca26b652603bc62953157a48e419f737d352d. - - - - - b3a3534b by nineonine at 2023-01-28T02:57:59-05:00 CApiFFI: add ConstPtr for encoding const-qualified pointer return types Previously, when using `capi` calling convention in foreign declarations, code generator failed to handle const-cualified pointer return types. This resulted in CC toolchain throwing `-Wincompatible-pointer-types-discards-qualifiers` warning. `Foreign.C.Types.ConstPtr` newtype was introduced to handle these cases - special treatment was put in place to generate appropritetly qualified C wrapper that no longer triggers the above mentioned warning. Fixes #22043. - - - - - 082b7d43 by Oleg Grenrus at 2023-01-28T02:58:38-05:00 Add Foldable1 Solo instance - - - - - 50b1e2e8 by Andrei Borzenkov at 2023-01-28T02:59:18-05:00 Convert diagnostics in GHC.Rename.Bind to proper TcRnMessage (#20115) I removed all occurrences of TcRnUnknownMessage in GHC.Rename.Bind module. Instead, these TcRnMessage messages were introduced: TcRnMultipleFixityDecls TcRnIllegalPatternSynonymDecl TcRnIllegalClassBiding TcRnOrphanCompletePragma TcRnEmptyCase TcRnNonStdGuards TcRnDuplicateSigDecl TcRnMisplacedSigDecl TcRnUnexpectedDefaultSig TcRnBindInBootFile TcRnDuplicateMinimalSig - - - - - 3330b819 by Matthew Pickering at 2023-01-28T02:59:54-05:00 hadrian: Fix library-dirs, dynamic-library-dirs and static-library-dirs in inplace .conf files Previously we were just throwing away the contents of the library-dirs fields but really we have to do the same thing as for include-dirs, relativise the paths into the current working directory and maintain any extra libraries the user has specified. Now the relevant section of the rts.conf file looks like: ``` library-dirs: ${pkgroot}/../rts/build ${pkgroot}/../../..//_build/stage1/rts/build /nix/store/av4c0fib4rkmb6sa1074z0rb1ciria5b-gperftools-2.10/lib /nix/store/2infxahfp9lj084xn3q9ib5ajks8447i-libffi-3.4.4/lib library-dirs-static: ${pkgroot}/../rts/build ${pkgroot}/../../..//_build/stage1/rts/build /nix/store/av4c0fib4rkmb6sa1074z0rb1ciria5b-gperftools-2.10/lib /nix/store/2infxahfp9lj084xn3q9ib5ajks8447i-libffi-3.4.4/lib dynamic-library-dirs: ${pkgroot}/../rts/build ${pkgroot}/../../..//_build/stage1/rts/build /nix/store/av4c0fib4rkmb6sa1074z0rb1ciria5b-gperftools-2.10/lib /nix/store/2infxahfp9lj084xn3q9ib5ajks8447i-libffi-3.4.4/lib ``` Fixes #22209 - - - - - c9ad8852 by Andrew Lelechenko at 2023-01-28T03:00:33-05:00 Document differences between Data.{Monoid,Semigroup}.{First,Last} - - - - - 7e11c6dc by Cheng Shao at 2023-01-28T03:01:09-05:00 compiler: fix subword literal narrowing logic in the wasm NCG This patch fixes the W8/W16 literal narrowing logic in the wasm NCG, which used to lower it to something like i32.const -1, without properly zeroing-out the unused higher bits. Fixes #22608. - - - - - 6ea2aa02 by Cheng Shao at 2023-01-28T03:01:46-05:00 compiler: fix lowering of CmmBlock in the wasm NCG The CmmBlock datacon was not handled in lower_CmmLit, since I thought it would have been eliminated after proc-point splitting. Turns out it still occurs in very rare occasions, and this patch is needed to fix T9329 for wasm. - - - - - 2b62739d by Andrew Lelechenko at 2023-01-28T17:16:11-05:00 Assorted changes to avoid Data.List.{head,tail} - - - - - 78c07219 by Cheng Shao at 2023-01-28T17:16:48-05:00 compiler: properly handle ForeignHints in the wasm NCG Properly handle ForeignHints of ccall arguments/return value, insert sign extends and truncations when handling signed subwords. Fixes #22852. - - - - - 9e0fefd8 by Andrei Borzenkov at 2023-01-30T14:02:04+04:00 Rename () to Unit, Rename (,,...,,) to Tuple<n> - - - - - 8bed166b by Ben Gamari at 2023-01-30T05:06:26-05:00 nativeGen: Disable asm-shortcutting on Darwin Asm-shortcutting may produce relative references to symbols defined in other compilation units. This is not something that MachO relocations support (see #21972). For this reason we disable the optimisation on Darwin. We do so without a warning since this flag is enabled by `-O2`. Another way to address this issue would be to rather implement a PLT-relocatable jump-table strategy. However, this would only benefit Darwin and does not seem worth the effort. Closes #21972. - - - - - da468391 by Cheng Shao at 2023-01-30T05:07:03-05:00 compiler: fix data section alignment in the wasm NCG Previously we tried to lower the alignment requirement as far as possible, based on the section kind inferred from the CLabel. For info tables, .p2align 1 was applied given the GC should only need the lowest bit to tag forwarding pointers. But this would lead to unaligned loads/stores, which has a performance penalty even if the wasm spec permits it. Furthermore, the test suite has shown memory corruption in a few cases when compacting gc is used. This patch takes a more conservative approach: all data sections except C strings align to word size. - - - - - 08ba8720 by Andreas Klebinger at 2023-01-30T21:18:45-05:00 ghc-the-library: Retain cafs in both static in dynamic builds. We use keepCAFsForGHCi.c to force -fkeep-cafs behaviour by using a __attribute__((constructor)) function. This broke for static builds where the linker discarded the object file since it was not reverenced from any exported code. We fix this by asserting that the flag is enabled using a function in the same module as the constructor. Which causes the object file to be retained by the linker, which in turn causes the constructor the be run in static builds. This changes nothing for dynamic builds using the ghc library. But causes static to also retain CAFs (as we expect them to). Fixes #22417. ------------------------- Metric Decrease: T21839r ------------------------- - - - - - 20598ef6 by Ryan Scott at 2023-01-30T21:19:20-05:00 Handle `type data` properly in tyThingParent_maybe Unlike most other data constructors, data constructors declared with `type data` are represented in `TyThing`s as `ATyCon` rather than `ADataCon`. The `ATyCon` case in `tyThingParent_maybe` previously did not consider the possibility of the underlying `TyCon` being a promoted data constructor, which led to the oddities observed in #22817. This patch adds a dedicated special case in `tyThingParent_maybe`'s `ATyCon` case for `type data` data constructors to fix these oddities. Fixes #22817. - - - - - 2f145052 by Ryan Scott at 2023-01-30T21:19:56-05:00 Fix two bugs in TypeData TH reification This patch fixes two issues in the way that `type data` declarations were reified with Template Haskell: * `type data` data constructors are now properly reified using `DataConI`. This is accomplished with a special case in `reifyTyCon`. Fixes #22818. * `type data` type constructors are now reified in `reifyTyCon` using `TypeDataD` instead of `DataD`. Fixes #22819. - - - - - d0f34f25 by Simon Peyton Jones at 2023-01-30T21:20:35-05:00 Take account of loop breakers in specLookupRule The key change is that in GHC.Core.Opt.Specialise.specLookupRule we were using realIdUnfolding, which ignores the loop-breaker flag. When given a loop breaker, rule matching therefore looped infinitely -- #22802. In fixing this I refactored a bit. * Define GHC.Core.InScopeEnv as a data type, and use it. (Previously it was a pair: hard to grep for.) * Put several functions returning an IdUnfoldingFun into GHC.Types.Id, namely idUnfolding alwaysActiveUnfoldingFun, whenActiveUnfoldingFun, noUnfoldingFun and use them. (The are all loop-breaker aware.) - - - - - de963cb6 by Matthew Pickering at 2023-01-30T21:21:11-05:00 ci: Remove FreeBSD job from release pipelines We no longer attempt to build or distribute this release - - - - - f26d27ec by Matthew Pickering at 2023-01-30T21:21:11-05:00 rel_eng: Add check to make sure that release jobs are downloaded by fetch-gitlab This check makes sure that if a job is a prefixed by "release-" then the script downloads it and understands how to map the job name to the platform. - - - - - 7619c0b4 by Matthew Pickering at 2023-01-30T21:21:11-05:00 rel_eng: Fix the name of the ubuntu-* jobs These were not uploaded for alpha1 Fixes #22844 - - - - - 68eb8877 by Matthew Pickering at 2023-01-30T21:21:11-05:00 gen_ci: Only consider release jobs for job metadata In particular we do not have a release job for FreeBSD so the generation of the platform mapping was failing. - - - - - b69461a0 by Jason Shipman at 2023-01-30T21:21:50-05:00 User's guide: Clarify overlapping instance candidate elimination This commit updates the user's guide section on overlapping instance candidate elimination to use "or" verbiage instead of "either/or" in regards to the current pair of candidates' being overlappable or overlapping. "Either IX is overlappable, or IY is overlapping" can cause confusion as it suggests "Either IX is overlappable, or IY is overlapping, but not both". This was initially discussed on this Discourse topic: https://discourse.haskell.org/t/clarification-on-overlapping-instance-candidate-elimination/5677 - - - - - 7cbdaad0 by Matthew Pickering at 2023-01-31T07:53:53-05:00 Fixes for cabal-reinstall CI job * Allow filepath to be reinstalled * Bump some version bounds to allow newer versions of libraries * Rework testing logic to avoid "install --lib" and package env files Fixes #22344 - - - - - fd8f32bf by Cheng Shao at 2023-01-31T07:54:29-05:00 rts: prevent potential divide-by-zero when tickInterval=0 This patch fixes a few places in RtsFlags.c that may result in divide-by-zero error when tickInterval=0, which is the default on wasm. Fixes #22603. - - - - - 085a6db6 by Joachim Breitner at 2023-01-31T07:55:05-05:00 Update note at beginning of GHC.Builtin.NAmes some things have been renamed since it was written, it seems. - - - - - 7716cbe6 by Cheng Shao at 2023-01-31T07:55:41-05:00 testsuite: use tgamma for cg007 gamma is a glibc-only deprecated function, use tgamma instead. It's required for fixing cg007 when testing the wasm unregisterised codegen. - - - - - 19c1fbcd by doyougnu at 2023-01-31T13:08:03-05:00 InfoTableProv: ShortText --> ShortByteString - - - - - 765fab98 by doyougnu at 2023-01-31T13:08:03-05:00 FastString: add fastStringToShorText - - - - - a83c810d by Simon Peyton Jones at 2023-01-31T13:08:38-05:00 Improve exprOkForSpeculation for classops This patch fixes #22745 and #15205, which are about GHC's failure to discard unnecessary superclass selections that yield coercions. See GHC.Core.Utils Note [exprOkForSpeculation and type classes] The main changes are: * Write new Note [NON-BOTTOM_DICTS invariant] in GHC.Core, and refer to it * Define new function isTerminatingType, to identify those guaranteed-terminating dictionary types. * exprOkForSpeculation has a new (very simple) case for ClassOpId * ClassOpId has a new field that says if the return type is an unlifted type, or a terminating type. This was surprisingly tricky to get right. In particular note that unlifted types are not terminating types; you can write an expression of unlifted type, that diverges. Not so for dictionaries (or, more precisely, for the dictionaries that GHC constructs). Metric Decrease: LargeRecord - - - - - f83374f8 by Krzysztof Gogolewski at 2023-01-31T13:09:14-05:00 Support "unusable UNPACK pragma" warning with -O0 Fixes #11270 - - - - - a2d814dc by Ben Gamari at 2023-01-31T13:09:50-05:00 configure: Always create the VERSION file Teach the `configure` script to create the `VERSION` file. This will serve as the stable interface to allow the user to determine the version number of a working tree. Fixes #22322. - - - - - 5618fc21 by sheaf at 2023-01-31T15:51:06-05:00 Cmm: track the type of global registers This patch tracks the type of Cmm global registers. This is needed in order to lint uses of polymorphic registers, such as SIMD vector registers that can be used both for floating-point and integer values. This changes allows us to refactor VanillaReg to not store VGcPtr, as that information is instead stored in the type of the usage of the register. Fixes #22297 - - - - - 78b99430 by sheaf at 2023-01-31T15:51:06-05:00 Revert "Cmm Lint: relax SIMD register assignment check" This reverts commit 3be48877, which weakened a Cmm Lint check involving SIMD vectors. Now that we keep track of the type a global register is used at, we can restore the original stronger check. - - - - - be417a47 by Ben Gamari at 2023-01-31T15:51:45-05:00 nativeGen/AArch64: Fix debugging output Previously various panics would rely on a half-written Show instance, leading to very unhelpful errors. Fix this. See #22798. - - - - - 30989d13 by Ben Gamari at 2023-01-31T15:51:45-05:00 nativeGen: Teach graph-colouring allocator that x18 is unusable Previously trivColourable for AArch64 claimed that at 18 registers were trivially-colourable. This is incorrect as x18 is reserved by the platform on AArch64/Darwin. See #22798. - - - - - 7566fd9d by Ben Gamari at 2023-01-31T15:51:45-05:00 nativeGen/AArch64: Fix graph-colouring allocator Previously various `Instr` queries used by the graph-colouring allocator failed to handle a few pseudo-instructions. This manifested in compiler panicks while compiling `SHA`, which uses `-fregs-graph`. Fixes #22798. - - - - - 2cb500a5 by Ben Gamari at 2023-01-31T15:51:45-05:00 testsuite: Add regression test for #22798 - - - - - 03d693b2 by Ben Gamari at 2023-01-31T15:52:32-05:00 Revert "Hadrian: fix doc generation" This is too large of a hammer. This reverts commit 5640cb1d84d3cce4ce0a9e90d29b2b20d2b38c2f. - - - - - f838815c by Ben Gamari at 2023-01-31T15:52:32-05:00 hadrian: Sphinx docs require templated cabal files The package-version discovery logic in `doc/users_guide/package_versions.py` uses packages' cabal files to determine package versions. Teach Sphinx about these dependencies in cases where the cabal files are generated by templates. - - - - - 2e48c19a by Ben Gamari at 2023-01-31T15:52:32-05:00 hadrian: Refactor templating logic This refactors Hadrian's autoconf-style templating logic to be explicit about which interpolation variables should be substituted in which files. This clears the way to fix #22714 without incurring rule cycles. - - - - - 93f0e3c4 by Ben Gamari at 2023-01-31T15:52:33-05:00 hadrian: Substitute LIBRARY_*_VERSION variables This teaches Hadrian to substitute the `LIBRARY_*_VERSION` variables in `libraries/prologue.txt`, fixing #22714. Fixes #22714. - - - - - 22089f69 by Ben Gamari at 2023-01-31T20:46:27-05:00 Bump transformers submodule to 0.6.0.6 Fixes #22862. - - - - - f0eefa3c by Cheng Shao at 2023-01-31T20:47:03-05:00 compiler: properly handle non-word-sized CmmSwitch scrutinees in the wasm NCG Currently, the wasm NCG has an implicit assumption: all CmmSwitch scrutinees are 32-bit integers. This is not always true; #22864 is one counter-example with a 64-bit scrutinee. This patch fixes the logic by explicitly converting the scrutinee to a word that can be used as a br_table operand. Fixes #22871. Also includes a regression test. - - - - - 9f95db54 by Simon Peyton Jones at 2023-02-01T08:55:08+00:00 Improve treatment of type applications in patterns This patch fixes a subtle bug in the typechecking of type applications in patterns, e.g. f (MkT @Int @a x y) = ... See Note [Type applications in patterns] in GHC.Tc.Gen.Pat. This fixes #19847, #22383, #19577, #21501 - - - - - 955a99ea by Simon Peyton Jones at 2023-02-01T12:31:23-05:00 Treat existentials correctly in dubiousDataConInstArgTys Consider (#22849) data T a where MkT :: forall k (t::k->*) (ix::k). t ix -> T @k a Then dubiousDataConInstArgTys MkT [Type, Foo] should return [Foo (ix::Type)] NOT [Foo (ix::k)] A bit of an obscure case, but it's an outright bug, and the fix is easy. - - - - - 0cc16aaf by Matthew Pickering at 2023-02-01T12:31:58-05:00 Bump supported LLVM range from 10 through 15 to 11 through 16 LLVM 15 turns on the new pass manager by default, which we have yet to migrate to so for new we pass the `-enable-new-pm-0` flag in our llvm-passes flag. LLVM 11 was the first version to support the `-enable-new-pm` flag so we bump the lowest supported version to 11. Our CI jobs are using LLVM 12 so they should continue to work despite this bump to the lower bound. Fixes #21936 - - - - - f94f1450 by Matthew Pickering at 2023-02-01T12:31:58-05:00 Bump DOCKER_REV to use alpine image without LLVM installed alpine_3_12 only supports LLVM 10, which is now outside the supported version range. - - - - - 083e26ed by Matthew Pickering at 2023-02-01T17:43:21-05:00 Remove tracing OPTIONS_GHC These were accidentally left over from !9542 - - - - - 354aa47d by Teo Camarasu at 2023-02-01T17:44:00-05:00 doc: fix gcdetails_block_fragmentation_bytes since annotation - - - - - 61ce5bf6 by Jaro Reinders at 2023-02-02T00:15:30-05:00 compiler: Implement higher order patterns in the rule matcher This implements proposal 555 and closes ticket #22465. See the proposal and ticket for motivation. The core changes of this patch are in the GHC.Core.Rules.match function and they are explained in the Note [Matching higher order patterns]. - - - - - 394b91ce by doyougnu at 2023-02-02T00:16:10-05:00 CI: JavaScript backend runs testsuite This MR runs the testsuite for the JS backend. Note that this is a temporary solution until !9515 is merged. Key point: The CI runs hadrian on the built cross compiler _but not_ on the bindist. Other Highlights: - stm submodule gets a bump to mark tests as broken - several tests are marked as broken or are fixed by adding more - conditions to their test runner instance. List of working commit messages: CI: test cross target _and_ emulator CI: JS: Try run testsuite with hadrian JS.CI: cleanup and simplify hadrian invocation use single bracket, print info JS CI: remove call to test_compiler from hadrian don't build haddock JS: mark more tests as broken Tracked in https://gitlab.haskell.org/ghc/ghc/-/issues/22576 JS testsuite: don't skip sum_mod test Its expected to fail, yet we skipped it which automatically makes it succeed leading to an unexpected success, JS testsuite: don't mark T12035j as skip leads to an unexpected pass JS testsuite: remove broken on T14075 leads to unexpected pass JS testsuite: mark more tests as broken JS testsuite: mark T11760 in base as broken JS testsuite: mark ManyUnbSums broken submodules: bump process and hpc for JS tests Both submodules has needed tests skipped or marked broken for th JS backend. This commit now adds these changes to GHC. See: HPC: https://gitlab.haskell.org/hpc/hpc/-/merge_requests/21 Process: https://github.com/haskell/process/pull/268 remove js_broken on now passing tests separate wasm and js backend ci test: T11760: add threaded, non-moving only_ways test: T10296a add req_c T13894: skip for JS backend tests: jspace, T22333: mark as js_broken(22573) test: T22513i mark as req_th stm submodule: mark stm055, T16707 broken for JS tests: js_broken(22374) on unpack_sums_6, T12010 dont run diff on JS CI, cleanup fixup: More CI cleanup fix: align text to master fix: align exceptions submodule to master CI: Bump DOCKER_REV Bump to ci-images commit that has a deb11 build with node. Required for !9552 testsuite: mark T22669 as js_skip See #22669 This test tests that .o-boot files aren't created when run in using the interpreter backend. Thus this is not relevant for the JS backend. testsuite: mark T22671 as broken on JS See #22835 base.testsuite: mark Chan002 fragile for JS see #22836 revert: submodule process bump bump stm submodule New hash includes skips for the JS backend. testsuite: mark RnPatternSynonymFail broken on JS Requires TH: - see !9779 - and #22261 compiler: GHC.hs ifdef import Utils.Panic.Plain - - - - - 1ffe770c by Cheng Shao at 2023-02-02T09:40:38+00:00 docs: 9.6 release notes for wasm backend - - - - - 0ada4547 by Matthew Pickering at 2023-02-02T11:39:44-05:00 Disable unfolding sharing for interface files with core definitions Ticket #22807 pointed out that the RHS sharing was not compatible with -fignore-interface-pragmas because the flag would remove unfoldings from identifiers before the `extra-decls` field was populated. For the 9.6 timescale the only solution is to disable this sharing, which will make interface files bigger but this is acceptable for the first release of `-fwrite-if-simplified-core`. For 9.8 it would be good to fix this by implementing #20056 due to the large number of other bugs that would fix. I also improved the error message in tc_iface_binding to avoid the "no match in record selector" error but it should never happen now as the entire sharing logic is disabled. Also added the currently broken test for #22807 which could be fixed by !6080 Fixes #22807 - - - - - 7e2d3eb5 by lrzlin at 2023-02-03T05:23:27-05:00 Enable tables next to code for LoongArch64 - - - - - 2931712a by Wander Hillen at 2023-02-03T05:24:06-05:00 Move pthread and timerfd ticker implementations to separate files - - - - - 41c4baf8 by Ben Gamari at 2023-02-03T05:24:44-05:00 base: Fix Note references in GHC.IO.Handle.Types - - - - - 31358198 by Andrew Lelechenko at 2023-02-03T05:25:22-05:00 Bump submodule containers to 0.6.7 Metric Decrease: ManyConstructors T10421 T12425 T12707 T13035 T13379 T15164 T1969 T783 T9198 T9961 WWRec - - - - - 8feb9301 by Ben Gamari at 2023-02-03T05:25:59-05:00 gitlab-ci: Eliminate redundant ghc --info output Previously ci.sh would emit the output of `ghc --info` every time it ran when using the nix toolchain. This produced a significant amount of noise. See #22861. - - - - - de1d1512 by Ryan Scott at 2023-02-03T14:07:30-05:00 Windows: Remove mingwex dependency The clang based toolchain uses ucrt as its math library and so mingwex is no longer needed. In fact using mingwex will cause incompatibilities as the default routines in both have differing ULPs and string formatting modifiers. ``` $ LIBRARY_PATH=/mingw64/lib ghc/_build/stage1/bin/ghc Bug.hs -fforce-recomp && ./Bug.exe [1 of 2] Compiling Main ( Bug.hs, Bug.o ) ghc.exe: | C:\Users\winferno\Software\ghc\_build\stage1\lib\x86_64-windows-ghc-9.5.20220908\base-4.17.0.0\libHSbase-4.17.0.0.a: unknown symbol `__imp___p__environ' ghc.exe: | C:\Users\winferno\Software\ghc\_build\stage1\lib\x86_64-windows-ghc-9.5.20220908\base-4.17.0.0\libHSbase-4.17.0.0.a: unknown symbol `__hscore_get_errno' ghc.exe: | C:\Users\winferno\Software\ghc\_build\stage1\lib\x86_64-windows-ghc-9.5.20220908\base-4.17.0.0\libHSbase-4.17.0.0.a: unknown symbol `base_ForeignziCziError_errnoToIOError_info' ghc.exe: | C:\Users\winferno\Software\ghc\_build\stage1\lib\x86_64-windows-ghc-9.5.20220908\base-4.17.0.0\libHSbase-4.17.0.0.a: unknown symbol `base_GHCziWindows_failIf2_closure' ghc.exe: | C:\Users\winferno\Software\ghc\_build\stage1\lib\x86_64-windows-ghc-9.5.20220908\base-4.17.0.0\libHSbase-4.17.0.0.a: unknown symbol `base_GHCziIOziEncodingziCodePageziAPI_mkCodePageEncoding_info' ghc.exe: | C:\Users\winferno\Software\ghc\_build\stage1\lib\x86_64-windows-ghc-9.5.20220908\base-4.17.0.0\libHSbase-4.17.0.0.a: unknown symbol `base_GHCziIOziEncodingziCodePage_currentCodePage_closure' ghc.exe: | C:\Users\winferno\Software\ghc\_build\stage1\lib\x86_64-windows-ghc-9.5.20220908\base-4.17.0.0\libHSbase-4.17.0.0.a: unknown symbol `base_GHCziIOziEncoding_getForeignEncoding_closure' ghc.exe: | C:\Users\winferno\Software\ghc\_build\stage1\lib\x86_64-windows-ghc-9.5.20220908\base-4.17.0.0\libHSbase-4.17.0.0.a: unknown symbol `base_ForeignziCziString_withCStringLen1_info' ghc.exe: | C:\Users\winferno\Software\ghc\_build\stage1\lib\x86_64-windows-ghc-9.5.20220908\base-4.17.0.0\libHSbase-4.17.0.0.a: unknown symbol `base_GHCziIOziHandleziInternals_zdwflushCharReadBuffer_info' ghc.exe: | C:\Users\winferno\Software\ghc\_build\stage1\lib\x86_64-windows-ghc-9.5.20220908\base-4.17.0.0\libHSbase-4.17.0.0.a: unknown symbol `base_GHCziIOziHandleziText_hGetBuf1_info' ghc.exe: | C:\Users\winferno\Software\ghc\_build\stage1\lib\x86_64-windows-ghc-9.5.20220908\base-4.17.0.0\libHSbase-4.17.0.0.a: unknown symbol `base_GHCziFingerprint_fingerprintString_closure' ghc.exe: | C:\Users\winferno\Software\ghc\_build\stage1\lib\x86_64-windows-ghc-9.5.20220908\base-4.17.0.0\libHSbase-4.17.0.0.a: unknown symbol `base_DataziTypeableziInternal_mkTrCon_closure' ghc.exe: | C:\Users\winferno\Software\ghc\_build\stage1\lib\x86_64-windows-ghc-9.5.20220908\base-4.17.0.0\libHSbase-4.17.0.0.a: unknown symbol `base_GHCziException_errorCallWithCallStackException_closure' ghc.exe: | C:\Users\winferno\Software\ghc\_build\stage1\lib\x86_64-windows-ghc-9.5.20220908\base-4.17.0.0\libHSbase-4.17.0.0.a: unknown symbol `base_GHCziErr_error_info' ghc.exe: | C:\Users\winferno\Software\ghc\_build\stage1\lib\x86_64-windows-ghc-9.5.20220908\template-haskell-2.19.0.0\libHStemplate-haskell-2.19.0.0.a: unknown symbol `base_DataziMaybe_fromJust1_info' ghc.exe: | C:\Users\winferno\Software\ghc\_build\stage1\lib\x86_64-windows-ghc-9.5.20220908\template-haskell-2.19.0.0\libHStemplate-haskell-2.19.0.0.a: unknown symbol `templatezmhaskell_LanguageziHaskellziTHziSyntax_IntPrimL_con_info' ghc.exe: ^^ Could not load 'templatezmhaskell_LanguageziHaskellziTHziLibziInternal_stringL_closure', dependency unresolved. See top entry above. <no location info>: error: GHC.ByteCode.Linker.lookupCE During interactive linking, GHCi couldn't find the following symbol: templatezmhaskell_LanguageziHaskellziTHziLibziInternal_stringL_closure This may be due to you not asking GHCi to load extra object files, archives or DLLs needed by your current session. Restart GHCi, specifying the missing library using the -L/path/to/object/dir and -lmissinglibname flags, or simply by naming the relevant files on the GHCi command line. Alternatively, this link failure might indicate a bug in GHCi. If you suspect the latter, please report this as a GHC bug: https://www.haskell.org/ghc/reportabug ``` - - - - - 48e39195 by Tamar Christina at 2023-02-03T14:07:30-05:00 linker: Fix BFD import libraries This commit fixes the BFD style import library support in the runtime linker. This was accidentally broken during the refactoring to clang and went unnoticed because clang itself is unable to generate the BFD style import libraries. With this change we can not link against both GCC or Clang produced libraries again and intermix code produced by both compilers. - - - - - b2bb3e62 by Ben Gamari at 2023-02-03T14:07:30-05:00 Bump Windows toolchain Updates to LLVM 14, hopefully fixing #21964. - - - - - bf3f88a1 by Andreas Klebinger at 2023-02-03T14:08:07-05:00 Fix CallerCC potentially shadowing other cost centres. Add a CallerCC cost centre flavour for cost centres added by the CallerCC pass. This avoids potential accidental shadowing between CCs added by user annotations and ones added by CallerCC. - - - - - faea4bcd by j at 2023-02-03T14:08:47-05:00 Disable several ignore-warning flags in genapply. - - - - - 25537dfd by Ben Gamari at 2023-02-04T04:12:57-05:00 Revert "Use fix-sized bit-fiddling primops for fixed size boxed types" This reverts commit 4512ad2d6a8e65ea43c86c816411cb13b822f674. This was never applied to master/9.6 originally. (cherry picked from commit a44bdc2720015c03d57f470b759ece7fab29a57a) - - - - - 7612dc71 by Krzysztof Gogolewski at 2023-02-04T04:13:34-05:00 Minor refactor * Introduce refactorDupsOn f = refactorDups (comparing f) * Make mkBigTupleCase and coreCaseTuple monadic. Every call to those functions was preceded by calling newUniqueSupply. * Use mkUserLocalOrCoVar, which is equivalent to combining mkLocalIdOrCoVar with mkInternalName. - - - - - 5a54ac0b by Andrew Lelechenko at 2023-02-04T18:48:32-05:00 Fix colors in emacs terminal - - - - - 3c0f0c6d by Andrew Lelechenko at 2023-02-04T18:49:11-05:00 base changelog: move entries which were not backported to ghc-9.6 to base-4.19 section - - - - - b18fbf52 by Josh Meredith at 2023-02-06T07:47:57+00:00 Update JavaScript fileStat to match Emscripten layout - - - - - 6636b670 by Sylvain Henry at 2023-02-06T09:43:21-05:00 JS: replace "js" architecture with "javascript" Despite Cabal supporting any architecture name, `cabal --check` only supports a few built-in ones. Sadly `cabal --check` is used by Hackage hence using any non built-in name in a package (e.g. `arch(js)`) is rejected and the package is prevented from being uploaded on Hackage. Luckily built-in support for the `javascript` architecture was added for GHCJS a while ago. In order to allow newer `base` to be uploaded on Hackage we make the switch from `js` to `javascript` architecture. Fixes #22740. Co-authored-by: Ben Gamari <ben at smart-cactus.org> - - - - - 77a8234c by Luite Stegeman at 2023-02-06T09:43:59-05:00 Fix marking async exceptions in the JS backend Async exceptions are posted as a pair of the exception and the thread object. This fixes the marking pass to correctly follow the two elements of the pair. Potentially fixes #22836 - - - - - 3e09cf82 by Jan Hrček at 2023-02-06T09:44:38-05:00 Remove extraneous word in Roles user guide - - - - - b17fb3d9 by sheaf at 2023-02-07T10:51:33-05:00 Don't allow . in overloaded labels This patch removes . from the list of allowed characters in a non-quoted overloaded label, as it was realised this steals syntax, e.g. (#.). Users who want this functionality will have to add quotes around the label, e.g. `#"17.28"`. Fixes #22821 - - - - - 5dce04ee by romes at 2023-02-07T10:52:10-05:00 Update kinds in comments in GHC.Core.TyCon Use `Type` instead of star kind (*) Fix comment with incorrect kind * to have kind `Constraint` - - - - - 92916194 by Ben Gamari at 2023-02-07T10:52:48-05:00 Revert "Use fix-sized equality primops for fixed size boxed types" This reverts commit 024020c38126f3ce326ff56906d53525bc71690c. This was never applied to master/9.6 originally. See #20405 for why using these primops is a bad idea. (cherry picked from commit b1d109ad542e4c37ae5af6ace71baf2cb509d865) - - - - - c1670c6b by Sylvain Henry at 2023-02-07T21:25:18-05:00 JS: avoid head/tail and unpackFS - - - - - a9912de7 by Krzysztof Gogolewski at 2023-02-07T21:25:53-05:00 testsuite: Fix Python warnings (#22856) - - - - - 9ee761bf by sheaf at 2023-02-08T14:40:40-05:00 Fix tyvar scoping within class SPECIALISE pragmas Type variables from class/instance headers scope over class/instance method type signatures, but DO NOT scope over the type signatures in SPECIALISE and SPECIALISE instance pragmas. The logic in GHC.Rename.Bind.rnMethodBinds correctly accounted for SPECIALISE inline pragmas, but forgot to apply the same treatment to method SPECIALISE pragmas, which lead to a Core Lint failure with an out-of-scope type variable. This patch makes sure we apply the same logic for both cases. Fixes #22913 - - - - - 7eac2468 by Matthew Pickering at 2023-02-08T14:41:17-05:00 Revert "Don't keep exit join points so much" This reverts commit caced75765472a1a94453f2e5a439dba0d04a265. It seems the patch "Don't keep exit join points so much" is causing wide-spread regressions in the bytestring library benchmarks. If I revert it then the 9.6 numbers are better on average than 9.4. See https://gitlab.haskell.org/ghc/ghc/-/issues/22893#note_479525 ------------------------- Metric Decrease: MultiComponentModules MultiComponentModulesRecomp MultiLayerModules MultiLayerModulesRecomp MultiLayerModulesTH_Make T12150 T13386 T13719 T21839c T3294 parsing001 ------------------------- - - - - - 633f2799 by Cheng Shao at 2023-02-08T18:42:16-05:00 testsuite: remove config.use_threads This patch simplifies the testsuite driver by removing the use_threads config field. It's just a degenerate case of threads=1. - - - - - ca6673e3 by Cheng Shao at 2023-02-08T18:42:16-05:00 testsuite: use concurrent.futures.ThreadPoolExecutor in the driver The testsuite driver used to create one thread per test case, and explicitly use semaphore and locks for rate limiting and synchronization. This is a bad practice in any language, and occasionally may result in livelock conditions (e.g. #22889). This patch uses concurrent.futures.ThreadPoolExecutor for scheduling test case runs, which is simpler and more robust. - - - - - f22cce70 by Alan Zimmerman at 2023-02-08T18:42:51-05:00 EPA: Comment between module and where should be in header comments Do not apply the heuristic to associate a comment with a prior declaration for the first declaration in the file. Closes #22919 - - - - - d69ecac2 by Josh Meredith at 2023-02-09T03:24:05-05:00 JS generated refs: update testsuite conditions - - - - - 2ea1a6bc by sheaf at 2023-02-09T03:24:44-05:00 Bump transformers to 0.6.1.0 This allows us to avoid orphans for Foldable1 instances, fixing #22898. Updates transformers submodule. - - - - - d9d0c28d by konsumlamm at 2023-02-09T14:07:48-05:00 Update `Data.List.singleton` doc comment - - - - - fe9cd6ef by Ben Gamari at 2023-02-09T14:08:23-05:00 gitlab-template: Emphasize `user facing` label My sense is that the current mention of the ~"user facing" label is overlooked by many MR authors. Let's move this point up in the list to make it more likely that it is seen. Also rephrase some of the points. - - - - - e45eb828 by Simon Peyton Jones at 2023-02-10T06:51:28-05:00 Refactor the simplifier a bit to fix #22761 The core change in this commit, which fixes #22761, is that * In a Core rule, ru_rhs is always occ-analysed. This means adding a couple of calls to occurAnalyseExpr when building a Rule, in * GHC.Core.Rules.mkRule * GHC.Core.Opt.Simplify.Iteration.simplRules But diagosing the bug made me stare carefully at the code of the Simplifier, and I ended up doing some only-loosely-related refactoring. * I think that RULES could be lost because not every code path did addBndrRules * The code around lambdas was very convoluted It's mainly moving deck chairs around, but I like it more now. - - - - - 11e0cacb by Rebecca Turner at 2023-02-10T06:52:09-05:00 Detect the `mold` linker Enables support for the `mold` linker by rui314. - - - - - 59556235 by parsonsmatt at 2023-02-10T09:53:11-05:00 Add Lift instance for Fixed - - - - - c44e5f30 by Sylvain Henry at 2023-02-10T09:53:51-05:00 Testsuite: decrease length001 timeout for JS (#22921) - - - - - 133516af by Zubin Duggal at 2023-02-10T09:54:27-05:00 compiler: Use NamedFieldPuns for `ModIface_` and `ModIfaceBackend` `NFData` instances This is a minor refactor that makes it easy to add and remove fields from `ModIface_` and `ModIfaceBackend`. Also change the formatting to make it clear exactly which fields are fully forced with `rnf` - - - - - 1e9eac1c by Matthew Pickering at 2023-02-13T11:36:41+01:00 Refresh profiling docs I went through the whole of the profiling docs and tried to amend them to reflect current best practices and tooling. In particular I removed some old references to tools such as hp2any and replaced them with references to eventlog2html. - - - - - da208b9a by Matthew Pickering at 2023-02-13T11:36:41+01:00 docs: Add section about profiling and foreign calls Previously there was no documentation for how foreign calls interacted with the profiler. This can be quite confusing for users so getting it into the user guide is the first step to a potentially better solution. See the ticket for more insightful discussion. Fixes #21764 - - - - - 081640f1 by Andrew Lelechenko at 2023-02-13T12:51:52-05:00 Document that -fproc-alignment was introduced only in GHC 8.6 - - - - - 16adc349 by Sven Tennie at 2023-02-14T11:26:31-05:00 Add clangd flag to include generated header files This enables clangd to correctly check C files that import Rts.h. (The added include directory contains ghcautoconf.h et. al.) - - - - - c399ccd9 by amesgen at 2023-02-14T11:27:14-05:00 Mention new `Foreign.Marshal.Pool` implementation in User's Guide - - - - - b9282cf7 by Ben Gamari at 2023-02-14T11:27:50-05:00 upload_ghc_libs: More control over which packages to operate on Here we add a `--skip` flag to `upload_ghc_libs`, making it easier to limit which packages to upload. This is often necessary when one package is not uploadable (e.g. see #22740). - - - - - aa3a262d by PHO at 2023-02-14T11:28:29-05:00 Assume platforms support rpaths if they use either ELF or Mach-O Not only Linux, Darwin, and FreeBSD support rpaths. Determine the usability of rpaths based on the object format, not on OS. - - - - - 47716024 by PHO at 2023-02-14T11:29:09-05:00 RTS linker: Improve compatibility with NetBSD 1. Hint address to NetBSD mmap(2) has a different semantics from that of Linux. When a hint address is provided, mmap(2) searches for a free region at or below the hint but *never* above it. This means we can't reliably search for free regions incrementally on the userland, especially when ASLR is enabled. Let the kernel do it for us if we don't care where the mapped address is going to be. 2. NetBSD not only hates to map pages as rwx, but also disallows to switch pages from rw- to r-x unless the intention is declared when pages are initially requested. This means we need a new MemoryAccess mode for pages that are going to be changed to r-x. - - - - - 11de324a by Li-yao Xia at 2023-02-14T11:29:49-05:00 base: Move changelog entry to its place - - - - - 75930424 by Ben Gamari at 2023-02-14T11:30:27-05:00 nativeGen/AArch64: Emit Atomic{Read,Write} inline Previously the AtomicRead and AtomicWrite operations were emitted as out-of-line calls. However, these tend to be very important for performance, especially the RELAXED case (which only exists for ThreadSanitizer checking). Fixes #22115. - - - - - d6411d6c by Andreas Klebinger at 2023-02-14T11:31:04-05:00 Fix some correctness issues around tag inference when targeting the bytecode generator. * Let binders are now always assumed untagged for bytecode. * Imported referenced are now always assumed to be untagged for bytecode. Fixes #22840 - - - - - 9fb4ca89 by sheaf at 2023-02-14T11:31:49-05:00 Introduce warning for loopy superclass solve Commit aed1974e completely re-engineered the treatment of loopy superclass dictionaries in instance declarations. Unfortunately, it has the potential to break (albeit in a rather minor way) user code. To alleviate migration concerns, this commit re-introduces the old behaviour. Any reliance on this old behaviour triggers a warning, controlled by `-Wloopy-superclass-solve`. The warning text explains that GHC might produce bottoming evidence, and provides a migration strategy. This allows us to provide a graceful migration period, alerting users when they are relying on this unsound behaviour. Fixes #22912 #22891 #20666 #22894 #22905 - - - - - 1928c7f3 by Cheng Shao at 2023-02-14T11:32:26-05:00 rts: make it possible to change mblock size on 32-bit targets The MBLOCK_SHIFT macro must be the single source of truth for defining the mblock size, and changing it should only affect performance, not correctness. This patch makes it truly possible to reconfigure mblock size, at least on 32-bit targets, by fixing places which implicitly relied on the previous MBLOCK_SHIFT constant. Fixes #22901. - - - - - 78aa3b39 by Simon Hengel at 2023-02-14T11:33:06-05:00 Update outdated references to notes - - - - - e8baecd2 by meooow25 at 2023-02-14T11:33:49-05:00 Documentation: Improve Foldable1 documentation * Explain foldrMap1, foldlMap1, foldlMap1', and foldrMap1' in greater detail, the text is mostly adapted from documentation of Foldable. * Describe foldr1, foldl1, foldl1' and foldr1' in terms of the above functions instead of redoing the full explanation. * Small updates to documentation of fold1, foldMap1 and toNonEmpty, again adapting from Foldable. * Update the foldMap1 example to lists instead of Sum since this is recommended for lazy right-associative folds. Fixes #22847 - - - - - 85a1a575 by romes at 2023-02-14T11:34:25-05:00 fix: Mark ghci Prelude import as implicit Fixes #22829 In GHCi, we were creating an import declaration for Prelude but we were not setting it as an implicit declaration. Therefore, ghci's import of Prelude triggered -Wmissing-import-lists. Adds regression test T22829 to testsuite - - - - - 3b019a7a by Cheng Shao at 2023-02-14T11:35:03-05:00 compiler: fix generateCgIPEStub for no-tables-next-to-code builds generateCgIPEStub already correctly implements the CmmTick finding logic for when tables-next-to-code is on/off, but it used the wrong predicate to decide when to switch between the two. Previously it switches based on whether the codegen is unregisterised, but there do exist registerised builds that disable tables-next-to-code! This patch corrects that problem. Fixes #22896. - - - - - 08c0822c by doyougnu at 2023-02-15T00:16:39-05:00 docs: release notes, user guide: add js backend Follow up from #21078 - - - - - 79d8fd65 by Bryan Richter at 2023-02-15T00:17:15-05:00 Allow failure in nightly-x86_64-linux-deb10-no_tntc-validate See #22343 - - - - - 9ca51f9e by Cheng Shao at 2023-02-15T00:17:53-05:00 rts: add the rts_clearMemory function This patch adds the rts_clearMemory function that does its best to zero out unused RTS memory for a wasm backend use case. See the comment above rts_clearMemory() prototype declaration for more detailed explanation. Closes #22920. - - - - - 26df73fb by Oleg Grenrus at 2023-02-15T22:20:57-05:00 Add -single-threaded flag to force single threaded rts This is the small part of implementing https://github.com/ghc-proposals/ghc-proposals/pull/240 - - - - - 631c6c72 by Cheng Shao at 2023-02-16T06:43:09-05:00 docs: add a section for the wasm backend Fixes #22658 - - - - - 1878e0bd by Bryan Richter at 2023-02-16T06:43:47-05:00 tests: Mark T12903 fragile everywhere See #21184 - - - - - b9420eac by Bryan Richter at 2023-02-16T06:43:47-05:00 Mark all T5435 variants as fragile See #22970. - - - - - df3d94bd by Sylvain Henry at 2023-02-16T06:44:33-05:00 Testsuite: mark T13167 as fragile for JS (#22921) - - - - - 324e925b by Sylvain Henry at 2023-02-16T06:45:15-05:00 JS: disable debugging info for heap objects - - - - - 518af814 by Josh Meredith at 2023-02-16T10:16:32-05:00 Factor JS Rts generation for h$c{_,0,1,2} into h$c{n} and improve name caching - - - - - 34cd308e by Ben Gamari at 2023-02-16T10:17:08-05:00 base: Note move of GHC.Stack.CCS.whereFrom to GHC.InfoProv in changelog Fixes #22883. - - - - - 12965aba by Simon Peyton Jones at 2023-02-16T10:17:46-05:00 Narrow the dont-decompose-newtype test Following #22924 this patch narrows the test that stops us decomposing newtypes. The key change is the use of noGivenNewtypeReprEqs in GHC.Tc.Solver.Canonical.canTyConApp. We went to and fro on the solution, as you can see in #22924. The result is carefully documented in Note [Decomoposing newtype equalities] On the way I had revert most of commit 3e827c3f74ef76d90d79ab6c4e71aa954a1a6b90 Author: Richard Eisenberg <rae at cs.brynmawr.edu> Date: Mon Dec 5 10:14:02 2022 -0500 Do newtype unwrapping in the canonicaliser and rewriter See Note [Unwrap newtypes first], which has the details. It turns out that (a) 3e827c3f makes GHC behave worse on some recursive newtypes (see one of the tests on this commit) (b) the finer-grained test (namely noGivenNewtypeReprEqs) renders 3e827c3f unnecessary - - - - - 5b038888 by Andrew Lelechenko at 2023-02-16T10:18:24-05:00 Documentation: add an example of SPEC usage - - - - - 681e0e8c by sheaf at 2023-02-16T14:09:56-05:00 No default finalizer exception handler Commit cfc8e2e2 introduced a mechanism for handling of exceptions that occur during Handle finalization, and 372cf730 set the default handler to print out the error to stderr. However, #21680 pointed out we might not want to set this by default, as it might pollute users' terminals with unwanted information. So, for the time being, the default handler discards the exception. Fixes #21680 - - - - - b3ac17ad by Matthew Pickering at 2023-02-16T14:10:31-05:00 unicode: Don't inline bitmap in generalCategory generalCategory contains a huge literal string but is marked INLINE, this will duplicate the string into any use site of generalCategory. In particular generalCategory is used in functions like isSpace and the literal gets inlined into this function which makes it massive. https://github.com/haskell/core-libraries-committee/issues/130 Fixes #22949 ------------------------- Metric Decrease: T4029 T18304 ------------------------- - - - - - 8988eeef by sheaf at 2023-02-16T20:32:27-05:00 Expand synonyms in RoughMap We were failing to expand type synonyms in the function GHC.Core.RoughMap.typeToRoughMatchLookupTc, even though the RoughMap infrastructure crucially relies on type synonym expansion to work. This patch adds the missing type-synonym expansion. Fixes #22985 - - - - - 3dd50e2f by Matthew Pickering at 2023-02-16T20:33:03-05:00 ghcup-metadata: Add test artifact Add the released testsuite tarball to the generated ghcup metadata. - - - - - c6a967d9 by Matthew Pickering at 2023-02-16T20:33:03-05:00 ghcup-metadata: Use Ubuntu and Rocky bindists Prefer to use the Ubuntu 20.04 and 18.04 binary distributions on Ubuntu and Linux Mint. Prefer to use the Rocky 8 binary distribution on unknown distributions. - - - - - be0b7209 by Matthew Pickering at 2023-02-17T09:37:16+00:00 Add INLINABLE pragmas to `generic*` functions in Data.OldList These functions are * recursive * overloaded So it's important to add an `INLINABLE` pragma to each so that they can be specialised at the use site when the specific numeric type is known. Adding these pragmas improves the LazyText replicate benchmark (see https://gitlab.haskell.org/ghc/ghc/-/issues/22886#note_481020) https://github.com/haskell/core-libraries-committee/issues/129 - - - - - a203ad85 by Sylvain Henry at 2023-02-17T15:59:16-05:00 Merge libiserv with ghci `libiserv` serves no purpose. As it depends on `ghci` and doesn't have more dependencies than the `ghci` package, its code could live in the `ghci` package too. This commit also moves most of the code from the `iserv` program into the `ghci` package as well so that it can be reused. This is especially useful for the implementation of TH for the JS backend (#22261, !9779). - - - - - 7080a93f by Simon Peyton Jones at 2023-02-20T12:06:32+01:00 Improve GHC.Tc.Gen.App.tcInstFun It wasn't behaving right when inst_final=False, and the function had no type variables f :: Foo => Int Rather a corner case, but we might as well do it right. Fixes #22908 Unexpectedly, three test cases (all using :type in GHCi) got slightly better output as a result: T17403, T14796, T12447 - - - - - 2592ab69 by Cheng Shao at 2023-02-20T10:35:30-05:00 compiler: fix cost centre profiling breakage in wasm NCG due to incorrect register mapping The wasm NCG used to map CCCS to a wasm global, based on the observation that CCCS is a transient register that's already handled by thread state load/store logic, so it doesn't need to be backed by the rCCCS field in the register table. Unfortunately, this is wrong, since even when Cmm execution hasn't yielded back to the scheduler, the Cmm code may call enterFunCCS, which does use rCCCS. This breaks cost centre profiling in a subtle way, resulting in inaccurate stack traces in some test cases. The fix is simple though: just remove the CCCS mapping. - - - - - 26243de1 by Alexis King at 2023-02-20T15:27:17-05:00 Handle top-level Addr# literals in the bytecode compiler Fixes #22376. - - - - - 0196cc2b by romes at 2023-02-20T15:27:52-05:00 fix: Explicitly flush stdout on plugin Because of #20791, the plugins tests often fail. This is a temporary fix to stop the tests from failing due to unflushed outputs on windows and the explicit flush should be removed when #20791 is fixed. - - - - - 4327d635 by Ryan Scott at 2023-02-20T20:44:34-05:00 Don't generate datacon wrappers for `type data` declarations Data constructor wrappers only make sense for _value_-level data constructors, but data constructors for `type data` declarations only exist at the _type_ level. This patch does the following: * The criteria in `GHC.Types.Id.Make.mkDataConRep` for whether a data constructor receives a wrapper now consider whether or not its parent data type was declared with `type data`, omitting a wrapper if this is the case. * Now that `type data` data constructors no longer receive wrappers, there is a spot of code in `refineDefaultAlt` that panics when it encounters a value headed by a `type data` type constructor. I've fixed this with a special case in `refineDefaultAlt` and expanded `Note [Refine DEFAULT case alternatives]` to explain why we do this. Fixes #22948. - - - - - 96dc58b9 by Ryan Scott at 2023-02-20T20:44:35-05:00 Treat type data declarations as empty when checking pattern-matching coverage The data constructors for a `type data` declaration don't exist at the value level, so we don't want GHC to warn users to match on them. Fixes #22964. - - - - - ff8e99f6 by Ryan Scott at 2023-02-20T20:44:35-05:00 Disallow `tagToEnum#` on `type data` types We don't want to allow users to conjure up values of a `type data` type using `tagToEnum#`, as these simply don't exist at the value level. - - - - - 8e765aff by Andrew Lelechenko at 2023-02-21T12:03:24-05:00 Bump submodule text to 2.0.2 - - - - - 172ff88f by Georgi Lyubenov at 2023-02-21T18:35:56-05:00 GHC proposal 496 - Nullary record wildcards This patch implements GHC proposal 496, which allows record wildcards to be used for nullary constructors, e.g. data A = MkA1 | MkA2 { fld1 :: Int } f :: A -> Int f (MkA1 {..}) = 0 f (MkA2 {..}) = fld1 To achieve this, we add arity information to the record field environment, so that we can accept a constructor which has no fields while continuing to reject non-record constructors with more than 1 field. See Note [Nullary constructors and empty record wildcards], as well as the more general overview in Note [Local constructor info in the renamer], both in the newly introduced GHC.Types.ConInfo module. Fixes #22161 - - - - - f70a0239 by sheaf at 2023-02-21T18:36:35-05:00 ghc-prim: levity-polymorphic array equality ops This patch changes the pointer-equality comparison operations in GHC.Prim.PtrEq to work with arrays of unlifted values, e.g. sameArray# :: forall {l} (a :: TYPE (BoxedRep l)). Array# a -> Array# a -> Int# Fixes #22976 - - - - - 9296660b by Andreas Klebinger at 2023-02-21T23:58:05-05:00 base: Correct @since annotation for FP<->Integral bit cast operations. Fixes #22708 - - - - - f11d9c27 by romes at 2023-02-21T23:58:42-05:00 fix: Update documentation links Closes #23008 Additionally batches some fixes to pointers to the Note [Wired-in units], and a typo in said note. - - - - - fb60339f by Bryan Richter at 2023-02-23T14:45:17+02:00 Propagate failure if unable to push notes - - - - - 8e170f86 by Alexis King at 2023-02-23T16:59:22-05:00 rts: Fix `prompt#` when profiling is enabled This commit also adds a new -Dk RTS option to the debug RTS to assist debugging continuation captures. Currently, the printed information is quite minimal, but more can be added in the future if it proves to be useful when debugging future issues. fixes #23001 - - - - - e9e7a00d by sheaf at 2023-02-23T17:00:01-05:00 Explicit migration timeline for loopy SC solving This patch updates the warning message introduced in commit 9fb4ca89bff9873e5f6a6849fa22a349c94deaae to specify an explicit migration timeline: GHC will no longer support this constraint solving mechanism starting from GHC 9.10. Fixes #22912 - - - - - 4eb9c234 by Sylvain Henry at 2023-02-24T17:27:45-05:00 JS: make some arithmetic primops faster (#22835) Don't use BigInt for wordAdd2, mulWord32, and timesInt32. Co-authored-by: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org> - - - - - 92e76483 by Ben Gamari at 2023-02-24T17:28:20-05:00 Bump terminfo submodule to 0.4.1.6 - - - - - f229db14 by Ben Gamari at 2023-02-24T17:28:20-05:00 Bump unix submodule to 2.8.1.0 - - - - - 47bd48c1 by Ben Gamari at 2023-02-24T17:28:20-05:00 Bump deepseq submodule to 1.4.8.1 - - - - - d2012594 by Ben Gamari at 2023-02-24T17:28:20-05:00 Bump directory submodule to 1.3.8.1 - - - - - df6f70d1 by Ben Gamari at 2023-02-24T17:28:20-05:00 Bump process submodule to v1.6.17.0 - - - - - 4c869e48 by Ben Gamari at 2023-02-24T17:28:20-05:00 Bump hsc2hs submodule to 0.68.8 - - - - - 81d96642 by Ben Gamari at 2023-02-24T17:28:20-05:00 Bump array submodule to 0.5.4.0 - - - - - 6361f771 by Ben Gamari at 2023-02-24T17:28:20-05:00 Bump Cabal submodule to 3.9 pre-release - - - - - 4085fb6c by Ben Gamari at 2023-02-24T17:28:20-05:00 Bump filepath submodule to 1.4.100.1 - - - - - 2bfad50f by Ben Gamari at 2023-02-24T17:28:20-05:00 Bump haskeline submodule to 0.8.2.1 - - - - - fdc89a8d by Ben Gamari at 2023-02-24T21:29:32-05:00 gitlab-ci: Run nix-build with -v0 This significantly cuts down on the amount of noise in the job log. Addresses #22861. - - - - - 69fb0b13 by Aaron Allen at 2023-02-24T21:30:10-05:00 Fix ParallelListComp out of scope suggestion This patch makes it so vars from one block of a parallel list comprehension are not in scope in a subsequent block during type checking. This was causing GHC to emit a faulty suggestion when an out of scope variable shared the occ name of a var from a different block. Fixes #22940 - - - - - ece092d0 by Simon Peyton Jones at 2023-02-24T21:30:45-05:00 Fix shadowing bug in prepareAlts As #23012 showed, GHC.Core.Opt.Simplify.Utils.prepareAlts was using an OutType to construct an InAlt. When shadowing is in play, this is outright wrong. See Note [Shadowing in prepareAlts]. - - - - - 7825fef9 by Sylvain Henry at 2023-02-24T21:31:25-05:00 JS: Store CI perf results (fix #22923) - - - - - b56025f4 by Gergő Érdi at 2023-02-27T13:34:22+00:00 Don't specialise incoherent instance applications Using incoherent instances, there can be situations where two occurrences of the same overloaded function at the same type use two different instances (see #22448). For incoherently resolved instances, we must mark them with `nospec` to avoid the specialiser rewriting one to the other. This marking is done during the desugaring of the `WpEvApp` wrapper. Fixes #22448 Metric Increase: T15304 - - - - - d0c7bbed by Tom Ellis at 2023-02-27T20:04:07-05:00 Fix SCC grouping example - - - - - f84a8cd4 by Bryan Richter at 2023-02-28T05:58:37-05:00 Mark setnumcapabilities001 fragile - - - - - 29a04d6e by Bryan Richter at 2023-02-28T05:58:37-05:00 Allow nightly-x86_64-linux-deb10-validate+thread_sanitizer to fail See #22520 - - - - - 9fa54572 by Cheng Shao at 2023-02-28T05:59:15-05:00 ghc-prim: fix hs_cmpxchg64 function prototype hs_cmpxchg64 must return a StgWord64, otherwise incorrect runtime results of 64-bit MO_Cmpxchg will appear in 32-bit unregisterised builds, which go unnoticed at compile-time due to C implicit casting in .hc files. - - - - - 0c200ab7 by Simon Peyton Jones at 2023-02-28T11:10:31-05:00 Account for local rules in specImports As #23024 showed, in GHC.Core.Opt.Specialise.specImports, we were generating specialisations (a locally-define function) for imported functions; and then generating specialisations for those locally-defined functions. The RULE for the latter should be attached to the local Id, not put in the rules-for-imported-ids set. Fix is easy; similar to what happens in GHC.HsToCore.addExportFlagsAndRules - - - - - 8b77f9bf by Sylvain Henry at 2023-02-28T11:11:21-05:00 JS: fix for overlap with copyMutableByteArray# (#23033) The code wasn't taking into account some kind of overlap. cgrun070 has been extended to test the missing case. - - - - - 239202a2 by Sylvain Henry at 2023-02-28T11:12:03-05:00 Testsuite: replace some js_skip with req_cmm req_cmm is more informative than js_skip - - - - - 7192ef91 by Simon Peyton Jones at 2023-02-28T18:54:59-05:00 Take more care with unlifted bindings in the specialiser As #22998 showed, we were floating an unlifted binding to top level, which breaks a Core invariant. The fix is easy, albeit a little bit conservative. See Note [Care with unlifted bindings] in GHC.Core.Opt.Specialise - - - - - bb500e2a by Simon Peyton Jones at 2023-02-28T18:55:35-05:00 Account for TYPE vs CONSTRAINT in mkSelCo As #23018 showed, in mkRuntimeRepCo we need to account for coercions between TYPE and COERCION. See Note [mkRuntimeRepCo] in GHC.Core.Coercion. - - - - - 79ffa170 by Ben Gamari at 2023-03-01T04:17:20-05:00 hadrian: Add dependency from lib/settings to mk/config.mk In 81975ef375de07a0ea5a69596b2077d7f5959182 we attempted to fix #20253 by adding logic to the bindist Makefile to regenerate the `settings` file from information gleaned by the bindist `configure` script. However, this fix had no effect as `lib/settings` is shipped in the binary distribution (to allow in-place use of the binary distribution). As `lib/settings` already existed and its rule declared no dependencies, `make` would fail to use the added rule to regenerate it. Fix this by explicitly declaring a dependency from `lib/settings` on `mk/config.mk`. Fixes #22982. - - - - - a2a1a1c0 by Sebastian Graf at 2023-03-01T04:17:56-05:00 Revert the main payload of "Make `drop` and `dropWhile` fuse (#18964)" This reverts the bits affecting fusion of `drop` and `dropWhile` of commit 0f7588b5df1fc7a58d8202761bf1501447e48914 and keeps just the small refactoring unifying `flipSeqTake` and `flipSeqScanl'` into `flipSeq`. It also adds a new test for #23021 (which was the reason for reverting) as well as adds a clarifying comment to T18964. Fixes #23021, unfixes #18964. Metric Increase: T18964 Metric Decrease: T18964 - - - - - cf118e2f by Simon Peyton Jones at 2023-03-01T04:18:33-05:00 Refine the test for naughty record selectors The test for naughtiness in record selectors is surprisingly subtle. See the revised Note [Naughty record selectors] in GHC.Tc.TyCl.Utils. Fixes #23038. - - - - - 86f240ca by romes at 2023-03-01T04:19:10-05:00 fix: Consider strictness annotation in rep_bind Fixes #23036 - - - - - 1ed573a5 by Richard Eisenberg at 2023-03-02T22:42:06-05:00 Don't suppress *all* Wanteds Code in GHC.Tc.Errors.reportWanteds suppresses a Wanted if its rewriters have unfilled coercion holes; see Note [Wanteds rewrite Wanteds] in GHC.Tc.Types.Constraint. But if we thereby suppress *all* errors that's really confusing, and as #22707 shows, GHC goes on without even realising that the program is broken. Disaster. This MR arranges to un-suppress them all if they all get suppressed. Close #22707 - - - - - 8919f341 by Luite Stegeman at 2023-03-02T22:42:45-05:00 Check for platform support for JavaScript foreign imports GHC was accepting `foreign import javascript` declarations on non-JavaScript platforms. This adds a check so that these are only supported on an platform that supports the JavaScript calling convention. Fixes #22774 - - - - - db83f8bb by Ben Gamari at 2023-03-02T22:43:22-05:00 rts: Statically assert alignment of Capability In #22965 we noticed that changes in the size of `Capability` can result in unsound behavior due to the `align` pragma claiming an alignment which we don't in practice observe. Avoid this by statically asserting that the size is a multiple of the alignment. - - - - - 5f7a4a6d by Ben Gamari at 2023-03-02T22:43:22-05:00 rts: Introduce stgMallocAlignedBytes - - - - - 8a6f745d by Ben Gamari at 2023-03-02T22:43:22-05:00 rts: Correctly align Capability allocations Previously we failed to tell the C allocator that `Capability`s needed to be aligned, resulting in #22965. Fixes #22965. Fixes #22975. - - - - - 5464c73f by Ben Gamari at 2023-03-02T22:43:22-05:00 rts: Drop no-alignment special case for Windows For reasons that aren't clear, we were previously not giving Capability the same favorable alignment on Windows that we provided on other platforms. Fix this. - - - - - a86aae8b by Matthew Pickering at 2023-03-02T22:43:59-05:00 constant folding: Correct type of decodeDouble_Int64 rule The first argument is Int64# unconditionally, so we better produce something of that type. This fixes a core lint error found in the ad package. Fixes #23019 - - - - - 68dd64ff by Zubin Duggal at 2023-03-02T22:44:35-05:00 ncg/aarch64: Handle MULTILINE_COMMENT identically as COMMENTs Commit 7566fd9de38c67360c090f828923d41587af519c with the fix for #22798 was incomplete as it failed to handle MULTILINE_COMMENT pseudo-instructions, and didn't completly fix the compiler panics when compiling with `-fregs-graph`. Fixes #23002 - - - - - 2f97c861 by Simon Peyton Jones at 2023-03-02T22:45:11-05:00 Get the right in-scope set in etaBodyForJoinPoint Fixes #23026 - - - - - 45af8482 by David Feuer at 2023-03-03T11:40:47-05:00 Export getSolo from Data.Tuple Proposed in [CLC proposal #113](https://github.com/haskell/core-libraries-committee/issues/113) and [approved by the CLC](https://github.com/haskell/core-libraries-committee/issues/113#issuecomment-1452452191) - - - - - 0c694895 by David Feuer at 2023-03-03T11:40:47-05:00 Document getSolo - - - - - bd0536af by Simon Peyton Jones at 2023-03-03T11:41:23-05:00 More fixes for `type data` declarations This MR fixes #23022 and #23023. Specifically * Beef up Note [Type data declarations] in GHC.Rename.Module, to make invariant (I1) explicit, and to name the several wrinkles. And add references to these specific wrinkles. * Add a Lint check for invariant (I1) above. See GHC.Core.Lint.checkTypeDataConOcc * Disable the `caseRules` for dataToTag# for `type data` values. See Wrinkle (W2c) in the Note above. Fixes #23023. * Refine the assertion in dataConRepArgTys, so that it does not complain about the absence of a wrapper for a `type data` constructor Fixes #23022. Acked-by: Simon Peyton Jones <simon.peytonjones at gmail.com> - - - - - 858f34d5 by Oleg Grenrus at 2023-03-04T01:13:55+02:00 Add decideSymbol, decideChar, decideNat, decTypeRep, decT and hdecT These all type-level equality decision procedures. Implementes a CLC proposal https://github.com/haskell/core-libraries-committee/issues/98 - - - - - bf43ba92 by Simon Peyton Jones at 2023-03-04T01:18:23-05:00 Add test for T22793 - - - - - c6e1f3cd by Chris Wendt at 2023-03-04T03:35:18-07:00 Fix typo in docs referring to threadLabel - - - - - 232cfc24 by Simon Peyton Jones at 2023-03-05T19:57:30-05:00 Add regression test for #22328 - - - - - 5ed77deb by Gabriella Gonzalez at 2023-03-06T17:06:50-05:00 Enable response files for linker if supported - - - - - 1e0f6c89 by Gabriella Gonzalez at 2023-03-06T17:06:50-05:00 Synchronize `configure.ac` and `distrib/configure.ac.in` - - - - - 70560952 by Gabriella Gonzalez at 2023-03-06T17:06:50-05:00 Fix `hadrian/bindist/config.mk.in` … as suggested by @bgamari - - - - - b042b125 by sheaf at 2023-03-06T17:06:50-05:00 Apply 1 suggestion(s) to 1 file(s) - - - - - 674b6b81 by Gabriella Gonzalez at 2023-03-06T17:06:50-05:00 Try to create somewhat portable `ld` command I cannot figure out a good way to generate an `ld` command that works on both Linux and macOS. Normally you'd use something like `AC_LINK_IFELSE` for this purpose (I think), but that won't let us test response file support. - - - - - 83b0177e by Gabriella Gonzalez at 2023-03-06T17:06:50-05:00 Quote variables … as suggested by @bgamari - - - - - 845f404d by Gabriella Gonzalez at 2023-03-06T17:06:50-05:00 Fix configure failure on alpine linux - - - - - c56a3ae6 by Gabriella Gonzalez at 2023-03-06T17:06:50-05:00 Small fixes to configure script - - - - - cad5c576 by Andrei Borzenkov at 2023-03-06T17:07:33-05:00 Convert diagnostics in GHC.Rename.Module to proper TcRnMessage (#20115) I've turned almost all occurrences of TcRnUnknownMessage in GHC.Rename.Module module into a proper TcRnMessage. Instead, these TcRnMessage messages were introduced: TcRnIllegalInstanceHeadDecl TcRnUnexpectedStandaloneDerivingDecl TcRnUnusedVariableInRuleDecl TcRnUnexpectedStandaloneKindSig TcRnIllegalRuleLhs TcRnBadAssocRhs TcRnDuplicateRoleAnnot TcRnDuplicateKindSig TcRnIllegalDerivStrategy TcRnIllegalMultipleDerivClauses TcRnNoDerivStratSpecified TcRnStupidThetaInGadt TcRnBadImplicitSplice TcRnShadowedTyVarNameInFamResult TcRnIncorrectTyVarOnLhsOfInjCond TcRnUnknownTyVarsOnRhsOfInjCond Was introduced one helper type: RuleLhsErrReason - - - - - c6432eac by Apoorv Ingle at 2023-03-06T23:26:12+00:00 Constraint simplification loop now depends on `ExpansionFuel` instead of a boolean flag for `CDictCan.cc_pend_sc`. Pending givens get a fuel of 3 while Wanted and quantified constraints get a fuel of 1. This helps pending given constraints to keep up with pending wanted constraints in case of `UndecidableSuperClasses` and superclass expansions while simplifying the infered type. Adds 3 dynamic flags for controlling the fuels for each type of constraints `-fgivens-expansion-fuel` for givens `-fwanteds-expansion-fuel` for wanteds and `-fqcs-expansion-fuel` for quantified constraints Fixes #21909 Added Tests T21909, T21909b Added Note [Expanding Recursive Superclasses and ExpansionFuel] - - - - - a5afc8ab by Andrew Lelechenko at 2023-03-06T22:51:01-05:00 Documentation: describe laziness of several function from Data.List - - - - - fa559c28 by Ollie Charles at 2023-03-07T20:56:21+00:00 Add `Data.Functor.unzip` This function is currently present in `Data.List.NonEmpty`, but `Data.Functor` is a better home for it. This change was discussed and approved by the CLC at https://github.com/haskell/core-libraries-committee/issues/88. - - - - - 2aa07708 by MorrowM at 2023-03-07T21:22:22-05:00 Fix documentation for traceWith and friends - - - - - f3ff7cb1 by David Binder at 2023-03-08T01:24:17-05:00 Remove utils/hpc subdirectory and its contents - - - - - cf98e286 by David Binder at 2023-03-08T01:24:17-05:00 Add git submodule for utils/hpc - - - - - 605fbbb2 by David Binder at 2023-03-08T01:24:18-05:00 Update commit for utils/hpc git submodule - - - - - 606793d4 by David Binder at 2023-03-08T01:24:18-05:00 Update commit for utils/hpc git submodule - - - - - 4158722a by Sylvain Henry at 2023-03-08T01:24:58-05:00 linker: fix linking with aligned sections (#23066) Take section alignment into account instead of assuming 16 bytes (which is wrong when the section requires 32 bytes, cf #23066). - - - - - 1e0d8fdb by Greg Steuck at 2023-03-08T08:59:05-05:00 Change hostSupportsRPaths to report False on OpenBSD OpenBSD does support -rpath but ghc build process relies on some related features that don't work there. See ghc/ghc#23011 - - - - - bed3a292 by Alexis King at 2023-03-08T08:59:53-05:00 bytecode: Fix bitmaps for BCOs used to tag tuples and prim call args fixes #23068 - - - - - 321d46d9 by Ben Gamari at 2023-03-08T15:02:30-05:00 rts: Drop redundant prototype - - - - - abb6070f by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Fix style - - - - - be278901 by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Deduplicate assertion - - - - - b9034639 by Ben Gamari at 2023-03-08T15:02:30-05:00 rts: Fix type issues in Sparks.h Adds explicit casts to satisfy a C++ compiler. - - - - - da7b2b94 by Ben Gamari at 2023-03-08T15:02:30-05:00 rts: Use release ordering when storing thread labels Since this makes the ByteArray# visible from other cores. - - - - - 5b7f6576 by Ben Gamari at 2023-03-08T15:02:30-05:00 rts/BlockAlloc: Allow disabling of internal assertions These can be quite expensive and it is sometimes useful to compile a DEBUG RTS without them. - - - - - 6283144f by Ben Gamari at 2023-03-08T15:02:30-05:00 rts/Sanity: Mark pinned_object_blocks - - - - - 9b528404 by Ben Gamari at 2023-03-08T15:02:30-05:00 rts/Sanity: Look at nonmoving saved_filled lists - - - - - 0edc5438 by Ben Gamari at 2023-03-08T15:02:30-05:00 Evac: Squash data race in eval_selector_chain - - - - - 7eab831a by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Clarify implementation This makes the intent of this implementation a bit clearer. - - - - - 532262b9 by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Clarify comment - - - - - bd9cd84b by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Add missing no-op in busy-wait loop - - - - - c4e6bfc8 by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Don't push empty arrays to update remembered set Previously the write barrier of resizeSmallArray# incorrectly handled resizing of zero-sized arrays, pushing an invalid pointer to the update remembered set. Fixes #22931. - - - - - 92227b60 by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Fix handling of weak pointers This fixes an interaction between aging and weak pointer handling which prevented the finalization of some weak pointers. In particular, weak pointers could have their keys incorrectly marked by the preparatory collector, preventing their finalization by the subsequent concurrent collection. While in the area, we also significantly improve the assertions regarding weak pointers. Fixes #22327. - - - - - ba7e7972 by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Sanity check nonmoving large objects and compacts - - - - - 71b038a1 by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Sanity check mutable list Assert that entries in the nonmoving generation's generational remembered set (a.k.a. mutable list) live in nonmoving generation. - - - - - 99d144d5 by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Don't show occupancy if we didn't collect live words - - - - - 81d6cc55 by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Fix tracking of FILLED_SWEEPING segments Previously we only updated the state of the segment at the head of each allocator's filled list. - - - - - 58e53bc4 by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Assert state of swept segments - - - - - 2db92e01 by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Handle new closures in nonmovingIsNowAlive We must conservatively assume that new closures are reachable since we are not guaranteed to mark such blocks. - - - - - e4c3249f by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Don't clobber update rem sets of old capabilities Previously `storageAddCapabilities` (called by `setNumCapabilities`) would clobber the update remembered sets of existing capabilities when increasing the capability count. Fix this by only initializing the update remembered sets of the newly-created capabilities. Fixes #22927. - - - - - 1b069671 by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Add missing write barriers in selector optimisation This fixes the selector optimisation, adding a few write barriers which are necessary for soundness. See the inline comments for details. Fixes #22930. - - - - - d4032690 by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Post-sweep sanity checking - - - - - 0baa8752 by Ben Gamari at 2023-03-08T15:02:30-05:00 nonmoving: Avoid n_caps race - - - - - 5d3232ba by Ben Gamari at 2023-03-08T15:02:31-05:00 nonmoving: Don't push if nonmoving collector isn't enabled - - - - - 0a7eb0aa by Ben Gamari at 2023-03-08T15:02:31-05:00 nonmoving: Be more paranoid in segment tracking Previously we left various segment link pointers dangling. None of this wrong per se, but it did make it harder than necessary to debug. - - - - - 7c817c0a by Ben Gamari at 2023-03-08T15:02:31-05:00 nonmoving: Sync-phase mark budgeting Here we significantly improve the bound on sync phase pause times by imposing a limit on the amount of work that we can perform during the sync. If we find that we have exceeded our marking budget then we allow the mutators to resume, return to concurrent marking, and try synchronizing again later. Fixes #22929. - - - - - ce22a3e2 by Ben Gamari at 2023-03-08T15:02:31-05:00 nonmoving: Allow pinned gen0 objects to be WEAK keys - - - - - 78746906 by Ben Gamari at 2023-03-08T15:02:31-05:00 rts: Reenable assertion - - - - - b500867a by Ben Gamari at 2023-03-08T15:02:31-05:00 nonmoving: Move current segment array into Capability The current segments are conceptually owned by the mutator, not the collector. Consequently, it was quite tricky to prove that the mutator would not race with the collect due to this shared state. It turns out that such races are possible: when resizing the current segment array we may concurrently try to take a heap census. This will attempt to walk the current segment array, causing a data race. Fix this by moving the current segment array into `Capability`, where it belongs. Fixes #22926. - - - - - 56e669c1 by Ben Gamari at 2023-03-08T15:02:31-05:00 nonmoving: Fix Note references Some references to Note [Deadlock detection under the non-moving collector] were missing an article. - - - - - 4a7650d7 by Ben Gamari at 2023-03-08T15:02:31-05:00 rts/Sanity: Fix block count assertion with non-moving collector The nonmoving collector does not use `oldest_gen->blocks` to track its block list. However, it nevertheless updates `oldest_gen->n_blocks` to ensure that its size is accounted for by the storage manager. Consequently, we must not attempt to assert consistency between the two. - - - - - 96a5aaed by Ben Gamari at 2023-03-08T15:02:31-05:00 nonmoving: Don't call prepareUnloadCheck When the nonmoving GC is in use we do not call `checkUnload` (since we don't unload code) and therefore should not call `prepareUnloadCheck`, lest we run into assertions. - - - - - 6c6674ca by Ben Gamari at 2023-03-08T15:02:31-05:00 rts: Encapsulate block allocator spinlock This makes it a bit easier to add instrumentation on this spinlock while debugging. - - - - - e84f7167 by Ben Gamari at 2023-03-08T15:02:31-05:00 testsuite: Skip some tests when sanity checking is enabled - - - - - 3ae0f368 by Ben Gamari at 2023-03-08T15:02:31-05:00 nonmoving: Fix unregisterised build - - - - - 4eb9d06b by Ben Gamari at 2023-03-08T15:02:31-05:00 nonmoving: Ensure that sanity checker accounts for saved_filled segments - - - - - f0cf384d by Ben Gamari at 2023-03-08T15:02:31-05:00 hadrian: Add +boot_nonmoving_gc flavour transformer For using GHC bootstrapping to validate the non-moving GC. - - - - - 581e58ac by Ben Gamari at 2023-03-08T15:02:31-05:00 gitlab-ci: Add job bootstrapping with nonmoving GC - - - - - 487a8b58 by Ben Gamari at 2023-03-08T15:02:31-05:00 nonmoving: Move allocator into new source file - - - - - 8f374139 by Ben Gamari at 2023-03-08T15:02:31-05:00 nonmoving: Split out nonmovingAllocateGC - - - - - 662b6166 by Ben Gamari at 2023-03-08T15:02:31-05:00 testsuite: Only run T22795* in the normal way It doesn't make sense to run these in multiple ways as they merely test whether `-threaded`/`-single-threaded` flags. - - - - - 0af21dfa by Ben Gamari at 2023-03-08T15:02:31-05:00 rts: Rename clear_segment(_free_blocks)? To reflect the fact that these are to do with the nonmoving collector, now since they are exposed no longer static. - - - - - 7bcb192b by Ben Gamari at 2023-03-08T15:02:31-05:00 rts: Fix incorrect STATIC_INLINE This should be INLINE_HEADER lest we get unused declaration warnings. - - - - - f1fd3ffb by Ben Gamari at 2023-03-08T15:02:31-05:00 testsuite: Mark ffi023 as broken due to #23089 - - - - - a57f12b3 by Ben Gamari at 2023-03-08T15:02:31-05:00 testsuite: Skip T7160 in the nonmoving way Finalization order is different under the nonmoving collector. - - - - - f6f12a36 by Ben Gamari at 2023-03-08T15:02:31-05:00 rts: Capture GC configuration in a struct The number of distinct arguments passed to GarbageCollect was getting a bit out of hand. - - - - - ba73a807 by Ben Gamari at 2023-03-08T15:02:31-05:00 nonmoving: Non-concurrent collection - - - - - 7c813d06 by Alexis King at 2023-03-08T15:03:10-05:00 hadrian: Fix flavour compiler stage options off-by-one error !9193 pointed out that ghcDebugAssertions was supposed to be a predicate on the stage of the built compiler, but in practice it was a predicate on the stage of the compiler used to build. Unfortunately, while it fixed that issue for ghcDebugAssertions, it documented every other similar option as behaving the same way when in fact they all used the old behavior. The new behavior of ghcDebugAssertions seems more intuitive, so this commit changes the interpretation of every other option to match. It also improves the enableProfiledGhc and debugGhc flavour transformers by making them more selective about which stages in which they build additional library/RTS ways. - - - - - f97c7f6d by Luite Stegeman at 2023-03-09T09:52:09-05:00 Delete created temporary subdirectories at end of session. This patch adds temporary subdirectories to the list of paths do clean up at the end of the GHC session. This fixes warnings about non-empty temporary directories. Fixes #22952 - - - - - 9ea719f2 by Apoorv Ingle at 2023-03-09T09:52:45-05:00 Fixes #19627. Previously the solver failed with an unhelpful "solver reached too may iterations" error. With the fix for #21909 in place we no longer have the possibility of generating such an error if we have `-fconstraint-solver-iteration` > `-fgivens-fuel > `-fwanteds-fuel`. This is true by default, and the said fix also gives programmers a knob to control how hard the solver should try before giving up. This commit adds: * Reference to ticket #19627 in the Note [Expanding Recursive Superclasses and ExpansionFuel] * Test `typecheck/should_fail/T19627.hs` for regression purposes - - - - - eb3968b5 by Ben Gamari at 2023-03-10T02:32:43-05:00 Bump versions for ghc-9.6 release - - - - - ec2d93eb by Sebastian Graf at 2023-03-10T10:18:54-05:00 DmdAnal: Fix a panic on OPAQUE and trivial/PAP RHS (#22997) We should not panic in `add_demands` (now `set_lam_dmds`), because that code path is legimitely taken for OPAQUE PAP bindings, as in T22997. Fixes #22997. - - - - - 5b4628ae by Sylvain Henry at 2023-03-10T10:19:34-05:00 JS: remove dead code for old integer-gmp - - - - - bab23279 by Josh Meredith at 2023-03-10T23:24:49-05:00 JS: Fix implementation of MK_JSVAL - - - - - ec263a59 by Sebastian Graf at 2023-03-10T23:25:25-05:00 Simplify: Move `wantEtaExpansion` before expensive `do_eta_expand` check There is no need to run arity analysis and what not if we are not in a Simplifier phase that eta-expands or if we don't want to eta-expand the expression in the first place. Purely a refactoring with the goal of improving compiler perf. - - - - - 047e9d4f by Josh Meredith at 2023-03-13T03:56:03+00:00 JS: fix implementation of forceBool to use JS backend syntax - - - - - 559a4804 by Sebastian Graf at 2023-03-13T07:31:23-04:00 Simplifier: `countValArgs` should not count Type args (#23102) I observed miscompilations while working on !10088 caused by this. Fixes #23102. Metric Decrease: T10421 - - - - - 536d1f90 by Matthew Pickering at 2023-03-13T14:04:49+00:00 Bump Win32 to 2.13.4.0 Updates Win32 submodule - - - - - ee17001e by Ben Gamari at 2023-03-13T21:18:24-04:00 ghc-bignum: Drop redundant include-dirs field - - - - - c9c26cd6 by Teo Camarasu at 2023-03-16T12:17:50-04:00 Fix BCO creation setting caps when -j > -N * Remove calls to 'setNumCapabilities' in 'createBCOs' These calls exist to ensure that 'createBCOs' can benefit from parallelism. But this is not the right place to call `setNumCapabilities`. Furthermore the logic differs from that in the driver causing the capability count to be raised and lowered at each TH call if -j > -N. * Remove 'BCOOpts' No longer needed as it was only used to thread the job count down to `createBCOs` Resolves #23049 - - - - - 5ddbf5ed by Teo Camarasu at 2023-03-16T12:17:50-04:00 Add changelog entry for #23049 - - - - - 6e3ce9a4 by Ben Gamari at 2023-03-16T12:18:26-04:00 configure: Fix FIND_CXX_STD_LIB test on Darwin Annoyingly, Darwin's <cstddef> includes <version> and APFS is case-insensitive. Consequently, it will end up #including the `VERSION` file generated by the `configure` script on the second and subsequent runs of the `configure` script. See #23116. - - - - - 19d6d039 by sheaf at 2023-03-16T21:31:22+01:00 ghci: only keep the GlobalRdrEnv in ModInfo The datatype GHC.UI.Info.ModInfo used to store a ModuleInfo, which includes a TypeEnv. This can easily cause space leaks as we have no way of forcing everything in a type environment. In GHC, we only use the GlobalRdrEnv, which we can force completely. So we only store that instead of a fully-fledged ModuleInfo. - - - - - 73d07c6e by Torsten Schmits at 2023-03-17T14:36:49-04:00 Add structured error messages for GHC.Tc.Utils.Backpack Tracking ticket: #20119 MR: !10127 This converts uses of `mkTcRnUnknownMessage` to newly added constructors of `TcRnMessage`. One occurrence, when handing a nested error from the interface loading machinery, was omitted. It will be handled by a subsequent changeset that addresses interface errors. - - - - - a13affce by Andrei Borzenkov at 2023-03-21T11:17:17-04:00 Rename () into Unit, (,,...,,) into Tuple<n> (#21294) This patch implements a part of GHC Proposal #475. The key change is in GHC.Tuple.Prim: - data () = () - data (a,b) = (a,b) - data (a,b,c) = (a,b,c) ... + data Unit = () + data Tuple2 a b = (a,b) + data Tuple3 a b c = (a,b,c) ... And the rest of the patch makes sure that Unit and Tuple<n> are pretty-printed as () and (,,...,,) in various contexts. Updates the haddock submodule. Co-authored-by: Vladislav Zavialov <vlad.z.4096 at gmail.com> - - - - - 23642bf6 by Adam Sandberg Ericsson at 2023-03-21T11:17:53-04:00 docs: fix some wrongs in the eventlog format documentation - - - - - 90159773 by Adam Sandberg Ericsson at 2023-03-21T11:17:53-04:00 docs: explain the BLOCK_MARKER event - - - - - ab1c25e8 by Adam Sandberg Ericsson at 2023-03-21T11:17:53-04:00 docs: add BlockedOnMVarRead thread status in eventlog encodings - - - - - 898afaef by Adam Sandberg Ericsson at 2023-03-21T11:17:53-04:00 docs: add TASK_DELETE event in eventlog encodings - - - - - bb05b4cc by Adam Sandberg Ericsson at 2023-03-21T11:17:53-04:00 docs: add WALL_CLOCK_TIME event in eventlog encodings - - - - - eeea0343 by Torsten Schmits at 2023-03-21T11:18:34-04:00 Add structured error messages for GHC.Tc.Utils.Env Tracking ticket: #20119 MR: !10129 This converts uses of `mkTcRnUnknownMessage` to newly added constructors of `TcRnMessage`. - - - - - be1d4be8 by Andrew Lelechenko at 2023-03-21T11:19:13-04:00 Document pdep / pext primops - - - - - e8b4aac4 by Alex Mason at 2023-03-21T18:11:04-04:00 Allow LLVM backend to use HDoc for faster file generation. Also remove the MetaStmt constructor from LlvmStatement and places the annotations into the Store statement. Includes “Implement a workaround for -no-asm-shortcutting bug“ (https://gitlab.haskell.org/ghc/ghc/-/commit/2fda9e0df886cc551e2cd6b9c2a384192bdc3045) - - - - - ea24360d by Luite Stegeman at 2023-03-21T18:11:44-04:00 Compute LambdaFormInfo when using JavaScript backend. CmmCgInfos is needed to write interface files, but the JavaScript backend does not generate it, causing "Name without LFInfo" warnings. This patch adds a conservative but always correct CmmCgInfos when the JavaScript backend is used. Fixes #23053 - - - - - 926ad6de by Simon Peyton Jones at 2023-03-22T01:03:08-04:00 Be more careful about quantification This MR is driven by #23051. It does several things: * It is guided by the generalisation plan described in #20686. But it is still far from a complete implementation of that plan. * Add Note [Inferred type with escaping kind] to GHC.Tc.Gen.Bind. This explains that we don't (yet, pending #20686) directly prevent generalising over escaping kinds. * In `GHC.Tc.Utils.TcMType.defaultTyVar` we default RuntimeRep and Multiplicity variables, beause we don't want to quantify over them. We want to do the same for a Concrete tyvar, but there is nothing sensible to default it to (unless it has kind RuntimeRep, in which case it'll be caught by an earlier case). So we promote instead. * Pure refactoring in GHC.Tc.Solver: * Rename decideMonoTyVars to decidePromotedTyVars, since that's what it does. * Move the actual promotion of the tyvars-to-promote from `defaultTyVarsAndSimplify` to `decidePromotedTyVars`. This is a no-op; just tidies up the code. E.g then we don't need to return the promoted tyvars from `decidePromotedTyVars`. * A little refactoring in `defaultTyVarsAndSimplify`, but no change in behaviour. * When making a TauTv unification variable into a ConcreteTv (in GHC.Tc.Utils.Concrete.makeTypeConcrete), preserve the occ-name of the type variable. This just improves error messages. * Kill off dead code: GHC.Tc.Utils.TcMType.newConcreteHole - - - - - 0ab0cc11 by Sylvain Henry at 2023-03-22T01:03:48-04:00 Testsuite: use appropriate predicate for ManyUbxSums test (#22576) - - - - - 048c881e by romes at 2023-03-22T01:04:24-04:00 fix: Incorrect @since annotations in GHC.TypeError Fixes #23128 - - - - - a1528b68 by Sylvain Henry at 2023-03-22T01:05:04-04:00 Testsuite: use req_interp predicate for T16318 (#22370) - - - - - ad765b6f by Sylvain Henry at 2023-03-22T01:05:04-04:00 Testsuite: use req_interp predicate for T20214 - - - - - e0b8eaf3 by Simon Peyton Jones at 2023-03-22T09:50:13+00:00 Refactor the constraint solver pipeline The big change is to put the entire type-equality solver into GHC.Tc.Solver.Equality, rather than scattering it over Canonical and Interact. Other changes * EqCt becomes its own data type, a bit like QCInst. This is great because EqualCtList is then just [EqCt] * New module GHC.Tc.Solver.Dict has come of the class-contraint solver. In due course it will be all. One step at a time. This MR is intended to have zero change in behaviour: it is a pure refactor. It opens the way to subsequent tidying up, we believe. - - - - - cedf9a3b by Torsten Schmits at 2023-03-22T15:31:18-04:00 Add structured error messages for GHC.Tc.Utils.TcMType Tracking ticket: #20119 MR: !10138 This converts uses of `mkTcRnUnknownMessage` to newly added constructors of `TcRnMessage`. - - - - - 30d45e97 by Sylvain Henry at 2023-03-22T15:32:01-04:00 Testsuite: use js_skip for T2615 (#22374) - - - - - 4aeead36 by Adam Gundry at 2023-03-23T13:53:47+01:00 Adapt to warning categories changes - - - - - 8c98deba by Armando Ramirez at 2023-03-23T09:19:32-04:00 Optimized Foldable methods for Data.Functor.Compose Explicitly define length, elem, etc. in Foldable instance for Data.Functor.Compose Implementation of https://github.com/haskell/core-libraries-committee/issues/57 - - - - - bc066108 by Armando Ramirez at 2023-03-23T09:19:32-04:00 Additional optimized versions - - - - - 80fce576 by Andrew Lelechenko at 2023-03-23T09:19:32-04:00 Simplify minimum/maximum in instance Foldable (Compose f g) - - - - - 8cb88a5a by Andrew Lelechenko at 2023-03-23T09:19:32-04:00 Update changelog to mention changes to instance Foldable (Compose f g) - - - - - e1c8c41d by Torsten Schmits at 2023-03-23T09:20:13-04:00 Add structured error messages for GHC.Tc.TyCl.PatSyn Tracking ticket: #20117 MR: !10158 This converts uses of `mkTcRnUnknownMessage` to newly added constructors of `TcRnMessage`. - - - - - f932c589 by Adam Gundry at 2023-03-24T02:36:09-04:00 Allow WARNING pragmas to be controlled with custom categories Closes #17209. This implements GHC Proposal 541, allowing a WARNING pragma to be annotated with a category like so: {-# WARNING in "x-partial" head "This function is undefined on empty lists." #-} The user can then enable, disable and set the severity of such warnings using command-line flags `-Wx-partial`, `-Werror=x-partial` and so on. There is a new warning group `-Wextended-warnings` containing all these warnings. Warnings without a category are treated as if the category was `deprecations`, and are (still) controlled by the flags `-Wdeprecations` and `-Wwarnings-deprecations`. Updates Haddock submodule. - - - - - 0426515b by Adam Gundry at 2023-03-24T02:36:09-04:00 Move mention of warning groups change to 9.8.1 release notes - - - - - b8d783d2 by Ben Gamari at 2023-03-24T02:36:45-04:00 nativeGen/AArch64: Fix bitmask immediate predicate Previously the predicate for determining whether a logical instruction operand could be encoded as a bitmask immediate was far too conservative. This meant that, e.g., pointer untagged required five instructions whereas it should only require one. Fixes #23030. - - - - - 46120bb6 by Joachim Breitner at 2023-03-24T13:09:43-04:00 User's guide: Improve docs for -Wall previously it would list the warnings _not_ enabled by -Wall. That’s unnecessary round-about and was out of date. So let's just name the relevant warnings (based on `compiler/GHC/Driver/Flags.hs`). - - - - - 509d1f11 by Ben Gamari at 2023-03-24T13:10:20-04:00 codeGen/tsan: Disable instrumentation of unaligned stores There is some disagreement regarding the prototype of `__tsan_unaligned_write` (specifically whether it takes just the written address, or the address and the value as an argument). Moreover, I have observed crashes which appear to be due to it. Disable instrumentation of unaligned stores as a temporary mitigation. Fixes #23096. - - - - - 6a73655f by Li-yao Xia at 2023-03-25T00:02:44-04:00 base: Document GHC versions associated with past base versions in the changelog - - - - - 43bd7694 by Teo Camarasu at 2023-03-25T00:03:24-04:00 Add regression test for #17574 This test currently fails in the nonmoving way - - - - - f2d56bf7 by Teo Camarasu at 2023-03-25T00:03:24-04:00 fix: account for large and compact object stats with nonmoving gc Make sure that we keep track of the size of large and compact objects that have been moved onto the nonmoving heap. We keep track of their size and add it to the amount of live bytes in nonmoving segments to get the total size of the live nonmoving heap. Resolves #17574 - - - - - 7131b705 by David Feuer at 2023-03-25T00:04:04-04:00 Modify ThreadId documentation and comments For a long time, `GHC.Conc.Sync` has said ```haskell -- ToDo: data ThreadId = ThreadId (Weak ThreadId#) -- But since ThreadId# is unlifted, the Weak type must use open -- type variables. ``` We are now actually capable of using `Weak# ThreadId#`, but the world has moved on. To support the `Show` and `Ord` instances, we'd need to store the thread ID number in the `ThreadId`. And it seems very difficult to continue to support `threadStatus` in that regime, since it needs to be able to explain how threads died. In addition, garbage collection of weak references can be quite expensive, and it would be hard to evaluate the cost over he whole ecosystem. As discussed in [this CLC issue](https://github.com/haskell/core-libraries-committee/issues/125), it doesn't seem very likely that we'll actually switch to weak references here. - - - - - c421bbbb by Ben Gamari at 2023-03-25T00:04:41-04:00 rts: Fix barriers of IND and IND_STATIC Previously IND and IND_STATIC lacked the acquire barriers enjoyed by BLACKHOLE. As noted in the (now updated) Note [Heap memory barriers], this barrier is critical to ensure that the indirectee is visible to the entering core. Fixes #22872. - - - - - 62fa7faa by Andrew Lelechenko at 2023-03-25T00:05:22-04:00 Improve documentation of atomicModifyMutVar2# - - - - - b2d14d0b by Cheng Shao at 2023-03-25T03:46:43-04:00 rts: use performBlockingMajorGC in hs_perform_gc and fix ffi023 This patch does a few things: - Add the missing RtsSymbols.c entry of performBlockingMajorGC - Make hs_perform_gc call performBlockingMajorGC, which restores previous behavior - Use hs_perform_gc in ffi023 - Remove rts_clearMemory() call in ffi023, it now works again in some test ways previously marked as broken. Fixes #23089 - - - - - d9ae24ad by Cheng Shao at 2023-03-25T03:46:44-04:00 testsuite: add the rts_clearMemory test case This patch adds a standalone test case for rts_clearMemory that mimics how it's typically used by wasm backend users and ensures this RTS API isn't broken by future RTS refactorings. Fixes #23901. - - - - - 80729d96 by Andrew Lelechenko at 2023-03-25T03:47:22-04:00 Improve documentation for resizing of byte arrays - - - - - c6ec4cd1 by Ben Gamari at 2023-03-25T20:23:47-04:00 rts: Don't rely on EXTERN_INLINE for slop-zeroing logic Previously we relied on calling EXTERN_INLINE functions defined in ClosureMacros.h from Cmm to zero slop. However, as far as I can tell, this is no longer safe to do in C99 as EXTERN_INLINE definitions may be emitted in each compilation unit. Fix this by explicitly declaring a new set of non-inline functions in ZeroSlop.c which can be called from Cmm and marking the ClosureMacros.h definitions as INLINE_HEADER. In the future we should try to eliminate EXTERN_INLINE. - - - - - c32abd4b by Ben Gamari at 2023-03-25T20:23:48-04:00 rts: Fix capability-count check in zeroSlop Previously `zeroSlop` examined `RtsFlags` to determine whether the program was single-threaded. This is wrong; a program may be started with `+RTS -N1` yet the process may later increase the capability count with `setNumCapabilities`. This lead to quite subtle and rare crashes. Fixes #23088. - - - - - 656d4cb3 by Ryan Scott at 2023-03-25T20:24:23-04:00 Add Eq/Ord instances for SSymbol, SChar, and SNat This implements [CLC proposal #148](https://github.com/haskell/core-libraries-committee/issues/148). - - - - - 4f93de88 by David Feuer at 2023-03-26T15:33:02-04:00 Update and expand atomic modification Haddocks * The documentation for `atomicModifyIORef` and `atomicModifyIORef'` were incomplete, and the documentation for `atomicModifyIORef` was out of date. Update and expand. * Remove a useless lazy pattern match in the definition of `atomicModifyIORef`. The pair it claims to match lazily was already forced by `atomicModifyIORef2`. - - - - - e1fb56b2 by David Feuer at 2023-03-26T15:33:41-04:00 Document the constructor name for lists Derived `Data` instances use raw infix constructor names when applicable. The `Data.Data [a]` instance, if derived, would have a constructor name of `":"`. However, it actually uses constructor name `"(:)"`. Document this peculiarity. See https://github.com/haskell/core-libraries-committee/issues/147 - - - - - c1f755c4 by Simon Peyton Jones at 2023-03-27T22:09:41+01:00 Make exprIsConApp_maybe a bit cleverer Addresses #23159. See Note Note [Exploit occ-info in exprIsConApp_maybe] in GHC.Core.SimpleOpt. Compile times go down very slightly, but always go down, never up. Good! Metrics: compile_time/bytes allocated ------------------------------------------------ CoOpt_Singletons(normal) -1.8% T15703(normal) -1.2% GOOD geo. mean -0.1% minimum -1.8% maximum +0.0% Metric Decrease: CoOpt_Singletons T15703 - - - - - 76bb4c58 by Ryan Scott at 2023-03-28T08:12:08-04:00 Add COMPLETE pragmas to TypeRep, SSymbol, SChar, and SNat This implements [CLC proposal #149](https://github.com/haskell/core-libraries-committee/issues/149). - - - - - 642d8d60 by sheaf at 2023-03-29T13:35:56+02:00 Adapt to record field refactor This commit adapts to the changes in GHC MR !8686, which overhauls the treatment of record fields in the renamer, adding separate record field namespaces and entirely removing the GreName datatype. - - - - - 3f374399 by sheaf at 2023-03-29T13:57:33+02:00 Handle records in the renamer This patch moves the field-based logic for disambiguating record updates to the renamer. The type-directed logic, scheduled for removal, remains in the typechecker. To do this properly (and fix the myriad of bugs surrounding the treatment of duplicate record fields), we took the following main steps: 1. Create GREInfo, a renamer-level equivalent to TyThing which stores information pertinent to the renamer. This allows us to uniformly treat imported and local Names in the renamer, as described in Note [GREInfo]. 2. Remove GreName. Instead of a GlobalRdrElt storing GreNames, which distinguished between normal names and field names, we now store simple Names in GlobalRdrElt, along with the new GREInfo information which allows us to recover the FieldLabel for record fields. 3. Add namespacing for record fields, within the OccNames themselves. This allows us to remove the mangling of duplicate field selectors. This change ensures we don't print mangled names to the user in error messages, and allows us to handle duplicate record fields in Template Haskell. 4. Move record disambiguation to the renamer, and operate on the level of data constructors instead, to handle #21443. The error message text for ambiguous record updates has also been changed to reflect that type-directed disambiguation is on the way out. (3) means that OccEnv is now a bit more complex: we first key on the textual name, which gives an inner map keyed on NameSpace: OccEnv a ~ FastStringEnv (UniqFM NameSpace a) Note that this change, along with (2), both increase the memory residency of GlobalRdrEnv = OccEnv [GlobalRdrElt], which causes a few tests to regress somewhat in compile-time allocation. Even though (3) simplified a lot of code (in particular the treatment of field selectors within Template Haskell and in error messages), it came with one important wrinkle: in the situation of -- M.hs-boot module M where { data A; foo :: A -> Int } -- M.hs module M where { data A = MkA { foo :: Int } } we have that M.hs-boot exports a variable foo, which is supposed to match with the record field foo that M exports. To solve this issue, we add a new impedance-matching binding to M foo{var} = foo{fld} This mimics the logic that existed already for impedance-binding DFunIds, but getting it right was a bit tricky. See Note [Record field impedance matching] in GHC.Tc.Module. We also needed to be careful to avoid introducing space leaks in GHCi. So we dehydrate the GlobalRdrEnv before storing it anywhere, e.g. in ModIface. This means stubbing out all the GREInfo fields, with the function forceGlobalRdrEnv. When we read it back in, we rehydrate with rehydrateGlobalRdrEnv. This robustly avoids any space leaks caused by retaining old type environments. Fixes #13352 #14848 #17381 #17551 #19664 #21443 #21444 #21720 #21898 #21946 #21959 #22125 #22160 #23010 #23062 #23063 Updates haddock submodule ------------------------- Metric Increase: MultiComponentModules MultiLayerModules MultiLayerModulesDefsGhci MultiLayerModulesNoCode T13701 T14697 hard_hole_fits ------------------------- - - - - - 4f1940f0 by sheaf at 2023-03-29T13:57:33+02:00 Avoid repeatedly shadowing in shadowNames This commit refactors GHC.Type.Name.Reader.shadowNames to first accumulate all the shadowing arising from the introduction of a new set of GREs, and then applies all the shadowing to the old GlobalRdrEnv in one go. - - - - - d246049c by sheaf at 2023-03-29T13:57:34+02:00 igre_prompt_env: discard "only-qualified" names We were unnecessarily carrying around names only available qualified in igre_prompt_env, violating the icReaderEnv invariant. We now get rid of these, as they aren't needed for the shadowing computation that igre_prompt_env exists for. Fixes #23177 ------------------------- Metric Decrease: T14052 T14052Type ------------------------- - - - - - ac8d4333 by doyougnu at 2023-03-29T11:11:44-04:00 Update UniqMap API - - - - - 41a572f6 by Matthew Pickering at 2023-03-29T16:17:21-04:00 hadrian: Fix path to HpcParser.y The source for this project has been moved into a src/ folder so we also need to update this path. Fixes #23187 - - - - - b159e0e9 by doyougnu at 2023-03-30T01:40:08-04:00 js: split JMacro into JS eDSL and JS syntax This commit: Splits JExpr and JStat into two nearly identical DSLs: - GHC.JS.Syntax is the JMacro based DSL without unsaturation, i.e., a value cannot be unsaturated, or, a value of this DSL is a witness that a value of GHC.JS.Unsat has been saturated - GHC.JS.Unsat is the JMacro DSL from GHCJS with Unsaturation. Then all binary and outputable instances are changed to use GHC.JS.Syntax. This moves us closer to closing out #22736 and #22352. See #22736 for roadmap. ------------------------- Metric Increase: CoOpt_Read LargeRecord ManyAlternatives PmSeriesS PmSeriesT PmSeriesV T10421 T10858 T11195 T11374 T11822 T12227 T12707 T13035 T13253 T13253-spj T13379 T14683 T15164 T15703 T16577 T17096 T17516 T17836 T18140 T18282 T18304 T18478 T18698a T18698b T18923 T1969 T19695 T20049 T21839c T3064 T4801 T5321FD T5321Fun T5631 T5642 T783 T9198 T9233 T9630 TcPlugin_RewritePerf WWRec ------------------------- - - - - - f4f1f14f by Sylvain Henry at 2023-03-30T01:40:49-04:00 ghc-heap: remove wrong Addr# coercion (#23181) Conversion from Addr# to I# isn't correct with the JS backend. Also used the opportunity to reenable 64-bit Word/Int tests - - - - - a5360490 by Ben Gamari at 2023-03-30T01:41:25-04:00 testsuite: Fix racing prints in T21465 As noted in #23155, we previously failed to add flushes necessary to ensure predictable output. Fixes #23155. - - - - - 98b5cf67 by Matthew Pickering at 2023-03-30T09:58:40+01:00 Revert "ghc-heap: remove wrong Addr# coercion (#23181)" This reverts commit f4f1f14f8009c3c120b8b963ec130cbbc774ec02. This fails to build with GHC-9.2 as a boot compiler. See #23195 for tracking this issue. - - - - - 61a2dfaa by Andrew Lelechenko at 2023-03-30T14:35:57-04:00 Add {-# WARNING #-} to Data.List.{head,tail} - - - - - 8f15c47c by Andrew Lelechenko at 2023-03-30T14:35:57-04:00 Fixes to accomodate Data.List.{head,tail} with {-# WARNING #-} - - - - - 7c7dbade by Andrew Lelechenko at 2023-03-30T14:35:57-04:00 Bump submodules - - - - - d2d8251b by Andrew Lelechenko at 2023-03-30T14:35:57-04:00 Fix tests - - - - - 3d38dcb6 by sheaf at 2023-03-30T14:35:57-04:00 Proxies for head and tail: review suggestions - - - - - 930edcfd by sheaf at 2023-03-30T14:36:33-04:00 docs: move RecordUpd changelog entry to 9.8 This was accidentally included in the 9.6 changelog instead of the 9.6 changelog. - - - - - 6f885e65 by sheaf at 2023-03-30T14:37:09-04:00 Add LANGUAGE GADTs to GHC.Rename.Env We need to enable this extension for the file to compile with ghc 9.2, as we are pattern matching on a GADT and this required the GADT extension to be enabled until 9.4. - - - - - 6d6a37a8 by Cheng Shao at 2023-03-30T18:42:56+00:00 ci: make lint-ci-config job fast again We don't pin our nixpkgs revision and tracks the default nixpkgs-unstable channel anyway. Instead of using haskell.packages.ghc924, we should be using haskell.packages.ghc92 to maximize the binary cache hit rate and make lint-ci-config job fast again. Also bumps the nix docker image to the latest revision. - - - - - ef1548c4 by Cheng Shao at 2023-03-30T18:42:56+00:00 ci: ensure that all non-i386 pipelines do parallel xz compression We can safely enable parallel xz compression for non-i386 pipelines. However, previously we didn't export XZ_OPT, so the xz process won't see it if XZ_OPT hasn't already been set in the current job. - - - - - 20432d16 by Cheng Shao at 2023-03-30T18:42:56+00:00 ci: unset CROSS_EMULATOR for js job - - - - - 4a24dbbe by Cheng Shao at 2023-03-30T18:42:56+00:00 ci: fix lint-testsuite job The list_broken make target will transitively depend on the calibrate.out target, which used STAGE1_GHC instead of TEST_HC. It really should be TEST_HC since that's what get passed in the gitlab CI config. - - - - - cea56ccc by Cheng Shao at 2023-03-30T18:42:56+00:00 ci: use alpine3_17-wasm image for wasm jobs Bump the ci-images dependency and use the new alpine3_17-wasm docker image for wasm jobs. - - - - - 79d0cb32 by Ben Gamari at 2023-03-30T18:43:53+00:00 testsuite/driver: Add basic support for testing cross-compilers - - - - - e7392b4e by Ben Gamari at 2023-03-30T18:43:53+00:00 testsuite/driver: Normalize away differences in ghc executable name - - - - - ee160d06 by Ben Gamari at 2023-03-30T18:43:53+00:00 hadrian: Pass CROSS_EMULATOR to runtests.py - - - - - 30c84511 by Cheng Shao at 2023-03-30T18:43:53+00:00 testsuite: don't add optllvm way for wasm32 - - - - - f1beee36 by Cheng Shao at 2023-03-30T18:43:53+00:00 testsuite: normalize the .wasm extension - - - - - a984a103 by Cheng Shao at 2023-03-30T18:43:53+00:00 testsuite: strip the cross ghc prefix in output and error message - - - - - f7478d95 by Cheng Shao at 2023-03-30T18:43:53+00:00 testsuite: handle target executable extension - - - - - 8fe8b653 by Cheng Shao at 2023-03-30T18:43:53+00:00 testsuite: mypy typing error fixes This patch fixes some mypy typing errors which weren't caught in previous linting jobs. - - - - - 0149f32f by Cheng Shao at 2023-03-30T18:43:53+00:00 testsuite: use context variable instead of thread-local variable This patch changes a thread-local variable to context variable instead, which works as intended when the testsuite transitions to use asyncio & coroutines instead of multi-threading to concurrently run test cases. Note that this also raises the minimum Python version to 3.7. - - - - - ea853ff0 by Cheng Shao at 2023-03-30T18:43:53+00:00 testsuite: asyncify the testsuite driver This patch refactors the testsuite driver, gets rid of multi-threading logic for running test cases concurrently, and uses asyncio & coroutines instead. This is not yak shaving for its own sake; the previous multi-threading logic is prone to livelock/deadlock conditions for some reason, even if the total number of threads is bounded to a thread pool's capacity. The asyncify change is an internal implementation detail of the testsuite driver and does not impact most GHC maintainers out there. The patch does not touch the .T files, test cases can be added/modified the exact same way as before. - - - - - 0077cb22 by Matthew Pickering at 2023-03-31T21:28:28-04:00 Add test for T23184 There was an outright bug, which Simon fixed in July 2021, as a little side-fix on a complicated patch: ``` commit 6656f0165a30fc2a22208532ba384fc8e2f11b46 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Fri Jul 23 23:57:01 2021 +0100 A bunch of changes related to eta reduction This is a large collection of changes all relating to eta reduction, originally triggered by #18993, but there followed a long saga. Specifics: ...lots of lines omitted... Other incidental changes * Fix a fairly long-standing outright bug in the ApplyToVal case of GHC.Core.Opt.Simplify.mkDupableContWithDmds. I was failing to take the tail of 'dmds' in the recursive call, which meant the demands were All Wrong. I have no idea why this has not caused problems before now. ``` Note this "Fix a fairly longstanding outright bug". This is the specific fix ``` @@ -3552,8 +3556,8 @@ mkDupableContWithDmds env dmds -- let a = ...arg... -- in [...hole...] a -- NB: sc_dup /= OkToDup; that is caught earlier by contIsDupable - do { let (dmd:_) = dmds -- Never fails - ; (floats1, cont') <- mkDupableContWithDmds env dmds cont + do { let (dmd:cont_dmds) = dmds -- Never fails + ; (floats1, cont') <- mkDupableContWithDmds env cont_dmds cont ; let env' = env `setInScopeFromF` floats1 ; (_, se', arg') <- simplArg env' dup se arg ; (let_floats2, arg'') <- makeTrivial env NotTopLevel dmd (fsLit "karg") arg' ``` Ticket #23184 is a report of the bug that this diff fixes. - - - - - 62d25071 by mangoiv at 2023-04-01T04:20:01-04:00 [feat] make ($) representation polymorphic - this change was approved by the CLC in [1] following a CLC proposal [2] - make ($) representation polymorphic (adjust the type signature) - change ($) implementation to allow additional polymorphism - adjust the haddock of ($) to reflect these changes - add additional documentation to document these changes - add changelog entry - adjust tests (move now succeeding tests and adjust stdout of some tests) [1] https://github.com/haskell/core-libraries-committee/issues/132#issuecomment-1487456854 [2] https://github.com/haskell/core-libraries-committee/issues/132 - - - - - 77c33fb9 by Artem Pelenitsyn at 2023-04-01T04:20:41-04:00 User Guide: update copyright year: 2020->2023 - - - - - 3b5be05a by doyougnu at 2023-04-01T09:42:31-04:00 driver: Unit State Data.Map -> GHC.Unique.UniqMap In pursuit of #22426. The driver and unit state are major contributors. This commit also bumps the haddock submodule to reflect the API changes in UniqMap. ------------------------- Metric Decrease: MultiComponentModules MultiComponentModulesRecomp T10421 T10547 T12150 T12234 T12425 T13035 T16875 T18140 T18304 T18698a T18698b T18923 T20049 T5837 T6048 T9198 ------------------------- - - - - - a84fba6e by Torsten Schmits at 2023-04-01T09:43:12-04:00 Add structured error messages for GHC.Tc.TyCl Tracking ticket: #20117 MR: !10183 This converts uses of `mkTcRnUnknownMessage` to newly added constructors of `TcRnMessage`. - - - - - 6e2eb275 by doyougnu at 2023-04-01T18:27:56-04:00 JS: Linker: use saturated JExpr Follow on to MR!10142 in pursuit of #22736 - - - - - 3da69346 by sheaf at 2023-04-01T18:28:37-04:00 Improve haddocks of template-haskell Con datatype This adds a bit more information, in particular about the lists of constructors in the GadtC and RecGadtC cases. - - - - - 3b7bbb39 by sheaf at 2023-04-01T18:28:37-04:00 TH: revert changes to GadtC & RecGadtC Commit 3f374399 included a breaking-change to the template-haskell library when it made the GadtC and RecGadtC constructors take non-empty lists of names. As this has the potential to break many users' packages, we decided to revert these changes for now. - - - - - f60f6110 by Andrew Lelechenko at 2023-04-02T18:59:30-04:00 Rework documentation for data Char - - - - - 43ebd5dc by Andrew Lelechenko at 2023-04-02T19:00:09-04:00 cmm: implement parsing of MO_AtomicRMW from hand-written CMM files Fixes #23206 - - - - - ab9cd52d by Sylvain Henry at 2023-04-03T08:15:21-04:00 ghc-heap: remove wrong Addr# coercion (#23181) Conversion from Addr# to I# isn't correct with the JS backend. - - - - - 2b2afff3 by Matthew Pickering at 2023-04-03T08:15:58-04:00 hadrian: Update bootstrap plans for 9.2.6, 9.2.7, 9.4.4, 9.4.5, 9.6.1 Also fixes the ./generate_bootstrap_plans script which was recently broken We can hopefully drop the 9.2 plans soon but they still work so kept them around for now. - - - - - c2605e25 by Matthew Pickering at 2023-04-03T08:15:58-04:00 ci: Add job to test 9.6 bootstrapping - - - - - 53e4d513 by Krzysztof Gogolewski at 2023-04-03T08:16:35-04:00 hadrian: Improve option parsing Several options in Hadrian had their argument marked as optional (`OptArg`), but if the argument wasn't there they were just giving an error. It's more idiomatic to mark the argument as required instead; the code uses less Maybes, the parser can enforce that the argument is present, --help gives better output. - - - - - a8e36892 by Sylvain Henry at 2023-04-03T08:17:16-04:00 JS: fix issues with FD api support - Add missing implementations for fcntl_read/write/lock - Fix fdGetMode These were found while implementing TH in !9779. These functions must be used somehow by the external interpreter code. - - - - - 8b092910 by Haskell-mouse at 2023-04-03T19:31:26-04:00 Convert diagnostics in GHC.Rename.HsType to proper TcRnMessage I've turned all occurrences of TcRnUnknownMessage in GHC.Rename.HsType module into a proper TcRnMessage. Instead, these TcRnMessage messages were introduced: TcRnDataKindsError TcRnUnusedQuantifiedTypeVar TcRnIllegalKindSignature TcRnUnexpectedPatSigType TcRnSectionPrecedenceError TcRnPrecedenceParsingError TcRnIllegalKind TcRnNegativeNumTypeLiteral TcRnUnexpectedKindVar TcRnBindMultipleVariables TcRnBindVarAlreadyInScope - - - - - 220a7a48 by Krzysztof Gogolewski at 2023-04-03T19:32:02-04:00 Fixes around unsafeCoerce# 1. `unsafeCoerce#` was documented in `GHC.Prim`. But since the overhaul in 74ad75e87317, `unsafeCoerce#` is no longer defined there. I've combined the documentation in `GHC.Prim` with the `Unsafe.Coerce` module. 2. The documentation of `unsafeCoerce#` stated that you should not cast a function to an algebraic type, even if you later cast it back before applying it. But ghci was doing that type of cast, as can be seen with 'ghci -ddump-ds' and typing 'x = not'. I've changed it to use Any following the documentation. - - - - - 9095e297 by Matthew Craven at 2023-04-04T01:04:10-04:00 Add a few more memcpy-ish primops * copyMutableByteArrayNonOverlapping# * copyAddrToAddr# * copyAddrToAddrNonOverlapping# * setAddrRange# The implementations of copyBytes, moveBytes, and fillBytes in base:Foreign.Marshal.Utils now use these new primops, which can cause us to work a bit harder generating code for them, resulting in the metric increase in T21839c observed by CI on some architectures. But in exchange, we get better code! Metric Increase: T21839c - - - - - f7da530c by Matthew Craven at 2023-04-04T01:04:10-04:00 StgToCmm: Upgrade -fcheck-prim-bounds behavior Fixes #21054. Additionally, we can now check for range overlap when generating Cmm for primops that use memcpy internally. - - - - - cd00e321 by sheaf at 2023-04-04T01:04:50-04:00 Relax assertion in varToRecFieldOcc When using Template Haskell, it is possible to re-parent a field OccName belonging to one data constructor to another data constructor. The lsp-types package did this in order to "extend" a data constructor with additional fields. This ran into an assertion in 'varToRecFieldOcc'. This assertion can simply be relaxed, as the resulting splices are perfectly sound. Fixes #23220 - - - - - eed0d930 by Sylvain Henry at 2023-04-04T11:09:15-04:00 GHCi.RemoteTypes: fix doc and avoid unsafeCoerce (#23201) - - - - - 071139c3 by Ryan Scott at 2023-04-04T11:09:51-04:00 Make INLINE pragmas for pattern synonyms work with TH Previously, the code for converting `INLINE <name>` pragmas from TH splices used `vNameN`, which assumed that `<name>` must live in the variable namespace. Pattern synonyms, on the other hand, live in the constructor namespace. I've fixed the issue by switching to `vcNameN` instead, which works for both the variable and constructor namespaces. Fixes #23203. - - - - - 7c16f3be by Krzysztof Gogolewski at 2023-04-04T17:13:00-04:00 Fix unification with oversaturated type families unify_ty was incorrectly saying that F x y ~ T x are surely apart, where F x y is an oversaturated type family and T x is a tyconapp. As a result, the simplifier dropped a live case alternative (#23134). - - - - - c165f079 by sheaf at 2023-04-04T17:13:40-04:00 Add testcase for #23192 This issue around solving of constraints arising from superclass expansion using other constraints also borned from superclass expansion was the topic of commit aed1974e. That commit made sure we don't emit a "redundant constraint" warning in a situation in which removing the constraint would cause errors. Fixes #23192 - - - - - d1bb16ed by Ben Gamari at 2023-04-06T03:40:45-04:00 nonmoving: Disable slop-zeroing As noted in #23170, the nonmoving GC can race with a mutator zeroing the slop of an updated thunk (in much the same way that two mutators would race). Consequently, we must disable slop-zeroing when the nonmoving GC is in use. Closes #23170 - - - - - 04b80850 by Brandon Chinn at 2023-04-06T03:41:21-04:00 Fix reverse flag for -Wunsupported-llvm-version - - - - - 0c990e13 by Pierre Le Marre at 2023-04-06T10:16:29+00:00 Add release note for GHC.Unicode refactor in base-4.18. Also merge CLC proposal 130 in base-4.19 with CLC proposal 59 in base-4.18 and add proper release date. - - - - - cbbfb283 by Alex Dixon at 2023-04-07T18:27:45-04:00 Improve documentation for ($) (#22963) - - - - - 5193c2b0 by Alex Dixon at 2023-04-07T18:27:45-04:00 Remove trailing whitespace from ($) commentary - - - - - b384523b by Sebastian Graf at 2023-04-07T18:27:45-04:00 Adjust wording wrt representation polymorphism of ($) - - - - - 6a788f0a by Torsten Schmits at 2023-04-07T22:29:28-04:00 Add structured error messages for GHC.Tc.TyCl.Utils Tracking ticket: #20117 MR: !10251 This converts uses of `mkTcRnUnknownMessage` to newly added constructors of `TcRnMessage`. - - - - - 3ba77b36 by sheaf at 2023-04-07T22:30:07-04:00 Renamer: don't call addUsedGRE on an exact Name When looking up a record field in GHC.Rename.Env.lookupRecFieldOcc, we could end up calling addUsedGRE on an exact Name, which would then lead to a panic in the bestImport function: it would be incapable of processing a GRE which is not local but also not brought into scope by any imports (as it is referred to by its unique instead). Fixes #23240 - - - - - bc4795d2 by Krzysztof Gogolewski at 2023-04-11T19:24:54-04:00 Add support for -debug in the testsuite Confusingly, GhcDebugged referred to GhcDebugAssertions. - - - - - b7474b57 by Krzysztof Gogolewski at 2023-04-11T19:24:54-04:00 Add missing cases in -Di prettyprinter Fixes #23142 - - - - - 6c392616 by Cheng Shao at 2023-04-11T19:25:31-04:00 compiler: make WasmCodeGenM an instance of MonadUnique - - - - - 05d26a65 by Cheng Shao at 2023-04-11T19:25:31-04:00 compiler: apply cmm node-splitting for wasm backend This patch applies cmm node-splitting for wasm32 NCG, which is required when handling irreducible CFGs. Fixes #23237. - - - - - f1892cc0 by Andrew Lelechenko at 2023-04-11T19:26:09-04:00 Set base 'maintainer' field to CLC - - - - - ecf22da3 by Simon Peyton Jones at 2023-04-11T19:26:45-04:00 Clarify a couple of Notes about 'nospec' - - - - - ebd8918b by Oleg Grenrus at 2023-04-12T12:32:57-04:00 Allow generation of TTH syntax with TH In other words allow generation of typed splices and brackets with Untyped Template Haskell. That is useful in cases where a library is build with TTH in mind, but we still want to generate some auxiliary declarations, where TTH cannot help us, but untyped TH can. Such example is e.g. `staged-sop` which works with TTH, but we would like to derive `Generic` declarations with TH. An alternative approach is to use `unsafeCodeCoerce`, but then the derived `Generic` instances would be type-checked only at use sites, i.e. much later. Also `-ddump-splices` output is quite ugly: user-written instances would use TTH brackets, not `unsafeCodeCoerce`. This commit doesn't allow generating of untyped template splices and brackets with untyped TH, as I don't know why one would want to do that (instead of merging the splices, e.g.) - - - - - 690d0225 by Rodrigo Mesquita at 2023-04-12T12:33:33-04:00 Add regression test for #23229 - - - - - 59321879 by Sylvain Henry at 2023-04-13T08:50:33-04:00 Add quotRem rules (#22152) case quotRemInt# x y of (# q, _ #) -> body ====> case quotInt# x y of q -> body case quotRemInt# x y of (# _, r #) -> body ====> case remInt# x y of r -> body - - - - - 4dd02122 by Sylvain Henry at 2023-04-13T08:50:33-04:00 Add quot folding rule (#22152) (x / l1) / l2 l1 and l2 /= 0 l1*l2 doesn't overflow ==> x / (l1 * l2) - - - - - 1148ac72 by Sylvain Henry at 2023-04-13T08:50:33-04:00 Make Int64/Word64 division ok for speculation too. Only when the divisor is definitely non-zero. - - - - - 8af401cc by Sylvain Henry at 2023-04-13T08:50:33-04:00 Make WordQuotRem2Op ok-for-speculation too - - - - - 27d2978e by Josh Meredith at 2023-04-13T08:51:09-04:00 Base/JS: GHC.JS.Foreign.Callback module (issue 23126) * Add the Callback module for "exporting" Haskell functions to be available to plain JavaScript code * Fix some primitives defined in GHC.JS.Prim * Add a JavaScript section to the user guide with instructions on how to use the JavaScript FFI, building up to using Callbacks to interact with the browser * Add tests for the JavaScript FFI and Callbacks - - - - - a34aa8da by Adam Sandberg Ericsson at 2023-04-14T04:17:52-04:00 rts: improve memory ordering and add some comments in the StablePtr implementation - - - - - d7a768a4 by Matthew Pickering at 2023-04-14T04:18:28-04:00 docs: Generate docs/index.html with version number * Generate docs/index.html to include the version of the ghc library * This also fixes the packageVersions interpolations which were - Missing an interpolation for `LIBRARY_ghc_VERSION` - Double quoting the version so that "9.7" was being inserted. Fixes #23121 - - - - - d48fbfea by Simon Peyton Jones at 2023-04-14T04:19:05-04:00 Stop if type constructors have kind errors Otherwise we get knock-on errors, such as #23252. This makes GHC fail a bit sooner, and I have not attempted to add recovery code, to add a fake TyCon place of the erroneous one, in an attempt to get more type errors in one pass. We could do that (perhaps) if there was a call for it. - - - - - 2371d6b2 by Simon Peyton Jones at 2023-04-14T20:01:02+02:00 Major refactor in the handling of equality constraints This MR substantially refactors the way in which the constraint solver deals with equality constraints. The big thing is: * Intead of a pipeline in which we /first/ canonicalise and /then/ interact (the latter including performing unification) the two steps are more closely integreated into one. That avoids the current rather indirect communication between the two steps. The proximate cause for this refactoring is fixing #22194, which involve solving [W] alpha[2] ~ Maybe (F beta[4]) by doing this: alpha[2] := Maybe delta[2] [W] delta[2] ~ F beta[4] That is, we don't promote beta[4]! This is very like introducing a cycle breaker, and was very awkward to do before, but now it is all nice. See GHC.Tc.Utils.Unify Note [Promotion and level-checking] and Note [Family applications in canonical constraints]. The big change is this: * Several canonicalisation checks (occurs-check, cycle-breaking, checking for concreteness) are combined into one new function: GHC.Tc.Utils.Unify.checkTyEqRhs This function is controlled by `TyEqFlags`, which says what to do for foralls, type families etc. * `canEqCanLHSFinish` now sees if unification is possible, and if so, actually does it: see `canEqCanLHSFinish_try_unification`. There are loads of smaller changes: * The on-the-fly unifier `GHC.Tc.Utils.Unify.unifyType` has a cheap-and-cheerful version of `checkTyEqRhs`, called `simpleUnifyCheck`. If `simpleUnifyCheck` succeeds, it can unify, otherwise it defers by emitting a constraint. This is simpler than before. * I simplified the swapping code in `GHC.Tc.Solver.Equality.canEqCanLHS`. Especially the nasty stuff involving `swap_for_occurs` and `canEqTyVarFunEq`. Much nicer now. See Note [Orienting TyVarLHS/TyFamLHS] Note [Orienting TyFamLHS/TyFamLHS] * Added `cteSkolemOccurs`, `cteConcrete`, and `cteCoercionHole` to the problems that can be discovered by `checkTyEqRhs`. * I fixed #23199 `pickQuantifiablePreds`, which actually allows GHC to to accept both cases in #22194 rather than rejecting both. Yet smaller: * Added a `synIsConcrete` flag to `SynonymTyCon` (alongside `synIsFamFree`) to reduce the need for synonym expansion when checking concreteness. Use it in `isConcreteType`. * Renamed `isConcrete` to `isConcreteType` * Defined `GHC.Core.TyCo.FVs.isInjectiveInType` as a more efficient way to find if a particular type variable is used injectively than finding all the injective variables. It is called in `GHC.Tc.Utils.Unify.definitely_poly`, which in turn is used quite a lot. * Moved `rewriterView` to `GHC.Core.Type`, so we can use it from the constraint solver. Fixes #22194, #23199 Compile times decrease by an average of 0.1%; but there is a 7.4% drop in compiler allocation on T15703. Metric Decrease: T15703 - - - - - 99b2734b by Simon Peyton Jones at 2023-04-14T20:01:02+02:00 Add some documentation about redundant constraints - - - - - 3f2d0eb8 by Simon Peyton Jones at 2023-04-14T20:01:02+02:00 Improve partial signatures This MR fixes #23223. The changes are in two places: * GHC.Tc.Bind.checkMonomorphismRestriction See the new `Note [When the MR applies]` We now no longer stupidly attempt to apply the MR when the user specifies a context, e.g. f :: Eq a => _ -> _ * GHC.Tc.Solver.decideQuantification See rewritten `Note [Constraints in partial type signatures]` Fixing this bug apparently breaks three tests: * partial-sigs/should_compile/T11192 * partial-sigs/should_fail/Defaulting1MROff * partial-sigs/should_fail/T11122 However they are all symptoms of #23232, so I'm marking them as expect_broken(23232). I feel happy about this MR. Nice. - - - - - 23e2a8a0 by Simon Peyton Jones at 2023-04-14T20:01:02+02:00 Make approximateWC a bit cleverer This MR fixes #23224: making approximateWC more clever See the long `Note [ApproximateWC]` in GHC.Tc.Solver All this is delicate and ad-hoc -- but it /has/ to be: we are talking about inferring a type for a binding in the presence of GADTs, type families and whatnot: known difficult territory. We just try as hard as we can. - - - - - 2c040246 by Matthew Pickering at 2023-04-15T00:57:14-04:00 docs: Update template-haskell docs to use Code Q a rather than Q (TExp a) Since GHC Proposal #195, the type of [|| ... ||] has been Code Q a rather than Q (TExp a). The documentation in the `template-haskell` library wasn't updated to reflect this change. Fixes #23148 - - - - - 0da18eb7 by Krzysztof Gogolewski at 2023-04-15T14:35:53+02:00 Show an error when we cannot default a concrete tyvar Fixes #23153 - - - - - bad2f8b8 by sheaf at 2023-04-15T15:14:36+02:00 Handle ConcreteTvs in inferResultToType inferResultToType was discarding the ir_frr information, which meant some metavariables ended up being MetaTvs instead of ConcreteTvs. This function now creates new ConcreteTvs as necessary, instead of always creating MetaTvs. Fixes #23154 - - - - - 3b0ea480 by Simon Peyton Jones at 2023-04-16T18:12:20-04:00 Transfer DFunId_ness onto specialised bindings Whether a binding is a DFunId or not has consequences for the `-fdicts-strict` flag, essentially if we are doing demand analysis for a DFunId then `-fdicts-strict` does not apply because the constraint solver can create recursive groups of dictionaries. In #22549 this was fixed for the "normal" case, see Note [Do not strictify the argument dictionaries of a dfun]. However the loop still existed if the DFunId was being specialised. The problem was that the specialiser would specialise a DFunId and turn it into a VanillaId and so the demand analyser didn't know to apply special treatment to the binding anymore and the whole recursive group was optimised to bottom. The solution is to transfer over the DFunId-ness of the binding in the specialiser so that the demand analyser knows not to apply the `-fstrict-dicts`. Fixes #22549 - - - - - a1371ebb by Oleg Grenrus at 2023-04-16T18:12:59-04:00 Add import lists to few GHC.Driver.Session imports Related to https://gitlab.haskell.org/ghc/ghc/-/issues/23261. There are a lot of GHC.Driver.Session which only use DynFlags, but not the parsing code. - - - - - 51479ceb by Matthew Pickering at 2023-04-17T08:08:48-04:00 Account for special GHC.Prim import in warnUnusedPackages The GHC.Prim import is treated quite specially primarily because there isn't an interface file for GHC.Prim. Therefore we record separately in the ModSummary if it's imported or not so we don't go looking for it. This logic hasn't made it's way to `-Wunused-packages` so if you imported GHC.Prim then the warning would complain you didn't use `-package ghc-prim`. Fixes #23212 - - - - - 1532a8b2 by Simon Peyton Jones at 2023-04-17T08:09:24-04:00 Add regression test for #23199 - - - - - 0158c5f1 by Ryan Scott at 2023-04-17T18:43:27-04:00 validDerivPred: Reject exotic constraints in IrredPreds This brings the `IrredPred` case in sync with the treatment of `ClassPred`s as described in `Note [Valid 'deriving' predicate]` in `GHC.Tc.Validity`. Namely, we should reject `IrredPred`s that are inferred from `deriving` clauses whose arguments contain other type constructors, as described in `(VD2) Reject exotic constraints` of that Note. This has the nice property that `deriving` clauses whose inferred instance context mention `TypeError` will now emit the type error in the resulting error message, which better matches existing intuitions about how `TypeError` should work. While I was in town, I noticed that much of `Note [Valid 'deriving' predicate]` was duplicated in a separate `Note [Exotic derived instance contexts]` in `GHC.Tc.Deriv.Infer`. I decided to fold the latter Note into the former so that there is a single authority on describing the conditions under which an inferred `deriving` constraint can be considered valid. This changes the behavior of `deriving` in a way that existing code might break, so I have made a mention of this in the GHC User's Guide. It seems very, very unlikely that much code is relying on this strange behavior, however, and even if there is, there is a clear, backwards-compatible migration path using `StandaloneDeriving`. Fixes #22696. - - - - - 10364818 by Krzysztof Gogolewski at 2023-04-17T18:44:03-04:00 Misc cleanup - Use dedicated list functions - Make cloneBndrs and cloneRecIdBndrs monadic - Fix invalid haddock comments in libraries/base - - - - - 5e1d33d7 by Matthew Pickering at 2023-04-18T10:31:02-04:00 Convert interface file loading errors into proper diagnostics This patch converts all the errors to do with loading interface files into proper structured diagnostics. * DriverMessage: Sometimes in the driver we attempt to load an interface file so we embed the IfaceMessage into the DriverMessage. * TcRnMessage: Most the time we are loading interface files during typechecking, so we embed the IfaceMessage This patch also removes the TcRnInterfaceLookupError constructor which is superceded by the IfaceMessage, which is now structured compared to just storing an SDoc before. - - - - - df1a5811 by sheaf at 2023-04-18T10:31:43-04:00 Don't panic in ltPatersonSize The function GHC.Tc.Utils.TcType.ltPatersonSize would panic when it encountered a type family on the RHS, as usually these are not allowed (type families are not allowed on the RHS of class instances or of quantified constraints). However, it is possible to still encounter type families on the RHS after doing a bit of constraint solving, as seen in test case T23171. This could trigger the panic in the call to ltPatersonSize in GHC.Tc.Solver.Canonical.mk_strict_superclasses, which is involved in avoiding loopy superclass constraints. This patch simply changes ltPatersonSize to return "I don't know, because there's a type family involved" in these cases. Fixes #23171 - - - - - d442ac05 by Sylvain Henry at 2023-04-19T20:04:35-04:00 JS: fix thread-related primops - - - - - 7a96f90b by Bryan Richter at 2023-04-19T20:05:11-04:00 CI: Disable abi-test-nightly See #23269 - - - - - ab6c1d29 by Sylvain Henry at 2023-04-19T20:05:50-04:00 Testsuite: don't use obsolescent egrep (#22351) Recent egrep displays the following message, breaking golden tests: egrep: warning: egrep is obsolescent; using grep -E Switch to using "grep -E" instead - - - - - 7866fc86 by Ben Orchard at 2023-04-20T11:29:33+02:00 update classify with new tokens - - - - - f15b0ce5 by Matthew Pickering at 2023-04-20T11:01:06-04:00 hadrian: Pass haddock file arguments in a response file In !10119 CI was failing on windows because the command line was too long. We can mitigate this by passing the file arguments to haddock in a response file. We can't easily pass all the arguments in a response file because the `+RTS` arguments can't be placed in the response file. Fixes #23273 - - - - - 7012ec2f by tocic at 2023-04-20T11:01:42-04:00 Fix doc typo in GHC.Read.readList - - - - - 5c873124 by sheaf at 2023-04-20T18:33:34-04:00 Implement -jsem: parallelism controlled by semaphores See https://github.com/ghc-proposals/ghc-proposals/pull/540/ for a complete description for the motivation for this feature. The `-jsem` option allows a build tool to pass a semaphore to GHC which GHC can use in order to control how much parallelism it requests. GHC itself acts as a client in the GHC jobserver protocol. ``` GHC Jobserver Protocol ~~~~~~~~~~~~~~~~~~~~~~ This proposal introduces the GHC Jobserver Protocol. This protocol allows a server to dynamically invoke many instances of a client process, while restricting all of those instances to use no more than <n> capabilities. This is achieved by coordination over a system semaphore (either a POSIX semaphore [6]_ in the case of Linux and Darwin, or a Win32 semaphore [7]_ in the case of Windows platforms). There are two kinds of participants in the GHC Jobserver protocol: - The *jobserver* creates a system semaphore with a certain number of available tokens. Each time the jobserver wants to spawn a new jobclient subprocess, it **must** first acquire a single token from the semaphore, before spawning the subprocess. This token **must** be released once the subprocess terminates. Once work is finished, the jobserver **must** destroy the semaphore it created. - A *jobclient* is a subprocess spawned by the jobserver or another jobclient. Each jobclient starts with one available token (its *implicit token*, which was acquired by the parent which spawned it), and can request more tokens through the Jobserver Protocol by waiting on the semaphore. Each time a jobclient wants to spawn a new jobclient subprocess, it **must** pass on a single token to the child jobclient. This token can either be the jobclient's implicit token, or another token which the jobclient acquired from the semaphore. Each jobclient **must** release exactly as many tokens as it has acquired from the semaphore (this does not include the implicit tokens). ``` Build tools such as cabal act as jobservers in the protocol and are responsibile for correctly creating, cleaning up and managing the semaphore. Adds a new submodule (semaphore-compat) for managing and interacting with semaphores in a cross-platform way. Fixes #19349 - - - - - 52d3e9b4 by Ben Gamari at 2023-04-20T18:34:11-04:00 rts: Initialize Array# header in listThreads# Previously the implementation of listThreads# failed to initialize the header of the created array, leading to various nastiness. Fixes #23071 - - - - - 1db30fe1 by Ben Gamari at 2023-04-20T18:34:11-04:00 testsuite: Add test for #23071 - - - - - dae514f9 by tocic at 2023-04-21T13:31:21-04:00 Fix doc typos in libraries/base/GHC - - - - - 113e21d7 by Sylvain Henry at 2023-04-21T13:32:01-04:00 Testsuite: replace some js_broken/js_skip predicates with req_c Using req_c is more precise. - - - - - 038bb031 by Krzysztof Gogolewski at 2023-04-21T18:03:04-04:00 Minor doc fixes - Add docs/index.html to .gitignore. It is created by ./hadrian/build docs, and it was the only file in Hadrian's templateRules not present in .gitignore. - Mention that MultiWayIf supports non-boolean guards - Remove documentation of optdll - removed in 2007, 763daed95 - Fix markdown syntax - - - - - e826cdb2 by amesgen at 2023-04-21T18:03:44-04:00 User's guide: DeepSubsumption is implied by Haskell{98,2010} - - - - - 499a1c20 by PHO at 2023-04-23T13:39:32-04:00 Implement executablePath for Solaris and make getBaseDir less platform-dependent Use base-4.17 executablePath when possible, and fall back on getExecutablePath when it's not available. The sole reason why getBaseDir had #ifdef's was apparently that getExecutablePath wasn't reliable, and we could reduce the number of CPP conditionals by making use of executablePath instead. Also export executablePath on js_HOST_ARCH. - - - - - 97a6f7bc by tocic at 2023-04-23T13:40:08-04:00 Fix doc typos in libraries/base - - - - - ffcdd683 by Finley McIlwaine at 2023-04-24T09:36:18-06:00 Remove index-state - - - - - 787c6e8c by Ben Gamari at 2023-04-24T12:19:06-04:00 testsuite/T20137: Avoid impl.-defined behavior Previously we would cast pointers to uint64_t. However, implementations are allowed to either zero- or sign-extend such casts. Instead cast to uintptr_t to avoid this. Fixes #23247. - - - - - 87095f6a by Cheng Shao at 2023-04-24T12:19:44-04:00 rts: always build 64-bit atomic ops This patch does a few things: - Always build 64-bit atomic ops in rts/ghc-prim, even on 32-bit platforms - Remove legacy "64bit" cabal flag of rts package - Fix hs_xchg64 function prototype for 32-bit platforms - Fix AtomicFetch test for wasm32 - - - - - 2685a12d by Cheng Shao at 2023-04-24T12:20:21-04:00 compiler: don't install signal handlers when the host platform doesn't have signals Previously, large parts of GHC API will transitively invoke withSignalHandlers, which doesn't work on host platforms without signal functionality at all (e.g. wasm32-wasi). By making withSignalHandlers a no-op on those platforms, we can make more parts of GHC API work out of the box when signals aren't supported. - - - - - 1338b7a3 by Cheng Shao at 2023-04-24T16:21:30-04:00 hadrian: fix non-ghc program paths passed to testsuite driver when testing cross GHC - - - - - 1a10f556 by Andrew Lelechenko at 2023-04-24T16:22:09-04:00 Add since pragma to Data.Functor.unzip - - - - - 0da9e882 by Soham Chowdhury at 2023-04-25T00:15:22-04:00 More informative errors for bad imports (#21826) - - - - - ebd5b078 by Josh Meredith at 2023-04-25T00:15:58-04:00 JS/base: provide implementation for mkdir (issue 22374) - - - - - 8f656188 by Josh Meredith at 2023-04-25T18:12:38-04:00 JS: Fix h$base_access implementation (issue 22576) - - - - - 74c55712 by Andrei Borzenkov at 2023-04-25T18:13:19-04:00 Give more guarntees about ImplicitParams (#23289) - Added new section in the GHC user's guide that legends behavior of nested implicit parameter bindings in these two cases: let ?f = 1 in let ?f = 2 in ?f and data T where MkT :: (?f :: Int) => T f :: T -> T -> Int f MkT MkT = ?f - Added new test case to examine this behavior. - - - - - 05b70982 by Finley McIlwaine at 2023-04-26T08:16:31-06:00 `renameInterface` space leak fixes - Change logic for accumulation of names for which link warnings will be generated - Change handling of `--ignore-link-symbol` to allow qualified and unqualified names. Added to CHANGES.md - Some formatting changes and comments here and there - - - - - c30ac25f by Sebastian Graf at 2023-04-26T14:50:51-04:00 DmdAnal: Unleash demand signatures of free RULE and unfolding binders (#23208) In #23208 we observed that the demand signature of a binder occuring in a RULE wasn't unleashed, leading to a transitively used binder being discarded as absent. The solution was to use the same code path that we already use for handling exported bindings. See the changes to `Note [Absence analysis for stable unfoldings and RULES]` for more details. I took the chance to factor out the old notion of a `PlusDmdArg` (a pair of a `VarEnv Demand` and a `Divergence`) into `DmdEnv`, which fits nicely into our existing framework. As a result, I had to touch quite a few places in the code. This refactoring exposed a few small bugs around correct handling of bottoming demand environments. As a result, some strictness signatures now mention uniques that weren't there before which caused test output changes to T13143, T19969 and T22112. But these tests compared whole -ddump-simpl listings which is a very fragile thing to begin with. I changed what exactly they test for based on the symptoms in the corresponding issues. There is a single regression in T18894 because we are more conservative around stable unfoldings now. Unfortunately it is not easily fixed; let's wait until there is a concrete motivation before invest more time. Fixes #23208. - - - - - 77f506b8 by Josh Meredith at 2023-04-26T14:51:28-04:00 Refactor GenStgRhs to include the Type in both constructors (#23280, #22576, #22364) Carry the actual type of an expression through the PreStgRhs and into GenStgRhs for use in later stages. Currently this is used in the JavaScript backend to fix some tests from the above mentioned issues: EtaExpandLevPoly, RepPolyWrappedVar2, T13822, T14749. - - - - - 052e2bb6 by Alan Zimmerman at 2023-04-26T14:52:05-04:00 EPA: Use ExplicitBraces only in HsModule !9018 brought in exact print annotations in LayoutInfo for open and close braces at the top level. But it retained them in the HsModule annotations too. Remove the originals, so exact printing uses LayoutInfo - - - - - d5c4629b by Cheng Shao at 2023-04-27T16:00:35-04:00 ci: update ci.sh to actually run the entire testsuite for wasm backend For the time being, we still need to use in-tree mode and can't test the bindist yet. - - - - - 533d075e by Cheng Shao at 2023-04-27T16:00:35-04:00 ci: additional wasm32 manual jobs in validate pipelines This patch enables bignum native & unregisterised wasm32 jobs as manual jobs in validate pipelines, which can be useful to prevent breakage when working on wasm32 related patches. - - - - - b5f00811 by Cheng Shao at 2023-04-27T16:00:35-04:00 testsuite: fix cross prefix stripping This patch fixes cross prefix stripping in the testsuite driver. The normalization logic used to only handle prefixes of the triple form <arch>-<vendor>-<os>, now it's relaxed to allow any number of tokens in the prefix tuple, so the cross prefix stripping logic would work when ghc is configured with something like --target=wasm32-wasi. - - - - - 6f511c36 by Cheng Shao at 2023-04-27T16:00:35-04:00 testsuite: include target exe extension in heap profile filenames This patch fixes hp2ps related framework failures when testing the wasm backend by including target exe extension in heap profile filenames. - - - - - e6416b10 by Cheng Shao at 2023-04-27T16:00:35-04:00 testsuite: exclude ghci ways if no rts linker is present This patch implements logic to automatically exclude ghci ways when there is no rts linker. It's way better than having to annotate individual test cases. - - - - - 791cce64 by Cheng Shao at 2023-04-27T16:00:35-04:00 testsuite: fix permission bits in copy_files When the testsuite driver copy files instead of symlinking them, it should also copy the permission bits, otherwise there'll be permission denied errors. Also, enforce file copying when testing wasm32, since wasmtime doesn't handle host symlinks quite well (https://github.com/bytecodealliance/wasmtime/issues/6227). - - - - - aa6afe8a by Cheng Shao at 2023-04-27T16:00:35-04:00 testsuite: add the req_ghc_with_threaded_rts predicate This patch adds the req_ghc_with_threaded_rts predicate to the testsuite to assert the platform has threaded RTS, and mark some tests as req_ghc_with_threaded_rts. Also makes ghc_with_threaded_rts a config field instead of a global variable. - - - - - ce580426 by Cheng Shao at 2023-04-27T16:00:35-04:00 testsuite: add the req_process predicate This patch adds the req_process predicate to the testsuite to assert the platform has a process model, also marking tests that involve spawning processes as req_process. Also bumps hpc & process submodule. - - - - - cb933665 by Cheng Shao at 2023-04-27T16:00:35-04:00 testsuite: add the req_host_target_ghc predicate This patch adds the req_host_target_ghc predicate to the testsuite to assert the ghc compiler being tested can compile both host/target code. When testing cross GHCs this is not supported yet, but it may change in the future. - - - - - b174a110 by Cheng Shao at 2023-04-27T16:00:35-04:00 testsuite: add missing annotations for some tests This patch adds missing annotations (req_th, req_dynamic_lib_support, req_rts_linker) to some tests. They were discovered when testing wasm32, though it's better to be explicit about what features they require, rather than simply adding when(arch('wasm32'), skip). - - - - - bd2bfdec by Cheng Shao at 2023-04-27T16:00:35-04:00 testsuite: wasm32-specific fixes This patch includes all wasm32-specific testsuite fixes. - - - - - 4eaf2c2a by Josh Meredith at 2023-04-27T16:01:11-04:00 JS: change GHC.JS.Transform.identsS/E/V to take a saturated IR (#23304) - - - - - e5697d7c by Finley McIlwaine at 2023-04-27T18:46:36-06:00 Messy things - ghc-debug dependency and instrumentation - cabal.project custom with-compiler - hie.yaml files - traces and such - - - - - 57277662 by sheaf at 2023-04-29T20:23:06+02:00 Add the Unsatisfiable class This commit implements GHC proposal #433, adding the Unsatisfiable class to the GHC.TypeError module. This provides an alternative to TypeError for which error reporting is more predictable: we report it when we are reporting unsolved Wanted constraints. Fixes #14983 #16249 #16906 #18310 #20835 - - - - - 00a8a5ff by Torsten Schmits at 2023-04-30T03:45:09-04:00 Add structured error messages for GHC.Rename.Names Tracking ticket: #20115 MR: !10336 This converts uses of `mkTcRnUnknownMessage` to newly added constructors of `TcRnMessage`. - - - - - 0b8ef80b by Finley McIlwaine at 2023-05-02T18:08:52-06:00 Stop retaining GRE closures GRE closures should never be necessary to Haddock, so we never want to keep them on the heap. Despite that, they are retained by a lot of the data structures that Haddock makes use of. - Attempt to fix that situation by adding strictness to various computations and pruning the `ifaceInstances` field of `Interface` to a much thinner data type. - Removes the `ifaceFamInstances` field, as it was never used. - Move some of the attach instances types (e.g. `SimpleType`) to the types module - - - - - 931c8d82 by Ben Orchard at 2023-05-03T20:16:18-04:00 Add sized primitive literal syntax Adds a new LANGUAGE pragma ExtendedLiterals, which enables defining unboxed numeric literals such as `0xFF#Word8 :: Word8#`. Implements GHC proposal 0451: https://github.com/ghc-proposals/ghc-proposals/blob/b384a538b34f79d18a0201455b7b3c473bc8c936/proposals/0451-sized-literals.rst Fixes #21422. Bumps haddock submodule. Co-authored-by: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> - - - - - f3460845 by Andrew Lelechenko at 2023-05-03T20:16:57-04:00 Document instances of Double - - - - - 1e9caa1a by Sylvain Henry at 2023-05-03T20:17:37-04:00 Bump Cabal submodule (#22356) - - - - - 4eafb52a by sheaf at 2023-05-03T20:18:16-04:00 Don't forget to check the parent in an export list Commit 3f374399 introduced a bug which caused us to forget to include the parent of an export item of the form T(..) (that is, IEThingAll) when checking for duplicate exports. Fixes #23318 - - - - - 8fde4ac8 by amesgen at 2023-05-03T20:18:57-04:00 Fix unlit path in cross bindists - - - - - 8cc9a534 by Matthew Pickering at 2023-05-04T14:58:14-04:00 hadrian: Flavour: Change args -> extraArgs Previously in a flavour definition you could override all the flags which were passed to GHC. This causes issues when needed to compute a package hash because we need to know what these extra arguments are going to be before computing the hash. The solution is to modify flavour so that the arguments you pass here are just extra ones rather than all the arguments that you need to compile something. This makes things work more like how cabal.project files work when you give extra arguments to a package and also means that flavour transformers correctly affect the hash. - - - - - 3fdb18f8 by romes at 2023-05-04T14:58:14-04:00 Hardwire a better unit-id for ghc Previously, the unit-id of ghc-the-library was fixed as `ghc`. This was done primarily because the compiler must know the unit-id of some packages (including ghc) a-priori to define wired-in names. However, as seen in #20742, a reinstallable `ghc` whose unit-id is fixed to `ghc` might result in subtle bugs when different ghc's interact. A good example of this is having GHC_A load a plugin compiled by GHC_B, where GHC_A and GHC_B are linked to ghc-libraries that are ABI incompatible. Without a distinction between the unit-id of the ghc library GHC_A is linked against and the ghc library the plugin it is loading was compiled against, we can't check compatibility. This patch gives a slightly better unit-id to ghc (ghc-version) by (1) Not setting -this-unit-id to ghc, but rather to the new unit-id (modulo stage0) (2) Adding a definition to `GHC.Settings.Config` whose value is the new unit-id. (2.1) `GHC.Settings.Config` is generated by Hadrian (2.2) and also by cabal through `compiler/Setup.hs` This unit-id definition is imported by `GHC.Unit.Types` and used to set the wired-in unit-id of "ghc", which was previously fixed to "ghc" The commits following this one will improve the unit-id with a cabal-style package hash and check compatibility when loading plugins. Note that we also ensure that ghc's unit key matches unit id both when hadrian or cabal builds ghc, and in this way we no longer need to add `ghc` to the WiringMap. - - - - - 6689c9c6 by romes at 2023-05-04T14:58:14-04:00 Validate compatibility of ghcs when loading plugins Ensure, when loading plugins, that the ghc the plugin depends on is the ghc loading the plugin -- otherwise fail to load the plugin. Progress towards #20742. - - - - - db4be339 by romes at 2023-05-04T14:58:14-04:00 Add hashes to unit-ids created by hadrian This commit adds support for computing an inputs hash for packages compiled by hadrian. The result is that ABI incompatible packages should be given different hashes and therefore be distinct in a cabal store. Hashing is enabled by the `--flag`, and is off by default as the hash contains a hash of the source files. We enable it when we produce release builds so that the artifacts we distribute have the right unit ids. - - - - - 944a9b94 by Matthew Pickering at 2023-05-04T14:58:14-04:00 Use hash-unit-ids in release jobs Includes fix upload_ghc_libs glob - - - - - 116d7312 by Josh Meredith at 2023-05-04T14:58:51-04:00 JS: fix bounds checking (Issue 23123) * For ByteArray-based bounds-checking, the JavaScript backend must use the `len` field, instead of the inbuild JavaScript `length` field. * Range-based operations must also check both the start and end of the range for bounds * All indicies are valid for ranges of size zero, since they are essentially no-ops * For cases of ByteArray accesses (e.g. read as Int), the end index is (i * sizeof(type) + sizeof(type) - 1), while the previous implementation uses (i + sizeof(type) - 1). In the Int32 example, this is (i * 4 + 3) * IndexByteArrayOp_Word8As* primitives use byte array indicies (unlike the previous point), but now check both start and end indicies * Byte array copies now check if the arrays are the same by identity and then if the ranges overlap. - - - - - 2d5c1dde by Sylvain Henry at 2023-05-04T14:58:51-04:00 Fix remaining issues with bound checking (#23123) While fixing these I've also changed the way we store addresses into ByteArray#. Addr# are composed of two parts: a JavaScript array and an offset (32-bit number). Suppose we want to store an Addr# in a ByteArray# foo at offset i. Before this patch, we were storing both fields as a tuple in the "arr" array field: foo.arr[i] = [addr_arr, addr_offset]; Now we only store the array part in the "arr" field and the offset directly in the array: foo.dv.setInt32(i, addr_offset): foo.arr[i] = addr_arr; It avoids wasting space for the tuple. - - - - - 98c5ee45 by Luite Stegeman at 2023-05-04T14:59:31-04:00 JavaScript: Correct arguments to h$appendToHsStringA fixes #23278 - - - - - ca611447 by Josh Meredith at 2023-05-04T15:00:07-04:00 base/encoding: add an allocations performance test (#22946) - - - - - e3ddf58d by Krzysztof Gogolewski at 2023-05-04T15:00:44-04:00 linear types: Don't add external names to the usage env This has no observable effect, but avoids storing useless data. - - - - - b3226616 by Andrei Borzenkov at 2023-05-04T15:01:25-04:00 Improved documentation for the Data.OldList.nub function There was recomentation to use map head . group . sort instead of nub function, but containers library has more suitable and efficient analogue - - - - - e8b72ff6 by Ryan Scott at 2023-05-04T15:02:02-04:00 Fix type variable substitution in gen_Newtype_fam_insts Previously, `gen_Newtype_fam_insts` was substituting the type variable binders of a type family instance using `substTyVars`, which failed to take type variable dependencies into account. There is similar code in `GHC.Tc.TyCl.Class.tcATDefault` that _does_ perform this substitution properly, so this patch: 1. Factors out this code into a top-level `substATBndrs` function, and 2. Uses `substATBndrs` in `gen_Newtype_fam_insts`. Fixes #23329. - - - - - 275836d2 by Torsten Schmits at 2023-05-05T08:43:02+00:00 Add structured error messages for GHC.Rename.Utils Tracking ticket: #20115 MR: !10350 This converts uses of `mkTcRnUnknownMessage` to newly added constructors of `TcRnMessage`. - - - - - 983ce558 by Oleg Grenrus at 2023-05-05T13:11:29-04:00 Use TemplateHaskellQuotes in TH.Syntax to construct Names - - - - - a5174a59 by Matthew Pickering at 2023-05-05T18:42:31-04:00 driver: Use hooks from plugin_hsc_env This fixes a bug in oneshot mode where hooks modified in a plugin wouldn't be used in oneshot mode because we neglected to use the right hsc_env. This was observed by @csabahruska. - - - - - 18a7d03d by Aaron Allen at 2023-05-05T18:42:31-04:00 Rework plugin initialisation points In general this patch pushes plugin initialisation points to earlier in the pipeline. As plugins can modify the `HscEnv`, it's imperative that the plugins are initialised as soon as possible and used thereafter. For example, there are some new tests which modify hsc_logger and other hooks which failed to fire before (and now do) One consequence of this change is that the error for specifying the usage of a HPT plugin from the command line has changed, because it's now attempted to be loaded at initialisation rather than causing a cyclic module import. Closes #21279 Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 6e776ed3 by Matthew Pickering at 2023-05-05T18:42:31-04:00 docs: Add Note [Timing of plugin initialization] - - - - - e1df8511 by Matthew Pickering at 2023-05-05T18:43:07-04:00 Incrementally update ghcup metadata in ghc/ghcup-metadata This job paves the way for distributing nightly builds * A new repo https://gitlab.haskell.org/ghc/ghcup-metadata stores the metadata on the "updates" branch. * Each night this metadata is downloaded and the nightly builds are appended to the end of the metadata. * The update job only runs on the scheduled nightly pipeline, not just when NIGHTLY=1. Things which are not done yet * Modify the retention policy for nightly jobs * Think about building release flavour compilers to distribute nightly. Fixes #23334 - - - - - 8f303d27 by Rodrigo Mesquita at 2023-05-05T22:04:31-04:00 docs: Remove mentions of ArrayArray# from unlifted FFI section Fixes #23277 - - - - - 994bda56 by Torsten Schmits at 2023-05-05T22:05:12-04:00 Add structured error messages for GHC.Rename.Module Tracking ticket: #20115 MR: !10361 This converts uses of `mkTcRnUnknownMessage` to newly added constructors of `TcRnMessage`. Only addresses the single warning missing from the previous MR. - - - - - 3e3a6be4 by Ben Gamari at 2023-05-08T12:15:19+00:00 rts: Fix data-race in hs_init_ghc As noticed by @Terrorjack, `hs_init_ghc` previously used non-atomic increment/decrement on the RTS's initialization count. This may go wrong in a multithreaded program which initializes the runtime multiple times. Closes #22756. - - - - - 8bda991b by Finley McIlwaine at 2023-05-08T16:07:51-06:00 Memory usage fixes - Refactor `ifaceDeclMap` to drastically reduce memory footprint. We no longer store all declarations associated with a given name, since we only cared to determine if the only declaration associated with a name was a value declaration. Change the `DeclMap` type to better reflect this. - Drop pre-renaming export items after the renaming step. Since the Hoogle backend used the pre-renamed export items, this isn't trivial. We now generate Hoogle output for exported declarations during the renaming step (if Hoogle output /should/ be generated), and store that with the renamed export item. - Slightly refactor Hoogle backend to handle the above change and allow for early generation of Hoogle output. - Remove the `ifaceRnDocMap` and `ifaceRnArgMap` fields of the `Interface` type, as they were never used. - Remove some unnecessary strictness - Remove a lot of dead code from `Syb` module - - - - - 78c8dc50 by Torsten Schmits at 2023-05-08T21:41:51-04:00 Add structured error messages for GHC.IfaceToCore Tracking ticket: #20114 MR: !10390 This converts uses of `mkTcRnUnknownMessage` to newly added constructors of `TcRnMessage`. - - - - - 0e2df4c9 by Bryan Richter at 2023-05-09T12:03:35+03:00 Fix up rules for ghcup-metadata-nightly-push - - - - - b970e64f by Ben Gamari at 2023-05-09T08:41:33-04:00 testsuite: Add test for atomicSwapIORef - - - - - 81cfefd2 by Ben Gamari at 2023-05-09T08:41:53-04:00 compiler: Implement atomicSwapIORef with xchg As requested by @treeowl in CLC#139. - - - - - 6b29154d by Ben Gamari at 2023-05-09T08:41:53-04:00 Make atomicSwapMutVar# an inline primop - - - - - 1611ac0c by Finley McIlwaine at 2023-05-09T11:51:57-06:00 Unify ErrMsgM and IfM - Delete ErrMsgM, stop accumulating warnings in a writer - Make IfM a state monad, print warnings directly to stdout, move IfM type into types module - Drop ErrMsg = String synonym - Unset IORefs from plugin after they are read, preventing unnecessary retention of interfaces - - - - - 64064cfe by doyougnu at 2023-05-09T18:40:01-04:00 JS: add GHC.JS.Optimizer, remove RTS.Printer, add Linker.Opt This MR changes some simple optimizations and is a first step in re-architecting the JS backend pipeline to add the optimizer. In particular it: - removes simple peep hole optimizations from `GHC.StgToJS.Printer` and removes that module - adds module `GHC.JS.Optimizer` - defines the same peep hole opts that were removed only now they are `Syntax -> Syntax` transformations rather than `Syntax -> JS code` optimizations - hooks the optimizer into code gen - adds FuncStat and ForStat constructors to the backend. Working Ticket: - #22736 Related MRs: - MR !10142 - MR !10000 ------------------------- Metric Decrease: CoOpt_Read ManyAlternatives PmSeriesS PmSeriesT PmSeriesV T10421 T12707 T13253 T13253-spj T15164 T17516 T18140 T18282 T18698a T18698b T18923 T1969 T19695 T20049 T3064 T5321FD T5321Fun T783 T9198 T9233 T9630 ------------------------- - - - - - 6738c01d by Krzysztof Gogolewski at 2023-05-09T18:40:38-04:00 Add a regression test for #21050 - - - - - b2cdb7da by Ben Gamari at 2023-05-09T18:41:14-04:00 nonmoving: Account for mutator allocations in bytes_allocated Previously we failed to account direct mutator allocations into the nonmoving heap against the mutator's allocation limit and `cap->total_allocated`. This only manifests during CAF evaluation (since we allocate the CAF's blackhole directly into the nonmoving heap). Fixes #23312. - - - - - 0657b482 by Sven Tennie at 2023-05-09T22:22:42-04:00 Adjust AArch64 stackFrameHeaderSize The prologue of each stack frame are the saved LR and FP registers, 8 byte each. I.e. the size of the stack frame header is 2 * 8 byte. - - - - - 7788c09c by konsumlamm at 2023-05-09T22:23:23-04:00 Make `(&)` representation polymorphic in the return type - - - - - b3195922 by Ben Gamari at 2023-05-10T05:06:45-04:00 ghc-prim: Generalize keepAlive#/touch# in state token type Closes #23163. - - - - - 1e6861dd by Cheng Shao at 2023-05-10T05:07:25-04:00 Bump hsc2hs submodule Fixes #22981. - - - - - 0a513952 by Ben Gamari at 2023-05-11T04:10:17-04:00 base: Export GHC.Conc.Sync.fromThreadId Closes #22706. - - - - - 29be39ba by Matthew Pickering at 2023-05-11T04:10:54-04:00 Build vanilla alpine bindists We currently attempt to build and distribute fully static alpine bindists (ones which could be used on any linux platform) but most people who use the alpine bindists want to use alpine to build their own static applications (for which a fully static bindist is not necessary). We should build and distribute these bindists for these users whilst the fully-static bindist is still unusable. Fixes #23349 - - - - - 40c7daed by Simon Peyton Jones at 2023-05-11T04:11:30-04:00 Look both ways when looking for quantified equalities When looking up (t1 ~# t2) in the quantified constraints, check both orientations. Forgetting this led to #23333. - - - - - c17bb82f by Rodrigo Mesquita at 2023-05-11T04:12:07-04:00 Move "target has RTS linker" out of settings We move the "target has RTS linker" information out of configure into a predicate in GHC, and remove this option from the settings file where it is unnecessary -- it's information statically known from the platform. Note that previously we would consider `powerpc`s and `s390x`s other than `powerpc-ibm-aix*` and `s390x-ibm-linux` to have an RTS linker, but the RTS linker supports neither platform. Closes #23361 - - - - - bd0b056e by Krzysztof Gogolewski at 2023-05-11T04:12:44-04:00 Add a test for #17284 Since !10123 we now reject this program. - - - - - 630b1fea by Andrew Lelechenko at 2023-05-11T04:13:24-04:00 Document unlawfulness of instance Num Fixed Fixes #22712 - - - - - 87eebf98 by sheaf at 2023-05-11T11:55:22-04:00 Add fused multiply-add instructions This patch adds eight new primops that fuse a multiplication and an addition or subtraction: - `{fmadd,fmsub,fnmadd,fnmsub}{Float,Double}#` fmadd x y z is x * y + z, computed with a single rounding step. This patch implements code generation for these primops in the following backends: - X86, AArch64 and PowerPC NCG, - LLVM - C WASM uses the C implementation. The primops are unsupported in the JavaScript backend. The following constant folding rules are also provided: - compute a * b + c when a, b, c are all literals, - x * y + 0 ==> x * y, - ±1 * y + z ==> z ± y and x * ±1 + z ==> z ± x. NB: the constant folding rules incorrectly handle signed zero. This is a known limitation with GHC's floating-point constant folding rules (#21227), which we hope to resolve in the future. - - - - - ad16a066 by Krzysztof Gogolewski at 2023-05-11T11:55:59-04:00 Add a test for #21278 - - - - - 05cea68c by Matthew Pickering at 2023-05-11T11:56:36-04:00 rts: Refine memory retention behaviour to account for pinned/compacted objects When using the copying collector there is still a lot of data which isn't copied (such as pinned, compacted, large objects etc). The logic to decide how much memory to retain didn't take into account that these wouldn't be copied. Therefore we pessimistically retained 2* the amount of memory for these blocks even though they wouldn't be copied by the collector. The solution is to split up the heap into two parts, the parts which will be copied and the parts which won't be copied. Then the appropiate factor is applied to each part individually (2 * for copying and 1.2 * for not copying). The T23221 test demonstrates this improvement with a program which first allocates many unpinned ByteArray# followed by many pinned ByteArray# and observes the difference in the ultimate memory baseline between the two. There are some charts on #23221. Fixes #23221 - - - - - 1bb24432 by Cheng Shao at 2023-05-11T11:57:15-04:00 hadrian: fix no_dynamic_libs flavour transformer This patch fixes the no_dynamic_libs flavour transformer and make fully_static reuse it. Previously building with no_dynamic_libs fails since ghc program is still dynamic and transitively brings in dyn ways of rts which are produced by no rules. - - - - - 42d696ab by Finley McIlwaine at 2023-05-11T15:52:07-06:00 Thunk leak fixes The strictness introduced in this commit was motivated by observing thunk leaks in the eventlog2html output. - Refactor attach instances list comprehension to avoid large intermediate thunks - Refactor some HTML backend list comprehensions to avoid large intermediate thunks - Avoid thunks accumulating in documentation types or documentation parser - A lot of orphan NFData instances to allow us to force documentation values - - - - - 68561cf6 by Finley McIlwaine at 2023-05-11T17:02:10-06:00 Remove GHC debug dep - - - - - 0ed493a3 by Josh Meredith at 2023-05-11T23:08:27-04:00 JS: refactor jsSaturate to return a saturated JStat (#23328) - - - - - a856d98e by Pierre Le Marre at 2023-05-11T23:09:08-04:00 Doc: Fix out-of-sync using-optimisation page - Make explicit that default flag values correspond to their -O0 value. - Fix -fignore-interface-pragmas, -fstg-cse, -fdo-eta-reduction, -fcross-module-specialise, -fsolve-constant-dicts, -fworker-wrapper. - - - - - c176ad18 by sheaf at 2023-05-12T06:10:57-04:00 Don't panic in mkNewTyConRhs This function could come across invalid newtype constructors, as we only perform validity checking of newtypes once we are outside the knot-tied typechecking loop. This patch changes this function to fake up a stub type in the case of an invalid newtype, instead of panicking. This patch also changes "checkNewDataCon" so that it reports as many errors as possible at once. Fixes #23308 - - - - - ab63daac by Krzysztof Gogolewski at 2023-05-12T06:11:38-04:00 Allow Core optimizations when interpreting bytecode Tracking ticket: #23056 MR: !10399 This adds the flag `-funoptimized-core-for-interpreter`, permitting use of the `-O` flag to enable optimizations when compiling with the interpreter backend, like in ghci. - - - - - c6cf9433 by Ben Gamari at 2023-05-12T06:12:14-04:00 hadrian: Fix mention of non-existent removeFiles function Previously Hadrian's bindist Makefile referred to a `removeFiles` function that was previously defined by the `make` build system. Since the `make` build system is no longer around, this function is now undefined. Naturally, make being make, this appears to be silently ignored instead of producing an error. Fix this by rewriting it to `rm -f`. Closes #23373. - - - - - eb60ec18 by Andrew Lelechenko at 2023-05-12T06:12:54-04:00 Mention new implementation of GHC.IORef.atomicSwapIORef in the changelog - - - - - aa84cff4 by Teo Camarasu at 2023-05-12T19:27:23-04:00 rts: Ensure non-moving gc is not running when pausing - - - - - 5ad776ab by Teo Camarasu at 2023-05-12T19:27:23-04:00 rts: Teach listAllBlocks about nonmoving heap List all blocks on the non-moving heap. Resolves #22627 - - - - - d683b2e5 by Krzysztof Gogolewski at 2023-05-12T19:28:00-04:00 Fix coercion optimisation for SelCo (#23362) setNominalRole_maybe is supposed to output a nominal coercion. In the SelCo case, it was not updating the stored role to Nominal, causing #23362. - - - - - 59aa4676 by Alexis King at 2023-05-12T19:28:47-04:00 hadrian: Fix linker script flag for MergeObjects builder This fixes what appears to have been a typo in !9530. The `-t` flag just enables tracing on all versions of `ld` I’ve looked at, while `-T` is used to specify a linker script. It seems that this worked anyway for some reason on some `ld` implementations (perhaps because they automatically detect linker scripts), but the missing `-T` argument causes `gold` to complain. - - - - - 4bf9fa0f by Adam Gundry at 2023-05-12T23:49:49-04:00 Less coercion optimization for non-newtype axioms See Note [Push transitivity inside newtype axioms only] for an explanation of the change here. This change substantially improves the performance of coercion optimization for programs involving transitive type family reductions. ------------------------- Metric Decrease: CoOpt_Singletons LargeRecord T12227 T12545 T13386 T15703 T5030 T8095 ------------------------- - - - - - dc0c9574 by Adam Gundry at 2023-05-12T23:49:49-04:00 Move checkAxInstCo to GHC.Core.Lint A consequence of the previous change is that checkAxInstCo is no longer called during coercion optimization, so it can be moved back where it belongs. Also includes some edits to Note [Conflict checking with AxiomInstCo] as suggested by @simonpj. - - - - - 8b9b7dbc by Simon Peyton Jones at 2023-05-12T23:50:25-04:00 Use the eager unifier in the constraint solver This patch continues the refactoring of the constraint solver described in #23070. The Big Deal in this patch is to call the regular, eager unifier from the constraint solver, when we want to create new equalities. This replaces the existing, unifyWanted which amounted to yet-another-unifier, so it reduces duplication of a rather subtle piece of technology. See * Note [The eager unifier] in GHC.Tc.Utils.Unify * GHC.Tc.Solver.Monad.wrapUnifierTcS I did lots of other refactoring along the way * I simplified the treatment of right hand sides that contain CoercionHoles. Now, a constraint that contains a hetero-kind CoercionHole is non-canonical, and cannot be used for rewriting or unification alike. This required me to add the ch_hertero_kind flag to CoercionHole, with consequent knock-on effects. See wrinkle (2) of `Note [Equalities with incompatible kinds]` in GHC.Tc.Solver.Equality. * I refactored the StopOrContinue type to add StartAgain, so that after a fundep improvement (for example) we can simply start the pipeline again. * I got rid of the unpleasant (and inefficient) rewriterSetFromType/Co functions. With Richard I concluded that they are never needed. * I discovered Wrinkle (W1) in Note [Wanteds rewrite Wanteds] in GHC.Tc.Types.Constraint, and therefore now prioritise non-rewritten equalities. Quite a few error messages change, I think always for the better. Compiler runtime stays about the same, with one outlier: a 17% improvement in T17836 Metric Decrease: T17836 T18223 - - - - - 5cad28e7 by Bartłomiej Cieślar at 2023-05-12T23:51:06-04:00 Cleanup of dynflags override in export renaming The deprecation warnings are normally emitted whenever the name's GRE is being looked up, which calls the GHC.Rename.Env.addUsedGRE function. We do not want those warnings to be emitted when renaming export lists, so they are artificially turned off by removing all warning categories from DynFlags at the beginning of GHC.Tc.Gen.Export.rnExports. This commit removes that dependency by unifying the function used for GRE lookup in lookup_ie to lookupGreAvailRn and disabling the call to addUsedGRE in said function (the warnings are also disabled in a call to lookupSubBndrOcc_helper in lookupChildrenExport), as per #17957. This commit also changes the setting for whether to warn about deprecated names in addUsedGREs to be an explicit enum instead of a boolean. - - - - - d85ed900 by Alexis King at 2023-05-13T08:45:18-04:00 Use a uniform return convention in bytecode for unary results fixes #22958 - - - - - 8a0d45f7 by Andrew Lelechenko at 2023-05-13T08:45:58-04:00 Add more instances for Compose: Enum, Bounded, Num, Real, Integral See https://github.com/haskell/core-libraries-committee/issues/160 for discussion - - - - - 902f0730 by Simon Peyton Jones at 2023-05-13T14:58:34-04:00 Make GHC.Types.Id.Make.shouldUnpackTy a bit more clever As #23307, GHC.Types.Id.Make.shouldUnpackTy was leaving money on the table, failing to unpack arguments that are perfectly unpackable. The fix is pretty easy; see Note [Recursive unboxing] - - - - - a5451438 by sheaf at 2023-05-13T14:59:13-04:00 Fix bad multiplicity role in tyConAppFunCo_maybe The function tyConAppFunCo_maybe produces a multiplicity coercion for the multiplicity argument of the function arrow, except that it could be at the wrong role if asked to produce a representational coercion. We fix this by using the 'funRole' function, which computes the right roles for arguments to the function arrow TyCon. Fixes #23386 - - - - - 5b9e9300 by sheaf at 2023-05-15T11:26:59-04:00 Turn "ambiguous import" error into a panic This error should never occur, as a lookup of a type or data constructor should never be ambiguous. This is because a single module cannot export multiple Names with the same OccName, as per item (1) of Note [Exporting duplicate declarations] in GHC.Tc.Gen.Export. This code path was intended to handle duplicate record fields, but the rest of the code had since been refactored to handle those in a different way. We also remove the AmbiguousImport constructor of IELookupError, as it is no longer used. Fixes #23302 - - - - - e305e60c by M Farkas-Dyck at 2023-05-15T11:27:41-04:00 Unbreak some tests with latest GNU grep, which now warns about stray '\'. Confusingly, the testsuite mangled the error to say "stray /". We also migrate some tests from grep to grep -E, as it seems the author actually wanted an "POSIX extended" (a.k.a. sane) regex. Background: POSIX specifies 2 "regex" syntaxen: "basic" and "extended". Of these, only "extended" syntax is actually a regular expression. Furthermore, "basic" syntax is inconsistent in its use of the '\' character — sometimes it escapes a regex metacharacter, but sometimes it unescapes it, i.e. it makes an otherwise normal character become a metacharacter. This baffles me and it seems also the authors of these tests. Also, the regex(7) man page (at least on Linux) says "basic" syntax is obsolete. Nearly all modern tools and libraries are consistent in this use of the '\' character (of which many use "extended" syntax by default). - - - - - 10519e3d by Finley McIlwaine at 2023-05-15T12:40:48-06:00 Force HIE file path Removes a potential retainer of `ModSummary`s - - - - - 5ae81842 by sheaf at 2023-05-15T14:49:17-04:00 Improve "ambiguous occurrence" error messages This error was sometimes a bit confusing, especially when data families were involved. This commit improves the general presentation of the "ambiguous occurrence" error, and adds a bit of extra context in the case of data families. Fixes #23301 - - - - - 2f571afe by Sylvain Henry at 2023-05-15T14:50:07-04:00 Fix GHCJS OS platform (fix #23346) - - - - - 86aae570 by Oleg Grenrus at 2023-05-15T14:50:43-04:00 Split DynFlags structure into own module This will allow to make command line parsing to depend on diagnostic system (which depends on dynflags) - - - - - 1e4a6ec6 by Finley McIlwaine at 2023-05-15T14:20:34-06:00 Re-add index-state, with-compiler, delete hie.yamls - - - - - a2363fe9 by Hécate Moonlight at 2023-05-15T22:45:16+02:00 Merge pull request haskell/haddock#1594 from FinleyMcIlwaine/finley/ghc-9.6-mem-fixes Reduce memory usage - - - - - fbe3fe00 by Josh Meredith at 2023-05-15T18:01:43-04:00 Replace the implementation of CodeBuffers with unboxed types - - - - - 21f3aae7 by Josh Meredith at 2023-05-15T18:01:43-04:00 Use unboxed codebuffers in base Metric Decrease: encodingAllocations - - - - - 18ea2295 by Ben Gamari at 2023-05-15T18:02:20-04:00 rts: Weak pointer cleanups Various stylistic cleanups. No functional changes. - - - - - c343112f by Ben Gamari at 2023-05-15T18:02:20-04:00 rts: Don't force debug output to stderr Previously `+RTS -Dw -l` would emit debug output to the eventlog while `+RTS -l -Dw` would emit it to stderr. This was because the parser for `-D` would unconditionally override the debug output target. Now we instead only do so if no it is currently `TRACE_NONE`. - - - - - a5f5f067 by Ben Gamari at 2023-05-15T18:02:20-04:00 rts: Forcibly flush eventlog on barf Previously we would attempt to flush via `endEventLogging` which can easily deadlock, e.g., if `barf` fails during GC. Using `flushEventLog` directly may result in slightly less consistent eventlog output (since we don't take all capabilities before flushing) but avoids deadlocking. - - - - - 73b1e87c by Ben Gamari at 2023-05-15T18:02:20-04:00 rts: Assert that pointers aren't cleared by -DZ This turns many segmentation faults into much easier-to-debug assertion failures by ensuring that LOOKS_LIKE_*_PTR checks recognize bit-patterns produced by `+RTS -DZ` clearing as invalid pointers. This is a bit ad-hoc but this is the debug runtime. - - - - - 37fb61d8 by Ben Gamari at 2023-05-15T18:02:20-04:00 rts: Introduce printGlobalThreads - - - - - 451d65a6 by Ben Gamari at 2023-05-15T18:02:20-04:00 rts: Don't sanity-check StgTSO.global_link See Note [Avoid dangling global_link pointers]. Fixes #19146. - - - - - d69cbd78 by sheaf at 2023-05-15T18:03:00-04:00 Split up tyThingToIfaceDecl from GHC.Iface.Make This commit moves tyThingToIfaceDecl and coAxiomToIfaceDecl from GHC.Iface.Make into GHC.Iface.Decl. This avoids GHC.Types.TyThing.Ppr, which needs tyThingToIfaceDecl, transitively depending on e.g. GHC.Iface.Load and GHC.Tc.Utils.Monad. - - - - - 4d29ecdf by sheaf at 2023-05-15T18:03:00-04:00 Migrate errors to diagnostics in GHC.Tc.Module This commit migrates the errors in GHC.Tc.Module to use the new diagnostic infrastructure. It required a significant overhaul of the compatibility checks between an hs-boot or signature module and its implementation; we now use a Writer monad to accumulate errors; see the BootMismatch datatype in GHC.Tc.Errors.Types, with its panoply of subtypes. For the sake of readability, several local functions inside the 'checkBootTyCon' function were split off into top-level functions. We split off GHC.Types.HscSource into a "boot or sig" vs "normal hs file" datatype, as this mirrors the logic in several other places where we want to treat hs-boot and hsig files in a similar fashion. This commit also refactors the Backpack checks for type synonyms implementing abstract data, to correctly reject implementations that contain qualified or quantified types (this fixes #23342 and #23344). - - - - - d986c98e by Rodrigo Mesquita at 2023-05-16T00:14:04-04:00 configure: Drop unused AC_PROG_CPP In configure, we were calling `AC_PROG_CPP` but never making use of the $CPP variable it sets or reads. The issue is $CPP will show up in the --help output of configure, falsely advertising a configuration option that does nothing. The reason we don't use the $CPP variable is because HS_CPP_CMD is expected to be a single command (without flags), but AC_PROG_CPP, when CPP is unset, will set said variable to something like `/usr/bin/gcc -E`. Instead, we configure HS_CPP_CMD through $CC. - - - - - a8f0435f by Cheng Shao at 2023-05-16T00:14:42-04:00 rts: fix --disable-large-address-space This patch moves ACQUIRE_ALLOC_BLOCK_SPIN_LOCK/RELEASE_ALLOC_BLOCK_SPIN_LOCK from Storage.h to HeapAlloc.h. When --disable-large-address-space is passed to configure, the code in HeapAlloc.h makes use of these two macros. Fixes #23385. - - - - - bdb93cd2 by Oleg Grenrus at 2023-05-16T07:59:21+03:00 Add -Wmissing-role-annotations Implements #22702 - - - - - 41ecfc34 by Ben Gamari at 2023-05-16T07:28:15-04:00 base: Export {get,set}ExceptionFinalizer from System.Mem.Weak As proposed in CLC Proposal #126 [1]. [1]: https://github.com/haskell/core-libraries-committee/issues/126 - - - - - 67330303 by Ben Gamari at 2023-05-16T07:28:16-04:00 base: Introduce printToHandleFinalizerExceptionHandler - - - - - 5e3f9bb5 by Josh Meredith at 2023-05-16T13:59:22-04:00 JS: Implement h$clock_gettime in the JavaScript RTS (#23360) - - - - - 90e69d5d by Zubin Duggal at 2023-05-16T14:00:00-04:00 compiler: Use compact representation for SourceText SourceText is serialized along with INLINE pragmas into interface files. Many of these SourceTexts are identical, for example "{-# INLINE#". When deserialized, each such SourceText was previously expanded out into a [Char], which is highly wasteful of memory, and each such instance of the text would allocate an independent list with its contents as deserializing breaks any sharing that might have existed. Instead, we use a `FastString` to represent these, so that each instance unique text will be interned and stored in a memory efficient manner. - - - - - b70bc690 by Zubin Duggal at 2023-05-16T14:00:00-04:00 compiler: Use compact representation/FastStrings for `SourceNote`s `SourceNote`s should not be stored as [Char] as this is highly wasteful and in certain scenarios can be highly duplicated. Metric Decrease: hard_hole_fits - - - - - 6231a126 by Zubin Duggal at 2023-05-16T14:00:00-04:00 compiler: Use compact representation for UsageFile (#22744) Use FastString to store filepaths in interface files, as this data is highly redundant so we want to share all instances of filepaths in the compiler session. - - - - - 47a58150 by Zubin Duggal at 2023-05-16T14:00:00-04:00 testsuite: add test for T22744 This test checks for #22744 by compiling 100 modules which each have a dependency on 1000 distinct external files. Previously, when loading these interfaces from disk, each individual instance of a filepath in the interface will would be allocated as an individual object on the heap, meaning we have heap objects for 100*1000 files, when there are only 1000 distinct files we care about. This test checks this by first compiling the module normally, then measuring the peak memory usage in a no-op recompile, as the recompilation checking will force the allocation of all these filepaths. - - - - - 0451bdc9 by Ben Gamari at 2023-05-16T21:31:40-04:00 users guide: Add glossary Currently this merely explains the meaning of "technology preview" in the context of released features. - - - - - 0ba52e4e by Ben Gamari at 2023-05-16T21:31:40-04:00 Update glossary.rst - - - - - 3d23060c by Ben Gamari at 2023-05-16T21:31:40-04:00 Use glossary directive - - - - - 2972fd66 by Sylvain Henry at 2023-05-16T21:32:20-04:00 JS: fix getpid (fix #23399) - - - - - e8a78383 by Finley McIlwaine at 2023-05-17T12:19:16-06:00 Merge branch ghc-9.6 into ghc-head - - - - - 22e25581 by Finley McIlwaine at 2023-05-17T12:20:23-06:00 Merge branch 'ghc-head' of gitlab.haskell.org:ghc/haddock into ghc-head - - - - - 5fe1d3e6 by Matthew Pickering at 2023-05-17T21:42:00-04:00 Use setSrcSpan rather than setLclEnv in solveForAll In subsequent MRs (#23409) we want to remove the TcLclEnv argument from a CtLoc. This MR prepares us for that by removing the one place where the entire TcLclEnv is used, by using it more precisely to just set the contexts source location. Fixes #23390 - - - - - 385edb65 by Torsten Schmits at 2023-05-17T21:42:40-04:00 Update the users guide paragraph on -O in GHCi In relation to #23056 - - - - - 87626ef0 by Ben Gamari at 2023-05-18T15:18:53-04:00 base: Add test for #13660 - - - - - 9eef53b1 by Ben Gamari at 2023-05-18T15:18:53-04:00 base: Move implementation of GHC.Foreign to GHC.Internal - - - - - 174ea2fa by Ben Gamari at 2023-05-18T15:18:53-04:00 base: Introduce {new,with}CStringLen0 These are useful helpers for implementing the internal-NUL code unit check needed to fix #13660. - - - - - a46ced16 by Ben Gamari at 2023-05-18T15:18:53-04:00 base: Clean up documentation - - - - - b98d99cc by Ben Gamari at 2023-05-18T15:18:53-04:00 base: Ensure that FilePaths don't contain NULs POSIX filepaths may not contain the NUL octet but previously we did not reject such paths. This could be exploited by untrusted input to cause discrepancies between various `FilePath` queries and the opened filename. For instance, `readFile "hello.so\x00.txt"` would open the file `"hello.so"` yet `takeFileExtension` would return `".txt"`. The same argument applies to Windows FilePaths Fixes #13660. - - - - - 7ae45459 by Simon Peyton Jones at 2023-05-18T15:19:29-04:00 Allow the demand analyser to unpack tuple and equality dictionaries Addresses #23398. The demand analyser usually does not unpack class dictionaries: see Note [Do not unbox class dictionaries] in GHC.Core.Opt.DmdAnal. This patch makes an exception for tuple dictionaries and equality dictionaries, for reasons explained in wrinkles (DNB1) and (DNB2) of the above Note. Compile times fall by 0.1% for some reason (max 0.7% on T18698b). - - - - - b53a9086 by Greg Steuck at 2023-05-18T15:20:08-04:00 Use a simpler and more portable construct in ld.ldd check printf '%q\n' is a bash extension which led to incorrectly failing an ld.lld test on OpenBSD which uses pdksh as /bin/sh - - - - - dd5710af by Torsten Schmits at 2023-05-18T15:20:50-04:00 Update the warning about interpreter optimizations to reflect that they're not incompatible anymore, but guarded by a flag - - - - - 4f6dd999 by Matthew Pickering at 2023-05-18T15:21:26-04:00 Remove stray dump flags in GHC.Rename.Names - - - - - 4bca0486 by Oleg Grenrus at 2023-05-19T11:51:33+03:00 Make Warn = Located DriverMessage This change makes command line argument parsing use diagnostic framework for producing warnings. - - - - - 525ed554 by Simon Peyton Jones at 2023-05-19T10:09:15-04:00 Type inference for data family newtype instances This patch addresses #23408, a tricky case with data family newtype instances. Consider type family TF a where TF Char = Bool data family DF a newtype instance DF Bool = MkDF Int and [W] Int ~R# DF (TF a), with a Given (a ~# Char). We must fully rewrite the Wanted so the tpye family can fire; that wasn't happening. - - - - - c6fb6690 by Peter Trommler at 2023-05-20T03:16:08-04:00 testsuite: fix predicate on rdynamic test Test rdynamic requires dynamic linking support, which is orthogonal to RTS linker support. Change the predicate accordingly. Fixes #23316 - - - - - 735d504e by Matthew Pickering at 2023-05-20T03:16:44-04:00 docs: Use ghc-ticket directive where appropiate in users guide Using the directive automatically formats and links the ticket appropiately. - - - - - b56d7379 by Sylvain Henry at 2023-05-22T14:21:22-04:00 NCG: remove useless .align directive (#20758) - - - - - 15b93d2f by Simon Peyton Jones at 2023-05-22T14:21:58-04:00 Add test for #23156 This program had exponential typechecking time in GHC 9.4 and 9.6 - - - - - 2b53f206 by Greg Steuck at 2023-05-22T20:23:11-04:00 Revert "Change hostSupportsRPaths to report False on OpenBSD" This reverts commit 1e0d8fdb55a38ece34fa6cf214e1d2d46f5f5bf2. - - - - - 882e43b7 by Greg Steuck at 2023-05-22T20:23:11-04:00 Disable T17414 on OpenBSD Like on other systems it's not guaranteed that there's sufficient space in /tmp to write 2G out. - - - - - 9d531f9a by Greg Steuck at 2023-05-22T20:23:11-04:00 Bring back getExecutablePath to getBaseDir on OpenBSD Fix #18173 - - - - - 9db0eadd by Krzysztof Gogolewski at 2023-05-22T20:23:47-04:00 Add an error origin for impedance matching (#23427) - - - - - 33cf4659 by Ben Gamari at 2023-05-23T03:46:20-04:00 testsuite: Add tests for #23146 Both lifted and unlifted variants. - - - - - 76727617 by Ben Gamari at 2023-05-23T03:46:21-04:00 codeGen: Fix some Haddocks - - - - - 33a8c348 by Ben Gamari at 2023-05-23T03:46:21-04:00 codeGen: Give proper LFInfo to datacon wrappers As noted in `Note [Conveying CAF-info and LFInfo between modules]`, when importing a binding from another module we must ensure that it gets the appropriate `LambdaFormInfo` if it is in WHNF to ensure that references to it are tagged correctly. However, the implementation responsible for doing this, `GHC.StgToCmm.Closure.mkLFImported`, only dealt with datacon workers and not wrappers. This lead to the crash of this program in #23146: module B where type NP :: [UnliftedType] -> UnliftedType data NP xs where UNil :: NP '[] module A where import B fieldsSam :: NP xs -> NP xs -> Bool fieldsSam UNil UNil = True x = fieldsSam UNil UNil Due to its GADT nature, `UNil` produces a trivial wrapper $WUNil :: NP '[] $WUNil = UNil @'[] @~(<co:1>) which is referenced in the RHS of `A.x`. Due to the above-mentioned bug in `mkLFImported`, the references to `$WUNil` passed to `fieldsSam` were not tagged. This is problematic as `fieldsSam` expected its arguments to be tagged as they are unlifted. The fix is straightforward: extend the logic in `mkLFImported` to cover (nullary) datacon wrappers as well as workers. This is safe because we know that the wrapper of a nullary datacon will be in WHNF, even if it includes equalities evidence (since such equalities are not runtime relevant). Thanks to @MangoIV for the great ticket and @alt-romes for his minimization and help debugging. Fixes #23146. - - - - - 2fc18e9e by Rodrigo Mesquita at 2023-05-23T03:46:21-04:00 codeGen: Fix LFInfo of imported datacon wrappers As noted in #23231 and in the previous commit, we were failing to give a an LFInfo of LFCon to a nullary datacon wrapper from another module, failing to properly tag pointers which ultimately led to the segmentation fault in #23146. On top of the previous commit which now considers wrappers where we previously only considered workers, we change the order of the guards so that we check for the arity of the binding before we check whether it is a constructor. This allows us to (1) Correctly assign `LFReEntrant` to imported wrappers whose worker was nullary, which we previously would fail to do (2) Remove the `isNullaryRepDataCon` predicate: (a) which was previously wrong, since it considered wrappers whose workers had zero-width arguments to be non-nullary and would fail to give `LFCon` to them (b) is now unnecessary, since arity == 0 guarantees - that the worker takes no arguments at all - and the wrapper takes no arguments and its RHS must be an application of the worker to zero-width-args only. - we lint these two items with an assertion that the datacon `hasNoNonZeroWidthArgs` We also update `isTagged` to use the new logic in determining the LFInfos of imported Ids. The creation of LFInfos for imported Ids and this detail are explained in Note [The LFInfo of Imported Ids]. Note that before the patch to those issues we would already consider these nullary wrappers to have `LFCon` lambda form info; but failed to re-construct that information in `mkLFImported` Closes #23231, #23146 (I've additionally batched some fixes to documentation I found while investigating this issue) - - - - - 0598f7f0 by Rodrigo Mesquita at 2023-05-23T03:46:21-04:00 Make LFInfos for DataCons on construction As a result of the discussion in !10165, we decided to amend the previous commit which fixed the logic of `mkLFImported` with regard to datacon workers and wrappers. Instead of having the logic for the LFInfo of datacons be in `mkLFImported`, we now construct an LFInfo for all data constructors on GHC.Types.Id.Make and store it in the `lfInfo` field. See the new Note [LFInfo of DataCon workers and wrappers] and ammendments to Note [The LFInfo of Imported Ids] - - - - - 12294b22 by Rodrigo Mesquita at 2023-05-23T03:46:21-04:00 Update Note [Core letrec invariant] Authored by @simonpj - - - - - e93ab972 by Rodrigo Mesquita at 2023-05-23T03:46:21-04:00 Rename mkLFImported to importedIdLFInfo The `mkLFImported` sounded too much like a constructor of sorts, when really it got the `LFInfo` of an imported Id from its `lf_info` field when this existed, and otherwise returned a conservative estimate of that imported Id's LFInfo. This in contrast to functions such as `mkLFReEntrant` which really are about constructing an `LFInfo`. - - - - - e54d9259 by Rodrigo Mesquita at 2023-05-23T03:46:21-04:00 Enforce invariant on typePrimRepArgs in the types As part of the documentation effort in !10165 I came across this invariant on 'typePrimRepArgs' which is easily expressed at the type-level through a NonEmpty list. It allowed us to remove one panic. - - - - - b8fe6a0c by Rodrigo Mesquita at 2023-05-23T03:46:21-04:00 Merge outdated Note [Data con representation] into Note [Data constructor representation] Introduce new Note [Constructor applications in STG] to better support the merge, and reference it from the relevant bits in the STG syntax. - - - - - e1590ddc by Simon Peyton Jones at 2023-05-23T03:46:57-04:00 Add the SolverStage monad This refactoring makes a substantial improvement in the structure of the type-checker's constraint solver: #23070. Specifically: * Introduced the SolverStage monad. See GHC.Tc.Solver.Monad Note [The SolverStage monad] * Make each solver pipeline (equalities, dictionaries, irreds etc) deal with updating the inert set, as a separate SolverStage. There is sometimes special stuff to do, and it means that each full pipeline can have type SolverStage Void, indicating that they never return anything. * Made GHC.Tc.Solver.Equality.zonkEqTypes into a SolverStage. Much nicer. * Combined the remnants of GHC.Tc.Solver.Canonical and GHC.Tc.Solver.Interact into a new module GHC.Tc.Solver.Solve. (Interact and Canonical are removed.) * Gave the same treatment to dictionary and irred constraints as I have already done for equality constraints: * New types (akin to EqCt): IrredCt and DictCt * Ct is now just a simple sum type data Ct = CDictCan DictCt | CIrredCan IrredCt | CEqCan EqCt | CQuantCan QCInst | CNonCanonical CtEvidence * inert_dicts can now have the better type DictMap DictCt, instead of DictMap Ct; and similarly inert_irreds. * Significantly simplified the treatment of implicit parameters. Previously we had a number of special cases * interactGivenIP, an entire function * special case in maybeKickOut * special case in findDict, when looking up dictionaries But actually it's simpler than that. When adding a new Given, implicit parameter constraint to the InertSet, we just need to kick out any existing inert constraints that mention that implicit parameter. The main work is done in GHC.Tc.Solver.InertSet.delIPDict, along with its auxiliary GHC.Core.Predicate.mentionsIP. See Note [Shadowing of implicit parameters] in GHC.Tc.Solver.Dict. * Add a new fast-path in GHC.Tc.Errors.Hole.tcCheckHoleFit. See Note [Fast path for tcCheckHoleFit]. This is a big win in some cases: test hard_hole_fits gets nearly 40% faster (at compile time). * Add a new fast-path for solving /boxed/ equality constraints (t1 ~ t2). See Note [Solving equality classes] in GHC.Tc.Solver.Dict. This makes a big difference too: test T17836 compiles 40% faster. * Implement the PermissivePlan of #23413, which concerns what happens with insoluble Givens. Our previous treatment was wildly inconsistent as that ticket pointed out. A part of this, I simplified GHC.Tc.Validity.checkAmbiguity: now we simply don't run the ambiguity check at all if -XAllowAmbiguousTypes is on. Smaller points: * In `GHC.Tc.Errors.misMatchOrCND` instead of having a special case for insoluble /occurs/ checks, broaden in to all insouluble constraints. Just generally better. See Note [Insoluble mis-match] in that module. As noted above, compile time perf gets better. Here are the changes over 0.5% on Fedora. (The figures are slightly larger on Windows for some reason.) Metrics: compile_time/bytes allocated ------------------------------------- LargeRecord(normal) -0.9% MultiLayerModulesTH_OneShot(normal) +0.5% T11822(normal) -0.6% T12227(normal) -1.8% GOOD T12545(normal) -0.5% T13035(normal) -0.6% T15703(normal) -1.4% GOOD T16875(normal) -0.5% T17836(normal) -40.7% GOOD T17836b(normal) -12.3% GOOD T17977b(normal) -0.5% T5837(normal) -1.1% T8095(normal) -2.7% GOOD T9020(optasm) -1.1% hard_hole_fits(normal) -37.0% GOOD geo. mean -1.3% minimum -40.7% maximum +0.5% Metric Decrease: T12227 T15703 T17836 T17836b T8095 hard_hole_fits LargeRecord T9198 T13035 - - - - - 6abf3648 by Simon Peyton Jones at 2023-05-23T03:46:57-04:00 Avoid an assertion failure in abstractFloats The function GHC.Core.Opt.Simplify.Utils.abstractFloats was carelessly calling lookupIdSubst_maybe on a CoVar; but a precondition of the latter is being given an Id. In fact it's harmless to call it on a CoVar, but still, the precondition on lookupIdSubst_maybe makes sense, so I added a test for CoVars. This avoids a crash in a DEBUG compiler, but otherwise has no effect. Fixes #23426. - - - - - 41bbf0df by Bartłomiej Cieślar at 2023-05-24T08:57:58+02:00 changes to the WarningTxt cases Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - 838aaf4b by hainq at 2023-05-24T12:41:19-04:00 Migrate errors in GHC.Tc.Validity This patch migrates the error messages in GHC.Tc.Validity to use the new diagnostic infrastructure. It adds the constructors: - TcRnSimplifiableConstraint - TcRnArityMismatch - TcRnIllegalInstanceDecl, with sub-datatypes for HasField errors and fundep coverage condition errors. - - - - - 8539764b by Krzysztof Gogolewski at 2023-05-24T12:41:56-04:00 linear lint: Add missing processing of DEFAULT In this correct program f :: a %1 -> a f x = case x of x { _DEFAULT -> x } after checking the alternative we weren't popping the case binder 'x' from the usage environment, which meant that the lambda-bound 'x' was counted twice: in the scrutinee and (incorrectly) in the alternative. In fact, we weren't checking the usage of 'x' at all. Now the code for handling _DEFAULT is similar to the one handling data constructors. Fixes #23025. - - - - - ae683454 by Matthew Pickering at 2023-05-24T12:42:32-04:00 Remove outdated "Don't check hs-boot type family instances too early" note This note was introduced in 25b70a29f623 which delayed performing some consistency checks for type families. However, the change was reverted later in 6998772043a7f0b0360116eb5ffcbaa5630b21fb but the note was not removed. I found it confusing when reading to code to try and work out what special behaviour there was for hs-boot files (when in-fact there isn't any). - - - - - 44af57de by Matthew Pickering at 2023-05-24T12:43:08-04:00 rts: Define ticky macro stubs These macros have long been undefined which has meant we were missing reporting these allocations in ticky profiles. The most critical missing definition was TICK_ALLOC_HEAP_NOCTR which was missing all the RTS calls to allocate, this leads to a the overall ALLOC_RTS_tot number to be severaly underreported. Of particular interest though is the ALLOC_STACK_ctr and ALLOC_STACK_tot counters which are useful to tracking stack allocations. Fixes #23421 - - - - - b2dabe3a by Matthew Pickering at 2023-05-24T12:43:08-04:00 rts: ticky: Rename TICK_ALLOC_HEAP_NOCTR to TICK_ALLOC_RTS This macro increments the ALLOC_HEAP_tot and ALLOC_HEAP_ctr so it makes more sense to name it after that rather than the suffix NOCTR, whose meaning has been lost to the mists of time. - - - - - eac4420a by Ben Gamari at 2023-05-24T12:43:45-04:00 users guide: A few small mark-up fixes - - - - - a320ca76 by Rodrigo Mesquita at 2023-05-24T12:44:20-04:00 configure: Fix support check for response files. In failing to escape the '-o' in '-o\nconftest\nconftest.o\n' argument to printf, the writing of the arguments response file always failed. The fix is to pass the arguments after `--` so that they are treated positional arguments rather than flags to printf. Closes #23435 - - - - - f21ce0e4 by mangoiv at 2023-05-24T12:45:00-04:00 [feat] add .direnv to the .gitignore file - - - - - 36d5944d by Andrew Lelechenko at 2023-05-24T20:58:34-04:00 Add Data.List.unsnoc See https://github.com/haskell/core-libraries-committee/issues/165 for discussion - - - - - c0f2f9e3 by Bartłomiej Cieślar at 2023-05-24T20:59:14-04:00 Fix crash in backpack signature merging with -ddump-rn-trace In some cases, backpack signature merging could crash in addUsedGRE when -ddump-rn-trace was enabled, as pretty-printing the GREInfo would cause unavailable interfaces to be loaded. This commit fixes that issue by not pretty-printing the GREInfo in addUsedGRE when -ddump-rn-trace is enabled. Fixes #23424 Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - 5a07d94a by Krzysztof Gogolewski at 2023-05-25T03:30:20-04:00 Add a regression test for #13981 The panic was fixed by 6998772043a7f0b. Fixes #13981. - - - - - 182df90e by Krzysztof Gogolewski at 2023-05-25T03:30:57-04:00 Add a test for #23355 It was fixed by !10061, so I'm adding it in the same group. - - - - - 1b31b039 by uhbif19 at 2023-05-25T12:08:28+02:00 Migrate errors in GHC.Rename.Splice GHC.Rename.Pat This commit migrates the errors in GHC.Rename.Splice and GHC.Rename.Pat to use the new diagnostic infrastructure. - - - - - 56abe494 by sheaf at 2023-05-25T12:09:55+02:00 Common up Template Haskell errors in TcRnMessage This commit commons up the various Template Haskell errors into a single constructor, TcRnTHError, of TcRnMessage. - - - - - a487ba9e by Krzysztof Gogolewski at 2023-05-25T14:35:56-04:00 Enable ghci tests for unboxed tuples The tests were originally skipped because ghci used not to support unboxed tuples/sums. - - - - - dc3422d4 by Matthew Pickering at 2023-05-25T18:57:19-04:00 rts: Build ticky GHC with single-threaded RTS The threaded RTS allows you to use ticky profiling but only for the counters in the generated code. The counters used in the C portion of the RTS are disabled. Updating the counters is also racy using the threaded RTS which can lead to misleading or incorrect ticky results. Therefore we change the hadrian flavour to build using the single-threaded RTS (mainly in order to get accurate C code counter increments) Fixes #23430 - - - - - fbc8e04e by sheaf at 2023-05-25T18:58:00-04:00 Propagate long-distance info in generated code When desugaring generated pattern matches, we skip pattern match checks. However, this ended up also discarding long-distance information, which might be needed for user-written sub-expressions. Example: ```haskell okay (GADT di) cd = let sr_field :: () sr_field = case getFooBar di of { Foo -> () } in case cd of { SomeRec _ -> SomeRec sr_field } ``` With sr_field a generated FunBind, we still want to propagate the outer long-distance information from the GADT pattern match into the checks for the user-written RHS of sr_field. Fixes #23445 - - - - - f8ced241 by Matthew Pickering at 2023-05-26T15:26:21-04:00 Introduce GHCiMessage to wrap GhcMessage By introducing a wrapped message type we can control how certain messages are printed in GHCi (to add extra information for example) - - - - - 58e554c1 by Matthew Pickering at 2023-05-26T15:26:22-04:00 Generalise UnknownDiagnostic to allow embedded diagnostics to access parent diagnostic options. * Split default diagnostic options from Diagnostic class into HasDefaultDiagnosticOpts class. * Generalise UnknownDiagnostic to allow embedded diagnostics to access options. The principle idea here is that when wrapping an error message (such as GHCMessage to make GHCiMessage) then we need to also be able to lift the configuration when overriding how messages are printed (see load' for an example). - - - - - b112546a by Matthew Pickering at 2023-05-26T15:26:22-04:00 Allow API users to wrap error messages created during 'load' This allows API users to configure how messages are rendered when they are emitted from the load function. For an example see how 'loadWithCache' is used in GHCi. - - - - - 2e4cf0ee by Matthew Pickering at 2023-05-26T15:26:22-04:00 Abstract cantFindError and turn Opt_BuildingCabal into a print-time option * cantFindError is abstracted so that the parts which mention specific things about ghc/ghci are parameters. The intention being that GHC/GHCi can specify the right values to put here but otherwise display the same error message. * The BuildingCabalPackage argument from GenericMissing is removed and turned into a print-time option. The reason for the error is not dependent on whether `-fbuilding-cabal-package` is passed, so we don't want to store that in the error message. - - - - - 34b44f7d by Matthew Pickering at 2023-05-26T15:26:22-04:00 error messages: Don't display ghci specific hints for missing packages Tickets like #22884 suggest that it is confusing that GHC used on the command line can suggest options which only work in GHCi. This ticket uses the error message infrastructure to override certain error messages which displayed GHCi specific information so that this information is only showed when using GHCi. The main annoyance is that we mostly want to display errors in the same way as before, but with some additional information. This means that the error rendering code has to be exported from the Iface/Errors/Ppr.hs module. I am unsure about whether the approach taken here is the best or most maintainable solution. Fixes #22884 - - - - - 05a1b626 by Matthew Pickering at 2023-05-26T15:26:58-04:00 ghcup-metadata: Don't override existing metadata if version already exists. If a nightly pipeline runs twice for some reason for the same version then we really don't want to override an existing entry with new bindists. This could cause ABI compatability issues for users or break ghcup's caching logic. - - - - - fcbcb3cc by Matthew Pickering at 2023-05-26T15:26:58-04:00 ghcup-metadata: Use proper API url for bindist download Previously we were using links from the web interface, but it's more robust and future-proof to use the documented links to the artifacts. https://docs.gitlab.com/ee/api/job_artifacts.html - - - - - 5b59c8fe by Matthew Pickering at 2023-05-26T15:26:58-04:00 ghcup-metadata: Set Nightly and LatestNightly tags The latest nightly release needs the LatestNightly tag, and all other nightly releases need the Nightly tag. Therefore when the metadata is updated we need to replace all LatestNightly with Nightly.` - - - - - 914e1468 by Matthew Pickering at 2023-05-26T15:26:58-04:00 ghcup-metadata: Download nightly metadata for correct date The metadata now lives in https://gitlab.haskell.org/ghc/ghcup-metadata with one metadata file per year. When we update the metadata we download and update the right file for the current year. - - - - - 16cf7d2e by Matthew Pickering at 2023-05-26T15:26:58-04:00 ghcup-metadata: Download metadata and update for correct year something about pipeline date - - - - - 14792c4b by Matthew Pickering at 2023-05-26T15:26:58-04:00 ghcup-metadata: Don't skip CI On a push we now have a CI job which updates gitlab pages with the metadata files. - - - - - 1121bdd8 by Matthew Pickering at 2023-05-26T15:26:59-04:00 ghcup-metadata: Add --date flag to specify the release date The ghcup-metadata now has a viReleaseDay field which needs to be populated with the day of the release. - - - - - bc478bee by Matthew Pickering at 2023-05-26T15:26:59-04:00 ghcup-metadata: Add dlOutput field ghcup now requires us to add this field which specifies where it should download the bindist to. See https://gitlab.haskell.org/ghc/ghcup-metadata/-/issues/1 for some more discussion. - - - - - 2bdbd9da by Josh Meredith at 2023-05-26T15:27:35-04:00 JS: Convert rendering to use HLine instead of SDoc (#22455) - - - - - abd9e37c by Norman Ramsey at 2023-05-26T15:28:12-04:00 testsuite: add WasmControlFlow test This patch adds the WasmControlFlow test to test the wasm backend's relooper component. - - - - - 07f858eb by Sylvain Henry at 2023-05-26T15:28:53-04:00 Factorize getLinkDeps Prepare reuse of getLinkDeps for TH implementation in the JS backend (cf #22261 and review of !9779). - - - - - fad9d092 by Oleg Grenrus at 2023-05-27T13:38:08-04:00 Change GHC.Driver.Session import to .DynFlags Also move targetPlatform selector Plenty of GHC needs just DynFlags. Even more can be made to use .DynFlags if more selectors is migrated. This is a low hanging fruit. - - - - - 69fdbece by Alan Zimmerman at 2023-05-27T13:38:45-04:00 EPA: Better fix for #22919 The original fix for #22919 simply removed the ability to match up prior comments with the first declaration in the file. Restore it, but add a check that the comment is on a single line, by ensuring that it comes immediately prior to the next thing (comment or start of declaration), and that the token preceding it is not on the same line. closes #22919 - - - - - 0350b186 by Josh Meredith at 2023-05-29T12:46:27+00:00 Remove JavaScriptFFI from --supported-extensions for non-JS targets (#11214) - - - - - b4816919 by Matthew Pickering at 2023-05-30T17:07:43-04:00 testsuite: Pass -kb16k -kc128k for performance tests Setting a larger stack chunk size gives a greater protection from stack thrashing (where the repeated overflow/underflow allocates a lot of stack chunks which sigificantly impact allocations). This stabilises some tests against differences cause by more things being pushed onto the stack. The performance tests are generally testing work done by the compiler, using allocation as a proxy, so removing/stabilising the allocations due to the stack gives us more stable tests which are also more sensitive to actual changes in compiler performance. The tests which increase are ones where we compile a lot of modules, and for each module we spawn a thread to compile the module in. Therefore increasing these numbers has a multiplying effect on these tests because there are many more stacks which we can increase in size. The most significant improvements though are cases such as T8095 which reduce significantly in allocations (30%). This isn't a performance improvement really but just helps stabilise the test against this threshold set by the defaults. Fixes #23439 ------------------------- Metric Decrease: InstanceMatching T14683 T8095 T9872b_defer T9872d T9961 hie002 T19695 T3064 Metric Increase: MultiLayerModules T13701 T14697 ------------------------- - - - - - 6629f1c5 by Ben Gamari at 2023-05-30T17:08:20-04:00 Move via-C flags into GHC These were previously hardcoded in configure (with no option for overriding them) and simply passed onto ghc through the settings file. Since configure already guarantees gcc supports those flags, we simply move them into GHC. - - - - - 981e5e11 by Arnaud Spiwack at 2023-05-31T08:34:33-04:00 Allow CPR on unrestricted constructors Per the new `Note [Linting linearity]`, we want optimisations over trying to preserve linearity. This will allow CPR to handle `Ur`, in particular. - - - - - bf9344d2 by Arnaud Spiwack at 2023-05-31T08:34:33-04:00 Push coercions across multiplicity boundaries Per the new `Note [Linting linearity]`, we want optimisations over trying to preserve linearity. This will avoid preventing inlinings and reductions and make linear programs more efficient. - - - - - d56dd695 by sheaf at 2023-05-31T11:37:12-04:00 Data.Bag: add INLINEABLE to polymorphic functions This commit allows polymorphic methods in GHC.Data.Bag to be specialised, avoiding having to pass explicit dictionaries when they are instantiated with e.g. a known monad. - - - - - 5366cd35 by sheaf at 2023-05-31T11:37:12-04:00 Split off TcBinderStack into its own module This commit splits off TcBinderStack into its own module, to avoid module cycles: we might want to refer to it without also pulling in the TcM monad. - - - - - 09d4d307 by sheaf at 2023-05-31T11:37:12-04:00 Split off TcRef into its own module This helps avoid pull in the full TcM monad when we just want access to mutable references in the typechecker. This facilitates later patches which introduce a slimmed down TcM monad for zonking. - - - - - 88cc19b3 by sheaf at 2023-05-31T11:37:12-04:00 Introduce Codensity monad The Codensity monad is useful to write state-passing computations in continuation-passing style, e.g. to implement a State monad as continuation-passing style over a Reader monad. - - - - - f62d8195 by sheaf at 2023-05-31T11:37:12-04:00 Restructure the zonker This commit splits up the zonker into a few separate components, described in Note [The structure of the zonker] in `GHC.Tc.Zonk.Type`. 1. `GHC.Tc.Zonk.Monad` introduces a pared-down `TcM` monad, `ZonkM`, which has enough information for zonking types. This allows us to refactor `ErrCtxt` to use `ZonkM` instead of `TcM`, which guarantees we don't throw an error while reporting an error. 2. `GHC.Tc.Zonk.Env` is the new home of `ZonkEnv`, and also defines two zonking monad transformers, `ZonkT` and `ZonkBndrT`. `ZonkT` is a reader monad transformer over `ZonkEnv`. `ZonkBndrT m` is the codensity monad over `ZonkT m`. `ZonkBndrT` is used for computations that accumulate binders in the `ZonkEnv`. 3. `GHC.Tc.Zonk.TcType` contains the code for zonking types, for use in the typechecker. It uses the `ZonkM` monad. 4. `GHC.Tc.Zonk.Type` contains the code for final zonking to `Type`, which has been refactored to use `ZonkTcM = ZonkT TcM` and `ZonkBndrTcM = ZonkBndrT TcM`. Allocations slightly decrease on the whole due to using continuation-passing style instead of manual state passing of ZonkEnv in the final zonking to Type. ------------------------- Metric Decrease: T4029 T8095 T14766 T15304 hard_hole_fits RecordUpdPerf Metric Increase: T10421 ------------------------- - - - - - 70526f5b by mimi.vx at 2023-05-31T11:37:53-04:00 Update rdt-theme to latest upstream version Fixes https://gitlab.haskell.org/ghc/ghc/-/issues/23444 - - - - - f3556d6c by Finley McIlwaine at 2023-06-01T04:53:12-04:00 Restructure IPE buffer layout Reference ticket #21766 This commit restructures IPE buffer list entries to not contain references to their corresponding info tables. IPE buffer list nodes now point to two lists of equal length, one holding the list of info table pointers and one holding the corresponding entries for each info table. This will allow the entry data to be compressed without losing the references to the info tables. - - - - - 5d1f2411 by Finley McIlwaine at 2023-06-01T04:53:12-04:00 Add IPE compression to configure Reference ticket #21766 Adds an `--enable-ipe-data-compreesion` flag to the configure script which will check for libzstd and set the appropriate flags to allow for IPE data compression in the compiler - - - - - b7a640ac by Finley McIlwaine at 2023-06-01T04:53:12-04:00 IPE data compression Reference ticket #21766 When IPE data compression is enabled, compress the emitted IPE buffer entries and decompress them in the RTS. - - - - - 5aef5658 by Finley McIlwaine at 2023-06-01T04:53:12-04:00 Fix libzstd detection in configure and RTS Ensure that `HAVE_LIBZSTD` gets defined to either 0 or 1 in all cases and properly check that before IPE data decompression in the RTS. See ticket #21766. - - - - - 69563c97 by Finley McIlwaine at 2023-06-01T04:53:12-04:00 Add note describing IPE data compression See ticket #21766 - - - - - 7872e2b6 by Finley McIlwaine at 2023-06-01T04:53:12-04:00 Fix byte order of IPE data, fix IPE tests Make sure byte order of written IPE buffer entries matches target. Make sure the IPE-related tests properly access the fields of IPE buffer entry nodes with the new IPE layout. This commit also introduces checks to avoid importing modules if IPE compression is not enabled. See ticket #21766. - - - - - 0e85099b by Finley McIlwaine at 2023-06-01T04:53:12-04:00 Fix IPE data decompression buffer allocation Capacity of buffers allocated for decompressed IPE data was incorrect due to a misuse of the `ZSTD_findFrameCompressedSize` function. Fix by always storing decompressed size of IPE data in IPE buffer list nodes and using `ZSTD_findFrameCompressedSize` to determine the size of the compressed data. See ticket #21766 - - - - - a0048866 by Finley McIlwaine at 2023-06-01T04:53:12-04:00 Add optional dependencies to ./configure output Changes the configure script to indicate whether libnuma, libzstd, or libdw are being used as dependencies due to their optional features being enabled. - - - - - 09d93bd0 by Finley McIlwaine at 2023-06-01T04:53:12-04:00 Add IPE-enabled builds to CI - Adds an IPE job to the CI pipeline which is triggered by the ~IPE label - Introduces CI logic to enable IPE data compression - Enables uncompressed IPE data on debug CI job - Regenerates jobs.yaml MR https://gitlab.haskell.org/ghc/ci-images/-/merge_requests/112 on the images repository is meant to ensure that the proper images have libzstd-dev installed. - - - - - 3ded9a1c by Finley McIlwaine at 2023-06-01T04:53:12-04:00 Update user's guide and release notes, small fixes Add mention of IPE data compression to user's guide and the release notes for 9.8.1. Also note the impact compression has on binary size in both places. Change IpeBufferListNode compression check so only the value `1` indicates compression. See ticket #21766 - - - - - 41b41577 by Finley McIlwaine at 2023-06-01T04:53:12-04:00 Remove IPE enabled builds from CI We don't need to explicitly specify the +ipe transformer to test IPE data since there are tests which manually enable IPE information. This commit does leave zstd IPE data compression enabled on the debian CI jobs. - - - - - 982bef3a by Krzysztof Gogolewski at 2023-06-01T04:53:49-04:00 Fix build with 9.2 GHC.Tc.Zonk.Type uses an equality constraint. ghc.nix currently provides 9.2. - - - - - 1c96bc3d by Krzysztof Gogolewski at 2023-06-01T10:56:11-04:00 Output Lint errors to stderr instead of stdout This is a continuation of 7b095b99, which fixed warnings but not errors. Refs #13342 - - - - - 8e81f140 by sheaf at 2023-06-01T10:56:51-04:00 Refactor lookupExactOrOrig & friends This refactors the panoply of renamer lookup functions relating to lookupExactOrOrig to more graciously handle Exact and Orig names. In particular, we avoid the situation in which we would add Exact/Orig GREs to the tcg_used_gres field, which could cause a panic in bestImport like in #23240. Fixes #23428 - - - - - 5d415bfd by Krzysztof Gogolewski at 2023-06-01T10:57:31-04:00 Use the one-shot trick for UM and RewriteM functors As described in Note [The one-shot state monad trick], we shouldn't use derived Functor instances for monads using one-shot. This was done for most of them, but UM and RewriteM were missed. - - - - - 2c38551e by Krzysztof Gogolewski at 2023-06-01T10:58:08-04:00 Fix testsuite skipping Lint setTestOpts() is used to modify the test options for an entire .T file, rather than a single test. If there was a test using collect_compiler_stats, all of the tests in the same file had lint disabled. Fixes #21247 - - - - - 00a1e50b by Krzysztof Gogolewski at 2023-06-01T10:58:44-04:00 Add testcases for already fixed #16432 They were fixed by 40c7daed0. Fixes #16432 - - - - - c686ba9b by Hécate Moonlight at 2023-06-01T14:03:02-06:00 Port the remains of Hi-Haddock - - - - - 9d8a85fd by Hécate Moonlight at 2023-06-01T14:03:06-06:00 Stdout for tests - - - - - 36331d07 by Finley McIlwaine at 2023-06-01T14:06:02-06:00 Formatting, organize imports - - - - - a06059b1 by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix empty context confusion in Convert module - - - - - 379346ae by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix associated type families in Hoogle output - - - - - fc6ea7ed by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix test refs Accept several changes in Hoogle tests: Pretty printing logic no longer prints the `(Proxy (Proxy (...))` chain in Bug806 with parentheses. Since this test was only meant to verify that line breaks do not occur, accept the change. `tyThingToLHsDecl` is called for class and data declarations, which ends up "synifying" the type variables and giving unlifted types kind signatures. As a result, type variables of kind `Type -> Type` are now printed with kind signatures in Hoogle output. This could be changed by manually drop kind signatures from class variables in the Hoogle backend if the behavior is deemed unacceptable. Sometimes subordinate declarations are exported separate from their parent declarations (e.g. record selectors). In this case, a type signature is cobbled together for the export item in `extractDecl`. Since this type signature is very manually constructed, it may lack kind signatures of decls constructed from `tyThingToLHsDecl`. An example of this is the `type-sigs` Hoogle test. Change `*` to `Type` in Hoogle test refs. I don't think this will break Hoogle behavior, since it appears to not consider type signatures in search. I have not fully verified this. - - - - - e14b7e58 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix LaTeX backend test refs Changes to GHC pretty printing code have resulted in some differences to Haddock's LaTeX output. - Type variables are printed explicitly quantified in the LinearTypes test - Wildcard types in type family equations are now printed numbered, e.g. _1 _2, in the TypeFamilies3 test - Combined signatures in DefaultSignatures test are now documented as separate signatures - - - - - 41b5b296 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and test source updates - Stop using kind `*` in html test sources - Add TypeOperators where necessary to avoid warnings and future errors - Rename some test modules to match their module names - - - - - c640e2a2 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix missing deprecation warnings on record fields `lookupOccEnv` was used to resolve `OccNames` with warnings attached, but it doesn't look in the record field namespace. Thus, if a record field had a warning attached, it would not resolve and the warning map would not include it. This commit fixes by using `lookupOccEnv_WithFields` instead. - - - - - fad0c462 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and some comments - - - - - 751fd023 by Finley McIlwaine at 2023-06-01T14:11:41-06:00 Accept HTML test diffs All diffs now boil down to the expected differences resulting from declarations being reified from TyThings in hi-haddock. Surface syntax now has much less control over the syntax used in the documentation. - - - - - d835c845 by Finley McIlwaine at 2023-06-01T14:11:45-06:00 Adapt to new load' type - - - - - dcf776c4 by Finley McIlwaine at 2023-06-01T14:13:13-06:00 Update mkWarningMap and moduleWarning - - - - - 8e8432fd by Finley McIlwaine at 2023-06-01T14:28:54-06:00 Revert load' changes - - - - - aeb2982c by Finley McIlwaine at 2023-06-01T14:40:24-06:00 Accept change to Instances test in html-test Link to Data.Tuple instead of GHC.Tuple.Prim - - - - - 8adfdbac by Finley McIlwaine at 2023-06-01T15:53:17-06:00 Reset ghc dep to ^>= 9.6 - - - - - f6e060cc by Krzysztof Gogolewski at 2023-06-02T09:07:25-04:00 cleanup: Remove unused field from SelfBoot It is no longer needed since Note [Extra dependencies from .hs-boot files] was deleted in 6998772043. I've also added tildes to Note headers, otherwise they're not detected by the linter. - - - - - 82eacab6 by sheaf at 2023-06-02T09:08:01-04:00 Delete GHC.Tc.Utils.Zonk This module was split up into GHC.Tc.Zonk.Type and GHC.Tc.Zonk.TcType in commit f62d8195, but I forgot to delete the original module - - - - - 4a4eb761 by Ben Gamari at 2023-06-02T23:53:21-04:00 base: Add build-order import of GHC.Types in GHC.IO.Handle.Types For reasons similar to those described in Note [Depend on GHC.Num.Integer]. Fixes #23411. - - - - - f53ac0ae by Sylvain Henry at 2023-06-02T23:54:01-04:00 JS: fix and enhance non-minimized code generation (#22455) Flag -ddisable-js-minimizer was producing invalid code. Fix that and also a few other things to generate nicer JS code for debugging. The added test checks that we don't regress when using the flag. - - - - - f7744e8e by Andrey Mokhov at 2023-06-03T16:49:44-04:00 [hadrian] Fix multiline synopsis rendering - - - - - b2c745db by Andrew Lelechenko at 2023-06-03T16:50:23-04:00 Elaborate on performance properties of Data.List.++ - - - - - 7cd8a61e by Matthew Pickering at 2023-06-05T11:46:23+01:00 Big TcLclEnv and CtLoc refactoring The overall goal of this refactoring is to reduce the dependency footprint of the parser and syntax tree. Good reasons include: - Better module graph parallelisability - Make it easier to migrate error messages without introducing module loops - Philosophically, there's not reason for the AST to depend on half the compiler. One of the key edges which added this dependency was > GHC.Hs.Expr -> GHC.Tc.Types (TcLclEnv) As this in turn depending on TcM which depends on HscEnv and so on. Therefore the goal of this patch is to move `TcLclEnv` out of `GHC.Tc.Types` so that `GHC.Hs.Expr` can import TcLclEnv without incurring a huge dependency chain. The changes in this patch are: * Move TcLclEnv from GHC.Tc.Types to GHC.Tc.Types.LclEnv * Create new smaller modules for the types used in TcLclEnv New Modules: - GHC.Tc.Types.ErrCtxt - GHC.Tc.Types.BasicTypes - GHC.Tc.Types.TH - GHC.Tc.Types.LclEnv - GHC.Tc.Types.CtLocEnv - GHC.Tc.Errors.Types.PromotionErr Removed Boot File: - {-# SOURCE #-} GHC.Tc.Types * Introduce TcLclCtxt, the part of the TcLclEnv which doesn't participate in restoreLclEnv. * Replace TcLclEnv in CtLoc with specific CtLocEnv which is defined in GHC.Tc.Types.CtLocEnv. Use CtLocEnv in Implic and CtLoc to record the location of the implication and constraint. By splitting up TcLclEnv from GHC.Tc.Types we allow GHC.Hs.Expr to no longer depend on the TcM monad and all that entails. Fixes #23389 #23409 - - - - - 3d8d39d1 by Matthew Pickering at 2023-06-05T11:46:23+01:00 Remove dependency of GHC.Tc.Utils.TcType on GHC.Driver.Session This removes the usage of DynFlags from Tc.Utils.TcType so that it no longer depends on GHC.Driver.Session. In general we don't want anything which is a dependency of Language.Haskell.Syntax to depend on GHC.Driver.Session and removing this edge gets us closer to that goal. - - - - - 18db5ada by Matthew Pickering at 2023-06-05T11:46:23+01:00 Move isIrrefutableHsPat to GHC.Rename.Utils and rename to isIrrefutableHsPatRn This removes edge from GHC.Hs.Pat to GHC.Driver.Session, which makes Language.Haskell.Syntax end up depending on GHC.Driver.Session. - - - - - 12919dd5 by Matthew Pickering at 2023-06-05T11:46:23+01:00 Remove dependency of GHC.Tc.Types.Constraint on GHC.Driver.Session - - - - - eb852371 by Matthew Pickering at 2023-06-05T11:46:24+01:00 hole fit plugins: Split definition into own module The hole fit plugins are defined in terms of TcM, a type we want to avoid depending on from `GHC.Tc.Errors.Types`. By moving it into its own module we can remove this dependency. It also simplifies the necessary boot file. - - - - - 9e5246d7 by Matthew Pickering at 2023-06-05T11:46:24+01:00 Move GHC.Core.Opt.CallerCC Types into separate module This allows `GHC.Driver.DynFlags` to depend on these types without depending on CoreM and hence the entire simplifier pipeline. We can also remove a hs-boot file with this change. - - - - - 52d6a7d7 by Matthew Pickering at 2023-06-05T11:46:24+01:00 Remove unecessary SOURCE import - - - - - 698d160c by Matthew Pickering at 2023-06-05T11:46:24+01:00 testsuite: Accept new output for CountDepsAst and CountDepsParser tests These are in a separate commit as the improvement to these tests is the cumulative effect of the previous set of patches rather than just the responsibility of the last one in the patchset. - - - - - 58ccf02e by sheaf at 2023-06-05T16:00:47-04:00 TTG: only allow VarBind at GhcTc The VarBind constructor of HsBind is only used at the GhcTc stage. This commit makes that explicit by setting the extension field of VarBind to be DataConCantHappen at all other stages. This allows us to delete a dead code path in GHC.HsToCore.Quote.rep_bind, and remove some panics. - - - - - 2b1ce93d by Finley McIlwaine at 2023-06-06T07:50:04-06:00 Update CHANGES.md, user guide, recomp avoidance * Add --trace-args flag for tracing arguments received to standard output * Avoid recompiling due to changes in optimization flags * Update users guide and changes.md - - - - - 54b83253 by Matthew Craven at 2023-06-06T12:59:25-04:00 Generate Addr# access ops programmatically The existing utils/genprimopcode/gen_bytearray_ops.py was relocated and extended for this purpose. Additionally, hadrian now knows about this script and uses it when generating primops.txt - - - - - ecadbc7e by Matthew Pickering at 2023-06-06T13:00:01-04:00 ghcup-metadata: Only add Nightly tag when replacing LatestNightly Previously we were always adding the Nightly tag, but this led to all the previous builds getting an increasing number of nightly tags over time. Now we just add it once, when we remove the LatestNightly tag. - - - - - f3da6676 by Finley McIlwaine at 2023-06-06T14:12:56-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - bf36c467 by Matthew Pickering at 2023-06-07T10:16:09+01:00 Revert back to e16e20d592a6f5d9ed1af17b77fafd6495242345 Neither of these MRs are ready to land yet which causes issues with other MRs which are ready to land and need haddock changes. - - - - - 421510a9 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 atSign has no unicode variant Prior to this change, atSign was defined as follows: atSign unicode = text (if unicode then "@" else "@") Yes, this is the same symbol '\64' and not your font playing tricks on you. Now we define: atSign = char '@' Both the LaTeX and the Xhtml backend are updated accordingly. - - - - - 3785c276 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 LaTeX: fix printing of type variable bindings Consider this type signature: kindOf :: forall {k} (a :: k). Proxy a -> Proxy k Prior to this fix, the LaTeX backend rendered it like this: kindOf :: forall k a. Proxy a -> Proxy k Now we preserve explicit specificity and kind annotations. - - - - - 0febf3a8 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 Add support for invisible binders in type declarations - - - - - 4aea0a72 by Vladislav Zavialov at 2023-06-07T12:06:46+02:00 Invisible binders in type declarations (#22560) This patch implements @k-binders introduced in GHC Proposal #425 and guarded behind the TypeAbstractions extension: type D :: forall k j. k -> j -> Type data D @k @j a b = ... ^^ ^^ To represent the new syntax, we modify LHsQTyVars as follows: - hsq_explicit :: [LHsTyVarBndr () pass] + hsq_explicit :: [LHsTyVarBndr (HsBndrVis pass) pass] HsBndrVis is a new data type that records the distinction between type variable binders written with and without the @ sign: data HsBndrVis pass = HsBndrRequired | HsBndrInvisible (LHsToken "@" pass) The rest of the patch updates GHC, template-haskell, and haddock to handle the new syntax. Parser: The PsErrUnexpectedTypeAppInDecl error message is removed. The syntax it used to reject is now permitted. Renamer: The @ sign does not affect the scope of a binder, so the changes to the renamer are minimal. See rnLHsTyVarBndrVisFlag. Type checker: There are three code paths that were updated to deal with the newly introduced invisible type variable binders: 1. checking SAKS: see kcCheckDeclHeader_sig, matchUpSigWithDecl 2. checking CUSK: see kcCheckDeclHeader_cusk 3. inference: see kcInferDeclHeader, rejectInvisibleBinders Helper functions bindExplicitTKBndrs_Q_Skol and bindExplicitTKBndrs_Q_Tv are generalized to work with HsBndrVis. Updates the haddock submodule. Metric Increase: MultiLayerModulesTH_OneShot Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> - - - - - b7600997 by Josh Meredith at 2023-06-07T13:10:21-04:00 JS: clean up FFI 'fat arrow' calls in base:System.Posix.Internals (#23481) - - - - - e5d3940d by Sebastian Graf at 2023-06-07T18:01:28-04:00 Update CODEOWNERS - - - - - 960ef111 by Matthew Pickering at 2023-06-07T18:02:04-04:00 Revert "Remove IPE enabled builds from CI" This reverts commit 41b41577c8a28c236fa37e8f73aa1c6dc368d951. - - - - - bad1c8cc by Matthew Pickering at 2023-06-07T18:02:04-04:00 Revert "Update user's guide and release notes, small fixes" This reverts commit 3ded9a1cd22f9083f31bc2f37ee1b37f9d25dab7. - - - - - 12726d90 by Matthew Pickering at 2023-06-07T18:02:04-04:00 Revert "Add IPE-enabled builds to CI" This reverts commit 09d93bd0305b0f73422ce7edb67168c71d32c15f. - - - - - dbdd989d by Matthew Pickering at 2023-06-07T18:02:04-04:00 Revert "Add optional dependencies to ./configure output" This reverts commit a00488665cd890a26a5564a64ba23ff12c9bec58. - - - - - 240483af by Matthew Pickering at 2023-06-07T18:02:04-04:00 Revert "Fix IPE data decompression buffer allocation" This reverts commit 0e85099b9316ee24565084d5586bb7290669b43a. - - - - - 9b8c7dd8 by Matthew Pickering at 2023-06-07T18:02:04-04:00 Revert "Fix byte order of IPE data, fix IPE tests" This reverts commit 7872e2b6f08ea40d19a251c4822a384d0b397327. - - - - - 3364379b by Matthew Pickering at 2023-06-07T18:02:04-04:00 Revert "Add note describing IPE data compression" This reverts commit 69563c97396b8fde91678fae7d2feafb7ab9a8b0. - - - - - fda30670 by Matthew Pickering at 2023-06-07T18:02:04-04:00 Revert "Fix libzstd detection in configure and RTS" This reverts commit 5aef5658ad5fb96bac7719710e0ea008bf7b62e0. - - - - - 1cbcda9a by Matthew Pickering at 2023-06-07T18:02:04-04:00 Revert "IPE data compression" This reverts commit b7a640acf7adc2880e5600d69bcf2918fee85553. - - - - - fb5e99aa by Matthew Pickering at 2023-06-07T18:02:04-04:00 Revert "Add IPE compression to configure" This reverts commit 5d1f2411f4becea8650d12d168e989241edee186. - - - - - 2cdcb3a5 by Matthew Pickering at 2023-06-07T18:02:04-04:00 Revert "Restructure IPE buffer layout" This reverts commit f3556d6cefd3d923b36bfcda0c8185abb1d11a91. - - - - - 2b0c9f5e by Simon Peyton Jones at 2023-06-08T07:52:34+00:00 Don't report redundant Givens from quantified constraints This fixes #23323 See (RC4) in Note [Tracking redundant constraints] - - - - - 13e33bb3 by Finley McIlwaine at 2023-06-08T07:51:59-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - 3e5340ce by Finley McIlwaine at 2023-06-08T07:54:27-06:00 Add note about stubdir to recompilation docs - - - - - db7e84dc by Finley at 2023-06-08T08:11:03-06:00 Merge pull request haskell/haddock#1597 from haskell/finley/hi-haddock-9.6 hi-haddock for ghc 9.6 - - - - - 567b32e1 by David Binder at 2023-06-08T18:41:29-04:00 Update the outdated instructions in HACKING.md on how to compile GHC - - - - - 2b1a4abe by Ryan Scott at 2023-06-09T07:56:58-04:00 Restore mingwex dependency on Windows This partially reverts some of the changes in !9475 to make `base` and `ghc-prim` depend on the `mingwex` library on Windows. It also restores the RTS's stubs for `mingwex`-specific symbols such as `_lock_file`. This is done because the C runtime provides `libmingwex` nowadays, and moreoever, not linking against `mingwex` requires downstream users to link against it explicitly in difficult-to-predict circumstances. Better to always link against `mingwex` and prevent users from having to do the guesswork themselves. See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10360#note_495873 for the discussion that led to this. - - - - - 28954758 by Ryan Scott at 2023-06-09T07:56:58-04:00 RtsSymbols.c: Remove mingwex symbol stubs As of !9475, the RTS now links against `ucrt` instead of `msvcrt` on Windows, which means that the RTS no longer needs to declare stubs for the `__mingw_*` family of symbols. Let's remove these stubs to avoid confusion. Fixes #23309. - - - - - 3ab0155b by Ryan Scott at 2023-06-09T07:57:35-04:00 Consistently use validity checks for TH conversion of data constructors We were checking that TH-spliced data declarations do not look like this: ```hs data D :: Type = MkD Int ``` But we were only doing so for `data` declarations' data constructors, not for `newtype`s, `data instance`s, or `newtype instance`s. This patch factors out the necessary validity checks into its own `cvtDataDefnCons` function and uses it in all of the places where it needs to be. Fixes #22559. - - - - - a24b83dd by Matthew Pickering at 2023-06-09T15:19:00-04:00 Fix behaviour of -keep-tmp-files when used in OPTIONS_GHC pragma This fixes the behaviour of -keep-tmp-files when used in an OPTIONS_GHC pragma for files with module level scope. Instead of simple not deleting the files, we also need to remove them from the TmpFs so they are not deleted later on when all the other files are deleted. There are additional complications because you also need to remove the directory where these files live from the TmpFs so we don't try to delete those later either. I added two tests. 1. Tests simply that -keep-tmp-files works at all with a single module and --make mode. 2. The other tests that temporary files are deleted for other modules which don't enable -keep-tmp-files. Fixes #23339 - - - - - dcf32882 by Matthew Pickering at 2023-06-09T15:19:00-04:00 withDeferredDiagnostics: When debugIsOn, write landmine into IORef to catch use-after-free. Ticket #23305 reports an error where we were attempting to use the logger which was created by withDeferredDiagnostics after its scope had ended. This problem would have been caught by this patch and a validate build: ``` +*** Exception: Use after free +CallStack (from HasCallStack): + error, called at compiler/GHC/Driver/Make.hs:<line>:<column> in <package-id>:GHC.Driver.Make ``` This general issue is tracked by #20981 - - - - - 432c736c by Matthew Pickering at 2023-06-09T15:19:00-04:00 Don't return complete HscEnv from upsweep By returning a complete HscEnv from upsweep the logger (as introduced by withDeferredDiagnostics) was escaping the scope of withDeferredDiagnostics and hence we were losing error messages. This is reminiscent of #20981, which also talks about writing errors into messages after their scope has ended. See #23305 for details. - - - - - 26013cdc by Alexander McKenna at 2023-06-09T15:19:41-04:00 Dump `SpecConstr` specialisations separately Introduce a `-ddump-spec-constr` flag which debugs specialisations from `SpecConstr`. These are no longer shown when you use `-ddump-spec`. - - - - - 4639100b by Matthew Pickering at 2023-06-09T18:50:43-04:00 Add role annotations to SNat, SSymbol and SChar Ticket #23454 explained it was possible to implement unsafeCoerce because SNat was lacking a role annotation. As these are supposed to be singleton types but backed by an efficient representation the correct annotation is nominal to ensure these kinds of coerces are forbidden. These annotations were missed from https://github.com/haskell/core-libraries-committee/issues/85 which was implemented in 532de36870ed9e880d5f146a478453701e9db25d. CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/170 Fixes #23454 - - - - - 9c0dcff7 by Matthew Pickering at 2023-06-09T18:51:19-04:00 Remove non-existant bytearray-ops.txt.pp file from ghc.cabal.in This broke the sdist generation. Fixes #23489 - - - - - 273ff0c7 by David Binder at 2023-06-09T18:52:00-04:00 Regression test T13438 is no longer marked as "expect_broken" in the testsuite driver. - - - - - b84a2900 by Andrei Borzenkov at 2023-06-10T08:27:28-04:00 Fix -Wterm-variable-capture scope (#23434) -Wterm-variable-capture wasn't accordant with type variable scoping in associated types, in type classes. For example, this code produced the warning: k = 12 class C k a where type AT a :: k -> Type I solved this issue by reusing machinery of newTyVarNameRn function that is accordand with associated types: it does lookup for each free type variable when we are in the type class context. And in this patch I use result of this work to make sure that -Wterm-variable-capture warns only on implicitly quantified type variables. - - - - - 9d1a8d87 by Jorge Mendes at 2023-06-10T08:28:10-04:00 Remove redundant case statement in rts/js/mem.js. - - - - - a1f350e2 by Oleg Grenrus at 2023-06-13T09:42:16-04:00 Change WarningWithFlag to plural WarningWithFlags Resolves #22825 Now each diagnostic can name multiple different warning flags for its reason. There is currently one use case: missing signatures. Currently we need to check which warning flags are enabled when generating the diagnostic, which is against the declarative nature of the diagnostic framework. This patch allows a warning diagnostic to have multiple warning flags, which makes setup more declarative. The WarningWithFlag pattern synonym is added for backwards compatibility The 'msgEnvReason' field is added to MsgEnvelope to store the `ResolvedDiagnosticReason`, which accounts for the enabled flags, and then that is used for pretty printing the diagnostic. - - - - - ec01f0ec by Matthew Pickering at 2023-06-13T09:42:59-04:00 Add a test Way for running ghci with Core optimizations Tracking ticket: #23059 This runs compile_and_run tests with optimised code with bytecode interpreter Changed submodules: hpc, process Co-authored-by: Torsten Schmits <git at tryp.io> - - - - - c6741e72 by Rodrigo Mesquita at 2023-06-13T09:43:38-04:00 Configure -Qunused-arguments instead of hardcoding it When GHC invokes clang, it currently passes -Qunused-arguments to discard warnings resulting from GHC using multiple options that aren't used. In this commit, we configure -Qunused-arguments into the Cc options instead of checking if the compiler is clang at runtime and hardcoding the flag into GHC. This is part of the effort to centralise toolchain information in toolchain target files at configure time with the end goal of a runtime retargetable GHC. This also means we don't need to call getCompilerInfo ever, which improves performance considerably (see !10589). Metric Decrease: PmSeriesG T10421 T11303b T12150 T12227 T12234 T12425 T13035 T13253-spj T13386 T15703 T16875 T17836b T17977 T17977b T18140 T18282 T18304 T18698a T18698b T18923 T20049 T21839c T3064 T5030 T5321FD T5321Fun T5837 T6048 T9020 T9198 T9872d T9961 - - - - - 0128db87 by Victor Cacciari Miraldo at 2023-06-13T09:44:18-04:00 Improve docs for Data.Fixed; adds 'realToFrac' as an option for conversion between different precisions. - - - - - 95b69cfb by Ryan Scott at 2023-06-13T09:44:55-04:00 Add regression test for #23143 !10541, the fix for #23323, also fixes #23143. Let's add a regression test to ensure that it stays fixed. Fixes #23143. - - - - - ed2dbdca by Emily Martins at 2023-06-13T09:45:37-04:00 delete GHCi.UI.Tags module and remove remaining references Co-authored-by: Tilde Rose <t1lde at protonmail.com> - - - - - c90d96e4 by Victor Cacciari Miraldo at 2023-06-13T09:46:26-04:00 Add regression test for 17328 - - - - - de58080c by Victor Cacciari Miraldo at 2023-06-13T09:46:26-04:00 Skip checking whether constructors are in scope when deriving newtype instances. Fixes #17328 - - - - - 5e3c2b05 by Philip Hazelden at 2023-06-13T09:47:07-04:00 Don't suggest `DeriveAnyClass` when instance can't be derived. Fixes #19692. Prototypical cases: class C1 a where x1 :: a -> Int data G1 = G1 deriving C1 class C2 a where x2 :: a -> Int x2 _ = 0 data G2 = G2 deriving C2 Both of these used to give this suggestion, but for C1 the suggestion would have failed (generated code with undefined methods, which compiles but warns). Now C2 still gives the suggestion but C1 doesn't. - - - - - 80a0b099 by David Binder at 2023-06-13T09:47:49-04:00 Add testcase for error GHC-00711 to testsuite - - - - - e4b33a1d by Oleg Grenrus at 2023-06-14T07:01:21-04:00 Add -Wmissing-poly-kind-signatures Implements #22826 This is a restricted version of -Wmissing-kind-signatures shown only for polykinded types. - - - - - f8395b94 by doyougnu at 2023-06-14T07:02:01-04:00 ci: special case in req_host_target_ghc for JS - - - - - b852a5b6 by Gergő Érdi at 2023-06-14T07:02:42-04:00 When forcing a `ModIface`, force the `MINIMAL` pragmas in class definitions Fixes #23486 - - - - - c29b45ee by Krzysztof Gogolewski at 2023-06-14T07:03:19-04:00 Add a testcase for #20076 Remove 'recursive' in the error message, since the error can arise without recursion. - - - - - b80ef202 by Krzysztof Gogolewski at 2023-06-14T07:03:56-04:00 Use tcInferFRR to prevent bad generalisation Fixes #23176 - - - - - bd8ef37d by Matthew Pickering at 2023-06-14T07:04:31-04:00 ci: Add dependenices on necessary aarch64 jobs for head.hackage ci These need to be added since we started testing aarch64 on head.hackage CI. The jobs will sometimes fail because they will start before the relevant aarch64 job has finished. Fixes #23511 - - - - - a0c27cee by Vladislav Zavialov at 2023-06-14T07:05:08-04:00 Add standalone kind signatures for Code and TExp CodeQ and TExpQ already had standalone kind signatures even before this change: type TExpQ :: TYPE r -> Kind.Type type CodeQ :: TYPE r -> Kind.Type Now Code and TExp have signatures too: type TExp :: TYPE r -> Kind.Type type Code :: (Kind.Type -> Kind.Type) -> TYPE r -> Kind.Type This is a stylistic change. - - - - - e70c1245 by Tom Ellis at 2023-06-14T07:05:48-04:00 Warn that GHC.TypeLits.Internal should not be used - - - - - 100650e3 by Tom Ellis at 2023-06-14T07:05:48-04:00 Warn that GHC.TypeNats.Internal should not be used - - - - - 4e085d17 by Finley McIlwaine at 2023-06-14T13:41:06-06:00 Replace SYB traversals - - - - - 7b39aec5 by Finley McIlwaine at 2023-06-14T14:20:17-06:00 Test ref accepts, remove unused HaddockClsInst - - - - - 078250ef by Jacco Krijnen at 2023-06-14T17:17:53-04:00 Add more flags for dumping core passes (#23491) - - - - - 1b7604af by Jacco Krijnen at 2023-06-14T17:17:53-04:00 Add tests for dumping flags (#23491) - - - - - 42000000 by Sebastian Graf at 2023-06-14T17:18:29-04:00 Provide a demand signature for atomicModifyMutVar.# (#23047) Fixes #23047 - - - - - 8f27023b by Ben Gamari at 2023-06-15T03:10:24-04:00 compiler: Cross-reference Note [StgToJS design] In particular, the numeric representations are quite useful context in a few places. - - - - - a71b60e9 by Andrei Borzenkov at 2023-06-15T03:11:00-04:00 Implement the -Wimplicit-rhs-quantification warning (#23510) GHC Proposal #425 "Invisible binders in type declarations" forbids implicit quantification of type variables that occur free on the right-hand side of a type synonym but are not mentioned on the left-hand side. The users are expected to rewrite this using invisible binders: type T1 :: forall a . Maybe a type T1 = 'Nothing :: Maybe a -- old type T1 @a = 'Nothing :: Maybe a -- new Since the @k-binders are a new feature, we need to wait for three releases before we require the use of the new syntax. In the meantime, we ought to provide users with a new warning, -Wimplicit-rhs-quantification, that would detect when such implicit quantification takes place, and include it in -Wcompat. - - - - - 0078dd00 by Sven Tennie at 2023-06-15T03:11:36-04:00 Minor refactorings to mkSpillInstr and mkLoadInstr Better error messages. And, use the existing `off` constant to reduce duplication. - - - - - 1792b57a by doyougnu at 2023-06-15T03:12:17-04:00 JS: merge util modules Merge Core and StgUtil modules for StgToJS pass. Closes: #23473 - - - - - 469ff08b by Vladislav Zavialov at 2023-06-15T03:12:57-04:00 Check visibility of nested foralls in can_eq_nc (#18863) Prior to this change, `can_eq_nc` checked the visibility of the outermost layer of foralls: forall a. forall b. forall c. phi1 forall x. forall y. forall z. phi2 ^^ up to here Then it delegated the rest of the work to `can_eq_nc_forall`, which split off all foralls: forall a. forall b. forall c. phi1 forall x. forall y. forall z. phi2 ^^ up to here This meant that some visibility flags were completely ignored. We fix this oversight by moving the check to `can_eq_nc_forall`. - - - - - 59c9065b by Luite Stegeman at 2023-06-15T03:13:37-04:00 JS: use regular mask for blocking IO Blocking IO used uninterruptibleMask which should make any thread blocked on IO unreachable by async exceptions (such as those from timeout). This changes it to a regular mask. It's important to note that the nodejs runtime does not actually interrupt the blocking IO when the Haskell thread receives an async exception, and that file positions may be updated and buffers may be written after the Haskell thread has already resumed. Any file descriptor affected by an async exception interruption should therefore be used with caution. - - - - - 907c06c3 by Luite Stegeman at 2023-06-15T03:13:37-04:00 JS: nodejs: do not set 'readable' handler on stdin at startup The Haskell runtime used to install a 'readable' handler on stdin at startup in nodejs. This would cause the nodejs system to start buffering the stream, causing data loss if the stdin file descriptor is passed to another process. This change delays installation of the 'readable' handler until the first read of stdin by Haskell code. - - - - - a54b40a9 by Luite Stegeman at 2023-06-15T03:13:37-04:00 JS: reserve one more virtual (negative) file descriptor This is needed for upcoming support of the process package - - - - - 78cd1132 by Andrei Borzenkov at 2023-06-15T11:16:11+04:00 Report scoped kind variables at the type-checking phase (#16635) This patch modifies the renamer to respect ScopedTypeVariables in kind signatures. This means that kind variables bound by the outermost `forall` now scope over the type: type F = '[Right @a @() () :: forall a. Either a ()] -- ^^^^^^^^^^^^^^^ ^^^ -- in scope here bound here However, any use of such variables is a type error, because we don't have type-level lambdas to bind them in Core. This is described in the new Note [Type variable scoping errors during type check] in GHC.Tc.Types. - - - - - df9c2090 by Finley McIlwaine at 2023-06-15T08:02:51-06:00 Use batchMsg for progress reporting during load With hi-haddock as is, there is an awkward silence during the load operation. This commit makes haddock use the default `batchMsg` Messager for progress reporting, and makes the default GHC verbosity level 1, so the user can see what GHC is doing. - - - - - f23679a8 by Hécate Moonlight at 2023-06-15T20:31:53+02:00 Merge pull request haskell/haddock#1600 from haskell/finley/hi-haddock-optim - - - - - a7982192 by Finley McIlwaine at 2023-06-15T15:02:16-06:00 hi-haddock squashed - - - - - 4a41ba75 by Sylvain Henry at 2023-06-15T18:09:15-04:00 JS: testsuite: use correct ticket number Replace #22356 with #22349 for these tests because #22356 has been fixed but now these tests fail because of #22349. - - - - - 15f150c8 by Sylvain Henry at 2023-06-15T18:09:16-04:00 JS: testsuite: update ticket numbers - - - - - 08d8e9ef by Sylvain Henry at 2023-06-15T18:09:16-04:00 JS: more triage - - - - - e8752e12 by Krzysztof Gogolewski at 2023-06-15T18:09:52-04:00 Fix test T18522-deb-ppr Fixes #23509 - - - - - c34f0c8d by Finley McIlwaine at 2023-06-15T16:22:03-06:00 Merge remote-tracking branch 'origin/ghc-9.6' into finley/hi-haddock-squashed - - - - - 62c56416 by Ben Price at 2023-06-16T05:52:39-04:00 Lint: more details on "Occurrence is GlobalId, but binding is LocalId" This is helpful when debugging a pass which accidentally shadowed a binder. - - - - - d4c10238 by Ryan Hendrickson at 2023-06-16T05:53:22-04:00 Clean a stray bit of text in user guide - - - - - 93647b5c by Vladislav Zavialov at 2023-06-16T05:54:02-04:00 testsuite: Add forall visibility test cases The added tests ensure that the type checker does not confuse visible and invisible foralls. VisFlag1: kind-checking type applications and inferred type variable instantiations VisFlag1_ql: kind-checking Quick Look instantiations VisFlag2: kind-checking type family instances VisFlag3: checking kind annotations on type parameters of associated type families VisFlag4: checking kind annotations on type parameters in type declarations with SAKS VisFlag5: checking the result kind annotation of data family instances - - - - - 40452797 by Bartłomiej Cieślar at 2023-06-16T12:26:04+02:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - e58673bf by Ben Gamari at 2023-06-16T09:33:35-04:00 Bump GHC version to 9.8 - - - - - 74bdf972 by Ben Gamari at 2023-06-16T09:36:18-04:00 Merge commit 'fcaaad06770a26d35d4aafd65772dedadf17669c' into ghc-head - - - - - a5f0c00e by Sylvain Henry at 2023-06-16T12:25:40-04:00 JS: factorize SaneDouble into its own module Follow-up of b159e0e9 whose ticket is #22736 - - - - - 0baf9e7c by Krzysztof Gogolewski at 2023-06-16T12:26:17-04:00 Add tests for #21973 - - - - - 640ea90e by Diego Diverio at 2023-06-16T23:07:55-04:00 Update documentation for `<**>` - - - - - 2469a813 by Diego Diverio at 2023-06-16T23:07:55-04:00 Update text - - - - - 1f515bbb by Diego Diverio at 2023-06-16T23:07:55-04:00 Update examples - - - - - 7af99a0d by Diego Diverio at 2023-06-16T23:07:55-04:00 Update documentation to actually display code correctly - - - - - 800aad7e by Andrei Borzenkov at 2023-06-16T23:08:32-04:00 Type/data instances: require that variables on the RHS are mentioned on the LHS (#23512) GHC Proposal #425 "Invisible binders in type declarations" restricts the scope of type and data family instances as follows: In type family and data family instances, require that every variable mentioned on the RHS must also occur on the LHS. For example, here are three equivalent type instance definitions accepted before this patch: type family F1 a :: k type instance F1 Int = Any :: j -> j type family F2 a :: k type instance F2 @(j -> j) Int = Any :: j -> j type family F3 a :: k type instance forall j. F3 Int = Any :: j -> j - In F1, j is implicitly quantified and it occurs only on the RHS; - In F2, j is implicitly quantified and it occurs both on the LHS and the RHS; - In F3, j is explicitly quantified. Now F1 is rejected with an out-of-scope error, while F2 and F3 continue to be accepted. - - - - - 9132d529 by Sylvain Henry at 2023-06-18T02:50:34-04:00 JS: testsuite: use correct ticket numbers - - - - - c3a1274c by Sylvain Henry at 2023-06-18T02:50:34-04:00 JS: don't dump eventlog to stderr by default Fix T16707 Bump stm submodule - - - - - 89bb8ad8 by Ryan Hendrickson at 2023-06-18T02:51:14-04:00 Fix TH name lookup for symbolic tycons (#23525) - - - - - cb9e1ce4 by Finley McIlwaine at 2023-06-18T21:16:45-06:00 IPE data compression IPE data resulting from the `-finfo-table-map` flag may now be compressed by configuring the GHC build with the `--enable-ipe-data-compression` flag. This results in about a 20% reduction in the size of IPE-enabled build results. The compression library, zstd, may optionally be statically linked by configuring with the `--enabled-static-libzstd` flag (on non-darwin platforms) libzstd version 1.4.0 or greater is required. - - - - - 0cbc3ae0 by Gergő Érdi at 2023-06-19T09:11:38-04:00 Add `IfaceWarnings` to represent the `ModIface`-storable parts of a `Warnings GhcRn`. Fixes #23516 - - - - - 3e80c2b4 by Arnaud Spiwack at 2023-06-20T03:19:41-04:00 Avoid desugaring non-recursive lets into recursive lets This prepares for having linear let expressions in the frontend. When desugaring lets, SPECIALISE statements create more copies of a let binding. Because of the rewrite rules attached to the bindings, there are dependencies between the generated binds. Before this commit, we simply wrapped all these in a mutually recursive let block, and left it to the simplified to sort it out. With this commit: we are careful to generate the bindings in dependency order, so that we can wrap them in consecutive lets (if the source is non-recursive). - - - - - 9fad49e0 by Ben Gamari at 2023-06-20T03:20:19-04:00 rts: Do not call exit() from SIGINT handler Previously `shutdown_handler` would call `stg_exit` if the scheduler was Oalready found to be in `SCHED_INTERRUPTING` state (or higher). However, `stg_exit` is not signal-safe as it calls `exit` (which calls `atexit` handlers). The only safe thing to do in this situation is to call `_exit`, which terminates with minimal cleanup. Fixes #23417. - - - - - 7485f848 by Andrew Lelechenko at 2023-06-20T03:20:57-04:00 Bump Cabal submodule This requires changing the recomp007 test because now cabal passes `this-unit-id` to executable components, and that unit-id contains a hash which includes the ABI of the dependencies. Therefore changing the dependencies means that -this-unit-id changes and recompilation is triggered. The spririt of the test is to test GHC's recompilation logic assuming that `-this-unit-id` is constant, so we explicitly pass `-ipid` to `./configure` rather than letting `Cabal` work it out. - - - - - 1464a2a8 by mangoiv at 2023-06-20T03:21:34-04:00 [feat] add a hint to `HasField` error message - add a hint that indicates that the record that the record dot is used on might just be missing a field - as the intention of the programmer is not entirely clear, it is only shown if the type is known - This addresses in part issue #22382 - - - - - 418ee3dc by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Remove NFData SourceText, IfaceWarnings updates The NFData SourceText instance is now available in GHC Handle mod_iface mi_warns now being IfaceWarnings - - - - - 62f31380 by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Accept Instances.hs test output Due to ghc!10469. - - - - - a8f2fc0e by Ben Gamari at 2023-06-20T15:48:08-04:00 Test fixes for "Fix associated data family doc structure items" Associated data families were being given their own export DocStructureItems, which resulted in them being documented separately from their classes in haddocks. This commit fixes it. - - - - - b65e78dd by Ben Gamari at 2023-06-20T16:56:43-04:00 rts/ipe: Fix unused lock warning - - - - - 6086effd by Ben Gamari at 2023-06-20T16:56:44-04:00 rts/ProfilerReportJson: Fix memory leak - - - - - 1e48c434 by Ben Gamari at 2023-06-20T16:56:44-04:00 rts: Various warnings fixes - - - - - 471486b9 by Ben Gamari at 2023-06-20T16:56:44-04:00 rts: Fix printf format mismatch - - - - - 80603fb3 by Ben Gamari at 2023-06-20T16:56:44-04:00 rts: Fix incorrect #include <sys/poll.h> According to Alpine's warnings and poll(2), <poll.h> should be preferred. - - - - - ff18e6fd by Ben Gamari at 2023-06-20T16:56:44-04:00 nonmoving: Fix unused definition warrnings - - - - - 6e7fe8ee by Ben Gamari at 2023-06-20T16:56:44-04:00 Disable futimens on Darwin. See #22938 - - - - - b7706508 by Ben Gamari at 2023-06-20T16:56:44-04:00 rts: Fix incorrect CPP guard - - - - - 94f00e9b by Ben Gamari at 2023-06-20T16:56:44-04:00 hadrian: Ensure that -Werror is passed when compiling the RTS. Previously the `+werror` transformer would only pass `-Werror` to GHC, which does not ensure that the same is passed to the C compiler when building the RTS. Arguably this is itself a bug but for now we will just work around this by passing `-optc-Werror` to GHC. I tried to enable `-Werror` in all C compilations but the boot libraries are something of a portability nightmare. - - - - - 5fb54bf8 by Ben Gamari at 2023-06-20T16:56:44-04:00 rts: Disable `#pragma GCC`s on clang compilers Otherwise the build fails due to warnings. See #23530. - - - - - cf87f380 by Ben Gamari at 2023-06-20T16:56:44-04:00 rts: Fix capitalization of prototype - - - - - 17f250d7 by Ben Gamari at 2023-06-20T16:56:44-04:00 rts: Fix incorrect format specifier - - - - - 0ff1c501 by Josh Meredith at 2023-06-20T16:57:20-04:00 JS: remove js_broken(22576) in favour of the pre-existing wordsize(32) condition (#22576) - - - - - 3d1d42b7 by Finley McIlwaine at 2023-06-21T12:04:58-04:00 Memory usage fixes for Haddock - Do not include `mi_globals` in the `NoBackend` backend. It was only included for Haddock, but Haddock does not actually need it. This causes a 200MB reduction in max residency when generating haddocks on the Agda codebase (roughly 1GB to 800MB). - Make haddock_{parser,renamer}_perf tests more accurate by forcing docs to be written to interface files using `-fwrite-interface` Bumps haddock submodule. Metric Decrease: haddock.base - - - - - 8185b1c2 by Finley McIlwaine at 2023-06-21T12:04:58-04:00 Fix associated data family doc structure items Associated data families were being given their own export DocStructureItems, which resulted in them being documented separately from their classes in haddocks. This commit fixes it. - - - - - 4d356ea3 by Sylvain Henry at 2023-06-21T12:04:59-04:00 JS: implement TH support - Add ghc-interp.js bootstrap script for the JS interpreter - Interactively link and execute iserv code from the ghci package - Incrementally load and run JS code for splices into the running iserv Co-authored-by: Luite Stegeman <stegeman at gmail.com> - - - - - 3249cf12 by Sylvain Henry at 2023-06-21T12:04:59-04:00 Don't use getKey - - - - - f84ff161 by Sylvain Henry at 2023-06-21T12:04:59-04:00 Stg: return imported FVs This is used to determine what to link when using the interpreter. For now it's only used by the JS interpreter but it could easily be used by the native interpreter too (instead of extracting names from compiled BCOs). - - - - - fab2ad23 by Sylvain Henry at 2023-06-21T12:04:59-04:00 Fix some recompilation avoidance tests - - - - - a897dc13 by Sylvain Henry at 2023-06-21T12:04:59-04:00 TH_import_loop is now broken as expected - - - - - dbb4ad51 by Sylvain Henry at 2023-06-21T12:04:59-04:00 JS: always recompile when TH is enabled (cf #23013) - - - - - cb1ac33e by Bartłomiej Cieślar at 2023-06-21T12:56:02-04:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - 9933e10b by Ben Gamari at 2023-06-21T12:56:02-04:00 Bump GHC version to 9.8 - - - - - 711b1d24 by Bartłomiej Cieślar at 2023-06-21T12:59:27-04:00 Add support for deprecating exported items (proposal #134) This is an implementation of the deprecated exports proposal #134. The proposal introduces an ability to introduce warnings to exports. This allows for deprecating a name only when it is exported from a specific module, rather than always depreacting its usage. In this example: module A ({-# DEPRECATED "do not use" #-} x) where x = undefined --- module B where import A(x) `x` will emit a warning when it is explicitly imported. Like the declaration warnings, export warnings are first accumulated within the `Warnings` struct, then passed into the ModIface, from which they are then looked up and warned about in the importing module in the `lookup_ie` helpers of the `filterImports` function (for the explicitly imported names) and in the `addUsedGRE(s)` functions where they warn about regular usages of the imported name. In terms of the AST information, the custom warning is stored in the extension field of the variants of the `IE` type (see Trees that Grow for more information). The commit includes a bump to the haddock submodule added in MR #28 Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - c1865854 by Ben Gamari at 2023-06-21T12:59:30-04:00 configure: Bump version to 9.8 Bumps Haddock submodule - - - - - fe8c18b6 by Ben Gamari at 2023-06-21T15:36:29-04:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - c61a0d5b by Ben Gamari at 2023-06-21T16:10:51-04:00 Bump GHC version to 9.9 - - - - - 4e1de71c by Ben Gamari at 2023-06-21T21:07:48-04:00 configure: Bump version to 9.9 Bumps haddock submodule. - - - - - 5b6612bc by Ben Gamari at 2023-06-23T03:56:49-04:00 rts: Work around missing prototypes errors Darwin's toolchain inexpliciably claims that `write_barrier` and friends have declarations without prototypes, despite the fact that (a) they are definitions, and (b) the prototypes appear only a few lines above. Work around this by making the definitions proper prototypes. - - - - - 43b66a13 by Matthew Pickering at 2023-06-23T03:57:26-04:00 ghcup-metadata: Fix date modifier (M = minutes, m = month) Fixes #23552 - - - - - 564164ef by Luite Stegeman at 2023-06-24T10:27:29+09:00 Support large stack frames/offsets in GHCi bytecode interpreter Bytecode instructions like PUSH_L (push a local variable) contain an operand that refers to the stack slot. Before this patch, the operand type was SmallOp (Word16), limiting the maximum stack offset to 65535 words. This could cause compiler panics in some cases (See #22888). This patch changes the operand type for stack offsets from SmallOp to Op, removing the stack offset limit. Fixes #22888 - - - - - 8d6574bc by Sylvain Henry at 2023-06-26T13:15:06-04:00 JS: support levity-polymorphic datatypes (#22360,#22291) - thread knowledge about levity into PrimRep instead of panicking - JS: remove assumption that unlifted heap objects are rts objects (TVar#, etc.) Doing this also fixes #22291 (test added). There is a small performance hit (~1% more allocations). Metric Increase: T18698a T18698b - - - - - 5578bbad by Matthew Pickering at 2023-06-26T13:15:43-04:00 MR Review Template: Mention "Blocked on Review" label In order to improve our MR review processes we now have the label "Blocked on Review" which allows people to signal that a MR is waiting on a review to happen. See: https://mail.haskell.org/pipermail/ghc-devs/2023-June/021255.html - - - - - 4427e9cf by Matthew Pickering at 2023-06-26T13:15:43-04:00 Move MR template to Default.md This makes it more obvious what you have to modify to affect the default template rather than looking in the project settings. - - - - - 522bd584 by Arnaud Spiwack at 2023-06-26T13:16:33-04:00 Revert "Avoid desugaring non-recursive lets into recursive lets" This (temporary) reverts commit 3e80c2b40213bebe302b1bd239af48b33f1b30ef. Fixes #23550 - - - - - c59fbb0b by Torsten Schmits at 2023-06-26T19:34:20+02:00 Propagate breakpoint information when inlining across modules Tracking ticket: #23394 MR: !10448 * Add constructor `IfaceBreakpoint` to `IfaceTickish` * Store breakpoint data in interface files * Store `BreakArray` for the breakpoint's module, not the current module, in BCOs * Store module name in BCOs instead of `Unique`, since the `Unique` from an `Iface` doesn't match the modules in GHCi's state * Allocate module name in `ModBreaks`, like `BreakArray` * Lookup breakpoint by module name in GHCi * Skip creating breakpoint instructions when no `ModBreaks` are available, rather than injecting `ModBreaks` in the linker when breakpoints are enabled, and panicking when `ModBreaks` is missing - - - - - 6f904808 by Greg Steuck at 2023-06-27T16:53:07-04:00 Remove undefined FP_PROG_LD_BUILD_ID from configure.ac's - - - - - e89aa072 by Andrei Borzenkov at 2023-06-27T16:53:44-04:00 Remove arity inference in type declarations (#23514) Arity inference in type declarations was introduced as a workaround for the lack of @k-binders. They were added in 4aea0a72040, so I simplified all of this by simply removing arity inference altogether. This is part of GHC Proposal #425 "Invisible binders in type declarations". - - - - - 459dee1b by Torsten Schmits at 2023-06-27T16:54:20-04:00 Relax defaulting of RuntimeRep/Levity when printing Fixes #16468 MR: !10702 Only default RuntimeRep to LiftedRep when variables are bound by the toplevel forall - - - - - 151f8f18 by Torsten Schmits at 2023-06-27T16:54:57-04:00 Remove duplicate link label in linear types docs - - - - - ecdc4353 by Rodrigo Mesquita at 2023-06-28T12:24:57-04:00 Stop configuring unused Ld command in `settings` GHC has no direct dependence on the linker. Rather, we depend upon the C compiler for linking and an object-merging program (which is typically `ld`) for production of GHCi objects and merging of C stubs into final object files. Despite this, for historical reasons we still recorded information about the linker into `settings`. Remove these entries from `settings`, `hadrian/cfg/system.config`, as well as the `configure` logic responsible for this information. Closes #23566. - - - - - bf9ec3e4 by Bryan Richter at 2023-06-28T12:25:33-04:00 Remove extraneous debug output - - - - - 7eb68dd6 by Bryan Richter at 2023-06-28T12:25:33-04:00 Work with unset vars in -e mode - - - - - 49c27936 by Bryan Richter at 2023-06-28T12:25:33-04:00 Pass positional arguments in their positions By quoting $cmd, the default "bash -i" is a single argument to run, and no file named "bash -i" actually exists to be run. - - - - - 887dc4fc by Bryan Richter at 2023-06-28T12:25:33-04:00 Handle unset value in -e context - - - - - 5ffc7d7b by Rodrigo Mesquita at 2023-06-28T21:07:36-04:00 Configure CPP into settings There is a distinction to be made between the Haskell Preprocessor and the C preprocessor. The former is used to preprocess Haskell files, while the latter is used in C preprocessing such as Cmm files. In practice, they are both the same program (usually the C compiler) but invoked with different flags. Previously we would, at configure time, configure the haskell preprocessor and save the configuration in the settings file, but, instead of doing the same for CPP, we had hardcoded in GHC that the CPP program was either `cc -E` or `cpp`. This commit fixes that asymmetry by also configuring CPP at configure time, and tries to make more explicit the difference between HsCpp and Cpp (see Note [Preprocessing invocations]). Note that we don't use the standard CPP and CPPFLAGS to configure Cpp, but instead use the non-standard --with-cpp and --with-cpp-flags. The reason is that autoconf sets CPP to "$CC -E", whereas we expect the CPP command to be configured as a standalone executable rather than a command. These are symmetrical with --with-hs-cpp and --with-hs-cpp-flags. Cleanup: Hadrian no longer needs to pass the CPP configuration for CPP to be C99 compatible through -optP, since we now configure that into settings. Closes #23422 - - - - - 5efa9ca5 by Ben Gamari at 2023-06-28T21:08:13-04:00 hadrian: Always canonicalize topDirectory Hadrian's `topDirectory` is intended to provide an absolute path to the root of the GHC tree. However, if the tree is reached via a symlink this One question here is whether the `canonicalizePath` call is expensive enough to warrant caching. In a quick microbenchmark I observed that `canonicalizePath "."` takes around 10us per call; this seems sufficiently low not to worry. Alternatively, another approach here would have been to rather move the canonicalization into `m4/fp_find_root.m4`. This would have avoided repeated canonicalization but sadly path canonicalization is a hard problem in POSIX shell. Addresses #22451. - - - - - b3e1436f by aadaa_fgtaa at 2023-06-28T21:08:53-04:00 Optimise ELF linker (#23464) - cache last elements of `relTable`, `relaTable` and `symbolTables` in `ocInit_ELF` - cache shndx table in ObjectCode - run `checkProddableBlock` only with debug rts - - - - - 30525b00 by Ben Gamari at 2023-06-28T21:09:30-04:00 compiler: Introduce MO_{ACQUIRE,RELEASE}_FENCE - - - - - b787e259 by Ben Gamari at 2023-06-28T21:09:30-04:00 compiler: Drop MO_WriteBarrier rts: Drop write_barrier - - - - - 7550b4a5 by Ben Gamari at 2023-06-28T21:09:30-04:00 rts: Drop load_store_barrier() This is no longer used. - - - - - d5f2875e by Ben Gamari at 2023-06-28T21:09:31-04:00 rts: Drop last instances of prim_{write,read}_barrier - - - - - 965ac2ba by Ben Gamari at 2023-06-28T21:09:31-04:00 rts: Eliminate remaining uses of load_load_barrier - - - - - 0fc5cb97 by Sven Tennie at 2023-06-28T21:09:31-04:00 compiler: Drop MO_ReadBarrier - - - - - 7a7d326c by Ben Gamari at 2023-06-28T21:09:31-04:00 rts: Drop load_load_barrier This is no longer used. - - - - - 9f63da66 by Sven Tennie at 2023-06-28T21:09:31-04:00 Delete write_barrier function - - - - - bb0ed354 by Ben Gamari at 2023-06-28T21:09:31-04:00 rts: Make collectFreshWeakPtrs definition a prototype x86-64/Darwin's toolchain inexplicably warns that collectFreshWeakPtrs needs to be a prototype. - - - - - ef81a1eb by Sven Tennie at 2023-06-28T21:10:08-04:00 Fix number of free double regs D1..D4 are defined for aarch64 and thus not free. - - - - - c335fb7c by Ryan Scott at 2023-06-28T21:10:44-04:00 Fix typechecking of promoted empty lists The `'[]` case in `tc_infer_hs_type` is smart enough to handle arity-0 uses of `'[]` (see the newly added `T23543` test case for an example), but the `'[]` case in `tc_hs_type` was not. We fix this by changing the `tc_hs_type` case to invoke `tc_infer_hs_type`, as prescribed in `Note [Future-proofing the type checker]`. There are some benign changes to test cases' expected output due to the new code path using `forall a. [a]` as the kind of `'[]` rather than `[k]`. Fixes #23543. - - - - - fcf310e7 by Rodrigo Mesquita at 2023-06-28T21:11:21-04:00 Configure MergeObjs supports response files rather than Ld The previous configuration script to test whether Ld supported response files was * Incorrect (see #23542) * Used, in practice, to check if the *merge objects tool* supported response files. This commit modifies the macro to run the merge objects tool (rather than Ld), using a response file, and checking the result with $NM Fixes #23542 - - - - - 78b2f3cc by Sylvain Henry at 2023-06-28T21:12:02-04:00 JS: fix JS stack printing (#23565) - - - - - 9f01d14b by Matthew Pickering at 2023-06-29T04:13:41-04:00 Add -fpolymorphic-specialisation flag (off by default at all optimisation levels) Polymorphic specialisation has led to a number of hard to diagnose incorrect runtime result bugs (see #23469, #23109, #21229, #23445) so this commit introduces a flag `-fpolymorhphic-specialisation` which allows users to turn on this experimental optimisation if they are willing to buy into things going very wrong. Ticket #23469 - - - - - b1e611d5 by Ben Gamari at 2023-06-29T04:14:17-04:00 Rip out runtime linker/compiler checks We used to choose flags to pass to the toolchain at runtime based on the platform running GHC, and in this commit we drop all of those runtime linker checks Ultimately, this represents a change in policy: We no longer adapt at runtime to the toolchain being used, but rather make final decisions about the toolchain used at /configure time/ (we have deleted Note [Run-time linker info] altogether!). This works towards the goal of having all toolchain configuration logic living in the same place, which facilities the work towards a runtime-retargetable GHC (see #19877). As of this commit, the runtime linker/compiler logic was moved to autoconf, but soon it, and the rest of the existing toolchain configuration logic, will live in the standalone ghc-toolchain program (see !9263) In particular, what used to be done at runtime is now as follows: * The flags -Wl,--no-as-needed for needed shared libs are configured into settings * The flag -fstack-check is configured into settings * The check for broken tables-next-to-code was outdated * We use the configured c compiler by default as the assembler program * We drop `asmOpts` because we already configure -Qunused-arguments flag into settings (see !10589) Fixes #23562 Co-author: Rodrigo Mesquita (@alt-romes) - - - - - 8b35e8ca by Ben Gamari at 2023-06-29T18:46:12-04:00 Define FFI_GO_CLOSURES The libffi shipped with Apple's XCode toolchain does not contain a definition of the FFI_GO_CLOSURES macro, despite containing references to said macro. Work around this by defining the macro, following the model of a similar workaround in OpenJDK [1]. [1] https://github.com/openjdk/jdk17u-dev/pull/741/files - - - - - d7ef1704 by Ben Gamari at 2023-06-29T18:46:12-04:00 base: Fix incorrect CPP guard This was guarded on `darwin_HOST_OS` instead of `defined(darwin_HOST_OS)`. - - - - - 7c7d1f66 by Ben Gamari at 2023-06-29T18:46:48-04:00 rts/Trace: Ensure that debugTrace arguments are used As debugTrace is a macro we must take care to ensure that the fact is clear to the compiler lest we see warnings. - - - - - cb92051e by Ben Gamari at 2023-06-29T18:46:48-04:00 rts: Various warnings fixes - - - - - dec81dd1 by Ben Gamari at 2023-06-29T18:46:48-04:00 hadrian: Ignore warnings in unix and semaphore-compat - - - - - d7f6448a by Matthew Pickering at 2023-06-30T12:38:43-04:00 hadrian: Fix dependencies of docs:* rule For the docs:* rule we need to actually build the package rather than just the haddocks for the dependent packages. Therefore we depend on the .conf files of the packages we are trying to build documentation for as well as the .haddock files. Fixes #23472 - - - - - cec90389 by sheaf at 2023-06-30T12:39:27-04:00 Add tests for #22106 Fixes #22106 - - - - - 083794b1 by Torsten Schmits at 2023-07-03T03:27:27-04:00 Add -fbreak-points to control breakpoint insertion Rather than statically enabling breakpoints only for the interpreter, this adds a new flag. Tracking ticket: #23057 MR: !10466 - - - - - fd8c5769 by Ben Gamari at 2023-07-03T03:28:04-04:00 rts: Ensure that pinned allocations respect block size Previously, it was possible for pinned, aligned allocation requests to allocate beyond the end of the pinned accumulator block. Specifically, we failed to account for the padding needed to achieve the requested alignment in the "large object" check. With large alignment requests, this can result in the allocator using the capability's pinned object accumulator block to service a request which is larger than `PINNED_EMPTY_SIZE`. To fix this we reorganize `allocatePinned` to consistently account for the alignment padding in all large object checks. This is a bit subtle as we must handle the case of a small allocation request filling the accumulator block, as well as large requests. Fixes #23400. - - - - - 98185d52 by Ben Gamari at 2023-07-03T03:28:05-04:00 testsuite: Add test for #23400 - - - - - 4aac0540 by Ben Gamari at 2023-07-03T03:28:42-04:00 ghc-heap: Support for BLOCKING_QUEUE closures - - - - - 03f941f4 by Ben Bellick at 2023-07-03T03:29:29-04:00 Add some structured diagnostics in Tc/Validity.hs This addresses the work of ticket #20118 Created the following constructors for TcRnMessage - TcRnInaccessibleCoAxBranch - TcRnPatersonCondFailure - - - - - 6074cc3c by Moisés Ackerman at 2023-07-03T03:30:13-04:00 Add failing test case for #23492 - - - - - 356a2692 by Moisés Ackerman at 2023-07-03T03:30:13-04:00 Use generated src span for catch-all case of record selector functions This fixes #23492. The problem was that we used the real source span of the field declaration for the generated catch-all case in the selector function, in particular in the generated call to `recSelError`, which meant it was included in the HIE output. Using `generatedSrcSpan` instead means that it is not included. - - - - - 3efe7f39 by Moisés Ackerman at 2023-07-03T03:30:13-04:00 Introduce genLHsApp and genLHsLit helpers in GHC.Rename.Utils - - - - - dd782343 by Moisés Ackerman at 2023-07-03T03:30:13-04:00 Construct catch-all default case using helpers GHC.Rename.Utils concrete helpers instead of wrapGenSpan + HS AST constructors - - - - - 0e09c38e by Ryan Hendrickson at 2023-07-03T03:30:56-04:00 Add regression test for #23549 - - - - - 32741743 by Alexis King at 2023-07-03T03:31:36-04:00 perf tests: Increase default stack size for MultiLayerModules An unhelpfully small stack size appears to have been the real culprit behind the metric fluctuations in #19293. Debugging metric decreases triggered by !10729 helped to finally identify the problem. Metric Decrease: MultiLayerModules MultiLayerModulesTH_Make T13701 T14697 - - - - - 82ac6bf1 by Bryan Richter at 2023-07-03T03:32:15-04:00 Add missing void prototypes to rts functions See #23561. - - - - - 6078b429 by Ben Gamari at 2023-07-03T03:32:51-04:00 gitlab-ci: Refactor compilation of gen_ci Flakify and document it, making it far less sensitive to the build environment. - - - - - aa2db0ae by Ben Gamari at 2023-07-03T03:33:29-04:00 testsuite: Update documentation - - - - - 924a2362 by Gregory Gerasev at 2023-07-03T03:34:10-04:00 Better error for data deriving of type synonym/family. Closes #23522 - - - - - 4457da2a by Dave Barton at 2023-07-03T03:34:51-04:00 Fix some broken links and typos - - - - - de5830d0 by Ben Gamari at 2023-07-04T22:03:59-04:00 configure: Rip out Solaris dyld check Solaris 11 was released over a decade ago and, moreover, I doubt we have any Solaris users - - - - - 59c5fe1d by doyougnu at 2023-07-04T22:04:56-04:00 CI: add JS release and debug builds, regen CI jobs - - - - - 679bbc97 by Vladislav Zavialov at 2023-07-04T22:05:32-04:00 testsuite: Do not require CUSKs Numerous tests make use of CUSKs (complete user-supplied kinds), a legacy feature scheduled for deprecation. In order to proceed with the said deprecation, the tests have been updated to use SAKS instead (standalone kind signatures). This also allows us to remove the Haskell2010 language pragmas that were added in 115cd3c85a8 to work around the lack of CUSKs in GHC2021. - - - - - 945d3599 by Ben Gamari at 2023-07-04T22:06:08-04:00 gitlab: Drop backport-for-8.8 MR template Its usefulness has long passed. - - - - - 66c721d3 by Alan Zimmerman at 2023-07-04T22:06:44-04:00 EPA: Simplify GHC/Parser.y comb2 Use the HasLoc instance from Ast.hs to allow comb2 to work with anything with a SrcSpan This gets rid of the custom comb2A, comb2Al, comb2N functions, and removes various reLoc calls. - - - - - 2be99b7e by Matthew Pickering at 2023-07-04T22:07:21-04:00 Fix deprecation warning when deprecated identifier is from another module A stray 'Just' was being printed in the deprecation message. Fixes #23573 - - - - - 46c9bcd6 by Ben Gamari at 2023-07-04T22:07:58-04:00 rts: Don't rely on initializers for sigaction_t As noted in #23577, CentOS's ancient toolchain throws spurious missing-field-initializer warnings. - - - - - ec55035f by Ben Gamari at 2023-07-04T22:07:58-04:00 hadrian: Don't treat -Winline warnings as fatal Such warnings are highly dependent upon the toolchain, platform, and build configuration. It's simply too fragile to rely on these. - - - - - 3a09b789 by Ben Gamari at 2023-07-04T22:07:58-04:00 hadrian: Only pass -Wno-nonportable-include-path on Darwin This flag, which was introduced due to #17798, is only understood by Clang and consequently throws warnings on platforms using gcc. Sadly, there is no good way to treat such warnings as non-fatal with `-Werror` so for now we simply make this flag specific to platforms known to use Clang and case-insensitive filesystems (Darwin and Windows). See #23577. - - - - - 4af7eac2 by Mario Blažević at 2023-07-04T22:08:38-04:00 Fixed ticket #23571, TH.Ppr.pprLit hanging on large numeric literals - - - - - 2304c697 by Ben Gamari at 2023-07-04T22:09:15-04:00 compiler: Make OccSet opaque - - - - - cf735db8 by Andrei Borzenkov at 2023-07-04T22:09:51-04:00 Add Note about why we need forall in Code to be on the right - - - - - fb140f82 by Hécate Moonlight at 2023-07-04T22:10:34-04:00 Relax the constraint about the foreign function's calling convention of FinalizerPtr to capi as well as ccall. - - - - - 9ce44336 by meooow25 at 2023-07-05T11:42:37-04:00 Improve the situation with the stimes cycle Currently the Semigroup stimes cycle is resolved in GHC.Base by importing stimes implementations from a hs-boot file. Resolve the cycle using hs-boot files for required classes (Num, Integral) instead. Now stimes can be defined directly in GHC.Base, making inlining and specialization possible. This leads to some new boot files for `GHC.Num` and `GHC.Real`, the methods for those are only used to implement `stimes` so it doesn't appear that these boot files will introduce any new performance traps. Metric Decrease: T13386 T8095 Metric Increase: T13253 T13386 T18698a T18698b T19695 T8095 - - - - - 9edcb1fb by Jaro Reinders at 2023-07-05T11:43:24-04:00 Refactor Unique to be represented by Word64 In #22010 we established that Int was not always sufficient to store all the uniques we generate during compilation on 32-bit platforms. This commit addresses that problem by using Word64 instead of Int for uniques. The core of the change is in GHC.Core.Types.Unique and GHC.Core.Types.Unique.Supply. However, the representation of uniques is used in many other places, so those needed changes too. Additionally, the RTS has been extended with an atomic_inc64 operation. One major change from this commit is the introduction of the Word64Set and Word64Map data types. These are adapted versions of IntSet and IntMap from the containers package. These are planned to be upstreamed in the future. As a natural consequence of these changes, the compiler will be a bit slower and take more space on 32-bit platforms. Our CI tests indicate around a 5% residency increase. Metric Increase: CoOpt_Read CoOpt_Singletons LargeRecord ManyAlternatives ManyConstructors MultiComponentModules MultiComponentModulesRecomp MultiLayerModulesTH_OneShot RecordUpdPerf T10421 T10547 T12150 T12227 T12234 T12425 T12707 T13035 T13056 T13253 T13253-spj T13379 T13386 T13719 T14683 T14697 T14766 T15164 T15703 T16577 T16875 T17516 T18140 T18223 T18282 T18304 T18698a T18698b T18923 T1969 T19695 T20049 T21839c T3064 T3294 T4801 T5030 T5321FD T5321Fun T5631 T5642 T5837 T6048 T783 T8095 T9020 T9198 T9233 T9630 T9675 T9872a T9872b T9872b_defer T9872c T9872d T9961 TcPlugin_RewritePerf UniqLoop WWRec hard_hole_fits - - - - - 6b9db7d4 by Brandon Chinn at 2023-07-05T11:44:03-04:00 Fix docs for __GLASGOW_HASKELL_FULL_VERSION__ macro - - - - - 40f4ef7c by Torsten Schmits at 2023-07-05T18:06:19-04:00 Substitute free variables captured by breakpoints in SpecConstr Fixes #23267 - - - - - 2b55cb5f by sheaf at 2023-07-05T18:07:07-04:00 Reinstate untouchable variable error messages This extra bit of information was accidentally being discarded after a refactoring of the way we reported problems when unifying a type variable with another type. This patch rectifies that. - - - - - 53ed21c5 by Rodrigo Mesquita at 2023-07-05T18:07:47-04:00 configure: Drop Clang command from settings Due to 01542cb7227614a93508b97ecad5b16dddeb6486 we no longer use the `runClang` function, and no longer need to configure into settings the Clang command. We used to determine options at runtime to pass clang when it was used as an assembler, but now that we configure at configure time we no longer need to. - - - - - 6fdcf969 by Torsten Schmits at 2023-07-06T12:12:09-04:00 Filter out nontrivial substituted expressions in substTickish Fixes #23272 - - - - - 41968fd6 by Sylvain Henry at 2023-07-06T12:13:02-04:00 JS: testsuite: use req_c predicate instead of js_broken - - - - - 74a4dd2e by Sylvain Henry at 2023-07-06T12:13:02-04:00 JS: implement some file primitives (lstat,rmdir) (#22374) - Implement lstat and rmdir. - Implement base_c_s_is* functions (testing a file type) - Enable passing tests - - - - - 7e759914 by Sylvain Henry at 2023-07-07T02:39:38-04:00 JS: cleanup utils (#23314) - Removed unused code - Don't export unused functions - Move toTypeList to Closure module - - - - - f617655c by Sylvain Henry at 2023-07-07T02:39:38-04:00 JS: rename VarType/Vt into JSRep - - - - - 19216ca5 by Sylvain Henry at 2023-07-07T02:39:38-04:00 JS: remove custom PrimRep conversion (#23314) We use the usual conversion to PrimRep and then we convert these PrimReps to JSReps. - - - - - d3de8668 by Sylvain Henry at 2023-07-07T02:39:38-04:00 JS: don't use isRuntimeRepKindedTy in JS FFI - - - - - 8d1b75cb by Matthew Pickering at 2023-07-07T02:40:15-04:00 ghcup-metadata: Also updates ghcup-nightlies-0.0.7.yaml file Fixes #23600 - - - - - e524fa7f by Matthew Pickering at 2023-07-07T02:40:15-04:00 ghcup-metadata: Use dynamically linked alpine bindists In theory these will work much better on alpine to allow people to build statically linked applications there. We don't need to distribute a statically linked application ourselves in order to allow that. Fixes #23602 - - - - - 0c2a756e by sheaf at 2023-07-07T13:45:12+02:00 Avoid incomplete record update in Haddock Hoogle This commit avoids running into an incomplete record update warning in the Hoogle backend of Haddock. This was only noticed now, because incomplete record updates were broken in GHC 9.6. Now that they are fixed, we have to avoid running into them! - - - - - b9e7beb9 by Ben Gamari at 2023-07-07T11:32:22-04:00 Drop circle-ci-job.sh - - - - - 9955eead by Ben Gamari at 2023-07-07T11:32:22-04:00 testsuite: Allow preservation of unexpected output Here we introduce a new flag to the testsuite driver, --unexpected-output-dir=<dir>, which allows the user to ask the driver to preserve unexpected output from tests. The intent is for this to be used in CI to allow users to more easily fix unexpected platform-dependent output. - - - - - 48f80968 by Ben Gamari at 2023-07-07T11:32:22-04:00 gitlab-ci: Preserve unexpected output Here we enable use of the testsuite driver's `--unexpected-output-dir` flag by CI, preserving the result as an artifact for use by users. - - - - - 76983a0d by Matthew Pickering at 2023-07-07T11:32:58-04:00 driver: Fix -S with .cmm files There was an oversight in the driver which assumed that you would always produce a `.o` file when compiling a .cmm file. Fixes #23610 - - - - - 6df15e93 by Mike Pilgrem at 2023-07-07T11:33:40-04:00 Update Hadrian's stack.yaml - - - - - 1dff43cf by Ben Gamari at 2023-07-08T05:05:37-04:00 compiler: Rework ShowSome Previously the field used to filter the sub-declarations to show was rather ad-hoc and was only able to show at most one sub-declaration. - - - - - 8165404b by Ben Gamari at 2023-07-08T05:05:37-04:00 testsuite: Add test to catch changes in core libraries This adds testing infrastructure to ensure that changes in core libraries (e.g. `base` and `ghc-prim`) are caught in CI. - - - - - ec1c32e2 by Melanie Phoenix at 2023-07-08T05:06:14-04:00 Deprecate Data.List.NonEmpty.unzip - - - - - 5d2442b8 by Ben Gamari at 2023-07-08T05:06:51-04:00 Drop latent mentions of -split-objs Closes #21134. - - - - - a9bc20cb by Oleg Grenrus at 2023-07-08T05:07:31-04:00 Add warn_and_run test kind This is a compile_and_run variant which also captures the GHC's stderr. The warn_and_run name is best I can come up with, as compile_and_run is taken. This is useful specifically for testing warnings. We want to test that when warning triggers, and it's not a false positive, i.e. that the runtime behaviour is indeed "incorrect". As an example a single test is altered to use warn_and_run - - - - - c7026962 by Ben Gamari at 2023-07-08T05:08:11-04:00 configure: Don't use ld.gold on i386 ld.gold appears to produce invalid static constructor tables on i386. While ideally we would add an autoconf check to check for this brokenness, sadly such a check isn't easy to compose. Instead to summarily reject such linkers on i386. Somewhat hackily closes #23579. - - - - - 054261dd by Andrew Lelechenko at 2023-07-08T19:32:47-04:00 Add since annotations for Data.Foldable1 - - - - - 550af505 by Sylvain Henry at 2023-07-08T19:33:28-04:00 JS: support -this-unit-id for programs in the linker (#23613) - - - - - d284470a by Andrew Lelechenko at 2023-07-08T19:34:08-04:00 Bump text submodule - - - - - 8e11630e by jade at 2023-07-10T16:58:40-04:00 Add a hint to enable ExplicitNamespaces for type operator imports (Fixes/Enhances #20007) As suggested in #20007 and implemented in !8895, trying to import type operators will suggest a fix to use the 'type' keyword, without considering whether ExplicitNamespaces is enabled. This patch will query whether ExplicitNamespaces is enabled and add a hint to suggest enabling ExplicitNamespaces if it isn't enabled, alongside the suggestion of adding the 'type' keyword. - - - - - 61b1932e by sheaf at 2023-07-10T16:59:26-04:00 tyThingLocalGREs: include all DataCons for RecFlds The GREInfo for a record field should include the collection of all the data constructors of the parent TyCon that have this record field. This information was being incorrectly computed in the tyThingLocalGREs function for a DataCon, as we were not taking into account other DataCons with the same parent TyCon. Fixes #23546 - - - - - e6627cbd by Alan Zimmerman at 2023-07-10T17:00:05-04:00 EPA: Simplify GHC/Parser.y comb3 A follow up to !10743 - - - - - ee20da34 by Andrew Lelechenko at 2023-07-10T17:01:01-04:00 Document that compareByteArrays# is available since ghc-prim-0.5.2.0 - - - - - 4926af7b by Matthew Pickering at 2023-07-10T17:01:38-04:00 Revert "Bump text submodule" This reverts commit d284470a77042e6bc17bdb0ab0d740011196958a. This commit requires that we bootstrap with ghc-9.4, which we do not require until #23195 has been completed. Subsequently this has broken nighty jobs such as the rocky8 job which in turn has broken nightly releases. - - - - - d1c92bf3 by Ben Gamari at 2023-07-11T08:07:02-04:00 compiler: Fingerprint more code generation flags Previously our recompilation check was quite inconsistent in its coverage of non-optimisation code generation flags. Specifically, we failed to account for most flags that would affect the behavior of generated code in ways that might affect the result of a program's execution (e.g. `-feager-blackholing`, `-fstrict-dicts`) Closes #23369. - - - - - eb623149 by Ben Gamari at 2023-07-11T08:07:02-04:00 compiler: Record original thunk info tables on stack Here we introduce a new code generation option, `-forig-thunk-info`, which ensures that an `stg_orig_thunk_info` frame is pushed before every update frame. This can be invaluable when debugging thunk cycles and similar. See Note [Original thunk info table frames] for details. Closes #23255. - - - - - 4731f44e by Jaro Reinders at 2023-07-11T08:07:40-04:00 Fix wrong MIN_VERSION_GLASGOW_HASKELL macros I forgot to change these after rebasing. - - - - - dd38aca9 by Andreas Schwab at 2023-07-11T13:55:56+00:00 Hadrian: enable GHCi support on riscv64 - - - - - 09a5c6cc by Josh Meredith at 2023-07-12T11:25:13-04:00 JavaScript: support unicode code points > 2^16 in toJSString using String.fromCodePoint (#23628) - - - - - 29fbbd4e by Matthew Pickering at 2023-07-12T11:25:49-04:00 Remove references to make build system in mk/build.mk Fixes #23636 - - - - - 630e3026 by sheaf at 2023-07-12T11:26:43-04:00 Valid hole fits: don't panic on a Given The function GHC.Tc.Errors.validHoleFits would end up panicking when encountering a Given constraint. To fix this, it suffices to filter out the Givens before continuing. Fixes #22684 - - - - - c39f279b by Matthew Pickering at 2023-07-12T23:18:38-04:00 Use deb10 for i386 bindists deb9 is now EOL so it's time to upgrade the i386 bindist to use deb10 Fixes #23585 - - - - - bf9b9de0 by Krzysztof Gogolewski at 2023-07-12T23:19:15-04:00 Fix #23567, a specializer bug Found by Simon in https://gitlab.haskell.org/ghc/ghc/-/issues/23567#note_507834 The testcase isn't ideal because it doesn't detect the bug in master, unless doNotUnbox is removed as in https://gitlab.haskell.org/ghc/ghc/-/issues/23567#note_507692. But I have confirmed that with that modification, it fails before and passes afterwards. - - - - - 84c1a4a2 by Bartłomiej Cieślar at 2023-07-12T23:20:08-04:00 Comments - - - - - b2846cb5 by Bartłomiej Cieślar at 2023-07-12T23:20:08-04:00 updates to comments - - - - - 2af23f0e by Bartłomiej Cieślar at 2023-07-12T23:20:08-04:00 changes - - - - - 6143838a by sheaf at 2023-07-13T08:02:17-04:00 Fix deprecation of record fields Commit 3f374399 inadvertently broke the deprecation/warning mechanism for record fields due to its introduction of record field namespaces. This patch ensures that, when a top-level deprecation is applied to an identifier, it applies to all the record fields as well. This is achieved by refactoring GHC.Rename.Env.lookupLocalTcNames, and GHC.Rename.Env.lookupBindGroupOcc, to not look up a fixed number of NameSpaces but to look up all NameSpaces and filter out the irrelevant ones. - - - - - 6fd8f566 by sheaf at 2023-07-13T08:02:17-04:00 Introduce greInfo, greParent These are simple helper functions that wrap the internal field names gre_info, gre_par. - - - - - 7f0a86ed by sheaf at 2023-07-13T08:02:17-04:00 Refactor lookupGRE_... functions This commit consolidates all the logic for looking up something in the Global Reader Environment into the single function lookupGRE. This allows us to declaratively specify all the different modes of looking up in the GlobalRdrEnv, and avoids manually passing around filtering functions as was the case in e.g. the function GHC.Rename.Env.lookupSubBndrOcc_helper. ------------------------- Metric Decrease: T8095 ------------------------- ------------------------- Metric Increase: T8095 ------------------------- - - - - - 5e951395 by Rodrigo Mesquita at 2023-07-13T08:02:54-04:00 configure: Drop DllWrap command We used to configure into settings a DllWrap command for windows builds and distributions, however, we no longer do, and dllwrap is effectively unused. This simplification is motivated in part by the larger toolchain-selection project (#19877, !9263) - - - - - e10556b6 by Teo Camarasu at 2023-07-14T16:28:46-04:00 base: fix haddock syntax in GHC.Profiling - - - - - 0f3fda81 by Matthew Pickering at 2023-07-14T16:29:23-04:00 Revert "CI: add JS release and debug builds, regen CI jobs" This reverts commit 59c5fe1d4b624423b1c37891710f2757bb58d6af. This commit added two duplicate jobs on all validate pipelines, so we are reverting for now whilst we work out what the best way forward is. Ticket #23618 - - - - - 54bca324 by Alan Zimmerman at 2023-07-15T03:23:26-04:00 EPA: Simplify GHC/Parser.y sLL Follow up to !10743 - - - - - c8863828 by sheaf at 2023-07-15T03:24:06-04:00 Configure: canonicalise PythonCmd on Windows This change makes PythonCmd resolve to a canonical absolute path on Windows, which prevents HLS getting confused (now that we have a build-time dependency on python). fixes #23652 - - - - - ca1e636a by Rodrigo Mesquita at 2023-07-15T03:24:42-04:00 Improve Note [Binder-swap during float-out] - - - - - cf86f3ec by Matthew Craven at 2023-07-16T01:42:09+02:00 Equality of forall-types is visibility aware This patch finally (I hope) nails the question of whether (forall a. ty) and (forall a -> ty) are `eqType`: they aren't! There is a long discussion in #22762, plus useful Notes: * Note [ForAllTy and type equality] in GHC.Core.TyCo.Compare * Note [Comparing visiblities] in GHC.Core.TyCo.Compare * Note [ForAllCo] in GHC.Core.TyCo.Rep It also establishes a helpful new invariant for ForAllCo, and ForAllTy, when the bound variable is a CoVar:in that case the visibility must be coreTyLamForAllTyFlag. All this is well documented in revised Notes. - - - - - 7f13acbf by Vladislav Zavialov at 2023-07-16T01:56:27-04:00 List and Tuple<n>: update documentation Add the missing changelog.md entries and @since-annotations. - - - - - 2afbddb0 by Andrei Borzenkov at 2023-07-16T10:21:24+04:00 Type patterns (#22478, #18986) Improved name resolution and type checking of type patterns in constructors: 1. HsTyPat: a new dedicated data type that represents type patterns in HsConPatDetails instead of reusing HsPatSigType 2. rnHsTyPat: a new function that renames a type pattern and collects its binders into three groups: - explicitly bound type variables, excluding locally bound variables - implicitly bound type variables from kind signatures (only if ScopedTypeVariables are enabled) - named wildcards (only from kind signatures) 2a. rnHsPatSigTypeBindingVars: removed in favour of rnHsTyPat 2b. rnImplcitTvBndrs: removed because no longer needed 3. collect_pat: updated to collect type variable binders from type patterns (this means that types and terms use the same infrastructure to detect conflicting bindings, unused variables and name shadowing) 3a. CollVarTyVarBinders: a new CollectFlag constructor that enables collection of type variables 4. tcHsTyPat: a new function that typechecks type patterns, capable of handling polymorphic kinds. See Note [Type patterns: binders and unifiers] Examples of code that is now accepted: f = \(P @a) -> \(P @a) -> ... -- triggers -Wname-shadowing g :: forall a. Proxy a -> ... g (P @a) = ... -- also triggers -Wname-shadowing h (P @($(TH.varT (TH.mkName "t")))) = ... -- t is bound at splice time j (P @(a :: (x,x))) = ... -- (x,x) is no longer rejected data T where MkT :: forall (f :: forall k. k -> Type). f Int -> f Maybe -> T k :: T -> () k (MkT @f (x :: f Int) (y :: f Maybe)) = () -- f :: forall k. k -> Type Examples of code that is rejected with better error messages: f (Left @a @a _) = ... -- new message: -- • Conflicting definitions for ‘a’ -- Bound at: Test.hs:1:11 -- Test.hs:1:14 Examples of code that is now rejected: {-# OPTIONS_GHC -Werror=unused-matches #-} f (P @a) = () -- Defined but not used: type variable ‘a’ - - - - - eb1a6ab1 by sheaf at 2023-07-16T09:20:45-04:00 Don't use substTyUnchecked in newMetaTyVar There were some comments that explained that we needed to use an unchecked substitution function because of issue #12931, but that has since been fixed, so we should be able to use substTy instead now. - - - - - c7bbad9a by sheaf at 2023-07-17T02:48:19-04:00 rnImports: var shouldn't import NoFldSelectors In an import declaration such as import M ( var ) the import of the variable "var" should **not** bring into scope record fields named "var" which are defined with NoFieldSelectors. Doing so can cause spurious "unused import" warnings, as reported in ticket #23557. Fixes #23557 - - - - - 1af2e773 by sheaf at 2023-07-17T02:48:19-04:00 Suggest similar names in imports This commit adds similar name suggestions when importing. For example module A where { spelling = 'o' } module B where { import B ( speling ) } will give rise to the error message: Module ‘A’ does not export ‘speling’. Suggested fix: Perhaps use ‘spelling’ This also provides hints when users try to import record fields defined with NoFieldSelectors. - - - - - 654fdb98 by Alan Zimmerman at 2023-07-17T02:48:55-04:00 EPA: Store leading AnnSemi for decllist in al_rest This simplifies the markAnnListA implementation in ExactPrint - - - - - 22565506 by sheaf at 2023-07-17T21:12:59-04:00 base: add COMPLETE pragma to BufferCodec PatSyn This implements CLC proposal #178, rectifying an oversight in the implementation of CLC proposal #134 which could lead to spurious pattern match warnings. https://github.com/haskell/core-libraries-committee/issues/178 https://github.com/haskell/core-libraries-committee/issues/134 - - - - - 860f6269 by sheaf at 2023-07-17T21:13:00-04:00 exactprint: silence incomplete record update warnings - - - - - df706de3 by sheaf at 2023-07-17T21:13:00-04:00 Re-instate -Wincomplete-record-updates Commit e74fc066 refactored the handling of record updates to use the HsExpanded mechanism. This meant that the pattern matching inherent to a record update was considered to be "generated code", and thus we stopped emitting "incomplete record update" warnings entirely. This commit changes the "data Origin = Source | Generated" datatype, adding a field to the Generated constructor to indicate whether we still want to perform pattern-match checking. We also have to do a bit of plumbing with HsCase, to record that the HsCase arose from an HsExpansion of a RecUpd, so that the error message continues to mention record updates as opposed to a generic "incomplete pattern matches in case" error. Finally, this patch also changes the way we handle inaccessible code warnings. Commit e74fc066 was also a regression in this regard, as we were emitting "inaccessible code" warnings for case statements spuriously generated when desugaring a record update (remember: the desugaring mechanism happens before typechecking; it thus can't take into account e.g. GADT information in order to decide which constructors to include in the RHS of the desugaring of the record update). We fix this by changing the mechanism through which we disable inaccessible code warnings: we now check whether we are in generated code in GHC.Tc.Utils.TcMType.newImplication in order to determine whether to emit inaccessible code warnings. Fixes #23520 Updates haddock submodule, to avoid incomplete record update warnings - - - - - 1d05971e by sheaf at 2023-07-17T21:13:00-04:00 Propagate long-distance information in do-notation The preceding commit re-enabled pattern-match checking inside record updates. This revealed that #21360 was in fact NOT fixed by e74fc066. This commit makes sure we correctly propagate long-distance information in do blocks, e.g. in ```haskell data T = A { fld :: Int } | B f :: T -> Maybe T f r = do a at A{} <- Just r Just $ case a of { A _ -> A 9 } ``` we need to propagate the fact that "a" is headed by the constructor "A" to see that the case expression "case a of { A _ -> A 9 }" cannot fail. Fixes #21360 - - - - - bea0e323 by sheaf at 2023-07-17T21:13:00-04:00 Skip PMC for boring patterns Some patterns introduce no new information to the pattern-match checker (such as plain variable or wildcard patterns). We can thus skip doing any pattern-match checking on them when the sole purpose for doing so was introducing new long-distance information. See Note [Boring patterns] in GHC.Hs.Pat. Doing this avoids regressing in performance now that we do additional pattern-match checking inside do notation. - - - - - ddcdd88c by Rodrigo Mesquita at 2023-07-17T21:13:36-04:00 Split GHC.Platform.ArchOS from ghc-boot into ghc-platform Split off the `GHC.Platform.ArchOS` module from the `ghc-boot` package into this reinstallable standalone package which abides by the PVP, in part motivated by the ongoing work on `ghc-toolchain` towards runtime retargetability. - - - - - b55a8ea7 by Sylvain Henry at 2023-07-17T21:14:27-04:00 JS: better implementation for plusWord64 (#23597) - - - - - 889c2bbb by sheaf at 2023-07-18T06:37:32-04:00 Do primop rep-poly checks when instantiating This patch changes how we perform representation-polymorphism checking for primops (and other wired-in Ids such as coerce). When instantiating the primop, we check whether each type variable is required to instantiated to a concrete type, and if so we create a new concrete metavariable (a ConcreteTv) instead of a simple MetaTv. (A little subtlety is the need to apply the substitution obtained from instantiating to the ConcreteTvOrigins, see Note [substConcreteTvOrigin] in GHC.Tc.Utils.TcMType.) This allows us to prevent representation-polymorphism in non-argument position, as that is required for some of these primops. We can also remove the logic in tcRemainingValArgs, except for the part concerning representation-polymorphic unlifted newtypes. The function has been renamed rejectRepPolyNewtypes; all it does now is reject unsaturated occurrences of representation-polymorphic newtype constructors when the representation of its argument isn't a concrete RuntimeRep (i.e. still a PHASE 1 FixedRuntimeRep check). The Note [Eta-expanding rep-poly unlifted newtypes] in GHC.Tc.Gen.Head gives more explanation about a possible path to PHASE 2, which would be in line with the treatment for primops taken in this patch. We also update the Core Lint check to handle this new framework. This means Core Lint now checks representation-polymorphism in continuation position like needed for catch#. Fixes #21906 ------------------------- Metric Increase: LargeRecord ------------------------- - - - - - 00648e5d by Krzysztof Gogolewski at 2023-07-18T06:38:10-04:00 Core Lint: distinguish let and letrec in locations Lint messages were saying "in the body of letrec" even for non-recursive let. I've also renamed BodyOfLetRec to BodyOfLet in stg, since there's no separate letrec. - - - - - 787bae96 by Krzysztof Gogolewski at 2023-07-18T06:38:50-04:00 Use extended literals when deriving Show This implements GHC proposal https://github.com/ghc-proposals/ghc-proposals/pull/596 Also add support for Int64# and Word64#; see testcase ShowPrim. - - - - - 257f1567 by Jaro Reinders at 2023-07-18T06:39:29-04:00 Add StgFromCore and StgCodeGen linting - - - - - 34d08a20 by Ben Gamari at 2023-07-19T03:33:22-04:00 Reg.Liveness: Strictness - - - - - c5deaa27 by Ben Gamari at 2023-07-19T03:33:22-04:00 Reg.Liveness: Don't repeatedly construct UniqSets - - - - - b947250b by Ben Gamari at 2023-07-19T03:33:22-04:00 compiler/Types: Ensure that fromList-type operations can fuse In #20740 I noticed that mkUniqSet does not fuse. In practice, allowing it to do so makes a considerable difference in allocations due to the backend. Metric Decrease: T12707 T13379 T3294 T4801 T5321FD T5321Fun T783 - - - - - 6c88c2ba by Sven Tennie at 2023-07-19T03:33:59-04:00 x86 Codegen: Implement MO_S_MulMayOflo for W16 - - - - - 5f1154e0 by Sven Tennie at 2023-07-19T03:33:59-04:00 x86 CodeGen: MO_S_MulMayOflo better error message for rep > W64 It's useful to see which value made the pattern match fail. (If it ever occurs.) - - - - - e8c9a95f by Sven Tennie at 2023-07-19T03:33:59-04:00 x86 CodeGen: Implement MO_S_MulMayOflo for W8 This case wasn't handled before. But, the test-primops test suite showed that it actually might appear. - - - - - a36f9dc9 by Sven Tennie at 2023-07-19T03:33:59-04:00 Add test for %mulmayoflo primop The test expects a perfect implementation with no false positives. - - - - - 38a36248 by Matthew Pickering at 2023-07-19T03:34:36-04:00 lint-ci-config: Generate jobs-metadata.json We also now save the jobs-metadata.json and jobs.yaml file as artifacts as: * It might be useful for someone who is modifying CI to copy jobs.yaml if they are having trouble regenerating locally. * jobs-metadata.json is very useful for downstream pipelines to work out the right job to download. Fixes #23654 - - - - - 1535a671 by Vladislav Zavialov at 2023-07-19T03:35:12-04:00 Initialize 9.10.1-notes.rst Create new release notes for the next GHC release (GHC 9.10) - - - - - 3bd4d5b5 by sheaf at 2023-07-19T03:35:53-04:00 Prioritise Parent when looking up class sub-binder When we look up children GlobalRdrElts of a given Parent, we sometimes would rather prioritise those GlobalRdrElts which have the right Parent, and sometimes prioritise those that have the right NameSpace: - in export lists, we should prioritise NameSpace - for class/instance binders, we should prioritise Parent See Note [childGREPriority] in GHC.Types.Name.Reader. fixes #23664 - - - - - 9c8fdda3 by Alan Zimmerman at 2023-07-19T03:36:29-04:00 EPA: Improve annotation management in getMonoBind Ensure the LHsDecl for a FunBind has the correct leading comments and trailing annotations. See the added note for details. - - - - - ff884b77 by Matthew Pickering at 2023-07-19T11:42:02+01:00 Remove unused files in .gitlab These were left over after 6078b429 - - - - - 29ef590c by Matthew Pickering at 2023-07-19T11:42:52+01:00 gen_ci: Add hie.yaml file This allows you to load `gen_ci.hs` into HLS, and now it is a huge module, that is quite useful. - - - - - 808b55cf by Matthew Pickering at 2023-07-19T12:24:41+01:00 ci: Make "fast-ci" the default validate configuration We are trying out a lighter weight validation pipeline where by default we just test on 5 platforms: * x86_64-deb10-slow-validate * windows * x86_64-fedora33-release * aarch64-darwin * aarch64-linux-deb10 In order to enable the "full" validation pipeline you can apply the `full-ci` label which will enable all the validation pipelines. All the validation jobs are still run on a marge batch. The goal is to reduce the overall CI capacity so that pipelines start faster for MRs and marge bot batches are faster. Fixes #23694 - - - - - 0b23db03 by Alan Zimmerman at 2023-07-20T05:28:47-04:00 EPA: Simplify GHC/Parser.y sL1 This is the next patch in a series simplifying location management in GHC/Parser.y This one simplifies sL1, to use the HasLoc instances introduced in !10743 (closed) - - - - - 3ece9856 by Ben Gamari at 2023-07-21T07:30:45-04:00 nativeGen: Explicitly set flags of text sections on Windows The binutils documentation (for COFF) claims, > If no flags are specified, the default flags depend upon the section > name. If the section name is not recognized, the default will be for the > section to be loaded and writable. We previously assumed that this would do the right thing for split sections (e.g. a section named `.text$foo` would be correctly inferred to be a text section). However, we have observed that this is not the case (at least under the clang toolchain used on Windows): when split-sections is enabled, text sections are treated by the assembler as data (matching the "default" behavior specified by the documentation). Avoid this by setting section flags explicitly. This should fix split sections on Windows. Fixes #22834. - - - - - db7f7240 by Ben Gamari at 2023-07-21T07:30:45-04:00 nativeGen: Set explicit section types on all platforms - - - - - b444c16f by Finley McIlwaine at 2023-07-21T07:31:28-04:00 Insert documentation into parsed signature modules Causes haddock comments in signature modules to be properly inserted into the AST (just as they are for regular modules) if the `-haddock` flag is given. Also adds a test that compares `-ddump-parsed-ast` output for a signature module to prevent further regressions. Fixes #23315 - - - - - f9b952a7 by Ben Gamari at 2023-07-21T11:58:05-04:00 Bump base bound to <4.20 For GHC 9.8. - - - - - c30cea53 by Ben Gamari at 2023-07-21T23:23:49-04:00 primops: Introduce unsafeThawByteArray# This addresses an odd asymmetry in the ByteArray# primops, which previously provided unsafeFreezeByteArray# but no corresponding thaw operation. Closes #22710 - - - - - 87f9bd47 by Ben Gamari at 2023-07-21T23:23:49-04:00 testsuite: Elaborate in interface stability README This discussion didn't make it into the original MR. - - - - - e4350b41 by Matthew Pickering at 2023-07-21T23:24:25-04:00 Allow users to override non-essential haddock options in a Flavour We now supply the non-essential options to haddock using the `extraArgs` field, which can be specified in a Flavour so that if an advanced user wants to change how documentation is generated then they can use something other than the `defaultHaddockExtraArgs`. This does have the potential to regress some packaging if a user has overridden `extraArgs` themselves, because now they also need to add the haddock options to extraArgs. This can easily be done by appending `defaultHaddockExtraArgs` to their extraArgs invocation but someone might not notice this behaviour has changed. In any case, I think passing the non-essential options in this manner is the right thing to do and matches what we do for the "ghc" builder, which by default doesn't pass any optmisation levels, and would likewise be very bad if someone didn't pass suitable `-O` levels for builds. Fixes #23625 - - - - - fc186b0c by Ilias Tsitsimpis at 2023-07-21T23:25:03-04:00 ghc-prim: Link against libatomic Commit b4d39adbb58 made 'hs_cmpxchg64()' available to all architectures. Unfortunately this made GHC to fail to build on armel, since armel needs libatomic to support atomic operations on 64-bit word sizes. Configure libraries/ghc-prim/ghc-prim.cabal to link against libatomic, the same way as we do in rts/rts.cabal. - - - - - 4f5538a8 by Matthew Pickering at 2023-07-21T23:25:39-04:00 simplifier: Correct InScopeSet in rule matching The in-scope set passedto the `exprIsLambda_maybe` call lacked all the in-scope binders. @simonpj suggests this fix where we augment the in-scope set with the free variables of expression which fixes this failure mode in quite a direct way. Fixes #23630 - - - - - 5ad8d597 by Krzysztof Gogolewski at 2023-07-21T23:26:17-04:00 Add a test for #23413 It was fixed by commit e1590ddc661d6: Add the SolverStage monad. - - - - - 7e05f6df by sheaf at 2023-07-21T23:26:56-04:00 Finish migration of diagnostics in GHC.Tc.Validity This patch finishes migrating the error messages in GHC.Tc.Validity to use the new diagnostic infrastructure. It also refactors the error message datatypes for class and family instances, to common them up under a single datatype as much as possible. - - - - - 4876fddc by Matthew Pickering at 2023-07-21T23:27:33-04:00 ci: Enable some more jobs to run in a marge batch In !10907 I made the majority of jobs not run on a validate pipeline but then forgot to renable a select few jobs on the marge batch MR. - - - - - 026991d7 by Jens Petersen at 2023-07-21T23:28:13-04:00 user_guide/flags.py: python-3.12 no longer includes distutils packaging.version seems able to handle this fine - - - - - b91bbc2b by Matthew Pickering at 2023-07-21T23:28:50-04:00 ci: Mention ~full-ci label in MR template We mention that if you need a full validation pipeline then you can apply the ~full-ci label to your MR in order to test against the full validation pipeline (like we do for marge). - - - - - 42b05e9b by sheaf at 2023-07-22T12:36:00-04:00 RTS: declare setKeepCAFs symbol Commit 08ba8720 failed to declare the dependency of keepCAFsForGHCi on the symbol setKeepCAFs in the RTS, which led to undefined symbol errors on Windows, as exhibited by the testcase frontend001. Thanks to Moritz Angermann and Ryan Scott for the diagnosis and fix. Fixes #22961 - - - - - a72015d6 by sheaf at 2023-07-22T12:36:01-04:00 Mark plugins-external as broken on Windows This test is broken on Windows, so we explicitly mark it as such now that we stop skipping plugin tests on Windows. - - - - - cb9c93d7 by sheaf at 2023-07-22T12:36:01-04:00 Stop marking plugin tests as fragile on Windows Now that b2bb3e62 has landed we are in a better situation with regards to plugins on Windows, allowing us to unmark many plugin tests as fragile. Fixes #16405 - - - - - a7349217 by Krzysztof Gogolewski at 2023-07-22T12:36:37-04:00 Misc cleanup - Remove unused RDR names - Fix typos in comments - Deriving: simplify boxConTbl and remove unused litConTbl - chmod -x GHC/Exts.hs, this seems accidental - - - - - 33b6850a by Vladislav Zavialov at 2023-07-23T10:27:37-04:00 Visible forall in types of terms: Part 1 (#22326) This patch implements part 1 of GHC Proposal #281, introducing explicit `type` patterns and `type` arguments. Summary of the changes: 1. New extension flag: RequiredTypeArguments 2. New user-facing syntax: `type p` patterns (represented by EmbTyPat) `type e` expressions (represented by HsEmbTy) 3. Functions with required type arguments (visible forall) can now be defined and applied: idv :: forall a -> a -> a -- signature (relevant change: checkVdqOK in GHC/Tc/Validity.hs) idv (type a) (x :: a) = x -- definition (relevant change: tcPats in GHC/Tc/Gen/Pat.hs) x = idv (type Int) 42 -- usage (relevant change: tcInstFun in GHC/Tc/Gen/App.hs) 4. template-haskell support: TH.TypeE corresponds to HsEmbTy TH.TypeP corresponds to EmbTyPat 5. Test cases and a new User's Guide section Changes *not* included here are the t2t (term-to-type) transformation and term variable capture; those belong to part 2. - - - - - 73b5c7ce by sheaf at 2023-07-23T10:28:18-04:00 Add test for #22424 This is a simple Template Haskell test in which we refer to record selectors by their exact Names, in two different ways. Fixes #22424 - - - - - 83cbc672 by Ben Gamari at 2023-07-24T07:40:49+00:00 ghc-toolchain: Initial commit - - - - - 31dcd26c by Rodrigo Mesquita at 2023-07-24T07:40:49+00:00 ghc-toolchain: Toolchain Selection This commit integrates ghc-toolchain, the brand new way of configuring toolchains for GHC, with the Hadrian build system, with configure, and extends and improves the first iteration of ghc-toolchain. The general overview is * We introduce a program invoked `ghc-toolchain --triple=...` which, when run, produces a file with a `Target`. A `GHC.Toolchain.Target.Target` describes the properties of a target and the toolchain (executables and configured flags) to produce code for that target * Hadrian was modified to read Target files, and will both * Invoke the toolchain configured in the Target file as needed * Produce a `settings` file for GHC based on the Target file for that stage * `./configure` will invoke ghc-toolchain to generate target files, but it will also generate target files based on the flags configure itself configured (through `.in` files that are substituted) * By default, the Targets generated by configure are still (for now) the ones used by Hadrian * But we additionally validate the Target files generated by ghc-toolchain against the ones generated by configure, to get a head start on catching configuration bugs before we transition completely. * When we make that transition, we will want to drop a lot of the toolchain configuration logic from configure, but keep it otherwise. * For each compiler stage we should have 1 target file (up to a stage compiler we can't run in our machine) * We just have a HOST target file, which we use as the target for stage0 * And a TARGET target file, which we use for stage1 (and later stages, if not cross compiling) * Note there is no BUILD target file, because we only support cross compilation where BUILD=HOST * (for more details on cross-compilation see discussion on !9263) See also * Note [How we configure the bundled windows toolchain] * Note [ghc-toolchain consistency checking] * Note [ghc-toolchain overview] Ticket: #19877 MR: !9263 - - - - - a732b6d3 by Rodrigo Mesquita at 2023-07-24T07:40:49+00:00 Add flag to enable/disable ghc-toolchain based configurations This flag is disabled by default, and we'll use the configure-generated-toolchains by default until we remove the toolchain configuration logic from configure. - - - - - 61eea240 by Rodrigo Mesquita at 2023-07-24T07:40:49+00:00 Split ghc-toolchain executable to new packge In light of #23690, we split the ghc-toolchain executable out of the library package to be able to ship it in the bindist using Hadrian. Ideally, we eventually revert this commit. - - - - - 38e795ff by Rodrigo Mesquita at 2023-07-24T07:40:49+00:00 Ship ghc-toolchain in the bindist Add the ghc-toolchain binary to the binary distribution we ship to users, and teach the bindist configure to use the existing ghc-toolchain. - - - - - 32cae784 by Matthew Craven at 2023-07-24T16:48:24-04:00 Kill off gen_bytearray_addr_access_ops.py The relevant primop descriptions are now generated directly by genprimopcode. This makes progress toward fixing #23490, but it is not a complete fix since there is more than one way in which cabal-reinstall (hadrian/build build-cabal) is broken. - - - - - 02e6a6ce by Matthew Pickering at 2023-07-24T16:49:00-04:00 compiler: Remove unused `containers.h` include Fixes #23712 - - - - - 822ef66b by Matthew Pickering at 2023-07-25T08:44:50-04:00 Fix pretty printing of WARNING pragmas There is still something quite unsavoury going on with WARNING pragma printing because the printing relies on the fact that for decl deprecations the SourceText of WarningTxt is empty. However, I let that lion sleep and just fixed things directly. Fixes #23465 - - - - - e7b38ede by Matthew Pickering at 2023-07-25T08:45:28-04:00 ci-images: Bump to commit which has 9.6 image The test-bootstrap job has been failing for 9.6 because we accidentally used a non-master commit. - - - - - bb408936 by Matthew Pickering at 2023-07-25T08:45:28-04:00 Update bootstrap plans for 9.6.2 and 9.4.5 - - - - - 355e1792 by Alan Zimmerman at 2023-07-26T10:17:32-04:00 EPA: Simplify GHC/Parser.y comb4/comb5 Use the HasLoc instance from Ast.hs to allow comb4/comb5 to work with anything with a SrcSpan Also get rid of some more now unnecessary reLoc calls. - - - - - 9393df83 by Gavin Zhao at 2023-07-26T10:18:16-04:00 compiler: make -ddump-asm work with wasm backend NCG Fixes #23503. Now the `-ddump-asm` flag is respected in the wasm backend NCG, so developers can directly view the generated ASM instead of needing to pass `-S` or `-keep-tmp-files` and manually find & open the assembly file. Ideally, we should be able to output the assembly files in smaller chunks like in other NCG backends. This would also make dumping assembly stats easier. However, this would require a large refactoring, so for short-term debugging purposes I think the current approach works fine. Signed-off-by: Gavin Zhao <git at gzgz.dev> - - - - - 79463036 by Krzysztof Gogolewski at 2023-07-26T10:18:54-04:00 llvm: Restore accidentally deleted code in 0fc5cb97 Fixes #23711 - - - - - 20db7e26 by Rodrigo Mesquita at 2023-07-26T10:19:33-04:00 configure: Default missing options to False when preparing ghc-toolchain Targets This commit fixes building ghc with 9.2 as the boostrap compiler. The ghc-toolchain patch assumed all _STAGE0 options were available, and forgot to account for this missing information in 9.2. Ghc 9.2 does not have in settings whether ar supports -l, hence can't report it with --info (unliked 9.4 upwards). The fix is to default the missing information (we default "ar supports -l" and other missing options to False) - - - - - fac9e84e by Naïm Favier at 2023-07-26T10:20:16-04:00 docs: Fix typo - - - - - 503fd647 by Bartłomiej Cieślar at 2023-07-26T17:23:10-04:00 This MR is an implementation of the proposal #516. It adds a warning -Wincomplete-record-selectors for usages of a record field access function (either a record selector or getField @"rec"), while trying to silence the warning whenever it can be sure that a constructor without the record field would not be invoked (which would otherwise cause the program to fail). For example: data T = T1 | T2 {x :: Bool} f a = x a -- this would throw an error g T1 = True g a = x a -- this would not throw an error h :: HasField "x" r Bool => r -> Bool h = getField @"x" j :: T -> Bool j = h -- this would throw an error because of the `HasField` -- constraint being solved See the tests DsIncompleteRecSel* and TcIncompleteRecSel for more examples of the warning. See Note [Detecting incomplete record selectors] in GHC.HsToCore.Expr for implementation details - - - - - af6fdf42 by Arnaud Spiwack at 2023-07-26T17:23:52-04:00 Fix user-facing label in MR template - - - - - 5d45b92a by Matthew Pickering at 2023-07-27T05:46:46-04:00 ci: Test bootstrapping configurations with full-ci and on marge batches There have been two incidents recently where bootstrapping has been broken by removing support for building with 9.2.*. The process for bumping the minimum required version starts with bumping the configure version and then other CI jobs such as the bootstrap jobs have to be updated. We must not silently bump the minimum required version. Now we are running a slimmed down validate pipeline it seems worthwile to test these bootstrap configurations in the full-ci pipeline. - - - - - 25d4fee7 by Matthew Pickering at 2023-07-27T05:46:46-04:00 bootstrap: Remove ghc-9_2_* plans We are anticipating shortly making it necessary to use ghc-9.4 to boot the compiler. - - - - - 2f66da16 by Matthew Pickering at 2023-07-27T05:46:46-04:00 Update bootstrap plans for ghc-platform and ghc-toolchain dependencies Fixes #23735 - - - - - c8c6eab1 by Matthew Pickering at 2023-07-27T05:46:46-04:00 bootstrap: Disable -selftest flag from bootstrap plans This saves on building one dependency (QuickCheck) which is unecessary for bootstrapping. - - - - - a80ca086 by Andrew Lelechenko at 2023-07-27T05:47:26-04:00 Link reference paper and package from System.Mem.{StableName,Weak} - - - - - a5319358 by David Knothe at 2023-07-28T13:13:10-04:00 Update Match Datatype EquationInfo currently contains a list of the equation's patterns together with a CoreExpr that is to be evaluated after a successful match on this equation. All the match-functions only operate on the first pattern of an equation - after successfully matching it, match is called recursively on the tail of the pattern list. We can express this more clearly and make the code a little more elegant by updating the datatype of EquationInfo as follows: data EquationInfo = EqnMatch { eqn_pat = Pat GhcTc, eqn_rest = EquationInfo } | EqnDone { eqn_rhs = MatchResult CoreExpr } An EquationInfo now explicitly exposes its first pattern which most functions operate on, and exposes the equation that remains after processing the first pattern. An EqnDone signifies an empty equation where the CoreExpr can now be evaluated. - - - - - 86ad1af9 by David Binder at 2023-07-28T13:13:53-04:00 Improve documentation for Data.Fixed - - - - - f8fa1d08 by Ben Gamari at 2023-07-28T13:14:31-04:00 ghc-prim: Use C11 atomics Previously `ghc-prim`'s atomic wrappers used the legacy `__sync_*` family of C builtins. Here we refactor these to rather use the appropriate C11 atomic equivalents, allowing us to be more explicit about the expected ordering semantics. - - - - - 0bfc8908 by Finley McIlwaine at 2023-07-28T18:46:26-04:00 Include -haddock in DynFlags fingerprint The -haddock flag determines whether or not the resulting .hi files contain haddock documentation strings. If the existing .hi files do not contain haddock documentation strings and the user requests them, we should recompile. - - - - - 40425c50 by Andreas Klebinger at 2023-07-28T18:47:02-04:00 Aarch64 NCG: Use encoded immediates for literals. Try to generate instr x2, <imm> instead of mov x1, lit instr x2, x1 When possible. This get's rid if quite a few redundant mov instructions. I believe this causes a metric decrease for LargeRecords as we reduce register pressure. ------------------------- Metric Decrease: LargeRecord ------------------------- - - - - - e9a0fa3f by Andrew Lelechenko at 2023-07-28T18:47:42-04:00 Bump filepath submodule to 1.4.100.4 Resolves #23741 Metric Decrease: MultiComponentModules MultiComponentModulesRecomp MultiLayerModules MultiLayerModulesRecomp T10421 T12234 T12425 T13035 T13701 T13719 T16875 T18304 T18698a T18698b T21839c T9198 TcPlugin_RewritePerf hard_hole_fits Metric decrease on Windows can be probably attributed to https://github.com/haskell/filepath/pull/183 - - - - - ee93edfd by Andrew Lelechenko at 2023-07-28T18:48:21-04:00 Add since pragmas to GHC.IO.Handle.FD - - - - - d0369802 by Simon Peyton Jones at 2023-07-30T09:24:48+01:00 Make the occurrence analyser smarter about join points This MR addresses #22404. There is a big Note Note [Occurrence analysis for join points] that explains it all. Significant changes * New field occ_join_points in OccEnv * The NonRec case of occAnalBind splits into two cases: one for existing join points (which does the special magic for Note [Occurrence analysis for join points], and one for other bindings. * mkOneOcc adds in info from occ_join_points. * All "bring into scope" activity is centralised in the new function `addInScope`. * I made a local data type LocalOcc for use inside the occurrence analyser It is like OccInfo, but lacks IAmDead and IAmALoopBreaker, which in turn makes computationns over it simpler and more efficient. * I found quite a bit of allocation in GHC.Core.Rules.getRules so I optimised it a bit. More minor changes * I found I was using (Maybe Arity) a lot, so I defined a new data type JoinPointHood and used it everwhere. This touches a lot of non-occ-anal files, but it makes everything more perspicuous. * Renamed data constructor WithUsageDetails to WUD, and WithTailUsageDetails to WTUD This also fixes #21128, on the way. --------- Compiler perf ----------- I spent quite a time on performance tuning, so even though it does more than before, the occurrence analyser runs slightly faster on average. Here are the compile-time allocation changes over 0.5% CoOpt_Read(normal) ghc/alloc 766,025,520 754,561,992 -1.5% CoOpt_Singletons(normal) ghc/alloc 759,436,840 762,925,512 +0.5% LargeRecord(normal) ghc/alloc 1,814,482,440 1,799,530,456 -0.8% PmSeriesT(normal) ghc/alloc 68,159,272 67,519,720 -0.9% T10858(normal) ghc/alloc 120,805,224 118,746,968 -1.7% T11374(normal) ghc/alloc 164,901,104 164,070,624 -0.5% T11545(normal) ghc/alloc 79,851,808 78,964,704 -1.1% T12150(optasm) ghc/alloc 73,903,664 71,237,544 -3.6% GOOD T12227(normal) ghc/alloc 333,663,200 331,625,864 -0.6% T12234(optasm) ghc/alloc 52,583,224 52,340,344 -0.5% T12425(optasm) ghc/alloc 81,943,216 81,566,720 -0.5% T13056(optasm) ghc/alloc 294,517,928 289,642,512 -1.7% T13253-spj(normal) ghc/alloc 118,271,264 59,859,040 -49.4% GOOD T15164(normal) ghc/alloc 1,102,630,352 1,091,841,296 -1.0% T15304(normal) ghc/alloc 1,196,084,000 1,166,733,000 -2.5% T15630(normal) ghc/alloc 148,729,632 147,261,064 -1.0% T15703(normal) ghc/alloc 379,366,664 377,600,008 -0.5% T16875(normal) ghc/alloc 32,907,120 32,670,976 -0.7% T17516(normal) ghc/alloc 1,658,001,888 1,627,863,848 -1.8% T17836(normal) ghc/alloc 395,329,400 393,080,248 -0.6% T18140(normal) ghc/alloc 71,968,824 73,243,040 +1.8% T18223(normal) ghc/alloc 456,852,568 453,059,088 -0.8% T18282(normal) ghc/alloc 129,105,576 131,397,064 +1.8% T18304(normal) ghc/alloc 71,311,712 70,722,720 -0.8% T18698a(normal) ghc/alloc 208,795,112 210,102,904 +0.6% T18698b(normal) ghc/alloc 230,320,736 232,697,976 +1.0% BAD T19695(normal) ghc/alloc 1,483,648,128 1,504,702,976 +1.4% T20049(normal) ghc/alloc 85,612,024 85,114,376 -0.6% T21839c(normal) ghc/alloc 415,080,992 410,906,216 -1.0% GOOD T4801(normal) ghc/alloc 247,590,920 250,726,272 +1.3% T6048(optasm) ghc/alloc 95,699,416 95,080,680 -0.6% T783(normal) ghc/alloc 335,323,384 332,988,120 -0.7% T9233(normal) ghc/alloc 709,641,224 685,947,008 -3.3% GOOD T9630(normal) ghc/alloc 965,635,712 948,356,120 -1.8% T9675(optasm) ghc/alloc 444,604,152 428,987,216 -3.5% GOOD T9961(normal) ghc/alloc 303,064,592 308,798,800 +1.9% BAD WWRec(normal) ghc/alloc 503,728,832 498,102,272 -1.1% geo. mean -1.0% minimum -49.4% maximum +1.9% In fact these figures seem to vary between platforms; generally worse on i386 for some reason. The Windows numbers vary by 1% espec in benchmarks where the total allocation is low. But the geom mean stays solidly negative, which is good. The "increase/decrease" list below covers all platforms. The big win on T13253-spj comes because it has a big nest of join points, each occurring twice in the next one. The new occ-anal takes only one iteration of the simplifier to do the inlining; the old one took four. Moreover, we get much smaller code with the new one: New: Result size of Tidy Core = {terms: 429, types: 84, coercions: 0, joins: 14/14} Old: Result size of Tidy Core = {terms: 2,437, types: 304, coercions: 0, joins: 10/10} --------- Runtime perf ----------- No significant changes in nofib results, except a 1% reduction in compiler allocation. Metric Decrease: CoOpt_Read T13253-spj T9233 T9630 T9675 T12150 T21839c LargeRecord MultiComponentModulesRecomp T10421 T13701 T10421 T13701 T12425 Metric Increase: T18140 T9961 T18282 T18698a T18698b T19695 - - - - - 42aa7fbd by Julian Ospald at 2023-07-30T17:22:01-04:00 Improve documentation around IOException and ioe_filename See: * https://github.com/haskell/core-libraries-committee/issues/189 * https://github.com/haskell/unix/pull/279 * https://github.com/haskell/unix/pull/289 - - - - - 33598ecb by Sylvain Henry at 2023-08-01T14:45:54-04:00 JS: implement getMonotonicTime (fix #23687) - - - - - d2bedffd by Bartłomiej Cieślar at 2023-08-01T14:46:40-04:00 Implementation of the Deprecated Instances proposal #575 This commit implements the ability to deprecate certain instances, which causes the compiler to emit the desired deprecation message whenever they are instantiated. For example: module A where class C t where instance {-# DEPRECATED "dont use" #-} C Int where module B where import A f :: C t => t f = undefined g :: Int g = f -- "dont use" emitted here The implementation is as follows: - In the parser, we parse deprecations/warnings attached to instances: instance {-# DEPRECATED "msg" #-} Show X deriving instance {-# WARNING "msg2" #-} Eq Y (Note that non-standalone deriving instance declarations do not support this mechanism.) - We store the resulting warning message in `ClsInstDecl` (respectively, `DerivDecl`). In `GHC.Tc.TyCl.Instance.tcClsInstDecl` (respectively, `GHC.Tc.Deriv.Utils.newDerivClsInst`), we pass on that information to `ClsInst` (and eventually store it in `IfaceClsInst` too). - Finally, when we solve a constraint using such an instance, in `GHC.Tc.Instance.Class.matchInstEnv`, we emit the appropriate warning that was stored in `ClsInst`. Note that we only emit a warning when the instance is used in a different module than it is defined, which keeps the behaviour in line with the deprecation of top-level identifiers. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - d5a65af6 by Ben Gamari at 2023-08-01T14:47:18-04:00 compiler: Style fixes - - - - - 7218c80a by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Fix implicit cast This ensures that Task.h can be built with a C++ compiler. - - - - - d6d5aafc by Ben Gamari at 2023-08-01T14:47:19-04:00 testsuite: Fix warning in hs_try_putmvar001 - - - - - d9eddf7a by Ben Gamari at 2023-08-01T14:47:19-04:00 testsuite: Add AtomicModifyIORef test - - - - - f9eea4ba by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Introduce NO_WARN macro This allows fine-grained ignoring of warnings. - - - - - 497b24ec by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Simplify atomicModifyMutVar2# implementation Previously we would perform a redundant load in the non-threaded RTS in atomicModifyMutVar2# implementation for the benefit of the non-moving GC's write barrier. Eliminate this. - - - - - 52ee082b by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Introduce more principled fence operations - - - - - cd3c0377 by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Introduce SET_INFO_RELAXED - - - - - 6df2352a by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Style fixes - - - - - 4ef6f319 by Ben Gamari at 2023-08-01T14:47:19-04:00 codeGen/tsan: Rework handling of spilling - - - - - f9ca7e27 by Ben Gamari at 2023-08-01T14:47:19-04:00 hadrian: More debug information - - - - - df4153ac by Ben Gamari at 2023-08-01T14:47:19-04:00 Improve TSAN documentation - - - - - fecae988 by Ben Gamari at 2023-08-01T14:47:19-04:00 hadrian: More selective TSAN instrumentation - - - - - 465a9a0b by Alan Zimmerman at 2023-08-01T14:47:56-04:00 EPA: Provide correct annotation span for ImportDecl Use the whole declaration, rather than just the span of the 'import' keyword. Metric Decrease: T9961 T5205 Metric Increase: T13035 - - - - - ae63d0fa by Bartłomiej Cieślar at 2023-08-01T14:48:40-04:00 Add cases to T23279: HasField for deprecated record fields This commit adds additional tests from ticket #23279 to ensure that we don't regress on reporting deprecated record fields in conjunction with HasField, either when using overloaded record dot syntax or directly through `getField`. Fixes #23279 - - - - - 00fb6e6b by Andreas Klebinger at 2023-08-01T14:49:17-04:00 AArch NCG: Pure refactor Combine some alternatives. Add some line breaks for overly long lines - - - - - 8f3b3b78 by Andreas Klebinger at 2023-08-01T14:49:54-04:00 Aarch ncg: Optimize immediate use for address calculations When the offset doesn't fit into the immediate we now just reuse the general getRegister' code path which is well optimized to compute the offset into a register instead of a special case for CmmRegOff. This means we generate a lot less code under certain conditions which is why performance metrics for these improve. ------------------------- Metric Decrease: T4801 T5321FD T5321Fun ------------------------- - - - - - 74a882dc by MorrowM at 2023-08-02T06:00:03-04:00 Add a RULE to make lookup fuse See https://github.com/haskell/core-libraries-committee/issues/175 Metric Increase: T18282 - - - - - cca74dab by Ben Gamari at 2023-08-02T06:00:39-04:00 hadrian: Ensure that way-flags are passed to CC Previously the way-specific compilation flags (e.g. `-DDEBUG`, `-DTHREADED_RTS`) would not be passed to the CC invocations. This meant that C dependency files would not correctly reflect dependencies predicated on the way, resulting in the rather painful #23554. Closes #23554. - - - - - 622b483c by Jaro Reinders at 2023-08-02T06:01:20-04:00 Native 32-bit Enum Int64/Word64 instances This commits adds more performant Enum Int64 and Enum Word64 instances for 32-bit platforms, replacing the Integer-based implementation. These instances are a copy of the Enum Int and Enum Word instances with minimal changes to manipulate Int64 and Word64 instead. On i386 this yields a 1.5x performance increase and for the JavaScript back end it even yields a 5.6x speedup. Metric Decrease: T18964 - - - - - c8bd7fa4 by Sylvain Henry at 2023-08-02T06:02:03-04:00 JS: fix typos in constants (#23650) - - - - - b9d5bfe9 by Josh Meredith at 2023-08-02T06:02:40-04:00 JavaScript: update MK_TUP macros to use current tuple constructors (#23659) - - - - - 28211215 by Matthew Pickering at 2023-08-02T06:03:19-04:00 ci: Pass -Werror when building hadrian in hadrian-ghc-in-ghci job Warnings when building Hadrian can end up cluttering the output of HLS, and we've had bug reports in the past about these warnings when building Hadrian. It would be nice to turn on -Werror on at least one build of Hadrian in CI to avoid a patch introducing warnings when building Hadrian. Fixes #23638 - - - - - aca20a5d by Ben Gamari at 2023-08-02T06:03:55-04:00 codeGen: Ensure that TSAN is aware of writeArray# write barriers By using a proper release store instead of a fence. - - - - - 453c0531 by Ben Gamari at 2023-08-02T06:03:55-04:00 codeGen: Ensure that array reads have necessary barriers This was the cause of #23541. - - - - - 93a0d089 by Arnaud Spiwack at 2023-08-02T06:04:37-04:00 Add test for #23550 - - - - - 6a2f4a20 by Arnaud Spiwack at 2023-08-02T06:04:37-04:00 Desugar non-recursive lets to non-recursive lets (take 2) This reverts commit 522bd584f71ddeda21efdf0917606ce3d81ec6cc. And takes care of the case that I missed in my previous attempt. Namely the case of an AbsBinds with no type variables and no dictionary variable. Ironically, the comment explaining why non-recursive lets were desugared to recursive lets were pointing specifically at this case as the reason. I just failed to understand that it was until Simon PJ pointed it out to me. See #23550 for more discussion. - - - - - ff81d53f by jade at 2023-08-02T06:05:20-04:00 Expand documentation of List & Data.List This commit aims to improve the documentation and examples of symbols exported from Data.List - - - - - fa4e5913 by Jade at 2023-08-02T06:06:03-04:00 Improve documentation of Semigroup & Monoid This commit aims to improve the documentation of various symbols exported from Data.Semigroup and Data.Monoid - - - - - 1b27e151 by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Check for puns (see ghc#23368) - - - - - 457341fd by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Remove fake exports for (~), List, and Tuple<n> The old reasoning no longer applies, nowadays those names can be mentioned in export lists. - - - - - bf3dcddf by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Fix pretty-printing of Solo and MkSolo - - - - - e2c91bff by Gergő Érdi at 2023-08-03T02:55:46+01:00 Desugar bindings in the context of their evidence Closes #23172 - - - - - 481f4a46 by Gergő Érdi at 2023-08-03T07:48:43+01:00 Add flag to `-f{no-}specialise-incoherents` to enable/disable specialisation of incoherent instances Fixes #23287 - - - - - d751c583 by Profpatsch at 2023-08-04T12:24:26-04:00 base: Improve String & IsString documentation - - - - - 01db1117 by Ben Gamari at 2023-08-04T12:25:02-04:00 rts/win32: Ensure reliability of IO manager shutdown When the Win32 threaded IO manager shuts down, `ioManagerDie` sends an `IO_MANAGER_DIE` event to the IO manager thread using the `io_manager_event` event object. Finally, it will closes the event object, and invalidate `io_manager_event`. Previously, `readIOManagerEvent` would see that `io_manager_event` is invalid and return `0`, suggesting that everything is right with the world. This meant that if `ioManagerDie` invalidated the handle before the event manager was blocked on the event we would end up in a situation where the event manager would never realize it was asked to shut down. Fix this by ensuring that `readIOManagerEvent` instead returns `IO_MANAGER_DIE` when we detect that the event object has been invalidated by `ioManagerDie`. Fixes #23691. - - - - - fdef003a by Ryan Scott at 2023-08-04T12:25:39-04:00 Look through TH splices in splitHsApps This modifies `splitHsApps` (a key function used in typechecking function applications) to look through untyped TH splices and quasiquotes. Not doing so was the cause of #21077. This builds on !7821 by making `splitHsApps` match on `HsUntypedSpliceTop`, which contains the `ThModFinalizers` that must be run as part of invoking the TH splice. See the new `Note [Looking through Template Haskell splices in splitHsApps]` in `GHC.Tc.Gen.Head`. Along the way, I needed to make the type of `splitHsApps.set` slightly more general to accommodate the fact that the location attached to a quasiquote is a `SrcAnn NoEpAnns` rather than a `SrcSpanAnnA`. Fixes #21077. - - - - - e77a0b41 by Ben Gamari at 2023-08-04T12:26:15-04:00 Bump deepseq submodule to 1.5. And bump bounds (cherry picked from commit 1228d3a4a08d30eaf0138a52d1be25b38339ef0b) - - - - - cebb5819 by Ben Gamari at 2023-08-04T12:26:15-04:00 configure: Bump minimal boot GHC version to 9.4 (cherry picked from commit d3ffdaf9137705894d15ccc3feff569d64163e8e) - - - - - 83766dbf by Ben Gamari at 2023-08-04T12:26:15-04:00 template-haskell: Bump version to 2.21.0.0 Bumps exceptions submodule. (cherry picked from commit bf57fc9aea1196f97f5adb72c8b56434ca4b87cb) - - - - - 1211112a by Ben Gamari at 2023-08-04T12:26:15-04:00 base: Bump version to 4.19 Updates all boot library submodules. (cherry picked from commit 433d99a3c24a55b14ec09099395e9b9641430143) - - - - - 3ab5efd9 by Ben Gamari at 2023-08-04T12:26:15-04:00 testsuite: Normalise versions more aggressively In backpack hashes can contain `+` characters. (cherry picked from commit 024861af51aee807d800e01e122897166a65ea93) - - - - - d52be957 by Ben Gamari at 2023-08-04T12:26:15-04:00 testsuite: Declare bkpcabal08 as fragile Due to spurious output changes described in #23648. (cherry picked from commit c046a2382420f2be2c4a657c56f8d95f914ea47b) - - - - - e75a58d1 by Ben Gamari at 2023-08-04T12:26:15-04:00 gitlab-ci: Only mark linker_unload_native as broken in static jobs This test passes on dynamically-linked Alpine. (cherry picked from commit f356a7e8ec8ec3d6b2b30fd175598b9b80065d87) - - - - - 8b176514 by Ben Gamari at 2023-08-04T12:26:15-04:00 testsuite: Update base-exports - - - - - 4b647936 by Ben Gamari at 2023-08-04T12:26:15-04:00 testsuite/interface-stability: normalise versions This eliminates spurious changes from version bumps. - - - - - 0eb54c05 by Ben Gamari at 2023-08-04T12:26:51-04:00 linker/PEi386: Don't sign-extend symbol section number Previously we incorrectly interpreted PE section numbers as signed values. However, this isn't the case; rather, it's an unsigned 16-bit number with a few special bit-patterns (0xffff and 0xfffe). This resulted in #22941 as the linker would conclude that the sections were invalid. Fixing this required quite a bit of refactoring. Closes #22941. - - - - - fd7ce39c by Ben Gamari at 2023-08-04T12:27:28-04:00 testsuite: Mark MulMayOflo_full as broken rather than skipping To ensure that we don't accidentally fix it. See #23742. - - - - - 824092f2 by Ben Gamari at 2023-08-04T12:27:28-04:00 nativeGen/AArch64: Fix sign extension in MulMayOflo Previously the 32-bit implementations of MulMayOflo would use the a non-sensical sign-extension mode. Rewrite these to reflect what gcc 11 produces. Also similarly rework the 16- and 8-bit cases. This now passes the MulMayOflo tests in ghc/test-primops> in all four widths, including the precision tests. Fixes #23721. - - - - - 1b15dbc4 by Jan Hrček at 2023-08-04T12:28:08-04:00 Fix haddock markup in code example for coerce - - - - - 46fd8ced by Vladislav Zavialov at 2023-08-04T12:28:44-04:00 Fix (~) and (@) infix operators in TH splices (#23748) 8168b42a "Whitespace-sensitive bang patterns" allows GHC to accept the following infix operators: a ~ b = () a @ b = () But not if TH is used to generate those declarations: $([d| a ~ b = () a @ b = () |]) -- Test.hs:5:2: error: [GHC-55017] -- Illegal variable name: ‘~’ -- When splicing a TH declaration: (~_0) a_1 b_2 = GHC.Tuple.Prim.() This is easily fixed by modifying `reservedOps` in GHC.Utils.Lexeme - - - - - a1899d8f by Aaron Allen at 2023-08-04T12:29:24-04:00 [#23663] Show Flag Suggestions in GHCi Makes suggestions when using `:set` in GHCi with a misspelled flag. This mirrors how invalid flags are handled when passed to GHC directly. Logic for producing flag suggestions was moved to GHC.Driver.Sesssion so it can be shared. resolves #23663 - - - - - 03f2debd by Rodrigo Mesquita at 2023-08-04T12:30:00-04:00 Improve ghc-toolchain validation configure warning Fixes the layout of the ghc-toolchain validation warning produced by configure. - - - - - de25487d by Alan Zimmerman at 2023-08-04T12:30:36-04:00 EPA make getLocA a synonym for getHasLoc This is basically a no-op change, but allows us to make future changes that can rely on the HasLoc instances And I presume this means we can use more precise functions based on class resolution, so the Windows CI build reports Metric Decrease: T12234 T13035 - - - - - 3ac423b9 by Ben Gamari at 2023-08-04T12:31:13-04:00 ghc-platform: Add upper bound on base Hackage upload requires this. - - - - - 8ba20b21 by Matthew Craven at 2023-08-04T17:22:59-04:00 Adjust and clarify handling of primop effects Fixes #17900; fixes #20195. The existing "can_fail" and "has_side_effects" primop attributes that previously governed this were used in inconsistent and confusingly-documented ways, especially with regard to raising exceptions. This patch replaces them with a single "effect" attribute, which has four possible values: NoEffect, CanFail, ThrowsException, and ReadWriteEffect. These are described in Note [Classifying primop effects]. A substantial amount of related documentation has been re-drafted for clarity and accuracy. In the process of making this attribute format change for literally every primop, several existing mis-classifications were detected and corrected. One of these mis-classifications was tagToEnum#, which is now considered CanFail; this particular fix is known to cause a regression in performance for derived Enum instances. (See #23782.) Fixing this is left as future work. New primop attributes "cheap" and "work_free" were also added, and used in the corresponding parts of GHC.Core.Utils. In view of their actual meaning and uses, `primOpOkForSideEffects` and `exprOkForSideEffects` have been renamed to `primOpOkToDiscard` and `exprOkToDiscard`, respectively. Metric Increase: T21839c - - - - - 41bf2c09 by sheaf at 2023-08-04T17:23:42-04:00 Update inert_solved_dicts for ImplicitParams When adding an implicit parameter dictionary to the inert set, we must make sure that it replaces any previous implicit parameter dictionaries that overlap, in order to get the appropriate shadowing behaviour, as in let ?x = 1 in let ?x = 2 in ?x We were already doing this for inert_cans, but we weren't doing the same thing for inert_solved_dicts, which lead to the bug reported in #23761. The fix is thus to make sure that, when handling an implicit parameter dictionary in updInertDicts, we update **both** inert_cans and inert_solved_dicts to ensure a new implicit parameter dictionary correctly shadows old ones. Fixes #23761 - - - - - 43578d60 by Matthew Craven at 2023-08-05T01:05:36-04:00 Bump bytestring submodule to 0.11.5.1 - - - - - 91353622 by Ben Gamari at 2023-08-05T01:06:13-04:00 Initial commit of Note [Thunks, blackholes, and indirections] This Note attempts to summarize the treatment of thunks, thunk update, and indirections. This fell out of work on #23185. - - - - - 8d686854 by sheaf at 2023-08-05T01:06:54-04:00 Remove zonk in tcVTA This removes the zonk in GHC.Tc.Gen.App.tc_inst_forall_arg and its accompanying Note [Visible type application zonk]. Indeed, this zonk is no longer necessary, as we no longer maintain the invariant that types are well-kinded without zonking; only that typeKind does not crash; see Note [The Purely Kinded Type Invariant (PKTI)]. This commit removes this zonking step (as well as a secondary zonk), and replaces the aforementioned Note with the explanatory Note [Type application substitution], which justifies why the substitution performed in tc_inst_forall_arg remains valid without this zonking step. Fixes #23661 - - - - - 19dea673 by Ben Gamari at 2023-08-05T01:07:30-04:00 Bump nofib submodule Ensuring that nofib can be build using the same range of bootstrap compilers as GHC itself. - - - - - aa07402e by Luite Stegeman at 2023-08-05T23:15:55+09:00 JS: Improve compatibility with recent emsdk The JavaScript code in libraries/base/jsbits/base.js had some hardcoded offsets for fields in structs, because we expected the layout of the data structures to remain unchanged. Emsdk 3.1.42 changed the layout of the stat struct, breaking this assumption, and causing code in .hsc files accessing the stat struct to fail. This patch improves compatibility with recent emsdk by removing the assumption that data layouts stay unchanged: 1. offsets of fields in structs used by JavaScript code are now computed by the configure script, so both the .js and .hsc files will automatically use the new layout if anything changes. 2. the distrib/configure script checks that the emsdk version on a user's system is the same version that a bindist was booted with, to avoid data layout inconsistencies See #23641 - - - - - b938950d by Luite Stegeman at 2023-08-07T06:27:51-04:00 JS: Fix missing local variable declarations This fixes some missing local variable declarations that were found by running the testsuite in strict mode. Fixes #23775 - - - - - 6c0e2247 by sheaf at 2023-08-07T13:31:21-04:00 Update Haddock submodule to fix #23368 This submodule update adds the following three commits: bbf1c8ae - Check for puns 0550694e - Remove fake exports for (~), List, and Tuple<n> 5877bceb - Fix pretty-printing of Solo and MkSolo These commits fix the issues with Haddock HTML rendering reported in ticket #23368. Fixes #23368 - - - - - 5b5be3ea by Matthew Pickering at 2023-08-07T13:32:00-04:00 Revert "Bump bytestring submodule to 0.11.5.1" This reverts commit 43578d60bfc478e7277dcd892463cec305400025. Fixes #23789 - - - - - 01961be3 by Ben Gamari at 2023-08-08T02:47:14-04:00 configure: Derive library version from ghc-prim.cabal.in Since ghc-prim.cabal is now generated by Hadrian, we cannot depend upon it. Closes #23726. - - - - - 3b373838 by Ryan Scott at 2023-08-08T02:47:49-04:00 tcExpr: Push expected types for untyped TH splices inwards In !10911, I deleted a `tcExpr` case for `HsUntypedSplice` in favor of a much simpler case that simply delegates to `tcApp`. Although this passed the test suite at the time, this was actually an error, as the previous `tcExpr` case was critically pushing the expected type inwards. This actually matters for programs like the one in #23796, which GHC would not accept with type inference alone—we need full-blown type _checking_ to accept these. I have added back the previous `tcExpr` case for `HsUntypedSplice` and now explain why we have two different `HsUntypedSplice` cases (one in `tcExpr` and another in `splitHsApps`) in `Note [Looking through Template Haskell splices in splitHsApps]` in `GHC.Tc.Gen.Head`. Fixes #23796. - - - - - 0ef1d8ae by sheaf at 2023-08-08T21:26:51-04:00 Compute all emitted diagnostic codes This commit introduces in GHC.Types.Error.Codes the function constructorCodes :: forall diag. (...) => Map DiagnosticCode String which computes a collection of all the diagnostic codes that correspond to a particular type. In particular, we can compute the collection of all diagnostic codes emitted by GHC using the invocation constructorCodes @GhcMessage We then make use of this functionality in the new "codes" test which checks consistency and coverage of GHC diagnostic codes. It performs three checks: - check 1: all non-outdated GhcDiagnosticCode equations are statically used. - check 2: all outdated GhcDiagnosticCode equations are statically unused. - check 3: all statically used diagnostic codes are covered by the testsuite (modulo accepted exceptions). - - - - - 4bc7b1e5 by Fraser Tweedale at 2023-08-08T21:27:32-04:00 numberToRangedRational: fix edge cases for exp ≈ (maxBound :: Int) Currently a negative exponent less than `minBound :: Int` results in Infinity, which is very surprising and obviously wrong. ``` λ> read "1e-9223372036854775808" :: Double 0.0 λ> read "1e-9223372036854775809" :: Double Infinity ``` There is a further edge case where the exponent can overflow when increased by the number of tens places in the integer part, or underflow when decreased by the number of leading zeros in the fractional part if the integer part is zero: ``` λ> read "10e9223372036854775807" :: Double 0.0 λ> read "0.01e-9223372036854775808" :: Double Infinity ``` To resolve both of these issues, perform all arithmetic and comparisons involving the exponent in type `Integer`. This approach also eliminates the need to explicitly check the exponent against `maxBound :: Int` and `minBound :: Int`, because the allowed range of the exponent (i.e. the result of `floatRange` for the target floating point type) is certainly within those bounds. This change implements CLC proposal 192: https://github.com/haskell/core-libraries-committee/issues/192 - - - - - 6eab07b2 by Alan Zimmerman at 2023-08-08T21:28:10-04:00 EPA: Remove Location from WarningTxt source This is not needed. - - - - - 1a98d673 by Sebastian Graf at 2023-08-09T16:24:29-04:00 Cleanup a TODO introduced in 1f94e0f7 The change must have slipped through review of !4412 - - - - - 2274abc8 by Sebastian Graf at 2023-08-09T16:24:29-04:00 More explicit strictness in GHC.Real - - - - - ce8aa54c by Sebastian Graf at 2023-08-09T16:24:30-04:00 exprIsTrivial: Factor out shared implementation The duplication between `exprIsTrivial` and `getIdFromTrivialExpr_maybe` has been bugging me for a long time. This patch introduces an inlinable worker function `trivial_expr_fold` acting as the single, shared decision procedure of triviality. It "returns" a Church-encoded `Maybe (Maybe Id)`, so when it is inlined, it fuses to similar code as before. (Better code, even, in the case of `getIdFromTrivialExpr` which presently allocates a `Just` constructor that cancels away after this patch.) - - - - - d004a36d by Sebastian Graf at 2023-08-09T16:24:30-04:00 Simplify: Simplification of arguments in a single function The Simplifier had a function `simplArg` that wasn't called in `rebuildCall`, which seems to be the main way to simplify args. Hence I consolidated the code path to call `simplArg`, too, renaming to `simplLazyArg`. - - - - - 8c73505e by Sebastian Graf at 2023-08-09T16:24:30-04:00 Core.Ppr: Omit case binder for empty case alternatives A minor improvement to pretty-printing - - - - - d8d993f1 by Sebastian Graf at 2023-08-09T16:24:30-04:00 Disable tests RepPolyWrappedVar2 and RepPolyUnsafeCoerce1 in JS backend ... because those coerce between incompatible/unknown PrimReps. - - - - - f06e87e4 by Sebastian Graf at 2023-08-09T16:24:30-04:00 Inlining literals into boring contexts is OK - - - - - 4a6b7c87 by Sebastian Graf at 2023-08-09T16:24:30-04:00 Clarify floating of unsafeEqualityProofs (#23754) - - - - - b0f4752e by Sebastian Graf at 2023-08-09T16:24:30-04:00 Kill SetLevel.notWorthFloating.is_triv (#23270) We have had it since b84ba676034, when it operated on annotated expressions. Nowadays it operates on vanilla `CoreExpr` though, so we should just call `exprIsTrivial`; thus handling empty cases and string literals correctly. - - - - - 7e0c8b3b by Sebastian Graf at 2023-08-09T16:24:30-04:00 ANFise string literal arguments (#23270) This instates the invariant that a trivial CoreExpr translates to an atomic StgExpr. Nice. Annoyingly, in -O0 we sometimes generate ``` foo = case "blah"# of sat { __DEFAULT -> unpackCString# sat } ``` which makes it a bit harder to spot that we can emit a standard `stg_unpack_cstring` thunk. Fixes #23270. - - - - - 357f2738 by Sebastian Graf at 2023-08-09T16:24:30-04:00 Deactivate -fcatch-nonexhaustive-cases in ghc-bignum (#23345) - - - - - 59202c80 by Sebastian Graf at 2023-08-09T16:24:30-04:00 CorePrep: Eliminate EmptyCase and unsafeEqualityProof in CoreToStg instead We eliminate EmptyCase by way of `coreToStg (Case e _ _ []) = coreToStg e` now. The main reason is that it plays far better in conjunction with eta expansion (as we aim to do for arguments in CorePrep, #23083), because we can discard any arguments, `(case e of {}) eta == case e of {}`, whereas in `(e |> co) eta` it's impossible to discard the argument. We do also give the same treatment to unsafeCoerce proofs and treat them as trivial iff their RHS is trivial. It is also both much simpler to describe than the previous mechanism of emitting an unsafe coercion and simpler to implement, removing quite a bit of commentary and `CorePrepProv`. In the ghc/alloc perf test `LargeRecord`, we introduce an additional Simplifier iteration due to #17910. E.g., FloatOut produces a binding ``` lvl_s6uK [Occ=Once1] :: GHC.Types.Int [LclId] lvl_s6uK = GHC.Types.I# 2# lvl_s6uL [Occ=Once1] :: GHC.Types.Any [LclId] lvl_s6uL = case Unsafe.Coerce.unsafeEqualityProof ... of { Unsafe.Coerce.UnsafeRefl v2_i6tr -> lvl_s6uK `cast` (... v2_i6tr ...) } ``` That occurs once and hence is pre-inlined unconditionally in the next Simplifier pass. It's non-trivial to find a way around that, but not really harmful otherwise. Hence we accept a 1.2% increase on some architectures. Metric Increase: LargeRecord - - - - - 00d31188 by Sebastian Graf at 2023-08-09T16:24:30-04:00 CorePrep: Eta expand arguments (#23083) Previously, we'd only eta expand let bindings and lambdas, now we'll also eta expand arguments such as in T23083: ```hs g f h = f (h `seq` (h $)) ``` Unless `-fpedantic-bottoms` is set, we'll now transform to ```hs g f h = f (\eta -> h eta) ``` in CorePrep. See the new `Note [Eta expansion of arguments in CorePrep]` for the details. We only do this optimisation with -O2 because we saw 2-3% ghc/alloc regressions in T4801 and T5321FD. Fixes #23083. - - - - - bf885d7a by Matthew Craven at 2023-08-09T16:25:07-04:00 Bump bytestring submodule to 0.11.5, again Fixes #23789. The bytestring commit used here is unreleased; a release can be made when necessary. - - - - - 7acbf0fd by Sven Tennie at 2023-08-10T19:17:11-04:00 Serialize CmmRetInfo in .rodata The handling of case was missing. - - - - - 0c3136f2 by Sven Tennie at 2023-08-10T19:17:11-04:00 Reference StgRetFun payload by its struct field address This is easier to grasp than relative pointer offsets. - - - - - f68ff313 by Sven Tennie at 2023-08-10T19:17:11-04:00 Better variable name: u -> frame The 'u' was likely introduced by copy'n'paste. - - - - - 0131bb7f by Sven Tennie at 2023-08-10T19:17:11-04:00 Make checkSTACK() public Such that it can also be used in tests. - - - - - 7b6e1e53 by Sven Tennie at 2023-08-10T19:17:11-04:00 Publish stack related fields in DerivedConstants.h These will be used in ghc-heap to decode these parts of the stack. - - - - - 907ed054 by Sven Tennie at 2023-08-10T19:17:11-04:00 ghc-heap: Decode StgStack and its stack frames Previously, ghc-heap could only decode heap closures. The approach is explained in detail in note [Decoding the stack]. - - - - - 6beb6ac2 by Sven Tennie at 2023-08-10T19:17:11-04:00 Remove RetFunType from RetFun stack frame representation It's a technical detail. The single usage is replaced by a predicate. - - - - - 006bb4f3 by Sven Tennie at 2023-08-10T19:17:11-04:00 Better parameter name The call-site uses the term "offset", too. - - - - - d4c2c1af by Sven Tennie at 2023-08-10T19:17:11-04:00 Make closure boxing pure There seems to be no need to do something complicated. However, the strictness of the closure pointer matters, otherwise a thunk gets decoded. - - - - - 8d8426c9 by Sven Tennie at 2023-08-10T19:17:11-04:00 Document entertainGC in test It wasn't obvious why it's there and what its role is. Also, increase the "entertainment level" a bit. I checked in STG and Cmm dumps that this really generates closures (and is not e.g. constant folded away.) - - - - - cc52c358 by Finley McIlwaine at 2023-08-10T19:17:47-04:00 Add -dipe-stats flag This is useful for seeing which info tables have information. - - - - - 261c4acb by Finley McIlwaine at 2023-08-10T19:17:47-04:00 Add -finfo-table-map-with-fallback -finfo-table-map-with-stack The -fno-info-table-map-with-stack flag omits STACK info tables from the info table map, and the -fno-info-table-map-with-fallback flag omits info tables with defaulted source locations from the map. In a test on the Agda codebase the build results were about 7% smaller when both of those types of tables were omitted. Adds a test that verifies that passing each combination of these flags results in the correct output for -dipe-stats, which is disabled for the js backend since profiling is not implemented. This commit also refactors a lot of the logic around extracting info tables from the Cmm results and building the info table map. This commit also fixes some issues in the users guide rst source to fix warnings that were noticed while debugging the documentation for these flags. Fixes #23702 - - - - - d7047e0d by Jaro Reinders at 2023-08-14T04:41:42-04:00 Add changelog entry for specialised Enum Int64/Word64 instances - - - - - 52f5e8fb by cydparser at 2023-08-14T04:42:20-04:00 Fix -ddump-to-file and -ddump-timings interaction (#20316) - - - - - 1274c5d6 by cydparser at 2023-08-14T04:42:20-04:00 Update release notes (#20316) - - - - - 8e699b23 by Matthew Pickering at 2023-08-14T10:44:47-04:00 base: Add changelog entry for CLC #188 This proposal modified the implementations of copyBytes, moveBytes and fillBytes (as detailed in the proposal) https://github.com/haskell/core-libraries-committee/issues/188 - - - - - 026f040a by Matthew Pickering at 2023-08-14T10:45:23-04:00 packaging: Build manpage in separate directory to other documentation We were installing two copies of the manpage: * One useless one in the `share/doc` folder, because we copy the doc/ folder into share/ * The one we deliberately installed into `share/man` etc The solution is to build the manpage into the `manpage` directory when building the bindist, and then just install it separately. Fixes #23707 - - - - - 524c60c8 by Bartłomiej Cieślar at 2023-08-14T13:46:33-04:00 Report deprecated fields bound by record wildcards when used This commit ensures that we emit the appropriate warnings when a deprecated record field bound by a record wildcard is used. For example: module A where data Foo = Foo {x :: Int, y :: Bool, z :: Char} {-# DEPRECATED x "Don't use x" #-} {-# WARNING y "Don't use y" #-} module B where import A foo (Foo {..}) = x This will cause us to emit a "Don't use x" warning, with location the location of the record wildcard. Note that we don't warn about `y`, because it is unused in the RHS of `foo`. Fixes #23382 - - - - - d6130065 by Matthew Pickering at 2023-08-14T13:47:11-04:00 Add zstd suffix to jobs which rely on zstd This was causing some confusion as the job was named simply "x86_64-linux-deb10-validate", which implies a standard configuration rather than any dependency on libzstd. - - - - - e24e44fc by Matthew Pickering at 2023-08-14T13:47:11-04:00 ci: Always run project-version job This is needed for the downstream test-primops pipeline to workout what the version of a bindist produced by a pipeline is. - - - - - f17b9d62 by Matthew Pickering at 2023-08-14T13:47:11-04:00 gen_ci: Rework how jobs-metadata.json is generated * We now represent a job group a triple of Maybes, which makes it easier to work out when jobs are enabled/disabled on certain pipelines. ``` data JobGroup a = StandardTriple { v :: Maybe (NamedJob a) , n :: Maybe (NamedJob a) , r :: Maybe (NamedJob a) } ``` * `jobs-metadata.json` generation is reworked using the following algorithm. - For each pipeline type, find all the platforms we are doing builds for. - Select one build per platform - Zip together the results This way we can choose different pipelines for validate/nightly/release which makes the metadata also useful for validate pipelines. This feature is used by the test-primops downstream CI in order to select the right bindist for testing validate pipelines. This makes it easier to inspect which jobs are going to be enabled on a particular pipeline. - - - - - f9a5563d by Matthew Pickering at 2023-08-14T13:47:11-04:00 gen_ci: Rules rework In particular we now distinguish between whether we are dealing with a Nightly/Release pipeline (which labels don't matter for) and a validate pipeline where labels do matter. The overall goal here is to allow a disjunction of labels for validate pipelines, for example, > Run a job if we have the full-ci label or test-primops label Therefore the "ValidateOnly" rules are treated as a set of disjunctions rather than conjunctions like before. What this means in particular is that if we want to ONLY run a job if a label is set, for example, "FreeBSD" label then we have to override the whole label set. Fixes #23772 - - - - - d54b0c1d by Matthew Pickering at 2023-08-14T13:47:11-04:00 ci: set -e for lint-ci-config scripts - - - - - 994a9b35 by Matthew Pickering at 2023-08-14T13:47:11-04:00 ci: Fix job metadata generation - - - - - e194ed2b by Ben Gamari at 2023-08-15T00:58:09-04:00 users-guide: Note that GHC2021 doesn't include ExplicitNamespaces As noted in #23801. - - - - - d814bda9 by Ben Gamari at 2023-08-15T05:43:53-04:00 users-guide: Support both distutils and packaging As noted in #23818, some old distributions (e.g. Debian 9) only include `distutils` while newer distributions only include `packaging`. Fixes #23818. - - - - - 1726db3f by Ben Gamari at 2023-08-15T05:43:53-04:00 users-guide: Ensure extlinks is compatible with Sphinx <4 The semantics of the `extlinks` attribute annoyingly changed in Sphinx 4. Reflect this in our configuration. See #22690. Fixes #23807. - - - - - 173338cf by Matthew Pickering at 2023-08-15T22:00:24-04:00 ci: Run full-ci on master and release branches Fixes #23737 - - - - - bdab6898 by Andrew Lelechenko at 2023-08-15T22:01:03-04:00 Add @since pragmas for Data.Ord.clamp and GHC.Float.clamp - - - - - 662d351b by Matthew Pickering at 2023-08-16T09:35:04-04:00 ghc-toolchain: Match CPP args with configure script At the moment we need ghc-toolchain to precisely match the output as provided by the normal configure script. The normal configure script (FP_HSCPP_CMD_WITH_ARGS) branches on whether we are using clang or gcc so we match that logic exactly in ghc-toolchain. The old implementation (which checks if certain flags are supported) is better but for now we have to match to catch any potential errors in the configuration. Ticket: #23720 - - - - - 09c6759e by Matthew Pickering at 2023-08-16T09:35:04-04:00 configure: Fix `-Wl,--no-as-needed` check The check was failing because the args supplied by $$1 were quoted which failed because then the C compiler thought they were an input file. Fixes #23720 - - - - - 2129678b by Matthew Pickering at 2023-08-16T09:35:04-04:00 configure: Add flag which turns ghc-toolchain check into error We want to catch these errors in CI, but first we need to a flag which turns this check into an error. - - - - - 6e2aa8e0 by Matthew Pickering at 2023-08-16T09:35:04-04:00 ci: Enable --enable-strict-ghc-toolchain-check for all CI jobs This will cause any CI job to fail if we have a mismatch between what ghc-toolchain reports and what ./configure natively reports. Fixing these kinds of issues is highest priority for 9.10 release. - - - - - 12d39e24 by Rodrigo Mesquita at 2023-08-16T09:35:04-04:00 Pass user-specified options to ghc-toolchain The current user interface to configuring target toolchains is `./configure`. In !9263 we added a new tool to configure target toolchains called `ghc-toolchain`, but the blessed way of creating these toolchains is still through configure. However, we were not passing the user-specified options given with the `./configure` invocation to the ghc-toolchain tool. This commit remedies that by storing the user options and environment variables in USER_* variables, which then get passed to GHC-toolchain. The exception to the rule is the windows bundled toolchain, which overrides the USER_* variables with whatever flags the windows bundled toolchain requires to work. We consider the bundled toolchain to be effectively the user specifying options, since the actual user delegated that configuration work. Closes #23678 - - - - - f7b3c3a0 by Rodrigo Mesquita at 2023-08-16T09:35:04-04:00 ghc-toolchain: Parse javascript and ghcjs as a Arch and OS - - - - - 8a0ae4ee by Rodrigo Mesquita at 2023-08-16T09:35:04-04:00 ghc-toolchain: Fix ranlib option - - - - - 31e9ec96 by Rodrigo Mesquita at 2023-08-16T09:35:04-04:00 Check Link Works with -Werror - - - - - bc1998b3 by Matthew Pickering at 2023-08-16T09:35:04-04:00 Only check for no_compact_unwind support on darwin While writing ghc-toolchain we noticed that the FP_PROG_LD_NO_COMPACT_UNWIND check is subtly wrong. Specifically, we pass -Wl,-no_compact_unwind to cc. However, ld.gold interprets this as -n o_compact_unwind, which is a valid argument. Fixes #23676 - - - - - 0283f36e by Matthew Pickering at 2023-08-16T09:35:04-04:00 Add some javascript special cases to ghc-toolchain On javascript there isn't a choice of toolchain but some of the configure checks were not accurately providing the correct answer. 1. The linker was reported as gnu LD because the --version output mentioned gnu LD. 2. The --target flag makes no sense on javascript but it was just ignored by the linker, so we add a special case to stop ghc-toolchain thinking that emcc supports --target when used as a linker. - - - - - a48ec5f8 by Matthew Pickering at 2023-08-16T09:35:04-04:00 check for emcc in gnu_LD check - - - - - 50df2e69 by Matthew Pickering at 2023-08-16T09:35:04-04:00 Add ldOverrideWhitelist to only default to ldOverride on windows/linux On some platforms - ie darwin, javascript etc we really do not want to allow the user to use any linker other than the default one as this leads to all kinds of bugs. Therefore it is a bit more prudant to add a whitelist which specifies on which platforms it might be possible to use a different linker. - - - - - a669a39c by Matthew Pickering at 2023-08-16T09:35:04-04:00 Fix plaform glob in FPTOOLS_SET_C_LD_FLAGS A normal triple may look like x86_64-unknown-linux but when cross-compiling you get $target set to a quad such as.. aarch64-unknown-linux-gnu Which should also match this check. - - - - - c52b6769 by Matthew Pickering at 2023-08-16T09:35:04-04:00 ghc-toolchain: Pass ld-override onto ghc-toolchain - - - - - 039b484f by Matthew Pickering at 2023-08-16T09:35:04-04:00 ld override: Make whitelist override user given option - - - - - d2b63cbc by Matthew Pickering at 2023-08-16T09:35:05-04:00 ghc-toolchain: Add format mode to normalise differences before diffing. The "format" mode takes an "--input" and "--ouput" target file and formats it. This is intended to be useful on windows where the configure/ghc-toolchain target files can't be diffed very easily because the path separators are different. - - - - - f2b39e4a by Matthew Pickering at 2023-08-16T09:35:05-04:00 ghc-toolchain: Bump ci-images commit to get new ghc-wasm-meta We needed to remove -Wno-unused-command-line-argument from the arguments passed in order for the configure check to report correctly. See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10976#note_516335 - - - - - 92103830 by Matthew Pickering at 2023-08-16T09:35:05-04:00 configure: MergeObjsCmd - distinguish between empty string and unset variable If `MergeObjsCmd` is explicitly set to the empty string then we should assume that MergeObjs is just not supported. This is especially important for windows where we set MergeObjsCmd to "" in m4/fp_setup_windows_toolchain.m4. - - - - - 3500bb2c by Matthew Pickering at 2023-08-16T09:35:05-04:00 configure: Add proper check to see if object merging works - - - - - 08c9a014 by Matthew Pickering at 2023-08-16T09:35:05-04:00 ghc-toolchain: If MergeObjsCmd is not set, replace setting with Nothing If the user explicitly chooses to not set a MergeObjsCmd then it is correct to use Nothing for tgtMergeObjs field in the Target file. - - - - - c9071d94 by Matthew Pickering at 2023-08-16T09:35:05-04:00 HsCppArgs: Augment the HsCppOptions This is important when we pass -I when setting up the windows toolchain. - - - - - 294a6d80 by Matthew Pickering at 2023-08-16T09:35:05-04:00 Set USER_CPP_ARGS when setting up windows toolchain - - - - - bde4b5d4 by Rodrigo Mesquita at 2023-08-16T09:35:05-04:00 Improve handling of Cc as a fallback - - - - - f4c1c3a3 by Rodrigo Mesquita at 2023-08-16T09:35:05-04:00 ghc-toolchain: Configure Cpp and HsCpp correctly when user specifies flags In ghc-toolchain, we were only /not/ configuring required flags when the user specified any flags at all for the of the HsCpp and Cpp tools. Otherwise, the linker takes into consideration the user specified flags to determine whether to search for a better linker implementation, but already configured the remaining GHC and platform-specific flags regardless of the user options. Other Tools consider the user options as a baseline for further configuration (see `findProgram`), so #23689 is not applicable. Closes #23689 - - - - - bfe4ffac by Matthew Pickering at 2023-08-16T09:35:05-04:00 CPP_ARGS: Put new options after user specified options This matches up with the behaviour of ghc-toolchain, so that the output of both matches. - - - - - a6828173 by Gergő Érdi at 2023-08-16T09:35:41-04:00 If a defaulting plugin made progress, re-zonk wanteds before built-in defaulting Fixes #23821. - - - - - e2b38115 by Sylvain Henry at 2023-08-17T07:54:06-04:00 JS: implement openat(AT_FDCWD...) (#23697) Use `openSync` to implement `openat(AT_FDCWD...)`. - - - - - a975c663 by sheaf at 2023-08-17T07:54:47-04:00 Use unsatisfiable for missing methods w/ defaults When a class instance has an Unsatisfiable constraint in its context and the user has not explicitly provided an implementation of a method, we now always provide a RHS of the form `unsatisfiable @msg`, even if the method has a default definition available. This ensures that, when deferring type errors, users get the appropriate error message instead of a possible runtime loop, if class default methods were defined recursively. Fixes #23816 - - - - - 45ca51e5 by Ben Gamari at 2023-08-17T15:16:41-04:00 ghc-internal: Initial commit of the skeleton - - - - - 88bbf8c5 by Ben Gamari at 2023-08-17T15:16:41-04:00 ghc-experimental: Initial commit - - - - - 664468c0 by Ben Gamari at 2023-08-17T15:17:17-04:00 testsuite/cloneStackLib: Fix incorrect format specifiers - - - - - eaa835bb by Ben Gamari at 2023-08-17T15:17:17-04:00 rts/ipe: Fix const-correctness of IpeBufferListNode Both info tables and the string table should be `const` - - - - - 78f6f6fd by Ben Gamari at 2023-08-17T15:17:17-04:00 nonmoving: Drop dead debugging utilities These are largely superceded by support in the ghc-utils GDB extension. - - - - - 3f6e8f42 by Ben Gamari at 2023-08-17T15:17:17-04:00 nonmoving: Refactor management of mark thread Here we refactor that treatment of the worker thread used by the nonmoving GC for concurrent marking, avoiding creating a new thread with every major GC cycle. As well, the new scheme is considerably easier to reason about, consolidating all state in one place, accessed via a small set of accessors with clear semantics. - - - - - 88c32b7d by Ben Gamari at 2023-08-17T15:17:17-04:00 testsuite: Skip T23221 in nonmoving GC ways This test is very dependent upon GC behavior. - - - - - 381cfaed by Ben Gamari at 2023-08-17T15:17:17-04:00 ghc-heap: Don't expose stack dirty and marking fields These are GC metadata and are not relevant to the end-user. Moreover, they are unstable which makes ghc-heap harder to test than necessary. - - - - - 16828ca5 by Luite Stegeman at 2023-08-21T18:42:53-04:00 bump process submodule to include macOS fix and JS support - - - - - b4d5f6ed by Matthew Pickering at 2023-08-21T18:43:29-04:00 ci: Add support for triggering test-primops pipelines This commit adds 4 ways to trigger testing with test-primops. 1. Applying the ~test-primops label to a validate pipeline. 2. A manually triggered job on a validate pipeline 3. A nightly pipeline job 4. A release pipeline job Fixes #23695 - - - - - 32c50daa by Matthew Pickering at 2023-08-21T18:43:29-04:00 Add test-primops label support The test-primops CI job requires some additional builds in the validation pipeline, so we make sure to enable these jobs when test-primops label is set. - - - - - 73ca8340 by Matthew Pickering at 2023-08-21T18:43:29-04:00 Revert "Aarch ncg: Optimize immediate use for address calculations" This reverts commit 8f3b3b78a8cce3bd463ed175ee933c2aabffc631. See #23793 - - - - - 5546ad9e by Matthew Pickering at 2023-08-21T18:43:29-04:00 Revert "AArch NCG: Pure refactor" This reverts commit 00fb6e6b06598752414a0b9a92840fb6ca61338d. See #23793 - - - - - 02dfcdc2 by Matthew Pickering at 2023-08-21T18:43:29-04:00 Revert "Aarch64 NCG: Use encoded immediates for literals." This reverts commit 40425c5021a9d8eb5e1c1046e2d5fa0a2918f96c. See #23793 ------------------------- Metric Increase: T4801 T5321FD T5321Fun ------------------------- - - - - - 7be4a272 by Matthew Pickering at 2023-08-22T08:55:20+01:00 ci: Remove manually triggered test-ci job This doesn't work on slimmed down pipelines as the needed jobs don't exist. If you want to run test-primops then apply the label. - - - - - 76a4d11b by Jaro Reinders at 2023-08-22T08:08:13-04:00 Remove Ptr example from roles docs - - - - - 069729d3 by Bryan Richter at 2023-08-22T08:08:49-04:00 Guard against duplicate pipelines in forks - - - - - f861423b by Rune K. Svendsen at 2023-08-22T08:09:35-04:00 dump-decls: fix "Ambiguous module name"-error Fixes errors of the following kind, which happen when dump-decls is run on a package that contains a module name that clashes with that of another package. ``` dump-decls: <no location info>: error: Ambiguous module name `System.Console.ANSI.Types': it was found in multiple packages: ansi-terminal-0.11.4 ansi-terminal-types-0.11.5 ``` - - - - - edd8bc43 by Krzysztof Gogolewski at 2023-08-22T12:31:20-04:00 Fix MultiWayIf linearity checking (#23814) Co-authored-by: Thomas BAGREL <thomas.bagrel at tweag.io> - - - - - 4ba088d1 by konsumlamm at 2023-08-22T12:32:02-04:00 Update `Control.Concurrent.*` documentation - - - - - 015886ec by ARATA Mizuki at 2023-08-22T15:13:13-04:00 Support 128-bit SIMD on AArch64 via LLVM backend - - - - - 52a6d868 by Krzysztof Gogolewski at 2023-08-22T15:13:51-04:00 Testsuite cleanup - Remove misleading help text in perf_notes, ways are not metrics - Remove no_print_summary - this was used for Phabricator - In linters tests, run 'git ls-files' just once. Previously, it was called on each has_ls_files() - Add ghc-prim.cabal to gitignore, noticed in #23726 - Remove ghc-prim.cabal, it was accidentally committed in 524c60c8cd - - - - - ab40aa52 by Alan Zimmerman at 2023-08-22T15:14:28-04:00 EPA: Use Introduce [DeclTag] in AnnSortKey The AnnSortKey is used to keep track of the order of declarations for printing when the container has split them apart. This applies to HsValBinds and ClassDecl, ClsInstDecl. When making modifications to the list of declarations, the new order must be captured for when it must be printed. For each list of declarations (binds and sigs for a HsValBind) we can just store the list in order. To recreate the list when printing, we must merge them, and this is what the AnnSortKey records. It used to be indexed by SrcSpan, we now simply index by a marker as to which list to take the next item from. - - - - - e7db36c1 by sheaf at 2023-08-23T08:41:28-04:00 Don't attempt pattern synonym error recovery This commit gets rid of the pattern synonym error recovery mechanism (recoverPSB). The rationale is that the fake pattern synonym binding that the recovery mechanism introduced could lead to undesirable knock-on errors, and it isn't really feasible to conjure up a satisfactory binding as pattern synonyms can be used both in expressions and patterns. See Note [Pattern synonym error recovery] in GHC.Tc.TyCl.PatSyn. It isn't such a big deal to eagerly fail compilation on a pattern synonym that doesn't typecheck anyway. Fixes #23467 - - - - - 6ccd9d65 by Ben Gamari at 2023-08-23T08:42:05-04:00 base: Don't use Data.ByteString.Internals.memcpy This function is now deprecated from `bytestring`. Use `Foreign.Marshal.Utils.copyBytes` instead. Fixes #23880. - - - - - 0bfa0031 by Matthew Pickering at 2023-08-23T13:43:48-04:00 hadrian: Uniformly pass buildOptions to all builders in runBuilder In Builder.hs, runBuilderWith mostly ignores the buildOptions in BuildInfo. This leads to hard to diagnose bugs as any build options you pass with runBuilderWithCmdOptions are ignored for many builders. Solution: Uniformly pass buildOptions to the invocation of cmd. Fixes #23845 - - - - - 9cac8f11 by Matthew Pickering at 2023-08-23T13:43:48-04:00 Abstract windows toolchain setup This commit splits up the windows toolchain setup logic into two functions. * FP_INSTALL_WINDOWS_TOOLCHAIN - deals with downloading the toolchain if it isn't already downloaded * FP_SETUP_WINDOWS_TOOLCHAIN - sets the environment variables to point to the correct place FP_SETUP_WINDOWS_TOOLCHAIN is abstracted from the location of the mingw toolchain and also the eventual location where we will install the toolchain in the installed bindist. This is the first step towards #23608 - - - - - 6c043187 by Matthew Pickering at 2023-08-23T13:43:48-04:00 Generate build.mk for bindists The config.mk.in script was relying on some variables which were supposed to be set by build.mk but therefore never were when used to install a bindist. Specifically * BUILD_PROF_LIBS to determine whether we had profiled libraries or not * DYNAMIC_GHC_PROGRAMS to determine whether we had shared libraries or not Not only were these never set but also not really accurate because you could have shared libaries but still statically linked ghc executable. In addition variables like GhcLibWays were just never used, so those have been deleted from the script. Now instead we generate a build.mk file which just directly specifies which RtsWays we have supplied in the bindist and whether we have DYNAMIC_GHC_PROGRAMS. - - - - - fe23629b by Matthew Pickering at 2023-08-23T13:43:48-04:00 hadrian: Add reloc-binary-dist-* targets This adds a command line option to build a "relocatable" bindist. The bindist is created by first creating a normal bindist and then installing it using the `RelocatableBuild=YES` option. This creates a bindist without any wrapper scripts pointing to the libdir. The motivation for this feature is that we want to ship relocatable bindists on windows and this method is more uniform than the ad-hoc method which lead to bugs such as #23608 and #23476 The relocatable bindist can be built with the "reloc-binary-dist" target and supports the same suffixes as the normal "binary-dist" command to specify the compression style. - - - - - 41cbaf44 by Matthew Pickering at 2023-08-23T13:43:48-04:00 packaging: Fix installation scripts on windows/RelocatableBuild case This includes quite a lot of small fixes which fix the installation makefile to work on windows properly. This also required fixing the RelocatableBuild variable which seemed to have been broken for a long while. Sam helped me a lot writing this patch by providing a windows machine to test the changes. Without him it would have taken ages to tweak everything. Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 03474456 by Matthew Pickering at 2023-08-23T13:43:48-04:00 ci: Build relocatable bindist on windows We now build the relocatable bindist target on windows, which means we test and distribute the new method of creating a relocatable bindist. - - - - - d0b48113 by Matthew Pickering at 2023-08-23T13:43:48-04:00 hadrian: Add error when trying to build binary-dist target on windows The binary dist produced by `binary-dist` target doesn't work on windows because of the wrapper script the makefile installs. In order to not surprise any packagers we just give an error if someone tries to build the old binary-dist target rather than the reloc-binary-dist target. - - - - - 7cbf9361 by Matthew Pickering at 2023-08-23T13:43:48-04:00 hadrian: Remove query' logic to use tooldir - - - - - 03fad42e by Matthew Pickering at 2023-08-23T13:43:48-04:00 configure: Set WindresCmd directly and removed unused variables For some reason there was an indirection via the Windres variable before setting WindresCmd. That indirection led to #23855. I then also noticed that these other variables were just not used anywhere when trying to work out what the correct condition was for this bit of the configure script. - - - - - c82770f5 by sheaf at 2023-08-23T13:43:48-04:00 Apply shellcheck suggestion to SUBST_TOOLDIR - - - - - 896e35e5 by sheaf at 2023-08-23T13:44:34-04:00 Compute hints from TcSolverReportMsg This commit changes how hints are handled in conjunction with constraint solver report messages. Instead of storing `[GhcHint]` in the TcRnSolverReport error constructor, we compute the hints depending on the underlying TcSolverReportMsg. This disentangles the logic and makes it easier to add new hints for certain errors. - - - - - a05cdaf0 by Alexander Esgen at 2023-08-23T13:45:16-04:00 users-guide: remove note about fatal Haddock parse failures - - - - - 4908d798 by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Introduce Data.Enum - - - - - f59707c7 by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Num.Integer - - - - - b1054053 by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Num - - - - - 6baa481d by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Num.Natural - - - - - 2ac15233 by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Float - - - - - f3c489de by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Real - - - - - 94f59eaa by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Eliminate module reexport in GHC.Exception The metric increase here isn't strictly due to this commit but it's a rather small, incidental change. Metric Increase: T8095 T13386 Metric Decrease: T8095 T13386 T18304 - - - - - be1fc7df by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add disclaimers in internal modules To warn users that these modules are internal and their interfaces may change with little warning. As proposed in Core Libraries Committee #146 [CLC146]. [CLC146]: https://github.com/haskell/core-libraries-committee/issues/146 - - - - - 0326f3f4 by sheaf at 2023-08-23T17:37:29-04:00 Bump Cabal submodule We need to bump the Cabal submodule to include commit ec75950 which fixes an issue with a dodgy import Rep(..) which relied on GHC bug #23570 - - - - - 0504cd08 by Facundo Domínguez at 2023-08-23T17:38:11-04:00 Fix typos in the documentation of Data.OldList.permutations - - - - - 1420b8cb by Antoine Leblanc at 2023-08-24T16:18:17-04:00 Be more eager in TyCon boot validity checking This commit performs boot-file consistency checking for TyCons into checkValidTyCl. This ensures that we eagerly catch any mismatches, which prevents the compiler from seeing these inconsistencies and panicking as a result. See Note [TyCon boot consistency checking] in GHC.Tc.TyCl. Fixes #16127 - - - - - d99c816f by Finley McIlwaine at 2023-08-24T16:18:55-04:00 Refactor estimation of stack info table provenance This commit greatly refactors the way we compute estimated provenance for stack info tables. Previously, this process was done using an entirely separate traversal of the whole Cmm code stream to build the map from info tables to source locations. The separate traversal is now fused with the Cmm code generation pipeline in GHC.Driver.Main. This results in very significant code generation speed ups when -finfo-table-map is enabled. In testing, this patch reduces code generation times by almost 30% with -finfo-table-map and -O0, and 60% with -finfo-table-map and -O1 or -O2 . Fixes #23103 - - - - - d3e0124c by Finley McIlwaine at 2023-08-24T16:18:55-04:00 Add a test checking overhead of -finfo-table-map We want to make sure we don't end up with poor codegen performance resulting from -finfo-table-map again as in #23103. This test adds a performance test tracking total allocations while compiling ExactPrint with -finfo-table-map. - - - - - fcfc1777 by Ben Gamari at 2023-08-25T10:58:16-04:00 llvmGen: Add export list to GHC.Llvm.MetaData - - - - - 5880fff6 by Ben Gamari at 2023-08-25T10:58:16-04:00 llvmGen: Allow LlvmLits in MetaExprs This omission appears to be an oversight. - - - - - 86ce92a2 by Ben Gamari at 2023-08-25T10:58:16-04:00 compiler: Move platform feature predicates to GHC.Driver.DynFlags These are useful in `GHC.Driver.Config.*`. - - - - - a6a38742 by Ben Gamari at 2023-08-25T10:58:16-04:00 llvmGen: Introduce infrastructure for module flag metadata - - - - - e9af2cf3 by Ben Gamari at 2023-08-25T10:58:16-04:00 llvmGen: Don't pass stack alignment via command line As of https://reviews.llvm.org/D103048 LLVM no longer supports the `-stack-alignment=...` flag. Instead this information is passed via a module flag metadata node. This requires dropping support for LLVM 11 and 12. Fixes #23870 - - - - - a936f244 by Alan Zimmerman at 2023-08-25T10:58:56-04:00 EPA: Keep track of "in" token for WarningTxt category A warning can now be written with a category, e.g. {-# WARNInG in "x-c" e "d" #-} Keep track of the location of the 'in' keyword and string, as well as the original SourceText of the label, in case it uses character escapes. - - - - - 3df8a653 by Matthew Pickering at 2023-08-25T17:42:18-04:00 Remove redundant import in InfoTableProv The copyBytes function is provided by the import of Foreign. Fixes #23889 - - - - - d6f807ec by Ben Gamari at 2023-08-25T17:42:54-04:00 gitlab/issue-template: Mention report-a-bug - - - - - 50b9f75d by Artin Ghasivand at 2023-08-26T20:02:50+03:30 Added StandaloneKindSignature examples to replace CUSKs ones - - - - - 2f6309a4 by Vladislav Zavialov at 2023-08-27T03:47:37-04:00 Remove outdated CPP in compiler/* and template-haskell/* The boot compiler was bumped to 9.4 in cebb5819b43. There is no point supporting older GHC versions with CPP. - - - - - 5248fdf7 by Zubin Duggal at 2023-08-28T15:01:09+05:30 testsuite: Add regression test for #23861 Simon says this was fixed by commit 8d68685468d0b6e922332a3ee8c7541efbe46137 Author: sheaf <sam.derbyshire at gmail.com> Date: Fri Aug 4 15:28:45 2023 +0200 Remove zonk in tcVTA - - - - - b6903f4d by Zubin Duggal at 2023-08-28T12:33:58-04:00 testsuite: Add regression test for #23864 Simon says this was fixed by commit 59202c800f2c97c16906120ab2561f6e1556e4af Author: Sebastian Graf <sebastian.graf at kit.edu> Date: Fri Mar 31 17:35:22 2023 +0200 CorePrep: Eliminate EmptyCase and unsafeEqualityProof in CoreToStg instead We eliminate EmptyCase by way of `coreToStg (Case e _ _ []) = coreToStg e` now. The main reason is that it plays far better in conjunction with eta expansion (as we aim to do for arguments in CorePrep, #23083), because we can discard any arguments, `(case e of {}) eta == case e of {}`, whereas in `(e |> co) eta` it's impossible to discard the argument. - - - - - 9eecdf33 by sheaf at 2023-08-28T18:54:06+00:00 Remove ScopedTypeVariables => TypeAbstractions This commit implements [amendment 604](https://github.com/ghc-proposals/ghc-proposals/pull/604/) to [GHC proposal 448](https://github.com/ghc-proposals/ghc-proposals/pull/448) by removing the implication of language extensions ScopedTypeVariables => TypeAbstractions To limit breakage, we now allow type arguments in constructor patterns when both ScopedTypeVariables and TypeApplications are enabled, but we emit a warning notifying the user that this is deprecated behaviour that will go away starting in GHC 9.12. Fixes #23776 - - - - - fadd5b4d by sheaf at 2023-08-28T18:54:06+00:00 .stderr: ScopedTypeVariables =/> TypeAbstractions This commit accepts testsuite changes for the changes in the previous commit, which mean that TypeAbstractions is no longer implied by ScopedTypeVariables. - - - - - 4f5fb500 by Greg Steuck at 2023-08-29T07:55:13-04:00 Repair `codes` test on OpenBSD by explicitly requesting extended RE - - - - - 6bbde581 by Vasily Sterekhov at 2023-08-29T12:06:58-04:00 Add test for #23540 `T23540.hs` makes use of `explainEv` from `HieQueries.hs`, so `explainEv` has been moved to `TestUtils.hs`. - - - - - 257bb3bd by Vasily Sterekhov at 2023-08-29T12:06:58-04:00 Add test for #23120 - - - - - 4f192947 by Vasily Sterekhov at 2023-08-29T12:06:58-04:00 Make some evidence uses reachable by toHie Resolves #23540, #23120 This adds spans to certain expressions in the typechecker and renamer, and lets 'toHie' make use of those spans. Therefore the relevant evidence uses for the following syntax will now show up under the expected nodes in 'HieAst's: - Overloaded literals ('IsString', 'Num', 'Fractional') - Natural patterns and N+k patterns ('Eq', 'Ord', and instances from the overloaded literals being matched on) - Arithmetic sequences ('Enum') - Monadic bind statements ('Monad') - Monadic body statements ('Monad', 'Alternative') - ApplicativeDo ('Applicative', 'Functor') - Overloaded lists ('IsList') Also see Note [Source locations for implicit function calls] In the process of handling overloaded lists I added an extra 'SrcSpan' field to 'VAExpansion' - this allows us to more accurately reconstruct the locations from the renamer in 'rebuildHsApps'. This also happens to fix #23120. See the additions to Note [Looking through HsExpanded] - - - - - fe9fcf9d by Sylvain Henry at 2023-08-29T12:07:50-04:00 ghc-heap: rename C file (fix #23898) - - - - - b60d6576 by Krzysztof Gogolewski at 2023-08-29T12:08:29-04:00 Misc cleanup - Builtin.PrimOps: ReturnsAlg was used only for unboxed tuples. Rename to ReturnsTuple. - Builtin.Utils: use SDoc for a panic message. The comment about <<details unavailable>> was obsoleted by e8d356773b56. - TagCheck: fix wrong logic. It was zipping a list 'args' with its version 'args_cmm' after filtering. - Core.Type: remove an outdated 1999 comment about unlifted polymorphic types - hadrian: remove leftover debugging print - - - - - 3054fd6d by Krzysztof Gogolewski at 2023-08-29T12:09:08-04:00 Add a regression test for #23903 The bug has been fixed by commit bad2f8b8aa8424. - - - - - 21584b12 by Ben Gamari at 2023-08-29T19:52:02-04:00 README: Refer to ghc-hq repository for contributor and governance information - - - - - e542d590 by sheaf at 2023-08-29T19:52:40-04:00 Export setInertSet from GHC.Tc.Solver.Monad We used to export getTcSInerts and setTcSInerts from GHC.Tc.Solver.Monad. These got renamed to getInertSet/setInertSet in e1590ddc. That commit also removed the export of setInertSet, but that function is useful for the GHC API. - - - - - 694ec5b1 by sheaf at 2023-08-30T10:18:32-04:00 Don't bundle children for non-parent Avails We used to bundle all children of the parent Avail with things that aren't the parent, e.g. with class C a where type T a meth :: .. we would bundle the whole Avail (C, T, meth) with all of C, T and meth, instead of only with C. Avoiding this fixes #23570 - - - - - d926380d by Krzysztof Gogolewski at 2023-08-30T10:19:08-04:00 Fix typos - - - - - d07080d2 by Josh Meredith at 2023-08-30T19:42:32-04:00 JS: Implement missing C functions `rename`, `realpath`, and `getcwd` (#23806) - - - - - e2940272 by David Binder at 2023-08-30T19:43:08-04:00 Bump submodules of hpc and hpc-bin to version 0.7.0.0 hpc 0.7.0.0 dropped SafeHaskell safety guarantees in order to simplify compatibility with newer versions of the directory package which dropped all SafeHaskell guarantees. - - - - - 5d56d05c by David Binder at 2023-08-30T19:43:08-04:00 Bump hpc bound in ghc.cabal.in - - - - - 99fff496 by Dominik Schrempf at 2023-08-31T00:04:46-04:00 ghc classes documentation: rm redundant comment - - - - - fe021bab by Dominik Schrempf at 2023-08-31T00:04:46-04:00 prelude documentation: various nits - - - - - 48c84547 by Dominik Schrempf at 2023-08-31T00:04:46-04:00 integer documentation: minor corrections - - - - - 20cd12f4 by Dominik Schrempf at 2023-08-31T00:04:46-04:00 real documentation: nits - - - - - dd39bdc0 by sheaf at 2023-08-31T00:05:27-04:00 Add a test for #21765 This issue (of reporting a constraint as being redundant even though removing it causes typechecking to fail) was fixed in aed1974e. This commit simply adds a regression test. Fixes #21765 - - - - - f1ec3628 by Andrew Lelechenko at 2023-08-31T23:53:30-04:00 Export foldl' from Prelude and bump submodules See https://github.com/haskell/core-libraries-committee/issues/167 for discussion Metric Decrease: T8095 T13386 Metric Increase: T13386 T8095 T8095 ghc/alloc decreased on x86_64, but increased on aarch64. T13386 ghc/alloc decreased on x86_64-windows, but increased on other platforms. Neither has anything to do with `foldl'`, so I conclude that both are flaky. - - - - - 3181b97d by Gergő Érdi at 2023-08-31T23:54:06-04:00 Allow cross-tyvar defaulting proposals from plugins Fixes #23832. - - - - - 495b2241 by Matthew Pickering at 2023-09-01T13:02:07+02:00 Fix issue with duplicate reexported definitions (T23616) When a class method was reexported, it's default methods were also showing up in the generated html page. The simplest and most non-invasive fix is to not look for the default method if we are just exporting the class method.. because the backends are just showing default methods when the whole class is exported. In general it would be worthwhile to rewrite this bit of code I think as the logic and what gets included is split over `lookupDocs` and `availExportDecl` it would be clearer to combine the two. The result of lookupDocs is always just passed to availExportDecl so it seems simpler and more obvious to just write the function directly. - - - - - e4af506e by Sebastian Graf at 2023-09-01T14:29:12-04:00 Clarify Note [GlobalId/LocalId] after CorePrep (#23797) Fixes #23797. - - - - - ac29787c by Sylvain Henry at 2023-09-01T14:30:02-04:00 Fix warning with UNPACK on sum type (#23921) - - - - - 9765ac7b by Zubin Duggal at 2023-09-05T00:37:45-04:00 hadrian: track python dependencies in doc rules - - - - - 1578215f by sheaf at 2023-09-05T00:38:26-04:00 Bump Haddock to fix #23616 This commit updates the Haddock submodule to include the fix to #23616. Fixes #23616 - - - - - 5a2fe35a by David Binder at 2023-09-05T00:39:07-04:00 Fix example in GHC user guide in SafeHaskell section The example given in the SafeHaskell section uses an implementation of Monad which no longer works. This MR removes the non-canonical return instance and adds the necessary instances of Functor and Applicative. - - - - - 291d81ae by Matthew Pickering at 2023-09-05T14:03:10-04:00 driver: Check transitive closure of haskell package dependencies when deciding whether to relink We were previously just checking whether direct package dependencies had been modified. This caused issues when compiling without optimisations as we wouldn't relink the direct dependency if one of its dependenices changed. Fixes #23724 - - - - - 35da0775 by Krzysztof Gogolewski at 2023-09-05T14:03:47-04:00 Re-export GHC.Utils.Panic.Plain from GHC.Utils.Panic Fixes #23930 - - - - - 6551824d by Finley McIlwaine at 2023-09-05T13:06:57-07:00 Remove fake export of `FUN` from Prelude This prevents `data FUN` from being shown at the top of the Prelude docs. Fixes \#23920 on GHC. - - - - - 3930d793 by Jaro Reinders at 2023-09-06T18:42:55-04:00 Make STG rewriter produce updatable closures - - - - - 0104221a by Krzysztof Gogolewski at 2023-09-06T18:43:32-04:00 configure: update message to use hadrian (#22616) - - - - - b34f8586 by Alan Zimmerman at 2023-09-07T10:58:38-04:00 EPA: Incorrect locations for UserTyVar with '@' In T13343.hs, the location for the @ is not within the span of the surrounding UserTyVar. type Bad @v = (forall (v1 :: RuntimeRep) (a1 :: TYPE v). a1) :: TYPE v Widen it so it is captured. Closes #23887 - - - - - 8046f020 by Finley McIlwaine at 2023-09-07T10:59:15-04:00 Bump haddock submodule to fix #23920 Removes the fake export of `FUN` from Prelude. Fixes #23920. Bumps haddock submodule. - - - - - e0aa8c6e by Krzysztof Gogolewski at 2023-09-07T11:00:03-04:00 Fix wrong role in mkSelCo_maybe In the Lint failure in #23938, we start with a coercion Refl :: T a ~R T a, and call mkSelCo (SelTyCon 1 nominal) Refl. The function incorrectly returned Refl :: a ~R a. The returned role should be nominal, according to the SelCo rule: co : (T s1..sn) ~r0 (T t1..tn) r = tyConRole tc r0 i ---------------------------------- SelCo (SelTyCon i r) : si ~r ti In this test case, r is nominal while r0 is representational. - - - - - 1d92f2df by Gergő Érdi at 2023-09-08T04:04:30-04:00 If we have multiple defaulting plugins, then we should zonk in between them after any defaulting has taken place, to avoid a defaulting plugin seeing a metavariable that has already been filled. Fixes #23821. - - - - - eaee4d29 by Gergő Érdi at 2023-09-08T04:04:30-04:00 Improvements to the documentation of defaulting plugins Based on @simonpj's draft and comments in !11117 - - - - - ede3df27 by Alan Zimmerman at 2023-09-08T04:05:06-04:00 EPA: Incorrect span for LWarnDec GhcPs The code (from T23465.hs) {-# WARNInG in "x-c" e "d" #-} e = e gives an incorrect span for the LWarnDecl GhcPs Closes #23892 It also fixes the Test23465/Test23464 mixup - - - - - a0ccef7a by Krzysztof Gogolewski at 2023-09-08T04:05:42-04:00 Valid hole fits: don't suggest unsafeCoerce (#17940) - - - - - 9ab5a448 by Alan Zimmerman at 2023-09-08T18:26:53+01:00 Match changes in wip/az/T23885-unicode-funtycon - - - - - 88b942c4 by Oleg Grenrus at 2023-09-08T19:58:42-04:00 Add warning for badly staged types. Resolves #23829. The stage violation results in out-of-bound names in splices. Technically this is an error, but someone might rely on this!? Internal changes: - we now track stages for TyVars. - thLevel (RunSplice _) = 0, instead of panic, as reifyInstances does in fact rename its argument type, and it can contain variables. - - - - - 9861f787 by Ben Gamari at 2023-09-08T19:59:19-04:00 rts: Fix invalid symbol type I suspect this code is dead since we haven't observed this failing despite the obviously incorrect macro name. - - - - - 03ed6a9a by Ben Gamari at 2023-09-08T19:59:19-04:00 testsuite: Add simple test exercising C11 atomics in GHCi See #22012. - - - - - 1aa5733a by Ben Gamari at 2023-09-08T19:59:19-04:00 rts/RtsSymbols: Add AArch64 outline atomic operations Fixes #22012 by adding the symbols described in https://github.com/llvm/llvm-project/blob/main/llvm/docs/Atomics.rst#libcalls-atomic. Ultimately this would be better addressed by #22011, but this is a first step in the right direction and fixes the immediate symptom. Note that we dropped the `__arch64_cas16` operations as these provided by all platforms's compilers. Also, we don't link directly against the libgcc/compiler-rt definitions but rather provide our own wrappers to work around broken toolchains (e.g. https://bugs.gentoo.org/868018). Generated via https://gitlab.haskell.org/ghc/ghc/-/snippets/5733. - - - - - 8f7d3041 by Matthew Pickering at 2023-09-08T19:59:55-04:00 ci: Build debian12 and fedora38 bindists This adds builds for the latest releases for fedora and debian We build these bindists in nightly and release pipelines. - - - - - a1f0d55c by Felix Leitz at 2023-09-08T20:00:37-04:00 Fix documentation around extension implication for MultiParamTypeClasses/ConstrainedClassMethods. - - - - - 98166389 by Teo Camarasu at 2023-09-12T04:30:54-04:00 docs: move -xn flag beside --nonmoving-gc It makes sense to have these beside each other as they are aliases. - - - - - f367835c by Teo Camarasu at 2023-09-12T04:30:55-04:00 nonmoving: introduce a family of dense allocators Supplement the existing power 2 sized nonmoving allocators with a family of dense allocators up to a configurable threshold. This should reduce waste from rounding up block sizes while keeping the amount of allocator sizes manageable. This patch: - Adds a new configuration option `--nonmoving-dense-allocator-count` to control the amount of these new dense allocators. - Adds some constants to `NonmovingAllocator` in order to keep marking fast with the new allocators. Resolves #23340 - - - - - 2b07bf2e by Teo Camarasu at 2023-09-12T04:30:55-04:00 Add changelog entry for #23340 - - - - - f96fe681 by sheaf at 2023-09-12T04:31:44-04:00 Use printGhciException in run{Stmt, Decls} When evaluating statements in GHCi, we need to use printGhciException instead of the printException function that GHC provides in order to get the appropriate error messages that are customised for ghci use. - - - - - d09b932b by psilospore at 2023-09-12T04:31:44-04:00 T23686: Suggest how to enable Language Extension when in ghci Fixes #23686 - - - - - da30f0be by Matthew Craven at 2023-09-12T04:32:24-04:00 Unarise: Split Rubbish literals in function args Fixes #23914. Also adds a check to STG lint that these args are properly unary or nullary after unarisation - - - - - 261b6747 by Matthew Pickering at 2023-09-12T04:33:04-04:00 darwin: Bump MAXOSX_DEPLOYMENT_TARGET to 10.13 This bumps the minumum supported version to 10.13 (High Sierra) which is 6 years old at this point. Fixes #22938 - - - - - f418f919 by Mario Blažević at 2023-09-12T04:33:45-04:00 Fix TH pretty-printing of nested GADTs, issue #23937 This commit fixes `Language.Haskell.TH.Ppr.pprint` so that it correctly pretty-prints GADTs declarations contained within data family instances. Fixes #23937 - - - - - d7a64753 by John Ericson at 2023-09-12T04:34:20-04:00 Put hadrian non-bootstrap plans through `jq` This makes it possible to review changes with conventional diffing tools. This is picking up where ad8cfed4195b1bbfc15b841f010e75e71f63157d left off. - - - - - ff0a709a by Sylvain Henry at 2023-09-12T08:46:28-04:00 JS: fix some tests - Tests using Setup programs need to pass --with-hc-pkg - Several other fixes See https://gitlab.haskell.org/ghc/ghc/-/wikis/javascript-backend/bug_triage for the current status - - - - - fc86f0e7 by Krzysztof Gogolewski at 2023-09-12T08:47:04-04:00 Fix in-scope set assertion failure (#23918) Patch by Simon - - - - - 21a906c2 by Matthew Pickering at 2023-09-12T17:21:04+02:00 Add -Winconsistent-flags warning The warning fires when inconsistent command line flags are passed. For example: * -dynamic-too and -dynamic * -dynamic-too on windows * -O and --interactive * etc This is on by default and allows users to control whether the warning is displayed and whether it should be an error or not. Fixes #22572 - - - - - dfc4f426 by Krzysztof Gogolewski at 2023-09-12T20:31:35-04:00 Avoid serializing BCOs with the internal interpreter Refs #23919 - - - - - 9217950b by Finley McIlwaine at 2023-09-13T08:06:03-04:00 Fix numa auto configure - - - - - 98e7c1cf by Simon Peyton Jones at 2023-09-13T08:06:40-04:00 Add -fno-cse to T15426 and T18964 This -fno-cse change is to avoid these performance tests depending on flukey CSE stuff. Each contains several independent tests, and we don't want them to interact. See #23925. By killing CSE we expect a 400% increase in T15426, and 100% in T18964. Metric Increase: T15426 T18964 - - - - - 236a134e by Simon Peyton Jones at 2023-09-13T08:06:40-04:00 Tiny refactor canEtaReduceToArity was only called internally, and always with two arguments equal to zero. This patch just specialises the function, and renames it to cantEtaReduceFun. No change in behaviour. - - - - - 56b403c9 by Ben Gamari at 2023-09-13T19:21:36-04:00 spec-constr: Lift argument limit for SPEC-marked functions When the user adds a SPEC argument to a function, they are informing us that they expect the function to be specialised. However, previously this instruction could be preempted by the specialised-argument limit (sc_max_args). Fix this. This fixes #14003. - - - - - 6840012e by Simon Peyton Jones at 2023-09-13T19:22:13-04:00 Fix eta reduction Issue #23922 showed that GHC was bogusly eta-reducing a join point. We should never eta-reduce (\x -> j x) to j, if j is a join point. It is extremly difficult to trigger this bug. It took me 45 mins of trying to make a small tests case, here immortalised as T23922a. - - - - - e5c00092 by Andreas Klebinger at 2023-09-14T08:57:43-04:00 Profiling: Properly escape characters when using `-pj`. There are some ways in which unusual characters like quotes or others can make it into cost centre names. So properly escape these. Fixes #23924 - - - - - ec490578 by Ellie Hermaszewska at 2023-09-14T08:58:24-04:00 Use clearer example variable names for bool eliminator - - - - - 5126a2fe by Sylvain Henry at 2023-09-15T11:18:02-04:00 Add missing int64/word64-to-double/float rules (#23907) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/203 - - - - - 566ef411 by Mario Blažević at 2023-09-15T11:18:43-04:00 Fix and test TH pretty-printing of type operator role declarations This commit fixes and tests `Language.Haskell.TH.Ppr.pprint` so that it correctly pretty-prints `type role` declarations for operator names. Fixes #23954 - - - - - 8e05c54a by Simon Peyton Jones at 2023-09-16T01:42:33-04:00 Use correct FunTyFlag in adjustJoinPointType As the Lint error in #23952 showed, the function adjustJoinPointType was failing to adjust the FunTyFlag when adjusting the type. I don't think this caused the seg-fault reported in the ticket, but it is definitely. This patch fixes it. It is tricky to come up a small test case; Krzysztof came up with this one, but it only triggers a failure in GHC 9.6. - - - - - 778c84b6 by Pierre Le Marre at 2023-09-16T01:43:15-04:00 Update to Unicode 15.1.0 See: https://www.unicode.org/versions/Unicode15.1.0/ - - - - - f9d79a6c by Alan Zimmerman at 2023-09-18T00:00:14-04:00 EPA: track unicode version for unrestrictedFunTyCon Closes #23885 Updates haddock submodule - - - - - 9374f116 by Andrew Lelechenko at 2023-09-18T00:00:54-04:00 Bump parsec submodule to allow text-2.1 and bytestring-0.12 - - - - - 7ca0240e by Ben Gamari at 2023-09-18T15:16:48-04:00 base: Advertise linear time of readFloat As noted in #23538, `readFloat` has runtime that scales nonlinearly in the size of its input. Consequently, its use on untrusted input can be exploited as a denial-of-service vector. Point this out and suggest use of `read` instead. See #23538. - - - - - f3f58f13 by Simon Peyton Jones at 2023-09-18T15:17:24-04:00 Remove dead code GHC.CoreToStg.Prep.canFloat This function never fires, so we can delete it: #23965. - - - - - ccab5b15 by Ben Gamari at 2023-09-18T15:18:02-04:00 base/changelog: Move fix for #23907 to 9.8.1 section Since the fix was backported to 9.8.1 - - - - - 51b57d65 by Matthew Pickering at 2023-09-19T08:44:31-04:00 Add aarch64 alpine bindist This is dynamically linked and makes creating statically linked executables more straightforward. Fixes #23482 - - - - - 02c87213 by Matthew Pickering at 2023-09-19T08:44:31-04:00 Add aarch64-deb11 bindist This adds a debian 11 release job for aarch64. Fixes #22005 - - - - - 8b61dfd6 by Alexis King at 2023-09-19T08:45:13-04:00 Don’t store the async exception masking state in CATCH frames - - - - - 86d2971e by doyougnu at 2023-09-19T19:08:19-04:00 compiler,ghci: error codes link to HF error index closes: #23259 - adds -fprint-error-index-links={auto|always|never} flag - - - - - 5f826c18 by sheaf at 2023-09-19T19:09:03-04:00 Pass quantified tyvars in tcDefaultAssocDecl This commit passes the correct set of quantified type variables written by the user in associated type default declarations for validity checking. This ensures that validity checking of associated type defaults mirrors that of standalone type family instances. Fixes #23768 (see testcase T23734 in subsequent commit) - - - - - aba18424 by sheaf at 2023-09-19T19:09:03-04:00 Avoid panic in mkGADTVars This commit avoids panicking in mkGADTVars when we encounter a type variable as in #23784 that is bound by a user-written forall but not actually used. Fixes #23784 - - - - - a525a92a by sheaf at 2023-09-19T19:09:03-04:00 Adjust reporting of unused tyvars in data FamInsts This commit adjusts the validity checking of data family instances to improve the reporting of unused type variables. See Note [Out of scope tvs in data family instances] in GHC.Tc.Validity. The problem was that, in a situation such as data family D :: Type data instance forall (d :: Type). D = MkD the RHS passed to 'checkFamPatBinders' would be the TyCon app R:D d which mentions the type variable 'd' quantified in the user-written forall. Thus, when computing the set of unused type variables in the RHS of the data family instance, we would find that 'd' is used, and report a strange error message that would say that 'd' is not bound on the LHS. To fix this, we special-case the data-family instance case, manually extracting all the type variables that appear in the arguments of all the data constructores of the data family instance. Fixes #23778 - - - - - 28dd52ee by sheaf at 2023-09-19T19:09:03-04:00 Unused tyvars in FamInst: only report user tyvars This commit changes how we perform some validity checking for coercion axioms to mirror how we handle default declarations for associated type families. This allows us to keep track of whether type variables in type and data family instances were user-written or not, in order to only report the user-written ones in "unused type variable" error messages. Consider for example: {-# LANGUAGE PolyKinds #-} type family F type instance forall a. F = () In this case, we get two quantified type variables, (k :: Type) and (a :: k); the second being user-written, but the first is introduced by the typechecker. We should only report 'a' as being unused, as the user has no idea what 'k' is. Fixes #23734 - - - - - 1eed645c by sheaf at 2023-09-19T19:09:03-04:00 Validity: refactor treatment of data families This commit refactors the reporting of unused type variables in type and data family instances to be more principled. This avoids ad-hoc logic in the treatment of data family instances. - - - - - 35bc506b by John Ericson at 2023-09-19T19:09:40-04:00 Remove `ghc-cabal` It is dead code since the Make build system was removed. I tried to go over every match of `git grep -i ghc-cabal` to find other stray bits. Some of those might be workarounds that can be further removed. - - - - - 665ca116 by John Paul Adrian Glaubitz at 2023-09-19T19:10:39-04:00 Re-add unregisterised build support for sparc and sparc64 Closes #23959 - - - - - 142f8740 by Matthew Pickering at 2023-09-19T19:11:16-04:00 Bump ci-images to use updated version of Alex Fixes #23977 - - - - - fa977034 by John Ericson at 2023-09-21T12:55:25-04:00 Use Cabal 3.10 for Hadrian We need the newer version for `CABAL_FLAG_*` env vars for #17191. - - - - - a5d22cab by John Ericson at 2023-09-21T12:55:25-04:00 hadrian: `need` any `configure` script we will call When the script is changed, we should reconfigure. - - - - - db882b57 by John Ericson at 2023-09-21T12:55:25-04:00 hadrian: Make it easier to debug Cabal configure Right now, output is squashed. This make per-package configure scripts extremely hard to maintain, because we get vague "library is missing" errors when the actually probably is usually completely unrelated except for also involving the C/C++ toolchain. (I can always pass `-VVV` to Hadrian locally, but these errors are subtle and I often cannot reproduce them locally!) `--disable-option-checking` was added back in 75c6e0684dda585c37b4ac254cd7a13537a59a91 but seems to be a bit overkill; if other flags are passed that are not recognized behind the two from Cabal mentioned in the former comment, we *do* want to know about it. - - - - - 7ed65f5a by John Ericson at 2023-09-21T12:55:25-04:00 hadrian: Increase verbosity of certain cabal commands This is a hack to get around the cabal function we're calling *decreasing* the verbosity it passes to another function, which is the stuff we often actually care about. Sigh. Keeping this a separate commit so if this makes things too verbose it is easy to revert. - - - - - a4fde569 by John Ericson at 2023-09-21T12:55:25-04:00 rts: Move most external symbols logic to the configure script This is much more terse because we are programmatically handling the leading underscore. `findPtr` however is still handled in the Cabal file because we need a newer Cabal to pass flags to the configure script automatically. Co-Authored-By: Ben Gamari <ben at well-typed.com> - - - - - 56cc85fb by Andrew Lelechenko at 2023-09-21T12:56:21-04:00 Bump Cabal submodule to allow text-2.1 and bytestring-0.12 - - - - - 0cd6148c by Matthew Pickering at 2023-09-21T12:56:21-04:00 hadrian: Generate Distribution/Fields/Lexer.x before creating a source-dist - - - - - b10ba6a3 by Andrew Lelechenko at 2023-09-21T12:56:21-04:00 Bump hadrian's index-state to upgrade alex at least to 3.2.7.3 - - - - - 11ecc37b by Luite Stegeman at 2023-09-21T12:57:03-04:00 JS: correct file size and times Programs produced by the JavaScript backend were returning incorrect file sizes and modification times, causing cabal related tests to fail. This fixes the problem and adds an additional test that verifies basic file information operations. fixes #23980 - - - - - b35fd2cd by Ben Gamari at 2023-09-21T12:57:39-04:00 gitlab-ci: Drop libiserv from upload_ghc_libs libiserv has been merged into the ghci package. - - - - - 37ad04e8 by Ben Gamari at 2023-09-21T12:58:15-04:00 testsuite: Fix Windows line endings - - - - - 5795b365 by Ben Gamari at 2023-09-21T12:58:15-04:00 testsuite: Use makefile_test - - - - - 15118740 by Ben Gamari at 2023-09-21T12:58:55-04:00 system-cxx-std-lib: Add license and description - - - - - 0208f1d5 by Ben Gamari at 2023-09-21T12:59:33-04:00 gitlab/issue-templates: Rename bug.md -> default.md So that it is visible by default. - - - - - 23cc3f21 by Andrew Lelechenko at 2023-09-21T20:18:11+01:00 Bump submodule text to 2.1 - - - - - b8e4fe23 by Andrew Lelechenko at 2023-09-22T20:05:05-04:00 Bump submodule unix to 2.8.2.1 - - - - - 54b2016e by John Ericson at 2023-09-23T11:40:41-04:00 Move lib{numa,dw} defines to RTS configure Clean up the m4 to handle the auto case always and be more consistent. Also simplify the CPP --- we should always have both headers if we are using libnuma. "side effects" (AC_DEFINE, and AC_SUBST) are removed from the macros to better separate searching from actions taken based on search results. This might seem overkill now, but will make shuffling logic between configure scripts easier later. The macro comments are converted from `dnl` to `#` following the recomendation in https://www.gnu.org/software/autoconf/manual/autoconf-2.71/html_node/Macro-Definitions.html - - - - - d51b601b by John Ericson at 2023-09-23T11:40:50-04:00 Shuffle libzstd configuring between scripts Like the prior commit for libdw and libnuma, `AC_DEFINE` to RTS configure, `AC_SUBST` goes to the top-level configure script, and the documentation of the m4 macro is improved. - - - - - d1425af0 by John Ericson at 2023-09-23T11:41:03-04:00 Move `FP_ARM_OUTLINE_ATOMICS` to RTS configure It is just `AC_DEFINE` it belongs there instead. - - - - - 18de37e4 by John Ericson at 2023-09-23T11:41:03-04:00 Move mmap in the runtime linker check to the RTS configure `AC_DEFINE` should go there instead. - - - - - 74132c2b by Andrew Lelechenko at 2023-09-25T21:56:54-04:00 Elaborate comment on GHC_NO_UNICODE - - - - - de142aa2 by Ben Gamari at 2023-09-26T15:25:03-04:00 gitlab-ci: Mark T22012 as broken on CentOS 7 Due to #23979. - - - - - 6a896ce8 by Teo Camarasu at 2023-09-26T15:25:39-04:00 hadrian: better error for failing to find file's dependencies Resolves #24004 - - - - - d697a6c2 by Stefan Holdermans at 2023-09-26T20:58:37+00:00 Refactor uses of `partitionEithers . map` This patch changes occurences of the idiom `partitionEithers (map f xs)` by the simpler form `partitionWith f xs` where `partitionWith` is the utility function defined in `GHC.Utils.Misc`. Resolves: #23953 - - - - - 8a2968b7 by Stefan Holdermans at 2023-09-26T20:58:37+00:00 Refactor uses of `partitionEithers <$> mapM f xs` This patch changes occurences of the idiom `partitionEithers <$> mapM f xs` by the simpler form `partitionWithM f xs` where `partitionWithM` is a utility function newly added to `GHC.Utils.Misc`. - - - - - 6a27eb97 by Stefan Holdermans at 2023-09-26T20:58:37+00:00 Mark `GHC.Utils.Misc.partitionWithM` as inlineable This patch adds an `INLINEABLE` pragma for `partitionWithM` to ensure that the right-hand side of the definition of this function remains available for specialisation at call sites. - - - - - f1e5245a by David Binder at 2023-09-27T01:19:00-04:00 Add RTS option to supress tix file - - - - - 1f43124f by David Binder at 2023-09-27T01:19:00-04:00 Add expected output to testsuite in test interface-stability/base-exports - - - - - b9d2c354 by David Binder at 2023-09-27T01:19:00-04:00 Expose HpcFlags and getHpcFlags from GHC.RTS.Flags - - - - - 345675c6 by David Binder at 2023-09-27T01:19:00-04:00 Fix expected output of interface-stability test - - - - - 146e1c39 by David Binder at 2023-09-27T01:19:00-04:00 Implement getHpcFlags - - - - - 61ba8e20 by David Binder at 2023-09-27T01:19:00-04:00 Add section in user guide - - - - - ea05f890 by David Binder at 2023-09-27T01:19:01-04:00 Rename --emit-tix-file to --write-tix-file - - - - - cabce2ce by David Binder at 2023-09-27T01:19:01-04:00 Update the golden files for interface stability - - - - - 1dbdb9d0 by Krzysztof Gogolewski at 2023-09-27T01:19:37-04:00 Refactor: introduce stgArgRep The function 'stgArgType' returns the type in STG. But this violates the abstraction: in STG we're supposed to operate on PrimReps. This introduces stgArgRep ty = typePrimRep (stgArgType ty) stgArgRep1 ty = typePrimRep1 (stgArgType ty) stgArgRep_maybe ty = typePrimRep_maybe (stgArgType ty) stgArgType is still directly used for unboxed tuples (should be fixable), FFI and in ticky. - - - - - b02f8042 by Mario Blažević at 2023-09-27T17:33:28-04:00 Fix TH pretty-printer's parenthesization This PR Fixes `Language.Haskell.TH.Ppr.pprint` so it correctly emits parentheses where needed. Fixes #23962, #23968, #23971, and #23986 - - - - - 79104334 by Krzysztof Gogolewski at 2023-09-27T17:34:04-04:00 Add a testcase for #17564 The code in the ticket relied on the behaviour of Derived constraints. Derived constraints were removed in GHC 9.4 and now the code works as expected. - - - - - d7a80143 by sheaf at 2023-09-28T03:25:53-04:00 lint-codes: add new modes of operation This commit adds two new modes of operation to the lint-codes utility: list - list all statically used diagnostic codes outdated - list all outdated diagnostic codes The previous behaviour is now: test - test consistency and coverage of diagnostic codes - - - - - 477d223c by sheaf at 2023-09-28T03:25:53-04:00 lint codes: avoid using git-grep We manually traverse through the filesystem to find the diagnostic codes embedded in .stdout and .stderr files, to avoid any issues with old versions of grep. Fixes #23843 - - - - - a38ae69a by sheaf at 2023-09-28T03:25:53-04:00 lint-codes: add Hadrian targets This commit adds new Hadrian targets: codes, codes:used - list all used diagnostic codes codes:outdated - list outdated diagnostic codes This allows users to easily query GHC for used and outdated diagnostic codes, e.g. hadrian/build -j --flavour=<..> codes will list all used diagnostic codes in the command line by running the lint-codes utility in the "list codes" mode of operation. The diagnostic code consistency and coverage test is still run as usual, through the testsuite: hadrian/build test --only="codes" - - - - - 9cdd629b by Ben Gamari at 2023-09-28T03:26:29-04:00 hadrian: Install LICENSE files in bindists Fixes #23548. - - - - - b8ebf876 by Matthew Craven at 2023-09-28T03:27:05-04:00 Fix visibility when eta-reducing a type lambda Fixes #24014. - - - - - d3874407 by Torsten Schmits at 2023-09-30T16:08:10-04:00 Fix several mistakes around free variables in iface breakpoints Fixes #23612 , #23607, #23998 and #23666. MR: !11026 The fingerprinting logic in `Iface.Recomp` failed lookups when processing decls containing breakpoints for two reasons: * IfaceBreakpoint created binders for free variables instead of expressions * When collecting free names for the dependency analysis for fingerprinting, breakpoint FVs were skipped - - - - - ef5342cd by Simon Peyton Jones at 2023-09-30T16:08:48-04:00 Refactor to combine HsLam and HsLamCase This MR is pure refactoring (#23916): * Combine `HsLam` and `HsLamCase` * Combine `HsCmdLam` and `HsCmdLamCase` This just arranges to treat uniformly \x -> e \case pi -> ei \cases pis -> ie In the exising code base the first is treated differently to the latter two. No change in behaviour. More specifics: * Combine `HsLam` and `HsLamCase` (constructors of `Language.Haskell.Syntax.Expr.HsExpr`) into one data construtor covering * Lambda * `\case` * `\cases` * The new `HsLam` has an argument of type `HsLamVariant` to distinguish the three cases. * Similarly, combine `HsCmdLam` and `HsCmdLamCase` (constructors of `Language.Haskell.Syntax.Expr.HsCmd` ) into one. * Similarly, combine `mkHsLamPV` and `mkHsLamCasePV` (methods of class `DisambECP`) into one. (Thank you Alan Zimmerman.) * Similarly, combine `LambdaExpr` and `LamCaseAlt` (constructors of `Language.Haskell.Syntax.Expr.HsMatchContext`) into one: `LamAlt` with a `HsLamVariant` argument. * Similarly, combine `KappaExpr` and `ArrowLamCaseAlt` (constructors of `Language.Haskell.Syntax.Expr.HsArrowMatchContext`) into one: `ArrowLamAlt` with a `HsLamVariant` argument. * Similarly, combine `PsErrLambdaInPat` and `PsErrLambdaCaseInPat` (constructors of `GHC.Parser.Errors.Ppr.PsError`) into one. * Similarly, combine `PsErrLambdaInPat` and `PsErrLambdaCaseInPat` (constructors of `GHC.Parser.Errors.Ppr.PsError`) into one. * In the same `PsError` data type, combine `PsErrLambdaCmdInFunAppCmd` and `PsErrLambdaCaseCmdInFunAppCmd` into one. * In the same `PsError` data tpye, combine `PsErrLambdaInFunAppExpr` and `PsErrLambdaCaseInFunAppExpr` into one. p* Smilarly combine `ExpectedFunTyLam` and `ExpectedFunTyLamCase` (constructors of `GHC.Tc.Types.Origin.ExpectedFunTyOrigin`) into one. Phew! - - - - - b048bea0 by Andreas Klebinger at 2023-09-30T16:09:24-04:00 Arm: Make ppr methods easier to use by not requiring NCGConfig - - - - - 2adc0508 by Andreas Klebinger at 2023-09-30T16:09:24-04:00 AArch64: Fix broken conditional jumps for offsets >= 1MB Rewrite conditional jump instructions with offsets >= 1MB to use unconditional jumps to avoid overflowing the immediate. Fixes #23746 - - - - - 1424f790 by Alan Zimmerman at 2023-09-30T16:10:00-04:00 EPA: Replace Monoid with NoAnn We currently use the Monoid class as a constraint on Exact Print Annotation functions, so we can use mempty. But this leads to requiring Semigroup instances too, which do not always make sense. Instead, introduce a class NoAnn, with a function noAnn analogous to mempty. Closes #20372 Updates haddock submodule - - - - - c1a3ecde by Ben Gamari at 2023-09-30T16:10:36-04:00 users-guide: Refactor handling of :base-ref: et al. - - - - - bc204783 by Richard Eisenberg at 2023-10-02T14:50:52+02:00 Simplify and correct nasty case in coercion opt This fixes #21062. No test case, because triggering this code seems challenging. - - - - - 9c9ca67e by Andrew Lelechenko at 2023-10-04T05:42:28-04:00 Bump bytestring submodule to 0.12.0.2 - - - - - 4e46dc2b by Andrew Lelechenko at 2023-10-04T05:42:28-04:00 Inline bucket_match - - - - - f6b2751f by Ben Gamari at 2023-10-04T05:43:05-04:00 configure: Fix #21712 again This is a bit of a shot in the dark to fix #24033, which appears to be another instance of #21712. For some reason the ld-override logic *still* appears to be active on Darwin targets (or at least one). Consequently, on misconfigured systems we may choose a non-`ld64` linker. It's a bit unclear exactly what happened in #24033 but ultimately the check added for #21712 was not quite right, checking for the `ghc_host_os` (the value of which depends upon the bootstrap compiler) instead of the target platform. Fix this. Fixes #24033. - - - - - 2f0a101d by Krzysztof Gogolewski at 2023-10-04T05:43:42-04:00 Add a regression test for #24029 - - - - - 8cee3fd7 by sheaf at 2023-10-04T05:44:22-04:00 Fix non-symbolic children lookup of fixity decl The fix for #23664 did not correctly account for non-symbolic names when looking up children of a given parent. This one-line fix changes that. Fixes #24037 - - - - - a4785b33 by Cheng Shao at 2023-10-04T05:44:59-04:00 rts: fix incorrect ticket reference - - - - - e037f459 by Ben Gamari at 2023-10-04T05:45:35-04:00 users-guide: Fix discussion of -Wpartial-fields * fix a few typos * add a new example showing when the warning fires * clarify the existing example * point out -Wincomplete-record-selects Fixes #24049. - - - - - 8ff3134e by Matthew Pickering at 2023-10-05T05:34:58-04:00 Revert "Pass preprocessor options to C compiler when building foreign C files (#16737)" This reverts commit 1c18d3b41f897f34a93669edaebe6069f319f9e2. `-optP` should pass options to the preprocessor, that might be a very different program to the C compiler, so passing the options to the C compiler is likely to result in `-optP` being useless. Fixes #17185 and #21291 - - - - - 8f6010b9 by Ben Gamari at 2023-10-05T05:35:36-04:00 rts/nonmoving: Fix on LLP64 platforms Previously `NONMOVING_SEGMENT_MASK` and friends were defined with the `UL` size suffix. However, this is wrong on LLP64 platforms like Windows, where `long` is 32-bits. Fixes #23003. Fixes #24042. - - - - - f20d02f8 by Andreas Klebinger at 2023-10-05T05:36:14-04:00 Fix isAArch64Bitmask for 32bit immediates. Fixes #23802 - - - - - 63afb701 by Bryan Richter at 2023-10-05T05:36:49-04:00 Work around perf note fetch failure Addresses #24055. - - - - - 242102f4 by Krzysztof Gogolewski at 2023-10-05T05:37:26-04:00 Add a test for #21348 - - - - - 7d390bce by Rewbert at 2023-10-05T05:38:08-04:00 Fixes #24046 - - - - - 69abb171 by Finley McIlwaine at 2023-10-06T14:06:28-07:00 Ensure unconstrained instance dictionaries get IPE info In the `StgRhsCon` case of `GHC.Stg.Debug.collectStgRhs`, we were not coming up with an initial source span based on the span of the binder, which was causing instance dictionaries without dynamic superclass constraints to not have source locations in their IPE info. Now they do. Resolves #24005 - - - - - 390443b7 by Andreas Klebinger at 2023-10-07T10:00:20-04:00 rts: Split up rts/include/stg/MachRegs.h by arch - - - - - 3685942f by Bryan Richter at 2023-10-07T10:00:56-04:00 Actually set hackage index state Or at least, use a version of the cabal command that *claims* to set the index state. Time will tell. - - - - - 46a0e5be by Bryan Richter at 2023-10-07T10:00:56-04:00 Update hackage index state - - - - - d4b037de by Bryan Richter at 2023-10-07T10:00:56-04:00 Ensure hadrian uses CI's hackage index state - - - - - e206be64 by Andrew Lelechenko at 2023-10-08T15:06:14-04:00 Do not use O_NONBLOCK on regular files or block devices CLC proposal https://github.com/haskell/core-libraries-committee/issues/166 - - - - - a06197c4 by David Binder at 2023-10-08T15:06:55-04:00 Update hpc-bin submodule to 0.69 - - - - - ed6785b6 by David Binder at 2023-10-08T15:06:55-04:00 Update Hadrian with correct path to happy file for hpc-bin - - - - - 94066d58 by Alan Zimmerman at 2023-10-09T21:35:53-04:00 EPA: Introduce HasAnnotation class The class is defined as class HasAnnotation e where noAnnSrcSpan :: SrcSpan -> e This generalises noAnnSrcSpan, and allows noLocA :: (HasAnnotation e) => a -> GenLocated e a noLocA = L (noAnnSrcSpan noSrcSpan) - - - - - 8792a1bc by Ben Gamari at 2023-10-09T21:36:29-04:00 Bump unix submodule to v2.8.3.0 - - - - - e96c51cb by Andreas Klebinger at 2023-10-10T16:44:27+01:00 Add a flag -fkeep-auto-rules to optionally keep auto-generated rules around. The motivation for the flag is given in #21917. - - - - - 3ed58cef by Matthew Pickering at 2023-10-10T19:01:22-04:00 hadrian: Add ghcToolchain to tool args list This allows you to load ghc-toolchain and ghc-toolchain-bin into HLS. - - - - - 476c02d4 by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Normalise triple via config.sub We were not normalising the target triple anymore like we did with the old make build system. Fixes #23856 - - - - - 303dd237 by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Add missing vendor normalisation This is copied from m4/ghc_convert_vendor.m4 Towards #23868 - - - - - 838026c9 by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Add loongarch64 to parseArch Towards #23868 - - - - - 1a5bc0b5 by Matthew Pickering at 2023-10-10T19:01:22-04:00 Add same LD hack to ghc-toolchain In the ./configure script, if you pass the `LD` variable then this has the effect of stopping use searching for a linker and hence passing `-fuse-ld=...`. We want to emulate this logic in ghc-toolchain, if a use explicilty specifies `LD` variable then don't add `-fuse-ld=..` with the goal of making ./configure and ghc-toolchain agree on which flags to use when using the C compiler as a linker. This is quite unsavoury as we don't bake the choice of LD into the configuration anywhere but what's important for now is making ghc-toolchain and ./configure agree as much as possible. See #23857 for more discussion - - - - - 42d50b5a by Ben Gamari at 2023-10-10T19:01:22-04:00 ghc-toolchain: Check for C99 support with -std=c99 Previously we failed to try enabling C99 support with `-std=c99`, as `autoconf` attempts. This broke on older compilers (e.g. CentOS 7) which don't enable C99 by default. Fixes #23879. - - - - - da2961af by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Add endianess check using __BYTE_ORDER__ macro In very old toolchains the BYTE_ORDER macro is not set but thankfully the __BYTE_ORDER__ macro can be used instead. - - - - - d8da73cd by Matthew Pickering at 2023-10-10T19:01:22-04:00 configure: AC_PATH_TARGET_TOOL for LD We want to make sure that LD is set to an absolute path in order to be consistent with the `LD=$(command -v ld)` call. The AC_PATH_TARGET_TOOL macro uses the absolute path rather than AC_CHECK_TARGET_TOOL which might use a relative path. - - - - - 171f93cc by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Check whether we need -std=gnu99 for CPP as well In ./configure the C99 flag is passed to the C compiler when used as a C preprocessor. So we also check the same thing in ghc-toolchain. - - - - - 89a0918d by Matthew Pickering at 2023-10-10T19:01:22-04:00 Check for --target linker flag separately to C compiler There are situations where the C compiler doesn't accept `--target` but when used as a linker it does (but doesn't do anything most likely) In particular with old gcc toolchains, the C compiler doesn't support --target but when used as a linker it does. - - - - - 37218329 by Matthew Pickering at 2023-10-10T19:01:22-04:00 Use Cc to compile test file in nopie check We were attempting to use the C compiler, as a linker, to compile a file in the nopie check, but that won't work in general as the flags we pass to the linker might not be compatible with the ones we pass when using the C compiler. - - - - - 9b2dfd21 by Matthew Pickering at 2023-10-10T19:01:22-04:00 configure: Error when ghc-toolchain fails to compile This is a small QOL change as if you are working on ghc-toolchain and it fails to compile then configure will continue and can give you outdated results. - - - - - 1f0de49a by Matthew Pickering at 2023-10-10T19:01:22-04:00 configure: Check whether -no-pie works when the C compiler is used as a linker `-no-pie` is a flag we pass when using the C compiler as a linker (see pieCCLDOpts in GHC.Driver.Session) so we should test whether the C compiler used as a linker supports the flag, rather than just the C compiler. - - - - - 62cd2579 by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Remove javascript special case for --target detection emcc when used as a linker seems to ignore the --target flag, and for consistency with configure which now tests for --target, we remove this special case. - - - - - 0720fde7 by Ben Gamari at 2023-10-10T19:01:22-04:00 toolchain: Don't pass --target to emscripten toolchain As noted in `Note [Don't pass --target to emscripten toolchain]`, emscripten's `emcc` is rather inconsistent with respect to its treatment of the `--target` flag. Avoid this by special-casing this toolchain in the `configure` script and `ghc-toolchain`. Fixes on aspect of #23744. - - - - - 6354e1da by Matthew Pickering at 2023-10-10T19:01:22-04:00 hadrian: Don't pass `--gcc-options` as a --configure-arg to cabal configure Stop passing -gcc-options which mixed together linker flags and non-linker flags. There's no guarantee the C compiler will accept both of these in each mode. - - - - - c00a4bd6 by Ben Gamari at 2023-10-10T19:01:22-04:00 configure: Probe stage0 link flags For consistency with later stages and CC. - - - - - 1f11e7c4 by Sebastian Graf at 2023-10-10T19:01:58-04:00 Stricter Binary.get in GHC.Types.Unit (#23964) I noticed some thunking while looking at Core. This change has very modest, but throughout positive ghc/alloc effect: ``` hard_hole_fits(normal) ghc/alloc 283,057,664 281,620,872 -0.5% geo. mean -0.1% minimum -0.5% maximum +0.0% ``` Fixes #23964. - - - - - a4f1a181 by Bryan Richter at 2023-10-10T19:02:37-04:00 rel_eng/upload.sh cleanups - - - - - 80705335 by doyougnu at 2023-10-10T19:03:18-04:00 ci: add javascript label rule This adds a rule which triggers the javascript job when the "javascript" label is assigned to an MR. - - - - - a2c0fff6 by Matthew Craven at 2023-10-10T19:03:54-04:00 Make 'wWarningFlagsDeps' include every WarningFlag Fixes #24071. - - - - - d055f099 by Jan Hrček at 2023-10-10T19:04:33-04:00 Fix pretty printing of overlap pragmas in TH splices (fixes #24074) - - - - - 0746b868 by Andreas Klebinger at 2023-10-10T19:05:09-04:00 Aarch64 NCG: Use encoded immediates for literals. Try to generate instr x2, <imm> instead of mov x1, lit instr x2, x1 When possible. This get's rid if quite a few redundant mov instructions. I believe this causes a metric decrease for LargeRecords as we reduce register pressure. ------------------------- Metric Decrease: LargeRecord ------------------------- - - - - - 739f4e6f by Andreas Klebinger at 2023-10-10T19:05:09-04:00 AArch NCG: Refactor getRegister' Remove some special cases which can be handled just as well by the generic case. This increases code re-use while also fixing #23749. Since some of the special case wasn't upholding Note [Signed arithmetic on AArch64]. - - - - - 1b213d33 by Andreas Klebinger at 2023-10-10T19:05:09-04:00 Aarch ncg: Optimize immediate use for address calculations When the offset doesn't fit into the immediate we now just reuse the general getRegister' code path which is well optimized to compute the offset into a register instead of a special case for CmmRegOff. This means we generate a lot less code under certain conditions which is why performance metrics for these improve. ------------------------- Metric Decrease: T4801 T5321FD T5321Fun ------------------------- - - - - - b7df0732 by John Ericson at 2023-10-11T16:02:11-04:00 RTS configure: Move over mem management checks These are for heap allocation, a strictly RTS concern. All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. The RTS configure one has a new ``` AC_CHECK_SIZEOF([void *]) ``` that the top-level configure version didn't have, so that `ac_cv_sizeof_void_p` is defined. Once more code is moved over in latter commits, that can go away. Progress towards #17191 - - - - - 41130a65 by John Ericson at 2023-10-11T16:02:11-04:00 RTS configure: Move over `__thread` check This used by (@bgamari thinks) the `GCThread` abstraction in the RTS. All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. Progress towards #17191 - - - - - cc5ec2bd by John Ericson at 2023-10-11T16:02:11-04:00 RTS configure: Move over misc function checks These are for general use in the RTS. All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. Progress towards #17191 - - - - - 809e7c2d by John Ericson at 2023-10-11T16:02:11-04:00 RTS configure: Move over `eventfd` check This check is for the RTS part of the event manager and has a corresponding part in `base`. All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. Progress towards #17191 - - - - - 58f3babf by John Ericson at 2023-10-11T16:02:48-04:00 Split `FP_CHECK_PTHREADS` and move part to RTS configure `NEED_PTHREAD_LIB` is unused since 3609340743c1b25fdfd0e18b1670dac54c8d8623 (part of the make build system), and so is no longer defined. Progress towards #17191 - - - - - e99cf237 by Moritz Angermann at 2023-10-11T16:03:24-04:00 nativeGen: section flags for .text$foo only Commit 3ece9856d157c85511d59f9f862ab351bbd9b38b, was supposed to fix #22834 in !9810. It does however add "xr" indiscriminatly to .text sections even if splitSections is disabled. This leads to the assembler saying: ghc_1.s:7849:0: error: Warning: Ignoring changed section attributes for .text | 7849 | .section .text,"xr" | ^ - - - - - f383a242 by Sylvain Henry at 2023-10-11T16:04:04-04:00 Modularity: pass TempDir instead of DynFlags (#17957) - - - - - 34fc28b0 by John Ericson at 2023-10-12T06:48:28-04:00 Test that functions from `mingwex` are available Ryan wrote these two minimizations, but they never got added to the test suite. See #23309, #23378 Co-Authored-By: Ben Gamari <bgamari.foss at gmail.com> Co-Authored-By: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - bdb54a0e by John Ericson at 2023-10-12T06:48:28-04:00 Do not check for the `mingwex` library in `/configure` See the recent discussion in !10360 --- Cabal will itself check for the library for the packages that need it, and while the autoconf check additionally does some other things like define a `HAS_LIBMINGWEX` C Preprocessor macro, those other things are also unused and unneeded. Progress towards #17191, which aims to get rid of `/configure` entirely. - - - - - 43e814e1 by Ben Gamari at 2023-10-12T06:49:40-04:00 base: Introduce move modules into src The only non-move changes here are whitespace changes to pass the `whitespace` test and a few testsuite adaptations. - - - - - df81536f by Moritz Angermann at 2023-10-12T06:50:16-04:00 [PEi386 linker] Bounds check and null-deref guard We should resonably be able to expect that we won't exceed the number of sections if we assume to be dealing with legal object files. We can however not guarantee that we get some negative values, and while we try to special case most, we should exclude negative indexing into the sections array. We also need to ensure that we do not try to derefences targetSection, if it is NULL, due to the switch statement. - - - - - c74c4f00 by John Ericson at 2023-10-12T10:31:13-04:00 Move apple compat check to RTS configure - - - - - c80778ea by John Ericson at 2023-10-12T10:31:13-04:00 Move clock/timer fun checks to RTS configure Actual library check (which will set the Cabal flag) is left in the top-level configure for now. Progress towards #17191 - - - - - 7f9f2686 by John Ericson at 2023-10-12T10:31:13-04:00 Move visibility and "musttail" annotation checks to the RTS configure All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. Progress towards #17191 - - - - - ffb3efe6 by John Ericson at 2023-10-12T10:31:13-04:00 Move leading underscore checks to RTS configure `CabalLeadingUnderscore` is done via Hadrian already, so we can stop `AC_SUBST`ing it completely. - - - - - 25fa4b02 by John Ericson at 2023-10-12T10:31:13-04:00 Move alloca, fork, const, and big endian checks to RTS configure All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. - - - - - 5170f42a by John Ericson at 2023-10-12T10:31:13-04:00 Move libdl check to RTS configure - - - - - ea7a1447 by John Ericson at 2023-10-12T10:31:13-04:00 Adjust `FP_FIND_LIBFFI` Just set vars, and `AC_SUBST` in top-level configure. Don't define `HAVE_SYSTEM_LIBFFI` because nothing is using it. It hasn't be in used since 3609340743c1b25fdfd0e18b1670dac54c8d8623 (part of the make build system). - - - - - f399812c by John Ericson at 2023-10-12T10:31:13-04:00 Split BFD support to RTS configure The flag is still in the top-level configure, but the other checks (which define various macros --- important) are in the RTS configure. - - - - - f64f44e9 by John Ericson at 2023-10-12T10:31:13-04:00 Split libm check between top level and RTS - - - - - dafc4709 by Moritz Angermann at 2023-10-12T10:31:49-04:00 CgUtils.fixStgRegStmt respect register width This change ensure that the reg + offset computation is always of the same size. Before this we could end up with a 64bit register, and then add a 32bit offset (on 32bit platforms). This not only would fail type sanity checking, but also incorrectly truncate 64bit values into 32bit values silently on 32bit architectures. - - - - - 9e6ef7ba by Matthew Pickering at 2023-10-12T20:35:00-04:00 hadrian: Decrease verbosity of cabal commands In Normal, most tools do not produce output to stdout unless there are error conditions. Reverts 7ed65f5a1bc8e040e318ccff395f53a9bbfd8217 - - - - - 08fc27af by John Ericson at 2023-10-12T20:35:36-04:00 Do not substitute `@...@` for stage-specific values in cabal files `rts` and `ghc-prim` now no longer have a `*.cabal.in` to set Cabal flag defaults; instead manual choices are passed to configure in the usual way. The old way was fundamentally broken, because it meant we were baking these Cabal files for a specific stage. Now we only do stage-agnostic @...@ substitution in cabal files (the GHC version), and so all stage-specific configuration is properly confined to `_build` and the right stage dir. Also `include-ghc-prim` is a flag that no longer exists for `ghc-prim` (it was removed in 835d8ddbbfb11796ea8a03d1806b7cee38ba17a6) so I got rid of it. Co-Authored-By: Matthew Pickering <matthewtpickering at gmail.com> - - - - - a0ac8785 by Sebastian Graf at 2023-10-14T19:17:12-04:00 Fix restarts in .ghcid Using the whole of `hadrian/` restarted in a loop for me. - - - - - fea9ecdb by Sebastian Graf at 2023-10-14T19:17:12-04:00 CorePrep: Refactor FloatingBind (#23442) A drastically improved architecture for local floating in CorePrep that decouples the decision of whether a float is going to be let- or case-bound from how far it can float (out of strict contexts, out of lazy contexts, to top-level). There are a couple of new Notes describing the effort: * `Note [Floating in CorePrep]` for the overview * `Note [BindInfo and FloatInfo]` for the new classification of floats * `Note [Floats and FloatDecision]` for how FloatInfo is used to inform floating decisions This is necessary ground work for proper treatment of Strict fields and unlifted values at top-level. Fixes #23442. NoFib results (omitted = 0.0%): ``` -------------------------------------------------------------------------------- Program Allocs Instrs -------------------------------------------------------------------------------- pretty 0.0% -1.6% scc 0.0% -1.7% -------------------------------------------------------------------------------- Min 0.0% -1.7% Max 0.0% -0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 32523713 by Matthew Pickering at 2023-10-14T19:17:49-04:00 hadrian: Move ghcBinDeps into ghcLibDeps This completes a5227080b57cb51ac34d4c9de1accdf6360b818b, the `ghc-usage.txt` and `ghci-usage.txt` file are also used by the `ghc` library so need to make sure they are present in the libdir even if we are not going to build `ghc-bin`. This also fixes things for cross compilers because the stage2 cross-compiler requires the ghc-usage.txt file, but we are using the stage2 lib folder but not building stage3:exe:ghc-bin so ghc-usage.txt was not being generated. - - - - - ec3c4488 by sheaf at 2023-10-14T19:18:29-04:00 Combine GREs when combining in mkImportOccEnv In `GHC.Rename.Names.mkImportOccEnv`, we sometimes discard one import item in favour of another, as explained in Note [Dealing with imports] in `GHC.Rename.Names`. However, this can cause us to lose track of important parent information. Consider for example #24084: module M1 where { class C a where { type T a } } module M2 ( module M1 ) where { import M1 } module M3 where { import M2 ( C, T ); instance C () where T () = () } When processing the import list of `M3`, we start off (for reasons that are not relevant right now) with two `Avail`s attached to `T`, namely `C(C, T)` and `T(T)`. We combine them in the `combine` function of `mkImportOccEnv`; as described in Note [Dealing with imports] we discard `C(C, T)` in favour of `T(T)`. However, in doing so, we **must not** discard the information want that `C` is the parent of `T`. Indeed, losing track of this information can cause errors when importing, as we could get an error of the form ‘T’ is not a (visible) associated type of class ‘C’ We fix this by combining the two GREs for `T` using `plusGRE`. Fixes #24084 - - - - - 257c2807 by Ilias Tsitsimpis at 2023-10-14T19:19:07-04:00 hadrian: Pass -DNOSMP to C compiler when needed Hadrian passes the -DNOSMP flag to GHC when the target doesn't support SMP, but doesn't pass it to CC as well, leading to the following compilation error on mips64el: | Run Cc (FindCDependencies CDep) Stage1: rts/sm/NonMovingScav.c => _build/stage1/rts/build/c/sm/NonMovingScav.o.d Command line: /usr/bin/mips64el-linux-gnuabi64-gcc -E -MM -MG -MF _build/stage1/rts/build/c/hooks/FlagDefaults.thr_debug_p_o.d -MT _build/stage1/rts/build/c/hooks/FlagDefaults.o -Irts/include -I_build/stage1/rts/build -I_build/stage1/rts/build/include -Irts/include -x c rts/hooks/FlagDefaults.c -Wall -Wextra -Wstrict-prototypes -Wmissing-prototypes -Wmissing-declarations -Winline -Wpointer-arith -Wmissing-noreturn -Wnested-externs -Wredundant-decls -Wundef -fno-strict-aliasing -DTHREADED_RTS -DDEBUG -fomit-frame-pointer -O2 -g -Irts -I_build/stage1/rts/build -DDEBUG -fno-omit-frame-pointer -g3 -O0 ===> Command failed with error code: 1 In file included from rts/include/Stg.h:348, from rts/include/Rts.h:38, from rts/hooks/FlagDefaults.c:8: rts/include/stg/SMP.h:416:2: error: #error memory barriers unimplemented on this architecture 416 | #error memory barriers unimplemented on this architecture | ^~~~~ rts/include/stg/SMP.h:440:2: error: #error memory barriers unimplemented on this architecture 440 | #error memory barriers unimplemented on this architecture | ^~~~~ rts/include/stg/SMP.h:464:2: error: #error memory barriers unimplemented on this architecture 464 | #error memory barriers unimplemented on this architecture | ^~~~~ The old make system correctly passed this flag to both GHC and CC [1]. Fix this error by passing -DNOSMP to CC as well. [1] https://gitlab.haskell.org/ghc/ghc/-/blob/00920f176b0235d5bb52a8e054d89a664f8938fe/rts/ghc.mk#L407 Closes #24082 - - - - - 13d3c613 by John Ericson at 2023-10-14T19:19:42-04:00 Users Guide: Drop dead code for Haddock refs to `parallel` I noticed while working on !11451 that `@LIBRARY_parallel_UNIT_ID@` was not substituted. It is dead code -- there is no `parallel-ref` usages and it doesn't look like there ever was (going back to 3e5d0f188d6c8633e55e9ba6c8941c07e459fa4b), so let's delete it. - - - - - fe067577 by Sylvain Henry at 2023-10-18T19:40:25-04:00 Avoid out-of-bound array access in bigNatIsPowerOf2 (fix #24066) bigNatIndex# in the `where` clause wasn't guarded by "bigNatIsZero a". - - - - - cc1625b1 by Sylvain Henry at 2023-10-18T19:40:25-04:00 Bignum: fix right shift of negative BigNat with native backend - - - - - cbe4400d by Sylvain Henry at 2023-10-18T19:40:25-04:00 Rts: expose rtsOutOfBoundsAccess symbol - - - - - 72c7380c by Sylvain Henry at 2023-10-18T19:40:25-04:00 Hadrian: enable `-fcheck-prim-bounds` in validate flavour This allows T24066 to fail when the bug is present. Otherwise the out-of-bound access isn't detected as it happens in ghc-bignum which wasn't compiled with the bounds check. - - - - - f9436990 by John Ericson at 2023-10-18T19:41:01-04:00 Make Hadrian solely responsible for substituting `docs/users_guide/ghc_config.py.in` Fixes #24091 Progress on #23966 Issue #24091 reports that `@ProjectVersion@` is no longer being substituted in the GHC user's guide. I assume this is a recent issue, but I am not sure how it's worked since c1a3ecde720b3bddc2c8616daaa06ee324e602ab; it looks like both Hadrian and configure are trying to substitute the same `.in` file! Now only Hadrian does. That is better anyways; already something that issue #23966 requested. It seems like we were missing some dependencies in Hadrian. (I really, really hate that this is possible!) Hopefully it is fixed now. - - - - - b12df0bb by John Ericson at 2023-10-18T19:41:37-04:00 `ghcversion.h`: No need to cope with undefined `ProjectPatchLevel*` Since 4e6c80197f1cc46dfdef0300de46847c7cfbdcb0, these are guaranteed to be defined. (Guaranteed including a test in the testsuite.) - - - - - 0295375a by John Ericson at 2023-10-18T19:41:37-04:00 Generate `ghcversion.h` from a `.in` file Now that there are no conditional sections (see the previous commit), we can just a do simple substitution rather than pasting it together line by line. Progress on #23966 - - - - - 740a1b85 by Krzysztof Gogolewski at 2023-10-19T11:37:20-04:00 Add a regression test for #24064 - - - - - 921fbf2f by Hécate Moonlight at 2023-10-19T11:37:59-04:00 CLC Proposal #182: Export List from Data.List Proposal link: https://github.com/haskell/core-libraries-committee/issues/182 - - - - - 4f02d3c1 by Sylvain Henry at 2023-10-20T04:01:32-04:00 rts: fix small argument passing on big-endian arch (fix #23387) - - - - - b86243b4 by Sylvain Henry at 2023-10-20T04:02:13-04:00 Interpreter: fix literal alignment on big-endian architectures (fix #19261) Literals weren't correctly aligned on big-endian, despite what the comment said. - - - - - a4b2ec47 by Sylvain Henry at 2023-10-20T04:02:54-04:00 Testsuite: recomp011 and recomp015 are fixed on powerpc These tests have been fixed but not tested and re-enabled on big-endian powerpc (see comments in #11260 and #11323) - - - - - fded7dd4 by Sebastian Graf at 2023-10-20T04:03:30-04:00 CorePrep: Allow floating dictionary applications in -O0 into a Rec (#24102) - - - - - 02efc181 by John Ericson at 2023-10-22T02:48:55-04:00 Move function checks to RTS configure Some of these functions are used in `base` too, but we can copy the checks over to its configure if that's an issue. - - - - - 5f4bccab by John Ericson at 2023-10-22T02:48:55-04:00 Move over a number of C-style checks to RTS configure - - - - - 5cf04f58 by John Ericson at 2023-10-22T02:48:55-04:00 Move/Copy more `AC_DEFINE` to RTS config Only exception is the LLVM version macros, which are used for GHC itself. - - - - - b8ce5dfe by John Ericson at 2023-10-22T02:48:55-04:00 Define `TABLES_NEXT_TO_CODE` in the RTS configure We create a new cabal flag to facilitate this. - - - - - 4a40271e by John Ericson at 2023-10-22T02:48:55-04:00 Configure scripts: `checkOS`: Make a bit more robust `mingw64` and `mingw32` are now both accepted for `OSMinGW32`. This allows us to cope with configs/triples that we haven't normalized extra being what GNU `config.sub` does. - - - - - 16bec0a0 by John Ericson at 2023-10-22T02:48:55-04:00 Generate `ghcplatform.h` from RTS configure We create a new cabal flag to facilitate this. - - - - - 7dfcab2f by John Ericson at 2023-10-22T02:48:55-04:00 Get rid of all mention of `mk/config.h` The RTS configure script is now solely responsible for managing its headers; the top level configure script does not help. - - - - - c1e3719c by Cheng Shao at 2023-10-22T02:49:33-04:00 rts: drop stale mentions of MIN_UPD_SIZE We used to have MIN_UPD_SIZE macro that describes the minimum reserved size for thunks, so that the thunk can be overwritten in place as indirections or blackholes. However, this macro has not been actually defined or used anywhere since a long time ago; StgThunkHeader already reserves a padding word for this purpose. Hence this patch which drops stale mentions of MIN_UPD_SIZE. - - - - - d24b0d85 by Andrew Lelechenko at 2023-10-22T02:50:11-04:00 base changelog: move non-backported entries from 4.19 section to 4.20 Neither !10933 (check https://hackage.haskell.org/package/base-4.19.0.0/docs/src/Text.Read.Lex.html#numberToRangedRational) nor !10189 (check https://hackage.haskell.org/package/base-4.19.0.0/docs/src/Data.List.NonEmpty.html#unzip) were backported to `base-4.19.0.0`. Moving them to `base-4.20.0.0` section. Also minor stylistic changes to other entries, bringing them to a uniform form. - - - - - de78b32a by Alan Zimmerman at 2023-10-23T09:09:41-04:00 EPA Some tweaks to annotations - Fix span for GRHS - Move TrailingAnns from last match to FunBind - Fix GADT 'where' clause span - Capture full range for a CaseAlt Match - - - - - d5a8780d by Simon Hengel at 2023-10-23T09:10:23-04:00 Update primitives.rst - - - - - 4d075924 by Josh Meredith at 2023-10-24T23:04:12+11:00 JS/userguide: add explanation of writing jsbits - - - - - 07ab5cc1 by Cheng Shao at 2023-10-24T15:40:32-04:00 testsuite: increase timeout of ghc-api tests for wasm32 ghc-api tests for wasm32 are more likely to timeout due to the large wasm module sizes, especially when testing with wasm native tail calls, given wasmtime's handling of tail call opcodes are suboptimal at the moment. It makes sense to increase timeout specifically for these tests on wasm32. This doesn't affect other targets, and for wasm32 we don't increase timeout for all tests, so not to risk letting major performance regressions slip through the testsuite. - - - - - 0d6acca5 by Greg Steuck at 2023-10-26T08:44:23-04:00 Explicitly require RLIMIT_AS before use in OSMem.c This is done elsewhere in the source tree. It also suddenly is required on OpenBSD. - - - - - 9408b086 by Sylvain Henry at 2023-10-26T08:45:03-04:00 Modularity: modularize external linker Decouple runLink from DynFlags to allow calling runLink more easily. This is preliminary work for calling Emscripten's linker (emcc) from our JavaScript linker. - - - - - e0f35030 by doyougnu at 2023-10-27T08:41:12-04:00 js: add JStg IR, remove unsaturated constructor - Major step towards #22736 and adding the optimizer in #22261 - - - - - 35587eba by Simon Peyton Jones at 2023-10-27T08:41:48-04:00 Fix a bug in tail calls with ticks See #24078 for the diagnosis. The change affects only the Tick case of occurrence analysis. It's a bit hard to test, so no regression test (yet anyway). - - - - - 9bc5cb92 by Matthew Craven at 2023-10-28T07:06:17-04:00 Teach tag-inference about SeqOp/seq# Fixes the STG/tag-inference analogue of #15226. Co-Authored-By: Simon Peyton Jones <simon.peytonjones at gmail.com> - - - - - 34f06334 by Moritz Angermann at 2023-10-28T07:06:53-04:00 [PEi386] Mask SYM_TYPE_DUP_DISCARD in makeSymbolExtra 48e391952c17ff7eab10b0b1456e3f2a2af28a9b introduced `SYM_TYPE_DUP_DISCARD` to the bitfield. The linker however, failed to mask the `SYM_TYPE_DUP_DISCARD` value. Thus `== SYM_TYPE_CODE` comparisons easily failed. This lead to us relocating DATA lookups (GOT) into E8 (call) and E9 (jump) instructions. - - - - - 5b51b2a2 by Mario Blažević at 2023-10-28T07:07:33-04:00 Fix and test for issue #24111, TH.Ppr output of pattern synonyms - - - - - 723bc352 by Alan Zimmerman at 2023-10-30T20:36:41-04:00 EPA: print doc comments as normal comments And ignore the ones allocated in haddock processing. It does not guarantee that every original haddock-like comment appears in the output, as it discards ones that have no legal attachment point. closes #23459 - - - - - 21b76843 by Simon Peyton Jones at 2023-10-30T20:37:17-04:00 Fix non-termination bug in equality solver constraint left-to-right then right to left, forever. Easily fixed. - - - - - 270867ac by Sebastian Graf at 2023-10-30T20:37:52-04:00 ghc-toolchain: build with `-package-env=-` (#24131) Otherwise globally installed libraries (via `cabal install --lib`) break the build. Fixes #24131. - - - - - 4d08364e by Alan Zimmerman at 2023-10-31T19:46:45+00:00 EPA: match changes in GHC - EPA: Comments in AnchorOperation - EPA: Remove EpaEofComment - - - - - 7a90020f by Krzysztof Gogolewski at 2023-10-31T20:03:37-04:00 docs: fix ScopedTypeVariables example (#24101) The previous example didn't compile. Furthermore, it wasn't demonstrating the point properly. I have changed it to an example which shows that 'a' in the signature must be the same 'a' as in the instance head. - - - - - 49f69f50 by Krzysztof Gogolewski at 2023-10-31T20:04:13-04:00 Fix pretty-printing of type family dependencies "where" should be after the injectivity annotation. - - - - - 73c191c0 by Ben Gamari at 2023-10-31T20:04:49-04:00 gitlab-ci: Bump LLVM bootstrap jobs to Debian 12 As the Debian 10 images have too old an LLVM. Addresses #24056. - - - - - 5b0392e0 by Matthew Pickering at 2023-10-31T20:04:49-04:00 ci: Run aarch64 llvm backend job with "LLVM backend" label This brings it into line with the x86 LLVM backend job. - - - - - 9f9c9227 by Ryan Scott at 2023-11-01T09:19:12-04:00 More robust checking for DataKinds As observed in #22141, GHC was not doing its due diligence in catching code that should require `DataKinds` in order to use. Most notably, it was allowing the use of arbitrary data types in kind contexts without `DataKinds`, e.g., ```hs data Vector :: Nat -> Type -> Type where ``` This patch revamps how GHC tracks `DataKinds`. The full specification is written out in the `DataKinds` section of the GHC User's Guide, and the implementation thereof is described in `Note [Checking for DataKinds]` in `GHC.Tc.Validity`. In brief: * We catch _type_-level `DataKinds` violations in the renamer. See `checkDataKinds` in `GHC.Rename.HsType` and `check_data_kinds` in `GHC.Rename.Pat`. * We catch _kind_-level `DataKinds` violations in the typechecker, as this allows us to catch things that appear beneath type synonyms. (We do *not* want to do this in type-level contexts, as it is perfectly fine for a type synonym to mention something that requires DataKinds while still using the type synonym in a module that doesn't enable DataKinds.) See `checkValidType` in `GHC.Tc.Validity`. * There is now a single `TcRnDataKindsError` that classifies all manner of `DataKinds` violations, both in the renamer and the typechecker. The `NoDataKindsDC` error has been removed, as it has been subsumed by `TcRnDataKindsError`. * I have added `CONSTRAINT` is `isKindTyCon`, which is what checks for illicit uses of data types at the kind level without `DataKinds`. Previously, `isKindTyCon` checked for `Constraint` but not `CONSTRAINT`. This is inconsistent, given that both `Type` and `TYPE` were checked by `isKindTyCon`. Moreover, it thwarted the implementation of the `DataKinds` check in `checkValidType`, since we would expand `Constraint` (which was OK without `DataKinds`) to `CONSTRAINT` (which was _not_ OK without `DataKinds`) and reject it. Now both are allowed. * I have added a flurry of additional test cases that test various corners of `DataKinds` checking. Fixes #22141. - - - - - 575d7690 by Sylvain Henry at 2023-11-01T09:19:53-04:00 JS: fix FFI "wrapper" and "dynamic" Fix codegen and helper functions for "wrapper" and "dynamic" foreign imports. Fix tests: - ffi006 - ffi011 - T2469 - T4038 Related to #22363 - - - - - 81fb8885 by Alan Zimmerman at 2023-11-01T22:23:56-04:00 EPA: Use full range for Anchor This change requires a series of related changes, which must all land at the same time, otherwise all the EPA tests break. * Use the current Anchor end as prior end Use the original anchor location end as the source of truth for calculating print deltas. This allows original spacing to apply in most cases, only changed AST items need initial delta positions. * Add DArrow to TrailingAnn * EPA Introduce HasTrailing in ExactPrint Use [TrailingAnn] in enterAnn and remove it from ExactPrint (LocatedN RdrName) * In HsDo, put TrailingAnns at top of LastStmt * EPA: do not convert comments to deltas when balancing. * EPA: deal with fallout from getMonoBind * EPA fix captureLineSpacing * EPA print any comments in the span before exiting it * EPA: Add comments to AnchorOperation * EPA: remove AnnEofComment, it is no longer used Updates Haddock submodule - - - - - 03e82511 by Rodrigo Mesquita at 2023-11-01T22:24:32-04:00 Fix in docs regarding SSymbol, SNat, SChar (#24119) - - - - - 362cc693 by Matthew Pickering at 2023-11-01T22:25:08-04:00 hadrian: Update bootstrap plans (9.4.6, 9.4.7, 9.6.2, 9.6.3, 9.8.1) Updating the bootstrap plans with more recent GHC versions. - - - - - 00b9b8d3 by Matthew Pickering at 2023-11-01T22:25:08-04:00 ci: Add 9.8.1 bootstrap testing job - - - - - ef3d20f8 by Matthew Pickering at 2023-11-01T22:25:08-04:00 Compatibility with 9.8.1 as boot compiler This fixes several compatability issues when using 9.8.1 as the boot compiler. * An incorrect version guard on the stack decoding logic in ghc-heap * Some ghc-prim bounds need relaxing * ghc is no longer wired in, so we have to remove the -this-unit-id ghc call. Fixes #24077 - - - - - 6755d833 by Jaro Reinders at 2023-11-03T10:54:42+01:00 Add NCG support for common 64bit operations to the x86 backend. These used to be implemented via C calls which was obviously quite bad for performance for operations like simple addition. Co-authored-by: Andreas Klebinger - - - - - 0dfb1fa7 by Vladislav Zavialov at 2023-11-03T14:08:41-04:00 T2T in Expressions (#23738) This patch implements the T2T (term-to-type) transformation in expressions. Given a function with a required type argument vfun :: forall a -> ... the user can now call it as vfun (Maybe Int) instead of vfun (type (Maybe Int)) The Maybe Int argument is parsed and renamed as a term (HsExpr), but then undergoes a conversion to a type (HsType). See the new function expr_to_type in compiler/GHC/Tc/Gen/App.hs and Note [RequiredTypeArguments and the T2T mapping] Left as future work: checking for puns. - - - - - cc1c7c54 by Duncan Coutts at 2023-11-05T00:23:44-04:00 Add a test for I/O managers It tries to cover the cases of multiple threads waiting on the same fd for reading and multiple threads waiting for writing, including wait cancellation by async exceptions. It should work for any I/O manager, in-RTS or in-Haskell. Unfortunately it will not currently work for Windows because it relies on anonymous unix sockets. It could in principle be ported to use Windows named pipes. - - - - - 2e448f98 by Cheng Shao at 2023-11-05T00:23:44-04:00 Skip the IOManager test on wasm32 arch. The test relies on the sockets API which are not (yet) available. - - - - - fe50eb35 by Cheng Shao at 2023-11-05T00:24:20-04:00 compiler: fix eager blackhole symbol in wasm32 NCG - - - - - af771148 by Cheng Shao at 2023-11-05T00:24:20-04:00 testsuite: fix optasm tests for wasm32 - - - - - 1b90735c by Matthew Pickering at 2023-11-05T00:24:20-04:00 testsuite: Add wasm32 to testsuite arches with NCG The compiler --info reports that wasm32 compilers have a NCG, so we should agree with that here. - - - - - db9a6496 by Alan Zimmerman at 2023-11-05T00:24:55-04:00 EPA: make locA a function, not a field name And use it to generalise reLoc The following for the windows pipeline one. 5.5% Metric Increase: T5205 - - - - - 833e250c by Simon Peyton Jones at 2023-11-05T00:25:31-04:00 Update the unification count in wrapUnifierX Omitting this caused type inference to fail in #24146. This was an accidental omision in my refactoring of the equality solver. - - - - - e451139f by Andreas Klebinger at 2023-11-05T00:26:07-04:00 Remove an accidental git conflict marker from a comment. - - - - - e7da0d25 by Alan Zimmerman at 2023-11-05T11:20:31+00:00 EPA: match changes in GHC, l2l cleanup - - - - - 30baac7a by Tobias Haslop at 2023-11-06T10:50:32+00:00 Add laws relating between Foldable/Traversable with their Bi- superclasses See https://github.com/haskell/core-libraries-committee/issues/205 for discussion. This commit also documents that the tuple instances only satisfy the laws up to lazyness, similar to the documentation added in !9512. - - - - - df626f00 by Tobias Haslop at 2023-11-07T02:20:37-05:00 Elaborate on the quantified superclass of Bifunctor This was requested in the comment https://github.com/haskell/core-libraries-committee/issues/93#issuecomment-1597271700 for when Traversable becomes a superclass of Bitraversable, but similarly applies to Functor/Bifunctor, which already are in a superclass relationship. - - - - - 8217acb8 by Alan Zimmerman at 2023-11-07T02:21:12-05:00 EPA: get rid of l2l and friends Replace them with l2l to convert the location la2la to convert a GenLocated thing Updates haddock submodule - - - - - dd88a260 by Luite Stegeman at 2023-11-07T02:21:53-05:00 JS: remove broken newIdents from JStg Monad GHC.JS.JStg.Monad.newIdents was broken, resulting in duplicate identifiers being generated in h$c1, h$c2, ... . This change removes the broken newIdents. - - - - - 455524a2 by Matthew Craven at 2023-11-09T08:41:59-05:00 Create specially-solved DataToTag class Closes #20532. This implements CLC proposal 104: https://github.com/haskell/core-libraries-committee/issues/104 The design is explained in Note [DataToTag overview] in GHC.Tc.Instance.Class. This replaces the existing `dataToTag#` primop. These metric changes are not "real"; they represent Unique-related flukes triggering on a different set of jobs than they did previously. See also #19414. Metric Decrease: T13386 T8095 Metric Increase: T13386 T8095 Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> - - - - - a05f4554 by Alan Zimmerman at 2023-11-09T08:42:35-05:00 EPA: get rid of glRR and friends in GHC/Parser.y With the HasLoc and HasAnnotation classes, we can replace a number of type-specific helper functions in the parser with polymorphic ones instead Metric Decrease: MultiLayerModulesTH_Make - - - - - 18498538 by Cheng Shao at 2023-11-09T16:58:12+00:00 ci: bump ci-images for wasi-sdk upgrade - - - - - 52c0fc69 by PHO at 2023-11-09T19:16:22-05:00 Don't assume the current locale is *.UTF-8, set the encoding explicitly primops.txt contains Unicode characters: > LC_ALL=C ./genprimopcode --data-decl < ./primops.txt > genprimopcode: <stdin>: hGetContents: invalid argument (cannot decode byte sequence starting from 226) Hadrian must also avoid using readFile' to read primops.txt because it tries to decode the file with a locale-specific encoding. - - - - - 7233b3b1 by PHO at 2023-11-09T19:17:01-05:00 Use '[' instead of '[[' because the latter is a Bash-ism It doesn't work on platforms where /bin/sh is something other than Bash. - - - - - 6dbab180 by Simon Peyton Jones at 2023-11-09T19:17:36-05:00 Add an extra check in kcCheckDeclHeader_sig Fix #24083 by checking for a implicitly-scoped type variable that is not actually bound. See Note [Disconnected type variables] in GHC.Tc.Gen.HsType For some reason, on aarch64-darwin we saw a 2.8% decrease in compiler allocations for MultiLayerModulesTH_Make; but 0.0% on other architectures. Metric Decrease: MultiLayerModulesTH_Make - - - - - 22551364 by Sven Tennie at 2023-11-11T06:35:22-05:00 AArch64: Delete unused LDATA pseudo-instruction Though there were consuming functions for LDATA, there were no producers. Thus, the removed code was "dead". - - - - - 2a0ec8eb by Alan Zimmerman at 2023-11-11T06:35:59-05:00 EPA: harmonise acsa and acsA in GHC/Parser.y With the HasLoc class, we can remove the acsa helper function, using acsA instead. - - - - - 4ceac14d by Alan Zimmerman at 2023-11-11T15:16:41+00:00 EPA: Replace Anchor with EpaLocation Match GHC - - - - - 7ae517a0 by Teo Camarasu at 2023-11-12T08:04:12-05:00 nofib: bump submodule This includes changes that: - fix building a benchmark with HEAD - remove a Makefile-ism that causes errors in bash scripts Resolves #24178 - - - - - 3f0036ec by Alan Zimmerman at 2023-11-12T08:04:47-05:00 EPA: Replace Anchor with EpaLocation An Anchor has a location and an operation, which is either that it is unchanged or that it has moved with a DeltaPos data Anchor = Anchor { anchor :: RealSrcSpan , anchor_op :: AnchorOperation } An EpaLocation also has either a location or a DeltaPos data EpaLocation = EpaSpan !RealSrcSpan !(Strict.Maybe BufSpan) | EpaDelta !DeltaPos ![LEpaComment] Now that we do not care about always having a location in the anchor, we remove Anchor and replace it with EpaLocation We do this with a type alias initially, to ease the transition. The alias will be removed in time. We also have helpers to reconstruct the AnchorOperation from an EpaLocation. This is also temporary. Updates Haddock submodule - - - - - a7492048 by Alan Zimmerman at 2023-11-12T13:43:07+00:00 EPA: get rid of AnchorOperation Now that the Anchor type is an alias for EpaLocation, remove AnchorOperation. Updates haddock submodule - - - - - 0745c34d by Andrew Lelechenko at 2023-11-13T16:25:07-05:00 Add since annotation for showHFloat - - - - - e98051a5 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 Suppress duplicate librares linker warning of new macOS linker Fixes #24167 XCode 15 introduced a new linker which warns on duplicate libraries being linked. To disable this warning, we pass -Wl,-no_warn_duplicate_libraries as suggested by Brad King in CMake issue #25297. This flag isn't necessarily available to other linkers on darwin, so we must only configure it into the CC linker arguments if valid. - - - - - c411c431 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 testsuite: Encoding test witnesses recent iconv bug is fragile A regression in the new iconv() distributed with XCode 15 and MacOS Sonoma causes the test 'encoding004' to fail in the CP936 roundrip. We mark this test as fragile until this is fixed upstream (rather than broken, since previous versions of iconv pass the test) See #24161 - - - - - ce7fe5a9 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 testsuite: Update to LC_ALL=C no longer being ignored in darwin MacOS seems to have fixed an issue where it used to ignore the variable `LC_ALL` in program invocations and default to using Unicode. Since the behaviour seems to be fixed to account for the locale variable, we mark tests that were previously broken in spite of it as fragile (since they now pass in recent macOS distributions) See #24161 - - - - - e6c803f7 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 darwin: Fix single_module is obsolete warning In XCode 15's linker, -single_module is the default and otherwise passing it as a flag results in a warning being raised: ld: warning: -single_module is obsolete This patch fixes this warning by, at configure time, determining whether the linker supports -single_module (which is likely false for all non-darwin linkers, and true for darwin linkers in previous versions of macOS), and using that information at runtime to decide to pass or not the flag in the invocation. Fixes #24168 - - - - - 929ba2f9 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 testsuite: Skip MultiLayerModulesTH_Make on darwin The recent toolchain upgrade on darwin machines resulted in the MultiLayerModulesTH_Make test metrics varying too much from the baseline, ultimately blocking the CI pipelines. This commit skips the test on darwin to temporarily avoid failures due to the environment change in the runners. However, the metrics divergence is being investigated still (tracked in #24177) - - - - - af261ccd by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 configure: check target (not build) understands -no_compact_unwind Previously, we were branching on whether the build system was darwin to shortcut this check, but we really want to branch on whether the target system (which is what we are configuring ld_prog for) is darwin. - - - - - 2125c176 by Luite Stegeman at 2023-11-15T13:19:38-05:00 JS: Fix missing variable declarations The JStg IR update was missing some local variable declarations that were present earlier, causing global variables to be used implicitly (or an error in JavaScript strict mode). This adds the local variable declarations again. - - - - - 99ced73b by Krzysztof Gogolewski at 2023-11-15T13:20:14-05:00 Remove loopy superclass solve mechanism Programs with a -Wloopy-superclass-solve warning will now fail with an error. Fixes #23017 - - - - - 2aff2361 by Zubin Duggal at 2023-11-15T13:20:50-05:00 users-guide: Fix links to libraries from the users-guide. The unit-ids generated in c1a3ecde720b3bddc2c8616daaa06ee324e602ab include the package name, so we don't need to explicitly add it to the links. Fixes #24151 - - - - - 27981fac by Alan Zimmerman at 2023-11-15T13:21:25-05:00 EPA: splitLHsForAllTyInvis does not return ann We did not use the annotations returned from splitLHsForAllTyInvis, so do not return them. - - - - - a6467834 by Krzysztof Gogolewski at 2023-11-15T22:22:59-05:00 Document defaulting of RuntimeReps Fixes #24099 - - - - - 2776920e by Simon Peyton Jones at 2023-11-15T22:23:35-05:00 Second fix to #24083 My earlier fix turns out to be too aggressive for data/type families See wrinkle (DTV1) in Note [Disconnected type variables] - - - - - cee81370 by Sylvain Henry at 2023-11-16T09:57:46-05:00 Fix unusable units and module reexport interaction (#21097) This commit fixes an issue with ModUnusable introduced in df0f148feae. In mkUnusableModuleNameProvidersMap we traverse the list of unusable units and generate ModUnusable origin for all the modules they contain: exposed modules, hidden modules, and also re-exported modules. To do this we have a two-level map: ModuleName -> Unit:ModuleName (aka Module) -> ModuleOrigin So for each module name "M" in broken unit "u" we have: "M" -> u:M -> ModUnusable reason However in the case of module reexports we were using the *target* module as a key. E.g. if "u:M" is a reexport for "X" from unit "o": "M" -> o:X -> ModUnusable reason Case 1: suppose a reexport without module renaming (u:M -> o:M) from unusable unit u: "M" -> o:M -> ModUnusable reason Here it's claiming that the import of M is unusable because a reexport from u is unusable. But if unit o isn't unusable we could also have in the map: "M" -> o:M -> ModOrigin ... Issue: the Semigroup instance of ModuleOrigin doesn't handle the case (ModUnusable <> ModOrigin) Case 2: similarly we could have 2 unusable units reexporting the same module without renaming, say (u:M -> o:M) and (v:M -> o:M) with u and v unusable. It gives: "M" -> o:M -> ModUnusable ... (for u) "M" -> o:M -> ModUnusable ... (for v) Issue: the Semigroup instance of ModuleOrigin doesn't handle the case (ModUnusable <> ModUnusable). This led to #21097, #16996, #11050. To fix this, in this commit we make ModUnusable track whether the module used as key is a reexport or not (for better error messages) and we use the re-export module as key. E.g. if "u:M" is a reexport for "o:X" and u is unusable, we now record: "M" -> u:M -> ModUnusable reason reexported=True So now, we have two cases for a reexport u:M -> o:X: - u unusable: "M" -> u:M -> ModUnusable ... reexported=True - u usable: "M" -> o:X -> ModOrigin ... reexportedFrom=u:M The second case is indexed with o:X because in this case the Semigroup instance of ModOrigin is used to combine valid expositions of a module (directly or via reexports). Note that module lookup functions select usable modules first (those who have a ModOrigin value), so it doesn't matter if we add new ModUnusable entries in the map like this: "M" -> { u:M -> ModUnusable ... reexported=True o:M -> ModOrigin ... } The ModOrigin one will be used. Only if there is no ModOrigin or ModHidden entry will the ModUnusable error be printed. See T21097 for an example printing several reasons why an import is unusable. - - - - - 3e606230 by Krzysztof Gogolewski at 2023-11-16T09:58:22-05:00 Fix IPE test A helper function was defined in a different module than used. To reproduce: ./hadrian/build test --test-root-dirs=testsuite/tests/rts/ipe - - - - - 49f5264b by Andreas Klebinger at 2023-11-16T20:52:11-05:00 Properly compute unpacked sizes for -funpack-small-strict-fields. Use rep size rather than rep count to compute the size. Fixes #22309 - - - - - b4f84e4b by James Henri Haydon at 2023-11-16T20:52:53-05:00 Explicit methods for Alternative Compose Explicitly define some and many in Alternative instance for Data.Functor.Compose Implementation of https://github.com/haskell/core-libraries-committee/issues/181 - - - - - 9bc0dd1f by Ignat Insarov at 2023-11-16T20:53:34-05:00 Add permutations for non-empty lists. Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/68#issuecomment-1221409837 - - - - - 5643ecf9 by Andrew Lelechenko at 2023-11-16T20:53:34-05:00 Update changelog and since annotations for Data.List.NonEmpty.permutations Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/68#issuecomment-1221409837 - - - - - 94ff2134 by Oleg Alexander at 2023-11-16T20:54:15-05:00 Update doc string for traceShow Updated doc string for traceShow. - - - - - faff671a by Luite Stegeman at 2023-11-17T14:12:51+01:00 JS: clean up some foreign imports - - - - - 856e0a4e by Sven Tennie at 2023-11-18T06:54:11-05:00 AArch64: Remove unused instructions As these aren't ever emitted, we don't even know if they work or will ever be used. If one of them is needed in future, we may easily re-add it. Deleted instructions are: - CMN - ANDS - BIC - BICS - EON - ORN - ROR - TST - STP - LDP - DMBSY - - - - - 615441ef by Alan Zimmerman at 2023-11-18T06:54:46-05:00 EPA: Replace Monoid with NoAnn Remove the final Monoid instances in the exact print infrastructure. For Windows CI Metric Decrease: T5205 - - - - - 5a6c49d4 by David Feuer at 2023-11-20T18:53:18-05:00 Speed up stimes in instance Semigroup Endo As discussed at https://github.com/haskell/core-libraries-committee/issues/4 - - - - - cf9da4b3 by Andrew Lelechenko at 2023-11-20T18:53:18-05:00 base: reflect latest changes in the changelog - - - - - 48bf364e by Alan Zimmerman at 2023-11-20T18:53:54-05:00 EPA: Use SrcSpan in EpaSpan This is more natural, since we already need to deal with invalid RealSrcSpans, and that is exactly what SrcSpan.UnhelpfulSpan is for. Updates haddock submodule. - - - - - 97ec37cc by Sebastian Graf at 2023-11-20T18:54:31-05:00 Add regression test for #6070 Fixes #6070. - - - - - e9d5ae41 by Owen Shepherd at 2023-11-21T18:32:23-05:00 chore: Correct typo in the gitlab MR template [skip ci] - - - - - f158a8d0 by Rodrigo Mesquita at 2023-11-21T18:32:59-05:00 Improve error message when reading invalid `.target` files A `.target` file generated by ghc-toolchain or by configure can become invalid if the target representation (`Toolchain.Target`) is changed while the files are not re-generated by calling `./configure` or `ghc-toolchain` again. There is also the issue of hadrian caching the dependencies on `.target` files, which makes parsing fail when reading reading the cached value if the representation has been updated. This patch provides a better error message in both situations, moving away from a terrible `Prelude.read: no parse` error that you would get otherwise. Fixes #24199 - - - - - 955520c6 by Ben Gamari at 2023-11-21T18:33:34-05:00 users guide: Note that QuantifiedConstraints implies ExplicitForAll Fixes #24025. - - - - - 17ec3e97 by Owen Shepherd at 2023-11-22T09:37:28+01:00 fix: Change type signatures in NonEmpty export comments to reflect reality This fixes several typos in the comments of Data.List.NonEmpty export list items. - - - - - 2fd78f9f by Samuel Thibault at 2023-11-22T11:49:13-05:00 Fix the platform string for GNU/Hurd As commited in Cargo https://github.com/haskell/cabal/pull/9434 there is confusion between "gnu" and "hurd". This got fixed in Cargo, we need the converse in Hadrian. Fixes #24180 - - - - - a79960fe by Alan Zimmerman at 2023-11-22T11:49:48-05:00 EPA: Tuple Present no longer has annotation The Present constructor for a Tuple argument will never have an exact print annotation. So make this impossible. - - - - - 121c9ab7 by David Binder at 2023-11-22T21:12:29-05:00 Unify the hpc testsuites The hpc testsuite was split between testsuite/tests/hpc and the submodule libraries/hpc/test. This commit unifies the two testsuites in the GHC repository in the directory testsuite/tests/hpc. - - - - - d2733a05 by Alan Zimmerman at 2023-11-22T21:13:05-05:00 EPA: empty tup_tail has noAnn In Parser.y, the tup_tail rule had the following option | {- empty -} %shift { return [Left noAnn] } Once this works through PostProcess.hs, it means we add an extra Missing constructor if the last item was a comma. Change the annotation type to a Bool to indicate this, and use the EpAnn Anchor for the print location for the others. - - - - - fa576eb8 by Andreas Klebinger at 2023-11-24T08:29:13-05:00 Fix FMA primops generating broken assembly on x86. `genFMA3Code` assumed that we had to take extra precations to avoid overwriting the result of `getNonClobberedReg`. One of these special cases caused a bug resulting in broken assembly. I believe we don't need to hadle these cases specially at all, which means this MR simply deletes the special cases to fix the bug. Fixes #24160 - - - - - 34d86315 by Alan Zimmerman at 2023-11-24T08:29:49-05:00 EPA: Remove parenthesizeHsType This is called from PostProcess.hs, and adds spurious parens. With the looser version of exact printing we had before we could tolerate this, as they would be swallowed by the original at the same place. But with the next change (remove EpAnnNotUsed) they result in duplicates in the output. For Darwin build: Metric Increase: MultiLayerModulesTH_OneShot - - - - - 3ede659d by Vladislav Zavialov at 2023-11-26T06:43:32-05:00 Add name for -Wdeprecated-type-abstractions (#24154) This warning had no name or flag and was triggered unconditionally. Now it is part of -Wcompat. - - - - - 7902ebf8 by Alan Zimmerman at 2023-11-26T06:44:08-05:00 EPA: Remove EpAnnNotUsed We no longer need the EpAnnNotUsed constructor for EpAnn, as we can represent an unused annotation with an anchor having a EpaDelta of zero, and empty comments and annotations. This simplifies code handling annotations considerably. Updates haddock submodule Metric Increase: parsing001 - - - - - 471b2672 by Mario Blažević at 2023-11-26T06:44:48-05:00 Bumped the upper bound of text to <2.2 - - - - - d1bf25c7 by Vladislav Zavialov at 2023-11-26T11:45:49-05:00 Term variable capture (#23740) This patch changes type variable lookup rules (lookupTypeOccRn) and implicit quantification rules (filterInScope) so that variables bound in the term namespace can be captured at the type level {-# LANGUAGE RequiredTypeArguments #-} f1 x = g1 @x -- `x` used in a type application f2 x = g2 (undefined :: x) -- `x` used in a type annotation f3 x = g3 (type x) -- `x` used in an embedded type f4 x = ... where g4 :: x -> x -- `x` used in a type signature g4 = ... This change alone does not allow us to accept examples shown above, but at least it gets them past the renamer. - - - - - da863d15 by Vladislav Zavialov at 2023-11-26T11:46:26-05:00 Update Note [hsScopedTvs and visible foralls] The Note was written before GHC gained support for visible forall in types of terms. Rewrite a few sentences and use a better example. - - - - - b5213542 by Matthew Pickering at 2023-11-27T12:53:59-05:00 testsuite: Add mechanism to collect generic metrics * Generalise the metric logic by adding an additional field which allows you to specify how to query for the actual value. Previously the method of querying the baseline value was abstracted (but always set to the same thing). * This requires rejigging how the stat collection works slightly but now it's more uniform and hopefully simpler. * Introduce some new "generic" helper functions for writing generic stats tests. - collect_size ( deviation, path ) Record the size of the file as a metric - stat_from_file ( metric, deviation, path ) Read a value from the given path, and store that as a metric - collect_generic_stat ( metric, deviation, get_stat) Provide your own `get_stat` function, `lambda way: <Int>`, which can be used to establish the current value of the metric. - collect_generic_stats ( metric_info ): Like collect_generic_stat but provide the whole dictionary of metric definitions. { metric: { deviation: <Int> current: lambda way: <Int> } } * Introduce two new "size" metrics for keeping track of build products. - `size_hello_obj` - The size of `hello.o` from compiling hello.hs - `libdir` - The total size of the `libdir` folder. * Track the number of modules in the AST tests - CountDepsAst - CountDepsParser This lays the infrastructure for #24191 #22256 #17129 - - - - - 7d9a2e44 by ARATA Mizuki at 2023-11-27T12:54:39-05:00 x86: Don't require -mavx2 when using 256-bit floating-point SIMD primitives Fixes #24222 - - - - - 4e5ff6a4 by Alan Zimmerman at 2023-11-27T12:55:15-05:00 EPA: Remove SrcSpanAnn Now that we only have a single constructor for EpAnn, And it uses a SrcSpan for its location, we can do away with SrcSpanAnn completely. It only existed to wrap the original SrcSpan in a location, and provide a place for the exact print annotation. For darwin only: Metric Increase: MultiLayerModulesTH_OneShot Updates haddock submodule - - - - - e05bca39 by Krzysztof Gogolewski at 2023-11-28T08:00:55-05:00 testsuite: don't initialize testdir to '.' The test directory is removed during cleanup, if there's an interrupt that could remove the entire repository. Fixes #24219 - - - - - af881674 by Alan Zimmerman at 2023-11-28T08:01:30-05:00 EPA: Clean up mkScope in Ast.hs Now that we have HasLoc we can get rid of all the custom variants of mkScope For deb10-numa Metric Increase: libdir - - - - - 292983c8 by Ben Gamari at 2023-11-28T22:44:28-05:00 distrib: Rediscover otool and install_name_tool on Darwin In the bindist configure script we must rediscover the `otool` and `install_name_tool`s since they may be different from the build environment. Fixes #24211. - - - - - dfe1c354 by Stefan Schulze Frielinghaus at 2023-11-28T22:45:04-05:00 llvmGen: Align objects in the data section Objects in the data section may be referenced via tagged pointers. Thus, align those objects to a 4- or 8-byte boundary for 32- or 64-bit platforms, respectively. Note, this may need to be reconsidered if objects with a greater natural alignment requirement are emitted as e.g. 128-bit atomics. Fixes #24163. - - - - - f6c486c3 by Matthew Pickering at 2023-11-29T11:08:13-05:00 metrics: Widen libdir and size_hello_obj acceptance window af8816740d9b8759be1a22af8adcb5f13edeb61d shows that the libdir size can fluctuate quite significantly even when the change is quite small. Therefore we widen the acceptance window to 10%. - - - - - 99a6a49c by Alan Zimmerman at 2023-11-29T11:08:49-05:00 EPA: Clean up TC Monad Utils We no longer need the alternative variant of addLocM (addLocMA) nor wrapLocAM, wrapLocSndMA. aarch64-darwin Metric Increase: MultiLayerModulesTH_OneShot deb10-numa-slow Metric Decrease: libdir - - - - - 94fb8d47 by Alan Zimmerman at 2023-11-29T18:10:26+00:00 Match GHC, No comments in EpaDelta for comments - - - - - cbc03fa0 by Sebastian Graf at 2023-11-30T12:37:21-05:00 perf tests: Move comments into new `Note [Sensitivity to unique increment]` (#19414) And additionally to T12545, link from T8095, T13386 to this new Note. - - - - - c7623b22 by Alan Zimmerman at 2023-11-30T12:37:56-05:00 EPA: EpaDelta for comment has no comments EpaLocation is used to position things. It has two constructors, EpaSpan holding a SrcSpan, and EpaDelta with a delta position and a possible list of comments. The comment list is needed because the location in EpaDelta has no absolute information to decide which comments should be emitted before them when printing. But it is also used for specifying the position of a comment. To prevent the absurdity of a comment position having a list of comments in it, we make EpaLocation parameterisable, using comments for the normal case and a constant for within comments. Updates haddock submodule. aarch64-darwin Metric Decrease: MultiLayerModulesTH_OneShot - - - - - bd8acc0c by Krzysztof Gogolewski at 2023-11-30T12:38:32-05:00 Kind-check body of a required forall We now require that in 'forall a -> ty', ty has kind TYPE r for some r. Fixes #24176 - - - - - 010fb784 by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Remove incorrect haddock link quotes in code block - - - - - cda9c12d by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Remove cycle from group haddock example - - - - - 495265b9 by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Use repl haddock syntax in group docs - - - - - d134d1de by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Use list [] notation in group haddock - - - - - dfcf629c by Owen Shepherd at 2023-12-03T00:10:10-05:00 docs(NonEmpty/group): Specify final property of group function in haddock - - - - - cad3b734 by Owen Shepherd at 2023-12-03T00:10:10-05:00 fix: Add missing property of List.group - - - - - bad37656 by Matthew Pickering at 2023-12-03T00:10:46-05:00 testsuite: Fix T21097b test with make 4.1 (deb9) cee81370cd6ef256f66035e3116878d4cb82e28b recently added a test which failed on deb9 because the version of make was emitting the recipe failure to stdout rather than stderr. One way to fix this is to be more precise in the test about which part of the output we care about inspecting. - - - - - 5efdf421 by Matthew Pickering at 2023-12-03T00:11:21-05:00 testsuite: Track size of libdir in bytes For consistency it's better if we track all size metrics in bytes. Metric Increase: libdir - - - - - f5eb0f29 by Matthew Pickering at 2023-12-03T00:11:22-05:00 testsuite: Remove rogue trace in testsuite I accidentally left a trace in the generics metric patch. - - - - - d5610737 by Claudio Bley at 2023-12-06T16:13:33-05:00 Only exit ghci in -e mode when :add command fails Previously, when running `ghci -e ':add Sample.hs'` the process would exit with exit code 1 if the file exists and could be loaded. Fixes #24115 - - - - - 0f0c53a5 by Vladislav Zavialov at 2023-12-06T16:14:09-05:00 T2T in Patterns (#23739) This patch implements the T2T (term-to-type) transformation in patterns. Patterns that are checked against a visible forall can now be written without the `type` keyword: \(type t) (x :: t) -> ... -- old \t (x :: t) -> ... -- new The `t` binder is parsed and renamed as a term pattern (Pat), but then undergoes a conversion to a type pattern (HsTyPat). See the new function pat_to_type_pat in compiler/GHC/Tc/Gen/Pat.hs - - - - - 10a1a6c6 by Sebastian Graf at 2023-12-06T16:14:45-05:00 Pmc: Fix SrcLoc and warning for incomplete irrefutable pats (#24234) Before, the source location would point at the surrounding function definition, causing the confusion in #24234. I also took the opportunity to introduce a new `LazyPatCtx :: HsMatchContext _` to make the warning message say "irrefutable pattern" instead of "pattern binding". - - - - - 36b9a38c by Matthew Pickering at 2023-12-06T16:15:21-05:00 libraries: Bump filepath to 1.4.200.1 and unix to 2.8.4.0 Updates filepath submodule Updates unix submodule Fixes #24240 - - - - - 91ff0971 by Matthew Pickering at 2023-12-06T16:15:21-05:00 Submodule linter: Allow references to tags We modify the submodule linter so that if the bumped commit is a specific tag then the commit is accepted. Fixes #24241 - - - - - 86f652dc by Zubin Duggal at 2023-12-06T16:15:21-05:00 hadrian: set -Wno-deprecations for directory and Win32 The filepath bump to 1.4.200.1 introduces a deprecation warning. See https://gitlab.haskell.org/ghc/ghc/-/issues/24240 https://github.com/haskell/filepath/pull/206 - - - - - 7ac6006e by Sylvain Henry at 2023-12-06T16:16:02-05:00 Zap OccInfo on case binders during StgCse #14895 #24233 StgCse can revive dead binders: case foo of dead { Foo x y -> Foo x y; ... } ===> case foo of dead { Foo x y -> dead; ... } -- dead is no longer dead So we must zap occurrence information on case binders. Fix #14895 and #24233 - - - - - 57c391c4 by Sebastian Graf at 2023-12-06T16:16:37-05:00 Cpr: Turn an assertion into a check to deal with some dead code (#23862) See the new `Note [Dead code may contain type confusions]`. Fixes #23862. - - - - - c1c8abf8 by Zubin Duggal at 2023-12-08T02:25:07-05:00 testsuite: add test for #23944 - - - - - 6329d308 by Zubin Duggal at 2023-12-08T02:25:07-05:00 driver: Only run a dynamic-too pipeline if object files are going to be generated Otherwise we run into a panic in hscMaybeWriteIface: "Unexpected DT_Dyn state when writing simple interface" when dynamic-too is enabled We could remove the panic and just write the interface even if the state is `DT_Dyn`, but it seems pointless to run the pipeline twice when `hscMaybeWriteIface` is already designed to write both `hi` and `dyn_hi` files if dynamic-too is enabled. Fixes #23944. - - - - - 28811f88 by Simon Peyton Jones at 2023-12-08T05:47:18-05:00 Improve duplicate elimination in SpecConstr This partially fixes #24229. See the new Note [Pattern duplicate elimination] in SpecConstr - - - - - fec7894f by Simon Peyton Jones at 2023-12-08T05:47:18-05:00 Make SpecConstr deal with casts better This patch does two things, to fix #23209: * It improves SpecConstr so that it no longer quantifies over coercion variables. See Note [SpecConstr and casts] * It improves the rule matcher to deal nicely with the case where the rule does not quantify over coercion variables, but the the template has a cast in it. See Note [Casts in the template] - - - - - 8db8d2fd by Zubin Duggal at 2023-12-08T05:47:54-05:00 driver: Don't lose track of nodes when we fail to resolve cycles The nodes that take part in a cycle should include both hs-boot and hs files, but when we fail to resolve a cycle, we were only counting the nodes from the graph without boot files. Fixes #24196 - - - - - c5b4efd3 by Zubin Duggal at 2023-12-08T05:48:30-05:00 testsuite: Skip MultiLayerModulesTH_OneShot on darwin See #24177 - - - - - fae472a9 by Wendao Lee at 2023-12-08T05:49:12-05:00 docs(Data.Char):Add more detailed descriptions for some functions Related changed function's docs: -GHC.Unicode.isAlpha -GHC.Unicode.isPrint -GHC.Unicode.isAlphaNum Add more details for what the function will return. Co-authored-by: Bodigrim <andrew.lelechenko at gmail.com> - - - - - ca7510e4 by Malik Ammar Faisal at 2023-12-08T05:49:55-05:00 Fix float parsing in GHC Cmm Lexer Add test case for bug #24224 - - - - - d8baa1bd by Simon Peyton Jones at 2023-12-08T15:40:37+00:00 Take care when simplifying unfoldings This MR fixes a very subtle bug exposed by #24242. See Note [Environment for simplLetUnfolding]. I also updated a bunch of Notes on shadowing - - - - - 03ca551d by Simon Peyton Jones at 2023-12-08T15:54:50-05:00 Comments only in FloatIn Relevant to #3458 - - - - - 50c78779 by Simon Peyton Jones at 2023-12-08T15:54:50-05:00 Comments only in SpecConstr - - - - - 9431e195 by Simon Peyton Jones at 2023-12-08T15:54:50-05:00 Add test for #22238 - - - - - d9e4c597 by Vladislav Zavialov at 2023-12-11T04:19:34-05:00 Make forall a keyword (#23719) Before this change, GHC used to accept `forall` as a term-level identifier: -- from constraints-0.13 forall :: forall p. (forall a. Dict (p a)) -> Dict (Forall p) forall d = ... Now it is a parse error. The -Wforall-identifier warning has served its purpose and is now a deprecated no-op. - - - - - 58d56644 by Zubin Duggal at 2023-12-11T04:20:10-05:00 driver: Ensure we actually clear the interactive context before reloading Previously we called discardIC, but immediately after set the session back to an old HscEnv that still contained the IC Partially addresses #24107 Fixes #23405 - - - - - 8e5745a0 by Zubin Duggal at 2023-12-11T04:20:10-05:00 driver: Ensure we force the lookup of old build artifacts before returning the build plan This prevents us from retaining all previous build artifacts in memory until a recompile finishes, instead only retaining the exact artifacts we need. Fixes #24118 - - - - - 105c370c by Zubin Duggal at 2023-12-11T04:20:10-05:00 testsuite: add test for #24118 and #24107 MultiLayerModulesDefsGhci was not able to catch the leak because it uses :l which discards the previous environment. Using :r catches both of these leaks - - - - - e822ff88 by Zubin Duggal at 2023-12-11T04:20:10-05:00 compiler: Add some strictness annotations to ImportSpec and related constructors This prevents us from retaining entire HscEnvs. Force these ImportSpecs when forcing the GlobalRdrEltX Adds an NFData instance for Bag Fixes #24107 - - - - - 522c12a4 by Zubin Duggal at 2023-12-11T04:20:10-05:00 compiler: Force IfGlobalRdrEnv in NFData instance. - - - - - 188b280d by Arnaud Spiwack at 2023-12-11T15:33:31+01:00 LinearTypes => MonoLocalBinds - - - - - 8e0446df by Arnaud Spiwack at 2023-12-11T15:44:28+01:00 Linear let and where bindings For expediency, the initial implementation of linear types in GHC made it so that let and where binders would always be considered unrestricted. This was rather unpleasant, and probably a big obstacle to adoption. At any rate, this was not how the proposal was designed. This patch fixes this infelicity. It was surprisingly difficult to build, which explains, in part, why it took so long to materialise. As of this patch, let or where bindings marked with %1 will be linear (respectively %p for an arbitrary multiplicity p). Unmarked let will infer their multiplicity. Here is a prototypical example of program that used to be rejected and is accepted with this patch: ```haskell f :: A %1 -> B g :: B %1 -> C h :: A %1 -> C h x = g y where y = f x ``` Exceptions: - Recursive let are unrestricted, as there isn't a clear semantics of what a linear recursive binding would be. - Destructive lets with lazy bindings are unrestricted, as their desugaring isn't linear (see also #23461). - (Strict) destructive lets with inferred polymorphic type are unrestricted. Because the desugaring isn't linear (See #18461 down-thread). Closes #18461 and #18739 Co-authored-by: @jackohughes - - - - - effa7e2d by Matthew Craven at 2023-12-12T04:37:20-05:00 Introduce `dataToTagSmall#` primop (closes #21710) ...and use it to generate slightly better code when dataToTag# is used at a "small data type" where there is no need to mess with "is_too_big_tag" or potentially look at an info table. Metric Decrease: T18304 - - - - - 35c7aef6 by Matthew Craven at 2023-12-12T04:37:20-05:00 Fix formatting of Note [alg-alt heap check] - - - - - 7397c784 by Oleg Grenrus at 2023-12-12T04:37:56-05:00 Allow untyped brackets in typed splices and vice versa. Resolves #24190 Apparently the check was essentially always (as far as I can trace back: d0d47ba76f8f0501cf3c4966bc83966ab38cac27), and while it does catch some mismatches, the type-checker will catch them too. OTOH, it prevents writing completely reasonable programs. - - - - - 32d208e1 by Vladislav Zavialov at 2023-12-12T20:41:36+03:00 EPA: Match changes to LHsToken removal - - - - - a3ee3b99 by Moritz Angermann at 2023-12-12T19:50:58-05:00 Drop hard Xcode dependency XCODE_VERSION calls out to `xcodebuild`, which is only available when having `Xcode` installed. The CommandLineTools are not sufficient. To install Xcode, you must have an apple id to download the Xcode.xip from apple. We do not use xcodebuild anywhere in our build explicilty. At best it appears to be a proxy for checking the linker or the compiler. These should rather be done with ``` xcrun ld -version ``` or similar, and not by proxy through Xcode. The CLR should be sufficient for building software on macOS. - - - - - 1c9496e0 by Vladislav Zavialov at 2023-12-12T19:51:34-05:00 docs: update information on RequiredTypeArguments Update the User's Guide and Release Notes to account for the recent progress in the implementation of RequiredTypeArguments. - - - - - d0b17576 by Ben Gamari at 2023-12-13T06:33:37-05:00 rts/eventlog: Fix off-by-one in assertion Previously we failed to account for the NULL terminator `postString` asserted that there is enough room in the buffer for the string. - - - - - a10f9b9b by Ben Gamari at 2023-12-13T06:33:37-05:00 rts/eventlog: Honor result of ensureRoomForVariableEvent is Previously we would keep plugging along, even if isn't enough room for the event. - - - - - 0e0f41c0 by Ben Gamari at 2023-12-13T06:33:37-05:00 rts/eventlog: Avoid truncating event sizes Previously ensureRoomForVariableEvent would truncate the desired size to 16-bits, resulting in #24197. Fixes #24197. - - - - - 64e724c8 by Artin Ghasivand at 2023-12-13T06:34:20-05:00 Remove the "Derived Constraint" argument of TcPluginSolver, docs - - - - - fe6d97dd by Vladislav Zavialov at 2023-12-13T06:34:56-05:00 EPA: Move tokens into GhcPs extension fields (#23447) Summary of changes * Remove Language.Haskell.Syntax.Concrete * Move all tokens into GhcPs extension fields (LHsToken -> EpToken) * Create new TTG extension fields as needed * Drop the MultAnn wrapper Updates the haddock submodule. Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 8106e695 by Zubin Duggal at 2023-12-13T06:35:34-05:00 testsuite: use copy_files in T23405 This prevents the tree from being dirtied when the file is modified. - - - - - ed0e4099 by Bryan Richter at 2023-12-14T04:30:53-05:00 Document ghc package's PVP-noncompliance This changes nothing, it just makes the status quo explicit. - - - - - 8bef8d9f by Luite Stegeman at 2023-12-14T04:31:33-05:00 JS: Mark spurious CI failures js_fragile(24259) This marks the spurious test failures on the JS platform as js_fragile(24259), so we don't hold up merge requests while fixing the underlying issues. See #24259 - - - - - 1c79526a by Finley McIlwaine at 2023-12-15T12:24:40-08:00 Late plugins - - - - - 000c3302 by Finley McIlwaine at 2023-12-15T12:24:40-08:00 withTiming on LateCCs and late plugins - - - - - be4551ac by Finley McIlwaine at 2023-12-15T12:24:40-08:00 add test for late plugins - - - - - 7c29da9f by Finley McIlwaine at 2023-12-15T12:24:40-08:00 Document late plugins - - - - - 9a52ae46 by Ben Gamari at 2023-12-20T07:07:26-05:00 Fix thunk update ordering Previously we attempted to ensure soundness of concurrent thunk update by synchronizing on the access of the thunk's info table pointer field. This was believed to be sufficient since the indirectee (which may expose a closure allocated by another core) would not be examined until the info table pointer update is complete. However, it turns out that this can result in data races in the presence of multiple threads racing a update a single thunk. For instance, consider this interleaving under the old scheme: Thread A Thread B --------- --------- t=0 Enter t 1 Push update frame 2 Begin evaluation 4 Pause thread 5 t.indirectee=tso 6 Release t.info=BLACKHOLE 7 ... (e.g. GC) 8 Resume thread 9 Finish evaluation 10 Relaxed t.indirectee=x 11 Load t.info 12 Acquire fence 13 Inspect t.indirectee 14 Release t.info=BLACKHOLE Here Thread A enters thunk `t` but is soon paused, resulting in `t` being lazily blackholed at t=6. Then, at t=10 Thread A finishes evaluation and updates `t.indirectee` with a relaxed store. Meanwhile, Thread B enters the blackhole. Under the old scheme this would introduce an acquire-fence but this would only synchronize with Thread A at t=6. Consequently, the result of the evaluation, `x`, is not visible to Thread B, introducing a data race. We fix this by treating the `indirectee` field as we do all other mutable fields. This means we must always access this field with acquire-loads and release-stores. See #23185. - - - - - f4b53538 by Vladislav Zavialov at 2023-12-20T07:08:02-05:00 docs: Fix link to 051-ghc-base-libraries.rst The proposal is no longer available at the previous URL. - - - - - f7e21fab by Matthew Pickering at 2023-12-21T14:57:40+00:00 hadrian: Build all executables in bin/ folder In the end the bindist creation logic copies them all into the bin folder. There is no benefit to building a specific few binaries in the lib/bin folder anymore. This also removes the ad-hoc logic to copy the touchy and unlit executables from stage0 into stage1. It takes <1s to build so we might as well just build it. - - - - - 0038d052 by Zubin Duggal at 2023-12-22T23:28:00-05:00 testsuite: mark jspace as fragile on i386. This test has been flaky for some time and has been failing consistently on i386-linux since 8e0446df landed. See #24261 - - - - - dfd670a0 by Ben Bellick at 2023-12-24T10:10:31-05:00 Deprecate -ddump-json and introduce -fdiagnostics-as-json Addresses #19278 This commit deprecates the underspecified -ddump-json flag and introduces a newer, well-specified flag -fdiagnostics-as-json. Also included is a JSON schema as part of the documentation. The -ddump-json flag will be slated for removal shortly after this merge. - - - - - 609e6225 by Ben Bellick at 2023-12-24T10:10:31-05:00 Deprecate -ddump-json and introduce -fdiagnostics-as-json Addresses #19278 This commit deprecates the underspecified -ddump-json flag and introduces a newer, well-specified flag -fdiagnostics-as-json. Also included is a JSON schema as part of the documentation. The -ddump-json flag will be slated for removal shortly after this merge. - - - - - 865513b2 by Ömer Sinan Ağacan at 2023-12-24T10:11:13-05:00 Fix BNF in user manual 6.6.8.2: formal syntax for instance declarations - - - - - c247b6be by Zubin Duggal at 2023-12-25T16:01:23-05:00 docs: document permissibility of -XOverloadedLabels (#24249) Document the permissibility introduced by https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0170-unrestricted-overloadedlabels.rst - - - - - e5b7eb59 by Ömer Sinan Ağacan at 2023-12-25T16:02:03-05:00 Fix a code block syntax in user manual sec. 6.8.8.6 - - - - - 2db11c08 by Ben Gamari at 2023-12-29T15:35:48-05:00 genSym: Reimplement via CAS on 32-bit platforms Previously the remaining use of the C implementation on 32-bit platforms resulted in a subtle bug, #24261. This was due to the C object (which used the RTS's `atomic_inc64` macro) being compiled without `-threaded` yet later being used in a threaded compiler. Side-step this issue by using the pure Haskell `genSym` implementation on all platforms. This required implementing `fetchAddWord64Addr#` in terms of CAS on 64-bit platforms. - - - - - 19328a8c by Xiaoyan Ren at 2023-12-29T15:36:30-05:00 Do not color the diagnostic code in error messages (#24172) - - - - - 685b467c by Krzysztof Gogolewski at 2023-12-29T15:37:06-05:00 Enforce that bindings of implicit parameters are lifted Fixes #24298 - - - - - bc4d67b7 by Matthew Craven at 2023-12-31T06:15:42-05:00 StgToCmm: Detect some no-op case-continuations ...and generate no code for them. Fixes #24264. - - - - - 5b603139 by Krzysztof Gogolewski at 2023-12-31T06:16:18-05:00 Revert "testsuite: mark jspace as fragile on i386." This reverts commit 0038d052c8c80b4b430bb2aa1c66d5280be1aa95. The atomicity bug should be fixed by !11802. - - - - - d55216ad by Krzysztof Gogolewski at 2024-01-01T12:05:49-05:00 Refactor: store [[PrimRep]] rather than [Type] in STG StgConApp stored a list of types. This list was used exclusively during unarisation of unboxed sums (mkUbxSum). However, this is at a wrong level of abstraction: STG shouldn't be concerned with Haskell types, only PrimReps. Update the code to store a [[PrimRep]]. Also, there's no point in storing this list when we're not dealing with an unboxed sum. - - - - - 8b340bc7 by Ömer Sinan Ağacan at 2024-01-01T12:06:29-05:00 Kind signatures docs: mention that they're allowed in newtypes - - - - - 989bf8e5 by Zubin Duggal at 2024-01-03T20:08:47-05:00 ci: Ensure we use the correct bindist name for the test artifact when generating release ghcup metadata Fixes #24268 - - - - - 89299a89 by Krzysztof Gogolewski at 2024-01-03T20:09:23-05:00 Refactor: remove calls to typePrimRepArgs The function typePrimRepArgs is just a thin wrapper around typePrimRep, adding a VoidRep if the list is empty. However, in StgToByteCode, we were discarding that VoidRep anyway, so there's no point in calling it. - - - - - c7be0c68 by mmzk1526 at 2024-01-03T20:10:07-05:00 Use "-V" for alex version check for better backward compatibility Fixes #24302. In recent versions of alex, "-v" is used for "--verbose" instead of "-version". - - - - - 67dbcc0a by Krzysztof Gogolewski at 2024-01-05T02:07:18-05:00 Fix VoidRep handling in ghci debugger 'go' inside extractSubTerms was giving a bad result given a VoidRep, attempting to round towards the next multiple of 0. I don't understand much about the debugger but the code should be better than it was. Fixes #24306 - - - - - 90ea574e by Krzysztof Gogolewski at 2024-01-05T02:07:54-05:00 VoidRep-related refactor * In GHC.StgToByteCode, replace bcIdPrimId with idPrimRep, bcIdArgRep with idArgRep, atomPrimRep with stgArgRep1. All of them were duplicates. * In GHC.Stg.Unarise, we were converting a PrimRep to a Type and back to PrimRep. Remove the calls to primRepToType and typePrimRep1 which cancel out. * In GHC.STG.Lint, GHC.StgToCmm, GHC.Types.RepType we were filtering out VoidRep from the result of typePrimRep. But typePrimRep never returns VoidRep - remove the filtering. - - - - - eaf72479 by brian at 2024-01-06T23:03:09-05:00 Add unaligned Addr# primops Implements CLC proposal #154: https://github.com/haskell/core-libraries-committee/issues/154 * add unaligned addr primops * add tests * accept tests * add documentation * fix js primops * uncomment in access ops * use Word64 in tests * apply suggestions * remove extra file * move docs * remove random options * use setByteArray# primop * better naming * update base-exports test * add base-exports for other architectures - - - - - d471d445 by Krzysztof Gogolewski at 2024-01-06T23:03:47-05:00 Remove VoidRep from PrimRep, introduce PrimOrVoidRep This introduces data PrimOrVoidRep = VoidRep | NVRep PrimRep changes typePrimRep1 to return PrimOrVoidRep, and adds a new function typePrimRepU to be used when the argument is definitely non-void. Details in Note [VoidRep] in GHC.Types.RepType. Fixes #19520 - - - - - 48720a07 by Matthew Craven at 2024-01-08T18:57:36-05:00 Apply Note [Sensitivity to unique increment] to LargeRecord - - - - - 9e2e180f by Sebastian Graf at 2024-01-08T18:58:13-05:00 Debugging: Add diffUFM for convenient diffing between UniqFMs - - - - - 948f3e35 by Sebastian Graf at 2024-01-08T18:58:13-05:00 Rename Opt_D_dump_stranal to Opt_D_dump_dmdanal ... and Opt_D_dump_str_signatures to Opt_D_dump_dmd_signatures - - - - - 4e217e3e by Sebastian Graf at 2024-01-08T18:58:13-05:00 Deprecate -ddump-stranal and -ddump-str-signatures ... and suggest -ddump-dmdanal and -ddump-dmd-signatures instead - - - - - 6c613c90 by Sebastian Graf at 2024-01-08T18:58:13-05:00 Move testsuite/tests/stranal to testsuite/tests/dmdanal A separate commit so that the rename is obvious to Git(Lab) - - - - - c929f02b by Sebastian Graf at 2024-01-08T18:58:13-05:00 CoreSubst: Stricten `substBndr` and `cloneBndr` Doing so reduced allocations of `cloneBndr` by about 25%. ``` T9233(normal) ghc/alloc 672,488,656 663,083,216 -1.4% GOOD T9675(optasm) ghc/alloc 423,029,256 415,812,200 -1.7% geo. mean -0.1% minimum -1.7% maximum +0.1% ``` Metric Decrease: T9233 - - - - - e3ca78f3 by Krzysztof Gogolewski at 2024-01-10T17:35:59-05:00 Deprecate -Wsemigroup This warning was used to prepare for Semigroup becoming a superclass of Monoid, and for (<>) being exported from Prelude. This happened in GHC 8.4 in 8ae263ceb3566 and feac0a3bc69fd3. The leftover logic for (<>) has been removed in GHC 9.8, 4d29ecdfcc79. Now the warning does nothing at all and can be deprecated. - - - - - 08d14925 by amesgen at 2024-01-10T17:36:42-05:00 WASM metadata: use correct GHC version - - - - - 7a808419 by Xiaoyan Ren at 2024-01-10T17:37:24-05:00 Allow SCC declarations in TH (#24081) - - - - - 28827c51 by Xiaoyan Ren at 2024-01-10T17:37:24-05:00 Fix prettyprinting of SCC pragmas - - - - - ae9cc1a8 by Matthew Craven at 2024-01-10T17:38:01-05:00 Fix loopification in the presence of void arguments This also removes Note [Void arguments in self-recursive tail calls], which was just misleading. It's important to count void args both in the function's arity and at the call site. Fixes #24295. - - - - - b718b145 by Zubin Duggal at 2024-01-10T17:38:36-05:00 testsuite: Teach testsuite driver about c++ sources - - - - - 09cb57ad by Zubin Duggal at 2024-01-10T17:38:36-05:00 driver: Set -DPROFILING when compiling C++ sources with profiling Earlier, we used to pass all preprocessor flags to the c++ compiler. This meant that -DPROFILING was passed to the c++ compiler because it was a part of C++ flags However, this was incorrect and the behaviour was changed in 8ff3134ed4aa323b0199ad683f72165e51a59ab6. See #21291. But that commit exposed this bug where -DPROFILING was no longer being passed when compiling c++ sources. The fix is to explicitly include -DPROFILING in `opt_cxx` when profiling is enabled to ensure we pass the correct options for the way to both C and C++ compilers Fixes #24286 - - - - - 2cf9dd96 by Zubin Duggal at 2024-01-10T17:38:36-05:00 testsuite: rename objcpp -> objcxx To avoid confusion with C Pre Processsor - - - - - af6932d6 by Simon Peyton Jones at 2024-01-10T17:39:12-05:00 Make TYPE and CONSTRAINT not-apart Issue #24279 showed up a bug in the logic in GHC.Core.Unify.unify_ty which is supposed to make TYPE and CONSTRAINT be not-apart. Easily fixed. - - - - - 4a39b5ff by Zubin Duggal at 2024-01-10T17:39:48-05:00 ci: Fix typo in mk_ghcup_metadata.py There was a missing colon in the fix to #24268 in 989bf8e53c08eb22de716901b914b3607bc8dd08 - - - - - 13503451 by Zubin Duggal at 2024-01-10T17:40:24-05:00 release-ci: remove release-x86_64-linux-deb11-release+boot_nonmoving_gc job There is no reason to have this release build or distribute this variation. This configuration is for testing purposes only. - - - - - afca46a4 by Sebastian Graf at 2024-01-10T17:41:00-05:00 Parser: Add a Note detailing why we need happy's `error` to implement layout - - - - - eaf8a06d by Krzysztof Gogolewski at 2024-01-11T00:43:17+01:00 Turn -Wtype-equality-out-of-scope on by default Also remove -Wnoncanonical-{monoid,monad}-instances from -Wcompat, since they are enabled by default. Refresh wcompat-warnings/ test with new -Wcompat warnings. Part of #24267 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 42bee5aa by Sebastian Graf at 2024-01-12T21:16:21-05:00 Arity: Require called *exactly once* for eta exp with -fpedantic-bottoms (#24296) In #24296, we had a program in which we eta expanded away an error despite the presence of `-fpedantic-bottoms`. This was caused by turning called *at least once* lambdas into one-shot lambdas, while with `-fpedantic-bottoms` it is only sound to eta expand over lambdas that are called *exactly* once. An example can be found in `Note [Combining arity type with demand info]`. Fixes #24296. - - - - - 7e95f738 by Andreas Klebinger at 2024-01-12T21:16:57-05:00 Aarch64: Enable -mfma by default. Fixes #24311 - - - - - e43788d0 by Jason Shipman at 2024-01-14T12:47:38-05:00 Add more instances for Compose: Fractional, RealFrac, Floating, RealFloat CLC proposal #226 https://github.com/haskell/core-libraries-committee/issues/226 - - - - - ae6d8cd2 by Sebastian Graf at 2024-01-14T12:48:15-05:00 Pmc: COMPLETE pragmas associated with Family TyCons should apply to representation TyCons as well (#24326) Fixes #24326. - - - - - c5fc7304 by sheaf at 2024-01-15T14:15:29-05:00 Use lookupOccRn_maybe in TH.lookupName When looking up a value, we want to be able to find both variables and record fields. So we should not use the lookupSameOccRn_maybe function, as we can't know ahead of time which record field namespace a record field with the given textual name will belong to. Fixes #24293 - - - - - da908790 by Krzysztof Gogolewski at 2024-01-15T14:16:05-05:00 Make the build more strict on documentation errors * Detect undefined labels. This can be tested by adding :ref:`nonexistent` to a documentation rst file; attempting to build docs will fail. Fixed the undefined label in `9.8.1-notes.rst`. * Detect errors. While we have plenty of warnings, we can at least enforce that Sphinx does not report errors. Fixed the error in `required_type_arguments.rst`. Unrelated change: I have documented that the `-dlint` enables `-fcatch-nonexhaustive-cases`, as can be verified by checking `enableDLint`. - - - - - 5077416e by Javier Sagredo at 2024-01-16T15:40:06-05:00 Profiling: Adds an option to not start time profiling at startup Using the functionality provided by d89deeba47ce04a5198a71fa4cbc203fe2c90794, this patch creates a new rts flag `--no-automatic-time-samples` which disables the time profiling when starting a program. It is then expected that the user starts it whenever it is needed. Fixes #24337 - - - - - 5776008c by Matthew Pickering at 2024-01-16T15:40:42-05:00 eventlog: Fix off-by-one error in postIPE We were missing the extra_comma from the calculation of the size of the payload of postIPE. This was causing assertion failures when the event would overflow the buffer by one byte, as ensureRoomForVariable event would report there was enough space for `n` bytes but then we would write `n + 1` bytes into the buffer. Fixes #24287 - - - - - 66dc09b1 by Simon Peyton Jones at 2024-01-16T15:41:18-05:00 Improve SpecConstr (esp nofib/spectral/ansi) This MR makes three improvements to SpecConstr: see #24282 * It fixes an outright (and recently-introduced) bug in `betterPat`, which was wrongly forgetting to compare the lengths of the argument lists. * It enhances ConVal to inclue a boolean for work-free-ness, so that the envt can contain non-work-free constructor applications, so that we can do more: see Note [ConVal work-free-ness] * It rejigs `subsumePats` so that it doesn't reverse the list. This can make a difference because, when patterns overlap, we arbitrarily pick the first. There is no "right" way, but this retains the old pre-subsumePats behaviour, thereby "fixing" the regression in #24282. Nofib results +======================================== | spectral/ansi -21.14% | spectral/hartel/comp_lab_zift -0.12% | spectral/hartel/parstof +0.09% | spectral/last-piece -2.32% | spectral/multiplier +6.03% | spectral/para +0.60% | spectral/simple -0.26% +======================================== | geom mean -0.18% +---------------------------------------- The regression in `multiplier` is sad, but it simply replicates GHC's previous behaviour (e.g. GHC 9.6). - - - - - 65da79b3 by Matthew Pickering at 2024-01-16T15:41:54-05:00 hadrian: Reduce Cabal verbosity The comment claims that `simpleUserHooks` decrease verbosity, and it does, but only for the `postConf` phase. The other phases are too verbose with `-V`. At the moment > 5000 lines of the build log are devoted to output from `cabal copy`. So I take the simple approach and just decrease the verbosity level again. If the output of `postConf` is essential then it would be better to implement our own `UserHooks` which doesn't decrease the verbosity for `postConf`. Fixes #24338 - - - - - 16414d7d by Matthew Pickering at 2024-01-17T10:54:59-05:00 Stop retaining old ModGuts throughout subsequent simplifier phases Each phase of the simplifier typically rewrites the majority of ModGuts, so we want to be able to release the old ModGuts as soon as possible. `name_ppr_ctxt` lives throught the whole optimiser phase and it was retaining a reference to `ModGuts`, so we were failing to release the old `ModGuts` until the end of the phase (potentially doubling peak memory usage for that particular phase). This was discovered using eras profiling (#24332) Fixes #24328 - - - - - 7f0879e1 by Matthew Pickering at 2024-01-17T10:55:35-05:00 Update nofib submodule - - - - - 320454d3 by Cheng Shao at 2024-01-17T23:02:40+00:00 ci: bump ci-images for updated wasm image - - - - - 2eca52b4 by Cheng Shao at 2024-01-17T23:06:44+00:00 base: treat all FDs as "nonblocking" on wasm On posix platforms, when performing read/write on FDs, we check the nonblocking flag first. For FDs without this flag (e.g. stdout), we call fdReady() first, which in turn calls poll() to wait for I/O to be available on that FD. This is problematic for wasm32-wasi: although select()/poll() is supported via the poll_oneoff() wasi syscall, that syscall is rather heavyweight and runtime behavior differs in different wasi implementations. The issue is even worse when targeting browsers, given there's no satisfactory way to implement async I/O as a synchronous syscall, so existing JS polyfills for wasi often give up and simply return ENOSYS. Before we have a proper I/O manager that avoids poll_oneoff() for async I/O on wasm, this patch improves the status quo a lot by merely pretending all FDs are "nonblocking". Read/write on FDs will directly invoke read()/write(), which are much more reliably handled in existing wasi implementations, especially those in browsers. Fixes #23275 and the following test cases: T7773 isEOF001 openFile009 T4808 cgrun025 Approved by CLC proposal #234: https://github.com/haskell/core-libraries-committee/issues/234 - - - - - 83c6c710 by Andrew Lelechenko at 2024-01-18T05:21:49-05:00 base: clarify how to disable warnings about partiality of Data.List.{head,tail} - - - - - c4078f2f by Simon Peyton Jones at 2024-01-18T05:22:25-05:00 Fix four bug in handling of (forall cv. body_ty) These bugs are all described in #24335 It's not easy to provoke the bug, hence no test case. - - - - - 119586ea by Alexis King at 2024-01-19T00:08:00-05:00 Always refresh profiling CCSes after running pending initializers Fixes #24171. - - - - - 9718d970 by Oleg Grenrus at 2024-01-19T00:08:36-05:00 Set default-language: GHC2021 in ghc library Go through compiler/ sources, and remove all BangPatterns (and other GHC2021 enabled extensions in these files). - - - - - 3ef71669 by Matthew Pickering at 2024-01-19T21:55:16-05:00 testsuite: Remove unused have_library function Also remove the hence unused testsuite option `--test-package-db`. Fixes #24342 - - - - - 5b7fa20c by Jade at 2024-01-19T21:55:53-05:00 Fix Spelling in the compiler Tracking: #16591 - - - - - 09875f48 by Matthew Pickering at 2024-01-20T12:20:44-05:00 testsuite: Implement `isInTreeCompiler` in a more robust way Just a small refactoring to avoid redundantly specifying the same strings in two different places. - - - - - 0d12b987 by Jade at 2024-01-20T12:21:20-05:00 Change maintainer email from cvs-ghc at haskell.org to ghc-devs at haskell.org. Fixes #22142 - - - - - eebdd316 by Apoorv Ingle at 2024-01-23T13:49:12+00:00 Changes for haskell/haddock#18324 - - - - - 1fa1c00c by Jade at 2024-01-23T19:17:03-05:00 Enhance Documentation of functions exported by Data.Function This patch aims to improve the documentation of functions exported in Data.Function Tracking: #17929 Fixes: #10065 - - - - - ab47a43d by Jade at 2024-01-23T19:17:39-05:00 Improve documentation of hGetLine. - Add explanation for whether a newline is returned - Add examples Fixes #14804 - - - - - dd4af0e5 by Cheng Shao at 2024-01-23T19:18:17-05:00 Fix genapply for cross-compilation by nuking fragile CPP logic This commit fixes incorrectly built genapply when cross compiling (#24347) by nuking all fragile CPP logic in it from the orbit. All target-specific info are now read from DerivedConstants.h at runtime, see added note for details. Also removes a legacy Makefile and adds haskell language server support for genapply. - - - - - 0cda2b8b by Cheng Shao at 2024-01-23T19:18:17-05:00 rts: enable wasm32 register mapping The wasm backend didn't properly make use of all Cmm global registers due to #24347. Now that it is fixed, this patch re-enables full register mapping for wasm32, and we can now generate smaller & faster wasm modules that doesn't always spill arguments onto the stack. Fixes #22460 #24152. - - - - - 0325a6e5 by Greg Steuck at 2024-01-24T01:29:44-05:00 Avoid utf8 in primops.txt.pp comments They don't make it through readFile' without explicitly setting the encoding. See https://gitlab.haskell.org/ghc/ghc/-/issues/17755 - - - - - 1aaf0bd8 by David Binder at 2024-01-24T01:30:20-05:00 Bump hpc and hpc-bin submodule Bump hpc to 0.7.0.1 Bump hpc-bin to commit d1780eb2 - - - - - e693a4e8 by Ben Gamari at 2024-01-24T01:30:56-05:00 testsuite: Ignore stderr in T8089 Otherwise spurious "Killed: 9" messages to stderr may cause the test to fail. Fixes #24361. - - - - - a40f4ab2 by sheaf at 2024-01-24T14:04:33-05:00 Fix FMA instruction on LLVM We were emitting the wrong instructions for fused multiply-add operations on LLVM: - the instruction name is "llvm.fma.f32" or "llvm.fma.f64", not "fmadd" - LLVM does not support other instructions such as "fmsub"; instead we implement these by flipping signs of some arguments - the instruction is an LLVM intrinsic, which requires handling it like a normal function call instead of a machine instruction Fixes #24223 - - - - - 69abc786 by Andrei Borzenkov at 2024-01-24T14:05:09-05:00 Add changelog entry for renaming tuples from (,,...,,) to Tuple<n> (24291) - - - - - 0ac8f385 by Cheng Shao at 2024-01-25T00:27:48-05:00 compiler: remove unused GHC.Linker module The GHC.Linker module is empty and unused, other than as a hack for the make build system. We can remove it now that make is long gone; the note is moved to GHC.Linker.Loader instead. - - - - - 699da01b by Hécate Moonlight at 2024-01-25T00:28:27-05:00 Clarification for newtype constructors when using `coerce` - - - - - b2d8cd85 by Matt Walker at 2024-01-26T09:50:08-05:00 Fix #24308 Add tests for semicolon separated where clauses - - - - - 0da490a1 by Ben Gamari at 2024-01-26T17:34:41-05:00 hsc2hs: Bump submodule - - - - - 3f442fd2 by Ben Gamari at 2024-01-26T17:34:41-05:00 Bump containers submodule to 0.7 - - - - - 82a1c656 by Sebastian Nagel at 2024-01-29T02:32:40-05:00 base: with{Binary}File{Blocking} only annotates own exceptions Fixes #20886 This ensures that inner, unrelated exceptions are not misleadingly annotated with the opened file. - - - - - 9294a086 by Andreas Klebinger at 2024-01-29T02:33:15-05:00 Fix fma warning when using llvm on aarch64. On aarch64 fma is always on so the +fma flag doesn't exist for that target. Hence no need to try and pass +fma to llvm. Fixes #24379 - - - - - ced2e731 by sheaf at 2024-01-29T17:27:12-05:00 No shadowing warnings for NoFieldSelector fields This commit ensures we don't emit shadowing warnings when a user shadows a field defined with NoFieldSelectors. Fixes #24381 - - - - - 8eeadfad by Patrick at 2024-01-29T17:27:51-05:00 Fix bug wrong span of nested_doc_comment #24378 close #24378 1. Update the start position of span in `nested_doc_comment` correctly. and hence the spans of identifiers of haddoc can be computed correctly. 2. add test `HaddockSpanIssueT24378`. - - - - - a557580f by Alexey Radkov at 2024-01-30T19:41:52-05:00 Fix irrelevant dodgy-foreign-imports warning on import f-pointers by value A test *сс018* is attached (not sure about the naming convention though). Note that without the fix, the test fails with the *dodgy-foreign-imports* warning passed to stderr. The warning disappears after the fix. GHC shouldn't warn on imports of natural function pointers from C by value (which is feasible with CApiFFI), such as ```haskell foreign import capi "cc018.h value f" f :: FunPtr (Int -> IO ()) ``` where ```c void (*f)(int); ``` See a related real-world use-case [here](https://gitlab.com/daniel-casanueva/pcre-light/-/merge_requests/17). There, GHC warns on import of C function pointer `pcre_free`. - - - - - ca99efaf by Alexey Radkov at 2024-01-30T19:41:53-05:00 Rename test cc018 -> T24034 - - - - - 88c38dd5 by Ben Gamari at 2024-01-30T19:42:28-05:00 rts/TraverseHeap.c: Ensure that PosixSource.h is included first - - - - - ca2e919e by Simon Peyton Jones at 2024-01-31T09:29:45+00:00 Make decomposeRuleLhs a bit more clever This fixes #24370 by making decomposeRuleLhs undertand dictionary /functions/ as well as plain /dictionaries/ - - - - - 94ce031d by Teo Camarasu at 2024-02-01T05:49:49-05:00 doc: Add -Dn flag to user guide Resolves #24394 - - - - - 31553b11 by Ben Gamari at 2024-02-01T12:21:29-05:00 cmm: Introduce MO_RelaxedRead In hand-written Cmm it can sometimes be necessary to atomically load from memory deep within an expression (e.g. see the `CHECK_GC` macro). This MachOp provides a convenient way to do so without breaking the expression into multiple statements. - - - - - 0785cf81 by Ben Gamari at 2024-02-01T12:21:29-05:00 codeGen: Use relaxed accesses in ticky bumping - - - - - be423dda by Ben Gamari at 2024-02-01T12:21:29-05:00 base: use atomic write when updating timer manager - - - - - 8a310e35 by Ben Gamari at 2024-02-01T12:21:29-05:00 Use relaxed atomics to manipulate TSO status fields - - - - - d6809ee4 by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Add necessary barriers when manipulating TSO owner - - - - - 39e3ac5d by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Use `switch` to branch on why_blocked This is a semantics-preserving refactoring. - - - - - 515eb33d by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix synchronization on thread blocking state We now use a release barrier whenever we update a thread's blocking state. This required widening StgTSO.why_blocked as AArch64 does not support atomic writes on 16-bit values. - - - - - eb38812e by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix data race in threadPaused This only affects an assertion in the debug RTS and only needs relaxed ordering. - - - - - 26c48dd6 by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix data race in threadStatus# - - - - - 6af43ab4 by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix data race in Interpreter's preemption check - - - - - 9502ad3c by Ben Gamari at 2024-02-01T12:21:29-05:00 rts/Messages: Fix data race - - - - - 60802db5 by Ben Gamari at 2024-02-01T12:21:30-05:00 rts/Prof: Fix data race - - - - - ef8ccef5 by Ben Gamari at 2024-02-01T12:21:30-05:00 rts: Use relaxed ordering on dirty/clean info tables updates When changing the dirty/clean state of a mutable object we needn't have any particular ordering. - - - - - 76fe2b75 by Ben Gamari at 2024-02-01T12:21:30-05:00 codeGen: Use relaxed-read in closureInfoPtr - - - - - a6316eb4 by Ben Gamari at 2024-02-01T12:21:30-05:00 STM: Use acquire loads when possible Full sequential consistency is not needed here. - - - - - 6bddfd3d by Ben Gamari at 2024-02-01T12:21:30-05:00 rts: Use fence rather than redundant load Previously we would use an atomic load to ensure acquire ordering. However, we now have `ACQUIRE_FENCE_ON`, which allows us to express this more directly. - - - - - 55c65dbc by Ben Gamari at 2024-02-01T12:21:30-05:00 rts: Fix data races in profiling timer - - - - - 856b5e75 by Ben Gamari at 2024-02-01T12:21:30-05:00 Add Note [C11 memory model] - - - - - 6534da24 by Cheng Shao at 2024-02-01T12:22:07-05:00 compiler: move generic cmm optimization logic in NCG to a standalone module This commit moves GHC.CmmToAsm.cmmToCmm to a standalone module, GHC.Cmm.GenericOpt. The main motivation is enabling this logic to be run in the wasm backend NCG code, which is defined in other modules that's imported by GHC.CmmToAsm, causing a cyclic dependency issue. - - - - - 87e34888 by Cheng Shao at 2024-02-01T12:22:07-05:00 compiler: explicitly disable PIC in wasm32 NCG This commit explicitly disables the ncgPIC flag for the wasm32 target. The wasm backend doesn't support PIC for the time being. - - - - - c6ce242e by Cheng Shao at 2024-02-01T12:22:07-05:00 compiler: enable generic cmm optimizations in wasm backend NCG This commit enables the generic cmm optimizations in other NCGs to be run in the wasm backend as well, followed by a late cmm control-flow optimization pass. The added optimizations do catch some corner cases not handled by the pre-NCG cmm pipeline and are useful in generating smaller CFGs. - - - - - 151dda4e by Andrei Borzenkov at 2024-02-01T12:22:43-05:00 Namespacing for WARNING/DEPRECATED pragmas (#24396) New syntax for WARNING and DEPRECATED pragmas was added, namely namespace specifierss: namespace_spec ::= 'type' | 'data' | {- empty -} warning ::= warning_category namespace_spec namelist strings deprecation ::= namespace_spec namelist strings A new data type was introduced to represent these namespace specifiers: data NamespaceSpecifier = NoSpecifier | TypeNamespaceSpecifier (EpToken "type") | DataNamespaceSpecifier (EpToken "data") Extension field XWarning now contains this NamespaceSpecifier. lookupBindGroupOcc function was changed: it now takes NamespaceSpecifier and checks that the namespace of the found names matches the passed flag. With this change {-# WARNING data D "..." #-} pragma will only affect value namespace and {-# WARNING type D "..." #-} will only affect type namespace. The same logic is applicable to DEPRECATED pragmas. Finding duplicated warnings inside rnSrcWarnDecls now takes into consideration NamespaceSpecifier flag to allow warnings with the same names that refer to different namespaces. - - - - - 38c3afb6 by Bryan Richter at 2024-02-01T12:23:19-05:00 CI: Disable the test-cabal-reinstall job Fixes #24363 - - - - - 27020458 by Matthew Craven at 2024-02-03T01:53:26-05:00 Bump bytestring submodule to something closer to 0.12.1 ...mostly so that 16d6b7e835ffdcf9b894e79f933dd52348dedd0c (which reworks unaligned writes in Builder) and the stuff in https://github.com/haskell/bytestring/pull/631 can see wider testing. The less-terrible code for unaligned writes used in Builder on hosts not known to be ulaigned-friendly also takes less effort for GHC to compile, resulting in a metric decrease for T21839c on some platforms. The metric increase on T21839r is caused by the unrelated commit 750dac33465e7b59100698a330b44de7049a345c. It perhaps warrants further analysis and discussion (see #23822) but is not critical. Metric Decrease: T21839c Metric Increase: T21839r - - - - - cdddeb0f by Rodrigo Mesquita at 2024-02-03T01:54:02-05:00 Work around autotools setting C11 standard in CC/CXX In autoconf >=2.70, C11 is set by default for $CC and $CXX via the -std=...11 flag. In this patch, we split the "-std" flag out of the $CC and $CXX variables, which we traditionally assume to be just the executable name/path, and move it to $CFLAGS/$CXXFLAGS instead. Fixes #24324 - - - - - 5ff7cc26 by Apoorv Ingle at 2024-02-03T13:14:46-06:00 Expand `do` blocks right before typechecking using the `HsExpansion` philosophy. - Fixes #18324 #20020 #23147 #22788 #15598 #22086 #21206 - The change is detailed in - Note [Expanding HsDo with HsExpansion] in `GHC.Tc.Gen.Do` - Note [Doing HsExpansion in the Renamer vs Typechecker] in `GHC.Rename.Expr` expains the rational of doing expansions in type checker as opposed to in the renamer - Adds new datatypes: - `GHC.Hs.Expr.XXExprGhcRn`: new datatype makes this expansion work easier 1. Expansion bits for Expressions, Statements and Patterns in (`ExpandedThingRn`) 2. `PopErrCtxt` a special GhcRn Phase only artifcat to pop the previous error message in the error context stack - `GHC.Basic.Origin` now tracks the reason for expansion in case of Generated This is useful for type checking cf. `GHC.Tc.Gen.Expr.tcExpr` case for `HsLam` - Kills `HsExpansion` and `HsExpanded` as we have inlined them in `XXExprGhcRn` and `XXExprGhcTc` - Ensures warnings such as 1. Pattern match checks 2. Failable patterns 3. non-() return in body statements are preserved - Kill `HsMatchCtxt` in favor of `TcMatchAltChecker` - Testcases: * T18324 T20020 T23147 T22788 T15598 T22086 * T23147b (error message check), * DoubleMatch (match inside a match for pmc check) * pattern-fails (check pattern match with non-refutable pattern, eg. newtype) * Simple-rec (rec statements inside do statment) * T22788 (code snippet from #22788) * DoExpanion1 (Error messages for body statments) * DoExpansion2 (Error messages for bind statements) * DoExpansion3 (Error messages for let statements) Also repoint haddock to the right submodule so that the test (haddockHypsrcTest) pass Metric Increase 'compile_time/bytes allocated': T9020 The testcase is a pathalogical example of a `do`-block with many statements that do nothing. Given that we are expanding the statements into function binds, we will have to bear a (small) 2% cost upfront in the compiler to unroll the statements. - - - - - 0df8ce27 by Vladislav Zavialov at 2024-02-04T03:55:14-05:00 Reduce parser allocations in allocateCommentsP In the most common case, the comment queue is empty, so we can skip the work of processing it. This reduces allocations by about 10% in the parsing001 test. Metric Decrease: MultiLayerModulesRecomp parsing001 - - - - - ae856a82 by Matthew Pickering at 2024-02-05T12:22:39+00:00 ghc-internals fallout - - - - - cfd68290 by Simon Peyton Jones at 2024-02-05T17:58:33-05:00 Stop dropping a case whose binder is demanded This MR fixes #24251. See Note [Case-to-let for strictly-used binders] in GHC.Core.Opt.Simplify.Iteration, plus #24251, for lots of discussion. Final Nofib changes over 0.1%: +----------------------------------------- | imaginary/digits-of-e2 -2.16% | imaginary/rfib -0.15% | real/fluid -0.10% | real/gamteb -1.47% | real/gg -0.20% | real/maillist +0.19% | real/pic -0.23% | real/scs -0.43% | shootout/n-body -0.41% | shootout/spectral-norm -0.12% +======================================== | geom mean -0.05% Pleasingly, overall executable size is down by just over 1%. Compile times (in perf/compiler) wobble around a bit +/- 0.5%, but the geometric mean is -0.1% which seems good. - - - - - e4d137bb by Simon Peyton Jones at 2024-02-05T17:58:33-05:00 Add Note [Bangs in Integer functions] ...to document the bangs in the functions in GHC.Num.Integer - - - - - ce90f12f by Andrei Borzenkov at 2024-02-05T17:59:09-05:00 Hide WARNING/DEPRECATED namespacing under -XExplicitNamespaces (#24396) - - - - - e2ea933f by Simon Peyton Jones at 2024-02-06T10:12:04-05:00 Refactoring in preparation for lazy skolemisation * Make HsMatchContext and HsStmtContext be parameterised over the function name itself, rather than over the pass. See [mc_fun field of FunRhs] in Language.Haskell.Syntax.Expr - Replace types HsMatchContext GhcPs --> HsMatchContextPs HsMatchContext GhcRn --> HsMatchContextRn HsMatchContext GhcTc --> HsMatchContextRn (sic! not Tc) HsStmtContext GhcRn --> HsStmtContextRn - Kill off convertHsMatchCtxt * Split GHC.Tc.Type.BasicTypes.TcSigInfo so that TcCompleteSig (describing a complete user-supplied signature) is its own data type. - Split TcIdSigInfo(CompleteSig, PartialSig) into TcCompleteSig(CSig) TcPartialSig(PSig) - Use TcCompleteSig in tcPolyCheck, CheckGen - Rename types and data constructors: TcIdSigInfo --> TcIdSig TcPatSynInfo(TPSI) --> TcPatSynSig(PatSig) - Shuffle around helper functions: tcSigInfoName (moved to GHC.Tc.Types.BasicTypes) completeSigPolyId_maybe (moved to GHC.Tc.Types.BasicTypes) tcIdSigName (inlined and removed) tcIdSigLoc (introduced) - Rearrange the pattern match in chooseInferredQuantifiers * Rename functions and types: tcMatchesCase --> tcCaseMatches tcMatchesFun --> tcFunBindMatches tcMatchLambda --> tcLambdaMatches tcPats --> tcMatchPats matchActualFunTysRho --> matchActualFunTys matchActualFunTySigma --> matchActualFunTy * Add HasDebugCallStack constraints to: mkBigCoreVarTupTy, mkBigCoreTupTy, boxTy, mkPiTy, mkPiTys, splitAppTys, splitTyConAppNoView_maybe * Use `penv` from the outer context in the inner loop of GHC.Tc.Gen.Pat.tcMultiple * Move tcMkVisFunTy, tcMkInvisFunTy, tcMkScaledFunTys down the file, factor out and export tcMkScaledFunTy. * Move isPatSigCtxt down the file. * Formatting and comments Co-authored-by: Vladislav Zavialov <vlad.z.4096 at gmail.com> - - - - - f5d3e03c by Andrei Borzenkov at 2024-02-06T10:12:04-05:00 Lazy skolemisation for @a-binders (#17594) This patch is a preparation for @a-binders implementation. The main changes are: * Skolemisation is now prepared to deal with @binders. See Note [Skolemisation overview] in GHC.Tc.Utils.Unify. Most of the action is in - Utils.Unify.matchExpectedFunTys - Gen.Pat.tcMatchPats - Gen.Expr.tcPolyExprCheck - Gen.Binds.tcPolyCheck Some accompanying refactoring: * I found that funTyConAppTy_maybe was doing a lot of allocation, and rejigged userTypeError_maybe to avoid calling it. - - - - - 532993c8 by Zubin Duggal at 2024-02-06T10:12:41-05:00 driver: Really don't lose track of nodes when we fail to resolve cycles This fixes a bug in 8db8d2fd1c881032b1b360c032b6d9d072c11723, where we could lose track of acyclic components at the start of an unresolved cycle. We now ensure we never loose track of any of these components. As T24275 demonstrates, a "cyclic" SCC might not really be a true SCC: When viewed without boot files, we have a single SCC ``` [REC main:T24275B [main:T24275B {-# SOURCE #-}, main:T24275A {-# SOURCE #-}] main:T24275A [main:T24275A {-# SOURCE #-}]] ``` But with boot files this turns into ``` [NONREC main:T24275B {-# SOURCE #-} [], REC main:T24275B [main:T24275B {-# SOURCE #-}, main:T24275A {-# SOURCE #-}] main:T24275A {-# SOURCE #-} [main:T24275B], NONREC main:T24275A [main:T24275A {-# SOURCE #-}]] ``` Note that this is truly not an SCC, as no nodes are reachable from T24275B.hs-boot. However, we treat this entire group as a single "SCC" because it seems so when we analyse the graph without taking boot files into account. Indeed, we must return a single ResolvedCycle element in the BuildPlan for this as described in Note [Upsweep]. However, since after resolving this is not a true SCC anymore, `findCycle` fails to find a cycle and we have a sub-optimal error message as a result. To handle this, I extended `findCycle` to not assume its input is an SCC, and to try harder to find cycles in its input. Fixes #24275 - - - - - b35dd613 by Zubin Duggal at 2024-02-06T10:13:17-05:00 GHCi: Lookup breakpoint CCs in the correct module We need to look up breakpoint CCs in the module that the breakpoint points to, and not the current module. Fixes #24327 - - - - - b09e6958 by Zubin Duggal at 2024-02-06T10:13:17-05:00 testsuite: Add test for #24327 - - - - - 569b4c10 by doyougnu at 2024-02-07T03:06:26-05:00 ts: add compile_artifact, ignore_extension flag In b521354216f2821e00d75f088d74081d8b236810 the testsuite gained the capability to collect generic metrics. But this assumed that the test was not linking and producing artifacts and we only wanted to track object files, interface files, or build artifacts from the compiler build. However, some backends, such as the JS backend, produce artifacts when compiling, such as the jsexe directory which we want to track. This patch: - tweaks the testsuite to collect generic metrics on any build artifact in the test directory. - expands the exe_extension function to consider windows and adds the ignore_extension flag. - Modifies certain tests to add the ignore_extension flag. Tests such as heaprof002 expect a .ps file, but on windows without ignore_extensions the testsuite will look for foo.exe.ps. Hence the flag. - adds the size_hello_artifact test - - - - - 75a31379 by doyougnu at 2024-02-07T03:06:26-05:00 ts: add wasm_arch, heapprof002 wasm extension - - - - - c9731d6d by Rodrigo Mesquita at 2024-02-07T03:07:03-05:00 Synchronize bindist configure for #24324 In cdddeb0f1280b40cc194028bbaef36e127175c4c, we set up a workaround for #24324 in the in-tree configure script, but forgot to update the bindist configure script accordingly. This updates it. - - - - - d309f4e7 by Matthew Pickering at 2024-02-07T03:07:38-05:00 distrib/configure: Fix typo in CONF_GCC_LINKER_OPTS_STAGE2 variable Instead we were setting CONF_GCC_LINK_OPTS_STAGE2 which meant that we were missing passing `--target` when invoking the linker. Fixes #24414 - - - - - 77db84ab by Ben Gamari at 2024-02-08T00:35:22-05:00 llvmGen: Adapt to allow use of new pass manager. We now must use `-passes` in place of `-O<n>` due to #21936. Closes #21936. - - - - - 3c9ddf97 by Matthew Pickering at 2024-02-08T00:35:59-05:00 testsuite: Mark length001 as fragile on javascript Modifying the timeout multiplier is not a robust way to get this test to reliably fail. Therefore we mark it as fragile until/if javascript ever supports the stack limit. - - - - - 20b702b5 by Matthew Pickering at 2024-02-08T00:35:59-05:00 Javascript: Don't filter out rtsDeps list This logic appears to be incorrect as it would drop any dependency which was not in a direct dependency of the package being linked. In the ghc-internals split this started to cause errors because `ghc-internal` is not a direct dependency of most packages, and hence important symbols to keep which are hard coded into the js runtime were getting dropped. - - - - - 2df96366 by Ben Gamari at 2024-02-08T00:35:59-05:00 base: Cleanup whitespace in cbits - - - - - 44f6557a by Ben Gamari at 2024-02-08T00:35:59-05:00 Move `base` to `ghc-internal` Here we move a good deal of the implementation of `base` into a new package, `ghc-internal` such that it can be evolved independently from the user-visible interfaces of `base`. While we want to isolate implementation from interfaces, naturally, we would like to avoid turning `base` into a mere set of module re-exports. However, this is a non-trivial undertaking for a variety of reasons: * `base` contains numerous known-key and wired-in things, requiring corresponding changes in the compiler * `base` contains a significant amount of C code and corresponding autoconf logic, which is very fragile and difficult to break apart * `base` has numerous import cycles, which are currently dealt with via carefully balanced `hs-boot` files * We must not break existing users To accomplish this migration, I tried the following approaches: * [Split-GHC.Base]: Break apart the GHC.Base knot to allow incremental migration of modules into ghc-internal: this knot is simply too intertwined to be easily pulled apart, especially given the rather tricky import cycles that it contains) * [Move-Core]: Moving the "core" connected component of base (roughly 150 modules) into ghc-internal. While the Haskell side of this seems tractable, the C dependencies are very subtle to break apart. * [Move-Incrementally]: 1. Move all of base into ghc-internal 2. Examine the module structure and begin moving obvious modules (e.g. leaves of the import graph) back into base 3. Examine the modules remaining in ghc-internal, refactor as necessary to facilitate further moves 4. Go to (2) iterate until the cost/benefit of further moves is insufficient to justify continuing 5. Rename the modules moved into ghc-internal to ensure that they don't overlap with those in base 6. For each module moved into ghc-internal, add a shim module to base with the declarations which should be exposed and any requisite Haddocks (thus guaranteeing that base will be insulated from changes in the export lists of modules in ghc-internal Here I am using the [Move-Incrementally] approach, which is empirically the least painful of the unpleasant options above Bumps haddock submodule. Metric Decrease: haddock.Cabal haddock.base Metric Increase: MultiComponentModulesRecomp T16875 size_hello_artifact - - - - - e8fb2451 by Vladislav Zavialov at 2024-02-08T00:36:36-05:00 Haddock comments on infix constructors (#24221) Rewrite the `HasHaddock` instance for `ConDecl GhcPs` to account for infix constructors. This change fixes a Haddock regression (introduced in 19e80b9af252) that affected leading comments on infix data constructor declarations: -- | Docs for infix constructor | Int :* Bool The comment should be associated with the data constructor (:*), not with its left-hand side Int. - - - - - 9060d55b by Ben Gamari at 2024-02-08T00:37:13-05:00 Add os-string as a boot package Introduces `os-string` submodule. This will be necessary for `filepath-1.5`. - - - - - 9d65235a by Ben Gamari at 2024-02-08T00:37:13-05:00 gitignore: Ignore .hadrian_ghci_multi/ - - - - - d7ee12ea by Ben Gamari at 2024-02-08T00:37:13-05:00 hadrian: Set -this-package-name When constructing the GHC flags for a package Hadrian must take care to set `-this-package-name` in addition to `-this-unit-id`. This hasn't broken until now as we have not had any uses of qualified package imports. However, this will change with `filepath-1.5` and the corresponding `unix` bump, breaking `hadrian/multi-ghci`. - - - - - f2dffd2e by Ben Gamari at 2024-02-08T00:37:13-05:00 Bump filepath to 1.5.0.0 Required bumps of the following submodules: * `directory` * `filepath` * `haskeline` * `process` * `unix` * `hsc2hs` * `Win32` * `semaphore-compat` and the addition of `os-string` as a boot package. - - - - - ab533e71 by Matthew Pickering at 2024-02-08T00:37:50-05:00 Use specific clang assembler when compiling with -fllvm There are situations where LLVM will produce assembly which older gcc toolchains can't handle. For example on Deb10, it seems that LLVM >= 13 produces assembly which the default gcc doesn't support. A more robust solution in the long term is to require a specific LLVM compatible assembler when using -fllvm. Fixes #16354 - - - - - c32b6426 by Matthew Pickering at 2024-02-08T00:37:50-05:00 Update CI images with LLVM 15, ghc-9.6.4 and cabal-install-3.10.2.0 - - - - - 5fcd58be by Matthew Pickering at 2024-02-08T00:37:50-05:00 Update bootstrap plans for 9.4.8 and 9.6.4 - - - - - 707a32f5 by Matthew Pickering at 2024-02-08T00:37:50-05:00 Add alpine 3_18 release job This is mainly experimental and future proofing to enable a smooth transition to newer alpine releases once 3_12 is too old. - - - - - c37931b3 by John Ericson at 2024-02-08T06:39:05-05:00 Generate LLVM min/max bound policy via Hadrian Per #23966, I want the top-level configure to only generate configuration data for Hadrian, not do any "real" tasks on its own. This is part of that effort --- one less file generated by it. (It is still done with a `.in` file, so in a future world non-Hadrian also can easily create this file.) Split modules: - GHC.CmmToLlvm.Config - GHC.CmmToLlvm.Version - GHC.CmmToLlvm.Version.Bounds - GHC.CmmToLlvm.Version.Type This also means we can get rid of the silly `unused.h` introduced in !6803 / 7dfcab2f4bcb7206174ea48857df1883d05e97a2 as temporary kludge. Part of #23966 - - - - - 9f987235 by Apoorv Ingle at 2024-02-08T06:39:42-05:00 Enable mdo statements to use HsExpansions Fixes: #24411 Added test T24411 for regression - - - - - f8429266 by Jade at 2024-02-08T14:56:50+01:00 Adjust test for ghc MR !10993 - - - - - 762b2120 by Jade at 2024-02-08T15:17:15+00:00 Improve Monad, Functor & Applicative docs This patch aims to improve the documentation of Functor, Applicative, Monad and related symbols. The main goal is to make it more consistent and make accessible. See also: !10979 (closed) and !10985 (closed) Ticket #17929 Updates haddock submodule - - - - - 151770ca by Josh Meredith at 2024-02-10T14:28:15-05:00 JavaScript codegen: Use GHC's tag inference where JS backend-specific evaluation inference was previously used (#24309) - - - - - 2e880635 by Zubin Duggal at 2024-02-10T14:28:51-05:00 ci: Allow release-hackage-lint to fail Otherwise it blocks the ghcup metadata pipeline from running. - - - - - b0293f78 by Matthew Pickering at 2024-02-10T14:29:28-05:00 rts: eras profiling mode The eras profiling mode is useful for tracking the life-time of closures. When a closure is written, the current era is recorded in the profiling header. This records the era in which the closure was created. * Enable with -he * User mode: Use functions ghc-experimental module GHC.Profiling.Eras to modify the era * Automatically: --automatic-era-increment, increases the user era on major collections * The first era is era 1 * -he<era> can be used with other profiling modes to select a specific era If you just want to record the era but not to perform heap profiling you can use `-he --no-automatic-heap-samples`. https://well-typed.com/blog/2024/01/ghc-eras-profiling/ Fixes #24332 - - - - - be674a2c by Jade at 2024-02-10T14:30:04-05:00 Adjust error message for trailing whitespace in as-pattern. Fixes #22524 - - - - - 53ef83f9 by doyougnu at 2024-02-10T14:30:47-05:00 gitlab: js: add codeowners Fixes: - #24409 Follow on from: - #21078 and MR !9133 - When we added the JS backend this was forgotten. This patch adds the rightful codeowners. - - - - - 8bbe12f2 by Matthew Pickering at 2024-02-10T14:31:23-05:00 Bump CI images so that alpine3_18 image includes clang15 The only changes here are that clang15 is now installed on the alpine-3_18 image. - - - - - df9fd9f7 by Sylvain Henry at 2024-02-12T12:18:42-05:00 JS: handle stored null StablePtr Some Haskell codes unsafely cast StablePtr into ptr to compare against NULL. E.g. in direct-sqlite: if castStablePtrToPtr aggStPtr /= nullPtr then where `aggStPtr` is read (`peek`) from zeroed memory initially. We fix this by giving these StablePtr the same representation as other null pointers. It's safe because StablePtr at offset 0 is unused (for this exact reason). - - - - - 55346ede by Sylvain Henry at 2024-02-12T12:18:42-05:00 JS: disable MergeObjsMode test This isn't implemented for JS backend objects. - - - - - aef587f6 by Sylvain Henry at 2024-02-12T12:18:42-05:00 JS: add support for linking C sources Support linking C sources with JS output of the JavaScript backend. See the added documentation in the users guide. The implementation simply extends the JS linker to use the objects (.o) that were already produced by the emcc compiler and which were filtered out previously. I've also added some options to control the link with C functions (see the documentation about pragmas). With this change I've successfully compiled the direct-sqlite package which embeds the sqlite.c database code. Some wrappers are still required (see the documentation about wrappers) but everything generic enough to be reused for other libraries have been integrated into rts/js/mem.js. - - - - - b71b392f by Sylvain Henry at 2024-02-12T12:18:42-05:00 JS: avoid EMCC logging spurious failure emcc would sometime output messages like: cache:INFO: generating system asset: symbol_lists/424b44514e43d789148e69e4e7d1c7fdc0350b79.json... (this will be cached in "/emsdk/upstream/emscripten/cache/symbol_lists/424b44514e43d789148e69e4e7d1c7fdc0350b79.json" for subsequent builds) cache:INFO: - ok Cf https://github.com/emscripten-core/emscripten/issues/18607 This breaks our tests matching the stderr output. We avoid this by setting EMCC_LOGGING=0 - - - - - ff2c0cc9 by Simon Peyton Jones at 2024-02-12T12:19:17-05:00 Remove a dead comment Just remove an out of date block of commented-out code, and tidy up the relevant Notes. See #8317. - - - - - bedb4f0d by Teo Camarasu at 2024-02-12T18:50:33-05:00 nonmoving: Add support for heap profiling Add support for heap profiling while using the nonmoving collector. We greatly simply the implementation by disabling concurrent collection for GCs when heap profiling is enabled. This entails that the marked objects on the nonmoving heap are exactly the live objects. Note that we match the behaviour for live bytes accounting by taking the size of objects on the nonmoving heap to be that of the segment's block rather than the object itself. Resolves #22221 - - - - - d0d5acb5 by Teo Camarasu at 2024-02-12T18:51:09-05:00 doc: Add requires prof annotation to options that require it Resolves #24421 - - - - - 6d1e2386 by Alan Zimmerman at 2024-02-13T22:00:28+03:00 EPA: Match changes to HsParTy and HsFunTy - - - - - 57bb8c92 by Cheng Shao at 2024-02-13T14:07:49-05:00 deriveConstants: add needed constants for wasm backend This commit adds needed constants to deriveConstants. They are used by RTS code in the wasm backend to support the JSFFI logic. - - - - - 615eb855 by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: make genSym use C-based atomic increment on non-JS 32-bit platforms The pure Haskell implementation causes i386 regression in unrelated work that can be fixed by using C-based atomic increment, see added comment for details. - - - - - a9918891 by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: allow JSFFI for wasm32 This commit allows the javascript calling convention to be used when the target platform is wasm32. - - - - - 8771a53b by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: allow boxed JSVal as a foreign type This commit allows the boxed JSVal type to be used as a foreign argument/result type. - - - - - 053c92b3 by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: ensure ctors have the right priority on wasm32 This commit fixes the priorities of ctors generated by GHC codegen on wasm32, see the referred note for details. - - - - - b7942e0a by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: add JSFFI desugar logic for wasm32 This commit adds JSFFI desugar logic for the wasm backend. - - - - - 2c1dca76 by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: add JavaScriptFFI to supported extension list on wasm32 This commit adds JavaScriptFFI as a supported extension when the target platform is wasm32. - - - - - 9ad0e2b4 by Cheng Shao at 2024-02-13T14:07:49-05:00 rts/ghc-internal: add JSFFI support logic for wasm32 This commit adds rts/ghc-internal logic to support the wasm backend's JSFFI functionality. - - - - - e9ebea66 by Cheng Shao at 2024-02-13T14:07:49-05:00 ghc-internal: fix threadDelay for wasm in browsers This commit fixes broken threadDelay for wasm when it runs in browsers, see added note for detailed explanation. - - - - - f85f3fdb by Cheng Shao at 2024-02-13T14:07:49-05:00 utils: add JSFFI utility code This commit adds JavaScript util code to utils to support the wasm backend's JSFFI functionality: - jsffi/post-link.mjs, a post-linker to process the linked wasm module and emit a small complement JavaScript ESM module to be used with it at runtime - jsffi/prelude.js, a tiny bit of prelude code as the JavaScript side of runtime logic - jsffi/test-runner.mjs, run the jsffi test cases Co-authored-by: amesgen <amesgen at amesgen.de> - - - - - 77e91500 by Cheng Shao at 2024-02-13T14:07:49-05:00 hadrian: distribute jsbits needed for wasm backend's JSFFI support The post-linker.mjs/prelude.js files are now distributed in the bindist libdir, so when using the wasm backend's JSFFI feature, the user wouldn't need to fetch them from a ghc checkout manually. - - - - - c47ba1c3 by Cheng Shao at 2024-02-13T14:07:49-05:00 testsuite: add opts.target_wrapper This commit adds opts.target_wrapper which allows overriding the target wrapper on a per test case basis when testing a cross target. This is used when testing the wasm backend's JSFFI functionality; the rest of the cases are tested using wasmtime, though the jsffi cases are tested using the node.js based test runner. - - - - - 8e048675 by Cheng Shao at 2024-02-13T14:07:49-05:00 testsuite: T22774 should work for wasm JSFFI T22774 works since the wasm backend now supports the JSFFI feature. - - - - - 1d07f9a6 by Cheng Shao at 2024-02-13T14:07:49-05:00 testsuite: add JSFFI test cases for wasm backend This commit adds a few test cases for the wasm backend's JSFFI functionality, as well as a simple README to instruct future contributors to add new test cases. - - - - - b8997080 by Cheng Shao at 2024-02-13T14:07:49-05:00 docs: add documentation for wasm backend JSFFI This commit adds changelog and user facing documentation for the wasm backend's JSFFI feature. - - - - - ffeb000d by David Binder at 2024-02-13T14:08:30-05:00 Add tests from libraries/process/tests and libraries/Win32/tests to GHC These tests were previously part of the libraries, which themselves are submodules of the GHC repository. This commit moves the tests directly to the GHC repository. - - - - - 5a932cf2 by David Binder at 2024-02-13T14:08:30-05:00 Do not execute win32 tests on non-windows runners - - - - - 500d8cb8 by Jade at 2024-02-13T14:09:07-05:00 prevent GHCi (and runghc) from suggesting other symbols when not finding main Fixes: #23996 - - - - - b19ec331 by Cheng Shao at 2024-02-13T14:09:46-05:00 rts: update xxHash to v0.8.2 - - - - - 4a97bdb8 by Cheng Shao at 2024-02-13T14:09:46-05:00 rts: use XXH3_64bits hash on all 64-bit platforms This commit enables XXH3_64bits hash to be used on all 64-bit platforms. Previously it was only enabled on x86_64, so platforms like aarch64 silently falls back to using XXH32 which degrades the hashing function quality. - - - - - ee01de7d by Cheng Shao at 2024-02-13T14:09:46-05:00 rts: define XXH_INLINE_ALL This commit cleans up how we include the xxhash.h header and only define XXH_INLINE_ALL, which is sufficient to inline the xxHash functions without symbol collision. - - - - - 0e01e1db by Alan Zimmerman at 2024-02-14T02:13:22-05:00 EPA: Move EpAnn out of extension points Leaving a few that are too tricky, maybe some other time. Also - remove some unneeded helpers from Parser.y - reduce allocations with strictness annotations Updates haddock submodule Metric Decrease: parsing001 - - - - - de589554 by Andreas Klebinger at 2024-02-14T02:13:59-05:00 Fix ffi callbacks with >6 args and non-64bit args. Check for ptr/int arguments rather than 64-bit width arguments when counting integer register arguments. The old approach broke when we stopped using exclusively W64-sized types to represent sub-word sized integers. Fixes #24314 - - - - - 9c588f19 by Fendor at 2024-02-14T11:05:36+01:00 Adapt to GHC giving better Name's for linking - - - - - 325b7613 by Ben Gamari at 2024-02-14T14:27:45-05:00 rts/EventLog: Place eliminate duplicate strlens Previously many of the `post*` implementations would first compute the length of the event's strings in order to determine the event length. Later we would then end up computing the length yet again in `postString`. Now we instead pass the string length to `postStringLen`, avoiding the repeated work. - - - - - 8aafa51c by Ben Gamari at 2024-02-14T14:27:46-05:00 rts/eventlog: Place upper bound on IPE string field lengths The strings in IPE events may be of unbounded length. Limit the lengths of these fields to 64k characters to ensure that we don't exceed the maximum event length. - - - - - 0e60d52c by Zubin Duggal at 2024-02-14T14:27:46-05:00 rts: drop unused postString function - - - - - d8d1333a by Cheng Shao at 2024-02-14T14:28:23-05:00 compiler/rts: fix wasm unreg regression This commit fixes two wasm unreg regressions caught by a nightly pipeline: - Unknown stg_scheduler_loopzh symbol when compiling scheduler.cmm - Invalid _hs_constructor(101) function name when handling ctor - - - - - 264a4fa9 by Owen Shepherd at 2024-02-15T09:41:06-05:00 feat: Add sortOn to Data.List.NonEmpty Adds `sortOn` to `Data.List.NonEmpty`, and adds comments describing when to use it, compared to `sortWith` or `sortBy . comparing`. The aim is to smooth out the API between `Data.List`, and `Data.List.NonEmpty`. This change has been discussed in the [clc issue](https://github.com/haskell/core-libraries-committee/issues/227). - - - - - b57200de by Fendor at 2024-02-15T09:41:47-05:00 Prefer RdrName over OccName for looking up locations in doc renaming step Looking up by OccName only does not take into account when functions are only imported in a qualified way. Fixes issue #24294 Bump haddock submodule to include regression test - - - - - 8ad02724 by Luite Stegeman at 2024-02-15T17:33:32-05:00 JS: add simple optimizer The simple optimizer reduces the size of the code generated by the JavaScript backend without the complexity and performance penalty of the optimizer in GHCJS. Also see #22736 Metric Decrease: libdir size_hello_artifact - - - - - 20769b36 by Matthew Pickering at 2024-02-15T17:34:07-05:00 base: Expose `--no-automatic-time-samples` in `GHC.RTS.Flags` API This patch builds on 5077416e12cf480fb2048928aa51fa4c8fc22cf1 and modifies the base API to reflect the new RTS flag. CLC proposal #243 - https://github.com/haskell/core-libraries-committee/issues/243 Fixes #24337 - - - - - 778e1db3 by Andrei Borzenkov at 2024-02-16T16:12:07+03:00 Namespace specifiers for fixity signatures - - - - - 08031ada by Teo Camarasu at 2024-02-16T13:37:00-05:00 base: export System.Mem.performBlockingMajorGC The corresponding C function was introduced in ba73a807edbb444c49e0cf21ab2ce89226a77f2e. As part of #22264. Resolves #24228 The CLC proposal was disccused at: https://github.com/haskell/core-libraries-committee/issues/230 Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 1f534c2e by Florian Weimer at 2024-02-16T13:37:42-05:00 Fix C output for modern C initiative GCC 14 on aarch64 rejects the C code written by GHC with this kind of error: error: assignment to ‘ffi_arg’ {aka ‘long unsigned int’} from ‘HsPtr’ {aka ‘void *’} makes integer from pointer without a cast [-Wint-conversion] 68 | *(ffi_arg*)resp = cret; | ^ Add the correct cast. For more information on this see: https://fedoraproject.org/wiki/Changes/PortingToModernC Tested-by: Richard W.M. Jones <rjones at redhat.com> - - - - - 5d3f7862 by Matthew Craven at 2024-02-16T13:38:18-05:00 Bump bytestring submodule to 0.12.1.0 - - - - - 902ebcc2 by Ian-Woo Kim at 2024-02-17T06:01:01-05:00 Add missing BCO handling in scavenge_one. - - - - - 97d26206 by Sylvain Henry at 2024-02-17T06:01:44-05:00 Make cast between words and floats real primops (#24331) First step towards fixing #24331. Replace foreign prim imports with real primops. - - - - - a40e4781 by Sylvain Henry at 2024-02-17T06:01:44-05:00 Perf: add constant folding for bitcast between float and word (#24331) - - - - - 5fd2c00f by Sylvain Henry at 2024-02-17T06:01:44-05:00 Perf: replace stack checks with assertions in casting primops There are RESERVED_STACK_WORDS free words (currently 21) on the stack, so omit the checks. Suggested by Cheng Shao. - - - - - 401dfe7b by Sylvain Henry at 2024-02-17T06:01:44-05:00 Reexport primops from GHC.Float + add deprecation - - - - - 4ab48edb by Ben Gamari at 2024-02-17T06:02:21-05:00 rts/Hash: Don't iterate over chunks if we don't need to free data When freeing a `HashTable` there is no reason to walk over the hash list before freeing it if the user has not given us a `dataFreeFun`. Noticed while looking at #24410. - - - - - bd5a1f91 by Cheng Shao at 2024-02-17T06:03:00-05:00 compiler: add SEQ_CST fence support In addition to existing Acquire/Release fences, this commit adds SEQ_CST fence support to GHC, allowing Cmm code to explicitly emit a fence that enforces total memory ordering. The following logic is added: - The MO_SeqCstFence callish MachOp - The %prim fence_seq_cst() Cmm syntax and the SEQ_CST_FENCE macro in Cmm.h - MO_SeqCstFence lowering logic in every single GHC codegen backend - - - - - 2ce2a493 by Cheng Shao at 2024-02-17T06:03:38-05:00 testsuite: fix hs_try_putmvar002 for targets without pthread.h hs_try_putmvar002 includes pthread.h and doesn't work on targets without this header (e.g. wasm32). It doesn't need to include this header at all. This was previously unnoticed by wasm CI, though recent toolchain upgrade brought in upstream changes that completely removes pthread.h in the single-threaded wasm32-wasi sysroot, therefore we need to handle that change. - - - - - 1fb3974e by Cheng Shao at 2024-02-17T06:03:38-05:00 ci: bump ci-images to use updated wasm image This commit bumps our ci-images revision to use updated wasm image. - - - - - 56e3f097 by Andrew Lelechenko at 2024-02-17T06:04:13-05:00 Bump submodule text to 2.1.1 T17123 allocates less because of improvements to Data.Text.concat in 1a6a06a. Metric Decrease: T17123 - - - - - a7569495 by Cheng Shao at 2024-02-17T06:04:51-05:00 rts: remove redundant rCCCS initialization This commit removes the redundant logic of initializing each Capability's rCCCS to CCS_SYSTEM in initProfiling(). Before initProfiling() is called during RTS startup, each Capability's rCCCS has already been assigned CCS_SYSTEM when they're first initialized. - - - - - 7a0293cc by Ben Gamari at 2024-02-19T07:11:00-05:00 Drop dependence on `touch` This drops GHC's dependence on the `touch` program, instead implementing it within GHC. This eliminates an external dependency and means that we have one fewer program to keep track of in the `configure` script - - - - - 0dbd729e by Andrei Borzenkov at 2024-02-19T07:11:37-05:00 Parser, renamer, type checker for @a-binders (#17594) GHC Proposal 448 introduces binders for invisible type arguments (@a-binders) in various contexts. This patch implements @-binders in lambda patterns and function equations: {-# LANGUAGE TypeAbstractions #-} id1 :: a -> a id1 @t x = x :: t -- @t-binder on the LHS of a function equation higherRank :: (forall a. (Num a, Bounded a) => a -> a) -> (Int8, Int16) higherRank f = (f 42, f 42) ex :: (Int8, Int16) ex = higherRank (\ @a x -> maxBound @a - x ) -- @a-binder in a lambda pattern in an argument -- to a higher-order function Syntax ------ To represent those @-binders in the AST, the list of patterns in Match now uses ArgPat instead of Pat: data Match p body = Match { ... - m_pats :: [LPat p], + m_pats :: [LArgPat p], ... } + data ArgPat pass + = VisPat (XVisPat pass) (LPat pass) + | InvisPat (XInvisPat pass) (HsTyPat (NoGhcTc pass)) + | XArgPat !(XXArgPat pass) The VisPat constructor represents patterns for visible arguments, which include ordinary value-level arguments and required type arguments (neither is prefixed with a @), while InvisPat represents invisible type arguments (prefixed with a @). Parser ------ In the grammar (Parser.y), the lambda and lambda-cases productions of aexp non-terminal were updated to accept argpats instead of apats: aexp : ... - | '\\' apats '->' exp + | '\\' argpats '->' exp ... - | '\\' 'lcases' altslist(apats) + | '\\' 'lcases' altslist(argpats) ... + argpat : apat + | PREFIX_AT atype Function left-hand sides did not require any changes to the grammar, as they were already parsed with productions capable of parsing @-binders. Those binders were being rejected in post-processing (isFunLhs), and now we accept them. In Parser.PostProcess, patterns are constructed with the help of PatBuilder, which is used as an intermediate data structure when disambiguating between FunBind and PatBind. In this patch we define ArgPatBuilder to accompany PatBuilder. ArgPatBuilder is a short-lived data structure produced in isFunLhs and consumed in checkFunBind. Renamer ------- Renaming of @-binders builds upon prior work on type patterns, implemented in 2afbddb0f24, which guarantees proper scoping and shadowing behavior of bound type variables. This patch merely defines rnLArgPatsAndThen to process a mix of visible and invisible patterns: + rnLArgPatsAndThen :: NameMaker -> [LArgPat GhcPs] -> CpsRn [LArgPat GhcRn] + rnLArgPatsAndThen mk = mapM (wrapSrcSpanCps rnArgPatAndThen) where + rnArgPatAndThen (VisPat x p) = ... rnLPatAndThen ... + rnArgPatAndThen (InvisPat _ tp) = ... rnHsTyPat ... Common logic between rnArgPats and rnPats is factored out into the rn_pats_general helper. Type checker ------------ Type-checking of @-binders builds upon prior work on lazy skolemisation, implemented in f5d3e03c56f. This patch extends tcMatchPats to handle @-binders. Now it takes and returns a list of LArgPat rather than LPat: tcMatchPats :: ... - -> [LPat GhcRn] + -> [LArgPat GhcRn] ... - -> TcM ([LPat GhcTc], a) + -> TcM ([LArgPat GhcTc], a) Invisible binders in the Match are matched up with invisible (Specified) foralls in the type. This is done with a new clause in the `loop` worker of tcMatchPats: loop :: [LArgPat GhcRn] -> [ExpPatType] -> TcM ([LArgPat GhcTc], a) loop (L l apat : pats) (ExpForAllPatTy (Bndr tv vis) : pat_tys) ... -- NEW CLAUSE: | InvisPat _ tp <- apat, isSpecifiedForAllTyFlag vis = ... In addition to that, tcMatchPats no longer discards type patterns. This is done by filterOutErasedPats in the desugarer instead. x86_64-linux-deb10-validate+debug_info Metric Increase: MultiLayerModulesTH_OneShot - - - - - 486979b0 by Jade at 2024-02-19T07:12:13-05:00 Add specialized sconcat implementation for Data.Monoid.First and Data.Semigroup.First Approved CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/246 Fixes: #24346 - - - - - 17e309d2 by John Ericson at 2024-02-19T07:12:49-05:00 Fix reST in users guide It appears that aef587f65de642142c1dcba0335a301711aab951 wasn't valid syntax. - - - - - 35b0ad90 by Brandon Chinn at 2024-02-19T07:13:25-05:00 Fix searching for errors in sphinx build - - - - - 4696b966 by Cheng Shao at 2024-02-19T07:14:02-05:00 hadrian: fix wasm backend post linker script permissions The post-link.mjs script was incorrectly copied and installed as a regular data file without executable permission, this commit fixes it. - - - - - a6142e0c by Cheng Shao at 2024-02-19T07:14:40-05:00 testsuite: mark T23540 as fragile on i386 See #24449 for details. - - - - - 249caf0d by Matthew Craven at 2024-02-19T20:36:09-05:00 Add @since annotation to Data.Data.mkConstrTag - - - - - cdd939e7 by Jade at 2024-02-19T20:36:46-05:00 Enhance documentation of Data.Complex - - - - - d04f384f by Ben Gamari at 2024-02-21T04:59:23-05:00 hadrian/bindist: Ensure that phony rules are marked as such Otherwise make may not run the rule if file with the same name as the rule happens to exist. - - - - - efcbad2d by Ben Gamari at 2024-02-21T04:59:23-05:00 hadrian: Generate HSC2HS_EXTRAS variable in bindist installation We must generate the hsc2hs wrapper at bindist installation time since it must contain `--lflag` and `--cflag` arguments which depend upon the installation path. The solution here is to substitute these variables in the configure script (see mk/hsc2hs.in). This is then copied over a dummy wrapper in the install rules. Fixes #24050. - - - - - c540559c by Matthew Pickering at 2024-02-21T04:59:23-05:00 ci: Show --info for installed compiler - - - - - ab9281a2 by Matthew Pickering at 2024-02-21T04:59:23-05:00 configure: Correctly set --target flag for linker opts Previously we were trying to use the FP_CC_SUPPORTS_TARGET with 4 arguments, when it only takes 3 arguments. Instead we need to use the `FP_PROG_CC_LINKER_TARGET` function in order to set the linker flags. Actually fixes #24414 - - - - - 9460d504 by Rodrigo Mesquita at 2024-02-21T04:59:59-05:00 configure: Do not override existing linker flags in FP_LD_NO_FIXUP_CHAINS - - - - - 77629e76 by Andrei Borzenkov at 2024-02-21T05:00:35-05:00 Namespacing for fixity signatures (#14032) Namespace specifiers were added to syntax of fixity signatures: - sigdecl ::= infix prec ops | ... + sigdecl ::= infix prec namespace_spec ops | ... To preserve namespace during renaming MiniFixityEnv type now has separate FastStringEnv fields for names that should be on the term level and for name that should be on the type level. makeMiniFixityEnv function was changed to fill MiniFixityEnv in the right way: - signatures without namespace specifiers fill both fields - signatures with 'data' specifier fill data field only - signatures with 'type' specifier fill type field only Was added helper function lookupMiniFixityEnv that takes care about looking for a name in an appropriate namespace. Updates haddock submodule. Metric Decrease: MultiLayerModulesTH_OneShot - - - - - 84357d11 by Teo Camarasu at 2024-02-21T05:01:11-05:00 rts: only collect live words in nonmoving census when non-concurrent This avoids segfaults when the mutator modifies closures as we examine them. Resolves #24393 - - - - - 9ca56dd3 by Ian-Woo Kim at 2024-02-21T05:01:53-05:00 mutex wrap in refreshProfilingCCSs - - - - - 1387966a by Cheng Shao at 2024-02-21T05:02:32-05:00 rts: remove unused HAVE_C11_ATOMICS macro This commit removes the unused HAVE_C11_ATOMICS macro. We used to have a few places that have fallback paths when HAVE_C11_ATOMICS is not defined, but that is completely redundant, since the FP_CC_SUPPORTS__ATOMICS configure check will fail when the C compiler doesn't support C11 style atomics. There are also many places (e.g. in unreg backend, SMP.h, library cbits, etc) where we unconditionally use C11 style atomics anyway which work in even CentOS 7 (gcc 4.8), the oldest distro we test in our CI, so there's no value in keeping HAVE_C11_ATOMICS. - - - - - 0f40d68f by Andreas Klebinger at 2024-02-21T05:03:09-05:00 RTS: -Ds - make sure incall is non-zero before dereferencing it. Fixes #24445 - - - - - e5886de5 by Ben Gamari at 2024-02-21T05:03:44-05:00 rts/AdjustorPool: Use ExecPage abstraction This is just a minor cleanup I found while reviewing the implementation. - - - - - 826c5b47 by Torsten Schmits at 2024-02-21T13:17:05+01:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 09941666 by Adam Gundry at 2024-02-21T13:53:12+00:00 Define GHC2024 language edition (#24320) See https://github.com/ghc-proposals/ghc-proposals/pull/613. Also fixes #24343 and improves the documentation of language editions. Co-authored-by: Joachim Breitner <mail at joachim-breitner.de> - - - - - 2cff14d5 by Ben Gamari at 2024-02-22T09:35:56-05:00 Bump bounds - - - - - f49376b3 by Ben Gamari at 2024-02-22T09:35:56-05:00 Allow `@since` annotations in export lists Here we extend Haddock to admit `@since` annotations in export lists. These can be attached to most export list items (although not subordinate lists). These annotations supercede the declaration's `@since` annotation in produced Haddocks. - - - - - b5aa93df by Ben Gamari at 2024-02-22T12:09:06-05:00 Allow package-qualified @since declarations - - - - - 8f5957f2 by Ben Gamari at 2024-02-22T13:55:19-05:00 Documentation changes from ghc-internal restructuring Previously many declarations (e.g. `Int`) were declared to have a "home" in `Prelude`. However, now Haddock instead chooses to put these in more specific homes (e.g. `Data.Int`). Given that the "home" decision is driven by heuristics and in general these changes seem quite reasonable I am accepting them: * `Int` moved from `Prelude` to `Data.Int` * `(~)` moved from `Prelude` to `Data.Type.Equality` * `Type` moved from `GHC.Types` to `Data.Kind` * `Maybe` moved from `Prelude` to `Data.Maybe` * `Bool` moved from `Prelude` to `Data.Bool` * `Ordering` moved from `Prelude` to `Data.Ord` As well, more identifiers are now hyperlinked; it's not immediately clear *why*, but it is an improvement nevertheless. - - - - - ec33fec3 by Ben Gamari at 2024-02-22T20:36:24-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 5121a4ed by Ben Gamari at 2024-02-23T06:40:55-05:00 Allow docstrings after exports Here we extend the parser and AST to preserve docstrings following export items. We then extend Haddock to parse `@since` annotations in such docstrings, allowing changes in export structure to be properly documented. Bumps haddock submodule. - - - - - 30cfd251 by Torsten Schmits at 2024-02-24T13:00:42-05:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 0eb2265d by Hécate Moonlight at 2024-02-24T16:02:16-05:00 Improve the synopsis and description of base - - - - - 2e36f5d2 by Jade at 2024-02-24T16:02:51-05:00 Error Messages: Properly align cyclic module error Fixes: #24476 - - - - - bbfb051c by Ben Gamari at 2024-02-24T19:10:23-05:00 Allow docstrings after exports Here we extend the parser and AST to preserve docstrings following export items. We then extend Haddock to parse `@since` annotations in such docstrings, allowing changes in export structure to be properly documented. - - - - - d8d6ad8c by Ben Gamari at 2024-02-24T19:10:23-05:00 ghc-internal: Move modules into GHC.Internal.* namespace Bumps haddock submodule due to testsuite output changes. - - - - - a82af7cd by Ben Gamari at 2024-02-24T19:10:23-05:00 ghc-internal: Rewrite `@since ` to `@since base-` These will be incrementally moved to the export sites in `base` where possible. - - - - - ca3836e1 by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Migrate Haddock `not-home` pragmas from `ghc-internal` This ensures that we do not use `base` stub modules as declarations' homes when not appropriate. - - - - - c8cf3e26 by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Partially freeze exports of GHC.Base Sadly there are still a few module reexports. However, at least we have decoupled from the exports of `GHC.Internal.Base`. - - - - - 272573c6 by Ben Gamari at 2024-02-24T19:10:23-05:00 Move Haddock named chunks - - - - - 2d8a881d by Ben Gamari at 2024-02-24T19:10:23-05:00 Drop GHC.Internal.Data.Int - - - - - 55c4c385 by Ben Gamari at 2024-02-24T19:10:23-05:00 compiler: Fix mention to `GHC....` modules in wasm desugaring Really, these references should be via known-key names anyways. I have fixed the proximate issue here but have opened #24472 to track the additional needed refactoring. - - - - - 64150911 by Ben Gamari at 2024-02-24T19:10:23-05:00 Accept performance shifts from ghc-internal restructure As expected, Haddock now does more work. Less expected is that some other testcases actually get faster, presumably due to less interface file loading. As well, the size_hello_artifact test regressed a bit when debug information is enabled due to debug information for the new stub symbols. Metric Decrease: T12227 T13056 Metric Increase: haddock.Cabal haddock.base MultiLayerModulesTH_OneShot size_hello_artifact - - - - - 317a915b by Ben Gamari at 2024-02-24T19:10:23-05:00 Expose GHC.Wasm.Prim from ghc-experimental Previously this was only exposed from `ghc-internal` which violates our agreement that users shall not rely on things exposed from that package. Fixes #24479. - - - - - 3bbd2bf2 by Ben Gamari at 2024-02-24T19:10:23-05:00 compiler/tc: Small optimisation of evCallStack Don't lookupIds unless we actually need them. - - - - - 3e5c9e3c by Ben Gamari at 2024-02-24T19:10:23-05:00 compiler/tc: Use toException instead of SomeException - - - - - 125714a6 by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Factor out errorBelch This was useful when debugging - - - - - 3d6aae7c by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Clean up imports of GHC.Stack.CloneStack - - - - - 6900306e by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Move PrimMVar to GHC.Internal.MVar - - - - - 28f8a148 by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Move prettyCallStack to GHC.Internal.Stack - - - - - 4892de47 by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Explicit dependency to workaround #24436 Currently `ghc -M` fails to account for `.hs-boot` files correctly, leading to issues with cross-package one-shot builds failing. This currently manifests in `GHC.Exception` due to the boot file for `GHC.Internal.Stack`. Work around this by adding an explicit `import`, ensuring that `GHC.Internal.Stack` is built before `GHC.Exception`. See #24436. - - - - - 294c93a5 by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Use displayException in top-level exception handler Happily this also allows us to eliminate a special case for Deadlock exceptions. Implements [CLC #198](https://github.com/haskell/core-libraries-committee/issues/198). - - - - - 732db81d by Ben Gamari at 2024-02-24T19:12:18-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - cf756a25 by Ben Gamari at 2024-02-24T22:11:53-05:00 rts: Fix symbol references in Wasm RTS - - - - - 4e4d47a0 by Jade at 2024-02-26T15:17:20-05:00 GHCi: Improve response to unloading, loading and reloading modules Fixes #13869 - - - - - f3de8a3c by Zubin Duggal at 2024-02-26T15:17:57-05:00 rel-eng/fetch-gitlab.py: Fix name of aarch64 alpine 3_18 release job - - - - - c71bfdff by Cheng Shao at 2024-02-26T15:18:35-05:00 hadrian/hie-bios: pass -j to hadrian This commit passes -j to hadrian in the hadrian/hie-bios scripts. When the user starts HLS in a fresh clone that has just been configured, it takes quite a while for hie-bios to pick up the ghc flags and start actual indexing, due to the fact that the hadrian build step defaulted to -j1, so -j speeds things up and improve HLS user experience in GHC. Also add -j flag to .ghcid to speed up ghcid, and sets the Windows build root to .hie-bios which also works and unifies with other platforms, the previous build root _hie-bios was missing from .gitignore anyway. - - - - - 50bfdb46 by Cheng Shao at 2024-02-26T15:18:35-05:00 ci: enable parallelism in hadrian/ghci scripts This commit enables parallelism when the hadrian/ghci scripts are called in CI. The time bottleneck is in the hadrian build step, but previously the build step wasn't parallelized. - - - - - 61a78231 by Felix Yan at 2024-02-26T15:19:14-05:00 m4: Correctly detect GCC version When calling as `cc`, GCC does not outputs lowercased "gcc" at least in 13.2.1 version here. ``` $ cc --version cc (GCC) 13.2.1 20230801 ... ``` This fails the check and outputs the confusing message: `configure: $CC is not gcc; assuming it's a reasonably new C compiler` This patch makes it check for upper-cased "GCC" too so that it works correctly: ``` checking version of gcc... 13.2.1 ``` - - - - - 001aa539 by Teo Camarasu at 2024-02-27T13:26:46-05:00 Fix formatting in whereFrom docstring Previously it used markdown syntax rather than Haddock syntax for code quotes - - - - - e8034d15 by Teo Camarasu at 2024-02-27T13:26:46-05:00 Move ClosureType type to ghc-internal - Use ClosureType for InfoProv.ipDesc. - Use ClosureType for CloneStack.closureType. - Now ghc-heap re-exports this type from ghc-internal. See the accompanying CLC proposal: https://github.com/haskell/core-libraries-committee/issues/210 Resolves #22600 - - - - - 3da0a551 by Matthew Craven at 2024-02-27T13:27:22-05:00 StgToJS: Simplify ExprInline constructor of ExprResult Its payload was used only for a small optimization in genAlts, avoiding a few assignments for programs of this form: case NormalDataCon arg1 arg2 of x { NormalDataCon x1 x2 -> ... ; } But when compiling with optimizations, this sort of code is generally eliminated by case-of-known-constructor in Core-to-Core. So it doesn't seem worth tracking and cleaning up again in StgToJS. - - - - - 61bc92cc by Cheng Shao at 2024-02-27T16:58:42-05:00 rts: add missing ccs_mutex guard to internal_dlopen See added comment for details. Closes #24423. - - - - - dd29d3b2 by doyougnu at 2024-02-27T16:59:23-05:00 cg: Remove GHC.Cmm.DataFlow.Collections In pursuit of #15560 and #17957 and generally removing redundancy. - - - - - d3a050d2 by Cheng Shao at 2024-02-27T17:00:00-05:00 utils: remove unused lndir from tree Ever since the removal of the make build system, the in tree lndir hasn't been actually built, so this patch removes it. - - - - - 86bf7010 by Ben Gamari at 2024-02-27T19:28:10-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 74b24a9b by Teo Camarasu at 2024-02-28T16:32:58+00:00 rts: avoid checking bdescr of value outside of Haskell heap In nonmovingTidyWeaks we want to check if the key of a weak pointer lives in the non-moving heap. We do this by checking the flags of the block the key lives in. But we need to be careful with values that live outside the Haskell heap, since they will lack a block descriptor and looking for one may lead to a segfault. In this case we should just accept that it isn't on the non-moving heap. Resolves #24492 - - - - - b4cae4ec by Simon Peyton Jones at 2024-02-29T02:10:08-05:00 In mkDataConRep, ensure the in-scope set is right A small change that fixes #24489 - - - - - 3836a110 by Cheng Shao at 2024-02-29T21:25:45-05:00 testsuite: fix T23540 fragility on 32-bit platforms T23540 is fragile on 32-bit platforms. The root cause is usage of `getEvidenceTreesAtPoint`, which internally relies on `Name`'s `Ord` instance, which is indeterministic. The solution is adding a deterministic `Ord` instance for `EvidenceInfo` and sorting the evidence trees before pretty printing. Fixes #24449. - - - - - 960c8d47 by Teo Camarasu at 2024-02-29T21:26:20-05:00 Reduce AtomicModifyIORef increment count This test leads to a lot of contention when N>2 and becomes very slow. Let's reduce the amount of work we do to compensate. Resolves #24490 - - - - - 2e46c8ad by Matthew Pickering at 2024-03-01T05:48:06-05:00 hadrian: Improve parallelism in binary-dist-dir rule I noticed that the "docs" target was needed after the libraries and executables were built. We can improve the parallelism by needing everything at once so that documentation can be built immediately after a library is built for example. - - - - - cb6c11fe by Matthew Pickering at 2024-03-01T05:48:07-05:00 ci: Bump windows and freebsd boot compilers to 9.6.4 We have previously bumped the docker images to use 9.6.4, but neglected to bump the windows images until now. - - - - - 30f06996 by Matthew Pickering at 2024-03-01T05:48:07-05:00 ci: darwin: Update to 9.6.2 for boot compiler 9.6.4 is currently broken due to #24050 Also update to use LLVM-15 rather than LLVM-11, which is out of date. - - - - - d9d69e12 by Matthew Pickering at 2024-03-01T05:48:07-05:00 Bump minimum bootstrap version to 9.6 - - - - - 67ace1c5 by Matthew Pickering at 2024-03-01T05:48:07-05:00 ci: Enable more documentation building Here we enable documentation building on 1. Darwin: The sphinx toolchain was already installed so we enable html and manpages. 2. Rocky8: Full documentation (toolchain already installed) 3. Alpine: Full documetnation (toolchain already installed) 4. Windows: HTML and manpages (toolchain already installed) Fixes #24465 - - - - - 39583c39 by Matthew Pickering at 2024-03-01T05:48:42-05:00 ci: Bump ci-images to allow updated aarch64-alpine image with llvm15 and clang15 - - - - - d91d00fc by Torsten Schmits at 2024-03-01T15:01:50-05:00 Introduce ListTuplePuns extension This implements Proposal 0475, introducing the `ListTuplePuns` extension which is enabled by default. Disabling this extension makes it invalid to refer to list, tuple and sum type constructors by using built-in syntax like `[Int]`, `(Int, Int)`, `(# Int#, Int# #)` or `(# Int | Int #)`. Instead, this syntax exclusively denotes data constructors for use with `DataKinds`. The conventional way of referring to these data constructors by prefixing them with a single quote (`'(Int, Int)`) is now a parser error. Tuple declarations have been moved to `GHC.Tuple.Prim` and the `Solo` data constructor has been renamed to `MkSolo` (in a previous commit). Unboxed tuples and sums now have real source declarations in `GHC.Types`. Unit and solo types for tuples are now called `Unit`, `Unit#`, `Solo` and `Solo#`. Constraint tuples now have the unambiguous type constructors `CTuple<n>` as well as `CUnit` and `CSolo`, defined in `GHC.Classes` like before. A new parser construct has been added for the unboxed sum data constructor declarations. The type families `Tuple`, `Sum#` etc. that were intended to provide nicer syntax have been omitted from this change set due to inference problems, to be implemented at a later time. See the MR discussion for more info. Updates the submodule utils/haddock. Updates the cabal submodule due to new language extension. Metric Increase: haddock.base Metric Decrease: MultiLayerModulesTH_OneShot size_hello_artifact Proposal document: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0475-tuple-syntax.rst Merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/8820 Tracking ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/21294 - - - - - bbdb6286 by Sylvain Henry at 2024-03-01T15:01:50-05:00 JS linker: filter unboxed tuples - - - - - dec6d8d3 by Arnaud Spiwack at 2024-03-01T15:02:30-05:00 Improve error messages coming from non-linear patterns This enriched the `CtOrigin` for non-linear patterns to include data of the pattern that created the constraint (which can be quite useful if it occurs nested in a pattern) as well as an explanation why the pattern is non-restricted in (at least in some cases). - - - - - 6612388e by Arnaud Spiwack at 2024-03-01T15:02:30-05:00 Adjust documentation of linear lets according to committee decision - - - - - 1c064ef1 by Cheng Shao at 2024-03-02T17:11:19-05:00 compiler: start deprecating cmmToRawCmmHook cmmToRawCmmHook was added 4 years ago in d561c8f6244f8280a2483e8753c38e39d34c1f01. Its only user is the Asterius project, which has been archived and deprecated in favor of the ghc wasm backend. This patch starts deprecating cmmToRawCmmHook by placing a DEPRECATED pragma, and actual removal shall happen in a future GHC major release if no issue to oppose the deprecation has been raised in the meantime. - - - - - 9b74845f by Andrew Lelechenko at 2024-03-02T17:11:55-05:00 Data.List.NonEmpty.unzip: use WARNING with category instead of DEPRECATED CLC proposal: https://github.com/haskell/core-libraries-committee/issues/258 - - - - - 61bb5ff6 by Finley McIlwaine at 2024-03-04T09:01:40-08:00 add -fprof-late-overloaded and -fprof-late-overloaded-calls * Refactor late cost centre insertion for extensibility * Add two more late cost centre insertion methods that add SCCs to overloaded top level bindings and call sites with dictionary arguments. * Some tests for the basic functionality of the new insertion methods Resolves: #24500 - - - - - 82ccb801 by Andreas Klebinger at 2024-03-04T19:59:14-05:00 x86-ncg: Fix fma codegen when arguments are globals Fix a bug in the x86 ncg where results would be wrong when the desired output register and one of the input registers were the same global. Also adds a tiny optimization to make use of the memory addressing support when convenient. Fixes #24496 - - - - - 18ad1077 by Matthew Pickering at 2024-03-05T14:22:31-05:00 rel_eng: Update hackage docs upload scripts This adds the upload of ghc-internal and ghc-experimental to our scripts which upload packages to hackage. - - - - - bf47c9ba by Matthew Pickering at 2024-03-05T14:22:31-05:00 docs: Remove stray module comment from GHC.Profiling.Eras - - - - - 37d9b340 by Matthew Pickering at 2024-03-05T14:22:31-05:00 Fix ghc-internal cabal file The file mentioned some artifacts relating to the base library. I have renamed these to the new ghc-internal variants. - - - - - 23f2a478 by Matthew Pickering at 2024-03-05T14:22:31-05:00 Fix haddock source links and hyperlinked source There were a few issues with the hackage links: 1. We were using the package id rather than the package name for the package links. This is fixed by now allowing the template to mention %pkg% or %pkgid% and substituing both appropiatly. 2. The `--haddock-base-url` flag is renamed to `--haddock-for-hackage` as the new base link works on a local or remote hackage server. 3. The "src" path including too much stuff, so cross-package source links were broken as the template was getting double expanded. Fixes #24086 - - - - - 2fa336a9 by Ben Gamari at 2024-03-05T14:23:07-05:00 filepath: Bump submodule to 1.5.2.0 - - - - - 31217944 by Ben Gamari at 2024-03-05T14:23:07-05:00 os-string: Bump submodule to 2.0.2 - - - - - 4074a3f2 by Matthew Pickering at 2024-03-05T21:44:35-05:00 base: Reflect new era profiling RTS flags in GHC.RTS.Flags * -he profiling mode * -he profiling selector * --automatic-era-increment CLC proposal #254 - https://github.com/haskell/core-libraries-committee/issues/254 - - - - - a8c0e31b by Sylvain Henry at 2024-03-05T21:45:14-05:00 JS: faster implementation for some numeric primitives (#23597) Use faster implementations for the following primitives in the JS backend by not using JavaScript's BigInt: - plusInt64 - minusInt64 - minusWord64 - timesWord64 - timesInt64 Co-authored-by: Josh Meredith <joshmeredith2008 at gmail.com> - - - - - 21e3f325 by Cheng Shao at 2024-03-05T21:45:52-05:00 rts: add -xr option to control two step allocator reserved space size This patch adds a -xr RTS option to control the size of virtual memory address space reserved by the two step allocator on a 64-bit platform, see added documentation for explanation. Closes #24498. - - - - - dedcf102 by Cheng Shao at 2024-03-06T13:39:04-05:00 rts: expose HeapAlloc.h as public header This commit exposes HeapAlloc.h as a public header. The intention is to expose HEAP_ALLOCED/HEAP_ALLOCED_GC, so they can be used in assertions in other public headers, and they may also be useful for user code. - - - - - d19441d7 by Cheng Shao at 2024-03-06T13:39:04-05:00 rts: assert pointer is indeed heap allocated in Bdescr() This commit adds an assertion to Bdescr() to assert the pointer is indeed heap allocated. This is useful to rule out RTS bugs that attempt to access non-existent block descriptor of a static closure, #24492 being one such example. - - - - - 9a656a04 by Ben Gamari at 2024-03-06T13:39:39-05:00 ghc-experimental: Add dummy dependencies to work around #23942 This is a temporary measure to improve CI reliability until a proper solution is developed. Works around #23942. - - - - - 1e84b924 by Simon Peyton Jones at 2024-03-06T13:39:39-05:00 Three compile perf improvements with deep nesting These were changes are all triggered by #24471. 1. Make GHC.Core.Opt.SetLevels.lvlMFE behave better when there are many free variables. See Note [Large free-variable sets]. 2. Make GHC.Core.Opt.Arity.floatIn a bit lazier in its Cost argument. This benefits the common case where the ArityType turns out to be nullary. See Note [Care with nested expressions] 3. Make GHC.CoreToStg.Prep.cpeArg behave for deeply-nested expressions. See Note [Eta expansion of arguments in CorePrep] wrinkle (EA2). Compile times go down by up to 4.5%, and much more in artificial cases. (Geo mean of compiler/perf changes is -0.4%.) Metric Decrease: CoOpt_Read T10421 T12425 - - - - - c4b13113 by Hécate Moonlight at 2024-03-06T13:40:17-05:00 Use "module" instead of "library" when applicable in base haddocks - - - - - 9cd9efb4 by Vladislav Zavialov at 2024-03-07T13:01:54+03:00 Rephrase error message to say "visible arguments" (#24318) * Main change: make the error message generated by mkFunTysMsg more accurate by changing "value arguments" to "visible arguments". * Refactor: define a new type synonym VisArity and use it instead of Arity in a few places. It might be the case that there other places in the compiler that should talk about visible arguments rather than value arguments, but I haven't tried to find them all, focusing only on the error message reported in the ticket. - - - - - 4b6e76b5 by Patrick at 2024-03-07T22:09:30+08:00 fix haskell/haddock#24493, with module name introduced in hieAst The accompanies haddoc PR with GHC PR https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12153 Two things have been done: 1. Link is introduced to every `X` in `module X where`, since we introduce the module name to HieAst, 2. `{-# LINE 4 "hypsrc-test/src/PositionPragmas.hs" #-}` is added before the `module PositionPragmas where` in ` hypsrc-test/ref/src/PositionPragmas.html `.It ensures only a single hieAst for file `hypsrc-test/src/PositionPragmas.hs` is generated. - - - - - d523a6a7 by Ben Gamari at 2024-03-07T19:40:45-05:00 Bump array submodule - - - - - 7e55003c by Ben Gamari at 2024-03-07T19:40:45-05:00 Bump stm submodule - - - - - 32d337ef by Ben Gamari at 2024-03-07T19:40:45-05:00 Introduce exception context Here we introduce the `ExceptionContext` type and `ExceptionAnnotation` class, allowing dynamically-typed user-defined annotations to be attached to exceptions. CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/199 GHC Proposal: https://github.com/ghc-proposals/ghc-proposals/pull/330 - - - - - 39f3d922 by Ben Gamari at 2024-03-07T19:40:46-05:00 testsuite/interface-stability: Update documentation - - - - - fdea7ada by Ben Gamari at 2024-03-07T19:40:46-05:00 ghc-internal: comment formatting - - - - - 4fba42ef by Ben Gamari at 2024-03-07T19:40:46-05:00 compiler: Default and warn ExceptionContext constraints - - - - - 3886a205 by Ben Gamari at 2024-03-07T19:40:46-05:00 base: Introduce exception backtraces Here we introduce the `Backtraces` type and associated machinery for attaching these via `ExceptionContext`. These has a few compile-time regressions (`T15703` and `T9872d`) due to the additional dependencies in the exception machinery. As well, there is a surprisingly large regression in the `size_hello_artifact` test. This appears to be due to various `Integer` and `Read` bits now being reachable at link-time. I believe it should be possible to avoid this but I have accepted the change for now to get the feature merged. CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/199 GHC Proposal: https://github.com/ghc-proposals/ghc-proposals/pull/330 Metric Increase: T15703 T9872d size_hello_artifact - - - - - 18c5409f by Ben Gamari at 2024-03-07T19:40:46-05:00 users guide: Release notes for exception backtrace work - - - - - f849c5fc by Ben Gamari at 2024-03-07T19:40:46-05:00 compiler: Don't show ExceptionContext of GhcExceptions Most GhcExceptions are user-facing errors and therefore the ExceptionContext has little value. Ideally we would enable it in the DEBUG compiler but I am leaving this for future work. - - - - - dc646e6f by Sylvain Henry at 2024-03-07T19:40:46-05:00 Disable T9930fail for the JS target (cf #19174) - - - - - bfc09760 by Alan Zimmerman at 2024-03-07T19:41:22-05:00 Update showAstData to honour blanking of AnnParen Also tweak rendering of SrcSpan to remove extra blank line. - - - - - 50454a29 by Ben Gamari at 2024-03-08T03:32:42-05:00 ghc-internal: Eliminate GHC.Internal.Data.Kind This was simply reexporting things from `ghc-prim`. Instead reexport these directly from `Data.Kind`. Also add build ordering dependency to work around #23942. - - - - - 38a4b6ab by Ben Gamari at 2024-03-08T03:33:18-05:00 rts: Fix SET_HDR initialization of retainer set This fixes a regression in retainer set profiling introduced by b0293f78cb6acf2540389e22bdda420d0ab874da. Prior to that commit the heap traversal word would be initialized by `SET_HDR` using `LDV_RECORD_CREATE`. However, the commit added a `doingLDVProfiling` check in `LDV_RECORD_CREATE`, meaning that this initialization no longer happened. Given that this initialization was awkwardly indirectly anyways, I have fixed this by explicitly initializating the heap traversal word to `NULL` in `SET_PROF_HDR`. This is equivalent to the previous behavior, but much more direct. Fixes #24513. - - - - - 635abccc by Ben Gamari at 2024-03-08T17:09:06-05:00 Bump ghc version to 9.10 - - - - - 2859a637 by Ben Gamari at 2024-03-08T18:26:47-05:00 base: Use strerror_r instead of strerror As noted by #24344, `strerror` is not necessarily thread-safe. Thankfully, POSIX.1-2001 has long offered `strerror_r`, which is safe to use. Fixes #24344. CLC discussion: https://github.com/haskell/core-libraries-committee/issues/249 - - - - - 5b934048 by Ben Gamari at 2024-03-08T18:50:12-05:00 Bump base upper bound - - - - - b30d134e by Ben Gamari at 2024-03-08T18:50:44-05:00 Testsuite output update - - - - - edb9bf77 by Jade at 2024-03-09T03:39:38-05:00 Error messages: Improve Error messages for Data constructors in type signatures. This patch improves the error messages from invalid type signatures by trying to guess what the user did and suggesting an appropriate fix. Partially fixes: #17879 - - - - - cfb197e3 by Patrick at 2024-03-09T03:40:15-05:00 HieAst: add module name #24493 The main purpose of this is to tuck the module name `xxx` in `module xxx where` into the hieAst. It should fix #24493. The following have been done: 1. Renamed and update the `tcg_doc_hdr :: Maybe (LHsDoc GhcRn)` to `tcg_hdr_info :: (Maybe (LHsDoc GhcRn), Maybe (XRec GhcRn ModuleName))` To store the located module name information. 2. update the `RenamedSource` and `RenamedStuff` with extra `Maybe (XRec GhcRn ModuleName)` located module name information. 3. add test `testsuite/tests/hiefile/should_compile/T24493.hs` to ensure the module name is added and update several relevent tests. 4. accompanied submodule haddoc test update MR in https://gitlab.haskell.org/ghc/haddock/-/merge_requests/53 - - - - - 2341d81e by Vaibhav Sagar at 2024-03-09T03:40:54-05:00 GHC.Utils.Binary: fix a couple of typos - - - - - 5580e1bd by Ben Gamari at 2024-03-09T03:41:30-05:00 rts: Drop .wasm suffix from .prof file names This replicates the behavior on Windows, where `Hi.exe` will produce profiling output named `Hi.prof` instead of `Hi.exe.prof`. While in the area I also fixed the extension-stripping logic, which incorrectly rewrote `Hi.exefoo` to `Hi.foo`. Closes #24515. - - - - - 259495ee by Cheng Shao at 2024-03-09T03:41:30-05:00 testsuite: drop exe extension from .hp & .prof filenames See #24515 for details. - - - - - c477a8d2 by Ben Gamari at 2024-03-09T03:42:05-05:00 rts/linker: Enable GOT support on all platforms There is nothing platform-dependent about our GOT implementation and GOT support is needed by `T24171` on i386. - - - - - 2e592857 by Vladislav Zavialov at 2024-03-09T03:42:41-05:00 Drop outdated comment on TcRnIllformedTypePattern This should have been done in 0f0c53a501b but I missed it. - - - - - c554b4da by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/CloneStack: Bounds check array write - - - - - 15c590a5 by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/CloneStack: Don't expose helper functions in header - - - - - e831ce31 by Ben Gamari at 2024-03-09T09:39:20-05:00 base: Move internals of GHC.InfoProv into GHC.InfoProv.Types Such that we can add new helpers into GHC.InfoProv.Types without breakage. - - - - - 6948e24d by Ben Gamari at 2024-03-09T09:39:20-05:00 rts: Lazily decode IPE tables Previously we would eagerly allocate `InfoTableEnt`s for each info table registered in the info table provenance map. However, this costs considerable memory and initialization time. Instead we now lazily decode these tables. This allows us to use one-third the memory *and* opens the door to taking advantage of sharing opportunities within a module. This required considerable reworking since lookupIPE now must be passed its result buffer. - - - - - 9204a04e by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/IPE: Don't expose helper in header - - - - - 308926ff by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/IPE: Share module_name within a Node This allows us to shave a 64-bit word off of the packed IPE entry size. - - - - - bebdea05 by Ben Gamari at 2024-03-09T09:39:20-05:00 IPE: Expose unit ID in InfoTableProv Here we add the unit ID to the info table provenance structure. - - - - - 6519c9ad by Ben Gamari at 2024-03-09T09:39:35-05:00 rts: Refactor GHC.Stack.CloneStack.decode Don't allocate a Ptr constructor per frame. - - - - - ed0b69dc by Ben Gamari at 2024-03-09T09:39:35-05:00 base: Do not expose whereFrom# from GHC.Exts - - - - - 2b1faea9 by Vladislav Zavialov at 2024-03-09T17:38:21-05:00 docs: Update info on TypeAbstractions * Mention TypeAbstractions in 9.10.1-notes.rst * Set the status to "Experimental". * Add a "Since: GHC 9.x" comment to each section. - - - - - f8b88918 by Ben Gamari at 2024-03-09T21:21:46-05:00 ci-images: Bump Alpine image to bootstrap with 9.8.2 - - - - - 705e6927 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Mark T24171 as fragile due to #24512 I will fix this but not in time for 9.10.1-alpha1 - - - - - c74196e1 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Mark linker_unload_native as fragile In particular this fails on platforms without `dlinfo`. I plan to address this but not before 9.10.1-alpha1. - - - - - f4d87f7a by Ben Gamari at 2024-03-09T21:21:46-05:00 configure: Bump version to 9.10 - - - - - 88df9a5f by Ben Gamari at 2024-03-09T21:21:46-05:00 Bump transformers submodule to 0.6.1.1 - - - - - 8176d5e8 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Increase ulimit for T18623 1 MByte was just too tight and failed intermittently on some platforms (e.g. CentOS 7). Bumping the limit to 8 MByte should provide sufficient headroom. Fixes #23139. - - - - - c74b38a3 by Ben Gamari at 2024-03-09T21:21:46-05:00 base: Bump version to 4.20.0.0 - - - - - b2937fc3 by Ben Gamari at 2024-03-09T21:21:46-05:00 ghc-internal: Set initial version at 9.1001.0 This provides PVP compliance while maintaining a clear correspondence between GHC releases and `ghc-internal` versions. - - - - - 4ae7d868 by Ben Gamari at 2024-03-09T21:21:46-05:00 ghc-prim: Bump version to 0.11.0 - - - - - 50798dc6 by Ben Gamari at 2024-03-09T21:21:46-05:00 template-haskell: Bump version to 2.22.0.0 - - - - - 8564f976 by Ben Gamari at 2024-03-09T21:21:46-05:00 base-exports: Accommodate spurious whitespace changes in 32-bit output It appears that this was - - - - - 9d4f0e98 by Ben Gamari at 2024-03-09T21:21:46-05:00 users-guide: Move exception backtrace relnotes to 9.10 This was previously mistakenly added to the GHC 9.8 release notes. - - - - - 145eae60 by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/rel_eng: Fix name of Rocky8 artifact - - - - - 39c2a630 by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/rel_eng: Fix path of generate_jobs_metadata - - - - - aed034de by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/upload: Rework recompression The old `combine` approach was quite fragile due to use of filename globbing. Moreover, it didn't parallelize well. This refactoring makes the goal more obvious, parallelizes better, and is more robust. - - - - - 9bdf3586 by Ben Gamari at 2024-03-09T21:37:44-05:00 Merge branch 'ghc-9.10' into ghc-head - - - - - cec76981 by Ben Gamari at 2024-03-09T21:54:00-05:00 Bump GHC version to 9.11 - - - - - 4c59feb7 by Ben Gamari at 2024-03-09T22:15:01-05:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - dc207d06 by Ben Gamari at 2024-03-10T08:56:08-04:00 configure: Bump GHC version to 9.11 Bumps haddock submodule. - - - - - 8b2513e8 by Ben Gamari at 2024-03-11T01:20:03-04:00 rts/linker: Don't unload code when profiling is enabled The heap census may contain references (e.g. `Counter.identity`) to static data which must be available when the census is reported at the end of execution. Fixes #24512. - - - - - 7810b4c3 by Ben Gamari at 2024-03-11T01:20:03-04:00 rts/linker: Don't unload native objects when dlinfo isn't available To do so is unsafe as we have no way of identifying references to symbols provided by the object. Fixes #24513. Fixes #23993. - - - - - 0590764c by Ben Gamari at 2024-03-11T01:20:39-04:00 rel_eng/upload: Purge both $rel_name/ and $ver/ This is necessary for prereleases, where GHCup accesses the release via `$ver/` - - - - - b85a4631 by Brandon Chinn at 2024-03-12T19:25:56-04:00 Remove duplicate code normalising slashes - - - - - c91946f9 by Brandon Chinn at 2024-03-12T19:25:56-04:00 Simplify regexes with raw strings - - - - - 1a5f53c6 by Brandon Chinn at 2024-03-12T19:25:57-04:00 Don't normalize backslashes in characters - - - - - 7ea971d3 by Andrei Borzenkov at 2024-03-12T19:26:32-04:00 Fix compiler crash caused by implicit RHS quantification in type synonyms (#24470) - - - - - 39f3ac3e by Cheng Shao at 2024-03-12T19:27:11-04:00 Revert "compiler: make genSym use C-based atomic increment on non-JS 32-bit platforms" This reverts commit 615eb855416ce536e02ed935ecc5a6f25519ae16. It was originally intended to fix #24449, but it was merely sweeping the bug under the rug. 3836a110577b5c9343915fd96c1b2c64217e0082 has properly fixed the fragile test, and we no longer need the C version of genSym. Furthermore, the C implementation causes trouble when compiling with clang that targets i386 due to alignment warning and libatomic linking issue, so it makes sense to revert it. - - - - - e6bfb85c by Cheng Shao at 2024-03-12T19:27:11-04:00 compiler: fix out-of-bound memory access of genSym on 32-bit This commit fixes an unnoticed out-of-bound memory access of genSym on 32-bit. ghc_unique_inc is 32-bit sized/aligned on 32-bit platforms, but we mistakenly treat it as a Word64 pointer in genSym, and therefore will accidentally load 2 garbage higher bytes, or with a small but non-zero chance, overwrite something else in the data section depends on how the linker places the data segments. This regression was introduced in !11802 and fixed here. - - - - - 77171cd1 by Ben Orchard at 2024-03-14T09:00:40-04:00 Note mutability of array and address access primops Without an understanding of immutable vs. mutable memory, the index primop family have a potentially non-intuitive type signature: indexOffAddr :: Addr# -> Int# -> a readOffAddr :: Addr# -> Int# -> State# d -> (# State# d, a #) indexOffAddr# might seem like a free generality improvement, which it certainly is not! This change adds a brief note on mutability expectations for most index/read/write access primops. - - - - - 7da7f8f6 by Alan Zimmerman at 2024-03-14T09:01:15-04:00 EPA: Fix regression discarding comments in contexts Closes #24533 - - - - - 73be65ab by Fendor at 2024-03-19T01:42:53-04:00 Fix sharing of 'IfaceTyConInfo' during core to iface type translation During heap analysis, we noticed that during generation of 'mi_extra_decls' we have lots of duplicates for the instances: * `IfaceTyConInfo NotPromoted IfaceNormalTyCon` * `IfaceTyConInfo IsPromoted IfaceNormalTyCon` which should be shared instead of duplicated. This duplication increased the number of live bytes by around 200MB while loading the agda codebase into GHCi. These instances are created during `CoreToIface` translation, in particular `toIfaceTyCon`. The generated core looks like: toIfaceTyCon = \ tc_sjJw -> case $wtoIfaceTyCon tc_sjJw of { (# ww_sjJz, ww1_sjNL, ww2_sjNM #) -> IfaceTyCon ww_sjJz (IfaceTyConInfo ww1_sjNL ww2_sjNM) } whichs removes causes the sharing to work propery. Adding explicit sharing, with NOINLINE annotations, changes the core to: toIfaceTyCon = \ tc_sjJq -> case $wtoIfaceTyCon tc_sjJq of { (# ww_sjNB, ww1_sjNC #) -> IfaceTyCon ww_sjNB ww1_sjNC } which looks much more like sharing is happening. We confirmed via ghc-debug that all duplications were eliminated and the number of live bytes are noticeably reduced. - - - - - bd8209eb by Alan Zimmerman at 2024-03-19T01:43:28-04:00 EPA: Address more 9.10.1-alpha1 regressions from recent changes Closes #24533 Hopefully for good this time - - - - - 31bf85ee by Fendor at 2024-03-19T14:48:08-04:00 Escape multiple arguments in the settings file Uses responseFile syntax. The issue arises when GHC is installed on windows into a location that has a space, for example the user name is 'Fake User'. The $topdir will also contain a space, consequentially. When we resolve the top dir in the string `-I$topdir/mingw/include`, then `words` will turn this single argument into `-I/C/Users/Fake` and `User/.../mingw/include` which trips up the flag argument parser of various tools such as gcc or clang. We avoid this by escaping the $topdir before replacing it in `initSettngs`. Additionally, we allow to escape spaces and quotation marks for arguments in `settings` file. Add regression test case to count the number of options after variable expansion and argument escaping took place. Additionally, we check that escaped spaces and double quotation marks are correctly parsed. - - - - - f45f700e by Matthew Pickering at 2024-03-19T14:48:44-04:00 Read global package database from settings file Before this patch, the global package database was always assumed to be in libdir </> package.conf.d. This causes issues in GHC's build system because there are sometimes situations where the package database you need to use is not located in the same place as the settings file. * The stage1 compiler needs to use stage1 libraries, so we should set "Global Package DB" for the stage1 compiler to the stage1 package database. * Stage 2 cross compilers need to use stage2 libraries, so likewise, we should set the package database path to `_build/stage2/lib/` * The normal situation is where the stage2 compiler uses stage1 libraries. Then everything lines up. * When installing we have rearranged everything so that the settings file and package database line up properly, so then everything should continue to work as before. In this case we set the relative package db path to `package.conf.d`, so it resolves the same as before. * ghc-pkg needs to be modified as well to look in the settings file fo the package database rather than assuming the global package database location relative to the lib folder. * Cabal/cabal-install will work correctly because they query the global package database using `--print-global-package-db`. A reasonable question is why not generate the "right" settings files in the right places in GHC's build system. In order to do this you would need to engineer wrappers for all executables to point to a specific libdir. There are also situations where the same package db is used by two different compilers with two different settings files (think stage2 cross compiler and stage3 compiler). In short, this 10 line patch allows for some reasonable simplifications in Hadrian at very little cost to anything else. Fixes #24502 - - - - - 4c8f1794 by Matthew Pickering at 2024-03-19T14:48:44-04:00 hadrian: Remove stage1 testsuite wrappers logic Now instead of producing wrappers which pass the global package database argument to ghc and ghc-pkg, we write the location of the correct package database into the settings file so you can just use the intree compiler directly. - - - - - da0d8ba5 by Matthew Craven at 2024-03-19T14:49:20-04:00 Remove unused ghc-internal module "GHC.Internal.Constants" - - - - - b56d2761 by Matthew Craven at 2024-03-19T14:49:20-04:00 CorePrep: Rework lowering of BigNat# literals Don't use bigNatFromWord#, because that's terrible: * We shouldn't have to traverse a linked list at run-time to build a BigNat# literal. That's just silly! * The static List object we have to create is much larger than the actual BigNat#'s contents, bloating code size. * We have to read the corresponding interface file, which causes un-tracked implicit dependencies. (#23942) Instead, encode them into the appropriate platform-dependent sequence of bytes, and generate code that copies these bytes at run-time from an Addr# literal into a new ByteArray#. A ByteArray# literal would be the correct thing to generate, but these are not yet supported; see also #17747. Somewhat surprisingly, this change results in a slight reduction in compiler allocations, averaging around 0.5% on ghc's compiler performance tests, including when compiling programs that contain no bignum literals to begin with. The specific cause of this has not been investigated. Since this lowering no longer reads the interface file for GHC.Num.BigNat, the reasoning in Note [Depend on GHC.Num.Integer] is obsoleted. But the story of un-tracked built-in dependencies remains complex, and Note [Tracking dependencies on primitives] now exists to explain this complexity. Additionally, many empty imports have been modified to refer to this new note and comply with its guidance. Several empty imports necessary for other reasons have also been given brief explanations. Metric Decrease: MultiLayerModulesTH_OneShot - - - - - 349ea330 by Fendor at 2024-03-19T14:50:00-04:00 Eliminate thunk in 'IfaceTyCon' Heap analysis showed that `IfaceTyCon` retains a thunk to `IfaceTyConInfo`, defeating the sharing of the most common instances of `IfaceTyConInfo`. We make sure the indirection is removed by adding bang patterns to `IfaceTyCon`. Experimental results on the agda code base, where the `mi_extra_decls` were read from disk: Before this change, we observe around 8654045 instances of: `IfaceTyCon[Name,THUNK_1_0]` But these thunks almost exclusively point to a shared value! Forcing the thunk a little bit more, leads to `ghc-debug` reporting: `IfaceTyCon[Name:Name,IfaceTyConInfo]` and a noticeable reduction of live bytes (on agda ~10%). - - - - - 594bee0b by Krzysztof Gogolewski at 2024-03-19T14:50:36-04:00 Minor misc cleanups - GHC.HsToCore.Foreign.JavaScript: remove dropRuntimeRepArgs; boxed tuples don't take RuntimeRep args - GHC.HsToCore.Foreign.Call: avoid partial pattern matching - GHC.Stg.Unarise: strengthen the assertion; we can assert that non-rubbish literals are unary rather than just non-void - GHC.Tc.Gen.HsType: make sure the fsLit "literal" rule fires - users_guide/using-warnings.rst: remove -Wforall-identifier, now deprecated and does nothing - users_guide/using.rst: fix formatting - andy_cherry/test.T: remove expect_broken_for(23272...), 23272 is fixed The rest are simple cleanups. - - - - - cf55a54b by Ben Gamari at 2024-03-19T14:51:12-04:00 mk/relpath: Fix quoting Previously there were two instances in this script which lacked proper quoting. This resulted in `relpath` invocations in the binary distribution Makefile producing incorrect results on Windows, leading to confusing failures from `sed` and the production of empty package registrations. Fixes #24538. - - - - - 5ff88389 by Bryan Richter at 2024-03-19T14:51:48-04:00 testsuite: Disable T21336a on wasm - - - - - 60023351 by Ben Gamari at 2024-03-19T22:33:10-04:00 hadrian/bindist: Eliminate extraneous `dirname` invocation Previously we would call `dirname` twice per installed library file. We now instead reuse this result. This helps appreciably on Windows, where processes are quite expensive. - - - - - 616ac300 by Ben Gamari at 2024-03-19T22:33:10-04:00 hadrian: Package mingw toolchain in expected location This fixes #24525, a regression due to 41cbaf44a6ab5eb9fa676d65d32df8377898dc89. Specifically, GHC expects to find the mingw32 toolchain in the binary distribution root. However, after this patch it was packaged in the `lib/` directory. - - - - - de9daade by Ben Gamari at 2024-03-19T22:33:11-04:00 gitlab/rel_eng: More upload.sh tweaks - - - - - 1dfe12db by Ben Gamari at 2024-03-19T22:33:11-04:00 rel_eng: Drop dead prepare_docs codepath - - - - - dd2d748b by Ben Gamari at 2024-03-19T22:33:11-04:00 rel_env/recompress_all: unxz before recompressing Previously we would rather compress the xz *again*, before in addition compressing it with the desired scheme. Fixes #24545. - - - - - 9d936c57 by Ben Gamari at 2024-03-19T22:33:11-04:00 mk-ghcup-metadata: Fix directory of testsuite tarball As reported in #24546, the `dlTest` artifact should be extracted into the `testsuite` directory. - - - - - 6d398066 by Ben Gamari at 2024-03-19T22:33:11-04:00 ghcup-metadata: Don't populate dlOutput unless necessary ghcup can apparently infer the output name of an artifact from its URL. Consequently, we should only include the `dlOutput` field when it would differ from the filename of `dlUri`. Fixes #24547. - - - - - 576f8b7e by Zubin Duggal at 2024-03-19T22:33:46-04:00 Revert "Apply shellcheck suggestion to SUBST_TOOLDIR" This reverts commit c82770f57977a2b5add6e1378f234f8dd6153392. The shellcheck suggestion is spurious and results in SUBST_TOOLDIR being a no-op. `set` sets positional arguments for bash, but we want to set the variable given as the first autoconf argument. Fixes #24542 Metric decreases because the paths in the settings file are now shorter, so we allocate less when we read the settings file. ------------------------- Metric Decrease: T12425 T13035 T9198 ------------------------- - - - - - cdfe6e01 by Fendor at 2024-03-19T22:34:22-04:00 Compact serialisation of IfaceAppArgs In #24563, we identified that IfaceAppArgs serialisation tags each cons cell element with a discriminator byte. These bytes add up quickly, blowing up interface files considerably when '-fwrite-if-simplified-core' is enabled. We compact the serialisation by writing out the length of 'IfaceAppArgs', followed by serialising the elements directly without any discriminator byte. This improvement can decrease the size of some interface files by up to 35%. - - - - - 97a2bb1c by Simon Peyton Jones at 2024-03-20T17:11:29+00:00 Expand untyped splices in tcPolyExprCheck Fixes #24559 - - - - - 5f275176 by Alan Zimmerman at 2024-03-20T22:44:12-04:00 EPA: Clean up Exactprint helper functions a bit - Introduce a helper lens to compose on `EpAnn a` vs `a` versions - Rename some prime versions of functions back to non-prime They were renamed during the rework - - - - - da2a10ce by Vladislav Zavialov at 2024-03-20T22:44:48-04:00 Type operators in promoteOccName (#24570) Type operators differ from term operators in that they are lexically classified as (type) constructors, not as (type) variables. Prior to this change, promoteOccName did not account for this difference, causing a scoping issue that affected RequiredTypeArguments. type (!@#) = Bool f = idee (!@#) -- Not in scope: ‘!@#’ (BUG) Now we have a special case in promoteOccName to account for this. - - - - - 247fc0fa by Preetham Gujjula at 2024-03-21T10:19:18-04:00 docs: Remove mention of non-existent Ord instance for Complex The documentation for Data.Complex says that the Ord instance for Complex Float is deficient, but there is no Ord instance for Complex a. The Eq instance for Complex Float is similarly deficient, so we use that as an example instead. - - - - - 6fafc51e by Andrei Borzenkov at 2024-03-21T10:19:54-04:00 Fix TH handling in `pat_to_type_pat` function (#24571) There was missing case for `SplicePat` in `pat_to_type_at` function, hence patterns with splicing that checked against `forall->` doesn't work properly because they fall into the "illegal pattern" case. Code example that is now accepted: g :: forall a -> () g $([p| a |]) = () - - - - - 52072f8e by Sylvain Henry at 2024-03-21T21:01:59-04:00 Type-check default declarations before deriving clauses (#24566) See added Note and #24566. Default declarations must be type-checked before deriving clauses. - - - - - 7dfdf3d9 by Sylvain Henry at 2024-03-21T21:02:40-04:00 Lexer: small perf changes - Use unsafeChr because we know our values to be valid - Remove some unnecessary use of `ord` (return Word8 values directly) - - - - - 864922ef by Sylvain Henry at 2024-03-21T21:02:40-04:00 JS: fix some comments - - - - - 3e0b2b1f by Sebastian Graf at 2024-03-21T21:03:16-04:00 Simplifier: Re-do dependency analysis in abstractFloats (#24551) In #24551, we abstracted a string literal binding over a type variable, triggering a CoreLint error when that binding floated to top-level. The solution implemented in this patch fixes this by re-doing dependency analysis on a simplified recursive let binding that is about to be type abstracted, in order to find the minimal set of type variables to abstract over. See wrinkle (AB5) of Note [Floating and type abstraction] for more details. Fixes #24551 - - - - - 8a8ac65a by Matthew Craven at 2024-03-23T00:20:52-04:00 Improve toInteger @Word32 on 64-bit platforms On 64-bit platforms, every Word32 fits in an Int, so we can convert to Int# without having to perform the overflow check integerFromWord# uses internally. - - - - - 0c48f2b9 by Apoorv Ingle at 2024-03-23T00:21:28-04:00 Fix for #24552 (see testcase T24552) Fixes for a bug in desugaring pattern synonyms matches, introduced while working on on expanding `do`-blocks in #18324 The `matchWrapper` unecessarily (and incorrectly) filtered out the default wild patterns in a match. Now the wild pattern alternative is simply ignored by the pm check as its origin is `Generated`. The current code now matches the expected semantics according to the language spec. - - - - - b72705e9 by Simon Peyton Jones at 2024-03-23T00:22:04-04:00 Print more info about kinds in error messages This fixes #24553, where GHC unhelpfully said error: [GHC-83865] • Expected kind ‘* -> * -> *’, but ‘Foo’ has kind ‘* -> * -> *’ See Note [Showing invisible bits of types in error messages] - - - - - 8f7cfc7e by Tristan Cacqueray at 2024-03-23T00:22:44-04:00 docs: remove the don't use float hint This hint is outdated, ``Complex Float`` are now specialised, and the heap space suggestion needs more nuance so it should be explained in the unboxed/storable array documentation. - - - - - 5bd8ed53 by Andreas Klebinger at 2024-03-23T16:18:33-04:00 NCG: Fix a bug in jump shortcutting. When checking if a jump has more than one destination account for the possibility of some jumps not being representable by a BlockId. We do so by having isJumpishInstr return a `Maybe BlockId` where Nothing represents non-BlockId jump destinations. Fixes #24507 - - - - - 8d67f247 by Ben Gamari at 2024-03-23T16:19:09-04:00 docs: Drop old release notes, add for 9.12.1 - - - - - 7db8c992 by Cheng Shao at 2024-03-25T13:45:46-04:00 rts: fix clang compilation on aarch64 This patch fixes function prototypes in ARMOutlineAtomicsSymbols.h which causes "error: address argument to atomic operation must be a pointer to _Atomic type" when compiling with clang on aarch64. - - - - - 237194ce by Sylvain Henry at 2024-03-25T13:46:27-04:00 Lexer: fix imports for Alex 3.5.1 (#24583) - - - - - 810660b7 by Cheng Shao at 2024-03-25T22:19:16-04:00 libffi-tarballs: bump libffi-tarballs submodule to libffi 3.4.6 This commit bumps the libffi-tarballs submodule to libffi 3.4.6, which includes numerous upstream libffi fixes, especially https://github.com/libffi/libffi/issues/760. - - - - - d2ba41e8 by Alan Zimmerman at 2024-03-25T22:19:51-04:00 EPA: do not duplicate comments in signature RHS - - - - - 32a8103f by Rodrigo Mesquita at 2024-03-26T21:16:12-04:00 configure: Use LDFLAGS when trying linkers A user may configure `LDFLAGS` but not `LD`. When choosing a linker, we will prefer `ldd`, then `ld.gold`, then `ld.bfd` -- however, we have to check for a working linker. If either of these fail, we try the next in line. However, we were not considering the `$LDFLAGS` when checking if these linkers worked. So we would pick a linker that does not support the current $LDFLAGS and fail further down the line when we used that linker with those flags. Fixes #24565, where `LDFLAGS=-Wl,-z,pack-relative-relocs` is not supported by `ld.gold` but that was being picked still. - - - - - bf65a7c3 by Rodrigo Mesquita at 2024-03-26T21:16:48-04:00 bindist: Clean xattrs of bin and lib at configure time For issue #21506, we started cleaning the extended attributes of binaries and libraries from the bindist *after* they were installed to workaround notarisation (#17418), as part of `make install`. However, the `ghc-toolchain` binary that is now shipped with the bindist must be run at `./configure` time. Since we only cleaned the xattributes of the binaries and libs after they were installed, in some situations users would be unable to run `ghc-toolchain` from the bindist, failing at configure time (#24554). In this commit we move the xattr cleaning logic to the configure script. Fixes #24554 - - - - - cfeb70d3 by Rodrigo Mesquita at 2024-03-26T21:17:24-04:00 Revert "NCG: Fix a bug in jump shortcutting." This reverts commit 5bd8ed53dcefe10b72acb5729789e19ceb22df66. Fixes #24586 - - - - - 13223f6d by Serge S. Gulin at 2024-03-27T07:28:51-04:00 JS: `h$rts_isProfiled` is removed from `profiling` and left its version at `rts/js/config.js` - - - - - 0acfe391 by Alan Zimmerman at 2024-03-27T07:29:27-04:00 EPA: Do not extend declaration range for trailine zero len semi The lexer inserts virtual semicolons having zero width. Do not use them to extend the list span of items in a list. - - - - - cd0fb82f by Alan Zimmerman at 2024-03-27T19:33:08+00:00 EPA: Fix FamDecl range The span was incorrect if opt_datafam_kind_sig was empty - - - - - f8f384a8 by Ben Gamari at 2024-03-29T01:23:03-04:00 Fix type of _get_osfhandle foreign import Fixes #24601. - - - - - 00d3ecf0 by Alan Zimmerman at 2024-03-29T12:19:10+00:00 EPA: Extend StringLiteral range to include trailing commas This goes slightly against the exact printing philosophy where trailing decorations should be in an annotation, but the practicalities of adding it to the WarningTxt environment, and the problems caused by deviating do not make a more principles approach worthwhile. - - - - - efab3649 by brandon s allbery kf8nh at 2024-03-31T20:04:01-04:00 clarify Note [Preproccesing invocations] - - - - - c8a4c050 by Ben Gamari at 2024-04-02T12:50:35-04:00 rts: Fix TSAN_ENABLED CPP guard This should be `#if defined(TSAN_ENABLED)`, not `#if TSAN_ENABLED`, lest we suffer warnings. - - - - - e91dad93 by Cheng Shao at 2024-04-02T12:50:35-04:00 rts: fix errors when compiling with TSAN This commit fixes rts compilation errors when compiling with TSAN: - xxx_FENCE macros are redefined and trigger CPP warnings. - Use SIZEOF_W. WORD_SIZE_IN_BITS is provided by MachDeps.h which Cmm.h doesn't include by default. - - - - - a9ab9455 by Cheng Shao at 2024-04-02T12:50:35-04:00 rts: fix clang-specific errors when compiling with TSAN This commit fixes clang-specific rts compilation errors when compiling with TSAN: - clang doesn't have -Wtsan flag - Fix prototype of ghc_tsan_* helper functions - __tsan_atomic_* functions aren't clang built-ins and sanitizer/tsan_interface_atomic.h needs to be included - On macOS, TSAN runtime library is libclang_rt.tsan_osx_dynamic.dylib, not libtsan. -fsanitize-thread as a link-time flag will take care of linking the TSAN runtime library anyway so remove tsan as an rts extra library - - - - - 865bd717 by Cheng Shao at 2024-04-02T12:50:35-04:00 compiler: fix github link to __tsan_memory_order in a comment - - - - - 07cb627c by Cheng Shao at 2024-04-02T12:50:35-04:00 ci: improve TSAN CI jobs - Run TSAN jobs with +thread_sanitizer_cmm which enables Cmm instrumentation as well. - Run TSAN jobs in deb12 which ships gcc-12, a reasonably recent gcc that @bgamari confirms he's using in #GHC:matrix.org. Ideally we should be using latest clang release for latest improvements in sanitizers, though that's left as future work. - Mark TSAN jobs as manual+allow_failure in validate pipelines. The purpose is to demonstrate that we have indeed at least fixed building of TSAN mode in CI without blocking the patch to land, and once merged other people can begin playing with TSAN using their own dev setups and feature branches. - - - - - a1c18c7b by Andrei Borzenkov at 2024-04-02T12:51:11-04:00 Merge tc_infer_hs_type and tc_hs_type into one function using ExpType philosophy (#24299, #23639) This patch implements refactoring which is a prerequisite to updating kind checking of type patterns. This is a huge simplification of the main worker that checks kind of HsType. It also fixes the issues caused by previous code duplication, e.g. that we didn't add module finalizers from splices in inference mode. - - - - - 817e8936 by Rodrigo Mesquita at 2024-04-02T20:13:05-04:00 th: Hide the Language.Haskell.TH.Lib.Internal module from haddock Fixes #24562 - - - - - b36ee57b by Sylvain Henry at 2024-04-02T20:13:46-04:00 JS: reenable h$appendToHsString optimization (#24495) The optimization introducing h$appendToHsString wasn't kicking in anymore (while it did in 9.8.1) because of the changes introduced in #23270 (7e0c8b3bab30). This patch reenables the optimization by matching on case-expression, as done in Cmm for unpackCString# standard thunks. The test is also T24495 added in the next commits (two commits for ease of backporting to 9.8). - - - - - 527616e9 by Sylvain Henry at 2024-04-02T20:13:46-04:00 JS: fix h$appendToHsString implementation (#24495) h$appendToHsString needs to wrap its argument in an updatable thunk to behave like unpackAppendCString#. Otherwise if a SingleEntry thunk is passed, it is stored as-is in a CONS cell, making the resulting list impossible to deepseq (forcing the thunk doesn't update the contents of the CONS cell)! The added test checks that the optimization kicks in and that h$appendToHsString works as intended. Fix #24495 - - - - - faa30b41 by Simon Peyton Jones at 2024-04-02T20:14:22-04:00 Deal with duplicate tyvars in type declarations GHC was outright crashing before this fix: #24604 - - - - - e0b0c717 by Simon Peyton Jones at 2024-04-02T20:14:58-04:00 Try using MCoercion in exprIsConApp_maybe This is just a simple refactor that makes exprIsConApp_maybe a little bit more direct, simple, and efficient. Metrics: compile_time/bytes allocated geo. mean -0.1% minimum -2.0% maximum -0.0% Not a big gain, but worthwhile given that the code is, if anything, easier to grok. - - - - - 15f4d867 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Initial ./configure support for selecting I/O managers In this patch we just define new CPP vars, but don't yet use them or replace the existing approach. That will follow. The intention here is that every I/O manager can be enabled/disabled at GHC build time (subject to some constraints). More than one I/O manager can be enabled to be built. At least one I/O manager supporting the non-threaded RTS must be enabled as well as at least one supporting the non-threaded RTS. The I/O managers enabled here will become the choices available at runtime at RTS startup (in later patches). The choice can be made with RTS flags. There are separate sets of choices for the threaded and non-threaded RTS ways, because most I/O managers are specific to these ways. Furthermore we must establish a default I/O manager for the threaded and non-threaded RTS. Most I/O managers are platform-specific so there are checks to ensure each one can be enabled on the platform. Such checks are also where (in future) any system dependencies (e.g. libraries) can be checked. The output is a set of CPP flags (in the mk/config.h file), with one flag per named I/O manager: * IOMGR_BUILD_<name> : which ones should be built (some) * IOMGR_DEFAULT_NON_THREADED_<name> : which one is default (exactly one) * IOMGR_DEFAULT_THREADED_<name> : which one is default (exactly one) and a set of derived flags in IOManager.h * IOMGR_ENABLED_<name> : enabled for the current RTS way Note that IOMGR_BUILD_<name> just says that an I/O manager will be built for _some_ RTS way (i.e. threaded or non-threaded). The derived flags IOMGR_ENABLED_<name> in IOManager.h say if each I/O manager is enabled in the "current" RTS way. These are the ones that can be used for conditional compilation of the I/O manager code. Co-authored-by: Pi Delport <pi at well-typed.com> - - - - - 85b0f87a by Duncan Coutts at 2024-04-03T01:27:17-04:00 Change the handling of the RTS flag --io-manager= Now instead of it being just used on Windows to select between the WinIO vs the MIO or Win32-legacy I/O managers, it is now used on all platforms for selecting the I/O manager to use. Right now it remains the case that there is only an actual choice on Windows, but that will change later. Document the --io-manager flag in the user guide. This change is also reflected in the RTS flags types in the base library. Deprecate the export of IoSubSystem from GHC.RTS.Flags with a message to import it from GHC.IO.Subsystem. The way the 'IoSubSystem' is detected also changes. Instead of looking at the RTS flag, there is now a C bool global var in the RTS which gets set on startup when the I/O manager is selected. This bool var says whether the selected I/O manager classifies as "native" on Windows, which in practice means the WinIO I/O manager has been selected. Similarly, the is_io_mng_native_p RTS helper function is re-implemented in terms of the selected I/O manager, rather than based on the RTS flags. We do however remove the ./configure --native-io-manager flag because we're bringing the WinIO/MIO/Win32-legacy choice under the new general scheme for selecting I/O managers, and that new scheme involves no ./configure time user choices, just runtime RTS flag choices. - - - - - 1a8f020f by Duncan Coutts at 2024-04-03T01:27:17-04:00 Convert {init,stop,exit}IOManager to switch style Rather than ad-hoc cpp conitionals on THREADED_RTS and mingw32_HOST_OS, we use a style where we switch on the I/O manager impl, with cases for each I/O manager impl. - - - - - a5bad3d2 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Split up the CapIOManager content by I/O manager Using the new IOMGR_ENABLED_<name> CPP defines. - - - - - 1d36e609 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Convert initIOManagerAfterFork and wakeupIOManager to switch style - - - - - c2f26f36 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move most of waitRead#/Write# from cmm to C Moves it into the IOManager.c where we can follow the new pattern of switching on the selected I/O manager. - - - - - 457705a8 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move most of the delay# impl from cmm to C Moves it into the IOManager.c where we can follow the new pattern of switching on the selected I/O manager. Uses a new IOManager API: syncDelay, following the naming convention of sync* for thread-synchronous I/O & timer/delay operations. As part of porting from cmm to C, we maintain the rule that the why_blocked gets accessed using load acquire and store release atomic memory operations. There was one exception to this rule: in the delay# primop cmm code on posix (not win32), the why_blocked was being updated using a store relaxed, not a store release. I've no idea why. In this convesion I'm playing it safe here and using store release consistently. - - - - - e93058e0 by Duncan Coutts at 2024-04-03T01:27:18-04:00 insertIntoSleepingQueue is no longer public No longer defined in IOManager.h, just a private function in IOManager.c. Since it is no longer called from cmm code, just from syncDelay. It ought to get moved further into the select() I/O manager impl, rather than living in IOManager.c. On the other hand appendToIOBlockedQueue is still called from cmm code in the win32-legacy I/O manager primops async{Read,Write}#, and it is also used by the select() I/O manager. Update the CPP and comments to reflect this. - - - - - 60ce9910 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move anyPendingTimeoutsOrIO impl from .h to .c The implementation is eventually going to need to use more private things, which will drag in unwanted includes into IOManager.h, so it's better to move the impl out of the header file and into the .c file, at the slight cost of it no longer being inline. At the same time, change to the "switch (iomgr_type)" style. - - - - - f70b8108 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Take a simpler approach to gcc warnings in IOManager.c We have lots of functions with conditional implementations for different I/O managers. Some functions, for some I/O managers, naturally have implementations that do nothing or barf. When only one such I/O manager is enabled then the whole function implementation will have an implementation that does nothing or barfs. This then results in warnings from gcc that parameters are unused, or that the function should be marked with attribute noreturn (since barf does not return). The USED_IF_THREADS trick for fine-grained warning supression is fine for just two cases, but an equivalent here would need USED_IF_THE_ONLY_ENABLED_IOMGR_IS_X_OR_Y which would have combinitorial blowup. So we take a coarse grained approach and simply disable these two warnings for the whole file. So we use a GCC pragma, with its handy push/pop support: #pragma GCC diagnostic push #pragma GCC diagnostic ignored "-Wsuggest-attribute=noreturn" #pragma GCC diagnostic ignored "-Wunused-parameter" ... #pragma GCC diagnostic pop - - - - - b48805b9 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add a new trace class for the iomanager It makes sense now for it to be separate from the scheduler class of tracers. Enabled with +RTS -Do. Document the -Do debug flag in the user guide. - - - - - f0c1f862 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Have the throwTo impl go via (new) IOManager APIs rather than directly operating on the IO manager's data structures. Specifically, when thowing an async exception to a thread that is blocked waiting for I/O or waiting for a timer, then we want to cancel that I/O waiting or cancel the timer. Currently this is done directly in removeFromQueues() in RaiseAsync.c. We want it to go via proper APIs both for modularity but also to let us support multiple I/O managers. So add sync{IO,Delay}Cancel, which is the cancellation for the corresponding sync{IO,Delay}. The implementations of these use the usual "switch (iomgr_type)" style. - - - - - 4f9e9c4e by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move awaitEvent into a proper IOManager API and have the scheduler use it. Previously the scheduler calls awaitEvent directly, and awaitEvent is implemented directly in the RTS I/O managers (select, win32). This relies on the old scheme where there's a single active I/O manager for each platform and RTS way. We want to move that to go via an API in IOManager.{h,c} which can then call out to the active I/O manager. Also take the opportunity to split awaitEvent into two. The existing awaitEvent has a bool wait parameter, to say if the call should be blocking or non-blocking. We split this into two separate functions: pollCompletedTimeoutsOrIO and awaitCompletedTimeoutsOrIO. We split them for a few reasons: they have different post-conditions (specifically the await version is supposed to guarantee that there are threads runnable when it completes). Secondly, it is also anticipated that in future I/O managers the implementations of the two cases will be simpler if they are separated. - - - - - 5ad4b30f by Duncan Coutts at 2024-04-03T01:27:18-04:00 Rename awaitEvent in select and win32 I/O managers These are now just called from IOManager.c and are the per-I/O manager backend impls (whereas previously awaitEvent was the entry point). Follow the new naming convention in the IOManager.{h,c} of awaitCompletedTimeoutsOrIO, with the I/O manager's name as a suffix: so awaitCompletedTimeoutsOrIO{Select,Win32}. - - - - - d30c6bc6 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Tidy up a couple things in Select.{h,c} Use the standard #include {Begin,End}Private.h style rather than RTS_PRIVATE on individual decls. And conditionally build the code for the select I/O manager based on the new CPP IOMGR_ENABLED_SELECT rather than on THREADED_RTS. - - - - - 4161f516 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add an IOManager API for scavenging TSO blocked_info When the GC scavenges a TSO it needs to scavenge the tso->blocked_info but the blocked_info is a big union and what lives there depends on the two->why_blocked, which for I/O-related reasons is something that in principle is the responsibility of the I/O manager and not the GC. So the right thing to do is for the GC to ask the I/O manager to sscavenge the blocked_info if it encounters any I/O-related why_blocked reasons. So we add scavengeTSOIOManager in IOManager.{h,c} with the usual style. Now as it happens, right now, there is no special scavenging to do, so the implementation of scavengeTSOIOManager is a fancy no-op. That's because the select I/O manager uses only the fd and target members, which are not GC pointers, and the win32-legacy I/O manager _ought_ to be using GC-managed heap objects for the StgAsyncIOResult but it is actually usingthe C heap, so again no GC pointers. If the win32-legacy were doing this more sensibly, then scavengeTSOIOManager would be the right place to do the GC magic. Future I/O managers will need GC heap objects in the tso->blocked_info and will make use of this functionality. - - - - - 94a87d21 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add I/O manager API notifyIOManagerCapabilitiesChanged Used in setNumCapabilities. It only does anything for MIO on Posix. Previously it always invoked Haskell code, but that code only did anything on non-Windows (and non-JS), and only threaded. That currently effectively means the MIO I/O manager on Posix. So now it only invokes it for the MIO Posix case. - - - - - 3be6d591 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Select an I/O manager early in RTS startup We need to select the I/O manager to use during startup before the per-cap I/O manager initialisation. - - - - - aaa294d0 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Make struct CapIOManager be fully opaque Provide an opaque (forward) definition in Capability.h (since the cap contains a *CapIOManager) and then only provide a full definition in a new file IOManagerInternals.h. This new file is only supposed to be included by the IOManager implementation, not by its users. So that means IOManager.c and individual I/O manager implementations. The posix/Signals.c still needs direct access, but that should be eliminated. Anything that needs direct access either needs to be clearly part of an I/O manager (e.g. the sleect() one) or go via a proper API. - - - - - 877a2a80 by Duncan Coutts at 2024-04-03T01:27:18-04:00 The select() I/O manager does have some global initialisation It's just to make sure an exception CAF is a GC root. - - - - - 9c51473b by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add tracing for the main I/O manager actions Using the new tracer class. Note: The unconditional definition of showIOManager should be compatible with the debugTrace change in 7c7d1f6. Co-authored-by: Pi Delport <pi at well-typed.com> - - - - - c7d3e3a3 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Include the default I/O manager in the +RTS --info output Document the extra +RTS --info output in the user guide - - - - - 8023bad4 by Duncan Coutts at 2024-04-03T01:27:18-04:00 waitRead# / waitWrite# do not work for win32-legacy I/O manager Previously it was unclear that they did not work because the code path was shared with other I/O managers (in particular select()). Following the code carefully shows that what actually happens is that the calling thread would block forever: the thread will be put into the blocked queue, but no other action is scheduled that will ever result in it getting unblocked. It's better to just fail loudly in case anyone accidentally calls it, also it's less confusing code. - - - - - 83a74d20 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Conditionally ignore some GCC warnings Some GCC versions don't know about some warnings, and they complain that we're ignoring unknown warnings. So we try to ignore the warning based on the GCC version. - - - - - 1adc6fa4 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Accept changes to base-exports All the changes are in fact not changes at all. Previously, the IoSubSystem data type was defined in GHC.RTS.Flags and exported from both GHC.RTS.Flags and GHC.IO.SubSystem. Now, the data type is defined in GHC.IO.SubSystem and still exported from both modules. Therefore, the same exports and same instances are still available from both modules. But the base-exports records only the defining module, and so it looks like a change when it is fully compatible. Related: we do add a deprecation to the export of the type via GHC.RTS.Flags, telling people to use the export from GHC.IO.SubSystem. Also the sort order for some unrelated Show instances changed. No idea why. The same changes apply in the other versions, with a few more changes due to sort order weirdness. - - - - - 8d950968 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Accept metric decrease in T12227 I can't think of any good reason that anything in this MR should have changed the number of allocations, up or down. (Yes this is an empty commit.) Metric Decrease: T12227 - - - - - e869605e by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Several improvements to the handling of coercions * Make `mkSymCo` and `mkInstCo` smarter Fixes #23642 * Fix return role of `SelCo` in the coercion optimiser. Fixes #23617 * Make the coercion optimiser `opt_trans_rule` work better for newtypes Fixes #23619 - - - - - 1efd0714 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 FloatOut: improve floating for join point See the new Note [Floating join point bindings]. * Completely get rid of the complicated join_ceiling nonsense, which I have never understood. * Do not float join points at all, except perhaps to top level. * Some refactoring around wantToFloat, to treat Rec and NonRec more uniformly - - - - - 9c00154d by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Improve eta-expansion through call stacks See Note [Eta expanding through CallStacks] in GHC.Core.Opt.Arity This is a one-line change, that fixes an inconsistency - || isCallStackPredTy ty + || isCallStackPredTy ty || isCallStackTy ty - - - - - 95a9a172 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Spelling, layout, pretty-printing only - - - - - bdf1660f by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Improve exprIsConApp_maybe a little Eliminate a redundant case at birth. This sometimes reduces Simplifier iterations. See Note [Case elim in exprIsConApp_maybe]. - - - - - 609cd32c by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Inline GHC.HsToCore.Pmc.Solver.Types.trvVarInfo When exploring compile-time regressions after meddling with the Simplifier, I discovered that GHC.HsToCore.Pmc.Solver.Types.trvVarInfo was very delicately balanced. It's a small, heavily used, overloaded function and it's important that it inlines. By a fluke it was before, but at various times in my journey it stopped doing so. So I just added an INLINE pragma to it; no sense in depending on a delicately-balanced fluke. - - - - - ae24c9bc by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Slight improvement in WorkWrap Ensure that WorkWrap preserves lambda binders, in case of join points. Sadly I have forgotten why I made this change (it was while I was doing a lot of meddling in the Simplifier, but * it does no harm, * it is slightly more efficient, and * presumably it made something better! Anyway I have kept it in a separate commit. - - - - - e9297181 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Use named record fields for the CastIt { ... } data constructor This is a pure refactor - - - - - b4581e23 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Remove a long-commented-out line Pure refactoring - - - - - e026bdf2 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Simplifier improvements This MR started as: allow the simplifer to do more in one pass, arising from places I could see the simplifier taking two iterations where one would do. But it turned into a larger project, because these changes unexpectedly made inlining blow up, especially join points in deeply-nested cases. The main changes are below. There are also many new or rewritten Notes. Avoiding simplifying repeatedly ~~~~~~~~~~~~~~~ See Note [Avoiding simplifying repeatedly] * The SimplEnv now has a seInlineDepth field, which says how deep in unfoldings we are. See Note [Inline depth] in Simplify.Env. Currently used only for the next point: avoiding repeatedly simplifying coercions. * Avoid repeatedly simplifying coercions. see Note [Avoid re-simplifying coercions] in Simplify.Iteration As you'll see from the Note, this makes use of the seInlineDepth. * Allow Simplify.Iteration.simplAuxBind to inline used-once things. This is another part of Note [Post-inline for single-use things], and is really good for reducing simplifier iterations in situations like case K e of { K x -> blah } wher x is used once in blah. * Make GHC.Core.SimpleOpt.exprIsConApp_maybe do some simple case elimination. Note [Case elim in exprIsConApp_maybe] * Improve the case-merge transformation: - Move the main code to `GHC.Core.Utils.mergeCaseAlts`, to join `filterAlts` and friends. See Note [Merge Nested Cases] in GHC.Core.Utils. - Add a new case for `tagToEnum#`; see wrinkle (MC3). - Add a new case to look through join points: see wrinkle (MC4) postInlineUnconditionally ~~~~~~~~~~~~~~~~~~~~~~~~~ * Allow Simplify.Utils.postInlineUnconditionally to inline variables that are used exactly once. See Note [Post-inline for single-use things]. * Do not postInlineUnconditionally join point, ever. Doing so does not reduce allocation, which is the main point, and with join points that are used a lot it can bloat code. See point (1) of Note [Duplicating join points] in GHC.Core.Opt.Simplify.Iteration. * Do not postInlineUnconditionally a strict (demanded) binding. It will not allocate a thunk (it'll turn into a case instead) so again the main point of inlining it doesn't hold. Better to check per-call-site. * Improve occurrence analyis for bottoming function calls, to help postInlineUnconditionally. See Note [Bottoming function calls] in GHC.Core.Opt.OccurAnal Inlining generally ~~~~~~~~~~~~~~~~~~ * In GHC.Core.Opt.Simplify.Utils.interestingCallContext, use RhsCtxt NonRecursive (not BoringCtxt) for a plain-seq case. See Note [Seq is boring] Also, wrinkle (SB1), inline in that `seq` context only for INLINE functions (UnfWhen guidance). * In GHC.Core.Opt.Simplify.Utils.interestingArg, - return ValueArg for OtherCon [c1,c2, ...], but - return NonTrivArg for OtherCon [] This makes a function a little less likely to inline if all we know is that the argument is evaluated, but nothing else. * isConLikeUnfolding is no longer true for OtherCon {}. This propagates to exprIsConLike. Con-like-ness has /positive/ information. Join points ~~~~~~~~~~~ * Be very careful about inlining join points. See these two long Notes Note [Duplicating join points] in GHC.Core.Opt.Simplify.Iteration Note [Inlining join points] in GHC.Core.Opt.Simplify.Inline * When making join points, don't do so if the join point is so small it will immediately be inlined; check uncondInlineJoin. * In GHC.Core.Opt.Simplify.Inline.tryUnfolding, improve the inlining heuristics for join points. In general we /do not/ want to inline join points /even if they are small/. See Note [Duplicating join points] GHC.Core.Opt.Simplify.Iteration. But sometimes we do: see Note [Inlining join points] in GHC.Core.Opt.Simplify.Inline; and the new `isBetterUnfoldingThan` function. * Do not add an unfolding to a join point at birth. This is a tricky one and has a long Note [Do not add unfoldings to join points at birth] It shows up in two places - In `mkDupableAlt` do not add an inlining - (trickier) In `simplLetUnfolding` don't add an unfolding for a fresh join point I am not fully satisifed with this, but it works and is well documented. * In GHC.Core.Unfold.sizeExpr, make jumps small, so that we don't penalise having a non-inlined join point. Performance changes ~~~~~~~~~~~~~~~~~~~ * Binary sizes fall by around 2.6%, according to nofib. * Compile times improve slightly. Here are the figures over 1%. I investiate the biggest differnce in T18304. It's a very small module, just a few hundred nodes. The large percentage difffence is due to a single function that didn't quite inline before, and does now, making code size a bit bigger. I decided gains outweighed the losses. Metrics: compile_time/bytes allocated (changes over +/- 1%) ------------------------------------------------ CoOpt_Singletons(normal) -9.2% GOOD LargeRecord(normal) -23.5% GOOD MultiComponentModulesRecomp(normal) +1.2% MultiLayerModulesTH_OneShot(normal) +4.1% BAD PmSeriesS(normal) -3.8% PmSeriesV(normal) -1.5% T11195(normal) -1.3% T12227(normal) -20.4% GOOD T12545(normal) -3.2% T12707(normal) -2.1% GOOD T13253(normal) -1.2% T13253-spj(normal) +8.1% BAD T13386(normal) -3.1% GOOD T14766(normal) -2.6% GOOD T15164(normal) -1.4% T15304(normal) +1.2% T15630(normal) -8.2% T15630a(normal) NEW T15703(normal) -14.7% GOOD T16577(normal) -2.3% GOOD T17516(normal) -39.7% GOOD T18140(normal) +1.2% T18223(normal) -17.1% GOOD T18282(normal) -5.0% GOOD T18304(normal) +10.8% BAD T18923(normal) -2.9% GOOD T1969(normal) +1.0% T19695(normal) -1.5% T20049(normal) -12.7% GOOD T21839c(normal) -4.1% GOOD T3064(normal) -1.5% T3294(normal) +1.2% BAD T4801(normal) +1.2% T5030(normal) -15.2% GOOD T5321Fun(normal) -2.2% GOOD T6048(optasm) -16.8% GOOD T783(normal) -1.2% T8095(normal) -6.0% GOOD T9630(normal) -4.7% GOOD T9961(normal) +1.9% BAD WWRec(normal) -1.4% info_table_map_perf(normal) -1.3% parsing001(normal) +1.5% geo. mean -2.0% minimum -39.7% maximum +10.8% * Runtimes generally improve. In the testsuite perf/should_run gives: Metrics: runtime/bytes allocated ------------------------------------------ Conversions(normal) -0.3% T13536a(optasm) -41.7% GOOD T4830(normal) -0.1% haddock.Cabal(normal) -0.1% haddock.base(normal) -0.1% haddock.compiler(normal) -0.1% geo. mean -0.8% minimum -41.7% maximum +0.0% * For runtime, nofib is a better test. The news is mostly good. Here are the number more than +/- 0.1%: # bytes allocated ==========================++========== imaginary/digits-of-e1 || -14.40% imaginary/digits-of-e2 || -4.41% imaginary/paraffins || -0.17% imaginary/rfib || -0.15% imaginary/wheel-sieve2 || -0.10% real/compress || -0.47% real/fluid || -0.10% real/fulsom || +0.14% real/gamteb || -1.47% real/gg || -0.20% real/infer || +0.24% real/pic || -0.23% real/prolog || -0.36% real/scs || -0.46% real/smallpt || +4.03% shootout/k-nucleotide || -20.23% shootout/n-body || -0.42% shootout/spectral-norm || -0.13% spectral/boyer2 || -3.80% spectral/constraints || -0.27% spectral/hartel/ida || -0.82% spectral/mate || -20.34% spectral/para || +0.46% spectral/rewrite || +1.30% spectral/sphere || -0.14% ==========================++========== geom mean || -0.59% real/smallpt has a huge nest of local definitions, and I could not pin down a reason for a regression. But there are three big wins! Metric Decrease: CoOpt_Singletons LargeRecord T12227 T12707 T13386 T13536a T14766 T15703 T16577 T17516 T18223 T18282 T18923 T21839c T20049 T5321Fun T5030 T6048 T8095 T9630 T783 Metric Increase: MultiLayerModulesTH_OneShot T13253-spj T18304 T18698a T9961 T3294 - - - - - 27db3c5e by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Testsuite message changes from simplifier improvements - - - - - 271a7812 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Account for bottoming functions in OccurAnal This fixes #24582, a small but long-standing bug - - - - - 0fde229f by Ben Gamari at 2024-04-04T07:04:58-04:00 testsuite: Introduce template-haskell-exports test - - - - - 0c4a9686 by Luite Stegeman at 2024-04-04T07:05:39-04:00 Update correct counter in bumpTickyAllocd - - - - - 5f085d3a by Fendor at 2024-04-04T14:47:33-04:00 Replace `SizedSeq` with `FlatBag` for flattened structure LinkedLists are notoriously memory ineffiecient when all we do is traversing a structure. As 'UnlinkedBCO' has been identified as a data structure that impacts the overall memory usage of GHCi sessions, we avoid linked lists and prefer flattened structure for storing. We introduce a new memory efficient representation of sequential elements that has special support for the cases: * Empty * Singleton * Tuple Elements This improves sharing in the 'Empty' case and avoids the overhead of 'Array' until its constant overhead is justified. - - - - - 82cfe10c by Fendor at 2024-04-04T14:47:33-04:00 Compact FlatBag array representation `Array` contains three additional `Word`'s we do not need in `FlatBag`. Move `FlatBag` to `SmallArray`. Expand the API of SmallArray by `sizeofSmallArray` and add common traversal functions, such as `mapSmallArray` and `foldMapSmallArray`. Additionally, allow users to force the elements of a `SmallArray` via `rnfSmallArray`. - - - - - 36a75b80 by Andrei Borzenkov at 2024-04-04T14:48:10-04:00 Change how invisible patterns represented in haskell syntax and TH AST (#24557) Before this patch: data ArgPat p = InvisPat (LHsType p) | VisPat (LPat p) With this patch: data Pat p = ... | InvisPat (LHsType p) ... And the same transformation in the TH land. The rest of the changes is just updating code to handle new AST and writing tests to check if it is possible to create invalid states using TH. Metric Increase: MultiLayerModulesTH_OneShot - - - - - 28009fbc by Matthew Pickering at 2024-04-04T14:48:46-04:00 Fix off by one error in seekBinNoExpand and seekBin - - - - - 9b9e031b by Ben Gamari at 2024-04-04T21:30:08-04:00 compiler: Allow more types in GHCForeignImportPrim For many, many years `GHCForeignImportPrim` has suffered from the rather restrictive limitation of not allowing any non-trivial types in arguments or results. This limitation was justified by the code generator allegely barfing in the presence of such types. However, this restriction appears to originate well before the NCG rewrite and the new NCG does not appear to have any trouble with such types (see the added `T24598` test). Lift this restriction. Fixes #24598. - - - - - 1324b862 by Alan Zimmerman at 2024-04-04T21:30:44-04:00 EPA: Use EpaLocation not SrcSpan in ForeignDecls This allows us to update them for makeDeltaAst in ghc-exactprint - - - - - 19883a23 by Alan Zimmerman at 2024-04-05T16:58:17-04:00 EPA: Use EpaLocation for RecFieldsDotDot So we can update it to a delta position in makeDeltaAst if needed. - - - - - e8724327 by Matthew Pickering at 2024-04-05T16:58:53-04:00 Remove accidentally committed test.hs - - - - - 88cb3e10 by Fendor at 2024-04-08T09:03:34-04:00 Avoid UArray when indexing is not required `UnlinkedBCO`'s can occur many times in the heap. Each `UnlinkedBCO` references two `UArray`'s but never indexes them. They are only needed to encode the elements into a `ByteArray#`. The three words for the lower bound, upper bound and number of elements are essentially unused, thus we replace `UArray` with a wrapper around `ByteArray#`. This saves us up to three words for each `UnlinkedBCO`. Further, to avoid re-allocating these words for `ResolvedBCO`, we repeat the procedure for `ResolvedBCO` and add custom `Binary` and `Show` instances. For example, agda's repl session has around 360_000 UnlinkedBCO's, so avoiding these three words is already saving us around 8MB residency. - - - - - f2cc1107 by Fendor at 2024-04-08T09:04:11-04:00 Never UNPACK `FastMutInt` for counting z-encoded `FastString`s In `FastStringTable`, we count the number of z-encoded FastStrings that exist in a GHC session. We used to UNPACK the counters to not waste memory, but live retainer analysis showed that we allocate a lot of `FastMutInt`s, retained by `mkFastZString`. We lazily compute the `FastZString`, only incrementing the counter when the `FastZString` is forced. The function `mkFastStringWith` calls `mkZFastString` and boxes the `FastMutInt`, leading to the following core: mkFastStringWith = \ mk_fs _ -> = case stringTable of { FastStringTable _ n_zencs segments# _ -> ... case ((mk_fs (I# ...) (FastMutInt n_zencs)) `cast` <Co:2> :: ...) ... Marking this field as `NOUNPACK` avoids this reboxing, eliminating the allocation of a fresh `FastMutInt` on every `FastString` allocation. - - - - - c6def949 by Matthew Pickering at 2024-04-08T16:06:51-04:00 Force in_multi to avoid retaining entire hsc_env - - - - - fbb91a63 by Fendor at 2024-04-08T16:06:51-04:00 Eliminate name thunk in declaration fingerprinting Thunk analysis showed that we have about 100_000 thunks (in agda and `-fwrite-simplified-core`) pointing to the name of the name decl. Forcing this thunk fixes this issue. The thunk created here is retained by the thunk created by forkM, it is better to eagerly force this because the result (a `Name`) is already retained indirectly via the `IfaceDecl`. - - - - - 3b7b0c1c by Alan Zimmerman at 2024-04-08T16:07:27-04:00 EPA: Use EpaLocation in WarningTxt This allows us to use an EpDelta if needed when using makeDeltaAst. - - - - - 12b997df by Alan Zimmerman at 2024-04-08T16:07:27-04:00 EPA: Move DeltaPos and EpaLocation' into GHC.Types.SrcLoc This allows us to use a NoCommentsLocation for the possibly trailing comma location in a StringLiteral. This in turn allows us to correctly roundtrip via makeDeltaAst. - - - - - 868c8a78 by Fendor at 2024-04-09T08:51:50-04:00 Prefer packed representation for CompiledByteCode As there are many 'CompiledByteCode' objects alive during a GHCi session, representing its element in a more packed manner improves space behaviour at a minimal cost. When running GHCi on the agda codebase, we find around 380 live 'CompiledByteCode' objects. Packing their respective 'UnlinkedByteCode' can save quite some pointers. - - - - - be3bddde by Alan Zimmerman at 2024-04-09T08:52:26-04:00 EPA: Capture all comments in a ClassDecl Hopefully the final fix needed for #24533 - - - - - 3d0806fc by Jade at 2024-04-10T05:39:53-04:00 Validate -main-is flag using parseIdentifier Fixes #24368 - - - - - dd530bb7 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 rts: free error message before returning Fixes a memory leak in rts/linker/PEi386.c - - - - - e008a19a by Alexis King at 2024-04-10T05:40:29-04:00 linker: Avoid linear search when looking up Haskell symbols via dlsym See the primary Note [Looking up symbols in the relevant objects] for a more in-depth explanation. When dynamically loading a Haskell symbol (typical when running a splice or GHCi expression), before this commit we would search for the symbol in all dynamic libraries that were loaded. However, this could be very inefficient when too many packages are loaded (which can happen if there are many package dependencies) because the time to lookup the would be linear in the number of packages loaded. This commit drastically improves symbol loading performance by introducing a mapping from units to the handles of corresponding loaded dlls. These handles are returned by dlopen when we load a dll, and can then be used to look up in a specific dynamic library. Looking up a given Name is now much more precise because we can get lookup its unit in the mapping and lookup the symbol solely in the handles of the dynamic libraries loaded for that unit. In one measurement, the wait time before the expression was executed went from +-38 seconds down to +-2s. This commit also includes Note [Symbols may not be found in pkgs_loaded], explaining the fallback to the old behaviour in case no dll can be found in the unit mapping for a given Name. Fixes #23415 Co-authored-by: Rodrigo Mesquita (@alt-romes) - - - - - dcfaa190 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 rts: Make addDLL a wrapper around loadNativeObj Rewrite the implementation of `addDLL` as a wrapper around the more principled `loadNativeObj` rts linker function. The latter should be preferred while the former is preserved for backwards compatibility. `loadNativeObj` was previously only available on ELF platforms, so this commit further refactors the rts linker to transform loadNativeObj_ELF into loadNativeObj_POSIX, which is available in ELF and MachO platforms. The refactor made it possible to remove the `dl_mutex` mutex in favour of always using `linker_mutex` (rather than a combination of both). Lastly, we implement `loadNativeObj` for Windows too. - - - - - 12931698 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 Use symbol cache in internal interpreter too This commit makes the symbol cache that was used by the external interpreter available for the internal interpreter too. This follows from the analysis in #23415 that suggests the internal interpreter could benefit from this cache too, and that there is no good reason not to have the cache for it too. It also makes it a bit more uniform to have the symbol cache range over both the internal and external interpreter. This commit also refactors the cache into a function which is used by both `lookupSymbol` and also by `lookupSymbolInDLL`, extending the caching logic to `lookupSymbolInDLL` too. - - - - - dccd3ea1 by Ben Gamari at 2024-04-10T05:40:29-04:00 testsuite: Add test for lookupSymbolInNativeObj - - - - - 1b1a92bd by Alan Zimmerman at 2024-04-10T05:41:05-04:00 EPA: Remove unnecessary XRec in CompleteMatchSig The XRec for [LIdP pass] is not needed for exact printing, remove it. - - - - - 6e18ce2b by Ben Gamari at 2024-04-12T08:16:09-04:00 users-guide: Clarify language extension documentation Over the years the users guide's language extension documentation has gone through quite a few refactorings. In the process some of the descriptions have been rendered non-sensical. For instance, the description of `NoImplicitPrelude` actually describes the semantics of `ImplicitPrelude`. To fix this we: * ensure that all extensions are named in their "positive" sense (e.g. `ImplicitPrelude` rather than `NoImplicitPrelude`). * rework the documentation to avoid flag-oriented wording like "enable" and "disable" * ensure that the polarity of the documentation is consistent with reality. Fixes #23895. - - - - - a933aff3 by Zubin Duggal at 2024-04-12T08:16:45-04:00 driver: Make `checkHomeUnitsClosed` faster The implementation of `checkHomeUnitsClosed` was traversing every single path in the unit dependency graph - this grows exponentially and quickly grows to be infeasible on larger unit dependency graphs. Instead we replace this with a faster implementation which follows from the specificiation of the closure property - there is a closure error if there are units which are both are both (transitively) depended upon by home units and (transitively) depend on home units, but are not themselves home units. To compute the set of units required for closure, we first compute the closure of the unit dependency graph, then the transpose of this closure, and find all units that are reachable from the home units in the transpose of the closure. - - - - - 23c3e624 by Andreas Klebinger at 2024-04-12T08:17:21-04:00 RTS: Emit warning when -M < -H Fixes #24487 - - - - - d23afb8c by Ben Gamari at 2024-04-12T08:17:56-04:00 testsuite: Add broken test for CApiFFI with -fprefer-bytecode See #24634. - - - - - a4bb3a51 by Ben Gamari at 2024-04-12T08:18:32-04:00 base: Deprecate GHC.Pack As proposed in #21461. Closes #21540. - - - - - 55eb8c98 by Ben Gamari at 2024-04-12T08:19:08-04:00 ghc-internal: Fix mentions of ghc-internal in deprecation warnings Closes #24609. - - - - - b0fbd181 by Ben Gamari at 2024-04-12T08:19:44-04:00 rts: Implement set_initial_registers for AArch64 Fixes #23680. - - - - - 14c9ec62 by Ben Gamari at 2024-04-12T08:20:20-04:00 ghcup-metadata: Use Debian 9 binaries on Ubuntu 16, 17 Closes #24646. - - - - - 35a1621e by Ben Gamari at 2024-04-12T08:20:55-04:00 Bump unix submodule to 2.8.5.1 Closes #24640. - - - - - a1c24df0 by Finley McIlwaine at 2024-04-12T08:21:31-04:00 Correct default -funfolding-use-threshold in docs - - - - - 0255d03c by Oleg Grenrus at 2024-04-12T08:22:07-04:00 FastString is a __Modified__ UTF-8 - - - - - c3489547 by Matthew Pickering at 2024-04-12T13:13:44-04:00 rts: Improve tracing message when nursery is resized It is sometimes more useful to know how much bigger or smaller the nursery got when it is resized. In particular I am trying to investigate situations where we end up with fragmentation due to the nursery (#24577) - - - - - 5e4f4ba8 by Simon Peyton Jones at 2024-04-12T13:14:20-04:00 Don't generate wrappers for `type data` constructors with StrictData Previously, the logic for checking if a data constructor needs a wrapper or not would take into account whether the constructor's fields have explicit strictness (e.g., `data T = MkT !Int`), but the logic would _not_ take into account whether `StrictData` was enabled. This meant that something like `type data T = MkT Int` would incorrectly generate a wrapper for `MkT` if `StrictData` was enabled, leading to the horrible errors seen in #24620. To fix this, we disable generating wrappers for `type data` constructors altogether. Fixes #24620. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - dbdf1995 by Alex Mason at 2024-04-15T15:28:26+10:00 Implements MO_S_Mul2 and MO_U_Mul2 using the UMULH, UMULL and SMULH instructions for AArch64 Also adds a test for MO_S_Mul2 - - - - - 42bd0407 by Teo Camarasu at 2024-04-16T20:06:39-04:00 Make template-haskell a stage1 package Promoting template-haskell from a stage0 to a stage1 package means that we can much more easily refactor template-haskell. We implement this by duplicating the in-tree `template-haskell`. A new `template-haskell-next` library is autogenerated to mirror `template-haskell` `stage1:ghc` to depend on the new interface of the library including the `Binary` instances without adding an explicit dependency on `template-haskell`. This is controlled by the `bootstrap-th` cabal flag When building `template-haskell` modules as part of this vendoring we do not have access to quote syntax, so we cannot use variable quote notation (`'Just`). So we either replace these with hand-written `Name`s or hide the code behind CPP. We can remove the `th_hack` from hadrian, which was required when building stage0 packages using the in-tree `template-haskell` library. For more details see Note [Bootstrapping Template Haskell]. Resolves #23536 Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> Co-Authored-By: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org> - - - - - 3d973e47 by Ben Gamari at 2024-04-16T20:07:15-04:00 Bump parsec submodule to 3.1.17.0 - - - - - 9d38bfa0 by Simon Peyton Jones at 2024-04-16T20:07:51-04:00 Clone CoVars in CorePrep This MR addresses #24463. It's all explained in the new Note [Cloning CoVars and TyVars] - - - - - 0fe2b410 by Andreas Klebinger at 2024-04-16T20:08:27-04:00 NCG: Fix a bug where we errounously removed a required jump instruction. Add a new method to the Instruction class to check if we can eliminate a jump in favour of fallthrough control flow. Fixes #24507 - - - - - 9f99126a by Teo Camarasu at 2024-04-16T20:09:04-04:00 Fix documentation preview from doc-tarball job - Include all the .html files and assets in the job artefacts - Include all the .pdf files in the job artefacts - Mark the artefact as an "exposed" artefact meaning it turns up in the UI. Resolves #24651 - - - - - 3a0642ea by Ben Gamari at 2024-04-16T20:09:39-04:00 rts: Ignore EINTR while polling in timerfd itimer implementation While the RTS does attempt to mask signals, it may be that a foreign library unmasks them. This previously caused benign warnings which we now ignore. See #24610. - - - - - 9a53cd3f by Alan Zimmerman at 2024-04-16T20:10:15-04:00 EPA: Add additional comments field to AnnsModule This is used in exact printing to store comments coming after the `where` keyword but before any comments allocated to imports or decls. It is used in ghc-exactprint, see https://github.com/alanz/ghc-exactprint/commit/44bbed311fd8f0d053053fef195bf47c17d34fa7 - - - - - e5c43259 by Bryan Richter at 2024-04-16T20:10:51-04:00 Remove unrunnable FreeBSD CI jobs FreeBSD runner supply is inelastic. Currently there is only one, and it's unavailable because of a hardware issue. - - - - - 914eb49a by Ben Gamari at 2024-04-16T20:11:27-04:00 rel-eng: Fix mktemp usage in recompress-all We need a temporary directory, not a file. - - - - - f30e4984 by Teo Camarasu at 2024-04-16T20:12:03-04:00 Fix ghc API link in docs/index.html This was missing part of the unit ID meaning it would 404. Resolves #24674 - - - - - d7a3d6b5 by Ben Gamari at 2024-04-16T20:12:39-04:00 template-haskell: Declare TH.Lib.Internal as not-home Rather than `hide`. Closes #24659. - - - - - 5eaa46e7 by Matthew Pickering at 2024-04-19T02:14:55-04:00 testsuite: Rename isCross() predicate to needsTargetWrapper() isCross() was a misnamed because it assumed that all cross targets would provide a target wrapper, but the two most common cross targets (javascript, wasm) don't need a target wrapper. Therefore we rename this predicate to `needsTargetWrapper()` so situations in the testsuite where we can check whether running executables requires a target wrapper or not. - - - - - 55a9d699 by Simon Peyton Jones at 2024-04-19T02:15:32-04:00 Do not float HNFs out of lambdas This MR adjusts SetLevels so that it is less eager to float a HNF (lambda or constructor application) out of a lambda, unless it gets to top level. Data suggests that this change is a small net win: * nofib bytes-allocated falls by -0.09% (but a couple go up) * perf/should_compile bytes-allocated falls by -0.5% * perf/should_run bytes-allocated falls by -0.1% See !12410 for more detail. When fiddling elsewhere, I also found that this patch had a huge positive effect on the (very delicate) test perf/should_run/T21839r But that improvement doesn't show up in this MR by itself. Metric Decrease: MultiLayerModulesRecomp T15703 parsing001 - - - - - f0701585 by Alan Zimmerman at 2024-04-19T02:16:08-04:00 EPA: Fix comments in mkListSyntaxTy0 Also extend the test to confirm. Addresses #24669, 1 of 4 - - - - - b01c01d4 by Serge S. Gulin at 2024-04-19T02:16:51-04:00 JS: set image `x86_64-linux-deb11-emsdk-closure` for build - - - - - c90c6039 by Alan Zimmerman at 2024-04-19T02:17:27-04:00 EPA: Provide correct span for PatBind And remove unused parameter in checkPatBind Contributes to #24669 - - - - - bee54c24 by Krzysztof Gogolewski at 2024-04-19T11:13:00+02:00 Update quantification order following GHC haskell/haddock#23764 - - - - - 2814eb89 by Ben Gamari at 2024-04-19T18:57:05+02:00 hypsrc-test: Fix output of PositionPragmas.html - - - - - 26036f96 by Alan Zimmerman at 2024-04-19T13:11:08-04:00 EPA: Fix span for PatBuilderAppType Include the location of the prefix @ in the span for InVisPat. Also removes unnecessary annotations from HsTP. Contributes to #24669 - - - - - dba03aab by Matthew Craven at 2024-04-19T13:11:44-04:00 testsuite: Give the pre_cmd for mhu-perf more time - - - - - d31fbf6c by Krzysztof Gogolewski at 2024-04-19T21:04:09-04:00 Fix quantification order for a `op` b and a %m -> b Fixes #23764 Implements https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0640-tyop-quantification-order.rst Updates haddock submodule. - - - - - 385cd1c4 by Sebastian Graf at 2024-04-19T21:04:45-04:00 Make `seq#` a magic Id and inline it in CorePrep (#24124) We can save much code and explanation in Tag Inference and StgToCmm by making `seq#` a known-key Magic Id in `GHC.Internal.IO` and inline this definition in CorePrep. See the updated `Note [seq# magic]`. I also implemented a new `Note [Flatten case-bind]` to get better code for otherwise nested case scrutinees. I renamed the contructors of `ArgInfo` to use an `AI` prefix in order to resolve the clash between `type CpeApp = CoreExpr` and the data constructor of `ArgInfo`, as well as fixed typos in `Note [CorePrep invariants]`. Fixes #24252 and #24124. - - - - - 275e41a9 by Jade at 2024-04-20T11:10:40-04:00 Put the newline after errors instead of before them This mainly has consequences for GHCi but also slightly alters how the output of GHC on the commandline looks. Fixes: #22499 - - - - - dd339c7a by Teo Camarasu at 2024-04-20T11:11:16-04:00 Remove unecessary stage0 packages Historically quite a few packages had to be stage0 as they depended on `template-haskell` and that was stage0. In #23536 we made it so that was no longer the case. This allows us to remove a bunch of packages from this list. A few still remain. A new version of `Win32` is required by `semaphore-compat`. Including `Win32` in the stage0 set requires also including `filepath` because otherwise Hadrian's dependency logic gets confused. Once our boot compiler has a newer version of `Win32` all of these will be able to be dropped. Resolves #24652 - - - - - 2f8e3a25 by Alan Zimmerman at 2024-04-20T11:11:52-04:00 EPA: Avoid duplicated comments in splice decls Contributes to #24669 - - - - - c70b9ddb by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: fix typos and namings (fixes #24602) You may noted that I've also changed term of ``` , global "h$vt_double" ||= toJExpr IntV ``` See "IntV" and ``` WaitReadOp -> \[] [fd] -> pure $ PRPrimCall $ returnS (app "h$waidRead" [fd]) ``` See "h$waidRead" - - - - - 3db54f9b by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: trivial checks for variable presence (fixes #24602) - - - - - 777f108f by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: fs module imported twice (by emscripten and by ghc-internal). ghc-internal import wrapped in a closure to prevent conflict with emscripten (fixes #24602) Better solution is to use some JavaScript module system like AMD, CommonJS or even UMD. It will be investigated at other issues. At first glance we should try UMD (See https://github.com/umdjs/umd) - - - - - a45a5712 by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: thread.js requires h$fds and h$fdReady to be declared for static code analysis, minimal code copied from GHCJS (fixes #24602) I've just copied some old pieces of GHCJS from publicly available sources (See https://github.com/Taneb/shims/blob/a6dd0202dcdb86ad63201495b8b5d9763483eb35/src/io.js#L607). Also I didn't put details to h$fds. I took minimal and left only its object initialization: `var h$fds = {};` - - - - - ad90bf12 by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: heap and stack overflows reporting defined as js hard failure (fixes #24602) These errors were treated as a hard failure for browser application. The fix is trivial: just throw error. - - - - - 5962fa52 by Serge S. Gulin at 2024-04-21T16:33:44+03:00 JS: Stubs for code without actual implementation detected by Google Closure Compiler (fixes #24602) These errors were fixed just by introducing stubbed functions with throw for further implementation. - - - - - a0694298 by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Add externs to linker (fixes #24602) After enabling jsdoc and built-in google closure compiler types I was needed to deal with the following: 1. Define NodeJS-environment types. I've just copied minimal set of externs from semi-official repo (see https://github.com/externs/nodejs/blob/6c6882c73efcdceecf42e7ba11f1e3e5c9c041f0/v8/nodejs.js#L8). 2. Define Emscripten-environment types: `HEAP8`. Emscripten already provides some externs in our code but it supposed to be run in some module system. And its definitions do not work well in plain bundle. 3. We have some functions which purpose is to add to functions some contextual information via function properties. These functions should be marked as `modifies` to let google closure compiler remove calls if these functions are not used actually by call graph. Such functions are: `h$o`, `h$sti`, `h$init_closure`, `h$setObjInfo`. 4. STG primitives such as registries and stuff from `GHC.StgToJS`. `dXX` properties were already present at externs generator function but they are started from `7`, not from `1`. This message is related: `// fixme does closure compiler bite us here?` - - - - - e58bb29f by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: added both tests: for size and for correctness (fixes #24602) By some reason MacOS builds add to stderr messages like: Ignoring unexpected archive entry: __.SYMDEF ... However I left stderr to `/dev/null` for compatibility with linux CI builds. - - - - - 909f3a9c by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Disable js linker warning for empty symbol table to make js tests running consistent across environments - - - - - 83eb10da by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Add special preprocessor for js files due of needing to keep jsdoc comments (fixes #24602) Our js files have defined google closure compiler types at jsdoc entries but these jsdoc entries are removed by cpp preprocessor. I considered that reusing them in javascript-backend would be a nice thing. Right now haskell processor uses `-traditional` option to deal with comments and `//` operators. But now there are following compiler options: `-C` and `-CC`. You can read about them at GCC (see https://gcc.gnu.org/onlinedocs/gcc/Preprocessor-Options.html#index-CC) and CLang (see https://clang.llvm.org/docs/ClangCommandLineReference.html#cmdoption-clang-CC). It seems that `-CC` works better for javascript jsdoc than `-traditional`. At least it leaves `/* ... */` comments w/o changes. - - - - - e1cf8dc2 by brandon s allbery kf8nh at 2024-04-22T03:48:26-04:00 fix link in CODEOWNERS It seems that our local Gitlab no longer has documentation for the `CODEOWNERS` file, but the master documentation still does. Use that instead. - - - - - a27c6a49 by Fendor at 2024-04-22T10:13:03+02:00 Adapt to UserData split - - - - - 1efc5a7a by Fendor at 2024-04-22T10:13:03+02:00 Adapt to BinHandle split - - - - - 593f4e04 by Fendor at 2024-04-23T10:19:14-04:00 Add performance regression test for '-fwrite-simplified-core' - - - - - 1ba39b05 by Fendor at 2024-04-23T10:19:14-04:00 Typecheck corebindings lazily during bytecode generation This delays typechecking the corebindings until the bytecode generation happens. We also avoid allocating a thunk that is retained by `unsafeInterleaveIO`. In general, we shouldn't retain values of the hydrated `Type`, as not evaluating the bytecode object keeps it alive. It is better if we retain the unhydrated `IfaceType`. See Note [Hydrating Modules] - - - - - e916fc92 by Alan Zimmerman at 2024-04-23T10:19:50-04:00 EPA: Keep comments in a CaseAlt match The comments now live in the surrounding location, not inside the Match. Make sure we keep them. Closes #24707 - - - - - d2b17f32 by Cheng Shao at 2024-04-23T15:01:22-04:00 driver: force merge objects when building dynamic objects This patch forces the driver to always merge objects when building dynamic objects even when ar -L is supported. It is an oversight of !8887: original rationale of that patch is favoring the relatively cheap ar -L operation over object merging when ar -L is supported, which makes sense but only if we are building static objects! Omitting check for whether we are building dynamic objects will result in broken .so files with undefined reference errors at executable link time when building GHC with llvm-ar. Fixes #22210. - - - - - 209d09f5 by Julian Ospald at 2024-04-23T15:02:03-04:00 Allow non-absolute values for bootstrap GHC variable Fixes #24682 - - - - - 3fff0977 by Matthew Pickering at 2024-04-23T15:02:38-04:00 Don't depend on registerPackage function in Cabal More recent versions of Cabal modify the behaviour of libAbiHash which breaks our usage of registerPackage. It is simpler to inline the part of registerPackage that we need and avoid any additional dependency and complication using the higher-level function introduces. - - - - - c62dc317 by Cheng Shao at 2024-04-25T01:32:02-04:00 ghc-bignum: remove obsolete ln script This commit removes an obsolete ln script in ghc-bignum/gmp. See 060251c24ad160264ae8553efecbb8bed2f06360 for its original intention, but it's been obsolete for a long time, especially since the removal of the make build system. Hence the house cleaning. - - - - - 6399d52b by Cheng Shao at 2024-04-25T01:32:02-04:00 ghc-bignum: update gmp to 6.3.0 This patch bumps the gmp-tarballs submodule and updates gmp to 6.3.0. The tarball format is now xz, and gmpsrc.patch has been patched into the tarball so hadrian no longer needs to deal with patching logic when building in-tree GMP. - - - - - 65b4b92f by Cheng Shao at 2024-04-25T01:32:02-04:00 hadrian: remove obsolete Patch logic This commit removes obsolete Patch logic from hadrian, given we no longer need to patch the gmp tarball when building in-tree GMP. - - - - - 71f28958 by Cheng Shao at 2024-04-25T01:32:02-04:00 autoconf: remove obsolete patch detection This commit removes obsolete deletection logic of the patch command from autoconf scripts, given we no longer need to patch anything in the GHC build process. - - - - - daeda834 by Sylvain Henry at 2024-04-25T01:32:43-04:00 JS: correctly handle RUBBISH literals (#24664) - - - - - 8a06ddf6 by Matthew Pickering at 2024-04-25T11:16:16-04:00 Linearise ghc-internal and base build This is achieved by requesting the final package database for ghc-internal, which mandates it is fully built as a dependency of configuring the `base` package. This is at the expense of cross-package parrallelism between ghc-internal and the base package. Fixes #24436 - - - - - 94da9365 by Andrei Borzenkov at 2024-04-25T11:16:54-04:00 Fix tuple puns renaming (24702) Move tuple renaming short cutter from `isBuiltInOcc_maybe` to `isPunOcc_maybe`, so we consider incoming module. I also fixed some hidden bugs that raised after the change was done. - - - - - fa03b1fb by Fendor at 2024-04-26T18:03:13-04:00 Refactor the Binary serialisation interface The goal is simplifiy adding deduplication tables to `ModIface` interface serialisation. We identify two main points of interest that make this difficult: 1. UserData hardcodes what `Binary` instances can have deduplication tables. Moreover, it heavily uses partial functions. 2. GHC.Iface.Binary hardcodes the deduplication tables for 'Name' and 'FastString', making it difficult to add more deduplication. Instead of having a single `UserData` record with fields for all the types that can have deduplication tables, we allow to provide custom serialisers for any `Typeable`. These are wrapped in existentials and stored in a `Map` indexed by their respective `TypeRep`. The `Binary` instance of the type to deduplicate still needs to explicitly look up the decoder via `findUserDataReader` and `findUserDataWriter`, which is no worse than the status-quo. `Map` was chosen as microbenchmarks indicate it is the fastest for a small number of keys (< 10). To generalise the deduplication table serialisation mechanism, we introduce the types `ReaderTable` and `WriterTable` which provide a simple interface that is sufficient to implement a general purpose deduplication mechanism for `writeBinIface` and `readBinIface`. This allows us to provide a list of deduplication tables for serialisation that can be extended more easily, for example for `IfaceTyCon`, see the issue https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for more motivation. In addition to this refactoring, we split `UserData` into `ReaderUserData` and `WriterUserData`, to avoid partial functions and reduce overall memory usage, as we need fewer mutable variables. Bump haddock submodule to accomodate for `UserData` split. ------------------------- Metric Increase: MultiLayerModulesTH_Make MultiLayerModulesRecomp T21839c ------------------------- - - - - - bac57298 by Fendor at 2024-04-26T18:03:13-04:00 Split `BinHandle` into `ReadBinHandle` and `WriteBinHandle` A `BinHandle` contains too much information for reading data. For example, it needs to keep a `FastMutInt` and a `IORef BinData`, when the non-mutable variants would suffice. Additionally, this change has the benefit that anyone can immediately tell whether the `BinHandle` is used for reading or writing. Bump haddock submodule BinHandle split. - - - - - 4d6394dd by Simon Peyton Jones at 2024-04-26T18:03:49-04:00 Fix missing escaping-kind check in tcPatSynSig Note [Escaping kind in type signatures] explains how we deal with escaping kinds in type signatures, e.g. f :: forall r (a :: TYPE r). a where the kind of the body is (TYPE r), but `r` is not in scope outside the forall-type. I had missed this subtlety in tcPatSynSig, leading to #24686. This MR fixes it; and a similar bug in tc_top_lhs_type. (The latter is tested by T24686a.) - - - - - 981c2c2c by Alan Zimmerman at 2024-04-26T18:04:25-04:00 EPA: check-exact: check that the roundtrip reproduces the source Closes #24670 - - - - - a8616747 by Andrew Lelechenko at 2024-04-26T18:05:01-04:00 Document that setEnv is not thread-safe - - - - - 1e41de83 by Bryan Richter at 2024-04-26T18:05:37-04:00 CI: Work around frequent Signal 9 errors - - - - - a6d5f9da by Naïm Favier at 2024-04-27T17:52:40-04:00 ghc-internal: add MonadFix instance for (,) Closes https://gitlab.haskell.org/ghc/ghc/-/issues/24288, implements CLC proposal https://github.com/haskell/core-libraries-committee/issues/238. Adds a MonadFix instance for tuples, permitting value recursion in the "native" writer monad and bringing consistency with the existing instance for transformers's WriterT (and, to a lesser extent, for Solo). - - - - - 64feadcd by Rodrigo Mesquita at 2024-04-27T17:53:16-04:00 bindist: Fix xattr cleaning The original fix (725343aa) was incorrect because it used the shell bracket syntax which is the quoting syntax in autoconf, making the test for existence be incorrect and therefore `xattr` was never run. Fixes #24554 - - - - - e2094df3 by damhiya at 2024-04-28T23:52:00+09:00 Make read accepts binary integer formats CLC proposal : https://github.com/haskell/core-libraries-committee/issues/177 - - - - - c62239b7 by Sylvain Henry at 2024-04-29T10:35:00+02:00 Fix tests for T22229 - - - - - 1c2fd963 by Alan Zimmerman at 2024-04-29T23:17:00-04:00 EPA: Preserve comments in Match Pats Closes #24708 Closes #24715 Closes #24734 - - - - - 4189d17e by Sylvain Henry at 2024-04-29T23:17:42-04:00 LLVM: better unreachable default destination in Switch (#24717) See added note. Co-authored-by: Siddharth Bhat <siddu.druid at gmail.com> - - - - - a3725c88 by Cheng Shao at 2024-04-29T23:18:20-04:00 ci: enable wasm jobs for MRs with wasm label This patch enables wasm jobs for MRs with wasm label. Previously the wasm label didn't actually have any effect on the CI pipeline, and full-ci needed to be applied to run wasm jobs which was a waste of runners when working on the wasm backend, hence the fix here. - - - - - 702f7964 by Matthew Pickering at 2024-04-29T23:18:56-04:00 Make interface files and object files depend on inplace .conf file A potential fix for #24737 - - - - - 728af21e by Cheng Shao at 2024-04-30T05:30:23-04:00 utils: remove obsolete vagrant scripts Vagrantfile has long been removed in !5288. This commit further removes the obsolete vagrant scripts in the tree. - - - - - 36f2c342 by Cheng Shao at 2024-04-30T05:31:00-04:00 Update autoconf scripts Scripts taken from autoconf 948ae97ca5703224bd3eada06b7a69f40dd15a02 - - - - - ecbf22a6 by Ben Gamari at 2024-04-30T05:31:36-04:00 ghcup-metadata: Drop output_name field This is entirely redundant to the filename of the URL. There is no compelling reason to name the downloaded file differently from its source. - - - - - c56d728e by Zubin Duggal at 2024-04-30T22:45:09-04:00 testsuite: Handle exceptions in framework_fail when testdir is not initialised When `framework_fail` is called before initialising testdir, it would fail with an exception reporting the testdir not being initialised instead of the actual failure. Ensure we report the actual reason for the failure instead of failing in this way. One way this can manifest is when trying to run a test that doesn't exist using `--only` - - - - - d5bea4d6 by Alan Zimmerman at 2024-04-30T22:45:45-04:00 EPA: Fix range for GADT decl with sig only Closes #24714 - - - - - 4d78c53c by Sylvain Henry at 2024-05-01T17:23:06-04:00 Fix TH dependencies (#22229) Add a dependency between Syntax and Internal (via module reexport). - - - - - 37e38db4 by Sylvain Henry at 2024-05-01T17:23:06-04:00 Bump haddock submodule - - - - - ca13075c by Sylvain Henry at 2024-05-01T17:23:47-04:00 JS: cleanup to prepare for #24743 - - - - - 40026ac3 by Alan Zimmerman at 2024-05-01T22:45:07-04:00 EPA: Preserve comments for PrefixCon Preserve comments in fun (Con {- c1 -} a b) = undefined Closes #24736 - - - - - 92134789 by Hécate Moonlight at 2024-05-01T22:45:42-04:00 Correct `@since` metadata in HpcFlags It was introduced in base-4.20, not 4.22. Fix #24721 - - - - - a580722e by Cheng Shao at 2024-05-02T08:18:45-04:00 testsuite: fix req_target_smp predicate - - - - - ac9c5f84 by Andreas Klebinger at 2024-05-02T08:18:45-04:00 STM: Remove (unused)coarse grained locking. The STM code had a coarse grained locking mode guarded by #defines that was unused. This commit removes the code. - - - - - 917ef81b by Andreas Klebinger at 2024-05-02T08:18:45-04:00 STM: Be more optimistic when validating in-flight transactions. * Don't lock tvars when performing non-committal validation. * If we encounter a locked tvar don't consider it a failure. This means in-flight validation will only fail if committing at the moment of validation is *guaranteed* to fail. This prevents in-flight validation from failing spuriously if it happens in parallel on multiple threads or parallel to thread comitting. - - - - - 167a56a0 by Alan Zimmerman at 2024-05-02T08:19:22-04:00 EPA: fix span for empty \case(s) In instance SDecide Nat where SZero %~ (SSucc _) = Disproved (\case) Ensure the span for the HsLam covers the full construct. Closes #24748 - - - - - 9bae34d8 by doyougnu at 2024-05-02T15:41:08-04:00 testsuite: expand size testing infrastructure - closes #24191 - adds windows_skip, wasm_skip, wasm_arch, find_so, _find_so - path_from_ghcPkg, collect_size_ghc_pkg, collect_object_size, find_non_inplace functions to testsuite - adds on_windows and req_dynamic_ghc predicate to testsuite The design is to not make the testsuite too smart and simply offload to ghc-pkg for locations of object files and directories. - - - - - b85b1199 by Sylvain Henry at 2024-05-02T15:41:49-04:00 GHCi: support inlining breakpoints (#24712) When a breakpoint is inlined, its context may change (e.g. tyvars in scope). We must take this into account and not used the breakpoint tick index as its sole identifier. Each instance of a breakpoint (even with the same tick index) now gets a different "info" index. We also need to distinguish modules: - tick module: module with the break array (tick counters, status, etc.) - info module: module having the CgBreakInfo (info at occurrence site) - - - - - 649c24b9 by Oleg Grenrus at 2024-05-03T20:45:42-04:00 Expose constructors of SNat, SChar and SSymbol in ghc-internal - - - - - d603f199 by Mikolaj Konarski at 2024-05-03T20:46:19-04:00 Add DCoVarSet to PluginProv (!12037) - - - - - ba480026 by Serge S. Gulin at 2024-05-03T20:47:01-04:00 JS: Enable more efficient packing of string data (fixes #24706) - - - - - be1e60ee by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Track in-scope variables in ruleCheckProgram This small patch fixes #24726, by tracking in-scope variables properly in -drule-check. Not hard to do! - - - - - 58408c77 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Add a couple more HasCallStack constraints in SimpleOpt Just for debugging, no effect on normal code - - - - - 70e245e8 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Add comments to Prep.hs This documentation patch fixes a TODO left over from !12364 - - - - - e5687186 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Use HasDebugCallStack, rather than HasCallStack - - - - - 631cefec by Cheng Shao at 2024-05-03T20:48:17-04:00 driver: always merge objects when possible This patch makes the driver always merge objects with `ld -r` when possible, and only fall back to calling `ar -L` when merge objects command is unavailable. This completely reverts !8887 and !12313, given more fixes in Cabal seems to be needed to avoid breaking certain configurations and the maintainence cost is exceeding the behefits in this case :/ - - - - - 1dacb506 by Ben Gamari at 2024-05-03T20:48:53-04:00 Bump time submodule to 1.14 As requested in #24528. ------------------------- Metric Decrease: ghc_bignum_so rts_so Metric Increase: cabal_syntax_dir rts_so time_dir time_so ------------------------- - - - - - 4941b90e by Ben Gamari at 2024-05-03T20:48:53-04:00 Bump terminfo submodule to current master - - - - - 43d48b44 by Cheng Shao at 2024-05-03T20:49:30-04:00 wasm: use scheduler.postTask() for context switch when available This patch makes use of scheduler.postTask() for JSFFI context switch when it's available. It's a more principled approach than our MessageChannel based setImmediate() implementation, and it's available in latest version of Chromium based browsers. - - - - - 08207501 by Cheng Shao at 2024-05-03T20:50:08-04:00 testsuite: give pre_cmd for mhu-perf 5x time - - - - - bf3d4db0 by Alan Zimmerman at 2024-05-03T20:50:43-04:00 EPA: Preserve comments for pattern synonym sig Closes #24749 - - - - - c49493f2 by Matthew Pickering at 2024-05-04T06:02:57-04:00 tests: Widen acceptance window for dir and so size tests These are testing things which are sometimes out the control of a GHC developer. Therefore we shouldn't fail CI if something about these dependencies change because we can't do anything about it. It is still useful to have these statistics for visualisation in grafana though. Ticket #24759 - - - - - 9562808d by Matthew Pickering at 2024-05-04T06:02:57-04:00 Disable rts_so test It has already manifested large fluctuations and destabilising CI Fixes #24762 - - - - - fc24c5cf by Ryan Scott at 2024-05-04T06:03:33-04:00 unboxedSum{Type,Data}Name: Use GHC.Types as the module Unboxed sum constructors are now defined in the `GHC.Types` module, so if you manually quote an unboxed sum (e.g., `''Sum2#`), you will get a `Name` like: ```hs GHC.Types.Sum2# ``` The `unboxedSumTypeName` function in `template-haskell`, however, mistakenly believes that unboxed sum constructors are defined in `GHC.Prim`, so `unboxedSumTypeName 2` would return an entirely different `Name`: ```hs GHC.Prim.(#|#) ``` This is a problem for Template Haskell users, as it means that they can't be sure which `Name` is the correct one. (Similarly for `unboxedSumDataName`.) This patch fixes the implementations of `unboxedSum{Type,Data}Name` to use `GHC.Types` as the module. For consistency with `unboxedTupleTypeName`, the `unboxedSumTypeName` function now uses the non-punned syntax for unboxed sums (`Sum<N>#`) as the `OccName`. Fixes #24750. - - - - - 7eab4e01 by Alan Zimmerman at 2024-05-04T16:14:55+01:00 EPA: Widen stmtslist to include last semicolon Closes #24754 - - - - - 06f7db40 by Teo Camarasu at 2024-05-05T00:19:38-04:00 doc: Fix type error in hs_try_putmvar example - - - - - af000532 by Moritz Schuler at 2024-05-05T06:30:58-04:00 Fix parsing of module names in CLI arguments closes issue #24732 - - - - - da74e9c9 by Ben Gamari at 2024-05-05T06:31:34-04:00 ghc-platform: Add Setup.hs The Hadrian bootstrapping script relies upon `Setup.hs` to drive its build. Addresses #24761. - - - - - 35d34fde by Alan Zimmerman at 2024-05-05T12:52:40-04:00 EPA: preserve comments in class and data decls Fix checkTyClHdr which was discarding comments. Closes #24755 - - - - - 03c5dfbf by Simon Peyton Jones at 2024-05-05T12:53:15-04:00 Fix a float-out error Ticket #24768 showed that the Simplifier was accidentally destroying a join point. It turned out to be that we were sending a bottoming join point to the top, accidentally abstracting over /other/ join points. Easily fixed. - - - - - adba68e7 by John Ericson at 2024-05-05T19:35:56-04:00 Substitute bindist files with Hadrian not configure The `ghc-toolchain` overhaul will eventually replace all this stuff with something much more cleaned up, but I think it is still worth making this sort of cleanup in the meantime so other untanglings and dead code cleaning can procede. I was able to delete a fair amount of dead code doing this too. `LLVMTarget_CPP` is renamed to / merged with `LLVMTarget` because it wasn't actually turned into a valid CPP identifier. (Original to 1345c7cc42c45e63ab1726a8fd24a7e4d4222467, actually.) Progress on #23966 Co-Authored-By: Sylvain Henry <hsyl20 at gmail.com> - - - - - 18f4ff84 by Alan Zimmerman at 2024-05-05T19:36:32-04:00 EPA: fix mkHsOpTyPV duplicating comments Closes #24753 - - - - - a19201d4 by Matthew Craven at 2024-05-06T19:54:29-04:00 Add test cases for #24664 ...since none are present in the original MR !12463 fixing this issue. - - - - - 46328a49 by Alan Zimmerman at 2024-05-06T19:55:05-04:00 EPA: preserve comments in data decls Closes #24771 - - - - - 3b51995c by Andrei Borzenkov at 2024-05-07T14:39:40-04:00 Rename Solo# data constructor to MkSolo# (#24673) - data Solo# a = (# a #) + data Solo# a = MkSolo# a And `(# foo #)` syntax now becomes just a syntactic sugar for `MkSolo# a`. - - - - - 4d59abf2 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Add the cmm_cpp_is_gcc predicate to the testsuite A future C-- test called T24474-cmm-override-g0 relies on the GCC-specific behaviour of -g3 implying -dD, which, in turn, leads to it emitting #defines past the preprocessing stage. Clang, at least, does not do this, so the test would fail if ran on Clang. As the behaviour here being tested is ``-optCmmP-g3'' undoing effects of the workaround we apply as a fix for bug #24474, and the workaround was for GCC-specific behaviour, the test needs to be marked as fragile on other compilers. - - - - - 25b0b404 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Split out the C-- preprocessor, and make it pass -g0 Previously, C-- was processed with the C preprocessor program. This means that it inherited flags passed via -optc. A flag that is somewhat often passed through -optc is -g. At certain -g levels (>=2), GCC starts emitting defines *after* preprocessing, for the purposes of debug info generation. This is not useful for the C-- compiler, and, in fact, causes lexer errors. We can suppress this effect (safely, if supported) via -g0. As a workaround, in older versions of GCC (<=10), GCC only emitted defines if a certain set of -g*3 flags was passed. Newer versions check the debug level. For the former, we filter out those -g*3 flags and, for the latter, we specify -g0 on top of that. As a compatible and effective solution, this change adds a C-- preprocessor distinct from the C compiler and preprocessor, but that keeps its flags. The command line produced for C-- preprocessing now looks like: $pgmCmmP $optCs_without_g3 $g0_if_supported $optCmmP Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/24474 - - - - - 9b4129a5 by Andreas Klebinger at 2024-05-08T13:24:20-04:00 -fprof-late: Only insert cost centres on functions/non-workfree cafs. They are usually useless and doing so for data values comes with a large compile time/code size overhead. Fixes #24103 - - - - - 259b63d3 by Sebastian Graf at 2024-05-08T13:24:57-04:00 Simplifier: Preserve OccInfo on DataAlt fields when case binder is dead (#24770) See the adjusted `Note [DataAlt occ info]`. This change also has a positive repercussion on `Note [Combine case alts: awkward corner]`. Fixes #24770. We now try not to call `dataConRepStrictness` in `adjustFieldsIdInfo` when all fields are lazy anyway, leading to a 2% ghc/alloc decrease in T9675. Metric Decrease: T9675 - - - - - 31b28cdb by Sebastian Graf at 2024-05-08T13:24:57-04:00 Kill seqRule, discard dead seq# in Prep (#24334) Discarding seq#s in Core land via `seqRule` was problematic; see #24334. So instead we discard certain dead, discardable seq#s in Prep now. See the updated `Note [seq# magic]`. This fixes the symptoms of #24334. - - - - - b2682534 by Rodrigo Mesquita at 2024-05-10T01:47:51-04:00 Document NcgImpl methods Fixes #19914 - - - - - 4d3acbcf by Zejun Wu at 2024-05-10T01:48:28-04:00 Make renamer to be more flexible with parens in the LHS of the rules We used to reject LHS like `(f a) b` in RULES and requires it to be written as `f a b`. It will be handy to allow both as the expression may be more readable with extra parens in some cases when infix operator is involved. Espceially when TemplateHaskell is used, extra parens may be added out of user's control and result in "valid" rules being rejected and there are not always ways to workaround it. Fixes #24621 - - - - - ab840ce6 by Ben Gamari at 2024-05-10T01:49:04-04:00 IPE: Eliminate dependency on Read Instead of encoding the closure type as decimal string we now simply represent it as an integer, eliminating the need for `Read` in `GHC.Internal.InfoProv.Types.peekInfoProv`. Closes #24504. ------------------------- Metric Decrease: T24602_perf_size size_hello_artifact ------------------------- - - - - - a9979f55 by Cheng Shao at 2024-05-10T01:49:43-04:00 testsuite: fix testwsdeque with recent clang This patch fixes compilation of testwsdeque.c with recent versions of clang, which will fail with the error below: ``` testwsdeque.c:95:33: error: warning: format specifies type 'long' but the argument has type 'void *' [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~~ ^ testwsdeque.c:95:39: error: warning: format specifies type 'int' but the argument has type 'StgWord' (aka 'unsigned long') [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~ ^~~ | %lu testwsdeque.c:133:42: error: error: incompatible function pointer types passing 'void (void *)' to parameter of type 'OSThreadProc *' (aka 'void *(*)(void *)') [-Wincompatible-function-pointer-types] 133 | createOSThread(&ids[n], "thief", thief, (void*)(StgWord)n); | ^~~~~ /workspace/ghc/_build/stage1/lib/../lib/x86_64-linux-ghc-9.11.20240502/rts-1.0.2/include/rts/OSThreads.h:193:51: error: note: passing argument to parameter 'startProc' here 193 | OSThreadProc *startProc, void *param); | ^ 2 warnings and 1 error generated. ``` - - - - - c2b33fc9 by Rodrigo Mesquita at 2024-05-10T01:50:20-04:00 Rename pre-processor invocation args Small clean up. Uses proper names for the various groups of arguments that make up the pre-processor invocation. - - - - - 2b1af08b by Cheng Shao at 2024-05-10T01:50:55-04:00 ghc-heap: fix typo in ghc-heap cbits - - - - - fc2d6de1 by Jade at 2024-05-10T21:07:16-04:00 Improve performance of Data.List.sort(By) This patch improves the algorithm to sort lists in base. It does so using two strategies: 1) Use a four-way-merge instead of the 'default' two-way-merge. This is able to save comparisons and allocations. 2) Use `(>) a b` over `compare a b == GT` and allow inlining and specialization. This mainly benefits types with a fast (>). Note that this *may* break instances with a *malformed* Ord instance where `a > b` is *not* equal to `compare a b == GT`. CLC proposal: https://github.com/haskell/core-libraries-committee/issues/236 Fixes #24280 ------------------------- Metric Decrease: MultiLayerModulesTH_Make T10421 T13719 T15164 T18698a T18698b T1969 T9872a T9961 T18730 WWRec T12425 T15703 ------------------------- - - - - - 1012e8aa by Matthew Pickering at 2024-05-10T21:07:52-04:00 Revert "ghcup-metadata: Drop output_name field" This reverts commit ecbf22a6ac397a791204590f94c0afa82e29e79f. This breaks the ghcup metadata generation on the nightly jobs. - - - - - daff1e30 by Jannis at 2024-05-12T13:38:35-04:00 Division by constants optimization - - - - - 413217ba by Andreas Klebinger at 2024-05-12T13:39:11-04:00 Tidy: Add flag to expose unfoldings if they take dictionary arguments. Add the flag `-fexpose-overloaded-unfoldings` to be able to control this behaviour. For ghc's boot libraries file size grew by less than 1% when it was enabled. However I refrained from enabling it by default for now. I've also added a section on specialization more broadly to the users guide. ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot Metric Increase: T12425 T13386 hard_hole_fits ------------------------- - - - - - c5d89412 by Zubin Duggal at 2024-05-13T22:19:53-04:00 Don't store a GlobalRdrEnv in `mi_globals` for GHCi. GHCi only needs the `mi_globals` field for modules imported with :module +*SomeModule. It uses this field to make the top level environment in `SomeModule` available to the repl. By default, only the first target in the command line parameters is "star" loaded into GHCi. Other modules have to be manually "star" loaded into the repl. Storing the top level GlobalRdrEnv for each module is very wasteful, especially given that we will most likely never need most of these environments. Instead we store only the information needed to reconstruct the top level environment in a module, which is the `IfaceTopEnv` data structure, consisting of all import statements as well as all top level symbols defined in the module (not taking export lists into account) When a particular module is "star-loaded" into GHCi (as the first commandline target, or via an explicit `:module +*SomeModule`, we reconstruct the top level environment on demand using the `IfaceTopEnv`. - - - - - d65bf4a2 by Fendor at 2024-05-13T22:20:30-04:00 Add perf regression test for `-fwrite-if-simplified-core` - - - - - 2c0f8ddb by Andrei Borzenkov at 2024-05-13T22:21:07-04:00 Improve pattern to type pattern transformation (23739) `pat_to_type_pat` function now can handle more patterns: - TuplePat - ListPat - LitPat - NPat - ConPat Allowing these new constructors in type patterns significantly increases possible shapes of type patterns without `type` keyword. This patch also changes how lookups in `lookupOccRnConstr` are performed, because we need to fall back into types when we didn't find a constructor on data level to perform `ConPat` to type transformation properly. - - - - - be514bb4 by Cheng Shao at 2024-05-13T22:21:43-04:00 hadrian: fix hadrian building with ghc-9.10.1 - - - - - ad38e954 by Cheng Shao at 2024-05-13T22:21:43-04:00 linters: fix lint-whitespace compilation with ghc-9.10.1 - - - - - a593f284 by Andreas Klebinger at 2024-05-15T07:32:10-04:00 Expand the `inline` rule to look through casts/ticks. Fixes #24808 - - - - - b1e0c313 by Cheng Shao at 2024-05-15T07:32:46-04:00 testsuite: bump PartialDownSweep timeout to 5x on wasm32 - - - - - b2227487 by Fendor at 2024-05-15T17:14:06-04:00 Add Eq and Ord instance to `IfaceType` We add an `Ord` instance so that we can store `IfaceType` in a `Data.Map` container. This is required to deduplicate `IfaceType` while writing `.hi` files to disk. Deduplication has many beneficial consequences to both file size and memory usage, as the deduplication enables implicit sharing of values. See issue #24540 for more motivation. The `Ord` instance would be unnecessary if we used a `TrieMap` instead of `Data.Map` for the deduplication process. While in theory this is clerarly the better option, experiments on the agda code base showed that a `TrieMap` implementation has worse run-time performance characteristics. To the change itself, we mostly derive `Eq` and `Ord`. This requires us to change occurrences of `FastString` with `LexicalFastString`, since `FastString` has no `Ord` instance. We change the definition of `IfLclName` to a newtype of `LexicalFastString`, to make such changes in the future easier. Bump haddock submodule for IfLclName changes - - - - - d368f9a6 by Fendor at 2024-05-15T17:14:06-04:00 Move out LiteralMap to avoid cyclic module dependencies - - - - - 2fcc09fd by Fendor at 2024-05-15T17:14:06-04:00 Add deduplication table for `IfaceType` The type `IfaceType` is a highly redundant, tree-like data structure. While benchmarking, we realised that the high redundancy of `IfaceType` causes high memory consumption in GHCi sessions when byte code is embedded into the `.hi` file via `-fwrite-if-simplified-core` or `-fbyte-code-and-object-code`. Loading such `.hi` files from disk introduces many duplicates of memory expensive values in `IfaceType`, such as `IfaceTyCon`, `IfaceTyConApp`, `IA_Arg` and many more. We improve the memory behaviour of GHCi by adding an additional deduplication table for `IfaceType` to the serialisation of `ModIface`, similar to how we deduplicate `Name`s and `FastString`s. When reading the interface file back, the table allows us to automatically share identical values of `IfaceType`. To provide some numbers, we evaluated this patch on the agda code base. We loaded the full library from the `.hi` files, which contained the embedded core expressions (`-fwrite-if-simplified-core`). Before this patch: * Load time: 11.7 s, 2.5 GB maximum residency. After this patch: * Load time: 7.3 s, 1.7 GB maximum residency. This deduplication has the beneficial side effect to additionally reduce the size of the on-disk interface files tremendously. For example, on agda, we reduce the size of `.hi` files (with `-fwrite-if-simplified-core`): * Before: 101 MB on disk * Now: 24 MB on disk This has even a beneficial side effect on the cabal store. We reduce the size of the store on disk: * Before: 341 MB on disk * Now: 310 MB on disk Note, none of the dependencies have been compiled with `-fwrite-if-simplified-core`, but `IfaceType` occurs in multiple locations in a `ModIface`. We also add IfaceType deduplication table to .hie serialisation and refactor .hie file serialisation to use the same infrastrucutre as `putWithTables`. Bump haddock submodule to accomodate for changes to the deduplication table layout and binary interface. - - - - - 36aa7cf1 by Fendor at 2024-05-15T17:14:06-04:00 Add run-time configurability of `.hi` file compression Introduce the flag `-fwrite-if-compression=<n>` which allows to configure the compression level of writing .hi files. The motivation is that some deduplication operations are too expensive for the average use case. Hence, we introduce multiple compression levels with variable impact on performance, but still reduce the memory residency and `.hi` file size on disk considerably. We introduce three compression levels: * `1`: `Normal` mode. This is the least amount of compression. It deduplicates only `Name` and `FastString`s, and is naturally the fastest compression mode. * `2`: `Safe` mode. It has a noticeable impact on .hi file size and is marginally slower than `Normal` mode. In general, it should be safe to always use `Safe` mode. * `3`: `Full` deduplication mode. Deduplicate as much as we can, resulting in minimal .hi files, but at the cost of additional compilation time. Reading .hi files doesn't need to know the initial compression level, and can always deserialise a `ModIface`, as we write out a byte that indicates the next value has been deduplicated. This allows users to experiment with different compression levels for packages, without recompilation of dependencies. Note, the deduplication also has an additional side effect of reduced memory consumption to implicit sharing of deduplicated elements. See https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for example where that matters. ------------------------- Metric Decrease: MultiLayerModulesDefsGhciWithCore T16875 T21839c T24471 hard_hole_fits libdir ------------------------- - - - - - 1e63a6fb by Matthew Pickering at 2024-05-15T17:14:07-04:00 Introduce regression tests for `.hi` file sizes Add regression tests to track how `-fwrite-if-compression` levels affect the size of `.hi` files. - - - - - 639d742b by M Farkas-Dyck at 2024-05-15T17:14:49-04:00 TTG: ApplicativeStatement exist only in Rn and Tc Co-Authored-By: romes <rodrigo.m.mesquita at gmail.com> - - - - - aa7b336b by Jade at 2024-05-15T23:06:17-04:00 Documentation: Improve documentation for symbols exported from System.IO - - - - - c561de8f by Jade at 2024-05-15T23:06:54-04:00 Improve suggestions for language extensions - When suggesting Language extensions, also suggest Extensions which imply them - Suggest ExplicitForAll and GADTSyntax instead of more specific extensions - Rephrase suggestion to include the term 'Extension' - Also moves some flag specific definitions out of Session.hs into Flags.hs (#24478) Fixes: #24477 Fixes: #24448 Fixes: #10893 - - - - - 4c7ae2a1 by Andreas Klebinger at 2024-05-15T23:07:30-04:00 Testsuite: Check if llvm assembler is available for have_llvm - - - - - bc672166 by Torsten Schmits at 2024-05-15T23:08:06-04:00 refactor quadratic search in warnMissingHomeModules - - - - - 7875e8cb by Torsten Schmits at 2024-05-15T23:08:06-04:00 add test that runs MakeDepend on thousands of modules - - - - - b84b91f5 by Adam Gundry at 2024-05-16T15:32:06-04:00 Representation-polymorphic HasField (fixes #22156) This generalises the HasField class to support representation polymorphism, so that instead of type HasField :: forall {k} . k -> Type -> Type -> Constraint we have type HasField :: forall {k} {r_rep} {a_rep} . k -> TYPE r_rep -> TYPE a_rep -> Constraint - - - - - 05285090 by Matthew Pickering at 2024-05-16T15:32:43-04:00 Bump os-string submodule to 2.0.2.2 Closes #24786 - - - - - 886ab43a by Cheng Shao at 2024-05-17T01:34:50-04:00 rts: do not prefetch mark_closure bdescr in non-moving gc when ASSERTS_ENABLED This commit fixes a small an oversight in !12148: the prefetch logic in non-moving GC may trap in debug RTS because it calls Bdescr() for mark_closure which may be a static one. It's fine in non-debug RTS because even invalid bdescr addresses are prefetched, they will not cause segfaults, so this commit implements the most straightforward fix: don't prefetch mark_closure bdescr when assertions are enabled. - - - - - b38dcf39 by Teo Camarasu at 2024-05-17T01:34:50-04:00 rts: Allocate non-moving segments with megablocks Non-moving segments are 8 blocks long and need to be aligned. Previously we serviced allocations by grabbing 15 blocks, finding an aligned 8 block group in it and returning the rest. This proved to lead to high levels of fragmentation as a de-allocating a segment caused an 8 block gap to form, and this could not be reused for allocation. This patch introduces a segment allocator based around using entire megablocks to service segment allocations in bulk. When there are no free segments, we grab an entire megablock and fill it with aligned segments. As the megablock is free, we can easily guarantee alignment. Any unused segments are placed on a free list. It only makes sense to free segments in bulk when all of the segments in a megablock are freeable. After sweeping, we grab the free list, sort it, and find all groups of segments where they cover the megablock and free them. This introduces a period of time when free segments are not available to the mutator, but the risk that this would lead to excessive allocation is low. Right after sweep, we should have an abundance of partially full segments, and this pruning step is relatively quick. In implementing this we drop the logic that kept NONMOVING_MAX_FREE segments on the free list. We also introduce an eventlog event to log the amount of pruned/retained free segments. See Note [Segment allocation strategy] Resolves #24150 ------------------------- Metric Decrease: T13253 T19695 ------------------------- - - - - - 710665bd by Cheng Shao at 2024-05-17T01:35:30-04:00 rts: fix I/O manager compilation errors for win32 target This patch fixes I/O manager compilation errors for win32 target discovered when cross-compiling to win32 using recent clang: ``` rts/win32/ThrIOManager.c:117:7: error: error: call to undeclared function 'is_io_mng_native_p'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 117 | if (is_io_mng_native_p ()) { | ^ | 117 | if (is_io_mng_native_p ()) { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/fs.c:143:28: error: error: a function declaration without a prototype is deprecated in all versions of C [-Werror,-Wstrict-prototypes] 143 | int setErrNoFromWin32Error () { | ^ | void | 143 | int setErrNoFromWin32Error () { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:227:9: error: error: call to undeclared function 'interruptIOManagerEvent'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 227 | interruptIOManagerEvent (); | ^ | 227 | interruptIOManagerEvent (); | ^ rts/win32/ConsoleHandler.c:227:9: error: note: did you mean 'getIOManagerEvent'? | 227 | interruptIOManagerEvent (); | ^ rts/include/rts/IOInterface.h:27:10: error: note: 'getIOManagerEvent' declared here 27 | void * getIOManagerEvent (void); | ^ | 27 | void * getIOManagerEvent (void); | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:196:9: error: error: call to undeclared function 'setThreadLabel'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/win32/ConsoleHandler.c:196:9: error: note: did you mean 'postThreadLabel'? | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/eventlog/EventLog.h:118:6: error: note: 'postThreadLabel' declared here 118 | void postThreadLabel(Capability *cap, | ^ | 118 | void postThreadLabel(Capability *cap, | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) ``` - - - - - 28b9cee0 by Rodrigo Mesquita at 2024-05-17T01:36:05-04:00 configure: Check C99-compat for Cmm preprocessor Fixes #24815 - - - - - 8927e0c3 by Andreas Klebinger at 2024-05-17T01:36:41-04:00 Ensure `tcHasFixedRuntimeRep (# #)` returns True. - - - - - 04179044 by doyougnu at 2024-05-17T09:00:32-04:00 testsuite: make find_so regex less general Closes #24759 Background. In MR !12372 we began tracking shared object files and directories sizes for dependencies. However, this broke release builds because release builds alter the filenames swapping "in-place" for a hash. This was not considered in the MR and thus broke release pipelines. Furthermore, the rts_so test was found to be wildly varying and was therefore disabled in !12561. This commit fixes both of these issues: - fix the rts_so test by making the regex less general, now the rts_so test and all other foo.so tests must match "libHS<some-lib>-<version>-<hash|'in-place>-<ghc>". This prevents the rts_so test from accidentally matching different rts variants such as rts_threaded, which was the cause of the wild swings after !12372. - add logic to match either a hash or the string in-place. This should make the find_so function build agnostic. - - - - - 0962b50d by Andreas Klebinger at 2024-05-17T09:01:08-04:00 TagAnalysis: Treat all bottom ids as tagged during analysis. Ticket #24806 showed that we also need to treat dead end thunks as tagged during the analysis. - - - - - 7eb9f184 by Ben Gamari at 2024-05-17T11:23:37-04:00 Remove haddock submodule In preparation for merge into the GHC, as proposed in #23178. - - - - - 47b14dcc by Fendor at 2024-05-17T11:28:17-04:00 Adapt to `IfLclName` newtype changes (cherry picked from commit a711607e29b925f3d69e27c5fde4ba655c711ff1) - - - - - 6cc6681d by Fendor at 2024-05-17T11:28:17-04:00 Add IfaceType deduplication table to interface file serialisation Although we do not really need it in the interface file serialisation, as the deserialisation uses `getWithUserData`, we need to mirror the structure `getWithUserData` expects. Thus, we write essentially an empty `IfaceType` table at the end of the file, as the interface file doesn't reference `IfaceType`. (cherry picked from commit c9bc29c6a708483d2abc3d8ec9262510ce87ca61) - - - - - b9721206 by Ben Gamari at 2024-05-17T11:30:22-04:00 ghc-tags.yaml: Initial commit - - - - - 074e7d8f by Ben Gamari at 2024-05-17T11:31:29-04:00 fourmolu: Add configuration - - - - - 151b1736 by Ben Gamari at 2024-05-17T11:32:52-04:00 Makefile: Rework for use by haddock developers Previously the Makefile was present only for GHC's old make-based build system. Now since the make-based build system is gone we can use it for more useful ends. - - - - - a7dcf13b by Ben Gamari at 2024-05-17T11:36:14-04:00 Reformat with fourmolu Using previously-added configuration and `fourmolu -i .` Note that we exclude the test-cases (`./{hoogle,html-hypsrc,latex}-test`) as they are sensitive to formatting. - - - - - 0ea6017b by Ben Gamari at 2024-05-17T11:40:04-04:00 Add 'utils/haddock/' from commit 'a7dcf13bfbb97b20e75cc8ce650e2bb628db4660' git-subtree-dir: utils/haddock git-subtree-mainline: 7eb9f1849b1c72a1c61dee88462b4244550406f3 git-subtree-split: a7dcf13bfbb97b20e75cc8ce650e2bb628db4660 - - - - - aba1d304 by Hécate Moonlight at 2024-05-17T11:40:48-04:00 Add exceptions to the dangling notes list - - - - - 527bfbfb by Hécate Moonlight at 2024-05-17T11:40:52-04:00 Add haddock to the whitespace lint ignore list - - - - - 43274677 by Ben Gamari at 2024-05-17T11:41:20-04:00 git-blame-ignore-revs: Ignore haddock reformatting - - - - - 0e679e37 by Fendor at 2024-05-18T00:27:24-04:00 Pass cpp options to the CC builder in hadrian - - - - - bb40244e by Sylvain Henry at 2024-05-18T00:28:06-04:00 JS: fix allocation constant (fix #24746) - - - - - 646d30ab by Jade at 2024-05-18T19:23:31+02:00 Add highlighting for inline-code snippets in haddock - - - - - 64459a3e by Hécate Moonlight at 2024-05-19T08:42:27-04:00 haddock: Add a .readthedocs.yml file for online documentation - - - - - 7d3d9bbf by Serge S. Gulin at 2024-05-19T18:47:05+00:00 Unicode: General Category size test (related #24789) Added trivial size performance test which involves unicode general category usage via `read`. The `read` itself uses general category to detect spaces. The purpose for this test is to measure outcome of applying improvements at General Category representation in code discussed at #24789. - - - - - 8e04efcf by Alan Zimmerman at 2024-05-19T21:29:34-04:00 EPA: Remove redundant code Remove unused epAnnAnns function various cases for showAstData that no longer exist - - - - - 071d7a1e by Rodrigo Mesquita at 2024-05-20T10:55:16-04:00 Improve docs on closed type families in hs-boots Fixes #24776 - - - - - d9e2c119 by Torsten Schmits at 2024-05-20T10:55:52-04:00 Use default deviation for large-project test This new performance test has the purpose of detecting regressions in complexity in relation to the number of modules in a project, so 1% deviation is way too small to avoid false positives. - - - - - 20b0136a by Ben Gamari at 2024-05-22T00:31:39-04:00 ghcup-metadata: Various fixes from 9.10.1 Use Debian 12/x86-64, Debian 10/aarch64, and Debian 11/aarch64 bindists where possible. - - - - - 6838a7c3 by Sylvain Henry at 2024-05-22T00:32:23-04:00 Reverse arguments to stgCallocBytes (fix #24828) - - - - - f50f46c3 by Fendor at 2024-05-22T00:32:59-04:00 Add log messages for Iface serialisation compression level Fix the label of the number of 'IfaceType' entries in the log message. Add log message for the compression level that is used to serialise a an interface file. Adds `Outputable` instance for 'CompressionIFace'. - - - - - 3bad5d55 by Hécate Moonlight at 2024-05-22T00:33:40-04:00 base: Update doctests outputs ghc-internal: Update doctests outputs - - - - - 9317c6fb by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix the testsuites of the haddock-library - Apply all the metadata revisions from Hackage to the cabal file. - Fix the `ParserSpec.hs` file in the `spec` testsuite of haddock-library. - Make `CHANGES.md` an extra-doc-file instead of an extra-source-file. - - - - - 54073b02 by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix parser of @since pragma The testsuite contained tests for annotations of the form `@since foo-bar-0.5.0`, but the parser was written incorrectly. - - - - - ede6ede3 by Matthew Pickering at 2024-05-22T00:34:57-04:00 Fix nightly pages job It seems likely broken by 9f99126a which moved `index.html` from the root folder into `docs/` folder. Fixes #24840 - - - - - b7bcf729 by Cheng Shao at 2024-05-22T00:35:32-04:00 autoconf: remove unused context diff check This patch removes redundant autoconf check for the context diff program given it isn't actually been used anywhere, especially since make removal. - - - - - ea2fe66e by Hécate Moonlight at 2024-05-22T00:36:13-04:00 haddock: Rework the contributing guide - - - - - 0f302a94 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 haddock: Add module relationships diagrams of haddock-api and haddock-library - - - - - d1a9f34f by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add instructions - - - - - b880ee80 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add SVG outputs - - - - - 6d7e6ad8 by Ben Gamari at 2024-05-22T13:40:05-04:00 rts: Fix size of StgOrigThunkInfo frames Previously the entry code of the `stg_orig_thunk` frame failed to account for the size of the profiling header as it hard-coded the frame size. Fix this. Fixes #24809. - - - - - c645fe40 by Fendor at 2024-05-22T13:40:05-04:00 Add regression test T24809 for stg_orig_thunk_info_frame size - - - - - 4181aa40 by Andreas Klebinger at 2024-05-22T13:40:42-04:00 bindists: Check for existence of share folder before trying to copy it. This folder isn't distributed in windows bindists A lack of doing so resulted us copying loads of files twice. - - - - - d216510e by Matthew Pickering at 2024-05-22T13:40:42-04:00 Remove ad-hoc installation of mingw toolchain in relocatable bindists This reverts 616ac30026e8dd7d2ebb98d92dde071eedf5d951 The choice about whether to install mingw is taken in the installation makefile. This is also broken on non-windows systems. The actual issue was the EnableDistroToolchain variable wasn't declared in mk/config.mk and therefore the check to install mingw was failing. - - - - - 7b4c1998 by Cheng Shao at 2024-05-22T21:52:52-04:00 testsuite: fix T17920 for wasm backend T17920 was marked as fragile on wasm before; it can be trivially fixed by avoiding calling variadic printf() in cmm. - - - - - c739383b by Cheng Shao at 2024-05-22T21:53:29-04:00 testsuite: bump T22744 timeout to 5x - - - - - c4c6d714 by Cheng Shao at 2024-05-22T21:54:06-04:00 testsuite: don't attempt to detect host cpu features when testing cross ghc The testsuite driver CPU feature detection logic only detects host CPU and only makes sense when we are not testing a cross GHC. - - - - - 3d9e4ce6 by Simon Peyton Jones at 2024-05-22T21:54:43-04:00 Better skolemisation As #24810 showed, it is (a little) better to skolemise en-bloc, so that Note [Let-bound skolems] fires more often. See Note [Skolemisation en bloc] in GHC.Tc.Utils.Instantiate. - - - - - a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00 Add missing parenthesizePat in cvtp We need to ensure that the output of `cvtp` is parenthesized (at precedence `sigPrec`) so that any pattern signatures with a surrounding pattern signature can parse correctly. Fixes #24837. - - - - - 4bb2a7cc by Hécate Moonlight at 2024-05-22T21:55:59-04:00 [base] Document the memory overhead of ByteArray Add a diagram that shows the constituent parts of a ByteArray and their memory overhead. - - - - - 8b2a016a by Hécate Moonlight at 2024-05-22T21:56:38-04:00 Haddock: Add MR template for Haddock - - - - - ead75532 by Peter Trommler at 2024-05-23T02:28:05-04:00 PPC: Support ELF v2 on powerpc64 big-endian Detect ELF v2 on PowerPC 64-bit systems. Check for `_CALL_ELF` preprocessor macro. Fixes #21191 - - - - - 9d4c10f2 by Hécate Kleidukos at 2024-05-23T02:28:44-04:00 gitlab: Add @Kleidukos to CODEOWNERS for utils/haddock - - - - - 28e64170 by Preetham Gujjula at 2024-05-23T07:20:48-04:00 haddock: Add cabal-fmt to tools for `make style` - - - - - 00126a89 by Andrei Borzenkov at 2024-05-23T07:21:24-04:00 haddock: fix verbosity option parsing - - - - - a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00 base: specify tie-breaking behavior of min, max, and related list/Foldable functions - - - - - bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00 cmm: add word <-> double/float bitcast - closes: #25331 This is the last step in the project plan described in #25331. This commit: - adds bitcast operands for x86_64, LLVM, aarch64 - For PPC and i386 we resort to using the cmm implementations - renames conversion MachOps from Conv to Round|Truncate - - - - - f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor Some functions in StgToByteCode were filtering out void arguments. However, StgToByteCode is called after unarisation: the void arguments should have been removed earlier. Instead of filtering out, we assert that the args are non-void. - - - - - 03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor `layoutNativeCall` was always called with a `primRepCmmType platform` callback. Hence we can put it inside of `layoutNativeCall` rather than repeat it. - - - - - 27c430f3 by David Binder at 2024-05-24T07:52:38-04:00 haddock: Remove compatibility shims for GHC < 8.4 from haddock-library - - - - - 8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00 compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs This patch makes the STG->Cmm backend avoid saving foreign call target to local when there are no caller-save GlobalRegs. Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a foreign call, we unconditionally save the foreign call target to a temporary local first, then rely on cmmSink to clean it up later, which only happens with -fcmm-sink (implied by -O) and not in unoptimized code. And this is troublesome for the wasm backend NCG, which needs to infer a foreign call target symbol's type signature from the Cmm call site. Previously, the NCG has been emitting incorrect type signatures for unoptimized code, which happens to work with `wasm-ld` most of the time, but this is never future-proof against upstream toolchain updates, and it causes horrible breakages when LTO objects are included in linker input. Hence this patch. - - - - - 986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00 testsuite: add callee-no-local regression test - - - - - 52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00 Fix HasCallStack leftovers from !12514 / #24726 - - - - - c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00 user_guide: Fix typo in MultiWayIf chapter Close #24829 - - - - - bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - 1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Fix changelog reference to setBacktraceMechanismState (cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d) - - - - - 43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00 Float/double unboxed literal support for HexFloatLiterals (fix #22155) - - - - - 4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00 Improve test labels for binary interface file size tests Test labels for binary interface file sizes are hard to read and overly verbose at the same time. Extend the name for the metric title, but shorten it in the actual comparison table. - - - - - 14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00 Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present" This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa. - - - - - f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00 Fix default hyperlinked sources pattern Previously this didn't include the `%M` token which manifested as broken links to the hyperlinked sources of reexports of declarations defined in other packages. Fixes haddock#1628. (cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36) - - - - - 42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00 Make DocPaths a proper data type (cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c) - - - - - 53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00 haddock: Bump version to 2.30 (cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602) - - - - - e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00 haddock-api: allow base 4.20 and ghc 9.11 - - - - - e294f7a2 by PHO at 2024-05-24T12:17:55-04:00 Add a flag "threaded" for building haddock with the threaded RTS GHC isn't guaranteed to have a threaded RTS. There should be a way to build it with the vanilla one. (cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d) - - - - - 51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00 Update ticky counter event docs. Add the info about the info table address and json fields. Fixes #23200 - - - - - 98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00 Export extractPromotedList (#24866) This can be useful in plugins. - - - - - 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 6be1f993 by romes at 2024-06-06T15:16:42+02:00 FastString as just a ShortByteString - - - - - 24 changed files: - − .appveyor.sh - .editorconfig - .ghcid - + .git-blame-ignore-revs - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - − .gitlab/circle-ci-job.sh - .gitlab/darwin/nix/sources.json - .gitlab/darwin/toolchain.nix - − .gitlab/gen_ci.hs - + .gitlab/generate-ci/LICENSE - + .gitlab/generate-ci/README.mkd - + .gitlab/generate-ci/flake.lock - + .gitlab/generate-ci/flake.nix - + .gitlab/generate-ci/gen_ci.hs - + .gitlab/generate-ci/generate-ci.cabal - + .gitlab/generate-ci/generate-job-metadata - + .gitlab/generate-ci/generate-jobs - + .gitlab/generate-ci/hie.yaml - − .gitlab/generate_jobs - + .gitlab/hello.hs - − .gitlab/issue_templates/bug.md - + .gitlab/issue_templates/default.md The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1019c94155ddb5169114ab696afc3c5780d2f0e5...6be1f993a691186c0180bed1820a28a09f19c194 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1019c94155ddb5169114ab696afc3c5780d2f0e5...6be1f993a691186c0180bed1820a28a09f19c194 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 13:24:35 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 06 Jun 2024 09:24:35 -0400 Subject: [Git][ghc/ghc][wip/romes/faststring-is-shortbytestring] Make FastString a ShortByteStr Message-ID: <6661b8936d5_12ae212793680625a7@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/faststring-is-shortbytestring at Glasgow Haskell Compiler / GHC Commits: be10e61a by Rodrigo Mesquita at 2024-06-06T15:24:09+02:00 Make FastString a ShortByteStr - - - - - 2 changed files: - compiler/GHC/Data/FastString.hs - compiler/GHC/Types/Unique.hs Changes: ===================================== compiler/GHC/Data/FastString.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE MagicHash #-} @@ -60,7 +61,7 @@ module GHC.Data.FastString lengthFZS, -- * FastStrings - FastString(..), -- not abstract, for now. + FastString, -- not abstract, for now. NonDetFastString (..), LexicalFastString (..), @@ -115,7 +116,6 @@ import GHC.Prelude.Basic as Prelude import GHC.Utils.Encoding import GHC.Utils.IO.Unsafe import GHC.Utils.Panic.Plain -import GHC.Utils.Misc import GHC.Data.FastMutInt import Control.Concurrent.MVar @@ -149,13 +149,13 @@ import GHC.IO -- | Gives the Modified UTF-8 encoded bytes corresponding to a 'FastString' bytesFS, fastStringToByteString :: FastString -> ByteString {-# INLINE[1] bytesFS #-} -bytesFS f = SBS.fromShort $ fs_sbs f +bytesFS f = SBS.fromShort $ f {-# DEPRECATED fastStringToByteString "Use `bytesFS` instead" #-} fastStringToByteString = bytesFS fastStringToShortByteString :: FastString -> ShortByteString -fastStringToShortByteString = fs_sbs +fastStringToShortByteString = id fastStringToShortText :: FastString -> ShortText fastStringToShortText = ShortText . fs_sbs @@ -167,8 +167,6 @@ fastZStringToByteString (FastZString bs) = bs unsafeMkByteString :: String -> ByteString unsafeMkByteString = BSC.pack -hashFastString :: FastString -> Int -hashFastString fs = hashStr $ fs_sbs fs -- ----------------------------------------------------------------------------- @@ -205,56 +203,23 @@ comparison. It is also associated with a lazy reference to the Z-encoding of this string which is used by the compiler internally. -} -data FastString = FastString { - uniq :: {-# UNPACK #-} !Int, -- unique id - n_chars :: {-# UNPACK #-} !Int, -- number of chars - fs_sbs :: {-# UNPACK #-} !ShortByteString, - fs_zenc :: FastZString - -- ^ Lazily computed Z-encoding of this string. See Note [Z-Encoding] in - -- GHC.Utils.Encoding. - -- - -- Since 'FastString's are globally memoized this is computed at most - -- once for any given string. - } - -instance Eq FastString where - f1 == f2 = uniq f1 == uniq f2 +type FastString = ShortByteString -- We don't provide any "Ord FastString" instance to force you to think about -- which ordering you want: -- * lexical: deterministic, O(n). Cf lexicalCompareFS and LexicalFastString. -- * by unique: non-deterministic, O(1). Cf uniqCompareFS and NonDetFastString. -instance IsString FastString where - fromString = fsLit -instance Semi.Semigroup FastString where - (<>) = appendFS -instance Monoid FastString where - mempty = nilFS - mappend = (Semi.<>) - mconcat = concatFS -instance Show FastString where - show fs = show (unpackFS fs) -instance Data FastString where - -- don't traverse? - toConstr _ = abstractConstr "FastString" - gunfold _ _ = error "gunfold" - dataTypeOf _ = mkNoRepType "FastString" -instance NFData FastString where - rnf fs = seq fs () -- | Compare FastString lexically -- -- If you don't care about the lexical ordering, use `uniqCompareFS` instead. lexicalCompareFS :: FastString -> FastString -> Ordering -lexicalCompareFS fs1 fs2 = - if uniq fs1 == uniq fs2 then EQ else - utf8CompareShortByteString (fs_sbs fs1) (fs_sbs fs2) -- perform a lexical comparison taking into account the Modified UTF-8 -- encoding we use (cf #18562) @@ -262,7 +227,7 @@ lexicalCompareFS fs1 fs2 = -- -- Much cheaper than `lexicalCompareFS` but non-deterministic! uniqCompareFS :: FastString -> FastString -> Ordering -uniqCompareFS fs1 fs2 = compare (uniq fs1) (uniq fs2) +uniqCompareFS = compare -- | Non-deterministic FastString -- @@ -332,48 +297,10 @@ Following parameters are determined based on: * Stats of @echo :browse | ghc --interactive -dfaststring-stats >/dev/null@: on 2018-10-24, we have 13920 entries. -} -segmentBits, numSegments, segmentMask, initialNumBuckets :: Int -segmentBits = 8 +numSegments, initialNumBuckets :: Int numSegments = 256 -- bit segmentBits -segmentMask = 0xff -- bit segmentBits - 1 initialNumBuckets = 64 -hashToSegment# :: Int# -> Int# -hashToSegment# hash# = hash# `andI#` segmentMask# - where - !(I# segmentMask#) = segmentMask - -hashToIndex# :: MutableArray# RealWorld [FastString] -> Int# -> Int# -hashToIndex# buckets# hash# = - (hash# `uncheckedIShiftRL#` segmentBits#) `remInt#` size# - where - !(I# segmentBits#) = segmentBits - size# = sizeofMutableArray# buckets# - -maybeResizeSegment :: IORef FastStringTableSegment -> IO FastStringTableSegment -maybeResizeSegment segmentRef = do - segment@(FastStringTableSegment lock counter old#) <- readIORef segmentRef - let oldSize# = sizeofMutableArray# old# - newSize# = oldSize# *# 2# - (I# n#) <- readFastMutInt counter - if isTrue# (n# <# newSize#) -- maximum load of 1 - then return segment - else do - resizedSegment@(FastStringTableSegment _ _ new#) <- IO $ \s1# -> - case newArray# newSize# [] s1# of - (# s2#, arr# #) -> (# s2#, FastStringTableSegment lock counter arr# #) - forM_ [0 .. (I# oldSize#) - 1] $ \(I# i#) -> do - fsList <- IO $ readArray# old# i# - forM_ fsList $ \fs -> do - let -- Shall we store in hash value in FastString instead? - !(I# hash#) = hashFastString fs - idx# = hashToIndex# new# hash# - IO $ \s1# -> - case readArray# new# idx# s1# of - (# s2#, bucket #) -> case writeArray# new# idx# (fs: bucket) s2# of - s3# -> (# s3#, () #) - writeIORef segmentRef resizedSegment - return resizedSegment {-# NOINLINE stringTable #-} stringTable :: FastStringTable @@ -473,60 +400,12 @@ The procedure goes like this: * Otherwise, insert and return the string we created. -} -mkFastStringWith - :: (Int -> FastMutInt-> IO FastString) -> ShortByteString -> IO FastString -mkFastStringWith mk_fs sbs = do - FastStringTableSegment lock _ buckets# <- readIORef segmentRef - let idx# = hashToIndex# buckets# hash# - bucket <- IO $ readArray# buckets# idx# - case bucket_match bucket sbs of - Just found -> return found - Nothing -> do - -- The withMVar below is not dupable. It can lead to deadlock if it is - -- only run partially and putMVar is not called after takeMVar. - noDuplicate - n <- get_uid - new_fs <- mk_fs n n_zencs - withMVar lock $ \_ -> insert new_fs - where - !(FastStringTable uid n_zencs segments#) = stringTable - get_uid = atomicFetchAddFastMut uid 1 - - !(I# hash#) = hashStr sbs - (# segmentRef #) = indexArray# segments# (hashToSegment# hash#) - insert fs = do - FastStringTableSegment _ counter buckets# <- maybeResizeSegment segmentRef - let idx# = hashToIndex# buckets# hash# - bucket <- IO $ readArray# buckets# idx# - case bucket_match bucket sbs of - -- The FastString was added by another thread after previous read and - -- before we acquired the write lock. - Just found -> return found - Nothing -> do - IO $ \s1# -> - case writeArray# buckets# idx# (fs : bucket) s1# of - s2# -> (# s2#, () #) - _ <- atomicFetchAddFastMut counter 1 - return fs - -bucket_match :: [FastString] -> ShortByteString -> Maybe FastString -bucket_match fs sbs = go fs - where go [] = Nothing - go (fs@(FastString {fs_sbs=fs_sbs}) : ls) - | fs_sbs == sbs = Just fs - | otherwise = go ls --- bucket_match used to inline before changes to instance Eq ShortByteString --- in bytestring-0.12, which made it slightly larger than inlining threshold. --- Non-inlining causes a small, but measurable performance regression, so let's force it. -{-# INLINE bucket_match #-} mkFastStringBytes :: Ptr Word8 -> Int -> FastString mkFastStringBytes !ptr !len = -- NB: Might as well use unsafeDupablePerformIO, since mkFastStringWith is -- idempotent. - unsafeDupablePerformIO $ do - sbs <- newSBSFromPtr ptr len - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs + unsafeDupablePerformIO $ newSBSFromPtr ptr len newSBSFromPtr :: Ptr a -> Int -> IO ShortByteString newSBSFromPtr (Ptr src#) (I# len#) = @@ -538,24 +417,18 @@ newSBSFromPtr (Ptr src#) (I# len#) = -- | Create a 'FastString' by copying an existing 'ByteString' mkFastStringByteString :: ByteString -> FastString -mkFastStringByteString bs = - let sbs = SBS.toShort bs in - inlinePerformIO $ - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs +mkFastStringByteString = SBS.toShort -- | Create a 'FastString' from an existing 'ShortByteString' without -- copying. mkFastStringShortByteString :: ShortByteString -> FastString -mkFastStringShortByteString sbs = - inlinePerformIO $ mkFastStringWith (mkNewFastStringShortByteString sbs) sbs +mkFastStringShortByteString = id -- | Creates a UTF-8 encoded 'FastString' from a 'String' mkFastString :: String -> FastString -{-# NOINLINE[1] mkFastString #-} mkFastString str = - inlinePerformIO $ do let !sbs = utf8EncodeShortByteString str - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs + in sbs -- The following rule is used to avoid polluting the non-reclaimable FastString -- table with transient strings when we only want their encoding. @@ -568,17 +441,6 @@ mkFastStringByteList str = mkFastStringShortByteString (SBS.pack str) -- | Creates a (lazy) Z-encoded 'FastString' from a 'ShortByteString' and -- account the number of forced z-strings into the passed 'FastMutInt'. -mkZFastString :: FastMutInt -> ShortByteString -> FastZString -mkZFastString n_zencs sbs = unsafePerformIO $ do - _ <- atomicFetchAddFastMut n_zencs 1 - return $ mkFastZStringString (zEncodeString (utf8DecodeShortByteString sbs)) - -mkNewFastStringShortByteString :: ShortByteString -> Int - -> FastMutInt -> IO FastString -mkNewFastStringShortByteString sbs uid n_zencs = do - let zstr = mkZFastString n_zencs sbs - chars = utf8CountCharsShortByteString sbs - return (FastString uid chars sbs zstr) hashStr :: ShortByteString -> Int -- produce a hash value between 0 & m (inclusive) @@ -603,15 +465,15 @@ hashStr sbs@(SBS.SBS ba#) = loop 0# 0# -- | Returns the length of the 'FastString' in characters lengthFS :: FastString -> Int -lengthFS fs = n_chars fs +lengthFS = inlinePerformIO . countUTF8Chars -- | Returns @True@ if the 'FastString' is empty nullFS :: FastString -> Bool -nullFS fs = SBS.null $ fs_sbs fs +nullFS = SBS.null -- | Lazily unpacks and decodes the FastString unpackFS :: FastString -> String -unpackFS fs = utf8DecodeShortByteString $ fs_sbs fs +unpackFS = utf8DecodeShortByteString -- | Returns a Z-encoded version of a 'FastString'. This might be the -- original, if it was already Z-encoded. The first time this @@ -619,14 +481,13 @@ unpackFS fs = utf8DecodeShortByteString $ fs_sbs fs -- memoized. -- zEncodeFS :: FastString -> FastZString -zEncodeFS fs = fs_zenc fs +zEncodeFS = mkFastZStringString . zEncodeString . utf8DecodeShortByteString appendFS :: FastString -> FastString -> FastString -appendFS fs1 fs2 = mkFastStringShortByteString - $ (Semi.<>) (fs_sbs fs1) (fs_sbs fs2) +appendFS = (Semi.<>) concatFS :: [FastString] -> FastString -concatFS = mkFastStringShortByteString . mconcat . map fs_sbs +concatFS = mconcat consFS :: Char -> FastString -> FastString consFS c fs = mkFastString (c : unpackFS fs) @@ -638,7 +499,7 @@ unconsFS fs = (chr : str) -> Just (chr, mkFastString str) uniqueOfFS :: FastString -> Int -uniqueOfFS fs = uniq fs +uniqueOfFS = hashStr nilFS :: FastString nilFS = mkFastString "" ===================================== compiler/GHC/Types/Unique.hs ===================================== @@ -19,6 +19,7 @@ Haskell). {-# LANGUAGE CPP #-} {-# LANGUAGE MagicHash #-} +{-# LANGUAGE TypeSynonymInstances #-} module GHC.Types.Unique ( -- * Main data types View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/be10e61a998202568fbc12d8f29cf08bad7ad9f2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/be10e61a998202568fbc12d8f29cf08bad7ad9f2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 13:36:34 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 06 Jun 2024 09:36:34 -0400 Subject: [Git][ghc/ghc][wip/romes/faststring-is-shortbytestring] Make FastString a ShortByteStr Message-ID: <6661bb6219b03_12ae2129dea706305@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/faststring-is-shortbytestring at Glasgow Haskell Compiler / GHC Commits: aaf2e3dd by Rodrigo Mesquita at 2024-06-06T15:36:20+02:00 Make FastString a ShortByteStr - - - - - 2 changed files: - compiler/GHC/Data/FastString.hs - compiler/GHC/Types/Unique.hs Changes: ===================================== compiler/GHC/Data/FastString.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE MagicHash #-} @@ -60,7 +61,7 @@ module GHC.Data.FastString lengthFZS, -- * FastStrings - FastString(..), -- not abstract, for now. + FastString, -- not abstract, for now. NonDetFastString (..), LexicalFastString (..), @@ -115,7 +116,6 @@ import GHC.Prelude.Basic as Prelude import GHC.Utils.Encoding import GHC.Utils.IO.Unsafe import GHC.Utils.Panic.Plain -import GHC.Utils.Misc import GHC.Data.FastMutInt import Control.Concurrent.MVar @@ -149,16 +149,16 @@ import GHC.IO -- | Gives the Modified UTF-8 encoded bytes corresponding to a 'FastString' bytesFS, fastStringToByteString :: FastString -> ByteString {-# INLINE[1] bytesFS #-} -bytesFS f = SBS.fromShort $ fs_sbs f +bytesFS f = SBS.fromShort $ f {-# DEPRECATED fastStringToByteString "Use `bytesFS` instead" #-} fastStringToByteString = bytesFS fastStringToShortByteString :: FastString -> ShortByteString -fastStringToShortByteString = fs_sbs +fastStringToShortByteString = id fastStringToShortText :: FastString -> ShortText -fastStringToShortText = ShortText . fs_sbs +fastStringToShortText = ShortText fastZStringToByteString :: FastZString -> ByteString fastZStringToByteString (FastZString bs) = bs @@ -167,8 +167,6 @@ fastZStringToByteString (FastZString bs) = bs unsafeMkByteString :: String -> ByteString unsafeMkByteString = BSC.pack -hashFastString :: FastString -> Int -hashFastString fs = hashStr $ fs_sbs fs -- ----------------------------------------------------------------------------- @@ -205,56 +203,24 @@ comparison. It is also associated with a lazy reference to the Z-encoding of this string which is used by the compiler internally. -} -data FastString = FastString { - uniq :: {-# UNPACK #-} !Int, -- unique id - n_chars :: {-# UNPACK #-} !Int, -- number of chars - fs_sbs :: {-# UNPACK #-} !ShortByteString, - fs_zenc :: FastZString - -- ^ Lazily computed Z-encoding of this string. See Note [Z-Encoding] in - -- GHC.Utils.Encoding. - -- - -- Since 'FastString's are globally memoized this is computed at most - -- once for any given string. - } - -instance Eq FastString where - f1 == f2 = uniq f1 == uniq f2 +type FastString = ShortByteString -- We don't provide any "Ord FastString" instance to force you to think about -- which ordering you want: -- * lexical: deterministic, O(n). Cf lexicalCompareFS and LexicalFastString. -- * by unique: non-deterministic, O(1). Cf uniqCompareFS and NonDetFastString. -instance IsString FastString where - fromString = fsLit -instance Semi.Semigroup FastString where - (<>) = appendFS -instance Monoid FastString where - mempty = nilFS - mappend = (Semi.<>) - mconcat = concatFS -instance Show FastString where - show fs = show (unpackFS fs) -instance Data FastString where - -- don't traverse? - toConstr _ = abstractConstr "FastString" - gunfold _ _ = error "gunfold" - dataTypeOf _ = mkNoRepType "FastString" -instance NFData FastString where - rnf fs = seq fs () -- | Compare FastString lexically -- -- If you don't care about the lexical ordering, use `uniqCompareFS` instead. lexicalCompareFS :: FastString -> FastString -> Ordering -lexicalCompareFS fs1 fs2 = - if uniq fs1 == uniq fs2 then EQ else - utf8CompareShortByteString (fs_sbs fs1) (fs_sbs fs2) +lexicalCompareFS = compare -- perform a lexical comparison taking into account the Modified UTF-8 -- encoding we use (cf #18562) @@ -262,7 +228,7 @@ lexicalCompareFS fs1 fs2 = -- -- Much cheaper than `lexicalCompareFS` but non-deterministic! uniqCompareFS :: FastString -> FastString -> Ordering -uniqCompareFS fs1 fs2 = compare (uniq fs1) (uniq fs2) +uniqCompareFS = compare -- | Non-deterministic FastString -- @@ -332,48 +298,10 @@ Following parameters are determined based on: * Stats of @echo :browse | ghc --interactive -dfaststring-stats >/dev/null@: on 2018-10-24, we have 13920 entries. -} -segmentBits, numSegments, segmentMask, initialNumBuckets :: Int -segmentBits = 8 +numSegments, initialNumBuckets :: Int numSegments = 256 -- bit segmentBits -segmentMask = 0xff -- bit segmentBits - 1 initialNumBuckets = 64 -hashToSegment# :: Int# -> Int# -hashToSegment# hash# = hash# `andI#` segmentMask# - where - !(I# segmentMask#) = segmentMask - -hashToIndex# :: MutableArray# RealWorld [FastString] -> Int# -> Int# -hashToIndex# buckets# hash# = - (hash# `uncheckedIShiftRL#` segmentBits#) `remInt#` size# - where - !(I# segmentBits#) = segmentBits - size# = sizeofMutableArray# buckets# - -maybeResizeSegment :: IORef FastStringTableSegment -> IO FastStringTableSegment -maybeResizeSegment segmentRef = do - segment@(FastStringTableSegment lock counter old#) <- readIORef segmentRef - let oldSize# = sizeofMutableArray# old# - newSize# = oldSize# *# 2# - (I# n#) <- readFastMutInt counter - if isTrue# (n# <# newSize#) -- maximum load of 1 - then return segment - else do - resizedSegment@(FastStringTableSegment _ _ new#) <- IO $ \s1# -> - case newArray# newSize# [] s1# of - (# s2#, arr# #) -> (# s2#, FastStringTableSegment lock counter arr# #) - forM_ [0 .. (I# oldSize#) - 1] $ \(I# i#) -> do - fsList <- IO $ readArray# old# i# - forM_ fsList $ \fs -> do - let -- Shall we store in hash value in FastString instead? - !(I# hash#) = hashFastString fs - idx# = hashToIndex# new# hash# - IO $ \s1# -> - case readArray# new# idx# s1# of - (# s2#, bucket #) -> case writeArray# new# idx# (fs: bucket) s2# of - s3# -> (# s3#, () #) - writeIORef segmentRef resizedSegment - return resizedSegment {-# NOINLINE stringTable #-} stringTable :: FastStringTable @@ -473,60 +401,12 @@ The procedure goes like this: * Otherwise, insert and return the string we created. -} -mkFastStringWith - :: (Int -> FastMutInt-> IO FastString) -> ShortByteString -> IO FastString -mkFastStringWith mk_fs sbs = do - FastStringTableSegment lock _ buckets# <- readIORef segmentRef - let idx# = hashToIndex# buckets# hash# - bucket <- IO $ readArray# buckets# idx# - case bucket_match bucket sbs of - Just found -> return found - Nothing -> do - -- The withMVar below is not dupable. It can lead to deadlock if it is - -- only run partially and putMVar is not called after takeMVar. - noDuplicate - n <- get_uid - new_fs <- mk_fs n n_zencs - withMVar lock $ \_ -> insert new_fs - where - !(FastStringTable uid n_zencs segments#) = stringTable - get_uid = atomicFetchAddFastMut uid 1 - - !(I# hash#) = hashStr sbs - (# segmentRef #) = indexArray# segments# (hashToSegment# hash#) - insert fs = do - FastStringTableSegment _ counter buckets# <- maybeResizeSegment segmentRef - let idx# = hashToIndex# buckets# hash# - bucket <- IO $ readArray# buckets# idx# - case bucket_match bucket sbs of - -- The FastString was added by another thread after previous read and - -- before we acquired the write lock. - Just found -> return found - Nothing -> do - IO $ \s1# -> - case writeArray# buckets# idx# (fs : bucket) s1# of - s2# -> (# s2#, () #) - _ <- atomicFetchAddFastMut counter 1 - return fs - -bucket_match :: [FastString] -> ShortByteString -> Maybe FastString -bucket_match fs sbs = go fs - where go [] = Nothing - go (fs@(FastString {fs_sbs=fs_sbs}) : ls) - | fs_sbs == sbs = Just fs - | otherwise = go ls --- bucket_match used to inline before changes to instance Eq ShortByteString --- in bytestring-0.12, which made it slightly larger than inlining threshold. --- Non-inlining causes a small, but measurable performance regression, so let's force it. -{-# INLINE bucket_match #-} mkFastStringBytes :: Ptr Word8 -> Int -> FastString mkFastStringBytes !ptr !len = -- NB: Might as well use unsafeDupablePerformIO, since mkFastStringWith is -- idempotent. - unsafeDupablePerformIO $ do - sbs <- newSBSFromPtr ptr len - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs + unsafeDupablePerformIO $ newSBSFromPtr ptr len newSBSFromPtr :: Ptr a -> Int -> IO ShortByteString newSBSFromPtr (Ptr src#) (I# len#) = @@ -538,24 +418,18 @@ newSBSFromPtr (Ptr src#) (I# len#) = -- | Create a 'FastString' by copying an existing 'ByteString' mkFastStringByteString :: ByteString -> FastString -mkFastStringByteString bs = - let sbs = SBS.toShort bs in - inlinePerformIO $ - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs +mkFastStringByteString = SBS.toShort -- | Create a 'FastString' from an existing 'ShortByteString' without -- copying. mkFastStringShortByteString :: ShortByteString -> FastString -mkFastStringShortByteString sbs = - inlinePerformIO $ mkFastStringWith (mkNewFastStringShortByteString sbs) sbs +mkFastStringShortByteString = id -- | Creates a UTF-8 encoded 'FastString' from a 'String' mkFastString :: String -> FastString -{-# NOINLINE[1] mkFastString #-} mkFastString str = - inlinePerformIO $ do let !sbs = utf8EncodeShortByteString str - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs + in sbs -- The following rule is used to avoid polluting the non-reclaimable FastString -- table with transient strings when we only want their encoding. @@ -568,17 +442,6 @@ mkFastStringByteList str = mkFastStringShortByteString (SBS.pack str) -- | Creates a (lazy) Z-encoded 'FastString' from a 'ShortByteString' and -- account the number of forced z-strings into the passed 'FastMutInt'. -mkZFastString :: FastMutInt -> ShortByteString -> FastZString -mkZFastString n_zencs sbs = unsafePerformIO $ do - _ <- atomicFetchAddFastMut n_zencs 1 - return $ mkFastZStringString (zEncodeString (utf8DecodeShortByteString sbs)) - -mkNewFastStringShortByteString :: ShortByteString -> Int - -> FastMutInt -> IO FastString -mkNewFastStringShortByteString sbs uid n_zencs = do - let zstr = mkZFastString n_zencs sbs - chars = utf8CountCharsShortByteString sbs - return (FastString uid chars sbs zstr) hashStr :: ShortByteString -> Int -- produce a hash value between 0 & m (inclusive) @@ -603,15 +466,15 @@ hashStr sbs@(SBS.SBS ba#) = loop 0# 0# -- | Returns the length of the 'FastString' in characters lengthFS :: FastString -> Int -lengthFS fs = n_chars fs +lengthFS = SBS.length -- romes: does this return utf8 length? -- | Returns @True@ if the 'FastString' is empty nullFS :: FastString -> Bool -nullFS fs = SBS.null $ fs_sbs fs +nullFS = SBS.null -- | Lazily unpacks and decodes the FastString unpackFS :: FastString -> String -unpackFS fs = utf8DecodeShortByteString $ fs_sbs fs +unpackFS = utf8DecodeShortByteString -- | Returns a Z-encoded version of a 'FastString'. This might be the -- original, if it was already Z-encoded. The first time this @@ -619,14 +482,13 @@ unpackFS fs = utf8DecodeShortByteString $ fs_sbs fs -- memoized. -- zEncodeFS :: FastString -> FastZString -zEncodeFS fs = fs_zenc fs +zEncodeFS = mkFastZStringString . zEncodeString . utf8DecodeShortByteString appendFS :: FastString -> FastString -> FastString -appendFS fs1 fs2 = mkFastStringShortByteString - $ (Semi.<>) (fs_sbs fs1) (fs_sbs fs2) +appendFS = (Semi.<>) concatFS :: [FastString] -> FastString -concatFS = mkFastStringShortByteString . mconcat . map fs_sbs +concatFS = mconcat consFS :: Char -> FastString -> FastString consFS c fs = mkFastString (c : unpackFS fs) @@ -638,7 +500,7 @@ unconsFS fs = (chr : str) -> Just (chr, mkFastString str) uniqueOfFS :: FastString -> Int -uniqueOfFS fs = uniq fs +uniqueOfFS = hashStr nilFS :: FastString nilFS = mkFastString "" ===================================== compiler/GHC/Types/Unique.hs ===================================== @@ -19,6 +19,7 @@ Haskell). {-# LANGUAGE CPP #-} {-# LANGUAGE MagicHash #-} +{-# LANGUAGE TypeSynonymInstances #-} module GHC.Types.Unique ( -- * Main data types View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aaf2e3ddb8256fd9cd1be79c80c780a1dcb69b2f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/aaf2e3ddb8256fd9cd1be79c80c780a1dcb69b2f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 13:48:37 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Thu, 06 Jun 2024 09:48:37 -0400 Subject: [Git][ghc/ghc][wip/T24945] rts: cleanup inlining logic Message-ID: <6661be35a7901_12ae212c54cb463567@gitlab.mail> Cheng Shao pushed to branch wip/T24945 at Glasgow Haskell Compiler / GHC Commits: f082ae24 by Cheng Shao at 2024-06-06T13:45:59+00:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 2 changed files: - rts/Inlines.c - rts/include/Stg.h Changes: ===================================== rts/Inlines.c ===================================== @@ -1,6 +1,7 @@ -// all functions declared with EXTERN_INLINE in the header files get -// compiled for real here, just in case the definition was not inlined -// at some call site: +// All functions declared with EXTERN_INLINE in the header files get +// compiled for real here. Some of them are called by Cmm (e.g. +// recordClosureMutated) and therefore the real thing needs to reside +// in Inlines.o for Cmm ccall to work. #define KEEP_INLINES #include "rts/PosixSource.h" #include "Rts.h" ===================================== rts/include/Stg.h ===================================== @@ -114,57 +114,19 @@ * 'Portable' inlining: * INLINE_HEADER is for inline functions in header files (macros) * STATIC_INLINE is for inline functions in source files - * EXTERN_INLINE is for functions that we want to inline sometimes - * (we also compile a static version of the function; see Inlines.c) + * EXTERN_INLINE is for functions that may be called in Cmm + * (we also compile a static version of an EXTERN_INLINE function; see Inlines.c) */ -// We generally assume C99 semantics albeit these two definitions work fine even -// when gnu90 semantics are active (i.e. when __GNUC_GNU_INLINE__ is defined or -// when a GCC older than 4.2 is used) -// -// The problem, however, is with 'extern inline' whose semantics significantly -// differs between gnu90 and C99 #define INLINE_HEADER static inline #define STATIC_INLINE static inline -// Figure out whether `__attributes__((gnu_inline))` is needed -// to force gnu90-style 'external inline' semantics. -#if defined(FORCE_GNU_INLINE) -// disable auto-detection since HAVE_GNU_INLINE has been defined externally -#elif defined(__GNUC_GNU_INLINE__) && __GNUC__ == 4 && __GNUC_MINOR__ == 2 -// GCC 4.2.x didn't properly support C99 inline semantics (GCC 4.3 was the first -// release to properly support C99 inline semantics), and therefore warned when -// using 'extern inline' while in C99 mode unless `__attributes__((gnu_inline))` -// was explicitly set. -# define FORCE_GNU_INLINE 1 -#endif - -#if defined(FORCE_GNU_INLINE) -// Force compiler into gnu90 semantics -# if defined(KEEP_INLINES) -# define EXTERN_INLINE inline __attribute__((gnu_inline)) -# else -# define EXTERN_INLINE extern inline __attribute__((gnu_inline)) -# endif -#elif defined(__GNUC_GNU_INLINE__) -// we're currently in gnu90 inline mode by default and -// __attribute__((gnu_inline)) may not be supported, so better leave it off -# if defined(KEEP_INLINES) -# define EXTERN_INLINE inline -# else -# define EXTERN_INLINE extern inline -# endif -#else -// Assume C99 semantics (yes, this curiously results in swapped definitions!) -// This is the preferred branch, and at some point we may drop support for -// compilers not supporting C99 semantics altogether. +// See comment in rts/Inlines.c for explanation. # if defined(KEEP_INLINES) # define EXTERN_INLINE extern inline # else -# define EXTERN_INLINE inline +# define EXTERN_INLINE static inline # endif -#endif - /* * GCC attributes View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f082ae246c25f6e103e67e6ba4df8e36a15fd2c3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f082ae246c25f6e103e67e6ba4df8e36a15fd2c3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 13:53:06 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 06 Jun 2024 09:53:06 -0400 Subject: [Git][ghc/ghc][wip/romes/faststring-is-shortbytestring] Make FastString a ShortByteStr Message-ID: <6661bf4259b1b_12ae212dbfb9464044@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/faststring-is-shortbytestring at Glasgow Haskell Compiler / GHC Commits: c96c3a95 by Rodrigo Mesquita at 2024-06-06T15:52:54+02:00 Make FastString a ShortByteStr - - - - - 2 changed files: - compiler/GHC/Data/FastString.hs - compiler/GHC/Types/Unique.hs Changes: ===================================== compiler/GHC/Data/FastString.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE MagicHash #-} @@ -60,7 +61,7 @@ module GHC.Data.FastString lengthFZS, -- * FastStrings - FastString(..), -- not abstract, for now. + FastString, -- not abstract, for now. NonDetFastString (..), LexicalFastString (..), @@ -115,7 +116,6 @@ import GHC.Prelude.Basic as Prelude import GHC.Utils.Encoding import GHC.Utils.IO.Unsafe import GHC.Utils.Panic.Plain -import GHC.Utils.Misc import GHC.Data.FastMutInt import Control.Concurrent.MVar @@ -148,17 +148,16 @@ import GHC.IO -- | Gives the Modified UTF-8 encoded bytes corresponding to a 'FastString' bytesFS, fastStringToByteString :: FastString -> ByteString -{-# INLINE[1] bytesFS #-} -bytesFS f = SBS.fromShort $ fs_sbs f +bytesFS = SBS.fromShort {-# DEPRECATED fastStringToByteString "Use `bytesFS` instead" #-} fastStringToByteString = bytesFS fastStringToShortByteString :: FastString -> ShortByteString -fastStringToShortByteString = fs_sbs +fastStringToShortByteString = id fastStringToShortText :: FastString -> ShortText -fastStringToShortText = ShortText . fs_sbs +fastStringToShortText = ShortText fastZStringToByteString :: FastZString -> ByteString fastZStringToByteString (FastZString bs) = bs @@ -167,8 +166,6 @@ fastZStringToByteString (FastZString bs) = bs unsafeMkByteString :: String -> ByteString unsafeMkByteString = BSC.pack -hashFastString :: FastString -> Int -hashFastString fs = hashStr $ fs_sbs fs -- ----------------------------------------------------------------------------- @@ -205,56 +202,24 @@ comparison. It is also associated with a lazy reference to the Z-encoding of this string which is used by the compiler internally. -} -data FastString = FastString { - uniq :: {-# UNPACK #-} !Int, -- unique id - n_chars :: {-# UNPACK #-} !Int, -- number of chars - fs_sbs :: {-# UNPACK #-} !ShortByteString, - fs_zenc :: FastZString - -- ^ Lazily computed Z-encoding of this string. See Note [Z-Encoding] in - -- GHC.Utils.Encoding. - -- - -- Since 'FastString's are globally memoized this is computed at most - -- once for any given string. - } - -instance Eq FastString where - f1 == f2 = uniq f1 == uniq f2 +type FastString = ShortByteString -- We don't provide any "Ord FastString" instance to force you to think about -- which ordering you want: -- * lexical: deterministic, O(n). Cf lexicalCompareFS and LexicalFastString. -- * by unique: non-deterministic, O(1). Cf uniqCompareFS and NonDetFastString. -instance IsString FastString where - fromString = fsLit -instance Semi.Semigroup FastString where - (<>) = appendFS -instance Monoid FastString where - mempty = nilFS - mappend = (Semi.<>) - mconcat = concatFS -instance Show FastString where - show fs = show (unpackFS fs) -instance Data FastString where - -- don't traverse? - toConstr _ = abstractConstr "FastString" - gunfold _ _ = error "gunfold" - dataTypeOf _ = mkNoRepType "FastString" -instance NFData FastString where - rnf fs = seq fs () -- | Compare FastString lexically -- -- If you don't care about the lexical ordering, use `uniqCompareFS` instead. lexicalCompareFS :: FastString -> FastString -> Ordering -lexicalCompareFS fs1 fs2 = - if uniq fs1 == uniq fs2 then EQ else - utf8CompareShortByteString (fs_sbs fs1) (fs_sbs fs2) +lexicalCompareFS = compare -- perform a lexical comparison taking into account the Modified UTF-8 -- encoding we use (cf #18562) @@ -262,7 +227,7 @@ lexicalCompareFS fs1 fs2 = -- -- Much cheaper than `lexicalCompareFS` but non-deterministic! uniqCompareFS :: FastString -> FastString -> Ordering -uniqCompareFS fs1 fs2 = compare (uniq fs1) (uniq fs2) +uniqCompareFS = compare -- | Non-deterministic FastString -- @@ -332,48 +297,10 @@ Following parameters are determined based on: * Stats of @echo :browse | ghc --interactive -dfaststring-stats >/dev/null@: on 2018-10-24, we have 13920 entries. -} -segmentBits, numSegments, segmentMask, initialNumBuckets :: Int -segmentBits = 8 +numSegments, initialNumBuckets :: Int numSegments = 256 -- bit segmentBits -segmentMask = 0xff -- bit segmentBits - 1 initialNumBuckets = 64 -hashToSegment# :: Int# -> Int# -hashToSegment# hash# = hash# `andI#` segmentMask# - where - !(I# segmentMask#) = segmentMask - -hashToIndex# :: MutableArray# RealWorld [FastString] -> Int# -> Int# -hashToIndex# buckets# hash# = - (hash# `uncheckedIShiftRL#` segmentBits#) `remInt#` size# - where - !(I# segmentBits#) = segmentBits - size# = sizeofMutableArray# buckets# - -maybeResizeSegment :: IORef FastStringTableSegment -> IO FastStringTableSegment -maybeResizeSegment segmentRef = do - segment@(FastStringTableSegment lock counter old#) <- readIORef segmentRef - let oldSize# = sizeofMutableArray# old# - newSize# = oldSize# *# 2# - (I# n#) <- readFastMutInt counter - if isTrue# (n# <# newSize#) -- maximum load of 1 - then return segment - else do - resizedSegment@(FastStringTableSegment _ _ new#) <- IO $ \s1# -> - case newArray# newSize# [] s1# of - (# s2#, arr# #) -> (# s2#, FastStringTableSegment lock counter arr# #) - forM_ [0 .. (I# oldSize#) - 1] $ \(I# i#) -> do - fsList <- IO $ readArray# old# i# - forM_ fsList $ \fs -> do - let -- Shall we store in hash value in FastString instead? - !(I# hash#) = hashFastString fs - idx# = hashToIndex# new# hash# - IO $ \s1# -> - case readArray# new# idx# s1# of - (# s2#, bucket #) -> case writeArray# new# idx# (fs: bucket) s2# of - s3# -> (# s3#, () #) - writeIORef segmentRef resizedSegment - return resizedSegment {-# NOINLINE stringTable #-} stringTable :: FastStringTable @@ -473,60 +400,12 @@ The procedure goes like this: * Otherwise, insert and return the string we created. -} -mkFastStringWith - :: (Int -> FastMutInt-> IO FastString) -> ShortByteString -> IO FastString -mkFastStringWith mk_fs sbs = do - FastStringTableSegment lock _ buckets# <- readIORef segmentRef - let idx# = hashToIndex# buckets# hash# - bucket <- IO $ readArray# buckets# idx# - case bucket_match bucket sbs of - Just found -> return found - Nothing -> do - -- The withMVar below is not dupable. It can lead to deadlock if it is - -- only run partially and putMVar is not called after takeMVar. - noDuplicate - n <- get_uid - new_fs <- mk_fs n n_zencs - withMVar lock $ \_ -> insert new_fs - where - !(FastStringTable uid n_zencs segments#) = stringTable - get_uid = atomicFetchAddFastMut uid 1 - - !(I# hash#) = hashStr sbs - (# segmentRef #) = indexArray# segments# (hashToSegment# hash#) - insert fs = do - FastStringTableSegment _ counter buckets# <- maybeResizeSegment segmentRef - let idx# = hashToIndex# buckets# hash# - bucket <- IO $ readArray# buckets# idx# - case bucket_match bucket sbs of - -- The FastString was added by another thread after previous read and - -- before we acquired the write lock. - Just found -> return found - Nothing -> do - IO $ \s1# -> - case writeArray# buckets# idx# (fs : bucket) s1# of - s2# -> (# s2#, () #) - _ <- atomicFetchAddFastMut counter 1 - return fs - -bucket_match :: [FastString] -> ShortByteString -> Maybe FastString -bucket_match fs sbs = go fs - where go [] = Nothing - go (fs@(FastString {fs_sbs=fs_sbs}) : ls) - | fs_sbs == sbs = Just fs - | otherwise = go ls --- bucket_match used to inline before changes to instance Eq ShortByteString --- in bytestring-0.12, which made it slightly larger than inlining threshold. --- Non-inlining causes a small, but measurable performance regression, so let's force it. -{-# INLINE bucket_match #-} mkFastStringBytes :: Ptr Word8 -> Int -> FastString mkFastStringBytes !ptr !len = -- NB: Might as well use unsafeDupablePerformIO, since mkFastStringWith is -- idempotent. - unsafeDupablePerformIO $ do - sbs <- newSBSFromPtr ptr len - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs + unsafeDupablePerformIO $ newSBSFromPtr ptr len newSBSFromPtr :: Ptr a -> Int -> IO ShortByteString newSBSFromPtr (Ptr src#) (I# len#) = @@ -538,29 +417,18 @@ newSBSFromPtr (Ptr src#) (I# len#) = -- | Create a 'FastString' by copying an existing 'ByteString' mkFastStringByteString :: ByteString -> FastString -mkFastStringByteString bs = - let sbs = SBS.toShort bs in - inlinePerformIO $ - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs +mkFastStringByteString = SBS.toShort -- | Create a 'FastString' from an existing 'ShortByteString' without -- copying. mkFastStringShortByteString :: ShortByteString -> FastString -mkFastStringShortByteString sbs = - inlinePerformIO $ mkFastStringWith (mkNewFastStringShortByteString sbs) sbs +mkFastStringShortByteString = id -- | Creates a UTF-8 encoded 'FastString' from a 'String' mkFastString :: String -> FastString -{-# NOINLINE[1] mkFastString #-} mkFastString str = - inlinePerformIO $ do let !sbs = utf8EncodeShortByteString str - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs - --- The following rule is used to avoid polluting the non-reclaimable FastString --- table with transient strings when we only want their encoding. -{-# RULES -"bytesFS/mkFastString" forall x. bytesFS (mkFastString x) = utf8EncodeByteString x #-} + in sbs -- | Creates a 'FastString' from a UTF-8 encoded @[Word8]@ mkFastStringByteList :: [Word8] -> FastString @@ -568,17 +436,6 @@ mkFastStringByteList str = mkFastStringShortByteString (SBS.pack str) -- | Creates a (lazy) Z-encoded 'FastString' from a 'ShortByteString' and -- account the number of forced z-strings into the passed 'FastMutInt'. -mkZFastString :: FastMutInt -> ShortByteString -> FastZString -mkZFastString n_zencs sbs = unsafePerformIO $ do - _ <- atomicFetchAddFastMut n_zencs 1 - return $ mkFastZStringString (zEncodeString (utf8DecodeShortByteString sbs)) - -mkNewFastStringShortByteString :: ShortByteString -> Int - -> FastMutInt -> IO FastString -mkNewFastStringShortByteString sbs uid n_zencs = do - let zstr = mkZFastString n_zencs sbs - chars = utf8CountCharsShortByteString sbs - return (FastString uid chars sbs zstr) hashStr :: ShortByteString -> Int -- produce a hash value between 0 & m (inclusive) @@ -603,15 +460,15 @@ hashStr sbs@(SBS.SBS ba#) = loop 0# 0# -- | Returns the length of the 'FastString' in characters lengthFS :: FastString -> Int -lengthFS fs = n_chars fs +lengthFS = SBS.length -- romes: does this return utf8 length? -- | Returns @True@ if the 'FastString' is empty nullFS :: FastString -> Bool -nullFS fs = SBS.null $ fs_sbs fs +nullFS = SBS.null -- | Lazily unpacks and decodes the FastString unpackFS :: FastString -> String -unpackFS fs = utf8DecodeShortByteString $ fs_sbs fs +unpackFS = utf8DecodeShortByteString -- | Returns a Z-encoded version of a 'FastString'. This might be the -- original, if it was already Z-encoded. The first time this @@ -619,14 +476,13 @@ unpackFS fs = utf8DecodeShortByteString $ fs_sbs fs -- memoized. -- zEncodeFS :: FastString -> FastZString -zEncodeFS fs = fs_zenc fs +zEncodeFS = mkFastZStringString . zEncodeString . utf8DecodeShortByteString appendFS :: FastString -> FastString -> FastString -appendFS fs1 fs2 = mkFastStringShortByteString - $ (Semi.<>) (fs_sbs fs1) (fs_sbs fs2) +appendFS = (Semi.<>) concatFS :: [FastString] -> FastString -concatFS = mkFastStringShortByteString . mconcat . map fs_sbs +concatFS = mconcat consFS :: Char -> FastString -> FastString consFS c fs = mkFastString (c : unpackFS fs) @@ -638,7 +494,7 @@ unconsFS fs = (chr : str) -> Just (chr, mkFastString str) uniqueOfFS :: FastString -> Int -uniqueOfFS fs = uniq fs +uniqueOfFS = hashStr nilFS :: FastString nilFS = mkFastString "" ===================================== compiler/GHC/Types/Unique.hs ===================================== @@ -19,6 +19,7 @@ Haskell). {-# LANGUAGE CPP #-} {-# LANGUAGE MagicHash #-} +{-# LANGUAGE TypeSynonymInstances #-} module GHC.Types.Unique ( -- * Main data types View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c96c3a9593c92181f36c64c20b5a9942d3462e80 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c96c3a9593c92181f36c64c20b5a9942d3462e80 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 14:39:54 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 06 Jun 2024 10:39:54 -0400 Subject: [Git][ghc/ghc][master] Improve haddocks of Language.Haskell.Syntax.Pat.Pat Message-ID: <6661ca3a3500b_12ae2135f72f8840d9@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 1 changed file: - compiler/Language/Haskell/Syntax/Pat.hs Changes: ===================================== compiler/Language/Haskell/Syntax/Pat.hs ===================================== @@ -57,62 +57,73 @@ import Data.List.NonEmpty (NonEmpty) type LPat p = XRec p (Pat p) -- | Pattern --- --- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang' - --- For details on above see Note [exact print annotations] in GHC.Parser.Annotation data Pat p = ------------ Simple patterns --------------- - WildPat (XWildPat p) -- ^ Wildcard Pattern - -- The sole reason for a type on a WildPat is to - -- support hsPatType :: Pat Id -> Type - - -- AZ:TODO above comment needs to be updated + WildPat (XWildPat p) + -- ^ Wildcard Pattern (@_@) | VarPat (XVarPat p) - (LIdP p) -- ^ Variable Pattern + (LIdP p) + -- ^ Variable Pattern, e.g. @x@ - -- See Note [Located RdrNames] in GHC.Hs.Expr + -- See Note [Located RdrNames] in GHC.Hs.Expr | LazyPat (XLazyPat p) - (LPat p) -- ^ Lazy Pattern - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnTilde' + (LPat p) + -- ^ Lazy Pattern, e.g. @~x@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnTilde' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | AsPat (XAsPat p) (LIdP p) - (LPat p) -- ^ As pattern - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnAt' + (LPat p) + -- ^ As pattern, e.g. @x\@pat@ + -- + -- - Location of '@' is captured by 'GHC.Parser.Annotation.EpToken' @"\@"@ -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | ParPat (XParPat p) - (LPat p) -- ^ Parenthesised pattern - -- See Note [Parens in HsSyn] in GHC.Hs.Expr - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'('@, - -- 'GHC.Parser.Annotation.AnnClose' @')'@ + (LPat p) + -- ^ Parenthesised pattern, e.g. @(x)@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : + -- 'GHC.Parser.Annotation.AnnOpen' @'('@, + -- 'GHC.Parser.Annotation.AnnClose' @')'@ + + -- See Note [Parens in HsSyn] in GHC.Hs.Expr -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | BangPat (XBangPat p) - (LPat p) -- ^ Bang pattern - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang' + (LPat p) + -- ^ Bang pattern, e.g. @!x@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation ------------ Lists, tuples, arrays --------------- | ListPat (XListPat p) [LPat p] + -- ^ Syntactic List, e.g. @[x]@ or @[x,y]@ (but not @[]@ nor @(x:xs)@ which are represented using 'ConPat') + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : + -- 'GHC.Parser.Annotation.AnnOpen' @'['@, + -- 'GHC.Parser.Annotation.AnnClose' @']'@ - -- ^ Syntactic List + -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation + + | -- | Tuple pattern, e.g. @(x, y)@ -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'['@, - -- 'GHC.Parser.Annotation.AnnClose' @']'@ + -- - 'GHC.Parser.Annotation.AnnKeywordId' : + -- 'GHC.Parser.Annotation.AnnOpen' @'('@ or @'(#'@, + -- 'GHC.Parser.Annotation.AnnClose' @')'@ or @'#)'@ -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation + TuplePat (XTuplePat p) -- ^ After typechecking, holds the types of the tuple components + [LPat p] -- ^ Tuple sub-patterns + Boxity -- ^ UnitPat is TuplePat [] - | TuplePat (XTuplePat p) - -- after typechecking, holds the types of the tuple components - [LPat p] -- Tuple sub-patterns - Boxity -- UnitPat is TuplePat [] -- You might think that the post typechecking Type was redundant, -- because we can get the pattern type by getting the types of the -- sub-patterns. @@ -129,11 +140,6 @@ data Pat p -- of the tuple is of type 'a' not Int. See selectMatchVar -- (June 14: I'm not sure this comment is right; the sub-patterns -- will be wrapped in CoPats, no?) - -- ^ Tuple sub-patterns - -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : - -- 'GHC.Parser.Annotation.AnnOpen' @'('@ or @'(#'@, - -- 'GHC.Parser.Annotation.AnnClose' @')'@ or @'#)'@ | OrPat (XOrPat p) (NonEmpty (LPat p)) @@ -143,7 +149,8 @@ data Pat p (LPat p) -- Sum sub-pattern ConTag -- Alternative (one-based) SumWidth -- Arity (INVARIANT: ≥ 2) - -- ^ Anonymous sum pattern + + -- ^ Anonymous sum pattern, e.g. @(# x | #)@. Used by @-XUnboxedSums@ -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : -- 'GHC.Parser.Annotation.AnnOpen' @'(#'@, @@ -157,35 +164,40 @@ data Pat p pat_con :: XRec p (ConLikeP p), pat_args :: HsConPatDetails p } - -- ^ Constructor Pattern + -- ^ Constructor Pattern, e.g. @[]@ or @Nothing@ ------------ View patterns --------------- - -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnRarrow' - -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | ViewPat (XViewPat p) (LHsExpr p) (LPat p) - -- ^ View Pattern + -- ^ View Pattern, e.g. @someFun -> pat at . Used by @-XViewPatterns@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnRarrow' + + -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation ------------ Pattern splices --------------- - -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'$('@ - -- 'GHC.Parser.Annotation.AnnClose' @')'@ - -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | SplicePat (XSplicePat p) - (HsUntypedSplice p) -- ^ Splice Pattern (Includes quasi-quotes) + (HsUntypedSplice p) + -- ^ Splice Pattern (Includes quasi-quotes @$(...)@) + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId': + -- 'GHC.Parser.Annotation.AnnOpen' @'$('@ + -- 'GHC.Parser.Annotation.AnnClose' @')'@ + + -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation ------------ Literal and n+k patterns --------------- | LitPat (XLitPat p) - (HsLit p) -- ^ Literal Pattern - -- Used for *non-overloaded* literal patterns: - -- Int#, Char#, Int, Char, String, etc. - - | NPat -- Natural Pattern - -- Used for all overloaded literals, - -- including overloaded strings with -XOverloadedStrings - (XNPat p) -- Overall type of pattern. Might be + (HsLit p) + -- ^ Literal Pattern + -- + -- Used for __non-overloaded__ literal patterns: + -- Int#, Char#, Int, Char, String, etc. + + | NPat (XNPat p) -- Overall type of pattern. Might be -- different than the literal's type -- if (==) or negate changes the type (XRec p (HsOverLit p)) -- ALWAYS positive @@ -194,7 +206,8 @@ data Pat p -- otherwise (SyntaxExpr p) -- Equality checker, of type t->t->Bool - -- ^ Natural Pattern + -- ^ Natural Pattern, used for all overloaded literals, including overloaded Strings + -- with @-XOverloadedStrings@ -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnVal' @'+'@ @@ -208,30 +221,35 @@ data Pat p (SyntaxExpr p) -- (>=) function, of type t1->t2->Bool (SyntaxExpr p) -- Name of '-' (see GHC.Rename.Env.lookupSyntax) - -- ^ n+k pattern + -- ^ n+k pattern, e.g. @n+1@, enabled by @-XNPlusKPatterns@ extension ------------ Pattern type signatures --------------- - -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' - -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | SigPat (XSigPat p) -- After typechecker: Type (LPat p) -- Pattern with a type signature (HsPatSigType (NoGhcTc p)) -- Signature can bind both -- kind and type vars - -- ^ Pattern with a type signature + -- ^ Pattern with a type signature, e.g. @x :: Int@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' + + -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation - -- Embed the syntax of types into patterns. - -- Used with RequiredTypeArguments, e.g. fn (type t) = rhs - | EmbTyPat (XEmbTyPat p) + | -- | Embed the syntax of types into patterns. + -- Used with @-XRequiredTypeArguments@, e.g. @fn (type t) = rhs@ + EmbTyPat (XEmbTyPat p) (HsTyPat (NoGhcTc p)) - -- See Note [Invisible binders in functions] in GHC.Hs.Pat | InvisPat (XInvisPat p) (HsTyPat (NoGhcTc p)) + -- ^ Type abstraction which brings into scope type variables associated with invisible forall. Used by @-XTypeAbstractions at . + -- + -- The location of @\@@ is captured by 'GHC.Parser.Annotation.EpToken' @"\@"@ + + -- See Note [Invisible binders in functions] in GHC.Hs.Pat - -- Extension point; see Note [Trees That Grow] in Language.Haskell.Syntax.Extension - | XPat - !(XXPat p) + | -- | TTG Extension point; see Note [Trees That Grow] in Language.Haskell.Syntax.Extension + XPat !(XXPat p) type family ConLikeP x @@ -311,7 +329,7 @@ type HsRecUpdField p q = HsFieldBind (LAmbiguousFieldOcc p) (LHsExpr q) -- | Haskell Field Binding -- --- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnEqual', +-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnEqual' -- -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation data HsFieldBind lhs rhs = HsFieldBind { View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8650338d157564f7a38579c2d5d58d22b63a227a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8650338d157564f7a38579c2d5d58d22b63a227a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 14:40:42 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 06 Jun 2024 10:40:42 -0400 Subject: [Git][ghc/ghc][master] testsuite: bump T7653 timeout for wasm Message-ID: <6661ca6a9d02a_12ae21372c44887157@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 1 changed file: - libraries/base/tests/all.T Changes: ===================================== libraries/base/tests/all.T ===================================== @@ -189,6 +189,7 @@ test('CatEntail', normal, compile, ['']) # When running with WAY=ghci and profiled ways, T7653 uses a lot of memory. test('T7653', [when(opsys('mingw32'), skip), + when(arch('wasm32'), run_timeout_multiplier(5)), omit_ways(prof_ways + ghci_ways)], compile_and_run, ['']) test('T7787', normal, compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2eee65e1a4f441e99b79f3dc6e7d60492e4cad78 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2eee65e1a4f441e99b79f3dc6e7d60492e4cad78 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 14:50:26 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 06 Jun 2024 10:50:26 -0400 Subject: [Git][ghc/ghc][wip/romes/faststring-is-shortbytestring] Make FastString a ShortByteStr Message-ID: <6661ccb2dabc6_12ae21392572c92947@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/faststring-is-shortbytestring at Glasgow Haskell Compiler / GHC Commits: b1fc0e35 by Rodrigo Mesquita at 2024-06-06T16:50:14+02:00 Make FastString a ShortByteStr - - - - - 2 changed files: - compiler/GHC/Data/FastString.hs - compiler/GHC/Types/Unique.hs Changes: ===================================== compiler/GHC/Data/FastString.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE MagicHash #-} @@ -60,7 +61,7 @@ module GHC.Data.FastString lengthFZS, -- * FastStrings - FastString(..), -- not abstract, for now. + FastString, -- not abstract, for now. NonDetFastString (..), LexicalFastString (..), @@ -115,7 +116,6 @@ import GHC.Prelude.Basic as Prelude import GHC.Utils.Encoding import GHC.Utils.IO.Unsafe import GHC.Utils.Panic.Plain -import GHC.Utils.Misc import GHC.Data.FastMutInt import Control.Concurrent.MVar @@ -148,17 +148,16 @@ import GHC.IO -- | Gives the Modified UTF-8 encoded bytes corresponding to a 'FastString' bytesFS, fastStringToByteString :: FastString -> ByteString -{-# INLINE[1] bytesFS #-} -bytesFS f = SBS.fromShort $ fs_sbs f +bytesFS = SBS.fromShort {-# DEPRECATED fastStringToByteString "Use `bytesFS` instead" #-} fastStringToByteString = bytesFS fastStringToShortByteString :: FastString -> ShortByteString -fastStringToShortByteString = fs_sbs +fastStringToShortByteString = id fastStringToShortText :: FastString -> ShortText -fastStringToShortText = ShortText . fs_sbs +fastStringToShortText = ShortText fastZStringToByteString :: FastZString -> ByteString fastZStringToByteString (FastZString bs) = bs @@ -167,8 +166,6 @@ fastZStringToByteString (FastZString bs) = bs unsafeMkByteString :: String -> ByteString unsafeMkByteString = BSC.pack -hashFastString :: FastString -> Int -hashFastString fs = hashStr $ fs_sbs fs -- ----------------------------------------------------------------------------- @@ -205,56 +202,24 @@ comparison. It is also associated with a lazy reference to the Z-encoding of this string which is used by the compiler internally. -} -data FastString = FastString { - uniq :: {-# UNPACK #-} !Int, -- unique id - n_chars :: {-# UNPACK #-} !Int, -- number of chars - fs_sbs :: {-# UNPACK #-} !ShortByteString, - fs_zenc :: FastZString - -- ^ Lazily computed Z-encoding of this string. See Note [Z-Encoding] in - -- GHC.Utils.Encoding. - -- - -- Since 'FastString's are globally memoized this is computed at most - -- once for any given string. - } - -instance Eq FastString where - f1 == f2 = uniq f1 == uniq f2 +type FastString = ShortByteString -- We don't provide any "Ord FastString" instance to force you to think about -- which ordering you want: -- * lexical: deterministic, O(n). Cf lexicalCompareFS and LexicalFastString. -- * by unique: non-deterministic, O(1). Cf uniqCompareFS and NonDetFastString. -instance IsString FastString where - fromString = fsLit -instance Semi.Semigroup FastString where - (<>) = appendFS -instance Monoid FastString where - mempty = nilFS - mappend = (Semi.<>) - mconcat = concatFS -instance Show FastString where - show fs = show (unpackFS fs) -instance Data FastString where - -- don't traverse? - toConstr _ = abstractConstr "FastString" - gunfold _ _ = error "gunfold" - dataTypeOf _ = mkNoRepType "FastString" -instance NFData FastString where - rnf fs = seq fs () -- | Compare FastString lexically -- -- If you don't care about the lexical ordering, use `uniqCompareFS` instead. lexicalCompareFS :: FastString -> FastString -> Ordering -lexicalCompareFS fs1 fs2 = - if uniq fs1 == uniq fs2 then EQ else - utf8CompareShortByteString (fs_sbs fs1) (fs_sbs fs2) +lexicalCompareFS = compare -- perform a lexical comparison taking into account the Modified UTF-8 -- encoding we use (cf #18562) @@ -262,7 +227,7 @@ lexicalCompareFS fs1 fs2 = -- -- Much cheaper than `lexicalCompareFS` but non-deterministic! uniqCompareFS :: FastString -> FastString -> Ordering -uniqCompareFS fs1 fs2 = compare (uniq fs1) (uniq fs2) +uniqCompareFS = compare -- | Non-deterministic FastString -- @@ -332,48 +297,10 @@ Following parameters are determined based on: * Stats of @echo :browse | ghc --interactive -dfaststring-stats >/dev/null@: on 2018-10-24, we have 13920 entries. -} -segmentBits, numSegments, segmentMask, initialNumBuckets :: Int -segmentBits = 8 +numSegments, initialNumBuckets :: Int numSegments = 256 -- bit segmentBits -segmentMask = 0xff -- bit segmentBits - 1 initialNumBuckets = 64 -hashToSegment# :: Int# -> Int# -hashToSegment# hash# = hash# `andI#` segmentMask# - where - !(I# segmentMask#) = segmentMask - -hashToIndex# :: MutableArray# RealWorld [FastString] -> Int# -> Int# -hashToIndex# buckets# hash# = - (hash# `uncheckedIShiftRL#` segmentBits#) `remInt#` size# - where - !(I# segmentBits#) = segmentBits - size# = sizeofMutableArray# buckets# - -maybeResizeSegment :: IORef FastStringTableSegment -> IO FastStringTableSegment -maybeResizeSegment segmentRef = do - segment@(FastStringTableSegment lock counter old#) <- readIORef segmentRef - let oldSize# = sizeofMutableArray# old# - newSize# = oldSize# *# 2# - (I# n#) <- readFastMutInt counter - if isTrue# (n# <# newSize#) -- maximum load of 1 - then return segment - else do - resizedSegment@(FastStringTableSegment _ _ new#) <- IO $ \s1# -> - case newArray# newSize# [] s1# of - (# s2#, arr# #) -> (# s2#, FastStringTableSegment lock counter arr# #) - forM_ [0 .. (I# oldSize#) - 1] $ \(I# i#) -> do - fsList <- IO $ readArray# old# i# - forM_ fsList $ \fs -> do - let -- Shall we store in hash value in FastString instead? - !(I# hash#) = hashFastString fs - idx# = hashToIndex# new# hash# - IO $ \s1# -> - case readArray# new# idx# s1# of - (# s2#, bucket #) -> case writeArray# new# idx# (fs: bucket) s2# of - s3# -> (# s3#, () #) - writeIORef segmentRef resizedSegment - return resizedSegment {-# NOINLINE stringTable #-} stringTable :: FastStringTable @@ -473,60 +400,12 @@ The procedure goes like this: * Otherwise, insert and return the string we created. -} -mkFastStringWith - :: (Int -> FastMutInt-> IO FastString) -> ShortByteString -> IO FastString -mkFastStringWith mk_fs sbs = do - FastStringTableSegment lock _ buckets# <- readIORef segmentRef - let idx# = hashToIndex# buckets# hash# - bucket <- IO $ readArray# buckets# idx# - case bucket_match bucket sbs of - Just found -> return found - Nothing -> do - -- The withMVar below is not dupable. It can lead to deadlock if it is - -- only run partially and putMVar is not called after takeMVar. - noDuplicate - n <- get_uid - new_fs <- mk_fs n n_zencs - withMVar lock $ \_ -> insert new_fs - where - !(FastStringTable uid n_zencs segments#) = stringTable - get_uid = atomicFetchAddFastMut uid 1 - - !(I# hash#) = hashStr sbs - (# segmentRef #) = indexArray# segments# (hashToSegment# hash#) - insert fs = do - FastStringTableSegment _ counter buckets# <- maybeResizeSegment segmentRef - let idx# = hashToIndex# buckets# hash# - bucket <- IO $ readArray# buckets# idx# - case bucket_match bucket sbs of - -- The FastString was added by another thread after previous read and - -- before we acquired the write lock. - Just found -> return found - Nothing -> do - IO $ \s1# -> - case writeArray# buckets# idx# (fs : bucket) s1# of - s2# -> (# s2#, () #) - _ <- atomicFetchAddFastMut counter 1 - return fs - -bucket_match :: [FastString] -> ShortByteString -> Maybe FastString -bucket_match fs sbs = go fs - where go [] = Nothing - go (fs@(FastString {fs_sbs=fs_sbs}) : ls) - | fs_sbs == sbs = Just fs - | otherwise = go ls --- bucket_match used to inline before changes to instance Eq ShortByteString --- in bytestring-0.12, which made it slightly larger than inlining threshold. --- Non-inlining causes a small, but measurable performance regression, so let's force it. -{-# INLINE bucket_match #-} mkFastStringBytes :: Ptr Word8 -> Int -> FastString mkFastStringBytes !ptr !len = -- NB: Might as well use unsafeDupablePerformIO, since mkFastStringWith is -- idempotent. - unsafeDupablePerformIO $ do - sbs <- newSBSFromPtr ptr len - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs + unsafeDupablePerformIO $ newSBSFromPtr ptr len newSBSFromPtr :: Ptr a -> Int -> IO ShortByteString newSBSFromPtr (Ptr src#) (I# len#) = @@ -538,48 +417,23 @@ newSBSFromPtr (Ptr src#) (I# len#) = -- | Create a 'FastString' by copying an existing 'ByteString' mkFastStringByteString :: ByteString -> FastString -mkFastStringByteString bs = - let sbs = SBS.toShort bs in - inlinePerformIO $ - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs +mkFastStringByteString = SBS.toShort -- | Create a 'FastString' from an existing 'ShortByteString' without -- copying. mkFastStringShortByteString :: ShortByteString -> FastString -mkFastStringShortByteString sbs = - inlinePerformIO $ mkFastStringWith (mkNewFastStringShortByteString sbs) sbs +mkFastStringShortByteString = id -- | Creates a UTF-8 encoded 'FastString' from a 'String' mkFastString :: String -> FastString -{-# NOINLINE[1] mkFastString #-} mkFastString str = - inlinePerformIO $ do let !sbs = utf8EncodeShortByteString str - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs - --- The following rule is used to avoid polluting the non-reclaimable FastString --- table with transient strings when we only want their encoding. -{-# RULES -"bytesFS/mkFastString" forall x. bytesFS (mkFastString x) = utf8EncodeByteString x #-} + in sbs -- | Creates a 'FastString' from a UTF-8 encoded @[Word8]@ mkFastStringByteList :: [Word8] -> FastString mkFastStringByteList str = mkFastStringShortByteString (SBS.pack str) --- | Creates a (lazy) Z-encoded 'FastString' from a 'ShortByteString' and --- account the number of forced z-strings into the passed 'FastMutInt'. -mkZFastString :: FastMutInt -> ShortByteString -> FastZString -mkZFastString n_zencs sbs = unsafePerformIO $ do - _ <- atomicFetchAddFastMut n_zencs 1 - return $ mkFastZStringString (zEncodeString (utf8DecodeShortByteString sbs)) - -mkNewFastStringShortByteString :: ShortByteString -> Int - -> FastMutInt -> IO FastString -mkNewFastStringShortByteString sbs uid n_zencs = do - let zstr = mkZFastString n_zencs sbs - chars = utf8CountCharsShortByteString sbs - return (FastString uid chars sbs zstr) - hashStr :: ShortByteString -> Int -- produce a hash value between 0 & m (inclusive) hashStr sbs@(SBS.SBS ba#) = loop 0# 0# @@ -603,15 +457,15 @@ hashStr sbs@(SBS.SBS ba#) = loop 0# 0# -- | Returns the length of the 'FastString' in characters lengthFS :: FastString -> Int -lengthFS fs = n_chars fs +lengthFS = SBS.length -- romes: does this return utf8 length? -- | Returns @True@ if the 'FastString' is empty nullFS :: FastString -> Bool -nullFS fs = SBS.null $ fs_sbs fs +nullFS = SBS.null -- | Lazily unpacks and decodes the FastString unpackFS :: FastString -> String -unpackFS fs = utf8DecodeShortByteString $ fs_sbs fs +unpackFS = utf8DecodeShortByteString -- | Returns a Z-encoded version of a 'FastString'. This might be the -- original, if it was already Z-encoded. The first time this @@ -619,14 +473,13 @@ unpackFS fs = utf8DecodeShortByteString $ fs_sbs fs -- memoized. -- zEncodeFS :: FastString -> FastZString -zEncodeFS fs = fs_zenc fs +zEncodeFS = mkFastZStringString . zEncodeString . utf8DecodeShortByteString appendFS :: FastString -> FastString -> FastString -appendFS fs1 fs2 = mkFastStringShortByteString - $ (Semi.<>) (fs_sbs fs1) (fs_sbs fs2) +appendFS = (Semi.<>) concatFS :: [FastString] -> FastString -concatFS = mkFastStringShortByteString . mconcat . map fs_sbs +concatFS = mconcat consFS :: Char -> FastString -> FastString consFS c fs = mkFastString (c : unpackFS fs) @@ -638,7 +491,8 @@ unconsFS fs = (chr : str) -> Just (chr, mkFastString str) uniqueOfFS :: FastString -> Int -uniqueOfFS fs = uniq fs +uniqueOfFS = (+1) . hashStr + -- The unique must be > 0, so we add 1 nilFS :: FastString nilFS = mkFastString "" ===================================== compiler/GHC/Types/Unique.hs ===================================== @@ -19,6 +19,7 @@ Haskell). {-# LANGUAGE CPP #-} {-# LANGUAGE MagicHash #-} +{-# LANGUAGE TypeSynonymInstances #-} module GHC.Types.Unique ( -- * Main data types View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b1fc0e3509385a60d8ae220884fe3c6d5d8a4f4b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b1fc0e3509385a60d8ae220884fe3c6d5d8a4f4b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 15:50:16 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 06 Jun 2024 11:50:16 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] SIMD NCG WIP: fix stack spilling Message-ID: <6661dab8b7cf7_12ae2141ac65c99596@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 34d7a170 by sheaf at 2024-06-06T17:49:05+02:00 SIMD NCG WIP: fix stack spilling - - - - - 22 changed files: - compiler/GHC/CmmToAsm/AArch64.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/PPC.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Coalesce.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs - compiler/GHC/CmmToAsm/Reg/Linear/State.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Platform/Reg.hs - compiler/GHC/Platform/Reg/Class.hs Changes: ===================================== compiler/GHC/CmmToAsm/AArch64.hs ===================================== @@ -49,8 +49,8 @@ instance Instruction AArch64.Instr where jumpDestsOfInstr = AArch64.jumpDestsOfInstr canFallthroughTo = AArch64.canFallthroughTo patchJumpInstr = AArch64.patchJumpInstr - mkSpillInstr = AArch64.mkSpillInstr - mkLoadInstr = AArch64.mkLoadInstr + mkSpillInstr cfg reg _ i j = AArch64.mkSpillInstr cfg reg i j + mkLoadInstr cfg reg _ i j = AArch64.mkLoadInstr cfg reg i j takeDeltaInstr = AArch64.takeDeltaInstr isMetaInstr = AArch64.isMetaInstr mkRegRegMoveInstr _ = AArch64.mkRegRegMoveInstr ===================================== compiler/GHC/CmmToAsm/AArch64/Instr.hs ===================================== @@ -145,8 +145,9 @@ regUsageOfInstr platform instr = case instr of -- filtering the usage is necessary, otherwise the register -- allocator will try to allocate pre-defined fixed stg -- registers as well, as they show up. - usage (src, dst) = RU (filter (interesting platform) src) - (filter (interesting platform) dst) + usage (src, dst) = RU (map (,II64) $ filter (interesting platform) src) + (map (,II64) $ filter (interesting platform) dst) + -- SIMD NCG TODO: remove this hack regAddr :: AddrMode -> [Reg] regAddr (AddrRegReg r1 r2) = [r1, r2] ===================================== compiler/GHC/CmmToAsm/Format.hs ===================================== @@ -1,3 +1,7 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE ViewPatterns #-} + -- | Formats on this architecture -- A Format is a combination of width and class -- @@ -9,7 +13,7 @@ -- properly. eg SPARC doesn't care about FF80. -- module GHC.CmmToAsm.Format ( - Format(..), + Format(.., IntegerFormat), ScalarFormat(..), intFormat, floatFormat, @@ -18,7 +22,7 @@ module GHC.CmmToAsm.Format ( isVecFormat, cmmTypeFormat, formatToWidth, - formatInBytes + formatInBytes, ) where @@ -73,7 +77,23 @@ data Format | FF32 | FF64 | VecFormat !Length !ScalarFormat !Width - deriving (Show, Eq) + deriving (Show, Eq, Ord) + +pattern IntegerFormat :: Format +pattern IntegerFormat <- ( isIntegerFormat -> True ) +{-# COMPLETE IntegerFormat, FF32, FF64, VecFormat #-} + +isIntegerFormat :: Format -> Bool +isIntegerFormat = \case + II8 -> True + II16 -> True + II32 -> True + II64 -> True + _ -> False + + +instance Outputable Format where + ppr fmt = text (show fmt) data ScalarFormat = FmtInt8 | FmtInt16 @@ -81,7 +101,7 @@ data ScalarFormat = FmtInt8 | FmtInt64 | FmtFloat | FmtDouble - deriving (Show, Eq) + deriving (Show, Eq, Ord) -- | Get the integer format of this width. intFormat :: Width -> Format ===================================== compiler/GHC/CmmToAsm/Instr.hs ===================================== @@ -16,6 +16,7 @@ import GHC.Cmm.BlockId import GHC.CmmToAsm.Config import GHC.Data.FastString +import GHC.CmmToAsm.Format -- | Holds a list of source and destination registers used by a -- particular instruction. @@ -29,8 +30,8 @@ import GHC.Data.FastString -- data RegUsage = RU { - reads :: [Reg], - writes :: [Reg] + reads :: [(Reg, Format)], + writes :: [(Reg, Format)] } deriving Show @@ -96,15 +97,17 @@ class Instruction instr where mkSpillInstr :: NCGConfig -> Reg -- ^ the reg to spill + -> Format -> Int -- ^ the current stack delta - -> Int -- ^ spill slot to use - -> [instr] -- ^ instructions + -> Int -- ^ spill slots to use + -> [instr] -- ^ instructions -- | An instruction to reload a register from a spill slot. mkLoadInstr :: NCGConfig -> Reg -- ^ the reg to reload. + -> Format -> Int -- ^ the current stack delta -> Int -- ^ the spill slot to use -> [instr] -- ^ instructions ===================================== compiler/GHC/CmmToAsm/PPC.hs ===================================== @@ -48,8 +48,8 @@ instance Instruction PPC.Instr where jumpDestsOfInstr = PPC.jumpDestsOfInstr canFallthroughTo = PPC.canFallthroughTo patchJumpInstr = PPC.patchJumpInstr - mkSpillInstr = PPC.mkSpillInstr - mkLoadInstr = PPC.mkLoadInstr + mkSpillInstr cfg reg _ i j = PPC.mkSpillInstr cfg reg i j + mkLoadInstr cfg reg _ i j = PPC.mkLoadInstr cfg reg i j takeDeltaInstr = PPC.takeDeltaInstr isMetaInstr = PPC.isMetaInstr mkRegRegMoveInstr _ = PPC.mkRegRegMoveInstr ===================================== compiler/GHC/CmmToAsm/PPC/Instr.hs ===================================== @@ -391,8 +391,9 @@ regUsageOfInstr platform instr FMADD _ _ rt ra rc rb -> usage ([ra, rc, rb], [rt]) _ -> noUsage where - usage (src, dst) = RU (filter (interesting platform) src) - (filter (interesting platform) dst) + usage (src, dst) = RU (map (,II64) $ filter (interesting platform) src) + (map (,II64) $ filter (interesting platform) dst) + -- SIMD NCG TODO: remove this hack regAddr (AddrRegReg r1 r2) = [r1, r2] regAddr (AddrRegImm r1 _) = [r1] ===================================== compiler/GHC/CmmToAsm/Reg/Graph.hs ===================================== @@ -335,21 +335,21 @@ buildGraph code -- | Add some conflict edges to the graph. -- Conflicts between virtual and real regs are recorded as exclusions. graphAddConflictSet - :: UniqSet Reg + :: RegMap (Reg, fmt) -> Color.Graph VirtualReg RegClass RealReg -> Color.Graph VirtualReg RegClass RealReg -graphAddConflictSet set graph +graphAddConflictSet regs graph = let virtuals = mkUniqSet - [ vr | RegVirtual vr <- nonDetEltsUniqSet set ] + [ vr | (RegVirtual vr, _) <- nonDetEltsUFM regs ] graph1 = Color.addConflicts virtuals classOfVirtualReg graph graph2 = foldr (\(r1, r2) -> Color.addExclusion r1 classOfVirtualReg r2) graph1 [ (vr, rr) - | RegVirtual vr <- nonDetEltsUniqSet set - , RegReal rr <- nonDetEltsUniqSet set] + | (RegVirtual vr, _) <- nonDetEltsUFM regs + , (RegReal rr, _) <- nonDetEltsUFM regs] -- See Note [Unique Determinism and code generation] in graph2 ===================================== compiler/GHC/CmmToAsm/Reg/Graph/Coalesce.hs ===================================== @@ -13,7 +13,6 @@ import GHC.Cmm import GHC.Data.Bag import GHC.Data.Graph.Directed import GHC.Types.Unique.FM -import GHC.Types.Unique.Set import GHC.Types.Unique.Supply @@ -85,8 +84,8 @@ slurpJoinMovs live slurpLI rs (LiveInstr _ Nothing) = rs slurpLI rs (LiveInstr instr (Just live)) | Just (r1, r2) <- takeRegRegMoveInstr instr - , elementOfUniqSet r1 $ liveDieRead live - , elementOfUniqSet r2 $ liveBorn live + , elemUFM r1 $ liveDieRead live + , elemUFM r2 $ liveBorn live -- only coalesce movs between two virtuals for now, -- else we end up with allocatable regs in the live ===================================== compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs ===================================== @@ -31,6 +31,7 @@ import Data.List (nub, (\\), intersect) import Data.Maybe import Data.IntSet (IntSet) import qualified Data.IntSet as IntSet +import GHC.CmmToAsm.Format -- | Spill all these virtual regs to stack slots. @@ -138,7 +139,7 @@ regSpill_top platform regSlotMap cmm -- then record the fact that these slots are now live in those blocks -- in the given slotmap. patchLiveSlot - :: BlockMap IntSet -> BlockId -> RegSet -> BlockMap IntSet + :: BlockMap IntSet -> BlockId -> RegMap (Reg, Format) -> BlockMap IntSet patchLiveSlot slotMap blockId regsLive = let @@ -148,7 +149,8 @@ regSpill_top platform regSlotMap cmm moreSlotsLive = IntSet.fromList $ mapMaybe (lookupUFM regSlotMap) - $ nonDetEltsUniqSet regsLive + $ map fst + $ nonDetEltsUFM regsLive -- See Note [Unique Determinism and code generation] slotMap' @@ -197,9 +199,9 @@ regSpill_instr platform regSlotMap (LiveInstr instr (Just _)) = do let rsModify = intersect rsRead_ rsWritten_ -- work out if any of the regs being used are currently being spilled. - let rsSpillRead = filter (\r -> elemUFM r regSlotMap) rsRead - let rsSpillWritten = filter (\r -> elemUFM r regSlotMap) rsWritten - let rsSpillModify = filter (\r -> elemUFM r regSlotMap) rsModify + let rsSpillRead = filter (\(r,_) -> elemUFM r regSlotMap) rsRead + let rsSpillWritten = filter (\(r,_) -> elemUFM r regSlotMap) rsWritten + let rsSpillModify = filter (\(r,_) -> elemUFM r regSlotMap) rsModify -- rewrite the instr and work out spill code. (instr1, prepost1) <- mapAccumLM (spillRead regSlotMap) instr rsSpillRead @@ -224,10 +226,10 @@ spillRead :: Instruction instr => UniqFM Reg Int -> instr - -> Reg + -> (Reg, Format) -> SpillM (instr, ([LiveInstr instr'], [LiveInstr instr'])) -spillRead regSlotMap instr reg +spillRead regSlotMap instr (reg, fmt) | Just slot <- lookupUFM regSlotMap reg = do (instr', nReg) <- patchInstr reg instr @@ -235,7 +237,7 @@ spillRead regSlotMap instr reg { stateSpillSL = addToUFM_C accSpillSL (stateSpillSL s) reg (reg, 0, 1) } return ( instr' - , ( [LiveInstr (RELOAD slot nReg) Nothing] + , ( [LiveInstr (RELOAD slot nReg fmt) Nothing] , []) ) | otherwise = panic "RegSpill.spillRead: no slot defined for spilled reg" @@ -247,10 +249,10 @@ spillWrite :: Instruction instr => UniqFM Reg Int -> instr - -> Reg + -> (Reg, Format) -> SpillM (instr, ([LiveInstr instr'], [LiveInstr instr'])) -spillWrite regSlotMap instr reg +spillWrite regSlotMap instr (reg, fmt) | Just slot <- lookupUFM regSlotMap reg = do (instr', nReg) <- patchInstr reg instr @@ -259,7 +261,7 @@ spillWrite regSlotMap instr reg return ( instr' , ( [] - , [LiveInstr (SPILL nReg slot) Nothing])) + , [LiveInstr (SPILL nReg fmt slot) Nothing])) | otherwise = panic "RegSpill.spillWrite: no slot defined for spilled reg" @@ -270,10 +272,10 @@ spillModify :: Instruction instr => UniqFM Reg Int -> instr - -> Reg + -> (Reg, Format) -> SpillM (instr, ([LiveInstr instr'], [LiveInstr instr'])) -spillModify regSlotMap instr reg +spillModify regSlotMap instr (reg, fmt) | Just slot <- lookupUFM regSlotMap reg = do (instr', nReg) <- patchInstr reg instr @@ -281,8 +283,8 @@ spillModify regSlotMap instr reg { stateSpillSL = addToUFM_C accSpillSL (stateSpillSL s) reg (reg, 1, 1) } return ( instr' - , ( [LiveInstr (RELOAD slot nReg) Nothing] - , [LiveInstr (SPILL nReg slot) Nothing])) + , ( [LiveInstr (RELOAD slot nReg fmt) Nothing] + , [LiveInstr (SPILL nReg fmt slot) Nothing])) | otherwise = panic "RegSpill.spillModify: no slot defined for spilled reg" ===================================== compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs ===================================== @@ -160,12 +160,13 @@ cleanForward _ _ _ acc [] -- hopefully the spill will be also be cleaned in the next pass cleanForward platform blockId assoc acc (li1 : li2 : instrs) - | LiveInstr (SPILL reg1 slot1) _ <- li1 - , LiveInstr (RELOAD slot2 reg2) _ <- li2 + | LiveInstr (SPILL reg1 _ slot1) _ <- li1 + , LiveInstr (RELOAD slot2 reg2 _) _ <- li2 , slot1 == slot2 = do modify $ \s -> s { sCleanedReloadsAcc = sCleanedReloadsAcc s + 1 } cleanForward platform blockId assoc acc + -- SIMD NCG TODO: is mkRegRegMoveInstr here OK for vectors? $ li1 : LiveInstr (mkRegRegMoveInstr platform reg1 reg2) Nothing : instrs @@ -189,7 +190,7 @@ cleanForward platform blockId assoc acc (li@(LiveInstr i1 _) : instrs) cleanForward platform blockId assoc acc (li : instrs) -- Update association due to the spill. - | LiveInstr (SPILL reg slot) _ <- li + | LiveInstr (SPILL reg _ slot) _ <- li = let assoc' = addAssoc (SReg reg) (SSlot slot) $ delAssoc (SSlot slot) $ assoc @@ -215,7 +216,7 @@ cleanForward platform blockId assoc acc (li : instrs) -- Writing to a reg changes its value. | LiveInstr instr _ <- li , RU _ written <- regUsageOfInstr platform instr - = let assoc' = foldr delAssoc assoc (map SReg $ nub written) + = let assoc' = foldr delAssoc assoc (map SReg $ nub $ map fst written) in cleanForward platform blockId assoc' (li : acc) instrs @@ -229,7 +230,7 @@ cleanReload -> LiveInstr instr -> CleanM (Assoc Store, Maybe (LiveInstr instr)) -cleanReload platform blockId assoc li@(LiveInstr (RELOAD slot reg) _) +cleanReload platform blockId assoc li@(LiveInstr (RELOAD slot reg _) _) -- If the reg we're reloading already has the same value as the slot -- then we can erase the instruction outright. @@ -355,12 +356,12 @@ cleanBackward' _ _ _ acc [] cleanBackward' liveSlotsOnEntry reloadedBy noReloads acc (li : instrs) -- If nothing ever reloads from this slot then we don't need the spill. - | LiveInstr (SPILL _ slot) _ <- li + | LiveInstr (SPILL _ _ slot) _ <- li , Nothing <- lookupUFM reloadedBy (SSlot slot) = do modify $ \s -> s { sCleanedSpillsAcc = sCleanedSpillsAcc s + 1 } cleanBackward liveSlotsOnEntry noReloads acc instrs - | LiveInstr (SPILL _ slot) _ <- li + | LiveInstr (SPILL _ _ slot) _ <- li = if elementOfUniqSet slot noReloads -- We can erase this spill because the slot won't be read until @@ -375,7 +376,7 @@ cleanBackward' liveSlotsOnEntry reloadedBy noReloads acc (li : instrs) cleanBackward liveSlotsOnEntry noReloads' (li : acc) instrs -- if we reload from a slot then it's no longer unused - | LiveInstr (RELOAD slot _) _ <- li + | LiveInstr (RELOAD slot _ _) _ <- li , noReloads' <- delOneFromUniqSet noReloads slot = cleanBackward liveSlotsOnEntry noReloads' (li : acc) instrs ===================================== compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs ===================================== @@ -129,8 +129,8 @@ slurpSpillCostInfo platform cfg cmm -- Increment counts for what regs were read/written from. let (RU read written) = regUsageOfInstr platform instr - mapM_ (incUses scale) $ mapMaybe takeVirtualReg $ nub read - mapM_ (incDefs scale) $ mapMaybe takeVirtualReg $ nub written + mapM_ (incUses scale) $ mapMaybe takeVirtualReg $ nub $ map fst read + mapM_ (incDefs scale) $ mapMaybe takeVirtualReg $ nub $ map fst written -- Compute liveness for entry to next instruction. let liveDieRead_virt = takeVirtuals (liveDieRead live) @@ -158,9 +158,9 @@ slurpSpillCostInfo platform cfg cmm = 1.0 -- Only if no cfg given -- | Take all the virtual registers from this set. -takeVirtuals :: UniqSet Reg -> UniqSet VirtualReg -takeVirtuals set = mkUniqSet - [ vr | RegVirtual vr <- nonDetEltsUniqSet set ] +takeVirtuals :: RegMap (Reg, fmt) -> UniqSet VirtualReg +takeVirtuals m = mkUniqSet + [ vr | (RegVirtual vr, _) <- nonDetEltsUFM m ] -- See Note [Unique Determinism and code generation] ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -127,7 +127,6 @@ import GHC.Cmm hiding (RegSet) import GHC.Data.Graph.Directed import GHC.Types.Unique -import GHC.Types.Unique.Set import GHC.Types.Unique.FM import GHC.Types.Unique.Supply import GHC.Utils.Outputable @@ -137,6 +136,7 @@ import GHC.Platform import Data.Maybe import Data.List (partition, nub) import Control.Monad +import GHC.CmmToAsm.Format -- ----------------------------------------------------------------------------- -- Top level of the register allocator @@ -203,7 +203,7 @@ linearRegAlloc :: forall instr. (Instruction instr) => NCGConfig -> [BlockId] -- ^ entry points - -> BlockMap RegSet + -> BlockMap (UniqFM Reg (Reg, Format)) -- ^ live regs on entry to each basic block -> [SCC (LiveBasicBlock instr)] -- ^ instructions annotated with "deaths" @@ -242,7 +242,7 @@ linearRegAlloc' => NCGConfig -> freeRegs -> [BlockId] -- ^ entry points - -> BlockMap RegSet -- ^ live regs on entry to each basic block + -> BlockMap (UniqFM Reg (Reg, Format)) -- ^ live regs on entry to each basic block -> [SCC (LiveBasicBlock instr)] -- ^ instructions annotated with "deaths" -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int) @@ -256,7 +256,7 @@ linearRegAlloc' config initFreeRegs entry_ids block_live sccs linearRA_SCCs :: OutputableRegConstraint freeRegs instr => [BlockId] - -> BlockMap RegSet + -> BlockMap (UniqFM Reg (Reg, Format)) -> [NatBasicBlock instr] -> [SCC (LiveBasicBlock instr)] -> RegM freeRegs [NatBasicBlock instr] @@ -291,7 +291,7 @@ linearRA_SCCs entry_ids block_live blocksAcc (CyclicSCC blocks : sccs) process :: forall freeRegs instr. (OutputableRegConstraint freeRegs instr) => [BlockId] - -> BlockMap RegSet + -> BlockMap (UniqFM Reg (Reg, Format)) -> [GenBasicBlock (LiveInstr instr)] -> RegM freeRegs [[NatBasicBlock instr]] process entry_ids block_live = @@ -330,7 +330,7 @@ process entry_ids block_live = -- processBlock :: OutputableRegConstraint freeRegs instr - => BlockMap RegSet -- ^ live regs on entry to each basic block + => BlockMap (UniqFM Reg (Reg, Format)) -- ^ live regs on entry to each basic block -> LiveBasicBlock instr -- ^ block to do register allocation on -> RegM freeRegs [NatBasicBlock instr] -- ^ block with registers allocated @@ -347,7 +347,7 @@ processBlock block_live (BasicBlock id instrs) -- | Load the freeregs and current reg assignment into the RegM state -- for the basic block with this BlockId. initBlock :: FR freeRegs - => BlockId -> BlockMap RegSet -> RegM freeRegs () + => BlockId -> BlockMap (UniqFM Reg (Reg, Format)) -> RegM freeRegs () initBlock id block_live = do platform <- getPlatform block_assig <- getBlockAssigR @@ -364,7 +364,7 @@ initBlock id block_live setFreeRegsR (frInitFreeRegs platform) Just live -> setFreeRegsR $ foldl' (flip $ frAllocateReg platform) (frInitFreeRegs platform) - [ r | RegReal r <- nonDetEltsUniqSet live ] + [ r | ( RegReal r, _ ) <- nonDetEltsUFM live ] -- See Note [Unique Determinism and code generation] setAssigR emptyRegMap @@ -377,7 +377,7 @@ initBlock id block_live -- | Do allocation for a sequence of instructions. linearRA :: forall freeRegs instr. (OutputableRegConstraint freeRegs instr) - => BlockMap RegSet -- ^ map of what vregs are live on entry to each block. + => BlockMap (UniqFM Reg (Reg, Format)) -- ^ map of what vregs are live on entry to each block. -> BlockId -- ^ id of the current block, for debugging. -> [LiveInstr instr] -- ^ liveness annotated instructions in this block. -> RegM freeRegs @@ -402,7 +402,7 @@ linearRA block_live block_id = go [] [] -- | Do allocation for a single instruction. raInsn :: OutputableRegConstraint freeRegs instr - => BlockMap RegSet -- ^ map of what vregs are love on entry to each block. + => BlockMap (UniqFM Reg (Reg, Format)) -- ^ map of what vregs are love on entry to each block. -> [instr] -- ^ accumulator for instructions already processed. -> BlockId -- ^ the id of the current block, for debugging -> LiveInstr instr -- ^ the instr to have its regs allocated, with liveness info. @@ -432,12 +432,12 @@ raInsn block_live new_instrs id (LiveInstr (Instr instr) (Just live)) -- (we can't eliminate it if the source register is on the stack, because -- we do not want to use one spill slot for different virtual registers) case takeRegRegMoveInstr instr of - Just (src,dst) | src `elementOfUniqSet` (liveDieRead live), + Just (src,dst) | Just (_, fmt) <- lookupUFM (liveDieRead live) src, isVirtualReg dst, not (dst `elemUFM` assig), isRealReg src || isInReg src assig -> do case src of - (RegReal rr) -> setAssigR (addToUFM assig dst (InReg rr)) + RegReal rr -> setAssigR (addToUFM assig dst (InReg $ RealRegUsage rr fmt)) -- if src is a fixed reg, then we just map dest to this -- reg in the assignment. src must be an allocatable reg, -- otherwise it wouldn't be in r_dying. @@ -456,8 +456,8 @@ raInsn block_live new_instrs id (LiveInstr (Instr instr) (Just live)) return (new_instrs, []) _ -> genRaInsn block_live new_instrs id instr - (nonDetEltsUniqSet $ liveDieRead live) - (nonDetEltsUniqSet $ liveDieWrite live) + (map fst $ nonDetEltsUFM $ liveDieRead live) + (map fst $ nonDetEltsUFM $ liveDieWrite live) -- See Note [Unique Determinism and code generation] raInsn _ _ _ instr @@ -486,7 +486,7 @@ isInReg src assig | Just (InReg _) <- lookupUFM assig src = True genRaInsn :: forall freeRegs instr. (OutputableRegConstraint freeRegs instr) - => BlockMap RegSet + => BlockMap (UniqFM Reg (Reg, Format)) -> [instr] -> BlockId -> instr @@ -499,13 +499,13 @@ genRaInsn block_live new_instrs block_id instr r_dying w_dying = do platform <- getPlatform case regUsageOfInstr platform instr of { RU read written -> do - let real_written = [ rr | (RegReal rr) <- written ] :: [RealReg] - let virt_written = [ vr | (RegVirtual vr) <- written ] + let real_written = [ rr | (RegReal rr, _) <- written ] :: [RealReg] + let virt_written = [ vr | (RegVirtual vr, _) <- written ] -- we don't need to do anything with real registers that are -- only read by this instr. (the list is typically ~2 elements, -- so using nub isn't a problem). - let virt_read = nub [ vr | (RegVirtual vr) <- read ] :: [VirtualReg] + let virt_read = nub [ vr | (RegVirtual vr, _) <- read ] :: [VirtualReg] -- do -- let real_read = nub [ rr | (RegReal rr) <- read] @@ -638,9 +638,9 @@ releaseRegs regs = do loop assig !free (r:rs) = case lookupUFM assig r of Just (InBoth real _) -> loop (delFromUFM assig r) - (frReleaseReg platform real free) rs + (frReleaseReg platform (realReg real) free) rs Just (InReg real) -> loop (delFromUFM assig r) - (frReleaseReg platform real free) rs + (frReleaseReg platform (realReg real) free) rs _ -> loop (delFromUFM assig r) free rs loop assig free regs @@ -688,15 +688,15 @@ saveClobberedTemps clobbered dying -- currently support deterministic code-generation. -- See Note [Unique Determinism and code generation] InReg reg - | any (realRegsAlias reg) clobbered + | any (realRegsAlias $ realReg reg) clobbered , temp `notElem` map getUnique dying - -> clobber temp (assig,instrs) (reg) + -> clobber temp (assig,instrs) reg _ -> return (assig,instrs) -- See Note [UniqFM and the register allocator] - clobber :: Unique -> (RegMap Loc,[instr]) -> (RealReg) -> RegM freeRegs (RegMap Loc,[instr]) - clobber temp (assig,instrs) (reg) + clobber :: Unique -> (RegMap Loc,[instr]) -> RealRegUsage -> RegM freeRegs (RegMap Loc,[instr]) + clobber temp (assig,instrs) (RealRegUsage reg fmt) = do platform <- getPlatform freeRegs <- getFreeRegsR @@ -711,7 +711,7 @@ saveClobberedTemps clobbered dying (my_reg : _) -> do setFreeRegsR (frAllocateReg platform my_reg freeRegs) - let new_assign = addToUFM_Directly assig temp (InReg my_reg) + let new_assign = addToUFM_Directly assig temp (InReg (RealRegUsage my_reg fmt)) let instr = mkRegRegMoveInstr platform (RegReal reg) (RegReal my_reg) @@ -719,12 +719,12 @@ saveClobberedTemps clobbered dying -- (2) no free registers: spill the value [] -> do - (spill, slot) <- spillR (RegReal reg) temp + (spill, slot) <- spillR (RegReal reg) fmt temp -- record why this reg was spilled for profiling recordSpill (SpillClobber temp) - let new_assign = addToUFM_Directly assig temp (InBoth reg slot) + let new_assign = addToUFM_Directly assig temp (InBoth (RealRegUsage reg fmt) slot) return (new_assign, (spill ++ instrs)) @@ -771,7 +771,7 @@ clobberRegs clobbered = assig clobber assig ((temp, InBoth reg slot) : rest) - | any (realRegsAlias reg) clobbered + | any (realRegsAlias $ realReg reg) clobbered = clobber (addToUFM_Directly assig temp (InMem slot)) rest clobber assig (_:rest) @@ -817,7 +817,7 @@ allocateRegsAndSpill reading keep spills alloc (r:rs) case lookupUFM assig r of -- case (1a): already in a register Just (InReg my_reg) -> - allocateRegsAndSpill reading keep spills (my_reg:alloc) rs + allocateRegsAndSpill reading keep spills (realReg my_reg:alloc) rs -- case (1b): already in a register (and memory) -- NB1. if we're writing this register, update its assignment to be @@ -826,7 +826,7 @@ allocateRegsAndSpill reading keep spills alloc (r:rs) -- are also read by the same instruction. Just (InBoth my_reg _) -> do when (not reading) (setAssigR $ toRegMap (addToUFM assig r (InReg my_reg))) - allocateRegsAndSpill reading keep spills (my_reg:alloc) rs + allocateRegsAndSpill reading keep spills (realReg my_reg:alloc) rs -- Not already in a register, so we need to find a free one... Just (InMem slot) | reading -> doSpill (ReadMem slot) @@ -869,7 +869,15 @@ allocRegsAndSpill_spill :: (FR freeRegs, Instruction instr) allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc = do platform <- getPlatform freeRegs <- getFreeRegsR - let freeRegs_thisClass = frGetFreeRegs platform (classOfVirtualReg r) freeRegs :: [RealReg] + let regclass = classOfVirtualReg r + freeRegs_thisClass = frGetFreeRegs platform regclass freeRegs :: [RealReg] + -- SIMD NCG TODO: this is not the right thing to be doing, + -- and is indicative we should not use Format but a more + -- trimmed down datatype that only keeps track of e.g. + -- how many stack slots something uses up. + vr_fmt = case r of + VirtualRegVec {} -> VecFormat 2 FmtDouble W64 + _ -> II64 -- Can we put the variable into a register it already was? pref_reg <- findPrefRealReg r @@ -883,10 +891,10 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc = reg | otherwise = first_free - spills' <- loadTemp r spill_loc final_reg spills + spills' <- loadTemp r vr_fmt spill_loc final_reg spills setAssigR $ toRegMap - $ (addToUFM assig r $! newLocation spill_loc final_reg) + $ (addToUFM assig r $! newLocation spill_loc $ RealRegUsage final_reg vr_fmt) setFreeRegsR $ frAllocateReg platform final_reg freeRegs allocateRegsAndSpill reading keep spills' (final_reg : alloc) rs @@ -908,48 +916,53 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc let candidates = nonDetUFMToList candidates' -- the vregs we could kick out that are already in a slot - let candidates_inBoth :: [(Unique, RealReg, StackSlot)] + let compat reg' r' + = let cls1 = targetClassOfRealReg platform reg' + cls2 = classOfVirtualReg r' + in (if cls1 == RcVector128 then RcDouble else cls1) + == (if cls2 == RcVector128 then RcDouble else cls2) + candidates_inBoth :: [(Unique, RealRegUsage, StackSlot)] candidates_inBoth = [ (temp, reg, mem) | (temp, InBoth reg mem) <- candidates - , targetClassOfRealReg platform reg == classOfVirtualReg r ] + , compat (realReg reg) r ] -- the vregs we could kick out that are only in a reg -- this would require writing the reg to a new slot before using it. let candidates_inReg = [ (temp, reg) | (temp, InReg reg) <- candidates - , targetClassOfRealReg platform reg == classOfVirtualReg r ] + , compat (realReg reg) r ] let result -- we have a temporary that is in both register and mem, -- just free up its register for use. - | (temp, my_reg, slot) : _ <- candidates_inBoth - = do spills' <- loadTemp r spill_loc my_reg spills + | (temp, myRegUse@(RealRegUsage my_reg fmt), slot) : _ <- candidates_inBoth + = do spills' <- loadTemp r fmt spill_loc my_reg spills let assig1 = addToUFM_Directly assig temp (InMem slot) - let assig2 = addToUFM assig1 r $! newLocation spill_loc my_reg + let assig2 = addToUFM assig1 r $! newLocation spill_loc myRegUse setAssigR $ toRegMap assig2 allocateRegsAndSpill reading keep spills' (my_reg:alloc) rs -- otherwise, we need to spill a temporary that currently -- resides in a register. - | (temp_to_push_out, (my_reg :: RealReg)) : _ + | (temp_to_push_out, RealRegUsage my_reg fmt) : _ <- candidates_inReg = do - (spill_store, slot) <- spillR (RegReal my_reg) temp_to_push_out + (spill_store, slot) <- spillR (RegReal my_reg) fmt temp_to_push_out -- record that this temp was spilled recordSpill (SpillAlloc temp_to_push_out) -- update the register assignment let assig1 = addToUFM_Directly assig temp_to_push_out (InMem slot) - let assig2 = addToUFM assig1 r $! newLocation spill_loc my_reg + let assig2 = addToUFM assig1 r $! newLocation spill_loc (RealRegUsage my_reg fmt) setAssigR $ toRegMap assig2 -- if need be, load up a spilled temp into the reg we've just freed up. - spills' <- loadTemp r spill_loc my_reg spills + spills' <- loadTemp r fmt spill_loc my_reg spills allocateRegsAndSpill reading keep (spill_store ++ spills') @@ -970,7 +983,7 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc -- | Calculate a new location after a register has been loaded. -newLocation :: SpillLoc -> RealReg -> Loc +newLocation :: SpillLoc -> RealRegUsage -> Loc -- if the tmp was read from a slot, then now its in a reg as well newLocation (ReadMem slot) my_reg = InBoth my_reg slot -- writes will always result in only the register being available @@ -980,16 +993,17 @@ newLocation _ my_reg = InReg my_reg loadTemp :: (Instruction instr) => VirtualReg -- the temp being loaded + -> Format -> SpillLoc -- the current location of this temp -> RealReg -- the hreg to load the temp into -> [instr] -> RegM freeRegs [instr] -loadTemp vreg (ReadMem slot) hreg spills +loadTemp vreg fmt (ReadMem slot) hreg spills = do - insn <- loadR (RegReal hreg) slot + insn <- loadR (RegReal hreg) fmt slot recordSpill (SpillLoad $ getUnique vreg) return $ {- mkComment (text "spill load") : -} insn ++ spills -loadTemp _ _ _ spills = +loadTemp _ _ _ _ spills = return spills ===================================== compiler/GHC/CmmToAsm/Reg/Linear/Base.hs ===================================== @@ -11,6 +11,7 @@ module GHC.CmmToAsm.Reg.Linear.Base ( Loc(..), regsOfLoc, + RealRegUsage(..), -- for stats SpillReason(..), @@ -36,6 +37,7 @@ import GHC.Types.Unique.Supply import GHC.Cmm.BlockId import GHC.Cmm.Dataflow.Label import GHC.CmmToAsm.Reg.Utils +import GHC.CmmToAsm.Format data ReadingOrWriting = Reading | Writing deriving (Eq,Ord) @@ -76,8 +78,8 @@ updateBlockAssignment dest (freeRegs, regMap) (BlockAssignment {..}) = combWithExisting old_reg _ = Just $ old_reg fromLoc :: Loc -> Maybe RealReg - fromLoc (InReg rr) = Just rr - fromLoc (InBoth rr _) = Just rr + fromLoc (InReg rr) = Just $ realReg rr + fromLoc (InBoth rr _) = Just $ realReg rr fromLoc _ = Nothing @@ -94,23 +96,29 @@ updateBlockAssignment dest (freeRegs, regMap) (BlockAssignment {..}) = -- data Loc -- | vreg is in a register - = InReg !RealReg + = InReg {-# UNPACK #-} !RealRegUsage - -- | vreg is held in a stack slot + -- | vreg is held in stack slots | InMem {-# UNPACK #-} !StackSlot - -- | vreg is held in both a register and a stack slot - | InBoth !RealReg + -- | vreg is held in both a register and stack slots + | InBoth {-# UNPACK #-} !RealRegUsage {-# UNPACK #-} !StackSlot deriving (Eq, Show, Ord) +data RealRegUsage + = RealRegUsage + { realReg :: !RealReg + , realRegFormat :: !Format + } deriving (Eq, Show, Ord) + instance Outputable Loc where ppr l = text (show l) -- | Get the reg numbers stored in this Loc. -regsOfLoc :: Loc -> [RealReg] +regsOfLoc :: Loc -> [RealRegUsage] regsOfLoc (InReg r) = [r] regsOfLoc (InBoth r _) = [r] regsOfLoc (InMem _) = [] ===================================== compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs ===================================== @@ -29,16 +29,16 @@ import GHC.Utils.Panic import GHC.Utils.Monad (concatMapM) import GHC.Types.Unique import GHC.Types.Unique.FM -import GHC.Types.Unique.Set import GHC.Utils.Outputable +import GHC.CmmToAsm.Format -- | For a jump instruction at the end of a block, generate fixup code so its -- vregs are in the correct regs for its destination. -- joinToTargets :: (FR freeRegs, Instruction instr) - => BlockMap RegSet -- ^ maps the unique of the blockid to the set of vregs + => BlockMap (RegMap (Reg, Format)) -- ^ maps the unique of the blockid to the set of vregs -- that are known to be live on the entry to each block. -> BlockId -- ^ id of the current block @@ -62,7 +62,7 @@ joinToTargets block_live id instr ----- joinToTargets' :: (FR freeRegs, Instruction instr) - => BlockMap RegSet -- ^ maps the unique of the blockid to the set of vregs + => BlockMap (RegMap (Reg, Format)) -- ^ maps the unique of the blockid to the set of vregs -- that are known to be live on the entry to each block. -> [NatBasicBlock instr] -- ^ acc blocks of fixup code. @@ -90,7 +90,7 @@ joinToTargets' block_live new_blocks block_id instr (dest:dests) -- adjust the current assignment to remove any vregs that are not live -- on entry to the destination block. let Just live_set = mapLookup dest block_live - let still_live uniq _ = uniq `elemUniqSet_Directly` live_set + let still_live uniq _ = uniq `elemUFM_Directly` live_set let adjusted_assig = filterUFM_Directly still_live assig -- and free up those registers which are now free. @@ -99,14 +99,14 @@ joinToTargets' block_live new_blocks block_id instr (dest:dests) -- This is non-deterministic but we do not -- currently support deterministic code-generation. -- See Note [Unique Determinism and code generation] - , not (elemUniqSet_Directly reg live_set) + , not (elemUFM_Directly reg live_set) , r <- regsOfLoc loc ] case lookupBlockAssignment dest block_assig of Nothing -> joinToTargets_first block_live new_blocks block_id instr dest dests - block_assig adjusted_assig to_free + block_assig adjusted_assig $ map realReg to_free Just (_, dest_assig) -> joinToTargets_again @@ -116,7 +116,7 @@ joinToTargets' block_live new_blocks block_id instr (dest:dests) -- this is the first time we jumped to this block. joinToTargets_first :: (FR freeRegs, Instruction instr) - => BlockMap RegSet + => BlockMap (UniqFM Reg (Reg, Format)) -> [NatBasicBlock instr] -> BlockId -> instr @@ -145,7 +145,7 @@ joinToTargets_first block_live new_blocks block_id instr dest dests -- we've jumped to this block before joinToTargets_again :: (Instruction instr, FR freeRegs) - => BlockMap RegSet + => BlockMap (UniqFM Reg (Reg, Format)) -> [NatBasicBlock instr] -> BlockId -> instr @@ -327,15 +327,15 @@ handleComponent delta _ (AcyclicSCC (DigraphNode vreg src dsts)) -- require a fixup. -- handleComponent delta instr - (CyclicSCC ((DigraphNode vreg (InReg sreg) ((InReg dreg: _))) : rest)) + (CyclicSCC ((DigraphNode vreg (InReg (RealRegUsage sreg scls)) ((InReg (RealRegUsage dreg dcls): _))) : rest)) -- dest list may have more than one element, if the reg is also InMem. = do -- spill the source into its slot (instrSpill, slot) - <- spillR (RegReal sreg) vreg + <- spillR (RegReal sreg) scls vreg -- reload into destination reg - instrLoad <- loadR (RegReal dreg) slot + instrLoad <- loadR (RegReal dreg) dcls slot remainingFixUps <- mapM (handleComponent delta instr) (stronglyConnCompFromEdgedVerticesOrdR rest) @@ -363,15 +363,16 @@ makeMove delta vreg src dst let platform = ncgPlatform config case (src, dst) of - (InReg s, InReg d) -> + (InReg (RealRegUsage s _), InReg (RealRegUsage d _)) -> do recordSpill (SpillJoinRR vreg) + -- SIMD NCG TODO: does reg-2-reg work for vector registers? return $ [mkRegRegMoveInstr platform (RegReal s) (RegReal d)] - (InMem s, InReg d) -> + (InMem s, InReg (RealRegUsage d cls)) -> do recordSpill (SpillJoinRM vreg) - return $ mkLoadInstr config (RegReal d) delta s - (InReg s, InMem d) -> + return $ mkLoadInstr config (RegReal d) cls delta s + (InReg (RealRegUsage s cls), InMem d) -> do recordSpill (SpillJoinRM vreg) - return $ mkSpillInstr config (RegReal s) delta d + return $ mkSpillInstr config (RegReal s) cls delta d _ -> -- we don't handle memory to memory moves. -- they shouldn't happen because we don't share ===================================== compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs ===================================== @@ -24,6 +24,7 @@ import GHC.Prelude import GHC.Types.Unique.FM import GHC.Types.Unique +import GHC.CmmToAsm.Format -- | Identifier for a stack slot. @@ -47,13 +48,18 @@ emptyStackMap = StackMap 0 emptyUFM -- | If this vreg unique already has a stack assignment then return the slot number, -- otherwise allocate a new slot, and update the map. -- -getStackSlotFor :: StackMap -> Unique -> (StackMap, Int) - -getStackSlotFor fs@(StackMap _ reserved) reg - | Just slot <- lookupUFM reserved reg = (fs, slot) - -getStackSlotFor (StackMap freeSlot reserved) reg = - (StackMap (freeSlot+1) (addToUFM reserved reg freeSlot), freeSlot) +getStackSlotFor :: StackMap -> Format -> Unique -> (StackMap, Int) + +getStackSlotFor fs@(StackMap _ reserved) _fmt regUnique + | Just slot <- lookupUFM reserved regUnique = (fs, slot) + +getStackSlotFor (StackMap freeSlot reserved) fmt regUnique = + let + nbSlots = case fmt of + VecFormat {} -> 2 -- SIMD NCG TODO: panic for unsupported vectors + _ -> 1 + in + (StackMap (freeSlot+nbSlots) (addToUFM reserved regUnique freeSlot), freeSlot) -- | Return the number of stack slots that were allocated getStackUse :: StackMap -> Int ===================================== compiler/GHC/CmmToAsm/Reg/Linear/State.hs ===================================== @@ -53,6 +53,7 @@ import GHC.Types.Unique.Supply import GHC.Exts (oneShot) import Control.Monad (ap) +import GHC.CmmToAsm.Format type RA_Result freeRegs a = (# RA_State freeRegs, a #) @@ -121,20 +122,20 @@ makeRAStats state spillR :: Instruction instr - => Reg -> Unique -> RegM freeRegs ([instr], Int) + => Reg -> Format -> Unique -> RegM freeRegs ([instr], Int) -spillR reg temp = mkRegM $ \s -> - let (stack1,slot) = getStackSlotFor (ra_stack s) temp - instr = mkSpillInstr (ra_config s) reg (ra_delta s) slot +spillR reg fmt temp = mkRegM $ \s -> + let (stack1,slots) = getStackSlotFor (ra_stack s) fmt temp + instr = mkSpillInstr (ra_config s) reg fmt (ra_delta s) slots in - RA_Result s{ra_stack=stack1} (instr,slot) + RA_Result s{ra_stack=stack1} (instr,slots) loadR :: Instruction instr - => Reg -> Int -> RegM freeRegs [instr] + => Reg -> Format -> Int -> RegM freeRegs [instr] -loadR reg slot = mkRegM $ \s -> - RA_Result s (mkLoadInstr (ra_config s) reg (ra_delta s) slot) +loadR reg fmt slot = mkRegM $ \s -> + RA_Result s (mkLoadInstr (ra_config s) reg fmt (ra_delta s) slot) getFreeRegsR :: RegM freeRegs freeRegs getFreeRegsR = mkRegM $ \ s at RA_State{ra_freeregs = freeregs} -> ===================================== compiler/GHC/CmmToAsm/Reg/Linear/X86.hs ===================================== @@ -32,13 +32,20 @@ getFreeRegs platform cls (FreeRegs f) = go f 0 where go 0 _ = [] go n m - | n .&. 1 /= 0 && classOfRealReg platform (RealRegSingle m) == cls + | n .&. 1 /= 0 && compatibleClass m = RealRegSingle m : (go (n `shiftR` 1) $! (m+1)) | otherwise = go (n `shiftR` 1) $! (m+1) -- ToDo: there's no point looking through all the integer registers -- in order to find a floating-point one. + compatibleClass i = + let regClass = classOfRealReg platform (RealRegSingle i) + in (if regClass == RcVector128 then RcDouble else regClass) + == (if cls == RcVector128 then RcDouble else cls) + -- SIMD NCG TODO: giant hack to account for xmm registers being + -- used for Double with SSE2. + allocateReg :: RealReg -> FreeRegs -> FreeRegs allocateReg (RealRegSingle r) (FreeRegs f) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs ===================================== @@ -32,13 +32,19 @@ getFreeRegs platform cls (FreeRegs f) = go f 0 where go 0 _ = [] go n m - | n .&. 1 /= 0 && classOfRealReg platform (RealRegSingle m) == cls + | n .&. 1 /= 0 && compatibleClass m = RealRegSingle m : (go (n `shiftR` 1) $! (m+1)) | otherwise = go (n `shiftR` 1) $! (m+1) -- ToDo: there's no point looking through all the integer registers -- in order to find a floating-point one. + compatibleClass i = + let regClass = classOfRealReg platform (RealRegSingle i) + in (if regClass == RcVector128 then RcDouble else regClass) + == (if cls == RcVector128 then RcDouble else cls) + -- SIMD NCG TODO: giant hack to account for xmm registers being + -- used for Double with SSE2. allocateReg :: RealReg -> FreeRegs -> FreeRegs allocateReg (RealRegSingle r) (FreeRegs f) ===================================== compiler/GHC/CmmToAsm/Reg/Liveness.hs ===================================== @@ -63,6 +63,8 @@ import GHC.Utils.Monad.State.Strict import Data.List (mapAccumL, partition) import Data.Maybe import Data.IntSet (IntSet) +import GHC.CmmToAsm.Format +import GHC.Types.Unique (Uniquable) ----------------------------------------------------------------------------- type RegSet = UniqSet Reg @@ -77,9 +79,6 @@ type RegMap a = UniqFM Reg a emptyRegMap :: RegMap a emptyRegMap = emptyUFM -emptyRegSet :: RegSet -emptyRegSet = emptyUniqSet - type BlockMap a = LabelMap a type SlotMap a = UniqFM Slot a @@ -101,10 +100,10 @@ data InstrSR instr = Instr instr -- | spill this reg to a stack slot - | SPILL Reg Int + | SPILL Reg Format Int -- | reload this reg from a stack slot - | RELOAD Int Reg + | RELOAD Int Reg Format deriving (Functor) @@ -112,14 +111,14 @@ instance Instruction instr => Instruction (InstrSR instr) where regUsageOfInstr platform i = case i of Instr instr -> regUsageOfInstr platform instr - SPILL reg _ -> RU [reg] [] - RELOAD _ reg -> RU [] [reg] + SPILL reg fmt _ -> RU [(reg, fmt)] [] + RELOAD _ reg fmt -> RU [] [(reg, fmt)] patchRegsOfInstr i f = case i of Instr instr -> Instr (patchRegsOfInstr instr f) - SPILL reg slot -> SPILL (f reg) slot - RELOAD slot reg -> RELOAD slot (f reg) + SPILL reg cls slot -> SPILL (f reg) cls slot + RELOAD slot reg cls -> RELOAD slot (f reg) cls isJumpishInstr i = case i of @@ -189,9 +188,9 @@ data LiveInstr instr data Liveness = Liveness - { liveBorn :: RegSet -- ^ registers born in this instruction (written to for first time). - , liveDieRead :: RegSet -- ^ registers that died because they were read for the last time. - , liveDieWrite :: RegSet } -- ^ registers that died because they were clobbered by something. + { liveBorn :: RegMap (Reg, Format) -- ^ registers born in this instruction (written to for first time). + , liveDieRead :: RegMap (Reg, Format) -- ^ registers that died because they were read for the last time. + , liveDieWrite :: RegMap (Reg, Format) } -- ^ registers that died because they were clobbered by something. -- | Stash regs live on entry to each basic block in the info part of the cmm code. @@ -200,7 +199,7 @@ data LiveInfo (LabelMap RawCmmStatics) -- cmm info table static stuff [BlockId] -- entry points (first one is the -- entry point for the proc). - (BlockMap RegSet) -- argument locals live on entry to this block + (BlockMap (UniqFM Reg (Reg, Format))) -- argument locals live on entry to this block (BlockMap IntSet) -- stack slots live on entry to this block @@ -215,7 +214,7 @@ instance Outputable instr ppr (Instr realInstr) = ppr realInstr - ppr (SPILL reg slot) + ppr (SPILL reg _cls slot) = hcat [ text "\tSPILL", char ' ', @@ -223,7 +222,7 @@ instance Outputable instr comma, text "SLOT" <> parens (int slot)] - ppr (RELOAD slot reg) + ppr (RELOAD slot reg _cls) = hcat [ text "\tRELOAD", char ' ', @@ -246,11 +245,11 @@ instance Outputable instr , pprRegs (text "# w_dying: ") (liveDieWrite live) ] $+$ space) - where pprRegs :: SDoc -> RegSet -> SDoc + where pprRegs :: Outputable a => SDoc -> RegMap a -> SDoc pprRegs name regs - | isEmptyUniqSet regs = empty + | isNullUFM regs = empty | otherwise = name <> - (pprUFM (getUniqSet regs) (hcat . punctuate space . map ppr)) + (pprUFM regs (hcat . punctuate space . map ppr)) instance OutputableP env instr => OutputableP env (LiveInstr instr) where pdoc env i = ppr (fmap (pdoc env) i) @@ -329,7 +328,7 @@ mapGenBlockTopM f (CmmProc header label live (ListGraph blocks)) slurpConflicts :: Instruction instr => LiveCmmDecl statics instr - -> (Bag (UniqSet Reg), Bag (Reg, Reg)) + -> (Bag (UniqFM Reg (Reg, Format)), Bag (Reg, Reg)) slurpConflicts live = slurpCmm (emptyBag, emptyBag) live @@ -363,23 +362,23 @@ slurpConflicts live = let -- regs that die because they are read for the last time at the start of an instruction -- are not live across it. - rsLiveAcross = rsLiveEntry `minusUniqSet` (liveDieRead live) + rsLiveAcross = rsLiveEntry `minusUFM` (liveDieRead live) -- regs live on entry to the next instruction. -- be careful of orphans, make sure to delete dying regs _after_ unioning -- in the ones that are born here. - rsLiveNext = (rsLiveAcross `unionUniqSets` (liveBorn live)) - `minusUniqSet` (liveDieWrite live) + rsLiveNext = (rsLiveAcross `plusUFM` (liveBorn live)) + `minusUFM` (liveDieWrite live) -- orphan vregs are the ones that die in the same instruction they are born in. -- these are likely to be results that are never used, but we still -- need to assign a hreg to them.. - rsOrphans = intersectUniqSets + rsOrphans = intersectUFM (liveBorn live) - (unionUniqSets (liveDieWrite live) (liveDieRead live)) + (plusUFM (liveDieWrite live) (liveDieRead live)) -- - rsConflicts = unionUniqSets rsLiveNext rsOrphans + rsConflicts = plusUFM rsLiveNext rsOrphans in case takeRegRegMoveInstr instr of Just rr -> slurpLIs rsLiveNext @@ -458,12 +457,12 @@ slurpReloadCoalesce live slurpLI slotMap li -- remember what reg was stored into the slot - | LiveInstr (SPILL reg slot) _ <- li - , slotMap' <- addToUFM slotMap slot reg + | LiveInstr (SPILL reg _cls slot) _ <- li + , slotMap' <- addToUFM slotMap slot reg = return (slotMap', Nothing) -- add an edge between the this reg and the last one stored into the slot - | LiveInstr (RELOAD slot reg) _ <- li + | LiveInstr (RELOAD slot reg _cls) _ <- li = case lookupUFM slotMap slot of Just reg2 | reg /= reg2 -> return (slotMap, Just (reg, reg2)) @@ -572,13 +571,13 @@ stripLiveBlock config (BasicBlock i lis) -- The SPILL/RELOAD cases do not appear to be exercised by our codegens -- - spillNat acc (LiveInstr (SPILL reg slot) _ : instrs) + spillNat acc (LiveInstr (SPILL reg cls slot) _ : instrs) = do delta <- get - spillNat (mkSpillInstr config reg delta slot ++ acc) instrs + spillNat (mkSpillInstr config reg cls delta slot ++ acc) instrs - spillNat acc (LiveInstr (RELOAD slot reg) _ : instrs) + spillNat acc (LiveInstr (RELOAD slot reg cls) _ : instrs) = do delta <- get - spillNat (mkLoadInstr config reg delta slot ++ acc) instrs + spillNat (mkLoadInstr config reg cls delta slot ++ acc) instrs spillNat acc (LiveInstr (Instr instr) _ : instrs) | Just i <- takeDeltaInstr instr @@ -621,9 +620,8 @@ patchEraseLive patchF cmm patchCmm (CmmProc info label live sccs) | LiveInfo static id blockMap mLiveSlots <- info = let - patchRegSet set = mkUniqSet $ map patchF $ nonDetEltsUFM set -- See Note [Unique Determinism and code generation] - blockMap' = mapMap (patchRegSet . getUniqSet) blockMap + blockMap' = mapMap (mapKeysUFM patchF) blockMap info' = LiveInfo static id blockMap' mLiveSlots in CmmProc info' label live $ map patchSCC sccs @@ -652,8 +650,8 @@ patchEraseLive patchF cmm | r1 == r2 = True -- destination reg is never used - | elementOfUniqSet r2 (liveBorn live) - , elementOfUniqSet r2 (liveDieRead live) || elementOfUniqSet r2 (liveDieWrite live) + | elemUFM r2 (liveBorn live) + , elemUFM r2 (liveDieRead live) || elemUFM r2 (liveDieWrite live) = True | otherwise = False @@ -676,11 +674,14 @@ patchRegsLiveInstr patchF li (patchRegsOfInstr instr patchF) (Just live { -- WARNING: have to go via lists here because patchF changes the uniq in the Reg - liveBorn = mapUniqSet patchF $ liveBorn live - , liveDieRead = mapUniqSet patchF $ liveDieRead live - , liveDieWrite = mapUniqSet patchF $ liveDieWrite live }) + liveBorn = mapKeysUFM patchF $ liveBorn live + , liveDieRead = mapKeysUFM patchF $ liveDieRead live + , liveDieWrite = mapKeysUFM patchF $ liveDieWrite live }) -- See Note [Unique Determinism and code generation] +-- SIMD NCG TODO: move this to Unique.FM module +mapKeysUFM :: Uniquable a => (t -> a) -> UniqFM key (t, b) -> UniqFM a (a, b) +mapKeysUFM f m = listToUFM $ map ( \ (r, fmt) -> let r' = f r in (r', (r', fmt)) ) $ nonDetEltsUFM m -------------------------------------------------------------------------------- -- | Convert a NatCmmDecl to a LiveCmmDecl, with liveness information @@ -869,7 +870,7 @@ computeLiveness -> [SCC (LiveBasicBlock instr)] -> ([SCC (LiveBasicBlock instr)], -- instructions annotated with list of registers -- which are "dead after this instruction". - BlockMap RegSet) -- blocks annotated with set of live registers + BlockMap (UniqFM Reg (Reg, Format))) -- blocks annotated with set of live registers -- on entry to the block. computeLiveness platform sccs @@ -884,11 +885,11 @@ computeLiveness platform sccs livenessSCCs :: Instruction instr => Platform - -> BlockMap RegSet + -> BlockMap (UniqFM Reg (Reg, Format)) -> [SCC (LiveBasicBlock instr)] -- accum -> [SCC (LiveBasicBlock instr)] -> ( [SCC (LiveBasicBlock instr)] - , BlockMap RegSet) + , BlockMap (UniqFM Reg (Reg, Format))) livenessSCCs _ blockmap done [] = (done, blockmap) @@ -917,8 +918,8 @@ livenessSCCs platform blockmap done linearLiveness :: Instruction instr - => BlockMap RegSet -> [LiveBasicBlock instr] - -> (BlockMap RegSet, [LiveBasicBlock instr]) + => BlockMap (UniqFM Reg (Reg, Format)) -> [LiveBasicBlock instr] + -> (BlockMap (UniqFM Reg (Reg, Format)), [LiveBasicBlock instr]) linearLiveness = mapAccumL (livenessBlock platform) @@ -926,9 +927,8 @@ livenessSCCs platform blockmap done -- BlockMaps for equality. equalBlockMaps a b = a' == b' - where a' = map f $ mapToList a - b' = map f $ mapToList b - f (key,elt) = (key, nonDetEltsUniqSet elt) + where a' = mapToList a + b' = mapToList b -- See Note [Unique Determinism and code generation] @@ -938,14 +938,14 @@ livenessSCCs platform blockmap done livenessBlock :: Instruction instr => Platform - -> BlockMap RegSet + -> BlockMap (UniqFM Reg (Reg, Format)) -> LiveBasicBlock instr - -> (BlockMap RegSet, LiveBasicBlock instr) + -> (BlockMap (UniqFM Reg (Reg, Format)), LiveBasicBlock instr) livenessBlock platform blockmap (BasicBlock block_id instrs) = let (regsLiveOnEntry, instrs1) - = livenessBack platform emptyUniqSet blockmap [] (reverse instrs) + = livenessBack platform emptyUFM blockmap [] (reverse instrs) blockmap' = mapInsert block_id regsLiveOnEntry blockmap instrs2 = livenessForward platform regsLiveOnEntry instrs1 @@ -960,7 +960,7 @@ livenessBlock platform blockmap (BasicBlock block_id instrs) livenessForward :: Instruction instr => Platform - -> RegSet -- regs live on this instr + -> UniqFM Reg (Reg, Format) -- regs live on this instr -> [LiveInstr instr] -> [LiveInstr instr] livenessForward _ _ [] = [] @@ -970,12 +970,14 @@ livenessForward platform rsLiveEntry (li@(LiveInstr instr mLive) : lis) RU _ written = regUsageOfInstr platform instr -- Regs that are written to but weren't live on entry to this instruction -- are recorded as being born here. - rsBorn = mkUniqSet - $ filter (\r -> not $ elementOfUniqSet r rsLiveEntry) written + rsBorn = listToUFM + $ map ( \ ( r, fmt ) -> ( r, ( r, fmt ) ) ) + $ filter (\( r, _) -> not $ elemUFM r rsLiveEntry) + $ written - rsLiveNext = (rsLiveEntry `unionUniqSets` rsBorn) - `minusUniqSet` (liveDieRead live) - `minusUniqSet` (liveDieWrite live) + rsLiveNext = (rsLiveEntry `plusUFM` rsBorn) + `minusUFM` (liveDieRead live) + `minusUFM` (liveDieWrite live) in LiveInstr instr (Just live { liveBorn = rsBorn }) : livenessForward platform rsLiveNext lis @@ -990,11 +992,11 @@ livenessForward platform rsLiveEntry (li@(LiveInstr instr mLive) : lis) livenessBack :: Instruction instr => Platform - -> RegSet -- regs live on this instr - -> BlockMap RegSet -- regs live on entry to other BBs + -> UniqFM Reg (Reg, Format) -- regs live on this instr + -> BlockMap (UniqFM Reg (Reg, Format)) -- regs live on entry to other BBs -> [LiveInstr instr] -- instructions (accum) -> [LiveInstr instr] -- instructions - -> (RegSet, [LiveInstr instr]) + -> (UniqFM Reg (Reg, Format), [LiveInstr instr]) livenessBack _ liveregs _ done [] = (liveregs, done) @@ -1007,10 +1009,10 @@ livenessBack platform liveregs blockmap acc (instr : instrs) liveness1 :: Instruction instr => Platform - -> RegSet - -> BlockMap RegSet + -> UniqFM Reg (Reg, Format) + -> BlockMap (UniqFM Reg (Reg, Format)) -> LiveInstr instr - -> (RegSet, LiveInstr instr) + -> (UniqFM Reg (Reg, Format), LiveInstr instr) liveness1 _ liveregs _ (LiveInstr instr _) | isMetaInstr instr @@ -1021,15 +1023,15 @@ liveness1 platform liveregs blockmap (LiveInstr instr _) | not_a_branch = (liveregs1, LiveInstr instr (Just $ Liveness - { liveBorn = emptyUniqSet + { liveBorn = emptyUFM , liveDieRead = r_dying , liveDieWrite = w_dying })) | otherwise = (liveregs_br, LiveInstr instr (Just $ Liveness - { liveBorn = emptyUniqSet - , liveDieRead = mkUniqSet r_dying_br + { liveBorn = emptyUFM + , liveDieRead = r_dying_br , liveDieWrite = w_dying })) where @@ -1037,18 +1039,18 @@ liveness1 platform liveregs blockmap (LiveInstr instr _) -- registers that were written here are dead going backwards. -- registers that were read here are live going backwards. - liveregs1 = (liveregs `delListFromUniqSet` written) - `addListToUniqSet` read + liveregs1 = (liveregs `delListFromUFM` (map fst written)) + `addListToUFM` (map (\(r, fmt) -> (r, (r,fmt))) read) -- registers that are not live beyond this point, are recorded -- as dying here. - r_dying = mkUniqSet - [ reg | reg <- read, reg `notElem` written, - not (elementOfUniqSet reg liveregs) ] + r_dying = listToUFM + [ (reg, (reg, fmt)) | (reg, fmt) <- read, reg `notElem` map fst written, + not (elemUFM reg liveregs) ] - w_dying = mkUniqSet - [ reg | reg <- written, - not (elementOfUniqSet reg liveregs) ] + w_dying = listToUFM + [ (reg, (reg, fmt)) | (reg, fmt) <- written, + not (elemUFM reg liveregs) ] -- union in the live regs from all the jump destinations of this -- instruction. @@ -1058,15 +1060,14 @@ liveness1 platform liveregs blockmap (LiveInstr instr _) targetLiveRegs target = case mapLookup target blockmap of Just ra -> ra - Nothing -> emptyRegSet + Nothing -> emptyUFM - live_from_branch = unionManyUniqSets (map targetLiveRegs targets) + live_from_branch = plusUFMList (map targetLiveRegs targets) - liveregs_br = liveregs1 `unionUniqSets` live_from_branch + liveregs_br = liveregs1 `plusUFM` live_from_branch -- registers that are live only in the branch targets should -- be listed as dying here. - live_branch_only = live_from_branch `minusUniqSet` liveregs - r_dying_br = nonDetEltsUniqSet (r_dying `unionUniqSets` - live_branch_only) + live_branch_only = live_from_branch `minusUFM` liveregs + r_dying_br = r_dying `plusUFM` live_branch_only -- See Note [Unique Determinism and code generation] ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -380,6 +380,8 @@ data Instr | VSHUFPS Format Imm Operand Reg | SHUFPD Format Imm Operand Reg | VSHUFPD Format Imm Operand Reg + -- SIMD NCG TODO: don't store the Format (or only what we need) + -- in order to emit these instructions. -- Shift | PSLLDQ Format Operand Reg @@ -401,129 +403,129 @@ data FMAPermutation = FMA132 | FMA213 | FMA231 regUsageOfInstr :: Platform -> Instr -> RegUsage regUsageOfInstr platform instr = case instr of - MOV _ src dst -> usageRW src dst - CMOV _ _ src dst -> mkRU (use_R src [dst]) [dst] - MOVZxL _ src dst -> usageRW src dst - MOVSxL _ src dst -> usageRW src dst - LEA _ src dst -> usageRW src dst - ADD _ src dst -> usageRM src dst - ADC _ src dst -> usageRM src dst - SUB _ src dst -> usageRM src dst - SBB _ src dst -> usageRM src dst - IMUL _ src dst -> usageRM src dst + MOV fmt src dst -> usageRW fmt src dst + CMOV _ fmt src dst -> mkRU fmt (use_R src [dst]) [dst] + MOVZxL fmt src dst -> usageRW fmt src dst + MOVSxL fmt src dst -> usageRW fmt src dst + LEA fmt src dst -> usageRW fmt src dst + ADD fmt src dst -> usageRM fmt src dst + ADC fmt src dst -> usageRM fmt src dst + SUB fmt src dst -> usageRM fmt src dst + SBB fmt src dst -> usageRM fmt src dst + IMUL fmt src dst -> usageRM fmt src dst -- Result of IMULB will be in just in %ax - IMUL2 II8 src -> mkRU (eax:use_R src []) [eax] + IMUL2 II8 src -> mkRU II8 (eax:use_R src []) [eax] -- Result of IMUL for wider values, will be split between %dx/%edx/%rdx and -- %ax/%eax/%rax. - IMUL2 _ src -> mkRU (eax:use_R src []) [eax,edx] - - MUL _ src dst -> usageRM src dst - MUL2 _ src -> mkRU (eax:use_R src []) [eax,edx] - DIV _ op -> mkRU (eax:edx:use_R op []) [eax,edx] - IDIV _ op -> mkRU (eax:edx:use_R op []) [eax,edx] - ADD_CC _ src dst -> usageRM src dst - SUB_CC _ src dst -> usageRM src dst - AND _ src dst -> usageRM src dst - OR _ src dst -> usageRM src dst - - XOR _ (OpReg src) (OpReg dst) - | src == dst -> mkRU [] [dst] - - XOR _ src dst -> usageRM src dst - NOT _ op -> usageM op - BSWAP _ reg -> mkRU [reg] [reg] - NEGI _ op -> usageM op - SHL _ imm dst -> usageRM imm dst - SAR _ imm dst -> usageRM imm dst - SHR _ imm dst -> usageRM imm dst - SHLD _ imm dst1 dst2 -> usageRMM imm dst1 dst2 - SHRD _ imm dst1 dst2 -> usageRMM imm dst1 dst2 - BT _ _ src -> mkRUR (use_R src []) - - PUSH _ op -> mkRUR (use_R op []) - POP _ op -> mkRU [] (def_W op) - TEST _ src dst -> mkRUR (use_R src $! use_R dst []) - CMP _ src dst -> mkRUR (use_R src $! use_R dst []) - SETCC _ op -> mkRU [] (def_W op) - JXX _ _ -> mkRU [] [] - JXX_GBL _ _ -> mkRU [] [] - JMP op regs -> mkRUR (use_R op regs) - JMP_TBL op _ _ _ -> mkRUR (use_R op []) - CALL (Left _) params -> mkRU params (callClobberedRegs platform) - CALL (Right reg) params -> mkRU (reg:params) (callClobberedRegs platform) - CLTD _ -> mkRU [eax] [edx] - NOP -> mkRU [] [] - - X87Store _ dst -> mkRUR ( use_EA dst []) - - CVTSS2SD src dst -> mkRU [src] [dst] - CVTSD2SS src dst -> mkRU [src] [dst] - CVTTSS2SIQ _ src dst -> mkRU (use_R src []) [dst] - CVTTSD2SIQ _ src dst -> mkRU (use_R src []) [dst] - CVTSI2SS _ src dst -> mkRU (use_R src []) [dst] - CVTSI2SD _ src dst -> mkRU (use_R src []) [dst] - FDIV _ src dst -> usageRM src dst - SQRT _ src dst -> mkRU (use_R src []) [dst] - - FETCHGOT reg -> mkRU [] [reg] - FETCHPC reg -> mkRU [] [reg] + IMUL2 fmt src -> mkRU fmt (eax:use_R src []) [eax,edx] + + MUL fmt src dst -> usageRM fmt src dst + MUL2 fmt src -> mkRU fmt (eax:use_R src []) [eax,edx] + DIV fmt op -> mkRU fmt (eax:edx:use_R op []) [eax,edx] + IDIV fmt op -> mkRU fmt (eax:edx:use_R op []) [eax,edx] + ADD_CC fmt src dst -> usageRM fmt src dst + SUB_CC fmt src dst -> usageRM fmt src dst + AND fmt src dst -> usageRM fmt src dst + OR fmt src dst -> usageRM fmt src dst + + XOR fmt (OpReg src) (OpReg dst) + | src == dst -> mkRU fmt [] [dst] + + XOR fmt src dst -> usageRM fmt src dst + NOT fmt op -> usageM fmt op + BSWAP fmt reg -> mkRU fmt [reg] [reg] + NEGI fmt op -> usageM fmt op + SHL fmt imm dst -> usageRM fmt imm dst + SAR fmt imm dst -> usageRM fmt imm dst + SHR fmt imm dst -> usageRM fmt imm dst + SHLD fmt imm dst1 dst2 -> usageRMM fmt imm dst1 dst2 + SHRD fmt imm dst1 dst2 -> usageRMM fmt imm dst1 dst2 + BT fmt _ src -> mkRUR fmt (use_R src []) + + PUSH fmt op -> mkRUR fmt (use_R op []) + POP fmt op -> mkRU fmt [] (def_W op) + TEST fmt src dst -> mkRUR fmt (use_R src $! use_R dst []) + CMP fmt src dst -> mkRUR fmt (use_R src $! use_R dst []) + SETCC _ op -> mkRU II64 [] (def_W op) + JXX _ _ -> mkRU II64 [] [] + JXX_GBL _ _ -> mkRU II64 [] [] + JMP op regs -> mkRUR II64 (use_R op regs) + JMP_TBL op _ _ _ -> mkRUR II64 (use_R op []) + CALL (Left _) params -> mkRU II64 params (callClobberedRegs platform) + CALL (Right reg) params -> mkRU II64 (reg:params) (callClobberedRegs platform) + CLTD _ -> mkRU II64 [eax] [edx] + NOP -> mkRU II64 [] [] + + X87Store fmt dst -> mkRUR fmt ( use_EA dst []) + + CVTSS2SD src dst -> mkRU FF64 [src] [dst] + CVTSD2SS src dst -> mkRU FF32 [src] [dst] + CVTTSS2SIQ _ src dst -> mkRU FF32 (use_R src []) [dst] + CVTTSD2SIQ _ src dst -> mkRU FF64 (use_R src []) [dst] + CVTSI2SS _ src dst -> mkRU FF32 (use_R src []) [dst] + CVTSI2SD _ src dst -> mkRU FF64 (use_R src []) [dst] + FDIV fmt src dst -> usageRM fmt src dst + SQRT fmt src dst -> mkRU fmt (use_R src []) [dst] + + FETCHGOT reg -> mkRU II64 [] [reg] + FETCHPC reg -> mkRU II64 [] [reg] COMMENT _ -> noUsage LOCATION{} -> noUsage UNWIND{} -> noUsage DELTA _ -> noUsage - POPCNT _ src dst -> mkRU (use_R src []) [dst] - LZCNT _ src dst -> mkRU (use_R src []) [dst] - TZCNT _ src dst -> mkRU (use_R src []) [dst] - BSF _ src dst -> mkRU (use_R src []) [dst] - BSR _ src dst -> mkRU (use_R src []) [dst] + POPCNT fmt src dst -> mkRU fmt (use_R src []) [dst] + LZCNT fmt src dst -> mkRU fmt (use_R src []) [dst] + TZCNT fmt src dst -> mkRU fmt (use_R src []) [dst] + BSF fmt src dst -> mkRU fmt (use_R src []) [dst] + BSR fmt src dst -> mkRU fmt (use_R src []) [dst] - PDEP _ src mask dst -> mkRU (use_R src $ use_R mask []) [dst] - PEXT _ src mask dst -> mkRU (use_R src $ use_R mask []) [dst] + PDEP fmt src mask dst -> mkRU fmt (use_R src $ use_R mask []) [dst] + PEXT fmt src mask dst -> mkRU fmt (use_R src $ use_R mask []) [dst] - FMA3 _ _ _ src3 src2 dst -> usageFMA src3 src2 dst + FMA3 fmt _ _ src3 src2 dst -> usageFMA fmt src3 src2 dst -- note: might be a better way to do this - PREFETCH _ _ src -> mkRU (use_R src []) [] + PREFETCH _ fmt src -> mkRU fmt (use_R src []) [] LOCK i -> regUsageOfInstr platform i - XADD _ src dst -> usageMM src dst - CMPXCHG _ src dst -> usageRMM src dst (OpReg eax) - XCHG _ src dst -> usageMM src (OpReg dst) + XADD fmt src dst -> usageMM fmt src dst + CMPXCHG fmt src dst -> usageRMM fmt src dst (OpReg eax) + XCHG fmt src dst -> usageMM fmt src (OpReg dst) MFENCE -> noUsage -- vector instructions - VBROADCAST _ src dst -> mkRU (use_EA src []) [dst] - VEXTRACT _ off src dst -> mkRU ((use_R off []) ++ [src]) (use_R dst []) - INSERTPS _ off src dst - -> mkRU ((use_R off []) ++ (use_R src []) ++ [dst]) [dst] - - VMOVU _ src dst -> mkRU (use_R src []) (use_R dst []) - MOVU _ src dst -> mkRU (use_R src []) (use_R dst []) - MOVL _ src dst -> mkRU (use_R src []) (use_R dst []) - MOVH _ src dst -> mkRU (use_R src []) (use_R dst []) - VPXOR _ s1 s2 dst -> mkRU [s1,s2] [dst] - - VADD _ s1 s2 dst -> mkRU ((use_R s1 []) ++ [s2]) [dst] - VSUB _ s1 s2 dst -> mkRU ((use_R s1 []) ++ [s2]) [dst] - VMUL _ s1 s2 dst -> mkRU ((use_R s1 []) ++ [s2]) [dst] - VDIV _ s1 s2 dst -> mkRU ((use_R s1 []) ++ [s2]) [dst] - - VPSHUFD _ _off src dst - -> mkRU (use_R src []) [dst] - PSHUFD _ _off src dst - -> mkRU (use_R src []) [dst] - SHUFPD _ _off src dst - -> mkRU (use_R src [dst]) [dst] - SHUFPS _ _off src dst - -> mkRU (use_R src [dst]) [dst] - VSHUFPD _ _off src dst - -> mkRU (use_R src [dst]) [dst] - VSHUFPS _ _off src dst - -> mkRU (use_R src [dst]) [dst] - - PSLLDQ _ off dst -> mkRU (use_R off []) [dst] + VBROADCAST fmt src dst -> mkRU fmt (use_EA src []) [dst] + VEXTRACT fmt off src dst -> mkRU fmt ((use_R off []) ++ [src]) (use_R dst []) + INSERTPS fmt off src dst + -> mkRU fmt ((use_R off []) ++ (use_R src []) ++ [dst]) [dst] + + VMOVU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) + MOVU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) + MOVL fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) + MOVH fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) + VPXOR fmt s1 s2 dst -> mkRU fmt [s1,s2] [dst] + + VADD fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] + VSUB fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] + VMUL fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] + VDIV fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] + + VPSHUFD fmt _off src dst + -> mkRU fmt (use_R src []) [dst] + PSHUFD fmt _off src dst + -> mkRU fmt (use_R src []) [dst] + SHUFPD fmt _off src dst + -> mkRU fmt (use_R src [dst]) [dst] + SHUFPS fmt _off src dst + -> mkRU fmt (use_R src [dst]) [dst] + VSHUFPD fmt _off src dst + -> mkRU fmt (use_R src [dst]) [dst] + VSHUFPS fmt _off src dst + -> mkRU fmt (use_R src [dst]) [dst] + + PSLLDQ fmt off dst -> mkRU fmt (use_R off []) [dst] _other -> panic "regUsage: unrecognised instr" where @@ -537,44 +539,44 @@ regUsageOfInstr platform instr -- are read. -- 2 operand form; first operand Read; second Written - usageRW :: Operand -> Operand -> RegUsage - usageRW op (OpReg reg) = mkRU (use_R op []) [reg] - usageRW op (OpAddr ea) = mkRUR (use_R op $! use_EA ea []) - usageRW _ _ = panic "X86.RegInfo.usageRW: no match" + usageRW :: Format -> Operand -> Operand -> RegUsage + usageRW fmt op (OpReg reg) = mkRU fmt (use_R op []) [reg] + usageRW fmt op (OpAddr ea) = mkRUR fmt (use_R op $! use_EA ea []) + usageRW _ _ _ = panic "X86.RegInfo.usageRW: no match" -- 2 operand form; first operand Read; second Modified - usageRM :: Operand -> Operand -> RegUsage - usageRM op (OpReg reg) = mkRU (use_R op [reg]) [reg] - usageRM op (OpAddr ea) = mkRUR (use_R op $! use_EA ea []) - usageRM _ _ = panic "X86.RegInfo.usageRM: no match" + usageRM :: Format -> Operand -> Operand -> RegUsage + usageRM fmt op (OpReg reg) = mkRU fmt (use_R op [reg]) [reg] + usageRM fmt op (OpAddr ea) = mkRUR fmt (use_R op $! use_EA ea []) + usageRM _ _ _ = panic "X86.RegInfo.usageRM: no match" -- 2 operand form; first operand Modified; second Modified - usageMM :: Operand -> Operand -> RegUsage - usageMM (OpReg src) (OpReg dst) = mkRU [src, dst] [src, dst] - usageMM (OpReg src) (OpAddr ea) = mkRU (use_EA ea [src]) [src] - usageMM (OpAddr ea) (OpReg dst) = mkRU (use_EA ea [dst]) [dst] - usageMM _ _ = panic "X86.RegInfo.usageMM: no match" + usageMM :: Format -> Operand -> Operand -> RegUsage + usageMM fmt (OpReg src) (OpReg dst) = mkRU fmt [src, dst] [src, dst] + usageMM fmt (OpReg src) (OpAddr ea) = mkRU fmt (use_EA ea [src]) [src] + usageMM fmt (OpAddr ea) (OpReg dst) = mkRU fmt (use_EA ea [dst]) [dst] + usageMM _ _ _ = panic "X86.RegInfo.usageMM: no match" -- 3 operand form; first operand Read; second Modified; third Modified - usageRMM :: Operand -> Operand -> Operand -> RegUsage - usageRMM (OpReg src) (OpReg dst) (OpReg reg) = mkRU [src, dst, reg] [dst, reg] - usageRMM (OpReg src) (OpAddr ea) (OpReg reg) = mkRU (use_EA ea [src, reg]) [reg] - usageRMM _ _ _ = panic "X86.RegInfo.usageRMM: no match" + usageRMM :: Format -> Operand -> Operand -> Operand -> RegUsage + usageRMM fmt (OpReg src) (OpReg dst) (OpReg reg) = mkRU fmt [src, dst, reg] [dst, reg] + usageRMM fmt (OpReg src) (OpAddr ea) (OpReg reg) = mkRU fmt (use_EA ea [src, reg]) [reg] + usageRMM _ _ _ _ = panic "X86.RegInfo.usageRMM: no match" -- 3 operand form of FMA instructions. - usageFMA :: Operand -> Reg -> Reg -> RegUsage - usageFMA (OpReg src1) src2 dst - = mkRU [src1, src2, dst] [dst] - usageFMA (OpAddr ea1) src2 dst - = mkRU (use_EA ea1 [src2, dst]) [dst] - usageFMA _ _ _ + usageFMA :: Format -> Operand -> Reg -> Reg -> RegUsage + usageFMA fmt (OpReg src1) src2 dst + = mkRU fmt [src1, src2, dst] [dst] + usageFMA fmt (OpAddr ea1) src2 dst + = mkRU fmt (use_EA ea1 [src2, dst]) [dst] + usageFMA _ _ _ _ = panic "X86.RegInfo.usageFMA: no match" -- 1 operand form; operand Modified - usageM :: Operand -> RegUsage - usageM (OpReg reg) = mkRU [reg] [reg] - usageM (OpAddr ea) = mkRUR (use_EA ea []) - usageM _ = panic "X86.RegInfo.usageM: no match" + usageM :: Format -> Operand -> RegUsage + usageM fmt (OpReg reg) = mkRU fmt [reg] [reg] + usageM fmt (OpAddr ea) = mkRUR fmt (use_EA ea []) + usageM _ _ = panic "X86.RegInfo.usageM: no match" -- Registers defd when an operand is written. def_W (OpReg reg) = [reg] @@ -595,10 +597,11 @@ regUsageOfInstr platform instr use_index EAIndexNone tl = tl use_index (EAIndex i _) tl = i : tl - mkRUR src = src' `seq` RU src' [] + mkRUR fmt src = src' `seq` RU (map (,fmt) src') [] where src' = filter (interesting platform) src - mkRU src dst = src' `seq` dst' `seq` RU src' dst' + + mkRU fmt src dst = src' `seq` dst' `seq` RU (map (,fmt) src') (map (,fmt) dst') where src' = filter (interesting platform) src dst' = filter (interesting platform) dst @@ -817,18 +820,27 @@ patchJumpInstr insn patchF mkSpillInstr :: NCGConfig -> Reg -- register to spill + -> Format -> Int -- current stack delta -> Int -- spill slot to use -> [Instr] -mkSpillInstr config reg delta slot - = let off = spillSlotToOffset platform slot - delta - in - case targetClassOfReg platform reg of - RcInteger -> [MOV (archWordFormat is32Bit) - (OpReg reg) (OpAddr (spRel platform off))] - RcDouble -> [MOV FF64 (OpReg reg) (OpAddr (spRel platform off))] - _ -> panic "X86.mkSpillInstr: no match" +mkSpillInstr config reg fmt delta slot + = let off s = spillSlotToOffset platform s - delta + in case fmt of + IntegerFormat -> [MOV (archWordFormat is32Bit) + (OpReg reg) (OpAddr (spRel platform $ off slot))] + FF64 -> [MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off slot))] + FF32 -> panic "X86_mkSpillInstr: RcFloat" + VecFormat {} -> + -- SIMD NCG TODO: panic for unsupported VecFormats (& same in mkLoadInstr) + [MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off slot)) + -- Now shuffle the register, putting the high half into the lower half. + ,SHUFPD (VecFormat 2 FmtDouble W64) (ImmInt 0b01) (OpReg reg) reg + -- NB: this format doesn't matter, we emit the same instruction + -- regardless of what is stored... + -- SIMD NCG TODO: avoid using MOV by using SHUFPD with an OpAddr argument? + ,MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off (slot + 1)))] where platform = ncgPlatform config is32Bit = target32Bit platform @@ -836,18 +848,30 @@ mkSpillInstr config reg delta slot mkLoadInstr :: NCGConfig -> Reg -- register to load + -> Format -> Int -- current stack delta -> Int -- spill slot to use -> [Instr] -mkLoadInstr config reg delta slot - = let off = spillSlotToOffset platform slot - delta +mkLoadInstr config reg fmt delta slot + = let off s = spillSlotToOffset platform s - delta in - case targetClassOfReg platform reg of - RcInteger -> ([MOV (archWordFormat is32Bit) - (OpAddr (spRel platform off)) (OpReg reg)]) - RcDouble -> ([MOV FF64 (OpAddr (spRel platform off)) (OpReg reg)]) - _ -> panic "X86.mkLoadInstr" + case fmt of + IntegerFormat -> ([MOV (archWordFormat is32Bit) + (OpAddr (spRel platform $ off slot)) (OpReg reg)]) + FF64 -> ([MOV FF64 (OpAddr (spRel platform $ off slot)) (OpReg reg)]) + FF32 -> panic "X86.mkLoadInstr RcFloat" + VecFormat {} -> + -- Load the higher half into the lower part of register from the second stack slot, + -- shuffle it into the higher part of the register, + -- and load then lower half into the lower part of the register. + [MOV FF64 (OpAddr (spRel platform $ off (slot + 1))) (OpReg reg) + ,SHUFPD (VecFormat 2 FmtDouble W64) (ImmInt 0b01) (OpReg reg) reg + -- SIMD NCG TODO: not sure about this immediate + -- SIMD NCG TODO: can we avoid the MOV instructions and directly + -- use SHUFPD for an Addr to Reg move? + ,MOV FF64 (OpAddr (spRel platform $ off slot)) (OpReg reg)] + where platform = ncgPlatform config is32Bit = target32Bit platform ===================================== compiler/GHC/Platform/Reg.hs ===================================== @@ -116,17 +116,12 @@ renameVirtualReg u r classOfVirtualReg :: VirtualReg -> RegClass classOfVirtualReg vr - = case vr of + = case vr of VirtualRegI{} -> RcInteger VirtualRegHi{} -> RcInteger VirtualRegF{} -> RcFloat VirtualRegD{} -> RcDouble - -- Below is an awful, largely x86-specific hack - VirtualRegVec{} -> RcDouble - -- SIMD NCG TODO: this seems very wrong and potentially the source of - -- bug #16927, because we use this function to determine how to spill - -- the contents of a virtual register - -- (see e.g. GHC.CmmToAsm.X86.Instr.mkSpillInstr). + VirtualRegVec{} -> RcVector128 -- Determine the upper-half vreg for a 64-bit quantity on a 32-bit platform ===================================== compiler/GHC/Platform/Reg/Class.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE LambdaCase #-} -- | An architecture independent description of a register's class. module GHC.Platform.Reg.Class ( RegClass (..) @@ -18,21 +19,26 @@ import GHC.Builtin.Uniques -- We treat all registers in a class as being interchangeable. -- data RegClass - = RcInteger - | RcFloat - | RcDouble - deriving (Eq, Show) + = RcInteger + | RcFloat + | RcDouble + | RcVector128 + deriving (Eq, Ord, Show) allRegClasses :: [RegClass] allRegClasses = - [RcInteger, RcFloat, RcDouble] + [ RcInteger, RcFloat, RcDouble, RcVector128 ] instance Uniquable RegClass where - getUnique RcInteger = mkRegClassUnique 0 - getUnique RcFloat = mkRegClassUnique 1 - getUnique RcDouble = mkRegClassUnique 2 + getUnique = \case + RcInteger -> mkRegClassUnique 0 + RcFloat -> mkRegClassUnique 1 + RcDouble -> mkRegClassUnique 2 + RcVector128 -> mkRegClassUnique 3 instance Outputable RegClass where - ppr RcInteger = Outputable.text "I" - ppr RcFloat = Outputable.text "F" - ppr RcDouble = Outputable.text "D" + ppr = \case + RcInteger -> Outputable.text "I" + RcFloat -> Outputable.text "F" + RcDouble -> Outputable.text "D" + RcVector128 -> Outputable.text "V" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/34d7a1702f9fc170f754726a665ddb3e36044992 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/34d7a1702f9fc170f754726a665ddb3e36044992 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 16:18:42 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Thu, 06 Jun 2024 12:18:42 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/fix-macos-wasm Message-ID: <6661e1621b695_12ae2144c43a810431e@gitlab.mail> Cheng Shao pushed new branch wip/fix-macos-wasm at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-macos-wasm You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 16:52:44 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 06 Jun 2024 12:52:44 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] SIMD NCG WIP: fix stack spilling Message-ID: <6661e95c4e02_167afa2ca6b484235@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: b2ca03a3 by sheaf at 2024-06-06T18:51:57+02:00 SIMD NCG WIP: fix stack spilling - - - - - 22 changed files: - compiler/GHC/CmmToAsm/AArch64.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/PPC.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Coalesce.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs - compiler/GHC/CmmToAsm/Reg/Linear/State.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Platform/Reg.hs - compiler/GHC/Platform/Reg/Class.hs Changes: ===================================== compiler/GHC/CmmToAsm/AArch64.hs ===================================== @@ -49,8 +49,8 @@ instance Instruction AArch64.Instr where jumpDestsOfInstr = AArch64.jumpDestsOfInstr canFallthroughTo = AArch64.canFallthroughTo patchJumpInstr = AArch64.patchJumpInstr - mkSpillInstr = AArch64.mkSpillInstr - mkLoadInstr = AArch64.mkLoadInstr + mkSpillInstr cfg reg _ i j = AArch64.mkSpillInstr cfg reg i j + mkLoadInstr cfg reg _ i j = AArch64.mkLoadInstr cfg reg i j takeDeltaInstr = AArch64.takeDeltaInstr isMetaInstr = AArch64.isMetaInstr mkRegRegMoveInstr _ = AArch64.mkRegRegMoveInstr ===================================== compiler/GHC/CmmToAsm/AArch64/Instr.hs ===================================== @@ -145,8 +145,9 @@ regUsageOfInstr platform instr = case instr of -- filtering the usage is necessary, otherwise the register -- allocator will try to allocate pre-defined fixed stg -- registers as well, as they show up. - usage (src, dst) = RU (filter (interesting platform) src) - (filter (interesting platform) dst) + usage (src, dst) = RU (map (,II64) $ filter (interesting platform) src) + (map (,II64) $ filter (interesting platform) dst) + -- SIMD NCG TODO: remove this hack regAddr :: AddrMode -> [Reg] regAddr (AddrRegReg r1 r2) = [r1, r2] ===================================== compiler/GHC/CmmToAsm/Format.hs ===================================== @@ -1,3 +1,7 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE ViewPatterns #-} + -- | Formats on this architecture -- A Format is a combination of width and class -- @@ -9,7 +13,7 @@ -- properly. eg SPARC doesn't care about FF80. -- module GHC.CmmToAsm.Format ( - Format(..), + Format(.., IntegerFormat), ScalarFormat(..), intFormat, floatFormat, @@ -18,7 +22,7 @@ module GHC.CmmToAsm.Format ( isVecFormat, cmmTypeFormat, formatToWidth, - formatInBytes + formatInBytes, ) where @@ -73,7 +77,23 @@ data Format | FF32 | FF64 | VecFormat !Length !ScalarFormat !Width - deriving (Show, Eq) + deriving (Show, Eq, Ord) + +pattern IntegerFormat :: Format +pattern IntegerFormat <- ( isIntegerFormat -> True ) +{-# COMPLETE IntegerFormat, FF32, FF64, VecFormat #-} + +isIntegerFormat :: Format -> Bool +isIntegerFormat = \case + II8 -> True + II16 -> True + II32 -> True + II64 -> True + _ -> False + + +instance Outputable Format where + ppr fmt = text (show fmt) data ScalarFormat = FmtInt8 | FmtInt16 @@ -81,7 +101,7 @@ data ScalarFormat = FmtInt8 | FmtInt64 | FmtFloat | FmtDouble - deriving (Show, Eq) + deriving (Show, Eq, Ord) -- | Get the integer format of this width. intFormat :: Width -> Format ===================================== compiler/GHC/CmmToAsm/Instr.hs ===================================== @@ -16,6 +16,7 @@ import GHC.Cmm.BlockId import GHC.CmmToAsm.Config import GHC.Data.FastString +import GHC.CmmToAsm.Format -- | Holds a list of source and destination registers used by a -- particular instruction. @@ -29,8 +30,8 @@ import GHC.Data.FastString -- data RegUsage = RU { - reads :: [Reg], - writes :: [Reg] + reads :: [(Reg, Format)], + writes :: [(Reg, Format)] } deriving Show @@ -96,15 +97,17 @@ class Instruction instr where mkSpillInstr :: NCGConfig -> Reg -- ^ the reg to spill + -> Format -> Int -- ^ the current stack delta - -> Int -- ^ spill slot to use - -> [instr] -- ^ instructions + -> Int -- ^ spill slots to use + -> [instr] -- ^ instructions -- | An instruction to reload a register from a spill slot. mkLoadInstr :: NCGConfig -> Reg -- ^ the reg to reload. + -> Format -> Int -- ^ the current stack delta -> Int -- ^ the spill slot to use -> [instr] -- ^ instructions ===================================== compiler/GHC/CmmToAsm/PPC.hs ===================================== @@ -48,8 +48,8 @@ instance Instruction PPC.Instr where jumpDestsOfInstr = PPC.jumpDestsOfInstr canFallthroughTo = PPC.canFallthroughTo patchJumpInstr = PPC.patchJumpInstr - mkSpillInstr = PPC.mkSpillInstr - mkLoadInstr = PPC.mkLoadInstr + mkSpillInstr cfg reg _ i j = PPC.mkSpillInstr cfg reg i j + mkLoadInstr cfg reg _ i j = PPC.mkLoadInstr cfg reg i j takeDeltaInstr = PPC.takeDeltaInstr isMetaInstr = PPC.isMetaInstr mkRegRegMoveInstr _ = PPC.mkRegRegMoveInstr ===================================== compiler/GHC/CmmToAsm/PPC/Instr.hs ===================================== @@ -391,8 +391,9 @@ regUsageOfInstr platform instr FMADD _ _ rt ra rc rb -> usage ([ra, rc, rb], [rt]) _ -> noUsage where - usage (src, dst) = RU (filter (interesting platform) src) - (filter (interesting platform) dst) + usage (src, dst) = RU (map (,II64) $ filter (interesting platform) src) + (map (,II64) $ filter (interesting platform) dst) + -- SIMD NCG TODO: remove this hack regAddr (AddrRegReg r1 r2) = [r1, r2] regAddr (AddrRegImm r1 _) = [r1] ===================================== compiler/GHC/CmmToAsm/Reg/Graph.hs ===================================== @@ -335,21 +335,21 @@ buildGraph code -- | Add some conflict edges to the graph. -- Conflicts between virtual and real regs are recorded as exclusions. graphAddConflictSet - :: UniqSet Reg + :: RegMap (Reg, fmt) -> Color.Graph VirtualReg RegClass RealReg -> Color.Graph VirtualReg RegClass RealReg -graphAddConflictSet set graph +graphAddConflictSet regs graph = let virtuals = mkUniqSet - [ vr | RegVirtual vr <- nonDetEltsUniqSet set ] + [ vr | (RegVirtual vr, _) <- nonDetEltsUFM regs ] graph1 = Color.addConflicts virtuals classOfVirtualReg graph graph2 = foldr (\(r1, r2) -> Color.addExclusion r1 classOfVirtualReg r2) graph1 [ (vr, rr) - | RegVirtual vr <- nonDetEltsUniqSet set - , RegReal rr <- nonDetEltsUniqSet set] + | (RegVirtual vr, _) <- nonDetEltsUFM regs + , (RegReal rr, _) <- nonDetEltsUFM regs] -- See Note [Unique Determinism and code generation] in graph2 ===================================== compiler/GHC/CmmToAsm/Reg/Graph/Coalesce.hs ===================================== @@ -13,7 +13,6 @@ import GHC.Cmm import GHC.Data.Bag import GHC.Data.Graph.Directed import GHC.Types.Unique.FM -import GHC.Types.Unique.Set import GHC.Types.Unique.Supply @@ -85,8 +84,8 @@ slurpJoinMovs live slurpLI rs (LiveInstr _ Nothing) = rs slurpLI rs (LiveInstr instr (Just live)) | Just (r1, r2) <- takeRegRegMoveInstr instr - , elementOfUniqSet r1 $ liveDieRead live - , elementOfUniqSet r2 $ liveBorn live + , elemUFM r1 $ liveDieRead live + , elemUFM r2 $ liveBorn live -- only coalesce movs between two virtuals for now, -- else we end up with allocatable regs in the live ===================================== compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs ===================================== @@ -31,6 +31,7 @@ import Data.List (nub, (\\), intersect) import Data.Maybe import Data.IntSet (IntSet) import qualified Data.IntSet as IntSet +import GHC.CmmToAsm.Format -- | Spill all these virtual regs to stack slots. @@ -138,7 +139,7 @@ regSpill_top platform regSlotMap cmm -- then record the fact that these slots are now live in those blocks -- in the given slotmap. patchLiveSlot - :: BlockMap IntSet -> BlockId -> RegSet -> BlockMap IntSet + :: BlockMap IntSet -> BlockId -> RegMap (Reg, Format) -> BlockMap IntSet patchLiveSlot slotMap blockId regsLive = let @@ -148,7 +149,8 @@ regSpill_top platform regSlotMap cmm moreSlotsLive = IntSet.fromList $ mapMaybe (lookupUFM regSlotMap) - $ nonDetEltsUniqSet regsLive + $ map fst + $ nonDetEltsUFM regsLive -- See Note [Unique Determinism and code generation] slotMap' @@ -197,9 +199,9 @@ regSpill_instr platform regSlotMap (LiveInstr instr (Just _)) = do let rsModify = intersect rsRead_ rsWritten_ -- work out if any of the regs being used are currently being spilled. - let rsSpillRead = filter (\r -> elemUFM r regSlotMap) rsRead - let rsSpillWritten = filter (\r -> elemUFM r regSlotMap) rsWritten - let rsSpillModify = filter (\r -> elemUFM r regSlotMap) rsModify + let rsSpillRead = filter (\(r,_) -> elemUFM r regSlotMap) rsRead + let rsSpillWritten = filter (\(r,_) -> elemUFM r regSlotMap) rsWritten + let rsSpillModify = filter (\(r,_) -> elemUFM r regSlotMap) rsModify -- rewrite the instr and work out spill code. (instr1, prepost1) <- mapAccumLM (spillRead regSlotMap) instr rsSpillRead @@ -224,10 +226,10 @@ spillRead :: Instruction instr => UniqFM Reg Int -> instr - -> Reg + -> (Reg, Format) -> SpillM (instr, ([LiveInstr instr'], [LiveInstr instr'])) -spillRead regSlotMap instr reg +spillRead regSlotMap instr (reg, fmt) | Just slot <- lookupUFM regSlotMap reg = do (instr', nReg) <- patchInstr reg instr @@ -235,7 +237,7 @@ spillRead regSlotMap instr reg { stateSpillSL = addToUFM_C accSpillSL (stateSpillSL s) reg (reg, 0, 1) } return ( instr' - , ( [LiveInstr (RELOAD slot nReg) Nothing] + , ( [LiveInstr (RELOAD slot nReg fmt) Nothing] , []) ) | otherwise = panic "RegSpill.spillRead: no slot defined for spilled reg" @@ -247,10 +249,10 @@ spillWrite :: Instruction instr => UniqFM Reg Int -> instr - -> Reg + -> (Reg, Format) -> SpillM (instr, ([LiveInstr instr'], [LiveInstr instr'])) -spillWrite regSlotMap instr reg +spillWrite regSlotMap instr (reg, fmt) | Just slot <- lookupUFM regSlotMap reg = do (instr', nReg) <- patchInstr reg instr @@ -259,7 +261,7 @@ spillWrite regSlotMap instr reg return ( instr' , ( [] - , [LiveInstr (SPILL nReg slot) Nothing])) + , [LiveInstr (SPILL nReg fmt slot) Nothing])) | otherwise = panic "RegSpill.spillWrite: no slot defined for spilled reg" @@ -270,10 +272,10 @@ spillModify :: Instruction instr => UniqFM Reg Int -> instr - -> Reg + -> (Reg, Format) -> SpillM (instr, ([LiveInstr instr'], [LiveInstr instr'])) -spillModify regSlotMap instr reg +spillModify regSlotMap instr (reg, fmt) | Just slot <- lookupUFM regSlotMap reg = do (instr', nReg) <- patchInstr reg instr @@ -281,8 +283,8 @@ spillModify regSlotMap instr reg { stateSpillSL = addToUFM_C accSpillSL (stateSpillSL s) reg (reg, 1, 1) } return ( instr' - , ( [LiveInstr (RELOAD slot nReg) Nothing] - , [LiveInstr (SPILL nReg slot) Nothing])) + , ( [LiveInstr (RELOAD slot nReg fmt) Nothing] + , [LiveInstr (SPILL nReg fmt slot) Nothing])) | otherwise = panic "RegSpill.spillModify: no slot defined for spilled reg" ===================================== compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs ===================================== @@ -160,12 +160,13 @@ cleanForward _ _ _ acc [] -- hopefully the spill will be also be cleaned in the next pass cleanForward platform blockId assoc acc (li1 : li2 : instrs) - | LiveInstr (SPILL reg1 slot1) _ <- li1 - , LiveInstr (RELOAD slot2 reg2) _ <- li2 + | LiveInstr (SPILL reg1 _ slot1) _ <- li1 + , LiveInstr (RELOAD slot2 reg2 _) _ <- li2 , slot1 == slot2 = do modify $ \s -> s { sCleanedReloadsAcc = sCleanedReloadsAcc s + 1 } cleanForward platform blockId assoc acc + -- SIMD NCG TODO: is mkRegRegMoveInstr here OK for vectors? $ li1 : LiveInstr (mkRegRegMoveInstr platform reg1 reg2) Nothing : instrs @@ -189,7 +190,7 @@ cleanForward platform blockId assoc acc (li@(LiveInstr i1 _) : instrs) cleanForward platform blockId assoc acc (li : instrs) -- Update association due to the spill. - | LiveInstr (SPILL reg slot) _ <- li + | LiveInstr (SPILL reg _ slot) _ <- li = let assoc' = addAssoc (SReg reg) (SSlot slot) $ delAssoc (SSlot slot) $ assoc @@ -215,7 +216,7 @@ cleanForward platform blockId assoc acc (li : instrs) -- Writing to a reg changes its value. | LiveInstr instr _ <- li , RU _ written <- regUsageOfInstr platform instr - = let assoc' = foldr delAssoc assoc (map SReg $ nub written) + = let assoc' = foldr delAssoc assoc (map SReg $ nub $ map fst written) in cleanForward platform blockId assoc' (li : acc) instrs @@ -229,7 +230,7 @@ cleanReload -> LiveInstr instr -> CleanM (Assoc Store, Maybe (LiveInstr instr)) -cleanReload platform blockId assoc li@(LiveInstr (RELOAD slot reg) _) +cleanReload platform blockId assoc li@(LiveInstr (RELOAD slot reg _) _) -- If the reg we're reloading already has the same value as the slot -- then we can erase the instruction outright. @@ -355,12 +356,12 @@ cleanBackward' _ _ _ acc [] cleanBackward' liveSlotsOnEntry reloadedBy noReloads acc (li : instrs) -- If nothing ever reloads from this slot then we don't need the spill. - | LiveInstr (SPILL _ slot) _ <- li + | LiveInstr (SPILL _ _ slot) _ <- li , Nothing <- lookupUFM reloadedBy (SSlot slot) = do modify $ \s -> s { sCleanedSpillsAcc = sCleanedSpillsAcc s + 1 } cleanBackward liveSlotsOnEntry noReloads acc instrs - | LiveInstr (SPILL _ slot) _ <- li + | LiveInstr (SPILL _ _ slot) _ <- li = if elementOfUniqSet slot noReloads -- We can erase this spill because the slot won't be read until @@ -375,7 +376,7 @@ cleanBackward' liveSlotsOnEntry reloadedBy noReloads acc (li : instrs) cleanBackward liveSlotsOnEntry noReloads' (li : acc) instrs -- if we reload from a slot then it's no longer unused - | LiveInstr (RELOAD slot _) _ <- li + | LiveInstr (RELOAD slot _ _) _ <- li , noReloads' <- delOneFromUniqSet noReloads slot = cleanBackward liveSlotsOnEntry noReloads' (li : acc) instrs ===================================== compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs ===================================== @@ -129,8 +129,8 @@ slurpSpillCostInfo platform cfg cmm -- Increment counts for what regs were read/written from. let (RU read written) = regUsageOfInstr platform instr - mapM_ (incUses scale) $ mapMaybe takeVirtualReg $ nub read - mapM_ (incDefs scale) $ mapMaybe takeVirtualReg $ nub written + mapM_ (incUses scale) $ mapMaybe takeVirtualReg $ nub $ map fst read + mapM_ (incDefs scale) $ mapMaybe takeVirtualReg $ nub $ map fst written -- Compute liveness for entry to next instruction. let liveDieRead_virt = takeVirtuals (liveDieRead live) @@ -158,9 +158,9 @@ slurpSpillCostInfo platform cfg cmm = 1.0 -- Only if no cfg given -- | Take all the virtual registers from this set. -takeVirtuals :: UniqSet Reg -> UniqSet VirtualReg -takeVirtuals set = mkUniqSet - [ vr | RegVirtual vr <- nonDetEltsUniqSet set ] +takeVirtuals :: RegMap (Reg, fmt) -> UniqSet VirtualReg +takeVirtuals m = mkUniqSet + [ vr | (RegVirtual vr, _) <- nonDetEltsUFM m ] -- See Note [Unique Determinism and code generation] ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -127,7 +127,6 @@ import GHC.Cmm hiding (RegSet) import GHC.Data.Graph.Directed import GHC.Types.Unique -import GHC.Types.Unique.Set import GHC.Types.Unique.FM import GHC.Types.Unique.Supply import GHC.Utils.Outputable @@ -137,6 +136,7 @@ import GHC.Platform import Data.Maybe import Data.List (partition, nub) import Control.Monad +import GHC.CmmToAsm.Format -- ----------------------------------------------------------------------------- -- Top level of the register allocator @@ -203,7 +203,7 @@ linearRegAlloc :: forall instr. (Instruction instr) => NCGConfig -> [BlockId] -- ^ entry points - -> BlockMap RegSet + -> BlockMap (UniqFM Reg (Reg, Format)) -- ^ live regs on entry to each basic block -> [SCC (LiveBasicBlock instr)] -- ^ instructions annotated with "deaths" @@ -242,7 +242,7 @@ linearRegAlloc' => NCGConfig -> freeRegs -> [BlockId] -- ^ entry points - -> BlockMap RegSet -- ^ live regs on entry to each basic block + -> BlockMap (UniqFM Reg (Reg, Format)) -- ^ live regs on entry to each basic block -> [SCC (LiveBasicBlock instr)] -- ^ instructions annotated with "deaths" -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int) @@ -256,7 +256,7 @@ linearRegAlloc' config initFreeRegs entry_ids block_live sccs linearRA_SCCs :: OutputableRegConstraint freeRegs instr => [BlockId] - -> BlockMap RegSet + -> BlockMap (UniqFM Reg (Reg, Format)) -> [NatBasicBlock instr] -> [SCC (LiveBasicBlock instr)] -> RegM freeRegs [NatBasicBlock instr] @@ -291,7 +291,7 @@ linearRA_SCCs entry_ids block_live blocksAcc (CyclicSCC blocks : sccs) process :: forall freeRegs instr. (OutputableRegConstraint freeRegs instr) => [BlockId] - -> BlockMap RegSet + -> BlockMap (UniqFM Reg (Reg, Format)) -> [GenBasicBlock (LiveInstr instr)] -> RegM freeRegs [[NatBasicBlock instr]] process entry_ids block_live = @@ -330,7 +330,7 @@ process entry_ids block_live = -- processBlock :: OutputableRegConstraint freeRegs instr - => BlockMap RegSet -- ^ live regs on entry to each basic block + => BlockMap (UniqFM Reg (Reg, Format)) -- ^ live regs on entry to each basic block -> LiveBasicBlock instr -- ^ block to do register allocation on -> RegM freeRegs [NatBasicBlock instr] -- ^ block with registers allocated @@ -347,7 +347,7 @@ processBlock block_live (BasicBlock id instrs) -- | Load the freeregs and current reg assignment into the RegM state -- for the basic block with this BlockId. initBlock :: FR freeRegs - => BlockId -> BlockMap RegSet -> RegM freeRegs () + => BlockId -> BlockMap (UniqFM Reg (Reg, Format)) -> RegM freeRegs () initBlock id block_live = do platform <- getPlatform block_assig <- getBlockAssigR @@ -364,7 +364,7 @@ initBlock id block_live setFreeRegsR (frInitFreeRegs platform) Just live -> setFreeRegsR $ foldl' (flip $ frAllocateReg platform) (frInitFreeRegs platform) - [ r | RegReal r <- nonDetEltsUniqSet live ] + [ r | ( RegReal r, _ ) <- nonDetEltsUFM live ] -- See Note [Unique Determinism and code generation] setAssigR emptyRegMap @@ -377,7 +377,7 @@ initBlock id block_live -- | Do allocation for a sequence of instructions. linearRA :: forall freeRegs instr. (OutputableRegConstraint freeRegs instr) - => BlockMap RegSet -- ^ map of what vregs are live on entry to each block. + => BlockMap (UniqFM Reg (Reg, Format)) -- ^ map of what vregs are live on entry to each block. -> BlockId -- ^ id of the current block, for debugging. -> [LiveInstr instr] -- ^ liveness annotated instructions in this block. -> RegM freeRegs @@ -402,7 +402,7 @@ linearRA block_live block_id = go [] [] -- | Do allocation for a single instruction. raInsn :: OutputableRegConstraint freeRegs instr - => BlockMap RegSet -- ^ map of what vregs are love on entry to each block. + => BlockMap (UniqFM Reg (Reg, Format)) -- ^ map of what vregs are love on entry to each block. -> [instr] -- ^ accumulator for instructions already processed. -> BlockId -- ^ the id of the current block, for debugging -> LiveInstr instr -- ^ the instr to have its regs allocated, with liveness info. @@ -432,12 +432,12 @@ raInsn block_live new_instrs id (LiveInstr (Instr instr) (Just live)) -- (we can't eliminate it if the source register is on the stack, because -- we do not want to use one spill slot for different virtual registers) case takeRegRegMoveInstr instr of - Just (src,dst) | src `elementOfUniqSet` (liveDieRead live), + Just (src,dst) | Just (_, fmt) <- lookupUFM (liveDieRead live) src, isVirtualReg dst, not (dst `elemUFM` assig), isRealReg src || isInReg src assig -> do case src of - (RegReal rr) -> setAssigR (addToUFM assig dst (InReg rr)) + RegReal rr -> setAssigR (addToUFM assig dst (InReg $ RealRegUsage rr fmt)) -- if src is a fixed reg, then we just map dest to this -- reg in the assignment. src must be an allocatable reg, -- otherwise it wouldn't be in r_dying. @@ -456,8 +456,8 @@ raInsn block_live new_instrs id (LiveInstr (Instr instr) (Just live)) return (new_instrs, []) _ -> genRaInsn block_live new_instrs id instr - (nonDetEltsUniqSet $ liveDieRead live) - (nonDetEltsUniqSet $ liveDieWrite live) + (map fst $ nonDetEltsUFM $ liveDieRead live) + (map fst $ nonDetEltsUFM $ liveDieWrite live) -- See Note [Unique Determinism and code generation] raInsn _ _ _ instr @@ -486,7 +486,7 @@ isInReg src assig | Just (InReg _) <- lookupUFM assig src = True genRaInsn :: forall freeRegs instr. (OutputableRegConstraint freeRegs instr) - => BlockMap RegSet + => BlockMap (UniqFM Reg (Reg, Format)) -> [instr] -> BlockId -> instr @@ -499,13 +499,13 @@ genRaInsn block_live new_instrs block_id instr r_dying w_dying = do platform <- getPlatform case regUsageOfInstr platform instr of { RU read written -> do - let real_written = [ rr | (RegReal rr) <- written ] :: [RealReg] - let virt_written = [ vr | (RegVirtual vr) <- written ] + let real_written = [ rr | (RegReal rr, _) <- written ] :: [RealReg] + let virt_written = [ vr | (RegVirtual vr, _) <- written ] -- we don't need to do anything with real registers that are -- only read by this instr. (the list is typically ~2 elements, -- so using nub isn't a problem). - let virt_read = nub [ vr | (RegVirtual vr) <- read ] :: [VirtualReg] + let virt_read = nub [ vr | (RegVirtual vr, _) <- read ] :: [VirtualReg] -- do -- let real_read = nub [ rr | (RegReal rr) <- read] @@ -638,9 +638,9 @@ releaseRegs regs = do loop assig !free (r:rs) = case lookupUFM assig r of Just (InBoth real _) -> loop (delFromUFM assig r) - (frReleaseReg platform real free) rs + (frReleaseReg platform (realReg real) free) rs Just (InReg real) -> loop (delFromUFM assig r) - (frReleaseReg platform real free) rs + (frReleaseReg platform (realReg real) free) rs _ -> loop (delFromUFM assig r) free rs loop assig free regs @@ -688,15 +688,15 @@ saveClobberedTemps clobbered dying -- currently support deterministic code-generation. -- See Note [Unique Determinism and code generation] InReg reg - | any (realRegsAlias reg) clobbered + | any (realRegsAlias $ realReg reg) clobbered , temp `notElem` map getUnique dying - -> clobber temp (assig,instrs) (reg) + -> clobber temp (assig,instrs) reg _ -> return (assig,instrs) -- See Note [UniqFM and the register allocator] - clobber :: Unique -> (RegMap Loc,[instr]) -> (RealReg) -> RegM freeRegs (RegMap Loc,[instr]) - clobber temp (assig,instrs) (reg) + clobber :: Unique -> (RegMap Loc,[instr]) -> RealRegUsage -> RegM freeRegs (RegMap Loc,[instr]) + clobber temp (assig,instrs) (RealRegUsage reg fmt) = do platform <- getPlatform freeRegs <- getFreeRegsR @@ -711,7 +711,7 @@ saveClobberedTemps clobbered dying (my_reg : _) -> do setFreeRegsR (frAllocateReg platform my_reg freeRegs) - let new_assign = addToUFM_Directly assig temp (InReg my_reg) + let new_assign = addToUFM_Directly assig temp (InReg (RealRegUsage my_reg fmt)) let instr = mkRegRegMoveInstr platform (RegReal reg) (RegReal my_reg) @@ -719,12 +719,12 @@ saveClobberedTemps clobbered dying -- (2) no free registers: spill the value [] -> do - (spill, slot) <- spillR (RegReal reg) temp + (spill, slot) <- spillR (RegReal reg) fmt temp -- record why this reg was spilled for profiling recordSpill (SpillClobber temp) - let new_assign = addToUFM_Directly assig temp (InBoth reg slot) + let new_assign = addToUFM_Directly assig temp (InBoth (RealRegUsage reg fmt) slot) return (new_assign, (spill ++ instrs)) @@ -771,7 +771,7 @@ clobberRegs clobbered = assig clobber assig ((temp, InBoth reg slot) : rest) - | any (realRegsAlias reg) clobbered + | any (realRegsAlias $ realReg reg) clobbered = clobber (addToUFM_Directly assig temp (InMem slot)) rest clobber assig (_:rest) @@ -817,7 +817,7 @@ allocateRegsAndSpill reading keep spills alloc (r:rs) case lookupUFM assig r of -- case (1a): already in a register Just (InReg my_reg) -> - allocateRegsAndSpill reading keep spills (my_reg:alloc) rs + allocateRegsAndSpill reading keep spills (realReg my_reg:alloc) rs -- case (1b): already in a register (and memory) -- NB1. if we're writing this register, update its assignment to be @@ -826,7 +826,7 @@ allocateRegsAndSpill reading keep spills alloc (r:rs) -- are also read by the same instruction. Just (InBoth my_reg _) -> do when (not reading) (setAssigR $ toRegMap (addToUFM assig r (InReg my_reg))) - allocateRegsAndSpill reading keep spills (my_reg:alloc) rs + allocateRegsAndSpill reading keep spills (realReg my_reg:alloc) rs -- Not already in a register, so we need to find a free one... Just (InMem slot) | reading -> doSpill (ReadMem slot) @@ -869,7 +869,15 @@ allocRegsAndSpill_spill :: (FR freeRegs, Instruction instr) allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc = do platform <- getPlatform freeRegs <- getFreeRegsR - let freeRegs_thisClass = frGetFreeRegs platform (classOfVirtualReg r) freeRegs :: [RealReg] + let regclass = classOfVirtualReg r + freeRegs_thisClass = frGetFreeRegs platform regclass freeRegs :: [RealReg] + -- SIMD NCG TODO: this is not the right thing to be doing, + -- and is indicative we should not use Format but a more + -- trimmed down datatype that only keeps track of e.g. + -- how many stack slots something uses up. + vr_fmt = case r of + VirtualRegVec {} -> VecFormat 2 FmtDouble W64 + _ -> II64 -- Can we put the variable into a register it already was? pref_reg <- findPrefRealReg r @@ -883,10 +891,10 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc = reg | otherwise = first_free - spills' <- loadTemp r spill_loc final_reg spills + spills' <- loadTemp r vr_fmt spill_loc final_reg spills setAssigR $ toRegMap - $ (addToUFM assig r $! newLocation spill_loc final_reg) + $ (addToUFM assig r $! newLocation spill_loc $ RealRegUsage final_reg vr_fmt) setFreeRegsR $ frAllocateReg platform final_reg freeRegs allocateRegsAndSpill reading keep spills' (final_reg : alloc) rs @@ -908,48 +916,53 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc let candidates = nonDetUFMToList candidates' -- the vregs we could kick out that are already in a slot - let candidates_inBoth :: [(Unique, RealReg, StackSlot)] + let compat reg' r' + = let cls1 = targetClassOfRealReg platform reg' + cls2 = classOfVirtualReg r' + in (if cls1 == RcVector128 then RcDouble else cls1) + == (if cls2 == RcVector128 then RcDouble else cls2) + candidates_inBoth :: [(Unique, RealRegUsage, StackSlot)] candidates_inBoth = [ (temp, reg, mem) | (temp, InBoth reg mem) <- candidates - , targetClassOfRealReg platform reg == classOfVirtualReg r ] + , compat (realReg reg) r ] -- the vregs we could kick out that are only in a reg -- this would require writing the reg to a new slot before using it. let candidates_inReg = [ (temp, reg) | (temp, InReg reg) <- candidates - , targetClassOfRealReg platform reg == classOfVirtualReg r ] + , compat (realReg reg) r ] let result -- we have a temporary that is in both register and mem, -- just free up its register for use. - | (temp, my_reg, slot) : _ <- candidates_inBoth - = do spills' <- loadTemp r spill_loc my_reg spills + | (temp, myRegUse@(RealRegUsage my_reg fmt), slot) : _ <- candidates_inBoth + = do spills' <- loadTemp r fmt spill_loc my_reg spills let assig1 = addToUFM_Directly assig temp (InMem slot) - let assig2 = addToUFM assig1 r $! newLocation spill_loc my_reg + let assig2 = addToUFM assig1 r $! newLocation spill_loc myRegUse setAssigR $ toRegMap assig2 allocateRegsAndSpill reading keep spills' (my_reg:alloc) rs -- otherwise, we need to spill a temporary that currently -- resides in a register. - | (temp_to_push_out, (my_reg :: RealReg)) : _ + | (temp_to_push_out, RealRegUsage my_reg fmt) : _ <- candidates_inReg = do - (spill_store, slot) <- spillR (RegReal my_reg) temp_to_push_out + (spill_store, slot) <- spillR (RegReal my_reg) fmt temp_to_push_out -- record that this temp was spilled recordSpill (SpillAlloc temp_to_push_out) -- update the register assignment let assig1 = addToUFM_Directly assig temp_to_push_out (InMem slot) - let assig2 = addToUFM assig1 r $! newLocation spill_loc my_reg + let assig2 = addToUFM assig1 r $! newLocation spill_loc (RealRegUsage my_reg fmt) setAssigR $ toRegMap assig2 -- if need be, load up a spilled temp into the reg we've just freed up. - spills' <- loadTemp r spill_loc my_reg spills + spills' <- loadTemp r fmt spill_loc my_reg spills allocateRegsAndSpill reading keep (spill_store ++ spills') @@ -970,7 +983,7 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc -- | Calculate a new location after a register has been loaded. -newLocation :: SpillLoc -> RealReg -> Loc +newLocation :: SpillLoc -> RealRegUsage -> Loc -- if the tmp was read from a slot, then now its in a reg as well newLocation (ReadMem slot) my_reg = InBoth my_reg slot -- writes will always result in only the register being available @@ -980,16 +993,17 @@ newLocation _ my_reg = InReg my_reg loadTemp :: (Instruction instr) => VirtualReg -- the temp being loaded + -> Format -> SpillLoc -- the current location of this temp -> RealReg -- the hreg to load the temp into -> [instr] -> RegM freeRegs [instr] -loadTemp vreg (ReadMem slot) hreg spills +loadTemp vreg fmt (ReadMem slot) hreg spills = do - insn <- loadR (RegReal hreg) slot + insn <- loadR (RegReal hreg) fmt slot recordSpill (SpillLoad $ getUnique vreg) return $ {- mkComment (text "spill load") : -} insn ++ spills -loadTemp _ _ _ spills = +loadTemp _ _ _ _ spills = return spills ===================================== compiler/GHC/CmmToAsm/Reg/Linear/Base.hs ===================================== @@ -11,6 +11,7 @@ module GHC.CmmToAsm.Reg.Linear.Base ( Loc(..), regsOfLoc, + RealRegUsage(..), -- for stats SpillReason(..), @@ -36,6 +37,7 @@ import GHC.Types.Unique.Supply import GHC.Cmm.BlockId import GHC.Cmm.Dataflow.Label import GHC.CmmToAsm.Reg.Utils +import GHC.CmmToAsm.Format data ReadingOrWriting = Reading | Writing deriving (Eq,Ord) @@ -76,8 +78,8 @@ updateBlockAssignment dest (freeRegs, regMap) (BlockAssignment {..}) = combWithExisting old_reg _ = Just $ old_reg fromLoc :: Loc -> Maybe RealReg - fromLoc (InReg rr) = Just rr - fromLoc (InBoth rr _) = Just rr + fromLoc (InReg rr) = Just $ realReg rr + fromLoc (InBoth rr _) = Just $ realReg rr fromLoc _ = Nothing @@ -94,23 +96,29 @@ updateBlockAssignment dest (freeRegs, regMap) (BlockAssignment {..}) = -- data Loc -- | vreg is in a register - = InReg !RealReg + = InReg {-# UNPACK #-} !RealRegUsage - -- | vreg is held in a stack slot + -- | vreg is held in stack slots | InMem {-# UNPACK #-} !StackSlot - -- | vreg is held in both a register and a stack slot - | InBoth !RealReg + -- | vreg is held in both a register and stack slots + | InBoth {-# UNPACK #-} !RealRegUsage {-# UNPACK #-} !StackSlot deriving (Eq, Show, Ord) +data RealRegUsage + = RealRegUsage + { realReg :: !RealReg + , realRegFormat :: !Format + } deriving (Eq, Show, Ord) + instance Outputable Loc where ppr l = text (show l) -- | Get the reg numbers stored in this Loc. -regsOfLoc :: Loc -> [RealReg] +regsOfLoc :: Loc -> [RealRegUsage] regsOfLoc (InReg r) = [r] regsOfLoc (InBoth r _) = [r] regsOfLoc (InMem _) = [] ===================================== compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs ===================================== @@ -29,16 +29,16 @@ import GHC.Utils.Panic import GHC.Utils.Monad (concatMapM) import GHC.Types.Unique import GHC.Types.Unique.FM -import GHC.Types.Unique.Set import GHC.Utils.Outputable +import GHC.CmmToAsm.Format -- | For a jump instruction at the end of a block, generate fixup code so its -- vregs are in the correct regs for its destination. -- joinToTargets :: (FR freeRegs, Instruction instr) - => BlockMap RegSet -- ^ maps the unique of the blockid to the set of vregs + => BlockMap (RegMap (Reg, Format)) -- ^ maps the unique of the blockid to the set of vregs -- that are known to be live on the entry to each block. -> BlockId -- ^ id of the current block @@ -62,7 +62,7 @@ joinToTargets block_live id instr ----- joinToTargets' :: (FR freeRegs, Instruction instr) - => BlockMap RegSet -- ^ maps the unique of the blockid to the set of vregs + => BlockMap (RegMap (Reg, Format)) -- ^ maps the unique of the blockid to the set of vregs -- that are known to be live on the entry to each block. -> [NatBasicBlock instr] -- ^ acc blocks of fixup code. @@ -90,7 +90,7 @@ joinToTargets' block_live new_blocks block_id instr (dest:dests) -- adjust the current assignment to remove any vregs that are not live -- on entry to the destination block. let Just live_set = mapLookup dest block_live - let still_live uniq _ = uniq `elemUniqSet_Directly` live_set + let still_live uniq _ = uniq `elemUFM_Directly` live_set let adjusted_assig = filterUFM_Directly still_live assig -- and free up those registers which are now free. @@ -99,14 +99,14 @@ joinToTargets' block_live new_blocks block_id instr (dest:dests) -- This is non-deterministic but we do not -- currently support deterministic code-generation. -- See Note [Unique Determinism and code generation] - , not (elemUniqSet_Directly reg live_set) + , not (elemUFM_Directly reg live_set) , r <- regsOfLoc loc ] case lookupBlockAssignment dest block_assig of Nothing -> joinToTargets_first block_live new_blocks block_id instr dest dests - block_assig adjusted_assig to_free + block_assig adjusted_assig $ map realReg to_free Just (_, dest_assig) -> joinToTargets_again @@ -116,7 +116,7 @@ joinToTargets' block_live new_blocks block_id instr (dest:dests) -- this is the first time we jumped to this block. joinToTargets_first :: (FR freeRegs, Instruction instr) - => BlockMap RegSet + => BlockMap (UniqFM Reg (Reg, Format)) -> [NatBasicBlock instr] -> BlockId -> instr @@ -145,7 +145,7 @@ joinToTargets_first block_live new_blocks block_id instr dest dests -- we've jumped to this block before joinToTargets_again :: (Instruction instr, FR freeRegs) - => BlockMap RegSet + => BlockMap (UniqFM Reg (Reg, Format)) -> [NatBasicBlock instr] -> BlockId -> instr @@ -327,15 +327,15 @@ handleComponent delta _ (AcyclicSCC (DigraphNode vreg src dsts)) -- require a fixup. -- handleComponent delta instr - (CyclicSCC ((DigraphNode vreg (InReg sreg) ((InReg dreg: _))) : rest)) + (CyclicSCC ((DigraphNode vreg (InReg (RealRegUsage sreg scls)) ((InReg (RealRegUsage dreg dcls): _))) : rest)) -- dest list may have more than one element, if the reg is also InMem. = do -- spill the source into its slot (instrSpill, slot) - <- spillR (RegReal sreg) vreg + <- spillR (RegReal sreg) scls vreg -- reload into destination reg - instrLoad <- loadR (RegReal dreg) slot + instrLoad <- loadR (RegReal dreg) dcls slot remainingFixUps <- mapM (handleComponent delta instr) (stronglyConnCompFromEdgedVerticesOrdR rest) @@ -363,15 +363,16 @@ makeMove delta vreg src dst let platform = ncgPlatform config case (src, dst) of - (InReg s, InReg d) -> + (InReg (RealRegUsage s _), InReg (RealRegUsage d _)) -> do recordSpill (SpillJoinRR vreg) + -- SIMD NCG TODO: does reg-2-reg work for vector registers? return $ [mkRegRegMoveInstr platform (RegReal s) (RegReal d)] - (InMem s, InReg d) -> + (InMem s, InReg (RealRegUsage d cls)) -> do recordSpill (SpillJoinRM vreg) - return $ mkLoadInstr config (RegReal d) delta s - (InReg s, InMem d) -> + return $ mkLoadInstr config (RegReal d) cls delta s + (InReg (RealRegUsage s cls), InMem d) -> do recordSpill (SpillJoinRM vreg) - return $ mkSpillInstr config (RegReal s) delta d + return $ mkSpillInstr config (RegReal s) cls delta d _ -> -- we don't handle memory to memory moves. -- they shouldn't happen because we don't share ===================================== compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs ===================================== @@ -24,6 +24,7 @@ import GHC.Prelude import GHC.Types.Unique.FM import GHC.Types.Unique +import GHC.CmmToAsm.Format -- | Identifier for a stack slot. @@ -47,13 +48,18 @@ emptyStackMap = StackMap 0 emptyUFM -- | If this vreg unique already has a stack assignment then return the slot number, -- otherwise allocate a new slot, and update the map. -- -getStackSlotFor :: StackMap -> Unique -> (StackMap, Int) - -getStackSlotFor fs@(StackMap _ reserved) reg - | Just slot <- lookupUFM reserved reg = (fs, slot) - -getStackSlotFor (StackMap freeSlot reserved) reg = - (StackMap (freeSlot+1) (addToUFM reserved reg freeSlot), freeSlot) +getStackSlotFor :: StackMap -> Format -> Unique -> (StackMap, Int) + +getStackSlotFor fs@(StackMap _ reserved) _fmt regUnique + | Just slot <- lookupUFM reserved regUnique = (fs, slot) + +getStackSlotFor (StackMap freeSlot reserved) fmt regUnique = + let + nbSlots = case fmt of + VecFormat {} -> 2 -- SIMD NCG TODO: panic for unsupported vectors + _ -> 1 + in + (StackMap (freeSlot+nbSlots) (addToUFM reserved regUnique freeSlot), freeSlot) -- | Return the number of stack slots that were allocated getStackUse :: StackMap -> Int ===================================== compiler/GHC/CmmToAsm/Reg/Linear/State.hs ===================================== @@ -53,6 +53,7 @@ import GHC.Types.Unique.Supply import GHC.Exts (oneShot) import Control.Monad (ap) +import GHC.CmmToAsm.Format type RA_Result freeRegs a = (# RA_State freeRegs, a #) @@ -121,20 +122,20 @@ makeRAStats state spillR :: Instruction instr - => Reg -> Unique -> RegM freeRegs ([instr], Int) + => Reg -> Format -> Unique -> RegM freeRegs ([instr], Int) -spillR reg temp = mkRegM $ \s -> - let (stack1,slot) = getStackSlotFor (ra_stack s) temp - instr = mkSpillInstr (ra_config s) reg (ra_delta s) slot +spillR reg fmt temp = mkRegM $ \s -> + let (stack1,slots) = getStackSlotFor (ra_stack s) fmt temp + instr = mkSpillInstr (ra_config s) reg fmt (ra_delta s) slots in - RA_Result s{ra_stack=stack1} (instr,slot) + RA_Result s{ra_stack=stack1} (instr,slots) loadR :: Instruction instr - => Reg -> Int -> RegM freeRegs [instr] + => Reg -> Format -> Int -> RegM freeRegs [instr] -loadR reg slot = mkRegM $ \s -> - RA_Result s (mkLoadInstr (ra_config s) reg (ra_delta s) slot) +loadR reg fmt slot = mkRegM $ \s -> + RA_Result s (mkLoadInstr (ra_config s) reg fmt (ra_delta s) slot) getFreeRegsR :: RegM freeRegs freeRegs getFreeRegsR = mkRegM $ \ s at RA_State{ra_freeregs = freeregs} -> ===================================== compiler/GHC/CmmToAsm/Reg/Linear/X86.hs ===================================== @@ -32,13 +32,20 @@ getFreeRegs platform cls (FreeRegs f) = go f 0 where go 0 _ = [] go n m - | n .&. 1 /= 0 && classOfRealReg platform (RealRegSingle m) == cls + | n .&. 1 /= 0 && compatibleClass m = RealRegSingle m : (go (n `shiftR` 1) $! (m+1)) | otherwise = go (n `shiftR` 1) $! (m+1) -- ToDo: there's no point looking through all the integer registers -- in order to find a floating-point one. + compatibleClass i = + let regClass = classOfRealReg platform (RealRegSingle i) + in (if regClass == RcVector128 then RcDouble else regClass) + == (if cls == RcVector128 then RcDouble else cls) + -- SIMD NCG TODO: giant hack to account for xmm registers being + -- used for Double with SSE2. + allocateReg :: RealReg -> FreeRegs -> FreeRegs allocateReg (RealRegSingle r) (FreeRegs f) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs ===================================== @@ -32,13 +32,19 @@ getFreeRegs platform cls (FreeRegs f) = go f 0 where go 0 _ = [] go n m - | n .&. 1 /= 0 && classOfRealReg platform (RealRegSingle m) == cls + | n .&. 1 /= 0 && compatibleClass m = RealRegSingle m : (go (n `shiftR` 1) $! (m+1)) | otherwise = go (n `shiftR` 1) $! (m+1) -- ToDo: there's no point looking through all the integer registers -- in order to find a floating-point one. + compatibleClass i = + let regClass = classOfRealReg platform (RealRegSingle i) + in (if regClass == RcVector128 then RcDouble else regClass) + == (if cls == RcVector128 then RcDouble else cls) + -- SIMD NCG TODO: giant hack to account for xmm registers being + -- used for Double with SSE2. allocateReg :: RealReg -> FreeRegs -> FreeRegs allocateReg (RealRegSingle r) (FreeRegs f) ===================================== compiler/GHC/CmmToAsm/Reg/Liveness.hs ===================================== @@ -63,6 +63,8 @@ import GHC.Utils.Monad.State.Strict import Data.List (mapAccumL, partition) import Data.Maybe import Data.IntSet (IntSet) +import GHC.CmmToAsm.Format +import GHC.Types.Unique (Uniquable) ----------------------------------------------------------------------------- type RegSet = UniqSet Reg @@ -77,9 +79,6 @@ type RegMap a = UniqFM Reg a emptyRegMap :: RegMap a emptyRegMap = emptyUFM -emptyRegSet :: RegSet -emptyRegSet = emptyUniqSet - type BlockMap a = LabelMap a type SlotMap a = UniqFM Slot a @@ -101,10 +100,10 @@ data InstrSR instr = Instr instr -- | spill this reg to a stack slot - | SPILL Reg Int + | SPILL Reg Format Int -- | reload this reg from a stack slot - | RELOAD Int Reg + | RELOAD Int Reg Format deriving (Functor) @@ -112,14 +111,14 @@ instance Instruction instr => Instruction (InstrSR instr) where regUsageOfInstr platform i = case i of Instr instr -> regUsageOfInstr platform instr - SPILL reg _ -> RU [reg] [] - RELOAD _ reg -> RU [] [reg] + SPILL reg fmt _ -> RU [(reg, fmt)] [] + RELOAD _ reg fmt -> RU [] [(reg, fmt)] patchRegsOfInstr i f = case i of Instr instr -> Instr (patchRegsOfInstr instr f) - SPILL reg slot -> SPILL (f reg) slot - RELOAD slot reg -> RELOAD slot (f reg) + SPILL reg cls slot -> SPILL (f reg) cls slot + RELOAD slot reg cls -> RELOAD slot (f reg) cls isJumpishInstr i = case i of @@ -189,9 +188,9 @@ data LiveInstr instr data Liveness = Liveness - { liveBorn :: RegSet -- ^ registers born in this instruction (written to for first time). - , liveDieRead :: RegSet -- ^ registers that died because they were read for the last time. - , liveDieWrite :: RegSet } -- ^ registers that died because they were clobbered by something. + { liveBorn :: RegMap (Reg, Format) -- ^ registers born in this instruction (written to for first time). + , liveDieRead :: RegMap (Reg, Format) -- ^ registers that died because they were read for the last time. + , liveDieWrite :: RegMap (Reg, Format) } -- ^ registers that died because they were clobbered by something. -- | Stash regs live on entry to each basic block in the info part of the cmm code. @@ -200,7 +199,7 @@ data LiveInfo (LabelMap RawCmmStatics) -- cmm info table static stuff [BlockId] -- entry points (first one is the -- entry point for the proc). - (BlockMap RegSet) -- argument locals live on entry to this block + (BlockMap (UniqFM Reg (Reg, Format))) -- argument locals live on entry to this block (BlockMap IntSet) -- stack slots live on entry to this block @@ -215,7 +214,7 @@ instance Outputable instr ppr (Instr realInstr) = ppr realInstr - ppr (SPILL reg slot) + ppr (SPILL reg _cls slot) = hcat [ text "\tSPILL", char ' ', @@ -223,7 +222,7 @@ instance Outputable instr comma, text "SLOT" <> parens (int slot)] - ppr (RELOAD slot reg) + ppr (RELOAD slot reg _cls) = hcat [ text "\tRELOAD", char ' ', @@ -246,11 +245,11 @@ instance Outputable instr , pprRegs (text "# w_dying: ") (liveDieWrite live) ] $+$ space) - where pprRegs :: SDoc -> RegSet -> SDoc + where pprRegs :: Outputable a => SDoc -> RegMap a -> SDoc pprRegs name regs - | isEmptyUniqSet regs = empty + | isNullUFM regs = empty | otherwise = name <> - (pprUFM (getUniqSet regs) (hcat . punctuate space . map ppr)) + (pprUFM regs (hcat . punctuate space . map ppr)) instance OutputableP env instr => OutputableP env (LiveInstr instr) where pdoc env i = ppr (fmap (pdoc env) i) @@ -329,7 +328,7 @@ mapGenBlockTopM f (CmmProc header label live (ListGraph blocks)) slurpConflicts :: Instruction instr => LiveCmmDecl statics instr - -> (Bag (UniqSet Reg), Bag (Reg, Reg)) + -> (Bag (UniqFM Reg (Reg, Format)), Bag (Reg, Reg)) slurpConflicts live = slurpCmm (emptyBag, emptyBag) live @@ -363,23 +362,23 @@ slurpConflicts live = let -- regs that die because they are read for the last time at the start of an instruction -- are not live across it. - rsLiveAcross = rsLiveEntry `minusUniqSet` (liveDieRead live) + rsLiveAcross = rsLiveEntry `minusUFM` (liveDieRead live) -- regs live on entry to the next instruction. -- be careful of orphans, make sure to delete dying regs _after_ unioning -- in the ones that are born here. - rsLiveNext = (rsLiveAcross `unionUniqSets` (liveBorn live)) - `minusUniqSet` (liveDieWrite live) + rsLiveNext = (rsLiveAcross `plusUFM` (liveBorn live)) + `minusUFM` (liveDieWrite live) -- orphan vregs are the ones that die in the same instruction they are born in. -- these are likely to be results that are never used, but we still -- need to assign a hreg to them.. - rsOrphans = intersectUniqSets + rsOrphans = intersectUFM (liveBorn live) - (unionUniqSets (liveDieWrite live) (liveDieRead live)) + (plusUFM (liveDieWrite live) (liveDieRead live)) -- - rsConflicts = unionUniqSets rsLiveNext rsOrphans + rsConflicts = plusUFM rsLiveNext rsOrphans in case takeRegRegMoveInstr instr of Just rr -> slurpLIs rsLiveNext @@ -458,12 +457,12 @@ slurpReloadCoalesce live slurpLI slotMap li -- remember what reg was stored into the slot - | LiveInstr (SPILL reg slot) _ <- li - , slotMap' <- addToUFM slotMap slot reg + | LiveInstr (SPILL reg _cls slot) _ <- li + , slotMap' <- addToUFM slotMap slot reg = return (slotMap', Nothing) -- add an edge between the this reg and the last one stored into the slot - | LiveInstr (RELOAD slot reg) _ <- li + | LiveInstr (RELOAD slot reg _cls) _ <- li = case lookupUFM slotMap slot of Just reg2 | reg /= reg2 -> return (slotMap, Just (reg, reg2)) @@ -572,13 +571,13 @@ stripLiveBlock config (BasicBlock i lis) -- The SPILL/RELOAD cases do not appear to be exercised by our codegens -- - spillNat acc (LiveInstr (SPILL reg slot) _ : instrs) + spillNat acc (LiveInstr (SPILL reg cls slot) _ : instrs) = do delta <- get - spillNat (mkSpillInstr config reg delta slot ++ acc) instrs + spillNat (mkSpillInstr config reg cls delta slot ++ acc) instrs - spillNat acc (LiveInstr (RELOAD slot reg) _ : instrs) + spillNat acc (LiveInstr (RELOAD slot reg cls) _ : instrs) = do delta <- get - spillNat (mkLoadInstr config reg delta slot ++ acc) instrs + spillNat (mkLoadInstr config reg cls delta slot ++ acc) instrs spillNat acc (LiveInstr (Instr instr) _ : instrs) | Just i <- takeDeltaInstr instr @@ -621,9 +620,8 @@ patchEraseLive patchF cmm patchCmm (CmmProc info label live sccs) | LiveInfo static id blockMap mLiveSlots <- info = let - patchRegSet set = mkUniqSet $ map patchF $ nonDetEltsUFM set -- See Note [Unique Determinism and code generation] - blockMap' = mapMap (patchRegSet . getUniqSet) blockMap + blockMap' = mapMap (mapKeysUFM patchF) blockMap info' = LiveInfo static id blockMap' mLiveSlots in CmmProc info' label live $ map patchSCC sccs @@ -652,8 +650,8 @@ patchEraseLive patchF cmm | r1 == r2 = True -- destination reg is never used - | elementOfUniqSet r2 (liveBorn live) - , elementOfUniqSet r2 (liveDieRead live) || elementOfUniqSet r2 (liveDieWrite live) + | elemUFM r2 (liveBorn live) + , elemUFM r2 (liveDieRead live) || elemUFM r2 (liveDieWrite live) = True | otherwise = False @@ -676,11 +674,14 @@ patchRegsLiveInstr patchF li (patchRegsOfInstr instr patchF) (Just live { -- WARNING: have to go via lists here because patchF changes the uniq in the Reg - liveBorn = mapUniqSet patchF $ liveBorn live - , liveDieRead = mapUniqSet patchF $ liveDieRead live - , liveDieWrite = mapUniqSet patchF $ liveDieWrite live }) + liveBorn = mapKeysUFM patchF $ liveBorn live + , liveDieRead = mapKeysUFM patchF $ liveDieRead live + , liveDieWrite = mapKeysUFM patchF $ liveDieWrite live }) -- See Note [Unique Determinism and code generation] +-- SIMD NCG TODO: move this to Unique.FM module +mapKeysUFM :: Uniquable a => (t -> a) -> UniqFM key (t, b) -> UniqFM a (a, b) +mapKeysUFM f m = listToUFM $ map ( \ (r, fmt) -> let r' = f r in (r', (r', fmt)) ) $ nonDetEltsUFM m -------------------------------------------------------------------------------- -- | Convert a NatCmmDecl to a LiveCmmDecl, with liveness information @@ -869,7 +870,7 @@ computeLiveness -> [SCC (LiveBasicBlock instr)] -> ([SCC (LiveBasicBlock instr)], -- instructions annotated with list of registers -- which are "dead after this instruction". - BlockMap RegSet) -- blocks annotated with set of live registers + BlockMap (UniqFM Reg (Reg, Format))) -- blocks annotated with set of live registers -- on entry to the block. computeLiveness platform sccs @@ -884,11 +885,11 @@ computeLiveness platform sccs livenessSCCs :: Instruction instr => Platform - -> BlockMap RegSet + -> BlockMap (UniqFM Reg (Reg, Format)) -> [SCC (LiveBasicBlock instr)] -- accum -> [SCC (LiveBasicBlock instr)] -> ( [SCC (LiveBasicBlock instr)] - , BlockMap RegSet) + , BlockMap (UniqFM Reg (Reg, Format))) livenessSCCs _ blockmap done [] = (done, blockmap) @@ -917,8 +918,8 @@ livenessSCCs platform blockmap done linearLiveness :: Instruction instr - => BlockMap RegSet -> [LiveBasicBlock instr] - -> (BlockMap RegSet, [LiveBasicBlock instr]) + => BlockMap (UniqFM Reg (Reg, Format)) -> [LiveBasicBlock instr] + -> (BlockMap (UniqFM Reg (Reg, Format)), [LiveBasicBlock instr]) linearLiveness = mapAccumL (livenessBlock platform) @@ -926,9 +927,8 @@ livenessSCCs platform blockmap done -- BlockMaps for equality. equalBlockMaps a b = a' == b' - where a' = map f $ mapToList a - b' = map f $ mapToList b - f (key,elt) = (key, nonDetEltsUniqSet elt) + where a' = mapToList a + b' = mapToList b -- See Note [Unique Determinism and code generation] @@ -938,14 +938,14 @@ livenessSCCs platform blockmap done livenessBlock :: Instruction instr => Platform - -> BlockMap RegSet + -> BlockMap (UniqFM Reg (Reg, Format)) -> LiveBasicBlock instr - -> (BlockMap RegSet, LiveBasicBlock instr) + -> (BlockMap (UniqFM Reg (Reg, Format)), LiveBasicBlock instr) livenessBlock platform blockmap (BasicBlock block_id instrs) = let (regsLiveOnEntry, instrs1) - = livenessBack platform emptyUniqSet blockmap [] (reverse instrs) + = livenessBack platform emptyUFM blockmap [] (reverse instrs) blockmap' = mapInsert block_id regsLiveOnEntry blockmap instrs2 = livenessForward platform regsLiveOnEntry instrs1 @@ -960,7 +960,7 @@ livenessBlock platform blockmap (BasicBlock block_id instrs) livenessForward :: Instruction instr => Platform - -> RegSet -- regs live on this instr + -> UniqFM Reg (Reg, Format) -- regs live on this instr -> [LiveInstr instr] -> [LiveInstr instr] livenessForward _ _ [] = [] @@ -970,12 +970,14 @@ livenessForward platform rsLiveEntry (li@(LiveInstr instr mLive) : lis) RU _ written = regUsageOfInstr platform instr -- Regs that are written to but weren't live on entry to this instruction -- are recorded as being born here. - rsBorn = mkUniqSet - $ filter (\r -> not $ elementOfUniqSet r rsLiveEntry) written + rsBorn = listToUFM + $ map ( \ ( r, fmt ) -> ( r, ( r, fmt ) ) ) + $ filter (\( r, _) -> not $ elemUFM r rsLiveEntry) + $ written - rsLiveNext = (rsLiveEntry `unionUniqSets` rsBorn) - `minusUniqSet` (liveDieRead live) - `minusUniqSet` (liveDieWrite live) + rsLiveNext = (rsLiveEntry `plusUFM` rsBorn) + `minusUFM` (liveDieRead live) + `minusUFM` (liveDieWrite live) in LiveInstr instr (Just live { liveBorn = rsBorn }) : livenessForward platform rsLiveNext lis @@ -990,11 +992,11 @@ livenessForward platform rsLiveEntry (li@(LiveInstr instr mLive) : lis) livenessBack :: Instruction instr => Platform - -> RegSet -- regs live on this instr - -> BlockMap RegSet -- regs live on entry to other BBs + -> UniqFM Reg (Reg, Format) -- regs live on this instr + -> BlockMap (UniqFM Reg (Reg, Format)) -- regs live on entry to other BBs -> [LiveInstr instr] -- instructions (accum) -> [LiveInstr instr] -- instructions - -> (RegSet, [LiveInstr instr]) + -> (UniqFM Reg (Reg, Format), [LiveInstr instr]) livenessBack _ liveregs _ done [] = (liveregs, done) @@ -1007,10 +1009,10 @@ livenessBack platform liveregs blockmap acc (instr : instrs) liveness1 :: Instruction instr => Platform - -> RegSet - -> BlockMap RegSet + -> UniqFM Reg (Reg, Format) + -> BlockMap (UniqFM Reg (Reg, Format)) -> LiveInstr instr - -> (RegSet, LiveInstr instr) + -> (UniqFM Reg (Reg, Format), LiveInstr instr) liveness1 _ liveregs _ (LiveInstr instr _) | isMetaInstr instr @@ -1021,15 +1023,15 @@ liveness1 platform liveregs blockmap (LiveInstr instr _) | not_a_branch = (liveregs1, LiveInstr instr (Just $ Liveness - { liveBorn = emptyUniqSet + { liveBorn = emptyUFM , liveDieRead = r_dying , liveDieWrite = w_dying })) | otherwise = (liveregs_br, LiveInstr instr (Just $ Liveness - { liveBorn = emptyUniqSet - , liveDieRead = mkUniqSet r_dying_br + { liveBorn = emptyUFM + , liveDieRead = r_dying_br , liveDieWrite = w_dying })) where @@ -1037,18 +1039,18 @@ liveness1 platform liveregs blockmap (LiveInstr instr _) -- registers that were written here are dead going backwards. -- registers that were read here are live going backwards. - liveregs1 = (liveregs `delListFromUniqSet` written) - `addListToUniqSet` read + liveregs1 = (liveregs `delListFromUFM` (map fst written)) + `addListToUFM` (map (\(r, fmt) -> (r, (r,fmt))) read) -- registers that are not live beyond this point, are recorded -- as dying here. - r_dying = mkUniqSet - [ reg | reg <- read, reg `notElem` written, - not (elementOfUniqSet reg liveregs) ] + r_dying = listToUFM + [ (reg, (reg, fmt)) | (reg, fmt) <- read, reg `notElem` map fst written, + not (elemUFM reg liveregs) ] - w_dying = mkUniqSet - [ reg | reg <- written, - not (elementOfUniqSet reg liveregs) ] + w_dying = listToUFM + [ (reg, (reg, fmt)) | (reg, fmt) <- written, + not (elemUFM reg liveregs) ] -- union in the live regs from all the jump destinations of this -- instruction. @@ -1058,15 +1060,14 @@ liveness1 platform liveregs blockmap (LiveInstr instr _) targetLiveRegs target = case mapLookup target blockmap of Just ra -> ra - Nothing -> emptyRegSet + Nothing -> emptyUFM - live_from_branch = unionManyUniqSets (map targetLiveRegs targets) + live_from_branch = plusUFMList (map targetLiveRegs targets) - liveregs_br = liveregs1 `unionUniqSets` live_from_branch + liveregs_br = liveregs1 `plusUFM` live_from_branch -- registers that are live only in the branch targets should -- be listed as dying here. - live_branch_only = live_from_branch `minusUniqSet` liveregs - r_dying_br = nonDetEltsUniqSet (r_dying `unionUniqSets` - live_branch_only) + live_branch_only = live_from_branch `minusUFM` liveregs + r_dying_br = r_dying `plusUFM` live_branch_only -- See Note [Unique Determinism and code generation] ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -380,6 +380,8 @@ data Instr | VSHUFPS Format Imm Operand Reg | SHUFPD Format Imm Operand Reg | VSHUFPD Format Imm Operand Reg + -- SIMD NCG TODO: don't store the Format (or only what we need) + -- in order to emit these instructions. -- Shift | PSLLDQ Format Operand Reg @@ -401,129 +403,129 @@ data FMAPermutation = FMA132 | FMA213 | FMA231 regUsageOfInstr :: Platform -> Instr -> RegUsage regUsageOfInstr platform instr = case instr of - MOV _ src dst -> usageRW src dst - CMOV _ _ src dst -> mkRU (use_R src [dst]) [dst] - MOVZxL _ src dst -> usageRW src dst - MOVSxL _ src dst -> usageRW src dst - LEA _ src dst -> usageRW src dst - ADD _ src dst -> usageRM src dst - ADC _ src dst -> usageRM src dst - SUB _ src dst -> usageRM src dst - SBB _ src dst -> usageRM src dst - IMUL _ src dst -> usageRM src dst + MOV fmt src dst -> usageRW fmt src dst + CMOV _ fmt src dst -> mkRU fmt (use_R src [dst]) [dst] + MOVZxL fmt src dst -> usageRW fmt src dst + MOVSxL fmt src dst -> usageRW fmt src dst + LEA fmt src dst -> usageRW fmt src dst + ADD fmt src dst -> usageRM fmt src dst + ADC fmt src dst -> usageRM fmt src dst + SUB fmt src dst -> usageRM fmt src dst + SBB fmt src dst -> usageRM fmt src dst + IMUL fmt src dst -> usageRM fmt src dst -- Result of IMULB will be in just in %ax - IMUL2 II8 src -> mkRU (eax:use_R src []) [eax] + IMUL2 II8 src -> mkRU II8 (eax:use_R src []) [eax] -- Result of IMUL for wider values, will be split between %dx/%edx/%rdx and -- %ax/%eax/%rax. - IMUL2 _ src -> mkRU (eax:use_R src []) [eax,edx] - - MUL _ src dst -> usageRM src dst - MUL2 _ src -> mkRU (eax:use_R src []) [eax,edx] - DIV _ op -> mkRU (eax:edx:use_R op []) [eax,edx] - IDIV _ op -> mkRU (eax:edx:use_R op []) [eax,edx] - ADD_CC _ src dst -> usageRM src dst - SUB_CC _ src dst -> usageRM src dst - AND _ src dst -> usageRM src dst - OR _ src dst -> usageRM src dst - - XOR _ (OpReg src) (OpReg dst) - | src == dst -> mkRU [] [dst] - - XOR _ src dst -> usageRM src dst - NOT _ op -> usageM op - BSWAP _ reg -> mkRU [reg] [reg] - NEGI _ op -> usageM op - SHL _ imm dst -> usageRM imm dst - SAR _ imm dst -> usageRM imm dst - SHR _ imm dst -> usageRM imm dst - SHLD _ imm dst1 dst2 -> usageRMM imm dst1 dst2 - SHRD _ imm dst1 dst2 -> usageRMM imm dst1 dst2 - BT _ _ src -> mkRUR (use_R src []) - - PUSH _ op -> mkRUR (use_R op []) - POP _ op -> mkRU [] (def_W op) - TEST _ src dst -> mkRUR (use_R src $! use_R dst []) - CMP _ src dst -> mkRUR (use_R src $! use_R dst []) - SETCC _ op -> mkRU [] (def_W op) - JXX _ _ -> mkRU [] [] - JXX_GBL _ _ -> mkRU [] [] - JMP op regs -> mkRUR (use_R op regs) - JMP_TBL op _ _ _ -> mkRUR (use_R op []) - CALL (Left _) params -> mkRU params (callClobberedRegs platform) - CALL (Right reg) params -> mkRU (reg:params) (callClobberedRegs platform) - CLTD _ -> mkRU [eax] [edx] - NOP -> mkRU [] [] - - X87Store _ dst -> mkRUR ( use_EA dst []) - - CVTSS2SD src dst -> mkRU [src] [dst] - CVTSD2SS src dst -> mkRU [src] [dst] - CVTTSS2SIQ _ src dst -> mkRU (use_R src []) [dst] - CVTTSD2SIQ _ src dst -> mkRU (use_R src []) [dst] - CVTSI2SS _ src dst -> mkRU (use_R src []) [dst] - CVTSI2SD _ src dst -> mkRU (use_R src []) [dst] - FDIV _ src dst -> usageRM src dst - SQRT _ src dst -> mkRU (use_R src []) [dst] - - FETCHGOT reg -> mkRU [] [reg] - FETCHPC reg -> mkRU [] [reg] + IMUL2 fmt src -> mkRU fmt (eax:use_R src []) [eax,edx] + + MUL fmt src dst -> usageRM fmt src dst + MUL2 fmt src -> mkRU fmt (eax:use_R src []) [eax,edx] + DIV fmt op -> mkRU fmt (eax:edx:use_R op []) [eax,edx] + IDIV fmt op -> mkRU fmt (eax:edx:use_R op []) [eax,edx] + ADD_CC fmt src dst -> usageRM fmt src dst + SUB_CC fmt src dst -> usageRM fmt src dst + AND fmt src dst -> usageRM fmt src dst + OR fmt src dst -> usageRM fmt src dst + + XOR fmt (OpReg src) (OpReg dst) + | src == dst -> mkRU fmt [] [dst] + + XOR fmt src dst -> usageRM fmt src dst + NOT fmt op -> usageM fmt op + BSWAP fmt reg -> mkRU fmt [reg] [reg] + NEGI fmt op -> usageM fmt op + SHL fmt imm dst -> usageRM fmt imm dst + SAR fmt imm dst -> usageRM fmt imm dst + SHR fmt imm dst -> usageRM fmt imm dst + SHLD fmt imm dst1 dst2 -> usageRMM fmt imm dst1 dst2 + SHRD fmt imm dst1 dst2 -> usageRMM fmt imm dst1 dst2 + BT fmt _ src -> mkRUR fmt (use_R src []) + + PUSH fmt op -> mkRUR fmt (use_R op []) + POP fmt op -> mkRU fmt [] (def_W op) + TEST fmt src dst -> mkRUR fmt (use_R src $! use_R dst []) + CMP fmt src dst -> mkRUR fmt (use_R src $! use_R dst []) + SETCC _ op -> mkRU II64 [] (def_W op) + JXX _ _ -> mkRU II64 [] [] + JXX_GBL _ _ -> mkRU II64 [] [] + JMP op regs -> mkRUR II64 (use_R op regs) + JMP_TBL op _ _ _ -> mkRUR II64 (use_R op []) + CALL (Left _) params -> mkRU II64 params (callClobberedRegs platform) + CALL (Right reg) params -> mkRU II64 (reg:params) (callClobberedRegs platform) + CLTD _ -> mkRU II64 [eax] [edx] + NOP -> mkRU II64 [] [] + + X87Store fmt dst -> mkRUR fmt ( use_EA dst []) + + CVTSS2SD src dst -> mkRU FF64 [src] [dst] + CVTSD2SS src dst -> mkRU FF32 [src] [dst] + CVTTSS2SIQ _ src dst -> mkRU FF32 (use_R src []) [dst] + CVTTSD2SIQ _ src dst -> mkRU FF64 (use_R src []) [dst] + CVTSI2SS _ src dst -> mkRU FF32 (use_R src []) [dst] + CVTSI2SD _ src dst -> mkRU FF64 (use_R src []) [dst] + FDIV fmt src dst -> usageRM fmt src dst + SQRT fmt src dst -> mkRU fmt (use_R src []) [dst] + + FETCHGOT reg -> mkRU II64 [] [reg] + FETCHPC reg -> mkRU II64 [] [reg] COMMENT _ -> noUsage LOCATION{} -> noUsage UNWIND{} -> noUsage DELTA _ -> noUsage - POPCNT _ src dst -> mkRU (use_R src []) [dst] - LZCNT _ src dst -> mkRU (use_R src []) [dst] - TZCNT _ src dst -> mkRU (use_R src []) [dst] - BSF _ src dst -> mkRU (use_R src []) [dst] - BSR _ src dst -> mkRU (use_R src []) [dst] + POPCNT fmt src dst -> mkRU fmt (use_R src []) [dst] + LZCNT fmt src dst -> mkRU fmt (use_R src []) [dst] + TZCNT fmt src dst -> mkRU fmt (use_R src []) [dst] + BSF fmt src dst -> mkRU fmt (use_R src []) [dst] + BSR fmt src dst -> mkRU fmt (use_R src []) [dst] - PDEP _ src mask dst -> mkRU (use_R src $ use_R mask []) [dst] - PEXT _ src mask dst -> mkRU (use_R src $ use_R mask []) [dst] + PDEP fmt src mask dst -> mkRU fmt (use_R src $ use_R mask []) [dst] + PEXT fmt src mask dst -> mkRU fmt (use_R src $ use_R mask []) [dst] - FMA3 _ _ _ src3 src2 dst -> usageFMA src3 src2 dst + FMA3 fmt _ _ src3 src2 dst -> usageFMA fmt src3 src2 dst -- note: might be a better way to do this - PREFETCH _ _ src -> mkRU (use_R src []) [] + PREFETCH _ fmt src -> mkRU fmt (use_R src []) [] LOCK i -> regUsageOfInstr platform i - XADD _ src dst -> usageMM src dst - CMPXCHG _ src dst -> usageRMM src dst (OpReg eax) - XCHG _ src dst -> usageMM src (OpReg dst) + XADD fmt src dst -> usageMM fmt src dst + CMPXCHG fmt src dst -> usageRMM fmt src dst (OpReg eax) + XCHG fmt src dst -> usageMM fmt src (OpReg dst) MFENCE -> noUsage -- vector instructions - VBROADCAST _ src dst -> mkRU (use_EA src []) [dst] - VEXTRACT _ off src dst -> mkRU ((use_R off []) ++ [src]) (use_R dst []) - INSERTPS _ off src dst - -> mkRU ((use_R off []) ++ (use_R src []) ++ [dst]) [dst] - - VMOVU _ src dst -> mkRU (use_R src []) (use_R dst []) - MOVU _ src dst -> mkRU (use_R src []) (use_R dst []) - MOVL _ src dst -> mkRU (use_R src []) (use_R dst []) - MOVH _ src dst -> mkRU (use_R src []) (use_R dst []) - VPXOR _ s1 s2 dst -> mkRU [s1,s2] [dst] - - VADD _ s1 s2 dst -> mkRU ((use_R s1 []) ++ [s2]) [dst] - VSUB _ s1 s2 dst -> mkRU ((use_R s1 []) ++ [s2]) [dst] - VMUL _ s1 s2 dst -> mkRU ((use_R s1 []) ++ [s2]) [dst] - VDIV _ s1 s2 dst -> mkRU ((use_R s1 []) ++ [s2]) [dst] - - VPSHUFD _ _off src dst - -> mkRU (use_R src []) [dst] - PSHUFD _ _off src dst - -> mkRU (use_R src []) [dst] - SHUFPD _ _off src dst - -> mkRU (use_R src [dst]) [dst] - SHUFPS _ _off src dst - -> mkRU (use_R src [dst]) [dst] - VSHUFPD _ _off src dst - -> mkRU (use_R src [dst]) [dst] - VSHUFPS _ _off src dst - -> mkRU (use_R src [dst]) [dst] - - PSLLDQ _ off dst -> mkRU (use_R off []) [dst] + VBROADCAST fmt src dst -> mkRU fmt (use_EA src []) [dst] + VEXTRACT fmt off src dst -> mkRU fmt ((use_R off []) ++ [src]) (use_R dst []) + INSERTPS fmt off src dst + -> mkRU fmt ((use_R off []) ++ (use_R src []) ++ [dst]) [dst] + + VMOVU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) + MOVU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) + MOVL fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) + MOVH fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) + VPXOR fmt s1 s2 dst -> mkRU fmt [s1,s2] [dst] + + VADD fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] + VSUB fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] + VMUL fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] + VDIV fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] + + VPSHUFD fmt _off src dst + -> mkRU fmt (use_R src []) [dst] + PSHUFD fmt _off src dst + -> mkRU fmt (use_R src []) [dst] + SHUFPD fmt _off src dst + -> mkRU fmt (use_R src [dst]) [dst] + SHUFPS fmt _off src dst + -> mkRU fmt (use_R src [dst]) [dst] + VSHUFPD fmt _off src dst + -> mkRU fmt (use_R src [dst]) [dst] + VSHUFPS fmt _off src dst + -> mkRU fmt (use_R src [dst]) [dst] + + PSLLDQ fmt off dst -> mkRU fmt (use_R off []) [dst] _other -> panic "regUsage: unrecognised instr" where @@ -537,44 +539,44 @@ regUsageOfInstr platform instr -- are read. -- 2 operand form; first operand Read; second Written - usageRW :: Operand -> Operand -> RegUsage - usageRW op (OpReg reg) = mkRU (use_R op []) [reg] - usageRW op (OpAddr ea) = mkRUR (use_R op $! use_EA ea []) - usageRW _ _ = panic "X86.RegInfo.usageRW: no match" + usageRW :: Format -> Operand -> Operand -> RegUsage + usageRW fmt op (OpReg reg) = mkRU fmt (use_R op []) [reg] + usageRW fmt op (OpAddr ea) = mkRUR fmt (use_R op $! use_EA ea []) + usageRW _ _ _ = panic "X86.RegInfo.usageRW: no match" -- 2 operand form; first operand Read; second Modified - usageRM :: Operand -> Operand -> RegUsage - usageRM op (OpReg reg) = mkRU (use_R op [reg]) [reg] - usageRM op (OpAddr ea) = mkRUR (use_R op $! use_EA ea []) - usageRM _ _ = panic "X86.RegInfo.usageRM: no match" + usageRM :: Format -> Operand -> Operand -> RegUsage + usageRM fmt op (OpReg reg) = mkRU fmt (use_R op [reg]) [reg] + usageRM fmt op (OpAddr ea) = mkRUR fmt (use_R op $! use_EA ea []) + usageRM _ _ _ = panic "X86.RegInfo.usageRM: no match" -- 2 operand form; first operand Modified; second Modified - usageMM :: Operand -> Operand -> RegUsage - usageMM (OpReg src) (OpReg dst) = mkRU [src, dst] [src, dst] - usageMM (OpReg src) (OpAddr ea) = mkRU (use_EA ea [src]) [src] - usageMM (OpAddr ea) (OpReg dst) = mkRU (use_EA ea [dst]) [dst] - usageMM _ _ = panic "X86.RegInfo.usageMM: no match" + usageMM :: Format -> Operand -> Operand -> RegUsage + usageMM fmt (OpReg src) (OpReg dst) = mkRU fmt [src, dst] [src, dst] + usageMM fmt (OpReg src) (OpAddr ea) = mkRU fmt (use_EA ea [src]) [src] + usageMM fmt (OpAddr ea) (OpReg dst) = mkRU fmt (use_EA ea [dst]) [dst] + usageMM _ _ _ = panic "X86.RegInfo.usageMM: no match" -- 3 operand form; first operand Read; second Modified; third Modified - usageRMM :: Operand -> Operand -> Operand -> RegUsage - usageRMM (OpReg src) (OpReg dst) (OpReg reg) = mkRU [src, dst, reg] [dst, reg] - usageRMM (OpReg src) (OpAddr ea) (OpReg reg) = mkRU (use_EA ea [src, reg]) [reg] - usageRMM _ _ _ = panic "X86.RegInfo.usageRMM: no match" + usageRMM :: Format -> Operand -> Operand -> Operand -> RegUsage + usageRMM fmt (OpReg src) (OpReg dst) (OpReg reg) = mkRU fmt [src, dst, reg] [dst, reg] + usageRMM fmt (OpReg src) (OpAddr ea) (OpReg reg) = mkRU fmt (use_EA ea [src, reg]) [reg] + usageRMM _ _ _ _ = panic "X86.RegInfo.usageRMM: no match" -- 3 operand form of FMA instructions. - usageFMA :: Operand -> Reg -> Reg -> RegUsage - usageFMA (OpReg src1) src2 dst - = mkRU [src1, src2, dst] [dst] - usageFMA (OpAddr ea1) src2 dst - = mkRU (use_EA ea1 [src2, dst]) [dst] - usageFMA _ _ _ + usageFMA :: Format -> Operand -> Reg -> Reg -> RegUsage + usageFMA fmt (OpReg src1) src2 dst + = mkRU fmt [src1, src2, dst] [dst] + usageFMA fmt (OpAddr ea1) src2 dst + = mkRU fmt (use_EA ea1 [src2, dst]) [dst] + usageFMA _ _ _ _ = panic "X86.RegInfo.usageFMA: no match" -- 1 operand form; operand Modified - usageM :: Operand -> RegUsage - usageM (OpReg reg) = mkRU [reg] [reg] - usageM (OpAddr ea) = mkRUR (use_EA ea []) - usageM _ = panic "X86.RegInfo.usageM: no match" + usageM :: Format -> Operand -> RegUsage + usageM fmt (OpReg reg) = mkRU fmt [reg] [reg] + usageM fmt (OpAddr ea) = mkRUR fmt (use_EA ea []) + usageM _ _ = panic "X86.RegInfo.usageM: no match" -- Registers defd when an operand is written. def_W (OpReg reg) = [reg] @@ -595,10 +597,11 @@ regUsageOfInstr platform instr use_index EAIndexNone tl = tl use_index (EAIndex i _) tl = i : tl - mkRUR src = src' `seq` RU src' [] + mkRUR fmt src = src' `seq` RU (map (,fmt) src') [] where src' = filter (interesting platform) src - mkRU src dst = src' `seq` dst' `seq` RU src' dst' + + mkRU fmt src dst = src' `seq` dst' `seq` RU (map (,fmt) src') (map (,fmt) dst') where src' = filter (interesting platform) src dst' = filter (interesting platform) dst @@ -817,18 +820,27 @@ patchJumpInstr insn patchF mkSpillInstr :: NCGConfig -> Reg -- register to spill + -> Format -> Int -- current stack delta -> Int -- spill slot to use -> [Instr] -mkSpillInstr config reg delta slot - = let off = spillSlotToOffset platform slot - delta - in - case targetClassOfReg platform reg of - RcInteger -> [MOV (archWordFormat is32Bit) - (OpReg reg) (OpAddr (spRel platform off))] - RcDouble -> [MOV FF64 (OpReg reg) (OpAddr (spRel platform off))] - _ -> panic "X86.mkSpillInstr: no match" +mkSpillInstr config reg fmt delta slot + = let off s = spillSlotToOffset platform s - delta + in case fmt of + IntegerFormat -> [MOV (archWordFormat is32Bit) + (OpReg reg) (OpAddr (spRel platform $ off slot))] + FF64 -> [MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off slot))] + FF32 -> panic "X86_mkSpillInstr: RcFloat" + VecFormat {} -> + -- SIMD NCG TODO: panic for unsupported VecFormats (& same in mkLoadInstr) + [MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off slot)) + -- Now shuffle the register, putting the high half into the lower half. + ,SHUFPD (VecFormat 2 FmtDouble W64) (ImmInt 0b01) (OpReg reg) reg + -- NB: this format doesn't matter, we emit the same instruction + -- regardless of what is stored... + -- SIMD NCG TODO: avoid using MOV by using SHUFPD with an OpAddr argument? + ,MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off (slot + 1)))] where platform = ncgPlatform config is32Bit = target32Bit platform @@ -836,18 +848,23 @@ mkSpillInstr config reg delta slot mkLoadInstr :: NCGConfig -> Reg -- register to load + -> Format -> Int -- current stack delta -> Int -- spill slot to use -> [Instr] -mkLoadInstr config reg delta slot - = let off = spillSlotToOffset platform slot - delta +mkLoadInstr config reg fmt delta slot + = let off s = spillSlotToOffset platform s - delta in - case targetClassOfReg platform reg of - RcInteger -> ([MOV (archWordFormat is32Bit) - (OpAddr (spRel platform off)) (OpReg reg)]) - RcDouble -> ([MOV FF64 (OpAddr (spRel platform off)) (OpReg reg)]) - _ -> panic "X86.mkLoadInstr" + case fmt of + IntegerFormat -> ([MOV (archWordFormat is32Bit) + (OpAddr (spRel platform $ off slot)) (OpReg reg)]) + FF64 -> ([MOV FF64 (OpAddr (spRel platform $ off slot)) (OpReg reg)]) + FF32 -> panic "X86.mkLoadInstr RcFloat" + VecFormat {} -> + [MOVH (VecFormat 2 FmtDouble W64) (OpAddr (spRel platform $ off (slot + 1))) (OpReg reg) + ,MOVL (VecFormat 2 FmtDouble W64) (OpAddr (spRel platform $ off slot)) (OpReg reg)] + where platform = ncgPlatform config is32Bit = target32Bit platform ===================================== compiler/GHC/Platform/Reg.hs ===================================== @@ -116,17 +116,12 @@ renameVirtualReg u r classOfVirtualReg :: VirtualReg -> RegClass classOfVirtualReg vr - = case vr of + = case vr of VirtualRegI{} -> RcInteger VirtualRegHi{} -> RcInteger VirtualRegF{} -> RcFloat VirtualRegD{} -> RcDouble - -- Below is an awful, largely x86-specific hack - VirtualRegVec{} -> RcDouble - -- SIMD NCG TODO: this seems very wrong and potentially the source of - -- bug #16927, because we use this function to determine how to spill - -- the contents of a virtual register - -- (see e.g. GHC.CmmToAsm.X86.Instr.mkSpillInstr). + VirtualRegVec{} -> RcVector128 -- Determine the upper-half vreg for a 64-bit quantity on a 32-bit platform ===================================== compiler/GHC/Platform/Reg/Class.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE LambdaCase #-} -- | An architecture independent description of a register's class. module GHC.Platform.Reg.Class ( RegClass (..) @@ -18,21 +19,26 @@ import GHC.Builtin.Uniques -- We treat all registers in a class as being interchangeable. -- data RegClass - = RcInteger - | RcFloat - | RcDouble - deriving (Eq, Show) + = RcInteger + | RcFloat + | RcDouble + | RcVector128 + deriving (Eq, Ord, Show) allRegClasses :: [RegClass] allRegClasses = - [RcInteger, RcFloat, RcDouble] + [ RcInteger, RcFloat, RcDouble, RcVector128 ] instance Uniquable RegClass where - getUnique RcInteger = mkRegClassUnique 0 - getUnique RcFloat = mkRegClassUnique 1 - getUnique RcDouble = mkRegClassUnique 2 + getUnique = \case + RcInteger -> mkRegClassUnique 0 + RcFloat -> mkRegClassUnique 1 + RcDouble -> mkRegClassUnique 2 + RcVector128 -> mkRegClassUnique 3 instance Outputable RegClass where - ppr RcInteger = Outputable.text "I" - ppr RcFloat = Outputable.text "F" - ppr RcDouble = Outputable.text "D" + ppr = \case + RcInteger -> Outputable.text "I" + RcFloat -> Outputable.text "F" + RcDouble -> Outputable.text "D" + RcVector128 -> Outputable.text "V" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b2ca03a3e8080aa16efbab292bab7716bcf27dd3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b2ca03a3e8080aa16efbab292bab7716bcf27dd3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 16:59:18 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 06 Jun 2024 12:59:18 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] SIMD NCG: accept simd006 Message-ID: <6661eae663b77_167afa36103c861c5@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 02bfe63c by sheaf at 2024-06-06T18:58:59+02:00 SIMD NCG: accept simd006 - - - - - 2 changed files: - testsuite/tests/codeGen/should_run/simd006.hs - + testsuite/tests/codeGen/should_run/simd006.stdout Changes: ===================================== testsuite/tests/codeGen/should_run/simd006.hs ===================================== @@ -127,15 +127,17 @@ instance Arbitrary Word32 where newtype FloatNT = FloatNT Float deriving newtype (Show, Num) instance Eq FloatNT where - FloatNT f1 == FloatNT f2 = - castFloatToWord32 f1 == castFloatToWord32 f2 + FloatNT f1 == FloatNT f2 = f1 == f2 + -- TODO: tests fail with this equality due to signed zeros + -- castFloatToWord32 f1 == castFloatToWord32 f2 instance Arbitrary FloatNT where arbitrary = FloatNT . castWord32ToFloat <$> arbitrary newtype DoubleNT = DoubleNT Double deriving newtype (Show, Num) instance Eq DoubleNT where - DoubleNT d1 == DoubleNT d2 = - castDoubleToWord64 d1 == castDoubleToWord64 d2 + DoubleNT d1 == DoubleNT d2 = d1 == d2 + -- TODO: tests fail with this equality due to signed zeros + -- castDoubleToWord64 d1 == castDoubleToWord64 d2 instance Arbitrary DoubleNT where arbitrary = DoubleNT . castWord64ToDouble <$> arbitrary ===================================== testsuite/tests/codeGen/should_run/simd006.stdout ===================================== @@ -0,0 +1,7 @@ +Group ALL + Group FloatX4 + Running FloatX4 + Passed 100 iterations + Group DoubleX2 + Running DoubleX2 + Passed 100 iterations View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/02bfe63c095424d1cdcd7498ce7978538f95d4b0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/02bfe63c095424d1cdcd7498ce7978538f95d4b0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 18:08:04 2024 From: gitlab at gitlab.haskell.org (Torsten Schmits (@torsten.schmits)) Date: Thu, 06 Jun 2024 14:08:04 -0400 Subject: [Git][ghc/ghc][wip/torsten.schmits/cross-package-objects] load modules recursively Message-ID: <6661fb047ad8c_167afa959e08923f9@gitlab.mail> Torsten Schmits pushed to branch wip/torsten.schmits/cross-package-objects at Glasgow Haskell Compiler / GHC Commits: 32fba601 by Torsten Schmits at 2024-06-06T20:07:54+02:00 load modules recursively - - - - - 6 changed files: - compiler/GHC/Linker/Loader.hs - + testsuite/tests/th/cross-package/CrossDepApi.hs - testsuite/tests/th/cross-package/CrossLocal.hs - testsuite/tests/th/cross-package/all.T - testsuite/tests/th/cross-package/dep.conf - testsuite/tests/th/cross-package/prep.bash Changes: ===================================== compiler/GHC/Linker/Loader.hs ===================================== @@ -111,13 +111,11 @@ import System.Win32.Info (getSystemDirectory) import GHC.Utils.Exception import GHC.Unit.Module.ModIface (ModIface, ModIface_ (..)) -import GHC.Unit.Module.ModDetails (ModDetails (..)) import GHC.Unit.Finder (FindResult(..), findImportedModule) -import qualified GHC.Data.Maybe as ME import GHC.Unit.Module.ModSummary (ModSummary(..)) import GHC.Unit.Module.WholeCoreBindings (WholeCoreBindings(..)) import GHC.Types.PkgQual (PkgQual(OtherPkg)) -import Control.Monad.Trans.State.Strict (StateT(..)) +import Control.Monad.Trans.State.Strict (StateT(..), state) import GHC.Utils.Misc (modificationTimeIfExists) -- Note [Linkers and loaders] @@ -239,7 +237,10 @@ loadDependencies interp hsc_env pls hydrate span needed_mods = do -- Find what packages and linkables are required deps <- getLinkDeps opts interp pls span needed_mods - (pls1, links_needed) <- loadIfacesByteCode interp hsc_env hydrate pls (ldNeededLinkables deps) + let s0 = LIBC {libc_loader = pls, libc_seen = emptyUniqDSet} + needed = ldNeededLinkables deps + load_bc = loadIfacesByteCode interp hsc_env hydrate needed + (links_needed, LIBC {libc_loader = pls1}) <- runStateT load_bc s0 let this_pkgs_needed = ldNeededUnits deps @@ -725,31 +726,43 @@ loadByteCode loc iface mod_sum = do return (Just (LM if_date this_mod [CoreBindings fi])) _ -> pure Nothing +data LIBC = + LIBC { + libc_loader :: LoaderState, + libc_seen :: UniqDSet Module + } + loadIfaceByteCode :: Interp -> HscEnv -> (ModIface -> Linkable -> IO Linkable) -> - LoaderState -> Module -> - IO ([Linkable], LoaderState) -loadIfaceByteCode interp hsc_env hydrate pls mod = do - iface <- run_ifg $ loadSysInterface (text "blarkh") mod - imp_mod <- findImportedModule hsc_env (moduleName mod) (OtherPkg (moduleUnitId mod)) + StateT LIBC IO [Linkable] +loadIfaceByteCode interp hsc_env hydrate mod = do + iface <- liftIO $ run_ifg $ loadSysInterface (text "blarkh") mod + imp_mod <- liftIO $ findImportedModule hsc_env (moduleName mod) (OtherPkg (moduleUnitId mod)) dbg "loadIfaceByteCode" [ ("mod", ppr mod), ("iface", ppr (mi_module iface)) ] case imp_mod of (Found loc _) -> do - summ <- mod_summary mod loc iface - l <- loadByteCode loc iface summ - lh <- maybeToList <$> traverse (hydrate iface) l - dbg "loadIfaceByteCode found" [("hi", text (ml_hi_file loc)), ("loaded", ppr lh)] - pls1 <- dynLinkBCOs interp pls lh - pure (lh, pls1) + summ <- liftIO $ mod_summary mod loc iface + l <- liftIO $ loadByteCode loc iface summ + lh <- liftIO $ maybeToList <$> traverse (hydrate iface) l + lh1 <- loadIfacesByteCode interp hsc_env hydrate lh + dbg "loadIfaceByteCode found" [ + ("hi", text (ml_hi_file loc)), + ("loaded", ppr lh), + ("loaded recursive", ppr lh1) + ] + StateT $ \ s -> do + pls <- dynLinkBCOs interp (libc_loader s) lh1 + pure ((), s {libc_loader = pls}) + pure lh1 fr -> do dbg "loadIfaceByteCode not found" [("impo", debugFr fr)] - pure ([], pls) + pure [] where run_ifg :: forall a . IfG a -> IO a run_ifg = initIfaceCheck (text "loader") hsc_env @@ -770,30 +783,34 @@ loadIfacesByteCode :: Interp -> HscEnv -> (ModIface -> Linkable -> IO Linkable) -> - LoaderState -> [Linkable] -> - IO (LoaderState, [Linkable]) -loadIfacesByteCode interp hsc_env hydrate pls lnks = do - (lnks1, pls1) <- runStateT (traverse one mods) pls - pure (pls1, mconcat (lnks : lnks1)) + StateT LIBC IO [Linkable] +loadIfacesByteCode interp hsc_env hydrate lnks = do + all <- state (filter_deps all_deps) + lnks1 <- traverse one (uniqDSetToList all) + pure (mconcat (lnks : lnks1)) where - one :: Module -> StateT LoaderState IO [Linkable] - one a = StateT (\ s -> loadIfaceByteCode interp hsc_env hydrate s a) - mods :: [Module] - mods = mconcat (bco_deps . linkableUnlinked <$> lnks) + one :: Module -> StateT LIBC IO [Linkable] + one = loadIfaceByteCode interp hsc_env hydrate + + all_deps = linkables_deps (concatMap linkableUnlinked lnks) + + linkables_deps = unionManyUniqDSets . fmap linkable_deps + + linkable_deps = \case + BCOs cbc _ -> + mapUniqDSet nameModule $ filterUniqDSet loadable (bco_free_names cbc) + LoadedBCOs l -> linkables_deps l + _ -> emptyUniqDSet + + loadable n = isExternalName n && not (isWiredInName n) && not (moduleUnitId (nameModule n) `elem` wiredInUnitIds) + bco_free_names cbc = - uniqDSetToList $ foldr (unionUniqDSets . bcoFreeNames) emptyUniqDSet (bc_bcos cbc) - bco_deps = concatMap $ \case - BCOs cbc _ -> - [ - nameModule n | - n <- bco_free_names cbc, - isExternalName n, - not (isWiredInName n) - ] - _ -> [] + filter_deps new s at LIBC {libc_seen} = + (minusUniqDSet new libc_seen, s {libc_seen = unionUniqDSets new libc_seen}) + loadDecls :: Interp -> ===================================== testsuite/tests/th/cross-package/CrossDepApi.hs ===================================== @@ -0,0 +1,7 @@ +module CrossDepApi (A (A), dep) where + +import CrossDep (A (A)) +import qualified CrossDep + +dep :: A +dep = CrossDep.dep ===================================== testsuite/tests/th/cross-package/CrossLocal.hs ===================================== @@ -5,7 +5,7 @@ module CrossLocal where import Language.Haskell.TH (ExpQ) import Language.Haskell.TH.Syntax (lift) -- just to be sure that the file isn't accidentally picked up locally -import "dep" CrossDep (dep, A (A)) +import "dep" CrossDepApi (dep, A (A)) import CrossNum (num) splc :: ExpQ ===================================== testsuite/tests/th/cross-package/all.T ===================================== @@ -2,7 +2,7 @@ test( 'CrossPackage', [ pre_cmd('$MAKE -s --no-print-directory CrossPackage'), - extra_files(['Cross.hs', 'CrossLocal.hs', 'CrossDep.hs', 'CrossNum.hs', 'prep.bash', 'dep.conf']), + extra_files(['Cross.hs', 'CrossLocal.hs', 'CrossDep.hs', 'CrossDepApi.hs', 'CrossNum.hs', 'prep.bash', 'dep.conf']), # ignore_stderr, ], # multimod_compile_and_run, ===================================== testsuite/tests/th/cross-package/dep.conf ===================================== @@ -3,7 +3,7 @@ version: 1.0 id: dep-1.0 key: dep-1.0 exposed: True -exposed-modules: CrossDep +exposed-modules: CrossDep CrossDepApi import-dirs: ${pkgroot}/dep library-dirs: ${pkgroot}/dep hs-libraries: HSdep-1.0 ===================================== testsuite/tests/th/cross-package/prep.bash ===================================== @@ -22,11 +22,13 @@ ghc() } mkdir -p "$lib" "$db" -cp CrossDep.hs dep.conf "$lib/" +mv CrossDep.hs CrossDepApi.hs dep.conf "$lib/" ghc_pkg recache -ghc "-package-db ${db at Q} -hidir ${lib at Q} -O0 -this-unit-id dep-1.0 -fbyte-code-and-object-code -c ${lib at Q}/CrossDep.hs" -$AR cqs "${lib}/libHSdep-1.0.a" "${lib}/CrossDep.o" +ghc "-package-db ${db at Q} -hidir ${lib at Q} -O0 -this-unit-id dep-1.0 -fbyte-code-and-object-code -c ${lib at Q}/CrossDep.hs ${lib at Q}/CrossDepApi.hs" +$AR cqs "${lib}/libHSdep-1.0.a" "${lib}/CrossDep.o" "${lib}/CrossDepApi.o" ghc_pkg -v0 register "${lib at Q}/dep.conf" + +tree >&2 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/32fba6015863cba2538d8a995fe63bd3563ae5cb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/32fba6015863cba2538d8a995fe63bd3563ae5cb You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 19:09:47 2024 From: gitlab at gitlab.haskell.org (Torsten Schmits (@torsten.schmits)) Date: Thu, 06 Jun 2024 15:09:47 -0400 Subject: [Git][ghc/ghc][wip/torsten.schmits/cross-package-objects] 2 commits: load from unexposed modules as well Message-ID: <6662097b5d250_a0b5d38e7f811030@gitlab.mail> Torsten Schmits pushed to branch wip/torsten.schmits/cross-package-objects at Glasgow Haskell Compiler / GHC Commits: 254e81e3 by Torsten Schmits at 2024-06-06T20:27:45+02:00 load from unexposed modules as well - - - - - b2c0184c by Torsten Schmits at 2024-06-06T21:07:32+02:00 refactorings - - - - - 2 changed files: - compiler/GHC/Linker/Loader.hs - testsuite/tests/th/cross-package/dep.conf Changes: ===================================== compiler/GHC/Linker/Loader.hs ===================================== @@ -90,6 +90,7 @@ import GHC.Linker.Types -- Standard libraries import Control.Monad +import Control.Monad.Trans.Class (lift) import qualified Data.Set as Set import Data.Char (isSpace) @@ -111,10 +112,9 @@ import System.Win32.Info (getSystemDirectory) import GHC.Utils.Exception import GHC.Unit.Module.ModIface (ModIface, ModIface_ (..)) -import GHC.Unit.Finder (FindResult(..), findImportedModule) +import GHC.Unit.Finder (findExactModule, InstalledFindResult (..)) import GHC.Unit.Module.ModSummary (ModSummary(..)) import GHC.Unit.Module.WholeCoreBindings (WholeCoreBindings(..)) -import GHC.Types.PkgQual (PkgQual(OtherPkg)) import Control.Monad.Trans.State.Strict (StateT(..), state) import GHC.Utils.Misc (modificationTimeIfExists) @@ -237,10 +237,15 @@ loadDependencies interp hsc_env pls hydrate span needed_mods = do -- Find what packages and linkables are required deps <- getLinkDeps opts interp pls span needed_mods + + -- Load bytecode from interface files in the package db let s0 = LIBC {libc_loader = pls, libc_seen = emptyUniqDSet} - needed = ldNeededLinkables deps - load_bc = loadIfacesByteCode interp hsc_env hydrate needed - (links_needed, LIBC {libc_loader = pls1}) <- runStateT load_bc s0 + handlers = libc_handlers interp hsc_env hydrate + load_bc = loadIfacesByteCode handlers (ldNeededLinkables deps) + + (links_needed, LIBC {libc_loader = pls1}) <- + initIfaceCheck (text "loader") hsc_env $ + runStateT load_bc s0 let this_pkgs_needed = ldNeededUnits deps @@ -732,67 +737,87 @@ data LIBC = libc_seen :: UniqDSet Module } -loadIfaceByteCode :: +data LIBCHandlers = + LIBCHandlers { + libc_find :: Module -> IO InstalledFindResult, + libc_hydrate :: ModIface -> Linkable -> IO Linkable, + libc_link :: forall m . MonadIO m => [Linkable] -> StateT LIBC m () + } + +libc_handlers :: Interp -> HscEnv -> (ModIface -> Linkable -> IO Linkable) -> + LIBCHandlers +libc_handlers interp hsc_env libc_hydrate = + LIBCHandlers {libc_find, libc_hydrate, libc_link} + where + unit_state = hsc_units hsc_env + fc = hsc_FC hsc_env + mhome_unit = Nothing + -- This would search in the home unit as well, but we don't need to load + -- core bindings for that. + -- mhome_unit = hsc_home_unit_maybe hsc_env + dflags = hsc_dflags hsc_env + fopts = initFinderOpts dflags + other_fopts = initFinderOpts . homeUnitEnv_dflags <$> (hsc_HUG hsc_env) + + libc_find mod = + findExactModule fc fopts other_fopts unit_state mhome_unit + (mkModule (moduleUnitId mod) (moduleName mod)) + + libc_link :: forall m . MonadIO m => [Linkable] -> StateT LIBC m () + libc_link linkables = StateT $ \ s -> do + pls <- liftIO $ dynLinkBCOs interp (libc_loader s) linkables + pure ((), s {libc_loader = pls}) + +loadIfaceByteCode :: + LIBCHandlers -> Module -> - StateT LIBC IO [Linkable] -loadIfaceByteCode interp hsc_env hydrate mod = do - iface <- liftIO $ run_ifg $ loadSysInterface (text "blarkh") mod - imp_mod <- liftIO $ findImportedModule hsc_env (moduleName mod) (OtherPkg (moduleUnitId mod)) + StateT LIBC IfG [Linkable] +loadIfaceByteCode handlers at LIBCHandlers {..} mod = do + iface <- lift $ loadSysInterface load_doc mod + find_res <- liftIO (libc_find mod) dbg "loadIfaceByteCode" [ ("mod", ppr mod), ("iface", ppr (mi_module iface)) ] - case imp_mod of - (Found loc _) -> do + case find_res of + (InstalledFound loc _) -> do summ <- liftIO $ mod_summary mod loc iface l <- liftIO $ loadByteCode loc iface summ - lh <- liftIO $ maybeToList <$> traverse (hydrate iface) l - lh1 <- loadIfacesByteCode interp hsc_env hydrate lh + lh <- liftIO $ maybeToList <$> traverse (libc_hydrate iface) l + lh1 <- loadIfacesByteCode handlers lh dbg "loadIfaceByteCode found" [ ("hi", text (ml_hi_file loc)), ("loaded", ppr lh), ("loaded recursive", ppr lh1) ] - StateT $ \ s -> do - pls <- dynLinkBCOs interp (libc_loader s) lh1 - pure ((), s {libc_loader = pls}) + libc_link lh1 pure lh1 - fr -> do - dbg "loadIfaceByteCode not found" [("impo", debugFr fr)] + result -> do + dbg "loadIfaceByteCode not found" [("result", debugFr result)] pure [] where - run_ifg :: forall a . IfG a -> IO a - run_ifg = initIfaceCheck (text "loader") hsc_env + load_doc = text "Loading core bindings of splice dependencies" debugFr = \case - Found _ _ -> text "found" - NoPackage u -> text "NoPackage " <+> ppr u - FoundMultiple _ -> text "FoundMultiple" - NotFound {..} -> vcat [ - text "paths:" <+> brackets (hsep (text <$> fr_paths)), - text "pkg:" <+> ppr fr_pkg, - text "fr_mods_hidden:" <+> ppr fr_mods_hidden, - text "fr_pkgs_hidden:" <+> ppr fr_pkgs_hidden, - text "fr_unusables:" <+> ppr (ModUnusable <$> fr_unusables) + InstalledFound _ _ -> text "found" + InstalledNoPackage u -> text "NoPackage " <+> ppr u + InstalledNotFound paths pkg -> vcat [ + text "paths:" <+> brackets (hsep (text <$> paths)), + text "pkg:" <+> ppr pkg ] loadIfacesByteCode :: - Interp -> - HscEnv -> - (ModIface -> Linkable -> IO Linkable) -> + LIBCHandlers -> [Linkable] -> - StateT LIBC IO [Linkable] -loadIfacesByteCode interp hsc_env hydrate lnks = do + StateT LIBC IfG [Linkable] +loadIfacesByteCode handlers lnks = do all <- state (filter_deps all_deps) - lnks1 <- traverse one (uniqDSetToList all) + lnks1 <- traverse (loadIfaceByteCode handlers) (uniqDSetToList all) pure (mconcat (lnks : lnks1)) where - one :: Module -> StateT LIBC IO [Linkable] - one = loadIfaceByteCode interp hsc_env hydrate - all_deps = linkables_deps (concatMap linkableUnlinked lnks) linkables_deps = unionManyUniqDSets . fmap linkable_deps @@ -803,7 +828,10 @@ loadIfacesByteCode interp hsc_env hydrate lnks = do LoadedBCOs l -> linkables_deps l _ -> emptyUniqDSet - loadable n = isExternalName n && not (isWiredInName n) && not (moduleUnitId (nameModule n) `elem` wiredInUnitIds) + loadable n = + isExternalName n && + not (isWiredInName n) && + not (moduleUnitId (nameModule n) `elem` wiredInUnitIds) bco_free_names cbc = foldr (unionUniqDSets . bcoFreeNames) emptyUniqDSet (bc_bcos cbc) ===================================== testsuite/tests/th/cross-package/dep.conf ===================================== @@ -3,7 +3,7 @@ version: 1.0 id: dep-1.0 key: dep-1.0 exposed: True -exposed-modules: CrossDep CrossDepApi +exposed-modules: CrossDepApi import-dirs: ${pkgroot}/dep library-dirs: ${pkgroot}/dep hs-libraries: HSdep-1.0 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/32fba6015863cba2538d8a995fe63bd3563ae5cb...b2c0184ca764e2e5b1d77acad7374cd2f8ec79f0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/32fba6015863cba2538d8a995fe63bd3563ae5cb...b2c0184ca764e2e5b1d77acad7374cd2f8ec79f0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 20:59:44 2024 From: gitlab at gitlab.haskell.org (Adam Gundry (@adamgundry)) Date: Thu, 06 Jun 2024 16:59:44 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/amg/module-cycle-error Message-ID: <666223404e469_a0b5defd05828244@gitlab.mail> Adam Gundry pushed new branch wip/amg/module-cycle-error at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/amg/module-cycle-error You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 21:05:49 2024 From: gitlab at gitlab.haskell.org (Adam Gundry (@adamgundry)) Date: Thu, 06 Jun 2024 17:05:49 -0400 Subject: [Git][ghc/ghc][wip/amg/module-cycle-error] Use structured error representation for module cycle errors (see #18516) Message-ID: <666224ad9f362_a0b5dfb5aa42842a@gitlab.mail> Adam Gundry pushed to branch wip/amg/module-cycle-error at Glasgow Haskell Compiler / GHC Commits: 4bc002ce by Adam Gundry at 2024-06-06T23:05:40+02:00 Use structured error representation for module cycle errors (see #18516) This removes the re-export of cyclicModuleErr from the top-level GHC module. - - - - - 10 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Errors/Ppr.hs - compiler/GHC/Driver/Errors/Types.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Types/Error/Codes.hs - testsuite/tests/backpack/should_fail/bkpfail51.stderr - testsuite/tests/driver/T20459.stderr - testsuite/tests/driver/T24196/T24196.stderr - testsuite/tests/driver/T24275/T24275.stderr Changes: ===================================== compiler/GHC.hs ===================================== @@ -285,11 +285,8 @@ module GHC ( parser, -- * API Annotations - AnnKeywordId(..),EpaComment(..), - - -- * Miscellaneous - --sessionHscEnv, - cyclicModuleErr, + AnnKeywordId(..), + EpaComment(..) ) where {- ===================================== compiler/GHC/Driver/Errors/Ppr.hs ===================================== @@ -20,7 +20,10 @@ import GHC.Types.Error import GHC.Types.Error.Codes import GHC.Unit.Types import GHC.Utils.Outputable +import GHC.Utils.Panic import GHC.Unit.Module +import GHC.Unit.Module.Graph +import GHC.Unit.Module.ModSummary import GHC.Unit.State import GHC.Types.Hint import GHC.Types.SrcLoc @@ -238,6 +241,30 @@ instance Diagnostic DriverMessage where -> mkSimpleDecorated $ text $ "unrecognised warning flag: -" ++ arg DriverDeprecatedFlag arg msg -> mkSimpleDecorated $ text $ arg ++ " is deprecated: " ++ msg + DriverModuleGraphCycle path + -> mkSimpleDecorated $ vcat + [ text "Module graph contains a cycle:" + , nest 2 (show_path path) ] + where + show_path :: [ModuleGraphNode] -> SDoc + show_path [] = panic "show_path" + show_path [m] = ppr_node m <+> text "imports itself" + show_path (m1:m2:ms) = vcat ( nest 14 (ppr_node m1) + : nest 6 (text "imports" <+> ppr_node m2) + : go ms ) + where + go [] = [text "which imports" <+> ppr_node m1] + go (m:ms) = (text "which imports" <+> ppr_node m) : go ms + + ppr_node :: ModuleGraphNode -> SDoc + ppr_node (ModuleNode _deps m) = text "module" <+> ppr_ms m + ppr_node (InstantiationNode _uid u) = text "instantiated unit" <+> ppr u + ppr_node (LinkNode uid _) = pprPanic "LinkNode should not be in a cycle" (ppr uid) + + ppr_ms :: ModSummary -> SDoc + ppr_ms ms = quotes (ppr (moduleName (ms_mod ms))) <+> + (parens (text (msHsFilePath ms))) + diagnosticReason = \case DriverUnknownMessage m @@ -303,6 +330,8 @@ instance Diagnostic DriverMessage where -> WarningWithFlag Opt_WarnUnrecognisedWarningFlags DriverDeprecatedFlag {} -> WarningWithFlag Opt_WarnDeprecatedFlags + DriverModuleGraphCycle {} + -> ErrorWithoutFlag diagnosticHints = \case DriverUnknownMessage m @@ -370,5 +399,7 @@ instance Diagnostic DriverMessage where -> noHints DriverDeprecatedFlag {} -> noHints + DriverModuleGraphCycle {} + -> noHints diagnosticCode = constructorCode ===================================== compiler/GHC/Driver/Errors/Types.hs ===================================== @@ -28,6 +28,7 @@ import GHC.Driver.DynFlags (DynFlags, PackageArg, gopt) import GHC.Driver.Flags (GeneralFlag (Opt_BuildingCabalPackage)) import GHC.Types.Error import GHC.Unit.Module +import GHC.Unit.Module.Graph import GHC.Unit.State import GHC.Parser.Errors.Types ( PsMessage(PsHeaderMessage) ) @@ -384,6 +385,18 @@ data DriverMessage where DriverDeprecatedFlag :: String -> String -> DriverMessage + {- | DriverModuleGraphCycle is an error that occurs if the module graph + contains cyclic imports. + + Test cases: + tests/backpack/should_fail/bkpfail51 + tests/driver/T20459 + tests/driver/T24196/T24196 + tests/driver/T24275/T24275 + + -} + DriverModuleGraphCycle :: [ModuleGraphNode] -> DriverMessage + deriving instance Generic DriverMessage data DriverMessageOpts = ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -1264,9 +1264,7 @@ upsweep n_jobs hsc_env hmi_cache diag_wrapper mHscMessage old_hpt build_plan = d -- of the upsweep. case cycle of Just mss -> do - let logger = hsc_logger hsc_env - liftIO $ fatalErrorMsg logger (cyclicModuleErr mss) - return (Failed, []) + cyclicModuleErr mss Nothing -> do let success_flag = successIf (all isJust res) return (success_flag, completed) @@ -2387,16 +2385,18 @@ multiRootsErr summs@(summ1:_) mod = ms_mod summ1 files = map (expectJust "checkDup" . ml_hs_file . ms_location) summs -cyclicModuleErr :: [ModuleGraphNode] -> SDoc +cyclicModuleErr :: [ModuleGraphNode] -> IO a -- From a strongly connected component we find -- a single cycle to report cyclicModuleErr mss = assert (not (null mss)) $ case findCycle graph of - Nothing -> text "Unexpected non-cycle" <+> ppr mss - Just path0 -> vcat - [ text "Module graph contains a cycle:" - , nest 2 (show_path path0)] + Nothing -> pprPanic "Unexpected non-cycle" (ppr mss) + Just path -> throwOneError $ mkPlainErrorMsgEnvelope src_span + $ GhcDriverMessage + $ DriverModuleGraphCycle path + where + src_span = maybe noSrcSpan (mkFileSrcSpan . ms_location) (moduleGraphNodeModSum (head path)) where graph :: [Node NodeKey ModuleGraphNode] graph = @@ -2408,24 +2408,11 @@ cyclicModuleErr mss | ms <- mss ] - show_path :: [ModuleGraphNode] -> SDoc - show_path [] = panic "show_path" - show_path [m] = ppr_node m <+> text "imports itself" - show_path (m1:m2:ms) = vcat ( nest 14 (ppr_node m1) - : nest 6 (text "imports" <+> ppr_node m2) - : go ms ) - where - go [] = [text "which imports" <+> ppr_node m1] - go (m:ms) = (text "which imports" <+> ppr_node m) : go ms - - ppr_node :: ModuleGraphNode -> SDoc - ppr_node (ModuleNode _deps m) = text "module" <+> ppr_ms m - ppr_node (InstantiationNode _uid u) = text "instantiated unit" <+> ppr u - ppr_node (LinkNode uid _) = pprPanic "LinkNode should not be in a cycle" (ppr uid) - - ppr_ms :: ModSummary -> SDoc - ppr_ms ms = quotes (ppr (moduleName (ms_mod ms))) <+> - (parens (text (msHsFilePath ms))) +mkFileSrcSpan :: ModLocation -> SrcSpan +mkFileSrcSpan mod_loc + = case ml_hs_file mod_loc of + Just file_path -> mkGeneralSrcSpan (mkFastString file_path) + Nothing -> interactiveSrcSpan -- Presumably cleanCurrentModuleTempFilesMaybe :: MonadIO m => Logger -> TmpFs -> DynFlags -> m () ===================================== compiler/GHC/Driver/MakeFile.hs ===================================== @@ -16,6 +16,7 @@ where import GHC.Prelude import qualified GHC +import GHC.Driver.Make import GHC.Driver.Monad import GHC.Driver.DynFlags import GHC.Driver.Ppr @@ -209,10 +210,9 @@ processDeps :: DynFlags -- -- For {-# SOURCE #-} imports the "hi" will be "hi-boot". -processDeps dflags _ _ _ _ (CyclicSCC nodes) +processDeps _ _ _ _ _ (CyclicSCC nodes) = -- There shouldn't be any cycles; report them - throwGhcExceptionIO $ ProgramError $ - showSDoc dflags $ GHC.cyclicModuleErr nodes + cyclicModuleErr nodes processDeps dflags _ _ _ _ (AcyclicSCC (InstantiationNode _uid node)) = -- There shouldn't be any backpack instantiations; report them as well ===================================== compiler/GHC/Types/Error/Codes.hs ===================================== @@ -318,6 +318,7 @@ type family GhcDiagnosticCode c = n | n -> c where GhcDiagnosticCode "DriverPackageTrustIgnored" = 83552 GhcDiagnosticCode "DriverUnrecognisedFlag" = 93741 GhcDiagnosticCode "DriverDeprecatedFlag" = 53692 + GhcDiagnosticCode "DriverModuleGraphCycle" = 92213 -- Constraint solver diagnostic codes GhcDiagnosticCode "BadTelescope" = 97739 ===================================== testsuite/tests/backpack/should_fail/bkpfail51.stderr ===================================== @@ -2,7 +2,9 @@ [1 of 2] Compiling H[sig] ( p/H.hsig, nothing ) [2 of 2] Compiling I ( p/I.hs, nothing ) [2 of 2] Processing q -Module graph contains a cycle: - instantiated unit p[H=A] - imports module ‘A’ (q/A.hsig) - which imports instantiated unit p[H=A] +: error: [GHC-92213] + Module graph contains a cycle: + instantiated unit p[H=] + imports module ‘A’ (q/A.hsig) + which imports instantiated unit p[H=] + ===================================== testsuite/tests/driver/T20459.stderr ===================================== @@ -1,2 +1,4 @@ -Module graph contains a cycle: - module ‘T20459A’ (./T20459A.hs) imports itself +./T20459A.hs: error: [GHC-92213] + Module graph contains a cycle: + module ‘T20459A’ (./T20459A.hs) imports itself + ===================================== testsuite/tests/driver/T24196/T24196.stderr ===================================== @@ -1,4 +1,6 @@ -Module graph contains a cycle: - module ‘T24196A’ (./T24196A.hs-boot) - imports module ‘T24196B’ (T24196B.hs) - which imports module ‘T24196A’ (./T24196A.hs-boot) +./T24196A.hs-boot: error: [GHC-92213] + Module graph contains a cycle: + module ‘T24196A’ (./T24196A.hs-boot) + imports module ‘T24196B’ (T24196B.hs) + which imports module ‘T24196A’ (./T24196A.hs-boot) + ===================================== testsuite/tests/driver/T24275/T24275.stderr ===================================== @@ -1,4 +1,6 @@ -Module graph contains a cycle: - module ‘T24275A’ (./T24275A.hs-boot) - imports module ‘T24275B’ (T24275B.hs) - which imports module ‘T24275A’ (./T24275A.hs-boot) +./T24275A.hs-boot: error: [GHC-92213] + Module graph contains a cycle: + module ‘T24275A’ (./T24275A.hs-boot) + imports module ‘T24275B’ (T24275B.hs) + which imports module ‘T24275A’ (./T24275A.hs-boot) + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4bc002ce5df8aca903ed0c5c8988fdb217f0f8ac -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4bc002ce5df8aca903ed0c5c8988fdb217f0f8ac You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 21:27:15 2024 From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim)) Date: Thu, 06 Jun 2024 17:27:15 -0400 Subject: [Git][ghc/ghc][wip/representation-polymorphic-flip] 35 commits: Migrate `Finder` component to `OsPath`, fixed #24616 Message-ID: <666229b34f828_a0b5d126b7e433967@gitlab.mail> Bodigrim pushed to branch wip/representation-polymorphic-flip at Glasgow Haskell Compiler / GHC Commits: c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - f9fd1fc3 by Andrew Lelechenko at 2024-06-06T22:27:05+01:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 30 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - compiler/GHC.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - + compiler/GHC/Data/OsPath.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Driver/Config/Finder.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Driver/Pipeline/Execute.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/de647cb8941d56fa94e0be22108d419013e2173c...f9fd1fc3a09e6d8b02f72d90212f8b00a7b9abf8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/de647cb8941d56fa94e0be22108d419013e2173c...f9fd1fc3a09e6d8b02f72d90212f8b00a7b9abf8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 6 23:18:24 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Thu, 06 Jun 2024 19:18:24 -0400 Subject: [Git][ghc/ghc][wip/T24676] Respond to Richard's review Message-ID: <666243c06d4f8_a0b5d2007fd83715a@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24676 at Glasgow Haskell Compiler / GHC Commits: 6afa552f by Simon Peyton Jones at 2024-06-07T00:18:05+01:00 Respond to Richard's review - - - - - 4 changed files: - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -43,7 +43,6 @@ import GHC.Core.DataCon ( dataConConcreteTyVars, isNewDataCon, dataConTyCon ) import GHC.Core.TyCon import GHC.Core.TyCo.Rep import GHC.Core.TyCo.Ppr -import GHC.Core.TyCo.FVs ( shallowTyCoVarsOfType ) import GHC.Core.TyCo.Subst ( substTyWithInScope ) import GHC.Core.Type import GHC.Core.Coercion @@ -58,7 +57,6 @@ import GHC.Types.Name.Env import GHC.Types.Name.Reader import GHC.Types.SrcLoc import GHC.Types.Var.Env ( emptyTidyEnv, mkInScopeSet ) -import GHC.Types.Var.Set import GHC.Data.Maybe @@ -103,7 +101,7 @@ Some notes relative to the paper (QL3) When QL is done, we turn the instantiation variables into ordinary unification variables, using qlZonkTcType. This function fully zonks the type (thereby - revealing all the polytypes, and updates any instantaition variables with + revealing all the polytypes), and updates any instantiation variables with ordinary unification variables. See Note [Instantiation variables are short lived]. @@ -118,9 +116,11 @@ Note [Instantiation variables are short lived] * Ordinary unifcation variables always stand for monotypes; only instantiation variables can be unified with a polytype (by `qlUnify`). -* By the time QL is done, all filled-in occurrences of instantiation variables - have been zonked away with `zonkTcType` (see "Crucial step" in tcValArgs). - +* When we start typechecking the argments of the call, in tcValArgs, we will + (a) monomorphise any un-filled-in instantiation variables + (see Note [Monomorphise instantiation variables]) + (b) zonk the argument type to reveal any polytypes before typechecking that + argument (see calls to `zonkTcType` and "Crucial step" in tcValArg).. See Section 4.3 "Applications and instantiation" of the paper. * The constraint solver never sees an instantiation variable [not quite true; @@ -522,6 +522,7 @@ tcValArg _ (EPrag l p) = return (EPrag l (tcExprPrag p)) tcValArg _ (ETypeArg l hty ty) = return (ETypeArg l hty ty) tcValArg do_ql (EWrap (EHsWrap w)) = do { whenQL do_ql $ qlMonoHsWrapper w ; return (EWrap (EHsWrap w)) } + -- qlMonoHsWrapper: see Note [Monomorphise instantiation variables] tcValArg _ (EWrap ew) = return (EWrap ew) tcValArg do_ql (EValArg { ea_ctxt = ctxt @@ -608,17 +609,6 @@ quickLookKeys :: [Unique] -- See Note [Quick Look for particular Ids] quickLookKeys = [dollarIdKey, leftSectionKey, rightSectionKey] -{- --- zonkArg is used *only* during debug-tracing, to make it easier to --- see what is going on. For that reason, it is not a full zonk: add --- more if you need it. -zonkArg :: HsExprArg 'TcpInst -> ZonkM (HsExprArg 'TcpInst) -zonkArg eva@(EValArg { ea_arg_ty = Scaled m ty }) - = do { ty' <- zonkTcType ty - ; return (eva { ea_arg_ty = Scaled m ty' }) } -zonkArg arg = return arg --} - {- ********************************************************************* * * Instantiating the call @@ -1576,7 +1566,7 @@ This turned out to be more subtle than I expected. Wrinkles: quick-look-arg judgement APP-QL are satisfied; this is captured in `arg_influences_enclosing_call`. -(QLA1) We avoid zonking, so the `arg_influences_enclosing_call` sees the +(QLA2) We avoid zonking, so the `arg_influences_enclosing_call` sees the argument type /before/ the QL substitution Theta is applied to it. So we achieve argument-order independence for free (see 5.7 in the paper). See the `isGuardedTy orig_arg_rho` test in `quickLookArg`. @@ -1598,7 +1588,13 @@ This turned out to be more subtle than I expected. Wrinkles: - Calling `tcInstFun` on the argument may have emitted some constraints, which we carefully captured in `quickLookArg` and stored in the EValArgQL. We must - now emit them with `emitConstraints`. + now emit them with `emitConstraints`. This must be done /under/ the skolemisation + of the argument's type (see `tcSkolemise` in `tcValArg` for EValArgQL { ...}. + Example: f :: (forall b. Ord b => b -> b -> Bool) -> ... + Call: f (==) + we must skolemise the argument type (forall b. Ord b => b -> b -> Bool) + before emitting the [W] Eq alpha constraint arising from the call to (==). + It will be solved from the Ord b! - quickLookArg may or may not have done `qlUnify` with the calling context. If not (eaql_encl = False) must do so now. Example: choose [] ids, @@ -1753,6 +1749,11 @@ See `qlMonoHsWrapper`. By going left to right, we are sure to monomorphise instantiation variables before we encounter them in an argument type (in `tcValArg`). +All instantiation variables for a call will be reachable from the type(s) +at which the function is instantiated -- i.e. those WpTyApps. Even instantiation +variables allocoated by tcInstFun itself, such as in the IRESULT rule, end up +connected to the original type(s) at which the function is instantiated. + To monomorphise the free QL instantiation variables of a type, we use `foldQLInstVars`. @@ -1772,11 +1773,13 @@ Wrinkles: -} qlMonoHsWrapper :: HsWrapper -> ZonkM () +-- See Note [Monomorphise instantiation variables] qlMonoHsWrapper (WpCompose w1 w2) = qlMonoHsWrapper w1 >> qlMonoHsWrapper w2 qlMonoHsWrapper (WpTyApp ty) = qlMonoTcType ty qlMonoHsWrapper _ = return () qlMonoTcType :: TcType -> ZonkM () +-- See Note [Monomorphise instantiation variables] qlMonoTcType ty = do { traceZonk "monomorphiseQLInstVars {" (ppr ty) ; go_ty ty @@ -1856,6 +1859,7 @@ foldQLInstVars check_tv ty folder :: TyCoFolder () a folder = TyCoFolder { tcf_view = noView -- See Note [Free vars and synonyms] + -- in GHC.Core.TyCo.FVs , tcf_tyvar = do_tv, tcf_covar = mempty , tcf_hole = do_hole, tcf_tycobinder = do_bndr } @@ -1876,106 +1880,98 @@ foldQLInstVars check_tv ty qlUnify :: TcType -> TcType -> TcM () -- Unify ty1 with ty2: --- * It unifies /only/ instantiation variables; --- it /never/ unifies ordinary unification variables +-- * It unifies /only/ instantiation variables. +-- It does not itself unify ordinary unification variables, +-- although it calls unifyKind which can do so. (It'd be ok for it to +-- unify ordinary unification variables, subject to the usual checks.) -- * It never produces errors, even for mis-matched types -- * It does not return a coercion (unlike unifyType); it is called -- for the sole purpose of unifying instantiation variables -- * It may return without having made the argument types equal, of course; -- it just makes best efforts. qlUnify ty1 ty2 - = go (emptyVarSet,emptyVarSet) ty1 ty2 + = go ty1 ty2 where - go :: (TyVarSet, TcTyVarSet) - -> TcType -> TcType + go :: TcType -> TcType -> TcM () -- The TyVarSets give the variables bound by enclosing foralls -- for the corresponding type. Don't unify with these. - go bvs (TyVarTy tv) ty2 - | isQLInstTyVar tv = go_kappa bvs tv ty2 + go (TyVarTy tv) ty2 + | isQLInstTyVar tv = go_kappa tv ty2 -- Only unify QL instantiation variables -- See (UQL3) in Note [QuickLook unification] - go (bvs1, bvs2) ty1 (TyVarTy tv) - | isQLInstTyVar tv = go_kappa (bvs2,bvs1) tv ty1 + go ty1 (TyVarTy tv) + | isQLInstTyVar tv = go_kappa tv ty1 - go bvs (CastTy ty1 _) ty2 = go bvs ty1 ty2 - go bvs ty1 (CastTy ty2 _) = go bvs ty1 ty2 + go (CastTy ty1 _) ty2 = go ty1 ty2 + go ty1 (CastTy ty2 _) = go ty1 ty2 - go _ (TyConApp tc1 []) (TyConApp tc2 []) + go (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 -- See GHC.Tc.Utils.Unify = return () -- Note [Expanding synonyms during unification] -- Now, and only now, expand synonyms - go bvs rho1 rho2 - | Just rho1 <- coreView rho1 = go bvs rho1 rho2 - | Just rho2 <- coreView rho2 = go bvs rho1 rho2 + go rho1 rho2 + | Just rho1 <- coreView rho1 = go rho1 rho2 + | Just rho2 <- coreView rho2 = go rho1 rho2 - go bvs (TyConApp tc1 tys1) (TyConApp tc2 tys2) + go (TyConApp tc1 tys1) (TyConApp tc2 tys2) | tc1 == tc2 , not (isTypeFamilyTyCon tc1) , tys1 `equalLength` tys2 - = zipWithM_ (go bvs) tys1 tys2 + = zipWithM_ go tys1 tys2 -- Decompose (arg1 -> res1) ~ (arg2 -> res2) -- and (c1 => res1) ~ (c2 => res2) -- But for the latter we only learn instantiation info from res1~res2 -- We look at the multiplicity too, although the chances of getting -- impredicative instantiation info from there seems...remote. - go bvs (FunTy { ft_af = af1, ft_arg = arg1, ft_res = res1, ft_mult = mult1 }) - (FunTy { ft_af = af2, ft_arg = arg2, ft_res = res2, ft_mult = mult2 }) + go (FunTy { ft_af = af1, ft_arg = arg1, ft_res = res1, ft_mult = mult1 }) + (FunTy { ft_af = af2, ft_arg = arg2, ft_res = res2, ft_mult = mult2 }) | af1 == af2 -- Match the arrow TyCon - = do { when (isVisibleFunArg af1) (go bvs arg1 arg2) - ; when (isFUNArg af1) (go bvs mult1 mult2) - ; go bvs res1 res2 } + = do { when (isVisibleFunArg af1) (go arg1 arg2) + ; when (isFUNArg af1) (go mult1 mult2) + ; go res1 res2 } -- ToDo: c.f. Tc.Utils.unify.uType, -- which does not split FunTy here -- Also NB tcSplitAppTyNoView here, which does not split (c => t) - go bvs (AppTy t1a t1b) ty2 + go (AppTy t1a t1b) ty2 | Just (t2a, t2b) <- tcSplitAppTyNoView_maybe ty2 - = do { go bvs t1a t2a; go bvs t1b t2b } + = do { go t1a t2a; go t1b t2b } - go bvs ty1 (AppTy t2a t2b) + go ty1 (AppTy t2a t2b) | Just (t1a, t1b) <- tcSplitAppTyNoView_maybe ty1 - = do { go bvs t1a t2a; go bvs t1b t2b } - - go (bvs1, bvs2) (ForAllTy bv1 ty1) (ForAllTy bv2 ty2) - = go (bvs1',bvs2') ty1 ty2 - where - bvs1' = bvs1 `extendVarSet` binderVar bv1 - bvs2' = bvs2 `extendVarSet` binderVar bv2 + = do { go t1a t2a; go t1b t2b } - go _ _ _ = return () + go _ _ = return () ---------------- - go_kappa bvs kappa ty2 + go_kappa kappa ty2 = assertPpr (isMetaTyVar kappa) (ppr kappa) $ do { info <- readMetaTyVar kappa ; case info of - Indirect ty1 -> go bvs ty1 ty2 + Indirect ty1 -> go ty1 ty2 Flexi -> do { ty2 <- liftZonkM $ zonkTcType ty2 - ; go_flexi bvs kappa ty2 } } + ; go_flexi kappa ty2 } } ---------------- -- Swap (kappa1[conc] ~ kappa2[tau]) -- otherwise we'll fail to unify and emit a coercion. -- Just an optimisation: emitting a coercion is fine - go_flexi bvs kappa (TyVarTy tv2) + go_flexi kappa (TyVarTy tv2) | isQLInstTyVar tv2, lhsPriority tv2 > lhsPriority kappa - = go_flexi1 bvs tv2 (TyVarTy kappa) - go_flexi bvs kappa ty2 - = go_flexi1 bvs kappa ty2 + = go_flexi1 tv2 (TyVarTy kappa) + go_flexi kappa ty2 + = go_flexi1 kappa ty2 - go_flexi1 (_,bvs2) kappa ty2 -- ty2 is zonked + go_flexi1 kappa ty2 -- ty2 is zonked | -- See Note [QuickLook unification] (UQL1) - let ty2_tvs = shallowTyCoVarsOfType ty2 - , not (ty2_tvs `intersectsVarSet` bvs2) - -- Can't instantiate a delta-var to a forall-bound variable - , Just ty2 <- occCheckExpand [kappa] ty2 + Just ty2 <- occCheckExpand [kappa] ty2 -- Passes the occurs check , not (isConcreteTyVar kappa) || isConcreteType ty2 - -- Don't unify a concrete instantiatiation variable with a non-concrete type + -- Don't unify a concrete instantiation variable with a non-concrete type = do { co <- unifyKind (Just (TypeThing ty2)) ty2_kind kappa_kind -- unifyKind: see (UQL2) in Note [QuickLook unification] ; let ty2' = mkCastTy ty2 co @@ -1997,9 +1993,6 @@ That is the entire point of qlUnify! Wrinkles: (UQL1) Before unifying an instantiation variable in `go_flexi`, we must check the usual unification conditions: see `GHC.Tc.Utils.Unify.simpleUnifyCheck` In particular: - * We must not unify with anything bound by an enclosing forall; e.g. - (forall a. kappa -> Int) ~ forall a. a -> Int) - That's tracked by the 'bvs' arg of 'go'. * We must not make an occurs-check; we use occCheckExpand for that. @@ -2020,12 +2013,15 @@ That is the entire point of qlUnify! Wrinkles: no good to unify (kappa := (forall a.blah) |> co) because we can't use that casted polytype. - BUT: the kind-unifer has emitted constraint(s) so we may as well use - them. (An alternative; use uType directly, and discard constraints - if the result is not Refl.) + BUT: unifyKind has emitted constraint(s) into the Tc monad, so we may as well + use them. (An alternative; use uType directly, if the result is not Refl, + discard the constraints and the coercion, and do not update the instantiation + variable.) + +(UQL3) qlUnify (and Quick Look generally) is only unifies instantiation + variables, not regular unification variables. Why? Nothing fundamental. + We would need to -(UQL3) qlUnify (and Quick Look generally) is very careful only to unify - instantiation variables, not regular unification variables. Why? Because instantiation variables don't really have a settled level yet; they have level QLInstVar (see Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. So we should be worried that we might unify ===================================== compiler/GHC/Tc/Utils/Instantiate.hs ===================================== @@ -426,10 +426,12 @@ right here. But note See Note [Let-bound skolems] in GHC.Tc.Solver.InertSet. If we substitute aggressively (including zonking) that abbreviation could work. But - again it affects what is typeable. + again it affects what is typeable. And we don't support equalities over polytypes, + currently, anyway. * There is little point in trying to optimise for - - (s ~# t), because few functions have primitive equalities in their context + - (s ~# t), because this has kind Constraint#, not Constraint, and so will not be + in the theta instantiated in instCalll - (s ~~ t), becaues heterogeneous equality is rare, and more complicated. Anyway, for now we don't take advantage of these potential effects. ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -80,7 +80,7 @@ module GHC.Tc.Utils.TcMType ( defaultTyVar, promoteMetaTyVarTo, promoteTyVarSet, quantifyTyVars, isQuantifiableTv, zonkAndSkolemise, skolemiseQuantifiedTyVar, - doNotQuantifyTyVars, demoteQLDelta, + doNotQuantifyTyVars, candidateQTyVarsOfType, candidateQTyVarsOfKind, candidateQTyVarsOfTypes, candidateQTyVarsOfKinds, @@ -2446,48 +2446,6 @@ promoteTyVarSet tvs -- Non-determinism is OK because order of promotion doesn't matter ; return (or bools) } -demoteDeltaTyVarTo :: TcLevel -> TcTyVar -> TcM () --- See Note [Quick Look at value arguments] wrinkle (QLA4) --- in GHC.Tc.Gen.App -demoteDeltaTyVarTo new_lvl tv - | MetaTv { mtv_ref = ref, mtv_tclvl = tv_lvl } <- tcTyVarDetails tv - = assertPpr (new_lvl `strictlyDeeperThan` tv_lvl) (ppr new_lvl <+> ppr tv) $ - do { info <- readTcRef ref - ; case info of { - Indirect {} -> return () ; -- The instantiation variable has already - -- been filled in; skip entirely - Flexi -> - do { cloned_tv <- cloneMetaTyVar tv - ; let rhs_tv = setMetaTyVarTcLevel cloned_tv new_lvl - ; liftZonkM $ writeTcRef ref (Indirect (TyVarTy rhs_tv)) - -- Do not go via writeMetaTyVar! In debug-mode it makes sanity check - -- on level numbers which /demoting/ deliberately disobeys - ; traceTc "demoteTyVar" (ppr tv <+> text "-->" <+> ppr rhs_tv) - ; return () } } } - | otherwise - = pprPanic "demoteDeltaTyVarTo" (ppr tv) - -demoteQLDelta :: TcTyVarSet -> TcM () --- See Note [Quick Look at value arguments] wrinkle (QLA5) --- in GHC.Tc.Gen.App --- --- Invariant: all elements of delta have the same level (namely --- the level of the original tcApp), so we need only --- check the first one -demoteQLDelta delta - = case tvs of - [] -> return () -- Could panic: we are always called with a non-empty set - (tv1:_) -> do { tclvl <- getTcLevel - ; assertPpr (isMetaTyVar tv1) (ppr delta) $ - when (tclvl `strictlyDeeperThan` tcTyVarLevel tv1) $ - -- This 'when' is just an optimisation - -- See (QLA6) in Note [Quick Look at value arguments] - -- in GHC.Tc.Gen.App. - mapM_ (demoteDeltaTyVarTo tclvl) tvs } - where - tvs = nonDetEltsUniqSet delta - -- Non-determinism is OK because order of demotion doesn't matter - {- %************************************************************************ %* * ===================================== compiler/GHC/Tc/Utils/TcType.hs ===================================== @@ -242,8 +242,6 @@ import Data.IORef ( IORef ) import Data.List.NonEmpty( NonEmpty(..) ) import Data.List ( partition, nub, (\\) ) -import GHC.Exts - {- ************************************************************************ * * @@ -695,7 +693,7 @@ noConcreteTyVars = emptyNameEnv * * ********************************************************************* -} -data TcLevel = TcLevel Int# +data TcLevel = TcLevel {-# UNPACK #-} !Int | QLInstVar -- See Note [TcLevel invariants] for what this Int is -- See also Note [TcLevel assignment] @@ -759,7 +757,7 @@ with a QL instantiation variable, e.g. alpha[tau:3] := Maybe beta[tau:qlinstvar] (This is an immediate consequence of our general rule that we never unify a variable with a type mentioning deeper variables; the skolem -escape check. +escape check.) QL instantation variables are eventually turned into ordinary unificaiton variables; see (QL3) in Note [Quick Look overview]. @@ -813,14 +811,14 @@ touchable; but then 'b' has escaped its scope into the outer implication. -} maxTcLevel :: TcLevel -> TcLevel -> TcLevel -maxTcLevel(TcLevel a) (TcLevel b) - | isTrue# (a ># b) = TcLevel a - | otherwise = TcLevel b -maxTcLevel _ _ = QLInstVar +maxTcLevel (TcLevel a) (TcLevel b) + | a > b = TcLevel a + | otherwise = TcLevel b +maxTcLevel _ _ = QLInstVar minTcLevel :: TcLevel -> TcLevel -> TcLevel minTcLevel tcla@(TcLevel a) tclb@(TcLevel b) - | isTrue# (a <# b) = tcla + | a < b = tcla | otherwise = tclb minTcLevel tcla@(TcLevel {}) QLInstVar = tcla minTcLevel QLInstVar tclb@(TcLevel {}) = tclb @@ -828,34 +826,34 @@ minTcLevel QLInstVar QLInstVar = QLInstVar topTcLevel :: TcLevel -- See Note [TcLevel assignment] -topTcLevel = TcLevel 0# -- 0 = outermost level +topTcLevel = TcLevel 0 -- 0 = outermost level isTopTcLevel :: TcLevel -> Bool -isTopTcLevel (TcLevel 0#) = True +isTopTcLevel (TcLevel 0) = True isTopTcLevel _ = False pushTcLevel :: TcLevel -> TcLevel -- See Note [TcLevel assignment] -pushTcLevel (TcLevel us) = TcLevel (us +# 1#) +pushTcLevel (TcLevel us) = TcLevel (us + 1) pushTcLevel QLInstVar = QLInstVar strictlyDeeperThan :: TcLevel -> TcLevel -> Bool -- See Note [The QLInstVar TcLevel] strictlyDeeperThan (TcLevel tv_tclvl) (TcLevel ctxt_tclvl) - = isTrue# (tv_tclvl ># ctxt_tclvl) + = tv_tclvl > ctxt_tclvl strictlyDeeperThan QLInstVar (TcLevel {}) = True strictlyDeeperThan _ _ = False deeperThanOrSame :: TcLevel -> TcLevel -> Bool -- See Note [The QLInstVar TcLevel] deeperThanOrSame (TcLevel tv_tclvl) (TcLevel ctxt_tclvl) - = isTrue# (tv_tclvl >=# ctxt_tclvl) + = tv_tclvl >= ctxt_tclvl deeperThanOrSame (TcLevel {}) QLInstVar = False deeperThanOrSame QLInstVar _ = True sameDepthAs :: TcLevel -> TcLevel -> Bool sameDepthAs (TcLevel ctxt_tclvl) (TcLevel tv_tclvl) - = isTrue# (ctxt_tclvl ==# tv_tclvl) + = ctxt_tclvl == tv_tclvl -- NB: invariant ctxt_tclvl >= tv_tclvl -- So <= would be equivalent sameDepthAs QLInstVar QLInstVar = True @@ -887,7 +885,7 @@ tcTypeLevel ty | otherwise = lvl instance Outputable TcLevel where - ppr (TcLevel n) = ppr (I# n) + ppr (TcLevel n) = ppr n ppr QLInstVar = text "qlinst" {- ********************************************************************* View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6afa552f643fc4a78e94562234e2f95b0166c19d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6afa552f643fc4a78e94562234e2f95b0166c19d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 05:15:34 2024 From: gitlab at gitlab.haskell.org (Adam Gundry (@adamgundry)) Date: Fri, 07 Jun 2024 01:15:34 -0400 Subject: [Git][ghc/ghc][wip/amg/module-cycle-error] Use structured error representation for module cycle errors (see #18516) Message-ID: <66629776b909_a0b5d4a9b13c41753@gitlab.mail> Adam Gundry pushed to branch wip/amg/module-cycle-error at Glasgow Haskell Compiler / GHC Commits: 153d4029 by Adam Gundry at 2024-06-07T07:15:22+02:00 Use structured error representation for module cycle errors (see #18516) This removes the re-export of cyclicModuleErr from the top-level GHC module. - - - - - 11 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Errors/Ppr.hs - compiler/GHC/Driver/Errors/Types.hs - compiler/GHC/Driver/Make.hs - compiler/GHC/Driver/MakeFile.hs - compiler/GHC/Types/Error/Codes.hs - testsuite/tests/backpack/should_fail/bkpfail51.stderr - testsuite/tests/count-deps/CountDepsParser.stdout - testsuite/tests/driver/T20459.stderr - testsuite/tests/driver/T24196/T24196.stderr - testsuite/tests/driver/T24275/T24275.stderr Changes: ===================================== compiler/GHC.hs ===================================== @@ -285,11 +285,8 @@ module GHC ( parser, -- * API Annotations - AnnKeywordId(..),EpaComment(..), - - -- * Miscellaneous - --sessionHscEnv, - cyclicModuleErr, + AnnKeywordId(..), + EpaComment(..) ) where {- ===================================== compiler/GHC/Driver/Errors/Ppr.hs ===================================== @@ -20,7 +20,10 @@ import GHC.Types.Error import GHC.Types.Error.Codes import GHC.Unit.Types import GHC.Utils.Outputable +import GHC.Utils.Panic import GHC.Unit.Module +import GHC.Unit.Module.Graph +import GHC.Unit.Module.ModSummary import GHC.Unit.State import GHC.Types.Hint import GHC.Types.SrcLoc @@ -238,6 +241,30 @@ instance Diagnostic DriverMessage where -> mkSimpleDecorated $ text $ "unrecognised warning flag: -" ++ arg DriverDeprecatedFlag arg msg -> mkSimpleDecorated $ text $ arg ++ " is deprecated: " ++ msg + DriverModuleGraphCycle path + -> mkSimpleDecorated $ vcat + [ text "Module graph contains a cycle:" + , nest 2 (show_path path) ] + where + show_path :: [ModuleGraphNode] -> SDoc + show_path [] = panic "show_path" + show_path [m] = ppr_node m <+> text "imports itself" + show_path (m1:m2:ms) = vcat ( nest 14 (ppr_node m1) + : nest 6 (text "imports" <+> ppr_node m2) + : go ms ) + where + go [] = [text "which imports" <+> ppr_node m1] + go (m:ms) = (text "which imports" <+> ppr_node m) : go ms + + ppr_node :: ModuleGraphNode -> SDoc + ppr_node (ModuleNode _deps m) = text "module" <+> ppr_ms m + ppr_node (InstantiationNode _uid u) = text "instantiated unit" <+> ppr u + ppr_node (LinkNode uid _) = pprPanic "LinkNode should not be in a cycle" (ppr uid) + + ppr_ms :: ModSummary -> SDoc + ppr_ms ms = quotes (ppr (moduleName (ms_mod ms))) <+> + (parens (text (msHsFilePath ms))) + diagnosticReason = \case DriverUnknownMessage m @@ -303,6 +330,8 @@ instance Diagnostic DriverMessage where -> WarningWithFlag Opt_WarnUnrecognisedWarningFlags DriverDeprecatedFlag {} -> WarningWithFlag Opt_WarnDeprecatedFlags + DriverModuleGraphCycle {} + -> ErrorWithoutFlag diagnosticHints = \case DriverUnknownMessage m @@ -370,5 +399,7 @@ instance Diagnostic DriverMessage where -> noHints DriverDeprecatedFlag {} -> noHints + DriverModuleGraphCycle {} + -> noHints diagnosticCode = constructorCode ===================================== compiler/GHC/Driver/Errors/Types.hs ===================================== @@ -28,6 +28,7 @@ import GHC.Driver.DynFlags (DynFlags, PackageArg, gopt) import GHC.Driver.Flags (GeneralFlag (Opt_BuildingCabalPackage)) import GHC.Types.Error import GHC.Unit.Module +import GHC.Unit.Module.Graph import GHC.Unit.State import GHC.Parser.Errors.Types ( PsMessage(PsHeaderMessage) ) @@ -384,6 +385,18 @@ data DriverMessage where DriverDeprecatedFlag :: String -> String -> DriverMessage + {- | DriverModuleGraphCycle is an error that occurs if the module graph + contains cyclic imports. + + Test cases: + tests/backpack/should_fail/bkpfail51 + tests/driver/T20459 + tests/driver/T24196/T24196 + tests/driver/T24275/T24275 + + -} + DriverModuleGraphCycle :: [ModuleGraphNode] -> DriverMessage + deriving instance Generic DriverMessage data DriverMessageOpts = ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -1264,9 +1264,7 @@ upsweep n_jobs hsc_env hmi_cache diag_wrapper mHscMessage old_hpt build_plan = d -- of the upsweep. case cycle of Just mss -> do - let logger = hsc_logger hsc_env - liftIO $ fatalErrorMsg logger (cyclicModuleErr mss) - return (Failed, []) + cyclicModuleErr mss Nothing -> do let success_flag = successIf (all isJust res) return (success_flag, completed) @@ -2387,16 +2385,18 @@ multiRootsErr summs@(summ1:_) mod = ms_mod summ1 files = map (expectJust "checkDup" . ml_hs_file . ms_location) summs -cyclicModuleErr :: [ModuleGraphNode] -> SDoc +cyclicModuleErr :: [ModuleGraphNode] -> IO a -- From a strongly connected component we find -- a single cycle to report cyclicModuleErr mss = assert (not (null mss)) $ case findCycle graph of - Nothing -> text "Unexpected non-cycle" <+> ppr mss - Just path0 -> vcat - [ text "Module graph contains a cycle:" - , nest 2 (show_path path0)] + Nothing -> pprPanic "Unexpected non-cycle" (ppr mss) + Just path -> throwOneError $ mkPlainErrorMsgEnvelope src_span + $ GhcDriverMessage + $ DriverModuleGraphCycle path + where + src_span = maybe noSrcSpan (mkFileSrcSpan . ms_location) (moduleGraphNodeModSum (head path)) where graph :: [Node NodeKey ModuleGraphNode] graph = @@ -2408,24 +2408,11 @@ cyclicModuleErr mss | ms <- mss ] - show_path :: [ModuleGraphNode] -> SDoc - show_path [] = panic "show_path" - show_path [m] = ppr_node m <+> text "imports itself" - show_path (m1:m2:ms) = vcat ( nest 14 (ppr_node m1) - : nest 6 (text "imports" <+> ppr_node m2) - : go ms ) - where - go [] = [text "which imports" <+> ppr_node m1] - go (m:ms) = (text "which imports" <+> ppr_node m) : go ms - - ppr_node :: ModuleGraphNode -> SDoc - ppr_node (ModuleNode _deps m) = text "module" <+> ppr_ms m - ppr_node (InstantiationNode _uid u) = text "instantiated unit" <+> ppr u - ppr_node (LinkNode uid _) = pprPanic "LinkNode should not be in a cycle" (ppr uid) - - ppr_ms :: ModSummary -> SDoc - ppr_ms ms = quotes (ppr (moduleName (ms_mod ms))) <+> - (parens (text (msHsFilePath ms))) +mkFileSrcSpan :: ModLocation -> SrcSpan +mkFileSrcSpan mod_loc + = case ml_hs_file mod_loc of + Just file_path -> mkGeneralSrcSpan (mkFastString file_path) + Nothing -> interactiveSrcSpan -- Presumably cleanCurrentModuleTempFilesMaybe :: MonadIO m => Logger -> TmpFs -> DynFlags -> m () ===================================== compiler/GHC/Driver/MakeFile.hs ===================================== @@ -16,6 +16,7 @@ where import GHC.Prelude import qualified GHC +import GHC.Driver.Make import GHC.Driver.Monad import GHC.Driver.DynFlags import GHC.Driver.Ppr @@ -209,10 +210,9 @@ processDeps :: DynFlags -- -- For {-# SOURCE #-} imports the "hi" will be "hi-boot". -processDeps dflags _ _ _ _ (CyclicSCC nodes) +processDeps _ _ _ _ _ (CyclicSCC nodes) = -- There shouldn't be any cycles; report them - throwGhcExceptionIO $ ProgramError $ - showSDoc dflags $ GHC.cyclicModuleErr nodes + cyclicModuleErr nodes processDeps dflags _ _ _ _ (AcyclicSCC (InstantiationNode _uid node)) = -- There shouldn't be any backpack instantiations; report them as well ===================================== compiler/GHC/Types/Error/Codes.hs ===================================== @@ -318,6 +318,7 @@ type family GhcDiagnosticCode c = n | n -> c where GhcDiagnosticCode "DriverPackageTrustIgnored" = 83552 GhcDiagnosticCode "DriverUnrecognisedFlag" = 93741 GhcDiagnosticCode "DriverDeprecatedFlag" = 53692 + GhcDiagnosticCode "DriverModuleGraphCycle" = 92213 -- Constraint solver diagnostic codes GhcDiagnosticCode "BadTelescope" = 97739 ===================================== testsuite/tests/backpack/should_fail/bkpfail51.stderr ===================================== @@ -2,7 +2,9 @@ [1 of 2] Compiling H[sig] ( p/H.hsig, nothing ) [2 of 2] Compiling I ( p/I.hs, nothing ) [2 of 2] Processing q -Module graph contains a cycle: - instantiated unit p[H=A] - imports module ‘A’ (q/A.hsig) - which imports instantiated unit p[H=A] +: error: [GHC-92213] + Module graph contains a cycle: + instantiated unit p[H=] + imports module ‘A’ (q/A.hsig) + which imports instantiated unit p[H=] + ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -112,6 +112,7 @@ GHC.Iface.Ext.Fields GHC.Iface.Recomp.Binary GHC.Iface.Syntax GHC.Iface.Type +GHC.Linker.Static.Utils GHC.Parser GHC.Parser.Annotation GHC.Parser.CharClass @@ -188,6 +189,7 @@ GHC.Types.SafeHaskell GHC.Types.SourceFile GHC.Types.SourceText GHC.Types.SrcLoc +GHC.Types.Target GHC.Types.Tickish GHC.Types.TyThing GHC.Types.Unique @@ -207,9 +209,11 @@ GHC.Unit.Info GHC.Unit.Module GHC.Unit.Module.Deps GHC.Unit.Module.Env +GHC.Unit.Module.Graph GHC.Unit.Module.Imported GHC.Unit.Module.Location GHC.Unit.Module.ModIface +GHC.Unit.Module.ModSummary GHC.Unit.Module.Warnings GHC.Unit.Parser GHC.Unit.Ppr ===================================== testsuite/tests/driver/T20459.stderr ===================================== @@ -1,2 +1,4 @@ -Module graph contains a cycle: - module ‘T20459A’ (./T20459A.hs) imports itself +./T20459A.hs: error: [GHC-92213] + Module graph contains a cycle: + module ‘T20459A’ (./T20459A.hs) imports itself + ===================================== testsuite/tests/driver/T24196/T24196.stderr ===================================== @@ -1,4 +1,6 @@ -Module graph contains a cycle: - module ‘T24196A’ (./T24196A.hs-boot) - imports module ‘T24196B’ (T24196B.hs) - which imports module ‘T24196A’ (./T24196A.hs-boot) +./T24196A.hs-boot: error: [GHC-92213] + Module graph contains a cycle: + module ‘T24196A’ (./T24196A.hs-boot) + imports module ‘T24196B’ (T24196B.hs) + which imports module ‘T24196A’ (./T24196A.hs-boot) + ===================================== testsuite/tests/driver/T24275/T24275.stderr ===================================== @@ -1,4 +1,6 @@ -Module graph contains a cycle: - module ‘T24275A’ (./T24275A.hs-boot) - imports module ‘T24275B’ (T24275B.hs) - which imports module ‘T24275A’ (./T24275A.hs-boot) +./T24275A.hs-boot: error: [GHC-92213] + Module graph contains a cycle: + module ‘T24275A’ (./T24275A.hs-boot) + imports module ‘T24275B’ (T24275B.hs) + which imports module ‘T24275A’ (./T24275A.hs-boot) + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/153d4029b09e5924423b26637b7470075191b2d5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/153d4029b09e5924423b26637b7470075191b2d5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 08:32:19 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 07 Jun 2024 04:32:19 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] WIP: fix mkSpillInstr/mkLoadInstr panics Message-ID: <6662c593be3e2_1b2a627937c5249e@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 1a05aafa by sheaf at 2024-06-07T10:31:52+02:00 WIP: fix mkSpillInstr/mkLoadInstr panics - - - - - 1 changed file: - compiler/GHC/CmmToAsm/X86/Instr.hs Changes: ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -828,10 +828,6 @@ mkSpillInstr mkSpillInstr config reg fmt delta slot = let off s = spillSlotToOffset platform s - delta in case fmt of - IntegerFormat -> [MOV (archWordFormat is32Bit) - (OpReg reg) (OpAddr (spRel platform $ off slot))] - FF64 -> [MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off slot))] - FF32 -> panic "X86_mkSpillInstr: RcFloat" VecFormat {} -> -- SIMD NCG TODO: panic for unsupported VecFormats (& same in mkLoadInstr) [MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off slot)) @@ -839,10 +835,10 @@ mkSpillInstr config reg fmt delta slot ,SHUFPD (VecFormat 2 FmtDouble W64) (ImmInt 0b01) (OpReg reg) reg -- NB: this format doesn't matter, we emit the same instruction -- regardless of what is stored... - -- SIMD NCG TODO: avoid using MOV by using SHUFPD with an OpAddr argument? + -- SIMD NCG TODO: can we emit more efficient code here? ,MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off (slot + 1)))] + _ -> [MOV fmt (OpReg reg) (OpAddr (spRel platform $ off slot))] where platform = ncgPlatform config - is32Bit = target32Bit platform -- | Make a spill reload instruction. mkLoadInstr @@ -857,16 +853,13 @@ mkLoadInstr config reg fmt delta slot = let off s = spillSlotToOffset platform s - delta in case fmt of - IntegerFormat -> ([MOV (archWordFormat is32Bit) - (OpAddr (spRel platform $ off slot)) (OpReg reg)]) - FF64 -> ([MOV FF64 (OpAddr (spRel platform $ off slot)) (OpReg reg)]) - FF32 -> panic "X86.mkLoadInstr RcFloat" VecFormat {} -> + -- SIMD NCG TODO: panic on unsupported VecFormats [MOVH (VecFormat 2 FmtDouble W64) (OpAddr (spRel platform $ off (slot + 1))) (OpReg reg) ,MOVL (VecFormat 2 FmtDouble W64) (OpAddr (spRel platform $ off slot)) (OpReg reg)] + _ -> [MOV fmt (OpAddr (spRel platform $ off slot)) (OpReg reg)] where platform = ncgPlatform config - is32Bit = target32Bit platform spillSlotSize :: Platform -> Int spillSlotSize platform View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1a05aafab2a9ae1d79d6ce746e33f3c2ac4d34b9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1a05aafab2a9ae1d79d6ce746e33f3c2ac4d34b9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 11:52:54 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 07 Jun 2024 07:52:54 -0400 Subject: [Git][ghc/ghc][wip/romes/faststring-is-shortbytestring] Make FastString a ShortByteStr Message-ID: <6662f49615ce2_1b2a6180a3947857a@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/faststring-is-shortbytestring at Glasgow Haskell Compiler / GHC Commits: 9efbd83a by Rodrigo Mesquita at 2024-06-07T13:52:40+02:00 Make FastString a ShortByteStr - - - - - 2 changed files: - compiler/GHC/Data/FastString.hs - compiler/GHC/Types/Unique.hs Changes: ===================================== compiler/GHC/Data/FastString.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE MagicHash #-} @@ -60,7 +61,7 @@ module GHC.Data.FastString lengthFZS, -- * FastStrings - FastString(..), -- not abstract, for now. + FastString, -- not abstract, for now. NonDetFastString (..), LexicalFastString (..), @@ -115,7 +116,6 @@ import GHC.Prelude.Basic as Prelude import GHC.Utils.Encoding import GHC.Utils.IO.Unsafe import GHC.Utils.Panic.Plain -import GHC.Utils.Misc import GHC.Data.FastMutInt import Control.Concurrent.MVar @@ -148,17 +148,16 @@ import GHC.IO -- | Gives the Modified UTF-8 encoded bytes corresponding to a 'FastString' bytesFS, fastStringToByteString :: FastString -> ByteString -{-# INLINE[1] bytesFS #-} -bytesFS f = SBS.fromShort $ fs_sbs f +bytesFS = SBS.fromShort {-# DEPRECATED fastStringToByteString "Use `bytesFS` instead" #-} fastStringToByteString = bytesFS fastStringToShortByteString :: FastString -> ShortByteString -fastStringToShortByteString = fs_sbs +fastStringToShortByteString = id fastStringToShortText :: FastString -> ShortText -fastStringToShortText = ShortText . fs_sbs +fastStringToShortText = ShortText fastZStringToByteString :: FastZString -> ByteString fastZStringToByteString (FastZString bs) = bs @@ -167,8 +166,6 @@ fastZStringToByteString (FastZString bs) = bs unsafeMkByteString :: String -> ByteString unsafeMkByteString = BSC.pack -hashFastString :: FastString -> Int -hashFastString fs = hashStr $ fs_sbs fs -- ----------------------------------------------------------------------------- @@ -205,56 +202,24 @@ comparison. It is also associated with a lazy reference to the Z-encoding of this string which is used by the compiler internally. -} -data FastString = FastString { - uniq :: {-# UNPACK #-} !Int, -- unique id - n_chars :: {-# UNPACK #-} !Int, -- number of chars - fs_sbs :: {-# UNPACK #-} !ShortByteString, - fs_zenc :: FastZString - -- ^ Lazily computed Z-encoding of this string. See Note [Z-Encoding] in - -- GHC.Utils.Encoding. - -- - -- Since 'FastString's are globally memoized this is computed at most - -- once for any given string. - } - -instance Eq FastString where - f1 == f2 = uniq f1 == uniq f2 +type FastString = ShortByteString -- We don't provide any "Ord FastString" instance to force you to think about -- which ordering you want: -- * lexical: deterministic, O(n). Cf lexicalCompareFS and LexicalFastString. -- * by unique: non-deterministic, O(1). Cf uniqCompareFS and NonDetFastString. -instance IsString FastString where - fromString = fsLit -instance Semi.Semigroup FastString where - (<>) = appendFS -instance Monoid FastString where - mempty = nilFS - mappend = (Semi.<>) - mconcat = concatFS -instance Show FastString where - show fs = show (unpackFS fs) -instance Data FastString where - -- don't traverse? - toConstr _ = abstractConstr "FastString" - gunfold _ _ = error "gunfold" - dataTypeOf _ = mkNoRepType "FastString" -instance NFData FastString where - rnf fs = seq fs () -- | Compare FastString lexically -- -- If you don't care about the lexical ordering, use `uniqCompareFS` instead. lexicalCompareFS :: FastString -> FastString -> Ordering -lexicalCompareFS fs1 fs2 = - if uniq fs1 == uniq fs2 then EQ else - utf8CompareShortByteString (fs_sbs fs1) (fs_sbs fs2) +lexicalCompareFS = compare -- perform a lexical comparison taking into account the Modified UTF-8 -- encoding we use (cf #18562) @@ -262,7 +227,7 @@ lexicalCompareFS fs1 fs2 = -- -- Much cheaper than `lexicalCompareFS` but non-deterministic! uniqCompareFS :: FastString -> FastString -> Ordering -uniqCompareFS fs1 fs2 = compare (uniq fs1) (uniq fs2) +uniqCompareFS = compare -- | Non-deterministic FastString -- @@ -332,48 +297,10 @@ Following parameters are determined based on: * Stats of @echo :browse | ghc --interactive -dfaststring-stats >/dev/null@: on 2018-10-24, we have 13920 entries. -} -segmentBits, numSegments, segmentMask, initialNumBuckets :: Int -segmentBits = 8 +numSegments, initialNumBuckets :: Int numSegments = 256 -- bit segmentBits -segmentMask = 0xff -- bit segmentBits - 1 initialNumBuckets = 64 -hashToSegment# :: Int# -> Int# -hashToSegment# hash# = hash# `andI#` segmentMask# - where - !(I# segmentMask#) = segmentMask - -hashToIndex# :: MutableArray# RealWorld [FastString] -> Int# -> Int# -hashToIndex# buckets# hash# = - (hash# `uncheckedIShiftRL#` segmentBits#) `remInt#` size# - where - !(I# segmentBits#) = segmentBits - size# = sizeofMutableArray# buckets# - -maybeResizeSegment :: IORef FastStringTableSegment -> IO FastStringTableSegment -maybeResizeSegment segmentRef = do - segment@(FastStringTableSegment lock counter old#) <- readIORef segmentRef - let oldSize# = sizeofMutableArray# old# - newSize# = oldSize# *# 2# - (I# n#) <- readFastMutInt counter - if isTrue# (n# <# newSize#) -- maximum load of 1 - then return segment - else do - resizedSegment@(FastStringTableSegment _ _ new#) <- IO $ \s1# -> - case newArray# newSize# [] s1# of - (# s2#, arr# #) -> (# s2#, FastStringTableSegment lock counter arr# #) - forM_ [0 .. (I# oldSize#) - 1] $ \(I# i#) -> do - fsList <- IO $ readArray# old# i# - forM_ fsList $ \fs -> do - let -- Shall we store in hash value in FastString instead? - !(I# hash#) = hashFastString fs - idx# = hashToIndex# new# hash# - IO $ \s1# -> - case readArray# new# idx# s1# of - (# s2#, bucket #) -> case writeArray# new# idx# (fs: bucket) s2# of - s3# -> (# s3#, () #) - writeIORef segmentRef resizedSegment - return resizedSegment {-# NOINLINE stringTable #-} stringTable :: FastStringTable @@ -473,60 +400,12 @@ The procedure goes like this: * Otherwise, insert and return the string we created. -} -mkFastStringWith - :: (Int -> FastMutInt-> IO FastString) -> ShortByteString -> IO FastString -mkFastStringWith mk_fs sbs = do - FastStringTableSegment lock _ buckets# <- readIORef segmentRef - let idx# = hashToIndex# buckets# hash# - bucket <- IO $ readArray# buckets# idx# - case bucket_match bucket sbs of - Just found -> return found - Nothing -> do - -- The withMVar below is not dupable. It can lead to deadlock if it is - -- only run partially and putMVar is not called after takeMVar. - noDuplicate - n <- get_uid - new_fs <- mk_fs n n_zencs - withMVar lock $ \_ -> insert new_fs - where - !(FastStringTable uid n_zencs segments#) = stringTable - get_uid = atomicFetchAddFastMut uid 1 - - !(I# hash#) = hashStr sbs - (# segmentRef #) = indexArray# segments# (hashToSegment# hash#) - insert fs = do - FastStringTableSegment _ counter buckets# <- maybeResizeSegment segmentRef - let idx# = hashToIndex# buckets# hash# - bucket <- IO $ readArray# buckets# idx# - case bucket_match bucket sbs of - -- The FastString was added by another thread after previous read and - -- before we acquired the write lock. - Just found -> return found - Nothing -> do - IO $ \s1# -> - case writeArray# buckets# idx# (fs : bucket) s1# of - s2# -> (# s2#, () #) - _ <- atomicFetchAddFastMut counter 1 - return fs - -bucket_match :: [FastString] -> ShortByteString -> Maybe FastString -bucket_match fs sbs = go fs - where go [] = Nothing - go (fs@(FastString {fs_sbs=fs_sbs}) : ls) - | fs_sbs == sbs = Just fs - | otherwise = go ls --- bucket_match used to inline before changes to instance Eq ShortByteString --- in bytestring-0.12, which made it slightly larger than inlining threshold. --- Non-inlining causes a small, but measurable performance regression, so let's force it. -{-# INLINE bucket_match #-} mkFastStringBytes :: Ptr Word8 -> Int -> FastString mkFastStringBytes !ptr !len = -- NB: Might as well use unsafeDupablePerformIO, since mkFastStringWith is -- idempotent. - unsafeDupablePerformIO $ do - sbs <- newSBSFromPtr ptr len - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs + unsafeDupablePerformIO $ newSBSFromPtr ptr len newSBSFromPtr :: Ptr a -> Int -> IO ShortByteString newSBSFromPtr (Ptr src#) (I# len#) = @@ -538,48 +417,23 @@ newSBSFromPtr (Ptr src#) (I# len#) = -- | Create a 'FastString' by copying an existing 'ByteString' mkFastStringByteString :: ByteString -> FastString -mkFastStringByteString bs = - let sbs = SBS.toShort bs in - inlinePerformIO $ - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs +mkFastStringByteString = SBS.toShort -- | Create a 'FastString' from an existing 'ShortByteString' without -- copying. mkFastStringShortByteString :: ShortByteString -> FastString -mkFastStringShortByteString sbs = - inlinePerformIO $ mkFastStringWith (mkNewFastStringShortByteString sbs) sbs +mkFastStringShortByteString = id -- | Creates a UTF-8 encoded 'FastString' from a 'String' mkFastString :: String -> FastString -{-# NOINLINE[1] mkFastString #-} mkFastString str = - inlinePerformIO $ do let !sbs = utf8EncodeShortByteString str - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs - --- The following rule is used to avoid polluting the non-reclaimable FastString --- table with transient strings when we only want their encoding. -{-# RULES -"bytesFS/mkFastString" forall x. bytesFS (mkFastString x) = utf8EncodeByteString x #-} + in sbs -- | Creates a 'FastString' from a UTF-8 encoded @[Word8]@ mkFastStringByteList :: [Word8] -> FastString mkFastStringByteList str = mkFastStringShortByteString (SBS.pack str) --- | Creates a (lazy) Z-encoded 'FastString' from a 'ShortByteString' and --- account the number of forced z-strings into the passed 'FastMutInt'. -mkZFastString :: FastMutInt -> ShortByteString -> FastZString -mkZFastString n_zencs sbs = unsafePerformIO $ do - _ <- atomicFetchAddFastMut n_zencs 1 - return $ mkFastZStringString (zEncodeString (utf8DecodeShortByteString sbs)) - -mkNewFastStringShortByteString :: ShortByteString -> Int - -> FastMutInt -> IO FastString -mkNewFastStringShortByteString sbs uid n_zencs = do - let zstr = mkZFastString n_zencs sbs - chars = utf8CountCharsShortByteString sbs - return (FastString uid chars sbs zstr) - hashStr :: ShortByteString -> Int -- produce a hash value between 0 & m (inclusive) hashStr sbs@(SBS.SBS ba#) = loop 0# 0# @@ -603,15 +457,15 @@ hashStr sbs@(SBS.SBS ba#) = loop 0# 0# -- | Returns the length of the 'FastString' in characters lengthFS :: FastString -> Int -lengthFS fs = n_chars fs +lengthFS = SBS.length -- romes: does this return utf8 length? -- | Returns @True@ if the 'FastString' is empty nullFS :: FastString -> Bool -nullFS fs = SBS.null $ fs_sbs fs +nullFS = SBS.null -- | Lazily unpacks and decodes the FastString unpackFS :: FastString -> String -unpackFS fs = utf8DecodeShortByteString $ fs_sbs fs +unpackFS = utf8DecodeShortByteString -- | Returns a Z-encoded version of a 'FastString'. This might be the -- original, if it was already Z-encoded. The first time this @@ -619,14 +473,13 @@ unpackFS fs = utf8DecodeShortByteString $ fs_sbs fs -- memoized. -- zEncodeFS :: FastString -> FastZString -zEncodeFS fs = fs_zenc fs +zEncodeFS = mkFastZStringString . zEncodeString . utf8DecodeShortByteString appendFS :: FastString -> FastString -> FastString -appendFS fs1 fs2 = mkFastStringShortByteString - $ (Semi.<>) (fs_sbs fs1) (fs_sbs fs2) +appendFS = (Semi.<>) concatFS :: [FastString] -> FastString -concatFS = mkFastStringShortByteString . mconcat . map fs_sbs +concatFS = mconcat consFS :: Char -> FastString -> FastString consFS c fs = mkFastString (c : unpackFS fs) @@ -638,7 +491,9 @@ unconsFS fs = (chr : str) -> Just (chr, mkFastString str) uniqueOfFS :: FastString -> Int -uniqueOfFS fs = uniq fs +uniqueOfFS x = + let y = hashStr x + in assert (0 <= y) y nilFS :: FastString nilFS = mkFastString "" ===================================== compiler/GHC/Types/Unique.hs ===================================== @@ -19,6 +19,7 @@ Haskell). {-# LANGUAGE CPP #-} {-# LANGUAGE MagicHash #-} +{-# LANGUAGE TypeSynonymInstances #-} module GHC.Types.Unique ( -- * Main data types View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9efbd83a797d03645b1682d7f8ba5cb263d7d91e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9efbd83a797d03645b1682d7f8ba5cb263d7d91e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 13:28:35 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 07 Jun 2024 09:28:35 -0400 Subject: [Git][ghc/ghc][wip/romes/faststring-is-shortbytestring] Make FastString a ShortByteStr Message-ID: <66630b0340008_1b2a623bb92c8783f@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/faststring-is-shortbytestring at Glasgow Haskell Compiler / GHC Commits: 2101e624 by Rodrigo Mesquita at 2024-06-07T15:28:21+02:00 Make FastString a ShortByteStr - - - - - 2 changed files: - compiler/GHC/Data/FastString.hs - compiler/GHC/Types/Unique.hs Changes: ===================================== compiler/GHC/Data/FastString.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE MagicHash #-} @@ -60,7 +61,7 @@ module GHC.Data.FastString lengthFZS, -- * FastStrings - FastString(..), -- not abstract, for now. + FastString, -- not abstract, for now. NonDetFastString (..), LexicalFastString (..), @@ -115,7 +116,6 @@ import GHC.Prelude.Basic as Prelude import GHC.Utils.Encoding import GHC.Utils.IO.Unsafe import GHC.Utils.Panic.Plain -import GHC.Utils.Misc import GHC.Data.FastMutInt import Control.Concurrent.MVar @@ -148,17 +148,16 @@ import GHC.IO -- | Gives the Modified UTF-8 encoded bytes corresponding to a 'FastString' bytesFS, fastStringToByteString :: FastString -> ByteString -{-# INLINE[1] bytesFS #-} -bytesFS f = SBS.fromShort $ fs_sbs f +bytesFS = SBS.fromShort {-# DEPRECATED fastStringToByteString "Use `bytesFS` instead" #-} fastStringToByteString = bytesFS fastStringToShortByteString :: FastString -> ShortByteString -fastStringToShortByteString = fs_sbs +fastStringToShortByteString = id fastStringToShortText :: FastString -> ShortText -fastStringToShortText = ShortText . fs_sbs +fastStringToShortText = ShortText fastZStringToByteString :: FastZString -> ByteString fastZStringToByteString (FastZString bs) = bs @@ -167,8 +166,6 @@ fastZStringToByteString (FastZString bs) = bs unsafeMkByteString :: String -> ByteString unsafeMkByteString = BSC.pack -hashFastString :: FastString -> Int -hashFastString fs = hashStr $ fs_sbs fs -- ----------------------------------------------------------------------------- @@ -205,56 +202,24 @@ comparison. It is also associated with a lazy reference to the Z-encoding of this string which is used by the compiler internally. -} -data FastString = FastString { - uniq :: {-# UNPACK #-} !Int, -- unique id - n_chars :: {-# UNPACK #-} !Int, -- number of chars - fs_sbs :: {-# UNPACK #-} !ShortByteString, - fs_zenc :: FastZString - -- ^ Lazily computed Z-encoding of this string. See Note [Z-Encoding] in - -- GHC.Utils.Encoding. - -- - -- Since 'FastString's are globally memoized this is computed at most - -- once for any given string. - } - -instance Eq FastString where - f1 == f2 = uniq f1 == uniq f2 +type FastString = ShortByteString -- We don't provide any "Ord FastString" instance to force you to think about -- which ordering you want: -- * lexical: deterministic, O(n). Cf lexicalCompareFS and LexicalFastString. -- * by unique: non-deterministic, O(1). Cf uniqCompareFS and NonDetFastString. -instance IsString FastString where - fromString = fsLit -instance Semi.Semigroup FastString where - (<>) = appendFS -instance Monoid FastString where - mempty = nilFS - mappend = (Semi.<>) - mconcat = concatFS -instance Show FastString where - show fs = show (unpackFS fs) -instance Data FastString where - -- don't traverse? - toConstr _ = abstractConstr "FastString" - gunfold _ _ = error "gunfold" - dataTypeOf _ = mkNoRepType "FastString" -instance NFData FastString where - rnf fs = seq fs () -- | Compare FastString lexically -- -- If you don't care about the lexical ordering, use `uniqCompareFS` instead. lexicalCompareFS :: FastString -> FastString -> Ordering -lexicalCompareFS fs1 fs2 = - if uniq fs1 == uniq fs2 then EQ else - utf8CompareShortByteString (fs_sbs fs1) (fs_sbs fs2) +lexicalCompareFS = compare -- perform a lexical comparison taking into account the Modified UTF-8 -- encoding we use (cf #18562) @@ -262,7 +227,7 @@ lexicalCompareFS fs1 fs2 = -- -- Much cheaper than `lexicalCompareFS` but non-deterministic! uniqCompareFS :: FastString -> FastString -> Ordering -uniqCompareFS fs1 fs2 = compare (uniq fs1) (uniq fs2) +uniqCompareFS = compare -- | Non-deterministic FastString -- @@ -332,48 +297,10 @@ Following parameters are determined based on: * Stats of @echo :browse | ghc --interactive -dfaststring-stats >/dev/null@: on 2018-10-24, we have 13920 entries. -} -segmentBits, numSegments, segmentMask, initialNumBuckets :: Int -segmentBits = 8 +numSegments, initialNumBuckets :: Int numSegments = 256 -- bit segmentBits -segmentMask = 0xff -- bit segmentBits - 1 initialNumBuckets = 64 -hashToSegment# :: Int# -> Int# -hashToSegment# hash# = hash# `andI#` segmentMask# - where - !(I# segmentMask#) = segmentMask - -hashToIndex# :: MutableArray# RealWorld [FastString] -> Int# -> Int# -hashToIndex# buckets# hash# = - (hash# `uncheckedIShiftRL#` segmentBits#) `remInt#` size# - where - !(I# segmentBits#) = segmentBits - size# = sizeofMutableArray# buckets# - -maybeResizeSegment :: IORef FastStringTableSegment -> IO FastStringTableSegment -maybeResizeSegment segmentRef = do - segment@(FastStringTableSegment lock counter old#) <- readIORef segmentRef - let oldSize# = sizeofMutableArray# old# - newSize# = oldSize# *# 2# - (I# n#) <- readFastMutInt counter - if isTrue# (n# <# newSize#) -- maximum load of 1 - then return segment - else do - resizedSegment@(FastStringTableSegment _ _ new#) <- IO $ \s1# -> - case newArray# newSize# [] s1# of - (# s2#, arr# #) -> (# s2#, FastStringTableSegment lock counter arr# #) - forM_ [0 .. (I# oldSize#) - 1] $ \(I# i#) -> do - fsList <- IO $ readArray# old# i# - forM_ fsList $ \fs -> do - let -- Shall we store in hash value in FastString instead? - !(I# hash#) = hashFastString fs - idx# = hashToIndex# new# hash# - IO $ \s1# -> - case readArray# new# idx# s1# of - (# s2#, bucket #) -> case writeArray# new# idx# (fs: bucket) s2# of - s3# -> (# s3#, () #) - writeIORef segmentRef resizedSegment - return resizedSegment {-# NOINLINE stringTable #-} stringTable :: FastStringTable @@ -473,60 +400,12 @@ The procedure goes like this: * Otherwise, insert and return the string we created. -} -mkFastStringWith - :: (Int -> FastMutInt-> IO FastString) -> ShortByteString -> IO FastString -mkFastStringWith mk_fs sbs = do - FastStringTableSegment lock _ buckets# <- readIORef segmentRef - let idx# = hashToIndex# buckets# hash# - bucket <- IO $ readArray# buckets# idx# - case bucket_match bucket sbs of - Just found -> return found - Nothing -> do - -- The withMVar below is not dupable. It can lead to deadlock if it is - -- only run partially and putMVar is not called after takeMVar. - noDuplicate - n <- get_uid - new_fs <- mk_fs n n_zencs - withMVar lock $ \_ -> insert new_fs - where - !(FastStringTable uid n_zencs segments#) = stringTable - get_uid = atomicFetchAddFastMut uid 1 - - !(I# hash#) = hashStr sbs - (# segmentRef #) = indexArray# segments# (hashToSegment# hash#) - insert fs = do - FastStringTableSegment _ counter buckets# <- maybeResizeSegment segmentRef - let idx# = hashToIndex# buckets# hash# - bucket <- IO $ readArray# buckets# idx# - case bucket_match bucket sbs of - -- The FastString was added by another thread after previous read and - -- before we acquired the write lock. - Just found -> return found - Nothing -> do - IO $ \s1# -> - case writeArray# buckets# idx# (fs : bucket) s1# of - s2# -> (# s2#, () #) - _ <- atomicFetchAddFastMut counter 1 - return fs - -bucket_match :: [FastString] -> ShortByteString -> Maybe FastString -bucket_match fs sbs = go fs - where go [] = Nothing - go (fs@(FastString {fs_sbs=fs_sbs}) : ls) - | fs_sbs == sbs = Just fs - | otherwise = go ls --- bucket_match used to inline before changes to instance Eq ShortByteString --- in bytestring-0.12, which made it slightly larger than inlining threshold. --- Non-inlining causes a small, but measurable performance regression, so let's force it. -{-# INLINE bucket_match #-} mkFastStringBytes :: Ptr Word8 -> Int -> FastString mkFastStringBytes !ptr !len = -- NB: Might as well use unsafeDupablePerformIO, since mkFastStringWith is -- idempotent. - unsafeDupablePerformIO $ do - sbs <- newSBSFromPtr ptr len - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs + unsafeDupablePerformIO $ newSBSFromPtr ptr len newSBSFromPtr :: Ptr a -> Int -> IO ShortByteString newSBSFromPtr (Ptr src#) (I# len#) = @@ -538,48 +417,23 @@ newSBSFromPtr (Ptr src#) (I# len#) = -- | Create a 'FastString' by copying an existing 'ByteString' mkFastStringByteString :: ByteString -> FastString -mkFastStringByteString bs = - let sbs = SBS.toShort bs in - inlinePerformIO $ - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs +mkFastStringByteString = SBS.toShort -- | Create a 'FastString' from an existing 'ShortByteString' without -- copying. mkFastStringShortByteString :: ShortByteString -> FastString -mkFastStringShortByteString sbs = - inlinePerformIO $ mkFastStringWith (mkNewFastStringShortByteString sbs) sbs +mkFastStringShortByteString = id -- | Creates a UTF-8 encoded 'FastString' from a 'String' mkFastString :: String -> FastString -{-# NOINLINE[1] mkFastString #-} mkFastString str = - inlinePerformIO $ do let !sbs = utf8EncodeShortByteString str - mkFastStringWith (mkNewFastStringShortByteString sbs) sbs - --- The following rule is used to avoid polluting the non-reclaimable FastString --- table with transient strings when we only want their encoding. -{-# RULES -"bytesFS/mkFastString" forall x. bytesFS (mkFastString x) = utf8EncodeByteString x #-} + in sbs -- | Creates a 'FastString' from a UTF-8 encoded @[Word8]@ mkFastStringByteList :: [Word8] -> FastString mkFastStringByteList str = mkFastStringShortByteString (SBS.pack str) --- | Creates a (lazy) Z-encoded 'FastString' from a 'ShortByteString' and --- account the number of forced z-strings into the passed 'FastMutInt'. -mkZFastString :: FastMutInt -> ShortByteString -> FastZString -mkZFastString n_zencs sbs = unsafePerformIO $ do - _ <- atomicFetchAddFastMut n_zencs 1 - return $ mkFastZStringString (zEncodeString (utf8DecodeShortByteString sbs)) - -mkNewFastStringShortByteString :: ShortByteString -> Int - -> FastMutInt -> IO FastString -mkNewFastStringShortByteString sbs uid n_zencs = do - let zstr = mkZFastString n_zencs sbs - chars = utf8CountCharsShortByteString sbs - return (FastString uid chars sbs zstr) - hashStr :: ShortByteString -> Int -- produce a hash value between 0 & m (inclusive) hashStr sbs@(SBS.SBS ba#) = loop 0# 0# @@ -603,15 +457,15 @@ hashStr sbs@(SBS.SBS ba#) = loop 0# 0# -- | Returns the length of the 'FastString' in characters lengthFS :: FastString -> Int -lengthFS fs = n_chars fs +lengthFS = SBS.length -- romes: does this return utf8 length? -- | Returns @True@ if the 'FastString' is empty nullFS :: FastString -> Bool -nullFS fs = SBS.null $ fs_sbs fs +nullFS = SBS.null -- | Lazily unpacks and decodes the FastString unpackFS :: FastString -> String -unpackFS fs = utf8DecodeShortByteString $ fs_sbs fs +unpackFS = utf8DecodeShortByteString -- | Returns a Z-encoded version of a 'FastString'. This might be the -- original, if it was already Z-encoded. The first time this @@ -619,14 +473,13 @@ unpackFS fs = utf8DecodeShortByteString $ fs_sbs fs -- memoized. -- zEncodeFS :: FastString -> FastZString -zEncodeFS fs = fs_zenc fs +zEncodeFS = mkFastZStringString . zEncodeString . utf8DecodeShortByteString appendFS :: FastString -> FastString -> FastString -appendFS fs1 fs2 = mkFastStringShortByteString - $ (Semi.<>) (fs_sbs fs1) (fs_sbs fs2) +appendFS = (Semi.<>) concatFS :: [FastString] -> FastString -concatFS = mkFastStringShortByteString . mconcat . map fs_sbs +concatFS = mconcat consFS :: Char -> FastString -> FastString consFS c fs = mkFastString (c : unpackFS fs) @@ -638,7 +491,9 @@ unconsFS fs = (chr : str) -> Just (chr, mkFastString str) uniqueOfFS :: FastString -> Int -uniqueOfFS fs = uniq fs +uniqueOfFS x = + let y = abs $ hashStr x -- that can't possibly be unique... + in assert (0 <= y) y nilFS :: FastString nilFS = mkFastString "" ===================================== compiler/GHC/Types/Unique.hs ===================================== @@ -19,6 +19,7 @@ Haskell). {-# LANGUAGE CPP #-} {-# LANGUAGE MagicHash #-} +{-# LANGUAGE TypeSynonymInstances #-} module GHC.Types.Unique ( -- * Main data types View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2101e6244ef39bc74f32aca7ef1f2a689c3085fe -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2101e6244ef39bc74f32aca7ef1f2a689c3085fe You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 15:00:02 2024 From: gitlab at gitlab.haskell.org (Vladislav Zavialov (@int-index)) Date: Fri, 07 Jun 2024 11:00:02 -0400 Subject: [Git][ghc/ghc][wip/int-index/types-in-terms] 4387 commits: [haddock @ 2002-04-04 16:23:43 by simonmar] Message-ID: <666320722ac15_1b2a6303d114986c3@gitlab.mail> Vladislav Zavialov pushed to branch wip/int-index/types-in-terms at Glasgow Haskell Compiler / GHC Commits: 2b39cd94 by Simon Marlow at 2002-04-04T16:23:43+00:00 [haddock @ 2002-04-04 16:23:43 by simonmar] This is Haddock, my stab at a Haskell documentation tool. It's not quite ready for release yet, but I'm putting it in the repository so others can take a look. It uses a locally modified version of the hssource parser, extended with support for GHC extensions and documentation annotations. - - - - - 99ede94f by Simon Marlow at 2002-04-04T16:24:10+00:00 [haddock @ 2002-04-04 16:24:10 by simonmar] forgot one file - - - - - 8363294c by Simon Marlow at 2002-04-05T13:58:15+00:00 [haddock @ 2002-04-05 13:58:15 by simonmar] Remap names in the exported declarations to be "closer" to the current module. eg. if an exported declaration mentions a type 'T' which is imported from module A then re-exported from the current module, then links from the type or indeed the documentation will point to the current module rather than module A. This is to support better hiding: module A won't be referred to in the generated output. - - - - - 1570cbc1 by Simon Marlow at 2002-04-05T13:58:23+00:00 [haddock @ 2002-04-05 13:58:23 by simonmar] update the TODO list - - - - - 3a62f96b by Simon Marlow at 2002-04-05T14:11:51+00:00 [haddock @ 2002-04-05 14:11:51 by simonmar] Fix the anchor for a class declaration - - - - - c5d9a471 by Simon Marlow at 2002-04-05T14:18:41+00:00 [haddock @ 2002-04-05 14:18:41 by simonmar] remove underlines on visited links - - - - - 97280525 by Simon Marlow at 2002-04-05T16:11:47+00:00 [haddock @ 2002-04-05 16:11:47 by simonmar] - Update to generate more correct HTML. - Use our own non-overloaded table combinators, as the overloaded versions were giving me a headache. The improved type safety caught several errors in the HTML generation. - - - - - 9acd3a4d by Simon Marlow at 2002-04-05T16:32:19+00:00 [haddock @ 2002-04-05 16:32:19 by simonmar] Add width property to the title, and add TD.children for the module contents page. - - - - - ec9a0847 by Simon Marlow at 2002-04-08T16:39:56+00:00 [haddock @ 2002-04-08 16:39:56 by simonmar] Fix a problem with exports of the form T(..). - - - - - e4627dc8 by Simon Marlow at 2002-04-08T16:41:38+00:00 [haddock @ 2002-04-08 16:41:37 by simonmar] - Add our own versions of Html & BlockTable for the time being. - Add support for generating an index to the HTML backend - - - - - 2d73fd75 by Simon Marlow at 2002-04-09T11:23:24+00:00 [haddock @ 2002-04-09 11:23:24 by simonmar] Add '-- /' as a synonym for '-- |', for compatibility with IDoc. - - - - - 3675464e by Simon Marlow at 2002-04-09T11:33:55+00:00 [haddock @ 2002-04-09 11:33:54 by simonmar] - add the <...> syntax for marking up URLs in documentation - Make the output for data & class declarations more compact when there aren't any documentation annotations on the individual methods or constructors respectively. - - - - - 5077f5b1 by Simon Marlow at 2002-04-09T11:36:04+00:00 [haddock @ 2002-04-09 11:36:04 by simonmar] Update the TODO list - - - - - 9e83c54d by Simon Marlow at 2002-04-10T10:50:06+00:00 [haddock @ 2002-04-10 10:50:06 by simonmar] Use explicit 'px' suffix on pixel sizes; IE seems to prefer them - - - - - 052de51c by Simon Marlow at 2002-04-10T13:23:13+00:00 [haddock @ 2002-04-10 13:23:13 by simonmar] Lex URLs as a single token to avoid having to escape special characters inside the URL string. - - - - - 47187edb by Simon Marlow at 2002-04-10T13:23:55+00:00 [haddock @ 2002-04-10 13:23:55 by simonmar] Not sure why I made the constructor name for a record declaration into a TyCls name, but change it back into a Var name anyhow. - - - - - 3dc6aa81 by Simon Marlow at 2002-04-10T13:26:10+00:00 [haddock @ 2002-04-10 13:26:09 by simonmar] Lots of changes, including: - add index support to the HTML backend - clean up the renamer, put it into a monad - propogate unresolved names to the top level and report them in a nicer way - various bugfixes - - - - - c2a70a72 by Simon Marlow at 2002-04-10T13:32:39+00:00 [haddock @ 2002-04-10 13:32:39 by simonmar] Skeleton documentation - - - - - 50c98d17 by Simon Marlow at 2002-04-10T13:37:23+00:00 [haddock @ 2002-04-10 13:37:23 by simonmar] Update the TODO list, separate into pre-1.0 and post-1.0 items - - - - - f3778be6 by Simon Marlow at 2002-04-10T14:30:58+00:00 [haddock @ 2002-04-10 14:30:58 by simonmar] Add an introduction - - - - - cfbaf9f7 by Simon Marlow at 2002-04-10T14:59:51+00:00 [haddock @ 2002-04-10 14:59:51 by simonmar] Sort the module tree - - - - - 76bd7b34 by Simon Marlow at 2002-04-10T15:50:11+00:00 [haddock @ 2002-04-10 15:50:10 by simonmar] Generate a little table of contents at the top of the module doc (only if the module actually contains some section headings, though). - - - - - bb8560a1 by Simon Marlow at 2002-04-10T16:10:26+00:00 [haddock @ 2002-04-10 16:10:26 by simonmar] Now we understand (or at least don't barf on) type signatures in patterns such as you might find when scoped type variables are in use. - - - - - 86c2a026 by Simon Marlow at 2002-04-10T16:10:49+00:00 [haddock @ 2002-04-10 16:10:49 by simonmar] more updates - - - - - 1c052b0e by Simon Marlow at 2002-04-10T16:28:05+00:00 [haddock @ 2002-04-10 16:28:05 by simonmar] Parse errors in doc strings are now reported as warnings rather that causing the whole thing to fall over. It still needs cleaning up (the warning is emitted with trace) but this will do for the time being. - - - - - ace03e8f by Simon Marlow at 2002-04-10T16:38:03+00:00 [haddock @ 2002-04-10 16:38:03 by simonmar] update again - - - - - 69006c3e by Simon Marlow at 2002-04-11T13:38:02+00:00 [haddock @ 2002-04-11 13:38:02 by simonmar] mention Opera - - - - - fe9b10f8 by Simon Marlow at 2002-04-11T13:40:31+00:00 [haddock @ 2002-04-11 13:40:30 by simonmar] - copy haddock.css into the same place as the generated HTML - new option: --css <file> specifies the style sheet to use - new option: -o <dir> specifies the directory in which to generate the output. - because Haddock now needs to know where to find its default stylesheet, we have to have a wrapper script and do the haddock-inplace thing (Makefile code copied largely from fptools/happy). - - - - - 106adbbe by Simon Marlow at 2002-04-24T15:12:41+00:00 [haddock @ 2002-04-24 15:12:41 by simonmar] Stop slurping comment lines when we see a row of dashes longer than length 2: these are useful as separators. - - - - - 995d3f9e by Simon Marlow at 2002-04-24T15:14:12+00:00 [haddock @ 2002-04-24 15:14:11 by simonmar] Grok the kind of module headers we use in fptools/libraries, and pass the "portability", "stability", and "maintainer" strings through into the generated HTML. If the module header doesn't match the pattern, then we don't include the info in the HTML. - - - - - e14da136 by Simon Marlow at 2002-04-24T15:16:57+00:00 [haddock @ 2002-04-24 15:16:57 by simonmar] Done module headers now. - - - - - 2ca8dfd4 by Simon Marlow at 2002-04-24T15:57:48+00:00 [haddock @ 2002-04-24 15:57:47 by simonmar] Handle gcons in export lists (a common extension). - - - - - 044cea81 by Simon Marlow at 2002-04-25T14:20:12+00:00 [haddock @ 2002-04-25 14:20:12 by simonmar] Add the little lambda icon - - - - - 63955027 by Simon Marlow at 2002-04-25T14:40:05+00:00 [haddock @ 2002-04-25 14:40:05 by simonmar] - Add support for named chunks of documentation which can be referenced from the export list. - Copy the icon from $libdir to the destination in HTML mode. - - - - - 36e3f913 by Simon Marlow at 2002-04-25T16:48:36+00:00 [haddock @ 2002-04-25 16:48:36 by simonmar] More keyboard bashing - - - - - 7ae18dd0 by Simon Marlow at 2002-04-26T08:43:33+00:00 [haddock @ 2002-04-26 08:43:33 by simonmar] Package util reqd. to compile with 4.08.2 - - - - - bbd5fbab by Simon Marlow at 2002-04-26T10:13:00+00:00 [haddock @ 2002-04-26 10:13:00 by simonmar] Include $(GHC_HAPPY_OPTS) when compiling HsParser - - - - - 31c53d79 by Simon Marlow at 2002-04-26T11:18:57+00:00 [haddock @ 2002-04-26 11:18:56 by simonmar] - support for fundeps (partially contributed by Brett Letner - thanks Brett). - make it build with GHC 4.08.2 - - - - - c415ce76 by Simon Marlow at 2002-04-26T13:15:02+00:00 [haddock @ 2002-04-26 13:15:02 by simonmar] Move the explicit formatting of the little table for the stability/portability/maintainer info from the HTML into the CSS, and remove the explicit table size (just right-align it). - - - - - 520ee21a by Simon Marlow at 2002-04-26T16:01:44+00:00 [haddock @ 2002-04-26 16:01:44 by simonmar] Yet more keyboard bashing - this is pretty much complete now. - - - - - 2ae37179 by Simon Marlow at 2002-04-26T16:02:14+00:00 [haddock @ 2002-04-26 16:02:14 by simonmar] Add a couple of things I forgot about - - - - - b7211e04 by Simon Marlow at 2002-04-29T15:28:12+00:00 [haddock @ 2002-04-29 15:28:12 by simonmar] bugfix for declBinders on a NewTypeDecl - - - - - 640c154a by Simon Marlow at 2002-04-29T15:28:54+00:00 [haddock @ 2002-04-29 15:28:54 by simonmar] Allow '-- |' style annotations on constructors and record fields. - - - - - 393f258a by Simon Marlow at 2002-04-29T15:37:32+00:00 [haddock @ 2002-04-29 15:37:32 by simonmar] syntax fix - - - - - 8a2c2549 by Simon Marlow at 2002-04-29T15:37:48+00:00 [haddock @ 2002-04-29 15:37:48 by simonmar] Add an example - - - - - db88f8a2 by Simon Marlow at 2002-04-29T15:55:46+00:00 [haddock @ 2002-04-29 15:55:46 by simonmar] remove a trace - - - - - 2b0248e0 by Simon Marlow at 2002-04-29T15:56:19+00:00 [haddock @ 2002-04-29 15:56:19 by simonmar] Fix for 'make install' - - - - - 120453a0 by Simon Marlow at 2002-04-29T15:56:39+00:00 [haddock @ 2002-04-29 15:56:39 by simonmar] Install the auxilliary bits - - - - - 950e6dbb by Simon Marlow at 2002-04-29T15:57:30+00:00 [haddock @ 2002-04-29 15:57:30 by simonmar] Add BinDist bits - - - - - 154b9d71 by Simon Marlow at 2002-05-01T11:02:52+00:00 [haddock @ 2002-05-01 11:02:52 by simonmar] update - - - - - ba6c39fa by Simon Marlow at 2002-05-01T11:03:26+00:00 [haddock @ 2002-05-01 11:03:26 by simonmar] Add another item - - - - - bacb5e33 by Simon Marlow at 2002-05-03T08:50:00+00:00 [haddock @ 2002-05-03 08:50:00 by simonmar] Fix some typos. - - - - - 54c87895 by Sven Panne at 2002-05-05T19:40:51+00:00 [haddock @ 2002-05-05 19:40:51 by panne] As a temporary hack/workaround for a bug in GHC's simplifier, don't pass Happy the -c option for generating the parsers in this subdir. Furthermore, disable -O for HaddocParse, too. - - - - - e6c08703 by Simon Marlow at 2002-05-06T09:51:10+00:00 [haddock @ 2002-05-06 09:51:10 by simonmar] Add RPM spec file (thanks to Tom Moertel <tom-rpms at moertel.com>) - - - - - 7b8fa8e7 by Simon Marlow at 2002-05-06T12:29:26+00:00 [haddock @ 2002-05-06 12:29:26 by simonmar] Add missing type signature (a different workaround for the bug in GHC's simplifier). - - - - - cd0e300d by Simon Marlow at 2002-05-06T12:30:09+00:00 [haddock @ 2002-05-06 12:30:09 by simonmar] Remove workaround for simplifier bug in previous revision. - - - - - 687e68fa by Simon Marlow at 2002-05-06T12:32:32+00:00 [haddock @ 2002-05-06 12:32:32 by simonmar] Allow empty data declarations (another GHC extension). - - - - - 8f29f696 by Simon Marlow at 2002-05-06T12:49:21+00:00 [haddock @ 2002-05-06 12:49:21 by simonmar] Fix silly bug in named documentation block lookup. - - - - - 8e0059af by Simon Marlow at 2002-05-06T13:02:42+00:00 [haddock @ 2002-05-06 13:02:42 by simonmar] Add another named chunk with a different name - - - - - 68f8a896 by Simon Marlow at 2002-05-06T13:32:32+00:00 [haddock @ 2002-05-06 13:32:32 by simonmar] Be more lenient about extra paragraph breaks - - - - - 65fc31db by Simon Marlow at 2002-05-07T15:36:36+00:00 [haddock @ 2002-05-07 15:36:36 by simonmar] DocEmpty is a right and left-unit of DocAppend (remove it in the smart constructor). - - - - - adc81078 by Simon Marlow at 2002-05-07T15:37:15+00:00 [haddock @ 2002-05-07 15:37:15 by simonmar] Allow code blocks to be denoted with bird-tracks in addition to [...]. - - - - - 1283a3c1 by Simon Marlow at 2002-05-08T11:21:56+00:00 [haddock @ 2002-05-08 11:21:56 by simonmar] Add a facility for specifying options that affect Haddock's treatment of the module. Options are given at the top of the module in a comma-separated list, beginning with '-- #'. eg. -- # prune, hide, ignore-exports Options currently available, with their meanings: prune: ignore declarations which have no documentation annotations ignore-exports: act as if the export list were not specified (i.e. export everything local to the module). hide: do not include this module in the generated documentation, but propagate any exported definitions to modules which re-export them. There's a slight change in the semantics for re-exporting a full module by giving 'module M' in the export list: if module M does not have the 'hide' option, then the documentation will now just contain a reference to module M rather than the full inlined contents of that module. These features, and some other changes in the pipeline, are the result of discussions between myself and Manuel Chakravarty <chak at cse.unsw.edu.au> (author of IDoc) yesterday. Also: some cleanups, use a Writer monad to collect error messages in some places instead of just printing them with trace. - - - - - a2239cf5 by Simon Marlow at 2002-05-08T11:22:30+00:00 [haddock @ 2002-05-08 11:22:30 by simonmar] Update to test new features. - - - - - 6add955f by Simon Marlow at 2002-05-08T13:37:25+00:00 [haddock @ 2002-05-08 13:37:25 by simonmar] Change the markup for typewriter-font from [...] to @... at . The reasoning is that the '@' symbol is much less likely to be needed than square brackets, and we don't want to have to escape square brackets in code fragments. This will be mildly painful in the short term, but it's better to get the change out of the way as early as possible. - - - - - cda06447 by Simon Marlow at 2002-05-08T13:39:56+00:00 [haddock @ 2002-05-08 13:39:56 by simonmar] Allow nested-style comments to be used as documentation annotations too. eg. {-| ... -} is equivalent to -- | ... An extra space can also be left after the comment opener: {- | ... -}. The only version that isn't allowed is {-# ... -}, because this syntax overlaps with Haskell pragmas; use {- # ... -} instead. - - - - - db23f65e by Simon Marlow at 2002-05-08T14:48:41+00:00 [haddock @ 2002-05-08 14:48:39 by simonmar] Add support for existential quantifiers on constructors. - - - - - adce3794 by Simon Marlow at 2002-05-08T15:43:25+00:00 [haddock @ 2002-05-08 15:43:25 by simonmar] update - - - - - 62a1f436 by Simon Marlow at 2002-05-08T15:44:10+00:00 [haddock @ 2002-05-08 15:44:10 by simonmar] Update to version 0.2 - - - - - f6a24ba3 by Simon Marlow at 2002-05-09T08:48:29+00:00 [haddock @ 2002-05-09 08:48:29 by simonmar] typo - - - - - 9f9522a4 by Simon Marlow at 2002-05-09T10:33:14+00:00 [haddock @ 2002-05-09 10:33:14 by simonmar] oops, left out '/' from the special characters in the last change. - - - - - 14abcb39 by Simon Marlow at 2002-05-09T10:34:44+00:00 [haddock @ 2002-05-09 10:34:44 by simonmar] Fix buglet - - - - - b8d878be by Simon Marlow at 2002-05-09T10:35:00+00:00 [haddock @ 2002-05-09 10:35:00 by simonmar] Give a more useful instance of Show for Module. - - - - - f7bfd626 by Simon Marlow at 2002-05-09T10:37:07+00:00 [haddock @ 2002-05-09 10:37:07 by simonmar] The last commit to Main.lhs broke the delicate balance of laziness which was being used to avoid computing the dependency graph of modules. So I finally bit the bullet and did a proper topological sort of the module graph, which turned out to be easy (stealing the Digraph module from GHC - this really ought to be in the libraries somewhere). - - - - - b481c1d0 by Simon Marlow at 2002-05-09T10:37:25+00:00 [haddock @ 2002-05-09 10:37:25 by simonmar] another item done - - - - - 032e2b42 by Simon Marlow at 2002-05-09T10:44:15+00:00 [haddock @ 2002-05-09 10:44:15 by simonmar] Don't consider a module re-export as having documentation, for the purposes of deciding whether we need a Synopsis section or not. - - - - - 5fb45e92 by Simon Marlow at 2002-05-09T11:10:55+00:00 [haddock @ 2002-05-09 11:10:55 by simonmar] Add a special case for list types in ppHsAType - - - - - 1937e428 by Simon Marlow at 2002-05-09T12:43:06+00:00 [haddock @ 2002-05-09 12:43:06 by simonmar] Type synonyms can accept a ctype on the RHS, to match GHC. - - - - - 0f16ce56 by Simon Marlow at 2002-05-09T12:45:19+00:00 [haddock @ 2002-05-09 12:45:19 by simonmar] Add 'stdcall' keyword - - - - - 29b0d7d2 by Simon Marlow at 2002-05-09T13:35:45+00:00 [haddock @ 2002-05-09 13:35:45 by simonmar] Add System Requirements section - - - - - bf14dddd by Simon Marlow at 2002-05-09T13:36:11+00:00 [haddock @ 2002-05-09 13:36:11 by simonmar] Test existential types, amongst other things - - - - - 502f8f6f by Simon Marlow at 2002-05-09T13:37:35+00:00 [haddock @ 2002-05-09 13:37:35 by simonmar] Print the module name in a doc-string parse error - - - - - ca1f8d49 by Simon Marlow at 2002-05-09T13:38:04+00:00 [haddock @ 2002-05-09 13:38:04 by simonmar] Add dependency - - - - - 8d3d91ff by Simon Marlow at 2002-05-09T15:37:57+00:00 [haddock @ 2002-05-09 15:37:57 by simonmar] Add the changelog/release notes - - - - - f3960959 by Simon Marlow at 2002-05-09T15:47:47+00:00 [haddock @ 2002-05-09 15:47:47 by simonmar] mention the backquote-style of markup - - - - - 089fb6e6 by Simon Marlow at 2002-05-09T15:59:45+00:00 [haddock @ 2002-05-09 15:59:45 by simonmar] update - - - - - bdd3be0b by Simon Marlow at 2002-05-09T15:59:56+00:00 [haddock @ 2002-05-09 15:59:56 by simonmar] Document changes since 0.1 - - - - - 00fc4af8 by Simon Marlow at 2002-05-10T08:22:48+00:00 [haddock @ 2002-05-10 08:22:48 by simonmar] oops, update to version 0.2 - - - - - a8a79041 by Simon Marlow at 2002-05-10T16:05:08+00:00 [haddock @ 2002-05-10 16:05:08 by simonmar] Only include a mini-contents if there are 2 or more sections - - - - - 06653319 by Simon Marlow at 2002-05-13T09:13:12+00:00 [haddock @ 2002-05-13 09:13:12 by simonmar] fix typos - - - - - 1402b19b by Simon Marlow at 2002-05-13T10:14:22+00:00 [haddock @ 2002-05-13 10:14:22 by simonmar] Allow backquote as the right-hand quote as well as the left-hand quote, as suggested by Dean Herrington. Clean up the grammar a litte. - - - - - dcd5320d by Simon Marlow at 2002-05-13T10:44:10+00:00 [haddock @ 2002-05-13 10:44:10 by simonmar] a couple more things, prioritise a bit - - - - - a90130c4 by Simon Marlow at 2002-05-13T15:19:03+00:00 [haddock @ 2002-05-13 15:19:03 by simonmar] Cope with datatypes which have documentation on the constructor but not the type itself, and records which have documentation on the fields but not the constructor. (Thanks to Ross Paterson for pointing out the bugs). - - - - - a774d432 by Simon Marlow at 2002-05-13T15:20:54+00:00 [haddock @ 2002-05-13 15:20:54 by simonmar] Fix one of the record examples - - - - - 2d1d5218 by Simon Marlow at 2002-05-15T12:44:35+00:00 [haddock @ 2002-05-15 12:44:35 by simonmar] Preserve the newline before a bird-track, but only within a paragraph. - - - - - 1554c09a by Simon Marlow at 2002-05-15T13:03:02+00:00 [haddock @ 2002-05-15 13:03:01 by simonmar] Reworking of the internals to support documenting function arguments (the Most Wanted new feature by the punters). The old method of keeping parsed documentation in a Name -> Doc mapping wasn't going to cut it for anntations on type components, where there's no name to attach the documentation to, so I've moved to storing all the documentation in the abstract syntax. Previously some of the documentation was left in the abstract syntax by the parser, but was later extracted into the mapping. In order to avoid having to parameterise the abstract syntax over the type of documentation stored in it, we have to parse the documentation at the same time as we parse the Haskell source (well, I suppose we could store 'Either String Doc' in the HsSyn, but that's clunky). One upshot is that documentation is now parsed eagerly, and documentation parse errors are fatal (but have better line numbers in the error message). The new story simplifies matters for the code that processes the source modules, because we don't have to maintain the extra Name->Doc mapping, and it should improve efficiency a little too. New features: - Function arguments and return values can now have doc annotations. - If you refer to a qualified name in a doc string, eg. 'IO.putStr', then Haddock will emit a hyperlink even if the identifier is not in scope, so you don't have to make sure everything referred to from the documentation is imported. - several bugs & minor infelicities fixed. - - - - - 57344dc3 by Simon Marlow at 2002-05-15T13:03:19+00:00 [haddock @ 2002-05-15 13:03:19 by simonmar] Bump to version 0.3 - - - - - b2791812 by Simon Marlow at 2002-05-15T13:03:41+00:00 [haddock @ 2002-05-15 13:03:41 by simonmar] update - - - - - fead183e by Simon Marlow at 2002-05-15T13:10:15+00:00 [haddock @ 2002-05-15 13:10:15 by simonmar] Rename Foo.hs to Test.hs, and add a Makefile - - - - - b0b1f89f by Simon Marlow at 2002-05-15T13:16:07+00:00 [haddock @ 2002-05-15 13:16:07 by simonmar] - Remove the note about function argument docs not being implemented - Note that qualified identifiers can be used to point to entities that aren't in scope. - - - - - 5665f31a by Simon Marlow at 2002-05-15T13:28:46+00:00 [haddock @ 2002-05-15 13:28:46 by simonmar] Patch to add support for GHC-style primitive strings ".."#, from Ross Paterson. - - - - - 0564505d by Simon Marlow at 2002-05-17T10:51:57+00:00 [haddock @ 2002-05-17 10:51:57 by simonmar] Fix bugs in qualified name handling (A.B.f was returned as B.f) - - - - - 10e7311c by Simon Marlow at 2002-05-21T10:24:52+00:00 [haddock @ 2002-05-21 10:24:52 by simonmar] - Use an alternate tabular layout for datatypes, which is more compact - Fix some problems with the function argument documentation - - - - - 2f91c2a6 by Simon Marlow at 2002-05-21T10:27:40+00:00 [haddock @ 2002-05-21 10:27:40 by simonmar] add a few more test cases - - - - - 01c2ddd2 by Simon Marlow at 2002-05-21T10:28:33+00:00 [haddock @ 2002-05-21 10:28:33 by simonmar] Rearrange a bit, and add support for tabular datatype rendering - - - - - a4e4c5f8 by Simon Marlow at 2002-05-27T09:03:52+00:00 [haddock @ 2002-05-27 09:03:51 by simonmar] Lots of changes: - instances of a class are listed with the class, and instances involving a datatype are listed with that type. Derived instances aren't included at the moment: the calculation to find the instance head for a derived instance is non-trivial. - some formatting changes; use rows with specified height rather than cellspacing in some places. - various fixes (source file links were wrong, amongst others) - - - - - 48722e68 by Simon Marlow at 2002-05-27T12:30:38+00:00 [haddock @ 2002-05-27 12:30:37 by simonmar] - Put function arguments *before* the doc for the function, as suggested by Sven Panne. This looks nicer when the function documentation is long. - Switch to using bold for binders at the definition site, and use underline for keywords. This makes the binder stand out more. - - - - - 657204d2 by Simon Marlow at 2002-05-27T13:19:49+00:00 [haddock @ 2002-05-27 13:19:49 by simonmar] Fix bug: we weren't renaming HsDocCommentNamed in renameDecl - - - - - 592aae66 by Simon Marlow at 2002-05-27T14:10:27+00:00 [haddock @ 2002-05-27 14:10:27 by simonmar] Fix some bugs in the rendering of qualified type signatures. - - - - - 69c8f763 by Simon Marlow at 2002-05-27T14:36:45+00:00 [haddock @ 2002-05-27 14:36:45 by simonmar] warning message tweak - - - - - 16e64e21 by Simon Marlow at 2002-05-27T14:53:53+00:00 [haddock @ 2002-05-27 14:53:53 by simonmar] hyperlinked identifiers should be in <tt> - - - - - 8d5e4783 by Simon Marlow at 2002-05-27T15:56:45+00:00 [haddock @ 2002-05-27 15:56:45 by simonmar] Do something sensible for modules which don't export anything (except instances). - - - - - 9d3ef811 by Simon Marlow at 2002-05-28T10:12:50+00:00 [haddock @ 2002-05-28 10:12:50 by simonmar] Rename the module documentation properly (bug reported by Sven Panne). - - - - - ef03a1cc by Simon Marlow at 2002-05-28T10:13:04+00:00 [haddock @ 2002-05-28 10:13:04 by simonmar] Add some more test cases - - - - - 92baa0e8 by Simon Marlow at 2002-05-28T11:17:55+00:00 [haddock @ 2002-05-28 11:17:55 by simonmar] If an identifier doesn't lex, then just replace it by a DocString. - - - - - a3156213 by Simon Marlow at 2002-05-28T16:16:19+00:00 [haddock @ 2002-05-28 16:16:19 by simonmar] Only link to names in the current module which are actually listed in the documentation. A name may be exported but not present in the documentation if it is exported as part of a 'module M' export specifier. - - - - - 31acf941 by Simon Marlow at 2002-05-28T16:17:11+00:00 [haddock @ 2002-05-28 16:17:11 by simonmar] update - - - - - 7e474ebf by Sigbjorn Finne at 2002-05-28T22:42:08+00:00 [haddock @ 2002-05-28 22:42:08 by sof] Handle lone occurrences of '/', e.g., -- | This/that. [did this in the lexer rather than in the parser, as I couldn't see a way not to introduce an S/R conflict that way.] - - - - - 093f7e53 by Simon Marlow at 2002-05-29T09:09:49+00:00 [haddock @ 2002-05-29 09:09:49 by simonmar] Back out previous change until we can find a better way to do this. - - - - - 9234389c by Simon Marlow at 2002-05-29T13:19:06+00:00 [haddock @ 2002-05-29 13:19:06 by simonmar] Make the markup syntax a little more friendly: - single quotes are now interpreted literally unless they surround a valid Haskell identifier. So for example now there's no need to escape a single quote used as an apostrophe. - text to the right of a bird track is now literal (if you want marked-up text in a code block, use @...@). - - - - - b3333526 by Simon Marlow at 2002-05-29T13:38:51+00:00 [haddock @ 2002-05-29 13:38:51 by simonmar] Document recent changes to markup syntax - - - - - f93641d6 by Simon Marlow at 2002-05-29T15:27:18+00:00 [haddock @ 2002-05-29 15:27:18 by simonmar] Include the instances in abstract data types too - - - - - 613f21e3 by Simon Marlow at 2002-06-03T13:05:58+00:00 [haddock @ 2002-06-03 13:05:57 by simonmar] Allow exporting of individual class methods and record selectors. For these we have to invent the correct type signature, which we do in the simplest possible way (i.e. no context reduction nonsense in the class case). - - - - - 14b36807 by Simon Marlow at 2002-06-03T13:20:00+00:00 [haddock @ 2002-06-03 13:20:00 by simonmar] Fix linking to qualified names again (thanks to Sven Panne for pointing out the bug). - - - - - 95b10eac by Simon Marlow at 2002-06-03T13:46:48+00:00 [haddock @ 2002-06-03 13:46:48 by simonmar] Fix for exporting record selectors from a newtype declaration - - - - - 272f932e by Simon Marlow at 2002-06-03T13:56:38+00:00 [haddock @ 2002-06-03 13:56:38 by simonmar] update to version 0.3 - - - - - 1c0a3bed by Simon Marlow at 2002-06-03T14:05:07+00:00 [haddock @ 2002-06-03 14:05:07 by simonmar] Add changes in version 0.3 - - - - - 145b4626 by Simon Marlow at 2002-06-03T14:12:38+00:00 [haddock @ 2002-06-03 14:12:38 by simonmar] Render class names as proper binders - - - - - 052106b3 by Simon Marlow at 2002-06-03T14:15:10+00:00 [haddock @ 2002-06-03 14:15:10 by simonmar] update, and separate into bugs, features, and cosmetic items. - - - - - 854f4914 by Simon Marlow at 2002-06-03T14:16:13+00:00 [haddock @ 2002-06-03 14:16:13 by simonmar] More test cases - - - - - 466922c8 by Simon Marlow at 2002-06-03T14:16:56+00:00 [haddock @ 2002-06-03 14:16:56 by simonmar] Example from the paper - - - - - 9962a045 by Simon Marlow at 2002-06-03T14:17:49+00:00 [haddock @ 2002-06-03 14:17:49 by simonmar] A debugging version of the style-sheet, which gives some tables coloured backgrounds so we can see what's going on. - - - - - f16b79db by Simon Marlow at 2002-06-03T14:19:46+00:00 [haddock @ 2002-06-03 14:19:46 by simonmar] typo - - - - - 620db27b by Simon Marlow at 2002-06-03T14:48:32+00:00 [haddock @ 2002-06-03 14:48:32 by simonmar] oops, fix markup bugs - - - - - 53fd105c by Simon Marlow at 2002-06-05T09:05:07+00:00 [haddock @ 2002-06-05 09:05:07 by simonmar] Keep foreign imports when there is no export list (bug reported by Sven Panne). - - - - - 6d98989c by Simon Marlow at 2002-06-05T09:12:02+00:00 [haddock @ 2002-06-05 09:12:02 by simonmar] Identifiers in single quotes can be symbol names too (bug reported by Hal Daume). - - - - - 001811e5 by Sven Panne at 2002-06-08T14:03:36+00:00 [haddock @ 2002-06-08 14:03:36 by panne] Tiny workaround for the fact that Haddock currently ignores HsImportSpecs: Let the local_orig_env take precedence. This is no real solution at all, but improves things sometimes, e.g. in my GLUT documentation. :-) - - - - - 504d19c9 by Simon Marlow at 2002-06-11T09:23:25+00:00 [haddock @ 2002-06-11 09:23:25 by simonmar] portability nit - - - - - e13b5af4 by Simon Marlow at 2002-06-20T12:38:07+00:00 [haddock @ 2002-06-20 12:38:07 by simonmar] Empty declaration fixes. - - - - - f467a9b6 by Simon Marlow at 2002-06-20T12:39:02+00:00 [haddock @ 2002-06-20 12:39:01 by simonmar] Add support for a "prologue" - a description for the whole library, placed on the contents page before the module list. - - - - - b8dbfe20 by Simon Marlow at 2002-06-21T12:43:06+00:00 [haddock @ 2002-06-21 12:43:06 by simonmar] When we have a single code block paragraph, don't place it in <pre>..</pre>, just use <tt>..</tt> to avoid generating extra vertical white space in some browsers. - - - - - 4831dbbd by Simon Marlow at 2002-06-21T15:50:42+00:00 [haddock @ 2002-06-21 15:50:42 by simonmar] Add support for reading and writing interface files(!) This turned out to be quite easy, and necessary to get decent hyperlinks between the documentation for separate packages in the libraries. The functionality isn't quite complete yet: for a given package of modules, you'd like to say "the HTML for these modules lives in directory <dir>" (currently they are assumed to be all in the same place). Two new flags: --dump-interface=FILE dump an interface file in FILE --read-interface=FILE read interface from FILE an interface file describes *all* the modules being processed. Only the exported names are kept in the interface: if you re-export a name from a module in another interface the signature won't be copied. This is a compromise to keep the size of the interfaces sensible. Also, I added another useful option: --no-implicit-prelude avoids trying to import the Prelude. Previously this was the default, but now importing the Prelude from elsewhere makes sense if you also read in an interface containing the Prelude module, so Haddock imports the Prelude implicitly according to the Haskell spec. - - - - - d3640a19 by Sven Panne at 2002-06-23T14:54:00+00:00 [haddock @ 2002-06-23 14:54:00 by panne] Make it compile with newer GHCs - - - - - 780c506b by Sven Panne at 2002-06-23T15:44:31+00:00 [haddock @ 2002-06-23 15:44:31 by panne] Cleaned up build root handling and added more docs - - - - - 45290d2e by Simon Marlow at 2002-06-24T14:37:43+00:00 [haddock @ 2002-06-24 14:37:42 by simonmar] When reading an interface, allow a file path offset to be specified which represents the path to the HTML files for the modules specified by that interface. The path may be either relative (to the location of the HTML for this package), or absolute. The syntax is --read-interface=PATH,FILE where PATH is the path to the HTML, and FILE is the filename containing the interface. - - - - - 4e2b9ae6 by Simon Marlow at 2002-07-03T16:01:08+00:00 [haddock @ 2002-07-03 16:01:07 by simonmar] Handle import specs properly, include 'hiding'. Haddock now has a complete implementation of the Haskell module system (more or less; I won't claim it's 100% correct). - - - - - 9a9aa1a8 by Simon Marlow at 2002-07-03T16:18:16+00:00 [haddock @ 2002-07-03 16:18:16 by simonmar] Update - - - - - 560c3026 by Simon Marlow at 2002-07-04T14:56:10+00:00 [haddock @ 2002-07-04 14:56:10 by simonmar] Clean up the code that constructs the exported declarations, and fix a couple of bugs along the way. Now if you import a class hiding one of the methods, then re-export the class, the version in the documentation will correctly have the appropriate method removed. - - - - - 2c26e77d by Simon Marlow at 2002-07-04T15:26:13+00:00 [haddock @ 2002-07-04 15:26:13 by simonmar] More bugfixes to the export handling - - - - - 03e0710d by Simon Marlow at 2002-07-09T10:12:10+00:00 [haddock @ 2002-07-09 10:12:10 by simonmar] Don't require that the list type comes from "Prelude" for it to be treated as special syntax (sometimes it comes from Data.List or maybe even GHC.Base). - - - - - 44f3891a by Simon Marlow at 2002-07-09T10:12:51+00:00 [haddock @ 2002-07-09 10:12:51 by simonmar] commented-out debugging code - - - - - 97280873 by Krasimir Angelov at 2002-07-09T16:33:33+00:00 [haddock @ 2002-07-09 16:33:31 by krasimir] 'Microsoft HTML Help' support - - - - - 3dc04655 by Simon Marlow at 2002-07-10T09:40:56+00:00 [haddock @ 2002-07-10 09:40:56 by simonmar] Fix for rendering of the (->) type constructor, from Ross Paterson. - - - - - c9f149c6 by Simon Marlow at 2002-07-10T10:26:11+00:00 [haddock @ 2002-07-10 10:26:11 by simonmar] Tweaks to the MS Help support: the extra files are now only generated if you ask for them (--ms-help). - - - - - e8acc1e6 by Simon Marlow at 2002-07-10T10:57:10+00:00 [haddock @ 2002-07-10 10:57:10 by simonmar] Document all the new options since 0.3 - - - - - 8bb85544 by Simon Marlow at 2002-07-10T10:58:31+00:00 [haddock @ 2002-07-10 10:58:31 by simonmar] Sort the options a bit - - - - - abc0dd59 by Simon Marlow at 2002-07-15T09:19:38+00:00 [haddock @ 2002-07-15 09:19:38 by simonmar] Fix a bug in mkExportItems when processing a module without an explicit export list. We were placing one copy of a declaration for each binder in the declaration, which for a data type would mean one copy of the whole declaration per constructor or record selector. - - - - - dde65bb9 by Simon Marlow at 2002-07-15T09:54:16+00:00 [haddock @ 2002-07-15 09:54:16 by simonmar] merge rev. 1.35 - - - - - bd7eb8c4 by Simon Marlow at 2002-07-15T10:14:31+00:00 [haddock @ 2002-07-15 10:14:30 by simonmar] Be a bit more liberal in the kind of commenting styles we allow, as suggested by Malcolm Wallace. Mostly this consists of allowing doc comments either side of a separator token. In an export list, a section heading is now allowed before the comma, as well as after it. eg. module M where ( T(..) -- * a section heading , f -- * another section heading , g ) In record fields, doc comments are allowed anywhere (previously a doc-next was allowed only after the comma, and a doc-before was allowed only before the comma). eg. data R = C { -- | describes 'f' f :: Int -- | describes 'g' , g :: Int } - - - - - 8f6dfe34 by Simon Marlow at 2002-07-15T10:21:56+00:00 [haddock @ 2002-07-15 10:21:56 by simonmar] Mention alternative commenting styles. - - - - - fc515bb7 by Simon Marlow at 2002-07-15T16:16:50+00:00 [haddock @ 2002-07-15 16:16:50 by simonmar] Allow multiple sections/subsections before and after a comma in the export list. Also at the same time I made the syntax a little stricter (multiple commas now aren't allowed between export specs). - - - - - 80a97e74 by Simon Marlow at 2002-07-19T09:13:10+00:00 [haddock @ 2002-07-19 09:13:10 by simonmar] Allow special id's ([], (), etc.) to be used in an import declaration. - - - - - a69d7378 by Simon Marlow at 2002-07-19T09:59:02+00:00 [haddock @ 2002-07-19 09:59:02 by simonmar] Allow special id's ([], (), etc.) to be used in an import declarations. - - - - - d205fa60 by Simon Marlow at 2002-07-19T10:00:16+00:00 [haddock @ 2002-07-19 10:00:16 by simonmar] Relax the restrictions which require doc comments to be followed by semi colons - in some cases this isn't necessary. Now you can write module M where { -- | some doc class C where {} } without needing to put a semicolon before the class declaration. - - - - - e9301e14 by Simon Marlow at 2002-07-23T08:24:09+00:00 [haddock @ 2002-07-23 08:24:09 by simonmar] A new TODO list item - - - - - e5d77586 by Simon Marlow at 2002-07-23T08:40:56+00:00 [haddock @ 2002-07-23 08:40:56 by simonmar] - update the acknowledgements - remove the paragraph that described how to use explicit layout with doc comments; it isn't relevant any more. - - - - - 78a94137 by Simon Marlow at 2002-07-23T08:43:02+00:00 [haddock @ 2002-07-23 08:43:02 by simonmar] more tests - - - - - 5c320927 by Simon Marlow at 2002-07-23T08:43:26+00:00 [haddock @ 2002-07-23 08:43:26 by simonmar] Updates for version 0.4 - - - - - 488e99ae by Simon Marlow at 2002-07-23T09:10:46+00:00 [haddock @ 2002-07-23 09:10:46 by simonmar] Fix the %changelog (rpm complained that it wasn't in the right order) - - - - - a77bb373 by Simon Marlow at 2002-07-23T09:12:38+00:00 [haddock @ 2002-07-23 09:12:38 by simonmar] Another item for the TODO list - - - - - f1ec1813 by Simon Marlow at 2002-07-23T10:18:46+00:00 [haddock @ 2002-07-23 10:18:46 by simonmar] Add a version banner when invoked with -v - - - - - 1d44cadf by Simon Marlow at 2002-07-24T09:28:19+00:00 [haddock @ 2002-07-24 09:28:19 by simonmar] Remove ^Ms - - - - - 4d8d5e94 by Simon Marlow at 2002-07-24T09:42:18+00:00 [haddock @ 2002-07-24 09:42:17 by simonmar] Patches to quieten ghc -Wall, from those nice folks at Galois. - - - - - d6edc43e by Simon Marlow at 2002-07-25T14:37:29+00:00 [haddock @ 2002-07-25 14:37:28 by simonmar] Patch to allow simple hyperlinking to an arbitrary location in another module's documentation, from Volker Stolz. Now in a doc comment: #foo# creates <a name="foo"></a> And you can use the form "M\#foo" to hyperlink to the label 'foo' in module 'M'. Note that the backslash is necessary for now. - - - - - b34d18fa by Simon Marlow at 2002-08-02T09:08:22+00:00 [haddock @ 2002-08-02 09:08:22 by simonmar] The <TT> and <PRE> environments seem to use a font that is a little too small in IE. Compensate. (suggestion from Daan Leijen). - - - - - 8106b086 by Simon Marlow at 2002-08-02T09:25:23+00:00 [haddock @ 2002-08-02 09:25:20 by simonmar] Remove <P>..</P> from around list items, to reduce excess whitespace between the items of bulleted and ordered lists. (Suggestion from Daan Leijen). - - - - - c1acff8f by Simon Marlow at 2002-08-05T09:03:49+00:00 [haddock @ 2002-08-05 09:03:49 by simonmar] update - - - - - f968661c by Simon Marlow at 2002-11-11T09:32:57+00:00 [haddock @ 2002-11-11 09:32:57 by simonmar] Fix cut-n-pasto - - - - - 12d02619 by Simon Marlow at 2002-11-13T09:49:46+00:00 [haddock @ 2002-11-13 09:49:46 by simonmar] Small bugfix in the --read-interface option parsing from Brett Letner. - - - - - 30e32d5e by Ross Paterson at 2003-01-16T15:07:57+00:00 [haddock @ 2003-01-16 15:07:57 by ross] Adjust for the new exception libraries (as well as the old ones). - - - - - 871f65df by Sven Panne at 2003-02-20T21:31:40+00:00 [haddock @ 2003-02-20 21:31:40 by panne] * Add varsyms and consyms to index * Exclude empty entries from index - - - - - bc42cc87 by Sven Panne at 2003-02-24T21:26:29+00:00 [haddock @ 2003-02-24 21:26:29 by panne] Don't convert a "newtype" to a single-constructor "data" for non-abstractly exported types, they are quite different regarding strictness/pattern matching. Now a "data" without any constructors is only emitted for an abstractly exported type, regardless if it is actually a "newtype" or a "data". - - - - - 0c2a1d99 by Sven Panne at 2003-03-08T19:02:38+00:00 [haddock @ 2003-03-08 19:02:38 by panne] Fixed some broken/redirected/canonicalized links found by a very picky link checker. - - - - - 25459269 by Sven Panne at 2003-03-09T21:13:43+00:00 [haddock @ 2003-03-09 21:13:43 by panne] Don't append a fragment to non-defining index entries, only documents with a defining occurrence have a name anchor. - - - - - 6be4db86 by Sven Panne at 2003-03-10T21:34:25+00:00 [haddock @ 2003-03-10 21:34:24 by panne] Escape fragments. This fixes e.g. links to operators. - - - - - eb12972c by Ross Paterson at 2003-04-25T10:50:06+00:00 [haddock @ 2003-04-25 10:50:05 by ross] An 80% solution to generating derived instances. A complete solution would duplicate the instance inference logic, but if a type variable occurs as a constructor argument, then we can just propagate the derived class to the variable. But we know nothing of the constraints on any type variables that occur elsewhere. For example, the declarations data Either a b = Left a | Right b deriving (Eq, Ord) data Ptr a = Ptr Addr# deriving (Eq, Ord) newtype IORef a = IORef (STRef RealWorld a) deriving Eq yield the instances (Eq a, Eq b) => Eq (Either a b) (Ord a, Ord b) => Ord (Either a b) Eq (Ptr a) Ord (Ptr a) (??? a) => Eq (IORef a) The last example shows the limits of this local analysis. Note that a type variable may be in both categories: then we know a constraint, but there may be more, or a stronger constraint, e.g. data Tree a = Node a [Tree a] deriving Eq yields (Eq a, ??? a) => Eq (Tree a) - - - - - de886f78 by Simon Marlow at 2003-04-25T11:17:55+00:00 [haddock @ 2003-04-25 11:17:55 by simonmar] Some updates, including moving the derived instance item down to the bottom of the list now that Ross has contributed some code that does the job for common cases. - - - - - 1b52cffd by Simon Marlow at 2003-04-30T14:02:32+00:00 [haddock @ 2003-04-30 14:02:32 by simonmar] When installing on Windows, run cygpath over $(HADDOCKLIB) so that haddock (a mingw program, built by GHC) can understand it. You still need to be in a cygwin environment to run Haddock, because of the shell script wrapper. - - - - - d4f638de by Simon Marlow at 2003-05-06T10:04:47+00:00 [haddock @ 2003-05-06 10:04:47 by simonmar] Catch another case of a paragraph containing just a DocMonospaced that should turn into a DocCodeBlock. - - - - - 4162b2b9 by Simon Marlow at 2003-05-06T10:11:44+00:00 [haddock @ 2003-05-06 10:11:44 by simonmar] Add some more code-block tests. - - - - - 4f5802c8 by Simon Marlow at 2003-05-06T10:14:52+00:00 [haddock @ 2003-05-06 10:14:52 by simonmar] Don't turn a single DocCodeBlock into a DocMonospaced, because that tends to remove the line breaks in the code. - - - - - ef8c45f7 by Simon Marlow at 2003-05-21T15:07:21+00:00 [haddock @ 2003-05-21 15:07:21 by simonmar] Only omit the module contents when there are no section headings at all. - - - - - bcee1e75 by Sigbjorn Finne at 2003-05-30T16:50:45+00:00 [haddock @ 2003-05-30 16:50:45 by sof] cygpath: for now, steer clear of --mixed - - - - - 30567af3 by Sigbjorn Finne at 2003-05-30T17:59:28+00:00 [haddock @ 2003-05-30 17:59:28 by sof] oops, drop test defn from prev commit - - - - - b0856e7d by Simon Marlow at 2003-06-03T09:55:26+00:00 [haddock @ 2003-06-03 09:55:26 by simonmar] Two small fixes to make the output valid HTML 4.01 (transitional). Thanks to Malcolm Wallace for pointing out the problems. - - - - - 70e137ea by Simon Marlow at 2003-07-28T13:30:35+00:00 [haddock @ 2003-07-28 13:30:35 by simonmar] Add tests for a couple of bugs. - - - - - 122bd578 by Simon Marlow at 2003-07-28T13:31:25+00:00 [haddock @ 2003-07-28 13:31:25 by simonmar] Add documentation for anchors. - - - - - 0bd27cb2 by Simon Marlow at 2003-07-28T13:31:46+00:00 [haddock @ 2003-07-28 13:31:46 by simonmar] Update - - - - - 08052d42 by Simon Marlow at 2003-07-28T13:32:12+00:00 [haddock @ 2003-07-28 13:32:12 by simonmar] layout tweak. - - - - - 13942749 by Simon Marlow at 2003-07-28T13:33:03+00:00 [haddock @ 2003-07-28 13:33:03 by simonmar] Differentiate links to types/classes from links to variables/constructors with a prefix ("t:" and "v:" respectively). - - - - - d7f493b9 by Simon Marlow at 2003-07-28T13:35:17+00:00 [haddock @ 2003-07-28 13:35:16 by simonmar] When a module A exports another module's contents via 'module B', then modules which import entities from B re-exported by A should link to B.foo rather than A.foo. See examples/Bug2.hs. - - - - - d94cf705 by Simon Marlow at 2003-07-28T13:36:14+00:00 [haddock @ 2003-07-28 13:36:14 by simonmar] Update to version 0.5 - - - - - dbb776cd by Sven Panne at 2003-07-28T14:02:43+00:00 [haddock @ 2003-07-28 14:02:43 by panne] * Updated to version 0.5 * Automagically generate configure if it is not there - - - - - 6cfeee53 by Simon Marlow at 2003-07-28T14:32:43+00:00 [haddock @ 2003-07-28 14:32:42 by simonmar] Update to avoid using hslibs with GHC >= 5.04 - - - - - a1ce838f by Simon Marlow at 2003-07-28T14:33:37+00:00 [haddock @ 2003-07-28 14:33:37 by simonmar] Update for 0.5 - - - - - c0fe6493 by Simon Marlow at 2003-07-28T14:53:22+00:00 [haddock @ 2003-07-28 14:53:22 by simonmar] Markup fix - - - - - 6ea31596 by Sven Panne at 2003-07-28T16:40:45+00:00 [haddock @ 2003-07-28 16:40:45 by panne] Make it compile with GHC >= 6.01 - - - - - afcd30fc by Simon Marlow at 2003-07-30T15:04:52+00:00 [haddock @ 2003-07-30 15:04:52 by simonmar] Pay attention to import specs when building the the import env, as well as the orig env. This may fix some wrong links in documentation when import specs are being used. - - - - - 17c3137f by Simon Marlow at 2003-07-30T16:05:41+00:00 [haddock @ 2003-07-30 16:05:40 by simonmar] Rename instances based on the import_env for the module in which they are to be displayed. This should give, in many cases, better links for the types and classes mentioned in the instance head. This involves keeping around the import_env in the iface until the end, because instances are not collected up until all the modules have been processed. Fortunately it doesn't seem to affect performance much. Instance heads are now attached to ExportDecls, rather than the HTML backend passing around a separate mapping for instances. This is a cleanup. - - - - - 3d3b5c87 by Sven Panne at 2003-08-04T10:18:24+00:00 [haddock @ 2003-08-04 10:18:24 by panne] Don't print parentheses around one-element contexts - - - - - 9e3f3f2d by Simon Marlow at 2003-08-04T12:59:47+00:00 [haddock @ 2003-08-04 12:59:47 by simonmar] A couple of TODOs. - - - - - e9d8085c by Simon Marlow at 2003-08-05T14:10:31+00:00 [haddock @ 2003-08-05 14:10:31 by simonmar] I'm not sure why, but it seems that the index entries for non-defining occurrences of entities did not have an anchor - the link just pointed to the module. This fixes it. - - - - - ff5c7d6d by Simon Marlow at 2003-08-15T14:42:59+00:00 [haddock @ 2003-08-15 14:42:59 by simonmar] Convert the lexer to Alex, and fix a bug in the process. - - - - - 1aa077bf by Simon Marlow at 2003-08-15T15:00:18+00:00 [haddock @ 2003-08-15 15:00:18 by simonmar] Update - - - - - d3de1e38 by Simon Marlow at 2003-08-15T15:01:03+00:00 [haddock @ 2003-08-15 15:01:03 by simonmar] wibbles - - - - - b40ece3b by Simon Marlow at 2003-08-18T10:04:47+00:00 [haddock @ 2003-08-18 10:04:47 by simonmar] Lex the 'mdo' keyword as 'do'. - - - - - 8f9a1146 by Simon Marlow at 2003-08-18T11:48:24+00:00 [haddock @ 2003-08-18 11:48:24 by simonmar] Two bugs from Sven. - - - - - ea54ebc0 by Simon Marlow at 2003-08-18T11:48:46+00:00 [haddock @ 2003-08-18 11:48:46 by simonmar] Fixes to the new lexer. - - - - - d5f6a4b5 by Simon Marlow at 2003-08-19T09:09:03+00:00 [haddock @ 2003-08-19 09:09:03 by simonmar] Further wibbles to the syntax. - - - - - 6bbdadb7 by Sven Panne at 2003-08-26T18:45:35+00:00 [haddock @ 2003-08-26 18:45:35 by panne] Use autoreconf instead of autoconf - - - - - 32e889cb by Sven Panne at 2003-08-26T19:01:19+00:00 [haddock @ 2003-08-26 19:01:18 by panne] Made option handling a bit more consistent with other tools, in particular: Every program in fptools should output * version info on stdout and terminate successfully when -V or --version * usage info on stdout and terminate successfully when -? or --help * usage info on stderr and terminate unsuccessfully when an unknown option is given. - - - - - 5d156a91 by Sven Panne at 2003-08-26T19:20:55+00:00 [haddock @ 2003-08-26 19:20:55 by panne] Make it *very* clear that we terminate when given a -V/--version flag - - - - - e6577265 by Sven Panne at 2003-08-27T07:50:03+00:00 [haddock @ 2003-08-27 07:50:02 by panne] * Made -D a short option for --dump-interface. * Made -m a short option for --ms-help. * Made -n a short option for --no-implicit-prelude. * Made -c a short option for --css. * Removed DocBook options from executable (they didn't do anything), but mark them as reserved in the docs. Note that the short option for DocBook output is now -S (from SGML) instead of -d. The latter is now a short option for --debug. * The order of the Options in the documentation now matches the order printed by Haddock itself. Note: Although changing the names of options is often a bad idea, I'd really like to make the options for the programs in fptools more consistent and compatible to the ones used in common GNU programs. - - - - - d303ff98 by Simon Marlow at 2003-09-10T08:23:48+00:00 [haddock @ 2003-09-10 08:23:48 by simonmar] Add doc subdir. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 9a70e46a by Simon Marlow at 2003-09-10T08:24:32+00:00 [haddock @ 2003-09-10 08:24:32 by simonmar] Install these files in $(datadir), not $(libdir), since they're architecture independent. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - bbb87e7a by Simon Marlow at 2003-09-10T08:25:31+00:00 [haddock @ 2003-09-10 08:25:31 by simonmar] Haddock's supplementary HTML bits now live in $(datadir), not $(libdir). Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 3587c24b by Simon Marlow at 2003-09-22T10:34:38+00:00 [haddock @ 2003-09-22 10:34:38 by simonmar] Allow installing of docs. - - - - - d510b517 by Sven Panne at 2003-10-11T08:10:44+00:00 [haddock @ 2003-10-11 08:10:44 by panne] Include architecture-independent files in file list - - - - - 187d7618 by Sigbjorn Finne at 2003-10-20T17:19:24+00:00 [haddock @ 2003-10-20 17:19:22 by sof] support for i-parameters + zip comprehensions - - - - - b6c7a273 by Simon Marlow at 2003-11-03T14:24:24+00:00 [haddock @ 2003-11-03 14:24:24 by simonmar] Update TODO file. - - - - - 58513e33 by Simon Marlow at 2003-11-05T11:22:04+00:00 [haddock @ 2003-11-05 11:22:04 by simonmar] Remove the last of the uses of 'trace' to emit warnings, and tidy up a couple of places where duplicate warnings were being emitted. - - - - - 33a78846 by Simon Marlow at 2003-11-05T11:30:53+00:00 [haddock @ 2003-11-05 11:30:52 by simonmar] - Suppress warnings about unknown imported modules by default. - Add a -v/--verbose flag to re-enable these warnings. The general idea is to suppress the "Warning: unknown module: Prelude" warnings which most Haddock users will see every time, and which aren't terribly useful. - - - - - a969de7f by Simon Marlow at 2003-11-05T12:30:28+00:00 [haddock @ 2003-11-05 12:30:28 by simonmar] - Remove the emboldening of index entries for defining locations. This isn't useful, and breaks abstractions. - If an entity is re-exported by a module but the module doesn't include documentation for that entity (perhaps because it is re-exported by 'module M'), then don't attempt to hyperlink to the documentation from the index. Instead, just list that module in the index, to indicate that the entity is exported from there. - - - - - f14ea82a by Simon Marlow at 2003-11-05T15:15:59+00:00 [haddock @ 2003-11-05 15:15:59 by simonmar] Index overhaul: - no more separate type/class and variable/function indices - the index now makes a distinction between different entities with the same name. One example is a type constructor with the same name as a data constructor, but another example is simply a function with the same name exported by two different modules. For example, the index entry for 'catch' now looks like this: catch 1 (Function) Control.Exception 2 (Function) GHC.Exception, Prelude, System.IO, System.IO.Error making it clear that there are two different 'catch'es, but one of them is exported by several modules. - Each index page now has the index contents (A B C ...) at the top. Please let me know if you really hate any of this. - - - - - 01a25ca6 by Simon Marlow at 2003-11-05T15:16:38+00:00 [haddock @ 2003-11-05 15:16:38 by simonmar] Update - - - - - 1a7ccb86 by Simon Marlow at 2003-11-05T17:16:05+00:00 [haddock @ 2003-11-05 17:16:04 by simonmar] Support for generating a single unified index for several packages. --use-index=URL turns off normal index generation, causes Index links to point to URL. --gen-index generates an combined index from the specified interfaces. Currently doesn't work exactly right, because the interfaces don't contain the iface_reexported info. I'll need to fix that up. - - - - - a2bca16d by Simon Marlow at 2003-11-06T10:44:52+00:00 [haddock @ 2003-11-06 10:44:52 by simonmar] Include iface_reexported in the .haddock file. This unfortunately bloats the file (40% for base). If this gets to be a problem we can always apply the dictionary trick that GHC uses for squashing .hi files. - - - - - 0a09c293 by Simon Marlow at 2003-11-06T12:39:47+00:00 [haddock @ 2003-11-06 12:39:46 by simonmar] - Add definition lists, marked up like this: -- | This is a definition list: -- -- [@foo@] The description of @foo at . -- -- [@bar@] The description of @bar at . Cunningly, the [] characters are not treated specially unless a [ is found at the beginning of a paragraph, in which case the ] becomes special in the following text. - Add --use-contents and --gen-contents, along the lines of --use-index and --gen-index added yesterday. Now we can generate a combined index and contents for the whole of the hierarchical libraries, and in theory the index/contents on the system could be updated as new packages are added. - - - - - fe1b3460 by Simon Marlow at 2003-11-06T14:47:36+00:00 [haddock @ 2003-11-06 14:47:36 by simonmar] Remove the 'Parent' button - it is of dubious use, and often points into thin air. - - - - - db6d762f by Simon Marlow at 2003-11-06T16:48:14+00:00 [haddock @ 2003-11-06 16:48:11 by simonmar] - Include the OptHide setting in the interface, so we don't include hidden modules in the combined index/contents. - Add a -k/--package flag to set the package name for the current set of modules. The package name for each module is now shown in the right-hand column of the contents, in a combined contents page. - - - - - 7d71718b by Simon Marlow at 2003-11-06T16:50:28+00:00 [haddock @ 2003-11-06 16:50:28 by simonmar] Add -k/--package docs - - - - - ef43949d by Simon Marlow at 2003-11-06T16:51:23+00:00 [haddock @ 2003-11-06 16:51:23 by simonmar] Bump to 0.6 - - - - - 1c419e06 by Simon Marlow at 2003-11-06T16:51:50+00:00 [haddock @ 2003-11-06 16:51:50 by simonmar] update - - - - - 69422327 by Simon Marlow at 2003-11-10T14:41:06+00:00 [haddock @ 2003-11-10 14:41:05 by simonmar] Re-exporting names from a different package is problematic, because we don't have access to the full documentation for the entity. Currently Haddock just ignores entities with no documentation, but this results in bogus-looking empty documentation for many of the modules in the haskell98 package. So: - the documentation will now just list the name, as a link pointing to the location of the actual documentation. - now we don't attempt to link to these re-exported entities if they are referred to by the current module. Additionally: - If there is no documentation in the current module, include just the Synopsis section (rather than just the documentation section, as it was before). This just looks nicer and was on the TODO list. - - - - - 3c3fc433 by Simon Marlow at 2003-11-10T14:51:59+00:00 [haddock @ 2003-11-10 14:51:59 by simonmar] Fix for getReExports: take into account names which are not visible because they are re-exported from a different package. - - - - - 31c8437b by Simon Marlow at 2003-11-10T15:10:53+00:00 [haddock @ 2003-11-10 15:10:53 by simonmar] Version 0.6 changes - - - - - a7c2430b by Simon Marlow at 2003-11-10T15:15:58+00:00 [haddock @ 2003-11-10 15:15:58 by simonmar] getReExports: one error case that isn't - - - - - 00cc459c by Simon Marlow at 2003-11-10T16:15:19+00:00 [haddock @ 2003-11-10 16:15:18 by simonmar] copyright update - - - - - ca62408d by Simon Marlow at 2003-11-11T09:57:25+00:00 [haddock @ 2003-11-11 09:57:25 by simonmar] Version 0.6 - - - - - 3acbf818 by Simon Marlow at 2003-11-11T12:10:44+00:00 [haddock @ 2003-11-11 12:10:44 by simonmar] Go back to producing just the documentation section, rather than just the synopsis section, for a module with no documentation annotations. One reason is that the synopsis section tries to link each entity to its documentation on the same page. Also, the doc section anchors each entity, and it lists instances which the synopsis doesn't. - - - - - 6c90abc2 by Simon Marlow at 2003-11-12T10:03:39+00:00 [haddock @ 2003-11-12 10:03:39 by simonmar] 2002 -> 2003 - - - - - 090bbc4c by Simon Marlow at 2003-11-28T12:08:00+00:00 [haddock @ 2003-11-28 12:08:00 by simonmar] update - - - - - 8096a832 by Simon Marlow at 2003-11-28T12:09:58+00:00 [haddock @ 2003-11-28 12:09:58 by simonmar] Fix some of the problems with Haddock generating pages that are too wide. Now we only specify 'nowrap' when it is necessary to avoid a code box getting squashed up by the text to the right of it. - - - - - 35294929 by Sven Panne at 2003-12-29T17:16:31+00:00 [haddock @ 2003-12-29 17:16:31 by panne] Updated my email address - - - - - cdb697bf by Simon Marlow at 2004-01-08T10:14:24+00:00 [haddock @ 2004-01-08 10:14:24 by simonmar] Add instructions for using GHC to pre-process source for feeding to Haddock. - - - - - 8dfc491f by Simon Marlow at 2004-01-09T12:45:46+00:00 [haddock @ 2004-01-09 12:45:46 by simonmar] Add -optP-P to example ghc command line. - - - - - ac41b820 by Simon Marlow at 2004-02-03T11:02:03+00:00 [haddock @ 2004-02-03 11:02:03 by simonmar] Fix bug in index generation - - - - - f4e7edcb by Simon Marlow at 2004-02-10T11:51:16+00:00 [haddock @ 2004-02-10 11:51:16 by simonmar] Don't throw away whitespace at the beginning of a line (experimental fix). - - - - - 68e212d2 by Simon Marlow at 2004-02-10T12:10:08+00:00 [haddock @ 2004-02-10 12:10:08 by simonmar] Fix for previous commit: I now realise why the whitespace was stripped from the beginning of the line. Work around it. - - - - - e7d7f2df by Sven Panne at 2004-02-10T18:38:45+00:00 [haddock @ 2004-02-10 18:38:45 by panne] Make Haddock link with the latest relocated monad transformer package - - - - - 992d4225 by Simon Marlow at 2004-02-16T10:21:35+00:00 [haddock @ 2004-02-16 10:21:35 by simonmar] Add a TODO - - - - - 1ac55326 by Simon Marlow at 2004-03-12T11:33:39+00:00 [haddock @ 2004-03-12 11:33:39 by simonmar] Add an item. - - - - - 0478e903 by Simon Marlow at 2004-03-15T12:24:05+00:00 [haddock @ 2004-03-15 12:24:05 by simonmar] Add an item. - - - - - 6f26d21a by Simon Marlow at 2004-03-18T14:21:29+00:00 [haddock @ 2004-03-18 14:21:29 by simonmar] Fix URL - - - - - 19b6bb99 by Simon Marlow at 2004-03-22T14:09:03+00:00 [haddock @ 2004-03-22 14:09:03 by simonmar] getReExports was bogus: we should really look in the import_env to find the documentation for an entity which we are re-exporting without documentation. Suggested by: Ross Paterson (patch modified by me). - - - - - 5c756031 by Simon Marlow at 2004-03-24T09:42:11+00:00 [haddock @ 2004-03-24 09:42:10 by simonmar] hiding bug from Ross Paterson (fixed in rev 1.59 of Main.hs) - - - - - 1b692e6c by Simon Marlow at 2004-03-24T10:10:50+00:00 [haddock @ 2004-03-24 10:10:50 by simonmar] mkExportItems fix & simplification: we should be looking at the actual exported names (calculated earlier) to figure out which subordinates of a declaration are exported. This means that if you export a record, and name its fields separately in the export list, the fields will still be visible in the documentation for the constructor. - - - - - 90e5e294 by Simon Marlow at 2004-03-24T10:12:08+00:00 [haddock @ 2004-03-24 10:12:08 by simonmar] Make restrictCons take into account record field names too (removing a ToDo). - - - - - 2600efa4 by Simon Marlow at 2004-03-24T10:16:17+00:00 [haddock @ 2004-03-24 10:16:17 by simonmar] Record export tests. - - - - - 6a8575c7 by Simon Marlow at 2004-03-25T09:35:14+00:00 [haddock @ 2004-03-25 09:35:14 by simonmar] restrictTo: fix for restricting a newtype with a record field. - - - - - dcf55a8d by Simon Marlow at 2004-03-25T10:01:42+00:00 [haddock @ 2004-03-25 10:01:42 by simonmar] Fix duplicate instance bug - - - - - f49aa758 by Simon Marlow at 2004-03-25T10:02:41+00:00 [haddock @ 2004-03-25 10:02:41 by simonmar] Duplicate instance bug. - - - - - 7b87344c by Simon Marlow at 2004-03-25T10:29:56+00:00 [haddock @ 2004-03-25 10:29:56 by simonmar] If a name is imported from two places, one hidden and one not, choose the unhidden one to link to. Also, when there's only a hidden module to link to, don't try linking to it. - - - - - 40f44d7b by Simon Marlow at 2004-03-25T15:17:24+00:00 [haddock @ 2004-03-25 15:17:23 by simonmar] Add support for collaspible parts of the page, with a +/- button and a bit of JavaScript. Make the instances collapsible, and collapse them by default. This makes documentation with long lists of instances (eg. the Prelude) much easier to read. Maybe we should give other documentation sections the same treatment. - - - - - 9b64dc0f by Simon Marlow at 2004-03-25T15:20:55+00:00 [haddock @ 2004-03-25 15:20:55 by simonmar] Update - - - - - c2fff7f2 by Simon Marlow at 2004-03-25T15:45:10+00:00 [haddock @ 2004-03-25 15:45:10 by simonmar] Eliminate some unnecessary spaces in the HTML rendering - - - - - b7948ff0 by Simon Marlow at 2004-03-25T16:00:37+00:00 [haddock @ 2004-03-25 16:00:36 by simonmar] Remove all that indentation in the generated HTML to keep the file sizes down. - - - - - da2bb4ca by Sven Panne at 2004-03-27T09:57:58+00:00 [haddock @ 2004-03-27 09:57:57 by panne] Added the new-born haddock.js to the build process and the documentation. - - - - - b99e6f8c by Sven Panne at 2004-03-27T10:32:20+00:00 [haddock @ 2004-03-27 10:32:20 by panne] "type" is a required attribute of the "script" element - - - - - 562b185a by Sven Panne at 2004-03-27T12:52:34+00:00 [haddock @ 2004-03-27 12:52:34 by panne] Add a doctype for the contents page, too. - - - - - f6a99c2d by Simon Marlow at 2004-04-14T10:03:25+00:00 [haddock @ 2004-04-14 10:03:25 by simonmar] fix for single-line comment syntax - - - - - de366303 by Simon Marlow at 2004-04-20T13:08:04+00:00 [haddock @ 2004-04-20 13:08:04 by simonmar] Allow a 'type' declaration to include documentation comments. These will be ignored by Haddock, but at least one user (Johannes Waldmann) finds this feature useful, and it's easy to add. - - - - - fd78f51e by Simon Marlow at 2004-05-07T15:14:56+00:00 [haddock @ 2004-05-07 15:14:56 by simonmar] - update copyright - add version to abstract - - - - - 59f53e32 by Sven Panne at 2004-05-09T14:39:53+00:00 [haddock @ 2004-05-09 14:39:53 by panne] Fix the fix for single-line comment syntax, ------------------------------------------- is now a valid comment line again. - - - - - 8b18f2fe by Simon Marlow at 2004-05-10T10:11:51+00:00 [haddock @ 2004-05-10 10:11:51 by simonmar] Update - - - - - 225a491d by Ross Paterson at 2004-05-19T13:10:23+00:00 [haddock @ 2004-05-19 13:10:23 by ross] Make the handling of "deriving" slightly smarter, by ignoring data constructor arguments that are identical to the lhs. Now handles things like data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving ... - - - - - 37588686 by Mike Thomas at 2004-05-21T06:38:14+00:00 [haddock @ 2004-05-21 06:38:14 by mthomas] Windows exe extensions (bin remains for Unix). - - - - - cf2b9152 by Simon Marlow at 2004-05-25T09:34:54+00:00 [haddock @ 2004-05-25 09:34:54 by simonmar] Add some TODO items - - - - - 4d29cdfc by Simon Marlow at 2004-05-25T10:41:46+00:00 [haddock @ 2004-05-25 10:41:46 by simonmar] Complain if -h is used with --gen-index or --gen-contents, because it'll overwrite the new index/contents. - - - - - 2e0771e0 by Mike Thomas at 2004-05-28T20:17:55+00:00 [haddock @ 2004-05-28 20:17:55 by mthomas] Windows: search for templates in executable directory. Unix: Haddock tries cwd first rather than error if no -l arg. - - - - - 8d10bde1 by Sven Panne at 2004-06-05T16:53:34+00:00 [haddock @ 2004-06-05 16:53:34 by panne] Misc. rpm spec file cleanup, including: * make BuildRoot handling more consistent * added default file attributes * consistent defines and tags - - - - - 59974349 by Sven Panne at 2004-06-05T18:01:00+00:00 [haddock @ 2004-06-05 18:01:00 by panne] More rpm spec file cleanup, including: * added some BuildRequires * changed packager to me, so people can complain at the right place :-] * consistently refer to haskell.org instead of www.haskell.org - - - - - b94d4903 by Simon Marlow at 2004-07-01T11:08:58+00:00 [haddock @ 2004-07-01 11:08:57 by simonmar] Update to the +/- buttons: use a resized image rather than a <button>. Still seeing some strange effects in Konqueror, so might need to use a fixed-size image instead. - - - - - d5278f67 by Sven Panne at 2004-07-04T15:15:55+00:00 [haddock @ 2004-07-04 15:15:55 by panne] Install pictures for +/- pictures, too (JPEG is a strange format for graphics like this, I would have expected GIF or PNG here.) Things look fine with Konqueror and Netscape on Linux now, the only downside is that the cursor doesn't change when positioned above the "button". - - - - - 46dec6c5 by Sven Panne at 2004-07-13T17:59:28+00:00 [haddock @ 2004-07-13 17:59:28 by panne] A quote is a valid part of a Haskell identifier, but it would interfere with an ECMA script string delimiter, so escape it there. - - - - - 1d7bc432 by Simon Marlow at 2004-07-22T08:54:06+00:00 [haddock @ 2004-07-22 08:54:06 by simonmar] Add single quote to $ident, so you can say eg. 'foldl'' to refer to foldl' (the longest match rule is our friend). Bug reported by Adrian Hey <ahey at iee.org> - - - - - f183618b by Krasimir Angelov at 2004-07-27T22:59:35+00:00 [haddock @ 2004-07-27 22:58:23 by krasimir] Add basic support for Microsoft HTML Help 2.0 - - - - - d515d0c2 by Krasimir Angelov at 2004-07-27T23:02:36+00:00 [haddock @ 2004-07-27 23:02:36 by krasimir] escape names in the index - - - - - a5f1be23 by Krasimir Angelov at 2004-07-27T23:05:21+00:00 [haddock @ 2004-07-27 23:05:21 by krasimir] Add jsFile, plusFile and minusFile to the file list - - - - - c4fb4881 by Krasimir Angelov at 2004-07-28T22:12:10+00:00 [haddock @ 2004-07-28 22:12:09 by krasimir] bugfix. Move contentsHtmlFile, indexHtmlFile and subIndexHtmlFile functions to HaddockUtil.hs module to make them accessible from HaddockHH2.hs - - - - - 64d30b1d by Krasimir Angelov at 2004-07-30T22:15:47+00:00 [haddock @ 2004-07-30 22:15:45 by krasimir] more stuffs - support for separated compilation of packages - the contents page now uses DHTML TreeView - fixed copyFile bug - - - - - 133c8c5c by Krasimir Angelov at 2004-07-31T12:04:38+00:00 [haddock @ 2004-07-31 12:04:37 by krasimir] make the DHtmlTree in contents page more portable. The +/- buttons are replaced with new images which looks more beatiful. - - - - - 79040963 by Krasimir Angelov at 2004-07-31T13:10:20+00:00 [haddock @ 2004-07-31 13:10:20 by krasimir] Make DHtmlTree compatible with Mozila browser - - - - - 1a55dc90 by Krasimir Angelov at 2004-07-31T14:52:55+00:00 [haddock @ 2004-07-31 14:52:55 by krasimir] fix - - - - - 85ce0237 by Krasimir Angelov at 2004-07-31T14:53:28+00:00 [haddock @ 2004-07-31 14:53:28 by krasimir] HtmlHelp 1.x - - - - - 3c0c53ba by Krasimir Angelov at 2004-07-31T20:35:21+00:00 [haddock @ 2004-07-31 20:35:21 by krasimir] Added support for DevHelp - - - - - d42b5af1 by Krasimir Angelov at 2004-07-31T21:17:51+00:00 [haddock @ 2004-07-31 21:17:51 by krasimir] Document new features in HtmlHelp - - - - - 790fe21e by Krasimir Angelov at 2004-08-01T15:14:02+00:00 [haddock @ 2004-08-01 15:14:02 by krasimir] add missing imports - - - - - fd7cc6bc by Krasimir Angelov at 2004-08-01T19:52:08+00:00 [haddock @ 2004-08-01 19:52:06 by krasimir] fix some bugs. Now I have got the entire libraries documentation in HtmlHelp 2.0 format. - - - - - 94ad7ac8 by Krasimir Angelov at 2004-08-01T19:53:50+00:00 [haddock @ 2004-08-01 19:53:50 by krasimir] I forgot to add the new +/- images - - - - - f0c65388 by Krasimir Angelov at 2004-08-02T16:25:53+00:00 [haddock @ 2004-08-02 16:25:53 by krasimir] Add root node to the table of contents. All modules in tree are not children of the root - - - - - f50bd85d by Sven Panne at 2004-08-02T18:17:46+00:00 [haddock @ 2004-08-02 18:17:46 by panne] Mainly DocBook fixes - - - - - 09527ce3 by Sven Panne at 2004-08-02T20:02:29+00:00 [haddock @ 2004-08-02 20:02:29 by panne] Fixed -o/--odir handling. Generating the output, especially the directory handling, is getting a bit convoluted nowadays... - - - - - c8fbacfa by Sven Panne at 2004-08-02T20:31:13+00:00 [haddock @ 2004-08-02 20:31:13 by panne] Warning police - - - - - 37830bff by Sven Panne at 2004-08-02T20:32:29+00:00 [haddock @ 2004-08-02 20:32:28 by panne] Nuked dead code - - - - - 13847171 by Sven Panne at 2004-08-02T21:12:27+00:00 [haddock @ 2004-08-02 21:12:25 by panne] Use pathJoin instead of low-level list-based manipulation for FilePaths - - - - - c711d61e by Sven Panne at 2004-08-02T21:16:02+00:00 [haddock @ 2004-08-02 21:16:02 by panne] Removed WinDoze CRs - - - - - b1f7dc88 by Sven Panne at 2004-08-03T19:35:59+00:00 [haddock @ 2004-08-03 19:35:59 by panne] Fixed spelling of "http-equiv" attribute - - - - - dd5f394e by Sven Panne at 2004-08-03T19:44:03+00:00 [haddock @ 2004-08-03 19:44:03 by panne] Pacify W3C validator: * Added document encoding (currently UTF-8, not sure if this is completely correct) * Fixed syntax of `id' attributes * Added necessary `alt' attribute for +/- images Small layout improvement: * Added space after +/- images (still not perfect, but better than before) - - - - - 919c47c6 by Sigbjorn Finne at 2004-08-03T19:45:11+00:00 [haddock @ 2004-08-03 19:45:11 by sof] make it compile with <= ghc-6.1 - - - - - 4d6f01d8 by Sigbjorn Finne at 2004-08-03T19:45:30+00:00 [haddock @ 2004-08-03 19:45:30 by sof] ffi wibble - - - - - 4770643a by Sven Panne at 2004-08-03T20:47:46+00:00 [haddock @ 2004-08-03 20:47:46 by panne] Fixed CSS for button style. Note that only "0" is a valid measure without a unit! - - - - - 14aaf2e5 by Sven Panne at 2004-08-03T21:07:59+00:00 [haddock @ 2004-08-03 21:07:58 by panne] Improved spacing of dynamic module tree - - - - - 97c3579a by Simon Marlow at 2004-08-09T11:03:04+00:00 [haddock @ 2004-08-09 11:03:04 by simonmar] Add FormatVersion Patch submitted by: George Russell <ger at informatik.uni-bremen.de> - - - - - af7f8c03 by Simon Marlow at 2004-08-09T11:55:07+00:00 [haddock @ 2004-08-09 11:55:05 by simonmar] Add support for a short description for each module, which is included in the contents. The short description should be given in a "Description: " field of the header. Included in this patch are changes that make the format of the header a little more flexible. From the comments: -- all fields in the header are optional and have the form -- -- [spaces1][field name][spaces] ":" -- [text]"\n" ([spaces2][space][text]"\n" | [spaces]"\n")* -- where each [spaces2] should have [spaces1] as a prefix. -- -- Thus for the key "Description", -- -- > Description : this is a -- > rather long -- > -- > description -- > -- > The module comment starts here -- -- the value will be "this is a .. description" and the rest will begin -- at "The module comment". The header fields must be in the following order: Module, Description, Copyright, License, Maintainer, Stability, Portability. Patches submitted by: George Russell <ger at informatik.uni-bremen.de>, with a few small changes be me, mostly to merge with other recent changes. ToDo: document the module header. - - - - - 7b865ad3 by Simon Marlow at 2004-08-10T14:09:57+00:00 [haddock @ 2004-08-10 14:09:57 by simonmar] Fixes for DevHelp/HtmlHelp following introduction of short module description. - - - - - 814766cd by Simon Marlow at 2004-08-10T14:33:46+00:00 [haddock @ 2004-08-10 14:33:45 by simonmar] Fixes to installation under Windows. - - - - - 39cf9ede by Simon Marlow at 2004-08-12T12:08:23+00:00 [haddock @ 2004-08-12 12:08:23 by simonmar] Avoid using string-gap tricks. - - - - - b6d78551 by Simon Marlow at 2004-08-13T10:53:21+00:00 [haddock @ 2004-08-13 10:53:21 by simonmar] Update - - - - - eaae7417 by Simon Marlow at 2004-08-13T10:53:50+00:00 [haddock @ 2004-08-13 10:53:50 by simonmar] Test for primes in quoted links - - - - - 68c34f06 by Sven Panne at 2004-08-16T19:59:38+00:00 [haddock @ 2004-08-16 19:59:36 by panne] XMLification - - - - - 7f45a6f9 by Sven Panne at 2004-08-18T16:42:54+00:00 [haddock @ 2004-08-18 16:42:54 by panne] Re-added indices + minor fixes - - - - - 8a5dd97c by Sigbjorn Finne at 2004-08-25T17:15:42+00:00 [haddock @ 2004-08-25 17:15:42 by sof] backquote HADDOCK_VERSION defn for <= ghc-6.0.x; believe this is only needed under mingw - - - - - 4b1b42ea by Sven Panne at 2004-08-26T20:08:50+00:00 [haddock @ 2004-08-26 20:08:49 by panne] SGML is dead, long live DocBook XML! Note: The BuildRequires tags in the spec files are still incomplete and the documentation about the DocBook tools needs to be updated, too. Stay tuned... - - - - - 8d52cedb by Sven Panne at 2004-08-26T21:03:19+00:00 [haddock @ 2004-08-26 21:03:19 by panne] Updated BuildRequires tags. Alas, there seems to be no real standard here, so your mileage may vary... At least the current specs should work on SuSE Linux. - - - - - e6982912 by Sigbjorn Finne at 2004-08-30T15:44:59+00:00 [haddock @ 2004-08-30 15:44:59 by sof] escape HADDOCK_VERSION double quotes on all platforms when compiling with <=6.0.x - - - - - b3fbc867 by Simon Marlow at 2004-08-31T13:09:42+00:00 [haddock @ 2004-08-31 13:09:42 by simonmar] Avoid GHC/shell versionitis and create Version.hs - - - - - c359e16a by Sven Panne at 2004-09-05T19:12:33+00:00 [haddock @ 2004-09-05 19:12:32 by panne] * HTML documentation for "foo.xml" goes into directory "foo" again, not "foo-html". This is nicer and consistent with the behaviour for building the docs from SGML. * Disabled building PostScript documentation in the spec files for now, there are some strange issues with the FO->PS conversion for some files which have to be clarified first. - - - - - c68b1eba by Sven Panne at 2004-09-24T07:04:38+00:00 [haddock @ 2004-09-24 07:04:38 by panne] Switched the default state for instances and the module hierarchy to non-collapsed. This can be reversed when we finally use cookies from JavaScript to have a more persistent state. Previously going back and forth in the documentation was simply too annoying because everything was collapsed again and therefore the documentation was not easily navigatable. - - - - - dfb32615 by Simon Marlow at 2004-09-30T08:21:29+00:00 [haddock @ 2004-09-30 08:21:29 by simonmar] Add a feature request - - - - - 45ff783c by Sven Panne at 2004-10-23T19:54:00+00:00 [haddock @ 2004-10-23 19:54:00 by panne] Improved the Cygwin/MinGW chaos a little bit. There is still confusion about host platform vs. target platform... - - - - - 5f644714 by Krasimir Angelov at 2004-10-28T16:01:51+00:00 [haddock @ 2004-10-28 16:01:51 by krasimir] update for ghc-6.3+ - - - - - 92d9753e by Sven Panne at 2004-11-01T16:39:01+00:00 [haddock @ 2004-11-01 16:39:01 by panne] Revert previous commit: It's Network.URI which should be changed, not Haddock. - - - - - 05f70f6e by Simon Marlow at 2005-01-04T16:15:51+00:00 [haddock @ 2005-01-04 16:15:51 by simonmar] parser fix: allow qualified specialids. - - - - - 47870837 by Simon Marlow at 2005-01-04T16:16:54+00:00 [haddock @ 2005-01-04 16:16:54 by simonmar] Add a test - - - - - ff11fc2c by Ross Paterson at 2005-01-10T19:18:22+00:00 [haddock @ 2005-01-10 19:18:22 by ross] Render non-ASCII characters using numeric character references, to simplify charset issues. There's a META tag saying the charset is UTF-8, but GHC outputs characters as raw bytes. Ideally we need an encoding on the input side too, primarily in comments, because source files containing non-ASCII characters aren't portable between locales. - - - - - eba2fc4e by Simon Marlow at 2005-01-11T10:44:37+00:00 [haddock @ 2005-01-11 10:44:37 by simonmar] Remove string gap - - - - - b899a381 by Ross Paterson at 2005-01-13T11:41:33+00:00 [haddock @ 2005-01-13 11:41:33 by ross] recognize SGML-style numeric character references &#ddd; or &#xhhhh; and translate them into Chars. - - - - - 106e3cf0 by Ross Paterson at 2005-01-13T14:43:41+00:00 [haddock @ 2005-01-13 14:43:41 by ross] also allow uppercase X in hexadecimal character references (like SGML) - - - - - e8f54f25 by Ross Paterson at 2005-01-13T14:44:24+00:00 [haddock @ 2005-01-13 14:44:24 by ross] Describe numeric character references. - - - - - 914ccdce by Sven Panne at 2005-01-15T18:44:48+00:00 [haddock @ 2005-01-15 18:44:45 by panne] Make Haddock compile again after the recent base package changed. The Map/Set legacy hell has been factored out, so that all modules can simply use the new non-deprecated interfaces. Probably a lot of things can be improved by a little bit of Map/Set/List algebra, this can be done later if needed. Small note: Currently the list of instances in HTML code is reversed. This will hopefully be fixed later. - - - - - 6ab20e84 by Sven Panne at 2005-01-16T12:18:26+00:00 [haddock @ 2005-01-16 12:18:26 by panne] Trim imports - - - - - efb81da9 by Sven Panne at 2005-01-16T12:58:08+00:00 [haddock @ 2005-01-16 12:58:03 by panne] Correctly handle the new order of arguments for the combining function given to fromListWith. - - - - - e27b5834 by Sven Panne at 2005-01-16T14:14:41+00:00 [haddock @ 2005-01-16 14:14:39 by panne] Data.Map.unions is left-biased. - - - - - dae3cc3e by Sven Panne at 2005-01-16T14:22:44+00:00 [haddock @ 2005-01-16 14:22:44 by panne] Added the last missing "flip" to get identical HTML output as previous versions. - - - - - 951d8408 by Sven Panne at 2005-01-16T14:37:10+00:00 [haddock @ 2005-01-16 14:37:10 by panne] Refactored Text.PrettyPrint legacy hell into a separate module. - - - - - f1c4b892 by Sven Panne at 2005-01-16T15:41:25+00:00 [haddock @ 2005-01-16 15:41:21 by panne] Cleaned up imports and dropped support for GHC < 5.03, it never worked, anyway. - - - - - 60824c6e by Simon Marlow at 2005-01-18T10:02:48+00:00 [haddock @ 2005-01-18 10:02:48 by simonmar] Add a TODO - - - - - a8c82f23 by Krasimir Angelov at 2005-01-28T23:19:39+00:00 [haddock @ 2005-01-28 23:19:39 by krasimir] import Foreign/Foreign.C are required for Windows - - - - - d8450a23 by Simon Marlow at 2005-02-02T16:23:04+00:00 [haddock @ 2005-02-02 16:23:00 by simonmar] Revamp the linking strategy in Haddock. Now name resolution is done in two phases: - first resolve everything to original names, like a Haskell compiler would. - then, figure out the "home" location for every entity, and point all the links to there. The home location is the lowest non-hidden module in the import hierarchy that documents the entity. If there are multiple candidates, one is chosen at random. Also: - Haddock should not generate any HTML with dangling links any more. Unlinked references are just rendered as plain text. - Error reporting is better: if we can't find a link destination for an entity reference, we now emit a warning. - - - - - 1cce71d0 by Simon Marlow at 2005-02-03T13:42:19+00:00 [haddock @ 2005-02-03 13:42:19 by simonmar] - add --ignore-all-exports flag, which behaves as if every module has the ignore-exports attribute (requested by Chris Ryder). - add --hide option to hide a module on the command line. - add --use-package option to get Haddock info for a package from ghc-pkg (largely untested). - remove reexports from the .haddock file, they aren't used any more. - - - - - 767123ef by Ross Paterson at 2005-02-03T16:17:37+00:00 [haddock @ 2005-02-03 16:17:37 by ross] fix typo for < 6.3 - - - - - 0c680c04 by Simon Marlow at 2005-02-04T12:03:31+00:00 [haddock @ 2005-02-04 12:03:31 by simonmar] Fix bug in renameExportItems that meant links in instances weren't being renamed properly. - - - - - ff7abe5f by Simon Marlow at 2005-02-04T12:15:53+00:00 [haddock @ 2005-02-04 12:15:52 by simonmar] Add attribute #not-home, to indicate that the current module should not be considered to be a home module for the each entity it exports, unless there is no other module that exports the entity. - - - - - fc2cfd27 by Simon Marlow at 2005-02-04T12:40:02+00:00 [haddock @ 2005-02-04 12:40:02 by simonmar] Update the documentation w.r.t. home modules and the not-home attribute. - - - - - 26b8ddf7 by Ross Paterson at 2005-02-04T13:36:06+00:00 [haddock @ 2005-02-04 13:36:05 by ross] sort lists of instances by - arity of the type constructors (so higher-kinded instances come first) - name of the class - argument types - - - - - 26bfb19c by Simon Marlow at 2005-02-23T15:57:12+00:00 [haddock @ 2005-02-23 15:57:12 by simonmar] Fix documentation regarding the module attributes. - - - - - 9c3afd02 by Simon Marlow at 2005-02-28T16:18:17+00:00 [haddock @ 2005-02-28 16:18:17 by simonmar] version 0.7 - - - - - a95fd63f by Simon Marlow at 2005-02-28T16:22:08+00:00 [haddock @ 2005-02-28 16:22:08 by simonmar] Attempt to fix the layout of the package names in the contents. Having tried just about everything, the only thing I can get to work reliably is to make the package names line up on a fixed offset from the left margin. This obviously isn't ideal, so anyone else that would like to have a go at improving it is welcome. One option is to remove the +/- buttons from the contents list and go back to a plain table. The contents page now uses CSS for layout rather than tables. It seems that most browsers have different interpretations of CSS layout, so only the simplest things lead to consistent results. - - - - - 905d42f7 by Simon Marlow at 2005-03-01T17:16:42+00:00 [haddock @ 2005-03-01 17:16:40 by simonmar] Another attempt at lining up the package names on the contents page. Now, they line up with Konqueror, and almost line up with Firefox & IE (different layout in each case). - - - - - a0e1d178 by Wolfgang Thaller at 2005-03-09T08:28:39+00:00 [haddock @ 2005-03-09 08:28:39 by wolfgang] Hack haddock's lexer to accept the output from Apple's broken version of cpp (Apple's cpp leaves #pragma set_debug_pwd directives in it's output). - - - - - 9e1eb784 by Simon Marlow at 2005-04-22T14:27:15+00:00 [haddock @ 2005-04-22 14:27:15 by simonmar] Add a TODO item - - - - - 23281f78 by Ross Paterson at 2005-05-18T12:41:59+00:00 [haddock @ 2005-05-18 12:41:59 by ross] fix 3 bugs in --use-package, and document it. - - - - - 00074a68 by Sven Panne at 2005-05-21T12:35:29+00:00 [haddock @ 2005-05-21 12:35:29 by panne] Warning/versionitis police - - - - - 341fa822 by Simon Marlow at 2005-06-15T15:43:21+00:00 [haddock @ 2005-06-15 15:43:21 by simonmar] Allow "licence" as an alternate spelling of "license" - - - - - 3b953f8b by Simon Marlow at 2005-06-16T08:14:12+00:00 [haddock @ 2005-06-16 08:14:12 by simonmar] wibble - - - - - abfd9826 by Simon Marlow at 2005-06-27T14:46:40+00:00 [haddock @ 2005-06-27 14:46:40 by simonmar] name hierarchical HTML files as A-B-C.html instead of A.B.C.html. The old way confused Apache because the extensions are sometimes interpreted as having special meanings. - - - - - a01eea00 by Simon Marlow at 2005-08-04T13:59:40+00:00 [haddock @ 2005-08-04 13:59:40 by simonmar] 0.7 changes - - - - - 170ef87e by Simon Marlow at 2005-08-04T15:08:03+00:00 [haddock @ 2005-08-04 15:08:03 by simonmar] spec file from Jens Peterson - - - - - 7621fde4 by Simon Marlow at 2005-08-04T15:59:30+00:00 [haddock @ 2005-08-04 15:59:30 by simonmar] replace mingw tests with $(Windows) - - - - - a20739bb by Sven Panne at 2005-08-05T07:01:12+00:00 [haddock @ 2005-08-05 07:01:12 by panne] Reverted to previous version (but with bumped version number), the last commit broke RPM building on SuSE systems due to differently named dependencies. As a clarification: All .spec files in the repository have to work at least on SuSE, because that's the system I'm using. And as "Mr. Building Police", I reserve me the right to keep them that way... >:-) It might very well be the case that we need different .spec files for different platforms, so packagers which are unhappy with the current .spec files should contact me, stating the actual problems. - - - - - 4afb15cf by Simon Marlow at 2005-10-05T10:51:45+00:00 [haddock @ 2005-10-05 10:51:45 by simonmar] Add a bug - - - - - 60f69f82 by Simon Marlow at 2005-10-05T12:52:03+00:00 [haddock @ 2005-10-05 12:52:03 by simonmar] Document new behaviour of -s option - - - - - f7e520ca by Simon Marlow at 2005-10-10T15:02:55+00:00 [haddock @ 2005-10-10 15:02:55 by simonmar] extractRecSel: ignore non-record constructors (fixes a crash when using datatypes with a mixture of record and non-record style constructors). - - - - - b2edbedb by Simon Marlow at 2005-10-14T09:44:21+00:00 Start CHANGES for 0.8 - - - - - 21c7ac8d by Simon Marlow at 2005-10-14T23:11:19+00:00 First cut of Cabal build system - - - - - 766cecdd by Simon Marlow at 2005-10-29T08:14:43+00:00 Add configure script and Makefile for the docs Add a separate configure script and build system for building the documentation. The configure and Makefile code is stolen from fptools. This is left as a separate build system so that the main Cabal setup doesn't require a Unix build environment or DocBook XML tools. - - - - - aa36c783 by Duncan Coutts at 2006-01-17T19:29:55+00:00 Add a --wiki=URL flag to add a per-module link to a correspondng wiki page. So each html page gets an extra link (placed next to the source code and contents links) to a corresponding wiki page. The idea is to let readers contribute their own notes, examples etc to the documentation. Also slightly tidy up the code for the --source option. - - - - - e06e2da2 by Simon Marlow at 2006-01-18T09:28:15+00:00 TODO: documnet --wiki - - - - - 17adfda9 by Duncan Coutts at 2006-01-19T20:17:59+00:00 Add an optional wiki link for each top level exported name. In each module, for each "top level" exported entity we add a hyper link to a corresponding wiki page. The link url gets the name of the exported entity as a '#'-style anchor, so if there is an anchor in the page with that name then the users browser should jump directly to it. By "top level" we mean functions, classes, class members and data types (data, type, newtype), but not data constructors, class instances or data type class membership. The link is added at the right of the page and in a small font. Hopefully this is the right balance of visibility/distraction. We also include a link to the wiki base url in the contents and index pages. - - - - - f52324bb by Duncan Coutts at 2006-01-19T20:28:27+00:00 Rewrite pathJoin to only add a path separator when necessary. When the path ends in a file seperator there is no need to add another. Now using "--wiki=http://blah.com/foo/" should do the right thing. (Code snippet adapted from Isaac's FilePath package.) - - - - - 43bb89fa by Duncan Coutts at 2006-01-21T17:15:27+00:00 Teach haddock about line pragmas and add accurate source code links Teach haddock about C and Haskell style line pragmas. Extend the lexer/parser's source location tracking to include the file name as well as line/column. This way each AST item that is tagged with a SrcLoc gets the original file name too. Use this original file name to add source links to each exported item, in the same visual style as the wiki links. Note that the per-export source links are to the defining module rather than whichever module haddock pretends it is exported from. This is what we want for source code links. The source code link URL can also contain the name of the export so one could implement jumping to the actual location of the function in the file if it were linked to an html version of the source rather than just plain text. The name can be selected with the %N wild card. So for linking to the raw source code one might use: --source=http://darcs/haskell.org/foo/%F Or for linking to html syntax highlighted code: --source=http://darcs/haskell.org/foo/%M.html#%N - - - - - edd9f229 by Duncan Coutts at 2006-01-22T00:02:00+00:00 Extend URL variable expansion syntax and add source links to the contents page Like the wiki link on the contents and index page, add a source code link too. Extend the wiki & source URL variable expansion syntax. The original syntax was: %F for the source file name (the .hs version only, not the .lhs or .hs.pp one) %M for the module name (with '.' replaced by '/') The new syntax is: %F or %{FILE} for the original source file name %M or %{MODULE} for the module name (no replacements) %N or %{NAME} for the function/type export name %K or %{KIND} for a type/value flag "t" or "v" with these extensions: %{MODULE/./c} to replace the '.' module seperator with any other char c %{VAR|some text with the % char in it} which means if the VAR is not in use in this URL context then "" else replace the given text with the '%' char replaced by the string value of the VAR. This extension allows us to construct URLs wit optional parts, since the module/file name is not available for the URL in the contents/index pages and the value/type name is not available for the URL at the top level of each module. - - - - - eb3c6ada by Duncan Coutts at 2006-01-23T13:42:34+00:00 Remove the complex substitutions and add more command line flags instead. Instead of incomprehensable URL substitutions like ${MODULE/./-|?m=%} we now use three seperate command line flags for the top level, per-module and per-entity source and wiki links. They are: --source-base, --source-module, --source-entity --comments-base, --comments-module, --comments-entity We leave -s, --source as an alias for --source-module which is how that option behaved previously. The long forms of the substitutions are still available, ${FILE} ${MODULE} etc and the only non-trivial substitution is ${MODULE/./c} to replace the '.' characters in the module name with any other character c. eg ${MODULE/./-} Seperating the source and wiki url flags has the added bonus that they can be turned on or off individually. So users can have per-module links for example without having to also have per-entity links.` - - - - - a2f0f2af by Duncan Coutts at 2006-01-23T13:54:52+00:00 Make the --help output fit in 80 columns. This is a purely cosmetic patch, feel free to ignore it. The only trickery going on is that we don't display the deprecated -s, --source flags in the help message, but we do still accept them. - - - - - 2d3a4b0c by Duncan Coutts at 2006-01-23T14:12:16+00:00 Add documentation for the new --source-* and --comments-* command line options - - - - - 1a82a297 by Simon Marlow at 2006-01-23T17:03:27+00:00 fix markup - - - - - 100d464a by Duncan Coutts at 2006-01-23T18:31:13+00:00 remove a couple TODO items that have been done The --wiki, or rather the --comment-* options are now documented. There is probably no need to have haddock invoke unlit or cpp itself since it can now pick up the line pragmas to get the source locations right. Tools like Cabal will arrange for preprocessors to be run so there is less of a need for tools like haddock to do it themselves. - - - - - 3162fa91 by Simon Marlow at 2006-01-24T14:21:56+00:00 add a test I had lying around - - - - - 98947063 by Simon Marlow at 2006-01-31T13:52:54+00:00 add scabal-version field - - - - - c41876e6 by Neil Mitchell at 2006-02-26T17:48:21+00:00 Add Hoogle output option - - - - - f86fb9c0 by Simon Marlow at 2006-03-08T09:15:20+00:00 add haskell.vim Contributed by Brad Bowman <bsb at bereft.net>, thanks! - - - - - 35d3c511 by benjamin.franksen at 2006-03-03T22:39:54+00:00 fixed libdir (/html was missing) - - - - - 4d08fd7d by Simon Marlow at 2006-03-10T11:13:31+00:00 add PatternGuards extension - - - - - 3f095e70 by Simon Marlow at 2006-03-13T11:40:42+00:00 bug fixes from Brad Bowman - - - - - 8610849d by Sven Panne at 2006-03-19T17:02:56+00:00 Fixed Cabal/RPM build - - - - - 34a994d6 by sven.panne at 2006-04-20T12:39:23+00:00 Avoid pattern guards Due to the use of pattern guards in Haddock, GHC was called with -fglasgow-exts. This in turn enables bang patterns, too, which broke the Haddock build. Removing some unnecessary pattern guards seemed to be the better way of fixing this instead of using a pragma to disable pattern guards. - - - - - bb523f51 by Ross Paterson at 2006-04-24T09:03:25+00:00 extend 'deriving' heuristic a little If an argument of a data constructor has a type variable head, it is irreducible and the same type class can be copied into the constraint. (Formerly we just did this for type variable arguments.) - - - - - dab9fe7a by Simon Marlow at 2006-04-26T10:02:31+00:00 record an idea - - - - - 748b7078 by Simon Marlow at 2006-05-08T08:28:53+00:00 add section about deriving - - - - - 11252ea1 by Simon Marlow at 2006-05-24T15:43:10+00:00 replace a fatal error in lexChar with a parseError - - - - - 382c9411 by Simon Marlow at 2006-05-24T15:45:47+00:00 add a bug - - - - - b79272f5 by Simon Marlow at 2006-05-24T15:46:29+00:00 add a bug report - - - - - 912edf65 by David Waern at 2006-07-10T19:09:23+00:00 Initial modifications -- doesn't compile - - - - - a3c7ba99 by David Waern at 2006-07-11T00:54:19+00:00 More porting work -- doesn't compile - - - - - 0a173d19 by David Waern at 2006-07-11T11:30:03+00:00 Make the repos temporarily compile and illustrate a problem - - - - - bad316de by David Waern at 2006-07-11T15:43:47+00:00 Progress on the porting process - - - - - bbf12d02 by David Waern at 2006-07-11T23:07:44+00:00 More progress on the porting -- first pass starting to shape up - - - - - de580ba2 by David Waern at 2006-07-20T17:48:30+00:00 More progress -- still on phase1 - - - - - 75a917a2 by David Waern at 2006-07-23T18:22:43+00:00 More work on pass1 -- mostly done - - - - - 6697b3f7 by David Waern at 2006-07-23T22:17:40+00:00 More work, started working on the renaming phase -- this code will need a cleanup soon :) - - - - - 82a5bcbb by David Waern at 2006-07-29T16:16:43+00:00 Add instances, build renaming environment, start on the renamer - - - - - c3f8f4f1 by David Waern at 2006-07-29T21:37:48+00:00 Complete the renamer - - - - - 7e00d464 by David Waern at 2006-07-30T21:01:57+00:00 Start porting the Html renderer - - - - - f04ce121 by David Waern at 2006-08-09T20:04:56+00:00 More Html rendering progress - - - - - 20c21b53 by David Waern at 2006-08-10T17:37:47+00:00 More progress - - - - - d7097e0d by David Waern at 2006-08-11T20:31:51+00:00 Cleanup - - - - - a7351e86 by David Waern at 2006-08-12T11:44:47+00:00 Render H98 Data declarations - - - - - 3fb2208e by David Waern at 2006-08-12T17:15:34+00:00 Perfect rendering of Test.hs - - - - - 454fd062 by David Waern at 2006-08-13T21:57:08+00:00 Misc fixes and interface load/save - - - - - 7ef7e7be by David Waern at 2006-08-14T00:56:07+00:00 Some refactoring - - - - - a7d3efef by David Waern at 2006-08-19T20:07:55+00:00 Adapt to latest GHC - - - - - 5fc3c0d7 by David Waern at 2006-08-20T21:28:11+00:00 Move interface read/write to its own module + some cleanup - - - - - 037e011c by David Waern at 2006-08-20T21:38:24+00:00 Small cleanup - - - - - da3a1023 by David Waern at 2006-09-03T16:05:22+00:00 Change mode to BatchCompile to avoid GHC API bug - - - - - 3cc9be3b by David Waern at 2006-09-03T16:06:59+00:00 Starting work on GADT rendering - - - - - 94506037 by David Waern at 2006-09-03T20:02:48+00:00 Compensate for change of export list order in GHC - - - - - c2cec4eb by David Waern at 2006-09-04T20:53:01+00:00 Rename a function - - - - - 9a9735ba by David Waern at 2006-09-05T15:51:21+00:00 Change version number to 2.0 - - - - - 3758a714 by David Waern at 2006-09-05T15:51:49+00:00 Align comment properly - - - - - 68478d9e by David Waern at 2006-09-15T18:03:00+00:00 Remove interface reading/writing code and use the GHC api for creating package environments instead - - - - - d2eedd95 by David Waern at 2006-09-15T18:05:29+00:00 Change the executable name to haddock-ghc-nolib - - - - - fcfbcf66 by David Waern at 2006-09-15T18:05:45+00:00 Small source code cleanup - - - - - d08eb017 by David Waern at 2006-09-15T18:06:21+00:00 Remove handling of --package flag - - - - - b8a4cf53 by David Waern at 2006-09-15T18:07:16+00:00 Remove commented-out code - - - - - bef0a684 by David Waern at 2006-09-15T18:37:57+00:00 Don't warn about missing links to () - - - - - e7d25fd7 by David Waern at 2006-09-15T19:50:49+00:00 Remove Interface and Binary2 modules - - - - - 9894f2a1 by David Waern at 2006-09-15T19:53:43+00:00 Remove debug printing from HaddockHtml - - - - - a0e7455d by David Waern at 2006-09-16T00:16:29+00:00 Comments only - - - - - d5b26fa7 by David Waern at 2006-09-16T00:16:57+00:00 Refactor PackageData creation code and start on building the doc env propery (unfinished) - - - - - 06aaa779 by David Waern at 2006-09-16T00:19:25+00:00 Better comments in Main.hs - - - - - 1a52d1b4 by David Waern at 2006-09-18T22:17:11+00:00 Comments and spacing change - - - - - e5a97767 by David Waern at 2006-09-21T17:02:45+00:00 Remove unnecessary fmapM import in Main - - - - - 9d0f9d3a by David Waern at 2006-09-22T18:07:07+00:00 Make import list in HaddockHtml prettier - - - - - 3452f662 by David Waern at 2006-09-22T18:08:47+00:00 Refactor context rendering - - - - - 12d0a6d0 by David Waern at 2006-09-22T18:09:52+00:00 Do proper HsType rendering (inser parentheses correctly) - - - - - 2c20c2f9 by David Waern at 2006-09-22T18:10:45+00:00 Fix a bug in Main.toHsType - - - - - c5396443 by David Waern at 2006-09-22T18:11:16+00:00 Skip external package modules sort for now - - - - - 3fb95547 by David Waern at 2006-09-22T20:35:40+00:00 Take away trailin "2" on all previously clashing type names - - - - - 2174755f by David Waern at 2006-09-22T20:51:43+00:00 Remove unused imports in Main - - - - - 1e9f7a39 by David Waern at 2006-09-22T20:52:11+00:00 Fix a comment in Main - - - - - 32d9e028 by David Waern at 2006-10-05T16:40:11+00:00 Merge with changes to ghc HEAD - - - - - 3058c8f5 by David Waern at 2006-10-05T16:41:02+00:00 Comment fixes - - - - - b9c217ec by David Waern at 2006-10-05T16:49:59+00:00 Filter out more builtin type constructors from warning messages - - - - - 67e7d252 by David Waern at 2006-10-05T19:38:22+00:00 Refactoring -- better structured pass1 - - - - - cd21c0c1 by David Waern at 2006-10-05T19:44:42+00:00 Remove read/dump interface flags - - - - - 313f9e69 by David Waern at 2006-10-05T19:49:26+00:00 Remove unused pretty printing - - - - - 480f09d1 by David Waern at 2006-12-28T13:22:24+00:00 Update to build with latest GHC HEAD - - - - - 63dccfcb by David Waern at 2007-01-05T01:38:45+00:00 Fixed a bug so that --ghc-flag works correctly - - - - - 3117dadc by David Waern at 2006-12-29T18:53:39+00:00 Automatically get the GHC lib dir - - - - - 9dc84a5c by David Waern at 2006-12-29T19:58:53+00:00 Comments - - - - - 0b0237cc by David Waern at 2007-01-05T16:48:30+00:00 Collect docs based on SrcLoc, syncing with removal of DeclEntity from GHC - - - - - a962c256 by David Waern at 2007-01-05T17:02:47+00:00 Add tabs in haddock.cabal - - - - - 0ca30c97 by David Waern at 2007-01-05T17:04:11+00:00 Add GHCUtils.hs - - - - - c0ab9abe by David Waern at 2007-01-10T11:43:08+00:00 Change package name to haddock-ghc, version 0.1 - - - - - 38e18b27 by David Waern at 2007-01-12T12:03:52+00:00 No binder name for foreign exports - - - - - d18587ab by David Waern at 2007-01-12T12:08:15+00:00 Temp record - - - - - ba6251a0 by David Waern at 2007-01-12T18:27:55+00:00 Remove read/dump-interface (again) - - - - - f4ba2b39 by David Waern at 2007-01-12T18:31:36+00:00 Remove DocOption, use the GHC type - - - - - 511be8bd by David Waern at 2007-01-12T18:32:41+00:00 Use exceptions instead of Either when loading package info - - - - - 0f2144d8 by David Waern at 2007-01-12T18:33:23+00:00 Small type change - - - - - 77507eb7 by David Waern at 2007-01-12T18:33:59+00:00 Remove interface file read/write - - - - - 0ea1e14f by David Waern at 2007-01-17T21:40:26+00:00 Add trace_ppr to GHCUtils - - - - - 3878b493 by David Waern at 2007-01-17T21:40:53+00:00 Sort external package modules and build a doc env - - - - - 8dc323fc by David Waern at 2007-01-17T21:42:41+00:00 Remove comment - - - - - f4c5b097 by David Waern at 2007-01-18T23:22:18+00:00 Add haddock-ghc.cabal and remove ghc option pragma in source file - - - - - da242b2c by David Waern at 2007-01-18T23:22:46+00:00 Remove some tabs - - - - - 288ed096 by David Waern at 2007-01-18T23:39:28+00:00 Moved the defaultErrorHandler to scope only over sortAndCheckModules for now - - - - - 4dd150fe by David Waern at 2007-02-03T21:23:56+00:00 Let restrictCons handle infix constructors - - - - - 97893442 by David Waern at 2007-02-04T16:26:00+00:00 Render infix data constructors - - - - - da89db72 by David Waern at 2007-02-04T16:26:33+00:00 CHange project name to Haddock-GHC - - - - - e93d48af by David Waern at 2007-02-04T16:59:08+00:00 Render infix type constructors properly - - - - - 357bc99b by David Waern at 2007-02-04T17:37:08+00:00 Insert spaces around infix function names - - - - - ab6cfc49 by David Waern at 2007-02-04T17:59:54+00:00 Do not list entities without documentation - - - - - 04249c7e by David Waern at 2007-02-04T19:16:25+00:00 Add GADT support (quite untested) - - - - - 2c223f8d by David Waern at 2007-02-04T19:25:10+00:00 Add package file write/save again! - - - - - b07ed218 by David Waern at 2007-02-04T19:33:02+00:00 Comment out minf_iface based stuff - - - - - 953d1fa7 by David Waern at 2007-02-05T00:12:23+00:00 Solve conflicts - - - - - 593247fc by David Waern at 2007-02-06T19:48:48+00:00 Remove -package flag, GHC's can be used instead - - - - - f658ded2 by David Waern at 2007-02-06T20:50:44+00:00 Start for support of ATs - - - - - 97f9e913 by David Waern at 2007-02-06T20:52:27+00:00 Wibble - - - - - 2ce8e4cf by David Waern at 2007-02-16T12:09:49+00:00 Add the DocOptions change - - - - - dee4a9b5 by David Waern at 2007-03-06T01:24:48+00:00 Wibble - - - - - 7cb99d18 by David Waern at 2007-03-06T01:24:58+00:00 Change version to 2.0 and executable name to haddock - - - - - c5aa02bc by David Waern at 2007-03-08T15:59:49+00:00 Go back to -B flag - - - - - 3a349201 by David Waern at 2007-03-09T13:31:59+00:00 Better exception handling and parsing of GHC flags - - - - - 05a69b71 by David Waern at 2007-03-09T17:45:44+00:00 Remove commented-out DocEntity printing - - - - - 755032cb by davve at dtek.chalmers.se at 2007-03-23T23:30:20+00:00 Remove a file that shouldn't be here - - - - - a7077e5f by davve at dtek.chalmers.se at 2007-03-24T03:58:48+00:00 Remove an import - - - - - 6f55aa8b by davve at dtek.chalmers.se at 2007-03-25T00:46:48+00:00 Start work on Haddock API - - - - - f0199480 by davve at dtek.chalmers.se at 2007-03-25T00:56:36+00:00 Prettify some comments - - - - - f952f9d1 by davve at dtek.chalmers.se at 2007-03-25T00:56:53+00:00 Remove ppr in HaddockTypes - - - - - bc594904 by davve at dtek.chalmers.se at 2007-03-25T00:57:53+00:00 Remove commented out doc env inference - - - - - 11ebf08d by davve at dtek.chalmers.se at 2007-03-25T01:23:25+00:00 De-flatten the namespace - - - - - f696b4bc by davve at dtek.chalmers.se at 2007-03-25T03:21:48+00:00 Add missing stuff to API - - - - - 9a2a04c3 by davve at dtek.chalmers.se at 2007-03-25T03:22:02+00:00 Wibble - - - - - 7d04a6d5 by davve at dtek.chalmers.se at 2007-03-25T03:22:08+00:00 Avoid a GHC bug with parseStaticFlags [] - - - - - 4d2820ba by davve at dtek.chalmers.se at 2007-03-26T04:57:01+00:00 Add fall-through case to mkExportItem - - - - - 6ebc8950 by Stefan O'Rear at 2007-03-26T04:14:53+00:00 Add shebang line to Setup.lhs - - - - - 80966ec5 by davve at dtek.chalmers.se at 2007-03-26T05:24:26+00:00 Fix stupid compile error - - - - - 1ea1385d by davve at dtek.chalmers.se at 2007-04-05T17:19:56+00:00 Do save/read of interface files properly - - - - - 0e4f6541 by David Waern at 2007-04-10T21:08:36+00:00 Add version to ghc dependency - - - - - b0499b63 by David Waern at 2007-04-10T21:37:08+00:00 Change package name to haddock - - - - - 9d50d27e by David Waern at 2007-04-24T00:22:14+00:00 Use filepath package instead of FilePath - - - - - 87c7fcdf by David Waern at 2007-07-10T21:03:04+00:00 Add new package dependencies - - - - - 4768709c by David Waern at 2007-07-11T20:37:11+00:00 Follow changes to record constructor representation - - - - - b9a02fee by Simon Marlow at 2007-05-30T14:00:48+00:00 update to compile with the latest GHC & Cabal - - - - - c0ebdc01 by David Waern at 2007-07-11T21:35:45+00:00 Fix conflicts - - - - - 97f7afd4 by David Waern at 2007-07-11T21:52:38+00:00 Follow changes to the GHC API - - - - - a5b7b58f by David Waern at 2007-07-12T20:36:48+00:00 Call parseStaticFlags before newSession - - - - - f7f50dbc by David Waern at 2007-08-01T21:52:58+00:00 Better indentation in haddock.cabal - - - - - d84e52ad by David Waern at 2007-08-02T00:08:18+00:00 Wibble - - - - - a23f494a by David Waern at 2007-08-02T00:08:24+00:00 Be better at trying to load all module dependencies (debugging) - - - - - ee917f13 by David Waern at 2007-08-03T18:48:08+00:00 Load all targets explicitly (checkModule doesn't chase dependencies anymore) - - - - - 5182d631 by David Waern at 2007-08-16T16:48:55+00:00 Finalize support for links to other packages - - - - - dfd1e3da by David Waern at 2007-08-16T16:51:11+00:00 Fix haddock comment errors in Haddock.Types - - - - - 50c0d83e by David Waern at 2007-08-16T16:51:37+00:00 Remove a debug import - - - - - d84b7c2b by David Waern at 2007-08-16T17:06:30+00:00 Rename PackageData to HaddockPackage - - - - - 3b52cb9f by David Waern at 2007-08-16T17:09:42+00:00 Simplify some comments - - - - - 66fa68d9 by David Waern at 2007-08-16T17:11:38+00:00 Comment the HaddockPackage definition - - - - - 8674c761 by David Waern at 2007-08-16T17:25:54+00:00 Improve code layout in Main - - - - - 571a3a0b by David Waern at 2007-08-16T17:32:13+00:00 Remove explict module imports in Main - - - - - d31b3cb0 by David Waern at 2007-08-16T17:36:23+00:00 Correct comments - - - - - 7f8a9f2b by David Waern at 2007-08-16T17:39:50+00:00 Fix layout problems in Haddock.Types - - - - - 9f421d7f by David Waern at 2007-08-17T11:16:48+00:00 Move options out of Main into Haddock.Options - - - - - 80042b63 by David Waern at 2007-08-17T11:26:59+00:00 Small comment/layout fixes - - - - - b141b982 by David Waern at 2007-08-17T11:28:28+00:00 Change project name from Haddock-GHC to Haddock - - - - - dbeb4a81 by David Waern at 2007-08-17T11:41:05+00:00 Add top module comment to all files - - - - - ce99cc9e by David Waern at 2007-08-17T14:53:04+00:00 Factor out typechecking phase into Haddock.Typecheck - - - - - 6bf75d9e by David Waern at 2007-08-17T16:55:35+00:00 Factor out package code to Haddock.Packages - - - - - b396db37 by David Waern at 2007-08-29T22:40:23+00:00 Major refactoring - - - - - 3d4f95ee by David Waern at 2007-08-29T23:26:24+00:00 Rename HaddockModule to Interface and a few more refactorings - - - - - c55326db by David Waern at 2007-08-29T23:48:03+00:00 Some comment cleanup - - - - - 9a84fc46 by David Waern at 2007-08-29T23:49:29+00:00 Add some modules that I forgot to add earlier - - - - - 4536dce2 by David Waern at 2007-08-29T23:55:24+00:00 Wibble - - - - - 9b7f0206 by David Waern at 2007-08-30T16:03:29+00:00 Wibble - - - - - c52c050a by David Waern at 2007-08-30T16:30:37+00:00 Rename HaddockModule to Interface - - - - - eae2995f by David Waern at 2007-08-30T16:42:59+00:00 Simplify createInterfaces - - - - - 53f99caa by David Waern at 2007-09-29T00:04:31+00:00 Add build-type: Simple to the cabal file - - - - - 0d3103a8 by David Waern at 2007-09-29T00:04:58+00:00 Add containers and array dependency - - - - - 6acf5f30 by David Waern at 2007-09-29T00:13:36+00:00 Prettify the cabal file - - - - - 87c1e378 by David Waern at 2007-09-29T13:16:39+00:00 FIX: consym data headers with more than two variables - - - - - b67fc16a by David Waern at 2007-09-29T14:01:32+00:00 FIX: prefix types used as operators should be quoted - - - - - a8f925bc by David Waern at 2007-09-29T14:02:26+00:00 Use isSymOcc from OccName instead of isConSym - - - - - fc330701 by David Waern at 2007-09-29T14:15:37+00:00 Use isLexConSym/isLexVarSym from OccName - - - - - e4f3dbad by David Waern at 2007-09-29T15:01:08+00:00 FIX: do not quote varsym type operators - - - - - 402207d2 by David Waern at 2007-09-29T15:01:50+00:00 Wibble - - - - - f9d89ef0 by David Waern at 2007-09-29T15:17:40+00:00 Take care when pp tyvars - add parens on syms - - - - - 849e2a77 by David Waern at 2007-10-01T21:56:39+00:00 Go back to using a ModuleMap instead of LookupMod - fixes a bug - - - - - 549dbac6 by David Waern at 2007-10-02T01:05:19+00:00 Improve parsing of doc options - - - - - a36021b8 by David Waern at 2007-10-02T23:05:00+00:00 FIX: double arrows in constructor contexts - - - - - d03bf347 by David Waern at 2007-10-09T16:14:05+00:00 Add a simple test suite - - - - - c252c140 by David Waern at 2007-10-17T16:02:28+00:00 Add --optghc=.. style flag passing to GHC - - - - - cce6c1b3 by David Waern at 2007-10-18T22:03:20+00:00 Add support for --read-interface again - - - - - 33d059c0 by David Waern at 2007-10-18T22:30:18+00:00 Refactoring -- get rid of Haddock.Packages - - - - - f9ed0a4c by David Waern at 2007-10-18T22:34:36+00:00 Name changes - - - - - 8a1c816f by David Waern at 2007-10-20T14:24:23+00:00 Add --ghc-version option - - - - - 4925aaa1 by David Waern at 2007-10-21T14:34:26+00:00 Add some Outputable utils - - - - - 69e7e47f by David Waern at 2007-10-21T14:35:49+00:00 FIX: Ord for OrdName was not comparing modules - - - - - 5a4ae535 by David Waern at 2007-10-21T21:18:48+00:00 Wibble - - - - - 03d48e20 by David Waern at 2007-10-24T15:52:56+00:00 Remove Main from "other modules" - - - - - c66f6d82 by David Waern at 2007-10-24T16:37:18+00:00 Make it possible to run haddock on itself - - - - - 21d156d8 by David Waern at 2007-10-25T14:02:14+00:00 Don't set boot modules as targets - - - - - f8bcf91c by David Waern at 2007-10-31T22:11:17+00:00 Add optimisation flags - - - - - 7ac758f2 by David Waern at 2007-11-04T09:48:28+00:00 Go back to loading only targets (seems to work now) - - - - - 4862aae1 by David Waern at 2007-11-05T22:24:57+00:00 Do full compilation of modules -- temporary fix for GHC API problem - - - - - 697e1517 by David Waern at 2007-11-05T22:25:50+00:00 Don't warn about not being able to link to wired/system/builtin-names - - - - - 892186da by David Waern at 2007-11-06T00:49:21+00:00 Filter out instances with TyCons that are not exported - - - - - 9548314c by David Waern at 2007-11-06T09:37:14+00:00 Wibble - - - - - 5cafd627 by David Waern at 2007-11-08T01:43:07+00:00 Filter out all non-vanilla type sigs - - - - - 04621830 by David Waern at 2007-11-08T01:45:13+00:00 Synch loading of names from .haddock files with GHC's name cache - - - - - 88d37f77 by David Waern at 2007-11-08T01:46:21+00:00 Remove commented-out code - - - - - 6409c911 by David Waern at 2007-11-08T01:56:00+00:00 Small bugfix and cleanup in getDeclFromTyCls - - - - - af59d9c2 by David Waern at 2007-11-08T02:08:44+00:00 Remove OrdName stuff - - - - - 3a615e2e by David Waern at 2007-11-08T02:13:41+00:00 Update runtests.hs following changes to haddock - - - - - 01f3314e by David Waern at 2007-11-08T02:33:01+00:00 Complain if we can't link to wired-in names - - - - - fcafb5d1 by David Waern at 2007-11-09T02:40:16+00:00 Don't exit when there are no file arguments - - - - - 194bc332 by David Waern at 2007-11-09T02:55:37+00:00 Wibble - - - - - dbe4cb55 by David Waern at 2007-11-09T02:56:14+00:00 Wibble - - - - - 82869fda by David Waern at 2007-11-10T17:01:43+00:00 Introduce InstalledInterface structure and add more stuff to the .haddock files We introduce InstalledInterface capturing the part of Interface that is stored in the interface files. We change the ppHtmlContents and ppHtmllIndex to take this structure instead of a partial Interface. We add stuff like the doc map and exported names to the .haddock file (via InstalledInterface). - - - - - d6bb57bf by David Waern at 2007-11-10T17:19:48+00:00 FIX: contents and index should include external package modules when --gen-contents/--gen-index - - - - - e8814716 by David Waern at 2007-11-11T00:29:27+00:00 Remove lDocLinkName and its use in Html backend - - - - - 6f9bd702 by David Waern at 2007-11-11T00:50:57+00:00 Do some refactoring in the html backend This also merges an old patch by Augustsson: Wed Jul 12 19:54:36 CEST 2006 lennart.augustsson at credit-suisse.com * Print type definitions like signatures if given arrows. - - - - - 09d0ce24 by Malcolm.Wallace at 2006-07-20T13:13:57+00:00 mention HsColour in the docs, next to option flags for linking to source code - - - - - 24da6c34 by Malcolm.Wallace at 2006-07-20T13:14:50+00:00 change doc references to CVS to give darcs repository location instead - - - - - 74d52cd6 by David Waern at 2007-11-11T00:55:33+00:00 Update copyright - - - - - fcaa3b4f by Duncan Coutts at 2006-09-08T13:41:00+00:00 Eliminate dep on network by doing a little cut'n'paste haddock depending on the network causes a circular dependency at least if you want to build the network lib with haddock docs. - - - - - 10cc9bda by David Waern at 2007-11-11T02:09:41+00:00 Fix conflicts - - - - - 4e3acd39 by David Waern at 2007-11-11T02:21:19+00:00 Manual merge of a patch from Duncan Coutts that removes the dependency on mtl - - - - - fa9070da by Neil Mitchell at 2006-09-29T15:52:03+00:00 Do not generate an empty table if there are no exports, this fixes a <table></table> tag being generated, which is not valid HTML 4.01 - - - - - d7431c85 by David Waern at 2007-11-11T02:28:50+00:00 Fix conflicts - - - - - f87e8f98 by Simon Marlow at 2006-10-10T11:37:16+00:00 changes for 0.8 - - - - - db929565 by Simon Marlow at 2006-10-10T12:07:12+00:00 fix the name of the source file - - - - - 8220aa4b by Simon Marlow at 2006-10-11T14:17:37+00:00 Rename haddock.js to haddock-util.js haddock.js will be run automatically by Windows when you type 'haddock' if it is found on the PATH, so rename to avoid confusion. Spotted by Adrian Hey. - - - - - 6bccdaa1 by sven.panne at 2006-10-12T15:28:23+00:00 Cabal's sdist does not generate "-src.tar.gz" files, but ".tar.gz" ones - - - - - d3f3fc19 by Simon Marlow at 2006-12-06T16:05:07+00:00 add todo item for --maintainer - - - - - 2da7e269 by Simon Marlow at 2006-12-15T15:52:00+00:00 TODO: do something better about re-exported symbols from another package - - - - - 42d85549 by David Waern at 2007-11-11T02:30:59+00:00 Fix conflicts - - - - - 5e7ef6e5 by Neil Mitchell at 2007-01-11T15:41:15+00:00 Never do spliting index files into many - - - - - f3d4aebe by Neil Mitchell at 2007-01-11T17:07:09+00:00 Add searching on the index page - - - - - bad3ab66 by Neil Mitchell at 2007-01-11T18:17:46+00:00 Delete dead code, now there is only one index page - - - - - cd09eedb by Neil Mitchell at 2007-01-11T18:21:19+00:00 Delete more stuff that is no longer required - - - - - e2806646 by David Waern at 2007-11-11T02:41:53+00:00 Fix conflicts - - - - - a872a823 by Neil Mitchell at 2007-01-11T18:51:43+00:00 Make the index be in case-insensitive alphabetic order - - - - - 8bddd9d7 by Neil Mitchell at 2007-02-06T17:49:12+00:00 Do not create empty tables for data declarations which don't have any constructors, instances or comments. Gets better HTML 4.01 compliance - - - - - 036b8120 by David Waern at 2007-11-11T02:56:58+00:00 Fix conflicts - - - - - f50c1639 by Conal Elliott at 2007-02-14T21:54:00+00:00 added substitution %{FILE///c} - - - - - 402e166a by David Waern at 2007-11-11T03:35:46+00:00 Manual merge of old patch: Sat Apr 21 04:36:43 CEST 2007 Roberto Zunino <zunrob at users.sf.net> * URL expansion for %%, %L, %{LINE} - - - - - 2f264fbd by David Waern at 2007-11-11T03:40:33+00:00 Manual merge of an old patch: Thu Apr 19 20:23:40 CEST 2007 Wolfgang Jeltsch <g9ks157k at acme.softbase.org> * bug fix When Haddock was invoked with the --ignore-all-exports flag but the ignore-exports module attribute wasn't used, hyperlinks weren't created for non-exported names. This fix might not be as clean as one would wish (since --ignore-all-exports now results in ignore_all_exports = True *and* an additional OptIgnoreExports option for every module) but at least the bug seems to be resolved now. - - - - - 7d7ae106 by sven.panne at 2007-09-02T12:18:02+00:00 Install LICENSE in the correct place - - - - - 66eaa924 by David Waern at 2007-11-11T19:02:46+00:00 Fix a bug that made haddock loop - - - - - 4ed47b58 by David Waern at 2007-11-11T19:03:09+00:00 Rename java-script file (this wasn't merge correctly) - - - - - d569534a by David Waern at 2007-11-11T19:06:44+00:00 Don't require -B <ghc-libdir> when no argument files Change readInterfaceFile to take a Maybe Session, to avoid having to pass -B <ghc-libdir> to Haddock when there're no source files to process. This is nice when computing contents/index for external packages. - - - - - 373368bc by Neil Mitchell at 2007-01-11T18:22:44+00:00 Change from tabs to spaces in the ppHtmlIndex function - - - - - 6b063a77 by Neil Mitchell at 2007-01-12T12:17:46+00:00 Rewrite much of the index searching code, previously was too slow to execute on the base library with IE, the new version guarantees less than O(log n) operations be performed, where n is the number in the list (before was always O(n)) - - - - - bfad00b7 by David Waern at 2007-11-11T23:33:53+00:00 Fix conflicts - - - - - cd2dcc09 by Neil Mitchell at 2007-01-12T12:25:01+00:00 Make the max number of results 75 instead of 50, to allow map searching in the base library to work - - - - - 3ae74764 by Neil Mitchell at 2007-01-12T12:58:17+00:00 Make the search box in a form so that enter does the default search - - - - - 142103e5 by David Waern at 2007-11-12T00:03:18+00:00 Merge patch from the old branch: Fri Aug 31 13:21:45 CEST 2007 Duncan Coutts <duncan at haskell.org> * Add category: Development to .cabal file Otherwise it appears on the hackage website in the "Unclassified" category. - - - - - 22ec2ddb by David Waern at 2007-11-25T01:55:29+00:00 A a list of small improvements to the TODO file - - - - - eb0129f4 by Wolfgang Jeltsch at 2007-12-03T23:47:55+00:00 addition of type equality support (at least for HTML generation) - - - - - 816a7e22 by David Waern at 2007-12-08T15:46:26+00:00 Handle class operators correctly when rendering predicates - - - - - 68baaad2 by David Waern at 2007-12-08T16:15:54+00:00 Code layout changes - - - - - 09b77fb4 by David Waern at 2007-12-08T16:16:03+00:00 Handle infix operators correctly in the Type -> HsType translation - - - - - 31c36da2 by David Waern at 2007-12-08T16:24:27+00:00 Add ppLParendTypes/ppLParendType - - - - - b17cc818 by David Waern at 2007-12-08T16:26:12+00:00 Use ppParendType when printing types args in predicates - - - - - ffd1f2cf by David Waern at 2007-12-08T16:45:06+00:00 Fix rendering of instance heads to handle infix operators This is also a refactoring to share this code for rendering predicates. - - - - - ff886d45 by David Waern at 2007-12-08T17:27:46+00:00 Fix rendering of class operators - - - - - e2fcbb9e by David Waern at 2007-12-08T17:59:28+00:00 Fix a bug (use ppTyName instead of ppName to print names in type apps) - - - - - 79a1056e by David Waern at 2007-12-08T21:25:18+00:00 Update tests - - - - - 867741ac by David Waern at 2007-12-08T21:25:49+00:00 Give a diff on test failure - - - - - 7e5eb274 by David Waern at 2008-01-05T14:33:45+00:00 Add DrIFT commands - - - - - 3656454d by David Waern at 2008-01-05T20:26:00+00:00 Add "cabal-version: >= 1.2" to the cabal file - - - - - 77974efc by Simon Marlow at 2007-12-20T09:52:44+00:00 add an item - - - - - f6ac1708 by Simon Marlow at 2007-12-06T14:00:10+00:00 Source links must point to the original module, not the referring module - - - - - eda1d5c9 by David Waern at 2008-01-06T14:40:52+00:00 Manual merge of a patch to the 0.8 branch Thu Dec 6 15:00:10 CET 2007 Simon Marlow <simonmar at microsoft.com> * Source links must point to the original module, not the referring module - - - - - 378f4085 by David Waern at 2008-01-06T16:03:45+00:00 Change stability from stable to experimental - - - - - 8bdafe44 by David Waern at 2008-01-06T16:14:22+00:00 Add haskell.vim (it had been removed somehow) - - - - - ea34d02e by David Waern at 2008-01-06T16:36:57+00:00 Change version to 2.0.0.0 - - - - - 34631ac0 by David Waern at 2008-01-06T16:44:57+00:00 Add missing modules to the cabal file - - - - - 9e142935 by David Waern at 2008-01-06T17:25:42+00:00 Depend on ghc >= 6.8.2 && < 6.9 - - - - - 59f9eeaa by Simon Marlow at 2007-12-20T10:43:04+00:00 add build scripts - - - - - 1c29ae30 by Simon Marlow at 2007-12-20T10:47:07+00:00 update version number - - - - - fe16a3e4 by Simon Marlow at 2007-12-20T10:48:03+00:00 update version - - - - - f688530f by Simon Marlow at 2007-12-20T10:48:29+00:00 doc updates - - - - - ce71b611 by David Waern at 2008-01-07T13:46:32+00:00 Change version in docs and spec - - - - - 03ab8d6f by David Waern at 2008-01-07T13:47:38+00:00 Manually merge over changes to CHANGES for 0.9 - - - - - 39f1b042 by David Waern at 2008-01-07T15:17:41+00:00 Remove the -use-package flag, we don't support it anyway - - - - - 7274a544 by David Waern at 2008-01-07T15:33:05+00:00 Update CHANGES for 2.0.0.0 - - - - - 96594f5d by David Waern at 2008-01-07T15:46:49+00:00 Wibble - - - - - f4c5a4c4 by David Waern at 2008-01-07T15:55:36+00:00 Change url to repo in documentation - - - - - 8a4c77f0 by David Waern at 2008-01-07T16:00:54+00:00 Update CHANGES - - - - - cb3a9288 by David Waern at 2008-01-07T16:02:55+00:00 Documentation fix - - - - - d8e45539 by David Waern at 2008-01-07T16:12:00+00:00 Update docs to say that Haddock accets .lhs files and module names - - - - - 4b5ce824 by David Waern at 2008-01-07T16:12:25+00:00 Document -B option - - - - - 47274262 by David Waern at 2008-01-07T16:23:07+00:00 Update CHANGES - - - - - 7ff314a9 by David Waern at 2008-01-07T16:23:20+00:00 Remove --use-package, --package & --no-implicit.. flags from docs - - - - - 6c3819c0 by David Waern at 2008-01-07T16:23:52+00:00 Remove --no-implicit-prelide flag - - - - - 1b14ae40 by David Waern at 2008-01-07T16:32:26+00:00 Update the "Using literate or pre-processed source" section - - - - - 0117f620 by David Waern at 2008-01-07T16:41:55+00:00 Document the --optghc flag - - - - - 087ab1cf by David Waern at 2008-01-07T16:42:10+00:00 Remove the documenation section on derived instances The problem mentioned there doesn't exist in Haddock 2.0.0.0 - - - - - 7253951e by David Waern at 2008-01-07T16:48:40+00:00 Document OPTIONS_HADDOCK - - - - - 3b6bdcf6 by David Waern at 2008-01-07T16:56:54+00:00 Wibble - - - - - 3025adf9 by David Waern at 2008-01-07T17:08:14+00:00 Wibble - - - - - 5f30f1a0 by David Waern at 2008-01-07T17:15:44+00:00 Change synopsis field to description - - - - - 1673f54b by David Waern at 2008-01-07T17:18:21+00:00 Change my email address in the cabal file - - - - - 55aa9808 by David Waern at 2008-01-07T18:18:02+00:00 Add documentation for readInterfaceFile - - - - - eaea417f by David Waern at 2008-01-07T18:21:30+00:00 Export necessary stuff from Distribution.Haddock - - - - - 7ea18759 by David Waern at 2008-01-07T18:31:49+00:00 Remove dep on Cabal - - - - - 7b79c74e by David Waern at 2008-01-07T18:33:49+00:00 Remove dep on process - - - - - ce3054e6 by David Waern at 2008-01-16T23:01:21+00:00 Add feature-requsts from Henning Thielemann to TODO - - - - - 0c08f1ec by David Waern at 2008-01-16T23:03:02+00:00 Record a bug in TODO - - - - - b04605f3 by David Waern at 2008-01-23T16:59:06+00:00 Add a bug reported by Ross to TODO - - - - - 5b17c030 by David Waern at 2008-01-23T18:05:53+00:00 A a bug report to TODO - - - - - 1c993b0d by David Waern at 2008-01-25T16:30:25+00:00 Accept test output - - - - - c22fc0d0 by David Waern at 2008-01-25T16:34:49+00:00 Accept test output - - - - - 4b795811 by David Waern at 2008-01-25T16:38:37+00:00 Change Hidden.hs (test) to use OPTIONS_HADDOCK - - - - - c124dbd9 by David Waern at 2008-01-25T16:39:23+00:00 Accept test output - - - - - ec6f6eea by David Waern at 2008-01-25T16:42:08+00:00 Add Hidden.html.ref to tests - - - - - 1dc9610c by David Waern at 2008-02-02T20:50:51+00:00 Add a comment about UNPACK bug in TODO - - - - - 2d3f7081 by David Waern at 2008-02-09T22:33:24+00:00 Change the representation of DocNames Ross Paterson reported a bug where links would point to the defining module instead of the "best" module for an identifier (e.g Int pointing to GHC.Base instead of Data.Int). This patch fixes this problem by refactoring the way renamed names are represented. Instead of representing them by: > data DocName = Link Name | NoLink Name they are now represented as such: > data DocName = Documented Name Module | Undocumented Name and the the link-env looks like this: > type LinkEnv = Map Name Module There are several reasons for this. First of all, the bug was caused by changing the module part of Names during the renaming process, without changing the Unique field. This caused names to be overwritten during the loading of .haddock files (which caches names using the NameCache of the GHC session). So we might create new Uniques during renaming to fix this (but I'm not sure that would be problem-free). Instead, we just keep the Name and add the Module where the name is best documented, since it can be useful to keep the original Name around (for e.g. source-code location info and for users of the Haddock API). Also, the names Link/NoLink don't really make sense, since wether to use links or not is entirely up to the users of DocName. In the process of following this change into H.Backends.Html I removed the assumption that binder names are Undocumented (which was just an unnecessary assumption, the OccName is the only thing needed to render these). This will probably make it possible to get rid of the renamer and replace it with a traversal from SYB or Uniplate. Since DocName has changed, InterfaceFile has changed so this patch also increments the file-format version. No backwards-compatibility is implemented. - - - - - 0f28c921 by David Waern at 2008-02-09T23:00:36+00:00 H.GHC.Utils: remove unused imports/exports - - - - - 0c44cad5 by David Waern at 2008-02-10T00:28:13+00:00 H.GHC.Utils: add some functions that were removed by mistake - - - - - e3452f49 by David Waern at 2008-02-10T00:28:48+00:00 Fix some trivial warnings in H.InterfaceFile - - - - - a6d74644 by David Waern at 2008-02-10T00:48:06+00:00 Update the version message to fit in small terminals - - - - - 76c9cd3e by David Waern at 2008-02-10T14:47:39+00:00 Remove bugs from TODO that don't apply anymore since the port - - - - - 5e10e090 by David Waern at 2008-02-10T15:22:47+00:00 Remove bugs from TODO that weren't actual bugs - - - - - fef70878 by David Waern at 2008-02-10T15:23:44+00:00 Remove yet another item from TODO that was not an actual bug - - - - - e1af47b8 by David Waern at 2008-02-11T10:25:57+00:00 Bump the version number to 2.1.0 Since the exported datatype DocName has changed, we need to bump the major version number. Let's also drop the fourth version component, it's not that useful. - - - - - e3be7825 by David Waern at 2008-04-11T14:29:04+00:00 Add a bug to TODO - - - - - cb6574be by David Waern at 2008-04-11T16:00:45+00:00 Use the in-place haddock when running tests - - - - - c6d7af0d by David Waern at 2008-04-11T16:09:16+00:00 Turn off GHC warnings when running tests - - - - - 7f61b546 by David Waern at 2008-04-11T17:24:00+00:00 Add a flag for turning off all warnings - - - - - 883b8422 by David Waern at 2008-04-12T14:02:18+00:00 Fix printing of data binders - - - - - 2a0db8fc by David Waern at 2008-04-12T18:52:46+00:00 Fix missing parenthesis in constructor args bug - - - - - 1b3ac3f9 by David Waern at 2008-04-12T18:57:23+00:00 Simplify test suite and add tests I move all tests into one single directory to simplify things, and add a test for the last bug that was fixed. - - - - - 8f178376 by David Waern at 2008-04-12T19:00:15+00:00 Add a script for copying test output to "expected" output - - - - - 193e3a03 by David Waern at 2008-04-12T19:16:37+00:00 Remove two fixed bugs from TODO - - - - - ddc9130c by David Waern at 2008-04-12T19:37:06+00:00 Update test README - - - - - 956069c0 by David Waern at 2008-05-01T12:16:14+00:00 Update version number in spec and docs - - - - - 5478621c by David Waern at 2008-05-01T12:28:12+00:00 Remove claim of backwards compatibility from docs for readInterfaceFile - - - - - 4a16dea9 by David Waern at 2008-05-01T12:33:04+00:00 Update CHANGES - - - - - 804216fb by David Waern at 2008-05-01T12:43:16+00:00 Add a synopsis - - - - - fd0c84d5 by David Waern at 2008-05-01T12:44:44+00:00 Add Haddock.DocName to the cabal file - - - - - 9f4a7439 by David Waern at 2008-05-01T12:45:53+00:00 Remove -fglasgow-exts and -fasm - - - - - aee7c145 by David Waern at 2008-05-01T12:54:01+00:00 Add LANGUAGE pragmas to source files - - - - - 9a58428b by David Waern at 2008-05-01T12:54:19+00:00 Add extensions to cabal file - - - - - 494f1bee by David Waern at 2008-05-01T13:12:09+00:00 Export DocName in the API - - - - - c938196b by David Waern at 2008-05-01T13:12:19+00:00 Add hide options to some source files - - - - - 236e86af by Neil Mitchell at 2008-06-07T20:45:10+00:00 Rewrite the --hoogle flag support - - - - - 6d910950 by Neil Mitchell at 2008-06-14T10:56:50+00:00 Simplify the newtype/data outputting in Hoogle, as haddock does it automatically - - - - - f87a95a8 by Neil Mitchell at 2008-06-14T12:10:18+00:00 Add initial structure for outputting documentation as well, but does not yet output anything - - - - - 7c3bce54 by Neil Mitchell at 2008-06-14T12:27:07+00:00 Remove <document comment> from the Hoogle output - - - - - 9504a325 by Neil Mitchell at 2008-06-16T06:33:21+00:00 Default to "main" if there is no package, otherwise will clobber hoogle's hoogle info - - - - - 4a794a79 by Neil Mitchell at 2008-06-16T06:53:29+00:00 Change packageName to packageStr, as it better reflects the information stored in it - - - - - 7abc9baf by Neil Mitchell at 2008-06-16T07:09:49+00:00 Add modulePkgInfo to Haddock.GHC.Utils, which gives back package name and version info - - - - - 8ca11514 by Neil Mitchell at 2008-06-16T07:13:48+00:00 Change Hoogle to take the package name and package version separately - - - - - a6da452d by Neil Mitchell at 2008-06-18T11:29:46+00:00 In Hoogle do not list things that are not local to this module - - - - - 974b76b7 by David Waern at 2008-06-19T18:40:13+00:00 Be more consistent with GHC API naming in H.GHC.Utils - - - - - 2facb4eb by David Waern at 2008-06-19T19:03:03+00:00 Update test output - - - - - c501de72 by David Waern at 2008-06-26T20:26:49+00:00 Use ghc-paths to get the lib dir The path can still be overridden using the -B flag. It's not longer required to pass the lib dir to the program that runs the test suite. - - - - - ac4c6836 by David Waern at 2008-06-26T20:33:08+00:00 Update CHANGES - - - - - 9d21c60a by David Waern at 2008-06-26T20:34:53+00:00 Update README - - - - - 741448f0 by David Waern at 2008-06-26T21:12:57+00:00 Improve wording in the help message - - - - - b1b42b11 by David Waern at 2008-06-30T10:16:17+00:00 Rename ForeignType - - - - - 6d6c2b34 by David Waern at 2008-06-30T10:25:09+00:00 Rename TyFamily - - - - - 8d1125ed by David Waern at 2008-06-30T10:37:21+00:00 Rename type patterns - - - - - 7610a4cb by David Waern at 2008-06-30T10:45:07+00:00 Rename associated types - - - - - 8eeba14c by David Waern at 2008-06-30T10:47:41+00:00 Remove the TODO file now that we have a trac - - - - - 1af5b25b by David Waern at 2008-07-02T18:19:28+00:00 Render type family declarations (untested) - - - - - ceb99797 by David Waern at 2008-07-02T18:24:06+00:00 Remove redundant check for summary when rendering data types - - - - - b36a58e0 by David Waern at 2008-07-02T22:01:38+00:00 More support for type families and associated types Now we just need to render the instances - - - - - 78784879 by David Waern at 2008-07-07T22:13:58+00:00 Remove filtering of instances We were filtering out all instances for types with unknown names. This was probably an attempt to filter out instances for internal types. I am removing the filtering for the moment, and will try to fix this properly later. - - - - - 3e758dad by David Waern at 2008-06-30T18:50:30+00:00 Run haddock in-place during testing - - - - - d9dab0ce by David Waern at 2008-07-08T21:04:32+00:00 Remove index.html and doc-index.html from output, they should not be versioned - - - - - 3e6c4681 by David Waern at 2008-07-08T21:06:42+00:00 Update test output following change to instance filtering - - - - - e34a3f14 by David Waern at 2008-07-12T16:48:28+00:00 Stop using the map from exported names to declarations During creation of the interface, we were using two maps: one from exported names to declarations, and one from all defined names in the module to declarations. The first contained subordinate names while the second one didn't. The first map was never used to look up names not defined in the associated module, so if we add subordinate names to the second map, we could use it everywhere. That's that this patch does. This simplifies code because we don't have to pass around two maps everywhere. We now store the map from locally defined things in the interface structure instead of the one from exported names. - - - - - 2e1d2766 by David Waern at 2008-07-12T16:55:21+00:00 Get the all locally defined names from GHC API We previously had some code to compute all locally defined names in a module including subordinate names. We don't need it since we can get the names from modInfoTyThings in the GHC API. - - - - - bf637994 by David Waern at 2008-07-13T13:09:16+00:00 Refactoring in H.Interface.Create We were creating a doc map, a declaration map and a list of entities separately by going through the HsGroup. These structures were all used to build the interface of a module. Instead of doing this, we can start by creating a list of declarations from the HsGroup, then collect the docs directly from this list (instead of using the list of entities), creating a documentation map. We no longer need the Entity data type, and we can store a single map from names to declarations and docs in the interface, instead of the declaration map and the doc map. This way, there is only one place where we filter out the declarations that we don't want, and we can remove a lot of code. Another advantage of this is that we can create the exports directly out of the list of declarations when we export the full module contents. (Previously we did a look up for each name to find the declarations). This is faster and removes another point where we depend on names to identify exported declarations, which is good because it eliminates problems with instances (which don't have names). - - - - - 547e410e by David Waern at 2008-07-13T13:34:51+00:00 Remove FastString import and FSLIT macro in H.I.Create -- they were unused - - - - - 693759d1 by David Waern at 2008-07-13T13:36:23+00:00 Remove unused import from H.I.Create - - - - - cde6e7fb by David Waern at 2008-07-13T13:51:54+00:00 Small touches - - - - - 96de8f1d by David Waern at 2008-07-20T11:21:46+00:00 Preparation for rendering instances as separate declarations We want to be able to render instances as separate declarations. So we remove the Name argument of ExportDecl, since instances are nameless. This patch also contains the first steps needed to gather type family instances and display them in the backend, but the implementation is far from complete. Because of this, we don't actually show the instances yet. - - - - - b0f824fb by David Waern at 2008-07-20T15:53:08+00:00 Follow changes to ExportDecl in Hoogle - - - - - 1192eff3 by Neil Mitchell at 2008-06-26T00:28:10+00:00 Change how the Hoogle backend outputs classes, adding the context in - - - - - 7a0d1464 by Neil Mitchell at 2008-06-26T00:28:46+00:00 Remove the indent utility function from Hoogle backend - - - - - 3361241b by Neil Mitchell at 2008-06-26T09:45:09+00:00 Add support for Hoogle writing ForeignImport/ForeignExport properly - - - - - 795ad3bf by Neil Mitchell at 2008-06-26T12:15:25+00:00 Flesh out the Hoogle code to render documentation - - - - - 23277995 by Neil Mitchell at 2008-06-26T14:56:41+00:00 Fix a bug in the Hoogle backend, unordered lists were being written out <ul>...</u> - - - - - db739b27 by Neil Mitchell at 2008-06-26T15:09:54+00:00 Remove any white space around a <li> element - - - - - f2e6bb8c by Neil Mitchell at 2008-07-10T15:30:47+00:00 Remove the TODO in the Hoogle HTML generation, was already done - - - - - 693ec9a3 by Neil Mitchell at 2008-07-10T15:53:00+00:00 Put brackets round operators in more places in the Hoogle output - - - - - 842313aa by Neil Mitchell at 2008-07-10T16:01:25+00:00 Print type signatures with brackets around the name - - - - - cf93deb0 by David Waern at 2008-07-20T17:04:22+00:00 Bump version number to 2.2.0 - - - - - 30e6a8d1 by David Waern at 2008-07-20T17:04:41+00:00 Resolve conflicts in H.B.Hoogle - - - - - 1f0071c9 by David Waern at 2008-07-23T23:05:01+00:00 Add "all" command to runtests.hs that runs all tests despite failures - - - - - f2723023 by David Waern at 2008-07-23T23:08:39+00:00 Update tests/README - - - - - c0304a11 by David Waern at 2008-07-23T23:21:15+00:00 Be compatible with GHC 6.8.3 The cabal file is converted to use the "new" syntax with explicit Library and Executable sections. We define the __GHC_PATCHLEVEL__ symbol using a conditinal cpp-options field in the cabal file. (Ideally, Cabal would define the symbol for us, like it does for __GLASGOW_HASKELL__). We use these symbols to #ifdef around a small difference between 6.8.2 and 6.8.3. Previously, we only supported GHC 6.8.2 officially but the dependencies field said "ghc <= 6.9". This was just for convenience when testing against the (then compatible) HEAD version of GHC, and was left in the release by mistake. Now, we support both GHC 6.8.2 and 6.8.3 and the dependencies field correctly reflects this. - - - - - 88a5fe71 by David Waern at 2008-07-23T23:54:16+00:00 Depend on the currently available ghc-paths versions only - - - - - 8738d97b by David Waern at 2008-07-24T10:50:44+00:00 FIX haskell/haddock#44: Propagate parenthesis level when printing documented types - - - - - 05339119 by David Waern at 2008-07-24T16:06:18+00:00 Drop unnecessary parenthesis in types, put in by the user We were putting in parenthesis were the user did. Let's remove this since it just clutters up the types. The types are readable anyway since we print parens around infix operators and do not rely on fixity levels. When doing this I discovered that we were relying on user parenthesis when printin types like (a `O` b) c. This patchs fixes this problem so that parenthesis are always inserted around an infix op application in case it is applied to further arguments, or if it's an arguments to a type constructor. Tests are updated. - - - - - b3a99828 by David Waern at 2008-07-24T10:19:43+00:00 Print parenthesis around non-atomic banged types Fixes half of haskell/haddock#44 - - - - - ab5238e0 by David Waern at 2008-07-24T22:07:49+00:00 Add a reference file for the TypeFamilies test - - - - - 1941cc11 by David Waern at 2008-07-25T17:15:53+00:00 Simplify definition of pretty and trace_ppr - - - - - e3bfa33c by David Waern at 2008-07-25T17:18:27+00:00 Warning messages Output a warning when filtering out data/type instances and associated types in instances. We don't show these in the documentation yet, and we need to let the user know. - - - - - 9b85fc89 by David Waern at 2008-07-25T17:45:40+00:00 Doc: Mention Hoogle in the Introduction - - - - - afb2dd60 by David Waern at 2008-07-25T17:49:00+00:00 Doc: update -B description - - - - - 584c0c91 by David Waern at 2008-07-25T18:11:38+00:00 Doc: describe -w flag - - - - - 77619c24 by David Waern at 2008-07-28T12:29:07+00:00 Remove TODO from cabal file - - - - - 96717d5f by David Waern at 2008-07-28T12:29:27+00:00 Support type equality predicates - - - - - c2fd2330 by David Waern at 2008-07-29T19:45:14+00:00 Move unL from H.B.Hoogle to H.GHC.Utils I like Neil's shorter unL better than unLoc from the GHC API. - - - - - c4c3bf6a by David Waern at 2008-07-29T19:47:36+00:00 Do not export ATs when not in list of subitems - - - - - bf9a7b85 by David Waern at 2008-08-03T11:42:59+00:00 Filter out ForeignExports - - - - - df59fcb0 by David Waern at 2008-08-03T14:02:51+00:00 Filter out more declarations The previous refactorings in H.I.Create introduced a few bugs. Filtering of some types of declarations that we don't handle was removed. This patch fixes this. - - - - - 2f8a958b by David Waern at 2008-08-03T15:24:07+00:00 Move reL to H.GHC.Utils so we can use it everywhere - - - - - 8ec15efd by David Waern at 2008-08-03T15:25:00+00:00 Use isVanillaLSig from GHC API instead of home brewn function - - - - - 300f93a2 by David Waern at 2008-08-03T15:25:27+00:00 Filter out separately exported ATs This is a quick and dirty hack to get rid of separately exported ATs. We haven't decided how to handle them yet. No warning message is given. - - - - - 8776d1ec by David Waern at 2008-08-03T16:21:21+00:00 Filter out more declarations and keep only vanilla type sigs in classes - - - - - ea07eada by David Waern at 2008-08-03T16:48:00+00:00 Fix layout - - - - - dd5e8199 by David Waern at 2008-08-03T16:50:52+00:00 Move some utility functions from H.I.Create to H.GHC.Utils - - - - - 4a1dbd72 by David Waern at 2008-08-03T17:39:55+00:00 Do not filter out doc declarations - - - - - 0bc8dca4 by David Waern at 2008-08-03T17:47:26+00:00 Filter out separately exported ATs (take two) - - - - - af970fe8 by David Waern at 2008-08-03T22:39:17+00:00 Update CHANGES - - - - - 5436ad24 by David Waern at 2008-08-03T22:40:20+00:00 Bump version number to 2.2.1 - - - - - d66de448 by David Waern at 2008-08-05T19:00:32+00:00 Remove version restriction on ghc-paths - - - - - 534b1364 by David Waern at 2008-08-05T19:04:35+00:00 Bump version to 2.2.2 and update CHANGES - - - - - 549188ff by David Waern at 2008-08-05T19:16:49+00:00 Fix CHANGES - - - - - 0d156bb4 by Luke Plant at 2008-08-11T15:20:59+00:00 invoking haddock clarification and help - - - - - 748295cc by David Waern at 2008-08-11T18:56:37+00:00 Doc: say that the --hoogle option is functional - - - - - 43301db4 by David Waern at 2008-08-05T19:26:08+00:00 Change ghc version dependency to >= 6.8.2 - - - - - 3e5a53b6 by David Waern at 2008-08-10T22:42:05+00:00 Make H.GHC.Utils build with GHC HEAD - - - - - 7568ace0 by David Waern at 2008-08-11T19:41:54+00:00 Import Control.OldException instead of C.Exception when using ghc >= 6.9 We should really test for base version instead, but I don't currently know which version to test for. - - - - - b71ae991 by David Waern at 2008-08-12T22:40:39+00:00 Make our .haddock file version number depend on the GHC version We need to do this, since our .haddock format can potentially change whenever GHC's version changes (even when only the patchlevel changes). - - - - - 6307ce3f by David Waern at 2008-08-12T22:49:57+00:00 Remove matching on NoteTy in AttachInstances, it has been removed - - - - - 2dbcfd5f by David Waern at 2008-08-12T23:02:02+00:00 Comment out H.GHC.loadPackages - it is unused and doesn't build with ghc >= 6.9 - - - - - c74db5c2 by David Waern at 2008-08-12T23:03:58+00:00 Hide <.> from GHC import in Hoogle only for ghc <= 6.8.3 - - - - - 69a44ebb by David Waern at 2008-08-12T23:11:12+00:00 Follow changes to parseDynamic/StaticFlags - - - - - 5881f3f0 by David Waern at 2008-08-13T21:43:58+00:00 Add __GHC_PATCHLEVEL__ symbol also when building the library - - - - - 8574dc11 by David Waern at 2008-08-13T21:44:17+00:00 Follow move of package string functions from PackageConfig to Module - - - - - c9baa77f by David Waern at 2008-08-13T21:45:29+00:00 Follow extensible exceptions changes - - - - - 9092de15 by David Waern at 2008-08-13T21:46:20+00:00 Update test following Haddock version change - - - - - ebe569a4 by David Waern at 2008-08-13T21:46:54+00:00 Follow changes to parseDynamic- parseStaticFlags in GHC - - - - - b8a5ffd3 by David Waern at 2008-08-13T21:47:36+00:00 Follow changes to Binary in GHC 6.9 - - - - - edfda1cc by David Waern at 2008-08-13T21:50:17+00:00 Change ghc version dependency to >= 6.8.2 && <= 6.9 - - - - - d59be1cf by Neil Mitchell at 2008-08-12T16:02:53+00:00 Output all items, even if they are not defined in this module - ensures map comes from Prelude, not just GHC.Base - - - - - dda93b9f by Neil Mitchell at 2008-08-12T21:37:32+00:00 Add support for type synonyms to Hoogle, was accidentally missing before (woops!) - - - - - b6ee795c by Neil Mitchell at 2008-08-13T14:03:24+00:00 Generalise Hoogle.doc and add a docWith - - - - - 415e1bb2 by Neil Mitchell at 2008-08-13T14:03:46+00:00 Make Hoogle add documentation to a package - - - - - 790a1202 by Neil Mitchell at 2008-08-18T12:52:43+00:00 Use the same method to put out signatures as class methods in the Hoogle backend - - - - - ded37eba by Neil Mitchell at 2008-08-18T12:53:04+00:00 Remove Explicit top-level forall's when pretty-printing signatures - - - - - 6468c722 by Neil Mitchell at 2008-08-20T07:59:13+00:00 Simplify the code by removing not-to-important use of <.> in the Hoogle back end - - - - - 788c3a8b by Neil Mitchell at 2008-08-21T18:20:24+00:00 In the hoogle back end, markup definition lists using <i>, not <b> - - - - - 77d4b000 by Ian Lynagh at 2008-08-14T10:49:14+00:00 Add a Makefile for GHC's build system. Still won't work yet, but we're closer - - - - - 920440d7 by Ian Lynagh at 2008-08-27T18:06:46+00:00 Add haddock.wrapper - - - - - bcda925f by Ian Lynagh at 2008-08-27T18:07:02+00:00 Add a manual Cabal flag to control the ghc-paths dependency - - - - - 04d194e2 by Ian Lynagh at 2008-08-27T20:41:27+00:00 Update extensions in Cabal file Use ScopedTypeVariables instead of PatternSignatures - - - - - 12480043 by Ian Lynagh at 2008-08-27T20:41:55+00:00 Increase the upper bound on the GHC version number - - - - - b1f809a5 by Ian Lynagh at 2008-08-27T21:32:22+00:00 Fix some warnings - - - - - aea0453d by Ian Lynagh at 2008-08-28T14:22:29+00:00 Fixes for using haddock in a GHC build tree - - - - - ad23bf86 by Ian Lynagh at 2008-08-28T21:14:27+00:00 Don't use Cabal wrappers on Windows - - - - - 35858e4c by Ian Lynagh at 2008-08-29T00:07:42+00:00 Fix in-tree haddock on Windows - - - - - c2642066 by Ian Lynagh at 2008-09-03T22:35:53+00:00 follow library changes - - - - - 2eb55d50 by Ian Lynagh at 2008-09-07T18:52:51+00:00 bindist fixes - - - - - 3daa5b59 by Ian Lynagh at 2008-09-10T16:58:18+00:00 We need to tell haddock that its datasubdir is . or it can't find package.conf - - - - - 388fd8c2 by Ian Lynagh at 2008-09-10T19:47:44+00:00 Fix haddock inplace on Windows - - - - - 70a641c1 by Ian Lynagh at 2008-09-10T22:15:44+00:00 Fix installed haddock on Windows - - - - - 83c1e997 by Neil Mitchell at 2008-09-11T10:48:55+00:00 Import GHC.Paths if not IN_GHC_TREE, seems to match the use of GHC.Paths functions much better - - - - - b452519b by Ian Lynagh at 2008-09-12T12:58:24+00:00 Add a LANGUAGE ForeignFunctionInterface pragma - - - - - afbd592c by Ian Lynagh at 2008-09-12T12:59:13+00:00 Wibble imports - - - - - 547ac4ad by Ian Lynagh at 2008-09-14T15:34:22+00:00 Add a "#!/bin/sh" to haddock.wrapper - - - - - f207a807 by Ian Lynagh at 2008-09-15T10:02:32+00:00 Use "exec" when calling haddock in the wrapper - - - - - 2ee68509 by Thomas Schilling at 2008-09-15T09:09:16+00:00 Port Haddock.Interface to new GHC API. This required one bigger change: 'readInterfaceFile' used to take an optional 'Session' argument. This was used to optionally update the name cache of an existing GHC session. This does not work with the new GHC API, because an active session requires the function to return a 'GhcMonad' action, but this is not possible if no session is provided. The solution is to use an argument of functions for reading and updating the name cache and to make the function work for any monad that embeds IO, so it's result type can adapt to the calling context. While refactoring, I tried to make the code a little more self-documenting, mostly turning comments into function names. - - - - - 3bb96431 by Thomas Schilling at 2008-09-15T09:09:37+00:00 Reflect GHC API changes. - - - - - 2e60f714 by Thomas Schilling at 2008-09-15T09:10:37+00:00 Port Haddock.GHC.Typecheck to new GHC API. - - - - - 9cfd4cff by Thomas Schilling at 2008-09-15T09:11:00+00:00 Port Haddock.GHC to new GHC API. - - - - - caffa003 by Thomas Schilling at 2008-09-15T09:11:25+00:00 Port Main to new GHC API. - - - - - 069a4608 by Ian Lynagh at 2008-09-21T11:19:00+00:00 Fix paths used on Windows frmo a GHC tree: There is no whare directory - - - - - 7ceee1f7 by Ian Lynagh at 2008-09-21T12:20:16+00:00 Fix the in-tree haddock on Windows - - - - - 0d486514 by Ian Lynagh at 2008-09-23T18:06:58+00:00 Increase the GHC upper bound from 6.11 to 6.13 - - - - - f092c414 by Neil Mitchell at 2008-09-11T14:56:07+00:00 Do not wrap __ in brackets - - - - - 036bdd13 by Ian Lynagh at 2008-09-28T01:42:35+00:00 Fix building haddock when GhcProfiled=YES - - - - - 01434a89 by David Waern at 2008-09-24T20:24:21+00:00 Add PatternSignatures LANGUAGE pragma to Main and Utils - - - - - 1671a750 by David Waern at 2008-10-02T22:57:25+00:00 For source links, get original module from declaration name instead of environment. Getting it from the environment must have been a remnant from the times when we were using unqualified names (versions 0.x). - - - - - a25dde99 by David Waern at 2008-10-02T22:59:57+00:00 Remove ifaceEnv from Interface - it's no longer used - - - - - 610993da by David Waern at 2008-10-02T23:04:58+00:00 Write a comment about source links for type instance declarations - - - - - 5a96b5d5 by Thomas Schilling at 2008-10-03T10:45:08+00:00 Follow GHC API change of parseModule. - - - - - 5a943ae5 by Ian Lynagh at 2008-10-03T15:56:58+00:00 TAG 2008-10-03 - - - - - 76cdd6ae by Thomas Schilling at 2008-10-08T12:29:50+00:00 Only load modules once when typechecking with GHC. This still doesn't fix the memory leak since the typechecked source is retained and then processed separately. To fix the leak, modules must be processed directly after typechecking. - - - - - 7074d251 by David Waern at 2008-10-09T23:53:54+00:00 Interleave typechecking with interface creation At the same time, we fix a bug where the list of interfaces were processed in the wrong order, when building the links and renaming the interfaces. - - - - - 4b9b2b2d by David Waern at 2008-10-09T23:54:49+00:00 Add some strictness annotations in Interface We add some strictness annotations to the fields of Interface, so that less GHC data is hold on to during processing. - - - - - 22035628 by David Waern at 2008-10-10T20:02:31+00:00 Remove typecheckFiles and MonadUtils import from H.GHC.Typeccheck - - - - - be637ad3 by David Waern at 2008-10-10T20:33:38+00:00 Make Haddock build with GHC 6.8.2 - - - - - 523b3404 by David Waern at 2008-10-10T21:08:09+00:00 Fix documentation for createInterfaces - - - - - e1556702 by David Waern at 2008-10-10T21:26:19+00:00 Hide H.Utils in library - - - - - a8e751c3 by David Waern at 2008-10-10T21:34:59+00:00 Add back .haddock file versioning based on GHC version It was accidentally removed in the patch for GHC 6.8.2 compatibility - - - - - 06fb3c01 by David Waern at 2008-10-10T21:47:15+00:00 Bump version number to 2.3.0 - - - - - ff087fce by David Waern at 2008-10-10T22:35:49+00:00 Add support for DocPic The support for DocPic was merged into the GHC source long ago, but the support in Haddock was forgotten. Thanks Peter Gavin for submitting this fix! - - - - - 3af85bf6 by David Waern at 2008-10-10T23:34:05+00:00 Update tests - - - - - 0966873c by Simon Marlow at 2008-10-10T14:43:04+00:00 no need for handleErrMsg now, we don't throw any ErrMsgs - - - - - f1870de3 by Clemens Fruhwirth at 2008-10-10T13:29:36+00:00 Compile with wrapper but remove it for dist-install - - - - - 7b440dc2 by David Waern at 2008-10-11T14:02:25+00:00 Remove interface from LinksInfo It was there to know the documentation home module when creating a wiki link, but we already know this since we have the DocName. - - - - - e5729e6a by David Waern at 2008-10-15T20:49:18+00:00 Wibble - - - - - b2a8e01a by David Waern at 2008-10-15T21:03:36+00:00 Use type synonyms for declarations and docs in H.I.Create - - - - - be71a15b by David Waern at 2008-10-15T21:12:17+00:00 Comment out unused type family stuff completely - - - - - 91aaf075 by David Waern at 2008-10-15T21:49:04+00:00 Wibble - - - - - 42ba4eb4 by David Waern at 2008-10-15T21:53:53+00:00 Move convenient type synonym to H.Types - - - - - db11b723 by David Waern at 2008-10-15T22:14:07+00:00 Add DeclInfo to H.Types - - - - - 193552b6 by David Waern at 2008-10-15T22:15:01+00:00 Add subordinates with docs to the declaration map The only place in the code where we want the subordinates for a declaration is right after having looked up the declaration in the map. And since we include subordinates in the map, we might as well take the opportunity to store those subordinates that belong to a particular declaration together with that declaration. We also store the documentation for each subordinate. - - - - - 31e6eebc by David Waern at 2008-10-16T17:18:47+00:00 Wibble - - - - - 0dcbd79f by David Waern at 2008-10-16T20:58:42+00:00 Fix haskell/haddock#61 We were not getting docs for re-exported class methods. This was because we were looking up the docs in a map made from the declarations in the current module being rendered. Obviously, re-exported class methods come from another module. Class methods and ATs were the only thing we were looking up using the doc map, everything else we found in the ExporItems. So now I've put subordinate docs in the ExportItem's directly, to make things a bit more consistent. To do this, I added subordinates to the the declarations in the declaration map. This was easy since we were computing subordinates anyway, to store stand-alone in the map. I added a new type synonym 'DeclInfo', which is what we call what is now stored in the map. This little refactoring removes duplicate code to retrieve subordinates and documentation from the HsGroup. - - - - - de47f20a by David Waern at 2008-10-16T22:06:35+00:00 Document function and improve its layout - - - - - e74e625a by Thomas Schilling at 2008-10-20T11:12:57+00:00 Force interface more aggressively. For running Haddock on GHC this reduces memory usage by about 50 MB on a 32 bit system. A heap profile shows total memory usage peak at about 100 MB, but actual usage is at around 300 MB even with compacting GC (+RTS -c). - - - - - b63ac9a1 by David Waern at 2008-10-20T20:25:50+00:00 Make renamer consistent Instead of explicitly making some binders Undocumented, treat all names the same way (that is, try to find a Documented name). - - - - - f6de0bb0 by Ian Lynagh at 2008-09-19T00:54:43+00:00 TAG GHC 6.10 fork - - - - - 74599cd0 by David Waern at 2008-10-20T21:13:24+00:00 Do not save hidden modules in the .haddock file We were saving interfaces of all processed modules including those hidden using {-# OPTIONS_HADDOCK hide #-} in the .haddock file. This caused broken links when generating the index for the libraries that come with GHC. This patch excludes modules with hidden documentation when writing .haddock files. It should fix the above problem. - - - - - 7b6742e9 by David Waern at 2008-10-21T19:54:52+00:00 Do not save hidden modules in the .haddock file (also for ghc >= 6.9) When writing the first patch, I forgot to do the fix in both branches of an #if macro. - - - - - b99b1951 by David Waern at 2008-10-22T20:04:18+00:00 Remove subordinate map and its usage It is not needed now that we store subordinate names in the DeclInfo map. - - - - - da97cddc by David Waern at 2008-10-22T20:11:46+00:00 Tidy up code in H.I.Create a little Remove commented out half-done type instance support, and remove DeclWithDoc synonym. - - - - - 6afa76f3 by David Waern at 2008-10-22T21:17:29+00:00 Fix warnings in H.GHC.Utils - - - - - 171ea1e8 by David Waern at 2008-10-22T21:35:04+00:00 Fix warnings in H.Utils - - - - - c8cb3b91 by David Waern at 2008-10-22T21:36:49+00:00 Wibble - - - - - 767fa06a by David Waern at 2008-10-27T19:59:04+00:00 Make named doc comments into ExportDoc instead of ExportDecl Fixes a crash when processing modules without export lists containing named docs. - - - - - e638bbc6 by David Waern at 2008-11-02T22:21:10+00:00 Add HCAR entry - - - - - 92b4ffcf by David Waern at 2008-11-02T22:44:19+00:00 Update CHANGES - - - - - 84d4da6e by David Waern at 2008-11-03T11:25:04+00:00 Add failing test for template haskell crash - - - - - 2a9cd2b1 by David Waern at 2008-11-04T21:13:44+00:00 Add tests/TH.hs - - - - - 8a59348e by David Waern at 2008-11-04T21:30:26+00:00 TAG 2.3.0 - - - - - 54f70d31 by Thomas Schilling at 2008-10-24T17:04:08+00:00 Enable framed view of the HTML documentation. This patch introduces: - A page that displays the documentation in a framed view. The left side will show a full module index. Clicking a module name will show it in the right frame. If Javascript is enabled, the left side is split again to show the modules at the top and a very short synopsis for the module currently displayed on the right. - Code to generate the mini-synopsis for each module and the mini module index ("index-frames.html"). - CSS rules for the mini-synopsis. - A very small amount of javascript to update the mini-synopsis (but only if inside a frame.) Some perhaps controversial things: - Sharing code was very difficult, so there is a small amount of code duplication. - The amount of generated pages has been doubled, since every module now also gets a mini-synopsis. The overhead should not be too much, but I haven't checked. Alternatively, the mini-synopsis could also be generated using Javascript if we properly annotate the actual synopsis. - - - - - 5d7ea5a6 by David Waern at 2008-11-04T23:20:17+00:00 Follow change to ExportDecl in frames code - - - - - 60e16308 by David Waern at 2008-11-04T23:35:26+00:00 Update CHANGES - - - - - d63fd26d by David Waern at 2008-11-04T23:37:43+00:00 Bump version number - - - - - c1660c39 by David Waern at 2008-11-04T23:44:46+00:00 Update CHANGES - - - - - 995ab384 by David Waern at 2008-11-04T23:55:21+00:00 Remove .ref files from tests/output/ - - - - - 1abbbe75 by David Waern at 2008-11-04T23:57:41+00:00 Output version info before running tests - - - - - 649b182f by David Waern at 2008-11-05T22:45:37+00:00 Add ANNOUNCE message - - - - - c36ae0bb by David Waern at 2008-11-05T23:15:35+00:00 Update ANNOUNCE - - - - - 9c4f3d40 by David Waern at 2008-11-05T23:18:30+00:00 Wibble - - - - - 5aac87ce by David Waern at 2008-11-06T21:07:48+00:00 Depend on base 4.* when using GHC >= 6.9, otherwise 3.* - - - - - b9796a74 by David Waern at 2008-11-06T21:13:40+00:00 Bump version to 2.4.1 and update CHANGES - - - - - d4b26baa by David Waern at 2008-11-06T21:26:33+00:00 Depend on base 4.0.* instead of 4.* - - - - - 2cb0903c by David Waern at 2008-11-06T21:46:53+00:00 Fix warnings in H.B.HH and H.B.HH2 - - - - - e568e89a by David Waern at 2008-11-06T21:47:12+00:00 Fix warnings in Haddock.ModuleTree - - - - - 9dc14fbd by David Waern at 2008-11-06T21:47:52+00:00 Fix warnings in Haddock.Version - - - - - 02ac197c by David Waern at 2008-11-06T21:51:31+00:00 Fix warnings in H.InterfaceFile and H.Options - - - - - 63e7439a by David Waern at 2008-11-06T21:59:45+00:00 Fix warnings in H.GHC.Typecheck - - - - - 4bca5b68 by David Waern at 2008-11-08T13:43:42+00:00 Set HscTarget to HscNothing instead of HscAsm There used to be a bug in the GHC API that prevented us from setting this value. - - - - - 07357aec by David Waern at 2008-11-09T22:27:00+00:00 Re-export NameCache and friends from Distribution.Haddock - - - - - ea554b5a by David Waern at 2008-11-09T23:14:10+00:00 Add Haddock.GHC.Utils to other-modules in library - - - - - 74aecfd7 by David Waern at 2008-11-10T01:18:57+00:00 Export DocName in the library - - - - - 241a58b3 by David Waern at 2008-11-10T01:19:18+00:00 Document the functions in H.DocName - - - - - edc2ef1b by David Waern at 2008-11-10T01:20:52+00:00 Export H.DocName in the library - - - - - 4f588d55 by David Waern at 2008-11-10T01:29:14+00:00 Make DocName an instance of NamedThing - - - - - b4647244 by David Waern at 2008-11-15T22:58:18+00:00 Reflect version bump in test suite - - - - - 4bee8ce2 by David Waern at 2008-11-15T22:58:45+00:00 Update tests For unknown reasons, test output for Bug1 and Test has changed for the better. - - - - - 1690e2f9 by David Waern at 2008-11-15T22:59:33+00:00 Store hidden modules in .haddock files We store documentation for an entity in the 'InstalledInterface' of the definition site module, and never in the same structure for a module which re-exports the entity. So when a client of the Haddock library wants to look up some documentation, he/she might need to access a hidden module. But we currently don't store hidden modules in the .haddock files. So we add the hidden modules and the Haddock options to the .haddock files. The options will be used to filter the module list to obtain the visible modules only, which is necessary for generating the contents and index for installed packages. - - - - - 8add6435 by David Waern at 2008-11-16T14:35:50+00:00 Bump major version number due to .haddock file format change - - - - - 48bfcf82 by David Waern at 2008-11-23T14:32:52+00:00 Update tests to account for version number bump - - - - - 0bbd1738 by David Waern at 2008-11-23T14:33:31+00:00 HADDOCK_DATA_DIR changed to haddock_datadir - - - - - 5088b78c by David Waern at 2008-11-23T17:13:21+00:00 FIX haskell/haddock#45: generate two anchors for each name We generate two anchor tags for each name, one where we don't escape the name and one where we URI-encode it. This is for compatibility between IE and Opera. Test output is updated. - - - - - 5ee5ca3b by Neil Mitchell at 2008-11-27T14:38:11+00:00 Drop HsDocTy annotations, they mess up pretty printing and also have a bracketing bug (#2584) - - - - - 51c014e9 by Roman Cheplyaka at 2008-11-27T22:27:36+00:00 Allow referring to a specific section within a module in a module link Fixes haskell/haddock#65 - - - - - 4094bdc5 by David Waern at 2008-11-28T21:13:33+00:00 Update tests following anchor change - - - - - f89552dd by Thomas Schilling at 2008-11-29T16:16:20+00:00 Haddock really shouldn't try to overwrite files. - - - - - 98127499 by David Waern at 2008-12-07T14:09:15+00:00 Solve conflict - - - - - 319356c5 by David Waern at 2008-10-22T21:16:55+00:00 Add -Wall -Werror to ghc-options - - - - - 3c4968c9 by David Waern at 2008-11-04T23:38:56+00:00 TAG 2.4.0 - - - - - 4b21e003 by David Waern at 2008-11-06T21:14:04+00:00 TAG 2.4.1 - - - - - 8e0cad5c by David Waern at 2008-12-07T14:12:54+00:00 Remove -Werror - - - - - 299d6deb by David Waern at 2008-12-07T14:25:18+00:00 Remove -Wall, we'll focus on warnings after 6.10.2 is out - - - - - 5f4216b6 by David Waern at 2008-12-07T20:58:05+00:00 Resolve conflict properly - - - - - 67d774e7 by Neil Mitchell at 2008-12-15T11:44:26+00:00 Make forall's in constructors explicit, i.e. data Foo = Foo {foo :: Eq a => a} - - - - - 61851792 by Neil Mitchell at 2008-12-18T15:39:39+00:00 Try and find a better package name than "main" for Hoogle, goes wrong when working on an executable rather than a library - - - - - 2fab8554 by David Waern at 2008-12-08T23:19:48+00:00 Make visible names from ExportItems Instead of a complicated calculation of visible names out of GHC's export items, we can get them straight out of the already calculated ExportItems. The ExportItems should represent exactly those items that are visible in an interface. If store all the exported sub-names in ExportDecl instead of only those with documentation, the calculation becomes very simple. So we do this change as well (should perhaps have been a separate patch). This should fix the problem with names from ghc-prim not appearing in the link environment. - - - - - 7caadd8c by Ian Lynagh at 2008-12-11T17:01:04+00:00 Wrap the GHC usage with defaultCleanupHandler This fixes a bug where haddock leaves /tmp/ghc* directories uncleaned. - - - - - 7c9fc9a5 by David Waern at 2009-01-02T21:38:27+00:00 Show re-exported names from external packages again This fixes GHC ticket 2746. In order to also link to the exported subordinate names of a declaration, we need to re-introduce the sub map in the .haddock files. - - - - - 119e4e05 by David Waern at 2009-01-06T23:34:17+00:00 Do not process boot modules We should of course not try to produce documentation for boot modules! The reason this has worked in the past is that the output of "real" modules overwrites the output of boot modules later in the process. However, this causes a subtle link environment problem. So let's get rid of this stupid behaviour. We avoid processing boot modules, but we continue to typecheck them. - - - - - c285b9d2 by David Waern at 2009-01-08T18:03:36+00:00 Export modules also when coming from external packages This seems to have regressed since a refactoring that was part of the 2.3.0 release. - - - - - 24031c17 by David Waern at 2009-01-10T15:26:26+00:00 Change version to 2.4.2 - no need to go to 2.5.0 - - - - - 864d1c3f by David Waern at 2009-01-10T15:35:20+00:00 Update tests to account for version number change - - - - - 524ba886 by David Waern at 2009-01-10T18:29:17+00:00 Add test for Template Haskell splicing - - - - - 05e6e003 by David Waern at 2009-01-10T19:35:42+00:00 Fix Trac haskell/haddock#68: Turn on compilation via C for Template Haskell packages We can't use HscNothing if we need to run code coming from modules inside the processed package during typechecking, which is the case for some packages using Template Haskell. This could be improved, to e.g. use HscInterpreted and HscNothing where possible, instead of using HscC for all modules in the package. - - - - - 2b2bafa1 by David Waern at 2009-01-10T20:22:25+00:00 Only use needsTemplateHaskell when compiling with GHC 6.10.2 or above - - - - - bedc3a93 by Ian Lynagh at 2009-01-11T14:58:41+00:00 Fix the location of INPLACE_PKG_CONF; fixes the build Spotted by Conal Elliott - - - - - 943107c8 by David Waern at 2009-01-20T19:27:39+00:00 Document H.I.Create.collectDocs better - - - - - c6252e37 by David Waern at 2009-01-20T19:29:51+00:00 Fix Trac haskell/haddock#59: TH-generated declarations disappearing This patch was contributed by Joachim Breitner (nomeata). - - - - - 3568a6af by David Waern at 2009-01-21T21:41:48+00:00 Do not indicate that a constructor argument is unboxed We only show the strictness annotation for an unboxed constructor argument. The fact that it is unboxed is an implementation detail and should not be part of the module interface. - - - - - 562a4523 by David Waern at 2009-01-22T18:53:49+00:00 Fix Trac haskell/haddock#50: do not attach docs to pragmas or other kinds of non-declarations We now filter out everything that is not a proper Haskell declaration before collecting the docs and attaching them to declarations. - - - - - 6fdf21c2 by David Waern at 2009-01-22T19:48:09+00:00 Add test for quasi quotation. No reference output yet. - - - - - dc4100fd by David Waern at 2009-01-22T19:57:47+00:00 Improve quasi-quotation test and add reference output - - - - - 908b74bb by David Waern at 2009-01-23T23:22:03+00:00 Filter out separately exported associated types in a smarter way - - - - - f6b42ecb by David Waern at 2009-01-24T16:54:39+00:00 Correct spelling mistake in error message - - - - - 24e4245d by David Waern at 2009-01-24T17:48:03+00:00 Correct comment - - - - - b5e8462f by David Waern at 2009-02-07T13:22:29+00:00 Do not show a subordinate at the top level if its parent is also exported See note in the source code for more info. - - - - - 4b09de57 by David Waern at 2009-02-07T13:53:53+00:00 Update test following change to top level subordinates - - - - - 76379896 by David Waern at 2009-02-07T13:58:04+00:00 Remove html files in the tests/output/ directory which have been accidentally added - - - - - 1a6d8b10 by Joachim Breitner at 2009-02-20T10:29:43+00:00 Typo in comment - - - - - fec367d0 by David Waern at 2009-02-24T20:21:17+00:00 Fix small bug The rule is to prefer type constructors to other things when an identifier in a doc string can refer to multiple things. This stopped working with newer GHC versions (due to a tiny change in the GHC renamer). We implement this rule in the HTML backend for now, instead of fixing it in GHC, since we will move renaming of doc strings to Haddock in the future anyway. - - - - - 9b4172eb by David Waern at 2009-02-25T20:04:38+00:00 Fix bad error handling with newer GHCs When support for GHC 6.10 was added, an error handler was installed only around the typechecking phase. This had the effect that errors thrown during dependency chasing were caught in the top-level exception handler and not printed with enough detail. With this patch we wrap the error handler around all our usage of the Ghc monad. - - - - - de2df363 by Simon Peyton Jones at 2009-02-02T16:47:42+00:00 Hide funTyConName, now exported by TypeRep - - - - - 4d40a29f by Ian Lynagh at 2009-02-12T18:57:49+00:00 Don't build the library when building in the GHC tree - - - - - 1cd0abe4 by Ian Lynagh at 2009-02-13T13:58:53+00:00 Add a ghc.mk - - - - - 3d814eeb by Ian Lynagh at 2009-02-13T18:50:28+00:00 do .depend generation for haddock with the stage1 compiler This is a bit of a hack. We mkdepend with stage1 as if .depend depends on the stage2 compiler then make goes wrong: haddock's .depend gets included, which means that make won't reload until it's built, but we can't build it without the stage2 compiler. We therefore build the stage2 compiler before its .depend file is available, and so compilation fails. - - - - - b55036a4 by Ian Lynagh at 2009-02-25T01:38:13+00:00 Give haddock a wrapper on unix in the new GHC build system - - - - - 9eabfe68 by Ian Lynagh at 2009-02-25T19:21:32+00:00 Create inplace/lib/html in the new GHC build system - - - - - 93af30c7 by Ian Lynagh at 2008-11-07T19:18:23+00:00 TAG GHC 6.10.1 release - - - - - 06e6e34a by Thomas Schilling at 2009-02-24T18:11:00+00:00 Define __GHC_PATCHLEVEL__ for recent version of GHC (stable). - - - - - 680e6ed8 by Thomas Schilling at 2009-02-24T18:12:26+00:00 'needsTemplateHaskell' is not defined in current stable GHC. - - - - - 6c5619df by David Waern at 2009-02-25T22:15:23+00:00 Hide fynTyConName only for recent GHC versions - - - - - 6b2344f1 by Ian Lynagh at 2009-02-26T00:49:56+00:00 Add the module to one of haddocks warnings - - - - - e5d11c70 by David Waern at 2009-02-27T21:37:20+00:00 Bug fix We tried to filter out subordinates that were already exported through their parent. This didn't work properly since we were in some cases looking at the grand-parent and not the parent. We now properly compute all the parent-child relations of a declaration, and use this information to get the parent of a subordinate. We also didn't consider record fields with multiple parents. This is now handled correctly. We don't currently support separately exported associated types. But when we do, they should be handled correctly by this process too. Also slightly improved the warning message that we give when filtering out subordinates. - - - - - 10a79a60 by David Waern at 2009-02-27T22:08:08+00:00 Fix error message conflict The module name is already written in the beginning of the message, as seems to be the convention in Haddock. Perhaps not so clear, but we should change it everywhere in that case. Leaving it as it is for now. - - - - - c5055c7f by David Waern at 2009-02-27T22:15:17+00:00 Shorten warning message - - - - - a72fed3a by David Waern at 2009-02-28T00:53:55+00:00 Do not show package name in warning message - - - - - a5daccb2 by Ian Lynagh at 2009-03-01T14:59:35+00:00 Install haddock in the new GHC build system - - - - - dfdb025c by Ian Lynagh at 2009-03-07T23:56:29+00:00 Relax base dependency to < 4.2, not < 4.1 - - - - - 5769c8b4 by David Waern at 2009-03-21T14:58:52+00:00 Bump .haddock file version number (due to change of format) - - - - - f1b8f67b by David Waern at 2009-03-21T14:59:26+00:00 Define __GHC_PATCHLEVEL__=1 when using ghc-6.10.1 - - - - - 23f78831 by David Waern at 2009-03-21T16:40:52+00:00 Update CHANGES - - - - - 7d2735e9 by David Waern at 2009-03-21T16:50:33+00:00 Update ANNOUNCE - - - - - 0771e00a by David Waern at 2009-03-21T16:54:40+00:00 Update ANNOUNCE, again - - - - - 81a6942a by David Waern at 2009-03-21T17:50:06+00:00 Don't be too verbose in CHANGES - - - - - 29861dcf by David Waern at 2009-03-21T18:03:31+00:00 TAG 2.4.2 - - - - - a585f285 by David Waern at 2009-03-21T19:20:29+00:00 Require Cabal >= 1.2.3 - - - - - 7c611662 by David Waern at 2009-03-21T19:21:48+00:00 TAG 2.4.2 with cabal-version >= 1.2.3 - - - - - 23b7deff by Simon Marlow at 2009-03-20T15:43:42+00:00 new GHC build system: use shell-wrappers macro - - - - - 25f8afe7 by Ian Lynagh at 2009-03-21T19:13:53+00:00 Fix (with a hack?) haddock in teh new build system - - - - - 6a29a37e by David Waern at 2009-03-24T22:10:15+00:00 Remove unnecessary LANGUAGE pragma - - - - - 954da57d by David Waern at 2009-03-24T22:21:23+00:00 Fix warnings in H.B.DevHelp - - - - - 1619f1df by David Waern at 2009-03-26T23:20:44+00:00 -Wall police in H.B.Html - - - - - b211e13b by Simon Marlow at 2009-03-24T13:00:56+00:00 install Haddock's html stuff - - - - - 78e0b107 by David Waern at 2008-12-07T19:58:53+00:00 Add verbosity flag and utils, remove "verbose" flag - - - - - 913dae06 by David Waern at 2008-12-07T20:01:05+00:00 Add some basic "verbose" mode logging in H.Interface - - - - - 1cbff3bf by David Waern at 2009-03-27T00:07:26+00:00 Fix conflicts - - - - - 22f82032 by David Waern at 2009-03-27T21:15:11+00:00 Remove H.GHC.Typecheck - - - - - 81557804 by David Waern at 2009-03-27T21:19:22+00:00 Remove docNameOrig and use getName everywhere instead - - - - - d8267213 by David Waern at 2009-03-27T21:21:46+00:00 Use docNameOcc instead of nameOccName . getName - - - - - 5d55deab by David Waern at 2009-03-27T21:33:04+00:00 Remove H.DocName and put DocName in H.Types - - - - - 8ba72611 by David Waern at 2009-03-27T22:06:26+00:00 Document DocName - - - - - 605f8ca5 by David Waern at 2009-03-27T22:45:21+00:00 -Wall police - - - - - e4da93ae by David Waern at 2009-03-27T23:12:53+00:00 -Wall police in H.B.Hoogle - - - - - bb255519 by David Waern at 2009-03-27T23:41:28+00:00 Define Foldable and Traversable instances for Located - - - - - f1195cfe by David Waern at 2009-03-27T23:51:34+00:00 Wibble - - - - - 23818d7c by David Waern at 2009-03-28T00:03:55+00:00 -Wall police in H.I.Rename - - - - - 0f050d67 by David Waern at 2009-03-28T00:15:15+00:00 -Wall police in H.I.AttachInstances - - - - - 0f3fe038 by David Waern at 2009-03-28T21:09:41+00:00 Wibble - - - - - 275d4865 by David Waern at 2009-03-28T21:27:06+00:00 Layout fix - - - - - 54ff0ef8 by David Waern at 2009-03-28T21:59:07+00:00 -Wall police in H.I.Create - - - - - 7f58b117 by David Waern at 2009-03-28T22:10:19+00:00 -Wall police in H.Interface - - - - - f0c03b44 by David Waern at 2009-03-28T22:22:59+00:00 -Wall police in Main - - - - - 29da355c by David Waern at 2009-03-28T22:23:39+00:00 Turn on -Wall -Werror - - - - - 446d3060 by David Waern at 2009-04-01T20:40:30+00:00 hlint police - - - - - 3867c9fc by David Waern at 2009-04-01T20:48:42+00:00 hlint police - - - - - bd1f1600 by David Waern at 2009-04-01T20:58:02+00:00 hlint police - - - - - e0e90866 by David Waern at 2009-04-05T12:42:53+00:00 Move H.GHC.Utils to H.GhcUtils - - - - - 9cbd426b by David Waern at 2009-04-05T12:57:21+00:00 Remove Haddock.GHC and move its (small) contents to Main - - - - - b5c2cbfd by David Waern at 2009-04-05T13:07:04+00:00 Fix whitespace and stylistic issues in Main - - - - - 3c04aa56 by porges at 2008-12-07T08:22:19+00:00 add unicode output - - - - - 607918da by David Waern at 2009-04-26T15:09:43+00:00 Resolve conflict - - - - - 4bec6b6b by Simon Marlow at 2009-05-13T10:00:31+00:00 fix markup - - - - - 436ad6f4 by Simon Marlow at 2009-03-23T11:54:45+00:00 clean up - - - - - bdcd1398 by Simon Marlow at 2009-03-24T10:36:45+00:00 new GHC build system: add $(exeext) - - - - - 9c0972f3 by Simon Marlow at 2009-03-24T11:04:31+00:00 update for new GHC build system layout - - - - - d0f3f83a by Ian Lynagh at 2009-03-29T15:31:43+00:00 GHC new build system fixes - - - - - 5a8245c2 by Ian Lynagh at 2009-04-04T20:44:23+00:00 Tweak new build system - - - - - 9c6f2d7b by Simon Marlow at 2009-05-13T10:01:27+00:00 add build instructions for GHC - - - - - 66d07c76 by Ian Lynagh at 2009-05-31T00:37:53+00:00 Quote program paths in ghc.mk - - - - - bb7de2cd by Ian Lynagh at 2009-06-03T22:57:55+00:00 Use a bang pattern on an unlifted binding - - - - - 3ad283fc by Ian Lynagh at 2009-06-13T16:17:50+00:00 Include haddock in GHC bindists - - - - - ac447ff4 by David Waern at 2009-06-24T21:07:50+00:00 Delete Haddock.Exception and move contents to Haddock.Types Only a few lines of code that mainly declares a type - why not just put it in Haddock.Types. - - - - - 4464fb9b by David Waern at 2009-06-24T22:23:23+00:00 Add Haddock module headers Add a proper Haddock module header to each module, with a more finegrained copyright. If you feel mis-accreditted, please correct any copyright notice! The maintainer field is set to haddock at projects.haskell.org. Next step is to add a brief description to each module. - - - - - 5f4c95dd by David Waern at 2009-06-24T22:39:44+00:00 Fix spelling error - - - - - 6d074cdb by David Waern at 2009-06-25T21:53:56+00:00 Document Interface and InstalledInterface better - - - - - d0cbd183 by David Waern at 2009-06-27T12:46:46+00:00 Remove misplaced whitespace in H.I.Rename - - - - - fa381c49 by David Waern at 2009-06-27T13:26:03+00:00 Fix haskell/haddock#104 - create output directory if missing - - - - - 91fb77ae by Ian Lynagh at 2009-06-25T15:59:50+00:00 TAG 2009-06-25 - - - - - 0d853f40 by Simon Peyton Jones at 2009-07-02T15:35:22+00:00 Follow extra field in ConDecl - - - - - b201735d by Ian Lynagh at 2009-07-05T16:50:35+00:00 Update Makefile for the new GHC build system - - - - - df6c0092 by Ian Lynagh at 2009-07-05T17:01:13+00:00 Resolve conflicts - - - - - 1066870a by Ian Lynagh at 2009-07-05T17:01:48+00:00 Remove the -Wwarn hack in the GHC build system - - - - - 7e856076 by Ian Lynagh at 2009-07-05T17:17:59+00:00 Fix warnings - - - - - 5d4cd958 by Ian Lynagh at 2009-07-05T19:35:40+00:00 Bump version number Cabal needs to distinguish between haddocks having a --verbose and --verbosity flag - - - - - 6ee07c99 by David Waern at 2009-07-06T20:14:57+00:00 Wibble - - - - - 2308b66f by David Waern at 2009-07-06T20:24:20+00:00 Clearer printing of versions by runtests.hs - - - - - d4b5d9ab by David Waern at 2009-07-06T21:22:42+00:00 Fix (invisible) bug introduced by unicode patch - - - - - 2caca8d8 by David Waern at 2009-07-06T21:44:10+00:00 Use HscAsm instead of HscC when using TH - - - - - 18f3b755 by David Waern at 2009-07-06T22:10:22+00:00 Update HCAR entry (by Janis) - - - - - a72ac9db by David Waern at 2009-07-06T23:01:35+00:00 Follow HsRecTy change with an #if __GLASGOW_HASKEL__ >= 611 - - - - - 549135d2 by David Waern at 2009-07-06T23:11:41+00:00 Remove unused functions from Haddock.Utils - - - - - b450134a by Isaac Dupree at 2009-07-11T14:59:00+00:00 revert to split-index for large indices - remove the search-box, because browsers have search-for-text abilities anyway. - pick 150 items in index as the arbitrary time at which to split it - notice the bug that identifiers starting with non-ASCII characters won't be listed in split-index, but don't bother to fix it yet (see ticket haskell/haddock#116, http://trac.haskell.org/haddock/ticket/116 ) - - - - - 78a5661e by Isaac Dupree at 2009-07-20T15:37:18+00:00 Implement GADT records in HTML backend - - - - - 4e163555 by Isaac Dupree at 2009-07-21T22:03:25+00:00 add test for GADT records - - - - - 79aa4d6e by David Waern at 2009-07-23T20:40:37+00:00 Update test suite following version bump - - - - - 5932c011 by David Waern at 2009-08-02T10:25:39+00:00 Fix documentation bug - - - - - a6970fca by David Waern at 2009-08-12T23:08:53+00:00 Remove support for ghc 6.8.* from .cabal file - - - - - c1695902 by Ian Lynagh at 2009-07-07T13:35:45+00:00 Fix unused import warnings - - - - - fb6df7f9 by Ian Lynagh at 2009-07-16T00:20:31+00:00 Use cProjectVersion directly rather than going through compilerInfo Fixes the build after changes in GHC - - - - - 548cdd66 by Simon Marlow at 2009-07-28T14:27:04+00:00 follow changes in GHC's ForeignType - - - - - 9395aaa0 by David Waern at 2009-08-13T22:17:33+00:00 Switch from PatternSignatures to ScopedTypeVariables in Main - - - - - eebf39bd by David Waern at 2009-08-14T17:14:28+00:00 Version .haddock files made with GHC 6.10.3/4 correclty - - - - - 58f3e735 by David Waern at 2009-08-14T17:19:37+00:00 Support GHC 6.10.* and 6.11.* only - - - - - 5f63cecc by David Waern at 2009-08-14T22:03:20+00:00 Do not version .haddock file based on GHC patchlevel version We require that the instances of Binary that we use from GHC will not change between patchlevel versions. - - - - - d519de9f by David Waern at 2009-08-14T23:50:00+00:00 Update CHANGES - - - - - 35dccf5c by David Waern at 2009-08-14T23:51:38+00:00 Update version number everywhere - - - - - 6d363fea by David Waern at 2009-08-15T09:46:49+00:00 Update ANNOUNCE - - - - - c7ee6bc2 by David Waern at 2009-08-15T09:47:13+00:00 Remove -Werror Forgot that Hackage doesn't like it. - - - - - a125c12b by David Waern at 2009-08-15T09:49:50+00:00 Require Cabal >= 1.6 - - - - - adb2f560 by Isaac Dupree at 2009-08-12T03:47:14+00:00 Cross-Package Documentation version 4 - - - - - 3d6dc04d by David Waern at 2009-08-15T23:42:57+00:00 Put all the IN_GHC_TREE stuff inside getGhcLibDir - - - - - 56624097 by David Waern at 2009-08-15T23:52:03+00:00 Add --print-ghc-libdir - - - - - f15d3ccb by David Waern at 2009-08-16T00:37:52+00:00 Read base.haddock when running tests We can now test cross-package docs. - - - - - 283f0fb9 by David Waern at 2009-08-16T00:50:59+00:00 Update test output - we now have more links - - - - - 673d1004 by David Waern at 2009-08-16T01:26:08+00:00 Read process.haddock when running tests - - - - - 0d127f82 by David Waern at 2009-08-16T01:43:04+00:00 Add a test for cross-package documentation - - - - - f94db967 by Ian Lynagh at 2009-08-16T18:42:44+00:00 Follow GHC build system changes - - - - - 5151278a by Isaac Dupree at 2009-08-16T19:58:05+00:00 make cross-package list types look nicer - - - - - c41e8228 by Isaac Dupree at 2009-08-18T01:47:47+00:00 Haddock.Convert: export more functions This lets us remove some code in Haddock.Interface.AttachInstances - - - - - 2e5fa398 by Isaac Dupree at 2009-08-18T02:11:05+00:00 switch AttachInstances to use synify code It changed an instance from showing ((,) a b) to (a, b) because my synify code is more sophisticated; I hope the latter is a good thing rather than a bad thing aesthetically, here. But this definitely reduces code duplication! - - - - - b8b07123 by Isaac Dupree at 2009-08-18T02:23:31+00:00 Find instances using GHC, which is more complete. In particular, it works cross-package. An intermediate patch also moved the instance-finding into createInterface, but that move turned out not to be necessary, so if we want to do that, it'd go in a separate patch. (Is that possible? Or will we need GHC to have loaded all the modules first, before we can go searching for the instances (e.g. if the modules are recursive or something)?) - - - - - 6959b451 by Isaac Dupree at 2009-08-17T00:37:18+00:00 fix preprocessor conditional sense - - - - - 942823af by Isaac Dupree at 2009-08-16T22:46:48+00:00 remove ghc 6.8 conditionals from Haddock.Interface - - - - - 4b3ad888 by Isaac Dupree at 2009-08-18T20:24:38+00:00 Fix GHC 6.11 build in Haddock.Convert - - - - - 0a89c5ab by Isaac Dupree at 2009-08-23T00:08:58+00:00 hacks to make it compile without fnArgDocsn - - - - - 7b3bed43 by Isaac Dupree at 2009-08-23T03:01:28+00:00 less big-Map-based proper extraction of constructor subdocs - - - - - b21c279a by Isaac Dupree at 2009-08-23T03:02:06+00:00 Html: remove unnecessary+troublesome GHC. qualifications - - - - - 96c97115 by Isaac Dupree at 2009-08-23T03:08:03+00:00 Move doc parsing/lexing into Haddock for ghc>=6.11 - - - - - e1cec02d by Isaac Dupree at 2009-08-23T05:08:14+00:00 get rid of unused DocMap parameter in Html - - - - - 66960c59 by Isaac Dupree at 2009-08-23T05:54:20+00:00 fix horrible named-docs-disappearing bug :-) - - - - - a9d7eff3 by Isaac Dupree at 2009-08-23T06:26:36+00:00 re-implement function-argument docs ..on top of the lexParseRn work. This patch doesn't change the InstalledInterface format, and thus, it does not work cross-package, but that will be easy to add subsequently. - - - - - 8bf6852c by Isaac Dupree at 2009-08-23T07:26:05+00:00 cross-package fnArgDocs. WARNING: changes .haddock binary format While breaking the format, I took the opportunity to unrename the DocMap that's saved to disk, because there's really no reason that we want to know what *another* package's favorite place to link a Name to was. (Is that true? Or might we want to know, someday?) Also, I added instance Binary Map in InterfaceFile. It makes the code a little simpler without changing anything of substance. Also it lets us add another Map hidden inside another Map (fnArgsDocs in instDocMap) without having really-convoluted serialization code. Instances are neat! I don't understand why this change to InterfaceFile seemed to subtly break binary compatibility all by itself, but no matter, I'll just roll it into the greater format-changing patch. Done! - - - - - 30115a64 by Isaac Dupree at 2009-08-23T18:22:47+00:00 Improve behavior for unfindable .haddock - - - - - aa364bda by Isaac Dupree at 2009-08-23T18:28:16+00:00 add comment for FnArgsDoc type - - - - - 49b23a99 by Isaac Dupree at 2009-08-23T21:52:48+00:00 bugfix: restore fnArgDocs for type-synonyms - - - - - f65f9467 by Isaac Dupree at 2009-08-23T22:06:55+00:00 Backends.Hoogle: eliminate warnings - - - - - a292d216 by Isaac Dupree at 2009-08-23T22:10:24+00:00 Haddock.Convert: eliminate warnings - - - - - 5546cd20 by Isaac Dupree at 2009-08-23T22:12:31+00:00 Haddock.Interface.Rename: eliminate warnings - - - - - 0a9798b6 by Isaac Dupree at 2009-08-23T22:18:47+00:00 Main.hs: remove ghc<6.9 conditionals - - - - - e8f9867f by Isaac Dupree at 2009-08-23T22:27:46+00:00 Main.hs: eliminate warnings (except for OldException) - - - - - 61c64247 by Isaac Dupree at 2009-08-23T22:41:01+00:00 move get*LibDir code in Main.hs, to +consistent code, -duplication - - - - - 948f1e69 by Isaac Dupree at 2009-08-23T23:14:26+00:00 Main.hs: OldException->Exception: which eliminates warnings - - - - - 3d5d5e03 by Isaac Dupree at 2009-08-23T23:20:11+00:00 GhcUtils: ghc >= 6.10 - - - - - 2771d657 by Isaac Dupree at 2009-08-23T23:21:55+00:00 InterfaceFile: ghc >= 6.10 - - - - - d9f2b9d1 by Isaac Dupree at 2009-08-23T23:22:58+00:00 Types: ghc >= 6.10 - - - - - ca39210e by Isaac Dupree at 2009-08-23T23:23:26+00:00 ModuleTree: ghc >= 6.10 - - - - - 883c4e59 by Isaac Dupree at 2009-08-23T23:24:04+00:00 Backends.DevHelp: ghc >= 6.10 - - - - - 04667df5 by Isaac Dupree at 2009-08-23T23:24:37+00:00 Backends.Html: ghc >= 6.10 - - - - - a9f7f25f by Isaac Dupree at 2009-08-23T23:25:24+00:00 Utils: ghc >= 6.10 - - - - - b7105022 by Isaac Dupree at 2009-08-23T23:37:47+00:00 eliminate haskell98 dependency, following GHC's example It turns out I/we already had, and it was only a matter of deleting it from the cabal file. - - - - - 292e0911 by Isaac Dupree at 2009-08-24T01:22:44+00:00 refactor out subordinatesWithNoDocs dep of inferenced-decls fix - - - - - c2ed46a2 by Isaac Dupree at 2009-08-24T01:24:03+00:00 Eradicate wrong runtime warning for type-inferenced exported-functions see the long comment in the patch for why I did it this way :-) - - - - - 4ac0b57c by David Waern at 2009-09-04T22:56:20+00:00 Clean up tyThingToHsSynSig a little Factor out noLoc and use the case construct. Also rename the function to tyThingToLHsDecl, since it doesn't just create type signatures. - - - - - 28ab9201 by David Waern at 2009-09-04T22:58:50+00:00 Wibble - - - - - 0d9fe6d0 by David Waern at 2009-09-06T18:39:30+00:00 Add more copyright owners to H.I.AttachInstances - - - - - 122441b1 by David Waern at 2009-09-06T18:44:12+00:00 Style police - - - - - 1fa79463 by David Waern at 2009-09-06T18:57:45+00:00 Move toHsInstHead to Haddock.Convert and call it synifyInstHead - - - - - 0d42a8aa by David Waern at 2009-09-06T21:11:38+00:00 Use colordiff to display test results if available - - - - - ea9d8e03 by Simon Marlow at 2009-08-24T08:46:14+00:00 Follow changes in GHC's interface file format Word32 instead of Int for FastString and Name offsets - - - - - 537e051e by Simon Marlow at 2009-07-29T14:16:53+00:00 define unpackPackageId (it was removed from GHC) - - - - - 50c63aa7 by David Waern at 2009-09-09T23:18:03+00:00 Remove commented-out code - - - - - 511631fe by David Waern at 2009-09-09T23:19:05+00:00 Correct copyright in H.I.ParseModuleHeader - - - - - 898ec768 by David Waern at 2009-09-11T11:22:29+00:00 Use Map.fromList/toList intead of fromAscList/toAscList when serializing Maps This fixes the missing docs problem. The Eq and Ord instances for Name uses the unique number in Name. This number is created at deserialization time by GHC's magic Binary instance for Name, and it is random. Thus, fromAscList can't be used at deserialization time, even though toAscList was used at serialization time. - - - - - 37bec0d5 by Simon Peyton Jones at 2009-09-11T08:28:04+00:00 Track change in HsType - - - - - eb3a97c3 by Ian Lynagh at 2009-09-11T16:07:09+00:00 Allow building with base 4.2 - - - - - bb4205ed by Ian Lynagh at 2009-09-22T13:50:02+00:00 Loosen the GHC dependency - - - - - 5c75deb2 by Ian Lynagh at 2009-09-22T14:08:39+00:00 Fix building with GHC >= 6.12 - - - - - fb131481 by David Waern at 2009-09-11T11:24:48+00:00 Update runtests.hs to work with GHC 6.11 - - - - - ac3a419d by David Waern at 2009-09-11T11:25:14+00:00 Update CrossPackageDocs test - - - - - ec65c3c6 by David Waern at 2009-09-11T11:25:40+00:00 Add reference output for CrossPackageDocs - - - - - 520c2758 by Ian Lynagh at 2009-10-25T17:26:40+00:00 Fix installation in the GHC build system - - - - - 28b3d7df by Ian Lynagh at 2009-11-05T15:57:27+00:00 GHC build system: Make *nix installation work in paths containing spaces - - - - - 5c9bb541 by David Waern at 2009-11-14T11:56:39+00:00 Track change in HsType for the right compiler version - - - - - 905097ce by David Waern at 2009-11-14T12:10:47+00:00 hlint police - - - - - 04920630 by Ian Lynagh at 2009-11-20T13:46:30+00:00 Use defaultObjectTarget rather than HscAsm This fixes haddock when we don't have a native code generator - - - - - 966eb079 by David Waern at 2009-11-15T12:32:21+00:00 Remove commented-out code - - - - - 37f00fc4 by David Waern at 2009-11-22T13:58:48+00:00 Make runtests.hs strip links before diffing Generates easier to read diffs when tests fail. The content of the links is not important anyway since it is not taken into account by the tests. - - - - - 3a9bb8ef by David Waern at 2009-11-22T14:05:06+00:00 Follow findProgramOnPath signature change in runtests.hs - - - - - b26b9e5a by David Waern at 2009-11-22T14:08:40+00:00 Follow removal of GHC.MVar from base in CrossPackageDocs - - - - - f4d90ae4 by David Waern at 2009-11-22T14:48:47+00:00 Make copy.hs strip link contents before copying No more updating of reference files when URLs in links changes. - - - - - 4c9c420d by David Waern at 2009-11-22T15:26:41+00:00 Update test reference output * More links (Int, Float etc) * Stripped link contents - - - - - a62b80e3 by David Waern at 2009-11-23T23:19:39+00:00 Update CrossPackageDocs reference output - Remove GHC.MVar import (removed from base) - Strip link contents - - - - - 43491394 by David Waern at 2009-11-23T23:20:00+00:00 Update test reference files with comments on instances - - - - - 0d370a0b by David Waern at 2009-11-23T23:25:16+00:00 Bump version number - - - - - 2293113e by David Waern at 2009-11-24T20:55:49+00:00 Comments on instances Implementing this was a little trickier than I thought, since we need to match up instances from the renamed syntax with instances represented by InstEnv.Instance. This is due to the current design of Haddock, which matches comments with declarations from the renamed syntax, while getting the list of instances of a class/family directly using the GHC API. - Works for class instances only (Haddock has no support for type family instances yet) - The comments are rendered to the right of the instance head in the HTML output - No change to the .haddock file format - Works for normal user-written instances only. No comments are added on derived or TH-generated instances - - - - - bf586f29 by David Waern at 2009-11-27T22:05:15+00:00 Whitespace police - - - - - b8f03afa by David Waern at 2009-11-27T22:11:46+00:00 Remove bad whitespace and commented-out pieces - - - - - 90b8ee90 by David Waern at 2009-11-27T22:15:04+00:00 Whitespace police - - - - - b5ede900 by David Waern at 2009-11-27T22:15:50+00:00 Whitespace police - - - - - e3fddbfe by David Waern at 2009-11-28T13:37:59+00:00 Remove Name from DocInstance It's not used. - - - - - 9502786c by David Waern at 2009-11-28T13:56:54+00:00 Require at least GHC 6.12 While regression testing Haddock, I found a bug that happens with GHC 6.10.3, but not with GHC 6.12-rc2 (haven't tried 6.10.4). I don't have time to track it down. I think we should just always require the latest major GHC version. The time spent on making Haddock work with older versions is too high compared to the time spent on bugfixing, refactoring and features. - - - - - 8fa688d8 by David Waern at 2009-11-28T15:05:03+00:00 Remove cruft due to compatibility with older GHCs - - - - - 46fbbe9d by David Waern at 2009-11-28T15:07:50+00:00 Add a documentation header to Haddock.Convert - - - - - c3d2cc4a by David Waern at 2009-11-28T15:10:14+00:00 Remove unused H.Utils.FastMutInt2 - - - - - 490aba80 by David Waern at 2009-11-28T15:36:36+00:00 Rename Distribution.Haddock into Documentation.Haddock - - - - - 33ee2397 by David Waern at 2009-11-28T15:36:47+00:00 Fix error message - - - - - a5a3b950 by David Waern at 2009-11-28T16:58:39+00:00 Add a test flag that brings in QuickCheck - - - - - fa049e13 by David Waern at 2009-11-28T19:32:18+00:00 Say that we want quickcheck 2 - - - - - f32b0d9b by David Waern at 2009-11-28T19:32:40+00:00 Add an Arbitrary instance for HsDoc - - - - - da9a8bd7 by David Waern at 2009-11-28T20:15:30+00:00 Rename HsDoc back into Doc - - - - - edb60101 by David Waern at 2009-11-28T22:16:16+00:00 Move H.Interface.Parse/Lex to H.Parse/Lex These are not just used to build Interfaces. - - - - - 0656a9b8 by David Waern at 2009-11-28T23:12:14+00:00 Update version number in test suite - - - - - 5e8c6f4a by David Waern at 2009-12-21T14:12:41+00:00 Improve doc of DocName - - - - - 7868e551 by Ian Lynagh at 2009-09-22T10:43:03+00:00 TAG GHC 6.12-branch created - - - - - 0452a3ea by Ian Lynagh at 2009-12-15T12:46:07+00:00 TAG GHC 6.12.1 release - - - - - 65e9be62 by David Waern at 2009-12-21T16:58:58+00:00 Update CHANGES - - - - - 145cee32 by David Waern at 2009-12-21T16:59:09+00:00 TAG 2.6.0 - - - - - 3c552008 by David Waern at 2009-12-22T17:11:14+00:00 Update ANNOUNCE - - - - - 931f9db4 by David Waern at 2010-01-22T19:57:17+00:00 Convert haddock.vim to use unix newlines - - - - - 4e56588f by David Waern at 2010-01-22T22:11:17+00:00 Remove unnecessary (and inexplicable) uses of nub - - - - - 744bb4d1 by David Waern at 2010-01-22T22:12:14+00:00 Follow move of parser and lexer - - - - - e34bab14 by David Waern at 2010-01-22T22:49:13+00:00 Use findProgramLocation instead of findProgramOnPath in runtests.hs - - - - - 8d39891b by Isaac Dupree at 2010-01-14T18:53:18+00:00 fix html arg-doc off-by-one and silliness - - - - - 9401f2e9 by David Waern at 2010-01-22T22:57:03+00:00 Create a test for function argument docs - - - - - 507a82d7 by David Waern at 2010-01-22T23:24:47+00:00 Put parenthesis around type signature arguments of function type - - - - - 8a305c28 by David Waern at 2010-01-23T17:26:59+00:00 Add reference file for the FunArgs test - - - - - 1309d5e1 by David Waern at 2010-01-24T16:05:08+00:00 Improve FunArg test and update Test.html.ref - - - - - 2990f055 by Yitzchak Gale at 2010-02-14T16:03:46+00:00 Do not generate illegal character in HTML ID attribute. - - - - - c5bcab7a by David Waern at 2010-02-22T22:10:30+00:00 Fix Haddock markup error in comment - - - - - c6416a73 by David Waern at 2010-02-24T22:55:08+00:00 Large additions to the Haddock API Also improved and added more doc comments. - - - - - 57d289d7 by David Waern at 2010-02-24T22:58:02+00:00 Remove unused ifaceLocals - - - - - 80528d93 by David Waern at 2010-02-25T21:05:09+00:00 Add HaddockModInfo to the API - - - - - 82806848 by David Waern at 2010-02-25T21:05:27+00:00 Wibble - - - - - 744cad4c by David Waern at 2010-02-25T23:30:59+00:00 Make it possible to run a single test - - - - - 6a806e4c by David Waern at 2010-03-14T14:19:39+00:00 Bump version number - - - - - a5a8e4a7 by David Waern at 2010-03-14T14:36:35+00:00 Update ANNOUNCE - - - - - 6f05435e by Simon Hengel at 2010-03-15T20:52:42+00:00 Add missing dependencies for 'library' in haddock.cabal - - - - - faefe2bd by David Waern at 2010-03-15T22:29:37+00:00 Solve conflicts - - - - - 9808ad52 by David Waern at 2010-03-15T22:51:21+00:00 Bump version number - - - - - eb0bf60b by David Waern at 2010-03-15T22:52:32+00:00 Update CHANGES - - - - - f95cd891 by David Waern at 2010-03-15T23:01:06+00:00 Add Paths_haddock to other-modules of library - - - - - 65997b0a by David Waern at 2010-03-15T23:14:59+00:00 Update CHANGES - - - - - 7e251731 by David Waern at 2010-03-15T23:15:30+00:00 Bump version number - - - - - c9cd0ddc by David Waern at 2010-03-16T00:28:34+00:00 Fix warning - - - - - 1cac2d93 by Simon Peyton Jones at 2010-01-04T15:22:16+00:00 Fix imports for new location of splitKindFunTys - - - - - 474f26f6 by Simon Peyton Jones at 2010-02-10T14:36:06+00:00 Update Haddock for quasiquotes - - - - - 0dcc06c0 by Simon Peyton Jones at 2010-02-10T10:59:45+00:00 Track changes in HsTyVarBndr - - - - - 2d84733a by Simon Peyton Jones at 2010-02-10T14:52:44+00:00 Track HsSyn chnages - - - - - 9e3adb8b by Ian Lynagh at 2010-02-20T17:09:42+00:00 Resolve conflicts - - - - - a3e72ff8 by Simon Peyton Jones at 2010-03-04T13:05:16+00:00 Track change in HsUtils; and use a nicer function not an internal one - - - - - 27994854 by David Waern at 2010-03-18T22:22:27+00:00 Fix build with GHC 6.12.1 - - - - - 11f6e488 by David Waern at 2010-03-18T22:24:09+00:00 Bump version in test reference files - - - - - 0ef2f11b by David Waern at 2010-03-20T00:56:30+00:00 Fix library part of cabal file when in ghc tree - - - - - 3f6146ff by Mark Lentczner at 2010-03-20T22:30:11+00:00 First, experimental XHTML rendering switch to using the xhtml package copied Html.hs to Xhtml.hs and split into sub-modules under Haddock/Backends/Xhtml and detabify moved footer into div, got ready for iface change headers converted to semantic markup contents in semantic markup summary as semantic markup description in semantic markup, info block in header fixed factored out rendering so during debug it can be readable (see renderToString) - - - - - b8ab329b by Mark Lentczner at 2010-03-20T22:54:01+00:00 apply changes to Html.hs to Xhtml/*.hs incorporate changes that were made between the time Html.hs was copied and split into Xhtml.hs and Xhtml/*.hs includes patchs after "Wibble" (!) through "Fix build with GHC 6.12.1" - - - - - 73df2433 by Ian Lynagh at 2010-03-20T21:56:37+00:00 Follow LazyUniqFM->UniqFM in GHC - - - - - db4f602b by David Waern at 2010-03-29T22:00:01+00:00 Fix build with GHC 6.12 - - - - - d8dca088 by Simon Hengel at 2010-04-02T16:39:55+00:00 Add missing dependencies to cabal file - - - - - e2adc437 by Simon Hengel at 2010-04-02T14:08:40+00:00 Add markup support for interactive examples - - - - - e882ac05 by Simon Hengel at 2010-04-02T14:11:53+00:00 Add tests for interactive examples - - - - - 5a07a6d3 by David Waern at 2010-04-07T17:05:20+00:00 Propagate source positions from Lex.x to Parse.y - - - - - 6493b46f by David Waern at 2010-04-07T21:48:57+00:00 Let runtests.hs die when haddock has not been built - - - - - 5e34423e by David Waern at 2010-04-07T22:01:13+00:00 Make runtests.hs slightly more readable - - - - - 321d59b3 by David Waern at 2010-04-07T22:13:27+00:00 Fix haskell/haddock#75 Add colons to the $ident character set. - - - - - 37b08b8d by David Waern at 2010-04-08T00:32:52+00:00 Fix haskell/haddock#118 Avoid being too greedy when lexing URL markup (<..>), in order to allow multiple URLs on the same line. Do the same thing with <<..>> and #..#. - - - - - df8feac9 by David Waern at 2010-04-08T00:57:33+00:00 Make it easier to add new package deps to test suite This is a hack - we should use Cabal to get the package details instead. - - - - - 1ca6f84b by David Waern at 2010-04-08T01:03:06+00:00 Add ghc-prim to test suite deps - - - - - 27371e3a by Simon Hengel at 2010-04-08T19:26:34+00:00 Let parsing fails on paragraphs that are immediately followed by an example This is more consistent with the way we treat code blocks. - - - - - 83096e4a by David Waern at 2010-04-08T21:20:00+00:00 Improve function name - - - - - 439983ce by David Waern at 2010-04-10T10:46:14+00:00 Fix haskell/haddock#112 No link was generated for 'Addr#' in a doc comment. The reason was simply that the identifier didn't parse. We were using parseIdentifier from the GHC API, with a parser state built from 'defaultDynFlags'. If we pass the dynflags of the module instead, the right options are turned on on while parsing the identifer (in this case -XMagicHash), and the parse succeeds. - - - - - 5c0d35d7 by David Waern at 2010-04-10T10:54:06+00:00 Rename startGhc into withGhc - - - - - dca081fa by Simon Hengel at 2010-04-12T19:09:16+00:00 Add documentation for interactive examples - - - - - c7f26bfa by David Waern at 2010-04-13T00:51:51+00:00 Slight fix to the documentation of examples - - - - - 06eb7c4c by David Waern at 2010-04-13T00:57:05+00:00 Rename Interactive Examples into Examples (and simplify explanation) - - - - - 264830cb by David Waern at 2010-05-10T20:07:27+00:00 Update CHANGES with info about 2.6.1 - - - - - 8e5d4514 by Simon Hengel at 2010-04-18T18:16:54+00:00 Add unit tests for parser - - - - - 68297f40 by David Waern at 2010-05-10T21:53:37+00:00 Improve testsuite README - - - - - f04eb6e4 by David Waern at 2010-05-11T19:14:31+00:00 Re-organise the testsuite structure - - - - - a360f710 by David Waern at 2010-05-11T19:18:03+00:00 Shorten function name - - - - - 1d5dd359 by David Waern at 2010-05-11T21:40:02+00:00 Update runtests.hs following testsuite re-organisation - - - - - ffebe217 by David Waern at 2010-05-11T21:40:10+00:00 Update runtests.hs to use base-4.2.0.1 - - - - - 635de402 by David Waern at 2010-05-11T21:41:11+00:00 Update runparsetests.hs following testsuite reorganisation - - - - - 72137910 by Ian Lynagh at 2010-05-06T20:43:06+00:00 Fix build - - - - - 1a80b76e by Ian Lynagh at 2010-05-06T22:25:29+00:00 Remove redundant import - - - - - 1031a80c by Simon Peyton Jones at 2010-05-07T13:21:09+00:00 Minor wibbles to HsBang stuff - - - - - dd8e7fe5 by Ian Lynagh at 2010-05-08T15:22:00+00:00 GHC build system: Follow "rm" variable changes - - - - - 7f5e6748 by David Waern at 2010-05-13T11:53:02+00:00 Fix build with GHC 6.12.2 - - - - - 7953d4d8 by David Waern at 2010-05-13T18:45:01+00:00 Fixes to comments only - - - - - 8ae8eb64 by David Waern at 2010-05-13T18:57:26+00:00 ModuleMap -> IfaceMap - - - - - 1c3eadc6 by David Waern at 2010-05-13T19:03:13+00:00 Fix whitespace style issues - - - - - e96783c0 by David Waern at 2010-05-13T19:08:53+00:00 Fix comment - - - - - c998a78b by David Waern at 2010-05-13T19:39:00+00:00 Position the module header the same way everywhere Silly, but nice with some consistency :-) - - - - - b48a714e by David Waern at 2010-05-13T19:41:32+00:00 Position of module header, this time in the HTML backends - - - - - f9bfb12e by David Waern at 2010-05-13T19:43:05+00:00 Two newlines between declarations in Main - - - - - 071d44c7 by David Waern at 2010-05-13T19:44:21+00:00 Newlines in Convert - - - - - 036346db by David Waern at 2010-05-13T19:46:47+00:00 Fix a few stylistic issues in H.InterfaceFile - - - - - f0b8379e by David Waern at 2010-05-13T19:47:53+00:00 Add newlines to H.ModuleTree - - - - - 27409f8e by David Waern at 2010-05-13T19:51:10+00:00 Fix stylistic issues in H.Utils - - - - - 24774a11 by David Waern at 2010-05-13T20:00:43+00:00 Structure H.Types better - - - - - 7b6f5e40 by David Waern at 2010-05-13T20:01:04+00:00 Remove bad Arbitrary instance - - - - - fac9f1f6 by David Waern at 2010-05-13T20:05:50+00:00 Get rid of H.Utils.pathJoin and use System.FilePath.joinPath instead - - - - - fe6d00c4 by David Waern at 2010-05-13T20:51:55+00:00 Export a couple of more types from the API - - - - - b2e33a5f by David Waern at 2010-05-13T21:27:51+00:00 Improve doc comment for Interface - - - - - c585f2ce by David Waern at 2010-05-13T21:30:14+00:00 Improve documentation of Haddock.Interface - - - - - e6791db2 by David Waern at 2010-05-13T22:07:35+00:00 Remove meaningless comments - - - - - 7801b390 by David Waern at 2010-05-14T17:53:33+00:00 Remove unused modules - - - - - f813e937 by David Waern at 2010-05-14T17:55:17+00:00 Re-direct compilation output to a temporary directory Also add a flag --no-tmp-comp-dir that can be used to get the old behaviour of writing compilation files to GHC's output directory (default "."). - - - - - e56737ec by David Waern at 2010-05-14T18:06:11+00:00 Wibble - - - - - e40b0447 by David Waern at 2010-05-14T19:01:52+00:00 Move flag evaluation code from Main to Haddock.Options Determining the value of "singular" flags (by e.g. taking the last occurrence of the flag) and other flag evaluation should done in Haddock.Options which is the module that is supposed to define the command line interface. This makes Main a bit easier on the eyes as well. - - - - - 27091f57 by David Waern at 2010-05-14T19:05:10+00:00 Wibble - - - - - c658cf61 by David Waern at 2010-05-14T19:06:49+00:00 Re-order things in Haddock.Options a bit - - - - - 8cfdd342 by David Waern at 2010-05-14T19:20:29+00:00 De-tabify Haddock.Options and fix other whitespace issues - - - - - 0df16b62 by David Waern at 2010-05-14T19:25:07+00:00 Improve comments - - - - - 80b38e2b by David Waern at 2010-05-14T19:26:42+00:00 Whitespace police - - - - - fe580255 by David Waern at 2010-05-14T19:31:23+00:00 Wibbles to comments - - - - - a2b43fad by David Waern at 2010-05-14T20:24:32+00:00 Move some more flag functions to Haddock.Options - - - - - 3f895547 by David Waern at 2010-05-14T20:37:12+00:00 Make renderStep a top-level function in Main - - - - - 5cdca11d by David Waern at 2010-05-14T20:39:27+00:00 Spelling in comment - - - - - ad98d14c by David Waern at 2010-05-14T20:40:26+00:00 Comment fixes - - - - - 0bb9218f by David Waern at 2010-05-14T20:49:01+00:00 Whitespace police - - - - - 0f0a533f by David Waern at 2010-05-15T16:42:29+00:00 Improve description of --dump-interface - - - - - 5b2833ac by David Waern at 2010-05-15T17:16:53+00:00 Document --no-tmp-comp-dir - - - - - 8160b170 by David Waern at 2010-05-15T17:18:59+00:00 Wibble - - - - - 570dbe33 by David Waern at 2010-05-18T21:15:38+00:00 HLint police - - - - - 204e425f by David Waern at 2010-05-18T21:16:30+00:00 HLint police - - - - - 6db657ac by David Waern at 2010-05-18T21:16:37+00:00 Wibble - - - - - b942ccd7 by Simon Marlow at 2010-06-02T08:27:30+00:00 Interrupted disappeared in GHC 6.13 (GHC ticket haskell/haddock#4100) - - - - - 3b94a819 by Simon Marlow at 2010-06-02T08:45:08+00:00 Allow base-4.3 - - - - - c5a1fb7c by Simon Marlow at 2010-06-02T09:03:04+00:00 Fix compilation with GHC 6.13 - - - - - 6181296c by David Waern at 2010-06-08T21:09:05+00:00 Display name of prologue file when parsing it fails - - - - - 7cbc6f60 by Ian Lynagh at 2010-06-13T16:20:25+00:00 Remove redundant imports - - - - - 980c804b by Simon Marlow at 2010-06-22T08:41:50+00:00 isLocalAndTypeInferenced: fix for local module names overlapping package modules - - - - - d74d4a12 by Simon Marlow at 2010-06-23T12:03:27+00:00 Unresolved identifiers in Doc get replaced with DocMonospaced rather than plain strings - - - - - d8546783 by Simon Marlow at 2010-06-30T12:45:17+00:00 LaTeX backend (new options: --latex, --latex-style=<style>) - - - - - 437afa9e by David Waern at 2010-07-01T12:02:44+00:00 Fix a few stylistic whitespace issues in LaTeX backend - - - - - 85bc1fae by David Waern at 2010-07-01T15:42:45+00:00 Make runtest.hs work with GHC 6.12.3 (we should really stop hard coding this) - - - - - 7d2eb86f by David Waern at 2010-07-01T15:43:33+00:00 Update test following Simon's patch to render unresolved names in monospaced font - - - - - 08fcbcd2 by David Waern at 2010-07-01T16:12:18+00:00 Warning police - - - - - d04a8d7a by David Waern at 2010-07-04T14:53:39+00:00 Fix a bug in attachInstances We didn't look for instance docs in all the interfaces of the package. This had the effect of instance docs not always showing up under a declaration. I took the opportunity to clean up the code in H.I.AttachInstances a bit as well. More cleanup is needed, however. - - - - - d10344eb by Simon Hengel at 2010-07-10T09:19:04+00:00 Add missing dependencies to cabal file - - - - - 24090531 by Mark Lentczner at 2010-03-21T04:51:16+00:00 add exports to Xhtml modules - - - - - 84f9a333 by Mark Lentczner at 2010-04-03T19:14:22+00:00 clean up Doc formatting code - add CSS for lists - renderToString now uses showHtml since prettyHtml messes up <pre> sections - - - - - bebccf52 by Mark Lentczner at 2010-04-04T04:51:08+00:00 tweak list css - - - - - 0c2aeb5e by Mark Lentczner at 2010-04-04T06:24:14+00:00 all decls now generate Html not HtmlTable - ppDecl return Html, and so now do all of the functions it calls - added some internal tables to some decls, which is wrong, and will have to be fixed - decl "Box" functions became "Elem" functions to make clear they aren't in a table anymore (see Layout.hs) - docBox went away, as only used in one place (and its days are numbered) - cleaned up logic in a number of places, removed dead code - added maybeDocToHtml which simplified a number of places in the code - - - - - dbf73e6e by Mark Lentczner at 2010-04-05T05:02:43+00:00 clean up processExport and place a div around each decl - - - - - e25b7e9f by Mark Lentczner at 2010-04-10T21:23:21+00:00 data decls are now a sequence of paragraphs, not a table - - - - - 89ee0294 by Mark Lentczner at 2010-04-10T21:29:16+00:00 removed commented out code that can't be maintained - - - - - d466f536 by Mark Lentczner at 2010-04-12T04:56:27+00:00 removed declWithDoc and cleaned up data decls in summary - - - - - ed755832 by Mark Lentczner at 2010-04-12T05:07:53+00:00 merge in markupExample changes - - - - - c36f51fd by Mark Lentczner at 2010-04-25T04:56:37+00:00 made record fields be an unordList, not a table - - - - - ed3a28d6 by Mark Lentczner at 2010-04-25T05:23:28+00:00 fixed surround of instance and constructor tables - - - - - 0e35bbc4 by Mark Lentczner at 2010-04-25T05:36:59+00:00 fix class member boxes in summary - - - - - 5041749b by Mark Lentczner at 2010-04-25T05:38:35+00:00 remove unused bodyBox - - - - - e91724db by Mark Lentczner at 2010-04-25T06:26:10+00:00 fixed javascript quoting/escpaing issue - - - - - f4abbb73 by Mark Lentczner at 2010-05-03T23:04:31+00:00 adjust css for current markup - - - - - e75fec4c by Mark Lentczner at 2010-05-04T06:14:34+00:00 added assoicated types and methods back into class decls - - - - - 84169323 by Mark Lentczner at 2010-05-24T13:13:42+00:00 merge in changes from the big-whitespace cleanup - - - - - 3c1c872e by Mark Lentczner at 2010-06-11T21:03:58+00:00 adjust synopsis and bottom bar spacing - - - - - 3c1f9ef7 by Mark Lentczner at 2010-06-11T21:14:44+00:00 fix missing space in "module" lines in synoposis - - - - - 9a137e6d by Mark Lentczner at 2010-06-11T21:34:08+00:00 changed tt elements to code elements - - - - - 50f71ef1 by Mark Lentczner at 2010-06-11T23:27:46+00:00 factored out ppInstances - - - - - 3b9a9de5 by Mark Lentczner at 2010-06-17T17:36:01+00:00 push single constructors (newtype) onto line with decl - - - - - e0f8f2ec by Mark Lentczner at 2010-06-17T22:20:56+00:00 remove <++> connector - - - - - 56c075dd by Mark Lentczner at 2010-07-13T05:26:21+00:00 change to new page structure - - - - - 04be6ca7 by Mark Lentczner at 2010-07-14T04:21:55+00:00 constructors and args as dl lists, built in Layout.hs - - - - - 65aeafc2 by Mark Lentczner at 2010-07-14T05:38:32+00:00 better interface to subDecls - - - - - 72032189 by Mark Lentczner at 2010-07-14T07:04:10+00:00 made subDecl tables looks just so - - - - - b782eca2 by Mark Lentczner at 2010-07-14T16:00:54+00:00 convert args to SubDecl format - - - - - cc75e98f by Mark Lentczner at 2010-07-14T16:28:53+00:00 convert instances to SubDecl - - - - - 34e2aa5a by Mark Lentczner at 2010-07-14T21:07:32+00:00 removing old table cruft from Layout.hs - - - - - d5810d95 by Mark Lentczner at 2010-07-14T21:54:58+00:00 methods and associated types in new layout scheme - - - - - 65ef9579 by Mark Lentczner at 2010-07-14T23:43:42+00:00 clean up synopsis lists - - - - - e523318f by Mark Lentczner at 2010-07-15T05:02:26+00:00 clean up of anchors - - - - - 1215dfc5 by Mark Lentczner at 2010-07-15T23:53:01+00:00 added two new themes and rough css switcher - - - - - 7f0fd36f by Mark Lentczner at 2010-07-16T04:57:38+00:00 fixed package catpion, added style menu - - - - - 0dd4999c by Mark Lentczner at 2010-07-16T20:12:39+00:00 new output for mini_ pages - - - - - 64b2810b by Mark Lentczner at 2010-07-16T20:58:41+00:00 reformat index-frames - - - - - 3173f555 by Mark Lentczner at 2010-07-16T22:41:53+00:00 convert index to new markup - - - - - b0a4b7c9 by Mark Lentczner at 2010-07-17T04:07:22+00:00 convert index.html to new markup, adjust module markup - - - - - 8261ae1e by Mark Lentczner at 2010-07-17T05:07:29+00:00 classing styling of ancillary pages - - - - - 2a4fb025 by Mark Lentczner at 2010-07-17T05:11:45+00:00 clean up Layout.hs: no more vanillaTable - - - - - 87eec685 by Mark Lentczner at 2010-07-17T05:35:16+00:00 clean up Util.hs - - - - - d304e9b0 by Mark Lentczner at 2010-07-17T05:38:50+00:00 qualify import of XHtml as XHtml - - - - - 7dc05807 by Mark Lentczner at 2010-07-17T06:17:53+00:00 factored out head element generation - - - - - 9cdaec9e by Mark Lentczner at 2010-07-17T06:44:54+00:00 refactored out main page body generation - - - - - 8a51019e by Mark Lentczner at 2010-07-17T06:48:20+00:00 moved footer into only place that used it - - - - - efa479da by Mark Lentczner at 2010-07-17T18:48:30+00:00 styling auxillary pages for tibbe and snappy themes - - - - - 81de5509 by Mark Lentczner at 2010-07-18T04:41:38+00:00 fixed alphabet on index page, and styling of it and packages in module lists - - - - - 20718c1a by Mark Lentczner at 2010-07-18T05:34:29+00:00 cleaned up div functions in Layout.hs - - - - - 60d50453 by Mark Lentczner at 2010-07-18T05:48:39+00:00 added content div to main pages - - - - - ed16561c by Mark Lentczner at 2010-07-18T06:12:22+00:00 add .doc class to documentation blocks - - - - - f5c781b0 by Mark Lentczner at 2010-07-19T05:20:53+00:00 refactoring of anchor ID and fragment handling - - - - - a69a93bf by Mark Lentczner at 2010-07-19T05:35:55+00:00 remove an explicit bold tag - replace with .def class - - - - - d76c7225 by Mark Lentczner at 2010-07-19T06:56:15+00:00 rename Haddock.Backends.Xhtml.Util to Utils - - - - - 5a58c0da by David Waern at 2010-07-21T13:30:54+00:00 Remove trailing whitespace in Haddock.Backends.Xhtml - - - - - 0652aa17 by David Waern at 2010-07-21T13:33:21+00:00 Align a few comments - - - - - 785776c3 by David Waern at 2010-07-21T13:39:04+00:00 Remove trailing whitespace in H.B.X.Decl - - - - - 71a30710 by David Waern at 2010-07-21T13:44:27+00:00 Remove more trailing whitespace - - - - - 38750394 by David Waern at 2010-07-21T13:50:43+00:00 Style police - - - - - 3023d940 by David Waern at 2010-07-21T14:01:22+00:00 Style police in H.B.X.Decl - - - - - df16e9e6 by David Waern at 2010-07-21T14:14:45+00:00 Style police in H.B.X.DocMarkup - - - - - 6020e321 by David Waern at 2010-07-21T14:17:32+00:00 More style police - - - - - 86ad8bf5 by David Waern at 2010-07-21T14:21:02+00:00 Style police in H.B.Xhtml - - - - - aea27d03 by David Waern at 2010-07-21T14:42:03+00:00 Fix warnings in LaTeX backend - - - - - 2aff34a9 by David Waern at 2010-07-21T14:50:46+00:00 Style police in LaTeX backend (mainly more newlines) - - - - - e517162d by David Waern at 2010-07-21T15:05:47+00:00 Doc sections in Main - - - - - b971aa0c by David Waern at 2010-07-21T15:06:17+00:00 Trailing whitespace in Documentation.Haddock - - - - - f11628fb by David Waern at 2010-07-21T15:07:06+00:00 Trailing whitespace in Haddock.Convert - - - - - cbaf284c by David Waern at 2010-07-21T15:08:11+00:00 Style police in Haddock.GhcUtils - - - - - 71feb77b by David Waern at 2010-07-21T15:09:06+00:00 Style police in Haddock.InterfaceFile - - - - - 0a9c80e6 by David Waern at 2010-07-21T15:11:33+00:00 Whitespace police - - - - - 6168376c by David Waern at 2010-07-21T15:16:35+00:00 Style police in Haddock.Utils - - - - - 9fe4dd90 by David Waern at 2010-07-21T15:19:31+00:00 Add -fwarn-tabs - - - - - a000d752 by Mark Lentczner at 2010-07-20T17:25:52+00:00 move CSS Theme functions into Themes.hs - - - - - b52b440f by Mark Lentczner at 2010-07-20T17:29:35+00:00 add Thomas Schilling's theme - - - - - e43fa7e8 by Mark Lentczner at 2010-07-21T04:49:34+00:00 correct icon used with Snappy theme - - - - - ba5092d3 by Mark Lentczner at 2010-07-21T04:56:47+00:00 apply Tibbe's updates to his theme - - - - - 7804eef6 by Mark Lentczner at 2010-07-21T05:15:49+00:00 space between "Style" and the downward triangle - - - - - 7131d4c6 by Mark Lentczner at 2010-07-21T17:43:35+00:00 merge with David's source cleanups - - - - - ee65f1cb by David Waern at 2010-07-22T16:50:46+00:00 Fix a bug where we allowed --hoogle, --latex, etc without input files - - - - - e413ff7a by David Waern at 2010-07-22T17:21:58+00:00 Improve function name - - - - - a0fd14f3 by Simon Marlow at 2010-06-30T15:34:32+00:00 fix warnings - - - - - 31f73d2a by David Waern at 2010-07-22T19:29:41+00:00 Solve conflicts - - - - - d563b4a5 by Simon Marlow at 2010-06-30T15:34:37+00:00 fix warning - - - - - 412b6469 by David Waern at 2010-07-22T19:31:28+00:00 Solve conflict - - - - - 35174b94 by Ian Lynagh at 2010-07-06T17:27:16+00:00 Follow mkPState argument order change - - - - - b5c3585c by Simon Marlow at 2010-07-14T08:49:21+00:00 common up code for instance rendering - - - - - d8009560 by Simon Marlow at 2010-07-14T12:37:11+00:00 fix warnings - - - - - a6d88695 by David Waern at 2010-07-24T15:33:33+00:00 Fix build with ghc < 6.13 - - - - - 94cf9de1 by David Waern at 2010-07-24T15:34:37+00:00 Remove conflict left-over - - - - - 313b15c0 by Mark Lentczner at 2010-07-21T22:09:04+00:00 reorganization of nhaddock.css with tibbe - - - - - 9defed80 by Mark Lentczner at 2010-07-21T22:42:14+00:00 further cleanup of nhaddock.css, float TOC, support aux. pages - - - - - 6d944c1b by Mark Lentczner at 2010-07-22T06:22:23+00:00 remove old HTML backend - - - - - b3e8cba5 by Mark Lentczner at 2010-07-22T06:43:32+00:00 remove --html-help support - it was old, out-of-date, and mostly missing - - - - - d2654a08 by Mark Lentczner at 2010-07-22T21:45:34+00:00 tweaks to nhaddock.css - - - - - f73b285c by Mark Lentczner at 2010-07-23T06:19:35+00:00 command like processing for theme selection The bulk of the change is threadnig the selected theme set through functions in Xhtml.hs so that the selected themes can be used when generating the page output. There isn't much going on in most of these changes, just passing it along. The real work is all done in Themes.hs. - - - - - 8bddc90d by Mark Lentczner at 2010-07-23T06:58:31+00:00 drop --themes support, add named theme support decided that --themes was silly - no one would do that, just use multiple --theme arguments made --theme a synonym for --css and -c made those arguments, if no file is found, look up the argument as the name of a built in theme all of this let's haddock be invoked with "--theme=classic" for example. - - - - - 20cafd4f by Mark Lentczner at 2010-07-23T17:44:29+00:00 rename --default-themes to --built-in-themes - - - - - 0fe41307 by Mark Lentczner at 2010-07-23T18:33:02+00:00 tweaks to theme for info table, headings, and tables - - - - - cba4fee0 by Mark Lentczner at 2010-07-23T19:13:59+00:00 tweaks for dl layout, though still not used - - - - - 463fa294 by Mark Lentczner at 2010-07-23T21:07:19+00:00 tweak look of mini pages, keywords, and preblocks - - - - - 5472fc02 by Mark Lentczner at 2010-07-24T05:36:15+00:00 slide out Synopsis drawer - - - - - 9d5d5de5 by Mark Lentczner at 2010-07-24T06:02:42+00:00 extend package header and footer to edges of page - - - - - a47c91a2 by Mark Lentczner at 2010-07-24T06:28:44+00:00 fields are def lists, tweak css for style menu, mini pages, arguments - - - - - ca20f23b by Mark Lentczner at 2010-07-24T16:55:22+00:00 excisting last vestiges of the --xhtml flag - - - - - 71fb012e by Mark Lentczner at 2010-07-25T18:47:49+00:00 change how collapsing sections are done make whole .caption be the target improve javascript for class toggling have plus/minus images come from .css, not img tags - - - - - c168c8d3 by Mark Lentczner at 2010-07-26T00:32:05+00:00 reorganize files in the html lib data dir - - - - - 93324301 by Mark Lentczner at 2010-07-26T01:27:42+00:00 cleaned up Themes.hs - - - - - ad3b5dd4 by Mark Lentczner at 2010-07-26T02:39:15+00:00 make module list use new collapsers - - - - - 1df9bfc6 by Mark Lentczner at 2010-07-27T19:09:25+00:00 remove Tibbe theme - - - - - 8b9b01b3 by Mark Lentczner at 2010-07-27T20:04:03+00:00 move themes into html dir with .theme and .std-theme extensions - - - - - a7beb965 by Mark Lentczner at 2010-07-27T21:06:34+00:00 give a class to empty dd elements so they can be hidden - - - - - a258c117 by Mark Lentczner at 2010-07-27T21:23:58+00:00 remove custom version of copyFile in Xhtml.hs - - - - - b70dba6e by Mark Lentczner at 2010-07-27T22:12:45+00:00 apply margin changes to pre and headings as per group decision, and small cleanups - - - - - e6f722a2 by Mark Lentczner at 2010-07-28T00:03:12+00:00 make info block and package bar links be floatable by placing them first in the dom tree - - - - - c8278867 by Mark Lentczner at 2010-07-28T19:01:18+00:00 styling source links on declarations - - - - - 88fdc399 by Mark Lentczner at 2010-07-29T01:12:46+00:00 styling tweaks don't generate an empty li for absent style menu in links area update css for Classic and Snappy to handle: dl lists links in package header and in declarations floating of links and info block in package and module headers - - - - - 8a75b213 by Ian Lynagh at 2010-07-30T20:21:46+00:00 Fix build in GHC tree - - - - - ce8e18b3 by Simon Hengel at 2010-08-03T18:37:26+00:00 Adapt paths to data files in cabal file - - - - - 9701a455 by Simon Hengel at 2010-08-07T13:20:27+00:00 Add missing dependency to cabal file - - - - - 01b838d1 by Mark Lentczner at 2010-07-30T20:19:40+00:00 improved synopsis drawer: on click, not hover - - - - - 7b6f3e59 by Mark Lentczner at 2010-07-30T23:38:55+00:00 put the synopsis back in the other themes - - - - - 7b2904c9 by Mark Lentczner at 2010-08-11T11:11:26+00:00 close arrows on expanded synopsis drawer - - - - - ea19e177 by Mark Lentczner at 2010-08-12T21:16:45+00:00 width and font changes removed the max width restrictions on the page as a whole and the synopsis made the main font size smaller (nominally 14pt) and then tweaked most font sizes (relative) to be more consistent - - - - - 5ced00c0 by Mark Lentczner at 2010-08-13T15:09:55+00:00 implemented YUI's CSS font approach - - - - - 2799c548 by Mark Lentczner at 2010-08-13T15:11:59+00:00 adjusted margin to 2em, 1 wasn't enough - - - - - 58f06893 by Mark Lentczner at 2010-08-13T15:48:44+00:00 removed underlining on hover for named anchors headings in interface lost thier a element, no need, just put id on heading css for a elements now only applies to those with href attribute - - - - - 7aced4c4 by Mark Lentczner at 2010-08-13T15:50:22+00:00 more space between elements - - - - - 5a3c1cce by Mark Lentczner at 2010-08-13T16:43:43+00:00 adjusted font sizes of auxilary pages per new scheme - - - - - 487539ef by Mark Lentczner at 2010-08-13T21:43:41+00:00 add Frames button and clean up frames.html - - - - - c1a140b6 by Mark Lentczner at 2010-08-13T22:17:48+00:00 move frames button to js - - - - - b0bdb68e by Mark Lentczner at 2010-08-14T03:44:46+00:00 build style menu in javascript moved to javascript, so as to not polute the content with the style menu removed menu building code in Themes.hs removed onclick in Utils.hs changed text of button in header from "Source code" to "Source" more consistent with links in rest of page - - - - - 43ab7120 by Mark Lentczner at 2010-08-16T15:15:37+00:00 font size and margin tweaks - - - - - c0b68652 by Mark Lentczner at 2010-08-17T18:19:52+00:00 clean up collapser logics javascript code for collapasble sections cleaned up rewrote class utilities in javascript to be more robust refactored utilities for generating collapsable sections made toc be same color as synopsis module list has needed clear attribute in CSS - - - - - 5d573427 by Mark Lentczner at 2010-08-17T23:06:02+00:00 don't collapse entries in module list when clicking on links - - - - - 8c307c4a by Mark Lentczner at 2010-08-17T23:21:43+00:00 add missing data file to .cabal - - - - - 414bcfcf by Mark Lentczner at 2010-08-17T23:28:47+00:00 remove synopsis when in frames - - - - - ba0fa98a by Mark Lentczner at 2010-08-18T16:16:11+00:00 layout tweeks - mini page font size, toc color, etc. - - - - - 63c1bed1 by Mark Lentczner at 2010-08-18T19:50:02+00:00 margin fiddling - - - - - c311c094 by Mark Lentczner at 2010-08-20T01:37:55+00:00 better synopsis handling logic - no flashing - - - - - f1fe5fa8 by Mark Lentczner at 2010-08-20T01:41:06+00:00 fix small layout issues mini frames should have same size top heading give info block dts some padding so they don't collide in some browsers - - - - - 0de84d77 by Mark Lentczner at 2010-08-20T02:13:09+00:00 made style changing and cookies storage robust - - - - - 1ef064f9 by Thomas Schilling at 2010-08-04T13:12:22+00:00 Make synopsis frame behave properly in Firefox. In Firefox, pressing the back button first reverted the synopsis frame, and only clicking the back button a second time would update the main frame. - - - - - dd1c9a94 by Mark Lentczner at 2010-08-21T01:46:19+00:00 remove Snappy theme - - - - - 2353a90d by Mark Lentczner at 2010-08-25T05:16:19+00:00 fix occasional v.scroll bars on pre blocks (I think) - - - - - 459b8bf1 by Simon Hengel at 2010-08-08T10:12:45+00:00 Add createInterfaces' (a more high-level alternative to createInterfaces) to Haddock API - - - - - b1b68675 by David Waern at 2010-08-26T20:31:58+00:00 Follow recent API additions with some refactorings Simon Hegel's patch prompted me to do some refactorings in Main, Haddock.Documentation and Haddock.Interface. - - - - - 264d4d67 by David Waern at 2010-08-26T21:40:59+00:00 Get rid of GhcModule and related cruft We can get everything we need directly from TypecheckedModule. - - - - - 0feacec2 by Mark Lentczner at 2010-08-26T23:44:13+00:00 fixed CSS for ordered lists and def lists in doc blocks - - - - - 2997e0c2 by Mark Lentczner at 2010-08-26T23:45:03+00:00 support both kinds of enumerated lists in doc markup The documentation for Haddock says enumerated lists can use either of (1) first item 2. second item The second form wasn't actually supported - - - - - 5d4ddeec by Mark Lentczner at 2010-08-27T21:29:48+00:00 fix broken header link margins - - - - - 614456ba by Mark Lentczner at 2010-08-27T22:16:19+00:00 fix table of contents CSS - - - - - 03f329a2 by David Waern at 2010-08-28T16:36:09+00:00 Update tests following switch to the Xhtml backend - - - - - ca689fa2 by Mark Lentczner at 2010-08-28T18:25:16+00:00 fix def lists - - - - - 18e1d3d2 by Mark Lentczner at 2010-08-28T18:26:18+00:00 push footer to bottom of window - - - - - b0ab8d82 by David Waern at 2010-08-28T22:04:32+00:00 Whitespace police - - - - - 2d217977 by David Waern at 2010-08-29T12:44:45+00:00 Remove Snappy data files - - - - - 01e27d5f by David Waern at 2010-08-29T13:03:28+00:00 Add source entity path to --read-interface You can now use this flag like this: --read-interface=<html path>,<source entity path>,<.haddock file> By "source entity path" I mean the same thing that is specified with the --source-entity flag. The purpose of this is to be able to specify the source entity path per package, to allow source links to work in the presence of cross-package documentation. When given two arguments or less the --read-interface flag behaves as before. - - - - - 20bf4aaa by David Waern at 2010-08-29T13:11:03+00:00 Naming wibbles - - - - - ad22463f by Mark Lentczner at 2010-08-29T15:14:54+00:00 make portability block be a table - solves layout issues - - - - - 97bd1ae6 by Mark Lentczner at 2010-08-29T15:17:42+00:00 update golden test for Test due to portability box change - - - - - d37e139e by Mark Lentczner at 2010-08-29T17:07:17+00:00 move TOC and Info blocks down 0.5em to improve layout issue w/Test.hs - - - - - acf52501 by David Waern at 2010-08-29T17:32:36+00:00 Allow building with ghc < 6.16 - - - - - 1cb34ed8 by Ian Lynagh at 2010-07-24T23:18:49+00:00 Flatten the dynflags before parsing - - - - - b36845b4 by Ian Lynagh at 2010-07-24T23:26:49+00:00 Follow flattenLanguageFlags -> flattenExtensionFlags rename - - - - - 7f7fcc7e by David Waern at 2010-08-29T17:46:23+00:00 Use flattenExtensionFlags with ghc >= 6.13 only - - - - - 13cf9411 by Ian Lynagh at 2010-08-01T18:09:54+00:00 Make the main haddock script versioned, and make plain "haddock" a symlink - - - - - 495cbff2 by Ian Lynagh at 2010-08-18T18:57:24+00:00 Fix installation in the GHC build system Data-files are now in subdirectories, so we need to handle that - - - - - 88ebab0a by Ian Lynagh at 2010-08-18T19:43:53+00:00 GHC build system: Add all the data files to BINDIST_EXTRAS - - - - - 65837172 by David Waern at 2010-08-29T20:12:34+00:00 Update Test - - - - - 094bbaa2 by David Waern at 2010-08-29T20:55:14+00:00 Revert update to Test - - - - - a881cfb3 by David Waern at 2010-08-31T18:24:15+00:00 Bump version number - - - - - 1fc8a3eb by David Waern at 2010-08-31T22:32:27+00:00 Update ANNOUNCE - - - - - ee1df9d0 by David Waern at 2010-08-31T22:33:11+00:00 Update CHANGES - - - - - 394cc854 by David Waern at 2010-08-31T22:33:23+00:00 Update interface file versioning to work with ghc 6.14/15 - - - - - 7d03b79b by David Waern at 2010-08-31T22:36:00+00:00 Update test output following version change - - - - - a48d82d1 by Mark Lentczner at 2010-09-01T04:29:35+00:00 sort options in doc to match --help output removed --html-help option, as it is no longer supported - - - - - 06561aeb by Mark Lentczner at 2010-09-01T05:29:32+00:00 update options documentation rewrote doc for --html added doc for --theme and --built-in-themes added --use-contents and --gen-contents - - - - - 57dea832 by Mark Lentczner at 2010-09-01T05:31:27+00:00 slight wording change about Frames mode - - - - - fa1f6da3 by David Waern at 2010-09-01T10:57:44+00:00 Update doc configure script to find docbook stylesheets on arch linux - - - - - addff770 by David Waern at 2010-09-01T11:02:29+00:00 Wibble - - - - - 8399006d by David Waern at 2010-09-01T11:19:21+00:00 Replace ghci> with >>> in example syntax - - - - - 35074cf8 by David Waern at 2010-09-01T19:03:27+00:00 Improve docs for --no-tmp-comp-dir - - - - - 0f8f8cfd by David Waern at 2010-09-02T11:22:27+00:00 Add a list of contributors to the user guide Break out everyone thanked in the `Acknowledgements` chapter into a separate contributor list and add everyone from `darcs show authors`. We consider everyone who is thanked to be a contributor as a conservative estimation :-) I have added some more contributors that I know about, who were not in the darcs history, but others may be missing. So please add anyone that you think is missing from the list. - - - - - 42ccf099 by David Waern at 2010-09-02T11:29:22+00:00 Update copyright years in license - - - - - 0d560479 by David Waern at 2010-09-02T11:38:52+00:00 Update release instructions - - - - - 72ab7796 by David Waern at 2010-09-02T19:27:08+00:00 Add a note to ANNOUNCE - - - - - bf9d9c5d by David Waern at 2010-09-02T19:27:48+00:00 H.Utils needs FFI on Win+MinGW - - - - - 048ae44a by Mark Lentczner at 2010-09-04T23:19:47+00:00 make TOC group header identifiers validate - - - - - 8c6faf36 by Simon Michael at 2010-09-22T07:12:34+00:00 add hints for cleaner darcs show authors output - - - - - 9909bd17 by Simon Michael at 2010-09-22T17:58:06+00:00 print haddock coverage info on stdout when generating docs A module's haddockable items are its exports and the module itself. The output is lightly formatted so you can align the :'s and sort for readability. - - - - - 6da72171 by David Waern at 2010-10-03T21:31:24+00:00 Style wibble - - - - - 2f8d8e4d by Tobias Brandt at 2010-08-27T07:01:21+00:00 adding the option to fully qualify identifiers - - - - - 833be6c6 by Tobias Brandt at 2010-08-27T15:50:28+00:00 adding support for local and relative name qualification - - - - - df15c4e9 by Tobias Brandt at 2010-08-27T15:56:37+00:00 corrected qualification help message - - - - - 449e9ce1 by David Waern at 2010-10-16T17:34:30+00:00 Solve conflicts - - - - - 3469bda5 by David Waern at 2010-10-16T18:42:40+00:00 Use "qual" as an abbreviation for qualification instead of "quali" for consistency - - - - - 97c2d728 by David Waern at 2010-10-16T18:47:07+00:00 Style police - - - - - ce14fbea by David Waern at 2010-10-16T21:15:25+00:00 Style police - - - - - fdf29e9d by David Waern at 2010-10-17T00:30:44+00:00 Add a pointer to the style guide - - - - - 8e6b44e8 by rrnewton at 2010-10-24T03:19:28+00:00 Change to index pages: include an 'All' option even when subdividing A-Z. - - - - - 755b131c by David Waern at 2010-11-14T19:39:36+00:00 Bump version - - - - - d0345a04 by David Waern at 2010-11-14T19:41:59+00:00 TAG 2.8.1 - - - - - f6221508 by Simon Peyton Jones at 2010-09-13T09:53:00+00:00 Adapt to minor changes in internal GHC functions - - - - - 1290713d by Ian Lynagh at 2010-09-15T10:37:18+00:00 Remove duplicate Outputable instance for Data.Map.Map - - - - - 87f69eef by Ian Lynagh at 2010-09-21T15:01:10+00:00 Bump GHC dep upper bound - - - - - af36e087 by Ian Lynagh at 2010-09-21T15:12:02+00:00 Fix up __GLASGOW_HASKELL__ tests - - - - - ad67716c by Ian Lynagh at 2010-09-21T20:31:35+00:00 Don't build haddock is HADDOCK_DOCS is NO - - - - - 63b3f1f5 by Ian Lynagh at 2010-09-21T21:39:51+00:00 Fixes for when HADDOCK_DOCS=NO - - - - - e92bfa42 by Ian Lynagh at 2010-09-29T21:15:38+00:00 Fix URL creation on Windows: Use / not \ in URLs. Fixes haskell/haddock#4353 - - - - - 66c55e05 by Ian Lynagh at 2010-09-30T17:03:34+00:00 Tidy up haddock symlink installation In particular, it now doesn't get created if we aren't installing haddock. - - - - - 549b5556 by Ian Lynagh at 2010-10-23T21:17:14+00:00 Follow extension-flattening change in GHC - - - - - d7c2f72b by David Waern at 2010-11-14T20:17:55+00:00 Bump version to 2.8.2 - - - - - 6989a3a9 by David Waern at 2010-11-14T20:26:01+00:00 Solve conflict - - - - - 055c6910 by Ian Lynagh at 2010-09-22T15:36:20+00:00 Bump GHC dep - - - - - c96c0763 by Simon Marlow at 2010-10-27T11:09:44+00:00 follow changes in the GHC API - - - - - 45907129 by David Waern at 2010-11-07T14:00:58+00:00 Update the HCAR entry - - - - - 61940b95 by David Waern at 2010-11-07T14:07:34+00:00 Make the HCAR entry smaller - - - - - aa590b7d by David Waern at 2010-11-14T21:30:59+00:00 Update HCAR entry with November 2010 version - - - - - 587f9847 by David Waern at 2010-11-14T23:48:17+00:00 Require ghc >= 7.0 - - - - - ff5c647c by David Waern at 2010-11-14T23:49:09+00:00 TAG 2.8.2 - - - - - 937fcb4f by David Waern at 2010-11-14T23:49:45+00:00 Solve conflict - - - - - 8e5d0c1a by David Waern at 2010-11-15T21:09:50+00:00 Remove code for ghc < 7 - - - - - 3d47b70a by David Waern at 2010-11-15T21:11:06+00:00 Fix bad merge - - - - - 7f4a0d8a by David Waern at 2010-11-15T21:13:57+00:00 Remove more ghc < 7 code - - - - - 9ee34b50 by David Waern at 2010-11-15T21:31:25+00:00 Match all AsyncExceptions in exception handler - - - - - 42849c70 by David Waern at 2010-11-15T21:35:31+00:00 Just say "internal error" instead of "internal Haddock or GHC error" - - - - - c88c809b by David Waern at 2010-11-15T21:44:19+00:00 Remove docNameOcc under the motto "don't name compositions" - - - - - b798fc7c by David Waern at 2010-11-15T23:27:13+00:00 Wibble - - - - - 2228197e by David Waern at 2010-11-15T23:28:24+00:00 Rename the HCAR entry file - - - - - 8a3f9090 by David Waern at 2010-11-16T00:05:29+00:00 Remove Haskell 2010 extensions from .cabal file - - - - - c7a0c597 by David Waern at 2010-11-16T00:10:28+00:00 Style wibbles - - - - - cde707a5 by David Waern at 2010-11-16T00:12:00+00:00 Remove LANGUAGE ForeignFunctionInterface pragmas - - - - - 1dbda8ed by David Waern at 2010-11-16T00:17:21+00:00 Make a little more use of DoAndIfThenElse - - - - - 4c45ff6e by David Waern at 2010-11-16T00:59:41+00:00 hlint police - - - - - d2feaf09 by David Waern at 2010-11-16T01:14:15+00:00 hlint police - - - - - 99876e97 by David Waern at 2010-11-20T19:06:00+00:00 Haddock documentation updates - - - - - 65ce6987 by David Waern at 2010-11-20T19:42:51+00:00 Follow the style guide closer in Haddock.Types and improve docs - - - - - 28ca304a by tob.brandt at 2010-11-20T17:04:40+00:00 add full qualification for undocumented names - - - - - d61341e3 by David Waern at 2010-11-20T20:04:15+00:00 Re-structure qualification code a little - - - - - 0057e4d6 by David Waern at 2010-11-20T20:07:55+00:00 Re-order functions - - - - - d7279afd by David Waern at 2010-11-21T03:39:54+00:00 Add BangPatterns to alex and happy source files - - - - - 629fe60e by tob.brandt at 2010-11-23T23:35:11+00:00 documentation for qualification - - - - - 37031cee by David Waern at 2010-11-23T21:06:44+00:00 Update CHANGES - don't mention 2.8.2, we won't release it - - - - - f2489e19 by David Waern at 2010-12-01T21:57:11+00:00 Update deps of runtests.hs to work with ghc 7.0.1 - - - - - d3657e9a by David Waern at 2010-12-01T22:04:57+00:00 Make tests compile with ghc 7.0.1 - - - - - a2f09d9b by David Waern at 2010-12-01T22:06:59+00:00 Update tests following version bump - - - - - 50883ebb by David Waern at 2010-12-06T14:09:18+00:00 Update tests following recent changes - - - - - fc2fadeb by David Waern at 2010-12-06T14:17:29+00:00 Add a flag --pretty-html for rendering indented html with newlines - - - - - 30832ef2 by David Waern at 2010-12-06T14:17:35+00:00 Use --pretty-html when running the test suite. Makes it easier to compare output - - - - - a0b81b31 by David Waern at 2010-12-06T14:18:27+00:00 Wibble - - - - - 3aaa23fe by David Waern at 2010-12-06T14:19:29+00:00 Haddockify ppHtml comments - - - - - 24bb24f0 by David Waern at 2010-12-06T14:23:15+00:00 Remove --debug. It was't used, and --verbosity should take its place - - - - - 6bc076e5 by David Waern at 2010-12-06T14:25:37+00:00 Rename golden-tests into html-tests. "golden tests" sounds strange - - - - - 53301e55 by David Waern at 2010-12-06T14:26:26+00:00 QUALI -> QUAL in the description --qual for consistency - - - - - 98b6affb by David Waern at 2010-12-06T21:54:02+00:00 Bump version - - - - - 371bf1b3 by David Waern at 2010-12-06T22:08:55+00:00 Update tests following version bump - - - - - 25be762d by David Waern at 2010-12-06T22:21:03+00:00 Update CHANGES - - - - - 7c7dac71 by David Waern at 2010-12-06T22:33:43+00:00 Update ANNOUNCE - - - - - 30d7a5f2 by Simon Peyton Jones at 2010-11-15T08:38:38+00:00 Alex generates BangPatterns, so make Lex.x accept them (It'd be better for Alex to generate this pragma.) - - - - - 605e8018 by Simon Marlow at 2010-11-17T11:37:24+00:00 Add {-# LANGUAGE BangPatterns #-} to mollify GHC - - - - - a46607ba by David Waern at 2010-12-07T14:08:10+00:00 Solve conflicts - - - - - b28cda66 by David Waern at 2010-12-09T20:41:35+00:00 Docs: Mention that \ is a special character in markup - - - - - a435bfdd by Ian Lynagh at 2010-11-17T14:01:19+00:00 TAG GHC 7.0.1 release - - - - - 5a15a05a by David Waern at 2010-12-11T17:51:19+00:00 Fix indentation problem - - - - - 4232289a by Lennart Kolmodin at 2010-12-17T18:32:03+00:00 Revise haddock.cabal given that we now require ghc-7 default-language should be Haskell2010, slight new semantics for extensions. Rewrite into clearer dependencies of base and Cabal. - - - - - a36302dc by David Waern at 2010-12-19T17:12:37+00:00 Update CHANGES - - - - - 7c8b85b3 by David Waern at 2010-12-19T17:14:24+00:00 Bump version - - - - - cff22813 by Ian Lynagh at 2011-01-05T18:24:27+00:00 Write hoogle output in utf8; fixes GHC build on Windows - - - - - c7e762ea by David Waern at 2011-01-22T00:00:35+00:00 Put title outside doc div when HTML:fying title+prologue Avoids indenting the title, and makes more sense since the title is not a doc string anyway. - - - - - 5f639054 by David Waern at 2011-01-22T16:09:44+00:00 Fix spelling error - contributed by Marco Silva - - - - - c11dce78 by Ian Lynagh at 2011-01-07T02:33:11+00:00 Follow GHC build system changes - - - - - 101cfaf5 by David Waern at 2011-01-08T14:06:44+00:00 Bump version - - - - - af62348b by David Waern at 2011-01-08T14:07:07+00:00 TAG 2.9.2 - - - - - 4d1f6461 by Ian Lynagh at 2011-01-07T23:06:57+00:00 Name the haddock script haddock-ghc-7.0.2 instead of haddock-7.0.2; haskell/haddock#4882 "7.0.2" looked like a haddock version number before - - - - - 8ee4d5d3 by Simon Peyton Jones at 2011-01-10T17:31:12+00:00 Update Haddock to reflect change in hs_tyclds field of HsGroup - - - - - 06f3e3db by Ian Lynagh at 2011-03-03T15:02:37+00:00 TAG GHC 7.0.2 release - - - - - 7de0667d by David Waern at 2011-03-10T22:47:13+00:00 Update CHANGES - - - - - 33a9f1c8 by David Waern at 2011-03-10T22:47:31+00:00 Fix build with ghc 7.0.1 - - - - - 4616f861 by David Waern at 2011-03-10T22:47:50+00:00 TAG 2.9.2-actual - - - - - 0dab5e3c by Simon Hengel at 2011-04-08T15:53:01+00:00 Set shell script for unit tests back to work - - - - - 85c54dee by Simon Hengel at 2011-04-08T16:01:24+00:00 Set unit tests back to work Here "ghci>" was still used instead of ">>>". - - - - - 1cea9b78 by Simon Hengel at 2011-04-08T16:25:36+00:00 Update runtests.hs for GHC 7.0.2 - - - - - 8e5b3bbb by Simon Hengel at 2011-04-08T16:28:49+00:00 Update Haddock version in *.html.ref - - - - - 2545e955 by Simon Hengel at 2011-04-08T17:09:28+00:00 Add support for blank lines in the result of examples Result lines that only contain the string "<BLANKLINE>" are treated as a blank line. - - - - - adf64d2e by Simon Hengel at 2011-04-08T17:36:50+00:00 Add documentation for "support for blank lines in the result of examples" - - - - - c51352ca by David Waern at 2011-05-21T23:57:56+00:00 Improve a haddock comment - - - - - 7419cf2c by David Waern at 2011-05-22T15:41:52+00:00 Use cabal's test suite support to run the test suite This gives up proper dependency tracking of the test script. - - - - - 7770070c by David Waern at 2011-05-22T01:45:44+00:00 We don't need to send DocOptions nor a flag to mkExportItems - - - - - 9d95b7b6 by David Waern at 2011-05-22T21:39:03+00:00 Fix a bug - - - - - 1f93699b by David Waern at 2011-05-22T21:40:21+00:00 Break out fullContentsOf, give it a better name and some documentation The documentation describes how we want this function to eventually behave, once we have fixed a few problems with the current implementation. - - - - - 9a86432f by David Waern at 2011-05-22T21:53:52+00:00 Fix some stylistic issues in mkExportItems - - - - - c271ff0c by David Waern at 2011-05-22T22:09:11+00:00 Indentation - - - - - 93e602b1 by David Waern at 2011-06-10T01:35:31+00:00 Add git commits since switchover: darcs format (followed by a conflict resolution): commit 6f92cdd12d1354dfbd80f8323ca333bea700896a Merge: f420cc4 28df3a1 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 19 17:54:34 2011 +0100 Merge remote branch 'origin/master' into ghc-generics commit 28df3a119f770fdfe85c687dd73d5f6712b8e7d0 Author: Max Bolingbroke <batterseapower at hotmail.com> Date: Sat May 14 22:37:02 2011 +0100 Unicode fix for getExecDir on Windows commit 89813e729be8bce26765b95419a171a7826f6d70 Merge: 6df3a04 797ab27 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 9 11:55:17 2011 +0100 Merge branch 'ghc-new-co' commit 6df3a040da3dbddee67c6e30a892f87e6b164383 Author: Ian Lynagh <igloo at earth.li> Date: Sun May 8 17:05:50 2011 +0100 Follow changes in SDoc commit f420cc48b9259f0b1afd2438b12f9a2bde57053d Author: Jose Pedro Magalhaes <jpm at cs.uu.nl> Date: Wed May 4 17:31:52 2011 +0200 Adapt haddock to the removal of HsNumTy and TypePat. commit 797ab27bdccf39c73ccad374fea265f124cb52ea Merge: 1d81436 5a91450 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:05:03 2011 +0100 Merge remote branch 'origin/master' into ghc-new-co commit 1d8143659a81cf9611668348e33fd0775c7ab1d2 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:03:46 2011 +0100 Wibbles for ghc-new-co branch commit 5a91450e2ea5a93c70bd3904b022445c9cc82488 Author: Ian Lynagh <igloo at earth.li> Date: Fri Apr 22 00:51:56 2011 +0100 Follow defaultDynFlags change in GHC - - - - - 498da5ae by David Waern at 2011-06-11T00:33:33+00:00 * Merge in git patch from Michal Terepeta >From 6fc71d067738ef4b7de159327bb6dc3d0596be29 Mon Sep 17 00:00:00 2001 From: Michal Terepeta <michal.terepeta at gmail.com> Date: Sat, 14 May 2011 19:18:22 +0200 Subject: [PATCH] Follow the change of TypeSig in GHC. This follows the change in GHC to make TypeSig take a list of names (instead of just one); GHC ticket haskell/haddock#1595. This should also improve the Haddock output in case the user writes a type signature that refers to many names: -- | Some comment.. foo, bar :: ... will now generate the expected output with one signature for both names. - - - - - 094607fe by Ian Lynagh at 2011-06-17T19:10:29+01:00 Fix build - - - - - 8fa35740 by Ian Lynagh at 2011-06-26T21:06:40+01:00 Bump GHC dep to allow 7.2 - - - - - e4d2ca3c by Ian Lynagh at 2011-07-07T23:06:28+01:00 Relax base dep - - - - - b948fde9 by Ian Lynagh at 2011-07-28T16:39:45+01:00 GHC build system: Don't install the datafiles twice - - - - - f82f6d70 by Simon Marlow at 2011-08-11T12:08:15+01:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - b341cc12 by Max Bolingbroke at 2011-08-22T20:25:27+01:00 Fix compilation with no-pred-ty GHC - - - - - 30494581 by Max Bolingbroke at 2011-08-23T10:20:54+01:00 Remaining fixes for PredTy removal - - - - - 0b197138 by Max Bolingbroke at 2011-08-26T08:27:45+01:00 Rename factKind to constraintKind - - - - - a379bec5 by Max Bolingbroke at 2011-09-04T12:54:47+01:00 Deal with change to IParam handling in GHC - - - - - f94e421b by Max Bolingbroke at 2011-09-06T17:34:31+01:00 Adapt Haddock for the ConstraintKind extension changes - - - - - 8821e5cc by Max Bolingbroke at 2011-09-09T08:24:59+01:00 Ignore associated type defaults (just as we ignore default methods) - - - - - 31a0afd4 by Max Bolingbroke at 2011-09-09T09:06:00+01:00 Merge branch 'no-pred-ty' of ssh://darcs.haskell.org/srv/darcs/haddock into no-pred-ty - - - - - dd3b530a by Max Bolingbroke at 2011-09-09T14:10:25+01:00 Merge branch 'no-pred-ty' Conflicts: src/Haddock/Convert.hs - - - - - 5f25ec96 by Max Bolingbroke at 2011-09-09T14:10:40+01:00 Replace FactTuple with ConstraintTuple - - - - - cd30b9cc by David Waern at 2011-09-26T02:17:55+02:00 Bump to version 2.9.3 - - - - - 4fbfd397 by Max Bolingbroke at 2011-09-27T14:55:21+01:00 Follow changes to BinIface Name serialization - - - - - 92257d90 by David Waern at 2011-09-30T23:45:07+02:00 Fix problem with test files not added to distribution tarball - - - - - 00255bda by David Waern at 2011-09-30T23:48:24+02:00 Merge branch 'development' - - - - - 5421264f by David Waern at 2011-10-01T01:25:39+02:00 Merge in darcs patch from Simon Meier: Wed Jun 1 19:41:16 CEST 2011 iridcode at gmail.com * prettier haddock coverage info The new coverage info rendering uses less horizontal space. This reduces the number of unnecessary line-wrappings. Moreover, the most important information, how much has been documented already, is now put up front. Hopefully, this makes it more likely that a library author is bothered by the low coverage of his modules and fixes that issue ;-) - - - - - 07d318ef by David Waern at 2011-10-01T01:34:10+02:00 Use printException instead of deprecated printExceptionAndWarnings - - - - - 40d52ee4 by David Waern at 2011-10-01T01:41:13+02:00 Merge in darcs pach: Mon Apr 11 18:09:54 JST 2011 Liyang HU <haddock at liyang.hu> * Remember collapsed sections in index.html / haddock-util.js - - - - - 279d6dd4 by David Waern at 2011-10-01T01:55:45+02:00 Merge in darcs patch: Joachim Breitner <mail at joachim-breitner.de>**20110619201645 Ignore-this: f6c51228205b0902ad5bfad5040b989a As reported on http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=578301, generating the global index takes much too long if type-level (with lots of auto-generated types) is installed. The patch avoids a quadratic runtime in the subfunction getIfaceIndex of ppHtmlIndex by using a temporary set. Runtime improvement observed here from 25.36s to 2.86s. - - - - - d1612383 by David Waern at 2011-10-01T01:56:48+02:00 Merge branch 'development' - - - - - 347520c1 by David Waern at 2011-10-01T01:56:54+02:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9a0c95e8 by David Waern at 2011-10-01T02:19:10+02:00 Improve .cabal file - - - - - 6967dc64 by Ian Lynagh at 2011-10-01T01:34:06+01:00 Follow changes to ForeignImport/ForeignExport in GHC - - - - - 565cb26b by Simon Marlow at 2011-10-04T00:15:04+02:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - 8b74f512 by David Waern at 2011-10-04T00:18:17+02:00 Requre ghc >= 7.2 - - - - - 271d360c by David Waern at 2011-10-04T00:22:50+02:00 Bump version to 2.9.4 - - - - - 37f3edb0 by David Waern at 2011-10-06T02:30:21+02:00 Add alex and happy to build-tools. - - - - - 7ac2bb6e by David Terei at 2011-10-12T14:02:55-07:00 Add safe haskell indication to haddock output - - - - - 42c91a47 by David Terei at 2011-10-12T14:06:03-07:00 Fix CSS issue with info table not being contained in module header - - - - - 0eddab6c by David Terei at 2011-10-12T14:06:58-07:00 Add safe haskell indication to haddock output - - - - - 3df058eb by David Terei at 2011-10-12T14:07:07-07:00 Fix CSS issue with info table not being contained in module header - - - - - a40a6c3f by David Waern at 2011-10-22T11:29:06+02:00 Bump .haddock file version since the format has changed recently - - - - - 8a6254be by David Waern at 2011-10-22T11:30:42+02:00 Merge branch 'development' - - - - - 642e3e02 by David Waern at 2011-10-23T21:23:39+02:00 Sort import list - - - - - 36371cf8 by David Waern at 2011-10-23T22:48:18+02:00 Remove NEW_GHC_LAYOUT conditional. - - - - - 5604b499 by David Waern at 2011-10-27T00:15:03+02:00 Add --print-ghc-path. - - - - - 463499fa by David Waern at 2011-10-27T00:16:22+02:00 Make testsuite able to find its dependencies automatically. - - - - - a3506172 by Ryan Newton at 2011-11-05T05:59:58-04:00 Improved declNames internal error. Added a case to handle DocD. - - - - - 001b8baf by David Waern at 2011-11-05T20:37:29+01:00 Rename copy.hs -> accept.hs. - - - - - 55d808d3 by David Waern at 2011-11-05T23:30:02+01:00 Fix build. - - - - - deb5c3be by David Waern at 2011-11-06T00:01:47+01:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9b663554 by David Waern at 2011-11-06T00:03:45+01:00 Merge https://github.com/rrnewton/haddock - - - - - 1abb0ff6 by David Waern at 2011-11-06T01:20:37+01:00 Use getDeclMainBinder instead of declNames. - - - - - 4b005c01 by David Waern at 2011-11-06T19:09:53+01:00 Fix build. - - - - - c2c51bc7 by Ian Lynagh at 2011-11-06T23:01:33+00:00 Remove -DNEW_GHC_LAYOUT in ghc.mk - - - - - f847d703 by Jose Pedro Magalhaes at 2011-11-11T09:07:39+00:00 New kind-polymorphic core This big patch implements a kind-polymorphic core for GHC. The current implementation focuses on making sure that all kind-monomorphic programs still work in the new core; it is not yet guaranteed that kind-polymorphic programs (using the new -XPolyKinds flag) will work. For more information, see http://haskell.org/haskellwiki/GHC/Kinds - - - - - 7d7c3b09 by Jose Pedro Magalhaes at 2011-11-16T21:42:22+01:00 Follow changes to tuple sorts in master - - - - - 8430e03e by Simon Peyton Jones at 2011-11-17T10:20:27+00:00 Remove redundant imports - - - - - d1b06832 by Ian Lynagh at 2011-11-19T01:33:21+00:00 Follow GHC build system change to the way we call rm - - - - - 9e2230ed by David Waern at 2011-11-24T15:00:24+01:00 Fix a bug in test runner and get rid of regex-compat dependency. - - - - - 52039b21 by David Waern at 2011-11-24T23:55:36+01:00 Avoid haskell98 dependency in test - - - - - 92e1220d by David Waern at 2011-11-25T00:03:33+01:00 Avoid depency on regex-compat also in accept.hs. - - - - - ddac6b6f by David Waern at 2011-11-25T02:13:38+01:00 Accept test output. - - - - - 5a720455 by David Waern at 2011-11-25T02:16:20+01:00 Some more changes to test scripts. - - - - - 170a9004 by David Waern at 2011-11-25T02:30:41+01:00 Add flag --interface-version. - - - - - d225576c by David Waern at 2011-11-25T02:39:26+01:00 Remove #ifs for older compiler versions. - - - - - f0d0a4f5 by David Waern at 2011-11-26T04:20:12+01:00 Give preference to type over data constructors for doc comment links at renaming time. Previously this was done in the backends. Also, warn when a doc comment refers to something that is in scope but which we don't have the .haddock file for. These changes mean we can make DocIdentifier [a] into DocIdentifier a. - - - - - eef0e776 by David Waern at 2011-11-26T17:01:06+01:00 Allow doc comments to link to out-of-scope things (#78). (A bug that should have been fixed long ago.) - - - - - 565ad529 by David Waern at 2011-11-26T19:56:21+01:00 Update tests. - - - - - fb3ce7b9 by David Waern at 2011-11-26T21:44:28+01:00 Cleanup. - - - - - d0328126 by David Waern at 2011-11-26T22:10:28+01:00 Fix module reference bug. - - - - - c03765f8 by David Waern at 2011-12-03T05:20:20+01:00 Slightly better behaviour on top-levels without type signatures. - Docs don't get attached to the next top-level with signature by mistake. - If there's an export list and the top-level is part of it, its doc comment shows up in the documentation. - - - - - 48461d31 by David Waern at 2011-12-03T05:38:10+01:00 Add a test for Unicode doc comments. - - - - - 549c4b4e by David Waern at 2011-12-03T19:07:55+01:00 Cleanup. - - - - - 7bfecf91 by David Waern at 2011-12-03T20:13:08+01:00 More cleanup. - - - - - 14fab722 by Ian Lynagh at 2011-12-12T21:21:35+00:00 Update dependencies and binaryInterfaceVersion - - - - - 469e6568 by Ian Lynagh at 2011-12-18T12:56:16+00:00 Fix (untested) building from source tarball without alex/happy haddock's .cabal file was declaring that it needed alex and happy to build, but in the GHC source tarballs it doesn't. - - - - - 895c9a8c by David Waern at 2011-12-27T12:57:43+01:00 Go back to having a doc, sub and decl map instead of one big decl map. This setup makes more sense since when we add value bindings to the processed declarations (for type inference), we will have multiple declarations which should share documentation. Also, we already have a separate doc map for instances which we can now merge into the main doc map. Another benefit is that we don't need the DeclInfo type any longer. - - - - - 736767d9 by David Waern at 2011-12-27T13:33:41+01:00 Merge ../../../haddock Conflicts: src/Haddock/InterfaceFile.hs - - - - - 20016f79 by David Waern at 2011-12-27T13:57:23+01:00 Bump version. - - - - - 31f276fb by David Waern at 2011-12-27T13:57:32+01:00 Merge ../ghc/utils/haddock - - - - - 95b367cd by David Waern at 2011-12-27T14:57:29+01:00 Update tests following version bump. - - - - - fa3c94cd by David Waern at 2011-12-27T14:57:51+01:00 Get rid of quite unnecessary use of different lists. - - - - - 9c4d3c54 by David Waern at 2011-12-27T15:26:42+01:00 Cleanup. - - - - - 2caf9f90 by David Waern at 2011-12-27T16:18:05+01:00 Wibbles. - - - - - 3757d09b by David Waern at 2011-12-27T20:50:26+01:00 Complete support for inferring types for top-level bindings. - - - - - 53418734 by David Waern at 2011-12-28T15:02:13+01:00 Minor fixes and cleanup. - - - - - 0c9d0385 by Ian Lynagh at 2012-01-03T18:31:29+00:00 Follow rename of Instance to ClsInst in GHC - - - - - c9bc969a by Simon Hengel at 2012-01-12T21:28:14+01:00 Make sure that generated xhtml is valid (close haskell/haddock#186) Thanks to Phyx. - - - - - 836a0b9a by David Waern at 2012-02-01T02:30:05+01:00 Fix bug introduced in my recent refactoring. - - - - - c7d733eb by David Waern at 2012-02-01T02:30:26+01:00 Cleanup mkMaps and avoid quadratic behaviour. - - - - - da3cda8f by David Waern at 2012-02-01T02:56:56+01:00 Require ghc >= 7.4. - - - - - 83a3287e by David Waern at 2012-02-01T02:57:36+01:00 Update CHANGES. - - - - - 93408f0b by Simon Hengel at 2012-02-04T00:48:04+01:00 Add reference renderings - - - - - 49d00d2c by Simon Hengel at 2012-02-04T00:48:25+01:00 Set unit tests for parser back to work - - - - - eb450980 by Simon Hengel at 2012-02-04T00:49:07+01:00 Add .gitignore - - - - - a841602c by Simon Hengel at 2012-02-04T00:49:16+01:00 Add .ghci file - - - - - 8861199d by Simon Hengel at 2012-02-04T00:49:29+01:00 tests/html-tests/copy.hs: Use mapM_ instead of mapM So we do net get a list of () on stdout when running with runhaskell. - - - - - b477d9b5 by Simon Hengel at 2012-02-04T00:49:46+01:00 Remove index files from golden tests - - - - - 9dbda34e by Simon Hengel at 2012-02-04T00:49:57+01:00 Add /tests/html-tests/tests/*index*.ref to .gitignore - - - - - a9434817 by Simon Hengel at 2012-02-04T00:50:04+01:00 Add DocWarning to Doc The Xhtml backend has special markup for that, Hoogle and LaTeX reuse what we have for DocEmphasis. - - - - - de2fb6fa by Simon Hengel at 2012-02-04T00:50:13+01:00 Add support for module warnings - - - - - 0640920e by Simon Hengel at 2012-02-04T00:50:21+01:00 Add tests for module warnings - - - - - 30ce0d77 by Simon Hengel at 2012-02-04T00:50:29+01:00 Add support for warnings - - - - - bb367960 by Simon Hengel at 2012-02-04T00:50:37+01:00 Add tests for warnings - - - - - 6af1dc2d by Simon Hengel at 2012-02-04T00:50:50+01:00 Expand type signatures in export list (fixes haskell/haddock#192) - - - - - a06cbf25 by Simon Hengel at 2012-02-04T00:51:04+01:00 Expand type signatures for modules without explicit export list - - - - - 57dda796 by Simon Hengel at 2012-02-04T00:51:15+01:00 Remove obsolete TODO - - - - - 270c3253 by David Waern at 2012-02-04T00:51:24+01:00 Fix issues in support for warnings. * Match against local names only. * Simplify (it's OK to map over the warnings). - - - - - 683634bd by David Waern at 2012-02-04T00:55:11+01:00 Some cleanup and make sure we filter warnings through exports. - - - - - 210cb4ca by David Waern at 2012-02-04T03:01:30+01:00 Merge branch 'fix-for-186' of https://github.com/sol/haddock into ghc-7.4 - - - - - e8db9031 by David Waern at 2012-02-04T03:07:51+01:00 Style police. - - - - - 261f9462 by David Waern at 2012-02-04T03:20:16+01:00 Update tests. - - - - - 823cfc7c by David Waern at 2012-02-04T03:21:12+01:00 Use mapM_ in accept.hs as well. - - - - - 873dd619 by David Waern at 2012-02-04T03:21:33+01:00 Remove copy.hs - use accept.hs instead. - - - - - 0e31a14a by David Waern at 2012-02-04T03:47:33+01:00 Use <> instead of mappend. - - - - - 2ff7544f by David Waern at 2012-02-04T03:48:55+01:00 Remove code for older ghc versions. - - - - - dacf2786 by David Waern at 2012-02-04T15:52:51+01:00 Clean up some code from last SoC project. - - - - - 00cbb117 by David Waern at 2012-02-04T21:43:49+01:00 Mostly hlint-inspired cleanup. - - - - - 7dc86cc2 by Simon Peyton Jones at 2012-02-06T09:14:41+00:00 Track changes in HsDecls - - - - - f91f82fe by Ian Lynagh at 2012-02-16T13:40:11+00:00 Follow changes in GHC caused by the CAPI CTYPE pragma - - - - - a0ea6b0b by Ian Lynagh at 2012-02-22T02:26:12+00:00 Follow changes in GHC - - - - - b23b07d1 by Simon Peyton Jones at 2012-03-02T16:36:41+00:00 Follow changes in data representation from the big PolyKinds commit - - - - - 43406022 by Simon Hengel at 2012-03-05T11:18:34+01:00 Save/restore global state for static flags when running GHC actions This is necessary if we want to run createInterfaces (from Documentation.Haddock) multiple times in the same process. - - - - - 9fba16fe by Paolo Capriotti at 2012-03-06T10:57:33+00:00 Update .gitignore. - - - - - a9325044 by Simon Peyton Jones at 2012-03-14T17:35:42+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - fd48065a by Iavor Diatchki at 2012-03-15T22:43:35-07:00 Add support for type-level literals. - - - - - 2e8206dd by Simon Peyton Jones at 2012-03-16T14:18:22+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - 93e13319 by Simon Peyton Jones at 2012-03-17T01:04:05+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock Conflicts: src/Haddock/Convert.hs - - - - - d253fa71 by Iavor Diatchki at 2012-03-19T20:12:18-07:00 Merge remote-tracking branch 'origin/master' into type-nats - - - - - fc40acc8 by Iavor Diatchki at 2012-03-19T20:31:27-07:00 Add a missing case for type literals. - - - - - fd2ad699 by Iavor Diatchki at 2012-03-24T13:28:29-07:00 Rename variable to avoid shadowing warning. - - - - - 9369dd3c by Simon Peyton Jones at 2012-03-26T09:14:23+01:00 Follow refactoring of TyClDecl/HsTyDefn - - - - - 38825ca5 by Simon Peyton Jones at 2012-03-26T09:14:37+01:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - 4324ac0f by David Waern at 2012-04-01T01:51:19+02:00 Disable unicode test. - - - - - 3165b750 by David Waern at 2012-04-01T01:51:34+02:00 Take reader environment directly from TypecheckedSource. - - - - - 213b644c by David Waern at 2012-04-01T01:55:20+02:00 Cleanup. - - - - - 3118b4ba by David Waern at 2012-04-01T02:16:15+02:00 Don't filter out unexported names from the four maps - fixes a regression. - - - - - d6524e17 by David Waern at 2012-04-01T02:40:34+02:00 Fix crash when using --qual. Naughty GHC API! - - - - - ea3c43d8 by Henning Thielemann at 2012-04-01T13:03:07+02:00 add QualOption type for distinction between qualification argument given by the user and the actual qualification for a concrete module - - - - - 5422ff05 by Henning Thielemann at 2012-04-01T16:25:02+02:00 emit an error message when the --qual option is used incorrectly - - - - - 026e3404 by David Waern at 2012-04-01T18:10:30+02:00 Don't crash on unicode strings in doc comments. - - - - - ce006632 by David Waern at 2012-04-01T20:13:35+02:00 Add test for --ignore-all-exports flag/ignore-exports pragma. - - - - - 6e4dd33c by David Waern at 2012-04-01T20:21:03+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.4 - - - - - 734ae124 by Henning Thielemann at 2012-04-01T20:22:10+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - 622f9ba5 by David Waern at 2012-04-01T21:26:13+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 55ce17cb by Henning Thielemann at 2012-04-01T22:03:25+02:00 'abbreviate' qualification style - basic support Currently we ignore the package a module is imported from. This means that a module import would shadow another one with the same module name from a different package. - - - - - c85314ef by David Waern at 2012-04-01T22:05:12+02:00 Check qualification option before processing modules. - - - - - ae4b626c by Henning Thielemann at 2012-04-02T00:19:36+02:00 abbreviated qualification: use Packages.lookupModuleInAllPackages for finding the package that a module belongs to - - - - - 60bdbcf5 by Henning Thielemann at 2012-04-02T00:25:31+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - df44301d by Henning Thielemann at 2012-04-02T00:29:05+02:00 qualification style 'abbreviated' -> 'aliased' - - - - - f4192a64 by David Waern at 2012-04-02T01:05:47+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 7ba09067 by David Terei at 2012-04-04T15:08:21-07:00 Fix reporting of modules safe haskell mode (#5989) - - - - - d0cc33d0 by David Terei at 2012-04-06T15:50:41+01:00 Fix reporting of modules safe haskell mode (#5989) - - - - - 6e3434c5 by Simon Peyton Jones at 2012-04-20T18:37:46+01:00 Track changes in HsSyn - - - - - 22014ed0 by Simon Peyton Jones at 2012-05-11T22:45:15+01:00 Follow changes to LHsTyVarBndrs - - - - - d9a07b24 by David Waern at 2012-05-15T01:46:35+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - a6c4ebc6 by David Waern at 2012-05-16T02:18:32+02:00 Update CHANGES. - - - - - 8e181d29 by David Waern at 2012-05-16T02:27:56+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - e358210d by David Waern at 2012-05-16T02:35:33+02:00 Mention the new aliased --qual mode in CHANGES. - - - - - efd36a28 by David Waern at 2012-05-16T21:33:13+02:00 Bump version number. - - - - - d6b3af14 by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for deprecated record field - - - - - 927f800e by Simon Hengel at 2012-05-17T19:08:20+02:00 Use >>= instead of fmap and join - - - - - 048b41d5 by Simon Hengel at 2012-05-17T19:08:20+02:00 newtype-wrap Doc nodes for things that may have warnings attached - - - - - e3a89fc3 by Simon Hengel at 2012-05-17T19:08:20+02:00 Attach warnings to `Documentation` type - - - - - 5d4cc43d by Simon Hengel at 2012-05-17T19:08:20+02:00 Simplify lookupWarning - - - - - cf8ae69d by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for haskell/haddock#205 - - - - - cb409b19 by Simon Peyton Jones at 2012-05-25T08:30:11+01:00 Follow changes in LHsTyVarBndrs - - - - - 2d5f4179 by Simon Hengel at 2012-05-26T19:21:29+02:00 Add Applicative instance for (GenRnM a) - - - - - e4373060 by Simon Hengel at 2012-05-26T19:21:33+02:00 Use a map for warnings, as suggested by @waern - - - - - 597a68c7 by Simon Hengel at 2012-05-27T08:48:24+02:00 Add an optional label to URLs - - - - - ef1ac7fe by Simon Hengel at 2012-05-27T08:48:24+02:00 Add support for hyperlink labels to parser - - - - - 41f2adce by Simon Hengel at 2012-05-27T08:48:24+02:00 Add golden test for hyperlinks - - - - - 83d5e764 by Simon Hengel at 2012-05-27T08:50:02+02:00 Use LANGUAGE pragmas instead of default-extensions in cabal file - - - - - ddb755e5 by Simon Hengel at 2012-05-27T08:50:02+02:00 Fix typo in comment - - - - - 110676b4 by Simon Hengel at 2012-05-27T08:50:02+02:00 Add a type signature for a where-binding - - - - - 7d9ba2a0 by Ian Lynagh at 2012-06-12T14:38:01+01:00 Follow changes in GHC - - - - - 47c704f2 by Ian Lynagh at 2012-06-12T18:52:16+01:00 Follow changes in GHC - - - - - e1efe1ab by Simon Peyton Jones at 2012-06-13T17:25:29+01:00 Follow changes for the implementation of implicit parameters - - - - - 69abc81c by Ian Lynagh at 2012-06-19T22:52:58+01:00 Follow changes in base - - - - - 9d074a21 by Paolo Capriotti at 2012-06-22T18:26:47+01:00 Use right docMap to get decl documentation. - - - - - e3292ef6 by Ian Lynagh at 2012-07-15T01:31:19+01:00 Follow changes in GHC - - - - - ceae56b0 by Ian Lynagh at 2012-07-16T21:22:48+01:00 Fix haddock following some GHC changes Passing _|_ as the Settings for defaultDynFlags no longer works well enough - - - - - 9df72735 by Paolo Capriotti at 2012-07-19T16:49:32+01:00 Forward port changes from stable. - - - - - 572f5fcf by Ian Lynagh at 2012-07-19T20:38:26+01:00 Merge branch 'master' of darcs.haskell.org:/srv/darcs//haddock - - - - - 9195aca4 by Paolo Capriotti at 2012-07-20T10:27:28+01:00 Update dependencies. - - - - - 33db3923 by Ian Lynagh at 2012-07-20T17:54:43+01:00 Build with GHC 7.7 - - - - - 925a2cea by David Waern at 2012-07-23T16:50:40+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.6 Conflicts: src/Haddock/InterfaceFile.hs - - - - - d710ef97 by David Waern at 2012-07-23T16:52:07+02:00 Bump version number. - - - - - eb0c2f83 by David Waern at 2012-07-23T16:57:58+02:00 Update CHANGES. - - - - - b3f56943 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Hide "internal" instances This fixes haskell/haddock#37 (http://trac.haskell.org/haddock/ticket/37) Precisely, we show an instance iff its class and all the types are exported by non-hidden modules. - - - - - a70aa412 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Tests for hiding instances (#37) - - - - - c0f4aa58 by Simon Hengel at 2012-07-27T13:00:13+03:00 Add an other test for hiding instances (#37) - - - - - a7ed6268 by Ian Lynagh at 2012-08-07T14:48:13+01:00 Follow changes in GHC - - - - - 0ab30d38 by Ian Lynagh at 2012-08-13T22:12:27+01:00 Improve haddock memory usage - - - - - 0eaa4e30 by Ian Lynagh at 2012-08-13T23:58:46+01:00 Improve haddock memory usage - - - - - 659d26cf by Ian Lynagh at 2012-08-14T13:16:48+01:00 Remove some temporary pragmas I accidentally recorded - - - - - d97fceb6 by Simon Hengel at 2012-08-25T13:19:34+02:00 Add missing dependency to library - - - - - 4c910697 by Simon Hengel at 2012-08-28T07:39:14+02:00 Move .ghci to project root - - - - - fc3c601a by Simon Hengel at 2012-08-28T07:39:14+02:00 accept.hs: Ignore some files - - - - - 1af9b984 by Simon Hengel at 2012-08-28T07:40:04+02:00 Update reference renderings (bump version) - - - - - 980dc253 by Simon Hengel at 2012-08-28T07:40:32+02:00 Update reference renderings (remove links for ()) - - - - - 33651dbf by Simon Hengel at 2012-08-28T07:41:50+02:00 Update documentation of `runInteractiveProcess` in reference rendering - - - - - 7ab25078 by David Waern at 2012-09-07T10:38:50+02:00 Merge branch 'hiddenInstances2' of http://github.com/feuerbach/haddock into ghc-7.6 - - - - - c3de3a4b by David Waern at 2012-09-07T14:29:27+02:00 Follow changes in GHC. - - - - - 298c43ac by David Waern at 2012-09-07T14:59:24+02:00 Update CHANGES. - - - - - e797993a by David Waern at 2012-09-07T15:21:30+02:00 Update ANNOUNCE. - - - - - d0b44790 by David Waern at 2012-09-07T15:22:43+02:00 Merge branch 'hidden-instances' into ghc-7.6 - - - - - 41a4adc8 by Simon Hengel at 2012-09-08T12:08:37+02:00 Update doc/README - - - - - 71ad1040 by Simon Hengel at 2012-09-08T12:17:17+02:00 Add documentation for URL labels - - - - - 9bb41afd by Simon Peyton Jones at 2012-09-20T18:14:26+01:00 Follow data type changes in the tc-untouchables branch Relating entirely to SynTyConRhs - - - - - b8139bfa by Simon Hengel at 2012-09-21T14:24:16+02:00 Disable Unicode test for now - - - - - a5fafdd7 by Simon Hengel at 2012-09-21T14:35:45+02:00 Update TypeOperators test for GHC 7.6.1 Type operators can't be used as type variables anymore! - - - - - 6ccf0025 by Simon Hengel at 2012-09-21T16:02:24+02:00 Remove (Monad (Either e)) instance from ref. rendering of CrossPackageDocs I do not really understand why the behavior changed, so I'll open a ticket, so that we can further investigate. - - - - - b5c6c138 by Ian Lynagh at 2012-09-27T02:00:57+01:00 Follow changes in GHC build system - - - - - b98eded0 by David Waern at 2012-09-27T15:37:02+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 76cc2051 by David Waern at 2012-09-27T15:48:19+02:00 Update hidden instances tests. - - - - - aeaa1c59 by David Waern at 2012-09-28T10:21:32+02:00 Make API buildable with GHC 7.6. - - - - - d76be1b0 by Simon Peyton Jones at 2012-09-28T15:57:05+01:00 Merge remote-tracking branch 'origin/master' into tc-untouchables - - - - - a1922af8 by David Waern at 2012-09-28T19:50:20+02:00 Fix spurious superclass constraints bug. - - - - - bc41bdbb by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove old examples - - - - - bed7d3dd by Simon Hengel at 2012-10-01T11:30:51+02:00 Adapt parsetests for GHC 7.6.1 - - - - - dcdb22bb by Simon Hengel at 2012-10-01T11:30:51+02:00 Add test-suite section for parsetests to cabal file + get rid of HUnit dependency - - - - - 1e5263c9 by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove test flag from cabal file This was not really used. - - - - - 4beee98b by David Waern at 2012-09-28T23:42:28+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 11dd2256 by Ian Lynagh at 2012-10-03T16:17:35+01:00 Follow change in GHC build system - - - - - fbd77962 by Simon Hengel at 2012-10-03T18:49:40+02:00 Remove redundant dependency from cabal file - - - - - 09218989 by Simon Hengel at 2012-10-04T16:03:05+02:00 Fix typo - - - - - 93a2d5f9 by Simon Hengel at 2012-10-04T16:11:41+02:00 Remove trailing whitespace from cabal file - - - - - c8b46cd3 by Simon Hengel at 2012-10-04T16:12:17+02:00 Export Haddock's main entry point from library - - - - - b411e77b by Simon Hengel at 2012-10-04T16:29:46+02:00 Depend on library for executable The main motivation for this is to increase build speed. In GHC's source tree the library is not build, but all modules are now required for the executable, so that GHC's validate will now detect build failures for the library. - - - - - f8f0979f by Simon Hengel at 2012-10-05T00:32:57+02:00 Set executable flag for Setup.lhs - - - - - dd045998 by Simon Hengel at 2012-10-07T16:44:06+02:00 Extend rather than set environment when running HTML tests On some platforms (e.g. ppc64) GHC requires gcc in the path. - - - - - 7b39c3ae by Simon Hengel at 2012-10-07T17:05:45+02:00 cross-package test: re-export IsString instead of Monad There is a monad instance for Q, which is not available on platforms that do not have GHCi support. This caused CrossPackageDocs to fail on those platforms. Re-exporting IsString should test the same thing, but it works on all platforms. - - - - - 0700c605 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Fix some warnings - - - - - f78eca79 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Make -Wall proof - - - - - 6beec041 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Use listToMaybe/fromMaybe instead of safeHead/maybe - - - - - 44b8ce86 by Ian Lynagh at 2012-10-08T21:59:46+01:00 Follow changes in GHC - - - - - 6da5f702 by Simon Hengel at 2012-10-09T11:16:19+02:00 Update .ghci - - - - - 9ac1a1b9 by Kazu Yamamoto at 2012-10-09T12:45:31+02:00 Add markup support for properties - - - - - 1944cb42 by Simon Hengel at 2012-10-09T12:45:31+02:00 Simplify lexing/parsing of properties In contrast to what we do for examples, we do not really need to capture the "prompt" here. - - - - - bffd8e62 by Simon Hengel at 2012-10-09T13:40:14+02:00 Add HTML test for properties - - - - - 2fe9c5cb by Simon Hengel at 2012-10-09T13:40:21+02:00 Add unit tests for properties - - - - - 874e361b by Simon Hengel at 2012-10-09T13:40:33+02:00 Bump interface version - - - - - 2506cc37 by Simon Hengel at 2012-10-09T15:15:04+02:00 Fix parser bug - - - - - 743d2b7d by Simon Hengel at 2012-10-09T15:31:06+02:00 Allow to load interface files with compatible versions - - - - - 981a1660 by Simon Hengel at 2012-10-10T10:32:05+02:00 Export more types from Documentation.Haddock (fixes haskell/haddock#216) - - - - - dff7dc76 by Simon Hengel at 2012-10-10T11:15:19+02:00 Update ANNOUNCE and CHANGES - - - - - edd2bb01 by Simon Hengel at 2012-10-10T11:22:50+02:00 Bump version - - - - - 5039163b by Simon Hengel at 2012-10-10T13:56:04+02:00 Fix typo in documentation - - - - - e4ce34da by Simon Hengel at 2012-10-10T14:28:35+02:00 Add documentation for properties - - - - - 9555ebca by Simon Hengel at 2012-10-11T10:49:04+02:00 Remove redundant if-defs, more source documentation - - - - - 87aa67e1 by Simon Hengel at 2012-10-11T12:32:51+02:00 Adapt cabal file - - - - - c44c1dee by Simon Hengel at 2012-10-11T12:41:58+02:00 Require ghc 7.6 - - - - - 8383bc34 by Simon Hengel at 2012-10-11T12:50:24+02:00 Bump version - - - - - 1030eb38 by Simon Hengel at 2012-10-11T12:55:44+02:00 Update ANNOUNCE and CHANGES - - - - - 74955088 by Simon Hengel at 2012-10-12T09:49:31+02:00 Improve note about `binaryInterfaceVersion` (thanks David) - - - - - ee30f6b7 by Simon Hengel at 2012-10-13T13:40:59+02:00 Update version in html tests, rpm spec file, and user manual - - - - - f2861f18 by Simon Hengel at 2012-10-13T14:40:33+02:00 Remove unused MonadFix constraint - - - - - dfdf1a74 by Simon Hengel at 2012-10-13T15:15:38+02:00 Minor code simplification - - - - - 4ecd1e70 by Simon Hengel at 2012-10-13T15:33:43+02:00 Increase code locality - - - - - f7df5cc9 by Simon Hengel at 2012-10-13T16:03:12+02:00 Minor code simplification - - - - - e737eb6e by Simon Hengel at 2012-10-13T19:03:04+02:00 Handle HsExplicitListTy in renameer (fixes haskell/haddock#213) - - - - - c2dc8f17 by Simon Hengel at 2012-10-13T20:46:31+02:00 Better error messages - - - - - 14d48b4c by Simon Hengel at 2012-10-14T00:21:07+02:00 Simplify RnM type - - - - - 6c2cc547 by Simon Hengel at 2012-10-14T00:23:35+02:00 Simplify lookupRn - - - - - bc77ce85 by Simon Hengel at 2012-10-14T01:51:32+02:00 Organize unite tests hierarchically - - - - - 2306d117 by Simon Hengel at 2012-10-14T10:34:58+02:00 Handle more cases in renameType - - - - - 8a864203 by Simon Hengel at 2012-10-14T11:47:59+02:00 Add mini_HiddenInstances.html.ref and mini_HiddenInstancesB.html.ref - - - - - 3a978eca by Simon Hengel at 2012-10-14T11:49:28+02:00 Add /tests/html-tests/output/ to .gitignore - - - - - db18888a by Simon Hengel at 2012-10-14T13:38:21+02:00 Allow haddock markup in deprecation messages - - - - - e7cfee9f by Simon Hengel at 2012-10-14T14:00:23+02:00 If parsing of deprecation message fails, include it verbatim - - - - - 242a85be by Simon Hengel at 2012-10-14T14:13:24+02:00 Add description for PruneWithWarning test - - - - - 43d33df1 by Simon Hengel at 2012-10-14T15:40:53+02:00 Minor formatting change - - - - - 22768c44 by Simon Hengel at 2012-10-14T16:03:43+02:00 Properly handle deprecation messages for re-exported things (fixes haskell/haddock#220) - - - - - cb4b9111 by Simon Hengel at 2012-10-14T17:30:28+02:00 Add build artifacts for documentation to .gitignore - - - - - 854cd8de by Simon Hengel at 2012-10-14T23:34:51+02:00 unit-tests: Improve readability Add IsString instance for (Doc RdrName) + use <> instead of DocAppend. - - - - - c4446d54 by Simon Hengel at 2012-10-14T23:37:21+02:00 unit-tests: Minor refactoring Rename parse to parseParas. - - - - - 04f2703c by Simon Hengel at 2012-10-15T00:36:42+02:00 Fix typo - - - - - 3d109e44 by Simon Hengel at 2012-10-15T10:30:07+02:00 Add description for DeprecatedReExport test - - - - - 84f0985c by Simon Hengel at 2012-10-15T14:54:19+02:00 Move resources to /resources directory - - - - - a5de7ca6 by Simon Hengel at 2012-10-15T15:46:18+02:00 Move HTML tests to directory /html-test/ - - - - - e21f727d by Simon Hengel at 2012-10-15T19:32:42+02:00 Move HTML reference renderings to /html-test/ref/ - - - - - 3a3c6c75 by Simon Hengel at 2012-10-15T19:32:42+02:00 Copy css, images, etc. on accept - - - - - 40ead6dc by Simon Hengel at 2012-10-15T19:32:42+02:00 Move unit tests to /test directory - - - - - 99a28231 by Simon Hengel at 2012-10-15T19:32:42+02:00 Fix Setup.lhs /usr/bin/runhaskell is not installed on all systems. - - - - - 95faf45e by Simon Hengel at 2012-10-15T19:32:42+02:00 Make test management scripts more robust * They are now independent from the current directory, and hence can be called from everywhere * On UNIX/Linux they can now be run as scripts - - - - - 027aaa2d by Simon Hengel at 2012-10-15T19:53:40+02:00 Add 'dev' flag to cabal file, that builds without -O2 That way --disable-optimization can be used, which decreases build time considerably. - - - - - e0266ede by Simon Hengel at 2012-10-15T20:03:43+02:00 Add test case for "spurious superclass constraints bug" - - - - - 52a2aa92 by Simon Hengel at 2012-10-15T20:28:55+02:00 Adapt accept.lhs, so that it ignores more index files - - - - - 53530781 by Simon Hengel at 2012-10-15T20:49:39+02:00 Rename html-test/runtests.lhs to html-test/run.lhs - - - - - 84518797 by Simon Hengel at 2012-10-15T20:49:39+02:00 Move source files for HTML tests to html-test/src - - - - - a911dc6c by Simon Hengel at 2012-10-15T20:49:39+02:00 Adapt output directory for HTML tests - - - - - d3c15857 by Ian Lynagh at 2012-10-16T16:54:43+01:00 Follow dopt->gopt rename - - - - - 956665a5 by Simon Hengel at 2012-10-18T08:42:48+02:00 Update html-test/README - - - - - 903b1029 by Simon Hengel at 2012-10-18T08:50:26+02:00 Use markdown for html-test/README - - - - - 150b4d63 by Ian Lynagh at 2012-10-18T16:36:00+01:00 Follow changes in GHC: 'flags' has been renamed 'generalFlags' - - - - - 41e04ff9 by Simon Hengel at 2012-11-28T09:54:35+01:00 Export missing types from Documentation.Haddock - - - - - 9be59237 by Ian Lynagh at 2012-11-30T23:20:47+00:00 Update dependencies - - - - - e06842f5 by Simon Hengel at 2012-12-07T20:58:05+01:00 Bump version - - - - - e3dbede0 by Simon Hengel at 2012-12-07T20:58:05+01:00 Add missing test files to cabal file (fixes haskell/haddock#230) - - - - - ee0dcca7 by Simon Hengel at 2012-12-07T20:58:05+01:00 Update CHANGES - - - - - 51601bdb by Simon Peyton Jones at 2012-12-19T17:28:35+00:00 Track changes in UNPACK pragma stuff - - - - - f2573bc1 by Richard Eisenberg at 2012-12-21T20:56:25-05:00 Implement overlapping type family instances. An ordered, overlapping type family instance is introduced by 'type instance where', followed by equations. See the new section in the user manual (7.7.2.2) for details. The canonical example is Boolean equality at the type level: type family Equals (a :: k) (b :: k) :: Bool type instance where Equals a a = True Equals a b = False A branched family instance, such as this one, checks its equations in order and applies only the first the matches. As explained in the note [Instance checking within groups] in FamInstEnv.lhs, we must be careful not to simplify, say, (Equals Int b) to False, because b might later unify with Int. This commit includes all of the commits on the overlapping-tyfams branch. SPJ requested that I combine all my commits over the past several months into one monolithic commit. The following GHC repos are affected: ghc, testsuite, utils/haddock, libraries/template-haskell, and libraries/dph. Here are some details for the interested: - The definition of CoAxiom has been moved from TyCon.lhs to a new file CoAxiom.lhs. I made this decision because of the number of definitions necessary to support BranchList. - BranchList is a GADT whose type tracks whether it is a singleton list or not-necessarily-a-singleton-list. The reason I introduced this type is to increase static checking of places where GHC code assumes that a FamInst or CoAxiom is indeed a singleton. This assumption takes place roughly 10 times throughout the code. I was worried that a future change to GHC would invalidate the assumption, and GHC might subtly fail to do the right thing. By explicitly labeling CoAxioms and FamInsts as being Unbranched (singleton) or Branched (not-necessarily-singleton), we make this assumption explicit and checkable. Furthermore, to enforce the accuracy of this label, the list of branches of a CoAxiom or FamInst is stored using a BranchList, whose constructors constrain its type index appropriately. I think that the decision to use BranchList is probably the most controversial decision I made from a code design point of view. Although I provide conversions to/from ordinary lists, it is more efficient to use the brList... functions provided in CoAxiom than always to convert. The use of these functions does not wander far from the core CoAxiom/FamInst logic. BranchLists are motivated and explained in the note [Branched axioms] in CoAxiom.lhs. - The CoAxiom type has changed significantly. You can see the new type in CoAxiom.lhs. It uses a CoAxBranch type to track branches of the CoAxiom. Correspondingly various functions producing and consuming CoAxioms had to change, including the binary layout of interface files. - To get branched axioms to work correctly, it is important to have a notion of type "apartness": two types are apart if they cannot unify, and no substitution of variables can ever get them to unify, even after type family simplification. (This is different than the normal failure to unify because of the type family bit.) This notion in encoded in tcApartTys, in Unify.lhs. Because apartness is finer-grained than unification, the tcUnifyTys now calls tcApartTys. - CoreLinting axioms has been updated, both to reflect the new form of CoAxiom and to enforce the apartness rules of branch application. The formalization of the new rules is in docs/core-spec/core-spec.pdf. - The FamInst type (in types/FamInstEnv.lhs) has changed significantly, paralleling the changes to CoAxiom. Of course, this forced minor changes in many files. - There are several new Notes in FamInstEnv.lhs, including one discussing confluent overlap and why we're not doing it. - lookupFamInstEnv, lookupFamInstEnvConflicts, and lookup_fam_inst_env' (the function that actually does the work) have all been more-or-less completely rewritten. There is a Note [lookup_fam_inst_env' implementation] describing the implementation. One of the changes that affects other files is to change the type of matches from a pair of (FamInst, [Type]) to a new datatype (which now includes the index of the matching branch). This seemed a better design. - The TySynInstD constructor in Template Haskell was updated to use the new datatype TySynEqn. I also bumped the TH version number, requiring changes to DPH cabal files. (That's why the DPH repo has an overlapping-tyfams branch.) - As SPJ requested, I refactored some of the code in HsDecls: * splitting up TyDecl into SynDecl and DataDecl, correspondingly changing HsTyDefn to HsDataDefn (with only one constructor) * splitting FamInstD into TyFamInstD and DataFamInstD and splitting FamInstDecl into DataFamInstDecl and TyFamInstDecl * making the ClsInstD take a ClsInstDecl, for parallelism with InstDecl's other constructors * changing constructor TyFamily into FamDecl * creating a FamilyDecl type that stores the details for a family declaration; this is useful because FamilyDecls can appear in classes but other decls cannot * restricting the associated types and associated type defaults for a * class to be the new, more restrictive types * splitting cid_fam_insts into cid_tyfam_insts and cid_datafam_insts, according to the new types * perhaps one or two more that I'm overlooking None of these changes has far-reaching implications. - The user manual, section 7.7.2.2, is updated to describe the new type family instances. - - - - - f788d0fb by Simon Peyton Jones at 2012-12-23T15:49:58+00:00 Track changes in HsBang - - - - - ca460a0c by Simon Peyton Jones at 2012-12-23T15:50:28+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - f078fea6 by Simon Peyton Jones at 2013-01-02T08:33:13+00:00 Use InstEnv.instanceSig rather than instanceHead (name change) - - - - - 88e41305 by Simon Peyton Jones at 2013-01-14T17:10:27+00:00 Track change to HsBang type - - - - - e1ad4e19 by Kazu Yamamoto at 2013-02-01T11:59:24+09:00 Merge branch 'ghc-7.6' into ghc-7.6-merge-2 Conflicts: haddock.cabal src/Haddock/Interface/AttachInstances.hs src/Haddock/Interface/Create.hs src/Haddock/Interface/LexParseRn.hs src/Haddock/InterfaceFile.hs src/Haddock/Types.hs Only GHC HEAD can compile this. GHC 7.6.x cannot compile this. Some test fail. - - - - - 62bec012 by Kazu Yamamoto at 2013-02-06T11:12:28+09:00 Using tcSplitSigmaTy in instanceHead' (FIXME is resolved.) - - - - - 013fd2e4 by Kazu Yamamoto at 2013-02-06T17:56:21+09:00 Refactoring instanceHead'. - - - - - 3148ce0e by Kazu Yamamoto at 2013-02-07T17:45:10+09:00 Using new syntax in html-test/src/GADTRecords.hs. - - - - - 626dabe7 by Gabor Greif at 2013-02-15T22:42:01+01:00 Typo - - - - - 1eb667ae by Ian Lynagh at 2013-02-16T17:02:07+00:00 Follow changes in base - - - - - 3ef8253a by Ian Lynagh at 2013-03-01T23:23:57+00:00 Follow changes in GHC's build system - - - - - 1a265a3c by Ian Lynagh at 2013-03-03T23:12:07+00:00 Follow changes in GHC build system - - - - - 69941c79 by Max Bolingbroke at 2013-03-10T09:38:28-07:00 Use Alex 3's Unicode support to properly lex source files as UTF-8 Signed-off-by: David Waern <david.waern at gmail.com> - - - - - ea687dad by Simon Peyton Jones at 2013-03-15T14:16:10+00:00 Adapt to tcRnGetInfo returning family instances too This API change was part of the fix to Trac haskell/haddock#4175. But it offers new information to Haddock: the type-family instances, as well as the class instances, of this type. This patch just drops the new information on the floor, but there's an open opportunity to use it in the information that Haddock displays. - - - - - 971a30b0 by Andreas Voellmy at 2013-05-19T20:47:39+01:00 Fix for haskell/haddock#7879. Changed copy of utils/haddock/html/resources/html to use "cp -RL" rather than "cp -R". This allows users to run validate in a build tree, where the build tree was setup using lndir with a relative path to the source directory. - - - - - 31fb7694 by Ian Lynagh at 2013-05-19T20:47:49+01:00 Use "cp -L" when making $(INPLACE_LIB)/latex too - - - - - e9952233 by Simon Hengel at 2013-06-01T18:06:50+02:00 Add -itest to .ghci - - - - - b06873b3 by Mateusz Kowalczyk at 2013-06-01T18:06:50+02:00 Workaround for a failing build with --enable-tests. - - - - - e7858d16 by Simon Hengel at 2013-06-01T19:29:28+02:00 Fix broken test - - - - - 0690acb1 by Richard Eisenberg at 2013-06-21T14:08:25+01:00 Updates to reflect changes in HsDecls to support closed type families. - - - - - 7fd347ec by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 53ed81b6 by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 931c4f4f by Richard Eisenberg at 2013-07-24T13:15:59+01:00 Remove (error "synifyKind") to use WithinType, to allow haddock to process base. - - - - - 55a9c804 by Richard Eisenberg at 2013-08-02T15:54:55+01:00 Changes to reflect changes in GHC's type HsTyVarBndr - - - - - b6e9226c by Mathieu Boespflug at 2013-08-04T10:39:43-07:00 Output Copright and License keys in Xhtml backend. This information is as relevant in the documentation as it is in the source files themselves. Signed-off-by: David Waern <david.waern at gmail.com> - - - - - 4c66028a by David Waern at 2013-08-04T15:27:36-07:00 Bump interface file version. - - - - - 67340163 by David Waern at 2013-08-09T16:12:51-07:00 Update tests. - - - - - 2087569b by Mateusz Kowalczyk at 2013-08-25T09:24:13+02:00 Add spec tests. This adds tests for all elements we can create during regular parsing. This also adds tests for text with unicode in it. - - - - - 97f36a11 by Mateusz Kowalczyk at 2013-08-27T06:59:12+01:00 Fix ticket haskell/haddock#247. I do the same thing that the XHTML backend does: give these no special treatment and just act as if they are regular functions. - - - - - 60681b4f by Mateusz Kowalczyk at 2013-08-27T21:22:48+02:00 LaTeX tests setup - - - - - fa4c27b2 by Mateusz Kowalczyk at 2013-09-02T23:21:43+01:00 Fixes haskell/haddock#253 - - - - - 1a202490 by Mateusz Kowalczyk at 2013-09-03T01:12:50+01:00 Use Hspec instead of nanospec This is motivated by the fact that Haddock tests are not ran by the GHC's ‘validate’ script so we're pretty liberal on dependencies in that area. Full Hspec gives us some nice features such as Quickcheck integration. - - - - - 8cde3b20 by David Luposchainsky at 2013-09-08T07:27:28-05:00 Fix AMP warnings Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - d10661f2 by Herbert Valerio Riedel at 2013-09-11T15:15:01+02:00 Update Git repo URL in `.cabal` file - - - - - 16a44eb5 by Richard Eisenberg at 2013-09-17T09:34:26-04:00 Revision to reflect new role annotation syntax in GHC. - - - - - 4b9833b9 by Herbert Valerio Riedel at 2013-09-18T10:15:28+02:00 Add missing `traverse` method for `GenLocated` As `Traversable` needs at least one of `traverse` or `sequenceA` to be overridden. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - b71fed5d by Simon Hengel at 2013-09-18T22:43:34+02:00 Add test helper - - - - - 4fc1ea86 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#231 - - - - - 435872f6 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#256 We inject -dynamic-too into flags before we run all our actions in the GHC monad. - - - - - b8b24abb by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Add new field to DynFlags - - - - - 49558795 by Simon Hengel at 2013-09-18T22:43:35+02:00 Fallback to ./resources when Cabal data is not found (so that themes are found during development) - - - - - bf79d05c by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Fixes haskell/haddock#5 - - - - - e1baebc2 by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Print missing documentation. Fixes haskell/haddock#258. - - - - - 02ea74de by Austin Seipp at 2013-10-09T10:52:22-05:00 Don't consider StaticFlags when parsing arguments. Instead, discard any static flags before parsing the command line using GHC's DynFlags parser. See http://ghc.haskell.org/trac/ghc/ticket/8276 Based off a patch from Simon Hengel. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 704fd5bb by Simon Hengel at 2013-11-09T00:15:13+01:00 Update HTML tests - - - - - f9fed49e by Simon Hengel at 2013-11-10T18:43:58+01:00 Bump version - - - - - 97ae1999 by Simon Peyton Jones at 2013-11-25T17:25:14+00:00 Track changes in HsSpliceTy data constructor - - - - - 59ad8268 by Simon Peyton Jones at 2014-01-10T18:17:43+00:00 Adapt to small change in Pretty's exports - - - - - 8b12e6aa by Simon Hengel at 2014-01-12T14:48:35-06:00 Some code simplification by using traverse - - - - - fc5ea9a2 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix warnings in test helper - - - - - 6dbb3ba5 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Add ByteString version of Attoparsec - - - - - 968d7774 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 One pass parser and tests. We remove the HTML test as it is no longer necessary. We cover the test case in spec tests and other HTML tests but keeping this around fails: this is because the new parser has different semantics there. In fact, I suspect the original behaviour was a bug that wasn't caught/fixed but simply included as-is during the testing. - - - - - 37a07c9c by Simon Hengel at 2014-01-12T14:48:35-06:00 Rename Haddock.ParseSpec to Haddock.ParserSpec - - - - - f0f68fe9 by Simon Hengel at 2014-01-12T14:48:35-06:00 Don't append newline to parseString input We also check that we have parsed everything with endOfInput. - - - - - 95d60093 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix totality, unicode, examples, paragraph parsing Also simplify specs and parsers while we're at it. Some parsers were made more generic. This commit is a part of GHC pre-merge squash, email fuuzetsu at fuuzetsu.co.uk if you need the full commit history. - - - - - 7d99108c by Simon Hengel at 2014-01-12T14:48:35-06:00 Update acceptance tests - - - - - d1b59640 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Support for bold. Conflicts: src/Haddock/Backends/Hoogle.hs src/Haddock/Interface/Rename.hs src/Haddock/Parser.hs - - - - - 4b412b39 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Allow for headings inside function documentation. LaTeX will treat the h3-h6 headings the same as we'd have to hack the style file heavily otherwise and it would make the headings tiny anyway. Hoogle upstream said they will put in the functionality on their end. Conflicts: src/Haddock/Interface/Rename.hs src/Haddock/Types.hs test/Haddock/ParserSpec.hs - - - - - fdcca428 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Per-module extension flags and language listing. Any extensions that are not enabled by a used language (Haskell2010 &c) will be shown. Furthermore, any implicitly enabled are also going to be shown. While we could eliminate this either by using the GHC API or a dirty hack, I opted not to: if a user doesn't want the implied flags to show, they are recommended to use enable extensions more carefully or individually. Perhaps this will encourage users to not enable the most powerful flags needlessly. Enabled with show-extensions. Conflicts: src/Haddock/InterfaceFile.hs - - - - - 368942a2 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Bump interface version There were some breaking changes over the last few patches so we bump the interface version. This causes a big problem with testing: 1. To generate cross package docs, we first need to generate docs for the package used. 2. To generate package docs with new interface version, we need to use Haddock which has the version bumped. 3. To get Haddock with the version bump, we first need to test cross package docs 4. GOTO 1 So the problem is the chicken and the egg problem. It seems that the only solution would be to generate some interface files on the fly but it is non-trivial. To run this test, you'll have to: * build Haddock without the test (make sure everything else passes) * rebuild the packages used in the test with your shiny new binary making sure they are visible to Haddock * remove the ‘_hidden’ suffix and re-run the tests Note: because the packages currently used for this test are those provided by GHC, it's probably non-trivial to just re-build them. Preferably something less tedious to rebuild should be used and something that is not subject to change. - - - - - 124ae7a9 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow for nesting of paragraphs under lists. The nesting rules are similar to Markdown's with the exception that we can not simply indent the first line of a hard wrapped indented paragraph and have it treated as if it was fully indented. The reason is differences in markup as some of our constructs care about whitespace while others just swallow everything up so it's just a lot easier to not bother with it rather than making arbitrary rules. Note that we now drop trailing for string entities inside of lists. They weren't needed and it makes the output look uniform whether we use a single or double newline between list elements. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - c7913535 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow escaping in URLs and pictures. Some tests were moved under parseString as they weren't about paragraph level markup. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - 32326680 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update documentation. - - - - - fbef6406 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update maintainer - - - - - b40e82f4 by Mateusz Kowalczyk at 2014-01-13T02:39:25-06:00 Fixes haskell/haddock#271 Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - f4eafbf8 by Gergő Érdi at 2014-01-19T15:35:16-06:00 Support for -XPatternSynonyms Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - a8939591 by Austin Seipp at 2014-01-29T08:09:04-06:00 Update CPP check for __GLASGOW_HASKELL__ Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 30d7e9d5 by Gergő Érdi at 2014-01-31T00:15:01+08:00 <+>: Don't insert a space when concatenating empty nodes - - - - - a25ccd4d by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Fix @ code blocks In cases where we had some horizontal space before the closing ‘@’, the parser would not accept the block as a code block and we'd get ugly output. - - - - - 0f67305a by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Update tests This updates tests due to Haddock Trac haskell/haddock#271 fix and due to removal of TypeHoles as an extension from GHC. - - - - - 157322a7 by Gergő Érdi at 2014-01-31T01:03:17+08:00 Handle infix vs prefix names correctly everywhere, by explicitly specifying the context The basic idea is that "a" and "+" are either pretty-printed as "a" and "(+)" or "`a`" and "+" - - - - - aa6d9685 by Mateusz Kowalczyk at 2014-01-30T17:21:50+00:00 Correct whitespace in ‘hidden’ test for <+> change - - - - - 121872f0 by Mateusz Kowalczyk at 2014-02-09T17:59:12+00:00 Document module header. Fixes Haddock Trac haskell/haddock#270. - - - - - e3253746 by Mateusz Kowalczyk at 2014-02-10T21:37:48+00:00 Insert a space between module link and description Fixes Haddock Trac haskell/haddock#277. - - - - - 771d2384 by Mateusz Kowalczyk at 2014-02-10T23:27:21+00:00 Ensure a space between type signature and ‘Source’ This is briefly related to Haddock Trac haskell/haddock#249 and employs effectively the suggested fix _but_ it doesn't actually fix the reported issue. This commit simply makes copying the full line a bit less of a pain. - - - - - 8cda9eff by nand at 2014-02-11T15:48:30+00:00 Add support for type/data families This adds support for type/data families with their respective instances, as well as closed type families and associated type/data families. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 3f22c510 by nand at 2014-02-11T15:53:50+00:00 Improve display of poly-kinded type operators This now displays them as (==) k a b c ... to mirror GHC's behavior, instead of the old (k == a) b c ... which was just wrong. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - effb2d6b by nand at 2014-02-11T15:56:50+00:00 Add test case for PatternSynonyms This just tests various stuff including poly-kinded patterns and operator patterns to make sure the rendering isn't broken. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - b38faf0d by Niklas Haas at 2014-02-13T21:53:32+00:00 Get rid of re-implementation of sortBy I have no idea what this was doing lying around here, and due to the usage of tuples it's actually slower, too. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - ac1e0413 by Mateusz Kowalczyk at 2014-02-13T23:57:16+00:00 Only warn about missing docs when docs are missing This fixes the ‘Missing documentation for…’ message for modules with 100% coverage. - - - - - cae2e36a by Niklas Haas at 2014-02-15T21:56:18+00:00 Add test case for inter-module type/data family instances These should show up in every place where the class is visible, and indeed they do right now. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 8bea5c3a by Mateusz Kowalczyk at 2014-02-19T05:11:34+00:00 Use a bespoke data type to indicate fixity This deals with what I imagine was an ancient TODO and makes it much clearer what the argument actually does rather than having the user chase down the comment. - - - - - 5b52d57c by Niklas Haas at 2014-02-22T21:31:03+01:00 Strip a single leading space from bird tracks (#201) This makes bird tracks in the form > foo > bar > bat parse as if they had been written as >foo >bar >bat ie. without the leading whitespace in front of every line. Ideally we also want to look into how leading whitespace affects code blocks written using the @ @ syntax, which are currently unaffected by this patch. - - - - - 5a1315a5 by Simon Hengel at 2014-02-22T21:55:35+01:00 Turn a source code comment into specs - - - - - 784cfe58 by Mateusz Kowalczyk at 2014-02-23T05:02:22+00:00 Update test case for lifted GADT type rendering The parsing of these seems to have been fixed by GHC folk and it now renders differently. IMHO it now renders in a better way so I'm updating the test to reflect this. - - - - - c3c88c2f by Mateusz Kowalczyk at 2014-02-23T06:37:14+00:00 Don't shadow ‘strip’. -Wall complains - - - - - 293031d8 by Niklas Haas at 2014-02-23T15:21:52+01:00 Make ImplicitParams render correctly (#260) This introduces a new precedence level for single contexts (because implicit param contexts always need parens around them, but other types of contexts don't necessarily, even when alone) - - - - - 4200842d by Niklas Haas at 2014-02-23T15:37:13+01:00 Lower precedence of equality constraints This drops them to the new precedence pREC_CTX, which makes single eqaulity constraints show up as (a ~ b) => ty, in line with GHC's rendering. Additional tests added to make sure other type operators render as intended. Current behavior matches GHC - - - - - b59e3227 by Niklas Haas at 2014-02-23T16:11:22+01:00 Add RankNTypes test case to ImplicitParams.hs This test actually tests what haskell/haddock#260 originally reported - I omitted the RankNTypes scenario from the original fix because I realized it's not relevant to the underlying issue and indeed, this renders as intended now. Still good to have more tests. - - - - - c373dbf7 by Mateusz Kowalczyk at 2014-02-24T06:09:54+00:00 Fix rendering of Contents when links are present Fixes Haddock Trac haskell/haddock#267. - - - - - 9ecb0e56 by Mateusz Kowalczyk at 2014-02-24T06:26:50+00:00 Fix wording in the docs - - - - - 4f4dcd8e by Mateusz Kowalczyk at 2014-02-27T03:00:33+00:00 Change rendering of duplicate record field docs See Haddock Trac haskell/haddock#195. We now change this behaviour to only rendering the documentation attached to the first instance of a duplicate field. Perhaps we could improve this by rendering the first instance that has documentation attached to it but for now, we'll stick with this. - - - - - ad8aa609 by Niklas Haas at 2014-03-08T09:43:26+01:00 Render fixity information Affects functions, type synonyms, type families, class names, data type names, constructors, data families, associated TFs/DFs, type synonyms, pattern synonyms and everything else I could think of. - - - - - 6a39c917 by Niklas Haas at 2014-03-09T07:43:39+01:00 Reorder topDeclElem to move the source/wiki links to the top They appear in the same position due to the float: right attribute but now they're always at the top of the box instead of at the bottom. - - - - - 2d34b3b4 by Niklas Haas at 2014-03-09T07:53:46+01:00 Use optLast instead of listToMaybe for sourceUrls/wikiUrls This lets you override them using eg. cabal haddock --haddock-options, which can come in handy if you want to use a different layout or URL for your source code links than cabal-install generates. - - - - - 0eff4624 by Niklas Haas at 2014-03-09T07:53:46+01:00 Differentiate between TH splices (line-links) and regular names This adds a new type of source code link, to a specific line rather than a specific declaration/name - this is used to link to the location of a TH splice that defines a certain name. Rather hefty changes throughout and still one unresolved issue (the line URLs aren't parsed from the third form of --read-interface which means they're currently restricted to same-interface links). Not sure if this issue is really worth all the hassle, especially since we could just use line links in general. This commit also contains some cleanup/clarification of the types in Haddock.Backends.Xhtml.Decl and shortens some overlong lines in the process. Notably, the Bool parameter was replaced by a Unicode type synonym to help clarify its presence in type signatures. - - - - - 66d6f77b by Niklas Haas at 2014-03-09T20:02:43+01:00 Group similar fixities together Identical fixities declared for the same line should now render using syntax like: infix 4 <, >=, >, <= - - - - - 6587f9f5 by Mateusz Kowalczyk at 2014-03-10T04:24:18+00:00 Update changelog - - - - - 7387ddad by Niklas Haas at 2014-03-11T10:26:04+01:00 Include fixity information in the Interface file This resolves fixity information not appearing across package borders. The binary file version has been increased accordingly. - - - - - ab46ef44 by Niklas Haas at 2014-03-11T10:26:04+01:00 Update changelog - - - - - 565cab6f by Niklas Haas at 2014-03-11T10:26:04+01:00 Update appearance of fixity annotations This moves them in-line with their corresponding lines, similar to a presentation envision by @hvr and described in #ghc. Redundant operator names are also omitted when no ambiguity is present. - - - - - 5d7afd67 by Niklas Haas at 2014-03-11T10:26:05+01:00 Filter family instances of hidden types Currently, this check does not extend to hidden right hand sides, although it probably should hide them in that case. - - - - - ec291b0c by Niklas Haas at 2014-03-11T10:26:05+01:00 Add documentation for --source-entity-line - - - - - 0922e581 by Niklas Haas at 2014-03-11T10:37:32+01:00 Revert "Reorder topDeclElem to move the source/wiki links to the top" This reverts commit 843c42c4179526a2ad3526e4c7d38cbf4d50001d. This change is no longer needed with the new rendering style, and it messes with copy/pasting lines. - - - - - 30618e8b by Mateusz Kowalczyk at 2014-03-11T09:41:07+00:00 Bump version to 2.15.0 - - - - - adf3f1bb by Mateusz Kowalczyk at 2014-03-11T09:41:09+00:00 Fix up some whitespace - - - - - 8905f57d by Niklas Haas at 2014-03-13T19:18:06+00:00 Hide RHS of TFs with non-exported right hand sides Not sure what to do about data families yet, since technically it would not make a lot of sense to display constructors that cannot be used by the user. - - - - - 5c44d5c2 by Niklas Haas at 2014-03-13T19:18:08+00:00 Add UnicodeSyntax alternatives for * and -> I could not find a cleaner way to do this other than checking for string equality with the given built-in types. But seeing as it's actually equivalent to string rewriting in GHC's implementation of UnicodeSyntax, it's probably fitting. - - - - - b04a63e6 by Niklas Haas at 2014-03-13T19:18:10+00:00 Display minimal complete definitions for type classes This corresponds to the new {-# MINIMAL #-} pragma present in GHC 7.8+. I also cleaned up some of the places in which ExportDecl is used to make adding fields easier in the future. Lots of test cases have been updated since they now render with minimality information. - - - - - a4a20b16 by Niklas Haas at 2014-03-13T19:18:12+00:00 Strip links from recently added html tests These were accidentally left there when the tests were originally added - - - - - d624f315 by Mateusz Kowalczyk at 2014-03-13T19:19:31+00:00 Update changelog - - - - - d27a21ac by Mateusz Kowalczyk at 2014-03-13T21:19:07+00:00 Always read in prologue files as UTF8 (#286). - - - - - 54b2fd78 by Mateusz Kowalczyk at 2014-03-13T21:28:09+00:00 Style only - - - - - fa4fe650 by Simon Hengel at 2014-03-15T09:04:18+01:00 Add Fuuzetsu maintainers field in cabal file - - - - - f83484b7 by Niklas Haas at 2014-03-15T18:20:24+00:00 Hide minimal definition for only-method classes Previously this was not covered by the All xs check since here it is not actually an All, rather a single Var n. This also adds the previously missing html-test/src/Minimal.hs. - - - - - 0099d276 by Niklas Haas at 2014-03-15T18:20:26+00:00 Fix issue haskell/haddock#281 This is a regression from the data family instances change. Data instances are now distinguished from regular lists by usage of the new class "inst", and the style has been updated to only apply to those. I've also updated the appropriate test case to test this a bit better, including GADT instances with GADT-style records. - - - - - 1f9687bd by Mateusz Kowalczyk at 2014-03-21T17:48:37+00:00 Please cabal sdist - - - - - 75542693 by Mateusz Kowalczyk at 2014-03-22T16:36:16+00:00 Drop needless --split-objs which slows us down. Involves tiny cleanup of all the dynflag bindings. Fixes haskell/haddock#292. - - - - - 31214dc3 by Herbert Valerio Riedel at 2014-03-23T18:01:01+01:00 Fix a few typos Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 0b73e638 by Mateusz Kowalczyk at 2014-03-31T05:34:36+01:00 Print kind signatures on GADTs - - - - - 2bab42f3 by Mateusz Kowalczyk at 2014-03-31T16:53:25+01:00 Add default for new PlatformConstraints field - - - - - 42647c5f by Mateusz Kowalczyk at 2014-03-31T18:29:04+01:00 Drop leading whitespace in @-style blocks. Fixes haskell/haddock#201. - - - - - 98208294 by Niklas Haas at 2014-03-31T20:09:58+02:00 Crash when exporting record selectors of data family instances This fixes bug haskell/haddock#294. This also fixes a related but never-before-mentioned bug about the display of GADT record selectors with non-polymorphic type signatures. Note: Associated data type constructors fail to show up if nothing is exported that they could be attached to. Exporting any of the data types in the instance head, or the class + data family itself, causes them to show up, but in the absence of either of these, exporting just the associated data type with the constructor itself will result in it being hidden. The only scenario I can come up that would involve this kind of situation involved OverlappingInstances, and even then it can be mitigated by just exporting the class itself, so I'm not going to solve it since the logic would most likely be very complicated. - - - - - 3832d171 by Mateusz Kowalczyk at 2014-04-01T19:07:33+01:00 Make CHANGES consistent with what's now in 2.14.2 - - - - - c386ae89 by Mateusz Kowalczyk at 2014-04-01T19:18:36+01:00 Actually bundle extra spec tests in sdist - - - - - bd57a6d3 by Mateusz Kowalczyk at 2014-04-03T21:13:48+01:00 Update test cases for GHC bug haskell/haddock#8945, Haddock haskell/haddock#188 The order of signature groups has been corrected upstream. Here we add a test case and update some existing test-cases to reflect this change. We remove grouped signature in test cases that we can (Minimal, BugDeprecated &c) so that the test is as self-contained as possible. - - - - - 708b88b1 by Mateusz Kowalczyk at 2014-04-03T21:16:07+01:00 Enforce strict GHC version in cabal file This stops people with 7.6.3 trying to install 2.15.x which clearly won't work. Unfortunately we shipped 2.14.x without realising this. - - - - - 60334f7c by Mateusz Kowalczyk at 2014-04-03T21:19:24+01:00 Initialise some new PlatformConstants fields - - - - - ea77f668 by Mateusz Kowalczyk at 2014-04-11T16:52:23+01:00 We don't actually want unicode here - - - - - 0b651cae by Mateusz Kowalczyk at 2014-04-11T18:13:30+01:00 Parse identifiers with ^ and ⋆ in them. Fixes haskell/haddock#298. - - - - - e8ad0f5f by Mateusz Kowalczyk at 2014-04-11T18:47:41+01:00 Ignore version string during HTML tests. - - - - - de489089 by Mateusz Kowalczyk at 2014-04-11T18:59:30+01:00 Update CHANGES to follow 2.14.3 - - - - - beb464a9 by Gergő Érdi at 2014-04-13T16:31:10+08:00 remove Origin flag from LHsBindsLR - - - - - cb16f07c by Herbert Valerio Riedel at 2014-04-21T17:16:50+02:00 Replace local `die` by new `System.Exit.die` Starting with GHC 7.10, System.Exit exports the new `die` which is essentially the same as Haddock.Util.die, so this commit changes Haddock.Util.die to be a simple re-export of System.Exit.die. See also https://ghc.haskell.org/trac/ghc/ticket/9016 for more details. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 9b9b23c7 by Mateusz Kowalczyk at 2014-05-03T15:40:11+02:00 Disambiguate ‘die’ in test runners. - - - - - 5d28a2b8 by Mateusz Kowalczyk at 2014-05-05T09:19:49+02:00 Prepare modules for parser split. We have to generalise the Doc (now DocH) slightly to remove the dependency on GHC-supplied type. - - - - - d3967ff3 by Mateusz Kowalczyk at 2014-05-05T11:00:41+02:00 Move parser + parser tests out to own package. We move some types out that are necessary as well and then re-export and specialise them in the core Haddock. Reason for moving out spec tests is that if we're working on the parser, we can simply work on that and we can ignore the rest of Haddock. The downside is that it's a little inconvenient if at the end of the day we want to see that everything passes. - - - - - 522a448d by Mateusz Kowalczyk at 2014-05-05T11:14:47+02:00 Move out Show and Eq instances to Types They are much more useful to the users here. - - - - - 11a6f0f2 by Mateusz Kowalczyk at 2014-05-06T13:50:31+02:00 Remove no longer necessary parser error handling. We can now drop some Maybe tests and even lets us strip an error handling monad away in a few places. - - - - - 6992c924 by Mateusz Kowalczyk at 2014-05-14T02:23:55+02:00 Please the GHC build-system. As I can not figure out how to do this properly, if we're in GHC tree, we treat the library as being the same package. If we're not in the tree, we require that the library be installed separately. - - - - - 7a8ad763 by Mateusz Kowalczyk at 2014-05-14T14:50:25+02:00 Update issue tracker URL - - - - - f616c521 by Mateusz Kowalczyk at 2014-05-14T14:53:32+02:00 Update issue tracker URL for haddock-library - - - - - 66580ded by Gergő Érdi at 2014-05-25T14:24:16+08:00 Accomodate change in PatSyn representation - - - - - 0e43b988 by Mateusz Kowalczyk at 2014-05-29T03:15:29+02:00 Revert "Accomodate change in PatSyn representation" This reverts commit 57aa591362d7c8ba21285fccd6a958629a422091. I am reverting this because I pushed it to master when it was meant to stay on a wip-branch. Sorry Gergo and everyone who had trouble due to this. - - - - - e10d7ec8 by Mateusz Kowalczyk at 2014-05-29T03:24:11+02:00 Revert "Revert "Accomodate change in PatSyn representation"" This reverts commit e110e6e70e40eed06c06676fd2e62578da01d295. Apparently as per GHC commit ac2796e6ddbd54c5762c53e2fcf29f20ea162fd5 this was actually intended. Embarrasing for me. - - - - - 5861aca9 by Mateusz Kowalczyk at 2014-06-05T19:49:27+02:00 Clear up highlighting of identifiers with ‘'’s. - - - - - d7cc420f by Simon Peyton Jones at 2014-06-06T12:41:09+01:00 Follow change in patSynSig - - - - - 938b4fd8 by Mateusz Kowalczyk at 2014-06-12T07:24:29+02:00 Slightly update the readme. Style-sheets are no longer a recent thing, dead links, old maintainers, different formats. - - - - - c7799dea by Mateusz Kowalczyk at 2014-06-18T00:05:56+02:00 Update cabal files Update repository urls, use subdir property for haddock-library and use a separate versioning scheme for haddock-library in preparation for release. - - - - - a2750b6a by Simon Hengel at 2014-06-18T11:01:18+08:00 Compatibility with older versions of base and bytestring - - - - - 009b4b03 by Simon Hengel at 2014-06-18T11:14:01+08:00 Enable travis-ci for haddock-library - - - - - 9b5862eb by Simon Hengel at 2014-06-18T11:14:01+08:00 haddock-library: Do not depend on haddock-library in test suite I think you either add src to hs-source-dirs or the library to build-depends. But doing both does not make sense (AFAICT). - - - - - fb1f3279 by Simon Hengel at 2014-06-18T11:49:05+08:00 haddock-library: Use -Wall for specs - - - - - 649340e1 by Mateusz Kowalczyk at 2014-06-18T06:58:54+02:00 Use Travis with multiple GHC versions When using HEAD, we build haddock-library directly from repository as a dependency (and thanks to --enable-tests, the tests get ran anyway). In all other cases, we manually run the tests on haddock-library only and don't test the main project. - - - - - d7eeeec2 by Mateusz Kowalczyk at 2014-06-18T07:49:04+02:00 Comment improvements + few words in cabal file - - - - - 0f8db914 by Simon Hengel at 2014-06-18T13:52:23+08:00 Use doctest to check examples in documentation - - - - - 2888a8dc by Simon Hengel at 2014-06-18T14:16:48+08:00 Remove doctest dependency (so that we can use haddock-library with doctest) - - - - - 626d5e85 by Mateusz Kowalczyk at 2014-06-18T08:41:25+02:00 Travis tweaks - - - - - 41d4f9cc by Mateusz Kowalczyk at 2014-06-18T08:58:43+02:00 Don't actually forget to install specified GHC. - - - - - c6aa512a by John MacFarlane at 2014-06-18T10:43:57-07:00 Removed reliance on LambdaCase (which breaks build with ghc 7.4). - - - - - b9b93b6f by John MacFarlane at 2014-06-18T10:54:56-07:00 Fixed haddock warnings. - - - - - a41b0ab5 by Mateusz Kowalczyk at 2014-06-19T01:20:10+02:00 Update Travis, bump version - - - - - 864bf62a by Mateusz Kowalczyk at 2014-06-25T10:36:54+02:00 Fix anchors. Closes haskell/haddock#308. - - - - - 53df91bb by Mateusz Kowalczyk at 2014-06-25T15:04:49+02:00 Drop DocParagraph from front of headers I can not remember why they were wrapped in paragraphs to begin with and it seems unnecessary now that I test it. Closes haskell/haddock#307. - - - - - 29b5f2fa by Mateusz Kowalczyk at 2014-06-25T15:17:20+02:00 Don't mangle append order for nested lists. The benefit of this is that the ‘top-level’ element of such lists is properly wrapped in <p> tags so any CSS working with these will be applied properly. It also just makes more sense. Pointed out at jgm/pandoc#1346. - - - - - 05cb6e9c by Mateusz Kowalczyk at 2014-06-25T15:19:45+02:00 Bump haddock-library to 1.1.0 for release - - - - - 70feab15 by Iavor Diatchki at 2014-07-01T03:37:07-07:00 Propagate overloading-mode for instance declarations in haddock (#9242) - - - - - d4ca34a7 by Simon Peyton Jones at 2014-07-14T16:23:15+01:00 Adapt to new definition of HsDecls.TyFamEqn This is a knock-on from the refactoring from Trac haskell/haddock#9063. I'll push the corresponding changes to GHC shortly. - - - - - f91e2276 by Edward Z. Yang at 2014-07-21T08:14:19-07:00 Track GHC PackageId to PackageKey renaming. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - b010f9ef by Edward Z. Yang at 2014-07-25T16:28:46-07:00 Track changes for module reexports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - 8b85f9f9 by Mateusz Kowalczyk at 2014-07-28T13:25:43+02:00 Catch mid-line URLs. Fixes haskell/haddock#314. - - - - - 4c613a78 by Edward Z. Yang at 2014-08-05T03:11:00-07:00 Track type signature change of lookupModuleInAllPackages Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - e80b051c by Edward Z. Yang at 2014-08-05T17:34:26+01:00 If GhcProfiled, also build Haddock profiled. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f9cccd29 by Edward Z. Yang at 2014-08-07T14:23:35+01:00 Ignore TAGS files. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 00b3af52 by Mateusz Kowalczyk at 2014-08-08T04:58:19+02:00 Update to attoparsec-0.12.1.1 There seems to be memory and speed improvement. - - - - - 5457dc71 by Mateusz Kowalczyk at 2014-08-08T18:24:02+02:00 Fix forgotten src - - - - - 3520cb04 by Mateusz Kowalczyk at 2014-08-14T20:19:07+01:00 Bump down the version for master to 2.14.4 - - - - - dc98c21b by Mateusz Kowalczyk at 2014-08-14T20:23:27+01:00 Revert "Track type signature change of lookupModuleInAllPackages" This reverts commit d59fec2c9551b5662a3507c0011e32a09a9c118f. - - - - - 3f2038c0 by Mateusz Kowalczyk at 2014-08-14T20:23:31+01:00 Revert "Track changes for module reexports." This reverts commit b99b57c0df072d12b67816b45eca2a03cb1da96d. - - - - - 56d4e49e by Mateusz Kowalczyk at 2014-08-14T20:23:42+01:00 Revert "Track GHC PackageId to PackageKey renaming." This reverts commit 8ac42d3327473939c013551750425cac191ff0fd. - - - - - 726ea3cb by Mateusz Kowalczyk at 2014-08-14T20:23:47+01:00 Revert "Adapt to new definition of HsDecls.TyFamEqn" This reverts commit cb96b4f1ed0462b4a394b9fda6612c3bea9886bd. - - - - - 61a88ff0 by Mateusz Kowalczyk at 2014-08-14T20:23:52+01:00 Revert "Propagate overloading-mode for instance declarations in haddock (#9242)" This reverts commit 8d20ca8d5a9bee73252ff2035ec45f9c03d0820c. - - - - - a32ba674 by Mateusz Kowalczyk at 2014-08-14T20:26:03+01:00 Revert "Disambiguate ‘die’ in test runners." This reverts commit dba02d6df32534aac5d257f2d28596238d248942. - - - - - f335820f by Mateusz Kowalczyk at 2014-08-14T20:26:09+01:00 Revert "Replace local `die` by new `System.Exit.die`" This reverts commit 08aa509ebac58bfb202ea79c7c41291ec280a1c5. - - - - - 107078e4 by Mateusz Kowalczyk at 2014-08-14T20:27:34+01:00 Merge branch 'reverts' This reverts any changes that were made to have Haddock compile with 7.9. When 7.10 release comes, we can simply re-apply all the patches and any patches that occur on ghc-head branch from now on. This allows us to build master with 7.8.3 - - - - - b44b3871 by Mateusz Kowalczyk at 2014-08-15T02:47:40+01:00 Fix haskell/haddock#313 by doing some list munging. I get rid of the Monoid instance because we weren't satisfying the laws. Convenience of having <> didn't outweigh the shock-factor of having it behave badly. - - - - - e1a62cde by Mateusz Kowalczyk at 2014-08-15T02:52:56+01:00 Stop testing haskell/haddock#188. Because the change is in GHC 7.9 and we now work against 7.8.3, this test no longer makes sense. We revert it until 7.10 becomes the standard version. If anything, there should be a test for this in GHC itself. - - - - - 54e8286d by Mateusz Kowalczyk at 2014-08-15T05:31:57+01:00 Add haskell/haddock#313 to CHANGES - - - - - 9df7ad5d by Simon Hengel at 2014-08-20T11:25:32+08:00 Fix warning - - - - - ee2574d6 by Simon Hengel at 2014-08-20T12:07:01+08:00 Fix travis builds - - - - - 384cf2e6 by Simon Hengel at 2014-08-20T12:14:31+08:00 Require GHC 7.8.3 - - - - - d4779863 by Simon Hengel at 2014-08-22T12:14:16+08:00 Move Haddock API to a separate package - - - - - 80f3e0e1 by Simon Hengel at 2014-08-22T14:57:38+08:00 Bump version to 2.15.0 and add version constraints - - - - - 309a94ce by Simon Hengel at 2014-08-22T15:18:06+08:00 Add deprecated compatibility module - - - - - 4d1e4e3f by Luite Stegeman at 2014-08-22T20:46:45+02:00 export things to allow customizing how the Ghc session is run - - - - - 47884591 by Luite Stegeman at 2014-08-22T20:46:51+02:00 ghc 7.8.2 compatibility - - - - - 5ea94e2c by Luite Stegeman at 2014-08-22T22:08:58+02:00 install dependencies for haddock-api on travis - - - - - 9fb845b2 by Mateusz Kowalczyk at 2014-08-23T10:09:34+01:00 Move sources under haddock-api/src - - - - - 85817dc4 by Mateusz Kowalczyk at 2014-08-23T10:10:48+01:00 Remove compat stuff - - - - - 151c6169 by Niklas Haas at 2014-08-24T08:14:10+02:00 Fix extra whitespace on signatures and update all test cases This was long overdue, now running ./accept.lhs on a clean test from master will not generate a bunch of changes. - - - - - d320e0d2 by Niklas Haas at 2014-08-24T08:14:35+02:00 Omit unnecessary foralls and fix haskell/haddock#315 This also fixes haskell/haddock#86. - - - - - bdafe108 by Mateusz Kowalczyk at 2014-08-24T15:06:46+01:00 Update CHANGES - - - - - fafa6d6e by Mateusz Kowalczyk at 2014-08-24T15:14:23+01:00 Delete few unused/irrelevant/badly-place files. - - - - - 3634923d by Duncan Coutts at 2014-08-27T13:49:31+01:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. - - - - - 539a7e70 by Herbert Valerio Riedel at 2014-08-31T11:36:32+02:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 9e3a0e5b by Mateusz Kowalczyk at 2014-08-31T12:54:43+01:00 Bump version in doc - - - - - 4a177525 by Mateusz Kowalczyk at 2014-08-31T13:01:23+01:00 Bump haddock-library version - - - - - f99c1384 by Mateusz Kowalczyk at 2014-08-31T13:05:25+01:00 Remove references to deleted files - - - - - 5e51a247 by Mateusz Kowalczyk at 2014-08-31T14:18:44+01:00 Make the doc parser not complain - - - - - 2cedb49a by Mateusz Kowalczyk at 2014-09-03T03:33:15+01:00 CONTRIBUTING file for issues - - - - - 88027143 by Mateusz Kowalczyk at 2014-09-04T00:46:59+01:00 Mention --print-missing-docs - - - - - 42f6754f by Alan Zimmerman at 2014-09-05T18:13:24-05:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e712719e by Austin Seipp at 2014-09-09T01:03:27-05:00 Fix import of 'empty' due to AMP. Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 71c29755 by Herbert Valerio Riedel at 2014-09-09T17:35:20+02:00 Bump `base` constraint for AMP - - - - - 0bf9f3ed by Mateusz Kowalczyk at 2014-09-12T19:18:32+01:00 Delete stale ANNOUNCE - - - - - cac89ee6 by Krzysztof Gogolewski at 2014-09-14T17:17:09+02:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 4d683426 by Edward Z. Yang at 2014-09-18T13:38:11-07:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 80697fd5 by Herbert Valerio Riedel at 2014-09-19T00:07:52+02:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. - - - - - c015eb70 by Herbert Valerio Riedel at 2014-09-19T00:10:36+02:00 Revert "Followup changes to addition of -fwarn-context-quantification" This reverts commit 4023817d7c0e46db012ba2eea28022626841ca9b temporarily as the respective feature hasn't landed in GHC HEAD yet, but this commit blocks later commits from being referenced in GHC HEAD. - - - - - 38ded784 by Edward Z. Yang at 2014-09-18T15:32:15-07:00 Revert "Revert "Followup changes to addition of -fwarn-context-quantification"" This reverts commit db14fd8ab4fab43694139bc203808b814eafb2dc. It's in HEAD now. - - - - - f55d59c9 by Herbert Valerio Riedel at 2014-09-26T19:18:28+02:00 Revert "Fix import of 'empty' due to AMP." This reverts commit 0cc5bc85e9fca92ab712b68a2ba2c0dd9d3d79f4 since it turns out we don't need to re-export `empty` from Control.Monad after all. - - - - - 467050f1 by David Feuer at 2014-10-09T20:07:36-04:00 Fix improper lazy IO use Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. - - - - - cc47b699 by Edward Z. Yang at 2014-10-09T21:38:19-07:00 Fix use-after-close lazy IO bug Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. Signed-off-by: David Feuer <David.Feuer at gmail.com> Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 87babcbe by Austin Seipp at 2014-10-20T20:05:27-05:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - ab259516 by Austin Seipp at 2014-10-20T20:07:01-05:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - b918093c by Mateusz Kowalczyk at 2014-10-29T03:59:39+00:00 Experimental support for collapsable headers Closes haskell/haddock#335 - - - - - 849db129 by Mateusz Kowalczyk at 2014-10-29T10:07:26+01:00 Experimental support for collapsable headers (cherry picked from commit e2ed3b9d8dfab09f1b1861dbc8e74f08e137ebcc) - - - - - a4cc4789 by Herbert Valerio Riedel at 2014-10-31T11:08:26+01:00 Collapse user-defined section by default (re haskell/haddock#335) - - - - - 9da1b33e by Yuras Shumovich at 2014-10-31T16:11:04-05:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - c625aefc by Austin Seipp at 2014-10-31T19:34:10-05:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - c7738e5e by Simon Hengel at 2014-11-02T07:25:30+08:00 Remove -fobject-code from .ghci (this slows down reloads on modifications) - - - - - d4a86e95 by Simon Hengel at 2014-11-03T09:26:11+08:00 Get rid of StandaloneDeriving - - - - - a974e311 by Simon Hengel at 2014-11-03T09:26:11+08:00 Derive more instances - - - - - 8aa0c4d7 by Simon Hengel at 2014-11-03T09:27:08+08:00 Remove unused language extensions - - - - - 3052d46a by Simon Hengel at 2014-11-03T09:30:46+08:00 Minor refactoring - - - - - 4281d3cb by Simon Hengel at 2014-11-03T09:30:46+08:00 parser: Try to parse definition lists right before text paragraphs - - - - - 8ba12bf9 by Simon Hengel at 2014-11-03T09:34:19+08:00 Add support for markdown links (closes haskell/haddock#336) - - - - - a2f8d747 by Simon Hengel at 2014-11-03T09:34:19+08:00 Allow markdown links at the beginning of a paragraph - - - - - 53b11207 by Simon Hengel at 2014-11-03T09:34:20+08:00 Update documentation - - - - - 652267c6 by Simon Hengel at 2014-11-03T09:34:20+08:00 Add support for markdown images - - - - - 9d667502 by Simon Hengel at 2014-11-03T09:34:20+08:00 Allow an optional colon after the closing bracket of definition lists This is to disambiguate them from markdown links and will be require with a future release. - - - - - 8167fc32 by Mateusz Kowalczyk at 2014-11-04T01:16:51+00:00 whitespace only - - - - - 3da62981 by Mateusz Kowalczyk at 2014-11-04T01:17:31+00:00 Fix re-exports of built-in type families Fixes haskell/haddock#310 - - - - - edc76b34 by Mateusz Kowalczyk at 2014-11-04T02:54:28+00:00 Turn some uses of error into recoverable warnings This should at the very least not abort when something weird happens. It does feel like we should have a type that carries these errors until the end however as the user might not see them unless they are printed at the end. - - - - - 0a137400 by Mateusz Kowalczyk at 2014-11-04T04:09:44+00:00 Fix warnings - - - - - d068fc21 by Mateusz Kowalczyk at 2014-11-04T21:04:07+00:00 Fix parsing of identifiers written in infix way - - - - - 1a9f2f3d by Simon Hengel at 2014-11-08T11:32:42+08:00 Minor code simplification - - - - - 6475e9b1 by Simon Hengel at 2014-11-08T17:28:33+08:00 newtype-wrap parser monad - - - - - dc1ea105 by Herbert Valerio Riedel at 2014-11-15T11:55:43+01:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - fbb1aca4 by Simon Hengel at 2014-11-16T08:51:38+08:00 State intention rather than implementation details in Haddock comment - - - - - 97851ab2 by Simon Hengel at 2014-11-16T10:20:19+08:00 (wip) Add support for @since (closes haskell/haddock#26) - - - - - 34bcd18e by Gergő Érdi at 2014-11-20T22:35:38+08:00 Update Haddock to new pattern synonym type signature syntax - - - - - 304b7dc3 by Jan Stolarek at 2014-11-20T17:48:43+01:00 Follow changes from haskell/haddock#9812 - - - - - 920f9b03 by Richard Eisenberg at 2014-11-20T16:52:50-05:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 0bfe4e78 by Alan Zimmerman at 2014-11-21T11:23:09-06:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 356ed45a by Thomas Winant at 2014-11-28T16:11:22-06:00 Support for PartialTypeSignatures - - - - - 5dc8f3b1 by Gergő Érdi at 2014-11-29T15:39:09+08:00 For pattern synonyms, render "pattern" as a keyword - - - - - fe704480 by Mateusz Kowalczyk at 2014-12-09T03:38:32+00:00 List new module in cabal file - - - - - b9ad5a29 by Mateusz Kowalczyk at 2014-12-10T00:58:24+00:00 Allow the parser to spit out meta-info Currently we only use it only for ‘since’ annotations but with these patches it should be fairly simple to add new attributes if we wish to. Closes haskell/haddock#26. It seems to work fine but due to 7.10 rush I don't have the chance to do more exhaustive testing right now. The way the meta is output (emphasis at the end of the whole comment) is fairly arbitrary and subject to bikeshedding. Note that this makes test for Bug310 fail due to interface version bump: it can't find the docs for base with this interface version so it fails. There is not much we can do to help this because it tests for ’built-in’ identifier, not something we can provide ourselves. - - - - - 765af0e3 by Mateusz Kowalczyk at 2014-12-10T01:17:19+00:00 Update doctest parts of comments - - - - - 8670272b by jpmoresmau at 2014-12-10T01:35:31+00:00 header could contain several lines Closes haskell/haddock#348 - - - - - 4f9ae4f3 by Mateusz Kowalczyk at 2014-12-12T06:22:31+00:00 Revert "Merge branch 'reverts'" This reverts commit 5c93cc347773c7634321edd5f808d5b55b46301f, reversing changes made to 5b81a9e53894d2ae591ca0c6c96199632d39eb06. Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - e974ac94 by Duncan Coutts at 2014-12-12T06:26:11+00:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. Conflicts: haddock-api/src/Haddock.hs - - - - - 2f3a2365 by Herbert Valerio Riedel at 2014-12-12T06:26:51+00:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 1dbd6390 by Alan Zimmerman at 2014-12-12T06:32:07+00:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - bb6ff1f4 by Mateusz Kowalczyk at 2014-12-12T06:35:07+00:00 Bump ‘base’ constraint Follows the similar commit made on ghc-head branch - - - - - 466fe4ab by Krzysztof Gogolewski at 2014-12-12T06:37:42+00:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 97e080c9 by Edward Z. Yang at 2014-12-12T06:39:35+00:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: haddock-api/src/Haddock/ModuleTree.hs - - - - - 20b2af56 by Herbert Valerio Riedel at 2014-12-12T06:42:50+00:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. Conflicts: haddock-library/src/Documentation/Haddock/Parser.hs - - - - - b3ad269d by Austin Seipp at 2014-12-12T06:44:14+00:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 072df0dd by Austin Seipp at 2014-12-12T06:45:01+00:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - dbb9294a by Herbert Valerio Riedel at 2014-12-12T06:46:17+00:00 Collapse user-defined section by default (re haskell/haddock#335) Conflicts: haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs - - - - - f23ab545 by Yuras Shumovich at 2014-12-12T06:46:41+00:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - 753a4b67 by Austin Seipp at 2014-12-12T06:46:51+00:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8954e8f5 by Herbert Valerio Riedel at 2014-12-12T06:50:53+00:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - d2b06d61 by Gergő Érdi at 2014-12-12T07:07:30+00:00 Update Haddock to new pattern synonym type signature syntax Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 1ff02426 by Jan Stolarek at 2014-12-12T07:13:24+00:00 Follow changes from haskell/haddock#9812 Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - 06ad7600 by Richard Eisenberg at 2014-12-12T07:13:43+00:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 8fd2aa8b by Alan Zimmerman at 2014-12-12T07:22:25+00:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Backends/LaTeX.hs haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 95c3db98 by Thomas Winant at 2014-12-12T07:35:49+00:00 Support for PartialTypeSignatures Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs haddock-api/src/Haddock/Interface/Create.hs - - - - - 45494428 by Gergő Érdi at 2014-12-12T07:36:18+00:00 For pattern synonyms, render "pattern" as a keyword - - - - - a237e3eb by Mateusz Kowalczyk at 2014-12-12T12:27:13+00:00 Various fixups and bumps for next release - - - - - 22918bcd by Herbert Valerio Riedel at 2014-12-14T10:11:47+01:00 Remove redundant wild-card pattern match (this would otherwise cause a build-failure with `-Werror`) - - - - - 1d6ce947 by Herbert Valerio Riedel at 2014-12-14T10:17:06+01:00 Treat GHC 7.10 the same as GHC 7.9 ...since the current GHC 7.9 is going to become GHC 7.10 real-soon-now anyway - - - - - f434ea89 by Herbert Valerio Riedel at 2014-12-14T18:26:50+01:00 Fixup ghc.mk (follow-up to 1739375eb23342) This makes the GHC build-system aware of the data-files to be copied into the bindist (as haddock.cabal doesn't list those anymore) - - - - - 6fb839eb by Mateusz Kowalczyk at 2014-12-17T09:28:59+00:00 Only keep one Version instead of blindly appending - - - - - 40645489 by Mateusz Kowalczyk at 2014-12-18T07:09:44+00:00 Fix dependency version - - - - - 8b3b927b by Mateusz Kowalczyk at 2014-12-18T07:14:23+00:00 Print missing docs by default Adds --no-print-missing-docs - - - - - 59666694 by Mateusz Kowalczyk at 2014-12-18T07:21:37+00:00 update changelog - - - - - aa6d168e by Mateusz Kowalczyk at 2014-12-18T07:30:58+00:00 Update docs for @since - - - - - 2d7043ee by Luite Stegeman at 2014-12-19T18:29:35-06:00 hide projectVersion from DynFlags since it clashes with Haddock.Version.projectVersion - - - - - aaa70fc0 by Luite Stegeman at 2014-12-22T15:58:43+01:00 Add missing import for standalone haddock-api package - - - - - 9ce01269 by Herbert Valerio Riedel at 2014-12-22T17:48:45+01:00 Reset ghc-head with master's tree (this is an overwriting git merge of master into ghc-head) - - - - - fcd6fec1 by Herbert Valerio Riedel at 2014-12-22T17:51:52+01:00 Bump versions for ghc-7.11 - - - - - 525ec900 by Mateusz Kowalczyk at 2014-12-23T13:36:24+00:00 travis-ci: test with HEAD - - - - - cbf494b5 by Simon Peyton Jones at 2014-12-23T15:22:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 50e01c99 by Mateusz Kowalczyk at 2014-12-29T15:28:47+00:00 Make travis use 7.10.x - - - - - 475e60b0 by Njagi Mwaniki at 2014-12-29T15:30:44+00:00 Turn the README into GitHub Markdown format. Closes haskell/haddock#354 - - - - - 8cacf48e by Luite Stegeman at 2015-01-05T16:25:37+01:00 bump haddock-api ghc dependency to allow release candidate and first release - - - - - 6ed6cf1f by Simon Peyton Jones at 2015-01-06T16:37:47+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 8b484f33 by Simon Peyton Jones at 2015-01-08T15:50:22+00:00 Track naming change in DataCon - - - - - 23c5c0b5 by Alan Zimmerman at 2015-01-16T10:15:11-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e7a5532c by JP Moresmau at 2015-01-22T17:19:03+00:00 Ignore warnings, install Cabal 1.22 - - - - - 86942c84 by jpmoresmau at 2015-01-22T17:19:04+00:00 solve dataDir ambiguity - - - - - 5ceb743e by jpmoresmau at 2015-01-22T19:17:32+00:00 support GHC 7.10: no Safe-Inferred, Foldable instance - - - - - 6a3b3fb5 by Mateusz Kowalczyk at 2015-01-22T19:32:10+00:00 Update test files Test: a correct behaviour for fields comma-separating values. I'm surprised we had no bug open for this. Maybe it affects how haskell/haddock#301 renders now but I doubt. Operators: Seems GHC is giving us a new order for operators, something must have changed on their side again. cc @haasn , this makes the fixity to the side not match the order on the LHS which is a bit unpleasant. Maybe the fixity can be made to match the GHC order? Bug335: We expand examples by default now. Bug310: Now inferred safe. - - - - - 708f8b2f by jpmoresmau at 2015-01-22T19:36:59+00:00 Links to source location of class instance definitions - - - - - 5cf8a6da by Vincent Berthoux at 2015-01-22T19:59:58+00:00 Filter '\r' from comments due to Windows problems. On Windows this was causing newline to be rendered twice in code blocks. Closes haskell/haddock#359, fixes haskell/haddock#356. - - - - - 1749e6f0 by Mateusz Kowalczyk at 2015-01-22T20:31:27+00:00 Changelog only - - - - - c8145f90 by Mateusz Kowalczyk at 2015-01-22T23:34:05+00:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. - - - - - 14248254 by Mateusz Kowalczyk at 2015-01-22T23:43:18+00:00 Sort out some module import warnings - - - - - d8a38989 by Simon Peyton Jones at 2015-01-23T07:10:16-06:00 Track naming change in DataCon (cherry picked from commit 04cf63d0195837ed52075ed7d2676e71831e8a0b) - - - - - d3ac6ae4 by Alan Zimmerman at 2015-01-23T07:17:19-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit d61bbc75890e4eb0ad508b9c2a27b91f691213e6) - - - - - 4c1ffeb0 by Simon Peyton Jones at 2015-02-10T12:10:33+00:00 Track changes in HsSyn for quasi-quotes - - - - - 775d20f7 by Mateusz Kowalczyk at 2015-03-15T08:11:48+01:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. (cherry picked from commit 8e06728afb0784128ab2df0be7a5d7a191d30ff4) - - - - - f9245e72 by Phil Ruffwind at 2015-03-16T04:32:01-04:00 Prevent Synopsis from using up too much horizontal space When long type signatures occur in the Synopsis, the element is stretched beyond the width of the window. Scrollbars don't appear, so it's impossible to read anything when this happens. - - - - - cd8fa415 by Mateusz Kowalczyk at 2015-03-17T21:59:39+00:00 Update changelog Closes haskell/haddock#151 due to 71170fc77962f10d7d001e3b8bc8b92bfeda99bc - - - - - b5248b47 by Ben Gamari at 2015-03-25T17:12:17+00:00 Make the error encountered when a package can't be found more user-friendly Closes haskell/haddock#369 - - - - - b756b772 by Mateusz Kowalczyk at 2015-03-26T16:31:40+00:00 Remove now redundant imports - - - - - 5ea5e8dd by Mateusz Kowalczyk at 2015-03-26T16:45:52+00:00 Update test to account for \r filtering - - - - - 6539bfb3 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Test for anchor defaulting I delete the old tests because it turns out that: * test runner would never put them in scope of each other even with imports so just one would suffice * test runner actually needed some hacking to keep links so in the end we would end up with no anchors making them useless - - - - - 1a01d950 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Clearly default to variables in out of scope case - - - - - 7943abe8 by Mateusz Kowalczyk at 2015-03-27T01:14:11+00:00 Fix Hoogle display of constructors Fixes haskell/haddock#361 - - - - - 6d6e587e by Mateusz Kowalczyk at 2015-03-27T01:45:18+00:00 Fully qualify names in Hoogle instances output Closes haskell/haddock#263 - - - - - 52dac365 by Mateusz Kowalczyk at 2015-03-27T01:55:01+00:00 Update changelog - - - - - ca5af9a8 by Mateusz Kowalczyk at 2015-03-27T02:43:55+00:00 Output method documentation in Hoogle backend One thing of note is that we no longer preserve grouping of methods and print each method on its own line. We could preserve it if no documentation is present for any methods in the group if someone asks for it though. Fixes haskell/haddock#259 - - - - - a33f0c10 by Mateusz Kowalczyk at 2015-03-27T03:04:21+00:00 Don't print instance safety information in Hoogle Fixes haskell/haddock#168 - - - - - df6c935a by Mateusz Kowalczyk at 2015-03-28T00:11:47+00:00 Post-release version bumps and changelog - - - - - dde8f7c0 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Loosen bounds on haddock-* - - - - - de93bf89 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Expand response files in arguments Closes haskell/haddock#285 - - - - - 1f0b0856 by Zejun Wu at 2015-04-26T16:35:35-07:00 Do not insert anchor for section headings in contents box - - - - - 860439d7 by Simon Peyton Jones at 2015-05-01T09:36:47+01:00 Track change in API of TyCon - - - - - a32f3e5f by Adam Gundry at 2015-05-04T15:32:59+01:00 Track API changes to support empty closed type familes - - - - - 77e98bee by Ben Gamari at 2015-05-06T20:17:08+01:00 Ignore doc/haddock.{ps,pdf} - - - - - 663d0204 by Murray Campbell at 2015-05-11T04:47:37-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8bb0dcf5 by Murray Campbell at 2015-05-11T06:35:06-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit 2380f07c430c525b205ce2eae6dab23c8388d899) - - - - - bad900ea by Adam Bergmark at 2015-05-11T15:29:39+01:00 haddock-library: require GHC >= 7.4 `Data.Monoid.<>` was added in base-4.5/GHC-7.4 Closes haskell/haddock#394 Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - daceff85 by Simon Peyton Jones at 2015-05-13T12:04:21+01:00 Track the new location of setRdrNameSpace - - - - - 1937d1c4 by Alan Zimmerman at 2015-05-25T21:27:15+02:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - ee0fb6c2 by Łukasz Hanuszczak at 2015-05-27T11:51:31+02:00 Create simple method for indentation parsing. - - - - - 7d6fcad5 by Łukasz Hanuszczak at 2015-05-27T21:36:13+02:00 Make nested lists count indentation according to first item. - - - - - d6819398 by Łukasz Hanuszczak at 2015-05-27T22:46:13+02:00 Add simple test case for arbitrary-depth list nesting. - - - - - 2929c54d by Łukasz Hanuszczak at 2015-06-03T02:11:31+02:00 Add arbitrary-indent spec test for parser. - - - - - 9a0a9bb0 by Mateusz Kowalczyk at 2015-06-03T05:25:29+01:00 Update docs with info on new list nesting rule Fixes haskell/haddock#278 through commits from PR haskell/haddock#401 - - - - - 12efc92c by Mateusz Kowalczyk at 2015-06-03T05:29:26+01:00 Update some meta data at the top of the docs - - - - - 765ee49f by Bartosz Nitka at 2015-06-07T08:40:59-07:00 Add some Hacking docs for getting started - - - - - 19aaf851 by Bartosz Nitka at 2015-06-07T08:44:30-07:00 Fix markdown - - - - - 2a90cb70 by Mateusz Kowalczyk at 2015-06-08T15:08:36+01:00 Refine hacking instructions slightly - - - - - 0894da6e by Thomas Winant at 2015-06-08T23:47:28-05:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 10a9bb76 by Emanuel Borsboom at 2015-06-12T02:46:23+01:00 Build executable with '-threaded' (fixes haskell/haddock#399) - - - - - 7696b94f by Mateusz Kowalczyk at 2015-06-12T02:59:19+01:00 Update changelog for -threaded Closes haskell/haddock#400 - - - - - d3c118ec by Bartosz Nitka at 2015-06-12T03:00:58+01:00 Fix haddock: internal error: spliceURL UnhelpfulSpan (#207) Inferred type signatures don't have SrcSpans, so let's use the one from the declaration. I've tested this manually on the test-case from haskell/haddock#207, but I got stuck at trying to run the test-suite. - - - - - b67e843b by Mateusz Kowalczyk at 2015-06-12T03:01:50+01:00 Changelog for haskell/haddock#207 Fixes haskell/haddock#207, closes haskell/haddock#402 - - - - - 841d785e by jpmoresmau at 2015-06-12T16:03:16+01:00 Attach to instance location the name that has the same location file Fixes haskell/haddock#383 - - - - - 98791cae by Mateusz Kowalczyk at 2015-06-12T16:08:27+01:00 Update changelog Closes haskell/haddock#398 - - - - - 7c0b5a87 by Phil Ruffwind at 2015-06-12T13:07:25-04:00 Fix alignment of Source links in instance table in Firefox Due to a Firefox bug [1], a combination of 'whitespace: nowrap' on the parent element with 'float: right' on the inner element can cause the floated element to be displaced downwards for no apparent reason. To work around this, the left side is wrapped in its own <span> and set to 'float: left'. As a precautionary measure to prevent the parent element from collapsing entirely, we also add the classic "clearfix" hack. The latter is not strictly needed but it helps prevent bugs if the layout is altered again in the future. Fixes haskell/haddock#384. Remark: line 159 of src/Haddock/Backends/Xhtml/Layout.hs was indented to prevent confusion over the operator precedence of (<+>) vs (<<). [1]: https://bugzilla.mozilla.org/show_bug.cgi?id=488725 - - - - - cfe86e73 by Mateusz Kowalczyk at 2015-06-14T10:49:01+01:00 Update tests for the CSS changes - - - - - 2d4983c1 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding for Haskell source parser module. - - - - - 29548785 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement function for tagging parsed chunks with source spans. - - - - - 6a5e4074 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement simple string chunking based on HsColour library. - - - - - 6e52291f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create basic token classification method. - - - - - da971a27 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Adapt source span tagging to work with current whitespace handling. - - - - - 4feb5a22 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add record accessors to exports of hyperlinker parser module. - - - - - a8cc4e39 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Make parser module export all types and associated accessors. - - - - - fb8d468f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple HTML renderer for parsed source file. - - - - - 80747822 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for specifying the CSS file path in HTML source renderer. - - - - - 994dc1f5 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix identifier recognition in Haskell source parser. - - - - - b1bd0430 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix comment recognition in Haskell source parser. - - - - - 11db85ae by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for recognizing compiler pragmas in source parser. - - - - - 736c7bd3 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding of module for associating tokens with AST names. - - - - - 7e149bc2 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement utility method for extracting variable identifiers from AST. - - - - - 32eb640a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple mechanism for associating tokens with AST names. - - - - - d4eba5bc by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add dummy support for hyperlinking named tokens. - - - - - 2b76141f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matcher bug causing wrong items being hyperlinked. - - - - - 2d48002e by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Constrain elements exported by hyperlinker modules. - - - - - 9715eec6 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for type token recognition. - - - - - 8fa401cb by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for binding token recognition. - - - - - d062400b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement go-to-definition mechanism for local bindings. - - - - - f4dc229b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement module export- and import-list item hyperlinking. - - - - - c9a46d58 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matching to allow parenthesized operators hyperlinking. - - - - - 03aad95a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix weird hyperlinking of parenthesized operators. - - - - - b4694a7d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for type declaration anchors. - - - - - 7358d2d2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for top-level function declaration anchors. - - - - - dfc24b24 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix external anchors to contain HTML file extension. - - - - - a045926c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Refactor the way AST names are handled within detailed tokens. - - - - - c76049b4 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement hyperlinking of imported module names. - - - - - 2d2a1572 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix parsing of single line comments with broken up newlines. - - - - - 11afdcf2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix bug with improper newline handling. - - - - - 8137f104 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issues with escaped newlines in comments. - - - - - 34759b19 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for parsing C preprocessor macros. - - - - - 09f0f847 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for parser module of source hyperlinker. - - - - - 709a8389 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for AST module of source hyperlinker. - - - - - 4df5c227 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add command line option for generating hyperlinked source. - - - - - 7a755ea2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Extend module interface with rich source token stream field. - - - - - 494f4ab1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement source tokenization during interface creation process. - - - - - 5f21c953 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create hyperlinker module and plug it into the Haddock pipeline. - - - - - 0cc8a216 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for providing custom CSS files for hyperlinked source. - - - - - a32bbdc1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for fancy highlighting upon hovering over identifier. - - - - - d16d642a by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make source hyperlinker generate output in apropriate directory. - - - - - ae12953d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create module with hyperlinker utility functions. - - - - - 6d4952c5 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make external hyperlinks point to locations specified by source URLs. - - - - - 8417555d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Rewrite source generation to fixed links and directory structure. - - - - - ce9cec01 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add basic support for cross-package hyperlink generation. - - - - - 7eaf025c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Disable generating hyperlinks for module references. - - - - - a50bf92e by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make Haddock generate source for all interfaces (also hidden ones). - - - - - f5ae2838 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Prevent source parser from throwing exception when lexing fails. - - - - - db9ffbe0 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement workaround for Chrome highlighting issues. - - - - - 0b6b453b by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate correct anchors for data constructors. - - - - - c86d38bc by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate anchors for record field declarations. - - - - - 063abf7f by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issue with hyperlink highlight styling in Chrome browser. - - - - - 880fc611 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking constructor names in patters. - - - - - c9e89b95 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record patterns. - - - - - 17a11996 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record expressions. - - - - - 0eef932d by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Make hyperlinker respect pretty-printer flag and add documentation. - - - - - f87c1776 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Unexpose hyperlinker modules in Cabal configuration. - - - - - 4c9e2b06 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Setup HSpec framework for Haddock API package. - - - - - 4b20cb30 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add basic tests related to comment parsing. - - - - - 6842e919 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add tests related to parsing basic language constructs. - - - - - 87bffb35 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add simple tests for do-notation parsing. - - - - - e7af1841 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add very simple QuickCheck properties for source parser spec. - - - - - c84efcf1 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Create simple test runner for hyperlinker tests. - - - - - 76b90447 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for basic identifier hyperlinking. - - - - - 0fbf4df6 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for operator hyperlinking. - - - - - 731aa039 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for constructor hyperlinking. - - - - - 995a78a2 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for record expressions and patterns hyperlinking. - - - - - 3566875a by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for literal syntax highlighting. - - - - - 68469a35 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add hyperlinker test runner to .cabal and .gitignore files. - - - - - aa946c93 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Adapt hyperlinker test runner to have the same interface as HTML one. - - - - - ce34da16 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Fix hyperlinker test runner file paths and add pretty-printing option. - - - - - 0d7dd65e by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add reference files for hyperlinker test cases. - - - - - efa4a1e0 by Łukasz Hanuszczak at 2015-07-01T00:47:32+02:00 Make hyperlinker test runner strip local links from generated source. - - - - - 3e96e584 by Łukasz Hanuszczak at 2015-07-01T01:14:59+02:00 Create simple script for accepting hyperlinker test case references. - - - - - 526fe610 by Łukasz Hanuszczak at 2015-07-01T01:16:41+02:00 Re-accept hyperlinker test cases with local references stripped out. - - - - - 892e2cb3 by Łukasz Hanuszczak at 2015-07-01T01:22:09+02:00 Fix bug with diffing wrong files in hyperlinker test runner. - - - - - 9ff46039 by Łukasz Hanuszczak at 2015-07-01T18:04:46+02:00 Remove unused dependencies in Haddock API spec configuration. - - - - - 47969c07 by Łukasz Hanuszczak at 2015-07-01T18:32:19+02:00 Add support for hyperlinking synonyms in patterns. - - - - - a73449e0 by Łukasz Hanuszczak at 2015-07-01T18:33:44+02:00 Create test case for hyperlinking @-patterns. - - - - - c2077ed8 by Łukasz Hanuszczak at 2015-07-01T19:06:04+02:00 Add support for hyperlinking universally quantified type variables. - - - - - 68017342 by Łukasz Hanuszczak at 2015-07-01T19:28:32+02:00 Create hyperlinker test case with quantified type variables. - - - - - 51c01a78 by Łukasz Hanuszczak at 2015-07-01T19:34:22+02:00 Add scoped type variables test for polymorphism test case. - - - - - 13181ae2 by Łukasz Hanuszczak at 2015-07-01T19:56:27+02:00 Add record wildcards test for records hyperlinking test case. - - - - - 991b81dd by Łukasz Hanuszczak at 2015-07-01T21:01:42+02:00 Document some functions in XHTML utlity module. - - - - - 98c8dfe5 by Łukasz Hanuszczak at 2015-07-01T22:25:21+02:00 Make hyperlinker render qualified names as one entity. - - - - - 75e13b9b by Łukasz Hanuszczak at 2015-07-01T22:27:38+02:00 Add qualified name test for identifiers hyperlinking test case. - - - - - de1e143f by Łukasz Hanuszczak at 2015-07-02T12:32:59+02:00 Fix crash happening when hyperlinking type family declarations. - - - - - 7a8fb175 by Łukasz Hanuszczak at 2015-07-02T12:47:03+02:00 Add support for anchoring data family constructor declarations. - - - - - 3b404e49 by Łukasz Hanuszczak at 2015-07-02T13:31:05+02:00 Improve support for hyperlinking type families. - - - - - 59eb7143 by Łukasz Hanuszczak at 2015-07-02T13:33:34+02:00 Add hyperlinker test case for checking type and type family declarations. - - - - - d1cda0c0 by Łukasz Hanuszczak at 2015-07-02T13:41:38+02:00 Fix issue with operators being recognized as preprocessor directives. - - - - - da206c9d by Łukasz Hanuszczak at 2015-07-02T17:18:12+02:00 Fix broken tests for parsing and hyperlinking hash operators. - - - - - 53750d1b by Łukasz Hanuszczak at 2015-07-02T18:53:28+02:00 Add support for anchoring signatures in type class declarations. - - - - - 1fa5bb10 by Łukasz Hanuszczak at 2015-07-02T19:04:47+02:00 Make hyperlinker generate anchors only to top-level value bindings. - - - - - a542305c by Łukasz Hanuszczak at 2015-07-02T19:05:58+02:00 Create hyperlinker test case for type classes. - - - - - b0dd4581 by Łukasz Hanuszczak at 2015-07-04T16:28:26+02:00 Update docs with information about source hyperlinking. - - - - - 9795302a by Łukasz Hanuszczak at 2015-07-04T16:52:15+02:00 Update docs on using `--read-interface` option. - - - - - 9acdc002 by Łukasz Hanuszczak at 2015-07-04T17:15:26+02:00 Remove potentially dangerous record access in hyperlinker AST module. - - - - - fb3ab7be by Łukasz Hanuszczak at 2015-07-04T17:40:10+02:00 Make Haddock generate warnings about potential misuse of hyperlinker. - - - - - a324c504 by Łukasz Hanuszczak at 2015-07-04T17:43:22+02:00 Fix incorrect specification of source style option in doc file. - - - - - 3f01a8e4 by Łukasz Hanuszczak at 2015-07-05T17:06:36+02:00 Refactor source path mapping to use modules as indices. - - - - - ac70f5b1 by Łukasz Hanuszczak at 2015-07-05T17:47:34+02:00 Fix bug where not all module interfaces were added to source mapping. - - - - - f5e57da9 by Łukasz Hanuszczak at 2015-07-06T16:39:57+02:00 Extract main hyperlinker types to separate module. - - - - - 43974905 by Łukasz Hanuszczak at 2015-07-06T16:52:13+02:00 Move source paths types to hyperlinker types module. - - - - - 3e236055 by Łukasz Hanuszczak at 2015-07-06T17:06:19+02:00 Add support for hyperlinking modules in import lists. - - - - - 58233d9f by Łukasz Hanuszczak at 2015-07-06T17:26:49+02:00 Add short documentation for hyperlinker source map type. - - - - - 14da016d by Łukasz Hanuszczak at 2015-07-06T18:07:20+02:00 Fix bug with module name being hyperlinked to `Prelude`. - - - - - 8f79db52 by Łukasz Hanuszczak at 2015-07-06T18:23:47+02:00 Fix problem with spec build in Haddock API configuration. - - - - - e7cc056c by Adam Sandberg Eriksson at 2015-07-07T23:22:21+01:00 StrictData: print correct strictness marks - - - - - e8253ca8 by Mateusz Kowalczyk at 2015-07-07T23:58:28+01:00 Update changelog - - - - - 0aba676b by Mateusz Kowalczyk at 2015-07-07T23:58:33+01:00 Relax upper bound on GHC a bit - - - - - 7a595381 by Mateusz Kowalczyk at 2015-07-07T23:58:52+01:00 Delete trailing whitespace - - - - - 50976d5e by Adam Sandberg Eriksson at 2015-07-08T15:03:04+02:00 StrictData: changes in HsBang type - - - - - 83b045fa by Mateusz Kowalczyk at 2015-07-11T14:35:18+01:00 Fix expansion icon for user-collapsible sections Closes haskell/haddock#412 - - - - - b2a3b0d1 by Mateusz Kowalczyk at 2015-07-22T22:03:21+01:00 Make some version changes after 2.16.1 release - - - - - a8294423 by Ben Gamari at 2015-07-27T13:16:07+02:00 Merge pull request haskell/haddock#422 from adamse/adamse-D1033 Merge for GHC D1033 - - - - - c0173f17 by randen at 2015-07-30T14:49:08-07:00 Break the response file by line termination rather than spaces, since spaces may be within the parameters. This simple approach avoids having the need for any quoting and/or escaping (although a newline char will not be possible in a parameter and has no escape mechanism to allow it). - - - - - 47c0ca14 by Alan Zimmerman at 2015-07-31T10:41:52+02:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - 45a9d770 by Mateusz Kowalczyk at 2015-07-31T09:47:43+01:00 Update changelog - - - - - 347a20a3 by Phil Ruffwind at 2015-08-02T23:15:26+01:00 Avoid JavaScript error during page load in non-frame mode In non-frame mode, parent.window.synopsis refers to the synopsis div rather than the nonexistent frame. Unfortunately, the script wrongly assumes that if it exists it must be a frame, leading to an error where it tries to access the nonexistent attribute 'replace' of an undefined value (synopsis.location). Closes haskell/haddock#406 - - - - - 54ebd519 by Phil Ruffwind at 2015-08-02T23:27:10+01:00 Link to the definitions to themselves Currently, the definitions already have an anchor tag that allows URLs with fragment identifiers to locate them, but it is rather inconvenient to obtain such a URL (so-called "permalink") as it would require finding the a link to the corresponding item in the Synopsis or elsewhere. This commit adds hyperlinks to the definitions themselves, allowing users to obtain links to them easily. To preserve the original aesthetics of the definitions, we alter the color of the link so as to be identical to what it was, except it now has a hover effect indicating that it is clickable. Additionally, the anchor now uses the 'id' attribute instead of the (obsolete) 'name' attribute. Closes haskell/haddock#407 - - - - - 02cc8bb7 by Phil Ruffwind at 2015-08-02T23:28:02+01:00 Fix typo in Haddock.Backends.Xhtml.Layout: divSynposis -> divSynopsis Closes haskell/haddock#408 - - - - - 2eb0a458 by Phil Ruffwind at 2015-08-02T23:30:07+01:00 Fix record field alignment when name is too long Change <dl> to <ul> and use display:table rather than floats to layout the record fields. This avoids bug haskell/haddock#301 that occurs whenever the field name gets too long. Slight aesthetic change: the entire cell of the field's source code is now shaded gray rather than just the area where text exists. Fixes haskell/haddock#301. Closes haskell/haddock#421 - - - - - 7abb3402 by Łukasz Hanuszczak at 2015-08-02T23:32:14+01:00 Add some utility definitions for generating line anchors. - - - - - e0b1d79b by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Make hyperlinked source renderer generate line anchors. - - - - - 24dd4c9f by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Re-accept test cases after adding line anchors for each of them. - - - - - 0372cfcb by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Override source line flags when source hyperlinker is enabled. - - - - - a81bcd07 by Mateusz Kowalczyk at 2015-08-02T23:58:25+01:00 Update tests to follow HTML changes - - - - - d2d7426f by Łukasz Hanuszczak at 2015-08-06T20:54:59+02:00 Fix quote syntax for promoted types. - - - - - 668cf029 by Łukasz Hanuszczak at 2015-08-06T21:12:00+02:00 Apply promoted type quoting to type-level consing. - - - - - 89f8e7c6 by Łukasz Hanuszczak at 2015-08-06T21:17:10+02:00 Extend advanced types test case with other examples. - - - - - 86494bca by Łukasz Hanuszczak at 2015-08-06T21:22:06+02:00 Rename advanced types test case and accept new output. - - - - - dbb7c7c0 by Adam Sandberg Eriksson at 2015-08-09T23:01:05+02:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 2a7704fa by Ben Gamari at 2015-08-10T13:18:05+02:00 Merge pull request haskell/haddock#433 from adamse/split-hsbang HsBang is split into HsSrcBang and HsImplBang - - - - - 891954bc by Thomas Miedema at 2015-08-15T14:51:18+02:00 Follow changes in GHC build system - - - - - b55d32ab by Mateusz Kowalczyk at 2015-08-21T18:06:09+01:00 Make Travis use 7.10.2 - - - - - 97348b51 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Move SYB utilities to standalone module. - - - - - 748ec081 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement `everywhere` transformation in SYB module. - - - - - 011cc543 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement generic transformation constructor. - - - - - b9510db2 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Create simple utility module for type specialization. - - - - - 43229fa6 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Make type of type specialization function more general. - - - - - fd844e90 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Add basic HTML test case for checking instance specialization. - - - - - 6ea0ad04 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Make HTML class instance printer take optional signature argument. - - - - - 65aa41b6 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Refactor instance head type to record instead of a meaningless tuple. - - - - - 3fc3bede by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add expandable method section for each class instance declaration. - - - - - 99ceb107 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Move dummy post-family instances for `DocName` to `Types` module. - - - - - e98f4708 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create convenience functions for type specialization module. - - - - - b947552f by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Hook type specialization logic with HTML pretty-printer. - - - - - dcaa8030 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create stub functions for sugaring specialized types. - - - - - fa84bc65 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement list syntax sugaring logic for specialized types. - - - - - e8b05b07 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement tuple syntax sugaring logic for specialized types. - - - - - 68a2e5bc by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Get rid of code duplication in type specialization module. - - - - - 4721c336 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create scaffolding of a framework for renaming specialized types. - - - - - 271b488d by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in missing cases in specialized type renaming function. - - - - - bfa5f2a4 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Remove code duplication in specialized type renamer. - - - - - ea6bd0e8 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Change state of the type renaming monad. - - - - - 77c5496e by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement simple mechanism for generating new type names. - - - - - 91bfb48b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in stub behaviour with actual environment renaming. - - - - - d244517b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix logic behind binder type renaming. - - - - - f3c5e360 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add SYB-like utility function for performing stateful queries. - - - - - eb3f9154 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create function for retrieving free variables from given type. - - - - - a94561d3 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix compilation error caused by incorrect type signature. - - - - - 8bb707cf by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Move `SetName` class definition to types module. - - - - - 5800b13b by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Hook type renamer with instance method HTML pretty-printer. - - - - - 6a480164 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some test cases for type renamer. - - - - - 839842f7 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized signatures refer to original signature declaration. - - - - - 4880f7c9 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized methods be nicely formatted again. - - - - - ab5a6a2e by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Attach source locations to the specialized class methods. - - - - - 43f8a559 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Extend instances test case to also test multi-name type signatures. - - - - - 59bc751c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix tab-based indentation in instances test case. - - - - - c2126815 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Improve placement of instance methods expander button. - - - - - 0a32e287 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add new data type declaration to instance specialization test case. - - - - - 5281af1f by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make type renamer first try single-letter names as alternatives. - - - - - 7d509475 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix type renamer bug with incorrect names being generated. - - - - - 0f35bf7c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some documentation and refactor type specialization module. - - - - - da1d0803 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix another bug where type renamer was generating incorrect names. - - - - - cd39b5cb by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Refactor type renamer to rebinding and pure renaming phases. - - - - - 850251f4 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix unwitting compilation bug. - - - - - e5e9fc01 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Integrate instance specification type into class instance definition. - - - - - 825b0ea0 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer neccessary instance specification type. - - - - - cdba44eb by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix declaration converter to use more appropriate mode for methods. - - - - - bc45c309 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug with types not being specialized at all. - - - - - 5d8e5d89 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug where instance expander was opening wrong section. - - - - - 6001ee41 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix another type renamer bug where not all names were rebound. - - - - - 5f58ce2a by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix yet another renamer bug where some names were not unique. - - - - - 8265e521 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split instance subsection layout method to top-level declarations. - - - - - e5e66298 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Rearrange layout of instance methods in generated documentation. - - - - - a50b4eea by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer used layout method. - - - - - 2ff36ec2 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach section title to the instance methods block. - - - - - 7ac15300 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Add basic tests for associated types in instances test case. - - - - - db0ea2f9 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach associated types information to instance header. - - - - - 71cad4d5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details section contain associated types information. - - - - - deee2809 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Improve look of rendered associated families in instance details. - - - - - 839d13a5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Introduce alternative type for family declarations. - - - - - d397f03f by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details record use new type for family declarations. - - - - - 2b23fe97 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split printer of type family header to separate functions. - - - - - c3498cdc by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Implement HTML renderer for pseudo-family declarations. - - - - - c12bbb04 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Apply type specializer to associated type family declarations. - - - - - 2fd69ff2 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Create helper method for specializing type signatures. - - - - - 475826e7 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Refactor specializer module to be independent from XHTML backend. - - - - - f00b431c by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add some documentation for instance head specializer. - - - - - a9fef2dc by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix bug with missing space in documentation for associated types. - - - - - 50e29056 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with incorrect instance details sections being expanded. - - - - - e6dfdd03 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by adding instance details section. - - - - - 75565b2a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make section identifier of instance details more GHC-independent. - - - - - add0c23e by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Re-accept tests after applying deterministic section identifiers. - - - - - 878f2534 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make identifier generation also architecture-independent. - - - - - 48be69f8 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with instance expander hijacking type hyperlink click. - - - - - 47830c1f by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Get rid of dreadful hashing function for generating identifiers. - - - - - 956cd5af by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Move `InstOrigin` type declaration to more appropriate module. - - - - - bf672ed3 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by changes related to instance expander. - - - - - 8f2a949a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add examples with type operators to the instances test case. - - - - - 64600a84 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add basic support for sugaring infix type operators. - - - - - 747d71b8 by Łukasz Hanuszczak at 2015-08-21T18:22:34+01:00 Add support for sugaring built-in function syntax. - - - - - d4696ffb by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Remove default methods from Hoogle class output. - - - - - bf0e09d7 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add fixity declarations in Hoogle backend output. - - - - - 90e91a51 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix bug with incorrect fixities being generated in Hoogle backend. - - - - - 48f11d35 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve class type family declarations output in Hoogle backend. - - - - - 661e8e8f by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add missing default family equations in Hoogle output. - - - - - e2d64103 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve formatting of class details output in Hoogle backend. - - - - - 490fc377 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix weird-looking Hoogle output for familyless classes. - - - - - ea115b64 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create script file for new HTML test runner. - - - - - 609913d3 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Set default behaviour if no arguments given. - - - - - dc115f67 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for providing optional arguments for test runner. - - - - - d93ec867 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve output of test runner error messages. - - - - - 0be9fe12 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for executing Haddock process in test runner. - - - - - 4e4d00d9 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add GHC path to test runner configuration. - - - - - d67a2086 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make GHC path a test runner command-line argument. - - - - - c810079a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Extend test runner configuration with Haddock arguments. - - - - - fee18845 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor test runner and create stub functions. - - - - - ff7c161f by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make test runner actually run Haddock executable. - - - - - 391f73e6 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with test runner not producing any output files. - - - - - 81a74e2d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Setup skeleton of framework for running tests. - - - - - f8a79ec4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with modules not being found in global search mode. - - - - - 7e700b4d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make Haddock standard output redirection be more configurable. - - - - - 53b4c17a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Incorporate old, ugly functions for comparing output files. - - - - - 8277c8aa by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor architecture of test runner output checking functions. - - - - - 587bb414 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement actual diffing mechanism. - - - - - 9ed2b5e4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve code style to match popular guidelines. - - - - - 14bffaf8 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make it possible to choose alternative diff tool. - - - - - 5cdfb005 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create stub methods for processing test output as XML documents. - - - - - 7ef8e12e by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement link-stripping logic as simple SYB transformation. - - - - - 8a1fcd4f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Incorporate link stripping to output diffing mechanism. - - - - - 37dba2bc by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement footer-stripping logic. - - - - - 9cd52120 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Add missing dependencies in Cabal configuration file. - - - - - e0f83c6e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix issue with output being printed in incorrect order. - - - - - 0a94fbb0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to run tests without generating diff. - - - - - 76a58c6f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor HTML test suite boilerplate to external package. - - - - - af41e6b0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utilities for storing directory configuration. - - - - - d8f0698f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move IO-dependent config of HTML test suite to test package. - - - - - 17369fa0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Enable all compiler warnings in Haddock test package configuration. - - - - - 9d03b47a by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move Haddock runner of HTML test suite to Haddock test package. - - - - - 4b3483c5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 03754194 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience wrappers to simplify in test entry points. - - - - - 27476ab7 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adjust module visibility and items they export. - - - - - c40002ba by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Remove no longer useful test option. - - - - - 55ab2541 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Change extension of test files used for diffing. - - - - - 136bf4e4 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor and simplify XHTML helper module of test package. - - - - - 69f7e3df by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix typo in link stripper of HTML test suite runner. - - - - - 0c3c1c6b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience script for running specific HTML tests. - - - - - 489e1b05 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement utility functions for conditional link stripping. - - - - - 0f985dc3 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt `hypsrc-test` module to work with new testing framework. - - - - - 927406f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement output accepting mechanism in test package. - - - - - 8545715e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utility function for recursive obtaining directory contents. - - - - - cb70381f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 019599b5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix path handling in test runner. - - - - - 399b985b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to specify ignored files for test output. - - - - - 41b3d93d by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt HTML test runner to use new ignoring functionality. - - - - - e2091c8b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix bug with not all test output files being checked. - - - - - b22134f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Specify ignored files for hyperlinker source test runner. - - - - - 3301dfa1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Copy test runner script for hyperlinked source case. - - - - - d39a6dfa by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner invoking Haddock in incorrect mode. - - - - - f32c8ff3 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix path handling in test module loader. - - - - - 10f94ee9 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make test runner ignore test packages with no modules. - - - - - 5dc4239c by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create test runner entry points for LaTeX test suite. - - - - - 58d1f7cf by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with unnecessary checking old test output. - - - - - c7ce76e1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Re-implement test acceptance functionality. - - - - - 13bbabe8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix warning about no longer needed definition. - - - - - 958a99b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Adapt Cabal configuration to execute LaTeX suite with new runner. - - - - - 550ff663 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Setup test suite for Hoogle backend. - - - - - 3aa969c4 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make Hoogle backend create output directory if needed. - - - - - eb085b02 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Add appropriate .gitignore entry and configure Hoogle test suite. - - - - - a50bf915 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner failing when run on multiple test packages. - - - - - bf5368b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create simple test cases for Hoogle backend. - - - - - 6121ba4b by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create helper function for conversion between XML and XHTML. - - - - - cb516061 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Refactor existing code to use XHTML printer instead of XML one. - - - - - e2de8c82 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Improve portability of test runner scripts. - - - - - 9563e774 by Łukasz Hanuszczak at 2015-08-22T23:43:16+02:00 Remove redundant import statement. - - - - - 55353df1 by Łukasz Hanuszczak at 2015-08-24T23:09:20+02:00 Fix bug with accepting to non-existing directory. - - - - - 00a334ca by Łukasz Hanuszczak at 2015-08-24T23:09:47+02:00 Accept output for Hoogle and LaTeX backends. - - - - - 29191d8b by Łukasz Hanuszczak at 2015-08-24T23:14:18+02:00 Get rid of obsolete testing utilities. - - - - - bbb25db3 by Łukasz Hanuszczak at 2015-08-24T23:18:50+02:00 Update sandbox setup guide to work with Haddock test package. - - - - - cfd45248 by Łukasz Hanuszczak at 2015-08-24T23:51:30+02:00 Make Travis aware of Haddock test package. - - - - - 74185b7a by Łukasz Hanuszczak at 2015-08-25T17:41:59+02:00 Fix test suite failure when used with Stack. - - - - - 18769697 by Łukasz Hanuszczak at 2015-08-25T18:02:09+02:00 Add sample Stack setup to the hacking guide. - - - - - 22715eeb by Łukasz Hanuszczak at 2015-08-25T18:04:47+02:00 Fix Markdown formatting of README file. - - - - - b49ec386 by Łukasz Hanuszczak at 2015-08-25T18:13:36+02:00 Setup Haddock executable path in Travis configuration. - - - - - 5d29eb03 by Eric Seidel at 2015-08-30T09:55:58-07:00 account for changes to ipClass - - - - - f111740a by Ben Gamari at 2015-09-02T13:20:37+02:00 Merge pull request haskell/haddock#443 from bgamari/ghc-head account for changes to ipClass - - - - - a2654bf6 by Jan Stolarek at 2015-09-03T01:32:57+02:00 Follow changes from haskell/haddock#6018 - - - - - 2678bafe by Richard Eisenberg at 2015-09-21T12:00:47-04:00 React to refactoring CoAxiom branch lists. - - - - - ebc56e24 by Edward Z. Yang at 2015-09-21T11:53:46-07:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4a8c4198 by Tamar Christina at 2015-09-27T13:59:08+02:00 Create Process: removed PhaseFailed - - - - - 7e99b790 by Oleg Grenrus at 2015-09-27T20:52:10+03:00 Generate docs for orphan instances - - - - - 32e932e2 by Oleg Grenrus at 2015-09-28T07:21:11+03:00 Have source links for orphan instances - - - - - c2eb9f4f by Oleg Grenrus at 2015-09-28T07:24:58+03:00 Print orphan instances header only if required - - - - - ff96f978 by Oleg Grenrus at 2015-09-28T07:40:54+03:00 Add orphan instances link to contents box - - - - - d72490a6 by Oleg Grenrus at 2015-09-28T16:37:44+03:00 Fix orphan instance collapsing - - - - - 25d3dfe5 by Ben Gamari at 2015-10-03T12:38:09+02:00 Merge pull request haskell/haddock#448 from Mistuke/fix-silent-death-of-runInteractive Remove PhaseFailed - - - - - 1e45e43b by Edward Z. Yang at 2015-10-11T13:10:10-07:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b1370ac1 by Adam Gundry at 2015-10-16T16:26:42+01:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 60bef421 by Simon Peyton Jones at 2015-10-26T12:52:36+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 4c1898ca by Simon Peyton Jones at 2015-10-27T14:24:56+00:00 Track change to PatSyn.patSynSig - - - - - 25108e85 by Simon Peyton Jones at 2015-10-27T17:34:18+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - 693643ac by Ben Gamari at 2015-10-28T14:33:06+01:00 Account for Typeable changes The treatment of type families changed. - - - - - cd7c2221 by Simon Peyton Jones at 2015-10-30T13:03:51+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - 712032cb by Herbert Valerio Riedel at 2015-10-31T11:01:45+01:00 Relax upper bound on `base` to allow base-4.9 - - - - - 0bfa0475 by Simon Peyton Jones at 2015-10-31T19:08:13+00:00 More adaption to wildcard-refactor - - - - - 0a3c0cb7 by Simon Peyton Jones at 2015-10-31T22:14:43+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - c4fd4ec9 by Alan Zimmerman at 2015-11-01T11:16:34+01:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 42cdd882 by Matthew Pickering at 2015-11-06T20:02:16+00:00 Change for IEThingWith - - - - - f368b7be by Ben Gamari at 2015-11-11T11:35:51+01:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - e32965b8 by Simon Peyton Jones at 2015-11-13T12:18:17+00:00 Merge with origin/head - - - - - ebcf795a by Edward Z. Yang at 2015-11-13T21:56:27-08:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4e23989f by Simon Peyton Jones at 2015-11-18T11:32:54+00:00 Wibbles to Haddock - - - - - 2289cd4a by Simon Peyton Jones at 2015-11-20T23:12:49+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor - - - - - 695975a6 by Alan Zimmerman at 2015-11-21T21:16:12+02:00 Update to match GHC wip/T11019 - - - - - bbba21e7 by Simon Peyton Jones at 2015-11-23T13:54:31+00:00 merge with origin/ghc-head - - - - - 3d664258 by Simon Peyton Jones at 2015-11-23T17:17:18+00:00 Wibble - - - - - e64cf586 by Herbert Valerio Riedel at 2015-12-05T00:29:55+01:00 Canonicalise Monad instances - - - - - a2de15a7 by Alan Zimmerman at 2015-12-05T17:33:52+02:00 Matching changes for haskell/haddock#11028 - - - - - cc29a3e4 by Alan Zimmerman at 2015-12-05T19:45:33+02:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 95dd15d1 by Richard Eisenberg at 2015-12-11T17:33:39-06:00 Update for type=kinds - - - - - cb5fd9ed by Herbert Valerio Riedel at 2015-12-14T15:07:30+00:00 Bump versions for ghc-7.11 - - - - - 4f286d96 by Simon Peyton Jones at 2015-12-14T15:10:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 13ea2733 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 098df8b8 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track changes in HsSyn for quasi-quotes - - - - - 716a64de by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track change in API of TyCon - - - - - 77a66bca by Adam Gundry at 2015-12-14T15:10:58+00:00 Track API changes to support empty closed type familes - - - - - f2808305 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track the new location of setRdrNameSpace - - - - - ba8b08a4 by Alan Zimmerman at 2015-12-14T15:10:59+00:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - a4ded87e by Thomas Winant at 2015-12-14T15:14:05+00:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 25c78107 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: print correct strictness marks - - - - - 6cbc41c4 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: changes in HsBang type - - - - - ad46821a by Alan Zimmerman at 2015-12-14T15:14:06+00:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - abc0ae5b by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 3308d06c by Thomas Miedema at 2015-12-14T15:14:07+00:00 Follow changes in GHC build system - - - - - 6c763deb by Eric Seidel at 2015-12-14T15:14:07+00:00 account for changes to ipClass - - - - - ae5b4eac by Jan Stolarek at 2015-12-14T15:17:00+00:00 Follow changes from haskell/haddock#6018 - - - - - ffbc40e0 by Richard Eisenberg at 2015-12-14T15:17:02+00:00 React to refactoring CoAxiom branch lists. - - - - - d1f531e9 by Edward Z. Yang at 2015-12-14T15:17:02+00:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 79f73754 by Tamar Christina at 2015-12-14T15:17:02+00:00 Create Process: removed PhaseFailed - - - - - 3d37bebb by Edward Z. Yang at 2015-12-14T15:20:46+00:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 5f8a9e44 by Adam Gundry at 2015-12-14T15:20:48+00:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 79dda70f by Simon Peyton Jones at 2015-12-14T15:26:02+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 959930fb by Simon Peyton Jones at 2015-12-14T15:37:50+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - e18a8df5 by Simon Peyton Jones at 2015-12-14T15:37:52+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - aa35ab52 by Simon Peyton Jones at 2015-12-14T15:40:18+00:00 More adaption to wildcard-refactor - - - - - 8ceef94b by Simon Peyton Jones at 2015-12-14T15:46:04+00:00 Track change to PatSyn.patSynSig - - - - - cd81e83d by Ben Gamari at 2015-12-14T15:46:06+00:00 Account for Typeable changes The treatment of type families changed. - - - - - 63c9117c by Herbert Valerio Riedel at 2015-12-14T15:46:34+00:00 Relax upper bound on `base` to allow base-4.9 - - - - - a484c613 by Alan Zimmerman at 2015-12-14T15:47:46+00:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 2c26fa51 by Matthew Pickering at 2015-12-14T15:47:47+00:00 Change for IEThingWith - - - - - 593baa0f by Ben Gamari at 2015-12-14T15:49:21+00:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - b6b5ca78 by Edward Z. Yang at 2015-12-14T15:49:54+00:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b5b0e072 by Alan Zimmerman at 2015-12-14T15:54:20+00:00 Update to match GHC wip/T11019 - - - - - 14ddeb68 by Simon Peyton Jones at 2015-12-14T15:54:22+00:00 Wibble - - - - - 10a90ad8 by Herbert Valerio Riedel at 2015-12-14T15:54:22+00:00 Canonicalise Monad instances - - - - - ed68ac50 by Alan Zimmerman at 2015-12-14T15:55:48+00:00 Matching changes for haskell/haddock#11028 - - - - - 3f7e5a2d by Alan Zimmerman at 2015-12-14T15:55:49+00:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 6543a73f by Richard Eisenberg at 2015-12-14T15:59:55+00:00 Update for type=kinds - - - - - 193a5c48 by Matthew Pickering at 2015-12-14T18:17:00+00:00 Changes to compile with 8.0 - - - - - add669ec by Matthew Pickering at 2015-12-14T18:47:12+00:00 Warnings - - - - - 223f3fb4 by Ben Gamari at 2015-12-15T23:45:05+01:00 Update for D1200 - - - - - d058388f by Ben Gamari at 2015-12-16T05:40:17-05:00 Types: Add Outputable[Bndr] DocName instances - - - - - 62ecd7fb by Ben Gamari at 2015-12-16T09:23:09-05:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ddbc187a by Ben Gamari at 2015-12-16T17:54:55+01:00 Update for D1200 - - - - - cec83b52 by Ben Gamari at 2015-12-16T17:54:55+01:00 Types: Add Outputable[Bndr] DocName instances - - - - - d12ecc98 by Ben Gamari at 2015-12-16T17:54:55+01:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ada1616f by Ben Gamari at 2015-12-16T17:54:58+01:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a4f0383d by Ben Gamari at 2015-12-16T23:32:38+01:00 Fix Hyperlinker GHC.con_names is now GHC.getConNames - - - - - a10e6849 by Ben Gamari at 2015-12-20T00:54:11+01:00 Merge remote-tracking branch 'mrhania/testing-framework-improvements' into ghc-head - - - - - f078b4fd by Ben Gamari at 2015-12-20T00:59:51+01:00 test: Compatibility with Cabal 1.23 - - - - - 88a511a9 by Ben Gamari at 2015-12-20T01:14:35+01:00 Merge remote-tracking branch 'phadej/orphans' into ghc-head - - - - - 4e250f36 by Ben Gamari at 2015-12-20T01:14:52+01:00 Add html-test for orphan instances output - - - - - 87fffbad by Alan Zimmerman at 2015-12-20T09:50:42+02:00 Update for GHC trac#11258 Adding locations to RdrName in FieldOcc and AmbiguousFieldOcc - - - - - 6b7e51c9 by idontgetoutmuch at 2015-12-20T21:01:47+00:00 Merge pull request haskell/haddock#1 from haskell/ghc-head Ghc head - - - - - 229c1fb5 by Dominic Steinitz at 2015-12-21T07:19:16+00:00 Handle inline math with mathjax. - - - - - 57902d66 by Dominic Steinitz at 2015-12-21T08:07:11+00:00 Fix the documentation for haddock itself. Change notation and add support for inline math. Allow newlines in display math. Add a command line option for the mathjax url (you might want to use a locally installed version). Rebase tests because of extra url and version change. Respond to (some of the) comments. Fix warnings in InterfaceFile.hs - - - - - 0e69f236 by Herbert Valerio Riedel at 2015-12-21T18:30:43+01:00 Fix-up left-over assumptions of GHC 7.12 into GHC 8.0 - - - - - c67f8444 by Simon Peyton Jones at 2015-12-22T16:26:56+00:00 Follow removal of NamedWildCard from HsType - - - - - da40327a by Ben Gamari at 2015-12-23T14:15:28+01:00 html-test/Operators: Clear up ambiguous types For reasons that aren't entirely clear a class with ambiguous types was accepted by GHC <8.0. I've added a functional dependency to clear up this ambiguity. - - - - - 541b7fa4 by Ben Gamari at 2015-12-23T14:18:51+01:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 0febc947 by Ben Gamari at 2015-12-24T00:30:20+01:00 hoogle-test/AssocTypes: Allow AmbiguousTypes GHC 8.0 complains otherwise - - - - - 25810841 by Ben Gamari at 2015-12-24T00:33:18+01:00 OrphanInstances: Accept test output - - - - - 841987f3 by Ben Gamari at 2015-12-25T11:03:11+01:00 Merge remote-tracking branch 'idontgetoutmuch/ghc-head' into ghc-head - - - - - 358391f0 by Ben Gamari at 2015-12-26T10:44:50+01:00 Add missing import - - - - - a8896885 by Ben Gamari at 2015-12-26T10:45:27+01:00 travis: Use Travis containers - - - - - 85e82134 by Herbert Valerio Riedel at 2015-12-30T17:25:39+01:00 tweak version bounds for GHC-8.1 - - - - - 672a5f75 by randen at 2016-01-01T23:45:25-08:00 The Haddock part for fully gcc-like response files " driver/Main.hs * Moved the response file handling into ResponseFile.hs, updating import section as appropriate. * driver/ResponseFile.hs * New file. In anticipation that maybe some day this could be provided by another library, and to make it possible to unit test, this functionality is pulled out of the Main.hs module, and expanded to support the style/format of response files which gcc uses. * The specification for the format of response files which gcc generates and consumes, seems to be best derived from the gcc code itself (libiberty/argv.c), so that is what has been done here. * This is intended to fix haskell/haddock#379 * driver-test/Main.hs * New file for testing code in the driver source tree * driver-test/ResponseFileSpec.hs * Tests, adapted/adopted from the same gcc code where the escaping/unescaping is from, in the hspec style of unit tests * haddock.cabal * Add the driver-test test-suite. Introduces a new library dependency (upon hspec) for the haddock driver target in the haddock.cabal file, but practically, this should not be a problem as the haddock-api tests already depend on hspec. - - - - - 498781df by Ben Gamari at 2016-01-06T13:41:04+01:00 Version bumps and changelog - - - - - 8451e46a by Ben Gamari at 2016-01-06T13:47:17+01:00 Merge remote-tracking branch 'randen/bug468' - - - - - fb2d9181 by Ben Gamari at 2016-01-06T08:14:42-05:00 Add ResponseFile to OtherModules - - - - - 2cb2d2e3 by Ben Gamari at 2016-01-06T14:35:00+01:00 Merge branch 'master' into ghc-head - - - - - 913477d4 by Eric Seidel at 2016-01-11T14:57:57-08:00 deal with un-wiring of IP class - - - - - c557a4b3 by Alan Zimmerman at 2016-01-15T11:14:35+02:00 Update to match wip/T11430 in GHC - - - - - 3e135093 by Alan Zimmerman at 2016-01-16T18:21:59+01:00 Update to match wip/T11430 in GHC - - - - - c48ef2f9 by Ben Gamari at 2016-01-18T09:50:06+01:00 Merge remote-tracking branch 'gridaphobe/ghc-head' into ghc-head - - - - - 9138a1b0 by Eric Seidel at 2016-01-18T12:50:15+01:00 deal with un-wiring of IP class (cherry picked from commit 17388b0f0029d969d79353be7737eb01c7b8dc5f) - - - - - b48c172e by Joachim Breitner at 2016-01-19T00:11:38+01:00 Make sure --mathjax affects all written HTML files This fixes haskell/haddock#475. - - - - - af61fe63 by Ryan Scott at 2016-02-07T23:25:57+01:00 Render */# instead of TYPE 'Lifted/TYPE 'Unlifted (fixes haskell/haddock#473) - - - - - b6458693 by Ben Gamari at 2016-02-07T23:29:27+01:00 Merge pull request haskell/haddock#477 from haskell/issue-475 Make sure --mathjax affects all written HTML files - - - - - adcc0071 by Ben Gamari at 2016-02-07T23:34:52+01:00 Merge branch 'master' into ghc-head - - - - - d0404e61 by Ben Gamari at 2016-02-08T12:46:49+01:00 doc: Switch to Sphinx - - - - - acb153b3 by Ben Gamari at 2016-02-08T12:46:56+01:00 Document --use-unicode flag - - - - - c20bdf1d by Ben Gamari at 2016-02-08T13:41:24+01:00 Fix GHC and haddock-library dependency bounds - - - - - 8d946801 by Ben Gamari at 2016-02-08T14:54:56+01:00 testsuite: Rework handling of output sanitization Previously un-cleaned artifacts were kept as reference output, making it difficult to tell what has changed and causing spurious changes in the version control history. Here we rework this, cleaning the output during acceptance. To accomplish this it was necessary to move to strict I/O to ensure the reference handle was closed before accept attempts to open the reference file. - - - - - c465705d by Ben Gamari at 2016-02-08T15:36:05+01:00 test: Compare on dump For reasons I don't understand the Xml representations differ despite their textual representations being identical. - - - - - 1ec0227a by Ben Gamari at 2016-02-08T15:36:05+01:00 html-test: Accept test output - - - - - eefbd63a by Ben Gamari at 2016-02-08T15:36:08+01:00 hypsrc-test: Accept test output And fix impredicative Polymorphism testcase. - - - - - d1df4372 by Ben Gamari at 2016-02-08T15:40:44+01:00 Merge branch 'fix-up-testsuite' - - - - - 206a3859 by Phil Ruffwind at 2016-02-08T17:51:21+01:00 Move the permalinks to "#" on the right side Since pull request haskell/haddock#407, the identifiers have been permalinked to themselves, but this makes it difficult to copy the identifier by double-clicking. To work around this usability problem, the permalinks are now placed on the far right adjacent to "Source", indicated by "#". Also, 'namedAnchor' now uses 'id' instead of 'name' (which is obsolete). - - - - - 6c89fa03 by Phil Ruffwind at 2016-02-08T17:54:44+01:00 Update tests for previous commit - - - - - effaa832 by Ben Gamari at 2016-02-08T17:56:17+01:00 Merge branch 'anchors-redux' - - - - - 9a2bec90 by Ben Gamari at 2016-02-08T17:58:40+01:00 Use -fprint-unicode-syntax when --use-unicode is enabled This allows GHC to render `*` as its Unicode representation, among other things. - - - - - 28ecac5b by Ben Gamari at 2016-02-11T18:53:03+01:00 Merge pull request haskell/haddock#480 from bgamari/sphinx Move documentation to ReStructuredText - - - - - 222e5920 by Ryan Scott at 2016-02-11T15:42:42-05:00 Collapse type/data family instances by default - - - - - a80ac03b by Ryan Scott at 2016-02-11T20:17:09-05:00 Ensure expanded family instances render correctly - - - - - 7f985231 by Ben Gamari at 2016-02-12T10:04:22+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - d4eda086 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Various cleanups - - - - - 79bee48d by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show kind signatures for type family variables Addresses GHC haskell/haddock#11588. - - - - - b2981d98 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show 'where ...' after closed type family Seems like we should ideally show the actual equations as well but that seems like it would be a fair amount of work - - - - - cfc0e621 by Ben Gamari at 2016-02-18T22:48:12+01:00 Merge pull request haskell/haddock#483 from bgamari/T11588 Fix GHC haskell/haddock#11588 This fixes GHC haskell/haddock#11588: * Show where ... after closed type families * Show kind signatures on type family type variables - - - - - 256e8a0d by Ben Gamari at 2016-02-18T23:15:39+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 32402036 by Richard Eisenberg at 2016-02-24T13:21:44-05:00 Follow-on changes to support RuntimeRep - - - - - 2b1c572d by Matthew Pickering at 2016-03-04T21:04:02+00:00 Remove unused functions - - - - - eb906f50 by Richard Eisenberg at 2016-03-13T21:17:20+01:00 Follow-on changes to support RuntimeRep (cherry picked from commit ab954263a793d8ced734459d6194a5d89214b66c) - - - - - 8c34ef34 by Richard Eisenberg at 2016-03-14T23:47:23-04:00 Changes due to fix for GHC#11648. - - - - - 0e022014 by Richard Eisenberg at 2016-03-15T14:06:45+01:00 Changes due to fix for GHC#11648. (cherry picked from commit bb994de1ab0c76d1aaf1e39c54158db2526d31f1) - - - - - ed3f78ab by Rik Steenkamp at 2016-04-02T22:20:36+01:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 - - - - - d3210042 by Rik Steenkamp at 2016-04-04T15:43:32+02:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 (cherry picked from commit 3ddcbd6b8e6884bd95028381176eb33bee6896fb) - - - - - 236eec90 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 692ee7e0 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. - - - - - 79619f57 by Ben Gamari at 2016-04-10T23:46:22+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. (cherry picked from commit c6d6a18d85e5e2d9bb5904e6919e8a8d7e31c4c5) - - - - - 3358ccb4 by Ben Gamari at 2016-04-10T23:47:27+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 264949b1 by Ben Gamari at 2016-04-16T17:50:23+02:00 Merge pull request haskell/haddock#482 from RyanGlScott/ghc-head Collapse type/data family instances by default - - - - - 478c483a by Ben Gamari at 2016-04-16T17:51:09+02:00 Merge pull request haskell/haddock#489 from mpickering/unused-functions Remove some unused functions - - - - - c94e55f0 by Ryan Scott at 2016-04-16T17:57:54+02:00 Collapse type/data family instances by default (cherry picked from commit 2da130a8db8f995c119b544fad807533236cf088) - - - - - 31e633d3 by Ryan Scott at 2016-04-16T17:58:06+02:00 Ensure expanded family instances render correctly (cherry picked from commit 1338b5d7c32939de6bbc31af0049477e4f847103) - - - - - 03e4d197 by Matthew Pickering at 2016-04-16T17:58:21+02:00 Remove unused functions (cherry picked from commit b89d1c2456bdb2d4208d94ded56155f7088a37d0) - - - - - ed4116f6 by Ben Gamari at 2016-04-20T10:46:57+02:00 ghc: Install files for needed --hyperlinked-source - - - - - 0be999c4 by Ben Gamari at 2016-04-20T11:37:54+02:00 ghc: Install files for needed --hyperlinked-source (cherry picked from commit 5c82c9fc2d21ddaae4a2470f1c375426968f19c6) - - - - - 4d17544c by Simon Peyton Jones at 2016-04-20T12:42:28+01:00 Track change to HsGroup This relates to a big GHC patch for Trac haskell/haddock#11348 - - - - - 1700a50d by Ben Gamari at 2016-05-01T13:19:27+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. - - - - - 0b7c8125 by Ben Gamari at 2016-05-01T13:21:43+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. (cherry picked from commit 609018dd09c4ffe27f9248b2d8b50f6196cd42b9) - - - - - af115ce0 by Ryan Scott at 2016-05-04T22:15:50-04:00 Render Haddocks for derived instances Currently, one can document top-level instance declarations, but derived instances (both those in `deriving` clauses and standalone `deriving` instances) do not enjoy the same privilege. This makes the necessary changes to the Haddock API to enable rendering Haddock comments for derived instances. This is part of a fix for Trac haskell/haddock#11768. - - - - - 76fa1edc by Ben Gamari at 2016-05-10T18:13:25+02:00 haddock-test: A bit of refactoring for debuggability - - - - - 7d4c4b20 by Ben Gamari at 2016-05-10T18:13:25+02:00 Create: Mark a comment as TODO - - - - - 2a6d0c90 by Ben Gamari at 2016-05-10T18:13:25+02:00 html-test: Update reference output - - - - - bd60913d by Ben Gamari at 2016-05-10T18:13:25+02:00 hypsrc-test: Fix reference file path in cabal file It appears the haddock insists on prefixing --hyperlinked-sourcer output with directory which the source appeared in. - - - - - c1548057 by Ben Gamari at 2016-05-10T18:22:12+02:00 doc: Update extra-source-files in Cabal file - - - - - 41d5bae3 by Ben Gamari at 2016-05-10T18:29:21+02:00 Bump versions - - - - - ca75b779 by Ben Gamari at 2016-05-11T16:03:44+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 4e3cfd62 by Ben Gamari at 2016-05-11T16:06:45+02:00 Merge remote-tracking branch 'RyanGlScott/ghc-head' into ghc-head - - - - - a2379970 by Ben Gamari at 2016-05-11T23:15:11+02:00 doc: Add clean targets - - - - - f275212e by Ben Gamari at 2016-05-11T23:15:14+02:00 doc: Add html as an all-target for ghc Otherwise the html documentation won't be installed for binary-dist. - - - - - 388fc0af by Ben Gamari at 2016-05-12T09:49:12+02:00 Update CHANGES - - - - - bad81ad5 by Ben Gamari at 2016-05-12T09:49:38+02:00 Version bump - - - - - c01688a7 by Ben Gamari at 2016-05-12T10:04:58+02:00 Revert "Version bump" This bump was a bit premature. This reverts commit 7b238d9c5be9b07aa2d10df323b5c7b8d1634dc8. - - - - - 7ed05724 by Ben Gamari at 2016-05-12T10:05:33+02:00 doc: Fix GHC clean rule Apparently GHC's build system doesn't permit wildcards in clean paths. - - - - - 5d9611f4 by Ben Gamari at 2016-05-12T17:43:50+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 653566b2 by Ben Gamari at 2016-05-14T09:57:31+02:00 Version bump to 2.17.2 - - - - - b355c439 by Ben Gamari at 2016-05-14T09:57:51+02:00 doc: Use `$(MAKE)` instead of `make` This is necessary to ensure we use gmake. - - - - - 8a18537d by Ben Gamari at 2016-05-14T10:15:45+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - b3290ef1 by Sebastian Meric de Bellefon at 2016-05-14T11:29:47-04:00 Fix haskell/haddock#303. Hide footer when printing The "Produced by Haddock" footer was overlapping the page's body when printing. This patch hides the footer with a css media rule. - - - - - b4a76f89 by Sebastian Meric de Bellefon at 2016-05-15T02:12:46-04:00 Fix haskell/haddock#280. Parsing of module header The initial newlines were counted as indentation spaces, thus disturbing the parsing of next lines - - - - - ba797c9e by Ben Gamari at 2016-05-16T14:53:46+02:00 doc: Vendorize alabaster Sphinx theme Alabaster is now the default sphinx theme and is a significant improvement over the previous default that it's worthproviding it when unavailable (e.g. Sphinx <1.3). - - - - - c9283e44 by Ben Gamari at 2016-05-16T14:55:17+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 1c9ea198 by Sebastian Méric de Bellefon at 2016-05-16T12:30:40-04:00 Merge pull request haskell/haddock#502 from Helkafen/master Fix haskell/haddock#303. Hide footer when printing - - - - - 33631016 by Ben Gamari at 2016-05-16T19:56:11+02:00 Revert "doc: Vendorize alabaster Sphinx theme" This ended up causes far too many issues to be worthwhile. We'll just have to live with inconsistent haddock documentation. This reverts commit cec21957001143794e71bcd9420283df18e7de40. - - - - - 93317d26 by Ben Gamari at 2016-05-16T19:56:11+02:00 cabal: Fix README path - - - - - c8695b22 by Ben Gamari at 2016-05-16T19:58:51+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 0b50eaaa by Ben Gamari at 2016-05-16T21:02:08+02:00 doc: Use whichever theme sphinx deems appropriate - - - - - 857c1c9c by Ben Gamari at 2016-05-16T21:07:08+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 15fc5637 by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Remove redundant imports - - - - - 132ddc6a by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Better debug output For tracking down haskell/haddock#505 - - - - - 2252a149 by Ben Gamari at 2016-05-22T12:43:59+02:00 Don't consider default class ops when looking for decls When we are looking for an operation within a class we don't care about `default`-type declarations. This was the cause of haskell/haddock#505. - - - - - 4886b2ec by Oleg Grenrus at 2016-05-24T16:19:48+03:00 UnfelpfulSpan line number omitted Kind of resolves https://github.com/haskell/haddock/issues/508 - - - - - a4befd36 by Oleg Grenrus at 2016-05-24T16:53:35+03:00 Change Hyperlinked lexer to know about DataKinds ticks - - - - - f45cb52e by David Feuer at 2016-05-24T18:48:53-04:00 Make parser state a newtype Previously, it was `data` wrapping a `Maybe`, which seems a bit silly. Obviously, this can be changed back if anyone wants to add more fields some day. - - - - - 05013dd7 by Sebastian Meric de Bellefon at 2016-05-24T22:03:55-04:00 remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) Frames are a bit broken, ignored by Hackage, and considered obsolete in general. This patch disables frames generation. The mini_*.html files are still used in the synopsis. - - - - - b8163a88 by Ben Gamari at 2016-05-25T14:44:15+02:00 Merge pull request haskell/haddock#507 from bgamari/T505 Fix haskell/haddock#505 - - - - - ea1b30c6 by Sebastian Meric de Bellefon at 2016-05-25T14:17:00-04:00 Update CHANGES - - - - - eddfc258 by Sebastian Méric de Bellefon at 2016-05-25T15:17:40-04:00 Merge pull request haskell/haddock#514 from Helkafen/frames remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) - - - - - 0e506818 by Alex Biehl at 2016-05-26T12:43:09+02:00 Remove misplaced haddock comment - - - - - a07d28c0 by Ben Gamari at 2016-05-27T11:34:59+02:00 Merge pull request haskell/haddock#515 from alexbiehl/master Remove misplaced haddock comment - - - - - 9001d267 by Ben Gamari at 2016-05-27T11:35:46+02:00 Merge pull request haskell/haddock#513 from treeowl/newtype-since Make parser state a newtype - - - - - 74e1a018 by Sebastian Méric de Bellefon at 2016-05-28T17:28:15-04:00 Merge pull request haskell/haddock#504 from Helkafen/issue-280 Fix haskell/haddock#280. Parsing of module header - - - - - 37557f4f by Alan Zimmerman at 2016-05-29T23:36:50+02:00 Matching changes for haskell/haddock#12105 - - - - - 7d09e5d6 by Sebastian Meric de Bellefon at 2016-06-03T18:07:48-04:00 Version bumps (2.17.3, 1.4.2) - - - - - 85b4bc15 by Sebastian Méric de Bellefon at 2016-06-06T18:35:13-04:00 Merge pull request haskell/haddock#521 from Helkafen/master Version bumps (2.17.3, 1.4.2) - - - - - e95f0dee by Sebastian Meric de Bellefon at 2016-06-06T19:11:35-04:00 publish haddock-test library - - - - - 4de40586 by Sebastian Méric de Bellefon at 2016-06-06T20:26:30-04:00 Merge pull request haskell/haddock#512 from phadej/oleg-fixes Fixes for haskell/haddock#508 and haskell/haddock#510 - - - - - ddfd0789 by Dominic Steinitz at 2016-06-09T09:27:28+01:00 Documentation for LaTeX markup. - - - - - 697a503a by Dominic Steinitz at 2016-06-09T09:33:59+01:00 Fix spelling mistake. - - - - - 246f6fff by Dominic Steinitz at 2016-06-09T09:37:15+01:00 Camel case MathJax. - - - - - 4684bd23 by Dominic Steinitz at 2016-06-09T09:44:53+01:00 Fix math typo and add link. - - - - - f20c037c by Simon Peyton Jones at 2016-06-13T18:26:03+01:00 Follow changes to LHsSigWcType - - - - - 0c58996d by Simon Peyton Jones at 2016-06-15T12:56:01+01:00 Follow GHC re-adding FunTy - - - - - 401b5ca7 by Sebastian Méric de Bellefon at 2016-06-15T12:16:47-04:00 Merge pull request haskell/haddock#525 from idontgetoutmuch/master Documentation for LaTeX markup. - - - - - 92d263b7 by Sebastian Méric de Bellefon at 2016-06-15T12:17:29-04:00 Merge pull request haskell/haddock#522 from Helkafen/master publish haddock-test library - - - - - 0953a2ca by Sebastian Meric de Bellefon at 2016-06-16T00:46:46-04:00 Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 65453e14 by Ben Gamari at 2016-06-16T11:16:32+02:00 ocean: Ensure that synopsis fully covers other content Previously MathJax content was being rendered on top of the synopsis due to ambiguous z-ordering. Here we explicitly give the synopsis block a higher z-index to ensure it is rendered on top. Fixes haskell/haddock#531. - - - - - 68e411a1 by Sebastian Méric de Bellefon at 2016-06-16T23:34:39-04:00 Merge pull request haskell/haddock#534 from bgamari/T531 ocean: Ensure that synopsis fully covers other content - - - - - fad6491b by Sebastian Méric de Bellefon at 2016-06-18T23:57:20-04:00 Merge pull request haskell/haddock#533 from Helkafen/master Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 6108e21b by Sebastian Meric de Bellefon at 2016-06-22T23:08:28-04:00 do not create empty src directory Fix haskell/haddock#536. - - - - - 1ef23823 by Sebastian Méric de Bellefon at 2016-06-24T00:04:48-04:00 Merge pull request haskell/haddock#537 from Helkafen/master do not create empty src directory - - - - - 966baa96 by Omari Norman at 2016-06-29T21:59:34-04:00 Add $ as a special character If this character is not escaped, documentation built with Haddock 2.17.2 will fail. This was not an issue with 2.16 series, which causes builds to fail and there is nothing in the docs or error message giving a clue about why builds that used to succeed now don't. - - - - - 324adb60 by Ben Gamari at 2016-07-01T12:18:51+02:00 GhcUtils: Changes for multi-pattern signatures - - - - - d7571675 by Ömer Sinan Ağacan at 2016-07-21T13:30:47+02:00 Add support for unboxed sums - - - - - 29d0907b by Simon Marlow at 2016-07-22T13:55:48+01:00 Disable NFData instances for GHC types when GHC >= 8.2 - - - - - 702d95f3 by Simon Marlow at 2016-08-02T15:57:30+02:00 Disable NFData instances for GHC types when GHC >= 8.0.2 (cherry picked from commit a3309e797c42dae9bccdeb17ce52fcababbaff8a) - - - - - f4fa79c3 by Ben Gamari at 2016-08-07T13:51:18+02:00 ghc.mk: Don't attempt to install html/frames.html The frames business has been removed. - - - - - 9cd63daf by Ben Gamari at 2016-08-07T13:51:40+02:00 Haddock.Types: More precise version guard This allows haddock to be built with GHC 8.0.2 pre-releases. - - - - - f3d7e03f by Mateusz Kowalczyk at 2016-08-29T20:47:45+01:00 Merge pull request haskell/haddock#538 from massysett/master Add $ as a special character - - - - - 16dbf7fd by Bartosz Nitka at 2016-09-20T19:44:04+01:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 - - - - - 7c31c1ff by Bartosz Nitka at 2016-09-27T17:32:22-04:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 (cherry picked from commit 073d899a8f94ddec698f617a38d3420160a7fd0b) - - - - - 33a90dce by Ryan Scott at 2016-09-30T20:53:41-04:00 Haddock changes for T10598 See https://ghc.haskell.org/trac/ghc/ticket/10598 - - - - - 1f32f7cb by Ben Gamari at 2016-10-13T20:01:26-04:00 Update for refactoring of NameCache - - - - - 1678ff2e by Ben Gamari at 2016-11-15T17:42:48-05:00 Bump upper bound on base - - - - - 9262a7c5 by Alan Zimmerman at 2016-12-07T21:14:28+02:00 Match changes in GHC wip/T3384 branch - - - - - ac0eaf1a by Ben Gamari at 2016-12-09T09:48:41-05:00 haddock-api: Don't use stdcall calling convention on 64-bit Windows See GHC haskell/haddock#12890. - - - - - 04afe4f7 by Alan Zimmerman at 2016-12-12T20:07:21+02:00 Matching changes for GHC wip/T12942 - - - - - e1d1701d by Ben Gamari at 2016-12-13T16:50:41-05:00 Bump base upper bound - - - - - 3d3eacd1 by Alan Zimmerman at 2017-01-10T16:59:38+02:00 HsIParamTy now has a Located name - - - - - 7dbceefd by Kyrill Briantsev at 2017-01-12T13:23:50+03:00 Prevent GHC API from doing optimization passes. - - - - - d48d1e33 by Richard Eisenberg at 2017-01-19T08:41:41-05:00 Upstream changes re levity polymorphism - - - - - 40c25ed6 by Alan Zimmerman at 2017-01-26T15:16:18+02:00 Changes to match haskell/haddock#13163 in GHC - - - - - 504f586d by Ben Gamari at 2017-02-02T17:19:37-05:00 Kill remaining static flags - - - - - 49147ea0 by Justus Adam at 2017-03-02T15:33:34+01:00 Adding MDoc to exports of Documentation.Haddock - - - - - 1cfba9b4 by Justus Adam at 2017-03-09T11:41:44+01:00 Also exposing toInstalledIface - - - - - 53f0c0dd by Ben Gamari at 2017-03-09T13:10:08-05:00 Bump for GHC 8.3 - - - - - c7902d2e by Ben Gamari at 2017-03-09T23:46:02-05:00 Bump for GHC 8.2 - - - - - 4f3a74f8 by Ben Gamari at 2017-03-10T10:21:55-05:00 Merge branch 'ghc-head' - - - - - e273b72f by Richard Eisenberg at 2017-03-14T13:34:04-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - 6ec3d436 by Richard Eisenberg at 2017-03-14T15:15:52-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - eee3cda1 by Ben Gamari at 2017-03-15T15:19:59-04:00 Adapt to EnumSet - - - - - 017cf58e by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 736d6773 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 475f84a0 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 13240b53 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - cd16d529 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 3bea97ae by Edward Z. Yang at 2017-03-15T22:50:46-07:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b2b051ce by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 0f082795 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 20ef63c9 by Edward Z. Yang at 2017-03-22T13:48:12-07:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 45692dcb by Edward Z. Yang at 2017-03-22T14:11:25-07:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4eae8caf by Ben Gamari at 2017-03-23T09:25:33-04:00 Merge commit '240bc38b94ed2d0af27333b23392d03eeb615e82' into HEAD - - - - - 0bbe03f5 by Ben Gamari at 2017-03-23T09:27:28-04:00 haddock-api: Bump bound on GHC - - - - - 65f3ac9d by Alex Biehl at 2017-03-23T17:36:11+01:00 Merge pull request haskell/haddock#581 from JustusAdam/master Adding more exports to Documentation.Haddock - - - - - 37d49a47 by Alex Biehl at 2017-03-23T17:39:14+01:00 Merge pull request haskell/haddock#568 from awson/ghc-head Prevent GHC API from doing optimization passes. - - - - - 1ed047e4 by Brian Huffman at 2017-03-23T17:45:58+01:00 Print any user-supplied kind signatures on type parameters. This applies to type parameters on data, newtype, type, and class declarations, and also to forall-bound type vars in type signatures. - - - - - 1b78ca5c by Brian Huffman at 2017-03-23T17:45:58+01:00 Update test suite to expect kind annotations on type parameters. - - - - - a856b162 by Alex Biehl at 2017-03-23T17:49:32+01:00 Include travis build indication badge - - - - - 8e2e2c56 by Ben Gamari at 2017-03-23T17:20:08-04:00 haddock-api: Bump bound on GHC - - - - - 4d2d9995 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 26d6c150b31bc4580ab17cfd07b6e7f9afe10737) - - - - - a650e20f by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 930cfbe58e2e87f5a4d431d89a3c204934e6e858) - - - - - caa282c2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 2067a2d0afa9cef381d26fb7140b67c62f433fc0) - - - - - 49684884 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 0671abfe7e8ceae2269467a30b77ed9d9656e2cc) - - - - - 4dcfeb1a by Edward Z. Yang at 2017-03-23T17:20:08-04:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 3d77b373dd5807d5d956719dd7c849a11534fa6a) - - - - - 74dd19d2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 94610e9b446324f4231fa6ad4c6ac51e4eba8c0e) - - - - - a9b19a23 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 6cc832dfb1de6088a4abcaae62b25a7e944d55c3) - - - - - d3631064 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit bf3c4d72a0fda38561376eac7eda216158783267) - - - - - ef2148fc by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 07b88c5d4e79b87a319fbb08f8ea01dbb41063c1) - - - - - 2f29518b by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 4eb765ca4205c79539d60b7afa9b7e261a4a49fe) - - - - - 37de047d by Phil Ruffwind at 2017-04-03T11:57:14+02:00 Update MathJax URL MathJax is shutting down their CDN: https://www.mathjax.org/cdn-shutting-down/ They recommend migrating to cdnjs. - - - - - e9d24ba8 by David C. Turner at 2017-04-03T14:58:01+02:00 Add highlight for :target to ocean.css - - - - - 4819a202 by Alex Biehl at 2017-04-11T19:36:48+02:00 Allow base-4.10 for haddock-test - - - - - 44cec69c by Alex Biehl at 2017-04-11T19:39:22+02:00 cabal.project for haddock-api, haddock-library and haddock-test - - - - - 935d0f6a by Alex Biehl at 2017-04-11T19:46:29+02:00 Move dist scripts to scripts/ - - - - - 128e150c by Alex Biehl at 2017-04-11T20:34:46+02:00 Add haddock to cabal.project - - - - - cc8e08ea by Alex Biehl at 2017-04-11T20:35:08+02:00 Read files for hyperlinker eagerly This also exposes Documentation.Haddock.Utf8 - - - - - 152dda78 by Alex Biehl at 2017-04-11T20:37:06+02:00 Explicit import list ofr Control.DeepSeq in Haddock.Interface.Create - - - - - 501b33c4 by Kyrill Briantsev at 2017-04-11T21:01:42+02:00 Prevent GHC API from doing optimization passes. - - - - - c9f3f5ff by Alexander Biehl at 2017-04-12T16:36:53+02:00 Add @alexbiehl as maintaner - - - - - 76f214cc by Alex Biehl at 2017-04-13T07:27:18+02:00 Disable doctest with ghc-8.3 Currently doctest doesn't support ghc-head - - - - - 46b4f5fc by Edward Z. Yang at 2017-04-22T20:38:26-07:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f0555235 by Alex Biehl at 2017-04-25T10:08:48+02:00 Travis: Use ghc-8.2.1 on master - - - - - 966ea348 by Alex Biehl at 2017-04-25T10:32:01+02:00 Travis: Verbose cabal output cf. https://travis-ci.org/haskell/haddock/jobs/225512194#L377 - - - - - 36972bcd by Alex Biehl at 2017-04-25T10:40:43+02:00 Use travis_retry for cabal invocations - - - - - b3a09d2c by Alex Biehl at 2017-04-25T17:02:20+02:00 Use new MathJax URL in html-test 18ed871afb82560d5433b2f53e31b4db9353a74e switched to a new MathJax URL but didn't update the tests. - - - - - ae331e5f by Alexander Biehl at 2017-04-25T17:02:20+02:00 Expand signatures for class declarations - - - - - e573c65a by Alexander Biehl at 2017-04-25T17:02:20+02:00 Hoogle: Correctly print classes with associated data types - - - - - 3fc6be9b by Edward Z. Yang at 2017-04-25T17:02:20+02:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit a0c4790e15a2d3fab8d830eee8fcd639fe6d39c9) - - - - - 6725c060 by Herbert Valerio Riedel at 2017-04-25T17:02:20+02:00 `html-test --accept` deltas to reference samples - - - - - 7d444d61 by Alex Biehl at 2017-04-26T07:13:50+02:00 Remove anything related to obsolete frames mode - - - - - b888972c by Alex Biehl at 2017-04-26T07:49:10+02:00 Cherry-picked remaining commits from haddock-2.17.4-release (#603) * Release haddock/haddock-api 2.17.4 and haddock-library 1.4.3 * Set version bounds for haddock-library NB: This allows GHC 8.2.1's base * Set version bounds for haddock & haddock-api The version bounds support GHC 8.2 * Merge (temporary) v2.17.3 branch into v2.17 This allows us to delete the v2.17.3 branch * Fixup changelog * Pin down haddock-api to a single version as otherwise `haddock`'s package version has no proper meaning * fix source-repo spec for haddock-api - - - - - 4161099b by Alex Biehl at 2017-04-26T11:11:20+02:00 Update changelog to reflect news in HEAD - - - - - eed72cb8 by Alex Biehl at 2017-04-26T11:11:20+02:00 Markdownify changelog - - - - - 5815cea1 by Alex Biehl at 2017-04-26T11:32:33+02:00 Bump to 2.18.0 (#605) - - - - - a551d558 by Alex Biehl at 2017-04-29T22:00:25+02:00 Update attoparsec-0.12.1.1 to attoparsec-0.13.1.0 - - - - - ea164a8d by Sergey Vinokurov at 2017-04-29T22:42:36+02:00 Improve error message - - - - - 2e10122f by Alex Biehl at 2017-04-30T10:07:46+02:00 Correctly remember collapsed sections (#608) Now the "collapsed" cookie stores which sections have changed state instead of which are collapsed. - - - - - f9b24d99 by Alex Biehl at 2017-05-01T17:40:36+02:00 Lazily decode docMap and argMap (#610) These are only used in case of a doc reexport so most of the time decoding these is wasted work. - - - - - 2372af62 by Alex Biehl at 2017-05-01T21:59:23+02:00 Fix Binary instance for InstalledInterface (#611) (#610) introduced lazy decoding for docs from InstalledInterface but forgot to remove the original calls to get and put_ - - - - - 6c633c13 by Nathan Collins at 2017-05-11T11:47:55+02:00 Improve documenation of Haddock markup (#614) * Improve documentation of Haddock markup. - document that Haddock supports inferring types top-level functions with without type signatures, but also explain why using this feature is discouraged. Looks like this feature has been around since version 2.0.0.0 in 2008! - rework the "Module description" section: - move the general discussion of field formatting to the section intro and add examples illustrating the prose for multiline fields. - mention that newlines are preserved in some multiline fields, but not in others (I also noticed that commas in the `Copyright` field are not preserved; I'll look into this bug later). - add a subsection for the module description fields documentation, and put the field keywords in code formatting (double back ticks) instead of double quotes, to be consistent with the typesetting of keywords in other parts of the documentation. - mention that "Named chunks" are not supported in the long-form "Module description" documentation. - fix formatting of keywords in the "Module attributes" section. Perhaps these errors were left over from an automatic translation to ReST from some other format as part of the transition to using Sphinx for Haddock documentation? Also, add a missing reference here; it just said "See ?"! - update footnote about special treatment for re-exporting partially imported modules not being implemented. In my tests it's not implemented at all -- I tried re-exporting both `import B hiding (f)` and `import B (a, b)` style partial imports, and in both cases got the same result as with full imports `import B`: I only get a module reference. * Rework the `Controlling the documentation structure` section. My main goal was to better explain how to use Haddock without an export list, since that's my most common use case, but I hope I improved the section overall: - remove the incomplete `Omitting the export list` section and fold it into the other sections. In particular, summarize the differences between using and not using an export list -- i.e. control over what and in what order is documented -- in the section lead. - add "realistic" examples that use the structure markup, both with and without an export list. I wanted a realistic example here to capture how it can be useful to explain the relationship between a group of functions in a section, in addition to documenting their individual APIs. - make it clear that you can associate documentation chunks with documentation sections when you aren't using an export list, and that doing it in the most obvious way -- i.e. with `-- |`, as you can in the export list -- doesn't work without an export list. It took me a while to figure this out the first time, since the docs didn't explain it at all before. - add a "no export list" example to the section header section. - add more cross references. * Add examples of gotchas for markup in `@...@`. I'm not sure this will help anyone, since I think most people first learn about `@...@` by reading other people's Haddocks, but I've documented the mistakes which I've made and then gotten confused by. * Use consistent Capitalization of Titles. Some titles were in usual title caps, and others only had the first word capitalized. I chose making them all use title caps because that seems to make the cross references look better. - - - - - d4734f45 by Ben Gamari at 2017-05-12T20:36:08+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 93883f37 by Alex Biehl at 2017-05-12T21:02:33+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 5b8f179c by Alex Biehl at 2017-05-13T12:48:10+02:00 Consequently use inClass and notInClass in haddock-library (#617) These allow attoparsec to do some clever lookup optimization - - - - - 77984b82 by Doug Wilson at 2017-05-27T17:37:38+02:00 Don't enable compilation for template haskell (#624) This is no longer necessary after ghc commit 53c78be0aab76a3107c4dacbb1d177afacdd37fa - - - - - 5a3de2b4 by Doug Wilson at 2017-05-27T19:54:53+02:00 Improve Syb code (#621) Specialize.hs and Ast.hs are modified to have their Syb code not recurse into Name or Id in HsSyn types. Specialize.hs is refactored to have fewer calls to Syb functions. Syb.hs has some foldl calls replaced with foldl' calls. There is still a lot of performance on the floor of Ast.hs. The RenamedSource is traversed many times, and lookupBySpan is very inefficient. everywhereBut and lookupBySpan dominate the runtime whenever --hyperlinked-source is passed. - - - - - 3d35a949 by Alex Biehl at 2017-05-30T19:01:37+02:00 Clear fixme comment (#625) - - - - - 2a44bd0c by Alex Biehl at 2017-05-30T19:02:12+02:00 Make haddock-library and haddock-api warning free (#626) - - - - - bd1a0e42 by Alex Biehl at 2017-06-01T10:40:33+02:00 Include `driver-test/*.hs` sdist (#630) This lead to haskell/haddock#629. - - - - - 184a3ab6 by Doug Wilson at 2017-06-03T12:02:08+02:00 Disable pattern match warnings (#628) This disables the pattern match checker which can be very expensive in some cases. The disabled warnings include: * Opt_WarnIncompletePatterns * Opt_WarnIncompleteUniPatterns * Opt_WarnIncompletePatternsRecUpd * Opt_WarnOverlappingPatterns - - - - - 0cf68004 by Alex Biehl at 2017-06-03T20:37:28+02:00 Allow user defined signatures for pattern synonyms (#631) - - - - - 7f51a58a by Alex Biehl at 2017-06-04T11:56:38+02:00 Use NameSet for isExported check (#632) - - - - - d8f044a9 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Match new AST as per GHC wip/new-tree-one-param See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow - - - - - da1254e3 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Rename extension index tags - - - - - 538c7514 by Christiaan Baaij at 2017-06-09T08:26:43+02:00 Haddock support for bundled pattern synonyms (#627) * Haddock support for bundled pattern synonyms * Add fixities to bundled pattern synonyms * Add bundled pattern synonyms to the synopsis * Store bundled pattern fixities in expItemFixities * Add test for bundled pattern synonyms * Stop threading fixities * Include bundled pattern synonyms for re-exported data types Sadly, fixity information isn't found for re-exported data types * Support for pattern synonyms * Modify tests after haskell/haddock#631 * Test some reexport variations * Also lookup bundled pattern synonyms from `InstalledInterface`s * Check isExported for bundled pattern synonyms * Pattern synonym is exported check * Always look for pattern synonyms in the current module Another overlooked cornercase * Account for types named twice in export lists Also introduce a fast function for nubbing on a `Name` and use it throughout the code base. * correct fixities for reexported pattern synonyms * Fuse concatMap and map * Remove obsolete import * Add pattern synonyms to visible exports * Fix test * Remove corner case - - - - - a050bffd by Doug Wilson at 2017-06-21T09:27:33+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#636) There is some performance improvement. GHC compiler: | version | bytes allocated | cpu_seconds --------------------------------- | before | 56057108648 | 41.0 | after | 51592019560 | 35.1 base: | version | bytes allocated | cpu_seconds --------------------------------- | before | 25174011784 | 14.6 | after | 23712637272 | 13.1 Cabal: | version | bytes allocated | cpu_seconds --------------------------------- | before | 18754966920 | 12.6 | after | 18198208864 | 11.6 - - - - - 5d06b871 by Doug Wilson at 2017-06-22T20:23:29+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#639) * Use new function getNameToInstancesIndex instead of tcRnGetInfo There is some significant performance improvement in the ghc testsuite. haddock.base: -23.3% haddock.Cabal: -16.7% haddock.compiler: -19.8% * Remove unused imports - - - - - b11bb73a by Alex Biehl at 2017-06-23T14:44:41+02:00 Lookup fixities for reexports without subordinates (#642) So we agree that reexported declarations which do not have subordinates (for example top-level functions) shouldn't have gotten fixities reexported according to the current logic. I wondered why for example Prelude.($) which is obviously reexported from GHC.Base has fixities attached (c.f. http://hackage.haskell.org/package/base-4.9.1.0/docs/Prelude.html#v:-36-). The reason is this: In mkMaps we lookup all the subordinates of top-level declarations, of course top-level functions don't have subordinates so for them the resulting list is empty. In haskell/haddock#644 I established the invariant that there won't be any empty lists in the subordinate map. Without the patch from haskell/haddock#642 top-level functions now started to fail reexporting their fixities. - - - - - d2a6dad6 by Alex Biehl at 2017-06-23T18:30:45+02:00 Don't include names with empty subordinates in maps (#644) These are unecessary anyway and just blow up interface size - - - - - 69c2aac4 by Alex Biehl at 2017-06-29T19:54:49+02:00 Make per-argument docs for class methods work again (#648) * Make per-argument docs for class methods work again * Test case - - - - - c9448d54 by Bartosz Nitka at 2017-07-02T12:12:01+02:00 Fix haddock: internal error: links: UnhelpfulSpan (#561) * Fix haddock: internal error: links: UnhelpfulSpan This fixes haskell/haddock#554 for me. I believe this is another fall out of `wildcard-refactor`, like haskell/haddock#549. * Comment to clarify why we take the methods name location - - - - - d4f29eb7 by Alex Biehl at 2017-07-03T19:43:04+02:00 Document record fields when DuplicateRecordFields is enabled (#649) - - - - - 9d6e3423 by Yuji Yamamoto at 2017-07-03T22:37:58+02:00 Fix test failures on Windows (#564) * Ignore .stack-work * Fix for windows: use nul instead of /dev/null * Fix for windows: canonicalize line separator * Also normalize osx line endings - - - - - 7d81e8b3 by Yuji Yamamoto at 2017-07-04T16:13:12+02:00 Avoid errors on non UTF-8 Windows (#566) * Avoid errors on non UTF-8 Windows Problem ==== haddock exits with errors like below: `(1)` ``` haddock: internal error: <stderr>: hPutChar: invalid argument (invalid character) ``` `(2)` ``` haddock: internal error: Language\Haskell\HsColour\Anchors.hs: hGetContents: invalid argument (invalid byte sequence) ``` `(1)` is caused by printing [the "bullet" character](http://www.fileformat.info/info/unicode/char/2022/index.htm) onto stderr. For example, this warning contains it: ``` Language\Haskell\HsColour\ANSI.hs:62:10: warning: [-Wmissing-methods] • No explicit implementation for ‘toEnum’ • In the instance declaration for ‘Enum Highlight’ ``` `(2)` is caused when the input file of `readFile` contains some Unicode characters. In the case above, '⇒' is the cause. Environment ---- OS: Windows 10 haddock: 2.17.3 GHC: 8.0.1 Solution ==== Add `hSetEncoding handle utf8` to avoid the errors. Note ==== - I found the detailed causes by these changes for debugging: - https://github.com/haskell/haddock/commit/8f29edb6b02691c1cf4c479f6c6f3f922b35a55b - https://github.com/haskell/haddock/commit/1dd23bf2065a1e1f2c14d0f4abd847c906b4ecb4 - These errors happen even after executing `chcp 65001` on the console. According to the debug code, `hGetEncoding stderr` returns `CP932` regardless of the console encoding. * Avoid 'internal error: <stderr>: hPutChar: invalid argument (invalid character)' non UTF-8 Windows Better solution for 59411754a6db41d17820733c076e6a72bcdbd82b's (1) - - - - - eded67d2 by Alex Biehl at 2017-07-07T19:17:15+02:00 Remove redudant import warning (#651) - - - - - 05114757 by Alex Biehl at 2017-07-08T00:33:12+02:00 Avoid missing home module warning (#652) * Avoid missing home module warning * Update haddock-library.cabal - - - - - e9cfc902 by Bryn Edwards at 2017-07-17T07:51:20+02:00 Fix haskell/haddock#249 (#655) - - - - - eb02792b by Herbert Valerio Riedel at 2017-07-20T09:09:15+02:00 Fix compilation of lib:haddock-library w/ GHC < 8 - - - - - 9200bfbc by Alex Biehl at 2017-07-20T09:20:38+02:00 Prepare 2.18.1 release (#657) - - - - - 46ddd22c by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Tweak haddock-api.cabal for pending release - - - - - 85e33d29 by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Avoid trivial use of LambdaCase otherwise we can't test w/ e.g. GHC 7.4.2 - - - - - 3afb4bfe by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Refactor .cabal to use sub-lib for vendored lib A practical benefit is that we can control the build-depends and also avoid some recompilation between library and test-suite. - - - - - e56a552e by Herbert Valerio Riedel at 2017-07-20T10:17:48+02:00 haddock-api: add changelog pointing to haddock's changelog This addresses https://github.com/haskell/haddock/issues/638#issuecomment-309283297 - - - - - 2222ff0d by Herbert Valerio Riedel at 2017-07-20T10:19:56+02:00 Drop obsolete/misleading `stability: experimental` This .cabal property has long been considered obsolete - - - - - 9b882905 by Alex Biehl at 2017-07-20T11:25:54+02:00 Beef up haddock description (#658) * Beef up haddock description * Handle empty lines - - - - - bb60e95c by Herbert Valerio Riedel at 2017-07-20T12:08:53+02:00 Import @aisamanra's Haddock cheatsheet from https://github.com/aisamanra/haddock-cheatsheet - - - - - 0761e456 by Herbert Valerio Riedel at 2017-07-20T12:12:55+02:00 Add cheatsheet to haddock.cabal - - - - - 2ece0f0f by Herbert Valerio Riedel at 2017-07-20T12:18:38+02:00 Mention new-build in README - - - - - 947b7865 by Herbert Valerio Riedel at 2017-07-20T12:32:16+02:00 Update README Also improves markup and removes/fixes redundant/obsolete parts [skip ci] - - - - - 785e09ad by Alex Biehl at 2017-07-27T07:28:57+02:00 Bump haddock to 2.18.2, haddock-library to 1.4.5 - - - - - e3ff1ca3 by Alex Biehl at 2017-07-31T20:15:32+02:00 Move `DocMarkup` from haddock-api to haddock-library (#659) * Move `DocMarkup` from haddock-api to haddock-library * Move more markup related functions * Markup module * CHANGELOG - - - - - cda7c20c by Alex Biehl at 2017-07-31T20:35:49+02:00 Fixup haddock - - - - - 583b6812 by Alex Biehl at 2017-07-31T21:20:45+02:00 Changelog for haddock-library - - - - - bac6a0eb by Alex Biehl at 2017-07-31T21:50:24+02:00 Prepare haddock-library-1.4.5 release - - - - - 58ce6877 by Moritz Drexl at 2017-08-05T16:44:40+02:00 Fix renaming after instance signature specializing (#660) * rework rename * Add regression test for Bug 613 * update tests * update changelog - - - - - b8137ec8 by Tim Baumann at 2017-08-06T11:33:38+02:00 Fix: Generate pattern signatures for constructors exported as patterns (#663) * Fix pretty-printing of pattern signatures Pattern synonyms can have up to two contexts, both having a different semantic meaning: The first holds the constraints required to perform the matching, the second contains the constraints provided by a successful pattern match. When the first context is empty but the second is not it is necessary to render the first, empty context. * Generate pattern synonym signatures for ctors exported as patterns This fixes haskell/haddock#653. * Simplify extractPatternSyn It is not necessary to generate the simplest type signature since it will be simplified when pretty-printed. * Add changelog entries for PR haskell/haddock#663 * Fix extractPatternSyn error message - - - - - d037086b by Alex Biehl at 2017-08-06T12:43:25+02:00 Bump haddock-library - - - - - 99d7e792 by Alex Biehl at 2017-08-06T12:44:07+02:00 Bump haddock-library in haddock-api - - - - - 94802a5b by Alex Biehl at 2017-08-06T13:18:02+02:00 Provide --show-interface option to dump interfaces (#645) * WIP: Provide --show-interface option to dump interfaces Like ghcs own --show-iface this flag dumps a binary interface file to stdout in a human (and machine) readable fashion. Currently it uses json as output format. * Fill all the jsonNull stubs * Rework Bifunctor instance of DocH, update changelog and documentation * replace changelog, bring DocMarkupH doc back * Update CHANGES.md * Update CHANGES.md * Move Control.Arrow up It would result in unused import if the Bifunctor instance is not generated. - - - - - c662e476 by Ryan Scott at 2017-08-14T21:00:21-04:00 Adapt to haskell/haddock#14060 - - - - - b891eb73 by Alex Biehl at 2017-08-16T08:24:48+02:00 Bifoldable and Bitraversable for DocH and MetaDoc - - - - - 021bb56c by Alex Biehl at 2017-08-16T09:06:40+02:00 Refactoring: Make doc renaming monadic This allows us to later throw warnings if can't find an identifier - - - - - 39fbf022 by Alex Biehl at 2017-08-19T20:35:27+02:00 Hyperlinker: Avoid linear lookup in enrichToken (#669) * Make Span strict in Position * Hyperlinker: Use a proper map to enrich tokens - - - - - e13baedd by Alex Biehl at 2017-08-21T20:05:42+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 27dd6e87 by Alex Biehl at 2017-08-21T22:06:35+02:00 Drop Avails from export list - - - - - 86b247e2 by Alex Biehl at 2017-08-22T08:44:22+02:00 Bump ghc version for haddock-api tests - - - - - d4607ca0 by Alex Biehl at 2017-08-22T08:45:17+02:00 Revert "Drop Avails from export list" This reverts commit a850ba86d88a4fb9c0bd175453a2580e544e3def. - - - - - c9c54c30 by Alex Biehl at 2017-08-22T09:26:01+02:00 IntefaceFile version - - - - - a85b7c02 by Ben Gamari at 2017-08-22T09:29:52-04:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 34e976f5 by Ben Gamari at 2017-08-22T17:40:06+02:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 577abf06 by Ryan Scott at 2017-08-23T14:47:29-04:00 Update for haskell/haddock#14131 - - - - - da68fc55 by Florian Eggenhofer at 2017-08-27T18:21:56+02:00 Generate an index for package content search (#662) Generate an index for package content search - - - - - 39e62302 by Alex Biehl at 2017-08-27T18:50:16+02:00 Content search for haddock html doc - - - - - 91fd6fb2 by Alex Biehl at 2017-08-28T18:39:58+02:00 Fix tests for content search - - - - - b4a3798a by Alex Biehl at 2017-08-28T18:44:08+02:00 Add search button to #page-menu - - - - - 25a7ca65 by Alex Biehl at 2017-08-28T18:47:43+02:00 Load javascript below the fold - - - - - 8d323c1a by Alex Biehl at 2017-08-28T18:49:22+02:00 Accept tests - - - - - c5dac557 by Alex Biehl at 2017-08-28T19:14:55+02:00 Content search css - - - - - 89a5af57 by Paolo Veronelli at 2017-08-29T07:42:13+02:00 Removed `nowrap` for interface method sigs (#674) with nowrap the interfaces method sigs would expand at libitum - - - - - a505f6f7 by Alex Biehl at 2017-08-29T08:05:33+02:00 Include subordinates in content index - - - - - 4bb698c4 by Alexander Biehl at 2017-08-29T11:40:19+02:00 QuickNav: Make docbase configurable - - - - - c783bf44 by Alexander Biehl at 2017-08-29T11:48:36+02:00 QuickNav: Also use baseUrl for doc-index.json request - - - - - 47017510 by Alex Biehl at 2017-08-29T17:56:47+02:00 Fix test fallout (again) - - - - - 924fc318 by Alex Biehl at 2017-08-30T09:24:56+02:00 Write meta.json when generating html output (#676) - - - - - 717dea52 by Alex Biehl at 2017-09-01T09:20:34+02:00 Use relative URL when no docBaseUrl given - - - - - e5d85f3b by Alex Biehl at 2017-09-01T09:35:19+02:00 Add missing js files to data-files (#677) - - - - - 95b9231a by Alex Biehl at 2017-09-01T11:01:36+02:00 Rename "Search" tab to "Quick Jump" - - - - - da0ead0b by Alex Biehl at 2017-09-01T13:03:49+02:00 Make trigger link configurable (#678) QuickNav: Configurable show/hide trigger - - - - - de7da594 by Ben Gamari at 2017-09-05T06:49:55-04:00 Account for "Remember the AvailInfo for each IE" As of GHC commit f609374a55bdcf3b79f3a299104767aae2ffbf21 GHC retains the AvailInfo associated with each IE. @alexbiehl has a patch making proper use of this change, but this is just to keep things building. - - - - - b05cd3b3 by Ben Gamari at 2017-09-14T07:55:07-04:00 Bump upper bound on base - - - - - 79db899e by Herbert Valerio Riedel at 2017-09-21T23:27:52+02:00 Make compatible with Prelude.<> export in GHC 8.4/base-4.11 - - - - - 3405dd52 by Tim Baumann at 2017-09-23T22:02:01+02:00 Add compile step that bundles and compresses JS files (#684) * Add compile step that bundles and compresses JS files Also, manage dependencies on third-party JS libraries using NPM. * Compile JS from TypeScript * Enable 'noImplicitAny' in TypeScript * QuickJump: use JSX syntax * Generate source maps from TypeScript for easier debugging * TypeScript: more accurate type * Separate quick jump css file from ocean theme - - - - - df0b5742 by Alex Biehl at 2017-09-29T21:15:40+02:00 Bump base for haddock-library and haddock-test - - - - - 62b12ea0 by Merijn Verstraaten at 2017-10-04T16:03:13+02:00 Inhibit output of coverage information for hidden modules. (#687) * Inhibit output of coverage information for hidden modules. * Add changelog entry. - - - - - 8daf8bc1 by Alexander Biehl at 2017-10-05T11:27:05+02:00 Don't use subMap in attachInstances - - - - - ad75114e by Alexander Biehl at 2017-10-05T11:27:58+02:00 Revert "Don't use subMap in attachInstances" This reverts commit 3adf5bcb1a6c5326ab33dc77b4aa229a91d91ce9. - - - - - 7d4aa02f by Alex Biehl at 2017-10-08T15:32:28+02:00 Precise Haddock: Use Avails for export resolution (#688) * Use Avails for export resolution * Support reexported modules * Factor out availExportItem * Use avails for fullModuleExports * Don't use subMap in attachInstances * lookupDocs without subMap * Completely remove subMap * Only calculate unqualified modules when explicit export list is given * Refactor * Refine comment * return * Fix * Refactoring * Split avail if declaration is not exported itself * Move avail splitting - - - - - b9b4faa8 by Alex Biehl at 2017-10-08T19:38:21+02:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 43325295 by Alex Biehl at 2017-10-08T20:18:46+02:00 Fix merge fallout - - - - - c6423cc0 by Alex Biehl at 2017-10-08T20:36:12+02:00 Copy QuickJump files over - - - - - 1db587c3 by Tim Baumann at 2017-10-09T18:33:09+02:00 Use <details> element for collapsibles (#690) * Remove unnecessary call to 'collapseSection' The call is unnecessary since there is no corresponding toggle for hiding the section of orphan instances. * Use <details> for collapsibles This makes them work even when JS is disabled. Closes haskell/haddock#560. - - - - - 1b54c64b by Tim Baumann at 2017-10-10T09:50:59+02:00 Quick Jump: Show error when loading 'doc-index.json' failed (#691) - - - - - 910f716d by Veronika Romashkina at 2017-10-24T07:36:20+02:00 Fix tiny typo in docs (#693) - - - - - b21de7e5 by Ryan Scott at 2017-10-24T13:07:15+02:00 Overhaul Haddock's rendering of kind signatures (#681) * Overhaul Haddock's rendering of kind signatures * Strip off kind signatures when specializing As an added bonus, this lets us remove an ugly hack specifically for `(->)`. Yay! * Update due to 0390e4a0f61e37bd1dcc24a36d499e92f2561b67 * @alexbiehl's suggestions * Import injectiveVarsOfBinder from GHC - - - - - 6704405c by Ryan Scott at 2017-10-28T07:10:27+02:00 Fix Haddock rendering of kind-indexed data family instances (#694) - - - - - 470f6b9c by Alex Biehl at 2017-10-30T08:45:51+01:00 Add QuickJump version to meta.json (#696) - - - - - b89eccdf by Alex Biehl at 2017-10-30T10:15:49+01:00 Put Quickjump behind --quickjump flag (#697) - - - - - 3095fb58 by Alex Biehl at 2017-10-30T19:09:06+01:00 Add build command to package.json - - - - - f223fda9 by Alex Biehl at 2017-10-30T19:10:39+01:00 Decrease threshold for fuzzy matching - - - - - 80245dda by Edward Z. Yang at 2017-10-31T20:35:05+01:00 Supported reexported-modules via --reexport flag. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 7e389742 by Alex Biehl at 2017-10-31T20:37:56+01:00 Correct missing title in changelog - - - - - 1a2a1c03 by Alex Biehl at 2017-10-31T20:59:07+01:00 Copy quickjump.css for nicer error messages - - - - - db234bb9 by Alex Biehl at 2017-10-31T21:31:18+01:00 Reexported modules: Report warnings if argument cannot be parsed or ... module cannot be found - - - - - eea8a205 by Carlo Hamalainen at 2017-10-31T21:43:14+01:00 More general type for nameCacheFromGhc. (#539) - - - - - 580eb42a by Alex Biehl at 2017-10-31T21:46:52+01:00 Remote tab - - - - - 0e599498 by Alex Biehl at 2017-10-31T21:48:55+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 7b8539bb by Alex Biehl at 2017-10-31T22:28:34+01:00 fullModuleContents traverses exports in declaration order - - - - - 0c91fbf2 by Alex Biehl at 2017-10-31T22:32:31+01:00 Remove excessive use of list comprehensions - - - - - f7356e02 by Alex Biehl at 2017-11-01T19:11:03+01:00 Make better use of AvailInfo - - - - - f3e512d5 by Alex Biehl at 2017-11-02T12:16:22+01:00 Always return documentation for exported subordinates ... event if they have no documentation (e.g. noDocForDecl) By using the information in the AvailInfo we don't need additional export checks. - - - - - 7cf58898 by Alan Zimmerman at 2017-11-07T08:28:03+02:00 Match changes for Trees that Grow in GHC - - - - - e5105a41 by Alan Zimmerman at 2017-11-08T17:21:58+02:00 Match Trees That Grow - - - - - 55178266 by Alan Zimmerman at 2017-11-11T22:20:31+02:00 Match Trees that Grow in GHC for HsExpr - - - - - 2082ab02 by Ryan Scott at 2017-11-14T15:27:03+01:00 Actually render infix type operators as infix (#703) * Actually render infix type operators as infix * Account for things like `(f :*: g) p`, too - - - - - c52ab7d0 by Alan Zimmerman at 2017-11-14T23:14:26+02:00 Clean up use of PlaceHolder, to match TTG - - - - - 81cc9851 by Moritz Angermann at 2017-11-20T07:52:49+01:00 Declare use of `Paths_haddock` module in other-modules (#705) This was detected by `-Wmissing-home-modules` - - - - - f9d27598 by Moritz Angermann at 2017-11-20T12:47:34+01:00 Drop Paths_haddock from ghc.mk (#707) With haskell/haddock#705 and haskell/haddock#706, the custom addition should not be necessary any more. # Conflicts: # ghc.mk - - - - - f34818dc by Moritz Angermann at 2017-11-20T12:47:59+01:00 Add autogen-modules (#706) > Packages using 'cabal-version: >= 1.25' and the autogenerated module Paths_* must include it also on the 'autogen-modules' field besides 'exposed-modules' and 'other-modules'. This specifies that the module does not come with the package and is generated on setup. Modules built with a custom Setup.hs script also go here to ensure that commands like sdist don't fail. # Conflicts: # haddock.cabal - - - - - bb43a0aa by Ben Gamari at 2017-11-21T15:50:12-05:00 Revert "Clean up use of PlaceHolder, to match TTG" This reverts commit 134a7bb054ea730b13c8629a76232d73e3ace049. - - - - - af9ebb2b by Ben Gamari at 2017-11-21T15:50:14-05:00 Revert "Match Trees that Grow in GHC for HsExpr" This reverts commit 9f054dc365379c66668de6719840918190ae6e44. - - - - - 5d35c3af by Ben Gamari at 2017-11-21T15:50:15-05:00 Revert "Match Trees That Grow" This reverts commit 73a26af844ac50b8bec39de11d64452a6286b00c. - - - - - 99a8e43b by Ben Gamari at 2017-11-21T16:36:06-05:00 Revert "Match changes for Trees that Grow in GHC" This reverts commit 01eeeb048acd2dd05ff6471ae148a97cf0720547. - - - - - c4d650c2 by Ben Gamari at 2017-12-04T15:06:07-05:00 Bump GHC version - - - - - 027b2274 by Ben Gamari at 2017-12-04T17:06:31-05:00 Bump GHC bound to 8.4.* - - - - - 58eaf755 by Alex Biehl at 2017-12-06T15:44:24+01:00 Update changelog - - - - - d68f5584 by Simon Peyton Jones at 2017-12-07T14:39:56+00:00 Track changes to follow Trac haskell/haddock#14529 This tracks the refactoring of HsDecl.ConDecl. - - - - - dc519d6b by Alec Theriault at 2018-01-06T08:20:43-08:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - 8285118c by Alec Theriault at 2018-01-13T12:12:37+01:00 Constructor and pattern synonym argument docs (#709) * Support Haddocks on constructor arguments This is in conjunction with https://phabricator.haskell.org/D4094. Adds support for rendering Haddock's on (non-record) constructor arguments, both for regular and GADT constructors. * Support haddocks on pattern synonym arguments It appears that GHC already parsed these - we just weren't using them. In the process of doing this, I tried to deduplicate some code around handling patterns. * Update the markup guide Add some information about the new support for commenting constructor arguments, and mention pattern synonyms and GADT-style constructors. * Overhaul LaTeX support for data/pattern decls This includes at least * fixing several bugs that resulted in invalid LaTeX * fixing GADT data declaration headers * overhaul handling of record fields * overhaul handling of GADT constructors * overhaul handling of bundled patterns * add support for constructor argument docs * Support GADT record constructors This means changes what existing HTML docs look like. As for LaTeX, looks like GADT records were never even supported. Now they are. * Clean up code/comments Made code/comments consistent between the LaTeX and XHTML backend when possible. * Update changelog * Patch post-rebase regressions * Another post-rebase change We want return values to be documentable on record GADT constructors. - - - - - ca4fabb4 by Alec Theriault at 2018-01-15T17:12:18-08:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 4c472fea by Ryan Scott at 2018-01-19T10:44:02+01:00 Fix haskell/haddock#732 (#733) - - - - - bff14dbd by Alex Biehl at 2018-01-19T15:33:30+01:00 extractDecl: Extract associated types correctly (#736) - - - - - a2a94a73 by Alex Biehl at 2018-01-19T15:34:40+01:00 extractDecl: Extract associated types correctly (#736) - - - - - 26df93dc by Alex Biehl at 2018-01-20T10:18:22+01:00 haddock-api: bump ghc to ^>= 8.4 - - - - - f65aeb1d by Alex Biehl at 2018-01-20T19:18:20+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - 0e721b97 by Alex Biehl at 2018-01-20T19:20:19+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - cb6234f6 by Ben Gamari at 2018-01-26T13:40:55-05:00 Merge remote-tracking branch 'harpocrates/fix/missing-orphan-instances' into ghc-head - - - - - 0fc28554 by Alec Theriault at 2018-02-01T14:58:18+01:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - b9123772 by Alec Theriault at 2018-02-01T14:58:18+01:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 0c12e274 by Ryan Scott at 2018-02-01T14:58:18+01:00 Fix haskell/haddock#548 by rendering datatype kinds more carefully (#702) - - - - - 8876d20b by Alec Theriault at 2018-02-01T14:58:18+01:00 Use the GHC lexer for the Hyperlinker backend (#714) * Start changing to use GHC lexer * better cpp * Change SrcSpan to RealSrcSpan * Remove error * Try to stop too many open files * wip * wip * Revert "wip" This reverts commit b605510a195f26315e3d8ca90e6d95a6737553e1. Conflicts: haddock-api/haddock-api.cabal haddock-api/src/Haddock/Interface.hs * Remove pointless 'caching' * Use dlist rather than lists when finding vars * Use a map rather than list * Delete bogus comment * Rebase followup Things now run using the GHC lexer. There are still - stray debug statements - unnecessary changes w.r.t. master * Cleaned up differences w.r.t. current Haddock HEAD Things are looking good. quasiquotes in particular look beautiful: the TH ones (with Haskell source inside) colour/link their contents too! Haven't yet begun to check for possible performance problems. * Support CPP and top-level pragmas The support for these is hackier - but no more hacky than the existing support. * Tests pass, CPP is better recognized The tests were in some cases altered: I consider the new output to be more correct than the old one.... * Fix shrinking of source without tabs in test * Replace 'Position'/'Span' with GHC counterparts Replaces 'Position' -> 'GHC.RealSrcLoc' and 'Span' -> 'GHC.RealSrcSpan'. * Nits * Forgot entry in .cabal * Update changelog - - - - - 95c6a771 by Alec Theriault at 2018-02-01T14:58:18+01:00 Clickable anchors for headings (#716) See haskell/haddock#579. This just adds an <a> tag around the heading, pointing to the heading itself. - - - - - 21463d28 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump: Matches on function names weight more than matches in ... module names. - - - - - 8023af39 by Alex Biehl at 2018-02-01T14:58:18+01:00 Treat escaped \] better in definition lists (#717) This fixes haskell/haddock#546. - - - - - e4866dc1 by Alex Biehl at 2018-02-01T14:58:18+01:00 Remove scanner, takeWhile1_ already takes care of escaping - - - - - 9bcaa49d by Alex Biehl at 2018-02-01T14:58:18+01:00 Take until line feed - - - - - 01d2af93 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Add simple framework for running parser fixtures (#668) * Add simple framework for running parser fixtures * Compatible with tree-diff-0.0.0.1 * Use parseParas to parse fixtures This allows to test all syntactic constructs available in haddock markup. - - - - - 31128417 by Alec Theriault at 2018-02-01T14:58:18+01:00 Patch flaky parser test (#720) * Patch flaky parser test This test was a great idea, but it doesn't port over too well to using the GHC lexer. GHC rewrites its input a bit - nothing surprising, but we need to guard against those cases for the test. * Change instance head * Change use site - - - - - 9704f214 by Herbert Valerio Riedel at 2018-02-01T14:58:18+01:00 Include secondary LICENSE file in source dist - - - - - 51f25074 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Grid Tables (#718) * Add table examples * Add table types and adopt simple parser Simple parser is done by Giovanni Cappellotto (@potomak) in https://github.com/haskell/haddock/pull/577 It seems to support single fine full tables, so far from full RST-grid tables, but it's good start. Table type support row- and colspans, but obviously parser is lacking. Still TODO: - Latex backend. Should we use multirow package https://ctan.org/pkg/multirow?lang=en? - Hoogle backend: ? * Implement grid-tables * Refactor table parser * Add two ill-examples * Update CHANGES.md * Basic documentation for tables * Fix documentation example - - - - - 670d6200 by Alex Biehl at 2018-02-01T14:58:18+01:00 Add grid table example to cheatsheet (pdf and svg need to be regenerated thought) - - - - - 4262dec9 by Alec Theriault at 2018-02-01T14:58:18+01:00 Fix infinite loop when specializing instance heads (#723) * Fix infinite loop when specializing instance heads The bug can only be triggered from TH, hence why it went un-noticed for so long. * Add test for haskell/haddock#679 and haskell/haddock#710 - - - - - 67ecd803 by Alec Theriault at 2018-02-01T14:58:18+01:00 Filter RTS arguments from 'ghc-options' arguments (#725) This fixes haskell/haddock#666. - - - - - 7db26992 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump Scrollable overlay - - - - - da9ff634 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Hyperlinker: Adjust parser to new PFailed constructor - - - - - 7b7cf8cb by Alexander Biehl at 2018-02-01T14:58:18+01:00 Specialize: Add missing IdP annotations - - - - - 78cd7231 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Convert: Correct pass type - - - - - a2d0f590 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Warning free compilation - - - - - cd861cf3 by Alexander Biehl at 2018-02-01T14:58:18+01:00 hadock-2.19.0 / haddock-api-2.19.0 / haddock-library-1.5.0 - - - - - c6651b72 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Adjust changelogs - - - - - 1e93da0b by Alexander Biehl at 2018-02-01T14:58:18+01:00 haddock-library: Info about breaking changes - - - - - f9b11db8 by Alec Theriault at 2018-02-02T12:36:02+01:00 Properly color pragma contents in hyperlinker The hyperlinker backend now classifies the content of pragmas as 'TkPragma'. That means that in something like '{-# INLINE foo #-}', 'foo' still gets classified as a pragma token. - - - - - c40b0043 by Alec Theriault at 2018-02-02T12:36:02+01:00 Support the new 'ITcolumn_prag' token - - - - - 4a2a4d39 by Alex Biehl at 2018-02-03T12:11:55+01:00 QuickJump: Mitigate encoding problems on Windows - - - - - bb34503a by Alex Biehl at 2018-02-04T18:39:31+01:00 Use withBinaryFile - - - - - 637605bf by Herbert Valerio Riedel at 2018-02-05T09:48:32+01:00 Try GHC 8.4.1 for Travis CI job - - - - - 7abb67e4 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 try harder to build w/ GHC 8.4.1 - - - - - 8255cc98 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 Add `SPDX-License-Identifier` as alised for "license" module header tokens C.f. SPDX 2.1 - Appendix V https://spdx.org/spdx-specification-21-web-version#h.twlc0ztnng3b The tag should appear on its own line in the source file, generally as part of a comment. SPDX-License-Identifier: <SPDX License Expression> Cherry-picked from haskell/haddock#743 - - - - - 267cd23d by Herbert Valerio Riedel at 2018-02-05T10:24:34+01:00 Make test-suite SMP compatible - - - - - 95d4bf40 by Alec Theriault at 2018-02-05T22:01:04+01:00 Hyperlink pattern synonyms and 'module' imports (#744) Links to pattern synonyms are now generated, as well as links from modules in import lists. Fixes haskell/haddock#731. - - - - - 67838dcd by Alec Theriault at 2018-02-06T08:23:36+01:00 Don't warn about missing '~' (#746) This manually filters out '~' from the list of things to warn about. It truly makes no sense to warn on this since '~' has nothing it could link to - it is magical. This fixes haskell/haddock#532. - - - - - ab6c3f9f by Alec Theriault at 2018-02-06T08:24:47+01:00 Don't barf on 'HsSpliceTy' (#745) This handles 'HsSpliceTy's by replacing them with what they expand to. IIUC everything that is happening, 'renameHsSpliceTy' should not be able to fail for the inputs we feed it from GHC. This fixes haskell/haddock#574. - - - - - 92bf95ad by Alex Biehl at 2018-02-06T08:28:23+01:00 Rename: renameHsSpliceTy ttg - - - - - 3130b1e1 by Alex Biehl at 2018-02-06T09:02:14+01:00 Expand SigDs - - - - - c72adae5 by Alex Biehl at 2018-02-06T09:20:51+01:00 fullModuleContents: support named docs - - - - - de2e4dbf by Alex Biehl at 2018-02-06T13:56:17+01:00 Hyperlinker: Also link pattern synonym arguments - - - - - b7c98237 by Alex Biehl at 2018-02-09T18:44:23+01:00 Expand SigD in a better place In https://github.com/haskell/haddock/issues/287 we found that haddock-2.19.0 would miss documentation on class methods with multiples names. This patch uses expandSigDecls in a more sensible place. - - - - - 8f598b27 by Alec Theriault at 2018-02-11T12:29:56+01:00 Add module tooltips to linked identifiers (#753) No more clicking to figure out whether your bytestring is strict or lazy! - - - - - d812e65d by Alec Theriault at 2018-02-11T12:31:44+01:00 Add 'show' option to complement 'hide' (#752) * Add 'show' option to complement 'hide' The behaviour is for flags passed in the command line to override flags in file headers. In the command line, later flags override earlier ones. Fixes haskell/haddock#751 and haskell/haddock#266. * Add a '--show-all' option - - - - - 6676cecb by Alex Biehl at 2018-02-18T11:07:15-05:00 QuickJump: Mitigate encoding problems on Windows (cherry picked from commit 86292c54bfee2343aee84559ec01f1fc68f52231) - - - - - e753dd88 by Alex Biehl at 2018-02-18T17:59:54+01:00 Use withBinaryFile - - - - - 724dc881 by Tamar Christina at 2018-02-19T05:34:49+01:00 Haddock: support splitted include paths. (#689) - - - - - 9b6d6f50 by Alex Biehl at 2018-02-19T05:57:02+01:00 Teach the HTML backend how to render methods with multiple names - - - - - a74aa754 by Alexander Biehl at 2018-02-19T10:04:34+01:00 Hoogle/Latex: Remove use of partial function - - - - - 66d8bb0e by Alec Theriault at 2018-02-25T16:04:01+01:00 Fix file handle leak (#763) (#764) Brought back some mistakenly deleted code for handling encoding and eager reading of files from e0ada1743cb722d2f82498a95b201f3ffb303137. - - - - - bb92d03d by Alex Biehl at 2018-03-02T14:21:23+01:00 Enable running test suite with stock haddock and ghc using ``` $ cabal new-run -- html-test --haddock-path=$(which haddock) --ghc-path=$(which ghc) ``` - - - - - dddb3cb2 by Alex Biehl at 2018-03-02T15:43:21+01:00 Make testsuite work with haddock-1.19.0 release (#766) - - - - - f38636ed by Alec Theriault at 2018-03-02T15:48:36+01:00 Support unicode operators, proper modules Unicode operators are a pretty big thing in Haskell, so supporting linking them seems like it outweighs the cost of the extra machinery to force Attoparsec to look for unicode. Fixes haskell/haddock#458. - - - - - 09d89f7c by Alec Theriault at 2018-03-02T15:48:43+01:00 Remove bang pattern - - - - - d150a687 by Alex Biehl at 2018-03-02T15:48:48+01:00 fix test - - - - - d6fd71a5 by Alex Biehl at 2018-03-02T16:22:38+01:00 haddock-test: Be more explicit which packages to pass We now pass `-hide-all-packages` to haddock when invoking the testsuite. This ensures we don't accidentally pick up any dependencies up through ghc.env files. - - - - - 0932c78c by Alex Biehl at 2018-03-02T17:50:38+01:00 Revert "fix test" This reverts commit 1ac2f9569242f6cb074ba6e577285a4c33ae1197. - - - - - 52516029 by Alex Biehl at 2018-03-02T18:16:50+01:00 Fix Bug548 for real - - - - - 89df9eb5 by Alex Biehl at 2018-03-05T18:28:19+01:00 Hyperlinker: Links for TyOps, class methods and associated types - - - - - d019a4cb by Ryan Scott at 2018-03-06T13:43:56-05:00 Updates for haskell/haddock#13324 - - - - - 6d5a42ce by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump haddock-2.19.0.1, haddock-api-2.19.0.1, haddock-library-1.5.0.1 - - - - - c0e6f380 by Alex Biehl at 2018-03-10T18:25:57+01:00 Update changelogs for haddock-2.19.0.1 and haddock-library-1.5.0.1 - - - - - 500da489 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Update to QC 2.11 - - - - - ce8362e9 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Restore backward-compat with base-4.5 through base-4.8 - - - - - baae4435 by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump lower bound for haddock-library - - - - - 10b7a73e by Alex Biehl at 2018-03-10T18:25:57+01:00 Haddock: Straighten out base bound - - - - - a6096f7b by Alex Biehl at 2018-03-13T08:45:06+01:00 extractDecl: Extract constructor patterns from data family instances (#776) * extractDecl: Allow extraction of data family instance constructors * extractDecl: extract data family instance constructors - - - - - ba4a0744 by Simon Jakobi at 2018-03-14T08:26:42+01:00 Readme: Update GHC version (#778) - - - - - 8de157d4 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for definition lists - - - - - 425b46f9 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for links - - - - - d53945d8 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for inline links - - - - - f1dc7c99 by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Slightly unmangle output - - - - - 0879d31c by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Prevent stdout buffering - - - - - 1f9e5f1b by Simon Jakobi at 2018-03-14T20:39:29+01:00 haddock-library.cabal: Clean up GHC options - - - - - 066b891a by Simon Jakobi at 2018-03-14T20:39:29+01:00 Make a proper definition for the <link> parser - - - - - 573d6ba7 by Alec Theriault at 2018-03-21T09:16:57+01:00 Show where instances are defined (#748) * Indicate source module of instances Above instance, we now also display a link to the module where the instance was defined. This is sometimes helpful in figuring out what to import. * Source module for type/data families too * Remove parens * Accept tests - - - - - 99b5d28b by Alex Biehl at 2018-03-21T09:20:36+01:00 Prepare changelog for next release - - - - - 482d3a93 by Alex Biehl at 2018-03-23T15:57:36+01:00 Useful cost centres, timers and allocation counters (#785) * Add some useful cost-centres for profiling * Add withTiming for each haddock phase Invoking haddock with `--optghc=-ddump-timings` now shows the amount of time spent and the number of allocated bytes for each phase. - - - - - 773b41bb by Alec Theriault at 2018-03-27T08:35:59+02:00 @since includes package name (#749) * Metadoc stores a package name This means that '@since' annotations can be package aware. * Get the package name the right way This should extract the package name for `@since` annotations the right way. I had to move `modulePackageInfo` around to do this and, in the process, I took the liberty to update it. Since it appears that finding the package name is something that can fail, I added a warning for this case. * Silence warnings * Hide package for local 'since' annotations As discussed, this is still the usual case (and we should avoid being noisy for it). Although this commit is large, it is basically only about threading a 'Maybe Package' from 'Haddock.render' all the way to 'Haddock.Backends.Xhtml.DocMarkup.renderMeta'. * Bump binary interface version * Add a '--since-qual' option This controls when to qualify since annotations with the package they come from. The default is always, but I've left an 'external' variant where only those annotations coming from outside of the current package are qualified. * Make ParserSpec work * Make Fixtures work * Use package name even if package version is not available The @since stuff needs only the package name passed in, so it makes sense to not be forced to pass in a version too. - - - - - e42c57bc by Alex Biehl at 2018-03-27T08:42:50+02:00 haddock-2.19.1, haddock-api-2.19.1, haddock-library-1.6.0 - - - - - 8373a529 by Alex Biehl at 2018-03-28T10:17:11+02:00 Bump haddock and haddock-api to 2.20.0 - - - - - 5038eddd by Jack Henahan at 2018-04-03T13:28:12+02:00 Clear search string on hide for haskell/haddock#781 (#789) - - - - - 920ca1eb by Alex Biehl at 2018-04-03T16:35:50+02:00 Travis: Build with ghc-8.4.2 (#793) - - - - - a232f0eb by Alan Zimmerman at 2018-04-07T14:14:32+02:00 Match changes in GHC for D4199 Removing HasSourceText and SourceTextX classes. - - - - - ab85060b by Alan Zimmerman at 2018-04-09T21:20:24+02:00 Match GHC changes for TTG - - - - - 739302b6 by Alan Zimmerman at 2018-04-13T13:31:44+02:00 Match GHC for TTG implemented on HsBinds, D4581 - - - - - 2f56d3cb by Ryan Scott at 2018-04-19T11:42:58-04:00 Bump upper bound on base to < 4.13 See https://ghc.haskell.org/trac/ghc/ticket/15018. - - - - - a49df92a by Alex Biehl at 2018-04-20T07:31:44+02:00 Don't treat fixity signatures like declarations - - - - - d02c103b by Ryan Scott at 2018-04-24T11:20:11-04:00 Add regression test for haskell/haddock#413 Fixes haskell/haddock#413. - - - - - c7577f52 by Ryan Scott at 2018-04-24T13:51:06-07:00 Improve the Hoogle backend's treatment of type families (#808) Fixes parts 1 and 2 of haskell/haddock#806. - - - - - d88f85b1 by Alec Theriault at 2018-04-25T11:24:07-07:00 Replace 'attoparsec' with 'parsec' (#799) * Remove attoparsec with parsec and start fixing failed parses * Make tests pass * Fix encoding issues The Haddock parser no longer needs to worry about bytestrings. All the internal parsing work in haddock-library happens over 'Text'. * Remove attoparsec vendor * Fix stuff broken in 'attoparsec' -> 'parsec' * hyperlinks * codeblocks * examples Pretty much all issues are due to attoparsec's backtracking failure behaviour vs. parsec's non-backtracking failure behaviour. * Fix small TODOs * Missing quote + Haddocks * Better handle spaces before/after paragraphs * Address review comments - - - - - fc25e2fe by Alan Zimmerman at 2018-04-27T15:36:53+02:00 Match changes in GHC for TTG - - - - - 06175f91 by Herbert Valerio Riedel at 2018-05-01T18:11:09+02:00 Merge branch 'ghc-head' with 'ghc-8.4' - - - - - 879caaa8 by Alec Theriault at 2018-05-07T18:53:15-07:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 3e0120cb by Simon Jakobi at 2018-05-07T19:00:18-07:00 Add docs for some DocH constructors (#814) - - - - - 0a32c6db by Alec Theriault at 2018-05-08T02:15:45-07:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 8816e783 by Simon Jakobi at 2018-05-08T10:48:11-07:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - ad60366f by Ryan Scott at 2018-05-10T11:19:47-04:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - 03b7cc3b by Ryan Scott at 2018-05-10T11:24:38-04:00 Wibbles - - - - - b03dd563 by Chaitanya Koparkar at 2018-05-10T11:44:58-04:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 9f298a40 by Ben Gamari at 2018-05-13T17:36:04-04:00 Account for refactoring of LitString - - - - - ea3dabe7 by Ryan Scott at 2018-05-16T09:21:43-04:00 Merge pull request haskell/haddock#826 from haskell/T825 Remove Hoogle backend hack that butchers infix datatype names - - - - - 0d234f7c by Alec Theriault at 2018-05-23T11:29:05+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 15fc9712 by Simon Jakobi at 2018-05-31T04:17:47+02:00 Adjust to new HsDocString internals - - - - - 6f1e19a8 by Ben Gamari at 2018-06-02T16:18:58-04:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 0d0355d9 by Ryan Scott at 2018-06-04T21:26:59-04:00 DerivingVia changes - - - - - 0d93475a by Simon Jakobi at 2018-06-05T19:47:05+02:00 Bump a few dependency bounds (#845) - - - - - 5cbef804 by Alec Theriault at 2018-06-05T19:47:16+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 9094c56f by Alec Theriault at 2018-06-05T22:53:25+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 70188719 by Simon Jakobi at 2018-06-08T22:20:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - 495cd1fc by Chaitanya Koparkar at 2018-06-13T23:01:34+02:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 81088732 by Ben Gamari at 2018-06-13T23:01:34+02:00 Account for refactoring of LitString - - - - - 7baf6587 by Simon Jakobi at 2018-06-13T23:05:08+02:00 Adjust to new HsDocString internals - - - - - bb61464d by Ben Gamari at 2018-06-13T23:05:22+02:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 5d8cb87f by Ryan Scott at 2018-06-13T23:39:30+02:00 DerivingVia changes - - - - - 73d373a3 by Alec Theriault at 2018-06-13T23:39:30+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 4865e254 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Remove `ITtildehsh` token - - - - - b867db54 by Alec Theriault at 2018-06-13T23:39:30+02:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 9598e392 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Add docs for some DocH constructors (#814) - - - - - 8a59035b by Alec Theriault at 2018-06-13T23:39:30+02:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 29350fc8 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - 2590bbd9 by Ryan Scott at 2018-06-13T23:39:30+02:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - a9939fdc by Ryan Scott at 2018-06-13T23:39:30+02:00 Wibbles - - - - - a22f7df4 by Alec Theriault at 2018-06-13T23:39:30+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 8741015d by Simon Jakobi at 2018-06-13T23:39:30+02:00 Bump a few dependency bounds (#845) - - - - - 4791e1cc by Alec Theriault at 2018-06-13T23:39:30+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 311d3216 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - d0577817 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Complete FixitySig and FamilyDecl pattern matches - - - - - 055b3aa7 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Fix redundant import warnings - - - - - f9ce19b1 by Simon Jakobi at 2018-06-13T23:49:52+02:00 html-test: Accept output - - - - - 04604ea7 by Simon Jakobi at 2018-06-13T23:54:37+02:00 Bump bounds on Cabal - - - - - 0713b692 by Simon Jakobi at 2018-06-14T00:00:12+02:00 Merge branch 'ghc-head' into ghc-head-update-3 - - - - - c6a56bfd by Simon Jakobi at 2018-06-14T02:33:27+02:00 Bump ghc bound for haddock-api spec test-suite - - - - - 119d04b2 by Simon Jakobi at 2018-06-14T12:37:48+02:00 Travis: `--allow-newer` for all packages - - - - - 0e876e2c by Alex Biehl at 2018-06-14T15:28:52+02:00 Merge pull request haskell/haddock#857 from sjakobi/ghc-head-update-3 Update ghc-head - - - - - 5be46454 by Alec Theriault at 2018-06-14T21:42:45+02:00 Improved handling of interfaces in 'haddock-test' (#851) This should now work with an inplace GHC where (for instance) HTML directories may not be properly recorded in the package DB. - - - - - 96ab1387 by Vladislav Zavialov at 2018-06-14T17:06:21-04:00 Handle -XStarIsType - - - - - e518f8c4 by Ben Gamari at 2018-06-14T17:48:00-04:00 Revert unintentional reversion of fix of haskell/haddock#548 - - - - - 01b9f96d by Alan Zimmerman at 2018-06-19T11:52:22+02:00 Match changes in GHC for haskell/haddock#14259 - - - - - 7f8c8298 by Ben Gamari at 2018-06-19T18:14:27-04:00 Bump GHC version to 8.6 - - - - - 11c6b5d2 by Ryan Scott at 2018-06-19T23:17:31-04:00 Remove HsEqTy and XEqTy - - - - - b33347c2 by Herbert Valerio Riedel at 2018-06-20T23:14:52+02:00 Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. - - - - - f0d2460e by Herbert Valerio Riedel at 2018-06-20T23:28:46+02:00 Update Travis CI job - - - - - ef239223 by Herbert Valerio Riedel at 2018-06-20T23:32:41+02:00 Drop GHC HEAD from CI and update GHC to 8.4.3 It's a waste of resource to even try to build this branch w/ ghc-head; so let's not do that... - - - - - 41c4a9fa by Ben Gamari at 2018-06-20T18:26:20-04:00 Bump GHC version to 8.7 - - - - - 8be593dc by Herbert Valerio Riedel at 2018-06-21T22:32:15+02:00 Update CI job to use GHC 8.7.* - - - - - b91d334a by Simon Jakobi at 2018-06-30T13:41:38+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section - - - - - f707d848 by Alec Theriault at 2018-07-05T10:43:35-04:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. - - - - - a6d2b8dc by Alec Theriault at 2018-07-06T10:06:32-04:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case - - - - - 13819f71 by Alan Zimmerman at 2018-07-15T19:33:51+02:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 - - - - - c346aa78 by Simon Jakobi at 2018-07-19T12:29:32+02:00 haddock-library: Bump bounds for containers - - - - - 722e733c by Simon Jakobi at 2018-07-19T13:36:45+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] - - - - - f0bd83fd by Alec Theriault at 2018-07-19T14:39:57+02:00 Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. - - - - - 394053a8 by Simon Jakobi at 2018-07-19T14:58:07+02:00 haddock-library: Bump bounds for containers - - - - - 1bda11a2 by Alec Theriault at 2018-07-20T09:04:03+02:00 Add HEAD.hackage overlay (#887) * Add HEAD.hackage overlay * Add HCPKG variable - - - - - c7b4ab45 by Alec Theriault at 2018-07-20T12:01:16+02:00 Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test - - - - - c05d32ad by Alec Theriault at 2018-07-20T12:01:49+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output - - - - - 24b39ee4 by Alec Theriault at 2018-07-20T12:02:16+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. - - - - - cb9d2099 by Simon Jakobi at 2018-07-20T13:39:29+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) - - - - - 133f24f5 by Alec Theriault at 2018-07-20T13:39:29+02:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) - - - - - 11024149 by Alec Theriault at 2018-07-20T13:39:29+02:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) - - - - - de0c139e by Simon Jakobi at 2018-07-20T13:39:29+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) - - - - - 6435e952 by Alec Theriault at 2018-07-20T13:39:29+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) - - - - - 1461af39 by Alec Theriault at 2018-07-20T13:39:29+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) - - - - - 69d3bde1 by Alec Theriault at 2018-07-20T13:49:47+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) - - - - - 6a5c73c7 by Alec Theriault at 2018-07-20T13:50:00+02:00 Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests - - - - - 92ca94c6 by Alec Theriault at 2018-07-20T13:55:36+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) - - - - - 981bc7fa by Simon Jakobi at 2018-07-20T15:06:06+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers - - - - - 27e7c0c5 by Simon Jakobi at 2018-07-20T15:09:05+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 49e1a415 by Simon Jakobi at 2018-07-20T16:02:02+02:00 Update the ghc-8.6 branch (#889) * Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. * README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) * Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) * Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) * tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) * Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. * Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test * Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) * Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) * Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) * Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests * Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 5ca14bed by Simon Jakobi at 2018-07-20T16:05:47+02:00 Revert "Revert "Bump GHC version to 8.6"" That commit didn't belong onto the ghc-8.6 branch. This reverts commit acbaef3b9daf1d2dea10017964bf886e77a8e967. - - - - - 2dd600dd by Simon Jakobi at 2018-07-20T16:18:21+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. - - - - - fceb2422 by Simon Jakobi at 2018-07-20T16:18:21+02:00 outOfScope: Recommend qualifying the identifier - - - - - acea5d23 by Simon Jakobi at 2018-07-20T16:19:35+02:00 outOfScope: Recommend qualifying the identifier (cherry picked from commit 73707ed58d879cc04cb644c5dab88c39ca1465b7) - - - - - 1a83ca55 by Simon Jakobi at 2018-07-20T16:19:35+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. (cherry picked from commit d504a2864a4e1982e142cf88c023e7caeea3b76f) - - - - - 48374451 by Masahiro Sakai at 2018-07-20T17:06:42+02:00 Add # as a special character (#884) '#' has special meaning used for anchors and can be escaped using backslash. Therefore it would be nice to be listed as special characters. - - - - - 5e1a5275 by Alec Theriault at 2018-07-20T23:37:24+02:00 Let `haddock-test` bypass interface version check (#890) This means `haddock-test` might * crash during deserialization * deserialize incorrectly Still - it means things _might_ work where they were previously sure not to. - - - - - 27286754 by Yuji Yamamoto at 2018-07-23T08:16:01+02:00 Avoid "invalid argument (invalid character)" on non-unicode Windows (#892) Steps to reproduce and the error message ==== ``` > stack haddock basement ... snip ... Warning: 'A' is out of scope. Warning: 'haddock: internal error: <stdout>: commitBuffer: invalid argument (invalid character) ``` Environment ==== OS: Windows 10 ver. 1709 haddock: [HEAD of ghc-8.4 when I reproduce the error](https://github.com/haskell/haddock/commit/532b209d127e4cecdbf7e9e3dcf4f653a5605b5a). (I had to use this version to avoid another probrem already fixed in HEAD) GHC: 8.4.3 stack: Version 1.7.1, Git revision 681c800873816c022739ca7ed14755e85a579565 (5807 commits) x86_64 hpack-0.28.2 Related pull request ==== https://github.com/haskell/haddock/pull/566 - - - - - 6729d361 by Alec Theriault at 2018-07-23T13:52:56-07:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). - - - - - 8cf4e6b5 by Ryan Scott at 2018-07-27T11:28:03-04:00 eqTyCon_RDR now lives in TysWiredIn After GHC commit http://git.haskell.org/ghc.git/commit/f265008fb6f70830e7e92ce563f6d83833cef071 - - - - - 1ad251a6 by Alan Zimmerman at 2018-07-30T13:28:09-04:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 (cherry picked from commit e3926b50ab8a7269fd6904b06e881745f08bc5d6) - - - - - 8aea2492 by Richard Eisenberg at 2018-08-02T10:54:17-04:00 Update against new HsImplicitBndrs - - - - - e42cada9 by Alec Theriault at 2018-08-04T17:51:30+02:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 0e852512 by Alex Biehl at 2018-08-06T13:04:02+02:00 Make --package-version optional for --hoogle generation (#899) * Make --package-version optional for --hoogle generation * Import mkVersion * It's makeVersion not mkVersion - - - - - d2abd684 by Noel Bourke at 2018-08-21T09:34:18+02:00 Remove unnecessary backslashes from docs (#908) On https://haskell-haddock.readthedocs.io/en/latest/markup.html#special-characters the backslash and backtick special characters showed up with an extra backslash before them – I think the escaping is not (or no longer) needed for those characters in rst. - - - - - 7a578a9e by Matthew Pickering at 2018-08-21T09:34:50+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - aa3d4db3 by Matthew Pickering at 2018-08-21T09:37:34+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - ede91744 by Alec Theriault at 2018-08-21T09:42:52+02:00 Better test output when Haddock crashes on a test (#902) In particular: we report the tests that crashed seperately from the tests that produced incorrect output. In order for tests to pass (and exit 0), they must not crash and must produce the right output. - - - - - 4a872b84 by Guillaume Bouchard at 2018-08-21T09:45:57+02:00 Fix a typo (#878) - - - - - 4dbf7595 by Ben Sklaroff at 2018-08-21T12:04:09-04:00 Add ITcomment_line_prag token to Hyperlinker Parser This token is necessary for parsing #line pragmas inside nested comments. Reviewers: bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D4935 - - - - - 9170b2a9 by Ben Gamari at 2018-08-21T17:55:15-04:00 Merge pull request haskell/haddock#893 from harpocrates/get-name-to-instances Accumulate explicitly which modules to load for 'attachInstances' - - - - - d57b57cc by Ben Gamari at 2018-08-21T17:59:13-04:00 Merge branch 'ghc-head' of github.com:haskell/haddock into ghc-head - - - - - 14601ca2 by Alec Theriault at 2018-08-21T19:09:37-04:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). (cherry picked from commit 5c7c596c51d69b92164e9ba920157b36ce2b2ec1) - - - - - 438c645e by Matthew Pickering at 2018-08-21T19:12:39-04:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 (cherry picked from commit e6aa8fb47b9477cc5ef5e46097524fe83e080f6d) - - - - - a80c5161 by Alec Theriault at 2018-08-21T22:06:40-07:00 Better rendering of unboxed sums/tuples * adds space after/before the '#' marks * properly reify 'HsSumTy' in 'synifyType' - - - - - 88456cc1 by Alec Theriault at 2018-08-21T22:06:40-07:00 Handle promoted tuples in 'synifyType' When we have a fully applied promoted tuple, we can expand it out properly. - - - - - fd1c1094 by Alec Theriault at 2018-08-21T22:19:34-07:00 Accept test cases - - - - - 6e80d9e0 by Alec Theriault at 2018-08-21T22:24:03-07:00 Merge pull request haskell/haddock#914 from harpocrates/feature/unboxed-stuff Better rendering of unboxed sums, unboxed tuples, promoted tuples. - - - - - 181a23f1 by Ben Gamari at 2018-08-23T15:53:48-04:00 Merge remote-tracking branch 'origin/ghc-8.6' into ghc-8.6 - - - - - 3a18c1d8 by Alec Theriault at 2018-08-27T14:15:25-07:00 Properly synify promoted list types We reconstruct promoted list literals whenever possible. That means that 'synifyType' produces '[Int, Bool, ()] instead of (Int ': (() ': (Bool ': ([] :: [Type])))) - - - - - b4794946 by Alec Theriault at 2018-09-03T07:19:55-07:00 Only look at visible types when synifying a 'HsListTy' The other types are still looked at when considering whether to make a kind signature or not. - - - - - a231fce2 by Alec Theriault at 2018-09-03T07:38:10-07:00 Merge pull request haskell/haddock#922 from harpocrates/promoted-lists Properly synify promoted list types - - - - - 0fdf044e by Ningning Xie at 2018-09-15T10:25:58-04:00 Update according to GHC Core changes - - - - - 7379b115 by Ningning Xie at 2018-09-15T15:40:18-04:00 update dataFullSig to work with Co Quantification This should have been in the previous patch, but wasn't. - - - - - cf84a046 by Alec Theriault at 2018-09-17T20:12:18-07:00 Fix/add to various docs * Add documentation for a bunch of previously undocumented options (fixes haskell/haddock#870) * Extend the documentation of `--hoogle` considerably (see haskell/haddock#807) * Describe how to add docs to `deriving` clauses (fixes haskell/haddock#912) * Fix inaccurate docs about hyperlinking infix identifiers (fixes haskell/haddock#780) - - - - - ae017935 by Alec Theriault at 2018-09-22T08:32:16-07:00 Update Travis - - - - - d95ae753 by Alec Theriault at 2018-09-22T09:34:10-07:00 Accept failing tests Also silence orphan warnings. - - - - - f3e67024 by Alec Theriault at 2018-09-22T09:41:23-07:00 Bump haddock-api-2.21.0, haddock-library-1.7.0 * Update CHANGELOGS * Update new versions in Cabal files * Purge references to ghc-8.4/master branches in README - - - - - 3f136d4a by Alec Theriault at 2018-09-22T10:53:31-07:00 Turn haddock-library into a minor release Fix some version bounds in haddock-library too. - - - - - b9def006 by Alec Theriault at 2018-09-22T13:07:35-07:00 keep cabal.project file - - - - - 4909aca7 by Alec Theriault at 2018-10-16T09:36:30-07:00 Build on 7.4 and 7.8 - - - - - 99d20a28 by Herbert Valerio Riedel at 2018-10-16T18:45:52+02:00 Minor tweak to package description - - - - - a8059618 by Herbert Valerio Riedel at 2018-10-16T18:47:24+02:00 Merge pull request haskell/haddock#945 haddock-api 2.21.0 and haddock-library 1.6.1 release - - - - - 2d9bdfc1 by Alec Theriault at 2018-10-16T10:54:21-07:00 Bump haddock-library to 1.7.0 The 1.6.1 release should've been a major bump, since types in the `Documentation.Haddock.Parser.Monad` module changed. This version makes that module internal (as it morally should be). - - - - - ed340cef by Alec Theriault at 2018-10-16T14:59:13-07:00 Merge branch 'ghc-8.4' into ghc-8.6 - - - - - 2821a8df by Alec Theriault at 2018-10-16T15:14:48-07:00 Merge branch 'ghc-8.6' into ghc-head - - - - - a722dc84 by Alec Theriault at 2018-10-16T16:28:55-07:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 63377496 by Alec Theriault at 2018-10-16T16:39:07-07:00 Update changelog - - - - - 099a0110 by Alec Theriault at 2018-10-16T16:49:28-07:00 Merge pull request haskell/haddock#942 from harpocrates/update-docs Fix & add to documentation - - - - - 0927416f by Alec Theriault at 2018-10-16T16:50:14-07:00 Set UTF-8 encoding before writing files (#934) This should fix haskell/haddock#929, as well as guard against future problems of this sort in other places. Basically replaces 'writeFile' (which selects the users default locale) with 'writeUtf8File' (which always uses utf8). - - - - - 83b7b017 by Alec Theriault at 2018-10-16T17:42:05-07:00 Output pattern synonyms in Hoogle backend (#947) * Output pattern synonyms in Hoogle backend We were previously weren't outputting _any_ pattern synonyms, bundled or not. Now, we output both. Fixes haskell/haddock#946. * Update changelog - - - - - 81e5033d by Alec Theriault at 2018-10-16T18:04:40-07:00 Release `haddock{,-api}-2.22.0` This version will accompany ghc-8.6.2 - - - - - 9661744e by Alex Biehl at 2018-10-18T08:14:32-07:00 Add NewOcean theme And make it the default theme. - - - - - 7ae6d722 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Improve appearance and readability These changes include: - use latest Haskell's logo colors - decrease #content width to improve readability - use nicer font - improve sizes and distances - - - - - 37f8703d by NunoAlexandre at 2018-10-18T08:14:32-07:00 Include custom font in the html head - - - - - 1d5e1d79 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Update html test reference files - - - - - 53b7651f by NunoAlexandre at 2018-10-18T08:14:32-07:00 Make it responsive - It makes small screens taking more space than larger ones - fixes a few issues present in small screens currently - make it look good across different screen sizes. - - - - - 6aa1aeb1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make the style consistent with hackage Several things are addressed here: - better responsive behaviour on the header - better space usage - consistent colors overall - other nit PR comments - - - - - 3a250c5c by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Place the package name before the menu links This supports the expected responsive menu design, where the package name appears above the menu links. - - - - - cae699b3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update html-test reference files The package name element in the package-header is now a div instead of a paragraph, and it is now above the menu ul.links instead of below. - - - - - 2ec7fd2d by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve synopsis style and code - Use CSS3 instead of loading pictures to show "+" and "-" symbols - Drop redundant code - - - - - 0c874c01 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Decrease space between code blocks There was too much space between code blocks as pointed out by reviewers. - - - - - 85568ce2 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Add an initial-scale property to all haddock pages This solves an issue reported about the content looking incredibly small on mobile devices. - - - - - c1538926 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Address several PR comments - Darken text color like done for hackage - Move synopsis to left side - Make table of contents stick to the left on wide screens - Wrap links to avoid page overflow - Improve expand/collapse buttons - Fix issue with content size on mobile devices - Fix issue with font-size on landscape mode - Increase width of the content - Change colors of table of contents and synopsis - Etc - - - - - e6639e5f by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make synopsis scrollable on wide screens When the synopsis is longer than the screen, you can’t see its end and you can't scroll down either, making the content unreachable. - - - - - 1f0591ff by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve information density - Reduce font size - Improve space between and within code blocks - Improve alignments - Improve spacing within sub-blocks - - - - - bf083097 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Minor adjustments Bring in some adjustments made to hackage: - link colors - page header show everything when package title is too long - - - - - 10375fc7 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix responsive triggers overlap issue The min and max width triggers have the same values, which caused the style resolution to take an intersection of both style declarations when the screen resolution had the size of the limts (say 1280px), causing an odd behaviour and look. - - - - - 95ff2f95 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix issue with menu alignment on firefox Reported and described here: https://github.com/haskell/haddock/pull/721#issuecomment-374668869 - - - - - dc86587e by Alex Biehl at 2018-10-18T08:14:32-07:00 Changelog entry for NewOcean - - - - - 27195e47 by Herbert Valerio Riedel at 2018-10-18T08:14:32-07:00 html-test --accept - - - - - 83f4f9c0 by Alex Biehl at 2018-10-18T08:14:32-07:00 Avoid name shadowing - - - - - 231487f1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font to PT Sans Also migrate some general text related changes from hackage. - - - - - 313db81a by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Use 'flex' to fix header alignment - - - - - 5087367b by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Misc of tweaks - Update link colors to hackage scheme - Tune spacing between content elements - Update footer style - Fix and improve code blocks identation - - - - - b08020df by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font in Xhtml.hs to PT Sans - - - - - 78ce06e3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve code blocks styling - Fix and improve spacing - Improve colors and borders - - - - - 81262d20 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make package-header caption backward-compatible The current html generator of this branch wraps the package-header caption as a div, which does not work (without style adjustments) with the old themes. Changing it from div to span does the trick, without needing to adjust the old stylesheets. - - - - - dc4475cb by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update test-suite reference html pages - - - - - 393d35d8 by Alec Theriault at 2018-10-18T08:25:36-07:00 Accept tests - - - - - a94484ba by Alec Theriault at 2018-10-21T10:29:29-07:00 Fix CHANGELOG - - - - - 8797eca3 by Alec Theriault at 2018-10-21T10:36:19-07:00 Update 'data-files' to include NewOcean stuff - - - - - 1ae51e4a by Simon Jakobi at 2018-10-23T11:29:14+02:00 Fix typo in a warning - - - - - 009ad8e8 by Alec Theriault at 2018-10-24T12:47:47-07:00 Update JS dependencies This was done via `npm audit fix`. I think this fixes haskell/haddock#903 along with some more serious vulnerabilities that nobody seems to have noticed. - - - - - 051994db by Alec Theriault at 2018-10-24T17:31:09-07:00 Resurrect the style-switcher This fixes haskell/haddock#810. Looks like things were broken during the quickjump refactor of the JS. For the (git) record: I do not think the style switcher is a good idea. I'm fixing it for the same reason @mzero added it; as an answer to "rumblings from some that they didn't want their pixels changed on bit" - - - - - 2a1d620f by Alec Theriault at 2018-10-24T17:38:07-07:00 Fix copy-pasta error in data-files - - - - - ed5bfb7f by Alec Theriault at 2018-10-24T20:42:14-07:00 Fix the synopsis button Here's these changes are supposed to do: * put the synopsis back on the right side * properly have it on the edge of the screen on wide screens * adjust the background of the synopsis to match the button (otherwise the grey blends in with what is underneath) * get rid of the dotted purple line * the synopsis contents are now scrollable even when in wide screens (this has been a long-standing bug) - - - - - 883fd74b by Alec Theriault at 2018-10-25T20:16:46-07:00 Avoid more conflicts in generated ids (#954) This fixes haskell/haddock#953 by passing more names into the generated ids. - - - - - ea54e331 by Alec Theriault at 2018-10-25T21:07:12-07:00 Don't hide bullets in method docs I think thst CSS was meant only to deal with fields and the effect on bullets was accidental. Fixes haskell/haddock#926. - - - - - 9a14ef4a by Alec Theriault at 2018-10-25T22:02:07-07:00 Indent more things + slightly smaller font - - - - - b9f17e29 by Alec Theriault at 2018-10-25T22:10:01-07:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 096a3cfa by Alec Theriault at 2018-10-25T22:24:38-07:00 Accept HTML output - - - - - 2669517d by Alec Theriault at 2018-10-26T09:02:35-07:00 User manual + stuff for building GHC docs - - - - - 46b27687 by Alec Theriault at 2018-10-26T09:10:59-07:00 Make 'Contents' in NewOcean scrollable This only happens if the contents block on the left is so big that it doesn't fit (vertically) on the page. If that happens, we want it to be scrollable. - - - - - 3443dd94 by Alec Theriault at 2018-10-26T09:36:46-07:00 Revert "Make 'Contents' in NewOcean scrollable" This reverts commit f909ffd8353d6463fd5dd184998a32aa98d5c922. I missed the fact this also forces the 'Contents' to always go down to the bottom of the page. - - - - - ed081424 by Alec Theriault at 2018-10-26T14:22:23-07:00 Avoid some partiality AFAICT this wasn't causing any crashes, but that's mostly because we happen not to be forcing `pkgStr` when it would diverge. We come dangerously close to doing that in `ppHtmlIndex`. Fixes haskell/haddock#569. - - - - - 6a5bec41 by Alec Theriault at 2018-10-27T10:05:04-07:00 Fix documentation in `haddock-api` (#957) * Fix misplaced Haddocks in Haddock itself Haddock should be able to generate documentation for 'haddock-api' again. * Make CI check that documentation can be built. * Add back a doc that is OK - - - - - 5100450a by Matthew Yacavone at 2018-10-27T14:51:38-04:00 More explicit foralls (GHC Proposal 0007) - - - - - 8771a6b0 by Alec Theriault at 2018-11-05T13:58:11-08:00 Only run MathJax on entities with "mathjax" class (#960) Correspondingly, we wrap all inline/diplay math in <span class="mathjax"> ... the math .... </span> This fixes haskell/haddock#959. - - - - - bd7ff5c5 by Alec Theriault at 2018-11-05T15:54:22-08:00 Deduplicate some work in 'AttachInstances' Perf only change: * avoid needlessly union-ing maps * avoid synify-ing instances twice Took this opportunity to add some docs too - - - - - cf99fd8f by Alec Theriault at 2018-11-05T15:54:22-08:00 Specialize some SYB functions Perf only change: * Add a 'SPECIALIZE' pragma to help GHC optimize a 'Data a =>' constraint * Manually specialize the needlessly general type of 'specializeTyVarBndrs' - - - - - 4f91c473 by Alec Theriault at 2018-11-05T15:54:22-08:00 Improve perf of renaming Perf only change: * don't look up type variable names (they're never in the environment) * use a difference list for accumulating missing names * more efficient 'Functor'/'Applicative' instances for 'RnM' - - - - - 4bbab0d4 by Alec Theriault at 2018-11-05T15:54:22-08:00 Faster 'Text' driven parser combinators Perf only change: * use 'getParserState'/'setParserState' to make 'Text'-optimized parser combinators * minimize uses of 'Data.Text.{pack,unpack,cons,snoc}' - - - - - fa430c02 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support hyperlink labels with inline markup The parser for pictures hasn't been properly adjusted yet. - - - - - c1431035 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support (and flatten) inline markup in image links Inline markup is supported in image links but, as per the [commonmark recommendation][0], it is stripped back to a plain text representation. [0]: https://spec.commonmark.org/0.28/#example-547 - - - - - d4ee1ba5 by Alec Theriault at 2018-11-06T12:03:24-08:00 Accept test case - - - - - 8088aeb1 by Alec Theriault at 2018-11-06T12:03:24-08:00 Fix/add to haddock-library test suite - - - - - e78f644d by Alec Theriault at 2018-11-06T13:26:31-08:00 Bump version bounds - - - - - 644335eb by Alec Theriault at 2018-11-06T13:53:30-08:00 Merge pull request haskell/haddock#875 from harpocrates/feature/markup-in-hyperlinks Inline markup in markdown-style links and images - - - - - e173ed0d by Alec Theriault at 2018-11-07T12:37:18-08:00 Fix issues around plus/minus * swap the minimize unicode to something more intuitive * use new unicode expander/collapser for instance lists * address some alignment issues in the "index" page - - - - - b2d92df7 by Alec Theriault at 2018-11-07T13:41:57-08:00 Allow "Contents" summary to scroll in a fixed div In the unfortunate event that the "Contents" summary doesn't fit vertically (like in the "Prelude"), it will be scrollable. - - - - - ca704c23 by Alec Theriault at 2018-11-07T13:45:15-08:00 Accept HTML output changes - - - - - 82c0ec6d by Alec Theriault at 2018-11-07T18:12:54-08:00 overflow-y 'scroll' -> 'auto' - - - - - 571d7657 by Alec Theriault at 2018-11-08T19:44:12-08:00 Clicking on "Contents" navigates to top of page - - - - - 8065a012 by Alec Theriault at 2018-11-08T19:44:17-08:00 Space out functions more Also, functions and data decls now have the same space before and after them. - - - - - cc650ede by Alec Theriault at 2018-11-09T08:13:35-08:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 65f8c17f by Alec Theriault at 2018-11-10T14:04:06-08:00 Update changelog - - - - - 20473847 by Alec Theriault at 2018-11-10T14:21:40-08:00 Replace oplus/ominus expander/collapser icons with triangles - - - - - 16592957 by Alec Theriault at 2018-11-10T14:35:10-08:00 Merge pull request haskell/haddock#949 from haskell/wip/new-ocean Introduce NewOcean theme. - - - - - 357cefe1 by Alec Theriault at 2018-11-10T16:02:13-08:00 Merge branch 'ghc-8.6' into ghc-head - - - - - de612267 by Alec Theriault at 2018-11-11T20:01:21-08:00 Rename 'NewOcean' theme to 'Linuwial' - - - - - 954b5baa by Alec Theriault at 2018-11-12T08:33:18-08:00 Add blockquote styling Matches b71da1feabf33efbbc517ac376bb690b5a604c2f from hackage-server. Fixes haskell/haddock#967. - - - - - d32c0b0b by Fangyi Zhou at 2018-11-12T10:24:13-08:00 Fix some broken links (#15733) Summary: For links in subpackages as well. https://phabricator.haskell.org/D5257 Test Plan: Manually verify links Reviewers: mpickering, bgamari, osa1 Reviewed By: osa1 GHC Trac Issues: haskell/haddock#15733 Differential Revision: https://phabricator.haskell.org/D5262 - - - - - 41098b1f by Alp Mestanogullari at 2018-11-15T22:40:09+01:00 Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change It got introduced in ghc/ghc at ae2c9b40f5b6bf272251d1f4107c60003f541b62. - - - - - c5c1c7e0 by Alec Theriault at 2018-11-15T13:48:13-08:00 Merge pull request haskell/haddock#970 from alpmestan/alp/fix-promotionflag Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change - - - - - 6473d3a4 by Shayan-Najd at 2018-11-23T01:38:49+01:00 [TTG: Handling Source Locations] Foundation and Pat Trac Issues haskell/haddock#15495 This patch removes the ping-pong style from HsPat (only, for now), using the plan laid out at https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/HandlingSourceLocations (solution A). - the class `HasSrcSpan`, and its functions (e.g., `cL` and `dL`), are introduced - some instances of `HasSrcSpan` are introduced - some constructors `L` are replaced with `cL` - some patterns `L` are replaced with `dL->L` view pattern - some type annotation are necessarily updated (e.g., `Pat p` --> `Pat (GhcPass p)`) - - - - - 7a088dfe by Alec Theriault at 2018-11-26T11:11:28-08:00 More uniform handling of `forall`'s in HTML/LaTeX * don't forget to print explicit `forall`'s when there are arg docs * when printing an explicit `forall`, print all tyvars Fixes haskell/haddock#973 - - - - - d735e570 by Alec Theriault at 2018-12-12T08:42:09-08:00 Fix warnings, accept output * remove redundant imports (only brought to light due to recent work for improving redundant import detection) * fix a bug that was casuing exports to appear in reverse order * fix something in haddock-library that prevented compilation on old GHC's - - - - - a3852f8a by Zejun Wu at 2018-12-14T09:37:47-05:00 Output better debug infromation on internal error in extractDecl This will make investigation of haskell/haddock#979 easier - - - - - 2eccb5b9 by Alec Theriault at 2018-12-17T09:25:10-05:00 Refactor names + unused functions (#982) This commit should not introduce any change in functionality! * consistently use `getOccString` to convert `Name`s to strings * compare names directly when possible (instead of comparing strings) * get rid of unused utility functions - - - - - e82e4df8 by Alec Theriault at 2018-12-20T16:16:30-05:00 Load plugins when compiling each module (#983) * WIP: Load (typechecker) plugins from language pragmas * Revert "Load plugins when starting a GHC session (#905)" This reverts commit 72d82e52f2a6225686d9668790ac33c1d1743193. * Simplify plugin initialization code - - - - - 96e86f38 by Alec Theriault at 2018-12-23T10:23:20-05:00 Properly synify and render promoted type variables (#985) * Synify and render properly promoted type variables Fixes haskell/haddock#923. * Accept output - - - - - 23343345 by Alec Theriault at 2018-12-27T16:39:38-05:00 Remove `haddock-test`'s dep. on `syb` (#987) The functionality is easily inlined into one short function: `gmapEverywhere`. This doesn't warrant pulling in another package. - - - - - d0734f21 by Alec Theriault at 2018-12-27T16:39:52-05:00 Address deprecation warnings in `haddock-test` (#988) Fixes haskell/haddock#885. - - - - - 4d9f144e by mynguyen at 2018-12-30T23:42:26-05:00 Visible kind application haddock update - - - - - ffe0e9ed by Alec Theriault at 2019-01-07T13:55:22-08:00 Print kinded tyvars in constructors for Hoogle (#993) Fixes haskell/haddock#992 - - - - - 2e18b55d by Alec Theriault at 2019-01-10T16:42:45-08:00 Accept new output `GHC.Maybe` -> `Data.Maybe` (#996) Since 53874834b779ad0dfbcde6650069c37926da1b79 in GHC, "GHC.Maybe" is marked as `not-home`. That changes around some test output. - - - - - 055da666 by Gabor Greif at 2019-01-22T14:41:51+01:00 Lone typofix - - - - - 01bb71c9 by Alec Theriault at 2019-01-23T11:46:46-08:00 Keep forall on H98 existential data constructors (#1003) The information about whether or not there is a source-level `forall` is already available on a `ConDecl` (as `con_forall`), so we should use it instead of always assuming `False`! Fixes haskell/haddock#1002. - - - - - f9b9bc0e by Ryan Scott at 2019-01-27T09:28:12-08:00 Fix haskell/haddock#1004 with a pinch of dropForAlls - - - - - 5cfcdd0a by Alec Theriault at 2019-01-28T16:49:57-08:00 Loosen 'QuickCheck' and 'hspec' bounds It looks like the new versions don't cause any breakage and loosening the bounds helps deps fit in one stack resolver. - - - - - 3545d3dd by Alec Theriault at 2019-01-31T01:37:25-08:00 Use `.hie` files for the Hyperlinker backend (#977) # Summary This is a large architectural change to the Hyperlinker. * extract link (and now also type) information from `.hie` instead of doing ad-hoc SYB traversals of the `RenamedSource`. Also adds a superb type-on-hover feature (#715). * re-engineer the lexer to avoid needless string conversions. By going directly through GHC's `P` monad and taking bytestring slices, we avoid a ton of allocation and have better handling of position pragmas and CPP. In terms of performance, the Haddock side of things has gotten _much_ more efficient. Unfortunately, much of this is cancelled out by the increased GHC workload for generating `.hie` files. For the full set of boot libs (including `ghc`-the-library) * the sum of total time went down by 9-10% overall * the sum of total allocations went down by 6-7% # Motivation Haddock is moving towards working entirely over `.hi` and `.hie` files. This change means we no longer need the `RenamedSource` from `TypecheckedModule` (something which is _not_ in `.hi` files). # Details Along the way a bunch of things were fixed: * Cross package (and other) links are now more reliable (#496) * The lexer tries to recover from errors on every line (instead of at CPP boundaries) * `LINE`/`COLUMN` pragmas are taken into account * filter out zero length tokens before rendering * avoid recomputing the `ModuleName`-based `SrcMap` * remove the last use of `Documentation.Haddock.Utf8` (see haskell/haddock#998) * restructure temporary folder logic for `.hi`/`.hie` model - - - - - 2ded3359 by Herbert Valerio Riedel at 2019-02-02T12:06:12+01:00 Update/modernise haddock-library.cabal file - - - - - 62b93451 by Herbert Valerio Riedel at 2019-02-02T12:19:31+01:00 Tentatively declare support for unreleased base-4.13/ghc-8.8 - - - - - 6041e767 by Herbert Valerio Riedel at 2019-02-02T16:04:32+01:00 Normalise LICENSE text w/ cabal's BSD2 template Also, correct the `.cabal` files to advertise `BSD2` instead of the incorrect `BSD3` license. - - - - - 0b459d7f by Alec Theriault at 2019-02-02T18:06:12-08:00 CI: fetch GHC from validate artifact Should help make CI be less broken - - - - - 6b5c07cf by Alec Theriault at 2019-02-02T18:06:12-08:00 Fix some Hyperlinker test suite fallout * Amend `ParserSpec` to match new Hyperlinker API - pass in compiler info - strip out null tokens * Make `hypsrc-test` pass reliably - strip out `local-*` ids - strip out `line-*` ids from the `ClangCppBug` test - re-accept output - - - - - ded34791 by Nathan Collins at 2019-02-02T18:31:23-08:00 Update README instructions for Stack No need to `stack install` Haddock to test it. Indeed, `stack install` changes the `haddock` on user's `PATH` if `~/.local/bin` is on user's `PATH` which may not be desirable when hacking on Haddock. - - - - - 723298c9 by Alec Theriault at 2019-02-03T09:11:05-08:00 Remove `Documentation.Haddock.Utf8` The circumstances under which this module appeared are completely gone. The Hyperlinker backend no longer needs this module (it uses the more efficient `Encoding` module from `ghc`). Why no deprecation? Because this module really shouldn't exist! - It isn't used in `haddock-library`/`haddock-api` anymore - It was copy pasted directly from `utf8-string` - Folks seeking a boot-lib only solution can use `ghc`'s `Encoding` - - - - - 51050006 by Alec Theriault at 2019-02-03T22:58:58-08:00 Miscellaneous improvements to `Convert` (#1020) Now that Haddock is moving towards working entirely over `.hi` and `.hie` files, all declarations and types are going to be synthesized via the `Convert` module. In preparation for this change, here are a bunch of fixes to this module: * Add kind annotations to type variables in `forall`'s whose kind is not `Type`, unless the kind can be inferred from some later use of the variable. See `implicitForAll` and `noKindTyVars` in particular if you wish to dive into this. * Properly detect `HsQualTy` in `synifyType`. This is done by following suit with what GHC's `toIfaceTypeX` does and checking the first argument of `FunTy{} :: Type` to see if it classified as a given/wanted in the typechecker (see `isPredTy`). * Beef up the logic around figuring out when an explicit `forall` is needed. This includes: observing if any of the type variables will need kind signatures, if the inferred type variable order _without_ a forall will still match the one GHC claims, and some other small things. * Add some (not yet used) functionality for default levity polymorphic type signatures. This functionality similar to `fprint-explicit-runtime-reps`. Couple other smaller fixes only worth mentioning: * Show the family result signature only when it isn't `Type` * Fix rendering of implicit parameters in the LaTeX and Hoogle backends * Better handling of the return kind of polykinded H98 data declarations * Class decls produced by `tyThingToLHsDecl` now contain associated type defaults and default method signatures when appropriate * Filter out more `forall`'s in pattern synonyms - - - - - 841980c4 by Oleg Grenrus at 2019-02-04T08:44:25-08:00 Make a fixture of weird parsing of lists (#997) The second example is interesting. If there's a list directly after the header, and that list has deeper structure, the parser is confused: It finds two lists: - One with the first nested element, - everything after it I'm not trying to fix this, as I'm not even sure this is a bug, and not a feature. - - - - - 7315c0c8 by Ryan Scott at 2019-02-04T12:17:56-08:00 Fix haskell/haddock#1015 with dataConUserTyVars (#1022) The central trick in this patch is to use `dataConUserTyVars` instead of `univ_tvs ++ ex_tvs`, which displays the foralls in a GADT constructor in a way that's more faithful to how the user originally wrote it. Fixes haskell/haddock#1015. - - - - - ee0b49a3 by Ryan Scott at 2019-02-04T15:25:17-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. - - - - - 1c850dc8 by Alan Zimmerman at 2019-02-05T21:54:18+02:00 Matching changes in GHC for haskell/haddock#16236 - - - - - ab03c38e by Simon Marlow at 2019-02-06T08:07:33+00:00 Merge pull request haskell/haddock#1014 from hvr/pr/bsd2-normalise Normalise LICENSE text w/ cabal's BSD2 template - - - - - 5a92ccae by Alec Theriault at 2019-02-10T06:21:55-05:00 Merge remote-tracking branch 'gitlab/wip/T16236-2' into ghc-head - - - - - c0485a1d by Alec Theriault at 2019-02-10T03:32:52-08:00 Removes `haddock-test`s dependency on `xml`/`xhtml` (#1027) This means that `html-test`, `latex-test`, `hoogle-test`, and `hypsrc-test` now only depend on GHC boot libs. So we should now be able to build and run these as part of GHC's testsuite. \o/ The reference output has changed very slightly, in three ways: * we don't convert quotes back into `&quot;` as the `xml` lib did * we don't add extra `&nbsp;` as the `xml` lib did * we now remove the entire footer `div` (instead of just emptying it) - - - - - 65a448e3 by Alec Theriault at 2019-02-11T12:27:41-05:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - 360ca937 by Alec Theriault at 2019-02-13T11:36:11-05:00 Clean up logic for guessing `-B` and `--lib` (#1026) Haddock built with the `in-ghc-tree` flag tries harder to find the GHC lib folder and its own resources. This should make it possible to use `in-ghc-tree`-built Haddock without having to specify the `-B` and `--lib` options (just how you can use in-tree GHC without always specifying the `-B` option). The logic to do this relies on `getExecutablePath`, so we only get this auto-detection on platforms where this function works. - - - - - d583e364 by Alec Theriault at 2019-02-16T10:41:22-05:00 Fix tests broken by GHC Changes in 19626218566ea709b5f6f287d3c296b0c4021de2 affected some of the hyperlinker output. Accepted the new output (hovering over a `..` now shows you what that wildcard binds). Also fixed some stray deprecation warnings. - - - - - da0c42cc by Vladislav Zavialov at 2019-02-17T11:39:19+03:00 Parser changes to match !380 - - - - - ab96bed7 by Ryan Scott at 2019-02-18T04:44:08-05:00 Bump ghc version to 8.9 - - - - - 44b7c714 by Alec Theriault at 2019-02-22T05:49:43-08:00 Match GHC changes for T16185 `FunTy` now has an `AnonArgFlag` that indicates whether the arrow is a `t1 => t2` or `t1 -> t2`. This commit shouldn't change any functionality in Haddock. - - - - - 2ee653b1 by Alec Theriault at 2019-02-24T18:53:33-08:00 Update .travis.yml Points to the new GHC CI artifact. - - - - - 90939d71 by Alec Theriault at 2019-02-25T00:42:41-08:00 Support value/type namespaces on identifier links Identifier links can be prefixed with a 'v' or 't' to indicate the value or type namespace of the desired identifier. For example: -- | Some link to a value: v'Data.Functor.Identity' -- -- Some link to a type: t'Data.Functor.Identity' The default is still the type (with a warning about the ambiguity) - - - - - d6ed496c by Alec Theriault at 2019-02-25T00:42:46-08:00 Better identifier parsing * '(<|>)' and '`elem`' now get parsed and rendered properly as links * 'DbModule'/'DbUnitId' now properly get split apart into two links * tuple names now get parsed properly * some more small niceties... The identifier parsing code is more precise and more efficient (although to be fair: it is also longer and in its own module). On the rendering side, we need to pipe through information about backticks/parens/neither all the way through from renaming to the backends. In terms of impact: a total of 35 modules in the entirety of the bootlib + ghc lib docs change. The only "regression" is things like '\0'. These should be changed to @\\0@ (the path by which this previously worked seems accidental). - - - - - 3c3b404c by Alec Theriault at 2019-02-25T22:12:11-08:00 Fix standalone deriving docs Docs on standalone deriving decls for classes with associated types should be associated with the class instance, not the associated type instance. Fixes haskell/haddock#1033 - - - - - d51ef69e by Alec Theriault at 2019-02-26T19:14:59-08:00 Fix bogus identifier defaulting This avoids a situation in which an identifier would get defaulted to a completely different identifier. Prior to this commit, the 'Bug1035' test case would hyperlink 'Foo' into 'Bar'! Fixes haskell/haddock#1035. - - - - - 88cbbdc7 by Ryan Scott at 2019-02-27T10:14:03-05:00 Visible dependent quantification (#16326) changes - - - - - 0dcf6cee by Xia Li-yao at 2019-02-27T21:53:27-05:00 Menu item controlling which instances are expanded/collapsed (#1007) Adds a menu item (like "Quick Jump") for options related to displaying instances. This provides functionality for: * expanding/collapsing all instances on the currently opened page * controlling whether instances are expanded/collapsed by default * controlling whether the state of instances should be "remembered" This new functionality is implemented in Typescript in `details-helper`. The built-in-themes style switcher also got a revamp so that all three of QuickJump, the style switcher, and instance preferences now have the same style and implementation structure. See also: https://mail.haskell.org/pipermail/haskell-cafe/2019-January/130495.html Fixes haskell/haddock#698. Co-authored-by: Lysxia <lysxia at gmail.com> Co-authored-by: Nathan Collins <conathan at galois.com> - - - - - 3828c0fb by Alec Theriault at 2019-02-28T12:42:49-05:00 `--show-interface` should output to stdout. (#1040) Fixes haskell/haddock#864. - - - - - a50f4cda by gbaz at 2019-03-01T07:43:16-08:00 Increase contrast of Linuwal theme (#1037) This is to address the concern that, on less nice and older screens, some of the shades of grey blend in too easily with the white background. * darken the font slightly * darken slightly the grey behind type signatures and such * add a border and round the corners on code blocks * knock the font down by one point - - - - - ab4d41de by Alec Theriault at 2019-03-03T09:23:26-08:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 12f509eb by Ben Gamari at 2019-03-04T22:13:20-05:00 Remove reference to Opt_SplitObjs flag Split-objects has been removed. - - - - - 5b3e4c9a by Ryan Scott at 2019-03-06T19:16:24-05:00 Update html-test output to reflect haskell/haddock#16391 changes - - - - - fc228af1 by Alec Theriault at 2019-03-09T08:29:23-08:00 Match changes for "Stop inferring over-polymorphic kinds" The `hsq_ext` field of `HsQTvs` is now just the implicit variables (instead of also including information about which of these variables are dependent). This commit shouldn't change any functionality in Haddock. - - - - - 6ac109eb by Alec Theriault at 2019-03-09T11:22:55-08:00 Add .hi, .dyn_hi, etc files to .gitignore Fixes haskell/haddock#1030. - - - - - b55f0c05 by Alec Theriault at 2019-03-09T11:22:55-08:00 Better support for default methods in classes * default methods now get rendered differently * default associated types get rendered * fix a forgotten `s/TypeSig/ClassOpSig/` refactor in LaTeX backend * LaTeX backend now renders default method signatures NB: there is still no way to document default class members and the NB: LaTeX backend still crashes on associated types - - - - - 10aea0cf by Alec Theriault at 2019-03-09T11:22:55-08:00 Avoid multi-line `emph` in LaTeX backend `markupWarning` often processes inputs which span across paragraphs. Unfortunately, LaTeX's `emph` is not made to handle this (and will crash). Fixes haskell/haddock#936. - - - - - d22dc2c9 by Alec Theriault at 2019-03-09T11:22:55-08:00 Many LaTeX backend fixes After this commit, we can run with `--latex` on all boot libraries without crashing (although the generated LaTeX still fails to compile in a handful of larger packages like `ghc` and `base`). * Add newlines after all block elements in LaTeX. This is important to prevent the final output from being more an more indented. See the `latext-test/src/Example` test case for a sample of this. * Support associated types in class declarations (but not yet defaults) * Several small issues for producing compiling LaTeX; - avoid empy `\haddockbeginargs` lists (ex: `type family Any`) - properly escape identifiers depending on context (ex: `Int#`) - add `vbox` around `itemize`/`enumerate` (so they can be in tables) * Several spacing fixes: - limit the width of `Pretty`-arranged monospaced code - cut out extra space characters in export lists - only escape spaces if there are _multiple_ spaces - allow type signatures to be multiline (even without docs) * Remove uninteresting and repetitive `main.tex`/`haddock.sty` files from `latex-test` test reference output. Fixes haskell/haddock#935, haskell/haddock#929 (LaTeX docs for `text` build & compile) Fixes haskell/haddock#727, haskell/haddock#930 (I think both are really about type families...) - - - - - 0e6cee00 by Alec Theriault at 2019-03-29T12:11:56-07:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - ce05434d by Alan Zimmerman at 2019-03-29T12:12:11-07:00 Matching changes in GHC for haskell/haddock#16236 (cherry picked from commit 3ee6526d4ae7bf4deb7cd1caf24b3d7355573576) - - - - - d85766b2 by Ben Gamari at 2019-03-29T12:14:04-07:00 Bump GHC to 8.8 - - - - - 5a82cbaf by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Redo ParseModuleHeader - - - - - b9033348 by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - bb55c8f4 by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove outdated `.ghci` files and `scripts` The `.ghci` files are actively annoying when trying to `cabal v2-repl`. As for the `scripts`, the distribution workflow is completely different. - - - - - 5ee244dc by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove obsolete arcanist files + STYLE Now that GHC is hosted on Gitlab, the arcanist files don't make sense anymore. The STYLE file contains nothing more than a dead link too. - - - - - d07c1928 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Redo ParseModuleHeader - - - - - 492762d2 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - af2ac773 by Ryan Scott at 2019-05-14T17:22:13-04:00 Changes for haskell/haddock#16110/#16356 - - - - - 6820ed0d by Alec Theriault at 2019-05-17T08:51:27-07:00 Unbreak haskell/haddock#1004 test case `fail` is no longer part of `Monad`. - - - - - 6bf7be98 by Alec Theriault at 2019-05-17T08:51:27-07:00 Fix haskell/haddock#1063 with better parenthesization logic for contexts The only other change in html/hoogle/hyperlinker output for the boot libraries that this caused is a fix to some Hoogle output for implicit params. ``` $ diff -r _build/docs/ old_docs diff -r _build/docs/html/libraries/base/base.txt old_docs/html/libraries/base/base.txt 13296c13296 < assertError :: (?callStack :: CallStack) => Bool -> a -> a --- > assertError :: ?callStack :: CallStack => Bool -> a -> a ``` - - - - - b5716b61 by Ryan Scott at 2019-05-22T17:24:32-04:00 Match changes with haskell/haddock#14332 - - - - - c115abf6 by Alec Theriault at 2019-05-26T16:01:58-04:00 Remove Haddock's dependency on `Cabal` At this point, Haddock depended on Cabal-the-library solely for a verbosity parser (which misleadingly accepts all sorts of verbosity options that Haddock never uses). Now, the only dependency on Cabal is for `haddock-test` (which uses Cabal to locate the Haddock interface files of a couple boot libraries). - - - - - e5b2d4a3 by Alec Theriault at 2019-05-26T16:16:25-04:00 Regression test: promoted lists in associated types When possible, associated types with promoted lists should use the promoted list literal syntax (instead of repeated applications of ': and '[]). This was fixed in 2122de5473fd5b434af690ff9ccb1a2e58491f8c. Closes haskell/haddock#466, - - - - - cc5ad5d3 by Alec Theriault at 2019-05-26T17:55:54-04:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 4b3301a6 by Alec Theriault at 2019-05-26T17:57:52-04:00 Release haddock-2.23, haddock-library-1.8.0 Tentatively adjust bounds and changelogs for the release to be bundled with GHC 8.8.1. - - - - - 69c7cfce by Matthew Pickering at 2019-05-30T10:54:27+01:00 Update hyperlinker tests for new types in .hie files - - - - - 29b7e738 by Zubin Duggal at 2019-05-30T10:57:51+01:00 update for new way to store hiefile headers - - - - - aeca5d5f by Zubin Duggal at 2019-06-04T18:57:42-04:00 update for new way to store hiefile headers - - - - - ba2ca518 by Ben Gamari at 2019-06-07T23:11:14+00:00 Update test output for introduction of Safe-Inferred - - - - - 3a975a6c by Ryan Scott at 2019-07-03T12:06:27-04:00 Changes for haskell/haddock#15247 - - - - - 0df46555 by Zubin Duggal at 2019-07-22T10:52:50+01:00 Fix haddockHypsrcTest - - - - - 2688686b by Sylvain Henry at 2019-09-12T23:19:39+02:00 Fix for GHC module renaming - - - - - 9ec0f3fc by Alec Theriault at 2019-09-20T03:21:00-04:00 Fix Travis CI, loosen .cabal bounds (#1089) Tentatively for the 2.23 release: * updated Travis CI to work again * tweaked bounds in the `.cabal` files * adjusted `extra-source-files` to properly identify test files - - - - - ca559beb by Matthías Páll Gissurarson at 2019-09-28T12:14:40-04:00 Small change in to facilitate extended typed-holes (#1090) This change has no functional effect on haddock itself, it just changes one pattern to use `_ (` rather than `_(`, so that we may use `_(` as a token for extended typed-holes later. - - - - - 02e28976 by Vladislav Zavialov at 2019-09-28T12:17:45-04:00 Remove spaces around @-patterns (#1093) This is needed to compile `haddock` when [GHC Proposal haskell/haddock#229](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0229-whitespace-bang-patterns.rst) is implemented. - - - - - 83cbbf55 by Alexis King at 2019-09-30T21:12:42-04:00 Fix the ignore-exports option (#1082) The `ignore-exports` option has been broken since haskell/haddock#688, as mentioned in https://github.com/haskell/haddock/pull/766#issue-172505043. This PR fixes it. - - - - - e127e0ab by Ben Gamari at 2019-10-06T15:12:06-04:00 Fix a few haddock issues - - - - - 3a0f5c89 by Zubin Duggal at 2019-10-07T17:56:13-04:00 Fix crash when there are no srcspans in the file due to CPP - - - - - 339c5ff8 by Alec Theriault at 2019-10-07T17:56:13-04:00 Prefer un-hyperlinked sources to no sources It is possible to fail to extract an HIE ast. This is however not a reason to produce _no_ output - we should still make a colorized HTML page. - - - - - d47ef478 by Alec Theriault at 2019-10-07T17:56:13-04:00 Add a regression test for haskell/haddock#1091 Previously, this input would crash Haddock. - - - - - ed7c8b0f by Alec Theriault at 2019-10-07T20:56:48-04:00 Add Hyperlinker test cases for TH-related stuff Hopefully this will guard against regressions around quasiquotes, TH quotes, and TH splices. - - - - - d00436ab by Andreas Klebinger at 2019-10-21T15:53:03+02:00 Refactor for withTiming changes. - - - - - 4230e712 by Ben Gamari at 2019-10-22T09:36:37-04:00 Merge pull request haskell/haddock#1101 from AndreasPK/withTimingRefactor Refactor for withTiming changes. - - - - - d155c5f4 by Ryan Scott at 2019-10-23T10:37:17-04:00 Reify oversaturated data family instances correctly (#1103) This fixes haskell/haddock#1103 by adapting the corresponding patch for GHC (see https://gitlab.haskell.org/ghc/ghc/issues/17296 and https://gitlab.haskell.org/ghc/ghc/merge_requests/1877). - - - - - 331a5adf by Sebastian Graf at 2019-10-25T17:14:40+02:00 Refactor for OutputableBndrId changes - - - - - 48a490e0 by Ben Gamari at 2019-10-27T10:16:16-04:00 Merge pull request haskell/haddock#1105 from sgraf812/wip/flexible-outputable Refactor for OutputableBndrId changes - - - - - f62a7dfc by Sebastian Graf at 2019-11-01T11:54:16+00:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - d9b242ed by Ryan Scott at 2019-11-03T13:20:03-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. (cherry picked from commit cfd682c5fd03b099a3d78c44f9279faf56a0ac70) - - - - - dfd42406 by Sebastian Graf at 2019-11-04T07:02:14-05:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - 0b15be7c by Ben Gamari at 2019-11-09T13:21:33-05:00 Import isRuntimeRepVar from Type rather than TyCoRep isRuntimeRepVar is not longer exported from TyCoRep due to ghc#17441. - - - - - 091f7283 by Ben Gamari at 2019-11-10T12:47:06-05:00 Bump to GHC 8.10 - - - - - e88c71f2 by Ben Gamari at 2019-11-14T00:22:24-05:00 Merge pull request haskell/haddock#1110 from haskell/wip/T17441 Import isRuntimeRepVar from Type rather than TyCoRep - - - - - 4e0bbc17 by Ben Gamari at 2019-11-14T00:22:45-05:00 Version bumps for GHC 8.11 - - - - - 0e85ceb4 by Ben Gamari at 2019-11-15T11:59:45-05:00 Bump to GHC 8.10 - - - - - 00d6d68b by Ben Gamari at 2019-11-16T18:35:58-05:00 Bump ghc version to 8.11 - - - - - dde1fc3f by Ben Gamari at 2019-11-16T20:40:37-05:00 Drop support for base 4.13 - - - - - f52e331d by Vladislav Zavialov at 2019-11-24T13:02:28+03:00 Update Hyperlinker.Parser.classify to use ITdollar - - - - - 1ad96198 by Vladislav Zavialov at 2019-11-28T16:12:33+03:00 Remove HasSrcSpan (#17494) - - - - - 651afd70 by Herbert Valerio Riedel at 2019-12-08T12:08:16+01:00 Document error-prone conditional definition of instances This can easily trip up people if one isn't aware of it. Usually it's better to avoid this kind of conditionality especially for typeclasses for which there's an compat-package as conditional instances like these tend to fragment the ecosystem into those packages that go the extra mile to provide backward compat via those compat-packages and those that fail to do so. - - - - - b521af56 by Herbert Valerio Riedel at 2019-12-08T12:09:54+01:00 Fix build-failure regression for base < 4.7 The `$>` operator definition is available only since base-4.7 which unfortunately wasn't caught before release to Hackage (but has been fixed up by a metadata-revision) This commit introduces a `CompatPrelude` module which allows to reduce the amount of CPP by ousting it to a central location, i.e. the new `CompatPrelude` module. This pattern also tends to reduce the tricks needed to silence unused import warnings. Addresses haskell/haddock#1119 - - - - - 556c375d by Sylvain Henry at 2020-01-02T19:01:55+01:00 Fix after Iface modules renaming - - - - - bd6c53e5 by Sylvain Henry at 2020-01-07T00:48:48+01:00 hsyl20-modules-renamer - - - - - fb23713b by Ryan Scott at 2020-01-08T07:41:13-05:00 Changes for GHC#17608 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2372 - - - - - 4a4dd382 by Ryan Scott at 2020-01-25T08:08:26-05:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - e782a44d by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename PackageConfig into UnitInfo - - - - - ba3c9f05 by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename lookupPackage - - - - - ab37f9b3 by Ben Gamari at 2020-01-29T13:00:44-05:00 Merge pull request haskell/haddock#1125 from haskell/wip/T17566-take-two Changes for GHC#17566 - - - - - 3ebd5ae0 by Ryan Scott at 2020-01-31T05:56:50-05:00 Merge branch 'wip-hsyl20-package-refactor' into ghc-head - - - - - 602a747e by Richard Eisenberg at 2020-02-04T09:05:43+00:00 Echo GHC's removal of PlaceHolder module This goes with GHC's !2083. - - - - - ccfe5679 by Sylvain Henry at 2020-02-10T10:13:56+01:00 Module hierarchy: runtime (cf haskell/haddock#13009) - - - - - 554914ce by Cale Gibbard at 2020-02-10T16:10:39-05:00 Fix build of haddock in stage1 We have to use the correct version of the GHC API, but the version of the compiler itself doesn't matter. - - - - - 5b6fa2a7 by John Ericson at 2020-02-10T16:18:07-05:00 Noramlize `tested-with` fields in cabal files - - - - - e6eb3ebe by Vladislav Zavialov at 2020-02-16T13:25:26+03:00 No MonadFail/Alternative for P - - - - - 90e181f7 by Ben Gamari at 2020-02-18T14:13:47-05:00 Merge pull request haskell/haddock#1129 from obsidiansystems/wip/fix-stage1-build Fix build of haddock in stage1 - - - - - 93b64636 by Sylvain Henry at 2020-02-19T11:20:27+01:00 Modules: Driver (#13009) - - - - - da4f6c7b by Vladislav Zavialov at 2020-02-22T15:33:02+03:00 Use RealSrcSpan in InstMap - - - - - 479b1b50 by Ben Gamari at 2020-02-23T10:28:13-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 55ecacf0 by Sylvain Henry at 2020-02-25T15:18:27+01:00 Modules: Core (#13009) - - - - - 60867b3b by Vladislav Zavialov at 2020-02-28T15:53:52+03:00 Ignore the BufLoc/BufSpan added in GHC's !2516 - - - - - 1e5506d3 by Sylvain Henry at 2020-03-02T12:32:43+01:00 Modules: Core (#13009) - - - - - 6fb53177 by Richard Eisenberg at 2020-03-09T14:49:40+00:00 Changes in GHC's !1913. - - - - - 30b792ea by Ben Gamari at 2020-03-16T12:45:02-04:00 Merge pull request haskell/haddock#1130 from hsyl20/wip/hsyl20-modules-core2 Modules: Core (#13009) - - - - - cd761ffa by Sylvain Henry at 2020-03-18T15:24:00+01:00 Modules: Types - - - - - b6646486 by Ben Gamari at 2020-03-18T14:42:43-04:00 Merge pull request haskell/haddock#1133 from hsyl20/wip/hsyl20/modules/types Modules: Types - - - - - 9325d734 by Kleidukos at 2020-03-19T12:38:31-04:00 Replace the 'caption' class so that the collapsible sections are shown - - - - - 5e2bb555 by Kleidukos at 2020-03-19T12:38:31-04:00 Force ghc-8.8.3 - - - - - c6fcd0aa by Kleidukos at 2020-03-19T12:38:31-04:00 Update test fixtures - - - - - 5c849cb1 by Sylvain Henry at 2020-03-20T09:34:39+01:00 Modules: Types - - - - - 7f439155 by Alec Theriault at 2020-03-20T20:17:01-04:00 Merge branch 'ghc-8.8' into ghc-8.10 - - - - - b7904e5c by Alina Banerjee at 2020-03-20T20:24:17-04:00 Update parsing to strip whitespace from table cells (#1074) * Update parsing to strip leading & trailing whitespace from table cells * Update fixture data to disallow whitespaces at both ends in table cells * Add test case for whitespaces stripped from both ends of table cells * Update table reference test data for html tests - - - - - b9d60a59 by Alec Theriault at 2020-03-22T11:46:42-04:00 Clean up warnings * unused imports * imports of `Data.List` without import lists * missing `CompatPrelude` file in `.cabal` - - - - - 0c317dbe by Alec Theriault at 2020-03-22T18:46:54-04:00 Fix NPM security warnings This was done by calling `npm audit fix`. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. - - - - - 6e306242 by Alec Theriault at 2020-03-22T20:10:52-04:00 Tentative 2.24 release Adjusted changelogs and versions in `.cabal` files in preparation for the upcoming release bundled with GHC 8.10. - - - - - 1bfb4645 by Ben Gamari at 2020-03-23T16:40:54-04:00 Merge commit '3c2944c037263b426c4fe60a3424c27b852ea71c' into HEAD More changes from the GHC types module refactoring. - - - - - be8c6f3d by Alec Theriault at 2020-03-26T20:10:53-04:00 Update `.travis.yml` to work with GHC 8.10.1 * Regenerated the Travis file with `haskell-ci` * Beef up `.cabal` files with more `tested-with` information - - - - - b025a9c6 by Alec Theriault at 2020-03-26T20:10:53-04:00 Update README Removed some out of date links/info, added some more useful links. * badge to Hackage * update old trac link * `ghc-head` => `ghc-8.10` * `cabal new-*` is now `cabal v2-*` and it should Just Work * `--test-option='--accept'` is the way to accept testsuite output - - - - - 564d889a by Alec Theriault at 2020-03-27T20:34:33-04:00 Fix crash in `haddock-library` on unicode space Our quickcheck tests for `haddock-library` stumbled across an edge case input that was causing Haddock to crash: it was a unicode space character. The root cause of the crash is that we were implicitly assuming that if a space character was not " \t\f\v\r", it would have to be "\n". We fix this by instead defining horizontal space as: any space character that is not '\n'. Fixes haskell/haddock#1142 - - - - - 2d360ba1 by Alec Theriault at 2020-03-27T21:57:32-04:00 Disallow qualified uses of reserved identifiers This a GHC bug (https://gitlab.haskell.org/ghc/ghc/issues/14109) too, but it is a relatively easy fix in Haddock. Note that the fix must live in `haddock-api` instead of `haddock-library` because we can only really decide if an identifier is a reserved one by asking the GHC lexer. Fixes haskell/haddock#952 - - - - - 47ae22ed by Alec Theriault at 2020-03-28T13:36:25-04:00 Remove unused `Haddock.Utils` functions * removed functions in `Haddock.Utils` that were not used anywhere (or exported from the `haddock-api` package) * moved GHC-specific utils from `Haddock.Utils` to `Haddock.GhcUtils` - - - - - c0291245 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use TTG empty extensions to remove some `error`'s None of these error cases should ever have been reachable, so this is just a matter of leveraging the type system to assert this. * Use the `NoExtCon` and `noExtCon` to handle case matches for no extension constructors, instead of throwing an `error`. * Use the extension field of `HsSpliceTy` to ensure that this variant of `HsType` cannot exist in an `HsType DocNameI`. - - - - - 0aff8dc4 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use `unLoc`/`noLoc` from GHC instead of `unL`/`reL` * `unL` is already defined by GHC as `unLoc` * `reL` is already defined by GHC as `noLoc` (in a safer way too!) * Condense `setOutputDir` and add a about exporting from GHC Fixes haskell/haddock#978 - - - - - bf6f2fb7 by Alec Theriault at 2020-03-28T13:36:25-04:00 Cleanup up GHC flags in `.cabal` files * enable more useful warning flags in `haddock-api`, handle the new warnings generated * remove `-fwarn-tabs` (now we'd use `-Wtabs`, but this has been in `-Wall` for a while now) - - - - - c576fbf1 by Alec Theriault at 2020-03-28T13:36:25-04:00 `haddock-library` document header level Document the fact the header level is going to always be between 1 and 6 inclusive. Along the way, I also optimized the parsing code a bit. - - - - - 71bce0ee by Alec Theriault at 2020-03-28T14:26:27-04:00 Disallow links in section headers This is quite straightforward to implement, since we already had a function `docToHtmlNoAnchors` (which we used to generate the link in the sidebar "Contents"). This breaks test `Bug387`, but that test case has aged badly: we now automatically generate anchors for all headings, so manually adding an anchor in a section makes no sense. Nested anchors are, as pointed out in haskell/haddock#1054, disallowed by the HTML standard. Fixes haskell/haddock#1054 - - - - - b461b0ed by Sylvain Henry at 2020-03-30T10:34:23+02:00 Modules: type checker - - - - - cd8cd1ee by Ben Gamari at 2020-03-31T12:45:02-04:00 Merge pull request haskell/haddock#1152 from hsyl20/wip/hsyl20/modules/tc Module renaming - - - - - 5e8f8ea7 by Felix Yan at 2020-04-01T17:58:06-07:00 Allow QuickCheck 2.14 Builds fine and all tests pass. - - - - - dc6b1633 by Sylvain Henry at 2020-04-05T16:43:44+02:00 Module renaming: amend previous patch - - - - - eee2f4ae by Ryan Scott at 2020-04-05T09:04:43-07:00 Fix haskell/haddock#1050 by filtering out invisible AppTy arguments This makes the `synifyType` case for `AppTy` more intelligent by taking into consideration the visibilities of each `AppTy` argument and filtering out any invisible arguments, as they aren't intended to be displayed in the source code. (See haskell/haddock#1050 for an example of what can happen if you fail to filter these out.) Along the way, I noticed that a special `synifyType` case for `AppTy t1 (CoercionTy {})` could be consolidated with the case below it, so I took the opportunity to tidy this up. - - - - - 23eb99e8 by Ben Gamari at 2020-04-07T11:19:58-04:00 Merge pull request haskell/haddock#1154 from hsyl20/wip/hsyl20/modules/tc Module renaming: amend previous patch - - - - - 072d994d by Ryan Scott at 2020-04-07T19:32:47-04:00 Make NoExtCon fields strict These changes are a part of a fix for [GHC#17992](https://gitlab.haskell.org/ghc/ghc/issues/17992). - - - - - d8ebf6c8 by Ignat Insarov at 2020-04-09T21:15:01-04:00 Recode Doc to Json. (#1159) * Recode Doc to Json. * More descriptive field labels. - - - - - 52df4b4e by Sylvain Henry at 2020-04-10T12:39:18+02:00 Module renaming - - - - - d9ab8ec8 by Cale Gibbard at 2020-04-14T11:43:34-04:00 Add instance of XCollectPat for DocNameI - - - - - 323d221d by Cale Gibbard at 2020-04-14T11:43:34-04:00 Rename XCollectPat -> CollectPass - - - - - 2df80867 by Alec Theriault at 2020-04-15T07:30:51-07:00 Prune docstrings that are never rendered When first creating a Haddock interface, trim `ifaceDocMap` and `ifaceArgMap` to not include docstrings that can never appear in the final output. Besides checking with GHC which names are exported, we also need to keep all the docs attached to instance declarations (it is much tougher to detect when an instance is fully private). This change means: * slightly smaller interface files (7% reduction on boot libs) * slightly less work to do processing docstrings that aren't used * no warnings in Haddock's output about private docstrings (see haskell/haddock#1070) I've tested manually that this does not affect any of the boot library generated docs (the only change in output was some small re-ordering in a handful of instance lists). This should mean no docstrings have been incorrectly dropped. - - - - - f49c90cc by Alec Theriault at 2020-04-15T07:30:51-07:00 Don't warn about missing links in miminal sigs When renaming the Haddock interface, never emit warnings when renaming a minimal signature. Also added some documention around `renameInterface`. Minimal signatures intentionally include references to potentially un-exported methods (see the discussion in haskell/haddock#330), so it is expected that they will not always have a link destination. On the principle that warnings should always be resolvable, this shouldn't produce a warning. See haskell/haddock#1070. - - - - - a9eda64d by Ben Gamari at 2020-04-17T09:27:35-04:00 Merge pull request haskell/haddock#1160 from hsyl20/wip/hsyl20/modules/systools Module renaming - - - - - f40d7879 by Cale Gibbard at 2020-04-20T11:30:38-04:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ttg-con-pat - - - - - a50e7753 by Ben Gamari at 2020-04-20T11:36:10-04:00 Merge pull request haskell/haddock#1165 from obsidiansystems/wip/ttg-con-pat Trees that Grow refactor (GHC !2553) - - - - - 6a24795c by Alec Theriault at 2020-04-21T08:06:45-07:00 Fallback to `hiDecl` when `extractDecl` fails Sometimes, the declaration being exported is a subdecl (for instance, a record accessor getting exported at the top-level). For these cases, Haddock has to find a way to produce some synthetic sensible top-level declaration. This is done with `extractDecl`. As is shown by haskell/haddock#1067, this is sometimes impossible to do just at a syntactic level (for instance when the subdecl is re-exported). In these cases, the only sensible thing to do is to try to reify a declaration based on a GHC `TyThing` via `hiDecl`. - - - - - eee1a8b7 by Sylvain Henry at 2020-04-24T15:46:05+02:00 Module structure - - - - - 50b9259c by Iñaki at 2020-04-25T18:38:11-04:00 Add support for custom section anchors (#1179) This allows to have stable anchors for groups, even if the set of groups in the documentation is altered. The syntax for setting the anchor of a group is -- * Group name #desiredAnchor# Which will produce an html anchor of the form '#g:desiredAnchor' Co-authored-by: Iñaki García Etxebarria <git at inaki.blueleaf.cc> - - - - - 4003c97a by Ben Gamari at 2020-04-26T09:35:15-04:00 Merge pull request haskell/haddock#1166 from hsyl20/wip/hsyl20/modules/utils Module structure - - - - - 5206ab60 by Sylvain Henry at 2020-04-27T16:47:39+02:00 Renamed UnitInfo fields - - - - - c32c333b by Sylvain Henry at 2020-04-27T17:32:58+02:00 UnitId has been renamed into Unit - - - - - 3e87db64 by Sylvain Henry at 2020-04-27T17:36:00+02:00 Fix for GHC.Unit.* modules - - - - - ae3323a7 by Ben Gamari at 2020-04-29T12:36:37-04:00 Merge pull request haskell/haddock#1183 from hsyl20/wip/hsyl20/unitid Refactoring of Unit code - - - - - b105564a by Artem Pelenitsyn at 2020-05-03T08:14:10+01:00 add dependency on exceptions because GHC.Exception was boiled down (ghc haskell/haddock#18075) - - - - - 9857eff3 by Zubin Duggal at 2020-05-04T18:48:25+01:00 Atomic update of NameCache in readHieFile - - - - - 86bbb226 by Sylvain Henry at 2020-05-14T16:36:27+02:00 Fix after Config module renaming - - - - - a4bbdbc2 by Gert-Jan Bottu at 2020-05-15T22:09:44+02:00 Explicit Specificity Support for Haddock - - - - - 46199daf by Ben Gamari at 2020-05-19T09:59:56-04:00 Merge pull request haskell/haddock#1192 from hsyl20/hsyl20/modules-config Fix after Config module renaming - - - - - f9a9d2ba by Gert-Jan Bottu at 2020-05-20T16:48:38-04:00 Explicit Specificity Support for Haddock - - - - - 55c5b7ea by Ben Gamari at 2020-05-21T00:32:02-04:00 Merge commit 'a8d7e66da4dcc3b242103271875261604be42d6e' into ghc-head - - - - - a566557f by Cale Gibbard at 2020-05-21T16:02:06-04:00 isBootSummary now produces a result of type IsBootInterface - - - - - ea52f905 by Zubin Duggal at 2020-05-24T17:55:48+01:00 update for hiefile-typeclass-info - - - - - 49ba7a67 by Willem Van Onsem at 2020-05-25T12:23:01-04:00 Use floor over round to calculate the percentage (#1195) If we compile documentation where only a small fraction is undocumented, it is misleading to see 100% coverage - 99% is more intuitive. Fixes haskell/haddock#1194 - - - - - c025ebf1 by Ben Gamari at 2020-05-29T14:32:42-04:00 Merge pull request haskell/haddock#1185 from obsidiansystems/boot-disambig isBootSummary now produces a result of type IsBootInterface - - - - - 74ab9415 by Ben Gamari at 2020-05-29T20:23:39-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - b40be944 by Ben Gamari at 2020-06-03T17:02:31-04:00 testsuite: Update expected output for simplified subsumption - - - - - 624be71c by Ryan Scott at 2020-06-05T12:43:23-04:00 Changes for GHC#18191 See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3337. - - - - - fbd8f7ce by Sylvain Henry at 2020-06-08T15:31:47+02:00 Fix after unit refactoring - - - - - 743fda4d by Ben Gamari at 2020-06-09T12:09:58-04:00 Merge pull request haskell/haddock#1202 from hsyl20/wip/hsyl20/unitid-ii Fix after unit refactoring - - - - - d07a06a9 by Ryan Scott at 2020-06-13T07:16:55-04:00 Use HsForAllTelescope (GHC#18235) - - - - - 389bb60d by Ben Gamari at 2020-06-13T15:30:52-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - 7a377f5f by Ben Gamari at 2020-06-17T14:53:16-04:00 Merge pull request haskell/haddock#1199 from bgamari/wip/ghc-8.12 haddock: Bounds bumps for GHC 8.12 - - - - - 9fd9e586 by Krzysztof Gogolewski at 2020-06-17T16:09:07-04:00 Adapt Haddock to LinearTypes See ghc/ghc!852. - - - - - 46fe7636 by Ben Gamari at 2020-06-18T14:20:02-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 35a3c9e2 by Zubin Duggal at 2020-06-21T21:19:18+05:30 Use functions exported from HsToCore - - - - - 8abe3928 by Ben Gamari at 2020-06-24T13:53:39-04:00 Merge pull request haskell/haddock#1204 from wz1000/wip/haddock-hstocore Use functions exported from GHC.HsToCore.Docs - - - - - 22f2c937 by Matthías Páll Gissurarson at 2020-06-26T19:07:03+02:00 Adapt Haddock for QualifiedDo - - - - - 3f6208d7 by Vladislav Zavialov at 2020-06-28T14:28:16+03:00 Handle LexicalNegation's ITprefixminus - - - - - 03a19f41 by Sylvain Henry at 2020-07-02T09:37:38+02:00 Rename hsctarget into backend - - - - - ea17ff23 by Andreas Klebinger at 2020-07-02T17:44:18+02:00 Update for UniqFM changes. - - - - - 9872f2f3 by Ben Gamari at 2020-07-09T10:39:19-04:00 Merge pull request haskell/haddock#1209 from AndreasPK/wip/typed_uniqfm Update for UniqFM changes. - - - - - 68f7b668 by Krzysztof Gogolewski at 2020-07-12T18:16:57+02:00 Sync with GHC removing {-# CORE #-} pragma See ghc ticket haskell/haddock#18048 - - - - - eb372681 by Sylvain Henry at 2020-07-20T11:41:30+02:00 Rename hscTarget into backend - - - - - fb7f78bf by Ben Gamari at 2020-07-21T12:15:25-04:00 Merge pull request haskell/haddock#1214 from hsyl20/wip/hsyl20/hadrian/ncg Rename hscTarget into backend - - - - - 1e8f5b56 by Ben Gamari at 2020-07-23T09:11:50-04:00 Merge commit '904dce0cafe0a241dd3ef355775db47fc12f434d' into ghc-head - - - - - d8fd1775 by Zubin Duggal at 2020-07-23T18:46:40+05:30 Update for modular ping pong - - - - - 8416f872 by Ben Gamari at 2020-07-23T09:35:03-04:00 Merge pull request haskell/haddock#1200 from wz1000/wip/wz1000-modular-ping-pong Modular ping pong - - - - - a24a8577 by Ben Gamari at 2020-07-28T15:23:36-04:00 Bump GHC version to 9.0 - - - - - 6a51c9dd by Sylvain Henry at 2020-08-05T18:47:05+02:00 Fix after Outputable refactoring - - - - - c05e1c99 by Ben Gamari at 2020-08-10T14:41:41-04:00 Merge pull request haskell/haddock#1223 from hsyl20/wip/hsyl20/dynflags/exception Fix after Outputable refactoring - - - - - d964f15b by Sylvain Henry at 2020-08-12T11:58:49+02:00 Fix after HomeUnit - - - - - 8e6d5b23 by Ben Gamari at 2020-08-12T14:25:30-04:00 Merge pull request haskell/haddock#1225 from hsyl20/wip/hsyl20/plugins/homeunit Fix after HomeUnit - - - - - 8c7880fe by Sylvain Henry at 2020-08-17T14:13:29+02:00 Remove Ord FastString instance - - - - - 8ea410db by Alex Biehl at 2020-08-19T10:56:32+02:00 Another round of `npm audit fix` (#1228) This should shut down the warnings on Github. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. Last NPM dependency audit happend in d576b2327e2bc117f912fe0a9d595e9ae62614e0 Co-authored-by: Alex Biehl <alex.biehl at target.com> - - - - - 7af6e2a8 by Ben Gamari at 2020-08-31T13:59:34-04:00 Merge pull request haskell/haddock#1226 from hsyl20/wip/hsyl20/fs_ord Remove Ord FastString instance - - - - - ffbc8702 by Alan Zimmerman at 2020-09-07T21:47:41+01:00 Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - a93f1268 by Alan Zimmerman at 2020-09-07T23:11:38+01:00 Merge pull request haskell/haddock#1232 from haskell/wip/T18639-remove-generated-pragma, Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - 1f605d50 by Ben Gamari at 2020-09-14T18:30:01-04:00 Bump GHC version to 9.1 - - - - - 6599df62 by Vladislav Zavialov at 2020-09-18T14:05:15+03:00 Bump base upper bound to 4.16 - - - - - a01b3c43 by Ben Gamari at 2020-09-22T15:41:48-04:00 Update hypsrc-test for QuickLook This appears to be a spurious change. - - - - - e9cc6cac by Vladislav Zavialov at 2020-09-26T21:00:12+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 30e3ca7c by Sylvain Henry at 2020-09-29T11:18:32-04:00 Update for parser (#1234) - - - - - b172f3e3 by Vladislav Zavialov at 2020-09-30T01:01:30+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 0b9c08d3 by Sylvain Henry at 2020-09-30T11:02:33+02:00 Adapt to GHC parser changes - - - - - b9540b7a by Sylvain Henry at 2020-10-12T09:13:38-04:00 Don't pass the HomeUnitId (#1239) - - - - - 34762e80 by HaskellMouse at 2020-10-13T12:58:04+03:00 Changed tests due to unification of `Nat` and `Natural` in the follwing merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3583 - - - - - 256f86b6 by Vladislav Zavialov at 2020-10-15T10:48:03+03:00 Add whitespace in: map ($ v) - - - - - 4a3f711b by Alan Zimmerman at 2020-10-19T08:57:27+01:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled - - - - - 072cdd21 by Alan Zimmerman at 2020-10-21T14:48:28-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 9e09a445 by Alan Zimmerman at 2020-10-21T23:53:34-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 636d7de3 by Sylvain Henry at 2020-10-26T14:31:54-04:00 GHC.Driver.Types refactoring (#1242) - - - - - a597f000 by Ryan Scott at 2020-10-29T04:18:05-04:00 Adapt to the removal of Hs{Boxed,Constraint}Tuple See ghc/ghc!4097 and GHC#18723. - - - - - b96660fb by Ryan Scott at 2020-10-30T04:53:05-04:00 Adapt to HsConDecl{H98,GADT}Details split Needed for GHC#18844. - - - - - c287d82c by Ryan Scott at 2020-10-30T19:35:59-04:00 Adapt to HsOuterTyVarBndrs These changes accompany ghc/ghc!4107, which aims to be a fix for haskell/haddock#16762. - - - - - a34c31a1 by Ryan Scott at 2020-11-13T13:38:34-05:00 Adapt to splitPiTysInvisible being renamed to splitInvisPiTys This is a part of !4434, a fix for GHC#18939. - - - - - 66ea459d by Sylvain Henry at 2020-11-16T10:59:30+01:00 Fix after Plugins moved into HscEnv - - - - - 508556d8 by Ben Gamari at 2020-11-18T15:47:40-05:00 Merge pull request haskell/haddock#1253 from hsyl20/wip/hsyl20/plugins/hscenv Fix after Plugins moved into HscEnv - - - - - 620fec1a by Andreas Klebinger at 2020-11-24T20:51:59+01:00 Update for changes in GHC's Pretty - - - - - 01cc13ab by Richard Eisenberg at 2020-11-25T23:18:35-05:00 Avoid GHC#18932. - - - - - 8d29ba21 by Cale Gibbard at 2020-11-25T23:18:35-05:00 Add type arguments to PrefixCon - - - - - 414d5f87 by Sylvain Henry at 2020-11-30T17:06:04+01:00 DynFlags's unit fields moved to HscEnv - - - - - e356668c by Ben Gamari at 2020-11-30T11:11:37-05:00 Merge pull request haskell/haddock#1258 from hsyl20/wip/hsyl20/hscenv/unitstate Unit fields moved from DynFlags to HscEnv - - - - - 7cf552f1 by Ben Gamari at 2020-12-03T10:31:27-05:00 Merge pull request haskell/haddock#1257 from AndreasPK/wip/andreask/opt_dumps Update for changes in GHC's Pretty - - - - - fc0871c3 by Veronika Romashkina at 2020-12-08T16:35:33+01:00 Fix docs links from Darcs to GitHub in intro (#1262) - - - - - 7059e808 by Veronika Romashkina at 2020-12-08T16:36:16+01:00 Use gender neutral word in docs (#1260) - - - - - 1b16e5ee by Maximilian Tagher at 2020-12-08T16:40:03+01:00 Allow scrolling search results (#1235) Closes https://github.com/haskell/haddock/issues/1231 - - - - - 8a118c01 by dependabot[bot] at 2020-12-08T16:40:25+01:00 Bump bl from 1.2.2 to 1.2.3 in /haddock-api/resources/html (#1255) Bumps [bl](https://github.com/rvagg/bl) from 1.2.2 to 1.2.3. - [Release notes](https://github.com/rvagg/bl/releases) - [Commits](https://github.com/rvagg/bl/compare/v1.2.2...v1.2.3) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - c89ff587 by Xia Li-yao at 2020-12-08T16:42:17+01:00 Allow more characters in anchor following module reference (#1220) - - - - - 14af7d64 by Xia Li-yao at 2020-12-08T16:43:05+01:00 Add dangling changes from branches ghc-8.6 and ghc-8.8 (#1243) * Fix multiple typos and inconsistencies in doc/markup.rst Note: I noticed some overlap with haskell/haddock#1112 from @wygulmage and haskell/haddock#1081 from @parsonsmatt after creating these proposed changes - mea culpa for not looking at the open PRs sooner. * Fix haskell/haddock#1113 If no Signatures, no section of index.html * Change the formatting of missing link destinations The current formatting of the missing link destination does not really help user to understand the reasons of the missing link. To address this, I've changed the formatting in two ways: - the missing link symbol name is now fully qualified. This way you immediately know which haskell module cannot be linked. It is then easier to understand why this module does not have documentation (hidden module or broken documentation). - one line per missing link, that's more readable now that symbol name can be longer due to qualification. For example, before haddock was listing missing symbol such as: ``` could not find link destinations for: Word8 Word16 mapMaybe ``` Now it is listed as: ``` could not find link destinations for: - Data.Word.Word8 - Data.Word.Word16 - Data.Maybe.mapMaybe ``` * Add `--ignore-link-symbol` command line argument This argument can be used multiples time. A missing link to a symbol listed by `--ignore-link-symbol` won't trigger "missing link" warning. * Forbid spaces in anchors (#1148) * Improve error messages with context information (#1060) Co-authored-by: Matt Audesse <matt at mattaudesse.com> Co-authored-by: Mike Pilgrem <mpilgrem at users.noreply.github.com> Co-authored-by: Guillaume Bouchard <guillaume.bouchard at tweag.io> Co-authored-by: Pepe Iborra <pepeiborra at gmail.com> - - - - - 89e3af13 by tomjaguarpaw at 2020-12-08T18:00:04+01:00 Enable two warnings (#1245) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - c3320f8d by Willem Van Onsem at 2020-12-08T18:26:55+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 685df308 by Alex Biehl at 2020-12-08T20:06:26+01:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - be3ec3c0 by Alex Biehl at 2020-12-08T20:06:26+01:00 Import intercalate - - - - - 32c33912 by Matthías Páll Gissurarson at 2020-12-08T21:15:30+01:00 Adapt Haddock for QualifiedDo - - - - - 31696088 by Alex Biehl at 2020-12-08T22:06:02+01:00 Fix haddock-library tests - - - - - fbc0998a by Alex Biehl at 2020-12-08T23:08:23+01:00 Move to GitHub CI (#1266) * Initial version of ci.yml This is a straight copy from Dmitrii Kovanikov's blog post at https://kodimensional.dev/github-actions. Will adapt to haddock in successive commits. * Delete .travis.yml * Modify to only test on ghc-8.10.{1,2} * Use actions/setup-haskell at v1.1.4 * Relax QuickCheck bound on haddock-api * Remove stack matrix for now * Nail down to ghc-8.10 branch for now * Pin index state to 2020-12-08T20:13:44Z for now * Disable macOS and Windows tests for now for speed up - - - - - 5b946b9a by tomjaguarpaw at 2020-12-10T19:01:41+01:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - bc5a408f by dependabot[bot] at 2020-12-10T19:02:16+01:00 Bump ini from 1.3.5 to 1.3.7 in /haddock-api/resources/html (#1269) Bumps [ini](https://github.com/isaacs/ini) from 1.3.5 to 1.3.7. - [Release notes](https://github.com/isaacs/ini/releases) - [Commits](https://github.com/isaacs/ini/compare/v1.3.5...v1.3.7) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - d02995f1 by Andrew Martin at 2020-12-14T16:48:40-05:00 Update for boxed rep - - - - - a381aeff by Ben Gamari at 2020-12-15T15:13:30-05:00 Revert "Enable two warnings (#1245) (#1268)" As this does not build on GHC `master`. This reverts commit 7936692badfe38f23ae95b51fb7bd7c2ff7e9bce. - - - - - a63c0a9e by Ben Gamari at 2020-12-15T15:17:59-05:00 Revert "Update for boxed rep" This reverts commit 4ffb30d8b637ccebecc81ce610f0af451ac8088d. - - - - - 53bfbb29 by Ben Gamari at 2020-12-15T15:37:24-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - bae76a30 by Ben Gamari at 2020-12-16T02:44:42+00:00 Update output for nullary TyConApp optimisation (ghc/ghc!2952) - - - - - 4b733b57 by Krzysztof Gogolewski at 2020-12-16T20:03:14+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. - - - - - ee463bd3 by Ryan Scott at 2020-12-16T16:55:23-05:00 Adapt to HsCoreTy (formerly NewHsTypeX) becoming a type synonym Needed for !4417, the fix for GHC#15706 and GHC#18914. - - - - - ed0b02f8 by tomjaguarpaw at 2020-12-19T10:17:19+00:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - d80bf8f5 by Sylvain Henry at 2020-12-21T10:09:25+01:00 Fix after binder collect changes - - - - - bf4c9d32 by Adam Gundry at 2020-12-23T21:35:01+00:00 Adapt to changes to GlobalRdrElt and AvailInfo Needed for ghc/ghc!4467 - - - - - 37736c4c by John Ericson at 2020-12-28T12:27:02-05:00 Support a new ghc --make node type for parallel backpack upsweep - - - - - 717bdeac by Vladislav Zavialov at 2020-12-29T10:50:02+03:00 Inline and fix getGADTConTypeG The getGADTConTypeG used HsRecTy, which is at odds with GHC issue haskell/haddock#18782. I noticed that getGADTConTypeG was only used in the Hoogle backend. Interestingly, when handling H98 constructors, Hoogle converts RecCon to PrefixCon (see Haddock.Backends.Hoogle.ppCtor). So I changed getGADTConTypeG to handle RecConGADT in the same manner as PrefixConGADT, and after this simplification moved it into the 'where' clause of ppCtor, to the only place where it is used. The practical effect of this change is as follows. Consider this example: data TestH98 = T98 { bar::Int } data TestGADT where TG :: { foo :: Int } -> TestGADT Before this patch, haddock --hoogle used to produce: T98 :: Int -> TestH98 [TG] :: {foo :: Int} -> TestGADT Notice how the record syntax was discarded in T98 but not TG. With this patch, we always produce signatures without record syntax: T98 :: Int -> TestH98 [TG] :: Int -> TestGADT I suspect this might also be a bugfix, as currently Hoogle doesn't seem to render GADT record constructors properly. - - - - - cb1b8c56 by Andreas Abel at 2020-12-30T21:12:37+01:00 Build instructions: haddock-library and -api first! - - - - - b947f6ad by Ben Gamari at 2020-12-31T13:04:19-05:00 Merge pull request haskell/haddock#1281 from obsidiansystems/wip/backpack-j Changes to support -j with backpack - - - - - 120e1cfd by Hécate Moonlight at 2021-01-04T19:54:58+01:00 Merge pull request haskell/haddock#1282 from andreasabel/master Build instructions: haddock-library and -api first! - - - - - fd45e41a by Ben Gamari at 2021-01-05T16:14:31-05:00 Merge remote-tracking branch 'origin/ghc-8.10' into ghc-9.0 - - - - - b471bdec by Ben Gamari at 2021-01-05T16:23:02-05:00 Merge commit '1e56f63c3197e7ca1c1e506e083c2bad25d08793' into ghc-9.0 - - - - - 81cdbc41 by Alex Biehl at 2021-01-09T12:14:41+01:00 Prepare Haddock for being a GHC Plugin - - - - - b646d952 by Alex Biehl at 2021-01-09T12:14:41+01:00 Make Haddock a GHC Plugin - - - - - cc044674 by Alex Biehl at 2021-01-09T12:14:41+01:00 Add -j[n] CLI param to Haddock executable It translates to `--ghcopt=-j[n]` - - - - - 84a04073 by Alex Biehl at 2021-01-09T12:14:41+01:00 Abstract Monad for interface creation I found that when running as a plugin the lookupName function (which runs in Ghc monad) does not work correctly from the typeCheckResultAction hook. Instead, we abstracted the monad used when creating interfaces, so that access to GHC session specific parts is explicit and so that the TcM can provide their (correct) implementation of lookupName. - - - - - 5be2c4f7 by Alex Biehl at 2021-01-09T12:14:41+01:00 Accept tests - - - - - 8cefee9d by Alex Biehl at 2021-01-09T16:10:47+01:00 Add missing dependency for mtl - - - - - 3681f919 by Ben Gamari at 2021-01-13T18:39:25-05:00 Merge remote-tracking branch 'origin/ghc-9.0' into ghc-head - - - - - 33c6b152 by Hécate Moonlight at 2021-01-14T16:04:20+01:00 Merge pull request haskell/haddock#1273 from hsyl20/wip/hsyl20/arrows Fix after binder collect changes - - - - - 70d13e8e by Joachim Breitner at 2021-01-22T19:03:45+01:00 Make haddock more robust to changes to the `Language` data type With the introduction of GHC2021, the `Languages` data type in GHC will grow. In preparation of that (and to avoid changing haddock with each new language), this change makes the code handle extensions to that data type gracefully. (cherry picked from commit c341dd7c9c3fc5ebc83a2d577c5a726f3eb152a5) - - - - - 7d6dd57a by John Ericson at 2021-01-22T22:02:02+00:00 Add `NoGhcTc` instance now that it's not closed - - - - - e5fdaf0a by Alan Zimmerman at 2021-01-23T22:57:44+00:00 Merge pull request haskell/haddock#1293 from obsidiansystems/wip/fix-18936 Add `NoGhcTc` instance now that it's not closed - - - - - 989a1e05 by Oleg Grenrus at 2021-01-24T16:11:46+03:00 Add import list to Data.List - - - - - 368e144a by Ben Gamari at 2021-01-28T22:15:48+01:00 Adapt to "Make PatSyn immutable" - - - - - abe66c21 by Alfredo Di Napoli at 2021-02-01T08:05:35+01:00 Rename pprLogErrMsg to new name - - - - - e600e75c by Hécate Moonlight at 2021-02-05T14:53:00+01:00 Move CI to ghc-9.0 - - - - - dd492961 by Vladislav Zavialov at 2021-02-05T14:53:00+01:00 Update cabal.project and README build instructions - - - - - 31bd292a by Hécate Moonlight at 2021-02-05T15:03:56+01:00 Merge pull request haskell/haddock#1296 from Kleidukos/ghc-9.0 Merge the late additions to ghc-8.10 into ghc-9.0 - - - - - 6388989e by Vladislav Zavialov at 2021-02-05T17:41:57+03:00 Cleanup: fix build warnings - - - - - f99407ef by Daniel Rogozin at 2021-02-05T18:11:48+03:00 type level characters support for haddock (required for haskell/haddock#11342) - - - - - d8c6b26f by Hécate Moonlight at 2021-02-05T17:44:50+01:00 Add a CONTRIBUTING.md file - - - - - 6a01ad98 by Hécate Moonlight at 2021-02-05T17:58:16+01:00 Merge pull request haskell/haddock#1312 from Kleidukos/proper-branch-etiquette Add a CONTRIBUTING.md file - - - - - 955eecc4 by Vladislav Zavialov at 2021-02-05T20:29:00+03:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into ghc-head - - - - - 47b3d6ab by Hécate Moonlight at 2021-02-05T19:09:38+01:00 Amend the CONTRIBUTING.md file - - - - - 23de6137 by Hécate Moonlight at 2021-02-05T19:16:49+01:00 Merge pull request haskell/haddock#1313 from Kleidukos/amend-contributing Amend the CONTRIBUTING.md file - - - - - 69026b59 by Krzysztof Gogolewski at 2021-02-05T23:05:56+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. (cherry picked from commit b4b4d896d2d68d6c48e7db7bfe95c185ca0709cb) - - - - - ea026b78 by Oleg Grenrus at 2021-02-06T17:14:45+01:00 Add import list to Data.List - - - - - 5204326f by Hécate Moonlight at 2021-02-06T17:15:44+01:00 Merge pull request haskell/haddock#1316 from Kleidukos/explicit-imports-to-data-list Add import list to Data.List - - - - - 1f4d2136 by Ben Gamari at 2021-02-06T11:53:31-05:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ghc-head-merge - - - - - 13f0d09a by Ben Gamari at 2021-02-06T11:53:45-05:00 Fix partial record selector warning - - - - - 5c115f7e by Ben Gamari at 2021-02-06T11:55:52-05:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into wip/ghc-head-merge - - - - - b6fd8b75 by Ben Gamari at 2021-02-06T12:01:31-05:00 Merge commit '41964cb2fd54b5a10f8c0f28147015b7d5ad2c02' into wip/ghc-head-merge - - - - - a967194c by Ben Gamari at 2021-02-06T18:30:35-05:00 Merge branch 'wip/ghc-head-merge' into ghc-head - - - - - 1f4c3a91 by MorrowM at 2021-02-07T01:52:33+02:00 Fix search div not scrolling - - - - - 684b1287 by Iñaki García Etxebarria at 2021-02-07T16:13:04+01:00 Add support for labeled module references Support a markdown-style way of annotating module references. For instance -- | [label]("Module.Name#anchor") will create a link that points to the same place as the module reference "Module.Name#anchor" but the text displayed on the link will be "label". - - - - - bdb55a5d by Hécate Moonlight at 2021-02-07T16:18:10+01:00 Merge pull request haskell/haddock#1319 from alexbiehl/alex/compat Backward compat: Add support for labeled module references - - - - - 6ca70991 by Hécate Moonlight at 2021-02-07T16:21:29+01:00 Merge pull request haskell/haddock#1314 from tweag/show-linear-backport Backport haskell/haddock#1238 (linear types) to ghc-9.0 - - - - - d9d73298 by Alex Biehl at 2021-02-07T17:46:25+01:00 Remove dubious parseModLink Instead construct the ModLink value directly when parsing. - - - - - 33b4d020 by Hécate Moonlight at 2021-02-07T17:52:05+01:00 Merge pull request haskell/haddock#1320 from haskell/alex/fix Remove dubious parseModLink - - - - - 54211316 by Hécate Moonlight at 2021-02-07T18:12:07+01:00 Merge pull request haskell/haddock#1318 from MorrowM/ghc-9.0 Fix search div not scrolling - - - - - 19db679e by alexbiehl-gc at 2021-02-07T18:14:46+01:00 Merge pull request haskell/haddock#1317 from bgamari/wip/ghc-head-merge Merge ghc-8.10 into ghc-head - - - - - 6bc1e9e4 by Willem Van Onsem at 2021-02-07T18:25:30+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - c8537cf8 by alexbiehl-gc at 2021-02-07T18:30:40+01:00 Merge pull request haskell/haddock#1322 from haskell/alex/forward-port simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 2d47ae4e by alexbiehl-gc at 2021-02-07T18:39:59+01:00 Merge branch 'ghc-head' into ghc-9.0 - - - - - 849e4733 by Hécate Moonlight at 2021-02-07T18:43:19+01:00 Merge pull request haskell/haddock#1321 from Kleidukos/ghc-9.0 Merge ghc-9.0 into ghc-head - - - - - ee6095d7 by Sylvain Henry at 2021-02-08T11:36:38+01:00 Update for Logger - - - - - 4ad688c9 by Alex Biehl at 2021-02-08T18:11:24+01:00 Merge pull request haskell/haddock#1310 from hsyl20/wip/hsyl20/logger2 Logger refactoring - - - - - 922a9e0e by Ben Gamari at 2021-02-08T12:54:33-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - 991649d2 by Sylvain Henry at 2021-02-09T10:55:17+01:00 Fix to build with HEAD - - - - - a8348dc2 by Hécate Moonlight at 2021-02-09T10:58:51+01:00 Merge pull request haskell/haddock#1327 from hsyl20/wip/hsyl20/logger2 Fix to build with HEAD - - - - - 0abdbca6 by Fendor at 2021-02-09T20:06:15+01:00 Add UnitId to Target record - - - - - d5790a0e by Alex Biehl at 2021-02-11T10:32:32+01:00 Stable sort for (data/newtype) instances - - - - - 8e6036f5 by Alex Biehl at 2021-02-11T10:32:32+01:00 Also make TyLit deterministic - - - - - f76d2945 by Hécate Moonlight at 2021-02-11T11:00:31+01:00 Merge pull request haskell/haddock#1329 from hsyl20/hsyl20/stabe_iface Stable sort for instances - - - - - 5e0469ea by Oleg Grenrus at 2021-02-14T15:28:15+02:00 Add import list to Data.List in Haddock.Interface.Create - - - - - fa57cd24 by Hécate Moonlight at 2021-02-14T17:19:27+01:00 Merge pull request haskell/haddock#1331 from phadej/more-explicit-data-list-imports Add import list to Data.List in Haddock.Interface.Create - - - - - f0cd629c by Hécate Moonlight at 2021-02-21T00:22:01+01:00 Merge pull request haskell/haddock#1311 from fendor/wip/add-targetUnitId-to-target Add UnitId to Target record - - - - - 674ef723 by Joachim Breitner at 2021-02-22T10:39:18+01:00 html-test: Always set language from ghc-9.2 on, the “default” langauge of GHC is expected to change more wildly. To prepare for that (and unblock https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4853), this sets the language for all the test files to `Haskell2010`. This should insolate this test suite against changes to the default. Cherry-picked from https://github.com/haskell/haddock/pull/1341 - - - - - f072d623 by Hécate Moonlight at 2021-02-22T10:56:51+01:00 Merge pull request haskell/haddock#1342 from nomeata/joachim/haskell2010-in-tests-ghc-head html-test: Always set language - - - - - caebbfca by Hécate Moonlight at 2021-02-22T11:53:07+01:00 Clean-up of Interface and Interface.Create's imports and pragmata - - - - - f6caa89d by Hécate Moonlight at 2021-02-22T11:54:58+01:00 Merge pull request haskell/haddock#1345 from Kleidukos/head/fix-interface-imports [ghc-head] Clean-up of Interface and Interface.Create's imports and pragmata - - - - - 7395c9cb by Hécate Moonlight at 2021-02-22T18:44:57+01:00 Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 6e9fb5d5 by Hécate Moonlight at 2021-02-22T18:45:28+01:00 Merge pull request haskell/haddock#1348 from Kleidukos/head/explicit-imports-interface Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 9198b118 by Alan Zimmerman at 2021-02-22T20:04:24+00:00 Context becomes a Maybe in the GHC AST This prevents noLoc's appearing in the ParsedSource. Match the change in GHC. - - - - - 0af20f64 by Hécate Moonlight at 2021-02-23T12:36:12+01:00 Fix the call-site of guessTarget in Interface.hs Explicit the imports from GHC.HsToCore.Docs - - - - - b7886885 by Hécate Moonlight at 2021-02-23T12:37:54+01:00 Merge pull request haskell/haddock#1349 from Kleidukos/fix-interface-guesstarget-call Fix the call-site of guessTarget in Interface.hs - - - - - 9cf041ba by Sylvain Henry at 2021-02-24T11:08:20+01:00 Fix haddockHypsrcTest output in ghc-head - - - - - b194182a by Hécate Moonlight at 2021-02-24T11:12:36+01:00 Merge pull request haskell/haddock#1351 from hsyl20/wip/hsyl20/fix-head Fix haddockHypsrcTest output in ghc-head - - - - - 3ce8b375 by Shayne Fletcher at 2021-03-06T09:55:03-05:00 Add ITproj to parser - - - - - d2abf762 by Ben Gamari at 2021-03-06T19:26:49-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a0f6047d by Andrew Martin at 2021-03-07T11:25:23-05:00 Update for boxed rep - - - - - 6f63c99e by Ben Gamari at 2021-03-10T13:20:21-05:00 Update for "FastString: Use FastMutInt instead of IORef Int" - - - - - e13f01df by Luke Lau at 2021-03-10T15:38:40-05:00 Implement template-haskell's putDoc This catches up to GHC using the new extractTHDocs function, which returns documentation added via the putDoc function (provided it was compiled with Opt_Haddock). Since it's already a map from names -> docs, there's no need to do traversal etc. It also matches the change from the argument map being made an IntMap rather than a Map Int - - - - - 89263d94 by Alan Zimmerman at 2021-03-15T17:15:26+00:00 Match changes in GHC AST for in-tree API Annotations As landed via https://gitlab.haskell.org/ghc/ghc/-/merge_requests/2418 - - - - - 28db1934 by Alan Zimmerman at 2021-03-15T20:40:09+00:00 Change some type family test results. It is not clear to me whether the original was printing incorrectly (since we did not have the TopLevel flag before now), or if this behaviour is expected. For the time being I am assuming the former. - - - - - 7c11c989 by Sylvain Henry at 2021-03-22T10:05:19+01:00 Fix after NameCache changes - - - - - addbde15 by Sylvain Henry at 2021-03-22T10:05:19+01:00 NameCache doesn't store a UniqSupply anymore - - - - - 15ec6cec by Ben Gamari at 2021-03-22T17:53:44-04:00 Bump GHC version to 9.2 - - - - - dbd6aa63 by Hécate Moonlight at 2021-03-24T14:28:36+01:00 Merge pull request haskell/haddock#1365 from hsyl20/wip/hsyl20/iface1 NameCache refactoring - - - - - 2d32da7e by Oleg Grenrus at 2021-03-27T01:12:00+02:00 Specialization of Data.List - - - - - 32b84fa6 by Fendor at 2021-03-27T10:50:17+01:00 Add UnitId to Target record This way we always know to which home-unit a given target belongs to. So far, there only exists a single home-unit at a time, but it enables having multiple home-units at the same time. - - - - - 54bf9f0e by Hécate Moonlight at 2021-03-28T14:08:35+02:00 Merge pull request haskell/haddock#1368 from fendor/target-unit-id-revert Add UnitId to Target record - - - - - 7dea168a by Alan Zimmerman at 2021-03-29T08:45:52+01:00 EPA : Rename ApiAnn to EpAnn - - - - - 72967f65 by Alfredo Di Napoli at 2021-03-29T09:47:01+02:00 pprError changed name in GHC - - - - - 4bc61035 by Alan Zimmerman at 2021-03-29T16:16:27-04:00 EPA : Rename ApiAnn to EpAnn - - - - - 108d031d by Ben Gamari at 2021-03-29T18:49:36-04:00 Merge commit '36418c4f70d7d2b179a77925b3ad5caedb08c9b5' into HEAD - - - - - 1444f700 by Ben Gamari at 2021-03-31T09:18:39-04:00 Merge pull request haskell/haddock#1370 from adinapoli/wip/adinapoli-diag-reason-severity Rename pprError to mkParserErr - - - - - d3087b79 by Ben Gamari at 2021-03-31T11:34:17-04:00 Merge commit 'd8d8024ad6796549a8d3b5512dabf3288d14e30f' into ghc-head - - - - - 170b79e9 by Ben Gamari at 2021-03-31T12:24:56-04:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - db0d6bae by Ben Gamari at 2021-04-10T09:34:35-04:00 Bump GHC version to 9.3 - - - - - a9f2c421 by Alan Zimmerman at 2021-04-19T18:26:46-04:00 Update for EPA changes in GHC (cherry picked from commit cafb48118f7c111020663776845897e225607b41) - - - - - 1ee4b7c7 by Sylvain Henry at 2021-05-11T10:00:06+02:00 Removal of HsVersions.h (#1388) * Update for EPA changes in GHC * Account for HsVersions.h removal Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 79e819e9 by Hécate Moonlight at 2021-05-11T10:14:47+02:00 Revert "Removal of HsVersions.h (#1388)" This reverts commit 72118896464f94d81f10c52f5d9261efcacc57a6. - - - - - 3dbd3f8b by Alan Zimmerman at 2021-05-11T10:15:17+02:00 Update for EPA changes in GHC - - - - - 2ce80c17 by Sylvain Henry at 2021-05-11T10:15:19+02:00 Account for HsVersions.h removal - - - - - 00e4c918 by Christiaan Baaij at 2021-05-13T08:21:56+02:00 Add Haddock support for the OPAQUE pragma (#1380) - - - - - 8f9049b2 by Hécate Moonlight at 2021-05-13T08:40:22+02:00 fixup! Use GHC 9.2 in CI runner - - - - - 27ddec38 by Alan Zimmerman at 2021-05-13T22:51:20+01:00 EPA: match changes from GHC T19834 - - - - - f8a1d714 by Felix Yan at 2021-05-14T17:10:04+02:00 Allow hspec 2.8 (#1389) All tests are passing. - - - - - df44453b by Divam Narula at 2021-05-20T15:42:42+02:00 Update ref, the variables got renamed. (#1391) This is due to ghc/ghc!5555 which caused a change in ModDetails in case of NoBackend. Now the initModDetails is used to recreate the ModDetails from interface and in-memory ModDetails is not used. - - - - - e46bfc87 by Alan Zimmerman at 2021-05-20T19:05:09+01:00 Remove Maybe from HsQualTy Match changes in GHC for haskell/haddock#19845 - - - - - 79bd7b62 by Shayne Fletcher at 2021-05-22T08:20:39+10:00 FieldOcc: rename extFieldOcc to foExt - - - - - 6ed68c74 by Ben Gamari at 2021-05-21T22:29:30-04:00 Merge commit '3b6a8774bdb543dad59b2618458b07feab8a55e9' into ghc-head - - - - - f9a02d34 by Alfredo Di Napoli at 2021-05-24T13:53:00+02:00 New Parser diagnostics interface - - - - - 392807d0 by Ben Gamari at 2021-05-24T09:57:40-04:00 Merge pull request haskell/haddock#1394 from adinapoli/wip/adinapoli-align-ps-messages Align Haddock to use the new Parser diagnostics interface - - - - - 33023cd8 by Ben Gamari at 2021-05-24T11:19:16-04:00 Revert "Add Haddock support for the OPAQUE pragma (#1380)" This reverts commit a1337c599ef7720b0482a25c55f11794112496dc. The GHC patch associated with this change is not yet ready to be merged. - - - - - 8c005af7 by Ben Simms at 2021-05-28T07:56:20+02:00 CI configuration for ghc-head (#1395) - - - - - 1e947612 by Hécate Moonlight at 2021-05-28T12:27:35+02:00 Use GHC 9.2 in CI runner (#1378) - - - - - e6fa10ab by CGenie at 2021-05-31T09:02:13+02:00 Add page about common errors (#1396) * Update index.rst Common errors page * Create common-errors.rst * Update common-errors.rst * Use GHC 9.2 in CI runner (#1378) * [haddock-api] remove .hspec-failures Co-authored-by: Hécate Moonlight <Kleidukos at users.noreply.github.com> - - - - - abc72a8d by Sylvain Henry at 2021-06-01T10:02:06+02:00 Adapt Haddock to Logger and Parser changes (#1399) - - - - - 91373656 by Zubin Duggal at 2021-06-01T20:45:10+02:00 Update haddockHypSrc tests since we now compute slighly more type info (#1397) - - - - - ed712822 by Marcin Szamotulski at 2021-06-02T08:54:33+02:00 Added myself to contributors - - - - - 49fdbcb7 by Marcin Szamotulski at 2021-06-02T08:57:24+02:00 Document multi component support - - - - - 9ddc8d7d by Hécate Moonlight at 2021-06-02T09:35:55+02:00 Merge pull request haskell/haddock#1379 from coot/coot/document-multi-component-support Document multi component support - - - - - 585b5c5e by Ben Simms at 2021-06-02T19:46:54+02:00 Update CONTRIBUTING.md (#1402) - - - - - 1df4a605 by Ben Simms at 2021-06-02T19:47:14+02:00 Update CONTRIBUTING.md (#1403) - - - - - 58ea43d2 by sheaf at 2021-06-02T22:09:06+02:00 Update Haddock Bug873 to account for renaming - - - - - c5d0ab23 by Vladislav Zavialov at 2021-06-10T13:35:42+03:00 HsToken in FunTy, RecConGADT - - - - - 1ae2f40c by Hécate Moonlight at 2021-06-11T11:19:09+02:00 Update the CI badges - - - - - 6fdc4de2 by Sylvain Henry at 2021-06-28T19:21:17+02:00 Fix mkParserOpts (#1411) - - - - - 18201670 by Alfredo Di Napoli at 2021-07-05T07:55:12+02:00 Rename getErrorMessages Lexer import This commit renames the Lexer import in `Hyperlinker.Parser` from `getErrorMessages` to `getPsErrorMessages` to eliminate the ambiguity with the `getErrorMessages` function defined in `GHC.Types.Error`. - - - - - 23173ca3 by Ben Gamari at 2021-07-07T11:31:44-04:00 Merge pull request haskell/haddock#1413 from adinapoli/wip/adinapoli-issue-19920 Rename getErrorMessages Lexer import - - - - - b3dc4ed8 by Alan Zimmerman at 2021-07-28T22:30:59+01:00 EPA: match changes from GHC T19834 (cherry picked from commit 2fec1b44e0ee7e263286709aa528b4ecb99ac6c2) - - - - - 5f177278 by Ben Gamari at 2021-08-06T01:17:37-04:00 Merge commit '2a966c8ca37' into HEAD - - - - - cdd81d08 by Marcin Szamotulski at 2021-08-08T17:19:06+02:00 coot/multiple packages (ghc-9.2) (#1418) - - - - - be0d71f1 by Marcin Szamotulski at 2021-08-16T08:46:03+02:00 coot/multiple package (ghc-head) (#1419) * FromJSON class Aeson style FromJSON class with Parsec based json parser. * doc-index.json file for multiple packages When creating haddock summary page for multiple packages render doc-index.json file using contents of all found 'doc-index.json' files. * Render doc-index.json When rendering html, render doc-index.json file independently of maybe_index_url option. doc-index.json file is useful now even if maybe_index_url is not `Nothing`. * base url option New `Flag_BaseURL` which configures from where static files are loaded (--base-url). If given and not equal "." static files are not coppied, as this indicates that they are not read from the the directory where we'd copy them. The default value is ".". - - - - - 3b09dbdf by Hécate Moonlight at 2021-10-07T23:26:03+02:00 Update GHC 9.2 to latest pre-release in CI - - - - - 7ac55417 by Zubin Duggal at 2021-10-11T12:10:19+02:00 Enable Haddock tests in GHC windows CI (#1428) * testsuite: strip windows line endings for haddock * hyperlinker: Work around double escaping (#19236) * deterministic SCC - - - - - 1cb81f25 by Andrew Lelechenko at 2021-10-12T15:23:19+02:00 haddock-library does not depend on bytestring or transformers (#1426) - - - - - a890b9aa by sheaf at 2021-10-15T22:19:42+02:00 update haddockHypsrcTest for GHC MR !6705 (#1430) - - - - - 42a55c6c by Sylvain Henry at 2021-10-15T22:20:10+02:00 Fix after PkgQual refactoring (#1429) - - - - - 91659238 by Alan Zimmerman at 2021-10-28T18:57:10+01:00 Update for changes in GHC for branch wip/az/no-srcspan-anno-instances - - - - - acf23e60 by Vladislav Zavialov at 2021-11-05T02:09:47+03:00 Do not use forall as an identifier See GHC ticket haskell/haddock#20609 - - - - - c565db0e by Krzysztof Gogolewski at 2021-11-27T02:42:35+01:00 Update after NoExtCon -> DataConCantHappen rename - - - - - b5f55590 by Artem Pelenitsyn at 2021-11-27T11:14:17+01:00 fix CI for 9.2 (#1436) - - - - - 25cd621e by Matthew Pickering at 2021-12-02T11:46:54+00:00 Update html-test for Data.List revert - - - - - 1d5ff85f by malteneuss at 2021-12-15T07:56:55+01:00 Add hint about inline link issue (#1444) - - - - - 791fde81 by Sylvain Henry at 2021-12-16T09:29:51+01:00 Bump ghc-head (#1445) * Update after NoExtCon -> DataConCantHappen rename * Update html-test for Data.List revert * Fix for new Plugins datatype Co-authored-by: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 44236317 by Sylvain Henry at 2021-12-17T09:39:00+01:00 Fix for new Plugins datatype - - - - - 80ada0fa by Hécate Moonlight at 2021-12-17T17:28:48+01:00 Remove ghc-head workflow (#1446) Contributions of GHC glue code are now done on the GHC gitlab, not in the GitHub repo anymore. - - - - - 49e171cd by Matthew Pickering at 2021-12-28T09:47:09+00:00 Remove use of ExtendedModSummary - - - - - 0e91b5ea by askeblad at 2022-01-04T09:18:35+01:00 update URLs - - - - - 9f13c212 by Hécate Moonlight at 2022-02-25T10:19:46+01:00 Fix solver for GHC 9.2 - - - - - 386751a1 by Meng Weng Wong at 2022-02-25T19:19:11+01:00 IDoc link has bitrotted; replaced with web.archive.org cache. (#1454) - - - - - d877cbe6 by Hécate Moonlight at 2022-02-25T19:21:58+01:00 Fix haddock user guide (#1456) - - - - - cc47f036 by Andrew Lelechenko at 2022-03-04T17:29:36+01:00 Allow text-2.0 in haddock-library (#1459) - - - - - 7b3685a3 by malteneuss at 2022-03-07T19:27:24+01:00 Add multi-line style hint to style section (#1460) - - - - - c51088b8 by John Ericson at 2022-03-11T16:46:26+01:00 Fix CollectPass instance to match TTG refactor Companion to GHC !7614 (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7614) - - - - - b882195b by Vladislav Zavialov at 2022-03-14T20:32:30+01:00 Link to (~) - - - - - 877349b8 by Christiaan Baaij at 2022-03-16T09:20:43+01:00 Add Haddock support for the OPAQUE pragma - - - - - 0ea22721 by askeblad at 2022-03-16T09:44:27+01:00 typos (#1464) - - - - - a6d13da1 by Matthew Pickering at 2022-03-22T13:41:17+00:00 Minimum changes needed for compilation with hi-haddock With hi-haddock, of course there is a much large refactoring of haddock which could be achieved but that is left for a future patch which can implemented at any time independently of GHC. - - - - - e7ac9129 by Matthew Pickering at 2022-03-22T21:17:50+00:00 Update test output - - - - - 6d916214 by Matthew Pickering at 2022-03-24T15:06:26+00:00 Merge branch 'wip/opaque_pragma' into 'ghc-head' Add Haddock support for the OPAQUE pragma See merge request ghc/haddock!2 - - - - - 42208183 by Steve Hart at 2022-03-25T20:43:50+01:00 Fix CI (#1467) * CI: Reinstall GHC with docs CI tests were failing because the GHC preinstalled to the CI environment does not include documentation, which is required for running the Haddock tests. This commit causes the CI workflow to reinstall GHC with docs so that tests can succeed. - - - - - 9676fd79 by Steve Hart at 2022-03-25T21:33:34+01:00 Make links in Synopsis functional again (#1458) Commit e41c1cbe9f0476997eac7b4a3f17cbc6b2262faf added a call to e.preventDefault() when handling click events that reach a toggle element. This prevents the browser from following hyperlinks within the Synopsis section when they are clicked by a user. This commit restores functioning hyperlinks within the Synopsis section by removing the call to e.preventDefault(), as it does not appear to be necessary, and removing it increases the flexibility of the details-helper code. - - - - - d1edd637 by sheaf at 2022-04-01T12:02:02+02:00 Keep track of promotion ticks in HsOpTy Keeping track of promotion ticks in HsOpTy allows us to properly pretty-print promoted constructors such as lists. - - - - - 9dcb2dfc by Jakob Brünker at 2022-04-01T15:46:22+00:00 Add support for \cases See merge request ghc/ghc!7873 - - - - - b0412ee5 by askeblad at 2022-04-06T17:47:57+02:00 spelling errors (#1471) - - - - - 6b18829b by Vladislav Zavialov at 2022-04-06T18:53:58+02:00 Rename [] to List - - - - - 2d046691 by Vladislav Zavialov at 2022-04-07T20:25:54+03:00 HsToken ConDeclGADT con_dcolon - - - - - 90b43da4 by Steve Hart at 2022-04-12T13:29:46+02:00 Parse Markdown links at beginning of line within a paragraph (#1470) * Catch Markdown links at beginning of line within paragraph Per Issue haskell/haddock#774, Markdown links were being parsed as ordinary text when they occurred at the beginning of a line other than the first line of the paragraph. This occurred because the parser was not interpreting a left square bracket as a special character that could delimit special markup. A space character was considered a special character, so, if a space occurred at the beginning of the new line, then the parser would interpret the space by itself and then continue parsing, thereby catching the Markdown link. '\n' was not treated as a special character, so the parser did not catch a Markdown link that may have followed. Note that this will allow for Markdown links that are not surrounded by spaces. For example, the following text includes a Markdown link that will be parsed: Hello, world[label](url) This is consistent with how the parser handles other types of markup. * Remove obsolete documentation hint Commit 6b9aeafddf20efc65d3725c16e3fc43a20aac343 should eliminate the need for the workaround suggested in the documentation. - - - - - 5b08312d by Hécate Moonlight at 2022-04-12T13:36:38+02:00 Force ghc-9.2 in the cabal.project - - - - - 0d0ea349 by dependabot[bot] at 2022-04-12T13:57:41+02:00 Bump path-parse from 1.0.5 to 1.0.7 in /haddock-api/resources/html (#1469) Bumps [path-parse](https://github.com/jbgutierrez/path-parse) from 1.0.5 to 1.0.7. - [Release notes](https://github.com/jbgutierrez/path-parse/releases) - [Commits](https://github.com/jbgutierrez/path-parse/commits/v1.0.7) --- updated-dependencies: - dependency-name: path-parse dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 2b9fc65e by dependabot[bot] at 2022-04-12T13:57:54+02:00 Bump copy-props from 2.0.4 to 2.0.5 in /haddock-api/resources/html (#1468) Bumps [copy-props](https://github.com/gulpjs/copy-props) from 2.0.4 to 2.0.5. - [Release notes](https://github.com/gulpjs/copy-props/releases) - [Changelog](https://github.com/gulpjs/copy-props/blob/master/CHANGELOG.md) - [Commits](https://github.com/gulpjs/copy-props/compare/2.0.4...2.0.5) --- updated-dependencies: - dependency-name: copy-props dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - ea98a6fb by Ben Gamari at 2022-04-23T22:54:37-04:00 Update for GHC 9.4 - - - - - 9e11864f by Ben Gamari at 2022-04-25T16:24:31-04:00 Merge remote-tracking branch 'upstream/ghc-9.2' into ghc-head - - - - - f83cc506 by Ben Gamari at 2022-04-25T17:00:25-04:00 Bump ghc version to 9.5 - - - - - e01c2e7d by Ben Gamari at 2022-04-28T16:19:04-04:00 Revert "Bump ghc-head (#1445)" This reverts commit b29a78ef6926101338f62e84f456dac8659dc9d2. This should not have been merged. - - - - - a2b5ee8c by Ben Gamari at 2022-04-28T16:19:24-04:00 Merge commit '2627a86c' into ghc-head - - - - - 0c6fe4f9 by Ben Gamari at 2022-04-29T10:05:54-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-9.4 - - - - - b6e5cb0a by Ben Gamari at 2022-04-29T11:46:06-04:00 Revert "HsToken ConDeclGADT con_dcolon" This reverts commit 24208496649a02d5f87373052c430ea4a97842c5. - - - - - 15a62888 by Ben Gamari at 2022-04-29T15:12:55-04:00 Bump base upper bound - - - - - 165b9031 by Ben Gamari at 2022-04-29T23:58:38-04:00 Update test output - - - - - e0c3e5da by Phil de Joux at 2022-05-02T14:46:38+02:00 Add hlint action .hlint.yaml with ignores & CPP. (#1475) - - - - - ead1158d by Raphael Das Gupta at 2022-05-02T14:46:48+02:00 fix grammar in docs: "can the" → "can be" (#1477) - - - - - cff97944 by Ben Gamari at 2022-05-02T18:38:56-04:00 Allow base-4.17 - - - - - e4ecb201 by Phil de Joux at 2022-05-03T13:14:55+02:00 Remove unused imports that GHC warned about. (#1480) - - - - - 222890b1 by Phil de Joux at 2022-05-03T13:15:46+02:00 Follow hlint suggestion to remove redundant bang. (#1479) - - - - - 058b671f by Phil de Joux at 2022-05-03T13:34:04+02:00 Follow hlint, remove language pragmas in libs. (#1478) - - - - - 0a645049 by Ben Simms at 2022-05-03T14:19:24+02:00 Keep track of ordered list indexes and render them (#1407) * Keep track of ordered list indexes and render them * Rename some identifiers to clarify - - - - - f0433304 by Norman Ramsey at 2022-05-04T15:13:34-04:00 update for changes in GHC API - - - - - 3740cf71 by Emily Martins at 2022-05-06T18:23:48+02:00 Add link to the readthedocs in cabal description to show on hackage. (cherry picked from commit 52e2d40d47295c02d3181aac0c53028e730f1e3b) - - - - - 5d754f1e by Hécate Moonlight at 2022-05-06T18:44:57+02:00 remove Bug873 - - - - - 968fc267 by Hécate Moonlight at 2022-05-06T18:48:28+02:00 Ignore "Use second" HLint suggestion. It increases laziness. - - - - - 02d14e97 by Jade Lovelace at 2022-05-07T17:42:08+02:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` - - - - - b22b87ed by Artem Pelenitsyn at 2022-05-08T16:19:47+02:00 fix parsing trailing quotes in backticked identifiers (#1408) (#1483) - - - - - 80ae107b by Alex Biehl at 2022-05-08T16:37:16+02:00 Fix "Defined by not used" error (cherry picked from commit 6e02a620a26c3a44f98675dd1b93b08070c36c0a) - - - - - 4c838e84 by Hécate Moonlight at 2022-05-08T16:37:16+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - fc9827b4 by Hécate Moonlight at 2022-05-08T16:40:40+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - b153b555 by Xia Li-yao at 2022-05-20T17:52:42+02:00 Hide synopsis from search when hidden (#1486) Fix haskell/haddock#1451 - - - - - f3e38b85 by Marcin Szamotulski at 2022-05-21T23:32:31+02:00 Allow to hide interfaces when rendering multiple components (#1487) This is useful when one wishes to `--gen-contents` when rendering multiple components, but one does not want to render all modules. This is in particular useful when adding base package. - - - - - f942863b by Marcin Szamotulski at 2022-05-24T08:29:59+02:00 Check if doc-index.json exists before reading it (#1488) - - - - - 31e92982 by Marcin Szamotulski at 2022-05-25T16:22:13+02:00 Version bump 2.26.1 (#1489) * Version bump 2.26.1 We extended format accepted by `--read-interface` option, which requires updating the minor version. * Update documentation of --read-interface option - - - - - 7cc873e0 by sheaf at 2022-05-25T16:42:31+02:00 Updated HaddockHypsrcTest output for record update changes (MR !7981) - - - - - cd196942 by Marcin Szamotulski at 2022-05-25T20:28:47+02:00 Use visibility to decide which interfaces are included in quickjump (#1490) This is also consistent with how html index is build. See haskell/cabal#7669 for rationale behind this decision. - - - - - 00c713c5 by Hécate Moonlight at 2022-05-26T17:09:15+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 2f3039f1 by Hécate Moonlight at 2022-05-26T17:10:59+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 63a5650c by romes at 2022-05-31T12:43:22+01:00 TTG: Match new GHC AST - - - - - dd7d1617 by romes at 2022-06-02T16:11:00+01:00 Update for IE changes in !8228 - - - - - c23aaab7 by cydparser at 2022-06-06T08:48:14+02:00 Fix and improve CI (#1495) * Pin GHC version before creating the freeze file * Use newest action versions * Improve caching * Avoid unnecessarily reinstalling GHC * Use GHC 9.2.2 for CI Co-authored-by: Cyd Wise <cwise at tripshot.com> - - - - - c156fa77 by Hécate Moonlight at 2022-06-06T11:59:35+02:00 Add Mergify configuration (#1496) - - - - - 2dba4188 by Hécate Moonlight at 2022-06-06T16:12:50+02:00 Bump haddock's version in cabal file to 2.26.1 (#1497) - - - - - d7d4b8b9 by Marcin Szamotulski at 2022-06-07T06:09:40+00:00 Render module tree per package in the content page (#1492) * Render module tree per package in the content page When rendering content page for multiple packages it is useful to split the module tree per package. Package names in this patch are inferred from haddock's interface file names. * Write PackageInfo into interface file To keep interface file format backward compatible, instead of using `Binary` instance for `InterfaceFile` we introduce functions to serialise and deserialise, which depends on the interface file version. - - - - - 77765665 by Mike Pilgrem at 2022-06-12T21:57:19+01:00 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - b0e079b0 by mergify[bot] at 2022-06-13T11:49:37+00:00 Merge pull request haskell/haddock#1108 from mpilgrem/fix783 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - 6c0292b1 by Hécate Moonlight at 2022-06-21T17:21:08+02:00 Update the contribution guide - - - - - e413b9fa by dependabot[bot] at 2022-06-21T23:38:19+02:00 Bump shell-quote from 1.6.1 to 1.7.3 in /haddock-api/resources/html (#1500) Bumps [shell-quote](https://github.com/substack/node-shell-quote) from 1.6.1 to 1.7.3. - [Release notes](https://github.com/substack/node-shell-quote/releases) - [Changelog](https://github.com/substack/node-shell-quote/blob/master/CHANGELOG.md) - [Commits](https://github.com/substack/node-shell-quote/compare/1.6.1...1.7.3) --- updated-dependencies: - dependency-name: shell-quote dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 29d0ef70 by romes at 2022-07-06T11:29:39+02:00 TTG: AST Updates for !8308 - - - - - 1bae7c87 by Alan Zimmerman at 2022-07-06T22:50:43+01:00 Match GHC changes for T21805 This brings in a newtype for FieldLabelString - - - - - 6fe8b988 by Phil de Joux at 2022-07-16T20:54:26+00:00 Bump hlint version to 3.4.1, the version with counts. (#1503) Redo the counts available with the --default option. - - - - - 48fb43af by Phil de Joux at 2022-07-19T09:32:55+02:00 Follow hlint suggestion: unused LANGUAGE pragma. (#1504) * Follow hlint suggestion: unused LANGUAGE pragma. * Ignore within modules to pass linting and pass tests. - - - - - c1cf1fa7 by Phil de Joux at 2022-07-24T13:45:59+02:00 Follow hlint suggestion: redundant $. (#1505) * Follow hlint suggestion: redundant $. * Remove $ and surplus blank lines in Operators. - - - - - 74777eb2 by Jade Lovelace at 2022-07-29T11:02:41+01:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` (cherry picked from commit ab53ccf089ea703b767581ac14be0f6c78a7678a) - - - - - faa4cfcf by Hécate Moonlight at 2022-07-29T20:31:20+02:00 Merge pull request haskell/haddock#1516 from duog/9-4-backport-fix-hyperlinks Backport 9-4: Fix hyperlinks to external items and modules (#1482) - - - - - 5d2450f3 by Ben Gamari at 2022-08-05T17:41:15-04:00 Merge remote-tracking branch 'origin/ghc-9.4' - - - - - 63954f73 by Ben Gamari at 2022-08-05T19:08:36-04:00 Clean up build and testsuite for GHC 9.4 - - - - - d4568cb8 by Hécate Moonlight at 2022-08-05T19:10:49-04:00 Bump the versions - - - - - 505583a4 by Ben Gamari at 2022-08-06T13:58:27-04:00 Merge pull request haskell/haddock#1518 from bgamari/wip/ghc-9.4-merge Merge GHC 9.4 into `main` - - - - - 5706f6a4 by Ben Gamari at 2022-08-06T22:57:21-04:00 html-test: Testsuite changes for GHC 9.4.1 - - - - - 5f2a45a2 by Ben Gamari at 2022-08-15T14:33:05-04:00 doc: Fix a few minor ReST issues Sphinx was complaining about too-short title underlines. - - - - - 220e6410 by Ben Gamari at 2022-08-15T14:41:24-04:00 Merge branch 'main' into ghc-head - - - - - fbeb1b02 by Ben Gamari at 2022-08-15T14:45:16-04:00 Updates for GHC 9.5 - - - - - eee562eb by Vladislav Zavialov at 2022-08-15T14:46:13-04:00 HsToken ConDeclGADT con_dcolon - - - - - c5f073db by Ben Gamari at 2022-08-15T16:55:35-04:00 Updates for GHC 9.5 - - - - - 3f7ab242 by Vladislav Zavialov at 2022-08-15T16:55:35-04:00 HsToken ConDeclGADT con_dcolon - - - - - a18e473d by Ben Gamari at 2022-08-16T08:35:19-04:00 Merge branch 'wip/ghc-head-bump' into ghc-head - - - - - af0ff3a4 by M Farkas-Dyck at 2022-09-15T21:16:05+00:00 Disuse `mapLoc`. - - - - - a748fc38 by Matthew Farkas-Dyck at 2022-09-17T10:44:18+00:00 Scrub partiality about `NewOrData`. - - - - - 2758fb6c by John Ericson at 2022-09-18T03:27:37+02:00 Test output changed because of change to `base` Spooky, but I guess that is intended? - - - - - a7eec128 by Torsten Schmits at 2022-09-21T11:06:55+02:00 update tests for the move of tuples to GHC.Tuple.Prim - - - - - 461e7b9d by Ross Paterson at 2022-09-24T22:01:25+00:00 match implementation of GHC proposal haskell/haddock#106 (Define Kinds Without Promotion) - - - - - f7fd77ef by sheaf at 2022-10-17T14:53:01+02:00 Update Haddock for GHC MR !8563 (configuration of diagnostics) - - - - - 3d3e85ab by Vladislav Zavialov at 2022-10-22T23:04:06+03:00 Class layout info - - - - - cbde4cb0 by Simon Peyton Jones at 2022-10-25T23:19:18+01:00 Adapt to Constraint-vs-Type See haskell/haddock#21623 and !8750 - - - - - 7108ba96 by Tom Smeding at 2022-11-01T22:33:23+01:00 Remove outdated footnote about module re-exports The footnote is invalid with GHC 9.2.4 (and possibly earlier): the described behaviour in the main text works fine. - - - - - 206c6bc7 by Hécate Moonlight at 2022-11-01T23:00:46+01:00 Merge pull request haskell/haddock#1534 from tomsmeding/patch-1 - - - - - a57b4c4b by Andrew Lelechenko at 2022-11-21T00:39:52+00:00 Support mtl-2.3 - - - - - e9d62453 by Simon Peyton Jones at 2022-11-25T13:49:12+01:00 Track small API change in TyCon.hs - - - - - eb1c73f7 by Ben Gamari at 2022-12-07T08:46:21-05:00 Update for GhC 9.6 - - - - - 063268dd by Ben Gamari at 2022-12-07T11:26:32-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 4ca722fe by Ben Gamari at 2022-12-08T14:43:26-05:00 Bump bounds to accomodate base-4.18 - - - - - 340b7511 by Vladislav Zavialov at 2022-12-10T12:31:28+00:00 HsToken in HsAppKindTy - - - - - 946226ec by Ben Gamari at 2022-12-13T20:12:56-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - fd8faa66 by Ben Gamari at 2022-12-22T13:44:28-05:00 Bump GHC version to 9.7 - - - - - 2958aa9c by Ben Gamari at 2022-12-22T14:49:16-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 9e0fefd8 by Andrei Borzenkov at 2023-01-30T14:02:04+04:00 Rename () to Unit, Rename (,,...,,) to Tuple<n> - - - - - eb3968b5 by Ben Gamari at 2023-03-10T02:32:43-05:00 Bump versions for ghc-9.6 release - - - - - 4aeead36 by Adam Gundry at 2023-03-23T13:53:47+01:00 Adapt to warning categories changes - - - - - 642d8d60 by sheaf at 2023-03-29T13:35:56+02:00 Adapt to record field refactor This commit adapts to the changes in GHC MR !8686, which overhauls the treatment of record fields in the renamer, adding separate record field namespaces and entirely removing the GreName datatype. - - - - - ac8d4333 by doyougnu at 2023-03-29T11:11:44-04:00 Update UniqMap API - - - - - 7866fc86 by Ben Orchard at 2023-04-20T11:29:33+02:00 update classify with new tokens - - - - - ffcdd683 by Finley McIlwaine at 2023-04-24T09:36:18-06:00 Remove index-state - - - - - 05b70982 by Finley McIlwaine at 2023-04-26T08:16:31-06:00 `renameInterface` space leak fixes - Change logic for accumulation of names for which link warnings will be generated - Change handling of `--ignore-link-symbol` to allow qualified and unqualified names. Added to CHANGES.md - Some formatting changes and comments here and there - - - - - e5697d7c by Finley McIlwaine at 2023-04-27T18:46:36-06:00 Messy things - ghc-debug dependency and instrumentation - cabal.project custom with-compiler - hie.yaml files - traces and such - - - - - 0b8ef80b by Finley McIlwaine at 2023-05-02T18:08:52-06:00 Stop retaining GRE closures GRE closures should never be necessary to Haddock, so we never want to keep them on the heap. Despite that, they are retained by a lot of the data structures that Haddock makes use of. - Attempt to fix that situation by adding strictness to various computations and pruning the `ifaceInstances` field of `Interface` to a much thinner data type. - Removes the `ifaceFamInstances` field, as it was never used. - Move some of the attach instances types (e.g. `SimpleType`) to the types module - - - - - 8bda991b by Finley McIlwaine at 2023-05-08T16:07:51-06:00 Memory usage fixes - Refactor `ifaceDeclMap` to drastically reduce memory footprint. We no longer store all declarations associated with a given name, since we only cared to determine if the only declaration associated with a name was a value declaration. Change the `DeclMap` type to better reflect this. - Drop pre-renaming export items after the renaming step. Since the Hoogle backend used the pre-renamed export items, this isn't trivial. We now generate Hoogle output for exported declarations during the renaming step (if Hoogle output /should/ be generated), and store that with the renamed export item. - Slightly refactor Hoogle backend to handle the above change and allow for early generation of Hoogle output. - Remove the `ifaceRnDocMap` and `ifaceRnArgMap` fields of the `Interface` type, as they were never used. - Remove some unnecessary strictness - Remove a lot of dead code from `Syb` module - - - - - 1611ac0c by Finley McIlwaine at 2023-05-09T11:51:57-06:00 Unify ErrMsgM and IfM - Delete ErrMsgM, stop accumulating warnings in a writer - Make IfM a state monad, print warnings directly to stdout, move IfM type into types module - Drop ErrMsg = String synonym - Unset IORefs from plugin after they are read, preventing unnecessary retention of interfaces - - - - - 42d696ab by Finley McIlwaine at 2023-05-11T15:52:07-06:00 Thunk leak fixes The strictness introduced in this commit was motivated by observing thunk leaks in the eventlog2html output. - Refactor attach instances list comprehension to avoid large intermediate thunks - Refactor some HTML backend list comprehensions to avoid large intermediate thunks - Avoid thunks accumulating in documentation types or documentation parser - A lot of orphan NFData instances to allow us to force documentation values - - - - - 68561cf6 by Finley McIlwaine at 2023-05-11T17:02:10-06:00 Remove GHC debug dep - - - - - 10519e3d by Finley McIlwaine at 2023-05-15T12:40:48-06:00 Force HIE file path Removes a potential retainer of `ModSummary`s - - - - - 1e4a6ec6 by Finley McIlwaine at 2023-05-15T14:20:34-06:00 Re-add index-state, with-compiler, delete hie.yamls - - - - - a2363fe9 by Hécate Moonlight at 2023-05-15T22:45:16+02:00 Merge pull request haskell/haddock#1594 from FinleyMcIlwaine/finley/ghc-9.6-mem-fixes Reduce memory usage - - - - - e8a78383 by Finley McIlwaine at 2023-05-17T12:19:16-06:00 Merge branch ghc-9.6 into ghc-head - - - - - 22e25581 by Finley McIlwaine at 2023-05-17T12:20:23-06:00 Merge branch 'ghc-head' of gitlab.haskell.org:ghc/haddock into ghc-head - - - - - 41bbf0df by Bartłomiej Cieślar at 2023-05-24T08:57:58+02:00 changes to the WarningTxt cases Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - c686ba9b by Hécate Moonlight at 2023-06-01T14:03:02-06:00 Port the remains of Hi-Haddock - - - - - 9d8a85fd by Hécate Moonlight at 2023-06-01T14:03:06-06:00 Stdout for tests - - - - - 36331d07 by Finley McIlwaine at 2023-06-01T14:06:02-06:00 Formatting, organize imports - - - - - a06059b1 by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix empty context confusion in Convert module - - - - - 379346ae by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix associated type families in Hoogle output - - - - - fc6ea7ed by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix test refs Accept several changes in Hoogle tests: Pretty printing logic no longer prints the `(Proxy (Proxy (...))` chain in Bug806 with parentheses. Since this test was only meant to verify that line breaks do not occur, accept the change. `tyThingToLHsDecl` is called for class and data declarations, which ends up "synifying" the type variables and giving unlifted types kind signatures. As a result, type variables of kind `Type -> Type` are now printed with kind signatures in Hoogle output. This could be changed by manually drop kind signatures from class variables in the Hoogle backend if the behavior is deemed unacceptable. Sometimes subordinate declarations are exported separate from their parent declarations (e.g. record selectors). In this case, a type signature is cobbled together for the export item in `extractDecl`. Since this type signature is very manually constructed, it may lack kind signatures of decls constructed from `tyThingToLHsDecl`. An example of this is the `type-sigs` Hoogle test. Change `*` to `Type` in Hoogle test refs. I don't think this will break Hoogle behavior, since it appears to not consider type signatures in search. I have not fully verified this. - - - - - e14b7e58 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix LaTeX backend test refs Changes to GHC pretty printing code have resulted in some differences to Haddock's LaTeX output. - Type variables are printed explicitly quantified in the LinearTypes test - Wildcard types in type family equations are now printed numbered, e.g. _1 _2, in the TypeFamilies3 test - Combined signatures in DefaultSignatures test are now documented as separate signatures - - - - - 41b5b296 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and test source updates - Stop using kind `*` in html test sources - Add TypeOperators where necessary to avoid warnings and future errors - Rename some test modules to match their module names - - - - - c640e2a2 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix missing deprecation warnings on record fields `lookupOccEnv` was used to resolve `OccNames` with warnings attached, but it doesn't look in the record field namespace. Thus, if a record field had a warning attached, it would not resolve and the warning map would not include it. This commit fixes by using `lookupOccEnv_WithFields` instead. - - - - - fad0c462 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and some comments - - - - - 751fd023 by Finley McIlwaine at 2023-06-01T14:11:41-06:00 Accept HTML test diffs All diffs now boil down to the expected differences resulting from declarations being reified from TyThings in hi-haddock. Surface syntax now has much less control over the syntax used in the documentation. - - - - - d835c845 by Finley McIlwaine at 2023-06-01T14:11:45-06:00 Adapt to new load' type - - - - - dcf776c4 by Finley McIlwaine at 2023-06-01T14:13:13-06:00 Update mkWarningMap and moduleWarning - - - - - 8e8432fd by Finley McIlwaine at 2023-06-01T14:28:54-06:00 Revert load' changes - - - - - aeb2982c by Finley McIlwaine at 2023-06-01T14:40:24-06:00 Accept change to Instances test in html-test Link to Data.Tuple instead of GHC.Tuple.Prim - - - - - 8adfdbac by Finley McIlwaine at 2023-06-01T15:53:17-06:00 Reset ghc dep to ^>= 9.6 - - - - - 2b1ce93d by Finley McIlwaine at 2023-06-06T07:50:04-06:00 Update CHANGES.md, user guide, recomp avoidance * Add --trace-args flag for tracing arguments received to standard output * Avoid recompiling due to changes in optimization flags * Update users guide and changes.md - - - - - f3da6676 by Finley McIlwaine at 2023-06-06T14:12:56-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - bf36c467 by Matthew Pickering at 2023-06-07T10:16:09+01:00 Revert back to e16e20d592a6f5d9ed1af17b77fafd6495242345 Neither of these MRs are ready to land yet which causes issues with other MRs which are ready to land and need haddock changes. - - - - - 421510a9 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 atSign has no unicode variant Prior to this change, atSign was defined as follows: atSign unicode = text (if unicode then "@" else "@") Yes, this is the same symbol '\64' and not your font playing tricks on you. Now we define: atSign = char '@' Both the LaTeX and the Xhtml backend are updated accordingly. - - - - - 3785c276 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 LaTeX: fix printing of type variable bindings Consider this type signature: kindOf :: forall {k} (a :: k). Proxy a -> Proxy k Prior to this fix, the LaTeX backend rendered it like this: kindOf :: forall k a. Proxy a -> Proxy k Now we preserve explicit specificity and kind annotations. - - - - - 0febf3a8 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 Add support for invisible binders in type declarations - - - - - 13e33bb3 by Finley McIlwaine at 2023-06-08T07:51:59-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - 3e5340ce by Finley McIlwaine at 2023-06-08T07:54:27-06:00 Add note about stubdir to recompilation docs - - - - - db7e84dc by Finley at 2023-06-08T08:11:03-06:00 Merge pull request haskell/haddock#1597 from haskell/finley/hi-haddock-9.6 hi-haddock for ghc 9.6 - - - - - 4e085d17 by Finley McIlwaine at 2023-06-14T13:41:06-06:00 Replace SYB traversals - - - - - 7b39aec5 by Finley McIlwaine at 2023-06-14T14:20:17-06:00 Test ref accepts, remove unused HaddockClsInst - - - - - df9c2090 by Finley McIlwaine at 2023-06-15T08:02:51-06:00 Use batchMsg for progress reporting during load With hi-haddock as is, there is an awkward silence during the load operation. This commit makes haddock use the default `batchMsg` Messager for progress reporting, and makes the default GHC verbosity level 1, so the user can see what GHC is doing. - - - - - f23679a8 by Hécate Moonlight at 2023-06-15T20:31:53+02:00 Merge pull request haskell/haddock#1600 from haskell/finley/hi-haddock-optim - - - - - a7982192 by Finley McIlwaine at 2023-06-15T15:02:16-06:00 hi-haddock squashed - - - - - c34f0c8d by Finley McIlwaine at 2023-06-15T16:22:03-06:00 Merge remote-tracking branch 'origin/ghc-9.6' into finley/hi-haddock-squashed - - - - - 40452797 by Bartłomiej Cieślar at 2023-06-16T12:26:04+02:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - e58673bf by Ben Gamari at 2023-06-16T09:33:35-04:00 Bump GHC version to 9.8 - - - - - 74bdf972 by Ben Gamari at 2023-06-16T09:36:18-04:00 Merge commit 'fcaaad06770a26d35d4aafd65772dedadf17669c' into ghc-head - - - - - 418ee3dc by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Remove NFData SourceText, IfaceWarnings updates The NFData SourceText instance is now available in GHC Handle mod_iface mi_warns now being IfaceWarnings - - - - - 62f31380 by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Accept Instances.hs test output Due to ghc!10469. - - - - - a8f2fc0e by Ben Gamari at 2023-06-20T15:48:08-04:00 Test fixes for "Fix associated data family doc structure items" Associated data families were being given their own export DocStructureItems, which resulted in them being documented separately from their classes in haddocks. This commit fixes it. - - - - - cb1ac33e by Bartłomiej Cieślar at 2023-06-21T12:56:02-04:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - 9933e10b by Ben Gamari at 2023-06-21T12:56:02-04:00 Bump GHC version to 9.8 - - - - - fe8c18b6 by Ben Gamari at 2023-06-21T15:36:29-04:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - c61a0d5b by Ben Gamari at 2023-06-21T16:10:51-04:00 Bump GHC version to 9.9 - - - - - 0c2a756e by sheaf at 2023-07-07T13:45:12+02:00 Avoid incomplete record update in Haddock Hoogle This commit avoids running into an incomplete record update warning in the Hoogle backend of Haddock. This was only noticed now, because incomplete record updates were broken in GHC 9.6. Now that they are fixed, we have to avoid running into them! - - - - - f9b952a7 by Ben Gamari at 2023-07-21T11:58:05-04:00 Bump base bound to <4.20 For GHC 9.8. - - - - - 1b27e151 by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Check for puns (see ghc#23368) - - - - - 457341fd by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Remove fake exports for (~), List, and Tuple<n> The old reasoning no longer applies, nowadays those names can be mentioned in export lists. - - - - - bf3dcddf by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Fix pretty-printing of Solo and MkSolo - - - - - 495b2241 by Matthew Pickering at 2023-09-01T13:02:07+02:00 Fix issue with duplicate reexported definitions (T23616) When a class method was reexported, it's default methods were also showing up in the generated html page. The simplest and most non-invasive fix is to not look for the default method if we are just exporting the class method.. because the backends are just showing default methods when the whole class is exported. In general it would be worthwhile to rewrite this bit of code I think as the logic and what gets included is split over `lookupDocs` and `availExportDecl` it would be clearer to combine the two. The result of lookupDocs is always just passed to availExportDecl so it seems simpler and more obvious to just write the function directly. - - - - - 6551824d by Finley McIlwaine at 2023-09-05T13:06:57-07:00 Remove fake export of `FUN` from Prelude This prevents `data FUN` from being shown at the top of the Prelude docs. Fixes \#23920 on GHC. - - - - - 9ab5a448 by Alan Zimmerman at 2023-09-08T18:26:53+01:00 Match changes in wip/az/T23885-unicode-funtycon - - - - - 4d08364e by Alan Zimmerman at 2023-10-31T19:46:45+00:00 EPA: match changes in GHC - EPA: Comments in AnchorOperation - EPA: Remove EpaEofComment - - - - - e7da0d25 by Alan Zimmerman at 2023-11-05T11:20:31+00:00 EPA: match changes in GHC, l2l cleanup - - - - - 4ceac14d by Alan Zimmerman at 2023-11-11T15:16:41+00:00 EPA: Replace Anchor with EpaLocation Match GHC - - - - - 94fb8d47 by Alan Zimmerman at 2023-11-29T18:10:26+00:00 Match GHC, No comments in EpaDelta for comments - - - - - 32d208e1 by Vladislav Zavialov at 2023-12-12T20:41:36+03:00 EPA: Match changes to LHsToken removal - - - - - eebdd316 by Apoorv Ingle at 2024-01-23T13:49:12+00:00 Changes for haskell/haddock#18324 - - - - - ae856a82 by Matthew Pickering at 2024-02-05T12:22:39+00:00 ghc-internals fallout - - - - - f8429266 by Jade at 2024-02-08T14:56:50+01:00 Adjust test for ghc MR !10993 - - - - - 6d1e2386 by Alan Zimmerman at 2024-02-13T22:00:28+03:00 EPA: Match changes to HsParTy and HsFunTy - - - - - 9c588f19 by Fendor at 2024-02-14T11:05:36+01:00 Adapt to GHC giving better Name's for linking - - - - - 778e1db3 by Andrei Borzenkov at 2024-02-16T16:12:07+03:00 Namespace specifiers for fixity signatures - - - - - 826c5b47 by Torsten Schmits at 2024-02-21T13:17:05+01:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 2cff14d5 by Ben Gamari at 2024-02-22T09:35:56-05:00 Bump bounds - - - - - f49376b3 by Ben Gamari at 2024-02-22T09:35:56-05:00 Allow `@since` annotations in export lists Here we extend Haddock to admit `@since` annotations in export lists. These can be attached to most export list items (although not subordinate lists). These annotations supercede the declaration's `@since` annotation in produced Haddocks. - - - - - b5aa93df by Ben Gamari at 2024-02-22T12:09:06-05:00 Allow package-qualified @since declarations - - - - - 8f5957f2 by Ben Gamari at 2024-02-22T13:55:19-05:00 Documentation changes from ghc-internal restructuring Previously many declarations (e.g. `Int`) were declared to have a "home" in `Prelude`. However, now Haddock instead chooses to put these in more specific homes (e.g. `Data.Int`). Given that the "home" decision is driven by heuristics and in general these changes seem quite reasonable I am accepting them: * `Int` moved from `Prelude` to `Data.Int` * `(~)` moved from `Prelude` to `Data.Type.Equality` * `Type` moved from `GHC.Types` to `Data.Kind` * `Maybe` moved from `Prelude` to `Data.Maybe` * `Bool` moved from `Prelude` to `Data.Bool` * `Ordering` moved from `Prelude` to `Data.Ord` As well, more identifiers are now hyperlinked; it's not immediately clear *why*, but it is an improvement nevertheless. - - - - - ec33fec3 by Ben Gamari at 2024-02-22T20:36:24-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 30cfd251 by Torsten Schmits at 2024-02-24T13:00:42-05:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 732db81d by Ben Gamari at 2024-02-24T19:12:18-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 86bf7010 by Ben Gamari at 2024-02-27T19:28:10-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 4b6e76b5 by Patrick at 2024-03-07T22:09:30+08:00 fix haskell/haddock#24493, with module name introduced in hieAst The accompanies haddoc PR with GHC PR https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12153 Two things have been done: 1. Link is introduced to every `X` in `module X where`, since we introduce the module name to HieAst, 2. `{-# LINE 4 "hypsrc-test/src/PositionPragmas.hs" #-}` is added before the `module PositionPragmas where` in ` hypsrc-test/ref/src/PositionPragmas.html `.It ensures only a single hieAst for file `hypsrc-test/src/PositionPragmas.hs` is generated. - - - - - 635abccc by Ben Gamari at 2024-03-08T17:09:06-05:00 Bump ghc version to 9.10 - - - - - 2859a637 by Ben Gamari at 2024-03-08T18:26:47-05:00 base: Use strerror_r instead of strerror As noted by #24344, `strerror` is not necessarily thread-safe. Thankfully, POSIX.1-2001 has long offered `strerror_r`, which is safe to use. Fixes #24344. CLC discussion: https://github.com/haskell/core-libraries-committee/issues/249 - - - - - 5b934048 by Ben Gamari at 2024-03-08T18:50:12-05:00 Bump base upper bound - - - - - b30d134e by Ben Gamari at 2024-03-08T18:50:44-05:00 Testsuite output update - - - - - edb9bf77 by Jade at 2024-03-09T03:39:38-05:00 Error messages: Improve Error messages for Data constructors in type signatures. This patch improves the error messages from invalid type signatures by trying to guess what the user did and suggesting an appropriate fix. Partially fixes: #17879 - - - - - cfb197e3 by Patrick at 2024-03-09T03:40:15-05:00 HieAst: add module name #24493 The main purpose of this is to tuck the module name `xxx` in `module xxx where` into the hieAst. It should fix #24493. The following have been done: 1. Renamed and update the `tcg_doc_hdr :: Maybe (LHsDoc GhcRn)` to `tcg_hdr_info :: (Maybe (LHsDoc GhcRn), Maybe (XRec GhcRn ModuleName))` To store the located module name information. 2. update the `RenamedSource` and `RenamedStuff` with extra `Maybe (XRec GhcRn ModuleName)` located module name information. 3. add test `testsuite/tests/hiefile/should_compile/T24493.hs` to ensure the module name is added and update several relevent tests. 4. accompanied submodule haddoc test update MR in https://gitlab.haskell.org/ghc/haddock/-/merge_requests/53 - - - - - 2341d81e by Vaibhav Sagar at 2024-03-09T03:40:54-05:00 GHC.Utils.Binary: fix a couple of typos - - - - - 5580e1bd by Ben Gamari at 2024-03-09T03:41:30-05:00 rts: Drop .wasm suffix from .prof file names This replicates the behavior on Windows, where `Hi.exe` will produce profiling output named `Hi.prof` instead of `Hi.exe.prof`. While in the area I also fixed the extension-stripping logic, which incorrectly rewrote `Hi.exefoo` to `Hi.foo`. Closes #24515. - - - - - 259495ee by Cheng Shao at 2024-03-09T03:41:30-05:00 testsuite: drop exe extension from .hp & .prof filenames See #24515 for details. - - - - - c477a8d2 by Ben Gamari at 2024-03-09T03:42:05-05:00 rts/linker: Enable GOT support on all platforms There is nothing platform-dependent about our GOT implementation and GOT support is needed by `T24171` on i386. - - - - - 2e592857 by Vladislav Zavialov at 2024-03-09T03:42:41-05:00 Drop outdated comment on TcRnIllformedTypePattern This should have been done in 0f0c53a501b but I missed it. - - - - - c554b4da by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/CloneStack: Bounds check array write - - - - - 15c590a5 by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/CloneStack: Don't expose helper functions in header - - - - - e831ce31 by Ben Gamari at 2024-03-09T09:39:20-05:00 base: Move internals of GHC.InfoProv into GHC.InfoProv.Types Such that we can add new helpers into GHC.InfoProv.Types without breakage. - - - - - 6948e24d by Ben Gamari at 2024-03-09T09:39:20-05:00 rts: Lazily decode IPE tables Previously we would eagerly allocate `InfoTableEnt`s for each info table registered in the info table provenance map. However, this costs considerable memory and initialization time. Instead we now lazily decode these tables. This allows us to use one-third the memory *and* opens the door to taking advantage of sharing opportunities within a module. This required considerable reworking since lookupIPE now must be passed its result buffer. - - - - - 9204a04e by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/IPE: Don't expose helper in header - - - - - 308926ff by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/IPE: Share module_name within a Node This allows us to shave a 64-bit word off of the packed IPE entry size. - - - - - bebdea05 by Ben Gamari at 2024-03-09T09:39:20-05:00 IPE: Expose unit ID in InfoTableProv Here we add the unit ID to the info table provenance structure. - - - - - 6519c9ad by Ben Gamari at 2024-03-09T09:39:35-05:00 rts: Refactor GHC.Stack.CloneStack.decode Don't allocate a Ptr constructor per frame. - - - - - ed0b69dc by Ben Gamari at 2024-03-09T09:39:35-05:00 base: Do not expose whereFrom# from GHC.Exts - - - - - 2b1faea9 by Vladislav Zavialov at 2024-03-09T17:38:21-05:00 docs: Update info on TypeAbstractions * Mention TypeAbstractions in 9.10.1-notes.rst * Set the status to "Experimental". * Add a "Since: GHC 9.x" comment to each section. - - - - - f8b88918 by Ben Gamari at 2024-03-09T21:21:46-05:00 ci-images: Bump Alpine image to bootstrap with 9.8.2 - - - - - 705e6927 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Mark T24171 as fragile due to #24512 I will fix this but not in time for 9.10.1-alpha1 - - - - - c74196e1 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Mark linker_unload_native as fragile In particular this fails on platforms without `dlinfo`. I plan to address this but not before 9.10.1-alpha1. - - - - - f4d87f7a by Ben Gamari at 2024-03-09T21:21:46-05:00 configure: Bump version to 9.10 - - - - - 88df9a5f by Ben Gamari at 2024-03-09T21:21:46-05:00 Bump transformers submodule to 0.6.1.1 - - - - - 8176d5e8 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Increase ulimit for T18623 1 MByte was just too tight and failed intermittently on some platforms (e.g. CentOS 7). Bumping the limit to 8 MByte should provide sufficient headroom. Fixes #23139. - - - - - c74b38a3 by Ben Gamari at 2024-03-09T21:21:46-05:00 base: Bump version to 4.20.0.0 - - - - - b2937fc3 by Ben Gamari at 2024-03-09T21:21:46-05:00 ghc-internal: Set initial version at 9.1001.0 This provides PVP compliance while maintaining a clear correspondence between GHC releases and `ghc-internal` versions. - - - - - 4ae7d868 by Ben Gamari at 2024-03-09T21:21:46-05:00 ghc-prim: Bump version to 0.11.0 - - - - - 50798dc6 by Ben Gamari at 2024-03-09T21:21:46-05:00 template-haskell: Bump version to 2.22.0.0 - - - - - 8564f976 by Ben Gamari at 2024-03-09T21:21:46-05:00 base-exports: Accommodate spurious whitespace changes in 32-bit output It appears that this was - - - - - 9d4f0e98 by Ben Gamari at 2024-03-09T21:21:46-05:00 users-guide: Move exception backtrace relnotes to 9.10 This was previously mistakenly added to the GHC 9.8 release notes. - - - - - 145eae60 by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/rel_eng: Fix name of Rocky8 artifact - - - - - 39c2a630 by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/rel_eng: Fix path of generate_jobs_metadata - - - - - aed034de by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/upload: Rework recompression The old `combine` approach was quite fragile due to use of filename globbing. Moreover, it didn't parallelize well. This refactoring makes the goal more obvious, parallelizes better, and is more robust. - - - - - 9bdf3586 by Ben Gamari at 2024-03-09T21:37:44-05:00 Merge branch 'ghc-9.10' into ghc-head - - - - - cec76981 by Ben Gamari at 2024-03-09T21:54:00-05:00 Bump GHC version to 9.11 - - - - - 4c59feb7 by Ben Gamari at 2024-03-09T22:15:01-05:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - dc207d06 by Ben Gamari at 2024-03-10T08:56:08-04:00 configure: Bump GHC version to 9.11 Bumps haddock submodule. - - - - - 8b2513e8 by Ben Gamari at 2024-03-11T01:20:03-04:00 rts/linker: Don't unload code when profiling is enabled The heap census may contain references (e.g. `Counter.identity`) to static data which must be available when the census is reported at the end of execution. Fixes #24512. - - - - - 7810b4c3 by Ben Gamari at 2024-03-11T01:20:03-04:00 rts/linker: Don't unload native objects when dlinfo isn't available To do so is unsafe as we have no way of identifying references to symbols provided by the object. Fixes #24513. Fixes #23993. - - - - - 0590764c by Ben Gamari at 2024-03-11T01:20:39-04:00 rel_eng/upload: Purge both $rel_name/ and $ver/ This is necessary for prereleases, where GHCup accesses the release via `$ver/` - - - - - b85a4631 by Brandon Chinn at 2024-03-12T19:25:56-04:00 Remove duplicate code normalising slashes - - - - - c91946f9 by Brandon Chinn at 2024-03-12T19:25:56-04:00 Simplify regexes with raw strings - - - - - 1a5f53c6 by Brandon Chinn at 2024-03-12T19:25:57-04:00 Don't normalize backslashes in characters - - - - - 7ea971d3 by Andrei Borzenkov at 2024-03-12T19:26:32-04:00 Fix compiler crash caused by implicit RHS quantification in type synonyms (#24470) - - - - - 39f3ac3e by Cheng Shao at 2024-03-12T19:27:11-04:00 Revert "compiler: make genSym use C-based atomic increment on non-JS 32-bit platforms" This reverts commit 615eb855416ce536e02ed935ecc5a6f25519ae16. It was originally intended to fix #24449, but it was merely sweeping the bug under the rug. 3836a110577b5c9343915fd96c1b2c64217e0082 has properly fixed the fragile test, and we no longer need the C version of genSym. Furthermore, the C implementation causes trouble when compiling with clang that targets i386 due to alignment warning and libatomic linking issue, so it makes sense to revert it. - - - - - e6bfb85c by Cheng Shao at 2024-03-12T19:27:11-04:00 compiler: fix out-of-bound memory access of genSym on 32-bit This commit fixes an unnoticed out-of-bound memory access of genSym on 32-bit. ghc_unique_inc is 32-bit sized/aligned on 32-bit platforms, but we mistakenly treat it as a Word64 pointer in genSym, and therefore will accidentally load 2 garbage higher bytes, or with a small but non-zero chance, overwrite something else in the data section depends on how the linker places the data segments. This regression was introduced in !11802 and fixed here. - - - - - 77171cd1 by Ben Orchard at 2024-03-14T09:00:40-04:00 Note mutability of array and address access primops Without an understanding of immutable vs. mutable memory, the index primop family have a potentially non-intuitive type signature: indexOffAddr :: Addr# -> Int# -> a readOffAddr :: Addr# -> Int# -> State# d -> (# State# d, a #) indexOffAddr# might seem like a free generality improvement, which it certainly is not! This change adds a brief note on mutability expectations for most index/read/write access primops. - - - - - 7da7f8f6 by Alan Zimmerman at 2024-03-14T09:01:15-04:00 EPA: Fix regression discarding comments in contexts Closes #24533 - - - - - 73be65ab by Fendor at 2024-03-19T01:42:53-04:00 Fix sharing of 'IfaceTyConInfo' during core to iface type translation During heap analysis, we noticed that during generation of 'mi_extra_decls' we have lots of duplicates for the instances: * `IfaceTyConInfo NotPromoted IfaceNormalTyCon` * `IfaceTyConInfo IsPromoted IfaceNormalTyCon` which should be shared instead of duplicated. This duplication increased the number of live bytes by around 200MB while loading the agda codebase into GHCi. These instances are created during `CoreToIface` translation, in particular `toIfaceTyCon`. The generated core looks like: toIfaceTyCon = \ tc_sjJw -> case $wtoIfaceTyCon tc_sjJw of { (# ww_sjJz, ww1_sjNL, ww2_sjNM #) -> IfaceTyCon ww_sjJz (IfaceTyConInfo ww1_sjNL ww2_sjNM) } whichs removes causes the sharing to work propery. Adding explicit sharing, with NOINLINE annotations, changes the core to: toIfaceTyCon = \ tc_sjJq -> case $wtoIfaceTyCon tc_sjJq of { (# ww_sjNB, ww1_sjNC #) -> IfaceTyCon ww_sjNB ww1_sjNC } which looks much more like sharing is happening. We confirmed via ghc-debug that all duplications were eliminated and the number of live bytes are noticeably reduced. - - - - - bd8209eb by Alan Zimmerman at 2024-03-19T01:43:28-04:00 EPA: Address more 9.10.1-alpha1 regressions from recent changes Closes #24533 Hopefully for good this time - - - - - 31bf85ee by Fendor at 2024-03-19T14:48:08-04:00 Escape multiple arguments in the settings file Uses responseFile syntax. The issue arises when GHC is installed on windows into a location that has a space, for example the user name is 'Fake User'. The $topdir will also contain a space, consequentially. When we resolve the top dir in the string `-I$topdir/mingw/include`, then `words` will turn this single argument into `-I/C/Users/Fake` and `User/.../mingw/include` which trips up the flag argument parser of various tools such as gcc or clang. We avoid this by escaping the $topdir before replacing it in `initSettngs`. Additionally, we allow to escape spaces and quotation marks for arguments in `settings` file. Add regression test case to count the number of options after variable expansion and argument escaping took place. Additionally, we check that escaped spaces and double quotation marks are correctly parsed. - - - - - f45f700e by Matthew Pickering at 2024-03-19T14:48:44-04:00 Read global package database from settings file Before this patch, the global package database was always assumed to be in libdir </> package.conf.d. This causes issues in GHC's build system because there are sometimes situations where the package database you need to use is not located in the same place as the settings file. * The stage1 compiler needs to use stage1 libraries, so we should set "Global Package DB" for the stage1 compiler to the stage1 package database. * Stage 2 cross compilers need to use stage2 libraries, so likewise, we should set the package database path to `_build/stage2/lib/` * The normal situation is where the stage2 compiler uses stage1 libraries. Then everything lines up. * When installing we have rearranged everything so that the settings file and package database line up properly, so then everything should continue to work as before. In this case we set the relative package db path to `package.conf.d`, so it resolves the same as before. * ghc-pkg needs to be modified as well to look in the settings file fo the package database rather than assuming the global package database location relative to the lib folder. * Cabal/cabal-install will work correctly because they query the global package database using `--print-global-package-db`. A reasonable question is why not generate the "right" settings files in the right places in GHC's build system. In order to do this you would need to engineer wrappers for all executables to point to a specific libdir. There are also situations where the same package db is used by two different compilers with two different settings files (think stage2 cross compiler and stage3 compiler). In short, this 10 line patch allows for some reasonable simplifications in Hadrian at very little cost to anything else. Fixes #24502 - - - - - 4c8f1794 by Matthew Pickering at 2024-03-19T14:48:44-04:00 hadrian: Remove stage1 testsuite wrappers logic Now instead of producing wrappers which pass the global package database argument to ghc and ghc-pkg, we write the location of the correct package database into the settings file so you can just use the intree compiler directly. - - - - - da0d8ba5 by Matthew Craven at 2024-03-19T14:49:20-04:00 Remove unused ghc-internal module "GHC.Internal.Constants" - - - - - b56d2761 by Matthew Craven at 2024-03-19T14:49:20-04:00 CorePrep: Rework lowering of BigNat# literals Don't use bigNatFromWord#, because that's terrible: * We shouldn't have to traverse a linked list at run-time to build a BigNat# literal. That's just silly! * The static List object we have to create is much larger than the actual BigNat#'s contents, bloating code size. * We have to read the corresponding interface file, which causes un-tracked implicit dependencies. (#23942) Instead, encode them into the appropriate platform-dependent sequence of bytes, and generate code that copies these bytes at run-time from an Addr# literal into a new ByteArray#. A ByteArray# literal would be the correct thing to generate, but these are not yet supported; see also #17747. Somewhat surprisingly, this change results in a slight reduction in compiler allocations, averaging around 0.5% on ghc's compiler performance tests, including when compiling programs that contain no bignum literals to begin with. The specific cause of this has not been investigated. Since this lowering no longer reads the interface file for GHC.Num.BigNat, the reasoning in Note [Depend on GHC.Num.Integer] is obsoleted. But the story of un-tracked built-in dependencies remains complex, and Note [Tracking dependencies on primitives] now exists to explain this complexity. Additionally, many empty imports have been modified to refer to this new note and comply with its guidance. Several empty imports necessary for other reasons have also been given brief explanations. Metric Decrease: MultiLayerModulesTH_OneShot - - - - - 349ea330 by Fendor at 2024-03-19T14:50:00-04:00 Eliminate thunk in 'IfaceTyCon' Heap analysis showed that `IfaceTyCon` retains a thunk to `IfaceTyConInfo`, defeating the sharing of the most common instances of `IfaceTyConInfo`. We make sure the indirection is removed by adding bang patterns to `IfaceTyCon`. Experimental results on the agda code base, where the `mi_extra_decls` were read from disk: Before this change, we observe around 8654045 instances of: `IfaceTyCon[Name,THUNK_1_0]` But these thunks almost exclusively point to a shared value! Forcing the thunk a little bit more, leads to `ghc-debug` reporting: `IfaceTyCon[Name:Name,IfaceTyConInfo]` and a noticeable reduction of live bytes (on agda ~10%). - - - - - 594bee0b by Krzysztof Gogolewski at 2024-03-19T14:50:36-04:00 Minor misc cleanups - GHC.HsToCore.Foreign.JavaScript: remove dropRuntimeRepArgs; boxed tuples don't take RuntimeRep args - GHC.HsToCore.Foreign.Call: avoid partial pattern matching - GHC.Stg.Unarise: strengthen the assertion; we can assert that non-rubbish literals are unary rather than just non-void - GHC.Tc.Gen.HsType: make sure the fsLit "literal" rule fires - users_guide/using-warnings.rst: remove -Wforall-identifier, now deprecated and does nothing - users_guide/using.rst: fix formatting - andy_cherry/test.T: remove expect_broken_for(23272...), 23272 is fixed The rest are simple cleanups. - - - - - cf55a54b by Ben Gamari at 2024-03-19T14:51:12-04:00 mk/relpath: Fix quoting Previously there were two instances in this script which lacked proper quoting. This resulted in `relpath` invocations in the binary distribution Makefile producing incorrect results on Windows, leading to confusing failures from `sed` and the production of empty package registrations. Fixes #24538. - - - - - 5ff88389 by Bryan Richter at 2024-03-19T14:51:48-04:00 testsuite: Disable T21336a on wasm - - - - - 60023351 by Ben Gamari at 2024-03-19T22:33:10-04:00 hadrian/bindist: Eliminate extraneous `dirname` invocation Previously we would call `dirname` twice per installed library file. We now instead reuse this result. This helps appreciably on Windows, where processes are quite expensive. - - - - - 616ac300 by Ben Gamari at 2024-03-19T22:33:10-04:00 hadrian: Package mingw toolchain in expected location This fixes #24525, a regression due to 41cbaf44a6ab5eb9fa676d65d32df8377898dc89. Specifically, GHC expects to find the mingw32 toolchain in the binary distribution root. However, after this patch it was packaged in the `lib/` directory. - - - - - de9daade by Ben Gamari at 2024-03-19T22:33:11-04:00 gitlab/rel_eng: More upload.sh tweaks - - - - - 1dfe12db by Ben Gamari at 2024-03-19T22:33:11-04:00 rel_eng: Drop dead prepare_docs codepath - - - - - dd2d748b by Ben Gamari at 2024-03-19T22:33:11-04:00 rel_env/recompress_all: unxz before recompressing Previously we would rather compress the xz *again*, before in addition compressing it with the desired scheme. Fixes #24545. - - - - - 9d936c57 by Ben Gamari at 2024-03-19T22:33:11-04:00 mk-ghcup-metadata: Fix directory of testsuite tarball As reported in #24546, the `dlTest` artifact should be extracted into the `testsuite` directory. - - - - - 6d398066 by Ben Gamari at 2024-03-19T22:33:11-04:00 ghcup-metadata: Don't populate dlOutput unless necessary ghcup can apparently infer the output name of an artifact from its URL. Consequently, we should only include the `dlOutput` field when it would differ from the filename of `dlUri`. Fixes #24547. - - - - - 576f8b7e by Zubin Duggal at 2024-03-19T22:33:46-04:00 Revert "Apply shellcheck suggestion to SUBST_TOOLDIR" This reverts commit c82770f57977a2b5add6e1378f234f8dd6153392. The shellcheck suggestion is spurious and results in SUBST_TOOLDIR being a no-op. `set` sets positional arguments for bash, but we want to set the variable given as the first autoconf argument. Fixes #24542 Metric decreases because the paths in the settings file are now shorter, so we allocate less when we read the settings file. ------------------------- Metric Decrease: T12425 T13035 T9198 ------------------------- - - - - - cdfe6e01 by Fendor at 2024-03-19T22:34:22-04:00 Compact serialisation of IfaceAppArgs In #24563, we identified that IfaceAppArgs serialisation tags each cons cell element with a discriminator byte. These bytes add up quickly, blowing up interface files considerably when '-fwrite-if-simplified-core' is enabled. We compact the serialisation by writing out the length of 'IfaceAppArgs', followed by serialising the elements directly without any discriminator byte. This improvement can decrease the size of some interface files by up to 35%. - - - - - 97a2bb1c by Simon Peyton Jones at 2024-03-20T17:11:29+00:00 Expand untyped splices in tcPolyExprCheck Fixes #24559 - - - - - 5f275176 by Alan Zimmerman at 2024-03-20T22:44:12-04:00 EPA: Clean up Exactprint helper functions a bit - Introduce a helper lens to compose on `EpAnn a` vs `a` versions - Rename some prime versions of functions back to non-prime They were renamed during the rework - - - - - da2a10ce by Vladislav Zavialov at 2024-03-20T22:44:48-04:00 Type operators in promoteOccName (#24570) Type operators differ from term operators in that they are lexically classified as (type) constructors, not as (type) variables. Prior to this change, promoteOccName did not account for this difference, causing a scoping issue that affected RequiredTypeArguments. type (!@#) = Bool f = idee (!@#) -- Not in scope: ‘!@#’ (BUG) Now we have a special case in promoteOccName to account for this. - - - - - 247fc0fa by Preetham Gujjula at 2024-03-21T10:19:18-04:00 docs: Remove mention of non-existent Ord instance for Complex The documentation for Data.Complex says that the Ord instance for Complex Float is deficient, but there is no Ord instance for Complex a. The Eq instance for Complex Float is similarly deficient, so we use that as an example instead. - - - - - 6fafc51e by Andrei Borzenkov at 2024-03-21T10:19:54-04:00 Fix TH handling in `pat_to_type_pat` function (#24571) There was missing case for `SplicePat` in `pat_to_type_at` function, hence patterns with splicing that checked against `forall->` doesn't work properly because they fall into the "illegal pattern" case. Code example that is now accepted: g :: forall a -> () g $([p| a |]) = () - - - - - 52072f8e by Sylvain Henry at 2024-03-21T21:01:59-04:00 Type-check default declarations before deriving clauses (#24566) See added Note and #24566. Default declarations must be type-checked before deriving clauses. - - - - - 7dfdf3d9 by Sylvain Henry at 2024-03-21T21:02:40-04:00 Lexer: small perf changes - Use unsafeChr because we know our values to be valid - Remove some unnecessary use of `ord` (return Word8 values directly) - - - - - 864922ef by Sylvain Henry at 2024-03-21T21:02:40-04:00 JS: fix some comments - - - - - 3e0b2b1f by Sebastian Graf at 2024-03-21T21:03:16-04:00 Simplifier: Re-do dependency analysis in abstractFloats (#24551) In #24551, we abstracted a string literal binding over a type variable, triggering a CoreLint error when that binding floated to top-level. The solution implemented in this patch fixes this by re-doing dependency analysis on a simplified recursive let binding that is about to be type abstracted, in order to find the minimal set of type variables to abstract over. See wrinkle (AB5) of Note [Floating and type abstraction] for more details. Fixes #24551 - - - - - 8a8ac65a by Matthew Craven at 2024-03-23T00:20:52-04:00 Improve toInteger @Word32 on 64-bit platforms On 64-bit platforms, every Word32 fits in an Int, so we can convert to Int# without having to perform the overflow check integerFromWord# uses internally. - - - - - 0c48f2b9 by Apoorv Ingle at 2024-03-23T00:21:28-04:00 Fix for #24552 (see testcase T24552) Fixes for a bug in desugaring pattern synonyms matches, introduced while working on on expanding `do`-blocks in #18324 The `matchWrapper` unecessarily (and incorrectly) filtered out the default wild patterns in a match. Now the wild pattern alternative is simply ignored by the pm check as its origin is `Generated`. The current code now matches the expected semantics according to the language spec. - - - - - b72705e9 by Simon Peyton Jones at 2024-03-23T00:22:04-04:00 Print more info about kinds in error messages This fixes #24553, where GHC unhelpfully said error: [GHC-83865] • Expected kind ‘* -> * -> *’, but ‘Foo’ has kind ‘* -> * -> *’ See Note [Showing invisible bits of types in error messages] - - - - - 8f7cfc7e by Tristan Cacqueray at 2024-03-23T00:22:44-04:00 docs: remove the don't use float hint This hint is outdated, ``Complex Float`` are now specialised, and the heap space suggestion needs more nuance so it should be explained in the unboxed/storable array documentation. - - - - - 5bd8ed53 by Andreas Klebinger at 2024-03-23T16:18:33-04:00 NCG: Fix a bug in jump shortcutting. When checking if a jump has more than one destination account for the possibility of some jumps not being representable by a BlockId. We do so by having isJumpishInstr return a `Maybe BlockId` where Nothing represents non-BlockId jump destinations. Fixes #24507 - - - - - 8d67f247 by Ben Gamari at 2024-03-23T16:19:09-04:00 docs: Drop old release notes, add for 9.12.1 - - - - - 7db8c992 by Cheng Shao at 2024-03-25T13:45:46-04:00 rts: fix clang compilation on aarch64 This patch fixes function prototypes in ARMOutlineAtomicsSymbols.h which causes "error: address argument to atomic operation must be a pointer to _Atomic type" when compiling with clang on aarch64. - - - - - 237194ce by Sylvain Henry at 2024-03-25T13:46:27-04:00 Lexer: fix imports for Alex 3.5.1 (#24583) - - - - - 810660b7 by Cheng Shao at 2024-03-25T22:19:16-04:00 libffi-tarballs: bump libffi-tarballs submodule to libffi 3.4.6 This commit bumps the libffi-tarballs submodule to libffi 3.4.6, which includes numerous upstream libffi fixes, especially https://github.com/libffi/libffi/issues/760. - - - - - d2ba41e8 by Alan Zimmerman at 2024-03-25T22:19:51-04:00 EPA: do not duplicate comments in signature RHS - - - - - 32a8103f by Rodrigo Mesquita at 2024-03-26T21:16:12-04:00 configure: Use LDFLAGS when trying linkers A user may configure `LDFLAGS` but not `LD`. When choosing a linker, we will prefer `ldd`, then `ld.gold`, then `ld.bfd` -- however, we have to check for a working linker. If either of these fail, we try the next in line. However, we were not considering the `$LDFLAGS` when checking if these linkers worked. So we would pick a linker that does not support the current $LDFLAGS and fail further down the line when we used that linker with those flags. Fixes #24565, where `LDFLAGS=-Wl,-z,pack-relative-relocs` is not supported by `ld.gold` but that was being picked still. - - - - - bf65a7c3 by Rodrigo Mesquita at 2024-03-26T21:16:48-04:00 bindist: Clean xattrs of bin and lib at configure time For issue #21506, we started cleaning the extended attributes of binaries and libraries from the bindist *after* they were installed to workaround notarisation (#17418), as part of `make install`. However, the `ghc-toolchain` binary that is now shipped with the bindist must be run at `./configure` time. Since we only cleaned the xattributes of the binaries and libs after they were installed, in some situations users would be unable to run `ghc-toolchain` from the bindist, failing at configure time (#24554). In this commit we move the xattr cleaning logic to the configure script. Fixes #24554 - - - - - cfeb70d3 by Rodrigo Mesquita at 2024-03-26T21:17:24-04:00 Revert "NCG: Fix a bug in jump shortcutting." This reverts commit 5bd8ed53dcefe10b72acb5729789e19ceb22df66. Fixes #24586 - - - - - 13223f6d by Serge S. Gulin at 2024-03-27T07:28:51-04:00 JS: `h$rts_isProfiled` is removed from `profiling` and left its version at `rts/js/config.js` - - - - - 0acfe391 by Alan Zimmerman at 2024-03-27T07:29:27-04:00 EPA: Do not extend declaration range for trailine zero len semi The lexer inserts virtual semicolons having zero width. Do not use them to extend the list span of items in a list. - - - - - cd0fb82f by Alan Zimmerman at 2024-03-27T19:33:08+00:00 EPA: Fix FamDecl range The span was incorrect if opt_datafam_kind_sig was empty - - - - - f8f384a8 by Ben Gamari at 2024-03-29T01:23:03-04:00 Fix type of _get_osfhandle foreign import Fixes #24601. - - - - - 00d3ecf0 by Alan Zimmerman at 2024-03-29T12:19:10+00:00 EPA: Extend StringLiteral range to include trailing commas This goes slightly against the exact printing philosophy where trailing decorations should be in an annotation, but the practicalities of adding it to the WarningTxt environment, and the problems caused by deviating do not make a more principles approach worthwhile. - - - - - efab3649 by brandon s allbery kf8nh at 2024-03-31T20:04:01-04:00 clarify Note [Preproccesing invocations] - - - - - c8a4c050 by Ben Gamari at 2024-04-02T12:50:35-04:00 rts: Fix TSAN_ENABLED CPP guard This should be `#if defined(TSAN_ENABLED)`, not `#if TSAN_ENABLED`, lest we suffer warnings. - - - - - e91dad93 by Cheng Shao at 2024-04-02T12:50:35-04:00 rts: fix errors when compiling with TSAN This commit fixes rts compilation errors when compiling with TSAN: - xxx_FENCE macros are redefined and trigger CPP warnings. - Use SIZEOF_W. WORD_SIZE_IN_BITS is provided by MachDeps.h which Cmm.h doesn't include by default. - - - - - a9ab9455 by Cheng Shao at 2024-04-02T12:50:35-04:00 rts: fix clang-specific errors when compiling with TSAN This commit fixes clang-specific rts compilation errors when compiling with TSAN: - clang doesn't have -Wtsan flag - Fix prototype of ghc_tsan_* helper functions - __tsan_atomic_* functions aren't clang built-ins and sanitizer/tsan_interface_atomic.h needs to be included - On macOS, TSAN runtime library is libclang_rt.tsan_osx_dynamic.dylib, not libtsan. -fsanitize-thread as a link-time flag will take care of linking the TSAN runtime library anyway so remove tsan as an rts extra library - - - - - 865bd717 by Cheng Shao at 2024-04-02T12:50:35-04:00 compiler: fix github link to __tsan_memory_order in a comment - - - - - 07cb627c by Cheng Shao at 2024-04-02T12:50:35-04:00 ci: improve TSAN CI jobs - Run TSAN jobs with +thread_sanitizer_cmm which enables Cmm instrumentation as well. - Run TSAN jobs in deb12 which ships gcc-12, a reasonably recent gcc that @bgamari confirms he's using in #GHC:matrix.org. Ideally we should be using latest clang release for latest improvements in sanitizers, though that's left as future work. - Mark TSAN jobs as manual+allow_failure in validate pipelines. The purpose is to demonstrate that we have indeed at least fixed building of TSAN mode in CI without blocking the patch to land, and once merged other people can begin playing with TSAN using their own dev setups and feature branches. - - - - - a1c18c7b by Andrei Borzenkov at 2024-04-02T12:51:11-04:00 Merge tc_infer_hs_type and tc_hs_type into one function using ExpType philosophy (#24299, #23639) This patch implements refactoring which is a prerequisite to updating kind checking of type patterns. This is a huge simplification of the main worker that checks kind of HsType. It also fixes the issues caused by previous code duplication, e.g. that we didn't add module finalizers from splices in inference mode. - - - - - 817e8936 by Rodrigo Mesquita at 2024-04-02T20:13:05-04:00 th: Hide the Language.Haskell.TH.Lib.Internal module from haddock Fixes #24562 - - - - - b36ee57b by Sylvain Henry at 2024-04-02T20:13:46-04:00 JS: reenable h$appendToHsString optimization (#24495) The optimization introducing h$appendToHsString wasn't kicking in anymore (while it did in 9.8.1) because of the changes introduced in #23270 (7e0c8b3bab30). This patch reenables the optimization by matching on case-expression, as done in Cmm for unpackCString# standard thunks. The test is also T24495 added in the next commits (two commits for ease of backporting to 9.8). - - - - - 527616e9 by Sylvain Henry at 2024-04-02T20:13:46-04:00 JS: fix h$appendToHsString implementation (#24495) h$appendToHsString needs to wrap its argument in an updatable thunk to behave like unpackAppendCString#. Otherwise if a SingleEntry thunk is passed, it is stored as-is in a CONS cell, making the resulting list impossible to deepseq (forcing the thunk doesn't update the contents of the CONS cell)! The added test checks that the optimization kicks in and that h$appendToHsString works as intended. Fix #24495 - - - - - faa30b41 by Simon Peyton Jones at 2024-04-02T20:14:22-04:00 Deal with duplicate tyvars in type declarations GHC was outright crashing before this fix: #24604 - - - - - e0b0c717 by Simon Peyton Jones at 2024-04-02T20:14:58-04:00 Try using MCoercion in exprIsConApp_maybe This is just a simple refactor that makes exprIsConApp_maybe a little bit more direct, simple, and efficient. Metrics: compile_time/bytes allocated geo. mean -0.1% minimum -2.0% maximum -0.0% Not a big gain, but worthwhile given that the code is, if anything, easier to grok. - - - - - 15f4d867 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Initial ./configure support for selecting I/O managers In this patch we just define new CPP vars, but don't yet use them or replace the existing approach. That will follow. The intention here is that every I/O manager can be enabled/disabled at GHC build time (subject to some constraints). More than one I/O manager can be enabled to be built. At least one I/O manager supporting the non-threaded RTS must be enabled as well as at least one supporting the non-threaded RTS. The I/O managers enabled here will become the choices available at runtime at RTS startup (in later patches). The choice can be made with RTS flags. There are separate sets of choices for the threaded and non-threaded RTS ways, because most I/O managers are specific to these ways. Furthermore we must establish a default I/O manager for the threaded and non-threaded RTS. Most I/O managers are platform-specific so there are checks to ensure each one can be enabled on the platform. Such checks are also where (in future) any system dependencies (e.g. libraries) can be checked. The output is a set of CPP flags (in the mk/config.h file), with one flag per named I/O manager: * IOMGR_BUILD_<name> : which ones should be built (some) * IOMGR_DEFAULT_NON_THREADED_<name> : which one is default (exactly one) * IOMGR_DEFAULT_THREADED_<name> : which one is default (exactly one) and a set of derived flags in IOManager.h * IOMGR_ENABLED_<name> : enabled for the current RTS way Note that IOMGR_BUILD_<name> just says that an I/O manager will be built for _some_ RTS way (i.e. threaded or non-threaded). The derived flags IOMGR_ENABLED_<name> in IOManager.h say if each I/O manager is enabled in the "current" RTS way. These are the ones that can be used for conditional compilation of the I/O manager code. Co-authored-by: Pi Delport <pi at well-typed.com> - - - - - 85b0f87a by Duncan Coutts at 2024-04-03T01:27:17-04:00 Change the handling of the RTS flag --io-manager= Now instead of it being just used on Windows to select between the WinIO vs the MIO or Win32-legacy I/O managers, it is now used on all platforms for selecting the I/O manager to use. Right now it remains the case that there is only an actual choice on Windows, but that will change later. Document the --io-manager flag in the user guide. This change is also reflected in the RTS flags types in the base library. Deprecate the export of IoSubSystem from GHC.RTS.Flags with a message to import it from GHC.IO.Subsystem. The way the 'IoSubSystem' is detected also changes. Instead of looking at the RTS flag, there is now a C bool global var in the RTS which gets set on startup when the I/O manager is selected. This bool var says whether the selected I/O manager classifies as "native" on Windows, which in practice means the WinIO I/O manager has been selected. Similarly, the is_io_mng_native_p RTS helper function is re-implemented in terms of the selected I/O manager, rather than based on the RTS flags. We do however remove the ./configure --native-io-manager flag because we're bringing the WinIO/MIO/Win32-legacy choice under the new general scheme for selecting I/O managers, and that new scheme involves no ./configure time user choices, just runtime RTS flag choices. - - - - - 1a8f020f by Duncan Coutts at 2024-04-03T01:27:17-04:00 Convert {init,stop,exit}IOManager to switch style Rather than ad-hoc cpp conitionals on THREADED_RTS and mingw32_HOST_OS, we use a style where we switch on the I/O manager impl, with cases for each I/O manager impl. - - - - - a5bad3d2 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Split up the CapIOManager content by I/O manager Using the new IOMGR_ENABLED_<name> CPP defines. - - - - - 1d36e609 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Convert initIOManagerAfterFork and wakeupIOManager to switch style - - - - - c2f26f36 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move most of waitRead#/Write# from cmm to C Moves it into the IOManager.c where we can follow the new pattern of switching on the selected I/O manager. - - - - - 457705a8 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move most of the delay# impl from cmm to C Moves it into the IOManager.c where we can follow the new pattern of switching on the selected I/O manager. Uses a new IOManager API: syncDelay, following the naming convention of sync* for thread-synchronous I/O & timer/delay operations. As part of porting from cmm to C, we maintain the rule that the why_blocked gets accessed using load acquire and store release atomic memory operations. There was one exception to this rule: in the delay# primop cmm code on posix (not win32), the why_blocked was being updated using a store relaxed, not a store release. I've no idea why. In this convesion I'm playing it safe here and using store release consistently. - - - - - e93058e0 by Duncan Coutts at 2024-04-03T01:27:18-04:00 insertIntoSleepingQueue is no longer public No longer defined in IOManager.h, just a private function in IOManager.c. Since it is no longer called from cmm code, just from syncDelay. It ought to get moved further into the select() I/O manager impl, rather than living in IOManager.c. On the other hand appendToIOBlockedQueue is still called from cmm code in the win32-legacy I/O manager primops async{Read,Write}#, and it is also used by the select() I/O manager. Update the CPP and comments to reflect this. - - - - - 60ce9910 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move anyPendingTimeoutsOrIO impl from .h to .c The implementation is eventually going to need to use more private things, which will drag in unwanted includes into IOManager.h, so it's better to move the impl out of the header file and into the .c file, at the slight cost of it no longer being inline. At the same time, change to the "switch (iomgr_type)" style. - - - - - f70b8108 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Take a simpler approach to gcc warnings in IOManager.c We have lots of functions with conditional implementations for different I/O managers. Some functions, for some I/O managers, naturally have implementations that do nothing or barf. When only one such I/O manager is enabled then the whole function implementation will have an implementation that does nothing or barfs. This then results in warnings from gcc that parameters are unused, or that the function should be marked with attribute noreturn (since barf does not return). The USED_IF_THREADS trick for fine-grained warning supression is fine for just two cases, but an equivalent here would need USED_IF_THE_ONLY_ENABLED_IOMGR_IS_X_OR_Y which would have combinitorial blowup. So we take a coarse grained approach and simply disable these two warnings for the whole file. So we use a GCC pragma, with its handy push/pop support: #pragma GCC diagnostic push #pragma GCC diagnostic ignored "-Wsuggest-attribute=noreturn" #pragma GCC diagnostic ignored "-Wunused-parameter" ... #pragma GCC diagnostic pop - - - - - b48805b9 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add a new trace class for the iomanager It makes sense now for it to be separate from the scheduler class of tracers. Enabled with +RTS -Do. Document the -Do debug flag in the user guide. - - - - - f0c1f862 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Have the throwTo impl go via (new) IOManager APIs rather than directly operating on the IO manager's data structures. Specifically, when thowing an async exception to a thread that is blocked waiting for I/O or waiting for a timer, then we want to cancel that I/O waiting or cancel the timer. Currently this is done directly in removeFromQueues() in RaiseAsync.c. We want it to go via proper APIs both for modularity but also to let us support multiple I/O managers. So add sync{IO,Delay}Cancel, which is the cancellation for the corresponding sync{IO,Delay}. The implementations of these use the usual "switch (iomgr_type)" style. - - - - - 4f9e9c4e by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move awaitEvent into a proper IOManager API and have the scheduler use it. Previously the scheduler calls awaitEvent directly, and awaitEvent is implemented directly in the RTS I/O managers (select, win32). This relies on the old scheme where there's a single active I/O manager for each platform and RTS way. We want to move that to go via an API in IOManager.{h,c} which can then call out to the active I/O manager. Also take the opportunity to split awaitEvent into two. The existing awaitEvent has a bool wait parameter, to say if the call should be blocking or non-blocking. We split this into two separate functions: pollCompletedTimeoutsOrIO and awaitCompletedTimeoutsOrIO. We split them for a few reasons: they have different post-conditions (specifically the await version is supposed to guarantee that there are threads runnable when it completes). Secondly, it is also anticipated that in future I/O managers the implementations of the two cases will be simpler if they are separated. - - - - - 5ad4b30f by Duncan Coutts at 2024-04-03T01:27:18-04:00 Rename awaitEvent in select and win32 I/O managers These are now just called from IOManager.c and are the per-I/O manager backend impls (whereas previously awaitEvent was the entry point). Follow the new naming convention in the IOManager.{h,c} of awaitCompletedTimeoutsOrIO, with the I/O manager's name as a suffix: so awaitCompletedTimeoutsOrIO{Select,Win32}. - - - - - d30c6bc6 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Tidy up a couple things in Select.{h,c} Use the standard #include {Begin,End}Private.h style rather than RTS_PRIVATE on individual decls. And conditionally build the code for the select I/O manager based on the new CPP IOMGR_ENABLED_SELECT rather than on THREADED_RTS. - - - - - 4161f516 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add an IOManager API for scavenging TSO blocked_info When the GC scavenges a TSO it needs to scavenge the tso->blocked_info but the blocked_info is a big union and what lives there depends on the two->why_blocked, which for I/O-related reasons is something that in principle is the responsibility of the I/O manager and not the GC. So the right thing to do is for the GC to ask the I/O manager to sscavenge the blocked_info if it encounters any I/O-related why_blocked reasons. So we add scavengeTSOIOManager in IOManager.{h,c} with the usual style. Now as it happens, right now, there is no special scavenging to do, so the implementation of scavengeTSOIOManager is a fancy no-op. That's because the select I/O manager uses only the fd and target members, which are not GC pointers, and the win32-legacy I/O manager _ought_ to be using GC-managed heap objects for the StgAsyncIOResult but it is actually usingthe C heap, so again no GC pointers. If the win32-legacy were doing this more sensibly, then scavengeTSOIOManager would be the right place to do the GC magic. Future I/O managers will need GC heap objects in the tso->blocked_info and will make use of this functionality. - - - - - 94a87d21 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add I/O manager API notifyIOManagerCapabilitiesChanged Used in setNumCapabilities. It only does anything for MIO on Posix. Previously it always invoked Haskell code, but that code only did anything on non-Windows (and non-JS), and only threaded. That currently effectively means the MIO I/O manager on Posix. So now it only invokes it for the MIO Posix case. - - - - - 3be6d591 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Select an I/O manager early in RTS startup We need to select the I/O manager to use during startup before the per-cap I/O manager initialisation. - - - - - aaa294d0 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Make struct CapIOManager be fully opaque Provide an opaque (forward) definition in Capability.h (since the cap contains a *CapIOManager) and then only provide a full definition in a new file IOManagerInternals.h. This new file is only supposed to be included by the IOManager implementation, not by its users. So that means IOManager.c and individual I/O manager implementations. The posix/Signals.c still needs direct access, but that should be eliminated. Anything that needs direct access either needs to be clearly part of an I/O manager (e.g. the sleect() one) or go via a proper API. - - - - - 877a2a80 by Duncan Coutts at 2024-04-03T01:27:18-04:00 The select() I/O manager does have some global initialisation It's just to make sure an exception CAF is a GC root. - - - - - 9c51473b by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add tracing for the main I/O manager actions Using the new tracer class. Note: The unconditional definition of showIOManager should be compatible with the debugTrace change in 7c7d1f6. Co-authored-by: Pi Delport <pi at well-typed.com> - - - - - c7d3e3a3 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Include the default I/O manager in the +RTS --info output Document the extra +RTS --info output in the user guide - - - - - 8023bad4 by Duncan Coutts at 2024-04-03T01:27:18-04:00 waitRead# / waitWrite# do not work for win32-legacy I/O manager Previously it was unclear that they did not work because the code path was shared with other I/O managers (in particular select()). Following the code carefully shows that what actually happens is that the calling thread would block forever: the thread will be put into the blocked queue, but no other action is scheduled that will ever result in it getting unblocked. It's better to just fail loudly in case anyone accidentally calls it, also it's less confusing code. - - - - - 83a74d20 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Conditionally ignore some GCC warnings Some GCC versions don't know about some warnings, and they complain that we're ignoring unknown warnings. So we try to ignore the warning based on the GCC version. - - - - - 1adc6fa4 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Accept changes to base-exports All the changes are in fact not changes at all. Previously, the IoSubSystem data type was defined in GHC.RTS.Flags and exported from both GHC.RTS.Flags and GHC.IO.SubSystem. Now, the data type is defined in GHC.IO.SubSystem and still exported from both modules. Therefore, the same exports and same instances are still available from both modules. But the base-exports records only the defining module, and so it looks like a change when it is fully compatible. Related: we do add a deprecation to the export of the type via GHC.RTS.Flags, telling people to use the export from GHC.IO.SubSystem. Also the sort order for some unrelated Show instances changed. No idea why. The same changes apply in the other versions, with a few more changes due to sort order weirdness. - - - - - 8d950968 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Accept metric decrease in T12227 I can't think of any good reason that anything in this MR should have changed the number of allocations, up or down. (Yes this is an empty commit.) Metric Decrease: T12227 - - - - - e869605e by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Several improvements to the handling of coercions * Make `mkSymCo` and `mkInstCo` smarter Fixes #23642 * Fix return role of `SelCo` in the coercion optimiser. Fixes #23617 * Make the coercion optimiser `opt_trans_rule` work better for newtypes Fixes #23619 - - - - - 1efd0714 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 FloatOut: improve floating for join point See the new Note [Floating join point bindings]. * Completely get rid of the complicated join_ceiling nonsense, which I have never understood. * Do not float join points at all, except perhaps to top level. * Some refactoring around wantToFloat, to treat Rec and NonRec more uniformly - - - - - 9c00154d by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Improve eta-expansion through call stacks See Note [Eta expanding through CallStacks] in GHC.Core.Opt.Arity This is a one-line change, that fixes an inconsistency - || isCallStackPredTy ty + || isCallStackPredTy ty || isCallStackTy ty - - - - - 95a9a172 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Spelling, layout, pretty-printing only - - - - - bdf1660f by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Improve exprIsConApp_maybe a little Eliminate a redundant case at birth. This sometimes reduces Simplifier iterations. See Note [Case elim in exprIsConApp_maybe]. - - - - - 609cd32c by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Inline GHC.HsToCore.Pmc.Solver.Types.trvVarInfo When exploring compile-time regressions after meddling with the Simplifier, I discovered that GHC.HsToCore.Pmc.Solver.Types.trvVarInfo was very delicately balanced. It's a small, heavily used, overloaded function and it's important that it inlines. By a fluke it was before, but at various times in my journey it stopped doing so. So I just added an INLINE pragma to it; no sense in depending on a delicately-balanced fluke. - - - - - ae24c9bc by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Slight improvement in WorkWrap Ensure that WorkWrap preserves lambda binders, in case of join points. Sadly I have forgotten why I made this change (it was while I was doing a lot of meddling in the Simplifier, but * it does no harm, * it is slightly more efficient, and * presumably it made something better! Anyway I have kept it in a separate commit. - - - - - e9297181 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Use named record fields for the CastIt { ... } data constructor This is a pure refactor - - - - - b4581e23 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Remove a long-commented-out line Pure refactoring - - - - - e026bdf2 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Simplifier improvements This MR started as: allow the simplifer to do more in one pass, arising from places I could see the simplifier taking two iterations where one would do. But it turned into a larger project, because these changes unexpectedly made inlining blow up, especially join points in deeply-nested cases. The main changes are below. There are also many new or rewritten Notes. Avoiding simplifying repeatedly ~~~~~~~~~~~~~~~ See Note [Avoiding simplifying repeatedly] * The SimplEnv now has a seInlineDepth field, which says how deep in unfoldings we are. See Note [Inline depth] in Simplify.Env. Currently used only for the next point: avoiding repeatedly simplifying coercions. * Avoid repeatedly simplifying coercions. see Note [Avoid re-simplifying coercions] in Simplify.Iteration As you'll see from the Note, this makes use of the seInlineDepth. * Allow Simplify.Iteration.simplAuxBind to inline used-once things. This is another part of Note [Post-inline for single-use things], and is really good for reducing simplifier iterations in situations like case K e of { K x -> blah } wher x is used once in blah. * Make GHC.Core.SimpleOpt.exprIsConApp_maybe do some simple case elimination. Note [Case elim in exprIsConApp_maybe] * Improve the case-merge transformation: - Move the main code to `GHC.Core.Utils.mergeCaseAlts`, to join `filterAlts` and friends. See Note [Merge Nested Cases] in GHC.Core.Utils. - Add a new case for `tagToEnum#`; see wrinkle (MC3). - Add a new case to look through join points: see wrinkle (MC4) postInlineUnconditionally ~~~~~~~~~~~~~~~~~~~~~~~~~ * Allow Simplify.Utils.postInlineUnconditionally to inline variables that are used exactly once. See Note [Post-inline for single-use things]. * Do not postInlineUnconditionally join point, ever. Doing so does not reduce allocation, which is the main point, and with join points that are used a lot it can bloat code. See point (1) of Note [Duplicating join points] in GHC.Core.Opt.Simplify.Iteration. * Do not postInlineUnconditionally a strict (demanded) binding. It will not allocate a thunk (it'll turn into a case instead) so again the main point of inlining it doesn't hold. Better to check per-call-site. * Improve occurrence analyis for bottoming function calls, to help postInlineUnconditionally. See Note [Bottoming function calls] in GHC.Core.Opt.OccurAnal Inlining generally ~~~~~~~~~~~~~~~~~~ * In GHC.Core.Opt.Simplify.Utils.interestingCallContext, use RhsCtxt NonRecursive (not BoringCtxt) for a plain-seq case. See Note [Seq is boring] Also, wrinkle (SB1), inline in that `seq` context only for INLINE functions (UnfWhen guidance). * In GHC.Core.Opt.Simplify.Utils.interestingArg, - return ValueArg for OtherCon [c1,c2, ...], but - return NonTrivArg for OtherCon [] This makes a function a little less likely to inline if all we know is that the argument is evaluated, but nothing else. * isConLikeUnfolding is no longer true for OtherCon {}. This propagates to exprIsConLike. Con-like-ness has /positive/ information. Join points ~~~~~~~~~~~ * Be very careful about inlining join points. See these two long Notes Note [Duplicating join points] in GHC.Core.Opt.Simplify.Iteration Note [Inlining join points] in GHC.Core.Opt.Simplify.Inline * When making join points, don't do so if the join point is so small it will immediately be inlined; check uncondInlineJoin. * In GHC.Core.Opt.Simplify.Inline.tryUnfolding, improve the inlining heuristics for join points. In general we /do not/ want to inline join points /even if they are small/. See Note [Duplicating join points] GHC.Core.Opt.Simplify.Iteration. But sometimes we do: see Note [Inlining join points] in GHC.Core.Opt.Simplify.Inline; and the new `isBetterUnfoldingThan` function. * Do not add an unfolding to a join point at birth. This is a tricky one and has a long Note [Do not add unfoldings to join points at birth] It shows up in two places - In `mkDupableAlt` do not add an inlining - (trickier) In `simplLetUnfolding` don't add an unfolding for a fresh join point I am not fully satisifed with this, but it works and is well documented. * In GHC.Core.Unfold.sizeExpr, make jumps small, so that we don't penalise having a non-inlined join point. Performance changes ~~~~~~~~~~~~~~~~~~~ * Binary sizes fall by around 2.6%, according to nofib. * Compile times improve slightly. Here are the figures over 1%. I investiate the biggest differnce in T18304. It's a very small module, just a few hundred nodes. The large percentage difffence is due to a single function that didn't quite inline before, and does now, making code size a bit bigger. I decided gains outweighed the losses. Metrics: compile_time/bytes allocated (changes over +/- 1%) ------------------------------------------------ CoOpt_Singletons(normal) -9.2% GOOD LargeRecord(normal) -23.5% GOOD MultiComponentModulesRecomp(normal) +1.2% MultiLayerModulesTH_OneShot(normal) +4.1% BAD PmSeriesS(normal) -3.8% PmSeriesV(normal) -1.5% T11195(normal) -1.3% T12227(normal) -20.4% GOOD T12545(normal) -3.2% T12707(normal) -2.1% GOOD T13253(normal) -1.2% T13253-spj(normal) +8.1% BAD T13386(normal) -3.1% GOOD T14766(normal) -2.6% GOOD T15164(normal) -1.4% T15304(normal) +1.2% T15630(normal) -8.2% T15630a(normal) NEW T15703(normal) -14.7% GOOD T16577(normal) -2.3% GOOD T17516(normal) -39.7% GOOD T18140(normal) +1.2% T18223(normal) -17.1% GOOD T18282(normal) -5.0% GOOD T18304(normal) +10.8% BAD T18923(normal) -2.9% GOOD T1969(normal) +1.0% T19695(normal) -1.5% T20049(normal) -12.7% GOOD T21839c(normal) -4.1% GOOD T3064(normal) -1.5% T3294(normal) +1.2% BAD T4801(normal) +1.2% T5030(normal) -15.2% GOOD T5321Fun(normal) -2.2% GOOD T6048(optasm) -16.8% GOOD T783(normal) -1.2% T8095(normal) -6.0% GOOD T9630(normal) -4.7% GOOD T9961(normal) +1.9% BAD WWRec(normal) -1.4% info_table_map_perf(normal) -1.3% parsing001(normal) +1.5% geo. mean -2.0% minimum -39.7% maximum +10.8% * Runtimes generally improve. In the testsuite perf/should_run gives: Metrics: runtime/bytes allocated ------------------------------------------ Conversions(normal) -0.3% T13536a(optasm) -41.7% GOOD T4830(normal) -0.1% haddock.Cabal(normal) -0.1% haddock.base(normal) -0.1% haddock.compiler(normal) -0.1% geo. mean -0.8% minimum -41.7% maximum +0.0% * For runtime, nofib is a better test. The news is mostly good. Here are the number more than +/- 0.1%: # bytes allocated ==========================++========== imaginary/digits-of-e1 || -14.40% imaginary/digits-of-e2 || -4.41% imaginary/paraffins || -0.17% imaginary/rfib || -0.15% imaginary/wheel-sieve2 || -0.10% real/compress || -0.47% real/fluid || -0.10% real/fulsom || +0.14% real/gamteb || -1.47% real/gg || -0.20% real/infer || +0.24% real/pic || -0.23% real/prolog || -0.36% real/scs || -0.46% real/smallpt || +4.03% shootout/k-nucleotide || -20.23% shootout/n-body || -0.42% shootout/spectral-norm || -0.13% spectral/boyer2 || -3.80% spectral/constraints || -0.27% spectral/hartel/ida || -0.82% spectral/mate || -20.34% spectral/para || +0.46% spectral/rewrite || +1.30% spectral/sphere || -0.14% ==========================++========== geom mean || -0.59% real/smallpt has a huge nest of local definitions, and I could not pin down a reason for a regression. But there are three big wins! Metric Decrease: CoOpt_Singletons LargeRecord T12227 T12707 T13386 T13536a T14766 T15703 T16577 T17516 T18223 T18282 T18923 T21839c T20049 T5321Fun T5030 T6048 T8095 T9630 T783 Metric Increase: MultiLayerModulesTH_OneShot T13253-spj T18304 T18698a T9961 T3294 - - - - - 27db3c5e by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Testsuite message changes from simplifier improvements - - - - - 271a7812 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Account for bottoming functions in OccurAnal This fixes #24582, a small but long-standing bug - - - - - 0fde229f by Ben Gamari at 2024-04-04T07:04:58-04:00 testsuite: Introduce template-haskell-exports test - - - - - 0c4a9686 by Luite Stegeman at 2024-04-04T07:05:39-04:00 Update correct counter in bumpTickyAllocd - - - - - 5f085d3a by Fendor at 2024-04-04T14:47:33-04:00 Replace `SizedSeq` with `FlatBag` for flattened structure LinkedLists are notoriously memory ineffiecient when all we do is traversing a structure. As 'UnlinkedBCO' has been identified as a data structure that impacts the overall memory usage of GHCi sessions, we avoid linked lists and prefer flattened structure for storing. We introduce a new memory efficient representation of sequential elements that has special support for the cases: * Empty * Singleton * Tuple Elements This improves sharing in the 'Empty' case and avoids the overhead of 'Array' until its constant overhead is justified. - - - - - 82cfe10c by Fendor at 2024-04-04T14:47:33-04:00 Compact FlatBag array representation `Array` contains three additional `Word`'s we do not need in `FlatBag`. Move `FlatBag` to `SmallArray`. Expand the API of SmallArray by `sizeofSmallArray` and add common traversal functions, such as `mapSmallArray` and `foldMapSmallArray`. Additionally, allow users to force the elements of a `SmallArray` via `rnfSmallArray`. - - - - - 36a75b80 by Andrei Borzenkov at 2024-04-04T14:48:10-04:00 Change how invisible patterns represented in haskell syntax and TH AST (#24557) Before this patch: data ArgPat p = InvisPat (LHsType p) | VisPat (LPat p) With this patch: data Pat p = ... | InvisPat (LHsType p) ... And the same transformation in the TH land. The rest of the changes is just updating code to handle new AST and writing tests to check if it is possible to create invalid states using TH. Metric Increase: MultiLayerModulesTH_OneShot - - - - - 28009fbc by Matthew Pickering at 2024-04-04T14:48:46-04:00 Fix off by one error in seekBinNoExpand and seekBin - - - - - 9b9e031b by Ben Gamari at 2024-04-04T21:30:08-04:00 compiler: Allow more types in GHCForeignImportPrim For many, many years `GHCForeignImportPrim` has suffered from the rather restrictive limitation of not allowing any non-trivial types in arguments or results. This limitation was justified by the code generator allegely barfing in the presence of such types. However, this restriction appears to originate well before the NCG rewrite and the new NCG does not appear to have any trouble with such types (see the added `T24598` test). Lift this restriction. Fixes #24598. - - - - - 1324b862 by Alan Zimmerman at 2024-04-04T21:30:44-04:00 EPA: Use EpaLocation not SrcSpan in ForeignDecls This allows us to update them for makeDeltaAst in ghc-exactprint - - - - - 19883a23 by Alan Zimmerman at 2024-04-05T16:58:17-04:00 EPA: Use EpaLocation for RecFieldsDotDot So we can update it to a delta position in makeDeltaAst if needed. - - - - - e8724327 by Matthew Pickering at 2024-04-05T16:58:53-04:00 Remove accidentally committed test.hs - - - - - 88cb3e10 by Fendor at 2024-04-08T09:03:34-04:00 Avoid UArray when indexing is not required `UnlinkedBCO`'s can occur many times in the heap. Each `UnlinkedBCO` references two `UArray`'s but never indexes them. They are only needed to encode the elements into a `ByteArray#`. The three words for the lower bound, upper bound and number of elements are essentially unused, thus we replace `UArray` with a wrapper around `ByteArray#`. This saves us up to three words for each `UnlinkedBCO`. Further, to avoid re-allocating these words for `ResolvedBCO`, we repeat the procedure for `ResolvedBCO` and add custom `Binary` and `Show` instances. For example, agda's repl session has around 360_000 UnlinkedBCO's, so avoiding these three words is already saving us around 8MB residency. - - - - - f2cc1107 by Fendor at 2024-04-08T09:04:11-04:00 Never UNPACK `FastMutInt` for counting z-encoded `FastString`s In `FastStringTable`, we count the number of z-encoded FastStrings that exist in a GHC session. We used to UNPACK the counters to not waste memory, but live retainer analysis showed that we allocate a lot of `FastMutInt`s, retained by `mkFastZString`. We lazily compute the `FastZString`, only incrementing the counter when the `FastZString` is forced. The function `mkFastStringWith` calls `mkZFastString` and boxes the `FastMutInt`, leading to the following core: mkFastStringWith = \ mk_fs _ -> = case stringTable of { FastStringTable _ n_zencs segments# _ -> ... case ((mk_fs (I# ...) (FastMutInt n_zencs)) `cast` <Co:2> :: ...) ... Marking this field as `NOUNPACK` avoids this reboxing, eliminating the allocation of a fresh `FastMutInt` on every `FastString` allocation. - - - - - c6def949 by Matthew Pickering at 2024-04-08T16:06:51-04:00 Force in_multi to avoid retaining entire hsc_env - - - - - fbb91a63 by Fendor at 2024-04-08T16:06:51-04:00 Eliminate name thunk in declaration fingerprinting Thunk analysis showed that we have about 100_000 thunks (in agda and `-fwrite-simplified-core`) pointing to the name of the name decl. Forcing this thunk fixes this issue. The thunk created here is retained by the thunk created by forkM, it is better to eagerly force this because the result (a `Name`) is already retained indirectly via the `IfaceDecl`. - - - - - 3b7b0c1c by Alan Zimmerman at 2024-04-08T16:07:27-04:00 EPA: Use EpaLocation in WarningTxt This allows us to use an EpDelta if needed when using makeDeltaAst. - - - - - 12b997df by Alan Zimmerman at 2024-04-08T16:07:27-04:00 EPA: Move DeltaPos and EpaLocation' into GHC.Types.SrcLoc This allows us to use a NoCommentsLocation for the possibly trailing comma location in a StringLiteral. This in turn allows us to correctly roundtrip via makeDeltaAst. - - - - - 868c8a78 by Fendor at 2024-04-09T08:51:50-04:00 Prefer packed representation for CompiledByteCode As there are many 'CompiledByteCode' objects alive during a GHCi session, representing its element in a more packed manner improves space behaviour at a minimal cost. When running GHCi on the agda codebase, we find around 380 live 'CompiledByteCode' objects. Packing their respective 'UnlinkedByteCode' can save quite some pointers. - - - - - be3bddde by Alan Zimmerman at 2024-04-09T08:52:26-04:00 EPA: Capture all comments in a ClassDecl Hopefully the final fix needed for #24533 - - - - - 3d0806fc by Jade at 2024-04-10T05:39:53-04:00 Validate -main-is flag using parseIdentifier Fixes #24368 - - - - - dd530bb7 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 rts: free error message before returning Fixes a memory leak in rts/linker/PEi386.c - - - - - e008a19a by Alexis King at 2024-04-10T05:40:29-04:00 linker: Avoid linear search when looking up Haskell symbols via dlsym See the primary Note [Looking up symbols in the relevant objects] for a more in-depth explanation. When dynamically loading a Haskell symbol (typical when running a splice or GHCi expression), before this commit we would search for the symbol in all dynamic libraries that were loaded. However, this could be very inefficient when too many packages are loaded (which can happen if there are many package dependencies) because the time to lookup the would be linear in the number of packages loaded. This commit drastically improves symbol loading performance by introducing a mapping from units to the handles of corresponding loaded dlls. These handles are returned by dlopen when we load a dll, and can then be used to look up in a specific dynamic library. Looking up a given Name is now much more precise because we can get lookup its unit in the mapping and lookup the symbol solely in the handles of the dynamic libraries loaded for that unit. In one measurement, the wait time before the expression was executed went from +-38 seconds down to +-2s. This commit also includes Note [Symbols may not be found in pkgs_loaded], explaining the fallback to the old behaviour in case no dll can be found in the unit mapping for a given Name. Fixes #23415 Co-authored-by: Rodrigo Mesquita (@alt-romes) - - - - - dcfaa190 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 rts: Make addDLL a wrapper around loadNativeObj Rewrite the implementation of `addDLL` as a wrapper around the more principled `loadNativeObj` rts linker function. The latter should be preferred while the former is preserved for backwards compatibility. `loadNativeObj` was previously only available on ELF platforms, so this commit further refactors the rts linker to transform loadNativeObj_ELF into loadNativeObj_POSIX, which is available in ELF and MachO platforms. The refactor made it possible to remove the `dl_mutex` mutex in favour of always using `linker_mutex` (rather than a combination of both). Lastly, we implement `loadNativeObj` for Windows too. - - - - - 12931698 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 Use symbol cache in internal interpreter too This commit makes the symbol cache that was used by the external interpreter available for the internal interpreter too. This follows from the analysis in #23415 that suggests the internal interpreter could benefit from this cache too, and that there is no good reason not to have the cache for it too. It also makes it a bit more uniform to have the symbol cache range over both the internal and external interpreter. This commit also refactors the cache into a function which is used by both `lookupSymbol` and also by `lookupSymbolInDLL`, extending the caching logic to `lookupSymbolInDLL` too. - - - - - dccd3ea1 by Ben Gamari at 2024-04-10T05:40:29-04:00 testsuite: Add test for lookupSymbolInNativeObj - - - - - 1b1a92bd by Alan Zimmerman at 2024-04-10T05:41:05-04:00 EPA: Remove unnecessary XRec in CompleteMatchSig The XRec for [LIdP pass] is not needed for exact printing, remove it. - - - - - 6e18ce2b by Ben Gamari at 2024-04-12T08:16:09-04:00 users-guide: Clarify language extension documentation Over the years the users guide's language extension documentation has gone through quite a few refactorings. In the process some of the descriptions have been rendered non-sensical. For instance, the description of `NoImplicitPrelude` actually describes the semantics of `ImplicitPrelude`. To fix this we: * ensure that all extensions are named in their "positive" sense (e.g. `ImplicitPrelude` rather than `NoImplicitPrelude`). * rework the documentation to avoid flag-oriented wording like "enable" and "disable" * ensure that the polarity of the documentation is consistent with reality. Fixes #23895. - - - - - a933aff3 by Zubin Duggal at 2024-04-12T08:16:45-04:00 driver: Make `checkHomeUnitsClosed` faster The implementation of `checkHomeUnitsClosed` was traversing every single path in the unit dependency graph - this grows exponentially and quickly grows to be infeasible on larger unit dependency graphs. Instead we replace this with a faster implementation which follows from the specificiation of the closure property - there is a closure error if there are units which are both are both (transitively) depended upon by home units and (transitively) depend on home units, but are not themselves home units. To compute the set of units required for closure, we first compute the closure of the unit dependency graph, then the transpose of this closure, and find all units that are reachable from the home units in the transpose of the closure. - - - - - 23c3e624 by Andreas Klebinger at 2024-04-12T08:17:21-04:00 RTS: Emit warning when -M < -H Fixes #24487 - - - - - d23afb8c by Ben Gamari at 2024-04-12T08:17:56-04:00 testsuite: Add broken test for CApiFFI with -fprefer-bytecode See #24634. - - - - - a4bb3a51 by Ben Gamari at 2024-04-12T08:18:32-04:00 base: Deprecate GHC.Pack As proposed in #21461. Closes #21540. - - - - - 55eb8c98 by Ben Gamari at 2024-04-12T08:19:08-04:00 ghc-internal: Fix mentions of ghc-internal in deprecation warnings Closes #24609. - - - - - b0fbd181 by Ben Gamari at 2024-04-12T08:19:44-04:00 rts: Implement set_initial_registers for AArch64 Fixes #23680. - - - - - 14c9ec62 by Ben Gamari at 2024-04-12T08:20:20-04:00 ghcup-metadata: Use Debian 9 binaries on Ubuntu 16, 17 Closes #24646. - - - - - 35a1621e by Ben Gamari at 2024-04-12T08:20:55-04:00 Bump unix submodule to 2.8.5.1 Closes #24640. - - - - - a1c24df0 by Finley McIlwaine at 2024-04-12T08:21:31-04:00 Correct default -funfolding-use-threshold in docs - - - - - 0255d03c by Oleg Grenrus at 2024-04-12T08:22:07-04:00 FastString is a __Modified__ UTF-8 - - - - - c3489547 by Matthew Pickering at 2024-04-12T13:13:44-04:00 rts: Improve tracing message when nursery is resized It is sometimes more useful to know how much bigger or smaller the nursery got when it is resized. In particular I am trying to investigate situations where we end up with fragmentation due to the nursery (#24577) - - - - - 5e4f4ba8 by Simon Peyton Jones at 2024-04-12T13:14:20-04:00 Don't generate wrappers for `type data` constructors with StrictData Previously, the logic for checking if a data constructor needs a wrapper or not would take into account whether the constructor's fields have explicit strictness (e.g., `data T = MkT !Int`), but the logic would _not_ take into account whether `StrictData` was enabled. This meant that something like `type data T = MkT Int` would incorrectly generate a wrapper for `MkT` if `StrictData` was enabled, leading to the horrible errors seen in #24620. To fix this, we disable generating wrappers for `type data` constructors altogether. Fixes #24620. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - dbdf1995 by Alex Mason at 2024-04-15T15:28:26+10:00 Implements MO_S_Mul2 and MO_U_Mul2 using the UMULH, UMULL and SMULH instructions for AArch64 Also adds a test for MO_S_Mul2 - - - - - 42bd0407 by Teo Camarasu at 2024-04-16T20:06:39-04:00 Make template-haskell a stage1 package Promoting template-haskell from a stage0 to a stage1 package means that we can much more easily refactor template-haskell. We implement this by duplicating the in-tree `template-haskell`. A new `template-haskell-next` library is autogenerated to mirror `template-haskell` `stage1:ghc` to depend on the new interface of the library including the `Binary` instances without adding an explicit dependency on `template-haskell`. This is controlled by the `bootstrap-th` cabal flag When building `template-haskell` modules as part of this vendoring we do not have access to quote syntax, so we cannot use variable quote notation (`'Just`). So we either replace these with hand-written `Name`s or hide the code behind CPP. We can remove the `th_hack` from hadrian, which was required when building stage0 packages using the in-tree `template-haskell` library. For more details see Note [Bootstrapping Template Haskell]. Resolves #23536 Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> Co-Authored-By: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org> - - - - - 3d973e47 by Ben Gamari at 2024-04-16T20:07:15-04:00 Bump parsec submodule to 3.1.17.0 - - - - - 9d38bfa0 by Simon Peyton Jones at 2024-04-16T20:07:51-04:00 Clone CoVars in CorePrep This MR addresses #24463. It's all explained in the new Note [Cloning CoVars and TyVars] - - - - - 0fe2b410 by Andreas Klebinger at 2024-04-16T20:08:27-04:00 NCG: Fix a bug where we errounously removed a required jump instruction. Add a new method to the Instruction class to check if we can eliminate a jump in favour of fallthrough control flow. Fixes #24507 - - - - - 9f99126a by Teo Camarasu at 2024-04-16T20:09:04-04:00 Fix documentation preview from doc-tarball job - Include all the .html files and assets in the job artefacts - Include all the .pdf files in the job artefacts - Mark the artefact as an "exposed" artefact meaning it turns up in the UI. Resolves #24651 - - - - - 3a0642ea by Ben Gamari at 2024-04-16T20:09:39-04:00 rts: Ignore EINTR while polling in timerfd itimer implementation While the RTS does attempt to mask signals, it may be that a foreign library unmasks them. This previously caused benign warnings which we now ignore. See #24610. - - - - - 9a53cd3f by Alan Zimmerman at 2024-04-16T20:10:15-04:00 EPA: Add additional comments field to AnnsModule This is used in exact printing to store comments coming after the `where` keyword but before any comments allocated to imports or decls. It is used in ghc-exactprint, see https://github.com/alanz/ghc-exactprint/commit/44bbed311fd8f0d053053fef195bf47c17d34fa7 - - - - - e5c43259 by Bryan Richter at 2024-04-16T20:10:51-04:00 Remove unrunnable FreeBSD CI jobs FreeBSD runner supply is inelastic. Currently there is only one, and it's unavailable because of a hardware issue. - - - - - 914eb49a by Ben Gamari at 2024-04-16T20:11:27-04:00 rel-eng: Fix mktemp usage in recompress-all We need a temporary directory, not a file. - - - - - f30e4984 by Teo Camarasu at 2024-04-16T20:12:03-04:00 Fix ghc API link in docs/index.html This was missing part of the unit ID meaning it would 404. Resolves #24674 - - - - - d7a3d6b5 by Ben Gamari at 2024-04-16T20:12:39-04:00 template-haskell: Declare TH.Lib.Internal as not-home Rather than `hide`. Closes #24659. - - - - - 5eaa46e7 by Matthew Pickering at 2024-04-19T02:14:55-04:00 testsuite: Rename isCross() predicate to needsTargetWrapper() isCross() was a misnamed because it assumed that all cross targets would provide a target wrapper, but the two most common cross targets (javascript, wasm) don't need a target wrapper. Therefore we rename this predicate to `needsTargetWrapper()` so situations in the testsuite where we can check whether running executables requires a target wrapper or not. - - - - - 55a9d699 by Simon Peyton Jones at 2024-04-19T02:15:32-04:00 Do not float HNFs out of lambdas This MR adjusts SetLevels so that it is less eager to float a HNF (lambda or constructor application) out of a lambda, unless it gets to top level. Data suggests that this change is a small net win: * nofib bytes-allocated falls by -0.09% (but a couple go up) * perf/should_compile bytes-allocated falls by -0.5% * perf/should_run bytes-allocated falls by -0.1% See !12410 for more detail. When fiddling elsewhere, I also found that this patch had a huge positive effect on the (very delicate) test perf/should_run/T21839r But that improvement doesn't show up in this MR by itself. Metric Decrease: MultiLayerModulesRecomp T15703 parsing001 - - - - - f0701585 by Alan Zimmerman at 2024-04-19T02:16:08-04:00 EPA: Fix comments in mkListSyntaxTy0 Also extend the test to confirm. Addresses #24669, 1 of 4 - - - - - b01c01d4 by Serge S. Gulin at 2024-04-19T02:16:51-04:00 JS: set image `x86_64-linux-deb11-emsdk-closure` for build - - - - - c90c6039 by Alan Zimmerman at 2024-04-19T02:17:27-04:00 EPA: Provide correct span for PatBind And remove unused parameter in checkPatBind Contributes to #24669 - - - - - bee54c24 by Krzysztof Gogolewski at 2024-04-19T11:13:00+02:00 Update quantification order following GHC haskell/haddock#23764 - - - - - 2814eb89 by Ben Gamari at 2024-04-19T18:57:05+02:00 hypsrc-test: Fix output of PositionPragmas.html - - - - - 26036f96 by Alan Zimmerman at 2024-04-19T13:11:08-04:00 EPA: Fix span for PatBuilderAppType Include the location of the prefix @ in the span for InVisPat. Also removes unnecessary annotations from HsTP. Contributes to #24669 - - - - - dba03aab by Matthew Craven at 2024-04-19T13:11:44-04:00 testsuite: Give the pre_cmd for mhu-perf more time - - - - - d31fbf6c by Krzysztof Gogolewski at 2024-04-19T21:04:09-04:00 Fix quantification order for a `op` b and a %m -> b Fixes #23764 Implements https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0640-tyop-quantification-order.rst Updates haddock submodule. - - - - - 385cd1c4 by Sebastian Graf at 2024-04-19T21:04:45-04:00 Make `seq#` a magic Id and inline it in CorePrep (#24124) We can save much code and explanation in Tag Inference and StgToCmm by making `seq#` a known-key Magic Id in `GHC.Internal.IO` and inline this definition in CorePrep. See the updated `Note [seq# magic]`. I also implemented a new `Note [Flatten case-bind]` to get better code for otherwise nested case scrutinees. I renamed the contructors of `ArgInfo` to use an `AI` prefix in order to resolve the clash between `type CpeApp = CoreExpr` and the data constructor of `ArgInfo`, as well as fixed typos in `Note [CorePrep invariants]`. Fixes #24252 and #24124. - - - - - 275e41a9 by Jade at 2024-04-20T11:10:40-04:00 Put the newline after errors instead of before them This mainly has consequences for GHCi but also slightly alters how the output of GHC on the commandline looks. Fixes: #22499 - - - - - dd339c7a by Teo Camarasu at 2024-04-20T11:11:16-04:00 Remove unecessary stage0 packages Historically quite a few packages had to be stage0 as they depended on `template-haskell` and that was stage0. In #23536 we made it so that was no longer the case. This allows us to remove a bunch of packages from this list. A few still remain. A new version of `Win32` is required by `semaphore-compat`. Including `Win32` in the stage0 set requires also including `filepath` because otherwise Hadrian's dependency logic gets confused. Once our boot compiler has a newer version of `Win32` all of these will be able to be dropped. Resolves #24652 - - - - - 2f8e3a25 by Alan Zimmerman at 2024-04-20T11:11:52-04:00 EPA: Avoid duplicated comments in splice decls Contributes to #24669 - - - - - c70b9ddb by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: fix typos and namings (fixes #24602) You may noted that I've also changed term of ``` , global "h$vt_double" ||= toJExpr IntV ``` See "IntV" and ``` WaitReadOp -> \[] [fd] -> pure $ PRPrimCall $ returnS (app "h$waidRead" [fd]) ``` See "h$waidRead" - - - - - 3db54f9b by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: trivial checks for variable presence (fixes #24602) - - - - - 777f108f by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: fs module imported twice (by emscripten and by ghc-internal). ghc-internal import wrapped in a closure to prevent conflict with emscripten (fixes #24602) Better solution is to use some JavaScript module system like AMD, CommonJS or even UMD. It will be investigated at other issues. At first glance we should try UMD (See https://github.com/umdjs/umd) - - - - - a45a5712 by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: thread.js requires h$fds and h$fdReady to be declared for static code analysis, minimal code copied from GHCJS (fixes #24602) I've just copied some old pieces of GHCJS from publicly available sources (See https://github.com/Taneb/shims/blob/a6dd0202dcdb86ad63201495b8b5d9763483eb35/src/io.js#L607). Also I didn't put details to h$fds. I took minimal and left only its object initialization: `var h$fds = {};` - - - - - ad90bf12 by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: heap and stack overflows reporting defined as js hard failure (fixes #24602) These errors were treated as a hard failure for browser application. The fix is trivial: just throw error. - - - - - 5962fa52 by Serge S. Gulin at 2024-04-21T16:33:44+03:00 JS: Stubs for code without actual implementation detected by Google Closure Compiler (fixes #24602) These errors were fixed just by introducing stubbed functions with throw for further implementation. - - - - - a0694298 by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Add externs to linker (fixes #24602) After enabling jsdoc and built-in google closure compiler types I was needed to deal with the following: 1. Define NodeJS-environment types. I've just copied minimal set of externs from semi-official repo (see https://github.com/externs/nodejs/blob/6c6882c73efcdceecf42e7ba11f1e3e5c9c041f0/v8/nodejs.js#L8). 2. Define Emscripten-environment types: `HEAP8`. Emscripten already provides some externs in our code but it supposed to be run in some module system. And its definitions do not work well in plain bundle. 3. We have some functions which purpose is to add to functions some contextual information via function properties. These functions should be marked as `modifies` to let google closure compiler remove calls if these functions are not used actually by call graph. Such functions are: `h$o`, `h$sti`, `h$init_closure`, `h$setObjInfo`. 4. STG primitives such as registries and stuff from `GHC.StgToJS`. `dXX` properties were already present at externs generator function but they are started from `7`, not from `1`. This message is related: `// fixme does closure compiler bite us here?` - - - - - e58bb29f by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: added both tests: for size and for correctness (fixes #24602) By some reason MacOS builds add to stderr messages like: Ignoring unexpected archive entry: __.SYMDEF ... However I left stderr to `/dev/null` for compatibility with linux CI builds. - - - - - 909f3a9c by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Disable js linker warning for empty symbol table to make js tests running consistent across environments - - - - - 83eb10da by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Add special preprocessor for js files due of needing to keep jsdoc comments (fixes #24602) Our js files have defined google closure compiler types at jsdoc entries but these jsdoc entries are removed by cpp preprocessor. I considered that reusing them in javascript-backend would be a nice thing. Right now haskell processor uses `-traditional` option to deal with comments and `//` operators. But now there are following compiler options: `-C` and `-CC`. You can read about them at GCC (see https://gcc.gnu.org/onlinedocs/gcc/Preprocessor-Options.html#index-CC) and CLang (see https://clang.llvm.org/docs/ClangCommandLineReference.html#cmdoption-clang-CC). It seems that `-CC` works better for javascript jsdoc than `-traditional`. At least it leaves `/* ... */` comments w/o changes. - - - - - e1cf8dc2 by brandon s allbery kf8nh at 2024-04-22T03:48:26-04:00 fix link in CODEOWNERS It seems that our local Gitlab no longer has documentation for the `CODEOWNERS` file, but the master documentation still does. Use that instead. - - - - - a27c6a49 by Fendor at 2024-04-22T10:13:03+02:00 Adapt to UserData split - - - - - 1efc5a7a by Fendor at 2024-04-22T10:13:03+02:00 Adapt to BinHandle split - - - - - 593f4e04 by Fendor at 2024-04-23T10:19:14-04:00 Add performance regression test for '-fwrite-simplified-core' - - - - - 1ba39b05 by Fendor at 2024-04-23T10:19:14-04:00 Typecheck corebindings lazily during bytecode generation This delays typechecking the corebindings until the bytecode generation happens. We also avoid allocating a thunk that is retained by `unsafeInterleaveIO`. In general, we shouldn't retain values of the hydrated `Type`, as not evaluating the bytecode object keeps it alive. It is better if we retain the unhydrated `IfaceType`. See Note [Hydrating Modules] - - - - - e916fc92 by Alan Zimmerman at 2024-04-23T10:19:50-04:00 EPA: Keep comments in a CaseAlt match The comments now live in the surrounding location, not inside the Match. Make sure we keep them. Closes #24707 - - - - - d2b17f32 by Cheng Shao at 2024-04-23T15:01:22-04:00 driver: force merge objects when building dynamic objects This patch forces the driver to always merge objects when building dynamic objects even when ar -L is supported. It is an oversight of !8887: original rationale of that patch is favoring the relatively cheap ar -L operation over object merging when ar -L is supported, which makes sense but only if we are building static objects! Omitting check for whether we are building dynamic objects will result in broken .so files with undefined reference errors at executable link time when building GHC with llvm-ar. Fixes #22210. - - - - - 209d09f5 by Julian Ospald at 2024-04-23T15:02:03-04:00 Allow non-absolute values for bootstrap GHC variable Fixes #24682 - - - - - 3fff0977 by Matthew Pickering at 2024-04-23T15:02:38-04:00 Don't depend on registerPackage function in Cabal More recent versions of Cabal modify the behaviour of libAbiHash which breaks our usage of registerPackage. It is simpler to inline the part of registerPackage that we need and avoid any additional dependency and complication using the higher-level function introduces. - - - - - c62dc317 by Cheng Shao at 2024-04-25T01:32:02-04:00 ghc-bignum: remove obsolete ln script This commit removes an obsolete ln script in ghc-bignum/gmp. See 060251c24ad160264ae8553efecbb8bed2f06360 for its original intention, but it's been obsolete for a long time, especially since the removal of the make build system. Hence the house cleaning. - - - - - 6399d52b by Cheng Shao at 2024-04-25T01:32:02-04:00 ghc-bignum: update gmp to 6.3.0 This patch bumps the gmp-tarballs submodule and updates gmp to 6.3.0. The tarball format is now xz, and gmpsrc.patch has been patched into the tarball so hadrian no longer needs to deal with patching logic when building in-tree GMP. - - - - - 65b4b92f by Cheng Shao at 2024-04-25T01:32:02-04:00 hadrian: remove obsolete Patch logic This commit removes obsolete Patch logic from hadrian, given we no longer need to patch the gmp tarball when building in-tree GMP. - - - - - 71f28958 by Cheng Shao at 2024-04-25T01:32:02-04:00 autoconf: remove obsolete patch detection This commit removes obsolete deletection logic of the patch command from autoconf scripts, given we no longer need to patch anything in the GHC build process. - - - - - daeda834 by Sylvain Henry at 2024-04-25T01:32:43-04:00 JS: correctly handle RUBBISH literals (#24664) - - - - - 8a06ddf6 by Matthew Pickering at 2024-04-25T11:16:16-04:00 Linearise ghc-internal and base build This is achieved by requesting the final package database for ghc-internal, which mandates it is fully built as a dependency of configuring the `base` package. This is at the expense of cross-package parrallelism between ghc-internal and the base package. Fixes #24436 - - - - - 94da9365 by Andrei Borzenkov at 2024-04-25T11:16:54-04:00 Fix tuple puns renaming (24702) Move tuple renaming short cutter from `isBuiltInOcc_maybe` to `isPunOcc_maybe`, so we consider incoming module. I also fixed some hidden bugs that raised after the change was done. - - - - - fa03b1fb by Fendor at 2024-04-26T18:03:13-04:00 Refactor the Binary serialisation interface The goal is simplifiy adding deduplication tables to `ModIface` interface serialisation. We identify two main points of interest that make this difficult: 1. UserData hardcodes what `Binary` instances can have deduplication tables. Moreover, it heavily uses partial functions. 2. GHC.Iface.Binary hardcodes the deduplication tables for 'Name' and 'FastString', making it difficult to add more deduplication. Instead of having a single `UserData` record with fields for all the types that can have deduplication tables, we allow to provide custom serialisers for any `Typeable`. These are wrapped in existentials and stored in a `Map` indexed by their respective `TypeRep`. The `Binary` instance of the type to deduplicate still needs to explicitly look up the decoder via `findUserDataReader` and `findUserDataWriter`, which is no worse than the status-quo. `Map` was chosen as microbenchmarks indicate it is the fastest for a small number of keys (< 10). To generalise the deduplication table serialisation mechanism, we introduce the types `ReaderTable` and `WriterTable` which provide a simple interface that is sufficient to implement a general purpose deduplication mechanism for `writeBinIface` and `readBinIface`. This allows us to provide a list of deduplication tables for serialisation that can be extended more easily, for example for `IfaceTyCon`, see the issue https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for more motivation. In addition to this refactoring, we split `UserData` into `ReaderUserData` and `WriterUserData`, to avoid partial functions and reduce overall memory usage, as we need fewer mutable variables. Bump haddock submodule to accomodate for `UserData` split. ------------------------- Metric Increase: MultiLayerModulesTH_Make MultiLayerModulesRecomp T21839c ------------------------- - - - - - bac57298 by Fendor at 2024-04-26T18:03:13-04:00 Split `BinHandle` into `ReadBinHandle` and `WriteBinHandle` A `BinHandle` contains too much information for reading data. For example, it needs to keep a `FastMutInt` and a `IORef BinData`, when the non-mutable variants would suffice. Additionally, this change has the benefit that anyone can immediately tell whether the `BinHandle` is used for reading or writing. Bump haddock submodule BinHandle split. - - - - - 4d6394dd by Simon Peyton Jones at 2024-04-26T18:03:49-04:00 Fix missing escaping-kind check in tcPatSynSig Note [Escaping kind in type signatures] explains how we deal with escaping kinds in type signatures, e.g. f :: forall r (a :: TYPE r). a where the kind of the body is (TYPE r), but `r` is not in scope outside the forall-type. I had missed this subtlety in tcPatSynSig, leading to #24686. This MR fixes it; and a similar bug in tc_top_lhs_type. (The latter is tested by T24686a.) - - - - - 981c2c2c by Alan Zimmerman at 2024-04-26T18:04:25-04:00 EPA: check-exact: check that the roundtrip reproduces the source Closes #24670 - - - - - a8616747 by Andrew Lelechenko at 2024-04-26T18:05:01-04:00 Document that setEnv is not thread-safe - - - - - 1e41de83 by Bryan Richter at 2024-04-26T18:05:37-04:00 CI: Work around frequent Signal 9 errors - - - - - a6d5f9da by Naïm Favier at 2024-04-27T17:52:40-04:00 ghc-internal: add MonadFix instance for (,) Closes https://gitlab.haskell.org/ghc/ghc/-/issues/24288, implements CLC proposal https://github.com/haskell/core-libraries-committee/issues/238. Adds a MonadFix instance for tuples, permitting value recursion in the "native" writer monad and bringing consistency with the existing instance for transformers's WriterT (and, to a lesser extent, for Solo). - - - - - 64feadcd by Rodrigo Mesquita at 2024-04-27T17:53:16-04:00 bindist: Fix xattr cleaning The original fix (725343aa) was incorrect because it used the shell bracket syntax which is the quoting syntax in autoconf, making the test for existence be incorrect and therefore `xattr` was never run. Fixes #24554 - - - - - e2094df3 by damhiya at 2024-04-28T23:52:00+09:00 Make read accepts binary integer formats CLC proposal : https://github.com/haskell/core-libraries-committee/issues/177 - - - - - c62239b7 by Sylvain Henry at 2024-04-29T10:35:00+02:00 Fix tests for T22229 - - - - - 1c2fd963 by Alan Zimmerman at 2024-04-29T23:17:00-04:00 EPA: Preserve comments in Match Pats Closes #24708 Closes #24715 Closes #24734 - - - - - 4189d17e by Sylvain Henry at 2024-04-29T23:17:42-04:00 LLVM: better unreachable default destination in Switch (#24717) See added note. Co-authored-by: Siddharth Bhat <siddu.druid at gmail.com> - - - - - a3725c88 by Cheng Shao at 2024-04-29T23:18:20-04:00 ci: enable wasm jobs for MRs with wasm label This patch enables wasm jobs for MRs with wasm label. Previously the wasm label didn't actually have any effect on the CI pipeline, and full-ci needed to be applied to run wasm jobs which was a waste of runners when working on the wasm backend, hence the fix here. - - - - - 702f7964 by Matthew Pickering at 2024-04-29T23:18:56-04:00 Make interface files and object files depend on inplace .conf file A potential fix for #24737 - - - - - 728af21e by Cheng Shao at 2024-04-30T05:30:23-04:00 utils: remove obsolete vagrant scripts Vagrantfile has long been removed in !5288. This commit further removes the obsolete vagrant scripts in the tree. - - - - - 36f2c342 by Cheng Shao at 2024-04-30T05:31:00-04:00 Update autoconf scripts Scripts taken from autoconf 948ae97ca5703224bd3eada06b7a69f40dd15a02 - - - - - ecbf22a6 by Ben Gamari at 2024-04-30T05:31:36-04:00 ghcup-metadata: Drop output_name field This is entirely redundant to the filename of the URL. There is no compelling reason to name the downloaded file differently from its source. - - - - - c56d728e by Zubin Duggal at 2024-04-30T22:45:09-04:00 testsuite: Handle exceptions in framework_fail when testdir is not initialised When `framework_fail` is called before initialising testdir, it would fail with an exception reporting the testdir not being initialised instead of the actual failure. Ensure we report the actual reason for the failure instead of failing in this way. One way this can manifest is when trying to run a test that doesn't exist using `--only` - - - - - d5bea4d6 by Alan Zimmerman at 2024-04-30T22:45:45-04:00 EPA: Fix range for GADT decl with sig only Closes #24714 - - - - - 4d78c53c by Sylvain Henry at 2024-05-01T17:23:06-04:00 Fix TH dependencies (#22229) Add a dependency between Syntax and Internal (via module reexport). - - - - - 37e38db4 by Sylvain Henry at 2024-05-01T17:23:06-04:00 Bump haddock submodule - - - - - ca13075c by Sylvain Henry at 2024-05-01T17:23:47-04:00 JS: cleanup to prepare for #24743 - - - - - 40026ac3 by Alan Zimmerman at 2024-05-01T22:45:07-04:00 EPA: Preserve comments for PrefixCon Preserve comments in fun (Con {- c1 -} a b) = undefined Closes #24736 - - - - - 92134789 by Hécate Moonlight at 2024-05-01T22:45:42-04:00 Correct `@since` metadata in HpcFlags It was introduced in base-4.20, not 4.22. Fix #24721 - - - - - a580722e by Cheng Shao at 2024-05-02T08:18:45-04:00 testsuite: fix req_target_smp predicate - - - - - ac9c5f84 by Andreas Klebinger at 2024-05-02T08:18:45-04:00 STM: Remove (unused)coarse grained locking. The STM code had a coarse grained locking mode guarded by #defines that was unused. This commit removes the code. - - - - - 917ef81b by Andreas Klebinger at 2024-05-02T08:18:45-04:00 STM: Be more optimistic when validating in-flight transactions. * Don't lock tvars when performing non-committal validation. * If we encounter a locked tvar don't consider it a failure. This means in-flight validation will only fail if committing at the moment of validation is *guaranteed* to fail. This prevents in-flight validation from failing spuriously if it happens in parallel on multiple threads or parallel to thread comitting. - - - - - 167a56a0 by Alan Zimmerman at 2024-05-02T08:19:22-04:00 EPA: fix span for empty \case(s) In instance SDecide Nat where SZero %~ (SSucc _) = Disproved (\case) Ensure the span for the HsLam covers the full construct. Closes #24748 - - - - - 9bae34d8 by doyougnu at 2024-05-02T15:41:08-04:00 testsuite: expand size testing infrastructure - closes #24191 - adds windows_skip, wasm_skip, wasm_arch, find_so, _find_so - path_from_ghcPkg, collect_size_ghc_pkg, collect_object_size, find_non_inplace functions to testsuite - adds on_windows and req_dynamic_ghc predicate to testsuite The design is to not make the testsuite too smart and simply offload to ghc-pkg for locations of object files and directories. - - - - - b85b1199 by Sylvain Henry at 2024-05-02T15:41:49-04:00 GHCi: support inlining breakpoints (#24712) When a breakpoint is inlined, its context may change (e.g. tyvars in scope). We must take this into account and not used the breakpoint tick index as its sole identifier. Each instance of a breakpoint (even with the same tick index) now gets a different "info" index. We also need to distinguish modules: - tick module: module with the break array (tick counters, status, etc.) - info module: module having the CgBreakInfo (info at occurrence site) - - - - - 649c24b9 by Oleg Grenrus at 2024-05-03T20:45:42-04:00 Expose constructors of SNat, SChar and SSymbol in ghc-internal - - - - - d603f199 by Mikolaj Konarski at 2024-05-03T20:46:19-04:00 Add DCoVarSet to PluginProv (!12037) - - - - - ba480026 by Serge S. Gulin at 2024-05-03T20:47:01-04:00 JS: Enable more efficient packing of string data (fixes #24706) - - - - - be1e60ee by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Track in-scope variables in ruleCheckProgram This small patch fixes #24726, by tracking in-scope variables properly in -drule-check. Not hard to do! - - - - - 58408c77 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Add a couple more HasCallStack constraints in SimpleOpt Just for debugging, no effect on normal code - - - - - 70e245e8 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Add comments to Prep.hs This documentation patch fixes a TODO left over from !12364 - - - - - e5687186 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Use HasDebugCallStack, rather than HasCallStack - - - - - 631cefec by Cheng Shao at 2024-05-03T20:48:17-04:00 driver: always merge objects when possible This patch makes the driver always merge objects with `ld -r` when possible, and only fall back to calling `ar -L` when merge objects command is unavailable. This completely reverts !8887 and !12313, given more fixes in Cabal seems to be needed to avoid breaking certain configurations and the maintainence cost is exceeding the behefits in this case :/ - - - - - 1dacb506 by Ben Gamari at 2024-05-03T20:48:53-04:00 Bump time submodule to 1.14 As requested in #24528. ------------------------- Metric Decrease: ghc_bignum_so rts_so Metric Increase: cabal_syntax_dir rts_so time_dir time_so ------------------------- - - - - - 4941b90e by Ben Gamari at 2024-05-03T20:48:53-04:00 Bump terminfo submodule to current master - - - - - 43d48b44 by Cheng Shao at 2024-05-03T20:49:30-04:00 wasm: use scheduler.postTask() for context switch when available This patch makes use of scheduler.postTask() for JSFFI context switch when it's available. It's a more principled approach than our MessageChannel based setImmediate() implementation, and it's available in latest version of Chromium based browsers. - - - - - 08207501 by Cheng Shao at 2024-05-03T20:50:08-04:00 testsuite: give pre_cmd for mhu-perf 5x time - - - - - bf3d4db0 by Alan Zimmerman at 2024-05-03T20:50:43-04:00 EPA: Preserve comments for pattern synonym sig Closes #24749 - - - - - c49493f2 by Matthew Pickering at 2024-05-04T06:02:57-04:00 tests: Widen acceptance window for dir and so size tests These are testing things which are sometimes out the control of a GHC developer. Therefore we shouldn't fail CI if something about these dependencies change because we can't do anything about it. It is still useful to have these statistics for visualisation in grafana though. Ticket #24759 - - - - - 9562808d by Matthew Pickering at 2024-05-04T06:02:57-04:00 Disable rts_so test It has already manifested large fluctuations and destabilising CI Fixes #24762 - - - - - fc24c5cf by Ryan Scott at 2024-05-04T06:03:33-04:00 unboxedSum{Type,Data}Name: Use GHC.Types as the module Unboxed sum constructors are now defined in the `GHC.Types` module, so if you manually quote an unboxed sum (e.g., `''Sum2#`), you will get a `Name` like: ```hs GHC.Types.Sum2# ``` The `unboxedSumTypeName` function in `template-haskell`, however, mistakenly believes that unboxed sum constructors are defined in `GHC.Prim`, so `unboxedSumTypeName 2` would return an entirely different `Name`: ```hs GHC.Prim.(#|#) ``` This is a problem for Template Haskell users, as it means that they can't be sure which `Name` is the correct one. (Similarly for `unboxedSumDataName`.) This patch fixes the implementations of `unboxedSum{Type,Data}Name` to use `GHC.Types` as the module. For consistency with `unboxedTupleTypeName`, the `unboxedSumTypeName` function now uses the non-punned syntax for unboxed sums (`Sum<N>#`) as the `OccName`. Fixes #24750. - - - - - 7eab4e01 by Alan Zimmerman at 2024-05-04T16:14:55+01:00 EPA: Widen stmtslist to include last semicolon Closes #24754 - - - - - 06f7db40 by Teo Camarasu at 2024-05-05T00:19:38-04:00 doc: Fix type error in hs_try_putmvar example - - - - - af000532 by Moritz Schuler at 2024-05-05T06:30:58-04:00 Fix parsing of module names in CLI arguments closes issue #24732 - - - - - da74e9c9 by Ben Gamari at 2024-05-05T06:31:34-04:00 ghc-platform: Add Setup.hs The Hadrian bootstrapping script relies upon `Setup.hs` to drive its build. Addresses #24761. - - - - - 35d34fde by Alan Zimmerman at 2024-05-05T12:52:40-04:00 EPA: preserve comments in class and data decls Fix checkTyClHdr which was discarding comments. Closes #24755 - - - - - 03c5dfbf by Simon Peyton Jones at 2024-05-05T12:53:15-04:00 Fix a float-out error Ticket #24768 showed that the Simplifier was accidentally destroying a join point. It turned out to be that we were sending a bottoming join point to the top, accidentally abstracting over /other/ join points. Easily fixed. - - - - - adba68e7 by John Ericson at 2024-05-05T19:35:56-04:00 Substitute bindist files with Hadrian not configure The `ghc-toolchain` overhaul will eventually replace all this stuff with something much more cleaned up, but I think it is still worth making this sort of cleanup in the meantime so other untanglings and dead code cleaning can procede. I was able to delete a fair amount of dead code doing this too. `LLVMTarget_CPP` is renamed to / merged with `LLVMTarget` because it wasn't actually turned into a valid CPP identifier. (Original to 1345c7cc42c45e63ab1726a8fd24a7e4d4222467, actually.) Progress on #23966 Co-Authored-By: Sylvain Henry <hsyl20 at gmail.com> - - - - - 18f4ff84 by Alan Zimmerman at 2024-05-05T19:36:32-04:00 EPA: fix mkHsOpTyPV duplicating comments Closes #24753 - - - - - a19201d4 by Matthew Craven at 2024-05-06T19:54:29-04:00 Add test cases for #24664 ...since none are present in the original MR !12463 fixing this issue. - - - - - 46328a49 by Alan Zimmerman at 2024-05-06T19:55:05-04:00 EPA: preserve comments in data decls Closes #24771 - - - - - 3b51995c by Andrei Borzenkov at 2024-05-07T14:39:40-04:00 Rename Solo# data constructor to MkSolo# (#24673) - data Solo# a = (# a #) + data Solo# a = MkSolo# a And `(# foo #)` syntax now becomes just a syntactic sugar for `MkSolo# a`. - - - - - 4d59abf2 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Add the cmm_cpp_is_gcc predicate to the testsuite A future C-- test called T24474-cmm-override-g0 relies on the GCC-specific behaviour of -g3 implying -dD, which, in turn, leads to it emitting #defines past the preprocessing stage. Clang, at least, does not do this, so the test would fail if ran on Clang. As the behaviour here being tested is ``-optCmmP-g3'' undoing effects of the workaround we apply as a fix for bug #24474, and the workaround was for GCC-specific behaviour, the test needs to be marked as fragile on other compilers. - - - - - 25b0b404 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Split out the C-- preprocessor, and make it pass -g0 Previously, C-- was processed with the C preprocessor program. This means that it inherited flags passed via -optc. A flag that is somewhat often passed through -optc is -g. At certain -g levels (>=2), GCC starts emitting defines *after* preprocessing, for the purposes of debug info generation. This is not useful for the C-- compiler, and, in fact, causes lexer errors. We can suppress this effect (safely, if supported) via -g0. As a workaround, in older versions of GCC (<=10), GCC only emitted defines if a certain set of -g*3 flags was passed. Newer versions check the debug level. For the former, we filter out those -g*3 flags and, for the latter, we specify -g0 on top of that. As a compatible and effective solution, this change adds a C-- preprocessor distinct from the C compiler and preprocessor, but that keeps its flags. The command line produced for C-- preprocessing now looks like: $pgmCmmP $optCs_without_g3 $g0_if_supported $optCmmP Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/24474 - - - - - 9b4129a5 by Andreas Klebinger at 2024-05-08T13:24:20-04:00 -fprof-late: Only insert cost centres on functions/non-workfree cafs. They are usually useless and doing so for data values comes with a large compile time/code size overhead. Fixes #24103 - - - - - 259b63d3 by Sebastian Graf at 2024-05-08T13:24:57-04:00 Simplifier: Preserve OccInfo on DataAlt fields when case binder is dead (#24770) See the adjusted `Note [DataAlt occ info]`. This change also has a positive repercussion on `Note [Combine case alts: awkward corner]`. Fixes #24770. We now try not to call `dataConRepStrictness` in `adjustFieldsIdInfo` when all fields are lazy anyway, leading to a 2% ghc/alloc decrease in T9675. Metric Decrease: T9675 - - - - - 31b28cdb by Sebastian Graf at 2024-05-08T13:24:57-04:00 Kill seqRule, discard dead seq# in Prep (#24334) Discarding seq#s in Core land via `seqRule` was problematic; see #24334. So instead we discard certain dead, discardable seq#s in Prep now. See the updated `Note [seq# magic]`. This fixes the symptoms of #24334. - - - - - b2682534 by Rodrigo Mesquita at 2024-05-10T01:47:51-04:00 Document NcgImpl methods Fixes #19914 - - - - - 4d3acbcf by Zejun Wu at 2024-05-10T01:48:28-04:00 Make renamer to be more flexible with parens in the LHS of the rules We used to reject LHS like `(f a) b` in RULES and requires it to be written as `f a b`. It will be handy to allow both as the expression may be more readable with extra parens in some cases when infix operator is involved. Espceially when TemplateHaskell is used, extra parens may be added out of user's control and result in "valid" rules being rejected and there are not always ways to workaround it. Fixes #24621 - - - - - ab840ce6 by Ben Gamari at 2024-05-10T01:49:04-04:00 IPE: Eliminate dependency on Read Instead of encoding the closure type as decimal string we now simply represent it as an integer, eliminating the need for `Read` in `GHC.Internal.InfoProv.Types.peekInfoProv`. Closes #24504. ------------------------- Metric Decrease: T24602_perf_size size_hello_artifact ------------------------- - - - - - a9979f55 by Cheng Shao at 2024-05-10T01:49:43-04:00 testsuite: fix testwsdeque with recent clang This patch fixes compilation of testwsdeque.c with recent versions of clang, which will fail with the error below: ``` testwsdeque.c:95:33: error: warning: format specifies type 'long' but the argument has type 'void *' [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~~ ^ testwsdeque.c:95:39: error: warning: format specifies type 'int' but the argument has type 'StgWord' (aka 'unsigned long') [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~ ^~~ | %lu testwsdeque.c:133:42: error: error: incompatible function pointer types passing 'void (void *)' to parameter of type 'OSThreadProc *' (aka 'void *(*)(void *)') [-Wincompatible-function-pointer-types] 133 | createOSThread(&ids[n], "thief", thief, (void*)(StgWord)n); | ^~~~~ /workspace/ghc/_build/stage1/lib/../lib/x86_64-linux-ghc-9.11.20240502/rts-1.0.2/include/rts/OSThreads.h:193:51: error: note: passing argument to parameter 'startProc' here 193 | OSThreadProc *startProc, void *param); | ^ 2 warnings and 1 error generated. ``` - - - - - c2b33fc9 by Rodrigo Mesquita at 2024-05-10T01:50:20-04:00 Rename pre-processor invocation args Small clean up. Uses proper names for the various groups of arguments that make up the pre-processor invocation. - - - - - 2b1af08b by Cheng Shao at 2024-05-10T01:50:55-04:00 ghc-heap: fix typo in ghc-heap cbits - - - - - fc2d6de1 by Jade at 2024-05-10T21:07:16-04:00 Improve performance of Data.List.sort(By) This patch improves the algorithm to sort lists in base. It does so using two strategies: 1) Use a four-way-merge instead of the 'default' two-way-merge. This is able to save comparisons and allocations. 2) Use `(>) a b` over `compare a b == GT` and allow inlining and specialization. This mainly benefits types with a fast (>). Note that this *may* break instances with a *malformed* Ord instance where `a > b` is *not* equal to `compare a b == GT`. CLC proposal: https://github.com/haskell/core-libraries-committee/issues/236 Fixes #24280 ------------------------- Metric Decrease: MultiLayerModulesTH_Make T10421 T13719 T15164 T18698a T18698b T1969 T9872a T9961 T18730 WWRec T12425 T15703 ------------------------- - - - - - 1012e8aa by Matthew Pickering at 2024-05-10T21:07:52-04:00 Revert "ghcup-metadata: Drop output_name field" This reverts commit ecbf22a6ac397a791204590f94c0afa82e29e79f. This breaks the ghcup metadata generation on the nightly jobs. - - - - - daff1e30 by Jannis at 2024-05-12T13:38:35-04:00 Division by constants optimization - - - - - 413217ba by Andreas Klebinger at 2024-05-12T13:39:11-04:00 Tidy: Add flag to expose unfoldings if they take dictionary arguments. Add the flag `-fexpose-overloaded-unfoldings` to be able to control this behaviour. For ghc's boot libraries file size grew by less than 1% when it was enabled. However I refrained from enabling it by default for now. I've also added a section on specialization more broadly to the users guide. ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot Metric Increase: T12425 T13386 hard_hole_fits ------------------------- - - - - - c5d89412 by Zubin Duggal at 2024-05-13T22:19:53-04:00 Don't store a GlobalRdrEnv in `mi_globals` for GHCi. GHCi only needs the `mi_globals` field for modules imported with :module +*SomeModule. It uses this field to make the top level environment in `SomeModule` available to the repl. By default, only the first target in the command line parameters is "star" loaded into GHCi. Other modules have to be manually "star" loaded into the repl. Storing the top level GlobalRdrEnv for each module is very wasteful, especially given that we will most likely never need most of these environments. Instead we store only the information needed to reconstruct the top level environment in a module, which is the `IfaceTopEnv` data structure, consisting of all import statements as well as all top level symbols defined in the module (not taking export lists into account) When a particular module is "star-loaded" into GHCi (as the first commandline target, or via an explicit `:module +*SomeModule`, we reconstruct the top level environment on demand using the `IfaceTopEnv`. - - - - - d65bf4a2 by Fendor at 2024-05-13T22:20:30-04:00 Add perf regression test for `-fwrite-if-simplified-core` - - - - - 2c0f8ddb by Andrei Borzenkov at 2024-05-13T22:21:07-04:00 Improve pattern to type pattern transformation (23739) `pat_to_type_pat` function now can handle more patterns: - TuplePat - ListPat - LitPat - NPat - ConPat Allowing these new constructors in type patterns significantly increases possible shapes of type patterns without `type` keyword. This patch also changes how lookups in `lookupOccRnConstr` are performed, because we need to fall back into types when we didn't find a constructor on data level to perform `ConPat` to type transformation properly. - - - - - be514bb4 by Cheng Shao at 2024-05-13T22:21:43-04:00 hadrian: fix hadrian building with ghc-9.10.1 - - - - - ad38e954 by Cheng Shao at 2024-05-13T22:21:43-04:00 linters: fix lint-whitespace compilation with ghc-9.10.1 - - - - - a593f284 by Andreas Klebinger at 2024-05-15T07:32:10-04:00 Expand the `inline` rule to look through casts/ticks. Fixes #24808 - - - - - b1e0c313 by Cheng Shao at 2024-05-15T07:32:46-04:00 testsuite: bump PartialDownSweep timeout to 5x on wasm32 - - - - - b2227487 by Fendor at 2024-05-15T17:14:06-04:00 Add Eq and Ord instance to `IfaceType` We add an `Ord` instance so that we can store `IfaceType` in a `Data.Map` container. This is required to deduplicate `IfaceType` while writing `.hi` files to disk. Deduplication has many beneficial consequences to both file size and memory usage, as the deduplication enables implicit sharing of values. See issue #24540 for more motivation. The `Ord` instance would be unnecessary if we used a `TrieMap` instead of `Data.Map` for the deduplication process. While in theory this is clerarly the better option, experiments on the agda code base showed that a `TrieMap` implementation has worse run-time performance characteristics. To the change itself, we mostly derive `Eq` and `Ord`. This requires us to change occurrences of `FastString` with `LexicalFastString`, since `FastString` has no `Ord` instance. We change the definition of `IfLclName` to a newtype of `LexicalFastString`, to make such changes in the future easier. Bump haddock submodule for IfLclName changes - - - - - d368f9a6 by Fendor at 2024-05-15T17:14:06-04:00 Move out LiteralMap to avoid cyclic module dependencies - - - - - 2fcc09fd by Fendor at 2024-05-15T17:14:06-04:00 Add deduplication table for `IfaceType` The type `IfaceType` is a highly redundant, tree-like data structure. While benchmarking, we realised that the high redundancy of `IfaceType` causes high memory consumption in GHCi sessions when byte code is embedded into the `.hi` file via `-fwrite-if-simplified-core` or `-fbyte-code-and-object-code`. Loading such `.hi` files from disk introduces many duplicates of memory expensive values in `IfaceType`, such as `IfaceTyCon`, `IfaceTyConApp`, `IA_Arg` and many more. We improve the memory behaviour of GHCi by adding an additional deduplication table for `IfaceType` to the serialisation of `ModIface`, similar to how we deduplicate `Name`s and `FastString`s. When reading the interface file back, the table allows us to automatically share identical values of `IfaceType`. To provide some numbers, we evaluated this patch on the agda code base. We loaded the full library from the `.hi` files, which contained the embedded core expressions (`-fwrite-if-simplified-core`). Before this patch: * Load time: 11.7 s, 2.5 GB maximum residency. After this patch: * Load time: 7.3 s, 1.7 GB maximum residency. This deduplication has the beneficial side effect to additionally reduce the size of the on-disk interface files tremendously. For example, on agda, we reduce the size of `.hi` files (with `-fwrite-if-simplified-core`): * Before: 101 MB on disk * Now: 24 MB on disk This has even a beneficial side effect on the cabal store. We reduce the size of the store on disk: * Before: 341 MB on disk * Now: 310 MB on disk Note, none of the dependencies have been compiled with `-fwrite-if-simplified-core`, but `IfaceType` occurs in multiple locations in a `ModIface`. We also add IfaceType deduplication table to .hie serialisation and refactor .hie file serialisation to use the same infrastrucutre as `putWithTables`. Bump haddock submodule to accomodate for changes to the deduplication table layout and binary interface. - - - - - 36aa7cf1 by Fendor at 2024-05-15T17:14:06-04:00 Add run-time configurability of `.hi` file compression Introduce the flag `-fwrite-if-compression=<n>` which allows to configure the compression level of writing .hi files. The motivation is that some deduplication operations are too expensive for the average use case. Hence, we introduce multiple compression levels with variable impact on performance, but still reduce the memory residency and `.hi` file size on disk considerably. We introduce three compression levels: * `1`: `Normal` mode. This is the least amount of compression. It deduplicates only `Name` and `FastString`s, and is naturally the fastest compression mode. * `2`: `Safe` mode. It has a noticeable impact on .hi file size and is marginally slower than `Normal` mode. In general, it should be safe to always use `Safe` mode. * `3`: `Full` deduplication mode. Deduplicate as much as we can, resulting in minimal .hi files, but at the cost of additional compilation time. Reading .hi files doesn't need to know the initial compression level, and can always deserialise a `ModIface`, as we write out a byte that indicates the next value has been deduplicated. This allows users to experiment with different compression levels for packages, without recompilation of dependencies. Note, the deduplication also has an additional side effect of reduced memory consumption to implicit sharing of deduplicated elements. See https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for example where that matters. ------------------------- Metric Decrease: MultiLayerModulesDefsGhciWithCore T16875 T21839c T24471 hard_hole_fits libdir ------------------------- - - - - - 1e63a6fb by Matthew Pickering at 2024-05-15T17:14:07-04:00 Introduce regression tests for `.hi` file sizes Add regression tests to track how `-fwrite-if-compression` levels affect the size of `.hi` files. - - - - - 639d742b by M Farkas-Dyck at 2024-05-15T17:14:49-04:00 TTG: ApplicativeStatement exist only in Rn and Tc Co-Authored-By: romes <rodrigo.m.mesquita at gmail.com> - - - - - aa7b336b by Jade at 2024-05-15T23:06:17-04:00 Documentation: Improve documentation for symbols exported from System.IO - - - - - c561de8f by Jade at 2024-05-15T23:06:54-04:00 Improve suggestions for language extensions - When suggesting Language extensions, also suggest Extensions which imply them - Suggest ExplicitForAll and GADTSyntax instead of more specific extensions - Rephrase suggestion to include the term 'Extension' - Also moves some flag specific definitions out of Session.hs into Flags.hs (#24478) Fixes: #24477 Fixes: #24448 Fixes: #10893 - - - - - 4c7ae2a1 by Andreas Klebinger at 2024-05-15T23:07:30-04:00 Testsuite: Check if llvm assembler is available for have_llvm - - - - - bc672166 by Torsten Schmits at 2024-05-15T23:08:06-04:00 refactor quadratic search in warnMissingHomeModules - - - - - 7875e8cb by Torsten Schmits at 2024-05-15T23:08:06-04:00 add test that runs MakeDepend on thousands of modules - - - - - b84b91f5 by Adam Gundry at 2024-05-16T15:32:06-04:00 Representation-polymorphic HasField (fixes #22156) This generalises the HasField class to support representation polymorphism, so that instead of type HasField :: forall {k} . k -> Type -> Type -> Constraint we have type HasField :: forall {k} {r_rep} {a_rep} . k -> TYPE r_rep -> TYPE a_rep -> Constraint - - - - - 05285090 by Matthew Pickering at 2024-05-16T15:32:43-04:00 Bump os-string submodule to 2.0.2.2 Closes #24786 - - - - - 886ab43a by Cheng Shao at 2024-05-17T01:34:50-04:00 rts: do not prefetch mark_closure bdescr in non-moving gc when ASSERTS_ENABLED This commit fixes a small an oversight in !12148: the prefetch logic in non-moving GC may trap in debug RTS because it calls Bdescr() for mark_closure which may be a static one. It's fine in non-debug RTS because even invalid bdescr addresses are prefetched, they will not cause segfaults, so this commit implements the most straightforward fix: don't prefetch mark_closure bdescr when assertions are enabled. - - - - - b38dcf39 by Teo Camarasu at 2024-05-17T01:34:50-04:00 rts: Allocate non-moving segments with megablocks Non-moving segments are 8 blocks long and need to be aligned. Previously we serviced allocations by grabbing 15 blocks, finding an aligned 8 block group in it and returning the rest. This proved to lead to high levels of fragmentation as a de-allocating a segment caused an 8 block gap to form, and this could not be reused for allocation. This patch introduces a segment allocator based around using entire megablocks to service segment allocations in bulk. When there are no free segments, we grab an entire megablock and fill it with aligned segments. As the megablock is free, we can easily guarantee alignment. Any unused segments are placed on a free list. It only makes sense to free segments in bulk when all of the segments in a megablock are freeable. After sweeping, we grab the free list, sort it, and find all groups of segments where they cover the megablock and free them. This introduces a period of time when free segments are not available to the mutator, but the risk that this would lead to excessive allocation is low. Right after sweep, we should have an abundance of partially full segments, and this pruning step is relatively quick. In implementing this we drop the logic that kept NONMOVING_MAX_FREE segments on the free list. We also introduce an eventlog event to log the amount of pruned/retained free segments. See Note [Segment allocation strategy] Resolves #24150 ------------------------- Metric Decrease: T13253 T19695 ------------------------- - - - - - 710665bd by Cheng Shao at 2024-05-17T01:35:30-04:00 rts: fix I/O manager compilation errors for win32 target This patch fixes I/O manager compilation errors for win32 target discovered when cross-compiling to win32 using recent clang: ``` rts/win32/ThrIOManager.c:117:7: error: error: call to undeclared function 'is_io_mng_native_p'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 117 | if (is_io_mng_native_p ()) { | ^ | 117 | if (is_io_mng_native_p ()) { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/fs.c:143:28: error: error: a function declaration without a prototype is deprecated in all versions of C [-Werror,-Wstrict-prototypes] 143 | int setErrNoFromWin32Error () { | ^ | void | 143 | int setErrNoFromWin32Error () { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:227:9: error: error: call to undeclared function 'interruptIOManagerEvent'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 227 | interruptIOManagerEvent (); | ^ | 227 | interruptIOManagerEvent (); | ^ rts/win32/ConsoleHandler.c:227:9: error: note: did you mean 'getIOManagerEvent'? | 227 | interruptIOManagerEvent (); | ^ rts/include/rts/IOInterface.h:27:10: error: note: 'getIOManagerEvent' declared here 27 | void * getIOManagerEvent (void); | ^ | 27 | void * getIOManagerEvent (void); | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:196:9: error: error: call to undeclared function 'setThreadLabel'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/win32/ConsoleHandler.c:196:9: error: note: did you mean 'postThreadLabel'? | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/eventlog/EventLog.h:118:6: error: note: 'postThreadLabel' declared here 118 | void postThreadLabel(Capability *cap, | ^ | 118 | void postThreadLabel(Capability *cap, | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) ``` - - - - - 28b9cee0 by Rodrigo Mesquita at 2024-05-17T01:36:05-04:00 configure: Check C99-compat for Cmm preprocessor Fixes #24815 - - - - - 8927e0c3 by Andreas Klebinger at 2024-05-17T01:36:41-04:00 Ensure `tcHasFixedRuntimeRep (# #)` returns True. - - - - - 04179044 by doyougnu at 2024-05-17T09:00:32-04:00 testsuite: make find_so regex less general Closes #24759 Background. In MR !12372 we began tracking shared object files and directories sizes for dependencies. However, this broke release builds because release builds alter the filenames swapping "in-place" for a hash. This was not considered in the MR and thus broke release pipelines. Furthermore, the rts_so test was found to be wildly varying and was therefore disabled in !12561. This commit fixes both of these issues: - fix the rts_so test by making the regex less general, now the rts_so test and all other foo.so tests must match "libHS<some-lib>-<version>-<hash|'in-place>-<ghc>". This prevents the rts_so test from accidentally matching different rts variants such as rts_threaded, which was the cause of the wild swings after !12372. - add logic to match either a hash or the string in-place. This should make the find_so function build agnostic. - - - - - 0962b50d by Andreas Klebinger at 2024-05-17T09:01:08-04:00 TagAnalysis: Treat all bottom ids as tagged during analysis. Ticket #24806 showed that we also need to treat dead end thunks as tagged during the analysis. - - - - - 7eb9f184 by Ben Gamari at 2024-05-17T11:23:37-04:00 Remove haddock submodule In preparation for merge into the GHC, as proposed in #23178. - - - - - 47b14dcc by Fendor at 2024-05-17T11:28:17-04:00 Adapt to `IfLclName` newtype changes (cherry picked from commit a711607e29b925f3d69e27c5fde4ba655c711ff1) - - - - - 6cc6681d by Fendor at 2024-05-17T11:28:17-04:00 Add IfaceType deduplication table to interface file serialisation Although we do not really need it in the interface file serialisation, as the deserialisation uses `getWithUserData`, we need to mirror the structure `getWithUserData` expects. Thus, we write essentially an empty `IfaceType` table at the end of the file, as the interface file doesn't reference `IfaceType`. (cherry picked from commit c9bc29c6a708483d2abc3d8ec9262510ce87ca61) - - - - - b9721206 by Ben Gamari at 2024-05-17T11:30:22-04:00 ghc-tags.yaml: Initial commit - - - - - 074e7d8f by Ben Gamari at 2024-05-17T11:31:29-04:00 fourmolu: Add configuration - - - - - 151b1736 by Ben Gamari at 2024-05-17T11:32:52-04:00 Makefile: Rework for use by haddock developers Previously the Makefile was present only for GHC's old make-based build system. Now since the make-based build system is gone we can use it for more useful ends. - - - - - a7dcf13b by Ben Gamari at 2024-05-17T11:36:14-04:00 Reformat with fourmolu Using previously-added configuration and `fourmolu -i .` Note that we exclude the test-cases (`./{hoogle,html-hypsrc,latex}-test`) as they are sensitive to formatting. - - - - - 0ea6017b by Ben Gamari at 2024-05-17T11:40:04-04:00 Add 'utils/haddock/' from commit 'a7dcf13bfbb97b20e75cc8ce650e2bb628db4660' git-subtree-dir: utils/haddock git-subtree-mainline: 7eb9f1849b1c72a1c61dee88462b4244550406f3 git-subtree-split: a7dcf13bfbb97b20e75cc8ce650e2bb628db4660 - - - - - aba1d304 by Hécate Moonlight at 2024-05-17T11:40:48-04:00 Add exceptions to the dangling notes list - - - - - 527bfbfb by Hécate Moonlight at 2024-05-17T11:40:52-04:00 Add haddock to the whitespace lint ignore list - - - - - 43274677 by Ben Gamari at 2024-05-17T11:41:20-04:00 git-blame-ignore-revs: Ignore haddock reformatting - - - - - 0e679e37 by Fendor at 2024-05-18T00:27:24-04:00 Pass cpp options to the CC builder in hadrian - - - - - bb40244e by Sylvain Henry at 2024-05-18T00:28:06-04:00 JS: fix allocation constant (fix #24746) - - - - - 646d30ab by Jade at 2024-05-18T19:23:31+02:00 Add highlighting for inline-code snippets in haddock - - - - - 64459a3e by Hécate Moonlight at 2024-05-19T08:42:27-04:00 haddock: Add a .readthedocs.yml file for online documentation - - - - - 7d3d9bbf by Serge S. Gulin at 2024-05-19T18:47:05+00:00 Unicode: General Category size test (related #24789) Added trivial size performance test which involves unicode general category usage via `read`. The `read` itself uses general category to detect spaces. The purpose for this test is to measure outcome of applying improvements at General Category representation in code discussed at #24789. - - - - - 8e04efcf by Alan Zimmerman at 2024-05-19T21:29:34-04:00 EPA: Remove redundant code Remove unused epAnnAnns function various cases for showAstData that no longer exist - - - - - 071d7a1e by Rodrigo Mesquita at 2024-05-20T10:55:16-04:00 Improve docs on closed type families in hs-boots Fixes #24776 - - - - - d9e2c119 by Torsten Schmits at 2024-05-20T10:55:52-04:00 Use default deviation for large-project test This new performance test has the purpose of detecting regressions in complexity in relation to the number of modules in a project, so 1% deviation is way too small to avoid false positives. - - - - - 20b0136a by Ben Gamari at 2024-05-22T00:31:39-04:00 ghcup-metadata: Various fixes from 9.10.1 Use Debian 12/x86-64, Debian 10/aarch64, and Debian 11/aarch64 bindists where possible. - - - - - 6838a7c3 by Sylvain Henry at 2024-05-22T00:32:23-04:00 Reverse arguments to stgCallocBytes (fix #24828) - - - - - f50f46c3 by Fendor at 2024-05-22T00:32:59-04:00 Add log messages for Iface serialisation compression level Fix the label of the number of 'IfaceType' entries in the log message. Add log message for the compression level that is used to serialise a an interface file. Adds `Outputable` instance for 'CompressionIFace'. - - - - - 3bad5d55 by Hécate Moonlight at 2024-05-22T00:33:40-04:00 base: Update doctests outputs ghc-internal: Update doctests outputs - - - - - 9317c6fb by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix the testsuites of the haddock-library - Apply all the metadata revisions from Hackage to the cabal file. - Fix the `ParserSpec.hs` file in the `spec` testsuite of haddock-library. - Make `CHANGES.md` an extra-doc-file instead of an extra-source-file. - - - - - 54073b02 by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix parser of @since pragma The testsuite contained tests for annotations of the form `@since foo-bar-0.5.0`, but the parser was written incorrectly. - - - - - ede6ede3 by Matthew Pickering at 2024-05-22T00:34:57-04:00 Fix nightly pages job It seems likely broken by 9f99126a which moved `index.html` from the root folder into `docs/` folder. Fixes #24840 - - - - - b7bcf729 by Cheng Shao at 2024-05-22T00:35:32-04:00 autoconf: remove unused context diff check This patch removes redundant autoconf check for the context diff program given it isn't actually been used anywhere, especially since make removal. - - - - - ea2fe66e by Hécate Moonlight at 2024-05-22T00:36:13-04:00 haddock: Rework the contributing guide - - - - - 0f302a94 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 haddock: Add module relationships diagrams of haddock-api and haddock-library - - - - - d1a9f34f by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add instructions - - - - - b880ee80 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add SVG outputs - - - - - 6d7e6ad8 by Ben Gamari at 2024-05-22T13:40:05-04:00 rts: Fix size of StgOrigThunkInfo frames Previously the entry code of the `stg_orig_thunk` frame failed to account for the size of the profiling header as it hard-coded the frame size. Fix this. Fixes #24809. - - - - - c645fe40 by Fendor at 2024-05-22T13:40:05-04:00 Add regression test T24809 for stg_orig_thunk_info_frame size - - - - - 4181aa40 by Andreas Klebinger at 2024-05-22T13:40:42-04:00 bindists: Check for existence of share folder before trying to copy it. This folder isn't distributed in windows bindists A lack of doing so resulted us copying loads of files twice. - - - - - d216510e by Matthew Pickering at 2024-05-22T13:40:42-04:00 Remove ad-hoc installation of mingw toolchain in relocatable bindists This reverts 616ac30026e8dd7d2ebb98d92dde071eedf5d951 The choice about whether to install mingw is taken in the installation makefile. This is also broken on non-windows systems. The actual issue was the EnableDistroToolchain variable wasn't declared in mk/config.mk and therefore the check to install mingw was failing. - - - - - 7b4c1998 by Cheng Shao at 2024-05-22T21:52:52-04:00 testsuite: fix T17920 for wasm backend T17920 was marked as fragile on wasm before; it can be trivially fixed by avoiding calling variadic printf() in cmm. - - - - - c739383b by Cheng Shao at 2024-05-22T21:53:29-04:00 testsuite: bump T22744 timeout to 5x - - - - - c4c6d714 by Cheng Shao at 2024-05-22T21:54:06-04:00 testsuite: don't attempt to detect host cpu features when testing cross ghc The testsuite driver CPU feature detection logic only detects host CPU and only makes sense when we are not testing a cross GHC. - - - - - 3d9e4ce6 by Simon Peyton Jones at 2024-05-22T21:54:43-04:00 Better skolemisation As #24810 showed, it is (a little) better to skolemise en-bloc, so that Note [Let-bound skolems] fires more often. See Note [Skolemisation en bloc] in GHC.Tc.Utils.Instantiate. - - - - - a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00 Add missing parenthesizePat in cvtp We need to ensure that the output of `cvtp` is parenthesized (at precedence `sigPrec`) so that any pattern signatures with a surrounding pattern signature can parse correctly. Fixes #24837. - - - - - 4bb2a7cc by Hécate Moonlight at 2024-05-22T21:55:59-04:00 [base] Document the memory overhead of ByteArray Add a diagram that shows the constituent parts of a ByteArray and their memory overhead. - - - - - 8b2a016a by Hécate Moonlight at 2024-05-22T21:56:38-04:00 Haddock: Add MR template for Haddock - - - - - ead75532 by Peter Trommler at 2024-05-23T02:28:05-04:00 PPC: Support ELF v2 on powerpc64 big-endian Detect ELF v2 on PowerPC 64-bit systems. Check for `_CALL_ELF` preprocessor macro. Fixes #21191 - - - - - 9d4c10f2 by Hécate Kleidukos at 2024-05-23T02:28:44-04:00 gitlab: Add @Kleidukos to CODEOWNERS for utils/haddock - - - - - 28e64170 by Preetham Gujjula at 2024-05-23T07:20:48-04:00 haddock: Add cabal-fmt to tools for `make style` - - - - - 00126a89 by Andrei Borzenkov at 2024-05-23T07:21:24-04:00 haddock: fix verbosity option parsing - - - - - a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00 base: specify tie-breaking behavior of min, max, and related list/Foldable functions - - - - - bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00 cmm: add word <-> double/float bitcast - closes: #25331 This is the last step in the project plan described in #25331. This commit: - adds bitcast operands for x86_64, LLVM, aarch64 - For PPC and i386 we resort to using the cmm implementations - renames conversion MachOps from Conv to Round|Truncate - - - - - f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor Some functions in StgToByteCode were filtering out void arguments. However, StgToByteCode is called after unarisation: the void arguments should have been removed earlier. Instead of filtering out, we assert that the args are non-void. - - - - - 03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor `layoutNativeCall` was always called with a `primRepCmmType platform` callback. Hence we can put it inside of `layoutNativeCall` rather than repeat it. - - - - - 27c430f3 by David Binder at 2024-05-24T07:52:38-04:00 haddock: Remove compatibility shims for GHC < 8.4 from haddock-library - - - - - 8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00 compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs This patch makes the STG->Cmm backend avoid saving foreign call target to local when there are no caller-save GlobalRegs. Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a foreign call, we unconditionally save the foreign call target to a temporary local first, then rely on cmmSink to clean it up later, which only happens with -fcmm-sink (implied by -O) and not in unoptimized code. And this is troublesome for the wasm backend NCG, which needs to infer a foreign call target symbol's type signature from the Cmm call site. Previously, the NCG has been emitting incorrect type signatures for unoptimized code, which happens to work with `wasm-ld` most of the time, but this is never future-proof against upstream toolchain updates, and it causes horrible breakages when LTO objects are included in linker input. Hence this patch. - - - - - 986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00 testsuite: add callee-no-local regression test - - - - - 52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00 Fix HasCallStack leftovers from !12514 / #24726 - - - - - c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00 user_guide: Fix typo in MultiWayIf chapter Close #24829 - - - - - bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - 1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Fix changelog reference to setBacktraceMechanismState (cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d) - - - - - 43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00 Float/double unboxed literal support for HexFloatLiterals (fix #22155) - - - - - 4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00 Improve test labels for binary interface file size tests Test labels for binary interface file sizes are hard to read and overly verbose at the same time. Extend the name for the metric title, but shorten it in the actual comparison table. - - - - - 14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00 Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present" This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa. - - - - - f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00 Fix default hyperlinked sources pattern Previously this didn't include the `%M` token which manifested as broken links to the hyperlinked sources of reexports of declarations defined in other packages. Fixes haddock#1628. (cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36) - - - - - 42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00 Make DocPaths a proper data type (cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c) - - - - - 53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00 haddock: Bump version to 2.30 (cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602) - - - - - e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00 haddock-api: allow base 4.20 and ghc 9.11 - - - - - e294f7a2 by PHO at 2024-05-24T12:17:55-04:00 Add a flag "threaded" for building haddock with the threaded RTS GHC isn't guaranteed to have a threaded RTS. There should be a way to build it with the vanilla one. (cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d) - - - - - 51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00 Update ticky counter event docs. Add the info about the info table address and json fields. Fixes #23200 - - - - - 98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00 Export extractPromotedList (#24866) This can be useful in plugins. - - - - - 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - e41c4ac1 by Vladislav Zavialov at 2024-06-07T17:02:06+03:00 WIP: Types in terms - - - - - 70b663cc by Vladislav Zavialov at 2024-06-07T17:02:42+03:00 WIP: -Wview-pattern-signatures - - - - - 30 changed files: - + .git-blame-ignore-revs - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - + .gitlab/merge_request_templates/Haddock.md - .gitlab/rel_eng/default.nix - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/README.mkd - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - + .gitlab/rel_eng/recompress-all - .gitlab/rel_eng/upload.sh - .gitmodules - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/PrimOps.hs-boot - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/Types/Prim.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Config.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/471b7bc75b2326a367bd8beada0768e5fc53b3f3...70b663cc6c08194c70ba9c7c0f2fd89e1088be19 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/471b7bc75b2326a367bd8beada0768e5fc53b3f3...70b663cc6c08194c70ba9c7c0f2fd89e1088be19 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 15:25:24 2024 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Fri, 07 Jun 2024 11:25:24 -0400 Subject: [Git][ghc/ghc][wip/expansions-appdo] 80 commits: template-haskell: Move wired-ins to ghc-internal Message-ID: <66632664bdec2_1b2a633fc2c89945f@gitlab.mail> Apoorv Ingle pushed to branch wip/expansions-appdo at Glasgow Haskell Compiler / GHC Commits: 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 4d2c7110 by Apoorv Ingle at 2024-06-06T12:16:04-05:00 Make ApplicativeDo work with HsExpansions testcase added: T24406 Issues Fixed: #24406, #16135 Code Changes: - Remove `XStmtLR GhcTc` as `XStmtLR GhcRn` is now compiled to `HsExpr GhcTc` - The expanded statements are guided by `GHC.Hs.Expr.TcFunInfo` which is used to decide if the `XExpr GhcRn` is to be typechecked using `tcApp` or `tcExpr` - - - - - 4c281e74 by Apoorv Ingle at 2024-06-07T10:23:52-05:00 remove ctx debugger - - - - - 30 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCon.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0dd8fb6b8ed90ca35e8fc9f3b1f9d1b186e18d7e...4c281e745b0270b1dc71641c5010b56cb373e0fc -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0dd8fb6b8ed90ca35e8fc9f3b1f9d1b186e18d7e...4c281e745b0270b1dc71641c5010b56cb373e0fc You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 15:35:57 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 07 Jun 2024 11:35:57 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Improve haddocks of Language.Haskell.Syntax.Pat.Pat Message-ID: <666328ddcf508_1b2a63690fe8102865@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 29951e67 by Sylvain Henry at 2024-06-07T11:35:12-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 04b08897 by Sylvain Henry at 2024-06-07T11:35:12-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 0aa54bc5 by Cheng Shao at 2024-06-07T11:35:12-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - 7 changed files: - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/Driver/Config/StgToCmm.hs - compiler/GHC/StgToCmm/Config.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/Language/Haskell/Syntax/Pat.hs - libraries/base/tests/all.T - testsuite/tests/driver/objc/all.T Changes: ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -94,12 +94,6 @@ is32BitPlatform = do platform <- getPlatform return $ target32Bit platform -expect32BitPlatform :: SDoc -> NatM () -expect32BitPlatform doc = do - is32Bit <- is32BitPlatform - when (not is32Bit) $ - pprPanic "Expecting 32-bit platform" doc - sse2Enabled :: NatM Bool sse2Enabled = do config <- getConfig @@ -2475,35 +2469,10 @@ genSimplePrim bid MO_F64_Acosh [dst] [src] = genLibCCall bid genSimplePrim bid MO_F64_Atanh [dst] [src] = genLibCCall bid (fsLit "atanh") [dst] [src] genSimplePrim bid MO_SuspendThread [tok] [rs,i] = genRTSCCall bid (fsLit "suspendThread") [tok] [rs,i] genSimplePrim bid MO_ResumeThread [rs] [tok] = genRTSCCall bid (fsLit "resumeThread") [rs] [tok] -genSimplePrim _ MO_I64_ToI [dst] [src] = genInt64ToInt dst src -genSimplePrim _ MO_I64_FromI [dst] [src] = genIntToInt64 dst src -genSimplePrim _ MO_W64_ToW [dst] [src] = genWord64ToWord dst src -genSimplePrim _ MO_W64_FromW [dst] [src] = genWordToWord64 dst src -genSimplePrim _ MO_x64_Neg [dst] [src] = genNeg64 dst src -genSimplePrim _ MO_x64_Add [dst] [x,y] = genAdd64 dst x y -genSimplePrim _ MO_x64_Sub [dst] [x,y] = genSub64 dst x y -genSimplePrim bid MO_x64_Mul [dst] [x,y] = genPrimCCall bid (fsLit "hs_mul64") [dst] [x,y] genSimplePrim bid MO_I64_Quot [dst] [x,y] = genPrimCCall bid (fsLit "hs_quotInt64") [dst] [x,y] genSimplePrim bid MO_I64_Rem [dst] [x,y] = genPrimCCall bid (fsLit "hs_remInt64") [dst] [x,y] genSimplePrim bid MO_W64_Quot [dst] [x,y] = genPrimCCall bid (fsLit "hs_quotWord64") [dst] [x,y] genSimplePrim bid MO_W64_Rem [dst] [x,y] = genPrimCCall bid (fsLit "hs_remWord64") [dst] [x,y] -genSimplePrim _ MO_x64_And [dst] [x,y] = genAnd64 dst x y -genSimplePrim _ MO_x64_Or [dst] [x,y] = genOr64 dst x y -genSimplePrim _ MO_x64_Xor [dst] [x,y] = genXor64 dst x y -genSimplePrim _ MO_x64_Not [dst] [src] = genNot64 dst src -genSimplePrim bid MO_x64_Shl [dst] [x,n] = genPrimCCall bid (fsLit "hs_uncheckedShiftL64") [dst] [x,n] -genSimplePrim bid MO_I64_Shr [dst] [x,n] = genPrimCCall bid (fsLit "hs_uncheckedIShiftRA64") [dst] [x,n] -genSimplePrim bid MO_W64_Shr [dst] [x,n] = genPrimCCall bid (fsLit "hs_uncheckedShiftRL64") [dst] [x,n] -genSimplePrim _ MO_x64_Eq [dst] [x,y] = genEq64 dst x y -genSimplePrim _ MO_x64_Ne [dst] [x,y] = genNe64 dst x y -genSimplePrim _ MO_I64_Ge [dst] [x,y] = genGeInt64 dst x y -genSimplePrim _ MO_I64_Gt [dst] [x,y] = genGtInt64 dst x y -genSimplePrim _ MO_I64_Le [dst] [x,y] = genLeInt64 dst x y -genSimplePrim _ MO_I64_Lt [dst] [x,y] = genLtInt64 dst x y -genSimplePrim _ MO_W64_Ge [dst] [x,y] = genGeWord64 dst x y -genSimplePrim _ MO_W64_Gt [dst] [x,y] = genGtWord64 dst x y -genSimplePrim _ MO_W64_Le [dst] [x,y] = genLeWord64 dst x y -genSimplePrim _ MO_W64_Lt [dst] [x,y] = genLtWord64 dst x y genSimplePrim _ op dst args = do platform <- ncgPlatform <$> getConfig pprPanic "genSimplePrim: unhandled primop" (ppr (pprCallishMachOp op, dst, fmap (pdoc platform) args)) @@ -4462,231 +4431,3 @@ genQuotRem width signed res_q res_r m_arg_x_high arg_x_low arg_y = do toOL [instr format y_reg, MOV format (OpReg rax) (OpReg reg_q), MOV format (OpReg rdx) (OpReg reg_r)] - - ----------------------------------------------------------------------------- --- The following functions implement certain 64-bit MachOps inline for 32-bit --- architectures. On 64-bit architectures, those MachOps aren't supported and --- calling these functions for a 64-bit target platform is considered an error --- (hence the use of `expect32BitPlatform`). --- --- On 64-bit platforms, generic MachOps should be used instead of these 64-bit --- specific ones (e.g. use MO_Add instead of MO_x64_Add). This MachOp selection --- is done by StgToCmm. - -genInt64ToInt :: LocalReg -> CmmExpr -> NatM InstrBlock -genInt64ToInt dst src = do - expect32BitPlatform (text "genInt64ToInt") - RegCode64 code _src_hi src_lo <- iselExpr64 src - let dst_r = getLocalRegReg dst - pure $ code `snocOL` MOV II32 (OpReg src_lo) (OpReg dst_r) - -genWord64ToWord :: LocalReg -> CmmExpr -> NatM InstrBlock -genWord64ToWord dst src = do - expect32BitPlatform (text "genWord64ToWord") - RegCode64 code _src_hi src_lo <- iselExpr64 src - let dst_r = getLocalRegReg dst - pure $ code `snocOL` MOV II32 (OpReg src_lo) (OpReg dst_r) - -genIntToInt64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genIntToInt64 dst src = do - expect32BitPlatform (text "genIntToInt64") - let Reg64 dst_hi dst_lo = localReg64 dst - src_code <- getAnyReg src - pure $ src_code rax `appOL` toOL - [ CLTD II32 -- sign extend EAX in EDX:EAX - , MOV II32 (OpReg rax) (OpReg dst_lo) - , MOV II32 (OpReg rdx) (OpReg dst_hi) - ] - -genWordToWord64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genWordToWord64 dst src = do - expect32BitPlatform (text "genWordToWord64") - let Reg64 dst_hi dst_lo = localReg64 dst - src_code <- getAnyReg src - pure $ src_code dst_lo - `snocOL` XOR II32 (OpReg dst_hi) (OpReg dst_hi) - -genNeg64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genNeg64 dst src = do - expect32BitPlatform (text "genNeg64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 code src_hi src_lo <- iselExpr64 src - pure $ code `appOL` toOL - [ MOV II32 (OpReg src_lo) (OpReg dst_lo) - , MOV II32 (OpReg src_hi) (OpReg dst_hi) - , NEGI II32 (OpReg dst_lo) - , ADC II32 (OpImm (ImmInt 0)) (OpReg dst_hi) - , NEGI II32 (OpReg dst_hi) - ] - -genAdd64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genAdd64 dst x y = do - expect32BitPlatform (text "genAdd64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , ADD II32 (OpReg y_lo) (OpReg dst_lo) - , ADC II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genSub64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genSub64 dst x y = do - expect32BitPlatform (text "genSub64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , SUB II32 (OpReg y_lo) (OpReg dst_lo) - , SBB II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genAnd64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genAnd64 dst x y = do - expect32BitPlatform (text "genAnd64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , AND II32 (OpReg y_lo) (OpReg dst_lo) - , AND II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genOr64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genOr64 dst x y = do - expect32BitPlatform (text "genOr64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , OR II32 (OpReg y_lo) (OpReg dst_lo) - , OR II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genXor64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genXor64 dst x y = do - expect32BitPlatform (text "genXor64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , XOR II32 (OpReg y_lo) (OpReg dst_lo) - , XOR II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genNot64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genNot64 dst src = do - expect32BitPlatform (text "genNot64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 src_code src_hi src_lo <- iselExpr64 src - pure $ src_code `appOL` toOL - [ MOV II32 (OpReg src_lo) (OpReg dst_lo) - , MOV II32 (OpReg src_hi) (OpReg dst_hi) - , NOT II32 (OpReg dst_lo) - , NOT II32 (OpReg dst_hi) - ] - -genEq64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genEq64 dst x y = do - expect32BitPlatform (text "genEq64") - let dst_r = getLocalRegReg dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - Reg64 tmp_hi tmp_lo <- getNewReg64 - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg tmp_lo) - , MOV II32 (OpReg x_hi) (OpReg tmp_hi) - , XOR II32 (OpReg y_lo) (OpReg tmp_lo) - , XOR II32 (OpReg y_hi) (OpReg tmp_hi) - , OR II32 (OpReg tmp_lo) (OpReg tmp_hi) - , SETCC EQQ (OpReg dst_r) - , MOVZxL II8 (OpReg dst_r) (OpReg dst_r) - ] - -genNe64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genNe64 dst x y = do - expect32BitPlatform (text "genNe64") - let dst_r = getLocalRegReg dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - Reg64 tmp_hi tmp_lo <- getNewReg64 - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg tmp_lo) - , MOV II32 (OpReg x_hi) (OpReg tmp_hi) - , XOR II32 (OpReg y_lo) (OpReg tmp_lo) - , XOR II32 (OpReg y_hi) (OpReg tmp_hi) - , OR II32 (OpReg tmp_lo) (OpReg tmp_hi) - , SETCC NE (OpReg dst_r) - , MOVZxL II8 (OpReg dst_r) (OpReg dst_r) - ] - -genGtWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGtWord64 dst x y = do - expect32BitPlatform (text "genGtWord64") - genPred64 LU dst y x - -genLtWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLtWord64 dst x y = do - expect32BitPlatform (text "genLtWord64") - genPred64 LU dst x y - -genGeWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGeWord64 dst x y = do - expect32BitPlatform (text "genGeWord64") - genPred64 GEU dst x y - -genLeWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLeWord64 dst x y = do - expect32BitPlatform (text "genLeWord64") - genPred64 GEU dst y x - -genGtInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGtInt64 dst x y = do - expect32BitPlatform (text "genGtInt64") - genPred64 LTT dst y x - -genLtInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLtInt64 dst x y = do - expect32BitPlatform (text "genLtInt64") - genPred64 LTT dst x y - -genGeInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGeInt64 dst x y = do - expect32BitPlatform (text "genGeInt64") - genPred64 GE dst x y - -genLeInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLeInt64 dst x y = do - expect32BitPlatform (text "genLeInt64") - genPred64 GE dst y x - -genPred64 :: Cond -> LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genPred64 cond dst x y = do - -- we can only rely on CF/SF/OF flags! - -- Not on ZF, which doesn't take into account the lower parts. - massert (cond `elem` [LU,GEU,LTT,GE]) - - let dst_r = getLocalRegReg dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - -- Basically we perform a subtraction with borrow. - -- As we don't need to result, we can use CMP instead of SUB for the low part - -- (it sets the borrow flag just like SUB does) - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_hi) (OpReg dst_r) - , CMP II32 (OpReg y_lo) (OpReg x_lo) - , SBB II32 (OpReg y_hi) (OpReg dst_r) - , SETCC cond (OpReg dst_r) - , MOVZxL II8 (OpReg dst_r) (OpReg dst_r) - ] ===================================== compiler/GHC/Driver/Config/StgToCmm.hs ===================================== @@ -53,9 +53,12 @@ initStgToCmmConfig dflags mod = StgToCmmConfig , stgToCmmExtDynRefs = gopt Opt_ExternalDynamicRefs dflags , stgToCmmDoBoundsCheck = gopt Opt_DoBoundsChecking dflags , stgToCmmDoTagCheck = gopt Opt_DoTagInferenceChecks dflags - -- backend flags - , stgToCmmAllowBigArith = not ncg || platformArch platform == ArchWasm32 || platformArch platform == ArchX86 - , stgToCmmAllowBigQuot = not ncg || platformArch platform == ArchWasm32 + + -- backend flags: + + -- LLVM, C, and some 32-bit NCG backends can also handle some 64-bit primops + , stgToCmmAllowArith64 = w64 || not ncg || platformArch platform == ArchWasm32 || platformArch platform == ArchX86 + , stgToCmmAllowQuot64 = w64 || not ncg || platformArch platform == ArchWasm32 , stgToCmmAllowQuotRemInstr = ncg && (x86ish || ppc) , stgToCmmAllowQuotRem2 = (ncg && (x86ish || ppc)) || llvm , stgToCmmAllowExtendedAddSubInstrs = (ncg && (x86ish || ppc)) || llvm @@ -90,6 +93,7 @@ initStgToCmmConfig dflags mod = StgToCmmConfig } where profile = targetProfile dflags platform = profilePlatform profile bk_end = backend dflags + w64 = platformWordSize platform == PW8 b_blob = if not ncg then Nothing else binBlobThreshold dflags (ncg, llvm) = case backendPrimitiveImplementation bk_end of GenericPrimitives -> (False, False) ===================================== compiler/GHC/StgToCmm/Config.hs ===================================== @@ -64,8 +64,8 @@ data StgToCmmConfig = StgToCmmConfig -- or not , stgToCmmDoTagCheck :: !Bool -- ^ Verify tag inference predictions. ------------------------------ Backend Flags ---------------------------------- - , stgToCmmAllowBigArith :: !Bool -- ^ Allowed to emit larger than native size arithmetic (only LLVM and C backends) - , stgToCmmAllowBigQuot :: !Bool -- ^ Allowed to emit larger than native size division operations + , stgToCmmAllowArith64 :: !Bool -- ^ Allowed to emit 64-bit arithmetic operations + , stgToCmmAllowQuot64 :: !Bool -- ^ Allowed to emit 64-bit division operations , stgToCmmAllowQuotRemInstr :: !Bool -- ^ Allowed to generate QuotRem instructions , stgToCmmAllowQuotRem2 :: !Bool -- ^ Allowed to generate QuotRem , stgToCmmAllowExtendedAddSubInstrs :: !Bool -- ^ Allowed to generate AddWordC, SubWordC, Add2, etc. ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -334,7 +334,7 @@ emitPrimOp cfg primop = StableNameToIntOp -> \[arg] -> opIntoRegs $ \[res] -> emitAssign (CmmLocal res) (cmmLoadIndexW platform arg (fixedHdrSizeW profile) (bWord platform)) - EqStablePtrOp -> \args -> opTranslate args (mo_wordEq platform) + EqStablePtrOp -> opTranslate (mo_wordEq platform) ReallyUnsafePtrEqualityOp -> \[arg1, arg2] -> opIntoRegs $ \[res] -> emitAssign (CmmLocal res) (CmmMachOp (mo_wordEq platform) [arg1,arg2]) @@ -1180,315 +1180,323 @@ emitPrimOp cfg primop = Narrow16WordOp -> \args -> opNarrow args (MO_UU_Conv, W16) Narrow32WordOp -> \args -> opNarrow args (MO_UU_Conv, W32) - DoublePowerOp -> \args -> opCallish args MO_F64_Pwr - DoubleSinOp -> \args -> opCallish args MO_F64_Sin - DoubleCosOp -> \args -> opCallish args MO_F64_Cos - DoubleTanOp -> \args -> opCallish args MO_F64_Tan - DoubleSinhOp -> \args -> opCallish args MO_F64_Sinh - DoubleCoshOp -> \args -> opCallish args MO_F64_Cosh - DoubleTanhOp -> \args -> opCallish args MO_F64_Tanh - DoubleAsinOp -> \args -> opCallish args MO_F64_Asin - DoubleAcosOp -> \args -> opCallish args MO_F64_Acos - DoubleAtanOp -> \args -> opCallish args MO_F64_Atan - DoubleAsinhOp -> \args -> opCallish args MO_F64_Asinh - DoubleAcoshOp -> \args -> opCallish args MO_F64_Acosh - DoubleAtanhOp -> \args -> opCallish args MO_F64_Atanh - DoubleLogOp -> \args -> opCallish args MO_F64_Log - DoubleLog1POp -> \args -> opCallish args MO_F64_Log1P - DoubleExpOp -> \args -> opCallish args MO_F64_Exp - DoubleExpM1Op -> \args -> opCallish args MO_F64_ExpM1 - DoubleSqrtOp -> \args -> opCallish args MO_F64_Sqrt - DoubleFabsOp -> \args -> opCallish args MO_F64_Fabs - - FloatPowerOp -> \args -> opCallish args MO_F32_Pwr - FloatSinOp -> \args -> opCallish args MO_F32_Sin - FloatCosOp -> \args -> opCallish args MO_F32_Cos - FloatTanOp -> \args -> opCallish args MO_F32_Tan - FloatSinhOp -> \args -> opCallish args MO_F32_Sinh - FloatCoshOp -> \args -> opCallish args MO_F32_Cosh - FloatTanhOp -> \args -> opCallish args MO_F32_Tanh - FloatAsinOp -> \args -> opCallish args MO_F32_Asin - FloatAcosOp -> \args -> opCallish args MO_F32_Acos - FloatAtanOp -> \args -> opCallish args MO_F32_Atan - FloatAsinhOp -> \args -> opCallish args MO_F32_Asinh - FloatAcoshOp -> \args -> opCallish args MO_F32_Acosh - FloatAtanhOp -> \args -> opCallish args MO_F32_Atanh - FloatLogOp -> \args -> opCallish args MO_F32_Log - FloatLog1POp -> \args -> opCallish args MO_F32_Log1P - FloatExpOp -> \args -> opCallish args MO_F32_Exp - FloatExpM1Op -> \args -> opCallish args MO_F32_ExpM1 - FloatSqrtOp -> \args -> opCallish args MO_F32_Sqrt - FloatFabsOp -> \args -> opCallish args MO_F32_Fabs + DoublePowerOp -> opCallish MO_F64_Pwr + DoubleSinOp -> opCallish MO_F64_Sin + DoubleCosOp -> opCallish MO_F64_Cos + DoubleTanOp -> opCallish MO_F64_Tan + DoubleSinhOp -> opCallish MO_F64_Sinh + DoubleCoshOp -> opCallish MO_F64_Cosh + DoubleTanhOp -> opCallish MO_F64_Tanh + DoubleAsinOp -> opCallish MO_F64_Asin + DoubleAcosOp -> opCallish MO_F64_Acos + DoubleAtanOp -> opCallish MO_F64_Atan + DoubleAsinhOp -> opCallish MO_F64_Asinh + DoubleAcoshOp -> opCallish MO_F64_Acosh + DoubleAtanhOp -> opCallish MO_F64_Atanh + DoubleLogOp -> opCallish MO_F64_Log + DoubleLog1POp -> opCallish MO_F64_Log1P + DoubleExpOp -> opCallish MO_F64_Exp + DoubleExpM1Op -> opCallish MO_F64_ExpM1 + DoubleSqrtOp -> opCallish MO_F64_Sqrt + DoubleFabsOp -> opCallish MO_F64_Fabs + + FloatPowerOp -> opCallish MO_F32_Pwr + FloatSinOp -> opCallish MO_F32_Sin + FloatCosOp -> opCallish MO_F32_Cos + FloatTanOp -> opCallish MO_F32_Tan + FloatSinhOp -> opCallish MO_F32_Sinh + FloatCoshOp -> opCallish MO_F32_Cosh + FloatTanhOp -> opCallish MO_F32_Tanh + FloatAsinOp -> opCallish MO_F32_Asin + FloatAcosOp -> opCallish MO_F32_Acos + FloatAtanOp -> opCallish MO_F32_Atan + FloatAsinhOp -> opCallish MO_F32_Asinh + FloatAcoshOp -> opCallish MO_F32_Acosh + FloatAtanhOp -> opCallish MO_F32_Atanh + FloatLogOp -> opCallish MO_F32_Log + FloatLog1POp -> opCallish MO_F32_Log1P + FloatExpOp -> opCallish MO_F32_Exp + FloatExpM1Op -> opCallish MO_F32_ExpM1 + FloatSqrtOp -> opCallish MO_F32_Sqrt + FloatFabsOp -> opCallish MO_F32_Fabs -- Native word signless ops - IntAddOp -> \args -> opTranslate args (mo_wordAdd platform) - IntSubOp -> \args -> opTranslate args (mo_wordSub platform) - WordAddOp -> \args -> opTranslate args (mo_wordAdd platform) - WordSubOp -> \args -> opTranslate args (mo_wordSub platform) - AddrAddOp -> \args -> opTranslate args (mo_wordAdd platform) - AddrSubOp -> \args -> opTranslate args (mo_wordSub platform) - - IntEqOp -> \args -> opTranslate args (mo_wordEq platform) - IntNeOp -> \args -> opTranslate args (mo_wordNe platform) - WordEqOp -> \args -> opTranslate args (mo_wordEq platform) - WordNeOp -> \args -> opTranslate args (mo_wordNe platform) - AddrEqOp -> \args -> opTranslate args (mo_wordEq platform) - AddrNeOp -> \args -> opTranslate args (mo_wordNe platform) - - WordAndOp -> \args -> opTranslate args (mo_wordAnd platform) - WordOrOp -> \args -> opTranslate args (mo_wordOr platform) - WordXorOp -> \args -> opTranslate args (mo_wordXor platform) - WordNotOp -> \args -> opTranslate args (mo_wordNot platform) - WordSllOp -> \args -> opTranslate args (mo_wordShl platform) - WordSrlOp -> \args -> opTranslate args (mo_wordUShr platform) - - AddrRemOp -> \args -> opTranslate args (mo_wordURem platform) + IntAddOp -> opTranslate (mo_wordAdd platform) + IntSubOp -> opTranslate (mo_wordSub platform) + WordAddOp -> opTranslate (mo_wordAdd platform) + WordSubOp -> opTranslate (mo_wordSub platform) + AddrAddOp -> opTranslate (mo_wordAdd platform) + AddrSubOp -> opTranslate (mo_wordSub platform) + + IntEqOp -> opTranslate (mo_wordEq platform) + IntNeOp -> opTranslate (mo_wordNe platform) + WordEqOp -> opTranslate (mo_wordEq platform) + WordNeOp -> opTranslate (mo_wordNe platform) + AddrEqOp -> opTranslate (mo_wordEq platform) + AddrNeOp -> opTranslate (mo_wordNe platform) + + WordAndOp -> opTranslate (mo_wordAnd platform) + WordOrOp -> opTranslate (mo_wordOr platform) + WordXorOp -> opTranslate (mo_wordXor platform) + WordNotOp -> opTranslate (mo_wordNot platform) + WordSllOp -> opTranslate (mo_wordShl platform) + WordSrlOp -> opTranslate (mo_wordUShr platform) + + AddrRemOp -> opTranslate (mo_wordURem platform) -- Native word signed ops - IntMulOp -> \args -> opTranslate args (mo_wordMul platform) - IntMulMayOfloOp -> \args -> opTranslate args (MO_S_MulMayOflo (wordWidth platform)) - IntQuotOp -> \args -> opTranslate args (mo_wordSQuot platform) - IntRemOp -> \args -> opTranslate args (mo_wordSRem platform) - IntNegOp -> \args -> opTranslate args (mo_wordSNeg platform) - - IntGeOp -> \args -> opTranslate args (mo_wordSGe platform) - IntLeOp -> \args -> opTranslate args (mo_wordSLe platform) - IntGtOp -> \args -> opTranslate args (mo_wordSGt platform) - IntLtOp -> \args -> opTranslate args (mo_wordSLt platform) - - IntAndOp -> \args -> opTranslate args (mo_wordAnd platform) - IntOrOp -> \args -> opTranslate args (mo_wordOr platform) - IntXorOp -> \args -> opTranslate args (mo_wordXor platform) - IntNotOp -> \args -> opTranslate args (mo_wordNot platform) - IntSllOp -> \args -> opTranslate args (mo_wordShl platform) - IntSraOp -> \args -> opTranslate args (mo_wordSShr platform) - IntSrlOp -> \args -> opTranslate args (mo_wordUShr platform) + IntMulOp -> opTranslate (mo_wordMul platform) + IntMulMayOfloOp -> opTranslate (MO_S_MulMayOflo (wordWidth platform)) + IntQuotOp -> opTranslate (mo_wordSQuot platform) + IntRemOp -> opTranslate (mo_wordSRem platform) + IntNegOp -> opTranslate (mo_wordSNeg platform) + + IntGeOp -> opTranslate (mo_wordSGe platform) + IntLeOp -> opTranslate (mo_wordSLe platform) + IntGtOp -> opTranslate (mo_wordSGt platform) + IntLtOp -> opTranslate (mo_wordSLt platform) + + IntAndOp -> opTranslate (mo_wordAnd platform) + IntOrOp -> opTranslate (mo_wordOr platform) + IntXorOp -> opTranslate (mo_wordXor platform) + IntNotOp -> opTranslate (mo_wordNot platform) + IntSllOp -> opTranslate (mo_wordShl platform) + IntSraOp -> opTranslate (mo_wordSShr platform) + IntSrlOp -> opTranslate (mo_wordUShr platform) -- Native word unsigned ops - WordGeOp -> \args -> opTranslate args (mo_wordUGe platform) - WordLeOp -> \args -> opTranslate args (mo_wordULe platform) - WordGtOp -> \args -> opTranslate args (mo_wordUGt platform) - WordLtOp -> \args -> opTranslate args (mo_wordULt platform) + WordGeOp -> opTranslate (mo_wordUGe platform) + WordLeOp -> opTranslate (mo_wordULe platform) + WordGtOp -> opTranslate (mo_wordUGt platform) + WordLtOp -> opTranslate (mo_wordULt platform) - WordMulOp -> \args -> opTranslate args (mo_wordMul platform) - WordQuotOp -> \args -> opTranslate args (mo_wordUQuot platform) - WordRemOp -> \args -> opTranslate args (mo_wordURem platform) + WordMulOp -> opTranslate (mo_wordMul platform) + WordQuotOp -> opTranslate (mo_wordUQuot platform) + WordRemOp -> opTranslate (mo_wordURem platform) - AddrGeOp -> \args -> opTranslate args (mo_wordUGe platform) - AddrLeOp -> \args -> opTranslate args (mo_wordULe platform) - AddrGtOp -> \args -> opTranslate args (mo_wordUGt platform) - AddrLtOp -> \args -> opTranslate args (mo_wordULt platform) + AddrGeOp -> opTranslate (mo_wordUGe platform) + AddrLeOp -> opTranslate (mo_wordULe platform) + AddrGtOp -> opTranslate (mo_wordUGt platform) + AddrLtOp -> opTranslate (mo_wordULt platform) -- Int8# signed ops - Int8ToIntOp -> \args -> opTranslate args (MO_SS_Conv W8 (wordWidth platform)) - IntToInt8Op -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W8) - Int8NegOp -> \args -> opTranslate args (MO_S_Neg W8) - Int8AddOp -> \args -> opTranslate args (MO_Add W8) - Int8SubOp -> \args -> opTranslate args (MO_Sub W8) - Int8MulOp -> \args -> opTranslate args (MO_Mul W8) - Int8QuotOp -> \args -> opTranslate args (MO_S_Quot W8) - Int8RemOp -> \args -> opTranslate args (MO_S_Rem W8) - - Int8SllOp -> \args -> opTranslate args (MO_Shl W8) - Int8SraOp -> \args -> opTranslate args (MO_S_Shr W8) - Int8SrlOp -> \args -> opTranslate args (MO_U_Shr W8) - - Int8EqOp -> \args -> opTranslate args (MO_Eq W8) - Int8GeOp -> \args -> opTranslate args (MO_S_Ge W8) - Int8GtOp -> \args -> opTranslate args (MO_S_Gt W8) - Int8LeOp -> \args -> opTranslate args (MO_S_Le W8) - Int8LtOp -> \args -> opTranslate args (MO_S_Lt W8) - Int8NeOp -> \args -> opTranslate args (MO_Ne W8) + Int8ToIntOp -> opTranslate (MO_SS_Conv W8 (wordWidth platform)) + IntToInt8Op -> opTranslate (MO_SS_Conv (wordWidth platform) W8) + Int8NegOp -> opTranslate (MO_S_Neg W8) + Int8AddOp -> opTranslate (MO_Add W8) + Int8SubOp -> opTranslate (MO_Sub W8) + Int8MulOp -> opTranslate (MO_Mul W8) + Int8QuotOp -> opTranslate (MO_S_Quot W8) + Int8RemOp -> opTranslate (MO_S_Rem W8) + + Int8SllOp -> opTranslate (MO_Shl W8) + Int8SraOp -> opTranslate (MO_S_Shr W8) + Int8SrlOp -> opTranslate (MO_U_Shr W8) + + Int8EqOp -> opTranslate (MO_Eq W8) + Int8GeOp -> opTranslate (MO_S_Ge W8) + Int8GtOp -> opTranslate (MO_S_Gt W8) + Int8LeOp -> opTranslate (MO_S_Le W8) + Int8LtOp -> opTranslate (MO_S_Lt W8) + Int8NeOp -> opTranslate (MO_Ne W8) -- Word8# unsigned ops - Word8ToWordOp -> \args -> opTranslate args (MO_UU_Conv W8 (wordWidth platform)) - WordToWord8Op -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W8) - Word8AddOp -> \args -> opTranslate args (MO_Add W8) - Word8SubOp -> \args -> opTranslate args (MO_Sub W8) - Word8MulOp -> \args -> opTranslate args (MO_Mul W8) - Word8QuotOp -> \args -> opTranslate args (MO_U_Quot W8) - Word8RemOp -> \args -> opTranslate args (MO_U_Rem W8) - - Word8AndOp -> \args -> opTranslate args (MO_And W8) - Word8OrOp -> \args -> opTranslate args (MO_Or W8) - Word8XorOp -> \args -> opTranslate args (MO_Xor W8) - Word8NotOp -> \args -> opTranslate args (MO_Not W8) - Word8SllOp -> \args -> opTranslate args (MO_Shl W8) - Word8SrlOp -> \args -> opTranslate args (MO_U_Shr W8) - - Word8EqOp -> \args -> opTranslate args (MO_Eq W8) - Word8GeOp -> \args -> opTranslate args (MO_U_Ge W8) - Word8GtOp -> \args -> opTranslate args (MO_U_Gt W8) - Word8LeOp -> \args -> opTranslate args (MO_U_Le W8) - Word8LtOp -> \args -> opTranslate args (MO_U_Lt W8) - Word8NeOp -> \args -> opTranslate args (MO_Ne W8) + Word8ToWordOp -> opTranslate (MO_UU_Conv W8 (wordWidth platform)) + WordToWord8Op -> opTranslate (MO_UU_Conv (wordWidth platform) W8) + Word8AddOp -> opTranslate (MO_Add W8) + Word8SubOp -> opTranslate (MO_Sub W8) + Word8MulOp -> opTranslate (MO_Mul W8) + Word8QuotOp -> opTranslate (MO_U_Quot W8) + Word8RemOp -> opTranslate (MO_U_Rem W8) + + Word8AndOp -> opTranslate (MO_And W8) + Word8OrOp -> opTranslate (MO_Or W8) + Word8XorOp -> opTranslate (MO_Xor W8) + Word8NotOp -> opTranslate (MO_Not W8) + Word8SllOp -> opTranslate (MO_Shl W8) + Word8SrlOp -> opTranslate (MO_U_Shr W8) + + Word8EqOp -> opTranslate (MO_Eq W8) + Word8GeOp -> opTranslate (MO_U_Ge W8) + Word8GtOp -> opTranslate (MO_U_Gt W8) + Word8LeOp -> opTranslate (MO_U_Le W8) + Word8LtOp -> opTranslate (MO_U_Lt W8) + Word8NeOp -> opTranslate (MO_Ne W8) -- Int16# signed ops - Int16ToIntOp -> \args -> opTranslate args (MO_SS_Conv W16 (wordWidth platform)) - IntToInt16Op -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W16) - Int16NegOp -> \args -> opTranslate args (MO_S_Neg W16) - Int16AddOp -> \args -> opTranslate args (MO_Add W16) - Int16SubOp -> \args -> opTranslate args (MO_Sub W16) - Int16MulOp -> \args -> opTranslate args (MO_Mul W16) - Int16QuotOp -> \args -> opTranslate args (MO_S_Quot W16) - Int16RemOp -> \args -> opTranslate args (MO_S_Rem W16) - - Int16SllOp -> \args -> opTranslate args (MO_Shl W16) - Int16SraOp -> \args -> opTranslate args (MO_S_Shr W16) - Int16SrlOp -> \args -> opTranslate args (MO_U_Shr W16) - - Int16EqOp -> \args -> opTranslate args (MO_Eq W16) - Int16GeOp -> \args -> opTranslate args (MO_S_Ge W16) - Int16GtOp -> \args -> opTranslate args (MO_S_Gt W16) - Int16LeOp -> \args -> opTranslate args (MO_S_Le W16) - Int16LtOp -> \args -> opTranslate args (MO_S_Lt W16) - Int16NeOp -> \args -> opTranslate args (MO_Ne W16) + Int16ToIntOp -> opTranslate (MO_SS_Conv W16 (wordWidth platform)) + IntToInt16Op -> opTranslate (MO_SS_Conv (wordWidth platform) W16) + Int16NegOp -> opTranslate (MO_S_Neg W16) + Int16AddOp -> opTranslate (MO_Add W16) + Int16SubOp -> opTranslate (MO_Sub W16) + Int16MulOp -> opTranslate (MO_Mul W16) + Int16QuotOp -> opTranslate (MO_S_Quot W16) + Int16RemOp -> opTranslate (MO_S_Rem W16) + + Int16SllOp -> opTranslate (MO_Shl W16) + Int16SraOp -> opTranslate (MO_S_Shr W16) + Int16SrlOp -> opTranslate (MO_U_Shr W16) + + Int16EqOp -> opTranslate (MO_Eq W16) + Int16GeOp -> opTranslate (MO_S_Ge W16) + Int16GtOp -> opTranslate (MO_S_Gt W16) + Int16LeOp -> opTranslate (MO_S_Le W16) + Int16LtOp -> opTranslate (MO_S_Lt W16) + Int16NeOp -> opTranslate (MO_Ne W16) -- Word16# unsigned ops - Word16ToWordOp -> \args -> opTranslate args (MO_UU_Conv W16 (wordWidth platform)) - WordToWord16Op -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W16) - Word16AddOp -> \args -> opTranslate args (MO_Add W16) - Word16SubOp -> \args -> opTranslate args (MO_Sub W16) - Word16MulOp -> \args -> opTranslate args (MO_Mul W16) - Word16QuotOp -> \args -> opTranslate args (MO_U_Quot W16) - Word16RemOp -> \args -> opTranslate args (MO_U_Rem W16) - - Word16AndOp -> \args -> opTranslate args (MO_And W16) - Word16OrOp -> \args -> opTranslate args (MO_Or W16) - Word16XorOp -> \args -> opTranslate args (MO_Xor W16) - Word16NotOp -> \args -> opTranslate args (MO_Not W16) - Word16SllOp -> \args -> opTranslate args (MO_Shl W16) - Word16SrlOp -> \args -> opTranslate args (MO_U_Shr W16) - - Word16EqOp -> \args -> opTranslate args (MO_Eq W16) - Word16GeOp -> \args -> opTranslate args (MO_U_Ge W16) - Word16GtOp -> \args -> opTranslate args (MO_U_Gt W16) - Word16LeOp -> \args -> opTranslate args (MO_U_Le W16) - Word16LtOp -> \args -> opTranslate args (MO_U_Lt W16) - Word16NeOp -> \args -> opTranslate args (MO_Ne W16) + Word16ToWordOp -> opTranslate (MO_UU_Conv W16 (wordWidth platform)) + WordToWord16Op -> opTranslate (MO_UU_Conv (wordWidth platform) W16) + Word16AddOp -> opTranslate (MO_Add W16) + Word16SubOp -> opTranslate (MO_Sub W16) + Word16MulOp -> opTranslate (MO_Mul W16) + Word16QuotOp -> opTranslate (MO_U_Quot W16) + Word16RemOp -> opTranslate (MO_U_Rem W16) + + Word16AndOp -> opTranslate (MO_And W16) + Word16OrOp -> opTranslate (MO_Or W16) + Word16XorOp -> opTranslate (MO_Xor W16) + Word16NotOp -> opTranslate (MO_Not W16) + Word16SllOp -> opTranslate (MO_Shl W16) + Word16SrlOp -> opTranslate (MO_U_Shr W16) + + Word16EqOp -> opTranslate (MO_Eq W16) + Word16GeOp -> opTranslate (MO_U_Ge W16) + Word16GtOp -> opTranslate (MO_U_Gt W16) + Word16LeOp -> opTranslate (MO_U_Le W16) + Word16LtOp -> opTranslate (MO_U_Lt W16) + Word16NeOp -> opTranslate (MO_Ne W16) -- Int32# signed ops - Int32ToIntOp -> \args -> opTranslate args (MO_SS_Conv W32 (wordWidth platform)) - IntToInt32Op -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W32) - Int32NegOp -> \args -> opTranslate args (MO_S_Neg W32) - Int32AddOp -> \args -> opTranslate args (MO_Add W32) - Int32SubOp -> \args -> opTranslate args (MO_Sub W32) - Int32MulOp -> \args -> opTranslate args (MO_Mul W32) - Int32QuotOp -> \args -> opTranslate args (MO_S_Quot W32) - Int32RemOp -> \args -> opTranslate args (MO_S_Rem W32) - - Int32SllOp -> \args -> opTranslate args (MO_Shl W32) - Int32SraOp -> \args -> opTranslate args (MO_S_Shr W32) - Int32SrlOp -> \args -> opTranslate args (MO_U_Shr W32) - - Int32EqOp -> \args -> opTranslate args (MO_Eq W32) - Int32GeOp -> \args -> opTranslate args (MO_S_Ge W32) - Int32GtOp -> \args -> opTranslate args (MO_S_Gt W32) - Int32LeOp -> \args -> opTranslate args (MO_S_Le W32) - Int32LtOp -> \args -> opTranslate args (MO_S_Lt W32) - Int32NeOp -> \args -> opTranslate args (MO_Ne W32) + Int32ToIntOp -> opTranslate (MO_SS_Conv W32 (wordWidth platform)) + IntToInt32Op -> opTranslate (MO_SS_Conv (wordWidth platform) W32) + Int32NegOp -> opTranslate (MO_S_Neg W32) + Int32AddOp -> opTranslate (MO_Add W32) + Int32SubOp -> opTranslate (MO_Sub W32) + Int32MulOp -> opTranslate (MO_Mul W32) + Int32QuotOp -> opTranslate (MO_S_Quot W32) + Int32RemOp -> opTranslate (MO_S_Rem W32) + + Int32SllOp -> opTranslate (MO_Shl W32) + Int32SraOp -> opTranslate (MO_S_Shr W32) + Int32SrlOp -> opTranslate (MO_U_Shr W32) + + Int32EqOp -> opTranslate (MO_Eq W32) + Int32GeOp -> opTranslate (MO_S_Ge W32) + Int32GtOp -> opTranslate (MO_S_Gt W32) + Int32LeOp -> opTranslate (MO_S_Le W32) + Int32LtOp -> opTranslate (MO_S_Lt W32) + Int32NeOp -> opTranslate (MO_Ne W32) -- Word32# unsigned ops - Word32ToWordOp -> \args -> opTranslate args (MO_UU_Conv W32 (wordWidth platform)) - WordToWord32Op -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W32) - Word32AddOp -> \args -> opTranslate args (MO_Add W32) - Word32SubOp -> \args -> opTranslate args (MO_Sub W32) - Word32MulOp -> \args -> opTranslate args (MO_Mul W32) - Word32QuotOp -> \args -> opTranslate args (MO_U_Quot W32) - Word32RemOp -> \args -> opTranslate args (MO_U_Rem W32) - - Word32AndOp -> \args -> opTranslate args (MO_And W32) - Word32OrOp -> \args -> opTranslate args (MO_Or W32) - Word32XorOp -> \args -> opTranslate args (MO_Xor W32) - Word32NotOp -> \args -> opTranslate args (MO_Not W32) - Word32SllOp -> \args -> opTranslate args (MO_Shl W32) - Word32SrlOp -> \args -> opTranslate args (MO_U_Shr W32) - - Word32EqOp -> \args -> opTranslate args (MO_Eq W32) - Word32GeOp -> \args -> opTranslate args (MO_U_Ge W32) - Word32GtOp -> \args -> opTranslate args (MO_U_Gt W32) - Word32LeOp -> \args -> opTranslate args (MO_U_Le W32) - Word32LtOp -> \args -> opTranslate args (MO_U_Lt W32) - Word32NeOp -> \args -> opTranslate args (MO_Ne W32) + Word32ToWordOp -> opTranslate (MO_UU_Conv W32 (wordWidth platform)) + WordToWord32Op -> opTranslate (MO_UU_Conv (wordWidth platform) W32) + Word32AddOp -> opTranslate (MO_Add W32) + Word32SubOp -> opTranslate (MO_Sub W32) + Word32MulOp -> opTranslate (MO_Mul W32) + Word32QuotOp -> opTranslate (MO_U_Quot W32) + Word32RemOp -> opTranslate (MO_U_Rem W32) + + Word32AndOp -> opTranslate (MO_And W32) + Word32OrOp -> opTranslate (MO_Or W32) + Word32XorOp -> opTranslate (MO_Xor W32) + Word32NotOp -> opTranslate (MO_Not W32) + Word32SllOp -> opTranslate (MO_Shl W32) + Word32SrlOp -> opTranslate (MO_U_Shr W32) + + Word32EqOp -> opTranslate (MO_Eq W32) + Word32GeOp -> opTranslate (MO_U_Ge W32) + Word32GtOp -> opTranslate (MO_U_Gt W32) + Word32LeOp -> opTranslate (MO_U_Le W32) + Word32LtOp -> opTranslate (MO_U_Lt W32) + Word32NeOp -> opTranslate (MO_Ne W32) -- Int64# signed ops - Int64ToIntOp -> \args -> opTranslate64 args (\w -> MO_SS_Conv w (wordWidth platform)) MO_I64_ToI - IntToInt64Op -> \args -> opTranslate64 args (\w -> MO_SS_Conv (wordWidth platform) w) MO_I64_FromI - Int64NegOp -> \args -> opTranslate64 args MO_S_Neg MO_x64_Neg - Int64AddOp -> \args -> opTranslate64 args MO_Add MO_x64_Add - Int64SubOp -> \args -> opTranslate64 args MO_Sub MO_x64_Sub - Int64MulOp -> \args -> opTranslate64 args MO_Mul MO_x64_Mul - Int64QuotOp -> \args -> opTranslate64 args MO_S_Quot MO_I64_Quot - Int64RemOp -> \args -> opTranslate64 args MO_S_Rem MO_I64_Rem - - Int64SllOp -> \args -> opTranslate64 args MO_Shl MO_x64_Shl - Int64SraOp -> \args -> opTranslate64 args MO_S_Shr MO_I64_Shr - Int64SrlOp -> \args -> opTranslate64 args MO_U_Shr MO_W64_Shr - - Int64EqOp -> \args -> opTranslate64 args MO_Eq MO_x64_Eq - Int64GeOp -> \args -> opTranslate64 args MO_S_Ge MO_I64_Ge - Int64GtOp -> \args -> opTranslate64 args MO_S_Gt MO_I64_Gt - Int64LeOp -> \args -> opTranslate64 args MO_S_Le MO_I64_Le - Int64LtOp -> \args -> opTranslate64 args MO_S_Lt MO_I64_Lt - Int64NeOp -> \args -> opTranslate64 args MO_Ne MO_x64_Ne + Int64ToIntOp -> opTranslate64 (MO_SS_Conv W64 (wordWidth platform)) MO_I64_ToI + IntToInt64Op -> opTranslate64 (MO_SS_Conv (wordWidth platform) W64) MO_I64_FromI + Int64NegOp -> opTranslate64 (MO_S_Neg W64) MO_x64_Neg + Int64AddOp -> opTranslate64 (MO_Add W64) MO_x64_Add + Int64SubOp -> opTranslate64 (MO_Sub W64) MO_x64_Sub + Int64MulOp -> opTranslate64 (MO_Mul W64) MO_x64_Mul + Int64QuotOp + | allowQuot64 -> opTranslate (MO_S_Quot W64) + | otherwise -> opCallish MO_I64_Quot + Int64RemOp + | allowQuot64 -> opTranslate (MO_S_Rem W64) + | otherwise -> opCallish MO_I64_Rem + + Int64SllOp -> opTranslate64 (MO_Shl W64) MO_x64_Shl + Int64SraOp -> opTranslate64 (MO_S_Shr W64) MO_I64_Shr + Int64SrlOp -> opTranslate64 (MO_U_Shr W64) MO_W64_Shr + + Int64EqOp -> opTranslate64 (MO_Eq W64) MO_x64_Eq + Int64GeOp -> opTranslate64 (MO_S_Ge W64) MO_I64_Ge + Int64GtOp -> opTranslate64 (MO_S_Gt W64) MO_I64_Gt + Int64LeOp -> opTranslate64 (MO_S_Le W64) MO_I64_Le + Int64LtOp -> opTranslate64 (MO_S_Lt W64) MO_I64_Lt + Int64NeOp -> opTranslate64 (MO_Ne W64) MO_x64_Ne -- Word64# unsigned ops - Word64ToWordOp -> \args -> opTranslate64 args (\w -> MO_UU_Conv w (wordWidth platform)) MO_W64_ToW - WordToWord64Op -> \args -> opTranslate64 args (\w -> MO_UU_Conv (wordWidth platform) w) MO_W64_FromW - Word64AddOp -> \args -> opTranslate64 args MO_Add MO_x64_Add - Word64SubOp -> \args -> opTranslate64 args MO_Sub MO_x64_Sub - Word64MulOp -> \args -> opTranslate64 args MO_Mul MO_x64_Mul - Word64QuotOp -> \args -> opTranslate64 args MO_U_Quot MO_W64_Quot - Word64RemOp -> \args -> opTranslate64 args MO_U_Rem MO_W64_Rem - - Word64AndOp -> \args -> opTranslate64 args MO_And MO_x64_And - Word64OrOp -> \args -> opTranslate64 args MO_Or MO_x64_Or - Word64XorOp -> \args -> opTranslate64 args MO_Xor MO_x64_Xor - Word64NotOp -> \args -> opTranslate64 args MO_Not MO_x64_Not - Word64SllOp -> \args -> opTranslate64 args MO_Shl MO_x64_Shl - Word64SrlOp -> \args -> opTranslate64 args MO_U_Shr MO_W64_Shr - - Word64EqOp -> \args -> opTranslate64 args MO_Eq MO_x64_Eq - Word64GeOp -> \args -> opTranslate64 args MO_U_Ge MO_W64_Ge - Word64GtOp -> \args -> opTranslate64 args MO_U_Gt MO_W64_Gt - Word64LeOp -> \args -> opTranslate64 args MO_U_Le MO_W64_Le - Word64LtOp -> \args -> opTranslate64 args MO_U_Lt MO_W64_Lt - Word64NeOp -> \args -> opTranslate64 args MO_Ne MO_x64_Ne + Word64ToWordOp -> opTranslate64 (MO_UU_Conv W64 (wordWidth platform)) MO_W64_ToW + WordToWord64Op -> opTranslate64 (MO_UU_Conv (wordWidth platform) W64) MO_W64_FromW + Word64AddOp -> opTranslate64 (MO_Add W64) MO_x64_Add + Word64SubOp -> opTranslate64 (MO_Sub W64) MO_x64_Sub + Word64MulOp -> opTranslate64 (MO_Mul W64) MO_x64_Mul + Word64QuotOp + | allowQuot64 -> opTranslate (MO_U_Quot W64) + | otherwise -> opCallish MO_W64_Quot + Word64RemOp + | allowQuot64 -> opTranslate (MO_U_Rem W64) + | otherwise -> opCallish MO_W64_Rem + + Word64AndOp -> opTranslate64 (MO_And W64) MO_x64_And + Word64OrOp -> opTranslate64 (MO_Or W64) MO_x64_Or + Word64XorOp -> opTranslate64 (MO_Xor W64) MO_x64_Xor + Word64NotOp -> opTranslate64 (MO_Not W64) MO_x64_Not + Word64SllOp -> opTranslate64 (MO_Shl W64) MO_x64_Shl + Word64SrlOp -> opTranslate64 (MO_U_Shr W64) MO_W64_Shr + + Word64EqOp -> opTranslate64 (MO_Eq W64) MO_x64_Eq + Word64GeOp -> opTranslate64 (MO_U_Ge W64) MO_W64_Ge + Word64GtOp -> opTranslate64 (MO_U_Gt W64) MO_W64_Gt + Word64LeOp -> opTranslate64 (MO_U_Le W64) MO_W64_Le + Word64LtOp -> opTranslate64 (MO_U_Lt W64) MO_W64_Lt + Word64NeOp -> opTranslate64 (MO_Ne W64) MO_x64_Ne -- Char# ops - CharEqOp -> \args -> opTranslate args (MO_Eq (wordWidth platform)) - CharNeOp -> \args -> opTranslate args (MO_Ne (wordWidth platform)) - CharGeOp -> \args -> opTranslate args (MO_U_Ge (wordWidth platform)) - CharLeOp -> \args -> opTranslate args (MO_U_Le (wordWidth platform)) - CharGtOp -> \args -> opTranslate args (MO_U_Gt (wordWidth platform)) - CharLtOp -> \args -> opTranslate args (MO_U_Lt (wordWidth platform)) + CharEqOp -> opTranslate (MO_Eq (wordWidth platform)) + CharNeOp -> opTranslate (MO_Ne (wordWidth platform)) + CharGeOp -> opTranslate (MO_U_Ge (wordWidth platform)) + CharLeOp -> opTranslate (MO_U_Le (wordWidth platform)) + CharGtOp -> opTranslate (MO_U_Gt (wordWidth platform)) + CharLtOp -> opTranslate (MO_U_Lt (wordWidth platform)) -- Double ops - DoubleEqOp -> \args -> opTranslate args (MO_F_Eq W64) - DoubleNeOp -> \args -> opTranslate args (MO_F_Ne W64) - DoubleGeOp -> \args -> opTranslate args (MO_F_Ge W64) - DoubleLeOp -> \args -> opTranslate args (MO_F_Le W64) - DoubleGtOp -> \args -> opTranslate args (MO_F_Gt W64) - DoubleLtOp -> \args -> opTranslate args (MO_F_Lt W64) + DoubleEqOp -> opTranslate (MO_F_Eq W64) + DoubleNeOp -> opTranslate (MO_F_Ne W64) + DoubleGeOp -> opTranslate (MO_F_Ge W64) + DoubleLeOp -> opTranslate (MO_F_Le W64) + DoubleGtOp -> opTranslate (MO_F_Gt W64) + DoubleLtOp -> opTranslate (MO_F_Lt W64) - DoubleAddOp -> \args -> opTranslate args (MO_F_Add W64) - DoubleSubOp -> \args -> opTranslate args (MO_F_Sub W64) - DoubleMulOp -> \args -> opTranslate args (MO_F_Mul W64) - DoubleDivOp -> \args -> opTranslate args (MO_F_Quot W64) - DoubleNegOp -> \args -> opTranslate args (MO_F_Neg W64) + DoubleAddOp -> opTranslate (MO_F_Add W64) + DoubleSubOp -> opTranslate (MO_F_Sub W64) + DoubleMulOp -> opTranslate (MO_F_Mul W64) + DoubleDivOp -> opTranslate (MO_F_Quot W64) + DoubleNegOp -> opTranslate (MO_F_Neg W64) DoubleFMAdd -> fmaOp FMAdd W64 DoubleFMSub -> fmaOp FMSub W64 @@ -1497,18 +1505,18 @@ emitPrimOp cfg primop = -- Float ops - FloatEqOp -> \args -> opTranslate args (MO_F_Eq W32) - FloatNeOp -> \args -> opTranslate args (MO_F_Ne W32) - FloatGeOp -> \args -> opTranslate args (MO_F_Ge W32) - FloatLeOp -> \args -> opTranslate args (MO_F_Le W32) - FloatGtOp -> \args -> opTranslate args (MO_F_Gt W32) - FloatLtOp -> \args -> opTranslate args (MO_F_Lt W32) + FloatEqOp -> opTranslate (MO_F_Eq W32) + FloatNeOp -> opTranslate (MO_F_Ne W32) + FloatGeOp -> opTranslate (MO_F_Ge W32) + FloatLeOp -> opTranslate (MO_F_Le W32) + FloatGtOp -> opTranslate (MO_F_Gt W32) + FloatLtOp -> opTranslate (MO_F_Lt W32) - FloatAddOp -> \args -> opTranslate args (MO_F_Add W32) - FloatSubOp -> \args -> opTranslate args (MO_F_Sub W32) - FloatMulOp -> \args -> opTranslate args (MO_F_Mul W32) - FloatDivOp -> \args -> opTranslate args (MO_F_Quot W32) - FloatNegOp -> \args -> opTranslate args (MO_F_Neg W32) + FloatAddOp -> opTranslate (MO_F_Add W32) + FloatSubOp -> opTranslate (MO_F_Sub W32) + FloatMulOp -> opTranslate (MO_F_Mul W32) + FloatDivOp -> opTranslate (MO_F_Quot W32) + FloatNegOp -> opTranslate (MO_F_Neg W32) FloatFMAdd -> fmaOp FMAdd W32 FloatFMSub -> fmaOp FMSub W32 @@ -1517,126 +1525,122 @@ emitPrimOp cfg primop = -- Vector ops - (VecAddOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Add n w) - (VecSubOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Sub n w) - (VecMulOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Mul n w) - (VecDivOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Quot n w) + (VecAddOp FloatVec n w) -> opTranslate (MO_VF_Add n w) + (VecSubOp FloatVec n w) -> opTranslate (MO_VF_Sub n w) + (VecMulOp FloatVec n w) -> opTranslate (MO_VF_Mul n w) + (VecDivOp FloatVec n w) -> opTranslate (MO_VF_Quot n w) (VecQuotOp FloatVec _ _) -> \_ -> panic "unsupported primop" (VecRemOp FloatVec _ _) -> \_ -> panic "unsupported primop" - (VecNegOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Neg n w) + (VecNegOp FloatVec n w) -> opTranslate (MO_VF_Neg n w) - (VecAddOp IntVec n w) -> \args -> opTranslate args (MO_V_Add n w) - (VecSubOp IntVec n w) -> \args -> opTranslate args (MO_V_Sub n w) - (VecMulOp IntVec n w) -> \args -> opTranslate args (MO_V_Mul n w) + (VecAddOp IntVec n w) -> opTranslate (MO_V_Add n w) + (VecSubOp IntVec n w) -> opTranslate (MO_V_Sub n w) + (VecMulOp IntVec n w) -> opTranslate (MO_V_Mul n w) (VecDivOp IntVec _ _) -> \_ -> panic "unsupported primop" - (VecQuotOp IntVec n w) -> \args -> opTranslate args (MO_VS_Quot n w) - (VecRemOp IntVec n w) -> \args -> opTranslate args (MO_VS_Rem n w) - (VecNegOp IntVec n w) -> \args -> opTranslate args (MO_VS_Neg n w) + (VecQuotOp IntVec n w) -> opTranslate (MO_VS_Quot n w) + (VecRemOp IntVec n w) -> opTranslate (MO_VS_Rem n w) + (VecNegOp IntVec n w) -> opTranslate (MO_VS_Neg n w) - (VecAddOp WordVec n w) -> \args -> opTranslate args (MO_V_Add n w) - (VecSubOp WordVec n w) -> \args -> opTranslate args (MO_V_Sub n w) - (VecMulOp WordVec n w) -> \args -> opTranslate args (MO_V_Mul n w) + (VecAddOp WordVec n w) -> opTranslate (MO_V_Add n w) + (VecSubOp WordVec n w) -> opTranslate (MO_V_Sub n w) + (VecMulOp WordVec n w) -> opTranslate (MO_V_Mul n w) (VecDivOp WordVec _ _) -> \_ -> panic "unsupported primop" - (VecQuotOp WordVec n w) -> \args -> opTranslate args (MO_VU_Quot n w) - (VecRemOp WordVec n w) -> \args -> opTranslate args (MO_VU_Rem n w) + (VecQuotOp WordVec n w) -> opTranslate (MO_VU_Quot n w) + (VecRemOp WordVec n w) -> opTranslate (MO_VU_Rem n w) (VecNegOp WordVec _ _) -> \_ -> panic "unsupported primop" -- Conversions - IntToDoubleOp -> \args -> opTranslate args (MO_SF_Round (wordWidth platform) W64) - DoubleToIntOp -> \args -> opTranslate args (MO_FS_Truncate W64 (wordWidth platform)) + IntToDoubleOp -> opTranslate (MO_SF_Round (wordWidth platform) W64) + DoubleToIntOp -> opTranslate (MO_FS_Truncate W64 (wordWidth platform)) - IntToFloatOp -> \args -> opTranslate args (MO_SF_Round (wordWidth platform) W32) - FloatToIntOp -> \args -> opTranslate args (MO_FS_Truncate W32 (wordWidth platform)) + IntToFloatOp -> opTranslate (MO_SF_Round (wordWidth platform) W32) + FloatToIntOp -> opTranslate (MO_FS_Truncate W32 (wordWidth platform)) - FloatToDoubleOp -> \args -> opTranslate args (MO_FF_Conv W32 W64) - DoubleToFloatOp -> \args -> opTranslate args (MO_FF_Conv W64 W32) + FloatToDoubleOp -> opTranslate (MO_FF_Conv W32 W64) + DoubleToFloatOp -> opTranslate (MO_FF_Conv W64 W32) - CastFloatToWord32Op -> - \args -> translateBitcasts (MO_FW_Bitcast W32) args - CastWord32ToFloatOp -> - \args -> translateBitcasts (MO_WF_Bitcast W32) args - CastDoubleToWord64Op -> - \args -> translateBitcasts (MO_FW_Bitcast W64) args - CastWord64ToDoubleOp -> - \args -> translateBitcasts (MO_WF_Bitcast W64) args + CastFloatToWord32Op -> translateBitcasts (MO_FW_Bitcast W32) + CastWord32ToFloatOp -> translateBitcasts (MO_WF_Bitcast W32) + CastDoubleToWord64Op -> translateBitcasts (MO_FW_Bitcast W64) + CastWord64ToDoubleOp -> translateBitcasts (MO_WF_Bitcast W64) - IntQuotRemOp -> \args -> opCallishHandledLater args $ + IntQuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem (wordWidth platform)) else Right (genericIntQuotRemOp (wordWidth platform)) - Int8QuotRemOp -> \args -> opCallishHandledLater args $ + Int8QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem W8) else Right (genericIntQuotRemOp W8) - Int16QuotRemOp -> \args -> opCallishHandledLater args $ + Int16QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem W16) else Right (genericIntQuotRemOp W16) - Int32QuotRemOp -> \args -> opCallishHandledLater args $ + Int32QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem W32) else Right (genericIntQuotRemOp W32) - WordQuotRemOp -> \args -> opCallishHandledLater args $ + WordQuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem (wordWidth platform)) else Right (genericWordQuotRemOp (wordWidth platform)) - WordQuotRem2Op -> \args -> opCallishHandledLater args $ + WordQuotRem2Op -> opCallishHandledLater $ if allowQuotRem2 then Left (MO_U_QuotRem2 (wordWidth platform)) else Right (genericWordQuotRem2Op platform) - Word8QuotRemOp -> \args -> opCallishHandledLater args $ + Word8QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem W8) else Right (genericWordQuotRemOp W8) - Word16QuotRemOp -> \args -> opCallishHandledLater args $ + Word16QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem W16) else Right (genericWordQuotRemOp W16) - Word32QuotRemOp -> \args -> opCallishHandledLater args $ + Word32QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem W32) else Right (genericWordQuotRemOp W32) - WordAdd2Op -> \args -> opCallishHandledLater args $ + WordAdd2Op -> opCallishHandledLater $ if allowExtAdd then Left (MO_Add2 (wordWidth platform)) else Right genericWordAdd2Op - WordAddCOp -> \args -> opCallishHandledLater args $ + WordAddCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_AddWordC (wordWidth platform)) else Right genericWordAddCOp - WordSubCOp -> \args -> opCallishHandledLater args $ + WordSubCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_SubWordC (wordWidth platform)) else Right genericWordSubCOp - IntAddCOp -> \args -> opCallishHandledLater args $ + IntAddCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_AddIntC (wordWidth platform)) else Right genericIntAddCOp - IntSubCOp -> \args -> opCallishHandledLater args $ + IntSubCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_SubIntC (wordWidth platform)) else Right genericIntSubCOp - WordMul2Op -> \args -> opCallishHandledLater args $ + WordMul2Op -> opCallishHandledLater $ if allowWord2Mul then Left (MO_U_Mul2 (wordWidth platform)) else Right genericWordMul2Op - IntMul2Op -> \args -> opCallishHandledLater args $ + IntMul2Op -> opCallishHandledLater $ if allowInt2Mul then Left (MO_S_Mul2 (wordWidth platform)) else Right genericIntMul2Op @@ -1775,42 +1779,33 @@ emitPrimOp cfg primop = -- These primops are implemented by CallishMachOps, because they sometimes -- turn into foreign calls depending on the backend. - opCallish :: [CmmExpr] -> CallishMachOp -> PrimopCmmEmit - opCallish args prim = opIntoRegs $ \[res] -> emitPrimCall [res] prim args + opCallish :: CallishMachOp -> [CmmExpr] -> PrimopCmmEmit + opCallish prim args = opIntoRegs $ \[res] -> emitPrimCall [res] prim args - opTranslate :: [CmmExpr] -> MachOp -> PrimopCmmEmit - opTranslate args mop = opIntoRegs $ \[res] -> do + opTranslate :: MachOp -> [CmmExpr] -> PrimopCmmEmit + opTranslate mop args = opIntoRegs $ \[res] -> do let stmt = mkAssign (CmmLocal res) (CmmMachOp mop args) emit stmt - isQuottishOp :: CallishMachOp -> Bool - isQuottishOp MO_I64_Quot = True - isQuottishOp MO_I64_Rem = True - isQuottishOp MO_W64_Quot = True - isQuottishOp MO_W64_Rem = True - isQuottishOp _ = False - opTranslate64 - :: [CmmExpr] - -> (Width -> MachOp) + :: MachOp -> CallishMachOp + -> [CmmExpr] -> PrimopCmmEmit - opTranslate64 args mkMop callish = - case platformWordSize platform of - -- LLVM and C `can handle larger than native size arithmetic natively. - _ | not (isQuottishOp callish), stgToCmmAllowBigArith cfg -> opTranslate args $ mkMop W64 - | isQuottishOp callish, stgToCmmAllowBigQuot cfg -> opTranslate args $ mkMop W64 - PW4 -> opCallish args callish - PW8 -> opTranslate args $ mkMop W64 + opTranslate64 mop callish + | allowArith64 = opTranslate mop + | otherwise = opCallish callish + -- backends not supporting 64-bit arithmetic primops: use callish machine + -- ops -- Basically a "manual" case, rather than one of the common repetitive forms -- above. The results are a parameter to the returned function so we know the -- choice of variant never depends on them. opCallishHandledLater - :: [CmmExpr] - -> Either CallishMachOp GenericOp + :: Either CallishMachOp GenericOp + -> [CmmExpr] -> PrimopCmmEmit - opCallishHandledLater args callOrNot = opIntoRegs $ \res0 -> case callOrNot of + opCallishHandledLater callOrNot args = opIntoRegs $ \res0 -> case callOrNot of Left op -> emit $ mkUnsafeCall (PrimTarget op) res0 args Right gen -> gen res0 args @@ -1838,21 +1833,23 @@ emitPrimOp cfg primop = allowExtAdd = stgToCmmAllowExtendedAddSubInstrs cfg allowInt2Mul = stgToCmmAllowIntMul2Instr cfg allowWord2Mul = stgToCmmAllowWordMul2Instr cfg + allowArith64 = stgToCmmAllowArith64 cfg + allowQuot64 = stgToCmmAllowQuot64 cfg -- a bit of a hack, for certain code generaters, e.g. PPC, and i386 we -- continue to use the cmm versions of these functions instead of inline -- assembly. Tracked in #24841. ppc = isPPC $ platformArch platform i386 = target32Bit platform - translateBitcasts mop args | ppc || i386 = alwaysExternal args - | otherwise = opTranslate args mop + translateBitcasts mop | ppc || i386 = alwaysExternal + | otherwise = opTranslate mop allowFMA = stgToCmmAllowFMAInstr cfg fmaOp :: FMASign -> Width -> [CmmActual] -> PrimopCmmEmit fmaOp signs w args@[arg_x, arg_y, arg_z] | allowFMA signs - = opTranslate args (MO_FMA signs w) + = opTranslate (MO_FMA signs w) args | otherwise = case signs of ===================================== compiler/Language/Haskell/Syntax/Pat.hs ===================================== @@ -57,62 +57,73 @@ import Data.List.NonEmpty (NonEmpty) type LPat p = XRec p (Pat p) -- | Pattern --- --- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang' - --- For details on above see Note [exact print annotations] in GHC.Parser.Annotation data Pat p = ------------ Simple patterns --------------- - WildPat (XWildPat p) -- ^ Wildcard Pattern - -- The sole reason for a type on a WildPat is to - -- support hsPatType :: Pat Id -> Type - - -- AZ:TODO above comment needs to be updated + WildPat (XWildPat p) + -- ^ Wildcard Pattern (@_@) | VarPat (XVarPat p) - (LIdP p) -- ^ Variable Pattern + (LIdP p) + -- ^ Variable Pattern, e.g. @x@ - -- See Note [Located RdrNames] in GHC.Hs.Expr + -- See Note [Located RdrNames] in GHC.Hs.Expr | LazyPat (XLazyPat p) - (LPat p) -- ^ Lazy Pattern - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnTilde' + (LPat p) + -- ^ Lazy Pattern, e.g. @~x@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnTilde' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | AsPat (XAsPat p) (LIdP p) - (LPat p) -- ^ As pattern - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnAt' + (LPat p) + -- ^ As pattern, e.g. @x\@pat@ + -- + -- - Location of '@' is captured by 'GHC.Parser.Annotation.EpToken' @"\@"@ -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | ParPat (XParPat p) - (LPat p) -- ^ Parenthesised pattern - -- See Note [Parens in HsSyn] in GHC.Hs.Expr - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'('@, - -- 'GHC.Parser.Annotation.AnnClose' @')'@ + (LPat p) + -- ^ Parenthesised pattern, e.g. @(x)@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : + -- 'GHC.Parser.Annotation.AnnOpen' @'('@, + -- 'GHC.Parser.Annotation.AnnClose' @')'@ + + -- See Note [Parens in HsSyn] in GHC.Hs.Expr -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | BangPat (XBangPat p) - (LPat p) -- ^ Bang pattern - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang' + (LPat p) + -- ^ Bang pattern, e.g. @!x@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation ------------ Lists, tuples, arrays --------------- | ListPat (XListPat p) [LPat p] + -- ^ Syntactic List, e.g. @[x]@ or @[x,y]@ (but not @[]@ nor @(x:xs)@ which are represented using 'ConPat') + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : + -- 'GHC.Parser.Annotation.AnnOpen' @'['@, + -- 'GHC.Parser.Annotation.AnnClose' @']'@ - -- ^ Syntactic List + -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation + + | -- | Tuple pattern, e.g. @(x, y)@ -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'['@, - -- 'GHC.Parser.Annotation.AnnClose' @']'@ + -- - 'GHC.Parser.Annotation.AnnKeywordId' : + -- 'GHC.Parser.Annotation.AnnOpen' @'('@ or @'(#'@, + -- 'GHC.Parser.Annotation.AnnClose' @')'@ or @'#)'@ -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation + TuplePat (XTuplePat p) -- ^ After typechecking, holds the types of the tuple components + [LPat p] -- ^ Tuple sub-patterns + Boxity -- ^ UnitPat is TuplePat [] - | TuplePat (XTuplePat p) - -- after typechecking, holds the types of the tuple components - [LPat p] -- Tuple sub-patterns - Boxity -- UnitPat is TuplePat [] -- You might think that the post typechecking Type was redundant, -- because we can get the pattern type by getting the types of the -- sub-patterns. @@ -129,11 +140,6 @@ data Pat p -- of the tuple is of type 'a' not Int. See selectMatchVar -- (June 14: I'm not sure this comment is right; the sub-patterns -- will be wrapped in CoPats, no?) - -- ^ Tuple sub-patterns - -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : - -- 'GHC.Parser.Annotation.AnnOpen' @'('@ or @'(#'@, - -- 'GHC.Parser.Annotation.AnnClose' @')'@ or @'#)'@ | OrPat (XOrPat p) (NonEmpty (LPat p)) @@ -143,7 +149,8 @@ data Pat p (LPat p) -- Sum sub-pattern ConTag -- Alternative (one-based) SumWidth -- Arity (INVARIANT: ≥ 2) - -- ^ Anonymous sum pattern + + -- ^ Anonymous sum pattern, e.g. @(# x | #)@. Used by @-XUnboxedSums@ -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : -- 'GHC.Parser.Annotation.AnnOpen' @'(#'@, @@ -157,35 +164,40 @@ data Pat p pat_con :: XRec p (ConLikeP p), pat_args :: HsConPatDetails p } - -- ^ Constructor Pattern + -- ^ Constructor Pattern, e.g. @[]@ or @Nothing@ ------------ View patterns --------------- - -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnRarrow' - -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | ViewPat (XViewPat p) (LHsExpr p) (LPat p) - -- ^ View Pattern + -- ^ View Pattern, e.g. @someFun -> pat at . Used by @-XViewPatterns@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnRarrow' + + -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation ------------ Pattern splices --------------- - -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'$('@ - -- 'GHC.Parser.Annotation.AnnClose' @')'@ - -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | SplicePat (XSplicePat p) - (HsUntypedSplice p) -- ^ Splice Pattern (Includes quasi-quotes) + (HsUntypedSplice p) + -- ^ Splice Pattern (Includes quasi-quotes @$(...)@) + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId': + -- 'GHC.Parser.Annotation.AnnOpen' @'$('@ + -- 'GHC.Parser.Annotation.AnnClose' @')'@ + + -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation ------------ Literal and n+k patterns --------------- | LitPat (XLitPat p) - (HsLit p) -- ^ Literal Pattern - -- Used for *non-overloaded* literal patterns: - -- Int#, Char#, Int, Char, String, etc. - - | NPat -- Natural Pattern - -- Used for all overloaded literals, - -- including overloaded strings with -XOverloadedStrings - (XNPat p) -- Overall type of pattern. Might be + (HsLit p) + -- ^ Literal Pattern + -- + -- Used for __non-overloaded__ literal patterns: + -- Int#, Char#, Int, Char, String, etc. + + | NPat (XNPat p) -- Overall type of pattern. Might be -- different than the literal's type -- if (==) or negate changes the type (XRec p (HsOverLit p)) -- ALWAYS positive @@ -194,7 +206,8 @@ data Pat p -- otherwise (SyntaxExpr p) -- Equality checker, of type t->t->Bool - -- ^ Natural Pattern + -- ^ Natural Pattern, used for all overloaded literals, including overloaded Strings + -- with @-XOverloadedStrings@ -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnVal' @'+'@ @@ -208,30 +221,35 @@ data Pat p (SyntaxExpr p) -- (>=) function, of type t1->t2->Bool (SyntaxExpr p) -- Name of '-' (see GHC.Rename.Env.lookupSyntax) - -- ^ n+k pattern + -- ^ n+k pattern, e.g. @n+1@, enabled by @-XNPlusKPatterns@ extension ------------ Pattern type signatures --------------- - -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' - -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | SigPat (XSigPat p) -- After typechecker: Type (LPat p) -- Pattern with a type signature (HsPatSigType (NoGhcTc p)) -- Signature can bind both -- kind and type vars - -- ^ Pattern with a type signature + -- ^ Pattern with a type signature, e.g. @x :: Int@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' + + -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation - -- Embed the syntax of types into patterns. - -- Used with RequiredTypeArguments, e.g. fn (type t) = rhs - | EmbTyPat (XEmbTyPat p) + | -- | Embed the syntax of types into patterns. + -- Used with @-XRequiredTypeArguments@, e.g. @fn (type t) = rhs@ + EmbTyPat (XEmbTyPat p) (HsTyPat (NoGhcTc p)) - -- See Note [Invisible binders in functions] in GHC.Hs.Pat | InvisPat (XInvisPat p) (HsTyPat (NoGhcTc p)) + -- ^ Type abstraction which brings into scope type variables associated with invisible forall. Used by @-XTypeAbstractions at . + -- + -- The location of @\@@ is captured by 'GHC.Parser.Annotation.EpToken' @"\@"@ + + -- See Note [Invisible binders in functions] in GHC.Hs.Pat - -- Extension point; see Note [Trees That Grow] in Language.Haskell.Syntax.Extension - | XPat - !(XXPat p) + | -- | TTG Extension point; see Note [Trees That Grow] in Language.Haskell.Syntax.Extension + XPat !(XXPat p) type family ConLikeP x @@ -311,7 +329,7 @@ type HsRecUpdField p q = HsFieldBind (LAmbiguousFieldOcc p) (LHsExpr q) -- | Haskell Field Binding -- --- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnEqual', +-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnEqual' -- -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation data HsFieldBind lhs rhs = HsFieldBind { ===================================== libraries/base/tests/all.T ===================================== @@ -189,6 +189,7 @@ test('CatEntail', normal, compile, ['']) # When running with WAY=ghci and profiled ways, T7653 uses a lot of memory. test('T7653', [when(opsys('mingw32'), skip), + when(arch('wasm32'), run_timeout_multiplier(5)), omit_ways(prof_ways + ghci_ways)], compile_and_run, ['']) test('T7787', normal, compile_and_run, ['']) ===================================== testsuite/tests/driver/objc/all.T ===================================== @@ -1,11 +1,13 @@ test('objc-hi', [ unless(opsys('darwin'), skip), + when(config.target_wrapper is not None, skip), objc_src, expect_fail_for(['ghci']) ], compile_and_run, ['-framework Foundation']) test('objcxx-hi', [ unless(opsys('darwin'), skip), + when(config.target_wrapper is not None, skip), objcxx_src, expect_fail_for(['ghci']) ], compile_and_run, ['-framework Foundation -lc++']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/058a7c774aee9eb53563c110e88795d499874cf8...0aa54bc5792d5487e3fa6d57ca026ba94c83e96a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/058a7c774aee9eb53563c110e88795d499874cf8...0aa54bc5792d5487e3fa6d57ca026ba94c83e96a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 16:32:10 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 07 Jun 2024 12:32:10 -0400 Subject: [Git][ghc/ghc][wip/T24676] Two small bu tsignificant changes to try: Message-ID: <6663360aa20db_1b2a63da08d81092b7@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24676 at Glasgow Haskell Compiler / GHC Commits: 499a71b2 by Simon Peyton Jones at 2024-06-07T17:30:21+01:00 Two small bu tsignificant changes to try: * Use simpleUnifyCheck in qlUnify rather than duplicating it. * Allow qlUnify to unify regular unification variables, if it finds an opportunity to do so. - - - - - 3 changed files: - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Utils/Unify.hs Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -1897,7 +1897,8 @@ qlUnify ty1 ty2 -- The TyVarSets give the variables bound by enclosing foralls -- for the corresponding type. Don't unify with these. go (TyVarTy tv) ty2 - | isQLInstTyVar tv = go_kappa tv ty2 +-- | isQLInstTyVar tv = go_kappa tv ty2 + | isMetaTyVar tv = go_kappa tv ty2 -- Only unify QL instantiation variables -- See (UQL3) in Note [QuickLook unification] go ty1 (TyVarTy tv) @@ -1961,17 +1962,15 @@ qlUnify ty1 ty2 -- otherwise we'll fail to unify and emit a coercion. -- Just an optimisation: emitting a coercion is fine go_flexi kappa (TyVarTy tv2) - | isQLInstTyVar tv2, lhsPriority tv2 > lhsPriority kappa +-- | isQLInstTyVar tv2, lhsPriority tv2 > lhsPriority kappa + | lhsPriority tv2 > lhsPriority kappa = go_flexi1 tv2 (TyVarTy kappa) go_flexi kappa ty2 = go_flexi1 kappa ty2 go_flexi1 kappa ty2 -- ty2 is zonked | -- See Note [QuickLook unification] (UQL1) - Just ty2 <- occCheckExpand [kappa] ty2 - -- Passes the occurs check - , not (isConcreteTyVar kappa) || isConcreteType ty2 - -- Don't unify a concrete instantiation variable with a non-concrete type + simpleUnifyCheck UC_QuickLook kappa ty2 = do { co <- unifyKind (Just (TypeThing ty2)) ty2_kind kappa_kind -- unifyKind: see (UQL2) in Note [QuickLook unification] ; let ty2' = mkCastTy ty2 co @@ -2020,7 +2019,7 @@ That is the entire point of qlUnify! Wrinkles: (UQL3) qlUnify (and Quick Look generally) is only unifies instantiation variables, not regular unification variables. Why? Nothing fundamental. - We would need to + ToDo: unfinished Because instantiation variables don't really have a settled level yet; they have level QLInstVar (see Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -2087,8 +2087,7 @@ checkTouchableTyVarEq -- with extra wanteds 'cts' -- If it returns (PuFail reason) we can't unify, and the reason explains why. checkTouchableTyVarEq ev lhs_tv rhs - | simpleUnifyCheck True lhs_tv rhs - -- True <=> type families are ok on the RHS + | simpleUnifyCheck UC_Solver lhs_tv rhs = do { traceTcS "checkTouchableTyVarEq: simple-check wins" (ppr lhs_tv $$ ppr rhs) ; return (pure (mkReflRedn Nominal rhs)) } ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -42,7 +42,8 @@ module GHC.Tc.Utils.Unify ( checkTyEqRhs, recurseIntoTyConApp, PuResult(..), failCheckWith, okCheckRefl, mapCheck, TyEqFlags(..), TyEqFamApp(..), AreUnifying(..), LevelCheck(..), FamAppBreaker, - famAppArgFlags, simpleUnifyCheck, checkPromoteFreeVars, + famAppArgFlags, checkPromoteFreeVars, + simpleUnifyCheck, UnifyCheckCaller(..), fillInferResult, ) where @@ -2449,7 +2450,7 @@ uUnfilledVar2 env@(UE { u_defer = def_eq_ref }) swapped tv1 ty2 -- Here we don't know about given equalities here; so we treat -- /any/ level outside this one as untouchable. Hence cur_lvl. ; if not (touchabilityAndShapeTest cur_lvl tv1 ty2 - && simpleUnifyCheck False tv1 ty2) + && simpleUnifyCheck UC_OnTheFly tv1 ty2) then not_ok_so_defer cur_lvl else do { def_eqs <- readTcRef def_eq_ref -- Capture current state of def_eqs @@ -2487,7 +2488,7 @@ uUnfilledVar2 env@(UE { u_defer = def_eq_ref }) swapped tv1 ty2 do { traceTc "uUnfilledVar2 not ok" $ vcat [ text "tv1:" <+> ppr tv1 , text "ty2:" <+> ppr ty2 - , text "simple-unify-chk:" <+> ppr (simpleUnifyCheck False tv1 ty2) + , text "simple-unify-chk:" <+> ppr (simpleUnifyCheck UC_OnTheFly tv1 ty2) , text "touchability:" <+> ppr (touchabilityAndShapeTest cur_lvl tv1 ty2)] -- Occurs check or an untouchable: just defer -- NB: occurs check isn't necessarily fatal: @@ -2876,10 +2877,13 @@ matchExpectedFunKind hs_ty n k = go n k * * ********************************************************************* -} -simpleUnifyCheck :: Bool -- True <=> called from constraint solver - -- False <=> called from on-the-fly unifier - -> TcTyVar -> TcType -> Bool --- A fast check: True <=> unification is OK +data UnifyCheckCaller + = UC_OnTheFly -- Called from the on-the-fly unifier + | UC_QuickLook -- Called from Quick Look + | UC_Solver -- Called from constraint solver + +simpleUnifyCheck :: UnifyCheckCaller -> TcTyVar -> TcType -> Bool +-- simpleUnifyCheck does a fast check: True <=> unification is OK -- If it says 'False' then unification might still be OK, but -- it'll take more work to do -- use the full checkTypeEq -- @@ -2891,7 +2895,7 @@ simpleUnifyCheck :: Bool -- True <=> called from constraint solver -- * Does a level-check for type variables -- -- This function is pretty heavily used, so it's optimised not to allocate -simpleUnifyCheck called_from_solver lhs_tv rhs +simpleUnifyCheck caller lhs_tv rhs = go rhs where @@ -2899,8 +2903,15 @@ simpleUnifyCheck called_from_solver lhs_tv rhs lhs_tv_lvl = tcTyVarLevel lhs_tv lhs_tv_is_concrete = isConcreteTyVar lhs_tv - forall_ok = isRuntimeUnkTyVar lhs_tv - fam_ok = called_from_solver + + forall_ok = case caller of + UC_QuickLook -> isQLInstTyVar lhs_tv + _ -> isRuntimeUnkTyVar lhs_tv + + fam_ok = case caller of + UC_Solver -> True + UC_QuickLook -> False + UC_OnTheFly -> False go (TyVarTy tv) | lhs_tv == tv = False View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/499a71b2f9db6b2c1c43b0b0c91aaa1364bf0196 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/499a71b2f9db6b2c1c43b0b0c91aaa1364bf0196 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 17:45:38 2024 From: gitlab at gitlab.haskell.org (Torsten Schmits (@torsten.schmits)) Date: Fri, 07 Jun 2024 13:45:38 -0400 Subject: [Git][ghc/ghc][wip/torsten.schmits/cross-package-objects] 2 commits: refactor again Message-ID: <66634742e5dc_1b2a646dcc941190e5@gitlab.mail> Torsten Schmits pushed to branch wip/torsten.schmits/cross-package-objects at Glasgow Haskell Compiler / GHC Commits: 40e6626d by Torsten Schmits at 2024-06-07T19:44:54+02:00 refactor again - - - - - 7cad5a6f by Torsten Schmits at 2024-06-07T19:45:24+02:00 only hydrate needed bindings - - - - - 4 changed files: - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Linker/Loader.hs - testsuite/tests/th/cross-package/CrossDep.hs - testsuite/tests/th/cross-package/all.T Changes: ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -41,7 +41,7 @@ module GHC.Iface.Syntax ( -- Free Names freeNamesIfDecl, freeNamesIfRule, freeNamesIfFamInst, - freeNamesIfConDecls, + freeNamesIfConDecls, freeNamesIfExpr, -- Pretty printing pprIfaceExpr, ===================================== compiler/GHC/Linker/Loader.hs ===================================== @@ -117,6 +117,10 @@ import GHC.Unit.Module.ModSummary (ModSummary(..)) import GHC.Unit.Module.WholeCoreBindings (WholeCoreBindings(..)) import Control.Monad.Trans.State.Strict (StateT(..), state) import GHC.Utils.Misc (modificationTimeIfExists) +import qualified Data.Map.Strict as Map +import Data.Foldable (toList) +import GHC.Iface.Syntax +import GHC.Types.Name.Set (unionNameSets, mkNameSet, intersectsNameSet, intersectNameSet, elemNameSet) -- Note [Linkers and loaders] -- ~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -206,7 +210,7 @@ loadName interp hsc_env name = do (pls, links, pkgs) <- if not (isExternalName name) then return (pls0, [], emptyUDFM) else do - (pls', ok, links, pkgs) <- loadDependencies interp hsc_env pls0 undefined noSrcSpan + (pls', ok, links, pkgs) <- loadDependencies interp hsc_env pls0 noSrcSpan [nameModule name] if failed ok then throwGhcExceptionIO (ProgramError "") @@ -227,46 +231,78 @@ loadDependencies :: Interp -> HscEnv -> LoaderState - -> (ModIface -> Linkable -> IO Linkable) -> SrcSpan -> [Module] -> IO (LoaderState, SuccessFlag, [Linkable], PkgsLoaded) -- ^ returns the set of linkables required -- When called, the loader state must have been initialized (see `initLoaderState`) -loadDependencies interp hsc_env pls hydrate span needed_mods = do +loadDependencies interp hsc_env pls span needed_mods = do let opts = initLinkDepsOpts hsc_env -- Find what packages and linkables are required deps <- getLinkDeps opts interp pls span needed_mods - -- Load bytecode from interface files in the package db - let s0 = LIBC {libc_loader = pls, libc_seen = emptyUniqDSet} - handlers = libc_handlers interp hsc_env hydrate - load_bc = loadIfacesByteCode handlers (ldNeededLinkables deps) - - (links_needed, LIBC {libc_loader = pls1}) <- - initIfaceCheck (text "loader") hsc_env $ - runStateT load_bc s0 - let this_pkgs_needed = ldNeededUnits deps -- Link the packages and modules required - pls2 <- loadPackages' interp hsc_env (ldUnits deps) pls1 - (pls3, succ) <- loadModuleLinkables interp hsc_env pls2 links_needed + pls1 <- loadPackages' interp hsc_env (ldUnits deps) pls + (pls2, succ) <- loadModuleLinkables interp hsc_env pls1 (ldNeededLinkables deps) let this_pkgs_loaded = udfmRestrictKeys all_pkgs_loaded $ getUniqDSet trans_pkgs_needed - all_pkgs_loaded = pkgs_loaded pls3 + all_pkgs_loaded = pkgs_loaded pls2 trans_pkgs_needed = unionManyUniqDSets (this_pkgs_needed : [ loaded_pkg_trans_deps pkg | pkg_id <- uniqDSetToList this_pkgs_needed , Just pkg <- [lookupUDFM all_pkgs_loaded pkg_id] ]) - dbg "loadDependencies" [ - ("needed_mods", ppr needed_mods), - ("objs_loaded", ppr (objs_loaded pls3)), - ("links_needed pre hydrate", ppr (ldNeededLinkables deps)), - ("links_needed post hydrate", ppr links_needed), - ("ldUnits", ppr (ldUnits deps)) - ] - return (pls3, succ, ldAllLinkables deps, this_pkgs_loaded) + return (pls2, succ, ldAllLinkables deps, this_pkgs_loaded) +loadByteCodeDependencies + :: Interp + -> HscEnv + -> LoaderState + -> (ModIface -> Linkable -> IO Linkable) + -> SrcSpan + -> [Unlinked] + -> IO (LoaderState, SuccessFlag, [Linkable], PkgsLoaded) +loadByteCodeDependencies interp hsc_env pls hydrate span needed = do + -- Load bytecode from interface files in the package db + (hydrated, CBLoaderState {cbl_loader = pls1, cbl_unavailable}) <- + initIfaceCheck (text "loader") hsc_env $ + runStateT (loadDepsFromCoreBindings handlers needed) s0 + + -- TODO call loadDependencies here with the modules we couldn't hydrate + -- Find what packages and linkables are required + let opts = initLinkDepsOpts hsc_env + deps <- getLinkDeps opts interp pls span (uniqDSetToList cbl_unavailable) + dbg "loadByteCodeDependencies" [ + ("unavailable modules", ppr cbl_unavailable), + ("needed linkables native", ppr (ldNeededLinkables deps)), + ("hydrated", ppr hydrated), + ("ldUnits", ppr (ldUnits deps)) + ] + + let this_pkgs_needed = ldNeededUnits deps + links_needed = hydrated ++ ldNeededLinkables deps + + -- Link the packages and modules required + pls2 <- loadPackages' interp hsc_env (ldUnits deps) pls1 + (pls3, succ) <- loadModuleLinkables interp hsc_env pls2 links_needed + let this_pkgs_loaded = udfmRestrictKeys all_pkgs_loaded $ getUniqDSet trans_pkgs_needed + all_pkgs_loaded = pkgs_loaded pls3 + trans_pkgs_needed = unionManyUniqDSets (this_pkgs_needed : [ loaded_pkg_trans_deps pkg + | pkg_id <- uniqDSetToList this_pkgs_needed + , Just pkg <- [lookupUDFM all_pkgs_loaded pkg_id] + ]) + dbg "loadByteCodeDependencies end" [ + ("objs_loaded", ppr (objs_loaded pls3)) + ] + return (pls3, succ, links_needed, this_pkgs_loaded) + where + s0 = + CBLoaderState { + cbl_loader = pls, + cbl_seen = emptyUniqDSet, + cbl_unavailable = emptyUniqDSet + } + handlers = cbl_handlers hsc_env hydrate -- | Temporarily extend the loaded env. withExtendedLoadedEnv @@ -309,6 +345,225 @@ showLoaderState interp = do return $ withPprStyle defaultDumpStyle $ vcat (text "----- Loader state -----":docs) +{- ********************************************************************** + + Loading whole core bindings + + ********************************************************************* -} + +cbload_mod_summary :: + Module -> + ModLocation -> + ModIface -> + IO ModSummary +cbload_mod_summary mod loc at ModLocation {..} ModIface {..} = do + hi_date <- modificationTimeIfExists ml_hi_file + hie_date <- modificationTimeIfExists ml_hie_file + o_mod <- modificationTimeIfExists ml_obj_file + dyn_o_mod <- modificationTimeIfExists ml_dyn_obj_file + pure ModSummary { + ms_mod = mod, + ms_hsc_src = mi_hsc_src, + ms_hspp_file = undefined, + ms_hspp_opts = undefined, + ms_hspp_buf = undefined, + ms_location = loc, + ms_hs_hash = mi_src_hash, + ms_obj_date = o_mod, + ms_dyn_obj_date = dyn_o_mod, + ms_parsed_mod = Nothing, + ms_iface_date = hi_date, + ms_hie_date = hie_date, + -- TODO this needs imports parsing and is accessed by our new logic + ms_ghc_prim_import = False, + ms_textual_imps = [], + ms_srcimps = [] + } + +loadByteCode :: ModLocation -> ModIface -> ModSummary -> IO (Maybe Linkable) +loadByteCode loc iface mod_sum = do + let + this_mod = mi_module iface + if_date = fromJust $ ms_iface_date mod_sum + case mi_extra_decls iface of + Just extra_decls -> do + let fi = WholeCoreBindings extra_decls this_mod loc + return (Just (LM if_date this_mod [CoreBindings fi])) + _ -> pure Nothing + +data CBLoaderState = + CBLoaderState { + cbl_loader :: LoaderState, + cbl_seen :: UniqDSet Name, + cbl_unavailable :: UniqDSet Module + } + +data CBLoaderHandlers = + CBLoaderHandlers { + cbl_find :: Module -> IO InstalledFindResult, + cbl_hydrate :: ModIface -> Linkable -> IO Linkable + } + +cbl_handlers :: + HscEnv -> + (ModIface -> Linkable -> IO Linkable) -> + CBLoaderHandlers +cbl_handlers hsc_env cbl_hydrate = + CBLoaderHandlers {cbl_find, cbl_hydrate} + where + unit_state = hsc_units hsc_env + fc = hsc_FC hsc_env + mhome_unit = hsc_home_unit_maybe hsc_env + dflags = hsc_dflags hsc_env + fopts = initFinderOpts dflags + other_fopts = initFinderOpts . homeUnitEnv_dflags <$> (hsc_HUG hsc_env) + + cbl_find mod = + findExactModule fc fopts other_fopts unit_state mhome_unit + (mkModule (moduleUnitId mod) (moduleName mod)) + +wcb_closure :: + MonadIO m => + [Name] -> + WholeCoreBindings -> + m WholeCoreBindings +wcb_closure names (WholeCoreBindings cbs m l) = do + dbg "wcb_closure" [ + ("cbs", ppr cbs), + ("names", ppr names), + ("top_names", ppr top_names), + ("used_top_names", ppr used_top_names), + ("all_used_names", ppr all_used_names), + ("all_used_binders", ppr all_used_binders), + ("wcb_c", ppr wcb_c) + ] + pure (WholeCoreBindings wcb_c m l) + where + wcb_c = fst <$> all_used_binders + all_used_binders = filter (has_used_name . snd) cbsn + has_used_name used = intersectsNameSet used all_used_names + + all_used_names = unionNameSets (used_top_names : (used_names_iface_binder . fst <$> used_top_binders)) + used_names_iface_binder = \case + IfaceNonRec _ r -> used_names r + IfaceRec bs -> unionNameSets (used_names . snd <$> bs) + used_names = \case + IfRhs r -> freeNamesIfExpr r + _ -> mempty + + used_top_binders = filter (is_used_iface_binder . fst) cbsn + is_used_iface_binder = \case + IfaceNonRec b _ -> is_used_binder b + IfaceRec bs -> any (is_used_binder . fst) bs + is_used_binder = \case + IfGblTopBndr name -> elemNameSet name used_top_names + IfLclTopBndr {} -> False + + cbsn = with_names <$> cbs + with_names ib = case ib of + IfaceNonRec b _ -> (ib, mkNameSet (binder_names b)) + IfaceRec bs -> (ib, mkNameSet (concatMap (binder_names . fst) bs)) + + used_top_names = intersectNameSet names_set top_names + top_names = mkNameSet (concatMap binder_names (concatMap toList cbs)) + binder_names = \case + IfGblTopBndr name -> [name] + IfLclTopBndr {} -> [] + names_set = mkNameSet names + +loadModuleNamesFromCoreBindings :: + CBLoaderHandlers -> + Module -> + [Name] -> + StateT CBLoaderState IfG [Linkable] +loadModuleNamesFromCoreBindings handlers at CBLoaderHandlers {..} mod names = do + iface <- lift $ loadSysInterface load_doc mod + find_res <- liftIO (cbl_find mod) + dbg "loadIfaceByteCode" [ + ("mod", ppr mod), + ("iface", ppr (mi_module iface)) + ] + loaded <- case find_res of + InstalledFound loc _ -> do + summ <- liftIO $ cbload_mod_summary mod loc iface + liftIO (loadByteCode loc iface summ) >>= \case + Just wcb_linkable at LM {linkableUnlinked = [CoreBindings wcb]} -> do + wcb' <- wcb_closure names wcb + hydrated <- liftIO $ cbl_hydrate iface (wcb_linkable { linkableUnlinked = [CoreBindings wcb']}) + let hydrated_bcos = unwrap_hydrated (linkableUnlinked hydrated) + complete <- loadDepsFromCoreBindings handlers hydrated_bcos + dbg "loadIfaceByteCode found" [ + ("hi", text (ml_hi_file loc)), + ("hydrated", ppr wcb_linkable), + ("hydrated_bcos", ppr hydrated_bcos), + ("complete", ppr complete) + ] + pure (Just (hydrated : complete)) + _ -> do + dbg "loadIfaceByteCode no whole core bindings" [] + pure Nothing + result -> do + dbg "loadIfaceByteCode not found" [("result", debugFr result)] + pure Nothing + case loaded of + Just lnks -> pure lnks + Nothing -> + state $ \ s -> + ([], s {cbl_unavailable = addOneToUniqDSet (cbl_unavailable s) mod}) + where + load_doc = text "Loading core bindings of splice dependencies" + + debugFr = \case + InstalledFound _ _ -> text "found" + InstalledNoPackage u -> text "NoPackage " <+> ppr u + InstalledNotFound paths pkg -> vcat [ + text "paths:" <+> brackets (hsep (text <$> paths)), + text "pkg:" <+> ppr pkg + ] + + unwrap_hydrated = concatMap $ \case + LoadedBCOs u -> unwrap_hydrated u + u -> [u] + +byte_code_deps :: [Unlinked] -> UniqDSet Name +byte_code_deps code = + filterUniqDSet loadable (unionManyUniqDSets (linkables_deps code)) + where + linkables_deps = concatMap linkable_deps + + linkable_deps = \case + BCOs cbc _ -> [bco_free_names cbc] + LoadedBCOs l -> linkables_deps l + _ -> [emptyUniqDSet] + + loadable n = + isExternalName n && + not (isWiredInName n) + + bco_free_names cbc = + foldr (unionUniqDSets . bcoFreeNames) emptyUniqDSet (bc_bcos cbc) + +loadNamesFromCoreBindings :: + CBLoaderHandlers -> + UniqDSet Name -> + StateT CBLoaderState IfG [Linkable] +loadNamesFromCoreBindings handlers all_names = do + names <- state (filter_deps all_names) + let + with_module = [(nameModule n, [n]) | n <- uniqDSetToList names] + by_module = Map.toList (Map.fromListWith (++) with_module) + concat <$> traverse (uncurry (loadModuleNamesFromCoreBindings handlers)) by_module + where + filter_deps new s at CBLoaderState {cbl_seen} = + (minusUniqDSet new cbl_seen, s {cbl_seen = unionUniqDSets new cbl_seen}) + +loadDepsFromCoreBindings :: + CBLoaderHandlers -> + [Unlinked] -> + StateT CBLoaderState IfG [Linkable] +loadDepsFromCoreBindings handlers code = + loadNamesFromCoreBindings handlers (byte_code_deps code) + {- ********************************************************************** @@ -638,7 +893,7 @@ loadExpr interp hsc_env span root_ul_bco = do -- Take lock for the actual work. modifyLoaderState interp $ \pls0 -> do -- Load the packages and modules required - (pls, ok, _, _) <- loadDependencies interp hsc_env pls0 undefined span needed_mods + (pls, ok, _, _) <- loadDependencies interp hsc_env pls0 span needed_mods if failed ok then throwGhcExceptionIO (ProgramError "") else do @@ -691,155 +946,6 @@ initLinkDepsOpts hsc_env = opts ********************************************************************* -} -mod_summary :: - Module -> - ModLocation -> - ModIface -> - IO ModSummary -mod_summary mod loc at ModLocation {..} ModIface {..} = do - hi_date <- modificationTimeIfExists ml_hi_file - hie_date <- modificationTimeIfExists ml_hie_file - o_mod <- modificationTimeIfExists ml_obj_file - dyn_o_mod <- modificationTimeIfExists ml_dyn_obj_file - pure ModSummary { - ms_mod = mod, - ms_hsc_src = mi_hsc_src, - ms_hspp_file = undefined, - ms_hspp_opts = undefined, - ms_hspp_buf = undefined, - ms_location = loc, - ms_hs_hash = mi_src_hash, - ms_obj_date = o_mod, - ms_dyn_obj_date = dyn_o_mod, - ms_parsed_mod = Nothing, - ms_iface_date = hi_date, - ms_hie_date = hie_date, - -- TODO this needs imports parsing and is accessed by our new logic - ms_ghc_prim_import = False, - ms_textual_imps = [], - ms_srcimps = [] - } - -loadByteCode :: ModLocation -> ModIface -> ModSummary -> IO (Maybe Linkable) -loadByteCode loc iface mod_sum = do - let - this_mod = mi_module iface - if_date = fromJust $ ms_iface_date mod_sum - case mi_extra_decls iface of - Just extra_decls -> do - let fi = WholeCoreBindings extra_decls this_mod loc - return (Just (LM if_date this_mod [CoreBindings fi])) - _ -> pure Nothing - -data LIBC = - LIBC { - libc_loader :: LoaderState, - libc_seen :: UniqDSet Module - } - -data LIBCHandlers = - LIBCHandlers { - libc_find :: Module -> IO InstalledFindResult, - libc_hydrate :: ModIface -> Linkable -> IO Linkable, - libc_link :: forall m . MonadIO m => [Linkable] -> StateT LIBC m () - } - -libc_handlers :: - Interp -> - HscEnv -> - (ModIface -> Linkable -> IO Linkable) -> - LIBCHandlers -libc_handlers interp hsc_env libc_hydrate = - LIBCHandlers {libc_find, libc_hydrate, libc_link} - where - unit_state = hsc_units hsc_env - fc = hsc_FC hsc_env - mhome_unit = Nothing - -- This would search in the home unit as well, but we don't need to load - -- core bindings for that. - -- mhome_unit = hsc_home_unit_maybe hsc_env - dflags = hsc_dflags hsc_env - fopts = initFinderOpts dflags - other_fopts = initFinderOpts . homeUnitEnv_dflags <$> (hsc_HUG hsc_env) - - libc_find mod = - findExactModule fc fopts other_fopts unit_state mhome_unit - (mkModule (moduleUnitId mod) (moduleName mod)) - - libc_link :: forall m . MonadIO m => [Linkable] -> StateT LIBC m () - libc_link linkables = StateT $ \ s -> do - pls <- liftIO $ dynLinkBCOs interp (libc_loader s) linkables - pure ((), s {libc_loader = pls}) - -loadIfaceByteCode :: - LIBCHandlers -> - Module -> - StateT LIBC IfG [Linkable] -loadIfaceByteCode handlers at LIBCHandlers {..} mod = do - iface <- lift $ loadSysInterface load_doc mod - find_res <- liftIO (libc_find mod) - dbg "loadIfaceByteCode" [ - ("mod", ppr mod), - ("iface", ppr (mi_module iface)) - ] - case find_res of - (InstalledFound loc _) -> do - summ <- liftIO $ mod_summary mod loc iface - l <- liftIO $ loadByteCode loc iface summ - lh <- liftIO $ maybeToList <$> traverse (libc_hydrate iface) l - lh1 <- loadIfacesByteCode handlers lh - dbg "loadIfaceByteCode found" [ - ("hi", text (ml_hi_file loc)), - ("loaded", ppr lh), - ("loaded recursive", ppr lh1) - ] - libc_link lh1 - pure lh1 - result -> do - dbg "loadIfaceByteCode not found" [("result", debugFr result)] - pure [] - where - load_doc = text "Loading core bindings of splice dependencies" - - debugFr = \case - InstalledFound _ _ -> text "found" - InstalledNoPackage u -> text "NoPackage " <+> ppr u - InstalledNotFound paths pkg -> vcat [ - text "paths:" <+> brackets (hsep (text <$> paths)), - text "pkg:" <+> ppr pkg - ] - -loadIfacesByteCode :: - LIBCHandlers -> - [Linkable] -> - StateT LIBC IfG [Linkable] -loadIfacesByteCode handlers lnks = do - all <- state (filter_deps all_deps) - lnks1 <- traverse (loadIfaceByteCode handlers) (uniqDSetToList all) - pure (mconcat (lnks : lnks1)) - where - all_deps = linkables_deps (concatMap linkableUnlinked lnks) - - linkables_deps = unionManyUniqDSets . fmap linkable_deps - - linkable_deps = \case - BCOs cbc _ -> - mapUniqDSet nameModule $ filterUniqDSet loadable (bco_free_names cbc) - LoadedBCOs l -> linkables_deps l - _ -> emptyUniqDSet - - loadable n = - isExternalName n && - not (isWiredInName n) && - not (moduleUnitId (nameModule n) `elem` wiredInUnitIds) - - bco_free_names cbc = - foldr (unionUniqDSets . bcoFreeNames) emptyUniqDSet (bc_bcos cbc) - - filter_deps new s at LIBC {libc_seen} = - (minusUniqDSet new libc_seen, s {libc_seen = unionUniqDSets new libc_seen}) - - loadDecls :: Interp -> HscEnv -> @@ -856,7 +962,8 @@ loadDecls interp hsc_env hydrate span cbc at CompiledByteCode{..} = do -- Take lock for the actual work. modifyLoaderState interp $ \pls0 -> do -- Link the packages and modules required - (pls, ok, links_needed, units_needed) <- loadDependencies interp hsc_env pls0 hydrate span needed_mods + (pls, ok, links_needed, units_needed) <- + loadByteCodeDependencies interp hsc_env pls0 hydrate span [BCOs cbc []] if failed ok then throwGhcExceptionIO (ProgramError "") else do @@ -871,19 +978,6 @@ loadDecls interp hsc_env hydrate span cbc at CompiledByteCode{..} = do let ce2 = extendClosureEnv (closure_env le2) nms_fhvs !pls2 = pls { linker_env = le2 { closure_env = ce2 } } return (pls2, (nms_fhvs, links_needed, units_needed)) - where - free_names = uniqDSetToList $ - foldr (unionUniqDSets . bcoFreeNames) emptyUniqDSet bc_bcos - - needed_mods :: [Module] - needed_mods = [ nameModule n | n <- free_names, - isExternalName n, -- Names from other modules - not (isWiredInName n) -- Exclude wired-in names - ] -- (see note below) - -- Exclude wired-in names because we may not have read - -- their interface files, so getLinkDeps will fail - -- All wired-in names are in the base package, which we link - -- by default, so we can safely ignore them here. {- ********************************************************************** @@ -895,7 +989,7 @@ loadModule :: Interp -> HscEnv -> Module -> IO () loadModule interp hsc_env mod = do initLoaderState interp hsc_env modifyLoaderState_ interp $ \pls -> do - (pls', ok, _, _) <- loadDependencies interp hsc_env pls undefined noSrcSpan [mod] + (pls', ok, _, _) <- loadDependencies interp hsc_env pls noSrcSpan [mod] if failed ok then throwGhcExceptionIO (ProgramError "could not load module") else return pls' @@ -927,7 +1021,7 @@ loadModuleLinkables interp hsc_env pls linkables return (pls1, Failed) else do pls2 <- dynLinkBCOs interp pls1 bcos - dbg "after dynLinkBCOs" [("loader state", pprLoaderState pls2)] + dbg "loadModuleLinkables, after dynLinkBCOs" [("loader state", pprLoaderState pls2)] return (pls2, Succeeded) ===================================== testsuite/tests/th/cross-package/CrossDep.hs ===================================== @@ -2,5 +2,14 @@ module CrossDep where data A = A Int +used :: Int +used = 9681 + dep :: A -dep = A 9681 +dep = A used + +unused1 :: A +unused1 = A 1 + +unused2 :: A +unused2 = unused1 ===================================== testsuite/tests/th/cross-package/all.T ===================================== @@ -7,5 +7,5 @@ test( ], # multimod_compile_and_run, multimod_compile, - ['Cross', '-package-db db -fprefer-byte-code -fbyte-code-and-object-code -package dep -v0'], + ['Cross', '-O0 -package-db db -fprefer-byte-code -fbyte-code-and-object-code -package dep -v0'], ) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b2c0184ca764e2e5b1d77acad7374cd2f8ec79f0...7cad5a6f0851470356c6f5996fe7336ebede9347 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b2c0184ca764e2e5b1d77acad7374cd2f8ec79f0...7cad5a6f0851470356c6f5996fe7336ebede9347 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 18:46:07 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 07 Jun 2024 14:46:07 -0400 Subject: [Git][ghc/ghc][master] 2 commits: StgToCmm: refactor opTranslate and friends Message-ID: <6663556f434f2_1b2a64f94c24126061@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 4 changed files: - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/Driver/Config/StgToCmm.hs - compiler/GHC/StgToCmm/Config.hs - compiler/GHC/StgToCmm/Prim.hs Changes: ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -94,12 +94,6 @@ is32BitPlatform = do platform <- getPlatform return $ target32Bit platform -expect32BitPlatform :: SDoc -> NatM () -expect32BitPlatform doc = do - is32Bit <- is32BitPlatform - when (not is32Bit) $ - pprPanic "Expecting 32-bit platform" doc - sse2Enabled :: NatM Bool sse2Enabled = do config <- getConfig @@ -2475,35 +2469,10 @@ genSimplePrim bid MO_F64_Acosh [dst] [src] = genLibCCall bid genSimplePrim bid MO_F64_Atanh [dst] [src] = genLibCCall bid (fsLit "atanh") [dst] [src] genSimplePrim bid MO_SuspendThread [tok] [rs,i] = genRTSCCall bid (fsLit "suspendThread") [tok] [rs,i] genSimplePrim bid MO_ResumeThread [rs] [tok] = genRTSCCall bid (fsLit "resumeThread") [rs] [tok] -genSimplePrim _ MO_I64_ToI [dst] [src] = genInt64ToInt dst src -genSimplePrim _ MO_I64_FromI [dst] [src] = genIntToInt64 dst src -genSimplePrim _ MO_W64_ToW [dst] [src] = genWord64ToWord dst src -genSimplePrim _ MO_W64_FromW [dst] [src] = genWordToWord64 dst src -genSimplePrim _ MO_x64_Neg [dst] [src] = genNeg64 dst src -genSimplePrim _ MO_x64_Add [dst] [x,y] = genAdd64 dst x y -genSimplePrim _ MO_x64_Sub [dst] [x,y] = genSub64 dst x y -genSimplePrim bid MO_x64_Mul [dst] [x,y] = genPrimCCall bid (fsLit "hs_mul64") [dst] [x,y] genSimplePrim bid MO_I64_Quot [dst] [x,y] = genPrimCCall bid (fsLit "hs_quotInt64") [dst] [x,y] genSimplePrim bid MO_I64_Rem [dst] [x,y] = genPrimCCall bid (fsLit "hs_remInt64") [dst] [x,y] genSimplePrim bid MO_W64_Quot [dst] [x,y] = genPrimCCall bid (fsLit "hs_quotWord64") [dst] [x,y] genSimplePrim bid MO_W64_Rem [dst] [x,y] = genPrimCCall bid (fsLit "hs_remWord64") [dst] [x,y] -genSimplePrim _ MO_x64_And [dst] [x,y] = genAnd64 dst x y -genSimplePrim _ MO_x64_Or [dst] [x,y] = genOr64 dst x y -genSimplePrim _ MO_x64_Xor [dst] [x,y] = genXor64 dst x y -genSimplePrim _ MO_x64_Not [dst] [src] = genNot64 dst src -genSimplePrim bid MO_x64_Shl [dst] [x,n] = genPrimCCall bid (fsLit "hs_uncheckedShiftL64") [dst] [x,n] -genSimplePrim bid MO_I64_Shr [dst] [x,n] = genPrimCCall bid (fsLit "hs_uncheckedIShiftRA64") [dst] [x,n] -genSimplePrim bid MO_W64_Shr [dst] [x,n] = genPrimCCall bid (fsLit "hs_uncheckedShiftRL64") [dst] [x,n] -genSimplePrim _ MO_x64_Eq [dst] [x,y] = genEq64 dst x y -genSimplePrim _ MO_x64_Ne [dst] [x,y] = genNe64 dst x y -genSimplePrim _ MO_I64_Ge [dst] [x,y] = genGeInt64 dst x y -genSimplePrim _ MO_I64_Gt [dst] [x,y] = genGtInt64 dst x y -genSimplePrim _ MO_I64_Le [dst] [x,y] = genLeInt64 dst x y -genSimplePrim _ MO_I64_Lt [dst] [x,y] = genLtInt64 dst x y -genSimplePrim _ MO_W64_Ge [dst] [x,y] = genGeWord64 dst x y -genSimplePrim _ MO_W64_Gt [dst] [x,y] = genGtWord64 dst x y -genSimplePrim _ MO_W64_Le [dst] [x,y] = genLeWord64 dst x y -genSimplePrim _ MO_W64_Lt [dst] [x,y] = genLtWord64 dst x y genSimplePrim _ op dst args = do platform <- ncgPlatform <$> getConfig pprPanic "genSimplePrim: unhandled primop" (ppr (pprCallishMachOp op, dst, fmap (pdoc platform) args)) @@ -4462,231 +4431,3 @@ genQuotRem width signed res_q res_r m_arg_x_high arg_x_low arg_y = do toOL [instr format y_reg, MOV format (OpReg rax) (OpReg reg_q), MOV format (OpReg rdx) (OpReg reg_r)] - - ----------------------------------------------------------------------------- --- The following functions implement certain 64-bit MachOps inline for 32-bit --- architectures. On 64-bit architectures, those MachOps aren't supported and --- calling these functions for a 64-bit target platform is considered an error --- (hence the use of `expect32BitPlatform`). --- --- On 64-bit platforms, generic MachOps should be used instead of these 64-bit --- specific ones (e.g. use MO_Add instead of MO_x64_Add). This MachOp selection --- is done by StgToCmm. - -genInt64ToInt :: LocalReg -> CmmExpr -> NatM InstrBlock -genInt64ToInt dst src = do - expect32BitPlatform (text "genInt64ToInt") - RegCode64 code _src_hi src_lo <- iselExpr64 src - let dst_r = getLocalRegReg dst - pure $ code `snocOL` MOV II32 (OpReg src_lo) (OpReg dst_r) - -genWord64ToWord :: LocalReg -> CmmExpr -> NatM InstrBlock -genWord64ToWord dst src = do - expect32BitPlatform (text "genWord64ToWord") - RegCode64 code _src_hi src_lo <- iselExpr64 src - let dst_r = getLocalRegReg dst - pure $ code `snocOL` MOV II32 (OpReg src_lo) (OpReg dst_r) - -genIntToInt64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genIntToInt64 dst src = do - expect32BitPlatform (text "genIntToInt64") - let Reg64 dst_hi dst_lo = localReg64 dst - src_code <- getAnyReg src - pure $ src_code rax `appOL` toOL - [ CLTD II32 -- sign extend EAX in EDX:EAX - , MOV II32 (OpReg rax) (OpReg dst_lo) - , MOV II32 (OpReg rdx) (OpReg dst_hi) - ] - -genWordToWord64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genWordToWord64 dst src = do - expect32BitPlatform (text "genWordToWord64") - let Reg64 dst_hi dst_lo = localReg64 dst - src_code <- getAnyReg src - pure $ src_code dst_lo - `snocOL` XOR II32 (OpReg dst_hi) (OpReg dst_hi) - -genNeg64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genNeg64 dst src = do - expect32BitPlatform (text "genNeg64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 code src_hi src_lo <- iselExpr64 src - pure $ code `appOL` toOL - [ MOV II32 (OpReg src_lo) (OpReg dst_lo) - , MOV II32 (OpReg src_hi) (OpReg dst_hi) - , NEGI II32 (OpReg dst_lo) - , ADC II32 (OpImm (ImmInt 0)) (OpReg dst_hi) - , NEGI II32 (OpReg dst_hi) - ] - -genAdd64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genAdd64 dst x y = do - expect32BitPlatform (text "genAdd64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , ADD II32 (OpReg y_lo) (OpReg dst_lo) - , ADC II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genSub64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genSub64 dst x y = do - expect32BitPlatform (text "genSub64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , SUB II32 (OpReg y_lo) (OpReg dst_lo) - , SBB II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genAnd64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genAnd64 dst x y = do - expect32BitPlatform (text "genAnd64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , AND II32 (OpReg y_lo) (OpReg dst_lo) - , AND II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genOr64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genOr64 dst x y = do - expect32BitPlatform (text "genOr64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , OR II32 (OpReg y_lo) (OpReg dst_lo) - , OR II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genXor64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genXor64 dst x y = do - expect32BitPlatform (text "genXor64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , XOR II32 (OpReg y_lo) (OpReg dst_lo) - , XOR II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genNot64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genNot64 dst src = do - expect32BitPlatform (text "genNot64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 src_code src_hi src_lo <- iselExpr64 src - pure $ src_code `appOL` toOL - [ MOV II32 (OpReg src_lo) (OpReg dst_lo) - , MOV II32 (OpReg src_hi) (OpReg dst_hi) - , NOT II32 (OpReg dst_lo) - , NOT II32 (OpReg dst_hi) - ] - -genEq64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genEq64 dst x y = do - expect32BitPlatform (text "genEq64") - let dst_r = getLocalRegReg dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - Reg64 tmp_hi tmp_lo <- getNewReg64 - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg tmp_lo) - , MOV II32 (OpReg x_hi) (OpReg tmp_hi) - , XOR II32 (OpReg y_lo) (OpReg tmp_lo) - , XOR II32 (OpReg y_hi) (OpReg tmp_hi) - , OR II32 (OpReg tmp_lo) (OpReg tmp_hi) - , SETCC EQQ (OpReg dst_r) - , MOVZxL II8 (OpReg dst_r) (OpReg dst_r) - ] - -genNe64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genNe64 dst x y = do - expect32BitPlatform (text "genNe64") - let dst_r = getLocalRegReg dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - Reg64 tmp_hi tmp_lo <- getNewReg64 - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg tmp_lo) - , MOV II32 (OpReg x_hi) (OpReg tmp_hi) - , XOR II32 (OpReg y_lo) (OpReg tmp_lo) - , XOR II32 (OpReg y_hi) (OpReg tmp_hi) - , OR II32 (OpReg tmp_lo) (OpReg tmp_hi) - , SETCC NE (OpReg dst_r) - , MOVZxL II8 (OpReg dst_r) (OpReg dst_r) - ] - -genGtWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGtWord64 dst x y = do - expect32BitPlatform (text "genGtWord64") - genPred64 LU dst y x - -genLtWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLtWord64 dst x y = do - expect32BitPlatform (text "genLtWord64") - genPred64 LU dst x y - -genGeWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGeWord64 dst x y = do - expect32BitPlatform (text "genGeWord64") - genPred64 GEU dst x y - -genLeWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLeWord64 dst x y = do - expect32BitPlatform (text "genLeWord64") - genPred64 GEU dst y x - -genGtInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGtInt64 dst x y = do - expect32BitPlatform (text "genGtInt64") - genPred64 LTT dst y x - -genLtInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLtInt64 dst x y = do - expect32BitPlatform (text "genLtInt64") - genPred64 LTT dst x y - -genGeInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGeInt64 dst x y = do - expect32BitPlatform (text "genGeInt64") - genPred64 GE dst x y - -genLeInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLeInt64 dst x y = do - expect32BitPlatform (text "genLeInt64") - genPred64 GE dst y x - -genPred64 :: Cond -> LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genPred64 cond dst x y = do - -- we can only rely on CF/SF/OF flags! - -- Not on ZF, which doesn't take into account the lower parts. - massert (cond `elem` [LU,GEU,LTT,GE]) - - let dst_r = getLocalRegReg dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - -- Basically we perform a subtraction with borrow. - -- As we don't need to result, we can use CMP instead of SUB for the low part - -- (it sets the borrow flag just like SUB does) - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_hi) (OpReg dst_r) - , CMP II32 (OpReg y_lo) (OpReg x_lo) - , SBB II32 (OpReg y_hi) (OpReg dst_r) - , SETCC cond (OpReg dst_r) - , MOVZxL II8 (OpReg dst_r) (OpReg dst_r) - ] ===================================== compiler/GHC/Driver/Config/StgToCmm.hs ===================================== @@ -53,9 +53,12 @@ initStgToCmmConfig dflags mod = StgToCmmConfig , stgToCmmExtDynRefs = gopt Opt_ExternalDynamicRefs dflags , stgToCmmDoBoundsCheck = gopt Opt_DoBoundsChecking dflags , stgToCmmDoTagCheck = gopt Opt_DoTagInferenceChecks dflags - -- backend flags - , stgToCmmAllowBigArith = not ncg || platformArch platform == ArchWasm32 || platformArch platform == ArchX86 - , stgToCmmAllowBigQuot = not ncg || platformArch platform == ArchWasm32 + + -- backend flags: + + -- LLVM, C, and some 32-bit NCG backends can also handle some 64-bit primops + , stgToCmmAllowArith64 = w64 || not ncg || platformArch platform == ArchWasm32 || platformArch platform == ArchX86 + , stgToCmmAllowQuot64 = w64 || not ncg || platformArch platform == ArchWasm32 , stgToCmmAllowQuotRemInstr = ncg && (x86ish || ppc) , stgToCmmAllowQuotRem2 = (ncg && (x86ish || ppc)) || llvm , stgToCmmAllowExtendedAddSubInstrs = (ncg && (x86ish || ppc)) || llvm @@ -90,6 +93,7 @@ initStgToCmmConfig dflags mod = StgToCmmConfig } where profile = targetProfile dflags platform = profilePlatform profile bk_end = backend dflags + w64 = platformWordSize platform == PW8 b_blob = if not ncg then Nothing else binBlobThreshold dflags (ncg, llvm) = case backendPrimitiveImplementation bk_end of GenericPrimitives -> (False, False) ===================================== compiler/GHC/StgToCmm/Config.hs ===================================== @@ -64,8 +64,8 @@ data StgToCmmConfig = StgToCmmConfig -- or not , stgToCmmDoTagCheck :: !Bool -- ^ Verify tag inference predictions. ------------------------------ Backend Flags ---------------------------------- - , stgToCmmAllowBigArith :: !Bool -- ^ Allowed to emit larger than native size arithmetic (only LLVM and C backends) - , stgToCmmAllowBigQuot :: !Bool -- ^ Allowed to emit larger than native size division operations + , stgToCmmAllowArith64 :: !Bool -- ^ Allowed to emit 64-bit arithmetic operations + , stgToCmmAllowQuot64 :: !Bool -- ^ Allowed to emit 64-bit division operations , stgToCmmAllowQuotRemInstr :: !Bool -- ^ Allowed to generate QuotRem instructions , stgToCmmAllowQuotRem2 :: !Bool -- ^ Allowed to generate QuotRem , stgToCmmAllowExtendedAddSubInstrs :: !Bool -- ^ Allowed to generate AddWordC, SubWordC, Add2, etc. ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -334,7 +334,7 @@ emitPrimOp cfg primop = StableNameToIntOp -> \[arg] -> opIntoRegs $ \[res] -> emitAssign (CmmLocal res) (cmmLoadIndexW platform arg (fixedHdrSizeW profile) (bWord platform)) - EqStablePtrOp -> \args -> opTranslate args (mo_wordEq platform) + EqStablePtrOp -> opTranslate (mo_wordEq platform) ReallyUnsafePtrEqualityOp -> \[arg1, arg2] -> opIntoRegs $ \[res] -> emitAssign (CmmLocal res) (CmmMachOp (mo_wordEq platform) [arg1,arg2]) @@ -1180,315 +1180,323 @@ emitPrimOp cfg primop = Narrow16WordOp -> \args -> opNarrow args (MO_UU_Conv, W16) Narrow32WordOp -> \args -> opNarrow args (MO_UU_Conv, W32) - DoublePowerOp -> \args -> opCallish args MO_F64_Pwr - DoubleSinOp -> \args -> opCallish args MO_F64_Sin - DoubleCosOp -> \args -> opCallish args MO_F64_Cos - DoubleTanOp -> \args -> opCallish args MO_F64_Tan - DoubleSinhOp -> \args -> opCallish args MO_F64_Sinh - DoubleCoshOp -> \args -> opCallish args MO_F64_Cosh - DoubleTanhOp -> \args -> opCallish args MO_F64_Tanh - DoubleAsinOp -> \args -> opCallish args MO_F64_Asin - DoubleAcosOp -> \args -> opCallish args MO_F64_Acos - DoubleAtanOp -> \args -> opCallish args MO_F64_Atan - DoubleAsinhOp -> \args -> opCallish args MO_F64_Asinh - DoubleAcoshOp -> \args -> opCallish args MO_F64_Acosh - DoubleAtanhOp -> \args -> opCallish args MO_F64_Atanh - DoubleLogOp -> \args -> opCallish args MO_F64_Log - DoubleLog1POp -> \args -> opCallish args MO_F64_Log1P - DoubleExpOp -> \args -> opCallish args MO_F64_Exp - DoubleExpM1Op -> \args -> opCallish args MO_F64_ExpM1 - DoubleSqrtOp -> \args -> opCallish args MO_F64_Sqrt - DoubleFabsOp -> \args -> opCallish args MO_F64_Fabs - - FloatPowerOp -> \args -> opCallish args MO_F32_Pwr - FloatSinOp -> \args -> opCallish args MO_F32_Sin - FloatCosOp -> \args -> opCallish args MO_F32_Cos - FloatTanOp -> \args -> opCallish args MO_F32_Tan - FloatSinhOp -> \args -> opCallish args MO_F32_Sinh - FloatCoshOp -> \args -> opCallish args MO_F32_Cosh - FloatTanhOp -> \args -> opCallish args MO_F32_Tanh - FloatAsinOp -> \args -> opCallish args MO_F32_Asin - FloatAcosOp -> \args -> opCallish args MO_F32_Acos - FloatAtanOp -> \args -> opCallish args MO_F32_Atan - FloatAsinhOp -> \args -> opCallish args MO_F32_Asinh - FloatAcoshOp -> \args -> opCallish args MO_F32_Acosh - FloatAtanhOp -> \args -> opCallish args MO_F32_Atanh - FloatLogOp -> \args -> opCallish args MO_F32_Log - FloatLog1POp -> \args -> opCallish args MO_F32_Log1P - FloatExpOp -> \args -> opCallish args MO_F32_Exp - FloatExpM1Op -> \args -> opCallish args MO_F32_ExpM1 - FloatSqrtOp -> \args -> opCallish args MO_F32_Sqrt - FloatFabsOp -> \args -> opCallish args MO_F32_Fabs + DoublePowerOp -> opCallish MO_F64_Pwr + DoubleSinOp -> opCallish MO_F64_Sin + DoubleCosOp -> opCallish MO_F64_Cos + DoubleTanOp -> opCallish MO_F64_Tan + DoubleSinhOp -> opCallish MO_F64_Sinh + DoubleCoshOp -> opCallish MO_F64_Cosh + DoubleTanhOp -> opCallish MO_F64_Tanh + DoubleAsinOp -> opCallish MO_F64_Asin + DoubleAcosOp -> opCallish MO_F64_Acos + DoubleAtanOp -> opCallish MO_F64_Atan + DoubleAsinhOp -> opCallish MO_F64_Asinh + DoubleAcoshOp -> opCallish MO_F64_Acosh + DoubleAtanhOp -> opCallish MO_F64_Atanh + DoubleLogOp -> opCallish MO_F64_Log + DoubleLog1POp -> opCallish MO_F64_Log1P + DoubleExpOp -> opCallish MO_F64_Exp + DoubleExpM1Op -> opCallish MO_F64_ExpM1 + DoubleSqrtOp -> opCallish MO_F64_Sqrt + DoubleFabsOp -> opCallish MO_F64_Fabs + + FloatPowerOp -> opCallish MO_F32_Pwr + FloatSinOp -> opCallish MO_F32_Sin + FloatCosOp -> opCallish MO_F32_Cos + FloatTanOp -> opCallish MO_F32_Tan + FloatSinhOp -> opCallish MO_F32_Sinh + FloatCoshOp -> opCallish MO_F32_Cosh + FloatTanhOp -> opCallish MO_F32_Tanh + FloatAsinOp -> opCallish MO_F32_Asin + FloatAcosOp -> opCallish MO_F32_Acos + FloatAtanOp -> opCallish MO_F32_Atan + FloatAsinhOp -> opCallish MO_F32_Asinh + FloatAcoshOp -> opCallish MO_F32_Acosh + FloatAtanhOp -> opCallish MO_F32_Atanh + FloatLogOp -> opCallish MO_F32_Log + FloatLog1POp -> opCallish MO_F32_Log1P + FloatExpOp -> opCallish MO_F32_Exp + FloatExpM1Op -> opCallish MO_F32_ExpM1 + FloatSqrtOp -> opCallish MO_F32_Sqrt + FloatFabsOp -> opCallish MO_F32_Fabs -- Native word signless ops - IntAddOp -> \args -> opTranslate args (mo_wordAdd platform) - IntSubOp -> \args -> opTranslate args (mo_wordSub platform) - WordAddOp -> \args -> opTranslate args (mo_wordAdd platform) - WordSubOp -> \args -> opTranslate args (mo_wordSub platform) - AddrAddOp -> \args -> opTranslate args (mo_wordAdd platform) - AddrSubOp -> \args -> opTranslate args (mo_wordSub platform) - - IntEqOp -> \args -> opTranslate args (mo_wordEq platform) - IntNeOp -> \args -> opTranslate args (mo_wordNe platform) - WordEqOp -> \args -> opTranslate args (mo_wordEq platform) - WordNeOp -> \args -> opTranslate args (mo_wordNe platform) - AddrEqOp -> \args -> opTranslate args (mo_wordEq platform) - AddrNeOp -> \args -> opTranslate args (mo_wordNe platform) - - WordAndOp -> \args -> opTranslate args (mo_wordAnd platform) - WordOrOp -> \args -> opTranslate args (mo_wordOr platform) - WordXorOp -> \args -> opTranslate args (mo_wordXor platform) - WordNotOp -> \args -> opTranslate args (mo_wordNot platform) - WordSllOp -> \args -> opTranslate args (mo_wordShl platform) - WordSrlOp -> \args -> opTranslate args (mo_wordUShr platform) - - AddrRemOp -> \args -> opTranslate args (mo_wordURem platform) + IntAddOp -> opTranslate (mo_wordAdd platform) + IntSubOp -> opTranslate (mo_wordSub platform) + WordAddOp -> opTranslate (mo_wordAdd platform) + WordSubOp -> opTranslate (mo_wordSub platform) + AddrAddOp -> opTranslate (mo_wordAdd platform) + AddrSubOp -> opTranslate (mo_wordSub platform) + + IntEqOp -> opTranslate (mo_wordEq platform) + IntNeOp -> opTranslate (mo_wordNe platform) + WordEqOp -> opTranslate (mo_wordEq platform) + WordNeOp -> opTranslate (mo_wordNe platform) + AddrEqOp -> opTranslate (mo_wordEq platform) + AddrNeOp -> opTranslate (mo_wordNe platform) + + WordAndOp -> opTranslate (mo_wordAnd platform) + WordOrOp -> opTranslate (mo_wordOr platform) + WordXorOp -> opTranslate (mo_wordXor platform) + WordNotOp -> opTranslate (mo_wordNot platform) + WordSllOp -> opTranslate (mo_wordShl platform) + WordSrlOp -> opTranslate (mo_wordUShr platform) + + AddrRemOp -> opTranslate (mo_wordURem platform) -- Native word signed ops - IntMulOp -> \args -> opTranslate args (mo_wordMul platform) - IntMulMayOfloOp -> \args -> opTranslate args (MO_S_MulMayOflo (wordWidth platform)) - IntQuotOp -> \args -> opTranslate args (mo_wordSQuot platform) - IntRemOp -> \args -> opTranslate args (mo_wordSRem platform) - IntNegOp -> \args -> opTranslate args (mo_wordSNeg platform) - - IntGeOp -> \args -> opTranslate args (mo_wordSGe platform) - IntLeOp -> \args -> opTranslate args (mo_wordSLe platform) - IntGtOp -> \args -> opTranslate args (mo_wordSGt platform) - IntLtOp -> \args -> opTranslate args (mo_wordSLt platform) - - IntAndOp -> \args -> opTranslate args (mo_wordAnd platform) - IntOrOp -> \args -> opTranslate args (mo_wordOr platform) - IntXorOp -> \args -> opTranslate args (mo_wordXor platform) - IntNotOp -> \args -> opTranslate args (mo_wordNot platform) - IntSllOp -> \args -> opTranslate args (mo_wordShl platform) - IntSraOp -> \args -> opTranslate args (mo_wordSShr platform) - IntSrlOp -> \args -> opTranslate args (mo_wordUShr platform) + IntMulOp -> opTranslate (mo_wordMul platform) + IntMulMayOfloOp -> opTranslate (MO_S_MulMayOflo (wordWidth platform)) + IntQuotOp -> opTranslate (mo_wordSQuot platform) + IntRemOp -> opTranslate (mo_wordSRem platform) + IntNegOp -> opTranslate (mo_wordSNeg platform) + + IntGeOp -> opTranslate (mo_wordSGe platform) + IntLeOp -> opTranslate (mo_wordSLe platform) + IntGtOp -> opTranslate (mo_wordSGt platform) + IntLtOp -> opTranslate (mo_wordSLt platform) + + IntAndOp -> opTranslate (mo_wordAnd platform) + IntOrOp -> opTranslate (mo_wordOr platform) + IntXorOp -> opTranslate (mo_wordXor platform) + IntNotOp -> opTranslate (mo_wordNot platform) + IntSllOp -> opTranslate (mo_wordShl platform) + IntSraOp -> opTranslate (mo_wordSShr platform) + IntSrlOp -> opTranslate (mo_wordUShr platform) -- Native word unsigned ops - WordGeOp -> \args -> opTranslate args (mo_wordUGe platform) - WordLeOp -> \args -> opTranslate args (mo_wordULe platform) - WordGtOp -> \args -> opTranslate args (mo_wordUGt platform) - WordLtOp -> \args -> opTranslate args (mo_wordULt platform) + WordGeOp -> opTranslate (mo_wordUGe platform) + WordLeOp -> opTranslate (mo_wordULe platform) + WordGtOp -> opTranslate (mo_wordUGt platform) + WordLtOp -> opTranslate (mo_wordULt platform) - WordMulOp -> \args -> opTranslate args (mo_wordMul platform) - WordQuotOp -> \args -> opTranslate args (mo_wordUQuot platform) - WordRemOp -> \args -> opTranslate args (mo_wordURem platform) + WordMulOp -> opTranslate (mo_wordMul platform) + WordQuotOp -> opTranslate (mo_wordUQuot platform) + WordRemOp -> opTranslate (mo_wordURem platform) - AddrGeOp -> \args -> opTranslate args (mo_wordUGe platform) - AddrLeOp -> \args -> opTranslate args (mo_wordULe platform) - AddrGtOp -> \args -> opTranslate args (mo_wordUGt platform) - AddrLtOp -> \args -> opTranslate args (mo_wordULt platform) + AddrGeOp -> opTranslate (mo_wordUGe platform) + AddrLeOp -> opTranslate (mo_wordULe platform) + AddrGtOp -> opTranslate (mo_wordUGt platform) + AddrLtOp -> opTranslate (mo_wordULt platform) -- Int8# signed ops - Int8ToIntOp -> \args -> opTranslate args (MO_SS_Conv W8 (wordWidth platform)) - IntToInt8Op -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W8) - Int8NegOp -> \args -> opTranslate args (MO_S_Neg W8) - Int8AddOp -> \args -> opTranslate args (MO_Add W8) - Int8SubOp -> \args -> opTranslate args (MO_Sub W8) - Int8MulOp -> \args -> opTranslate args (MO_Mul W8) - Int8QuotOp -> \args -> opTranslate args (MO_S_Quot W8) - Int8RemOp -> \args -> opTranslate args (MO_S_Rem W8) - - Int8SllOp -> \args -> opTranslate args (MO_Shl W8) - Int8SraOp -> \args -> opTranslate args (MO_S_Shr W8) - Int8SrlOp -> \args -> opTranslate args (MO_U_Shr W8) - - Int8EqOp -> \args -> opTranslate args (MO_Eq W8) - Int8GeOp -> \args -> opTranslate args (MO_S_Ge W8) - Int8GtOp -> \args -> opTranslate args (MO_S_Gt W8) - Int8LeOp -> \args -> opTranslate args (MO_S_Le W8) - Int8LtOp -> \args -> opTranslate args (MO_S_Lt W8) - Int8NeOp -> \args -> opTranslate args (MO_Ne W8) + Int8ToIntOp -> opTranslate (MO_SS_Conv W8 (wordWidth platform)) + IntToInt8Op -> opTranslate (MO_SS_Conv (wordWidth platform) W8) + Int8NegOp -> opTranslate (MO_S_Neg W8) + Int8AddOp -> opTranslate (MO_Add W8) + Int8SubOp -> opTranslate (MO_Sub W8) + Int8MulOp -> opTranslate (MO_Mul W8) + Int8QuotOp -> opTranslate (MO_S_Quot W8) + Int8RemOp -> opTranslate (MO_S_Rem W8) + + Int8SllOp -> opTranslate (MO_Shl W8) + Int8SraOp -> opTranslate (MO_S_Shr W8) + Int8SrlOp -> opTranslate (MO_U_Shr W8) + + Int8EqOp -> opTranslate (MO_Eq W8) + Int8GeOp -> opTranslate (MO_S_Ge W8) + Int8GtOp -> opTranslate (MO_S_Gt W8) + Int8LeOp -> opTranslate (MO_S_Le W8) + Int8LtOp -> opTranslate (MO_S_Lt W8) + Int8NeOp -> opTranslate (MO_Ne W8) -- Word8# unsigned ops - Word8ToWordOp -> \args -> opTranslate args (MO_UU_Conv W8 (wordWidth platform)) - WordToWord8Op -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W8) - Word8AddOp -> \args -> opTranslate args (MO_Add W8) - Word8SubOp -> \args -> opTranslate args (MO_Sub W8) - Word8MulOp -> \args -> opTranslate args (MO_Mul W8) - Word8QuotOp -> \args -> opTranslate args (MO_U_Quot W8) - Word8RemOp -> \args -> opTranslate args (MO_U_Rem W8) - - Word8AndOp -> \args -> opTranslate args (MO_And W8) - Word8OrOp -> \args -> opTranslate args (MO_Or W8) - Word8XorOp -> \args -> opTranslate args (MO_Xor W8) - Word8NotOp -> \args -> opTranslate args (MO_Not W8) - Word8SllOp -> \args -> opTranslate args (MO_Shl W8) - Word8SrlOp -> \args -> opTranslate args (MO_U_Shr W8) - - Word8EqOp -> \args -> opTranslate args (MO_Eq W8) - Word8GeOp -> \args -> opTranslate args (MO_U_Ge W8) - Word8GtOp -> \args -> opTranslate args (MO_U_Gt W8) - Word8LeOp -> \args -> opTranslate args (MO_U_Le W8) - Word8LtOp -> \args -> opTranslate args (MO_U_Lt W8) - Word8NeOp -> \args -> opTranslate args (MO_Ne W8) + Word8ToWordOp -> opTranslate (MO_UU_Conv W8 (wordWidth platform)) + WordToWord8Op -> opTranslate (MO_UU_Conv (wordWidth platform) W8) + Word8AddOp -> opTranslate (MO_Add W8) + Word8SubOp -> opTranslate (MO_Sub W8) + Word8MulOp -> opTranslate (MO_Mul W8) + Word8QuotOp -> opTranslate (MO_U_Quot W8) + Word8RemOp -> opTranslate (MO_U_Rem W8) + + Word8AndOp -> opTranslate (MO_And W8) + Word8OrOp -> opTranslate (MO_Or W8) + Word8XorOp -> opTranslate (MO_Xor W8) + Word8NotOp -> opTranslate (MO_Not W8) + Word8SllOp -> opTranslate (MO_Shl W8) + Word8SrlOp -> opTranslate (MO_U_Shr W8) + + Word8EqOp -> opTranslate (MO_Eq W8) + Word8GeOp -> opTranslate (MO_U_Ge W8) + Word8GtOp -> opTranslate (MO_U_Gt W8) + Word8LeOp -> opTranslate (MO_U_Le W8) + Word8LtOp -> opTranslate (MO_U_Lt W8) + Word8NeOp -> opTranslate (MO_Ne W8) -- Int16# signed ops - Int16ToIntOp -> \args -> opTranslate args (MO_SS_Conv W16 (wordWidth platform)) - IntToInt16Op -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W16) - Int16NegOp -> \args -> opTranslate args (MO_S_Neg W16) - Int16AddOp -> \args -> opTranslate args (MO_Add W16) - Int16SubOp -> \args -> opTranslate args (MO_Sub W16) - Int16MulOp -> \args -> opTranslate args (MO_Mul W16) - Int16QuotOp -> \args -> opTranslate args (MO_S_Quot W16) - Int16RemOp -> \args -> opTranslate args (MO_S_Rem W16) - - Int16SllOp -> \args -> opTranslate args (MO_Shl W16) - Int16SraOp -> \args -> opTranslate args (MO_S_Shr W16) - Int16SrlOp -> \args -> opTranslate args (MO_U_Shr W16) - - Int16EqOp -> \args -> opTranslate args (MO_Eq W16) - Int16GeOp -> \args -> opTranslate args (MO_S_Ge W16) - Int16GtOp -> \args -> opTranslate args (MO_S_Gt W16) - Int16LeOp -> \args -> opTranslate args (MO_S_Le W16) - Int16LtOp -> \args -> opTranslate args (MO_S_Lt W16) - Int16NeOp -> \args -> opTranslate args (MO_Ne W16) + Int16ToIntOp -> opTranslate (MO_SS_Conv W16 (wordWidth platform)) + IntToInt16Op -> opTranslate (MO_SS_Conv (wordWidth platform) W16) + Int16NegOp -> opTranslate (MO_S_Neg W16) + Int16AddOp -> opTranslate (MO_Add W16) + Int16SubOp -> opTranslate (MO_Sub W16) + Int16MulOp -> opTranslate (MO_Mul W16) + Int16QuotOp -> opTranslate (MO_S_Quot W16) + Int16RemOp -> opTranslate (MO_S_Rem W16) + + Int16SllOp -> opTranslate (MO_Shl W16) + Int16SraOp -> opTranslate (MO_S_Shr W16) + Int16SrlOp -> opTranslate (MO_U_Shr W16) + + Int16EqOp -> opTranslate (MO_Eq W16) + Int16GeOp -> opTranslate (MO_S_Ge W16) + Int16GtOp -> opTranslate (MO_S_Gt W16) + Int16LeOp -> opTranslate (MO_S_Le W16) + Int16LtOp -> opTranslate (MO_S_Lt W16) + Int16NeOp -> opTranslate (MO_Ne W16) -- Word16# unsigned ops - Word16ToWordOp -> \args -> opTranslate args (MO_UU_Conv W16 (wordWidth platform)) - WordToWord16Op -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W16) - Word16AddOp -> \args -> opTranslate args (MO_Add W16) - Word16SubOp -> \args -> opTranslate args (MO_Sub W16) - Word16MulOp -> \args -> opTranslate args (MO_Mul W16) - Word16QuotOp -> \args -> opTranslate args (MO_U_Quot W16) - Word16RemOp -> \args -> opTranslate args (MO_U_Rem W16) - - Word16AndOp -> \args -> opTranslate args (MO_And W16) - Word16OrOp -> \args -> opTranslate args (MO_Or W16) - Word16XorOp -> \args -> opTranslate args (MO_Xor W16) - Word16NotOp -> \args -> opTranslate args (MO_Not W16) - Word16SllOp -> \args -> opTranslate args (MO_Shl W16) - Word16SrlOp -> \args -> opTranslate args (MO_U_Shr W16) - - Word16EqOp -> \args -> opTranslate args (MO_Eq W16) - Word16GeOp -> \args -> opTranslate args (MO_U_Ge W16) - Word16GtOp -> \args -> opTranslate args (MO_U_Gt W16) - Word16LeOp -> \args -> opTranslate args (MO_U_Le W16) - Word16LtOp -> \args -> opTranslate args (MO_U_Lt W16) - Word16NeOp -> \args -> opTranslate args (MO_Ne W16) + Word16ToWordOp -> opTranslate (MO_UU_Conv W16 (wordWidth platform)) + WordToWord16Op -> opTranslate (MO_UU_Conv (wordWidth platform) W16) + Word16AddOp -> opTranslate (MO_Add W16) + Word16SubOp -> opTranslate (MO_Sub W16) + Word16MulOp -> opTranslate (MO_Mul W16) + Word16QuotOp -> opTranslate (MO_U_Quot W16) + Word16RemOp -> opTranslate (MO_U_Rem W16) + + Word16AndOp -> opTranslate (MO_And W16) + Word16OrOp -> opTranslate (MO_Or W16) + Word16XorOp -> opTranslate (MO_Xor W16) + Word16NotOp -> opTranslate (MO_Not W16) + Word16SllOp -> opTranslate (MO_Shl W16) + Word16SrlOp -> opTranslate (MO_U_Shr W16) + + Word16EqOp -> opTranslate (MO_Eq W16) + Word16GeOp -> opTranslate (MO_U_Ge W16) + Word16GtOp -> opTranslate (MO_U_Gt W16) + Word16LeOp -> opTranslate (MO_U_Le W16) + Word16LtOp -> opTranslate (MO_U_Lt W16) + Word16NeOp -> opTranslate (MO_Ne W16) -- Int32# signed ops - Int32ToIntOp -> \args -> opTranslate args (MO_SS_Conv W32 (wordWidth platform)) - IntToInt32Op -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W32) - Int32NegOp -> \args -> opTranslate args (MO_S_Neg W32) - Int32AddOp -> \args -> opTranslate args (MO_Add W32) - Int32SubOp -> \args -> opTranslate args (MO_Sub W32) - Int32MulOp -> \args -> opTranslate args (MO_Mul W32) - Int32QuotOp -> \args -> opTranslate args (MO_S_Quot W32) - Int32RemOp -> \args -> opTranslate args (MO_S_Rem W32) - - Int32SllOp -> \args -> opTranslate args (MO_Shl W32) - Int32SraOp -> \args -> opTranslate args (MO_S_Shr W32) - Int32SrlOp -> \args -> opTranslate args (MO_U_Shr W32) - - Int32EqOp -> \args -> opTranslate args (MO_Eq W32) - Int32GeOp -> \args -> opTranslate args (MO_S_Ge W32) - Int32GtOp -> \args -> opTranslate args (MO_S_Gt W32) - Int32LeOp -> \args -> opTranslate args (MO_S_Le W32) - Int32LtOp -> \args -> opTranslate args (MO_S_Lt W32) - Int32NeOp -> \args -> opTranslate args (MO_Ne W32) + Int32ToIntOp -> opTranslate (MO_SS_Conv W32 (wordWidth platform)) + IntToInt32Op -> opTranslate (MO_SS_Conv (wordWidth platform) W32) + Int32NegOp -> opTranslate (MO_S_Neg W32) + Int32AddOp -> opTranslate (MO_Add W32) + Int32SubOp -> opTranslate (MO_Sub W32) + Int32MulOp -> opTranslate (MO_Mul W32) + Int32QuotOp -> opTranslate (MO_S_Quot W32) + Int32RemOp -> opTranslate (MO_S_Rem W32) + + Int32SllOp -> opTranslate (MO_Shl W32) + Int32SraOp -> opTranslate (MO_S_Shr W32) + Int32SrlOp -> opTranslate (MO_U_Shr W32) + + Int32EqOp -> opTranslate (MO_Eq W32) + Int32GeOp -> opTranslate (MO_S_Ge W32) + Int32GtOp -> opTranslate (MO_S_Gt W32) + Int32LeOp -> opTranslate (MO_S_Le W32) + Int32LtOp -> opTranslate (MO_S_Lt W32) + Int32NeOp -> opTranslate (MO_Ne W32) -- Word32# unsigned ops - Word32ToWordOp -> \args -> opTranslate args (MO_UU_Conv W32 (wordWidth platform)) - WordToWord32Op -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W32) - Word32AddOp -> \args -> opTranslate args (MO_Add W32) - Word32SubOp -> \args -> opTranslate args (MO_Sub W32) - Word32MulOp -> \args -> opTranslate args (MO_Mul W32) - Word32QuotOp -> \args -> opTranslate args (MO_U_Quot W32) - Word32RemOp -> \args -> opTranslate args (MO_U_Rem W32) - - Word32AndOp -> \args -> opTranslate args (MO_And W32) - Word32OrOp -> \args -> opTranslate args (MO_Or W32) - Word32XorOp -> \args -> opTranslate args (MO_Xor W32) - Word32NotOp -> \args -> opTranslate args (MO_Not W32) - Word32SllOp -> \args -> opTranslate args (MO_Shl W32) - Word32SrlOp -> \args -> opTranslate args (MO_U_Shr W32) - - Word32EqOp -> \args -> opTranslate args (MO_Eq W32) - Word32GeOp -> \args -> opTranslate args (MO_U_Ge W32) - Word32GtOp -> \args -> opTranslate args (MO_U_Gt W32) - Word32LeOp -> \args -> opTranslate args (MO_U_Le W32) - Word32LtOp -> \args -> opTranslate args (MO_U_Lt W32) - Word32NeOp -> \args -> opTranslate args (MO_Ne W32) + Word32ToWordOp -> opTranslate (MO_UU_Conv W32 (wordWidth platform)) + WordToWord32Op -> opTranslate (MO_UU_Conv (wordWidth platform) W32) + Word32AddOp -> opTranslate (MO_Add W32) + Word32SubOp -> opTranslate (MO_Sub W32) + Word32MulOp -> opTranslate (MO_Mul W32) + Word32QuotOp -> opTranslate (MO_U_Quot W32) + Word32RemOp -> opTranslate (MO_U_Rem W32) + + Word32AndOp -> opTranslate (MO_And W32) + Word32OrOp -> opTranslate (MO_Or W32) + Word32XorOp -> opTranslate (MO_Xor W32) + Word32NotOp -> opTranslate (MO_Not W32) + Word32SllOp -> opTranslate (MO_Shl W32) + Word32SrlOp -> opTranslate (MO_U_Shr W32) + + Word32EqOp -> opTranslate (MO_Eq W32) + Word32GeOp -> opTranslate (MO_U_Ge W32) + Word32GtOp -> opTranslate (MO_U_Gt W32) + Word32LeOp -> opTranslate (MO_U_Le W32) + Word32LtOp -> opTranslate (MO_U_Lt W32) + Word32NeOp -> opTranslate (MO_Ne W32) -- Int64# signed ops - Int64ToIntOp -> \args -> opTranslate64 args (\w -> MO_SS_Conv w (wordWidth platform)) MO_I64_ToI - IntToInt64Op -> \args -> opTranslate64 args (\w -> MO_SS_Conv (wordWidth platform) w) MO_I64_FromI - Int64NegOp -> \args -> opTranslate64 args MO_S_Neg MO_x64_Neg - Int64AddOp -> \args -> opTranslate64 args MO_Add MO_x64_Add - Int64SubOp -> \args -> opTranslate64 args MO_Sub MO_x64_Sub - Int64MulOp -> \args -> opTranslate64 args MO_Mul MO_x64_Mul - Int64QuotOp -> \args -> opTranslate64 args MO_S_Quot MO_I64_Quot - Int64RemOp -> \args -> opTranslate64 args MO_S_Rem MO_I64_Rem - - Int64SllOp -> \args -> opTranslate64 args MO_Shl MO_x64_Shl - Int64SraOp -> \args -> opTranslate64 args MO_S_Shr MO_I64_Shr - Int64SrlOp -> \args -> opTranslate64 args MO_U_Shr MO_W64_Shr - - Int64EqOp -> \args -> opTranslate64 args MO_Eq MO_x64_Eq - Int64GeOp -> \args -> opTranslate64 args MO_S_Ge MO_I64_Ge - Int64GtOp -> \args -> opTranslate64 args MO_S_Gt MO_I64_Gt - Int64LeOp -> \args -> opTranslate64 args MO_S_Le MO_I64_Le - Int64LtOp -> \args -> opTranslate64 args MO_S_Lt MO_I64_Lt - Int64NeOp -> \args -> opTranslate64 args MO_Ne MO_x64_Ne + Int64ToIntOp -> opTranslate64 (MO_SS_Conv W64 (wordWidth platform)) MO_I64_ToI + IntToInt64Op -> opTranslate64 (MO_SS_Conv (wordWidth platform) W64) MO_I64_FromI + Int64NegOp -> opTranslate64 (MO_S_Neg W64) MO_x64_Neg + Int64AddOp -> opTranslate64 (MO_Add W64) MO_x64_Add + Int64SubOp -> opTranslate64 (MO_Sub W64) MO_x64_Sub + Int64MulOp -> opTranslate64 (MO_Mul W64) MO_x64_Mul + Int64QuotOp + | allowQuot64 -> opTranslate (MO_S_Quot W64) + | otherwise -> opCallish MO_I64_Quot + Int64RemOp + | allowQuot64 -> opTranslate (MO_S_Rem W64) + | otherwise -> opCallish MO_I64_Rem + + Int64SllOp -> opTranslate64 (MO_Shl W64) MO_x64_Shl + Int64SraOp -> opTranslate64 (MO_S_Shr W64) MO_I64_Shr + Int64SrlOp -> opTranslate64 (MO_U_Shr W64) MO_W64_Shr + + Int64EqOp -> opTranslate64 (MO_Eq W64) MO_x64_Eq + Int64GeOp -> opTranslate64 (MO_S_Ge W64) MO_I64_Ge + Int64GtOp -> opTranslate64 (MO_S_Gt W64) MO_I64_Gt + Int64LeOp -> opTranslate64 (MO_S_Le W64) MO_I64_Le + Int64LtOp -> opTranslate64 (MO_S_Lt W64) MO_I64_Lt + Int64NeOp -> opTranslate64 (MO_Ne W64) MO_x64_Ne -- Word64# unsigned ops - Word64ToWordOp -> \args -> opTranslate64 args (\w -> MO_UU_Conv w (wordWidth platform)) MO_W64_ToW - WordToWord64Op -> \args -> opTranslate64 args (\w -> MO_UU_Conv (wordWidth platform) w) MO_W64_FromW - Word64AddOp -> \args -> opTranslate64 args MO_Add MO_x64_Add - Word64SubOp -> \args -> opTranslate64 args MO_Sub MO_x64_Sub - Word64MulOp -> \args -> opTranslate64 args MO_Mul MO_x64_Mul - Word64QuotOp -> \args -> opTranslate64 args MO_U_Quot MO_W64_Quot - Word64RemOp -> \args -> opTranslate64 args MO_U_Rem MO_W64_Rem - - Word64AndOp -> \args -> opTranslate64 args MO_And MO_x64_And - Word64OrOp -> \args -> opTranslate64 args MO_Or MO_x64_Or - Word64XorOp -> \args -> opTranslate64 args MO_Xor MO_x64_Xor - Word64NotOp -> \args -> opTranslate64 args MO_Not MO_x64_Not - Word64SllOp -> \args -> opTranslate64 args MO_Shl MO_x64_Shl - Word64SrlOp -> \args -> opTranslate64 args MO_U_Shr MO_W64_Shr - - Word64EqOp -> \args -> opTranslate64 args MO_Eq MO_x64_Eq - Word64GeOp -> \args -> opTranslate64 args MO_U_Ge MO_W64_Ge - Word64GtOp -> \args -> opTranslate64 args MO_U_Gt MO_W64_Gt - Word64LeOp -> \args -> opTranslate64 args MO_U_Le MO_W64_Le - Word64LtOp -> \args -> opTranslate64 args MO_U_Lt MO_W64_Lt - Word64NeOp -> \args -> opTranslate64 args MO_Ne MO_x64_Ne + Word64ToWordOp -> opTranslate64 (MO_UU_Conv W64 (wordWidth platform)) MO_W64_ToW + WordToWord64Op -> opTranslate64 (MO_UU_Conv (wordWidth platform) W64) MO_W64_FromW + Word64AddOp -> opTranslate64 (MO_Add W64) MO_x64_Add + Word64SubOp -> opTranslate64 (MO_Sub W64) MO_x64_Sub + Word64MulOp -> opTranslate64 (MO_Mul W64) MO_x64_Mul + Word64QuotOp + | allowQuot64 -> opTranslate (MO_U_Quot W64) + | otherwise -> opCallish MO_W64_Quot + Word64RemOp + | allowQuot64 -> opTranslate (MO_U_Rem W64) + | otherwise -> opCallish MO_W64_Rem + + Word64AndOp -> opTranslate64 (MO_And W64) MO_x64_And + Word64OrOp -> opTranslate64 (MO_Or W64) MO_x64_Or + Word64XorOp -> opTranslate64 (MO_Xor W64) MO_x64_Xor + Word64NotOp -> opTranslate64 (MO_Not W64) MO_x64_Not + Word64SllOp -> opTranslate64 (MO_Shl W64) MO_x64_Shl + Word64SrlOp -> opTranslate64 (MO_U_Shr W64) MO_W64_Shr + + Word64EqOp -> opTranslate64 (MO_Eq W64) MO_x64_Eq + Word64GeOp -> opTranslate64 (MO_U_Ge W64) MO_W64_Ge + Word64GtOp -> opTranslate64 (MO_U_Gt W64) MO_W64_Gt + Word64LeOp -> opTranslate64 (MO_U_Le W64) MO_W64_Le + Word64LtOp -> opTranslate64 (MO_U_Lt W64) MO_W64_Lt + Word64NeOp -> opTranslate64 (MO_Ne W64) MO_x64_Ne -- Char# ops - CharEqOp -> \args -> opTranslate args (MO_Eq (wordWidth platform)) - CharNeOp -> \args -> opTranslate args (MO_Ne (wordWidth platform)) - CharGeOp -> \args -> opTranslate args (MO_U_Ge (wordWidth platform)) - CharLeOp -> \args -> opTranslate args (MO_U_Le (wordWidth platform)) - CharGtOp -> \args -> opTranslate args (MO_U_Gt (wordWidth platform)) - CharLtOp -> \args -> opTranslate args (MO_U_Lt (wordWidth platform)) + CharEqOp -> opTranslate (MO_Eq (wordWidth platform)) + CharNeOp -> opTranslate (MO_Ne (wordWidth platform)) + CharGeOp -> opTranslate (MO_U_Ge (wordWidth platform)) + CharLeOp -> opTranslate (MO_U_Le (wordWidth platform)) + CharGtOp -> opTranslate (MO_U_Gt (wordWidth platform)) + CharLtOp -> opTranslate (MO_U_Lt (wordWidth platform)) -- Double ops - DoubleEqOp -> \args -> opTranslate args (MO_F_Eq W64) - DoubleNeOp -> \args -> opTranslate args (MO_F_Ne W64) - DoubleGeOp -> \args -> opTranslate args (MO_F_Ge W64) - DoubleLeOp -> \args -> opTranslate args (MO_F_Le W64) - DoubleGtOp -> \args -> opTranslate args (MO_F_Gt W64) - DoubleLtOp -> \args -> opTranslate args (MO_F_Lt W64) + DoubleEqOp -> opTranslate (MO_F_Eq W64) + DoubleNeOp -> opTranslate (MO_F_Ne W64) + DoubleGeOp -> opTranslate (MO_F_Ge W64) + DoubleLeOp -> opTranslate (MO_F_Le W64) + DoubleGtOp -> opTranslate (MO_F_Gt W64) + DoubleLtOp -> opTranslate (MO_F_Lt W64) - DoubleAddOp -> \args -> opTranslate args (MO_F_Add W64) - DoubleSubOp -> \args -> opTranslate args (MO_F_Sub W64) - DoubleMulOp -> \args -> opTranslate args (MO_F_Mul W64) - DoubleDivOp -> \args -> opTranslate args (MO_F_Quot W64) - DoubleNegOp -> \args -> opTranslate args (MO_F_Neg W64) + DoubleAddOp -> opTranslate (MO_F_Add W64) + DoubleSubOp -> opTranslate (MO_F_Sub W64) + DoubleMulOp -> opTranslate (MO_F_Mul W64) + DoubleDivOp -> opTranslate (MO_F_Quot W64) + DoubleNegOp -> opTranslate (MO_F_Neg W64) DoubleFMAdd -> fmaOp FMAdd W64 DoubleFMSub -> fmaOp FMSub W64 @@ -1497,18 +1505,18 @@ emitPrimOp cfg primop = -- Float ops - FloatEqOp -> \args -> opTranslate args (MO_F_Eq W32) - FloatNeOp -> \args -> opTranslate args (MO_F_Ne W32) - FloatGeOp -> \args -> opTranslate args (MO_F_Ge W32) - FloatLeOp -> \args -> opTranslate args (MO_F_Le W32) - FloatGtOp -> \args -> opTranslate args (MO_F_Gt W32) - FloatLtOp -> \args -> opTranslate args (MO_F_Lt W32) + FloatEqOp -> opTranslate (MO_F_Eq W32) + FloatNeOp -> opTranslate (MO_F_Ne W32) + FloatGeOp -> opTranslate (MO_F_Ge W32) + FloatLeOp -> opTranslate (MO_F_Le W32) + FloatGtOp -> opTranslate (MO_F_Gt W32) + FloatLtOp -> opTranslate (MO_F_Lt W32) - FloatAddOp -> \args -> opTranslate args (MO_F_Add W32) - FloatSubOp -> \args -> opTranslate args (MO_F_Sub W32) - FloatMulOp -> \args -> opTranslate args (MO_F_Mul W32) - FloatDivOp -> \args -> opTranslate args (MO_F_Quot W32) - FloatNegOp -> \args -> opTranslate args (MO_F_Neg W32) + FloatAddOp -> opTranslate (MO_F_Add W32) + FloatSubOp -> opTranslate (MO_F_Sub W32) + FloatMulOp -> opTranslate (MO_F_Mul W32) + FloatDivOp -> opTranslate (MO_F_Quot W32) + FloatNegOp -> opTranslate (MO_F_Neg W32) FloatFMAdd -> fmaOp FMAdd W32 FloatFMSub -> fmaOp FMSub W32 @@ -1517,126 +1525,122 @@ emitPrimOp cfg primop = -- Vector ops - (VecAddOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Add n w) - (VecSubOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Sub n w) - (VecMulOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Mul n w) - (VecDivOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Quot n w) + (VecAddOp FloatVec n w) -> opTranslate (MO_VF_Add n w) + (VecSubOp FloatVec n w) -> opTranslate (MO_VF_Sub n w) + (VecMulOp FloatVec n w) -> opTranslate (MO_VF_Mul n w) + (VecDivOp FloatVec n w) -> opTranslate (MO_VF_Quot n w) (VecQuotOp FloatVec _ _) -> \_ -> panic "unsupported primop" (VecRemOp FloatVec _ _) -> \_ -> panic "unsupported primop" - (VecNegOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Neg n w) + (VecNegOp FloatVec n w) -> opTranslate (MO_VF_Neg n w) - (VecAddOp IntVec n w) -> \args -> opTranslate args (MO_V_Add n w) - (VecSubOp IntVec n w) -> \args -> opTranslate args (MO_V_Sub n w) - (VecMulOp IntVec n w) -> \args -> opTranslate args (MO_V_Mul n w) + (VecAddOp IntVec n w) -> opTranslate (MO_V_Add n w) + (VecSubOp IntVec n w) -> opTranslate (MO_V_Sub n w) + (VecMulOp IntVec n w) -> opTranslate (MO_V_Mul n w) (VecDivOp IntVec _ _) -> \_ -> panic "unsupported primop" - (VecQuotOp IntVec n w) -> \args -> opTranslate args (MO_VS_Quot n w) - (VecRemOp IntVec n w) -> \args -> opTranslate args (MO_VS_Rem n w) - (VecNegOp IntVec n w) -> \args -> opTranslate args (MO_VS_Neg n w) + (VecQuotOp IntVec n w) -> opTranslate (MO_VS_Quot n w) + (VecRemOp IntVec n w) -> opTranslate (MO_VS_Rem n w) + (VecNegOp IntVec n w) -> opTranslate (MO_VS_Neg n w) - (VecAddOp WordVec n w) -> \args -> opTranslate args (MO_V_Add n w) - (VecSubOp WordVec n w) -> \args -> opTranslate args (MO_V_Sub n w) - (VecMulOp WordVec n w) -> \args -> opTranslate args (MO_V_Mul n w) + (VecAddOp WordVec n w) -> opTranslate (MO_V_Add n w) + (VecSubOp WordVec n w) -> opTranslate (MO_V_Sub n w) + (VecMulOp WordVec n w) -> opTranslate (MO_V_Mul n w) (VecDivOp WordVec _ _) -> \_ -> panic "unsupported primop" - (VecQuotOp WordVec n w) -> \args -> opTranslate args (MO_VU_Quot n w) - (VecRemOp WordVec n w) -> \args -> opTranslate args (MO_VU_Rem n w) + (VecQuotOp WordVec n w) -> opTranslate (MO_VU_Quot n w) + (VecRemOp WordVec n w) -> opTranslate (MO_VU_Rem n w) (VecNegOp WordVec _ _) -> \_ -> panic "unsupported primop" -- Conversions - IntToDoubleOp -> \args -> opTranslate args (MO_SF_Round (wordWidth platform) W64) - DoubleToIntOp -> \args -> opTranslate args (MO_FS_Truncate W64 (wordWidth platform)) + IntToDoubleOp -> opTranslate (MO_SF_Round (wordWidth platform) W64) + DoubleToIntOp -> opTranslate (MO_FS_Truncate W64 (wordWidth platform)) - IntToFloatOp -> \args -> opTranslate args (MO_SF_Round (wordWidth platform) W32) - FloatToIntOp -> \args -> opTranslate args (MO_FS_Truncate W32 (wordWidth platform)) + IntToFloatOp -> opTranslate (MO_SF_Round (wordWidth platform) W32) + FloatToIntOp -> opTranslate (MO_FS_Truncate W32 (wordWidth platform)) - FloatToDoubleOp -> \args -> opTranslate args (MO_FF_Conv W32 W64) - DoubleToFloatOp -> \args -> opTranslate args (MO_FF_Conv W64 W32) + FloatToDoubleOp -> opTranslate (MO_FF_Conv W32 W64) + DoubleToFloatOp -> opTranslate (MO_FF_Conv W64 W32) - CastFloatToWord32Op -> - \args -> translateBitcasts (MO_FW_Bitcast W32) args - CastWord32ToFloatOp -> - \args -> translateBitcasts (MO_WF_Bitcast W32) args - CastDoubleToWord64Op -> - \args -> translateBitcasts (MO_FW_Bitcast W64) args - CastWord64ToDoubleOp -> - \args -> translateBitcasts (MO_WF_Bitcast W64) args + CastFloatToWord32Op -> translateBitcasts (MO_FW_Bitcast W32) + CastWord32ToFloatOp -> translateBitcasts (MO_WF_Bitcast W32) + CastDoubleToWord64Op -> translateBitcasts (MO_FW_Bitcast W64) + CastWord64ToDoubleOp -> translateBitcasts (MO_WF_Bitcast W64) - IntQuotRemOp -> \args -> opCallishHandledLater args $ + IntQuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem (wordWidth platform)) else Right (genericIntQuotRemOp (wordWidth platform)) - Int8QuotRemOp -> \args -> opCallishHandledLater args $ + Int8QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem W8) else Right (genericIntQuotRemOp W8) - Int16QuotRemOp -> \args -> opCallishHandledLater args $ + Int16QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem W16) else Right (genericIntQuotRemOp W16) - Int32QuotRemOp -> \args -> opCallishHandledLater args $ + Int32QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem W32) else Right (genericIntQuotRemOp W32) - WordQuotRemOp -> \args -> opCallishHandledLater args $ + WordQuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem (wordWidth platform)) else Right (genericWordQuotRemOp (wordWidth platform)) - WordQuotRem2Op -> \args -> opCallishHandledLater args $ + WordQuotRem2Op -> opCallishHandledLater $ if allowQuotRem2 then Left (MO_U_QuotRem2 (wordWidth platform)) else Right (genericWordQuotRem2Op platform) - Word8QuotRemOp -> \args -> opCallishHandledLater args $ + Word8QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem W8) else Right (genericWordQuotRemOp W8) - Word16QuotRemOp -> \args -> opCallishHandledLater args $ + Word16QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem W16) else Right (genericWordQuotRemOp W16) - Word32QuotRemOp -> \args -> opCallishHandledLater args $ + Word32QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem W32) else Right (genericWordQuotRemOp W32) - WordAdd2Op -> \args -> opCallishHandledLater args $ + WordAdd2Op -> opCallishHandledLater $ if allowExtAdd then Left (MO_Add2 (wordWidth platform)) else Right genericWordAdd2Op - WordAddCOp -> \args -> opCallishHandledLater args $ + WordAddCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_AddWordC (wordWidth platform)) else Right genericWordAddCOp - WordSubCOp -> \args -> opCallishHandledLater args $ + WordSubCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_SubWordC (wordWidth platform)) else Right genericWordSubCOp - IntAddCOp -> \args -> opCallishHandledLater args $ + IntAddCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_AddIntC (wordWidth platform)) else Right genericIntAddCOp - IntSubCOp -> \args -> opCallishHandledLater args $ + IntSubCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_SubIntC (wordWidth platform)) else Right genericIntSubCOp - WordMul2Op -> \args -> opCallishHandledLater args $ + WordMul2Op -> opCallishHandledLater $ if allowWord2Mul then Left (MO_U_Mul2 (wordWidth platform)) else Right genericWordMul2Op - IntMul2Op -> \args -> opCallishHandledLater args $ + IntMul2Op -> opCallishHandledLater $ if allowInt2Mul then Left (MO_S_Mul2 (wordWidth platform)) else Right genericIntMul2Op @@ -1775,42 +1779,33 @@ emitPrimOp cfg primop = -- These primops are implemented by CallishMachOps, because they sometimes -- turn into foreign calls depending on the backend. - opCallish :: [CmmExpr] -> CallishMachOp -> PrimopCmmEmit - opCallish args prim = opIntoRegs $ \[res] -> emitPrimCall [res] prim args + opCallish :: CallishMachOp -> [CmmExpr] -> PrimopCmmEmit + opCallish prim args = opIntoRegs $ \[res] -> emitPrimCall [res] prim args - opTranslate :: [CmmExpr] -> MachOp -> PrimopCmmEmit - opTranslate args mop = opIntoRegs $ \[res] -> do + opTranslate :: MachOp -> [CmmExpr] -> PrimopCmmEmit + opTranslate mop args = opIntoRegs $ \[res] -> do let stmt = mkAssign (CmmLocal res) (CmmMachOp mop args) emit stmt - isQuottishOp :: CallishMachOp -> Bool - isQuottishOp MO_I64_Quot = True - isQuottishOp MO_I64_Rem = True - isQuottishOp MO_W64_Quot = True - isQuottishOp MO_W64_Rem = True - isQuottishOp _ = False - opTranslate64 - :: [CmmExpr] - -> (Width -> MachOp) + :: MachOp -> CallishMachOp + -> [CmmExpr] -> PrimopCmmEmit - opTranslate64 args mkMop callish = - case platformWordSize platform of - -- LLVM and C `can handle larger than native size arithmetic natively. - _ | not (isQuottishOp callish), stgToCmmAllowBigArith cfg -> opTranslate args $ mkMop W64 - | isQuottishOp callish, stgToCmmAllowBigQuot cfg -> opTranslate args $ mkMop W64 - PW4 -> opCallish args callish - PW8 -> opTranslate args $ mkMop W64 + opTranslate64 mop callish + | allowArith64 = opTranslate mop + | otherwise = opCallish callish + -- backends not supporting 64-bit arithmetic primops: use callish machine + -- ops -- Basically a "manual" case, rather than one of the common repetitive forms -- above. The results are a parameter to the returned function so we know the -- choice of variant never depends on them. opCallishHandledLater - :: [CmmExpr] - -> Either CallishMachOp GenericOp + :: Either CallishMachOp GenericOp + -> [CmmExpr] -> PrimopCmmEmit - opCallishHandledLater args callOrNot = opIntoRegs $ \res0 -> case callOrNot of + opCallishHandledLater callOrNot args = opIntoRegs $ \res0 -> case callOrNot of Left op -> emit $ mkUnsafeCall (PrimTarget op) res0 args Right gen -> gen res0 args @@ -1838,21 +1833,23 @@ emitPrimOp cfg primop = allowExtAdd = stgToCmmAllowExtendedAddSubInstrs cfg allowInt2Mul = stgToCmmAllowIntMul2Instr cfg allowWord2Mul = stgToCmmAllowWordMul2Instr cfg + allowArith64 = stgToCmmAllowArith64 cfg + allowQuot64 = stgToCmmAllowQuot64 cfg -- a bit of a hack, for certain code generaters, e.g. PPC, and i386 we -- continue to use the cmm versions of these functions instead of inline -- assembly. Tracked in #24841. ppc = isPPC $ platformArch platform i386 = target32Bit platform - translateBitcasts mop args | ppc || i386 = alwaysExternal args - | otherwise = opTranslate args mop + translateBitcasts mop | ppc || i386 = alwaysExternal + | otherwise = opTranslate mop allowFMA = stgToCmmAllowFMAInstr cfg fmaOp :: FMASign -> Width -> [CmmActual] -> PrimopCmmEmit fmaOp signs w args@[arg_x, arg_y, arg_z] | allowFMA signs - = opTranslate args (MO_FMA signs w) + = opTranslate (MO_FMA signs w) args | otherwise = case signs of View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2eee65e1a4f441e99b79f3dc6e7d60492e4cad78...1afad514cd65c0cae66d4c53454c61ef45b2af29 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2eee65e1a4f441e99b79f3dc6e7d60492e4cad78...1afad514cd65c0cae66d4c53454c61ef45b2af29 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 18:47:00 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 07 Jun 2024 14:47:00 -0400 Subject: [Git][ghc/ghc][master] testsuite: skip objc-hi/objcxx-hi when cross compiling Message-ID: <666355a42af27_1b2a651164a8129181@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - 1 changed file: - testsuite/tests/driver/objc/all.T Changes: ===================================== testsuite/tests/driver/objc/all.T ===================================== @@ -1,11 +1,13 @@ test('objc-hi', [ unless(opsys('darwin'), skip), + when(config.target_wrapper is not None, skip), objc_src, expect_fail_for(['ghci']) ], compile_and_run, ['-framework Foundation']) test('objcxx-hi', [ unless(opsys('darwin'), skip), + when(config.target_wrapper is not None, skip), objcxx_src, expect_fail_for(['ghci']) ], compile_and_run, ['-framework Foundation -lc++']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/595c0894f630f4fc377c6bf14a5fb88ca0f1398c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/595c0894f630f4fc377c6bf14a5fb88ca0f1398c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 18:59:20 2024 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Fri, 07 Jun 2024 14:59:20 -0400 Subject: [Git][ghc/ghc][wip/expansions-appdo] Make ApplicativeDo work with HsExpansions Message-ID: <666358882e2b5_1b2a653763ec12930@gitlab.mail> Apoorv Ingle pushed to branch wip/expansions-appdo at Glasgow Haskell Compiler / GHC Commits: 23338b91 by Apoorv Ingle at 2024-06-07T11:49:42-05:00 Make ApplicativeDo work with HsExpansions testcase added: T24406 Issues Fixed: #24406, #16135 Code Changes: - Remove `XStmtLR GhcTc` as `XStmtLR GhcRn` is now compiled to `HsExpr GhcTc` - The expanded statements are guided by `GHC.Hs.Expr.TcFunInfo` which is used to decide if the `XExpr GhcRn` is to be typechecked using `tcApp` or `tcExpr` - - - - - 30 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Utils/Unify.hs - compiler/GHC/Tc/Zonk/Type.hs - testsuite/tests/ado/T13242a.stderr - testsuite/tests/ado/T16135.hs - − testsuite/tests/ado/T16135.stderr - + testsuite/tests/ado/T24406.hs - testsuite/tests/ado/ado002.stderr - testsuite/tests/ado/ado003.stderr - testsuite/tests/ado/ado004.stderr - testsuite/tests/ado/all.T - testsuite/tests/determinism/determ021/determ021.stdout - testsuite/tests/ghci.debugger/scripts/break029.stdout The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/23338b91d356715b92b4b85827ee561cf05ce30e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/23338b91d356715b92b4b85827ee561cf05ce30e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 20:56:09 2024 From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim)) Date: Fri, 07 Jun 2024 16:56:09 -0400 Subject: [Git][ghc/ghc][wip/representation-polymorphic-flip] 4 commits: StgToCmm: refactor opTranslate and friends Message-ID: <666373e9a9d9c_1b2a660f06e41346d8@gitlab.mail> Bodigrim pushed to branch wip/representation-polymorphic-flip at Glasgow Haskell Compiler / GHC Commits: 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edbec6d4 by Andrew Lelechenko at 2024-06-07T22:55:44+02:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 15 changed files: - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/Driver/Config/StgToCmm.hs - compiler/GHC/StgToCmm/Config.hs - compiler/GHC/StgToCmm/Prim.hs - libraries/base/changelog.md - libraries/ghc-internal/src/GHC/Internal/Base.hs - testsuite/tests/driver/objc/all.T - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/typecheck/should_compile/abstract_refinement_hole_fits.stderr - testsuite/tests/typecheck/should_compile/holes.stderr - testsuite/tests/typecheck/should_compile/holes3.stderr - testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr Changes: ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -94,12 +94,6 @@ is32BitPlatform = do platform <- getPlatform return $ target32Bit platform -expect32BitPlatform :: SDoc -> NatM () -expect32BitPlatform doc = do - is32Bit <- is32BitPlatform - when (not is32Bit) $ - pprPanic "Expecting 32-bit platform" doc - sse2Enabled :: NatM Bool sse2Enabled = do config <- getConfig @@ -2475,35 +2469,10 @@ genSimplePrim bid MO_F64_Acosh [dst] [src] = genLibCCall bid genSimplePrim bid MO_F64_Atanh [dst] [src] = genLibCCall bid (fsLit "atanh") [dst] [src] genSimplePrim bid MO_SuspendThread [tok] [rs,i] = genRTSCCall bid (fsLit "suspendThread") [tok] [rs,i] genSimplePrim bid MO_ResumeThread [rs] [tok] = genRTSCCall bid (fsLit "resumeThread") [rs] [tok] -genSimplePrim _ MO_I64_ToI [dst] [src] = genInt64ToInt dst src -genSimplePrim _ MO_I64_FromI [dst] [src] = genIntToInt64 dst src -genSimplePrim _ MO_W64_ToW [dst] [src] = genWord64ToWord dst src -genSimplePrim _ MO_W64_FromW [dst] [src] = genWordToWord64 dst src -genSimplePrim _ MO_x64_Neg [dst] [src] = genNeg64 dst src -genSimplePrim _ MO_x64_Add [dst] [x,y] = genAdd64 dst x y -genSimplePrim _ MO_x64_Sub [dst] [x,y] = genSub64 dst x y -genSimplePrim bid MO_x64_Mul [dst] [x,y] = genPrimCCall bid (fsLit "hs_mul64") [dst] [x,y] genSimplePrim bid MO_I64_Quot [dst] [x,y] = genPrimCCall bid (fsLit "hs_quotInt64") [dst] [x,y] genSimplePrim bid MO_I64_Rem [dst] [x,y] = genPrimCCall bid (fsLit "hs_remInt64") [dst] [x,y] genSimplePrim bid MO_W64_Quot [dst] [x,y] = genPrimCCall bid (fsLit "hs_quotWord64") [dst] [x,y] genSimplePrim bid MO_W64_Rem [dst] [x,y] = genPrimCCall bid (fsLit "hs_remWord64") [dst] [x,y] -genSimplePrim _ MO_x64_And [dst] [x,y] = genAnd64 dst x y -genSimplePrim _ MO_x64_Or [dst] [x,y] = genOr64 dst x y -genSimplePrim _ MO_x64_Xor [dst] [x,y] = genXor64 dst x y -genSimplePrim _ MO_x64_Not [dst] [src] = genNot64 dst src -genSimplePrim bid MO_x64_Shl [dst] [x,n] = genPrimCCall bid (fsLit "hs_uncheckedShiftL64") [dst] [x,n] -genSimplePrim bid MO_I64_Shr [dst] [x,n] = genPrimCCall bid (fsLit "hs_uncheckedIShiftRA64") [dst] [x,n] -genSimplePrim bid MO_W64_Shr [dst] [x,n] = genPrimCCall bid (fsLit "hs_uncheckedShiftRL64") [dst] [x,n] -genSimplePrim _ MO_x64_Eq [dst] [x,y] = genEq64 dst x y -genSimplePrim _ MO_x64_Ne [dst] [x,y] = genNe64 dst x y -genSimplePrim _ MO_I64_Ge [dst] [x,y] = genGeInt64 dst x y -genSimplePrim _ MO_I64_Gt [dst] [x,y] = genGtInt64 dst x y -genSimplePrim _ MO_I64_Le [dst] [x,y] = genLeInt64 dst x y -genSimplePrim _ MO_I64_Lt [dst] [x,y] = genLtInt64 dst x y -genSimplePrim _ MO_W64_Ge [dst] [x,y] = genGeWord64 dst x y -genSimplePrim _ MO_W64_Gt [dst] [x,y] = genGtWord64 dst x y -genSimplePrim _ MO_W64_Le [dst] [x,y] = genLeWord64 dst x y -genSimplePrim _ MO_W64_Lt [dst] [x,y] = genLtWord64 dst x y genSimplePrim _ op dst args = do platform <- ncgPlatform <$> getConfig pprPanic "genSimplePrim: unhandled primop" (ppr (pprCallishMachOp op, dst, fmap (pdoc platform) args)) @@ -4462,231 +4431,3 @@ genQuotRem width signed res_q res_r m_arg_x_high arg_x_low arg_y = do toOL [instr format y_reg, MOV format (OpReg rax) (OpReg reg_q), MOV format (OpReg rdx) (OpReg reg_r)] - - ----------------------------------------------------------------------------- --- The following functions implement certain 64-bit MachOps inline for 32-bit --- architectures. On 64-bit architectures, those MachOps aren't supported and --- calling these functions for a 64-bit target platform is considered an error --- (hence the use of `expect32BitPlatform`). --- --- On 64-bit platforms, generic MachOps should be used instead of these 64-bit --- specific ones (e.g. use MO_Add instead of MO_x64_Add). This MachOp selection --- is done by StgToCmm. - -genInt64ToInt :: LocalReg -> CmmExpr -> NatM InstrBlock -genInt64ToInt dst src = do - expect32BitPlatform (text "genInt64ToInt") - RegCode64 code _src_hi src_lo <- iselExpr64 src - let dst_r = getLocalRegReg dst - pure $ code `snocOL` MOV II32 (OpReg src_lo) (OpReg dst_r) - -genWord64ToWord :: LocalReg -> CmmExpr -> NatM InstrBlock -genWord64ToWord dst src = do - expect32BitPlatform (text "genWord64ToWord") - RegCode64 code _src_hi src_lo <- iselExpr64 src - let dst_r = getLocalRegReg dst - pure $ code `snocOL` MOV II32 (OpReg src_lo) (OpReg dst_r) - -genIntToInt64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genIntToInt64 dst src = do - expect32BitPlatform (text "genIntToInt64") - let Reg64 dst_hi dst_lo = localReg64 dst - src_code <- getAnyReg src - pure $ src_code rax `appOL` toOL - [ CLTD II32 -- sign extend EAX in EDX:EAX - , MOV II32 (OpReg rax) (OpReg dst_lo) - , MOV II32 (OpReg rdx) (OpReg dst_hi) - ] - -genWordToWord64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genWordToWord64 dst src = do - expect32BitPlatform (text "genWordToWord64") - let Reg64 dst_hi dst_lo = localReg64 dst - src_code <- getAnyReg src - pure $ src_code dst_lo - `snocOL` XOR II32 (OpReg dst_hi) (OpReg dst_hi) - -genNeg64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genNeg64 dst src = do - expect32BitPlatform (text "genNeg64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 code src_hi src_lo <- iselExpr64 src - pure $ code `appOL` toOL - [ MOV II32 (OpReg src_lo) (OpReg dst_lo) - , MOV II32 (OpReg src_hi) (OpReg dst_hi) - , NEGI II32 (OpReg dst_lo) - , ADC II32 (OpImm (ImmInt 0)) (OpReg dst_hi) - , NEGI II32 (OpReg dst_hi) - ] - -genAdd64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genAdd64 dst x y = do - expect32BitPlatform (text "genAdd64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , ADD II32 (OpReg y_lo) (OpReg dst_lo) - , ADC II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genSub64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genSub64 dst x y = do - expect32BitPlatform (text "genSub64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , SUB II32 (OpReg y_lo) (OpReg dst_lo) - , SBB II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genAnd64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genAnd64 dst x y = do - expect32BitPlatform (text "genAnd64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , AND II32 (OpReg y_lo) (OpReg dst_lo) - , AND II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genOr64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genOr64 dst x y = do - expect32BitPlatform (text "genOr64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , OR II32 (OpReg y_lo) (OpReg dst_lo) - , OR II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genXor64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genXor64 dst x y = do - expect32BitPlatform (text "genXor64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , XOR II32 (OpReg y_lo) (OpReg dst_lo) - , XOR II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genNot64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genNot64 dst src = do - expect32BitPlatform (text "genNot64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 src_code src_hi src_lo <- iselExpr64 src - pure $ src_code `appOL` toOL - [ MOV II32 (OpReg src_lo) (OpReg dst_lo) - , MOV II32 (OpReg src_hi) (OpReg dst_hi) - , NOT II32 (OpReg dst_lo) - , NOT II32 (OpReg dst_hi) - ] - -genEq64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genEq64 dst x y = do - expect32BitPlatform (text "genEq64") - let dst_r = getLocalRegReg dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - Reg64 tmp_hi tmp_lo <- getNewReg64 - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg tmp_lo) - , MOV II32 (OpReg x_hi) (OpReg tmp_hi) - , XOR II32 (OpReg y_lo) (OpReg tmp_lo) - , XOR II32 (OpReg y_hi) (OpReg tmp_hi) - , OR II32 (OpReg tmp_lo) (OpReg tmp_hi) - , SETCC EQQ (OpReg dst_r) - , MOVZxL II8 (OpReg dst_r) (OpReg dst_r) - ] - -genNe64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genNe64 dst x y = do - expect32BitPlatform (text "genNe64") - let dst_r = getLocalRegReg dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - Reg64 tmp_hi tmp_lo <- getNewReg64 - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg tmp_lo) - , MOV II32 (OpReg x_hi) (OpReg tmp_hi) - , XOR II32 (OpReg y_lo) (OpReg tmp_lo) - , XOR II32 (OpReg y_hi) (OpReg tmp_hi) - , OR II32 (OpReg tmp_lo) (OpReg tmp_hi) - , SETCC NE (OpReg dst_r) - , MOVZxL II8 (OpReg dst_r) (OpReg dst_r) - ] - -genGtWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGtWord64 dst x y = do - expect32BitPlatform (text "genGtWord64") - genPred64 LU dst y x - -genLtWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLtWord64 dst x y = do - expect32BitPlatform (text "genLtWord64") - genPred64 LU dst x y - -genGeWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGeWord64 dst x y = do - expect32BitPlatform (text "genGeWord64") - genPred64 GEU dst x y - -genLeWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLeWord64 dst x y = do - expect32BitPlatform (text "genLeWord64") - genPred64 GEU dst y x - -genGtInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGtInt64 dst x y = do - expect32BitPlatform (text "genGtInt64") - genPred64 LTT dst y x - -genLtInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLtInt64 dst x y = do - expect32BitPlatform (text "genLtInt64") - genPred64 LTT dst x y - -genGeInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGeInt64 dst x y = do - expect32BitPlatform (text "genGeInt64") - genPred64 GE dst x y - -genLeInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLeInt64 dst x y = do - expect32BitPlatform (text "genLeInt64") - genPred64 GE dst y x - -genPred64 :: Cond -> LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genPred64 cond dst x y = do - -- we can only rely on CF/SF/OF flags! - -- Not on ZF, which doesn't take into account the lower parts. - massert (cond `elem` [LU,GEU,LTT,GE]) - - let dst_r = getLocalRegReg dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - -- Basically we perform a subtraction with borrow. - -- As we don't need to result, we can use CMP instead of SUB for the low part - -- (it sets the borrow flag just like SUB does) - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_hi) (OpReg dst_r) - , CMP II32 (OpReg y_lo) (OpReg x_lo) - , SBB II32 (OpReg y_hi) (OpReg dst_r) - , SETCC cond (OpReg dst_r) - , MOVZxL II8 (OpReg dst_r) (OpReg dst_r) - ] ===================================== compiler/GHC/Driver/Config/StgToCmm.hs ===================================== @@ -53,9 +53,12 @@ initStgToCmmConfig dflags mod = StgToCmmConfig , stgToCmmExtDynRefs = gopt Opt_ExternalDynamicRefs dflags , stgToCmmDoBoundsCheck = gopt Opt_DoBoundsChecking dflags , stgToCmmDoTagCheck = gopt Opt_DoTagInferenceChecks dflags - -- backend flags - , stgToCmmAllowBigArith = not ncg || platformArch platform == ArchWasm32 || platformArch platform == ArchX86 - , stgToCmmAllowBigQuot = not ncg || platformArch platform == ArchWasm32 + + -- backend flags: + + -- LLVM, C, and some 32-bit NCG backends can also handle some 64-bit primops + , stgToCmmAllowArith64 = w64 || not ncg || platformArch platform == ArchWasm32 || platformArch platform == ArchX86 + , stgToCmmAllowQuot64 = w64 || not ncg || platformArch platform == ArchWasm32 , stgToCmmAllowQuotRemInstr = ncg && (x86ish || ppc) , stgToCmmAllowQuotRem2 = (ncg && (x86ish || ppc)) || llvm , stgToCmmAllowExtendedAddSubInstrs = (ncg && (x86ish || ppc)) || llvm @@ -90,6 +93,7 @@ initStgToCmmConfig dflags mod = StgToCmmConfig } where profile = targetProfile dflags platform = profilePlatform profile bk_end = backend dflags + w64 = platformWordSize platform == PW8 b_blob = if not ncg then Nothing else binBlobThreshold dflags (ncg, llvm) = case backendPrimitiveImplementation bk_end of GenericPrimitives -> (False, False) ===================================== compiler/GHC/StgToCmm/Config.hs ===================================== @@ -64,8 +64,8 @@ data StgToCmmConfig = StgToCmmConfig -- or not , stgToCmmDoTagCheck :: !Bool -- ^ Verify tag inference predictions. ------------------------------ Backend Flags ---------------------------------- - , stgToCmmAllowBigArith :: !Bool -- ^ Allowed to emit larger than native size arithmetic (only LLVM and C backends) - , stgToCmmAllowBigQuot :: !Bool -- ^ Allowed to emit larger than native size division operations + , stgToCmmAllowArith64 :: !Bool -- ^ Allowed to emit 64-bit arithmetic operations + , stgToCmmAllowQuot64 :: !Bool -- ^ Allowed to emit 64-bit division operations , stgToCmmAllowQuotRemInstr :: !Bool -- ^ Allowed to generate QuotRem instructions , stgToCmmAllowQuotRem2 :: !Bool -- ^ Allowed to generate QuotRem , stgToCmmAllowExtendedAddSubInstrs :: !Bool -- ^ Allowed to generate AddWordC, SubWordC, Add2, etc. ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -334,7 +334,7 @@ emitPrimOp cfg primop = StableNameToIntOp -> \[arg] -> opIntoRegs $ \[res] -> emitAssign (CmmLocal res) (cmmLoadIndexW platform arg (fixedHdrSizeW profile) (bWord platform)) - EqStablePtrOp -> \args -> opTranslate args (mo_wordEq platform) + EqStablePtrOp -> opTranslate (mo_wordEq platform) ReallyUnsafePtrEqualityOp -> \[arg1, arg2] -> opIntoRegs $ \[res] -> emitAssign (CmmLocal res) (CmmMachOp (mo_wordEq platform) [arg1,arg2]) @@ -1180,315 +1180,323 @@ emitPrimOp cfg primop = Narrow16WordOp -> \args -> opNarrow args (MO_UU_Conv, W16) Narrow32WordOp -> \args -> opNarrow args (MO_UU_Conv, W32) - DoublePowerOp -> \args -> opCallish args MO_F64_Pwr - DoubleSinOp -> \args -> opCallish args MO_F64_Sin - DoubleCosOp -> \args -> opCallish args MO_F64_Cos - DoubleTanOp -> \args -> opCallish args MO_F64_Tan - DoubleSinhOp -> \args -> opCallish args MO_F64_Sinh - DoubleCoshOp -> \args -> opCallish args MO_F64_Cosh - DoubleTanhOp -> \args -> opCallish args MO_F64_Tanh - DoubleAsinOp -> \args -> opCallish args MO_F64_Asin - DoubleAcosOp -> \args -> opCallish args MO_F64_Acos - DoubleAtanOp -> \args -> opCallish args MO_F64_Atan - DoubleAsinhOp -> \args -> opCallish args MO_F64_Asinh - DoubleAcoshOp -> \args -> opCallish args MO_F64_Acosh - DoubleAtanhOp -> \args -> opCallish args MO_F64_Atanh - DoubleLogOp -> \args -> opCallish args MO_F64_Log - DoubleLog1POp -> \args -> opCallish args MO_F64_Log1P - DoubleExpOp -> \args -> opCallish args MO_F64_Exp - DoubleExpM1Op -> \args -> opCallish args MO_F64_ExpM1 - DoubleSqrtOp -> \args -> opCallish args MO_F64_Sqrt - DoubleFabsOp -> \args -> opCallish args MO_F64_Fabs - - FloatPowerOp -> \args -> opCallish args MO_F32_Pwr - FloatSinOp -> \args -> opCallish args MO_F32_Sin - FloatCosOp -> \args -> opCallish args MO_F32_Cos - FloatTanOp -> \args -> opCallish args MO_F32_Tan - FloatSinhOp -> \args -> opCallish args MO_F32_Sinh - FloatCoshOp -> \args -> opCallish args MO_F32_Cosh - FloatTanhOp -> \args -> opCallish args MO_F32_Tanh - FloatAsinOp -> \args -> opCallish args MO_F32_Asin - FloatAcosOp -> \args -> opCallish args MO_F32_Acos - FloatAtanOp -> \args -> opCallish args MO_F32_Atan - FloatAsinhOp -> \args -> opCallish args MO_F32_Asinh - FloatAcoshOp -> \args -> opCallish args MO_F32_Acosh - FloatAtanhOp -> \args -> opCallish args MO_F32_Atanh - FloatLogOp -> \args -> opCallish args MO_F32_Log - FloatLog1POp -> \args -> opCallish args MO_F32_Log1P - FloatExpOp -> \args -> opCallish args MO_F32_Exp - FloatExpM1Op -> \args -> opCallish args MO_F32_ExpM1 - FloatSqrtOp -> \args -> opCallish args MO_F32_Sqrt - FloatFabsOp -> \args -> opCallish args MO_F32_Fabs + DoublePowerOp -> opCallish MO_F64_Pwr + DoubleSinOp -> opCallish MO_F64_Sin + DoubleCosOp -> opCallish MO_F64_Cos + DoubleTanOp -> opCallish MO_F64_Tan + DoubleSinhOp -> opCallish MO_F64_Sinh + DoubleCoshOp -> opCallish MO_F64_Cosh + DoubleTanhOp -> opCallish MO_F64_Tanh + DoubleAsinOp -> opCallish MO_F64_Asin + DoubleAcosOp -> opCallish MO_F64_Acos + DoubleAtanOp -> opCallish MO_F64_Atan + DoubleAsinhOp -> opCallish MO_F64_Asinh + DoubleAcoshOp -> opCallish MO_F64_Acosh + DoubleAtanhOp -> opCallish MO_F64_Atanh + DoubleLogOp -> opCallish MO_F64_Log + DoubleLog1POp -> opCallish MO_F64_Log1P + DoubleExpOp -> opCallish MO_F64_Exp + DoubleExpM1Op -> opCallish MO_F64_ExpM1 + DoubleSqrtOp -> opCallish MO_F64_Sqrt + DoubleFabsOp -> opCallish MO_F64_Fabs + + FloatPowerOp -> opCallish MO_F32_Pwr + FloatSinOp -> opCallish MO_F32_Sin + FloatCosOp -> opCallish MO_F32_Cos + FloatTanOp -> opCallish MO_F32_Tan + FloatSinhOp -> opCallish MO_F32_Sinh + FloatCoshOp -> opCallish MO_F32_Cosh + FloatTanhOp -> opCallish MO_F32_Tanh + FloatAsinOp -> opCallish MO_F32_Asin + FloatAcosOp -> opCallish MO_F32_Acos + FloatAtanOp -> opCallish MO_F32_Atan + FloatAsinhOp -> opCallish MO_F32_Asinh + FloatAcoshOp -> opCallish MO_F32_Acosh + FloatAtanhOp -> opCallish MO_F32_Atanh + FloatLogOp -> opCallish MO_F32_Log + FloatLog1POp -> opCallish MO_F32_Log1P + FloatExpOp -> opCallish MO_F32_Exp + FloatExpM1Op -> opCallish MO_F32_ExpM1 + FloatSqrtOp -> opCallish MO_F32_Sqrt + FloatFabsOp -> opCallish MO_F32_Fabs -- Native word signless ops - IntAddOp -> \args -> opTranslate args (mo_wordAdd platform) - IntSubOp -> \args -> opTranslate args (mo_wordSub platform) - WordAddOp -> \args -> opTranslate args (mo_wordAdd platform) - WordSubOp -> \args -> opTranslate args (mo_wordSub platform) - AddrAddOp -> \args -> opTranslate args (mo_wordAdd platform) - AddrSubOp -> \args -> opTranslate args (mo_wordSub platform) - - IntEqOp -> \args -> opTranslate args (mo_wordEq platform) - IntNeOp -> \args -> opTranslate args (mo_wordNe platform) - WordEqOp -> \args -> opTranslate args (mo_wordEq platform) - WordNeOp -> \args -> opTranslate args (mo_wordNe platform) - AddrEqOp -> \args -> opTranslate args (mo_wordEq platform) - AddrNeOp -> \args -> opTranslate args (mo_wordNe platform) - - WordAndOp -> \args -> opTranslate args (mo_wordAnd platform) - WordOrOp -> \args -> opTranslate args (mo_wordOr platform) - WordXorOp -> \args -> opTranslate args (mo_wordXor platform) - WordNotOp -> \args -> opTranslate args (mo_wordNot platform) - WordSllOp -> \args -> opTranslate args (mo_wordShl platform) - WordSrlOp -> \args -> opTranslate args (mo_wordUShr platform) - - AddrRemOp -> \args -> opTranslate args (mo_wordURem platform) + IntAddOp -> opTranslate (mo_wordAdd platform) + IntSubOp -> opTranslate (mo_wordSub platform) + WordAddOp -> opTranslate (mo_wordAdd platform) + WordSubOp -> opTranslate (mo_wordSub platform) + AddrAddOp -> opTranslate (mo_wordAdd platform) + AddrSubOp -> opTranslate (mo_wordSub platform) + + IntEqOp -> opTranslate (mo_wordEq platform) + IntNeOp -> opTranslate (mo_wordNe platform) + WordEqOp -> opTranslate (mo_wordEq platform) + WordNeOp -> opTranslate (mo_wordNe platform) + AddrEqOp -> opTranslate (mo_wordEq platform) + AddrNeOp -> opTranslate (mo_wordNe platform) + + WordAndOp -> opTranslate (mo_wordAnd platform) + WordOrOp -> opTranslate (mo_wordOr platform) + WordXorOp -> opTranslate (mo_wordXor platform) + WordNotOp -> opTranslate (mo_wordNot platform) + WordSllOp -> opTranslate (mo_wordShl platform) + WordSrlOp -> opTranslate (mo_wordUShr platform) + + AddrRemOp -> opTranslate (mo_wordURem platform) -- Native word signed ops - IntMulOp -> \args -> opTranslate args (mo_wordMul platform) - IntMulMayOfloOp -> \args -> opTranslate args (MO_S_MulMayOflo (wordWidth platform)) - IntQuotOp -> \args -> opTranslate args (mo_wordSQuot platform) - IntRemOp -> \args -> opTranslate args (mo_wordSRem platform) - IntNegOp -> \args -> opTranslate args (mo_wordSNeg platform) - - IntGeOp -> \args -> opTranslate args (mo_wordSGe platform) - IntLeOp -> \args -> opTranslate args (mo_wordSLe platform) - IntGtOp -> \args -> opTranslate args (mo_wordSGt platform) - IntLtOp -> \args -> opTranslate args (mo_wordSLt platform) - - IntAndOp -> \args -> opTranslate args (mo_wordAnd platform) - IntOrOp -> \args -> opTranslate args (mo_wordOr platform) - IntXorOp -> \args -> opTranslate args (mo_wordXor platform) - IntNotOp -> \args -> opTranslate args (mo_wordNot platform) - IntSllOp -> \args -> opTranslate args (mo_wordShl platform) - IntSraOp -> \args -> opTranslate args (mo_wordSShr platform) - IntSrlOp -> \args -> opTranslate args (mo_wordUShr platform) + IntMulOp -> opTranslate (mo_wordMul platform) + IntMulMayOfloOp -> opTranslate (MO_S_MulMayOflo (wordWidth platform)) + IntQuotOp -> opTranslate (mo_wordSQuot platform) + IntRemOp -> opTranslate (mo_wordSRem platform) + IntNegOp -> opTranslate (mo_wordSNeg platform) + + IntGeOp -> opTranslate (mo_wordSGe platform) + IntLeOp -> opTranslate (mo_wordSLe platform) + IntGtOp -> opTranslate (mo_wordSGt platform) + IntLtOp -> opTranslate (mo_wordSLt platform) + + IntAndOp -> opTranslate (mo_wordAnd platform) + IntOrOp -> opTranslate (mo_wordOr platform) + IntXorOp -> opTranslate (mo_wordXor platform) + IntNotOp -> opTranslate (mo_wordNot platform) + IntSllOp -> opTranslate (mo_wordShl platform) + IntSraOp -> opTranslate (mo_wordSShr platform) + IntSrlOp -> opTranslate (mo_wordUShr platform) -- Native word unsigned ops - WordGeOp -> \args -> opTranslate args (mo_wordUGe platform) - WordLeOp -> \args -> opTranslate args (mo_wordULe platform) - WordGtOp -> \args -> opTranslate args (mo_wordUGt platform) - WordLtOp -> \args -> opTranslate args (mo_wordULt platform) + WordGeOp -> opTranslate (mo_wordUGe platform) + WordLeOp -> opTranslate (mo_wordULe platform) + WordGtOp -> opTranslate (mo_wordUGt platform) + WordLtOp -> opTranslate (mo_wordULt platform) - WordMulOp -> \args -> opTranslate args (mo_wordMul platform) - WordQuotOp -> \args -> opTranslate args (mo_wordUQuot platform) - WordRemOp -> \args -> opTranslate args (mo_wordURem platform) + WordMulOp -> opTranslate (mo_wordMul platform) + WordQuotOp -> opTranslate (mo_wordUQuot platform) + WordRemOp -> opTranslate (mo_wordURem platform) - AddrGeOp -> \args -> opTranslate args (mo_wordUGe platform) - AddrLeOp -> \args -> opTranslate args (mo_wordULe platform) - AddrGtOp -> \args -> opTranslate args (mo_wordUGt platform) - AddrLtOp -> \args -> opTranslate args (mo_wordULt platform) + AddrGeOp -> opTranslate (mo_wordUGe platform) + AddrLeOp -> opTranslate (mo_wordULe platform) + AddrGtOp -> opTranslate (mo_wordUGt platform) + AddrLtOp -> opTranslate (mo_wordULt platform) -- Int8# signed ops - Int8ToIntOp -> \args -> opTranslate args (MO_SS_Conv W8 (wordWidth platform)) - IntToInt8Op -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W8) - Int8NegOp -> \args -> opTranslate args (MO_S_Neg W8) - Int8AddOp -> \args -> opTranslate args (MO_Add W8) - Int8SubOp -> \args -> opTranslate args (MO_Sub W8) - Int8MulOp -> \args -> opTranslate args (MO_Mul W8) - Int8QuotOp -> \args -> opTranslate args (MO_S_Quot W8) - Int8RemOp -> \args -> opTranslate args (MO_S_Rem W8) - - Int8SllOp -> \args -> opTranslate args (MO_Shl W8) - Int8SraOp -> \args -> opTranslate args (MO_S_Shr W8) - Int8SrlOp -> \args -> opTranslate args (MO_U_Shr W8) - - Int8EqOp -> \args -> opTranslate args (MO_Eq W8) - Int8GeOp -> \args -> opTranslate args (MO_S_Ge W8) - Int8GtOp -> \args -> opTranslate args (MO_S_Gt W8) - Int8LeOp -> \args -> opTranslate args (MO_S_Le W8) - Int8LtOp -> \args -> opTranslate args (MO_S_Lt W8) - Int8NeOp -> \args -> opTranslate args (MO_Ne W8) + Int8ToIntOp -> opTranslate (MO_SS_Conv W8 (wordWidth platform)) + IntToInt8Op -> opTranslate (MO_SS_Conv (wordWidth platform) W8) + Int8NegOp -> opTranslate (MO_S_Neg W8) + Int8AddOp -> opTranslate (MO_Add W8) + Int8SubOp -> opTranslate (MO_Sub W8) + Int8MulOp -> opTranslate (MO_Mul W8) + Int8QuotOp -> opTranslate (MO_S_Quot W8) + Int8RemOp -> opTranslate (MO_S_Rem W8) + + Int8SllOp -> opTranslate (MO_Shl W8) + Int8SraOp -> opTranslate (MO_S_Shr W8) + Int8SrlOp -> opTranslate (MO_U_Shr W8) + + Int8EqOp -> opTranslate (MO_Eq W8) + Int8GeOp -> opTranslate (MO_S_Ge W8) + Int8GtOp -> opTranslate (MO_S_Gt W8) + Int8LeOp -> opTranslate (MO_S_Le W8) + Int8LtOp -> opTranslate (MO_S_Lt W8) + Int8NeOp -> opTranslate (MO_Ne W8) -- Word8# unsigned ops - Word8ToWordOp -> \args -> opTranslate args (MO_UU_Conv W8 (wordWidth platform)) - WordToWord8Op -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W8) - Word8AddOp -> \args -> opTranslate args (MO_Add W8) - Word8SubOp -> \args -> opTranslate args (MO_Sub W8) - Word8MulOp -> \args -> opTranslate args (MO_Mul W8) - Word8QuotOp -> \args -> opTranslate args (MO_U_Quot W8) - Word8RemOp -> \args -> opTranslate args (MO_U_Rem W8) - - Word8AndOp -> \args -> opTranslate args (MO_And W8) - Word8OrOp -> \args -> opTranslate args (MO_Or W8) - Word8XorOp -> \args -> opTranslate args (MO_Xor W8) - Word8NotOp -> \args -> opTranslate args (MO_Not W8) - Word8SllOp -> \args -> opTranslate args (MO_Shl W8) - Word8SrlOp -> \args -> opTranslate args (MO_U_Shr W8) - - Word8EqOp -> \args -> opTranslate args (MO_Eq W8) - Word8GeOp -> \args -> opTranslate args (MO_U_Ge W8) - Word8GtOp -> \args -> opTranslate args (MO_U_Gt W8) - Word8LeOp -> \args -> opTranslate args (MO_U_Le W8) - Word8LtOp -> \args -> opTranslate args (MO_U_Lt W8) - Word8NeOp -> \args -> opTranslate args (MO_Ne W8) + Word8ToWordOp -> opTranslate (MO_UU_Conv W8 (wordWidth platform)) + WordToWord8Op -> opTranslate (MO_UU_Conv (wordWidth platform) W8) + Word8AddOp -> opTranslate (MO_Add W8) + Word8SubOp -> opTranslate (MO_Sub W8) + Word8MulOp -> opTranslate (MO_Mul W8) + Word8QuotOp -> opTranslate (MO_U_Quot W8) + Word8RemOp -> opTranslate (MO_U_Rem W8) + + Word8AndOp -> opTranslate (MO_And W8) + Word8OrOp -> opTranslate (MO_Or W8) + Word8XorOp -> opTranslate (MO_Xor W8) + Word8NotOp -> opTranslate (MO_Not W8) + Word8SllOp -> opTranslate (MO_Shl W8) + Word8SrlOp -> opTranslate (MO_U_Shr W8) + + Word8EqOp -> opTranslate (MO_Eq W8) + Word8GeOp -> opTranslate (MO_U_Ge W8) + Word8GtOp -> opTranslate (MO_U_Gt W8) + Word8LeOp -> opTranslate (MO_U_Le W8) + Word8LtOp -> opTranslate (MO_U_Lt W8) + Word8NeOp -> opTranslate (MO_Ne W8) -- Int16# signed ops - Int16ToIntOp -> \args -> opTranslate args (MO_SS_Conv W16 (wordWidth platform)) - IntToInt16Op -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W16) - Int16NegOp -> \args -> opTranslate args (MO_S_Neg W16) - Int16AddOp -> \args -> opTranslate args (MO_Add W16) - Int16SubOp -> \args -> opTranslate args (MO_Sub W16) - Int16MulOp -> \args -> opTranslate args (MO_Mul W16) - Int16QuotOp -> \args -> opTranslate args (MO_S_Quot W16) - Int16RemOp -> \args -> opTranslate args (MO_S_Rem W16) - - Int16SllOp -> \args -> opTranslate args (MO_Shl W16) - Int16SraOp -> \args -> opTranslate args (MO_S_Shr W16) - Int16SrlOp -> \args -> opTranslate args (MO_U_Shr W16) - - Int16EqOp -> \args -> opTranslate args (MO_Eq W16) - Int16GeOp -> \args -> opTranslate args (MO_S_Ge W16) - Int16GtOp -> \args -> opTranslate args (MO_S_Gt W16) - Int16LeOp -> \args -> opTranslate args (MO_S_Le W16) - Int16LtOp -> \args -> opTranslate args (MO_S_Lt W16) - Int16NeOp -> \args -> opTranslate args (MO_Ne W16) + Int16ToIntOp -> opTranslate (MO_SS_Conv W16 (wordWidth platform)) + IntToInt16Op -> opTranslate (MO_SS_Conv (wordWidth platform) W16) + Int16NegOp -> opTranslate (MO_S_Neg W16) + Int16AddOp -> opTranslate (MO_Add W16) + Int16SubOp -> opTranslate (MO_Sub W16) + Int16MulOp -> opTranslate (MO_Mul W16) + Int16QuotOp -> opTranslate (MO_S_Quot W16) + Int16RemOp -> opTranslate (MO_S_Rem W16) + + Int16SllOp -> opTranslate (MO_Shl W16) + Int16SraOp -> opTranslate (MO_S_Shr W16) + Int16SrlOp -> opTranslate (MO_U_Shr W16) + + Int16EqOp -> opTranslate (MO_Eq W16) + Int16GeOp -> opTranslate (MO_S_Ge W16) + Int16GtOp -> opTranslate (MO_S_Gt W16) + Int16LeOp -> opTranslate (MO_S_Le W16) + Int16LtOp -> opTranslate (MO_S_Lt W16) + Int16NeOp -> opTranslate (MO_Ne W16) -- Word16# unsigned ops - Word16ToWordOp -> \args -> opTranslate args (MO_UU_Conv W16 (wordWidth platform)) - WordToWord16Op -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W16) - Word16AddOp -> \args -> opTranslate args (MO_Add W16) - Word16SubOp -> \args -> opTranslate args (MO_Sub W16) - Word16MulOp -> \args -> opTranslate args (MO_Mul W16) - Word16QuotOp -> \args -> opTranslate args (MO_U_Quot W16) - Word16RemOp -> \args -> opTranslate args (MO_U_Rem W16) - - Word16AndOp -> \args -> opTranslate args (MO_And W16) - Word16OrOp -> \args -> opTranslate args (MO_Or W16) - Word16XorOp -> \args -> opTranslate args (MO_Xor W16) - Word16NotOp -> \args -> opTranslate args (MO_Not W16) - Word16SllOp -> \args -> opTranslate args (MO_Shl W16) - Word16SrlOp -> \args -> opTranslate args (MO_U_Shr W16) - - Word16EqOp -> \args -> opTranslate args (MO_Eq W16) - Word16GeOp -> \args -> opTranslate args (MO_U_Ge W16) - Word16GtOp -> \args -> opTranslate args (MO_U_Gt W16) - Word16LeOp -> \args -> opTranslate args (MO_U_Le W16) - Word16LtOp -> \args -> opTranslate args (MO_U_Lt W16) - Word16NeOp -> \args -> opTranslate args (MO_Ne W16) + Word16ToWordOp -> opTranslate (MO_UU_Conv W16 (wordWidth platform)) + WordToWord16Op -> opTranslate (MO_UU_Conv (wordWidth platform) W16) + Word16AddOp -> opTranslate (MO_Add W16) + Word16SubOp -> opTranslate (MO_Sub W16) + Word16MulOp -> opTranslate (MO_Mul W16) + Word16QuotOp -> opTranslate (MO_U_Quot W16) + Word16RemOp -> opTranslate (MO_U_Rem W16) + + Word16AndOp -> opTranslate (MO_And W16) + Word16OrOp -> opTranslate (MO_Or W16) + Word16XorOp -> opTranslate (MO_Xor W16) + Word16NotOp -> opTranslate (MO_Not W16) + Word16SllOp -> opTranslate (MO_Shl W16) + Word16SrlOp -> opTranslate (MO_U_Shr W16) + + Word16EqOp -> opTranslate (MO_Eq W16) + Word16GeOp -> opTranslate (MO_U_Ge W16) + Word16GtOp -> opTranslate (MO_U_Gt W16) + Word16LeOp -> opTranslate (MO_U_Le W16) + Word16LtOp -> opTranslate (MO_U_Lt W16) + Word16NeOp -> opTranslate (MO_Ne W16) -- Int32# signed ops - Int32ToIntOp -> \args -> opTranslate args (MO_SS_Conv W32 (wordWidth platform)) - IntToInt32Op -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W32) - Int32NegOp -> \args -> opTranslate args (MO_S_Neg W32) - Int32AddOp -> \args -> opTranslate args (MO_Add W32) - Int32SubOp -> \args -> opTranslate args (MO_Sub W32) - Int32MulOp -> \args -> opTranslate args (MO_Mul W32) - Int32QuotOp -> \args -> opTranslate args (MO_S_Quot W32) - Int32RemOp -> \args -> opTranslate args (MO_S_Rem W32) - - Int32SllOp -> \args -> opTranslate args (MO_Shl W32) - Int32SraOp -> \args -> opTranslate args (MO_S_Shr W32) - Int32SrlOp -> \args -> opTranslate args (MO_U_Shr W32) - - Int32EqOp -> \args -> opTranslate args (MO_Eq W32) - Int32GeOp -> \args -> opTranslate args (MO_S_Ge W32) - Int32GtOp -> \args -> opTranslate args (MO_S_Gt W32) - Int32LeOp -> \args -> opTranslate args (MO_S_Le W32) - Int32LtOp -> \args -> opTranslate args (MO_S_Lt W32) - Int32NeOp -> \args -> opTranslate args (MO_Ne W32) + Int32ToIntOp -> opTranslate (MO_SS_Conv W32 (wordWidth platform)) + IntToInt32Op -> opTranslate (MO_SS_Conv (wordWidth platform) W32) + Int32NegOp -> opTranslate (MO_S_Neg W32) + Int32AddOp -> opTranslate (MO_Add W32) + Int32SubOp -> opTranslate (MO_Sub W32) + Int32MulOp -> opTranslate (MO_Mul W32) + Int32QuotOp -> opTranslate (MO_S_Quot W32) + Int32RemOp -> opTranslate (MO_S_Rem W32) + + Int32SllOp -> opTranslate (MO_Shl W32) + Int32SraOp -> opTranslate (MO_S_Shr W32) + Int32SrlOp -> opTranslate (MO_U_Shr W32) + + Int32EqOp -> opTranslate (MO_Eq W32) + Int32GeOp -> opTranslate (MO_S_Ge W32) + Int32GtOp -> opTranslate (MO_S_Gt W32) + Int32LeOp -> opTranslate (MO_S_Le W32) + Int32LtOp -> opTranslate (MO_S_Lt W32) + Int32NeOp -> opTranslate (MO_Ne W32) -- Word32# unsigned ops - Word32ToWordOp -> \args -> opTranslate args (MO_UU_Conv W32 (wordWidth platform)) - WordToWord32Op -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W32) - Word32AddOp -> \args -> opTranslate args (MO_Add W32) - Word32SubOp -> \args -> opTranslate args (MO_Sub W32) - Word32MulOp -> \args -> opTranslate args (MO_Mul W32) - Word32QuotOp -> \args -> opTranslate args (MO_U_Quot W32) - Word32RemOp -> \args -> opTranslate args (MO_U_Rem W32) - - Word32AndOp -> \args -> opTranslate args (MO_And W32) - Word32OrOp -> \args -> opTranslate args (MO_Or W32) - Word32XorOp -> \args -> opTranslate args (MO_Xor W32) - Word32NotOp -> \args -> opTranslate args (MO_Not W32) - Word32SllOp -> \args -> opTranslate args (MO_Shl W32) - Word32SrlOp -> \args -> opTranslate args (MO_U_Shr W32) - - Word32EqOp -> \args -> opTranslate args (MO_Eq W32) - Word32GeOp -> \args -> opTranslate args (MO_U_Ge W32) - Word32GtOp -> \args -> opTranslate args (MO_U_Gt W32) - Word32LeOp -> \args -> opTranslate args (MO_U_Le W32) - Word32LtOp -> \args -> opTranslate args (MO_U_Lt W32) - Word32NeOp -> \args -> opTranslate args (MO_Ne W32) + Word32ToWordOp -> opTranslate (MO_UU_Conv W32 (wordWidth platform)) + WordToWord32Op -> opTranslate (MO_UU_Conv (wordWidth platform) W32) + Word32AddOp -> opTranslate (MO_Add W32) + Word32SubOp -> opTranslate (MO_Sub W32) + Word32MulOp -> opTranslate (MO_Mul W32) + Word32QuotOp -> opTranslate (MO_U_Quot W32) + Word32RemOp -> opTranslate (MO_U_Rem W32) + + Word32AndOp -> opTranslate (MO_And W32) + Word32OrOp -> opTranslate (MO_Or W32) + Word32XorOp -> opTranslate (MO_Xor W32) + Word32NotOp -> opTranslate (MO_Not W32) + Word32SllOp -> opTranslate (MO_Shl W32) + Word32SrlOp -> opTranslate (MO_U_Shr W32) + + Word32EqOp -> opTranslate (MO_Eq W32) + Word32GeOp -> opTranslate (MO_U_Ge W32) + Word32GtOp -> opTranslate (MO_U_Gt W32) + Word32LeOp -> opTranslate (MO_U_Le W32) + Word32LtOp -> opTranslate (MO_U_Lt W32) + Word32NeOp -> opTranslate (MO_Ne W32) -- Int64# signed ops - Int64ToIntOp -> \args -> opTranslate64 args (\w -> MO_SS_Conv w (wordWidth platform)) MO_I64_ToI - IntToInt64Op -> \args -> opTranslate64 args (\w -> MO_SS_Conv (wordWidth platform) w) MO_I64_FromI - Int64NegOp -> \args -> opTranslate64 args MO_S_Neg MO_x64_Neg - Int64AddOp -> \args -> opTranslate64 args MO_Add MO_x64_Add - Int64SubOp -> \args -> opTranslate64 args MO_Sub MO_x64_Sub - Int64MulOp -> \args -> opTranslate64 args MO_Mul MO_x64_Mul - Int64QuotOp -> \args -> opTranslate64 args MO_S_Quot MO_I64_Quot - Int64RemOp -> \args -> opTranslate64 args MO_S_Rem MO_I64_Rem - - Int64SllOp -> \args -> opTranslate64 args MO_Shl MO_x64_Shl - Int64SraOp -> \args -> opTranslate64 args MO_S_Shr MO_I64_Shr - Int64SrlOp -> \args -> opTranslate64 args MO_U_Shr MO_W64_Shr - - Int64EqOp -> \args -> opTranslate64 args MO_Eq MO_x64_Eq - Int64GeOp -> \args -> opTranslate64 args MO_S_Ge MO_I64_Ge - Int64GtOp -> \args -> opTranslate64 args MO_S_Gt MO_I64_Gt - Int64LeOp -> \args -> opTranslate64 args MO_S_Le MO_I64_Le - Int64LtOp -> \args -> opTranslate64 args MO_S_Lt MO_I64_Lt - Int64NeOp -> \args -> opTranslate64 args MO_Ne MO_x64_Ne + Int64ToIntOp -> opTranslate64 (MO_SS_Conv W64 (wordWidth platform)) MO_I64_ToI + IntToInt64Op -> opTranslate64 (MO_SS_Conv (wordWidth platform) W64) MO_I64_FromI + Int64NegOp -> opTranslate64 (MO_S_Neg W64) MO_x64_Neg + Int64AddOp -> opTranslate64 (MO_Add W64) MO_x64_Add + Int64SubOp -> opTranslate64 (MO_Sub W64) MO_x64_Sub + Int64MulOp -> opTranslate64 (MO_Mul W64) MO_x64_Mul + Int64QuotOp + | allowQuot64 -> opTranslate (MO_S_Quot W64) + | otherwise -> opCallish MO_I64_Quot + Int64RemOp + | allowQuot64 -> opTranslate (MO_S_Rem W64) + | otherwise -> opCallish MO_I64_Rem + + Int64SllOp -> opTranslate64 (MO_Shl W64) MO_x64_Shl + Int64SraOp -> opTranslate64 (MO_S_Shr W64) MO_I64_Shr + Int64SrlOp -> opTranslate64 (MO_U_Shr W64) MO_W64_Shr + + Int64EqOp -> opTranslate64 (MO_Eq W64) MO_x64_Eq + Int64GeOp -> opTranslate64 (MO_S_Ge W64) MO_I64_Ge + Int64GtOp -> opTranslate64 (MO_S_Gt W64) MO_I64_Gt + Int64LeOp -> opTranslate64 (MO_S_Le W64) MO_I64_Le + Int64LtOp -> opTranslate64 (MO_S_Lt W64) MO_I64_Lt + Int64NeOp -> opTranslate64 (MO_Ne W64) MO_x64_Ne -- Word64# unsigned ops - Word64ToWordOp -> \args -> opTranslate64 args (\w -> MO_UU_Conv w (wordWidth platform)) MO_W64_ToW - WordToWord64Op -> \args -> opTranslate64 args (\w -> MO_UU_Conv (wordWidth platform) w) MO_W64_FromW - Word64AddOp -> \args -> opTranslate64 args MO_Add MO_x64_Add - Word64SubOp -> \args -> opTranslate64 args MO_Sub MO_x64_Sub - Word64MulOp -> \args -> opTranslate64 args MO_Mul MO_x64_Mul - Word64QuotOp -> \args -> opTranslate64 args MO_U_Quot MO_W64_Quot - Word64RemOp -> \args -> opTranslate64 args MO_U_Rem MO_W64_Rem - - Word64AndOp -> \args -> opTranslate64 args MO_And MO_x64_And - Word64OrOp -> \args -> opTranslate64 args MO_Or MO_x64_Or - Word64XorOp -> \args -> opTranslate64 args MO_Xor MO_x64_Xor - Word64NotOp -> \args -> opTranslate64 args MO_Not MO_x64_Not - Word64SllOp -> \args -> opTranslate64 args MO_Shl MO_x64_Shl - Word64SrlOp -> \args -> opTranslate64 args MO_U_Shr MO_W64_Shr - - Word64EqOp -> \args -> opTranslate64 args MO_Eq MO_x64_Eq - Word64GeOp -> \args -> opTranslate64 args MO_U_Ge MO_W64_Ge - Word64GtOp -> \args -> opTranslate64 args MO_U_Gt MO_W64_Gt - Word64LeOp -> \args -> opTranslate64 args MO_U_Le MO_W64_Le - Word64LtOp -> \args -> opTranslate64 args MO_U_Lt MO_W64_Lt - Word64NeOp -> \args -> opTranslate64 args MO_Ne MO_x64_Ne + Word64ToWordOp -> opTranslate64 (MO_UU_Conv W64 (wordWidth platform)) MO_W64_ToW + WordToWord64Op -> opTranslate64 (MO_UU_Conv (wordWidth platform) W64) MO_W64_FromW + Word64AddOp -> opTranslate64 (MO_Add W64) MO_x64_Add + Word64SubOp -> opTranslate64 (MO_Sub W64) MO_x64_Sub + Word64MulOp -> opTranslate64 (MO_Mul W64) MO_x64_Mul + Word64QuotOp + | allowQuot64 -> opTranslate (MO_U_Quot W64) + | otherwise -> opCallish MO_W64_Quot + Word64RemOp + | allowQuot64 -> opTranslate (MO_U_Rem W64) + | otherwise -> opCallish MO_W64_Rem + + Word64AndOp -> opTranslate64 (MO_And W64) MO_x64_And + Word64OrOp -> opTranslate64 (MO_Or W64) MO_x64_Or + Word64XorOp -> opTranslate64 (MO_Xor W64) MO_x64_Xor + Word64NotOp -> opTranslate64 (MO_Not W64) MO_x64_Not + Word64SllOp -> opTranslate64 (MO_Shl W64) MO_x64_Shl + Word64SrlOp -> opTranslate64 (MO_U_Shr W64) MO_W64_Shr + + Word64EqOp -> opTranslate64 (MO_Eq W64) MO_x64_Eq + Word64GeOp -> opTranslate64 (MO_U_Ge W64) MO_W64_Ge + Word64GtOp -> opTranslate64 (MO_U_Gt W64) MO_W64_Gt + Word64LeOp -> opTranslate64 (MO_U_Le W64) MO_W64_Le + Word64LtOp -> opTranslate64 (MO_U_Lt W64) MO_W64_Lt + Word64NeOp -> opTranslate64 (MO_Ne W64) MO_x64_Ne -- Char# ops - CharEqOp -> \args -> opTranslate args (MO_Eq (wordWidth platform)) - CharNeOp -> \args -> opTranslate args (MO_Ne (wordWidth platform)) - CharGeOp -> \args -> opTranslate args (MO_U_Ge (wordWidth platform)) - CharLeOp -> \args -> opTranslate args (MO_U_Le (wordWidth platform)) - CharGtOp -> \args -> opTranslate args (MO_U_Gt (wordWidth platform)) - CharLtOp -> \args -> opTranslate args (MO_U_Lt (wordWidth platform)) + CharEqOp -> opTranslate (MO_Eq (wordWidth platform)) + CharNeOp -> opTranslate (MO_Ne (wordWidth platform)) + CharGeOp -> opTranslate (MO_U_Ge (wordWidth platform)) + CharLeOp -> opTranslate (MO_U_Le (wordWidth platform)) + CharGtOp -> opTranslate (MO_U_Gt (wordWidth platform)) + CharLtOp -> opTranslate (MO_U_Lt (wordWidth platform)) -- Double ops - DoubleEqOp -> \args -> opTranslate args (MO_F_Eq W64) - DoubleNeOp -> \args -> opTranslate args (MO_F_Ne W64) - DoubleGeOp -> \args -> opTranslate args (MO_F_Ge W64) - DoubleLeOp -> \args -> opTranslate args (MO_F_Le W64) - DoubleGtOp -> \args -> opTranslate args (MO_F_Gt W64) - DoubleLtOp -> \args -> opTranslate args (MO_F_Lt W64) + DoubleEqOp -> opTranslate (MO_F_Eq W64) + DoubleNeOp -> opTranslate (MO_F_Ne W64) + DoubleGeOp -> opTranslate (MO_F_Ge W64) + DoubleLeOp -> opTranslate (MO_F_Le W64) + DoubleGtOp -> opTranslate (MO_F_Gt W64) + DoubleLtOp -> opTranslate (MO_F_Lt W64) - DoubleAddOp -> \args -> opTranslate args (MO_F_Add W64) - DoubleSubOp -> \args -> opTranslate args (MO_F_Sub W64) - DoubleMulOp -> \args -> opTranslate args (MO_F_Mul W64) - DoubleDivOp -> \args -> opTranslate args (MO_F_Quot W64) - DoubleNegOp -> \args -> opTranslate args (MO_F_Neg W64) + DoubleAddOp -> opTranslate (MO_F_Add W64) + DoubleSubOp -> opTranslate (MO_F_Sub W64) + DoubleMulOp -> opTranslate (MO_F_Mul W64) + DoubleDivOp -> opTranslate (MO_F_Quot W64) + DoubleNegOp -> opTranslate (MO_F_Neg W64) DoubleFMAdd -> fmaOp FMAdd W64 DoubleFMSub -> fmaOp FMSub W64 @@ -1497,18 +1505,18 @@ emitPrimOp cfg primop = -- Float ops - FloatEqOp -> \args -> opTranslate args (MO_F_Eq W32) - FloatNeOp -> \args -> opTranslate args (MO_F_Ne W32) - FloatGeOp -> \args -> opTranslate args (MO_F_Ge W32) - FloatLeOp -> \args -> opTranslate args (MO_F_Le W32) - FloatGtOp -> \args -> opTranslate args (MO_F_Gt W32) - FloatLtOp -> \args -> opTranslate args (MO_F_Lt W32) + FloatEqOp -> opTranslate (MO_F_Eq W32) + FloatNeOp -> opTranslate (MO_F_Ne W32) + FloatGeOp -> opTranslate (MO_F_Ge W32) + FloatLeOp -> opTranslate (MO_F_Le W32) + FloatGtOp -> opTranslate (MO_F_Gt W32) + FloatLtOp -> opTranslate (MO_F_Lt W32) - FloatAddOp -> \args -> opTranslate args (MO_F_Add W32) - FloatSubOp -> \args -> opTranslate args (MO_F_Sub W32) - FloatMulOp -> \args -> opTranslate args (MO_F_Mul W32) - FloatDivOp -> \args -> opTranslate args (MO_F_Quot W32) - FloatNegOp -> \args -> opTranslate args (MO_F_Neg W32) + FloatAddOp -> opTranslate (MO_F_Add W32) + FloatSubOp -> opTranslate (MO_F_Sub W32) + FloatMulOp -> opTranslate (MO_F_Mul W32) + FloatDivOp -> opTranslate (MO_F_Quot W32) + FloatNegOp -> opTranslate (MO_F_Neg W32) FloatFMAdd -> fmaOp FMAdd W32 FloatFMSub -> fmaOp FMSub W32 @@ -1517,126 +1525,122 @@ emitPrimOp cfg primop = -- Vector ops - (VecAddOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Add n w) - (VecSubOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Sub n w) - (VecMulOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Mul n w) - (VecDivOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Quot n w) + (VecAddOp FloatVec n w) -> opTranslate (MO_VF_Add n w) + (VecSubOp FloatVec n w) -> opTranslate (MO_VF_Sub n w) + (VecMulOp FloatVec n w) -> opTranslate (MO_VF_Mul n w) + (VecDivOp FloatVec n w) -> opTranslate (MO_VF_Quot n w) (VecQuotOp FloatVec _ _) -> \_ -> panic "unsupported primop" (VecRemOp FloatVec _ _) -> \_ -> panic "unsupported primop" - (VecNegOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Neg n w) + (VecNegOp FloatVec n w) -> opTranslate (MO_VF_Neg n w) - (VecAddOp IntVec n w) -> \args -> opTranslate args (MO_V_Add n w) - (VecSubOp IntVec n w) -> \args -> opTranslate args (MO_V_Sub n w) - (VecMulOp IntVec n w) -> \args -> opTranslate args (MO_V_Mul n w) + (VecAddOp IntVec n w) -> opTranslate (MO_V_Add n w) + (VecSubOp IntVec n w) -> opTranslate (MO_V_Sub n w) + (VecMulOp IntVec n w) -> opTranslate (MO_V_Mul n w) (VecDivOp IntVec _ _) -> \_ -> panic "unsupported primop" - (VecQuotOp IntVec n w) -> \args -> opTranslate args (MO_VS_Quot n w) - (VecRemOp IntVec n w) -> \args -> opTranslate args (MO_VS_Rem n w) - (VecNegOp IntVec n w) -> \args -> opTranslate args (MO_VS_Neg n w) + (VecQuotOp IntVec n w) -> opTranslate (MO_VS_Quot n w) + (VecRemOp IntVec n w) -> opTranslate (MO_VS_Rem n w) + (VecNegOp IntVec n w) -> opTranslate (MO_VS_Neg n w) - (VecAddOp WordVec n w) -> \args -> opTranslate args (MO_V_Add n w) - (VecSubOp WordVec n w) -> \args -> opTranslate args (MO_V_Sub n w) - (VecMulOp WordVec n w) -> \args -> opTranslate args (MO_V_Mul n w) + (VecAddOp WordVec n w) -> opTranslate (MO_V_Add n w) + (VecSubOp WordVec n w) -> opTranslate (MO_V_Sub n w) + (VecMulOp WordVec n w) -> opTranslate (MO_V_Mul n w) (VecDivOp WordVec _ _) -> \_ -> panic "unsupported primop" - (VecQuotOp WordVec n w) -> \args -> opTranslate args (MO_VU_Quot n w) - (VecRemOp WordVec n w) -> \args -> opTranslate args (MO_VU_Rem n w) + (VecQuotOp WordVec n w) -> opTranslate (MO_VU_Quot n w) + (VecRemOp WordVec n w) -> opTranslate (MO_VU_Rem n w) (VecNegOp WordVec _ _) -> \_ -> panic "unsupported primop" -- Conversions - IntToDoubleOp -> \args -> opTranslate args (MO_SF_Round (wordWidth platform) W64) - DoubleToIntOp -> \args -> opTranslate args (MO_FS_Truncate W64 (wordWidth platform)) + IntToDoubleOp -> opTranslate (MO_SF_Round (wordWidth platform) W64) + DoubleToIntOp -> opTranslate (MO_FS_Truncate W64 (wordWidth platform)) - IntToFloatOp -> \args -> opTranslate args (MO_SF_Round (wordWidth platform) W32) - FloatToIntOp -> \args -> opTranslate args (MO_FS_Truncate W32 (wordWidth platform)) + IntToFloatOp -> opTranslate (MO_SF_Round (wordWidth platform) W32) + FloatToIntOp -> opTranslate (MO_FS_Truncate W32 (wordWidth platform)) - FloatToDoubleOp -> \args -> opTranslate args (MO_FF_Conv W32 W64) - DoubleToFloatOp -> \args -> opTranslate args (MO_FF_Conv W64 W32) + FloatToDoubleOp -> opTranslate (MO_FF_Conv W32 W64) + DoubleToFloatOp -> opTranslate (MO_FF_Conv W64 W32) - CastFloatToWord32Op -> - \args -> translateBitcasts (MO_FW_Bitcast W32) args - CastWord32ToFloatOp -> - \args -> translateBitcasts (MO_WF_Bitcast W32) args - CastDoubleToWord64Op -> - \args -> translateBitcasts (MO_FW_Bitcast W64) args - CastWord64ToDoubleOp -> - \args -> translateBitcasts (MO_WF_Bitcast W64) args + CastFloatToWord32Op -> translateBitcasts (MO_FW_Bitcast W32) + CastWord32ToFloatOp -> translateBitcasts (MO_WF_Bitcast W32) + CastDoubleToWord64Op -> translateBitcasts (MO_FW_Bitcast W64) + CastWord64ToDoubleOp -> translateBitcasts (MO_WF_Bitcast W64) - IntQuotRemOp -> \args -> opCallishHandledLater args $ + IntQuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem (wordWidth platform)) else Right (genericIntQuotRemOp (wordWidth platform)) - Int8QuotRemOp -> \args -> opCallishHandledLater args $ + Int8QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem W8) else Right (genericIntQuotRemOp W8) - Int16QuotRemOp -> \args -> opCallishHandledLater args $ + Int16QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem W16) else Right (genericIntQuotRemOp W16) - Int32QuotRemOp -> \args -> opCallishHandledLater args $ + Int32QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem W32) else Right (genericIntQuotRemOp W32) - WordQuotRemOp -> \args -> opCallishHandledLater args $ + WordQuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem (wordWidth platform)) else Right (genericWordQuotRemOp (wordWidth platform)) - WordQuotRem2Op -> \args -> opCallishHandledLater args $ + WordQuotRem2Op -> opCallishHandledLater $ if allowQuotRem2 then Left (MO_U_QuotRem2 (wordWidth platform)) else Right (genericWordQuotRem2Op platform) - Word8QuotRemOp -> \args -> opCallishHandledLater args $ + Word8QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem W8) else Right (genericWordQuotRemOp W8) - Word16QuotRemOp -> \args -> opCallishHandledLater args $ + Word16QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem W16) else Right (genericWordQuotRemOp W16) - Word32QuotRemOp -> \args -> opCallishHandledLater args $ + Word32QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem W32) else Right (genericWordQuotRemOp W32) - WordAdd2Op -> \args -> opCallishHandledLater args $ + WordAdd2Op -> opCallishHandledLater $ if allowExtAdd then Left (MO_Add2 (wordWidth platform)) else Right genericWordAdd2Op - WordAddCOp -> \args -> opCallishHandledLater args $ + WordAddCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_AddWordC (wordWidth platform)) else Right genericWordAddCOp - WordSubCOp -> \args -> opCallishHandledLater args $ + WordSubCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_SubWordC (wordWidth platform)) else Right genericWordSubCOp - IntAddCOp -> \args -> opCallishHandledLater args $ + IntAddCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_AddIntC (wordWidth platform)) else Right genericIntAddCOp - IntSubCOp -> \args -> opCallishHandledLater args $ + IntSubCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_SubIntC (wordWidth platform)) else Right genericIntSubCOp - WordMul2Op -> \args -> opCallishHandledLater args $ + WordMul2Op -> opCallishHandledLater $ if allowWord2Mul then Left (MO_U_Mul2 (wordWidth platform)) else Right genericWordMul2Op - IntMul2Op -> \args -> opCallishHandledLater args $ + IntMul2Op -> opCallishHandledLater $ if allowInt2Mul then Left (MO_S_Mul2 (wordWidth platform)) else Right genericIntMul2Op @@ -1775,42 +1779,33 @@ emitPrimOp cfg primop = -- These primops are implemented by CallishMachOps, because they sometimes -- turn into foreign calls depending on the backend. - opCallish :: [CmmExpr] -> CallishMachOp -> PrimopCmmEmit - opCallish args prim = opIntoRegs $ \[res] -> emitPrimCall [res] prim args + opCallish :: CallishMachOp -> [CmmExpr] -> PrimopCmmEmit + opCallish prim args = opIntoRegs $ \[res] -> emitPrimCall [res] prim args - opTranslate :: [CmmExpr] -> MachOp -> PrimopCmmEmit - opTranslate args mop = opIntoRegs $ \[res] -> do + opTranslate :: MachOp -> [CmmExpr] -> PrimopCmmEmit + opTranslate mop args = opIntoRegs $ \[res] -> do let stmt = mkAssign (CmmLocal res) (CmmMachOp mop args) emit stmt - isQuottishOp :: CallishMachOp -> Bool - isQuottishOp MO_I64_Quot = True - isQuottishOp MO_I64_Rem = True - isQuottishOp MO_W64_Quot = True - isQuottishOp MO_W64_Rem = True - isQuottishOp _ = False - opTranslate64 - :: [CmmExpr] - -> (Width -> MachOp) + :: MachOp -> CallishMachOp + -> [CmmExpr] -> PrimopCmmEmit - opTranslate64 args mkMop callish = - case platformWordSize platform of - -- LLVM and C `can handle larger than native size arithmetic natively. - _ | not (isQuottishOp callish), stgToCmmAllowBigArith cfg -> opTranslate args $ mkMop W64 - | isQuottishOp callish, stgToCmmAllowBigQuot cfg -> opTranslate args $ mkMop W64 - PW4 -> opCallish args callish - PW8 -> opTranslate args $ mkMop W64 + opTranslate64 mop callish + | allowArith64 = opTranslate mop + | otherwise = opCallish callish + -- backends not supporting 64-bit arithmetic primops: use callish machine + -- ops -- Basically a "manual" case, rather than one of the common repetitive forms -- above. The results are a parameter to the returned function so we know the -- choice of variant never depends on them. opCallishHandledLater - :: [CmmExpr] - -> Either CallishMachOp GenericOp + :: Either CallishMachOp GenericOp + -> [CmmExpr] -> PrimopCmmEmit - opCallishHandledLater args callOrNot = opIntoRegs $ \res0 -> case callOrNot of + opCallishHandledLater callOrNot args = opIntoRegs $ \res0 -> case callOrNot of Left op -> emit $ mkUnsafeCall (PrimTarget op) res0 args Right gen -> gen res0 args @@ -1838,21 +1833,23 @@ emitPrimOp cfg primop = allowExtAdd = stgToCmmAllowExtendedAddSubInstrs cfg allowInt2Mul = stgToCmmAllowIntMul2Instr cfg allowWord2Mul = stgToCmmAllowWordMul2Instr cfg + allowArith64 = stgToCmmAllowArith64 cfg + allowQuot64 = stgToCmmAllowQuot64 cfg -- a bit of a hack, for certain code generaters, e.g. PPC, and i386 we -- continue to use the cmm versions of these functions instead of inline -- assembly. Tracked in #24841. ppc = isPPC $ platformArch platform i386 = target32Bit platform - translateBitcasts mop args | ppc || i386 = alwaysExternal args - | otherwise = opTranslate args mop + translateBitcasts mop | ppc || i386 = alwaysExternal + | otherwise = opTranslate mop allowFMA = stgToCmmAllowFMAInstr cfg fmaOp :: FMASign -> Width -> [CmmActual] -> PrimopCmmEmit fmaOp signs w args@[arg_x, arg_y, arg_z] | allowFMA signs - = opTranslate args (MO_FMA signs w) + = opTranslate (MO_FMA signs w) args | otherwise = case signs of ===================================== libraries/base/changelog.md ===================================== @@ -3,6 +3,7 @@ ## 4.21.0.0 *TBA* * Add the `MonadFix` instance for `(,) a`, similar to the one for `Writer a` ([CLC proposal #238](https://github.com/haskell/core-libraries-committee/issues/238)) * Improve `toInteger :: Word32 -> Integer` on 64-bit platforms ([CLC proposal #259](https://github.com/haskell/core-libraries-committee/issues/259)) + * Make `flip` representation polymorphic ([CLC proposal #245](https://github.com/haskell/core-libraries-committee/issues/245)) * The `HasField` class now supports representation polymorphism ([CLC proposal #194](https://github.com/haskell/core-libraries-committee/issues/194)) * Make `read` accept binary integer notation ([CLC proposal #177](https://github.com/haskell/core-libraries-committee/issues/177)) * Improve the performance of `Data.List.sort` using an improved merging strategy. Instead of `compare`, `sort` now uses `(>)` which may break *malformed* `Ord` instances ([CLC proposal #236](https://github.com/haskell/core-libraries-committee/issues/236)) ===================================== libraries/ghc-internal/src/GHC/Internal/Base.hs ===================================== @@ -2184,7 +2184,7 @@ const x _ = x -- -- >>> let (.>) = flip (.) in (+1) .> show $ 5 -- "6" -flip :: (a -> b -> c) -> b -> a -> c +flip :: forall repc a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c flip f x y = f y x -- Note: Before base-4.19, ($) was not representation polymorphic ===================================== testsuite/tests/driver/objc/all.T ===================================== @@ -1,11 +1,13 @@ test('objc-hi', [ unless(opsys('darwin'), skip), + when(config.target_wrapper is not None, skip), objc_src, expect_fail_for(['ghci']) ], compile_and_run, ['-framework Foundation']) test('objcxx-hi', [ unless(opsys('darwin'), skip), + when(config.target_wrapper is not None, skip), objcxx_src, expect_fail_for(['ghci']) ], compile_and_run, ['-framework Foundation -lc++']) ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -1095,7 +1095,7 @@ module Data.Function where applyWhen :: forall a. GHC.Types.Bool -> (a -> a) -> a -> a const :: forall a b. a -> b -> a fix :: forall a. (a -> a) -> a - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c id :: forall a. a -> a on :: forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c @@ -3714,7 +3714,7 @@ module GHC.Base where fetchXorIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) fetchXorWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #) finalizeWeak# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c float2Double# :: Float# -> Double# float2Int# :: Float# -> Int# fmaddDouble# :: Double# -> Double# -> Double# -> Double# @@ -10127,7 +10127,7 @@ module Prelude where errorWithoutStackTrace :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r). [Char] -> a even :: forall a. Integral a => a -> Bool filter :: forall a. (a -> Bool) -> [a] -> [a] - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c fromIntegral :: forall a b. (Integral a, Num b) => a -> b fst :: forall a b. (a, b) -> a gcd :: forall a. Integral a => a -> a -> a ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -1095,7 +1095,7 @@ module Data.Function where applyWhen :: forall a. GHC.Types.Bool -> (a -> a) -> a -> a const :: forall a b. a -> b -> a fix :: forall a. (a -> a) -> a - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c id :: forall a. a -> a on :: forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c @@ -3714,7 +3714,7 @@ module GHC.Base where fetchXorIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) fetchXorWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #) finalizeWeak# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c float2Double# :: Float# -> Double# float2Int# :: Float# -> Int# fmaddDouble# :: Double# -> Double# -> Double# -> Double# @@ -13169,7 +13169,7 @@ module Prelude where errorWithoutStackTrace :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r). [Char] -> a even :: forall a. Integral a => a -> Bool filter :: forall a. (a -> Bool) -> [a] -> [a] - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c fromIntegral :: forall a b. (Integral a, Num b) => a -> b fst :: forall a b. (a, b) -> a gcd :: forall a. Integral a => a -> a -> a ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -1095,7 +1095,7 @@ module Data.Function where applyWhen :: forall a. GHC.Types.Bool -> (a -> a) -> a -> a const :: forall a b. a -> b -> a fix :: forall a. (a -> a) -> a - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c id :: forall a. a -> a on :: forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c @@ -3717,7 +3717,7 @@ module GHC.Base where fetchXorIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) fetchXorWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #) finalizeWeak# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c float2Double# :: Float# -> Double# float2Int# :: Float# -> Int# fmaddDouble# :: Double# -> Double# -> Double# -> Double# @@ -10413,7 +10413,7 @@ module Prelude where errorWithoutStackTrace :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r). [Char] -> a even :: forall a. Integral a => a -> Bool filter :: forall a. (a -> Bool) -> [a] -> [a] - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c fromIntegral :: forall a b. (Integral a, Num b) => a -> b fst :: forall a b. (a, b) -> a gcd :: forall a. Integral a => a -> a -> a ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -1095,7 +1095,7 @@ module Data.Function where applyWhen :: forall a. GHC.Types.Bool -> (a -> a) -> a -> a const :: forall a b. a -> b -> a fix :: forall a. (a -> a) -> a - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c id :: forall a. a -> a on :: forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c @@ -3714,7 +3714,7 @@ module GHC.Base where fetchXorIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) fetchXorWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #) finalizeWeak# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c float2Double# :: Float# -> Double# float2Int# :: Float# -> Int# fmaddDouble# :: Double# -> Double# -> Double# -> Double# @@ -10127,7 +10127,7 @@ module Prelude where errorWithoutStackTrace :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r). [Char] -> a even :: forall a. Integral a => a -> Bool filter :: forall a. (a -> Bool) -> [a] -> [a] - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c fromIntegral :: forall a b. (Integral a, Num b) => a -> b fst :: forall a b. (a, b) -> a gcd :: forall a. Integral a => a -> a -> a ===================================== testsuite/tests/typecheck/should_compile/abstract_refinement_hole_fits.stderr ===================================== @@ -39,14 +39,14 @@ abstract_refinement_hole_fits.hs:4:5: warning: [GHC-88464] [-Wtyped-holes (in -W where const :: forall a b. a -> b -> a (.) (_ :: b1 -> Integer) (_ :: [Integer] -> b1) where (.) :: forall b c a. (b -> c) -> (a -> b) -> a -> c - flip (_ :: [Integer] -> t0 -> Integer) (_ :: t0) - where flip :: forall a b c. (a -> b -> c) -> b -> a -> c curry (_ :: (t0, [Integer]) -> Integer) (_ :: t0) where curry :: forall a b c. ((a, b) -> c) -> a -> b -> c ($) (_ :: [Integer] -> Integer) where ($) :: forall a b. (a -> b) -> a -> b ($!) (_ :: [Integer] -> Integer) where ($!) :: forall a b. (a -> b) -> a -> b + flip (_ :: [Integer] -> t0 -> Integer) (_ :: t0) + where flip :: forall a b c. (a -> b -> c) -> b -> a -> c id (_ :: t0 -> [Integer] -> Integer) (_ :: t0) where id :: forall a. a -> a head (_ :: [t0 -> [Integer] -> Integer]) (_ :: t0) @@ -160,22 +160,22 @@ abstract_refinement_hole_fits.hs:7:5: warning: [GHC-88464] [-Wtyped-holes (in -W where foldr :: forall (t :: * -> *) a b. Foldable t => (a -> b -> b) -> b -> t a -> b - flip (_ :: [Integer] -> Integer -> Integer) - where flip :: forall a b c. (a -> b -> c) -> b -> a -> c curry (_ :: (Integer, [Integer]) -> Integer) where curry :: forall a b c. ((a, b) -> c) -> a -> b -> c const (_ :: [Integer] -> Integer) where const :: forall a b. a -> b -> a + flip (_ :: [Integer] -> Integer -> Integer) + where flip :: forall a b c. (a -> b -> c) -> b -> a -> c (.) (_ :: b1 -> [Integer] -> Integer) (_ :: Integer -> b1) where (.) :: forall b c a. (b -> c) -> (a -> b) -> a -> c - flip (_ :: Integer -> t0 -> [Integer] -> Integer) (_ :: t0) - where flip :: forall a b c. (a -> b -> c) -> b -> a -> c curry (_ :: (t0, Integer) -> [Integer] -> Integer) (_ :: t0) where curry :: forall a b c. ((a, b) -> c) -> a -> b -> c ($) (_ :: Integer -> [Integer] -> Integer) where ($) :: forall a b. (a -> b) -> a -> b ($!) (_ :: Integer -> [Integer] -> Integer) where ($!) :: forall a b. (a -> b) -> a -> b + flip (_ :: Integer -> t0 -> [Integer] -> Integer) (_ :: t0) + where flip :: forall a b c. (a -> b -> c) -> b -> a -> c id (_ :: t0 -> Integer -> [Integer] -> Integer) (_ :: t0) where id :: forall a. a -> a head (_ :: [t0 -> Integer -> [Integer] -> Integer]) (_ :: t0) ===================================== testsuite/tests/typecheck/should_compile/holes.stderr ===================================== @@ -194,7 +194,6 @@ holes.hs:11:15: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] seq :: forall a b. a -> b -> b ($!) :: forall a b. (a -> b) -> a -> b (.) :: forall b c a. (b -> c) -> (a -> b) -> a -> c - flip :: forall a b c. (a -> b -> c) -> b -> a -> c either :: forall a c b. (a -> c) -> (b -> c) -> Either a b -> c curry :: forall a b c. ((a, b) -> c) -> a -> b -> c uncurry :: forall a b c. (a -> b -> c) -> (a, b) -> c @@ -202,5 +201,6 @@ holes.hs:11:15: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] zip3 :: forall a b c. [a] -> [b] -> [c] -> [(a, b, c)] zipWith :: forall a b c. (a -> b -> c) -> [a] -> [b] -> [c] ($) :: forall a b. (a -> b) -> a -> b + flip :: forall a b c. (a -> b -> c) -> b -> a -> c zipWith3 :: forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] ===================================== testsuite/tests/typecheck/should_compile/holes3.stderr ===================================== @@ -197,7 +197,6 @@ holes3.hs:11:15: error: [GHC-88464] seq :: forall a b. a -> b -> b ($!) :: forall a b. (a -> b) -> a -> b (.) :: forall b c a. (b -> c) -> (a -> b) -> a -> c - flip :: forall a b c. (a -> b -> c) -> b -> a -> c either :: forall a c b. (a -> c) -> (b -> c) -> Either a b -> c curry :: forall a b c. ((a, b) -> c) -> a -> b -> c uncurry :: forall a b c. (a -> b -> c) -> (a, b) -> c @@ -205,5 +204,6 @@ holes3.hs:11:15: error: [GHC-88464] zip3 :: forall a b c. [a] -> [b] -> [c] -> [(a, b, c)] zipWith :: forall a b c. (a -> b -> c) -> [a] -> [b] -> [c] ($) :: forall a b. (a -> b) -> a -> b + flip :: forall a b c. (a -> b -> c) -> b -> a -> c zipWith3 :: forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] ===================================== testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr ===================================== @@ -172,11 +172,6 @@ refinement_hole_fits.hs:7:5: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] with foldr @[] @Integer @Integer (imported from ‘Prelude’ at refinement_hole_fits.hs:1:8-30 (and originally defined in ‘GHC.Internal.Data.Foldable’)) - flip (_ :: [Integer] -> Integer -> Integer) - where flip :: forall a b c. (a -> b -> c) -> b -> a -> c - with flip @[Integer] @Integer @Integer - (imported from ‘Prelude’ at refinement_hole_fits.hs:1:8-30 - (and originally defined in ‘GHC.Internal.Base’)) curry (_ :: (Integer, [Integer]) -> Integer) where curry :: forall a b c. ((a, b) -> c) -> a -> b -> c with curry @Integer @[Integer] @Integer @@ -187,6 +182,11 @@ refinement_hole_fits.hs:7:5: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] with const @([Integer] -> Integer) @Integer (imported from ‘Prelude’ at refinement_hole_fits.hs:1:8-30 (and originally defined in ‘GHC.Internal.Base’)) + flip (_ :: [Integer] -> Integer -> Integer) + where flip :: forall a b c. (a -> b -> c) -> b -> a -> c + with flip @GHC.Types.LiftedRep @[Integer] @Integer @Integer + (imported from ‘Prelude’ at refinement_hole_fits.hs:1:8-30 + (and originally defined in ‘GHC.Internal.Base’)) ($) (_ :: Integer -> [Integer] -> Integer) where ($) :: forall a b. (a -> b) -> a -> b with ($) @GHC.Types.LiftedRep View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f9fd1fc3a09e6d8b02f72d90212f8b00a7b9abf8...edbec6d40aa7ff39f87ea7e75a4cc3f5cbe07d8f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f9fd1fc3a09e6d8b02f72d90212f8b00a7b9abf8...edbec6d40aa7ff39f87ea7e75a4cc3f5cbe07d8f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 21:34:35 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 07 Jun 2024 17:34:35 -0400 Subject: [Git][ghc/ghc][wip/T24676] Wibbles Message-ID: <66637ceb35dfa_1b2a6662559c13508f@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24676 at Glasgow Haskell Compiler / GHC Commits: 286e7acd by Simon Peyton Jones at 2024-06-07T22:34:19+01:00 Wibbles - - - - - 2 changed files: - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Utils/Unify.hs Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -406,17 +406,21 @@ tcApp rn_expr exp_res_ty tcInstFun do_ql True tc_head fun_sigma rn_args ; case do_ql of - NoQL -> do { -- Step 4.1: subsumption check against expecte result type + NoQL -> do { traceTc "tcApp:NoQL" (ppr rn_fun $$ ppr app_res_rho) + + -- Step 4.1: subsumption check against expected result type -- See Note [Unify with expected type before typechecking arguments] - res_wrap <- checkResultTy rn_expr tc_head inst_args + ; res_wrap <- checkResultTy rn_expr tc_head inst_args app_res_rho exp_res_ty -- Step 4.2: typecheck the arguments ; tc_args <- tcValArgs NoQL inst_args -- Step 4.3: wrap up ; finishApp tc_head tc_args app_res_rho res_wrap } - DoQL -> do { -- Step 5.1: Take a quick look at the result type - quickLookResultType app_res_rho exp_res_ty + DoQL -> do { traceTc "tcApp:DoQL" (ppr rn_fun $$ ppr app_res_rho) + + -- Step 5.1: Take a quick look at the result type + ; quickLookResultType app_res_rho exp_res_ty -- Step 5.2: typecheck the arguments, and monomorphise -- any un-unified instantiation variables ; tc_args <- tcValArgs DoQL inst_args @@ -1890,7 +1894,8 @@ qlUnify :: TcType -> TcType -> TcM () -- * It may return without having made the argument types equal, of course; -- it just makes best efforts. qlUnify ty1 ty2 - = go ty1 ty2 + = do { traceTc "qlUnify" (ppr ty1 $$ ppr ty2) + ; go ty1 ty2 } where go :: TcType -> TcType -> TcM () ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -2910,7 +2910,7 @@ simpleUnifyCheck caller lhs_tv rhs fam_ok = case caller of UC_Solver -> True - UC_QuickLook -> False + UC_QuickLook -> True UC_OnTheFly -> False go (TyVarTy tv) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/286e7acd3fadf5015fd0f10cc40566b0266a0a5d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/286e7acd3fadf5015fd0f10cc40566b0266a0a5d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 21:40:43 2024 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Fri, 07 Jun 2024 17:40:43 -0400 Subject: [Git][ghc/ghc][wip/expansions-appdo] Make ApplicativeDo work with HsExpansions Message-ID: <66637e5bc5006_1b2a667a94e01360e0@gitlab.mail> Apoorv Ingle pushed to branch wip/expansions-appdo at Glasgow Haskell Compiler / GHC Commits: 96f76d93 by Apoorv Ingle at 2024-06-07T16:39:53-05:00 Make ApplicativeDo work with HsExpansions testcase added: T24406 Issues Fixed: #24406, #16135 Code Changes: - Remove `XStmtLR GhcTc` as `XStmtLR GhcRn` is now compiled to `HsExpr GhcTc` - The expanded statements are guided by `GHC.Hs.Expr.TcFunInfo` which is used to decide if the `XExpr GhcRn` is to be typechecked using `tcApp` or `tcExpr` Note [Expanding HsDo with XXExprGhcRn] explains the change in more detail - - - - - 30 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Monad.hs - compiler/GHC/Tc/Zonk/Type.hs - testsuite/tests/ado/T13242a.stderr - testsuite/tests/ado/T16135.hs - − testsuite/tests/ado/T16135.stderr - + testsuite/tests/ado/T24406.hs - testsuite/tests/ado/ado002.stderr - testsuite/tests/ado/ado003.stderr - testsuite/tests/ado/ado004.stderr - testsuite/tests/ado/all.T - testsuite/tests/determinism/determ021/determ021.stdout - testsuite/tests/ghci.debugger/scripts/break029.stdout - testsuite/tests/hiefile/should_run/T23540.stdout Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -473,11 +473,14 @@ type instance XXExpr GhcTc = XXExprGhcTc * * ********************************************************************* -} +-- | Hint to the typechecker how to typecheck the expanded expression +data TCFunInfo = TcApp | TcExpr + -- | The different source constructs that we use to instantiate the "original" field -- in an `XXExprGhcRn original expansion` data HsThingRn = OrigExpr (HsExpr GhcRn) - | OrigStmt (ExprLStmt GhcRn) - | OrigPat (LPat GhcRn) + | OrigStmt (ExprLStmt GhcRn) HsDoFlavour -- ^ which kind of do-block did this statement come from + | OrigPat (LPat GhcRn) (Maybe (HsDoFlavour, ExprLStmt GhcRn)) isHsThingRnExpr, isHsThingRnStmt, isHsThingRnPat :: HsThingRn -> Bool isHsThingRnExpr (OrigExpr{}) = True @@ -491,7 +494,10 @@ isHsThingRnPat _ = False data XXExprGhcRn = ExpandedThingRn { xrn_orig :: HsThingRn -- The original source thing - , xrn_expanded :: HsExpr GhcRn } -- The compiler generated expanded thing + , xrn_expanded :: HsExpr GhcRn -- The compiler generated expanded thing + , xrn_TCFunInfo :: TCFunInfo } -- A Hint to the type checker of how to proceed + -- TcApp <=> use GHC.Tc.Gen.Expr.tcApp + -- TcExpr <=> use GHC.Tc.Gen.Expr.tcExpr | PopErrCtxt -- A hint for typechecker to pop {-# UNPACK #-} !(LHsExpr GhcRn) -- the top of the error context stack @@ -515,22 +521,25 @@ mkExpandedExpr :: HsExpr GhcRn -- ^ source expression -> HsExpr GhcRn -- ^ expanded expression -> HsExpr GhcRn -- ^ suitably wrapped 'XXExprGhcRn' -mkExpandedExpr oExpr eExpr = XExpr (ExpandedThingRn (OrigExpr oExpr) eExpr) +mkExpandedExpr oExpr eExpr = XExpr (ExpandedThingRn (OrigExpr oExpr) eExpr TcExpr) -- | Build an expression using the extension constructor `XExpr`, -- and the two components of the expansion: original do stmt and -- expanded expression mkExpandedStmt :: ExprLStmt GhcRn -- ^ source statement + -> HsDoFlavour + -> TCFunInfo -> HsExpr GhcRn -- ^ expanded expression -> HsExpr GhcRn -- ^ suitably wrapped 'XXExprGhcRn' -mkExpandedStmt oStmt eExpr = XExpr (ExpandedThingRn (OrigStmt oStmt) eExpr) +mkExpandedStmt oStmt flav tc_fun eExpr = XExpr (ExpandedThingRn (OrigStmt oStmt flav) eExpr tc_fun) mkExpandedPatRn - :: LPat GhcRn -- ^ source pattern - -> HsExpr GhcRn -- ^ expanded expression - -> HsExpr GhcRn -- ^ suitably wrapped 'XXExprGhcRn' -mkExpandedPatRn oPat eExpr = XExpr (ExpandedThingRn (OrigPat oPat) eExpr) + :: LPat GhcRn -- ^ source pattern + -> Maybe (HsDoFlavour, ExprLStmt GhcRn) -- ^ pattern statement origin + -> HsExpr GhcRn -- ^ expanded expression + -> HsExpr GhcRn -- ^ suitably wrapped 'XXExprGhcRn' +mkExpandedPatRn oPat mb_stmt_info eExpr = XExpr (ExpandedThingRn (OrigPat oPat mb_stmt_info) eExpr TcExpr) -- | Build an expression using the extension constructor `XExpr`, -- and the two components of the expansion: original do stmt and @@ -538,17 +547,21 @@ mkExpandedPatRn oPat eExpr = XExpr (ExpandedThingRn (OrigPat oPat) eExpr) mkExpandedStmtAt :: SrcSpanAnnA -- ^ Location for the expansion expression -> ExprLStmt GhcRn -- ^ source statement + -> HsDoFlavour + -> TCFunInfo -> HsExpr GhcRn -- ^ expanded expression -> LHsExpr GhcRn -- ^ suitably wrapped located 'XXExprGhcRn' -mkExpandedStmtAt loc oStmt eExpr = L loc $ mkExpandedStmt oStmt eExpr +mkExpandedStmtAt loc oStmt flav tcFun eExpr = L loc $ mkExpandedStmt oStmt flav tcFun eExpr -- | Wrap the expanded version of the expression with a pop. mkExpandedStmtPopAt :: SrcSpanAnnA -- ^ Location for the expansion statement -> ExprLStmt GhcRn -- ^ source statement + -> HsDoFlavour + -> TCFunInfo -> HsExpr GhcRn -- ^ expanded expression -> LHsExpr GhcRn -- ^ suitably wrapped 'XXExprGhcRn' -mkExpandedStmtPopAt loc oStmt eExpr = mkPopErrCtxtExprAt loc $ mkExpandedStmtAt loc oStmt eExpr +mkExpandedStmtPopAt loc oStmt flav tc_fun eExpr = mkPopErrCtxtExprAt loc $ mkExpandedStmtAt loc oStmt flav tc_fun eExpr data XXExprGhcTc @@ -593,9 +606,10 @@ mkExpandedExprTc oExpr eExpr = XExpr (ExpandedThingTc (OrigExpr oExpr) eExpr) -- expanded typechecked expression. mkExpandedStmtTc :: ExprLStmt GhcRn -- ^ source do statement + -> HsDoFlavour -> HsExpr GhcTc -- ^ expanded typechecked expression -> HsExpr GhcTc -- ^ suitably wrapped 'XXExprGhcRn' -mkExpandedStmtTc oStmt eExpr = XExpr (ExpandedThingTc (OrigStmt oStmt) eExpr) +mkExpandedStmtTc oStmt flav eExpr = XExpr (ExpandedThingTc (OrigStmt oStmt flav) eExpr) {- ********************************************************************* * * @@ -836,13 +850,13 @@ instance Outputable HsThingRn where ppr thing = case thing of OrigExpr x -> ppr_builder ":" x - OrigStmt x -> ppr_builder ":" x - OrigPat x -> ppr_builder ":" x + OrigStmt x _ -> ppr_builder ":" x + OrigPat x _ -> ppr_builder ":" x where ppr_builder prefix x = ifPprDebug (braces (text prefix <+> parens (ppr x))) (ppr x) instance Outputable XXExprGhcRn where - ppr (ExpandedThingRn o e) = ifPprDebug (braces $ vcat [ppr o, ppr e]) (ppr o) - ppr (PopErrCtxt e) = ifPprDebug (braces (text "" <+> ppr e)) (ppr e) + ppr (ExpandedThingRn o e _) = ifPprDebug (braces $ vcat [ppr o, text ";;" , ppr e]) (ppr o) + ppr (PopErrCtxt e) = ifPprDebug (braces (text "" <+> ppr e)) (ppr e) instance Outputable XXExprGhcTc where ppr (WrapExpr (HsWrap co_fn e)) @@ -882,7 +896,7 @@ ppr_infix_expr (XExpr x) = case ghcPass @p of ppr_infix_expr _ = Nothing ppr_infix_expr_rn :: XXExprGhcRn -> Maybe SDoc -ppr_infix_expr_rn (ExpandedThingRn thing _) = ppr_infix_hs_expansion thing +ppr_infix_expr_rn (ExpandedThingRn thing _ _) = ppr_infix_hs_expansion thing ppr_infix_expr_rn (PopErrCtxt (L _ a)) = ppr_infix_expr a ppr_infix_expr_tc :: XXExprGhcTc -> Maybe SDoc @@ -993,7 +1007,7 @@ hsExprNeedsParens prec = go go_x_tc (HsBinTick _ _ (L _ e)) = hsExprNeedsParens prec e go_x_rn :: XXExprGhcRn -> Bool - go_x_rn (ExpandedThingRn thing _) = hsExpandedNeedsParens thing + go_x_rn (ExpandedThingRn thing _ _) = hsExpandedNeedsParens thing go_x_rn (PopErrCtxt (L _ a)) = hsExprNeedsParens prec a hsExpandedNeedsParens :: HsThingRn -> Bool @@ -1045,7 +1059,7 @@ isAtomicHsExpr (XExpr x) go_x_tc (HsBinTick {}) = False go_x_rn :: XXExprGhcRn -> Bool - go_x_rn (ExpandedThingRn thing _) = isAtomicExpandedThingRn thing + go_x_rn (ExpandedThingRn thing _ _) = isAtomicExpandedThingRn thing go_x_rn (PopErrCtxt (L _ a)) = isAtomicHsExpr a isAtomicExpandedThingRn :: HsThingRn -> Bool @@ -1568,7 +1582,7 @@ pprMatch (Match { m_pats = pats, m_ctxt = ctxt, m_grhss = grhss }) <+> pprInfixOcc fun <+> pprParendLPat opPrec p2 _ -> pprPanic "pprMatch" (ppr ctxt $$ ppr pats) - + StmtCtxt _ -> (char '\\', pats) LamAlt LamSingle -> (char '\\', pats) ArrowMatchCtxt (ArrowLamAlt LamSingle) -> (char '\\', pats) LamAlt LamCases -> lam_cases_result @@ -1609,6 +1623,7 @@ matchSeparator IfAlt = text "->" matchSeparator ArrowMatchCtxt{} = text "->" matchSeparator PatBindRhs = text "=" matchSeparator PatBindGuards = text "=" +matchSeparator (StmtCtxt (HsDoStmt{})) = text "->" matchSeparator StmtCtxt{} = text "<-" matchSeparator RecUpd = text "=" -- This can be printed by the pattern matchSeparator PatSyn = text "<-" -- match checker trace @@ -1668,7 +1683,7 @@ data XBindStmtTc = XBindStmtTc type instance XApplicativeStmt (GhcPass _) GhcPs = NoExtField type instance XApplicativeStmt (GhcPass _) GhcRn = NoExtField -type instance XApplicativeStmt (GhcPass _) GhcTc = Type +type instance XApplicativeStmt (GhcPass _) GhcTc = DataConCantHappen type instance XBodyStmt (GhcPass _) GhcPs b = NoExtField type instance XBodyStmt (GhcPass _) GhcRn b = NoExtField @@ -1690,7 +1705,7 @@ type instance XRecStmt (GhcPass _) GhcTc b = RecStmtTc type instance XXStmtLR (GhcPass _) GhcPs b = DataConCantHappen type instance XXStmtLR (GhcPass x) GhcRn b = ApplicativeStmt (GhcPass x) GhcRn -type instance XXStmtLR (GhcPass x) GhcTc b = ApplicativeStmt (GhcPass x) GhcTc +type instance XXStmtLR (GhcPass x) GhcTc b = DataConCantHappen -- | 'ApplicativeStmt' represents an applicative expression built with -- '<$>' and '<*>'. It is generated by the renamer, and is desugared into the @@ -1731,7 +1746,7 @@ data ApplicativeArg idL | ApplicativeArgMany -- do { stmts; return vars } { xarg_app_arg_many :: XApplicativeArgMany idL , app_stmts :: [ExprLStmt idL] -- stmts - , final_expr :: HsExpr idL -- return (v1,..,vn), or just (v1,..,vn) + , final_expr :: LHsExpr idL -- return (v1,..,vn), or just (v1,..,vn) , bv_pattern :: LPat idL -- (v1,...,vn) , stmt_context :: HsDoFlavour -- ^ context of the do expression, used in pprArg @@ -1750,7 +1765,7 @@ type instance XXParStmtBlock (GhcPass pL) (GhcPass pR) = DataConCantHappen type instance XApplicativeArgOne GhcPs = NoExtField type instance XApplicativeArgOne GhcRn = FailOperator GhcRn -type instance XApplicativeArgOne GhcTc = FailOperator GhcTc +type instance XApplicativeArgOne GhcTc = DataConCantHappen type instance XApplicativeArgMany (GhcPass _) = NoExtField type instance XXApplicativeArg (GhcPass _) = DataConCantHappen @@ -1796,7 +1811,6 @@ pprStmt (RecStmt { recS_stmts = segment, recS_rec_ids = rec_ids pprStmt (XStmtLR x) = case ghcPass :: GhcPass idR of GhcRn -> pprApplicativeStmt x - GhcTc -> pprApplicativeStmt x where pprApplicativeStmt :: (OutputableBndrId idL, OutputableBndrId idR) => ApplicativeStmt (GhcPass idL) (GhcPass idR) -> SDoc @@ -1817,7 +1831,6 @@ pprStmt (XStmtLR x) = case ghcPass :: GhcPass idR of flattenStmt :: ExprLStmt (GhcPass idL) -> [SDoc] flattenStmt (L _ (XStmtLR x)) = case ghcPass :: GhcPass idL of GhcRn | (ApplicativeStmt _ args _) <- x -> concatMap flattenArg args - GhcTc | (ApplicativeStmt _ args _) <- x -> concatMap flattenArg args flattenStmt stmt = [ppr stmt] flattenArg :: (a, ApplicativeArg (GhcPass idL)) -> [SDoc] @@ -1846,13 +1859,13 @@ instance (OutputableBndrId idL) pprArg :: forall idL . (OutputableBndrId idL) => ApplicativeArg (GhcPass idL) -> SDoc pprArg (ApplicativeArgOne _ pat expr isBody) - | isBody = ppr expr -- See Note [Applicative BodyStmt] - | otherwise = pprBindStmt pat expr + | isBody = whenPprDebug (text "[AppStmt]") <+> ppr expr -- See Note [Applicative BodyStmt] + | otherwise = whenPprDebug (text "[AppStmt]") <+> pprBindStmt pat expr pprArg (ApplicativeArgMany _ stmts return pat ctxt) = ppr pat <+> text "<-" <+> pprDo ctxt (stmts ++ - [noLocA (LastStmt noExtField (noLocA return) Nothing noSyntaxExpr)]) + [noLocA (LastStmt noExtField return Nothing noSyntaxExpr)]) pprTransformStmt :: (OutputableBndrId p) => [IdP (GhcPass p)] -> LHsExpr (GhcPass p) ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -569,6 +569,7 @@ deriving instance Eq (IE GhcTc) -- --------------------------------------------------------------------- deriving instance Data HsThingRn +deriving instance Data TCFunInfo deriving instance Data XXExprGhcRn deriving instance Data XXExprGhcTc deriving instance Data XXPatGhcTc ===================================== compiler/GHC/Hs/Utils.hs ===================================== @@ -1188,7 +1188,6 @@ collectStmtBinders flag = \case RecStmt { recS_stmts = L _ ss } -> collectLStmtsBinders flag ss XStmtLR x -> case ghcPass :: GhcPass idR of GhcRn -> collectApplicativeStmtBndrs x - GhcTc -> collectApplicativeStmtBndrs x where collectApplicativeStmtBndrs :: ApplicativeStmt (GhcPass idL) a -> [IdP (GhcPass idL)] collectApplicativeStmtBndrs (ApplicativeStmt _ args _) = concatMap (collectArgBinders . snd) args @@ -1781,7 +1780,6 @@ lStmtsImplicits = hs_lstmts hs_stmt (BindStmt _ pat _) = lPatImplicits pat hs_stmt (XStmtLR x) = case ghcPass :: GhcPass idR of GhcRn -> hs_applicative_stmt x - GhcTc -> hs_applicative_stmt x hs_stmt (LetStmt _ binds) = hs_local_binds binds hs_stmt (BodyStmt {}) = [] hs_stmt (LastStmt {}) = [] ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -315,7 +315,7 @@ dsExpr (HsOverLit _ lit) dsExpr e@(XExpr ext_expr_tc) = case ext_expr_tc of ExpandedThingTc o e - | OrigStmt (L loc _) <- o + | OrigStmt (L loc _) _ <- o -> putSrcSpanDsA loc $ dsExpr e | otherwise -> dsExpr e WrapExpr {} -> dsHsWrapped e @@ -463,10 +463,10 @@ dsExpr (HsLet _ binds body) = do -- because the interpretation of `stmts' depends on what sort of thing it is. -- dsExpr (HsDo res_ty ListComp (L _ stmts)) = dsListComp stmts res_ty -dsExpr (HsDo res_ty ctx at DoExpr{} (L _ stmts)) = dsDo ctx stmts res_ty -dsExpr (HsDo res_ty ctx at GhciStmtCtxt (L _ stmts)) = dsDo ctx stmts res_ty -dsExpr (HsDo res_ty ctx at MDoExpr{} (L _ stmts)) = dsDo ctx stmts res_ty dsExpr (HsDo _ MonadComp (L _ stmts)) = dsMonadComp stmts +dsExpr (HsDo res_ty ctx at GhciStmtCtxt (L _ stmts)) = dsDo ctx stmts res_ty +dsExpr (HsDo _ DoExpr{} (L _ stmts)) = pprPanic "shouldn't happen dsDo DoExpr" (ppr stmts) +dsExpr (HsDo _ MDoExpr{} (L _ stmts)) = pprPanic "shouldn't happen dsDo MDoExpr" (ppr stmts) dsExpr (HsIf _ guard_expr then_expr else_expr) = do { pred <- dsLExpr guard_expr @@ -823,37 +823,6 @@ dsDo ctx stmts res_ty -- which ignores the return_op in the LastStmt, -- so we must apply the return_op explicitly - go _ (XStmtLR (ApplicativeStmt body_ty args mb_join)) stmts - = do { - let - (pats, rhss) = unzip (map (do_arg . snd) args) - - do_arg (ApplicativeArgOne fail_op pat expr _) = - ((pat, fail_op), dsLExpr expr) - do_arg (ApplicativeArgMany _ stmts ret pat _) = - ((pat, Nothing), dsDo ctx (stmts ++ [noLocA $ mkLastStmt (noLocA ret)]) res_ty) - - ; rhss' <- sequence rhss - - ; body' <- dsLExpr $ noLocA $ HsDo body_ty ctx (noLocA stmts) - - ; let match_args (pat, fail_op) (vs,body) - = putSrcSpanDs (getLocA pat) $ - do { var <- selectSimpleMatchVarL ManyTy pat - ; match <- matchSinglePatVar var Nothing (StmtCtxt (HsDoStmt ctx)) pat - body_ty (cantFailMatchResult body) - ; match_code <- dsHandleMonadicFailure ctx pat body_ty match fail_op - ; return (var:vs, match_code) - } - - ; (vars, body) <- foldrM match_args ([],body') pats - ; let fun' = mkLams vars body - ; let mk_ap_call l (op,r) = dsSyntaxExpr op [l,r] - ; expr <- foldlM mk_ap_call fun' (zip (map fst args) rhss') - ; case mb_join of - Nothing -> return expr - Just join_op -> dsSyntaxExpr join_op [expr] } - go _ (ParStmt {}) _ = panic "dsDo ParStmt" go _ (TransStmt {}) _ = panic "dsDo TransStmt" ===================================== compiler/GHC/HsToCore/GuardedRHSs.hs ===================================== @@ -144,8 +144,6 @@ matchGuards (LastStmt {} : _) _ _ _ _ = panic "matchGuards LastStmt" matchGuards (ParStmt {} : _) _ _ _ _ = panic "matchGuards ParStmt" matchGuards (TransStmt {} : _) _ _ _ _ = panic "matchGuards TransStmt" matchGuards (RecStmt {} : _) _ _ _ _ = panic "matchGuards RecStmt" -matchGuards (XStmtLR ApplicativeStmt {} : _) _ _ _ _ = - panic "matchGuards ApplicativeLastStmt" {- Should {\em fail} if @e@ returns @D@ ===================================== compiler/GHC/HsToCore/ListComp.hs ===================================== @@ -257,9 +257,6 @@ deListComp (ParStmt _ stmtss_w_bndrs _ _ : quals) list deListComp (RecStmt {} : _) _ = panic "deListComp RecStmt" -deListComp (XStmtLR ApplicativeStmt {} : _) _ = - panic "deListComp ApplicativeStmt" - deBindComp :: LPat GhcTc -> CoreExpr -> [ExprStmt GhcTc] @@ -352,8 +349,6 @@ dfListComp c_id n_id (BindStmt _ pat list1 : quals) = do dfListComp _ _ (ParStmt {} : _) = panic "dfListComp ParStmt" dfListComp _ _ (RecStmt {} : _) = panic "dfListComp RecStmt" -dfListComp _ _ (XStmtLR ApplicativeStmt {} : _) = - panic "dfListComp ApplicativeStmt" dfBindComp :: Id -> Id -- 'c' and 'n' -> (LPat GhcTc, CoreExpr) @@ -580,7 +575,6 @@ dsMcStmt (ParStmt bind_ty blocks mzip_op bind_op) stmts_rest = do { exp <- dsInnerMonadComp stmts bndrs return_op ; return (exp, mkBigCoreVarTupTy bndrs) } -dsMcStmt stmt@(XStmtLR ApplicativeStmt {}) _ = pprPanic "dsMcStmt: unexpected stmt" (ppr stmt) dsMcStmt stmt@(RecStmt {}) _ = pprPanic "dsMcStmt: unexpected stmt" (ppr stmt) matchTuple :: [Id] -> CoreExpr -> DsM CoreExpr ===================================== compiler/GHC/HsToCore/Pmc/Desugar.hs ===================================== @@ -373,7 +373,6 @@ desugarGuard guard = case guard of ParStmt {} -> panic "desugarGuard ParStmt" TransStmt {} -> panic "desugarGuard TransStmt" RecStmt {} -> panic "desugarGuard RecStmt" - XStmtLR ApplicativeStmt{} -> panic "desugarGuard ApplicativeLastStmt" sequenceGrdDagMapM :: Applicative f => (a -> f GrdDag) -> [a] -> f GrdDag sequenceGrdDagMapM f as = sequenceGrdDags <$> traverse f as ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -1684,7 +1684,7 @@ repE (HsProjection _ xs) = repProjection (fmap (field_label . unLoc . dfoLabel . repE (HsEmbTy _ t) = do t1 <- repLTy (hswc_body t) rep2 typeEName [unC t1] -repE e@(XExpr (ExpandedThingRn o x)) +repE e@(XExpr (ExpandedThingRn o x _)) | OrigExpr e <- o = do { rebindable_on <- lift $ xoptM LangExt.RebindableSyntax ; if rebindable_on -- See Note [Quotation and rebindable syntax] ===================================== compiler/GHC/HsToCore/Ticks.hs ===================================== @@ -611,7 +611,7 @@ addTickHsExpr (HsDo srcloc cxt (L l stmts)) _ -> Nothing addTickHsExpanded :: HsThingRn -> HsExpr GhcTc -> TM (HsExpr GhcTc) -addTickHsExpanded o@(OrigStmt (L pos LastStmt{})) e +addTickHsExpanded o@(OrigStmt (L pos LastStmt{}) _) e -- LastStmt always gets a tick for breakpoint and hpc coverage = do d <- getDensity case d of @@ -752,33 +752,10 @@ addTickStmt isGuard stmt@(RecStmt {}) ; return (stmt { recS_stmts = noLocA stmts', recS_ret_fn = ret' , recS_mfix_fn = mfix', recS_bind_fn = bind' }) } -addTickStmt isGuard (XStmtLR (ApplicativeStmt body_ty args mb_join)) = do - args' <- mapM (addTickApplicativeArg isGuard) args - return (XStmtLR (ApplicativeStmt body_ty args' mb_join)) - addTick :: Maybe (Bool -> BoxLabel) -> LHsExpr GhcTc -> TM (LHsExpr GhcTc) addTick isGuard e | Just fn <- isGuard = addBinTickLHsExpr fn e | otherwise = addTickLHsExprRHS e -addTickApplicativeArg - :: Maybe (Bool -> BoxLabel) -> (SyntaxExpr GhcTc, ApplicativeArg GhcTc) - -> TM (SyntaxExpr GhcTc, ApplicativeArg GhcTc) -addTickApplicativeArg isGuard (op, arg) = - liftM2 (,) (addTickSyntaxExpr hpcSrcSpan op) (addTickArg arg) - where - addTickArg (ApplicativeArgOne m_fail pat expr isBody) = - ApplicativeArgOne - <$> mapM (addTickSyntaxExpr hpcSrcSpan) m_fail - <*> addTickLPat pat - <*> addTickLHsExpr expr - <*> pure isBody - addTickArg (ApplicativeArgMany x stmts ret pat ctxt) = - (ApplicativeArgMany x) - <$> addTickLStmts isGuard stmts - <*> (unLoc <$> addTickLHsExpr (L (noAnnSrcSpan hpcSrcSpan) ret)) - <*> addTickLPat pat - <*> pure ctxt - addTickStmtAndBinders :: Maybe (Bool -> BoxLabel) -> ParStmtBlock GhcTc GhcTc -> TM (ParStmtBlock GhcTc GhcTc) addTickStmtAndBinders isGuard (ParStmtBlock x stmts ids returnExpr) = @@ -967,8 +944,6 @@ addTickCmdStmt stmt@(RecStmt {}) ; bind' <- addTickSyntaxExpr hpcSrcSpan (recS_bind_fn stmt) ; return (stmt { recS_stmts = noLocA stmts', recS_ret_fn = ret' , recS_mfix_fn = mfix', recS_bind_fn = bind' }) } -addTickCmdStmt (XStmtLR (ApplicativeStmt{})) = - panic "ToDo: addTickCmdStmt ApplicativeLastStmt" -- Others should never happen in a command context. addTickCmdStmt stmt = pprPanic "addTickHsCmd" (ppr stmt) ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1372,7 +1372,6 @@ instance ( ToHie (LocatedA (body (GhcPass p))) ] XStmtLR x -> case hiePass @p of HieRn -> extApplicativeStmt x - HieTc -> extApplicativeStmt x where node = case hiePass @p of HieTc -> makeNodeA stmt span ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -1965,15 +1965,10 @@ ApplicativeDo touches a few phases in the compiler: don't exist in the source code. See ApplicativeStmt and ApplicativeArg in HsExpr. -* Typechecker: ApplicativeDo passes through the typechecker much like any - other form of expression. The only crux is that the typechecker has to - be aware of the special ApplicativeDo statements in the do-notation, and - typecheck them appropriately. - Relevant module: GHC.Tc.Gen.Match - -* Desugarer: Any do-block which contains applicative statements is desugared - as outlined above, to use the Applicative combinators. - Relevant module: GHC.HsToCore.Expr +* Typechecker: All the ApplicativeDo statements are expanded on the fly + to its actual semantics (as shown above) with appropriate user syntax. The typechecker + then checks the syntax as any other form of expression. + Relevant module: GHC.Tc.Gen.Do , GHC.Tc.Gen.Match.tcStmts -} @@ -2221,12 +2216,12 @@ stmtTreeToStmts monad_names ctxt (StmtTreeApplicative trees) tail tail_fvs = do (stmts',fvs2) <- stmtTreeToStmts monad_names ctxt tree [] pvarset (mb_ret, fvs1) <- if | L _ (XStmtLR ApplicativeStmt{}) <- last stmts' -> - return (unLoc tup, emptyNameSet) + return (tup, emptyNameSet) | otherwise -> do -- Need 'pureAName' and not 'returnMName' here, so that it requires -- 'Applicative' and not 'Monad' whenever possible (until #20540 is fixed). (ret, _) <- lookupQualifiedDoExpr (HsDoStmt ctxt) pureAName - let expr = HsApp noExtField (noLocA ret) tup + let expr = noLocA (HsApp noExtField (noLocA ret) tup) return (expr, emptyFVs) return ( ApplicativeArgMany { xarg_app_arg_many = noExtField ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -464,10 +464,12 @@ tcValArgs do_ql args -- Now check the argument ; arg' <- tcScalingUsage mult $ - do { traceTc "tcEValArg" $ - vcat [ ppr ctxt - , text "arg type:" <+> ppr arg_ty - , text "arg:" <+> ppr arg ] + do { ingencode <- inGeneratedCode + ; traceTc "tcEValArg" $ + vcat [ ppr ctxt + , text "arg type:" <+> ppr arg_ty + , text "arg:" <+> ppr arg + , ppr ingencode ] ; tcEValArg ctxt arg arg_ty } ; return (eva { eva_arg = ValArg arg' @@ -537,7 +539,7 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args fun_orig | VAExpansion (OrigStmt{}) _ _ <- fun_ctxt = DoOrigin - | VAExpansion (OrigPat pat) _ _ <- fun_ctxt + | VAExpansion (OrigPat pat _) _ _ <- fun_ctxt = DoPatOrigin pat | VAExpansion (OrigExpr e) _ _ <- fun_ctxt = exprCtOrigin e @@ -731,9 +733,8 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args -- representation; matchActualFunTy checks that when -- taking apart the arrow type (a -> Int). matchActualFunTy herald - (Just $ HsExprTcThing tc_fun) - (n_val_args, fun_sigma) fun_ty - + (Just $ HsExprTcThing tc_fun) + (n_val_args, fun_sigma) fun_ty ; (delta', arg') <- if do_ql then addArgCtxt ctxt arg $ -- Context needed for constraints @@ -796,28 +797,37 @@ addArgCtxt :: AppCtxt -> LHsExpr GhcRn addArgCtxt ctxt (L arg_loc arg) thing_inside = do { in_generated_code <- inGeneratedCode ; case ctxt of - VACall fun arg_no _ | not in_generated_code + VACall _ _ _ + | XExpr (PopErrCtxt{}) <- arg + -> thing_inside + VACall _ _ _ + | XExpr (ExpandedThingRn o _ _) <- arg + , isHsThingRnStmt o || isHsThingRnPat o + -> thing_inside + + VACall fun arg_no _ + | not in_generated_code -> do setSrcSpanA arg_loc $ addErrCtxt (funAppCtxt fun arg arg_no) $ thing_inside - VAExpansion (OrigStmt (L _ stmt@(BindStmt {}))) _ loc + VAExpansion (OrigStmt (L _ stmt@(BindStmt {})) flav) _ loc | isGeneratedSrcSpan (locA arg_loc) -- This arg is the second argument to generated (>>=) -> setSrcSpan loc $ - addStmtCtxt stmt $ + addStmtCtxt stmt flav $ thing_inside - | otherwise -- This arg is the first argument to generated (>>=) + | otherwise -- This arg is the first argument to generated (>>=) -> setSrcSpanA arg_loc $ - addStmtCtxt stmt $ + addStmtCtxt stmt flav $ thing_inside - VAExpansion (OrigStmt (L loc stmt)) _ _ + VAExpansion (OrigStmt (L loc stmt) flav) _ _ -> setSrcSpanA loc $ - addStmtCtxt stmt $ + addStmtCtxt stmt flav $ thing_inside _ -> setSrcSpanA arg_loc $ - addExprCtxt arg $ -- Auto-suppressed if arg_loc is generated - thing_inside } + addExprCtxt arg $ -- Auto-suppressed if arg_loc is generated + thing_inside } {- ********************************************************************* * * @@ -943,7 +953,7 @@ expr_to_type earg = | otherwise = not_in_scope where occ = occName rdr not_in_scope = failWith $ mkTcRnNotInScope rdr NotInScope - go (L l (XExpr (ExpandedThingRn (OrigExpr orig) _))) = + go (L l (XExpr (ExpandedThingRn (OrigExpr orig) _ _))) = -- Use the original, user-written expression (before expansion). -- Example. Say we have vfun :: forall a -> blah -- and the call vfun (Maybe [1,2,3]) ===================================== compiler/GHC/Tc/Gen/Do.hs ===================================== @@ -21,8 +21,8 @@ module GHC.Tc.Gen.Do (expandDoStmts) where import GHC.Prelude -import GHC.Rename.Utils ( wrapGenSpan, genHsExpApps, genHsApp, genHsLet, - genHsLamDoExp, genHsCaseAltDoExp, genWildPat ) +import GHC.Rename.Utils ( wrapGenSpan, genHsExpApps, genHsApp, genHsLet, genLHsApp, + genHsLamDoExp, genHsCaseAltDoExp ) import GHC.Tc.Utils.Monad import GHC.Tc.Gen.Pat import GHC.Tc.Utils.TcMType @@ -53,66 +53,56 @@ import Data.List ((\\)) -- so that they can be typechecked. -- See Note [Expanding HsDo with XXExprGhcRn] below for `HsDo` specific commentary -- and Note [Handling overloaded and rebindable constructs] for high level commentary -expandDoStmts :: HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (LHsExpr GhcRn) -expandDoStmts doFlav stmts = do expanded_expr <- expand_do_stmts doFlav stmts - case expanded_expr of - L _ (XExpr (PopErrCtxt e)) -> return e - -- The first expanded stmt doesn't need a pop as - -- it would otherwise pop the "In the expression do ... " from - -- the error context - _ -> return expanded_expr +expandDoStmts :: HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (HsExpr GhcRn) +expandDoStmts doFlav stmts = unLoc <$> expand_do_stmts False doFlav stmts -- | The main work horse for expanding do block statements into applications of binds and thens -- See Note [Expanding HsDo with XXExprGhcRn] -expand_do_stmts :: HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (LHsExpr GhcRn) +expand_do_stmts :: Bool -> HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (LHsExpr GhcRn) -expand_do_stmts ListComp _ = +expand_do_stmts _ ListComp _ = pprPanic "expand_do_stmts: impossible happened. ListComp" empty -- handeled by `GHC.Tc.Gen.Match.tcLcStmt` -expand_do_stmts _ [] = pprPanic "expand_do_stmts: impossible happened. Empty stmts" empty +expand_do_stmts _ _ [] = pprPanic "expand_do_stmts: impossible happened. Empty stmts" empty -expand_do_stmts _ (stmt@(L _ (TransStmt {})):_) = +expand_do_stmts _ _ (stmt@(L _ (TransStmt {})):_) = pprPanic "expand_do_stmts: TransStmt" $ ppr stmt -- handeled by `GHC.Tc.Gen.Match.tcLcStmt` -expand_do_stmts _ (stmt@(L _ (ParStmt {})):_) = +expand_do_stmts _ _ (stmt@(L _ (ParStmt {})):_) = pprPanic "expand_do_stmts: ParStmt" $ ppr stmt -- handeled by `GHC.Tc.Gen.Match.tcLcStmt` -expand_do_stmts _ (stmt@(L _ (XStmtLR ApplicativeStmt{})): _) = - pprPanic "expand_do_stmts: Applicative Stmt" $ ppr stmt - -- Handeled by tcSyntaxOp see `GHC.Tc.Gen.Match.tcStmtsAndThen` - - -expand_do_stmts _ [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_expr))] +expand_do_stmts addPop flav [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_expr))] -- See Note [Expanding HsDo with XXExprGhcRn] Equation (5) below -- last statement of a list comprehension, needs to explicitly return it -- See `checkLastStmt` and `Syntax.Expr.StmtLR.LastStmt` | NoSyntaxExprRn <- ret_expr -- Last statement is just body if we are not in ListComp context. See Syntax.Expr.LastStmt - = do traceTc "expand_do_stmts last" (ppr ret_expr) - return $ mkExpandedStmtPopAt loc stmt body + = return $ if addPop then mkExpandedStmtPopAt loc stmt flav TcExpr body + else mkExpandedStmtAt loc stmt flav TcExpr body | SyntaxExprRn ret <- ret_expr -- -- ------------------------------------------------ -- return e ~~> return e -- to make T18324 work - = do traceTc "expand_do_stmts last" (ppr ret_expr) - let expansion = genHsApp ret (L body_loc body) - return $ mkExpandedStmtPopAt loc stmt expansion + = do let expansion = genHsApp ret (L body_loc body) + return $ if addPop then mkExpandedStmtPopAt loc stmt flav TcExpr expansion + else mkExpandedStmtAt loc stmt flav TcExpr expansion -expand_do_stmts do_or_lc (stmt@(L loc (LetStmt _ bs)) : lstmts) = +expand_do_stmts addPop doFlavour (stmt@(L loc (LetStmt _ bs)) : lstmts) = -- See Note [Expanding HsDo with XXExprGhcRn] Equation (3) below -- stmts ~~> stmts' -- ------------------------------------------------ -- let x = e ; stmts ~~> let x = e in stmts' - do expand_stmts <- expand_do_stmts do_or_lc lstmts + do expand_stmts <- expand_do_stmts True doFlavour lstmts let expansion = genHsLet bs expand_stmts - return $ mkExpandedStmtPopAt loc stmt expansion + return $ if addPop then mkExpandedStmtPopAt loc stmt doFlavour TcExpr expansion + else mkExpandedStmtAt loc stmt doFlavour TcExpr expansion -expand_do_stmts do_or_lc (stmt@(L loc (BindStmt xbsrn pat e)): lstmts) +expand_do_stmts addPop doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts) | SyntaxExprRn bind_op <- xbsrn_bindOp xbsrn , fail_op <- xbsrn_failOp xbsrn -- See Note [Expanding HsDo with XXExprGhcRn] Equation (2) below @@ -121,29 +111,31 @@ expand_do_stmts do_or_lc (stmt@(L loc (BindStmt xbsrn pat e)): lstmts) -- _ -> fail "Pattern match failure .." -- ------------------------------------------------------- -- pat <- e ; stmts ~~> (>>=) e f - = do expand_stmts <- expand_do_stmts do_or_lc lstmts - failable_expr <- mk_failable_expr do_or_lc pat expand_stmts fail_op + = do expand_stmts <- expand_do_stmts True doFlavour lstmts + failable_expr <- mk_failable_expr doFlavour Nothing pat expand_stmts fail_op let expansion = genHsExpApps bind_op -- (>>=) [ e , failable_expr ] - return $ mkExpandedStmtPopAt loc stmt expansion + return $ if addPop then mkExpandedStmtPopAt loc stmt doFlavour TcApp expansion + else mkExpandedStmtAt loc stmt doFlavour TcApp expansion | otherwise = pprPanic "expand_do_stmts: The impossible happened, missing bind operator from renamer" (text "stmt" <+> ppr stmt) -expand_do_stmts do_or_lc (stmt@(L loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) = +expand_do_stmts addPop doFlavour (stmt@(L loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) = -- See Note [BodyStmt] in Language.Haskell.Syntax.Expr -- See Note [Expanding HsDo with XXExprGhcRn] Equation (1) below -- stmts ~~> stmts' -- ---------------------------------------------- -- e ; stmts ~~> (>>) e stmts' - do expand_stmts_expr <- expand_do_stmts do_or_lc lstmts + do expand_stmts_expr <- expand_do_stmts True doFlavour lstmts let expansion = genHsExpApps then_op -- (>>) [ e , expand_stmts_expr ] - return $ mkExpandedStmtPopAt loc stmt expansion + return $ if addPop then mkExpandedStmtPopAt loc stmt doFlavour TcApp expansion + else mkExpandedStmtAt loc stmt doFlavour TcApp expansion -expand_do_stmts do_or_lc +expand_do_stmts _ doFlavour ((L loc (RecStmt { recS_stmts = L stmts_loc rec_stmts , recS_later_ids = later_ids -- forward referenced local ids , recS_rec_ids = local_ids -- ids referenced outside of the rec block @@ -163,12 +155,12 @@ expand_do_stmts do_or_lc -- -> do { rec_stmts -- ; return (local_only_ids ++ later_ids) } )) -- (\ [ local_only_ids ++ later_ids ] -> stmts') - do expand_stmts <- expand_do_stmts do_or_lc lstmts + do expand_stmts <- expand_do_stmts True doFlavour lstmts -- NB: No need to wrap the expansion with an ExpandedStmt -- as we want to flatten the rec block statements into its parent do block anyway return $ mkHsApps (wrapGenSpan bind_fun) -- (>>=) [ (wrapGenSpan mfix_fun) `mkHsApp` mfix_expr -- (mfix (do block)) - , genHsLamDoExp do_or_lc [ mkBigLHsVarPatTup all_ids ] -- (\ x -> + , genHsLamDoExp doFlavour [ mkBigLHsVarPatTup all_ids ] -- (\ x -> expand_stmts -- stmts') ] where @@ -184,33 +176,112 @@ expand_do_stmts do_or_lc do_stmts :: XRec GhcRn [ExprLStmt GhcRn] do_stmts = L stmts_loc $ rec_stmts ++ [return_stmt] do_block :: LHsExpr GhcRn - do_block = L loc $ HsDo noExtField do_or_lc do_stmts + do_block = L loc $ HsDo noExtField doFlavour do_stmts mfix_expr :: LHsExpr GhcRn - mfix_expr = genHsLamDoExp do_or_lc [ wrapGenSpan (LazyPat noExtField $ mkBigLHsVarPatTup all_ids) ] + mfix_expr = genHsLamDoExp doFlavour [ wrapGenSpan (LazyPat noExtField $ mkBigLHsVarPatTup all_ids) ] $ do_block -- NB: LazyPat because we do not want to eagerly evaluate the pattern -- and potentially loop forever -expand_do_stmts _ stmts = pprPanic "expand_do_stmts: impossible happened" $ (ppr stmts) +expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join))): lstmts) = +-- See Note [Applicative BodyStmt] +-- +-- stmts ~~> stmts' +-- ------------------------------------------------------------------------- +-- [(fmap, \ x -> e1), (<*>, e2), (<*>, e3), .. ] ; stmts ~~> (\ x -> stmts') <$> e1 <*> e2 ... +-- +-- Very similar to HsToCore.Expr.dsDo + +-- args are [(<$>, e1), (<*>, e2), .., ] + do { xexpr <- expand_do_stmts False doFlavour lstmts + -- extracts pats and arg bodies (rhss) from args + + ; (pats_can_fail, rhss) <- unzip <$> mapM (do_arg . snd) args + + -- add blocks for failable patterns + ; body_with_fails <- foldrM match_args xexpr (zip pats_can_fail rhss) + + -- builds (body <$> e1 <*> e2 ...) + ; let expand_ado_expr = foldl mk_apps body_with_fails (zip (map fst args) rhss) + + -- wrap the expanded expression with a `join` if needed + ; let final_expr = case mb_join of + Just (SyntaxExprRn join_op) + -> genLHsApp join_op expand_ado_expr + _ -> expand_ado_expr + ; traceTc "expand_do_stmts AppStmt" (vcat [ text "args:" <+> ppr args + , text "lstmts:" <+> ppr lstmts + , text "mb_join:" <+> ppr mb_join + , text "expansion:" <+> ppr final_expr]) + ; return $ final_expr + + } + where + do_arg :: ApplicativeArg GhcRn -> TcM ((LPat GhcRn, FailOperator GhcRn), LHsExpr GhcRn) + do_arg (ApplicativeArgOne + { xarg_app_arg_one = mb_fail_op + , app_arg_pattern = pat + , arg_expr = (L rhs_loc rhs) + , is_body_stmt = is_body_stmt + }) = + do let xx_expr = if addPop then mkExpandedStmtPopAt rhs_loc stmt doFlavour TcExpr rhs + else mkExpandedStmtAt rhs_loc stmt doFlavour TcExpr rhs + traceTc "do_arg" (text "OneArg" <+> vcat [ppr pat, ppr xx_expr]) + return ((pat, mb_fail_op) + , xx_expr) + where stmt = if is_body_stmt + then (L rhs_loc (BodyStmt NoExtField (L rhs_loc rhs) NoSyntaxExprRn NoSyntaxExprRn)) + else (L rhs_loc (BindStmt xbsn pat (L rhs_loc rhs))) + do_arg (ApplicativeArgMany _ stmts ret@(L ret_loc _) pat ctxt) = + do { xx_expr <- expand_do_stmts False ctxt $ stmts ++ [L ret_loc $ mkLastStmt ret] + ; traceTc "do_arg" (text "ManyArg" <+> vcat [ppr stmts, text "--", ppr xx_expr]) + ; return ((pat, Nothing) + , xx_expr) } + + match_args :: ((LPat GhcRn, FailOperator GhcRn), LHsExpr GhcRn) -> LHsExpr GhcRn -> TcM (LHsExpr GhcRn) + match_args ((pat, fail_op), stmt_expr) body = mk_failable_expr doFlavour stmt_ctxt pat body fail_op + where stmt_ctxt = case unLoc stmt_expr of + XExpr (ExpandedThingRn (OrigStmt s _) _ _) -> Just (doFlavour, s) + _ -> Nothing + + mk_apps :: LHsExpr GhcRn -> (SyntaxExprRn, LHsExpr GhcRn) -> LHsExpr GhcRn + mk_apps l_expr (op, r_expr) = + case op of + SyntaxExprRn op -> wrapGenSpan $ genHsExpApps op [ l_expr, r_expr ] + NoSyntaxExprRn -> pprPanic "expand_do_stmts applicative op:" (ppr op) + + xbsn :: XBindStmtRn + xbsn = XBindStmtRn NoSyntaxExprRn Nothing + + +expand_do_stmts _ _ stmts = pprPanic "expand_do_stmts: impossible happened" $ (ppr stmts) -- checks the pattern `pat`for irrefutability which decides if we need to wrap it with a fail block -mk_failable_expr :: HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (LHsExpr GhcRn) -mk_failable_expr doFlav pat@(L loc _) expr fail_op = +mk_failable_expr :: HsDoFlavour -> Maybe (HsDoFlavour, ExprLStmt GhcRn) + -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (LHsExpr GhcRn) +mk_failable_expr doFlav mb_stmt_info lpat@(L loc pat) expr fail_op = do { is_strict <- xoptM LangExt.Strict - ; irrf_pat <- isIrrefutableHsPatRnTcM is_strict pat - ; traceTc "mk_failable_expr" (vcat [ text "pat:" <+> ppr pat + ; irrf_pat <- isIrrefutableHsPatRnTcM is_strict lpat + ; traceTc "mk_failable_expr" (vcat [ text "pat:" <+> ppr lpat , text "isIrrefutable:" <+> ppr irrf_pat ]) ; if irrf_pat -- don't wrap with fail block if -- the pattern is irrefutable - then return $ genHsLamDoExp doFlav [pat] expr - else L loc <$> mk_fail_block doFlav pat expr fail_op + then case pat of + (WildPat{}) -> return $ genHsLamDoExp doFlav [L noSrcSpanA pat] expr + _ -> return $ case mb_stmt_info of + Nothing -> genHsLamDoExp doFlav [lpat] expr + Just (f, s) -> wrapGenSpan (mkExpandedStmt s f TcExpr + (unLoc $ (genHsLamDoExp f [lpat] + $ wrapGenSpan (mkPopErrCtxtExpr expr)))) + else L loc <$> mk_fail_block doFlav mb_stmt_info lpat expr fail_op } -- makes the fail block with a given fail_op -mk_fail_block :: HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (HsExpr GhcRn) -mk_fail_block doFlav pat@(L ploc _) e (Just (SyntaxExprRn fail_op)) = +mk_fail_block :: HsDoFlavour -> Maybe (HsDoFlavour, ExprLStmt GhcRn) + -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (HsExpr GhcRn) +mk_fail_block doFlav mb_stmt_info pat@(L ploc _) e (Just (SyntaxExprRn fail_op)) = do dflags <- getDynFlags return $ HsLam noAnn LamCases $ mkMatchGroup (doExpansionOrigin doFlav) -- \ (wrapGenSpan [ genHsCaseAltDoExp doFlav pat e -- pat -> expr @@ -218,22 +289,22 @@ mk_fail_block doFlav pat@(L ploc _) e (Just (SyntaxExprRn fail_op)) = ]) where fail_alt_case :: DynFlags -> LPat GhcRn -> HsExpr GhcRn -> LMatch GhcRn (LHsExpr GhcRn) - fail_alt_case dflags pat fail_op = genHsCaseAltDoExp doFlav genWildPat $ + fail_alt_case dflags pat fail_op = genHsCaseAltDoExp doFlav (L ploc $ WildPat noExtField) $ L ploc (fail_op_expr dflags pat fail_op) fail_op_expr :: DynFlags -> LPat GhcRn -> HsExpr GhcRn -> HsExpr GhcRn fail_op_expr dflags pat fail_op - = mkExpandedPatRn pat $ + = mkExpandedPatRn pat mb_stmt_info $ genHsApp fail_op (mk_fail_msg_expr dflags pat) mk_fail_msg_expr :: DynFlags -> LPat GhcRn -> LHsExpr GhcRn mk_fail_msg_expr dflags pat = nlHsLit $ mkHsString $ showPpr dflags $ - text "Pattern match failure in" <+> pprHsDoFlavour (DoExpr Nothing) + text "Pattern match failure in" <+> pprHsDoFlavour doFlav <+> text "at" <+> ppr (getLocA pat) -mk_fail_block _ _ _ _ = pprPanic "mk_fail_block: impossible happened" empty +mk_fail_block _ _ _ _ _ = pprPanic "mk_fail_block: impossible happened" empty {- Note [Expanding HsDo with XXExprGhcRn] @@ -302,12 +373,29 @@ They capture the essence of statement expansions as implemented in `expand_do_st (5) DO【 s 】 = s + (4) DO【 AppStmt s; ss 】 + = APPSTMT【 (AppStmt s, ss) 】 + + RECDO【 _ 】 maps a sequence of recursively dependent monadic statements and converts it into an expression paired with the variables that the rec finds a fix point of. (6) RECDO【 ss 】 = (vars, mfix (\~vars -> (>>=) (DO【 ss 】) (return vars))) where vars are all the variables free in ss + APPSTMT【 _ 】 expands the applicative statements as given in Note [ApplicativeDo] in GHC.Rename.Expr (dsDo) + The applicative statement is generated by GHC.Rename.Expr.postProcessStmtsForApplicativeDo + + + (7) APPSTMT 【 (AppStmt (s1 | s2 ... | sn), ss) 】 + = join (\argpat (s1) .. argpat(sn) -> DO 【 ss 】) + <$> ‹ExpansionStmt s1› argexpr(arg_1) + <*> ... + <*> ‹PopErrCtxt› ‹ExpansionStmt s1› argexpr(arg_n) + + where argpat (p <- s) = p + argexpr(p <- s) = s + For a concrete example, consider a `do`-block written by the user ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -710,27 +710,25 @@ tcXExpr (PopErrCtxt (L loc e)) res_ty setSrcSpanA loc $ tcExpr e res_ty -tcXExpr xe@(ExpandedThingRn o e') res_ty - | OrigStmt ls@(L loc s at LetStmt{}) <- o +tcXExpr xe@(ExpandedThingRn o e' tc_info) res_ty + | OrigStmt ls@(L loc s at LetStmt{}) flav <- o , HsLet x binds e <- e' = do { (binds', wrapper, e') <- setSrcSpanA loc $ - addStmtCtxt s $ + addStmtCtxt s flav $ tcLocalBinds binds $ tcMonoExprNC e res_ty -- NB: Do not call tcMonoExpr here as it adds -- a duplicate error context - ; return $ mkExpandedStmtTc ls (HsLet x binds' (mkLHsWrap wrapper e')) + ; return $ mkExpandedStmtTc ls flav (HsLet x binds' (mkLHsWrap wrapper e')) } - | OrigStmt ls@(L loc s at LastStmt{}) <- o - = setSrcSpanA loc $ - addStmtCtxt s $ - mkExpandedStmtTc ls <$> tcExpr e' res_ty - -- It is important that we call tcExpr (and not tcApp) here as - -- `e` is the last statement's body expression - -- and not a HsApp of a generated (>>) or (>>=) - -- This improves error messages e.g. tests: DoExpansion1, DoExpansion2, DoExpansion3 - | OrigStmt ls@(L loc _) <- o + | OrigStmt ls@(L loc s) flav <- o + , TcExpr <- tc_info = setSrcSpanA loc $ - mkExpandedStmtTc ls <$> tcApp (XExpr xe) res_ty + addStmtCtxt s flav $ + mkExpandedStmtTc ls flav <$> tcExpr e' res_ty + | OrigStmt ls@(L loc _) flav <- o + , TcApp <- tc_info + = setSrcSpanA loc $ + mkExpandedStmtTc ls flav <$> tcApp (XExpr xe) res_ty tcXExpr xe res_ty = tcApp (XExpr xe) res_ty ===================================== compiler/GHC/Tc/Gen/Head.hs ===================================== @@ -240,7 +240,7 @@ appCtxtLoc (VACall _ _ l) = l insideExpansion :: AppCtxt -> Bool insideExpansion (VAExpansion {}) = True -insideExpansion (VACall {}) = False -- but what if the VACall has a generated context? +insideExpansion (VACall _ _ src) = isGeneratedSrcSpan src instance Outputable AppCtxt where ppr (VAExpansion e l _) = text "VAExpansion" <+> ppr e <+> ppr l @@ -292,7 +292,7 @@ splitHsApps e = go e (top_ctxt 0 e) [] top_ctxt n (HsPragE _ _ fun) = top_lctxt n fun top_ctxt n (HsAppType _ fun _) = top_lctxt (n+1) fun top_ctxt n (HsApp _ fun _) = top_lctxt (n+1) fun - top_ctxt n (XExpr (ExpandedThingRn o _)) + top_ctxt n (XExpr (ExpandedThingRn o _ _)) | OrigExpr fun <- o = VACall fun n noSrcSpan top_ctxt n other_fun = VACall other_fun n noSrcSpan @@ -317,19 +317,19 @@ splitHsApps e = go e (top_ctxt 0 e) [] HsQuasiQuote _ _ (L l _) -> set l ctxt -- l :: SrcAnn NoEpAnns -- See Note [Looking through ExpandedThingRn] - go (XExpr (ExpandedThingRn o e)) ctxt args + go (XExpr (ExpandedThingRn o e _)) ctxt args | isHsThingRnExpr o = go e (VAExpansion o (appCtxtLoc ctxt) (appCtxtLoc ctxt)) (EWrap (EExpand o) : args) - | OrigStmt (L _ stmt) <- o -- so that we set `(>>)` as generated + | OrigStmt (L _ stmt) _ <- o -- so that we set `(>>)` as generated , BodyStmt{} <- stmt -- and get the right unused bind warnings = go e (VAExpansion o generatedSrcSpan generatedSrcSpan) -- See Part 3. in Note [Expanding HsDo with XXExprGhcRn] (EWrap (EExpand o) : args) -- in `GHC.Tc.Gen.Do` - | OrigPat (L loc _) <- o -- so that we set the compiler generated fail context + | OrigPat (L loc _) _ <- o -- so that we set the compiler generated fail context = go e (VAExpansion o (locA loc) (locA loc)) -- to be originating from a failable pattern -- See Part 1. Wrinkle 2. of (EWrap (EExpand o) : args) -- Note [Expanding HsDo with XXExprGhcRn] @@ -893,17 +893,20 @@ tcInferAppHead_maybe fun _ -> return Nothing addHeadCtxt :: AppCtxt -> TcM a -> TcM a -addHeadCtxt (VAExpansion (OrigStmt (L loc stmt)) _ _) thing_inside = - do setSrcSpanA loc $ - addStmtCtxt stmt +addHeadCtxt (VAExpansion (OrigStmt (L loc stmt) flav) _ _) thing_inside = + do traceTc "addHeadCtxt stmt" (ppr stmt) + setSrcSpanA loc $ + addStmtCtxt stmt flav $ thing_inside addHeadCtxt fun_ctxt thing_inside | not (isGoodSrcSpan fun_loc) -- noSrcSpan => no arguments = thing_inside -- => context is already set | otherwise = setSrcSpan fun_loc $ - do case fun_ctxt of + do traceTc "addHeadCtxt fun_loc" (ppr fun_ctxt) + case fun_ctxt of VAExpansion (OrigExpr orig) _ _ -> addExprCtxt orig thing_inside + VAExpansion (OrigPat _ (Just (flav, stmt))) _ _ -> addStmtCtxt (unLoc stmt) flav $ thing_inside _ -> thing_inside where fun_loc = appCtxtLoc fun_ctxt @@ -1587,9 +1590,9 @@ mis-match in the number of value arguments. * * ********************************************************************* -} -addStmtCtxt :: ExprStmt GhcRn -> TcRn a -> TcRn a -addStmtCtxt stmt thing_inside - = do let err_doc = pprStmtInCtxt (HsDoStmt (DoExpr Nothing)) stmt +addStmtCtxt :: ExprStmt GhcRn -> HsDoFlavour -> TcRn a -> TcRn a +addStmtCtxt stmt flav thing_inside + = do let err_doc = pprStmtInCtxt (HsDoStmt flav) stmt addErrCtxt err_doc thing_inside where pprStmtInCtxt :: HsStmtContextRn -> StmtLR GhcRn GhcRn (LHsExpr GhcRn) -> SDoc @@ -1602,6 +1605,7 @@ addExprCtxt :: HsExpr GhcRn -> TcRn a -> TcRn a addExprCtxt e thing_inside = case e of HsUnboundVar {} -> thing_inside + XExpr (ExpandedThingRn (OrigStmt stmt flav) _ _) -> addStmtCtxt (unLoc stmt) flav thing_inside _ -> addErrCtxt (exprCtxt e) thing_inside -- The HsUnboundVar special case addresses situations like -- f x = _ ===================================== compiler/GHC/Tc/Gen/Match.hs ===================================== @@ -78,13 +78,9 @@ import GHC.Types.SrcLoc import GHC.Types.Basic( VisArity, isDoExpansionGenerated ) import Control.Monad -import Control.Arrow ( second ) import qualified Data.List.NonEmpty as NE import Data.Maybe (mapMaybe) -import qualified GHC.LanguageExtensions as LangExt - - {- ************************************************************************ * * @@ -353,20 +349,16 @@ tcDoStmts ListComp (L l stmts) res_ty (mkCheckExpType elt_ty) ; return $ mkHsWrapCo co (HsDo list_ty ListComp (L l stmts')) } -tcDoStmts doExpr@(DoExpr _) ss@(L l stmts) res_ty - = do { isApplicativeDo <- xoptM LangExt.ApplicativeDo - ; if isApplicativeDo - then do { stmts' <- tcStmts (HsDoStmt doExpr) tcDoStmt stmts res_ty - ; res_ty <- readExpType res_ty - ; return (HsDo res_ty doExpr (L l stmts')) } - else do { expanded_expr <- expandDoStmts doExpr stmts - -- Do expansion on the fly - ; mkExpandedExprTc (HsDo noExtField doExpr ss) <$> tcExpr (unLoc expanded_expr) res_ty } +tcDoStmts doExpr@(DoExpr _) ss@(L _ stmts) res_ty + = do { traceTc "tcDoStmts" $ text "original:" <+> ppr ss + ; expanded_expr <- expandDoStmts doExpr stmts -- Do expansion on the fly + ; traceTc "tcDoStmts" $ text "expansion:" <+> ppr expanded_expr + ; mkExpandedExprTc (HsDo noExtField doExpr ss) <$> tcExpr expanded_expr res_ty } tcDoStmts mDoExpr@(MDoExpr _) ss@(L _ stmts) res_ty = do { expanded_expr <- expandDoStmts mDoExpr stmts -- Do expansion on the fly - ; mkExpandedExprTc (HsDo noExtField mDoExpr ss) <$> tcExpr (unLoc expanded_expr) res_ty } + ; mkExpandedExprTc (HsDo noExtField mDoExpr ss) <$> tcExpr expanded_expr res_ty } tcDoStmts MonadComp (L l stmts) res_ty = do { stmts' <- tcStmts (HsDoStmt MonadComp) tcMcStmt stmts res_ty @@ -997,18 +989,6 @@ tcDoStmt ctxt (RecStmt { recS_stmts = L l stmts, recS_later_ids = later_names , recS_ret_ty = stmts_ty} }, thing) }} -tcDoStmt ctxt (XStmtLR (ApplicativeStmt _ pairs mb_join)) res_ty thing_inside - = do { let tc_app_stmts ty = tcApplicativeStmts ctxt pairs ty $ - thing_inside . mkCheckExpType - ; ((pairs', body_ty, thing), mb_join') <- case mb_join of - Nothing -> (, Nothing) <$> tc_app_stmts res_ty - Just join_op -> - second Just <$> - (tcSyntaxOp DoOrigin join_op [SynRho] res_ty $ - \ [rhs_ty] [rhs_mult] -> tcScalingUsage rhs_mult $ tc_app_stmts (mkCheckExpType rhs_ty)) - - ; return (XStmtLR $ ApplicativeStmt body_ty pairs' mb_join', thing) } - tcDoStmt _ stmt _ _ = pprPanic "tcDoStmt: unexpected Stmt" (ppr stmt) @@ -1084,87 +1064,6 @@ To achieve this we: all branches. This step is done with bindLocalNames. -} -tcApplicativeStmts - :: HsStmtContextRn - -> [(SyntaxExpr GhcRn, ApplicativeArg GhcRn)] - -> ExpRhoType -- rhs_ty - -> (TcRhoType -> TcM t) -- thing_inside - -> TcM ([(SyntaxExpr GhcTc, ApplicativeArg GhcTc)], Type, t) - -tcApplicativeStmts ctxt pairs rhs_ty thing_inside - = do { body_ty <- newFlexiTyVarTy liftedTypeKind - ; let arity = length pairs - ; ts <- replicateM (arity-1) $ newInferExpType - ; exp_tys <- replicateM arity $ newFlexiTyVarTy liftedTypeKind - ; pat_tys <- replicateM arity $ newFlexiTyVarTy liftedTypeKind - ; let fun_ty = mkVisFunTysMany pat_tys body_ty - - -- NB. do the <$>,<*> operators first, we don't want type errors here - -- i.e. goOps before goArgs - -- See Note [Treat rebindable syntax first] - ; let (ops, args) = unzip pairs - ; ops' <- goOps fun_ty (zip3 ops (ts ++ [rhs_ty]) exp_tys) - - -- Typecheck each ApplicativeArg separately - -- See Note [ApplicativeDo and constraints] - ; args' <- mapM (goArg body_ty) (zip3 args pat_tys exp_tys) - - -- Bring into scope all the things bound by the args, - -- and typecheck the thing_inside - -- See Note [ApplicativeDo and constraints] - ; res <- tcExtendIdEnv (concatMap get_arg_bndrs args') $ - thing_inside body_ty - - ; return (zip ops' args', body_ty, res) } - where - goOps _ [] = return [] - goOps t_left ((op,t_i,exp_ty) : ops) - = do { (_, op') - <- tcSyntaxOp DoOrigin op - [synKnownType t_left, synKnownType exp_ty] t_i $ - \ _ _ -> return () - ; t_i <- readExpType t_i - ; ops' <- goOps t_i ops - ; return (op' : ops') } - - goArg :: Type -> (ApplicativeArg GhcRn, Type, Type) - -> TcM (ApplicativeArg GhcTc) - - goArg body_ty (ApplicativeArgOne - { xarg_app_arg_one = fail_op - , app_arg_pattern = pat - , arg_expr = rhs - , .. - }, pat_ty, exp_ty) - = setSrcSpan (combineSrcSpans (getLocA pat) (getLocA rhs)) $ - addErrCtxt (pprStmtInCtxt ctxt (mkRnBindStmt pat rhs)) $ - do { rhs' <- tcCheckMonoExprNC rhs exp_ty - ; (pat', _) <- tcCheckPat (StmtCtxt ctxt) pat (unrestricted pat_ty) $ - return () - ; fail_op' <- fmap join . forM fail_op $ \fail -> - tcMonadFailOp (DoPatOrigin pat) pat' fail body_ty - - ; return (ApplicativeArgOne - { xarg_app_arg_one = fail_op' - , app_arg_pattern = pat' - , arg_expr = rhs' - , .. } - ) } - - goArg _body_ty (ApplicativeArgMany x stmts ret pat ctxt, pat_ty, exp_ty) - = do { (stmts', (ret',pat')) <- - tcStmtsAndThen (HsDoStmt ctxt) tcDoStmt stmts (mkCheckExpType exp_ty) $ - \res_ty -> do - { ret' <- tcExpr ret res_ty - ; (pat', _) <- tcCheckPat (StmtCtxt (HsDoStmt ctxt)) pat (unrestricted pat_ty) $ - return () - ; return (ret', pat') - } - ; return (ApplicativeArgMany x stmts' ret' pat' ctxt) } - - get_arg_bndrs :: ApplicativeArg GhcTc -> [Id] - get_arg_bndrs (ApplicativeArgOne { app_arg_pattern = pat }) = collectPatBinders CollNoDictBinders pat - get_arg_bndrs (ApplicativeArgMany { bv_pattern = pat }) = collectPatBinders CollNoDictBinders pat {- Note [ApplicativeDo and constraints] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -751,9 +751,9 @@ exprCtOrigin (HsUntypedSplice {}) = Shouldn'tHappenOrigin "TH untyped splice" exprCtOrigin (HsProc {}) = Shouldn'tHappenOrigin "proc" exprCtOrigin (HsStatic {}) = Shouldn'tHappenOrigin "static expression" exprCtOrigin (HsEmbTy {}) = Shouldn'tHappenOrigin "type expression" -exprCtOrigin (XExpr (ExpandedThingRn thing _)) | OrigExpr a <- thing = exprCtOrigin a - | OrigStmt _ <- thing = DoOrigin - | OrigPat p <- thing = DoPatOrigin p +exprCtOrigin (XExpr (ExpandedThingRn thing _ _)) | OrigExpr a <- thing = exprCtOrigin a + | OrigStmt _ _ <- thing = DoOrigin + | OrigPat p _ <- thing = DoPatOrigin p exprCtOrigin (XExpr (PopErrCtxt {})) = Shouldn'tHappenOrigin "PopErrCtxt" -- | Extract a suitable CtOrigin from a MatchGroup ===================================== compiler/GHC/Tc/Utils/Monad.hs ===================================== @@ -1264,7 +1264,7 @@ updCtxt ctxt env popErrCtxt :: TcM a -> TcM a popErrCtxt thing_inside = updLclEnv (\env -> setLclEnvErrCtxt (pop $ getLclEnvErrCtxt env) env) $ - thing_inside + thing_inside where pop [] = [] pop (_:msgs) = msgs ===================================== compiler/GHC/Tc/Zonk/Type.hs ===================================== @@ -97,7 +97,6 @@ import GHC.Tc.Types.BasicTypes import GHC.Data.Maybe import GHC.Data.Bag -import Control.Monad import Control.Monad.Trans.Class ( lift ) import Data.Semigroup import Data.List.NonEmpty ( NonEmpty ) @@ -1409,54 +1408,6 @@ zonkStmt zBody (BindStmt xbs pat body) }) new_pat new_body } --- Scopes: join > ops (in reverse order) > pats (in forward order) --- > rest of stmts -zonkStmt _zBody (XStmtLR (ApplicativeStmt body_ty args mb_join)) - = do { new_mb_join <- zonk_join mb_join - ; new_args <- zonk_args args - ; new_body_ty <- noBinders $ zonkTcTypeToTypeX body_ty - ; return $ XStmtLR $ ApplicativeStmt new_body_ty new_args new_mb_join } - where - zonk_join Nothing = return Nothing - zonk_join (Just j) = Just <$> zonkSyntaxExpr j - - get_pat :: (SyntaxExpr GhcTc, ApplicativeArg GhcTc) -> LPat GhcTc - get_pat (_, ApplicativeArgOne _ pat _ _) = pat - get_pat (_, ApplicativeArgMany _ _ _ pat _) = pat - - replace_pat :: LPat GhcTc - -> (SyntaxExpr GhcTc, ApplicativeArg GhcTc) - -> (SyntaxExpr GhcTc, ApplicativeArg GhcTc) - replace_pat pat (op, ApplicativeArgOne fail_op _ a isBody) - = (op, ApplicativeArgOne fail_op pat a isBody) - replace_pat pat (op, ApplicativeArgMany x a b _ c) - = (op, ApplicativeArgMany x a b pat c) - - zonk_args args - = do { new_args_rev <- zonk_args_rev (reverse args) - ; new_pats <- zonkPats (map get_pat args) - ; return $ zipWithEqual "zonkStmt" replace_pat - new_pats (reverse new_args_rev) } - - -- these need to go backward, because if any operators are higher-rank, - -- later operators may introduce skolems that are in scope for earlier - -- arguments - zonk_args_rev ((op, arg) : args) - = do { new_op <- zonkSyntaxExpr op - ; new_arg <- noBinders $ zonk_arg arg - ; new_args <- zonk_args_rev args - ; return $ (new_op, new_arg) : new_args } - zonk_args_rev [] = return [] - - zonk_arg (ApplicativeArgOne fail_op pat expr isBody) - = do { new_expr <- zonkLExpr expr - ; new_fail <- forM fail_op $ don'tBind . zonkSyntaxExpr - ; return (ApplicativeArgOne new_fail pat new_expr isBody) } - zonk_arg (ApplicativeArgMany x stmts ret pat ctxt) - = runZonkBndrT (zonkStmts zonkLExpr stmts) $ \ new_stmts -> - do { new_ret <- zonkExpr ret - ; return (ApplicativeArgMany x new_stmts new_ret pat ctxt) } - ------------------------------------------------------------------------- zonkRecFields :: HsRecordBinds GhcTc -> ZonkTcM (HsRecordBinds GhcTc) zonkRecFields (HsRecFields flds dd) ===================================== testsuite/tests/ado/T13242a.stderr ===================================== @@ -1,13 +1,13 @@ - T13242a.hs:10:5: error: [GHC-46956] • Couldn't match expected type ‘a0’ with actual type ‘a’ - • because type variable ‘a’ would escape its scope - This (rigid, skolem) type variable is bound by - a pattern with constructor: A :: forall a. Eq a => a -> T, - in a pattern binding in - a 'do' block - at T13242a.hs:10:3-5 - • In the expression: + because type variable ‘a’ would escape its scope + This (rigid, skolem) type variable is bound by + a pattern with constructor: A :: forall a. Eq a => a -> T, + in a pattern binding in + a 'do' block + at T13242a.hs:10:3-5 + • In a stmt of a 'do' block: A x <- undefined + In the expression: do A x <- undefined _ <- return 'a' _ <- return 'b' @@ -29,7 +29,7 @@ T13242a.hs:13:13: error: [GHC-39999] instance Eq Ordering -- Defined in ‘GHC.Classes’ instance Eq Integer -- Defined in ‘GHC.Num.Integer’ ...plus 23 others - ...plus five instances involving out-of-scope types + ...plus six instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In a stmt of a 'do' block: return (x == x) In the expression: @@ -43,3 +43,4 @@ T13242a.hs:13:13: error: [GHC-39999] _ <- return 'a' _ <- return 'b' return (x == x) + ===================================== testsuite/tests/ado/T16135.hs ===================================== @@ -1,5 +1,9 @@ {-# LANGUAGE ExistentialQuantification, ApplicativeDo #-} +{- This testcase failed before we treated Do statements via HsExpansions + This test passes after #24406 +-} + module Bug where data T f = forall a. MkT (f a) ===================================== testsuite/tests/ado/T16135.stderr deleted ===================================== @@ -1,19 +0,0 @@ -T16135.hs:11:18: error: [GHC-83865] - • Couldn't match type ‘a0’ with ‘a’ - Expected: f a0 - Actual: f a - ‘a0’ is untouchable - inside the constraints: Functor f - bound by the type signature for: - runf :: forall (f :: * -> *). Functor f => IO (T f) - at T16135.hs:7:1-39 - ‘a’ is a rigid type variable bound by - a pattern with constructor: - MkT :: forall {k} (f :: k -> *) (a :: k). f a -> T f, - in a pattern binding in - a 'do' block - at T16135.hs:10:5-10 - • In the first argument of ‘MkT’, namely ‘fa’ - In the second argument of ‘($)’, namely ‘MkT fa’ - In a stmt of a 'do' block: return $ MkT fa - • Relevant bindings include fa :: f a (bound at T16135.hs:10:9) ===================================== testsuite/tests/ado/T24406.hs ===================================== @@ -0,0 +1,14 @@ +{-# LANGUAGE ImpredicativeTypes, ApplicativeDo #-} +module T where + +t :: IO (forall a. a -> a) +t = return id + +p :: (forall a. a -> a) -> (Bool, Int) +p f = (f True, f 3) + +-- This typechecks (with QL) +foo1 = t >>= \x -> return (p x) + +-- But this did not not type check: +foo2 = do { x <- t ; return (p x) } ===================================== testsuite/tests/ado/ado002.stderr ===================================== @@ -1,4 +1,3 @@ - ado002.hs:8:8: error: [GHC-83865] • Couldn't match expected type: Char -> IO b0 with actual type: IO Char @@ -24,30 +23,39 @@ ado002.hs:9:3: error: [GHC-83865] y <- getChar 'a' print (x, y) -ado002.hs:15:11: error: [GHC-83865] - • Couldn't match expected type ‘Int’ with actual type ‘Char’ - • In the expression: y - In a stmt of a 'do' block: return (y, x) +ado002.hs:13:8: error: [GHC-83865] + • Couldn't match type ‘Char’ with ‘Int’ + Expected: IO Int + Actual: IO Char + • In a stmt of a 'do' block: x <- getChar In the expression: do x <- getChar y <- getChar return (y, x) + In an equation for ‘g’: + g = do x <- getChar + y <- getChar + return (y, x) -ado002.hs:15:13: error: [GHC-83865] - • Couldn't match expected type ‘Int’ with actual type ‘Char’ - • In the expression: x - In a stmt of a 'do' block: return (y, x) +ado002.hs:14:8: error: [GHC-83865] + • Couldn't match type ‘Char’ with ‘Int’ + Expected: IO Int + Actual: IO Char + • In a stmt of a 'do' block: y <- getChar In the expression: do x <- getChar y <- getChar return (y, x) + In an equation for ‘g’: + g = do x <- getChar + y <- getChar + return (y, x) -ado002.hs:23:9: error: [GHC-83865] - • Couldn't match expected type: Char -> IO a0 - with actual type: IO Char - • The function ‘getChar’ is applied to one visible argument, - but its type ‘IO Char’ has none - In a stmt of a 'do' block: x5 <- getChar x4 +ado002.hs:20:9: error: [GHC-83865] + • Couldn't match type ‘Char’ with ‘Int’ + Expected: IO Int + Actual: IO Char + • In a stmt of a 'do' block: x2 <- getChar In the expression: do x1 <- getChar x2 <- getChar @@ -55,11 +63,17 @@ ado002.hs:23:9: error: [GHC-83865] x4 <- getChar x5 <- getChar x4 return (x2, x4) + In an equation for ‘h’: + h = do x1 <- getChar + x2 <- getChar + x3 <- const (return ()) x1 + x4 <- getChar + x5 <- getChar x4 + return (x2, x4) -ado002.hs:24:11: error: [GHC-83865] +ado002.hs:23:3: error: [GHC-83865] • Couldn't match expected type ‘Int’ with actual type ‘Char’ - • In the expression: x2 - In a stmt of a 'do' block: return (x2, x4) + • In a stmt of a 'do' block: x4 <- getChar In the expression: do x1 <- getChar x2 <- getChar @@ -67,11 +81,20 @@ ado002.hs:24:11: error: [GHC-83865] x4 <- getChar x5 <- getChar x4 return (x2, x4) + In an equation for ‘h’: + h = do x1 <- getChar + x2 <- getChar + x3 <- const (return ()) x1 + x4 <- getChar + x5 <- getChar x4 + return (x2, x4) -ado002.hs:24:14: error: [GHC-83865] - • Couldn't match expected type ‘Int’ with actual type ‘Char’ - • In the expression: x4 - In a stmt of a 'do' block: return (x2, x4) +ado002.hs:23:9: error: [GHC-83865] + • Couldn't match expected type: Char -> IO a0 + with actual type: IO Char + • The function ‘getChar’ is applied to one visible argument, + but its type ‘IO Char’ has none + In a stmt of a 'do' block: x5 <- getChar x4 In the expression: do x1 <- getChar x2 <- getChar @@ -79,3 +102,4 @@ ado002.hs:24:14: error: [GHC-83865] x4 <- getChar x5 <- getChar x4 return (x2, x4) + ===================================== testsuite/tests/ado/ado003.stderr ===================================== @@ -1,7 +1,7 @@ -ado003.hs:7:3: error: [GHC-83865] - • Couldn't match expected type ‘Int’ with actual type ‘Char’ - • In the pattern: 'a' +ado003.hs:7:18: error: [GHC-83865] + • Couldn't match expected type ‘Char’ with actual type ‘Int’ + • In the first argument of ‘return’, namely ‘(3 :: Int)’ In a stmt of a 'do' block: 'a' <- return (3 :: Int) In the expression: do x <- getChar ===================================== testsuite/tests/ado/ado004.stderr ===================================== @@ -8,24 +8,24 @@ TYPE SIGNATURES test1c :: forall (f :: * -> *). Applicative f => (Int -> f Int) -> f Int test2 :: - forall {f :: * -> *} {t} {b}. - (Applicative f, Num t, Num b) => + forall {f :: * -> *} {b} {t}. + (Applicative f, Num b, Num t) => (t -> f b) -> f b test2a :: - forall {f :: * -> *} {t} {b}. - (Functor f, Num t, Num b) => + forall {f :: * -> *} {b} {t}. + (Functor f, Num b, Num t) => (t -> f b) -> f b test2b :: forall {f :: * -> *} {t} {a}. (Applicative f, Num t) => (t -> a) -> f a test2c :: - forall {f :: * -> *} {t} {b}. - (Functor f, Num t, Num b) => + forall {f :: * -> *} {b} {t}. + (Functor f, Num b, Num t) => (t -> f b) -> f b test2d :: - forall {f :: * -> *} {t} {b} {a}. - (Functor f, Num t, Num b) => + forall {f :: * -> *} {b} {t} {a}. + (Functor f, Num b, Num t) => (t -> f a) -> f b test3 :: forall {m :: * -> *} {t1} {t2} {a}. @@ -44,4 +44,4 @@ TYPE SIGNATURES (Monad m, Num (m a)) => (m a -> m (m a)) -> p -> m a Dependent modules: [] -Dependent packages: [base-4.16.0.0] +Dependent packages: [base-4.20.0.0] ===================================== testsuite/tests/ado/all.T ===================================== @@ -20,6 +20,7 @@ test('T15344', normal, compile_and_run, ['']) test('T16628', normal, compile_fail, ['']) test('T17835', normal, compile, ['']) test('T20540', normal, compile, ['']) -test('T16135', [when(compiler_debugged(),expect_broken(16135))], compile_fail, ['']) +test('T16135', normal, compile, ['']) test('T22483', normal, compile, ['-Wall']) test('OrPatStrictness', normal, compile_and_run, ['']) +test('T24406', normal, compile, ['']) ===================================== testsuite/tests/determinism/determ021/determ021.stdout ===================================== @@ -1,16 +1,16 @@ [1 of 1] Compiling A ( A.hs, A.o ) TYPE SIGNATURES test2 :: - forall {f :: * -> *} {t} {b}. - (Applicative f, Num t, Num b) => + forall {f :: * -> *} {b} {t}. + (Applicative f, Num b, Num t) => (t -> f b) -> f b Dependent modules: [] -Dependent packages: [base-4.16.0.0] +Dependent packages: [base-4.20.0.0] [1 of 1] Compiling A ( A.hs, A.o ) TYPE SIGNATURES test2 :: - forall {f :: * -> *} {t} {b}. - (Applicative f, Num t, Num b) => + forall {f :: * -> *} {b} {t}. + (Applicative f, Num b, Num t) => (t -> f b) -> f b Dependent modules: [] -Dependent packages: [base-4.16.0.0] +Dependent packages: [base-4.20.0.0] ===================================== testsuite/tests/ghci.debugger/scripts/break029.stdout ===================================== @@ -1,9 +1,9 @@ Stopped in Main.f, break029.hs:(4,7)-(6,16) _result :: IO Int = _ x :: Int = 3 -Stopped in Main.f, break029.hs:5:8-21 -_result :: IO Int = _ -x :: Int = 3 +Stopped in Main.f, break029.hs:6:3-16 +_result :: Int = _ +y :: Int = _ Stopped in Main.f, break029.hs:6:11-15 _result :: Int = _ y :: Int = _ ===================================== testsuite/tests/hiefile/should_run/T23540.stdout ===================================== @@ -28,22 +28,6 @@ At point (15,8), we found: ========================== At point (30,8), we found: ========================== -┌ -│ $dMonad at T23540.hs:1:1, of type: Monad Identity -│ is an evidence variable bound by a let, depending on: [$fMonadIdentity] -│ with scope: ModuleScope -│ -│ Defined at -└ -| -`- ┌ - │ $fMonadIdentity at T23540.hs:25:10-23, of type: Monad Identity - │ is an evidence variable bound by an instance of class Monad - │ with scope: ModuleScope - │ - │ Defined at T23540.hs:25:10 - └ - ========================== At point (43,8), we found: ========================== @@ -123,38 +107,6 @@ At point (49,14), we found: ========================== At point (61,7), we found: ========================== -┌ -│ $dApplicative at T23540.hs:1:1, of type: Applicative Identity' -│ is an evidence variable bound by a let, depending on: [$fApplicativeIdentity'] -│ with scope: ModuleScope -│ -│ Defined at -└ -| -`- ┌ - │ $fApplicativeIdentity' at T23540.hs:56:10-30, of type: Applicative Identity' - │ is an evidence variable bound by an instance of class Applicative - │ with scope: ModuleScope - │ - │ Defined at T23540.hs:56:10 - └ - -┌ -│ $dFunctor at T23540.hs:1:1, of type: Functor Identity' -│ is an evidence variable bound by a let, depending on: [$fFunctorIdentity'] -│ with scope: ModuleScope -│ -│ Defined at -└ -| -`- ┌ - │ $fFunctorIdentity' at T23540.hs:54:10-26, of type: Functor Identity' - │ is an evidence variable bound by an instance of class Functor - │ with scope: ModuleScope - │ - │ Defined at T23540.hs:54:10 - └ - ========================== At point (69,4), we found: ========================== View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/96f76d934d60e43eec35b9cb071935ae0989e607 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/96f76d934d60e43eec35b9cb071935ae0989e607 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 21:52:35 2024 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Fri, 07 Jun 2024 17:52:35 -0400 Subject: [Git][ghc/ghc][wip/expansions-appdo] Make ApplicativeDo work with HsExpansions Message-ID: <66638123966fb_1b2a6697efa41364e0@gitlab.mail> Apoorv Ingle pushed to branch wip/expansions-appdo at Glasgow Haskell Compiler / GHC Commits: 6575ca67 by Apoorv Ingle at 2024-06-07T16:50:15-05:00 Make ApplicativeDo work with HsExpansions testcase added: T24406 Issues Fixed: #24406, #16135 Code Changes: - Remove `XStmtLR GhcTc` as `XStmtLR GhcRn` is now compiled to `HsExpr GhcTc` - The expanded statements are guided by `GHC.Hs.Expr.TcFunInfo` which is used to decide if the `XExpr GhcRn` is to be typechecked using `tcApp` or `tcExpr` Note [Expanding HsDo with XXExprGhcRn] explains the change in more detail - - - - - 29 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Zonk/Type.hs - testsuite/tests/ado/T13242a.stderr - testsuite/tests/ado/T16135.hs - − testsuite/tests/ado/T16135.stderr - + testsuite/tests/ado/T24406.hs - testsuite/tests/ado/ado002.stderr - testsuite/tests/ado/ado003.stderr - testsuite/tests/ado/ado004.stderr - testsuite/tests/ado/all.T - testsuite/tests/determinism/determ021/determ021.stdout - testsuite/tests/ghci.debugger/scripts/break029.stdout - testsuite/tests/hiefile/should_run/T23540.stdout Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -473,11 +473,14 @@ type instance XXExpr GhcTc = XXExprGhcTc * * ********************************************************************* -} +-- | Hint to the typechecker how to typecheck the expanded expression +data TCFunInfo = TcApp | TcExpr + -- | The different source constructs that we use to instantiate the "original" field -- in an `XXExprGhcRn original expansion` data HsThingRn = OrigExpr (HsExpr GhcRn) - | OrigStmt (ExprLStmt GhcRn) - | OrigPat (LPat GhcRn) + | OrigStmt (ExprLStmt GhcRn) HsDoFlavour -- ^ which kind of do-block did this statement come from + | OrigPat (LPat GhcRn) (Maybe (HsDoFlavour, ExprLStmt GhcRn)) isHsThingRnExpr, isHsThingRnStmt, isHsThingRnPat :: HsThingRn -> Bool isHsThingRnExpr (OrigExpr{}) = True @@ -491,7 +494,10 @@ isHsThingRnPat _ = False data XXExprGhcRn = ExpandedThingRn { xrn_orig :: HsThingRn -- The original source thing - , xrn_expanded :: HsExpr GhcRn } -- The compiler generated expanded thing + , xrn_expanded :: HsExpr GhcRn -- The compiler generated expanded thing + , xrn_TCFunInfo :: TCFunInfo } -- A Hint to the type checker of how to proceed + -- TcApp <=> use GHC.Tc.Gen.Expr.tcApp + -- TcExpr <=> use GHC.Tc.Gen.Expr.tcExpr | PopErrCtxt -- A hint for typechecker to pop {-# UNPACK #-} !(LHsExpr GhcRn) -- the top of the error context stack @@ -515,22 +521,25 @@ mkExpandedExpr :: HsExpr GhcRn -- ^ source expression -> HsExpr GhcRn -- ^ expanded expression -> HsExpr GhcRn -- ^ suitably wrapped 'XXExprGhcRn' -mkExpandedExpr oExpr eExpr = XExpr (ExpandedThingRn (OrigExpr oExpr) eExpr) +mkExpandedExpr oExpr eExpr = XExpr (ExpandedThingRn (OrigExpr oExpr) eExpr TcExpr) -- | Build an expression using the extension constructor `XExpr`, -- and the two components of the expansion: original do stmt and -- expanded expression mkExpandedStmt :: ExprLStmt GhcRn -- ^ source statement + -> HsDoFlavour + -> TCFunInfo -> HsExpr GhcRn -- ^ expanded expression -> HsExpr GhcRn -- ^ suitably wrapped 'XXExprGhcRn' -mkExpandedStmt oStmt eExpr = XExpr (ExpandedThingRn (OrigStmt oStmt) eExpr) +mkExpandedStmt oStmt flav tc_fun eExpr = XExpr (ExpandedThingRn (OrigStmt oStmt flav) eExpr tc_fun) mkExpandedPatRn - :: LPat GhcRn -- ^ source pattern - -> HsExpr GhcRn -- ^ expanded expression - -> HsExpr GhcRn -- ^ suitably wrapped 'XXExprGhcRn' -mkExpandedPatRn oPat eExpr = XExpr (ExpandedThingRn (OrigPat oPat) eExpr) + :: LPat GhcRn -- ^ source pattern + -> Maybe (HsDoFlavour, ExprLStmt GhcRn) -- ^ pattern statement origin + -> HsExpr GhcRn -- ^ expanded expression + -> HsExpr GhcRn -- ^ suitably wrapped 'XXExprGhcRn' +mkExpandedPatRn oPat mb_stmt_info eExpr = XExpr (ExpandedThingRn (OrigPat oPat mb_stmt_info) eExpr TcExpr) -- | Build an expression using the extension constructor `XExpr`, -- and the two components of the expansion: original do stmt and @@ -538,17 +547,21 @@ mkExpandedPatRn oPat eExpr = XExpr (ExpandedThingRn (OrigPat oPat) eExpr) mkExpandedStmtAt :: SrcSpanAnnA -- ^ Location for the expansion expression -> ExprLStmt GhcRn -- ^ source statement + -> HsDoFlavour + -> TCFunInfo -> HsExpr GhcRn -- ^ expanded expression -> LHsExpr GhcRn -- ^ suitably wrapped located 'XXExprGhcRn' -mkExpandedStmtAt loc oStmt eExpr = L loc $ mkExpandedStmt oStmt eExpr +mkExpandedStmtAt loc oStmt flav tcFun eExpr = L loc $ mkExpandedStmt oStmt flav tcFun eExpr -- | Wrap the expanded version of the expression with a pop. mkExpandedStmtPopAt :: SrcSpanAnnA -- ^ Location for the expansion statement -> ExprLStmt GhcRn -- ^ source statement + -> HsDoFlavour + -> TCFunInfo -> HsExpr GhcRn -- ^ expanded expression -> LHsExpr GhcRn -- ^ suitably wrapped 'XXExprGhcRn' -mkExpandedStmtPopAt loc oStmt eExpr = mkPopErrCtxtExprAt loc $ mkExpandedStmtAt loc oStmt eExpr +mkExpandedStmtPopAt loc oStmt flav tc_fun eExpr = mkPopErrCtxtExprAt loc $ mkExpandedStmtAt loc oStmt flav tc_fun eExpr data XXExprGhcTc @@ -593,9 +606,10 @@ mkExpandedExprTc oExpr eExpr = XExpr (ExpandedThingTc (OrigExpr oExpr) eExpr) -- expanded typechecked expression. mkExpandedStmtTc :: ExprLStmt GhcRn -- ^ source do statement + -> HsDoFlavour -> HsExpr GhcTc -- ^ expanded typechecked expression -> HsExpr GhcTc -- ^ suitably wrapped 'XXExprGhcRn' -mkExpandedStmtTc oStmt eExpr = XExpr (ExpandedThingTc (OrigStmt oStmt) eExpr) +mkExpandedStmtTc oStmt flav eExpr = XExpr (ExpandedThingTc (OrigStmt oStmt flav) eExpr) {- ********************************************************************* * * @@ -836,13 +850,13 @@ instance Outputable HsThingRn where ppr thing = case thing of OrigExpr x -> ppr_builder ":" x - OrigStmt x -> ppr_builder ":" x - OrigPat x -> ppr_builder ":" x + OrigStmt x _ -> ppr_builder ":" x + OrigPat x _ -> ppr_builder ":" x where ppr_builder prefix x = ifPprDebug (braces (text prefix <+> parens (ppr x))) (ppr x) instance Outputable XXExprGhcRn where - ppr (ExpandedThingRn o e) = ifPprDebug (braces $ vcat [ppr o, ppr e]) (ppr o) - ppr (PopErrCtxt e) = ifPprDebug (braces (text "" <+> ppr e)) (ppr e) + ppr (ExpandedThingRn o e _) = ifPprDebug (braces $ vcat [ppr o, text ";;" , ppr e]) (ppr o) + ppr (PopErrCtxt e) = ifPprDebug (braces (text "" <+> ppr e)) (ppr e) instance Outputable XXExprGhcTc where ppr (WrapExpr (HsWrap co_fn e)) @@ -882,7 +896,7 @@ ppr_infix_expr (XExpr x) = case ghcPass @p of ppr_infix_expr _ = Nothing ppr_infix_expr_rn :: XXExprGhcRn -> Maybe SDoc -ppr_infix_expr_rn (ExpandedThingRn thing _) = ppr_infix_hs_expansion thing +ppr_infix_expr_rn (ExpandedThingRn thing _ _) = ppr_infix_hs_expansion thing ppr_infix_expr_rn (PopErrCtxt (L _ a)) = ppr_infix_expr a ppr_infix_expr_tc :: XXExprGhcTc -> Maybe SDoc @@ -993,7 +1007,7 @@ hsExprNeedsParens prec = go go_x_tc (HsBinTick _ _ (L _ e)) = hsExprNeedsParens prec e go_x_rn :: XXExprGhcRn -> Bool - go_x_rn (ExpandedThingRn thing _) = hsExpandedNeedsParens thing + go_x_rn (ExpandedThingRn thing _ _) = hsExpandedNeedsParens thing go_x_rn (PopErrCtxt (L _ a)) = hsExprNeedsParens prec a hsExpandedNeedsParens :: HsThingRn -> Bool @@ -1045,7 +1059,7 @@ isAtomicHsExpr (XExpr x) go_x_tc (HsBinTick {}) = False go_x_rn :: XXExprGhcRn -> Bool - go_x_rn (ExpandedThingRn thing _) = isAtomicExpandedThingRn thing + go_x_rn (ExpandedThingRn thing _ _) = isAtomicExpandedThingRn thing go_x_rn (PopErrCtxt (L _ a)) = isAtomicHsExpr a isAtomicExpandedThingRn :: HsThingRn -> Bool @@ -1568,7 +1582,7 @@ pprMatch (Match { m_pats = pats, m_ctxt = ctxt, m_grhss = grhss }) <+> pprInfixOcc fun <+> pprParendLPat opPrec p2 _ -> pprPanic "pprMatch" (ppr ctxt $$ ppr pats) - + StmtCtxt _ -> (char '\\', pats) LamAlt LamSingle -> (char '\\', pats) ArrowMatchCtxt (ArrowLamAlt LamSingle) -> (char '\\', pats) LamAlt LamCases -> lam_cases_result @@ -1609,6 +1623,7 @@ matchSeparator IfAlt = text "->" matchSeparator ArrowMatchCtxt{} = text "->" matchSeparator PatBindRhs = text "=" matchSeparator PatBindGuards = text "=" +matchSeparator (StmtCtxt (HsDoStmt{})) = text "->" matchSeparator StmtCtxt{} = text "<-" matchSeparator RecUpd = text "=" -- This can be printed by the pattern matchSeparator PatSyn = text "<-" -- match checker trace @@ -1668,7 +1683,7 @@ data XBindStmtTc = XBindStmtTc type instance XApplicativeStmt (GhcPass _) GhcPs = NoExtField type instance XApplicativeStmt (GhcPass _) GhcRn = NoExtField -type instance XApplicativeStmt (GhcPass _) GhcTc = Type +type instance XApplicativeStmt (GhcPass _) GhcTc = DataConCantHappen type instance XBodyStmt (GhcPass _) GhcPs b = NoExtField type instance XBodyStmt (GhcPass _) GhcRn b = NoExtField @@ -1690,7 +1705,7 @@ type instance XRecStmt (GhcPass _) GhcTc b = RecStmtTc type instance XXStmtLR (GhcPass _) GhcPs b = DataConCantHappen type instance XXStmtLR (GhcPass x) GhcRn b = ApplicativeStmt (GhcPass x) GhcRn -type instance XXStmtLR (GhcPass x) GhcTc b = ApplicativeStmt (GhcPass x) GhcTc +type instance XXStmtLR (GhcPass x) GhcTc b = DataConCantHappen -- | 'ApplicativeStmt' represents an applicative expression built with -- '<$>' and '<*>'. It is generated by the renamer, and is desugared into the @@ -1731,7 +1746,7 @@ data ApplicativeArg idL | ApplicativeArgMany -- do { stmts; return vars } { xarg_app_arg_many :: XApplicativeArgMany idL , app_stmts :: [ExprLStmt idL] -- stmts - , final_expr :: HsExpr idL -- return (v1,..,vn), or just (v1,..,vn) + , final_expr :: LHsExpr idL -- return (v1,..,vn), or just (v1,..,vn) , bv_pattern :: LPat idL -- (v1,...,vn) , stmt_context :: HsDoFlavour -- ^ context of the do expression, used in pprArg @@ -1750,7 +1765,7 @@ type instance XXParStmtBlock (GhcPass pL) (GhcPass pR) = DataConCantHappen type instance XApplicativeArgOne GhcPs = NoExtField type instance XApplicativeArgOne GhcRn = FailOperator GhcRn -type instance XApplicativeArgOne GhcTc = FailOperator GhcTc +type instance XApplicativeArgOne GhcTc = DataConCantHappen type instance XApplicativeArgMany (GhcPass _) = NoExtField type instance XXApplicativeArg (GhcPass _) = DataConCantHappen @@ -1796,7 +1811,6 @@ pprStmt (RecStmt { recS_stmts = segment, recS_rec_ids = rec_ids pprStmt (XStmtLR x) = case ghcPass :: GhcPass idR of GhcRn -> pprApplicativeStmt x - GhcTc -> pprApplicativeStmt x where pprApplicativeStmt :: (OutputableBndrId idL, OutputableBndrId idR) => ApplicativeStmt (GhcPass idL) (GhcPass idR) -> SDoc @@ -1817,7 +1831,6 @@ pprStmt (XStmtLR x) = case ghcPass :: GhcPass idR of flattenStmt :: ExprLStmt (GhcPass idL) -> [SDoc] flattenStmt (L _ (XStmtLR x)) = case ghcPass :: GhcPass idL of GhcRn | (ApplicativeStmt _ args _) <- x -> concatMap flattenArg args - GhcTc | (ApplicativeStmt _ args _) <- x -> concatMap flattenArg args flattenStmt stmt = [ppr stmt] flattenArg :: (a, ApplicativeArg (GhcPass idL)) -> [SDoc] @@ -1846,13 +1859,13 @@ instance (OutputableBndrId idL) pprArg :: forall idL . (OutputableBndrId idL) => ApplicativeArg (GhcPass idL) -> SDoc pprArg (ApplicativeArgOne _ pat expr isBody) - | isBody = ppr expr -- See Note [Applicative BodyStmt] - | otherwise = pprBindStmt pat expr + | isBody = whenPprDebug (text "[AppStmt]") <+> ppr expr -- See Note [Applicative BodyStmt] + | otherwise = whenPprDebug (text "[AppStmt]") <+> pprBindStmt pat expr pprArg (ApplicativeArgMany _ stmts return pat ctxt) = ppr pat <+> text "<-" <+> pprDo ctxt (stmts ++ - [noLocA (LastStmt noExtField (noLocA return) Nothing noSyntaxExpr)]) + [noLocA (LastStmt noExtField return Nothing noSyntaxExpr)]) pprTransformStmt :: (OutputableBndrId p) => [IdP (GhcPass p)] -> LHsExpr (GhcPass p) ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -569,6 +569,7 @@ deriving instance Eq (IE GhcTc) -- --------------------------------------------------------------------- deriving instance Data HsThingRn +deriving instance Data TCFunInfo deriving instance Data XXExprGhcRn deriving instance Data XXExprGhcTc deriving instance Data XXPatGhcTc ===================================== compiler/GHC/Hs/Utils.hs ===================================== @@ -1188,7 +1188,6 @@ collectStmtBinders flag = \case RecStmt { recS_stmts = L _ ss } -> collectLStmtsBinders flag ss XStmtLR x -> case ghcPass :: GhcPass idR of GhcRn -> collectApplicativeStmtBndrs x - GhcTc -> collectApplicativeStmtBndrs x where collectApplicativeStmtBndrs :: ApplicativeStmt (GhcPass idL) a -> [IdP (GhcPass idL)] collectApplicativeStmtBndrs (ApplicativeStmt _ args _) = concatMap (collectArgBinders . snd) args @@ -1781,7 +1780,6 @@ lStmtsImplicits = hs_lstmts hs_stmt (BindStmt _ pat _) = lPatImplicits pat hs_stmt (XStmtLR x) = case ghcPass :: GhcPass idR of GhcRn -> hs_applicative_stmt x - GhcTc -> hs_applicative_stmt x hs_stmt (LetStmt _ binds) = hs_local_binds binds hs_stmt (BodyStmt {}) = [] hs_stmt (LastStmt {}) = [] ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -315,7 +315,7 @@ dsExpr (HsOverLit _ lit) dsExpr e@(XExpr ext_expr_tc) = case ext_expr_tc of ExpandedThingTc o e - | OrigStmt (L loc _) <- o + | OrigStmt (L loc _) _ <- o -> putSrcSpanDsA loc $ dsExpr e | otherwise -> dsExpr e WrapExpr {} -> dsHsWrapped e @@ -463,10 +463,10 @@ dsExpr (HsLet _ binds body) = do -- because the interpretation of `stmts' depends on what sort of thing it is. -- dsExpr (HsDo res_ty ListComp (L _ stmts)) = dsListComp stmts res_ty -dsExpr (HsDo res_ty ctx at DoExpr{} (L _ stmts)) = dsDo ctx stmts res_ty -dsExpr (HsDo res_ty ctx at GhciStmtCtxt (L _ stmts)) = dsDo ctx stmts res_ty -dsExpr (HsDo res_ty ctx at MDoExpr{} (L _ stmts)) = dsDo ctx stmts res_ty dsExpr (HsDo _ MonadComp (L _ stmts)) = dsMonadComp stmts +dsExpr (HsDo res_ty ctx at GhciStmtCtxt (L _ stmts)) = dsDo ctx stmts res_ty +dsExpr (HsDo _ DoExpr{} (L _ stmts)) = pprPanic "shouldn't happen dsDo DoExpr" (ppr stmts) +dsExpr (HsDo _ MDoExpr{} (L _ stmts)) = pprPanic "shouldn't happen dsDo MDoExpr" (ppr stmts) dsExpr (HsIf _ guard_expr then_expr else_expr) = do { pred <- dsLExpr guard_expr @@ -823,37 +823,6 @@ dsDo ctx stmts res_ty -- which ignores the return_op in the LastStmt, -- so we must apply the return_op explicitly - go _ (XStmtLR (ApplicativeStmt body_ty args mb_join)) stmts - = do { - let - (pats, rhss) = unzip (map (do_arg . snd) args) - - do_arg (ApplicativeArgOne fail_op pat expr _) = - ((pat, fail_op), dsLExpr expr) - do_arg (ApplicativeArgMany _ stmts ret pat _) = - ((pat, Nothing), dsDo ctx (stmts ++ [noLocA $ mkLastStmt (noLocA ret)]) res_ty) - - ; rhss' <- sequence rhss - - ; body' <- dsLExpr $ noLocA $ HsDo body_ty ctx (noLocA stmts) - - ; let match_args (pat, fail_op) (vs,body) - = putSrcSpanDs (getLocA pat) $ - do { var <- selectSimpleMatchVarL ManyTy pat - ; match <- matchSinglePatVar var Nothing (StmtCtxt (HsDoStmt ctx)) pat - body_ty (cantFailMatchResult body) - ; match_code <- dsHandleMonadicFailure ctx pat body_ty match fail_op - ; return (var:vs, match_code) - } - - ; (vars, body) <- foldrM match_args ([],body') pats - ; let fun' = mkLams vars body - ; let mk_ap_call l (op,r) = dsSyntaxExpr op [l,r] - ; expr <- foldlM mk_ap_call fun' (zip (map fst args) rhss') - ; case mb_join of - Nothing -> return expr - Just join_op -> dsSyntaxExpr join_op [expr] } - go _ (ParStmt {}) _ = panic "dsDo ParStmt" go _ (TransStmt {}) _ = panic "dsDo TransStmt" ===================================== compiler/GHC/HsToCore/GuardedRHSs.hs ===================================== @@ -144,8 +144,6 @@ matchGuards (LastStmt {} : _) _ _ _ _ = panic "matchGuards LastStmt" matchGuards (ParStmt {} : _) _ _ _ _ = panic "matchGuards ParStmt" matchGuards (TransStmt {} : _) _ _ _ _ = panic "matchGuards TransStmt" matchGuards (RecStmt {} : _) _ _ _ _ = panic "matchGuards RecStmt" -matchGuards (XStmtLR ApplicativeStmt {} : _) _ _ _ _ = - panic "matchGuards ApplicativeLastStmt" {- Should {\em fail} if @e@ returns @D@ ===================================== compiler/GHC/HsToCore/ListComp.hs ===================================== @@ -257,9 +257,6 @@ deListComp (ParStmt _ stmtss_w_bndrs _ _ : quals) list deListComp (RecStmt {} : _) _ = panic "deListComp RecStmt" -deListComp (XStmtLR ApplicativeStmt {} : _) _ = - panic "deListComp ApplicativeStmt" - deBindComp :: LPat GhcTc -> CoreExpr -> [ExprStmt GhcTc] @@ -352,8 +349,6 @@ dfListComp c_id n_id (BindStmt _ pat list1 : quals) = do dfListComp _ _ (ParStmt {} : _) = panic "dfListComp ParStmt" dfListComp _ _ (RecStmt {} : _) = panic "dfListComp RecStmt" -dfListComp _ _ (XStmtLR ApplicativeStmt {} : _) = - panic "dfListComp ApplicativeStmt" dfBindComp :: Id -> Id -- 'c' and 'n' -> (LPat GhcTc, CoreExpr) @@ -580,7 +575,6 @@ dsMcStmt (ParStmt bind_ty blocks mzip_op bind_op) stmts_rest = do { exp <- dsInnerMonadComp stmts bndrs return_op ; return (exp, mkBigCoreVarTupTy bndrs) } -dsMcStmt stmt@(XStmtLR ApplicativeStmt {}) _ = pprPanic "dsMcStmt: unexpected stmt" (ppr stmt) dsMcStmt stmt@(RecStmt {}) _ = pprPanic "dsMcStmt: unexpected stmt" (ppr stmt) matchTuple :: [Id] -> CoreExpr -> DsM CoreExpr ===================================== compiler/GHC/HsToCore/Pmc/Desugar.hs ===================================== @@ -373,7 +373,6 @@ desugarGuard guard = case guard of ParStmt {} -> panic "desugarGuard ParStmt" TransStmt {} -> panic "desugarGuard TransStmt" RecStmt {} -> panic "desugarGuard RecStmt" - XStmtLR ApplicativeStmt{} -> panic "desugarGuard ApplicativeLastStmt" sequenceGrdDagMapM :: Applicative f => (a -> f GrdDag) -> [a] -> f GrdDag sequenceGrdDagMapM f as = sequenceGrdDags <$> traverse f as ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -1684,7 +1684,7 @@ repE (HsProjection _ xs) = repProjection (fmap (field_label . unLoc . dfoLabel . repE (HsEmbTy _ t) = do t1 <- repLTy (hswc_body t) rep2 typeEName [unC t1] -repE e@(XExpr (ExpandedThingRn o x)) +repE e@(XExpr (ExpandedThingRn o x _)) | OrigExpr e <- o = do { rebindable_on <- lift $ xoptM LangExt.RebindableSyntax ; if rebindable_on -- See Note [Quotation and rebindable syntax] ===================================== compiler/GHC/HsToCore/Ticks.hs ===================================== @@ -611,7 +611,7 @@ addTickHsExpr (HsDo srcloc cxt (L l stmts)) _ -> Nothing addTickHsExpanded :: HsThingRn -> HsExpr GhcTc -> TM (HsExpr GhcTc) -addTickHsExpanded o@(OrigStmt (L pos LastStmt{})) e +addTickHsExpanded o@(OrigStmt (L pos LastStmt{}) _) e -- LastStmt always gets a tick for breakpoint and hpc coverage = do d <- getDensity case d of @@ -752,33 +752,10 @@ addTickStmt isGuard stmt@(RecStmt {}) ; return (stmt { recS_stmts = noLocA stmts', recS_ret_fn = ret' , recS_mfix_fn = mfix', recS_bind_fn = bind' }) } -addTickStmt isGuard (XStmtLR (ApplicativeStmt body_ty args mb_join)) = do - args' <- mapM (addTickApplicativeArg isGuard) args - return (XStmtLR (ApplicativeStmt body_ty args' mb_join)) - addTick :: Maybe (Bool -> BoxLabel) -> LHsExpr GhcTc -> TM (LHsExpr GhcTc) addTick isGuard e | Just fn <- isGuard = addBinTickLHsExpr fn e | otherwise = addTickLHsExprRHS e -addTickApplicativeArg - :: Maybe (Bool -> BoxLabel) -> (SyntaxExpr GhcTc, ApplicativeArg GhcTc) - -> TM (SyntaxExpr GhcTc, ApplicativeArg GhcTc) -addTickApplicativeArg isGuard (op, arg) = - liftM2 (,) (addTickSyntaxExpr hpcSrcSpan op) (addTickArg arg) - where - addTickArg (ApplicativeArgOne m_fail pat expr isBody) = - ApplicativeArgOne - <$> mapM (addTickSyntaxExpr hpcSrcSpan) m_fail - <*> addTickLPat pat - <*> addTickLHsExpr expr - <*> pure isBody - addTickArg (ApplicativeArgMany x stmts ret pat ctxt) = - (ApplicativeArgMany x) - <$> addTickLStmts isGuard stmts - <*> (unLoc <$> addTickLHsExpr (L (noAnnSrcSpan hpcSrcSpan) ret)) - <*> addTickLPat pat - <*> pure ctxt - addTickStmtAndBinders :: Maybe (Bool -> BoxLabel) -> ParStmtBlock GhcTc GhcTc -> TM (ParStmtBlock GhcTc GhcTc) addTickStmtAndBinders isGuard (ParStmtBlock x stmts ids returnExpr) = @@ -967,8 +944,6 @@ addTickCmdStmt stmt@(RecStmt {}) ; bind' <- addTickSyntaxExpr hpcSrcSpan (recS_bind_fn stmt) ; return (stmt { recS_stmts = noLocA stmts', recS_ret_fn = ret' , recS_mfix_fn = mfix', recS_bind_fn = bind' }) } -addTickCmdStmt (XStmtLR (ApplicativeStmt{})) = - panic "ToDo: addTickCmdStmt ApplicativeLastStmt" -- Others should never happen in a command context. addTickCmdStmt stmt = pprPanic "addTickHsCmd" (ppr stmt) ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1372,7 +1372,6 @@ instance ( ToHie (LocatedA (body (GhcPass p))) ] XStmtLR x -> case hiePass @p of HieRn -> extApplicativeStmt x - HieTc -> extApplicativeStmt x where node = case hiePass @p of HieTc -> makeNodeA stmt span ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -1965,15 +1965,10 @@ ApplicativeDo touches a few phases in the compiler: don't exist in the source code. See ApplicativeStmt and ApplicativeArg in HsExpr. -* Typechecker: ApplicativeDo passes through the typechecker much like any - other form of expression. The only crux is that the typechecker has to - be aware of the special ApplicativeDo statements in the do-notation, and - typecheck them appropriately. - Relevant module: GHC.Tc.Gen.Match - -* Desugarer: Any do-block which contains applicative statements is desugared - as outlined above, to use the Applicative combinators. - Relevant module: GHC.HsToCore.Expr +* Typechecker: All the ApplicativeDo statements are expanded on the fly + to its actual semantics (as shown above) with appropriate user syntax. The typechecker + then checks the syntax as any other form of expression. + Relevant module: GHC.Tc.Gen.Do , GHC.Tc.Gen.Match.tcStmts -} @@ -2221,12 +2216,12 @@ stmtTreeToStmts monad_names ctxt (StmtTreeApplicative trees) tail tail_fvs = do (stmts',fvs2) <- stmtTreeToStmts monad_names ctxt tree [] pvarset (mb_ret, fvs1) <- if | L _ (XStmtLR ApplicativeStmt{}) <- last stmts' -> - return (unLoc tup, emptyNameSet) + return (tup, emptyNameSet) | otherwise -> do -- Need 'pureAName' and not 'returnMName' here, so that it requires -- 'Applicative' and not 'Monad' whenever possible (until #20540 is fixed). (ret, _) <- lookupQualifiedDoExpr (HsDoStmt ctxt) pureAName - let expr = HsApp noExtField (noLocA ret) tup + let expr = noLocA (HsApp noExtField (noLocA ret) tup) return (expr, emptyFVs) return ( ApplicativeArgMany { xarg_app_arg_many = noExtField ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -464,10 +464,11 @@ tcValArgs do_ql args -- Now check the argument ; arg' <- tcScalingUsage mult $ - do { traceTc "tcEValArg" $ - vcat [ ppr ctxt - , text "arg type:" <+> ppr arg_ty - , text "arg:" <+> ppr arg ] + do { ingencode <- inGeneratedCode + ; traceTc "tcEValArg" $ + vcat [ ppr ctxt + , text "arg type:" <+> ppr arg_ty + , text "arg:" <+> ppr arg ] ; tcEValArg ctxt arg arg_ty } ; return (eva { eva_arg = ValArg arg' @@ -537,7 +538,7 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args fun_orig | VAExpansion (OrigStmt{}) _ _ <- fun_ctxt = DoOrigin - | VAExpansion (OrigPat pat) _ _ <- fun_ctxt + | VAExpansion (OrigPat pat _) _ _ <- fun_ctxt = DoPatOrigin pat | VAExpansion (OrigExpr e) _ _ <- fun_ctxt = exprCtOrigin e @@ -733,7 +734,6 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args matchActualFunTy herald (Just $ HsExprTcThing tc_fun) (n_val_args, fun_sigma) fun_ty - ; (delta', arg') <- if do_ql then addArgCtxt ctxt arg $ -- Context needed for constraints @@ -796,23 +796,32 @@ addArgCtxt :: AppCtxt -> LHsExpr GhcRn addArgCtxt ctxt (L arg_loc arg) thing_inside = do { in_generated_code <- inGeneratedCode ; case ctxt of - VACall fun arg_no _ | not in_generated_code + VACall{} + | XExpr (PopErrCtxt{}) <- arg + -> thing_inside + VACall{} + | XExpr (ExpandedThingRn o _ _) <- arg + , not isHsThingRnExpr o + -> thing_inside + + VACall fun arg_no _ + | not in_generated_code -> do setSrcSpanA arg_loc $ addErrCtxt (funAppCtxt fun arg arg_no) $ thing_inside - VAExpansion (OrigStmt (L _ stmt@(BindStmt {}))) _ loc + VAExpansion (OrigStmt (L _ stmt@(BindStmt {})) flav) _ loc | isGeneratedSrcSpan (locA arg_loc) -- This arg is the second argument to generated (>>=) -> setSrcSpan loc $ - addStmtCtxt stmt $ + addStmtCtxt stmt flav $ thing_inside - | otherwise -- This arg is the first argument to generated (>>=) + | otherwise -- This arg is the first argument to generated (>>=) -> setSrcSpanA arg_loc $ - addStmtCtxt stmt $ + addStmtCtxt stmt flav $ thing_inside - VAExpansion (OrigStmt (L loc stmt)) _ _ + VAExpansion (OrigStmt (L loc stmt) flav) _ _ -> setSrcSpanA loc $ - addStmtCtxt stmt $ + addStmtCtxt stmt flav $ thing_inside _ -> setSrcSpanA arg_loc $ @@ -943,7 +952,7 @@ expr_to_type earg = | otherwise = not_in_scope where occ = occName rdr not_in_scope = failWith $ mkTcRnNotInScope rdr NotInScope - go (L l (XExpr (ExpandedThingRn (OrigExpr orig) _))) = + go (L l (XExpr (ExpandedThingRn (OrigExpr orig) _ _))) = -- Use the original, user-written expression (before expansion). -- Example. Say we have vfun :: forall a -> blah -- and the call vfun (Maybe [1,2,3]) ===================================== compiler/GHC/Tc/Gen/Do.hs ===================================== @@ -21,8 +21,8 @@ module GHC.Tc.Gen.Do (expandDoStmts) where import GHC.Prelude -import GHC.Rename.Utils ( wrapGenSpan, genHsExpApps, genHsApp, genHsLet, - genHsLamDoExp, genHsCaseAltDoExp, genWildPat ) +import GHC.Rename.Utils ( wrapGenSpan, genHsExpApps, genHsApp, genHsLet, genLHsApp, + genHsLamDoExp, genHsCaseAltDoExp ) import GHC.Tc.Utils.Monad import GHC.Tc.Gen.Pat import GHC.Tc.Utils.TcMType @@ -53,66 +53,56 @@ import Data.List ((\\)) -- so that they can be typechecked. -- See Note [Expanding HsDo with XXExprGhcRn] below for `HsDo` specific commentary -- and Note [Handling overloaded and rebindable constructs] for high level commentary -expandDoStmts :: HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (LHsExpr GhcRn) -expandDoStmts doFlav stmts = do expanded_expr <- expand_do_stmts doFlav stmts - case expanded_expr of - L _ (XExpr (PopErrCtxt e)) -> return e - -- The first expanded stmt doesn't need a pop as - -- it would otherwise pop the "In the expression do ... " from - -- the error context - _ -> return expanded_expr +expandDoStmts :: HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (HsExpr GhcRn) +expandDoStmts doFlav stmts = unLoc <$> expand_do_stmts False doFlav stmts -- | The main work horse for expanding do block statements into applications of binds and thens -- See Note [Expanding HsDo with XXExprGhcRn] -expand_do_stmts :: HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (LHsExpr GhcRn) +expand_do_stmts :: Bool -> HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (LHsExpr GhcRn) -expand_do_stmts ListComp _ = +expand_do_stmts _ ListComp _ = pprPanic "expand_do_stmts: impossible happened. ListComp" empty -- handeled by `GHC.Tc.Gen.Match.tcLcStmt` -expand_do_stmts _ [] = pprPanic "expand_do_stmts: impossible happened. Empty stmts" empty +expand_do_stmts _ _ [] = pprPanic "expand_do_stmts: impossible happened. Empty stmts" empty -expand_do_stmts _ (stmt@(L _ (TransStmt {})):_) = +expand_do_stmts _ _ (stmt@(L _ (TransStmt {})):_) = pprPanic "expand_do_stmts: TransStmt" $ ppr stmt -- handeled by `GHC.Tc.Gen.Match.tcLcStmt` -expand_do_stmts _ (stmt@(L _ (ParStmt {})):_) = +expand_do_stmts _ _ (stmt@(L _ (ParStmt {})):_) = pprPanic "expand_do_stmts: ParStmt" $ ppr stmt -- handeled by `GHC.Tc.Gen.Match.tcLcStmt` -expand_do_stmts _ (stmt@(L _ (XStmtLR ApplicativeStmt{})): _) = - pprPanic "expand_do_stmts: Applicative Stmt" $ ppr stmt - -- Handeled by tcSyntaxOp see `GHC.Tc.Gen.Match.tcStmtsAndThen` - - -expand_do_stmts _ [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_expr))] +expand_do_stmts addPop flav [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_expr))] -- See Note [Expanding HsDo with XXExprGhcRn] Equation (5) below -- last statement of a list comprehension, needs to explicitly return it -- See `checkLastStmt` and `Syntax.Expr.StmtLR.LastStmt` | NoSyntaxExprRn <- ret_expr -- Last statement is just body if we are not in ListComp context. See Syntax.Expr.LastStmt - = do traceTc "expand_do_stmts last" (ppr ret_expr) - return $ mkExpandedStmtPopAt loc stmt body + = return $ if addPop then mkExpandedStmtPopAt loc stmt flav TcExpr body + else mkExpandedStmtAt loc stmt flav TcExpr body | SyntaxExprRn ret <- ret_expr -- -- ------------------------------------------------ -- return e ~~> return e -- to make T18324 work - = do traceTc "expand_do_stmts last" (ppr ret_expr) - let expansion = genHsApp ret (L body_loc body) - return $ mkExpandedStmtPopAt loc stmt expansion + = do let expansion = genHsApp ret (L body_loc body) + return $ if addPop then mkExpandedStmtPopAt loc stmt flav TcExpr expansion + else mkExpandedStmtAt loc stmt flav TcExpr expansion -expand_do_stmts do_or_lc (stmt@(L loc (LetStmt _ bs)) : lstmts) = +expand_do_stmts addPop doFlavour (stmt@(L loc (LetStmt _ bs)) : lstmts) = -- See Note [Expanding HsDo with XXExprGhcRn] Equation (3) below -- stmts ~~> stmts' -- ------------------------------------------------ -- let x = e ; stmts ~~> let x = e in stmts' - do expand_stmts <- expand_do_stmts do_or_lc lstmts + do expand_stmts <- expand_do_stmts True doFlavour lstmts let expansion = genHsLet bs expand_stmts - return $ mkExpandedStmtPopAt loc stmt expansion + return $ if addPop then mkExpandedStmtPopAt loc stmt doFlavour TcExpr expansion + else mkExpandedStmtAt loc stmt doFlavour TcExpr expansion -expand_do_stmts do_or_lc (stmt@(L loc (BindStmt xbsrn pat e)): lstmts) +expand_do_stmts addPop doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts) | SyntaxExprRn bind_op <- xbsrn_bindOp xbsrn , fail_op <- xbsrn_failOp xbsrn -- See Note [Expanding HsDo with XXExprGhcRn] Equation (2) below @@ -121,29 +111,31 @@ expand_do_stmts do_or_lc (stmt@(L loc (BindStmt xbsrn pat e)): lstmts) -- _ -> fail "Pattern match failure .." -- ------------------------------------------------------- -- pat <- e ; stmts ~~> (>>=) e f - = do expand_stmts <- expand_do_stmts do_or_lc lstmts - failable_expr <- mk_failable_expr do_or_lc pat expand_stmts fail_op + = do expand_stmts <- expand_do_stmts True doFlavour lstmts + failable_expr <- mk_failable_expr doFlavour Nothing pat expand_stmts fail_op let expansion = genHsExpApps bind_op -- (>>=) [ e , failable_expr ] - return $ mkExpandedStmtPopAt loc stmt expansion + return $ if addPop then mkExpandedStmtPopAt loc stmt doFlavour TcApp expansion + else mkExpandedStmtAt loc stmt doFlavour TcApp expansion | otherwise = pprPanic "expand_do_stmts: The impossible happened, missing bind operator from renamer" (text "stmt" <+> ppr stmt) -expand_do_stmts do_or_lc (stmt@(L loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) = +expand_do_stmts addPop doFlavour (stmt@(L loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) = -- See Note [BodyStmt] in Language.Haskell.Syntax.Expr -- See Note [Expanding HsDo with XXExprGhcRn] Equation (1) below -- stmts ~~> stmts' -- ---------------------------------------------- -- e ; stmts ~~> (>>) e stmts' - do expand_stmts_expr <- expand_do_stmts do_or_lc lstmts + do expand_stmts_expr <- expand_do_stmts True doFlavour lstmts let expansion = genHsExpApps then_op -- (>>) [ e , expand_stmts_expr ] - return $ mkExpandedStmtPopAt loc stmt expansion + return $ if addPop then mkExpandedStmtPopAt loc stmt doFlavour TcApp expansion + else mkExpandedStmtAt loc stmt doFlavour TcApp expansion -expand_do_stmts do_or_lc +expand_do_stmts _ doFlavour ((L loc (RecStmt { recS_stmts = L stmts_loc rec_stmts , recS_later_ids = later_ids -- forward referenced local ids , recS_rec_ids = local_ids -- ids referenced outside of the rec block @@ -163,12 +155,12 @@ expand_do_stmts do_or_lc -- -> do { rec_stmts -- ; return (local_only_ids ++ later_ids) } )) -- (\ [ local_only_ids ++ later_ids ] -> stmts') - do expand_stmts <- expand_do_stmts do_or_lc lstmts + do expand_stmts <- expand_do_stmts True doFlavour lstmts -- NB: No need to wrap the expansion with an ExpandedStmt -- as we want to flatten the rec block statements into its parent do block anyway return $ mkHsApps (wrapGenSpan bind_fun) -- (>>=) [ (wrapGenSpan mfix_fun) `mkHsApp` mfix_expr -- (mfix (do block)) - , genHsLamDoExp do_or_lc [ mkBigLHsVarPatTup all_ids ] -- (\ x -> + , genHsLamDoExp doFlavour [ mkBigLHsVarPatTup all_ids ] -- (\ x -> expand_stmts -- stmts') ] where @@ -184,33 +176,112 @@ expand_do_stmts do_or_lc do_stmts :: XRec GhcRn [ExprLStmt GhcRn] do_stmts = L stmts_loc $ rec_stmts ++ [return_stmt] do_block :: LHsExpr GhcRn - do_block = L loc $ HsDo noExtField do_or_lc do_stmts + do_block = L loc $ HsDo noExtField doFlavour do_stmts mfix_expr :: LHsExpr GhcRn - mfix_expr = genHsLamDoExp do_or_lc [ wrapGenSpan (LazyPat noExtField $ mkBigLHsVarPatTup all_ids) ] + mfix_expr = genHsLamDoExp doFlavour [ wrapGenSpan (LazyPat noExtField $ mkBigLHsVarPatTup all_ids) ] $ do_block -- NB: LazyPat because we do not want to eagerly evaluate the pattern -- and potentially loop forever -expand_do_stmts _ stmts = pprPanic "expand_do_stmts: impossible happened" $ (ppr stmts) +expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join))): lstmts) = +-- See Note [Applicative BodyStmt] +-- +-- stmts ~~> stmts' +-- ------------------------------------------------------------------------- +-- [(fmap, \ x -> e1), (<*>, e2), (<*>, e3), .. ] ; stmts ~~> (\ x -> stmts') <$> e1 <*> e2 ... +-- +-- Very similar to HsToCore.Expr.dsDo + +-- args are [(<$>, e1), (<*>, e2), .., ] + do { xexpr <- expand_do_stmts False doFlavour lstmts + -- extracts pats and arg bodies (rhss) from args + + ; (pats_can_fail, rhss) <- unzip <$> mapM (do_arg . snd) args + + -- add blocks for failable patterns + ; body_with_fails <- foldrM match_args xexpr (zip pats_can_fail rhss) + + -- builds (body <$> e1 <*> e2 ...) + ; let expand_ado_expr = foldl mk_apps body_with_fails (zip (map fst args) rhss) + + -- wrap the expanded expression with a `join` if needed + ; let final_expr = case mb_join of + Just (SyntaxExprRn join_op) + -> genLHsApp join_op expand_ado_expr + _ -> expand_ado_expr + ; traceTc "expand_do_stmts AppStmt" (vcat [ text "args:" <+> ppr args + , text "lstmts:" <+> ppr lstmts + , text "mb_join:" <+> ppr mb_join + , text "expansion:" <+> ppr final_expr]) + ; return $ final_expr + + } + where + do_arg :: ApplicativeArg GhcRn -> TcM ((LPat GhcRn, FailOperator GhcRn), LHsExpr GhcRn) + do_arg (ApplicativeArgOne + { xarg_app_arg_one = mb_fail_op + , app_arg_pattern = pat + , arg_expr = (L rhs_loc rhs) + , is_body_stmt = is_body_stmt + }) = + do let xx_expr = if addPop then mkExpandedStmtPopAt rhs_loc stmt doFlavour TcExpr rhs + else mkExpandedStmtAt rhs_loc stmt doFlavour TcExpr rhs + traceTc "do_arg" (text "OneArg" <+> vcat [ppr pat, ppr xx_expr]) + return ((pat, mb_fail_op) + , xx_expr) + where stmt = if is_body_stmt + then (L rhs_loc (BodyStmt NoExtField (L rhs_loc rhs) NoSyntaxExprRn NoSyntaxExprRn)) + else (L rhs_loc (BindStmt xbsn pat (L rhs_loc rhs))) + do_arg (ApplicativeArgMany _ stmts ret@(L ret_loc _) pat ctxt) = + do { xx_expr <- expand_do_stmts False ctxt $ stmts ++ [L ret_loc $ mkLastStmt ret] + ; traceTc "do_arg" (text "ManyArg" <+> vcat [ppr stmts, text "--", ppr xx_expr]) + ; return ((pat, Nothing) + , xx_expr) } + + match_args :: ((LPat GhcRn, FailOperator GhcRn), LHsExpr GhcRn) -> LHsExpr GhcRn -> TcM (LHsExpr GhcRn) + match_args ((pat, fail_op), stmt_expr) body = mk_failable_expr doFlavour stmt_ctxt pat body fail_op + where stmt_ctxt = case unLoc stmt_expr of + XExpr (ExpandedThingRn (OrigStmt s _) _ _) -> Just (doFlavour, s) + _ -> Nothing + + mk_apps :: LHsExpr GhcRn -> (SyntaxExprRn, LHsExpr GhcRn) -> LHsExpr GhcRn + mk_apps l_expr (op, r_expr) = + case op of + SyntaxExprRn op -> wrapGenSpan $ genHsExpApps op [ l_expr, r_expr ] + NoSyntaxExprRn -> pprPanic "expand_do_stmts applicative op:" (ppr op) + + xbsn :: XBindStmtRn + xbsn = XBindStmtRn NoSyntaxExprRn Nothing + + +expand_do_stmts _ _ stmts = pprPanic "expand_do_stmts: impossible happened" $ (ppr stmts) -- checks the pattern `pat`for irrefutability which decides if we need to wrap it with a fail block -mk_failable_expr :: HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (LHsExpr GhcRn) -mk_failable_expr doFlav pat@(L loc _) expr fail_op = +mk_failable_expr :: HsDoFlavour -> Maybe (HsDoFlavour, ExprLStmt GhcRn) + -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (LHsExpr GhcRn) +mk_failable_expr doFlav mb_stmt_info lpat@(L loc pat) expr fail_op = do { is_strict <- xoptM LangExt.Strict - ; irrf_pat <- isIrrefutableHsPatRnTcM is_strict pat - ; traceTc "mk_failable_expr" (vcat [ text "pat:" <+> ppr pat + ; irrf_pat <- isIrrefutableHsPatRnTcM is_strict lpat + ; traceTc "mk_failable_expr" (vcat [ text "pat:" <+> ppr lpat , text "isIrrefutable:" <+> ppr irrf_pat ]) ; if irrf_pat -- don't wrap with fail block if -- the pattern is irrefutable - then return $ genHsLamDoExp doFlav [pat] expr - else L loc <$> mk_fail_block doFlav pat expr fail_op + then case pat of + (WildPat{}) -> return $ genHsLamDoExp doFlav [L noSrcSpanA pat] expr + _ -> return $ case mb_stmt_info of + Nothing -> genHsLamDoExp doFlav [lpat] expr + Just (f, s) -> wrapGenSpan (mkExpandedStmt s f TcExpr + (unLoc $ (genHsLamDoExp f [lpat] + $ wrapGenSpan (mkPopErrCtxtExpr expr)))) + else L loc <$> mk_fail_block doFlav mb_stmt_info lpat expr fail_op } -- makes the fail block with a given fail_op -mk_fail_block :: HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (HsExpr GhcRn) -mk_fail_block doFlav pat@(L ploc _) e (Just (SyntaxExprRn fail_op)) = +mk_fail_block :: HsDoFlavour -> Maybe (HsDoFlavour, ExprLStmt GhcRn) + -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (HsExpr GhcRn) +mk_fail_block doFlav mb_stmt_info pat@(L ploc _) e (Just (SyntaxExprRn fail_op)) = do dflags <- getDynFlags return $ HsLam noAnn LamCases $ mkMatchGroup (doExpansionOrigin doFlav) -- \ (wrapGenSpan [ genHsCaseAltDoExp doFlav pat e -- pat -> expr @@ -218,22 +289,22 @@ mk_fail_block doFlav pat@(L ploc _) e (Just (SyntaxExprRn fail_op)) = ]) where fail_alt_case :: DynFlags -> LPat GhcRn -> HsExpr GhcRn -> LMatch GhcRn (LHsExpr GhcRn) - fail_alt_case dflags pat fail_op = genHsCaseAltDoExp doFlav genWildPat $ + fail_alt_case dflags pat fail_op = genHsCaseAltDoExp doFlav (L ploc $ WildPat noExtField) $ L ploc (fail_op_expr dflags pat fail_op) fail_op_expr :: DynFlags -> LPat GhcRn -> HsExpr GhcRn -> HsExpr GhcRn fail_op_expr dflags pat fail_op - = mkExpandedPatRn pat $ + = mkExpandedPatRn pat mb_stmt_info $ genHsApp fail_op (mk_fail_msg_expr dflags pat) mk_fail_msg_expr :: DynFlags -> LPat GhcRn -> LHsExpr GhcRn mk_fail_msg_expr dflags pat = nlHsLit $ mkHsString $ showPpr dflags $ - text "Pattern match failure in" <+> pprHsDoFlavour (DoExpr Nothing) + text "Pattern match failure in" <+> pprHsDoFlavour doFlav <+> text "at" <+> ppr (getLocA pat) -mk_fail_block _ _ _ _ = pprPanic "mk_fail_block: impossible happened" empty +mk_fail_block _ _ _ _ _ = pprPanic "mk_fail_block: impossible happened" empty {- Note [Expanding HsDo with XXExprGhcRn] @@ -302,12 +373,29 @@ They capture the essence of statement expansions as implemented in `expand_do_st (5) DO【 s 】 = s + (4) DO【 AppStmt s; ss 】 + = APPSTMT【 (AppStmt s, ss) 】 + + RECDO【 _ 】 maps a sequence of recursively dependent monadic statements and converts it into an expression paired with the variables that the rec finds a fix point of. (6) RECDO【 ss 】 = (vars, mfix (\~vars -> (>>=) (DO【 ss 】) (return vars))) where vars are all the variables free in ss + APPSTMT【 _ 】 expands the applicative statements as given in Note [ApplicativeDo] in GHC.Rename.Expr (dsDo) + The applicative statement is generated by GHC.Rename.Expr.postProcessStmtsForApplicativeDo + + + (7) APPSTMT 【 (AppStmt (s1 | s2 ... | sn), ss) 】 + = join (\argpat (s1) .. argpat(sn) -> DO 【 ss 】) + <$> ‹ExpansionStmt s1› argexpr(arg_1) + <*> ... + <*> ‹PopErrCtxt› ‹ExpansionStmt s1› argexpr(arg_n) + + where argpat (p <- s) = p + argexpr(p <- s) = s + For a concrete example, consider a `do`-block written by the user ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -710,27 +710,25 @@ tcXExpr (PopErrCtxt (L loc e)) res_ty setSrcSpanA loc $ tcExpr e res_ty -tcXExpr xe@(ExpandedThingRn o e') res_ty - | OrigStmt ls@(L loc s at LetStmt{}) <- o +tcXExpr xe@(ExpandedThingRn o e' tc_info) res_ty + | OrigStmt ls@(L loc s at LetStmt{}) flav <- o , HsLet x binds e <- e' = do { (binds', wrapper, e') <- setSrcSpanA loc $ - addStmtCtxt s $ + addStmtCtxt s flav $ tcLocalBinds binds $ tcMonoExprNC e res_ty -- NB: Do not call tcMonoExpr here as it adds -- a duplicate error context - ; return $ mkExpandedStmtTc ls (HsLet x binds' (mkLHsWrap wrapper e')) + ; return $ mkExpandedStmtTc ls flav (HsLet x binds' (mkLHsWrap wrapper e')) } - | OrigStmt ls@(L loc s at LastStmt{}) <- o - = setSrcSpanA loc $ - addStmtCtxt s $ - mkExpandedStmtTc ls <$> tcExpr e' res_ty - -- It is important that we call tcExpr (and not tcApp) here as - -- `e` is the last statement's body expression - -- and not a HsApp of a generated (>>) or (>>=) - -- This improves error messages e.g. tests: DoExpansion1, DoExpansion2, DoExpansion3 - | OrigStmt ls@(L loc _) <- o + | OrigStmt ls@(L loc s) flav <- o + , TcExpr <- tc_info = setSrcSpanA loc $ - mkExpandedStmtTc ls <$> tcApp (XExpr xe) res_ty + addStmtCtxt s flav $ + mkExpandedStmtTc ls flav <$> tcExpr e' res_ty + | OrigStmt ls@(L loc _) flav <- o + , TcApp <- tc_info + = setSrcSpanA loc $ + mkExpandedStmtTc ls flav <$> tcApp (XExpr xe) res_ty tcXExpr xe res_ty = tcApp (XExpr xe) res_ty ===================================== compiler/GHC/Tc/Gen/Head.hs ===================================== @@ -240,7 +240,7 @@ appCtxtLoc (VACall _ _ l) = l insideExpansion :: AppCtxt -> Bool insideExpansion (VAExpansion {}) = True -insideExpansion (VACall {}) = False -- but what if the VACall has a generated context? +insideExpansion (VACall _ _ src) = isGeneratedSrcSpan src instance Outputable AppCtxt where ppr (VAExpansion e l _) = text "VAExpansion" <+> ppr e <+> ppr l @@ -292,7 +292,7 @@ splitHsApps e = go e (top_ctxt 0 e) [] top_ctxt n (HsPragE _ _ fun) = top_lctxt n fun top_ctxt n (HsAppType _ fun _) = top_lctxt (n+1) fun top_ctxt n (HsApp _ fun _) = top_lctxt (n+1) fun - top_ctxt n (XExpr (ExpandedThingRn o _)) + top_ctxt n (XExpr (ExpandedThingRn o _ _)) | OrigExpr fun <- o = VACall fun n noSrcSpan top_ctxt n other_fun = VACall other_fun n noSrcSpan @@ -317,19 +317,19 @@ splitHsApps e = go e (top_ctxt 0 e) [] HsQuasiQuote _ _ (L l _) -> set l ctxt -- l :: SrcAnn NoEpAnns -- See Note [Looking through ExpandedThingRn] - go (XExpr (ExpandedThingRn o e)) ctxt args + go (XExpr (ExpandedThingRn o e _)) ctxt args | isHsThingRnExpr o = go e (VAExpansion o (appCtxtLoc ctxt) (appCtxtLoc ctxt)) (EWrap (EExpand o) : args) - | OrigStmt (L _ stmt) <- o -- so that we set `(>>)` as generated + | OrigStmt (L _ stmt) _ <- o -- so that we set `(>>)` as generated , BodyStmt{} <- stmt -- and get the right unused bind warnings = go e (VAExpansion o generatedSrcSpan generatedSrcSpan) -- See Part 3. in Note [Expanding HsDo with XXExprGhcRn] (EWrap (EExpand o) : args) -- in `GHC.Tc.Gen.Do` - | OrigPat (L loc _) <- o -- so that we set the compiler generated fail context + | OrigPat (L loc _) _ <- o -- so that we set the compiler generated fail context = go e (VAExpansion o (locA loc) (locA loc)) -- to be originating from a failable pattern -- See Part 1. Wrinkle 2. of (EWrap (EExpand o) : args) -- Note [Expanding HsDo with XXExprGhcRn] @@ -893,17 +893,20 @@ tcInferAppHead_maybe fun _ -> return Nothing addHeadCtxt :: AppCtxt -> TcM a -> TcM a -addHeadCtxt (VAExpansion (OrigStmt (L loc stmt)) _ _) thing_inside = - do setSrcSpanA loc $ - addStmtCtxt stmt +addHeadCtxt (VAExpansion (OrigStmt (L loc stmt) flav) _ _) thing_inside = + do traceTc "addHeadCtxt stmt" (ppr stmt) + setSrcSpanA loc $ + addStmtCtxt stmt flav $ thing_inside addHeadCtxt fun_ctxt thing_inside | not (isGoodSrcSpan fun_loc) -- noSrcSpan => no arguments = thing_inside -- => context is already set | otherwise = setSrcSpan fun_loc $ - do case fun_ctxt of + do traceTc "addHeadCtxt fun_loc" (ppr fun_ctxt) + case fun_ctxt of VAExpansion (OrigExpr orig) _ _ -> addExprCtxt orig thing_inside + VAExpansion (OrigPat _ (Just (flav, stmt))) _ _ -> addStmtCtxt (unLoc stmt) flav $ thing_inside _ -> thing_inside where fun_loc = appCtxtLoc fun_ctxt @@ -1587,9 +1590,9 @@ mis-match in the number of value arguments. * * ********************************************************************* -} -addStmtCtxt :: ExprStmt GhcRn -> TcRn a -> TcRn a -addStmtCtxt stmt thing_inside - = do let err_doc = pprStmtInCtxt (HsDoStmt (DoExpr Nothing)) stmt +addStmtCtxt :: ExprStmt GhcRn -> HsDoFlavour -> TcRn a -> TcRn a +addStmtCtxt stmt flav thing_inside + = do let err_doc = pprStmtInCtxt (HsDoStmt flav) stmt addErrCtxt err_doc thing_inside where pprStmtInCtxt :: HsStmtContextRn -> StmtLR GhcRn GhcRn (LHsExpr GhcRn) -> SDoc @@ -1602,6 +1605,7 @@ addExprCtxt :: HsExpr GhcRn -> TcRn a -> TcRn a addExprCtxt e thing_inside = case e of HsUnboundVar {} -> thing_inside + XExpr (ExpandedThingRn (OrigStmt stmt flav) _ _) -> addStmtCtxt (unLoc stmt) flav thing_inside _ -> addErrCtxt (exprCtxt e) thing_inside -- The HsUnboundVar special case addresses situations like -- f x = _ ===================================== compiler/GHC/Tc/Gen/Match.hs ===================================== @@ -78,13 +78,9 @@ import GHC.Types.SrcLoc import GHC.Types.Basic( VisArity, isDoExpansionGenerated ) import Control.Monad -import Control.Arrow ( second ) import qualified Data.List.NonEmpty as NE import Data.Maybe (mapMaybe) -import qualified GHC.LanguageExtensions as LangExt - - {- ************************************************************************ * * @@ -353,20 +349,16 @@ tcDoStmts ListComp (L l stmts) res_ty (mkCheckExpType elt_ty) ; return $ mkHsWrapCo co (HsDo list_ty ListComp (L l stmts')) } -tcDoStmts doExpr@(DoExpr _) ss@(L l stmts) res_ty - = do { isApplicativeDo <- xoptM LangExt.ApplicativeDo - ; if isApplicativeDo - then do { stmts' <- tcStmts (HsDoStmt doExpr) tcDoStmt stmts res_ty - ; res_ty <- readExpType res_ty - ; return (HsDo res_ty doExpr (L l stmts')) } - else do { expanded_expr <- expandDoStmts doExpr stmts - -- Do expansion on the fly - ; mkExpandedExprTc (HsDo noExtField doExpr ss) <$> tcExpr (unLoc expanded_expr) res_ty } +tcDoStmts doExpr@(DoExpr _) ss@(L _ stmts) res_ty + = do { traceTc "tcDoStmts" $ text "original:" <+> ppr ss + ; expanded_expr <- expandDoStmts doExpr stmts -- Do expansion on the fly + ; traceTc "tcDoStmts" $ text "expansion:" <+> ppr expanded_expr + ; mkExpandedExprTc (HsDo noExtField doExpr ss) <$> tcExpr expanded_expr res_ty } tcDoStmts mDoExpr@(MDoExpr _) ss@(L _ stmts) res_ty = do { expanded_expr <- expandDoStmts mDoExpr stmts -- Do expansion on the fly - ; mkExpandedExprTc (HsDo noExtField mDoExpr ss) <$> tcExpr (unLoc expanded_expr) res_ty } + ; mkExpandedExprTc (HsDo noExtField mDoExpr ss) <$> tcExpr expanded_expr res_ty } tcDoStmts MonadComp (L l stmts) res_ty = do { stmts' <- tcStmts (HsDoStmt MonadComp) tcMcStmt stmts res_ty @@ -997,18 +989,6 @@ tcDoStmt ctxt (RecStmt { recS_stmts = L l stmts, recS_later_ids = later_names , recS_ret_ty = stmts_ty} }, thing) }} -tcDoStmt ctxt (XStmtLR (ApplicativeStmt _ pairs mb_join)) res_ty thing_inside - = do { let tc_app_stmts ty = tcApplicativeStmts ctxt pairs ty $ - thing_inside . mkCheckExpType - ; ((pairs', body_ty, thing), mb_join') <- case mb_join of - Nothing -> (, Nothing) <$> tc_app_stmts res_ty - Just join_op -> - second Just <$> - (tcSyntaxOp DoOrigin join_op [SynRho] res_ty $ - \ [rhs_ty] [rhs_mult] -> tcScalingUsage rhs_mult $ tc_app_stmts (mkCheckExpType rhs_ty)) - - ; return (XStmtLR $ ApplicativeStmt body_ty pairs' mb_join', thing) } - tcDoStmt _ stmt _ _ = pprPanic "tcDoStmt: unexpected Stmt" (ppr stmt) @@ -1084,87 +1064,6 @@ To achieve this we: all branches. This step is done with bindLocalNames. -} -tcApplicativeStmts - :: HsStmtContextRn - -> [(SyntaxExpr GhcRn, ApplicativeArg GhcRn)] - -> ExpRhoType -- rhs_ty - -> (TcRhoType -> TcM t) -- thing_inside - -> TcM ([(SyntaxExpr GhcTc, ApplicativeArg GhcTc)], Type, t) - -tcApplicativeStmts ctxt pairs rhs_ty thing_inside - = do { body_ty <- newFlexiTyVarTy liftedTypeKind - ; let arity = length pairs - ; ts <- replicateM (arity-1) $ newInferExpType - ; exp_tys <- replicateM arity $ newFlexiTyVarTy liftedTypeKind - ; pat_tys <- replicateM arity $ newFlexiTyVarTy liftedTypeKind - ; let fun_ty = mkVisFunTysMany pat_tys body_ty - - -- NB. do the <$>,<*> operators first, we don't want type errors here - -- i.e. goOps before goArgs - -- See Note [Treat rebindable syntax first] - ; let (ops, args) = unzip pairs - ; ops' <- goOps fun_ty (zip3 ops (ts ++ [rhs_ty]) exp_tys) - - -- Typecheck each ApplicativeArg separately - -- See Note [ApplicativeDo and constraints] - ; args' <- mapM (goArg body_ty) (zip3 args pat_tys exp_tys) - - -- Bring into scope all the things bound by the args, - -- and typecheck the thing_inside - -- See Note [ApplicativeDo and constraints] - ; res <- tcExtendIdEnv (concatMap get_arg_bndrs args') $ - thing_inside body_ty - - ; return (zip ops' args', body_ty, res) } - where - goOps _ [] = return [] - goOps t_left ((op,t_i,exp_ty) : ops) - = do { (_, op') - <- tcSyntaxOp DoOrigin op - [synKnownType t_left, synKnownType exp_ty] t_i $ - \ _ _ -> return () - ; t_i <- readExpType t_i - ; ops' <- goOps t_i ops - ; return (op' : ops') } - - goArg :: Type -> (ApplicativeArg GhcRn, Type, Type) - -> TcM (ApplicativeArg GhcTc) - - goArg body_ty (ApplicativeArgOne - { xarg_app_arg_one = fail_op - , app_arg_pattern = pat - , arg_expr = rhs - , .. - }, pat_ty, exp_ty) - = setSrcSpan (combineSrcSpans (getLocA pat) (getLocA rhs)) $ - addErrCtxt (pprStmtInCtxt ctxt (mkRnBindStmt pat rhs)) $ - do { rhs' <- tcCheckMonoExprNC rhs exp_ty - ; (pat', _) <- tcCheckPat (StmtCtxt ctxt) pat (unrestricted pat_ty) $ - return () - ; fail_op' <- fmap join . forM fail_op $ \fail -> - tcMonadFailOp (DoPatOrigin pat) pat' fail body_ty - - ; return (ApplicativeArgOne - { xarg_app_arg_one = fail_op' - , app_arg_pattern = pat' - , arg_expr = rhs' - , .. } - ) } - - goArg _body_ty (ApplicativeArgMany x stmts ret pat ctxt, pat_ty, exp_ty) - = do { (stmts', (ret',pat')) <- - tcStmtsAndThen (HsDoStmt ctxt) tcDoStmt stmts (mkCheckExpType exp_ty) $ - \res_ty -> do - { ret' <- tcExpr ret res_ty - ; (pat', _) <- tcCheckPat (StmtCtxt (HsDoStmt ctxt)) pat (unrestricted pat_ty) $ - return () - ; return (ret', pat') - } - ; return (ApplicativeArgMany x stmts' ret' pat' ctxt) } - - get_arg_bndrs :: ApplicativeArg GhcTc -> [Id] - get_arg_bndrs (ApplicativeArgOne { app_arg_pattern = pat }) = collectPatBinders CollNoDictBinders pat - get_arg_bndrs (ApplicativeArgMany { bv_pattern = pat }) = collectPatBinders CollNoDictBinders pat {- Note [ApplicativeDo and constraints] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -751,9 +751,9 @@ exprCtOrigin (HsUntypedSplice {}) = Shouldn'tHappenOrigin "TH untyped splice" exprCtOrigin (HsProc {}) = Shouldn'tHappenOrigin "proc" exprCtOrigin (HsStatic {}) = Shouldn'tHappenOrigin "static expression" exprCtOrigin (HsEmbTy {}) = Shouldn'tHappenOrigin "type expression" -exprCtOrigin (XExpr (ExpandedThingRn thing _)) | OrigExpr a <- thing = exprCtOrigin a - | OrigStmt _ <- thing = DoOrigin - | OrigPat p <- thing = DoPatOrigin p +exprCtOrigin (XExpr (ExpandedThingRn thing _ _)) | OrigExpr a <- thing = exprCtOrigin a + | OrigStmt _ _ <- thing = DoOrigin + | OrigPat p _ <- thing = DoPatOrigin p exprCtOrigin (XExpr (PopErrCtxt {})) = Shouldn'tHappenOrigin "PopErrCtxt" -- | Extract a suitable CtOrigin from a MatchGroup ===================================== compiler/GHC/Tc/Zonk/Type.hs ===================================== @@ -97,7 +97,6 @@ import GHC.Tc.Types.BasicTypes import GHC.Data.Maybe import GHC.Data.Bag -import Control.Monad import Control.Monad.Trans.Class ( lift ) import Data.Semigroup import Data.List.NonEmpty ( NonEmpty ) @@ -1409,54 +1408,6 @@ zonkStmt zBody (BindStmt xbs pat body) }) new_pat new_body } --- Scopes: join > ops (in reverse order) > pats (in forward order) --- > rest of stmts -zonkStmt _zBody (XStmtLR (ApplicativeStmt body_ty args mb_join)) - = do { new_mb_join <- zonk_join mb_join - ; new_args <- zonk_args args - ; new_body_ty <- noBinders $ zonkTcTypeToTypeX body_ty - ; return $ XStmtLR $ ApplicativeStmt new_body_ty new_args new_mb_join } - where - zonk_join Nothing = return Nothing - zonk_join (Just j) = Just <$> zonkSyntaxExpr j - - get_pat :: (SyntaxExpr GhcTc, ApplicativeArg GhcTc) -> LPat GhcTc - get_pat (_, ApplicativeArgOne _ pat _ _) = pat - get_pat (_, ApplicativeArgMany _ _ _ pat _) = pat - - replace_pat :: LPat GhcTc - -> (SyntaxExpr GhcTc, ApplicativeArg GhcTc) - -> (SyntaxExpr GhcTc, ApplicativeArg GhcTc) - replace_pat pat (op, ApplicativeArgOne fail_op _ a isBody) - = (op, ApplicativeArgOne fail_op pat a isBody) - replace_pat pat (op, ApplicativeArgMany x a b _ c) - = (op, ApplicativeArgMany x a b pat c) - - zonk_args args - = do { new_args_rev <- zonk_args_rev (reverse args) - ; new_pats <- zonkPats (map get_pat args) - ; return $ zipWithEqual "zonkStmt" replace_pat - new_pats (reverse new_args_rev) } - - -- these need to go backward, because if any operators are higher-rank, - -- later operators may introduce skolems that are in scope for earlier - -- arguments - zonk_args_rev ((op, arg) : args) - = do { new_op <- zonkSyntaxExpr op - ; new_arg <- noBinders $ zonk_arg arg - ; new_args <- zonk_args_rev args - ; return $ (new_op, new_arg) : new_args } - zonk_args_rev [] = return [] - - zonk_arg (ApplicativeArgOne fail_op pat expr isBody) - = do { new_expr <- zonkLExpr expr - ; new_fail <- forM fail_op $ don'tBind . zonkSyntaxExpr - ; return (ApplicativeArgOne new_fail pat new_expr isBody) } - zonk_arg (ApplicativeArgMany x stmts ret pat ctxt) - = runZonkBndrT (zonkStmts zonkLExpr stmts) $ \ new_stmts -> - do { new_ret <- zonkExpr ret - ; return (ApplicativeArgMany x new_stmts new_ret pat ctxt) } - ------------------------------------------------------------------------- zonkRecFields :: HsRecordBinds GhcTc -> ZonkTcM (HsRecordBinds GhcTc) zonkRecFields (HsRecFields flds dd) ===================================== testsuite/tests/ado/T13242a.stderr ===================================== @@ -1,13 +1,13 @@ - T13242a.hs:10:5: error: [GHC-46956] • Couldn't match expected type ‘a0’ with actual type ‘a’ - • because type variable ‘a’ would escape its scope - This (rigid, skolem) type variable is bound by - a pattern with constructor: A :: forall a. Eq a => a -> T, - in a pattern binding in - a 'do' block - at T13242a.hs:10:3-5 - • In the expression: + because type variable ‘a’ would escape its scope + This (rigid, skolem) type variable is bound by + a pattern with constructor: A :: forall a. Eq a => a -> T, + in a pattern binding in + a 'do' block + at T13242a.hs:10:3-5 + • In a stmt of a 'do' block: A x <- undefined + In the expression: do A x <- undefined _ <- return 'a' _ <- return 'b' @@ -29,7 +29,7 @@ T13242a.hs:13:13: error: [GHC-39999] instance Eq Ordering -- Defined in ‘GHC.Classes’ instance Eq Integer -- Defined in ‘GHC.Num.Integer’ ...plus 23 others - ...plus five instances involving out-of-scope types + ...plus six instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In a stmt of a 'do' block: return (x == x) In the expression: @@ -43,3 +43,4 @@ T13242a.hs:13:13: error: [GHC-39999] _ <- return 'a' _ <- return 'b' return (x == x) + ===================================== testsuite/tests/ado/T16135.hs ===================================== @@ -1,5 +1,9 @@ {-# LANGUAGE ExistentialQuantification, ApplicativeDo #-} +{- This testcase failed before we treated Do statements via HsExpansions + This test passes after #24406 +-} + module Bug where data T f = forall a. MkT (f a) ===================================== testsuite/tests/ado/T16135.stderr deleted ===================================== @@ -1,19 +0,0 @@ -T16135.hs:11:18: error: [GHC-83865] - • Couldn't match type ‘a0’ with ‘a’ - Expected: f a0 - Actual: f a - ‘a0’ is untouchable - inside the constraints: Functor f - bound by the type signature for: - runf :: forall (f :: * -> *). Functor f => IO (T f) - at T16135.hs:7:1-39 - ‘a’ is a rigid type variable bound by - a pattern with constructor: - MkT :: forall {k} (f :: k -> *) (a :: k). f a -> T f, - in a pattern binding in - a 'do' block - at T16135.hs:10:5-10 - • In the first argument of ‘MkT’, namely ‘fa’ - In the second argument of ‘($)’, namely ‘MkT fa’ - In a stmt of a 'do' block: return $ MkT fa - • Relevant bindings include fa :: f a (bound at T16135.hs:10:9) ===================================== testsuite/tests/ado/T24406.hs ===================================== @@ -0,0 +1,14 @@ +{-# LANGUAGE ImpredicativeTypes, ApplicativeDo #-} +module T where + +t :: IO (forall a. a -> a) +t = return id + +p :: (forall a. a -> a) -> (Bool, Int) +p f = (f True, f 3) + +-- This typechecks (with QL) +foo1 = t >>= \x -> return (p x) + +-- But this did not not type check: +foo2 = do { x <- t ; return (p x) } ===================================== testsuite/tests/ado/ado002.stderr ===================================== @@ -1,4 +1,3 @@ - ado002.hs:8:8: error: [GHC-83865] • Couldn't match expected type: Char -> IO b0 with actual type: IO Char @@ -24,30 +23,39 @@ ado002.hs:9:3: error: [GHC-83865] y <- getChar 'a' print (x, y) -ado002.hs:15:11: error: [GHC-83865] - • Couldn't match expected type ‘Int’ with actual type ‘Char’ - • In the expression: y - In a stmt of a 'do' block: return (y, x) +ado002.hs:13:8: error: [GHC-83865] + • Couldn't match type ‘Char’ with ‘Int’ + Expected: IO Int + Actual: IO Char + • In a stmt of a 'do' block: x <- getChar In the expression: do x <- getChar y <- getChar return (y, x) + In an equation for ‘g’: + g = do x <- getChar + y <- getChar + return (y, x) -ado002.hs:15:13: error: [GHC-83865] - • Couldn't match expected type ‘Int’ with actual type ‘Char’ - • In the expression: x - In a stmt of a 'do' block: return (y, x) +ado002.hs:14:8: error: [GHC-83865] + • Couldn't match type ‘Char’ with ‘Int’ + Expected: IO Int + Actual: IO Char + • In a stmt of a 'do' block: y <- getChar In the expression: do x <- getChar y <- getChar return (y, x) + In an equation for ‘g’: + g = do x <- getChar + y <- getChar + return (y, x) -ado002.hs:23:9: error: [GHC-83865] - • Couldn't match expected type: Char -> IO a0 - with actual type: IO Char - • The function ‘getChar’ is applied to one visible argument, - but its type ‘IO Char’ has none - In a stmt of a 'do' block: x5 <- getChar x4 +ado002.hs:20:9: error: [GHC-83865] + • Couldn't match type ‘Char’ with ‘Int’ + Expected: IO Int + Actual: IO Char + • In a stmt of a 'do' block: x2 <- getChar In the expression: do x1 <- getChar x2 <- getChar @@ -55,11 +63,17 @@ ado002.hs:23:9: error: [GHC-83865] x4 <- getChar x5 <- getChar x4 return (x2, x4) + In an equation for ‘h’: + h = do x1 <- getChar + x2 <- getChar + x3 <- const (return ()) x1 + x4 <- getChar + x5 <- getChar x4 + return (x2, x4) -ado002.hs:24:11: error: [GHC-83865] +ado002.hs:23:3: error: [GHC-83865] • Couldn't match expected type ‘Int’ with actual type ‘Char’ - • In the expression: x2 - In a stmt of a 'do' block: return (x2, x4) + • In a stmt of a 'do' block: x4 <- getChar In the expression: do x1 <- getChar x2 <- getChar @@ -67,11 +81,20 @@ ado002.hs:24:11: error: [GHC-83865] x4 <- getChar x5 <- getChar x4 return (x2, x4) + In an equation for ‘h’: + h = do x1 <- getChar + x2 <- getChar + x3 <- const (return ()) x1 + x4 <- getChar + x5 <- getChar x4 + return (x2, x4) -ado002.hs:24:14: error: [GHC-83865] - • Couldn't match expected type ‘Int’ with actual type ‘Char’ - • In the expression: x4 - In a stmt of a 'do' block: return (x2, x4) +ado002.hs:23:9: error: [GHC-83865] + • Couldn't match expected type: Char -> IO a0 + with actual type: IO Char + • The function ‘getChar’ is applied to one visible argument, + but its type ‘IO Char’ has none + In a stmt of a 'do' block: x5 <- getChar x4 In the expression: do x1 <- getChar x2 <- getChar @@ -79,3 +102,4 @@ ado002.hs:24:14: error: [GHC-83865] x4 <- getChar x5 <- getChar x4 return (x2, x4) + ===================================== testsuite/tests/ado/ado003.stderr ===================================== @@ -1,7 +1,7 @@ -ado003.hs:7:3: error: [GHC-83865] - • Couldn't match expected type ‘Int’ with actual type ‘Char’ - • In the pattern: 'a' +ado003.hs:7:18: error: [GHC-83865] + • Couldn't match expected type ‘Char’ with actual type ‘Int’ + • In the first argument of ‘return’, namely ‘(3 :: Int)’ In a stmt of a 'do' block: 'a' <- return (3 :: Int) In the expression: do x <- getChar ===================================== testsuite/tests/ado/ado004.stderr ===================================== @@ -8,24 +8,24 @@ TYPE SIGNATURES test1c :: forall (f :: * -> *). Applicative f => (Int -> f Int) -> f Int test2 :: - forall {f :: * -> *} {t} {b}. - (Applicative f, Num t, Num b) => + forall {f :: * -> *} {b} {t}. + (Applicative f, Num b, Num t) => (t -> f b) -> f b test2a :: - forall {f :: * -> *} {t} {b}. - (Functor f, Num t, Num b) => + forall {f :: * -> *} {b} {t}. + (Functor f, Num b, Num t) => (t -> f b) -> f b test2b :: forall {f :: * -> *} {t} {a}. (Applicative f, Num t) => (t -> a) -> f a test2c :: - forall {f :: * -> *} {t} {b}. - (Functor f, Num t, Num b) => + forall {f :: * -> *} {b} {t}. + (Functor f, Num b, Num t) => (t -> f b) -> f b test2d :: - forall {f :: * -> *} {t} {b} {a}. - (Functor f, Num t, Num b) => + forall {f :: * -> *} {b} {t} {a}. + (Functor f, Num b, Num t) => (t -> f a) -> f b test3 :: forall {m :: * -> *} {t1} {t2} {a}. @@ -44,4 +44,4 @@ TYPE SIGNATURES (Monad m, Num (m a)) => (m a -> m (m a)) -> p -> m a Dependent modules: [] -Dependent packages: [base-4.16.0.0] +Dependent packages: [base-4.20.0.0] ===================================== testsuite/tests/ado/all.T ===================================== @@ -20,6 +20,7 @@ test('T15344', normal, compile_and_run, ['']) test('T16628', normal, compile_fail, ['']) test('T17835', normal, compile, ['']) test('T20540', normal, compile, ['']) -test('T16135', [when(compiler_debugged(),expect_broken(16135))], compile_fail, ['']) +test('T16135', normal, compile, ['']) test('T22483', normal, compile, ['-Wall']) test('OrPatStrictness', normal, compile_and_run, ['']) +test('T24406', normal, compile, ['']) ===================================== testsuite/tests/determinism/determ021/determ021.stdout ===================================== @@ -1,16 +1,16 @@ [1 of 1] Compiling A ( A.hs, A.o ) TYPE SIGNATURES test2 :: - forall {f :: * -> *} {t} {b}. - (Applicative f, Num t, Num b) => + forall {f :: * -> *} {b} {t}. + (Applicative f, Num b, Num t) => (t -> f b) -> f b Dependent modules: [] -Dependent packages: [base-4.16.0.0] +Dependent packages: [base-4.20.0.0] [1 of 1] Compiling A ( A.hs, A.o ) TYPE SIGNATURES test2 :: - forall {f :: * -> *} {t} {b}. - (Applicative f, Num t, Num b) => + forall {f :: * -> *} {b} {t}. + (Applicative f, Num b, Num t) => (t -> f b) -> f b Dependent modules: [] -Dependent packages: [base-4.16.0.0] +Dependent packages: [base-4.20.0.0] ===================================== testsuite/tests/ghci.debugger/scripts/break029.stdout ===================================== @@ -1,9 +1,9 @@ Stopped in Main.f, break029.hs:(4,7)-(6,16) _result :: IO Int = _ x :: Int = 3 -Stopped in Main.f, break029.hs:5:8-21 -_result :: IO Int = _ -x :: Int = 3 +Stopped in Main.f, break029.hs:6:3-16 +_result :: Int = _ +y :: Int = _ Stopped in Main.f, break029.hs:6:11-15 _result :: Int = _ y :: Int = _ ===================================== testsuite/tests/hiefile/should_run/T23540.stdout ===================================== @@ -28,22 +28,6 @@ At point (15,8), we found: ========================== At point (30,8), we found: ========================== -┌ -│ $dMonad at T23540.hs:1:1, of type: Monad Identity -│ is an evidence variable bound by a let, depending on: [$fMonadIdentity] -│ with scope: ModuleScope -│ -│ Defined at -└ -| -`- ┌ - │ $fMonadIdentity at T23540.hs:25:10-23, of type: Monad Identity - │ is an evidence variable bound by an instance of class Monad - │ with scope: ModuleScope - │ - │ Defined at T23540.hs:25:10 - └ - ========================== At point (43,8), we found: ========================== @@ -123,38 +107,6 @@ At point (49,14), we found: ========================== At point (61,7), we found: ========================== -┌ -│ $dApplicative at T23540.hs:1:1, of type: Applicative Identity' -│ is an evidence variable bound by a let, depending on: [$fApplicativeIdentity'] -│ with scope: ModuleScope -│ -│ Defined at -└ -| -`- ┌ - │ $fApplicativeIdentity' at T23540.hs:56:10-30, of type: Applicative Identity' - │ is an evidence variable bound by an instance of class Applicative - │ with scope: ModuleScope - │ - │ Defined at T23540.hs:56:10 - └ - -┌ -│ $dFunctor at T23540.hs:1:1, of type: Functor Identity' -│ is an evidence variable bound by a let, depending on: [$fFunctorIdentity'] -│ with scope: ModuleScope -│ -│ Defined at -└ -| -`- ┌ - │ $fFunctorIdentity' at T23540.hs:54:10-26, of type: Functor Identity' - │ is an evidence variable bound by an instance of class Functor - │ with scope: ModuleScope - │ - │ Defined at T23540.hs:54:10 - └ - ========================== At point (69,4), we found: ========================== View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6575ca679c9883cf834e0a5a2e6d5300e4f8f476 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6575ca679c9883cf834e0a5a2e6d5300e4f8f476 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 7 21:56:21 2024 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Fri, 07 Jun 2024 17:56:21 -0400 Subject: [Git][ghc/ghc][wip/expansions-appdo] 4 commits: StgToCmm: refactor opTranslate and friends Message-ID: <66638205bc101_1b2a66b0b78c1368bb@gitlab.mail> Apoorv Ingle pushed to branch wip/expansions-appdo at Glasgow Haskell Compiler / GHC Commits: 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - 8a753de0 by Apoorv Ingle at 2024-06-07T16:56:09-05:00 Make ApplicativeDo work with HsExpansions testcase added: T24406 Issues Fixed: #24406, #16135 Code Changes: - Remove `XStmtLR GhcTc` as `XStmtLR GhcRn` is now compiled to `HsExpr GhcTc` - The expanded statements are guided by `GHC.Hs.Expr.TcFunInfo` which is used to decide if the `XExpr GhcRn` is to be typechecked using `tcApp` or `tcExpr` Note [Expanding HsDo with XXExprGhcRn] explains the change in more detail - - - - - 30 changed files: - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/Driver/Config/StgToCmm.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/StgToCmm/Config.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Zonk/Type.hs - testsuite/tests/ado/T13242a.stderr - testsuite/tests/ado/T16135.hs - − testsuite/tests/ado/T16135.stderr - + testsuite/tests/ado/T24406.hs - testsuite/tests/ado/ado002.stderr - testsuite/tests/ado/ado003.stderr - testsuite/tests/ado/ado004.stderr - testsuite/tests/ado/all.T The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6575ca679c9883cf834e0a5a2e6d5300e4f8f476...8a753de0626d75d94ad774197d98aaed273db5a0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6575ca679c9883cf834e0a5a2e6d5300e4f8f476...8a753de0626d75d94ad774197d98aaed273db5a0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 04:35:04 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sat, 08 Jun 2024 00:35:04 -0400 Subject: [Git][ghc/ghc][wip/T24945] 6 commits: Improve haddocks of Language.Haskell.Syntax.Pat.Pat Message-ID: <6663df782eb15_3d87d32c7b3287487@gitlab.mail> Cheng Shao pushed to branch wip/T24945 at Glasgow Haskell Compiler / GHC Commits: 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - 5ef6cbeb by Cheng Shao at 2024-06-08T04:34:32+00:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9 changed files: - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/Driver/Config/StgToCmm.hs - compiler/GHC/StgToCmm/Config.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/Language/Haskell/Syntax/Pat.hs - libraries/base/tests/all.T - rts/Inlines.c - rts/include/Stg.h - testsuite/tests/driver/objc/all.T Changes: ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -94,12 +94,6 @@ is32BitPlatform = do platform <- getPlatform return $ target32Bit platform -expect32BitPlatform :: SDoc -> NatM () -expect32BitPlatform doc = do - is32Bit <- is32BitPlatform - when (not is32Bit) $ - pprPanic "Expecting 32-bit platform" doc - sse2Enabled :: NatM Bool sse2Enabled = do config <- getConfig @@ -2475,35 +2469,10 @@ genSimplePrim bid MO_F64_Acosh [dst] [src] = genLibCCall bid genSimplePrim bid MO_F64_Atanh [dst] [src] = genLibCCall bid (fsLit "atanh") [dst] [src] genSimplePrim bid MO_SuspendThread [tok] [rs,i] = genRTSCCall bid (fsLit "suspendThread") [tok] [rs,i] genSimplePrim bid MO_ResumeThread [rs] [tok] = genRTSCCall bid (fsLit "resumeThread") [rs] [tok] -genSimplePrim _ MO_I64_ToI [dst] [src] = genInt64ToInt dst src -genSimplePrim _ MO_I64_FromI [dst] [src] = genIntToInt64 dst src -genSimplePrim _ MO_W64_ToW [dst] [src] = genWord64ToWord dst src -genSimplePrim _ MO_W64_FromW [dst] [src] = genWordToWord64 dst src -genSimplePrim _ MO_x64_Neg [dst] [src] = genNeg64 dst src -genSimplePrim _ MO_x64_Add [dst] [x,y] = genAdd64 dst x y -genSimplePrim _ MO_x64_Sub [dst] [x,y] = genSub64 dst x y -genSimplePrim bid MO_x64_Mul [dst] [x,y] = genPrimCCall bid (fsLit "hs_mul64") [dst] [x,y] genSimplePrim bid MO_I64_Quot [dst] [x,y] = genPrimCCall bid (fsLit "hs_quotInt64") [dst] [x,y] genSimplePrim bid MO_I64_Rem [dst] [x,y] = genPrimCCall bid (fsLit "hs_remInt64") [dst] [x,y] genSimplePrim bid MO_W64_Quot [dst] [x,y] = genPrimCCall bid (fsLit "hs_quotWord64") [dst] [x,y] genSimplePrim bid MO_W64_Rem [dst] [x,y] = genPrimCCall bid (fsLit "hs_remWord64") [dst] [x,y] -genSimplePrim _ MO_x64_And [dst] [x,y] = genAnd64 dst x y -genSimplePrim _ MO_x64_Or [dst] [x,y] = genOr64 dst x y -genSimplePrim _ MO_x64_Xor [dst] [x,y] = genXor64 dst x y -genSimplePrim _ MO_x64_Not [dst] [src] = genNot64 dst src -genSimplePrim bid MO_x64_Shl [dst] [x,n] = genPrimCCall bid (fsLit "hs_uncheckedShiftL64") [dst] [x,n] -genSimplePrim bid MO_I64_Shr [dst] [x,n] = genPrimCCall bid (fsLit "hs_uncheckedIShiftRA64") [dst] [x,n] -genSimplePrim bid MO_W64_Shr [dst] [x,n] = genPrimCCall bid (fsLit "hs_uncheckedShiftRL64") [dst] [x,n] -genSimplePrim _ MO_x64_Eq [dst] [x,y] = genEq64 dst x y -genSimplePrim _ MO_x64_Ne [dst] [x,y] = genNe64 dst x y -genSimplePrim _ MO_I64_Ge [dst] [x,y] = genGeInt64 dst x y -genSimplePrim _ MO_I64_Gt [dst] [x,y] = genGtInt64 dst x y -genSimplePrim _ MO_I64_Le [dst] [x,y] = genLeInt64 dst x y -genSimplePrim _ MO_I64_Lt [dst] [x,y] = genLtInt64 dst x y -genSimplePrim _ MO_W64_Ge [dst] [x,y] = genGeWord64 dst x y -genSimplePrim _ MO_W64_Gt [dst] [x,y] = genGtWord64 dst x y -genSimplePrim _ MO_W64_Le [dst] [x,y] = genLeWord64 dst x y -genSimplePrim _ MO_W64_Lt [dst] [x,y] = genLtWord64 dst x y genSimplePrim _ op dst args = do platform <- ncgPlatform <$> getConfig pprPanic "genSimplePrim: unhandled primop" (ppr (pprCallishMachOp op, dst, fmap (pdoc platform) args)) @@ -4462,231 +4431,3 @@ genQuotRem width signed res_q res_r m_arg_x_high arg_x_low arg_y = do toOL [instr format y_reg, MOV format (OpReg rax) (OpReg reg_q), MOV format (OpReg rdx) (OpReg reg_r)] - - ----------------------------------------------------------------------------- --- The following functions implement certain 64-bit MachOps inline for 32-bit --- architectures. On 64-bit architectures, those MachOps aren't supported and --- calling these functions for a 64-bit target platform is considered an error --- (hence the use of `expect32BitPlatform`). --- --- On 64-bit platforms, generic MachOps should be used instead of these 64-bit --- specific ones (e.g. use MO_Add instead of MO_x64_Add). This MachOp selection --- is done by StgToCmm. - -genInt64ToInt :: LocalReg -> CmmExpr -> NatM InstrBlock -genInt64ToInt dst src = do - expect32BitPlatform (text "genInt64ToInt") - RegCode64 code _src_hi src_lo <- iselExpr64 src - let dst_r = getLocalRegReg dst - pure $ code `snocOL` MOV II32 (OpReg src_lo) (OpReg dst_r) - -genWord64ToWord :: LocalReg -> CmmExpr -> NatM InstrBlock -genWord64ToWord dst src = do - expect32BitPlatform (text "genWord64ToWord") - RegCode64 code _src_hi src_lo <- iselExpr64 src - let dst_r = getLocalRegReg dst - pure $ code `snocOL` MOV II32 (OpReg src_lo) (OpReg dst_r) - -genIntToInt64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genIntToInt64 dst src = do - expect32BitPlatform (text "genIntToInt64") - let Reg64 dst_hi dst_lo = localReg64 dst - src_code <- getAnyReg src - pure $ src_code rax `appOL` toOL - [ CLTD II32 -- sign extend EAX in EDX:EAX - , MOV II32 (OpReg rax) (OpReg dst_lo) - , MOV II32 (OpReg rdx) (OpReg dst_hi) - ] - -genWordToWord64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genWordToWord64 dst src = do - expect32BitPlatform (text "genWordToWord64") - let Reg64 dst_hi dst_lo = localReg64 dst - src_code <- getAnyReg src - pure $ src_code dst_lo - `snocOL` XOR II32 (OpReg dst_hi) (OpReg dst_hi) - -genNeg64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genNeg64 dst src = do - expect32BitPlatform (text "genNeg64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 code src_hi src_lo <- iselExpr64 src - pure $ code `appOL` toOL - [ MOV II32 (OpReg src_lo) (OpReg dst_lo) - , MOV II32 (OpReg src_hi) (OpReg dst_hi) - , NEGI II32 (OpReg dst_lo) - , ADC II32 (OpImm (ImmInt 0)) (OpReg dst_hi) - , NEGI II32 (OpReg dst_hi) - ] - -genAdd64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genAdd64 dst x y = do - expect32BitPlatform (text "genAdd64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , ADD II32 (OpReg y_lo) (OpReg dst_lo) - , ADC II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genSub64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genSub64 dst x y = do - expect32BitPlatform (text "genSub64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , SUB II32 (OpReg y_lo) (OpReg dst_lo) - , SBB II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genAnd64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genAnd64 dst x y = do - expect32BitPlatform (text "genAnd64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , AND II32 (OpReg y_lo) (OpReg dst_lo) - , AND II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genOr64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genOr64 dst x y = do - expect32BitPlatform (text "genOr64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , OR II32 (OpReg y_lo) (OpReg dst_lo) - , OR II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genXor64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genXor64 dst x y = do - expect32BitPlatform (text "genXor64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , XOR II32 (OpReg y_lo) (OpReg dst_lo) - , XOR II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genNot64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genNot64 dst src = do - expect32BitPlatform (text "genNot64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 src_code src_hi src_lo <- iselExpr64 src - pure $ src_code `appOL` toOL - [ MOV II32 (OpReg src_lo) (OpReg dst_lo) - , MOV II32 (OpReg src_hi) (OpReg dst_hi) - , NOT II32 (OpReg dst_lo) - , NOT II32 (OpReg dst_hi) - ] - -genEq64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genEq64 dst x y = do - expect32BitPlatform (text "genEq64") - let dst_r = getLocalRegReg dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - Reg64 tmp_hi tmp_lo <- getNewReg64 - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg tmp_lo) - , MOV II32 (OpReg x_hi) (OpReg tmp_hi) - , XOR II32 (OpReg y_lo) (OpReg tmp_lo) - , XOR II32 (OpReg y_hi) (OpReg tmp_hi) - , OR II32 (OpReg tmp_lo) (OpReg tmp_hi) - , SETCC EQQ (OpReg dst_r) - , MOVZxL II8 (OpReg dst_r) (OpReg dst_r) - ] - -genNe64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genNe64 dst x y = do - expect32BitPlatform (text "genNe64") - let dst_r = getLocalRegReg dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - Reg64 tmp_hi tmp_lo <- getNewReg64 - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg tmp_lo) - , MOV II32 (OpReg x_hi) (OpReg tmp_hi) - , XOR II32 (OpReg y_lo) (OpReg tmp_lo) - , XOR II32 (OpReg y_hi) (OpReg tmp_hi) - , OR II32 (OpReg tmp_lo) (OpReg tmp_hi) - , SETCC NE (OpReg dst_r) - , MOVZxL II8 (OpReg dst_r) (OpReg dst_r) - ] - -genGtWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGtWord64 dst x y = do - expect32BitPlatform (text "genGtWord64") - genPred64 LU dst y x - -genLtWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLtWord64 dst x y = do - expect32BitPlatform (text "genLtWord64") - genPred64 LU dst x y - -genGeWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGeWord64 dst x y = do - expect32BitPlatform (text "genGeWord64") - genPred64 GEU dst x y - -genLeWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLeWord64 dst x y = do - expect32BitPlatform (text "genLeWord64") - genPred64 GEU dst y x - -genGtInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGtInt64 dst x y = do - expect32BitPlatform (text "genGtInt64") - genPred64 LTT dst y x - -genLtInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLtInt64 dst x y = do - expect32BitPlatform (text "genLtInt64") - genPred64 LTT dst x y - -genGeInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGeInt64 dst x y = do - expect32BitPlatform (text "genGeInt64") - genPred64 GE dst x y - -genLeInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLeInt64 dst x y = do - expect32BitPlatform (text "genLeInt64") - genPred64 GE dst y x - -genPred64 :: Cond -> LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genPred64 cond dst x y = do - -- we can only rely on CF/SF/OF flags! - -- Not on ZF, which doesn't take into account the lower parts. - massert (cond `elem` [LU,GEU,LTT,GE]) - - let dst_r = getLocalRegReg dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - -- Basically we perform a subtraction with borrow. - -- As we don't need to result, we can use CMP instead of SUB for the low part - -- (it sets the borrow flag just like SUB does) - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_hi) (OpReg dst_r) - , CMP II32 (OpReg y_lo) (OpReg x_lo) - , SBB II32 (OpReg y_hi) (OpReg dst_r) - , SETCC cond (OpReg dst_r) - , MOVZxL II8 (OpReg dst_r) (OpReg dst_r) - ] ===================================== compiler/GHC/Driver/Config/StgToCmm.hs ===================================== @@ -53,9 +53,12 @@ initStgToCmmConfig dflags mod = StgToCmmConfig , stgToCmmExtDynRefs = gopt Opt_ExternalDynamicRefs dflags , stgToCmmDoBoundsCheck = gopt Opt_DoBoundsChecking dflags , stgToCmmDoTagCheck = gopt Opt_DoTagInferenceChecks dflags - -- backend flags - , stgToCmmAllowBigArith = not ncg || platformArch platform == ArchWasm32 || platformArch platform == ArchX86 - , stgToCmmAllowBigQuot = not ncg || platformArch platform == ArchWasm32 + + -- backend flags: + + -- LLVM, C, and some 32-bit NCG backends can also handle some 64-bit primops + , stgToCmmAllowArith64 = w64 || not ncg || platformArch platform == ArchWasm32 || platformArch platform == ArchX86 + , stgToCmmAllowQuot64 = w64 || not ncg || platformArch platform == ArchWasm32 , stgToCmmAllowQuotRemInstr = ncg && (x86ish || ppc) , stgToCmmAllowQuotRem2 = (ncg && (x86ish || ppc)) || llvm , stgToCmmAllowExtendedAddSubInstrs = (ncg && (x86ish || ppc)) || llvm @@ -90,6 +93,7 @@ initStgToCmmConfig dflags mod = StgToCmmConfig } where profile = targetProfile dflags platform = profilePlatform profile bk_end = backend dflags + w64 = platformWordSize platform == PW8 b_blob = if not ncg then Nothing else binBlobThreshold dflags (ncg, llvm) = case backendPrimitiveImplementation bk_end of GenericPrimitives -> (False, False) ===================================== compiler/GHC/StgToCmm/Config.hs ===================================== @@ -64,8 +64,8 @@ data StgToCmmConfig = StgToCmmConfig -- or not , stgToCmmDoTagCheck :: !Bool -- ^ Verify tag inference predictions. ------------------------------ Backend Flags ---------------------------------- - , stgToCmmAllowBigArith :: !Bool -- ^ Allowed to emit larger than native size arithmetic (only LLVM and C backends) - , stgToCmmAllowBigQuot :: !Bool -- ^ Allowed to emit larger than native size division operations + , stgToCmmAllowArith64 :: !Bool -- ^ Allowed to emit 64-bit arithmetic operations + , stgToCmmAllowQuot64 :: !Bool -- ^ Allowed to emit 64-bit division operations , stgToCmmAllowQuotRemInstr :: !Bool -- ^ Allowed to generate QuotRem instructions , stgToCmmAllowQuotRem2 :: !Bool -- ^ Allowed to generate QuotRem , stgToCmmAllowExtendedAddSubInstrs :: !Bool -- ^ Allowed to generate AddWordC, SubWordC, Add2, etc. ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -334,7 +334,7 @@ emitPrimOp cfg primop = StableNameToIntOp -> \[arg] -> opIntoRegs $ \[res] -> emitAssign (CmmLocal res) (cmmLoadIndexW platform arg (fixedHdrSizeW profile) (bWord platform)) - EqStablePtrOp -> \args -> opTranslate args (mo_wordEq platform) + EqStablePtrOp -> opTranslate (mo_wordEq platform) ReallyUnsafePtrEqualityOp -> \[arg1, arg2] -> opIntoRegs $ \[res] -> emitAssign (CmmLocal res) (CmmMachOp (mo_wordEq platform) [arg1,arg2]) @@ -1180,315 +1180,323 @@ emitPrimOp cfg primop = Narrow16WordOp -> \args -> opNarrow args (MO_UU_Conv, W16) Narrow32WordOp -> \args -> opNarrow args (MO_UU_Conv, W32) - DoublePowerOp -> \args -> opCallish args MO_F64_Pwr - DoubleSinOp -> \args -> opCallish args MO_F64_Sin - DoubleCosOp -> \args -> opCallish args MO_F64_Cos - DoubleTanOp -> \args -> opCallish args MO_F64_Tan - DoubleSinhOp -> \args -> opCallish args MO_F64_Sinh - DoubleCoshOp -> \args -> opCallish args MO_F64_Cosh - DoubleTanhOp -> \args -> opCallish args MO_F64_Tanh - DoubleAsinOp -> \args -> opCallish args MO_F64_Asin - DoubleAcosOp -> \args -> opCallish args MO_F64_Acos - DoubleAtanOp -> \args -> opCallish args MO_F64_Atan - DoubleAsinhOp -> \args -> opCallish args MO_F64_Asinh - DoubleAcoshOp -> \args -> opCallish args MO_F64_Acosh - DoubleAtanhOp -> \args -> opCallish args MO_F64_Atanh - DoubleLogOp -> \args -> opCallish args MO_F64_Log - DoubleLog1POp -> \args -> opCallish args MO_F64_Log1P - DoubleExpOp -> \args -> opCallish args MO_F64_Exp - DoubleExpM1Op -> \args -> opCallish args MO_F64_ExpM1 - DoubleSqrtOp -> \args -> opCallish args MO_F64_Sqrt - DoubleFabsOp -> \args -> opCallish args MO_F64_Fabs - - FloatPowerOp -> \args -> opCallish args MO_F32_Pwr - FloatSinOp -> \args -> opCallish args MO_F32_Sin - FloatCosOp -> \args -> opCallish args MO_F32_Cos - FloatTanOp -> \args -> opCallish args MO_F32_Tan - FloatSinhOp -> \args -> opCallish args MO_F32_Sinh - FloatCoshOp -> \args -> opCallish args MO_F32_Cosh - FloatTanhOp -> \args -> opCallish args MO_F32_Tanh - FloatAsinOp -> \args -> opCallish args MO_F32_Asin - FloatAcosOp -> \args -> opCallish args MO_F32_Acos - FloatAtanOp -> \args -> opCallish args MO_F32_Atan - FloatAsinhOp -> \args -> opCallish args MO_F32_Asinh - FloatAcoshOp -> \args -> opCallish args MO_F32_Acosh - FloatAtanhOp -> \args -> opCallish args MO_F32_Atanh - FloatLogOp -> \args -> opCallish args MO_F32_Log - FloatLog1POp -> \args -> opCallish args MO_F32_Log1P - FloatExpOp -> \args -> opCallish args MO_F32_Exp - FloatExpM1Op -> \args -> opCallish args MO_F32_ExpM1 - FloatSqrtOp -> \args -> opCallish args MO_F32_Sqrt - FloatFabsOp -> \args -> opCallish args MO_F32_Fabs + DoublePowerOp -> opCallish MO_F64_Pwr + DoubleSinOp -> opCallish MO_F64_Sin + DoubleCosOp -> opCallish MO_F64_Cos + DoubleTanOp -> opCallish MO_F64_Tan + DoubleSinhOp -> opCallish MO_F64_Sinh + DoubleCoshOp -> opCallish MO_F64_Cosh + DoubleTanhOp -> opCallish MO_F64_Tanh + DoubleAsinOp -> opCallish MO_F64_Asin + DoubleAcosOp -> opCallish MO_F64_Acos + DoubleAtanOp -> opCallish MO_F64_Atan + DoubleAsinhOp -> opCallish MO_F64_Asinh + DoubleAcoshOp -> opCallish MO_F64_Acosh + DoubleAtanhOp -> opCallish MO_F64_Atanh + DoubleLogOp -> opCallish MO_F64_Log + DoubleLog1POp -> opCallish MO_F64_Log1P + DoubleExpOp -> opCallish MO_F64_Exp + DoubleExpM1Op -> opCallish MO_F64_ExpM1 + DoubleSqrtOp -> opCallish MO_F64_Sqrt + DoubleFabsOp -> opCallish MO_F64_Fabs + + FloatPowerOp -> opCallish MO_F32_Pwr + FloatSinOp -> opCallish MO_F32_Sin + FloatCosOp -> opCallish MO_F32_Cos + FloatTanOp -> opCallish MO_F32_Tan + FloatSinhOp -> opCallish MO_F32_Sinh + FloatCoshOp -> opCallish MO_F32_Cosh + FloatTanhOp -> opCallish MO_F32_Tanh + FloatAsinOp -> opCallish MO_F32_Asin + FloatAcosOp -> opCallish MO_F32_Acos + FloatAtanOp -> opCallish MO_F32_Atan + FloatAsinhOp -> opCallish MO_F32_Asinh + FloatAcoshOp -> opCallish MO_F32_Acosh + FloatAtanhOp -> opCallish MO_F32_Atanh + FloatLogOp -> opCallish MO_F32_Log + FloatLog1POp -> opCallish MO_F32_Log1P + FloatExpOp -> opCallish MO_F32_Exp + FloatExpM1Op -> opCallish MO_F32_ExpM1 + FloatSqrtOp -> opCallish MO_F32_Sqrt + FloatFabsOp -> opCallish MO_F32_Fabs -- Native word signless ops - IntAddOp -> \args -> opTranslate args (mo_wordAdd platform) - IntSubOp -> \args -> opTranslate args (mo_wordSub platform) - WordAddOp -> \args -> opTranslate args (mo_wordAdd platform) - WordSubOp -> \args -> opTranslate args (mo_wordSub platform) - AddrAddOp -> \args -> opTranslate args (mo_wordAdd platform) - AddrSubOp -> \args -> opTranslate args (mo_wordSub platform) - - IntEqOp -> \args -> opTranslate args (mo_wordEq platform) - IntNeOp -> \args -> opTranslate args (mo_wordNe platform) - WordEqOp -> \args -> opTranslate args (mo_wordEq platform) - WordNeOp -> \args -> opTranslate args (mo_wordNe platform) - AddrEqOp -> \args -> opTranslate args (mo_wordEq platform) - AddrNeOp -> \args -> opTranslate args (mo_wordNe platform) - - WordAndOp -> \args -> opTranslate args (mo_wordAnd platform) - WordOrOp -> \args -> opTranslate args (mo_wordOr platform) - WordXorOp -> \args -> opTranslate args (mo_wordXor platform) - WordNotOp -> \args -> opTranslate args (mo_wordNot platform) - WordSllOp -> \args -> opTranslate args (mo_wordShl platform) - WordSrlOp -> \args -> opTranslate args (mo_wordUShr platform) - - AddrRemOp -> \args -> opTranslate args (mo_wordURem platform) + IntAddOp -> opTranslate (mo_wordAdd platform) + IntSubOp -> opTranslate (mo_wordSub platform) + WordAddOp -> opTranslate (mo_wordAdd platform) + WordSubOp -> opTranslate (mo_wordSub platform) + AddrAddOp -> opTranslate (mo_wordAdd platform) + AddrSubOp -> opTranslate (mo_wordSub platform) + + IntEqOp -> opTranslate (mo_wordEq platform) + IntNeOp -> opTranslate (mo_wordNe platform) + WordEqOp -> opTranslate (mo_wordEq platform) + WordNeOp -> opTranslate (mo_wordNe platform) + AddrEqOp -> opTranslate (mo_wordEq platform) + AddrNeOp -> opTranslate (mo_wordNe platform) + + WordAndOp -> opTranslate (mo_wordAnd platform) + WordOrOp -> opTranslate (mo_wordOr platform) + WordXorOp -> opTranslate (mo_wordXor platform) + WordNotOp -> opTranslate (mo_wordNot platform) + WordSllOp -> opTranslate (mo_wordShl platform) + WordSrlOp -> opTranslate (mo_wordUShr platform) + + AddrRemOp -> opTranslate (mo_wordURem platform) -- Native word signed ops - IntMulOp -> \args -> opTranslate args (mo_wordMul platform) - IntMulMayOfloOp -> \args -> opTranslate args (MO_S_MulMayOflo (wordWidth platform)) - IntQuotOp -> \args -> opTranslate args (mo_wordSQuot platform) - IntRemOp -> \args -> opTranslate args (mo_wordSRem platform) - IntNegOp -> \args -> opTranslate args (mo_wordSNeg platform) - - IntGeOp -> \args -> opTranslate args (mo_wordSGe platform) - IntLeOp -> \args -> opTranslate args (mo_wordSLe platform) - IntGtOp -> \args -> opTranslate args (mo_wordSGt platform) - IntLtOp -> \args -> opTranslate args (mo_wordSLt platform) - - IntAndOp -> \args -> opTranslate args (mo_wordAnd platform) - IntOrOp -> \args -> opTranslate args (mo_wordOr platform) - IntXorOp -> \args -> opTranslate args (mo_wordXor platform) - IntNotOp -> \args -> opTranslate args (mo_wordNot platform) - IntSllOp -> \args -> opTranslate args (mo_wordShl platform) - IntSraOp -> \args -> opTranslate args (mo_wordSShr platform) - IntSrlOp -> \args -> opTranslate args (mo_wordUShr platform) + IntMulOp -> opTranslate (mo_wordMul platform) + IntMulMayOfloOp -> opTranslate (MO_S_MulMayOflo (wordWidth platform)) + IntQuotOp -> opTranslate (mo_wordSQuot platform) + IntRemOp -> opTranslate (mo_wordSRem platform) + IntNegOp -> opTranslate (mo_wordSNeg platform) + + IntGeOp -> opTranslate (mo_wordSGe platform) + IntLeOp -> opTranslate (mo_wordSLe platform) + IntGtOp -> opTranslate (mo_wordSGt platform) + IntLtOp -> opTranslate (mo_wordSLt platform) + + IntAndOp -> opTranslate (mo_wordAnd platform) + IntOrOp -> opTranslate (mo_wordOr platform) + IntXorOp -> opTranslate (mo_wordXor platform) + IntNotOp -> opTranslate (mo_wordNot platform) + IntSllOp -> opTranslate (mo_wordShl platform) + IntSraOp -> opTranslate (mo_wordSShr platform) + IntSrlOp -> opTranslate (mo_wordUShr platform) -- Native word unsigned ops - WordGeOp -> \args -> opTranslate args (mo_wordUGe platform) - WordLeOp -> \args -> opTranslate args (mo_wordULe platform) - WordGtOp -> \args -> opTranslate args (mo_wordUGt platform) - WordLtOp -> \args -> opTranslate args (mo_wordULt platform) + WordGeOp -> opTranslate (mo_wordUGe platform) + WordLeOp -> opTranslate (mo_wordULe platform) + WordGtOp -> opTranslate (mo_wordUGt platform) + WordLtOp -> opTranslate (mo_wordULt platform) - WordMulOp -> \args -> opTranslate args (mo_wordMul platform) - WordQuotOp -> \args -> opTranslate args (mo_wordUQuot platform) - WordRemOp -> \args -> opTranslate args (mo_wordURem platform) + WordMulOp -> opTranslate (mo_wordMul platform) + WordQuotOp -> opTranslate (mo_wordUQuot platform) + WordRemOp -> opTranslate (mo_wordURem platform) - AddrGeOp -> \args -> opTranslate args (mo_wordUGe platform) - AddrLeOp -> \args -> opTranslate args (mo_wordULe platform) - AddrGtOp -> \args -> opTranslate args (mo_wordUGt platform) - AddrLtOp -> \args -> opTranslate args (mo_wordULt platform) + AddrGeOp -> opTranslate (mo_wordUGe platform) + AddrLeOp -> opTranslate (mo_wordULe platform) + AddrGtOp -> opTranslate (mo_wordUGt platform) + AddrLtOp -> opTranslate (mo_wordULt platform) -- Int8# signed ops - Int8ToIntOp -> \args -> opTranslate args (MO_SS_Conv W8 (wordWidth platform)) - IntToInt8Op -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W8) - Int8NegOp -> \args -> opTranslate args (MO_S_Neg W8) - Int8AddOp -> \args -> opTranslate args (MO_Add W8) - Int8SubOp -> \args -> opTranslate args (MO_Sub W8) - Int8MulOp -> \args -> opTranslate args (MO_Mul W8) - Int8QuotOp -> \args -> opTranslate args (MO_S_Quot W8) - Int8RemOp -> \args -> opTranslate args (MO_S_Rem W8) - - Int8SllOp -> \args -> opTranslate args (MO_Shl W8) - Int8SraOp -> \args -> opTranslate args (MO_S_Shr W8) - Int8SrlOp -> \args -> opTranslate args (MO_U_Shr W8) - - Int8EqOp -> \args -> opTranslate args (MO_Eq W8) - Int8GeOp -> \args -> opTranslate args (MO_S_Ge W8) - Int8GtOp -> \args -> opTranslate args (MO_S_Gt W8) - Int8LeOp -> \args -> opTranslate args (MO_S_Le W8) - Int8LtOp -> \args -> opTranslate args (MO_S_Lt W8) - Int8NeOp -> \args -> opTranslate args (MO_Ne W8) + Int8ToIntOp -> opTranslate (MO_SS_Conv W8 (wordWidth platform)) + IntToInt8Op -> opTranslate (MO_SS_Conv (wordWidth platform) W8) + Int8NegOp -> opTranslate (MO_S_Neg W8) + Int8AddOp -> opTranslate (MO_Add W8) + Int8SubOp -> opTranslate (MO_Sub W8) + Int8MulOp -> opTranslate (MO_Mul W8) + Int8QuotOp -> opTranslate (MO_S_Quot W8) + Int8RemOp -> opTranslate (MO_S_Rem W8) + + Int8SllOp -> opTranslate (MO_Shl W8) + Int8SraOp -> opTranslate (MO_S_Shr W8) + Int8SrlOp -> opTranslate (MO_U_Shr W8) + + Int8EqOp -> opTranslate (MO_Eq W8) + Int8GeOp -> opTranslate (MO_S_Ge W8) + Int8GtOp -> opTranslate (MO_S_Gt W8) + Int8LeOp -> opTranslate (MO_S_Le W8) + Int8LtOp -> opTranslate (MO_S_Lt W8) + Int8NeOp -> opTranslate (MO_Ne W8) -- Word8# unsigned ops - Word8ToWordOp -> \args -> opTranslate args (MO_UU_Conv W8 (wordWidth platform)) - WordToWord8Op -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W8) - Word8AddOp -> \args -> opTranslate args (MO_Add W8) - Word8SubOp -> \args -> opTranslate args (MO_Sub W8) - Word8MulOp -> \args -> opTranslate args (MO_Mul W8) - Word8QuotOp -> \args -> opTranslate args (MO_U_Quot W8) - Word8RemOp -> \args -> opTranslate args (MO_U_Rem W8) - - Word8AndOp -> \args -> opTranslate args (MO_And W8) - Word8OrOp -> \args -> opTranslate args (MO_Or W8) - Word8XorOp -> \args -> opTranslate args (MO_Xor W8) - Word8NotOp -> \args -> opTranslate args (MO_Not W8) - Word8SllOp -> \args -> opTranslate args (MO_Shl W8) - Word8SrlOp -> \args -> opTranslate args (MO_U_Shr W8) - - Word8EqOp -> \args -> opTranslate args (MO_Eq W8) - Word8GeOp -> \args -> opTranslate args (MO_U_Ge W8) - Word8GtOp -> \args -> opTranslate args (MO_U_Gt W8) - Word8LeOp -> \args -> opTranslate args (MO_U_Le W8) - Word8LtOp -> \args -> opTranslate args (MO_U_Lt W8) - Word8NeOp -> \args -> opTranslate args (MO_Ne W8) + Word8ToWordOp -> opTranslate (MO_UU_Conv W8 (wordWidth platform)) + WordToWord8Op -> opTranslate (MO_UU_Conv (wordWidth platform) W8) + Word8AddOp -> opTranslate (MO_Add W8) + Word8SubOp -> opTranslate (MO_Sub W8) + Word8MulOp -> opTranslate (MO_Mul W8) + Word8QuotOp -> opTranslate (MO_U_Quot W8) + Word8RemOp -> opTranslate (MO_U_Rem W8) + + Word8AndOp -> opTranslate (MO_And W8) + Word8OrOp -> opTranslate (MO_Or W8) + Word8XorOp -> opTranslate (MO_Xor W8) + Word8NotOp -> opTranslate (MO_Not W8) + Word8SllOp -> opTranslate (MO_Shl W8) + Word8SrlOp -> opTranslate (MO_U_Shr W8) + + Word8EqOp -> opTranslate (MO_Eq W8) + Word8GeOp -> opTranslate (MO_U_Ge W8) + Word8GtOp -> opTranslate (MO_U_Gt W8) + Word8LeOp -> opTranslate (MO_U_Le W8) + Word8LtOp -> opTranslate (MO_U_Lt W8) + Word8NeOp -> opTranslate (MO_Ne W8) -- Int16# signed ops - Int16ToIntOp -> \args -> opTranslate args (MO_SS_Conv W16 (wordWidth platform)) - IntToInt16Op -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W16) - Int16NegOp -> \args -> opTranslate args (MO_S_Neg W16) - Int16AddOp -> \args -> opTranslate args (MO_Add W16) - Int16SubOp -> \args -> opTranslate args (MO_Sub W16) - Int16MulOp -> \args -> opTranslate args (MO_Mul W16) - Int16QuotOp -> \args -> opTranslate args (MO_S_Quot W16) - Int16RemOp -> \args -> opTranslate args (MO_S_Rem W16) - - Int16SllOp -> \args -> opTranslate args (MO_Shl W16) - Int16SraOp -> \args -> opTranslate args (MO_S_Shr W16) - Int16SrlOp -> \args -> opTranslate args (MO_U_Shr W16) - - Int16EqOp -> \args -> opTranslate args (MO_Eq W16) - Int16GeOp -> \args -> opTranslate args (MO_S_Ge W16) - Int16GtOp -> \args -> opTranslate args (MO_S_Gt W16) - Int16LeOp -> \args -> opTranslate args (MO_S_Le W16) - Int16LtOp -> \args -> opTranslate args (MO_S_Lt W16) - Int16NeOp -> \args -> opTranslate args (MO_Ne W16) + Int16ToIntOp -> opTranslate (MO_SS_Conv W16 (wordWidth platform)) + IntToInt16Op -> opTranslate (MO_SS_Conv (wordWidth platform) W16) + Int16NegOp -> opTranslate (MO_S_Neg W16) + Int16AddOp -> opTranslate (MO_Add W16) + Int16SubOp -> opTranslate (MO_Sub W16) + Int16MulOp -> opTranslate (MO_Mul W16) + Int16QuotOp -> opTranslate (MO_S_Quot W16) + Int16RemOp -> opTranslate (MO_S_Rem W16) + + Int16SllOp -> opTranslate (MO_Shl W16) + Int16SraOp -> opTranslate (MO_S_Shr W16) + Int16SrlOp -> opTranslate (MO_U_Shr W16) + + Int16EqOp -> opTranslate (MO_Eq W16) + Int16GeOp -> opTranslate (MO_S_Ge W16) + Int16GtOp -> opTranslate (MO_S_Gt W16) + Int16LeOp -> opTranslate (MO_S_Le W16) + Int16LtOp -> opTranslate (MO_S_Lt W16) + Int16NeOp -> opTranslate (MO_Ne W16) -- Word16# unsigned ops - Word16ToWordOp -> \args -> opTranslate args (MO_UU_Conv W16 (wordWidth platform)) - WordToWord16Op -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W16) - Word16AddOp -> \args -> opTranslate args (MO_Add W16) - Word16SubOp -> \args -> opTranslate args (MO_Sub W16) - Word16MulOp -> \args -> opTranslate args (MO_Mul W16) - Word16QuotOp -> \args -> opTranslate args (MO_U_Quot W16) - Word16RemOp -> \args -> opTranslate args (MO_U_Rem W16) - - Word16AndOp -> \args -> opTranslate args (MO_And W16) - Word16OrOp -> \args -> opTranslate args (MO_Or W16) - Word16XorOp -> \args -> opTranslate args (MO_Xor W16) - Word16NotOp -> \args -> opTranslate args (MO_Not W16) - Word16SllOp -> \args -> opTranslate args (MO_Shl W16) - Word16SrlOp -> \args -> opTranslate args (MO_U_Shr W16) - - Word16EqOp -> \args -> opTranslate args (MO_Eq W16) - Word16GeOp -> \args -> opTranslate args (MO_U_Ge W16) - Word16GtOp -> \args -> opTranslate args (MO_U_Gt W16) - Word16LeOp -> \args -> opTranslate args (MO_U_Le W16) - Word16LtOp -> \args -> opTranslate args (MO_U_Lt W16) - Word16NeOp -> \args -> opTranslate args (MO_Ne W16) + Word16ToWordOp -> opTranslate (MO_UU_Conv W16 (wordWidth platform)) + WordToWord16Op -> opTranslate (MO_UU_Conv (wordWidth platform) W16) + Word16AddOp -> opTranslate (MO_Add W16) + Word16SubOp -> opTranslate (MO_Sub W16) + Word16MulOp -> opTranslate (MO_Mul W16) + Word16QuotOp -> opTranslate (MO_U_Quot W16) + Word16RemOp -> opTranslate (MO_U_Rem W16) + + Word16AndOp -> opTranslate (MO_And W16) + Word16OrOp -> opTranslate (MO_Or W16) + Word16XorOp -> opTranslate (MO_Xor W16) + Word16NotOp -> opTranslate (MO_Not W16) + Word16SllOp -> opTranslate (MO_Shl W16) + Word16SrlOp -> opTranslate (MO_U_Shr W16) + + Word16EqOp -> opTranslate (MO_Eq W16) + Word16GeOp -> opTranslate (MO_U_Ge W16) + Word16GtOp -> opTranslate (MO_U_Gt W16) + Word16LeOp -> opTranslate (MO_U_Le W16) + Word16LtOp -> opTranslate (MO_U_Lt W16) + Word16NeOp -> opTranslate (MO_Ne W16) -- Int32# signed ops - Int32ToIntOp -> \args -> opTranslate args (MO_SS_Conv W32 (wordWidth platform)) - IntToInt32Op -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W32) - Int32NegOp -> \args -> opTranslate args (MO_S_Neg W32) - Int32AddOp -> \args -> opTranslate args (MO_Add W32) - Int32SubOp -> \args -> opTranslate args (MO_Sub W32) - Int32MulOp -> \args -> opTranslate args (MO_Mul W32) - Int32QuotOp -> \args -> opTranslate args (MO_S_Quot W32) - Int32RemOp -> \args -> opTranslate args (MO_S_Rem W32) - - Int32SllOp -> \args -> opTranslate args (MO_Shl W32) - Int32SraOp -> \args -> opTranslate args (MO_S_Shr W32) - Int32SrlOp -> \args -> opTranslate args (MO_U_Shr W32) - - Int32EqOp -> \args -> opTranslate args (MO_Eq W32) - Int32GeOp -> \args -> opTranslate args (MO_S_Ge W32) - Int32GtOp -> \args -> opTranslate args (MO_S_Gt W32) - Int32LeOp -> \args -> opTranslate args (MO_S_Le W32) - Int32LtOp -> \args -> opTranslate args (MO_S_Lt W32) - Int32NeOp -> \args -> opTranslate args (MO_Ne W32) + Int32ToIntOp -> opTranslate (MO_SS_Conv W32 (wordWidth platform)) + IntToInt32Op -> opTranslate (MO_SS_Conv (wordWidth platform) W32) + Int32NegOp -> opTranslate (MO_S_Neg W32) + Int32AddOp -> opTranslate (MO_Add W32) + Int32SubOp -> opTranslate (MO_Sub W32) + Int32MulOp -> opTranslate (MO_Mul W32) + Int32QuotOp -> opTranslate (MO_S_Quot W32) + Int32RemOp -> opTranslate (MO_S_Rem W32) + + Int32SllOp -> opTranslate (MO_Shl W32) + Int32SraOp -> opTranslate (MO_S_Shr W32) + Int32SrlOp -> opTranslate (MO_U_Shr W32) + + Int32EqOp -> opTranslate (MO_Eq W32) + Int32GeOp -> opTranslate (MO_S_Ge W32) + Int32GtOp -> opTranslate (MO_S_Gt W32) + Int32LeOp -> opTranslate (MO_S_Le W32) + Int32LtOp -> opTranslate (MO_S_Lt W32) + Int32NeOp -> opTranslate (MO_Ne W32) -- Word32# unsigned ops - Word32ToWordOp -> \args -> opTranslate args (MO_UU_Conv W32 (wordWidth platform)) - WordToWord32Op -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W32) - Word32AddOp -> \args -> opTranslate args (MO_Add W32) - Word32SubOp -> \args -> opTranslate args (MO_Sub W32) - Word32MulOp -> \args -> opTranslate args (MO_Mul W32) - Word32QuotOp -> \args -> opTranslate args (MO_U_Quot W32) - Word32RemOp -> \args -> opTranslate args (MO_U_Rem W32) - - Word32AndOp -> \args -> opTranslate args (MO_And W32) - Word32OrOp -> \args -> opTranslate args (MO_Or W32) - Word32XorOp -> \args -> opTranslate args (MO_Xor W32) - Word32NotOp -> \args -> opTranslate args (MO_Not W32) - Word32SllOp -> \args -> opTranslate args (MO_Shl W32) - Word32SrlOp -> \args -> opTranslate args (MO_U_Shr W32) - - Word32EqOp -> \args -> opTranslate args (MO_Eq W32) - Word32GeOp -> \args -> opTranslate args (MO_U_Ge W32) - Word32GtOp -> \args -> opTranslate args (MO_U_Gt W32) - Word32LeOp -> \args -> opTranslate args (MO_U_Le W32) - Word32LtOp -> \args -> opTranslate args (MO_U_Lt W32) - Word32NeOp -> \args -> opTranslate args (MO_Ne W32) + Word32ToWordOp -> opTranslate (MO_UU_Conv W32 (wordWidth platform)) + WordToWord32Op -> opTranslate (MO_UU_Conv (wordWidth platform) W32) + Word32AddOp -> opTranslate (MO_Add W32) + Word32SubOp -> opTranslate (MO_Sub W32) + Word32MulOp -> opTranslate (MO_Mul W32) + Word32QuotOp -> opTranslate (MO_U_Quot W32) + Word32RemOp -> opTranslate (MO_U_Rem W32) + + Word32AndOp -> opTranslate (MO_And W32) + Word32OrOp -> opTranslate (MO_Or W32) + Word32XorOp -> opTranslate (MO_Xor W32) + Word32NotOp -> opTranslate (MO_Not W32) + Word32SllOp -> opTranslate (MO_Shl W32) + Word32SrlOp -> opTranslate (MO_U_Shr W32) + + Word32EqOp -> opTranslate (MO_Eq W32) + Word32GeOp -> opTranslate (MO_U_Ge W32) + Word32GtOp -> opTranslate (MO_U_Gt W32) + Word32LeOp -> opTranslate (MO_U_Le W32) + Word32LtOp -> opTranslate (MO_U_Lt W32) + Word32NeOp -> opTranslate (MO_Ne W32) -- Int64# signed ops - Int64ToIntOp -> \args -> opTranslate64 args (\w -> MO_SS_Conv w (wordWidth platform)) MO_I64_ToI - IntToInt64Op -> \args -> opTranslate64 args (\w -> MO_SS_Conv (wordWidth platform) w) MO_I64_FromI - Int64NegOp -> \args -> opTranslate64 args MO_S_Neg MO_x64_Neg - Int64AddOp -> \args -> opTranslate64 args MO_Add MO_x64_Add - Int64SubOp -> \args -> opTranslate64 args MO_Sub MO_x64_Sub - Int64MulOp -> \args -> opTranslate64 args MO_Mul MO_x64_Mul - Int64QuotOp -> \args -> opTranslate64 args MO_S_Quot MO_I64_Quot - Int64RemOp -> \args -> opTranslate64 args MO_S_Rem MO_I64_Rem - - Int64SllOp -> \args -> opTranslate64 args MO_Shl MO_x64_Shl - Int64SraOp -> \args -> opTranslate64 args MO_S_Shr MO_I64_Shr - Int64SrlOp -> \args -> opTranslate64 args MO_U_Shr MO_W64_Shr - - Int64EqOp -> \args -> opTranslate64 args MO_Eq MO_x64_Eq - Int64GeOp -> \args -> opTranslate64 args MO_S_Ge MO_I64_Ge - Int64GtOp -> \args -> opTranslate64 args MO_S_Gt MO_I64_Gt - Int64LeOp -> \args -> opTranslate64 args MO_S_Le MO_I64_Le - Int64LtOp -> \args -> opTranslate64 args MO_S_Lt MO_I64_Lt - Int64NeOp -> \args -> opTranslate64 args MO_Ne MO_x64_Ne + Int64ToIntOp -> opTranslate64 (MO_SS_Conv W64 (wordWidth platform)) MO_I64_ToI + IntToInt64Op -> opTranslate64 (MO_SS_Conv (wordWidth platform) W64) MO_I64_FromI + Int64NegOp -> opTranslate64 (MO_S_Neg W64) MO_x64_Neg + Int64AddOp -> opTranslate64 (MO_Add W64) MO_x64_Add + Int64SubOp -> opTranslate64 (MO_Sub W64) MO_x64_Sub + Int64MulOp -> opTranslate64 (MO_Mul W64) MO_x64_Mul + Int64QuotOp + | allowQuot64 -> opTranslate (MO_S_Quot W64) + | otherwise -> opCallish MO_I64_Quot + Int64RemOp + | allowQuot64 -> opTranslate (MO_S_Rem W64) + | otherwise -> opCallish MO_I64_Rem + + Int64SllOp -> opTranslate64 (MO_Shl W64) MO_x64_Shl + Int64SraOp -> opTranslate64 (MO_S_Shr W64) MO_I64_Shr + Int64SrlOp -> opTranslate64 (MO_U_Shr W64) MO_W64_Shr + + Int64EqOp -> opTranslate64 (MO_Eq W64) MO_x64_Eq + Int64GeOp -> opTranslate64 (MO_S_Ge W64) MO_I64_Ge + Int64GtOp -> opTranslate64 (MO_S_Gt W64) MO_I64_Gt + Int64LeOp -> opTranslate64 (MO_S_Le W64) MO_I64_Le + Int64LtOp -> opTranslate64 (MO_S_Lt W64) MO_I64_Lt + Int64NeOp -> opTranslate64 (MO_Ne W64) MO_x64_Ne -- Word64# unsigned ops - Word64ToWordOp -> \args -> opTranslate64 args (\w -> MO_UU_Conv w (wordWidth platform)) MO_W64_ToW - WordToWord64Op -> \args -> opTranslate64 args (\w -> MO_UU_Conv (wordWidth platform) w) MO_W64_FromW - Word64AddOp -> \args -> opTranslate64 args MO_Add MO_x64_Add - Word64SubOp -> \args -> opTranslate64 args MO_Sub MO_x64_Sub - Word64MulOp -> \args -> opTranslate64 args MO_Mul MO_x64_Mul - Word64QuotOp -> \args -> opTranslate64 args MO_U_Quot MO_W64_Quot - Word64RemOp -> \args -> opTranslate64 args MO_U_Rem MO_W64_Rem - - Word64AndOp -> \args -> opTranslate64 args MO_And MO_x64_And - Word64OrOp -> \args -> opTranslate64 args MO_Or MO_x64_Or - Word64XorOp -> \args -> opTranslate64 args MO_Xor MO_x64_Xor - Word64NotOp -> \args -> opTranslate64 args MO_Not MO_x64_Not - Word64SllOp -> \args -> opTranslate64 args MO_Shl MO_x64_Shl - Word64SrlOp -> \args -> opTranslate64 args MO_U_Shr MO_W64_Shr - - Word64EqOp -> \args -> opTranslate64 args MO_Eq MO_x64_Eq - Word64GeOp -> \args -> opTranslate64 args MO_U_Ge MO_W64_Ge - Word64GtOp -> \args -> opTranslate64 args MO_U_Gt MO_W64_Gt - Word64LeOp -> \args -> opTranslate64 args MO_U_Le MO_W64_Le - Word64LtOp -> \args -> opTranslate64 args MO_U_Lt MO_W64_Lt - Word64NeOp -> \args -> opTranslate64 args MO_Ne MO_x64_Ne + Word64ToWordOp -> opTranslate64 (MO_UU_Conv W64 (wordWidth platform)) MO_W64_ToW + WordToWord64Op -> opTranslate64 (MO_UU_Conv (wordWidth platform) W64) MO_W64_FromW + Word64AddOp -> opTranslate64 (MO_Add W64) MO_x64_Add + Word64SubOp -> opTranslate64 (MO_Sub W64) MO_x64_Sub + Word64MulOp -> opTranslate64 (MO_Mul W64) MO_x64_Mul + Word64QuotOp + | allowQuot64 -> opTranslate (MO_U_Quot W64) + | otherwise -> opCallish MO_W64_Quot + Word64RemOp + | allowQuot64 -> opTranslate (MO_U_Rem W64) + | otherwise -> opCallish MO_W64_Rem + + Word64AndOp -> opTranslate64 (MO_And W64) MO_x64_And + Word64OrOp -> opTranslate64 (MO_Or W64) MO_x64_Or + Word64XorOp -> opTranslate64 (MO_Xor W64) MO_x64_Xor + Word64NotOp -> opTranslate64 (MO_Not W64) MO_x64_Not + Word64SllOp -> opTranslate64 (MO_Shl W64) MO_x64_Shl + Word64SrlOp -> opTranslate64 (MO_U_Shr W64) MO_W64_Shr + + Word64EqOp -> opTranslate64 (MO_Eq W64) MO_x64_Eq + Word64GeOp -> opTranslate64 (MO_U_Ge W64) MO_W64_Ge + Word64GtOp -> opTranslate64 (MO_U_Gt W64) MO_W64_Gt + Word64LeOp -> opTranslate64 (MO_U_Le W64) MO_W64_Le + Word64LtOp -> opTranslate64 (MO_U_Lt W64) MO_W64_Lt + Word64NeOp -> opTranslate64 (MO_Ne W64) MO_x64_Ne -- Char# ops - CharEqOp -> \args -> opTranslate args (MO_Eq (wordWidth platform)) - CharNeOp -> \args -> opTranslate args (MO_Ne (wordWidth platform)) - CharGeOp -> \args -> opTranslate args (MO_U_Ge (wordWidth platform)) - CharLeOp -> \args -> opTranslate args (MO_U_Le (wordWidth platform)) - CharGtOp -> \args -> opTranslate args (MO_U_Gt (wordWidth platform)) - CharLtOp -> \args -> opTranslate args (MO_U_Lt (wordWidth platform)) + CharEqOp -> opTranslate (MO_Eq (wordWidth platform)) + CharNeOp -> opTranslate (MO_Ne (wordWidth platform)) + CharGeOp -> opTranslate (MO_U_Ge (wordWidth platform)) + CharLeOp -> opTranslate (MO_U_Le (wordWidth platform)) + CharGtOp -> opTranslate (MO_U_Gt (wordWidth platform)) + CharLtOp -> opTranslate (MO_U_Lt (wordWidth platform)) -- Double ops - DoubleEqOp -> \args -> opTranslate args (MO_F_Eq W64) - DoubleNeOp -> \args -> opTranslate args (MO_F_Ne W64) - DoubleGeOp -> \args -> opTranslate args (MO_F_Ge W64) - DoubleLeOp -> \args -> opTranslate args (MO_F_Le W64) - DoubleGtOp -> \args -> opTranslate args (MO_F_Gt W64) - DoubleLtOp -> \args -> opTranslate args (MO_F_Lt W64) + DoubleEqOp -> opTranslate (MO_F_Eq W64) + DoubleNeOp -> opTranslate (MO_F_Ne W64) + DoubleGeOp -> opTranslate (MO_F_Ge W64) + DoubleLeOp -> opTranslate (MO_F_Le W64) + DoubleGtOp -> opTranslate (MO_F_Gt W64) + DoubleLtOp -> opTranslate (MO_F_Lt W64) - DoubleAddOp -> \args -> opTranslate args (MO_F_Add W64) - DoubleSubOp -> \args -> opTranslate args (MO_F_Sub W64) - DoubleMulOp -> \args -> opTranslate args (MO_F_Mul W64) - DoubleDivOp -> \args -> opTranslate args (MO_F_Quot W64) - DoubleNegOp -> \args -> opTranslate args (MO_F_Neg W64) + DoubleAddOp -> opTranslate (MO_F_Add W64) + DoubleSubOp -> opTranslate (MO_F_Sub W64) + DoubleMulOp -> opTranslate (MO_F_Mul W64) + DoubleDivOp -> opTranslate (MO_F_Quot W64) + DoubleNegOp -> opTranslate (MO_F_Neg W64) DoubleFMAdd -> fmaOp FMAdd W64 DoubleFMSub -> fmaOp FMSub W64 @@ -1497,18 +1505,18 @@ emitPrimOp cfg primop = -- Float ops - FloatEqOp -> \args -> opTranslate args (MO_F_Eq W32) - FloatNeOp -> \args -> opTranslate args (MO_F_Ne W32) - FloatGeOp -> \args -> opTranslate args (MO_F_Ge W32) - FloatLeOp -> \args -> opTranslate args (MO_F_Le W32) - FloatGtOp -> \args -> opTranslate args (MO_F_Gt W32) - FloatLtOp -> \args -> opTranslate args (MO_F_Lt W32) + FloatEqOp -> opTranslate (MO_F_Eq W32) + FloatNeOp -> opTranslate (MO_F_Ne W32) + FloatGeOp -> opTranslate (MO_F_Ge W32) + FloatLeOp -> opTranslate (MO_F_Le W32) + FloatGtOp -> opTranslate (MO_F_Gt W32) + FloatLtOp -> opTranslate (MO_F_Lt W32) - FloatAddOp -> \args -> opTranslate args (MO_F_Add W32) - FloatSubOp -> \args -> opTranslate args (MO_F_Sub W32) - FloatMulOp -> \args -> opTranslate args (MO_F_Mul W32) - FloatDivOp -> \args -> opTranslate args (MO_F_Quot W32) - FloatNegOp -> \args -> opTranslate args (MO_F_Neg W32) + FloatAddOp -> opTranslate (MO_F_Add W32) + FloatSubOp -> opTranslate (MO_F_Sub W32) + FloatMulOp -> opTranslate (MO_F_Mul W32) + FloatDivOp -> opTranslate (MO_F_Quot W32) + FloatNegOp -> opTranslate (MO_F_Neg W32) FloatFMAdd -> fmaOp FMAdd W32 FloatFMSub -> fmaOp FMSub W32 @@ -1517,126 +1525,122 @@ emitPrimOp cfg primop = -- Vector ops - (VecAddOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Add n w) - (VecSubOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Sub n w) - (VecMulOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Mul n w) - (VecDivOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Quot n w) + (VecAddOp FloatVec n w) -> opTranslate (MO_VF_Add n w) + (VecSubOp FloatVec n w) -> opTranslate (MO_VF_Sub n w) + (VecMulOp FloatVec n w) -> opTranslate (MO_VF_Mul n w) + (VecDivOp FloatVec n w) -> opTranslate (MO_VF_Quot n w) (VecQuotOp FloatVec _ _) -> \_ -> panic "unsupported primop" (VecRemOp FloatVec _ _) -> \_ -> panic "unsupported primop" - (VecNegOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Neg n w) + (VecNegOp FloatVec n w) -> opTranslate (MO_VF_Neg n w) - (VecAddOp IntVec n w) -> \args -> opTranslate args (MO_V_Add n w) - (VecSubOp IntVec n w) -> \args -> opTranslate args (MO_V_Sub n w) - (VecMulOp IntVec n w) -> \args -> opTranslate args (MO_V_Mul n w) + (VecAddOp IntVec n w) -> opTranslate (MO_V_Add n w) + (VecSubOp IntVec n w) -> opTranslate (MO_V_Sub n w) + (VecMulOp IntVec n w) -> opTranslate (MO_V_Mul n w) (VecDivOp IntVec _ _) -> \_ -> panic "unsupported primop" - (VecQuotOp IntVec n w) -> \args -> opTranslate args (MO_VS_Quot n w) - (VecRemOp IntVec n w) -> \args -> opTranslate args (MO_VS_Rem n w) - (VecNegOp IntVec n w) -> \args -> opTranslate args (MO_VS_Neg n w) + (VecQuotOp IntVec n w) -> opTranslate (MO_VS_Quot n w) + (VecRemOp IntVec n w) -> opTranslate (MO_VS_Rem n w) + (VecNegOp IntVec n w) -> opTranslate (MO_VS_Neg n w) - (VecAddOp WordVec n w) -> \args -> opTranslate args (MO_V_Add n w) - (VecSubOp WordVec n w) -> \args -> opTranslate args (MO_V_Sub n w) - (VecMulOp WordVec n w) -> \args -> opTranslate args (MO_V_Mul n w) + (VecAddOp WordVec n w) -> opTranslate (MO_V_Add n w) + (VecSubOp WordVec n w) -> opTranslate (MO_V_Sub n w) + (VecMulOp WordVec n w) -> opTranslate (MO_V_Mul n w) (VecDivOp WordVec _ _) -> \_ -> panic "unsupported primop" - (VecQuotOp WordVec n w) -> \args -> opTranslate args (MO_VU_Quot n w) - (VecRemOp WordVec n w) -> \args -> opTranslate args (MO_VU_Rem n w) + (VecQuotOp WordVec n w) -> opTranslate (MO_VU_Quot n w) + (VecRemOp WordVec n w) -> opTranslate (MO_VU_Rem n w) (VecNegOp WordVec _ _) -> \_ -> panic "unsupported primop" -- Conversions - IntToDoubleOp -> \args -> opTranslate args (MO_SF_Round (wordWidth platform) W64) - DoubleToIntOp -> \args -> opTranslate args (MO_FS_Truncate W64 (wordWidth platform)) + IntToDoubleOp -> opTranslate (MO_SF_Round (wordWidth platform) W64) + DoubleToIntOp -> opTranslate (MO_FS_Truncate W64 (wordWidth platform)) - IntToFloatOp -> \args -> opTranslate args (MO_SF_Round (wordWidth platform) W32) - FloatToIntOp -> \args -> opTranslate args (MO_FS_Truncate W32 (wordWidth platform)) + IntToFloatOp -> opTranslate (MO_SF_Round (wordWidth platform) W32) + FloatToIntOp -> opTranslate (MO_FS_Truncate W32 (wordWidth platform)) - FloatToDoubleOp -> \args -> opTranslate args (MO_FF_Conv W32 W64) - DoubleToFloatOp -> \args -> opTranslate args (MO_FF_Conv W64 W32) + FloatToDoubleOp -> opTranslate (MO_FF_Conv W32 W64) + DoubleToFloatOp -> opTranslate (MO_FF_Conv W64 W32) - CastFloatToWord32Op -> - \args -> translateBitcasts (MO_FW_Bitcast W32) args - CastWord32ToFloatOp -> - \args -> translateBitcasts (MO_WF_Bitcast W32) args - CastDoubleToWord64Op -> - \args -> translateBitcasts (MO_FW_Bitcast W64) args - CastWord64ToDoubleOp -> - \args -> translateBitcasts (MO_WF_Bitcast W64) args + CastFloatToWord32Op -> translateBitcasts (MO_FW_Bitcast W32) + CastWord32ToFloatOp -> translateBitcasts (MO_WF_Bitcast W32) + CastDoubleToWord64Op -> translateBitcasts (MO_FW_Bitcast W64) + CastWord64ToDoubleOp -> translateBitcasts (MO_WF_Bitcast W64) - IntQuotRemOp -> \args -> opCallishHandledLater args $ + IntQuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem (wordWidth platform)) else Right (genericIntQuotRemOp (wordWidth platform)) - Int8QuotRemOp -> \args -> opCallishHandledLater args $ + Int8QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem W8) else Right (genericIntQuotRemOp W8) - Int16QuotRemOp -> \args -> opCallishHandledLater args $ + Int16QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem W16) else Right (genericIntQuotRemOp W16) - Int32QuotRemOp -> \args -> opCallishHandledLater args $ + Int32QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem W32) else Right (genericIntQuotRemOp W32) - WordQuotRemOp -> \args -> opCallishHandledLater args $ + WordQuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem (wordWidth platform)) else Right (genericWordQuotRemOp (wordWidth platform)) - WordQuotRem2Op -> \args -> opCallishHandledLater args $ + WordQuotRem2Op -> opCallishHandledLater $ if allowQuotRem2 then Left (MO_U_QuotRem2 (wordWidth platform)) else Right (genericWordQuotRem2Op platform) - Word8QuotRemOp -> \args -> opCallishHandledLater args $ + Word8QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem W8) else Right (genericWordQuotRemOp W8) - Word16QuotRemOp -> \args -> opCallishHandledLater args $ + Word16QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem W16) else Right (genericWordQuotRemOp W16) - Word32QuotRemOp -> \args -> opCallishHandledLater args $ + Word32QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem W32) else Right (genericWordQuotRemOp W32) - WordAdd2Op -> \args -> opCallishHandledLater args $ + WordAdd2Op -> opCallishHandledLater $ if allowExtAdd then Left (MO_Add2 (wordWidth platform)) else Right genericWordAdd2Op - WordAddCOp -> \args -> opCallishHandledLater args $ + WordAddCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_AddWordC (wordWidth platform)) else Right genericWordAddCOp - WordSubCOp -> \args -> opCallishHandledLater args $ + WordSubCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_SubWordC (wordWidth platform)) else Right genericWordSubCOp - IntAddCOp -> \args -> opCallishHandledLater args $ + IntAddCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_AddIntC (wordWidth platform)) else Right genericIntAddCOp - IntSubCOp -> \args -> opCallishHandledLater args $ + IntSubCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_SubIntC (wordWidth platform)) else Right genericIntSubCOp - WordMul2Op -> \args -> opCallishHandledLater args $ + WordMul2Op -> opCallishHandledLater $ if allowWord2Mul then Left (MO_U_Mul2 (wordWidth platform)) else Right genericWordMul2Op - IntMul2Op -> \args -> opCallishHandledLater args $ + IntMul2Op -> opCallishHandledLater $ if allowInt2Mul then Left (MO_S_Mul2 (wordWidth platform)) else Right genericIntMul2Op @@ -1775,42 +1779,33 @@ emitPrimOp cfg primop = -- These primops are implemented by CallishMachOps, because they sometimes -- turn into foreign calls depending on the backend. - opCallish :: [CmmExpr] -> CallishMachOp -> PrimopCmmEmit - opCallish args prim = opIntoRegs $ \[res] -> emitPrimCall [res] prim args + opCallish :: CallishMachOp -> [CmmExpr] -> PrimopCmmEmit + opCallish prim args = opIntoRegs $ \[res] -> emitPrimCall [res] prim args - opTranslate :: [CmmExpr] -> MachOp -> PrimopCmmEmit - opTranslate args mop = opIntoRegs $ \[res] -> do + opTranslate :: MachOp -> [CmmExpr] -> PrimopCmmEmit + opTranslate mop args = opIntoRegs $ \[res] -> do let stmt = mkAssign (CmmLocal res) (CmmMachOp mop args) emit stmt - isQuottishOp :: CallishMachOp -> Bool - isQuottishOp MO_I64_Quot = True - isQuottishOp MO_I64_Rem = True - isQuottishOp MO_W64_Quot = True - isQuottishOp MO_W64_Rem = True - isQuottishOp _ = False - opTranslate64 - :: [CmmExpr] - -> (Width -> MachOp) + :: MachOp -> CallishMachOp + -> [CmmExpr] -> PrimopCmmEmit - opTranslate64 args mkMop callish = - case platformWordSize platform of - -- LLVM and C `can handle larger than native size arithmetic natively. - _ | not (isQuottishOp callish), stgToCmmAllowBigArith cfg -> opTranslate args $ mkMop W64 - | isQuottishOp callish, stgToCmmAllowBigQuot cfg -> opTranslate args $ mkMop W64 - PW4 -> opCallish args callish - PW8 -> opTranslate args $ mkMop W64 + opTranslate64 mop callish + | allowArith64 = opTranslate mop + | otherwise = opCallish callish + -- backends not supporting 64-bit arithmetic primops: use callish machine + -- ops -- Basically a "manual" case, rather than one of the common repetitive forms -- above. The results are a parameter to the returned function so we know the -- choice of variant never depends on them. opCallishHandledLater - :: [CmmExpr] - -> Either CallishMachOp GenericOp + :: Either CallishMachOp GenericOp + -> [CmmExpr] -> PrimopCmmEmit - opCallishHandledLater args callOrNot = opIntoRegs $ \res0 -> case callOrNot of + opCallishHandledLater callOrNot args = opIntoRegs $ \res0 -> case callOrNot of Left op -> emit $ mkUnsafeCall (PrimTarget op) res0 args Right gen -> gen res0 args @@ -1838,21 +1833,23 @@ emitPrimOp cfg primop = allowExtAdd = stgToCmmAllowExtendedAddSubInstrs cfg allowInt2Mul = stgToCmmAllowIntMul2Instr cfg allowWord2Mul = stgToCmmAllowWordMul2Instr cfg + allowArith64 = stgToCmmAllowArith64 cfg + allowQuot64 = stgToCmmAllowQuot64 cfg -- a bit of a hack, for certain code generaters, e.g. PPC, and i386 we -- continue to use the cmm versions of these functions instead of inline -- assembly. Tracked in #24841. ppc = isPPC $ platformArch platform i386 = target32Bit platform - translateBitcasts mop args | ppc || i386 = alwaysExternal args - | otherwise = opTranslate args mop + translateBitcasts mop | ppc || i386 = alwaysExternal + | otherwise = opTranslate mop allowFMA = stgToCmmAllowFMAInstr cfg fmaOp :: FMASign -> Width -> [CmmActual] -> PrimopCmmEmit fmaOp signs w args@[arg_x, arg_y, arg_z] | allowFMA signs - = opTranslate args (MO_FMA signs w) + = opTranslate (MO_FMA signs w) args | otherwise = case signs of ===================================== compiler/Language/Haskell/Syntax/Pat.hs ===================================== @@ -57,62 +57,73 @@ import Data.List.NonEmpty (NonEmpty) type LPat p = XRec p (Pat p) -- | Pattern --- --- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang' - --- For details on above see Note [exact print annotations] in GHC.Parser.Annotation data Pat p = ------------ Simple patterns --------------- - WildPat (XWildPat p) -- ^ Wildcard Pattern - -- The sole reason for a type on a WildPat is to - -- support hsPatType :: Pat Id -> Type - - -- AZ:TODO above comment needs to be updated + WildPat (XWildPat p) + -- ^ Wildcard Pattern (@_@) | VarPat (XVarPat p) - (LIdP p) -- ^ Variable Pattern + (LIdP p) + -- ^ Variable Pattern, e.g. @x@ - -- See Note [Located RdrNames] in GHC.Hs.Expr + -- See Note [Located RdrNames] in GHC.Hs.Expr | LazyPat (XLazyPat p) - (LPat p) -- ^ Lazy Pattern - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnTilde' + (LPat p) + -- ^ Lazy Pattern, e.g. @~x@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnTilde' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | AsPat (XAsPat p) (LIdP p) - (LPat p) -- ^ As pattern - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnAt' + (LPat p) + -- ^ As pattern, e.g. @x\@pat@ + -- + -- - Location of '@' is captured by 'GHC.Parser.Annotation.EpToken' @"\@"@ -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | ParPat (XParPat p) - (LPat p) -- ^ Parenthesised pattern - -- See Note [Parens in HsSyn] in GHC.Hs.Expr - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'('@, - -- 'GHC.Parser.Annotation.AnnClose' @')'@ + (LPat p) + -- ^ Parenthesised pattern, e.g. @(x)@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : + -- 'GHC.Parser.Annotation.AnnOpen' @'('@, + -- 'GHC.Parser.Annotation.AnnClose' @')'@ + + -- See Note [Parens in HsSyn] in GHC.Hs.Expr -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | BangPat (XBangPat p) - (LPat p) -- ^ Bang pattern - -- ^ - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang' + (LPat p) + -- ^ Bang pattern, e.g. @!x@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation ------------ Lists, tuples, arrays --------------- | ListPat (XListPat p) [LPat p] + -- ^ Syntactic List, e.g. @[x]@ or @[x,y]@ (but not @[]@ nor @(x:xs)@ which are represented using 'ConPat') + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : + -- 'GHC.Parser.Annotation.AnnOpen' @'['@, + -- 'GHC.Parser.Annotation.AnnClose' @']'@ - -- ^ Syntactic List + -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation + + | -- | Tuple pattern, e.g. @(x, y)@ -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'['@, - -- 'GHC.Parser.Annotation.AnnClose' @']'@ + -- - 'GHC.Parser.Annotation.AnnKeywordId' : + -- 'GHC.Parser.Annotation.AnnOpen' @'('@ or @'(#'@, + -- 'GHC.Parser.Annotation.AnnClose' @')'@ or @'#)'@ -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation + TuplePat (XTuplePat p) -- ^ After typechecking, holds the types of the tuple components + [LPat p] -- ^ Tuple sub-patterns + Boxity -- ^ UnitPat is TuplePat [] - | TuplePat (XTuplePat p) - -- after typechecking, holds the types of the tuple components - [LPat p] -- Tuple sub-patterns - Boxity -- UnitPat is TuplePat [] -- You might think that the post typechecking Type was redundant, -- because we can get the pattern type by getting the types of the -- sub-patterns. @@ -129,11 +140,6 @@ data Pat p -- of the tuple is of type 'a' not Int. See selectMatchVar -- (June 14: I'm not sure this comment is right; the sub-patterns -- will be wrapped in CoPats, no?) - -- ^ Tuple sub-patterns - -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : - -- 'GHC.Parser.Annotation.AnnOpen' @'('@ or @'(#'@, - -- 'GHC.Parser.Annotation.AnnClose' @')'@ or @'#)'@ | OrPat (XOrPat p) (NonEmpty (LPat p)) @@ -143,7 +149,8 @@ data Pat p (LPat p) -- Sum sub-pattern ConTag -- Alternative (one-based) SumWidth -- Arity (INVARIANT: ≥ 2) - -- ^ Anonymous sum pattern + + -- ^ Anonymous sum pattern, e.g. @(# x | #)@. Used by @-XUnboxedSums@ -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : -- 'GHC.Parser.Annotation.AnnOpen' @'(#'@, @@ -157,35 +164,40 @@ data Pat p pat_con :: XRec p (ConLikeP p), pat_args :: HsConPatDetails p } - -- ^ Constructor Pattern + -- ^ Constructor Pattern, e.g. @[]@ or @Nothing@ ------------ View patterns --------------- - -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnRarrow' - -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | ViewPat (XViewPat p) (LHsExpr p) (LPat p) - -- ^ View Pattern + -- ^ View Pattern, e.g. @someFun -> pat at . Used by @-XViewPatterns@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnRarrow' + + -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation ------------ Pattern splices --------------- - -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen' @'$('@ - -- 'GHC.Parser.Annotation.AnnClose' @')'@ - -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | SplicePat (XSplicePat p) - (HsUntypedSplice p) -- ^ Splice Pattern (Includes quasi-quotes) + (HsUntypedSplice p) + -- ^ Splice Pattern (Includes quasi-quotes @$(...)@) + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId': + -- 'GHC.Parser.Annotation.AnnOpen' @'$('@ + -- 'GHC.Parser.Annotation.AnnClose' @')'@ + + -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation ------------ Literal and n+k patterns --------------- | LitPat (XLitPat p) - (HsLit p) -- ^ Literal Pattern - -- Used for *non-overloaded* literal patterns: - -- Int#, Char#, Int, Char, String, etc. - - | NPat -- Natural Pattern - -- Used for all overloaded literals, - -- including overloaded strings with -XOverloadedStrings - (XNPat p) -- Overall type of pattern. Might be + (HsLit p) + -- ^ Literal Pattern + -- + -- Used for __non-overloaded__ literal patterns: + -- Int#, Char#, Int, Char, String, etc. + + | NPat (XNPat p) -- Overall type of pattern. Might be -- different than the literal's type -- if (==) or negate changes the type (XRec p (HsOverLit p)) -- ALWAYS positive @@ -194,7 +206,8 @@ data Pat p -- otherwise (SyntaxExpr p) -- Equality checker, of type t->t->Bool - -- ^ Natural Pattern + -- ^ Natural Pattern, used for all overloaded literals, including overloaded Strings + -- with @-XOverloadedStrings@ -- -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnVal' @'+'@ @@ -208,30 +221,35 @@ data Pat p (SyntaxExpr p) -- (>=) function, of type t1->t2->Bool (SyntaxExpr p) -- Name of '-' (see GHC.Rename.Env.lookupSyntax) - -- ^ n+k pattern + -- ^ n+k pattern, e.g. @n+1@, enabled by @-XNPlusKPatterns@ extension ------------ Pattern type signatures --------------- - -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' - -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | SigPat (XSigPat p) -- After typechecker: Type (LPat p) -- Pattern with a type signature (HsPatSigType (NoGhcTc p)) -- Signature can bind both -- kind and type vars - -- ^ Pattern with a type signature + -- ^ Pattern with a type signature, e.g. @x :: Int@ + -- + -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' + + -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation - -- Embed the syntax of types into patterns. - -- Used with RequiredTypeArguments, e.g. fn (type t) = rhs - | EmbTyPat (XEmbTyPat p) + | -- | Embed the syntax of types into patterns. + -- Used with @-XRequiredTypeArguments@, e.g. @fn (type t) = rhs@ + EmbTyPat (XEmbTyPat p) (HsTyPat (NoGhcTc p)) - -- See Note [Invisible binders in functions] in GHC.Hs.Pat | InvisPat (XInvisPat p) (HsTyPat (NoGhcTc p)) + -- ^ Type abstraction which brings into scope type variables associated with invisible forall. Used by @-XTypeAbstractions at . + -- + -- The location of @\@@ is captured by 'GHC.Parser.Annotation.EpToken' @"\@"@ + + -- See Note [Invisible binders in functions] in GHC.Hs.Pat - -- Extension point; see Note [Trees That Grow] in Language.Haskell.Syntax.Extension - | XPat - !(XXPat p) + | -- | TTG Extension point; see Note [Trees That Grow] in Language.Haskell.Syntax.Extension + XPat !(XXPat p) type family ConLikeP x @@ -311,7 +329,7 @@ type HsRecUpdField p q = HsFieldBind (LAmbiguousFieldOcc p) (LHsExpr q) -- | Haskell Field Binding -- --- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnEqual', +-- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnEqual' -- -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation data HsFieldBind lhs rhs = HsFieldBind { ===================================== libraries/base/tests/all.T ===================================== @@ -189,6 +189,7 @@ test('CatEntail', normal, compile, ['']) # When running with WAY=ghci and profiled ways, T7653 uses a lot of memory. test('T7653', [when(opsys('mingw32'), skip), + when(arch('wasm32'), run_timeout_multiplier(5)), omit_ways(prof_ways + ghci_ways)], compile_and_run, ['']) test('T7787', normal, compile_and_run, ['']) ===================================== rts/Inlines.c ===================================== @@ -1,6 +1,7 @@ -// all functions declared with EXTERN_INLINE in the header files get -// compiled for real here, just in case the definition was not inlined -// at some call site: +// All functions declared with EXTERN_INLINE in the header files get +// compiled for real here. Some of them are called by Cmm (e.g. +// recordClosureMutated) and therefore the real thing needs to reside +// in Inlines.o for Cmm ccall to work. #define KEEP_INLINES #include "rts/PosixSource.h" #include "Rts.h" ===================================== rts/include/Stg.h ===================================== @@ -114,57 +114,19 @@ * 'Portable' inlining: * INLINE_HEADER is for inline functions in header files (macros) * STATIC_INLINE is for inline functions in source files - * EXTERN_INLINE is for functions that we want to inline sometimes - * (we also compile a static version of the function; see Inlines.c) + * EXTERN_INLINE is for functions that may be called in Cmm + * (we also compile a static version of an EXTERN_INLINE function; see Inlines.c) */ -// We generally assume C99 semantics albeit these two definitions work fine even -// when gnu90 semantics are active (i.e. when __GNUC_GNU_INLINE__ is defined or -// when a GCC older than 4.2 is used) -// -// The problem, however, is with 'extern inline' whose semantics significantly -// differs between gnu90 and C99 #define INLINE_HEADER static inline #define STATIC_INLINE static inline -// Figure out whether `__attributes__((gnu_inline))` is needed -// to force gnu90-style 'external inline' semantics. -#if defined(FORCE_GNU_INLINE) -// disable auto-detection since HAVE_GNU_INLINE has been defined externally -#elif defined(__GNUC_GNU_INLINE__) && __GNUC__ == 4 && __GNUC_MINOR__ == 2 -// GCC 4.2.x didn't properly support C99 inline semantics (GCC 4.3 was the first -// release to properly support C99 inline semantics), and therefore warned when -// using 'extern inline' while in C99 mode unless `__attributes__((gnu_inline))` -// was explicitly set. -# define FORCE_GNU_INLINE 1 -#endif - -#if defined(FORCE_GNU_INLINE) -// Force compiler into gnu90 semantics -# if defined(KEEP_INLINES) -# define EXTERN_INLINE inline __attribute__((gnu_inline)) -# else -# define EXTERN_INLINE extern inline __attribute__((gnu_inline)) -# endif -#elif defined(__GNUC_GNU_INLINE__) -// we're currently in gnu90 inline mode by default and -// __attribute__((gnu_inline)) may not be supported, so better leave it off -# if defined(KEEP_INLINES) -# define EXTERN_INLINE inline -# else -# define EXTERN_INLINE extern inline -# endif -#else -// Assume C99 semantics (yes, this curiously results in swapped definitions!) -// This is the preferred branch, and at some point we may drop support for -// compilers not supporting C99 semantics altogether. +// See comment in rts/Inlines.c for explanation. # if defined(KEEP_INLINES) # define EXTERN_INLINE extern inline # else -# define EXTERN_INLINE inline +# define EXTERN_INLINE static inline # endif -#endif - /* * GCC attributes ===================================== testsuite/tests/driver/objc/all.T ===================================== @@ -1,11 +1,13 @@ test('objc-hi', [ unless(opsys('darwin'), skip), + when(config.target_wrapper is not None, skip), objc_src, expect_fail_for(['ghci']) ], compile_and_run, ['-framework Foundation']) test('objcxx-hi', [ unless(opsys('darwin'), skip), + when(config.target_wrapper is not None, skip), objcxx_src, expect_fail_for(['ghci']) ], compile_and_run, ['-framework Foundation -lc++']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f082ae246c25f6e103e67e6ba4df8e36a15fd2c3...5ef6cbeb5452ac41d33b0eef227fb1bd5b9f9244 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f082ae246c25f6e103e67e6ba4df8e36a15fd2c3...5ef6cbeb5452ac41d33b0eef227fb1bd5b9f9244 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 08:23:25 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Sat, 08 Jun 2024 04:23:25 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] improve RegClass Message-ID: <666414fd21544_3d87d34e99428897b9@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 3bbc4fcd by sheaf at 2024-06-08T10:22:34+02:00 improve RegClass - - - - - 14 changed files: - compiler/GHC/CmmToAsm/AArch64/Regs.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/PPC/Regs.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs - compiler/GHC/CmmToAsm/Reg/Linear/PPC.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Regs.hs - compiler/GHC/Platform/Reg.hs - compiler/GHC/Platform/Reg/Class.hs Changes: ===================================== compiler/GHC/CmmToAsm/AArch64/Regs.hs ===================================== @@ -108,14 +108,12 @@ virtualRegSqueeze cls vr VirtualRegHi{} -> 1 _other -> 0 - RcDouble + RcFloatOrVector -> case vr of VirtualRegD{} -> 1 VirtualRegF{} -> 0 _other -> 0 - _other -> 0 - {-# INLINE realRegSqueeze #-} realRegSqueeze :: RegClass -> RealReg -> Int realRegSqueeze cls rr @@ -126,14 +124,12 @@ realRegSqueeze cls rr | regNo < 32 -> 1 -- first fp reg is 32 | otherwise -> 0 - RcDouble + RcFloatOrVector -> case rr of RealRegSingle regNo | regNo < 32 -> 0 | otherwise -> 1 - _other -> 0 - mkVirtualReg :: Unique -> Format -> VirtualReg mkVirtualReg u format | not (isFloatFormat format) = VirtualRegI u @@ -147,18 +143,18 @@ mkVirtualReg u format classOfRealReg :: RealReg -> RegClass classOfRealReg (RealRegSingle i) | i < 32 = RcInteger - | otherwise = RcDouble + | otherwise = RcFloatOrVector +-- SIMD NCG TODO: get rid of this function; +-- mkSpillInstr will receive the Format of what's stored in the register. fmtOfRealReg :: RealReg -> Format fmtOfRealReg real_reg = case classOfRealReg real_reg of - RcInteger -> II64 - RcDouble -> FF64 - RcFloat -> panic "No float regs on arm" + RcInteger -> II64 + RcFloatOrVector -> FF64 regDotColor :: RealReg -> SDoc regDotColor reg = case classOfRealReg reg of RcInteger -> text "blue" - RcFloat -> text "red" - RcDouble -> text "green" + RcFloatOrVector -> text "red" ===================================== compiler/GHC/CmmToAsm/PPC/CodeGen.hs ===================================== @@ -449,7 +449,7 @@ getRegister' _ platform (CmmMachOp (MO_SS_Conv W64 W32) [x]) getRegister' _ platform (CmmLoad mem pk _) | not (isWord64 pk) = do Amode addr addr_code <- getAmode D mem - let code dst = assert ((targetClassOfReg platform dst == RcDouble) == isFloatType pk) $ + let code dst = assert ((targetClassOfReg platform dst == RcFloatOrVector) == isFloatType pk) $ addr_code `snocOL` LD format dst addr return (Any format code) | not (target32Bit platform) = do ===================================== compiler/GHC/CmmToAsm/PPC/Instr.hs ===================================== @@ -562,7 +562,7 @@ mkSpillInstr config reg delta slot RcInteger -> case arch of ArchPPC -> II32 _ -> II64 - RcDouble -> FF64 + RcFloatOrVector -> FF64 _ -> panic "PPC.Instr.mkSpillInstr: no match" instr = case makeImmediate W32 True (off-delta) of Just _ -> ST @@ -587,7 +587,7 @@ mkLoadInstr config reg delta slot RcInteger -> case arch of ArchPPC -> II32 _ -> II64 - RcDouble -> FF64 + RcFloatOrVector -> FF64 _ -> panic "PPC.Instr.mkLoadInstr: no match" instr = case makeImmediate W32 True (off-delta) of Just _ -> LD ===================================== compiler/GHC/CmmToAsm/PPC/Regs.hs ===================================== @@ -83,14 +83,12 @@ virtualRegSqueeze cls vr VirtualRegHi{} -> 1 _other -> 0 - RcDouble + RcFloatOrVector -> case vr of VirtualRegD{} -> 1 VirtualRegF{} -> 0 _other -> 0 - _other -> 0 - {-# INLINE realRegSqueeze #-} realRegSqueeze :: RegClass -> RealReg -> Int realRegSqueeze cls rr @@ -102,15 +100,13 @@ realRegSqueeze cls rr | otherwise -> 0 - RcDouble + RcFloatOrVector -> case rr of RealRegSingle regNo | regNo < 32 -> 0 | otherwise -> 1 - _other -> 0 - mkVirtualReg :: Unique -> Format -> VirtualReg mkVirtualReg u format | not (isFloatFormat format) = VirtualRegI u @@ -124,8 +120,7 @@ regDotColor :: RealReg -> SDoc regDotColor reg = case classOfRealReg reg of RcInteger -> text "blue" - RcFloat -> text "red" - RcDouble -> text "green" + RcFloatOrVector -> text "red" @@ -235,8 +230,8 @@ allMachRegNos = [0..63] {-# INLINE classOfRealReg #-} classOfRealReg :: RealReg -> RegClass classOfRealReg (RealRegSingle i) - | i < 32 = RcInteger - | otherwise = RcDouble + | i < 32 = RcInteger + | otherwise = RcFloatOrVector showReg :: RegNo -> String showReg n ===================================== compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs ===================================== @@ -22,7 +22,7 @@ import GHC.Utils.Panic -- This gets hammered by scanGraph during register allocation, -- so needs to be fairly efficient. -- --- NOTE: This only works for architectures with just RcInteger and RcDouble +-- NOTE: This only works for architectures with just RcInteger and RcFloatOrVector -- (which are disjoint) ie. x86, x86_64 and ppc -- -- The number of allocatable regs is hard coded in here so we can do @@ -134,42 +134,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts excl = count3 < cALLOCATABLE_REGS_INTEGER -trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclusions - | let cALLOCATABLE_REGS_FLOAT - = (case platformArch platform of - -- On x86_64 and x86, Float and RcDouble - -- use the same registers, - -- so we only use RcDouble to represent the - -- register allocation problem on those types. - ArchX86 -> 0 - ArchX86_64 -> 0 - ArchPPC -> 0 - ArchPPC_64 _ -> 0 - ArchARM _ _ _ -> panic "trivColorable ArchARM" - -- we can in principle address all the float regs as - -- segments. So we could have 64 Float regs. Or - -- 128 Half regs, or even 256 Byte regs. - ArchAArch64 -> 0 - ArchAlpha -> panic "trivColorable ArchAlpha" - ArchMipseb -> panic "trivColorable ArchMipseb" - ArchMipsel -> panic "trivColorable ArchMipsel" - ArchS390X -> panic "trivColorable ArchS390X" - ArchRISCV64 -> panic "trivColorable ArchRISCV64" - ArchLoongArch64->panic "trivColorable ArchLoongArch64" - ArchJavaScript-> panic "trivColorable ArchJavaScript" - ArchWasm32 -> panic "trivColorable ArchWasm32" - ArchUnknown -> panic "trivColorable ArchUnknown") - , count2 <- accSqueeze 0 cALLOCATABLE_REGS_FLOAT - (virtualRegSqueeze RcFloat) - conflicts - - , count3 <- accSqueeze count2 cALLOCATABLE_REGS_FLOAT - (realRegSqueeze RcFloat) - exclusions - - = count3 < cALLOCATABLE_REGS_FLOAT - -trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclusions +trivColorable platform virtualRegSqueeze realRegSqueeze RcFloatOrVector conflicts exclusions | let cALLOCATABLE_REGS_DOUBLE = (case platformArch platform of ArchX86 -> 8 @@ -194,11 +159,11 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclu ArchWasm32 -> panic "trivColorable ArchWasm32" ArchUnknown -> panic "trivColorable ArchUnknown") , count2 <- accSqueeze 0 cALLOCATABLE_REGS_DOUBLE - (virtualRegSqueeze RcDouble) + (virtualRegSqueeze RcFloatOrVector) conflicts , count3 <- accSqueeze count2 cALLOCATABLE_REGS_DOUBLE - (realRegSqueeze RcDouble) + (realRegSqueeze RcFloatOrVector) exclusions = count3 < cALLOCATABLE_REGS_DOUBLE @@ -221,21 +186,21 @@ trivColorable classN conflicts exclusions acc r (cd, cf) = case regClass r of RcInteger -> (cd+1, cf) - RcFloat -> (cd, cf+1) + RcFloatOrVector -> (cd, cf+1) _ -> panic "Regs.trivColorable: reg class not handled" tmp = nonDetFoldUFM acc (0, 0) conflicts (countInt, countFloat) = nonDetFoldUFM acc tmp exclusions squeese = worst countInt classN RcInteger - + worst countFloat classN RcFloat + + worst countFloat classN RcFloatOrVector in squeese < allocatableRegsInClass classN -- | Worst case displacement -- node N of classN has n neighbors of class C. -- --- We currently only have RcInteger and RcDouble, which don't conflict at all. +-- We currently only have RcInteger and RcFloatOrVector, which don't conflict at all. -- This is a bit boring compared to what's in RegArchX86. -- worst :: Int -> RegClass -> RegClass -> Int @@ -244,11 +209,11 @@ worst n classN classC RcInteger -> case classC of RcInteger -> min n (allocatableRegsInClass RcInteger) - RcFloat -> 0 + RcFloatOrVector -> 0 - RcDouble + RcFloatOrVector -> case classC of - RcFloat -> min n (allocatableRegsInClass RcFloat) + RcFloatOrVector -> min n (allocatableRegsInClass RcFloatOrVector) RcInteger -> 0 -- allocatableRegs is allMachRegNos with the fixed-use regs removed. @@ -267,7 +232,7 @@ allocatableRegsInClass :: RegClass -> Int allocatableRegsInClass cls = case cls of RcInteger -> allocatableRegsInteger - RcFloat -> allocatableRegsDouble + RcFloatOrVector -> allocatableRegsDouble allocatableRegsInteger :: Int allocatableRegsInteger @@ -276,6 +241,6 @@ allocatableRegsInteger allocatableRegsFloat :: Int allocatableRegsFloat - = length $ filter (\r -> regClass r == RcFloat + = length $ filter (\r -> regClass r == RcFloatOrVector $ map RealReg allocatableRegs -} ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -742,12 +742,11 @@ clobberRegs clobbered = do platform <- getPlatform freeregs <- getFreeRegsR - let gpRegs = frGetFreeRegs platform RcInteger freeregs :: [RealReg] - fltRegs = frGetFreeRegs platform RcFloat freeregs :: [RealReg] - dblRegs = frGetFreeRegs platform RcDouble freeregs :: [RealReg] + let gpRegs = frGetFreeRegs platform RcInteger freeregs :: [RealReg] + vecRegs = frGetFreeRegs platform RcFloatOrVector freeregs :: [RealReg] let extra_clobbered = [ r | r <- clobbered - , r `elem` (gpRegs ++ fltRegs ++ dblRegs) ] + , r `elem` (gpRegs ++ vecRegs) ] setFreeRegsR $! foldl' (flip $ frAllocateReg platform) freeregs extra_clobbered @@ -917,10 +916,8 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc -- the vregs we could kick out that are already in a slot let compat reg' r' - = let cls1 = targetClassOfRealReg platform reg' - cls2 = classOfVirtualReg r' - in (if cls1 == RcVector128 then RcDouble else cls1) - == (if cls2 == RcVector128 then RcDouble else cls2) + = targetClassOfRealReg platform reg' + == classOfVirtualReg r' candidates_inBoth :: [(Unique, RealRegUsage, StackSlot)] candidates_inBoth = [ (temp, reg, mem) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs ===================================== @@ -115,10 +115,10 @@ def CC_AArch64_GHC : CallingConv<[ -} getFreeRegs :: RegClass -> FreeRegs -> [RealReg] -getFreeRegs cls (FreeRegs g f) - | RcFloat <- cls = [] -- For now we only support double and integer registers, floats will need to be promoted. - | RcDouble <- cls = go 32 f 31 - | RcInteger <- cls = go 0 g 18 +getFreeRegs cls (FreeRegs g f) = + case cls of + RcFloatOrVector -> go 32 f 31 + RcInteger -> go 0 g 18 where go _ _ i | i < 0 = [] go off x i | testBit x i = RealRegSingle (off + i) : (go off x $! i - 1) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/PPC.hs ===================================== @@ -41,10 +41,10 @@ initFreeRegs :: Platform -> FreeRegs initFreeRegs platform = foldl' (flip releaseReg) noFreeRegs (allocatableRegs platform) getFreeRegs :: RegClass -> FreeRegs -> [RealReg] -- lazily -getFreeRegs cls (FreeRegs g f) - | RcFloat <- cls = [] -- no float regs on PowerPC, use double - | RcDouble <- cls = go f (0x80000000) 63 - | RcInteger <- cls = go g (0x80000000) 31 +getFreeRegs cls (FreeRegs g f) = + case cls of + RcFloatOrVector -> go f (0x80000000) 63 + RcInteger -> go g (0x80000000) 31 where go _ 0 _ = [] go x m i | x .&. m /= 0 = RealRegSingle i : (go x (m `shiftR` 1) $! i-1) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/X86.hs ===================================== @@ -40,11 +40,7 @@ getFreeRegs platform cls (FreeRegs f) = go f 0 -- ToDo: there's no point looking through all the integer registers -- in order to find a floating-point one. compatibleClass i = - let regClass = classOfRealReg platform (RealRegSingle i) - in (if regClass == RcVector128 then RcDouble else regClass) - == (if cls == RcVector128 then RcDouble else cls) - -- SIMD NCG TODO: giant hack to account for xmm registers being - -- used for Double with SSE2. + cls == classOfRealReg platform (RealRegSingle i) allocateReg :: RealReg -> FreeRegs -> FreeRegs ===================================== compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs ===================================== @@ -40,11 +40,7 @@ getFreeRegs platform cls (FreeRegs f) = go f 0 -- ToDo: there's no point looking through all the integer registers -- in order to find a floating-point one. compatibleClass i = - let regClass = classOfRealReg platform (RealRegSingle i) - in (if regClass == RcVector128 then RcDouble else regClass) - == (if cls == RcVector128 then RcDouble else cls) - -- SIMD NCG TODO: giant hack to account for xmm registers being - -- used for Double with SSE2. + cls == classOfRealReg platform (RealRegSingle i) allocateReg :: RealReg -> FreeRegs -> FreeRegs allocateReg (RealRegSingle r) (FreeRegs f) ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -832,9 +832,7 @@ mkSpillInstr config reg fmt delta slot -- SIMD NCG TODO: panic for unsupported VecFormats (& same in mkLoadInstr) [MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off slot)) -- Now shuffle the register, putting the high half into the lower half. - ,SHUFPD (VecFormat 2 FmtDouble W64) (ImmInt 0b01) (OpReg reg) reg - -- NB: this format doesn't matter, we emit the same instruction - -- regardless of what is stored... + ,SHUFPD fmt (ImmInt 0b01) (OpReg reg) reg -- SIMD NCG TODO: can we emit more efficient code here? ,MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off (slot + 1)))] _ -> [MOV fmt (OpReg reg) (OpAddr (spRel platform $ off slot))] @@ -922,7 +920,7 @@ mkRegRegMoveInstr platform src dst ArchX86 -> MOV II32 (OpReg src) (OpReg dst) ArchX86_64 -> MOV II64 (OpReg src) (OpReg dst) _ -> panic "X86.mkRegRegMoveInstr: Bad arch" - RcDouble -> MOV FF64 (OpReg src) (OpReg dst) + RcFloatOrVector -> MOV FF64 (OpReg src) (OpReg dst) -- this code is the lie we tell ourselves because both float and double -- use the same register class.on x86_64 and x86 32bit with SSE2, -- more plainly, both use the XMM registers ===================================== compiler/GHC/CmmToAsm/X86/Regs.hs ===================================== @@ -77,7 +77,7 @@ virtualRegSqueeze cls vr VirtualRegHi{} -> 1 _other -> 0 - RcDouble + RcFloatOrVector -> case vr of VirtualRegD{} -> 1 VirtualRegF{} -> 0 @@ -97,7 +97,7 @@ realRegSqueeze cls rr | regNo < firstxmm -> 1 | otherwise -> 0 - RcDouble + RcFloatOrVector -> case rr of RealRegSingle regNo | regNo >= firstxmm -> 1 @@ -243,7 +243,7 @@ classOfRealReg platform reg = case reg of RealRegSingle i | i <= lastint platform -> RcInteger - | i <= lastxmm platform -> RcDouble + | i <= lastxmm platform -> RcFloatOrVector | otherwise -> panic "X86.Reg.classOfRealReg registerSingle too high" -- | Get the name of the register with this number. @@ -272,11 +272,8 @@ Intel x86 architecture: - Registers 0-7 have 16-bit counterparts (ax, bx etc.) - Registers 0-3 have 8 bit counterparts (ah, bh etc.) -The fp registers are all Double registers; we don't have any RcFloat class -regs. @regClass@ barfs if you give it a VirtualRegF, and mkVReg above should -never generate them. - -TODO: cleanup modelling float vs double registers and how they are the same class. +The fp registers support Float, Doubles and vectors of those, as well +as vectors of integer values. -} ===================================== compiler/GHC/Platform/Reg.hs ===================================== @@ -119,9 +119,9 @@ classOfVirtualReg vr = case vr of VirtualRegI{} -> RcInteger VirtualRegHi{} -> RcInteger - VirtualRegF{} -> RcFloat - VirtualRegD{} -> RcDouble - VirtualRegVec{} -> RcVector128 + VirtualRegF{} -> RcFloatOrVector + VirtualRegD{} -> RcFloatOrVector + VirtualRegVec{} -> RcFloatOrVector -- Determine the upper-half vreg for a 64-bit quantity on a 32-bit platform ===================================== compiler/GHC/Platform/Reg/Class.hs ===================================== @@ -19,26 +19,22 @@ import GHC.Builtin.Uniques -- We treat all registers in a class as being interchangeable. -- data RegClass + -- | Supports (scalar) integers only. = RcInteger - | RcFloat - | RcDouble - | RcVector128 + -- | Supports vectors (both integers & floats) as well as scalar values + -- (but in practice not used for scalar integer values). + | RcFloatOrVector deriving (Eq, Ord, Show) allRegClasses :: [RegClass] -allRegClasses = - [ RcInteger, RcFloat, RcDouble, RcVector128 ] +allRegClasses = [RcInteger, RcFloatOrVector] instance Uniquable RegClass where getUnique = \case - RcInteger -> mkRegClassUnique 0 - RcFloat -> mkRegClassUnique 1 - RcDouble -> mkRegClassUnique 2 - RcVector128 -> mkRegClassUnique 3 + RcInteger -> mkRegClassUnique 0 + RcFloatOrVector -> mkRegClassUnique 1 instance Outputable RegClass where ppr = \case - RcInteger -> Outputable.text "I" - RcFloat -> Outputable.text "F" - RcDouble -> Outputable.text "D" - RcVector128 -> Outputable.text "V" + RcInteger -> Outputable.text "I" + RcFloatOrVector -> Outputable.text "F" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3bbc4fcd1a58596ccae43cf50da00f99a8880790 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3bbc4fcd1a58596ccae43cf50da00f99a8880790 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 08:29:53 2024 From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim)) Date: Sat, 08 Jun 2024 04:29:53 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/clc-codeowners Message-ID: <6664168182b39_3d87d350306d890361@gitlab.mail> Bodigrim pushed new branch wip/clc-codeowners at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/clc-codeowners You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 08:31:19 2024 From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim)) Date: Sat, 08 Jun 2024 04:31:19 -0400 Subject: [Git][ghc/ghc][wip/clc-codeowners] CODEOWNERS: add @core-libraries to track base interface changes Message-ID: <666416d7e0127_3d87d350bbcd8905d9@gitlab.mail> Bodigrim pushed to branch wip/clc-codeowners at Glasgow Haskell Compiler / GHC Commits: 35e71933 by Andrew Lelechenko at 2024-06-08T10:30:32+02:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 1 changed file: - CODEOWNERS Changes: ===================================== CODEOWNERS ===================================== @@ -60,6 +60,7 @@ /libraries/base/ @hvr /libraries/ghci/ @simonmar /libraries/template-haskell/ @rae +/testsuite/tests/interface-stability/ @core-libraries [Internal utilities and libraries] /utils/iserv-proxy/ @angerman @simonmar View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/35e719336dca4b44fa51539af18d4ae594dbf040 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/35e719336dca4b44fa51539af18d4ae594dbf040 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 08:36:38 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Sat, 08 Jun 2024 04:36:38 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] 2 commits: improve RegClass Message-ID: <666418169f63b_3d87d351ed0989297e@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: e5fba538 by sheaf at 2024-06-08T10:35:24+02:00 improve RegClass - - - - - c9203839 by sheaf at 2024-06-08T10:35:44+02:00 set up basics for AArch64 SIMD - - - - - 16 changed files: - compiler/GHC/CmmToAsm/AArch64.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Regs.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/PPC/Regs.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs - compiler/GHC/CmmToAsm/Reg/Linear/PPC.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Regs.hs - compiler/GHC/Platform/Reg.hs - compiler/GHC/Platform/Reg/Class.hs Changes: ===================================== compiler/GHC/CmmToAsm/AArch64.hs ===================================== @@ -49,8 +49,8 @@ instance Instruction AArch64.Instr where jumpDestsOfInstr = AArch64.jumpDestsOfInstr canFallthroughTo = AArch64.canFallthroughTo patchJumpInstr = AArch64.patchJumpInstr - mkSpillInstr cfg reg _ i j = AArch64.mkSpillInstr cfg reg i j - mkLoadInstr cfg reg _ i j = AArch64.mkLoadInstr cfg reg i j + mkSpillInstr = AArch64.mkSpillInstr + mkLoadInstr = AArch64.mkLoadInstr takeDeltaInstr = AArch64.takeDeltaInstr isMetaInstr = AArch64.isMetaInstr mkRegRegMoveInstr _ = AArch64.mkRegRegMoveInstr ===================================== compiler/GHC/CmmToAsm/AArch64/Instr.hs ===================================== @@ -360,11 +360,12 @@ mkSpillInstr :: HasCallStack => NCGConfig -> Reg -- register to spill + -> Format -> Int -- current stack delta -> Int -- spill slot to use -> [Instr] -mkSpillInstr config reg delta slot = +mkSpillInstr config reg fmt delta slot = case off - delta of imm | -256 <= imm && imm <= 255 -> [ mkStrSp imm ] imm | imm > 0 && imm .&. 0x7 == 0x0 && imm <= 0xfff -> [ mkStrSp imm ] @@ -375,8 +376,8 @@ mkSpillInstr config reg delta slot = where a .&~. b = a .&. (complement b) - fmt = fmtOfRealReg (case reg of { RegReal r -> r; _ -> panic "Expected real reg"}) - + -- SIMD NCG TODO: emit the correct instructions to spill a vector register. + -- You can take inspiration fro the X86_64 backend. mkIp0SpillAddr imm = ANN (text "Spill: IP0 <- SP + " <> int imm) $ ADD ip0 sp (OpImm (ImmInt imm)) mkStrSp imm = ANN (text "Spill@" <> int (off - delta)) $ STR fmt (OpReg W64 reg) (OpAddr (AddrRegImm (regSingle 31) (ImmInt imm))) mkStrIp0 imm = ANN (text "Spill@" <> int (off - delta)) $ STR fmt (OpReg W64 reg) (OpAddr (AddrRegImm (regSingle 16) (ImmInt imm))) @@ -386,11 +387,11 @@ mkSpillInstr config reg delta slot = mkLoadInstr :: NCGConfig -> Reg -- register to load + -> Format -> Int -- current stack delta -> Int -- spill slot to use -> [Instr] - -mkLoadInstr config reg delta slot = +mkLoadInstr config reg fmt delta slot = case off - delta of imm | -256 <= imm && imm <= 255 -> [ mkLdrSp imm ] imm | imm > 0 && imm .&. 0x7 == 0x0 && imm <= 0xfff -> [ mkLdrSp imm ] @@ -401,8 +402,8 @@ mkLoadInstr config reg delta slot = where a .&~. b = a .&. (complement b) - fmt = fmtOfRealReg (case reg of { RegReal r -> r; _ -> panic "Expected real reg"}) - + -- SIMD NCG TODO: emit the correct instructions to load a vector register. + -- You can take inspiration fro the X86_64 backend. mkIp0SpillAddr imm = ANN (text "Reload: IP0 <- SP + " <> int imm) $ ADD ip0 sp (OpImm (ImmInt imm)) mkLdrSp imm = ANN (text "Reload@" <> int (off - delta)) $ LDR fmt (OpReg W64 reg) (OpAddr (AddrRegImm (regSingle 31) (ImmInt imm))) mkLdrIp0 imm = ANN (text "Reload@" <> int (off - delta)) $ LDR fmt (OpReg W64 reg) (OpAddr (AddrRegImm (regSingle 16) (ImmInt imm))) ===================================== compiler/GHC/CmmToAsm/AArch64/Regs.hs ===================================== @@ -108,14 +108,12 @@ virtualRegSqueeze cls vr VirtualRegHi{} -> 1 _other -> 0 - RcDouble + RcFloatOrVector -> case vr of VirtualRegD{} -> 1 VirtualRegF{} -> 0 _other -> 0 - _other -> 0 - {-# INLINE realRegSqueeze #-} realRegSqueeze :: RegClass -> RealReg -> Int realRegSqueeze cls rr @@ -126,14 +124,12 @@ realRegSqueeze cls rr | regNo < 32 -> 1 -- first fp reg is 32 | otherwise -> 0 - RcDouble + RcFloatOrVector -> case rr of RealRegSingle regNo | regNo < 32 -> 0 | otherwise -> 1 - _other -> 0 - mkVirtualReg :: Unique -> Format -> VirtualReg mkVirtualReg u format | not (isFloatFormat format) = VirtualRegI u @@ -147,18 +143,10 @@ mkVirtualReg u format classOfRealReg :: RealReg -> RegClass classOfRealReg (RealRegSingle i) | i < 32 = RcInteger - | otherwise = RcDouble - -fmtOfRealReg :: RealReg -> Format -fmtOfRealReg real_reg = - case classOfRealReg real_reg of - RcInteger -> II64 - RcDouble -> FF64 - RcFloat -> panic "No float regs on arm" + | otherwise = RcFloatOrVector regDotColor :: RealReg -> SDoc regDotColor reg = case classOfRealReg reg of RcInteger -> text "blue" - RcFloat -> text "red" - RcDouble -> text "green" + RcFloatOrVector -> text "red" ===================================== compiler/GHC/CmmToAsm/PPC/CodeGen.hs ===================================== @@ -449,7 +449,7 @@ getRegister' _ platform (CmmMachOp (MO_SS_Conv W64 W32) [x]) getRegister' _ platform (CmmLoad mem pk _) | not (isWord64 pk) = do Amode addr addr_code <- getAmode D mem - let code dst = assert ((targetClassOfReg platform dst == RcDouble) == isFloatType pk) $ + let code dst = assert ((targetClassOfReg platform dst == RcFloatOrVector) == isFloatType pk) $ addr_code `snocOL` LD format dst addr return (Any format code) | not (target32Bit platform) = do ===================================== compiler/GHC/CmmToAsm/PPC/Instr.hs ===================================== @@ -562,7 +562,7 @@ mkSpillInstr config reg delta slot RcInteger -> case arch of ArchPPC -> II32 _ -> II64 - RcDouble -> FF64 + RcFloatOrVector -> FF64 _ -> panic "PPC.Instr.mkSpillInstr: no match" instr = case makeImmediate W32 True (off-delta) of Just _ -> ST @@ -587,7 +587,7 @@ mkLoadInstr config reg delta slot RcInteger -> case arch of ArchPPC -> II32 _ -> II64 - RcDouble -> FF64 + RcFloatOrVector -> FF64 _ -> panic "PPC.Instr.mkLoadInstr: no match" instr = case makeImmediate W32 True (off-delta) of Just _ -> LD ===================================== compiler/GHC/CmmToAsm/PPC/Regs.hs ===================================== @@ -83,14 +83,12 @@ virtualRegSqueeze cls vr VirtualRegHi{} -> 1 _other -> 0 - RcDouble + RcFloatOrVector -> case vr of VirtualRegD{} -> 1 VirtualRegF{} -> 0 _other -> 0 - _other -> 0 - {-# INLINE realRegSqueeze #-} realRegSqueeze :: RegClass -> RealReg -> Int realRegSqueeze cls rr @@ -102,15 +100,13 @@ realRegSqueeze cls rr | otherwise -> 0 - RcDouble + RcFloatOrVector -> case rr of RealRegSingle regNo | regNo < 32 -> 0 | otherwise -> 1 - _other -> 0 - mkVirtualReg :: Unique -> Format -> VirtualReg mkVirtualReg u format | not (isFloatFormat format) = VirtualRegI u @@ -124,8 +120,7 @@ regDotColor :: RealReg -> SDoc regDotColor reg = case classOfRealReg reg of RcInteger -> text "blue" - RcFloat -> text "red" - RcDouble -> text "green" + RcFloatOrVector -> text "red" @@ -235,8 +230,8 @@ allMachRegNos = [0..63] {-# INLINE classOfRealReg #-} classOfRealReg :: RealReg -> RegClass classOfRealReg (RealRegSingle i) - | i < 32 = RcInteger - | otherwise = RcDouble + | i < 32 = RcInteger + | otherwise = RcFloatOrVector showReg :: RegNo -> String showReg n ===================================== compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs ===================================== @@ -22,7 +22,7 @@ import GHC.Utils.Panic -- This gets hammered by scanGraph during register allocation, -- so needs to be fairly efficient. -- --- NOTE: This only works for architectures with just RcInteger and RcDouble +-- NOTE: This only works for architectures with just RcInteger and RcFloatOrVector -- (which are disjoint) ie. x86, x86_64 and ppc -- -- The number of allocatable regs is hard coded in here so we can do @@ -134,42 +134,7 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts excl = count3 < cALLOCATABLE_REGS_INTEGER -trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclusions - | let cALLOCATABLE_REGS_FLOAT - = (case platformArch platform of - -- On x86_64 and x86, Float and RcDouble - -- use the same registers, - -- so we only use RcDouble to represent the - -- register allocation problem on those types. - ArchX86 -> 0 - ArchX86_64 -> 0 - ArchPPC -> 0 - ArchPPC_64 _ -> 0 - ArchARM _ _ _ -> panic "trivColorable ArchARM" - -- we can in principle address all the float regs as - -- segments. So we could have 64 Float regs. Or - -- 128 Half regs, or even 256 Byte regs. - ArchAArch64 -> 0 - ArchAlpha -> panic "trivColorable ArchAlpha" - ArchMipseb -> panic "trivColorable ArchMipseb" - ArchMipsel -> panic "trivColorable ArchMipsel" - ArchS390X -> panic "trivColorable ArchS390X" - ArchRISCV64 -> panic "trivColorable ArchRISCV64" - ArchLoongArch64->panic "trivColorable ArchLoongArch64" - ArchJavaScript-> panic "trivColorable ArchJavaScript" - ArchWasm32 -> panic "trivColorable ArchWasm32" - ArchUnknown -> panic "trivColorable ArchUnknown") - , count2 <- accSqueeze 0 cALLOCATABLE_REGS_FLOAT - (virtualRegSqueeze RcFloat) - conflicts - - , count3 <- accSqueeze count2 cALLOCATABLE_REGS_FLOAT - (realRegSqueeze RcFloat) - exclusions - - = count3 < cALLOCATABLE_REGS_FLOAT - -trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclusions +trivColorable platform virtualRegSqueeze realRegSqueeze RcFloatOrVector conflicts exclusions | let cALLOCATABLE_REGS_DOUBLE = (case platformArch platform of ArchX86 -> 8 @@ -194,11 +159,11 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclu ArchWasm32 -> panic "trivColorable ArchWasm32" ArchUnknown -> panic "trivColorable ArchUnknown") , count2 <- accSqueeze 0 cALLOCATABLE_REGS_DOUBLE - (virtualRegSqueeze RcDouble) + (virtualRegSqueeze RcFloatOrVector) conflicts , count3 <- accSqueeze count2 cALLOCATABLE_REGS_DOUBLE - (realRegSqueeze RcDouble) + (realRegSqueeze RcFloatOrVector) exclusions = count3 < cALLOCATABLE_REGS_DOUBLE @@ -221,21 +186,21 @@ trivColorable classN conflicts exclusions acc r (cd, cf) = case regClass r of RcInteger -> (cd+1, cf) - RcFloat -> (cd, cf+1) + RcFloatOrVector -> (cd, cf+1) _ -> panic "Regs.trivColorable: reg class not handled" tmp = nonDetFoldUFM acc (0, 0) conflicts (countInt, countFloat) = nonDetFoldUFM acc tmp exclusions squeese = worst countInt classN RcInteger - + worst countFloat classN RcFloat + + worst countFloat classN RcFloatOrVector in squeese < allocatableRegsInClass classN -- | Worst case displacement -- node N of classN has n neighbors of class C. -- --- We currently only have RcInteger and RcDouble, which don't conflict at all. +-- We currently only have RcInteger and RcFloatOrVector, which don't conflict at all. -- This is a bit boring compared to what's in RegArchX86. -- worst :: Int -> RegClass -> RegClass -> Int @@ -244,11 +209,11 @@ worst n classN classC RcInteger -> case classC of RcInteger -> min n (allocatableRegsInClass RcInteger) - RcFloat -> 0 + RcFloatOrVector -> 0 - RcDouble + RcFloatOrVector -> case classC of - RcFloat -> min n (allocatableRegsInClass RcFloat) + RcFloatOrVector -> min n (allocatableRegsInClass RcFloatOrVector) RcInteger -> 0 -- allocatableRegs is allMachRegNos with the fixed-use regs removed. @@ -267,7 +232,7 @@ allocatableRegsInClass :: RegClass -> Int allocatableRegsInClass cls = case cls of RcInteger -> allocatableRegsInteger - RcFloat -> allocatableRegsDouble + RcFloatOrVector -> allocatableRegsDouble allocatableRegsInteger :: Int allocatableRegsInteger @@ -276,6 +241,6 @@ allocatableRegsInteger allocatableRegsFloat :: Int allocatableRegsFloat - = length $ filter (\r -> regClass r == RcFloat + = length $ filter (\r -> regClass r == RcFloatOrVector $ map RealReg allocatableRegs -} ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -742,12 +742,11 @@ clobberRegs clobbered = do platform <- getPlatform freeregs <- getFreeRegsR - let gpRegs = frGetFreeRegs platform RcInteger freeregs :: [RealReg] - fltRegs = frGetFreeRegs platform RcFloat freeregs :: [RealReg] - dblRegs = frGetFreeRegs platform RcDouble freeregs :: [RealReg] + let gpRegs = frGetFreeRegs platform RcInteger freeregs :: [RealReg] + vecRegs = frGetFreeRegs platform RcFloatOrVector freeregs :: [RealReg] let extra_clobbered = [ r | r <- clobbered - , r `elem` (gpRegs ++ fltRegs ++ dblRegs) ] + , r `elem` (gpRegs ++ vecRegs) ] setFreeRegsR $! foldl' (flip $ frAllocateReg platform) freeregs extra_clobbered @@ -917,10 +916,8 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc -- the vregs we could kick out that are already in a slot let compat reg' r' - = let cls1 = targetClassOfRealReg platform reg' - cls2 = classOfVirtualReg r' - in (if cls1 == RcVector128 then RcDouble else cls1) - == (if cls2 == RcVector128 then RcDouble else cls2) + = targetClassOfRealReg platform reg' + == classOfVirtualReg r' candidates_inBoth :: [(Unique, RealRegUsage, StackSlot)] candidates_inBoth = [ (temp, reg, mem) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs ===================================== @@ -115,10 +115,10 @@ def CC_AArch64_GHC : CallingConv<[ -} getFreeRegs :: RegClass -> FreeRegs -> [RealReg] -getFreeRegs cls (FreeRegs g f) - | RcFloat <- cls = [] -- For now we only support double and integer registers, floats will need to be promoted. - | RcDouble <- cls = go 32 f 31 - | RcInteger <- cls = go 0 g 18 +getFreeRegs cls (FreeRegs g f) = + case cls of + RcFloatOrVector -> go 32 f 31 + RcInteger -> go 0 g 18 where go _ _ i | i < 0 = [] go off x i | testBit x i = RealRegSingle (off + i) : (go off x $! i - 1) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/PPC.hs ===================================== @@ -41,10 +41,10 @@ initFreeRegs :: Platform -> FreeRegs initFreeRegs platform = foldl' (flip releaseReg) noFreeRegs (allocatableRegs platform) getFreeRegs :: RegClass -> FreeRegs -> [RealReg] -- lazily -getFreeRegs cls (FreeRegs g f) - | RcFloat <- cls = [] -- no float regs on PowerPC, use double - | RcDouble <- cls = go f (0x80000000) 63 - | RcInteger <- cls = go g (0x80000000) 31 +getFreeRegs cls (FreeRegs g f) = + case cls of + RcFloatOrVector -> go f (0x80000000) 63 + RcInteger -> go g (0x80000000) 31 where go _ 0 _ = [] go x m i | x .&. m /= 0 = RealRegSingle i : (go x (m `shiftR` 1) $! i-1) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/X86.hs ===================================== @@ -40,11 +40,7 @@ getFreeRegs platform cls (FreeRegs f) = go f 0 -- ToDo: there's no point looking through all the integer registers -- in order to find a floating-point one. compatibleClass i = - let regClass = classOfRealReg platform (RealRegSingle i) - in (if regClass == RcVector128 then RcDouble else regClass) - == (if cls == RcVector128 then RcDouble else cls) - -- SIMD NCG TODO: giant hack to account for xmm registers being - -- used for Double with SSE2. + cls == classOfRealReg platform (RealRegSingle i) allocateReg :: RealReg -> FreeRegs -> FreeRegs ===================================== compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs ===================================== @@ -40,11 +40,7 @@ getFreeRegs platform cls (FreeRegs f) = go f 0 -- ToDo: there's no point looking through all the integer registers -- in order to find a floating-point one. compatibleClass i = - let regClass = classOfRealReg platform (RealRegSingle i) - in (if regClass == RcVector128 then RcDouble else regClass) - == (if cls == RcVector128 then RcDouble else cls) - -- SIMD NCG TODO: giant hack to account for xmm registers being - -- used for Double with SSE2. + cls == classOfRealReg platform (RealRegSingle i) allocateReg :: RealReg -> FreeRegs -> FreeRegs allocateReg (RealRegSingle r) (FreeRegs f) ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -832,9 +832,7 @@ mkSpillInstr config reg fmt delta slot -- SIMD NCG TODO: panic for unsupported VecFormats (& same in mkLoadInstr) [MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off slot)) -- Now shuffle the register, putting the high half into the lower half. - ,SHUFPD (VecFormat 2 FmtDouble W64) (ImmInt 0b01) (OpReg reg) reg - -- NB: this format doesn't matter, we emit the same instruction - -- regardless of what is stored... + ,SHUFPD fmt (ImmInt 0b01) (OpReg reg) reg -- SIMD NCG TODO: can we emit more efficient code here? ,MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off (slot + 1)))] _ -> [MOV fmt (OpReg reg) (OpAddr (spRel platform $ off slot))] @@ -922,11 +920,7 @@ mkRegRegMoveInstr platform src dst ArchX86 -> MOV II32 (OpReg src) (OpReg dst) ArchX86_64 -> MOV II64 (OpReg src) (OpReg dst) _ -> panic "X86.mkRegRegMoveInstr: Bad arch" - RcDouble -> MOV FF64 (OpReg src) (OpReg dst) - -- this code is the lie we tell ourselves because both float and double - -- use the same register class.on x86_64 and x86 32bit with SSE2, - -- more plainly, both use the XMM registers - _ -> panic "X86.RegInfo.mkRegRegMoveInstr: no match" + RcFloatOrVector -> MOV FF64 (OpReg src) (OpReg dst) -- | Check whether an instruction represents a reg-reg move. -- The register allocator attempts to eliminate reg->reg moves whenever it can, ===================================== compiler/GHC/CmmToAsm/X86/Regs.hs ===================================== @@ -77,7 +77,7 @@ virtualRegSqueeze cls vr VirtualRegHi{} -> 1 _other -> 0 - RcDouble + RcFloatOrVector -> case vr of VirtualRegD{} -> 1 VirtualRegF{} -> 0 @@ -85,8 +85,6 @@ virtualRegSqueeze cls vr _other -> 0 - _other -> 0 - {-# INLINE realRegSqueeze #-} realRegSqueeze :: RegClass -> RealReg -> Int realRegSqueeze cls rr @@ -97,14 +95,12 @@ realRegSqueeze cls rr | regNo < firstxmm -> 1 | otherwise -> 0 - RcDouble + RcFloatOrVector -> case rr of RealRegSingle regNo | regNo >= firstxmm -> 1 | otherwise -> 0 - _other -> 0 - -- ----------------------------------------------------------------------------- -- Immediates @@ -243,7 +239,7 @@ classOfRealReg platform reg = case reg of RealRegSingle i | i <= lastint platform -> RcInteger - | i <= lastxmm platform -> RcDouble + | i <= lastxmm platform -> RcFloatOrVector | otherwise -> panic "X86.Reg.classOfRealReg registerSingle too high" -- | Get the name of the register with this number. @@ -272,11 +268,8 @@ Intel x86 architecture: - Registers 0-7 have 16-bit counterparts (ax, bx etc.) - Registers 0-3 have 8 bit counterparts (ah, bh etc.) -The fp registers are all Double registers; we don't have any RcFloat class -regs. @regClass@ barfs if you give it a VirtualRegF, and mkVReg above should -never generate them. - -TODO: cleanup modelling float vs double registers and how they are the same class. +The fp registers support Float, Doubles and vectors of those, as well +as vectors of integer values. -} ===================================== compiler/GHC/Platform/Reg.hs ===================================== @@ -119,9 +119,9 @@ classOfVirtualReg vr = case vr of VirtualRegI{} -> RcInteger VirtualRegHi{} -> RcInteger - VirtualRegF{} -> RcFloat - VirtualRegD{} -> RcDouble - VirtualRegVec{} -> RcVector128 + VirtualRegF{} -> RcFloatOrVector + VirtualRegD{} -> RcFloatOrVector + VirtualRegVec{} -> RcFloatOrVector -- Determine the upper-half vreg for a 64-bit quantity on a 32-bit platform ===================================== compiler/GHC/Platform/Reg/Class.hs ===================================== @@ -19,26 +19,22 @@ import GHC.Builtin.Uniques -- We treat all registers in a class as being interchangeable. -- data RegClass + -- | Supports (scalar) integers only. = RcInteger - | RcFloat - | RcDouble - | RcVector128 + -- | Supports vectors (both integers & floats) as well as scalar values + -- (but in practice not used for scalar integer values). + | RcFloatOrVector deriving (Eq, Ord, Show) allRegClasses :: [RegClass] -allRegClasses = - [ RcInteger, RcFloat, RcDouble, RcVector128 ] +allRegClasses = [RcInteger, RcFloatOrVector] instance Uniquable RegClass where getUnique = \case - RcInteger -> mkRegClassUnique 0 - RcFloat -> mkRegClassUnique 1 - RcDouble -> mkRegClassUnique 2 - RcVector128 -> mkRegClassUnique 3 + RcInteger -> mkRegClassUnique 0 + RcFloatOrVector -> mkRegClassUnique 1 instance Outputable RegClass where ppr = \case - RcInteger -> Outputable.text "I" - RcFloat -> Outputable.text "F" - RcDouble -> Outputable.text "D" - RcVector128 -> Outputable.text "V" + RcInteger -> Outputable.text "I" + RcFloatOrVector -> Outputable.text "F" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3bbc4fcd1a58596ccae43cf50da00f99a8880790...c9203839124a5cf87a07af22a6d592012f487d9f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3bbc4fcd1a58596ccae43cf50da00f99a8880790...c9203839124a5cf87a07af22a6d592012f487d9f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 10:10:28 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sat, 08 Jun 2024 06:10:28 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/kill-pre-c11 Message-ID: <66642e14c75ff_3d87d35d212981089b6@gitlab.mail> Cheng Shao pushed new branch wip/kill-pre-c11 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/kill-pre-c11 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 10:54:13 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 08 Jun 2024 06:54:13 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: StgToCmm: refactor opTranslate and friends Message-ID: <66643855af080_3d87d363de0401236a@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - baef54f2 by qqwy at 2024-06-08T06:53:44-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - edd1ae6d by Cheng Shao at 2024-06-08T06:53:45-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - aae3e02f by Andrew Lelechenko at 2024-06-08T06:53:45-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 13 changed files: - CODEOWNERS - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/Driver/Config/StgToCmm.hs - compiler/GHC/StgToCmm/Config.hs - compiler/GHC/StgToCmm/Prim.hs - libraries/ghc-internal/src/GHC/Internal/Exception.hs - rts/Inlines.c - rts/include/Stg.h - testsuite/tests/driver/objc/all.T - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 Changes: ===================================== CODEOWNERS ===================================== @@ -60,6 +60,7 @@ /libraries/base/ @hvr /libraries/ghci/ @simonmar /libraries/template-haskell/ @rae +/testsuite/tests/interface-stability/ @core-libraries [Internal utilities and libraries] /utils/iserv-proxy/ @angerman @simonmar ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -94,12 +94,6 @@ is32BitPlatform = do platform <- getPlatform return $ target32Bit platform -expect32BitPlatform :: SDoc -> NatM () -expect32BitPlatform doc = do - is32Bit <- is32BitPlatform - when (not is32Bit) $ - pprPanic "Expecting 32-bit platform" doc - sse2Enabled :: NatM Bool sse2Enabled = do config <- getConfig @@ -2475,35 +2469,10 @@ genSimplePrim bid MO_F64_Acosh [dst] [src] = genLibCCall bid genSimplePrim bid MO_F64_Atanh [dst] [src] = genLibCCall bid (fsLit "atanh") [dst] [src] genSimplePrim bid MO_SuspendThread [tok] [rs,i] = genRTSCCall bid (fsLit "suspendThread") [tok] [rs,i] genSimplePrim bid MO_ResumeThread [rs] [tok] = genRTSCCall bid (fsLit "resumeThread") [rs] [tok] -genSimplePrim _ MO_I64_ToI [dst] [src] = genInt64ToInt dst src -genSimplePrim _ MO_I64_FromI [dst] [src] = genIntToInt64 dst src -genSimplePrim _ MO_W64_ToW [dst] [src] = genWord64ToWord dst src -genSimplePrim _ MO_W64_FromW [dst] [src] = genWordToWord64 dst src -genSimplePrim _ MO_x64_Neg [dst] [src] = genNeg64 dst src -genSimplePrim _ MO_x64_Add [dst] [x,y] = genAdd64 dst x y -genSimplePrim _ MO_x64_Sub [dst] [x,y] = genSub64 dst x y -genSimplePrim bid MO_x64_Mul [dst] [x,y] = genPrimCCall bid (fsLit "hs_mul64") [dst] [x,y] genSimplePrim bid MO_I64_Quot [dst] [x,y] = genPrimCCall bid (fsLit "hs_quotInt64") [dst] [x,y] genSimplePrim bid MO_I64_Rem [dst] [x,y] = genPrimCCall bid (fsLit "hs_remInt64") [dst] [x,y] genSimplePrim bid MO_W64_Quot [dst] [x,y] = genPrimCCall bid (fsLit "hs_quotWord64") [dst] [x,y] genSimplePrim bid MO_W64_Rem [dst] [x,y] = genPrimCCall bid (fsLit "hs_remWord64") [dst] [x,y] -genSimplePrim _ MO_x64_And [dst] [x,y] = genAnd64 dst x y -genSimplePrim _ MO_x64_Or [dst] [x,y] = genOr64 dst x y -genSimplePrim _ MO_x64_Xor [dst] [x,y] = genXor64 dst x y -genSimplePrim _ MO_x64_Not [dst] [src] = genNot64 dst src -genSimplePrim bid MO_x64_Shl [dst] [x,n] = genPrimCCall bid (fsLit "hs_uncheckedShiftL64") [dst] [x,n] -genSimplePrim bid MO_I64_Shr [dst] [x,n] = genPrimCCall bid (fsLit "hs_uncheckedIShiftRA64") [dst] [x,n] -genSimplePrim bid MO_W64_Shr [dst] [x,n] = genPrimCCall bid (fsLit "hs_uncheckedShiftRL64") [dst] [x,n] -genSimplePrim _ MO_x64_Eq [dst] [x,y] = genEq64 dst x y -genSimplePrim _ MO_x64_Ne [dst] [x,y] = genNe64 dst x y -genSimplePrim _ MO_I64_Ge [dst] [x,y] = genGeInt64 dst x y -genSimplePrim _ MO_I64_Gt [dst] [x,y] = genGtInt64 dst x y -genSimplePrim _ MO_I64_Le [dst] [x,y] = genLeInt64 dst x y -genSimplePrim _ MO_I64_Lt [dst] [x,y] = genLtInt64 dst x y -genSimplePrim _ MO_W64_Ge [dst] [x,y] = genGeWord64 dst x y -genSimplePrim _ MO_W64_Gt [dst] [x,y] = genGtWord64 dst x y -genSimplePrim _ MO_W64_Le [dst] [x,y] = genLeWord64 dst x y -genSimplePrim _ MO_W64_Lt [dst] [x,y] = genLtWord64 dst x y genSimplePrim _ op dst args = do platform <- ncgPlatform <$> getConfig pprPanic "genSimplePrim: unhandled primop" (ppr (pprCallishMachOp op, dst, fmap (pdoc platform) args)) @@ -4462,231 +4431,3 @@ genQuotRem width signed res_q res_r m_arg_x_high arg_x_low arg_y = do toOL [instr format y_reg, MOV format (OpReg rax) (OpReg reg_q), MOV format (OpReg rdx) (OpReg reg_r)] - - ----------------------------------------------------------------------------- --- The following functions implement certain 64-bit MachOps inline for 32-bit --- architectures. On 64-bit architectures, those MachOps aren't supported and --- calling these functions for a 64-bit target platform is considered an error --- (hence the use of `expect32BitPlatform`). --- --- On 64-bit platforms, generic MachOps should be used instead of these 64-bit --- specific ones (e.g. use MO_Add instead of MO_x64_Add). This MachOp selection --- is done by StgToCmm. - -genInt64ToInt :: LocalReg -> CmmExpr -> NatM InstrBlock -genInt64ToInt dst src = do - expect32BitPlatform (text "genInt64ToInt") - RegCode64 code _src_hi src_lo <- iselExpr64 src - let dst_r = getLocalRegReg dst - pure $ code `snocOL` MOV II32 (OpReg src_lo) (OpReg dst_r) - -genWord64ToWord :: LocalReg -> CmmExpr -> NatM InstrBlock -genWord64ToWord dst src = do - expect32BitPlatform (text "genWord64ToWord") - RegCode64 code _src_hi src_lo <- iselExpr64 src - let dst_r = getLocalRegReg dst - pure $ code `snocOL` MOV II32 (OpReg src_lo) (OpReg dst_r) - -genIntToInt64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genIntToInt64 dst src = do - expect32BitPlatform (text "genIntToInt64") - let Reg64 dst_hi dst_lo = localReg64 dst - src_code <- getAnyReg src - pure $ src_code rax `appOL` toOL - [ CLTD II32 -- sign extend EAX in EDX:EAX - , MOV II32 (OpReg rax) (OpReg dst_lo) - , MOV II32 (OpReg rdx) (OpReg dst_hi) - ] - -genWordToWord64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genWordToWord64 dst src = do - expect32BitPlatform (text "genWordToWord64") - let Reg64 dst_hi dst_lo = localReg64 dst - src_code <- getAnyReg src - pure $ src_code dst_lo - `snocOL` XOR II32 (OpReg dst_hi) (OpReg dst_hi) - -genNeg64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genNeg64 dst src = do - expect32BitPlatform (text "genNeg64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 code src_hi src_lo <- iselExpr64 src - pure $ code `appOL` toOL - [ MOV II32 (OpReg src_lo) (OpReg dst_lo) - , MOV II32 (OpReg src_hi) (OpReg dst_hi) - , NEGI II32 (OpReg dst_lo) - , ADC II32 (OpImm (ImmInt 0)) (OpReg dst_hi) - , NEGI II32 (OpReg dst_hi) - ] - -genAdd64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genAdd64 dst x y = do - expect32BitPlatform (text "genAdd64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , ADD II32 (OpReg y_lo) (OpReg dst_lo) - , ADC II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genSub64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genSub64 dst x y = do - expect32BitPlatform (text "genSub64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , SUB II32 (OpReg y_lo) (OpReg dst_lo) - , SBB II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genAnd64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genAnd64 dst x y = do - expect32BitPlatform (text "genAnd64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , AND II32 (OpReg y_lo) (OpReg dst_lo) - , AND II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genOr64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genOr64 dst x y = do - expect32BitPlatform (text "genOr64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , OR II32 (OpReg y_lo) (OpReg dst_lo) - , OR II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genXor64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genXor64 dst x y = do - expect32BitPlatform (text "genXor64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg dst_lo) - , MOV II32 (OpReg x_hi) (OpReg dst_hi) - , XOR II32 (OpReg y_lo) (OpReg dst_lo) - , XOR II32 (OpReg y_hi) (OpReg dst_hi) - ] - -genNot64 :: LocalReg -> CmmExpr -> NatM InstrBlock -genNot64 dst src = do - expect32BitPlatform (text "genNot64") - let Reg64 dst_hi dst_lo = localReg64 dst - RegCode64 src_code src_hi src_lo <- iselExpr64 src - pure $ src_code `appOL` toOL - [ MOV II32 (OpReg src_lo) (OpReg dst_lo) - , MOV II32 (OpReg src_hi) (OpReg dst_hi) - , NOT II32 (OpReg dst_lo) - , NOT II32 (OpReg dst_hi) - ] - -genEq64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genEq64 dst x y = do - expect32BitPlatform (text "genEq64") - let dst_r = getLocalRegReg dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - Reg64 tmp_hi tmp_lo <- getNewReg64 - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg tmp_lo) - , MOV II32 (OpReg x_hi) (OpReg tmp_hi) - , XOR II32 (OpReg y_lo) (OpReg tmp_lo) - , XOR II32 (OpReg y_hi) (OpReg tmp_hi) - , OR II32 (OpReg tmp_lo) (OpReg tmp_hi) - , SETCC EQQ (OpReg dst_r) - , MOVZxL II8 (OpReg dst_r) (OpReg dst_r) - ] - -genNe64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genNe64 dst x y = do - expect32BitPlatform (text "genNe64") - let dst_r = getLocalRegReg dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - Reg64 tmp_hi tmp_lo <- getNewReg64 - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_lo) (OpReg tmp_lo) - , MOV II32 (OpReg x_hi) (OpReg tmp_hi) - , XOR II32 (OpReg y_lo) (OpReg tmp_lo) - , XOR II32 (OpReg y_hi) (OpReg tmp_hi) - , OR II32 (OpReg tmp_lo) (OpReg tmp_hi) - , SETCC NE (OpReg dst_r) - , MOVZxL II8 (OpReg dst_r) (OpReg dst_r) - ] - -genGtWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGtWord64 dst x y = do - expect32BitPlatform (text "genGtWord64") - genPred64 LU dst y x - -genLtWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLtWord64 dst x y = do - expect32BitPlatform (text "genLtWord64") - genPred64 LU dst x y - -genGeWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGeWord64 dst x y = do - expect32BitPlatform (text "genGeWord64") - genPred64 GEU dst x y - -genLeWord64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLeWord64 dst x y = do - expect32BitPlatform (text "genLeWord64") - genPred64 GEU dst y x - -genGtInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGtInt64 dst x y = do - expect32BitPlatform (text "genGtInt64") - genPred64 LTT dst y x - -genLtInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLtInt64 dst x y = do - expect32BitPlatform (text "genLtInt64") - genPred64 LTT dst x y - -genGeInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genGeInt64 dst x y = do - expect32BitPlatform (text "genGeInt64") - genPred64 GE dst x y - -genLeInt64 :: LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genLeInt64 dst x y = do - expect32BitPlatform (text "genLeInt64") - genPred64 GE dst y x - -genPred64 :: Cond -> LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock -genPred64 cond dst x y = do - -- we can only rely on CF/SF/OF flags! - -- Not on ZF, which doesn't take into account the lower parts. - massert (cond `elem` [LU,GEU,LTT,GE]) - - let dst_r = getLocalRegReg dst - RegCode64 x_code x_hi x_lo <- iselExpr64 x - RegCode64 y_code y_hi y_lo <- iselExpr64 y - -- Basically we perform a subtraction with borrow. - -- As we don't need to result, we can use CMP instead of SUB for the low part - -- (it sets the borrow flag just like SUB does) - pure $ x_code `appOL` y_code `appOL` toOL - [ MOV II32 (OpReg x_hi) (OpReg dst_r) - , CMP II32 (OpReg y_lo) (OpReg x_lo) - , SBB II32 (OpReg y_hi) (OpReg dst_r) - , SETCC cond (OpReg dst_r) - , MOVZxL II8 (OpReg dst_r) (OpReg dst_r) - ] ===================================== compiler/GHC/Driver/Config/StgToCmm.hs ===================================== @@ -53,9 +53,12 @@ initStgToCmmConfig dflags mod = StgToCmmConfig , stgToCmmExtDynRefs = gopt Opt_ExternalDynamicRefs dflags , stgToCmmDoBoundsCheck = gopt Opt_DoBoundsChecking dflags , stgToCmmDoTagCheck = gopt Opt_DoTagInferenceChecks dflags - -- backend flags - , stgToCmmAllowBigArith = not ncg || platformArch platform == ArchWasm32 || platformArch platform == ArchX86 - , stgToCmmAllowBigQuot = not ncg || platformArch platform == ArchWasm32 + + -- backend flags: + + -- LLVM, C, and some 32-bit NCG backends can also handle some 64-bit primops + , stgToCmmAllowArith64 = w64 || not ncg || platformArch platform == ArchWasm32 || platformArch platform == ArchX86 + , stgToCmmAllowQuot64 = w64 || not ncg || platformArch platform == ArchWasm32 , stgToCmmAllowQuotRemInstr = ncg && (x86ish || ppc) , stgToCmmAllowQuotRem2 = (ncg && (x86ish || ppc)) || llvm , stgToCmmAllowExtendedAddSubInstrs = (ncg && (x86ish || ppc)) || llvm @@ -90,6 +93,7 @@ initStgToCmmConfig dflags mod = StgToCmmConfig } where profile = targetProfile dflags platform = profilePlatform profile bk_end = backend dflags + w64 = platformWordSize platform == PW8 b_blob = if not ncg then Nothing else binBlobThreshold dflags (ncg, llvm) = case backendPrimitiveImplementation bk_end of GenericPrimitives -> (False, False) ===================================== compiler/GHC/StgToCmm/Config.hs ===================================== @@ -64,8 +64,8 @@ data StgToCmmConfig = StgToCmmConfig -- or not , stgToCmmDoTagCheck :: !Bool -- ^ Verify tag inference predictions. ------------------------------ Backend Flags ---------------------------------- - , stgToCmmAllowBigArith :: !Bool -- ^ Allowed to emit larger than native size arithmetic (only LLVM and C backends) - , stgToCmmAllowBigQuot :: !Bool -- ^ Allowed to emit larger than native size division operations + , stgToCmmAllowArith64 :: !Bool -- ^ Allowed to emit 64-bit arithmetic operations + , stgToCmmAllowQuot64 :: !Bool -- ^ Allowed to emit 64-bit division operations , stgToCmmAllowQuotRemInstr :: !Bool -- ^ Allowed to generate QuotRem instructions , stgToCmmAllowQuotRem2 :: !Bool -- ^ Allowed to generate QuotRem , stgToCmmAllowExtendedAddSubInstrs :: !Bool -- ^ Allowed to generate AddWordC, SubWordC, Add2, etc. ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -334,7 +334,7 @@ emitPrimOp cfg primop = StableNameToIntOp -> \[arg] -> opIntoRegs $ \[res] -> emitAssign (CmmLocal res) (cmmLoadIndexW platform arg (fixedHdrSizeW profile) (bWord platform)) - EqStablePtrOp -> \args -> opTranslate args (mo_wordEq platform) + EqStablePtrOp -> opTranslate (mo_wordEq platform) ReallyUnsafePtrEqualityOp -> \[arg1, arg2] -> opIntoRegs $ \[res] -> emitAssign (CmmLocal res) (CmmMachOp (mo_wordEq platform) [arg1,arg2]) @@ -1180,315 +1180,323 @@ emitPrimOp cfg primop = Narrow16WordOp -> \args -> opNarrow args (MO_UU_Conv, W16) Narrow32WordOp -> \args -> opNarrow args (MO_UU_Conv, W32) - DoublePowerOp -> \args -> opCallish args MO_F64_Pwr - DoubleSinOp -> \args -> opCallish args MO_F64_Sin - DoubleCosOp -> \args -> opCallish args MO_F64_Cos - DoubleTanOp -> \args -> opCallish args MO_F64_Tan - DoubleSinhOp -> \args -> opCallish args MO_F64_Sinh - DoubleCoshOp -> \args -> opCallish args MO_F64_Cosh - DoubleTanhOp -> \args -> opCallish args MO_F64_Tanh - DoubleAsinOp -> \args -> opCallish args MO_F64_Asin - DoubleAcosOp -> \args -> opCallish args MO_F64_Acos - DoubleAtanOp -> \args -> opCallish args MO_F64_Atan - DoubleAsinhOp -> \args -> opCallish args MO_F64_Asinh - DoubleAcoshOp -> \args -> opCallish args MO_F64_Acosh - DoubleAtanhOp -> \args -> opCallish args MO_F64_Atanh - DoubleLogOp -> \args -> opCallish args MO_F64_Log - DoubleLog1POp -> \args -> opCallish args MO_F64_Log1P - DoubleExpOp -> \args -> opCallish args MO_F64_Exp - DoubleExpM1Op -> \args -> opCallish args MO_F64_ExpM1 - DoubleSqrtOp -> \args -> opCallish args MO_F64_Sqrt - DoubleFabsOp -> \args -> opCallish args MO_F64_Fabs - - FloatPowerOp -> \args -> opCallish args MO_F32_Pwr - FloatSinOp -> \args -> opCallish args MO_F32_Sin - FloatCosOp -> \args -> opCallish args MO_F32_Cos - FloatTanOp -> \args -> opCallish args MO_F32_Tan - FloatSinhOp -> \args -> opCallish args MO_F32_Sinh - FloatCoshOp -> \args -> opCallish args MO_F32_Cosh - FloatTanhOp -> \args -> opCallish args MO_F32_Tanh - FloatAsinOp -> \args -> opCallish args MO_F32_Asin - FloatAcosOp -> \args -> opCallish args MO_F32_Acos - FloatAtanOp -> \args -> opCallish args MO_F32_Atan - FloatAsinhOp -> \args -> opCallish args MO_F32_Asinh - FloatAcoshOp -> \args -> opCallish args MO_F32_Acosh - FloatAtanhOp -> \args -> opCallish args MO_F32_Atanh - FloatLogOp -> \args -> opCallish args MO_F32_Log - FloatLog1POp -> \args -> opCallish args MO_F32_Log1P - FloatExpOp -> \args -> opCallish args MO_F32_Exp - FloatExpM1Op -> \args -> opCallish args MO_F32_ExpM1 - FloatSqrtOp -> \args -> opCallish args MO_F32_Sqrt - FloatFabsOp -> \args -> opCallish args MO_F32_Fabs + DoublePowerOp -> opCallish MO_F64_Pwr + DoubleSinOp -> opCallish MO_F64_Sin + DoubleCosOp -> opCallish MO_F64_Cos + DoubleTanOp -> opCallish MO_F64_Tan + DoubleSinhOp -> opCallish MO_F64_Sinh + DoubleCoshOp -> opCallish MO_F64_Cosh + DoubleTanhOp -> opCallish MO_F64_Tanh + DoubleAsinOp -> opCallish MO_F64_Asin + DoubleAcosOp -> opCallish MO_F64_Acos + DoubleAtanOp -> opCallish MO_F64_Atan + DoubleAsinhOp -> opCallish MO_F64_Asinh + DoubleAcoshOp -> opCallish MO_F64_Acosh + DoubleAtanhOp -> opCallish MO_F64_Atanh + DoubleLogOp -> opCallish MO_F64_Log + DoubleLog1POp -> opCallish MO_F64_Log1P + DoubleExpOp -> opCallish MO_F64_Exp + DoubleExpM1Op -> opCallish MO_F64_ExpM1 + DoubleSqrtOp -> opCallish MO_F64_Sqrt + DoubleFabsOp -> opCallish MO_F64_Fabs + + FloatPowerOp -> opCallish MO_F32_Pwr + FloatSinOp -> opCallish MO_F32_Sin + FloatCosOp -> opCallish MO_F32_Cos + FloatTanOp -> opCallish MO_F32_Tan + FloatSinhOp -> opCallish MO_F32_Sinh + FloatCoshOp -> opCallish MO_F32_Cosh + FloatTanhOp -> opCallish MO_F32_Tanh + FloatAsinOp -> opCallish MO_F32_Asin + FloatAcosOp -> opCallish MO_F32_Acos + FloatAtanOp -> opCallish MO_F32_Atan + FloatAsinhOp -> opCallish MO_F32_Asinh + FloatAcoshOp -> opCallish MO_F32_Acosh + FloatAtanhOp -> opCallish MO_F32_Atanh + FloatLogOp -> opCallish MO_F32_Log + FloatLog1POp -> opCallish MO_F32_Log1P + FloatExpOp -> opCallish MO_F32_Exp + FloatExpM1Op -> opCallish MO_F32_ExpM1 + FloatSqrtOp -> opCallish MO_F32_Sqrt + FloatFabsOp -> opCallish MO_F32_Fabs -- Native word signless ops - IntAddOp -> \args -> opTranslate args (mo_wordAdd platform) - IntSubOp -> \args -> opTranslate args (mo_wordSub platform) - WordAddOp -> \args -> opTranslate args (mo_wordAdd platform) - WordSubOp -> \args -> opTranslate args (mo_wordSub platform) - AddrAddOp -> \args -> opTranslate args (mo_wordAdd platform) - AddrSubOp -> \args -> opTranslate args (mo_wordSub platform) - - IntEqOp -> \args -> opTranslate args (mo_wordEq platform) - IntNeOp -> \args -> opTranslate args (mo_wordNe platform) - WordEqOp -> \args -> opTranslate args (mo_wordEq platform) - WordNeOp -> \args -> opTranslate args (mo_wordNe platform) - AddrEqOp -> \args -> opTranslate args (mo_wordEq platform) - AddrNeOp -> \args -> opTranslate args (mo_wordNe platform) - - WordAndOp -> \args -> opTranslate args (mo_wordAnd platform) - WordOrOp -> \args -> opTranslate args (mo_wordOr platform) - WordXorOp -> \args -> opTranslate args (mo_wordXor platform) - WordNotOp -> \args -> opTranslate args (mo_wordNot platform) - WordSllOp -> \args -> opTranslate args (mo_wordShl platform) - WordSrlOp -> \args -> opTranslate args (mo_wordUShr platform) - - AddrRemOp -> \args -> opTranslate args (mo_wordURem platform) + IntAddOp -> opTranslate (mo_wordAdd platform) + IntSubOp -> opTranslate (mo_wordSub platform) + WordAddOp -> opTranslate (mo_wordAdd platform) + WordSubOp -> opTranslate (mo_wordSub platform) + AddrAddOp -> opTranslate (mo_wordAdd platform) + AddrSubOp -> opTranslate (mo_wordSub platform) + + IntEqOp -> opTranslate (mo_wordEq platform) + IntNeOp -> opTranslate (mo_wordNe platform) + WordEqOp -> opTranslate (mo_wordEq platform) + WordNeOp -> opTranslate (mo_wordNe platform) + AddrEqOp -> opTranslate (mo_wordEq platform) + AddrNeOp -> opTranslate (mo_wordNe platform) + + WordAndOp -> opTranslate (mo_wordAnd platform) + WordOrOp -> opTranslate (mo_wordOr platform) + WordXorOp -> opTranslate (mo_wordXor platform) + WordNotOp -> opTranslate (mo_wordNot platform) + WordSllOp -> opTranslate (mo_wordShl platform) + WordSrlOp -> opTranslate (mo_wordUShr platform) + + AddrRemOp -> opTranslate (mo_wordURem platform) -- Native word signed ops - IntMulOp -> \args -> opTranslate args (mo_wordMul platform) - IntMulMayOfloOp -> \args -> opTranslate args (MO_S_MulMayOflo (wordWidth platform)) - IntQuotOp -> \args -> opTranslate args (mo_wordSQuot platform) - IntRemOp -> \args -> opTranslate args (mo_wordSRem platform) - IntNegOp -> \args -> opTranslate args (mo_wordSNeg platform) - - IntGeOp -> \args -> opTranslate args (mo_wordSGe platform) - IntLeOp -> \args -> opTranslate args (mo_wordSLe platform) - IntGtOp -> \args -> opTranslate args (mo_wordSGt platform) - IntLtOp -> \args -> opTranslate args (mo_wordSLt platform) - - IntAndOp -> \args -> opTranslate args (mo_wordAnd platform) - IntOrOp -> \args -> opTranslate args (mo_wordOr platform) - IntXorOp -> \args -> opTranslate args (mo_wordXor platform) - IntNotOp -> \args -> opTranslate args (mo_wordNot platform) - IntSllOp -> \args -> opTranslate args (mo_wordShl platform) - IntSraOp -> \args -> opTranslate args (mo_wordSShr platform) - IntSrlOp -> \args -> opTranslate args (mo_wordUShr platform) + IntMulOp -> opTranslate (mo_wordMul platform) + IntMulMayOfloOp -> opTranslate (MO_S_MulMayOflo (wordWidth platform)) + IntQuotOp -> opTranslate (mo_wordSQuot platform) + IntRemOp -> opTranslate (mo_wordSRem platform) + IntNegOp -> opTranslate (mo_wordSNeg platform) + + IntGeOp -> opTranslate (mo_wordSGe platform) + IntLeOp -> opTranslate (mo_wordSLe platform) + IntGtOp -> opTranslate (mo_wordSGt platform) + IntLtOp -> opTranslate (mo_wordSLt platform) + + IntAndOp -> opTranslate (mo_wordAnd platform) + IntOrOp -> opTranslate (mo_wordOr platform) + IntXorOp -> opTranslate (mo_wordXor platform) + IntNotOp -> opTranslate (mo_wordNot platform) + IntSllOp -> opTranslate (mo_wordShl platform) + IntSraOp -> opTranslate (mo_wordSShr platform) + IntSrlOp -> opTranslate (mo_wordUShr platform) -- Native word unsigned ops - WordGeOp -> \args -> opTranslate args (mo_wordUGe platform) - WordLeOp -> \args -> opTranslate args (mo_wordULe platform) - WordGtOp -> \args -> opTranslate args (mo_wordUGt platform) - WordLtOp -> \args -> opTranslate args (mo_wordULt platform) + WordGeOp -> opTranslate (mo_wordUGe platform) + WordLeOp -> opTranslate (mo_wordULe platform) + WordGtOp -> opTranslate (mo_wordUGt platform) + WordLtOp -> opTranslate (mo_wordULt platform) - WordMulOp -> \args -> opTranslate args (mo_wordMul platform) - WordQuotOp -> \args -> opTranslate args (mo_wordUQuot platform) - WordRemOp -> \args -> opTranslate args (mo_wordURem platform) + WordMulOp -> opTranslate (mo_wordMul platform) + WordQuotOp -> opTranslate (mo_wordUQuot platform) + WordRemOp -> opTranslate (mo_wordURem platform) - AddrGeOp -> \args -> opTranslate args (mo_wordUGe platform) - AddrLeOp -> \args -> opTranslate args (mo_wordULe platform) - AddrGtOp -> \args -> opTranslate args (mo_wordUGt platform) - AddrLtOp -> \args -> opTranslate args (mo_wordULt platform) + AddrGeOp -> opTranslate (mo_wordUGe platform) + AddrLeOp -> opTranslate (mo_wordULe platform) + AddrGtOp -> opTranslate (mo_wordUGt platform) + AddrLtOp -> opTranslate (mo_wordULt platform) -- Int8# signed ops - Int8ToIntOp -> \args -> opTranslate args (MO_SS_Conv W8 (wordWidth platform)) - IntToInt8Op -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W8) - Int8NegOp -> \args -> opTranslate args (MO_S_Neg W8) - Int8AddOp -> \args -> opTranslate args (MO_Add W8) - Int8SubOp -> \args -> opTranslate args (MO_Sub W8) - Int8MulOp -> \args -> opTranslate args (MO_Mul W8) - Int8QuotOp -> \args -> opTranslate args (MO_S_Quot W8) - Int8RemOp -> \args -> opTranslate args (MO_S_Rem W8) - - Int8SllOp -> \args -> opTranslate args (MO_Shl W8) - Int8SraOp -> \args -> opTranslate args (MO_S_Shr W8) - Int8SrlOp -> \args -> opTranslate args (MO_U_Shr W8) - - Int8EqOp -> \args -> opTranslate args (MO_Eq W8) - Int8GeOp -> \args -> opTranslate args (MO_S_Ge W8) - Int8GtOp -> \args -> opTranslate args (MO_S_Gt W8) - Int8LeOp -> \args -> opTranslate args (MO_S_Le W8) - Int8LtOp -> \args -> opTranslate args (MO_S_Lt W8) - Int8NeOp -> \args -> opTranslate args (MO_Ne W8) + Int8ToIntOp -> opTranslate (MO_SS_Conv W8 (wordWidth platform)) + IntToInt8Op -> opTranslate (MO_SS_Conv (wordWidth platform) W8) + Int8NegOp -> opTranslate (MO_S_Neg W8) + Int8AddOp -> opTranslate (MO_Add W8) + Int8SubOp -> opTranslate (MO_Sub W8) + Int8MulOp -> opTranslate (MO_Mul W8) + Int8QuotOp -> opTranslate (MO_S_Quot W8) + Int8RemOp -> opTranslate (MO_S_Rem W8) + + Int8SllOp -> opTranslate (MO_Shl W8) + Int8SraOp -> opTranslate (MO_S_Shr W8) + Int8SrlOp -> opTranslate (MO_U_Shr W8) + + Int8EqOp -> opTranslate (MO_Eq W8) + Int8GeOp -> opTranslate (MO_S_Ge W8) + Int8GtOp -> opTranslate (MO_S_Gt W8) + Int8LeOp -> opTranslate (MO_S_Le W8) + Int8LtOp -> opTranslate (MO_S_Lt W8) + Int8NeOp -> opTranslate (MO_Ne W8) -- Word8# unsigned ops - Word8ToWordOp -> \args -> opTranslate args (MO_UU_Conv W8 (wordWidth platform)) - WordToWord8Op -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W8) - Word8AddOp -> \args -> opTranslate args (MO_Add W8) - Word8SubOp -> \args -> opTranslate args (MO_Sub W8) - Word8MulOp -> \args -> opTranslate args (MO_Mul W8) - Word8QuotOp -> \args -> opTranslate args (MO_U_Quot W8) - Word8RemOp -> \args -> opTranslate args (MO_U_Rem W8) - - Word8AndOp -> \args -> opTranslate args (MO_And W8) - Word8OrOp -> \args -> opTranslate args (MO_Or W8) - Word8XorOp -> \args -> opTranslate args (MO_Xor W8) - Word8NotOp -> \args -> opTranslate args (MO_Not W8) - Word8SllOp -> \args -> opTranslate args (MO_Shl W8) - Word8SrlOp -> \args -> opTranslate args (MO_U_Shr W8) - - Word8EqOp -> \args -> opTranslate args (MO_Eq W8) - Word8GeOp -> \args -> opTranslate args (MO_U_Ge W8) - Word8GtOp -> \args -> opTranslate args (MO_U_Gt W8) - Word8LeOp -> \args -> opTranslate args (MO_U_Le W8) - Word8LtOp -> \args -> opTranslate args (MO_U_Lt W8) - Word8NeOp -> \args -> opTranslate args (MO_Ne W8) + Word8ToWordOp -> opTranslate (MO_UU_Conv W8 (wordWidth platform)) + WordToWord8Op -> opTranslate (MO_UU_Conv (wordWidth platform) W8) + Word8AddOp -> opTranslate (MO_Add W8) + Word8SubOp -> opTranslate (MO_Sub W8) + Word8MulOp -> opTranslate (MO_Mul W8) + Word8QuotOp -> opTranslate (MO_U_Quot W8) + Word8RemOp -> opTranslate (MO_U_Rem W8) + + Word8AndOp -> opTranslate (MO_And W8) + Word8OrOp -> opTranslate (MO_Or W8) + Word8XorOp -> opTranslate (MO_Xor W8) + Word8NotOp -> opTranslate (MO_Not W8) + Word8SllOp -> opTranslate (MO_Shl W8) + Word8SrlOp -> opTranslate (MO_U_Shr W8) + + Word8EqOp -> opTranslate (MO_Eq W8) + Word8GeOp -> opTranslate (MO_U_Ge W8) + Word8GtOp -> opTranslate (MO_U_Gt W8) + Word8LeOp -> opTranslate (MO_U_Le W8) + Word8LtOp -> opTranslate (MO_U_Lt W8) + Word8NeOp -> opTranslate (MO_Ne W8) -- Int16# signed ops - Int16ToIntOp -> \args -> opTranslate args (MO_SS_Conv W16 (wordWidth platform)) - IntToInt16Op -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W16) - Int16NegOp -> \args -> opTranslate args (MO_S_Neg W16) - Int16AddOp -> \args -> opTranslate args (MO_Add W16) - Int16SubOp -> \args -> opTranslate args (MO_Sub W16) - Int16MulOp -> \args -> opTranslate args (MO_Mul W16) - Int16QuotOp -> \args -> opTranslate args (MO_S_Quot W16) - Int16RemOp -> \args -> opTranslate args (MO_S_Rem W16) - - Int16SllOp -> \args -> opTranslate args (MO_Shl W16) - Int16SraOp -> \args -> opTranslate args (MO_S_Shr W16) - Int16SrlOp -> \args -> opTranslate args (MO_U_Shr W16) - - Int16EqOp -> \args -> opTranslate args (MO_Eq W16) - Int16GeOp -> \args -> opTranslate args (MO_S_Ge W16) - Int16GtOp -> \args -> opTranslate args (MO_S_Gt W16) - Int16LeOp -> \args -> opTranslate args (MO_S_Le W16) - Int16LtOp -> \args -> opTranslate args (MO_S_Lt W16) - Int16NeOp -> \args -> opTranslate args (MO_Ne W16) + Int16ToIntOp -> opTranslate (MO_SS_Conv W16 (wordWidth platform)) + IntToInt16Op -> opTranslate (MO_SS_Conv (wordWidth platform) W16) + Int16NegOp -> opTranslate (MO_S_Neg W16) + Int16AddOp -> opTranslate (MO_Add W16) + Int16SubOp -> opTranslate (MO_Sub W16) + Int16MulOp -> opTranslate (MO_Mul W16) + Int16QuotOp -> opTranslate (MO_S_Quot W16) + Int16RemOp -> opTranslate (MO_S_Rem W16) + + Int16SllOp -> opTranslate (MO_Shl W16) + Int16SraOp -> opTranslate (MO_S_Shr W16) + Int16SrlOp -> opTranslate (MO_U_Shr W16) + + Int16EqOp -> opTranslate (MO_Eq W16) + Int16GeOp -> opTranslate (MO_S_Ge W16) + Int16GtOp -> opTranslate (MO_S_Gt W16) + Int16LeOp -> opTranslate (MO_S_Le W16) + Int16LtOp -> opTranslate (MO_S_Lt W16) + Int16NeOp -> opTranslate (MO_Ne W16) -- Word16# unsigned ops - Word16ToWordOp -> \args -> opTranslate args (MO_UU_Conv W16 (wordWidth platform)) - WordToWord16Op -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W16) - Word16AddOp -> \args -> opTranslate args (MO_Add W16) - Word16SubOp -> \args -> opTranslate args (MO_Sub W16) - Word16MulOp -> \args -> opTranslate args (MO_Mul W16) - Word16QuotOp -> \args -> opTranslate args (MO_U_Quot W16) - Word16RemOp -> \args -> opTranslate args (MO_U_Rem W16) - - Word16AndOp -> \args -> opTranslate args (MO_And W16) - Word16OrOp -> \args -> opTranslate args (MO_Or W16) - Word16XorOp -> \args -> opTranslate args (MO_Xor W16) - Word16NotOp -> \args -> opTranslate args (MO_Not W16) - Word16SllOp -> \args -> opTranslate args (MO_Shl W16) - Word16SrlOp -> \args -> opTranslate args (MO_U_Shr W16) - - Word16EqOp -> \args -> opTranslate args (MO_Eq W16) - Word16GeOp -> \args -> opTranslate args (MO_U_Ge W16) - Word16GtOp -> \args -> opTranslate args (MO_U_Gt W16) - Word16LeOp -> \args -> opTranslate args (MO_U_Le W16) - Word16LtOp -> \args -> opTranslate args (MO_U_Lt W16) - Word16NeOp -> \args -> opTranslate args (MO_Ne W16) + Word16ToWordOp -> opTranslate (MO_UU_Conv W16 (wordWidth platform)) + WordToWord16Op -> opTranslate (MO_UU_Conv (wordWidth platform) W16) + Word16AddOp -> opTranslate (MO_Add W16) + Word16SubOp -> opTranslate (MO_Sub W16) + Word16MulOp -> opTranslate (MO_Mul W16) + Word16QuotOp -> opTranslate (MO_U_Quot W16) + Word16RemOp -> opTranslate (MO_U_Rem W16) + + Word16AndOp -> opTranslate (MO_And W16) + Word16OrOp -> opTranslate (MO_Or W16) + Word16XorOp -> opTranslate (MO_Xor W16) + Word16NotOp -> opTranslate (MO_Not W16) + Word16SllOp -> opTranslate (MO_Shl W16) + Word16SrlOp -> opTranslate (MO_U_Shr W16) + + Word16EqOp -> opTranslate (MO_Eq W16) + Word16GeOp -> opTranslate (MO_U_Ge W16) + Word16GtOp -> opTranslate (MO_U_Gt W16) + Word16LeOp -> opTranslate (MO_U_Le W16) + Word16LtOp -> opTranslate (MO_U_Lt W16) + Word16NeOp -> opTranslate (MO_Ne W16) -- Int32# signed ops - Int32ToIntOp -> \args -> opTranslate args (MO_SS_Conv W32 (wordWidth platform)) - IntToInt32Op -> \args -> opTranslate args (MO_SS_Conv (wordWidth platform) W32) - Int32NegOp -> \args -> opTranslate args (MO_S_Neg W32) - Int32AddOp -> \args -> opTranslate args (MO_Add W32) - Int32SubOp -> \args -> opTranslate args (MO_Sub W32) - Int32MulOp -> \args -> opTranslate args (MO_Mul W32) - Int32QuotOp -> \args -> opTranslate args (MO_S_Quot W32) - Int32RemOp -> \args -> opTranslate args (MO_S_Rem W32) - - Int32SllOp -> \args -> opTranslate args (MO_Shl W32) - Int32SraOp -> \args -> opTranslate args (MO_S_Shr W32) - Int32SrlOp -> \args -> opTranslate args (MO_U_Shr W32) - - Int32EqOp -> \args -> opTranslate args (MO_Eq W32) - Int32GeOp -> \args -> opTranslate args (MO_S_Ge W32) - Int32GtOp -> \args -> opTranslate args (MO_S_Gt W32) - Int32LeOp -> \args -> opTranslate args (MO_S_Le W32) - Int32LtOp -> \args -> opTranslate args (MO_S_Lt W32) - Int32NeOp -> \args -> opTranslate args (MO_Ne W32) + Int32ToIntOp -> opTranslate (MO_SS_Conv W32 (wordWidth platform)) + IntToInt32Op -> opTranslate (MO_SS_Conv (wordWidth platform) W32) + Int32NegOp -> opTranslate (MO_S_Neg W32) + Int32AddOp -> opTranslate (MO_Add W32) + Int32SubOp -> opTranslate (MO_Sub W32) + Int32MulOp -> opTranslate (MO_Mul W32) + Int32QuotOp -> opTranslate (MO_S_Quot W32) + Int32RemOp -> opTranslate (MO_S_Rem W32) + + Int32SllOp -> opTranslate (MO_Shl W32) + Int32SraOp -> opTranslate (MO_S_Shr W32) + Int32SrlOp -> opTranslate (MO_U_Shr W32) + + Int32EqOp -> opTranslate (MO_Eq W32) + Int32GeOp -> opTranslate (MO_S_Ge W32) + Int32GtOp -> opTranslate (MO_S_Gt W32) + Int32LeOp -> opTranslate (MO_S_Le W32) + Int32LtOp -> opTranslate (MO_S_Lt W32) + Int32NeOp -> opTranslate (MO_Ne W32) -- Word32# unsigned ops - Word32ToWordOp -> \args -> opTranslate args (MO_UU_Conv W32 (wordWidth platform)) - WordToWord32Op -> \args -> opTranslate args (MO_UU_Conv (wordWidth platform) W32) - Word32AddOp -> \args -> opTranslate args (MO_Add W32) - Word32SubOp -> \args -> opTranslate args (MO_Sub W32) - Word32MulOp -> \args -> opTranslate args (MO_Mul W32) - Word32QuotOp -> \args -> opTranslate args (MO_U_Quot W32) - Word32RemOp -> \args -> opTranslate args (MO_U_Rem W32) - - Word32AndOp -> \args -> opTranslate args (MO_And W32) - Word32OrOp -> \args -> opTranslate args (MO_Or W32) - Word32XorOp -> \args -> opTranslate args (MO_Xor W32) - Word32NotOp -> \args -> opTranslate args (MO_Not W32) - Word32SllOp -> \args -> opTranslate args (MO_Shl W32) - Word32SrlOp -> \args -> opTranslate args (MO_U_Shr W32) - - Word32EqOp -> \args -> opTranslate args (MO_Eq W32) - Word32GeOp -> \args -> opTranslate args (MO_U_Ge W32) - Word32GtOp -> \args -> opTranslate args (MO_U_Gt W32) - Word32LeOp -> \args -> opTranslate args (MO_U_Le W32) - Word32LtOp -> \args -> opTranslate args (MO_U_Lt W32) - Word32NeOp -> \args -> opTranslate args (MO_Ne W32) + Word32ToWordOp -> opTranslate (MO_UU_Conv W32 (wordWidth platform)) + WordToWord32Op -> opTranslate (MO_UU_Conv (wordWidth platform) W32) + Word32AddOp -> opTranslate (MO_Add W32) + Word32SubOp -> opTranslate (MO_Sub W32) + Word32MulOp -> opTranslate (MO_Mul W32) + Word32QuotOp -> opTranslate (MO_U_Quot W32) + Word32RemOp -> opTranslate (MO_U_Rem W32) + + Word32AndOp -> opTranslate (MO_And W32) + Word32OrOp -> opTranslate (MO_Or W32) + Word32XorOp -> opTranslate (MO_Xor W32) + Word32NotOp -> opTranslate (MO_Not W32) + Word32SllOp -> opTranslate (MO_Shl W32) + Word32SrlOp -> opTranslate (MO_U_Shr W32) + + Word32EqOp -> opTranslate (MO_Eq W32) + Word32GeOp -> opTranslate (MO_U_Ge W32) + Word32GtOp -> opTranslate (MO_U_Gt W32) + Word32LeOp -> opTranslate (MO_U_Le W32) + Word32LtOp -> opTranslate (MO_U_Lt W32) + Word32NeOp -> opTranslate (MO_Ne W32) -- Int64# signed ops - Int64ToIntOp -> \args -> opTranslate64 args (\w -> MO_SS_Conv w (wordWidth platform)) MO_I64_ToI - IntToInt64Op -> \args -> opTranslate64 args (\w -> MO_SS_Conv (wordWidth platform) w) MO_I64_FromI - Int64NegOp -> \args -> opTranslate64 args MO_S_Neg MO_x64_Neg - Int64AddOp -> \args -> opTranslate64 args MO_Add MO_x64_Add - Int64SubOp -> \args -> opTranslate64 args MO_Sub MO_x64_Sub - Int64MulOp -> \args -> opTranslate64 args MO_Mul MO_x64_Mul - Int64QuotOp -> \args -> opTranslate64 args MO_S_Quot MO_I64_Quot - Int64RemOp -> \args -> opTranslate64 args MO_S_Rem MO_I64_Rem - - Int64SllOp -> \args -> opTranslate64 args MO_Shl MO_x64_Shl - Int64SraOp -> \args -> opTranslate64 args MO_S_Shr MO_I64_Shr - Int64SrlOp -> \args -> opTranslate64 args MO_U_Shr MO_W64_Shr - - Int64EqOp -> \args -> opTranslate64 args MO_Eq MO_x64_Eq - Int64GeOp -> \args -> opTranslate64 args MO_S_Ge MO_I64_Ge - Int64GtOp -> \args -> opTranslate64 args MO_S_Gt MO_I64_Gt - Int64LeOp -> \args -> opTranslate64 args MO_S_Le MO_I64_Le - Int64LtOp -> \args -> opTranslate64 args MO_S_Lt MO_I64_Lt - Int64NeOp -> \args -> opTranslate64 args MO_Ne MO_x64_Ne + Int64ToIntOp -> opTranslate64 (MO_SS_Conv W64 (wordWidth platform)) MO_I64_ToI + IntToInt64Op -> opTranslate64 (MO_SS_Conv (wordWidth platform) W64) MO_I64_FromI + Int64NegOp -> opTranslate64 (MO_S_Neg W64) MO_x64_Neg + Int64AddOp -> opTranslate64 (MO_Add W64) MO_x64_Add + Int64SubOp -> opTranslate64 (MO_Sub W64) MO_x64_Sub + Int64MulOp -> opTranslate64 (MO_Mul W64) MO_x64_Mul + Int64QuotOp + | allowQuot64 -> opTranslate (MO_S_Quot W64) + | otherwise -> opCallish MO_I64_Quot + Int64RemOp + | allowQuot64 -> opTranslate (MO_S_Rem W64) + | otherwise -> opCallish MO_I64_Rem + + Int64SllOp -> opTranslate64 (MO_Shl W64) MO_x64_Shl + Int64SraOp -> opTranslate64 (MO_S_Shr W64) MO_I64_Shr + Int64SrlOp -> opTranslate64 (MO_U_Shr W64) MO_W64_Shr + + Int64EqOp -> opTranslate64 (MO_Eq W64) MO_x64_Eq + Int64GeOp -> opTranslate64 (MO_S_Ge W64) MO_I64_Ge + Int64GtOp -> opTranslate64 (MO_S_Gt W64) MO_I64_Gt + Int64LeOp -> opTranslate64 (MO_S_Le W64) MO_I64_Le + Int64LtOp -> opTranslate64 (MO_S_Lt W64) MO_I64_Lt + Int64NeOp -> opTranslate64 (MO_Ne W64) MO_x64_Ne -- Word64# unsigned ops - Word64ToWordOp -> \args -> opTranslate64 args (\w -> MO_UU_Conv w (wordWidth platform)) MO_W64_ToW - WordToWord64Op -> \args -> opTranslate64 args (\w -> MO_UU_Conv (wordWidth platform) w) MO_W64_FromW - Word64AddOp -> \args -> opTranslate64 args MO_Add MO_x64_Add - Word64SubOp -> \args -> opTranslate64 args MO_Sub MO_x64_Sub - Word64MulOp -> \args -> opTranslate64 args MO_Mul MO_x64_Mul - Word64QuotOp -> \args -> opTranslate64 args MO_U_Quot MO_W64_Quot - Word64RemOp -> \args -> opTranslate64 args MO_U_Rem MO_W64_Rem - - Word64AndOp -> \args -> opTranslate64 args MO_And MO_x64_And - Word64OrOp -> \args -> opTranslate64 args MO_Or MO_x64_Or - Word64XorOp -> \args -> opTranslate64 args MO_Xor MO_x64_Xor - Word64NotOp -> \args -> opTranslate64 args MO_Not MO_x64_Not - Word64SllOp -> \args -> opTranslate64 args MO_Shl MO_x64_Shl - Word64SrlOp -> \args -> opTranslate64 args MO_U_Shr MO_W64_Shr - - Word64EqOp -> \args -> opTranslate64 args MO_Eq MO_x64_Eq - Word64GeOp -> \args -> opTranslate64 args MO_U_Ge MO_W64_Ge - Word64GtOp -> \args -> opTranslate64 args MO_U_Gt MO_W64_Gt - Word64LeOp -> \args -> opTranslate64 args MO_U_Le MO_W64_Le - Word64LtOp -> \args -> opTranslate64 args MO_U_Lt MO_W64_Lt - Word64NeOp -> \args -> opTranslate64 args MO_Ne MO_x64_Ne + Word64ToWordOp -> opTranslate64 (MO_UU_Conv W64 (wordWidth platform)) MO_W64_ToW + WordToWord64Op -> opTranslate64 (MO_UU_Conv (wordWidth platform) W64) MO_W64_FromW + Word64AddOp -> opTranslate64 (MO_Add W64) MO_x64_Add + Word64SubOp -> opTranslate64 (MO_Sub W64) MO_x64_Sub + Word64MulOp -> opTranslate64 (MO_Mul W64) MO_x64_Mul + Word64QuotOp + | allowQuot64 -> opTranslate (MO_U_Quot W64) + | otherwise -> opCallish MO_W64_Quot + Word64RemOp + | allowQuot64 -> opTranslate (MO_U_Rem W64) + | otherwise -> opCallish MO_W64_Rem + + Word64AndOp -> opTranslate64 (MO_And W64) MO_x64_And + Word64OrOp -> opTranslate64 (MO_Or W64) MO_x64_Or + Word64XorOp -> opTranslate64 (MO_Xor W64) MO_x64_Xor + Word64NotOp -> opTranslate64 (MO_Not W64) MO_x64_Not + Word64SllOp -> opTranslate64 (MO_Shl W64) MO_x64_Shl + Word64SrlOp -> opTranslate64 (MO_U_Shr W64) MO_W64_Shr + + Word64EqOp -> opTranslate64 (MO_Eq W64) MO_x64_Eq + Word64GeOp -> opTranslate64 (MO_U_Ge W64) MO_W64_Ge + Word64GtOp -> opTranslate64 (MO_U_Gt W64) MO_W64_Gt + Word64LeOp -> opTranslate64 (MO_U_Le W64) MO_W64_Le + Word64LtOp -> opTranslate64 (MO_U_Lt W64) MO_W64_Lt + Word64NeOp -> opTranslate64 (MO_Ne W64) MO_x64_Ne -- Char# ops - CharEqOp -> \args -> opTranslate args (MO_Eq (wordWidth platform)) - CharNeOp -> \args -> opTranslate args (MO_Ne (wordWidth platform)) - CharGeOp -> \args -> opTranslate args (MO_U_Ge (wordWidth platform)) - CharLeOp -> \args -> opTranslate args (MO_U_Le (wordWidth platform)) - CharGtOp -> \args -> opTranslate args (MO_U_Gt (wordWidth platform)) - CharLtOp -> \args -> opTranslate args (MO_U_Lt (wordWidth platform)) + CharEqOp -> opTranslate (MO_Eq (wordWidth platform)) + CharNeOp -> opTranslate (MO_Ne (wordWidth platform)) + CharGeOp -> opTranslate (MO_U_Ge (wordWidth platform)) + CharLeOp -> opTranslate (MO_U_Le (wordWidth platform)) + CharGtOp -> opTranslate (MO_U_Gt (wordWidth platform)) + CharLtOp -> opTranslate (MO_U_Lt (wordWidth platform)) -- Double ops - DoubleEqOp -> \args -> opTranslate args (MO_F_Eq W64) - DoubleNeOp -> \args -> opTranslate args (MO_F_Ne W64) - DoubleGeOp -> \args -> opTranslate args (MO_F_Ge W64) - DoubleLeOp -> \args -> opTranslate args (MO_F_Le W64) - DoubleGtOp -> \args -> opTranslate args (MO_F_Gt W64) - DoubleLtOp -> \args -> opTranslate args (MO_F_Lt W64) + DoubleEqOp -> opTranslate (MO_F_Eq W64) + DoubleNeOp -> opTranslate (MO_F_Ne W64) + DoubleGeOp -> opTranslate (MO_F_Ge W64) + DoubleLeOp -> opTranslate (MO_F_Le W64) + DoubleGtOp -> opTranslate (MO_F_Gt W64) + DoubleLtOp -> opTranslate (MO_F_Lt W64) - DoubleAddOp -> \args -> opTranslate args (MO_F_Add W64) - DoubleSubOp -> \args -> opTranslate args (MO_F_Sub W64) - DoubleMulOp -> \args -> opTranslate args (MO_F_Mul W64) - DoubleDivOp -> \args -> opTranslate args (MO_F_Quot W64) - DoubleNegOp -> \args -> opTranslate args (MO_F_Neg W64) + DoubleAddOp -> opTranslate (MO_F_Add W64) + DoubleSubOp -> opTranslate (MO_F_Sub W64) + DoubleMulOp -> opTranslate (MO_F_Mul W64) + DoubleDivOp -> opTranslate (MO_F_Quot W64) + DoubleNegOp -> opTranslate (MO_F_Neg W64) DoubleFMAdd -> fmaOp FMAdd W64 DoubleFMSub -> fmaOp FMSub W64 @@ -1497,18 +1505,18 @@ emitPrimOp cfg primop = -- Float ops - FloatEqOp -> \args -> opTranslate args (MO_F_Eq W32) - FloatNeOp -> \args -> opTranslate args (MO_F_Ne W32) - FloatGeOp -> \args -> opTranslate args (MO_F_Ge W32) - FloatLeOp -> \args -> opTranslate args (MO_F_Le W32) - FloatGtOp -> \args -> opTranslate args (MO_F_Gt W32) - FloatLtOp -> \args -> opTranslate args (MO_F_Lt W32) + FloatEqOp -> opTranslate (MO_F_Eq W32) + FloatNeOp -> opTranslate (MO_F_Ne W32) + FloatGeOp -> opTranslate (MO_F_Ge W32) + FloatLeOp -> opTranslate (MO_F_Le W32) + FloatGtOp -> opTranslate (MO_F_Gt W32) + FloatLtOp -> opTranslate (MO_F_Lt W32) - FloatAddOp -> \args -> opTranslate args (MO_F_Add W32) - FloatSubOp -> \args -> opTranslate args (MO_F_Sub W32) - FloatMulOp -> \args -> opTranslate args (MO_F_Mul W32) - FloatDivOp -> \args -> opTranslate args (MO_F_Quot W32) - FloatNegOp -> \args -> opTranslate args (MO_F_Neg W32) + FloatAddOp -> opTranslate (MO_F_Add W32) + FloatSubOp -> opTranslate (MO_F_Sub W32) + FloatMulOp -> opTranslate (MO_F_Mul W32) + FloatDivOp -> opTranslate (MO_F_Quot W32) + FloatNegOp -> opTranslate (MO_F_Neg W32) FloatFMAdd -> fmaOp FMAdd W32 FloatFMSub -> fmaOp FMSub W32 @@ -1517,126 +1525,122 @@ emitPrimOp cfg primop = -- Vector ops - (VecAddOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Add n w) - (VecSubOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Sub n w) - (VecMulOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Mul n w) - (VecDivOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Quot n w) + (VecAddOp FloatVec n w) -> opTranslate (MO_VF_Add n w) + (VecSubOp FloatVec n w) -> opTranslate (MO_VF_Sub n w) + (VecMulOp FloatVec n w) -> opTranslate (MO_VF_Mul n w) + (VecDivOp FloatVec n w) -> opTranslate (MO_VF_Quot n w) (VecQuotOp FloatVec _ _) -> \_ -> panic "unsupported primop" (VecRemOp FloatVec _ _) -> \_ -> panic "unsupported primop" - (VecNegOp FloatVec n w) -> \args -> opTranslate args (MO_VF_Neg n w) + (VecNegOp FloatVec n w) -> opTranslate (MO_VF_Neg n w) - (VecAddOp IntVec n w) -> \args -> opTranslate args (MO_V_Add n w) - (VecSubOp IntVec n w) -> \args -> opTranslate args (MO_V_Sub n w) - (VecMulOp IntVec n w) -> \args -> opTranslate args (MO_V_Mul n w) + (VecAddOp IntVec n w) -> opTranslate (MO_V_Add n w) + (VecSubOp IntVec n w) -> opTranslate (MO_V_Sub n w) + (VecMulOp IntVec n w) -> opTranslate (MO_V_Mul n w) (VecDivOp IntVec _ _) -> \_ -> panic "unsupported primop" - (VecQuotOp IntVec n w) -> \args -> opTranslate args (MO_VS_Quot n w) - (VecRemOp IntVec n w) -> \args -> opTranslate args (MO_VS_Rem n w) - (VecNegOp IntVec n w) -> \args -> opTranslate args (MO_VS_Neg n w) + (VecQuotOp IntVec n w) -> opTranslate (MO_VS_Quot n w) + (VecRemOp IntVec n w) -> opTranslate (MO_VS_Rem n w) + (VecNegOp IntVec n w) -> opTranslate (MO_VS_Neg n w) - (VecAddOp WordVec n w) -> \args -> opTranslate args (MO_V_Add n w) - (VecSubOp WordVec n w) -> \args -> opTranslate args (MO_V_Sub n w) - (VecMulOp WordVec n w) -> \args -> opTranslate args (MO_V_Mul n w) + (VecAddOp WordVec n w) -> opTranslate (MO_V_Add n w) + (VecSubOp WordVec n w) -> opTranslate (MO_V_Sub n w) + (VecMulOp WordVec n w) -> opTranslate (MO_V_Mul n w) (VecDivOp WordVec _ _) -> \_ -> panic "unsupported primop" - (VecQuotOp WordVec n w) -> \args -> opTranslate args (MO_VU_Quot n w) - (VecRemOp WordVec n w) -> \args -> opTranslate args (MO_VU_Rem n w) + (VecQuotOp WordVec n w) -> opTranslate (MO_VU_Quot n w) + (VecRemOp WordVec n w) -> opTranslate (MO_VU_Rem n w) (VecNegOp WordVec _ _) -> \_ -> panic "unsupported primop" -- Conversions - IntToDoubleOp -> \args -> opTranslate args (MO_SF_Round (wordWidth platform) W64) - DoubleToIntOp -> \args -> opTranslate args (MO_FS_Truncate W64 (wordWidth platform)) + IntToDoubleOp -> opTranslate (MO_SF_Round (wordWidth platform) W64) + DoubleToIntOp -> opTranslate (MO_FS_Truncate W64 (wordWidth platform)) - IntToFloatOp -> \args -> opTranslate args (MO_SF_Round (wordWidth platform) W32) - FloatToIntOp -> \args -> opTranslate args (MO_FS_Truncate W32 (wordWidth platform)) + IntToFloatOp -> opTranslate (MO_SF_Round (wordWidth platform) W32) + FloatToIntOp -> opTranslate (MO_FS_Truncate W32 (wordWidth platform)) - FloatToDoubleOp -> \args -> opTranslate args (MO_FF_Conv W32 W64) - DoubleToFloatOp -> \args -> opTranslate args (MO_FF_Conv W64 W32) + FloatToDoubleOp -> opTranslate (MO_FF_Conv W32 W64) + DoubleToFloatOp -> opTranslate (MO_FF_Conv W64 W32) - CastFloatToWord32Op -> - \args -> translateBitcasts (MO_FW_Bitcast W32) args - CastWord32ToFloatOp -> - \args -> translateBitcasts (MO_WF_Bitcast W32) args - CastDoubleToWord64Op -> - \args -> translateBitcasts (MO_FW_Bitcast W64) args - CastWord64ToDoubleOp -> - \args -> translateBitcasts (MO_WF_Bitcast W64) args + CastFloatToWord32Op -> translateBitcasts (MO_FW_Bitcast W32) + CastWord32ToFloatOp -> translateBitcasts (MO_WF_Bitcast W32) + CastDoubleToWord64Op -> translateBitcasts (MO_FW_Bitcast W64) + CastWord64ToDoubleOp -> translateBitcasts (MO_WF_Bitcast W64) - IntQuotRemOp -> \args -> opCallishHandledLater args $ + IntQuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem (wordWidth platform)) else Right (genericIntQuotRemOp (wordWidth platform)) - Int8QuotRemOp -> \args -> opCallishHandledLater args $ + Int8QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem W8) else Right (genericIntQuotRemOp W8) - Int16QuotRemOp -> \args -> opCallishHandledLater args $ + Int16QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem W16) else Right (genericIntQuotRemOp W16) - Int32QuotRemOp -> \args -> opCallishHandledLater args $ + Int32QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_S_QuotRem W32) else Right (genericIntQuotRemOp W32) - WordQuotRemOp -> \args -> opCallishHandledLater args $ + WordQuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem (wordWidth platform)) else Right (genericWordQuotRemOp (wordWidth platform)) - WordQuotRem2Op -> \args -> opCallishHandledLater args $ + WordQuotRem2Op -> opCallishHandledLater $ if allowQuotRem2 then Left (MO_U_QuotRem2 (wordWidth platform)) else Right (genericWordQuotRem2Op platform) - Word8QuotRemOp -> \args -> opCallishHandledLater args $ + Word8QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem W8) else Right (genericWordQuotRemOp W8) - Word16QuotRemOp -> \args -> opCallishHandledLater args $ + Word16QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem W16) else Right (genericWordQuotRemOp W16) - Word32QuotRemOp -> \args -> opCallishHandledLater args $ + Word32QuotRemOp -> opCallishHandledLater $ if allowQuotRem then Left (MO_U_QuotRem W32) else Right (genericWordQuotRemOp W32) - WordAdd2Op -> \args -> opCallishHandledLater args $ + WordAdd2Op -> opCallishHandledLater $ if allowExtAdd then Left (MO_Add2 (wordWidth platform)) else Right genericWordAdd2Op - WordAddCOp -> \args -> opCallishHandledLater args $ + WordAddCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_AddWordC (wordWidth platform)) else Right genericWordAddCOp - WordSubCOp -> \args -> opCallishHandledLater args $ + WordSubCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_SubWordC (wordWidth platform)) else Right genericWordSubCOp - IntAddCOp -> \args -> opCallishHandledLater args $ + IntAddCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_AddIntC (wordWidth platform)) else Right genericIntAddCOp - IntSubCOp -> \args -> opCallishHandledLater args $ + IntSubCOp -> opCallishHandledLater $ if allowExtAdd then Left (MO_SubIntC (wordWidth platform)) else Right genericIntSubCOp - WordMul2Op -> \args -> opCallishHandledLater args $ + WordMul2Op -> opCallishHandledLater $ if allowWord2Mul then Left (MO_U_Mul2 (wordWidth platform)) else Right genericWordMul2Op - IntMul2Op -> \args -> opCallishHandledLater args $ + IntMul2Op -> opCallishHandledLater $ if allowInt2Mul then Left (MO_S_Mul2 (wordWidth platform)) else Right genericIntMul2Op @@ -1775,42 +1779,33 @@ emitPrimOp cfg primop = -- These primops are implemented by CallishMachOps, because they sometimes -- turn into foreign calls depending on the backend. - opCallish :: [CmmExpr] -> CallishMachOp -> PrimopCmmEmit - opCallish args prim = opIntoRegs $ \[res] -> emitPrimCall [res] prim args + opCallish :: CallishMachOp -> [CmmExpr] -> PrimopCmmEmit + opCallish prim args = opIntoRegs $ \[res] -> emitPrimCall [res] prim args - opTranslate :: [CmmExpr] -> MachOp -> PrimopCmmEmit - opTranslate args mop = opIntoRegs $ \[res] -> do + opTranslate :: MachOp -> [CmmExpr] -> PrimopCmmEmit + opTranslate mop args = opIntoRegs $ \[res] -> do let stmt = mkAssign (CmmLocal res) (CmmMachOp mop args) emit stmt - isQuottishOp :: CallishMachOp -> Bool - isQuottishOp MO_I64_Quot = True - isQuottishOp MO_I64_Rem = True - isQuottishOp MO_W64_Quot = True - isQuottishOp MO_W64_Rem = True - isQuottishOp _ = False - opTranslate64 - :: [CmmExpr] - -> (Width -> MachOp) + :: MachOp -> CallishMachOp + -> [CmmExpr] -> PrimopCmmEmit - opTranslate64 args mkMop callish = - case platformWordSize platform of - -- LLVM and C `can handle larger than native size arithmetic natively. - _ | not (isQuottishOp callish), stgToCmmAllowBigArith cfg -> opTranslate args $ mkMop W64 - | isQuottishOp callish, stgToCmmAllowBigQuot cfg -> opTranslate args $ mkMop W64 - PW4 -> opCallish args callish - PW8 -> opTranslate args $ mkMop W64 + opTranslate64 mop callish + | allowArith64 = opTranslate mop + | otherwise = opCallish callish + -- backends not supporting 64-bit arithmetic primops: use callish machine + -- ops -- Basically a "manual" case, rather than one of the common repetitive forms -- above. The results are a parameter to the returned function so we know the -- choice of variant never depends on them. opCallishHandledLater - :: [CmmExpr] - -> Either CallishMachOp GenericOp + :: Either CallishMachOp GenericOp + -> [CmmExpr] -> PrimopCmmEmit - opCallishHandledLater args callOrNot = opIntoRegs $ \res0 -> case callOrNot of + opCallishHandledLater callOrNot args = opIntoRegs $ \res0 -> case callOrNot of Left op -> emit $ mkUnsafeCall (PrimTarget op) res0 args Right gen -> gen res0 args @@ -1838,21 +1833,23 @@ emitPrimOp cfg primop = allowExtAdd = stgToCmmAllowExtendedAddSubInstrs cfg allowInt2Mul = stgToCmmAllowIntMul2Instr cfg allowWord2Mul = stgToCmmAllowWordMul2Instr cfg + allowArith64 = stgToCmmAllowArith64 cfg + allowQuot64 = stgToCmmAllowQuot64 cfg -- a bit of a hack, for certain code generaters, e.g. PPC, and i386 we -- continue to use the cmm versions of these functions instead of inline -- assembly. Tracked in #24841. ppc = isPPC $ platformArch platform i386 = target32Bit platform - translateBitcasts mop args | ppc || i386 = alwaysExternal args - | otherwise = opTranslate args mop + translateBitcasts mop | ppc || i386 = alwaysExternal + | otherwise = opTranslate mop allowFMA = stgToCmmAllowFMAInstr cfg fmaOp :: FMASign -> Width -> [CmmActual] -> PrimopCmmEmit fmaOp signs w args@[arg_x, arg_y, arg_z] | allowFMA signs - = opTranslate args (MO_FMA signs w) + = opTranslate (MO_FMA signs w) args | otherwise = case signs of ===================================== libraries/ghc-internal/src/GHC/Internal/Exception.hs ===================================== @@ -79,7 +79,7 @@ import GHC.Internal.Exception.Type -- WARNING: You may want to use 'throwIO' instead so that your pure code -- stays exception-free. throw :: forall (r :: RuntimeRep). forall (a :: TYPE r). forall e. - (?callStack :: CallStack, Exception e) => e -> a + (HasCallStack, Exception e) => e -> a throw e = let !se = unsafePerformIO (toExceptionWithBacktrace e) in raise# se ===================================== rts/Inlines.c ===================================== @@ -1,6 +1,7 @@ -// all functions declared with EXTERN_INLINE in the header files get -// compiled for real here, just in case the definition was not inlined -// at some call site: +// All functions declared with EXTERN_INLINE in the header files get +// compiled for real here. Some of them are called by Cmm (e.g. +// recordClosureMutated) and therefore the real thing needs to reside +// in Inlines.o for Cmm ccall to work. #define KEEP_INLINES #include "rts/PosixSource.h" #include "Rts.h" ===================================== rts/include/Stg.h ===================================== @@ -114,57 +114,19 @@ * 'Portable' inlining: * INLINE_HEADER is for inline functions in header files (macros) * STATIC_INLINE is for inline functions in source files - * EXTERN_INLINE is for functions that we want to inline sometimes - * (we also compile a static version of the function; see Inlines.c) + * EXTERN_INLINE is for functions that may be called in Cmm + * (we also compile a static version of an EXTERN_INLINE function; see Inlines.c) */ -// We generally assume C99 semantics albeit these two definitions work fine even -// when gnu90 semantics are active (i.e. when __GNUC_GNU_INLINE__ is defined or -// when a GCC older than 4.2 is used) -// -// The problem, however, is with 'extern inline' whose semantics significantly -// differs between gnu90 and C99 #define INLINE_HEADER static inline #define STATIC_INLINE static inline -// Figure out whether `__attributes__((gnu_inline))` is needed -// to force gnu90-style 'external inline' semantics. -#if defined(FORCE_GNU_INLINE) -// disable auto-detection since HAVE_GNU_INLINE has been defined externally -#elif defined(__GNUC_GNU_INLINE__) && __GNUC__ == 4 && __GNUC_MINOR__ == 2 -// GCC 4.2.x didn't properly support C99 inline semantics (GCC 4.3 was the first -// release to properly support C99 inline semantics), and therefore warned when -// using 'extern inline' while in C99 mode unless `__attributes__((gnu_inline))` -// was explicitly set. -# define FORCE_GNU_INLINE 1 -#endif - -#if defined(FORCE_GNU_INLINE) -// Force compiler into gnu90 semantics -# if defined(KEEP_INLINES) -# define EXTERN_INLINE inline __attribute__((gnu_inline)) -# else -# define EXTERN_INLINE extern inline __attribute__((gnu_inline)) -# endif -#elif defined(__GNUC_GNU_INLINE__) -// we're currently in gnu90 inline mode by default and -// __attribute__((gnu_inline)) may not be supported, so better leave it off -# if defined(KEEP_INLINES) -# define EXTERN_INLINE inline -# else -# define EXTERN_INLINE extern inline -# endif -#else -// Assume C99 semantics (yes, this curiously results in swapped definitions!) -// This is the preferred branch, and at some point we may drop support for -// compilers not supporting C99 semantics altogether. +// See comment in rts/Inlines.c for explanation. # if defined(KEEP_INLINES) # define EXTERN_INLINE extern inline # else -# define EXTERN_INLINE inline +# define EXTERN_INLINE static inline # endif -#endif - /* * GCC attributes ===================================== testsuite/tests/driver/objc/all.T ===================================== @@ -1,11 +1,13 @@ test('objc-hi', [ unless(opsys('darwin'), skip), + when(config.target_wrapper is not None, skip), objc_src, expect_fail_for(['ghci']) ], compile_and_run, ['-framework Foundation']) test('objcxx-hi', [ unless(opsys('darwin'), skip), + when(config.target_wrapper is not None, skip), objcxx_src, expect_fail_for(['ghci']) ], compile_and_run, ['-framework Foundation -lc++']) ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5319,7 +5319,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5288,7 +5288,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5465,7 +5465,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5319,7 +5319,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0aa54bc5792d5487e3fa6d57ca026ba94c83e96a...aae3e02fbd6b3dacf32808d5540a611e40824756 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0aa54bc5792d5487e3fa6d57ca026ba94c83e96a...aae3e02fbd6b3dacf32808d5540a611e40824756 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 11:40:59 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Sat, 08 Jun 2024 07:40:59 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/fix-movq-comment Message-ID: <6664434bdbcfd_3d87d36a302541371be@gitlab.mail> Ben Gamari pushed new branch wip/fix-movq-comment at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-movq-comment You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 11:42:17 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Sat, 08 Jun 2024 07:42:17 -0400 Subject: [Git][ghc/ghc][wip/T24906] 72 commits: rts: ensure gc_thread/gen_workspace is allocated with proper alignment Message-ID: <66644399d68b6_3d87d36aa9a50137376@gitlab.mail> Ben Gamari pushed to branch wip/T24906 at Glasgow Haskell Compiler / GHC Commits: 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - 61ba0f54 by Ben Gamari at 2024-06-08T07:29:52-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 6f0fe7d4 by Ben Gamari at 2024-06-08T07:30:07-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCon.hs - + compiler/GHC/Data/OsPath.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c08d373efbf83ff64737f49afd4d70bb15d6a8ea...6f0fe7d46dd7d11bc4e78ccaa763395da4e7a39b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c08d373efbf83ff64737f49afd4d70bb15d6a8ea...6f0fe7d46dd7d11bc4e78ccaa763395da4e7a39b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 11:43:16 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Sat, 08 Jun 2024 07:43:16 -0400 Subject: [Git][ghc/ghc][wip/fix-movq-comment] compiler: Clarify comment regarding need for MOVABS Message-ID: <666443d47f938_3d87d36b3954c1392bb@gitlab.mail> Ben Gamari pushed to branch wip/fix-movq-comment at Glasgow Haskell Compiler / GHC Commits: 13bc871b by Ben Gamari at 2024-06-08T07:43:06-04:00 compiler: Clarify comment regarding need for MOVABS - - - - - 1 changed file: - compiler/GHC/CmmToAsm/X86/Instr.hs Changes: ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -198,10 +198,13 @@ data Instr -- Moves. | MOV Format Operand Operand - -- ^ N.B. when used with the 'II64' 'Format', the source + -- ^ N.B. Due to AT&T assembler quirks, when used with 'II64' + -- 'Format' immediate source and memory target operand, the source -- operand is interpreted to be a 32-bit sign-extended value. - -- True 64-bit operands need to be moved with @MOVABS@, which we - -- currently don't use. + -- True 64-bit operands need to be either first moved to a register or moved + -- with @MOVABS@; we currently do not use this instruction in GHC. + -- See https://stackoverflow.com/questions/52434073/whats-the-difference-between-the-x86-64-att-instructions-movq-and-movabsq. + | MOVD Format Operand Operand -- ^ MOVD/MOVQ SSE2 instructions -- (bitcast between a general purpose -- register and a float register). View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/13bc871b9e1a1f7ce32b3ccee863fbb4ade5ba2d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/13bc871b9e1a1f7ce32b3ccee863fbb4ade5ba2d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 11:44:09 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Sat, 08 Jun 2024 07:44:09 -0400 Subject: [Git][ghc/ghc][wip/fix-movq-comment] compiler: Clarify comment regarding need for MOVABS Message-ID: <6664440911e02_3d87d36ba78f8139448@gitlab.mail> Ben Gamari pushed to branch wip/fix-movq-comment at Glasgow Haskell Compiler / GHC Commits: 3cdd85b5 by Ben Gamari at 2024-06-08T07:43:26-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 1 changed file: - compiler/GHC/CmmToAsm/X86/Instr.hs Changes: ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -198,10 +198,13 @@ data Instr -- Moves. | MOV Format Operand Operand - -- ^ N.B. when used with the 'II64' 'Format', the source + -- ^ N.B. Due to AT&T assembler quirks, when used with 'II64' + -- 'Format' immediate source and memory target operand, the source -- operand is interpreted to be a 32-bit sign-extended value. - -- True 64-bit operands need to be moved with @MOVABS@, which we - -- currently don't use. + -- True 64-bit operands need to be either first moved to a register or moved + -- with @MOVABS@; we currently do not use this instruction in GHC. + -- See https://stackoverflow.com/questions/52434073/whats-the-difference-between-the-x86-64-att-instructions-movq-and-movabsq. + | MOVD Format Operand Operand -- ^ MOVD/MOVQ SSE2 instructions -- (bitcast between a general purpose -- register and a float register). View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3cdd85b584ec09bc3170264a77cd85fb98b016da -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3cdd85b584ec09bc3170264a77cd85fb98b016da You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 12:23:19 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sat, 08 Jun 2024 08:23:19 -0400 Subject: [Git][ghc/ghc][wip/supersven/ghc-9.10-riscv-ncg] Add fused multiplication/addition (FMA) Message-ID: <66644d3786077_3096f972f0b05629e@gitlab.mail> Sven Tennie pushed to branch wip/supersven/ghc-9.10-riscv-ncg at Glasgow Haskell Compiler / GHC Commits: 53da5e54 by Sven Tennie at 2024-06-08T12:21:52+00:00 Add fused multiplication/addition (FMA) - - - - - 3 changed files: - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs Changes: ===================================== compiler/GHC/CmmToAsm/RV64/CodeGen.hs ===================================== @@ -755,7 +755,7 @@ getRegister' config plat expr = where w' = formatToWidth (cmmTypeFormat (cmmRegType reg)) r' = getRegisterReg plat reg - -- Generic case. + -- Generic binary case. CmmMachOp op [x, y] -> do let -- A "plain" operation. @@ -910,6 +910,42 @@ getRegister' config plat expr = MO_S_Shr w -> intOp True w (\d x y -> unitOL $ annExpr expr (ASR d x y)) op -> pprPanic "getRegister' (unhandled dyadic CmmMachOp): " $ pprMachOp op <+> text "in" <+> pdoc plat expr + + -- Generic ternary case. + CmmMachOp op [x, y, z] -> + + case op of + + -- Floating-point fused multiply-add operations + + -- x86 fmadd x * y + z <=> AArch64 fmadd : d = r1 * r2 + r3 + -- x86 fmsub x * y - z <=> AArch64 fnmsub: d = r1 * r2 - r3 + -- x86 fnmadd - x * y + z <=> AArch64 fmsub : d = - r1 * r2 + r3 + -- x86 fnmsub - x * y - z <=> AArch64 fnmadd: d = - r1 * r2 - r3 + + MO_FMA var w -> case var of + FMAdd -> float3Op w (\d n m a -> unitOL $ FMA FMAdd d n m a) + FMSub -> float3Op w (\d n m a -> unitOL $ FMA FMSub d n m a) + FNMAdd -> float3Op w (\d n m a -> unitOL $ FMA FNMSub d n m a) + FNMSub -> float3Op w (\d n m a -> unitOL $ FMA FNMAdd d n m a) + + _ -> pprPanic "getRegister' (unhandled ternary CmmMachOp): " $ + (pprMachOp op) <+> text "in" <+> (pdoc plat expr) + + where + float3Op w op = do + (reg_fx, format_x, code_fx) <- getFloatReg x + (reg_fy, format_y, code_fy) <- getFloatReg y + (reg_fz, format_z, code_fz) <- getFloatReg z + massertPpr (isFloatFormat format_x && isFloatFormat format_y && isFloatFormat format_z) $ + text "float3Op: non-float" + return $ + Any (floatFormat w) $ \ dst -> + code_fx `appOL` + code_fy `appOL` + code_fz `appOL` + op (OpReg w dst) (OpReg w reg_fx) (OpReg w reg_fy) (OpReg w reg_fz) + CmmMachOp _op _xs -> pprPanic "getRegister' (variadic CmmMachOp): " (pdoc plat expr) ===================================== compiler/GHC/CmmToAsm/RV64/Instr.hs ===================================== @@ -134,6 +134,8 @@ regUsageOfInstr platform instr = case instr of SCVTF dst src -> usage (regOp src, regOp dst) FCVTZS dst src -> usage (regOp src, regOp dst) FABS dst src -> usage (regOp src, regOp dst) + FMA _ dst src1 src2 src3 -> + usage (regOp src1 ++ regOp src2 ++ regOp src3, regOp dst) _ -> panic $ "regUsageOfInstr: " ++ instrCon instr @@ -253,6 +255,8 @@ patchRegsOfInstr instr env = case instr of SCVTF o1 o2 -> SCVTF (patchOp o1) (patchOp o2) FCVTZS o1 o2 -> FCVTZS (patchOp o1) (patchOp o2) FABS o1 o2 -> FABS (patchOp o1) (patchOp o2) + FMA s o1 o2 o3 o4 -> + FMA s (patchOp o1) (patchOp o2) (patchOp o3) (patchOp o4) _ -> panic $ "patchRegsOfInstr: " ++ instrCon instr where patchOp :: Operand -> Operand @@ -634,6 +638,13 @@ data Instr | FCVTZS Operand Operand -- Float ABSolute value | FABS Operand Operand + -- | Floating-point fused multiply-add instructions + -- + -- - fmadd : d = r1 * r2 + r3 + -- - fnmsub: d = r1 * r2 - r3 + -- - fmsub : d = - r1 * r2 + r3 + -- - fnmadd: d = - r1 * r2 - r3 + | FMA FMASign Operand Operand Operand Operand data DmbType = DmbRead | DmbWrite | DmbReadWrite @@ -683,6 +694,12 @@ instrCon i = SCVTF{} -> "SCVTF" FCVTZS{} -> "FCVTZS" FABS{} -> "FABS" + FMA variant _ _ _ _ -> + case variant of + FMAdd -> "FMADD" + FMSub -> "FMSUB" + FNMAdd -> "FNMADD" + FNMSub -> "FNMSUB" data Target = TBlock BlockId ===================================== compiler/GHC/CmmToAsm/RV64/Ppr.hs ===================================== @@ -648,12 +648,23 @@ pprInstr platform instr = case instr of FABS o1 o2 | isSingleOp o2 -> op2 (text "\tfabs.s") o1 o2 FABS o1 o2 | isDoubleOp o2 -> op2 (text "\tfabs.d") o1 o2 + FMA variant d r1 r2 r3 -> + let fma = case variant of + FMAdd -> text "\tfmadd" <> dot <> floatPrecission d + FMSub -> text "\tfmsub" <> dot <> floatPrecission d + FNMAdd -> text "\tfnmadd" <> dot <> floatPrecission d + FNMSub -> text "\tfnmsub" <> dot <> floatPrecission d + in op4 fma d r1 r2 r3 instr -> panic $ "RV64.pprInstr - Unknown instruction: " ++ instrCon instr where op2 op o1 o2 = line $ op <+> pprOp platform o1 <> comma <+> pprOp platform o2 op3 op o1 o2 o3 = line $ op <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 + op4 op o1 o2 o3 o4 = line $ op <+> pprOp platform o1 <> comma <+> pprOp platform o2 <> comma <+> pprOp platform o3 <> comma <+> pprOp platform o4 pprDmbType DmbRead = text "r" pprDmbType DmbWrite = text "w" pprDmbType DmbReadWrite = text "rw" + floatPrecission o | isSingleOp o = text "s" + | isDoubleOp o = text "d" + | otherwise = pprPanic "Impossible floating point precission: " (pprOp platform o) floatOpPrecision :: Platform -> Operand -> Operand -> String floatOpPrecision _p l r | isFloatOp l && isFloatOp r && isSingleOp l && isSingleOp r = "s" -- single precision View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/53da5e54a2021cc9042a9a3274dcd5bf840c6d6c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/53da5e54a2021cc9042a9a3274dcd5bf840c6d6c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 12:39:29 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Sat, 08 Jun 2024 08:39:29 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] use MOVU instructions for spill/unspill Message-ID: <66645101936b0_3096f9b61fac613c@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 3ed919cf by sheaf at 2024-06-08T14:38:42+02:00 use MOVU instructions for spill/unspill - - - - - 2 changed files: - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs Changes: ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -363,6 +363,7 @@ data Instr | MOVU Format Operand Operand | MOVL Format Operand Operand | MOVH Format Operand Operand + | MOVA Format Operand Operand -- logic operations | VPXOR Format Reg Reg Reg @@ -503,6 +504,7 @@ regUsageOfInstr platform instr VMOVU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) MOVU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) + MOVA fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) MOVL fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) MOVH fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) VPXOR fmt s1 s2 dst -> mkRU fmt [s1,s2] [dst] @@ -709,6 +711,7 @@ patchRegsOfInstr instr env VMOVU fmt src dst -> VMOVU fmt (patchOp src) (patchOp dst) MOVU fmt src dst -> MOVU fmt (patchOp src) (patchOp dst) + MOVA fmt src dst -> MOVA fmt (patchOp src) (patchOp dst) MOVL fmt src dst -> MOVL fmt (patchOp src) (patchOp dst) MOVH fmt src dst -> MOVH fmt (patchOp src) (patchOp dst) VPXOR fmt s1 s2 dst -> VPXOR fmt (env s1) (env s2) (env dst) @@ -826,16 +829,14 @@ mkSpillInstr -> [Instr] mkSpillInstr config reg fmt delta slot - = let off s = spillSlotToOffset platform s - delta + = let off = spillSlotToOffset platform slot - delta in case fmt of - VecFormat {} -> + VecFormat {} -- SIMD NCG TODO: panic for unsupported VecFormats (& same in mkLoadInstr) - [MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off slot)) - -- Now shuffle the register, putting the high half into the lower half. - ,SHUFPD fmt (ImmInt 0b01) (OpReg reg) reg - -- SIMD NCG TODO: can we emit more efficient code here? - ,MOV FF64 (OpReg reg) (OpAddr (spRel platform $ off (slot + 1)))] - _ -> [MOV fmt (OpReg reg) (OpAddr (spRel platform $ off slot))] + -> [MOVU fmt (OpReg reg) (OpAddr (spRel platform off))] + -- NB: not using MOVA because we have no guarantees about the stack + -- being sufficiently aligned, including even numbered stack slots. + _ -> [MOV fmt (OpReg reg) (OpAddr (spRel platform off))] where platform = ncgPlatform config -- | Make a spill reload instruction. @@ -848,14 +849,14 @@ mkLoadInstr -> [Instr] mkLoadInstr config reg fmt delta slot - = let off s = spillSlotToOffset platform s - delta - in - case fmt of - VecFormat {} -> - -- SIMD NCG TODO: panic on unsupported VecFormats - [MOVH (VecFormat 2 FmtDouble W64) (OpAddr (spRel platform $ off (slot + 1))) (OpReg reg) - ,MOVL (VecFormat 2 FmtDouble W64) (OpAddr (spRel platform $ off slot)) (OpReg reg)] - _ -> [MOV fmt (OpAddr (spRel platform $ off slot)) (OpReg reg)] + = let off = spillSlotToOffset platform slot - delta + in case fmt of + VecFormat {} + -- SIMD NCG TODO: panic for unsupported VecFormats (& same in mkLoadInstr) + -> [MOVU fmt (OpAddr (spRel platform off)) (OpReg reg)] + -- NB: not using MOVA because we have no guarantees about the stack + -- being sufficiently aligned, including even numbered stack slots. + _ -> [MOV fmt (OpAddr (spRel platform off)) (OpReg reg)] where platform = ncgPlatform config ===================================== compiler/GHC/CmmToAsm/X86/Ppr.hs ===================================== @@ -928,6 +928,8 @@ pprInstr platform i = case i of -> pprFormatOpOp (text "vmovu") format from to MOVU format from to -> pprFormatOpOp (text "movu") format from to + MOVA format from to + -> pprFormatOpOp (text "mova") format from to MOVL format from to -> pprFormatOpOp (text "movl") format from to MOVH format from to View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3ed919cf1ad69b0ee05954e79f4e9c38bc0319aa -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3ed919cf1ad69b0ee05954e79f4e9c38bc0319aa You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 12:49:59 2024 From: gitlab at gitlab.haskell.org (Zubin (@wz1000)) Date: Sat, 08 Jun 2024 08:49:59 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/faststring-no-z Message-ID: <66645377be71e_3096f9cee3346159@gitlab.mail> Zubin pushed new branch wip/faststring-no-z at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/faststring-no-z You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 13:15:52 2024 From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim)) Date: Sat, 08 Jun 2024 09:15:52 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/Data.List.compareLength Message-ID: <6664598828349_3096f910315f070573@gitlab.mail> Bodigrim pushed new branch wip/Data.List.compareLength at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/Data.List.compareLength You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 13:16:58 2024 From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim)) Date: Sat, 08 Jun 2024 09:16:58 -0400 Subject: [Git][ghc/ghc][wip/Data.List.compareLength] Implement Data.List.compareLength and Data.List.NonEmpty.compareLength Message-ID: <666459ca3c3ed_3096f910e65a472460@gitlab.mail> Bodigrim pushed to branch wip/Data.List.compareLength at Glasgow Haskell Compiler / GHC Commits: 74adbb13 by Andrew Lelechenko at 2024-06-08T15:16:38+02:00 Implement Data.List.compareLength and Data.List.NonEmpty.compareLength As per https://github.com/haskell/core-libraries-committee/issues/257 - - - - - 10 changed files: - libraries/base/src/Data/List.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/base/src/GHC/List.hs - libraries/ghc-internal/src/GHC/Internal/Data/List.hs - libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs - libraries/ghc-internal/src/GHC/Internal/List.hs - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 Changes: ===================================== libraries/base/src/Data/List.hs ===================================== @@ -26,6 +26,7 @@ module Data.List singleton, null, length, + compareLength, -- * List transformations map, reverse, ===================================== libraries/base/src/Data/List/NonEmpty.hs ===================================== @@ -36,6 +36,7 @@ module Data.List.NonEmpty ( , sortWith -- :: Ord o => (a -> o) -> NonEmpty a -> NonEmpty a -- * Basic functions , length -- :: NonEmpty a -> Int + , compareLength , head -- :: NonEmpty a -> a , tail -- :: NonEmpty a -> [a] , last -- :: NonEmpty a -> a @@ -128,6 +129,30 @@ infixr 5 <| length :: NonEmpty a -> Int length (_ :| xs) = 1 + Prelude.length xs +-- | Use 'compareLength' @xs@ @n@ as a safer and faster alternative +-- to 'compare' ('length' @xs@) @n at . Similarly, it's better +-- to write @compareLength xs 10 == LT@ instead of @length xs < 10 at . +-- +-- While 'length' would force and traverse +-- the entire spine of @xs@ (which could even diverge if @xs@ is infinite), +-- 'compareLength' traverses at most @n@ elements to determine its result. +-- +-- >>> compareLength ('a' :| []) 1 +-- EQ +-- >>> compareLength ('a' :| ['b']) 3 +-- LT +-- >>> compareLength (0 :| [1..]) 100 +-- GT +-- >>> compareLength undefined 0 +-- GT +-- +-- @since base-4.21.0.0 +-- +compareLength :: NonEmpty a -> Int -> Ordering +compareLength xs n + | n < 1 = GT + | otherwise = foldr (\_ f m -> if 0 > m then GT else f (m - 1)) (compare 0) xs n + -- | Compute n-ary logic exclusive OR operation on 'NonEmpty' list. xor :: NonEmpty Bool -> Bool xor (x :| xs) = foldr xor' x xs ===================================== libraries/base/src/GHC/List.hs ===================================== @@ -22,7 +22,7 @@ module GHC.List ( -- * List-monomorphic Foldable methods and misc functions foldr, foldr', foldr1, foldl, foldl', foldl1, - null, length, elem, notElem, + null, length, compareLength, elem, notElem, maximum, minimum, sum, product, and, or, any, all, -- * Other functions ===================================== libraries/ghc-internal/src/GHC/Internal/Data/List.hs ===================================== @@ -30,6 +30,7 @@ module GHC.Internal.Data.List , singleton , null , length + , compareLength -- * List transformations , map @@ -224,7 +225,7 @@ import GHC.Internal.Data.OldList hiding length, notElem, null, or, product, sum ) import GHC.Internal.Base ( Bool(..), Eq((==)), otherwise ) -import GHC.Internal.List (List) +import GHC.Internal.List (List, compareLength) -- | The 'isSubsequenceOf' function takes two lists and returns 'True' if all -- the elements of the first list occur, in order, in the second. The ===================================== libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs ===================================== @@ -30,6 +30,7 @@ module GHC.Internal.Data.OldList , singleton , null , length + , compareLength -- * List transformations , map ===================================== libraries/ghc-internal/src/GHC/Internal/List.hs ===================================== @@ -25,7 +25,7 @@ module GHC.Internal.List ( -- * List-monomorphic Foldable methods and misc functions foldr, foldr', foldr1, foldl, foldl', foldl1, - null, length, elem, notElem, + null, length, compareLength, elem, notElem, maximum, minimum, sum, product, and, or, any, all, -- * Other functions @@ -297,6 +297,34 @@ lengthFB _ r = \ !a -> r (a + 1) idLength :: Int -> Int idLength = id +-- | Use 'compareLength' @xs@ @n@ as a safer and faster alternative +-- to 'compare' ('length' @xs@) @n at . Similarly, it's better +-- to write @compareLength xs 10 == LT@ instead of @length xs < 10 at . +-- +-- While 'length' would force and traverse +-- the entire spine of @xs@ (which could even diverge if @xs@ is infinite), +-- 'compareLength' traverses at most @n@ elements to determine its result. +-- +-- >>> compareLength [] 0 +-- EQ +-- >>> compareLength [] 1 +-- LT +-- >>> compareLength ['a'] 1 +-- EQ +-- >>> compareLength ['a', 'b'] 1 +-- GT +-- >>> compareLength [0..] 100 +-- GT +-- >>> compareLength undefined (-1) +-- GT +-- +-- @since base-4.21.0.0 +-- +compareLength :: [a] -> Int -> Ordering +compareLength xs n + | n < 0 = GT + | otherwise = foldr (\_ f m -> if 0 > m then GT else f (m - 1)) (compare 0) xs n + -- | \(\mathcal{O}(n)\). 'filter', applied to a predicate and a list, returns -- the list of those elements that satisfy the predicate; i.e., -- ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -1299,6 +1299,7 @@ module Data.List where and :: forall (t :: * -> *). GHC.Internal.Data.Foldable.Foldable t => t GHC.Types.Bool -> GHC.Types.Bool any :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Types.Bool break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => t [a] -> [a] concatMap :: forall (t :: * -> *) a b. GHC.Internal.Data.Foldable.Foldable t => (a -> [b]) -> t a -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] @@ -1421,6 +1422,7 @@ module Data.List.NonEmpty where append :: forall a. NonEmpty a -> NonEmpty a -> NonEmpty a appendList :: forall a. NonEmpty a -> [a] -> NonEmpty a break :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> ([a], [a]) + compareLength :: forall a. NonEmpty a -> GHC.Types.Int -> GHC.Types.Ordering cons :: forall a. a -> NonEmpty a -> NonEmpty a cycle :: forall a. NonEmpty a -> NonEmpty a drop :: forall a. GHC.Types.Int -> NonEmpty a -> [a] @@ -8251,6 +8253,7 @@ module GHC.List where augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall a. [[a]] -> [a] concatMap :: forall a b. (a -> [b]) -> [a] -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] @@ -8904,6 +8907,7 @@ module GHC.OldList where and :: [GHC.Types.Bool] -> GHC.Types.Bool any :: forall a. (a -> GHC.Types.Bool) -> [a] -> GHC.Types.Bool break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall a. [[a]] -> [a] concatMap :: forall a b. (a -> [b]) -> [a] -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -1299,6 +1299,7 @@ module Data.List where and :: forall (t :: * -> *). GHC.Internal.Data.Foldable.Foldable t => t GHC.Types.Bool -> GHC.Types.Bool any :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Types.Bool break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => t [a] -> [a] concatMap :: forall (t :: * -> *) a b. GHC.Internal.Data.Foldable.Foldable t => (a -> [b]) -> t a -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] @@ -1421,6 +1422,7 @@ module Data.List.NonEmpty where append :: forall a. NonEmpty a -> NonEmpty a -> NonEmpty a appendList :: forall a. NonEmpty a -> [a] -> NonEmpty a break :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> ([a], [a]) + compareLength :: forall a. NonEmpty a -> GHC.Types.Int -> GHC.Types.Ordering cons :: forall a. a -> NonEmpty a -> NonEmpty a cycle :: forall a. NonEmpty a -> NonEmpty a drop :: forall a. GHC.Types.Int -> NonEmpty a -> [a] @@ -11293,6 +11295,7 @@ module GHC.List where augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall a. [[a]] -> [a] concatMap :: forall a b. (a -> [b]) -> [a] -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] @@ -11946,6 +11949,7 @@ module GHC.OldList where and :: [GHC.Types.Bool] -> GHC.Types.Bool any :: forall a. (a -> GHC.Types.Bool) -> [a] -> GHC.Types.Bool break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall a. [[a]] -> [a] concatMap :: forall a b. (a -> [b]) -> [a] -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -1299,6 +1299,7 @@ module Data.List where and :: forall (t :: * -> *). GHC.Internal.Data.Foldable.Foldable t => t GHC.Types.Bool -> GHC.Types.Bool any :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Types.Bool break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => t [a] -> [a] concatMap :: forall (t :: * -> *) a b. GHC.Internal.Data.Foldable.Foldable t => (a -> [b]) -> t a -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] @@ -1421,6 +1422,7 @@ module Data.List.NonEmpty where append :: forall a. NonEmpty a -> NonEmpty a -> NonEmpty a appendList :: forall a. NonEmpty a -> [a] -> NonEmpty a break :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> ([a], [a]) + compareLength :: forall a. NonEmpty a -> GHC.Types.Int -> GHC.Types.Ordering cons :: forall a. a -> NonEmpty a -> NonEmpty a cycle :: forall a. NonEmpty a -> NonEmpty a drop :: forall a. GHC.Types.Int -> NonEmpty a -> [a] @@ -8475,6 +8477,7 @@ module GHC.List where augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall a. [[a]] -> [a] concatMap :: forall a b. (a -> [b]) -> [a] -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] @@ -9128,6 +9131,7 @@ module GHC.OldList where and :: [GHC.Types.Bool] -> GHC.Types.Bool any :: forall a. (a -> GHC.Types.Bool) -> [a] -> GHC.Types.Bool break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall a. [[a]] -> [a] concatMap :: forall a b. (a -> [b]) -> [a] -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -1299,6 +1299,7 @@ module Data.List where and :: forall (t :: * -> *). GHC.Internal.Data.Foldable.Foldable t => t GHC.Types.Bool -> GHC.Types.Bool any :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Types.Bool break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => t [a] -> [a] concatMap :: forall (t :: * -> *) a b. GHC.Internal.Data.Foldable.Foldable t => (a -> [b]) -> t a -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] @@ -1421,6 +1422,7 @@ module Data.List.NonEmpty where append :: forall a. NonEmpty a -> NonEmpty a -> NonEmpty a appendList :: forall a. NonEmpty a -> [a] -> NonEmpty a break :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> ([a], [a]) + compareLength :: forall a. NonEmpty a -> GHC.Types.Int -> GHC.Types.Ordering cons :: forall a. a -> NonEmpty a -> NonEmpty a cycle :: forall a. NonEmpty a -> NonEmpty a drop :: forall a. GHC.Types.Int -> NonEmpty a -> [a] @@ -8251,6 +8253,7 @@ module GHC.List where augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall a. [[a]] -> [a] concatMap :: forall a b. (a -> [b]) -> [a] -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] @@ -8904,6 +8907,7 @@ module GHC.OldList where and :: [GHC.Types.Bool] -> GHC.Types.Bool any :: forall a. (a -> GHC.Types.Bool) -> [a] -> GHC.Types.Bool break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall a. [[a]] -> [a] concatMap :: forall a b. (a -> [b]) -> [a] -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/74adbb136c67df7997f0336fe027140b34e56ed4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/74adbb136c67df7997f0336fe027140b34e56ed4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 13:37:29 2024 From: gitlab at gitlab.haskell.org (Alexander Foremny (@aforemny)) Date: Sat, 08 Jun 2024 09:37:29 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/aforemny/ast Message-ID: <66645e995a7fa_3096f913c08ec76362@gitlab.mail> Alexander Foremny pushed new branch wip/aforemny/ast at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/aforemny/ast You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 13:39:29 2024 From: gitlab at gitlab.haskell.org (Maurice Scheffmacher (@mauscheff)) Date: Sat, 08 Jun 2024 09:39:29 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/mauscheff/ast Message-ID: <66645f119f4cb_3096f91430d40768f6@gitlab.mail> Maurice Scheffmacher pushed new branch wip/mauscheff/ast at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/mauscheff/ast You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 13:45:23 2024 From: gitlab at gitlab.haskell.org (Alexander Foremny (@aforemny)) Date: Sat, 08 Jun 2024 09:45:23 -0400 Subject: [Git][ghc/ghc][wip/aforemny/ast] AST: GHC.Prelude -> Prelude Message-ID: <66646073d0d45_3096f9162395478072@gitlab.mail> Alexander Foremny pushed to branch wip/aforemny/ast at Glasgow Haskell Compiler / GHC Commits: 30c86dd2 by Alexander Foremny at 2024-06-08T15:44:15+02:00 AST: GHC.Prelude -> Prelude Refactor occurrences to GHC.Prelude with Prelude within Language/Haskell. - - - - - 1 changed file: - compiler/Language/Haskell/Syntax/Expr.hs-boot Changes: ===================================== compiler/Language/Haskell/Syntax/Expr.hs-boot ===================================== @@ -9,7 +9,7 @@ module Language.Haskell.Syntax.Expr where import Language.Haskell.Syntax.Extension ( XRec ) import Data.Kind ( Type ) -import GHC.Prelude (Eq) +import Prelude (Eq) import Data.Data (Data) type role HsExpr nominal View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/30c86dd2ce065b5e71e448da54c0bb2891d4f2ae -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/30c86dd2ce065b5e71e448da54c0bb2891d4f2ae You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 13:48:31 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sat, 08 Jun 2024 09:48:31 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/rts-tls-proper Message-ID: <6664612f6516f_3096f916be56c78324@gitlab.mail> Cheng Shao pushed new branch wip/rts-tls-proper at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/rts-tls-proper You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 13:53:59 2024 From: gitlab at gitlab.haskell.org (Alexander Foremny (@aforemny)) Date: Sat, 08 Jun 2024 09:53:59 -0400 Subject: [Git][ghc/ghc][wip/aforemny/ast] AST: remove occurrences of GHC.Unit.Module.ModuleName Message-ID: <66646277e6d62_3096f91888b1883511@gitlab.mail> Alexander Foremny pushed to branch wip/aforemny/ast at Glasgow Haskell Compiler / GHC Commits: 1f172333 by Alexander Foremny at 2024-06-08T15:53:07+02:00 AST: remove occurrences of GHC.Unit.Module.ModuleName `GHC.Unit.Module` re-exports `ModuleName` from `Language.Haskell.Syntax.Module.Name`. - - - - - 1 changed file: - compiler/Language/Haskell/Syntax/Expr.hs Changes: ===================================== compiler/Language/Haskell/Syntax/Expr.hs ===================================== @@ -26,6 +26,7 @@ import Language.Haskell.Syntax.Decls import Language.Haskell.Syntax.Pat import Language.Haskell.Syntax.Lit import Language.Haskell.Syntax.Extension +import Language.Haskell.Syntax.Module.Name (ModuleName) import Language.Haskell.Syntax.Type import Language.Haskell.Syntax.Binds @@ -33,7 +34,6 @@ import Language.Haskell.Syntax.Binds import GHC.Types.Fixity (LexicalFixity(Infix), Fixity) import GHC.Types.SourceText (StringLiteral, SourceText) -import GHC.Unit.Module (ModuleName) import GHC.Data.FastString (FastString) -- libraries: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1f1723330ad946bca9c3405d29ff4ced99e4eb5b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1f1723330ad946bca9c3405d29ff4ced99e4eb5b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 14:02:24 2024 From: gitlab at gitlab.haskell.org (Zubin (@wz1000)) Date: Sat, 08 Jun 2024 10:02:24 -0400 Subject: [Git][ghc/ghc][wip/faststring-no-z] wip Message-ID: <66646470ae63c_3096f919fc300888a3@gitlab.mail> Zubin pushed to branch wip/faststring-no-z at Glasgow Haskell Compiler / GHC Commits: c405b5a5 by Zubin Duggal at 2024-06-08T16:01:54+02:00 wip - - - - - 3 changed files: - compiler/GHC/Data/FastString.hs - compiler/GHC/Unit/Info.hs - hadrian/src/Rules/Rts.hs Changes: ===================================== compiler/GHC/Data/FastString.hs ===================================== @@ -323,7 +323,13 @@ data FastZStringTable = FastZStringTable -- ^ The number of encoded Z strings (Array# (IORef FastZStringTableSegment)) -- ^ concurrent segments -type FastZStringTableSegment = TableSegment (Int,FastZString) +type FastZStringTableSegment = TableSegment HashedFastZString + +data HashedFastZString + = HashedFastZString + { zStringHash :: {-# UNPACK #-} !Int + , zStringPayload :: {-# NOUNPACK #-} !FastZString + } {- Following parameters are determined based on: @@ -579,7 +585,7 @@ mkNewFastZString (FastString uniq _ sbs) = do !(I# hash#) = uniq*6364136223846793005 + 1 (# segmentRef #) = indexArray# segments# (hashToSegment# hash#) insert n fs = do - TableSegment _ counter buckets# <- maybeResizeSegment fst segmentRef + TableSegment _ counter buckets# <- maybeResizeSegment zStringHash segmentRef let idx# = hashToIndex# buckets# hash# bucket <- IO $ readArray# buckets# idx# case zbucket_match bucket hash# of @@ -588,17 +594,18 @@ mkNewFastZString (FastString uniq _ sbs) = do Just found -> return found Nothing -> do IO $ \s1# -> - case writeArray# buckets# idx# ((n,fs) : bucket) s1# of + case writeArray# buckets# idx# (HashedFastZString n fs : bucket) s1# of s2# -> (# s2#, () #) _ <- atomicFetchAddFastMut counter 1 return fs -zbucket_match :: [(Int,FastZString)] -> Int# -> Maybe FastZString +zbucket_match :: [HashedFastZString] -> Int# -> Maybe FastZString zbucket_match fs hash = go fs where go [] = Nothing - go ((I# u,x) : ls) + go (HashedFastZString (I# u) x : ls) | isTrue# (u ==# hash) = Just x | otherwise = go ls +{-# INLINE zbucket_match #-} mkFastStringBytes :: Ptr Word8 -> Int -> FastString mkFastStringBytes !ptr !len = ===================================== compiler/GHC/Unit/Info.hs ===================================== @@ -236,7 +236,7 @@ unitHsLibs namever ways0 p = map (mkDynName . addSuffix . ST.unpack) (unitLibrar -- This change elevates the need to add custom hooks -- and handling specifically for the `rts` package. addSuffix rts@"HSrts" = rts ++ (expandTag rts_tag) - addSuffix rts@"HSrts-1.0.2" = rts ++ (expandTag rts_tag) + addSuffix rts@"HSrts-1.0.3" = rts ++ (expandTag rts_tag) addSuffix other_lib = other_lib ++ (expandTag tag) expandTag t | null t = "" ===================================== hadrian/src/Rules/Rts.hs ===================================== @@ -161,7 +161,7 @@ needRtsSymLinks stage rtsWays prefix, versionlessPrefix :: String versionlessPrefix = "libHSrts" -prefix = versionlessPrefix ++ "-1.0.2" +prefix = versionlessPrefix ++ "-1.0.3" -- removeRtsDummyVersion "a/libHSrts-1.0-ghc1.2.3.4.so" -- == "a/libHSrts-ghc1.2.3.4.so" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c405b5a5f0249d5f8ae72b9602a8a19ea7411634 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c405b5a5f0249d5f8ae72b9602a8a19ea7411634 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 14:24:11 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Sat, 08 Jun 2024 10:24:11 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/kirchner/ast Message-ID: <6664698b146c2_3096f91d854f4938b5@gitlab.mail> Fabian Kirchner pushed new branch wip/kirchner/ast at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/kirchner/ast You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 14:28:15 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Sat, 08 Jun 2024 10:28:15 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ast] AST: move Data instance definition for ModuleName to GHC.Unit.Types Message-ID: <66646a7f59189_3096f91e3e55894070@gitlab.mail> Fabian Kirchner pushed to branch wip/kirchner/ast at Glasgow Haskell Compiler / GHC Commits: af609165 by Fabian Kirchner at 2024-06-08T16:28:04+02:00 AST: move Data instance definition for ModuleName to GHC.Unit.Types To remove the dependency on GHC.Utils.Misc inside Language.Haskell.Syntax.Module.Name, the instance definition is moved from there into GHC.Unit.Types. - - - - - 2 changed files: - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Module/Name.hs Changes: ===================================== compiler/GHC/Unit/Types.hs ===================================== @@ -735,3 +735,9 @@ instance Outputable a => Outputable (GenWithIsBoot a) where ppr (GWIB { gwib_mod, gwib_isBoot }) = hsep $ ppr gwib_mod : case gwib_isBoot of IsBoot -> [ text "{-# SOURCE #-}" ] NotBoot -> [] + +instance Data ModuleName where + -- don't traverse? + toConstr _ = abstractConstr "ModuleName" + gunfold _ _ = error "gunfold" + dataTypeOf _ = mkNoRepType "ModuleName" ===================================== compiler/Language/Haskell/Syntax/Module/Name.hs ===================================== @@ -2,13 +2,11 @@ module Language.Haskell.Syntax.Module.Name where import Prelude -import Data.Data import Data.Char (isAlphaNum) import Control.DeepSeq import qualified Text.ParserCombinators.ReadP as Parse import System.FilePath -import GHC.Utils.Misc (abstractConstr) import GHC.Data.FastString -- | A ModuleName is essentially a simple string, e.g. @Data.List at . @@ -17,12 +15,6 @@ newtype ModuleName = ModuleName FastString deriving (Show, Eq) instance Ord ModuleName where nm1 `compare` nm2 = stableModuleNameCmp nm1 nm2 -instance Data ModuleName where - -- don't traverse? - toConstr _ = abstractConstr "ModuleName" - gunfold _ _ = error "gunfold" - dataTypeOf _ = mkNoRepType "ModuleName" - instance NFData ModuleName where rnf x = x `seq` () View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/af609165552ef09dbab96e39436863af524e4218 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/af609165552ef09dbab96e39436863af524e4218 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 14:37:24 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Sat, 08 Jun 2024 10:37:24 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ast] AST: move Data instance definition for ModuleName to GHC.Unit.Types Message-ID: <66646ca432d0b_3096f91f66df495064@gitlab.mail> Fabian Kirchner pushed to branch wip/kirchner/ast at Glasgow Haskell Compiler / GHC Commits: 5f889a55 by Fabian Kirchner at 2024-06-08T16:37:14+02:00 AST: move Data instance definition for ModuleName to GHC.Unit.Types To remove the dependency on GHC.Utils.Misc inside Language.Haskell.Syntax.Module.Name, the instance definition is moved from there into GHC.Unit.Types. - - - - - 2 changed files: - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Module/Name.hs Changes: ===================================== compiler/GHC/Unit/Types.hs ===================================== @@ -124,6 +124,12 @@ data GenModule unit = Module } deriving (Eq,Ord,Data,Functor) +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 ===================================== @@ -2,13 +2,11 @@ module Language.Haskell.Syntax.Module.Name where import Prelude -import Data.Data import Data.Char (isAlphaNum) import Control.DeepSeq import qualified Text.ParserCombinators.ReadP as Parse import System.FilePath -import GHC.Utils.Misc (abstractConstr) import GHC.Data.FastString -- | A ModuleName is essentially a simple string, e.g. @Data.List at . @@ -17,12 +15,6 @@ newtype ModuleName = ModuleName FastString deriving (Show, Eq) instance Ord ModuleName where nm1 `compare` nm2 = stableModuleNameCmp nm1 nm2 -instance Data ModuleName where - -- don't traverse? - toConstr _ = abstractConstr "ModuleName" - gunfold _ _ = error "gunfold" - dataTypeOf _ = mkNoRepType "ModuleName" - instance NFData ModuleName where rnf x = x `seq` () View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5f889a5561a8043274d4c28295784dd657380ff7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5f889a5561a8043274d4c28295784dd657380ff7 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 14:42:59 2024 From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim)) Date: Sat, 08 Jun 2024 10:42:59 -0400 Subject: [Git][ghc/ghc][wip/Data.List.compareLength] Implement Data.List.compareLength and Data.List.NonEmpty.compareLength Message-ID: <66646df2f0c18_3096f920b2e881001fa@gitlab.mail> Bodigrim pushed to branch wip/Data.List.compareLength at Glasgow Haskell Compiler / GHC Commits: 3feaa3e4 by Andrew Lelechenko at 2024-06-08T16:42:36+02:00 Implement Data.List.compareLength and Data.List.NonEmpty.compareLength As per https://github.com/haskell/core-libraries-committee/issues/257 - - - - - 10 changed files: - libraries/base/src/Data/List.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/base/src/GHC/List.hs - libraries/ghc-internal/src/GHC/Internal/Data/List.hs - libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs - libraries/ghc-internal/src/GHC/Internal/List.hs - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 Changes: ===================================== libraries/base/src/Data/List.hs ===================================== @@ -26,6 +26,7 @@ module Data.List singleton, null, length, + compareLength, -- * List transformations map, reverse, ===================================== libraries/base/src/Data/List/NonEmpty.hs ===================================== @@ -36,6 +36,7 @@ module Data.List.NonEmpty ( , sortWith -- :: Ord o => (a -> o) -> NonEmpty a -> NonEmpty a -- * Basic functions , length -- :: NonEmpty a -> Int + , compareLength , head -- :: NonEmpty a -> a , tail -- :: NonEmpty a -> [a] , last -- :: NonEmpty a -> a @@ -128,6 +129,30 @@ infixr 5 <| length :: NonEmpty a -> Int length (_ :| xs) = 1 + Prelude.length xs +-- | Use 'compareLength' @xs@ @n@ as a safer and faster alternative +-- to 'compare' ('length' @xs@) @n at . Similarly, it's better +-- to write @compareLength xs 10 == LT@ instead of @length xs < 10 at . +-- +-- While 'length' would force and traverse +-- the entire spine of @xs@ (which could even diverge if @xs@ is infinite), +-- 'compareLength' traverses at most @n@ elements to determine its result. +-- +-- >>> compareLength ('a' :| []) 1 +-- EQ +-- >>> compareLength ('a' :| ['b']) 3 +-- LT +-- >>> compareLength (0 :| [1..]) 100 +-- GT +-- >>> compareLength undefined 0 +-- GT +-- +-- @since base-4.21.0.0 +-- +compareLength :: NonEmpty a -> Int -> Ordering +compareLength xs n + | n < 1 = GT + | otherwise = foldr (\_ f m -> if 0 > m then GT else f (m - 1)) (compare 0) xs n + -- | Compute n-ary logic exclusive OR operation on 'NonEmpty' list. xor :: NonEmpty Bool -> Bool xor (x :| xs) = foldr xor' x xs ===================================== libraries/base/src/GHC/List.hs ===================================== @@ -22,7 +22,7 @@ module GHC.List ( -- * List-monomorphic Foldable methods and misc functions foldr, foldr', foldr1, foldl, foldl', foldl1, - null, length, elem, notElem, + null, length, compareLength, elem, notElem, maximum, minimum, sum, product, and, or, any, all, -- * Other functions ===================================== libraries/ghc-internal/src/GHC/Internal/Data/List.hs ===================================== @@ -30,6 +30,7 @@ module GHC.Internal.Data.List , singleton , null , length + , compareLength -- * List transformations , map ===================================== libraries/ghc-internal/src/GHC/Internal/Data/OldList.hs ===================================== @@ -30,6 +30,7 @@ module GHC.Internal.Data.OldList , singleton , null , length + , compareLength -- * List transformations , map ===================================== libraries/ghc-internal/src/GHC/Internal/List.hs ===================================== @@ -25,7 +25,7 @@ module GHC.Internal.List ( -- * List-monomorphic Foldable methods and misc functions foldr, foldr', foldr1, foldl, foldl', foldl1, - null, length, elem, notElem, + null, length, compareLength, elem, notElem, maximum, minimum, sum, product, and, or, any, all, -- * Other functions @@ -297,6 +297,34 @@ lengthFB _ r = \ !a -> r (a + 1) idLength :: Int -> Int idLength = id +-- | Use 'compareLength' @xs@ @n@ as a safer and faster alternative +-- to 'compare' ('length' @xs@) @n at . Similarly, it's better +-- to write @compareLength xs 10 == LT@ instead of @length xs < 10 at . +-- +-- While 'length' would force and traverse +-- the entire spine of @xs@ (which could even diverge if @xs@ is infinite), +-- 'compareLength' traverses at most @n@ elements to determine its result. +-- +-- >>> compareLength [] 0 +-- EQ +-- >>> compareLength [] 1 +-- LT +-- >>> compareLength ['a'] 1 +-- EQ +-- >>> compareLength ['a', 'b'] 1 +-- GT +-- >>> compareLength [0..] 100 +-- GT +-- >>> compareLength undefined (-1) +-- GT +-- +-- @since base-4.21.0.0 +-- +compareLength :: [a] -> Int -> Ordering +compareLength xs n + | n < 0 = GT + | otherwise = foldr (\_ f m -> if 0 > m then GT else f (m - 1)) (compare 0) xs n + -- | \(\mathcal{O}(n)\). 'filter', applied to a predicate and a list, returns -- the list of those elements that satisfy the predicate; i.e., -- ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -1299,6 +1299,7 @@ module Data.List where and :: forall (t :: * -> *). GHC.Internal.Data.Foldable.Foldable t => t GHC.Types.Bool -> GHC.Types.Bool any :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Types.Bool break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => t [a] -> [a] concatMap :: forall (t :: * -> *) a b. GHC.Internal.Data.Foldable.Foldable t => (a -> [b]) -> t a -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] @@ -1421,6 +1422,7 @@ module Data.List.NonEmpty where append :: forall a. NonEmpty a -> NonEmpty a -> NonEmpty a appendList :: forall a. NonEmpty a -> [a] -> NonEmpty a break :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> ([a], [a]) + compareLength :: forall a. NonEmpty a -> GHC.Types.Int -> GHC.Types.Ordering cons :: forall a. a -> NonEmpty a -> NonEmpty a cycle :: forall a. NonEmpty a -> NonEmpty a drop :: forall a. GHC.Types.Int -> NonEmpty a -> [a] @@ -8251,6 +8253,7 @@ module GHC.List where augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall a. [[a]] -> [a] concatMap :: forall a b. (a -> [b]) -> [a] -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] @@ -8904,6 +8907,7 @@ module GHC.OldList where and :: [GHC.Types.Bool] -> GHC.Types.Bool any :: forall a. (a -> GHC.Types.Bool) -> [a] -> GHC.Types.Bool break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall a. [[a]] -> [a] concatMap :: forall a b. (a -> [b]) -> [a] -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -1299,6 +1299,7 @@ module Data.List where and :: forall (t :: * -> *). GHC.Internal.Data.Foldable.Foldable t => t GHC.Types.Bool -> GHC.Types.Bool any :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Types.Bool break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => t [a] -> [a] concatMap :: forall (t :: * -> *) a b. GHC.Internal.Data.Foldable.Foldable t => (a -> [b]) -> t a -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] @@ -1421,6 +1422,7 @@ module Data.List.NonEmpty where append :: forall a. NonEmpty a -> NonEmpty a -> NonEmpty a appendList :: forall a. NonEmpty a -> [a] -> NonEmpty a break :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> ([a], [a]) + compareLength :: forall a. NonEmpty a -> GHC.Types.Int -> GHC.Types.Ordering cons :: forall a. a -> NonEmpty a -> NonEmpty a cycle :: forall a. NonEmpty a -> NonEmpty a drop :: forall a. GHC.Types.Int -> NonEmpty a -> [a] @@ -11293,6 +11295,7 @@ module GHC.List where augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall a. [[a]] -> [a] concatMap :: forall a b. (a -> [b]) -> [a] -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] @@ -11946,6 +11949,7 @@ module GHC.OldList where and :: [GHC.Types.Bool] -> GHC.Types.Bool any :: forall a. (a -> GHC.Types.Bool) -> [a] -> GHC.Types.Bool break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall a. [[a]] -> [a] concatMap :: forall a b. (a -> [b]) -> [a] -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -1299,6 +1299,7 @@ module Data.List where and :: forall (t :: * -> *). GHC.Internal.Data.Foldable.Foldable t => t GHC.Types.Bool -> GHC.Types.Bool any :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Types.Bool break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => t [a] -> [a] concatMap :: forall (t :: * -> *) a b. GHC.Internal.Data.Foldable.Foldable t => (a -> [b]) -> t a -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] @@ -1421,6 +1422,7 @@ module Data.List.NonEmpty where append :: forall a. NonEmpty a -> NonEmpty a -> NonEmpty a appendList :: forall a. NonEmpty a -> [a] -> NonEmpty a break :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> ([a], [a]) + compareLength :: forall a. NonEmpty a -> GHC.Types.Int -> GHC.Types.Ordering cons :: forall a. a -> NonEmpty a -> NonEmpty a cycle :: forall a. NonEmpty a -> NonEmpty a drop :: forall a. GHC.Types.Int -> NonEmpty a -> [a] @@ -8475,6 +8477,7 @@ module GHC.List where augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall a. [[a]] -> [a] concatMap :: forall a b. (a -> [b]) -> [a] -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] @@ -9128,6 +9131,7 @@ module GHC.OldList where and :: [GHC.Types.Bool] -> GHC.Types.Bool any :: forall a. (a -> GHC.Types.Bool) -> [a] -> GHC.Types.Bool break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall a. [[a]] -> [a] concatMap :: forall a b. (a -> [b]) -> [a] -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -1299,6 +1299,7 @@ module Data.List where and :: forall (t :: * -> *). GHC.Internal.Data.Foldable.Foldable t => t GHC.Types.Bool -> GHC.Types.Bool any :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Types.Bool break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => t [a] -> [a] concatMap :: forall (t :: * -> *) a b. GHC.Internal.Data.Foldable.Foldable t => (a -> [b]) -> t a -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] @@ -1421,6 +1422,7 @@ module Data.List.NonEmpty where append :: forall a. NonEmpty a -> NonEmpty a -> NonEmpty a appendList :: forall a. NonEmpty a -> [a] -> NonEmpty a break :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> ([a], [a]) + compareLength :: forall a. NonEmpty a -> GHC.Types.Int -> GHC.Types.Ordering cons :: forall a. a -> NonEmpty a -> NonEmpty a cycle :: forall a. NonEmpty a -> NonEmpty a drop :: forall a. GHC.Types.Int -> NonEmpty a -> [a] @@ -8251,6 +8253,7 @@ module GHC.List where augment :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] -> [a] break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) build :: forall a. (forall b. (a -> b -> b) -> b -> b) -> [a] + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall a. [[a]] -> [a] concatMap :: forall a b. (a -> [b]) -> [a] -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] @@ -8904,6 +8907,7 @@ module GHC.OldList where and :: [GHC.Types.Bool] -> GHC.Types.Bool any :: forall a. (a -> GHC.Types.Bool) -> [a] -> GHC.Types.Bool break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a]) + compareLength :: forall a. [a] -> GHC.Types.Int -> GHC.Types.Ordering concat :: forall a. [[a]] -> [a] concatMap :: forall a b. (a -> [b]) -> [a] -> [b] cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3feaa3e45860ca7130e3c4c86dc96ebb319455e6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3feaa3e45860ca7130e3c4c86dc96ebb319455e6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 14:45:25 2024 From: gitlab at gitlab.haskell.org (Adriaan Leijnse (@aidylns)) Date: Sat, 08 Jun 2024 10:45:25 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/aidylns/remove-sourcetext-from-overloadedlabel Message-ID: <66646e8514388_3096f92196ee410087f@gitlab.mail> Adriaan Leijnse pushed new branch wip/aidylns/remove-sourcetext-from-overloadedlabel at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/aidylns/remove-sourcetext-from-overloadedlabel You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 14:53:52 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Sat, 08 Jun 2024 10:53:52 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ast] AST: move negateOverLitVal into GHC.Hs.Lit Message-ID: <66647080d1f12_3096f922d3e381049d6@gitlab.mail> Fabian Kirchner pushed to branch wip/kirchner/ast at Glasgow Haskell Compiler / GHC Commits: f64a7cfb by Fabian Kirchner at 2024-06-08T16:52:33+02:00 AST: move negateOverLitVal into GHC.Hs.Lit The function negateOverLitVal is not used within Language.Haskell and therefore can be moved to the respective module inside GHC.Hs. - - - - - 2 changed files: - compiler/GHC/Hs/Lit.hs - compiler/Language/Haskell/Syntax/Lit.hs Changes: ===================================== compiler/GHC/Hs/Lit.hs ===================================== @@ -30,6 +30,7 @@ import GHC.Core.Ppr ( {- instance OutputableBndr TyVar -} ) import GHC.Types.SourceText import GHC.Core.Type import GHC.Utils.Outputable +import GHC.Utils.Panic (panic) import GHC.Hs.Extension import Language.Haskell.Syntax.Expr ( HsExpr ) import Language.Haskell.Syntax.Extension @@ -248,3 +249,7 @@ pmPprHsLit (HsRat _ f _) = ppr f pmPprHsLit (HsFloatPrim _ f) = ppr f pmPprHsLit (HsDoublePrim _ d) = ppr d +negateOverLitVal :: OverLitVal -> OverLitVal +negateOverLitVal (HsIntegral i) = HsIntegral (negateIntegralLit i) +negateOverLitVal (HsFractional f) = HsFractional (negateFractionalLit f) +negateOverLitVal _ = panic "negateOverLitVal: argument is not a number" ===================================== compiler/Language/Haskell/Syntax/Lit.hs ===================================== @@ -21,7 +21,7 @@ module Language.Haskell.Syntax.Lit where import Language.Haskell.Syntax.Extension import GHC.Utils.Panic (panic) -import GHC.Types.SourceText (IntegralLit, FractionalLit, SourceText, negateIntegralLit, negateFractionalLit) +import GHC.Types.SourceText (IntegralLit, FractionalLit, SourceText) import GHC.Core.Type (Type) import GHC.Data.FastString (FastString, lexicalCompareFS) @@ -128,11 +128,6 @@ data OverLitVal | HsIsString !SourceText !FastString -- ^ String-looking literals deriving Data -negateOverLitVal :: OverLitVal -> OverLitVal -negateOverLitVal (HsIntegral i) = HsIntegral (negateIntegralLit i) -negateOverLitVal (HsFractional f) = HsFractional (negateFractionalLit f) -negateOverLitVal _ = panic "negateOverLitVal: argument is not a number" - -- Comparison operations are needed when grouping literals -- for compiling pattern-matching (module GHC.HsToCore.Match.Literal) instance (Eq (XXOverLit p)) => Eq (HsOverLit p) where View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f64a7cfbc933834e2e1c5d795da41b0bde5514ca -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f64a7cfbc933834e2e1c5d795da41b0bde5514ca You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 15:24:24 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 08 Jun 2024 11:24:24 -0400 Subject: [Git][ghc/ghc][master] Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw Message-ID: <666477a8b6737_3096f92896938123684@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 5 changed files: - libraries/ghc-internal/src/GHC/Internal/Exception.hs - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/Exception.hs ===================================== @@ -79,7 +79,7 @@ import GHC.Internal.Exception.Type -- WARNING: You may want to use 'throwIO' instead so that your pure code -- stays exception-free. throw :: forall (r :: RuntimeRep). forall (a :: TYPE r). forall e. - (?callStack :: CallStack, Exception e) => e -> a + (HasCallStack, Exception e) => e -> a throw e = let !se = unsafePerformIO (toExceptionWithBacktrace e) in raise# se ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5319,7 +5319,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5288,7 +5288,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5465,7 +5465,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5319,7 +5319,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/edfe6140be64f0d9365f7e954d3db534d63bb04f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/edfe6140be64f0d9365f7e954d3db534d63bb04f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 15:25:06 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 08 Jun 2024 11:25:06 -0400 Subject: [Git][ghc/ghc][master] rts: cleanup inlining logic Message-ID: <666477d24ff08_3096f92a272fc1281a4@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 2 changed files: - rts/Inlines.c - rts/include/Stg.h Changes: ===================================== rts/Inlines.c ===================================== @@ -1,6 +1,7 @@ -// all functions declared with EXTERN_INLINE in the header files get -// compiled for real here, just in case the definition was not inlined -// at some call site: +// All functions declared with EXTERN_INLINE in the header files get +// compiled for real here. Some of them are called by Cmm (e.g. +// recordClosureMutated) and therefore the real thing needs to reside +// in Inlines.o for Cmm ccall to work. #define KEEP_INLINES #include "rts/PosixSource.h" #include "Rts.h" ===================================== rts/include/Stg.h ===================================== @@ -114,57 +114,19 @@ * 'Portable' inlining: * INLINE_HEADER is for inline functions in header files (macros) * STATIC_INLINE is for inline functions in source files - * EXTERN_INLINE is for functions that we want to inline sometimes - * (we also compile a static version of the function; see Inlines.c) + * EXTERN_INLINE is for functions that may be called in Cmm + * (we also compile a static version of an EXTERN_INLINE function; see Inlines.c) */ -// We generally assume C99 semantics albeit these two definitions work fine even -// when gnu90 semantics are active (i.e. when __GNUC_GNU_INLINE__ is defined or -// when a GCC older than 4.2 is used) -// -// The problem, however, is with 'extern inline' whose semantics significantly -// differs between gnu90 and C99 #define INLINE_HEADER static inline #define STATIC_INLINE static inline -// Figure out whether `__attributes__((gnu_inline))` is needed -// to force gnu90-style 'external inline' semantics. -#if defined(FORCE_GNU_INLINE) -// disable auto-detection since HAVE_GNU_INLINE has been defined externally -#elif defined(__GNUC_GNU_INLINE__) && __GNUC__ == 4 && __GNUC_MINOR__ == 2 -// GCC 4.2.x didn't properly support C99 inline semantics (GCC 4.3 was the first -// release to properly support C99 inline semantics), and therefore warned when -// using 'extern inline' while in C99 mode unless `__attributes__((gnu_inline))` -// was explicitly set. -# define FORCE_GNU_INLINE 1 -#endif - -#if defined(FORCE_GNU_INLINE) -// Force compiler into gnu90 semantics -# if defined(KEEP_INLINES) -# define EXTERN_INLINE inline __attribute__((gnu_inline)) -# else -# define EXTERN_INLINE extern inline __attribute__((gnu_inline)) -# endif -#elif defined(__GNUC_GNU_INLINE__) -// we're currently in gnu90 inline mode by default and -// __attribute__((gnu_inline)) may not be supported, so better leave it off -# if defined(KEEP_INLINES) -# define EXTERN_INLINE inline -# else -# define EXTERN_INLINE extern inline -# endif -#else -// Assume C99 semantics (yes, this curiously results in swapped definitions!) -// This is the preferred branch, and at some point we may drop support for -// compilers not supporting C99 semantics altogether. +// See comment in rts/Inlines.c for explanation. # if defined(KEEP_INLINES) # define EXTERN_INLINE extern inline # else -# define EXTERN_INLINE inline +# define EXTERN_INLINE static inline # endif -#endif - /* * GCC attributes View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/35a64220c9e47d64635ae732f33795c611eb1fc8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/35a64220c9e47d64635ae732f33795c611eb1fc8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 15:26:19 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 08 Jun 2024 11:26:19 -0400 Subject: [Git][ghc/ghc][master] CODEOWNERS: add @core-libraries to track base interface changes Message-ID: <6664781b12a59_3096f92c0162c132664@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 1 changed file: - CODEOWNERS Changes: ===================================== CODEOWNERS ===================================== @@ -60,6 +60,7 @@ /libraries/base/ @hvr /libraries/ghci/ @simonmar /libraries/template-haskell/ @rae +/testsuite/tests/interface-stability/ @core-libraries [Internal utilities and libraries] /utils/iserv-proxy/ @angerman @simonmar View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9ea90ed2e4870c7bfed3e09d0b033fc630802304 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9ea90ed2e4870c7bfed3e09d0b033fc630802304 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 15:44:29 2024 From: gitlab at gitlab.haskell.org (=?UTF-8?B?QmVyayDDlnprw7x0w7xrIChAb3prdXR1ayk=?=) Date: Sat, 08 Jun 2024 11:44:29 -0400 Subject: [Git][ghc/ghc][wip/ozkutuk/sprint-fun] 5395 commits: [haddock @ 2002-04-04 16:23:43 by simonmar] Message-ID: <66647c5ddc929_3096f92f5ca4c138296@gitlab.mail> Berk Özkütük pushed to branch wip/ozkutuk/sprint-fun at Glasgow Haskell Compiler / GHC Commits: 2b39cd94 by Simon Marlow at 2002-04-04T16:23:43+00:00 [haddock @ 2002-04-04 16:23:43 by simonmar] This is Haddock, my stab at a Haskell documentation tool. It's not quite ready for release yet, but I'm putting it in the repository so others can take a look. It uses a locally modified version of the hssource parser, extended with support for GHC extensions and documentation annotations. - - - - - 99ede94f by Simon Marlow at 2002-04-04T16:24:10+00:00 [haddock @ 2002-04-04 16:24:10 by simonmar] forgot one file - - - - - 8363294c by Simon Marlow at 2002-04-05T13:58:15+00:00 [haddock @ 2002-04-05 13:58:15 by simonmar] Remap names in the exported declarations to be "closer" to the current module. eg. if an exported declaration mentions a type 'T' which is imported from module A then re-exported from the current module, then links from the type or indeed the documentation will point to the current module rather than module A. This is to support better hiding: module A won't be referred to in the generated output. - - - - - 1570cbc1 by Simon Marlow at 2002-04-05T13:58:23+00:00 [haddock @ 2002-04-05 13:58:23 by simonmar] update the TODO list - - - - - 3a62f96b by Simon Marlow at 2002-04-05T14:11:51+00:00 [haddock @ 2002-04-05 14:11:51 by simonmar] Fix the anchor for a class declaration - - - - - c5d9a471 by Simon Marlow at 2002-04-05T14:18:41+00:00 [haddock @ 2002-04-05 14:18:41 by simonmar] remove underlines on visited links - - - - - 97280525 by Simon Marlow at 2002-04-05T16:11:47+00:00 [haddock @ 2002-04-05 16:11:47 by simonmar] - Update to generate more correct HTML. - Use our own non-overloaded table combinators, as the overloaded versions were giving me a headache. The improved type safety caught several errors in the HTML generation. - - - - - 9acd3a4d by Simon Marlow at 2002-04-05T16:32:19+00:00 [haddock @ 2002-04-05 16:32:19 by simonmar] Add width property to the title, and add TD.children for the module contents page. - - - - - ec9a0847 by Simon Marlow at 2002-04-08T16:39:56+00:00 [haddock @ 2002-04-08 16:39:56 by simonmar] Fix a problem with exports of the form T(..). - - - - - e4627dc8 by Simon Marlow at 2002-04-08T16:41:38+00:00 [haddock @ 2002-04-08 16:41:37 by simonmar] - Add our own versions of Html & BlockTable for the time being. - Add support for generating an index to the HTML backend - - - - - 2d73fd75 by Simon Marlow at 2002-04-09T11:23:24+00:00 [haddock @ 2002-04-09 11:23:24 by simonmar] Add '-- /' as a synonym for '-- |', for compatibility with IDoc. - - - - - 3675464e by Simon Marlow at 2002-04-09T11:33:55+00:00 [haddock @ 2002-04-09 11:33:54 by simonmar] - add the <...> syntax for marking up URLs in documentation - Make the output for data & class declarations more compact when there aren't any documentation annotations on the individual methods or constructors respectively. - - - - - 5077f5b1 by Simon Marlow at 2002-04-09T11:36:04+00:00 [haddock @ 2002-04-09 11:36:04 by simonmar] Update the TODO list - - - - - 9e83c54d by Simon Marlow at 2002-04-10T10:50:06+00:00 [haddock @ 2002-04-10 10:50:06 by simonmar] Use explicit 'px' suffix on pixel sizes; IE seems to prefer them - - - - - 052de51c by Simon Marlow at 2002-04-10T13:23:13+00:00 [haddock @ 2002-04-10 13:23:13 by simonmar] Lex URLs as a single token to avoid having to escape special characters inside the URL string. - - - - - 47187edb by Simon Marlow at 2002-04-10T13:23:55+00:00 [haddock @ 2002-04-10 13:23:55 by simonmar] Not sure why I made the constructor name for a record declaration into a TyCls name, but change it back into a Var name anyhow. - - - - - 3dc6aa81 by Simon Marlow at 2002-04-10T13:26:10+00:00 [haddock @ 2002-04-10 13:26:09 by simonmar] Lots of changes, including: - add index support to the HTML backend - clean up the renamer, put it into a monad - propogate unresolved names to the top level and report them in a nicer way - various bugfixes - - - - - c2a70a72 by Simon Marlow at 2002-04-10T13:32:39+00:00 [haddock @ 2002-04-10 13:32:39 by simonmar] Skeleton documentation - - - - - 50c98d17 by Simon Marlow at 2002-04-10T13:37:23+00:00 [haddock @ 2002-04-10 13:37:23 by simonmar] Update the TODO list, separate into pre-1.0 and post-1.0 items - - - - - f3778be6 by Simon Marlow at 2002-04-10T14:30:58+00:00 [haddock @ 2002-04-10 14:30:58 by simonmar] Add an introduction - - - - - cfbaf9f7 by Simon Marlow at 2002-04-10T14:59:51+00:00 [haddock @ 2002-04-10 14:59:51 by simonmar] Sort the module tree - - - - - 76bd7b34 by Simon Marlow at 2002-04-10T15:50:11+00:00 [haddock @ 2002-04-10 15:50:10 by simonmar] Generate a little table of contents at the top of the module doc (only if the module actually contains some section headings, though). - - - - - bb8560a1 by Simon Marlow at 2002-04-10T16:10:26+00:00 [haddock @ 2002-04-10 16:10:26 by simonmar] Now we understand (or at least don't barf on) type signatures in patterns such as you might find when scoped type variables are in use. - - - - - 86c2a026 by Simon Marlow at 2002-04-10T16:10:49+00:00 [haddock @ 2002-04-10 16:10:49 by simonmar] more updates - - - - - 1c052b0e by Simon Marlow at 2002-04-10T16:28:05+00:00 [haddock @ 2002-04-10 16:28:05 by simonmar] Parse errors in doc strings are now reported as warnings rather that causing the whole thing to fall over. It still needs cleaning up (the warning is emitted with trace) but this will do for the time being. - - - - - ace03e8f by Simon Marlow at 2002-04-10T16:38:03+00:00 [haddock @ 2002-04-10 16:38:03 by simonmar] update again - - - - - 69006c3e by Simon Marlow at 2002-04-11T13:38:02+00:00 [haddock @ 2002-04-11 13:38:02 by simonmar] mention Opera - - - - - fe9b10f8 by Simon Marlow at 2002-04-11T13:40:31+00:00 [haddock @ 2002-04-11 13:40:30 by simonmar] - copy haddock.css into the same place as the generated HTML - new option: --css <file> specifies the style sheet to use - new option: -o <dir> specifies the directory in which to generate the output. - because Haddock now needs to know where to find its default stylesheet, we have to have a wrapper script and do the haddock-inplace thing (Makefile code copied largely from fptools/happy). - - - - - 106adbbe by Simon Marlow at 2002-04-24T15:12:41+00:00 [haddock @ 2002-04-24 15:12:41 by simonmar] Stop slurping comment lines when we see a row of dashes longer than length 2: these are useful as separators. - - - - - 995d3f9e by Simon Marlow at 2002-04-24T15:14:12+00:00 [haddock @ 2002-04-24 15:14:11 by simonmar] Grok the kind of module headers we use in fptools/libraries, and pass the "portability", "stability", and "maintainer" strings through into the generated HTML. If the module header doesn't match the pattern, then we don't include the info in the HTML. - - - - - e14da136 by Simon Marlow at 2002-04-24T15:16:57+00:00 [haddock @ 2002-04-24 15:16:57 by simonmar] Done module headers now. - - - - - 2ca8dfd4 by Simon Marlow at 2002-04-24T15:57:48+00:00 [haddock @ 2002-04-24 15:57:47 by simonmar] Handle gcons in export lists (a common extension). - - - - - 044cea81 by Simon Marlow at 2002-04-25T14:20:12+00:00 [haddock @ 2002-04-25 14:20:12 by simonmar] Add the little lambda icon - - - - - 63955027 by Simon Marlow at 2002-04-25T14:40:05+00:00 [haddock @ 2002-04-25 14:40:05 by simonmar] - Add support for named chunks of documentation which can be referenced from the export list. - Copy the icon from $libdir to the destination in HTML mode. - - - - - 36e3f913 by Simon Marlow at 2002-04-25T16:48:36+00:00 [haddock @ 2002-04-25 16:48:36 by simonmar] More keyboard bashing - - - - - 7ae18dd0 by Simon Marlow at 2002-04-26T08:43:33+00:00 [haddock @ 2002-04-26 08:43:33 by simonmar] Package util reqd. to compile with 4.08.2 - - - - - bbd5fbab by Simon Marlow at 2002-04-26T10:13:00+00:00 [haddock @ 2002-04-26 10:13:00 by simonmar] Include $(GHC_HAPPY_OPTS) when compiling HsParser - - - - - 31c53d79 by Simon Marlow at 2002-04-26T11:18:57+00:00 [haddock @ 2002-04-26 11:18:56 by simonmar] - support for fundeps (partially contributed by Brett Letner - thanks Brett). - make it build with GHC 4.08.2 - - - - - c415ce76 by Simon Marlow at 2002-04-26T13:15:02+00:00 [haddock @ 2002-04-26 13:15:02 by simonmar] Move the explicit formatting of the little table for the stability/portability/maintainer info from the HTML into the CSS, and remove the explicit table size (just right-align it). - - - - - 520ee21a by Simon Marlow at 2002-04-26T16:01:44+00:00 [haddock @ 2002-04-26 16:01:44 by simonmar] Yet more keyboard bashing - this is pretty much complete now. - - - - - 2ae37179 by Simon Marlow at 2002-04-26T16:02:14+00:00 [haddock @ 2002-04-26 16:02:14 by simonmar] Add a couple of things I forgot about - - - - - b7211e04 by Simon Marlow at 2002-04-29T15:28:12+00:00 [haddock @ 2002-04-29 15:28:12 by simonmar] bugfix for declBinders on a NewTypeDecl - - - - - 640c154a by Simon Marlow at 2002-04-29T15:28:54+00:00 [haddock @ 2002-04-29 15:28:54 by simonmar] Allow '-- |' style annotations on constructors and record fields. - - - - - 393f258a by Simon Marlow at 2002-04-29T15:37:32+00:00 [haddock @ 2002-04-29 15:37:32 by simonmar] syntax fix - - - - - 8a2c2549 by Simon Marlow at 2002-04-29T15:37:48+00:00 [haddock @ 2002-04-29 15:37:48 by simonmar] Add an example - - - - - db88f8a2 by Simon Marlow at 2002-04-29T15:55:46+00:00 [haddock @ 2002-04-29 15:55:46 by simonmar] remove a trace - - - - - 2b0248e0 by Simon Marlow at 2002-04-29T15:56:19+00:00 [haddock @ 2002-04-29 15:56:19 by simonmar] Fix for 'make install' - - - - - 120453a0 by Simon Marlow at 2002-04-29T15:56:39+00:00 [haddock @ 2002-04-29 15:56:39 by simonmar] Install the auxilliary bits - - - - - 950e6dbb by Simon Marlow at 2002-04-29T15:57:30+00:00 [haddock @ 2002-04-29 15:57:30 by simonmar] Add BinDist bits - - - - - 154b9d71 by Simon Marlow at 2002-05-01T11:02:52+00:00 [haddock @ 2002-05-01 11:02:52 by simonmar] update - - - - - ba6c39fa by Simon Marlow at 2002-05-01T11:03:26+00:00 [haddock @ 2002-05-01 11:03:26 by simonmar] Add another item - - - - - bacb5e33 by Simon Marlow at 2002-05-03T08:50:00+00:00 [haddock @ 2002-05-03 08:50:00 by simonmar] Fix some typos. - - - - - 54c87895 by Sven Panne at 2002-05-05T19:40:51+00:00 [haddock @ 2002-05-05 19:40:51 by panne] As a temporary hack/workaround for a bug in GHC's simplifier, don't pass Happy the -c option for generating the parsers in this subdir. Furthermore, disable -O for HaddocParse, too. - - - - - e6c08703 by Simon Marlow at 2002-05-06T09:51:10+00:00 [haddock @ 2002-05-06 09:51:10 by simonmar] Add RPM spec file (thanks to Tom Moertel <tom-rpms at moertel.com>) - - - - - 7b8fa8e7 by Simon Marlow at 2002-05-06T12:29:26+00:00 [haddock @ 2002-05-06 12:29:26 by simonmar] Add missing type signature (a different workaround for the bug in GHC's simplifier). - - - - - cd0e300d by Simon Marlow at 2002-05-06T12:30:09+00:00 [haddock @ 2002-05-06 12:30:09 by simonmar] Remove workaround for simplifier bug in previous revision. - - - - - 687e68fa by Simon Marlow at 2002-05-06T12:32:32+00:00 [haddock @ 2002-05-06 12:32:32 by simonmar] Allow empty data declarations (another GHC extension). - - - - - 8f29f696 by Simon Marlow at 2002-05-06T12:49:21+00:00 [haddock @ 2002-05-06 12:49:21 by simonmar] Fix silly bug in named documentation block lookup. - - - - - 8e0059af by Simon Marlow at 2002-05-06T13:02:42+00:00 [haddock @ 2002-05-06 13:02:42 by simonmar] Add another named chunk with a different name - - - - - 68f8a896 by Simon Marlow at 2002-05-06T13:32:32+00:00 [haddock @ 2002-05-06 13:32:32 by simonmar] Be more lenient about extra paragraph breaks - - - - - 65fc31db by Simon Marlow at 2002-05-07T15:36:36+00:00 [haddock @ 2002-05-07 15:36:36 by simonmar] DocEmpty is a right and left-unit of DocAppend (remove it in the smart constructor). - - - - - adc81078 by Simon Marlow at 2002-05-07T15:37:15+00:00 [haddock @ 2002-05-07 15:37:15 by simonmar] Allow code blocks to be denoted with bird-tracks in addition to [...]. - - - - - 1283a3c1 by Simon Marlow at 2002-05-08T11:21:56+00:00 [haddock @ 2002-05-08 11:21:56 by simonmar] Add a facility for specifying options that affect Haddock's treatment of the module. Options are given at the top of the module in a comma-separated list, beginning with '-- #'. eg. -- # prune, hide, ignore-exports Options currently available, with their meanings: prune: ignore declarations which have no documentation annotations ignore-exports: act as if the export list were not specified (i.e. export everything local to the module). hide: do not include this module in the generated documentation, but propagate any exported definitions to modules which re-export them. There's a slight change in the semantics for re-exporting a full module by giving 'module M' in the export list: if module M does not have the 'hide' option, then the documentation will now just contain a reference to module M rather than the full inlined contents of that module. These features, and some other changes in the pipeline, are the result of discussions between myself and Manuel Chakravarty <chak at cse.unsw.edu.au> (author of IDoc) yesterday. Also: some cleanups, use a Writer monad to collect error messages in some places instead of just printing them with trace. - - - - - a2239cf5 by Simon Marlow at 2002-05-08T11:22:30+00:00 [haddock @ 2002-05-08 11:22:30 by simonmar] Update to test new features. - - - - - 6add955f by Simon Marlow at 2002-05-08T13:37:25+00:00 [haddock @ 2002-05-08 13:37:25 by simonmar] Change the markup for typewriter-font from [...] to @... at . The reasoning is that the '@' symbol is much less likely to be needed than square brackets, and we don't want to have to escape square brackets in code fragments. This will be mildly painful in the short term, but it's better to get the change out of the way as early as possible. - - - - - cda06447 by Simon Marlow at 2002-05-08T13:39:56+00:00 [haddock @ 2002-05-08 13:39:56 by simonmar] Allow nested-style comments to be used as documentation annotations too. eg. {-| ... -} is equivalent to -- | ... An extra space can also be left after the comment opener: {- | ... -}. The only version that isn't allowed is {-# ... -}, because this syntax overlaps with Haskell pragmas; use {- # ... -} instead. - - - - - db23f65e by Simon Marlow at 2002-05-08T14:48:41+00:00 [haddock @ 2002-05-08 14:48:39 by simonmar] Add support for existential quantifiers on constructors. - - - - - adce3794 by Simon Marlow at 2002-05-08T15:43:25+00:00 [haddock @ 2002-05-08 15:43:25 by simonmar] update - - - - - 62a1f436 by Simon Marlow at 2002-05-08T15:44:10+00:00 [haddock @ 2002-05-08 15:44:10 by simonmar] Update to version 0.2 - - - - - f6a24ba3 by Simon Marlow at 2002-05-09T08:48:29+00:00 [haddock @ 2002-05-09 08:48:29 by simonmar] typo - - - - - 9f9522a4 by Simon Marlow at 2002-05-09T10:33:14+00:00 [haddock @ 2002-05-09 10:33:14 by simonmar] oops, left out '/' from the special characters in the last change. - - - - - 14abcb39 by Simon Marlow at 2002-05-09T10:34:44+00:00 [haddock @ 2002-05-09 10:34:44 by simonmar] Fix buglet - - - - - b8d878be by Simon Marlow at 2002-05-09T10:35:00+00:00 [haddock @ 2002-05-09 10:35:00 by simonmar] Give a more useful instance of Show for Module. - - - - - f7bfd626 by Simon Marlow at 2002-05-09T10:37:07+00:00 [haddock @ 2002-05-09 10:37:07 by simonmar] The last commit to Main.lhs broke the delicate balance of laziness which was being used to avoid computing the dependency graph of modules. So I finally bit the bullet and did a proper topological sort of the module graph, which turned out to be easy (stealing the Digraph module from GHC - this really ought to be in the libraries somewhere). - - - - - b481c1d0 by Simon Marlow at 2002-05-09T10:37:25+00:00 [haddock @ 2002-05-09 10:37:25 by simonmar] another item done - - - - - 032e2b42 by Simon Marlow at 2002-05-09T10:44:15+00:00 [haddock @ 2002-05-09 10:44:15 by simonmar] Don't consider a module re-export as having documentation, for the purposes of deciding whether we need a Synopsis section or not. - - - - - 5fb45e92 by Simon Marlow at 2002-05-09T11:10:55+00:00 [haddock @ 2002-05-09 11:10:55 by simonmar] Add a special case for list types in ppHsAType - - - - - 1937e428 by Simon Marlow at 2002-05-09T12:43:06+00:00 [haddock @ 2002-05-09 12:43:06 by simonmar] Type synonyms can accept a ctype on the RHS, to match GHC. - - - - - 0f16ce56 by Simon Marlow at 2002-05-09T12:45:19+00:00 [haddock @ 2002-05-09 12:45:19 by simonmar] Add 'stdcall' keyword - - - - - 29b0d7d2 by Simon Marlow at 2002-05-09T13:35:45+00:00 [haddock @ 2002-05-09 13:35:45 by simonmar] Add System Requirements section - - - - - bf14dddd by Simon Marlow at 2002-05-09T13:36:11+00:00 [haddock @ 2002-05-09 13:36:11 by simonmar] Test existential types, amongst other things - - - - - 502f8f6f by Simon Marlow at 2002-05-09T13:37:35+00:00 [haddock @ 2002-05-09 13:37:35 by simonmar] Print the module name in a doc-string parse error - - - - - ca1f8d49 by Simon Marlow at 2002-05-09T13:38:04+00:00 [haddock @ 2002-05-09 13:38:04 by simonmar] Add dependency - - - - - 8d3d91ff by Simon Marlow at 2002-05-09T15:37:57+00:00 [haddock @ 2002-05-09 15:37:57 by simonmar] Add the changelog/release notes - - - - - f3960959 by Simon Marlow at 2002-05-09T15:47:47+00:00 [haddock @ 2002-05-09 15:47:47 by simonmar] mention the backquote-style of markup - - - - - 089fb6e6 by Simon Marlow at 2002-05-09T15:59:45+00:00 [haddock @ 2002-05-09 15:59:45 by simonmar] update - - - - - bdd3be0b by Simon Marlow at 2002-05-09T15:59:56+00:00 [haddock @ 2002-05-09 15:59:56 by simonmar] Document changes since 0.1 - - - - - 00fc4af8 by Simon Marlow at 2002-05-10T08:22:48+00:00 [haddock @ 2002-05-10 08:22:48 by simonmar] oops, update to version 0.2 - - - - - a8a79041 by Simon Marlow at 2002-05-10T16:05:08+00:00 [haddock @ 2002-05-10 16:05:08 by simonmar] Only include a mini-contents if there are 2 or more sections - - - - - 06653319 by Simon Marlow at 2002-05-13T09:13:12+00:00 [haddock @ 2002-05-13 09:13:12 by simonmar] fix typos - - - - - 1402b19b by Simon Marlow at 2002-05-13T10:14:22+00:00 [haddock @ 2002-05-13 10:14:22 by simonmar] Allow backquote as the right-hand quote as well as the left-hand quote, as suggested by Dean Herrington. Clean up the grammar a litte. - - - - - dcd5320d by Simon Marlow at 2002-05-13T10:44:10+00:00 [haddock @ 2002-05-13 10:44:10 by simonmar] a couple more things, prioritise a bit - - - - - a90130c4 by Simon Marlow at 2002-05-13T15:19:03+00:00 [haddock @ 2002-05-13 15:19:03 by simonmar] Cope with datatypes which have documentation on the constructor but not the type itself, and records which have documentation on the fields but not the constructor. (Thanks to Ross Paterson for pointing out the bugs). - - - - - a774d432 by Simon Marlow at 2002-05-13T15:20:54+00:00 [haddock @ 2002-05-13 15:20:54 by simonmar] Fix one of the record examples - - - - - 2d1d5218 by Simon Marlow at 2002-05-15T12:44:35+00:00 [haddock @ 2002-05-15 12:44:35 by simonmar] Preserve the newline before a bird-track, but only within a paragraph. - - - - - 1554c09a by Simon Marlow at 2002-05-15T13:03:02+00:00 [haddock @ 2002-05-15 13:03:01 by simonmar] Reworking of the internals to support documenting function arguments (the Most Wanted new feature by the punters). The old method of keeping parsed documentation in a Name -> Doc mapping wasn't going to cut it for anntations on type components, where there's no name to attach the documentation to, so I've moved to storing all the documentation in the abstract syntax. Previously some of the documentation was left in the abstract syntax by the parser, but was later extracted into the mapping. In order to avoid having to parameterise the abstract syntax over the type of documentation stored in it, we have to parse the documentation at the same time as we parse the Haskell source (well, I suppose we could store 'Either String Doc' in the HsSyn, but that's clunky). One upshot is that documentation is now parsed eagerly, and documentation parse errors are fatal (but have better line numbers in the error message). The new story simplifies matters for the code that processes the source modules, because we don't have to maintain the extra Name->Doc mapping, and it should improve efficiency a little too. New features: - Function arguments and return values can now have doc annotations. - If you refer to a qualified name in a doc string, eg. 'IO.putStr', then Haddock will emit a hyperlink even if the identifier is not in scope, so you don't have to make sure everything referred to from the documentation is imported. - several bugs & minor infelicities fixed. - - - - - 57344dc3 by Simon Marlow at 2002-05-15T13:03:19+00:00 [haddock @ 2002-05-15 13:03:19 by simonmar] Bump to version 0.3 - - - - - b2791812 by Simon Marlow at 2002-05-15T13:03:41+00:00 [haddock @ 2002-05-15 13:03:41 by simonmar] update - - - - - fead183e by Simon Marlow at 2002-05-15T13:10:15+00:00 [haddock @ 2002-05-15 13:10:15 by simonmar] Rename Foo.hs to Test.hs, and add a Makefile - - - - - b0b1f89f by Simon Marlow at 2002-05-15T13:16:07+00:00 [haddock @ 2002-05-15 13:16:07 by simonmar] - Remove the note about function argument docs not being implemented - Note that qualified identifiers can be used to point to entities that aren't in scope. - - - - - 5665f31a by Simon Marlow at 2002-05-15T13:28:46+00:00 [haddock @ 2002-05-15 13:28:46 by simonmar] Patch to add support for GHC-style primitive strings ".."#, from Ross Paterson. - - - - - 0564505d by Simon Marlow at 2002-05-17T10:51:57+00:00 [haddock @ 2002-05-17 10:51:57 by simonmar] Fix bugs in qualified name handling (A.B.f was returned as B.f) - - - - - 10e7311c by Simon Marlow at 2002-05-21T10:24:52+00:00 [haddock @ 2002-05-21 10:24:52 by simonmar] - Use an alternate tabular layout for datatypes, which is more compact - Fix some problems with the function argument documentation - - - - - 2f91c2a6 by Simon Marlow at 2002-05-21T10:27:40+00:00 [haddock @ 2002-05-21 10:27:40 by simonmar] add a few more test cases - - - - - 01c2ddd2 by Simon Marlow at 2002-05-21T10:28:33+00:00 [haddock @ 2002-05-21 10:28:33 by simonmar] Rearrange a bit, and add support for tabular datatype rendering - - - - - a4e4c5f8 by Simon Marlow at 2002-05-27T09:03:52+00:00 [haddock @ 2002-05-27 09:03:51 by simonmar] Lots of changes: - instances of a class are listed with the class, and instances involving a datatype are listed with that type. Derived instances aren't included at the moment: the calculation to find the instance head for a derived instance is non-trivial. - some formatting changes; use rows with specified height rather than cellspacing in some places. - various fixes (source file links were wrong, amongst others) - - - - - 48722e68 by Simon Marlow at 2002-05-27T12:30:38+00:00 [haddock @ 2002-05-27 12:30:37 by simonmar] - Put function arguments *before* the doc for the function, as suggested by Sven Panne. This looks nicer when the function documentation is long. - Switch to using bold for binders at the definition site, and use underline for keywords. This makes the binder stand out more. - - - - - 657204d2 by Simon Marlow at 2002-05-27T13:19:49+00:00 [haddock @ 2002-05-27 13:19:49 by simonmar] Fix bug: we weren't renaming HsDocCommentNamed in renameDecl - - - - - 592aae66 by Simon Marlow at 2002-05-27T14:10:27+00:00 [haddock @ 2002-05-27 14:10:27 by simonmar] Fix some bugs in the rendering of qualified type signatures. - - - - - 69c8f763 by Simon Marlow at 2002-05-27T14:36:45+00:00 [haddock @ 2002-05-27 14:36:45 by simonmar] warning message tweak - - - - - 16e64e21 by Simon Marlow at 2002-05-27T14:53:53+00:00 [haddock @ 2002-05-27 14:53:53 by simonmar] hyperlinked identifiers should be in <tt> - - - - - 8d5e4783 by Simon Marlow at 2002-05-27T15:56:45+00:00 [haddock @ 2002-05-27 15:56:45 by simonmar] Do something sensible for modules which don't export anything (except instances). - - - - - 9d3ef811 by Simon Marlow at 2002-05-28T10:12:50+00:00 [haddock @ 2002-05-28 10:12:50 by simonmar] Rename the module documentation properly (bug reported by Sven Panne). - - - - - ef03a1cc by Simon Marlow at 2002-05-28T10:13:04+00:00 [haddock @ 2002-05-28 10:13:04 by simonmar] Add some more test cases - - - - - 92baa0e8 by Simon Marlow at 2002-05-28T11:17:55+00:00 [haddock @ 2002-05-28 11:17:55 by simonmar] If an identifier doesn't lex, then just replace it by a DocString. - - - - - a3156213 by Simon Marlow at 2002-05-28T16:16:19+00:00 [haddock @ 2002-05-28 16:16:19 by simonmar] Only link to names in the current module which are actually listed in the documentation. A name may be exported but not present in the documentation if it is exported as part of a 'module M' export specifier. - - - - - 31acf941 by Simon Marlow at 2002-05-28T16:17:11+00:00 [haddock @ 2002-05-28 16:17:11 by simonmar] update - - - - - 7e474ebf by Sigbjorn Finne at 2002-05-28T22:42:08+00:00 [haddock @ 2002-05-28 22:42:08 by sof] Handle lone occurrences of '/', e.g., -- | This/that. [did this in the lexer rather than in the parser, as I couldn't see a way not to introduce an S/R conflict that way.] - - - - - 093f7e53 by Simon Marlow at 2002-05-29T09:09:49+00:00 [haddock @ 2002-05-29 09:09:49 by simonmar] Back out previous change until we can find a better way to do this. - - - - - 9234389c by Simon Marlow at 2002-05-29T13:19:06+00:00 [haddock @ 2002-05-29 13:19:06 by simonmar] Make the markup syntax a little more friendly: - single quotes are now interpreted literally unless they surround a valid Haskell identifier. So for example now there's no need to escape a single quote used as an apostrophe. - text to the right of a bird track is now literal (if you want marked-up text in a code block, use @...@). - - - - - b3333526 by Simon Marlow at 2002-05-29T13:38:51+00:00 [haddock @ 2002-05-29 13:38:51 by simonmar] Document recent changes to markup syntax - - - - - f93641d6 by Simon Marlow at 2002-05-29T15:27:18+00:00 [haddock @ 2002-05-29 15:27:18 by simonmar] Include the instances in abstract data types too - - - - - 613f21e3 by Simon Marlow at 2002-06-03T13:05:58+00:00 [haddock @ 2002-06-03 13:05:57 by simonmar] Allow exporting of individual class methods and record selectors. For these we have to invent the correct type signature, which we do in the simplest possible way (i.e. no context reduction nonsense in the class case). - - - - - 14b36807 by Simon Marlow at 2002-06-03T13:20:00+00:00 [haddock @ 2002-06-03 13:20:00 by simonmar] Fix linking to qualified names again (thanks to Sven Panne for pointing out the bug). - - - - - 95b10eac by Simon Marlow at 2002-06-03T13:46:48+00:00 [haddock @ 2002-06-03 13:46:48 by simonmar] Fix for exporting record selectors from a newtype declaration - - - - - 272f932e by Simon Marlow at 2002-06-03T13:56:38+00:00 [haddock @ 2002-06-03 13:56:38 by simonmar] update to version 0.3 - - - - - 1c0a3bed by Simon Marlow at 2002-06-03T14:05:07+00:00 [haddock @ 2002-06-03 14:05:07 by simonmar] Add changes in version 0.3 - - - - - 145b4626 by Simon Marlow at 2002-06-03T14:12:38+00:00 [haddock @ 2002-06-03 14:12:38 by simonmar] Render class names as proper binders - - - - - 052106b3 by Simon Marlow at 2002-06-03T14:15:10+00:00 [haddock @ 2002-06-03 14:15:10 by simonmar] update, and separate into bugs, features, and cosmetic items. - - - - - 854f4914 by Simon Marlow at 2002-06-03T14:16:13+00:00 [haddock @ 2002-06-03 14:16:13 by simonmar] More test cases - - - - - 466922c8 by Simon Marlow at 2002-06-03T14:16:56+00:00 [haddock @ 2002-06-03 14:16:56 by simonmar] Example from the paper - - - - - 9962a045 by Simon Marlow at 2002-06-03T14:17:49+00:00 [haddock @ 2002-06-03 14:17:49 by simonmar] A debugging version of the style-sheet, which gives some tables coloured backgrounds so we can see what's going on. - - - - - f16b79db by Simon Marlow at 2002-06-03T14:19:46+00:00 [haddock @ 2002-06-03 14:19:46 by simonmar] typo - - - - - 620db27b by Simon Marlow at 2002-06-03T14:48:32+00:00 [haddock @ 2002-06-03 14:48:32 by simonmar] oops, fix markup bugs - - - - - 53fd105c by Simon Marlow at 2002-06-05T09:05:07+00:00 [haddock @ 2002-06-05 09:05:07 by simonmar] Keep foreign imports when there is no export list (bug reported by Sven Panne). - - - - - 6d98989c by Simon Marlow at 2002-06-05T09:12:02+00:00 [haddock @ 2002-06-05 09:12:02 by simonmar] Identifiers in single quotes can be symbol names too (bug reported by Hal Daume). - - - - - 001811e5 by Sven Panne at 2002-06-08T14:03:36+00:00 [haddock @ 2002-06-08 14:03:36 by panne] Tiny workaround for the fact that Haddock currently ignores HsImportSpecs: Let the local_orig_env take precedence. This is no real solution at all, but improves things sometimes, e.g. in my GLUT documentation. :-) - - - - - 504d19c9 by Simon Marlow at 2002-06-11T09:23:25+00:00 [haddock @ 2002-06-11 09:23:25 by simonmar] portability nit - - - - - e13b5af4 by Simon Marlow at 2002-06-20T12:38:07+00:00 [haddock @ 2002-06-20 12:38:07 by simonmar] Empty declaration fixes. - - - - - f467a9b6 by Simon Marlow at 2002-06-20T12:39:02+00:00 [haddock @ 2002-06-20 12:39:01 by simonmar] Add support for a "prologue" - a description for the whole library, placed on the contents page before the module list. - - - - - b8dbfe20 by Simon Marlow at 2002-06-21T12:43:06+00:00 [haddock @ 2002-06-21 12:43:06 by simonmar] When we have a single code block paragraph, don't place it in <pre>..</pre>, just use <tt>..</tt> to avoid generating extra vertical white space in some browsers. - - - - - 4831dbbd by Simon Marlow at 2002-06-21T15:50:42+00:00 [haddock @ 2002-06-21 15:50:42 by simonmar] Add support for reading and writing interface files(!) This turned out to be quite easy, and necessary to get decent hyperlinks between the documentation for separate packages in the libraries. The functionality isn't quite complete yet: for a given package of modules, you'd like to say "the HTML for these modules lives in directory <dir>" (currently they are assumed to be all in the same place). Two new flags: --dump-interface=FILE dump an interface file in FILE --read-interface=FILE read interface from FILE an interface file describes *all* the modules being processed. Only the exported names are kept in the interface: if you re-export a name from a module in another interface the signature won't be copied. This is a compromise to keep the size of the interfaces sensible. Also, I added another useful option: --no-implicit-prelude avoids trying to import the Prelude. Previously this was the default, but now importing the Prelude from elsewhere makes sense if you also read in an interface containing the Prelude module, so Haddock imports the Prelude implicitly according to the Haskell spec. - - - - - d3640a19 by Sven Panne at 2002-06-23T14:54:00+00:00 [haddock @ 2002-06-23 14:54:00 by panne] Make it compile with newer GHCs - - - - - 780c506b by Sven Panne at 2002-06-23T15:44:31+00:00 [haddock @ 2002-06-23 15:44:31 by panne] Cleaned up build root handling and added more docs - - - - - 45290d2e by Simon Marlow at 2002-06-24T14:37:43+00:00 [haddock @ 2002-06-24 14:37:42 by simonmar] When reading an interface, allow a file path offset to be specified which represents the path to the HTML files for the modules specified by that interface. The path may be either relative (to the location of the HTML for this package), or absolute. The syntax is --read-interface=PATH,FILE where PATH is the path to the HTML, and FILE is the filename containing the interface. - - - - - 4e2b9ae6 by Simon Marlow at 2002-07-03T16:01:08+00:00 [haddock @ 2002-07-03 16:01:07 by simonmar] Handle import specs properly, include 'hiding'. Haddock now has a complete implementation of the Haskell module system (more or less; I won't claim it's 100% correct). - - - - - 9a9aa1a8 by Simon Marlow at 2002-07-03T16:18:16+00:00 [haddock @ 2002-07-03 16:18:16 by simonmar] Update - - - - - 560c3026 by Simon Marlow at 2002-07-04T14:56:10+00:00 [haddock @ 2002-07-04 14:56:10 by simonmar] Clean up the code that constructs the exported declarations, and fix a couple of bugs along the way. Now if you import a class hiding one of the methods, then re-export the class, the version in the documentation will correctly have the appropriate method removed. - - - - - 2c26e77d by Simon Marlow at 2002-07-04T15:26:13+00:00 [haddock @ 2002-07-04 15:26:13 by simonmar] More bugfixes to the export handling - - - - - 03e0710d by Simon Marlow at 2002-07-09T10:12:10+00:00 [haddock @ 2002-07-09 10:12:10 by simonmar] Don't require that the list type comes from "Prelude" for it to be treated as special syntax (sometimes it comes from Data.List or maybe even GHC.Base). - - - - - 44f3891a by Simon Marlow at 2002-07-09T10:12:51+00:00 [haddock @ 2002-07-09 10:12:51 by simonmar] commented-out debugging code - - - - - 97280873 by Krasimir Angelov at 2002-07-09T16:33:33+00:00 [haddock @ 2002-07-09 16:33:31 by krasimir] 'Microsoft HTML Help' support - - - - - 3dc04655 by Simon Marlow at 2002-07-10T09:40:56+00:00 [haddock @ 2002-07-10 09:40:56 by simonmar] Fix for rendering of the (->) type constructor, from Ross Paterson. - - - - - c9f149c6 by Simon Marlow at 2002-07-10T10:26:11+00:00 [haddock @ 2002-07-10 10:26:11 by simonmar] Tweaks to the MS Help support: the extra files are now only generated if you ask for them (--ms-help). - - - - - e8acc1e6 by Simon Marlow at 2002-07-10T10:57:10+00:00 [haddock @ 2002-07-10 10:57:10 by simonmar] Document all the new options since 0.3 - - - - - 8bb85544 by Simon Marlow at 2002-07-10T10:58:31+00:00 [haddock @ 2002-07-10 10:58:31 by simonmar] Sort the options a bit - - - - - abc0dd59 by Simon Marlow at 2002-07-15T09:19:38+00:00 [haddock @ 2002-07-15 09:19:38 by simonmar] Fix a bug in mkExportItems when processing a module without an explicit export list. We were placing one copy of a declaration for each binder in the declaration, which for a data type would mean one copy of the whole declaration per constructor or record selector. - - - - - dde65bb9 by Simon Marlow at 2002-07-15T09:54:16+00:00 [haddock @ 2002-07-15 09:54:16 by simonmar] merge rev. 1.35 - - - - - bd7eb8c4 by Simon Marlow at 2002-07-15T10:14:31+00:00 [haddock @ 2002-07-15 10:14:30 by simonmar] Be a bit more liberal in the kind of commenting styles we allow, as suggested by Malcolm Wallace. Mostly this consists of allowing doc comments either side of a separator token. In an export list, a section heading is now allowed before the comma, as well as after it. eg. module M where ( T(..) -- * a section heading , f -- * another section heading , g ) In record fields, doc comments are allowed anywhere (previously a doc-next was allowed only after the comma, and a doc-before was allowed only before the comma). eg. data R = C { -- | describes 'f' f :: Int -- | describes 'g' , g :: Int } - - - - - 8f6dfe34 by Simon Marlow at 2002-07-15T10:21:56+00:00 [haddock @ 2002-07-15 10:21:56 by simonmar] Mention alternative commenting styles. - - - - - fc515bb7 by Simon Marlow at 2002-07-15T16:16:50+00:00 [haddock @ 2002-07-15 16:16:50 by simonmar] Allow multiple sections/subsections before and after a comma in the export list. Also at the same time I made the syntax a little stricter (multiple commas now aren't allowed between export specs). - - - - - 80a97e74 by Simon Marlow at 2002-07-19T09:13:10+00:00 [haddock @ 2002-07-19 09:13:10 by simonmar] Allow special id's ([], (), etc.) to be used in an import declaration. - - - - - a69d7378 by Simon Marlow at 2002-07-19T09:59:02+00:00 [haddock @ 2002-07-19 09:59:02 by simonmar] Allow special id's ([], (), etc.) to be used in an import declarations. - - - - - d205fa60 by Simon Marlow at 2002-07-19T10:00:16+00:00 [haddock @ 2002-07-19 10:00:16 by simonmar] Relax the restrictions which require doc comments to be followed by semi colons - in some cases this isn't necessary. Now you can write module M where { -- | some doc class C where {} } without needing to put a semicolon before the class declaration. - - - - - e9301e14 by Simon Marlow at 2002-07-23T08:24:09+00:00 [haddock @ 2002-07-23 08:24:09 by simonmar] A new TODO list item - - - - - e5d77586 by Simon Marlow at 2002-07-23T08:40:56+00:00 [haddock @ 2002-07-23 08:40:56 by simonmar] - update the acknowledgements - remove the paragraph that described how to use explicit layout with doc comments; it isn't relevant any more. - - - - - 78a94137 by Simon Marlow at 2002-07-23T08:43:02+00:00 [haddock @ 2002-07-23 08:43:02 by simonmar] more tests - - - - - 5c320927 by Simon Marlow at 2002-07-23T08:43:26+00:00 [haddock @ 2002-07-23 08:43:26 by simonmar] Updates for version 0.4 - - - - - 488e99ae by Simon Marlow at 2002-07-23T09:10:46+00:00 [haddock @ 2002-07-23 09:10:46 by simonmar] Fix the %changelog (rpm complained that it wasn't in the right order) - - - - - a77bb373 by Simon Marlow at 2002-07-23T09:12:38+00:00 [haddock @ 2002-07-23 09:12:38 by simonmar] Another item for the TODO list - - - - - f1ec1813 by Simon Marlow at 2002-07-23T10:18:46+00:00 [haddock @ 2002-07-23 10:18:46 by simonmar] Add a version banner when invoked with -v - - - - - 1d44cadf by Simon Marlow at 2002-07-24T09:28:19+00:00 [haddock @ 2002-07-24 09:28:19 by simonmar] Remove ^Ms - - - - - 4d8d5e94 by Simon Marlow at 2002-07-24T09:42:18+00:00 [haddock @ 2002-07-24 09:42:17 by simonmar] Patches to quieten ghc -Wall, from those nice folks at Galois. - - - - - d6edc43e by Simon Marlow at 2002-07-25T14:37:29+00:00 [haddock @ 2002-07-25 14:37:28 by simonmar] Patch to allow simple hyperlinking to an arbitrary location in another module's documentation, from Volker Stolz. Now in a doc comment: #foo# creates <a name="foo"></a> And you can use the form "M\#foo" to hyperlink to the label 'foo' in module 'M'. Note that the backslash is necessary for now. - - - - - b34d18fa by Simon Marlow at 2002-08-02T09:08:22+00:00 [haddock @ 2002-08-02 09:08:22 by simonmar] The <TT> and <PRE> environments seem to use a font that is a little too small in IE. Compensate. (suggestion from Daan Leijen). - - - - - 8106b086 by Simon Marlow at 2002-08-02T09:25:23+00:00 [haddock @ 2002-08-02 09:25:20 by simonmar] Remove <P>..</P> from around list items, to reduce excess whitespace between the items of bulleted and ordered lists. (Suggestion from Daan Leijen). - - - - - c1acff8f by Simon Marlow at 2002-08-05T09:03:49+00:00 [haddock @ 2002-08-05 09:03:49 by simonmar] update - - - - - f968661c by Simon Marlow at 2002-11-11T09:32:57+00:00 [haddock @ 2002-11-11 09:32:57 by simonmar] Fix cut-n-pasto - - - - - 12d02619 by Simon Marlow at 2002-11-13T09:49:46+00:00 [haddock @ 2002-11-13 09:49:46 by simonmar] Small bugfix in the --read-interface option parsing from Brett Letner. - - - - - 30e32d5e by Ross Paterson at 2003-01-16T15:07:57+00:00 [haddock @ 2003-01-16 15:07:57 by ross] Adjust for the new exception libraries (as well as the old ones). - - - - - 871f65df by Sven Panne at 2003-02-20T21:31:40+00:00 [haddock @ 2003-02-20 21:31:40 by panne] * Add varsyms and consyms to index * Exclude empty entries from index - - - - - bc42cc87 by Sven Panne at 2003-02-24T21:26:29+00:00 [haddock @ 2003-02-24 21:26:29 by panne] Don't convert a "newtype" to a single-constructor "data" for non-abstractly exported types, they are quite different regarding strictness/pattern matching. Now a "data" without any constructors is only emitted for an abstractly exported type, regardless if it is actually a "newtype" or a "data". - - - - - 0c2a1d99 by Sven Panne at 2003-03-08T19:02:38+00:00 [haddock @ 2003-03-08 19:02:38 by panne] Fixed some broken/redirected/canonicalized links found by a very picky link checker. - - - - - 25459269 by Sven Panne at 2003-03-09T21:13:43+00:00 [haddock @ 2003-03-09 21:13:43 by panne] Don't append a fragment to non-defining index entries, only documents with a defining occurrence have a name anchor. - - - - - 6be4db86 by Sven Panne at 2003-03-10T21:34:25+00:00 [haddock @ 2003-03-10 21:34:24 by panne] Escape fragments. This fixes e.g. links to operators. - - - - - eb12972c by Ross Paterson at 2003-04-25T10:50:06+00:00 [haddock @ 2003-04-25 10:50:05 by ross] An 80% solution to generating derived instances. A complete solution would duplicate the instance inference logic, but if a type variable occurs as a constructor argument, then we can just propagate the derived class to the variable. But we know nothing of the constraints on any type variables that occur elsewhere. For example, the declarations data Either a b = Left a | Right b deriving (Eq, Ord) data Ptr a = Ptr Addr# deriving (Eq, Ord) newtype IORef a = IORef (STRef RealWorld a) deriving Eq yield the instances (Eq a, Eq b) => Eq (Either a b) (Ord a, Ord b) => Ord (Either a b) Eq (Ptr a) Ord (Ptr a) (??? a) => Eq (IORef a) The last example shows the limits of this local analysis. Note that a type variable may be in both categories: then we know a constraint, but there may be more, or a stronger constraint, e.g. data Tree a = Node a [Tree a] deriving Eq yields (Eq a, ??? a) => Eq (Tree a) - - - - - de886f78 by Simon Marlow at 2003-04-25T11:17:55+00:00 [haddock @ 2003-04-25 11:17:55 by simonmar] Some updates, including moving the derived instance item down to the bottom of the list now that Ross has contributed some code that does the job for common cases. - - - - - 1b52cffd by Simon Marlow at 2003-04-30T14:02:32+00:00 [haddock @ 2003-04-30 14:02:32 by simonmar] When installing on Windows, run cygpath over $(HADDOCKLIB) so that haddock (a mingw program, built by GHC) can understand it. You still need to be in a cygwin environment to run Haddock, because of the shell script wrapper. - - - - - d4f638de by Simon Marlow at 2003-05-06T10:04:47+00:00 [haddock @ 2003-05-06 10:04:47 by simonmar] Catch another case of a paragraph containing just a DocMonospaced that should turn into a DocCodeBlock. - - - - - 4162b2b9 by Simon Marlow at 2003-05-06T10:11:44+00:00 [haddock @ 2003-05-06 10:11:44 by simonmar] Add some more code-block tests. - - - - - 4f5802c8 by Simon Marlow at 2003-05-06T10:14:52+00:00 [haddock @ 2003-05-06 10:14:52 by simonmar] Don't turn a single DocCodeBlock into a DocMonospaced, because that tends to remove the line breaks in the code. - - - - - ef8c45f7 by Simon Marlow at 2003-05-21T15:07:21+00:00 [haddock @ 2003-05-21 15:07:21 by simonmar] Only omit the module contents when there are no section headings at all. - - - - - bcee1e75 by Sigbjorn Finne at 2003-05-30T16:50:45+00:00 [haddock @ 2003-05-30 16:50:45 by sof] cygpath: for now, steer clear of --mixed - - - - - 30567af3 by Sigbjorn Finne at 2003-05-30T17:59:28+00:00 [haddock @ 2003-05-30 17:59:28 by sof] oops, drop test defn from prev commit - - - - - b0856e7d by Simon Marlow at 2003-06-03T09:55:26+00:00 [haddock @ 2003-06-03 09:55:26 by simonmar] Two small fixes to make the output valid HTML 4.01 (transitional). Thanks to Malcolm Wallace for pointing out the problems. - - - - - 70e137ea by Simon Marlow at 2003-07-28T13:30:35+00:00 [haddock @ 2003-07-28 13:30:35 by simonmar] Add tests for a couple of bugs. - - - - - 122bd578 by Simon Marlow at 2003-07-28T13:31:25+00:00 [haddock @ 2003-07-28 13:31:25 by simonmar] Add documentation for anchors. - - - - - 0bd27cb2 by Simon Marlow at 2003-07-28T13:31:46+00:00 [haddock @ 2003-07-28 13:31:46 by simonmar] Update - - - - - 08052d42 by Simon Marlow at 2003-07-28T13:32:12+00:00 [haddock @ 2003-07-28 13:32:12 by simonmar] layout tweak. - - - - - 13942749 by Simon Marlow at 2003-07-28T13:33:03+00:00 [haddock @ 2003-07-28 13:33:03 by simonmar] Differentiate links to types/classes from links to variables/constructors with a prefix ("t:" and "v:" respectively). - - - - - d7f493b9 by Simon Marlow at 2003-07-28T13:35:17+00:00 [haddock @ 2003-07-28 13:35:16 by simonmar] When a module A exports another module's contents via 'module B', then modules which import entities from B re-exported by A should link to B.foo rather than A.foo. See examples/Bug2.hs. - - - - - d94cf705 by Simon Marlow at 2003-07-28T13:36:14+00:00 [haddock @ 2003-07-28 13:36:14 by simonmar] Update to version 0.5 - - - - - dbb776cd by Sven Panne at 2003-07-28T14:02:43+00:00 [haddock @ 2003-07-28 14:02:43 by panne] * Updated to version 0.5 * Automagically generate configure if it is not there - - - - - 6cfeee53 by Simon Marlow at 2003-07-28T14:32:43+00:00 [haddock @ 2003-07-28 14:32:42 by simonmar] Update to avoid using hslibs with GHC >= 5.04 - - - - - a1ce838f by Simon Marlow at 2003-07-28T14:33:37+00:00 [haddock @ 2003-07-28 14:33:37 by simonmar] Update for 0.5 - - - - - c0fe6493 by Simon Marlow at 2003-07-28T14:53:22+00:00 [haddock @ 2003-07-28 14:53:22 by simonmar] Markup fix - - - - - 6ea31596 by Sven Panne at 2003-07-28T16:40:45+00:00 [haddock @ 2003-07-28 16:40:45 by panne] Make it compile with GHC >= 6.01 - - - - - afcd30fc by Simon Marlow at 2003-07-30T15:04:52+00:00 [haddock @ 2003-07-30 15:04:52 by simonmar] Pay attention to import specs when building the the import env, as well as the orig env. This may fix some wrong links in documentation when import specs are being used. - - - - - 17c3137f by Simon Marlow at 2003-07-30T16:05:41+00:00 [haddock @ 2003-07-30 16:05:40 by simonmar] Rename instances based on the import_env for the module in which they are to be displayed. This should give, in many cases, better links for the types and classes mentioned in the instance head. This involves keeping around the import_env in the iface until the end, because instances are not collected up until all the modules have been processed. Fortunately it doesn't seem to affect performance much. Instance heads are now attached to ExportDecls, rather than the HTML backend passing around a separate mapping for instances. This is a cleanup. - - - - - 3d3b5c87 by Sven Panne at 2003-08-04T10:18:24+00:00 [haddock @ 2003-08-04 10:18:24 by panne] Don't print parentheses around one-element contexts - - - - - 9e3f3f2d by Simon Marlow at 2003-08-04T12:59:47+00:00 [haddock @ 2003-08-04 12:59:47 by simonmar] A couple of TODOs. - - - - - e9d8085c by Simon Marlow at 2003-08-05T14:10:31+00:00 [haddock @ 2003-08-05 14:10:31 by simonmar] I'm not sure why, but it seems that the index entries for non-defining occurrences of entities did not have an anchor - the link just pointed to the module. This fixes it. - - - - - ff5c7d6d by Simon Marlow at 2003-08-15T14:42:59+00:00 [haddock @ 2003-08-15 14:42:59 by simonmar] Convert the lexer to Alex, and fix a bug in the process. - - - - - 1aa077bf by Simon Marlow at 2003-08-15T15:00:18+00:00 [haddock @ 2003-08-15 15:00:18 by simonmar] Update - - - - - d3de1e38 by Simon Marlow at 2003-08-15T15:01:03+00:00 [haddock @ 2003-08-15 15:01:03 by simonmar] wibbles - - - - - b40ece3b by Simon Marlow at 2003-08-18T10:04:47+00:00 [haddock @ 2003-08-18 10:04:47 by simonmar] Lex the 'mdo' keyword as 'do'. - - - - - 8f9a1146 by Simon Marlow at 2003-08-18T11:48:24+00:00 [haddock @ 2003-08-18 11:48:24 by simonmar] Two bugs from Sven. - - - - - ea54ebc0 by Simon Marlow at 2003-08-18T11:48:46+00:00 [haddock @ 2003-08-18 11:48:46 by simonmar] Fixes to the new lexer. - - - - - d5f6a4b5 by Simon Marlow at 2003-08-19T09:09:03+00:00 [haddock @ 2003-08-19 09:09:03 by simonmar] Further wibbles to the syntax. - - - - - 6bbdadb7 by Sven Panne at 2003-08-26T18:45:35+00:00 [haddock @ 2003-08-26 18:45:35 by panne] Use autoreconf instead of autoconf - - - - - 32e889cb by Sven Panne at 2003-08-26T19:01:19+00:00 [haddock @ 2003-08-26 19:01:18 by panne] Made option handling a bit more consistent with other tools, in particular: Every program in fptools should output * version info on stdout and terminate successfully when -V or --version * usage info on stdout and terminate successfully when -? or --help * usage info on stderr and terminate unsuccessfully when an unknown option is given. - - - - - 5d156a91 by Sven Panne at 2003-08-26T19:20:55+00:00 [haddock @ 2003-08-26 19:20:55 by panne] Make it *very* clear that we terminate when given a -V/--version flag - - - - - e6577265 by Sven Panne at 2003-08-27T07:50:03+00:00 [haddock @ 2003-08-27 07:50:02 by panne] * Made -D a short option for --dump-interface. * Made -m a short option for --ms-help. * Made -n a short option for --no-implicit-prelude. * Made -c a short option for --css. * Removed DocBook options from executable (they didn't do anything), but mark them as reserved in the docs. Note that the short option for DocBook output is now -S (from SGML) instead of -d. The latter is now a short option for --debug. * The order of the Options in the documentation now matches the order printed by Haddock itself. Note: Although changing the names of options is often a bad idea, I'd really like to make the options for the programs in fptools more consistent and compatible to the ones used in common GNU programs. - - - - - d303ff98 by Simon Marlow at 2003-09-10T08:23:48+00:00 [haddock @ 2003-09-10 08:23:48 by simonmar] Add doc subdir. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 9a70e46a by Simon Marlow at 2003-09-10T08:24:32+00:00 [haddock @ 2003-09-10 08:24:32 by simonmar] Install these files in $(datadir), not $(libdir), since they're architecture independent. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - bbb87e7a by Simon Marlow at 2003-09-10T08:25:31+00:00 [haddock @ 2003-09-10 08:25:31 by simonmar] Haddock's supplementary HTML bits now live in $(datadir), not $(libdir). Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 3587c24b by Simon Marlow at 2003-09-22T10:34:38+00:00 [haddock @ 2003-09-22 10:34:38 by simonmar] Allow installing of docs. - - - - - d510b517 by Sven Panne at 2003-10-11T08:10:44+00:00 [haddock @ 2003-10-11 08:10:44 by panne] Include architecture-independent files in file list - - - - - 187d7618 by Sigbjorn Finne at 2003-10-20T17:19:24+00:00 [haddock @ 2003-10-20 17:19:22 by sof] support for i-parameters + zip comprehensions - - - - - b6c7a273 by Simon Marlow at 2003-11-03T14:24:24+00:00 [haddock @ 2003-11-03 14:24:24 by simonmar] Update TODO file. - - - - - 58513e33 by Simon Marlow at 2003-11-05T11:22:04+00:00 [haddock @ 2003-11-05 11:22:04 by simonmar] Remove the last of the uses of 'trace' to emit warnings, and tidy up a couple of places where duplicate warnings were being emitted. - - - - - 33a78846 by Simon Marlow at 2003-11-05T11:30:53+00:00 [haddock @ 2003-11-05 11:30:52 by simonmar] - Suppress warnings about unknown imported modules by default. - Add a -v/--verbose flag to re-enable these warnings. The general idea is to suppress the "Warning: unknown module: Prelude" warnings which most Haddock users will see every time, and which aren't terribly useful. - - - - - a969de7f by Simon Marlow at 2003-11-05T12:30:28+00:00 [haddock @ 2003-11-05 12:30:28 by simonmar] - Remove the emboldening of index entries for defining locations. This isn't useful, and breaks abstractions. - If an entity is re-exported by a module but the module doesn't include documentation for that entity (perhaps because it is re-exported by 'module M'), then don't attempt to hyperlink to the documentation from the index. Instead, just list that module in the index, to indicate that the entity is exported from there. - - - - - f14ea82a by Simon Marlow at 2003-11-05T15:15:59+00:00 [haddock @ 2003-11-05 15:15:59 by simonmar] Index overhaul: - no more separate type/class and variable/function indices - the index now makes a distinction between different entities with the same name. One example is a type constructor with the same name as a data constructor, but another example is simply a function with the same name exported by two different modules. For example, the index entry for 'catch' now looks like this: catch 1 (Function) Control.Exception 2 (Function) GHC.Exception, Prelude, System.IO, System.IO.Error making it clear that there are two different 'catch'es, but one of them is exported by several modules. - Each index page now has the index contents (A B C ...) at the top. Please let me know if you really hate any of this. - - - - - 01a25ca6 by Simon Marlow at 2003-11-05T15:16:38+00:00 [haddock @ 2003-11-05 15:16:38 by simonmar] Update - - - - - 1a7ccb86 by Simon Marlow at 2003-11-05T17:16:05+00:00 [haddock @ 2003-11-05 17:16:04 by simonmar] Support for generating a single unified index for several packages. --use-index=URL turns off normal index generation, causes Index links to point to URL. --gen-index generates an combined index from the specified interfaces. Currently doesn't work exactly right, because the interfaces don't contain the iface_reexported info. I'll need to fix that up. - - - - - a2bca16d by Simon Marlow at 2003-11-06T10:44:52+00:00 [haddock @ 2003-11-06 10:44:52 by simonmar] Include iface_reexported in the .haddock file. This unfortunately bloats the file (40% for base). If this gets to be a problem we can always apply the dictionary trick that GHC uses for squashing .hi files. - - - - - 0a09c293 by Simon Marlow at 2003-11-06T12:39:47+00:00 [haddock @ 2003-11-06 12:39:46 by simonmar] - Add definition lists, marked up like this: -- | This is a definition list: -- -- [@foo@] The description of @foo at . -- -- [@bar@] The description of @bar at . Cunningly, the [] characters are not treated specially unless a [ is found at the beginning of a paragraph, in which case the ] becomes special in the following text. - Add --use-contents and --gen-contents, along the lines of --use-index and --gen-index added yesterday. Now we can generate a combined index and contents for the whole of the hierarchical libraries, and in theory the index/contents on the system could be updated as new packages are added. - - - - - fe1b3460 by Simon Marlow at 2003-11-06T14:47:36+00:00 [haddock @ 2003-11-06 14:47:36 by simonmar] Remove the 'Parent' button - it is of dubious use, and often points into thin air. - - - - - db6d762f by Simon Marlow at 2003-11-06T16:48:14+00:00 [haddock @ 2003-11-06 16:48:11 by simonmar] - Include the OptHide setting in the interface, so we don't include hidden modules in the combined index/contents. - Add a -k/--package flag to set the package name for the current set of modules. The package name for each module is now shown in the right-hand column of the contents, in a combined contents page. - - - - - 7d71718b by Simon Marlow at 2003-11-06T16:50:28+00:00 [haddock @ 2003-11-06 16:50:28 by simonmar] Add -k/--package docs - - - - - ef43949d by Simon Marlow at 2003-11-06T16:51:23+00:00 [haddock @ 2003-11-06 16:51:23 by simonmar] Bump to 0.6 - - - - - 1c419e06 by Simon Marlow at 2003-11-06T16:51:50+00:00 [haddock @ 2003-11-06 16:51:50 by simonmar] update - - - - - 69422327 by Simon Marlow at 2003-11-10T14:41:06+00:00 [haddock @ 2003-11-10 14:41:05 by simonmar] Re-exporting names from a different package is problematic, because we don't have access to the full documentation for the entity. Currently Haddock just ignores entities with no documentation, but this results in bogus-looking empty documentation for many of the modules in the haskell98 package. So: - the documentation will now just list the name, as a link pointing to the location of the actual documentation. - now we don't attempt to link to these re-exported entities if they are referred to by the current module. Additionally: - If there is no documentation in the current module, include just the Synopsis section (rather than just the documentation section, as it was before). This just looks nicer and was on the TODO list. - - - - - 3c3fc433 by Simon Marlow at 2003-11-10T14:51:59+00:00 [haddock @ 2003-11-10 14:51:59 by simonmar] Fix for getReExports: take into account names which are not visible because they are re-exported from a different package. - - - - - 31c8437b by Simon Marlow at 2003-11-10T15:10:53+00:00 [haddock @ 2003-11-10 15:10:53 by simonmar] Version 0.6 changes - - - - - a7c2430b by Simon Marlow at 2003-11-10T15:15:58+00:00 [haddock @ 2003-11-10 15:15:58 by simonmar] getReExports: one error case that isn't - - - - - 00cc459c by Simon Marlow at 2003-11-10T16:15:19+00:00 [haddock @ 2003-11-10 16:15:18 by simonmar] copyright update - - - - - ca62408d by Simon Marlow at 2003-11-11T09:57:25+00:00 [haddock @ 2003-11-11 09:57:25 by simonmar] Version 0.6 - - - - - 3acbf818 by Simon Marlow at 2003-11-11T12:10:44+00:00 [haddock @ 2003-11-11 12:10:44 by simonmar] Go back to producing just the documentation section, rather than just the synopsis section, for a module with no documentation annotations. One reason is that the synopsis section tries to link each entity to its documentation on the same page. Also, the doc section anchors each entity, and it lists instances which the synopsis doesn't. - - - - - 6c90abc2 by Simon Marlow at 2003-11-12T10:03:39+00:00 [haddock @ 2003-11-12 10:03:39 by simonmar] 2002 -> 2003 - - - - - 090bbc4c by Simon Marlow at 2003-11-28T12:08:00+00:00 [haddock @ 2003-11-28 12:08:00 by simonmar] update - - - - - 8096a832 by Simon Marlow at 2003-11-28T12:09:58+00:00 [haddock @ 2003-11-28 12:09:58 by simonmar] Fix some of the problems with Haddock generating pages that are too wide. Now we only specify 'nowrap' when it is necessary to avoid a code box getting squashed up by the text to the right of it. - - - - - 35294929 by Sven Panne at 2003-12-29T17:16:31+00:00 [haddock @ 2003-12-29 17:16:31 by panne] Updated my email address - - - - - cdb697bf by Simon Marlow at 2004-01-08T10:14:24+00:00 [haddock @ 2004-01-08 10:14:24 by simonmar] Add instructions for using GHC to pre-process source for feeding to Haddock. - - - - - 8dfc491f by Simon Marlow at 2004-01-09T12:45:46+00:00 [haddock @ 2004-01-09 12:45:46 by simonmar] Add -optP-P to example ghc command line. - - - - - ac41b820 by Simon Marlow at 2004-02-03T11:02:03+00:00 [haddock @ 2004-02-03 11:02:03 by simonmar] Fix bug in index generation - - - - - f4e7edcb by Simon Marlow at 2004-02-10T11:51:16+00:00 [haddock @ 2004-02-10 11:51:16 by simonmar] Don't throw away whitespace at the beginning of a line (experimental fix). - - - - - 68e212d2 by Simon Marlow at 2004-02-10T12:10:08+00:00 [haddock @ 2004-02-10 12:10:08 by simonmar] Fix for previous commit: I now realise why the whitespace was stripped from the beginning of the line. Work around it. - - - - - e7d7f2df by Sven Panne at 2004-02-10T18:38:45+00:00 [haddock @ 2004-02-10 18:38:45 by panne] Make Haddock link with the latest relocated monad transformer package - - - - - 992d4225 by Simon Marlow at 2004-02-16T10:21:35+00:00 [haddock @ 2004-02-16 10:21:35 by simonmar] Add a TODO - - - - - 1ac55326 by Simon Marlow at 2004-03-12T11:33:39+00:00 [haddock @ 2004-03-12 11:33:39 by simonmar] Add an item. - - - - - 0478e903 by Simon Marlow at 2004-03-15T12:24:05+00:00 [haddock @ 2004-03-15 12:24:05 by simonmar] Add an item. - - - - - 6f26d21a by Simon Marlow at 2004-03-18T14:21:29+00:00 [haddock @ 2004-03-18 14:21:29 by simonmar] Fix URL - - - - - 19b6bb99 by Simon Marlow at 2004-03-22T14:09:03+00:00 [haddock @ 2004-03-22 14:09:03 by simonmar] getReExports was bogus: we should really look in the import_env to find the documentation for an entity which we are re-exporting without documentation. Suggested by: Ross Paterson (patch modified by me). - - - - - 5c756031 by Simon Marlow at 2004-03-24T09:42:11+00:00 [haddock @ 2004-03-24 09:42:10 by simonmar] hiding bug from Ross Paterson (fixed in rev 1.59 of Main.hs) - - - - - 1b692e6c by Simon Marlow at 2004-03-24T10:10:50+00:00 [haddock @ 2004-03-24 10:10:50 by simonmar] mkExportItems fix & simplification: we should be looking at the actual exported names (calculated earlier) to figure out which subordinates of a declaration are exported. This means that if you export a record, and name its fields separately in the export list, the fields will still be visible in the documentation for the constructor. - - - - - 90e5e294 by Simon Marlow at 2004-03-24T10:12:08+00:00 [haddock @ 2004-03-24 10:12:08 by simonmar] Make restrictCons take into account record field names too (removing a ToDo). - - - - - 2600efa4 by Simon Marlow at 2004-03-24T10:16:17+00:00 [haddock @ 2004-03-24 10:16:17 by simonmar] Record export tests. - - - - - 6a8575c7 by Simon Marlow at 2004-03-25T09:35:14+00:00 [haddock @ 2004-03-25 09:35:14 by simonmar] restrictTo: fix for restricting a newtype with a record field. - - - - - dcf55a8d by Simon Marlow at 2004-03-25T10:01:42+00:00 [haddock @ 2004-03-25 10:01:42 by simonmar] Fix duplicate instance bug - - - - - f49aa758 by Simon Marlow at 2004-03-25T10:02:41+00:00 [haddock @ 2004-03-25 10:02:41 by simonmar] Duplicate instance bug. - - - - - 7b87344c by Simon Marlow at 2004-03-25T10:29:56+00:00 [haddock @ 2004-03-25 10:29:56 by simonmar] If a name is imported from two places, one hidden and one not, choose the unhidden one to link to. Also, when there's only a hidden module to link to, don't try linking to it. - - - - - 40f44d7b by Simon Marlow at 2004-03-25T15:17:24+00:00 [haddock @ 2004-03-25 15:17:23 by simonmar] Add support for collaspible parts of the page, with a +/- button and a bit of JavaScript. Make the instances collapsible, and collapse them by default. This makes documentation with long lists of instances (eg. the Prelude) much easier to read. Maybe we should give other documentation sections the same treatment. - - - - - 9b64dc0f by Simon Marlow at 2004-03-25T15:20:55+00:00 [haddock @ 2004-03-25 15:20:55 by simonmar] Update - - - - - c2fff7f2 by Simon Marlow at 2004-03-25T15:45:10+00:00 [haddock @ 2004-03-25 15:45:10 by simonmar] Eliminate some unnecessary spaces in the HTML rendering - - - - - b7948ff0 by Simon Marlow at 2004-03-25T16:00:37+00:00 [haddock @ 2004-03-25 16:00:36 by simonmar] Remove all that indentation in the generated HTML to keep the file sizes down. - - - - - da2bb4ca by Sven Panne at 2004-03-27T09:57:58+00:00 [haddock @ 2004-03-27 09:57:57 by panne] Added the new-born haddock.js to the build process and the documentation. - - - - - b99e6f8c by Sven Panne at 2004-03-27T10:32:20+00:00 [haddock @ 2004-03-27 10:32:20 by panne] "type" is a required attribute of the "script" element - - - - - 562b185a by Sven Panne at 2004-03-27T12:52:34+00:00 [haddock @ 2004-03-27 12:52:34 by panne] Add a doctype for the contents page, too. - - - - - f6a99c2d by Simon Marlow at 2004-04-14T10:03:25+00:00 [haddock @ 2004-04-14 10:03:25 by simonmar] fix for single-line comment syntax - - - - - de366303 by Simon Marlow at 2004-04-20T13:08:04+00:00 [haddock @ 2004-04-20 13:08:04 by simonmar] Allow a 'type' declaration to include documentation comments. These will be ignored by Haddock, but at least one user (Johannes Waldmann) finds this feature useful, and it's easy to add. - - - - - fd78f51e by Simon Marlow at 2004-05-07T15:14:56+00:00 [haddock @ 2004-05-07 15:14:56 by simonmar] - update copyright - add version to abstract - - - - - 59f53e32 by Sven Panne at 2004-05-09T14:39:53+00:00 [haddock @ 2004-05-09 14:39:53 by panne] Fix the fix for single-line comment syntax, ------------------------------------------- is now a valid comment line again. - - - - - 8b18f2fe by Simon Marlow at 2004-05-10T10:11:51+00:00 [haddock @ 2004-05-10 10:11:51 by simonmar] Update - - - - - 225a491d by Ross Paterson at 2004-05-19T13:10:23+00:00 [haddock @ 2004-05-19 13:10:23 by ross] Make the handling of "deriving" slightly smarter, by ignoring data constructor arguments that are identical to the lhs. Now handles things like data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving ... - - - - - 37588686 by Mike Thomas at 2004-05-21T06:38:14+00:00 [haddock @ 2004-05-21 06:38:14 by mthomas] Windows exe extensions (bin remains for Unix). - - - - - cf2b9152 by Simon Marlow at 2004-05-25T09:34:54+00:00 [haddock @ 2004-05-25 09:34:54 by simonmar] Add some TODO items - - - - - 4d29cdfc by Simon Marlow at 2004-05-25T10:41:46+00:00 [haddock @ 2004-05-25 10:41:46 by simonmar] Complain if -h is used with --gen-index or --gen-contents, because it'll overwrite the new index/contents. - - - - - 2e0771e0 by Mike Thomas at 2004-05-28T20:17:55+00:00 [haddock @ 2004-05-28 20:17:55 by mthomas] Windows: search for templates in executable directory. Unix: Haddock tries cwd first rather than error if no -l arg. - - - - - 8d10bde1 by Sven Panne at 2004-06-05T16:53:34+00:00 [haddock @ 2004-06-05 16:53:34 by panne] Misc. rpm spec file cleanup, including: * make BuildRoot handling more consistent * added default file attributes * consistent defines and tags - - - - - 59974349 by Sven Panne at 2004-06-05T18:01:00+00:00 [haddock @ 2004-06-05 18:01:00 by panne] More rpm spec file cleanup, including: * added some BuildRequires * changed packager to me, so people can complain at the right place :-] * consistently refer to haskell.org instead of www.haskell.org - - - - - b94d4903 by Simon Marlow at 2004-07-01T11:08:58+00:00 [haddock @ 2004-07-01 11:08:57 by simonmar] Update to the +/- buttons: use a resized image rather than a <button>. Still seeing some strange effects in Konqueror, so might need to use a fixed-size image instead. - - - - - d5278f67 by Sven Panne at 2004-07-04T15:15:55+00:00 [haddock @ 2004-07-04 15:15:55 by panne] Install pictures for +/- pictures, too (JPEG is a strange format for graphics like this, I would have expected GIF or PNG here.) Things look fine with Konqueror and Netscape on Linux now, the only downside is that the cursor doesn't change when positioned above the "button". - - - - - 46dec6c5 by Sven Panne at 2004-07-13T17:59:28+00:00 [haddock @ 2004-07-13 17:59:28 by panne] A quote is a valid part of a Haskell identifier, but it would interfere with an ECMA script string delimiter, so escape it there. - - - - - 1d7bc432 by Simon Marlow at 2004-07-22T08:54:06+00:00 [haddock @ 2004-07-22 08:54:06 by simonmar] Add single quote to $ident, so you can say eg. 'foldl'' to refer to foldl' (the longest match rule is our friend). Bug reported by Adrian Hey <ahey at iee.org> - - - - - f183618b by Krasimir Angelov at 2004-07-27T22:59:35+00:00 [haddock @ 2004-07-27 22:58:23 by krasimir] Add basic support for Microsoft HTML Help 2.0 - - - - - d515d0c2 by Krasimir Angelov at 2004-07-27T23:02:36+00:00 [haddock @ 2004-07-27 23:02:36 by krasimir] escape names in the index - - - - - a5f1be23 by Krasimir Angelov at 2004-07-27T23:05:21+00:00 [haddock @ 2004-07-27 23:05:21 by krasimir] Add jsFile, plusFile and minusFile to the file list - - - - - c4fb4881 by Krasimir Angelov at 2004-07-28T22:12:10+00:00 [haddock @ 2004-07-28 22:12:09 by krasimir] bugfix. Move contentsHtmlFile, indexHtmlFile and subIndexHtmlFile functions to HaddockUtil.hs module to make them accessible from HaddockHH2.hs - - - - - 64d30b1d by Krasimir Angelov at 2004-07-30T22:15:47+00:00 [haddock @ 2004-07-30 22:15:45 by krasimir] more stuffs - support for separated compilation of packages - the contents page now uses DHTML TreeView - fixed copyFile bug - - - - - 133c8c5c by Krasimir Angelov at 2004-07-31T12:04:38+00:00 [haddock @ 2004-07-31 12:04:37 by krasimir] make the DHtmlTree in contents page more portable. The +/- buttons are replaced with new images which looks more beatiful. - - - - - 79040963 by Krasimir Angelov at 2004-07-31T13:10:20+00:00 [haddock @ 2004-07-31 13:10:20 by krasimir] Make DHtmlTree compatible with Mozila browser - - - - - 1a55dc90 by Krasimir Angelov at 2004-07-31T14:52:55+00:00 [haddock @ 2004-07-31 14:52:55 by krasimir] fix - - - - - 85ce0237 by Krasimir Angelov at 2004-07-31T14:53:28+00:00 [haddock @ 2004-07-31 14:53:28 by krasimir] HtmlHelp 1.x - - - - - 3c0c53ba by Krasimir Angelov at 2004-07-31T20:35:21+00:00 [haddock @ 2004-07-31 20:35:21 by krasimir] Added support for DevHelp - - - - - d42b5af1 by Krasimir Angelov at 2004-07-31T21:17:51+00:00 [haddock @ 2004-07-31 21:17:51 by krasimir] Document new features in HtmlHelp - - - - - 790fe21e by Krasimir Angelov at 2004-08-01T15:14:02+00:00 [haddock @ 2004-08-01 15:14:02 by krasimir] add missing imports - - - - - fd7cc6bc by Krasimir Angelov at 2004-08-01T19:52:08+00:00 [haddock @ 2004-08-01 19:52:06 by krasimir] fix some bugs. Now I have got the entire libraries documentation in HtmlHelp 2.0 format. - - - - - 94ad7ac8 by Krasimir Angelov at 2004-08-01T19:53:50+00:00 [haddock @ 2004-08-01 19:53:50 by krasimir] I forgot to add the new +/- images - - - - - f0c65388 by Krasimir Angelov at 2004-08-02T16:25:53+00:00 [haddock @ 2004-08-02 16:25:53 by krasimir] Add root node to the table of contents. All modules in tree are not children of the root - - - - - f50bd85d by Sven Panne at 2004-08-02T18:17:46+00:00 [haddock @ 2004-08-02 18:17:46 by panne] Mainly DocBook fixes - - - - - 09527ce3 by Sven Panne at 2004-08-02T20:02:29+00:00 [haddock @ 2004-08-02 20:02:29 by panne] Fixed -o/--odir handling. Generating the output, especially the directory handling, is getting a bit convoluted nowadays... - - - - - c8fbacfa by Sven Panne at 2004-08-02T20:31:13+00:00 [haddock @ 2004-08-02 20:31:13 by panne] Warning police - - - - - 37830bff by Sven Panne at 2004-08-02T20:32:29+00:00 [haddock @ 2004-08-02 20:32:28 by panne] Nuked dead code - - - - - 13847171 by Sven Panne at 2004-08-02T21:12:27+00:00 [haddock @ 2004-08-02 21:12:25 by panne] Use pathJoin instead of low-level list-based manipulation for FilePaths - - - - - c711d61e by Sven Panne at 2004-08-02T21:16:02+00:00 [haddock @ 2004-08-02 21:16:02 by panne] Removed WinDoze CRs - - - - - b1f7dc88 by Sven Panne at 2004-08-03T19:35:59+00:00 [haddock @ 2004-08-03 19:35:59 by panne] Fixed spelling of "http-equiv" attribute - - - - - dd5f394e by Sven Panne at 2004-08-03T19:44:03+00:00 [haddock @ 2004-08-03 19:44:03 by panne] Pacify W3C validator: * Added document encoding (currently UTF-8, not sure if this is completely correct) * Fixed syntax of `id' attributes * Added necessary `alt' attribute for +/- images Small layout improvement: * Added space after +/- images (still not perfect, but better than before) - - - - - 919c47c6 by Sigbjorn Finne at 2004-08-03T19:45:11+00:00 [haddock @ 2004-08-03 19:45:11 by sof] make it compile with <= ghc-6.1 - - - - - 4d6f01d8 by Sigbjorn Finne at 2004-08-03T19:45:30+00:00 [haddock @ 2004-08-03 19:45:30 by sof] ffi wibble - - - - - 4770643a by Sven Panne at 2004-08-03T20:47:46+00:00 [haddock @ 2004-08-03 20:47:46 by panne] Fixed CSS for button style. Note that only "0" is a valid measure without a unit! - - - - - 14aaf2e5 by Sven Panne at 2004-08-03T21:07:59+00:00 [haddock @ 2004-08-03 21:07:58 by panne] Improved spacing of dynamic module tree - - - - - 97c3579a by Simon Marlow at 2004-08-09T11:03:04+00:00 [haddock @ 2004-08-09 11:03:04 by simonmar] Add FormatVersion Patch submitted by: George Russell <ger at informatik.uni-bremen.de> - - - - - af7f8c03 by Simon Marlow at 2004-08-09T11:55:07+00:00 [haddock @ 2004-08-09 11:55:05 by simonmar] Add support for a short description for each module, which is included in the contents. The short description should be given in a "Description: " field of the header. Included in this patch are changes that make the format of the header a little more flexible. From the comments: -- all fields in the header are optional and have the form -- -- [spaces1][field name][spaces] ":" -- [text]"\n" ([spaces2][space][text]"\n" | [spaces]"\n")* -- where each [spaces2] should have [spaces1] as a prefix. -- -- Thus for the key "Description", -- -- > Description : this is a -- > rather long -- > -- > description -- > -- > The module comment starts here -- -- the value will be "this is a .. description" and the rest will begin -- at "The module comment". The header fields must be in the following order: Module, Description, Copyright, License, Maintainer, Stability, Portability. Patches submitted by: George Russell <ger at informatik.uni-bremen.de>, with a few small changes be me, mostly to merge with other recent changes. ToDo: document the module header. - - - - - 7b865ad3 by Simon Marlow at 2004-08-10T14:09:57+00:00 [haddock @ 2004-08-10 14:09:57 by simonmar] Fixes for DevHelp/HtmlHelp following introduction of short module description. - - - - - 814766cd by Simon Marlow at 2004-08-10T14:33:46+00:00 [haddock @ 2004-08-10 14:33:45 by simonmar] Fixes to installation under Windows. - - - - - 39cf9ede by Simon Marlow at 2004-08-12T12:08:23+00:00 [haddock @ 2004-08-12 12:08:23 by simonmar] Avoid using string-gap tricks. - - - - - b6d78551 by Simon Marlow at 2004-08-13T10:53:21+00:00 [haddock @ 2004-08-13 10:53:21 by simonmar] Update - - - - - eaae7417 by Simon Marlow at 2004-08-13T10:53:50+00:00 [haddock @ 2004-08-13 10:53:50 by simonmar] Test for primes in quoted links - - - - - 68c34f06 by Sven Panne at 2004-08-16T19:59:38+00:00 [haddock @ 2004-08-16 19:59:36 by panne] XMLification - - - - - 7f45a6f9 by Sven Panne at 2004-08-18T16:42:54+00:00 [haddock @ 2004-08-18 16:42:54 by panne] Re-added indices + minor fixes - - - - - 8a5dd97c by Sigbjorn Finne at 2004-08-25T17:15:42+00:00 [haddock @ 2004-08-25 17:15:42 by sof] backquote HADDOCK_VERSION defn for <= ghc-6.0.x; believe this is only needed under mingw - - - - - 4b1b42ea by Sven Panne at 2004-08-26T20:08:50+00:00 [haddock @ 2004-08-26 20:08:49 by panne] SGML is dead, long live DocBook XML! Note: The BuildRequires tags in the spec files are still incomplete and the documentation about the DocBook tools needs to be updated, too. Stay tuned... - - - - - 8d52cedb by Sven Panne at 2004-08-26T21:03:19+00:00 [haddock @ 2004-08-26 21:03:19 by panne] Updated BuildRequires tags. Alas, there seems to be no real standard here, so your mileage may vary... At least the current specs should work on SuSE Linux. - - - - - e6982912 by Sigbjorn Finne at 2004-08-30T15:44:59+00:00 [haddock @ 2004-08-30 15:44:59 by sof] escape HADDOCK_VERSION double quotes on all platforms when compiling with <=6.0.x - - - - - b3fbc867 by Simon Marlow at 2004-08-31T13:09:42+00:00 [haddock @ 2004-08-31 13:09:42 by simonmar] Avoid GHC/shell versionitis and create Version.hs - - - - - c359e16a by Sven Panne at 2004-09-05T19:12:33+00:00 [haddock @ 2004-09-05 19:12:32 by panne] * HTML documentation for "foo.xml" goes into directory "foo" again, not "foo-html". This is nicer and consistent with the behaviour for building the docs from SGML. * Disabled building PostScript documentation in the spec files for now, there are some strange issues with the FO->PS conversion for some files which have to be clarified first. - - - - - c68b1eba by Sven Panne at 2004-09-24T07:04:38+00:00 [haddock @ 2004-09-24 07:04:38 by panne] Switched the default state for instances and the module hierarchy to non-collapsed. This can be reversed when we finally use cookies from JavaScript to have a more persistent state. Previously going back and forth in the documentation was simply too annoying because everything was collapsed again and therefore the documentation was not easily navigatable. - - - - - dfb32615 by Simon Marlow at 2004-09-30T08:21:29+00:00 [haddock @ 2004-09-30 08:21:29 by simonmar] Add a feature request - - - - - 45ff783c by Sven Panne at 2004-10-23T19:54:00+00:00 [haddock @ 2004-10-23 19:54:00 by panne] Improved the Cygwin/MinGW chaos a little bit. There is still confusion about host platform vs. target platform... - - - - - 5f644714 by Krasimir Angelov at 2004-10-28T16:01:51+00:00 [haddock @ 2004-10-28 16:01:51 by krasimir] update for ghc-6.3+ - - - - - 92d9753e by Sven Panne at 2004-11-01T16:39:01+00:00 [haddock @ 2004-11-01 16:39:01 by panne] Revert previous commit: It's Network.URI which should be changed, not Haddock. - - - - - 05f70f6e by Simon Marlow at 2005-01-04T16:15:51+00:00 [haddock @ 2005-01-04 16:15:51 by simonmar] parser fix: allow qualified specialids. - - - - - 47870837 by Simon Marlow at 2005-01-04T16:16:54+00:00 [haddock @ 2005-01-04 16:16:54 by simonmar] Add a test - - - - - ff11fc2c by Ross Paterson at 2005-01-10T19:18:22+00:00 [haddock @ 2005-01-10 19:18:22 by ross] Render non-ASCII characters using numeric character references, to simplify charset issues. There's a META tag saying the charset is UTF-8, but GHC outputs characters as raw bytes. Ideally we need an encoding on the input side too, primarily in comments, because source files containing non-ASCII characters aren't portable between locales. - - - - - eba2fc4e by Simon Marlow at 2005-01-11T10:44:37+00:00 [haddock @ 2005-01-11 10:44:37 by simonmar] Remove string gap - - - - - b899a381 by Ross Paterson at 2005-01-13T11:41:33+00:00 [haddock @ 2005-01-13 11:41:33 by ross] recognize SGML-style numeric character references &#ddd; or &#xhhhh; and translate them into Chars. - - - - - 106e3cf0 by Ross Paterson at 2005-01-13T14:43:41+00:00 [haddock @ 2005-01-13 14:43:41 by ross] also allow uppercase X in hexadecimal character references (like SGML) - - - - - e8f54f25 by Ross Paterson at 2005-01-13T14:44:24+00:00 [haddock @ 2005-01-13 14:44:24 by ross] Describe numeric character references. - - - - - 914ccdce by Sven Panne at 2005-01-15T18:44:48+00:00 [haddock @ 2005-01-15 18:44:45 by panne] Make Haddock compile again after the recent base package changed. The Map/Set legacy hell has been factored out, so that all modules can simply use the new non-deprecated interfaces. Probably a lot of things can be improved by a little bit of Map/Set/List algebra, this can be done later if needed. Small note: Currently the list of instances in HTML code is reversed. This will hopefully be fixed later. - - - - - 6ab20e84 by Sven Panne at 2005-01-16T12:18:26+00:00 [haddock @ 2005-01-16 12:18:26 by panne] Trim imports - - - - - efb81da9 by Sven Panne at 2005-01-16T12:58:08+00:00 [haddock @ 2005-01-16 12:58:03 by panne] Correctly handle the new order of arguments for the combining function given to fromListWith. - - - - - e27b5834 by Sven Panne at 2005-01-16T14:14:41+00:00 [haddock @ 2005-01-16 14:14:39 by panne] Data.Map.unions is left-biased. - - - - - dae3cc3e by Sven Panne at 2005-01-16T14:22:44+00:00 [haddock @ 2005-01-16 14:22:44 by panne] Added the last missing "flip" to get identical HTML output as previous versions. - - - - - 951d8408 by Sven Panne at 2005-01-16T14:37:10+00:00 [haddock @ 2005-01-16 14:37:10 by panne] Refactored Text.PrettyPrint legacy hell into a separate module. - - - - - f1c4b892 by Sven Panne at 2005-01-16T15:41:25+00:00 [haddock @ 2005-01-16 15:41:21 by panne] Cleaned up imports and dropped support for GHC < 5.03, it never worked, anyway. - - - - - 60824c6e by Simon Marlow at 2005-01-18T10:02:48+00:00 [haddock @ 2005-01-18 10:02:48 by simonmar] Add a TODO - - - - - a8c82f23 by Krasimir Angelov at 2005-01-28T23:19:39+00:00 [haddock @ 2005-01-28 23:19:39 by krasimir] import Foreign/Foreign.C are required for Windows - - - - - d8450a23 by Simon Marlow at 2005-02-02T16:23:04+00:00 [haddock @ 2005-02-02 16:23:00 by simonmar] Revamp the linking strategy in Haddock. Now name resolution is done in two phases: - first resolve everything to original names, like a Haskell compiler would. - then, figure out the "home" location for every entity, and point all the links to there. The home location is the lowest non-hidden module in the import hierarchy that documents the entity. If there are multiple candidates, one is chosen at random. Also: - Haddock should not generate any HTML with dangling links any more. Unlinked references are just rendered as plain text. - Error reporting is better: if we can't find a link destination for an entity reference, we now emit a warning. - - - - - 1cce71d0 by Simon Marlow at 2005-02-03T13:42:19+00:00 [haddock @ 2005-02-03 13:42:19 by simonmar] - add --ignore-all-exports flag, which behaves as if every module has the ignore-exports attribute (requested by Chris Ryder). - add --hide option to hide a module on the command line. - add --use-package option to get Haddock info for a package from ghc-pkg (largely untested). - remove reexports from the .haddock file, they aren't used any more. - - - - - 767123ef by Ross Paterson at 2005-02-03T16:17:37+00:00 [haddock @ 2005-02-03 16:17:37 by ross] fix typo for < 6.3 - - - - - 0c680c04 by Simon Marlow at 2005-02-04T12:03:31+00:00 [haddock @ 2005-02-04 12:03:31 by simonmar] Fix bug in renameExportItems that meant links in instances weren't being renamed properly. - - - - - ff7abe5f by Simon Marlow at 2005-02-04T12:15:53+00:00 [haddock @ 2005-02-04 12:15:52 by simonmar] Add attribute #not-home, to indicate that the current module should not be considered to be a home module for the each entity it exports, unless there is no other module that exports the entity. - - - - - fc2cfd27 by Simon Marlow at 2005-02-04T12:40:02+00:00 [haddock @ 2005-02-04 12:40:02 by simonmar] Update the documentation w.r.t. home modules and the not-home attribute. - - - - - 26b8ddf7 by Ross Paterson at 2005-02-04T13:36:06+00:00 [haddock @ 2005-02-04 13:36:05 by ross] sort lists of instances by - arity of the type constructors (so higher-kinded instances come first) - name of the class - argument types - - - - - 26bfb19c by Simon Marlow at 2005-02-23T15:57:12+00:00 [haddock @ 2005-02-23 15:57:12 by simonmar] Fix documentation regarding the module attributes. - - - - - 9c3afd02 by Simon Marlow at 2005-02-28T16:18:17+00:00 [haddock @ 2005-02-28 16:18:17 by simonmar] version 0.7 - - - - - a95fd63f by Simon Marlow at 2005-02-28T16:22:08+00:00 [haddock @ 2005-02-28 16:22:08 by simonmar] Attempt to fix the layout of the package names in the contents. Having tried just about everything, the only thing I can get to work reliably is to make the package names line up on a fixed offset from the left margin. This obviously isn't ideal, so anyone else that would like to have a go at improving it is welcome. One option is to remove the +/- buttons from the contents list and go back to a plain table. The contents page now uses CSS for layout rather than tables. It seems that most browsers have different interpretations of CSS layout, so only the simplest things lead to consistent results. - - - - - 905d42f7 by Simon Marlow at 2005-03-01T17:16:42+00:00 [haddock @ 2005-03-01 17:16:40 by simonmar] Another attempt at lining up the package names on the contents page. Now, they line up with Konqueror, and almost line up with Firefox & IE (different layout in each case). - - - - - a0e1d178 by Wolfgang Thaller at 2005-03-09T08:28:39+00:00 [haddock @ 2005-03-09 08:28:39 by wolfgang] Hack haddock's lexer to accept the output from Apple's broken version of cpp (Apple's cpp leaves #pragma set_debug_pwd directives in it's output). - - - - - 9e1eb784 by Simon Marlow at 2005-04-22T14:27:15+00:00 [haddock @ 2005-04-22 14:27:15 by simonmar] Add a TODO item - - - - - 23281f78 by Ross Paterson at 2005-05-18T12:41:59+00:00 [haddock @ 2005-05-18 12:41:59 by ross] fix 3 bugs in --use-package, and document it. - - - - - 00074a68 by Sven Panne at 2005-05-21T12:35:29+00:00 [haddock @ 2005-05-21 12:35:29 by panne] Warning/versionitis police - - - - - 341fa822 by Simon Marlow at 2005-06-15T15:43:21+00:00 [haddock @ 2005-06-15 15:43:21 by simonmar] Allow "licence" as an alternate spelling of "license" - - - - - 3b953f8b by Simon Marlow at 2005-06-16T08:14:12+00:00 [haddock @ 2005-06-16 08:14:12 by simonmar] wibble - - - - - abfd9826 by Simon Marlow at 2005-06-27T14:46:40+00:00 [haddock @ 2005-06-27 14:46:40 by simonmar] name hierarchical HTML files as A-B-C.html instead of A.B.C.html. The old way confused Apache because the extensions are sometimes interpreted as having special meanings. - - - - - a01eea00 by Simon Marlow at 2005-08-04T13:59:40+00:00 [haddock @ 2005-08-04 13:59:40 by simonmar] 0.7 changes - - - - - 170ef87e by Simon Marlow at 2005-08-04T15:08:03+00:00 [haddock @ 2005-08-04 15:08:03 by simonmar] spec file from Jens Peterson - - - - - 7621fde4 by Simon Marlow at 2005-08-04T15:59:30+00:00 [haddock @ 2005-08-04 15:59:30 by simonmar] replace mingw tests with $(Windows) - - - - - a20739bb by Sven Panne at 2005-08-05T07:01:12+00:00 [haddock @ 2005-08-05 07:01:12 by panne] Reverted to previous version (but with bumped version number), the last commit broke RPM building on SuSE systems due to differently named dependencies. As a clarification: All .spec files in the repository have to work at least on SuSE, because that's the system I'm using. And as "Mr. Building Police", I reserve me the right to keep them that way... >:-) It might very well be the case that we need different .spec files for different platforms, so packagers which are unhappy with the current .spec files should contact me, stating the actual problems. - - - - - 4afb15cf by Simon Marlow at 2005-10-05T10:51:45+00:00 [haddock @ 2005-10-05 10:51:45 by simonmar] Add a bug - - - - - 60f69f82 by Simon Marlow at 2005-10-05T12:52:03+00:00 [haddock @ 2005-10-05 12:52:03 by simonmar] Document new behaviour of -s option - - - - - f7e520ca by Simon Marlow at 2005-10-10T15:02:55+00:00 [haddock @ 2005-10-10 15:02:55 by simonmar] extractRecSel: ignore non-record constructors (fixes a crash when using datatypes with a mixture of record and non-record style constructors). - - - - - b2edbedb by Simon Marlow at 2005-10-14T09:44:21+00:00 Start CHANGES for 0.8 - - - - - 21c7ac8d by Simon Marlow at 2005-10-14T23:11:19+00:00 First cut of Cabal build system - - - - - 766cecdd by Simon Marlow at 2005-10-29T08:14:43+00:00 Add configure script and Makefile for the docs Add a separate configure script and build system for building the documentation. The configure and Makefile code is stolen from fptools. This is left as a separate build system so that the main Cabal setup doesn't require a Unix build environment or DocBook XML tools. - - - - - aa36c783 by Duncan Coutts at 2006-01-17T19:29:55+00:00 Add a --wiki=URL flag to add a per-module link to a correspondng wiki page. So each html page gets an extra link (placed next to the source code and contents links) to a corresponding wiki page. The idea is to let readers contribute their own notes, examples etc to the documentation. Also slightly tidy up the code for the --source option. - - - - - e06e2da2 by Simon Marlow at 2006-01-18T09:28:15+00:00 TODO: documnet --wiki - - - - - 17adfda9 by Duncan Coutts at 2006-01-19T20:17:59+00:00 Add an optional wiki link for each top level exported name. In each module, for each "top level" exported entity we add a hyper link to a corresponding wiki page. The link url gets the name of the exported entity as a '#'-style anchor, so if there is an anchor in the page with that name then the users browser should jump directly to it. By "top level" we mean functions, classes, class members and data types (data, type, newtype), but not data constructors, class instances or data type class membership. The link is added at the right of the page and in a small font. Hopefully this is the right balance of visibility/distraction. We also include a link to the wiki base url in the contents and index pages. - - - - - f52324bb by Duncan Coutts at 2006-01-19T20:28:27+00:00 Rewrite pathJoin to only add a path separator when necessary. When the path ends in a file seperator there is no need to add another. Now using "--wiki=http://blah.com/foo/" should do the right thing. (Code snippet adapted from Isaac's FilePath package.) - - - - - 43bb89fa by Duncan Coutts at 2006-01-21T17:15:27+00:00 Teach haddock about line pragmas and add accurate source code links Teach haddock about C and Haskell style line pragmas. Extend the lexer/parser's source location tracking to include the file name as well as line/column. This way each AST item that is tagged with a SrcLoc gets the original file name too. Use this original file name to add source links to each exported item, in the same visual style as the wiki links. Note that the per-export source links are to the defining module rather than whichever module haddock pretends it is exported from. This is what we want for source code links. The source code link URL can also contain the name of the export so one could implement jumping to the actual location of the function in the file if it were linked to an html version of the source rather than just plain text. The name can be selected with the %N wild card. So for linking to the raw source code one might use: --source=http://darcs/haskell.org/foo/%F Or for linking to html syntax highlighted code: --source=http://darcs/haskell.org/foo/%M.html#%N - - - - - edd9f229 by Duncan Coutts at 2006-01-22T00:02:00+00:00 Extend URL variable expansion syntax and add source links to the contents page Like the wiki link on the contents and index page, add a source code link too. Extend the wiki & source URL variable expansion syntax. The original syntax was: %F for the source file name (the .hs version only, not the .lhs or .hs.pp one) %M for the module name (with '.' replaced by '/') The new syntax is: %F or %{FILE} for the original source file name %M or %{MODULE} for the module name (no replacements) %N or %{NAME} for the function/type export name %K or %{KIND} for a type/value flag "t" or "v" with these extensions: %{MODULE/./c} to replace the '.' module seperator with any other char c %{VAR|some text with the % char in it} which means if the VAR is not in use in this URL context then "" else replace the given text with the '%' char replaced by the string value of the VAR. This extension allows us to construct URLs wit optional parts, since the module/file name is not available for the URL in the contents/index pages and the value/type name is not available for the URL at the top level of each module. - - - - - eb3c6ada by Duncan Coutts at 2006-01-23T13:42:34+00:00 Remove the complex substitutions and add more command line flags instead. Instead of incomprehensable URL substitutions like ${MODULE/./-|?m=%} we now use three seperate command line flags for the top level, per-module and per-entity source and wiki links. They are: --source-base, --source-module, --source-entity --comments-base, --comments-module, --comments-entity We leave -s, --source as an alias for --source-module which is how that option behaved previously. The long forms of the substitutions are still available, ${FILE} ${MODULE} etc and the only non-trivial substitution is ${MODULE/./c} to replace the '.' characters in the module name with any other character c. eg ${MODULE/./-} Seperating the source and wiki url flags has the added bonus that they can be turned on or off individually. So users can have per-module links for example without having to also have per-entity links.` - - - - - a2f0f2af by Duncan Coutts at 2006-01-23T13:54:52+00:00 Make the --help output fit in 80 columns. This is a purely cosmetic patch, feel free to ignore it. The only trickery going on is that we don't display the deprecated -s, --source flags in the help message, but we do still accept them. - - - - - 2d3a4b0c by Duncan Coutts at 2006-01-23T14:12:16+00:00 Add documentation for the new --source-* and --comments-* command line options - - - - - 1a82a297 by Simon Marlow at 2006-01-23T17:03:27+00:00 fix markup - - - - - 100d464a by Duncan Coutts at 2006-01-23T18:31:13+00:00 remove a couple TODO items that have been done The --wiki, or rather the --comment-* options are now documented. There is probably no need to have haddock invoke unlit or cpp itself since it can now pick up the line pragmas to get the source locations right. Tools like Cabal will arrange for preprocessors to be run so there is less of a need for tools like haddock to do it themselves. - - - - - 3162fa91 by Simon Marlow at 2006-01-24T14:21:56+00:00 add a test I had lying around - - - - - 98947063 by Simon Marlow at 2006-01-31T13:52:54+00:00 add scabal-version field - - - - - c41876e6 by Neil Mitchell at 2006-02-26T17:48:21+00:00 Add Hoogle output option - - - - - f86fb9c0 by Simon Marlow at 2006-03-08T09:15:20+00:00 add haskell.vim Contributed by Brad Bowman <bsb at bereft.net>, thanks! - - - - - 35d3c511 by benjamin.franksen at 2006-03-03T22:39:54+00:00 fixed libdir (/html was missing) - - - - - 4d08fd7d by Simon Marlow at 2006-03-10T11:13:31+00:00 add PatternGuards extension - - - - - 3f095e70 by Simon Marlow at 2006-03-13T11:40:42+00:00 bug fixes from Brad Bowman - - - - - 8610849d by Sven Panne at 2006-03-19T17:02:56+00:00 Fixed Cabal/RPM build - - - - - 34a994d6 by sven.panne at 2006-04-20T12:39:23+00:00 Avoid pattern guards Due to the use of pattern guards in Haddock, GHC was called with -fglasgow-exts. This in turn enables bang patterns, too, which broke the Haddock build. Removing some unnecessary pattern guards seemed to be the better way of fixing this instead of using a pragma to disable pattern guards. - - - - - bb523f51 by Ross Paterson at 2006-04-24T09:03:25+00:00 extend 'deriving' heuristic a little If an argument of a data constructor has a type variable head, it is irreducible and the same type class can be copied into the constraint. (Formerly we just did this for type variable arguments.) - - - - - dab9fe7a by Simon Marlow at 2006-04-26T10:02:31+00:00 record an idea - - - - - 748b7078 by Simon Marlow at 2006-05-08T08:28:53+00:00 add section about deriving - - - - - 11252ea1 by Simon Marlow at 2006-05-24T15:43:10+00:00 replace a fatal error in lexChar with a parseError - - - - - 382c9411 by Simon Marlow at 2006-05-24T15:45:47+00:00 add a bug - - - - - b79272f5 by Simon Marlow at 2006-05-24T15:46:29+00:00 add a bug report - - - - - 912edf65 by David Waern at 2006-07-10T19:09:23+00:00 Initial modifications -- doesn't compile - - - - - a3c7ba99 by David Waern at 2006-07-11T00:54:19+00:00 More porting work -- doesn't compile - - - - - 0a173d19 by David Waern at 2006-07-11T11:30:03+00:00 Make the repos temporarily compile and illustrate a problem - - - - - bad316de by David Waern at 2006-07-11T15:43:47+00:00 Progress on the porting process - - - - - bbf12d02 by David Waern at 2006-07-11T23:07:44+00:00 More progress on the porting -- first pass starting to shape up - - - - - de580ba2 by David Waern at 2006-07-20T17:48:30+00:00 More progress -- still on phase1 - - - - - 75a917a2 by David Waern at 2006-07-23T18:22:43+00:00 More work on pass1 -- mostly done - - - - - 6697b3f7 by David Waern at 2006-07-23T22:17:40+00:00 More work, started working on the renaming phase -- this code will need a cleanup soon :) - - - - - 82a5bcbb by David Waern at 2006-07-29T16:16:43+00:00 Add instances, build renaming environment, start on the renamer - - - - - c3f8f4f1 by David Waern at 2006-07-29T21:37:48+00:00 Complete the renamer - - - - - 7e00d464 by David Waern at 2006-07-30T21:01:57+00:00 Start porting the Html renderer - - - - - f04ce121 by David Waern at 2006-08-09T20:04:56+00:00 More Html rendering progress - - - - - 20c21b53 by David Waern at 2006-08-10T17:37:47+00:00 More progress - - - - - d7097e0d by David Waern at 2006-08-11T20:31:51+00:00 Cleanup - - - - - a7351e86 by David Waern at 2006-08-12T11:44:47+00:00 Render H98 Data declarations - - - - - 3fb2208e by David Waern at 2006-08-12T17:15:34+00:00 Perfect rendering of Test.hs - - - - - 454fd062 by David Waern at 2006-08-13T21:57:08+00:00 Misc fixes and interface load/save - - - - - 7ef7e7be by David Waern at 2006-08-14T00:56:07+00:00 Some refactoring - - - - - a7d3efef by David Waern at 2006-08-19T20:07:55+00:00 Adapt to latest GHC - - - - - 5fc3c0d7 by David Waern at 2006-08-20T21:28:11+00:00 Move interface read/write to its own module + some cleanup - - - - - 037e011c by David Waern at 2006-08-20T21:38:24+00:00 Small cleanup - - - - - da3a1023 by David Waern at 2006-09-03T16:05:22+00:00 Change mode to BatchCompile to avoid GHC API bug - - - - - 3cc9be3b by David Waern at 2006-09-03T16:06:59+00:00 Starting work on GADT rendering - - - - - 94506037 by David Waern at 2006-09-03T20:02:48+00:00 Compensate for change of export list order in GHC - - - - - c2cec4eb by David Waern at 2006-09-04T20:53:01+00:00 Rename a function - - - - - 9a9735ba by David Waern at 2006-09-05T15:51:21+00:00 Change version number to 2.0 - - - - - 3758a714 by David Waern at 2006-09-05T15:51:49+00:00 Align comment properly - - - - - 68478d9e by David Waern at 2006-09-15T18:03:00+00:00 Remove interface reading/writing code and use the GHC api for creating package environments instead - - - - - d2eedd95 by David Waern at 2006-09-15T18:05:29+00:00 Change the executable name to haddock-ghc-nolib - - - - - fcfbcf66 by David Waern at 2006-09-15T18:05:45+00:00 Small source code cleanup - - - - - d08eb017 by David Waern at 2006-09-15T18:06:21+00:00 Remove handling of --package flag - - - - - b8a4cf53 by David Waern at 2006-09-15T18:07:16+00:00 Remove commented-out code - - - - - bef0a684 by David Waern at 2006-09-15T18:37:57+00:00 Don't warn about missing links to () - - - - - e7d25fd7 by David Waern at 2006-09-15T19:50:49+00:00 Remove Interface and Binary2 modules - - - - - 9894f2a1 by David Waern at 2006-09-15T19:53:43+00:00 Remove debug printing from HaddockHtml - - - - - a0e7455d by David Waern at 2006-09-16T00:16:29+00:00 Comments only - - - - - d5b26fa7 by David Waern at 2006-09-16T00:16:57+00:00 Refactor PackageData creation code and start on building the doc env propery (unfinished) - - - - - 06aaa779 by David Waern at 2006-09-16T00:19:25+00:00 Better comments in Main.hs - - - - - 1a52d1b4 by David Waern at 2006-09-18T22:17:11+00:00 Comments and spacing change - - - - - e5a97767 by David Waern at 2006-09-21T17:02:45+00:00 Remove unnecessary fmapM import in Main - - - - - 9d0f9d3a by David Waern at 2006-09-22T18:07:07+00:00 Make import list in HaddockHtml prettier - - - - - 3452f662 by David Waern at 2006-09-22T18:08:47+00:00 Refactor context rendering - - - - - 12d0a6d0 by David Waern at 2006-09-22T18:09:52+00:00 Do proper HsType rendering (inser parentheses correctly) - - - - - 2c20c2f9 by David Waern at 2006-09-22T18:10:45+00:00 Fix a bug in Main.toHsType - - - - - c5396443 by David Waern at 2006-09-22T18:11:16+00:00 Skip external package modules sort for now - - - - - 3fb95547 by David Waern at 2006-09-22T20:35:40+00:00 Take away trailin "2" on all previously clashing type names - - - - - 2174755f by David Waern at 2006-09-22T20:51:43+00:00 Remove unused imports in Main - - - - - 1e9f7a39 by David Waern at 2006-09-22T20:52:11+00:00 Fix a comment in Main - - - - - 32d9e028 by David Waern at 2006-10-05T16:40:11+00:00 Merge with changes to ghc HEAD - - - - - 3058c8f5 by David Waern at 2006-10-05T16:41:02+00:00 Comment fixes - - - - - b9c217ec by David Waern at 2006-10-05T16:49:59+00:00 Filter out more builtin type constructors from warning messages - - - - - 67e7d252 by David Waern at 2006-10-05T19:38:22+00:00 Refactoring -- better structured pass1 - - - - - cd21c0c1 by David Waern at 2006-10-05T19:44:42+00:00 Remove read/dump interface flags - - - - - 313f9e69 by David Waern at 2006-10-05T19:49:26+00:00 Remove unused pretty printing - - - - - 480f09d1 by David Waern at 2006-12-28T13:22:24+00:00 Update to build with latest GHC HEAD - - - - - 63dccfcb by David Waern at 2007-01-05T01:38:45+00:00 Fixed a bug so that --ghc-flag works correctly - - - - - 3117dadc by David Waern at 2006-12-29T18:53:39+00:00 Automatically get the GHC lib dir - - - - - 9dc84a5c by David Waern at 2006-12-29T19:58:53+00:00 Comments - - - - - 0b0237cc by David Waern at 2007-01-05T16:48:30+00:00 Collect docs based on SrcLoc, syncing with removal of DeclEntity from GHC - - - - - a962c256 by David Waern at 2007-01-05T17:02:47+00:00 Add tabs in haddock.cabal - - - - - 0ca30c97 by David Waern at 2007-01-05T17:04:11+00:00 Add GHCUtils.hs - - - - - c0ab9abe by David Waern at 2007-01-10T11:43:08+00:00 Change package name to haddock-ghc, version 0.1 - - - - - 38e18b27 by David Waern at 2007-01-12T12:03:52+00:00 No binder name for foreign exports - - - - - d18587ab by David Waern at 2007-01-12T12:08:15+00:00 Temp record - - - - - ba6251a0 by David Waern at 2007-01-12T18:27:55+00:00 Remove read/dump-interface (again) - - - - - f4ba2b39 by David Waern at 2007-01-12T18:31:36+00:00 Remove DocOption, use the GHC type - - - - - 511be8bd by David Waern at 2007-01-12T18:32:41+00:00 Use exceptions instead of Either when loading package info - - - - - 0f2144d8 by David Waern at 2007-01-12T18:33:23+00:00 Small type change - - - - - 77507eb7 by David Waern at 2007-01-12T18:33:59+00:00 Remove interface file read/write - - - - - 0ea1e14f by David Waern at 2007-01-17T21:40:26+00:00 Add trace_ppr to GHCUtils - - - - - 3878b493 by David Waern at 2007-01-17T21:40:53+00:00 Sort external package modules and build a doc env - - - - - 8dc323fc by David Waern at 2007-01-17T21:42:41+00:00 Remove comment - - - - - f4c5b097 by David Waern at 2007-01-18T23:22:18+00:00 Add haddock-ghc.cabal and remove ghc option pragma in source file - - - - - da242b2c by David Waern at 2007-01-18T23:22:46+00:00 Remove some tabs - - - - - 288ed096 by David Waern at 2007-01-18T23:39:28+00:00 Moved the defaultErrorHandler to scope only over sortAndCheckModules for now - - - - - 4dd150fe by David Waern at 2007-02-03T21:23:56+00:00 Let restrictCons handle infix constructors - - - - - 97893442 by David Waern at 2007-02-04T16:26:00+00:00 Render infix data constructors - - - - - da89db72 by David Waern at 2007-02-04T16:26:33+00:00 CHange project name to Haddock-GHC - - - - - e93d48af by David Waern at 2007-02-04T16:59:08+00:00 Render infix type constructors properly - - - - - 357bc99b by David Waern at 2007-02-04T17:37:08+00:00 Insert spaces around infix function names - - - - - ab6cfc49 by David Waern at 2007-02-04T17:59:54+00:00 Do not list entities without documentation - - - - - 04249c7e by David Waern at 2007-02-04T19:16:25+00:00 Add GADT support (quite untested) - - - - - 2c223f8d by David Waern at 2007-02-04T19:25:10+00:00 Add package file write/save again! - - - - - b07ed218 by David Waern at 2007-02-04T19:33:02+00:00 Comment out minf_iface based stuff - - - - - 953d1fa7 by David Waern at 2007-02-05T00:12:23+00:00 Solve conflicts - - - - - 593247fc by David Waern at 2007-02-06T19:48:48+00:00 Remove -package flag, GHC's can be used instead - - - - - f658ded2 by David Waern at 2007-02-06T20:50:44+00:00 Start for support of ATs - - - - - 97f9e913 by David Waern at 2007-02-06T20:52:27+00:00 Wibble - - - - - 2ce8e4cf by David Waern at 2007-02-16T12:09:49+00:00 Add the DocOptions change - - - - - dee4a9b5 by David Waern at 2007-03-06T01:24:48+00:00 Wibble - - - - - 7cb99d18 by David Waern at 2007-03-06T01:24:58+00:00 Change version to 2.0 and executable name to haddock - - - - - c5aa02bc by David Waern at 2007-03-08T15:59:49+00:00 Go back to -B flag - - - - - 3a349201 by David Waern at 2007-03-09T13:31:59+00:00 Better exception handling and parsing of GHC flags - - - - - 05a69b71 by David Waern at 2007-03-09T17:45:44+00:00 Remove commented-out DocEntity printing - - - - - 755032cb by davve at dtek.chalmers.se at 2007-03-23T23:30:20+00:00 Remove a file that shouldn't be here - - - - - a7077e5f by davve at dtek.chalmers.se at 2007-03-24T03:58:48+00:00 Remove an import - - - - - 6f55aa8b by davve at dtek.chalmers.se at 2007-03-25T00:46:48+00:00 Start work on Haddock API - - - - - f0199480 by davve at dtek.chalmers.se at 2007-03-25T00:56:36+00:00 Prettify some comments - - - - - f952f9d1 by davve at dtek.chalmers.se at 2007-03-25T00:56:53+00:00 Remove ppr in HaddockTypes - - - - - bc594904 by davve at dtek.chalmers.se at 2007-03-25T00:57:53+00:00 Remove commented out doc env inference - - - - - 11ebf08d by davve at dtek.chalmers.se at 2007-03-25T01:23:25+00:00 De-flatten the namespace - - - - - f696b4bc by davve at dtek.chalmers.se at 2007-03-25T03:21:48+00:00 Add missing stuff to API - - - - - 9a2a04c3 by davve at dtek.chalmers.se at 2007-03-25T03:22:02+00:00 Wibble - - - - - 7d04a6d5 by davve at dtek.chalmers.se at 2007-03-25T03:22:08+00:00 Avoid a GHC bug with parseStaticFlags [] - - - - - 4d2820ba by davve at dtek.chalmers.se at 2007-03-26T04:57:01+00:00 Add fall-through case to mkExportItem - - - - - 6ebc8950 by Stefan O'Rear at 2007-03-26T04:14:53+00:00 Add shebang line to Setup.lhs - - - - - 80966ec5 by davve at dtek.chalmers.se at 2007-03-26T05:24:26+00:00 Fix stupid compile error - - - - - 1ea1385d by davve at dtek.chalmers.se at 2007-04-05T17:19:56+00:00 Do save/read of interface files properly - - - - - 0e4f6541 by David Waern at 2007-04-10T21:08:36+00:00 Add version to ghc dependency - - - - - b0499b63 by David Waern at 2007-04-10T21:37:08+00:00 Change package name to haddock - - - - - 9d50d27e by David Waern at 2007-04-24T00:22:14+00:00 Use filepath package instead of FilePath - - - - - 87c7fcdf by David Waern at 2007-07-10T21:03:04+00:00 Add new package dependencies - - - - - 4768709c by David Waern at 2007-07-11T20:37:11+00:00 Follow changes to record constructor representation - - - - - b9a02fee by Simon Marlow at 2007-05-30T14:00:48+00:00 update to compile with the latest GHC & Cabal - - - - - c0ebdc01 by David Waern at 2007-07-11T21:35:45+00:00 Fix conflicts - - - - - 97f7afd4 by David Waern at 2007-07-11T21:52:38+00:00 Follow changes to the GHC API - - - - - a5b7b58f by David Waern at 2007-07-12T20:36:48+00:00 Call parseStaticFlags before newSession - - - - - f7f50dbc by David Waern at 2007-08-01T21:52:58+00:00 Better indentation in haddock.cabal - - - - - d84e52ad by David Waern at 2007-08-02T00:08:18+00:00 Wibble - - - - - a23f494a by David Waern at 2007-08-02T00:08:24+00:00 Be better at trying to load all module dependencies (debugging) - - - - - ee917f13 by David Waern at 2007-08-03T18:48:08+00:00 Load all targets explicitly (checkModule doesn't chase dependencies anymore) - - - - - 5182d631 by David Waern at 2007-08-16T16:48:55+00:00 Finalize support for links to other packages - - - - - dfd1e3da by David Waern at 2007-08-16T16:51:11+00:00 Fix haddock comment errors in Haddock.Types - - - - - 50c0d83e by David Waern at 2007-08-16T16:51:37+00:00 Remove a debug import - - - - - d84b7c2b by David Waern at 2007-08-16T17:06:30+00:00 Rename PackageData to HaddockPackage - - - - - 3b52cb9f by David Waern at 2007-08-16T17:09:42+00:00 Simplify some comments - - - - - 66fa68d9 by David Waern at 2007-08-16T17:11:38+00:00 Comment the HaddockPackage definition - - - - - 8674c761 by David Waern at 2007-08-16T17:25:54+00:00 Improve code layout in Main - - - - - 571a3a0b by David Waern at 2007-08-16T17:32:13+00:00 Remove explict module imports in Main - - - - - d31b3cb0 by David Waern at 2007-08-16T17:36:23+00:00 Correct comments - - - - - 7f8a9f2b by David Waern at 2007-08-16T17:39:50+00:00 Fix layout problems in Haddock.Types - - - - - 9f421d7f by David Waern at 2007-08-17T11:16:48+00:00 Move options out of Main into Haddock.Options - - - - - 80042b63 by David Waern at 2007-08-17T11:26:59+00:00 Small comment/layout fixes - - - - - b141b982 by David Waern at 2007-08-17T11:28:28+00:00 Change project name from Haddock-GHC to Haddock - - - - - dbeb4a81 by David Waern at 2007-08-17T11:41:05+00:00 Add top module comment to all files - - - - - ce99cc9e by David Waern at 2007-08-17T14:53:04+00:00 Factor out typechecking phase into Haddock.Typecheck - - - - - 6bf75d9e by David Waern at 2007-08-17T16:55:35+00:00 Factor out package code to Haddock.Packages - - - - - b396db37 by David Waern at 2007-08-29T22:40:23+00:00 Major refactoring - - - - - 3d4f95ee by David Waern at 2007-08-29T23:26:24+00:00 Rename HaddockModule to Interface and a few more refactorings - - - - - c55326db by David Waern at 2007-08-29T23:48:03+00:00 Some comment cleanup - - - - - 9a84fc46 by David Waern at 2007-08-29T23:49:29+00:00 Add some modules that I forgot to add earlier - - - - - 4536dce2 by David Waern at 2007-08-29T23:55:24+00:00 Wibble - - - - - 9b7f0206 by David Waern at 2007-08-30T16:03:29+00:00 Wibble - - - - - c52c050a by David Waern at 2007-08-30T16:30:37+00:00 Rename HaddockModule to Interface - - - - - eae2995f by David Waern at 2007-08-30T16:42:59+00:00 Simplify createInterfaces - - - - - 53f99caa by David Waern at 2007-09-29T00:04:31+00:00 Add build-type: Simple to the cabal file - - - - - 0d3103a8 by David Waern at 2007-09-29T00:04:58+00:00 Add containers and array dependency - - - - - 6acf5f30 by David Waern at 2007-09-29T00:13:36+00:00 Prettify the cabal file - - - - - 87c1e378 by David Waern at 2007-09-29T13:16:39+00:00 FIX: consym data headers with more than two variables - - - - - b67fc16a by David Waern at 2007-09-29T14:01:32+00:00 FIX: prefix types used as operators should be quoted - - - - - a8f925bc by David Waern at 2007-09-29T14:02:26+00:00 Use isSymOcc from OccName instead of isConSym - - - - - fc330701 by David Waern at 2007-09-29T14:15:37+00:00 Use isLexConSym/isLexVarSym from OccName - - - - - e4f3dbad by David Waern at 2007-09-29T15:01:08+00:00 FIX: do not quote varsym type operators - - - - - 402207d2 by David Waern at 2007-09-29T15:01:50+00:00 Wibble - - - - - f9d89ef0 by David Waern at 2007-09-29T15:17:40+00:00 Take care when pp tyvars - add parens on syms - - - - - 849e2a77 by David Waern at 2007-10-01T21:56:39+00:00 Go back to using a ModuleMap instead of LookupMod - fixes a bug - - - - - 549dbac6 by David Waern at 2007-10-02T01:05:19+00:00 Improve parsing of doc options - - - - - a36021b8 by David Waern at 2007-10-02T23:05:00+00:00 FIX: double arrows in constructor contexts - - - - - d03bf347 by David Waern at 2007-10-09T16:14:05+00:00 Add a simple test suite - - - - - c252c140 by David Waern at 2007-10-17T16:02:28+00:00 Add --optghc=.. style flag passing to GHC - - - - - cce6c1b3 by David Waern at 2007-10-18T22:03:20+00:00 Add support for --read-interface again - - - - - 33d059c0 by David Waern at 2007-10-18T22:30:18+00:00 Refactoring -- get rid of Haddock.Packages - - - - - f9ed0a4c by David Waern at 2007-10-18T22:34:36+00:00 Name changes - - - - - 8a1c816f by David Waern at 2007-10-20T14:24:23+00:00 Add --ghc-version option - - - - - 4925aaa1 by David Waern at 2007-10-21T14:34:26+00:00 Add some Outputable utils - - - - - 69e7e47f by David Waern at 2007-10-21T14:35:49+00:00 FIX: Ord for OrdName was not comparing modules - - - - - 5a4ae535 by David Waern at 2007-10-21T21:18:48+00:00 Wibble - - - - - 03d48e20 by David Waern at 2007-10-24T15:52:56+00:00 Remove Main from "other modules" - - - - - c66f6d82 by David Waern at 2007-10-24T16:37:18+00:00 Make it possible to run haddock on itself - - - - - 21d156d8 by David Waern at 2007-10-25T14:02:14+00:00 Don't set boot modules as targets - - - - - f8bcf91c by David Waern at 2007-10-31T22:11:17+00:00 Add optimisation flags - - - - - 7ac758f2 by David Waern at 2007-11-04T09:48:28+00:00 Go back to loading only targets (seems to work now) - - - - - 4862aae1 by David Waern at 2007-11-05T22:24:57+00:00 Do full compilation of modules -- temporary fix for GHC API problem - - - - - 697e1517 by David Waern at 2007-11-05T22:25:50+00:00 Don't warn about not being able to link to wired/system/builtin-names - - - - - 892186da by David Waern at 2007-11-06T00:49:21+00:00 Filter out instances with TyCons that are not exported - - - - - 9548314c by David Waern at 2007-11-06T09:37:14+00:00 Wibble - - - - - 5cafd627 by David Waern at 2007-11-08T01:43:07+00:00 Filter out all non-vanilla type sigs - - - - - 04621830 by David Waern at 2007-11-08T01:45:13+00:00 Synch loading of names from .haddock files with GHC's name cache - - - - - 88d37f77 by David Waern at 2007-11-08T01:46:21+00:00 Remove commented-out code - - - - - 6409c911 by David Waern at 2007-11-08T01:56:00+00:00 Small bugfix and cleanup in getDeclFromTyCls - - - - - af59d9c2 by David Waern at 2007-11-08T02:08:44+00:00 Remove OrdName stuff - - - - - 3a615e2e by David Waern at 2007-11-08T02:13:41+00:00 Update runtests.hs following changes to haddock - - - - - 01f3314e by David Waern at 2007-11-08T02:33:01+00:00 Complain if we can't link to wired-in names - - - - - fcafb5d1 by David Waern at 2007-11-09T02:40:16+00:00 Don't exit when there are no file arguments - - - - - 194bc332 by David Waern at 2007-11-09T02:55:37+00:00 Wibble - - - - - dbe4cb55 by David Waern at 2007-11-09T02:56:14+00:00 Wibble - - - - - 82869fda by David Waern at 2007-11-10T17:01:43+00:00 Introduce InstalledInterface structure and add more stuff to the .haddock files We introduce InstalledInterface capturing the part of Interface that is stored in the interface files. We change the ppHtmlContents and ppHtmllIndex to take this structure instead of a partial Interface. We add stuff like the doc map and exported names to the .haddock file (via InstalledInterface). - - - - - d6bb57bf by David Waern at 2007-11-10T17:19:48+00:00 FIX: contents and index should include external package modules when --gen-contents/--gen-index - - - - - e8814716 by David Waern at 2007-11-11T00:29:27+00:00 Remove lDocLinkName and its use in Html backend - - - - - 6f9bd702 by David Waern at 2007-11-11T00:50:57+00:00 Do some refactoring in the html backend This also merges an old patch by Augustsson: Wed Jul 12 19:54:36 CEST 2006 lennart.augustsson at credit-suisse.com * Print type definitions like signatures if given arrows. - - - - - 09d0ce24 by Malcolm.Wallace at 2006-07-20T13:13:57+00:00 mention HsColour in the docs, next to option flags for linking to source code - - - - - 24da6c34 by Malcolm.Wallace at 2006-07-20T13:14:50+00:00 change doc references to CVS to give darcs repository location instead - - - - - 74d52cd6 by David Waern at 2007-11-11T00:55:33+00:00 Update copyright - - - - - fcaa3b4f by Duncan Coutts at 2006-09-08T13:41:00+00:00 Eliminate dep on network by doing a little cut'n'paste haddock depending on the network causes a circular dependency at least if you want to build the network lib with haddock docs. - - - - - 10cc9bda by David Waern at 2007-11-11T02:09:41+00:00 Fix conflicts - - - - - 4e3acd39 by David Waern at 2007-11-11T02:21:19+00:00 Manual merge of a patch from Duncan Coutts that removes the dependency on mtl - - - - - fa9070da by Neil Mitchell at 2006-09-29T15:52:03+00:00 Do not generate an empty table if there are no exports, this fixes a <table></table> tag being generated, which is not valid HTML 4.01 - - - - - d7431c85 by David Waern at 2007-11-11T02:28:50+00:00 Fix conflicts - - - - - f87e8f98 by Simon Marlow at 2006-10-10T11:37:16+00:00 changes for 0.8 - - - - - db929565 by Simon Marlow at 2006-10-10T12:07:12+00:00 fix the name of the source file - - - - - 8220aa4b by Simon Marlow at 2006-10-11T14:17:37+00:00 Rename haddock.js to haddock-util.js haddock.js will be run automatically by Windows when you type 'haddock' if it is found on the PATH, so rename to avoid confusion. Spotted by Adrian Hey. - - - - - 6bccdaa1 by sven.panne at 2006-10-12T15:28:23+00:00 Cabal's sdist does not generate "-src.tar.gz" files, but ".tar.gz" ones - - - - - d3f3fc19 by Simon Marlow at 2006-12-06T16:05:07+00:00 add todo item for --maintainer - - - - - 2da7e269 by Simon Marlow at 2006-12-15T15:52:00+00:00 TODO: do something better about re-exported symbols from another package - - - - - 42d85549 by David Waern at 2007-11-11T02:30:59+00:00 Fix conflicts - - - - - 5e7ef6e5 by Neil Mitchell at 2007-01-11T15:41:15+00:00 Never do spliting index files into many - - - - - f3d4aebe by Neil Mitchell at 2007-01-11T17:07:09+00:00 Add searching on the index page - - - - - bad3ab66 by Neil Mitchell at 2007-01-11T18:17:46+00:00 Delete dead code, now there is only one index page - - - - - cd09eedb by Neil Mitchell at 2007-01-11T18:21:19+00:00 Delete more stuff that is no longer required - - - - - e2806646 by David Waern at 2007-11-11T02:41:53+00:00 Fix conflicts - - - - - a872a823 by Neil Mitchell at 2007-01-11T18:51:43+00:00 Make the index be in case-insensitive alphabetic order - - - - - 8bddd9d7 by Neil Mitchell at 2007-02-06T17:49:12+00:00 Do not create empty tables for data declarations which don't have any constructors, instances or comments. Gets better HTML 4.01 compliance - - - - - 036b8120 by David Waern at 2007-11-11T02:56:58+00:00 Fix conflicts - - - - - f50c1639 by Conal Elliott at 2007-02-14T21:54:00+00:00 added substitution %{FILE///c} - - - - - 402e166a by David Waern at 2007-11-11T03:35:46+00:00 Manual merge of old patch: Sat Apr 21 04:36:43 CEST 2007 Roberto Zunino <zunrob at users.sf.net> * URL expansion for %%, %L, %{LINE} - - - - - 2f264fbd by David Waern at 2007-11-11T03:40:33+00:00 Manual merge of an old patch: Thu Apr 19 20:23:40 CEST 2007 Wolfgang Jeltsch <g9ks157k at acme.softbase.org> * bug fix When Haddock was invoked with the --ignore-all-exports flag but the ignore-exports module attribute wasn't used, hyperlinks weren't created for non-exported names. This fix might not be as clean as one would wish (since --ignore-all-exports now results in ignore_all_exports = True *and* an additional OptIgnoreExports option for every module) but at least the bug seems to be resolved now. - - - - - 7d7ae106 by sven.panne at 2007-09-02T12:18:02+00:00 Install LICENSE in the correct place - - - - - 66eaa924 by David Waern at 2007-11-11T19:02:46+00:00 Fix a bug that made haddock loop - - - - - 4ed47b58 by David Waern at 2007-11-11T19:03:09+00:00 Rename java-script file (this wasn't merge correctly) - - - - - d569534a by David Waern at 2007-11-11T19:06:44+00:00 Don't require -B <ghc-libdir> when no argument files Change readInterfaceFile to take a Maybe Session, to avoid having to pass -B <ghc-libdir> to Haddock when there're no source files to process. This is nice when computing contents/index for external packages. - - - - - 373368bc by Neil Mitchell at 2007-01-11T18:22:44+00:00 Change from tabs to spaces in the ppHtmlIndex function - - - - - 6b063a77 by Neil Mitchell at 2007-01-12T12:17:46+00:00 Rewrite much of the index searching code, previously was too slow to execute on the base library with IE, the new version guarantees less than O(log n) operations be performed, where n is the number in the list (before was always O(n)) - - - - - bfad00b7 by David Waern at 2007-11-11T23:33:53+00:00 Fix conflicts - - - - - cd2dcc09 by Neil Mitchell at 2007-01-12T12:25:01+00:00 Make the max number of results 75 instead of 50, to allow map searching in the base library to work - - - - - 3ae74764 by Neil Mitchell at 2007-01-12T12:58:17+00:00 Make the search box in a form so that enter does the default search - - - - - 142103e5 by David Waern at 2007-11-12T00:03:18+00:00 Merge patch from the old branch: Fri Aug 31 13:21:45 CEST 2007 Duncan Coutts <duncan at haskell.org> * Add category: Development to .cabal file Otherwise it appears on the hackage website in the "Unclassified" category. - - - - - 22ec2ddb by David Waern at 2007-11-25T01:55:29+00:00 A a list of small improvements to the TODO file - - - - - eb0129f4 by Wolfgang Jeltsch at 2007-12-03T23:47:55+00:00 addition of type equality support (at least for HTML generation) - - - - - 816a7e22 by David Waern at 2007-12-08T15:46:26+00:00 Handle class operators correctly when rendering predicates - - - - - 68baaad2 by David Waern at 2007-12-08T16:15:54+00:00 Code layout changes - - - - - 09b77fb4 by David Waern at 2007-12-08T16:16:03+00:00 Handle infix operators correctly in the Type -> HsType translation - - - - - 31c36da2 by David Waern at 2007-12-08T16:24:27+00:00 Add ppLParendTypes/ppLParendType - - - - - b17cc818 by David Waern at 2007-12-08T16:26:12+00:00 Use ppParendType when printing types args in predicates - - - - - ffd1f2cf by David Waern at 2007-12-08T16:45:06+00:00 Fix rendering of instance heads to handle infix operators This is also a refactoring to share this code for rendering predicates. - - - - - ff886d45 by David Waern at 2007-12-08T17:27:46+00:00 Fix rendering of class operators - - - - - e2fcbb9e by David Waern at 2007-12-08T17:59:28+00:00 Fix a bug (use ppTyName instead of ppName to print names in type apps) - - - - - 79a1056e by David Waern at 2007-12-08T21:25:18+00:00 Update tests - - - - - 867741ac by David Waern at 2007-12-08T21:25:49+00:00 Give a diff on test failure - - - - - 7e5eb274 by David Waern at 2008-01-05T14:33:45+00:00 Add DrIFT commands - - - - - 3656454d by David Waern at 2008-01-05T20:26:00+00:00 Add "cabal-version: >= 1.2" to the cabal file - - - - - 77974efc by Simon Marlow at 2007-12-20T09:52:44+00:00 add an item - - - - - f6ac1708 by Simon Marlow at 2007-12-06T14:00:10+00:00 Source links must point to the original module, not the referring module - - - - - eda1d5c9 by David Waern at 2008-01-06T14:40:52+00:00 Manual merge of a patch to the 0.8 branch Thu Dec 6 15:00:10 CET 2007 Simon Marlow <simonmar at microsoft.com> * Source links must point to the original module, not the referring module - - - - - 378f4085 by David Waern at 2008-01-06T16:03:45+00:00 Change stability from stable to experimental - - - - - 8bdafe44 by David Waern at 2008-01-06T16:14:22+00:00 Add haskell.vim (it had been removed somehow) - - - - - ea34d02e by David Waern at 2008-01-06T16:36:57+00:00 Change version to 2.0.0.0 - - - - - 34631ac0 by David Waern at 2008-01-06T16:44:57+00:00 Add missing modules to the cabal file - - - - - 9e142935 by David Waern at 2008-01-06T17:25:42+00:00 Depend on ghc >= 6.8.2 && < 6.9 - - - - - 59f9eeaa by Simon Marlow at 2007-12-20T10:43:04+00:00 add build scripts - - - - - 1c29ae30 by Simon Marlow at 2007-12-20T10:47:07+00:00 update version number - - - - - fe16a3e4 by Simon Marlow at 2007-12-20T10:48:03+00:00 update version - - - - - f688530f by Simon Marlow at 2007-12-20T10:48:29+00:00 doc updates - - - - - ce71b611 by David Waern at 2008-01-07T13:46:32+00:00 Change version in docs and spec - - - - - 03ab8d6f by David Waern at 2008-01-07T13:47:38+00:00 Manually merge over changes to CHANGES for 0.9 - - - - - 39f1b042 by David Waern at 2008-01-07T15:17:41+00:00 Remove the -use-package flag, we don't support it anyway - - - - - 7274a544 by David Waern at 2008-01-07T15:33:05+00:00 Update CHANGES for 2.0.0.0 - - - - - 96594f5d by David Waern at 2008-01-07T15:46:49+00:00 Wibble - - - - - f4c5a4c4 by David Waern at 2008-01-07T15:55:36+00:00 Change url to repo in documentation - - - - - 8a4c77f0 by David Waern at 2008-01-07T16:00:54+00:00 Update CHANGES - - - - - cb3a9288 by David Waern at 2008-01-07T16:02:55+00:00 Documentation fix - - - - - d8e45539 by David Waern at 2008-01-07T16:12:00+00:00 Update docs to say that Haddock accets .lhs files and module names - - - - - 4b5ce824 by David Waern at 2008-01-07T16:12:25+00:00 Document -B option - - - - - 47274262 by David Waern at 2008-01-07T16:23:07+00:00 Update CHANGES - - - - - 7ff314a9 by David Waern at 2008-01-07T16:23:20+00:00 Remove --use-package, --package & --no-implicit.. flags from docs - - - - - 6c3819c0 by David Waern at 2008-01-07T16:23:52+00:00 Remove --no-implicit-prelide flag - - - - - 1b14ae40 by David Waern at 2008-01-07T16:32:26+00:00 Update the "Using literate or pre-processed source" section - - - - - 0117f620 by David Waern at 2008-01-07T16:41:55+00:00 Document the --optghc flag - - - - - 087ab1cf by David Waern at 2008-01-07T16:42:10+00:00 Remove the documenation section on derived instances The problem mentioned there doesn't exist in Haddock 2.0.0.0 - - - - - 7253951e by David Waern at 2008-01-07T16:48:40+00:00 Document OPTIONS_HADDOCK - - - - - 3b6bdcf6 by David Waern at 2008-01-07T16:56:54+00:00 Wibble - - - - - 3025adf9 by David Waern at 2008-01-07T17:08:14+00:00 Wibble - - - - - 5f30f1a0 by David Waern at 2008-01-07T17:15:44+00:00 Change synopsis field to description - - - - - 1673f54b by David Waern at 2008-01-07T17:18:21+00:00 Change my email address in the cabal file - - - - - 55aa9808 by David Waern at 2008-01-07T18:18:02+00:00 Add documentation for readInterfaceFile - - - - - eaea417f by David Waern at 2008-01-07T18:21:30+00:00 Export necessary stuff from Distribution.Haddock - - - - - 7ea18759 by David Waern at 2008-01-07T18:31:49+00:00 Remove dep on Cabal - - - - - 7b79c74e by David Waern at 2008-01-07T18:33:49+00:00 Remove dep on process - - - - - ce3054e6 by David Waern at 2008-01-16T23:01:21+00:00 Add feature-requsts from Henning Thielemann to TODO - - - - - 0c08f1ec by David Waern at 2008-01-16T23:03:02+00:00 Record a bug in TODO - - - - - b04605f3 by David Waern at 2008-01-23T16:59:06+00:00 Add a bug reported by Ross to TODO - - - - - 5b17c030 by David Waern at 2008-01-23T18:05:53+00:00 A a bug report to TODO - - - - - 1c993b0d by David Waern at 2008-01-25T16:30:25+00:00 Accept test output - - - - - c22fc0d0 by David Waern at 2008-01-25T16:34:49+00:00 Accept test output - - - - - 4b795811 by David Waern at 2008-01-25T16:38:37+00:00 Change Hidden.hs (test) to use OPTIONS_HADDOCK - - - - - c124dbd9 by David Waern at 2008-01-25T16:39:23+00:00 Accept test output - - - - - ec6f6eea by David Waern at 2008-01-25T16:42:08+00:00 Add Hidden.html.ref to tests - - - - - 1dc9610c by David Waern at 2008-02-02T20:50:51+00:00 Add a comment about UNPACK bug in TODO - - - - - 2d3f7081 by David Waern at 2008-02-09T22:33:24+00:00 Change the representation of DocNames Ross Paterson reported a bug where links would point to the defining module instead of the "best" module for an identifier (e.g Int pointing to GHC.Base instead of Data.Int). This patch fixes this problem by refactoring the way renamed names are represented. Instead of representing them by: > data DocName = Link Name | NoLink Name they are now represented as such: > data DocName = Documented Name Module | Undocumented Name and the the link-env looks like this: > type LinkEnv = Map Name Module There are several reasons for this. First of all, the bug was caused by changing the module part of Names during the renaming process, without changing the Unique field. This caused names to be overwritten during the loading of .haddock files (which caches names using the NameCache of the GHC session). So we might create new Uniques during renaming to fix this (but I'm not sure that would be problem-free). Instead, we just keep the Name and add the Module where the name is best documented, since it can be useful to keep the original Name around (for e.g. source-code location info and for users of the Haddock API). Also, the names Link/NoLink don't really make sense, since wether to use links or not is entirely up to the users of DocName. In the process of following this change into H.Backends.Html I removed the assumption that binder names are Undocumented (which was just an unnecessary assumption, the OccName is the only thing needed to render these). This will probably make it possible to get rid of the renamer and replace it with a traversal from SYB or Uniplate. Since DocName has changed, InterfaceFile has changed so this patch also increments the file-format version. No backwards-compatibility is implemented. - - - - - 0f28c921 by David Waern at 2008-02-09T23:00:36+00:00 H.GHC.Utils: remove unused imports/exports - - - - - 0c44cad5 by David Waern at 2008-02-10T00:28:13+00:00 H.GHC.Utils: add some functions that were removed by mistake - - - - - e3452f49 by David Waern at 2008-02-10T00:28:48+00:00 Fix some trivial warnings in H.InterfaceFile - - - - - a6d74644 by David Waern at 2008-02-10T00:48:06+00:00 Update the version message to fit in small terminals - - - - - 76c9cd3e by David Waern at 2008-02-10T14:47:39+00:00 Remove bugs from TODO that don't apply anymore since the port - - - - - 5e10e090 by David Waern at 2008-02-10T15:22:47+00:00 Remove bugs from TODO that weren't actual bugs - - - - - fef70878 by David Waern at 2008-02-10T15:23:44+00:00 Remove yet another item from TODO that was not an actual bug - - - - - e1af47b8 by David Waern at 2008-02-11T10:25:57+00:00 Bump the version number to 2.1.0 Since the exported datatype DocName has changed, we need to bump the major version number. Let's also drop the fourth version component, it's not that useful. - - - - - e3be7825 by David Waern at 2008-04-11T14:29:04+00:00 Add a bug to TODO - - - - - cb6574be by David Waern at 2008-04-11T16:00:45+00:00 Use the in-place haddock when running tests - - - - - c6d7af0d by David Waern at 2008-04-11T16:09:16+00:00 Turn off GHC warnings when running tests - - - - - 7f61b546 by David Waern at 2008-04-11T17:24:00+00:00 Add a flag for turning off all warnings - - - - - 883b8422 by David Waern at 2008-04-12T14:02:18+00:00 Fix printing of data binders - - - - - 2a0db8fc by David Waern at 2008-04-12T18:52:46+00:00 Fix missing parenthesis in constructor args bug - - - - - 1b3ac3f9 by David Waern at 2008-04-12T18:57:23+00:00 Simplify test suite and add tests I move all tests into one single directory to simplify things, and add a test for the last bug that was fixed. - - - - - 8f178376 by David Waern at 2008-04-12T19:00:15+00:00 Add a script for copying test output to "expected" output - - - - - 193e3a03 by David Waern at 2008-04-12T19:16:37+00:00 Remove two fixed bugs from TODO - - - - - ddc9130c by David Waern at 2008-04-12T19:37:06+00:00 Update test README - - - - - 956069c0 by David Waern at 2008-05-01T12:16:14+00:00 Update version number in spec and docs - - - - - 5478621c by David Waern at 2008-05-01T12:28:12+00:00 Remove claim of backwards compatibility from docs for readInterfaceFile - - - - - 4a16dea9 by David Waern at 2008-05-01T12:33:04+00:00 Update CHANGES - - - - - 804216fb by David Waern at 2008-05-01T12:43:16+00:00 Add a synopsis - - - - - fd0c84d5 by David Waern at 2008-05-01T12:44:44+00:00 Add Haddock.DocName to the cabal file - - - - - 9f4a7439 by David Waern at 2008-05-01T12:45:53+00:00 Remove -fglasgow-exts and -fasm - - - - - aee7c145 by David Waern at 2008-05-01T12:54:01+00:00 Add LANGUAGE pragmas to source files - - - - - 9a58428b by David Waern at 2008-05-01T12:54:19+00:00 Add extensions to cabal file - - - - - 494f1bee by David Waern at 2008-05-01T13:12:09+00:00 Export DocName in the API - - - - - c938196b by David Waern at 2008-05-01T13:12:19+00:00 Add hide options to some source files - - - - - 236e86af by Neil Mitchell at 2008-06-07T20:45:10+00:00 Rewrite the --hoogle flag support - - - - - 6d910950 by Neil Mitchell at 2008-06-14T10:56:50+00:00 Simplify the newtype/data outputting in Hoogle, as haddock does it automatically - - - - - f87a95a8 by Neil Mitchell at 2008-06-14T12:10:18+00:00 Add initial structure for outputting documentation as well, but does not yet output anything - - - - - 7c3bce54 by Neil Mitchell at 2008-06-14T12:27:07+00:00 Remove <document comment> from the Hoogle output - - - - - 9504a325 by Neil Mitchell at 2008-06-16T06:33:21+00:00 Default to "main" if there is no package, otherwise will clobber hoogle's hoogle info - - - - - 4a794a79 by Neil Mitchell at 2008-06-16T06:53:29+00:00 Change packageName to packageStr, as it better reflects the information stored in it - - - - - 7abc9baf by Neil Mitchell at 2008-06-16T07:09:49+00:00 Add modulePkgInfo to Haddock.GHC.Utils, which gives back package name and version info - - - - - 8ca11514 by Neil Mitchell at 2008-06-16T07:13:48+00:00 Change Hoogle to take the package name and package version separately - - - - - a6da452d by Neil Mitchell at 2008-06-18T11:29:46+00:00 In Hoogle do not list things that are not local to this module - - - - - 974b76b7 by David Waern at 2008-06-19T18:40:13+00:00 Be more consistent with GHC API naming in H.GHC.Utils - - - - - 2facb4eb by David Waern at 2008-06-19T19:03:03+00:00 Update test output - - - - - c501de72 by David Waern at 2008-06-26T20:26:49+00:00 Use ghc-paths to get the lib dir The path can still be overridden using the -B flag. It's not longer required to pass the lib dir to the program that runs the test suite. - - - - - ac4c6836 by David Waern at 2008-06-26T20:33:08+00:00 Update CHANGES - - - - - 9d21c60a by David Waern at 2008-06-26T20:34:53+00:00 Update README - - - - - 741448f0 by David Waern at 2008-06-26T21:12:57+00:00 Improve wording in the help message - - - - - b1b42b11 by David Waern at 2008-06-30T10:16:17+00:00 Rename ForeignType - - - - - 6d6c2b34 by David Waern at 2008-06-30T10:25:09+00:00 Rename TyFamily - - - - - 8d1125ed by David Waern at 2008-06-30T10:37:21+00:00 Rename type patterns - - - - - 7610a4cb by David Waern at 2008-06-30T10:45:07+00:00 Rename associated types - - - - - 8eeba14c by David Waern at 2008-06-30T10:47:41+00:00 Remove the TODO file now that we have a trac - - - - - 1af5b25b by David Waern at 2008-07-02T18:19:28+00:00 Render type family declarations (untested) - - - - - ceb99797 by David Waern at 2008-07-02T18:24:06+00:00 Remove redundant check for summary when rendering data types - - - - - b36a58e0 by David Waern at 2008-07-02T22:01:38+00:00 More support for type families and associated types Now we just need to render the instances - - - - - 78784879 by David Waern at 2008-07-07T22:13:58+00:00 Remove filtering of instances We were filtering out all instances for types with unknown names. This was probably an attempt to filter out instances for internal types. I am removing the filtering for the moment, and will try to fix this properly later. - - - - - 3e758dad by David Waern at 2008-06-30T18:50:30+00:00 Run haddock in-place during testing - - - - - d9dab0ce by David Waern at 2008-07-08T21:04:32+00:00 Remove index.html and doc-index.html from output, they should not be versioned - - - - - 3e6c4681 by David Waern at 2008-07-08T21:06:42+00:00 Update test output following change to instance filtering - - - - - e34a3f14 by David Waern at 2008-07-12T16:48:28+00:00 Stop using the map from exported names to declarations During creation of the interface, we were using two maps: one from exported names to declarations, and one from all defined names in the module to declarations. The first contained subordinate names while the second one didn't. The first map was never used to look up names not defined in the associated module, so if we add subordinate names to the second map, we could use it everywhere. That's that this patch does. This simplifies code because we don't have to pass around two maps everywhere. We now store the map from locally defined things in the interface structure instead of the one from exported names. - - - - - 2e1d2766 by David Waern at 2008-07-12T16:55:21+00:00 Get the all locally defined names from GHC API We previously had some code to compute all locally defined names in a module including subordinate names. We don't need it since we can get the names from modInfoTyThings in the GHC API. - - - - - bf637994 by David Waern at 2008-07-13T13:09:16+00:00 Refactoring in H.Interface.Create We were creating a doc map, a declaration map and a list of entities separately by going through the HsGroup. These structures were all used to build the interface of a module. Instead of doing this, we can start by creating a list of declarations from the HsGroup, then collect the docs directly from this list (instead of using the list of entities), creating a documentation map. We no longer need the Entity data type, and we can store a single map from names to declarations and docs in the interface, instead of the declaration map and the doc map. This way, there is only one place where we filter out the declarations that we don't want, and we can remove a lot of code. Another advantage of this is that we can create the exports directly out of the list of declarations when we export the full module contents. (Previously we did a look up for each name to find the declarations). This is faster and removes another point where we depend on names to identify exported declarations, which is good because it eliminates problems with instances (which don't have names). - - - - - 547e410e by David Waern at 2008-07-13T13:34:51+00:00 Remove FastString import and FSLIT macro in H.I.Create -- they were unused - - - - - 693759d1 by David Waern at 2008-07-13T13:36:23+00:00 Remove unused import from H.I.Create - - - - - cde6e7fb by David Waern at 2008-07-13T13:51:54+00:00 Small touches - - - - - 96de8f1d by David Waern at 2008-07-20T11:21:46+00:00 Preparation for rendering instances as separate declarations We want to be able to render instances as separate declarations. So we remove the Name argument of ExportDecl, since instances are nameless. This patch also contains the first steps needed to gather type family instances and display them in the backend, but the implementation is far from complete. Because of this, we don't actually show the instances yet. - - - - - b0f824fb by David Waern at 2008-07-20T15:53:08+00:00 Follow changes to ExportDecl in Hoogle - - - - - 1192eff3 by Neil Mitchell at 2008-06-26T00:28:10+00:00 Change how the Hoogle backend outputs classes, adding the context in - - - - - 7a0d1464 by Neil Mitchell at 2008-06-26T00:28:46+00:00 Remove the indent utility function from Hoogle backend - - - - - 3361241b by Neil Mitchell at 2008-06-26T09:45:09+00:00 Add support for Hoogle writing ForeignImport/ForeignExport properly - - - - - 795ad3bf by Neil Mitchell at 2008-06-26T12:15:25+00:00 Flesh out the Hoogle code to render documentation - - - - - 23277995 by Neil Mitchell at 2008-06-26T14:56:41+00:00 Fix a bug in the Hoogle backend, unordered lists were being written out <ul>...</u> - - - - - db739b27 by Neil Mitchell at 2008-06-26T15:09:54+00:00 Remove any white space around a <li> element - - - - - f2e6bb8c by Neil Mitchell at 2008-07-10T15:30:47+00:00 Remove the TODO in the Hoogle HTML generation, was already done - - - - - 693ec9a3 by Neil Mitchell at 2008-07-10T15:53:00+00:00 Put brackets round operators in more places in the Hoogle output - - - - - 842313aa by Neil Mitchell at 2008-07-10T16:01:25+00:00 Print type signatures with brackets around the name - - - - - cf93deb0 by David Waern at 2008-07-20T17:04:22+00:00 Bump version number to 2.2.0 - - - - - 30e6a8d1 by David Waern at 2008-07-20T17:04:41+00:00 Resolve conflicts in H.B.Hoogle - - - - - 1f0071c9 by David Waern at 2008-07-23T23:05:01+00:00 Add "all" command to runtests.hs that runs all tests despite failures - - - - - f2723023 by David Waern at 2008-07-23T23:08:39+00:00 Update tests/README - - - - - c0304a11 by David Waern at 2008-07-23T23:21:15+00:00 Be compatible with GHC 6.8.3 The cabal file is converted to use the "new" syntax with explicit Library and Executable sections. We define the __GHC_PATCHLEVEL__ symbol using a conditinal cpp-options field in the cabal file. (Ideally, Cabal would define the symbol for us, like it does for __GLASGOW_HASKELL__). We use these symbols to #ifdef around a small difference between 6.8.2 and 6.8.3. Previously, we only supported GHC 6.8.2 officially but the dependencies field said "ghc <= 6.9". This was just for convenience when testing against the (then compatible) HEAD version of GHC, and was left in the release by mistake. Now, we support both GHC 6.8.2 and 6.8.3 and the dependencies field correctly reflects this. - - - - - 88a5fe71 by David Waern at 2008-07-23T23:54:16+00:00 Depend on the currently available ghc-paths versions only - - - - - 8738d97b by David Waern at 2008-07-24T10:50:44+00:00 FIX haskell/haddock#44: Propagate parenthesis level when printing documented types - - - - - 05339119 by David Waern at 2008-07-24T16:06:18+00:00 Drop unnecessary parenthesis in types, put in by the user We were putting in parenthesis were the user did. Let's remove this since it just clutters up the types. The types are readable anyway since we print parens around infix operators and do not rely on fixity levels. When doing this I discovered that we were relying on user parenthesis when printin types like (a `O` b) c. This patchs fixes this problem so that parenthesis are always inserted around an infix op application in case it is applied to further arguments, or if it's an arguments to a type constructor. Tests are updated. - - - - - b3a99828 by David Waern at 2008-07-24T10:19:43+00:00 Print parenthesis around non-atomic banged types Fixes half of haskell/haddock#44 - - - - - ab5238e0 by David Waern at 2008-07-24T22:07:49+00:00 Add a reference file for the TypeFamilies test - - - - - 1941cc11 by David Waern at 2008-07-25T17:15:53+00:00 Simplify definition of pretty and trace_ppr - - - - - e3bfa33c by David Waern at 2008-07-25T17:18:27+00:00 Warning messages Output a warning when filtering out data/type instances and associated types in instances. We don't show these in the documentation yet, and we need to let the user know. - - - - - 9b85fc89 by David Waern at 2008-07-25T17:45:40+00:00 Doc: Mention Hoogle in the Introduction - - - - - afb2dd60 by David Waern at 2008-07-25T17:49:00+00:00 Doc: update -B description - - - - - 584c0c91 by David Waern at 2008-07-25T18:11:38+00:00 Doc: describe -w flag - - - - - 77619c24 by David Waern at 2008-07-28T12:29:07+00:00 Remove TODO from cabal file - - - - - 96717d5f by David Waern at 2008-07-28T12:29:27+00:00 Support type equality predicates - - - - - c2fd2330 by David Waern at 2008-07-29T19:45:14+00:00 Move unL from H.B.Hoogle to H.GHC.Utils I like Neil's shorter unL better than unLoc from the GHC API. - - - - - c4c3bf6a by David Waern at 2008-07-29T19:47:36+00:00 Do not export ATs when not in list of subitems - - - - - bf9a7b85 by David Waern at 2008-08-03T11:42:59+00:00 Filter out ForeignExports - - - - - df59fcb0 by David Waern at 2008-08-03T14:02:51+00:00 Filter out more declarations The previous refactorings in H.I.Create introduced a few bugs. Filtering of some types of declarations that we don't handle was removed. This patch fixes this. - - - - - 2f8a958b by David Waern at 2008-08-03T15:24:07+00:00 Move reL to H.GHC.Utils so we can use it everywhere - - - - - 8ec15efd by David Waern at 2008-08-03T15:25:00+00:00 Use isVanillaLSig from GHC API instead of home brewn function - - - - - 300f93a2 by David Waern at 2008-08-03T15:25:27+00:00 Filter out separately exported ATs This is a quick and dirty hack to get rid of separately exported ATs. We haven't decided how to handle them yet. No warning message is given. - - - - - 8776d1ec by David Waern at 2008-08-03T16:21:21+00:00 Filter out more declarations and keep only vanilla type sigs in classes - - - - - ea07eada by David Waern at 2008-08-03T16:48:00+00:00 Fix layout - - - - - dd5e8199 by David Waern at 2008-08-03T16:50:52+00:00 Move some utility functions from H.I.Create to H.GHC.Utils - - - - - 4a1dbd72 by David Waern at 2008-08-03T17:39:55+00:00 Do not filter out doc declarations - - - - - 0bc8dca4 by David Waern at 2008-08-03T17:47:26+00:00 Filter out separately exported ATs (take two) - - - - - af970fe8 by David Waern at 2008-08-03T22:39:17+00:00 Update CHANGES - - - - - 5436ad24 by David Waern at 2008-08-03T22:40:20+00:00 Bump version number to 2.2.1 - - - - - d66de448 by David Waern at 2008-08-05T19:00:32+00:00 Remove version restriction on ghc-paths - - - - - 534b1364 by David Waern at 2008-08-05T19:04:35+00:00 Bump version to 2.2.2 and update CHANGES - - - - - 549188ff by David Waern at 2008-08-05T19:16:49+00:00 Fix CHANGES - - - - - 0d156bb4 by Luke Plant at 2008-08-11T15:20:59+00:00 invoking haddock clarification and help - - - - - 748295cc by David Waern at 2008-08-11T18:56:37+00:00 Doc: say that the --hoogle option is functional - - - - - 43301db4 by David Waern at 2008-08-05T19:26:08+00:00 Change ghc version dependency to >= 6.8.2 - - - - - 3e5a53b6 by David Waern at 2008-08-10T22:42:05+00:00 Make H.GHC.Utils build with GHC HEAD - - - - - 7568ace0 by David Waern at 2008-08-11T19:41:54+00:00 Import Control.OldException instead of C.Exception when using ghc >= 6.9 We should really test for base version instead, but I don't currently know which version to test for. - - - - - b71ae991 by David Waern at 2008-08-12T22:40:39+00:00 Make our .haddock file version number depend on the GHC version We need to do this, since our .haddock format can potentially change whenever GHC's version changes (even when only the patchlevel changes). - - - - - 6307ce3f by David Waern at 2008-08-12T22:49:57+00:00 Remove matching on NoteTy in AttachInstances, it has been removed - - - - - 2dbcfd5f by David Waern at 2008-08-12T23:02:02+00:00 Comment out H.GHC.loadPackages - it is unused and doesn't build with ghc >= 6.9 - - - - - c74db5c2 by David Waern at 2008-08-12T23:03:58+00:00 Hide <.> from GHC import in Hoogle only for ghc <= 6.8.3 - - - - - 69a44ebb by David Waern at 2008-08-12T23:11:12+00:00 Follow changes to parseDynamic/StaticFlags - - - - - 5881f3f0 by David Waern at 2008-08-13T21:43:58+00:00 Add __GHC_PATCHLEVEL__ symbol also when building the library - - - - - 8574dc11 by David Waern at 2008-08-13T21:44:17+00:00 Follow move of package string functions from PackageConfig to Module - - - - - c9baa77f by David Waern at 2008-08-13T21:45:29+00:00 Follow extensible exceptions changes - - - - - 9092de15 by David Waern at 2008-08-13T21:46:20+00:00 Update test following Haddock version change - - - - - ebe569a4 by David Waern at 2008-08-13T21:46:54+00:00 Follow changes to parseDynamic- parseStaticFlags in GHC - - - - - b8a5ffd3 by David Waern at 2008-08-13T21:47:36+00:00 Follow changes to Binary in GHC 6.9 - - - - - edfda1cc by David Waern at 2008-08-13T21:50:17+00:00 Change ghc version dependency to >= 6.8.2 && <= 6.9 - - - - - d59be1cf by Neil Mitchell at 2008-08-12T16:02:53+00:00 Output all items, even if they are not defined in this module - ensures map comes from Prelude, not just GHC.Base - - - - - dda93b9f by Neil Mitchell at 2008-08-12T21:37:32+00:00 Add support for type synonyms to Hoogle, was accidentally missing before (woops!) - - - - - b6ee795c by Neil Mitchell at 2008-08-13T14:03:24+00:00 Generalise Hoogle.doc and add a docWith - - - - - 415e1bb2 by Neil Mitchell at 2008-08-13T14:03:46+00:00 Make Hoogle add documentation to a package - - - - - 790a1202 by Neil Mitchell at 2008-08-18T12:52:43+00:00 Use the same method to put out signatures as class methods in the Hoogle backend - - - - - ded37eba by Neil Mitchell at 2008-08-18T12:53:04+00:00 Remove Explicit top-level forall's when pretty-printing signatures - - - - - 6468c722 by Neil Mitchell at 2008-08-20T07:59:13+00:00 Simplify the code by removing not-to-important use of <.> in the Hoogle back end - - - - - 788c3a8b by Neil Mitchell at 2008-08-21T18:20:24+00:00 In the hoogle back end, markup definition lists using <i>, not <b> - - - - - 77d4b000 by Ian Lynagh at 2008-08-14T10:49:14+00:00 Add a Makefile for GHC's build system. Still won't work yet, but we're closer - - - - - 920440d7 by Ian Lynagh at 2008-08-27T18:06:46+00:00 Add haddock.wrapper - - - - - bcda925f by Ian Lynagh at 2008-08-27T18:07:02+00:00 Add a manual Cabal flag to control the ghc-paths dependency - - - - - 04d194e2 by Ian Lynagh at 2008-08-27T20:41:27+00:00 Update extensions in Cabal file Use ScopedTypeVariables instead of PatternSignatures - - - - - 12480043 by Ian Lynagh at 2008-08-27T20:41:55+00:00 Increase the upper bound on the GHC version number - - - - - b1f809a5 by Ian Lynagh at 2008-08-27T21:32:22+00:00 Fix some warnings - - - - - aea0453d by Ian Lynagh at 2008-08-28T14:22:29+00:00 Fixes for using haddock in a GHC build tree - - - - - ad23bf86 by Ian Lynagh at 2008-08-28T21:14:27+00:00 Don't use Cabal wrappers on Windows - - - - - 35858e4c by Ian Lynagh at 2008-08-29T00:07:42+00:00 Fix in-tree haddock on Windows - - - - - c2642066 by Ian Lynagh at 2008-09-03T22:35:53+00:00 follow library changes - - - - - 2eb55d50 by Ian Lynagh at 2008-09-07T18:52:51+00:00 bindist fixes - - - - - 3daa5b59 by Ian Lynagh at 2008-09-10T16:58:18+00:00 We need to tell haddock that its datasubdir is . or it can't find package.conf - - - - - 388fd8c2 by Ian Lynagh at 2008-09-10T19:47:44+00:00 Fix haddock inplace on Windows - - - - - 70a641c1 by Ian Lynagh at 2008-09-10T22:15:44+00:00 Fix installed haddock on Windows - - - - - 83c1e997 by Neil Mitchell at 2008-09-11T10:48:55+00:00 Import GHC.Paths if not IN_GHC_TREE, seems to match the use of GHC.Paths functions much better - - - - - b452519b by Ian Lynagh at 2008-09-12T12:58:24+00:00 Add a LANGUAGE ForeignFunctionInterface pragma - - - - - afbd592c by Ian Lynagh at 2008-09-12T12:59:13+00:00 Wibble imports - - - - - 547ac4ad by Ian Lynagh at 2008-09-14T15:34:22+00:00 Add a "#!/bin/sh" to haddock.wrapper - - - - - f207a807 by Ian Lynagh at 2008-09-15T10:02:32+00:00 Use "exec" when calling haddock in the wrapper - - - - - 2ee68509 by Thomas Schilling at 2008-09-15T09:09:16+00:00 Port Haddock.Interface to new GHC API. This required one bigger change: 'readInterfaceFile' used to take an optional 'Session' argument. This was used to optionally update the name cache of an existing GHC session. This does not work with the new GHC API, because an active session requires the function to return a 'GhcMonad' action, but this is not possible if no session is provided. The solution is to use an argument of functions for reading and updating the name cache and to make the function work for any monad that embeds IO, so it's result type can adapt to the calling context. While refactoring, I tried to make the code a little more self-documenting, mostly turning comments into function names. - - - - - 3bb96431 by Thomas Schilling at 2008-09-15T09:09:37+00:00 Reflect GHC API changes. - - - - - 2e60f714 by Thomas Schilling at 2008-09-15T09:10:37+00:00 Port Haddock.GHC.Typecheck to new GHC API. - - - - - 9cfd4cff by Thomas Schilling at 2008-09-15T09:11:00+00:00 Port Haddock.GHC to new GHC API. - - - - - caffa003 by Thomas Schilling at 2008-09-15T09:11:25+00:00 Port Main to new GHC API. - - - - - 069a4608 by Ian Lynagh at 2008-09-21T11:19:00+00:00 Fix paths used on Windows frmo a GHC tree: There is no whare directory - - - - - 7ceee1f7 by Ian Lynagh at 2008-09-21T12:20:16+00:00 Fix the in-tree haddock on Windows - - - - - 0d486514 by Ian Lynagh at 2008-09-23T18:06:58+00:00 Increase the GHC upper bound from 6.11 to 6.13 - - - - - f092c414 by Neil Mitchell at 2008-09-11T14:56:07+00:00 Do not wrap __ in brackets - - - - - 036bdd13 by Ian Lynagh at 2008-09-28T01:42:35+00:00 Fix building haddock when GhcProfiled=YES - - - - - 01434a89 by David Waern at 2008-09-24T20:24:21+00:00 Add PatternSignatures LANGUAGE pragma to Main and Utils - - - - - 1671a750 by David Waern at 2008-10-02T22:57:25+00:00 For source links, get original module from declaration name instead of environment. Getting it from the environment must have been a remnant from the times when we were using unqualified names (versions 0.x). - - - - - a25dde99 by David Waern at 2008-10-02T22:59:57+00:00 Remove ifaceEnv from Interface - it's no longer used - - - - - 610993da by David Waern at 2008-10-02T23:04:58+00:00 Write a comment about source links for type instance declarations - - - - - 5a96b5d5 by Thomas Schilling at 2008-10-03T10:45:08+00:00 Follow GHC API change of parseModule. - - - - - 5a943ae5 by Ian Lynagh at 2008-10-03T15:56:58+00:00 TAG 2008-10-03 - - - - - 76cdd6ae by Thomas Schilling at 2008-10-08T12:29:50+00:00 Only load modules once when typechecking with GHC. This still doesn't fix the memory leak since the typechecked source is retained and then processed separately. To fix the leak, modules must be processed directly after typechecking. - - - - - 7074d251 by David Waern at 2008-10-09T23:53:54+00:00 Interleave typechecking with interface creation At the same time, we fix a bug where the list of interfaces were processed in the wrong order, when building the links and renaming the interfaces. - - - - - 4b9b2b2d by David Waern at 2008-10-09T23:54:49+00:00 Add some strictness annotations in Interface We add some strictness annotations to the fields of Interface, so that less GHC data is hold on to during processing. - - - - - 22035628 by David Waern at 2008-10-10T20:02:31+00:00 Remove typecheckFiles and MonadUtils import from H.GHC.Typeccheck - - - - - be637ad3 by David Waern at 2008-10-10T20:33:38+00:00 Make Haddock build with GHC 6.8.2 - - - - - 523b3404 by David Waern at 2008-10-10T21:08:09+00:00 Fix documentation for createInterfaces - - - - - e1556702 by David Waern at 2008-10-10T21:26:19+00:00 Hide H.Utils in library - - - - - a8e751c3 by David Waern at 2008-10-10T21:34:59+00:00 Add back .haddock file versioning based on GHC version It was accidentally removed in the patch for GHC 6.8.2 compatibility - - - - - 06fb3c01 by David Waern at 2008-10-10T21:47:15+00:00 Bump version number to 2.3.0 - - - - - ff087fce by David Waern at 2008-10-10T22:35:49+00:00 Add support for DocPic The support for DocPic was merged into the GHC source long ago, but the support in Haddock was forgotten. Thanks Peter Gavin for submitting this fix! - - - - - 3af85bf6 by David Waern at 2008-10-10T23:34:05+00:00 Update tests - - - - - 0966873c by Simon Marlow at 2008-10-10T14:43:04+00:00 no need for handleErrMsg now, we don't throw any ErrMsgs - - - - - f1870de3 by Clemens Fruhwirth at 2008-10-10T13:29:36+00:00 Compile with wrapper but remove it for dist-install - - - - - 7b440dc2 by David Waern at 2008-10-11T14:02:25+00:00 Remove interface from LinksInfo It was there to know the documentation home module when creating a wiki link, but we already know this since we have the DocName. - - - - - e5729e6a by David Waern at 2008-10-15T20:49:18+00:00 Wibble - - - - - b2a8e01a by David Waern at 2008-10-15T21:03:36+00:00 Use type synonyms for declarations and docs in H.I.Create - - - - - be71a15b by David Waern at 2008-10-15T21:12:17+00:00 Comment out unused type family stuff completely - - - - - 91aaf075 by David Waern at 2008-10-15T21:49:04+00:00 Wibble - - - - - 42ba4eb4 by David Waern at 2008-10-15T21:53:53+00:00 Move convenient type synonym to H.Types - - - - - db11b723 by David Waern at 2008-10-15T22:14:07+00:00 Add DeclInfo to H.Types - - - - - 193552b6 by David Waern at 2008-10-15T22:15:01+00:00 Add subordinates with docs to the declaration map The only place in the code where we want the subordinates for a declaration is right after having looked up the declaration in the map. And since we include subordinates in the map, we might as well take the opportunity to store those subordinates that belong to a particular declaration together with that declaration. We also store the documentation for each subordinate. - - - - - 31e6eebc by David Waern at 2008-10-16T17:18:47+00:00 Wibble - - - - - 0dcbd79f by David Waern at 2008-10-16T20:58:42+00:00 Fix haskell/haddock#61 We were not getting docs for re-exported class methods. This was because we were looking up the docs in a map made from the declarations in the current module being rendered. Obviously, re-exported class methods come from another module. Class methods and ATs were the only thing we were looking up using the doc map, everything else we found in the ExporItems. So now I've put subordinate docs in the ExportItem's directly, to make things a bit more consistent. To do this, I added subordinates to the the declarations in the declaration map. This was easy since we were computing subordinates anyway, to store stand-alone in the map. I added a new type synonym 'DeclInfo', which is what we call what is now stored in the map. This little refactoring removes duplicate code to retrieve subordinates and documentation from the HsGroup. - - - - - de47f20a by David Waern at 2008-10-16T22:06:35+00:00 Document function and improve its layout - - - - - e74e625a by Thomas Schilling at 2008-10-20T11:12:57+00:00 Force interface more aggressively. For running Haddock on GHC this reduces memory usage by about 50 MB on a 32 bit system. A heap profile shows total memory usage peak at about 100 MB, but actual usage is at around 300 MB even with compacting GC (+RTS -c). - - - - - b63ac9a1 by David Waern at 2008-10-20T20:25:50+00:00 Make renamer consistent Instead of explicitly making some binders Undocumented, treat all names the same way (that is, try to find a Documented name). - - - - - f6de0bb0 by Ian Lynagh at 2008-09-19T00:54:43+00:00 TAG GHC 6.10 fork - - - - - 74599cd0 by David Waern at 2008-10-20T21:13:24+00:00 Do not save hidden modules in the .haddock file We were saving interfaces of all processed modules including those hidden using {-# OPTIONS_HADDOCK hide #-} in the .haddock file. This caused broken links when generating the index for the libraries that come with GHC. This patch excludes modules with hidden documentation when writing .haddock files. It should fix the above problem. - - - - - 7b6742e9 by David Waern at 2008-10-21T19:54:52+00:00 Do not save hidden modules in the .haddock file (also for ghc >= 6.9) When writing the first patch, I forgot to do the fix in both branches of an #if macro. - - - - - b99b1951 by David Waern at 2008-10-22T20:04:18+00:00 Remove subordinate map and its usage It is not needed now that we store subordinate names in the DeclInfo map. - - - - - da97cddc by David Waern at 2008-10-22T20:11:46+00:00 Tidy up code in H.I.Create a little Remove commented out half-done type instance support, and remove DeclWithDoc synonym. - - - - - 6afa76f3 by David Waern at 2008-10-22T21:17:29+00:00 Fix warnings in H.GHC.Utils - - - - - 171ea1e8 by David Waern at 2008-10-22T21:35:04+00:00 Fix warnings in H.Utils - - - - - c8cb3b91 by David Waern at 2008-10-22T21:36:49+00:00 Wibble - - - - - 767fa06a by David Waern at 2008-10-27T19:59:04+00:00 Make named doc comments into ExportDoc instead of ExportDecl Fixes a crash when processing modules without export lists containing named docs. - - - - - e638bbc6 by David Waern at 2008-11-02T22:21:10+00:00 Add HCAR entry - - - - - 92b4ffcf by David Waern at 2008-11-02T22:44:19+00:00 Update CHANGES - - - - - 84d4da6e by David Waern at 2008-11-03T11:25:04+00:00 Add failing test for template haskell crash - - - - - 2a9cd2b1 by David Waern at 2008-11-04T21:13:44+00:00 Add tests/TH.hs - - - - - 8a59348e by David Waern at 2008-11-04T21:30:26+00:00 TAG 2.3.0 - - - - - 54f70d31 by Thomas Schilling at 2008-10-24T17:04:08+00:00 Enable framed view of the HTML documentation. This patch introduces: - A page that displays the documentation in a framed view. The left side will show a full module index. Clicking a module name will show it in the right frame. If Javascript is enabled, the left side is split again to show the modules at the top and a very short synopsis for the module currently displayed on the right. - Code to generate the mini-synopsis for each module and the mini module index ("index-frames.html"). - CSS rules for the mini-synopsis. - A very small amount of javascript to update the mini-synopsis (but only if inside a frame.) Some perhaps controversial things: - Sharing code was very difficult, so there is a small amount of code duplication. - The amount of generated pages has been doubled, since every module now also gets a mini-synopsis. The overhead should not be too much, but I haven't checked. Alternatively, the mini-synopsis could also be generated using Javascript if we properly annotate the actual synopsis. - - - - - 5d7ea5a6 by David Waern at 2008-11-04T23:20:17+00:00 Follow change to ExportDecl in frames code - - - - - 60e16308 by David Waern at 2008-11-04T23:35:26+00:00 Update CHANGES - - - - - d63fd26d by David Waern at 2008-11-04T23:37:43+00:00 Bump version number - - - - - c1660c39 by David Waern at 2008-11-04T23:44:46+00:00 Update CHANGES - - - - - 995ab384 by David Waern at 2008-11-04T23:55:21+00:00 Remove .ref files from tests/output/ - - - - - 1abbbe75 by David Waern at 2008-11-04T23:57:41+00:00 Output version info before running tests - - - - - 649b182f by David Waern at 2008-11-05T22:45:37+00:00 Add ANNOUNCE message - - - - - c36ae0bb by David Waern at 2008-11-05T23:15:35+00:00 Update ANNOUNCE - - - - - 9c4f3d40 by David Waern at 2008-11-05T23:18:30+00:00 Wibble - - - - - 5aac87ce by David Waern at 2008-11-06T21:07:48+00:00 Depend on base 4.* when using GHC >= 6.9, otherwise 3.* - - - - - b9796a74 by David Waern at 2008-11-06T21:13:40+00:00 Bump version to 2.4.1 and update CHANGES - - - - - d4b26baa by David Waern at 2008-11-06T21:26:33+00:00 Depend on base 4.0.* instead of 4.* - - - - - 2cb0903c by David Waern at 2008-11-06T21:46:53+00:00 Fix warnings in H.B.HH and H.B.HH2 - - - - - e568e89a by David Waern at 2008-11-06T21:47:12+00:00 Fix warnings in Haddock.ModuleTree - - - - - 9dc14fbd by David Waern at 2008-11-06T21:47:52+00:00 Fix warnings in Haddock.Version - - - - - 02ac197c by David Waern at 2008-11-06T21:51:31+00:00 Fix warnings in H.InterfaceFile and H.Options - - - - - 63e7439a by David Waern at 2008-11-06T21:59:45+00:00 Fix warnings in H.GHC.Typecheck - - - - - 4bca5b68 by David Waern at 2008-11-08T13:43:42+00:00 Set HscTarget to HscNothing instead of HscAsm There used to be a bug in the GHC API that prevented us from setting this value. - - - - - 07357aec by David Waern at 2008-11-09T22:27:00+00:00 Re-export NameCache and friends from Distribution.Haddock - - - - - ea554b5a by David Waern at 2008-11-09T23:14:10+00:00 Add Haddock.GHC.Utils to other-modules in library - - - - - 74aecfd7 by David Waern at 2008-11-10T01:18:57+00:00 Export DocName in the library - - - - - 241a58b3 by David Waern at 2008-11-10T01:19:18+00:00 Document the functions in H.DocName - - - - - edc2ef1b by David Waern at 2008-11-10T01:20:52+00:00 Export H.DocName in the library - - - - - 4f588d55 by David Waern at 2008-11-10T01:29:14+00:00 Make DocName an instance of NamedThing - - - - - b4647244 by David Waern at 2008-11-15T22:58:18+00:00 Reflect version bump in test suite - - - - - 4bee8ce2 by David Waern at 2008-11-15T22:58:45+00:00 Update tests For unknown reasons, test output for Bug1 and Test has changed for the better. - - - - - 1690e2f9 by David Waern at 2008-11-15T22:59:33+00:00 Store hidden modules in .haddock files We store documentation for an entity in the 'InstalledInterface' of the definition site module, and never in the same structure for a module which re-exports the entity. So when a client of the Haddock library wants to look up some documentation, he/she might need to access a hidden module. But we currently don't store hidden modules in the .haddock files. So we add the hidden modules and the Haddock options to the .haddock files. The options will be used to filter the module list to obtain the visible modules only, which is necessary for generating the contents and index for installed packages. - - - - - 8add6435 by David Waern at 2008-11-16T14:35:50+00:00 Bump major version number due to .haddock file format change - - - - - 48bfcf82 by David Waern at 2008-11-23T14:32:52+00:00 Update tests to account for version number bump - - - - - 0bbd1738 by David Waern at 2008-11-23T14:33:31+00:00 HADDOCK_DATA_DIR changed to haddock_datadir - - - - - 5088b78c by David Waern at 2008-11-23T17:13:21+00:00 FIX haskell/haddock#45: generate two anchors for each name We generate two anchor tags for each name, one where we don't escape the name and one where we URI-encode it. This is for compatibility between IE and Opera. Test output is updated. - - - - - 5ee5ca3b by Neil Mitchell at 2008-11-27T14:38:11+00:00 Drop HsDocTy annotations, they mess up pretty printing and also have a bracketing bug (#2584) - - - - - 51c014e9 by Roman Cheplyaka at 2008-11-27T22:27:36+00:00 Allow referring to a specific section within a module in a module link Fixes haskell/haddock#65 - - - - - 4094bdc5 by David Waern at 2008-11-28T21:13:33+00:00 Update tests following anchor change - - - - - f89552dd by Thomas Schilling at 2008-11-29T16:16:20+00:00 Haddock really shouldn't try to overwrite files. - - - - - 98127499 by David Waern at 2008-12-07T14:09:15+00:00 Solve conflict - - - - - 319356c5 by David Waern at 2008-10-22T21:16:55+00:00 Add -Wall -Werror to ghc-options - - - - - 3c4968c9 by David Waern at 2008-11-04T23:38:56+00:00 TAG 2.4.0 - - - - - 4b21e003 by David Waern at 2008-11-06T21:14:04+00:00 TAG 2.4.1 - - - - - 8e0cad5c by David Waern at 2008-12-07T14:12:54+00:00 Remove -Werror - - - - - 299d6deb by David Waern at 2008-12-07T14:25:18+00:00 Remove -Wall, we'll focus on warnings after 6.10.2 is out - - - - - 5f4216b6 by David Waern at 2008-12-07T20:58:05+00:00 Resolve conflict properly - - - - - 67d774e7 by Neil Mitchell at 2008-12-15T11:44:26+00:00 Make forall's in constructors explicit, i.e. data Foo = Foo {foo :: Eq a => a} - - - - - 61851792 by Neil Mitchell at 2008-12-18T15:39:39+00:00 Try and find a better package name than "main" for Hoogle, goes wrong when working on an executable rather than a library - - - - - 2fab8554 by David Waern at 2008-12-08T23:19:48+00:00 Make visible names from ExportItems Instead of a complicated calculation of visible names out of GHC's export items, we can get them straight out of the already calculated ExportItems. The ExportItems should represent exactly those items that are visible in an interface. If store all the exported sub-names in ExportDecl instead of only those with documentation, the calculation becomes very simple. So we do this change as well (should perhaps have been a separate patch). This should fix the problem with names from ghc-prim not appearing in the link environment. - - - - - 7caadd8c by Ian Lynagh at 2008-12-11T17:01:04+00:00 Wrap the GHC usage with defaultCleanupHandler This fixes a bug where haddock leaves /tmp/ghc* directories uncleaned. - - - - - 7c9fc9a5 by David Waern at 2009-01-02T21:38:27+00:00 Show re-exported names from external packages again This fixes GHC ticket 2746. In order to also link to the exported subordinate names of a declaration, we need to re-introduce the sub map in the .haddock files. - - - - - 119e4e05 by David Waern at 2009-01-06T23:34:17+00:00 Do not process boot modules We should of course not try to produce documentation for boot modules! The reason this has worked in the past is that the output of "real" modules overwrites the output of boot modules later in the process. However, this causes a subtle link environment problem. So let's get rid of this stupid behaviour. We avoid processing boot modules, but we continue to typecheck them. - - - - - c285b9d2 by David Waern at 2009-01-08T18:03:36+00:00 Export modules also when coming from external packages This seems to have regressed since a refactoring that was part of the 2.3.0 release. - - - - - 24031c17 by David Waern at 2009-01-10T15:26:26+00:00 Change version to 2.4.2 - no need to go to 2.5.0 - - - - - 864d1c3f by David Waern at 2009-01-10T15:35:20+00:00 Update tests to account for version number change - - - - - 524ba886 by David Waern at 2009-01-10T18:29:17+00:00 Add test for Template Haskell splicing - - - - - 05e6e003 by David Waern at 2009-01-10T19:35:42+00:00 Fix Trac haskell/haddock#68: Turn on compilation via C for Template Haskell packages We can't use HscNothing if we need to run code coming from modules inside the processed package during typechecking, which is the case for some packages using Template Haskell. This could be improved, to e.g. use HscInterpreted and HscNothing where possible, instead of using HscC for all modules in the package. - - - - - 2b2bafa1 by David Waern at 2009-01-10T20:22:25+00:00 Only use needsTemplateHaskell when compiling with GHC 6.10.2 or above - - - - - bedc3a93 by Ian Lynagh at 2009-01-11T14:58:41+00:00 Fix the location of INPLACE_PKG_CONF; fixes the build Spotted by Conal Elliott - - - - - 943107c8 by David Waern at 2009-01-20T19:27:39+00:00 Document H.I.Create.collectDocs better - - - - - c6252e37 by David Waern at 2009-01-20T19:29:51+00:00 Fix Trac haskell/haddock#59: TH-generated declarations disappearing This patch was contributed by Joachim Breitner (nomeata). - - - - - 3568a6af by David Waern at 2009-01-21T21:41:48+00:00 Do not indicate that a constructor argument is unboxed We only show the strictness annotation for an unboxed constructor argument. The fact that it is unboxed is an implementation detail and should not be part of the module interface. - - - - - 562a4523 by David Waern at 2009-01-22T18:53:49+00:00 Fix Trac haskell/haddock#50: do not attach docs to pragmas or other kinds of non-declarations We now filter out everything that is not a proper Haskell declaration before collecting the docs and attaching them to declarations. - - - - - 6fdf21c2 by David Waern at 2009-01-22T19:48:09+00:00 Add test for quasi quotation. No reference output yet. - - - - - dc4100fd by David Waern at 2009-01-22T19:57:47+00:00 Improve quasi-quotation test and add reference output - - - - - 908b74bb by David Waern at 2009-01-23T23:22:03+00:00 Filter out separately exported associated types in a smarter way - - - - - f6b42ecb by David Waern at 2009-01-24T16:54:39+00:00 Correct spelling mistake in error message - - - - - 24e4245d by David Waern at 2009-01-24T17:48:03+00:00 Correct comment - - - - - b5e8462f by David Waern at 2009-02-07T13:22:29+00:00 Do not show a subordinate at the top level if its parent is also exported See note in the source code for more info. - - - - - 4b09de57 by David Waern at 2009-02-07T13:53:53+00:00 Update test following change to top level subordinates - - - - - 76379896 by David Waern at 2009-02-07T13:58:04+00:00 Remove html files in the tests/output/ directory which have been accidentally added - - - - - 1a6d8b10 by Joachim Breitner at 2009-02-20T10:29:43+00:00 Typo in comment - - - - - fec367d0 by David Waern at 2009-02-24T20:21:17+00:00 Fix small bug The rule is to prefer type constructors to other things when an identifier in a doc string can refer to multiple things. This stopped working with newer GHC versions (due to a tiny change in the GHC renamer). We implement this rule in the HTML backend for now, instead of fixing it in GHC, since we will move renaming of doc strings to Haddock in the future anyway. - - - - - 9b4172eb by David Waern at 2009-02-25T20:04:38+00:00 Fix bad error handling with newer GHCs When support for GHC 6.10 was added, an error handler was installed only around the typechecking phase. This had the effect that errors thrown during dependency chasing were caught in the top-level exception handler and not printed with enough detail. With this patch we wrap the error handler around all our usage of the Ghc monad. - - - - - de2df363 by Simon Peyton Jones at 2009-02-02T16:47:42+00:00 Hide funTyConName, now exported by TypeRep - - - - - 4d40a29f by Ian Lynagh at 2009-02-12T18:57:49+00:00 Don't build the library when building in the GHC tree - - - - - 1cd0abe4 by Ian Lynagh at 2009-02-13T13:58:53+00:00 Add a ghc.mk - - - - - 3d814eeb by Ian Lynagh at 2009-02-13T18:50:28+00:00 do .depend generation for haddock with the stage1 compiler This is a bit of a hack. We mkdepend with stage1 as if .depend depends on the stage2 compiler then make goes wrong: haddock's .depend gets included, which means that make won't reload until it's built, but we can't build it without the stage2 compiler. We therefore build the stage2 compiler before its .depend file is available, and so compilation fails. - - - - - b55036a4 by Ian Lynagh at 2009-02-25T01:38:13+00:00 Give haddock a wrapper on unix in the new GHC build system - - - - - 9eabfe68 by Ian Lynagh at 2009-02-25T19:21:32+00:00 Create inplace/lib/html in the new GHC build system - - - - - 93af30c7 by Ian Lynagh at 2008-11-07T19:18:23+00:00 TAG GHC 6.10.1 release - - - - - 06e6e34a by Thomas Schilling at 2009-02-24T18:11:00+00:00 Define __GHC_PATCHLEVEL__ for recent version of GHC (stable). - - - - - 680e6ed8 by Thomas Schilling at 2009-02-24T18:12:26+00:00 'needsTemplateHaskell' is not defined in current stable GHC. - - - - - 6c5619df by David Waern at 2009-02-25T22:15:23+00:00 Hide fynTyConName only for recent GHC versions - - - - - 6b2344f1 by Ian Lynagh at 2009-02-26T00:49:56+00:00 Add the module to one of haddocks warnings - - - - - e5d11c70 by David Waern at 2009-02-27T21:37:20+00:00 Bug fix We tried to filter out subordinates that were already exported through their parent. This didn't work properly since we were in some cases looking at the grand-parent and not the parent. We now properly compute all the parent-child relations of a declaration, and use this information to get the parent of a subordinate. We also didn't consider record fields with multiple parents. This is now handled correctly. We don't currently support separately exported associated types. But when we do, they should be handled correctly by this process too. Also slightly improved the warning message that we give when filtering out subordinates. - - - - - 10a79a60 by David Waern at 2009-02-27T22:08:08+00:00 Fix error message conflict The module name is already written in the beginning of the message, as seems to be the convention in Haddock. Perhaps not so clear, but we should change it everywhere in that case. Leaving it as it is for now. - - - - - c5055c7f by David Waern at 2009-02-27T22:15:17+00:00 Shorten warning message - - - - - a72fed3a by David Waern at 2009-02-28T00:53:55+00:00 Do not show package name in warning message - - - - - a5daccb2 by Ian Lynagh at 2009-03-01T14:59:35+00:00 Install haddock in the new GHC build system - - - - - dfdb025c by Ian Lynagh at 2009-03-07T23:56:29+00:00 Relax base dependency to < 4.2, not < 4.1 - - - - - 5769c8b4 by David Waern at 2009-03-21T14:58:52+00:00 Bump .haddock file version number (due to change of format) - - - - - f1b8f67b by David Waern at 2009-03-21T14:59:26+00:00 Define __GHC_PATCHLEVEL__=1 when using ghc-6.10.1 - - - - - 23f78831 by David Waern at 2009-03-21T16:40:52+00:00 Update CHANGES - - - - - 7d2735e9 by David Waern at 2009-03-21T16:50:33+00:00 Update ANNOUNCE - - - - - 0771e00a by David Waern at 2009-03-21T16:54:40+00:00 Update ANNOUNCE, again - - - - - 81a6942a by David Waern at 2009-03-21T17:50:06+00:00 Don't be too verbose in CHANGES - - - - - 29861dcf by David Waern at 2009-03-21T18:03:31+00:00 TAG 2.4.2 - - - - - a585f285 by David Waern at 2009-03-21T19:20:29+00:00 Require Cabal >= 1.2.3 - - - - - 7c611662 by David Waern at 2009-03-21T19:21:48+00:00 TAG 2.4.2 with cabal-version >= 1.2.3 - - - - - 23b7deff by Simon Marlow at 2009-03-20T15:43:42+00:00 new GHC build system: use shell-wrappers macro - - - - - 25f8afe7 by Ian Lynagh at 2009-03-21T19:13:53+00:00 Fix (with a hack?) haddock in teh new build system - - - - - 6a29a37e by David Waern at 2009-03-24T22:10:15+00:00 Remove unnecessary LANGUAGE pragma - - - - - 954da57d by David Waern at 2009-03-24T22:21:23+00:00 Fix warnings in H.B.DevHelp - - - - - 1619f1df by David Waern at 2009-03-26T23:20:44+00:00 -Wall police in H.B.Html - - - - - b211e13b by Simon Marlow at 2009-03-24T13:00:56+00:00 install Haddock's html stuff - - - - - 78e0b107 by David Waern at 2008-12-07T19:58:53+00:00 Add verbosity flag and utils, remove "verbose" flag - - - - - 913dae06 by David Waern at 2008-12-07T20:01:05+00:00 Add some basic "verbose" mode logging in H.Interface - - - - - 1cbff3bf by David Waern at 2009-03-27T00:07:26+00:00 Fix conflicts - - - - - 22f82032 by David Waern at 2009-03-27T21:15:11+00:00 Remove H.GHC.Typecheck - - - - - 81557804 by David Waern at 2009-03-27T21:19:22+00:00 Remove docNameOrig and use getName everywhere instead - - - - - d8267213 by David Waern at 2009-03-27T21:21:46+00:00 Use docNameOcc instead of nameOccName . getName - - - - - 5d55deab by David Waern at 2009-03-27T21:33:04+00:00 Remove H.DocName and put DocName in H.Types - - - - - 8ba72611 by David Waern at 2009-03-27T22:06:26+00:00 Document DocName - - - - - 605f8ca5 by David Waern at 2009-03-27T22:45:21+00:00 -Wall police - - - - - e4da93ae by David Waern at 2009-03-27T23:12:53+00:00 -Wall police in H.B.Hoogle - - - - - bb255519 by David Waern at 2009-03-27T23:41:28+00:00 Define Foldable and Traversable instances for Located - - - - - f1195cfe by David Waern at 2009-03-27T23:51:34+00:00 Wibble - - - - - 23818d7c by David Waern at 2009-03-28T00:03:55+00:00 -Wall police in H.I.Rename - - - - - 0f050d67 by David Waern at 2009-03-28T00:15:15+00:00 -Wall police in H.I.AttachInstances - - - - - 0f3fe038 by David Waern at 2009-03-28T21:09:41+00:00 Wibble - - - - - 275d4865 by David Waern at 2009-03-28T21:27:06+00:00 Layout fix - - - - - 54ff0ef8 by David Waern at 2009-03-28T21:59:07+00:00 -Wall police in H.I.Create - - - - - 7f58b117 by David Waern at 2009-03-28T22:10:19+00:00 -Wall police in H.Interface - - - - - f0c03b44 by David Waern at 2009-03-28T22:22:59+00:00 -Wall police in Main - - - - - 29da355c by David Waern at 2009-03-28T22:23:39+00:00 Turn on -Wall -Werror - - - - - 446d3060 by David Waern at 2009-04-01T20:40:30+00:00 hlint police - - - - - 3867c9fc by David Waern at 2009-04-01T20:48:42+00:00 hlint police - - - - - bd1f1600 by David Waern at 2009-04-01T20:58:02+00:00 hlint police - - - - - e0e90866 by David Waern at 2009-04-05T12:42:53+00:00 Move H.GHC.Utils to H.GhcUtils - - - - - 9cbd426b by David Waern at 2009-04-05T12:57:21+00:00 Remove Haddock.GHC and move its (small) contents to Main - - - - - b5c2cbfd by David Waern at 2009-04-05T13:07:04+00:00 Fix whitespace and stylistic issues in Main - - - - - 3c04aa56 by porges at 2008-12-07T08:22:19+00:00 add unicode output - - - - - 607918da by David Waern at 2009-04-26T15:09:43+00:00 Resolve conflict - - - - - 4bec6b6b by Simon Marlow at 2009-05-13T10:00:31+00:00 fix markup - - - - - 436ad6f4 by Simon Marlow at 2009-03-23T11:54:45+00:00 clean up - - - - - bdcd1398 by Simon Marlow at 2009-03-24T10:36:45+00:00 new GHC build system: add $(exeext) - - - - - 9c0972f3 by Simon Marlow at 2009-03-24T11:04:31+00:00 update for new GHC build system layout - - - - - d0f3f83a by Ian Lynagh at 2009-03-29T15:31:43+00:00 GHC new build system fixes - - - - - 5a8245c2 by Ian Lynagh at 2009-04-04T20:44:23+00:00 Tweak new build system - - - - - 9c6f2d7b by Simon Marlow at 2009-05-13T10:01:27+00:00 add build instructions for GHC - - - - - 66d07c76 by Ian Lynagh at 2009-05-31T00:37:53+00:00 Quote program paths in ghc.mk - - - - - bb7de2cd by Ian Lynagh at 2009-06-03T22:57:55+00:00 Use a bang pattern on an unlifted binding - - - - - 3ad283fc by Ian Lynagh at 2009-06-13T16:17:50+00:00 Include haddock in GHC bindists - - - - - ac447ff4 by David Waern at 2009-06-24T21:07:50+00:00 Delete Haddock.Exception and move contents to Haddock.Types Only a few lines of code that mainly declares a type - why not just put it in Haddock.Types. - - - - - 4464fb9b by David Waern at 2009-06-24T22:23:23+00:00 Add Haddock module headers Add a proper Haddock module header to each module, with a more finegrained copyright. If you feel mis-accreditted, please correct any copyright notice! The maintainer field is set to haddock at projects.haskell.org. Next step is to add a brief description to each module. - - - - - 5f4c95dd by David Waern at 2009-06-24T22:39:44+00:00 Fix spelling error - - - - - 6d074cdb by David Waern at 2009-06-25T21:53:56+00:00 Document Interface and InstalledInterface better - - - - - d0cbd183 by David Waern at 2009-06-27T12:46:46+00:00 Remove misplaced whitespace in H.I.Rename - - - - - fa381c49 by David Waern at 2009-06-27T13:26:03+00:00 Fix haskell/haddock#104 - create output directory if missing - - - - - 91fb77ae by Ian Lynagh at 2009-06-25T15:59:50+00:00 TAG 2009-06-25 - - - - - 0d853f40 by Simon Peyton Jones at 2009-07-02T15:35:22+00:00 Follow extra field in ConDecl - - - - - b201735d by Ian Lynagh at 2009-07-05T16:50:35+00:00 Update Makefile for the new GHC build system - - - - - df6c0092 by Ian Lynagh at 2009-07-05T17:01:13+00:00 Resolve conflicts - - - - - 1066870a by Ian Lynagh at 2009-07-05T17:01:48+00:00 Remove the -Wwarn hack in the GHC build system - - - - - 7e856076 by Ian Lynagh at 2009-07-05T17:17:59+00:00 Fix warnings - - - - - 5d4cd958 by Ian Lynagh at 2009-07-05T19:35:40+00:00 Bump version number Cabal needs to distinguish between haddocks having a --verbose and --verbosity flag - - - - - 6ee07c99 by David Waern at 2009-07-06T20:14:57+00:00 Wibble - - - - - 2308b66f by David Waern at 2009-07-06T20:24:20+00:00 Clearer printing of versions by runtests.hs - - - - - d4b5d9ab by David Waern at 2009-07-06T21:22:42+00:00 Fix (invisible) bug introduced by unicode patch - - - - - 2caca8d8 by David Waern at 2009-07-06T21:44:10+00:00 Use HscAsm instead of HscC when using TH - - - - - 18f3b755 by David Waern at 2009-07-06T22:10:22+00:00 Update HCAR entry (by Janis) - - - - - a72ac9db by David Waern at 2009-07-06T23:01:35+00:00 Follow HsRecTy change with an #if __GLASGOW_HASKEL__ >= 611 - - - - - 549135d2 by David Waern at 2009-07-06T23:11:41+00:00 Remove unused functions from Haddock.Utils - - - - - b450134a by Isaac Dupree at 2009-07-11T14:59:00+00:00 revert to split-index for large indices - remove the search-box, because browsers have search-for-text abilities anyway. - pick 150 items in index as the arbitrary time at which to split it - notice the bug that identifiers starting with non-ASCII characters won't be listed in split-index, but don't bother to fix it yet (see ticket haskell/haddock#116, http://trac.haskell.org/haddock/ticket/116 ) - - - - - 78a5661e by Isaac Dupree at 2009-07-20T15:37:18+00:00 Implement GADT records in HTML backend - - - - - 4e163555 by Isaac Dupree at 2009-07-21T22:03:25+00:00 add test for GADT records - - - - - 79aa4d6e by David Waern at 2009-07-23T20:40:37+00:00 Update test suite following version bump - - - - - 5932c011 by David Waern at 2009-08-02T10:25:39+00:00 Fix documentation bug - - - - - a6970fca by David Waern at 2009-08-12T23:08:53+00:00 Remove support for ghc 6.8.* from .cabal file - - - - - c1695902 by Ian Lynagh at 2009-07-07T13:35:45+00:00 Fix unused import warnings - - - - - fb6df7f9 by Ian Lynagh at 2009-07-16T00:20:31+00:00 Use cProjectVersion directly rather than going through compilerInfo Fixes the build after changes in GHC - - - - - 548cdd66 by Simon Marlow at 2009-07-28T14:27:04+00:00 follow changes in GHC's ForeignType - - - - - 9395aaa0 by David Waern at 2009-08-13T22:17:33+00:00 Switch from PatternSignatures to ScopedTypeVariables in Main - - - - - eebf39bd by David Waern at 2009-08-14T17:14:28+00:00 Version .haddock files made with GHC 6.10.3/4 correclty - - - - - 58f3e735 by David Waern at 2009-08-14T17:19:37+00:00 Support GHC 6.10.* and 6.11.* only - - - - - 5f63cecc by David Waern at 2009-08-14T22:03:20+00:00 Do not version .haddock file based on GHC patchlevel version We require that the instances of Binary that we use from GHC will not change between patchlevel versions. - - - - - d519de9f by David Waern at 2009-08-14T23:50:00+00:00 Update CHANGES - - - - - 35dccf5c by David Waern at 2009-08-14T23:51:38+00:00 Update version number everywhere - - - - - 6d363fea by David Waern at 2009-08-15T09:46:49+00:00 Update ANNOUNCE - - - - - c7ee6bc2 by David Waern at 2009-08-15T09:47:13+00:00 Remove -Werror Forgot that Hackage doesn't like it. - - - - - a125c12b by David Waern at 2009-08-15T09:49:50+00:00 Require Cabal >= 1.6 - - - - - adb2f560 by Isaac Dupree at 2009-08-12T03:47:14+00:00 Cross-Package Documentation version 4 - - - - - 3d6dc04d by David Waern at 2009-08-15T23:42:57+00:00 Put all the IN_GHC_TREE stuff inside getGhcLibDir - - - - - 56624097 by David Waern at 2009-08-15T23:52:03+00:00 Add --print-ghc-libdir - - - - - f15d3ccb by David Waern at 2009-08-16T00:37:52+00:00 Read base.haddock when running tests We can now test cross-package docs. - - - - - 283f0fb9 by David Waern at 2009-08-16T00:50:59+00:00 Update test output - we now have more links - - - - - 673d1004 by David Waern at 2009-08-16T01:26:08+00:00 Read process.haddock when running tests - - - - - 0d127f82 by David Waern at 2009-08-16T01:43:04+00:00 Add a test for cross-package documentation - - - - - f94db967 by Ian Lynagh at 2009-08-16T18:42:44+00:00 Follow GHC build system changes - - - - - 5151278a by Isaac Dupree at 2009-08-16T19:58:05+00:00 make cross-package list types look nicer - - - - - c41e8228 by Isaac Dupree at 2009-08-18T01:47:47+00:00 Haddock.Convert: export more functions This lets us remove some code in Haddock.Interface.AttachInstances - - - - - 2e5fa398 by Isaac Dupree at 2009-08-18T02:11:05+00:00 switch AttachInstances to use synify code It changed an instance from showing ((,) a b) to (a, b) because my synify code is more sophisticated; I hope the latter is a good thing rather than a bad thing aesthetically, here. But this definitely reduces code duplication! - - - - - b8b07123 by Isaac Dupree at 2009-08-18T02:23:31+00:00 Find instances using GHC, which is more complete. In particular, it works cross-package. An intermediate patch also moved the instance-finding into createInterface, but that move turned out not to be necessary, so if we want to do that, it'd go in a separate patch. (Is that possible? Or will we need GHC to have loaded all the modules first, before we can go searching for the instances (e.g. if the modules are recursive or something)?) - - - - - 6959b451 by Isaac Dupree at 2009-08-17T00:37:18+00:00 fix preprocessor conditional sense - - - - - 942823af by Isaac Dupree at 2009-08-16T22:46:48+00:00 remove ghc 6.8 conditionals from Haddock.Interface - - - - - 4b3ad888 by Isaac Dupree at 2009-08-18T20:24:38+00:00 Fix GHC 6.11 build in Haddock.Convert - - - - - 0a89c5ab by Isaac Dupree at 2009-08-23T00:08:58+00:00 hacks to make it compile without fnArgDocsn - - - - - 7b3bed43 by Isaac Dupree at 2009-08-23T03:01:28+00:00 less big-Map-based proper extraction of constructor subdocs - - - - - b21c279a by Isaac Dupree at 2009-08-23T03:02:06+00:00 Html: remove unnecessary+troublesome GHC. qualifications - - - - - 96c97115 by Isaac Dupree at 2009-08-23T03:08:03+00:00 Move doc parsing/lexing into Haddock for ghc>=6.11 - - - - - e1cec02d by Isaac Dupree at 2009-08-23T05:08:14+00:00 get rid of unused DocMap parameter in Html - - - - - 66960c59 by Isaac Dupree at 2009-08-23T05:54:20+00:00 fix horrible named-docs-disappearing bug :-) - - - - - a9d7eff3 by Isaac Dupree at 2009-08-23T06:26:36+00:00 re-implement function-argument docs ..on top of the lexParseRn work. This patch doesn't change the InstalledInterface format, and thus, it does not work cross-package, but that will be easy to add subsequently. - - - - - 8bf6852c by Isaac Dupree at 2009-08-23T07:26:05+00:00 cross-package fnArgDocs. WARNING: changes .haddock binary format While breaking the format, I took the opportunity to unrename the DocMap that's saved to disk, because there's really no reason that we want to know what *another* package's favorite place to link a Name to was. (Is that true? Or might we want to know, someday?) Also, I added instance Binary Map in InterfaceFile. It makes the code a little simpler without changing anything of substance. Also it lets us add another Map hidden inside another Map (fnArgsDocs in instDocMap) without having really-convoluted serialization code. Instances are neat! I don't understand why this change to InterfaceFile seemed to subtly break binary compatibility all by itself, but no matter, I'll just roll it into the greater format-changing patch. Done! - - - - - 30115a64 by Isaac Dupree at 2009-08-23T18:22:47+00:00 Improve behavior for unfindable .haddock - - - - - aa364bda by Isaac Dupree at 2009-08-23T18:28:16+00:00 add comment for FnArgsDoc type - - - - - 49b23a99 by Isaac Dupree at 2009-08-23T21:52:48+00:00 bugfix: restore fnArgDocs for type-synonyms - - - - - f65f9467 by Isaac Dupree at 2009-08-23T22:06:55+00:00 Backends.Hoogle: eliminate warnings - - - - - a292d216 by Isaac Dupree at 2009-08-23T22:10:24+00:00 Haddock.Convert: eliminate warnings - - - - - 5546cd20 by Isaac Dupree at 2009-08-23T22:12:31+00:00 Haddock.Interface.Rename: eliminate warnings - - - - - 0a9798b6 by Isaac Dupree at 2009-08-23T22:18:47+00:00 Main.hs: remove ghc<6.9 conditionals - - - - - e8f9867f by Isaac Dupree at 2009-08-23T22:27:46+00:00 Main.hs: eliminate warnings (except for OldException) - - - - - 61c64247 by Isaac Dupree at 2009-08-23T22:41:01+00:00 move get*LibDir code in Main.hs, to +consistent code, -duplication - - - - - 948f1e69 by Isaac Dupree at 2009-08-23T23:14:26+00:00 Main.hs: OldException->Exception: which eliminates warnings - - - - - 3d5d5e03 by Isaac Dupree at 2009-08-23T23:20:11+00:00 GhcUtils: ghc >= 6.10 - - - - - 2771d657 by Isaac Dupree at 2009-08-23T23:21:55+00:00 InterfaceFile: ghc >= 6.10 - - - - - d9f2b9d1 by Isaac Dupree at 2009-08-23T23:22:58+00:00 Types: ghc >= 6.10 - - - - - ca39210e by Isaac Dupree at 2009-08-23T23:23:26+00:00 ModuleTree: ghc >= 6.10 - - - - - 883c4e59 by Isaac Dupree at 2009-08-23T23:24:04+00:00 Backends.DevHelp: ghc >= 6.10 - - - - - 04667df5 by Isaac Dupree at 2009-08-23T23:24:37+00:00 Backends.Html: ghc >= 6.10 - - - - - a9f7f25f by Isaac Dupree at 2009-08-23T23:25:24+00:00 Utils: ghc >= 6.10 - - - - - b7105022 by Isaac Dupree at 2009-08-23T23:37:47+00:00 eliminate haskell98 dependency, following GHC's example It turns out I/we already had, and it was only a matter of deleting it from the cabal file. - - - - - 292e0911 by Isaac Dupree at 2009-08-24T01:22:44+00:00 refactor out subordinatesWithNoDocs dep of inferenced-decls fix - - - - - c2ed46a2 by Isaac Dupree at 2009-08-24T01:24:03+00:00 Eradicate wrong runtime warning for type-inferenced exported-functions see the long comment in the patch for why I did it this way :-) - - - - - 4ac0b57c by David Waern at 2009-09-04T22:56:20+00:00 Clean up tyThingToHsSynSig a little Factor out noLoc and use the case construct. Also rename the function to tyThingToLHsDecl, since it doesn't just create type signatures. - - - - - 28ab9201 by David Waern at 2009-09-04T22:58:50+00:00 Wibble - - - - - 0d9fe6d0 by David Waern at 2009-09-06T18:39:30+00:00 Add more copyright owners to H.I.AttachInstances - - - - - 122441b1 by David Waern at 2009-09-06T18:44:12+00:00 Style police - - - - - 1fa79463 by David Waern at 2009-09-06T18:57:45+00:00 Move toHsInstHead to Haddock.Convert and call it synifyInstHead - - - - - 0d42a8aa by David Waern at 2009-09-06T21:11:38+00:00 Use colordiff to display test results if available - - - - - ea9d8e03 by Simon Marlow at 2009-08-24T08:46:14+00:00 Follow changes in GHC's interface file format Word32 instead of Int for FastString and Name offsets - - - - - 537e051e by Simon Marlow at 2009-07-29T14:16:53+00:00 define unpackPackageId (it was removed from GHC) - - - - - 50c63aa7 by David Waern at 2009-09-09T23:18:03+00:00 Remove commented-out code - - - - - 511631fe by David Waern at 2009-09-09T23:19:05+00:00 Correct copyright in H.I.ParseModuleHeader - - - - - 898ec768 by David Waern at 2009-09-11T11:22:29+00:00 Use Map.fromList/toList intead of fromAscList/toAscList when serializing Maps This fixes the missing docs problem. The Eq and Ord instances for Name uses the unique number in Name. This number is created at deserialization time by GHC's magic Binary instance for Name, and it is random. Thus, fromAscList can't be used at deserialization time, even though toAscList was used at serialization time. - - - - - 37bec0d5 by Simon Peyton Jones at 2009-09-11T08:28:04+00:00 Track change in HsType - - - - - eb3a97c3 by Ian Lynagh at 2009-09-11T16:07:09+00:00 Allow building with base 4.2 - - - - - bb4205ed by Ian Lynagh at 2009-09-22T13:50:02+00:00 Loosen the GHC dependency - - - - - 5c75deb2 by Ian Lynagh at 2009-09-22T14:08:39+00:00 Fix building with GHC >= 6.12 - - - - - fb131481 by David Waern at 2009-09-11T11:24:48+00:00 Update runtests.hs to work with GHC 6.11 - - - - - ac3a419d by David Waern at 2009-09-11T11:25:14+00:00 Update CrossPackageDocs test - - - - - ec65c3c6 by David Waern at 2009-09-11T11:25:40+00:00 Add reference output for CrossPackageDocs - - - - - 520c2758 by Ian Lynagh at 2009-10-25T17:26:40+00:00 Fix installation in the GHC build system - - - - - 28b3d7df by Ian Lynagh at 2009-11-05T15:57:27+00:00 GHC build system: Make *nix installation work in paths containing spaces - - - - - 5c9bb541 by David Waern at 2009-11-14T11:56:39+00:00 Track change in HsType for the right compiler version - - - - - 905097ce by David Waern at 2009-11-14T12:10:47+00:00 hlint police - - - - - 04920630 by Ian Lynagh at 2009-11-20T13:46:30+00:00 Use defaultObjectTarget rather than HscAsm This fixes haddock when we don't have a native code generator - - - - - 966eb079 by David Waern at 2009-11-15T12:32:21+00:00 Remove commented-out code - - - - - 37f00fc4 by David Waern at 2009-11-22T13:58:48+00:00 Make runtests.hs strip links before diffing Generates easier to read diffs when tests fail. The content of the links is not important anyway since it is not taken into account by the tests. - - - - - 3a9bb8ef by David Waern at 2009-11-22T14:05:06+00:00 Follow findProgramOnPath signature change in runtests.hs - - - - - b26b9e5a by David Waern at 2009-11-22T14:08:40+00:00 Follow removal of GHC.MVar from base in CrossPackageDocs - - - - - f4d90ae4 by David Waern at 2009-11-22T14:48:47+00:00 Make copy.hs strip link contents before copying No more updating of reference files when URLs in links changes. - - - - - 4c9c420d by David Waern at 2009-11-22T15:26:41+00:00 Update test reference output * More links (Int, Float etc) * Stripped link contents - - - - - a62b80e3 by David Waern at 2009-11-23T23:19:39+00:00 Update CrossPackageDocs reference output - Remove GHC.MVar import (removed from base) - Strip link contents - - - - - 43491394 by David Waern at 2009-11-23T23:20:00+00:00 Update test reference files with comments on instances - - - - - 0d370a0b by David Waern at 2009-11-23T23:25:16+00:00 Bump version number - - - - - 2293113e by David Waern at 2009-11-24T20:55:49+00:00 Comments on instances Implementing this was a little trickier than I thought, since we need to match up instances from the renamed syntax with instances represented by InstEnv.Instance. This is due to the current design of Haddock, which matches comments with declarations from the renamed syntax, while getting the list of instances of a class/family directly using the GHC API. - Works for class instances only (Haddock has no support for type family instances yet) - The comments are rendered to the right of the instance head in the HTML output - No change to the .haddock file format - Works for normal user-written instances only. No comments are added on derived or TH-generated instances - - - - - bf586f29 by David Waern at 2009-11-27T22:05:15+00:00 Whitespace police - - - - - b8f03afa by David Waern at 2009-11-27T22:11:46+00:00 Remove bad whitespace and commented-out pieces - - - - - 90b8ee90 by David Waern at 2009-11-27T22:15:04+00:00 Whitespace police - - - - - b5ede900 by David Waern at 2009-11-27T22:15:50+00:00 Whitespace police - - - - - e3fddbfe by David Waern at 2009-11-28T13:37:59+00:00 Remove Name from DocInstance It's not used. - - - - - 9502786c by David Waern at 2009-11-28T13:56:54+00:00 Require at least GHC 6.12 While regression testing Haddock, I found a bug that happens with GHC 6.10.3, but not with GHC 6.12-rc2 (haven't tried 6.10.4). I don't have time to track it down. I think we should just always require the latest major GHC version. The time spent on making Haddock work with older versions is too high compared to the time spent on bugfixing, refactoring and features. - - - - - 8fa688d8 by David Waern at 2009-11-28T15:05:03+00:00 Remove cruft due to compatibility with older GHCs - - - - - 46fbbe9d by David Waern at 2009-11-28T15:07:50+00:00 Add a documentation header to Haddock.Convert - - - - - c3d2cc4a by David Waern at 2009-11-28T15:10:14+00:00 Remove unused H.Utils.FastMutInt2 - - - - - 490aba80 by David Waern at 2009-11-28T15:36:36+00:00 Rename Distribution.Haddock into Documentation.Haddock - - - - - 33ee2397 by David Waern at 2009-11-28T15:36:47+00:00 Fix error message - - - - - a5a3b950 by David Waern at 2009-11-28T16:58:39+00:00 Add a test flag that brings in QuickCheck - - - - - fa049e13 by David Waern at 2009-11-28T19:32:18+00:00 Say that we want quickcheck 2 - - - - - f32b0d9b by David Waern at 2009-11-28T19:32:40+00:00 Add an Arbitrary instance for HsDoc - - - - - da9a8bd7 by David Waern at 2009-11-28T20:15:30+00:00 Rename HsDoc back into Doc - - - - - edb60101 by David Waern at 2009-11-28T22:16:16+00:00 Move H.Interface.Parse/Lex to H.Parse/Lex These are not just used to build Interfaces. - - - - - 0656a9b8 by David Waern at 2009-11-28T23:12:14+00:00 Update version number in test suite - - - - - 5e8c6f4a by David Waern at 2009-12-21T14:12:41+00:00 Improve doc of DocName - - - - - 7868e551 by Ian Lynagh at 2009-09-22T10:43:03+00:00 TAG GHC 6.12-branch created - - - - - 0452a3ea by Ian Lynagh at 2009-12-15T12:46:07+00:00 TAG GHC 6.12.1 release - - - - - 65e9be62 by David Waern at 2009-12-21T16:58:58+00:00 Update CHANGES - - - - - 145cee32 by David Waern at 2009-12-21T16:59:09+00:00 TAG 2.6.0 - - - - - 3c552008 by David Waern at 2009-12-22T17:11:14+00:00 Update ANNOUNCE - - - - - 931f9db4 by David Waern at 2010-01-22T19:57:17+00:00 Convert haddock.vim to use unix newlines - - - - - 4e56588f by David Waern at 2010-01-22T22:11:17+00:00 Remove unnecessary (and inexplicable) uses of nub - - - - - 744bb4d1 by David Waern at 2010-01-22T22:12:14+00:00 Follow move of parser and lexer - - - - - e34bab14 by David Waern at 2010-01-22T22:49:13+00:00 Use findProgramLocation instead of findProgramOnPath in runtests.hs - - - - - 8d39891b by Isaac Dupree at 2010-01-14T18:53:18+00:00 fix html arg-doc off-by-one and silliness - - - - - 9401f2e9 by David Waern at 2010-01-22T22:57:03+00:00 Create a test for function argument docs - - - - - 507a82d7 by David Waern at 2010-01-22T23:24:47+00:00 Put parenthesis around type signature arguments of function type - - - - - 8a305c28 by David Waern at 2010-01-23T17:26:59+00:00 Add reference file for the FunArgs test - - - - - 1309d5e1 by David Waern at 2010-01-24T16:05:08+00:00 Improve FunArg test and update Test.html.ref - - - - - 2990f055 by Yitzchak Gale at 2010-02-14T16:03:46+00:00 Do not generate illegal character in HTML ID attribute. - - - - - c5bcab7a by David Waern at 2010-02-22T22:10:30+00:00 Fix Haddock markup error in comment - - - - - c6416a73 by David Waern at 2010-02-24T22:55:08+00:00 Large additions to the Haddock API Also improved and added more doc comments. - - - - - 57d289d7 by David Waern at 2010-02-24T22:58:02+00:00 Remove unused ifaceLocals - - - - - 80528d93 by David Waern at 2010-02-25T21:05:09+00:00 Add HaddockModInfo to the API - - - - - 82806848 by David Waern at 2010-02-25T21:05:27+00:00 Wibble - - - - - 744cad4c by David Waern at 2010-02-25T23:30:59+00:00 Make it possible to run a single test - - - - - 6a806e4c by David Waern at 2010-03-14T14:19:39+00:00 Bump version number - - - - - a5a8e4a7 by David Waern at 2010-03-14T14:36:35+00:00 Update ANNOUNCE - - - - - 6f05435e by Simon Hengel at 2010-03-15T20:52:42+00:00 Add missing dependencies for 'library' in haddock.cabal - - - - - faefe2bd by David Waern at 2010-03-15T22:29:37+00:00 Solve conflicts - - - - - 9808ad52 by David Waern at 2010-03-15T22:51:21+00:00 Bump version number - - - - - eb0bf60b by David Waern at 2010-03-15T22:52:32+00:00 Update CHANGES - - - - - f95cd891 by David Waern at 2010-03-15T23:01:06+00:00 Add Paths_haddock to other-modules of library - - - - - 65997b0a by David Waern at 2010-03-15T23:14:59+00:00 Update CHANGES - - - - - 7e251731 by David Waern at 2010-03-15T23:15:30+00:00 Bump version number - - - - - c9cd0ddc by David Waern at 2010-03-16T00:28:34+00:00 Fix warning - - - - - 1cac2d93 by Simon Peyton Jones at 2010-01-04T15:22:16+00:00 Fix imports for new location of splitKindFunTys - - - - - 474f26f6 by Simon Peyton Jones at 2010-02-10T14:36:06+00:00 Update Haddock for quasiquotes - - - - - 0dcc06c0 by Simon Peyton Jones at 2010-02-10T10:59:45+00:00 Track changes in HsTyVarBndr - - - - - 2d84733a by Simon Peyton Jones at 2010-02-10T14:52:44+00:00 Track HsSyn chnages - - - - - 9e3adb8b by Ian Lynagh at 2010-02-20T17:09:42+00:00 Resolve conflicts - - - - - a3e72ff8 by Simon Peyton Jones at 2010-03-04T13:05:16+00:00 Track change in HsUtils; and use a nicer function not an internal one - - - - - 27994854 by David Waern at 2010-03-18T22:22:27+00:00 Fix build with GHC 6.12.1 - - - - - 11f6e488 by David Waern at 2010-03-18T22:24:09+00:00 Bump version in test reference files - - - - - 0ef2f11b by David Waern at 2010-03-20T00:56:30+00:00 Fix library part of cabal file when in ghc tree - - - - - 3f6146ff by Mark Lentczner at 2010-03-20T22:30:11+00:00 First, experimental XHTML rendering switch to using the xhtml package copied Html.hs to Xhtml.hs and split into sub-modules under Haddock/Backends/Xhtml and detabify moved footer into div, got ready for iface change headers converted to semantic markup contents in semantic markup summary as semantic markup description in semantic markup, info block in header fixed factored out rendering so during debug it can be readable (see renderToString) - - - - - b8ab329b by Mark Lentczner at 2010-03-20T22:54:01+00:00 apply changes to Html.hs to Xhtml/*.hs incorporate changes that were made between the time Html.hs was copied and split into Xhtml.hs and Xhtml/*.hs includes patchs after "Wibble" (!) through "Fix build with GHC 6.12.1" - - - - - 73df2433 by Ian Lynagh at 2010-03-20T21:56:37+00:00 Follow LazyUniqFM->UniqFM in GHC - - - - - db4f602b by David Waern at 2010-03-29T22:00:01+00:00 Fix build with GHC 6.12 - - - - - d8dca088 by Simon Hengel at 2010-04-02T16:39:55+00:00 Add missing dependencies to cabal file - - - - - e2adc437 by Simon Hengel at 2010-04-02T14:08:40+00:00 Add markup support for interactive examples - - - - - e882ac05 by Simon Hengel at 2010-04-02T14:11:53+00:00 Add tests for interactive examples - - - - - 5a07a6d3 by David Waern at 2010-04-07T17:05:20+00:00 Propagate source positions from Lex.x to Parse.y - - - - - 6493b46f by David Waern at 2010-04-07T21:48:57+00:00 Let runtests.hs die when haddock has not been built - - - - - 5e34423e by David Waern at 2010-04-07T22:01:13+00:00 Make runtests.hs slightly more readable - - - - - 321d59b3 by David Waern at 2010-04-07T22:13:27+00:00 Fix haskell/haddock#75 Add colons to the $ident character set. - - - - - 37b08b8d by David Waern at 2010-04-08T00:32:52+00:00 Fix haskell/haddock#118 Avoid being too greedy when lexing URL markup (<..>), in order to allow multiple URLs on the same line. Do the same thing with <<..>> and #..#. - - - - - df8feac9 by David Waern at 2010-04-08T00:57:33+00:00 Make it easier to add new package deps to test suite This is a hack - we should use Cabal to get the package details instead. - - - - - 1ca6f84b by David Waern at 2010-04-08T01:03:06+00:00 Add ghc-prim to test suite deps - - - - - 27371e3a by Simon Hengel at 2010-04-08T19:26:34+00:00 Let parsing fails on paragraphs that are immediately followed by an example This is more consistent with the way we treat code blocks. - - - - - 83096e4a by David Waern at 2010-04-08T21:20:00+00:00 Improve function name - - - - - 439983ce by David Waern at 2010-04-10T10:46:14+00:00 Fix haskell/haddock#112 No link was generated for 'Addr#' in a doc comment. The reason was simply that the identifier didn't parse. We were using parseIdentifier from the GHC API, with a parser state built from 'defaultDynFlags'. If we pass the dynflags of the module instead, the right options are turned on on while parsing the identifer (in this case -XMagicHash), and the parse succeeds. - - - - - 5c0d35d7 by David Waern at 2010-04-10T10:54:06+00:00 Rename startGhc into withGhc - - - - - dca081fa by Simon Hengel at 2010-04-12T19:09:16+00:00 Add documentation for interactive examples - - - - - c7f26bfa by David Waern at 2010-04-13T00:51:51+00:00 Slight fix to the documentation of examples - - - - - 06eb7c4c by David Waern at 2010-04-13T00:57:05+00:00 Rename Interactive Examples into Examples (and simplify explanation) - - - - - 264830cb by David Waern at 2010-05-10T20:07:27+00:00 Update CHANGES with info about 2.6.1 - - - - - 8e5d4514 by Simon Hengel at 2010-04-18T18:16:54+00:00 Add unit tests for parser - - - - - 68297f40 by David Waern at 2010-05-10T21:53:37+00:00 Improve testsuite README - - - - - f04eb6e4 by David Waern at 2010-05-11T19:14:31+00:00 Re-organise the testsuite structure - - - - - a360f710 by David Waern at 2010-05-11T19:18:03+00:00 Shorten function name - - - - - 1d5dd359 by David Waern at 2010-05-11T21:40:02+00:00 Update runtests.hs following testsuite re-organisation - - - - - ffebe217 by David Waern at 2010-05-11T21:40:10+00:00 Update runtests.hs to use base-4.2.0.1 - - - - - 635de402 by David Waern at 2010-05-11T21:41:11+00:00 Update runparsetests.hs following testsuite reorganisation - - - - - 72137910 by Ian Lynagh at 2010-05-06T20:43:06+00:00 Fix build - - - - - 1a80b76e by Ian Lynagh at 2010-05-06T22:25:29+00:00 Remove redundant import - - - - - 1031a80c by Simon Peyton Jones at 2010-05-07T13:21:09+00:00 Minor wibbles to HsBang stuff - - - - - dd8e7fe5 by Ian Lynagh at 2010-05-08T15:22:00+00:00 GHC build system: Follow "rm" variable changes - - - - - 7f5e6748 by David Waern at 2010-05-13T11:53:02+00:00 Fix build with GHC 6.12.2 - - - - - 7953d4d8 by David Waern at 2010-05-13T18:45:01+00:00 Fixes to comments only - - - - - 8ae8eb64 by David Waern at 2010-05-13T18:57:26+00:00 ModuleMap -> IfaceMap - - - - - 1c3eadc6 by David Waern at 2010-05-13T19:03:13+00:00 Fix whitespace style issues - - - - - e96783c0 by David Waern at 2010-05-13T19:08:53+00:00 Fix comment - - - - - c998a78b by David Waern at 2010-05-13T19:39:00+00:00 Position the module header the same way everywhere Silly, but nice with some consistency :-) - - - - - b48a714e by David Waern at 2010-05-13T19:41:32+00:00 Position of module header, this time in the HTML backends - - - - - f9bfb12e by David Waern at 2010-05-13T19:43:05+00:00 Two newlines between declarations in Main - - - - - 071d44c7 by David Waern at 2010-05-13T19:44:21+00:00 Newlines in Convert - - - - - 036346db by David Waern at 2010-05-13T19:46:47+00:00 Fix a few stylistic issues in H.InterfaceFile - - - - - f0b8379e by David Waern at 2010-05-13T19:47:53+00:00 Add newlines to H.ModuleTree - - - - - 27409f8e by David Waern at 2010-05-13T19:51:10+00:00 Fix stylistic issues in H.Utils - - - - - 24774a11 by David Waern at 2010-05-13T20:00:43+00:00 Structure H.Types better - - - - - 7b6f5e40 by David Waern at 2010-05-13T20:01:04+00:00 Remove bad Arbitrary instance - - - - - fac9f1f6 by David Waern at 2010-05-13T20:05:50+00:00 Get rid of H.Utils.pathJoin and use System.FilePath.joinPath instead - - - - - fe6d00c4 by David Waern at 2010-05-13T20:51:55+00:00 Export a couple of more types from the API - - - - - b2e33a5f by David Waern at 2010-05-13T21:27:51+00:00 Improve doc comment for Interface - - - - - c585f2ce by David Waern at 2010-05-13T21:30:14+00:00 Improve documentation of Haddock.Interface - - - - - e6791db2 by David Waern at 2010-05-13T22:07:35+00:00 Remove meaningless comments - - - - - 7801b390 by David Waern at 2010-05-14T17:53:33+00:00 Remove unused modules - - - - - f813e937 by David Waern at 2010-05-14T17:55:17+00:00 Re-direct compilation output to a temporary directory Also add a flag --no-tmp-comp-dir that can be used to get the old behaviour of writing compilation files to GHC's output directory (default "."). - - - - - e56737ec by David Waern at 2010-05-14T18:06:11+00:00 Wibble - - - - - e40b0447 by David Waern at 2010-05-14T19:01:52+00:00 Move flag evaluation code from Main to Haddock.Options Determining the value of "singular" flags (by e.g. taking the last occurrence of the flag) and other flag evaluation should done in Haddock.Options which is the module that is supposed to define the command line interface. This makes Main a bit easier on the eyes as well. - - - - - 27091f57 by David Waern at 2010-05-14T19:05:10+00:00 Wibble - - - - - c658cf61 by David Waern at 2010-05-14T19:06:49+00:00 Re-order things in Haddock.Options a bit - - - - - 8cfdd342 by David Waern at 2010-05-14T19:20:29+00:00 De-tabify Haddock.Options and fix other whitespace issues - - - - - 0df16b62 by David Waern at 2010-05-14T19:25:07+00:00 Improve comments - - - - - 80b38e2b by David Waern at 2010-05-14T19:26:42+00:00 Whitespace police - - - - - fe580255 by David Waern at 2010-05-14T19:31:23+00:00 Wibbles to comments - - - - - a2b43fad by David Waern at 2010-05-14T20:24:32+00:00 Move some more flag functions to Haddock.Options - - - - - 3f895547 by David Waern at 2010-05-14T20:37:12+00:00 Make renderStep a top-level function in Main - - - - - 5cdca11d by David Waern at 2010-05-14T20:39:27+00:00 Spelling in comment - - - - - ad98d14c by David Waern at 2010-05-14T20:40:26+00:00 Comment fixes - - - - - 0bb9218f by David Waern at 2010-05-14T20:49:01+00:00 Whitespace police - - - - - 0f0a533f by David Waern at 2010-05-15T16:42:29+00:00 Improve description of --dump-interface - - - - - 5b2833ac by David Waern at 2010-05-15T17:16:53+00:00 Document --no-tmp-comp-dir - - - - - 8160b170 by David Waern at 2010-05-15T17:18:59+00:00 Wibble - - - - - 570dbe33 by David Waern at 2010-05-18T21:15:38+00:00 HLint police - - - - - 204e425f by David Waern at 2010-05-18T21:16:30+00:00 HLint police - - - - - 6db657ac by David Waern at 2010-05-18T21:16:37+00:00 Wibble - - - - - b942ccd7 by Simon Marlow at 2010-06-02T08:27:30+00:00 Interrupted disappeared in GHC 6.13 (GHC ticket haskell/haddock#4100) - - - - - 3b94a819 by Simon Marlow at 2010-06-02T08:45:08+00:00 Allow base-4.3 - - - - - c5a1fb7c by Simon Marlow at 2010-06-02T09:03:04+00:00 Fix compilation with GHC 6.13 - - - - - 6181296c by David Waern at 2010-06-08T21:09:05+00:00 Display name of prologue file when parsing it fails - - - - - 7cbc6f60 by Ian Lynagh at 2010-06-13T16:20:25+00:00 Remove redundant imports - - - - - 980c804b by Simon Marlow at 2010-06-22T08:41:50+00:00 isLocalAndTypeInferenced: fix for local module names overlapping package modules - - - - - d74d4a12 by Simon Marlow at 2010-06-23T12:03:27+00:00 Unresolved identifiers in Doc get replaced with DocMonospaced rather than plain strings - - - - - d8546783 by Simon Marlow at 2010-06-30T12:45:17+00:00 LaTeX backend (new options: --latex, --latex-style=<style>) - - - - - 437afa9e by David Waern at 2010-07-01T12:02:44+00:00 Fix a few stylistic whitespace issues in LaTeX backend - - - - - 85bc1fae by David Waern at 2010-07-01T15:42:45+00:00 Make runtest.hs work with GHC 6.12.3 (we should really stop hard coding this) - - - - - 7d2eb86f by David Waern at 2010-07-01T15:43:33+00:00 Update test following Simon's patch to render unresolved names in monospaced font - - - - - 08fcbcd2 by David Waern at 2010-07-01T16:12:18+00:00 Warning police - - - - - d04a8d7a by David Waern at 2010-07-04T14:53:39+00:00 Fix a bug in attachInstances We didn't look for instance docs in all the interfaces of the package. This had the effect of instance docs not always showing up under a declaration. I took the opportunity to clean up the code in H.I.AttachInstances a bit as well. More cleanup is needed, however. - - - - - d10344eb by Simon Hengel at 2010-07-10T09:19:04+00:00 Add missing dependencies to cabal file - - - - - 24090531 by Mark Lentczner at 2010-03-21T04:51:16+00:00 add exports to Xhtml modules - - - - - 84f9a333 by Mark Lentczner at 2010-04-03T19:14:22+00:00 clean up Doc formatting code - add CSS for lists - renderToString now uses showHtml since prettyHtml messes up <pre> sections - - - - - bebccf52 by Mark Lentczner at 2010-04-04T04:51:08+00:00 tweak list css - - - - - 0c2aeb5e by Mark Lentczner at 2010-04-04T06:24:14+00:00 all decls now generate Html not HtmlTable - ppDecl return Html, and so now do all of the functions it calls - added some internal tables to some decls, which is wrong, and will have to be fixed - decl "Box" functions became "Elem" functions to make clear they aren't in a table anymore (see Layout.hs) - docBox went away, as only used in one place (and its days are numbered) - cleaned up logic in a number of places, removed dead code - added maybeDocToHtml which simplified a number of places in the code - - - - - dbf73e6e by Mark Lentczner at 2010-04-05T05:02:43+00:00 clean up processExport and place a div around each decl - - - - - e25b7e9f by Mark Lentczner at 2010-04-10T21:23:21+00:00 data decls are now a sequence of paragraphs, not a table - - - - - 89ee0294 by Mark Lentczner at 2010-04-10T21:29:16+00:00 removed commented out code that can't be maintained - - - - - d466f536 by Mark Lentczner at 2010-04-12T04:56:27+00:00 removed declWithDoc and cleaned up data decls in summary - - - - - ed755832 by Mark Lentczner at 2010-04-12T05:07:53+00:00 merge in markupExample changes - - - - - c36f51fd by Mark Lentczner at 2010-04-25T04:56:37+00:00 made record fields be an unordList, not a table - - - - - ed3a28d6 by Mark Lentczner at 2010-04-25T05:23:28+00:00 fixed surround of instance and constructor tables - - - - - 0e35bbc4 by Mark Lentczner at 2010-04-25T05:36:59+00:00 fix class member boxes in summary - - - - - 5041749b by Mark Lentczner at 2010-04-25T05:38:35+00:00 remove unused bodyBox - - - - - e91724db by Mark Lentczner at 2010-04-25T06:26:10+00:00 fixed javascript quoting/escpaing issue - - - - - f4abbb73 by Mark Lentczner at 2010-05-03T23:04:31+00:00 adjust css for current markup - - - - - e75fec4c by Mark Lentczner at 2010-05-04T06:14:34+00:00 added assoicated types and methods back into class decls - - - - - 84169323 by Mark Lentczner at 2010-05-24T13:13:42+00:00 merge in changes from the big-whitespace cleanup - - - - - 3c1c872e by Mark Lentczner at 2010-06-11T21:03:58+00:00 adjust synopsis and bottom bar spacing - - - - - 3c1f9ef7 by Mark Lentczner at 2010-06-11T21:14:44+00:00 fix missing space in "module" lines in synoposis - - - - - 9a137e6d by Mark Lentczner at 2010-06-11T21:34:08+00:00 changed tt elements to code elements - - - - - 50f71ef1 by Mark Lentczner at 2010-06-11T23:27:46+00:00 factored out ppInstances - - - - - 3b9a9de5 by Mark Lentczner at 2010-06-17T17:36:01+00:00 push single constructors (newtype) onto line with decl - - - - - e0f8f2ec by Mark Lentczner at 2010-06-17T22:20:56+00:00 remove <++> connector - - - - - 56c075dd by Mark Lentczner at 2010-07-13T05:26:21+00:00 change to new page structure - - - - - 04be6ca7 by Mark Lentczner at 2010-07-14T04:21:55+00:00 constructors and args as dl lists, built in Layout.hs - - - - - 65aeafc2 by Mark Lentczner at 2010-07-14T05:38:32+00:00 better interface to subDecls - - - - - 72032189 by Mark Lentczner at 2010-07-14T07:04:10+00:00 made subDecl tables looks just so - - - - - b782eca2 by Mark Lentczner at 2010-07-14T16:00:54+00:00 convert args to SubDecl format - - - - - cc75e98f by Mark Lentczner at 2010-07-14T16:28:53+00:00 convert instances to SubDecl - - - - - 34e2aa5a by Mark Lentczner at 2010-07-14T21:07:32+00:00 removing old table cruft from Layout.hs - - - - - d5810d95 by Mark Lentczner at 2010-07-14T21:54:58+00:00 methods and associated types in new layout scheme - - - - - 65ef9579 by Mark Lentczner at 2010-07-14T23:43:42+00:00 clean up synopsis lists - - - - - e523318f by Mark Lentczner at 2010-07-15T05:02:26+00:00 clean up of anchors - - - - - 1215dfc5 by Mark Lentczner at 2010-07-15T23:53:01+00:00 added two new themes and rough css switcher - - - - - 7f0fd36f by Mark Lentczner at 2010-07-16T04:57:38+00:00 fixed package catpion, added style menu - - - - - 0dd4999c by Mark Lentczner at 2010-07-16T20:12:39+00:00 new output for mini_ pages - - - - - 64b2810b by Mark Lentczner at 2010-07-16T20:58:41+00:00 reformat index-frames - - - - - 3173f555 by Mark Lentczner at 2010-07-16T22:41:53+00:00 convert index to new markup - - - - - b0a4b7c9 by Mark Lentczner at 2010-07-17T04:07:22+00:00 convert index.html to new markup, adjust module markup - - - - - 8261ae1e by Mark Lentczner at 2010-07-17T05:07:29+00:00 classing styling of ancillary pages - - - - - 2a4fb025 by Mark Lentczner at 2010-07-17T05:11:45+00:00 clean up Layout.hs: no more vanillaTable - - - - - 87eec685 by Mark Lentczner at 2010-07-17T05:35:16+00:00 clean up Util.hs - - - - - d304e9b0 by Mark Lentczner at 2010-07-17T05:38:50+00:00 qualify import of XHtml as XHtml - - - - - 7dc05807 by Mark Lentczner at 2010-07-17T06:17:53+00:00 factored out head element generation - - - - - 9cdaec9e by Mark Lentczner at 2010-07-17T06:44:54+00:00 refactored out main page body generation - - - - - 8a51019e by Mark Lentczner at 2010-07-17T06:48:20+00:00 moved footer into only place that used it - - - - - efa479da by Mark Lentczner at 2010-07-17T18:48:30+00:00 styling auxillary pages for tibbe and snappy themes - - - - - 81de5509 by Mark Lentczner at 2010-07-18T04:41:38+00:00 fixed alphabet on index page, and styling of it and packages in module lists - - - - - 20718c1a by Mark Lentczner at 2010-07-18T05:34:29+00:00 cleaned up div functions in Layout.hs - - - - - 60d50453 by Mark Lentczner at 2010-07-18T05:48:39+00:00 added content div to main pages - - - - - ed16561c by Mark Lentczner at 2010-07-18T06:12:22+00:00 add .doc class to documentation blocks - - - - - f5c781b0 by Mark Lentczner at 2010-07-19T05:20:53+00:00 refactoring of anchor ID and fragment handling - - - - - a69a93bf by Mark Lentczner at 2010-07-19T05:35:55+00:00 remove an explicit bold tag - replace with .def class - - - - - d76c7225 by Mark Lentczner at 2010-07-19T06:56:15+00:00 rename Haddock.Backends.Xhtml.Util to Utils - - - - - 5a58c0da by David Waern at 2010-07-21T13:30:54+00:00 Remove trailing whitespace in Haddock.Backends.Xhtml - - - - - 0652aa17 by David Waern at 2010-07-21T13:33:21+00:00 Align a few comments - - - - - 785776c3 by David Waern at 2010-07-21T13:39:04+00:00 Remove trailing whitespace in H.B.X.Decl - - - - - 71a30710 by David Waern at 2010-07-21T13:44:27+00:00 Remove more trailing whitespace - - - - - 38750394 by David Waern at 2010-07-21T13:50:43+00:00 Style police - - - - - 3023d940 by David Waern at 2010-07-21T14:01:22+00:00 Style police in H.B.X.Decl - - - - - df16e9e6 by David Waern at 2010-07-21T14:14:45+00:00 Style police in H.B.X.DocMarkup - - - - - 6020e321 by David Waern at 2010-07-21T14:17:32+00:00 More style police - - - - - 86ad8bf5 by David Waern at 2010-07-21T14:21:02+00:00 Style police in H.B.Xhtml - - - - - aea27d03 by David Waern at 2010-07-21T14:42:03+00:00 Fix warnings in LaTeX backend - - - - - 2aff34a9 by David Waern at 2010-07-21T14:50:46+00:00 Style police in LaTeX backend (mainly more newlines) - - - - - e517162d by David Waern at 2010-07-21T15:05:47+00:00 Doc sections in Main - - - - - b971aa0c by David Waern at 2010-07-21T15:06:17+00:00 Trailing whitespace in Documentation.Haddock - - - - - f11628fb by David Waern at 2010-07-21T15:07:06+00:00 Trailing whitespace in Haddock.Convert - - - - - cbaf284c by David Waern at 2010-07-21T15:08:11+00:00 Style police in Haddock.GhcUtils - - - - - 71feb77b by David Waern at 2010-07-21T15:09:06+00:00 Style police in Haddock.InterfaceFile - - - - - 0a9c80e6 by David Waern at 2010-07-21T15:11:33+00:00 Whitespace police - - - - - 6168376c by David Waern at 2010-07-21T15:16:35+00:00 Style police in Haddock.Utils - - - - - 9fe4dd90 by David Waern at 2010-07-21T15:19:31+00:00 Add -fwarn-tabs - - - - - a000d752 by Mark Lentczner at 2010-07-20T17:25:52+00:00 move CSS Theme functions into Themes.hs - - - - - b52b440f by Mark Lentczner at 2010-07-20T17:29:35+00:00 add Thomas Schilling's theme - - - - - e43fa7e8 by Mark Lentczner at 2010-07-21T04:49:34+00:00 correct icon used with Snappy theme - - - - - ba5092d3 by Mark Lentczner at 2010-07-21T04:56:47+00:00 apply Tibbe's updates to his theme - - - - - 7804eef6 by Mark Lentczner at 2010-07-21T05:15:49+00:00 space between "Style" and the downward triangle - - - - - 7131d4c6 by Mark Lentczner at 2010-07-21T17:43:35+00:00 merge with David's source cleanups - - - - - ee65f1cb by David Waern at 2010-07-22T16:50:46+00:00 Fix a bug where we allowed --hoogle, --latex, etc without input files - - - - - e413ff7a by David Waern at 2010-07-22T17:21:58+00:00 Improve function name - - - - - a0fd14f3 by Simon Marlow at 2010-06-30T15:34:32+00:00 fix warnings - - - - - 31f73d2a by David Waern at 2010-07-22T19:29:41+00:00 Solve conflicts - - - - - d563b4a5 by Simon Marlow at 2010-06-30T15:34:37+00:00 fix warning - - - - - 412b6469 by David Waern at 2010-07-22T19:31:28+00:00 Solve conflict - - - - - 35174b94 by Ian Lynagh at 2010-07-06T17:27:16+00:00 Follow mkPState argument order change - - - - - b5c3585c by Simon Marlow at 2010-07-14T08:49:21+00:00 common up code for instance rendering - - - - - d8009560 by Simon Marlow at 2010-07-14T12:37:11+00:00 fix warnings - - - - - a6d88695 by David Waern at 2010-07-24T15:33:33+00:00 Fix build with ghc < 6.13 - - - - - 94cf9de1 by David Waern at 2010-07-24T15:34:37+00:00 Remove conflict left-over - - - - - 313b15c0 by Mark Lentczner at 2010-07-21T22:09:04+00:00 reorganization of nhaddock.css with tibbe - - - - - 9defed80 by Mark Lentczner at 2010-07-21T22:42:14+00:00 further cleanup of nhaddock.css, float TOC, support aux. pages - - - - - 6d944c1b by Mark Lentczner at 2010-07-22T06:22:23+00:00 remove old HTML backend - - - - - b3e8cba5 by Mark Lentczner at 2010-07-22T06:43:32+00:00 remove --html-help support - it was old, out-of-date, and mostly missing - - - - - d2654a08 by Mark Lentczner at 2010-07-22T21:45:34+00:00 tweaks to nhaddock.css - - - - - f73b285c by Mark Lentczner at 2010-07-23T06:19:35+00:00 command like processing for theme selection The bulk of the change is threadnig the selected theme set through functions in Xhtml.hs so that the selected themes can be used when generating the page output. There isn't much going on in most of these changes, just passing it along. The real work is all done in Themes.hs. - - - - - 8bddc90d by Mark Lentczner at 2010-07-23T06:58:31+00:00 drop --themes support, add named theme support decided that --themes was silly - no one would do that, just use multiple --theme arguments made --theme a synonym for --css and -c made those arguments, if no file is found, look up the argument as the name of a built in theme all of this let's haddock be invoked with "--theme=classic" for example. - - - - - 20cafd4f by Mark Lentczner at 2010-07-23T17:44:29+00:00 rename --default-themes to --built-in-themes - - - - - 0fe41307 by Mark Lentczner at 2010-07-23T18:33:02+00:00 tweaks to theme for info table, headings, and tables - - - - - cba4fee0 by Mark Lentczner at 2010-07-23T19:13:59+00:00 tweaks for dl layout, though still not used - - - - - 463fa294 by Mark Lentczner at 2010-07-23T21:07:19+00:00 tweak look of mini pages, keywords, and preblocks - - - - - 5472fc02 by Mark Lentczner at 2010-07-24T05:36:15+00:00 slide out Synopsis drawer - - - - - 9d5d5de5 by Mark Lentczner at 2010-07-24T06:02:42+00:00 extend package header and footer to edges of page - - - - - a47c91a2 by Mark Lentczner at 2010-07-24T06:28:44+00:00 fields are def lists, tweak css for style menu, mini pages, arguments - - - - - ca20f23b by Mark Lentczner at 2010-07-24T16:55:22+00:00 excisting last vestiges of the --xhtml flag - - - - - 71fb012e by Mark Lentczner at 2010-07-25T18:47:49+00:00 change how collapsing sections are done make whole .caption be the target improve javascript for class toggling have plus/minus images come from .css, not img tags - - - - - c168c8d3 by Mark Lentczner at 2010-07-26T00:32:05+00:00 reorganize files in the html lib data dir - - - - - 93324301 by Mark Lentczner at 2010-07-26T01:27:42+00:00 cleaned up Themes.hs - - - - - ad3b5dd4 by Mark Lentczner at 2010-07-26T02:39:15+00:00 make module list use new collapsers - - - - - 1df9bfc6 by Mark Lentczner at 2010-07-27T19:09:25+00:00 remove Tibbe theme - - - - - 8b9b01b3 by Mark Lentczner at 2010-07-27T20:04:03+00:00 move themes into html dir with .theme and .std-theme extensions - - - - - a7beb965 by Mark Lentczner at 2010-07-27T21:06:34+00:00 give a class to empty dd elements so they can be hidden - - - - - a258c117 by Mark Lentczner at 2010-07-27T21:23:58+00:00 remove custom version of copyFile in Xhtml.hs - - - - - b70dba6e by Mark Lentczner at 2010-07-27T22:12:45+00:00 apply margin changes to pre and headings as per group decision, and small cleanups - - - - - e6f722a2 by Mark Lentczner at 2010-07-28T00:03:12+00:00 make info block and package bar links be floatable by placing them first in the dom tree - - - - - c8278867 by Mark Lentczner at 2010-07-28T19:01:18+00:00 styling source links on declarations - - - - - 88fdc399 by Mark Lentczner at 2010-07-29T01:12:46+00:00 styling tweaks don't generate an empty li for absent style menu in links area update css for Classic and Snappy to handle: dl lists links in package header and in declarations floating of links and info block in package and module headers - - - - - 8a75b213 by Ian Lynagh at 2010-07-30T20:21:46+00:00 Fix build in GHC tree - - - - - ce8e18b3 by Simon Hengel at 2010-08-03T18:37:26+00:00 Adapt paths to data files in cabal file - - - - - 9701a455 by Simon Hengel at 2010-08-07T13:20:27+00:00 Add missing dependency to cabal file - - - - - 01b838d1 by Mark Lentczner at 2010-07-30T20:19:40+00:00 improved synopsis drawer: on click, not hover - - - - - 7b6f3e59 by Mark Lentczner at 2010-07-30T23:38:55+00:00 put the synopsis back in the other themes - - - - - 7b2904c9 by Mark Lentczner at 2010-08-11T11:11:26+00:00 close arrows on expanded synopsis drawer - - - - - ea19e177 by Mark Lentczner at 2010-08-12T21:16:45+00:00 width and font changes removed the max width restrictions on the page as a whole and the synopsis made the main font size smaller (nominally 14pt) and then tweaked most font sizes (relative) to be more consistent - - - - - 5ced00c0 by Mark Lentczner at 2010-08-13T15:09:55+00:00 implemented YUI's CSS font approach - - - - - 2799c548 by Mark Lentczner at 2010-08-13T15:11:59+00:00 adjusted margin to 2em, 1 wasn't enough - - - - - 58f06893 by Mark Lentczner at 2010-08-13T15:48:44+00:00 removed underlining on hover for named anchors headings in interface lost thier a element, no need, just put id on heading css for a elements now only applies to those with href attribute - - - - - 7aced4c4 by Mark Lentczner at 2010-08-13T15:50:22+00:00 more space between elements - - - - - 5a3c1cce by Mark Lentczner at 2010-08-13T16:43:43+00:00 adjusted font sizes of auxilary pages per new scheme - - - - - 487539ef by Mark Lentczner at 2010-08-13T21:43:41+00:00 add Frames button and clean up frames.html - - - - - c1a140b6 by Mark Lentczner at 2010-08-13T22:17:48+00:00 move frames button to js - - - - - b0bdb68e by Mark Lentczner at 2010-08-14T03:44:46+00:00 build style menu in javascript moved to javascript, so as to not polute the content with the style menu removed menu building code in Themes.hs removed onclick in Utils.hs changed text of button in header from "Source code" to "Source" more consistent with links in rest of page - - - - - 43ab7120 by Mark Lentczner at 2010-08-16T15:15:37+00:00 font size and margin tweaks - - - - - c0b68652 by Mark Lentczner at 2010-08-17T18:19:52+00:00 clean up collapser logics javascript code for collapasble sections cleaned up rewrote class utilities in javascript to be more robust refactored utilities for generating collapsable sections made toc be same color as synopsis module list has needed clear attribute in CSS - - - - - 5d573427 by Mark Lentczner at 2010-08-17T23:06:02+00:00 don't collapse entries in module list when clicking on links - - - - - 8c307c4a by Mark Lentczner at 2010-08-17T23:21:43+00:00 add missing data file to .cabal - - - - - 414bcfcf by Mark Lentczner at 2010-08-17T23:28:47+00:00 remove synopsis when in frames - - - - - ba0fa98a by Mark Lentczner at 2010-08-18T16:16:11+00:00 layout tweeks - mini page font size, toc color, etc. - - - - - 63c1bed1 by Mark Lentczner at 2010-08-18T19:50:02+00:00 margin fiddling - - - - - c311c094 by Mark Lentczner at 2010-08-20T01:37:55+00:00 better synopsis handling logic - no flashing - - - - - f1fe5fa8 by Mark Lentczner at 2010-08-20T01:41:06+00:00 fix small layout issues mini frames should have same size top heading give info block dts some padding so they don't collide in some browsers - - - - - 0de84d77 by Mark Lentczner at 2010-08-20T02:13:09+00:00 made style changing and cookies storage robust - - - - - 1ef064f9 by Thomas Schilling at 2010-08-04T13:12:22+00:00 Make synopsis frame behave properly in Firefox. In Firefox, pressing the back button first reverted the synopsis frame, and only clicking the back button a second time would update the main frame. - - - - - dd1c9a94 by Mark Lentczner at 2010-08-21T01:46:19+00:00 remove Snappy theme - - - - - 2353a90d by Mark Lentczner at 2010-08-25T05:16:19+00:00 fix occasional v.scroll bars on pre blocks (I think) - - - - - 459b8bf1 by Simon Hengel at 2010-08-08T10:12:45+00:00 Add createInterfaces' (a more high-level alternative to createInterfaces) to Haddock API - - - - - b1b68675 by David Waern at 2010-08-26T20:31:58+00:00 Follow recent API additions with some refactorings Simon Hegel's patch prompted me to do some refactorings in Main, Haddock.Documentation and Haddock.Interface. - - - - - 264d4d67 by David Waern at 2010-08-26T21:40:59+00:00 Get rid of GhcModule and related cruft We can get everything we need directly from TypecheckedModule. - - - - - 0feacec2 by Mark Lentczner at 2010-08-26T23:44:13+00:00 fixed CSS for ordered lists and def lists in doc blocks - - - - - 2997e0c2 by Mark Lentczner at 2010-08-26T23:45:03+00:00 support both kinds of enumerated lists in doc markup The documentation for Haddock says enumerated lists can use either of (1) first item 2. second item The second form wasn't actually supported - - - - - 5d4ddeec by Mark Lentczner at 2010-08-27T21:29:48+00:00 fix broken header link margins - - - - - 614456ba by Mark Lentczner at 2010-08-27T22:16:19+00:00 fix table of contents CSS - - - - - 03f329a2 by David Waern at 2010-08-28T16:36:09+00:00 Update tests following switch to the Xhtml backend - - - - - ca689fa2 by Mark Lentczner at 2010-08-28T18:25:16+00:00 fix def lists - - - - - 18e1d3d2 by Mark Lentczner at 2010-08-28T18:26:18+00:00 push footer to bottom of window - - - - - b0ab8d82 by David Waern at 2010-08-28T22:04:32+00:00 Whitespace police - - - - - 2d217977 by David Waern at 2010-08-29T12:44:45+00:00 Remove Snappy data files - - - - - 01e27d5f by David Waern at 2010-08-29T13:03:28+00:00 Add source entity path to --read-interface You can now use this flag like this: --read-interface=<html path>,<source entity path>,<.haddock file> By "source entity path" I mean the same thing that is specified with the --source-entity flag. The purpose of this is to be able to specify the source entity path per package, to allow source links to work in the presence of cross-package documentation. When given two arguments or less the --read-interface flag behaves as before. - - - - - 20bf4aaa by David Waern at 2010-08-29T13:11:03+00:00 Naming wibbles - - - - - ad22463f by Mark Lentczner at 2010-08-29T15:14:54+00:00 make portability block be a table - solves layout issues - - - - - 97bd1ae6 by Mark Lentczner at 2010-08-29T15:17:42+00:00 update golden test for Test due to portability box change - - - - - d37e139e by Mark Lentczner at 2010-08-29T17:07:17+00:00 move TOC and Info blocks down 0.5em to improve layout issue w/Test.hs - - - - - acf52501 by David Waern at 2010-08-29T17:32:36+00:00 Allow building with ghc < 6.16 - - - - - 1cb34ed8 by Ian Lynagh at 2010-07-24T23:18:49+00:00 Flatten the dynflags before parsing - - - - - b36845b4 by Ian Lynagh at 2010-07-24T23:26:49+00:00 Follow flattenLanguageFlags -> flattenExtensionFlags rename - - - - - 7f7fcc7e by David Waern at 2010-08-29T17:46:23+00:00 Use flattenExtensionFlags with ghc >= 6.13 only - - - - - 13cf9411 by Ian Lynagh at 2010-08-01T18:09:54+00:00 Make the main haddock script versioned, and make plain "haddock" a symlink - - - - - 495cbff2 by Ian Lynagh at 2010-08-18T18:57:24+00:00 Fix installation in the GHC build system Data-files are now in subdirectories, so we need to handle that - - - - - 88ebab0a by Ian Lynagh at 2010-08-18T19:43:53+00:00 GHC build system: Add all the data files to BINDIST_EXTRAS - - - - - 65837172 by David Waern at 2010-08-29T20:12:34+00:00 Update Test - - - - - 094bbaa2 by David Waern at 2010-08-29T20:55:14+00:00 Revert update to Test - - - - - a881cfb3 by David Waern at 2010-08-31T18:24:15+00:00 Bump version number - - - - - 1fc8a3eb by David Waern at 2010-08-31T22:32:27+00:00 Update ANNOUNCE - - - - - ee1df9d0 by David Waern at 2010-08-31T22:33:11+00:00 Update CHANGES - - - - - 394cc854 by David Waern at 2010-08-31T22:33:23+00:00 Update interface file versioning to work with ghc 6.14/15 - - - - - 7d03b79b by David Waern at 2010-08-31T22:36:00+00:00 Update test output following version change - - - - - a48d82d1 by Mark Lentczner at 2010-09-01T04:29:35+00:00 sort options in doc to match --help output removed --html-help option, as it is no longer supported - - - - - 06561aeb by Mark Lentczner at 2010-09-01T05:29:32+00:00 update options documentation rewrote doc for --html added doc for --theme and --built-in-themes added --use-contents and --gen-contents - - - - - 57dea832 by Mark Lentczner at 2010-09-01T05:31:27+00:00 slight wording change about Frames mode - - - - - fa1f6da3 by David Waern at 2010-09-01T10:57:44+00:00 Update doc configure script to find docbook stylesheets on arch linux - - - - - addff770 by David Waern at 2010-09-01T11:02:29+00:00 Wibble - - - - - 8399006d by David Waern at 2010-09-01T11:19:21+00:00 Replace ghci> with >>> in example syntax - - - - - 35074cf8 by David Waern at 2010-09-01T19:03:27+00:00 Improve docs for --no-tmp-comp-dir - - - - - 0f8f8cfd by David Waern at 2010-09-02T11:22:27+00:00 Add a list of contributors to the user guide Break out everyone thanked in the `Acknowledgements` chapter into a separate contributor list and add everyone from `darcs show authors`. We consider everyone who is thanked to be a contributor as a conservative estimation :-) I have added some more contributors that I know about, who were not in the darcs history, but others may be missing. So please add anyone that you think is missing from the list. - - - - - 42ccf099 by David Waern at 2010-09-02T11:29:22+00:00 Update copyright years in license - - - - - 0d560479 by David Waern at 2010-09-02T11:38:52+00:00 Update release instructions - - - - - 72ab7796 by David Waern at 2010-09-02T19:27:08+00:00 Add a note to ANNOUNCE - - - - - bf9d9c5d by David Waern at 2010-09-02T19:27:48+00:00 H.Utils needs FFI on Win+MinGW - - - - - 048ae44a by Mark Lentczner at 2010-09-04T23:19:47+00:00 make TOC group header identifiers validate - - - - - 8c6faf36 by Simon Michael at 2010-09-22T07:12:34+00:00 add hints for cleaner darcs show authors output - - - - - 9909bd17 by Simon Michael at 2010-09-22T17:58:06+00:00 print haddock coverage info on stdout when generating docs A module's haddockable items are its exports and the module itself. The output is lightly formatted so you can align the :'s and sort for readability. - - - - - 6da72171 by David Waern at 2010-10-03T21:31:24+00:00 Style wibble - - - - - 2f8d8e4d by Tobias Brandt at 2010-08-27T07:01:21+00:00 adding the option to fully qualify identifiers - - - - - 833be6c6 by Tobias Brandt at 2010-08-27T15:50:28+00:00 adding support for local and relative name qualification - - - - - df15c4e9 by Tobias Brandt at 2010-08-27T15:56:37+00:00 corrected qualification help message - - - - - 449e9ce1 by David Waern at 2010-10-16T17:34:30+00:00 Solve conflicts - - - - - 3469bda5 by David Waern at 2010-10-16T18:42:40+00:00 Use "qual" as an abbreviation for qualification instead of "quali" for consistency - - - - - 97c2d728 by David Waern at 2010-10-16T18:47:07+00:00 Style police - - - - - ce14fbea by David Waern at 2010-10-16T21:15:25+00:00 Style police - - - - - fdf29e9d by David Waern at 2010-10-17T00:30:44+00:00 Add a pointer to the style guide - - - - - 8e6b44e8 by rrnewton at 2010-10-24T03:19:28+00:00 Change to index pages: include an 'All' option even when subdividing A-Z. - - - - - 755b131c by David Waern at 2010-11-14T19:39:36+00:00 Bump version - - - - - d0345a04 by David Waern at 2010-11-14T19:41:59+00:00 TAG 2.8.1 - - - - - f6221508 by Simon Peyton Jones at 2010-09-13T09:53:00+00:00 Adapt to minor changes in internal GHC functions - - - - - 1290713d by Ian Lynagh at 2010-09-15T10:37:18+00:00 Remove duplicate Outputable instance for Data.Map.Map - - - - - 87f69eef by Ian Lynagh at 2010-09-21T15:01:10+00:00 Bump GHC dep upper bound - - - - - af36e087 by Ian Lynagh at 2010-09-21T15:12:02+00:00 Fix up __GLASGOW_HASKELL__ tests - - - - - ad67716c by Ian Lynagh at 2010-09-21T20:31:35+00:00 Don't build haddock is HADDOCK_DOCS is NO - - - - - 63b3f1f5 by Ian Lynagh at 2010-09-21T21:39:51+00:00 Fixes for when HADDOCK_DOCS=NO - - - - - e92bfa42 by Ian Lynagh at 2010-09-29T21:15:38+00:00 Fix URL creation on Windows: Use / not \ in URLs. Fixes haskell/haddock#4353 - - - - - 66c55e05 by Ian Lynagh at 2010-09-30T17:03:34+00:00 Tidy up haddock symlink installation In particular, it now doesn't get created if we aren't installing haddock. - - - - - 549b5556 by Ian Lynagh at 2010-10-23T21:17:14+00:00 Follow extension-flattening change in GHC - - - - - d7c2f72b by David Waern at 2010-11-14T20:17:55+00:00 Bump version to 2.8.2 - - - - - 6989a3a9 by David Waern at 2010-11-14T20:26:01+00:00 Solve conflict - - - - - 055c6910 by Ian Lynagh at 2010-09-22T15:36:20+00:00 Bump GHC dep - - - - - c96c0763 by Simon Marlow at 2010-10-27T11:09:44+00:00 follow changes in the GHC API - - - - - 45907129 by David Waern at 2010-11-07T14:00:58+00:00 Update the HCAR entry - - - - - 61940b95 by David Waern at 2010-11-07T14:07:34+00:00 Make the HCAR entry smaller - - - - - aa590b7d by David Waern at 2010-11-14T21:30:59+00:00 Update HCAR entry with November 2010 version - - - - - 587f9847 by David Waern at 2010-11-14T23:48:17+00:00 Require ghc >= 7.0 - - - - - ff5c647c by David Waern at 2010-11-14T23:49:09+00:00 TAG 2.8.2 - - - - - 937fcb4f by David Waern at 2010-11-14T23:49:45+00:00 Solve conflict - - - - - 8e5d0c1a by David Waern at 2010-11-15T21:09:50+00:00 Remove code for ghc < 7 - - - - - 3d47b70a by David Waern at 2010-11-15T21:11:06+00:00 Fix bad merge - - - - - 7f4a0d8a by David Waern at 2010-11-15T21:13:57+00:00 Remove more ghc < 7 code - - - - - 9ee34b50 by David Waern at 2010-11-15T21:31:25+00:00 Match all AsyncExceptions in exception handler - - - - - 42849c70 by David Waern at 2010-11-15T21:35:31+00:00 Just say "internal error" instead of "internal Haddock or GHC error" - - - - - c88c809b by David Waern at 2010-11-15T21:44:19+00:00 Remove docNameOcc under the motto "don't name compositions" - - - - - b798fc7c by David Waern at 2010-11-15T23:27:13+00:00 Wibble - - - - - 2228197e by David Waern at 2010-11-15T23:28:24+00:00 Rename the HCAR entry file - - - - - 8a3f9090 by David Waern at 2010-11-16T00:05:29+00:00 Remove Haskell 2010 extensions from .cabal file - - - - - c7a0c597 by David Waern at 2010-11-16T00:10:28+00:00 Style wibbles - - - - - cde707a5 by David Waern at 2010-11-16T00:12:00+00:00 Remove LANGUAGE ForeignFunctionInterface pragmas - - - - - 1dbda8ed by David Waern at 2010-11-16T00:17:21+00:00 Make a little more use of DoAndIfThenElse - - - - - 4c45ff6e by David Waern at 2010-11-16T00:59:41+00:00 hlint police - - - - - d2feaf09 by David Waern at 2010-11-16T01:14:15+00:00 hlint police - - - - - 99876e97 by David Waern at 2010-11-20T19:06:00+00:00 Haddock documentation updates - - - - - 65ce6987 by David Waern at 2010-11-20T19:42:51+00:00 Follow the style guide closer in Haddock.Types and improve docs - - - - - 28ca304a by tob.brandt at 2010-11-20T17:04:40+00:00 add full qualification for undocumented names - - - - - d61341e3 by David Waern at 2010-11-20T20:04:15+00:00 Re-structure qualification code a little - - - - - 0057e4d6 by David Waern at 2010-11-20T20:07:55+00:00 Re-order functions - - - - - d7279afd by David Waern at 2010-11-21T03:39:54+00:00 Add BangPatterns to alex and happy source files - - - - - 629fe60e by tob.brandt at 2010-11-23T23:35:11+00:00 documentation for qualification - - - - - 37031cee by David Waern at 2010-11-23T21:06:44+00:00 Update CHANGES - don't mention 2.8.2, we won't release it - - - - - f2489e19 by David Waern at 2010-12-01T21:57:11+00:00 Update deps of runtests.hs to work with ghc 7.0.1 - - - - - d3657e9a by David Waern at 2010-12-01T22:04:57+00:00 Make tests compile with ghc 7.0.1 - - - - - a2f09d9b by David Waern at 2010-12-01T22:06:59+00:00 Update tests following version bump - - - - - 50883ebb by David Waern at 2010-12-06T14:09:18+00:00 Update tests following recent changes - - - - - fc2fadeb by David Waern at 2010-12-06T14:17:29+00:00 Add a flag --pretty-html for rendering indented html with newlines - - - - - 30832ef2 by David Waern at 2010-12-06T14:17:35+00:00 Use --pretty-html when running the test suite. Makes it easier to compare output - - - - - a0b81b31 by David Waern at 2010-12-06T14:18:27+00:00 Wibble - - - - - 3aaa23fe by David Waern at 2010-12-06T14:19:29+00:00 Haddockify ppHtml comments - - - - - 24bb24f0 by David Waern at 2010-12-06T14:23:15+00:00 Remove --debug. It was't used, and --verbosity should take its place - - - - - 6bc076e5 by David Waern at 2010-12-06T14:25:37+00:00 Rename golden-tests into html-tests. "golden tests" sounds strange - - - - - 53301e55 by David Waern at 2010-12-06T14:26:26+00:00 QUALI -> QUAL in the description --qual for consistency - - - - - 98b6affb by David Waern at 2010-12-06T21:54:02+00:00 Bump version - - - - - 371bf1b3 by David Waern at 2010-12-06T22:08:55+00:00 Update tests following version bump - - - - - 25be762d by David Waern at 2010-12-06T22:21:03+00:00 Update CHANGES - - - - - 7c7dac71 by David Waern at 2010-12-06T22:33:43+00:00 Update ANNOUNCE - - - - - 30d7a5f2 by Simon Peyton Jones at 2010-11-15T08:38:38+00:00 Alex generates BangPatterns, so make Lex.x accept them (It'd be better for Alex to generate this pragma.) - - - - - 605e8018 by Simon Marlow at 2010-11-17T11:37:24+00:00 Add {-# LANGUAGE BangPatterns #-} to mollify GHC - - - - - a46607ba by David Waern at 2010-12-07T14:08:10+00:00 Solve conflicts - - - - - b28cda66 by David Waern at 2010-12-09T20:41:35+00:00 Docs: Mention that \ is a special character in markup - - - - - a435bfdd by Ian Lynagh at 2010-11-17T14:01:19+00:00 TAG GHC 7.0.1 release - - - - - 5a15a05a by David Waern at 2010-12-11T17:51:19+00:00 Fix indentation problem - - - - - 4232289a by Lennart Kolmodin at 2010-12-17T18:32:03+00:00 Revise haddock.cabal given that we now require ghc-7 default-language should be Haskell2010, slight new semantics for extensions. Rewrite into clearer dependencies of base and Cabal. - - - - - a36302dc by David Waern at 2010-12-19T17:12:37+00:00 Update CHANGES - - - - - 7c8b85b3 by David Waern at 2010-12-19T17:14:24+00:00 Bump version - - - - - cff22813 by Ian Lynagh at 2011-01-05T18:24:27+00:00 Write hoogle output in utf8; fixes GHC build on Windows - - - - - c7e762ea by David Waern at 2011-01-22T00:00:35+00:00 Put title outside doc div when HTML:fying title+prologue Avoids indenting the title, and makes more sense since the title is not a doc string anyway. - - - - - 5f639054 by David Waern at 2011-01-22T16:09:44+00:00 Fix spelling error - contributed by Marco Silva - - - - - c11dce78 by Ian Lynagh at 2011-01-07T02:33:11+00:00 Follow GHC build system changes - - - - - 101cfaf5 by David Waern at 2011-01-08T14:06:44+00:00 Bump version - - - - - af62348b by David Waern at 2011-01-08T14:07:07+00:00 TAG 2.9.2 - - - - - 4d1f6461 by Ian Lynagh at 2011-01-07T23:06:57+00:00 Name the haddock script haddock-ghc-7.0.2 instead of haddock-7.0.2; haskell/haddock#4882 "7.0.2" looked like a haddock version number before - - - - - 8ee4d5d3 by Simon Peyton Jones at 2011-01-10T17:31:12+00:00 Update Haddock to reflect change in hs_tyclds field of HsGroup - - - - - 06f3e3db by Ian Lynagh at 2011-03-03T15:02:37+00:00 TAG GHC 7.0.2 release - - - - - 7de0667d by David Waern at 2011-03-10T22:47:13+00:00 Update CHANGES - - - - - 33a9f1c8 by David Waern at 2011-03-10T22:47:31+00:00 Fix build with ghc 7.0.1 - - - - - 4616f861 by David Waern at 2011-03-10T22:47:50+00:00 TAG 2.9.2-actual - - - - - 0dab5e3c by Simon Hengel at 2011-04-08T15:53:01+00:00 Set shell script for unit tests back to work - - - - - 85c54dee by Simon Hengel at 2011-04-08T16:01:24+00:00 Set unit tests back to work Here "ghci>" was still used instead of ">>>". - - - - - 1cea9b78 by Simon Hengel at 2011-04-08T16:25:36+00:00 Update runtests.hs for GHC 7.0.2 - - - - - 8e5b3bbb by Simon Hengel at 2011-04-08T16:28:49+00:00 Update Haddock version in *.html.ref - - - - - 2545e955 by Simon Hengel at 2011-04-08T17:09:28+00:00 Add support for blank lines in the result of examples Result lines that only contain the string "<BLANKLINE>" are treated as a blank line. - - - - - adf64d2e by Simon Hengel at 2011-04-08T17:36:50+00:00 Add documentation for "support for blank lines in the result of examples" - - - - - c51352ca by David Waern at 2011-05-21T23:57:56+00:00 Improve a haddock comment - - - - - 7419cf2c by David Waern at 2011-05-22T15:41:52+00:00 Use cabal's test suite support to run the test suite This gives up proper dependency tracking of the test script. - - - - - 7770070c by David Waern at 2011-05-22T01:45:44+00:00 We don't need to send DocOptions nor a flag to mkExportItems - - - - - 9d95b7b6 by David Waern at 2011-05-22T21:39:03+00:00 Fix a bug - - - - - 1f93699b by David Waern at 2011-05-22T21:40:21+00:00 Break out fullContentsOf, give it a better name and some documentation The documentation describes how we want this function to eventually behave, once we have fixed a few problems with the current implementation. - - - - - 9a86432f by David Waern at 2011-05-22T21:53:52+00:00 Fix some stylistic issues in mkExportItems - - - - - c271ff0c by David Waern at 2011-05-22T22:09:11+00:00 Indentation - - - - - 93e602b1 by David Waern at 2011-06-10T01:35:31+00:00 Add git commits since switchover: darcs format (followed by a conflict resolution): commit 6f92cdd12d1354dfbd80f8323ca333bea700896a Merge: f420cc4 28df3a1 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 19 17:54:34 2011 +0100 Merge remote branch 'origin/master' into ghc-generics commit 28df3a119f770fdfe85c687dd73d5f6712b8e7d0 Author: Max Bolingbroke <batterseapower at hotmail.com> Date: Sat May 14 22:37:02 2011 +0100 Unicode fix for getExecDir on Windows commit 89813e729be8bce26765b95419a171a7826f6d70 Merge: 6df3a04 797ab27 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 9 11:55:17 2011 +0100 Merge branch 'ghc-new-co' commit 6df3a040da3dbddee67c6e30a892f87e6b164383 Author: Ian Lynagh <igloo at earth.li> Date: Sun May 8 17:05:50 2011 +0100 Follow changes in SDoc commit f420cc48b9259f0b1afd2438b12f9a2bde57053d Author: Jose Pedro Magalhaes <jpm at cs.uu.nl> Date: Wed May 4 17:31:52 2011 +0200 Adapt haddock to the removal of HsNumTy and TypePat. commit 797ab27bdccf39c73ccad374fea265f124cb52ea Merge: 1d81436 5a91450 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:05:03 2011 +0100 Merge remote branch 'origin/master' into ghc-new-co commit 1d8143659a81cf9611668348e33fd0775c7ab1d2 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:03:46 2011 +0100 Wibbles for ghc-new-co branch commit 5a91450e2ea5a93c70bd3904b022445c9cc82488 Author: Ian Lynagh <igloo at earth.li> Date: Fri Apr 22 00:51:56 2011 +0100 Follow defaultDynFlags change in GHC - - - - - 498da5ae by David Waern at 2011-06-11T00:33:33+00:00 * Merge in git patch from Michal Terepeta >From 6fc71d067738ef4b7de159327bb6dc3d0596be29 Mon Sep 17 00:00:00 2001 From: Michal Terepeta <michal.terepeta at gmail.com> Date: Sat, 14 May 2011 19:18:22 +0200 Subject: [PATCH] Follow the change of TypeSig in GHC. This follows the change in GHC to make TypeSig take a list of names (instead of just one); GHC ticket haskell/haddock#1595. This should also improve the Haddock output in case the user writes a type signature that refers to many names: -- | Some comment.. foo, bar :: ... will now generate the expected output with one signature for both names. - - - - - 094607fe by Ian Lynagh at 2011-06-17T19:10:29+01:00 Fix build - - - - - 8fa35740 by Ian Lynagh at 2011-06-26T21:06:40+01:00 Bump GHC dep to allow 7.2 - - - - - e4d2ca3c by Ian Lynagh at 2011-07-07T23:06:28+01:00 Relax base dep - - - - - b948fde9 by Ian Lynagh at 2011-07-28T16:39:45+01:00 GHC build system: Don't install the datafiles twice - - - - - f82f6d70 by Simon Marlow at 2011-08-11T12:08:15+01:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - b341cc12 by Max Bolingbroke at 2011-08-22T20:25:27+01:00 Fix compilation with no-pred-ty GHC - - - - - 30494581 by Max Bolingbroke at 2011-08-23T10:20:54+01:00 Remaining fixes for PredTy removal - - - - - 0b197138 by Max Bolingbroke at 2011-08-26T08:27:45+01:00 Rename factKind to constraintKind - - - - - a379bec5 by Max Bolingbroke at 2011-09-04T12:54:47+01:00 Deal with change to IParam handling in GHC - - - - - f94e421b by Max Bolingbroke at 2011-09-06T17:34:31+01:00 Adapt Haddock for the ConstraintKind extension changes - - - - - 8821e5cc by Max Bolingbroke at 2011-09-09T08:24:59+01:00 Ignore associated type defaults (just as we ignore default methods) - - - - - 31a0afd4 by Max Bolingbroke at 2011-09-09T09:06:00+01:00 Merge branch 'no-pred-ty' of ssh://darcs.haskell.org/srv/darcs/haddock into no-pred-ty - - - - - dd3b530a by Max Bolingbroke at 2011-09-09T14:10:25+01:00 Merge branch 'no-pred-ty' Conflicts: src/Haddock/Convert.hs - - - - - 5f25ec96 by Max Bolingbroke at 2011-09-09T14:10:40+01:00 Replace FactTuple with ConstraintTuple - - - - - cd30b9cc by David Waern at 2011-09-26T02:17:55+02:00 Bump to version 2.9.3 - - - - - 4fbfd397 by Max Bolingbroke at 2011-09-27T14:55:21+01:00 Follow changes to BinIface Name serialization - - - - - 92257d90 by David Waern at 2011-09-30T23:45:07+02:00 Fix problem with test files not added to distribution tarball - - - - - 00255bda by David Waern at 2011-09-30T23:48:24+02:00 Merge branch 'development' - - - - - 5421264f by David Waern at 2011-10-01T01:25:39+02:00 Merge in darcs patch from Simon Meier: Wed Jun 1 19:41:16 CEST 2011 iridcode at gmail.com * prettier haddock coverage info The new coverage info rendering uses less horizontal space. This reduces the number of unnecessary line-wrappings. Moreover, the most important information, how much has been documented already, is now put up front. Hopefully, this makes it more likely that a library author is bothered by the low coverage of his modules and fixes that issue ;-) - - - - - 07d318ef by David Waern at 2011-10-01T01:34:10+02:00 Use printException instead of deprecated printExceptionAndWarnings - - - - - 40d52ee4 by David Waern at 2011-10-01T01:41:13+02:00 Merge in darcs pach: Mon Apr 11 18:09:54 JST 2011 Liyang HU <haddock at liyang.hu> * Remember collapsed sections in index.html / haddock-util.js - - - - - 279d6dd4 by David Waern at 2011-10-01T01:55:45+02:00 Merge in darcs patch: Joachim Breitner <mail at joachim-breitner.de>**20110619201645 Ignore-this: f6c51228205b0902ad5bfad5040b989a As reported on http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=578301, generating the global index takes much too long if type-level (with lots of auto-generated types) is installed. The patch avoids a quadratic runtime in the subfunction getIfaceIndex of ppHtmlIndex by using a temporary set. Runtime improvement observed here from 25.36s to 2.86s. - - - - - d1612383 by David Waern at 2011-10-01T01:56:48+02:00 Merge branch 'development' - - - - - 347520c1 by David Waern at 2011-10-01T01:56:54+02:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9a0c95e8 by David Waern at 2011-10-01T02:19:10+02:00 Improve .cabal file - - - - - 6967dc64 by Ian Lynagh at 2011-10-01T01:34:06+01:00 Follow changes to ForeignImport/ForeignExport in GHC - - - - - 565cb26b by Simon Marlow at 2011-10-04T00:15:04+02:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - 8b74f512 by David Waern at 2011-10-04T00:18:17+02:00 Requre ghc >= 7.2 - - - - - 271d360c by David Waern at 2011-10-04T00:22:50+02:00 Bump version to 2.9.4 - - - - - 37f3edb0 by David Waern at 2011-10-06T02:30:21+02:00 Add alex and happy to build-tools. - - - - - 7ac2bb6e by David Terei at 2011-10-12T14:02:55-07:00 Add safe haskell indication to haddock output - - - - - 42c91a47 by David Terei at 2011-10-12T14:06:03-07:00 Fix CSS issue with info table not being contained in module header - - - - - 0eddab6c by David Terei at 2011-10-12T14:06:58-07:00 Add safe haskell indication to haddock output - - - - - 3df058eb by David Terei at 2011-10-12T14:07:07-07:00 Fix CSS issue with info table not being contained in module header - - - - - a40a6c3f by David Waern at 2011-10-22T11:29:06+02:00 Bump .haddock file version since the format has changed recently - - - - - 8a6254be by David Waern at 2011-10-22T11:30:42+02:00 Merge branch 'development' - - - - - 642e3e02 by David Waern at 2011-10-23T21:23:39+02:00 Sort import list - - - - - 36371cf8 by David Waern at 2011-10-23T22:48:18+02:00 Remove NEW_GHC_LAYOUT conditional. - - - - - 5604b499 by David Waern at 2011-10-27T00:15:03+02:00 Add --print-ghc-path. - - - - - 463499fa by David Waern at 2011-10-27T00:16:22+02:00 Make testsuite able to find its dependencies automatically. - - - - - a3506172 by Ryan Newton at 2011-11-05T05:59:58-04:00 Improved declNames internal error. Added a case to handle DocD. - - - - - 001b8baf by David Waern at 2011-11-05T20:37:29+01:00 Rename copy.hs -> accept.hs. - - - - - 55d808d3 by David Waern at 2011-11-05T23:30:02+01:00 Fix build. - - - - - deb5c3be by David Waern at 2011-11-06T00:01:47+01:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9b663554 by David Waern at 2011-11-06T00:03:45+01:00 Merge https://github.com/rrnewton/haddock - - - - - 1abb0ff6 by David Waern at 2011-11-06T01:20:37+01:00 Use getDeclMainBinder instead of declNames. - - - - - 4b005c01 by David Waern at 2011-11-06T19:09:53+01:00 Fix build. - - - - - c2c51bc7 by Ian Lynagh at 2011-11-06T23:01:33+00:00 Remove -DNEW_GHC_LAYOUT in ghc.mk - - - - - f847d703 by Jose Pedro Magalhaes at 2011-11-11T09:07:39+00:00 New kind-polymorphic core This big patch implements a kind-polymorphic core for GHC. The current implementation focuses on making sure that all kind-monomorphic programs still work in the new core; it is not yet guaranteed that kind-polymorphic programs (using the new -XPolyKinds flag) will work. For more information, see http://haskell.org/haskellwiki/GHC/Kinds - - - - - 7d7c3b09 by Jose Pedro Magalhaes at 2011-11-16T21:42:22+01:00 Follow changes to tuple sorts in master - - - - - 8430e03e by Simon Peyton Jones at 2011-11-17T10:20:27+00:00 Remove redundant imports - - - - - d1b06832 by Ian Lynagh at 2011-11-19T01:33:21+00:00 Follow GHC build system change to the way we call rm - - - - - 9e2230ed by David Waern at 2011-11-24T15:00:24+01:00 Fix a bug in test runner and get rid of regex-compat dependency. - - - - - 52039b21 by David Waern at 2011-11-24T23:55:36+01:00 Avoid haskell98 dependency in test - - - - - 92e1220d by David Waern at 2011-11-25T00:03:33+01:00 Avoid depency on regex-compat also in accept.hs. - - - - - ddac6b6f by David Waern at 2011-11-25T02:13:38+01:00 Accept test output. - - - - - 5a720455 by David Waern at 2011-11-25T02:16:20+01:00 Some more changes to test scripts. - - - - - 170a9004 by David Waern at 2011-11-25T02:30:41+01:00 Add flag --interface-version. - - - - - d225576c by David Waern at 2011-11-25T02:39:26+01:00 Remove #ifs for older compiler versions. - - - - - f0d0a4f5 by David Waern at 2011-11-26T04:20:12+01:00 Give preference to type over data constructors for doc comment links at renaming time. Previously this was done in the backends. Also, warn when a doc comment refers to something that is in scope but which we don't have the .haddock file for. These changes mean we can make DocIdentifier [a] into DocIdentifier a. - - - - - eef0e776 by David Waern at 2011-11-26T17:01:06+01:00 Allow doc comments to link to out-of-scope things (#78). (A bug that should have been fixed long ago.) - - - - - 565ad529 by David Waern at 2011-11-26T19:56:21+01:00 Update tests. - - - - - fb3ce7b9 by David Waern at 2011-11-26T21:44:28+01:00 Cleanup. - - - - - d0328126 by David Waern at 2011-11-26T22:10:28+01:00 Fix module reference bug. - - - - - c03765f8 by David Waern at 2011-12-03T05:20:20+01:00 Slightly better behaviour on top-levels without type signatures. - Docs don't get attached to the next top-level with signature by mistake. - If there's an export list and the top-level is part of it, its doc comment shows up in the documentation. - - - - - 48461d31 by David Waern at 2011-12-03T05:38:10+01:00 Add a test for Unicode doc comments. - - - - - 549c4b4e by David Waern at 2011-12-03T19:07:55+01:00 Cleanup. - - - - - 7bfecf91 by David Waern at 2011-12-03T20:13:08+01:00 More cleanup. - - - - - 14fab722 by Ian Lynagh at 2011-12-12T21:21:35+00:00 Update dependencies and binaryInterfaceVersion - - - - - 469e6568 by Ian Lynagh at 2011-12-18T12:56:16+00:00 Fix (untested) building from source tarball without alex/happy haddock's .cabal file was declaring that it needed alex and happy to build, but in the GHC source tarballs it doesn't. - - - - - 895c9a8c by David Waern at 2011-12-27T12:57:43+01:00 Go back to having a doc, sub and decl map instead of one big decl map. This setup makes more sense since when we add value bindings to the processed declarations (for type inference), we will have multiple declarations which should share documentation. Also, we already have a separate doc map for instances which we can now merge into the main doc map. Another benefit is that we don't need the DeclInfo type any longer. - - - - - 736767d9 by David Waern at 2011-12-27T13:33:41+01:00 Merge ../../../haddock Conflicts: src/Haddock/InterfaceFile.hs - - - - - 20016f79 by David Waern at 2011-12-27T13:57:23+01:00 Bump version. - - - - - 31f276fb by David Waern at 2011-12-27T13:57:32+01:00 Merge ../ghc/utils/haddock - - - - - 95b367cd by David Waern at 2011-12-27T14:57:29+01:00 Update tests following version bump. - - - - - fa3c94cd by David Waern at 2011-12-27T14:57:51+01:00 Get rid of quite unnecessary use of different lists. - - - - - 9c4d3c54 by David Waern at 2011-12-27T15:26:42+01:00 Cleanup. - - - - - 2caf9f90 by David Waern at 2011-12-27T16:18:05+01:00 Wibbles. - - - - - 3757d09b by David Waern at 2011-12-27T20:50:26+01:00 Complete support for inferring types for top-level bindings. - - - - - 53418734 by David Waern at 2011-12-28T15:02:13+01:00 Minor fixes and cleanup. - - - - - 0c9d0385 by Ian Lynagh at 2012-01-03T18:31:29+00:00 Follow rename of Instance to ClsInst in GHC - - - - - c9bc969a by Simon Hengel at 2012-01-12T21:28:14+01:00 Make sure that generated xhtml is valid (close haskell/haddock#186) Thanks to Phyx. - - - - - 836a0b9a by David Waern at 2012-02-01T02:30:05+01:00 Fix bug introduced in my recent refactoring. - - - - - c7d733eb by David Waern at 2012-02-01T02:30:26+01:00 Cleanup mkMaps and avoid quadratic behaviour. - - - - - da3cda8f by David Waern at 2012-02-01T02:56:56+01:00 Require ghc >= 7.4. - - - - - 83a3287e by David Waern at 2012-02-01T02:57:36+01:00 Update CHANGES. - - - - - 93408f0b by Simon Hengel at 2012-02-04T00:48:04+01:00 Add reference renderings - - - - - 49d00d2c by Simon Hengel at 2012-02-04T00:48:25+01:00 Set unit tests for parser back to work - - - - - eb450980 by Simon Hengel at 2012-02-04T00:49:07+01:00 Add .gitignore - - - - - a841602c by Simon Hengel at 2012-02-04T00:49:16+01:00 Add .ghci file - - - - - 8861199d by Simon Hengel at 2012-02-04T00:49:29+01:00 tests/html-tests/copy.hs: Use mapM_ instead of mapM So we do net get a list of () on stdout when running with runhaskell. - - - - - b477d9b5 by Simon Hengel at 2012-02-04T00:49:46+01:00 Remove index files from golden tests - - - - - 9dbda34e by Simon Hengel at 2012-02-04T00:49:57+01:00 Add /tests/html-tests/tests/*index*.ref to .gitignore - - - - - a9434817 by Simon Hengel at 2012-02-04T00:50:04+01:00 Add DocWarning to Doc The Xhtml backend has special markup for that, Hoogle and LaTeX reuse what we have for DocEmphasis. - - - - - de2fb6fa by Simon Hengel at 2012-02-04T00:50:13+01:00 Add support for module warnings - - - - - 0640920e by Simon Hengel at 2012-02-04T00:50:21+01:00 Add tests for module warnings - - - - - 30ce0d77 by Simon Hengel at 2012-02-04T00:50:29+01:00 Add support for warnings - - - - - bb367960 by Simon Hengel at 2012-02-04T00:50:37+01:00 Add tests for warnings - - - - - 6af1dc2d by Simon Hengel at 2012-02-04T00:50:50+01:00 Expand type signatures in export list (fixes haskell/haddock#192) - - - - - a06cbf25 by Simon Hengel at 2012-02-04T00:51:04+01:00 Expand type signatures for modules without explicit export list - - - - - 57dda796 by Simon Hengel at 2012-02-04T00:51:15+01:00 Remove obsolete TODO - - - - - 270c3253 by David Waern at 2012-02-04T00:51:24+01:00 Fix issues in support for warnings. * Match against local names only. * Simplify (it's OK to map over the warnings). - - - - - 683634bd by David Waern at 2012-02-04T00:55:11+01:00 Some cleanup and make sure we filter warnings through exports. - - - - - 210cb4ca by David Waern at 2012-02-04T03:01:30+01:00 Merge branch 'fix-for-186' of https://github.com/sol/haddock into ghc-7.4 - - - - - e8db9031 by David Waern at 2012-02-04T03:07:51+01:00 Style police. - - - - - 261f9462 by David Waern at 2012-02-04T03:20:16+01:00 Update tests. - - - - - 823cfc7c by David Waern at 2012-02-04T03:21:12+01:00 Use mapM_ in accept.hs as well. - - - - - 873dd619 by David Waern at 2012-02-04T03:21:33+01:00 Remove copy.hs - use accept.hs instead. - - - - - 0e31a14a by David Waern at 2012-02-04T03:47:33+01:00 Use <> instead of mappend. - - - - - 2ff7544f by David Waern at 2012-02-04T03:48:55+01:00 Remove code for older ghc versions. - - - - - dacf2786 by David Waern at 2012-02-04T15:52:51+01:00 Clean up some code from last SoC project. - - - - - 00cbb117 by David Waern at 2012-02-04T21:43:49+01:00 Mostly hlint-inspired cleanup. - - - - - 7dc86cc2 by Simon Peyton Jones at 2012-02-06T09:14:41+00:00 Track changes in HsDecls - - - - - f91f82fe by Ian Lynagh at 2012-02-16T13:40:11+00:00 Follow changes in GHC caused by the CAPI CTYPE pragma - - - - - a0ea6b0b by Ian Lynagh at 2012-02-22T02:26:12+00:00 Follow changes in GHC - - - - - b23b07d1 by Simon Peyton Jones at 2012-03-02T16:36:41+00:00 Follow changes in data representation from the big PolyKinds commit - - - - - 43406022 by Simon Hengel at 2012-03-05T11:18:34+01:00 Save/restore global state for static flags when running GHC actions This is necessary if we want to run createInterfaces (from Documentation.Haddock) multiple times in the same process. - - - - - 9fba16fe by Paolo Capriotti at 2012-03-06T10:57:33+00:00 Update .gitignore. - - - - - a9325044 by Simon Peyton Jones at 2012-03-14T17:35:42+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - fd48065a by Iavor Diatchki at 2012-03-15T22:43:35-07:00 Add support for type-level literals. - - - - - 2e8206dd by Simon Peyton Jones at 2012-03-16T14:18:22+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - 93e13319 by Simon Peyton Jones at 2012-03-17T01:04:05+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock Conflicts: src/Haddock/Convert.hs - - - - - d253fa71 by Iavor Diatchki at 2012-03-19T20:12:18-07:00 Merge remote-tracking branch 'origin/master' into type-nats - - - - - fc40acc8 by Iavor Diatchki at 2012-03-19T20:31:27-07:00 Add a missing case for type literals. - - - - - fd2ad699 by Iavor Diatchki at 2012-03-24T13:28:29-07:00 Rename variable to avoid shadowing warning. - - - - - 9369dd3c by Simon Peyton Jones at 2012-03-26T09:14:23+01:00 Follow refactoring of TyClDecl/HsTyDefn - - - - - 38825ca5 by Simon Peyton Jones at 2012-03-26T09:14:37+01:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - 4324ac0f by David Waern at 2012-04-01T01:51:19+02:00 Disable unicode test. - - - - - 3165b750 by David Waern at 2012-04-01T01:51:34+02:00 Take reader environment directly from TypecheckedSource. - - - - - 213b644c by David Waern at 2012-04-01T01:55:20+02:00 Cleanup. - - - - - 3118b4ba by David Waern at 2012-04-01T02:16:15+02:00 Don't filter out unexported names from the four maps - fixes a regression. - - - - - d6524e17 by David Waern at 2012-04-01T02:40:34+02:00 Fix crash when using --qual. Naughty GHC API! - - - - - ea3c43d8 by Henning Thielemann at 2012-04-01T13:03:07+02:00 add QualOption type for distinction between qualification argument given by the user and the actual qualification for a concrete module - - - - - 5422ff05 by Henning Thielemann at 2012-04-01T16:25:02+02:00 emit an error message when the --qual option is used incorrectly - - - - - 026e3404 by David Waern at 2012-04-01T18:10:30+02:00 Don't crash on unicode strings in doc comments. - - - - - ce006632 by David Waern at 2012-04-01T20:13:35+02:00 Add test for --ignore-all-exports flag/ignore-exports pragma. - - - - - 6e4dd33c by David Waern at 2012-04-01T20:21:03+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.4 - - - - - 734ae124 by Henning Thielemann at 2012-04-01T20:22:10+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - 622f9ba5 by David Waern at 2012-04-01T21:26:13+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 55ce17cb by Henning Thielemann at 2012-04-01T22:03:25+02:00 'abbreviate' qualification style - basic support Currently we ignore the package a module is imported from. This means that a module import would shadow another one with the same module name from a different package. - - - - - c85314ef by David Waern at 2012-04-01T22:05:12+02:00 Check qualification option before processing modules. - - - - - ae4b626c by Henning Thielemann at 2012-04-02T00:19:36+02:00 abbreviated qualification: use Packages.lookupModuleInAllPackages for finding the package that a module belongs to - - - - - 60bdbcf5 by Henning Thielemann at 2012-04-02T00:25:31+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - df44301d by Henning Thielemann at 2012-04-02T00:29:05+02:00 qualification style 'abbreviated' -> 'aliased' - - - - - f4192a64 by David Waern at 2012-04-02T01:05:47+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 7ba09067 by David Terei at 2012-04-04T15:08:21-07:00 Fix reporting of modules safe haskell mode (#5989) - - - - - d0cc33d0 by David Terei at 2012-04-06T15:50:41+01:00 Fix reporting of modules safe haskell mode (#5989) - - - - - 6e3434c5 by Simon Peyton Jones at 2012-04-20T18:37:46+01:00 Track changes in HsSyn - - - - - 22014ed0 by Simon Peyton Jones at 2012-05-11T22:45:15+01:00 Follow changes to LHsTyVarBndrs - - - - - d9a07b24 by David Waern at 2012-05-15T01:46:35+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - a6c4ebc6 by David Waern at 2012-05-16T02:18:32+02:00 Update CHANGES. - - - - - 8e181d29 by David Waern at 2012-05-16T02:27:56+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - e358210d by David Waern at 2012-05-16T02:35:33+02:00 Mention the new aliased --qual mode in CHANGES. - - - - - efd36a28 by David Waern at 2012-05-16T21:33:13+02:00 Bump version number. - - - - - d6b3af14 by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for deprecated record field - - - - - 927f800e by Simon Hengel at 2012-05-17T19:08:20+02:00 Use >>= instead of fmap and join - - - - - 048b41d5 by Simon Hengel at 2012-05-17T19:08:20+02:00 newtype-wrap Doc nodes for things that may have warnings attached - - - - - e3a89fc3 by Simon Hengel at 2012-05-17T19:08:20+02:00 Attach warnings to `Documentation` type - - - - - 5d4cc43d by Simon Hengel at 2012-05-17T19:08:20+02:00 Simplify lookupWarning - - - - - cf8ae69d by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for haskell/haddock#205 - - - - - cb409b19 by Simon Peyton Jones at 2012-05-25T08:30:11+01:00 Follow changes in LHsTyVarBndrs - - - - - 2d5f4179 by Simon Hengel at 2012-05-26T19:21:29+02:00 Add Applicative instance for (GenRnM a) - - - - - e4373060 by Simon Hengel at 2012-05-26T19:21:33+02:00 Use a map for warnings, as suggested by @waern - - - - - 597a68c7 by Simon Hengel at 2012-05-27T08:48:24+02:00 Add an optional label to URLs - - - - - ef1ac7fe by Simon Hengel at 2012-05-27T08:48:24+02:00 Add support for hyperlink labels to parser - - - - - 41f2adce by Simon Hengel at 2012-05-27T08:48:24+02:00 Add golden test for hyperlinks - - - - - 83d5e764 by Simon Hengel at 2012-05-27T08:50:02+02:00 Use LANGUAGE pragmas instead of default-extensions in cabal file - - - - - ddb755e5 by Simon Hengel at 2012-05-27T08:50:02+02:00 Fix typo in comment - - - - - 110676b4 by Simon Hengel at 2012-05-27T08:50:02+02:00 Add a type signature for a where-binding - - - - - 7d9ba2a0 by Ian Lynagh at 2012-06-12T14:38:01+01:00 Follow changes in GHC - - - - - 47c704f2 by Ian Lynagh at 2012-06-12T18:52:16+01:00 Follow changes in GHC - - - - - e1efe1ab by Simon Peyton Jones at 2012-06-13T17:25:29+01:00 Follow changes for the implementation of implicit parameters - - - - - 69abc81c by Ian Lynagh at 2012-06-19T22:52:58+01:00 Follow changes in base - - - - - 9d074a21 by Paolo Capriotti at 2012-06-22T18:26:47+01:00 Use right docMap to get decl documentation. - - - - - e3292ef6 by Ian Lynagh at 2012-07-15T01:31:19+01:00 Follow changes in GHC - - - - - ceae56b0 by Ian Lynagh at 2012-07-16T21:22:48+01:00 Fix haddock following some GHC changes Passing _|_ as the Settings for defaultDynFlags no longer works well enough - - - - - 9df72735 by Paolo Capriotti at 2012-07-19T16:49:32+01:00 Forward port changes from stable. - - - - - 572f5fcf by Ian Lynagh at 2012-07-19T20:38:26+01:00 Merge branch 'master' of darcs.haskell.org:/srv/darcs//haddock - - - - - 9195aca4 by Paolo Capriotti at 2012-07-20T10:27:28+01:00 Update dependencies. - - - - - 33db3923 by Ian Lynagh at 2012-07-20T17:54:43+01:00 Build with GHC 7.7 - - - - - 925a2cea by David Waern at 2012-07-23T16:50:40+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.6 Conflicts: src/Haddock/InterfaceFile.hs - - - - - d710ef97 by David Waern at 2012-07-23T16:52:07+02:00 Bump version number. - - - - - eb0c2f83 by David Waern at 2012-07-23T16:57:58+02:00 Update CHANGES. - - - - - b3f56943 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Hide "internal" instances This fixes haskell/haddock#37 (http://trac.haskell.org/haddock/ticket/37) Precisely, we show an instance iff its class and all the types are exported by non-hidden modules. - - - - - a70aa412 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Tests for hiding instances (#37) - - - - - c0f4aa58 by Simon Hengel at 2012-07-27T13:00:13+03:00 Add an other test for hiding instances (#37) - - - - - a7ed6268 by Ian Lynagh at 2012-08-07T14:48:13+01:00 Follow changes in GHC - - - - - 0ab30d38 by Ian Lynagh at 2012-08-13T22:12:27+01:00 Improve haddock memory usage - - - - - 0eaa4e30 by Ian Lynagh at 2012-08-13T23:58:46+01:00 Improve haddock memory usage - - - - - 659d26cf by Ian Lynagh at 2012-08-14T13:16:48+01:00 Remove some temporary pragmas I accidentally recorded - - - - - d97fceb6 by Simon Hengel at 2012-08-25T13:19:34+02:00 Add missing dependency to library - - - - - 4c910697 by Simon Hengel at 2012-08-28T07:39:14+02:00 Move .ghci to project root - - - - - fc3c601a by Simon Hengel at 2012-08-28T07:39:14+02:00 accept.hs: Ignore some files - - - - - 1af9b984 by Simon Hengel at 2012-08-28T07:40:04+02:00 Update reference renderings (bump version) - - - - - 980dc253 by Simon Hengel at 2012-08-28T07:40:32+02:00 Update reference renderings (remove links for ()) - - - - - 33651dbf by Simon Hengel at 2012-08-28T07:41:50+02:00 Update documentation of `runInteractiveProcess` in reference rendering - - - - - 7ab25078 by David Waern at 2012-09-07T10:38:50+02:00 Merge branch 'hiddenInstances2' of http://github.com/feuerbach/haddock into ghc-7.6 - - - - - c3de3a4b by David Waern at 2012-09-07T14:29:27+02:00 Follow changes in GHC. - - - - - 298c43ac by David Waern at 2012-09-07T14:59:24+02:00 Update CHANGES. - - - - - e797993a by David Waern at 2012-09-07T15:21:30+02:00 Update ANNOUNCE. - - - - - d0b44790 by David Waern at 2012-09-07T15:22:43+02:00 Merge branch 'hidden-instances' into ghc-7.6 - - - - - 41a4adc8 by Simon Hengel at 2012-09-08T12:08:37+02:00 Update doc/README - - - - - 71ad1040 by Simon Hengel at 2012-09-08T12:17:17+02:00 Add documentation for URL labels - - - - - 9bb41afd by Simon Peyton Jones at 2012-09-20T18:14:26+01:00 Follow data type changes in the tc-untouchables branch Relating entirely to SynTyConRhs - - - - - b8139bfa by Simon Hengel at 2012-09-21T14:24:16+02:00 Disable Unicode test for now - - - - - a5fafdd7 by Simon Hengel at 2012-09-21T14:35:45+02:00 Update TypeOperators test for GHC 7.6.1 Type operators can't be used as type variables anymore! - - - - - 6ccf0025 by Simon Hengel at 2012-09-21T16:02:24+02:00 Remove (Monad (Either e)) instance from ref. rendering of CrossPackageDocs I do not really understand why the behavior changed, so I'll open a ticket, so that we can further investigate. - - - - - b5c6c138 by Ian Lynagh at 2012-09-27T02:00:57+01:00 Follow changes in GHC build system - - - - - b98eded0 by David Waern at 2012-09-27T15:37:02+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 76cc2051 by David Waern at 2012-09-27T15:48:19+02:00 Update hidden instances tests. - - - - - aeaa1c59 by David Waern at 2012-09-28T10:21:32+02:00 Make API buildable with GHC 7.6. - - - - - d76be1b0 by Simon Peyton Jones at 2012-09-28T15:57:05+01:00 Merge remote-tracking branch 'origin/master' into tc-untouchables - - - - - a1922af8 by David Waern at 2012-09-28T19:50:20+02:00 Fix spurious superclass constraints bug. - - - - - bc41bdbb by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove old examples - - - - - bed7d3dd by Simon Hengel at 2012-10-01T11:30:51+02:00 Adapt parsetests for GHC 7.6.1 - - - - - dcdb22bb by Simon Hengel at 2012-10-01T11:30:51+02:00 Add test-suite section for parsetests to cabal file + get rid of HUnit dependency - - - - - 1e5263c9 by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove test flag from cabal file This was not really used. - - - - - 4beee98b by David Waern at 2012-09-28T23:42:28+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 11dd2256 by Ian Lynagh at 2012-10-03T16:17:35+01:00 Follow change in GHC build system - - - - - fbd77962 by Simon Hengel at 2012-10-03T18:49:40+02:00 Remove redundant dependency from cabal file - - - - - 09218989 by Simon Hengel at 2012-10-04T16:03:05+02:00 Fix typo - - - - - 93a2d5f9 by Simon Hengel at 2012-10-04T16:11:41+02:00 Remove trailing whitespace from cabal file - - - - - c8b46cd3 by Simon Hengel at 2012-10-04T16:12:17+02:00 Export Haddock's main entry point from library - - - - - b411e77b by Simon Hengel at 2012-10-04T16:29:46+02:00 Depend on library for executable The main motivation for this is to increase build speed. In GHC's source tree the library is not build, but all modules are now required for the executable, so that GHC's validate will now detect build failures for the library. - - - - - f8f0979f by Simon Hengel at 2012-10-05T00:32:57+02:00 Set executable flag for Setup.lhs - - - - - dd045998 by Simon Hengel at 2012-10-07T16:44:06+02:00 Extend rather than set environment when running HTML tests On some platforms (e.g. ppc64) GHC requires gcc in the path. - - - - - 7b39c3ae by Simon Hengel at 2012-10-07T17:05:45+02:00 cross-package test: re-export IsString instead of Monad There is a monad instance for Q, which is not available on platforms that do not have GHCi support. This caused CrossPackageDocs to fail on those platforms. Re-exporting IsString should test the same thing, but it works on all platforms. - - - - - 0700c605 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Fix some warnings - - - - - f78eca79 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Make -Wall proof - - - - - 6beec041 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Use listToMaybe/fromMaybe instead of safeHead/maybe - - - - - 44b8ce86 by Ian Lynagh at 2012-10-08T21:59:46+01:00 Follow changes in GHC - - - - - 6da5f702 by Simon Hengel at 2012-10-09T11:16:19+02:00 Update .ghci - - - - - 9ac1a1b9 by Kazu Yamamoto at 2012-10-09T12:45:31+02:00 Add markup support for properties - - - - - 1944cb42 by Simon Hengel at 2012-10-09T12:45:31+02:00 Simplify lexing/parsing of properties In contrast to what we do for examples, we do not really need to capture the "prompt" here. - - - - - bffd8e62 by Simon Hengel at 2012-10-09T13:40:14+02:00 Add HTML test for properties - - - - - 2fe9c5cb by Simon Hengel at 2012-10-09T13:40:21+02:00 Add unit tests for properties - - - - - 874e361b by Simon Hengel at 2012-10-09T13:40:33+02:00 Bump interface version - - - - - 2506cc37 by Simon Hengel at 2012-10-09T15:15:04+02:00 Fix parser bug - - - - - 743d2b7d by Simon Hengel at 2012-10-09T15:31:06+02:00 Allow to load interface files with compatible versions - - - - - 981a1660 by Simon Hengel at 2012-10-10T10:32:05+02:00 Export more types from Documentation.Haddock (fixes haskell/haddock#216) - - - - - dff7dc76 by Simon Hengel at 2012-10-10T11:15:19+02:00 Update ANNOUNCE and CHANGES - - - - - edd2bb01 by Simon Hengel at 2012-10-10T11:22:50+02:00 Bump version - - - - - 5039163b by Simon Hengel at 2012-10-10T13:56:04+02:00 Fix typo in documentation - - - - - e4ce34da by Simon Hengel at 2012-10-10T14:28:35+02:00 Add documentation for properties - - - - - 9555ebca by Simon Hengel at 2012-10-11T10:49:04+02:00 Remove redundant if-defs, more source documentation - - - - - 87aa67e1 by Simon Hengel at 2012-10-11T12:32:51+02:00 Adapt cabal file - - - - - c44c1dee by Simon Hengel at 2012-10-11T12:41:58+02:00 Require ghc 7.6 - - - - - 8383bc34 by Simon Hengel at 2012-10-11T12:50:24+02:00 Bump version - - - - - 1030eb38 by Simon Hengel at 2012-10-11T12:55:44+02:00 Update ANNOUNCE and CHANGES - - - - - 74955088 by Simon Hengel at 2012-10-12T09:49:31+02:00 Improve note about `binaryInterfaceVersion` (thanks David) - - - - - ee30f6b7 by Simon Hengel at 2012-10-13T13:40:59+02:00 Update version in html tests, rpm spec file, and user manual - - - - - f2861f18 by Simon Hengel at 2012-10-13T14:40:33+02:00 Remove unused MonadFix constraint - - - - - dfdf1a74 by Simon Hengel at 2012-10-13T15:15:38+02:00 Minor code simplification - - - - - 4ecd1e70 by Simon Hengel at 2012-10-13T15:33:43+02:00 Increase code locality - - - - - f7df5cc9 by Simon Hengel at 2012-10-13T16:03:12+02:00 Minor code simplification - - - - - e737eb6e by Simon Hengel at 2012-10-13T19:03:04+02:00 Handle HsExplicitListTy in renameer (fixes haskell/haddock#213) - - - - - c2dc8f17 by Simon Hengel at 2012-10-13T20:46:31+02:00 Better error messages - - - - - 14d48b4c by Simon Hengel at 2012-10-14T00:21:07+02:00 Simplify RnM type - - - - - 6c2cc547 by Simon Hengel at 2012-10-14T00:23:35+02:00 Simplify lookupRn - - - - - bc77ce85 by Simon Hengel at 2012-10-14T01:51:32+02:00 Organize unite tests hierarchically - - - - - 2306d117 by Simon Hengel at 2012-10-14T10:34:58+02:00 Handle more cases in renameType - - - - - 8a864203 by Simon Hengel at 2012-10-14T11:47:59+02:00 Add mini_HiddenInstances.html.ref and mini_HiddenInstancesB.html.ref - - - - - 3a978eca by Simon Hengel at 2012-10-14T11:49:28+02:00 Add /tests/html-tests/output/ to .gitignore - - - - - db18888a by Simon Hengel at 2012-10-14T13:38:21+02:00 Allow haddock markup in deprecation messages - - - - - e7cfee9f by Simon Hengel at 2012-10-14T14:00:23+02:00 If parsing of deprecation message fails, include it verbatim - - - - - 242a85be by Simon Hengel at 2012-10-14T14:13:24+02:00 Add description for PruneWithWarning test - - - - - 43d33df1 by Simon Hengel at 2012-10-14T15:40:53+02:00 Minor formatting change - - - - - 22768c44 by Simon Hengel at 2012-10-14T16:03:43+02:00 Properly handle deprecation messages for re-exported things (fixes haskell/haddock#220) - - - - - cb4b9111 by Simon Hengel at 2012-10-14T17:30:28+02:00 Add build artifacts for documentation to .gitignore - - - - - 854cd8de by Simon Hengel at 2012-10-14T23:34:51+02:00 unit-tests: Improve readability Add IsString instance for (Doc RdrName) + use <> instead of DocAppend. - - - - - c4446d54 by Simon Hengel at 2012-10-14T23:37:21+02:00 unit-tests: Minor refactoring Rename parse to parseParas. - - - - - 04f2703c by Simon Hengel at 2012-10-15T00:36:42+02:00 Fix typo - - - - - 3d109e44 by Simon Hengel at 2012-10-15T10:30:07+02:00 Add description for DeprecatedReExport test - - - - - 84f0985c by Simon Hengel at 2012-10-15T14:54:19+02:00 Move resources to /resources directory - - - - - a5de7ca6 by Simon Hengel at 2012-10-15T15:46:18+02:00 Move HTML tests to directory /html-test/ - - - - - e21f727d by Simon Hengel at 2012-10-15T19:32:42+02:00 Move HTML reference renderings to /html-test/ref/ - - - - - 3a3c6c75 by Simon Hengel at 2012-10-15T19:32:42+02:00 Copy css, images, etc. on accept - - - - - 40ead6dc by Simon Hengel at 2012-10-15T19:32:42+02:00 Move unit tests to /test directory - - - - - 99a28231 by Simon Hengel at 2012-10-15T19:32:42+02:00 Fix Setup.lhs /usr/bin/runhaskell is not installed on all systems. - - - - - 95faf45e by Simon Hengel at 2012-10-15T19:32:42+02:00 Make test management scripts more robust * They are now independent from the current directory, and hence can be called from everywhere * On UNIX/Linux they can now be run as scripts - - - - - 027aaa2d by Simon Hengel at 2012-10-15T19:53:40+02:00 Add 'dev' flag to cabal file, that builds without -O2 That way --disable-optimization can be used, which decreases build time considerably. - - - - - e0266ede by Simon Hengel at 2012-10-15T20:03:43+02:00 Add test case for "spurious superclass constraints bug" - - - - - 52a2aa92 by Simon Hengel at 2012-10-15T20:28:55+02:00 Adapt accept.lhs, so that it ignores more index files - - - - - 53530781 by Simon Hengel at 2012-10-15T20:49:39+02:00 Rename html-test/runtests.lhs to html-test/run.lhs - - - - - 84518797 by Simon Hengel at 2012-10-15T20:49:39+02:00 Move source files for HTML tests to html-test/src - - - - - a911dc6c by Simon Hengel at 2012-10-15T20:49:39+02:00 Adapt output directory for HTML tests - - - - - d3c15857 by Ian Lynagh at 2012-10-16T16:54:43+01:00 Follow dopt->gopt rename - - - - - 956665a5 by Simon Hengel at 2012-10-18T08:42:48+02:00 Update html-test/README - - - - - 903b1029 by Simon Hengel at 2012-10-18T08:50:26+02:00 Use markdown for html-test/README - - - - - 150b4d63 by Ian Lynagh at 2012-10-18T16:36:00+01:00 Follow changes in GHC: 'flags' has been renamed 'generalFlags' - - - - - 41e04ff9 by Simon Hengel at 2012-11-28T09:54:35+01:00 Export missing types from Documentation.Haddock - - - - - 9be59237 by Ian Lynagh at 2012-11-30T23:20:47+00:00 Update dependencies - - - - - e06842f5 by Simon Hengel at 2012-12-07T20:58:05+01:00 Bump version - - - - - e3dbede0 by Simon Hengel at 2012-12-07T20:58:05+01:00 Add missing test files to cabal file (fixes haskell/haddock#230) - - - - - ee0dcca7 by Simon Hengel at 2012-12-07T20:58:05+01:00 Update CHANGES - - - - - 51601bdb by Simon Peyton Jones at 2012-12-19T17:28:35+00:00 Track changes in UNPACK pragma stuff - - - - - f2573bc1 by Richard Eisenberg at 2012-12-21T20:56:25-05:00 Implement overlapping type family instances. An ordered, overlapping type family instance is introduced by 'type instance where', followed by equations. See the new section in the user manual (7.7.2.2) for details. The canonical example is Boolean equality at the type level: type family Equals (a :: k) (b :: k) :: Bool type instance where Equals a a = True Equals a b = False A branched family instance, such as this one, checks its equations in order and applies only the first the matches. As explained in the note [Instance checking within groups] in FamInstEnv.lhs, we must be careful not to simplify, say, (Equals Int b) to False, because b might later unify with Int. This commit includes all of the commits on the overlapping-tyfams branch. SPJ requested that I combine all my commits over the past several months into one monolithic commit. The following GHC repos are affected: ghc, testsuite, utils/haddock, libraries/template-haskell, and libraries/dph. Here are some details for the interested: - The definition of CoAxiom has been moved from TyCon.lhs to a new file CoAxiom.lhs. I made this decision because of the number of definitions necessary to support BranchList. - BranchList is a GADT whose type tracks whether it is a singleton list or not-necessarily-a-singleton-list. The reason I introduced this type is to increase static checking of places where GHC code assumes that a FamInst or CoAxiom is indeed a singleton. This assumption takes place roughly 10 times throughout the code. I was worried that a future change to GHC would invalidate the assumption, and GHC might subtly fail to do the right thing. By explicitly labeling CoAxioms and FamInsts as being Unbranched (singleton) or Branched (not-necessarily-singleton), we make this assumption explicit and checkable. Furthermore, to enforce the accuracy of this label, the list of branches of a CoAxiom or FamInst is stored using a BranchList, whose constructors constrain its type index appropriately. I think that the decision to use BranchList is probably the most controversial decision I made from a code design point of view. Although I provide conversions to/from ordinary lists, it is more efficient to use the brList... functions provided in CoAxiom than always to convert. The use of these functions does not wander far from the core CoAxiom/FamInst logic. BranchLists are motivated and explained in the note [Branched axioms] in CoAxiom.lhs. - The CoAxiom type has changed significantly. You can see the new type in CoAxiom.lhs. It uses a CoAxBranch type to track branches of the CoAxiom. Correspondingly various functions producing and consuming CoAxioms had to change, including the binary layout of interface files. - To get branched axioms to work correctly, it is important to have a notion of type "apartness": two types are apart if they cannot unify, and no substitution of variables can ever get them to unify, even after type family simplification. (This is different than the normal failure to unify because of the type family bit.) This notion in encoded in tcApartTys, in Unify.lhs. Because apartness is finer-grained than unification, the tcUnifyTys now calls tcApartTys. - CoreLinting axioms has been updated, both to reflect the new form of CoAxiom and to enforce the apartness rules of branch application. The formalization of the new rules is in docs/core-spec/core-spec.pdf. - The FamInst type (in types/FamInstEnv.lhs) has changed significantly, paralleling the changes to CoAxiom. Of course, this forced minor changes in many files. - There are several new Notes in FamInstEnv.lhs, including one discussing confluent overlap and why we're not doing it. - lookupFamInstEnv, lookupFamInstEnvConflicts, and lookup_fam_inst_env' (the function that actually does the work) have all been more-or-less completely rewritten. There is a Note [lookup_fam_inst_env' implementation] describing the implementation. One of the changes that affects other files is to change the type of matches from a pair of (FamInst, [Type]) to a new datatype (which now includes the index of the matching branch). This seemed a better design. - The TySynInstD constructor in Template Haskell was updated to use the new datatype TySynEqn. I also bumped the TH version number, requiring changes to DPH cabal files. (That's why the DPH repo has an overlapping-tyfams branch.) - As SPJ requested, I refactored some of the code in HsDecls: * splitting up TyDecl into SynDecl and DataDecl, correspondingly changing HsTyDefn to HsDataDefn (with only one constructor) * splitting FamInstD into TyFamInstD and DataFamInstD and splitting FamInstDecl into DataFamInstDecl and TyFamInstDecl * making the ClsInstD take a ClsInstDecl, for parallelism with InstDecl's other constructors * changing constructor TyFamily into FamDecl * creating a FamilyDecl type that stores the details for a family declaration; this is useful because FamilyDecls can appear in classes but other decls cannot * restricting the associated types and associated type defaults for a * class to be the new, more restrictive types * splitting cid_fam_insts into cid_tyfam_insts and cid_datafam_insts, according to the new types * perhaps one or two more that I'm overlooking None of these changes has far-reaching implications. - The user manual, section 7.7.2.2, is updated to describe the new type family instances. - - - - - f788d0fb by Simon Peyton Jones at 2012-12-23T15:49:58+00:00 Track changes in HsBang - - - - - ca460a0c by Simon Peyton Jones at 2012-12-23T15:50:28+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - f078fea6 by Simon Peyton Jones at 2013-01-02T08:33:13+00:00 Use InstEnv.instanceSig rather than instanceHead (name change) - - - - - 88e41305 by Simon Peyton Jones at 2013-01-14T17:10:27+00:00 Track change to HsBang type - - - - - e1ad4e19 by Kazu Yamamoto at 2013-02-01T11:59:24+09:00 Merge branch 'ghc-7.6' into ghc-7.6-merge-2 Conflicts: haddock.cabal src/Haddock/Interface/AttachInstances.hs src/Haddock/Interface/Create.hs src/Haddock/Interface/LexParseRn.hs src/Haddock/InterfaceFile.hs src/Haddock/Types.hs Only GHC HEAD can compile this. GHC 7.6.x cannot compile this. Some test fail. - - - - - 62bec012 by Kazu Yamamoto at 2013-02-06T11:12:28+09:00 Using tcSplitSigmaTy in instanceHead' (FIXME is resolved.) - - - - - 013fd2e4 by Kazu Yamamoto at 2013-02-06T17:56:21+09:00 Refactoring instanceHead'. - - - - - 3148ce0e by Kazu Yamamoto at 2013-02-07T17:45:10+09:00 Using new syntax in html-test/src/GADTRecords.hs. - - - - - 626dabe7 by Gabor Greif at 2013-02-15T22:42:01+01:00 Typo - - - - - 1eb667ae by Ian Lynagh at 2013-02-16T17:02:07+00:00 Follow changes in base - - - - - 3ef8253a by Ian Lynagh at 2013-03-01T23:23:57+00:00 Follow changes in GHC's build system - - - - - 1a265a3c by Ian Lynagh at 2013-03-03T23:12:07+00:00 Follow changes in GHC build system - - - - - 69941c79 by Max Bolingbroke at 2013-03-10T09:38:28-07:00 Use Alex 3's Unicode support to properly lex source files as UTF-8 Signed-off-by: David Waern <david.waern at gmail.com> - - - - - ea687dad by Simon Peyton Jones at 2013-03-15T14:16:10+00:00 Adapt to tcRnGetInfo returning family instances too This API change was part of the fix to Trac haskell/haddock#4175. But it offers new information to Haddock: the type-family instances, as well as the class instances, of this type. This patch just drops the new information on the floor, but there's an open opportunity to use it in the information that Haddock displays. - - - - - 971a30b0 by Andreas Voellmy at 2013-05-19T20:47:39+01:00 Fix for haskell/haddock#7879. Changed copy of utils/haddock/html/resources/html to use "cp -RL" rather than "cp -R". This allows users to run validate in a build tree, where the build tree was setup using lndir with a relative path to the source directory. - - - - - 31fb7694 by Ian Lynagh at 2013-05-19T20:47:49+01:00 Use "cp -L" when making $(INPLACE_LIB)/latex too - - - - - e9952233 by Simon Hengel at 2013-06-01T18:06:50+02:00 Add -itest to .ghci - - - - - b06873b3 by Mateusz Kowalczyk at 2013-06-01T18:06:50+02:00 Workaround for a failing build with --enable-tests. - - - - - e7858d16 by Simon Hengel at 2013-06-01T19:29:28+02:00 Fix broken test - - - - - 0690acb1 by Richard Eisenberg at 2013-06-21T14:08:25+01:00 Updates to reflect changes in HsDecls to support closed type families. - - - - - 7fd347ec by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 53ed81b6 by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 931c4f4f by Richard Eisenberg at 2013-07-24T13:15:59+01:00 Remove (error "synifyKind") to use WithinType, to allow haddock to process base. - - - - - 55a9c804 by Richard Eisenberg at 2013-08-02T15:54:55+01:00 Changes to reflect changes in GHC's type HsTyVarBndr - - - - - b6e9226c by Mathieu Boespflug at 2013-08-04T10:39:43-07:00 Output Copright and License keys in Xhtml backend. This information is as relevant in the documentation as it is in the source files themselves. Signed-off-by: David Waern <david.waern at gmail.com> - - - - - 4c66028a by David Waern at 2013-08-04T15:27:36-07:00 Bump interface file version. - - - - - 67340163 by David Waern at 2013-08-09T16:12:51-07:00 Update tests. - - - - - 2087569b by Mateusz Kowalczyk at 2013-08-25T09:24:13+02:00 Add spec tests. This adds tests for all elements we can create during regular parsing. This also adds tests for text with unicode in it. - - - - - 97f36a11 by Mateusz Kowalczyk at 2013-08-27T06:59:12+01:00 Fix ticket haskell/haddock#247. I do the same thing that the XHTML backend does: give these no special treatment and just act as if they are regular functions. - - - - - 60681b4f by Mateusz Kowalczyk at 2013-08-27T21:22:48+02:00 LaTeX tests setup - - - - - fa4c27b2 by Mateusz Kowalczyk at 2013-09-02T23:21:43+01:00 Fixes haskell/haddock#253 - - - - - 1a202490 by Mateusz Kowalczyk at 2013-09-03T01:12:50+01:00 Use Hspec instead of nanospec This is motivated by the fact that Haddock tests are not ran by the GHC's ‘validate’ script so we're pretty liberal on dependencies in that area. Full Hspec gives us some nice features such as Quickcheck integration. - - - - - 8cde3b20 by David Luposchainsky at 2013-09-08T07:27:28-05:00 Fix AMP warnings Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - d10661f2 by Herbert Valerio Riedel at 2013-09-11T15:15:01+02:00 Update Git repo URL in `.cabal` file - - - - - 16a44eb5 by Richard Eisenberg at 2013-09-17T09:34:26-04:00 Revision to reflect new role annotation syntax in GHC. - - - - - 4b9833b9 by Herbert Valerio Riedel at 2013-09-18T10:15:28+02:00 Add missing `traverse` method for `GenLocated` As `Traversable` needs at least one of `traverse` or `sequenceA` to be overridden. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - b71fed5d by Simon Hengel at 2013-09-18T22:43:34+02:00 Add test helper - - - - - 4fc1ea86 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#231 - - - - - 435872f6 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#256 We inject -dynamic-too into flags before we run all our actions in the GHC monad. - - - - - b8b24abb by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Add new field to DynFlags - - - - - 49558795 by Simon Hengel at 2013-09-18T22:43:35+02:00 Fallback to ./resources when Cabal data is not found (so that themes are found during development) - - - - - bf79d05c by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Fixes haskell/haddock#5 - - - - - e1baebc2 by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Print missing documentation. Fixes haskell/haddock#258. - - - - - 02ea74de by Austin Seipp at 2013-10-09T10:52:22-05:00 Don't consider StaticFlags when parsing arguments. Instead, discard any static flags before parsing the command line using GHC's DynFlags parser. See http://ghc.haskell.org/trac/ghc/ticket/8276 Based off a patch from Simon Hengel. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 704fd5bb by Simon Hengel at 2013-11-09T00:15:13+01:00 Update HTML tests - - - - - f9fed49e by Simon Hengel at 2013-11-10T18:43:58+01:00 Bump version - - - - - 97ae1999 by Simon Peyton Jones at 2013-11-25T17:25:14+00:00 Track changes in HsSpliceTy data constructor - - - - - 59ad8268 by Simon Peyton Jones at 2014-01-10T18:17:43+00:00 Adapt to small change in Pretty's exports - - - - - 8b12e6aa by Simon Hengel at 2014-01-12T14:48:35-06:00 Some code simplification by using traverse - - - - - fc5ea9a2 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix warnings in test helper - - - - - 6dbb3ba5 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Add ByteString version of Attoparsec - - - - - 968d7774 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 One pass parser and tests. We remove the HTML test as it is no longer necessary. We cover the test case in spec tests and other HTML tests but keeping this around fails: this is because the new parser has different semantics there. In fact, I suspect the original behaviour was a bug that wasn't caught/fixed but simply included as-is during the testing. - - - - - 37a07c9c by Simon Hengel at 2014-01-12T14:48:35-06:00 Rename Haddock.ParseSpec to Haddock.ParserSpec - - - - - f0f68fe9 by Simon Hengel at 2014-01-12T14:48:35-06:00 Don't append newline to parseString input We also check that we have parsed everything with endOfInput. - - - - - 95d60093 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix totality, unicode, examples, paragraph parsing Also simplify specs and parsers while we're at it. Some parsers were made more generic. This commit is a part of GHC pre-merge squash, email fuuzetsu at fuuzetsu.co.uk if you need the full commit history. - - - - - 7d99108c by Simon Hengel at 2014-01-12T14:48:35-06:00 Update acceptance tests - - - - - d1b59640 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Support for bold. Conflicts: src/Haddock/Backends/Hoogle.hs src/Haddock/Interface/Rename.hs src/Haddock/Parser.hs - - - - - 4b412b39 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Allow for headings inside function documentation. LaTeX will treat the h3-h6 headings the same as we'd have to hack the style file heavily otherwise and it would make the headings tiny anyway. Hoogle upstream said they will put in the functionality on their end. Conflicts: src/Haddock/Interface/Rename.hs src/Haddock/Types.hs test/Haddock/ParserSpec.hs - - - - - fdcca428 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Per-module extension flags and language listing. Any extensions that are not enabled by a used language (Haskell2010 &c) will be shown. Furthermore, any implicitly enabled are also going to be shown. While we could eliminate this either by using the GHC API or a dirty hack, I opted not to: if a user doesn't want the implied flags to show, they are recommended to use enable extensions more carefully or individually. Perhaps this will encourage users to not enable the most powerful flags needlessly. Enabled with show-extensions. Conflicts: src/Haddock/InterfaceFile.hs - - - - - 368942a2 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Bump interface version There were some breaking changes over the last few patches so we bump the interface version. This causes a big problem with testing: 1. To generate cross package docs, we first need to generate docs for the package used. 2. To generate package docs with new interface version, we need to use Haddock which has the version bumped. 3. To get Haddock with the version bump, we first need to test cross package docs 4. GOTO 1 So the problem is the chicken and the egg problem. It seems that the only solution would be to generate some interface files on the fly but it is non-trivial. To run this test, you'll have to: * build Haddock without the test (make sure everything else passes) * rebuild the packages used in the test with your shiny new binary making sure they are visible to Haddock * remove the ‘_hidden’ suffix and re-run the tests Note: because the packages currently used for this test are those provided by GHC, it's probably non-trivial to just re-build them. Preferably something less tedious to rebuild should be used and something that is not subject to change. - - - - - 124ae7a9 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow for nesting of paragraphs under lists. The nesting rules are similar to Markdown's with the exception that we can not simply indent the first line of a hard wrapped indented paragraph and have it treated as if it was fully indented. The reason is differences in markup as some of our constructs care about whitespace while others just swallow everything up so it's just a lot easier to not bother with it rather than making arbitrary rules. Note that we now drop trailing for string entities inside of lists. They weren't needed and it makes the output look uniform whether we use a single or double newline between list elements. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - c7913535 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow escaping in URLs and pictures. Some tests were moved under parseString as they weren't about paragraph level markup. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - 32326680 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update documentation. - - - - - fbef6406 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update maintainer - - - - - b40e82f4 by Mateusz Kowalczyk at 2014-01-13T02:39:25-06:00 Fixes haskell/haddock#271 Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - f4eafbf8 by Gergő Érdi at 2014-01-19T15:35:16-06:00 Support for -XPatternSynonyms Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - a8939591 by Austin Seipp at 2014-01-29T08:09:04-06:00 Update CPP check for __GLASGOW_HASKELL__ Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 30d7e9d5 by Gergő Érdi at 2014-01-31T00:15:01+08:00 <+>: Don't insert a space when concatenating empty nodes - - - - - a25ccd4d by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Fix @ code blocks In cases where we had some horizontal space before the closing ‘@’, the parser would not accept the block as a code block and we'd get ugly output. - - - - - 0f67305a by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Update tests This updates tests due to Haddock Trac haskell/haddock#271 fix and due to removal of TypeHoles as an extension from GHC. - - - - - 157322a7 by Gergő Érdi at 2014-01-31T01:03:17+08:00 Handle infix vs prefix names correctly everywhere, by explicitly specifying the context The basic idea is that "a" and "+" are either pretty-printed as "a" and "(+)" or "`a`" and "+" - - - - - aa6d9685 by Mateusz Kowalczyk at 2014-01-30T17:21:50+00:00 Correct whitespace in ‘hidden’ test for <+> change - - - - - 121872f0 by Mateusz Kowalczyk at 2014-02-09T17:59:12+00:00 Document module header. Fixes Haddock Trac haskell/haddock#270. - - - - - e3253746 by Mateusz Kowalczyk at 2014-02-10T21:37:48+00:00 Insert a space between module link and description Fixes Haddock Trac haskell/haddock#277. - - - - - 771d2384 by Mateusz Kowalczyk at 2014-02-10T23:27:21+00:00 Ensure a space between type signature and ‘Source’ This is briefly related to Haddock Trac haskell/haddock#249 and employs effectively the suggested fix _but_ it doesn't actually fix the reported issue. This commit simply makes copying the full line a bit less of a pain. - - - - - 8cda9eff by nand at 2014-02-11T15:48:30+00:00 Add support for type/data families This adds support for type/data families with their respective instances, as well as closed type families and associated type/data families. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 3f22c510 by nand at 2014-02-11T15:53:50+00:00 Improve display of poly-kinded type operators This now displays them as (==) k a b c ... to mirror GHC's behavior, instead of the old (k == a) b c ... which was just wrong. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - effb2d6b by nand at 2014-02-11T15:56:50+00:00 Add test case for PatternSynonyms This just tests various stuff including poly-kinded patterns and operator patterns to make sure the rendering isn't broken. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - b38faf0d by Niklas Haas at 2014-02-13T21:53:32+00:00 Get rid of re-implementation of sortBy I have no idea what this was doing lying around here, and due to the usage of tuples it's actually slower, too. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - ac1e0413 by Mateusz Kowalczyk at 2014-02-13T23:57:16+00:00 Only warn about missing docs when docs are missing This fixes the ‘Missing documentation for…’ message for modules with 100% coverage. - - - - - cae2e36a by Niklas Haas at 2014-02-15T21:56:18+00:00 Add test case for inter-module type/data family instances These should show up in every place where the class is visible, and indeed they do right now. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 8bea5c3a by Mateusz Kowalczyk at 2014-02-19T05:11:34+00:00 Use a bespoke data type to indicate fixity This deals with what I imagine was an ancient TODO and makes it much clearer what the argument actually does rather than having the user chase down the comment. - - - - - 5b52d57c by Niklas Haas at 2014-02-22T21:31:03+01:00 Strip a single leading space from bird tracks (#201) This makes bird tracks in the form > foo > bar > bat parse as if they had been written as >foo >bar >bat ie. without the leading whitespace in front of every line. Ideally we also want to look into how leading whitespace affects code blocks written using the @ @ syntax, which are currently unaffected by this patch. - - - - - 5a1315a5 by Simon Hengel at 2014-02-22T21:55:35+01:00 Turn a source code comment into specs - - - - - 784cfe58 by Mateusz Kowalczyk at 2014-02-23T05:02:22+00:00 Update test case for lifted GADT type rendering The parsing of these seems to have been fixed by GHC folk and it now renders differently. IMHO it now renders in a better way so I'm updating the test to reflect this. - - - - - c3c88c2f by Mateusz Kowalczyk at 2014-02-23T06:37:14+00:00 Don't shadow ‘strip’. -Wall complains - - - - - 293031d8 by Niklas Haas at 2014-02-23T15:21:52+01:00 Make ImplicitParams render correctly (#260) This introduces a new precedence level for single contexts (because implicit param contexts always need parens around them, but other types of contexts don't necessarily, even when alone) - - - - - 4200842d by Niklas Haas at 2014-02-23T15:37:13+01:00 Lower precedence of equality constraints This drops them to the new precedence pREC_CTX, which makes single eqaulity constraints show up as (a ~ b) => ty, in line with GHC's rendering. Additional tests added to make sure other type operators render as intended. Current behavior matches GHC - - - - - b59e3227 by Niklas Haas at 2014-02-23T16:11:22+01:00 Add RankNTypes test case to ImplicitParams.hs This test actually tests what haskell/haddock#260 originally reported - I omitted the RankNTypes scenario from the original fix because I realized it's not relevant to the underlying issue and indeed, this renders as intended now. Still good to have more tests. - - - - - c373dbf7 by Mateusz Kowalczyk at 2014-02-24T06:09:54+00:00 Fix rendering of Contents when links are present Fixes Haddock Trac haskell/haddock#267. - - - - - 9ecb0e56 by Mateusz Kowalczyk at 2014-02-24T06:26:50+00:00 Fix wording in the docs - - - - - 4f4dcd8e by Mateusz Kowalczyk at 2014-02-27T03:00:33+00:00 Change rendering of duplicate record field docs See Haddock Trac haskell/haddock#195. We now change this behaviour to only rendering the documentation attached to the first instance of a duplicate field. Perhaps we could improve this by rendering the first instance that has documentation attached to it but for now, we'll stick with this. - - - - - ad8aa609 by Niklas Haas at 2014-03-08T09:43:26+01:00 Render fixity information Affects functions, type synonyms, type families, class names, data type names, constructors, data families, associated TFs/DFs, type synonyms, pattern synonyms and everything else I could think of. - - - - - 6a39c917 by Niklas Haas at 2014-03-09T07:43:39+01:00 Reorder topDeclElem to move the source/wiki links to the top They appear in the same position due to the float: right attribute but now they're always at the top of the box instead of at the bottom. - - - - - 2d34b3b4 by Niklas Haas at 2014-03-09T07:53:46+01:00 Use optLast instead of listToMaybe for sourceUrls/wikiUrls This lets you override them using eg. cabal haddock --haddock-options, which can come in handy if you want to use a different layout or URL for your source code links than cabal-install generates. - - - - - 0eff4624 by Niklas Haas at 2014-03-09T07:53:46+01:00 Differentiate between TH splices (line-links) and regular names This adds a new type of source code link, to a specific line rather than a specific declaration/name - this is used to link to the location of a TH splice that defines a certain name. Rather hefty changes throughout and still one unresolved issue (the line URLs aren't parsed from the third form of --read-interface which means they're currently restricted to same-interface links). Not sure if this issue is really worth all the hassle, especially since we could just use line links in general. This commit also contains some cleanup/clarification of the types in Haddock.Backends.Xhtml.Decl and shortens some overlong lines in the process. Notably, the Bool parameter was replaced by a Unicode type synonym to help clarify its presence in type signatures. - - - - - 66d6f77b by Niklas Haas at 2014-03-09T20:02:43+01:00 Group similar fixities together Identical fixities declared for the same line should now render using syntax like: infix 4 <, >=, >, <= - - - - - 6587f9f5 by Mateusz Kowalczyk at 2014-03-10T04:24:18+00:00 Update changelog - - - - - 7387ddad by Niklas Haas at 2014-03-11T10:26:04+01:00 Include fixity information in the Interface file This resolves fixity information not appearing across package borders. The binary file version has been increased accordingly. - - - - - ab46ef44 by Niklas Haas at 2014-03-11T10:26:04+01:00 Update changelog - - - - - 565cab6f by Niklas Haas at 2014-03-11T10:26:04+01:00 Update appearance of fixity annotations This moves them in-line with their corresponding lines, similar to a presentation envision by @hvr and described in #ghc. Redundant operator names are also omitted when no ambiguity is present. - - - - - 5d7afd67 by Niklas Haas at 2014-03-11T10:26:05+01:00 Filter family instances of hidden types Currently, this check does not extend to hidden right hand sides, although it probably should hide them in that case. - - - - - ec291b0c by Niklas Haas at 2014-03-11T10:26:05+01:00 Add documentation for --source-entity-line - - - - - 0922e581 by Niklas Haas at 2014-03-11T10:37:32+01:00 Revert "Reorder topDeclElem to move the source/wiki links to the top" This reverts commit 843c42c4179526a2ad3526e4c7d38cbf4d50001d. This change is no longer needed with the new rendering style, and it messes with copy/pasting lines. - - - - - 30618e8b by Mateusz Kowalczyk at 2014-03-11T09:41:07+00:00 Bump version to 2.15.0 - - - - - adf3f1bb by Mateusz Kowalczyk at 2014-03-11T09:41:09+00:00 Fix up some whitespace - - - - - 8905f57d by Niklas Haas at 2014-03-13T19:18:06+00:00 Hide RHS of TFs with non-exported right hand sides Not sure what to do about data families yet, since technically it would not make a lot of sense to display constructors that cannot be used by the user. - - - - - 5c44d5c2 by Niklas Haas at 2014-03-13T19:18:08+00:00 Add UnicodeSyntax alternatives for * and -> I could not find a cleaner way to do this other than checking for string equality with the given built-in types. But seeing as it's actually equivalent to string rewriting in GHC's implementation of UnicodeSyntax, it's probably fitting. - - - - - b04a63e6 by Niklas Haas at 2014-03-13T19:18:10+00:00 Display minimal complete definitions for type classes This corresponds to the new {-# MINIMAL #-} pragma present in GHC 7.8+. I also cleaned up some of the places in which ExportDecl is used to make adding fields easier in the future. Lots of test cases have been updated since they now render with minimality information. - - - - - a4a20b16 by Niklas Haas at 2014-03-13T19:18:12+00:00 Strip links from recently added html tests These were accidentally left there when the tests were originally added - - - - - d624f315 by Mateusz Kowalczyk at 2014-03-13T19:19:31+00:00 Update changelog - - - - - d27a21ac by Mateusz Kowalczyk at 2014-03-13T21:19:07+00:00 Always read in prologue files as UTF8 (#286). - - - - - 54b2fd78 by Mateusz Kowalczyk at 2014-03-13T21:28:09+00:00 Style only - - - - - fa4fe650 by Simon Hengel at 2014-03-15T09:04:18+01:00 Add Fuuzetsu maintainers field in cabal file - - - - - f83484b7 by Niklas Haas at 2014-03-15T18:20:24+00:00 Hide minimal definition for only-method classes Previously this was not covered by the All xs check since here it is not actually an All, rather a single Var n. This also adds the previously missing html-test/src/Minimal.hs. - - - - - 0099d276 by Niklas Haas at 2014-03-15T18:20:26+00:00 Fix issue haskell/haddock#281 This is a regression from the data family instances change. Data instances are now distinguished from regular lists by usage of the new class "inst", and the style has been updated to only apply to those. I've also updated the appropriate test case to test this a bit better, including GADT instances with GADT-style records. - - - - - 1f9687bd by Mateusz Kowalczyk at 2014-03-21T17:48:37+00:00 Please cabal sdist - - - - - 75542693 by Mateusz Kowalczyk at 2014-03-22T16:36:16+00:00 Drop needless --split-objs which slows us down. Involves tiny cleanup of all the dynflag bindings. Fixes haskell/haddock#292. - - - - - 31214dc3 by Herbert Valerio Riedel at 2014-03-23T18:01:01+01:00 Fix a few typos Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 0b73e638 by Mateusz Kowalczyk at 2014-03-31T05:34:36+01:00 Print kind signatures on GADTs - - - - - 2bab42f3 by Mateusz Kowalczyk at 2014-03-31T16:53:25+01:00 Add default for new PlatformConstraints field - - - - - 42647c5f by Mateusz Kowalczyk at 2014-03-31T18:29:04+01:00 Drop leading whitespace in @-style blocks. Fixes haskell/haddock#201. - - - - - 98208294 by Niklas Haas at 2014-03-31T20:09:58+02:00 Crash when exporting record selectors of data family instances This fixes bug haskell/haddock#294. This also fixes a related but never-before-mentioned bug about the display of GADT record selectors with non-polymorphic type signatures. Note: Associated data type constructors fail to show up if nothing is exported that they could be attached to. Exporting any of the data types in the instance head, or the class + data family itself, causes them to show up, but in the absence of either of these, exporting just the associated data type with the constructor itself will result in it being hidden. The only scenario I can come up that would involve this kind of situation involved OverlappingInstances, and even then it can be mitigated by just exporting the class itself, so I'm not going to solve it since the logic would most likely be very complicated. - - - - - 3832d171 by Mateusz Kowalczyk at 2014-04-01T19:07:33+01:00 Make CHANGES consistent with what's now in 2.14.2 - - - - - c386ae89 by Mateusz Kowalczyk at 2014-04-01T19:18:36+01:00 Actually bundle extra spec tests in sdist - - - - - bd57a6d3 by Mateusz Kowalczyk at 2014-04-03T21:13:48+01:00 Update test cases for GHC bug haskell/haddock#8945, Haddock haskell/haddock#188 The order of signature groups has been corrected upstream. Here we add a test case and update some existing test-cases to reflect this change. We remove grouped signature in test cases that we can (Minimal, BugDeprecated &c) so that the test is as self-contained as possible. - - - - - 708b88b1 by Mateusz Kowalczyk at 2014-04-03T21:16:07+01:00 Enforce strict GHC version in cabal file This stops people with 7.6.3 trying to install 2.15.x which clearly won't work. Unfortunately we shipped 2.14.x without realising this. - - - - - 60334f7c by Mateusz Kowalczyk at 2014-04-03T21:19:24+01:00 Initialise some new PlatformConstants fields - - - - - ea77f668 by Mateusz Kowalczyk at 2014-04-11T16:52:23+01:00 We don't actually want unicode here - - - - - 0b651cae by Mateusz Kowalczyk at 2014-04-11T18:13:30+01:00 Parse identifiers with ^ and ⋆ in them. Fixes haskell/haddock#298. - - - - - e8ad0f5f by Mateusz Kowalczyk at 2014-04-11T18:47:41+01:00 Ignore version string during HTML tests. - - - - - de489089 by Mateusz Kowalczyk at 2014-04-11T18:59:30+01:00 Update CHANGES to follow 2.14.3 - - - - - beb464a9 by Gergő Érdi at 2014-04-13T16:31:10+08:00 remove Origin flag from LHsBindsLR - - - - - cb16f07c by Herbert Valerio Riedel at 2014-04-21T17:16:50+02:00 Replace local `die` by new `System.Exit.die` Starting with GHC 7.10, System.Exit exports the new `die` which is essentially the same as Haddock.Util.die, so this commit changes Haddock.Util.die to be a simple re-export of System.Exit.die. See also https://ghc.haskell.org/trac/ghc/ticket/9016 for more details. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 9b9b23c7 by Mateusz Kowalczyk at 2014-05-03T15:40:11+02:00 Disambiguate ‘die’ in test runners. - - - - - 5d28a2b8 by Mateusz Kowalczyk at 2014-05-05T09:19:49+02:00 Prepare modules for parser split. We have to generalise the Doc (now DocH) slightly to remove the dependency on GHC-supplied type. - - - - - d3967ff3 by Mateusz Kowalczyk at 2014-05-05T11:00:41+02:00 Move parser + parser tests out to own package. We move some types out that are necessary as well and then re-export and specialise them in the core Haddock. Reason for moving out spec tests is that if we're working on the parser, we can simply work on that and we can ignore the rest of Haddock. The downside is that it's a little inconvenient if at the end of the day we want to see that everything passes. - - - - - 522a448d by Mateusz Kowalczyk at 2014-05-05T11:14:47+02:00 Move out Show and Eq instances to Types They are much more useful to the users here. - - - - - 11a6f0f2 by Mateusz Kowalczyk at 2014-05-06T13:50:31+02:00 Remove no longer necessary parser error handling. We can now drop some Maybe tests and even lets us strip an error handling monad away in a few places. - - - - - 6992c924 by Mateusz Kowalczyk at 2014-05-14T02:23:55+02:00 Please the GHC build-system. As I can not figure out how to do this properly, if we're in GHC tree, we treat the library as being the same package. If we're not in the tree, we require that the library be installed separately. - - - - - 7a8ad763 by Mateusz Kowalczyk at 2014-05-14T14:50:25+02:00 Update issue tracker URL - - - - - f616c521 by Mateusz Kowalczyk at 2014-05-14T14:53:32+02:00 Update issue tracker URL for haddock-library - - - - - 66580ded by Gergő Érdi at 2014-05-25T14:24:16+08:00 Accomodate change in PatSyn representation - - - - - 0e43b988 by Mateusz Kowalczyk at 2014-05-29T03:15:29+02:00 Revert "Accomodate change in PatSyn representation" This reverts commit 57aa591362d7c8ba21285fccd6a958629a422091. I am reverting this because I pushed it to master when it was meant to stay on a wip-branch. Sorry Gergo and everyone who had trouble due to this. - - - - - e10d7ec8 by Mateusz Kowalczyk at 2014-05-29T03:24:11+02:00 Revert "Revert "Accomodate change in PatSyn representation"" This reverts commit e110e6e70e40eed06c06676fd2e62578da01d295. Apparently as per GHC commit ac2796e6ddbd54c5762c53e2fcf29f20ea162fd5 this was actually intended. Embarrasing for me. - - - - - 5861aca9 by Mateusz Kowalczyk at 2014-06-05T19:49:27+02:00 Clear up highlighting of identifiers with ‘'’s. - - - - - d7cc420f by Simon Peyton Jones at 2014-06-06T12:41:09+01:00 Follow change in patSynSig - - - - - 938b4fd8 by Mateusz Kowalczyk at 2014-06-12T07:24:29+02:00 Slightly update the readme. Style-sheets are no longer a recent thing, dead links, old maintainers, different formats. - - - - - c7799dea by Mateusz Kowalczyk at 2014-06-18T00:05:56+02:00 Update cabal files Update repository urls, use subdir property for haddock-library and use a separate versioning scheme for haddock-library in preparation for release. - - - - - a2750b6a by Simon Hengel at 2014-06-18T11:01:18+08:00 Compatibility with older versions of base and bytestring - - - - - 009b4b03 by Simon Hengel at 2014-06-18T11:14:01+08:00 Enable travis-ci for haddock-library - - - - - 9b5862eb by Simon Hengel at 2014-06-18T11:14:01+08:00 haddock-library: Do not depend on haddock-library in test suite I think you either add src to hs-source-dirs or the library to build-depends. But doing both does not make sense (AFAICT). - - - - - fb1f3279 by Simon Hengel at 2014-06-18T11:49:05+08:00 haddock-library: Use -Wall for specs - - - - - 649340e1 by Mateusz Kowalczyk at 2014-06-18T06:58:54+02:00 Use Travis with multiple GHC versions When using HEAD, we build haddock-library directly from repository as a dependency (and thanks to --enable-tests, the tests get ran anyway). In all other cases, we manually run the tests on haddock-library only and don't test the main project. - - - - - d7eeeec2 by Mateusz Kowalczyk at 2014-06-18T07:49:04+02:00 Comment improvements + few words in cabal file - - - - - 0f8db914 by Simon Hengel at 2014-06-18T13:52:23+08:00 Use doctest to check examples in documentation - - - - - 2888a8dc by Simon Hengel at 2014-06-18T14:16:48+08:00 Remove doctest dependency (so that we can use haddock-library with doctest) - - - - - 626d5e85 by Mateusz Kowalczyk at 2014-06-18T08:41:25+02:00 Travis tweaks - - - - - 41d4f9cc by Mateusz Kowalczyk at 2014-06-18T08:58:43+02:00 Don't actually forget to install specified GHC. - - - - - c6aa512a by John MacFarlane at 2014-06-18T10:43:57-07:00 Removed reliance on LambdaCase (which breaks build with ghc 7.4). - - - - - b9b93b6f by John MacFarlane at 2014-06-18T10:54:56-07:00 Fixed haddock warnings. - - - - - a41b0ab5 by Mateusz Kowalczyk at 2014-06-19T01:20:10+02:00 Update Travis, bump version - - - - - 864bf62a by Mateusz Kowalczyk at 2014-06-25T10:36:54+02:00 Fix anchors. Closes haskell/haddock#308. - - - - - 53df91bb by Mateusz Kowalczyk at 2014-06-25T15:04:49+02:00 Drop DocParagraph from front of headers I can not remember why they were wrapped in paragraphs to begin with and it seems unnecessary now that I test it. Closes haskell/haddock#307. - - - - - 29b5f2fa by Mateusz Kowalczyk at 2014-06-25T15:17:20+02:00 Don't mangle append order for nested lists. The benefit of this is that the ‘top-level’ element of such lists is properly wrapped in <p> tags so any CSS working with these will be applied properly. It also just makes more sense. Pointed out at jgm/pandoc#1346. - - - - - 05cb6e9c by Mateusz Kowalczyk at 2014-06-25T15:19:45+02:00 Bump haddock-library to 1.1.0 for release - - - - - 70feab15 by Iavor Diatchki at 2014-07-01T03:37:07-07:00 Propagate overloading-mode for instance declarations in haddock (#9242) - - - - - d4ca34a7 by Simon Peyton Jones at 2014-07-14T16:23:15+01:00 Adapt to new definition of HsDecls.TyFamEqn This is a knock-on from the refactoring from Trac haskell/haddock#9063. I'll push the corresponding changes to GHC shortly. - - - - - f91e2276 by Edward Z. Yang at 2014-07-21T08:14:19-07:00 Track GHC PackageId to PackageKey renaming. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - b010f9ef by Edward Z. Yang at 2014-07-25T16:28:46-07:00 Track changes for module reexports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - 8b85f9f9 by Mateusz Kowalczyk at 2014-07-28T13:25:43+02:00 Catch mid-line URLs. Fixes haskell/haddock#314. - - - - - 4c613a78 by Edward Z. Yang at 2014-08-05T03:11:00-07:00 Track type signature change of lookupModuleInAllPackages Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - e80b051c by Edward Z. Yang at 2014-08-05T17:34:26+01:00 If GhcProfiled, also build Haddock profiled. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f9cccd29 by Edward Z. Yang at 2014-08-07T14:23:35+01:00 Ignore TAGS files. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 00b3af52 by Mateusz Kowalczyk at 2014-08-08T04:58:19+02:00 Update to attoparsec-0.12.1.1 There seems to be memory and speed improvement. - - - - - 5457dc71 by Mateusz Kowalczyk at 2014-08-08T18:24:02+02:00 Fix forgotten src - - - - - 3520cb04 by Mateusz Kowalczyk at 2014-08-14T20:19:07+01:00 Bump down the version for master to 2.14.4 - - - - - dc98c21b by Mateusz Kowalczyk at 2014-08-14T20:23:27+01:00 Revert "Track type signature change of lookupModuleInAllPackages" This reverts commit d59fec2c9551b5662a3507c0011e32a09a9c118f. - - - - - 3f2038c0 by Mateusz Kowalczyk at 2014-08-14T20:23:31+01:00 Revert "Track changes for module reexports." This reverts commit b99b57c0df072d12b67816b45eca2a03cb1da96d. - - - - - 56d4e49e by Mateusz Kowalczyk at 2014-08-14T20:23:42+01:00 Revert "Track GHC PackageId to PackageKey renaming." This reverts commit 8ac42d3327473939c013551750425cac191ff0fd. - - - - - 726ea3cb by Mateusz Kowalczyk at 2014-08-14T20:23:47+01:00 Revert "Adapt to new definition of HsDecls.TyFamEqn" This reverts commit cb96b4f1ed0462b4a394b9fda6612c3bea9886bd. - - - - - 61a88ff0 by Mateusz Kowalczyk at 2014-08-14T20:23:52+01:00 Revert "Propagate overloading-mode for instance declarations in haddock (#9242)" This reverts commit 8d20ca8d5a9bee73252ff2035ec45f9c03d0820c. - - - - - a32ba674 by Mateusz Kowalczyk at 2014-08-14T20:26:03+01:00 Revert "Disambiguate ‘die’ in test runners." This reverts commit dba02d6df32534aac5d257f2d28596238d248942. - - - - - f335820f by Mateusz Kowalczyk at 2014-08-14T20:26:09+01:00 Revert "Replace local `die` by new `System.Exit.die`" This reverts commit 08aa509ebac58bfb202ea79c7c41291ec280a1c5. - - - - - 107078e4 by Mateusz Kowalczyk at 2014-08-14T20:27:34+01:00 Merge branch 'reverts' This reverts any changes that were made to have Haddock compile with 7.9. When 7.10 release comes, we can simply re-apply all the patches and any patches that occur on ghc-head branch from now on. This allows us to build master with 7.8.3 - - - - - b44b3871 by Mateusz Kowalczyk at 2014-08-15T02:47:40+01:00 Fix haskell/haddock#313 by doing some list munging. I get rid of the Monoid instance because we weren't satisfying the laws. Convenience of having <> didn't outweigh the shock-factor of having it behave badly. - - - - - e1a62cde by Mateusz Kowalczyk at 2014-08-15T02:52:56+01:00 Stop testing haskell/haddock#188. Because the change is in GHC 7.9 and we now work against 7.8.3, this test no longer makes sense. We revert it until 7.10 becomes the standard version. If anything, there should be a test for this in GHC itself. - - - - - 54e8286d by Mateusz Kowalczyk at 2014-08-15T05:31:57+01:00 Add haskell/haddock#313 to CHANGES - - - - - 9df7ad5d by Simon Hengel at 2014-08-20T11:25:32+08:00 Fix warning - - - - - ee2574d6 by Simon Hengel at 2014-08-20T12:07:01+08:00 Fix travis builds - - - - - 384cf2e6 by Simon Hengel at 2014-08-20T12:14:31+08:00 Require GHC 7.8.3 - - - - - d4779863 by Simon Hengel at 2014-08-22T12:14:16+08:00 Move Haddock API to a separate package - - - - - 80f3e0e1 by Simon Hengel at 2014-08-22T14:57:38+08:00 Bump version to 2.15.0 and add version constraints - - - - - 309a94ce by Simon Hengel at 2014-08-22T15:18:06+08:00 Add deprecated compatibility module - - - - - 4d1e4e3f by Luite Stegeman at 2014-08-22T20:46:45+02:00 export things to allow customizing how the Ghc session is run - - - - - 47884591 by Luite Stegeman at 2014-08-22T20:46:51+02:00 ghc 7.8.2 compatibility - - - - - 5ea94e2c by Luite Stegeman at 2014-08-22T22:08:58+02:00 install dependencies for haddock-api on travis - - - - - 9fb845b2 by Mateusz Kowalczyk at 2014-08-23T10:09:34+01:00 Move sources under haddock-api/src - - - - - 85817dc4 by Mateusz Kowalczyk at 2014-08-23T10:10:48+01:00 Remove compat stuff - - - - - 151c6169 by Niklas Haas at 2014-08-24T08:14:10+02:00 Fix extra whitespace on signatures and update all test cases This was long overdue, now running ./accept.lhs on a clean test from master will not generate a bunch of changes. - - - - - d320e0d2 by Niklas Haas at 2014-08-24T08:14:35+02:00 Omit unnecessary foralls and fix haskell/haddock#315 This also fixes haskell/haddock#86. - - - - - bdafe108 by Mateusz Kowalczyk at 2014-08-24T15:06:46+01:00 Update CHANGES - - - - - fafa6d6e by Mateusz Kowalczyk at 2014-08-24T15:14:23+01:00 Delete few unused/irrelevant/badly-place files. - - - - - 3634923d by Duncan Coutts at 2014-08-27T13:49:31+01:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. - - - - - 539a7e70 by Herbert Valerio Riedel at 2014-08-31T11:36:32+02:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 9e3a0e5b by Mateusz Kowalczyk at 2014-08-31T12:54:43+01:00 Bump version in doc - - - - - 4a177525 by Mateusz Kowalczyk at 2014-08-31T13:01:23+01:00 Bump haddock-library version - - - - - f99c1384 by Mateusz Kowalczyk at 2014-08-31T13:05:25+01:00 Remove references to deleted files - - - - - 5e51a247 by Mateusz Kowalczyk at 2014-08-31T14:18:44+01:00 Make the doc parser not complain - - - - - 2cedb49a by Mateusz Kowalczyk at 2014-09-03T03:33:15+01:00 CONTRIBUTING file for issues - - - - - 88027143 by Mateusz Kowalczyk at 2014-09-04T00:46:59+01:00 Mention --print-missing-docs - - - - - 42f6754f by Alan Zimmerman at 2014-09-05T18:13:24-05:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e712719e by Austin Seipp at 2014-09-09T01:03:27-05:00 Fix import of 'empty' due to AMP. Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 71c29755 by Herbert Valerio Riedel at 2014-09-09T17:35:20+02:00 Bump `base` constraint for AMP - - - - - 0bf9f3ed by Mateusz Kowalczyk at 2014-09-12T19:18:32+01:00 Delete stale ANNOUNCE - - - - - cac89ee6 by Krzysztof Gogolewski at 2014-09-14T17:17:09+02:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 4d683426 by Edward Z. Yang at 2014-09-18T13:38:11-07:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 80697fd5 by Herbert Valerio Riedel at 2014-09-19T00:07:52+02:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. - - - - - c015eb70 by Herbert Valerio Riedel at 2014-09-19T00:10:36+02:00 Revert "Followup changes to addition of -fwarn-context-quantification" This reverts commit 4023817d7c0e46db012ba2eea28022626841ca9b temporarily as the respective feature hasn't landed in GHC HEAD yet, but this commit blocks later commits from being referenced in GHC HEAD. - - - - - 38ded784 by Edward Z. Yang at 2014-09-18T15:32:15-07:00 Revert "Revert "Followup changes to addition of -fwarn-context-quantification"" This reverts commit db14fd8ab4fab43694139bc203808b814eafb2dc. It's in HEAD now. - - - - - f55d59c9 by Herbert Valerio Riedel at 2014-09-26T19:18:28+02:00 Revert "Fix import of 'empty' due to AMP." This reverts commit 0cc5bc85e9fca92ab712b68a2ba2c0dd9d3d79f4 since it turns out we don't need to re-export `empty` from Control.Monad after all. - - - - - 467050f1 by David Feuer at 2014-10-09T20:07:36-04:00 Fix improper lazy IO use Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. - - - - - cc47b699 by Edward Z. Yang at 2014-10-09T21:38:19-07:00 Fix use-after-close lazy IO bug Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. Signed-off-by: David Feuer <David.Feuer at gmail.com> Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 87babcbe by Austin Seipp at 2014-10-20T20:05:27-05:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - ab259516 by Austin Seipp at 2014-10-20T20:07:01-05:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - b918093c by Mateusz Kowalczyk at 2014-10-29T03:59:39+00:00 Experimental support for collapsable headers Closes haskell/haddock#335 - - - - - 849db129 by Mateusz Kowalczyk at 2014-10-29T10:07:26+01:00 Experimental support for collapsable headers (cherry picked from commit e2ed3b9d8dfab09f1b1861dbc8e74f08e137ebcc) - - - - - a4cc4789 by Herbert Valerio Riedel at 2014-10-31T11:08:26+01:00 Collapse user-defined section by default (re haskell/haddock#335) - - - - - 9da1b33e by Yuras Shumovich at 2014-10-31T16:11:04-05:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - c625aefc by Austin Seipp at 2014-10-31T19:34:10-05:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - c7738e5e by Simon Hengel at 2014-11-02T07:25:30+08:00 Remove -fobject-code from .ghci (this slows down reloads on modifications) - - - - - d4a86e95 by Simon Hengel at 2014-11-03T09:26:11+08:00 Get rid of StandaloneDeriving - - - - - a974e311 by Simon Hengel at 2014-11-03T09:26:11+08:00 Derive more instances - - - - - 8aa0c4d7 by Simon Hengel at 2014-11-03T09:27:08+08:00 Remove unused language extensions - - - - - 3052d46a by Simon Hengel at 2014-11-03T09:30:46+08:00 Minor refactoring - - - - - 4281d3cb by Simon Hengel at 2014-11-03T09:30:46+08:00 parser: Try to parse definition lists right before text paragraphs - - - - - 8ba12bf9 by Simon Hengel at 2014-11-03T09:34:19+08:00 Add support for markdown links (closes haskell/haddock#336) - - - - - a2f8d747 by Simon Hengel at 2014-11-03T09:34:19+08:00 Allow markdown links at the beginning of a paragraph - - - - - 53b11207 by Simon Hengel at 2014-11-03T09:34:20+08:00 Update documentation - - - - - 652267c6 by Simon Hengel at 2014-11-03T09:34:20+08:00 Add support for markdown images - - - - - 9d667502 by Simon Hengel at 2014-11-03T09:34:20+08:00 Allow an optional colon after the closing bracket of definition lists This is to disambiguate them from markdown links and will be require with a future release. - - - - - 8167fc32 by Mateusz Kowalczyk at 2014-11-04T01:16:51+00:00 whitespace only - - - - - 3da62981 by Mateusz Kowalczyk at 2014-11-04T01:17:31+00:00 Fix re-exports of built-in type families Fixes haskell/haddock#310 - - - - - edc76b34 by Mateusz Kowalczyk at 2014-11-04T02:54:28+00:00 Turn some uses of error into recoverable warnings This should at the very least not abort when something weird happens. It does feel like we should have a type that carries these errors until the end however as the user might not see them unless they are printed at the end. - - - - - 0a137400 by Mateusz Kowalczyk at 2014-11-04T04:09:44+00:00 Fix warnings - - - - - d068fc21 by Mateusz Kowalczyk at 2014-11-04T21:04:07+00:00 Fix parsing of identifiers written in infix way - - - - - 1a9f2f3d by Simon Hengel at 2014-11-08T11:32:42+08:00 Minor code simplification - - - - - 6475e9b1 by Simon Hengel at 2014-11-08T17:28:33+08:00 newtype-wrap parser monad - - - - - dc1ea105 by Herbert Valerio Riedel at 2014-11-15T11:55:43+01:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - fbb1aca4 by Simon Hengel at 2014-11-16T08:51:38+08:00 State intention rather than implementation details in Haddock comment - - - - - 97851ab2 by Simon Hengel at 2014-11-16T10:20:19+08:00 (wip) Add support for @since (closes haskell/haddock#26) - - - - - 34bcd18e by Gergő Érdi at 2014-11-20T22:35:38+08:00 Update Haddock to new pattern synonym type signature syntax - - - - - 304b7dc3 by Jan Stolarek at 2014-11-20T17:48:43+01:00 Follow changes from haskell/haddock#9812 - - - - - 920f9b03 by Richard Eisenberg at 2014-11-20T16:52:50-05:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 0bfe4e78 by Alan Zimmerman at 2014-11-21T11:23:09-06:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 356ed45a by Thomas Winant at 2014-11-28T16:11:22-06:00 Support for PartialTypeSignatures - - - - - 5dc8f3b1 by Gergő Érdi at 2014-11-29T15:39:09+08:00 For pattern synonyms, render "pattern" as a keyword - - - - - fe704480 by Mateusz Kowalczyk at 2014-12-09T03:38:32+00:00 List new module in cabal file - - - - - b9ad5a29 by Mateusz Kowalczyk at 2014-12-10T00:58:24+00:00 Allow the parser to spit out meta-info Currently we only use it only for ‘since’ annotations but with these patches it should be fairly simple to add new attributes if we wish to. Closes haskell/haddock#26. It seems to work fine but due to 7.10 rush I don't have the chance to do more exhaustive testing right now. The way the meta is output (emphasis at the end of the whole comment) is fairly arbitrary and subject to bikeshedding. Note that this makes test for Bug310 fail due to interface version bump: it can't find the docs for base with this interface version so it fails. There is not much we can do to help this because it tests for ’built-in’ identifier, not something we can provide ourselves. - - - - - 765af0e3 by Mateusz Kowalczyk at 2014-12-10T01:17:19+00:00 Update doctest parts of comments - - - - - 8670272b by jpmoresmau at 2014-12-10T01:35:31+00:00 header could contain several lines Closes haskell/haddock#348 - - - - - 4f9ae4f3 by Mateusz Kowalczyk at 2014-12-12T06:22:31+00:00 Revert "Merge branch 'reverts'" This reverts commit 5c93cc347773c7634321edd5f808d5b55b46301f, reversing changes made to 5b81a9e53894d2ae591ca0c6c96199632d39eb06. Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - e974ac94 by Duncan Coutts at 2014-12-12T06:26:11+00:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. Conflicts: haddock-api/src/Haddock.hs - - - - - 2f3a2365 by Herbert Valerio Riedel at 2014-12-12T06:26:51+00:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 1dbd6390 by Alan Zimmerman at 2014-12-12T06:32:07+00:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - bb6ff1f4 by Mateusz Kowalczyk at 2014-12-12T06:35:07+00:00 Bump ‘base’ constraint Follows the similar commit made on ghc-head branch - - - - - 466fe4ab by Krzysztof Gogolewski at 2014-12-12T06:37:42+00:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 97e080c9 by Edward Z. Yang at 2014-12-12T06:39:35+00:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: haddock-api/src/Haddock/ModuleTree.hs - - - - - 20b2af56 by Herbert Valerio Riedel at 2014-12-12T06:42:50+00:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. Conflicts: haddock-library/src/Documentation/Haddock/Parser.hs - - - - - b3ad269d by Austin Seipp at 2014-12-12T06:44:14+00:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 072df0dd by Austin Seipp at 2014-12-12T06:45:01+00:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - dbb9294a by Herbert Valerio Riedel at 2014-12-12T06:46:17+00:00 Collapse user-defined section by default (re haskell/haddock#335) Conflicts: haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs - - - - - f23ab545 by Yuras Shumovich at 2014-12-12T06:46:41+00:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - 753a4b67 by Austin Seipp at 2014-12-12T06:46:51+00:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8954e8f5 by Herbert Valerio Riedel at 2014-12-12T06:50:53+00:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - d2b06d61 by Gergő Érdi at 2014-12-12T07:07:30+00:00 Update Haddock to new pattern synonym type signature syntax Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 1ff02426 by Jan Stolarek at 2014-12-12T07:13:24+00:00 Follow changes from haskell/haddock#9812 Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - 06ad7600 by Richard Eisenberg at 2014-12-12T07:13:43+00:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 8fd2aa8b by Alan Zimmerman at 2014-12-12T07:22:25+00:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Backends/LaTeX.hs haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 95c3db98 by Thomas Winant at 2014-12-12T07:35:49+00:00 Support for PartialTypeSignatures Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs haddock-api/src/Haddock/Interface/Create.hs - - - - - 45494428 by Gergő Érdi at 2014-12-12T07:36:18+00:00 For pattern synonyms, render "pattern" as a keyword - - - - - a237e3eb by Mateusz Kowalczyk at 2014-12-12T12:27:13+00:00 Various fixups and bumps for next release - - - - - 22918bcd by Herbert Valerio Riedel at 2014-12-14T10:11:47+01:00 Remove redundant wild-card pattern match (this would otherwise cause a build-failure with `-Werror`) - - - - - 1d6ce947 by Herbert Valerio Riedel at 2014-12-14T10:17:06+01:00 Treat GHC 7.10 the same as GHC 7.9 ...since the current GHC 7.9 is going to become GHC 7.10 real-soon-now anyway - - - - - f434ea89 by Herbert Valerio Riedel at 2014-12-14T18:26:50+01:00 Fixup ghc.mk (follow-up to 1739375eb23342) This makes the GHC build-system aware of the data-files to be copied into the bindist (as haddock.cabal doesn't list those anymore) - - - - - 6fb839eb by Mateusz Kowalczyk at 2014-12-17T09:28:59+00:00 Only keep one Version instead of blindly appending - - - - - 40645489 by Mateusz Kowalczyk at 2014-12-18T07:09:44+00:00 Fix dependency version - - - - - 8b3b927b by Mateusz Kowalczyk at 2014-12-18T07:14:23+00:00 Print missing docs by default Adds --no-print-missing-docs - - - - - 59666694 by Mateusz Kowalczyk at 2014-12-18T07:21:37+00:00 update changelog - - - - - aa6d168e by Mateusz Kowalczyk at 2014-12-18T07:30:58+00:00 Update docs for @since - - - - - 2d7043ee by Luite Stegeman at 2014-12-19T18:29:35-06:00 hide projectVersion from DynFlags since it clashes with Haddock.Version.projectVersion - - - - - aaa70fc0 by Luite Stegeman at 2014-12-22T15:58:43+01:00 Add missing import for standalone haddock-api package - - - - - 9ce01269 by Herbert Valerio Riedel at 2014-12-22T17:48:45+01:00 Reset ghc-head with master's tree (this is an overwriting git merge of master into ghc-head) - - - - - fcd6fec1 by Herbert Valerio Riedel at 2014-12-22T17:51:52+01:00 Bump versions for ghc-7.11 - - - - - 525ec900 by Mateusz Kowalczyk at 2014-12-23T13:36:24+00:00 travis-ci: test with HEAD - - - - - cbf494b5 by Simon Peyton Jones at 2014-12-23T15:22:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 50e01c99 by Mateusz Kowalczyk at 2014-12-29T15:28:47+00:00 Make travis use 7.10.x - - - - - 475e60b0 by Njagi Mwaniki at 2014-12-29T15:30:44+00:00 Turn the README into GitHub Markdown format. Closes haskell/haddock#354 - - - - - 8cacf48e by Luite Stegeman at 2015-01-05T16:25:37+01:00 bump haddock-api ghc dependency to allow release candidate and first release - - - - - 6ed6cf1f by Simon Peyton Jones at 2015-01-06T16:37:47+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 8b484f33 by Simon Peyton Jones at 2015-01-08T15:50:22+00:00 Track naming change in DataCon - - - - - 23c5c0b5 by Alan Zimmerman at 2015-01-16T10:15:11-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e7a5532c by JP Moresmau at 2015-01-22T17:19:03+00:00 Ignore warnings, install Cabal 1.22 - - - - - 86942c84 by jpmoresmau at 2015-01-22T17:19:04+00:00 solve dataDir ambiguity - - - - - 5ceb743e by jpmoresmau at 2015-01-22T19:17:32+00:00 support GHC 7.10: no Safe-Inferred, Foldable instance - - - - - 6a3b3fb5 by Mateusz Kowalczyk at 2015-01-22T19:32:10+00:00 Update test files Test: a correct behaviour for fields comma-separating values. I'm surprised we had no bug open for this. Maybe it affects how haskell/haddock#301 renders now but I doubt. Operators: Seems GHC is giving us a new order for operators, something must have changed on their side again. cc @haasn , this makes the fixity to the side not match the order on the LHS which is a bit unpleasant. Maybe the fixity can be made to match the GHC order? Bug335: We expand examples by default now. Bug310: Now inferred safe. - - - - - 708f8b2f by jpmoresmau at 2015-01-22T19:36:59+00:00 Links to source location of class instance definitions - - - - - 5cf8a6da by Vincent Berthoux at 2015-01-22T19:59:58+00:00 Filter '\r' from comments due to Windows problems. On Windows this was causing newline to be rendered twice in code blocks. Closes haskell/haddock#359, fixes haskell/haddock#356. - - - - - 1749e6f0 by Mateusz Kowalczyk at 2015-01-22T20:31:27+00:00 Changelog only - - - - - c8145f90 by Mateusz Kowalczyk at 2015-01-22T23:34:05+00:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. - - - - - 14248254 by Mateusz Kowalczyk at 2015-01-22T23:43:18+00:00 Sort out some module import warnings - - - - - d8a38989 by Simon Peyton Jones at 2015-01-23T07:10:16-06:00 Track naming change in DataCon (cherry picked from commit 04cf63d0195837ed52075ed7d2676e71831e8a0b) - - - - - d3ac6ae4 by Alan Zimmerman at 2015-01-23T07:17:19-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit d61bbc75890e4eb0ad508b9c2a27b91f691213e6) - - - - - 4c1ffeb0 by Simon Peyton Jones at 2015-02-10T12:10:33+00:00 Track changes in HsSyn for quasi-quotes - - - - - 775d20f7 by Mateusz Kowalczyk at 2015-03-15T08:11:48+01:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. (cherry picked from commit 8e06728afb0784128ab2df0be7a5d7a191d30ff4) - - - - - f9245e72 by Phil Ruffwind at 2015-03-16T04:32:01-04:00 Prevent Synopsis from using up too much horizontal space When long type signatures occur in the Synopsis, the element is stretched beyond the width of the window. Scrollbars don't appear, so it's impossible to read anything when this happens. - - - - - cd8fa415 by Mateusz Kowalczyk at 2015-03-17T21:59:39+00:00 Update changelog Closes haskell/haddock#151 due to 71170fc77962f10d7d001e3b8bc8b92bfeda99bc - - - - - b5248b47 by Ben Gamari at 2015-03-25T17:12:17+00:00 Make the error encountered when a package can't be found more user-friendly Closes haskell/haddock#369 - - - - - b756b772 by Mateusz Kowalczyk at 2015-03-26T16:31:40+00:00 Remove now redundant imports - - - - - 5ea5e8dd by Mateusz Kowalczyk at 2015-03-26T16:45:52+00:00 Update test to account for \r filtering - - - - - 6539bfb3 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Test for anchor defaulting I delete the old tests because it turns out that: * test runner would never put them in scope of each other even with imports so just one would suffice * test runner actually needed some hacking to keep links so in the end we would end up with no anchors making them useless - - - - - 1a01d950 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Clearly default to variables in out of scope case - - - - - 7943abe8 by Mateusz Kowalczyk at 2015-03-27T01:14:11+00:00 Fix Hoogle display of constructors Fixes haskell/haddock#361 - - - - - 6d6e587e by Mateusz Kowalczyk at 2015-03-27T01:45:18+00:00 Fully qualify names in Hoogle instances output Closes haskell/haddock#263 - - - - - 52dac365 by Mateusz Kowalczyk at 2015-03-27T01:55:01+00:00 Update changelog - - - - - ca5af9a8 by Mateusz Kowalczyk at 2015-03-27T02:43:55+00:00 Output method documentation in Hoogle backend One thing of note is that we no longer preserve grouping of methods and print each method on its own line. We could preserve it if no documentation is present for any methods in the group if someone asks for it though. Fixes haskell/haddock#259 - - - - - a33f0c10 by Mateusz Kowalczyk at 2015-03-27T03:04:21+00:00 Don't print instance safety information in Hoogle Fixes haskell/haddock#168 - - - - - df6c935a by Mateusz Kowalczyk at 2015-03-28T00:11:47+00:00 Post-release version bumps and changelog - - - - - dde8f7c0 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Loosen bounds on haddock-* - - - - - de93bf89 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Expand response files in arguments Closes haskell/haddock#285 - - - - - 1f0b0856 by Zejun Wu at 2015-04-26T16:35:35-07:00 Do not insert anchor for section headings in contents box - - - - - 860439d7 by Simon Peyton Jones at 2015-05-01T09:36:47+01:00 Track change in API of TyCon - - - - - a32f3e5f by Adam Gundry at 2015-05-04T15:32:59+01:00 Track API changes to support empty closed type familes - - - - - 77e98bee by Ben Gamari at 2015-05-06T20:17:08+01:00 Ignore doc/haddock.{ps,pdf} - - - - - 663d0204 by Murray Campbell at 2015-05-11T04:47:37-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8bb0dcf5 by Murray Campbell at 2015-05-11T06:35:06-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit 2380f07c430c525b205ce2eae6dab23c8388d899) - - - - - bad900ea by Adam Bergmark at 2015-05-11T15:29:39+01:00 haddock-library: require GHC >= 7.4 `Data.Monoid.<>` was added in base-4.5/GHC-7.4 Closes haskell/haddock#394 Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - daceff85 by Simon Peyton Jones at 2015-05-13T12:04:21+01:00 Track the new location of setRdrNameSpace - - - - - 1937d1c4 by Alan Zimmerman at 2015-05-25T21:27:15+02:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - ee0fb6c2 by Łukasz Hanuszczak at 2015-05-27T11:51:31+02:00 Create simple method for indentation parsing. - - - - - 7d6fcad5 by Łukasz Hanuszczak at 2015-05-27T21:36:13+02:00 Make nested lists count indentation according to first item. - - - - - d6819398 by Łukasz Hanuszczak at 2015-05-27T22:46:13+02:00 Add simple test case for arbitrary-depth list nesting. - - - - - 2929c54d by Łukasz Hanuszczak at 2015-06-03T02:11:31+02:00 Add arbitrary-indent spec test for parser. - - - - - 9a0a9bb0 by Mateusz Kowalczyk at 2015-06-03T05:25:29+01:00 Update docs with info on new list nesting rule Fixes haskell/haddock#278 through commits from PR haskell/haddock#401 - - - - - 12efc92c by Mateusz Kowalczyk at 2015-06-03T05:29:26+01:00 Update some meta data at the top of the docs - - - - - 765ee49f by Bartosz Nitka at 2015-06-07T08:40:59-07:00 Add some Hacking docs for getting started - - - - - 19aaf851 by Bartosz Nitka at 2015-06-07T08:44:30-07:00 Fix markdown - - - - - 2a90cb70 by Mateusz Kowalczyk at 2015-06-08T15:08:36+01:00 Refine hacking instructions slightly - - - - - 0894da6e by Thomas Winant at 2015-06-08T23:47:28-05:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 10a9bb76 by Emanuel Borsboom at 2015-06-12T02:46:23+01:00 Build executable with '-threaded' (fixes haskell/haddock#399) - - - - - 7696b94f by Mateusz Kowalczyk at 2015-06-12T02:59:19+01:00 Update changelog for -threaded Closes haskell/haddock#400 - - - - - d3c118ec by Bartosz Nitka at 2015-06-12T03:00:58+01:00 Fix haddock: internal error: spliceURL UnhelpfulSpan (#207) Inferred type signatures don't have SrcSpans, so let's use the one from the declaration. I've tested this manually on the test-case from haskell/haddock#207, but I got stuck at trying to run the test-suite. - - - - - b67e843b by Mateusz Kowalczyk at 2015-06-12T03:01:50+01:00 Changelog for haskell/haddock#207 Fixes haskell/haddock#207, closes haskell/haddock#402 - - - - - 841d785e by jpmoresmau at 2015-06-12T16:03:16+01:00 Attach to instance location the name that has the same location file Fixes haskell/haddock#383 - - - - - 98791cae by Mateusz Kowalczyk at 2015-06-12T16:08:27+01:00 Update changelog Closes haskell/haddock#398 - - - - - 7c0b5a87 by Phil Ruffwind at 2015-06-12T13:07:25-04:00 Fix alignment of Source links in instance table in Firefox Due to a Firefox bug [1], a combination of 'whitespace: nowrap' on the parent element with 'float: right' on the inner element can cause the floated element to be displaced downwards for no apparent reason. To work around this, the left side is wrapped in its own <span> and set to 'float: left'. As a precautionary measure to prevent the parent element from collapsing entirely, we also add the classic "clearfix" hack. The latter is not strictly needed but it helps prevent bugs if the layout is altered again in the future. Fixes haskell/haddock#384. Remark: line 159 of src/Haddock/Backends/Xhtml/Layout.hs was indented to prevent confusion over the operator precedence of (<+>) vs (<<). [1]: https://bugzilla.mozilla.org/show_bug.cgi?id=488725 - - - - - cfe86e73 by Mateusz Kowalczyk at 2015-06-14T10:49:01+01:00 Update tests for the CSS changes - - - - - 2d4983c1 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding for Haskell source parser module. - - - - - 29548785 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement function for tagging parsed chunks with source spans. - - - - - 6a5e4074 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement simple string chunking based on HsColour library. - - - - - 6e52291f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create basic token classification method. - - - - - da971a27 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Adapt source span tagging to work with current whitespace handling. - - - - - 4feb5a22 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add record accessors to exports of hyperlinker parser module. - - - - - a8cc4e39 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Make parser module export all types and associated accessors. - - - - - fb8d468f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple HTML renderer for parsed source file. - - - - - 80747822 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for specifying the CSS file path in HTML source renderer. - - - - - 994dc1f5 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix identifier recognition in Haskell source parser. - - - - - b1bd0430 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix comment recognition in Haskell source parser. - - - - - 11db85ae by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for recognizing compiler pragmas in source parser. - - - - - 736c7bd3 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding of module for associating tokens with AST names. - - - - - 7e149bc2 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement utility method for extracting variable identifiers from AST. - - - - - 32eb640a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple mechanism for associating tokens with AST names. - - - - - d4eba5bc by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add dummy support for hyperlinking named tokens. - - - - - 2b76141f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matcher bug causing wrong items being hyperlinked. - - - - - 2d48002e by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Constrain elements exported by hyperlinker modules. - - - - - 9715eec6 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for type token recognition. - - - - - 8fa401cb by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for binding token recognition. - - - - - d062400b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement go-to-definition mechanism for local bindings. - - - - - f4dc229b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement module export- and import-list item hyperlinking. - - - - - c9a46d58 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matching to allow parenthesized operators hyperlinking. - - - - - 03aad95a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix weird hyperlinking of parenthesized operators. - - - - - b4694a7d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for type declaration anchors. - - - - - 7358d2d2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for top-level function declaration anchors. - - - - - dfc24b24 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix external anchors to contain HTML file extension. - - - - - a045926c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Refactor the way AST names are handled within detailed tokens. - - - - - c76049b4 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement hyperlinking of imported module names. - - - - - 2d2a1572 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix parsing of single line comments with broken up newlines. - - - - - 11afdcf2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix bug with improper newline handling. - - - - - 8137f104 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issues with escaped newlines in comments. - - - - - 34759b19 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for parsing C preprocessor macros. - - - - - 09f0f847 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for parser module of source hyperlinker. - - - - - 709a8389 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for AST module of source hyperlinker. - - - - - 4df5c227 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add command line option for generating hyperlinked source. - - - - - 7a755ea2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Extend module interface with rich source token stream field. - - - - - 494f4ab1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement source tokenization during interface creation process. - - - - - 5f21c953 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create hyperlinker module and plug it into the Haddock pipeline. - - - - - 0cc8a216 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for providing custom CSS files for hyperlinked source. - - - - - a32bbdc1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for fancy highlighting upon hovering over identifier. - - - - - d16d642a by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make source hyperlinker generate output in apropriate directory. - - - - - ae12953d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create module with hyperlinker utility functions. - - - - - 6d4952c5 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make external hyperlinks point to locations specified by source URLs. - - - - - 8417555d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Rewrite source generation to fixed links and directory structure. - - - - - ce9cec01 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add basic support for cross-package hyperlink generation. - - - - - 7eaf025c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Disable generating hyperlinks for module references. - - - - - a50bf92e by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make Haddock generate source for all interfaces (also hidden ones). - - - - - f5ae2838 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Prevent source parser from throwing exception when lexing fails. - - - - - db9ffbe0 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement workaround for Chrome highlighting issues. - - - - - 0b6b453b by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate correct anchors for data constructors. - - - - - c86d38bc by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate anchors for record field declarations. - - - - - 063abf7f by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issue with hyperlink highlight styling in Chrome browser. - - - - - 880fc611 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking constructor names in patters. - - - - - c9e89b95 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record patterns. - - - - - 17a11996 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record expressions. - - - - - 0eef932d by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Make hyperlinker respect pretty-printer flag and add documentation. - - - - - f87c1776 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Unexpose hyperlinker modules in Cabal configuration. - - - - - 4c9e2b06 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Setup HSpec framework for Haddock API package. - - - - - 4b20cb30 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add basic tests related to comment parsing. - - - - - 6842e919 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add tests related to parsing basic language constructs. - - - - - 87bffb35 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add simple tests for do-notation parsing. - - - - - e7af1841 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add very simple QuickCheck properties for source parser spec. - - - - - c84efcf1 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Create simple test runner for hyperlinker tests. - - - - - 76b90447 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for basic identifier hyperlinking. - - - - - 0fbf4df6 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for operator hyperlinking. - - - - - 731aa039 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for constructor hyperlinking. - - - - - 995a78a2 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for record expressions and patterns hyperlinking. - - - - - 3566875a by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for literal syntax highlighting. - - - - - 68469a35 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add hyperlinker test runner to .cabal and .gitignore files. - - - - - aa946c93 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Adapt hyperlinker test runner to have the same interface as HTML one. - - - - - ce34da16 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Fix hyperlinker test runner file paths and add pretty-printing option. - - - - - 0d7dd65e by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add reference files for hyperlinker test cases. - - - - - efa4a1e0 by Łukasz Hanuszczak at 2015-07-01T00:47:32+02:00 Make hyperlinker test runner strip local links from generated source. - - - - - 3e96e584 by Łukasz Hanuszczak at 2015-07-01T01:14:59+02:00 Create simple script for accepting hyperlinker test case references. - - - - - 526fe610 by Łukasz Hanuszczak at 2015-07-01T01:16:41+02:00 Re-accept hyperlinker test cases with local references stripped out. - - - - - 892e2cb3 by Łukasz Hanuszczak at 2015-07-01T01:22:09+02:00 Fix bug with diffing wrong files in hyperlinker test runner. - - - - - 9ff46039 by Łukasz Hanuszczak at 2015-07-01T18:04:46+02:00 Remove unused dependencies in Haddock API spec configuration. - - - - - 47969c07 by Łukasz Hanuszczak at 2015-07-01T18:32:19+02:00 Add support for hyperlinking synonyms in patterns. - - - - - a73449e0 by Łukasz Hanuszczak at 2015-07-01T18:33:44+02:00 Create test case for hyperlinking @-patterns. - - - - - c2077ed8 by Łukasz Hanuszczak at 2015-07-01T19:06:04+02:00 Add support for hyperlinking universally quantified type variables. - - - - - 68017342 by Łukasz Hanuszczak at 2015-07-01T19:28:32+02:00 Create hyperlinker test case with quantified type variables. - - - - - 51c01a78 by Łukasz Hanuszczak at 2015-07-01T19:34:22+02:00 Add scoped type variables test for polymorphism test case. - - - - - 13181ae2 by Łukasz Hanuszczak at 2015-07-01T19:56:27+02:00 Add record wildcards test for records hyperlinking test case. - - - - - 991b81dd by Łukasz Hanuszczak at 2015-07-01T21:01:42+02:00 Document some functions in XHTML utlity module. - - - - - 98c8dfe5 by Łukasz Hanuszczak at 2015-07-01T22:25:21+02:00 Make hyperlinker render qualified names as one entity. - - - - - 75e13b9b by Łukasz Hanuszczak at 2015-07-01T22:27:38+02:00 Add qualified name test for identifiers hyperlinking test case. - - - - - de1e143f by Łukasz Hanuszczak at 2015-07-02T12:32:59+02:00 Fix crash happening when hyperlinking type family declarations. - - - - - 7a8fb175 by Łukasz Hanuszczak at 2015-07-02T12:47:03+02:00 Add support for anchoring data family constructor declarations. - - - - - 3b404e49 by Łukasz Hanuszczak at 2015-07-02T13:31:05+02:00 Improve support for hyperlinking type families. - - - - - 59eb7143 by Łukasz Hanuszczak at 2015-07-02T13:33:34+02:00 Add hyperlinker test case for checking type and type family declarations. - - - - - d1cda0c0 by Łukasz Hanuszczak at 2015-07-02T13:41:38+02:00 Fix issue with operators being recognized as preprocessor directives. - - - - - da206c9d by Łukasz Hanuszczak at 2015-07-02T17:18:12+02:00 Fix broken tests for parsing and hyperlinking hash operators. - - - - - 53750d1b by Łukasz Hanuszczak at 2015-07-02T18:53:28+02:00 Add support for anchoring signatures in type class declarations. - - - - - 1fa5bb10 by Łukasz Hanuszczak at 2015-07-02T19:04:47+02:00 Make hyperlinker generate anchors only to top-level value bindings. - - - - - a542305c by Łukasz Hanuszczak at 2015-07-02T19:05:58+02:00 Create hyperlinker test case for type classes. - - - - - b0dd4581 by Łukasz Hanuszczak at 2015-07-04T16:28:26+02:00 Update docs with information about source hyperlinking. - - - - - 9795302a by Łukasz Hanuszczak at 2015-07-04T16:52:15+02:00 Update docs on using `--read-interface` option. - - - - - 9acdc002 by Łukasz Hanuszczak at 2015-07-04T17:15:26+02:00 Remove potentially dangerous record access in hyperlinker AST module. - - - - - fb3ab7be by Łukasz Hanuszczak at 2015-07-04T17:40:10+02:00 Make Haddock generate warnings about potential misuse of hyperlinker. - - - - - a324c504 by Łukasz Hanuszczak at 2015-07-04T17:43:22+02:00 Fix incorrect specification of source style option in doc file. - - - - - 3f01a8e4 by Łukasz Hanuszczak at 2015-07-05T17:06:36+02:00 Refactor source path mapping to use modules as indices. - - - - - ac70f5b1 by Łukasz Hanuszczak at 2015-07-05T17:47:34+02:00 Fix bug where not all module interfaces were added to source mapping. - - - - - f5e57da9 by Łukasz Hanuszczak at 2015-07-06T16:39:57+02:00 Extract main hyperlinker types to separate module. - - - - - 43974905 by Łukasz Hanuszczak at 2015-07-06T16:52:13+02:00 Move source paths types to hyperlinker types module. - - - - - 3e236055 by Łukasz Hanuszczak at 2015-07-06T17:06:19+02:00 Add support for hyperlinking modules in import lists. - - - - - 58233d9f by Łukasz Hanuszczak at 2015-07-06T17:26:49+02:00 Add short documentation for hyperlinker source map type. - - - - - 14da016d by Łukasz Hanuszczak at 2015-07-06T18:07:20+02:00 Fix bug with module name being hyperlinked to `Prelude`. - - - - - 8f79db52 by Łukasz Hanuszczak at 2015-07-06T18:23:47+02:00 Fix problem with spec build in Haddock API configuration. - - - - - e7cc056c by Adam Sandberg Eriksson at 2015-07-07T23:22:21+01:00 StrictData: print correct strictness marks - - - - - e8253ca8 by Mateusz Kowalczyk at 2015-07-07T23:58:28+01:00 Update changelog - - - - - 0aba676b by Mateusz Kowalczyk at 2015-07-07T23:58:33+01:00 Relax upper bound on GHC a bit - - - - - 7a595381 by Mateusz Kowalczyk at 2015-07-07T23:58:52+01:00 Delete trailing whitespace - - - - - 50976d5e by Adam Sandberg Eriksson at 2015-07-08T15:03:04+02:00 StrictData: changes in HsBang type - - - - - 83b045fa by Mateusz Kowalczyk at 2015-07-11T14:35:18+01:00 Fix expansion icon for user-collapsible sections Closes haskell/haddock#412 - - - - - b2a3b0d1 by Mateusz Kowalczyk at 2015-07-22T22:03:21+01:00 Make some version changes after 2.16.1 release - - - - - a8294423 by Ben Gamari at 2015-07-27T13:16:07+02:00 Merge pull request haskell/haddock#422 from adamse/adamse-D1033 Merge for GHC D1033 - - - - - c0173f17 by randen at 2015-07-30T14:49:08-07:00 Break the response file by line termination rather than spaces, since spaces may be within the parameters. This simple approach avoids having the need for any quoting and/or escaping (although a newline char will not be possible in a parameter and has no escape mechanism to allow it). - - - - - 47c0ca14 by Alan Zimmerman at 2015-07-31T10:41:52+02:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - 45a9d770 by Mateusz Kowalczyk at 2015-07-31T09:47:43+01:00 Update changelog - - - - - 347a20a3 by Phil Ruffwind at 2015-08-02T23:15:26+01:00 Avoid JavaScript error during page load in non-frame mode In non-frame mode, parent.window.synopsis refers to the synopsis div rather than the nonexistent frame. Unfortunately, the script wrongly assumes that if it exists it must be a frame, leading to an error where it tries to access the nonexistent attribute 'replace' of an undefined value (synopsis.location). Closes haskell/haddock#406 - - - - - 54ebd519 by Phil Ruffwind at 2015-08-02T23:27:10+01:00 Link to the definitions to themselves Currently, the definitions already have an anchor tag that allows URLs with fragment identifiers to locate them, but it is rather inconvenient to obtain such a URL (so-called "permalink") as it would require finding the a link to the corresponding item in the Synopsis or elsewhere. This commit adds hyperlinks to the definitions themselves, allowing users to obtain links to them easily. To preserve the original aesthetics of the definitions, we alter the color of the link so as to be identical to what it was, except it now has a hover effect indicating that it is clickable. Additionally, the anchor now uses the 'id' attribute instead of the (obsolete) 'name' attribute. Closes haskell/haddock#407 - - - - - 02cc8bb7 by Phil Ruffwind at 2015-08-02T23:28:02+01:00 Fix typo in Haddock.Backends.Xhtml.Layout: divSynposis -> divSynopsis Closes haskell/haddock#408 - - - - - 2eb0a458 by Phil Ruffwind at 2015-08-02T23:30:07+01:00 Fix record field alignment when name is too long Change <dl> to <ul> and use display:table rather than floats to layout the record fields. This avoids bug haskell/haddock#301 that occurs whenever the field name gets too long. Slight aesthetic change: the entire cell of the field's source code is now shaded gray rather than just the area where text exists. Fixes haskell/haddock#301. Closes haskell/haddock#421 - - - - - 7abb3402 by Łukasz Hanuszczak at 2015-08-02T23:32:14+01:00 Add some utility definitions for generating line anchors. - - - - - e0b1d79b by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Make hyperlinked source renderer generate line anchors. - - - - - 24dd4c9f by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Re-accept test cases after adding line anchors for each of them. - - - - - 0372cfcb by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Override source line flags when source hyperlinker is enabled. - - - - - a81bcd07 by Mateusz Kowalczyk at 2015-08-02T23:58:25+01:00 Update tests to follow HTML changes - - - - - d2d7426f by Łukasz Hanuszczak at 2015-08-06T20:54:59+02:00 Fix quote syntax for promoted types. - - - - - 668cf029 by Łukasz Hanuszczak at 2015-08-06T21:12:00+02:00 Apply promoted type quoting to type-level consing. - - - - - 89f8e7c6 by Łukasz Hanuszczak at 2015-08-06T21:17:10+02:00 Extend advanced types test case with other examples. - - - - - 86494bca by Łukasz Hanuszczak at 2015-08-06T21:22:06+02:00 Rename advanced types test case and accept new output. - - - - - dbb7c7c0 by Adam Sandberg Eriksson at 2015-08-09T23:01:05+02:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 2a7704fa by Ben Gamari at 2015-08-10T13:18:05+02:00 Merge pull request haskell/haddock#433 from adamse/split-hsbang HsBang is split into HsSrcBang and HsImplBang - - - - - 891954bc by Thomas Miedema at 2015-08-15T14:51:18+02:00 Follow changes in GHC build system - - - - - b55d32ab by Mateusz Kowalczyk at 2015-08-21T18:06:09+01:00 Make Travis use 7.10.2 - - - - - 97348b51 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Move SYB utilities to standalone module. - - - - - 748ec081 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement `everywhere` transformation in SYB module. - - - - - 011cc543 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement generic transformation constructor. - - - - - b9510db2 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Create simple utility module for type specialization. - - - - - 43229fa6 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Make type of type specialization function more general. - - - - - fd844e90 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Add basic HTML test case for checking instance specialization. - - - - - 6ea0ad04 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Make HTML class instance printer take optional signature argument. - - - - - 65aa41b6 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Refactor instance head type to record instead of a meaningless tuple. - - - - - 3fc3bede by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add expandable method section for each class instance declaration. - - - - - 99ceb107 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Move dummy post-family instances for `DocName` to `Types` module. - - - - - e98f4708 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create convenience functions for type specialization module. - - - - - b947552f by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Hook type specialization logic with HTML pretty-printer. - - - - - dcaa8030 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create stub functions for sugaring specialized types. - - - - - fa84bc65 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement list syntax sugaring logic for specialized types. - - - - - e8b05b07 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement tuple syntax sugaring logic for specialized types. - - - - - 68a2e5bc by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Get rid of code duplication in type specialization module. - - - - - 4721c336 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create scaffolding of a framework for renaming specialized types. - - - - - 271b488d by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in missing cases in specialized type renaming function. - - - - - bfa5f2a4 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Remove code duplication in specialized type renamer. - - - - - ea6bd0e8 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Change state of the type renaming monad. - - - - - 77c5496e by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement simple mechanism for generating new type names. - - - - - 91bfb48b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in stub behaviour with actual environment renaming. - - - - - d244517b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix logic behind binder type renaming. - - - - - f3c5e360 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add SYB-like utility function for performing stateful queries. - - - - - eb3f9154 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create function for retrieving free variables from given type. - - - - - a94561d3 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix compilation error caused by incorrect type signature. - - - - - 8bb707cf by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Move `SetName` class definition to types module. - - - - - 5800b13b by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Hook type renamer with instance method HTML pretty-printer. - - - - - 6a480164 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some test cases for type renamer. - - - - - 839842f7 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized signatures refer to original signature declaration. - - - - - 4880f7c9 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized methods be nicely formatted again. - - - - - ab5a6a2e by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Attach source locations to the specialized class methods. - - - - - 43f8a559 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Extend instances test case to also test multi-name type signatures. - - - - - 59bc751c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix tab-based indentation in instances test case. - - - - - c2126815 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Improve placement of instance methods expander button. - - - - - 0a32e287 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add new data type declaration to instance specialization test case. - - - - - 5281af1f by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make type renamer first try single-letter names as alternatives. - - - - - 7d509475 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix type renamer bug with incorrect names being generated. - - - - - 0f35bf7c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some documentation and refactor type specialization module. - - - - - da1d0803 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix another bug where type renamer was generating incorrect names. - - - - - cd39b5cb by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Refactor type renamer to rebinding and pure renaming phases. - - - - - 850251f4 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix unwitting compilation bug. - - - - - e5e9fc01 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Integrate instance specification type into class instance definition. - - - - - 825b0ea0 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer neccessary instance specification type. - - - - - cdba44eb by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix declaration converter to use more appropriate mode for methods. - - - - - bc45c309 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug with types not being specialized at all. - - - - - 5d8e5d89 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug where instance expander was opening wrong section. - - - - - 6001ee41 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix another type renamer bug where not all names were rebound. - - - - - 5f58ce2a by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix yet another renamer bug where some names were not unique. - - - - - 8265e521 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split instance subsection layout method to top-level declarations. - - - - - e5e66298 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Rearrange layout of instance methods in generated documentation. - - - - - a50b4eea by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer used layout method. - - - - - 2ff36ec2 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach section title to the instance methods block. - - - - - 7ac15300 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Add basic tests for associated types in instances test case. - - - - - db0ea2f9 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach associated types information to instance header. - - - - - 71cad4d5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details section contain associated types information. - - - - - deee2809 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Improve look of rendered associated families in instance details. - - - - - 839d13a5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Introduce alternative type for family declarations. - - - - - d397f03f by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details record use new type for family declarations. - - - - - 2b23fe97 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split printer of type family header to separate functions. - - - - - c3498cdc by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Implement HTML renderer for pseudo-family declarations. - - - - - c12bbb04 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Apply type specializer to associated type family declarations. - - - - - 2fd69ff2 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Create helper method for specializing type signatures. - - - - - 475826e7 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Refactor specializer module to be independent from XHTML backend. - - - - - f00b431c by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add some documentation for instance head specializer. - - - - - a9fef2dc by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix bug with missing space in documentation for associated types. - - - - - 50e29056 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with incorrect instance details sections being expanded. - - - - - e6dfdd03 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by adding instance details section. - - - - - 75565b2a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make section identifier of instance details more GHC-independent. - - - - - add0c23e by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Re-accept tests after applying deterministic section identifiers. - - - - - 878f2534 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make identifier generation also architecture-independent. - - - - - 48be69f8 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with instance expander hijacking type hyperlink click. - - - - - 47830c1f by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Get rid of dreadful hashing function for generating identifiers. - - - - - 956cd5af by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Move `InstOrigin` type declaration to more appropriate module. - - - - - bf672ed3 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by changes related to instance expander. - - - - - 8f2a949a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add examples with type operators to the instances test case. - - - - - 64600a84 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add basic support for sugaring infix type operators. - - - - - 747d71b8 by Łukasz Hanuszczak at 2015-08-21T18:22:34+01:00 Add support for sugaring built-in function syntax. - - - - - d4696ffb by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Remove default methods from Hoogle class output. - - - - - bf0e09d7 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add fixity declarations in Hoogle backend output. - - - - - 90e91a51 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix bug with incorrect fixities being generated in Hoogle backend. - - - - - 48f11d35 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve class type family declarations output in Hoogle backend. - - - - - 661e8e8f by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add missing default family equations in Hoogle output. - - - - - e2d64103 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve formatting of class details output in Hoogle backend. - - - - - 490fc377 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix weird-looking Hoogle output for familyless classes. - - - - - ea115b64 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create script file for new HTML test runner. - - - - - 609913d3 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Set default behaviour if no arguments given. - - - - - dc115f67 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for providing optional arguments for test runner. - - - - - d93ec867 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve output of test runner error messages. - - - - - 0be9fe12 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for executing Haddock process in test runner. - - - - - 4e4d00d9 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add GHC path to test runner configuration. - - - - - d67a2086 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make GHC path a test runner command-line argument. - - - - - c810079a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Extend test runner configuration with Haddock arguments. - - - - - fee18845 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor test runner and create stub functions. - - - - - ff7c161f by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make test runner actually run Haddock executable. - - - - - 391f73e6 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with test runner not producing any output files. - - - - - 81a74e2d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Setup skeleton of framework for running tests. - - - - - f8a79ec4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with modules not being found in global search mode. - - - - - 7e700b4d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make Haddock standard output redirection be more configurable. - - - - - 53b4c17a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Incorporate old, ugly functions for comparing output files. - - - - - 8277c8aa by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor architecture of test runner output checking functions. - - - - - 587bb414 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement actual diffing mechanism. - - - - - 9ed2b5e4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve code style to match popular guidelines. - - - - - 14bffaf8 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make it possible to choose alternative diff tool. - - - - - 5cdfb005 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create stub methods for processing test output as XML documents. - - - - - 7ef8e12e by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement link-stripping logic as simple SYB transformation. - - - - - 8a1fcd4f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Incorporate link stripping to output diffing mechanism. - - - - - 37dba2bc by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement footer-stripping logic. - - - - - 9cd52120 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Add missing dependencies in Cabal configuration file. - - - - - e0f83c6e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix issue with output being printed in incorrect order. - - - - - 0a94fbb0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to run tests without generating diff. - - - - - 76a58c6f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor HTML test suite boilerplate to external package. - - - - - af41e6b0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utilities for storing directory configuration. - - - - - d8f0698f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move IO-dependent config of HTML test suite to test package. - - - - - 17369fa0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Enable all compiler warnings in Haddock test package configuration. - - - - - 9d03b47a by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move Haddock runner of HTML test suite to Haddock test package. - - - - - 4b3483c5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 03754194 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience wrappers to simplify in test entry points. - - - - - 27476ab7 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adjust module visibility and items they export. - - - - - c40002ba by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Remove no longer useful test option. - - - - - 55ab2541 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Change extension of test files used for diffing. - - - - - 136bf4e4 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor and simplify XHTML helper module of test package. - - - - - 69f7e3df by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix typo in link stripper of HTML test suite runner. - - - - - 0c3c1c6b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience script for running specific HTML tests. - - - - - 489e1b05 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement utility functions for conditional link stripping. - - - - - 0f985dc3 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt `hypsrc-test` module to work with new testing framework. - - - - - 927406f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement output accepting mechanism in test package. - - - - - 8545715e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utility function for recursive obtaining directory contents. - - - - - cb70381f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 019599b5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix path handling in test runner. - - - - - 399b985b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to specify ignored files for test output. - - - - - 41b3d93d by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt HTML test runner to use new ignoring functionality. - - - - - e2091c8b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix bug with not all test output files being checked. - - - - - b22134f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Specify ignored files for hyperlinker source test runner. - - - - - 3301dfa1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Copy test runner script for hyperlinked source case. - - - - - d39a6dfa by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner invoking Haddock in incorrect mode. - - - - - f32c8ff3 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix path handling in test module loader. - - - - - 10f94ee9 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make test runner ignore test packages with no modules. - - - - - 5dc4239c by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create test runner entry points for LaTeX test suite. - - - - - 58d1f7cf by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with unnecessary checking old test output. - - - - - c7ce76e1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Re-implement test acceptance functionality. - - - - - 13bbabe8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix warning about no longer needed definition. - - - - - 958a99b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Adapt Cabal configuration to execute LaTeX suite with new runner. - - - - - 550ff663 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Setup test suite for Hoogle backend. - - - - - 3aa969c4 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make Hoogle backend create output directory if needed. - - - - - eb085b02 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Add appropriate .gitignore entry and configure Hoogle test suite. - - - - - a50bf915 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner failing when run on multiple test packages. - - - - - bf5368b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create simple test cases for Hoogle backend. - - - - - 6121ba4b by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create helper function for conversion between XML and XHTML. - - - - - cb516061 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Refactor existing code to use XHTML printer instead of XML one. - - - - - e2de8c82 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Improve portability of test runner scripts. - - - - - 9563e774 by Łukasz Hanuszczak at 2015-08-22T23:43:16+02:00 Remove redundant import statement. - - - - - 55353df1 by Łukasz Hanuszczak at 2015-08-24T23:09:20+02:00 Fix bug with accepting to non-existing directory. - - - - - 00a334ca by Łukasz Hanuszczak at 2015-08-24T23:09:47+02:00 Accept output for Hoogle and LaTeX backends. - - - - - 29191d8b by Łukasz Hanuszczak at 2015-08-24T23:14:18+02:00 Get rid of obsolete testing utilities. - - - - - bbb25db3 by Łukasz Hanuszczak at 2015-08-24T23:18:50+02:00 Update sandbox setup guide to work with Haddock test package. - - - - - cfd45248 by Łukasz Hanuszczak at 2015-08-24T23:51:30+02:00 Make Travis aware of Haddock test package. - - - - - 74185b7a by Łukasz Hanuszczak at 2015-08-25T17:41:59+02:00 Fix test suite failure when used with Stack. - - - - - 18769697 by Łukasz Hanuszczak at 2015-08-25T18:02:09+02:00 Add sample Stack setup to the hacking guide. - - - - - 22715eeb by Łukasz Hanuszczak at 2015-08-25T18:04:47+02:00 Fix Markdown formatting of README file. - - - - - b49ec386 by Łukasz Hanuszczak at 2015-08-25T18:13:36+02:00 Setup Haddock executable path in Travis configuration. - - - - - 5d29eb03 by Eric Seidel at 2015-08-30T09:55:58-07:00 account for changes to ipClass - - - - - f111740a by Ben Gamari at 2015-09-02T13:20:37+02:00 Merge pull request haskell/haddock#443 from bgamari/ghc-head account for changes to ipClass - - - - - a2654bf6 by Jan Stolarek at 2015-09-03T01:32:57+02:00 Follow changes from haskell/haddock#6018 - - - - - 2678bafe by Richard Eisenberg at 2015-09-21T12:00:47-04:00 React to refactoring CoAxiom branch lists. - - - - - ebc56e24 by Edward Z. Yang at 2015-09-21T11:53:46-07:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4a8c4198 by Tamar Christina at 2015-09-27T13:59:08+02:00 Create Process: removed PhaseFailed - - - - - 7e99b790 by Oleg Grenrus at 2015-09-27T20:52:10+03:00 Generate docs for orphan instances - - - - - 32e932e2 by Oleg Grenrus at 2015-09-28T07:21:11+03:00 Have source links for orphan instances - - - - - c2eb9f4f by Oleg Grenrus at 2015-09-28T07:24:58+03:00 Print orphan instances header only if required - - - - - ff96f978 by Oleg Grenrus at 2015-09-28T07:40:54+03:00 Add orphan instances link to contents box - - - - - d72490a6 by Oleg Grenrus at 2015-09-28T16:37:44+03:00 Fix orphan instance collapsing - - - - - 25d3dfe5 by Ben Gamari at 2015-10-03T12:38:09+02:00 Merge pull request haskell/haddock#448 from Mistuke/fix-silent-death-of-runInteractive Remove PhaseFailed - - - - - 1e45e43b by Edward Z. Yang at 2015-10-11T13:10:10-07:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b1370ac1 by Adam Gundry at 2015-10-16T16:26:42+01:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 60bef421 by Simon Peyton Jones at 2015-10-26T12:52:36+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 4c1898ca by Simon Peyton Jones at 2015-10-27T14:24:56+00:00 Track change to PatSyn.patSynSig - - - - - 25108e85 by Simon Peyton Jones at 2015-10-27T17:34:18+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - 693643ac by Ben Gamari at 2015-10-28T14:33:06+01:00 Account for Typeable changes The treatment of type families changed. - - - - - cd7c2221 by Simon Peyton Jones at 2015-10-30T13:03:51+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - 712032cb by Herbert Valerio Riedel at 2015-10-31T11:01:45+01:00 Relax upper bound on `base` to allow base-4.9 - - - - - 0bfa0475 by Simon Peyton Jones at 2015-10-31T19:08:13+00:00 More adaption to wildcard-refactor - - - - - 0a3c0cb7 by Simon Peyton Jones at 2015-10-31T22:14:43+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - c4fd4ec9 by Alan Zimmerman at 2015-11-01T11:16:34+01:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 42cdd882 by Matthew Pickering at 2015-11-06T20:02:16+00:00 Change for IEThingWith - - - - - f368b7be by Ben Gamari at 2015-11-11T11:35:51+01:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - e32965b8 by Simon Peyton Jones at 2015-11-13T12:18:17+00:00 Merge with origin/head - - - - - ebcf795a by Edward Z. Yang at 2015-11-13T21:56:27-08:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4e23989f by Simon Peyton Jones at 2015-11-18T11:32:54+00:00 Wibbles to Haddock - - - - - 2289cd4a by Simon Peyton Jones at 2015-11-20T23:12:49+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor - - - - - 695975a6 by Alan Zimmerman at 2015-11-21T21:16:12+02:00 Update to match GHC wip/T11019 - - - - - bbba21e7 by Simon Peyton Jones at 2015-11-23T13:54:31+00:00 merge with origin/ghc-head - - - - - 3d664258 by Simon Peyton Jones at 2015-11-23T17:17:18+00:00 Wibble - - - - - e64cf586 by Herbert Valerio Riedel at 2015-12-05T00:29:55+01:00 Canonicalise Monad instances - - - - - a2de15a7 by Alan Zimmerman at 2015-12-05T17:33:52+02:00 Matching changes for haskell/haddock#11028 - - - - - cc29a3e4 by Alan Zimmerman at 2015-12-05T19:45:33+02:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 95dd15d1 by Richard Eisenberg at 2015-12-11T17:33:39-06:00 Update for type=kinds - - - - - cb5fd9ed by Herbert Valerio Riedel at 2015-12-14T15:07:30+00:00 Bump versions for ghc-7.11 - - - - - 4f286d96 by Simon Peyton Jones at 2015-12-14T15:10:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 13ea2733 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 098df8b8 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track changes in HsSyn for quasi-quotes - - - - - 716a64de by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track change in API of TyCon - - - - - 77a66bca by Adam Gundry at 2015-12-14T15:10:58+00:00 Track API changes to support empty closed type familes - - - - - f2808305 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track the new location of setRdrNameSpace - - - - - ba8b08a4 by Alan Zimmerman at 2015-12-14T15:10:59+00:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - a4ded87e by Thomas Winant at 2015-12-14T15:14:05+00:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 25c78107 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: print correct strictness marks - - - - - 6cbc41c4 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: changes in HsBang type - - - - - ad46821a by Alan Zimmerman at 2015-12-14T15:14:06+00:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - abc0ae5b by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 3308d06c by Thomas Miedema at 2015-12-14T15:14:07+00:00 Follow changes in GHC build system - - - - - 6c763deb by Eric Seidel at 2015-12-14T15:14:07+00:00 account for changes to ipClass - - - - - ae5b4eac by Jan Stolarek at 2015-12-14T15:17:00+00:00 Follow changes from haskell/haddock#6018 - - - - - ffbc40e0 by Richard Eisenberg at 2015-12-14T15:17:02+00:00 React to refactoring CoAxiom branch lists. - - - - - d1f531e9 by Edward Z. Yang at 2015-12-14T15:17:02+00:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 79f73754 by Tamar Christina at 2015-12-14T15:17:02+00:00 Create Process: removed PhaseFailed - - - - - 3d37bebb by Edward Z. Yang at 2015-12-14T15:20:46+00:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 5f8a9e44 by Adam Gundry at 2015-12-14T15:20:48+00:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 79dda70f by Simon Peyton Jones at 2015-12-14T15:26:02+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 959930fb by Simon Peyton Jones at 2015-12-14T15:37:50+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - e18a8df5 by Simon Peyton Jones at 2015-12-14T15:37:52+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - aa35ab52 by Simon Peyton Jones at 2015-12-14T15:40:18+00:00 More adaption to wildcard-refactor - - - - - 8ceef94b by Simon Peyton Jones at 2015-12-14T15:46:04+00:00 Track change to PatSyn.patSynSig - - - - - cd81e83d by Ben Gamari at 2015-12-14T15:46:06+00:00 Account for Typeable changes The treatment of type families changed. - - - - - 63c9117c by Herbert Valerio Riedel at 2015-12-14T15:46:34+00:00 Relax upper bound on `base` to allow base-4.9 - - - - - a484c613 by Alan Zimmerman at 2015-12-14T15:47:46+00:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 2c26fa51 by Matthew Pickering at 2015-12-14T15:47:47+00:00 Change for IEThingWith - - - - - 593baa0f by Ben Gamari at 2015-12-14T15:49:21+00:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - b6b5ca78 by Edward Z. Yang at 2015-12-14T15:49:54+00:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b5b0e072 by Alan Zimmerman at 2015-12-14T15:54:20+00:00 Update to match GHC wip/T11019 - - - - - 14ddeb68 by Simon Peyton Jones at 2015-12-14T15:54:22+00:00 Wibble - - - - - 10a90ad8 by Herbert Valerio Riedel at 2015-12-14T15:54:22+00:00 Canonicalise Monad instances - - - - - ed68ac50 by Alan Zimmerman at 2015-12-14T15:55:48+00:00 Matching changes for haskell/haddock#11028 - - - - - 3f7e5a2d by Alan Zimmerman at 2015-12-14T15:55:49+00:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 6543a73f by Richard Eisenberg at 2015-12-14T15:59:55+00:00 Update for type=kinds - - - - - 193a5c48 by Matthew Pickering at 2015-12-14T18:17:00+00:00 Changes to compile with 8.0 - - - - - add669ec by Matthew Pickering at 2015-12-14T18:47:12+00:00 Warnings - - - - - 223f3fb4 by Ben Gamari at 2015-12-15T23:45:05+01:00 Update for D1200 - - - - - d058388f by Ben Gamari at 2015-12-16T05:40:17-05:00 Types: Add Outputable[Bndr] DocName instances - - - - - 62ecd7fb by Ben Gamari at 2015-12-16T09:23:09-05:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ddbc187a by Ben Gamari at 2015-12-16T17:54:55+01:00 Update for D1200 - - - - - cec83b52 by Ben Gamari at 2015-12-16T17:54:55+01:00 Types: Add Outputable[Bndr] DocName instances - - - - - d12ecc98 by Ben Gamari at 2015-12-16T17:54:55+01:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ada1616f by Ben Gamari at 2015-12-16T17:54:58+01:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a4f0383d by Ben Gamari at 2015-12-16T23:32:38+01:00 Fix Hyperlinker GHC.con_names is now GHC.getConNames - - - - - a10e6849 by Ben Gamari at 2015-12-20T00:54:11+01:00 Merge remote-tracking branch 'mrhania/testing-framework-improvements' into ghc-head - - - - - f078b4fd by Ben Gamari at 2015-12-20T00:59:51+01:00 test: Compatibility with Cabal 1.23 - - - - - 88a511a9 by Ben Gamari at 2015-12-20T01:14:35+01:00 Merge remote-tracking branch 'phadej/orphans' into ghc-head - - - - - 4e250f36 by Ben Gamari at 2015-12-20T01:14:52+01:00 Add html-test for orphan instances output - - - - - 87fffbad by Alan Zimmerman at 2015-12-20T09:50:42+02:00 Update for GHC trac#11258 Adding locations to RdrName in FieldOcc and AmbiguousFieldOcc - - - - - 6b7e51c9 by idontgetoutmuch at 2015-12-20T21:01:47+00:00 Merge pull request haskell/haddock#1 from haskell/ghc-head Ghc head - - - - - 229c1fb5 by Dominic Steinitz at 2015-12-21T07:19:16+00:00 Handle inline math with mathjax. - - - - - 57902d66 by Dominic Steinitz at 2015-12-21T08:07:11+00:00 Fix the documentation for haddock itself. Change notation and add support for inline math. Allow newlines in display math. Add a command line option for the mathjax url (you might want to use a locally installed version). Rebase tests because of extra url and version change. Respond to (some of the) comments. Fix warnings in InterfaceFile.hs - - - - - 0e69f236 by Herbert Valerio Riedel at 2015-12-21T18:30:43+01:00 Fix-up left-over assumptions of GHC 7.12 into GHC 8.0 - - - - - c67f8444 by Simon Peyton Jones at 2015-12-22T16:26:56+00:00 Follow removal of NamedWildCard from HsType - - - - - da40327a by Ben Gamari at 2015-12-23T14:15:28+01:00 html-test/Operators: Clear up ambiguous types For reasons that aren't entirely clear a class with ambiguous types was accepted by GHC <8.0. I've added a functional dependency to clear up this ambiguity. - - - - - 541b7fa4 by Ben Gamari at 2015-12-23T14:18:51+01:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 0febc947 by Ben Gamari at 2015-12-24T00:30:20+01:00 hoogle-test/AssocTypes: Allow AmbiguousTypes GHC 8.0 complains otherwise - - - - - 25810841 by Ben Gamari at 2015-12-24T00:33:18+01:00 OrphanInstances: Accept test output - - - - - 841987f3 by Ben Gamari at 2015-12-25T11:03:11+01:00 Merge remote-tracking branch 'idontgetoutmuch/ghc-head' into ghc-head - - - - - 358391f0 by Ben Gamari at 2015-12-26T10:44:50+01:00 Add missing import - - - - - a8896885 by Ben Gamari at 2015-12-26T10:45:27+01:00 travis: Use Travis containers - - - - - 85e82134 by Herbert Valerio Riedel at 2015-12-30T17:25:39+01:00 tweak version bounds for GHC-8.1 - - - - - 672a5f75 by randen at 2016-01-01T23:45:25-08:00 The Haddock part for fully gcc-like response files " driver/Main.hs * Moved the response file handling into ResponseFile.hs, updating import section as appropriate. * driver/ResponseFile.hs * New file. In anticipation that maybe some day this could be provided by another library, and to make it possible to unit test, this functionality is pulled out of the Main.hs module, and expanded to support the style/format of response files which gcc uses. * The specification for the format of response files which gcc generates and consumes, seems to be best derived from the gcc code itself (libiberty/argv.c), so that is what has been done here. * This is intended to fix haskell/haddock#379 * driver-test/Main.hs * New file for testing code in the driver source tree * driver-test/ResponseFileSpec.hs * Tests, adapted/adopted from the same gcc code where the escaping/unescaping is from, in the hspec style of unit tests * haddock.cabal * Add the driver-test test-suite. Introduces a new library dependency (upon hspec) for the haddock driver target in the haddock.cabal file, but practically, this should not be a problem as the haddock-api tests already depend on hspec. - - - - - 498781df by Ben Gamari at 2016-01-06T13:41:04+01:00 Version bumps and changelog - - - - - 8451e46a by Ben Gamari at 2016-01-06T13:47:17+01:00 Merge remote-tracking branch 'randen/bug468' - - - - - fb2d9181 by Ben Gamari at 2016-01-06T08:14:42-05:00 Add ResponseFile to OtherModules - - - - - 2cb2d2e3 by Ben Gamari at 2016-01-06T14:35:00+01:00 Merge branch 'master' into ghc-head - - - - - 913477d4 by Eric Seidel at 2016-01-11T14:57:57-08:00 deal with un-wiring of IP class - - - - - c557a4b3 by Alan Zimmerman at 2016-01-15T11:14:35+02:00 Update to match wip/T11430 in GHC - - - - - 3e135093 by Alan Zimmerman at 2016-01-16T18:21:59+01:00 Update to match wip/T11430 in GHC - - - - - c48ef2f9 by Ben Gamari at 2016-01-18T09:50:06+01:00 Merge remote-tracking branch 'gridaphobe/ghc-head' into ghc-head - - - - - 9138a1b0 by Eric Seidel at 2016-01-18T12:50:15+01:00 deal with un-wiring of IP class (cherry picked from commit 17388b0f0029d969d79353be7737eb01c7b8dc5f) - - - - - b48c172e by Joachim Breitner at 2016-01-19T00:11:38+01:00 Make sure --mathjax affects all written HTML files This fixes haskell/haddock#475. - - - - - af61fe63 by Ryan Scott at 2016-02-07T23:25:57+01:00 Render */# instead of TYPE 'Lifted/TYPE 'Unlifted (fixes haskell/haddock#473) - - - - - b6458693 by Ben Gamari at 2016-02-07T23:29:27+01:00 Merge pull request haskell/haddock#477 from haskell/issue-475 Make sure --mathjax affects all written HTML files - - - - - adcc0071 by Ben Gamari at 2016-02-07T23:34:52+01:00 Merge branch 'master' into ghc-head - - - - - d0404e61 by Ben Gamari at 2016-02-08T12:46:49+01:00 doc: Switch to Sphinx - - - - - acb153b3 by Ben Gamari at 2016-02-08T12:46:56+01:00 Document --use-unicode flag - - - - - c20bdf1d by Ben Gamari at 2016-02-08T13:41:24+01:00 Fix GHC and haddock-library dependency bounds - - - - - 8d946801 by Ben Gamari at 2016-02-08T14:54:56+01:00 testsuite: Rework handling of output sanitization Previously un-cleaned artifacts were kept as reference output, making it difficult to tell what has changed and causing spurious changes in the version control history. Here we rework this, cleaning the output during acceptance. To accomplish this it was necessary to move to strict I/O to ensure the reference handle was closed before accept attempts to open the reference file. - - - - - c465705d by Ben Gamari at 2016-02-08T15:36:05+01:00 test: Compare on dump For reasons I don't understand the Xml representations differ despite their textual representations being identical. - - - - - 1ec0227a by Ben Gamari at 2016-02-08T15:36:05+01:00 html-test: Accept test output - - - - - eefbd63a by Ben Gamari at 2016-02-08T15:36:08+01:00 hypsrc-test: Accept test output And fix impredicative Polymorphism testcase. - - - - - d1df4372 by Ben Gamari at 2016-02-08T15:40:44+01:00 Merge branch 'fix-up-testsuite' - - - - - 206a3859 by Phil Ruffwind at 2016-02-08T17:51:21+01:00 Move the permalinks to "#" on the right side Since pull request haskell/haddock#407, the identifiers have been permalinked to themselves, but this makes it difficult to copy the identifier by double-clicking. To work around this usability problem, the permalinks are now placed on the far right adjacent to "Source", indicated by "#". Also, 'namedAnchor' now uses 'id' instead of 'name' (which is obsolete). - - - - - 6c89fa03 by Phil Ruffwind at 2016-02-08T17:54:44+01:00 Update tests for previous commit - - - - - effaa832 by Ben Gamari at 2016-02-08T17:56:17+01:00 Merge branch 'anchors-redux' - - - - - 9a2bec90 by Ben Gamari at 2016-02-08T17:58:40+01:00 Use -fprint-unicode-syntax when --use-unicode is enabled This allows GHC to render `*` as its Unicode representation, among other things. - - - - - 28ecac5b by Ben Gamari at 2016-02-11T18:53:03+01:00 Merge pull request haskell/haddock#480 from bgamari/sphinx Move documentation to ReStructuredText - - - - - 222e5920 by Ryan Scott at 2016-02-11T15:42:42-05:00 Collapse type/data family instances by default - - - - - a80ac03b by Ryan Scott at 2016-02-11T20:17:09-05:00 Ensure expanded family instances render correctly - - - - - 7f985231 by Ben Gamari at 2016-02-12T10:04:22+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - d4eda086 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Various cleanups - - - - - 79bee48d by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show kind signatures for type family variables Addresses GHC haskell/haddock#11588. - - - - - b2981d98 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show 'where ...' after closed type family Seems like we should ideally show the actual equations as well but that seems like it would be a fair amount of work - - - - - cfc0e621 by Ben Gamari at 2016-02-18T22:48:12+01:00 Merge pull request haskell/haddock#483 from bgamari/T11588 Fix GHC haskell/haddock#11588 This fixes GHC haskell/haddock#11588: * Show where ... after closed type families * Show kind signatures on type family type variables - - - - - 256e8a0d by Ben Gamari at 2016-02-18T23:15:39+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 32402036 by Richard Eisenberg at 2016-02-24T13:21:44-05:00 Follow-on changes to support RuntimeRep - - - - - 2b1c572d by Matthew Pickering at 2016-03-04T21:04:02+00:00 Remove unused functions - - - - - eb906f50 by Richard Eisenberg at 2016-03-13T21:17:20+01:00 Follow-on changes to support RuntimeRep (cherry picked from commit ab954263a793d8ced734459d6194a5d89214b66c) - - - - - 8c34ef34 by Richard Eisenberg at 2016-03-14T23:47:23-04:00 Changes due to fix for GHC#11648. - - - - - 0e022014 by Richard Eisenberg at 2016-03-15T14:06:45+01:00 Changes due to fix for GHC#11648. (cherry picked from commit bb994de1ab0c76d1aaf1e39c54158db2526d31f1) - - - - - ed3f78ab by Rik Steenkamp at 2016-04-02T22:20:36+01:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 - - - - - d3210042 by Rik Steenkamp at 2016-04-04T15:43:32+02:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 (cherry picked from commit 3ddcbd6b8e6884bd95028381176eb33bee6896fb) - - - - - 236eec90 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 692ee7e0 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. - - - - - 79619f57 by Ben Gamari at 2016-04-10T23:46:22+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. (cherry picked from commit c6d6a18d85e5e2d9bb5904e6919e8a8d7e31c4c5) - - - - - 3358ccb4 by Ben Gamari at 2016-04-10T23:47:27+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 264949b1 by Ben Gamari at 2016-04-16T17:50:23+02:00 Merge pull request haskell/haddock#482 from RyanGlScott/ghc-head Collapse type/data family instances by default - - - - - 478c483a by Ben Gamari at 2016-04-16T17:51:09+02:00 Merge pull request haskell/haddock#489 from mpickering/unused-functions Remove some unused functions - - - - - c94e55f0 by Ryan Scott at 2016-04-16T17:57:54+02:00 Collapse type/data family instances by default (cherry picked from commit 2da130a8db8f995c119b544fad807533236cf088) - - - - - 31e633d3 by Ryan Scott at 2016-04-16T17:58:06+02:00 Ensure expanded family instances render correctly (cherry picked from commit 1338b5d7c32939de6bbc31af0049477e4f847103) - - - - - 03e4d197 by Matthew Pickering at 2016-04-16T17:58:21+02:00 Remove unused functions (cherry picked from commit b89d1c2456bdb2d4208d94ded56155f7088a37d0) - - - - - ed4116f6 by Ben Gamari at 2016-04-20T10:46:57+02:00 ghc: Install files for needed --hyperlinked-source - - - - - 0be999c4 by Ben Gamari at 2016-04-20T11:37:54+02:00 ghc: Install files for needed --hyperlinked-source (cherry picked from commit 5c82c9fc2d21ddaae4a2470f1c375426968f19c6) - - - - - 4d17544c by Simon Peyton Jones at 2016-04-20T12:42:28+01:00 Track change to HsGroup This relates to a big GHC patch for Trac haskell/haddock#11348 - - - - - 1700a50d by Ben Gamari at 2016-05-01T13:19:27+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. - - - - - 0b7c8125 by Ben Gamari at 2016-05-01T13:21:43+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. (cherry picked from commit 609018dd09c4ffe27f9248b2d8b50f6196cd42b9) - - - - - af115ce0 by Ryan Scott at 2016-05-04T22:15:50-04:00 Render Haddocks for derived instances Currently, one can document top-level instance declarations, but derived instances (both those in `deriving` clauses and standalone `deriving` instances) do not enjoy the same privilege. This makes the necessary changes to the Haddock API to enable rendering Haddock comments for derived instances. This is part of a fix for Trac haskell/haddock#11768. - - - - - 76fa1edc by Ben Gamari at 2016-05-10T18:13:25+02:00 haddock-test: A bit of refactoring for debuggability - - - - - 7d4c4b20 by Ben Gamari at 2016-05-10T18:13:25+02:00 Create: Mark a comment as TODO - - - - - 2a6d0c90 by Ben Gamari at 2016-05-10T18:13:25+02:00 html-test: Update reference output - - - - - bd60913d by Ben Gamari at 2016-05-10T18:13:25+02:00 hypsrc-test: Fix reference file path in cabal file It appears the haddock insists on prefixing --hyperlinked-sourcer output with directory which the source appeared in. - - - - - c1548057 by Ben Gamari at 2016-05-10T18:22:12+02:00 doc: Update extra-source-files in Cabal file - - - - - 41d5bae3 by Ben Gamari at 2016-05-10T18:29:21+02:00 Bump versions - - - - - ca75b779 by Ben Gamari at 2016-05-11T16:03:44+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 4e3cfd62 by Ben Gamari at 2016-05-11T16:06:45+02:00 Merge remote-tracking branch 'RyanGlScott/ghc-head' into ghc-head - - - - - a2379970 by Ben Gamari at 2016-05-11T23:15:11+02:00 doc: Add clean targets - - - - - f275212e by Ben Gamari at 2016-05-11T23:15:14+02:00 doc: Add html as an all-target for ghc Otherwise the html documentation won't be installed for binary-dist. - - - - - 388fc0af by Ben Gamari at 2016-05-12T09:49:12+02:00 Update CHANGES - - - - - bad81ad5 by Ben Gamari at 2016-05-12T09:49:38+02:00 Version bump - - - - - c01688a7 by Ben Gamari at 2016-05-12T10:04:58+02:00 Revert "Version bump" This bump was a bit premature. This reverts commit 7b238d9c5be9b07aa2d10df323b5c7b8d1634dc8. - - - - - 7ed05724 by Ben Gamari at 2016-05-12T10:05:33+02:00 doc: Fix GHC clean rule Apparently GHC's build system doesn't permit wildcards in clean paths. - - - - - 5d9611f4 by Ben Gamari at 2016-05-12T17:43:50+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 653566b2 by Ben Gamari at 2016-05-14T09:57:31+02:00 Version bump to 2.17.2 - - - - - b355c439 by Ben Gamari at 2016-05-14T09:57:51+02:00 doc: Use `$(MAKE)` instead of `make` This is necessary to ensure we use gmake. - - - - - 8a18537d by Ben Gamari at 2016-05-14T10:15:45+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - b3290ef1 by Sebastian Meric de Bellefon at 2016-05-14T11:29:47-04:00 Fix haskell/haddock#303. Hide footer when printing The "Produced by Haddock" footer was overlapping the page's body when printing. This patch hides the footer with a css media rule. - - - - - b4a76f89 by Sebastian Meric de Bellefon at 2016-05-15T02:12:46-04:00 Fix haskell/haddock#280. Parsing of module header The initial newlines were counted as indentation spaces, thus disturbing the parsing of next lines - - - - - ba797c9e by Ben Gamari at 2016-05-16T14:53:46+02:00 doc: Vendorize alabaster Sphinx theme Alabaster is now the default sphinx theme and is a significant improvement over the previous default that it's worthproviding it when unavailable (e.g. Sphinx <1.3). - - - - - c9283e44 by Ben Gamari at 2016-05-16T14:55:17+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 1c9ea198 by Sebastian Méric de Bellefon at 2016-05-16T12:30:40-04:00 Merge pull request haskell/haddock#502 from Helkafen/master Fix haskell/haddock#303. Hide footer when printing - - - - - 33631016 by Ben Gamari at 2016-05-16T19:56:11+02:00 Revert "doc: Vendorize alabaster Sphinx theme" This ended up causes far too many issues to be worthwhile. We'll just have to live with inconsistent haddock documentation. This reverts commit cec21957001143794e71bcd9420283df18e7de40. - - - - - 93317d26 by Ben Gamari at 2016-05-16T19:56:11+02:00 cabal: Fix README path - - - - - c8695b22 by Ben Gamari at 2016-05-16T19:58:51+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 0b50eaaa by Ben Gamari at 2016-05-16T21:02:08+02:00 doc: Use whichever theme sphinx deems appropriate - - - - - 857c1c9c by Ben Gamari at 2016-05-16T21:07:08+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 15fc5637 by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Remove redundant imports - - - - - 132ddc6a by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Better debug output For tracking down haskell/haddock#505 - - - - - 2252a149 by Ben Gamari at 2016-05-22T12:43:59+02:00 Don't consider default class ops when looking for decls When we are looking for an operation within a class we don't care about `default`-type declarations. This was the cause of haskell/haddock#505. - - - - - 4886b2ec by Oleg Grenrus at 2016-05-24T16:19:48+03:00 UnfelpfulSpan line number omitted Kind of resolves https://github.com/haskell/haddock/issues/508 - - - - - a4befd36 by Oleg Grenrus at 2016-05-24T16:53:35+03:00 Change Hyperlinked lexer to know about DataKinds ticks - - - - - f45cb52e by David Feuer at 2016-05-24T18:48:53-04:00 Make parser state a newtype Previously, it was `data` wrapping a `Maybe`, which seems a bit silly. Obviously, this can be changed back if anyone wants to add more fields some day. - - - - - 05013dd7 by Sebastian Meric de Bellefon at 2016-05-24T22:03:55-04:00 remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) Frames are a bit broken, ignored by Hackage, and considered obsolete in general. This patch disables frames generation. The mini_*.html files are still used in the synopsis. - - - - - b8163a88 by Ben Gamari at 2016-05-25T14:44:15+02:00 Merge pull request haskell/haddock#507 from bgamari/T505 Fix haskell/haddock#505 - - - - - ea1b30c6 by Sebastian Meric de Bellefon at 2016-05-25T14:17:00-04:00 Update CHANGES - - - - - eddfc258 by Sebastian Méric de Bellefon at 2016-05-25T15:17:40-04:00 Merge pull request haskell/haddock#514 from Helkafen/frames remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) - - - - - 0e506818 by Alex Biehl at 2016-05-26T12:43:09+02:00 Remove misplaced haddock comment - - - - - a07d28c0 by Ben Gamari at 2016-05-27T11:34:59+02:00 Merge pull request haskell/haddock#515 from alexbiehl/master Remove misplaced haddock comment - - - - - 9001d267 by Ben Gamari at 2016-05-27T11:35:46+02:00 Merge pull request haskell/haddock#513 from treeowl/newtype-since Make parser state a newtype - - - - - 74e1a018 by Sebastian Méric de Bellefon at 2016-05-28T17:28:15-04:00 Merge pull request haskell/haddock#504 from Helkafen/issue-280 Fix haskell/haddock#280. Parsing of module header - - - - - 37557f4f by Alan Zimmerman at 2016-05-29T23:36:50+02:00 Matching changes for haskell/haddock#12105 - - - - - 7d09e5d6 by Sebastian Meric de Bellefon at 2016-06-03T18:07:48-04:00 Version bumps (2.17.3, 1.4.2) - - - - - 85b4bc15 by Sebastian Méric de Bellefon at 2016-06-06T18:35:13-04:00 Merge pull request haskell/haddock#521 from Helkafen/master Version bumps (2.17.3, 1.4.2) - - - - - e95f0dee by Sebastian Meric de Bellefon at 2016-06-06T19:11:35-04:00 publish haddock-test library - - - - - 4de40586 by Sebastian Méric de Bellefon at 2016-06-06T20:26:30-04:00 Merge pull request haskell/haddock#512 from phadej/oleg-fixes Fixes for haskell/haddock#508 and haskell/haddock#510 - - - - - ddfd0789 by Dominic Steinitz at 2016-06-09T09:27:28+01:00 Documentation for LaTeX markup. - - - - - 697a503a by Dominic Steinitz at 2016-06-09T09:33:59+01:00 Fix spelling mistake. - - - - - 246f6fff by Dominic Steinitz at 2016-06-09T09:37:15+01:00 Camel case MathJax. - - - - - 4684bd23 by Dominic Steinitz at 2016-06-09T09:44:53+01:00 Fix math typo and add link. - - - - - f20c037c by Simon Peyton Jones at 2016-06-13T18:26:03+01:00 Follow changes to LHsSigWcType - - - - - 0c58996d by Simon Peyton Jones at 2016-06-15T12:56:01+01:00 Follow GHC re-adding FunTy - - - - - 401b5ca7 by Sebastian Méric de Bellefon at 2016-06-15T12:16:47-04:00 Merge pull request haskell/haddock#525 from idontgetoutmuch/master Documentation for LaTeX markup. - - - - - 92d263b7 by Sebastian Méric de Bellefon at 2016-06-15T12:17:29-04:00 Merge pull request haskell/haddock#522 from Helkafen/master publish haddock-test library - - - - - 0953a2ca by Sebastian Meric de Bellefon at 2016-06-16T00:46:46-04:00 Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 65453e14 by Ben Gamari at 2016-06-16T11:16:32+02:00 ocean: Ensure that synopsis fully covers other content Previously MathJax content was being rendered on top of the synopsis due to ambiguous z-ordering. Here we explicitly give the synopsis block a higher z-index to ensure it is rendered on top. Fixes haskell/haddock#531. - - - - - 68e411a1 by Sebastian Méric de Bellefon at 2016-06-16T23:34:39-04:00 Merge pull request haskell/haddock#534 from bgamari/T531 ocean: Ensure that synopsis fully covers other content - - - - - fad6491b by Sebastian Méric de Bellefon at 2016-06-18T23:57:20-04:00 Merge pull request haskell/haddock#533 from Helkafen/master Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 6108e21b by Sebastian Meric de Bellefon at 2016-06-22T23:08:28-04:00 do not create empty src directory Fix haskell/haddock#536. - - - - - 1ef23823 by Sebastian Méric de Bellefon at 2016-06-24T00:04:48-04:00 Merge pull request haskell/haddock#537 from Helkafen/master do not create empty src directory - - - - - 966baa96 by Omari Norman at 2016-06-29T21:59:34-04:00 Add $ as a special character If this character is not escaped, documentation built with Haddock 2.17.2 will fail. This was not an issue with 2.16 series, which causes builds to fail and there is nothing in the docs or error message giving a clue about why builds that used to succeed now don't. - - - - - 324adb60 by Ben Gamari at 2016-07-01T12:18:51+02:00 GhcUtils: Changes for multi-pattern signatures - - - - - d7571675 by Ömer Sinan Ağacan at 2016-07-21T13:30:47+02:00 Add support for unboxed sums - - - - - 29d0907b by Simon Marlow at 2016-07-22T13:55:48+01:00 Disable NFData instances for GHC types when GHC >= 8.2 - - - - - 702d95f3 by Simon Marlow at 2016-08-02T15:57:30+02:00 Disable NFData instances for GHC types when GHC >= 8.0.2 (cherry picked from commit a3309e797c42dae9bccdeb17ce52fcababbaff8a) - - - - - f4fa79c3 by Ben Gamari at 2016-08-07T13:51:18+02:00 ghc.mk: Don't attempt to install html/frames.html The frames business has been removed. - - - - - 9cd63daf by Ben Gamari at 2016-08-07T13:51:40+02:00 Haddock.Types: More precise version guard This allows haddock to be built with GHC 8.0.2 pre-releases. - - - - - f3d7e03f by Mateusz Kowalczyk at 2016-08-29T20:47:45+01:00 Merge pull request haskell/haddock#538 from massysett/master Add $ as a special character - - - - - 16dbf7fd by Bartosz Nitka at 2016-09-20T19:44:04+01:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 - - - - - 7c31c1ff by Bartosz Nitka at 2016-09-27T17:32:22-04:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 (cherry picked from commit 073d899a8f94ddec698f617a38d3420160a7fd0b) - - - - - 33a90dce by Ryan Scott at 2016-09-30T20:53:41-04:00 Haddock changes for T10598 See https://ghc.haskell.org/trac/ghc/ticket/10598 - - - - - 1f32f7cb by Ben Gamari at 2016-10-13T20:01:26-04:00 Update for refactoring of NameCache - - - - - 1678ff2e by Ben Gamari at 2016-11-15T17:42:48-05:00 Bump upper bound on base - - - - - 9262a7c5 by Alan Zimmerman at 2016-12-07T21:14:28+02:00 Match changes in GHC wip/T3384 branch - - - - - ac0eaf1a by Ben Gamari at 2016-12-09T09:48:41-05:00 haddock-api: Don't use stdcall calling convention on 64-bit Windows See GHC haskell/haddock#12890. - - - - - 04afe4f7 by Alan Zimmerman at 2016-12-12T20:07:21+02:00 Matching changes for GHC wip/T12942 - - - - - e1d1701d by Ben Gamari at 2016-12-13T16:50:41-05:00 Bump base upper bound - - - - - 3d3eacd1 by Alan Zimmerman at 2017-01-10T16:59:38+02:00 HsIParamTy now has a Located name - - - - - 7dbceefd by Kyrill Briantsev at 2017-01-12T13:23:50+03:00 Prevent GHC API from doing optimization passes. - - - - - d48d1e33 by Richard Eisenberg at 2017-01-19T08:41:41-05:00 Upstream changes re levity polymorphism - - - - - 40c25ed6 by Alan Zimmerman at 2017-01-26T15:16:18+02:00 Changes to match haskell/haddock#13163 in GHC - - - - - 504f586d by Ben Gamari at 2017-02-02T17:19:37-05:00 Kill remaining static flags - - - - - 49147ea0 by Justus Adam at 2017-03-02T15:33:34+01:00 Adding MDoc to exports of Documentation.Haddock - - - - - 1cfba9b4 by Justus Adam at 2017-03-09T11:41:44+01:00 Also exposing toInstalledIface - - - - - 53f0c0dd by Ben Gamari at 2017-03-09T13:10:08-05:00 Bump for GHC 8.3 - - - - - c7902d2e by Ben Gamari at 2017-03-09T23:46:02-05:00 Bump for GHC 8.2 - - - - - 4f3a74f8 by Ben Gamari at 2017-03-10T10:21:55-05:00 Merge branch 'ghc-head' - - - - - e273b72f by Richard Eisenberg at 2017-03-14T13:34:04-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - 6ec3d436 by Richard Eisenberg at 2017-03-14T15:15:52-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - eee3cda1 by Ben Gamari at 2017-03-15T15:19:59-04:00 Adapt to EnumSet - - - - - 017cf58e by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 736d6773 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 475f84a0 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 13240b53 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - cd16d529 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 3bea97ae by Edward Z. Yang at 2017-03-15T22:50:46-07:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b2b051ce by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 0f082795 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 20ef63c9 by Edward Z. Yang at 2017-03-22T13:48:12-07:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 45692dcb by Edward Z. Yang at 2017-03-22T14:11:25-07:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4eae8caf by Ben Gamari at 2017-03-23T09:25:33-04:00 Merge commit '240bc38b94ed2d0af27333b23392d03eeb615e82' into HEAD - - - - - 0bbe03f5 by Ben Gamari at 2017-03-23T09:27:28-04:00 haddock-api: Bump bound on GHC - - - - - 65f3ac9d by Alex Biehl at 2017-03-23T17:36:11+01:00 Merge pull request haskell/haddock#581 from JustusAdam/master Adding more exports to Documentation.Haddock - - - - - 37d49a47 by Alex Biehl at 2017-03-23T17:39:14+01:00 Merge pull request haskell/haddock#568 from awson/ghc-head Prevent GHC API from doing optimization passes. - - - - - 1ed047e4 by Brian Huffman at 2017-03-23T17:45:58+01:00 Print any user-supplied kind signatures on type parameters. This applies to type parameters on data, newtype, type, and class declarations, and also to forall-bound type vars in type signatures. - - - - - 1b78ca5c by Brian Huffman at 2017-03-23T17:45:58+01:00 Update test suite to expect kind annotations on type parameters. - - - - - a856b162 by Alex Biehl at 2017-03-23T17:49:32+01:00 Include travis build indication badge - - - - - 8e2e2c56 by Ben Gamari at 2017-03-23T17:20:08-04:00 haddock-api: Bump bound on GHC - - - - - 4d2d9995 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 26d6c150b31bc4580ab17cfd07b6e7f9afe10737) - - - - - a650e20f by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 930cfbe58e2e87f5a4d431d89a3c204934e6e858) - - - - - caa282c2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 2067a2d0afa9cef381d26fb7140b67c62f433fc0) - - - - - 49684884 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 0671abfe7e8ceae2269467a30b77ed9d9656e2cc) - - - - - 4dcfeb1a by Edward Z. Yang at 2017-03-23T17:20:08-04:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 3d77b373dd5807d5d956719dd7c849a11534fa6a) - - - - - 74dd19d2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 94610e9b446324f4231fa6ad4c6ac51e4eba8c0e) - - - - - a9b19a23 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 6cc832dfb1de6088a4abcaae62b25a7e944d55c3) - - - - - d3631064 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit bf3c4d72a0fda38561376eac7eda216158783267) - - - - - ef2148fc by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 07b88c5d4e79b87a319fbb08f8ea01dbb41063c1) - - - - - 2f29518b by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 4eb765ca4205c79539d60b7afa9b7e261a4a49fe) - - - - - 37de047d by Phil Ruffwind at 2017-04-03T11:57:14+02:00 Update MathJax URL MathJax is shutting down their CDN: https://www.mathjax.org/cdn-shutting-down/ They recommend migrating to cdnjs. - - - - - e9d24ba8 by David C. Turner at 2017-04-03T14:58:01+02:00 Add highlight for :target to ocean.css - - - - - 4819a202 by Alex Biehl at 2017-04-11T19:36:48+02:00 Allow base-4.10 for haddock-test - - - - - 44cec69c by Alex Biehl at 2017-04-11T19:39:22+02:00 cabal.project for haddock-api, haddock-library and haddock-test - - - - - 935d0f6a by Alex Biehl at 2017-04-11T19:46:29+02:00 Move dist scripts to scripts/ - - - - - 128e150c by Alex Biehl at 2017-04-11T20:34:46+02:00 Add haddock to cabal.project - - - - - cc8e08ea by Alex Biehl at 2017-04-11T20:35:08+02:00 Read files for hyperlinker eagerly This also exposes Documentation.Haddock.Utf8 - - - - - 152dda78 by Alex Biehl at 2017-04-11T20:37:06+02:00 Explicit import list ofr Control.DeepSeq in Haddock.Interface.Create - - - - - 501b33c4 by Kyrill Briantsev at 2017-04-11T21:01:42+02:00 Prevent GHC API from doing optimization passes. - - - - - c9f3f5ff by Alexander Biehl at 2017-04-12T16:36:53+02:00 Add @alexbiehl as maintaner - - - - - 76f214cc by Alex Biehl at 2017-04-13T07:27:18+02:00 Disable doctest with ghc-8.3 Currently doctest doesn't support ghc-head - - - - - 46b4f5fc by Edward Z. Yang at 2017-04-22T20:38:26-07:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f0555235 by Alex Biehl at 2017-04-25T10:08:48+02:00 Travis: Use ghc-8.2.1 on master - - - - - 966ea348 by Alex Biehl at 2017-04-25T10:32:01+02:00 Travis: Verbose cabal output cf. https://travis-ci.org/haskell/haddock/jobs/225512194#L377 - - - - - 36972bcd by Alex Biehl at 2017-04-25T10:40:43+02:00 Use travis_retry for cabal invocations - - - - - b3a09d2c by Alex Biehl at 2017-04-25T17:02:20+02:00 Use new MathJax URL in html-test 18ed871afb82560d5433b2f53e31b4db9353a74e switched to a new MathJax URL but didn't update the tests. - - - - - ae331e5f by Alexander Biehl at 2017-04-25T17:02:20+02:00 Expand signatures for class declarations - - - - - e573c65a by Alexander Biehl at 2017-04-25T17:02:20+02:00 Hoogle: Correctly print classes with associated data types - - - - - 3fc6be9b by Edward Z. Yang at 2017-04-25T17:02:20+02:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit a0c4790e15a2d3fab8d830eee8fcd639fe6d39c9) - - - - - 6725c060 by Herbert Valerio Riedel at 2017-04-25T17:02:20+02:00 `html-test --accept` deltas to reference samples - - - - - 7d444d61 by Alex Biehl at 2017-04-26T07:13:50+02:00 Remove anything related to obsolete frames mode - - - - - b888972c by Alex Biehl at 2017-04-26T07:49:10+02:00 Cherry-picked remaining commits from haddock-2.17.4-release (#603) * Release haddock/haddock-api 2.17.4 and haddock-library 1.4.3 * Set version bounds for haddock-library NB: This allows GHC 8.2.1's base * Set version bounds for haddock & haddock-api The version bounds support GHC 8.2 * Merge (temporary) v2.17.3 branch into v2.17 This allows us to delete the v2.17.3 branch * Fixup changelog * Pin down haddock-api to a single version as otherwise `haddock`'s package version has no proper meaning * fix source-repo spec for haddock-api - - - - - 4161099b by Alex Biehl at 2017-04-26T11:11:20+02:00 Update changelog to reflect news in HEAD - - - - - eed72cb8 by Alex Biehl at 2017-04-26T11:11:20+02:00 Markdownify changelog - - - - - 5815cea1 by Alex Biehl at 2017-04-26T11:32:33+02:00 Bump to 2.18.0 (#605) - - - - - a551d558 by Alex Biehl at 2017-04-29T22:00:25+02:00 Update attoparsec-0.12.1.1 to attoparsec-0.13.1.0 - - - - - ea164a8d by Sergey Vinokurov at 2017-04-29T22:42:36+02:00 Improve error message - - - - - 2e10122f by Alex Biehl at 2017-04-30T10:07:46+02:00 Correctly remember collapsed sections (#608) Now the "collapsed" cookie stores which sections have changed state instead of which are collapsed. - - - - - f9b24d99 by Alex Biehl at 2017-05-01T17:40:36+02:00 Lazily decode docMap and argMap (#610) These are only used in case of a doc reexport so most of the time decoding these is wasted work. - - - - - 2372af62 by Alex Biehl at 2017-05-01T21:59:23+02:00 Fix Binary instance for InstalledInterface (#611) (#610) introduced lazy decoding for docs from InstalledInterface but forgot to remove the original calls to get and put_ - - - - - 6c633c13 by Nathan Collins at 2017-05-11T11:47:55+02:00 Improve documenation of Haddock markup (#614) * Improve documentation of Haddock markup. - document that Haddock supports inferring types top-level functions with without type signatures, but also explain why using this feature is discouraged. Looks like this feature has been around since version 2.0.0.0 in 2008! - rework the "Module description" section: - move the general discussion of field formatting to the section intro and add examples illustrating the prose for multiline fields. - mention that newlines are preserved in some multiline fields, but not in others (I also noticed that commas in the `Copyright` field are not preserved; I'll look into this bug later). - add a subsection for the module description fields documentation, and put the field keywords in code formatting (double back ticks) instead of double quotes, to be consistent with the typesetting of keywords in other parts of the documentation. - mention that "Named chunks" are not supported in the long-form "Module description" documentation. - fix formatting of keywords in the "Module attributes" section. Perhaps these errors were left over from an automatic translation to ReST from some other format as part of the transition to using Sphinx for Haddock documentation? Also, add a missing reference here; it just said "See ?"! - update footnote about special treatment for re-exporting partially imported modules not being implemented. In my tests it's not implemented at all -- I tried re-exporting both `import B hiding (f)` and `import B (a, b)` style partial imports, and in both cases got the same result as with full imports `import B`: I only get a module reference. * Rework the `Controlling the documentation structure` section. My main goal was to better explain how to use Haddock without an export list, since that's my most common use case, but I hope I improved the section overall: - remove the incomplete `Omitting the export list` section and fold it into the other sections. In particular, summarize the differences between using and not using an export list -- i.e. control over what and in what order is documented -- in the section lead. - add "realistic" examples that use the structure markup, both with and without an export list. I wanted a realistic example here to capture how it can be useful to explain the relationship between a group of functions in a section, in addition to documenting their individual APIs. - make it clear that you can associate documentation chunks with documentation sections when you aren't using an export list, and that doing it in the most obvious way -- i.e. with `-- |`, as you can in the export list -- doesn't work without an export list. It took me a while to figure this out the first time, since the docs didn't explain it at all before. - add a "no export list" example to the section header section. - add more cross references. * Add examples of gotchas for markup in `@...@`. I'm not sure this will help anyone, since I think most people first learn about `@...@` by reading other people's Haddocks, but I've documented the mistakes which I've made and then gotten confused by. * Use consistent Capitalization of Titles. Some titles were in usual title caps, and others only had the first word capitalized. I chose making them all use title caps because that seems to make the cross references look better. - - - - - d4734f45 by Ben Gamari at 2017-05-12T20:36:08+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 93883f37 by Alex Biehl at 2017-05-12T21:02:33+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 5b8f179c by Alex Biehl at 2017-05-13T12:48:10+02:00 Consequently use inClass and notInClass in haddock-library (#617) These allow attoparsec to do some clever lookup optimization - - - - - 77984b82 by Doug Wilson at 2017-05-27T17:37:38+02:00 Don't enable compilation for template haskell (#624) This is no longer necessary after ghc commit 53c78be0aab76a3107c4dacbb1d177afacdd37fa - - - - - 5a3de2b4 by Doug Wilson at 2017-05-27T19:54:53+02:00 Improve Syb code (#621) Specialize.hs and Ast.hs are modified to have their Syb code not recurse into Name or Id in HsSyn types. Specialize.hs is refactored to have fewer calls to Syb functions. Syb.hs has some foldl calls replaced with foldl' calls. There is still a lot of performance on the floor of Ast.hs. The RenamedSource is traversed many times, and lookupBySpan is very inefficient. everywhereBut and lookupBySpan dominate the runtime whenever --hyperlinked-source is passed. - - - - - 3d35a949 by Alex Biehl at 2017-05-30T19:01:37+02:00 Clear fixme comment (#625) - - - - - 2a44bd0c by Alex Biehl at 2017-05-30T19:02:12+02:00 Make haddock-library and haddock-api warning free (#626) - - - - - bd1a0e42 by Alex Biehl at 2017-06-01T10:40:33+02:00 Include `driver-test/*.hs` sdist (#630) This lead to haskell/haddock#629. - - - - - 184a3ab6 by Doug Wilson at 2017-06-03T12:02:08+02:00 Disable pattern match warnings (#628) This disables the pattern match checker which can be very expensive in some cases. The disabled warnings include: * Opt_WarnIncompletePatterns * Opt_WarnIncompleteUniPatterns * Opt_WarnIncompletePatternsRecUpd * Opt_WarnOverlappingPatterns - - - - - 0cf68004 by Alex Biehl at 2017-06-03T20:37:28+02:00 Allow user defined signatures for pattern synonyms (#631) - - - - - 7f51a58a by Alex Biehl at 2017-06-04T11:56:38+02:00 Use NameSet for isExported check (#632) - - - - - d8f044a9 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Match new AST as per GHC wip/new-tree-one-param See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow - - - - - da1254e3 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Rename extension index tags - - - - - 538c7514 by Christiaan Baaij at 2017-06-09T08:26:43+02:00 Haddock support for bundled pattern synonyms (#627) * Haddock support for bundled pattern synonyms * Add fixities to bundled pattern synonyms * Add bundled pattern synonyms to the synopsis * Store bundled pattern fixities in expItemFixities * Add test for bundled pattern synonyms * Stop threading fixities * Include bundled pattern synonyms for re-exported data types Sadly, fixity information isn't found for re-exported data types * Support for pattern synonyms * Modify tests after haskell/haddock#631 * Test some reexport variations * Also lookup bundled pattern synonyms from `InstalledInterface`s * Check isExported for bundled pattern synonyms * Pattern synonym is exported check * Always look for pattern synonyms in the current module Another overlooked cornercase * Account for types named twice in export lists Also introduce a fast function for nubbing on a `Name` and use it throughout the code base. * correct fixities for reexported pattern synonyms * Fuse concatMap and map * Remove obsolete import * Add pattern synonyms to visible exports * Fix test * Remove corner case - - - - - a050bffd by Doug Wilson at 2017-06-21T09:27:33+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#636) There is some performance improvement. GHC compiler: | version | bytes allocated | cpu_seconds --------------------------------- | before | 56057108648 | 41.0 | after | 51592019560 | 35.1 base: | version | bytes allocated | cpu_seconds --------------------------------- | before | 25174011784 | 14.6 | after | 23712637272 | 13.1 Cabal: | version | bytes allocated | cpu_seconds --------------------------------- | before | 18754966920 | 12.6 | after | 18198208864 | 11.6 - - - - - 5d06b871 by Doug Wilson at 2017-06-22T20:23:29+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#639) * Use new function getNameToInstancesIndex instead of tcRnGetInfo There is some significant performance improvement in the ghc testsuite. haddock.base: -23.3% haddock.Cabal: -16.7% haddock.compiler: -19.8% * Remove unused imports - - - - - b11bb73a by Alex Biehl at 2017-06-23T14:44:41+02:00 Lookup fixities for reexports without subordinates (#642) So we agree that reexported declarations which do not have subordinates (for example top-level functions) shouldn't have gotten fixities reexported according to the current logic. I wondered why for example Prelude.($) which is obviously reexported from GHC.Base has fixities attached (c.f. http://hackage.haskell.org/package/base-4.9.1.0/docs/Prelude.html#v:-36-). The reason is this: In mkMaps we lookup all the subordinates of top-level declarations, of course top-level functions don't have subordinates so for them the resulting list is empty. In haskell/haddock#644 I established the invariant that there won't be any empty lists in the subordinate map. Without the patch from haskell/haddock#642 top-level functions now started to fail reexporting their fixities. - - - - - d2a6dad6 by Alex Biehl at 2017-06-23T18:30:45+02:00 Don't include names with empty subordinates in maps (#644) These are unecessary anyway and just blow up interface size - - - - - 69c2aac4 by Alex Biehl at 2017-06-29T19:54:49+02:00 Make per-argument docs for class methods work again (#648) * Make per-argument docs for class methods work again * Test case - - - - - c9448d54 by Bartosz Nitka at 2017-07-02T12:12:01+02:00 Fix haddock: internal error: links: UnhelpfulSpan (#561) * Fix haddock: internal error: links: UnhelpfulSpan This fixes haskell/haddock#554 for me. I believe this is another fall out of `wildcard-refactor`, like haskell/haddock#549. * Comment to clarify why we take the methods name location - - - - - d4f29eb7 by Alex Biehl at 2017-07-03T19:43:04+02:00 Document record fields when DuplicateRecordFields is enabled (#649) - - - - - 9d6e3423 by Yuji Yamamoto at 2017-07-03T22:37:58+02:00 Fix test failures on Windows (#564) * Ignore .stack-work * Fix for windows: use nul instead of /dev/null * Fix for windows: canonicalize line separator * Also normalize osx line endings - - - - - 7d81e8b3 by Yuji Yamamoto at 2017-07-04T16:13:12+02:00 Avoid errors on non UTF-8 Windows (#566) * Avoid errors on non UTF-8 Windows Problem ==== haddock exits with errors like below: `(1)` ``` haddock: internal error: <stderr>: hPutChar: invalid argument (invalid character) ``` `(2)` ``` haddock: internal error: Language\Haskell\HsColour\Anchors.hs: hGetContents: invalid argument (invalid byte sequence) ``` `(1)` is caused by printing [the "bullet" character](http://www.fileformat.info/info/unicode/char/2022/index.htm) onto stderr. For example, this warning contains it: ``` Language\Haskell\HsColour\ANSI.hs:62:10: warning: [-Wmissing-methods] • No explicit implementation for ‘toEnum’ • In the instance declaration for ‘Enum Highlight’ ``` `(2)` is caused when the input file of `readFile` contains some Unicode characters. In the case above, '⇒' is the cause. Environment ---- OS: Windows 10 haddock: 2.17.3 GHC: 8.0.1 Solution ==== Add `hSetEncoding handle utf8` to avoid the errors. Note ==== - I found the detailed causes by these changes for debugging: - https://github.com/haskell/haddock/commit/8f29edb6b02691c1cf4c479f6c6f3f922b35a55b - https://github.com/haskell/haddock/commit/1dd23bf2065a1e1f2c14d0f4abd847c906b4ecb4 - These errors happen even after executing `chcp 65001` on the console. According to the debug code, `hGetEncoding stderr` returns `CP932` regardless of the console encoding. * Avoid 'internal error: <stderr>: hPutChar: invalid argument (invalid character)' non UTF-8 Windows Better solution for 59411754a6db41d17820733c076e6a72bcdbd82b's (1) - - - - - eded67d2 by Alex Biehl at 2017-07-07T19:17:15+02:00 Remove redudant import warning (#651) - - - - - 05114757 by Alex Biehl at 2017-07-08T00:33:12+02:00 Avoid missing home module warning (#652) * Avoid missing home module warning * Update haddock-library.cabal - - - - - e9cfc902 by Bryn Edwards at 2017-07-17T07:51:20+02:00 Fix haskell/haddock#249 (#655) - - - - - eb02792b by Herbert Valerio Riedel at 2017-07-20T09:09:15+02:00 Fix compilation of lib:haddock-library w/ GHC < 8 - - - - - 9200bfbc by Alex Biehl at 2017-07-20T09:20:38+02:00 Prepare 2.18.1 release (#657) - - - - - 46ddd22c by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Tweak haddock-api.cabal for pending release - - - - - 85e33d29 by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Avoid trivial use of LambdaCase otherwise we can't test w/ e.g. GHC 7.4.2 - - - - - 3afb4bfe by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Refactor .cabal to use sub-lib for vendored lib A practical benefit is that we can control the build-depends and also avoid some recompilation between library and test-suite. - - - - - e56a552e by Herbert Valerio Riedel at 2017-07-20T10:17:48+02:00 haddock-api: add changelog pointing to haddock's changelog This addresses https://github.com/haskell/haddock/issues/638#issuecomment-309283297 - - - - - 2222ff0d by Herbert Valerio Riedel at 2017-07-20T10:19:56+02:00 Drop obsolete/misleading `stability: experimental` This .cabal property has long been considered obsolete - - - - - 9b882905 by Alex Biehl at 2017-07-20T11:25:54+02:00 Beef up haddock description (#658) * Beef up haddock description * Handle empty lines - - - - - bb60e95c by Herbert Valerio Riedel at 2017-07-20T12:08:53+02:00 Import @aisamanra's Haddock cheatsheet from https://github.com/aisamanra/haddock-cheatsheet - - - - - 0761e456 by Herbert Valerio Riedel at 2017-07-20T12:12:55+02:00 Add cheatsheet to haddock.cabal - - - - - 2ece0f0f by Herbert Valerio Riedel at 2017-07-20T12:18:38+02:00 Mention new-build in README - - - - - 947b7865 by Herbert Valerio Riedel at 2017-07-20T12:32:16+02:00 Update README Also improves markup and removes/fixes redundant/obsolete parts [skip ci] - - - - - 785e09ad by Alex Biehl at 2017-07-27T07:28:57+02:00 Bump haddock to 2.18.2, haddock-library to 1.4.5 - - - - - e3ff1ca3 by Alex Biehl at 2017-07-31T20:15:32+02:00 Move `DocMarkup` from haddock-api to haddock-library (#659) * Move `DocMarkup` from haddock-api to haddock-library * Move more markup related functions * Markup module * CHANGELOG - - - - - cda7c20c by Alex Biehl at 2017-07-31T20:35:49+02:00 Fixup haddock - - - - - 583b6812 by Alex Biehl at 2017-07-31T21:20:45+02:00 Changelog for haddock-library - - - - - bac6a0eb by Alex Biehl at 2017-07-31T21:50:24+02:00 Prepare haddock-library-1.4.5 release - - - - - 58ce6877 by Moritz Drexl at 2017-08-05T16:44:40+02:00 Fix renaming after instance signature specializing (#660) * rework rename * Add regression test for Bug 613 * update tests * update changelog - - - - - b8137ec8 by Tim Baumann at 2017-08-06T11:33:38+02:00 Fix: Generate pattern signatures for constructors exported as patterns (#663) * Fix pretty-printing of pattern signatures Pattern synonyms can have up to two contexts, both having a different semantic meaning: The first holds the constraints required to perform the matching, the second contains the constraints provided by a successful pattern match. When the first context is empty but the second is not it is necessary to render the first, empty context. * Generate pattern synonym signatures for ctors exported as patterns This fixes haskell/haddock#653. * Simplify extractPatternSyn It is not necessary to generate the simplest type signature since it will be simplified when pretty-printed. * Add changelog entries for PR haskell/haddock#663 * Fix extractPatternSyn error message - - - - - d037086b by Alex Biehl at 2017-08-06T12:43:25+02:00 Bump haddock-library - - - - - 99d7e792 by Alex Biehl at 2017-08-06T12:44:07+02:00 Bump haddock-library in haddock-api - - - - - 94802a5b by Alex Biehl at 2017-08-06T13:18:02+02:00 Provide --show-interface option to dump interfaces (#645) * WIP: Provide --show-interface option to dump interfaces Like ghcs own --show-iface this flag dumps a binary interface file to stdout in a human (and machine) readable fashion. Currently it uses json as output format. * Fill all the jsonNull stubs * Rework Bifunctor instance of DocH, update changelog and documentation * replace changelog, bring DocMarkupH doc back * Update CHANGES.md * Update CHANGES.md * Move Control.Arrow up It would result in unused import if the Bifunctor instance is not generated. - - - - - c662e476 by Ryan Scott at 2017-08-14T21:00:21-04:00 Adapt to haskell/haddock#14060 - - - - - b891eb73 by Alex Biehl at 2017-08-16T08:24:48+02:00 Bifoldable and Bitraversable for DocH and MetaDoc - - - - - 021bb56c by Alex Biehl at 2017-08-16T09:06:40+02:00 Refactoring: Make doc renaming monadic This allows us to later throw warnings if can't find an identifier - - - - - 39fbf022 by Alex Biehl at 2017-08-19T20:35:27+02:00 Hyperlinker: Avoid linear lookup in enrichToken (#669) * Make Span strict in Position * Hyperlinker: Use a proper map to enrich tokens - - - - - e13baedd by Alex Biehl at 2017-08-21T20:05:42+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 27dd6e87 by Alex Biehl at 2017-08-21T22:06:35+02:00 Drop Avails from export list - - - - - 86b247e2 by Alex Biehl at 2017-08-22T08:44:22+02:00 Bump ghc version for haddock-api tests - - - - - d4607ca0 by Alex Biehl at 2017-08-22T08:45:17+02:00 Revert "Drop Avails from export list" This reverts commit a850ba86d88a4fb9c0bd175453a2580e544e3def. - - - - - c9c54c30 by Alex Biehl at 2017-08-22T09:26:01+02:00 IntefaceFile version - - - - - a85b7c02 by Ben Gamari at 2017-08-22T09:29:52-04:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 34e976f5 by Ben Gamari at 2017-08-22T17:40:06+02:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 577abf06 by Ryan Scott at 2017-08-23T14:47:29-04:00 Update for haskell/haddock#14131 - - - - - da68fc55 by Florian Eggenhofer at 2017-08-27T18:21:56+02:00 Generate an index for package content search (#662) Generate an index for package content search - - - - - 39e62302 by Alex Biehl at 2017-08-27T18:50:16+02:00 Content search for haddock html doc - - - - - 91fd6fb2 by Alex Biehl at 2017-08-28T18:39:58+02:00 Fix tests for content search - - - - - b4a3798a by Alex Biehl at 2017-08-28T18:44:08+02:00 Add search button to #page-menu - - - - - 25a7ca65 by Alex Biehl at 2017-08-28T18:47:43+02:00 Load javascript below the fold - - - - - 8d323c1a by Alex Biehl at 2017-08-28T18:49:22+02:00 Accept tests - - - - - c5dac557 by Alex Biehl at 2017-08-28T19:14:55+02:00 Content search css - - - - - 89a5af57 by Paolo Veronelli at 2017-08-29T07:42:13+02:00 Removed `nowrap` for interface method sigs (#674) with nowrap the interfaces method sigs would expand at libitum - - - - - a505f6f7 by Alex Biehl at 2017-08-29T08:05:33+02:00 Include subordinates in content index - - - - - 4bb698c4 by Alexander Biehl at 2017-08-29T11:40:19+02:00 QuickNav: Make docbase configurable - - - - - c783bf44 by Alexander Biehl at 2017-08-29T11:48:36+02:00 QuickNav: Also use baseUrl for doc-index.json request - - - - - 47017510 by Alex Biehl at 2017-08-29T17:56:47+02:00 Fix test fallout (again) - - - - - 924fc318 by Alex Biehl at 2017-08-30T09:24:56+02:00 Write meta.json when generating html output (#676) - - - - - 717dea52 by Alex Biehl at 2017-09-01T09:20:34+02:00 Use relative URL when no docBaseUrl given - - - - - e5d85f3b by Alex Biehl at 2017-09-01T09:35:19+02:00 Add missing js files to data-files (#677) - - - - - 95b9231a by Alex Biehl at 2017-09-01T11:01:36+02:00 Rename "Search" tab to "Quick Jump" - - - - - da0ead0b by Alex Biehl at 2017-09-01T13:03:49+02:00 Make trigger link configurable (#678) QuickNav: Configurable show/hide trigger - - - - - de7da594 by Ben Gamari at 2017-09-05T06:49:55-04:00 Account for "Remember the AvailInfo for each IE" As of GHC commit f609374a55bdcf3b79f3a299104767aae2ffbf21 GHC retains the AvailInfo associated with each IE. @alexbiehl has a patch making proper use of this change, but this is just to keep things building. - - - - - b05cd3b3 by Ben Gamari at 2017-09-14T07:55:07-04:00 Bump upper bound on base - - - - - 79db899e by Herbert Valerio Riedel at 2017-09-21T23:27:52+02:00 Make compatible with Prelude.<> export in GHC 8.4/base-4.11 - - - - - 3405dd52 by Tim Baumann at 2017-09-23T22:02:01+02:00 Add compile step that bundles and compresses JS files (#684) * Add compile step that bundles and compresses JS files Also, manage dependencies on third-party JS libraries using NPM. * Compile JS from TypeScript * Enable 'noImplicitAny' in TypeScript * QuickJump: use JSX syntax * Generate source maps from TypeScript for easier debugging * TypeScript: more accurate type * Separate quick jump css file from ocean theme - - - - - df0b5742 by Alex Biehl at 2017-09-29T21:15:40+02:00 Bump base for haddock-library and haddock-test - - - - - 62b12ea0 by Merijn Verstraaten at 2017-10-04T16:03:13+02:00 Inhibit output of coverage information for hidden modules. (#687) * Inhibit output of coverage information for hidden modules. * Add changelog entry. - - - - - 8daf8bc1 by Alexander Biehl at 2017-10-05T11:27:05+02:00 Don't use subMap in attachInstances - - - - - ad75114e by Alexander Biehl at 2017-10-05T11:27:58+02:00 Revert "Don't use subMap in attachInstances" This reverts commit 3adf5bcb1a6c5326ab33dc77b4aa229a91d91ce9. - - - - - 7d4aa02f by Alex Biehl at 2017-10-08T15:32:28+02:00 Precise Haddock: Use Avails for export resolution (#688) * Use Avails for export resolution * Support reexported modules * Factor out availExportItem * Use avails for fullModuleExports * Don't use subMap in attachInstances * lookupDocs without subMap * Completely remove subMap * Only calculate unqualified modules when explicit export list is given * Refactor * Refine comment * return * Fix * Refactoring * Split avail if declaration is not exported itself * Move avail splitting - - - - - b9b4faa8 by Alex Biehl at 2017-10-08T19:38:21+02:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 43325295 by Alex Biehl at 2017-10-08T20:18:46+02:00 Fix merge fallout - - - - - c6423cc0 by Alex Biehl at 2017-10-08T20:36:12+02:00 Copy QuickJump files over - - - - - 1db587c3 by Tim Baumann at 2017-10-09T18:33:09+02:00 Use <details> element for collapsibles (#690) * Remove unnecessary call to 'collapseSection' The call is unnecessary since there is no corresponding toggle for hiding the section of orphan instances. * Use <details> for collapsibles This makes them work even when JS is disabled. Closes haskell/haddock#560. - - - - - 1b54c64b by Tim Baumann at 2017-10-10T09:50:59+02:00 Quick Jump: Show error when loading 'doc-index.json' failed (#691) - - - - - 910f716d by Veronika Romashkina at 2017-10-24T07:36:20+02:00 Fix tiny typo in docs (#693) - - - - - b21de7e5 by Ryan Scott at 2017-10-24T13:07:15+02:00 Overhaul Haddock's rendering of kind signatures (#681) * Overhaul Haddock's rendering of kind signatures * Strip off kind signatures when specializing As an added bonus, this lets us remove an ugly hack specifically for `(->)`. Yay! * Update due to 0390e4a0f61e37bd1dcc24a36d499e92f2561b67 * @alexbiehl's suggestions * Import injectiveVarsOfBinder from GHC - - - - - 6704405c by Ryan Scott at 2017-10-28T07:10:27+02:00 Fix Haddock rendering of kind-indexed data family instances (#694) - - - - - 470f6b9c by Alex Biehl at 2017-10-30T08:45:51+01:00 Add QuickJump version to meta.json (#696) - - - - - b89eccdf by Alex Biehl at 2017-10-30T10:15:49+01:00 Put Quickjump behind --quickjump flag (#697) - - - - - 3095fb58 by Alex Biehl at 2017-10-30T19:09:06+01:00 Add build command to package.json - - - - - f223fda9 by Alex Biehl at 2017-10-30T19:10:39+01:00 Decrease threshold for fuzzy matching - - - - - 80245dda by Edward Z. Yang at 2017-10-31T20:35:05+01:00 Supported reexported-modules via --reexport flag. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 7e389742 by Alex Biehl at 2017-10-31T20:37:56+01:00 Correct missing title in changelog - - - - - 1a2a1c03 by Alex Biehl at 2017-10-31T20:59:07+01:00 Copy quickjump.css for nicer error messages - - - - - db234bb9 by Alex Biehl at 2017-10-31T21:31:18+01:00 Reexported modules: Report warnings if argument cannot be parsed or ... module cannot be found - - - - - eea8a205 by Carlo Hamalainen at 2017-10-31T21:43:14+01:00 More general type for nameCacheFromGhc. (#539) - - - - - 580eb42a by Alex Biehl at 2017-10-31T21:46:52+01:00 Remote tab - - - - - 0e599498 by Alex Biehl at 2017-10-31T21:48:55+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 7b8539bb by Alex Biehl at 2017-10-31T22:28:34+01:00 fullModuleContents traverses exports in declaration order - - - - - 0c91fbf2 by Alex Biehl at 2017-10-31T22:32:31+01:00 Remove excessive use of list comprehensions - - - - - f7356e02 by Alex Biehl at 2017-11-01T19:11:03+01:00 Make better use of AvailInfo - - - - - f3e512d5 by Alex Biehl at 2017-11-02T12:16:22+01:00 Always return documentation for exported subordinates ... event if they have no documentation (e.g. noDocForDecl) By using the information in the AvailInfo we don't need additional export checks. - - - - - 7cf58898 by Alan Zimmerman at 2017-11-07T08:28:03+02:00 Match changes for Trees that Grow in GHC - - - - - e5105a41 by Alan Zimmerman at 2017-11-08T17:21:58+02:00 Match Trees That Grow - - - - - 55178266 by Alan Zimmerman at 2017-11-11T22:20:31+02:00 Match Trees that Grow in GHC for HsExpr - - - - - 2082ab02 by Ryan Scott at 2017-11-14T15:27:03+01:00 Actually render infix type operators as infix (#703) * Actually render infix type operators as infix * Account for things like `(f :*: g) p`, too - - - - - c52ab7d0 by Alan Zimmerman at 2017-11-14T23:14:26+02:00 Clean up use of PlaceHolder, to match TTG - - - - - 81cc9851 by Moritz Angermann at 2017-11-20T07:52:49+01:00 Declare use of `Paths_haddock` module in other-modules (#705) This was detected by `-Wmissing-home-modules` - - - - - f9d27598 by Moritz Angermann at 2017-11-20T12:47:34+01:00 Drop Paths_haddock from ghc.mk (#707) With haskell/haddock#705 and haskell/haddock#706, the custom addition should not be necessary any more. # Conflicts: # ghc.mk - - - - - f34818dc by Moritz Angermann at 2017-11-20T12:47:59+01:00 Add autogen-modules (#706) > Packages using 'cabal-version: >= 1.25' and the autogenerated module Paths_* must include it also on the 'autogen-modules' field besides 'exposed-modules' and 'other-modules'. This specifies that the module does not come with the package and is generated on setup. Modules built with a custom Setup.hs script also go here to ensure that commands like sdist don't fail. # Conflicts: # haddock.cabal - - - - - bb43a0aa by Ben Gamari at 2017-11-21T15:50:12-05:00 Revert "Clean up use of PlaceHolder, to match TTG" This reverts commit 134a7bb054ea730b13c8629a76232d73e3ace049. - - - - - af9ebb2b by Ben Gamari at 2017-11-21T15:50:14-05:00 Revert "Match Trees that Grow in GHC for HsExpr" This reverts commit 9f054dc365379c66668de6719840918190ae6e44. - - - - - 5d35c3af by Ben Gamari at 2017-11-21T15:50:15-05:00 Revert "Match Trees That Grow" This reverts commit 73a26af844ac50b8bec39de11d64452a6286b00c. - - - - - 99a8e43b by Ben Gamari at 2017-11-21T16:36:06-05:00 Revert "Match changes for Trees that Grow in GHC" This reverts commit 01eeeb048acd2dd05ff6471ae148a97cf0720547. - - - - - c4d650c2 by Ben Gamari at 2017-12-04T15:06:07-05:00 Bump GHC version - - - - - 027b2274 by Ben Gamari at 2017-12-04T17:06:31-05:00 Bump GHC bound to 8.4.* - - - - - 58eaf755 by Alex Biehl at 2017-12-06T15:44:24+01:00 Update changelog - - - - - d68f5584 by Simon Peyton Jones at 2017-12-07T14:39:56+00:00 Track changes to follow Trac haskell/haddock#14529 This tracks the refactoring of HsDecl.ConDecl. - - - - - dc519d6b by Alec Theriault at 2018-01-06T08:20:43-08:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - 8285118c by Alec Theriault at 2018-01-13T12:12:37+01:00 Constructor and pattern synonym argument docs (#709) * Support Haddocks on constructor arguments This is in conjunction with https://phabricator.haskell.org/D4094. Adds support for rendering Haddock's on (non-record) constructor arguments, both for regular and GADT constructors. * Support haddocks on pattern synonym arguments It appears that GHC already parsed these - we just weren't using them. In the process of doing this, I tried to deduplicate some code around handling patterns. * Update the markup guide Add some information about the new support for commenting constructor arguments, and mention pattern synonyms and GADT-style constructors. * Overhaul LaTeX support for data/pattern decls This includes at least * fixing several bugs that resulted in invalid LaTeX * fixing GADT data declaration headers * overhaul handling of record fields * overhaul handling of GADT constructors * overhaul handling of bundled patterns * add support for constructor argument docs * Support GADT record constructors This means changes what existing HTML docs look like. As for LaTeX, looks like GADT records were never even supported. Now they are. * Clean up code/comments Made code/comments consistent between the LaTeX and XHTML backend when possible. * Update changelog * Patch post-rebase regressions * Another post-rebase change We want return values to be documentable on record GADT constructors. - - - - - ca4fabb4 by Alec Theriault at 2018-01-15T17:12:18-08:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 4c472fea by Ryan Scott at 2018-01-19T10:44:02+01:00 Fix haskell/haddock#732 (#733) - - - - - bff14dbd by Alex Biehl at 2018-01-19T15:33:30+01:00 extractDecl: Extract associated types correctly (#736) - - - - - a2a94a73 by Alex Biehl at 2018-01-19T15:34:40+01:00 extractDecl: Extract associated types correctly (#736) - - - - - 26df93dc by Alex Biehl at 2018-01-20T10:18:22+01:00 haddock-api: bump ghc to ^>= 8.4 - - - - - f65aeb1d by Alex Biehl at 2018-01-20T19:18:20+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - 0e721b97 by Alex Biehl at 2018-01-20T19:20:19+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - cb6234f6 by Ben Gamari at 2018-01-26T13:40:55-05:00 Merge remote-tracking branch 'harpocrates/fix/missing-orphan-instances' into ghc-head - - - - - 0fc28554 by Alec Theriault at 2018-02-01T14:58:18+01:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - b9123772 by Alec Theriault at 2018-02-01T14:58:18+01:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 0c12e274 by Ryan Scott at 2018-02-01T14:58:18+01:00 Fix haskell/haddock#548 by rendering datatype kinds more carefully (#702) - - - - - 8876d20b by Alec Theriault at 2018-02-01T14:58:18+01:00 Use the GHC lexer for the Hyperlinker backend (#714) * Start changing to use GHC lexer * better cpp * Change SrcSpan to RealSrcSpan * Remove error * Try to stop too many open files * wip * wip * Revert "wip" This reverts commit b605510a195f26315e3d8ca90e6d95a6737553e1. Conflicts: haddock-api/haddock-api.cabal haddock-api/src/Haddock/Interface.hs * Remove pointless 'caching' * Use dlist rather than lists when finding vars * Use a map rather than list * Delete bogus comment * Rebase followup Things now run using the GHC lexer. There are still - stray debug statements - unnecessary changes w.r.t. master * Cleaned up differences w.r.t. current Haddock HEAD Things are looking good. quasiquotes in particular look beautiful: the TH ones (with Haskell source inside) colour/link their contents too! Haven't yet begun to check for possible performance problems. * Support CPP and top-level pragmas The support for these is hackier - but no more hacky than the existing support. * Tests pass, CPP is better recognized The tests were in some cases altered: I consider the new output to be more correct than the old one.... * Fix shrinking of source without tabs in test * Replace 'Position'/'Span' with GHC counterparts Replaces 'Position' -> 'GHC.RealSrcLoc' and 'Span' -> 'GHC.RealSrcSpan'. * Nits * Forgot entry in .cabal * Update changelog - - - - - 95c6a771 by Alec Theriault at 2018-02-01T14:58:18+01:00 Clickable anchors for headings (#716) See haskell/haddock#579. This just adds an <a> tag around the heading, pointing to the heading itself. - - - - - 21463d28 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump: Matches on function names weight more than matches in ... module names. - - - - - 8023af39 by Alex Biehl at 2018-02-01T14:58:18+01:00 Treat escaped \] better in definition lists (#717) This fixes haskell/haddock#546. - - - - - e4866dc1 by Alex Biehl at 2018-02-01T14:58:18+01:00 Remove scanner, takeWhile1_ already takes care of escaping - - - - - 9bcaa49d by Alex Biehl at 2018-02-01T14:58:18+01:00 Take until line feed - - - - - 01d2af93 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Add simple framework for running parser fixtures (#668) * Add simple framework for running parser fixtures * Compatible with tree-diff-0.0.0.1 * Use parseParas to parse fixtures This allows to test all syntactic constructs available in haddock markup. - - - - - 31128417 by Alec Theriault at 2018-02-01T14:58:18+01:00 Patch flaky parser test (#720) * Patch flaky parser test This test was a great idea, but it doesn't port over too well to using the GHC lexer. GHC rewrites its input a bit - nothing surprising, but we need to guard against those cases for the test. * Change instance head * Change use site - - - - - 9704f214 by Herbert Valerio Riedel at 2018-02-01T14:58:18+01:00 Include secondary LICENSE file in source dist - - - - - 51f25074 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Grid Tables (#718) * Add table examples * Add table types and adopt simple parser Simple parser is done by Giovanni Cappellotto (@potomak) in https://github.com/haskell/haddock/pull/577 It seems to support single fine full tables, so far from full RST-grid tables, but it's good start. Table type support row- and colspans, but obviously parser is lacking. Still TODO: - Latex backend. Should we use multirow package https://ctan.org/pkg/multirow?lang=en? - Hoogle backend: ? * Implement grid-tables * Refactor table parser * Add two ill-examples * Update CHANGES.md * Basic documentation for tables * Fix documentation example - - - - - 670d6200 by Alex Biehl at 2018-02-01T14:58:18+01:00 Add grid table example to cheatsheet (pdf and svg need to be regenerated thought) - - - - - 4262dec9 by Alec Theriault at 2018-02-01T14:58:18+01:00 Fix infinite loop when specializing instance heads (#723) * Fix infinite loop when specializing instance heads The bug can only be triggered from TH, hence why it went un-noticed for so long. * Add test for haskell/haddock#679 and haskell/haddock#710 - - - - - 67ecd803 by Alec Theriault at 2018-02-01T14:58:18+01:00 Filter RTS arguments from 'ghc-options' arguments (#725) This fixes haskell/haddock#666. - - - - - 7db26992 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump Scrollable overlay - - - - - da9ff634 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Hyperlinker: Adjust parser to new PFailed constructor - - - - - 7b7cf8cb by Alexander Biehl at 2018-02-01T14:58:18+01:00 Specialize: Add missing IdP annotations - - - - - 78cd7231 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Convert: Correct pass type - - - - - a2d0f590 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Warning free compilation - - - - - cd861cf3 by Alexander Biehl at 2018-02-01T14:58:18+01:00 hadock-2.19.0 / haddock-api-2.19.0 / haddock-library-1.5.0 - - - - - c6651b72 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Adjust changelogs - - - - - 1e93da0b by Alexander Biehl at 2018-02-01T14:58:18+01:00 haddock-library: Info about breaking changes - - - - - f9b11db8 by Alec Theriault at 2018-02-02T12:36:02+01:00 Properly color pragma contents in hyperlinker The hyperlinker backend now classifies the content of pragmas as 'TkPragma'. That means that in something like '{-# INLINE foo #-}', 'foo' still gets classified as a pragma token. - - - - - c40b0043 by Alec Theriault at 2018-02-02T12:36:02+01:00 Support the new 'ITcolumn_prag' token - - - - - 4a2a4d39 by Alex Biehl at 2018-02-03T12:11:55+01:00 QuickJump: Mitigate encoding problems on Windows - - - - - bb34503a by Alex Biehl at 2018-02-04T18:39:31+01:00 Use withBinaryFile - - - - - 637605bf by Herbert Valerio Riedel at 2018-02-05T09:48:32+01:00 Try GHC 8.4.1 for Travis CI job - - - - - 7abb67e4 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 try harder to build w/ GHC 8.4.1 - - - - - 8255cc98 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 Add `SPDX-License-Identifier` as alised for "license" module header tokens C.f. SPDX 2.1 - Appendix V https://spdx.org/spdx-specification-21-web-version#h.twlc0ztnng3b The tag should appear on its own line in the source file, generally as part of a comment. SPDX-License-Identifier: <SPDX License Expression> Cherry-picked from haskell/haddock#743 - - - - - 267cd23d by Herbert Valerio Riedel at 2018-02-05T10:24:34+01:00 Make test-suite SMP compatible - - - - - 95d4bf40 by Alec Theriault at 2018-02-05T22:01:04+01:00 Hyperlink pattern synonyms and 'module' imports (#744) Links to pattern synonyms are now generated, as well as links from modules in import lists. Fixes haskell/haddock#731. - - - - - 67838dcd by Alec Theriault at 2018-02-06T08:23:36+01:00 Don't warn about missing '~' (#746) This manually filters out '~' from the list of things to warn about. It truly makes no sense to warn on this since '~' has nothing it could link to - it is magical. This fixes haskell/haddock#532. - - - - - ab6c3f9f by Alec Theriault at 2018-02-06T08:24:47+01:00 Don't barf on 'HsSpliceTy' (#745) This handles 'HsSpliceTy's by replacing them with what they expand to. IIUC everything that is happening, 'renameHsSpliceTy' should not be able to fail for the inputs we feed it from GHC. This fixes haskell/haddock#574. - - - - - 92bf95ad by Alex Biehl at 2018-02-06T08:28:23+01:00 Rename: renameHsSpliceTy ttg - - - - - 3130b1e1 by Alex Biehl at 2018-02-06T09:02:14+01:00 Expand SigDs - - - - - c72adae5 by Alex Biehl at 2018-02-06T09:20:51+01:00 fullModuleContents: support named docs - - - - - de2e4dbf by Alex Biehl at 2018-02-06T13:56:17+01:00 Hyperlinker: Also link pattern synonym arguments - - - - - b7c98237 by Alex Biehl at 2018-02-09T18:44:23+01:00 Expand SigD in a better place In https://github.com/haskell/haddock/issues/287 we found that haddock-2.19.0 would miss documentation on class methods with multiples names. This patch uses expandSigDecls in a more sensible place. - - - - - 8f598b27 by Alec Theriault at 2018-02-11T12:29:56+01:00 Add module tooltips to linked identifiers (#753) No more clicking to figure out whether your bytestring is strict or lazy! - - - - - d812e65d by Alec Theriault at 2018-02-11T12:31:44+01:00 Add 'show' option to complement 'hide' (#752) * Add 'show' option to complement 'hide' The behaviour is for flags passed in the command line to override flags in file headers. In the command line, later flags override earlier ones. Fixes haskell/haddock#751 and haskell/haddock#266. * Add a '--show-all' option - - - - - 6676cecb by Alex Biehl at 2018-02-18T11:07:15-05:00 QuickJump: Mitigate encoding problems on Windows (cherry picked from commit 86292c54bfee2343aee84559ec01f1fc68f52231) - - - - - e753dd88 by Alex Biehl at 2018-02-18T17:59:54+01:00 Use withBinaryFile - - - - - 724dc881 by Tamar Christina at 2018-02-19T05:34:49+01:00 Haddock: support splitted include paths. (#689) - - - - - 9b6d6f50 by Alex Biehl at 2018-02-19T05:57:02+01:00 Teach the HTML backend how to render methods with multiple names - - - - - a74aa754 by Alexander Biehl at 2018-02-19T10:04:34+01:00 Hoogle/Latex: Remove use of partial function - - - - - 66d8bb0e by Alec Theriault at 2018-02-25T16:04:01+01:00 Fix file handle leak (#763) (#764) Brought back some mistakenly deleted code for handling encoding and eager reading of files from e0ada1743cb722d2f82498a95b201f3ffb303137. - - - - - bb92d03d by Alex Biehl at 2018-03-02T14:21:23+01:00 Enable running test suite with stock haddock and ghc using ``` $ cabal new-run -- html-test --haddock-path=$(which haddock) --ghc-path=$(which ghc) ``` - - - - - dddb3cb2 by Alex Biehl at 2018-03-02T15:43:21+01:00 Make testsuite work with haddock-1.19.0 release (#766) - - - - - f38636ed by Alec Theriault at 2018-03-02T15:48:36+01:00 Support unicode operators, proper modules Unicode operators are a pretty big thing in Haskell, so supporting linking them seems like it outweighs the cost of the extra machinery to force Attoparsec to look for unicode. Fixes haskell/haddock#458. - - - - - 09d89f7c by Alec Theriault at 2018-03-02T15:48:43+01:00 Remove bang pattern - - - - - d150a687 by Alex Biehl at 2018-03-02T15:48:48+01:00 fix test - - - - - d6fd71a5 by Alex Biehl at 2018-03-02T16:22:38+01:00 haddock-test: Be more explicit which packages to pass We now pass `-hide-all-packages` to haddock when invoking the testsuite. This ensures we don't accidentally pick up any dependencies up through ghc.env files. - - - - - 0932c78c by Alex Biehl at 2018-03-02T17:50:38+01:00 Revert "fix test" This reverts commit 1ac2f9569242f6cb074ba6e577285a4c33ae1197. - - - - - 52516029 by Alex Biehl at 2018-03-02T18:16:50+01:00 Fix Bug548 for real - - - - - 89df9eb5 by Alex Biehl at 2018-03-05T18:28:19+01:00 Hyperlinker: Links for TyOps, class methods and associated types - - - - - d019a4cb by Ryan Scott at 2018-03-06T13:43:56-05:00 Updates for haskell/haddock#13324 - - - - - 6d5a42ce by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump haddock-2.19.0.1, haddock-api-2.19.0.1, haddock-library-1.5.0.1 - - - - - c0e6f380 by Alex Biehl at 2018-03-10T18:25:57+01:00 Update changelogs for haddock-2.19.0.1 and haddock-library-1.5.0.1 - - - - - 500da489 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Update to QC 2.11 - - - - - ce8362e9 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Restore backward-compat with base-4.5 through base-4.8 - - - - - baae4435 by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump lower bound for haddock-library - - - - - 10b7a73e by Alex Biehl at 2018-03-10T18:25:57+01:00 Haddock: Straighten out base bound - - - - - a6096f7b by Alex Biehl at 2018-03-13T08:45:06+01:00 extractDecl: Extract constructor patterns from data family instances (#776) * extractDecl: Allow extraction of data family instance constructors * extractDecl: extract data family instance constructors - - - - - ba4a0744 by Simon Jakobi at 2018-03-14T08:26:42+01:00 Readme: Update GHC version (#778) - - - - - 8de157d4 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for definition lists - - - - - 425b46f9 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for links - - - - - d53945d8 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for inline links - - - - - f1dc7c99 by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Slightly unmangle output - - - - - 0879d31c by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Prevent stdout buffering - - - - - 1f9e5f1b by Simon Jakobi at 2018-03-14T20:39:29+01:00 haddock-library.cabal: Clean up GHC options - - - - - 066b891a by Simon Jakobi at 2018-03-14T20:39:29+01:00 Make a proper definition for the <link> parser - - - - - 573d6ba7 by Alec Theriault at 2018-03-21T09:16:57+01:00 Show where instances are defined (#748) * Indicate source module of instances Above instance, we now also display a link to the module where the instance was defined. This is sometimes helpful in figuring out what to import. * Source module for type/data families too * Remove parens * Accept tests - - - - - 99b5d28b by Alex Biehl at 2018-03-21T09:20:36+01:00 Prepare changelog for next release - - - - - 482d3a93 by Alex Biehl at 2018-03-23T15:57:36+01:00 Useful cost centres, timers and allocation counters (#785) * Add some useful cost-centres for profiling * Add withTiming for each haddock phase Invoking haddock with `--optghc=-ddump-timings` now shows the amount of time spent and the number of allocated bytes for each phase. - - - - - 773b41bb by Alec Theriault at 2018-03-27T08:35:59+02:00 @since includes package name (#749) * Metadoc stores a package name This means that '@since' annotations can be package aware. * Get the package name the right way This should extract the package name for `@since` annotations the right way. I had to move `modulePackageInfo` around to do this and, in the process, I took the liberty to update it. Since it appears that finding the package name is something that can fail, I added a warning for this case. * Silence warnings * Hide package for local 'since' annotations As discussed, this is still the usual case (and we should avoid being noisy for it). Although this commit is large, it is basically only about threading a 'Maybe Package' from 'Haddock.render' all the way to 'Haddock.Backends.Xhtml.DocMarkup.renderMeta'. * Bump binary interface version * Add a '--since-qual' option This controls when to qualify since annotations with the package they come from. The default is always, but I've left an 'external' variant where only those annotations coming from outside of the current package are qualified. * Make ParserSpec work * Make Fixtures work * Use package name even if package version is not available The @since stuff needs only the package name passed in, so it makes sense to not be forced to pass in a version too. - - - - - e42c57bc by Alex Biehl at 2018-03-27T08:42:50+02:00 haddock-2.19.1, haddock-api-2.19.1, haddock-library-1.6.0 - - - - - 8373a529 by Alex Biehl at 2018-03-28T10:17:11+02:00 Bump haddock and haddock-api to 2.20.0 - - - - - 5038eddd by Jack Henahan at 2018-04-03T13:28:12+02:00 Clear search string on hide for haskell/haddock#781 (#789) - - - - - 920ca1eb by Alex Biehl at 2018-04-03T16:35:50+02:00 Travis: Build with ghc-8.4.2 (#793) - - - - - a232f0eb by Alan Zimmerman at 2018-04-07T14:14:32+02:00 Match changes in GHC for D4199 Removing HasSourceText and SourceTextX classes. - - - - - ab85060b by Alan Zimmerman at 2018-04-09T21:20:24+02:00 Match GHC changes for TTG - - - - - 739302b6 by Alan Zimmerman at 2018-04-13T13:31:44+02:00 Match GHC for TTG implemented on HsBinds, D4581 - - - - - 2f56d3cb by Ryan Scott at 2018-04-19T11:42:58-04:00 Bump upper bound on base to < 4.13 See https://ghc.haskell.org/trac/ghc/ticket/15018. - - - - - a49df92a by Alex Biehl at 2018-04-20T07:31:44+02:00 Don't treat fixity signatures like declarations - - - - - d02c103b by Ryan Scott at 2018-04-24T11:20:11-04:00 Add regression test for haskell/haddock#413 Fixes haskell/haddock#413. - - - - - c7577f52 by Ryan Scott at 2018-04-24T13:51:06-07:00 Improve the Hoogle backend's treatment of type families (#808) Fixes parts 1 and 2 of haskell/haddock#806. - - - - - d88f85b1 by Alec Theriault at 2018-04-25T11:24:07-07:00 Replace 'attoparsec' with 'parsec' (#799) * Remove attoparsec with parsec and start fixing failed parses * Make tests pass * Fix encoding issues The Haddock parser no longer needs to worry about bytestrings. All the internal parsing work in haddock-library happens over 'Text'. * Remove attoparsec vendor * Fix stuff broken in 'attoparsec' -> 'parsec' * hyperlinks * codeblocks * examples Pretty much all issues are due to attoparsec's backtracking failure behaviour vs. parsec's non-backtracking failure behaviour. * Fix small TODOs * Missing quote + Haddocks * Better handle spaces before/after paragraphs * Address review comments - - - - - fc25e2fe by Alan Zimmerman at 2018-04-27T15:36:53+02:00 Match changes in GHC for TTG - - - - - 06175f91 by Herbert Valerio Riedel at 2018-05-01T18:11:09+02:00 Merge branch 'ghc-head' with 'ghc-8.4' - - - - - 879caaa8 by Alec Theriault at 2018-05-07T18:53:15-07:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 3e0120cb by Simon Jakobi at 2018-05-07T19:00:18-07:00 Add docs for some DocH constructors (#814) - - - - - 0a32c6db by Alec Theriault at 2018-05-08T02:15:45-07:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 8816e783 by Simon Jakobi at 2018-05-08T10:48:11-07:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - ad60366f by Ryan Scott at 2018-05-10T11:19:47-04:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - 03b7cc3b by Ryan Scott at 2018-05-10T11:24:38-04:00 Wibbles - - - - - b03dd563 by Chaitanya Koparkar at 2018-05-10T11:44:58-04:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 9f298a40 by Ben Gamari at 2018-05-13T17:36:04-04:00 Account for refactoring of LitString - - - - - ea3dabe7 by Ryan Scott at 2018-05-16T09:21:43-04:00 Merge pull request haskell/haddock#826 from haskell/T825 Remove Hoogle backend hack that butchers infix datatype names - - - - - 0d234f7c by Alec Theriault at 2018-05-23T11:29:05+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 15fc9712 by Simon Jakobi at 2018-05-31T04:17:47+02:00 Adjust to new HsDocString internals - - - - - 6f1e19a8 by Ben Gamari at 2018-06-02T16:18:58-04:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 0d0355d9 by Ryan Scott at 2018-06-04T21:26:59-04:00 DerivingVia changes - - - - - 0d93475a by Simon Jakobi at 2018-06-05T19:47:05+02:00 Bump a few dependency bounds (#845) - - - - - 5cbef804 by Alec Theriault at 2018-06-05T19:47:16+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 9094c56f by Alec Theriault at 2018-06-05T22:53:25+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 70188719 by Simon Jakobi at 2018-06-08T22:20:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - 495cd1fc by Chaitanya Koparkar at 2018-06-13T23:01:34+02:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 81088732 by Ben Gamari at 2018-06-13T23:01:34+02:00 Account for refactoring of LitString - - - - - 7baf6587 by Simon Jakobi at 2018-06-13T23:05:08+02:00 Adjust to new HsDocString internals - - - - - bb61464d by Ben Gamari at 2018-06-13T23:05:22+02:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 5d8cb87f by Ryan Scott at 2018-06-13T23:39:30+02:00 DerivingVia changes - - - - - 73d373a3 by Alec Theriault at 2018-06-13T23:39:30+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 4865e254 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Remove `ITtildehsh` token - - - - - b867db54 by Alec Theriault at 2018-06-13T23:39:30+02:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 9598e392 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Add docs for some DocH constructors (#814) - - - - - 8a59035b by Alec Theriault at 2018-06-13T23:39:30+02:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 29350fc8 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - 2590bbd9 by Ryan Scott at 2018-06-13T23:39:30+02:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - a9939fdc by Ryan Scott at 2018-06-13T23:39:30+02:00 Wibbles - - - - - a22f7df4 by Alec Theriault at 2018-06-13T23:39:30+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 8741015d by Simon Jakobi at 2018-06-13T23:39:30+02:00 Bump a few dependency bounds (#845) - - - - - 4791e1cc by Alec Theriault at 2018-06-13T23:39:30+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 311d3216 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - d0577817 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Complete FixitySig and FamilyDecl pattern matches - - - - - 055b3aa7 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Fix redundant import warnings - - - - - f9ce19b1 by Simon Jakobi at 2018-06-13T23:49:52+02:00 html-test: Accept output - - - - - 04604ea7 by Simon Jakobi at 2018-06-13T23:54:37+02:00 Bump bounds on Cabal - - - - - 0713b692 by Simon Jakobi at 2018-06-14T00:00:12+02:00 Merge branch 'ghc-head' into ghc-head-update-3 - - - - - c6a56bfd by Simon Jakobi at 2018-06-14T02:33:27+02:00 Bump ghc bound for haddock-api spec test-suite - - - - - 119d04b2 by Simon Jakobi at 2018-06-14T12:37:48+02:00 Travis: `--allow-newer` for all packages - - - - - 0e876e2c by Alex Biehl at 2018-06-14T15:28:52+02:00 Merge pull request haskell/haddock#857 from sjakobi/ghc-head-update-3 Update ghc-head - - - - - 5be46454 by Alec Theriault at 2018-06-14T21:42:45+02:00 Improved handling of interfaces in 'haddock-test' (#851) This should now work with an inplace GHC where (for instance) HTML directories may not be properly recorded in the package DB. - - - - - 96ab1387 by Vladislav Zavialov at 2018-06-14T17:06:21-04:00 Handle -XStarIsType - - - - - e518f8c4 by Ben Gamari at 2018-06-14T17:48:00-04:00 Revert unintentional reversion of fix of haskell/haddock#548 - - - - - 01b9f96d by Alan Zimmerman at 2018-06-19T11:52:22+02:00 Match changes in GHC for haskell/haddock#14259 - - - - - 7f8c8298 by Ben Gamari at 2018-06-19T18:14:27-04:00 Bump GHC version to 8.6 - - - - - 11c6b5d2 by Ryan Scott at 2018-06-19T23:17:31-04:00 Remove HsEqTy and XEqTy - - - - - b33347c2 by Herbert Valerio Riedel at 2018-06-20T23:14:52+02:00 Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. - - - - - f0d2460e by Herbert Valerio Riedel at 2018-06-20T23:28:46+02:00 Update Travis CI job - - - - - ef239223 by Herbert Valerio Riedel at 2018-06-20T23:32:41+02:00 Drop GHC HEAD from CI and update GHC to 8.4.3 It's a waste of resource to even try to build this branch w/ ghc-head; so let's not do that... - - - - - 41c4a9fa by Ben Gamari at 2018-06-20T18:26:20-04:00 Bump GHC version to 8.7 - - - - - 8be593dc by Herbert Valerio Riedel at 2018-06-21T22:32:15+02:00 Update CI job to use GHC 8.7.* - - - - - b91d334a by Simon Jakobi at 2018-06-30T13:41:38+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section - - - - - f707d848 by Alec Theriault at 2018-07-05T10:43:35-04:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. - - - - - a6d2b8dc by Alec Theriault at 2018-07-06T10:06:32-04:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case - - - - - 13819f71 by Alan Zimmerman at 2018-07-15T19:33:51+02:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 - - - - - c346aa78 by Simon Jakobi at 2018-07-19T12:29:32+02:00 haddock-library: Bump bounds for containers - - - - - 722e733c by Simon Jakobi at 2018-07-19T13:36:45+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] - - - - - f0bd83fd by Alec Theriault at 2018-07-19T14:39:57+02:00 Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. - - - - - 394053a8 by Simon Jakobi at 2018-07-19T14:58:07+02:00 haddock-library: Bump bounds for containers - - - - - 1bda11a2 by Alec Theriault at 2018-07-20T09:04:03+02:00 Add HEAD.hackage overlay (#887) * Add HEAD.hackage overlay * Add HCPKG variable - - - - - c7b4ab45 by Alec Theriault at 2018-07-20T12:01:16+02:00 Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test - - - - - c05d32ad by Alec Theriault at 2018-07-20T12:01:49+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output - - - - - 24b39ee4 by Alec Theriault at 2018-07-20T12:02:16+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. - - - - - cb9d2099 by Simon Jakobi at 2018-07-20T13:39:29+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) - - - - - 133f24f5 by Alec Theriault at 2018-07-20T13:39:29+02:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) - - - - - 11024149 by Alec Theriault at 2018-07-20T13:39:29+02:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) - - - - - de0c139e by Simon Jakobi at 2018-07-20T13:39:29+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) - - - - - 6435e952 by Alec Theriault at 2018-07-20T13:39:29+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) - - - - - 1461af39 by Alec Theriault at 2018-07-20T13:39:29+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) - - - - - 69d3bde1 by Alec Theriault at 2018-07-20T13:49:47+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) - - - - - 6a5c73c7 by Alec Theriault at 2018-07-20T13:50:00+02:00 Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests - - - - - 92ca94c6 by Alec Theriault at 2018-07-20T13:55:36+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) - - - - - 981bc7fa by Simon Jakobi at 2018-07-20T15:06:06+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers - - - - - 27e7c0c5 by Simon Jakobi at 2018-07-20T15:09:05+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 49e1a415 by Simon Jakobi at 2018-07-20T16:02:02+02:00 Update the ghc-8.6 branch (#889) * Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. * README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) * Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) * Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) * tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) * Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. * Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test * Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) * Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) * Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) * Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests * Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 5ca14bed by Simon Jakobi at 2018-07-20T16:05:47+02:00 Revert "Revert "Bump GHC version to 8.6"" That commit didn't belong onto the ghc-8.6 branch. This reverts commit acbaef3b9daf1d2dea10017964bf886e77a8e967. - - - - - 2dd600dd by Simon Jakobi at 2018-07-20T16:18:21+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. - - - - - fceb2422 by Simon Jakobi at 2018-07-20T16:18:21+02:00 outOfScope: Recommend qualifying the identifier - - - - - acea5d23 by Simon Jakobi at 2018-07-20T16:19:35+02:00 outOfScope: Recommend qualifying the identifier (cherry picked from commit 73707ed58d879cc04cb644c5dab88c39ca1465b7) - - - - - 1a83ca55 by Simon Jakobi at 2018-07-20T16:19:35+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. (cherry picked from commit d504a2864a4e1982e142cf88c023e7caeea3b76f) - - - - - 48374451 by Masahiro Sakai at 2018-07-20T17:06:42+02:00 Add # as a special character (#884) '#' has special meaning used for anchors and can be escaped using backslash. Therefore it would be nice to be listed as special characters. - - - - - 5e1a5275 by Alec Theriault at 2018-07-20T23:37:24+02:00 Let `haddock-test` bypass interface version check (#890) This means `haddock-test` might * crash during deserialization * deserialize incorrectly Still - it means things _might_ work where they were previously sure not to. - - - - - 27286754 by Yuji Yamamoto at 2018-07-23T08:16:01+02:00 Avoid "invalid argument (invalid character)" on non-unicode Windows (#892) Steps to reproduce and the error message ==== ``` > stack haddock basement ... snip ... Warning: 'A' is out of scope. Warning: 'haddock: internal error: <stdout>: commitBuffer: invalid argument (invalid character) ``` Environment ==== OS: Windows 10 ver. 1709 haddock: [HEAD of ghc-8.4 when I reproduce the error](https://github.com/haskell/haddock/commit/532b209d127e4cecdbf7e9e3dcf4f653a5605b5a). (I had to use this version to avoid another probrem already fixed in HEAD) GHC: 8.4.3 stack: Version 1.7.1, Git revision 681c800873816c022739ca7ed14755e85a579565 (5807 commits) x86_64 hpack-0.28.2 Related pull request ==== https://github.com/haskell/haddock/pull/566 - - - - - 6729d361 by Alec Theriault at 2018-07-23T13:52:56-07:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). - - - - - 8cf4e6b5 by Ryan Scott at 2018-07-27T11:28:03-04:00 eqTyCon_RDR now lives in TysWiredIn After GHC commit http://git.haskell.org/ghc.git/commit/f265008fb6f70830e7e92ce563f6d83833cef071 - - - - - 1ad251a6 by Alan Zimmerman at 2018-07-30T13:28:09-04:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 (cherry picked from commit e3926b50ab8a7269fd6904b06e881745f08bc5d6) - - - - - 8aea2492 by Richard Eisenberg at 2018-08-02T10:54:17-04:00 Update against new HsImplicitBndrs - - - - - e42cada9 by Alec Theriault at 2018-08-04T17:51:30+02:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 0e852512 by Alex Biehl at 2018-08-06T13:04:02+02:00 Make --package-version optional for --hoogle generation (#899) * Make --package-version optional for --hoogle generation * Import mkVersion * It's makeVersion not mkVersion - - - - - d2abd684 by Noel Bourke at 2018-08-21T09:34:18+02:00 Remove unnecessary backslashes from docs (#908) On https://haskell-haddock.readthedocs.io/en/latest/markup.html#special-characters the backslash and backtick special characters showed up with an extra backslash before them – I think the escaping is not (or no longer) needed for those characters in rst. - - - - - 7a578a9e by Matthew Pickering at 2018-08-21T09:34:50+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - aa3d4db3 by Matthew Pickering at 2018-08-21T09:37:34+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - ede91744 by Alec Theriault at 2018-08-21T09:42:52+02:00 Better test output when Haddock crashes on a test (#902) In particular: we report the tests that crashed seperately from the tests that produced incorrect output. In order for tests to pass (and exit 0), they must not crash and must produce the right output. - - - - - 4a872b84 by Guillaume Bouchard at 2018-08-21T09:45:57+02:00 Fix a typo (#878) - - - - - 4dbf7595 by Ben Sklaroff at 2018-08-21T12:04:09-04:00 Add ITcomment_line_prag token to Hyperlinker Parser This token is necessary for parsing #line pragmas inside nested comments. Reviewers: bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D4935 - - - - - 9170b2a9 by Ben Gamari at 2018-08-21T17:55:15-04:00 Merge pull request haskell/haddock#893 from harpocrates/get-name-to-instances Accumulate explicitly which modules to load for 'attachInstances' - - - - - d57b57cc by Ben Gamari at 2018-08-21T17:59:13-04:00 Merge branch 'ghc-head' of github.com:haskell/haddock into ghc-head - - - - - 14601ca2 by Alec Theriault at 2018-08-21T19:09:37-04:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). (cherry picked from commit 5c7c596c51d69b92164e9ba920157b36ce2b2ec1) - - - - - 438c645e by Matthew Pickering at 2018-08-21T19:12:39-04:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 (cherry picked from commit e6aa8fb47b9477cc5ef5e46097524fe83e080f6d) - - - - - a80c5161 by Alec Theriault at 2018-08-21T22:06:40-07:00 Better rendering of unboxed sums/tuples * adds space after/before the '#' marks * properly reify 'HsSumTy' in 'synifyType' - - - - - 88456cc1 by Alec Theriault at 2018-08-21T22:06:40-07:00 Handle promoted tuples in 'synifyType' When we have a fully applied promoted tuple, we can expand it out properly. - - - - - fd1c1094 by Alec Theriault at 2018-08-21T22:19:34-07:00 Accept test cases - - - - - 6e80d9e0 by Alec Theriault at 2018-08-21T22:24:03-07:00 Merge pull request haskell/haddock#914 from harpocrates/feature/unboxed-stuff Better rendering of unboxed sums, unboxed tuples, promoted tuples. - - - - - 181a23f1 by Ben Gamari at 2018-08-23T15:53:48-04:00 Merge remote-tracking branch 'origin/ghc-8.6' into ghc-8.6 - - - - - 3a18c1d8 by Alec Theriault at 2018-08-27T14:15:25-07:00 Properly synify promoted list types We reconstruct promoted list literals whenever possible. That means that 'synifyType' produces '[Int, Bool, ()] instead of (Int ': (() ': (Bool ': ([] :: [Type])))) - - - - - b4794946 by Alec Theriault at 2018-09-03T07:19:55-07:00 Only look at visible types when synifying a 'HsListTy' The other types are still looked at when considering whether to make a kind signature or not. - - - - - a231fce2 by Alec Theriault at 2018-09-03T07:38:10-07:00 Merge pull request haskell/haddock#922 from harpocrates/promoted-lists Properly synify promoted list types - - - - - 0fdf044e by Ningning Xie at 2018-09-15T10:25:58-04:00 Update according to GHC Core changes - - - - - 7379b115 by Ningning Xie at 2018-09-15T15:40:18-04:00 update dataFullSig to work with Co Quantification This should have been in the previous patch, but wasn't. - - - - - cf84a046 by Alec Theriault at 2018-09-17T20:12:18-07:00 Fix/add to various docs * Add documentation for a bunch of previously undocumented options (fixes haskell/haddock#870) * Extend the documentation of `--hoogle` considerably (see haskell/haddock#807) * Describe how to add docs to `deriving` clauses (fixes haskell/haddock#912) * Fix inaccurate docs about hyperlinking infix identifiers (fixes haskell/haddock#780) - - - - - ae017935 by Alec Theriault at 2018-09-22T08:32:16-07:00 Update Travis - - - - - d95ae753 by Alec Theriault at 2018-09-22T09:34:10-07:00 Accept failing tests Also silence orphan warnings. - - - - - f3e67024 by Alec Theriault at 2018-09-22T09:41:23-07:00 Bump haddock-api-2.21.0, haddock-library-1.7.0 * Update CHANGELOGS * Update new versions in Cabal files * Purge references to ghc-8.4/master branches in README - - - - - 3f136d4a by Alec Theriault at 2018-09-22T10:53:31-07:00 Turn haddock-library into a minor release Fix some version bounds in haddock-library too. - - - - - b9def006 by Alec Theriault at 2018-09-22T13:07:35-07:00 keep cabal.project file - - - - - 4909aca7 by Alec Theriault at 2018-10-16T09:36:30-07:00 Build on 7.4 and 7.8 - - - - - 99d20a28 by Herbert Valerio Riedel at 2018-10-16T18:45:52+02:00 Minor tweak to package description - - - - - a8059618 by Herbert Valerio Riedel at 2018-10-16T18:47:24+02:00 Merge pull request haskell/haddock#945 haddock-api 2.21.0 and haddock-library 1.6.1 release - - - - - 2d9bdfc1 by Alec Theriault at 2018-10-16T10:54:21-07:00 Bump haddock-library to 1.7.0 The 1.6.1 release should've been a major bump, since types in the `Documentation.Haddock.Parser.Monad` module changed. This version makes that module internal (as it morally should be). - - - - - ed340cef by Alec Theriault at 2018-10-16T14:59:13-07:00 Merge branch 'ghc-8.4' into ghc-8.6 - - - - - 2821a8df by Alec Theriault at 2018-10-16T15:14:48-07:00 Merge branch 'ghc-8.6' into ghc-head - - - - - a722dc84 by Alec Theriault at 2018-10-16T16:28:55-07:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 63377496 by Alec Theriault at 2018-10-16T16:39:07-07:00 Update changelog - - - - - 099a0110 by Alec Theriault at 2018-10-16T16:49:28-07:00 Merge pull request haskell/haddock#942 from harpocrates/update-docs Fix & add to documentation - - - - - 0927416f by Alec Theriault at 2018-10-16T16:50:14-07:00 Set UTF-8 encoding before writing files (#934) This should fix haskell/haddock#929, as well as guard against future problems of this sort in other places. Basically replaces 'writeFile' (which selects the users default locale) with 'writeUtf8File' (which always uses utf8). - - - - - 83b7b017 by Alec Theriault at 2018-10-16T17:42:05-07:00 Output pattern synonyms in Hoogle backend (#947) * Output pattern synonyms in Hoogle backend We were previously weren't outputting _any_ pattern synonyms, bundled or not. Now, we output both. Fixes haskell/haddock#946. * Update changelog - - - - - 81e5033d by Alec Theriault at 2018-10-16T18:04:40-07:00 Release `haddock{,-api}-2.22.0` This version will accompany ghc-8.6.2 - - - - - 9661744e by Alex Biehl at 2018-10-18T08:14:32-07:00 Add NewOcean theme And make it the default theme. - - - - - 7ae6d722 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Improve appearance and readability These changes include: - use latest Haskell's logo colors - decrease #content width to improve readability - use nicer font - improve sizes and distances - - - - - 37f8703d by NunoAlexandre at 2018-10-18T08:14:32-07:00 Include custom font in the html head - - - - - 1d5e1d79 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Update html test reference files - - - - - 53b7651f by NunoAlexandre at 2018-10-18T08:14:32-07:00 Make it responsive - It makes small screens taking more space than larger ones - fixes a few issues present in small screens currently - make it look good across different screen sizes. - - - - - 6aa1aeb1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make the style consistent with hackage Several things are addressed here: - better responsive behaviour on the header - better space usage - consistent colors overall - other nit PR comments - - - - - 3a250c5c by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Place the package name before the menu links This supports the expected responsive menu design, where the package name appears above the menu links. - - - - - cae699b3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update html-test reference files The package name element in the package-header is now a div instead of a paragraph, and it is now above the menu ul.links instead of below. - - - - - 2ec7fd2d by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve synopsis style and code - Use CSS3 instead of loading pictures to show "+" and "-" symbols - Drop redundant code - - - - - 0c874c01 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Decrease space between code blocks There was too much space between code blocks as pointed out by reviewers. - - - - - 85568ce2 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Add an initial-scale property to all haddock pages This solves an issue reported about the content looking incredibly small on mobile devices. - - - - - c1538926 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Address several PR comments - Darken text color like done for hackage - Move synopsis to left side - Make table of contents stick to the left on wide screens - Wrap links to avoid page overflow - Improve expand/collapse buttons - Fix issue with content size on mobile devices - Fix issue with font-size on landscape mode - Increase width of the content - Change colors of table of contents and synopsis - Etc - - - - - e6639e5f by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make synopsis scrollable on wide screens When the synopsis is longer than the screen, you can’t see its end and you can't scroll down either, making the content unreachable. - - - - - 1f0591ff by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve information density - Reduce font size - Improve space between and within code blocks - Improve alignments - Improve spacing within sub-blocks - - - - - bf083097 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Minor adjustments Bring in some adjustments made to hackage: - link colors - page header show everything when package title is too long - - - - - 10375fc7 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix responsive triggers overlap issue The min and max width triggers have the same values, which caused the style resolution to take an intersection of both style declarations when the screen resolution had the size of the limts (say 1280px), causing an odd behaviour and look. - - - - - 95ff2f95 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix issue with menu alignment on firefox Reported and described here: https://github.com/haskell/haddock/pull/721#issuecomment-374668869 - - - - - dc86587e by Alex Biehl at 2018-10-18T08:14:32-07:00 Changelog entry for NewOcean - - - - - 27195e47 by Herbert Valerio Riedel at 2018-10-18T08:14:32-07:00 html-test --accept - - - - - 83f4f9c0 by Alex Biehl at 2018-10-18T08:14:32-07:00 Avoid name shadowing - - - - - 231487f1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font to PT Sans Also migrate some general text related changes from hackage. - - - - - 313db81a by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Use 'flex' to fix header alignment - - - - - 5087367b by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Misc of tweaks - Update link colors to hackage scheme - Tune spacing between content elements - Update footer style - Fix and improve code blocks identation - - - - - b08020df by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font in Xhtml.hs to PT Sans - - - - - 78ce06e3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve code blocks styling - Fix and improve spacing - Improve colors and borders - - - - - 81262d20 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make package-header caption backward-compatible The current html generator of this branch wraps the package-header caption as a div, which does not work (without style adjustments) with the old themes. Changing it from div to span does the trick, without needing to adjust the old stylesheets. - - - - - dc4475cb by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update test-suite reference html pages - - - - - 393d35d8 by Alec Theriault at 2018-10-18T08:25:36-07:00 Accept tests - - - - - a94484ba by Alec Theriault at 2018-10-21T10:29:29-07:00 Fix CHANGELOG - - - - - 8797eca3 by Alec Theriault at 2018-10-21T10:36:19-07:00 Update 'data-files' to include NewOcean stuff - - - - - 1ae51e4a by Simon Jakobi at 2018-10-23T11:29:14+02:00 Fix typo in a warning - - - - - 009ad8e8 by Alec Theriault at 2018-10-24T12:47:47-07:00 Update JS dependencies This was done via `npm audit fix`. I think this fixes haskell/haddock#903 along with some more serious vulnerabilities that nobody seems to have noticed. - - - - - 051994db by Alec Theriault at 2018-10-24T17:31:09-07:00 Resurrect the style-switcher This fixes haskell/haddock#810. Looks like things were broken during the quickjump refactor of the JS. For the (git) record: I do not think the style switcher is a good idea. I'm fixing it for the same reason @mzero added it; as an answer to "rumblings from some that they didn't want their pixels changed on bit" - - - - - 2a1d620f by Alec Theriault at 2018-10-24T17:38:07-07:00 Fix copy-pasta error in data-files - - - - - ed5bfb7f by Alec Theriault at 2018-10-24T20:42:14-07:00 Fix the synopsis button Here's these changes are supposed to do: * put the synopsis back on the right side * properly have it on the edge of the screen on wide screens * adjust the background of the synopsis to match the button (otherwise the grey blends in with what is underneath) * get rid of the dotted purple line * the synopsis contents are now scrollable even when in wide screens (this has been a long-standing bug) - - - - - 883fd74b by Alec Theriault at 2018-10-25T20:16:46-07:00 Avoid more conflicts in generated ids (#954) This fixes haskell/haddock#953 by passing more names into the generated ids. - - - - - ea54e331 by Alec Theriault at 2018-10-25T21:07:12-07:00 Don't hide bullets in method docs I think thst CSS was meant only to deal with fields and the effect on bullets was accidental. Fixes haskell/haddock#926. - - - - - 9a14ef4a by Alec Theriault at 2018-10-25T22:02:07-07:00 Indent more things + slightly smaller font - - - - - b9f17e29 by Alec Theriault at 2018-10-25T22:10:01-07:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 096a3cfa by Alec Theriault at 2018-10-25T22:24:38-07:00 Accept HTML output - - - - - 2669517d by Alec Theriault at 2018-10-26T09:02:35-07:00 User manual + stuff for building GHC docs - - - - - 46b27687 by Alec Theriault at 2018-10-26T09:10:59-07:00 Make 'Contents' in NewOcean scrollable This only happens if the contents block on the left is so big that it doesn't fit (vertically) on the page. If that happens, we want it to be scrollable. - - - - - 3443dd94 by Alec Theriault at 2018-10-26T09:36:46-07:00 Revert "Make 'Contents' in NewOcean scrollable" This reverts commit f909ffd8353d6463fd5dd184998a32aa98d5c922. I missed the fact this also forces the 'Contents' to always go down to the bottom of the page. - - - - - ed081424 by Alec Theriault at 2018-10-26T14:22:23-07:00 Avoid some partiality AFAICT this wasn't causing any crashes, but that's mostly because we happen not to be forcing `pkgStr` when it would diverge. We come dangerously close to doing that in `ppHtmlIndex`. Fixes haskell/haddock#569. - - - - - 6a5bec41 by Alec Theriault at 2018-10-27T10:05:04-07:00 Fix documentation in `haddock-api` (#957) * Fix misplaced Haddocks in Haddock itself Haddock should be able to generate documentation for 'haddock-api' again. * Make CI check that documentation can be built. * Add back a doc that is OK - - - - - 5100450a by Matthew Yacavone at 2018-10-27T14:51:38-04:00 More explicit foralls (GHC Proposal 0007) - - - - - 8771a6b0 by Alec Theriault at 2018-11-05T13:58:11-08:00 Only run MathJax on entities with "mathjax" class (#960) Correspondingly, we wrap all inline/diplay math in <span class="mathjax"> ... the math .... </span> This fixes haskell/haddock#959. - - - - - bd7ff5c5 by Alec Theriault at 2018-11-05T15:54:22-08:00 Deduplicate some work in 'AttachInstances' Perf only change: * avoid needlessly union-ing maps * avoid synify-ing instances twice Took this opportunity to add some docs too - - - - - cf99fd8f by Alec Theriault at 2018-11-05T15:54:22-08:00 Specialize some SYB functions Perf only change: * Add a 'SPECIALIZE' pragma to help GHC optimize a 'Data a =>' constraint * Manually specialize the needlessly general type of 'specializeTyVarBndrs' - - - - - 4f91c473 by Alec Theriault at 2018-11-05T15:54:22-08:00 Improve perf of renaming Perf only change: * don't look up type variable names (they're never in the environment) * use a difference list for accumulating missing names * more efficient 'Functor'/'Applicative' instances for 'RnM' - - - - - 4bbab0d4 by Alec Theriault at 2018-11-05T15:54:22-08:00 Faster 'Text' driven parser combinators Perf only change: * use 'getParserState'/'setParserState' to make 'Text'-optimized parser combinators * minimize uses of 'Data.Text.{pack,unpack,cons,snoc}' - - - - - fa430c02 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support hyperlink labels with inline markup The parser for pictures hasn't been properly adjusted yet. - - - - - c1431035 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support (and flatten) inline markup in image links Inline markup is supported in image links but, as per the [commonmark recommendation][0], it is stripped back to a plain text representation. [0]: https://spec.commonmark.org/0.28/#example-547 - - - - - d4ee1ba5 by Alec Theriault at 2018-11-06T12:03:24-08:00 Accept test case - - - - - 8088aeb1 by Alec Theriault at 2018-11-06T12:03:24-08:00 Fix/add to haddock-library test suite - - - - - e78f644d by Alec Theriault at 2018-11-06T13:26:31-08:00 Bump version bounds - - - - - 644335eb by Alec Theriault at 2018-11-06T13:53:30-08:00 Merge pull request haskell/haddock#875 from harpocrates/feature/markup-in-hyperlinks Inline markup in markdown-style links and images - - - - - e173ed0d by Alec Theriault at 2018-11-07T12:37:18-08:00 Fix issues around plus/minus * swap the minimize unicode to something more intuitive * use new unicode expander/collapser for instance lists * address some alignment issues in the "index" page - - - - - b2d92df7 by Alec Theriault at 2018-11-07T13:41:57-08:00 Allow "Contents" summary to scroll in a fixed div In the unfortunate event that the "Contents" summary doesn't fit vertically (like in the "Prelude"), it will be scrollable. - - - - - ca704c23 by Alec Theriault at 2018-11-07T13:45:15-08:00 Accept HTML output changes - - - - - 82c0ec6d by Alec Theriault at 2018-11-07T18:12:54-08:00 overflow-y 'scroll' -> 'auto' - - - - - 571d7657 by Alec Theriault at 2018-11-08T19:44:12-08:00 Clicking on "Contents" navigates to top of page - - - - - 8065a012 by Alec Theriault at 2018-11-08T19:44:17-08:00 Space out functions more Also, functions and data decls now have the same space before and after them. - - - - - cc650ede by Alec Theriault at 2018-11-09T08:13:35-08:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 65f8c17f by Alec Theriault at 2018-11-10T14:04:06-08:00 Update changelog - - - - - 20473847 by Alec Theriault at 2018-11-10T14:21:40-08:00 Replace oplus/ominus expander/collapser icons with triangles - - - - - 16592957 by Alec Theriault at 2018-11-10T14:35:10-08:00 Merge pull request haskell/haddock#949 from haskell/wip/new-ocean Introduce NewOcean theme. - - - - - 357cefe1 by Alec Theriault at 2018-11-10T16:02:13-08:00 Merge branch 'ghc-8.6' into ghc-head - - - - - de612267 by Alec Theriault at 2018-11-11T20:01:21-08:00 Rename 'NewOcean' theme to 'Linuwial' - - - - - 954b5baa by Alec Theriault at 2018-11-12T08:33:18-08:00 Add blockquote styling Matches b71da1feabf33efbbc517ac376bb690b5a604c2f from hackage-server. Fixes haskell/haddock#967. - - - - - d32c0b0b by Fangyi Zhou at 2018-11-12T10:24:13-08:00 Fix some broken links (#15733) Summary: For links in subpackages as well. https://phabricator.haskell.org/D5257 Test Plan: Manually verify links Reviewers: mpickering, bgamari, osa1 Reviewed By: osa1 GHC Trac Issues: haskell/haddock#15733 Differential Revision: https://phabricator.haskell.org/D5262 - - - - - 41098b1f by Alp Mestanogullari at 2018-11-15T22:40:09+01:00 Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change It got introduced in ghc/ghc at ae2c9b40f5b6bf272251d1f4107c60003f541b62. - - - - - c5c1c7e0 by Alec Theriault at 2018-11-15T13:48:13-08:00 Merge pull request haskell/haddock#970 from alpmestan/alp/fix-promotionflag Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change - - - - - 6473d3a4 by Shayan-Najd at 2018-11-23T01:38:49+01:00 [TTG: Handling Source Locations] Foundation and Pat Trac Issues haskell/haddock#15495 This patch removes the ping-pong style from HsPat (only, for now), using the plan laid out at https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/HandlingSourceLocations (solution A). - the class `HasSrcSpan`, and its functions (e.g., `cL` and `dL`), are introduced - some instances of `HasSrcSpan` are introduced - some constructors `L` are replaced with `cL` - some patterns `L` are replaced with `dL->L` view pattern - some type annotation are necessarily updated (e.g., `Pat p` --> `Pat (GhcPass p)`) - - - - - 7a088dfe by Alec Theriault at 2018-11-26T11:11:28-08:00 More uniform handling of `forall`'s in HTML/LaTeX * don't forget to print explicit `forall`'s when there are arg docs * when printing an explicit `forall`, print all tyvars Fixes haskell/haddock#973 - - - - - d735e570 by Alec Theriault at 2018-12-12T08:42:09-08:00 Fix warnings, accept output * remove redundant imports (only brought to light due to recent work for improving redundant import detection) * fix a bug that was casuing exports to appear in reverse order * fix something in haddock-library that prevented compilation on old GHC's - - - - - a3852f8a by Zejun Wu at 2018-12-14T09:37:47-05:00 Output better debug infromation on internal error in extractDecl This will make investigation of haskell/haddock#979 easier - - - - - 2eccb5b9 by Alec Theriault at 2018-12-17T09:25:10-05:00 Refactor names + unused functions (#982) This commit should not introduce any change in functionality! * consistently use `getOccString` to convert `Name`s to strings * compare names directly when possible (instead of comparing strings) * get rid of unused utility functions - - - - - e82e4df8 by Alec Theriault at 2018-12-20T16:16:30-05:00 Load plugins when compiling each module (#983) * WIP: Load (typechecker) plugins from language pragmas * Revert "Load plugins when starting a GHC session (#905)" This reverts commit 72d82e52f2a6225686d9668790ac33c1d1743193. * Simplify plugin initialization code - - - - - 96e86f38 by Alec Theriault at 2018-12-23T10:23:20-05:00 Properly synify and render promoted type variables (#985) * Synify and render properly promoted type variables Fixes haskell/haddock#923. * Accept output - - - - - 23343345 by Alec Theriault at 2018-12-27T16:39:38-05:00 Remove `haddock-test`'s dep. on `syb` (#987) The functionality is easily inlined into one short function: `gmapEverywhere`. This doesn't warrant pulling in another package. - - - - - d0734f21 by Alec Theriault at 2018-12-27T16:39:52-05:00 Address deprecation warnings in `haddock-test` (#988) Fixes haskell/haddock#885. - - - - - 4d9f144e by mynguyen at 2018-12-30T23:42:26-05:00 Visible kind application haddock update - - - - - ffe0e9ed by Alec Theriault at 2019-01-07T13:55:22-08:00 Print kinded tyvars in constructors for Hoogle (#993) Fixes haskell/haddock#992 - - - - - 2e18b55d by Alec Theriault at 2019-01-10T16:42:45-08:00 Accept new output `GHC.Maybe` -> `Data.Maybe` (#996) Since 53874834b779ad0dfbcde6650069c37926da1b79 in GHC, "GHC.Maybe" is marked as `not-home`. That changes around some test output. - - - - - 055da666 by Gabor Greif at 2019-01-22T14:41:51+01:00 Lone typofix - - - - - 01bb71c9 by Alec Theriault at 2019-01-23T11:46:46-08:00 Keep forall on H98 existential data constructors (#1003) The information about whether or not there is a source-level `forall` is already available on a `ConDecl` (as `con_forall`), so we should use it instead of always assuming `False`! Fixes haskell/haddock#1002. - - - - - f9b9bc0e by Ryan Scott at 2019-01-27T09:28:12-08:00 Fix haskell/haddock#1004 with a pinch of dropForAlls - - - - - 5cfcdd0a by Alec Theriault at 2019-01-28T16:49:57-08:00 Loosen 'QuickCheck' and 'hspec' bounds It looks like the new versions don't cause any breakage and loosening the bounds helps deps fit in one stack resolver. - - - - - 3545d3dd by Alec Theriault at 2019-01-31T01:37:25-08:00 Use `.hie` files for the Hyperlinker backend (#977) # Summary This is a large architectural change to the Hyperlinker. * extract link (and now also type) information from `.hie` instead of doing ad-hoc SYB traversals of the `RenamedSource`. Also adds a superb type-on-hover feature (#715). * re-engineer the lexer to avoid needless string conversions. By going directly through GHC's `P` monad and taking bytestring slices, we avoid a ton of allocation and have better handling of position pragmas and CPP. In terms of performance, the Haddock side of things has gotten _much_ more efficient. Unfortunately, much of this is cancelled out by the increased GHC workload for generating `.hie` files. For the full set of boot libs (including `ghc`-the-library) * the sum of total time went down by 9-10% overall * the sum of total allocations went down by 6-7% # Motivation Haddock is moving towards working entirely over `.hi` and `.hie` files. This change means we no longer need the `RenamedSource` from `TypecheckedModule` (something which is _not_ in `.hi` files). # Details Along the way a bunch of things were fixed: * Cross package (and other) links are now more reliable (#496) * The lexer tries to recover from errors on every line (instead of at CPP boundaries) * `LINE`/`COLUMN` pragmas are taken into account * filter out zero length tokens before rendering * avoid recomputing the `ModuleName`-based `SrcMap` * remove the last use of `Documentation.Haddock.Utf8` (see haskell/haddock#998) * restructure temporary folder logic for `.hi`/`.hie` model - - - - - 2ded3359 by Herbert Valerio Riedel at 2019-02-02T12:06:12+01:00 Update/modernise haddock-library.cabal file - - - - - 62b93451 by Herbert Valerio Riedel at 2019-02-02T12:19:31+01:00 Tentatively declare support for unreleased base-4.13/ghc-8.8 - - - - - 6041e767 by Herbert Valerio Riedel at 2019-02-02T16:04:32+01:00 Normalise LICENSE text w/ cabal's BSD2 template Also, correct the `.cabal` files to advertise `BSD2` instead of the incorrect `BSD3` license. - - - - - 0b459d7f by Alec Theriault at 2019-02-02T18:06:12-08:00 CI: fetch GHC from validate artifact Should help make CI be less broken - - - - - 6b5c07cf by Alec Theriault at 2019-02-02T18:06:12-08:00 Fix some Hyperlinker test suite fallout * Amend `ParserSpec` to match new Hyperlinker API - pass in compiler info - strip out null tokens * Make `hypsrc-test` pass reliably - strip out `local-*` ids - strip out `line-*` ids from the `ClangCppBug` test - re-accept output - - - - - ded34791 by Nathan Collins at 2019-02-02T18:31:23-08:00 Update README instructions for Stack No need to `stack install` Haddock to test it. Indeed, `stack install` changes the `haddock` on user's `PATH` if `~/.local/bin` is on user's `PATH` which may not be desirable when hacking on Haddock. - - - - - 723298c9 by Alec Theriault at 2019-02-03T09:11:05-08:00 Remove `Documentation.Haddock.Utf8` The circumstances under which this module appeared are completely gone. The Hyperlinker backend no longer needs this module (it uses the more efficient `Encoding` module from `ghc`). Why no deprecation? Because this module really shouldn't exist! - It isn't used in `haddock-library`/`haddock-api` anymore - It was copy pasted directly from `utf8-string` - Folks seeking a boot-lib only solution can use `ghc`'s `Encoding` - - - - - 51050006 by Alec Theriault at 2019-02-03T22:58:58-08:00 Miscellaneous improvements to `Convert` (#1020) Now that Haddock is moving towards working entirely over `.hi` and `.hie` files, all declarations and types are going to be synthesized via the `Convert` module. In preparation for this change, here are a bunch of fixes to this module: * Add kind annotations to type variables in `forall`'s whose kind is not `Type`, unless the kind can be inferred from some later use of the variable. See `implicitForAll` and `noKindTyVars` in particular if you wish to dive into this. * Properly detect `HsQualTy` in `synifyType`. This is done by following suit with what GHC's `toIfaceTypeX` does and checking the first argument of `FunTy{} :: Type` to see if it classified as a given/wanted in the typechecker (see `isPredTy`). * Beef up the logic around figuring out when an explicit `forall` is needed. This includes: observing if any of the type variables will need kind signatures, if the inferred type variable order _without_ a forall will still match the one GHC claims, and some other small things. * Add some (not yet used) functionality for default levity polymorphic type signatures. This functionality similar to `fprint-explicit-runtime-reps`. Couple other smaller fixes only worth mentioning: * Show the family result signature only when it isn't `Type` * Fix rendering of implicit parameters in the LaTeX and Hoogle backends * Better handling of the return kind of polykinded H98 data declarations * Class decls produced by `tyThingToLHsDecl` now contain associated type defaults and default method signatures when appropriate * Filter out more `forall`'s in pattern synonyms - - - - - 841980c4 by Oleg Grenrus at 2019-02-04T08:44:25-08:00 Make a fixture of weird parsing of lists (#997) The second example is interesting. If there's a list directly after the header, and that list has deeper structure, the parser is confused: It finds two lists: - One with the first nested element, - everything after it I'm not trying to fix this, as I'm not even sure this is a bug, and not a feature. - - - - - 7315c0c8 by Ryan Scott at 2019-02-04T12:17:56-08:00 Fix haskell/haddock#1015 with dataConUserTyVars (#1022) The central trick in this patch is to use `dataConUserTyVars` instead of `univ_tvs ++ ex_tvs`, which displays the foralls in a GADT constructor in a way that's more faithful to how the user originally wrote it. Fixes haskell/haddock#1015. - - - - - ee0b49a3 by Ryan Scott at 2019-02-04T15:25:17-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. - - - - - 1c850dc8 by Alan Zimmerman at 2019-02-05T21:54:18+02:00 Matching changes in GHC for haskell/haddock#16236 - - - - - ab03c38e by Simon Marlow at 2019-02-06T08:07:33+00:00 Merge pull request haskell/haddock#1014 from hvr/pr/bsd2-normalise Normalise LICENSE text w/ cabal's BSD2 template - - - - - 5a92ccae by Alec Theriault at 2019-02-10T06:21:55-05:00 Merge remote-tracking branch 'gitlab/wip/T16236-2' into ghc-head - - - - - c0485a1d by Alec Theriault at 2019-02-10T03:32:52-08:00 Removes `haddock-test`s dependency on `xml`/`xhtml` (#1027) This means that `html-test`, `latex-test`, `hoogle-test`, and `hypsrc-test` now only depend on GHC boot libs. So we should now be able to build and run these as part of GHC's testsuite. \o/ The reference output has changed very slightly, in three ways: * we don't convert quotes back into `&quot;` as the `xml` lib did * we don't add extra `&nbsp;` as the `xml` lib did * we now remove the entire footer `div` (instead of just emptying it) - - - - - 65a448e3 by Alec Theriault at 2019-02-11T12:27:41-05:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - 360ca937 by Alec Theriault at 2019-02-13T11:36:11-05:00 Clean up logic for guessing `-B` and `--lib` (#1026) Haddock built with the `in-ghc-tree` flag tries harder to find the GHC lib folder and its own resources. This should make it possible to use `in-ghc-tree`-built Haddock without having to specify the `-B` and `--lib` options (just how you can use in-tree GHC without always specifying the `-B` option). The logic to do this relies on `getExecutablePath`, so we only get this auto-detection on platforms where this function works. - - - - - d583e364 by Alec Theriault at 2019-02-16T10:41:22-05:00 Fix tests broken by GHC Changes in 19626218566ea709b5f6f287d3c296b0c4021de2 affected some of the hyperlinker output. Accepted the new output (hovering over a `..` now shows you what that wildcard binds). Also fixed some stray deprecation warnings. - - - - - da0c42cc by Vladislav Zavialov at 2019-02-17T11:39:19+03:00 Parser changes to match !380 - - - - - ab96bed7 by Ryan Scott at 2019-02-18T04:44:08-05:00 Bump ghc version to 8.9 - - - - - 44b7c714 by Alec Theriault at 2019-02-22T05:49:43-08:00 Match GHC changes for T16185 `FunTy` now has an `AnonArgFlag` that indicates whether the arrow is a `t1 => t2` or `t1 -> t2`. This commit shouldn't change any functionality in Haddock. - - - - - 2ee653b1 by Alec Theriault at 2019-02-24T18:53:33-08:00 Update .travis.yml Points to the new GHC CI artifact. - - - - - 90939d71 by Alec Theriault at 2019-02-25T00:42:41-08:00 Support value/type namespaces on identifier links Identifier links can be prefixed with a 'v' or 't' to indicate the value or type namespace of the desired identifier. For example: -- | Some link to a value: v'Data.Functor.Identity' -- -- Some link to a type: t'Data.Functor.Identity' The default is still the type (with a warning about the ambiguity) - - - - - d6ed496c by Alec Theriault at 2019-02-25T00:42:46-08:00 Better identifier parsing * '(<|>)' and '`elem`' now get parsed and rendered properly as links * 'DbModule'/'DbUnitId' now properly get split apart into two links * tuple names now get parsed properly * some more small niceties... The identifier parsing code is more precise and more efficient (although to be fair: it is also longer and in its own module). On the rendering side, we need to pipe through information about backticks/parens/neither all the way through from renaming to the backends. In terms of impact: a total of 35 modules in the entirety of the bootlib + ghc lib docs change. The only "regression" is things like '\0'. These should be changed to @\\0@ (the path by which this previously worked seems accidental). - - - - - 3c3b404c by Alec Theriault at 2019-02-25T22:12:11-08:00 Fix standalone deriving docs Docs on standalone deriving decls for classes with associated types should be associated with the class instance, not the associated type instance. Fixes haskell/haddock#1033 - - - - - d51ef69e by Alec Theriault at 2019-02-26T19:14:59-08:00 Fix bogus identifier defaulting This avoids a situation in which an identifier would get defaulted to a completely different identifier. Prior to this commit, the 'Bug1035' test case would hyperlink 'Foo' into 'Bar'! Fixes haskell/haddock#1035. - - - - - 88cbbdc7 by Ryan Scott at 2019-02-27T10:14:03-05:00 Visible dependent quantification (#16326) changes - - - - - 0dcf6cee by Xia Li-yao at 2019-02-27T21:53:27-05:00 Menu item controlling which instances are expanded/collapsed (#1007) Adds a menu item (like "Quick Jump") for options related to displaying instances. This provides functionality for: * expanding/collapsing all instances on the currently opened page * controlling whether instances are expanded/collapsed by default * controlling whether the state of instances should be "remembered" This new functionality is implemented in Typescript in `details-helper`. The built-in-themes style switcher also got a revamp so that all three of QuickJump, the style switcher, and instance preferences now have the same style and implementation structure. See also: https://mail.haskell.org/pipermail/haskell-cafe/2019-January/130495.html Fixes haskell/haddock#698. Co-authored-by: Lysxia <lysxia at gmail.com> Co-authored-by: Nathan Collins <conathan at galois.com> - - - - - 3828c0fb by Alec Theriault at 2019-02-28T12:42:49-05:00 `--show-interface` should output to stdout. (#1040) Fixes haskell/haddock#864. - - - - - a50f4cda by gbaz at 2019-03-01T07:43:16-08:00 Increase contrast of Linuwal theme (#1037) This is to address the concern that, on less nice and older screens, some of the shades of grey blend in too easily with the white background. * darken the font slightly * darken slightly the grey behind type signatures and such * add a border and round the corners on code blocks * knock the font down by one point - - - - - ab4d41de by Alec Theriault at 2019-03-03T09:23:26-08:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 12f509eb by Ben Gamari at 2019-03-04T22:13:20-05:00 Remove reference to Opt_SplitObjs flag Split-objects has been removed. - - - - - 5b3e4c9a by Ryan Scott at 2019-03-06T19:16:24-05:00 Update html-test output to reflect haskell/haddock#16391 changes - - - - - fc228af1 by Alec Theriault at 2019-03-09T08:29:23-08:00 Match changes for "Stop inferring over-polymorphic kinds" The `hsq_ext` field of `HsQTvs` is now just the implicit variables (instead of also including information about which of these variables are dependent). This commit shouldn't change any functionality in Haddock. - - - - - 6ac109eb by Alec Theriault at 2019-03-09T11:22:55-08:00 Add .hi, .dyn_hi, etc files to .gitignore Fixes haskell/haddock#1030. - - - - - b55f0c05 by Alec Theriault at 2019-03-09T11:22:55-08:00 Better support for default methods in classes * default methods now get rendered differently * default associated types get rendered * fix a forgotten `s/TypeSig/ClassOpSig/` refactor in LaTeX backend * LaTeX backend now renders default method signatures NB: there is still no way to document default class members and the NB: LaTeX backend still crashes on associated types - - - - - 10aea0cf by Alec Theriault at 2019-03-09T11:22:55-08:00 Avoid multi-line `emph` in LaTeX backend `markupWarning` often processes inputs which span across paragraphs. Unfortunately, LaTeX's `emph` is not made to handle this (and will crash). Fixes haskell/haddock#936. - - - - - d22dc2c9 by Alec Theriault at 2019-03-09T11:22:55-08:00 Many LaTeX backend fixes After this commit, we can run with `--latex` on all boot libraries without crashing (although the generated LaTeX still fails to compile in a handful of larger packages like `ghc` and `base`). * Add newlines after all block elements in LaTeX. This is important to prevent the final output from being more an more indented. See the `latext-test/src/Example` test case for a sample of this. * Support associated types in class declarations (but not yet defaults) * Several small issues for producing compiling LaTeX; - avoid empy `\haddockbeginargs` lists (ex: `type family Any`) - properly escape identifiers depending on context (ex: `Int#`) - add `vbox` around `itemize`/`enumerate` (so they can be in tables) * Several spacing fixes: - limit the width of `Pretty`-arranged monospaced code - cut out extra space characters in export lists - only escape spaces if there are _multiple_ spaces - allow type signatures to be multiline (even without docs) * Remove uninteresting and repetitive `main.tex`/`haddock.sty` files from `latex-test` test reference output. Fixes haskell/haddock#935, haskell/haddock#929 (LaTeX docs for `text` build & compile) Fixes haskell/haddock#727, haskell/haddock#930 (I think both are really about type families...) - - - - - 0e6cee00 by Alec Theriault at 2019-03-29T12:11:56-07:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - ce05434d by Alan Zimmerman at 2019-03-29T12:12:11-07:00 Matching changes in GHC for haskell/haddock#16236 (cherry picked from commit 3ee6526d4ae7bf4deb7cd1caf24b3d7355573576) - - - - - d85766b2 by Ben Gamari at 2019-03-29T12:14:04-07:00 Bump GHC to 8.8 - - - - - 5a82cbaf by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Redo ParseModuleHeader - - - - - b9033348 by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - bb55c8f4 by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove outdated `.ghci` files and `scripts` The `.ghci` files are actively annoying when trying to `cabal v2-repl`. As for the `scripts`, the distribution workflow is completely different. - - - - - 5ee244dc by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove obsolete arcanist files + STYLE Now that GHC is hosted on Gitlab, the arcanist files don't make sense anymore. The STYLE file contains nothing more than a dead link too. - - - - - d07c1928 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Redo ParseModuleHeader - - - - - 492762d2 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - af2ac773 by Ryan Scott at 2019-05-14T17:22:13-04:00 Changes for haskell/haddock#16110/#16356 - - - - - 6820ed0d by Alec Theriault at 2019-05-17T08:51:27-07:00 Unbreak haskell/haddock#1004 test case `fail` is no longer part of `Monad`. - - - - - 6bf7be98 by Alec Theriault at 2019-05-17T08:51:27-07:00 Fix haskell/haddock#1063 with better parenthesization logic for contexts The only other change in html/hoogle/hyperlinker output for the boot libraries that this caused is a fix to some Hoogle output for implicit params. ``` $ diff -r _build/docs/ old_docs diff -r _build/docs/html/libraries/base/base.txt old_docs/html/libraries/base/base.txt 13296c13296 < assertError :: (?callStack :: CallStack) => Bool -> a -> a --- > assertError :: ?callStack :: CallStack => Bool -> a -> a ``` - - - - - b5716b61 by Ryan Scott at 2019-05-22T17:24:32-04:00 Match changes with haskell/haddock#14332 - - - - - c115abf6 by Alec Theriault at 2019-05-26T16:01:58-04:00 Remove Haddock's dependency on `Cabal` At this point, Haddock depended on Cabal-the-library solely for a verbosity parser (which misleadingly accepts all sorts of verbosity options that Haddock never uses). Now, the only dependency on Cabal is for `haddock-test` (which uses Cabal to locate the Haddock interface files of a couple boot libraries). - - - - - e5b2d4a3 by Alec Theriault at 2019-05-26T16:16:25-04:00 Regression test: promoted lists in associated types When possible, associated types with promoted lists should use the promoted list literal syntax (instead of repeated applications of ': and '[]). This was fixed in 2122de5473fd5b434af690ff9ccb1a2e58491f8c. Closes haskell/haddock#466, - - - - - cc5ad5d3 by Alec Theriault at 2019-05-26T17:55:54-04:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 4b3301a6 by Alec Theriault at 2019-05-26T17:57:52-04:00 Release haddock-2.23, haddock-library-1.8.0 Tentatively adjust bounds and changelogs for the release to be bundled with GHC 8.8.1. - - - - - 69c7cfce by Matthew Pickering at 2019-05-30T10:54:27+01:00 Update hyperlinker tests for new types in .hie files - - - - - 29b7e738 by Zubin Duggal at 2019-05-30T10:57:51+01:00 update for new way to store hiefile headers - - - - - aeca5d5f by Zubin Duggal at 2019-06-04T18:57:42-04:00 update for new way to store hiefile headers - - - - - ba2ca518 by Ben Gamari at 2019-06-07T23:11:14+00:00 Update test output for introduction of Safe-Inferred - - - - - 3a975a6c by Ryan Scott at 2019-07-03T12:06:27-04:00 Changes for haskell/haddock#15247 - - - - - 0df46555 by Zubin Duggal at 2019-07-22T10:52:50+01:00 Fix haddockHypsrcTest - - - - - 2688686b by Sylvain Henry at 2019-09-12T23:19:39+02:00 Fix for GHC module renaming - - - - - 9ec0f3fc by Alec Theriault at 2019-09-20T03:21:00-04:00 Fix Travis CI, loosen .cabal bounds (#1089) Tentatively for the 2.23 release: * updated Travis CI to work again * tweaked bounds in the `.cabal` files * adjusted `extra-source-files` to properly identify test files - - - - - ca559beb by Matthías Páll Gissurarson at 2019-09-28T12:14:40-04:00 Small change in to facilitate extended typed-holes (#1090) This change has no functional effect on haddock itself, it just changes one pattern to use `_ (` rather than `_(`, so that we may use `_(` as a token for extended typed-holes later. - - - - - 02e28976 by Vladislav Zavialov at 2019-09-28T12:17:45-04:00 Remove spaces around @-patterns (#1093) This is needed to compile `haddock` when [GHC Proposal haskell/haddock#229](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0229-whitespace-bang-patterns.rst) is implemented. - - - - - 83cbbf55 by Alexis King at 2019-09-30T21:12:42-04:00 Fix the ignore-exports option (#1082) The `ignore-exports` option has been broken since haskell/haddock#688, as mentioned in https://github.com/haskell/haddock/pull/766#issue-172505043. This PR fixes it. - - - - - e127e0ab by Ben Gamari at 2019-10-06T15:12:06-04:00 Fix a few haddock issues - - - - - 3a0f5c89 by Zubin Duggal at 2019-10-07T17:56:13-04:00 Fix crash when there are no srcspans in the file due to CPP - - - - - 339c5ff8 by Alec Theriault at 2019-10-07T17:56:13-04:00 Prefer un-hyperlinked sources to no sources It is possible to fail to extract an HIE ast. This is however not a reason to produce _no_ output - we should still make a colorized HTML page. - - - - - d47ef478 by Alec Theriault at 2019-10-07T17:56:13-04:00 Add a regression test for haskell/haddock#1091 Previously, this input would crash Haddock. - - - - - ed7c8b0f by Alec Theriault at 2019-10-07T20:56:48-04:00 Add Hyperlinker test cases for TH-related stuff Hopefully this will guard against regressions around quasiquotes, TH quotes, and TH splices. - - - - - d00436ab by Andreas Klebinger at 2019-10-21T15:53:03+02:00 Refactor for withTiming changes. - - - - - 4230e712 by Ben Gamari at 2019-10-22T09:36:37-04:00 Merge pull request haskell/haddock#1101 from AndreasPK/withTimingRefactor Refactor for withTiming changes. - - - - - d155c5f4 by Ryan Scott at 2019-10-23T10:37:17-04:00 Reify oversaturated data family instances correctly (#1103) This fixes haskell/haddock#1103 by adapting the corresponding patch for GHC (see https://gitlab.haskell.org/ghc/ghc/issues/17296 and https://gitlab.haskell.org/ghc/ghc/merge_requests/1877). - - - - - 331a5adf by Sebastian Graf at 2019-10-25T17:14:40+02:00 Refactor for OutputableBndrId changes - - - - - 48a490e0 by Ben Gamari at 2019-10-27T10:16:16-04:00 Merge pull request haskell/haddock#1105 from sgraf812/wip/flexible-outputable Refactor for OutputableBndrId changes - - - - - f62a7dfc by Sebastian Graf at 2019-11-01T11:54:16+00:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - d9b242ed by Ryan Scott at 2019-11-03T13:20:03-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. (cherry picked from commit cfd682c5fd03b099a3d78c44f9279faf56a0ac70) - - - - - dfd42406 by Sebastian Graf at 2019-11-04T07:02:14-05:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - 0b15be7c by Ben Gamari at 2019-11-09T13:21:33-05:00 Import isRuntimeRepVar from Type rather than TyCoRep isRuntimeRepVar is not longer exported from TyCoRep due to ghc#17441. - - - - - 091f7283 by Ben Gamari at 2019-11-10T12:47:06-05:00 Bump to GHC 8.10 - - - - - e88c71f2 by Ben Gamari at 2019-11-14T00:22:24-05:00 Merge pull request haskell/haddock#1110 from haskell/wip/T17441 Import isRuntimeRepVar from Type rather than TyCoRep - - - - - 4e0bbc17 by Ben Gamari at 2019-11-14T00:22:45-05:00 Version bumps for GHC 8.11 - - - - - 0e85ceb4 by Ben Gamari at 2019-11-15T11:59:45-05:00 Bump to GHC 8.10 - - - - - 00d6d68b by Ben Gamari at 2019-11-16T18:35:58-05:00 Bump ghc version to 8.11 - - - - - dde1fc3f by Ben Gamari at 2019-11-16T20:40:37-05:00 Drop support for base 4.13 - - - - - f52e331d by Vladislav Zavialov at 2019-11-24T13:02:28+03:00 Update Hyperlinker.Parser.classify to use ITdollar - - - - - 1ad96198 by Vladislav Zavialov at 2019-11-28T16:12:33+03:00 Remove HasSrcSpan (#17494) - - - - - 651afd70 by Herbert Valerio Riedel at 2019-12-08T12:08:16+01:00 Document error-prone conditional definition of instances This can easily trip up people if one isn't aware of it. Usually it's better to avoid this kind of conditionality especially for typeclasses for which there's an compat-package as conditional instances like these tend to fragment the ecosystem into those packages that go the extra mile to provide backward compat via those compat-packages and those that fail to do so. - - - - - b521af56 by Herbert Valerio Riedel at 2019-12-08T12:09:54+01:00 Fix build-failure regression for base < 4.7 The `$>` operator definition is available only since base-4.7 which unfortunately wasn't caught before release to Hackage (but has been fixed up by a metadata-revision) This commit introduces a `CompatPrelude` module which allows to reduce the amount of CPP by ousting it to a central location, i.e. the new `CompatPrelude` module. This pattern also tends to reduce the tricks needed to silence unused import warnings. Addresses haskell/haddock#1119 - - - - - 556c375d by Sylvain Henry at 2020-01-02T19:01:55+01:00 Fix after Iface modules renaming - - - - - bd6c53e5 by Sylvain Henry at 2020-01-07T00:48:48+01:00 hsyl20-modules-renamer - - - - - fb23713b by Ryan Scott at 2020-01-08T07:41:13-05:00 Changes for GHC#17608 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2372 - - - - - 4a4dd382 by Ryan Scott at 2020-01-25T08:08:26-05:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - e782a44d by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename PackageConfig into UnitInfo - - - - - ba3c9f05 by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename lookupPackage - - - - - ab37f9b3 by Ben Gamari at 2020-01-29T13:00:44-05:00 Merge pull request haskell/haddock#1125 from haskell/wip/T17566-take-two Changes for GHC#17566 - - - - - 3ebd5ae0 by Ryan Scott at 2020-01-31T05:56:50-05:00 Merge branch 'wip-hsyl20-package-refactor' into ghc-head - - - - - 602a747e by Richard Eisenberg at 2020-02-04T09:05:43+00:00 Echo GHC's removal of PlaceHolder module This goes with GHC's !2083. - - - - - ccfe5679 by Sylvain Henry at 2020-02-10T10:13:56+01:00 Module hierarchy: runtime (cf haskell/haddock#13009) - - - - - 554914ce by Cale Gibbard at 2020-02-10T16:10:39-05:00 Fix build of haddock in stage1 We have to use the correct version of the GHC API, but the version of the compiler itself doesn't matter. - - - - - 5b6fa2a7 by John Ericson at 2020-02-10T16:18:07-05:00 Noramlize `tested-with` fields in cabal files - - - - - e6eb3ebe by Vladislav Zavialov at 2020-02-16T13:25:26+03:00 No MonadFail/Alternative for P - - - - - 90e181f7 by Ben Gamari at 2020-02-18T14:13:47-05:00 Merge pull request haskell/haddock#1129 from obsidiansystems/wip/fix-stage1-build Fix build of haddock in stage1 - - - - - 93b64636 by Sylvain Henry at 2020-02-19T11:20:27+01:00 Modules: Driver (#13009) - - - - - da4f6c7b by Vladislav Zavialov at 2020-02-22T15:33:02+03:00 Use RealSrcSpan in InstMap - - - - - 479b1b50 by Ben Gamari at 2020-02-23T10:28:13-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 55ecacf0 by Sylvain Henry at 2020-02-25T15:18:27+01:00 Modules: Core (#13009) - - - - - 60867b3b by Vladislav Zavialov at 2020-02-28T15:53:52+03:00 Ignore the BufLoc/BufSpan added in GHC's !2516 - - - - - 1e5506d3 by Sylvain Henry at 2020-03-02T12:32:43+01:00 Modules: Core (#13009) - - - - - 6fb53177 by Richard Eisenberg at 2020-03-09T14:49:40+00:00 Changes in GHC's !1913. - - - - - 30b792ea by Ben Gamari at 2020-03-16T12:45:02-04:00 Merge pull request haskell/haddock#1130 from hsyl20/wip/hsyl20-modules-core2 Modules: Core (#13009) - - - - - cd761ffa by Sylvain Henry at 2020-03-18T15:24:00+01:00 Modules: Types - - - - - b6646486 by Ben Gamari at 2020-03-18T14:42:43-04:00 Merge pull request haskell/haddock#1133 from hsyl20/wip/hsyl20/modules/types Modules: Types - - - - - 9325d734 by Kleidukos at 2020-03-19T12:38:31-04:00 Replace the 'caption' class so that the collapsible sections are shown - - - - - 5e2bb555 by Kleidukos at 2020-03-19T12:38:31-04:00 Force ghc-8.8.3 - - - - - c6fcd0aa by Kleidukos at 2020-03-19T12:38:31-04:00 Update test fixtures - - - - - 5c849cb1 by Sylvain Henry at 2020-03-20T09:34:39+01:00 Modules: Types - - - - - 7f439155 by Alec Theriault at 2020-03-20T20:17:01-04:00 Merge branch 'ghc-8.8' into ghc-8.10 - - - - - b7904e5c by Alina Banerjee at 2020-03-20T20:24:17-04:00 Update parsing to strip whitespace from table cells (#1074) * Update parsing to strip leading & trailing whitespace from table cells * Update fixture data to disallow whitespaces at both ends in table cells * Add test case for whitespaces stripped from both ends of table cells * Update table reference test data for html tests - - - - - b9d60a59 by Alec Theriault at 2020-03-22T11:46:42-04:00 Clean up warnings * unused imports * imports of `Data.List` without import lists * missing `CompatPrelude` file in `.cabal` - - - - - 0c317dbe by Alec Theriault at 2020-03-22T18:46:54-04:00 Fix NPM security warnings This was done by calling `npm audit fix`. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. - - - - - 6e306242 by Alec Theriault at 2020-03-22T20:10:52-04:00 Tentative 2.24 release Adjusted changelogs and versions in `.cabal` files in preparation for the upcoming release bundled with GHC 8.10. - - - - - 1bfb4645 by Ben Gamari at 2020-03-23T16:40:54-04:00 Merge commit '3c2944c037263b426c4fe60a3424c27b852ea71c' into HEAD More changes from the GHC types module refactoring. - - - - - be8c6f3d by Alec Theriault at 2020-03-26T20:10:53-04:00 Update `.travis.yml` to work with GHC 8.10.1 * Regenerated the Travis file with `haskell-ci` * Beef up `.cabal` files with more `tested-with` information - - - - - b025a9c6 by Alec Theriault at 2020-03-26T20:10:53-04:00 Update README Removed some out of date links/info, added some more useful links. * badge to Hackage * update old trac link * `ghc-head` => `ghc-8.10` * `cabal new-*` is now `cabal v2-*` and it should Just Work * `--test-option='--accept'` is the way to accept testsuite output - - - - - 564d889a by Alec Theriault at 2020-03-27T20:34:33-04:00 Fix crash in `haddock-library` on unicode space Our quickcheck tests for `haddock-library` stumbled across an edge case input that was causing Haddock to crash: it was a unicode space character. The root cause of the crash is that we were implicitly assuming that if a space character was not " \t\f\v\r", it would have to be "\n". We fix this by instead defining horizontal space as: any space character that is not '\n'. Fixes haskell/haddock#1142 - - - - - 2d360ba1 by Alec Theriault at 2020-03-27T21:57:32-04:00 Disallow qualified uses of reserved identifiers This a GHC bug (https://gitlab.haskell.org/ghc/ghc/issues/14109) too, but it is a relatively easy fix in Haddock. Note that the fix must live in `haddock-api` instead of `haddock-library` because we can only really decide if an identifier is a reserved one by asking the GHC lexer. Fixes haskell/haddock#952 - - - - - 47ae22ed by Alec Theriault at 2020-03-28T13:36:25-04:00 Remove unused `Haddock.Utils` functions * removed functions in `Haddock.Utils` that were not used anywhere (or exported from the `haddock-api` package) * moved GHC-specific utils from `Haddock.Utils` to `Haddock.GhcUtils` - - - - - c0291245 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use TTG empty extensions to remove some `error`'s None of these error cases should ever have been reachable, so this is just a matter of leveraging the type system to assert this. * Use the `NoExtCon` and `noExtCon` to handle case matches for no extension constructors, instead of throwing an `error`. * Use the extension field of `HsSpliceTy` to ensure that this variant of `HsType` cannot exist in an `HsType DocNameI`. - - - - - 0aff8dc4 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use `unLoc`/`noLoc` from GHC instead of `unL`/`reL` * `unL` is already defined by GHC as `unLoc` * `reL` is already defined by GHC as `noLoc` (in a safer way too!) * Condense `setOutputDir` and add a about exporting from GHC Fixes haskell/haddock#978 - - - - - bf6f2fb7 by Alec Theriault at 2020-03-28T13:36:25-04:00 Cleanup up GHC flags in `.cabal` files * enable more useful warning flags in `haddock-api`, handle the new warnings generated * remove `-fwarn-tabs` (now we'd use `-Wtabs`, but this has been in `-Wall` for a while now) - - - - - c576fbf1 by Alec Theriault at 2020-03-28T13:36:25-04:00 `haddock-library` document header level Document the fact the header level is going to always be between 1 and 6 inclusive. Along the way, I also optimized the parsing code a bit. - - - - - 71bce0ee by Alec Theriault at 2020-03-28T14:26:27-04:00 Disallow links in section headers This is quite straightforward to implement, since we already had a function `docToHtmlNoAnchors` (which we used to generate the link in the sidebar "Contents"). This breaks test `Bug387`, but that test case has aged badly: we now automatically generate anchors for all headings, so manually adding an anchor in a section makes no sense. Nested anchors are, as pointed out in haskell/haddock#1054, disallowed by the HTML standard. Fixes haskell/haddock#1054 - - - - - b461b0ed by Sylvain Henry at 2020-03-30T10:34:23+02:00 Modules: type checker - - - - - cd8cd1ee by Ben Gamari at 2020-03-31T12:45:02-04:00 Merge pull request haskell/haddock#1152 from hsyl20/wip/hsyl20/modules/tc Module renaming - - - - - 5e8f8ea7 by Felix Yan at 2020-04-01T17:58:06-07:00 Allow QuickCheck 2.14 Builds fine and all tests pass. - - - - - dc6b1633 by Sylvain Henry at 2020-04-05T16:43:44+02:00 Module renaming: amend previous patch - - - - - eee2f4ae by Ryan Scott at 2020-04-05T09:04:43-07:00 Fix haskell/haddock#1050 by filtering out invisible AppTy arguments This makes the `synifyType` case for `AppTy` more intelligent by taking into consideration the visibilities of each `AppTy` argument and filtering out any invisible arguments, as they aren't intended to be displayed in the source code. (See haskell/haddock#1050 for an example of what can happen if you fail to filter these out.) Along the way, I noticed that a special `synifyType` case for `AppTy t1 (CoercionTy {})` could be consolidated with the case below it, so I took the opportunity to tidy this up. - - - - - 23eb99e8 by Ben Gamari at 2020-04-07T11:19:58-04:00 Merge pull request haskell/haddock#1154 from hsyl20/wip/hsyl20/modules/tc Module renaming: amend previous patch - - - - - 072d994d by Ryan Scott at 2020-04-07T19:32:47-04:00 Make NoExtCon fields strict These changes are a part of a fix for [GHC#17992](https://gitlab.haskell.org/ghc/ghc/issues/17992). - - - - - d8ebf6c8 by Ignat Insarov at 2020-04-09T21:15:01-04:00 Recode Doc to Json. (#1159) * Recode Doc to Json. * More descriptive field labels. - - - - - 52df4b4e by Sylvain Henry at 2020-04-10T12:39:18+02:00 Module renaming - - - - - d9ab8ec8 by Cale Gibbard at 2020-04-14T11:43:34-04:00 Add instance of XCollectPat for DocNameI - - - - - 323d221d by Cale Gibbard at 2020-04-14T11:43:34-04:00 Rename XCollectPat -> CollectPass - - - - - 2df80867 by Alec Theriault at 2020-04-15T07:30:51-07:00 Prune docstrings that are never rendered When first creating a Haddock interface, trim `ifaceDocMap` and `ifaceArgMap` to not include docstrings that can never appear in the final output. Besides checking with GHC which names are exported, we also need to keep all the docs attached to instance declarations (it is much tougher to detect when an instance is fully private). This change means: * slightly smaller interface files (7% reduction on boot libs) * slightly less work to do processing docstrings that aren't used * no warnings in Haddock's output about private docstrings (see haskell/haddock#1070) I've tested manually that this does not affect any of the boot library generated docs (the only change in output was some small re-ordering in a handful of instance lists). This should mean no docstrings have been incorrectly dropped. - - - - - f49c90cc by Alec Theriault at 2020-04-15T07:30:51-07:00 Don't warn about missing links in miminal sigs When renaming the Haddock interface, never emit warnings when renaming a minimal signature. Also added some documention around `renameInterface`. Minimal signatures intentionally include references to potentially un-exported methods (see the discussion in haskell/haddock#330), so it is expected that they will not always have a link destination. On the principle that warnings should always be resolvable, this shouldn't produce a warning. See haskell/haddock#1070. - - - - - a9eda64d by Ben Gamari at 2020-04-17T09:27:35-04:00 Merge pull request haskell/haddock#1160 from hsyl20/wip/hsyl20/modules/systools Module renaming - - - - - f40d7879 by Cale Gibbard at 2020-04-20T11:30:38-04:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ttg-con-pat - - - - - a50e7753 by Ben Gamari at 2020-04-20T11:36:10-04:00 Merge pull request haskell/haddock#1165 from obsidiansystems/wip/ttg-con-pat Trees that Grow refactor (GHC !2553) - - - - - 6a24795c by Alec Theriault at 2020-04-21T08:06:45-07:00 Fallback to `hiDecl` when `extractDecl` fails Sometimes, the declaration being exported is a subdecl (for instance, a record accessor getting exported at the top-level). For these cases, Haddock has to find a way to produce some synthetic sensible top-level declaration. This is done with `extractDecl`. As is shown by haskell/haddock#1067, this is sometimes impossible to do just at a syntactic level (for instance when the subdecl is re-exported). In these cases, the only sensible thing to do is to try to reify a declaration based on a GHC `TyThing` via `hiDecl`. - - - - - eee1a8b7 by Sylvain Henry at 2020-04-24T15:46:05+02:00 Module structure - - - - - 50b9259c by Iñaki at 2020-04-25T18:38:11-04:00 Add support for custom section anchors (#1179) This allows to have stable anchors for groups, even if the set of groups in the documentation is altered. The syntax for setting the anchor of a group is -- * Group name #desiredAnchor# Which will produce an html anchor of the form '#g:desiredAnchor' Co-authored-by: Iñaki García Etxebarria <git at inaki.blueleaf.cc> - - - - - 4003c97a by Ben Gamari at 2020-04-26T09:35:15-04:00 Merge pull request haskell/haddock#1166 from hsyl20/wip/hsyl20/modules/utils Module structure - - - - - 5206ab60 by Sylvain Henry at 2020-04-27T16:47:39+02:00 Renamed UnitInfo fields - - - - - c32c333b by Sylvain Henry at 2020-04-27T17:32:58+02:00 UnitId has been renamed into Unit - - - - - 3e87db64 by Sylvain Henry at 2020-04-27T17:36:00+02:00 Fix for GHC.Unit.* modules - - - - - ae3323a7 by Ben Gamari at 2020-04-29T12:36:37-04:00 Merge pull request haskell/haddock#1183 from hsyl20/wip/hsyl20/unitid Refactoring of Unit code - - - - - b105564a by Artem Pelenitsyn at 2020-05-03T08:14:10+01:00 add dependency on exceptions because GHC.Exception was boiled down (ghc haskell/haddock#18075) - - - - - 9857eff3 by Zubin Duggal at 2020-05-04T18:48:25+01:00 Atomic update of NameCache in readHieFile - - - - - 86bbb226 by Sylvain Henry at 2020-05-14T16:36:27+02:00 Fix after Config module renaming - - - - - a4bbdbc2 by Gert-Jan Bottu at 2020-05-15T22:09:44+02:00 Explicit Specificity Support for Haddock - - - - - 46199daf by Ben Gamari at 2020-05-19T09:59:56-04:00 Merge pull request haskell/haddock#1192 from hsyl20/hsyl20/modules-config Fix after Config module renaming - - - - - f9a9d2ba by Gert-Jan Bottu at 2020-05-20T16:48:38-04:00 Explicit Specificity Support for Haddock - - - - - 55c5b7ea by Ben Gamari at 2020-05-21T00:32:02-04:00 Merge commit 'a8d7e66da4dcc3b242103271875261604be42d6e' into ghc-head - - - - - a566557f by Cale Gibbard at 2020-05-21T16:02:06-04:00 isBootSummary now produces a result of type IsBootInterface - - - - - ea52f905 by Zubin Duggal at 2020-05-24T17:55:48+01:00 update for hiefile-typeclass-info - - - - - 49ba7a67 by Willem Van Onsem at 2020-05-25T12:23:01-04:00 Use floor over round to calculate the percentage (#1195) If we compile documentation where only a small fraction is undocumented, it is misleading to see 100% coverage - 99% is more intuitive. Fixes haskell/haddock#1194 - - - - - c025ebf1 by Ben Gamari at 2020-05-29T14:32:42-04:00 Merge pull request haskell/haddock#1185 from obsidiansystems/boot-disambig isBootSummary now produces a result of type IsBootInterface - - - - - 74ab9415 by Ben Gamari at 2020-05-29T20:23:39-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - b40be944 by Ben Gamari at 2020-06-03T17:02:31-04:00 testsuite: Update expected output for simplified subsumption - - - - - 624be71c by Ryan Scott at 2020-06-05T12:43:23-04:00 Changes for GHC#18191 See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3337. - - - - - fbd8f7ce by Sylvain Henry at 2020-06-08T15:31:47+02:00 Fix after unit refactoring - - - - - 743fda4d by Ben Gamari at 2020-06-09T12:09:58-04:00 Merge pull request haskell/haddock#1202 from hsyl20/wip/hsyl20/unitid-ii Fix after unit refactoring - - - - - d07a06a9 by Ryan Scott at 2020-06-13T07:16:55-04:00 Use HsForAllTelescope (GHC#18235) - - - - - 389bb60d by Ben Gamari at 2020-06-13T15:30:52-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - 7a377f5f by Ben Gamari at 2020-06-17T14:53:16-04:00 Merge pull request haskell/haddock#1199 from bgamari/wip/ghc-8.12 haddock: Bounds bumps for GHC 8.12 - - - - - 9fd9e586 by Krzysztof Gogolewski at 2020-06-17T16:09:07-04:00 Adapt Haddock to LinearTypes See ghc/ghc!852. - - - - - 46fe7636 by Ben Gamari at 2020-06-18T14:20:02-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 35a3c9e2 by Zubin Duggal at 2020-06-21T21:19:18+05:30 Use functions exported from HsToCore - - - - - 8abe3928 by Ben Gamari at 2020-06-24T13:53:39-04:00 Merge pull request haskell/haddock#1204 from wz1000/wip/haddock-hstocore Use functions exported from GHC.HsToCore.Docs - - - - - 22f2c937 by Matthías Páll Gissurarson at 2020-06-26T19:07:03+02:00 Adapt Haddock for QualifiedDo - - - - - 3f6208d7 by Vladislav Zavialov at 2020-06-28T14:28:16+03:00 Handle LexicalNegation's ITprefixminus - - - - - 03a19f41 by Sylvain Henry at 2020-07-02T09:37:38+02:00 Rename hsctarget into backend - - - - - ea17ff23 by Andreas Klebinger at 2020-07-02T17:44:18+02:00 Update for UniqFM changes. - - - - - 9872f2f3 by Ben Gamari at 2020-07-09T10:39:19-04:00 Merge pull request haskell/haddock#1209 from AndreasPK/wip/typed_uniqfm Update for UniqFM changes. - - - - - 68f7b668 by Krzysztof Gogolewski at 2020-07-12T18:16:57+02:00 Sync with GHC removing {-# CORE #-} pragma See ghc ticket haskell/haddock#18048 - - - - - eb372681 by Sylvain Henry at 2020-07-20T11:41:30+02:00 Rename hscTarget into backend - - - - - fb7f78bf by Ben Gamari at 2020-07-21T12:15:25-04:00 Merge pull request haskell/haddock#1214 from hsyl20/wip/hsyl20/hadrian/ncg Rename hscTarget into backend - - - - - 1e8f5b56 by Ben Gamari at 2020-07-23T09:11:50-04:00 Merge commit '904dce0cafe0a241dd3ef355775db47fc12f434d' into ghc-head - - - - - d8fd1775 by Zubin Duggal at 2020-07-23T18:46:40+05:30 Update for modular ping pong - - - - - 8416f872 by Ben Gamari at 2020-07-23T09:35:03-04:00 Merge pull request haskell/haddock#1200 from wz1000/wip/wz1000-modular-ping-pong Modular ping pong - - - - - a24a8577 by Ben Gamari at 2020-07-28T15:23:36-04:00 Bump GHC version to 9.0 - - - - - 6a51c9dd by Sylvain Henry at 2020-08-05T18:47:05+02:00 Fix after Outputable refactoring - - - - - c05e1c99 by Ben Gamari at 2020-08-10T14:41:41-04:00 Merge pull request haskell/haddock#1223 from hsyl20/wip/hsyl20/dynflags/exception Fix after Outputable refactoring - - - - - d964f15b by Sylvain Henry at 2020-08-12T11:58:49+02:00 Fix after HomeUnit - - - - - 8e6d5b23 by Ben Gamari at 2020-08-12T14:25:30-04:00 Merge pull request haskell/haddock#1225 from hsyl20/wip/hsyl20/plugins/homeunit Fix after HomeUnit - - - - - 8c7880fe by Sylvain Henry at 2020-08-17T14:13:29+02:00 Remove Ord FastString instance - - - - - 8ea410db by Alex Biehl at 2020-08-19T10:56:32+02:00 Another round of `npm audit fix` (#1228) This should shut down the warnings on Github. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. Last NPM dependency audit happend in d576b2327e2bc117f912fe0a9d595e9ae62614e0 Co-authored-by: Alex Biehl <alex.biehl at target.com> - - - - - 7af6e2a8 by Ben Gamari at 2020-08-31T13:59:34-04:00 Merge pull request haskell/haddock#1226 from hsyl20/wip/hsyl20/fs_ord Remove Ord FastString instance - - - - - ffbc8702 by Alan Zimmerman at 2020-09-07T21:47:41+01:00 Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - a93f1268 by Alan Zimmerman at 2020-09-07T23:11:38+01:00 Merge pull request haskell/haddock#1232 from haskell/wip/T18639-remove-generated-pragma, Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - 1f605d50 by Ben Gamari at 2020-09-14T18:30:01-04:00 Bump GHC version to 9.1 - - - - - 6599df62 by Vladislav Zavialov at 2020-09-18T14:05:15+03:00 Bump base upper bound to 4.16 - - - - - a01b3c43 by Ben Gamari at 2020-09-22T15:41:48-04:00 Update hypsrc-test for QuickLook This appears to be a spurious change. - - - - - e9cc6cac by Vladislav Zavialov at 2020-09-26T21:00:12+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 30e3ca7c by Sylvain Henry at 2020-09-29T11:18:32-04:00 Update for parser (#1234) - - - - - b172f3e3 by Vladislav Zavialov at 2020-09-30T01:01:30+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 0b9c08d3 by Sylvain Henry at 2020-09-30T11:02:33+02:00 Adapt to GHC parser changes - - - - - b9540b7a by Sylvain Henry at 2020-10-12T09:13:38-04:00 Don't pass the HomeUnitId (#1239) - - - - - 34762e80 by HaskellMouse at 2020-10-13T12:58:04+03:00 Changed tests due to unification of `Nat` and `Natural` in the follwing merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3583 - - - - - 256f86b6 by Vladislav Zavialov at 2020-10-15T10:48:03+03:00 Add whitespace in: map ($ v) - - - - - 4a3f711b by Alan Zimmerman at 2020-10-19T08:57:27+01:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled - - - - - 072cdd21 by Alan Zimmerman at 2020-10-21T14:48:28-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 9e09a445 by Alan Zimmerman at 2020-10-21T23:53:34-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 636d7de3 by Sylvain Henry at 2020-10-26T14:31:54-04:00 GHC.Driver.Types refactoring (#1242) - - - - - a597f000 by Ryan Scott at 2020-10-29T04:18:05-04:00 Adapt to the removal of Hs{Boxed,Constraint}Tuple See ghc/ghc!4097 and GHC#18723. - - - - - b96660fb by Ryan Scott at 2020-10-30T04:53:05-04:00 Adapt to HsConDecl{H98,GADT}Details split Needed for GHC#18844. - - - - - c287d82c by Ryan Scott at 2020-10-30T19:35:59-04:00 Adapt to HsOuterTyVarBndrs These changes accompany ghc/ghc!4107, which aims to be a fix for haskell/haddock#16762. - - - - - a34c31a1 by Ryan Scott at 2020-11-13T13:38:34-05:00 Adapt to splitPiTysInvisible being renamed to splitInvisPiTys This is a part of !4434, a fix for GHC#18939. - - - - - 66ea459d by Sylvain Henry at 2020-11-16T10:59:30+01:00 Fix after Plugins moved into HscEnv - - - - - 508556d8 by Ben Gamari at 2020-11-18T15:47:40-05:00 Merge pull request haskell/haddock#1253 from hsyl20/wip/hsyl20/plugins/hscenv Fix after Plugins moved into HscEnv - - - - - 620fec1a by Andreas Klebinger at 2020-11-24T20:51:59+01:00 Update for changes in GHC's Pretty - - - - - 01cc13ab by Richard Eisenberg at 2020-11-25T23:18:35-05:00 Avoid GHC#18932. - - - - - 8d29ba21 by Cale Gibbard at 2020-11-25T23:18:35-05:00 Add type arguments to PrefixCon - - - - - 414d5f87 by Sylvain Henry at 2020-11-30T17:06:04+01:00 DynFlags's unit fields moved to HscEnv - - - - - e356668c by Ben Gamari at 2020-11-30T11:11:37-05:00 Merge pull request haskell/haddock#1258 from hsyl20/wip/hsyl20/hscenv/unitstate Unit fields moved from DynFlags to HscEnv - - - - - 7cf552f1 by Ben Gamari at 2020-12-03T10:31:27-05:00 Merge pull request haskell/haddock#1257 from AndreasPK/wip/andreask/opt_dumps Update for changes in GHC's Pretty - - - - - fc0871c3 by Veronika Romashkina at 2020-12-08T16:35:33+01:00 Fix docs links from Darcs to GitHub in intro (#1262) - - - - - 7059e808 by Veronika Romashkina at 2020-12-08T16:36:16+01:00 Use gender neutral word in docs (#1260) - - - - - 1b16e5ee by Maximilian Tagher at 2020-12-08T16:40:03+01:00 Allow scrolling search results (#1235) Closes https://github.com/haskell/haddock/issues/1231 - - - - - 8a118c01 by dependabot[bot] at 2020-12-08T16:40:25+01:00 Bump bl from 1.2.2 to 1.2.3 in /haddock-api/resources/html (#1255) Bumps [bl](https://github.com/rvagg/bl) from 1.2.2 to 1.2.3. - [Release notes](https://github.com/rvagg/bl/releases) - [Commits](https://github.com/rvagg/bl/compare/v1.2.2...v1.2.3) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - c89ff587 by Xia Li-yao at 2020-12-08T16:42:17+01:00 Allow more characters in anchor following module reference (#1220) - - - - - 14af7d64 by Xia Li-yao at 2020-12-08T16:43:05+01:00 Add dangling changes from branches ghc-8.6 and ghc-8.8 (#1243) * Fix multiple typos and inconsistencies in doc/markup.rst Note: I noticed some overlap with haskell/haddock#1112 from @wygulmage and haskell/haddock#1081 from @parsonsmatt after creating these proposed changes - mea culpa for not looking at the open PRs sooner. * Fix haskell/haddock#1113 If no Signatures, no section of index.html * Change the formatting of missing link destinations The current formatting of the missing link destination does not really help user to understand the reasons of the missing link. To address this, I've changed the formatting in two ways: - the missing link symbol name is now fully qualified. This way you immediately know which haskell module cannot be linked. It is then easier to understand why this module does not have documentation (hidden module or broken documentation). - one line per missing link, that's more readable now that symbol name can be longer due to qualification. For example, before haddock was listing missing symbol such as: ``` could not find link destinations for: Word8 Word16 mapMaybe ``` Now it is listed as: ``` could not find link destinations for: - Data.Word.Word8 - Data.Word.Word16 - Data.Maybe.mapMaybe ``` * Add `--ignore-link-symbol` command line argument This argument can be used multiples time. A missing link to a symbol listed by `--ignore-link-symbol` won't trigger "missing link" warning. * Forbid spaces in anchors (#1148) * Improve error messages with context information (#1060) Co-authored-by: Matt Audesse <matt at mattaudesse.com> Co-authored-by: Mike Pilgrem <mpilgrem at users.noreply.github.com> Co-authored-by: Guillaume Bouchard <guillaume.bouchard at tweag.io> Co-authored-by: Pepe Iborra <pepeiborra at gmail.com> - - - - - 89e3af13 by tomjaguarpaw at 2020-12-08T18:00:04+01:00 Enable two warnings (#1245) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - c3320f8d by Willem Van Onsem at 2020-12-08T18:26:55+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 685df308 by Alex Biehl at 2020-12-08T20:06:26+01:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - be3ec3c0 by Alex Biehl at 2020-12-08T20:06:26+01:00 Import intercalate - - - - - 32c33912 by Matthías Páll Gissurarson at 2020-12-08T21:15:30+01:00 Adapt Haddock for QualifiedDo - - - - - 31696088 by Alex Biehl at 2020-12-08T22:06:02+01:00 Fix haddock-library tests - - - - - fbc0998a by Alex Biehl at 2020-12-08T23:08:23+01:00 Move to GitHub CI (#1266) * Initial version of ci.yml This is a straight copy from Dmitrii Kovanikov's blog post at https://kodimensional.dev/github-actions. Will adapt to haddock in successive commits. * Delete .travis.yml * Modify to only test on ghc-8.10.{1,2} * Use actions/setup-haskell at v1.1.4 * Relax QuickCheck bound on haddock-api * Remove stack matrix for now * Nail down to ghc-8.10 branch for now * Pin index state to 2020-12-08T20:13:44Z for now * Disable macOS and Windows tests for now for speed up - - - - - 5b946b9a by tomjaguarpaw at 2020-12-10T19:01:41+01:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - bc5a408f by dependabot[bot] at 2020-12-10T19:02:16+01:00 Bump ini from 1.3.5 to 1.3.7 in /haddock-api/resources/html (#1269) Bumps [ini](https://github.com/isaacs/ini) from 1.3.5 to 1.3.7. - [Release notes](https://github.com/isaacs/ini/releases) - [Commits](https://github.com/isaacs/ini/compare/v1.3.5...v1.3.7) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - d02995f1 by Andrew Martin at 2020-12-14T16:48:40-05:00 Update for boxed rep - - - - - a381aeff by Ben Gamari at 2020-12-15T15:13:30-05:00 Revert "Enable two warnings (#1245) (#1268)" As this does not build on GHC `master`. This reverts commit 7936692badfe38f23ae95b51fb7bd7c2ff7e9bce. - - - - - a63c0a9e by Ben Gamari at 2020-12-15T15:17:59-05:00 Revert "Update for boxed rep" This reverts commit 4ffb30d8b637ccebecc81ce610f0af451ac8088d. - - - - - 53bfbb29 by Ben Gamari at 2020-12-15T15:37:24-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - bae76a30 by Ben Gamari at 2020-12-16T02:44:42+00:00 Update output for nullary TyConApp optimisation (ghc/ghc!2952) - - - - - 4b733b57 by Krzysztof Gogolewski at 2020-12-16T20:03:14+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. - - - - - ee463bd3 by Ryan Scott at 2020-12-16T16:55:23-05:00 Adapt to HsCoreTy (formerly NewHsTypeX) becoming a type synonym Needed for !4417, the fix for GHC#15706 and GHC#18914. - - - - - ed0b02f8 by tomjaguarpaw at 2020-12-19T10:17:19+00:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - d80bf8f5 by Sylvain Henry at 2020-12-21T10:09:25+01:00 Fix after binder collect changes - - - - - bf4c9d32 by Adam Gundry at 2020-12-23T21:35:01+00:00 Adapt to changes to GlobalRdrElt and AvailInfo Needed for ghc/ghc!4467 - - - - - 37736c4c by John Ericson at 2020-12-28T12:27:02-05:00 Support a new ghc --make node type for parallel backpack upsweep - - - - - 717bdeac by Vladislav Zavialov at 2020-12-29T10:50:02+03:00 Inline and fix getGADTConTypeG The getGADTConTypeG used HsRecTy, which is at odds with GHC issue haskell/haddock#18782. I noticed that getGADTConTypeG was only used in the Hoogle backend. Interestingly, when handling H98 constructors, Hoogle converts RecCon to PrefixCon (see Haddock.Backends.Hoogle.ppCtor). So I changed getGADTConTypeG to handle RecConGADT in the same manner as PrefixConGADT, and after this simplification moved it into the 'where' clause of ppCtor, to the only place where it is used. The practical effect of this change is as follows. Consider this example: data TestH98 = T98 { bar::Int } data TestGADT where TG :: { foo :: Int } -> TestGADT Before this patch, haddock --hoogle used to produce: T98 :: Int -> TestH98 [TG] :: {foo :: Int} -> TestGADT Notice how the record syntax was discarded in T98 but not TG. With this patch, we always produce signatures without record syntax: T98 :: Int -> TestH98 [TG] :: Int -> TestGADT I suspect this might also be a bugfix, as currently Hoogle doesn't seem to render GADT record constructors properly. - - - - - cb1b8c56 by Andreas Abel at 2020-12-30T21:12:37+01:00 Build instructions: haddock-library and -api first! - - - - - b947f6ad by Ben Gamari at 2020-12-31T13:04:19-05:00 Merge pull request haskell/haddock#1281 from obsidiansystems/wip/backpack-j Changes to support -j with backpack - - - - - 120e1cfd by Hécate Moonlight at 2021-01-04T19:54:58+01:00 Merge pull request haskell/haddock#1282 from andreasabel/master Build instructions: haddock-library and -api first! - - - - - fd45e41a by Ben Gamari at 2021-01-05T16:14:31-05:00 Merge remote-tracking branch 'origin/ghc-8.10' into ghc-9.0 - - - - - b471bdec by Ben Gamari at 2021-01-05T16:23:02-05:00 Merge commit '1e56f63c3197e7ca1c1e506e083c2bad25d08793' into ghc-9.0 - - - - - 81cdbc41 by Alex Biehl at 2021-01-09T12:14:41+01:00 Prepare Haddock for being a GHC Plugin - - - - - b646d952 by Alex Biehl at 2021-01-09T12:14:41+01:00 Make Haddock a GHC Plugin - - - - - cc044674 by Alex Biehl at 2021-01-09T12:14:41+01:00 Add -j[n] CLI param to Haddock executable It translates to `--ghcopt=-j[n]` - - - - - 84a04073 by Alex Biehl at 2021-01-09T12:14:41+01:00 Abstract Monad for interface creation I found that when running as a plugin the lookupName function (which runs in Ghc monad) does not work correctly from the typeCheckResultAction hook. Instead, we abstracted the monad used when creating interfaces, so that access to GHC session specific parts is explicit and so that the TcM can provide their (correct) implementation of lookupName. - - - - - 5be2c4f7 by Alex Biehl at 2021-01-09T12:14:41+01:00 Accept tests - - - - - 8cefee9d by Alex Biehl at 2021-01-09T16:10:47+01:00 Add missing dependency for mtl - - - - - 3681f919 by Ben Gamari at 2021-01-13T18:39:25-05:00 Merge remote-tracking branch 'origin/ghc-9.0' into ghc-head - - - - - 33c6b152 by Hécate Moonlight at 2021-01-14T16:04:20+01:00 Merge pull request haskell/haddock#1273 from hsyl20/wip/hsyl20/arrows Fix after binder collect changes - - - - - 70d13e8e by Joachim Breitner at 2021-01-22T19:03:45+01:00 Make haddock more robust to changes to the `Language` data type With the introduction of GHC2021, the `Languages` data type in GHC will grow. In preparation of that (and to avoid changing haddock with each new language), this change makes the code handle extensions to that data type gracefully. (cherry picked from commit c341dd7c9c3fc5ebc83a2d577c5a726f3eb152a5) - - - - - 7d6dd57a by John Ericson at 2021-01-22T22:02:02+00:00 Add `NoGhcTc` instance now that it's not closed - - - - - e5fdaf0a by Alan Zimmerman at 2021-01-23T22:57:44+00:00 Merge pull request haskell/haddock#1293 from obsidiansystems/wip/fix-18936 Add `NoGhcTc` instance now that it's not closed - - - - - 989a1e05 by Oleg Grenrus at 2021-01-24T16:11:46+03:00 Add import list to Data.List - - - - - 368e144a by Ben Gamari at 2021-01-28T22:15:48+01:00 Adapt to "Make PatSyn immutable" - - - - - abe66c21 by Alfredo Di Napoli at 2021-02-01T08:05:35+01:00 Rename pprLogErrMsg to new name - - - - - e600e75c by Hécate Moonlight at 2021-02-05T14:53:00+01:00 Move CI to ghc-9.0 - - - - - dd492961 by Vladislav Zavialov at 2021-02-05T14:53:00+01:00 Update cabal.project and README build instructions - - - - - 31bd292a by Hécate Moonlight at 2021-02-05T15:03:56+01:00 Merge pull request haskell/haddock#1296 from Kleidukos/ghc-9.0 Merge the late additions to ghc-8.10 into ghc-9.0 - - - - - 6388989e by Vladislav Zavialov at 2021-02-05T17:41:57+03:00 Cleanup: fix build warnings - - - - - f99407ef by Daniel Rogozin at 2021-02-05T18:11:48+03:00 type level characters support for haddock (required for haskell/haddock#11342) - - - - - d8c6b26f by Hécate Moonlight at 2021-02-05T17:44:50+01:00 Add a CONTRIBUTING.md file - - - - - 6a01ad98 by Hécate Moonlight at 2021-02-05T17:58:16+01:00 Merge pull request haskell/haddock#1312 from Kleidukos/proper-branch-etiquette Add a CONTRIBUTING.md file - - - - - 955eecc4 by Vladislav Zavialov at 2021-02-05T20:29:00+03:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into ghc-head - - - - - 47b3d6ab by Hécate Moonlight at 2021-02-05T19:09:38+01:00 Amend the CONTRIBUTING.md file - - - - - 23de6137 by Hécate Moonlight at 2021-02-05T19:16:49+01:00 Merge pull request haskell/haddock#1313 from Kleidukos/amend-contributing Amend the CONTRIBUTING.md file - - - - - 69026b59 by Krzysztof Gogolewski at 2021-02-05T23:05:56+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. (cherry picked from commit b4b4d896d2d68d6c48e7db7bfe95c185ca0709cb) - - - - - ea026b78 by Oleg Grenrus at 2021-02-06T17:14:45+01:00 Add import list to Data.List - - - - - 5204326f by Hécate Moonlight at 2021-02-06T17:15:44+01:00 Merge pull request haskell/haddock#1316 from Kleidukos/explicit-imports-to-data-list Add import list to Data.List - - - - - 1f4d2136 by Ben Gamari at 2021-02-06T11:53:31-05:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ghc-head-merge - - - - - 13f0d09a by Ben Gamari at 2021-02-06T11:53:45-05:00 Fix partial record selector warning - - - - - 5c115f7e by Ben Gamari at 2021-02-06T11:55:52-05:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into wip/ghc-head-merge - - - - - b6fd8b75 by Ben Gamari at 2021-02-06T12:01:31-05:00 Merge commit '41964cb2fd54b5a10f8c0f28147015b7d5ad2c02' into wip/ghc-head-merge - - - - - a967194c by Ben Gamari at 2021-02-06T18:30:35-05:00 Merge branch 'wip/ghc-head-merge' into ghc-head - - - - - 1f4c3a91 by MorrowM at 2021-02-07T01:52:33+02:00 Fix search div not scrolling - - - - - 684b1287 by Iñaki García Etxebarria at 2021-02-07T16:13:04+01:00 Add support for labeled module references Support a markdown-style way of annotating module references. For instance -- | [label]("Module.Name#anchor") will create a link that points to the same place as the module reference "Module.Name#anchor" but the text displayed on the link will be "label". - - - - - bdb55a5d by Hécate Moonlight at 2021-02-07T16:18:10+01:00 Merge pull request haskell/haddock#1319 from alexbiehl/alex/compat Backward compat: Add support for labeled module references - - - - - 6ca70991 by Hécate Moonlight at 2021-02-07T16:21:29+01:00 Merge pull request haskell/haddock#1314 from tweag/show-linear-backport Backport haskell/haddock#1238 (linear types) to ghc-9.0 - - - - - d9d73298 by Alex Biehl at 2021-02-07T17:46:25+01:00 Remove dubious parseModLink Instead construct the ModLink value directly when parsing. - - - - - 33b4d020 by Hécate Moonlight at 2021-02-07T17:52:05+01:00 Merge pull request haskell/haddock#1320 from haskell/alex/fix Remove dubious parseModLink - - - - - 54211316 by Hécate Moonlight at 2021-02-07T18:12:07+01:00 Merge pull request haskell/haddock#1318 from MorrowM/ghc-9.0 Fix search div not scrolling - - - - - 19db679e by alexbiehl-gc at 2021-02-07T18:14:46+01:00 Merge pull request haskell/haddock#1317 from bgamari/wip/ghc-head-merge Merge ghc-8.10 into ghc-head - - - - - 6bc1e9e4 by Willem Van Onsem at 2021-02-07T18:25:30+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - c8537cf8 by alexbiehl-gc at 2021-02-07T18:30:40+01:00 Merge pull request haskell/haddock#1322 from haskell/alex/forward-port simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 2d47ae4e by alexbiehl-gc at 2021-02-07T18:39:59+01:00 Merge branch 'ghc-head' into ghc-9.0 - - - - - 849e4733 by Hécate Moonlight at 2021-02-07T18:43:19+01:00 Merge pull request haskell/haddock#1321 from Kleidukos/ghc-9.0 Merge ghc-9.0 into ghc-head - - - - - ee6095d7 by Sylvain Henry at 2021-02-08T11:36:38+01:00 Update for Logger - - - - - 4ad688c9 by Alex Biehl at 2021-02-08T18:11:24+01:00 Merge pull request haskell/haddock#1310 from hsyl20/wip/hsyl20/logger2 Logger refactoring - - - - - 922a9e0e by Ben Gamari at 2021-02-08T12:54:33-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - 991649d2 by Sylvain Henry at 2021-02-09T10:55:17+01:00 Fix to build with HEAD - - - - - a8348dc2 by Hécate Moonlight at 2021-02-09T10:58:51+01:00 Merge pull request haskell/haddock#1327 from hsyl20/wip/hsyl20/logger2 Fix to build with HEAD - - - - - 0abdbca6 by Fendor at 2021-02-09T20:06:15+01:00 Add UnitId to Target record - - - - - d5790a0e by Alex Biehl at 2021-02-11T10:32:32+01:00 Stable sort for (data/newtype) instances - - - - - 8e6036f5 by Alex Biehl at 2021-02-11T10:32:32+01:00 Also make TyLit deterministic - - - - - f76d2945 by Hécate Moonlight at 2021-02-11T11:00:31+01:00 Merge pull request haskell/haddock#1329 from hsyl20/hsyl20/stabe_iface Stable sort for instances - - - - - 5e0469ea by Oleg Grenrus at 2021-02-14T15:28:15+02:00 Add import list to Data.List in Haddock.Interface.Create - - - - - fa57cd24 by Hécate Moonlight at 2021-02-14T17:19:27+01:00 Merge pull request haskell/haddock#1331 from phadej/more-explicit-data-list-imports Add import list to Data.List in Haddock.Interface.Create - - - - - f0cd629c by Hécate Moonlight at 2021-02-21T00:22:01+01:00 Merge pull request haskell/haddock#1311 from fendor/wip/add-targetUnitId-to-target Add UnitId to Target record - - - - - 674ef723 by Joachim Breitner at 2021-02-22T10:39:18+01:00 html-test: Always set language from ghc-9.2 on, the “default” langauge of GHC is expected to change more wildly. To prepare for that (and unblock https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4853), this sets the language for all the test files to `Haskell2010`. This should insolate this test suite against changes to the default. Cherry-picked from https://github.com/haskell/haddock/pull/1341 - - - - - f072d623 by Hécate Moonlight at 2021-02-22T10:56:51+01:00 Merge pull request haskell/haddock#1342 from nomeata/joachim/haskell2010-in-tests-ghc-head html-test: Always set language - - - - - caebbfca by Hécate Moonlight at 2021-02-22T11:53:07+01:00 Clean-up of Interface and Interface.Create's imports and pragmata - - - - - f6caa89d by Hécate Moonlight at 2021-02-22T11:54:58+01:00 Merge pull request haskell/haddock#1345 from Kleidukos/head/fix-interface-imports [ghc-head] Clean-up of Interface and Interface.Create's imports and pragmata - - - - - 7395c9cb by Hécate Moonlight at 2021-02-22T18:44:57+01:00 Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 6e9fb5d5 by Hécate Moonlight at 2021-02-22T18:45:28+01:00 Merge pull request haskell/haddock#1348 from Kleidukos/head/explicit-imports-interface Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 9198b118 by Alan Zimmerman at 2021-02-22T20:04:24+00:00 Context becomes a Maybe in the GHC AST This prevents noLoc's appearing in the ParsedSource. Match the change in GHC. - - - - - 0af20f64 by Hécate Moonlight at 2021-02-23T12:36:12+01:00 Fix the call-site of guessTarget in Interface.hs Explicit the imports from GHC.HsToCore.Docs - - - - - b7886885 by Hécate Moonlight at 2021-02-23T12:37:54+01:00 Merge pull request haskell/haddock#1349 from Kleidukos/fix-interface-guesstarget-call Fix the call-site of guessTarget in Interface.hs - - - - - 9cf041ba by Sylvain Henry at 2021-02-24T11:08:20+01:00 Fix haddockHypsrcTest output in ghc-head - - - - - b194182a by Hécate Moonlight at 2021-02-24T11:12:36+01:00 Merge pull request haskell/haddock#1351 from hsyl20/wip/hsyl20/fix-head Fix haddockHypsrcTest output in ghc-head - - - - - 3ce8b375 by Shayne Fletcher at 2021-03-06T09:55:03-05:00 Add ITproj to parser - - - - - d2abf762 by Ben Gamari at 2021-03-06T19:26:49-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a0f6047d by Andrew Martin at 2021-03-07T11:25:23-05:00 Update for boxed rep - - - - - 6f63c99e by Ben Gamari at 2021-03-10T13:20:21-05:00 Update for "FastString: Use FastMutInt instead of IORef Int" - - - - - e13f01df by Luke Lau at 2021-03-10T15:38:40-05:00 Implement template-haskell's putDoc This catches up to GHC using the new extractTHDocs function, which returns documentation added via the putDoc function (provided it was compiled with Opt_Haddock). Since it's already a map from names -> docs, there's no need to do traversal etc. It also matches the change from the argument map being made an IntMap rather than a Map Int - - - - - 89263d94 by Alan Zimmerman at 2021-03-15T17:15:26+00:00 Match changes in GHC AST for in-tree API Annotations As landed via https://gitlab.haskell.org/ghc/ghc/-/merge_requests/2418 - - - - - 28db1934 by Alan Zimmerman at 2021-03-15T20:40:09+00:00 Change some type family test results. It is not clear to me whether the original was printing incorrectly (since we did not have the TopLevel flag before now), or if this behaviour is expected. For the time being I am assuming the former. - - - - - 7c11c989 by Sylvain Henry at 2021-03-22T10:05:19+01:00 Fix after NameCache changes - - - - - addbde15 by Sylvain Henry at 2021-03-22T10:05:19+01:00 NameCache doesn't store a UniqSupply anymore - - - - - 15ec6cec by Ben Gamari at 2021-03-22T17:53:44-04:00 Bump GHC version to 9.2 - - - - - dbd6aa63 by Hécate Moonlight at 2021-03-24T14:28:36+01:00 Merge pull request haskell/haddock#1365 from hsyl20/wip/hsyl20/iface1 NameCache refactoring - - - - - 2d32da7e by Oleg Grenrus at 2021-03-27T01:12:00+02:00 Specialization of Data.List - - - - - 32b84fa6 by Fendor at 2021-03-27T10:50:17+01:00 Add UnitId to Target record This way we always know to which home-unit a given target belongs to. So far, there only exists a single home-unit at a time, but it enables having multiple home-units at the same time. - - - - - 54bf9f0e by Hécate Moonlight at 2021-03-28T14:08:35+02:00 Merge pull request haskell/haddock#1368 from fendor/target-unit-id-revert Add UnitId to Target record - - - - - 7dea168a by Alan Zimmerman at 2021-03-29T08:45:52+01:00 EPA : Rename ApiAnn to EpAnn - - - - - 72967f65 by Alfredo Di Napoli at 2021-03-29T09:47:01+02:00 pprError changed name in GHC - - - - - 4bc61035 by Alan Zimmerman at 2021-03-29T16:16:27-04:00 EPA : Rename ApiAnn to EpAnn - - - - - 108d031d by Ben Gamari at 2021-03-29T18:49:36-04:00 Merge commit '36418c4f70d7d2b179a77925b3ad5caedb08c9b5' into HEAD - - - - - 1444f700 by Ben Gamari at 2021-03-31T09:18:39-04:00 Merge pull request haskell/haddock#1370 from adinapoli/wip/adinapoli-diag-reason-severity Rename pprError to mkParserErr - - - - - d3087b79 by Ben Gamari at 2021-03-31T11:34:17-04:00 Merge commit 'd8d8024ad6796549a8d3b5512dabf3288d14e30f' into ghc-head - - - - - 170b79e9 by Ben Gamari at 2021-03-31T12:24:56-04:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - db0d6bae by Ben Gamari at 2021-04-10T09:34:35-04:00 Bump GHC version to 9.3 - - - - - a9f2c421 by Alan Zimmerman at 2021-04-19T18:26:46-04:00 Update for EPA changes in GHC (cherry picked from commit cafb48118f7c111020663776845897e225607b41) - - - - - 1ee4b7c7 by Sylvain Henry at 2021-05-11T10:00:06+02:00 Removal of HsVersions.h (#1388) * Update for EPA changes in GHC * Account for HsVersions.h removal Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 79e819e9 by Hécate Moonlight at 2021-05-11T10:14:47+02:00 Revert "Removal of HsVersions.h (#1388)" This reverts commit 72118896464f94d81f10c52f5d9261efcacc57a6. - - - - - 3dbd3f8b by Alan Zimmerman at 2021-05-11T10:15:17+02:00 Update for EPA changes in GHC - - - - - 2ce80c17 by Sylvain Henry at 2021-05-11T10:15:19+02:00 Account for HsVersions.h removal - - - - - 00e4c918 by Christiaan Baaij at 2021-05-13T08:21:56+02:00 Add Haddock support for the OPAQUE pragma (#1380) - - - - - 8f9049b2 by Hécate Moonlight at 2021-05-13T08:40:22+02:00 fixup! Use GHC 9.2 in CI runner - - - - - 27ddec38 by Alan Zimmerman at 2021-05-13T22:51:20+01:00 EPA: match changes from GHC T19834 - - - - - f8a1d714 by Felix Yan at 2021-05-14T17:10:04+02:00 Allow hspec 2.8 (#1389) All tests are passing. - - - - - df44453b by Divam Narula at 2021-05-20T15:42:42+02:00 Update ref, the variables got renamed. (#1391) This is due to ghc/ghc!5555 which caused a change in ModDetails in case of NoBackend. Now the initModDetails is used to recreate the ModDetails from interface and in-memory ModDetails is not used. - - - - - e46bfc87 by Alan Zimmerman at 2021-05-20T19:05:09+01:00 Remove Maybe from HsQualTy Match changes in GHC for haskell/haddock#19845 - - - - - 79bd7b62 by Shayne Fletcher at 2021-05-22T08:20:39+10:00 FieldOcc: rename extFieldOcc to foExt - - - - - 6ed68c74 by Ben Gamari at 2021-05-21T22:29:30-04:00 Merge commit '3b6a8774bdb543dad59b2618458b07feab8a55e9' into ghc-head - - - - - f9a02d34 by Alfredo Di Napoli at 2021-05-24T13:53:00+02:00 New Parser diagnostics interface - - - - - 392807d0 by Ben Gamari at 2021-05-24T09:57:40-04:00 Merge pull request haskell/haddock#1394 from adinapoli/wip/adinapoli-align-ps-messages Align Haddock to use the new Parser diagnostics interface - - - - - 33023cd8 by Ben Gamari at 2021-05-24T11:19:16-04:00 Revert "Add Haddock support for the OPAQUE pragma (#1380)" This reverts commit a1337c599ef7720b0482a25c55f11794112496dc. The GHC patch associated with this change is not yet ready to be merged. - - - - - 8c005af7 by Ben Simms at 2021-05-28T07:56:20+02:00 CI configuration for ghc-head (#1395) - - - - - 1e947612 by Hécate Moonlight at 2021-05-28T12:27:35+02:00 Use GHC 9.2 in CI runner (#1378) - - - - - e6fa10ab by CGenie at 2021-05-31T09:02:13+02:00 Add page about common errors (#1396) * Update index.rst Common errors page * Create common-errors.rst * Update common-errors.rst * Use GHC 9.2 in CI runner (#1378) * [haddock-api] remove .hspec-failures Co-authored-by: Hécate Moonlight <Kleidukos at users.noreply.github.com> - - - - - abc72a8d by Sylvain Henry at 2021-06-01T10:02:06+02:00 Adapt Haddock to Logger and Parser changes (#1399) - - - - - 91373656 by Zubin Duggal at 2021-06-01T20:45:10+02:00 Update haddockHypSrc tests since we now compute slighly more type info (#1397) - - - - - ed712822 by Marcin Szamotulski at 2021-06-02T08:54:33+02:00 Added myself to contributors - - - - - 49fdbcb7 by Marcin Szamotulski at 2021-06-02T08:57:24+02:00 Document multi component support - - - - - 9ddc8d7d by Hécate Moonlight at 2021-06-02T09:35:55+02:00 Merge pull request haskell/haddock#1379 from coot/coot/document-multi-component-support Document multi component support - - - - - 585b5c5e by Ben Simms at 2021-06-02T19:46:54+02:00 Update CONTRIBUTING.md (#1402) - - - - - 1df4a605 by Ben Simms at 2021-06-02T19:47:14+02:00 Update CONTRIBUTING.md (#1403) - - - - - 58ea43d2 by sheaf at 2021-06-02T22:09:06+02:00 Update Haddock Bug873 to account for renaming - - - - - c5d0ab23 by Vladislav Zavialov at 2021-06-10T13:35:42+03:00 HsToken in FunTy, RecConGADT - - - - - 1ae2f40c by Hécate Moonlight at 2021-06-11T11:19:09+02:00 Update the CI badges - - - - - 6fdc4de2 by Sylvain Henry at 2021-06-28T19:21:17+02:00 Fix mkParserOpts (#1411) - - - - - 18201670 by Alfredo Di Napoli at 2021-07-05T07:55:12+02:00 Rename getErrorMessages Lexer import This commit renames the Lexer import in `Hyperlinker.Parser` from `getErrorMessages` to `getPsErrorMessages` to eliminate the ambiguity with the `getErrorMessages` function defined in `GHC.Types.Error`. - - - - - 23173ca3 by Ben Gamari at 2021-07-07T11:31:44-04:00 Merge pull request haskell/haddock#1413 from adinapoli/wip/adinapoli-issue-19920 Rename getErrorMessages Lexer import - - - - - b3dc4ed8 by Alan Zimmerman at 2021-07-28T22:30:59+01:00 EPA: match changes from GHC T19834 (cherry picked from commit 2fec1b44e0ee7e263286709aa528b4ecb99ac6c2) - - - - - 5f177278 by Ben Gamari at 2021-08-06T01:17:37-04:00 Merge commit '2a966c8ca37' into HEAD - - - - - cdd81d08 by Marcin Szamotulski at 2021-08-08T17:19:06+02:00 coot/multiple packages (ghc-9.2) (#1418) - - - - - be0d71f1 by Marcin Szamotulski at 2021-08-16T08:46:03+02:00 coot/multiple package (ghc-head) (#1419) * FromJSON class Aeson style FromJSON class with Parsec based json parser. * doc-index.json file for multiple packages When creating haddock summary page for multiple packages render doc-index.json file using contents of all found 'doc-index.json' files. * Render doc-index.json When rendering html, render doc-index.json file independently of maybe_index_url option. doc-index.json file is useful now even if maybe_index_url is not `Nothing`. * base url option New `Flag_BaseURL` which configures from where static files are loaded (--base-url). If given and not equal "." static files are not coppied, as this indicates that they are not read from the the directory where we'd copy them. The default value is ".". - - - - - 3b09dbdf by Hécate Moonlight at 2021-10-07T23:26:03+02:00 Update GHC 9.2 to latest pre-release in CI - - - - - 7ac55417 by Zubin Duggal at 2021-10-11T12:10:19+02:00 Enable Haddock tests in GHC windows CI (#1428) * testsuite: strip windows line endings for haddock * hyperlinker: Work around double escaping (#19236) * deterministic SCC - - - - - 1cb81f25 by Andrew Lelechenko at 2021-10-12T15:23:19+02:00 haddock-library does not depend on bytestring or transformers (#1426) - - - - - a890b9aa by sheaf at 2021-10-15T22:19:42+02:00 update haddockHypsrcTest for GHC MR !6705 (#1430) - - - - - 42a55c6c by Sylvain Henry at 2021-10-15T22:20:10+02:00 Fix after PkgQual refactoring (#1429) - - - - - 91659238 by Alan Zimmerman at 2021-10-28T18:57:10+01:00 Update for changes in GHC for branch wip/az/no-srcspan-anno-instances - - - - - acf23e60 by Vladislav Zavialov at 2021-11-05T02:09:47+03:00 Do not use forall as an identifier See GHC ticket haskell/haddock#20609 - - - - - c565db0e by Krzysztof Gogolewski at 2021-11-27T02:42:35+01:00 Update after NoExtCon -> DataConCantHappen rename - - - - - b5f55590 by Artem Pelenitsyn at 2021-11-27T11:14:17+01:00 fix CI for 9.2 (#1436) - - - - - 25cd621e by Matthew Pickering at 2021-12-02T11:46:54+00:00 Update html-test for Data.List revert - - - - - 1d5ff85f by malteneuss at 2021-12-15T07:56:55+01:00 Add hint about inline link issue (#1444) - - - - - 791fde81 by Sylvain Henry at 2021-12-16T09:29:51+01:00 Bump ghc-head (#1445) * Update after NoExtCon -> DataConCantHappen rename * Update html-test for Data.List revert * Fix for new Plugins datatype Co-authored-by: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 44236317 by Sylvain Henry at 2021-12-17T09:39:00+01:00 Fix for new Plugins datatype - - - - - 80ada0fa by Hécate Moonlight at 2021-12-17T17:28:48+01:00 Remove ghc-head workflow (#1446) Contributions of GHC glue code are now done on the GHC gitlab, not in the GitHub repo anymore. - - - - - 49e171cd by Matthew Pickering at 2021-12-28T09:47:09+00:00 Remove use of ExtendedModSummary - - - - - 0e91b5ea by askeblad at 2022-01-04T09:18:35+01:00 update URLs - - - - - 9f13c212 by Hécate Moonlight at 2022-02-25T10:19:46+01:00 Fix solver for GHC 9.2 - - - - - 386751a1 by Meng Weng Wong at 2022-02-25T19:19:11+01:00 IDoc link has bitrotted; replaced with web.archive.org cache. (#1454) - - - - - d877cbe6 by Hécate Moonlight at 2022-02-25T19:21:58+01:00 Fix haddock user guide (#1456) - - - - - cc47f036 by Andrew Lelechenko at 2022-03-04T17:29:36+01:00 Allow text-2.0 in haddock-library (#1459) - - - - - 7b3685a3 by malteneuss at 2022-03-07T19:27:24+01:00 Add multi-line style hint to style section (#1460) - - - - - c51088b8 by John Ericson at 2022-03-11T16:46:26+01:00 Fix CollectPass instance to match TTG refactor Companion to GHC !7614 (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7614) - - - - - b882195b by Vladislav Zavialov at 2022-03-14T20:32:30+01:00 Link to (~) - - - - - 877349b8 by Christiaan Baaij at 2022-03-16T09:20:43+01:00 Add Haddock support for the OPAQUE pragma - - - - - 0ea22721 by askeblad at 2022-03-16T09:44:27+01:00 typos (#1464) - - - - - a6d13da1 by Matthew Pickering at 2022-03-22T13:41:17+00:00 Minimum changes needed for compilation with hi-haddock With hi-haddock, of course there is a much large refactoring of haddock which could be achieved but that is left for a future patch which can implemented at any time independently of GHC. - - - - - e7ac9129 by Matthew Pickering at 2022-03-22T21:17:50+00:00 Update test output - - - - - 6d916214 by Matthew Pickering at 2022-03-24T15:06:26+00:00 Merge branch 'wip/opaque_pragma' into 'ghc-head' Add Haddock support for the OPAQUE pragma See merge request ghc/haddock!2 - - - - - 42208183 by Steve Hart at 2022-03-25T20:43:50+01:00 Fix CI (#1467) * CI: Reinstall GHC with docs CI tests were failing because the GHC preinstalled to the CI environment does not include documentation, which is required for running the Haddock tests. This commit causes the CI workflow to reinstall GHC with docs so that tests can succeed. - - - - - 9676fd79 by Steve Hart at 2022-03-25T21:33:34+01:00 Make links in Synopsis functional again (#1458) Commit e41c1cbe9f0476997eac7b4a3f17cbc6b2262faf added a call to e.preventDefault() when handling click events that reach a toggle element. This prevents the browser from following hyperlinks within the Synopsis section when they are clicked by a user. This commit restores functioning hyperlinks within the Synopsis section by removing the call to e.preventDefault(), as it does not appear to be necessary, and removing it increases the flexibility of the details-helper code. - - - - - d1edd637 by sheaf at 2022-04-01T12:02:02+02:00 Keep track of promotion ticks in HsOpTy Keeping track of promotion ticks in HsOpTy allows us to properly pretty-print promoted constructors such as lists. - - - - - 9dcb2dfc by Jakob Brünker at 2022-04-01T15:46:22+00:00 Add support for \cases See merge request ghc/ghc!7873 - - - - - b0412ee5 by askeblad at 2022-04-06T17:47:57+02:00 spelling errors (#1471) - - - - - 6b18829b by Vladislav Zavialov at 2022-04-06T18:53:58+02:00 Rename [] to List - - - - - 2d046691 by Vladislav Zavialov at 2022-04-07T20:25:54+03:00 HsToken ConDeclGADT con_dcolon - - - - - 90b43da4 by Steve Hart at 2022-04-12T13:29:46+02:00 Parse Markdown links at beginning of line within a paragraph (#1470) * Catch Markdown links at beginning of line within paragraph Per Issue haskell/haddock#774, Markdown links were being parsed as ordinary text when they occurred at the beginning of a line other than the first line of the paragraph. This occurred because the parser was not interpreting a left square bracket as a special character that could delimit special markup. A space character was considered a special character, so, if a space occurred at the beginning of the new line, then the parser would interpret the space by itself and then continue parsing, thereby catching the Markdown link. '\n' was not treated as a special character, so the parser did not catch a Markdown link that may have followed. Note that this will allow for Markdown links that are not surrounded by spaces. For example, the following text includes a Markdown link that will be parsed: Hello, world[label](url) This is consistent with how the parser handles other types of markup. * Remove obsolete documentation hint Commit 6b9aeafddf20efc65d3725c16e3fc43a20aac343 should eliminate the need for the workaround suggested in the documentation. - - - - - 5b08312d by Hécate Moonlight at 2022-04-12T13:36:38+02:00 Force ghc-9.2 in the cabal.project - - - - - 0d0ea349 by dependabot[bot] at 2022-04-12T13:57:41+02:00 Bump path-parse from 1.0.5 to 1.0.7 in /haddock-api/resources/html (#1469) Bumps [path-parse](https://github.com/jbgutierrez/path-parse) from 1.0.5 to 1.0.7. - [Release notes](https://github.com/jbgutierrez/path-parse/releases) - [Commits](https://github.com/jbgutierrez/path-parse/commits/v1.0.7) --- updated-dependencies: - dependency-name: path-parse dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 2b9fc65e by dependabot[bot] at 2022-04-12T13:57:54+02:00 Bump copy-props from 2.0.4 to 2.0.5 in /haddock-api/resources/html (#1468) Bumps [copy-props](https://github.com/gulpjs/copy-props) from 2.0.4 to 2.0.5. - [Release notes](https://github.com/gulpjs/copy-props/releases) - [Changelog](https://github.com/gulpjs/copy-props/blob/master/CHANGELOG.md) - [Commits](https://github.com/gulpjs/copy-props/compare/2.0.4...2.0.5) --- updated-dependencies: - dependency-name: copy-props dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - ea98a6fb by Ben Gamari at 2022-04-23T22:54:37-04:00 Update for GHC 9.4 - - - - - 9e11864f by Ben Gamari at 2022-04-25T16:24:31-04:00 Merge remote-tracking branch 'upstream/ghc-9.2' into ghc-head - - - - - f83cc506 by Ben Gamari at 2022-04-25T17:00:25-04:00 Bump ghc version to 9.5 - - - - - e01c2e7d by Ben Gamari at 2022-04-28T16:19:04-04:00 Revert "Bump ghc-head (#1445)" This reverts commit b29a78ef6926101338f62e84f456dac8659dc9d2. This should not have been merged. - - - - - a2b5ee8c by Ben Gamari at 2022-04-28T16:19:24-04:00 Merge commit '2627a86c' into ghc-head - - - - - 0c6fe4f9 by Ben Gamari at 2022-04-29T10:05:54-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-9.4 - - - - - b6e5cb0a by Ben Gamari at 2022-04-29T11:46:06-04:00 Revert "HsToken ConDeclGADT con_dcolon" This reverts commit 24208496649a02d5f87373052c430ea4a97842c5. - - - - - 15a62888 by Ben Gamari at 2022-04-29T15:12:55-04:00 Bump base upper bound - - - - - 165b9031 by Ben Gamari at 2022-04-29T23:58:38-04:00 Update test output - - - - - e0c3e5da by Phil de Joux at 2022-05-02T14:46:38+02:00 Add hlint action .hlint.yaml with ignores & CPP. (#1475) - - - - - ead1158d by Raphael Das Gupta at 2022-05-02T14:46:48+02:00 fix grammar in docs: "can the" → "can be" (#1477) - - - - - cff97944 by Ben Gamari at 2022-05-02T18:38:56-04:00 Allow base-4.17 - - - - - e4ecb201 by Phil de Joux at 2022-05-03T13:14:55+02:00 Remove unused imports that GHC warned about. (#1480) - - - - - 222890b1 by Phil de Joux at 2022-05-03T13:15:46+02:00 Follow hlint suggestion to remove redundant bang. (#1479) - - - - - 058b671f by Phil de Joux at 2022-05-03T13:34:04+02:00 Follow hlint, remove language pragmas in libs. (#1478) - - - - - 0a645049 by Ben Simms at 2022-05-03T14:19:24+02:00 Keep track of ordered list indexes and render them (#1407) * Keep track of ordered list indexes and render them * Rename some identifiers to clarify - - - - - f0433304 by Norman Ramsey at 2022-05-04T15:13:34-04:00 update for changes in GHC API - - - - - 3740cf71 by Emily Martins at 2022-05-06T18:23:48+02:00 Add link to the readthedocs in cabal description to show on hackage. (cherry picked from commit 52e2d40d47295c02d3181aac0c53028e730f1e3b) - - - - - 5d754f1e by Hécate Moonlight at 2022-05-06T18:44:57+02:00 remove Bug873 - - - - - 968fc267 by Hécate Moonlight at 2022-05-06T18:48:28+02:00 Ignore "Use second" HLint suggestion. It increases laziness. - - - - - 02d14e97 by Jade Lovelace at 2022-05-07T17:42:08+02:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` - - - - - b22b87ed by Artem Pelenitsyn at 2022-05-08T16:19:47+02:00 fix parsing trailing quotes in backticked identifiers (#1408) (#1483) - - - - - 80ae107b by Alex Biehl at 2022-05-08T16:37:16+02:00 Fix "Defined by not used" error (cherry picked from commit 6e02a620a26c3a44f98675dd1b93b08070c36c0a) - - - - - 4c838e84 by Hécate Moonlight at 2022-05-08T16:37:16+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - fc9827b4 by Hécate Moonlight at 2022-05-08T16:40:40+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - b153b555 by Xia Li-yao at 2022-05-20T17:52:42+02:00 Hide synopsis from search when hidden (#1486) Fix haskell/haddock#1451 - - - - - f3e38b85 by Marcin Szamotulski at 2022-05-21T23:32:31+02:00 Allow to hide interfaces when rendering multiple components (#1487) This is useful when one wishes to `--gen-contents` when rendering multiple components, but one does not want to render all modules. This is in particular useful when adding base package. - - - - - f942863b by Marcin Szamotulski at 2022-05-24T08:29:59+02:00 Check if doc-index.json exists before reading it (#1488) - - - - - 31e92982 by Marcin Szamotulski at 2022-05-25T16:22:13+02:00 Version bump 2.26.1 (#1489) * Version bump 2.26.1 We extended format accepted by `--read-interface` option, which requires updating the minor version. * Update documentation of --read-interface option - - - - - 7cc873e0 by sheaf at 2022-05-25T16:42:31+02:00 Updated HaddockHypsrcTest output for record update changes (MR !7981) - - - - - cd196942 by Marcin Szamotulski at 2022-05-25T20:28:47+02:00 Use visibility to decide which interfaces are included in quickjump (#1490) This is also consistent with how html index is build. See haskell/cabal#7669 for rationale behind this decision. - - - - - 00c713c5 by Hécate Moonlight at 2022-05-26T17:09:15+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 2f3039f1 by Hécate Moonlight at 2022-05-26T17:10:59+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 63a5650c by romes at 2022-05-31T12:43:22+01:00 TTG: Match new GHC AST - - - - - dd7d1617 by romes at 2022-06-02T16:11:00+01:00 Update for IE changes in !8228 - - - - - c23aaab7 by cydparser at 2022-06-06T08:48:14+02:00 Fix and improve CI (#1495) * Pin GHC version before creating the freeze file * Use newest action versions * Improve caching * Avoid unnecessarily reinstalling GHC * Use GHC 9.2.2 for CI Co-authored-by: Cyd Wise <cwise at tripshot.com> - - - - - c156fa77 by Hécate Moonlight at 2022-06-06T11:59:35+02:00 Add Mergify configuration (#1496) - - - - - 2dba4188 by Hécate Moonlight at 2022-06-06T16:12:50+02:00 Bump haddock's version in cabal file to 2.26.1 (#1497) - - - - - d7d4b8b9 by Marcin Szamotulski at 2022-06-07T06:09:40+00:00 Render module tree per package in the content page (#1492) * Render module tree per package in the content page When rendering content page for multiple packages it is useful to split the module tree per package. Package names in this patch are inferred from haddock's interface file names. * Write PackageInfo into interface file To keep interface file format backward compatible, instead of using `Binary` instance for `InterfaceFile` we introduce functions to serialise and deserialise, which depends on the interface file version. - - - - - 77765665 by Mike Pilgrem at 2022-06-12T21:57:19+01:00 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - b0e079b0 by mergify[bot] at 2022-06-13T11:49:37+00:00 Merge pull request haskell/haddock#1108 from mpilgrem/fix783 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - 6c0292b1 by Hécate Moonlight at 2022-06-21T17:21:08+02:00 Update the contribution guide - - - - - e413b9fa by dependabot[bot] at 2022-06-21T23:38:19+02:00 Bump shell-quote from 1.6.1 to 1.7.3 in /haddock-api/resources/html (#1500) Bumps [shell-quote](https://github.com/substack/node-shell-quote) from 1.6.1 to 1.7.3. - [Release notes](https://github.com/substack/node-shell-quote/releases) - [Changelog](https://github.com/substack/node-shell-quote/blob/master/CHANGELOG.md) - [Commits](https://github.com/substack/node-shell-quote/compare/1.6.1...1.7.3) --- updated-dependencies: - dependency-name: shell-quote dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 29d0ef70 by romes at 2022-07-06T11:29:39+02:00 TTG: AST Updates for !8308 - - - - - 1bae7c87 by Alan Zimmerman at 2022-07-06T22:50:43+01:00 Match GHC changes for T21805 This brings in a newtype for FieldLabelString - - - - - 6fe8b988 by Phil de Joux at 2022-07-16T20:54:26+00:00 Bump hlint version to 3.4.1, the version with counts. (#1503) Redo the counts available with the --default option. - - - - - 48fb43af by Phil de Joux at 2022-07-19T09:32:55+02:00 Follow hlint suggestion: unused LANGUAGE pragma. (#1504) * Follow hlint suggestion: unused LANGUAGE pragma. * Ignore within modules to pass linting and pass tests. - - - - - c1cf1fa7 by Phil de Joux at 2022-07-24T13:45:59+02:00 Follow hlint suggestion: redundant $. (#1505) * Follow hlint suggestion: redundant $. * Remove $ and surplus blank lines in Operators. - - - - - 74777eb2 by Jade Lovelace at 2022-07-29T11:02:41+01:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` (cherry picked from commit ab53ccf089ea703b767581ac14be0f6c78a7678a) - - - - - faa4cfcf by Hécate Moonlight at 2022-07-29T20:31:20+02:00 Merge pull request haskell/haddock#1516 from duog/9-4-backport-fix-hyperlinks Backport 9-4: Fix hyperlinks to external items and modules (#1482) - - - - - 5d2450f3 by Ben Gamari at 2022-08-05T17:41:15-04:00 Merge remote-tracking branch 'origin/ghc-9.4' - - - - - 63954f73 by Ben Gamari at 2022-08-05T19:08:36-04:00 Clean up build and testsuite for GHC 9.4 - - - - - d4568cb8 by Hécate Moonlight at 2022-08-05T19:10:49-04:00 Bump the versions - - - - - 505583a4 by Ben Gamari at 2022-08-06T13:58:27-04:00 Merge pull request haskell/haddock#1518 from bgamari/wip/ghc-9.4-merge Merge GHC 9.4 into `main` - - - - - 5706f6a4 by Ben Gamari at 2022-08-06T22:57:21-04:00 html-test: Testsuite changes for GHC 9.4.1 - - - - - 5f2a45a2 by Ben Gamari at 2022-08-15T14:33:05-04:00 doc: Fix a few minor ReST issues Sphinx was complaining about too-short title underlines. - - - - - 220e6410 by Ben Gamari at 2022-08-15T14:41:24-04:00 Merge branch 'main' into ghc-head - - - - - fbeb1b02 by Ben Gamari at 2022-08-15T14:45:16-04:00 Updates for GHC 9.5 - - - - - eee562eb by Vladislav Zavialov at 2022-08-15T14:46:13-04:00 HsToken ConDeclGADT con_dcolon - - - - - c5f073db by Ben Gamari at 2022-08-15T16:55:35-04:00 Updates for GHC 9.5 - - - - - 3f7ab242 by Vladislav Zavialov at 2022-08-15T16:55:35-04:00 HsToken ConDeclGADT con_dcolon - - - - - a18e473d by Ben Gamari at 2022-08-16T08:35:19-04:00 Merge branch 'wip/ghc-head-bump' into ghc-head - - - - - af0ff3a4 by M Farkas-Dyck at 2022-09-15T21:16:05+00:00 Disuse `mapLoc`. - - - - - a748fc38 by Matthew Farkas-Dyck at 2022-09-17T10:44:18+00:00 Scrub partiality about `NewOrData`. - - - - - 2758fb6c by John Ericson at 2022-09-18T03:27:37+02:00 Test output changed because of change to `base` Spooky, but I guess that is intended? - - - - - a7eec128 by Torsten Schmits at 2022-09-21T11:06:55+02:00 update tests for the move of tuples to GHC.Tuple.Prim - - - - - 461e7b9d by Ross Paterson at 2022-09-24T22:01:25+00:00 match implementation of GHC proposal haskell/haddock#106 (Define Kinds Without Promotion) - - - - - f7fd77ef by sheaf at 2022-10-17T14:53:01+02:00 Update Haddock for GHC MR !8563 (configuration of diagnostics) - - - - - 3d3e85ab by Vladislav Zavialov at 2022-10-22T23:04:06+03:00 Class layout info - - - - - cbde4cb0 by Simon Peyton Jones at 2022-10-25T23:19:18+01:00 Adapt to Constraint-vs-Type See haskell/haddock#21623 and !8750 - - - - - 7108ba96 by Tom Smeding at 2022-11-01T22:33:23+01:00 Remove outdated footnote about module re-exports The footnote is invalid with GHC 9.2.4 (and possibly earlier): the described behaviour in the main text works fine. - - - - - 206c6bc7 by Hécate Moonlight at 2022-11-01T23:00:46+01:00 Merge pull request haskell/haddock#1534 from tomsmeding/patch-1 - - - - - a57b4c4b by Andrew Lelechenko at 2022-11-21T00:39:52+00:00 Support mtl-2.3 - - - - - e9d62453 by Simon Peyton Jones at 2022-11-25T13:49:12+01:00 Track small API change in TyCon.hs - - - - - eb1c73f7 by Ben Gamari at 2022-12-07T08:46:21-05:00 Update for GhC 9.6 - - - - - 063268dd by Ben Gamari at 2022-12-07T11:26:32-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 4ca722fe by Ben Gamari at 2022-12-08T14:43:26-05:00 Bump bounds to accomodate base-4.18 - - - - - 340b7511 by Vladislav Zavialov at 2022-12-10T12:31:28+00:00 HsToken in HsAppKindTy - - - - - 946226ec by Ben Gamari at 2022-12-13T20:12:56-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - fd8faa66 by Ben Gamari at 2022-12-22T13:44:28-05:00 Bump GHC version to 9.7 - - - - - 2958aa9c by Ben Gamari at 2022-12-22T14:49:16-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 9e0fefd8 by Andrei Borzenkov at 2023-01-30T14:02:04+04:00 Rename () to Unit, Rename (,,...,,) to Tuple<n> - - - - - eb3968b5 by Ben Gamari at 2023-03-10T02:32:43-05:00 Bump versions for ghc-9.6 release - - - - - 4aeead36 by Adam Gundry at 2023-03-23T13:53:47+01:00 Adapt to warning categories changes - - - - - 642d8d60 by sheaf at 2023-03-29T13:35:56+02:00 Adapt to record field refactor This commit adapts to the changes in GHC MR !8686, which overhauls the treatment of record fields in the renamer, adding separate record field namespaces and entirely removing the GreName datatype. - - - - - ac8d4333 by doyougnu at 2023-03-29T11:11:44-04:00 Update UniqMap API - - - - - 7866fc86 by Ben Orchard at 2023-04-20T11:29:33+02:00 update classify with new tokens - - - - - ffcdd683 by Finley McIlwaine at 2023-04-24T09:36:18-06:00 Remove index-state - - - - - 05b70982 by Finley McIlwaine at 2023-04-26T08:16:31-06:00 `renameInterface` space leak fixes - Change logic for accumulation of names for which link warnings will be generated - Change handling of `--ignore-link-symbol` to allow qualified and unqualified names. Added to CHANGES.md - Some formatting changes and comments here and there - - - - - e5697d7c by Finley McIlwaine at 2023-04-27T18:46:36-06:00 Messy things - ghc-debug dependency and instrumentation - cabal.project custom with-compiler - hie.yaml files - traces and such - - - - - 0b8ef80b by Finley McIlwaine at 2023-05-02T18:08:52-06:00 Stop retaining GRE closures GRE closures should never be necessary to Haddock, so we never want to keep them on the heap. Despite that, they are retained by a lot of the data structures that Haddock makes use of. - Attempt to fix that situation by adding strictness to various computations and pruning the `ifaceInstances` field of `Interface` to a much thinner data type. - Removes the `ifaceFamInstances` field, as it was never used. - Move some of the attach instances types (e.g. `SimpleType`) to the types module - - - - - 8bda991b by Finley McIlwaine at 2023-05-08T16:07:51-06:00 Memory usage fixes - Refactor `ifaceDeclMap` to drastically reduce memory footprint. We no longer store all declarations associated with a given name, since we only cared to determine if the only declaration associated with a name was a value declaration. Change the `DeclMap` type to better reflect this. - Drop pre-renaming export items after the renaming step. Since the Hoogle backend used the pre-renamed export items, this isn't trivial. We now generate Hoogle output for exported declarations during the renaming step (if Hoogle output /should/ be generated), and store that with the renamed export item. - Slightly refactor Hoogle backend to handle the above change and allow for early generation of Hoogle output. - Remove the `ifaceRnDocMap` and `ifaceRnArgMap` fields of the `Interface` type, as they were never used. - Remove some unnecessary strictness - Remove a lot of dead code from `Syb` module - - - - - 1611ac0c by Finley McIlwaine at 2023-05-09T11:51:57-06:00 Unify ErrMsgM and IfM - Delete ErrMsgM, stop accumulating warnings in a writer - Make IfM a state monad, print warnings directly to stdout, move IfM type into types module - Drop ErrMsg = String synonym - Unset IORefs from plugin after they are read, preventing unnecessary retention of interfaces - - - - - 42d696ab by Finley McIlwaine at 2023-05-11T15:52:07-06:00 Thunk leak fixes The strictness introduced in this commit was motivated by observing thunk leaks in the eventlog2html output. - Refactor attach instances list comprehension to avoid large intermediate thunks - Refactor some HTML backend list comprehensions to avoid large intermediate thunks - Avoid thunks accumulating in documentation types or documentation parser - A lot of orphan NFData instances to allow us to force documentation values - - - - - 68561cf6 by Finley McIlwaine at 2023-05-11T17:02:10-06:00 Remove GHC debug dep - - - - - 10519e3d by Finley McIlwaine at 2023-05-15T12:40:48-06:00 Force HIE file path Removes a potential retainer of `ModSummary`s - - - - - 1e4a6ec6 by Finley McIlwaine at 2023-05-15T14:20:34-06:00 Re-add index-state, with-compiler, delete hie.yamls - - - - - a2363fe9 by Hécate Moonlight at 2023-05-15T22:45:16+02:00 Merge pull request haskell/haddock#1594 from FinleyMcIlwaine/finley/ghc-9.6-mem-fixes Reduce memory usage - - - - - e8a78383 by Finley McIlwaine at 2023-05-17T12:19:16-06:00 Merge branch ghc-9.6 into ghc-head - - - - - 22e25581 by Finley McIlwaine at 2023-05-17T12:20:23-06:00 Merge branch 'ghc-head' of gitlab.haskell.org:ghc/haddock into ghc-head - - - - - 41bbf0df by Bartłomiej Cieślar at 2023-05-24T08:57:58+02:00 changes to the WarningTxt cases Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - c686ba9b by Hécate Moonlight at 2023-06-01T14:03:02-06:00 Port the remains of Hi-Haddock - - - - - 9d8a85fd by Hécate Moonlight at 2023-06-01T14:03:06-06:00 Stdout for tests - - - - - 36331d07 by Finley McIlwaine at 2023-06-01T14:06:02-06:00 Formatting, organize imports - - - - - a06059b1 by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix empty context confusion in Convert module - - - - - 379346ae by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix associated type families in Hoogle output - - - - - fc6ea7ed by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix test refs Accept several changes in Hoogle tests: Pretty printing logic no longer prints the `(Proxy (Proxy (...))` chain in Bug806 with parentheses. Since this test was only meant to verify that line breaks do not occur, accept the change. `tyThingToLHsDecl` is called for class and data declarations, which ends up "synifying" the type variables and giving unlifted types kind signatures. As a result, type variables of kind `Type -> Type` are now printed with kind signatures in Hoogle output. This could be changed by manually drop kind signatures from class variables in the Hoogle backend if the behavior is deemed unacceptable. Sometimes subordinate declarations are exported separate from their parent declarations (e.g. record selectors). In this case, a type signature is cobbled together for the export item in `extractDecl`. Since this type signature is very manually constructed, it may lack kind signatures of decls constructed from `tyThingToLHsDecl`. An example of this is the `type-sigs` Hoogle test. Change `*` to `Type` in Hoogle test refs. I don't think this will break Hoogle behavior, since it appears to not consider type signatures in search. I have not fully verified this. - - - - - e14b7e58 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix LaTeX backend test refs Changes to GHC pretty printing code have resulted in some differences to Haddock's LaTeX output. - Type variables are printed explicitly quantified in the LinearTypes test - Wildcard types in type family equations are now printed numbered, e.g. _1 _2, in the TypeFamilies3 test - Combined signatures in DefaultSignatures test are now documented as separate signatures - - - - - 41b5b296 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and test source updates - Stop using kind `*` in html test sources - Add TypeOperators where necessary to avoid warnings and future errors - Rename some test modules to match their module names - - - - - c640e2a2 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix missing deprecation warnings on record fields `lookupOccEnv` was used to resolve `OccNames` with warnings attached, but it doesn't look in the record field namespace. Thus, if a record field had a warning attached, it would not resolve and the warning map would not include it. This commit fixes by using `lookupOccEnv_WithFields` instead. - - - - - fad0c462 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and some comments - - - - - 751fd023 by Finley McIlwaine at 2023-06-01T14:11:41-06:00 Accept HTML test diffs All diffs now boil down to the expected differences resulting from declarations being reified from TyThings in hi-haddock. Surface syntax now has much less control over the syntax used in the documentation. - - - - - d835c845 by Finley McIlwaine at 2023-06-01T14:11:45-06:00 Adapt to new load' type - - - - - dcf776c4 by Finley McIlwaine at 2023-06-01T14:13:13-06:00 Update mkWarningMap and moduleWarning - - - - - 8e8432fd by Finley McIlwaine at 2023-06-01T14:28:54-06:00 Revert load' changes - - - - - aeb2982c by Finley McIlwaine at 2023-06-01T14:40:24-06:00 Accept change to Instances test in html-test Link to Data.Tuple instead of GHC.Tuple.Prim - - - - - 8adfdbac by Finley McIlwaine at 2023-06-01T15:53:17-06:00 Reset ghc dep to ^>= 9.6 - - - - - 2b1ce93d by Finley McIlwaine at 2023-06-06T07:50:04-06:00 Update CHANGES.md, user guide, recomp avoidance * Add --trace-args flag for tracing arguments received to standard output * Avoid recompiling due to changes in optimization flags * Update users guide and changes.md - - - - - f3da6676 by Finley McIlwaine at 2023-06-06T14:12:56-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - bf36c467 by Matthew Pickering at 2023-06-07T10:16:09+01:00 Revert back to e16e20d592a6f5d9ed1af17b77fafd6495242345 Neither of these MRs are ready to land yet which causes issues with other MRs which are ready to land and need haddock changes. - - - - - 421510a9 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 atSign has no unicode variant Prior to this change, atSign was defined as follows: atSign unicode = text (if unicode then "@" else "@") Yes, this is the same symbol '\64' and not your font playing tricks on you. Now we define: atSign = char '@' Both the LaTeX and the Xhtml backend are updated accordingly. - - - - - 3785c276 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 LaTeX: fix printing of type variable bindings Consider this type signature: kindOf :: forall {k} (a :: k). Proxy a -> Proxy k Prior to this fix, the LaTeX backend rendered it like this: kindOf :: forall k a. Proxy a -> Proxy k Now we preserve explicit specificity and kind annotations. - - - - - 0febf3a8 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 Add support for invisible binders in type declarations - - - - - 13e33bb3 by Finley McIlwaine at 2023-06-08T07:51:59-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - 3e5340ce by Finley McIlwaine at 2023-06-08T07:54:27-06:00 Add note about stubdir to recompilation docs - - - - - db7e84dc by Finley at 2023-06-08T08:11:03-06:00 Merge pull request haskell/haddock#1597 from haskell/finley/hi-haddock-9.6 hi-haddock for ghc 9.6 - - - - - 4e085d17 by Finley McIlwaine at 2023-06-14T13:41:06-06:00 Replace SYB traversals - - - - - 7b39aec5 by Finley McIlwaine at 2023-06-14T14:20:17-06:00 Test ref accepts, remove unused HaddockClsInst - - - - - df9c2090 by Finley McIlwaine at 2023-06-15T08:02:51-06:00 Use batchMsg for progress reporting during load With hi-haddock as is, there is an awkward silence during the load operation. This commit makes haddock use the default `batchMsg` Messager for progress reporting, and makes the default GHC verbosity level 1, so the user can see what GHC is doing. - - - - - f23679a8 by Hécate Moonlight at 2023-06-15T20:31:53+02:00 Merge pull request haskell/haddock#1600 from haskell/finley/hi-haddock-optim - - - - - a7982192 by Finley McIlwaine at 2023-06-15T15:02:16-06:00 hi-haddock squashed - - - - - c34f0c8d by Finley McIlwaine at 2023-06-15T16:22:03-06:00 Merge remote-tracking branch 'origin/ghc-9.6' into finley/hi-haddock-squashed - - - - - 40452797 by Bartłomiej Cieślar at 2023-06-16T12:26:04+02:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - e58673bf by Ben Gamari at 2023-06-16T09:33:35-04:00 Bump GHC version to 9.8 - - - - - 74bdf972 by Ben Gamari at 2023-06-16T09:36:18-04:00 Merge commit 'fcaaad06770a26d35d4aafd65772dedadf17669c' into ghc-head - - - - - 418ee3dc by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Remove NFData SourceText, IfaceWarnings updates The NFData SourceText instance is now available in GHC Handle mod_iface mi_warns now being IfaceWarnings - - - - - 62f31380 by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Accept Instances.hs test output Due to ghc!10469. - - - - - a8f2fc0e by Ben Gamari at 2023-06-20T15:48:08-04:00 Test fixes for "Fix associated data family doc structure items" Associated data families were being given their own export DocStructureItems, which resulted in them being documented separately from their classes in haddocks. This commit fixes it. - - - - - cb1ac33e by Bartłomiej Cieślar at 2023-06-21T12:56:02-04:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - 9933e10b by Ben Gamari at 2023-06-21T12:56:02-04:00 Bump GHC version to 9.8 - - - - - fe8c18b6 by Ben Gamari at 2023-06-21T15:36:29-04:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - c61a0d5b by Ben Gamari at 2023-06-21T16:10:51-04:00 Bump GHC version to 9.9 - - - - - 0c2a756e by sheaf at 2023-07-07T13:45:12+02:00 Avoid incomplete record update in Haddock Hoogle This commit avoids running into an incomplete record update warning in the Hoogle backend of Haddock. This was only noticed now, because incomplete record updates were broken in GHC 9.6. Now that they are fixed, we have to avoid running into them! - - - - - 8e11630e by jade at 2023-07-10T16:58:40-04:00 Add a hint to enable ExplicitNamespaces for type operator imports (Fixes/Enhances #20007) As suggested in #20007 and implemented in !8895, trying to import type operators will suggest a fix to use the 'type' keyword, without considering whether ExplicitNamespaces is enabled. This patch will query whether ExplicitNamespaces is enabled and add a hint to suggest enabling ExplicitNamespaces if it isn't enabled, alongside the suggestion of adding the 'type' keyword. - - - - - 61b1932e by sheaf at 2023-07-10T16:59:26-04:00 tyThingLocalGREs: include all DataCons for RecFlds The GREInfo for a record field should include the collection of all the data constructors of the parent TyCon that have this record field. This information was being incorrectly computed in the tyThingLocalGREs function for a DataCon, as we were not taking into account other DataCons with the same parent TyCon. Fixes #23546 - - - - - e6627cbd by Alan Zimmerman at 2023-07-10T17:00:05-04:00 EPA: Simplify GHC/Parser.y comb3 A follow up to !10743 - - - - - ee20da34 by Andrew Lelechenko at 2023-07-10T17:01:01-04:00 Document that compareByteArrays# is available since ghc-prim-0.5.2.0 - - - - - 4926af7b by Matthew Pickering at 2023-07-10T17:01:38-04:00 Revert "Bump text submodule" This reverts commit d284470a77042e6bc17bdb0ab0d740011196958a. This commit requires that we bootstrap with ghc-9.4, which we do not require until #23195 has been completed. Subsequently this has broken nighty jobs such as the rocky8 job which in turn has broken nightly releases. - - - - - d1c92bf3 by Ben Gamari at 2023-07-11T08:07:02-04:00 compiler: Fingerprint more code generation flags Previously our recompilation check was quite inconsistent in its coverage of non-optimisation code generation flags. Specifically, we failed to account for most flags that would affect the behavior of generated code in ways that might affect the result of a program's execution (e.g. `-feager-blackholing`, `-fstrict-dicts`) Closes #23369. - - - - - eb623149 by Ben Gamari at 2023-07-11T08:07:02-04:00 compiler: Record original thunk info tables on stack Here we introduce a new code generation option, `-forig-thunk-info`, which ensures that an `stg_orig_thunk_info` frame is pushed before every update frame. This can be invaluable when debugging thunk cycles and similar. See Note [Original thunk info table frames] for details. Closes #23255. - - - - - 4731f44e by Jaro Reinders at 2023-07-11T08:07:40-04:00 Fix wrong MIN_VERSION_GLASGOW_HASKELL macros I forgot to change these after rebasing. - - - - - dd38aca9 by Andreas Schwab at 2023-07-11T13:55:56+00:00 Hadrian: enable GHCi support on riscv64 - - - - - 09a5c6cc by Josh Meredith at 2023-07-12T11:25:13-04:00 JavaScript: support unicode code points > 2^16 in toJSString using String.fromCodePoint (#23628) - - - - - 29fbbd4e by Matthew Pickering at 2023-07-12T11:25:49-04:00 Remove references to make build system in mk/build.mk Fixes #23636 - - - - - 630e3026 by sheaf at 2023-07-12T11:26:43-04:00 Valid hole fits: don't panic on a Given The function GHC.Tc.Errors.validHoleFits would end up panicking when encountering a Given constraint. To fix this, it suffices to filter out the Givens before continuing. Fixes #22684 - - - - - c39f279b by Matthew Pickering at 2023-07-12T23:18:38-04:00 Use deb10 for i386 bindists deb9 is now EOL so it's time to upgrade the i386 bindist to use deb10 Fixes #23585 - - - - - bf9b9de0 by Krzysztof Gogolewski at 2023-07-12T23:19:15-04:00 Fix #23567, a specializer bug Found by Simon in https://gitlab.haskell.org/ghc/ghc/-/issues/23567#note_507834 The testcase isn't ideal because it doesn't detect the bug in master, unless doNotUnbox is removed as in https://gitlab.haskell.org/ghc/ghc/-/issues/23567#note_507692. But I have confirmed that with that modification, it fails before and passes afterwards. - - - - - 84c1a4a2 by Bartłomiej Cieślar at 2023-07-12T23:20:08-04:00 Comments - - - - - b2846cb5 by Bartłomiej Cieślar at 2023-07-12T23:20:08-04:00 updates to comments - - - - - 2af23f0e by Bartłomiej Cieślar at 2023-07-12T23:20:08-04:00 changes - - - - - 6143838a by sheaf at 2023-07-13T08:02:17-04:00 Fix deprecation of record fields Commit 3f374399 inadvertently broke the deprecation/warning mechanism for record fields due to its introduction of record field namespaces. This patch ensures that, when a top-level deprecation is applied to an identifier, it applies to all the record fields as well. This is achieved by refactoring GHC.Rename.Env.lookupLocalTcNames, and GHC.Rename.Env.lookupBindGroupOcc, to not look up a fixed number of NameSpaces but to look up all NameSpaces and filter out the irrelevant ones. - - - - - 6fd8f566 by sheaf at 2023-07-13T08:02:17-04:00 Introduce greInfo, greParent These are simple helper functions that wrap the internal field names gre_info, gre_par. - - - - - 7f0a86ed by sheaf at 2023-07-13T08:02:17-04:00 Refactor lookupGRE_... functions This commit consolidates all the logic for looking up something in the Global Reader Environment into the single function lookupGRE. This allows us to declaratively specify all the different modes of looking up in the GlobalRdrEnv, and avoids manually passing around filtering functions as was the case in e.g. the function GHC.Rename.Env.lookupSubBndrOcc_helper. ------------------------- Metric Decrease: T8095 ------------------------- ------------------------- Metric Increase: T8095 ------------------------- - - - - - 5e951395 by Rodrigo Mesquita at 2023-07-13T08:02:54-04:00 configure: Drop DllWrap command We used to configure into settings a DllWrap command for windows builds and distributions, however, we no longer do, and dllwrap is effectively unused. This simplification is motivated in part by the larger toolchain-selection project (#19877, !9263) - - - - - e10556b6 by Teo Camarasu at 2023-07-14T16:28:46-04:00 base: fix haddock syntax in GHC.Profiling - - - - - 0f3fda81 by Matthew Pickering at 2023-07-14T16:29:23-04:00 Revert "CI: add JS release and debug builds, regen CI jobs" This reverts commit 59c5fe1d4b624423b1c37891710f2757bb58d6af. This commit added two duplicate jobs on all validate pipelines, so we are reverting for now whilst we work out what the best way forward is. Ticket #23618 - - - - - 54bca324 by Alan Zimmerman at 2023-07-15T03:23:26-04:00 EPA: Simplify GHC/Parser.y sLL Follow up to !10743 - - - - - c8863828 by sheaf at 2023-07-15T03:24:06-04:00 Configure: canonicalise PythonCmd on Windows This change makes PythonCmd resolve to a canonical absolute path on Windows, which prevents HLS getting confused (now that we have a build-time dependency on python). fixes #23652 - - - - - ca1e636a by Rodrigo Mesquita at 2023-07-15T03:24:42-04:00 Improve Note [Binder-swap during float-out] - - - - - cf86f3ec by Matthew Craven at 2023-07-16T01:42:09+02:00 Equality of forall-types is visibility aware This patch finally (I hope) nails the question of whether (forall a. ty) and (forall a -> ty) are `eqType`: they aren't! There is a long discussion in #22762, plus useful Notes: * Note [ForAllTy and type equality] in GHC.Core.TyCo.Compare * Note [Comparing visiblities] in GHC.Core.TyCo.Compare * Note [ForAllCo] in GHC.Core.TyCo.Rep It also establishes a helpful new invariant for ForAllCo, and ForAllTy, when the bound variable is a CoVar:in that case the visibility must be coreTyLamForAllTyFlag. All this is well documented in revised Notes. - - - - - 7f13acbf by Vladislav Zavialov at 2023-07-16T01:56:27-04:00 List and Tuple<n>: update documentation Add the missing changelog.md entries and @since-annotations. - - - - - 2afbddb0 by Andrei Borzenkov at 2023-07-16T10:21:24+04:00 Type patterns (#22478, #18986) Improved name resolution and type checking of type patterns in constructors: 1. HsTyPat: a new dedicated data type that represents type patterns in HsConPatDetails instead of reusing HsPatSigType 2. rnHsTyPat: a new function that renames a type pattern and collects its binders into three groups: - explicitly bound type variables, excluding locally bound variables - implicitly bound type variables from kind signatures (only if ScopedTypeVariables are enabled) - named wildcards (only from kind signatures) 2a. rnHsPatSigTypeBindingVars: removed in favour of rnHsTyPat 2b. rnImplcitTvBndrs: removed because no longer needed 3. collect_pat: updated to collect type variable binders from type patterns (this means that types and terms use the same infrastructure to detect conflicting bindings, unused variables and name shadowing) 3a. CollVarTyVarBinders: a new CollectFlag constructor that enables collection of type variables 4. tcHsTyPat: a new function that typechecks type patterns, capable of handling polymorphic kinds. See Note [Type patterns: binders and unifiers] Examples of code that is now accepted: f = \(P @a) -> \(P @a) -> ... -- triggers -Wname-shadowing g :: forall a. Proxy a -> ... g (P @a) = ... -- also triggers -Wname-shadowing h (P @($(TH.varT (TH.mkName "t")))) = ... -- t is bound at splice time j (P @(a :: (x,x))) = ... -- (x,x) is no longer rejected data T where MkT :: forall (f :: forall k. k -> Type). f Int -> f Maybe -> T k :: T -> () k (MkT @f (x :: f Int) (y :: f Maybe)) = () -- f :: forall k. k -> Type Examples of code that is rejected with better error messages: f (Left @a @a _) = ... -- new message: -- • Conflicting definitions for ‘a’ -- Bound at: Test.hs:1:11 -- Test.hs:1:14 Examples of code that is now rejected: {-# OPTIONS_GHC -Werror=unused-matches #-} f (P @a) = () -- Defined but not used: type variable ‘a’ - - - - - eb1a6ab1 by sheaf at 2023-07-16T09:20:45-04:00 Don't use substTyUnchecked in newMetaTyVar There were some comments that explained that we needed to use an unchecked substitution function because of issue #12931, but that has since been fixed, so we should be able to use substTy instead now. - - - - - c7bbad9a by sheaf at 2023-07-17T02:48:19-04:00 rnImports: var shouldn't import NoFldSelectors In an import declaration such as import M ( var ) the import of the variable "var" should **not** bring into scope record fields named "var" which are defined with NoFieldSelectors. Doing so can cause spurious "unused import" warnings, as reported in ticket #23557. Fixes #23557 - - - - - 1af2e773 by sheaf at 2023-07-17T02:48:19-04:00 Suggest similar names in imports This commit adds similar name suggestions when importing. For example module A where { spelling = 'o' } module B where { import B ( speling ) } will give rise to the error message: Module ‘A’ does not export ‘speling’. Suggested fix: Perhaps use ‘spelling’ This also provides hints when users try to import record fields defined with NoFieldSelectors. - - - - - 654fdb98 by Alan Zimmerman at 2023-07-17T02:48:55-04:00 EPA: Store leading AnnSemi for decllist in al_rest This simplifies the markAnnListA implementation in ExactPrint - - - - - 22565506 by sheaf at 2023-07-17T21:12:59-04:00 base: add COMPLETE pragma to BufferCodec PatSyn This implements CLC proposal #178, rectifying an oversight in the implementation of CLC proposal #134 which could lead to spurious pattern match warnings. https://github.com/haskell/core-libraries-committee/issues/178 https://github.com/haskell/core-libraries-committee/issues/134 - - - - - 860f6269 by sheaf at 2023-07-17T21:13:00-04:00 exactprint: silence incomplete record update warnings - - - - - df706de3 by sheaf at 2023-07-17T21:13:00-04:00 Re-instate -Wincomplete-record-updates Commit e74fc066 refactored the handling of record updates to use the HsExpanded mechanism. This meant that the pattern matching inherent to a record update was considered to be "generated code", and thus we stopped emitting "incomplete record update" warnings entirely. This commit changes the "data Origin = Source | Generated" datatype, adding a field to the Generated constructor to indicate whether we still want to perform pattern-match checking. We also have to do a bit of plumbing with HsCase, to record that the HsCase arose from an HsExpansion of a RecUpd, so that the error message continues to mention record updates as opposed to a generic "incomplete pattern matches in case" error. Finally, this patch also changes the way we handle inaccessible code warnings. Commit e74fc066 was also a regression in this regard, as we were emitting "inaccessible code" warnings for case statements spuriously generated when desugaring a record update (remember: the desugaring mechanism happens before typechecking; it thus can't take into account e.g. GADT information in order to decide which constructors to include in the RHS of the desugaring of the record update). We fix this by changing the mechanism through which we disable inaccessible code warnings: we now check whether we are in generated code in GHC.Tc.Utils.TcMType.newImplication in order to determine whether to emit inaccessible code warnings. Fixes #23520 Updates haddock submodule, to avoid incomplete record update warnings - - - - - 1d05971e by sheaf at 2023-07-17T21:13:00-04:00 Propagate long-distance information in do-notation The preceding commit re-enabled pattern-match checking inside record updates. This revealed that #21360 was in fact NOT fixed by e74fc066. This commit makes sure we correctly propagate long-distance information in do blocks, e.g. in ```haskell data T = A { fld :: Int } | B f :: T -> Maybe T f r = do a at A{} <- Just r Just $ case a of { A _ -> A 9 } ``` we need to propagate the fact that "a" is headed by the constructor "A" to see that the case expression "case a of { A _ -> A 9 }" cannot fail. Fixes #21360 - - - - - bea0e323 by sheaf at 2023-07-17T21:13:00-04:00 Skip PMC for boring patterns Some patterns introduce no new information to the pattern-match checker (such as plain variable or wildcard patterns). We can thus skip doing any pattern-match checking on them when the sole purpose for doing so was introducing new long-distance information. See Note [Boring patterns] in GHC.Hs.Pat. Doing this avoids regressing in performance now that we do additional pattern-match checking inside do notation. - - - - - ddcdd88c by Rodrigo Mesquita at 2023-07-17T21:13:36-04:00 Split GHC.Platform.ArchOS from ghc-boot into ghc-platform Split off the `GHC.Platform.ArchOS` module from the `ghc-boot` package into this reinstallable standalone package which abides by the PVP, in part motivated by the ongoing work on `ghc-toolchain` towards runtime retargetability. - - - - - b55a8ea7 by Sylvain Henry at 2023-07-17T21:14:27-04:00 JS: better implementation for plusWord64 (#23597) - - - - - 889c2bbb by sheaf at 2023-07-18T06:37:32-04:00 Do primop rep-poly checks when instantiating This patch changes how we perform representation-polymorphism checking for primops (and other wired-in Ids such as coerce). When instantiating the primop, we check whether each type variable is required to instantiated to a concrete type, and if so we create a new concrete metavariable (a ConcreteTv) instead of a simple MetaTv. (A little subtlety is the need to apply the substitution obtained from instantiating to the ConcreteTvOrigins, see Note [substConcreteTvOrigin] in GHC.Tc.Utils.TcMType.) This allows us to prevent representation-polymorphism in non-argument position, as that is required for some of these primops. We can also remove the logic in tcRemainingValArgs, except for the part concerning representation-polymorphic unlifted newtypes. The function has been renamed rejectRepPolyNewtypes; all it does now is reject unsaturated occurrences of representation-polymorphic newtype constructors when the representation of its argument isn't a concrete RuntimeRep (i.e. still a PHASE 1 FixedRuntimeRep check). The Note [Eta-expanding rep-poly unlifted newtypes] in GHC.Tc.Gen.Head gives more explanation about a possible path to PHASE 2, which would be in line with the treatment for primops taken in this patch. We also update the Core Lint check to handle this new framework. This means Core Lint now checks representation-polymorphism in continuation position like needed for catch#. Fixes #21906 ------------------------- Metric Increase: LargeRecord ------------------------- - - - - - 00648e5d by Krzysztof Gogolewski at 2023-07-18T06:38:10-04:00 Core Lint: distinguish let and letrec in locations Lint messages were saying "in the body of letrec" even for non-recursive let. I've also renamed BodyOfLetRec to BodyOfLet in stg, since there's no separate letrec. - - - - - 787bae96 by Krzysztof Gogolewski at 2023-07-18T06:38:50-04:00 Use extended literals when deriving Show This implements GHC proposal https://github.com/ghc-proposals/ghc-proposals/pull/596 Also add support for Int64# and Word64#; see testcase ShowPrim. - - - - - 257f1567 by Jaro Reinders at 2023-07-18T06:39:29-04:00 Add StgFromCore and StgCodeGen linting - - - - - 34d08a20 by Ben Gamari at 2023-07-19T03:33:22-04:00 Reg.Liveness: Strictness - - - - - c5deaa27 by Ben Gamari at 2023-07-19T03:33:22-04:00 Reg.Liveness: Don't repeatedly construct UniqSets - - - - - b947250b by Ben Gamari at 2023-07-19T03:33:22-04:00 compiler/Types: Ensure that fromList-type operations can fuse In #20740 I noticed that mkUniqSet does not fuse. In practice, allowing it to do so makes a considerable difference in allocations due to the backend. Metric Decrease: T12707 T13379 T3294 T4801 T5321FD T5321Fun T783 - - - - - 6c88c2ba by Sven Tennie at 2023-07-19T03:33:59-04:00 x86 Codegen: Implement MO_S_MulMayOflo for W16 - - - - - 5f1154e0 by Sven Tennie at 2023-07-19T03:33:59-04:00 x86 CodeGen: MO_S_MulMayOflo better error message for rep > W64 It's useful to see which value made the pattern match fail. (If it ever occurs.) - - - - - e8c9a95f by Sven Tennie at 2023-07-19T03:33:59-04:00 x86 CodeGen: Implement MO_S_MulMayOflo for W8 This case wasn't handled before. But, the test-primops test suite showed that it actually might appear. - - - - - a36f9dc9 by Sven Tennie at 2023-07-19T03:33:59-04:00 Add test for %mulmayoflo primop The test expects a perfect implementation with no false positives. - - - - - 38a36248 by Matthew Pickering at 2023-07-19T03:34:36-04:00 lint-ci-config: Generate jobs-metadata.json We also now save the jobs-metadata.json and jobs.yaml file as artifacts as: * It might be useful for someone who is modifying CI to copy jobs.yaml if they are having trouble regenerating locally. * jobs-metadata.json is very useful for downstream pipelines to work out the right job to download. Fixes #23654 - - - - - 1535a671 by Vladislav Zavialov at 2023-07-19T03:35:12-04:00 Initialize 9.10.1-notes.rst Create new release notes for the next GHC release (GHC 9.10) - - - - - 3bd4d5b5 by sheaf at 2023-07-19T03:35:53-04:00 Prioritise Parent when looking up class sub-binder When we look up children GlobalRdrElts of a given Parent, we sometimes would rather prioritise those GlobalRdrElts which have the right Parent, and sometimes prioritise those that have the right NameSpace: - in export lists, we should prioritise NameSpace - for class/instance binders, we should prioritise Parent See Note [childGREPriority] in GHC.Types.Name.Reader. fixes #23664 - - - - - 9c8fdda3 by Alan Zimmerman at 2023-07-19T03:36:29-04:00 EPA: Improve annotation management in getMonoBind Ensure the LHsDecl for a FunBind has the correct leading comments and trailing annotations. See the added note for details. - - - - - ff884b77 by Matthew Pickering at 2023-07-19T11:42:02+01:00 Remove unused files in .gitlab These were left over after 6078b429 - - - - - 29ef590c by Matthew Pickering at 2023-07-19T11:42:52+01:00 gen_ci: Add hie.yaml file This allows you to load `gen_ci.hs` into HLS, and now it is a huge module, that is quite useful. - - - - - 808b55cf by Matthew Pickering at 2023-07-19T12:24:41+01:00 ci: Make "fast-ci" the default validate configuration We are trying out a lighter weight validation pipeline where by default we just test on 5 platforms: * x86_64-deb10-slow-validate * windows * x86_64-fedora33-release * aarch64-darwin * aarch64-linux-deb10 In order to enable the "full" validation pipeline you can apply the `full-ci` label which will enable all the validation pipelines. All the validation jobs are still run on a marge batch. The goal is to reduce the overall CI capacity so that pipelines start faster for MRs and marge bot batches are faster. Fixes #23694 - - - - - 0b23db03 by Alan Zimmerman at 2023-07-20T05:28:47-04:00 EPA: Simplify GHC/Parser.y sL1 This is the next patch in a series simplifying location management in GHC/Parser.y This one simplifies sL1, to use the HasLoc instances introduced in !10743 (closed) - - - - - 3ece9856 by Ben Gamari at 2023-07-21T07:30:45-04:00 nativeGen: Explicitly set flags of text sections on Windows The binutils documentation (for COFF) claims, > If no flags are specified, the default flags depend upon the section > name. If the section name is not recognized, the default will be for the > section to be loaded and writable. We previously assumed that this would do the right thing for split sections (e.g. a section named `.text$foo` would be correctly inferred to be a text section). However, we have observed that this is not the case (at least under the clang toolchain used on Windows): when split-sections is enabled, text sections are treated by the assembler as data (matching the "default" behavior specified by the documentation). Avoid this by setting section flags explicitly. This should fix split sections on Windows. Fixes #22834. - - - - - db7f7240 by Ben Gamari at 2023-07-21T07:30:45-04:00 nativeGen: Set explicit section types on all platforms - - - - - b444c16f by Finley McIlwaine at 2023-07-21T07:31:28-04:00 Insert documentation into parsed signature modules Causes haddock comments in signature modules to be properly inserted into the AST (just as they are for regular modules) if the `-haddock` flag is given. Also adds a test that compares `-ddump-parsed-ast` output for a signature module to prevent further regressions. Fixes #23315 - - - - - f9b952a7 by Ben Gamari at 2023-07-21T11:58:05-04:00 Bump base bound to <4.20 For GHC 9.8. - - - - - c30cea53 by Ben Gamari at 2023-07-21T23:23:49-04:00 primops: Introduce unsafeThawByteArray# This addresses an odd asymmetry in the ByteArray# primops, which previously provided unsafeFreezeByteArray# but no corresponding thaw operation. Closes #22710 - - - - - 87f9bd47 by Ben Gamari at 2023-07-21T23:23:49-04:00 testsuite: Elaborate in interface stability README This discussion didn't make it into the original MR. - - - - - e4350b41 by Matthew Pickering at 2023-07-21T23:24:25-04:00 Allow users to override non-essential haddock options in a Flavour We now supply the non-essential options to haddock using the `extraArgs` field, which can be specified in a Flavour so that if an advanced user wants to change how documentation is generated then they can use something other than the `defaultHaddockExtraArgs`. This does have the potential to regress some packaging if a user has overridden `extraArgs` themselves, because now they also need to add the haddock options to extraArgs. This can easily be done by appending `defaultHaddockExtraArgs` to their extraArgs invocation but someone might not notice this behaviour has changed. In any case, I think passing the non-essential options in this manner is the right thing to do and matches what we do for the "ghc" builder, which by default doesn't pass any optmisation levels, and would likewise be very bad if someone didn't pass suitable `-O` levels for builds. Fixes #23625 - - - - - fc186b0c by Ilias Tsitsimpis at 2023-07-21T23:25:03-04:00 ghc-prim: Link against libatomic Commit b4d39adbb58 made 'hs_cmpxchg64()' available to all architectures. Unfortunately this made GHC to fail to build on armel, since armel needs libatomic to support atomic operations on 64-bit word sizes. Configure libraries/ghc-prim/ghc-prim.cabal to link against libatomic, the same way as we do in rts/rts.cabal. - - - - - 4f5538a8 by Matthew Pickering at 2023-07-21T23:25:39-04:00 simplifier: Correct InScopeSet in rule matching The in-scope set passedto the `exprIsLambda_maybe` call lacked all the in-scope binders. @simonpj suggests this fix where we augment the in-scope set with the free variables of expression which fixes this failure mode in quite a direct way. Fixes #23630 - - - - - 5ad8d597 by Krzysztof Gogolewski at 2023-07-21T23:26:17-04:00 Add a test for #23413 It was fixed by commit e1590ddc661d6: Add the SolverStage monad. - - - - - 7e05f6df by sheaf at 2023-07-21T23:26:56-04:00 Finish migration of diagnostics in GHC.Tc.Validity This patch finishes migrating the error messages in GHC.Tc.Validity to use the new diagnostic infrastructure. It also refactors the error message datatypes for class and family instances, to common them up under a single datatype as much as possible. - - - - - 4876fddc by Matthew Pickering at 2023-07-21T23:27:33-04:00 ci: Enable some more jobs to run in a marge batch In !10907 I made the majority of jobs not run on a validate pipeline but then forgot to renable a select few jobs on the marge batch MR. - - - - - 026991d7 by Jens Petersen at 2023-07-21T23:28:13-04:00 user_guide/flags.py: python-3.12 no longer includes distutils packaging.version seems able to handle this fine - - - - - b91bbc2b by Matthew Pickering at 2023-07-21T23:28:50-04:00 ci: Mention ~full-ci label in MR template We mention that if you need a full validation pipeline then you can apply the ~full-ci label to your MR in order to test against the full validation pipeline (like we do for marge). - - - - - 42b05e9b by sheaf at 2023-07-22T12:36:00-04:00 RTS: declare setKeepCAFs symbol Commit 08ba8720 failed to declare the dependency of keepCAFsForGHCi on the symbol setKeepCAFs in the RTS, which led to undefined symbol errors on Windows, as exhibited by the testcase frontend001. Thanks to Moritz Angermann and Ryan Scott for the diagnosis and fix. Fixes #22961 - - - - - a72015d6 by sheaf at 2023-07-22T12:36:01-04:00 Mark plugins-external as broken on Windows This test is broken on Windows, so we explicitly mark it as such now that we stop skipping plugin tests on Windows. - - - - - cb9c93d7 by sheaf at 2023-07-22T12:36:01-04:00 Stop marking plugin tests as fragile on Windows Now that b2bb3e62 has landed we are in a better situation with regards to plugins on Windows, allowing us to unmark many plugin tests as fragile. Fixes #16405 - - - - - a7349217 by Krzysztof Gogolewski at 2023-07-22T12:36:37-04:00 Misc cleanup - Remove unused RDR names - Fix typos in comments - Deriving: simplify boxConTbl and remove unused litConTbl - chmod -x GHC/Exts.hs, this seems accidental - - - - - 33b6850a by Vladislav Zavialov at 2023-07-23T10:27:37-04:00 Visible forall in types of terms: Part 1 (#22326) This patch implements part 1 of GHC Proposal #281, introducing explicit `type` patterns and `type` arguments. Summary of the changes: 1. New extension flag: RequiredTypeArguments 2. New user-facing syntax: `type p` patterns (represented by EmbTyPat) `type e` expressions (represented by HsEmbTy) 3. Functions with required type arguments (visible forall) can now be defined and applied: idv :: forall a -> a -> a -- signature (relevant change: checkVdqOK in GHC/Tc/Validity.hs) idv (type a) (x :: a) = x -- definition (relevant change: tcPats in GHC/Tc/Gen/Pat.hs) x = idv (type Int) 42 -- usage (relevant change: tcInstFun in GHC/Tc/Gen/App.hs) 4. template-haskell support: TH.TypeE corresponds to HsEmbTy TH.TypeP corresponds to EmbTyPat 5. Test cases and a new User's Guide section Changes *not* included here are the t2t (term-to-type) transformation and term variable capture; those belong to part 2. - - - - - 73b5c7ce by sheaf at 2023-07-23T10:28:18-04:00 Add test for #22424 This is a simple Template Haskell test in which we refer to record selectors by their exact Names, in two different ways. Fixes #22424 - - - - - 83cbc672 by Ben Gamari at 2023-07-24T07:40:49+00:00 ghc-toolchain: Initial commit - - - - - 31dcd26c by Rodrigo Mesquita at 2023-07-24T07:40:49+00:00 ghc-toolchain: Toolchain Selection This commit integrates ghc-toolchain, the brand new way of configuring toolchains for GHC, with the Hadrian build system, with configure, and extends and improves the first iteration of ghc-toolchain. The general overview is * We introduce a program invoked `ghc-toolchain --triple=...` which, when run, produces a file with a `Target`. A `GHC.Toolchain.Target.Target` describes the properties of a target and the toolchain (executables and configured flags) to produce code for that target * Hadrian was modified to read Target files, and will both * Invoke the toolchain configured in the Target file as needed * Produce a `settings` file for GHC based on the Target file for that stage * `./configure` will invoke ghc-toolchain to generate target files, but it will also generate target files based on the flags configure itself configured (through `.in` files that are substituted) * By default, the Targets generated by configure are still (for now) the ones used by Hadrian * But we additionally validate the Target files generated by ghc-toolchain against the ones generated by configure, to get a head start on catching configuration bugs before we transition completely. * When we make that transition, we will want to drop a lot of the toolchain configuration logic from configure, but keep it otherwise. * For each compiler stage we should have 1 target file (up to a stage compiler we can't run in our machine) * We just have a HOST target file, which we use as the target for stage0 * And a TARGET target file, which we use for stage1 (and later stages, if not cross compiling) * Note there is no BUILD target file, because we only support cross compilation where BUILD=HOST * (for more details on cross-compilation see discussion on !9263) See also * Note [How we configure the bundled windows toolchain] * Note [ghc-toolchain consistency checking] * Note [ghc-toolchain overview] Ticket: #19877 MR: !9263 - - - - - a732b6d3 by Rodrigo Mesquita at 2023-07-24T07:40:49+00:00 Add flag to enable/disable ghc-toolchain based configurations This flag is disabled by default, and we'll use the configure-generated-toolchains by default until we remove the toolchain configuration logic from configure. - - - - - 61eea240 by Rodrigo Mesquita at 2023-07-24T07:40:49+00:00 Split ghc-toolchain executable to new packge In light of #23690, we split the ghc-toolchain executable out of the library package to be able to ship it in the bindist using Hadrian. Ideally, we eventually revert this commit. - - - - - 38e795ff by Rodrigo Mesquita at 2023-07-24T07:40:49+00:00 Ship ghc-toolchain in the bindist Add the ghc-toolchain binary to the binary distribution we ship to users, and teach the bindist configure to use the existing ghc-toolchain. - - - - - 32cae784 by Matthew Craven at 2023-07-24T16:48:24-04:00 Kill off gen_bytearray_addr_access_ops.py The relevant primop descriptions are now generated directly by genprimopcode. This makes progress toward fixing #23490, but it is not a complete fix since there is more than one way in which cabal-reinstall (hadrian/build build-cabal) is broken. - - - - - 02e6a6ce by Matthew Pickering at 2023-07-24T16:49:00-04:00 compiler: Remove unused `containers.h` include Fixes #23712 - - - - - 822ef66b by Matthew Pickering at 2023-07-25T08:44:50-04:00 Fix pretty printing of WARNING pragmas There is still something quite unsavoury going on with WARNING pragma printing because the printing relies on the fact that for decl deprecations the SourceText of WarningTxt is empty. However, I let that lion sleep and just fixed things directly. Fixes #23465 - - - - - e7b38ede by Matthew Pickering at 2023-07-25T08:45:28-04:00 ci-images: Bump to commit which has 9.6 image The test-bootstrap job has been failing for 9.6 because we accidentally used a non-master commit. - - - - - bb408936 by Matthew Pickering at 2023-07-25T08:45:28-04:00 Update bootstrap plans for 9.6.2 and 9.4.5 - - - - - 355e1792 by Alan Zimmerman at 2023-07-26T10:17:32-04:00 EPA: Simplify GHC/Parser.y comb4/comb5 Use the HasLoc instance from Ast.hs to allow comb4/comb5 to work with anything with a SrcSpan Also get rid of some more now unnecessary reLoc calls. - - - - - 9393df83 by Gavin Zhao at 2023-07-26T10:18:16-04:00 compiler: make -ddump-asm work with wasm backend NCG Fixes #23503. Now the `-ddump-asm` flag is respected in the wasm backend NCG, so developers can directly view the generated ASM instead of needing to pass `-S` or `-keep-tmp-files` and manually find & open the assembly file. Ideally, we should be able to output the assembly files in smaller chunks like in other NCG backends. This would also make dumping assembly stats easier. However, this would require a large refactoring, so for short-term debugging purposes I think the current approach works fine. Signed-off-by: Gavin Zhao <git at gzgz.dev> - - - - - 79463036 by Krzysztof Gogolewski at 2023-07-26T10:18:54-04:00 llvm: Restore accidentally deleted code in 0fc5cb97 Fixes #23711 - - - - - 20db7e26 by Rodrigo Mesquita at 2023-07-26T10:19:33-04:00 configure: Default missing options to False when preparing ghc-toolchain Targets This commit fixes building ghc with 9.2 as the boostrap compiler. The ghc-toolchain patch assumed all _STAGE0 options were available, and forgot to account for this missing information in 9.2. Ghc 9.2 does not have in settings whether ar supports -l, hence can't report it with --info (unliked 9.4 upwards). The fix is to default the missing information (we default "ar supports -l" and other missing options to False) - - - - - fac9e84e by Naïm Favier at 2023-07-26T10:20:16-04:00 docs: Fix typo - - - - - 503fd647 by Bartłomiej Cieślar at 2023-07-26T17:23:10-04:00 This MR is an implementation of the proposal #516. It adds a warning -Wincomplete-record-selectors for usages of a record field access function (either a record selector or getField @"rec"), while trying to silence the warning whenever it can be sure that a constructor without the record field would not be invoked (which would otherwise cause the program to fail). For example: data T = T1 | T2 {x :: Bool} f a = x a -- this would throw an error g T1 = True g a = x a -- this would not throw an error h :: HasField "x" r Bool => r -> Bool h = getField @"x" j :: T -> Bool j = h -- this would throw an error because of the `HasField` -- constraint being solved See the tests DsIncompleteRecSel* and TcIncompleteRecSel for more examples of the warning. See Note [Detecting incomplete record selectors] in GHC.HsToCore.Expr for implementation details - - - - - af6fdf42 by Arnaud Spiwack at 2023-07-26T17:23:52-04:00 Fix user-facing label in MR template - - - - - 5d45b92a by Matthew Pickering at 2023-07-27T05:46:46-04:00 ci: Test bootstrapping configurations with full-ci and on marge batches There have been two incidents recently where bootstrapping has been broken by removing support for building with 9.2.*. The process for bumping the minimum required version starts with bumping the configure version and then other CI jobs such as the bootstrap jobs have to be updated. We must not silently bump the minimum required version. Now we are running a slimmed down validate pipeline it seems worthwile to test these bootstrap configurations in the full-ci pipeline. - - - - - 25d4fee7 by Matthew Pickering at 2023-07-27T05:46:46-04:00 bootstrap: Remove ghc-9_2_* plans We are anticipating shortly making it necessary to use ghc-9.4 to boot the compiler. - - - - - 2f66da16 by Matthew Pickering at 2023-07-27T05:46:46-04:00 Update bootstrap plans for ghc-platform and ghc-toolchain dependencies Fixes #23735 - - - - - c8c6eab1 by Matthew Pickering at 2023-07-27T05:46:46-04:00 bootstrap: Disable -selftest flag from bootstrap plans This saves on building one dependency (QuickCheck) which is unecessary for bootstrapping. - - - - - a80ca086 by Andrew Lelechenko at 2023-07-27T05:47:26-04:00 Link reference paper and package from System.Mem.{StableName,Weak} - - - - - a5319358 by David Knothe at 2023-07-28T13:13:10-04:00 Update Match Datatype EquationInfo currently contains a list of the equation's patterns together with a CoreExpr that is to be evaluated after a successful match on this equation. All the match-functions only operate on the first pattern of an equation - after successfully matching it, match is called recursively on the tail of the pattern list. We can express this more clearly and make the code a little more elegant by updating the datatype of EquationInfo as follows: data EquationInfo = EqnMatch { eqn_pat = Pat GhcTc, eqn_rest = EquationInfo } | EqnDone { eqn_rhs = MatchResult CoreExpr } An EquationInfo now explicitly exposes its first pattern which most functions operate on, and exposes the equation that remains after processing the first pattern. An EqnDone signifies an empty equation where the CoreExpr can now be evaluated. - - - - - 86ad1af9 by David Binder at 2023-07-28T13:13:53-04:00 Improve documentation for Data.Fixed - - - - - f8fa1d08 by Ben Gamari at 2023-07-28T13:14:31-04:00 ghc-prim: Use C11 atomics Previously `ghc-prim`'s atomic wrappers used the legacy `__sync_*` family of C builtins. Here we refactor these to rather use the appropriate C11 atomic equivalents, allowing us to be more explicit about the expected ordering semantics. - - - - - 0bfc8908 by Finley McIlwaine at 2023-07-28T18:46:26-04:00 Include -haddock in DynFlags fingerprint The -haddock flag determines whether or not the resulting .hi files contain haddock documentation strings. If the existing .hi files do not contain haddock documentation strings and the user requests them, we should recompile. - - - - - 40425c50 by Andreas Klebinger at 2023-07-28T18:47:02-04:00 Aarch64 NCG: Use encoded immediates for literals. Try to generate instr x2, <imm> instead of mov x1, lit instr x2, x1 When possible. This get's rid if quite a few redundant mov instructions. I believe this causes a metric decrease for LargeRecords as we reduce register pressure. ------------------------- Metric Decrease: LargeRecord ------------------------- - - - - - e9a0fa3f by Andrew Lelechenko at 2023-07-28T18:47:42-04:00 Bump filepath submodule to 1.4.100.4 Resolves #23741 Metric Decrease: MultiComponentModules MultiComponentModulesRecomp MultiLayerModules MultiLayerModulesRecomp T10421 T12234 T12425 T13035 T13701 T13719 T16875 T18304 T18698a T18698b T21839c T9198 TcPlugin_RewritePerf hard_hole_fits Metric decrease on Windows can be probably attributed to https://github.com/haskell/filepath/pull/183 - - - - - ee93edfd by Andrew Lelechenko at 2023-07-28T18:48:21-04:00 Add since pragmas to GHC.IO.Handle.FD - - - - - d0369802 by Simon Peyton Jones at 2023-07-30T09:24:48+01:00 Make the occurrence analyser smarter about join points This MR addresses #22404. There is a big Note Note [Occurrence analysis for join points] that explains it all. Significant changes * New field occ_join_points in OccEnv * The NonRec case of occAnalBind splits into two cases: one for existing join points (which does the special magic for Note [Occurrence analysis for join points], and one for other bindings. * mkOneOcc adds in info from occ_join_points. * All "bring into scope" activity is centralised in the new function `addInScope`. * I made a local data type LocalOcc for use inside the occurrence analyser It is like OccInfo, but lacks IAmDead and IAmALoopBreaker, which in turn makes computationns over it simpler and more efficient. * I found quite a bit of allocation in GHC.Core.Rules.getRules so I optimised it a bit. More minor changes * I found I was using (Maybe Arity) a lot, so I defined a new data type JoinPointHood and used it everwhere. This touches a lot of non-occ-anal files, but it makes everything more perspicuous. * Renamed data constructor WithUsageDetails to WUD, and WithTailUsageDetails to WTUD This also fixes #21128, on the way. --------- Compiler perf ----------- I spent quite a time on performance tuning, so even though it does more than before, the occurrence analyser runs slightly faster on average. Here are the compile-time allocation changes over 0.5% CoOpt_Read(normal) ghc/alloc 766,025,520 754,561,992 -1.5% CoOpt_Singletons(normal) ghc/alloc 759,436,840 762,925,512 +0.5% LargeRecord(normal) ghc/alloc 1,814,482,440 1,799,530,456 -0.8% PmSeriesT(normal) ghc/alloc 68,159,272 67,519,720 -0.9% T10858(normal) ghc/alloc 120,805,224 118,746,968 -1.7% T11374(normal) ghc/alloc 164,901,104 164,070,624 -0.5% T11545(normal) ghc/alloc 79,851,808 78,964,704 -1.1% T12150(optasm) ghc/alloc 73,903,664 71,237,544 -3.6% GOOD T12227(normal) ghc/alloc 333,663,200 331,625,864 -0.6% T12234(optasm) ghc/alloc 52,583,224 52,340,344 -0.5% T12425(optasm) ghc/alloc 81,943,216 81,566,720 -0.5% T13056(optasm) ghc/alloc 294,517,928 289,642,512 -1.7% T13253-spj(normal) ghc/alloc 118,271,264 59,859,040 -49.4% GOOD T15164(normal) ghc/alloc 1,102,630,352 1,091,841,296 -1.0% T15304(normal) ghc/alloc 1,196,084,000 1,166,733,000 -2.5% T15630(normal) ghc/alloc 148,729,632 147,261,064 -1.0% T15703(normal) ghc/alloc 379,366,664 377,600,008 -0.5% T16875(normal) ghc/alloc 32,907,120 32,670,976 -0.7% T17516(normal) ghc/alloc 1,658,001,888 1,627,863,848 -1.8% T17836(normal) ghc/alloc 395,329,400 393,080,248 -0.6% T18140(normal) ghc/alloc 71,968,824 73,243,040 +1.8% T18223(normal) ghc/alloc 456,852,568 453,059,088 -0.8% T18282(normal) ghc/alloc 129,105,576 131,397,064 +1.8% T18304(normal) ghc/alloc 71,311,712 70,722,720 -0.8% T18698a(normal) ghc/alloc 208,795,112 210,102,904 +0.6% T18698b(normal) ghc/alloc 230,320,736 232,697,976 +1.0% BAD T19695(normal) ghc/alloc 1,483,648,128 1,504,702,976 +1.4% T20049(normal) ghc/alloc 85,612,024 85,114,376 -0.6% T21839c(normal) ghc/alloc 415,080,992 410,906,216 -1.0% GOOD T4801(normal) ghc/alloc 247,590,920 250,726,272 +1.3% T6048(optasm) ghc/alloc 95,699,416 95,080,680 -0.6% T783(normal) ghc/alloc 335,323,384 332,988,120 -0.7% T9233(normal) ghc/alloc 709,641,224 685,947,008 -3.3% GOOD T9630(normal) ghc/alloc 965,635,712 948,356,120 -1.8% T9675(optasm) ghc/alloc 444,604,152 428,987,216 -3.5% GOOD T9961(normal) ghc/alloc 303,064,592 308,798,800 +1.9% BAD WWRec(normal) ghc/alloc 503,728,832 498,102,272 -1.1% geo. mean -1.0% minimum -49.4% maximum +1.9% In fact these figures seem to vary between platforms; generally worse on i386 for some reason. The Windows numbers vary by 1% espec in benchmarks where the total allocation is low. But the geom mean stays solidly negative, which is good. The "increase/decrease" list below covers all platforms. The big win on T13253-spj comes because it has a big nest of join points, each occurring twice in the next one. The new occ-anal takes only one iteration of the simplifier to do the inlining; the old one took four. Moreover, we get much smaller code with the new one: New: Result size of Tidy Core = {terms: 429, types: 84, coercions: 0, joins: 14/14} Old: Result size of Tidy Core = {terms: 2,437, types: 304, coercions: 0, joins: 10/10} --------- Runtime perf ----------- No significant changes in nofib results, except a 1% reduction in compiler allocation. Metric Decrease: CoOpt_Read T13253-spj T9233 T9630 T9675 T12150 T21839c LargeRecord MultiComponentModulesRecomp T10421 T13701 T10421 T13701 T12425 Metric Increase: T18140 T9961 T18282 T18698a T18698b T19695 - - - - - 42aa7fbd by Julian Ospald at 2023-07-30T17:22:01-04:00 Improve documentation around IOException and ioe_filename See: * https://github.com/haskell/core-libraries-committee/issues/189 * https://github.com/haskell/unix/pull/279 * https://github.com/haskell/unix/pull/289 - - - - - 33598ecb by Sylvain Henry at 2023-08-01T14:45:54-04:00 JS: implement getMonotonicTime (fix #23687) - - - - - d2bedffd by Bartłomiej Cieślar at 2023-08-01T14:46:40-04:00 Implementation of the Deprecated Instances proposal #575 This commit implements the ability to deprecate certain instances, which causes the compiler to emit the desired deprecation message whenever they are instantiated. For example: module A where class C t where instance {-# DEPRECATED "dont use" #-} C Int where module B where import A f :: C t => t f = undefined g :: Int g = f -- "dont use" emitted here The implementation is as follows: - In the parser, we parse deprecations/warnings attached to instances: instance {-# DEPRECATED "msg" #-} Show X deriving instance {-# WARNING "msg2" #-} Eq Y (Note that non-standalone deriving instance declarations do not support this mechanism.) - We store the resulting warning message in `ClsInstDecl` (respectively, `DerivDecl`). In `GHC.Tc.TyCl.Instance.tcClsInstDecl` (respectively, `GHC.Tc.Deriv.Utils.newDerivClsInst`), we pass on that information to `ClsInst` (and eventually store it in `IfaceClsInst` too). - Finally, when we solve a constraint using such an instance, in `GHC.Tc.Instance.Class.matchInstEnv`, we emit the appropriate warning that was stored in `ClsInst`. Note that we only emit a warning when the instance is used in a different module than it is defined, which keeps the behaviour in line with the deprecation of top-level identifiers. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - d5a65af6 by Ben Gamari at 2023-08-01T14:47:18-04:00 compiler: Style fixes - - - - - 7218c80a by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Fix implicit cast This ensures that Task.h can be built with a C++ compiler. - - - - - d6d5aafc by Ben Gamari at 2023-08-01T14:47:19-04:00 testsuite: Fix warning in hs_try_putmvar001 - - - - - d9eddf7a by Ben Gamari at 2023-08-01T14:47:19-04:00 testsuite: Add AtomicModifyIORef test - - - - - f9eea4ba by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Introduce NO_WARN macro This allows fine-grained ignoring of warnings. - - - - - 497b24ec by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Simplify atomicModifyMutVar2# implementation Previously we would perform a redundant load in the non-threaded RTS in atomicModifyMutVar2# implementation for the benefit of the non-moving GC's write barrier. Eliminate this. - - - - - 52ee082b by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Introduce more principled fence operations - - - - - cd3c0377 by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Introduce SET_INFO_RELAXED - - - - - 6df2352a by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Style fixes - - - - - 4ef6f319 by Ben Gamari at 2023-08-01T14:47:19-04:00 codeGen/tsan: Rework handling of spilling - - - - - f9ca7e27 by Ben Gamari at 2023-08-01T14:47:19-04:00 hadrian: More debug information - - - - - df4153ac by Ben Gamari at 2023-08-01T14:47:19-04:00 Improve TSAN documentation - - - - - fecae988 by Ben Gamari at 2023-08-01T14:47:19-04:00 hadrian: More selective TSAN instrumentation - - - - - 465a9a0b by Alan Zimmerman at 2023-08-01T14:47:56-04:00 EPA: Provide correct annotation span for ImportDecl Use the whole declaration, rather than just the span of the 'import' keyword. Metric Decrease: T9961 T5205 Metric Increase: T13035 - - - - - ae63d0fa by Bartłomiej Cieślar at 2023-08-01T14:48:40-04:00 Add cases to T23279: HasField for deprecated record fields This commit adds additional tests from ticket #23279 to ensure that we don't regress on reporting deprecated record fields in conjunction with HasField, either when using overloaded record dot syntax or directly through `getField`. Fixes #23279 - - - - - 00fb6e6b by Andreas Klebinger at 2023-08-01T14:49:17-04:00 AArch NCG: Pure refactor Combine some alternatives. Add some line breaks for overly long lines - - - - - 8f3b3b78 by Andreas Klebinger at 2023-08-01T14:49:54-04:00 Aarch ncg: Optimize immediate use for address calculations When the offset doesn't fit into the immediate we now just reuse the general getRegister' code path which is well optimized to compute the offset into a register instead of a special case for CmmRegOff. This means we generate a lot less code under certain conditions which is why performance metrics for these improve. ------------------------- Metric Decrease: T4801 T5321FD T5321Fun ------------------------- - - - - - 74a882dc by MorrowM at 2023-08-02T06:00:03-04:00 Add a RULE to make lookup fuse See https://github.com/haskell/core-libraries-committee/issues/175 Metric Increase: T18282 - - - - - cca74dab by Ben Gamari at 2023-08-02T06:00:39-04:00 hadrian: Ensure that way-flags are passed to CC Previously the way-specific compilation flags (e.g. `-DDEBUG`, `-DTHREADED_RTS`) would not be passed to the CC invocations. This meant that C dependency files would not correctly reflect dependencies predicated on the way, resulting in the rather painful #23554. Closes #23554. - - - - - 622b483c by Jaro Reinders at 2023-08-02T06:01:20-04:00 Native 32-bit Enum Int64/Word64 instances This commits adds more performant Enum Int64 and Enum Word64 instances for 32-bit platforms, replacing the Integer-based implementation. These instances are a copy of the Enum Int and Enum Word instances with minimal changes to manipulate Int64 and Word64 instead. On i386 this yields a 1.5x performance increase and for the JavaScript back end it even yields a 5.6x speedup. Metric Decrease: T18964 - - - - - c8bd7fa4 by Sylvain Henry at 2023-08-02T06:02:03-04:00 JS: fix typos in constants (#23650) - - - - - b9d5bfe9 by Josh Meredith at 2023-08-02T06:02:40-04:00 JavaScript: update MK_TUP macros to use current tuple constructors (#23659) - - - - - 28211215 by Matthew Pickering at 2023-08-02T06:03:19-04:00 ci: Pass -Werror when building hadrian in hadrian-ghc-in-ghci job Warnings when building Hadrian can end up cluttering the output of HLS, and we've had bug reports in the past about these warnings when building Hadrian. It would be nice to turn on -Werror on at least one build of Hadrian in CI to avoid a patch introducing warnings when building Hadrian. Fixes #23638 - - - - - aca20a5d by Ben Gamari at 2023-08-02T06:03:55-04:00 codeGen: Ensure that TSAN is aware of writeArray# write barriers By using a proper release store instead of a fence. - - - - - 453c0531 by Ben Gamari at 2023-08-02T06:03:55-04:00 codeGen: Ensure that array reads have necessary barriers This was the cause of #23541. - - - - - 93a0d089 by Arnaud Spiwack at 2023-08-02T06:04:37-04:00 Add test for #23550 - - - - - 6a2f4a20 by Arnaud Spiwack at 2023-08-02T06:04:37-04:00 Desugar non-recursive lets to non-recursive lets (take 2) This reverts commit 522bd584f71ddeda21efdf0917606ce3d81ec6cc. And takes care of the case that I missed in my previous attempt. Namely the case of an AbsBinds with no type variables and no dictionary variable. Ironically, the comment explaining why non-recursive lets were desugared to recursive lets were pointing specifically at this case as the reason. I just failed to understand that it was until Simon PJ pointed it out to me. See #23550 for more discussion. - - - - - ff81d53f by jade at 2023-08-02T06:05:20-04:00 Expand documentation of List & Data.List This commit aims to improve the documentation and examples of symbols exported from Data.List - - - - - fa4e5913 by Jade at 2023-08-02T06:06:03-04:00 Improve documentation of Semigroup & Monoid This commit aims to improve the documentation of various symbols exported from Data.Semigroup and Data.Monoid - - - - - 1b27e151 by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Check for puns (see ghc#23368) - - - - - 457341fd by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Remove fake exports for (~), List, and Tuple<n> The old reasoning no longer applies, nowadays those names can be mentioned in export lists. - - - - - bf3dcddf by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Fix pretty-printing of Solo and MkSolo - - - - - e2c91bff by Gergő Érdi at 2023-08-03T02:55:46+01:00 Desugar bindings in the context of their evidence Closes #23172 - - - - - 481f4a46 by Gergő Érdi at 2023-08-03T07:48:43+01:00 Add flag to `-f{no-}specialise-incoherents` to enable/disable specialisation of incoherent instances Fixes #23287 - - - - - d751c583 by Profpatsch at 2023-08-04T12:24:26-04:00 base: Improve String & IsString documentation - - - - - 01db1117 by Ben Gamari at 2023-08-04T12:25:02-04:00 rts/win32: Ensure reliability of IO manager shutdown When the Win32 threaded IO manager shuts down, `ioManagerDie` sends an `IO_MANAGER_DIE` event to the IO manager thread using the `io_manager_event` event object. Finally, it will closes the event object, and invalidate `io_manager_event`. Previously, `readIOManagerEvent` would see that `io_manager_event` is invalid and return `0`, suggesting that everything is right with the world. This meant that if `ioManagerDie` invalidated the handle before the event manager was blocked on the event we would end up in a situation where the event manager would never realize it was asked to shut down. Fix this by ensuring that `readIOManagerEvent` instead returns `IO_MANAGER_DIE` when we detect that the event object has been invalidated by `ioManagerDie`. Fixes #23691. - - - - - fdef003a by Ryan Scott at 2023-08-04T12:25:39-04:00 Look through TH splices in splitHsApps This modifies `splitHsApps` (a key function used in typechecking function applications) to look through untyped TH splices and quasiquotes. Not doing so was the cause of #21077. This builds on !7821 by making `splitHsApps` match on `HsUntypedSpliceTop`, which contains the `ThModFinalizers` that must be run as part of invoking the TH splice. See the new `Note [Looking through Template Haskell splices in splitHsApps]` in `GHC.Tc.Gen.Head`. Along the way, I needed to make the type of `splitHsApps.set` slightly more general to accommodate the fact that the location attached to a quasiquote is a `SrcAnn NoEpAnns` rather than a `SrcSpanAnnA`. Fixes #21077. - - - - - e77a0b41 by Ben Gamari at 2023-08-04T12:26:15-04:00 Bump deepseq submodule to 1.5. And bump bounds (cherry picked from commit 1228d3a4a08d30eaf0138a52d1be25b38339ef0b) - - - - - cebb5819 by Ben Gamari at 2023-08-04T12:26:15-04:00 configure: Bump minimal boot GHC version to 9.4 (cherry picked from commit d3ffdaf9137705894d15ccc3feff569d64163e8e) - - - - - 83766dbf by Ben Gamari at 2023-08-04T12:26:15-04:00 template-haskell: Bump version to 2.21.0.0 Bumps exceptions submodule. (cherry picked from commit bf57fc9aea1196f97f5adb72c8b56434ca4b87cb) - - - - - 1211112a by Ben Gamari at 2023-08-04T12:26:15-04:00 base: Bump version to 4.19 Updates all boot library submodules. (cherry picked from commit 433d99a3c24a55b14ec09099395e9b9641430143) - - - - - 3ab5efd9 by Ben Gamari at 2023-08-04T12:26:15-04:00 testsuite: Normalise versions more aggressively In backpack hashes can contain `+` characters. (cherry picked from commit 024861af51aee807d800e01e122897166a65ea93) - - - - - d52be957 by Ben Gamari at 2023-08-04T12:26:15-04:00 testsuite: Declare bkpcabal08 as fragile Due to spurious output changes described in #23648. (cherry picked from commit c046a2382420f2be2c4a657c56f8d95f914ea47b) - - - - - e75a58d1 by Ben Gamari at 2023-08-04T12:26:15-04:00 gitlab-ci: Only mark linker_unload_native as broken in static jobs This test passes on dynamically-linked Alpine. (cherry picked from commit f356a7e8ec8ec3d6b2b30fd175598b9b80065d87) - - - - - 8b176514 by Ben Gamari at 2023-08-04T12:26:15-04:00 testsuite: Update base-exports - - - - - 4b647936 by Ben Gamari at 2023-08-04T12:26:15-04:00 testsuite/interface-stability: normalise versions This eliminates spurious changes from version bumps. - - - - - 0eb54c05 by Ben Gamari at 2023-08-04T12:26:51-04:00 linker/PEi386: Don't sign-extend symbol section number Previously we incorrectly interpreted PE section numbers as signed values. However, this isn't the case; rather, it's an unsigned 16-bit number with a few special bit-patterns (0xffff and 0xfffe). This resulted in #22941 as the linker would conclude that the sections were invalid. Fixing this required quite a bit of refactoring. Closes #22941. - - - - - fd7ce39c by Ben Gamari at 2023-08-04T12:27:28-04:00 testsuite: Mark MulMayOflo_full as broken rather than skipping To ensure that we don't accidentally fix it. See #23742. - - - - - 824092f2 by Ben Gamari at 2023-08-04T12:27:28-04:00 nativeGen/AArch64: Fix sign extension in MulMayOflo Previously the 32-bit implementations of MulMayOflo would use the a non-sensical sign-extension mode. Rewrite these to reflect what gcc 11 produces. Also similarly rework the 16- and 8-bit cases. This now passes the MulMayOflo tests in ghc/test-primops> in all four widths, including the precision tests. Fixes #23721. - - - - - 1b15dbc4 by Jan Hrček at 2023-08-04T12:28:08-04:00 Fix haddock markup in code example for coerce - - - - - 46fd8ced by Vladislav Zavialov at 2023-08-04T12:28:44-04:00 Fix (~) and (@) infix operators in TH splices (#23748) 8168b42a "Whitespace-sensitive bang patterns" allows GHC to accept the following infix operators: a ~ b = () a @ b = () But not if TH is used to generate those declarations: $([d| a ~ b = () a @ b = () |]) -- Test.hs:5:2: error: [GHC-55017] -- Illegal variable name: ‘~’ -- When splicing a TH declaration: (~_0) a_1 b_2 = GHC.Tuple.Prim.() This is easily fixed by modifying `reservedOps` in GHC.Utils.Lexeme - - - - - a1899d8f by Aaron Allen at 2023-08-04T12:29:24-04:00 [#23663] Show Flag Suggestions in GHCi Makes suggestions when using `:set` in GHCi with a misspelled flag. This mirrors how invalid flags are handled when passed to GHC directly. Logic for producing flag suggestions was moved to GHC.Driver.Sesssion so it can be shared. resolves #23663 - - - - - 03f2debd by Rodrigo Mesquita at 2023-08-04T12:30:00-04:00 Improve ghc-toolchain validation configure warning Fixes the layout of the ghc-toolchain validation warning produced by configure. - - - - - de25487d by Alan Zimmerman at 2023-08-04T12:30:36-04:00 EPA make getLocA a synonym for getHasLoc This is basically a no-op change, but allows us to make future changes that can rely on the HasLoc instances And I presume this means we can use more precise functions based on class resolution, so the Windows CI build reports Metric Decrease: T12234 T13035 - - - - - 3ac423b9 by Ben Gamari at 2023-08-04T12:31:13-04:00 ghc-platform: Add upper bound on base Hackage upload requires this. - - - - - 8ba20b21 by Matthew Craven at 2023-08-04T17:22:59-04:00 Adjust and clarify handling of primop effects Fixes #17900; fixes #20195. The existing "can_fail" and "has_side_effects" primop attributes that previously governed this were used in inconsistent and confusingly-documented ways, especially with regard to raising exceptions. This patch replaces them with a single "effect" attribute, which has four possible values: NoEffect, CanFail, ThrowsException, and ReadWriteEffect. These are described in Note [Classifying primop effects]. A substantial amount of related documentation has been re-drafted for clarity and accuracy. In the process of making this attribute format change for literally every primop, several existing mis-classifications were detected and corrected. One of these mis-classifications was tagToEnum#, which is now considered CanFail; this particular fix is known to cause a regression in performance for derived Enum instances. (See #23782.) Fixing this is left as future work. New primop attributes "cheap" and "work_free" were also added, and used in the corresponding parts of GHC.Core.Utils. In view of their actual meaning and uses, `primOpOkForSideEffects` and `exprOkForSideEffects` have been renamed to `primOpOkToDiscard` and `exprOkToDiscard`, respectively. Metric Increase: T21839c - - - - - 41bf2c09 by sheaf at 2023-08-04T17:23:42-04:00 Update inert_solved_dicts for ImplicitParams When adding an implicit parameter dictionary to the inert set, we must make sure that it replaces any previous implicit parameter dictionaries that overlap, in order to get the appropriate shadowing behaviour, as in let ?x = 1 in let ?x = 2 in ?x We were already doing this for inert_cans, but we weren't doing the same thing for inert_solved_dicts, which lead to the bug reported in #23761. The fix is thus to make sure that, when handling an implicit parameter dictionary in updInertDicts, we update **both** inert_cans and inert_solved_dicts to ensure a new implicit parameter dictionary correctly shadows old ones. Fixes #23761 - - - - - 43578d60 by Matthew Craven at 2023-08-05T01:05:36-04:00 Bump bytestring submodule to 0.11.5.1 - - - - - 91353622 by Ben Gamari at 2023-08-05T01:06:13-04:00 Initial commit of Note [Thunks, blackholes, and indirections] This Note attempts to summarize the treatment of thunks, thunk update, and indirections. This fell out of work on #23185. - - - - - 8d686854 by sheaf at 2023-08-05T01:06:54-04:00 Remove zonk in tcVTA This removes the zonk in GHC.Tc.Gen.App.tc_inst_forall_arg and its accompanying Note [Visible type application zonk]. Indeed, this zonk is no longer necessary, as we no longer maintain the invariant that types are well-kinded without zonking; only that typeKind does not crash; see Note [The Purely Kinded Type Invariant (PKTI)]. This commit removes this zonking step (as well as a secondary zonk), and replaces the aforementioned Note with the explanatory Note [Type application substitution], which justifies why the substitution performed in tc_inst_forall_arg remains valid without this zonking step. Fixes #23661 - - - - - 19dea673 by Ben Gamari at 2023-08-05T01:07:30-04:00 Bump nofib submodule Ensuring that nofib can be build using the same range of bootstrap compilers as GHC itself. - - - - - aa07402e by Luite Stegeman at 2023-08-05T23:15:55+09:00 JS: Improve compatibility with recent emsdk The JavaScript code in libraries/base/jsbits/base.js had some hardcoded offsets for fields in structs, because we expected the layout of the data structures to remain unchanged. Emsdk 3.1.42 changed the layout of the stat struct, breaking this assumption, and causing code in .hsc files accessing the stat struct to fail. This patch improves compatibility with recent emsdk by removing the assumption that data layouts stay unchanged: 1. offsets of fields in structs used by JavaScript code are now computed by the configure script, so both the .js and .hsc files will automatically use the new layout if anything changes. 2. the distrib/configure script checks that the emsdk version on a user's system is the same version that a bindist was booted with, to avoid data layout inconsistencies See #23641 - - - - - b938950d by Luite Stegeman at 2023-08-07T06:27:51-04:00 JS: Fix missing local variable declarations This fixes some missing local variable declarations that were found by running the testsuite in strict mode. Fixes #23775 - - - - - 6c0e2247 by sheaf at 2023-08-07T13:31:21-04:00 Update Haddock submodule to fix #23368 This submodule update adds the following three commits: bbf1c8ae - Check for puns 0550694e - Remove fake exports for (~), List, and Tuple<n> 5877bceb - Fix pretty-printing of Solo and MkSolo These commits fix the issues with Haddock HTML rendering reported in ticket #23368. Fixes #23368 - - - - - 5b5be3ea by Matthew Pickering at 2023-08-07T13:32:00-04:00 Revert "Bump bytestring submodule to 0.11.5.1" This reverts commit 43578d60bfc478e7277dcd892463cec305400025. Fixes #23789 - - - - - 01961be3 by Ben Gamari at 2023-08-08T02:47:14-04:00 configure: Derive library version from ghc-prim.cabal.in Since ghc-prim.cabal is now generated by Hadrian, we cannot depend upon it. Closes #23726. - - - - - 3b373838 by Ryan Scott at 2023-08-08T02:47:49-04:00 tcExpr: Push expected types for untyped TH splices inwards In !10911, I deleted a `tcExpr` case for `HsUntypedSplice` in favor of a much simpler case that simply delegates to `tcApp`. Although this passed the test suite at the time, this was actually an error, as the previous `tcExpr` case was critically pushing the expected type inwards. This actually matters for programs like the one in #23796, which GHC would not accept with type inference alone—we need full-blown type _checking_ to accept these. I have added back the previous `tcExpr` case for `HsUntypedSplice` and now explain why we have two different `HsUntypedSplice` cases (one in `tcExpr` and another in `splitHsApps`) in `Note [Looking through Template Haskell splices in splitHsApps]` in `GHC.Tc.Gen.Head`. Fixes #23796. - - - - - 0ef1d8ae by sheaf at 2023-08-08T21:26:51-04:00 Compute all emitted diagnostic codes This commit introduces in GHC.Types.Error.Codes the function constructorCodes :: forall diag. (...) => Map DiagnosticCode String which computes a collection of all the diagnostic codes that correspond to a particular type. In particular, we can compute the collection of all diagnostic codes emitted by GHC using the invocation constructorCodes @GhcMessage We then make use of this functionality in the new "codes" test which checks consistency and coverage of GHC diagnostic codes. It performs three checks: - check 1: all non-outdated GhcDiagnosticCode equations are statically used. - check 2: all outdated GhcDiagnosticCode equations are statically unused. - check 3: all statically used diagnostic codes are covered by the testsuite (modulo accepted exceptions). - - - - - 4bc7b1e5 by Fraser Tweedale at 2023-08-08T21:27:32-04:00 numberToRangedRational: fix edge cases for exp ≈ (maxBound :: Int) Currently a negative exponent less than `minBound :: Int` results in Infinity, which is very surprising and obviously wrong. ``` λ> read "1e-9223372036854775808" :: Double 0.0 λ> read "1e-9223372036854775809" :: Double Infinity ``` There is a further edge case where the exponent can overflow when increased by the number of tens places in the integer part, or underflow when decreased by the number of leading zeros in the fractional part if the integer part is zero: ``` λ> read "10e9223372036854775807" :: Double 0.0 λ> read "0.01e-9223372036854775808" :: Double Infinity ``` To resolve both of these issues, perform all arithmetic and comparisons involving the exponent in type `Integer`. This approach also eliminates the need to explicitly check the exponent against `maxBound :: Int` and `minBound :: Int`, because the allowed range of the exponent (i.e. the result of `floatRange` for the target floating point type) is certainly within those bounds. This change implements CLC proposal 192: https://github.com/haskell/core-libraries-committee/issues/192 - - - - - 6eab07b2 by Alan Zimmerman at 2023-08-08T21:28:10-04:00 EPA: Remove Location from WarningTxt source This is not needed. - - - - - 1a98d673 by Sebastian Graf at 2023-08-09T16:24:29-04:00 Cleanup a TODO introduced in 1f94e0f7 The change must have slipped through review of !4412 - - - - - 2274abc8 by Sebastian Graf at 2023-08-09T16:24:29-04:00 More explicit strictness in GHC.Real - - - - - ce8aa54c by Sebastian Graf at 2023-08-09T16:24:30-04:00 exprIsTrivial: Factor out shared implementation The duplication between `exprIsTrivial` and `getIdFromTrivialExpr_maybe` has been bugging me for a long time. This patch introduces an inlinable worker function `trivial_expr_fold` acting as the single, shared decision procedure of triviality. It "returns" a Church-encoded `Maybe (Maybe Id)`, so when it is inlined, it fuses to similar code as before. (Better code, even, in the case of `getIdFromTrivialExpr` which presently allocates a `Just` constructor that cancels away after this patch.) - - - - - d004a36d by Sebastian Graf at 2023-08-09T16:24:30-04:00 Simplify: Simplification of arguments in a single function The Simplifier had a function `simplArg` that wasn't called in `rebuildCall`, which seems to be the main way to simplify args. Hence I consolidated the code path to call `simplArg`, too, renaming to `simplLazyArg`. - - - - - 8c73505e by Sebastian Graf at 2023-08-09T16:24:30-04:00 Core.Ppr: Omit case binder for empty case alternatives A minor improvement to pretty-printing - - - - - d8d993f1 by Sebastian Graf at 2023-08-09T16:24:30-04:00 Disable tests RepPolyWrappedVar2 and RepPolyUnsafeCoerce1 in JS backend ... because those coerce between incompatible/unknown PrimReps. - - - - - f06e87e4 by Sebastian Graf at 2023-08-09T16:24:30-04:00 Inlining literals into boring contexts is OK - - - - - 4a6b7c87 by Sebastian Graf at 2023-08-09T16:24:30-04:00 Clarify floating of unsafeEqualityProofs (#23754) - - - - - b0f4752e by Sebastian Graf at 2023-08-09T16:24:30-04:00 Kill SetLevel.notWorthFloating.is_triv (#23270) We have had it since b84ba676034, when it operated on annotated expressions. Nowadays it operates on vanilla `CoreExpr` though, so we should just call `exprIsTrivial`; thus handling empty cases and string literals correctly. - - - - - 7e0c8b3b by Sebastian Graf at 2023-08-09T16:24:30-04:00 ANFise string literal arguments (#23270) This instates the invariant that a trivial CoreExpr translates to an atomic StgExpr. Nice. Annoyingly, in -O0 we sometimes generate ``` foo = case "blah"# of sat { __DEFAULT -> unpackCString# sat } ``` which makes it a bit harder to spot that we can emit a standard `stg_unpack_cstring` thunk. Fixes #23270. - - - - - 357f2738 by Sebastian Graf at 2023-08-09T16:24:30-04:00 Deactivate -fcatch-nonexhaustive-cases in ghc-bignum (#23345) - - - - - 59202c80 by Sebastian Graf at 2023-08-09T16:24:30-04:00 CorePrep: Eliminate EmptyCase and unsafeEqualityProof in CoreToStg instead We eliminate EmptyCase by way of `coreToStg (Case e _ _ []) = coreToStg e` now. The main reason is that it plays far better in conjunction with eta expansion (as we aim to do for arguments in CorePrep, #23083), because we can discard any arguments, `(case e of {}) eta == case e of {}`, whereas in `(e |> co) eta` it's impossible to discard the argument. We do also give the same treatment to unsafeCoerce proofs and treat them as trivial iff their RHS is trivial. It is also both much simpler to describe than the previous mechanism of emitting an unsafe coercion and simpler to implement, removing quite a bit of commentary and `CorePrepProv`. In the ghc/alloc perf test `LargeRecord`, we introduce an additional Simplifier iteration due to #17910. E.g., FloatOut produces a binding ``` lvl_s6uK [Occ=Once1] :: GHC.Types.Int [LclId] lvl_s6uK = GHC.Types.I# 2# lvl_s6uL [Occ=Once1] :: GHC.Types.Any [LclId] lvl_s6uL = case Unsafe.Coerce.unsafeEqualityProof ... of { Unsafe.Coerce.UnsafeRefl v2_i6tr -> lvl_s6uK `cast` (... v2_i6tr ...) } ``` That occurs once and hence is pre-inlined unconditionally in the next Simplifier pass. It's non-trivial to find a way around that, but not really harmful otherwise. Hence we accept a 1.2% increase on some architectures. Metric Increase: LargeRecord - - - - - 00d31188 by Sebastian Graf at 2023-08-09T16:24:30-04:00 CorePrep: Eta expand arguments (#23083) Previously, we'd only eta expand let bindings and lambdas, now we'll also eta expand arguments such as in T23083: ```hs g f h = f (h `seq` (h $)) ``` Unless `-fpedantic-bottoms` is set, we'll now transform to ```hs g f h = f (\eta -> h eta) ``` in CorePrep. See the new `Note [Eta expansion of arguments in CorePrep]` for the details. We only do this optimisation with -O2 because we saw 2-3% ghc/alloc regressions in T4801 and T5321FD. Fixes #23083. - - - - - bf885d7a by Matthew Craven at 2023-08-09T16:25:07-04:00 Bump bytestring submodule to 0.11.5, again Fixes #23789. The bytestring commit used here is unreleased; a release can be made when necessary. - - - - - 7acbf0fd by Sven Tennie at 2023-08-10T19:17:11-04:00 Serialize CmmRetInfo in .rodata The handling of case was missing. - - - - - 0c3136f2 by Sven Tennie at 2023-08-10T19:17:11-04:00 Reference StgRetFun payload by its struct field address This is easier to grasp than relative pointer offsets. - - - - - f68ff313 by Sven Tennie at 2023-08-10T19:17:11-04:00 Better variable name: u -> frame The 'u' was likely introduced by copy'n'paste. - - - - - 0131bb7f by Sven Tennie at 2023-08-10T19:17:11-04:00 Make checkSTACK() public Such that it can also be used in tests. - - - - - 7b6e1e53 by Sven Tennie at 2023-08-10T19:17:11-04:00 Publish stack related fields in DerivedConstants.h These will be used in ghc-heap to decode these parts of the stack. - - - - - 907ed054 by Sven Tennie at 2023-08-10T19:17:11-04:00 ghc-heap: Decode StgStack and its stack frames Previously, ghc-heap could only decode heap closures. The approach is explained in detail in note [Decoding the stack]. - - - - - 6beb6ac2 by Sven Tennie at 2023-08-10T19:17:11-04:00 Remove RetFunType from RetFun stack frame representation It's a technical detail. The single usage is replaced by a predicate. - - - - - 006bb4f3 by Sven Tennie at 2023-08-10T19:17:11-04:00 Better parameter name The call-site uses the term "offset", too. - - - - - d4c2c1af by Sven Tennie at 2023-08-10T19:17:11-04:00 Make closure boxing pure There seems to be no need to do something complicated. However, the strictness of the closure pointer matters, otherwise a thunk gets decoded. - - - - - 8d8426c9 by Sven Tennie at 2023-08-10T19:17:11-04:00 Document entertainGC in test It wasn't obvious why it's there and what its role is. Also, increase the "entertainment level" a bit. I checked in STG and Cmm dumps that this really generates closures (and is not e.g. constant folded away.) - - - - - cc52c358 by Finley McIlwaine at 2023-08-10T19:17:47-04:00 Add -dipe-stats flag This is useful for seeing which info tables have information. - - - - - 261c4acb by Finley McIlwaine at 2023-08-10T19:17:47-04:00 Add -finfo-table-map-with-fallback -finfo-table-map-with-stack The -fno-info-table-map-with-stack flag omits STACK info tables from the info table map, and the -fno-info-table-map-with-fallback flag omits info tables with defaulted source locations from the map. In a test on the Agda codebase the build results were about 7% smaller when both of those types of tables were omitted. Adds a test that verifies that passing each combination of these flags results in the correct output for -dipe-stats, which is disabled for the js backend since profiling is not implemented. This commit also refactors a lot of the logic around extracting info tables from the Cmm results and building the info table map. This commit also fixes some issues in the users guide rst source to fix warnings that were noticed while debugging the documentation for these flags. Fixes #23702 - - - - - d7047e0d by Jaro Reinders at 2023-08-14T04:41:42-04:00 Add changelog entry for specialised Enum Int64/Word64 instances - - - - - 52f5e8fb by cydparser at 2023-08-14T04:42:20-04:00 Fix -ddump-to-file and -ddump-timings interaction (#20316) - - - - - 1274c5d6 by cydparser at 2023-08-14T04:42:20-04:00 Update release notes (#20316) - - - - - 8e699b23 by Matthew Pickering at 2023-08-14T10:44:47-04:00 base: Add changelog entry for CLC #188 This proposal modified the implementations of copyBytes, moveBytes and fillBytes (as detailed in the proposal) https://github.com/haskell/core-libraries-committee/issues/188 - - - - - 026f040a by Matthew Pickering at 2023-08-14T10:45:23-04:00 packaging: Build manpage in separate directory to other documentation We were installing two copies of the manpage: * One useless one in the `share/doc` folder, because we copy the doc/ folder into share/ * The one we deliberately installed into `share/man` etc The solution is to build the manpage into the `manpage` directory when building the bindist, and then just install it separately. Fixes #23707 - - - - - 524c60c8 by Bartłomiej Cieślar at 2023-08-14T13:46:33-04:00 Report deprecated fields bound by record wildcards when used This commit ensures that we emit the appropriate warnings when a deprecated record field bound by a record wildcard is used. For example: module A where data Foo = Foo {x :: Int, y :: Bool, z :: Char} {-# DEPRECATED x "Don't use x" #-} {-# WARNING y "Don't use y" #-} module B where import A foo (Foo {..}) = x This will cause us to emit a "Don't use x" warning, with location the location of the record wildcard. Note that we don't warn about `y`, because it is unused in the RHS of `foo`. Fixes #23382 - - - - - d6130065 by Matthew Pickering at 2023-08-14T13:47:11-04:00 Add zstd suffix to jobs which rely on zstd This was causing some confusion as the job was named simply "x86_64-linux-deb10-validate", which implies a standard configuration rather than any dependency on libzstd. - - - - - e24e44fc by Matthew Pickering at 2023-08-14T13:47:11-04:00 ci: Always run project-version job This is needed for the downstream test-primops pipeline to workout what the version of a bindist produced by a pipeline is. - - - - - f17b9d62 by Matthew Pickering at 2023-08-14T13:47:11-04:00 gen_ci: Rework how jobs-metadata.json is generated * We now represent a job group a triple of Maybes, which makes it easier to work out when jobs are enabled/disabled on certain pipelines. ``` data JobGroup a = StandardTriple { v :: Maybe (NamedJob a) , n :: Maybe (NamedJob a) , r :: Maybe (NamedJob a) } ``` * `jobs-metadata.json` generation is reworked using the following algorithm. - For each pipeline type, find all the platforms we are doing builds for. - Select one build per platform - Zip together the results This way we can choose different pipelines for validate/nightly/release which makes the metadata also useful for validate pipelines. This feature is used by the test-primops downstream CI in order to select the right bindist for testing validate pipelines. This makes it easier to inspect which jobs are going to be enabled on a particular pipeline. - - - - - f9a5563d by Matthew Pickering at 2023-08-14T13:47:11-04:00 gen_ci: Rules rework In particular we now distinguish between whether we are dealing with a Nightly/Release pipeline (which labels don't matter for) and a validate pipeline where labels do matter. The overall goal here is to allow a disjunction of labels for validate pipelines, for example, > Run a job if we have the full-ci label or test-primops label Therefore the "ValidateOnly" rules are treated as a set of disjunctions rather than conjunctions like before. What this means in particular is that if we want to ONLY run a job if a label is set, for example, "FreeBSD" label then we have to override the whole label set. Fixes #23772 - - - - - d54b0c1d by Matthew Pickering at 2023-08-14T13:47:11-04:00 ci: set -e for lint-ci-config scripts - - - - - 994a9b35 by Matthew Pickering at 2023-08-14T13:47:11-04:00 ci: Fix job metadata generation - - - - - e194ed2b by Ben Gamari at 2023-08-15T00:58:09-04:00 users-guide: Note that GHC2021 doesn't include ExplicitNamespaces As noted in #23801. - - - - - d814bda9 by Ben Gamari at 2023-08-15T05:43:53-04:00 users-guide: Support both distutils and packaging As noted in #23818, some old distributions (e.g. Debian 9) only include `distutils` while newer distributions only include `packaging`. Fixes #23818. - - - - - 1726db3f by Ben Gamari at 2023-08-15T05:43:53-04:00 users-guide: Ensure extlinks is compatible with Sphinx <4 The semantics of the `extlinks` attribute annoyingly changed in Sphinx 4. Reflect this in our configuration. See #22690. Fixes #23807. - - - - - 173338cf by Matthew Pickering at 2023-08-15T22:00:24-04:00 ci: Run full-ci on master and release branches Fixes #23737 - - - - - bdab6898 by Andrew Lelechenko at 2023-08-15T22:01:03-04:00 Add @since pragmas for Data.Ord.clamp and GHC.Float.clamp - - - - - 662d351b by Matthew Pickering at 2023-08-16T09:35:04-04:00 ghc-toolchain: Match CPP args with configure script At the moment we need ghc-toolchain to precisely match the output as provided by the normal configure script. The normal configure script (FP_HSCPP_CMD_WITH_ARGS) branches on whether we are using clang or gcc so we match that logic exactly in ghc-toolchain. The old implementation (which checks if certain flags are supported) is better but for now we have to match to catch any potential errors in the configuration. Ticket: #23720 - - - - - 09c6759e by Matthew Pickering at 2023-08-16T09:35:04-04:00 configure: Fix `-Wl,--no-as-needed` check The check was failing because the args supplied by $$1 were quoted which failed because then the C compiler thought they were an input file. Fixes #23720 - - - - - 2129678b by Matthew Pickering at 2023-08-16T09:35:04-04:00 configure: Add flag which turns ghc-toolchain check into error We want to catch these errors in CI, but first we need to a flag which turns this check into an error. - - - - - 6e2aa8e0 by Matthew Pickering at 2023-08-16T09:35:04-04:00 ci: Enable --enable-strict-ghc-toolchain-check for all CI jobs This will cause any CI job to fail if we have a mismatch between what ghc-toolchain reports and what ./configure natively reports. Fixing these kinds of issues is highest priority for 9.10 release. - - - - - 12d39e24 by Rodrigo Mesquita at 2023-08-16T09:35:04-04:00 Pass user-specified options to ghc-toolchain The current user interface to configuring target toolchains is `./configure`. In !9263 we added a new tool to configure target toolchains called `ghc-toolchain`, but the blessed way of creating these toolchains is still through configure. However, we were not passing the user-specified options given with the `./configure` invocation to the ghc-toolchain tool. This commit remedies that by storing the user options and environment variables in USER_* variables, which then get passed to GHC-toolchain. The exception to the rule is the windows bundled toolchain, which overrides the USER_* variables with whatever flags the windows bundled toolchain requires to work. We consider the bundled toolchain to be effectively the user specifying options, since the actual user delegated that configuration work. Closes #23678 - - - - - f7b3c3a0 by Rodrigo Mesquita at 2023-08-16T09:35:04-04:00 ghc-toolchain: Parse javascript and ghcjs as a Arch and OS - - - - - 8a0ae4ee by Rodrigo Mesquita at 2023-08-16T09:35:04-04:00 ghc-toolchain: Fix ranlib option - - - - - 31e9ec96 by Rodrigo Mesquita at 2023-08-16T09:35:04-04:00 Check Link Works with -Werror - - - - - bc1998b3 by Matthew Pickering at 2023-08-16T09:35:04-04:00 Only check for no_compact_unwind support on darwin While writing ghc-toolchain we noticed that the FP_PROG_LD_NO_COMPACT_UNWIND check is subtly wrong. Specifically, we pass -Wl,-no_compact_unwind to cc. However, ld.gold interprets this as -n o_compact_unwind, which is a valid argument. Fixes #23676 - - - - - 0283f36e by Matthew Pickering at 2023-08-16T09:35:04-04:00 Add some javascript special cases to ghc-toolchain On javascript there isn't a choice of toolchain but some of the configure checks were not accurately providing the correct answer. 1. The linker was reported as gnu LD because the --version output mentioned gnu LD. 2. The --target flag makes no sense on javascript but it was just ignored by the linker, so we add a special case to stop ghc-toolchain thinking that emcc supports --target when used as a linker. - - - - - a48ec5f8 by Matthew Pickering at 2023-08-16T09:35:04-04:00 check for emcc in gnu_LD check - - - - - 50df2e69 by Matthew Pickering at 2023-08-16T09:35:04-04:00 Add ldOverrideWhitelist to only default to ldOverride on windows/linux On some platforms - ie darwin, javascript etc we really do not want to allow the user to use any linker other than the default one as this leads to all kinds of bugs. Therefore it is a bit more prudant to add a whitelist which specifies on which platforms it might be possible to use a different linker. - - - - - a669a39c by Matthew Pickering at 2023-08-16T09:35:04-04:00 Fix plaform glob in FPTOOLS_SET_C_LD_FLAGS A normal triple may look like x86_64-unknown-linux but when cross-compiling you get $target set to a quad such as.. aarch64-unknown-linux-gnu Which should also match this check. - - - - - c52b6769 by Matthew Pickering at 2023-08-16T09:35:04-04:00 ghc-toolchain: Pass ld-override onto ghc-toolchain - - - - - 039b484f by Matthew Pickering at 2023-08-16T09:35:04-04:00 ld override: Make whitelist override user given option - - - - - d2b63cbc by Matthew Pickering at 2023-08-16T09:35:05-04:00 ghc-toolchain: Add format mode to normalise differences before diffing. The "format" mode takes an "--input" and "--ouput" target file and formats it. This is intended to be useful on windows where the configure/ghc-toolchain target files can't be diffed very easily because the path separators are different. - - - - - f2b39e4a by Matthew Pickering at 2023-08-16T09:35:05-04:00 ghc-toolchain: Bump ci-images commit to get new ghc-wasm-meta We needed to remove -Wno-unused-command-line-argument from the arguments passed in order for the configure check to report correctly. See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10976#note_516335 - - - - - 92103830 by Matthew Pickering at 2023-08-16T09:35:05-04:00 configure: MergeObjsCmd - distinguish between empty string and unset variable If `MergeObjsCmd` is explicitly set to the empty string then we should assume that MergeObjs is just not supported. This is especially important for windows where we set MergeObjsCmd to "" in m4/fp_setup_windows_toolchain.m4. - - - - - 3500bb2c by Matthew Pickering at 2023-08-16T09:35:05-04:00 configure: Add proper check to see if object merging works - - - - - 08c9a014 by Matthew Pickering at 2023-08-16T09:35:05-04:00 ghc-toolchain: If MergeObjsCmd is not set, replace setting with Nothing If the user explicitly chooses to not set a MergeObjsCmd then it is correct to use Nothing for tgtMergeObjs field in the Target file. - - - - - c9071d94 by Matthew Pickering at 2023-08-16T09:35:05-04:00 HsCppArgs: Augment the HsCppOptions This is important when we pass -I when setting up the windows toolchain. - - - - - 294a6d80 by Matthew Pickering at 2023-08-16T09:35:05-04:00 Set USER_CPP_ARGS when setting up windows toolchain - - - - - bde4b5d4 by Rodrigo Mesquita at 2023-08-16T09:35:05-04:00 Improve handling of Cc as a fallback - - - - - f4c1c3a3 by Rodrigo Mesquita at 2023-08-16T09:35:05-04:00 ghc-toolchain: Configure Cpp and HsCpp correctly when user specifies flags In ghc-toolchain, we were only /not/ configuring required flags when the user specified any flags at all for the of the HsCpp and Cpp tools. Otherwise, the linker takes into consideration the user specified flags to determine whether to search for a better linker implementation, but already configured the remaining GHC and platform-specific flags regardless of the user options. Other Tools consider the user options as a baseline for further configuration (see `findProgram`), so #23689 is not applicable. Closes #23689 - - - - - bfe4ffac by Matthew Pickering at 2023-08-16T09:35:05-04:00 CPP_ARGS: Put new options after user specified options This matches up with the behaviour of ghc-toolchain, so that the output of both matches. - - - - - a6828173 by Gergő Érdi at 2023-08-16T09:35:41-04:00 If a defaulting plugin made progress, re-zonk wanteds before built-in defaulting Fixes #23821. - - - - - e2b38115 by Sylvain Henry at 2023-08-17T07:54:06-04:00 JS: implement openat(AT_FDCWD...) (#23697) Use `openSync` to implement `openat(AT_FDCWD...)`. - - - - - a975c663 by sheaf at 2023-08-17T07:54:47-04:00 Use unsatisfiable for missing methods w/ defaults When a class instance has an Unsatisfiable constraint in its context and the user has not explicitly provided an implementation of a method, we now always provide a RHS of the form `unsatisfiable @msg`, even if the method has a default definition available. This ensures that, when deferring type errors, users get the appropriate error message instead of a possible runtime loop, if class default methods were defined recursively. Fixes #23816 - - - - - 45ca51e5 by Ben Gamari at 2023-08-17T15:16:41-04:00 ghc-internal: Initial commit of the skeleton - - - - - 88bbf8c5 by Ben Gamari at 2023-08-17T15:16:41-04:00 ghc-experimental: Initial commit - - - - - 664468c0 by Ben Gamari at 2023-08-17T15:17:17-04:00 testsuite/cloneStackLib: Fix incorrect format specifiers - - - - - eaa835bb by Ben Gamari at 2023-08-17T15:17:17-04:00 rts/ipe: Fix const-correctness of IpeBufferListNode Both info tables and the string table should be `const` - - - - - 78f6f6fd by Ben Gamari at 2023-08-17T15:17:17-04:00 nonmoving: Drop dead debugging utilities These are largely superceded by support in the ghc-utils GDB extension. - - - - - 3f6e8f42 by Ben Gamari at 2023-08-17T15:17:17-04:00 nonmoving: Refactor management of mark thread Here we refactor that treatment of the worker thread used by the nonmoving GC for concurrent marking, avoiding creating a new thread with every major GC cycle. As well, the new scheme is considerably easier to reason about, consolidating all state in one place, accessed via a small set of accessors with clear semantics. - - - - - 88c32b7d by Ben Gamari at 2023-08-17T15:17:17-04:00 testsuite: Skip T23221 in nonmoving GC ways This test is very dependent upon GC behavior. - - - - - 381cfaed by Ben Gamari at 2023-08-17T15:17:17-04:00 ghc-heap: Don't expose stack dirty and marking fields These are GC metadata and are not relevant to the end-user. Moreover, they are unstable which makes ghc-heap harder to test than necessary. - - - - - 16828ca5 by Luite Stegeman at 2023-08-21T18:42:53-04:00 bump process submodule to include macOS fix and JS support - - - - - b4d5f6ed by Matthew Pickering at 2023-08-21T18:43:29-04:00 ci: Add support for triggering test-primops pipelines This commit adds 4 ways to trigger testing with test-primops. 1. Applying the ~test-primops label to a validate pipeline. 2. A manually triggered job on a validate pipeline 3. A nightly pipeline job 4. A release pipeline job Fixes #23695 - - - - - 32c50daa by Matthew Pickering at 2023-08-21T18:43:29-04:00 Add test-primops label support The test-primops CI job requires some additional builds in the validation pipeline, so we make sure to enable these jobs when test-primops label is set. - - - - - 73ca8340 by Matthew Pickering at 2023-08-21T18:43:29-04:00 Revert "Aarch ncg: Optimize immediate use for address calculations" This reverts commit 8f3b3b78a8cce3bd463ed175ee933c2aabffc631. See #23793 - - - - - 5546ad9e by Matthew Pickering at 2023-08-21T18:43:29-04:00 Revert "AArch NCG: Pure refactor" This reverts commit 00fb6e6b06598752414a0b9a92840fb6ca61338d. See #23793 - - - - - 02dfcdc2 by Matthew Pickering at 2023-08-21T18:43:29-04:00 Revert "Aarch64 NCG: Use encoded immediates for literals." This reverts commit 40425c5021a9d8eb5e1c1046e2d5fa0a2918f96c. See #23793 ------------------------- Metric Increase: T4801 T5321FD T5321Fun ------------------------- - - - - - 7be4a272 by Matthew Pickering at 2023-08-22T08:55:20+01:00 ci: Remove manually triggered test-ci job This doesn't work on slimmed down pipelines as the needed jobs don't exist. If you want to run test-primops then apply the label. - - - - - 76a4d11b by Jaro Reinders at 2023-08-22T08:08:13-04:00 Remove Ptr example from roles docs - - - - - 069729d3 by Bryan Richter at 2023-08-22T08:08:49-04:00 Guard against duplicate pipelines in forks - - - - - f861423b by Rune K. Svendsen at 2023-08-22T08:09:35-04:00 dump-decls: fix "Ambiguous module name"-error Fixes errors of the following kind, which happen when dump-decls is run on a package that contains a module name that clashes with that of another package. ``` dump-decls: <no location info>: error: Ambiguous module name `System.Console.ANSI.Types': it was found in multiple packages: ansi-terminal-0.11.4 ansi-terminal-types-0.11.5 ``` - - - - - edd8bc43 by Krzysztof Gogolewski at 2023-08-22T12:31:20-04:00 Fix MultiWayIf linearity checking (#23814) Co-authored-by: Thomas BAGREL <thomas.bagrel at tweag.io> - - - - - 4ba088d1 by konsumlamm at 2023-08-22T12:32:02-04:00 Update `Control.Concurrent.*` documentation - - - - - 015886ec by ARATA Mizuki at 2023-08-22T15:13:13-04:00 Support 128-bit SIMD on AArch64 via LLVM backend - - - - - 52a6d868 by Krzysztof Gogolewski at 2023-08-22T15:13:51-04:00 Testsuite cleanup - Remove misleading help text in perf_notes, ways are not metrics - Remove no_print_summary - this was used for Phabricator - In linters tests, run 'git ls-files' just once. Previously, it was called on each has_ls_files() - Add ghc-prim.cabal to gitignore, noticed in #23726 - Remove ghc-prim.cabal, it was accidentally committed in 524c60c8cd - - - - - ab40aa52 by Alan Zimmerman at 2023-08-22T15:14:28-04:00 EPA: Use Introduce [DeclTag] in AnnSortKey The AnnSortKey is used to keep track of the order of declarations for printing when the container has split them apart. This applies to HsValBinds and ClassDecl, ClsInstDecl. When making modifications to the list of declarations, the new order must be captured for when it must be printed. For each list of declarations (binds and sigs for a HsValBind) we can just store the list in order. To recreate the list when printing, we must merge them, and this is what the AnnSortKey records. It used to be indexed by SrcSpan, we now simply index by a marker as to which list to take the next item from. - - - - - e7db36c1 by sheaf at 2023-08-23T08:41:28-04:00 Don't attempt pattern synonym error recovery This commit gets rid of the pattern synonym error recovery mechanism (recoverPSB). The rationale is that the fake pattern synonym binding that the recovery mechanism introduced could lead to undesirable knock-on errors, and it isn't really feasible to conjure up a satisfactory binding as pattern synonyms can be used both in expressions and patterns. See Note [Pattern synonym error recovery] in GHC.Tc.TyCl.PatSyn. It isn't such a big deal to eagerly fail compilation on a pattern synonym that doesn't typecheck anyway. Fixes #23467 - - - - - 6ccd9d65 by Ben Gamari at 2023-08-23T08:42:05-04:00 base: Don't use Data.ByteString.Internals.memcpy This function is now deprecated from `bytestring`. Use `Foreign.Marshal.Utils.copyBytes` instead. Fixes #23880. - - - - - 0bfa0031 by Matthew Pickering at 2023-08-23T13:43:48-04:00 hadrian: Uniformly pass buildOptions to all builders in runBuilder In Builder.hs, runBuilderWith mostly ignores the buildOptions in BuildInfo. This leads to hard to diagnose bugs as any build options you pass with runBuilderWithCmdOptions are ignored for many builders. Solution: Uniformly pass buildOptions to the invocation of cmd. Fixes #23845 - - - - - 9cac8f11 by Matthew Pickering at 2023-08-23T13:43:48-04:00 Abstract windows toolchain setup This commit splits up the windows toolchain setup logic into two functions. * FP_INSTALL_WINDOWS_TOOLCHAIN - deals with downloading the toolchain if it isn't already downloaded * FP_SETUP_WINDOWS_TOOLCHAIN - sets the environment variables to point to the correct place FP_SETUP_WINDOWS_TOOLCHAIN is abstracted from the location of the mingw toolchain and also the eventual location where we will install the toolchain in the installed bindist. This is the first step towards #23608 - - - - - 6c043187 by Matthew Pickering at 2023-08-23T13:43:48-04:00 Generate build.mk for bindists The config.mk.in script was relying on some variables which were supposed to be set by build.mk but therefore never were when used to install a bindist. Specifically * BUILD_PROF_LIBS to determine whether we had profiled libraries or not * DYNAMIC_GHC_PROGRAMS to determine whether we had shared libraries or not Not only were these never set but also not really accurate because you could have shared libaries but still statically linked ghc executable. In addition variables like GhcLibWays were just never used, so those have been deleted from the script. Now instead we generate a build.mk file which just directly specifies which RtsWays we have supplied in the bindist and whether we have DYNAMIC_GHC_PROGRAMS. - - - - - fe23629b by Matthew Pickering at 2023-08-23T13:43:48-04:00 hadrian: Add reloc-binary-dist-* targets This adds a command line option to build a "relocatable" bindist. The bindist is created by first creating a normal bindist and then installing it using the `RelocatableBuild=YES` option. This creates a bindist without any wrapper scripts pointing to the libdir. The motivation for this feature is that we want to ship relocatable bindists on windows and this method is more uniform than the ad-hoc method which lead to bugs such as #23608 and #23476 The relocatable bindist can be built with the "reloc-binary-dist" target and supports the same suffixes as the normal "binary-dist" command to specify the compression style. - - - - - 41cbaf44 by Matthew Pickering at 2023-08-23T13:43:48-04:00 packaging: Fix installation scripts on windows/RelocatableBuild case This includes quite a lot of small fixes which fix the installation makefile to work on windows properly. This also required fixing the RelocatableBuild variable which seemed to have been broken for a long while. Sam helped me a lot writing this patch by providing a windows machine to test the changes. Without him it would have taken ages to tweak everything. Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 03474456 by Matthew Pickering at 2023-08-23T13:43:48-04:00 ci: Build relocatable bindist on windows We now build the relocatable bindist target on windows, which means we test and distribute the new method of creating a relocatable bindist. - - - - - d0b48113 by Matthew Pickering at 2023-08-23T13:43:48-04:00 hadrian: Add error when trying to build binary-dist target on windows The binary dist produced by `binary-dist` target doesn't work on windows because of the wrapper script the makefile installs. In order to not surprise any packagers we just give an error if someone tries to build the old binary-dist target rather than the reloc-binary-dist target. - - - - - 7cbf9361 by Matthew Pickering at 2023-08-23T13:43:48-04:00 hadrian: Remove query' logic to use tooldir - - - - - 03fad42e by Matthew Pickering at 2023-08-23T13:43:48-04:00 configure: Set WindresCmd directly and removed unused variables For some reason there was an indirection via the Windres variable before setting WindresCmd. That indirection led to #23855. I then also noticed that these other variables were just not used anywhere when trying to work out what the correct condition was for this bit of the configure script. - - - - - c82770f5 by sheaf at 2023-08-23T13:43:48-04:00 Apply shellcheck suggestion to SUBST_TOOLDIR - - - - - 896e35e5 by sheaf at 2023-08-23T13:44:34-04:00 Compute hints from TcSolverReportMsg This commit changes how hints are handled in conjunction with constraint solver report messages. Instead of storing `[GhcHint]` in the TcRnSolverReport error constructor, we compute the hints depending on the underlying TcSolverReportMsg. This disentangles the logic and makes it easier to add new hints for certain errors. - - - - - a05cdaf0 by Alexander Esgen at 2023-08-23T13:45:16-04:00 users-guide: remove note about fatal Haddock parse failures - - - - - 4908d798 by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Introduce Data.Enum - - - - - f59707c7 by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Num.Integer - - - - - b1054053 by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Num - - - - - 6baa481d by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Num.Natural - - - - - 2ac15233 by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Float - - - - - f3c489de by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Real - - - - - 94f59eaa by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Eliminate module reexport in GHC.Exception The metric increase here isn't strictly due to this commit but it's a rather small, incidental change. Metric Increase: T8095 T13386 Metric Decrease: T8095 T13386 T18304 - - - - - be1fc7df by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add disclaimers in internal modules To warn users that these modules are internal and their interfaces may change with little warning. As proposed in Core Libraries Committee #146 [CLC146]. [CLC146]: https://github.com/haskell/core-libraries-committee/issues/146 - - - - - 0326f3f4 by sheaf at 2023-08-23T17:37:29-04:00 Bump Cabal submodule We need to bump the Cabal submodule to include commit ec75950 which fixes an issue with a dodgy import Rep(..) which relied on GHC bug #23570 - - - - - 0504cd08 by Facundo Domínguez at 2023-08-23T17:38:11-04:00 Fix typos in the documentation of Data.OldList.permutations - - - - - 1420b8cb by Antoine Leblanc at 2023-08-24T16:18:17-04:00 Be more eager in TyCon boot validity checking This commit performs boot-file consistency checking for TyCons into checkValidTyCl. This ensures that we eagerly catch any mismatches, which prevents the compiler from seeing these inconsistencies and panicking as a result. See Note [TyCon boot consistency checking] in GHC.Tc.TyCl. Fixes #16127 - - - - - d99c816f by Finley McIlwaine at 2023-08-24T16:18:55-04:00 Refactor estimation of stack info table provenance This commit greatly refactors the way we compute estimated provenance for stack info tables. Previously, this process was done using an entirely separate traversal of the whole Cmm code stream to build the map from info tables to source locations. The separate traversal is now fused with the Cmm code generation pipeline in GHC.Driver.Main. This results in very significant code generation speed ups when -finfo-table-map is enabled. In testing, this patch reduces code generation times by almost 30% with -finfo-table-map and -O0, and 60% with -finfo-table-map and -O1 or -O2 . Fixes #23103 - - - - - d3e0124c by Finley McIlwaine at 2023-08-24T16:18:55-04:00 Add a test checking overhead of -finfo-table-map We want to make sure we don't end up with poor codegen performance resulting from -finfo-table-map again as in #23103. This test adds a performance test tracking total allocations while compiling ExactPrint with -finfo-table-map. - - - - - fcfc1777 by Ben Gamari at 2023-08-25T10:58:16-04:00 llvmGen: Add export list to GHC.Llvm.MetaData - - - - - 5880fff6 by Ben Gamari at 2023-08-25T10:58:16-04:00 llvmGen: Allow LlvmLits in MetaExprs This omission appears to be an oversight. - - - - - 86ce92a2 by Ben Gamari at 2023-08-25T10:58:16-04:00 compiler: Move platform feature predicates to GHC.Driver.DynFlags These are useful in `GHC.Driver.Config.*`. - - - - - a6a38742 by Ben Gamari at 2023-08-25T10:58:16-04:00 llvmGen: Introduce infrastructure for module flag metadata - - - - - e9af2cf3 by Ben Gamari at 2023-08-25T10:58:16-04:00 llvmGen: Don't pass stack alignment via command line As of https://reviews.llvm.org/D103048 LLVM no longer supports the `-stack-alignment=...` flag. Instead this information is passed via a module flag metadata node. This requires dropping support for LLVM 11 and 12. Fixes #23870 - - - - - a936f244 by Alan Zimmerman at 2023-08-25T10:58:56-04:00 EPA: Keep track of "in" token for WarningTxt category A warning can now be written with a category, e.g. {-# WARNInG in "x-c" e "d" #-} Keep track of the location of the 'in' keyword and string, as well as the original SourceText of the label, in case it uses character escapes. - - - - - 3df8a653 by Matthew Pickering at 2023-08-25T17:42:18-04:00 Remove redundant import in InfoTableProv The copyBytes function is provided by the import of Foreign. Fixes #23889 - - - - - d6f807ec by Ben Gamari at 2023-08-25T17:42:54-04:00 gitlab/issue-template: Mention report-a-bug - - - - - 50b9f75d by Artin Ghasivand at 2023-08-26T20:02:50+03:30 Added StandaloneKindSignature examples to replace CUSKs ones - - - - - 2f6309a4 by Vladislav Zavialov at 2023-08-27T03:47:37-04:00 Remove outdated CPP in compiler/* and template-haskell/* The boot compiler was bumped to 9.4 in cebb5819b43. There is no point supporting older GHC versions with CPP. - - - - - 5248fdf7 by Zubin Duggal at 2023-08-28T15:01:09+05:30 testsuite: Add regression test for #23861 Simon says this was fixed by commit 8d68685468d0b6e922332a3ee8c7541efbe46137 Author: sheaf <sam.derbyshire at gmail.com> Date: Fri Aug 4 15:28:45 2023 +0200 Remove zonk in tcVTA - - - - - b6903f4d by Zubin Duggal at 2023-08-28T12:33:58-04:00 testsuite: Add regression test for #23864 Simon says this was fixed by commit 59202c800f2c97c16906120ab2561f6e1556e4af Author: Sebastian Graf <sebastian.graf at kit.edu> Date: Fri Mar 31 17:35:22 2023 +0200 CorePrep: Eliminate EmptyCase and unsafeEqualityProof in CoreToStg instead We eliminate EmptyCase by way of `coreToStg (Case e _ _ []) = coreToStg e` now. The main reason is that it plays far better in conjunction with eta expansion (as we aim to do for arguments in CorePrep, #23083), because we can discard any arguments, `(case e of {}) eta == case e of {}`, whereas in `(e |> co) eta` it's impossible to discard the argument. - - - - - 9eecdf33 by sheaf at 2023-08-28T18:54:06+00:00 Remove ScopedTypeVariables => TypeAbstractions This commit implements [amendment 604](https://github.com/ghc-proposals/ghc-proposals/pull/604/) to [GHC proposal 448](https://github.com/ghc-proposals/ghc-proposals/pull/448) by removing the implication of language extensions ScopedTypeVariables => TypeAbstractions To limit breakage, we now allow type arguments in constructor patterns when both ScopedTypeVariables and TypeApplications are enabled, but we emit a warning notifying the user that this is deprecated behaviour that will go away starting in GHC 9.12. Fixes #23776 - - - - - fadd5b4d by sheaf at 2023-08-28T18:54:06+00:00 .stderr: ScopedTypeVariables =/> TypeAbstractions This commit accepts testsuite changes for the changes in the previous commit, which mean that TypeAbstractions is no longer implied by ScopedTypeVariables. - - - - - 4f5fb500 by Greg Steuck at 2023-08-29T07:55:13-04:00 Repair `codes` test on OpenBSD by explicitly requesting extended RE - - - - - 6bbde581 by Vasily Sterekhov at 2023-08-29T12:06:58-04:00 Add test for #23540 `T23540.hs` makes use of `explainEv` from `HieQueries.hs`, so `explainEv` has been moved to `TestUtils.hs`. - - - - - 257bb3bd by Vasily Sterekhov at 2023-08-29T12:06:58-04:00 Add test for #23120 - - - - - 4f192947 by Vasily Sterekhov at 2023-08-29T12:06:58-04:00 Make some evidence uses reachable by toHie Resolves #23540, #23120 This adds spans to certain expressions in the typechecker and renamer, and lets 'toHie' make use of those spans. Therefore the relevant evidence uses for the following syntax will now show up under the expected nodes in 'HieAst's: - Overloaded literals ('IsString', 'Num', 'Fractional') - Natural patterns and N+k patterns ('Eq', 'Ord', and instances from the overloaded literals being matched on) - Arithmetic sequences ('Enum') - Monadic bind statements ('Monad') - Monadic body statements ('Monad', 'Alternative') - ApplicativeDo ('Applicative', 'Functor') - Overloaded lists ('IsList') Also see Note [Source locations for implicit function calls] In the process of handling overloaded lists I added an extra 'SrcSpan' field to 'VAExpansion' - this allows us to more accurately reconstruct the locations from the renamer in 'rebuildHsApps'. This also happens to fix #23120. See the additions to Note [Looking through HsExpanded] - - - - - fe9fcf9d by Sylvain Henry at 2023-08-29T12:07:50-04:00 ghc-heap: rename C file (fix #23898) - - - - - b60d6576 by Krzysztof Gogolewski at 2023-08-29T12:08:29-04:00 Misc cleanup - Builtin.PrimOps: ReturnsAlg was used only for unboxed tuples. Rename to ReturnsTuple. - Builtin.Utils: use SDoc for a panic message. The comment about <<details unavailable>> was obsoleted by e8d356773b56. - TagCheck: fix wrong logic. It was zipping a list 'args' with its version 'args_cmm' after filtering. - Core.Type: remove an outdated 1999 comment about unlifted polymorphic types - hadrian: remove leftover debugging print - - - - - 3054fd6d by Krzysztof Gogolewski at 2023-08-29T12:09:08-04:00 Add a regression test for #23903 The bug has been fixed by commit bad2f8b8aa8424. - - - - - 21584b12 by Ben Gamari at 2023-08-29T19:52:02-04:00 README: Refer to ghc-hq repository for contributor and governance information - - - - - e542d590 by sheaf at 2023-08-29T19:52:40-04:00 Export setInertSet from GHC.Tc.Solver.Monad We used to export getTcSInerts and setTcSInerts from GHC.Tc.Solver.Monad. These got renamed to getInertSet/setInertSet in e1590ddc. That commit also removed the export of setInertSet, but that function is useful for the GHC API. - - - - - 694ec5b1 by sheaf at 2023-08-30T10:18:32-04:00 Don't bundle children for non-parent Avails We used to bundle all children of the parent Avail with things that aren't the parent, e.g. with class C a where type T a meth :: .. we would bundle the whole Avail (C, T, meth) with all of C, T and meth, instead of only with C. Avoiding this fixes #23570 - - - - - d926380d by Krzysztof Gogolewski at 2023-08-30T10:19:08-04:00 Fix typos - - - - - d07080d2 by Josh Meredith at 2023-08-30T19:42:32-04:00 JS: Implement missing C functions `rename`, `realpath`, and `getcwd` (#23806) - - - - - e2940272 by David Binder at 2023-08-30T19:43:08-04:00 Bump submodules of hpc and hpc-bin to version 0.7.0.0 hpc 0.7.0.0 dropped SafeHaskell safety guarantees in order to simplify compatibility with newer versions of the directory package which dropped all SafeHaskell guarantees. - - - - - 5d56d05c by David Binder at 2023-08-30T19:43:08-04:00 Bump hpc bound in ghc.cabal.in - - - - - 99fff496 by Dominik Schrempf at 2023-08-31T00:04:46-04:00 ghc classes documentation: rm redundant comment - - - - - fe021bab by Dominik Schrempf at 2023-08-31T00:04:46-04:00 prelude documentation: various nits - - - - - 48c84547 by Dominik Schrempf at 2023-08-31T00:04:46-04:00 integer documentation: minor corrections - - - - - 20cd12f4 by Dominik Schrempf at 2023-08-31T00:04:46-04:00 real documentation: nits - - - - - dd39bdc0 by sheaf at 2023-08-31T00:05:27-04:00 Add a test for #21765 This issue (of reporting a constraint as being redundant even though removing it causes typechecking to fail) was fixed in aed1974e. This commit simply adds a regression test. Fixes #21765 - - - - - f1ec3628 by Andrew Lelechenko at 2023-08-31T23:53:30-04:00 Export foldl' from Prelude and bump submodules See https://github.com/haskell/core-libraries-committee/issues/167 for discussion Metric Decrease: T8095 T13386 Metric Increase: T13386 T8095 T8095 ghc/alloc decreased on x86_64, but increased on aarch64. T13386 ghc/alloc decreased on x86_64-windows, but increased on other platforms. Neither has anything to do with `foldl'`, so I conclude that both are flaky. - - - - - 3181b97d by Gergő Érdi at 2023-08-31T23:54:06-04:00 Allow cross-tyvar defaulting proposals from plugins Fixes #23832. - - - - - 495b2241 by Matthew Pickering at 2023-09-01T13:02:07+02:00 Fix issue with duplicate reexported definitions (T23616) When a class method was reexported, it's default methods were also showing up in the generated html page. The simplest and most non-invasive fix is to not look for the default method if we are just exporting the class method.. because the backends are just showing default methods when the whole class is exported. In general it would be worthwhile to rewrite this bit of code I think as the logic and what gets included is split over `lookupDocs` and `availExportDecl` it would be clearer to combine the two. The result of lookupDocs is always just passed to availExportDecl so it seems simpler and more obvious to just write the function directly. - - - - - e4af506e by Sebastian Graf at 2023-09-01T14:29:12-04:00 Clarify Note [GlobalId/LocalId] after CorePrep (#23797) Fixes #23797. - - - - - ac29787c by Sylvain Henry at 2023-09-01T14:30:02-04:00 Fix warning with UNPACK on sum type (#23921) - - - - - 9765ac7b by Zubin Duggal at 2023-09-05T00:37:45-04:00 hadrian: track python dependencies in doc rules - - - - - 1578215f by sheaf at 2023-09-05T00:38:26-04:00 Bump Haddock to fix #23616 This commit updates the Haddock submodule to include the fix to #23616. Fixes #23616 - - - - - 5a2fe35a by David Binder at 2023-09-05T00:39:07-04:00 Fix example in GHC user guide in SafeHaskell section The example given in the SafeHaskell section uses an implementation of Monad which no longer works. This MR removes the non-canonical return instance and adds the necessary instances of Functor and Applicative. - - - - - 291d81ae by Matthew Pickering at 2023-09-05T14:03:10-04:00 driver: Check transitive closure of haskell package dependencies when deciding whether to relink We were previously just checking whether direct package dependencies had been modified. This caused issues when compiling without optimisations as we wouldn't relink the direct dependency if one of its dependenices changed. Fixes #23724 - - - - - 35da0775 by Krzysztof Gogolewski at 2023-09-05T14:03:47-04:00 Re-export GHC.Utils.Panic.Plain from GHC.Utils.Panic Fixes #23930 - - - - - 6551824d by Finley McIlwaine at 2023-09-05T13:06:57-07:00 Remove fake export of `FUN` from Prelude This prevents `data FUN` from being shown at the top of the Prelude docs. Fixes \#23920 on GHC. - - - - - 3930d793 by Jaro Reinders at 2023-09-06T18:42:55-04:00 Make STG rewriter produce updatable closures - - - - - 0104221a by Krzysztof Gogolewski at 2023-09-06T18:43:32-04:00 configure: update message to use hadrian (#22616) - - - - - b34f8586 by Alan Zimmerman at 2023-09-07T10:58:38-04:00 EPA: Incorrect locations for UserTyVar with '@' In T13343.hs, the location for the @ is not within the span of the surrounding UserTyVar. type Bad @v = (forall (v1 :: RuntimeRep) (a1 :: TYPE v). a1) :: TYPE v Widen it so it is captured. Closes #23887 - - - - - 8046f020 by Finley McIlwaine at 2023-09-07T10:59:15-04:00 Bump haddock submodule to fix #23920 Removes the fake export of `FUN` from Prelude. Fixes #23920. Bumps haddock submodule. - - - - - e0aa8c6e by Krzysztof Gogolewski at 2023-09-07T11:00:03-04:00 Fix wrong role in mkSelCo_maybe In the Lint failure in #23938, we start with a coercion Refl :: T a ~R T a, and call mkSelCo (SelTyCon 1 nominal) Refl. The function incorrectly returned Refl :: a ~R a. The returned role should be nominal, according to the SelCo rule: co : (T s1..sn) ~r0 (T t1..tn) r = tyConRole tc r0 i ---------------------------------- SelCo (SelTyCon i r) : si ~r ti In this test case, r is nominal while r0 is representational. - - - - - 1d92f2df by Gergő Érdi at 2023-09-08T04:04:30-04:00 If we have multiple defaulting plugins, then we should zonk in between them after any defaulting has taken place, to avoid a defaulting plugin seeing a metavariable that has already been filled. Fixes #23821. - - - - - eaee4d29 by Gergő Érdi at 2023-09-08T04:04:30-04:00 Improvements to the documentation of defaulting plugins Based on @simonpj's draft and comments in !11117 - - - - - ede3df27 by Alan Zimmerman at 2023-09-08T04:05:06-04:00 EPA: Incorrect span for LWarnDec GhcPs The code (from T23465.hs) {-# WARNInG in "x-c" e "d" #-} e = e gives an incorrect span for the LWarnDecl GhcPs Closes #23892 It also fixes the Test23465/Test23464 mixup - - - - - a0ccef7a by Krzysztof Gogolewski at 2023-09-08T04:05:42-04:00 Valid hole fits: don't suggest unsafeCoerce (#17940) - - - - - 9ab5a448 by Alan Zimmerman at 2023-09-08T18:26:53+01:00 Match changes in wip/az/T23885-unicode-funtycon - - - - - 88b942c4 by Oleg Grenrus at 2023-09-08T19:58:42-04:00 Add warning for badly staged types. Resolves #23829. The stage violation results in out-of-bound names in splices. Technically this is an error, but someone might rely on this!? Internal changes: - we now track stages for TyVars. - thLevel (RunSplice _) = 0, instead of panic, as reifyInstances does in fact rename its argument type, and it can contain variables. - - - - - 9861f787 by Ben Gamari at 2023-09-08T19:59:19-04:00 rts: Fix invalid symbol type I suspect this code is dead since we haven't observed this failing despite the obviously incorrect macro name. - - - - - 03ed6a9a by Ben Gamari at 2023-09-08T19:59:19-04:00 testsuite: Add simple test exercising C11 atomics in GHCi See #22012. - - - - - 1aa5733a by Ben Gamari at 2023-09-08T19:59:19-04:00 rts/RtsSymbols: Add AArch64 outline atomic operations Fixes #22012 by adding the symbols described in https://github.com/llvm/llvm-project/blob/main/llvm/docs/Atomics.rst#libcalls-atomic. Ultimately this would be better addressed by #22011, but this is a first step in the right direction and fixes the immediate symptom. Note that we dropped the `__arch64_cas16` operations as these provided by all platforms's compilers. Also, we don't link directly against the libgcc/compiler-rt definitions but rather provide our own wrappers to work around broken toolchains (e.g. https://bugs.gentoo.org/868018). Generated via https://gitlab.haskell.org/ghc/ghc/-/snippets/5733. - - - - - 8f7d3041 by Matthew Pickering at 2023-09-08T19:59:55-04:00 ci: Build debian12 and fedora38 bindists This adds builds for the latest releases for fedora and debian We build these bindists in nightly and release pipelines. - - - - - a1f0d55c by Felix Leitz at 2023-09-08T20:00:37-04:00 Fix documentation around extension implication for MultiParamTypeClasses/ConstrainedClassMethods. - - - - - 98166389 by Teo Camarasu at 2023-09-12T04:30:54-04:00 docs: move -xn flag beside --nonmoving-gc It makes sense to have these beside each other as they are aliases. - - - - - f367835c by Teo Camarasu at 2023-09-12T04:30:55-04:00 nonmoving: introduce a family of dense allocators Supplement the existing power 2 sized nonmoving allocators with a family of dense allocators up to a configurable threshold. This should reduce waste from rounding up block sizes while keeping the amount of allocator sizes manageable. This patch: - Adds a new configuration option `--nonmoving-dense-allocator-count` to control the amount of these new dense allocators. - Adds some constants to `NonmovingAllocator` in order to keep marking fast with the new allocators. Resolves #23340 - - - - - 2b07bf2e by Teo Camarasu at 2023-09-12T04:30:55-04:00 Add changelog entry for #23340 - - - - - f96fe681 by sheaf at 2023-09-12T04:31:44-04:00 Use printGhciException in run{Stmt, Decls} When evaluating statements in GHCi, we need to use printGhciException instead of the printException function that GHC provides in order to get the appropriate error messages that are customised for ghci use. - - - - - d09b932b by psilospore at 2023-09-12T04:31:44-04:00 T23686: Suggest how to enable Language Extension when in ghci Fixes #23686 - - - - - da30f0be by Matthew Craven at 2023-09-12T04:32:24-04:00 Unarise: Split Rubbish literals in function args Fixes #23914. Also adds a check to STG lint that these args are properly unary or nullary after unarisation - - - - - 261b6747 by Matthew Pickering at 2023-09-12T04:33:04-04:00 darwin: Bump MAXOSX_DEPLOYMENT_TARGET to 10.13 This bumps the minumum supported version to 10.13 (High Sierra) which is 6 years old at this point. Fixes #22938 - - - - - f418f919 by Mario Blažević at 2023-09-12T04:33:45-04:00 Fix TH pretty-printing of nested GADTs, issue #23937 This commit fixes `Language.Haskell.TH.Ppr.pprint` so that it correctly pretty-prints GADTs declarations contained within data family instances. Fixes #23937 - - - - - d7a64753 by John Ericson at 2023-09-12T04:34:20-04:00 Put hadrian non-bootstrap plans through `jq` This makes it possible to review changes with conventional diffing tools. This is picking up where ad8cfed4195b1bbfc15b841f010e75e71f63157d left off. - - - - - ff0a709a by Sylvain Henry at 2023-09-12T08:46:28-04:00 JS: fix some tests - Tests using Setup programs need to pass --with-hc-pkg - Several other fixes See https://gitlab.haskell.org/ghc/ghc/-/wikis/javascript-backend/bug_triage for the current status - - - - - fc86f0e7 by Krzysztof Gogolewski at 2023-09-12T08:47:04-04:00 Fix in-scope set assertion failure (#23918) Patch by Simon - - - - - 21a906c2 by Matthew Pickering at 2023-09-12T17:21:04+02:00 Add -Winconsistent-flags warning The warning fires when inconsistent command line flags are passed. For example: * -dynamic-too and -dynamic * -dynamic-too on windows * -O and --interactive * etc This is on by default and allows users to control whether the warning is displayed and whether it should be an error or not. Fixes #22572 - - - - - dfc4f426 by Krzysztof Gogolewski at 2023-09-12T20:31:35-04:00 Avoid serializing BCOs with the internal interpreter Refs #23919 - - - - - 9217950b by Finley McIlwaine at 2023-09-13T08:06:03-04:00 Fix numa auto configure - - - - - 98e7c1cf by Simon Peyton Jones at 2023-09-13T08:06:40-04:00 Add -fno-cse to T15426 and T18964 This -fno-cse change is to avoid these performance tests depending on flukey CSE stuff. Each contains several independent tests, and we don't want them to interact. See #23925. By killing CSE we expect a 400% increase in T15426, and 100% in T18964. Metric Increase: T15426 T18964 - - - - - 236a134e by Simon Peyton Jones at 2023-09-13T08:06:40-04:00 Tiny refactor canEtaReduceToArity was only called internally, and always with two arguments equal to zero. This patch just specialises the function, and renames it to cantEtaReduceFun. No change in behaviour. - - - - - 56b403c9 by Ben Gamari at 2023-09-13T19:21:36-04:00 spec-constr: Lift argument limit for SPEC-marked functions When the user adds a SPEC argument to a function, they are informing us that they expect the function to be specialised. However, previously this instruction could be preempted by the specialised-argument limit (sc_max_args). Fix this. This fixes #14003. - - - - - 6840012e by Simon Peyton Jones at 2023-09-13T19:22:13-04:00 Fix eta reduction Issue #23922 showed that GHC was bogusly eta-reducing a join point. We should never eta-reduce (\x -> j x) to j, if j is a join point. It is extremly difficult to trigger this bug. It took me 45 mins of trying to make a small tests case, here immortalised as T23922a. - - - - - e5c00092 by Andreas Klebinger at 2023-09-14T08:57:43-04:00 Profiling: Properly escape characters when using `-pj`. There are some ways in which unusual characters like quotes or others can make it into cost centre names. So properly escape these. Fixes #23924 - - - - - ec490578 by Ellie Hermaszewska at 2023-09-14T08:58:24-04:00 Use clearer example variable names for bool eliminator - - - - - 5126a2fe by Sylvain Henry at 2023-09-15T11:18:02-04:00 Add missing int64/word64-to-double/float rules (#23907) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/203 - - - - - 566ef411 by Mario Blažević at 2023-09-15T11:18:43-04:00 Fix and test TH pretty-printing of type operator role declarations This commit fixes and tests `Language.Haskell.TH.Ppr.pprint` so that it correctly pretty-prints `type role` declarations for operator names. Fixes #23954 - - - - - 8e05c54a by Simon Peyton Jones at 2023-09-16T01:42:33-04:00 Use correct FunTyFlag in adjustJoinPointType As the Lint error in #23952 showed, the function adjustJoinPointType was failing to adjust the FunTyFlag when adjusting the type. I don't think this caused the seg-fault reported in the ticket, but it is definitely. This patch fixes it. It is tricky to come up a small test case; Krzysztof came up with this one, but it only triggers a failure in GHC 9.6. - - - - - 778c84b6 by Pierre Le Marre at 2023-09-16T01:43:15-04:00 Update to Unicode 15.1.0 See: https://www.unicode.org/versions/Unicode15.1.0/ - - - - - f9d79a6c by Alan Zimmerman at 2023-09-18T00:00:14-04:00 EPA: track unicode version for unrestrictedFunTyCon Closes #23885 Updates haddock submodule - - - - - 9374f116 by Andrew Lelechenko at 2023-09-18T00:00:54-04:00 Bump parsec submodule to allow text-2.1 and bytestring-0.12 - - - - - 7ca0240e by Ben Gamari at 2023-09-18T15:16:48-04:00 base: Advertise linear time of readFloat As noted in #23538, `readFloat` has runtime that scales nonlinearly in the size of its input. Consequently, its use on untrusted input can be exploited as a denial-of-service vector. Point this out and suggest use of `read` instead. See #23538. - - - - - f3f58f13 by Simon Peyton Jones at 2023-09-18T15:17:24-04:00 Remove dead code GHC.CoreToStg.Prep.canFloat This function never fires, so we can delete it: #23965. - - - - - ccab5b15 by Ben Gamari at 2023-09-18T15:18:02-04:00 base/changelog: Move fix for #23907 to 9.8.1 section Since the fix was backported to 9.8.1 - - - - - 51b57d65 by Matthew Pickering at 2023-09-19T08:44:31-04:00 Add aarch64 alpine bindist This is dynamically linked and makes creating statically linked executables more straightforward. Fixes #23482 - - - - - 02c87213 by Matthew Pickering at 2023-09-19T08:44:31-04:00 Add aarch64-deb11 bindist This adds a debian 11 release job for aarch64. Fixes #22005 - - - - - 8b61dfd6 by Alexis King at 2023-09-19T08:45:13-04:00 Don’t store the async exception masking state in CATCH frames - - - - - 86d2971e by doyougnu at 2023-09-19T19:08:19-04:00 compiler,ghci: error codes link to HF error index closes: #23259 - adds -fprint-error-index-links={auto|always|never} flag - - - - - 5f826c18 by sheaf at 2023-09-19T19:09:03-04:00 Pass quantified tyvars in tcDefaultAssocDecl This commit passes the correct set of quantified type variables written by the user in associated type default declarations for validity checking. This ensures that validity checking of associated type defaults mirrors that of standalone type family instances. Fixes #23768 (see testcase T23734 in subsequent commit) - - - - - aba18424 by sheaf at 2023-09-19T19:09:03-04:00 Avoid panic in mkGADTVars This commit avoids panicking in mkGADTVars when we encounter a type variable as in #23784 that is bound by a user-written forall but not actually used. Fixes #23784 - - - - - a525a92a by sheaf at 2023-09-19T19:09:03-04:00 Adjust reporting of unused tyvars in data FamInsts This commit adjusts the validity checking of data family instances to improve the reporting of unused type variables. See Note [Out of scope tvs in data family instances] in GHC.Tc.Validity. The problem was that, in a situation such as data family D :: Type data instance forall (d :: Type). D = MkD the RHS passed to 'checkFamPatBinders' would be the TyCon app R:D d which mentions the type variable 'd' quantified in the user-written forall. Thus, when computing the set of unused type variables in the RHS of the data family instance, we would find that 'd' is used, and report a strange error message that would say that 'd' is not bound on the LHS. To fix this, we special-case the data-family instance case, manually extracting all the type variables that appear in the arguments of all the data constructores of the data family instance. Fixes #23778 - - - - - 28dd52ee by sheaf at 2023-09-19T19:09:03-04:00 Unused tyvars in FamInst: only report user tyvars This commit changes how we perform some validity checking for coercion axioms to mirror how we handle default declarations for associated type families. This allows us to keep track of whether type variables in type and data family instances were user-written or not, in order to only report the user-written ones in "unused type variable" error messages. Consider for example: {-# LANGUAGE PolyKinds #-} type family F type instance forall a. F = () In this case, we get two quantified type variables, (k :: Type) and (a :: k); the second being user-written, but the first is introduced by the typechecker. We should only report 'a' as being unused, as the user has no idea what 'k' is. Fixes #23734 - - - - - 1eed645c by sheaf at 2023-09-19T19:09:03-04:00 Validity: refactor treatment of data families This commit refactors the reporting of unused type variables in type and data family instances to be more principled. This avoids ad-hoc logic in the treatment of data family instances. - - - - - 35bc506b by John Ericson at 2023-09-19T19:09:40-04:00 Remove `ghc-cabal` It is dead code since the Make build system was removed. I tried to go over every match of `git grep -i ghc-cabal` to find other stray bits. Some of those might be workarounds that can be further removed. - - - - - 665ca116 by John Paul Adrian Glaubitz at 2023-09-19T19:10:39-04:00 Re-add unregisterised build support for sparc and sparc64 Closes #23959 - - - - - 142f8740 by Matthew Pickering at 2023-09-19T19:11:16-04:00 Bump ci-images to use updated version of Alex Fixes #23977 - - - - - fa977034 by John Ericson at 2023-09-21T12:55:25-04:00 Use Cabal 3.10 for Hadrian We need the newer version for `CABAL_FLAG_*` env vars for #17191. - - - - - a5d22cab by John Ericson at 2023-09-21T12:55:25-04:00 hadrian: `need` any `configure` script we will call When the script is changed, we should reconfigure. - - - - - db882b57 by John Ericson at 2023-09-21T12:55:25-04:00 hadrian: Make it easier to debug Cabal configure Right now, output is squashed. This make per-package configure scripts extremely hard to maintain, because we get vague "library is missing" errors when the actually probably is usually completely unrelated except for also involving the C/C++ toolchain. (I can always pass `-VVV` to Hadrian locally, but these errors are subtle and I often cannot reproduce them locally!) `--disable-option-checking` was added back in 75c6e0684dda585c37b4ac254cd7a13537a59a91 but seems to be a bit overkill; if other flags are passed that are not recognized behind the two from Cabal mentioned in the former comment, we *do* want to know about it. - - - - - 7ed65f5a by John Ericson at 2023-09-21T12:55:25-04:00 hadrian: Increase verbosity of certain cabal commands This is a hack to get around the cabal function we're calling *decreasing* the verbosity it passes to another function, which is the stuff we often actually care about. Sigh. Keeping this a separate commit so if this makes things too verbose it is easy to revert. - - - - - a4fde569 by John Ericson at 2023-09-21T12:55:25-04:00 rts: Move most external symbols logic to the configure script This is much more terse because we are programmatically handling the leading underscore. `findPtr` however is still handled in the Cabal file because we need a newer Cabal to pass flags to the configure script automatically. Co-Authored-By: Ben Gamari <ben at well-typed.com> - - - - - 56cc85fb by Andrew Lelechenko at 2023-09-21T12:56:21-04:00 Bump Cabal submodule to allow text-2.1 and bytestring-0.12 - - - - - 0cd6148c by Matthew Pickering at 2023-09-21T12:56:21-04:00 hadrian: Generate Distribution/Fields/Lexer.x before creating a source-dist - - - - - b10ba6a3 by Andrew Lelechenko at 2023-09-21T12:56:21-04:00 Bump hadrian's index-state to upgrade alex at least to 3.2.7.3 - - - - - 11ecc37b by Luite Stegeman at 2023-09-21T12:57:03-04:00 JS: correct file size and times Programs produced by the JavaScript backend were returning incorrect file sizes and modification times, causing cabal related tests to fail. This fixes the problem and adds an additional test that verifies basic file information operations. fixes #23980 - - - - - b35fd2cd by Ben Gamari at 2023-09-21T12:57:39-04:00 gitlab-ci: Drop libiserv from upload_ghc_libs libiserv has been merged into the ghci package. - - - - - 37ad04e8 by Ben Gamari at 2023-09-21T12:58:15-04:00 testsuite: Fix Windows line endings - - - - - 5795b365 by Ben Gamari at 2023-09-21T12:58:15-04:00 testsuite: Use makefile_test - - - - - 15118740 by Ben Gamari at 2023-09-21T12:58:55-04:00 system-cxx-std-lib: Add license and description - - - - - 0208f1d5 by Ben Gamari at 2023-09-21T12:59:33-04:00 gitlab/issue-templates: Rename bug.md -> default.md So that it is visible by default. - - - - - 23cc3f21 by Andrew Lelechenko at 2023-09-21T20:18:11+01:00 Bump submodule text to 2.1 - - - - - b8e4fe23 by Andrew Lelechenko at 2023-09-22T20:05:05-04:00 Bump submodule unix to 2.8.2.1 - - - - - 54b2016e by John Ericson at 2023-09-23T11:40:41-04:00 Move lib{numa,dw} defines to RTS configure Clean up the m4 to handle the auto case always and be more consistent. Also simplify the CPP --- we should always have both headers if we are using libnuma. "side effects" (AC_DEFINE, and AC_SUBST) are removed from the macros to better separate searching from actions taken based on search results. This might seem overkill now, but will make shuffling logic between configure scripts easier later. The macro comments are converted from `dnl` to `#` following the recomendation in https://www.gnu.org/software/autoconf/manual/autoconf-2.71/html_node/Macro-Definitions.html - - - - - d51b601b by John Ericson at 2023-09-23T11:40:50-04:00 Shuffle libzstd configuring between scripts Like the prior commit for libdw and libnuma, `AC_DEFINE` to RTS configure, `AC_SUBST` goes to the top-level configure script, and the documentation of the m4 macro is improved. - - - - - d1425af0 by John Ericson at 2023-09-23T11:41:03-04:00 Move `FP_ARM_OUTLINE_ATOMICS` to RTS configure It is just `AC_DEFINE` it belongs there instead. - - - - - 18de37e4 by John Ericson at 2023-09-23T11:41:03-04:00 Move mmap in the runtime linker check to the RTS configure `AC_DEFINE` should go there instead. - - - - - 74132c2b by Andrew Lelechenko at 2023-09-25T21:56:54-04:00 Elaborate comment on GHC_NO_UNICODE - - - - - de142aa2 by Ben Gamari at 2023-09-26T15:25:03-04:00 gitlab-ci: Mark T22012 as broken on CentOS 7 Due to #23979. - - - - - 6a896ce8 by Teo Camarasu at 2023-09-26T15:25:39-04:00 hadrian: better error for failing to find file's dependencies Resolves #24004 - - - - - d697a6c2 by Stefan Holdermans at 2023-09-26T20:58:37+00:00 Refactor uses of `partitionEithers . map` This patch changes occurences of the idiom `partitionEithers (map f xs)` by the simpler form `partitionWith f xs` where `partitionWith` is the utility function defined in `GHC.Utils.Misc`. Resolves: #23953 - - - - - 8a2968b7 by Stefan Holdermans at 2023-09-26T20:58:37+00:00 Refactor uses of `partitionEithers <$> mapM f xs` This patch changes occurences of the idiom `partitionEithers <$> mapM f xs` by the simpler form `partitionWithM f xs` where `partitionWithM` is a utility function newly added to `GHC.Utils.Misc`. - - - - - 6a27eb97 by Stefan Holdermans at 2023-09-26T20:58:37+00:00 Mark `GHC.Utils.Misc.partitionWithM` as inlineable This patch adds an `INLINEABLE` pragma for `partitionWithM` to ensure that the right-hand side of the definition of this function remains available for specialisation at call sites. - - - - - f1e5245a by David Binder at 2023-09-27T01:19:00-04:00 Add RTS option to supress tix file - - - - - 1f43124f by David Binder at 2023-09-27T01:19:00-04:00 Add expected output to testsuite in test interface-stability/base-exports - - - - - b9d2c354 by David Binder at 2023-09-27T01:19:00-04:00 Expose HpcFlags and getHpcFlags from GHC.RTS.Flags - - - - - 345675c6 by David Binder at 2023-09-27T01:19:00-04:00 Fix expected output of interface-stability test - - - - - 146e1c39 by David Binder at 2023-09-27T01:19:00-04:00 Implement getHpcFlags - - - - - 61ba8e20 by David Binder at 2023-09-27T01:19:00-04:00 Add section in user guide - - - - - ea05f890 by David Binder at 2023-09-27T01:19:01-04:00 Rename --emit-tix-file to --write-tix-file - - - - - cabce2ce by David Binder at 2023-09-27T01:19:01-04:00 Update the golden files for interface stability - - - - - 1dbdb9d0 by Krzysztof Gogolewski at 2023-09-27T01:19:37-04:00 Refactor: introduce stgArgRep The function 'stgArgType' returns the type in STG. But this violates the abstraction: in STG we're supposed to operate on PrimReps. This introduces stgArgRep ty = typePrimRep (stgArgType ty) stgArgRep1 ty = typePrimRep1 (stgArgType ty) stgArgRep_maybe ty = typePrimRep_maybe (stgArgType ty) stgArgType is still directly used for unboxed tuples (should be fixable), FFI and in ticky. - - - - - b02f8042 by Mario Blažević at 2023-09-27T17:33:28-04:00 Fix TH pretty-printer's parenthesization This PR Fixes `Language.Haskell.TH.Ppr.pprint` so it correctly emits parentheses where needed. Fixes #23962, #23968, #23971, and #23986 - - - - - 79104334 by Krzysztof Gogolewski at 2023-09-27T17:34:04-04:00 Add a testcase for #17564 The code in the ticket relied on the behaviour of Derived constraints. Derived constraints were removed in GHC 9.4 and now the code works as expected. - - - - - d7a80143 by sheaf at 2023-09-28T03:25:53-04:00 lint-codes: add new modes of operation This commit adds two new modes of operation to the lint-codes utility: list - list all statically used diagnostic codes outdated - list all outdated diagnostic codes The previous behaviour is now: test - test consistency and coverage of diagnostic codes - - - - - 477d223c by sheaf at 2023-09-28T03:25:53-04:00 lint codes: avoid using git-grep We manually traverse through the filesystem to find the diagnostic codes embedded in .stdout and .stderr files, to avoid any issues with old versions of grep. Fixes #23843 - - - - - a38ae69a by sheaf at 2023-09-28T03:25:53-04:00 lint-codes: add Hadrian targets This commit adds new Hadrian targets: codes, codes:used - list all used diagnostic codes codes:outdated - list outdated diagnostic codes This allows users to easily query GHC for used and outdated diagnostic codes, e.g. hadrian/build -j --flavour=<..> codes will list all used diagnostic codes in the command line by running the lint-codes utility in the "list codes" mode of operation. The diagnostic code consistency and coverage test is still run as usual, through the testsuite: hadrian/build test --only="codes" - - - - - 9cdd629b by Ben Gamari at 2023-09-28T03:26:29-04:00 hadrian: Install LICENSE files in bindists Fixes #23548. - - - - - b8ebf876 by Matthew Craven at 2023-09-28T03:27:05-04:00 Fix visibility when eta-reducing a type lambda Fixes #24014. - - - - - d3874407 by Torsten Schmits at 2023-09-30T16:08:10-04:00 Fix several mistakes around free variables in iface breakpoints Fixes #23612 , #23607, #23998 and #23666. MR: !11026 The fingerprinting logic in `Iface.Recomp` failed lookups when processing decls containing breakpoints for two reasons: * IfaceBreakpoint created binders for free variables instead of expressions * When collecting free names for the dependency analysis for fingerprinting, breakpoint FVs were skipped - - - - - ef5342cd by Simon Peyton Jones at 2023-09-30T16:08:48-04:00 Refactor to combine HsLam and HsLamCase This MR is pure refactoring (#23916): * Combine `HsLam` and `HsLamCase` * Combine `HsCmdLam` and `HsCmdLamCase` This just arranges to treat uniformly \x -> e \case pi -> ei \cases pis -> ie In the exising code base the first is treated differently to the latter two. No change in behaviour. More specifics: * Combine `HsLam` and `HsLamCase` (constructors of `Language.Haskell.Syntax.Expr.HsExpr`) into one data construtor covering * Lambda * `\case` * `\cases` * The new `HsLam` has an argument of type `HsLamVariant` to distinguish the three cases. * Similarly, combine `HsCmdLam` and `HsCmdLamCase` (constructors of `Language.Haskell.Syntax.Expr.HsCmd` ) into one. * Similarly, combine `mkHsLamPV` and `mkHsLamCasePV` (methods of class `DisambECP`) into one. (Thank you Alan Zimmerman.) * Similarly, combine `LambdaExpr` and `LamCaseAlt` (constructors of `Language.Haskell.Syntax.Expr.HsMatchContext`) into one: `LamAlt` with a `HsLamVariant` argument. * Similarly, combine `KappaExpr` and `ArrowLamCaseAlt` (constructors of `Language.Haskell.Syntax.Expr.HsArrowMatchContext`) into one: `ArrowLamAlt` with a `HsLamVariant` argument. * Similarly, combine `PsErrLambdaInPat` and `PsErrLambdaCaseInPat` (constructors of `GHC.Parser.Errors.Ppr.PsError`) into one. * Similarly, combine `PsErrLambdaInPat` and `PsErrLambdaCaseInPat` (constructors of `GHC.Parser.Errors.Ppr.PsError`) into one. * In the same `PsError` data type, combine `PsErrLambdaCmdInFunAppCmd` and `PsErrLambdaCaseCmdInFunAppCmd` into one. * In the same `PsError` data tpye, combine `PsErrLambdaInFunAppExpr` and `PsErrLambdaCaseInFunAppExpr` into one. p* Smilarly combine `ExpectedFunTyLam` and `ExpectedFunTyLamCase` (constructors of `GHC.Tc.Types.Origin.ExpectedFunTyOrigin`) into one. Phew! - - - - - b048bea0 by Andreas Klebinger at 2023-09-30T16:09:24-04:00 Arm: Make ppr methods easier to use by not requiring NCGConfig - - - - - 2adc0508 by Andreas Klebinger at 2023-09-30T16:09:24-04:00 AArch64: Fix broken conditional jumps for offsets >= 1MB Rewrite conditional jump instructions with offsets >= 1MB to use unconditional jumps to avoid overflowing the immediate. Fixes #23746 - - - - - 1424f790 by Alan Zimmerman at 2023-09-30T16:10:00-04:00 EPA: Replace Monoid with NoAnn We currently use the Monoid class as a constraint on Exact Print Annotation functions, so we can use mempty. But this leads to requiring Semigroup instances too, which do not always make sense. Instead, introduce a class NoAnn, with a function noAnn analogous to mempty. Closes #20372 Updates haddock submodule - - - - - c1a3ecde by Ben Gamari at 2023-09-30T16:10:36-04:00 users-guide: Refactor handling of :base-ref: et al. - - - - - bc204783 by Richard Eisenberg at 2023-10-02T14:50:52+02:00 Simplify and correct nasty case in coercion opt This fixes #21062. No test case, because triggering this code seems challenging. - - - - - 9c9ca67e by Andrew Lelechenko at 2023-10-04T05:42:28-04:00 Bump bytestring submodule to 0.12.0.2 - - - - - 4e46dc2b by Andrew Lelechenko at 2023-10-04T05:42:28-04:00 Inline bucket_match - - - - - f6b2751f by Ben Gamari at 2023-10-04T05:43:05-04:00 configure: Fix #21712 again This is a bit of a shot in the dark to fix #24033, which appears to be another instance of #21712. For some reason the ld-override logic *still* appears to be active on Darwin targets (or at least one). Consequently, on misconfigured systems we may choose a non-`ld64` linker. It's a bit unclear exactly what happened in #24033 but ultimately the check added for #21712 was not quite right, checking for the `ghc_host_os` (the value of which depends upon the bootstrap compiler) instead of the target platform. Fix this. Fixes #24033. - - - - - 2f0a101d by Krzysztof Gogolewski at 2023-10-04T05:43:42-04:00 Add a regression test for #24029 - - - - - 8cee3fd7 by sheaf at 2023-10-04T05:44:22-04:00 Fix non-symbolic children lookup of fixity decl The fix for #23664 did not correctly account for non-symbolic names when looking up children of a given parent. This one-line fix changes that. Fixes #24037 - - - - - a4785b33 by Cheng Shao at 2023-10-04T05:44:59-04:00 rts: fix incorrect ticket reference - - - - - e037f459 by Ben Gamari at 2023-10-04T05:45:35-04:00 users-guide: Fix discussion of -Wpartial-fields * fix a few typos * add a new example showing when the warning fires * clarify the existing example * point out -Wincomplete-record-selects Fixes #24049. - - - - - 8ff3134e by Matthew Pickering at 2023-10-05T05:34:58-04:00 Revert "Pass preprocessor options to C compiler when building foreign C files (#16737)" This reverts commit 1c18d3b41f897f34a93669edaebe6069f319f9e2. `-optP` should pass options to the preprocessor, that might be a very different program to the C compiler, so passing the options to the C compiler is likely to result in `-optP` being useless. Fixes #17185 and #21291 - - - - - 8f6010b9 by Ben Gamari at 2023-10-05T05:35:36-04:00 rts/nonmoving: Fix on LLP64 platforms Previously `NONMOVING_SEGMENT_MASK` and friends were defined with the `UL` size suffix. However, this is wrong on LLP64 platforms like Windows, where `long` is 32-bits. Fixes #23003. Fixes #24042. - - - - - f20d02f8 by Andreas Klebinger at 2023-10-05T05:36:14-04:00 Fix isAArch64Bitmask for 32bit immediates. Fixes #23802 - - - - - 63afb701 by Bryan Richter at 2023-10-05T05:36:49-04:00 Work around perf note fetch failure Addresses #24055. - - - - - 242102f4 by Krzysztof Gogolewski at 2023-10-05T05:37:26-04:00 Add a test for #21348 - - - - - 7d390bce by Rewbert at 2023-10-05T05:38:08-04:00 Fixes #24046 - - - - - 69abb171 by Finley McIlwaine at 2023-10-06T14:06:28-07:00 Ensure unconstrained instance dictionaries get IPE info In the `StgRhsCon` case of `GHC.Stg.Debug.collectStgRhs`, we were not coming up with an initial source span based on the span of the binder, which was causing instance dictionaries without dynamic superclass constraints to not have source locations in their IPE info. Now they do. Resolves #24005 - - - - - 390443b7 by Andreas Klebinger at 2023-10-07T10:00:20-04:00 rts: Split up rts/include/stg/MachRegs.h by arch - - - - - 3685942f by Bryan Richter at 2023-10-07T10:00:56-04:00 Actually set hackage index state Or at least, use a version of the cabal command that *claims* to set the index state. Time will tell. - - - - - 46a0e5be by Bryan Richter at 2023-10-07T10:00:56-04:00 Update hackage index state - - - - - d4b037de by Bryan Richter at 2023-10-07T10:00:56-04:00 Ensure hadrian uses CI's hackage index state - - - - - e206be64 by Andrew Lelechenko at 2023-10-08T15:06:14-04:00 Do not use O_NONBLOCK on regular files or block devices CLC proposal https://github.com/haskell/core-libraries-committee/issues/166 - - - - - a06197c4 by David Binder at 2023-10-08T15:06:55-04:00 Update hpc-bin submodule to 0.69 - - - - - ed6785b6 by David Binder at 2023-10-08T15:06:55-04:00 Update Hadrian with correct path to happy file for hpc-bin - - - - - 94066d58 by Alan Zimmerman at 2023-10-09T21:35:53-04:00 EPA: Introduce HasAnnotation class The class is defined as class HasAnnotation e where noAnnSrcSpan :: SrcSpan -> e This generalises noAnnSrcSpan, and allows noLocA :: (HasAnnotation e) => a -> GenLocated e a noLocA = L (noAnnSrcSpan noSrcSpan) - - - - - 8792a1bc by Ben Gamari at 2023-10-09T21:36:29-04:00 Bump unix submodule to v2.8.3.0 - - - - - e96c51cb by Andreas Klebinger at 2023-10-10T16:44:27+01:00 Add a flag -fkeep-auto-rules to optionally keep auto-generated rules around. The motivation for the flag is given in #21917. - - - - - 3ed58cef by Matthew Pickering at 2023-10-10T19:01:22-04:00 hadrian: Add ghcToolchain to tool args list This allows you to load ghc-toolchain and ghc-toolchain-bin into HLS. - - - - - 476c02d4 by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Normalise triple via config.sub We were not normalising the target triple anymore like we did with the old make build system. Fixes #23856 - - - - - 303dd237 by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Add missing vendor normalisation This is copied from m4/ghc_convert_vendor.m4 Towards #23868 - - - - - 838026c9 by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Add loongarch64 to parseArch Towards #23868 - - - - - 1a5bc0b5 by Matthew Pickering at 2023-10-10T19:01:22-04:00 Add same LD hack to ghc-toolchain In the ./configure script, if you pass the `LD` variable then this has the effect of stopping use searching for a linker and hence passing `-fuse-ld=...`. We want to emulate this logic in ghc-toolchain, if a use explicilty specifies `LD` variable then don't add `-fuse-ld=..` with the goal of making ./configure and ghc-toolchain agree on which flags to use when using the C compiler as a linker. This is quite unsavoury as we don't bake the choice of LD into the configuration anywhere but what's important for now is making ghc-toolchain and ./configure agree as much as possible. See #23857 for more discussion - - - - - 42d50b5a by Ben Gamari at 2023-10-10T19:01:22-04:00 ghc-toolchain: Check for C99 support with -std=c99 Previously we failed to try enabling C99 support with `-std=c99`, as `autoconf` attempts. This broke on older compilers (e.g. CentOS 7) which don't enable C99 by default. Fixes #23879. - - - - - da2961af by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Add endianess check using __BYTE_ORDER__ macro In very old toolchains the BYTE_ORDER macro is not set but thankfully the __BYTE_ORDER__ macro can be used instead. - - - - - d8da73cd by Matthew Pickering at 2023-10-10T19:01:22-04:00 configure: AC_PATH_TARGET_TOOL for LD We want to make sure that LD is set to an absolute path in order to be consistent with the `LD=$(command -v ld)` call. The AC_PATH_TARGET_TOOL macro uses the absolute path rather than AC_CHECK_TARGET_TOOL which might use a relative path. - - - - - 171f93cc by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Check whether we need -std=gnu99 for CPP as well In ./configure the C99 flag is passed to the C compiler when used as a C preprocessor. So we also check the same thing in ghc-toolchain. - - - - - 89a0918d by Matthew Pickering at 2023-10-10T19:01:22-04:00 Check for --target linker flag separately to C compiler There are situations where the C compiler doesn't accept `--target` but when used as a linker it does (but doesn't do anything most likely) In particular with old gcc toolchains, the C compiler doesn't support --target but when used as a linker it does. - - - - - 37218329 by Matthew Pickering at 2023-10-10T19:01:22-04:00 Use Cc to compile test file in nopie check We were attempting to use the C compiler, as a linker, to compile a file in the nopie check, but that won't work in general as the flags we pass to the linker might not be compatible with the ones we pass when using the C compiler. - - - - - 9b2dfd21 by Matthew Pickering at 2023-10-10T19:01:22-04:00 configure: Error when ghc-toolchain fails to compile This is a small QOL change as if you are working on ghc-toolchain and it fails to compile then configure will continue and can give you outdated results. - - - - - 1f0de49a by Matthew Pickering at 2023-10-10T19:01:22-04:00 configure: Check whether -no-pie works when the C compiler is used as a linker `-no-pie` is a flag we pass when using the C compiler as a linker (see pieCCLDOpts in GHC.Driver.Session) so we should test whether the C compiler used as a linker supports the flag, rather than just the C compiler. - - - - - 62cd2579 by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Remove javascript special case for --target detection emcc when used as a linker seems to ignore the --target flag, and for consistency with configure which now tests for --target, we remove this special case. - - - - - 0720fde7 by Ben Gamari at 2023-10-10T19:01:22-04:00 toolchain: Don't pass --target to emscripten toolchain As noted in `Note [Don't pass --target to emscripten toolchain]`, emscripten's `emcc` is rather inconsistent with respect to its treatment of the `--target` flag. Avoid this by special-casing this toolchain in the `configure` script and `ghc-toolchain`. Fixes on aspect of #23744. - - - - - 6354e1da by Matthew Pickering at 2023-10-10T19:01:22-04:00 hadrian: Don't pass `--gcc-options` as a --configure-arg to cabal configure Stop passing -gcc-options which mixed together linker flags and non-linker flags. There's no guarantee the C compiler will accept both of these in each mode. - - - - - c00a4bd6 by Ben Gamari at 2023-10-10T19:01:22-04:00 configure: Probe stage0 link flags For consistency with later stages and CC. - - - - - 1f11e7c4 by Sebastian Graf at 2023-10-10T19:01:58-04:00 Stricter Binary.get in GHC.Types.Unit (#23964) I noticed some thunking while looking at Core. This change has very modest, but throughout positive ghc/alloc effect: ``` hard_hole_fits(normal) ghc/alloc 283,057,664 281,620,872 -0.5% geo. mean -0.1% minimum -0.5% maximum +0.0% ``` Fixes #23964. - - - - - a4f1a181 by Bryan Richter at 2023-10-10T19:02:37-04:00 rel_eng/upload.sh cleanups - - - - - 80705335 by doyougnu at 2023-10-10T19:03:18-04:00 ci: add javascript label rule This adds a rule which triggers the javascript job when the "javascript" label is assigned to an MR. - - - - - a2c0fff6 by Matthew Craven at 2023-10-10T19:03:54-04:00 Make 'wWarningFlagsDeps' include every WarningFlag Fixes #24071. - - - - - d055f099 by Jan Hrček at 2023-10-10T19:04:33-04:00 Fix pretty printing of overlap pragmas in TH splices (fixes #24074) - - - - - 0746b868 by Andreas Klebinger at 2023-10-10T19:05:09-04:00 Aarch64 NCG: Use encoded immediates for literals. Try to generate instr x2, <imm> instead of mov x1, lit instr x2, x1 When possible. This get's rid if quite a few redundant mov instructions. I believe this causes a metric decrease for LargeRecords as we reduce register pressure. ------------------------- Metric Decrease: LargeRecord ------------------------- - - - - - 739f4e6f by Andreas Klebinger at 2023-10-10T19:05:09-04:00 AArch NCG: Refactor getRegister' Remove some special cases which can be handled just as well by the generic case. This increases code re-use while also fixing #23749. Since some of the special case wasn't upholding Note [Signed arithmetic on AArch64]. - - - - - 1b213d33 by Andreas Klebinger at 2023-10-10T19:05:09-04:00 Aarch ncg: Optimize immediate use for address calculations When the offset doesn't fit into the immediate we now just reuse the general getRegister' code path which is well optimized to compute the offset into a register instead of a special case for CmmRegOff. This means we generate a lot less code under certain conditions which is why performance metrics for these improve. ------------------------- Metric Decrease: T4801 T5321FD T5321Fun ------------------------- - - - - - b7df0732 by John Ericson at 2023-10-11T16:02:11-04:00 RTS configure: Move over mem management checks These are for heap allocation, a strictly RTS concern. All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. The RTS configure one has a new ``` AC_CHECK_SIZEOF([void *]) ``` that the top-level configure version didn't have, so that `ac_cv_sizeof_void_p` is defined. Once more code is moved over in latter commits, that can go away. Progress towards #17191 - - - - - 41130a65 by John Ericson at 2023-10-11T16:02:11-04:00 RTS configure: Move over `__thread` check This used by (@bgamari thinks) the `GCThread` abstraction in the RTS. All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. Progress towards #17191 - - - - - cc5ec2bd by John Ericson at 2023-10-11T16:02:11-04:00 RTS configure: Move over misc function checks These are for general use in the RTS. All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. Progress towards #17191 - - - - - 809e7c2d by John Ericson at 2023-10-11T16:02:11-04:00 RTS configure: Move over `eventfd` check This check is for the RTS part of the event manager and has a corresponding part in `base`. All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. Progress towards #17191 - - - - - 58f3babf by John Ericson at 2023-10-11T16:02:48-04:00 Split `FP_CHECK_PTHREADS` and move part to RTS configure `NEED_PTHREAD_LIB` is unused since 3609340743c1b25fdfd0e18b1670dac54c8d8623 (part of the make build system), and so is no longer defined. Progress towards #17191 - - - - - e99cf237 by Moritz Angermann at 2023-10-11T16:03:24-04:00 nativeGen: section flags for .text$foo only Commit 3ece9856d157c85511d59f9f862ab351bbd9b38b, was supposed to fix #22834 in !9810. It does however add "xr" indiscriminatly to .text sections even if splitSections is disabled. This leads to the assembler saying: ghc_1.s:7849:0: error: Warning: Ignoring changed section attributes for .text | 7849 | .section .text,"xr" | ^ - - - - - f383a242 by Sylvain Henry at 2023-10-11T16:04:04-04:00 Modularity: pass TempDir instead of DynFlags (#17957) - - - - - 34fc28b0 by John Ericson at 2023-10-12T06:48:28-04:00 Test that functions from `mingwex` are available Ryan wrote these two minimizations, but they never got added to the test suite. See #23309, #23378 Co-Authored-By: Ben Gamari <bgamari.foss at gmail.com> Co-Authored-By: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - bdb54a0e by John Ericson at 2023-10-12T06:48:28-04:00 Do not check for the `mingwex` library in `/configure` See the recent discussion in !10360 --- Cabal will itself check for the library for the packages that need it, and while the autoconf check additionally does some other things like define a `HAS_LIBMINGWEX` C Preprocessor macro, those other things are also unused and unneeded. Progress towards #17191, which aims to get rid of `/configure` entirely. - - - - - 43e814e1 by Ben Gamari at 2023-10-12T06:49:40-04:00 base: Introduce move modules into src The only non-move changes here are whitespace changes to pass the `whitespace` test and a few testsuite adaptations. - - - - - df81536f by Moritz Angermann at 2023-10-12T06:50:16-04:00 [PEi386 linker] Bounds check and null-deref guard We should resonably be able to expect that we won't exceed the number of sections if we assume to be dealing with legal object files. We can however not guarantee that we get some negative values, and while we try to special case most, we should exclude negative indexing into the sections array. We also need to ensure that we do not try to derefences targetSection, if it is NULL, due to the switch statement. - - - - - c74c4f00 by John Ericson at 2023-10-12T10:31:13-04:00 Move apple compat check to RTS configure - - - - - c80778ea by John Ericson at 2023-10-12T10:31:13-04:00 Move clock/timer fun checks to RTS configure Actual library check (which will set the Cabal flag) is left in the top-level configure for now. Progress towards #17191 - - - - - 7f9f2686 by John Ericson at 2023-10-12T10:31:13-04:00 Move visibility and "musttail" annotation checks to the RTS configure All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. Progress towards #17191 - - - - - ffb3efe6 by John Ericson at 2023-10-12T10:31:13-04:00 Move leading underscore checks to RTS configure `CabalLeadingUnderscore` is done via Hadrian already, so we can stop `AC_SUBST`ing it completely. - - - - - 25fa4b02 by John Ericson at 2023-10-12T10:31:13-04:00 Move alloca, fork, const, and big endian checks to RTS configure All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. - - - - - 5170f42a by John Ericson at 2023-10-12T10:31:13-04:00 Move libdl check to RTS configure - - - - - ea7a1447 by John Ericson at 2023-10-12T10:31:13-04:00 Adjust `FP_FIND_LIBFFI` Just set vars, and `AC_SUBST` in top-level configure. Don't define `HAVE_SYSTEM_LIBFFI` because nothing is using it. It hasn't be in used since 3609340743c1b25fdfd0e18b1670dac54c8d8623 (part of the make build system). - - - - - f399812c by John Ericson at 2023-10-12T10:31:13-04:00 Split BFD support to RTS configure The flag is still in the top-level configure, but the other checks (which define various macros --- important) are in the RTS configure. - - - - - f64f44e9 by John Ericson at 2023-10-12T10:31:13-04:00 Split libm check between top level and RTS - - - - - dafc4709 by Moritz Angermann at 2023-10-12T10:31:49-04:00 CgUtils.fixStgRegStmt respect register width This change ensure that the reg + offset computation is always of the same size. Before this we could end up with a 64bit register, and then add a 32bit offset (on 32bit platforms). This not only would fail type sanity checking, but also incorrectly truncate 64bit values into 32bit values silently on 32bit architectures. - - - - - 9e6ef7ba by Matthew Pickering at 2023-10-12T20:35:00-04:00 hadrian: Decrease verbosity of cabal commands In Normal, most tools do not produce output to stdout unless there are error conditions. Reverts 7ed65f5a1bc8e040e318ccff395f53a9bbfd8217 - - - - - 08fc27af by John Ericson at 2023-10-12T20:35:36-04:00 Do not substitute `@...@` for stage-specific values in cabal files `rts` and `ghc-prim` now no longer have a `*.cabal.in` to set Cabal flag defaults; instead manual choices are passed to configure in the usual way. The old way was fundamentally broken, because it meant we were baking these Cabal files for a specific stage. Now we only do stage-agnostic @...@ substitution in cabal files (the GHC version), and so all stage-specific configuration is properly confined to `_build` and the right stage dir. Also `include-ghc-prim` is a flag that no longer exists for `ghc-prim` (it was removed in 835d8ddbbfb11796ea8a03d1806b7cee38ba17a6) so I got rid of it. Co-Authored-By: Matthew Pickering <matthewtpickering at gmail.com> - - - - - a0ac8785 by Sebastian Graf at 2023-10-14T19:17:12-04:00 Fix restarts in .ghcid Using the whole of `hadrian/` restarted in a loop for me. - - - - - fea9ecdb by Sebastian Graf at 2023-10-14T19:17:12-04:00 CorePrep: Refactor FloatingBind (#23442) A drastically improved architecture for local floating in CorePrep that decouples the decision of whether a float is going to be let- or case-bound from how far it can float (out of strict contexts, out of lazy contexts, to top-level). There are a couple of new Notes describing the effort: * `Note [Floating in CorePrep]` for the overview * `Note [BindInfo and FloatInfo]` for the new classification of floats * `Note [Floats and FloatDecision]` for how FloatInfo is used to inform floating decisions This is necessary ground work for proper treatment of Strict fields and unlifted values at top-level. Fixes #23442. NoFib results (omitted = 0.0%): ``` -------------------------------------------------------------------------------- Program Allocs Instrs -------------------------------------------------------------------------------- pretty 0.0% -1.6% scc 0.0% -1.7% -------------------------------------------------------------------------------- Min 0.0% -1.7% Max 0.0% -0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 32523713 by Matthew Pickering at 2023-10-14T19:17:49-04:00 hadrian: Move ghcBinDeps into ghcLibDeps This completes a5227080b57cb51ac34d4c9de1accdf6360b818b, the `ghc-usage.txt` and `ghci-usage.txt` file are also used by the `ghc` library so need to make sure they are present in the libdir even if we are not going to build `ghc-bin`. This also fixes things for cross compilers because the stage2 cross-compiler requires the ghc-usage.txt file, but we are using the stage2 lib folder but not building stage3:exe:ghc-bin so ghc-usage.txt was not being generated. - - - - - ec3c4488 by sheaf at 2023-10-14T19:18:29-04:00 Combine GREs when combining in mkImportOccEnv In `GHC.Rename.Names.mkImportOccEnv`, we sometimes discard one import item in favour of another, as explained in Note [Dealing with imports] in `GHC.Rename.Names`. However, this can cause us to lose track of important parent information. Consider for example #24084: module M1 where { class C a where { type T a } } module M2 ( module M1 ) where { import M1 } module M3 where { import M2 ( C, T ); instance C () where T () = () } When processing the import list of `M3`, we start off (for reasons that are not relevant right now) with two `Avail`s attached to `T`, namely `C(C, T)` and `T(T)`. We combine them in the `combine` function of `mkImportOccEnv`; as described in Note [Dealing with imports] we discard `C(C, T)` in favour of `T(T)`. However, in doing so, we **must not** discard the information want that `C` is the parent of `T`. Indeed, losing track of this information can cause errors when importing, as we could get an error of the form ‘T’ is not a (visible) associated type of class ‘C’ We fix this by combining the two GREs for `T` using `plusGRE`. Fixes #24084 - - - - - 257c2807 by Ilias Tsitsimpis at 2023-10-14T19:19:07-04:00 hadrian: Pass -DNOSMP to C compiler when needed Hadrian passes the -DNOSMP flag to GHC when the target doesn't support SMP, but doesn't pass it to CC as well, leading to the following compilation error on mips64el: | Run Cc (FindCDependencies CDep) Stage1: rts/sm/NonMovingScav.c => _build/stage1/rts/build/c/sm/NonMovingScav.o.d Command line: /usr/bin/mips64el-linux-gnuabi64-gcc -E -MM -MG -MF _build/stage1/rts/build/c/hooks/FlagDefaults.thr_debug_p_o.d -MT _build/stage1/rts/build/c/hooks/FlagDefaults.o -Irts/include -I_build/stage1/rts/build -I_build/stage1/rts/build/include -Irts/include -x c rts/hooks/FlagDefaults.c -Wall -Wextra -Wstrict-prototypes -Wmissing-prototypes -Wmissing-declarations -Winline -Wpointer-arith -Wmissing-noreturn -Wnested-externs -Wredundant-decls -Wundef -fno-strict-aliasing -DTHREADED_RTS -DDEBUG -fomit-frame-pointer -O2 -g -Irts -I_build/stage1/rts/build -DDEBUG -fno-omit-frame-pointer -g3 -O0 ===> Command failed with error code: 1 In file included from rts/include/Stg.h:348, from rts/include/Rts.h:38, from rts/hooks/FlagDefaults.c:8: rts/include/stg/SMP.h:416:2: error: #error memory barriers unimplemented on this architecture 416 | #error memory barriers unimplemented on this architecture | ^~~~~ rts/include/stg/SMP.h:440:2: error: #error memory barriers unimplemented on this architecture 440 | #error memory barriers unimplemented on this architecture | ^~~~~ rts/include/stg/SMP.h:464:2: error: #error memory barriers unimplemented on this architecture 464 | #error memory barriers unimplemented on this architecture | ^~~~~ The old make system correctly passed this flag to both GHC and CC [1]. Fix this error by passing -DNOSMP to CC as well. [1] https://gitlab.haskell.org/ghc/ghc/-/blob/00920f176b0235d5bb52a8e054d89a664f8938fe/rts/ghc.mk#L407 Closes #24082 - - - - - 13d3c613 by John Ericson at 2023-10-14T19:19:42-04:00 Users Guide: Drop dead code for Haddock refs to `parallel` I noticed while working on !11451 that `@LIBRARY_parallel_UNIT_ID@` was not substituted. It is dead code -- there is no `parallel-ref` usages and it doesn't look like there ever was (going back to 3e5d0f188d6c8633e55e9ba6c8941c07e459fa4b), so let's delete it. - - - - - fe067577 by Sylvain Henry at 2023-10-18T19:40:25-04:00 Avoid out-of-bound array access in bigNatIsPowerOf2 (fix #24066) bigNatIndex# in the `where` clause wasn't guarded by "bigNatIsZero a". - - - - - cc1625b1 by Sylvain Henry at 2023-10-18T19:40:25-04:00 Bignum: fix right shift of negative BigNat with native backend - - - - - cbe4400d by Sylvain Henry at 2023-10-18T19:40:25-04:00 Rts: expose rtsOutOfBoundsAccess symbol - - - - - 72c7380c by Sylvain Henry at 2023-10-18T19:40:25-04:00 Hadrian: enable `-fcheck-prim-bounds` in validate flavour This allows T24066 to fail when the bug is present. Otherwise the out-of-bound access isn't detected as it happens in ghc-bignum which wasn't compiled with the bounds check. - - - - - f9436990 by John Ericson at 2023-10-18T19:41:01-04:00 Make Hadrian solely responsible for substituting `docs/users_guide/ghc_config.py.in` Fixes #24091 Progress on #23966 Issue #24091 reports that `@ProjectVersion@` is no longer being substituted in the GHC user's guide. I assume this is a recent issue, but I am not sure how it's worked since c1a3ecde720b3bddc2c8616daaa06ee324e602ab; it looks like both Hadrian and configure are trying to substitute the same `.in` file! Now only Hadrian does. That is better anyways; already something that issue #23966 requested. It seems like we were missing some dependencies in Hadrian. (I really, really hate that this is possible!) Hopefully it is fixed now. - - - - - b12df0bb by John Ericson at 2023-10-18T19:41:37-04:00 `ghcversion.h`: No need to cope with undefined `ProjectPatchLevel*` Since 4e6c80197f1cc46dfdef0300de46847c7cfbdcb0, these are guaranteed to be defined. (Guaranteed including a test in the testsuite.) - - - - - 0295375a by John Ericson at 2023-10-18T19:41:37-04:00 Generate `ghcversion.h` from a `.in` file Now that there are no conditional sections (see the previous commit), we can just a do simple substitution rather than pasting it together line by line. Progress on #23966 - - - - - 740a1b85 by Krzysztof Gogolewski at 2023-10-19T11:37:20-04:00 Add a regression test for #24064 - - - - - 921fbf2f by Hécate Moonlight at 2023-10-19T11:37:59-04:00 CLC Proposal #182: Export List from Data.List Proposal link: https://github.com/haskell/core-libraries-committee/issues/182 - - - - - 4f02d3c1 by Sylvain Henry at 2023-10-20T04:01:32-04:00 rts: fix small argument passing on big-endian arch (fix #23387) - - - - - b86243b4 by Sylvain Henry at 2023-10-20T04:02:13-04:00 Interpreter: fix literal alignment on big-endian architectures (fix #19261) Literals weren't correctly aligned on big-endian, despite what the comment said. - - - - - a4b2ec47 by Sylvain Henry at 2023-10-20T04:02:54-04:00 Testsuite: recomp011 and recomp015 are fixed on powerpc These tests have been fixed but not tested and re-enabled on big-endian powerpc (see comments in #11260 and #11323) - - - - - fded7dd4 by Sebastian Graf at 2023-10-20T04:03:30-04:00 CorePrep: Allow floating dictionary applications in -O0 into a Rec (#24102) - - - - - 02efc181 by John Ericson at 2023-10-22T02:48:55-04:00 Move function checks to RTS configure Some of these functions are used in `base` too, but we can copy the checks over to its configure if that's an issue. - - - - - 5f4bccab by John Ericson at 2023-10-22T02:48:55-04:00 Move over a number of C-style checks to RTS configure - - - - - 5cf04f58 by John Ericson at 2023-10-22T02:48:55-04:00 Move/Copy more `AC_DEFINE` to RTS config Only exception is the LLVM version macros, which are used for GHC itself. - - - - - b8ce5dfe by John Ericson at 2023-10-22T02:48:55-04:00 Define `TABLES_NEXT_TO_CODE` in the RTS configure We create a new cabal flag to facilitate this. - - - - - 4a40271e by John Ericson at 2023-10-22T02:48:55-04:00 Configure scripts: `checkOS`: Make a bit more robust `mingw64` and `mingw32` are now both accepted for `OSMinGW32`. This allows us to cope with configs/triples that we haven't normalized extra being what GNU `config.sub` does. - - - - - 16bec0a0 by John Ericson at 2023-10-22T02:48:55-04:00 Generate `ghcplatform.h` from RTS configure We create a new cabal flag to facilitate this. - - - - - 7dfcab2f by John Ericson at 2023-10-22T02:48:55-04:00 Get rid of all mention of `mk/config.h` The RTS configure script is now solely responsible for managing its headers; the top level configure script does not help. - - - - - c1e3719c by Cheng Shao at 2023-10-22T02:49:33-04:00 rts: drop stale mentions of MIN_UPD_SIZE We used to have MIN_UPD_SIZE macro that describes the minimum reserved size for thunks, so that the thunk can be overwritten in place as indirections or blackholes. However, this macro has not been actually defined or used anywhere since a long time ago; StgThunkHeader already reserves a padding word for this purpose. Hence this patch which drops stale mentions of MIN_UPD_SIZE. - - - - - d24b0d85 by Andrew Lelechenko at 2023-10-22T02:50:11-04:00 base changelog: move non-backported entries from 4.19 section to 4.20 Neither !10933 (check https://hackage.haskell.org/package/base-4.19.0.0/docs/src/Text.Read.Lex.html#numberToRangedRational) nor !10189 (check https://hackage.haskell.org/package/base-4.19.0.0/docs/src/Data.List.NonEmpty.html#unzip) were backported to `base-4.19.0.0`. Moving them to `base-4.20.0.0` section. Also minor stylistic changes to other entries, bringing them to a uniform form. - - - - - de78b32a by Alan Zimmerman at 2023-10-23T09:09:41-04:00 EPA Some tweaks to annotations - Fix span for GRHS - Move TrailingAnns from last match to FunBind - Fix GADT 'where' clause span - Capture full range for a CaseAlt Match - - - - - d5a8780d by Simon Hengel at 2023-10-23T09:10:23-04:00 Update primitives.rst - - - - - 4d075924 by Josh Meredith at 2023-10-24T23:04:12+11:00 JS/userguide: add explanation of writing jsbits - - - - - 07ab5cc1 by Cheng Shao at 2023-10-24T15:40:32-04:00 testsuite: increase timeout of ghc-api tests for wasm32 ghc-api tests for wasm32 are more likely to timeout due to the large wasm module sizes, especially when testing with wasm native tail calls, given wasmtime's handling of tail call opcodes are suboptimal at the moment. It makes sense to increase timeout specifically for these tests on wasm32. This doesn't affect other targets, and for wasm32 we don't increase timeout for all tests, so not to risk letting major performance regressions slip through the testsuite. - - - - - 0d6acca5 by Greg Steuck at 2023-10-26T08:44:23-04:00 Explicitly require RLIMIT_AS before use in OSMem.c This is done elsewhere in the source tree. It also suddenly is required on OpenBSD. - - - - - 9408b086 by Sylvain Henry at 2023-10-26T08:45:03-04:00 Modularity: modularize external linker Decouple runLink from DynFlags to allow calling runLink more easily. This is preliminary work for calling Emscripten's linker (emcc) from our JavaScript linker. - - - - - e0f35030 by doyougnu at 2023-10-27T08:41:12-04:00 js: add JStg IR, remove unsaturated constructor - Major step towards #22736 and adding the optimizer in #22261 - - - - - 35587eba by Simon Peyton Jones at 2023-10-27T08:41:48-04:00 Fix a bug in tail calls with ticks See #24078 for the diagnosis. The change affects only the Tick case of occurrence analysis. It's a bit hard to test, so no regression test (yet anyway). - - - - - 9bc5cb92 by Matthew Craven at 2023-10-28T07:06:17-04:00 Teach tag-inference about SeqOp/seq# Fixes the STG/tag-inference analogue of #15226. Co-Authored-By: Simon Peyton Jones <simon.peytonjones at gmail.com> - - - - - 34f06334 by Moritz Angermann at 2023-10-28T07:06:53-04:00 [PEi386] Mask SYM_TYPE_DUP_DISCARD in makeSymbolExtra 48e391952c17ff7eab10b0b1456e3f2a2af28a9b introduced `SYM_TYPE_DUP_DISCARD` to the bitfield. The linker however, failed to mask the `SYM_TYPE_DUP_DISCARD` value. Thus `== SYM_TYPE_CODE` comparisons easily failed. This lead to us relocating DATA lookups (GOT) into E8 (call) and E9 (jump) instructions. - - - - - 5b51b2a2 by Mario Blažević at 2023-10-28T07:07:33-04:00 Fix and test for issue #24111, TH.Ppr output of pattern synonyms - - - - - 723bc352 by Alan Zimmerman at 2023-10-30T20:36:41-04:00 EPA: print doc comments as normal comments And ignore the ones allocated in haddock processing. It does not guarantee that every original haddock-like comment appears in the output, as it discards ones that have no legal attachment point. closes #23459 - - - - - 21b76843 by Simon Peyton Jones at 2023-10-30T20:37:17-04:00 Fix non-termination bug in equality solver constraint left-to-right then right to left, forever. Easily fixed. - - - - - 270867ac by Sebastian Graf at 2023-10-30T20:37:52-04:00 ghc-toolchain: build with `-package-env=-` (#24131) Otherwise globally installed libraries (via `cabal install --lib`) break the build. Fixes #24131. - - - - - 4d08364e by Alan Zimmerman at 2023-10-31T19:46:45+00:00 EPA: match changes in GHC - EPA: Comments in AnchorOperation - EPA: Remove EpaEofComment - - - - - 7a90020f by Krzysztof Gogolewski at 2023-10-31T20:03:37-04:00 docs: fix ScopedTypeVariables example (#24101) The previous example didn't compile. Furthermore, it wasn't demonstrating the point properly. I have changed it to an example which shows that 'a' in the signature must be the same 'a' as in the instance head. - - - - - 49f69f50 by Krzysztof Gogolewski at 2023-10-31T20:04:13-04:00 Fix pretty-printing of type family dependencies "where" should be after the injectivity annotation. - - - - - 73c191c0 by Ben Gamari at 2023-10-31T20:04:49-04:00 gitlab-ci: Bump LLVM bootstrap jobs to Debian 12 As the Debian 10 images have too old an LLVM. Addresses #24056. - - - - - 5b0392e0 by Matthew Pickering at 2023-10-31T20:04:49-04:00 ci: Run aarch64 llvm backend job with "LLVM backend" label This brings it into line with the x86 LLVM backend job. - - - - - 9f9c9227 by Ryan Scott at 2023-11-01T09:19:12-04:00 More robust checking for DataKinds As observed in #22141, GHC was not doing its due diligence in catching code that should require `DataKinds` in order to use. Most notably, it was allowing the use of arbitrary data types in kind contexts without `DataKinds`, e.g., ```hs data Vector :: Nat -> Type -> Type where ``` This patch revamps how GHC tracks `DataKinds`. The full specification is written out in the `DataKinds` section of the GHC User's Guide, and the implementation thereof is described in `Note [Checking for DataKinds]` in `GHC.Tc.Validity`. In brief: * We catch _type_-level `DataKinds` violations in the renamer. See `checkDataKinds` in `GHC.Rename.HsType` and `check_data_kinds` in `GHC.Rename.Pat`. * We catch _kind_-level `DataKinds` violations in the typechecker, as this allows us to catch things that appear beneath type synonyms. (We do *not* want to do this in type-level contexts, as it is perfectly fine for a type synonym to mention something that requires DataKinds while still using the type synonym in a module that doesn't enable DataKinds.) See `checkValidType` in `GHC.Tc.Validity`. * There is now a single `TcRnDataKindsError` that classifies all manner of `DataKinds` violations, both in the renamer and the typechecker. The `NoDataKindsDC` error has been removed, as it has been subsumed by `TcRnDataKindsError`. * I have added `CONSTRAINT` is `isKindTyCon`, which is what checks for illicit uses of data types at the kind level without `DataKinds`. Previously, `isKindTyCon` checked for `Constraint` but not `CONSTRAINT`. This is inconsistent, given that both `Type` and `TYPE` were checked by `isKindTyCon`. Moreover, it thwarted the implementation of the `DataKinds` check in `checkValidType`, since we would expand `Constraint` (which was OK without `DataKinds`) to `CONSTRAINT` (which was _not_ OK without `DataKinds`) and reject it. Now both are allowed. * I have added a flurry of additional test cases that test various corners of `DataKinds` checking. Fixes #22141. - - - - - 575d7690 by Sylvain Henry at 2023-11-01T09:19:53-04:00 JS: fix FFI "wrapper" and "dynamic" Fix codegen and helper functions for "wrapper" and "dynamic" foreign imports. Fix tests: - ffi006 - ffi011 - T2469 - T4038 Related to #22363 - - - - - 81fb8885 by Alan Zimmerman at 2023-11-01T22:23:56-04:00 EPA: Use full range for Anchor This change requires a series of related changes, which must all land at the same time, otherwise all the EPA tests break. * Use the current Anchor end as prior end Use the original anchor location end as the source of truth for calculating print deltas. This allows original spacing to apply in most cases, only changed AST items need initial delta positions. * Add DArrow to TrailingAnn * EPA Introduce HasTrailing in ExactPrint Use [TrailingAnn] in enterAnn and remove it from ExactPrint (LocatedN RdrName) * In HsDo, put TrailingAnns at top of LastStmt * EPA: do not convert comments to deltas when balancing. * EPA: deal with fallout from getMonoBind * EPA fix captureLineSpacing * EPA print any comments in the span before exiting it * EPA: Add comments to AnchorOperation * EPA: remove AnnEofComment, it is no longer used Updates Haddock submodule - - - - - 03e82511 by Rodrigo Mesquita at 2023-11-01T22:24:32-04:00 Fix in docs regarding SSymbol, SNat, SChar (#24119) - - - - - 362cc693 by Matthew Pickering at 2023-11-01T22:25:08-04:00 hadrian: Update bootstrap plans (9.4.6, 9.4.7, 9.6.2, 9.6.3, 9.8.1) Updating the bootstrap plans with more recent GHC versions. - - - - - 00b9b8d3 by Matthew Pickering at 2023-11-01T22:25:08-04:00 ci: Add 9.8.1 bootstrap testing job - - - - - ef3d20f8 by Matthew Pickering at 2023-11-01T22:25:08-04:00 Compatibility with 9.8.1 as boot compiler This fixes several compatability issues when using 9.8.1 as the boot compiler. * An incorrect version guard on the stack decoding logic in ghc-heap * Some ghc-prim bounds need relaxing * ghc is no longer wired in, so we have to remove the -this-unit-id ghc call. Fixes #24077 - - - - - 6755d833 by Jaro Reinders at 2023-11-03T10:54:42+01:00 Add NCG support for common 64bit operations to the x86 backend. These used to be implemented via C calls which was obviously quite bad for performance for operations like simple addition. Co-authored-by: Andreas Klebinger - - - - - 0dfb1fa7 by Vladislav Zavialov at 2023-11-03T14:08:41-04:00 T2T in Expressions (#23738) This patch implements the T2T (term-to-type) transformation in expressions. Given a function with a required type argument vfun :: forall a -> ... the user can now call it as vfun (Maybe Int) instead of vfun (type (Maybe Int)) The Maybe Int argument is parsed and renamed as a term (HsExpr), but then undergoes a conversion to a type (HsType). See the new function expr_to_type in compiler/GHC/Tc/Gen/App.hs and Note [RequiredTypeArguments and the T2T mapping] Left as future work: checking for puns. - - - - - cc1c7c54 by Duncan Coutts at 2023-11-05T00:23:44-04:00 Add a test for I/O managers It tries to cover the cases of multiple threads waiting on the same fd for reading and multiple threads waiting for writing, including wait cancellation by async exceptions. It should work for any I/O manager, in-RTS or in-Haskell. Unfortunately it will not currently work for Windows because it relies on anonymous unix sockets. It could in principle be ported to use Windows named pipes. - - - - - 2e448f98 by Cheng Shao at 2023-11-05T00:23:44-04:00 Skip the IOManager test on wasm32 arch. The test relies on the sockets API which are not (yet) available. - - - - - fe50eb35 by Cheng Shao at 2023-11-05T00:24:20-04:00 compiler: fix eager blackhole symbol in wasm32 NCG - - - - - af771148 by Cheng Shao at 2023-11-05T00:24:20-04:00 testsuite: fix optasm tests for wasm32 - - - - - 1b90735c by Matthew Pickering at 2023-11-05T00:24:20-04:00 testsuite: Add wasm32 to testsuite arches with NCG The compiler --info reports that wasm32 compilers have a NCG, so we should agree with that here. - - - - - db9a6496 by Alan Zimmerman at 2023-11-05T00:24:55-04:00 EPA: make locA a function, not a field name And use it to generalise reLoc The following for the windows pipeline one. 5.5% Metric Increase: T5205 - - - - - 833e250c by Simon Peyton Jones at 2023-11-05T00:25:31-04:00 Update the unification count in wrapUnifierX Omitting this caused type inference to fail in #24146. This was an accidental omision in my refactoring of the equality solver. - - - - - e451139f by Andreas Klebinger at 2023-11-05T00:26:07-04:00 Remove an accidental git conflict marker from a comment. - - - - - e7da0d25 by Alan Zimmerman at 2023-11-05T11:20:31+00:00 EPA: match changes in GHC, l2l cleanup - - - - - 30baac7a by Tobias Haslop at 2023-11-06T10:50:32+00:00 Add laws relating between Foldable/Traversable with their Bi- superclasses See https://github.com/haskell/core-libraries-committee/issues/205 for discussion. This commit also documents that the tuple instances only satisfy the laws up to lazyness, similar to the documentation added in !9512. - - - - - df626f00 by Tobias Haslop at 2023-11-07T02:20:37-05:00 Elaborate on the quantified superclass of Bifunctor This was requested in the comment https://github.com/haskell/core-libraries-committee/issues/93#issuecomment-1597271700 for when Traversable becomes a superclass of Bitraversable, but similarly applies to Functor/Bifunctor, which already are in a superclass relationship. - - - - - 8217acb8 by Alan Zimmerman at 2023-11-07T02:21:12-05:00 EPA: get rid of l2l and friends Replace them with l2l to convert the location la2la to convert a GenLocated thing Updates haddock submodule - - - - - dd88a260 by Luite Stegeman at 2023-11-07T02:21:53-05:00 JS: remove broken newIdents from JStg Monad GHC.JS.JStg.Monad.newIdents was broken, resulting in duplicate identifiers being generated in h$c1, h$c2, ... . This change removes the broken newIdents. - - - - - 455524a2 by Matthew Craven at 2023-11-09T08:41:59-05:00 Create specially-solved DataToTag class Closes #20532. This implements CLC proposal 104: https://github.com/haskell/core-libraries-committee/issues/104 The design is explained in Note [DataToTag overview] in GHC.Tc.Instance.Class. This replaces the existing `dataToTag#` primop. These metric changes are not "real"; they represent Unique-related flukes triggering on a different set of jobs than they did previously. See also #19414. Metric Decrease: T13386 T8095 Metric Increase: T13386 T8095 Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> - - - - - a05f4554 by Alan Zimmerman at 2023-11-09T08:42:35-05:00 EPA: get rid of glRR and friends in GHC/Parser.y With the HasLoc and HasAnnotation classes, we can replace a number of type-specific helper functions in the parser with polymorphic ones instead Metric Decrease: MultiLayerModulesTH_Make - - - - - 18498538 by Cheng Shao at 2023-11-09T16:58:12+00:00 ci: bump ci-images for wasi-sdk upgrade - - - - - 52c0fc69 by PHO at 2023-11-09T19:16:22-05:00 Don't assume the current locale is *.UTF-8, set the encoding explicitly primops.txt contains Unicode characters: > LC_ALL=C ./genprimopcode --data-decl < ./primops.txt > genprimopcode: <stdin>: hGetContents: invalid argument (cannot decode byte sequence starting from 226) Hadrian must also avoid using readFile' to read primops.txt because it tries to decode the file with a locale-specific encoding. - - - - - 7233b3b1 by PHO at 2023-11-09T19:17:01-05:00 Use '[' instead of '[[' because the latter is a Bash-ism It doesn't work on platforms where /bin/sh is something other than Bash. - - - - - 6dbab180 by Simon Peyton Jones at 2023-11-09T19:17:36-05:00 Add an extra check in kcCheckDeclHeader_sig Fix #24083 by checking for a implicitly-scoped type variable that is not actually bound. See Note [Disconnected type variables] in GHC.Tc.Gen.HsType For some reason, on aarch64-darwin we saw a 2.8% decrease in compiler allocations for MultiLayerModulesTH_Make; but 0.0% on other architectures. Metric Decrease: MultiLayerModulesTH_Make - - - - - 22551364 by Sven Tennie at 2023-11-11T06:35:22-05:00 AArch64: Delete unused LDATA pseudo-instruction Though there were consuming functions for LDATA, there were no producers. Thus, the removed code was "dead". - - - - - 2a0ec8eb by Alan Zimmerman at 2023-11-11T06:35:59-05:00 EPA: harmonise acsa and acsA in GHC/Parser.y With the HasLoc class, we can remove the acsa helper function, using acsA instead. - - - - - 4ceac14d by Alan Zimmerman at 2023-11-11T15:16:41+00:00 EPA: Replace Anchor with EpaLocation Match GHC - - - - - 7ae517a0 by Teo Camarasu at 2023-11-12T08:04:12-05:00 nofib: bump submodule This includes changes that: - fix building a benchmark with HEAD - remove a Makefile-ism that causes errors in bash scripts Resolves #24178 - - - - - 3f0036ec by Alan Zimmerman at 2023-11-12T08:04:47-05:00 EPA: Replace Anchor with EpaLocation An Anchor has a location and an operation, which is either that it is unchanged or that it has moved with a DeltaPos data Anchor = Anchor { anchor :: RealSrcSpan , anchor_op :: AnchorOperation } An EpaLocation also has either a location or a DeltaPos data EpaLocation = EpaSpan !RealSrcSpan !(Strict.Maybe BufSpan) | EpaDelta !DeltaPos ![LEpaComment] Now that we do not care about always having a location in the anchor, we remove Anchor and replace it with EpaLocation We do this with a type alias initially, to ease the transition. The alias will be removed in time. We also have helpers to reconstruct the AnchorOperation from an EpaLocation. This is also temporary. Updates Haddock submodule - - - - - a7492048 by Alan Zimmerman at 2023-11-12T13:43:07+00:00 EPA: get rid of AnchorOperation Now that the Anchor type is an alias for EpaLocation, remove AnchorOperation. Updates haddock submodule - - - - - 0745c34d by Andrew Lelechenko at 2023-11-13T16:25:07-05:00 Add since annotation for showHFloat - - - - - e98051a5 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 Suppress duplicate librares linker warning of new macOS linker Fixes #24167 XCode 15 introduced a new linker which warns on duplicate libraries being linked. To disable this warning, we pass -Wl,-no_warn_duplicate_libraries as suggested by Brad King in CMake issue #25297. This flag isn't necessarily available to other linkers on darwin, so we must only configure it into the CC linker arguments if valid. - - - - - c411c431 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 testsuite: Encoding test witnesses recent iconv bug is fragile A regression in the new iconv() distributed with XCode 15 and MacOS Sonoma causes the test 'encoding004' to fail in the CP936 roundrip. We mark this test as fragile until this is fixed upstream (rather than broken, since previous versions of iconv pass the test) See #24161 - - - - - ce7fe5a9 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 testsuite: Update to LC_ALL=C no longer being ignored in darwin MacOS seems to have fixed an issue where it used to ignore the variable `LC_ALL` in program invocations and default to using Unicode. Since the behaviour seems to be fixed to account for the locale variable, we mark tests that were previously broken in spite of it as fragile (since they now pass in recent macOS distributions) See #24161 - - - - - e6c803f7 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 darwin: Fix single_module is obsolete warning In XCode 15's linker, -single_module is the default and otherwise passing it as a flag results in a warning being raised: ld: warning: -single_module is obsolete This patch fixes this warning by, at configure time, determining whether the linker supports -single_module (which is likely false for all non-darwin linkers, and true for darwin linkers in previous versions of macOS), and using that information at runtime to decide to pass or not the flag in the invocation. Fixes #24168 - - - - - 929ba2f9 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 testsuite: Skip MultiLayerModulesTH_Make on darwin The recent toolchain upgrade on darwin machines resulted in the MultiLayerModulesTH_Make test metrics varying too much from the baseline, ultimately blocking the CI pipelines. This commit skips the test on darwin to temporarily avoid failures due to the environment change in the runners. However, the metrics divergence is being investigated still (tracked in #24177) - - - - - af261ccd by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 configure: check target (not build) understands -no_compact_unwind Previously, we were branching on whether the build system was darwin to shortcut this check, but we really want to branch on whether the target system (which is what we are configuring ld_prog for) is darwin. - - - - - 2125c176 by Luite Stegeman at 2023-11-15T13:19:38-05:00 JS: Fix missing variable declarations The JStg IR update was missing some local variable declarations that were present earlier, causing global variables to be used implicitly (or an error in JavaScript strict mode). This adds the local variable declarations again. - - - - - 99ced73b by Krzysztof Gogolewski at 2023-11-15T13:20:14-05:00 Remove loopy superclass solve mechanism Programs with a -Wloopy-superclass-solve warning will now fail with an error. Fixes #23017 - - - - - 2aff2361 by Zubin Duggal at 2023-11-15T13:20:50-05:00 users-guide: Fix links to libraries from the users-guide. The unit-ids generated in c1a3ecde720b3bddc2c8616daaa06ee324e602ab include the package name, so we don't need to explicitly add it to the links. Fixes #24151 - - - - - 27981fac by Alan Zimmerman at 2023-11-15T13:21:25-05:00 EPA: splitLHsForAllTyInvis does not return ann We did not use the annotations returned from splitLHsForAllTyInvis, so do not return them. - - - - - a6467834 by Krzysztof Gogolewski at 2023-11-15T22:22:59-05:00 Document defaulting of RuntimeReps Fixes #24099 - - - - - 2776920e by Simon Peyton Jones at 2023-11-15T22:23:35-05:00 Second fix to #24083 My earlier fix turns out to be too aggressive for data/type families See wrinkle (DTV1) in Note [Disconnected type variables] - - - - - cee81370 by Sylvain Henry at 2023-11-16T09:57:46-05:00 Fix unusable units and module reexport interaction (#21097) This commit fixes an issue with ModUnusable introduced in df0f148feae. In mkUnusableModuleNameProvidersMap we traverse the list of unusable units and generate ModUnusable origin for all the modules they contain: exposed modules, hidden modules, and also re-exported modules. To do this we have a two-level map: ModuleName -> Unit:ModuleName (aka Module) -> ModuleOrigin So for each module name "M" in broken unit "u" we have: "M" -> u:M -> ModUnusable reason However in the case of module reexports we were using the *target* module as a key. E.g. if "u:M" is a reexport for "X" from unit "o": "M" -> o:X -> ModUnusable reason Case 1: suppose a reexport without module renaming (u:M -> o:M) from unusable unit u: "M" -> o:M -> ModUnusable reason Here it's claiming that the import of M is unusable because a reexport from u is unusable. But if unit o isn't unusable we could also have in the map: "M" -> o:M -> ModOrigin ... Issue: the Semigroup instance of ModuleOrigin doesn't handle the case (ModUnusable <> ModOrigin) Case 2: similarly we could have 2 unusable units reexporting the same module without renaming, say (u:M -> o:M) and (v:M -> o:M) with u and v unusable. It gives: "M" -> o:M -> ModUnusable ... (for u) "M" -> o:M -> ModUnusable ... (for v) Issue: the Semigroup instance of ModuleOrigin doesn't handle the case (ModUnusable <> ModUnusable). This led to #21097, #16996, #11050. To fix this, in this commit we make ModUnusable track whether the module used as key is a reexport or not (for better error messages) and we use the re-export module as key. E.g. if "u:M" is a reexport for "o:X" and u is unusable, we now record: "M" -> u:M -> ModUnusable reason reexported=True So now, we have two cases for a reexport u:M -> o:X: - u unusable: "M" -> u:M -> ModUnusable ... reexported=True - u usable: "M" -> o:X -> ModOrigin ... reexportedFrom=u:M The second case is indexed with o:X because in this case the Semigroup instance of ModOrigin is used to combine valid expositions of a module (directly or via reexports). Note that module lookup functions select usable modules first (those who have a ModOrigin value), so it doesn't matter if we add new ModUnusable entries in the map like this: "M" -> { u:M -> ModUnusable ... reexported=True o:M -> ModOrigin ... } The ModOrigin one will be used. Only if there is no ModOrigin or ModHidden entry will the ModUnusable error be printed. See T21097 for an example printing several reasons why an import is unusable. - - - - - 3e606230 by Krzysztof Gogolewski at 2023-11-16T09:58:22-05:00 Fix IPE test A helper function was defined in a different module than used. To reproduce: ./hadrian/build test --test-root-dirs=testsuite/tests/rts/ipe - - - - - 49f5264b by Andreas Klebinger at 2023-11-16T20:52:11-05:00 Properly compute unpacked sizes for -funpack-small-strict-fields. Use rep size rather than rep count to compute the size. Fixes #22309 - - - - - b4f84e4b by James Henri Haydon at 2023-11-16T20:52:53-05:00 Explicit methods for Alternative Compose Explicitly define some and many in Alternative instance for Data.Functor.Compose Implementation of https://github.com/haskell/core-libraries-committee/issues/181 - - - - - 9bc0dd1f by Ignat Insarov at 2023-11-16T20:53:34-05:00 Add permutations for non-empty lists. Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/68#issuecomment-1221409837 - - - - - 5643ecf9 by Andrew Lelechenko at 2023-11-16T20:53:34-05:00 Update changelog and since annotations for Data.List.NonEmpty.permutations Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/68#issuecomment-1221409837 - - - - - 94ff2134 by Oleg Alexander at 2023-11-16T20:54:15-05:00 Update doc string for traceShow Updated doc string for traceShow. - - - - - faff671a by Luite Stegeman at 2023-11-17T14:12:51+01:00 JS: clean up some foreign imports - - - - - 856e0a4e by Sven Tennie at 2023-11-18T06:54:11-05:00 AArch64: Remove unused instructions As these aren't ever emitted, we don't even know if they work or will ever be used. If one of them is needed in future, we may easily re-add it. Deleted instructions are: - CMN - ANDS - BIC - BICS - EON - ORN - ROR - TST - STP - LDP - DMBSY - - - - - 615441ef by Alan Zimmerman at 2023-11-18T06:54:46-05:00 EPA: Replace Monoid with NoAnn Remove the final Monoid instances in the exact print infrastructure. For Windows CI Metric Decrease: T5205 - - - - - 5a6c49d4 by David Feuer at 2023-11-20T18:53:18-05:00 Speed up stimes in instance Semigroup Endo As discussed at https://github.com/haskell/core-libraries-committee/issues/4 - - - - - cf9da4b3 by Andrew Lelechenko at 2023-11-20T18:53:18-05:00 base: reflect latest changes in the changelog - - - - - 48bf364e by Alan Zimmerman at 2023-11-20T18:53:54-05:00 EPA: Use SrcSpan in EpaSpan This is more natural, since we already need to deal with invalid RealSrcSpans, and that is exactly what SrcSpan.UnhelpfulSpan is for. Updates haddock submodule. - - - - - 97ec37cc by Sebastian Graf at 2023-11-20T18:54:31-05:00 Add regression test for #6070 Fixes #6070. - - - - - e9d5ae41 by Owen Shepherd at 2023-11-21T18:32:23-05:00 chore: Correct typo in the gitlab MR template [skip ci] - - - - - f158a8d0 by Rodrigo Mesquita at 2023-11-21T18:32:59-05:00 Improve error message when reading invalid `.target` files A `.target` file generated by ghc-toolchain or by configure can become invalid if the target representation (`Toolchain.Target`) is changed while the files are not re-generated by calling `./configure` or `ghc-toolchain` again. There is also the issue of hadrian caching the dependencies on `.target` files, which makes parsing fail when reading reading the cached value if the representation has been updated. This patch provides a better error message in both situations, moving away from a terrible `Prelude.read: no parse` error that you would get otherwise. Fixes #24199 - - - - - 955520c6 by Ben Gamari at 2023-11-21T18:33:34-05:00 users guide: Note that QuantifiedConstraints implies ExplicitForAll Fixes #24025. - - - - - 17ec3e97 by Owen Shepherd at 2023-11-22T09:37:28+01:00 fix: Change type signatures in NonEmpty export comments to reflect reality This fixes several typos in the comments of Data.List.NonEmpty export list items. - - - - - 2fd78f9f by Samuel Thibault at 2023-11-22T11:49:13-05:00 Fix the platform string for GNU/Hurd As commited in Cargo https://github.com/haskell/cabal/pull/9434 there is confusion between "gnu" and "hurd". This got fixed in Cargo, we need the converse in Hadrian. Fixes #24180 - - - - - a79960fe by Alan Zimmerman at 2023-11-22T11:49:48-05:00 EPA: Tuple Present no longer has annotation The Present constructor for a Tuple argument will never have an exact print annotation. So make this impossible. - - - - - 121c9ab7 by David Binder at 2023-11-22T21:12:29-05:00 Unify the hpc testsuites The hpc testsuite was split between testsuite/tests/hpc and the submodule libraries/hpc/test. This commit unifies the two testsuites in the GHC repository in the directory testsuite/tests/hpc. - - - - - d2733a05 by Alan Zimmerman at 2023-11-22T21:13:05-05:00 EPA: empty tup_tail has noAnn In Parser.y, the tup_tail rule had the following option | {- empty -} %shift { return [Left noAnn] } Once this works through PostProcess.hs, it means we add an extra Missing constructor if the last item was a comma. Change the annotation type to a Bool to indicate this, and use the EpAnn Anchor for the print location for the others. - - - - - fa576eb8 by Andreas Klebinger at 2023-11-24T08:29:13-05:00 Fix FMA primops generating broken assembly on x86. `genFMA3Code` assumed that we had to take extra precations to avoid overwriting the result of `getNonClobberedReg`. One of these special cases caused a bug resulting in broken assembly. I believe we don't need to hadle these cases specially at all, which means this MR simply deletes the special cases to fix the bug. Fixes #24160 - - - - - 34d86315 by Alan Zimmerman at 2023-11-24T08:29:49-05:00 EPA: Remove parenthesizeHsType This is called from PostProcess.hs, and adds spurious parens. With the looser version of exact printing we had before we could tolerate this, as they would be swallowed by the original at the same place. But with the next change (remove EpAnnNotUsed) they result in duplicates in the output. For Darwin build: Metric Increase: MultiLayerModulesTH_OneShot - - - - - 3ede659d by Vladislav Zavialov at 2023-11-26T06:43:32-05:00 Add name for -Wdeprecated-type-abstractions (#24154) This warning had no name or flag and was triggered unconditionally. Now it is part of -Wcompat. - - - - - 7902ebf8 by Alan Zimmerman at 2023-11-26T06:44:08-05:00 EPA: Remove EpAnnNotUsed We no longer need the EpAnnNotUsed constructor for EpAnn, as we can represent an unused annotation with an anchor having a EpaDelta of zero, and empty comments and annotations. This simplifies code handling annotations considerably. Updates haddock submodule Metric Increase: parsing001 - - - - - 471b2672 by Mario Blažević at 2023-11-26T06:44:48-05:00 Bumped the upper bound of text to <2.2 - - - - - d1bf25c7 by Vladislav Zavialov at 2023-11-26T11:45:49-05:00 Term variable capture (#23740) This patch changes type variable lookup rules (lookupTypeOccRn) and implicit quantification rules (filterInScope) so that variables bound in the term namespace can be captured at the type level {-# LANGUAGE RequiredTypeArguments #-} f1 x = g1 @x -- `x` used in a type application f2 x = g2 (undefined :: x) -- `x` used in a type annotation f3 x = g3 (type x) -- `x` used in an embedded type f4 x = ... where g4 :: x -> x -- `x` used in a type signature g4 = ... This change alone does not allow us to accept examples shown above, but at least it gets them past the renamer. - - - - - da863d15 by Vladislav Zavialov at 2023-11-26T11:46:26-05:00 Update Note [hsScopedTvs and visible foralls] The Note was written before GHC gained support for visible forall in types of terms. Rewrite a few sentences and use a better example. - - - - - b5213542 by Matthew Pickering at 2023-11-27T12:53:59-05:00 testsuite: Add mechanism to collect generic metrics * Generalise the metric logic by adding an additional field which allows you to specify how to query for the actual value. Previously the method of querying the baseline value was abstracted (but always set to the same thing). * This requires rejigging how the stat collection works slightly but now it's more uniform and hopefully simpler. * Introduce some new "generic" helper functions for writing generic stats tests. - collect_size ( deviation, path ) Record the size of the file as a metric - stat_from_file ( metric, deviation, path ) Read a value from the given path, and store that as a metric - collect_generic_stat ( metric, deviation, get_stat) Provide your own `get_stat` function, `lambda way: <Int>`, which can be used to establish the current value of the metric. - collect_generic_stats ( metric_info ): Like collect_generic_stat but provide the whole dictionary of metric definitions. { metric: { deviation: <Int> current: lambda way: <Int> } } * Introduce two new "size" metrics for keeping track of build products. - `size_hello_obj` - The size of `hello.o` from compiling hello.hs - `libdir` - The total size of the `libdir` folder. * Track the number of modules in the AST tests - CountDepsAst - CountDepsParser This lays the infrastructure for #24191 #22256 #17129 - - - - - 7d9a2e44 by ARATA Mizuki at 2023-11-27T12:54:39-05:00 x86: Don't require -mavx2 when using 256-bit floating-point SIMD primitives Fixes #24222 - - - - - 4e5ff6a4 by Alan Zimmerman at 2023-11-27T12:55:15-05:00 EPA: Remove SrcSpanAnn Now that we only have a single constructor for EpAnn, And it uses a SrcSpan for its location, we can do away with SrcSpanAnn completely. It only existed to wrap the original SrcSpan in a location, and provide a place for the exact print annotation. For darwin only: Metric Increase: MultiLayerModulesTH_OneShot Updates haddock submodule - - - - - e05bca39 by Krzysztof Gogolewski at 2023-11-28T08:00:55-05:00 testsuite: don't initialize testdir to '.' The test directory is removed during cleanup, if there's an interrupt that could remove the entire repository. Fixes #24219 - - - - - af881674 by Alan Zimmerman at 2023-11-28T08:01:30-05:00 EPA: Clean up mkScope in Ast.hs Now that we have HasLoc we can get rid of all the custom variants of mkScope For deb10-numa Metric Increase: libdir - - - - - 292983c8 by Ben Gamari at 2023-11-28T22:44:28-05:00 distrib: Rediscover otool and install_name_tool on Darwin In the bindist configure script we must rediscover the `otool` and `install_name_tool`s since they may be different from the build environment. Fixes #24211. - - - - - dfe1c354 by Stefan Schulze Frielinghaus at 2023-11-28T22:45:04-05:00 llvmGen: Align objects in the data section Objects in the data section may be referenced via tagged pointers. Thus, align those objects to a 4- or 8-byte boundary for 32- or 64-bit platforms, respectively. Note, this may need to be reconsidered if objects with a greater natural alignment requirement are emitted as e.g. 128-bit atomics. Fixes #24163. - - - - - f6c486c3 by Matthew Pickering at 2023-11-29T11:08:13-05:00 metrics: Widen libdir and size_hello_obj acceptance window af8816740d9b8759be1a22af8adcb5f13edeb61d shows that the libdir size can fluctuate quite significantly even when the change is quite small. Therefore we widen the acceptance window to 10%. - - - - - 99a6a49c by Alan Zimmerman at 2023-11-29T11:08:49-05:00 EPA: Clean up TC Monad Utils We no longer need the alternative variant of addLocM (addLocMA) nor wrapLocAM, wrapLocSndMA. aarch64-darwin Metric Increase: MultiLayerModulesTH_OneShot deb10-numa-slow Metric Decrease: libdir - - - - - 94fb8d47 by Alan Zimmerman at 2023-11-29T18:10:26+00:00 Match GHC, No comments in EpaDelta for comments - - - - - cbc03fa0 by Sebastian Graf at 2023-11-30T12:37:21-05:00 perf tests: Move comments into new `Note [Sensitivity to unique increment]` (#19414) And additionally to T12545, link from T8095, T13386 to this new Note. - - - - - c7623b22 by Alan Zimmerman at 2023-11-30T12:37:56-05:00 EPA: EpaDelta for comment has no comments EpaLocation is used to position things. It has two constructors, EpaSpan holding a SrcSpan, and EpaDelta with a delta position and a possible list of comments. The comment list is needed because the location in EpaDelta has no absolute information to decide which comments should be emitted before them when printing. But it is also used for specifying the position of a comment. To prevent the absurdity of a comment position having a list of comments in it, we make EpaLocation parameterisable, using comments for the normal case and a constant for within comments. Updates haddock submodule. aarch64-darwin Metric Decrease: MultiLayerModulesTH_OneShot - - - - - bd8acc0c by Krzysztof Gogolewski at 2023-11-30T12:38:32-05:00 Kind-check body of a required forall We now require that in 'forall a -> ty', ty has kind TYPE r for some r. Fixes #24176 - - - - - 010fb784 by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Remove incorrect haddock link quotes in code block - - - - - cda9c12d by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Remove cycle from group haddock example - - - - - 495265b9 by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Use repl haddock syntax in group docs - - - - - d134d1de by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Use list [] notation in group haddock - - - - - dfcf629c by Owen Shepherd at 2023-12-03T00:10:10-05:00 docs(NonEmpty/group): Specify final property of group function in haddock - - - - - cad3b734 by Owen Shepherd at 2023-12-03T00:10:10-05:00 fix: Add missing property of List.group - - - - - bad37656 by Matthew Pickering at 2023-12-03T00:10:46-05:00 testsuite: Fix T21097b test with make 4.1 (deb9) cee81370cd6ef256f66035e3116878d4cb82e28b recently added a test which failed on deb9 because the version of make was emitting the recipe failure to stdout rather than stderr. One way to fix this is to be more precise in the test about which part of the output we care about inspecting. - - - - - 5efdf421 by Matthew Pickering at 2023-12-03T00:11:21-05:00 testsuite: Track size of libdir in bytes For consistency it's better if we track all size metrics in bytes. Metric Increase: libdir - - - - - f5eb0f29 by Matthew Pickering at 2023-12-03T00:11:22-05:00 testsuite: Remove rogue trace in testsuite I accidentally left a trace in the generics metric patch. - - - - - d5610737 by Claudio Bley at 2023-12-06T16:13:33-05:00 Only exit ghci in -e mode when :add command fails Previously, when running `ghci -e ':add Sample.hs'` the process would exit with exit code 1 if the file exists and could be loaded. Fixes #24115 - - - - - 0f0c53a5 by Vladislav Zavialov at 2023-12-06T16:14:09-05:00 T2T in Patterns (#23739) This patch implements the T2T (term-to-type) transformation in patterns. Patterns that are checked against a visible forall can now be written without the `type` keyword: \(type t) (x :: t) -> ... -- old \t (x :: t) -> ... -- new The `t` binder is parsed and renamed as a term pattern (Pat), but then undergoes a conversion to a type pattern (HsTyPat). See the new function pat_to_type_pat in compiler/GHC/Tc/Gen/Pat.hs - - - - - 10a1a6c6 by Sebastian Graf at 2023-12-06T16:14:45-05:00 Pmc: Fix SrcLoc and warning for incomplete irrefutable pats (#24234) Before, the source location would point at the surrounding function definition, causing the confusion in #24234. I also took the opportunity to introduce a new `LazyPatCtx :: HsMatchContext _` to make the warning message say "irrefutable pattern" instead of "pattern binding". - - - - - 36b9a38c by Matthew Pickering at 2023-12-06T16:15:21-05:00 libraries: Bump filepath to 1.4.200.1 and unix to 2.8.4.0 Updates filepath submodule Updates unix submodule Fixes #24240 - - - - - 91ff0971 by Matthew Pickering at 2023-12-06T16:15:21-05:00 Submodule linter: Allow references to tags We modify the submodule linter so that if the bumped commit is a specific tag then the commit is accepted. Fixes #24241 - - - - - 86f652dc by Zubin Duggal at 2023-12-06T16:15:21-05:00 hadrian: set -Wno-deprecations for directory and Win32 The filepath bump to 1.4.200.1 introduces a deprecation warning. See https://gitlab.haskell.org/ghc/ghc/-/issues/24240 https://github.com/haskell/filepath/pull/206 - - - - - 7ac6006e by Sylvain Henry at 2023-12-06T16:16:02-05:00 Zap OccInfo on case binders during StgCse #14895 #24233 StgCse can revive dead binders: case foo of dead { Foo x y -> Foo x y; ... } ===> case foo of dead { Foo x y -> dead; ... } -- dead is no longer dead So we must zap occurrence information on case binders. Fix #14895 and #24233 - - - - - 57c391c4 by Sebastian Graf at 2023-12-06T16:16:37-05:00 Cpr: Turn an assertion into a check to deal with some dead code (#23862) See the new `Note [Dead code may contain type confusions]`. Fixes #23862. - - - - - c1c8abf8 by Zubin Duggal at 2023-12-08T02:25:07-05:00 testsuite: add test for #23944 - - - - - 6329d308 by Zubin Duggal at 2023-12-08T02:25:07-05:00 driver: Only run a dynamic-too pipeline if object files are going to be generated Otherwise we run into a panic in hscMaybeWriteIface: "Unexpected DT_Dyn state when writing simple interface" when dynamic-too is enabled We could remove the panic and just write the interface even if the state is `DT_Dyn`, but it seems pointless to run the pipeline twice when `hscMaybeWriteIface` is already designed to write both `hi` and `dyn_hi` files if dynamic-too is enabled. Fixes #23944. - - - - - 28811f88 by Simon Peyton Jones at 2023-12-08T05:47:18-05:00 Improve duplicate elimination in SpecConstr This partially fixes #24229. See the new Note [Pattern duplicate elimination] in SpecConstr - - - - - fec7894f by Simon Peyton Jones at 2023-12-08T05:47:18-05:00 Make SpecConstr deal with casts better This patch does two things, to fix #23209: * It improves SpecConstr so that it no longer quantifies over coercion variables. See Note [SpecConstr and casts] * It improves the rule matcher to deal nicely with the case where the rule does not quantify over coercion variables, but the the template has a cast in it. See Note [Casts in the template] - - - - - 8db8d2fd by Zubin Duggal at 2023-12-08T05:47:54-05:00 driver: Don't lose track of nodes when we fail to resolve cycles The nodes that take part in a cycle should include both hs-boot and hs files, but when we fail to resolve a cycle, we were only counting the nodes from the graph without boot files. Fixes #24196 - - - - - c5b4efd3 by Zubin Duggal at 2023-12-08T05:48:30-05:00 testsuite: Skip MultiLayerModulesTH_OneShot on darwin See #24177 - - - - - fae472a9 by Wendao Lee at 2023-12-08T05:49:12-05:00 docs(Data.Char):Add more detailed descriptions for some functions Related changed function's docs: -GHC.Unicode.isAlpha -GHC.Unicode.isPrint -GHC.Unicode.isAlphaNum Add more details for what the function will return. Co-authored-by: Bodigrim <andrew.lelechenko at gmail.com> - - - - - ca7510e4 by Malik Ammar Faisal at 2023-12-08T05:49:55-05:00 Fix float parsing in GHC Cmm Lexer Add test case for bug #24224 - - - - - d8baa1bd by Simon Peyton Jones at 2023-12-08T15:40:37+00:00 Take care when simplifying unfoldings This MR fixes a very subtle bug exposed by #24242. See Note [Environment for simplLetUnfolding]. I also updated a bunch of Notes on shadowing - - - - - 03ca551d by Simon Peyton Jones at 2023-12-08T15:54:50-05:00 Comments only in FloatIn Relevant to #3458 - - - - - 50c78779 by Simon Peyton Jones at 2023-12-08T15:54:50-05:00 Comments only in SpecConstr - - - - - 9431e195 by Simon Peyton Jones at 2023-12-08T15:54:50-05:00 Add test for #22238 - - - - - d9e4c597 by Vladislav Zavialov at 2023-12-11T04:19:34-05:00 Make forall a keyword (#23719) Before this change, GHC used to accept `forall` as a term-level identifier: -- from constraints-0.13 forall :: forall p. (forall a. Dict (p a)) -> Dict (Forall p) forall d = ... Now it is a parse error. The -Wforall-identifier warning has served its purpose and is now a deprecated no-op. - - - - - 58d56644 by Zubin Duggal at 2023-12-11T04:20:10-05:00 driver: Ensure we actually clear the interactive context before reloading Previously we called discardIC, but immediately after set the session back to an old HscEnv that still contained the IC Partially addresses #24107 Fixes #23405 - - - - - 8e5745a0 by Zubin Duggal at 2023-12-11T04:20:10-05:00 driver: Ensure we force the lookup of old build artifacts before returning the build plan This prevents us from retaining all previous build artifacts in memory until a recompile finishes, instead only retaining the exact artifacts we need. Fixes #24118 - - - - - 105c370c by Zubin Duggal at 2023-12-11T04:20:10-05:00 testsuite: add test for #24118 and #24107 MultiLayerModulesDefsGhci was not able to catch the leak because it uses :l which discards the previous environment. Using :r catches both of these leaks - - - - - e822ff88 by Zubin Duggal at 2023-12-11T04:20:10-05:00 compiler: Add some strictness annotations to ImportSpec and related constructors This prevents us from retaining entire HscEnvs. Force these ImportSpecs when forcing the GlobalRdrEltX Adds an NFData instance for Bag Fixes #24107 - - - - - 522c12a4 by Zubin Duggal at 2023-12-11T04:20:10-05:00 compiler: Force IfGlobalRdrEnv in NFData instance. - - - - - 188b280d by Arnaud Spiwack at 2023-12-11T15:33:31+01:00 LinearTypes => MonoLocalBinds - - - - - 8e0446df by Arnaud Spiwack at 2023-12-11T15:44:28+01:00 Linear let and where bindings For expediency, the initial implementation of linear types in GHC made it so that let and where binders would always be considered unrestricted. This was rather unpleasant, and probably a big obstacle to adoption. At any rate, this was not how the proposal was designed. This patch fixes this infelicity. It was surprisingly difficult to build, which explains, in part, why it took so long to materialise. As of this patch, let or where bindings marked with %1 will be linear (respectively %p for an arbitrary multiplicity p). Unmarked let will infer their multiplicity. Here is a prototypical example of program that used to be rejected and is accepted with this patch: ```haskell f :: A %1 -> B g :: B %1 -> C h :: A %1 -> C h x = g y where y = f x ``` Exceptions: - Recursive let are unrestricted, as there isn't a clear semantics of what a linear recursive binding would be. - Destructive lets with lazy bindings are unrestricted, as their desugaring isn't linear (see also #23461). - (Strict) destructive lets with inferred polymorphic type are unrestricted. Because the desugaring isn't linear (See #18461 down-thread). Closes #18461 and #18739 Co-authored-by: @jackohughes - - - - - effa7e2d by Matthew Craven at 2023-12-12T04:37:20-05:00 Introduce `dataToTagSmall#` primop (closes #21710) ...and use it to generate slightly better code when dataToTag# is used at a "small data type" where there is no need to mess with "is_too_big_tag" or potentially look at an info table. Metric Decrease: T18304 - - - - - 35c7aef6 by Matthew Craven at 2023-12-12T04:37:20-05:00 Fix formatting of Note [alg-alt heap check] - - - - - 7397c784 by Oleg Grenrus at 2023-12-12T04:37:56-05:00 Allow untyped brackets in typed splices and vice versa. Resolves #24190 Apparently the check was essentially always (as far as I can trace back: d0d47ba76f8f0501cf3c4966bc83966ab38cac27), and while it does catch some mismatches, the type-checker will catch them too. OTOH, it prevents writing completely reasonable programs. - - - - - 32d208e1 by Vladislav Zavialov at 2023-12-12T20:41:36+03:00 EPA: Match changes to LHsToken removal - - - - - a3ee3b99 by Moritz Angermann at 2023-12-12T19:50:58-05:00 Drop hard Xcode dependency XCODE_VERSION calls out to `xcodebuild`, which is only available when having `Xcode` installed. The CommandLineTools are not sufficient. To install Xcode, you must have an apple id to download the Xcode.xip from apple. We do not use xcodebuild anywhere in our build explicilty. At best it appears to be a proxy for checking the linker or the compiler. These should rather be done with ``` xcrun ld -version ``` or similar, and not by proxy through Xcode. The CLR should be sufficient for building software on macOS. - - - - - 1c9496e0 by Vladislav Zavialov at 2023-12-12T19:51:34-05:00 docs: update information on RequiredTypeArguments Update the User's Guide and Release Notes to account for the recent progress in the implementation of RequiredTypeArguments. - - - - - d0b17576 by Ben Gamari at 2023-12-13T06:33:37-05:00 rts/eventlog: Fix off-by-one in assertion Previously we failed to account for the NULL terminator `postString` asserted that there is enough room in the buffer for the string. - - - - - a10f9b9b by Ben Gamari at 2023-12-13T06:33:37-05:00 rts/eventlog: Honor result of ensureRoomForVariableEvent is Previously we would keep plugging along, even if isn't enough room for the event. - - - - - 0e0f41c0 by Ben Gamari at 2023-12-13T06:33:37-05:00 rts/eventlog: Avoid truncating event sizes Previously ensureRoomForVariableEvent would truncate the desired size to 16-bits, resulting in #24197. Fixes #24197. - - - - - 64e724c8 by Artin Ghasivand at 2023-12-13T06:34:20-05:00 Remove the "Derived Constraint" argument of TcPluginSolver, docs - - - - - fe6d97dd by Vladislav Zavialov at 2023-12-13T06:34:56-05:00 EPA: Move tokens into GhcPs extension fields (#23447) Summary of changes * Remove Language.Haskell.Syntax.Concrete * Move all tokens into GhcPs extension fields (LHsToken -> EpToken) * Create new TTG extension fields as needed * Drop the MultAnn wrapper Updates the haddock submodule. Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 8106e695 by Zubin Duggal at 2023-12-13T06:35:34-05:00 testsuite: use copy_files in T23405 This prevents the tree from being dirtied when the file is modified. - - - - - ed0e4099 by Bryan Richter at 2023-12-14T04:30:53-05:00 Document ghc package's PVP-noncompliance This changes nothing, it just makes the status quo explicit. - - - - - 8bef8d9f by Luite Stegeman at 2023-12-14T04:31:33-05:00 JS: Mark spurious CI failures js_fragile(24259) This marks the spurious test failures on the JS platform as js_fragile(24259), so we don't hold up merge requests while fixing the underlying issues. See #24259 - - - - - 1c79526a by Finley McIlwaine at 2023-12-15T12:24:40-08:00 Late plugins - - - - - 000c3302 by Finley McIlwaine at 2023-12-15T12:24:40-08:00 withTiming on LateCCs and late plugins - - - - - be4551ac by Finley McIlwaine at 2023-12-15T12:24:40-08:00 add test for late plugins - - - - - 7c29da9f by Finley McIlwaine at 2023-12-15T12:24:40-08:00 Document late plugins - - - - - 9a52ae46 by Ben Gamari at 2023-12-20T07:07:26-05:00 Fix thunk update ordering Previously we attempted to ensure soundness of concurrent thunk update by synchronizing on the access of the thunk's info table pointer field. This was believed to be sufficient since the indirectee (which may expose a closure allocated by another core) would not be examined until the info table pointer update is complete. However, it turns out that this can result in data races in the presence of multiple threads racing a update a single thunk. For instance, consider this interleaving under the old scheme: Thread A Thread B --------- --------- t=0 Enter t 1 Push update frame 2 Begin evaluation 4 Pause thread 5 t.indirectee=tso 6 Release t.info=BLACKHOLE 7 ... (e.g. GC) 8 Resume thread 9 Finish evaluation 10 Relaxed t.indirectee=x 11 Load t.info 12 Acquire fence 13 Inspect t.indirectee 14 Release t.info=BLACKHOLE Here Thread A enters thunk `t` but is soon paused, resulting in `t` being lazily blackholed at t=6. Then, at t=10 Thread A finishes evaluation and updates `t.indirectee` with a relaxed store. Meanwhile, Thread B enters the blackhole. Under the old scheme this would introduce an acquire-fence but this would only synchronize with Thread A at t=6. Consequently, the result of the evaluation, `x`, is not visible to Thread B, introducing a data race. We fix this by treating the `indirectee` field as we do all other mutable fields. This means we must always access this field with acquire-loads and release-stores. See #23185. - - - - - f4b53538 by Vladislav Zavialov at 2023-12-20T07:08:02-05:00 docs: Fix link to 051-ghc-base-libraries.rst The proposal is no longer available at the previous URL. - - - - - f7e21fab by Matthew Pickering at 2023-12-21T14:57:40+00:00 hadrian: Build all executables in bin/ folder In the end the bindist creation logic copies them all into the bin folder. There is no benefit to building a specific few binaries in the lib/bin folder anymore. This also removes the ad-hoc logic to copy the touchy and unlit executables from stage0 into stage1. It takes <1s to build so we might as well just build it. - - - - - 0038d052 by Zubin Duggal at 2023-12-22T23:28:00-05:00 testsuite: mark jspace as fragile on i386. This test has been flaky for some time and has been failing consistently on i386-linux since 8e0446df landed. See #24261 - - - - - dfd670a0 by Ben Bellick at 2023-12-24T10:10:31-05:00 Deprecate -ddump-json and introduce -fdiagnostics-as-json Addresses #19278 This commit deprecates the underspecified -ddump-json flag and introduces a newer, well-specified flag -fdiagnostics-as-json. Also included is a JSON schema as part of the documentation. The -ddump-json flag will be slated for removal shortly after this merge. - - - - - 609e6225 by Ben Bellick at 2023-12-24T10:10:31-05:00 Deprecate -ddump-json and introduce -fdiagnostics-as-json Addresses #19278 This commit deprecates the underspecified -ddump-json flag and introduces a newer, well-specified flag -fdiagnostics-as-json. Also included is a JSON schema as part of the documentation. The -ddump-json flag will be slated for removal shortly after this merge. - - - - - 865513b2 by Ömer Sinan Ağacan at 2023-12-24T10:11:13-05:00 Fix BNF in user manual 6.6.8.2: formal syntax for instance declarations - - - - - c247b6be by Zubin Duggal at 2023-12-25T16:01:23-05:00 docs: document permissibility of -XOverloadedLabels (#24249) Document the permissibility introduced by https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0170-unrestricted-overloadedlabels.rst - - - - - e5b7eb59 by Ömer Sinan Ağacan at 2023-12-25T16:02:03-05:00 Fix a code block syntax in user manual sec. 6.8.8.6 - - - - - 2db11c08 by Ben Gamari at 2023-12-29T15:35:48-05:00 genSym: Reimplement via CAS on 32-bit platforms Previously the remaining use of the C implementation on 32-bit platforms resulted in a subtle bug, #24261. This was due to the C object (which used the RTS's `atomic_inc64` macro) being compiled without `-threaded` yet later being used in a threaded compiler. Side-step this issue by using the pure Haskell `genSym` implementation on all platforms. This required implementing `fetchAddWord64Addr#` in terms of CAS on 64-bit platforms. - - - - - 19328a8c by Xiaoyan Ren at 2023-12-29T15:36:30-05:00 Do not color the diagnostic code in error messages (#24172) - - - - - 685b467c by Krzysztof Gogolewski at 2023-12-29T15:37:06-05:00 Enforce that bindings of implicit parameters are lifted Fixes #24298 - - - - - bc4d67b7 by Matthew Craven at 2023-12-31T06:15:42-05:00 StgToCmm: Detect some no-op case-continuations ...and generate no code for them. Fixes #24264. - - - - - 5b603139 by Krzysztof Gogolewski at 2023-12-31T06:16:18-05:00 Revert "testsuite: mark jspace as fragile on i386." This reverts commit 0038d052c8c80b4b430bb2aa1c66d5280be1aa95. The atomicity bug should be fixed by !11802. - - - - - d55216ad by Krzysztof Gogolewski at 2024-01-01T12:05:49-05:00 Refactor: store [[PrimRep]] rather than [Type] in STG StgConApp stored a list of types. This list was used exclusively during unarisation of unboxed sums (mkUbxSum). However, this is at a wrong level of abstraction: STG shouldn't be concerned with Haskell types, only PrimReps. Update the code to store a [[PrimRep]]. Also, there's no point in storing this list when we're not dealing with an unboxed sum. - - - - - 8b340bc7 by Ömer Sinan Ağacan at 2024-01-01T12:06:29-05:00 Kind signatures docs: mention that they're allowed in newtypes - - - - - 989bf8e5 by Zubin Duggal at 2024-01-03T20:08:47-05:00 ci: Ensure we use the correct bindist name for the test artifact when generating release ghcup metadata Fixes #24268 - - - - - 89299a89 by Krzysztof Gogolewski at 2024-01-03T20:09:23-05:00 Refactor: remove calls to typePrimRepArgs The function typePrimRepArgs is just a thin wrapper around typePrimRep, adding a VoidRep if the list is empty. However, in StgToByteCode, we were discarding that VoidRep anyway, so there's no point in calling it. - - - - - c7be0c68 by mmzk1526 at 2024-01-03T20:10:07-05:00 Use "-V" for alex version check for better backward compatibility Fixes #24302. In recent versions of alex, "-v" is used for "--verbose" instead of "-version". - - - - - 67dbcc0a by Krzysztof Gogolewski at 2024-01-05T02:07:18-05:00 Fix VoidRep handling in ghci debugger 'go' inside extractSubTerms was giving a bad result given a VoidRep, attempting to round towards the next multiple of 0. I don't understand much about the debugger but the code should be better than it was. Fixes #24306 - - - - - 90ea574e by Krzysztof Gogolewski at 2024-01-05T02:07:54-05:00 VoidRep-related refactor * In GHC.StgToByteCode, replace bcIdPrimId with idPrimRep, bcIdArgRep with idArgRep, atomPrimRep with stgArgRep1. All of them were duplicates. * In GHC.Stg.Unarise, we were converting a PrimRep to a Type and back to PrimRep. Remove the calls to primRepToType and typePrimRep1 which cancel out. * In GHC.STG.Lint, GHC.StgToCmm, GHC.Types.RepType we were filtering out VoidRep from the result of typePrimRep. But typePrimRep never returns VoidRep - remove the filtering. - - - - - eaf72479 by brian at 2024-01-06T23:03:09-05:00 Add unaligned Addr# primops Implements CLC proposal #154: https://github.com/haskell/core-libraries-committee/issues/154 * add unaligned addr primops * add tests * accept tests * add documentation * fix js primops * uncomment in access ops * use Word64 in tests * apply suggestions * remove extra file * move docs * remove random options * use setByteArray# primop * better naming * update base-exports test * add base-exports for other architectures - - - - - d471d445 by Krzysztof Gogolewski at 2024-01-06T23:03:47-05:00 Remove VoidRep from PrimRep, introduce PrimOrVoidRep This introduces data PrimOrVoidRep = VoidRep | NVRep PrimRep changes typePrimRep1 to return PrimOrVoidRep, and adds a new function typePrimRepU to be used when the argument is definitely non-void. Details in Note [VoidRep] in GHC.Types.RepType. Fixes #19520 - - - - - 48720a07 by Matthew Craven at 2024-01-08T18:57:36-05:00 Apply Note [Sensitivity to unique increment] to LargeRecord - - - - - 9e2e180f by Sebastian Graf at 2024-01-08T18:58:13-05:00 Debugging: Add diffUFM for convenient diffing between UniqFMs - - - - - 948f3e35 by Sebastian Graf at 2024-01-08T18:58:13-05:00 Rename Opt_D_dump_stranal to Opt_D_dump_dmdanal ... and Opt_D_dump_str_signatures to Opt_D_dump_dmd_signatures - - - - - 4e217e3e by Sebastian Graf at 2024-01-08T18:58:13-05:00 Deprecate -ddump-stranal and -ddump-str-signatures ... and suggest -ddump-dmdanal and -ddump-dmd-signatures instead - - - - - 6c613c90 by Sebastian Graf at 2024-01-08T18:58:13-05:00 Move testsuite/tests/stranal to testsuite/tests/dmdanal A separate commit so that the rename is obvious to Git(Lab) - - - - - c929f02b by Sebastian Graf at 2024-01-08T18:58:13-05:00 CoreSubst: Stricten `substBndr` and `cloneBndr` Doing so reduced allocations of `cloneBndr` by about 25%. ``` T9233(normal) ghc/alloc 672,488,656 663,083,216 -1.4% GOOD T9675(optasm) ghc/alloc 423,029,256 415,812,200 -1.7% geo. mean -0.1% minimum -1.7% maximum +0.1% ``` Metric Decrease: T9233 - - - - - e3ca78f3 by Krzysztof Gogolewski at 2024-01-10T17:35:59-05:00 Deprecate -Wsemigroup This warning was used to prepare for Semigroup becoming a superclass of Monoid, and for (<>) being exported from Prelude. This happened in GHC 8.4 in 8ae263ceb3566 and feac0a3bc69fd3. The leftover logic for (<>) has been removed in GHC 9.8, 4d29ecdfcc79. Now the warning does nothing at all and can be deprecated. - - - - - 08d14925 by amesgen at 2024-01-10T17:36:42-05:00 WASM metadata: use correct GHC version - - - - - 7a808419 by Xiaoyan Ren at 2024-01-10T17:37:24-05:00 Allow SCC declarations in TH (#24081) - - - - - 28827c51 by Xiaoyan Ren at 2024-01-10T17:37:24-05:00 Fix prettyprinting of SCC pragmas - - - - - ae9cc1a8 by Matthew Craven at 2024-01-10T17:38:01-05:00 Fix loopification in the presence of void arguments This also removes Note [Void arguments in self-recursive tail calls], which was just misleading. It's important to count void args both in the function's arity and at the call site. Fixes #24295. - - - - - b718b145 by Zubin Duggal at 2024-01-10T17:38:36-05:00 testsuite: Teach testsuite driver about c++ sources - - - - - 09cb57ad by Zubin Duggal at 2024-01-10T17:38:36-05:00 driver: Set -DPROFILING when compiling C++ sources with profiling Earlier, we used to pass all preprocessor flags to the c++ compiler. This meant that -DPROFILING was passed to the c++ compiler because it was a part of C++ flags However, this was incorrect and the behaviour was changed in 8ff3134ed4aa323b0199ad683f72165e51a59ab6. See #21291. But that commit exposed this bug where -DPROFILING was no longer being passed when compiling c++ sources. The fix is to explicitly include -DPROFILING in `opt_cxx` when profiling is enabled to ensure we pass the correct options for the way to both C and C++ compilers Fixes #24286 - - - - - 2cf9dd96 by Zubin Duggal at 2024-01-10T17:38:36-05:00 testsuite: rename objcpp -> objcxx To avoid confusion with C Pre Processsor - - - - - af6932d6 by Simon Peyton Jones at 2024-01-10T17:39:12-05:00 Make TYPE and CONSTRAINT not-apart Issue #24279 showed up a bug in the logic in GHC.Core.Unify.unify_ty which is supposed to make TYPE and CONSTRAINT be not-apart. Easily fixed. - - - - - 4a39b5ff by Zubin Duggal at 2024-01-10T17:39:48-05:00 ci: Fix typo in mk_ghcup_metadata.py There was a missing colon in the fix to #24268 in 989bf8e53c08eb22de716901b914b3607bc8dd08 - - - - - 13503451 by Zubin Duggal at 2024-01-10T17:40:24-05:00 release-ci: remove release-x86_64-linux-deb11-release+boot_nonmoving_gc job There is no reason to have this release build or distribute this variation. This configuration is for testing purposes only. - - - - - afca46a4 by Sebastian Graf at 2024-01-10T17:41:00-05:00 Parser: Add a Note detailing why we need happy's `error` to implement layout - - - - - eaf8a06d by Krzysztof Gogolewski at 2024-01-11T00:43:17+01:00 Turn -Wtype-equality-out-of-scope on by default Also remove -Wnoncanonical-{monoid,monad}-instances from -Wcompat, since they are enabled by default. Refresh wcompat-warnings/ test with new -Wcompat warnings. Part of #24267 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 42bee5aa by Sebastian Graf at 2024-01-12T21:16:21-05:00 Arity: Require called *exactly once* for eta exp with -fpedantic-bottoms (#24296) In #24296, we had a program in which we eta expanded away an error despite the presence of `-fpedantic-bottoms`. This was caused by turning called *at least once* lambdas into one-shot lambdas, while with `-fpedantic-bottoms` it is only sound to eta expand over lambdas that are called *exactly* once. An example can be found in `Note [Combining arity type with demand info]`. Fixes #24296. - - - - - 7e95f738 by Andreas Klebinger at 2024-01-12T21:16:57-05:00 Aarch64: Enable -mfma by default. Fixes #24311 - - - - - e43788d0 by Jason Shipman at 2024-01-14T12:47:38-05:00 Add more instances for Compose: Fractional, RealFrac, Floating, RealFloat CLC proposal #226 https://github.com/haskell/core-libraries-committee/issues/226 - - - - - ae6d8cd2 by Sebastian Graf at 2024-01-14T12:48:15-05:00 Pmc: COMPLETE pragmas associated with Family TyCons should apply to representation TyCons as well (#24326) Fixes #24326. - - - - - c5fc7304 by sheaf at 2024-01-15T14:15:29-05:00 Use lookupOccRn_maybe in TH.lookupName When looking up a value, we want to be able to find both variables and record fields. So we should not use the lookupSameOccRn_maybe function, as we can't know ahead of time which record field namespace a record field with the given textual name will belong to. Fixes #24293 - - - - - da908790 by Krzysztof Gogolewski at 2024-01-15T14:16:05-05:00 Make the build more strict on documentation errors * Detect undefined labels. This can be tested by adding :ref:`nonexistent` to a documentation rst file; attempting to build docs will fail. Fixed the undefined label in `9.8.1-notes.rst`. * Detect errors. While we have plenty of warnings, we can at least enforce that Sphinx does not report errors. Fixed the error in `required_type_arguments.rst`. Unrelated change: I have documented that the `-dlint` enables `-fcatch-nonexhaustive-cases`, as can be verified by checking `enableDLint`. - - - - - 5077416e by Javier Sagredo at 2024-01-16T15:40:06-05:00 Profiling: Adds an option to not start time profiling at startup Using the functionality provided by d89deeba47ce04a5198a71fa4cbc203fe2c90794, this patch creates a new rts flag `--no-automatic-time-samples` which disables the time profiling when starting a program. It is then expected that the user starts it whenever it is needed. Fixes #24337 - - - - - 5776008c by Matthew Pickering at 2024-01-16T15:40:42-05:00 eventlog: Fix off-by-one error in postIPE We were missing the extra_comma from the calculation of the size of the payload of postIPE. This was causing assertion failures when the event would overflow the buffer by one byte, as ensureRoomForVariable event would report there was enough space for `n` bytes but then we would write `n + 1` bytes into the buffer. Fixes #24287 - - - - - 66dc09b1 by Simon Peyton Jones at 2024-01-16T15:41:18-05:00 Improve SpecConstr (esp nofib/spectral/ansi) This MR makes three improvements to SpecConstr: see #24282 * It fixes an outright (and recently-introduced) bug in `betterPat`, which was wrongly forgetting to compare the lengths of the argument lists. * It enhances ConVal to inclue a boolean for work-free-ness, so that the envt can contain non-work-free constructor applications, so that we can do more: see Note [ConVal work-free-ness] * It rejigs `subsumePats` so that it doesn't reverse the list. This can make a difference because, when patterns overlap, we arbitrarily pick the first. There is no "right" way, but this retains the old pre-subsumePats behaviour, thereby "fixing" the regression in #24282. Nofib results +======================================== | spectral/ansi -21.14% | spectral/hartel/comp_lab_zift -0.12% | spectral/hartel/parstof +0.09% | spectral/last-piece -2.32% | spectral/multiplier +6.03% | spectral/para +0.60% | spectral/simple -0.26% +======================================== | geom mean -0.18% +---------------------------------------- The regression in `multiplier` is sad, but it simply replicates GHC's previous behaviour (e.g. GHC 9.6). - - - - - 65da79b3 by Matthew Pickering at 2024-01-16T15:41:54-05:00 hadrian: Reduce Cabal verbosity The comment claims that `simpleUserHooks` decrease verbosity, and it does, but only for the `postConf` phase. The other phases are too verbose with `-V`. At the moment > 5000 lines of the build log are devoted to output from `cabal copy`. So I take the simple approach and just decrease the verbosity level again. If the output of `postConf` is essential then it would be better to implement our own `UserHooks` which doesn't decrease the verbosity for `postConf`. Fixes #24338 - - - - - 16414d7d by Matthew Pickering at 2024-01-17T10:54:59-05:00 Stop retaining old ModGuts throughout subsequent simplifier phases Each phase of the simplifier typically rewrites the majority of ModGuts, so we want to be able to release the old ModGuts as soon as possible. `name_ppr_ctxt` lives throught the whole optimiser phase and it was retaining a reference to `ModGuts`, so we were failing to release the old `ModGuts` until the end of the phase (potentially doubling peak memory usage for that particular phase). This was discovered using eras profiling (#24332) Fixes #24328 - - - - - 7f0879e1 by Matthew Pickering at 2024-01-17T10:55:35-05:00 Update nofib submodule - - - - - 320454d3 by Cheng Shao at 2024-01-17T23:02:40+00:00 ci: bump ci-images for updated wasm image - - - - - 2eca52b4 by Cheng Shao at 2024-01-17T23:06:44+00:00 base: treat all FDs as "nonblocking" on wasm On posix platforms, when performing read/write on FDs, we check the nonblocking flag first. For FDs without this flag (e.g. stdout), we call fdReady() first, which in turn calls poll() to wait for I/O to be available on that FD. This is problematic for wasm32-wasi: although select()/poll() is supported via the poll_oneoff() wasi syscall, that syscall is rather heavyweight and runtime behavior differs in different wasi implementations. The issue is even worse when targeting browsers, given there's no satisfactory way to implement async I/O as a synchronous syscall, so existing JS polyfills for wasi often give up and simply return ENOSYS. Before we have a proper I/O manager that avoids poll_oneoff() for async I/O on wasm, this patch improves the status quo a lot by merely pretending all FDs are "nonblocking". Read/write on FDs will directly invoke read()/write(), which are much more reliably handled in existing wasi implementations, especially those in browsers. Fixes #23275 and the following test cases: T7773 isEOF001 openFile009 T4808 cgrun025 Approved by CLC proposal #234: https://github.com/haskell/core-libraries-committee/issues/234 - - - - - 83c6c710 by Andrew Lelechenko at 2024-01-18T05:21:49-05:00 base: clarify how to disable warnings about partiality of Data.List.{head,tail} - - - - - c4078f2f by Simon Peyton Jones at 2024-01-18T05:22:25-05:00 Fix four bug in handling of (forall cv. body_ty) These bugs are all described in #24335 It's not easy to provoke the bug, hence no test case. - - - - - 119586ea by Alexis King at 2024-01-19T00:08:00-05:00 Always refresh profiling CCSes after running pending initializers Fixes #24171. - - - - - 9718d970 by Oleg Grenrus at 2024-01-19T00:08:36-05:00 Set default-language: GHC2021 in ghc library Go through compiler/ sources, and remove all BangPatterns (and other GHC2021 enabled extensions in these files). - - - - - 3ef71669 by Matthew Pickering at 2024-01-19T21:55:16-05:00 testsuite: Remove unused have_library function Also remove the hence unused testsuite option `--test-package-db`. Fixes #24342 - - - - - 5b7fa20c by Jade at 2024-01-19T21:55:53-05:00 Fix Spelling in the compiler Tracking: #16591 - - - - - 09875f48 by Matthew Pickering at 2024-01-20T12:20:44-05:00 testsuite: Implement `isInTreeCompiler` in a more robust way Just a small refactoring to avoid redundantly specifying the same strings in two different places. - - - - - 0d12b987 by Jade at 2024-01-20T12:21:20-05:00 Change maintainer email from cvs-ghc at haskell.org to ghc-devs at haskell.org. Fixes #22142 - - - - - eebdd316 by Apoorv Ingle at 2024-01-23T13:49:12+00:00 Changes for haskell/haddock#18324 - - - - - 1fa1c00c by Jade at 2024-01-23T19:17:03-05:00 Enhance Documentation of functions exported by Data.Function This patch aims to improve the documentation of functions exported in Data.Function Tracking: #17929 Fixes: #10065 - - - - - ab47a43d by Jade at 2024-01-23T19:17:39-05:00 Improve documentation of hGetLine. - Add explanation for whether a newline is returned - Add examples Fixes #14804 - - - - - dd4af0e5 by Cheng Shao at 2024-01-23T19:18:17-05:00 Fix genapply for cross-compilation by nuking fragile CPP logic This commit fixes incorrectly built genapply when cross compiling (#24347) by nuking all fragile CPP logic in it from the orbit. All target-specific info are now read from DerivedConstants.h at runtime, see added note for details. Also removes a legacy Makefile and adds haskell language server support for genapply. - - - - - 0cda2b8b by Cheng Shao at 2024-01-23T19:18:17-05:00 rts: enable wasm32 register mapping The wasm backend didn't properly make use of all Cmm global registers due to #24347. Now that it is fixed, this patch re-enables full register mapping for wasm32, and we can now generate smaller & faster wasm modules that doesn't always spill arguments onto the stack. Fixes #22460 #24152. - - - - - 0325a6e5 by Greg Steuck at 2024-01-24T01:29:44-05:00 Avoid utf8 in primops.txt.pp comments They don't make it through readFile' without explicitly setting the encoding. See https://gitlab.haskell.org/ghc/ghc/-/issues/17755 - - - - - 1aaf0bd8 by David Binder at 2024-01-24T01:30:20-05:00 Bump hpc and hpc-bin submodule Bump hpc to 0.7.0.1 Bump hpc-bin to commit d1780eb2 - - - - - e693a4e8 by Ben Gamari at 2024-01-24T01:30:56-05:00 testsuite: Ignore stderr in T8089 Otherwise spurious "Killed: 9" messages to stderr may cause the test to fail. Fixes #24361. - - - - - a40f4ab2 by sheaf at 2024-01-24T14:04:33-05:00 Fix FMA instruction on LLVM We were emitting the wrong instructions for fused multiply-add operations on LLVM: - the instruction name is "llvm.fma.f32" or "llvm.fma.f64", not "fmadd" - LLVM does not support other instructions such as "fmsub"; instead we implement these by flipping signs of some arguments - the instruction is an LLVM intrinsic, which requires handling it like a normal function call instead of a machine instruction Fixes #24223 - - - - - 69abc786 by Andrei Borzenkov at 2024-01-24T14:05:09-05:00 Add changelog entry for renaming tuples from (,,...,,) to Tuple<n> (24291) - - - - - 0ac8f385 by Cheng Shao at 2024-01-25T00:27:48-05:00 compiler: remove unused GHC.Linker module The GHC.Linker module is empty and unused, other than as a hack for the make build system. We can remove it now that make is long gone; the note is moved to GHC.Linker.Loader instead. - - - - - 699da01b by Hécate Moonlight at 2024-01-25T00:28:27-05:00 Clarification for newtype constructors when using `coerce` - - - - - b2d8cd85 by Matt Walker at 2024-01-26T09:50:08-05:00 Fix #24308 Add tests for semicolon separated where clauses - - - - - 0da490a1 by Ben Gamari at 2024-01-26T17:34:41-05:00 hsc2hs: Bump submodule - - - - - 3f442fd2 by Ben Gamari at 2024-01-26T17:34:41-05:00 Bump containers submodule to 0.7 - - - - - 82a1c656 by Sebastian Nagel at 2024-01-29T02:32:40-05:00 base: with{Binary}File{Blocking} only annotates own exceptions Fixes #20886 This ensures that inner, unrelated exceptions are not misleadingly annotated with the opened file. - - - - - 9294a086 by Andreas Klebinger at 2024-01-29T02:33:15-05:00 Fix fma warning when using llvm on aarch64. On aarch64 fma is always on so the +fma flag doesn't exist for that target. Hence no need to try and pass +fma to llvm. Fixes #24379 - - - - - ced2e731 by sheaf at 2024-01-29T17:27:12-05:00 No shadowing warnings for NoFieldSelector fields This commit ensures we don't emit shadowing warnings when a user shadows a field defined with NoFieldSelectors. Fixes #24381 - - - - - 8eeadfad by Patrick at 2024-01-29T17:27:51-05:00 Fix bug wrong span of nested_doc_comment #24378 close #24378 1. Update the start position of span in `nested_doc_comment` correctly. and hence the spans of identifiers of haddoc can be computed correctly. 2. add test `HaddockSpanIssueT24378`. - - - - - a557580f by Alexey Radkov at 2024-01-30T19:41:52-05:00 Fix irrelevant dodgy-foreign-imports warning on import f-pointers by value A test *сс018* is attached (not sure about the naming convention though). Note that without the fix, the test fails with the *dodgy-foreign-imports* warning passed to stderr. The warning disappears after the fix. GHC shouldn't warn on imports of natural function pointers from C by value (which is feasible with CApiFFI), such as ```haskell foreign import capi "cc018.h value f" f :: FunPtr (Int -> IO ()) ``` where ```c void (*f)(int); ``` See a related real-world use-case [here](https://gitlab.com/daniel-casanueva/pcre-light/-/merge_requests/17). There, GHC warns on import of C function pointer `pcre_free`. - - - - - ca99efaf by Alexey Radkov at 2024-01-30T19:41:53-05:00 Rename test cc018 -> T24034 - - - - - 88c38dd5 by Ben Gamari at 2024-01-30T19:42:28-05:00 rts/TraverseHeap.c: Ensure that PosixSource.h is included first - - - - - ca2e919e by Simon Peyton Jones at 2024-01-31T09:29:45+00:00 Make decomposeRuleLhs a bit more clever This fixes #24370 by making decomposeRuleLhs undertand dictionary /functions/ as well as plain /dictionaries/ - - - - - 94ce031d by Teo Camarasu at 2024-02-01T05:49:49-05:00 doc: Add -Dn flag to user guide Resolves #24394 - - - - - 31553b11 by Ben Gamari at 2024-02-01T12:21:29-05:00 cmm: Introduce MO_RelaxedRead In hand-written Cmm it can sometimes be necessary to atomically load from memory deep within an expression (e.g. see the `CHECK_GC` macro). This MachOp provides a convenient way to do so without breaking the expression into multiple statements. - - - - - 0785cf81 by Ben Gamari at 2024-02-01T12:21:29-05:00 codeGen: Use relaxed accesses in ticky bumping - - - - - be423dda by Ben Gamari at 2024-02-01T12:21:29-05:00 base: use atomic write when updating timer manager - - - - - 8a310e35 by Ben Gamari at 2024-02-01T12:21:29-05:00 Use relaxed atomics to manipulate TSO status fields - - - - - d6809ee4 by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Add necessary barriers when manipulating TSO owner - - - - - 39e3ac5d by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Use `switch` to branch on why_blocked This is a semantics-preserving refactoring. - - - - - 515eb33d by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix synchronization on thread blocking state We now use a release barrier whenever we update a thread's blocking state. This required widening StgTSO.why_blocked as AArch64 does not support atomic writes on 16-bit values. - - - - - eb38812e by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix data race in threadPaused This only affects an assertion in the debug RTS and only needs relaxed ordering. - - - - - 26c48dd6 by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix data race in threadStatus# - - - - - 6af43ab4 by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix data race in Interpreter's preemption check - - - - - 9502ad3c by Ben Gamari at 2024-02-01T12:21:29-05:00 rts/Messages: Fix data race - - - - - 60802db5 by Ben Gamari at 2024-02-01T12:21:30-05:00 rts/Prof: Fix data race - - - - - ef8ccef5 by Ben Gamari at 2024-02-01T12:21:30-05:00 rts: Use relaxed ordering on dirty/clean info tables updates When changing the dirty/clean state of a mutable object we needn't have any particular ordering. - - - - - 76fe2b75 by Ben Gamari at 2024-02-01T12:21:30-05:00 codeGen: Use relaxed-read in closureInfoPtr - - - - - a6316eb4 by Ben Gamari at 2024-02-01T12:21:30-05:00 STM: Use acquire loads when possible Full sequential consistency is not needed here. - - - - - 6bddfd3d by Ben Gamari at 2024-02-01T12:21:30-05:00 rts: Use fence rather than redundant load Previously we would use an atomic load to ensure acquire ordering. However, we now have `ACQUIRE_FENCE_ON`, which allows us to express this more directly. - - - - - 55c65dbc by Ben Gamari at 2024-02-01T12:21:30-05:00 rts: Fix data races in profiling timer - - - - - 856b5e75 by Ben Gamari at 2024-02-01T12:21:30-05:00 Add Note [C11 memory model] - - - - - 6534da24 by Cheng Shao at 2024-02-01T12:22:07-05:00 compiler: move generic cmm optimization logic in NCG to a standalone module This commit moves GHC.CmmToAsm.cmmToCmm to a standalone module, GHC.Cmm.GenericOpt. The main motivation is enabling this logic to be run in the wasm backend NCG code, which is defined in other modules that's imported by GHC.CmmToAsm, causing a cyclic dependency issue. - - - - - 87e34888 by Cheng Shao at 2024-02-01T12:22:07-05:00 compiler: explicitly disable PIC in wasm32 NCG This commit explicitly disables the ncgPIC flag for the wasm32 target. The wasm backend doesn't support PIC for the time being. - - - - - c6ce242e by Cheng Shao at 2024-02-01T12:22:07-05:00 compiler: enable generic cmm optimizations in wasm backend NCG This commit enables the generic cmm optimizations in other NCGs to be run in the wasm backend as well, followed by a late cmm control-flow optimization pass. The added optimizations do catch some corner cases not handled by the pre-NCG cmm pipeline and are useful in generating smaller CFGs. - - - - - 151dda4e by Andrei Borzenkov at 2024-02-01T12:22:43-05:00 Namespacing for WARNING/DEPRECATED pragmas (#24396) New syntax for WARNING and DEPRECATED pragmas was added, namely namespace specifierss: namespace_spec ::= 'type' | 'data' | {- empty -} warning ::= warning_category namespace_spec namelist strings deprecation ::= namespace_spec namelist strings A new data type was introduced to represent these namespace specifiers: data NamespaceSpecifier = NoSpecifier | TypeNamespaceSpecifier (EpToken "type") | DataNamespaceSpecifier (EpToken "data") Extension field XWarning now contains this NamespaceSpecifier. lookupBindGroupOcc function was changed: it now takes NamespaceSpecifier and checks that the namespace of the found names matches the passed flag. With this change {-# WARNING data D "..." #-} pragma will only affect value namespace and {-# WARNING type D "..." #-} will only affect type namespace. The same logic is applicable to DEPRECATED pragmas. Finding duplicated warnings inside rnSrcWarnDecls now takes into consideration NamespaceSpecifier flag to allow warnings with the same names that refer to different namespaces. - - - - - 38c3afb6 by Bryan Richter at 2024-02-01T12:23:19-05:00 CI: Disable the test-cabal-reinstall job Fixes #24363 - - - - - 27020458 by Matthew Craven at 2024-02-03T01:53:26-05:00 Bump bytestring submodule to something closer to 0.12.1 ...mostly so that 16d6b7e835ffdcf9b894e79f933dd52348dedd0c (which reworks unaligned writes in Builder) and the stuff in https://github.com/haskell/bytestring/pull/631 can see wider testing. The less-terrible code for unaligned writes used in Builder on hosts not known to be ulaigned-friendly also takes less effort for GHC to compile, resulting in a metric decrease for T21839c on some platforms. The metric increase on T21839r is caused by the unrelated commit 750dac33465e7b59100698a330b44de7049a345c. It perhaps warrants further analysis and discussion (see #23822) but is not critical. Metric Decrease: T21839c Metric Increase: T21839r - - - - - cdddeb0f by Rodrigo Mesquita at 2024-02-03T01:54:02-05:00 Work around autotools setting C11 standard in CC/CXX In autoconf >=2.70, C11 is set by default for $CC and $CXX via the -std=...11 flag. In this patch, we split the "-std" flag out of the $CC and $CXX variables, which we traditionally assume to be just the executable name/path, and move it to $CFLAGS/$CXXFLAGS instead. Fixes #24324 - - - - - 5ff7cc26 by Apoorv Ingle at 2024-02-03T13:14:46-06:00 Expand `do` blocks right before typechecking using the `HsExpansion` philosophy. - Fixes #18324 #20020 #23147 #22788 #15598 #22086 #21206 - The change is detailed in - Note [Expanding HsDo with HsExpansion] in `GHC.Tc.Gen.Do` - Note [Doing HsExpansion in the Renamer vs Typechecker] in `GHC.Rename.Expr` expains the rational of doing expansions in type checker as opposed to in the renamer - Adds new datatypes: - `GHC.Hs.Expr.XXExprGhcRn`: new datatype makes this expansion work easier 1. Expansion bits for Expressions, Statements and Patterns in (`ExpandedThingRn`) 2. `PopErrCtxt` a special GhcRn Phase only artifcat to pop the previous error message in the error context stack - `GHC.Basic.Origin` now tracks the reason for expansion in case of Generated This is useful for type checking cf. `GHC.Tc.Gen.Expr.tcExpr` case for `HsLam` - Kills `HsExpansion` and `HsExpanded` as we have inlined them in `XXExprGhcRn` and `XXExprGhcTc` - Ensures warnings such as 1. Pattern match checks 2. Failable patterns 3. non-() return in body statements are preserved - Kill `HsMatchCtxt` in favor of `TcMatchAltChecker` - Testcases: * T18324 T20020 T23147 T22788 T15598 T22086 * T23147b (error message check), * DoubleMatch (match inside a match for pmc check) * pattern-fails (check pattern match with non-refutable pattern, eg. newtype) * Simple-rec (rec statements inside do statment) * T22788 (code snippet from #22788) * DoExpanion1 (Error messages for body statments) * DoExpansion2 (Error messages for bind statements) * DoExpansion3 (Error messages for let statements) Also repoint haddock to the right submodule so that the test (haddockHypsrcTest) pass Metric Increase 'compile_time/bytes allocated': T9020 The testcase is a pathalogical example of a `do`-block with many statements that do nothing. Given that we are expanding the statements into function binds, we will have to bear a (small) 2% cost upfront in the compiler to unroll the statements. - - - - - 0df8ce27 by Vladislav Zavialov at 2024-02-04T03:55:14-05:00 Reduce parser allocations in allocateCommentsP In the most common case, the comment queue is empty, so we can skip the work of processing it. This reduces allocations by about 10% in the parsing001 test. Metric Decrease: MultiLayerModulesRecomp parsing001 - - - - - ae856a82 by Matthew Pickering at 2024-02-05T12:22:39+00:00 ghc-internals fallout - - - - - cfd68290 by Simon Peyton Jones at 2024-02-05T17:58:33-05:00 Stop dropping a case whose binder is demanded This MR fixes #24251. See Note [Case-to-let for strictly-used binders] in GHC.Core.Opt.Simplify.Iteration, plus #24251, for lots of discussion. Final Nofib changes over 0.1%: +----------------------------------------- | imaginary/digits-of-e2 -2.16% | imaginary/rfib -0.15% | real/fluid -0.10% | real/gamteb -1.47% | real/gg -0.20% | real/maillist +0.19% | real/pic -0.23% | real/scs -0.43% | shootout/n-body -0.41% | shootout/spectral-norm -0.12% +======================================== | geom mean -0.05% Pleasingly, overall executable size is down by just over 1%. Compile times (in perf/compiler) wobble around a bit +/- 0.5%, but the geometric mean is -0.1% which seems good. - - - - - e4d137bb by Simon Peyton Jones at 2024-02-05T17:58:33-05:00 Add Note [Bangs in Integer functions] ...to document the bangs in the functions in GHC.Num.Integer - - - - - ce90f12f by Andrei Borzenkov at 2024-02-05T17:59:09-05:00 Hide WARNING/DEPRECATED namespacing under -XExplicitNamespaces (#24396) - - - - - e2ea933f by Simon Peyton Jones at 2024-02-06T10:12:04-05:00 Refactoring in preparation for lazy skolemisation * Make HsMatchContext and HsStmtContext be parameterised over the function name itself, rather than over the pass. See [mc_fun field of FunRhs] in Language.Haskell.Syntax.Expr - Replace types HsMatchContext GhcPs --> HsMatchContextPs HsMatchContext GhcRn --> HsMatchContextRn HsMatchContext GhcTc --> HsMatchContextRn (sic! not Tc) HsStmtContext GhcRn --> HsStmtContextRn - Kill off convertHsMatchCtxt * Split GHC.Tc.Type.BasicTypes.TcSigInfo so that TcCompleteSig (describing a complete user-supplied signature) is its own data type. - Split TcIdSigInfo(CompleteSig, PartialSig) into TcCompleteSig(CSig) TcPartialSig(PSig) - Use TcCompleteSig in tcPolyCheck, CheckGen - Rename types and data constructors: TcIdSigInfo --> TcIdSig TcPatSynInfo(TPSI) --> TcPatSynSig(PatSig) - Shuffle around helper functions: tcSigInfoName (moved to GHC.Tc.Types.BasicTypes) completeSigPolyId_maybe (moved to GHC.Tc.Types.BasicTypes) tcIdSigName (inlined and removed) tcIdSigLoc (introduced) - Rearrange the pattern match in chooseInferredQuantifiers * Rename functions and types: tcMatchesCase --> tcCaseMatches tcMatchesFun --> tcFunBindMatches tcMatchLambda --> tcLambdaMatches tcPats --> tcMatchPats matchActualFunTysRho --> matchActualFunTys matchActualFunTySigma --> matchActualFunTy * Add HasDebugCallStack constraints to: mkBigCoreVarTupTy, mkBigCoreTupTy, boxTy, mkPiTy, mkPiTys, splitAppTys, splitTyConAppNoView_maybe * Use `penv` from the outer context in the inner loop of GHC.Tc.Gen.Pat.tcMultiple * Move tcMkVisFunTy, tcMkInvisFunTy, tcMkScaledFunTys down the file, factor out and export tcMkScaledFunTy. * Move isPatSigCtxt down the file. * Formatting and comments Co-authored-by: Vladislav Zavialov <vlad.z.4096 at gmail.com> - - - - - f5d3e03c by Andrei Borzenkov at 2024-02-06T10:12:04-05:00 Lazy skolemisation for @a-binders (#17594) This patch is a preparation for @a-binders implementation. The main changes are: * Skolemisation is now prepared to deal with @binders. See Note [Skolemisation overview] in GHC.Tc.Utils.Unify. Most of the action is in - Utils.Unify.matchExpectedFunTys - Gen.Pat.tcMatchPats - Gen.Expr.tcPolyExprCheck - Gen.Binds.tcPolyCheck Some accompanying refactoring: * I found that funTyConAppTy_maybe was doing a lot of allocation, and rejigged userTypeError_maybe to avoid calling it. - - - - - 532993c8 by Zubin Duggal at 2024-02-06T10:12:41-05:00 driver: Really don't lose track of nodes when we fail to resolve cycles This fixes a bug in 8db8d2fd1c881032b1b360c032b6d9d072c11723, where we could lose track of acyclic components at the start of an unresolved cycle. We now ensure we never loose track of any of these components. As T24275 demonstrates, a "cyclic" SCC might not really be a true SCC: When viewed without boot files, we have a single SCC ``` [REC main:T24275B [main:T24275B {-# SOURCE #-}, main:T24275A {-# SOURCE #-}] main:T24275A [main:T24275A {-# SOURCE #-}]] ``` But with boot files this turns into ``` [NONREC main:T24275B {-# SOURCE #-} [], REC main:T24275B [main:T24275B {-# SOURCE #-}, main:T24275A {-# SOURCE #-}] main:T24275A {-# SOURCE #-} [main:T24275B], NONREC main:T24275A [main:T24275A {-# SOURCE #-}]] ``` Note that this is truly not an SCC, as no nodes are reachable from T24275B.hs-boot. However, we treat this entire group as a single "SCC" because it seems so when we analyse the graph without taking boot files into account. Indeed, we must return a single ResolvedCycle element in the BuildPlan for this as described in Note [Upsweep]. However, since after resolving this is not a true SCC anymore, `findCycle` fails to find a cycle and we have a sub-optimal error message as a result. To handle this, I extended `findCycle` to not assume its input is an SCC, and to try harder to find cycles in its input. Fixes #24275 - - - - - b35dd613 by Zubin Duggal at 2024-02-06T10:13:17-05:00 GHCi: Lookup breakpoint CCs in the correct module We need to look up breakpoint CCs in the module that the breakpoint points to, and not the current module. Fixes #24327 - - - - - b09e6958 by Zubin Duggal at 2024-02-06T10:13:17-05:00 testsuite: Add test for #24327 - - - - - 569b4c10 by doyougnu at 2024-02-07T03:06:26-05:00 ts: add compile_artifact, ignore_extension flag In b521354216f2821e00d75f088d74081d8b236810 the testsuite gained the capability to collect generic metrics. But this assumed that the test was not linking and producing artifacts and we only wanted to track object files, interface files, or build artifacts from the compiler build. However, some backends, such as the JS backend, produce artifacts when compiling, such as the jsexe directory which we want to track. This patch: - tweaks the testsuite to collect generic metrics on any build artifact in the test directory. - expands the exe_extension function to consider windows and adds the ignore_extension flag. - Modifies certain tests to add the ignore_extension flag. Tests such as heaprof002 expect a .ps file, but on windows without ignore_extensions the testsuite will look for foo.exe.ps. Hence the flag. - adds the size_hello_artifact test - - - - - 75a31379 by doyougnu at 2024-02-07T03:06:26-05:00 ts: add wasm_arch, heapprof002 wasm extension - - - - - c9731d6d by Rodrigo Mesquita at 2024-02-07T03:07:03-05:00 Synchronize bindist configure for #24324 In cdddeb0f1280b40cc194028bbaef36e127175c4c, we set up a workaround for #24324 in the in-tree configure script, but forgot to update the bindist configure script accordingly. This updates it. - - - - - d309f4e7 by Matthew Pickering at 2024-02-07T03:07:38-05:00 distrib/configure: Fix typo in CONF_GCC_LINKER_OPTS_STAGE2 variable Instead we were setting CONF_GCC_LINK_OPTS_STAGE2 which meant that we were missing passing `--target` when invoking the linker. Fixes #24414 - - - - - 77db84ab by Ben Gamari at 2024-02-08T00:35:22-05:00 llvmGen: Adapt to allow use of new pass manager. We now must use `-passes` in place of `-O<n>` due to #21936. Closes #21936. - - - - - 3c9ddf97 by Matthew Pickering at 2024-02-08T00:35:59-05:00 testsuite: Mark length001 as fragile on javascript Modifying the timeout multiplier is not a robust way to get this test to reliably fail. Therefore we mark it as fragile until/if javascript ever supports the stack limit. - - - - - 20b702b5 by Matthew Pickering at 2024-02-08T00:35:59-05:00 Javascript: Don't filter out rtsDeps list This logic appears to be incorrect as it would drop any dependency which was not in a direct dependency of the package being linked. In the ghc-internals split this started to cause errors because `ghc-internal` is not a direct dependency of most packages, and hence important symbols to keep which are hard coded into the js runtime were getting dropped. - - - - - 2df96366 by Ben Gamari at 2024-02-08T00:35:59-05:00 base: Cleanup whitespace in cbits - - - - - 44f6557a by Ben Gamari at 2024-02-08T00:35:59-05:00 Move `base` to `ghc-internal` Here we move a good deal of the implementation of `base` into a new package, `ghc-internal` such that it can be evolved independently from the user-visible interfaces of `base`. While we want to isolate implementation from interfaces, naturally, we would like to avoid turning `base` into a mere set of module re-exports. However, this is a non-trivial undertaking for a variety of reasons: * `base` contains numerous known-key and wired-in things, requiring corresponding changes in the compiler * `base` contains a significant amount of C code and corresponding autoconf logic, which is very fragile and difficult to break apart * `base` has numerous import cycles, which are currently dealt with via carefully balanced `hs-boot` files * We must not break existing users To accomplish this migration, I tried the following approaches: * [Split-GHC.Base]: Break apart the GHC.Base knot to allow incremental migration of modules into ghc-internal: this knot is simply too intertwined to be easily pulled apart, especially given the rather tricky import cycles that it contains) * [Move-Core]: Moving the "core" connected component of base (roughly 150 modules) into ghc-internal. While the Haskell side of this seems tractable, the C dependencies are very subtle to break apart. * [Move-Incrementally]: 1. Move all of base into ghc-internal 2. Examine the module structure and begin moving obvious modules (e.g. leaves of the import graph) back into base 3. Examine the modules remaining in ghc-internal, refactor as necessary to facilitate further moves 4. Go to (2) iterate until the cost/benefit of further moves is insufficient to justify continuing 5. Rename the modules moved into ghc-internal to ensure that they don't overlap with those in base 6. For each module moved into ghc-internal, add a shim module to base with the declarations which should be exposed and any requisite Haddocks (thus guaranteeing that base will be insulated from changes in the export lists of modules in ghc-internal Here I am using the [Move-Incrementally] approach, which is empirically the least painful of the unpleasant options above Bumps haddock submodule. Metric Decrease: haddock.Cabal haddock.base Metric Increase: MultiComponentModulesRecomp T16875 size_hello_artifact - - - - - e8fb2451 by Vladislav Zavialov at 2024-02-08T00:36:36-05:00 Haddock comments on infix constructors (#24221) Rewrite the `HasHaddock` instance for `ConDecl GhcPs` to account for infix constructors. This change fixes a Haddock regression (introduced in 19e80b9af252) that affected leading comments on infix data constructor declarations: -- | Docs for infix constructor | Int :* Bool The comment should be associated with the data constructor (:*), not with its left-hand side Int. - - - - - 9060d55b by Ben Gamari at 2024-02-08T00:37:13-05:00 Add os-string as a boot package Introduces `os-string` submodule. This will be necessary for `filepath-1.5`. - - - - - 9d65235a by Ben Gamari at 2024-02-08T00:37:13-05:00 gitignore: Ignore .hadrian_ghci_multi/ - - - - - d7ee12ea by Ben Gamari at 2024-02-08T00:37:13-05:00 hadrian: Set -this-package-name When constructing the GHC flags for a package Hadrian must take care to set `-this-package-name` in addition to `-this-unit-id`. This hasn't broken until now as we have not had any uses of qualified package imports. However, this will change with `filepath-1.5` and the corresponding `unix` bump, breaking `hadrian/multi-ghci`. - - - - - f2dffd2e by Ben Gamari at 2024-02-08T00:37:13-05:00 Bump filepath to 1.5.0.0 Required bumps of the following submodules: * `directory` * `filepath` * `haskeline` * `process` * `unix` * `hsc2hs` * `Win32` * `semaphore-compat` and the addition of `os-string` as a boot package. - - - - - ab533e71 by Matthew Pickering at 2024-02-08T00:37:50-05:00 Use specific clang assembler when compiling with -fllvm There are situations where LLVM will produce assembly which older gcc toolchains can't handle. For example on Deb10, it seems that LLVM >= 13 produces assembly which the default gcc doesn't support. A more robust solution in the long term is to require a specific LLVM compatible assembler when using -fllvm. Fixes #16354 - - - - - c32b6426 by Matthew Pickering at 2024-02-08T00:37:50-05:00 Update CI images with LLVM 15, ghc-9.6.4 and cabal-install-3.10.2.0 - - - - - 5fcd58be by Matthew Pickering at 2024-02-08T00:37:50-05:00 Update bootstrap plans for 9.4.8 and 9.6.4 - - - - - 707a32f5 by Matthew Pickering at 2024-02-08T00:37:50-05:00 Add alpine 3_18 release job This is mainly experimental and future proofing to enable a smooth transition to newer alpine releases once 3_12 is too old. - - - - - c37931b3 by John Ericson at 2024-02-08T06:39:05-05:00 Generate LLVM min/max bound policy via Hadrian Per #23966, I want the top-level configure to only generate configuration data for Hadrian, not do any "real" tasks on its own. This is part of that effort --- one less file generated by it. (It is still done with a `.in` file, so in a future world non-Hadrian also can easily create this file.) Split modules: - GHC.CmmToLlvm.Config - GHC.CmmToLlvm.Version - GHC.CmmToLlvm.Version.Bounds - GHC.CmmToLlvm.Version.Type This also means we can get rid of the silly `unused.h` introduced in !6803 / 7dfcab2f4bcb7206174ea48857df1883d05e97a2 as temporary kludge. Part of #23966 - - - - - 9f987235 by Apoorv Ingle at 2024-02-08T06:39:42-05:00 Enable mdo statements to use HsExpansions Fixes: #24411 Added test T24411 for regression - - - - - f8429266 by Jade at 2024-02-08T14:56:50+01:00 Adjust test for ghc MR !10993 - - - - - 762b2120 by Jade at 2024-02-08T15:17:15+00:00 Improve Monad, Functor & Applicative docs This patch aims to improve the documentation of Functor, Applicative, Monad and related symbols. The main goal is to make it more consistent and make accessible. See also: !10979 (closed) and !10985 (closed) Ticket #17929 Updates haddock submodule - - - - - 151770ca by Josh Meredith at 2024-02-10T14:28:15-05:00 JavaScript codegen: Use GHC's tag inference where JS backend-specific evaluation inference was previously used (#24309) - - - - - 2e880635 by Zubin Duggal at 2024-02-10T14:28:51-05:00 ci: Allow release-hackage-lint to fail Otherwise it blocks the ghcup metadata pipeline from running. - - - - - b0293f78 by Matthew Pickering at 2024-02-10T14:29:28-05:00 rts: eras profiling mode The eras profiling mode is useful for tracking the life-time of closures. When a closure is written, the current era is recorded in the profiling header. This records the era in which the closure was created. * Enable with -he * User mode: Use functions ghc-experimental module GHC.Profiling.Eras to modify the era * Automatically: --automatic-era-increment, increases the user era on major collections * The first era is era 1 * -he<era> can be used with other profiling modes to select a specific era If you just want to record the era but not to perform heap profiling you can use `-he --no-automatic-heap-samples`. https://well-typed.com/blog/2024/01/ghc-eras-profiling/ Fixes #24332 - - - - - be674a2c by Jade at 2024-02-10T14:30:04-05:00 Adjust error message for trailing whitespace in as-pattern. Fixes #22524 - - - - - 53ef83f9 by doyougnu at 2024-02-10T14:30:47-05:00 gitlab: js: add codeowners Fixes: - #24409 Follow on from: - #21078 and MR !9133 - When we added the JS backend this was forgotten. This patch adds the rightful codeowners. - - - - - 8bbe12f2 by Matthew Pickering at 2024-02-10T14:31:23-05:00 Bump CI images so that alpine3_18 image includes clang15 The only changes here are that clang15 is now installed on the alpine-3_18 image. - - - - - df9fd9f7 by Sylvain Henry at 2024-02-12T12:18:42-05:00 JS: handle stored null StablePtr Some Haskell codes unsafely cast StablePtr into ptr to compare against NULL. E.g. in direct-sqlite: if castStablePtrToPtr aggStPtr /= nullPtr then where `aggStPtr` is read (`peek`) from zeroed memory initially. We fix this by giving these StablePtr the same representation as other null pointers. It's safe because StablePtr at offset 0 is unused (for this exact reason). - - - - - 55346ede by Sylvain Henry at 2024-02-12T12:18:42-05:00 JS: disable MergeObjsMode test This isn't implemented for JS backend objects. - - - - - aef587f6 by Sylvain Henry at 2024-02-12T12:18:42-05:00 JS: add support for linking C sources Support linking C sources with JS output of the JavaScript backend. See the added documentation in the users guide. The implementation simply extends the JS linker to use the objects (.o) that were already produced by the emcc compiler and which were filtered out previously. I've also added some options to control the link with C functions (see the documentation about pragmas). With this change I've successfully compiled the direct-sqlite package which embeds the sqlite.c database code. Some wrappers are still required (see the documentation about wrappers) but everything generic enough to be reused for other libraries have been integrated into rts/js/mem.js. - - - - - b71b392f by Sylvain Henry at 2024-02-12T12:18:42-05:00 JS: avoid EMCC logging spurious failure emcc would sometime output messages like: cache:INFO: generating system asset: symbol_lists/424b44514e43d789148e69e4e7d1c7fdc0350b79.json... (this will be cached in "/emsdk/upstream/emscripten/cache/symbol_lists/424b44514e43d789148e69e4e7d1c7fdc0350b79.json" for subsequent builds) cache:INFO: - ok Cf https://github.com/emscripten-core/emscripten/issues/18607 This breaks our tests matching the stderr output. We avoid this by setting EMCC_LOGGING=0 - - - - - ff2c0cc9 by Simon Peyton Jones at 2024-02-12T12:19:17-05:00 Remove a dead comment Just remove an out of date block of commented-out code, and tidy up the relevant Notes. See #8317. - - - - - bedb4f0d by Teo Camarasu at 2024-02-12T18:50:33-05:00 nonmoving: Add support for heap profiling Add support for heap profiling while using the nonmoving collector. We greatly simply the implementation by disabling concurrent collection for GCs when heap profiling is enabled. This entails that the marked objects on the nonmoving heap are exactly the live objects. Note that we match the behaviour for live bytes accounting by taking the size of objects on the nonmoving heap to be that of the segment's block rather than the object itself. Resolves #22221 - - - - - d0d5acb5 by Teo Camarasu at 2024-02-12T18:51:09-05:00 doc: Add requires prof annotation to options that require it Resolves #24421 - - - - - 6d1e2386 by Alan Zimmerman at 2024-02-13T22:00:28+03:00 EPA: Match changes to HsParTy and HsFunTy - - - - - 57bb8c92 by Cheng Shao at 2024-02-13T14:07:49-05:00 deriveConstants: add needed constants for wasm backend This commit adds needed constants to deriveConstants. They are used by RTS code in the wasm backend to support the JSFFI logic. - - - - - 615eb855 by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: make genSym use C-based atomic increment on non-JS 32-bit platforms The pure Haskell implementation causes i386 regression in unrelated work that can be fixed by using C-based atomic increment, see added comment for details. - - - - - a9918891 by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: allow JSFFI for wasm32 This commit allows the javascript calling convention to be used when the target platform is wasm32. - - - - - 8771a53b by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: allow boxed JSVal as a foreign type This commit allows the boxed JSVal type to be used as a foreign argument/result type. - - - - - 053c92b3 by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: ensure ctors have the right priority on wasm32 This commit fixes the priorities of ctors generated by GHC codegen on wasm32, see the referred note for details. - - - - - b7942e0a by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: add JSFFI desugar logic for wasm32 This commit adds JSFFI desugar logic for the wasm backend. - - - - - 2c1dca76 by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: add JavaScriptFFI to supported extension list on wasm32 This commit adds JavaScriptFFI as a supported extension when the target platform is wasm32. - - - - - 9ad0e2b4 by Cheng Shao at 2024-02-13T14:07:49-05:00 rts/ghc-internal: add JSFFI support logic for wasm32 This commit adds rts/ghc-internal logic to support the wasm backend's JSFFI functionality. - - - - - e9ebea66 by Cheng Shao at 2024-02-13T14:07:49-05:00 ghc-internal: fix threadDelay for wasm in browsers This commit fixes broken threadDelay for wasm when it runs in browsers, see added note for detailed explanation. - - - - - f85f3fdb by Cheng Shao at 2024-02-13T14:07:49-05:00 utils: add JSFFI utility code This commit adds JavaScript util code to utils to support the wasm backend's JSFFI functionality: - jsffi/post-link.mjs, a post-linker to process the linked wasm module and emit a small complement JavaScript ESM module to be used with it at runtime - jsffi/prelude.js, a tiny bit of prelude code as the JavaScript side of runtime logic - jsffi/test-runner.mjs, run the jsffi test cases Co-authored-by: amesgen <amesgen at amesgen.de> - - - - - 77e91500 by Cheng Shao at 2024-02-13T14:07:49-05:00 hadrian: distribute jsbits needed for wasm backend's JSFFI support The post-linker.mjs/prelude.js files are now distributed in the bindist libdir, so when using the wasm backend's JSFFI feature, the user wouldn't need to fetch them from a ghc checkout manually. - - - - - c47ba1c3 by Cheng Shao at 2024-02-13T14:07:49-05:00 testsuite: add opts.target_wrapper This commit adds opts.target_wrapper which allows overriding the target wrapper on a per test case basis when testing a cross target. This is used when testing the wasm backend's JSFFI functionality; the rest of the cases are tested using wasmtime, though the jsffi cases are tested using the node.js based test runner. - - - - - 8e048675 by Cheng Shao at 2024-02-13T14:07:49-05:00 testsuite: T22774 should work for wasm JSFFI T22774 works since the wasm backend now supports the JSFFI feature. - - - - - 1d07f9a6 by Cheng Shao at 2024-02-13T14:07:49-05:00 testsuite: add JSFFI test cases for wasm backend This commit adds a few test cases for the wasm backend's JSFFI functionality, as well as a simple README to instruct future contributors to add new test cases. - - - - - b8997080 by Cheng Shao at 2024-02-13T14:07:49-05:00 docs: add documentation for wasm backend JSFFI This commit adds changelog and user facing documentation for the wasm backend's JSFFI feature. - - - - - ffeb000d by David Binder at 2024-02-13T14:08:30-05:00 Add tests from libraries/process/tests and libraries/Win32/tests to GHC These tests were previously part of the libraries, which themselves are submodules of the GHC repository. This commit moves the tests directly to the GHC repository. - - - - - 5a932cf2 by David Binder at 2024-02-13T14:08:30-05:00 Do not execute win32 tests on non-windows runners - - - - - 500d8cb8 by Jade at 2024-02-13T14:09:07-05:00 prevent GHCi (and runghc) from suggesting other symbols when not finding main Fixes: #23996 - - - - - b19ec331 by Cheng Shao at 2024-02-13T14:09:46-05:00 rts: update xxHash to v0.8.2 - - - - - 4a97bdb8 by Cheng Shao at 2024-02-13T14:09:46-05:00 rts: use XXH3_64bits hash on all 64-bit platforms This commit enables XXH3_64bits hash to be used on all 64-bit platforms. Previously it was only enabled on x86_64, so platforms like aarch64 silently falls back to using XXH32 which degrades the hashing function quality. - - - - - ee01de7d by Cheng Shao at 2024-02-13T14:09:46-05:00 rts: define XXH_INLINE_ALL This commit cleans up how we include the xxhash.h header and only define XXH_INLINE_ALL, which is sufficient to inline the xxHash functions without symbol collision. - - - - - 0e01e1db by Alan Zimmerman at 2024-02-14T02:13:22-05:00 EPA: Move EpAnn out of extension points Leaving a few that are too tricky, maybe some other time. Also - remove some unneeded helpers from Parser.y - reduce allocations with strictness annotations Updates haddock submodule Metric Decrease: parsing001 - - - - - de589554 by Andreas Klebinger at 2024-02-14T02:13:59-05:00 Fix ffi callbacks with >6 args and non-64bit args. Check for ptr/int arguments rather than 64-bit width arguments when counting integer register arguments. The old approach broke when we stopped using exclusively W64-sized types to represent sub-word sized integers. Fixes #24314 - - - - - 9c588f19 by Fendor at 2024-02-14T11:05:36+01:00 Adapt to GHC giving better Name's for linking - - - - - 325b7613 by Ben Gamari at 2024-02-14T14:27:45-05:00 rts/EventLog: Place eliminate duplicate strlens Previously many of the `post*` implementations would first compute the length of the event's strings in order to determine the event length. Later we would then end up computing the length yet again in `postString`. Now we instead pass the string length to `postStringLen`, avoiding the repeated work. - - - - - 8aafa51c by Ben Gamari at 2024-02-14T14:27:46-05:00 rts/eventlog: Place upper bound on IPE string field lengths The strings in IPE events may be of unbounded length. Limit the lengths of these fields to 64k characters to ensure that we don't exceed the maximum event length. - - - - - 0e60d52c by Zubin Duggal at 2024-02-14T14:27:46-05:00 rts: drop unused postString function - - - - - d8d1333a by Cheng Shao at 2024-02-14T14:28:23-05:00 compiler/rts: fix wasm unreg regression This commit fixes two wasm unreg regressions caught by a nightly pipeline: - Unknown stg_scheduler_loopzh symbol when compiling scheduler.cmm - Invalid _hs_constructor(101) function name when handling ctor - - - - - 264a4fa9 by Owen Shepherd at 2024-02-15T09:41:06-05:00 feat: Add sortOn to Data.List.NonEmpty Adds `sortOn` to `Data.List.NonEmpty`, and adds comments describing when to use it, compared to `sortWith` or `sortBy . comparing`. The aim is to smooth out the API between `Data.List`, and `Data.List.NonEmpty`. This change has been discussed in the [clc issue](https://github.com/haskell/core-libraries-committee/issues/227). - - - - - b57200de by Fendor at 2024-02-15T09:41:47-05:00 Prefer RdrName over OccName for looking up locations in doc renaming step Looking up by OccName only does not take into account when functions are only imported in a qualified way. Fixes issue #24294 Bump haddock submodule to include regression test - - - - - 8ad02724 by Luite Stegeman at 2024-02-15T17:33:32-05:00 JS: add simple optimizer The simple optimizer reduces the size of the code generated by the JavaScript backend without the complexity and performance penalty of the optimizer in GHCJS. Also see #22736 Metric Decrease: libdir size_hello_artifact - - - - - 20769b36 by Matthew Pickering at 2024-02-15T17:34:07-05:00 base: Expose `--no-automatic-time-samples` in `GHC.RTS.Flags` API This patch builds on 5077416e12cf480fb2048928aa51fa4c8fc22cf1 and modifies the base API to reflect the new RTS flag. CLC proposal #243 - https://github.com/haskell/core-libraries-committee/issues/243 Fixes #24337 - - - - - 778e1db3 by Andrei Borzenkov at 2024-02-16T16:12:07+03:00 Namespace specifiers for fixity signatures - - - - - 08031ada by Teo Camarasu at 2024-02-16T13:37:00-05:00 base: export System.Mem.performBlockingMajorGC The corresponding C function was introduced in ba73a807edbb444c49e0cf21ab2ce89226a77f2e. As part of #22264. Resolves #24228 The CLC proposal was disccused at: https://github.com/haskell/core-libraries-committee/issues/230 Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 1f534c2e by Florian Weimer at 2024-02-16T13:37:42-05:00 Fix C output for modern C initiative GCC 14 on aarch64 rejects the C code written by GHC with this kind of error: error: assignment to ‘ffi_arg’ {aka ‘long unsigned int’} from ‘HsPtr’ {aka ‘void *’} makes integer from pointer without a cast [-Wint-conversion] 68 | *(ffi_arg*)resp = cret; | ^ Add the correct cast. For more information on this see: https://fedoraproject.org/wiki/Changes/PortingToModernC Tested-by: Richard W.M. Jones <rjones at redhat.com> - - - - - 5d3f7862 by Matthew Craven at 2024-02-16T13:38:18-05:00 Bump bytestring submodule to 0.12.1.0 - - - - - 902ebcc2 by Ian-Woo Kim at 2024-02-17T06:01:01-05:00 Add missing BCO handling in scavenge_one. - - - - - 97d26206 by Sylvain Henry at 2024-02-17T06:01:44-05:00 Make cast between words and floats real primops (#24331) First step towards fixing #24331. Replace foreign prim imports with real primops. - - - - - a40e4781 by Sylvain Henry at 2024-02-17T06:01:44-05:00 Perf: add constant folding for bitcast between float and word (#24331) - - - - - 5fd2c00f by Sylvain Henry at 2024-02-17T06:01:44-05:00 Perf: replace stack checks with assertions in casting primops There are RESERVED_STACK_WORDS free words (currently 21) on the stack, so omit the checks. Suggested by Cheng Shao. - - - - - 401dfe7b by Sylvain Henry at 2024-02-17T06:01:44-05:00 Reexport primops from GHC.Float + add deprecation - - - - - 4ab48edb by Ben Gamari at 2024-02-17T06:02:21-05:00 rts/Hash: Don't iterate over chunks if we don't need to free data When freeing a `HashTable` there is no reason to walk over the hash list before freeing it if the user has not given us a `dataFreeFun`. Noticed while looking at #24410. - - - - - bd5a1f91 by Cheng Shao at 2024-02-17T06:03:00-05:00 compiler: add SEQ_CST fence support In addition to existing Acquire/Release fences, this commit adds SEQ_CST fence support to GHC, allowing Cmm code to explicitly emit a fence that enforces total memory ordering. The following logic is added: - The MO_SeqCstFence callish MachOp - The %prim fence_seq_cst() Cmm syntax and the SEQ_CST_FENCE macro in Cmm.h - MO_SeqCstFence lowering logic in every single GHC codegen backend - - - - - 2ce2a493 by Cheng Shao at 2024-02-17T06:03:38-05:00 testsuite: fix hs_try_putmvar002 for targets without pthread.h hs_try_putmvar002 includes pthread.h and doesn't work on targets without this header (e.g. wasm32). It doesn't need to include this header at all. This was previously unnoticed by wasm CI, though recent toolchain upgrade brought in upstream changes that completely removes pthread.h in the single-threaded wasm32-wasi sysroot, therefore we need to handle that change. - - - - - 1fb3974e by Cheng Shao at 2024-02-17T06:03:38-05:00 ci: bump ci-images to use updated wasm image This commit bumps our ci-images revision to use updated wasm image. - - - - - 56e3f097 by Andrew Lelechenko at 2024-02-17T06:04:13-05:00 Bump submodule text to 2.1.1 T17123 allocates less because of improvements to Data.Text.concat in 1a6a06a. Metric Decrease: T17123 - - - - - a7569495 by Cheng Shao at 2024-02-17T06:04:51-05:00 rts: remove redundant rCCCS initialization This commit removes the redundant logic of initializing each Capability's rCCCS to CCS_SYSTEM in initProfiling(). Before initProfiling() is called during RTS startup, each Capability's rCCCS has already been assigned CCS_SYSTEM when they're first initialized. - - - - - 7a0293cc by Ben Gamari at 2024-02-19T07:11:00-05:00 Drop dependence on `touch` This drops GHC's dependence on the `touch` program, instead implementing it within GHC. This eliminates an external dependency and means that we have one fewer program to keep track of in the `configure` script - - - - - 0dbd729e by Andrei Borzenkov at 2024-02-19T07:11:37-05:00 Parser, renamer, type checker for @a-binders (#17594) GHC Proposal 448 introduces binders for invisible type arguments (@a-binders) in various contexts. This patch implements @-binders in lambda patterns and function equations: {-# LANGUAGE TypeAbstractions #-} id1 :: a -> a id1 @t x = x :: t -- @t-binder on the LHS of a function equation higherRank :: (forall a. (Num a, Bounded a) => a -> a) -> (Int8, Int16) higherRank f = (f 42, f 42) ex :: (Int8, Int16) ex = higherRank (\ @a x -> maxBound @a - x ) -- @a-binder in a lambda pattern in an argument -- to a higher-order function Syntax ------ To represent those @-binders in the AST, the list of patterns in Match now uses ArgPat instead of Pat: data Match p body = Match { ... - m_pats :: [LPat p], + m_pats :: [LArgPat p], ... } + data ArgPat pass + = VisPat (XVisPat pass) (LPat pass) + | InvisPat (XInvisPat pass) (HsTyPat (NoGhcTc pass)) + | XArgPat !(XXArgPat pass) The VisPat constructor represents patterns for visible arguments, which include ordinary value-level arguments and required type arguments (neither is prefixed with a @), while InvisPat represents invisible type arguments (prefixed with a @). Parser ------ In the grammar (Parser.y), the lambda and lambda-cases productions of aexp non-terminal were updated to accept argpats instead of apats: aexp : ... - | '\\' apats '->' exp + | '\\' argpats '->' exp ... - | '\\' 'lcases' altslist(apats) + | '\\' 'lcases' altslist(argpats) ... + argpat : apat + | PREFIX_AT atype Function left-hand sides did not require any changes to the grammar, as they were already parsed with productions capable of parsing @-binders. Those binders were being rejected in post-processing (isFunLhs), and now we accept them. In Parser.PostProcess, patterns are constructed with the help of PatBuilder, which is used as an intermediate data structure when disambiguating between FunBind and PatBind. In this patch we define ArgPatBuilder to accompany PatBuilder. ArgPatBuilder is a short-lived data structure produced in isFunLhs and consumed in checkFunBind. Renamer ------- Renaming of @-binders builds upon prior work on type patterns, implemented in 2afbddb0f24, which guarantees proper scoping and shadowing behavior of bound type variables. This patch merely defines rnLArgPatsAndThen to process a mix of visible and invisible patterns: + rnLArgPatsAndThen :: NameMaker -> [LArgPat GhcPs] -> CpsRn [LArgPat GhcRn] + rnLArgPatsAndThen mk = mapM (wrapSrcSpanCps rnArgPatAndThen) where + rnArgPatAndThen (VisPat x p) = ... rnLPatAndThen ... + rnArgPatAndThen (InvisPat _ tp) = ... rnHsTyPat ... Common logic between rnArgPats and rnPats is factored out into the rn_pats_general helper. Type checker ------------ Type-checking of @-binders builds upon prior work on lazy skolemisation, implemented in f5d3e03c56f. This patch extends tcMatchPats to handle @-binders. Now it takes and returns a list of LArgPat rather than LPat: tcMatchPats :: ... - -> [LPat GhcRn] + -> [LArgPat GhcRn] ... - -> TcM ([LPat GhcTc], a) + -> TcM ([LArgPat GhcTc], a) Invisible binders in the Match are matched up with invisible (Specified) foralls in the type. This is done with a new clause in the `loop` worker of tcMatchPats: loop :: [LArgPat GhcRn] -> [ExpPatType] -> TcM ([LArgPat GhcTc], a) loop (L l apat : pats) (ExpForAllPatTy (Bndr tv vis) : pat_tys) ... -- NEW CLAUSE: | InvisPat _ tp <- apat, isSpecifiedForAllTyFlag vis = ... In addition to that, tcMatchPats no longer discards type patterns. This is done by filterOutErasedPats in the desugarer instead. x86_64-linux-deb10-validate+debug_info Metric Increase: MultiLayerModulesTH_OneShot - - - - - 486979b0 by Jade at 2024-02-19T07:12:13-05:00 Add specialized sconcat implementation for Data.Monoid.First and Data.Semigroup.First Approved CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/246 Fixes: #24346 - - - - - 17e309d2 by John Ericson at 2024-02-19T07:12:49-05:00 Fix reST in users guide It appears that aef587f65de642142c1dcba0335a301711aab951 wasn't valid syntax. - - - - - 35b0ad90 by Brandon Chinn at 2024-02-19T07:13:25-05:00 Fix searching for errors in sphinx build - - - - - 4696b966 by Cheng Shao at 2024-02-19T07:14:02-05:00 hadrian: fix wasm backend post linker script permissions The post-link.mjs script was incorrectly copied and installed as a regular data file without executable permission, this commit fixes it. - - - - - a6142e0c by Cheng Shao at 2024-02-19T07:14:40-05:00 testsuite: mark T23540 as fragile on i386 See #24449 for details. - - - - - 249caf0d by Matthew Craven at 2024-02-19T20:36:09-05:00 Add @since annotation to Data.Data.mkConstrTag - - - - - cdd939e7 by Jade at 2024-02-19T20:36:46-05:00 Enhance documentation of Data.Complex - - - - - d04f384f by Ben Gamari at 2024-02-21T04:59:23-05:00 hadrian/bindist: Ensure that phony rules are marked as such Otherwise make may not run the rule if file with the same name as the rule happens to exist. - - - - - efcbad2d by Ben Gamari at 2024-02-21T04:59:23-05:00 hadrian: Generate HSC2HS_EXTRAS variable in bindist installation We must generate the hsc2hs wrapper at bindist installation time since it must contain `--lflag` and `--cflag` arguments which depend upon the installation path. The solution here is to substitute these variables in the configure script (see mk/hsc2hs.in). This is then copied over a dummy wrapper in the install rules. Fixes #24050. - - - - - c540559c by Matthew Pickering at 2024-02-21T04:59:23-05:00 ci: Show --info for installed compiler - - - - - ab9281a2 by Matthew Pickering at 2024-02-21T04:59:23-05:00 configure: Correctly set --target flag for linker opts Previously we were trying to use the FP_CC_SUPPORTS_TARGET with 4 arguments, when it only takes 3 arguments. Instead we need to use the `FP_PROG_CC_LINKER_TARGET` function in order to set the linker flags. Actually fixes #24414 - - - - - 9460d504 by Rodrigo Mesquita at 2024-02-21T04:59:59-05:00 configure: Do not override existing linker flags in FP_LD_NO_FIXUP_CHAINS - - - - - 77629e76 by Andrei Borzenkov at 2024-02-21T05:00:35-05:00 Namespacing for fixity signatures (#14032) Namespace specifiers were added to syntax of fixity signatures: - sigdecl ::= infix prec ops | ... + sigdecl ::= infix prec namespace_spec ops | ... To preserve namespace during renaming MiniFixityEnv type now has separate FastStringEnv fields for names that should be on the term level and for name that should be on the type level. makeMiniFixityEnv function was changed to fill MiniFixityEnv in the right way: - signatures without namespace specifiers fill both fields - signatures with 'data' specifier fill data field only - signatures with 'type' specifier fill type field only Was added helper function lookupMiniFixityEnv that takes care about looking for a name in an appropriate namespace. Updates haddock submodule. Metric Decrease: MultiLayerModulesTH_OneShot - - - - - 84357d11 by Teo Camarasu at 2024-02-21T05:01:11-05:00 rts: only collect live words in nonmoving census when non-concurrent This avoids segfaults when the mutator modifies closures as we examine them. Resolves #24393 - - - - - 9ca56dd3 by Ian-Woo Kim at 2024-02-21T05:01:53-05:00 mutex wrap in refreshProfilingCCSs - - - - - 1387966a by Cheng Shao at 2024-02-21T05:02:32-05:00 rts: remove unused HAVE_C11_ATOMICS macro This commit removes the unused HAVE_C11_ATOMICS macro. We used to have a few places that have fallback paths when HAVE_C11_ATOMICS is not defined, but that is completely redundant, since the FP_CC_SUPPORTS__ATOMICS configure check will fail when the C compiler doesn't support C11 style atomics. There are also many places (e.g. in unreg backend, SMP.h, library cbits, etc) where we unconditionally use C11 style atomics anyway which work in even CentOS 7 (gcc 4.8), the oldest distro we test in our CI, so there's no value in keeping HAVE_C11_ATOMICS. - - - - - 0f40d68f by Andreas Klebinger at 2024-02-21T05:03:09-05:00 RTS: -Ds - make sure incall is non-zero before dereferencing it. Fixes #24445 - - - - - e5886de5 by Ben Gamari at 2024-02-21T05:03:44-05:00 rts/AdjustorPool: Use ExecPage abstraction This is just a minor cleanup I found while reviewing the implementation. - - - - - 826c5b47 by Torsten Schmits at 2024-02-21T13:17:05+01:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 09941666 by Adam Gundry at 2024-02-21T13:53:12+00:00 Define GHC2024 language edition (#24320) See https://github.com/ghc-proposals/ghc-proposals/pull/613. Also fixes #24343 and improves the documentation of language editions. Co-authored-by: Joachim Breitner <mail at joachim-breitner.de> - - - - - 2cff14d5 by Ben Gamari at 2024-02-22T09:35:56-05:00 Bump bounds - - - - - f49376b3 by Ben Gamari at 2024-02-22T09:35:56-05:00 Allow `@since` annotations in export lists Here we extend Haddock to admit `@since` annotations in export lists. These can be attached to most export list items (although not subordinate lists). These annotations supercede the declaration's `@since` annotation in produced Haddocks. - - - - - b5aa93df by Ben Gamari at 2024-02-22T12:09:06-05:00 Allow package-qualified @since declarations - - - - - 8f5957f2 by Ben Gamari at 2024-02-22T13:55:19-05:00 Documentation changes from ghc-internal restructuring Previously many declarations (e.g. `Int`) were declared to have a "home" in `Prelude`. However, now Haddock instead chooses to put these in more specific homes (e.g. `Data.Int`). Given that the "home" decision is driven by heuristics and in general these changes seem quite reasonable I am accepting them: * `Int` moved from `Prelude` to `Data.Int` * `(~)` moved from `Prelude` to `Data.Type.Equality` * `Type` moved from `GHC.Types` to `Data.Kind` * `Maybe` moved from `Prelude` to `Data.Maybe` * `Bool` moved from `Prelude` to `Data.Bool` * `Ordering` moved from `Prelude` to `Data.Ord` As well, more identifiers are now hyperlinked; it's not immediately clear *why*, but it is an improvement nevertheless. - - - - - ec33fec3 by Ben Gamari at 2024-02-22T20:36:24-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 5121a4ed by Ben Gamari at 2024-02-23T06:40:55-05:00 Allow docstrings after exports Here we extend the parser and AST to preserve docstrings following export items. We then extend Haddock to parse `@since` annotations in such docstrings, allowing changes in export structure to be properly documented. Bumps haddock submodule. - - - - - 30cfd251 by Torsten Schmits at 2024-02-24T13:00:42-05:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 0eb2265d by Hécate Moonlight at 2024-02-24T16:02:16-05:00 Improve the synopsis and description of base - - - - - 2e36f5d2 by Jade at 2024-02-24T16:02:51-05:00 Error Messages: Properly align cyclic module error Fixes: #24476 - - - - - bbfb051c by Ben Gamari at 2024-02-24T19:10:23-05:00 Allow docstrings after exports Here we extend the parser and AST to preserve docstrings following export items. We then extend Haddock to parse `@since` annotations in such docstrings, allowing changes in export structure to be properly documented. - - - - - d8d6ad8c by Ben Gamari at 2024-02-24T19:10:23-05:00 ghc-internal: Move modules into GHC.Internal.* namespace Bumps haddock submodule due to testsuite output changes. - - - - - a82af7cd by Ben Gamari at 2024-02-24T19:10:23-05:00 ghc-internal: Rewrite `@since ` to `@since base-` These will be incrementally moved to the export sites in `base` where possible. - - - - - ca3836e1 by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Migrate Haddock `not-home` pragmas from `ghc-internal` This ensures that we do not use `base` stub modules as declarations' homes when not appropriate. - - - - - c8cf3e26 by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Partially freeze exports of GHC.Base Sadly there are still a few module reexports. However, at least we have decoupled from the exports of `GHC.Internal.Base`. - - - - - 272573c6 by Ben Gamari at 2024-02-24T19:10:23-05:00 Move Haddock named chunks - - - - - 2d8a881d by Ben Gamari at 2024-02-24T19:10:23-05:00 Drop GHC.Internal.Data.Int - - - - - 55c4c385 by Ben Gamari at 2024-02-24T19:10:23-05:00 compiler: Fix mention to `GHC....` modules in wasm desugaring Really, these references should be via known-key names anyways. I have fixed the proximate issue here but have opened #24472 to track the additional needed refactoring. - - - - - 64150911 by Ben Gamari at 2024-02-24T19:10:23-05:00 Accept performance shifts from ghc-internal restructure As expected, Haddock now does more work. Less expected is that some other testcases actually get faster, presumably due to less interface file loading. As well, the size_hello_artifact test regressed a bit when debug information is enabled due to debug information for the new stub symbols. Metric Decrease: T12227 T13056 Metric Increase: haddock.Cabal haddock.base MultiLayerModulesTH_OneShot size_hello_artifact - - - - - 317a915b by Ben Gamari at 2024-02-24T19:10:23-05:00 Expose GHC.Wasm.Prim from ghc-experimental Previously this was only exposed from `ghc-internal` which violates our agreement that users shall not rely on things exposed from that package. Fixes #24479. - - - - - 3bbd2bf2 by Ben Gamari at 2024-02-24T19:10:23-05:00 compiler/tc: Small optimisation of evCallStack Don't lookupIds unless we actually need them. - - - - - 3e5c9e3c by Ben Gamari at 2024-02-24T19:10:23-05:00 compiler/tc: Use toException instead of SomeException - - - - - 125714a6 by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Factor out errorBelch This was useful when debugging - - - - - 3d6aae7c by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Clean up imports of GHC.Stack.CloneStack - - - - - 6900306e by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Move PrimMVar to GHC.Internal.MVar - - - - - 28f8a148 by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Move prettyCallStack to GHC.Internal.Stack - - - - - 4892de47 by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Explicit dependency to workaround #24436 Currently `ghc -M` fails to account for `.hs-boot` files correctly, leading to issues with cross-package one-shot builds failing. This currently manifests in `GHC.Exception` due to the boot file for `GHC.Internal.Stack`. Work around this by adding an explicit `import`, ensuring that `GHC.Internal.Stack` is built before `GHC.Exception`. See #24436. - - - - - 294c93a5 by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Use displayException in top-level exception handler Happily this also allows us to eliminate a special case for Deadlock exceptions. Implements [CLC #198](https://github.com/haskell/core-libraries-committee/issues/198). - - - - - 732db81d by Ben Gamari at 2024-02-24T19:12:18-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - cf756a25 by Ben Gamari at 2024-02-24T22:11:53-05:00 rts: Fix symbol references in Wasm RTS - - - - - 4e4d47a0 by Jade at 2024-02-26T15:17:20-05:00 GHCi: Improve response to unloading, loading and reloading modules Fixes #13869 - - - - - f3de8a3c by Zubin Duggal at 2024-02-26T15:17:57-05:00 rel-eng/fetch-gitlab.py: Fix name of aarch64 alpine 3_18 release job - - - - - c71bfdff by Cheng Shao at 2024-02-26T15:18:35-05:00 hadrian/hie-bios: pass -j to hadrian This commit passes -j to hadrian in the hadrian/hie-bios scripts. When the user starts HLS in a fresh clone that has just been configured, it takes quite a while for hie-bios to pick up the ghc flags and start actual indexing, due to the fact that the hadrian build step defaulted to -j1, so -j speeds things up and improve HLS user experience in GHC. Also add -j flag to .ghcid to speed up ghcid, and sets the Windows build root to .hie-bios which also works and unifies with other platforms, the previous build root _hie-bios was missing from .gitignore anyway. - - - - - 50bfdb46 by Cheng Shao at 2024-02-26T15:18:35-05:00 ci: enable parallelism in hadrian/ghci scripts This commit enables parallelism when the hadrian/ghci scripts are called in CI. The time bottleneck is in the hadrian build step, but previously the build step wasn't parallelized. - - - - - 61a78231 by Felix Yan at 2024-02-26T15:19:14-05:00 m4: Correctly detect GCC version When calling as `cc`, GCC does not outputs lowercased "gcc" at least in 13.2.1 version here. ``` $ cc --version cc (GCC) 13.2.1 20230801 ... ``` This fails the check and outputs the confusing message: `configure: $CC is not gcc; assuming it's a reasonably new C compiler` This patch makes it check for upper-cased "GCC" too so that it works correctly: ``` checking version of gcc... 13.2.1 ``` - - - - - 001aa539 by Teo Camarasu at 2024-02-27T13:26:46-05:00 Fix formatting in whereFrom docstring Previously it used markdown syntax rather than Haddock syntax for code quotes - - - - - e8034d15 by Teo Camarasu at 2024-02-27T13:26:46-05:00 Move ClosureType type to ghc-internal - Use ClosureType for InfoProv.ipDesc. - Use ClosureType for CloneStack.closureType. - Now ghc-heap re-exports this type from ghc-internal. See the accompanying CLC proposal: https://github.com/haskell/core-libraries-committee/issues/210 Resolves #22600 - - - - - 3da0a551 by Matthew Craven at 2024-02-27T13:27:22-05:00 StgToJS: Simplify ExprInline constructor of ExprResult Its payload was used only for a small optimization in genAlts, avoiding a few assignments for programs of this form: case NormalDataCon arg1 arg2 of x { NormalDataCon x1 x2 -> ... ; } But when compiling with optimizations, this sort of code is generally eliminated by case-of-known-constructor in Core-to-Core. So it doesn't seem worth tracking and cleaning up again in StgToJS. - - - - - 61bc92cc by Cheng Shao at 2024-02-27T16:58:42-05:00 rts: add missing ccs_mutex guard to internal_dlopen See added comment for details. Closes #24423. - - - - - dd29d3b2 by doyougnu at 2024-02-27T16:59:23-05:00 cg: Remove GHC.Cmm.DataFlow.Collections In pursuit of #15560 and #17957 and generally removing redundancy. - - - - - d3a050d2 by Cheng Shao at 2024-02-27T17:00:00-05:00 utils: remove unused lndir from tree Ever since the removal of the make build system, the in tree lndir hasn't been actually built, so this patch removes it. - - - - - 86bf7010 by Ben Gamari at 2024-02-27T19:28:10-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 74b24a9b by Teo Camarasu at 2024-02-28T16:32:58+00:00 rts: avoid checking bdescr of value outside of Haskell heap In nonmovingTidyWeaks we want to check if the key of a weak pointer lives in the non-moving heap. We do this by checking the flags of the block the key lives in. But we need to be careful with values that live outside the Haskell heap, since they will lack a block descriptor and looking for one may lead to a segfault. In this case we should just accept that it isn't on the non-moving heap. Resolves #24492 - - - - - b4cae4ec by Simon Peyton Jones at 2024-02-29T02:10:08-05:00 In mkDataConRep, ensure the in-scope set is right A small change that fixes #24489 - - - - - 3836a110 by Cheng Shao at 2024-02-29T21:25:45-05:00 testsuite: fix T23540 fragility on 32-bit platforms T23540 is fragile on 32-bit platforms. The root cause is usage of `getEvidenceTreesAtPoint`, which internally relies on `Name`'s `Ord` instance, which is indeterministic. The solution is adding a deterministic `Ord` instance for `EvidenceInfo` and sorting the evidence trees before pretty printing. Fixes #24449. - - - - - 960c8d47 by Teo Camarasu at 2024-02-29T21:26:20-05:00 Reduce AtomicModifyIORef increment count This test leads to a lot of contention when N>2 and becomes very slow. Let's reduce the amount of work we do to compensate. Resolves #24490 - - - - - 2e46c8ad by Matthew Pickering at 2024-03-01T05:48:06-05:00 hadrian: Improve parallelism in binary-dist-dir rule I noticed that the "docs" target was needed after the libraries and executables were built. We can improve the parallelism by needing everything at once so that documentation can be built immediately after a library is built for example. - - - - - cb6c11fe by Matthew Pickering at 2024-03-01T05:48:07-05:00 ci: Bump windows and freebsd boot compilers to 9.6.4 We have previously bumped the docker images to use 9.6.4, but neglected to bump the windows images until now. - - - - - 30f06996 by Matthew Pickering at 2024-03-01T05:48:07-05:00 ci: darwin: Update to 9.6.2 for boot compiler 9.6.4 is currently broken due to #24050 Also update to use LLVM-15 rather than LLVM-11, which is out of date. - - - - - d9d69e12 by Matthew Pickering at 2024-03-01T05:48:07-05:00 Bump minimum bootstrap version to 9.6 - - - - - 67ace1c5 by Matthew Pickering at 2024-03-01T05:48:07-05:00 ci: Enable more documentation building Here we enable documentation building on 1. Darwin: The sphinx toolchain was already installed so we enable html and manpages. 2. Rocky8: Full documentation (toolchain already installed) 3. Alpine: Full documetnation (toolchain already installed) 4. Windows: HTML and manpages (toolchain already installed) Fixes #24465 - - - - - 39583c39 by Matthew Pickering at 2024-03-01T05:48:42-05:00 ci: Bump ci-images to allow updated aarch64-alpine image with llvm15 and clang15 - - - - - d91d00fc by Torsten Schmits at 2024-03-01T15:01:50-05:00 Introduce ListTuplePuns extension This implements Proposal 0475, introducing the `ListTuplePuns` extension which is enabled by default. Disabling this extension makes it invalid to refer to list, tuple and sum type constructors by using built-in syntax like `[Int]`, `(Int, Int)`, `(# Int#, Int# #)` or `(# Int | Int #)`. Instead, this syntax exclusively denotes data constructors for use with `DataKinds`. The conventional way of referring to these data constructors by prefixing them with a single quote (`'(Int, Int)`) is now a parser error. Tuple declarations have been moved to `GHC.Tuple.Prim` and the `Solo` data constructor has been renamed to `MkSolo` (in a previous commit). Unboxed tuples and sums now have real source declarations in `GHC.Types`. Unit and solo types for tuples are now called `Unit`, `Unit#`, `Solo` and `Solo#`. Constraint tuples now have the unambiguous type constructors `CTuple<n>` as well as `CUnit` and `CSolo`, defined in `GHC.Classes` like before. A new parser construct has been added for the unboxed sum data constructor declarations. The type families `Tuple`, `Sum#` etc. that were intended to provide nicer syntax have been omitted from this change set due to inference problems, to be implemented at a later time. See the MR discussion for more info. Updates the submodule utils/haddock. Updates the cabal submodule due to new language extension. Metric Increase: haddock.base Metric Decrease: MultiLayerModulesTH_OneShot size_hello_artifact Proposal document: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0475-tuple-syntax.rst Merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/8820 Tracking ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/21294 - - - - - bbdb6286 by Sylvain Henry at 2024-03-01T15:01:50-05:00 JS linker: filter unboxed tuples - - - - - dec6d8d3 by Arnaud Spiwack at 2024-03-01T15:02:30-05:00 Improve error messages coming from non-linear patterns This enriched the `CtOrigin` for non-linear patterns to include data of the pattern that created the constraint (which can be quite useful if it occurs nested in a pattern) as well as an explanation why the pattern is non-restricted in (at least in some cases). - - - - - 6612388e by Arnaud Spiwack at 2024-03-01T15:02:30-05:00 Adjust documentation of linear lets according to committee decision - - - - - 1c064ef1 by Cheng Shao at 2024-03-02T17:11:19-05:00 compiler: start deprecating cmmToRawCmmHook cmmToRawCmmHook was added 4 years ago in d561c8f6244f8280a2483e8753c38e39d34c1f01. Its only user is the Asterius project, which has been archived and deprecated in favor of the ghc wasm backend. This patch starts deprecating cmmToRawCmmHook by placing a DEPRECATED pragma, and actual removal shall happen in a future GHC major release if no issue to oppose the deprecation has been raised in the meantime. - - - - - 9b74845f by Andrew Lelechenko at 2024-03-02T17:11:55-05:00 Data.List.NonEmpty.unzip: use WARNING with category instead of DEPRECATED CLC proposal: https://github.com/haskell/core-libraries-committee/issues/258 - - - - - 61bb5ff6 by Finley McIlwaine at 2024-03-04T09:01:40-08:00 add -fprof-late-overloaded and -fprof-late-overloaded-calls * Refactor late cost centre insertion for extensibility * Add two more late cost centre insertion methods that add SCCs to overloaded top level bindings and call sites with dictionary arguments. * Some tests for the basic functionality of the new insertion methods Resolves: #24500 - - - - - 82ccb801 by Andreas Klebinger at 2024-03-04T19:59:14-05:00 x86-ncg: Fix fma codegen when arguments are globals Fix a bug in the x86 ncg where results would be wrong when the desired output register and one of the input registers were the same global. Also adds a tiny optimization to make use of the memory addressing support when convenient. Fixes #24496 - - - - - 18ad1077 by Matthew Pickering at 2024-03-05T14:22:31-05:00 rel_eng: Update hackage docs upload scripts This adds the upload of ghc-internal and ghc-experimental to our scripts which upload packages to hackage. - - - - - bf47c9ba by Matthew Pickering at 2024-03-05T14:22:31-05:00 docs: Remove stray module comment from GHC.Profiling.Eras - - - - - 37d9b340 by Matthew Pickering at 2024-03-05T14:22:31-05:00 Fix ghc-internal cabal file The file mentioned some artifacts relating to the base library. I have renamed these to the new ghc-internal variants. - - - - - 23f2a478 by Matthew Pickering at 2024-03-05T14:22:31-05:00 Fix haddock source links and hyperlinked source There were a few issues with the hackage links: 1. We were using the package id rather than the package name for the package links. This is fixed by now allowing the template to mention %pkg% or %pkgid% and substituing both appropiatly. 2. The `--haddock-base-url` flag is renamed to `--haddock-for-hackage` as the new base link works on a local or remote hackage server. 3. The "src" path including too much stuff, so cross-package source links were broken as the template was getting double expanded. Fixes #24086 - - - - - 2fa336a9 by Ben Gamari at 2024-03-05T14:23:07-05:00 filepath: Bump submodule to 1.5.2.0 - - - - - 31217944 by Ben Gamari at 2024-03-05T14:23:07-05:00 os-string: Bump submodule to 2.0.2 - - - - - 4074a3f2 by Matthew Pickering at 2024-03-05T21:44:35-05:00 base: Reflect new era profiling RTS flags in GHC.RTS.Flags * -he profiling mode * -he profiling selector * --automatic-era-increment CLC proposal #254 - https://github.com/haskell/core-libraries-committee/issues/254 - - - - - a8c0e31b by Sylvain Henry at 2024-03-05T21:45:14-05:00 JS: faster implementation for some numeric primitives (#23597) Use faster implementations for the following primitives in the JS backend by not using JavaScript's BigInt: - plusInt64 - minusInt64 - minusWord64 - timesWord64 - timesInt64 Co-authored-by: Josh Meredith <joshmeredith2008 at gmail.com> - - - - - 21e3f325 by Cheng Shao at 2024-03-05T21:45:52-05:00 rts: add -xr option to control two step allocator reserved space size This patch adds a -xr RTS option to control the size of virtual memory address space reserved by the two step allocator on a 64-bit platform, see added documentation for explanation. Closes #24498. - - - - - dedcf102 by Cheng Shao at 2024-03-06T13:39:04-05:00 rts: expose HeapAlloc.h as public header This commit exposes HeapAlloc.h as a public header. The intention is to expose HEAP_ALLOCED/HEAP_ALLOCED_GC, so they can be used in assertions in other public headers, and they may also be useful for user code. - - - - - d19441d7 by Cheng Shao at 2024-03-06T13:39:04-05:00 rts: assert pointer is indeed heap allocated in Bdescr() This commit adds an assertion to Bdescr() to assert the pointer is indeed heap allocated. This is useful to rule out RTS bugs that attempt to access non-existent block descriptor of a static closure, #24492 being one such example. - - - - - 9a656a04 by Ben Gamari at 2024-03-06T13:39:39-05:00 ghc-experimental: Add dummy dependencies to work around #23942 This is a temporary measure to improve CI reliability until a proper solution is developed. Works around #23942. - - - - - 1e84b924 by Simon Peyton Jones at 2024-03-06T13:39:39-05:00 Three compile perf improvements with deep nesting These were changes are all triggered by #24471. 1. Make GHC.Core.Opt.SetLevels.lvlMFE behave better when there are many free variables. See Note [Large free-variable sets]. 2. Make GHC.Core.Opt.Arity.floatIn a bit lazier in its Cost argument. This benefits the common case where the ArityType turns out to be nullary. See Note [Care with nested expressions] 3. Make GHC.CoreToStg.Prep.cpeArg behave for deeply-nested expressions. See Note [Eta expansion of arguments in CorePrep] wrinkle (EA2). Compile times go down by up to 4.5%, and much more in artificial cases. (Geo mean of compiler/perf changes is -0.4%.) Metric Decrease: CoOpt_Read T10421 T12425 - - - - - c4b13113 by Hécate Moonlight at 2024-03-06T13:40:17-05:00 Use "module" instead of "library" when applicable in base haddocks - - - - - 9cd9efb4 by Vladislav Zavialov at 2024-03-07T13:01:54+03:00 Rephrase error message to say "visible arguments" (#24318) * Main change: make the error message generated by mkFunTysMsg more accurate by changing "value arguments" to "visible arguments". * Refactor: define a new type synonym VisArity and use it instead of Arity in a few places. It might be the case that there other places in the compiler that should talk about visible arguments rather than value arguments, but I haven't tried to find them all, focusing only on the error message reported in the ticket. - - - - - 4b6e76b5 by Patrick at 2024-03-07T22:09:30+08:00 fix haskell/haddock#24493, with module name introduced in hieAst The accompanies haddoc PR with GHC PR https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12153 Two things have been done: 1. Link is introduced to every `X` in `module X where`, since we introduce the module name to HieAst, 2. `{-# LINE 4 "hypsrc-test/src/PositionPragmas.hs" #-}` is added before the `module PositionPragmas where` in ` hypsrc-test/ref/src/PositionPragmas.html `.It ensures only a single hieAst for file `hypsrc-test/src/PositionPragmas.hs` is generated. - - - - - d523a6a7 by Ben Gamari at 2024-03-07T19:40:45-05:00 Bump array submodule - - - - - 7e55003c by Ben Gamari at 2024-03-07T19:40:45-05:00 Bump stm submodule - - - - - 32d337ef by Ben Gamari at 2024-03-07T19:40:45-05:00 Introduce exception context Here we introduce the `ExceptionContext` type and `ExceptionAnnotation` class, allowing dynamically-typed user-defined annotations to be attached to exceptions. CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/199 GHC Proposal: https://github.com/ghc-proposals/ghc-proposals/pull/330 - - - - - 39f3d922 by Ben Gamari at 2024-03-07T19:40:46-05:00 testsuite/interface-stability: Update documentation - - - - - fdea7ada by Ben Gamari at 2024-03-07T19:40:46-05:00 ghc-internal: comment formatting - - - - - 4fba42ef by Ben Gamari at 2024-03-07T19:40:46-05:00 compiler: Default and warn ExceptionContext constraints - - - - - 3886a205 by Ben Gamari at 2024-03-07T19:40:46-05:00 base: Introduce exception backtraces Here we introduce the `Backtraces` type and associated machinery for attaching these via `ExceptionContext`. These has a few compile-time regressions (`T15703` and `T9872d`) due to the additional dependencies in the exception machinery. As well, there is a surprisingly large regression in the `size_hello_artifact` test. This appears to be due to various `Integer` and `Read` bits now being reachable at link-time. I believe it should be possible to avoid this but I have accepted the change for now to get the feature merged. CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/199 GHC Proposal: https://github.com/ghc-proposals/ghc-proposals/pull/330 Metric Increase: T15703 T9872d size_hello_artifact - - - - - 18c5409f by Ben Gamari at 2024-03-07T19:40:46-05:00 users guide: Release notes for exception backtrace work - - - - - f849c5fc by Ben Gamari at 2024-03-07T19:40:46-05:00 compiler: Don't show ExceptionContext of GhcExceptions Most GhcExceptions are user-facing errors and therefore the ExceptionContext has little value. Ideally we would enable it in the DEBUG compiler but I am leaving this for future work. - - - - - dc646e6f by Sylvain Henry at 2024-03-07T19:40:46-05:00 Disable T9930fail for the JS target (cf #19174) - - - - - bfc09760 by Alan Zimmerman at 2024-03-07T19:41:22-05:00 Update showAstData to honour blanking of AnnParen Also tweak rendering of SrcSpan to remove extra blank line. - - - - - 50454a29 by Ben Gamari at 2024-03-08T03:32:42-05:00 ghc-internal: Eliminate GHC.Internal.Data.Kind This was simply reexporting things from `ghc-prim`. Instead reexport these directly from `Data.Kind`. Also add build ordering dependency to work around #23942. - - - - - 38a4b6ab by Ben Gamari at 2024-03-08T03:33:18-05:00 rts: Fix SET_HDR initialization of retainer set This fixes a regression in retainer set profiling introduced by b0293f78cb6acf2540389e22bdda420d0ab874da. Prior to that commit the heap traversal word would be initialized by `SET_HDR` using `LDV_RECORD_CREATE`. However, the commit added a `doingLDVProfiling` check in `LDV_RECORD_CREATE`, meaning that this initialization no longer happened. Given that this initialization was awkwardly indirectly anyways, I have fixed this by explicitly initializating the heap traversal word to `NULL` in `SET_PROF_HDR`. This is equivalent to the previous behavior, but much more direct. Fixes #24513. - - - - - 635abccc by Ben Gamari at 2024-03-08T17:09:06-05:00 Bump ghc version to 9.10 - - - - - 2859a637 by Ben Gamari at 2024-03-08T18:26:47-05:00 base: Use strerror_r instead of strerror As noted by #24344, `strerror` is not necessarily thread-safe. Thankfully, POSIX.1-2001 has long offered `strerror_r`, which is safe to use. Fixes #24344. CLC discussion: https://github.com/haskell/core-libraries-committee/issues/249 - - - - - 5b934048 by Ben Gamari at 2024-03-08T18:50:12-05:00 Bump base upper bound - - - - - b30d134e by Ben Gamari at 2024-03-08T18:50:44-05:00 Testsuite output update - - - - - edb9bf77 by Jade at 2024-03-09T03:39:38-05:00 Error messages: Improve Error messages for Data constructors in type signatures. This patch improves the error messages from invalid type signatures by trying to guess what the user did and suggesting an appropriate fix. Partially fixes: #17879 - - - - - cfb197e3 by Patrick at 2024-03-09T03:40:15-05:00 HieAst: add module name #24493 The main purpose of this is to tuck the module name `xxx` in `module xxx where` into the hieAst. It should fix #24493. The following have been done: 1. Renamed and update the `tcg_doc_hdr :: Maybe (LHsDoc GhcRn)` to `tcg_hdr_info :: (Maybe (LHsDoc GhcRn), Maybe (XRec GhcRn ModuleName))` To store the located module name information. 2. update the `RenamedSource` and `RenamedStuff` with extra `Maybe (XRec GhcRn ModuleName)` located module name information. 3. add test `testsuite/tests/hiefile/should_compile/T24493.hs` to ensure the module name is added and update several relevent tests. 4. accompanied submodule haddoc test update MR in https://gitlab.haskell.org/ghc/haddock/-/merge_requests/53 - - - - - 2341d81e by Vaibhav Sagar at 2024-03-09T03:40:54-05:00 GHC.Utils.Binary: fix a couple of typos - - - - - 5580e1bd by Ben Gamari at 2024-03-09T03:41:30-05:00 rts: Drop .wasm suffix from .prof file names This replicates the behavior on Windows, where `Hi.exe` will produce profiling output named `Hi.prof` instead of `Hi.exe.prof`. While in the area I also fixed the extension-stripping logic, which incorrectly rewrote `Hi.exefoo` to `Hi.foo`. Closes #24515. - - - - - 259495ee by Cheng Shao at 2024-03-09T03:41:30-05:00 testsuite: drop exe extension from .hp & .prof filenames See #24515 for details. - - - - - c477a8d2 by Ben Gamari at 2024-03-09T03:42:05-05:00 rts/linker: Enable GOT support on all platforms There is nothing platform-dependent about our GOT implementation and GOT support is needed by `T24171` on i386. - - - - - 2e592857 by Vladislav Zavialov at 2024-03-09T03:42:41-05:00 Drop outdated comment on TcRnIllformedTypePattern This should have been done in 0f0c53a501b but I missed it. - - - - - c554b4da by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/CloneStack: Bounds check array write - - - - - 15c590a5 by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/CloneStack: Don't expose helper functions in header - - - - - e831ce31 by Ben Gamari at 2024-03-09T09:39:20-05:00 base: Move internals of GHC.InfoProv into GHC.InfoProv.Types Such that we can add new helpers into GHC.InfoProv.Types without breakage. - - - - - 6948e24d by Ben Gamari at 2024-03-09T09:39:20-05:00 rts: Lazily decode IPE tables Previously we would eagerly allocate `InfoTableEnt`s for each info table registered in the info table provenance map. However, this costs considerable memory and initialization time. Instead we now lazily decode these tables. This allows us to use one-third the memory *and* opens the door to taking advantage of sharing opportunities within a module. This required considerable reworking since lookupIPE now must be passed its result buffer. - - - - - 9204a04e by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/IPE: Don't expose helper in header - - - - - 308926ff by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/IPE: Share module_name within a Node This allows us to shave a 64-bit word off of the packed IPE entry size. - - - - - bebdea05 by Ben Gamari at 2024-03-09T09:39:20-05:00 IPE: Expose unit ID in InfoTableProv Here we add the unit ID to the info table provenance structure. - - - - - 6519c9ad by Ben Gamari at 2024-03-09T09:39:35-05:00 rts: Refactor GHC.Stack.CloneStack.decode Don't allocate a Ptr constructor per frame. - - - - - ed0b69dc by Ben Gamari at 2024-03-09T09:39:35-05:00 base: Do not expose whereFrom# from GHC.Exts - - - - - 2b1faea9 by Vladislav Zavialov at 2024-03-09T17:38:21-05:00 docs: Update info on TypeAbstractions * Mention TypeAbstractions in 9.10.1-notes.rst * Set the status to "Experimental". * Add a "Since: GHC 9.x" comment to each section. - - - - - f8b88918 by Ben Gamari at 2024-03-09T21:21:46-05:00 ci-images: Bump Alpine image to bootstrap with 9.8.2 - - - - - 705e6927 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Mark T24171 as fragile due to #24512 I will fix this but not in time for 9.10.1-alpha1 - - - - - c74196e1 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Mark linker_unload_native as fragile In particular this fails on platforms without `dlinfo`. I plan to address this but not before 9.10.1-alpha1. - - - - - f4d87f7a by Ben Gamari at 2024-03-09T21:21:46-05:00 configure: Bump version to 9.10 - - - - - 88df9a5f by Ben Gamari at 2024-03-09T21:21:46-05:00 Bump transformers submodule to 0.6.1.1 - - - - - 8176d5e8 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Increase ulimit for T18623 1 MByte was just too tight and failed intermittently on some platforms (e.g. CentOS 7). Bumping the limit to 8 MByte should provide sufficient headroom. Fixes #23139. - - - - - c74b38a3 by Ben Gamari at 2024-03-09T21:21:46-05:00 base: Bump version to 4.20.0.0 - - - - - b2937fc3 by Ben Gamari at 2024-03-09T21:21:46-05:00 ghc-internal: Set initial version at 9.1001.0 This provides PVP compliance while maintaining a clear correspondence between GHC releases and `ghc-internal` versions. - - - - - 4ae7d868 by Ben Gamari at 2024-03-09T21:21:46-05:00 ghc-prim: Bump version to 0.11.0 - - - - - 50798dc6 by Ben Gamari at 2024-03-09T21:21:46-05:00 template-haskell: Bump version to 2.22.0.0 - - - - - 8564f976 by Ben Gamari at 2024-03-09T21:21:46-05:00 base-exports: Accommodate spurious whitespace changes in 32-bit output It appears that this was - - - - - 9d4f0e98 by Ben Gamari at 2024-03-09T21:21:46-05:00 users-guide: Move exception backtrace relnotes to 9.10 This was previously mistakenly added to the GHC 9.8 release notes. - - - - - 145eae60 by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/rel_eng: Fix name of Rocky8 artifact - - - - - 39c2a630 by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/rel_eng: Fix path of generate_jobs_metadata - - - - - aed034de by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/upload: Rework recompression The old `combine` approach was quite fragile due to use of filename globbing. Moreover, it didn't parallelize well. This refactoring makes the goal more obvious, parallelizes better, and is more robust. - - - - - 9bdf3586 by Ben Gamari at 2024-03-09T21:37:44-05:00 Merge branch 'ghc-9.10' into ghc-head - - - - - cec76981 by Ben Gamari at 2024-03-09T21:54:00-05:00 Bump GHC version to 9.11 - - - - - 4c59feb7 by Ben Gamari at 2024-03-09T22:15:01-05:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - dc207d06 by Ben Gamari at 2024-03-10T08:56:08-04:00 configure: Bump GHC version to 9.11 Bumps haddock submodule. - - - - - 8b2513e8 by Ben Gamari at 2024-03-11T01:20:03-04:00 rts/linker: Don't unload code when profiling is enabled The heap census may contain references (e.g. `Counter.identity`) to static data which must be available when the census is reported at the end of execution. Fixes #24512. - - - - - 7810b4c3 by Ben Gamari at 2024-03-11T01:20:03-04:00 rts/linker: Don't unload native objects when dlinfo isn't available To do so is unsafe as we have no way of identifying references to symbols provided by the object. Fixes #24513. Fixes #23993. - - - - - 0590764c by Ben Gamari at 2024-03-11T01:20:39-04:00 rel_eng/upload: Purge both $rel_name/ and $ver/ This is necessary for prereleases, where GHCup accesses the release via `$ver/` - - - - - b85a4631 by Brandon Chinn at 2024-03-12T19:25:56-04:00 Remove duplicate code normalising slashes - - - - - c91946f9 by Brandon Chinn at 2024-03-12T19:25:56-04:00 Simplify regexes with raw strings - - - - - 1a5f53c6 by Brandon Chinn at 2024-03-12T19:25:57-04:00 Don't normalize backslashes in characters - - - - - 7ea971d3 by Andrei Borzenkov at 2024-03-12T19:26:32-04:00 Fix compiler crash caused by implicit RHS quantification in type synonyms (#24470) - - - - - 39f3ac3e by Cheng Shao at 2024-03-12T19:27:11-04:00 Revert "compiler: make genSym use C-based atomic increment on non-JS 32-bit platforms" This reverts commit 615eb855416ce536e02ed935ecc5a6f25519ae16. It was originally intended to fix #24449, but it was merely sweeping the bug under the rug. 3836a110577b5c9343915fd96c1b2c64217e0082 has properly fixed the fragile test, and we no longer need the C version of genSym. Furthermore, the C implementation causes trouble when compiling with clang that targets i386 due to alignment warning and libatomic linking issue, so it makes sense to revert it. - - - - - e6bfb85c by Cheng Shao at 2024-03-12T19:27:11-04:00 compiler: fix out-of-bound memory access of genSym on 32-bit This commit fixes an unnoticed out-of-bound memory access of genSym on 32-bit. ghc_unique_inc is 32-bit sized/aligned on 32-bit platforms, but we mistakenly treat it as a Word64 pointer in genSym, and therefore will accidentally load 2 garbage higher bytes, or with a small but non-zero chance, overwrite something else in the data section depends on how the linker places the data segments. This regression was introduced in !11802 and fixed here. - - - - - 77171cd1 by Ben Orchard at 2024-03-14T09:00:40-04:00 Note mutability of array and address access primops Without an understanding of immutable vs. mutable memory, the index primop family have a potentially non-intuitive type signature: indexOffAddr :: Addr# -> Int# -> a readOffAddr :: Addr# -> Int# -> State# d -> (# State# d, a #) indexOffAddr# might seem like a free generality improvement, which it certainly is not! This change adds a brief note on mutability expectations for most index/read/write access primops. - - - - - 7da7f8f6 by Alan Zimmerman at 2024-03-14T09:01:15-04:00 EPA: Fix regression discarding comments in contexts Closes #24533 - - - - - 73be65ab by Fendor at 2024-03-19T01:42:53-04:00 Fix sharing of 'IfaceTyConInfo' during core to iface type translation During heap analysis, we noticed that during generation of 'mi_extra_decls' we have lots of duplicates for the instances: * `IfaceTyConInfo NotPromoted IfaceNormalTyCon` * `IfaceTyConInfo IsPromoted IfaceNormalTyCon` which should be shared instead of duplicated. This duplication increased the number of live bytes by around 200MB while loading the agda codebase into GHCi. These instances are created during `CoreToIface` translation, in particular `toIfaceTyCon`. The generated core looks like: toIfaceTyCon = \ tc_sjJw -> case $wtoIfaceTyCon tc_sjJw of { (# ww_sjJz, ww1_sjNL, ww2_sjNM #) -> IfaceTyCon ww_sjJz (IfaceTyConInfo ww1_sjNL ww2_sjNM) } whichs removes causes the sharing to work propery. Adding explicit sharing, with NOINLINE annotations, changes the core to: toIfaceTyCon = \ tc_sjJq -> case $wtoIfaceTyCon tc_sjJq of { (# ww_sjNB, ww1_sjNC #) -> IfaceTyCon ww_sjNB ww1_sjNC } which looks much more like sharing is happening. We confirmed via ghc-debug that all duplications were eliminated and the number of live bytes are noticeably reduced. - - - - - bd8209eb by Alan Zimmerman at 2024-03-19T01:43:28-04:00 EPA: Address more 9.10.1-alpha1 regressions from recent changes Closes #24533 Hopefully for good this time - - - - - 31bf85ee by Fendor at 2024-03-19T14:48:08-04:00 Escape multiple arguments in the settings file Uses responseFile syntax. The issue arises when GHC is installed on windows into a location that has a space, for example the user name is 'Fake User'. The $topdir will also contain a space, consequentially. When we resolve the top dir in the string `-I$topdir/mingw/include`, then `words` will turn this single argument into `-I/C/Users/Fake` and `User/.../mingw/include` which trips up the flag argument parser of various tools such as gcc or clang. We avoid this by escaping the $topdir before replacing it in `initSettngs`. Additionally, we allow to escape spaces and quotation marks for arguments in `settings` file. Add regression test case to count the number of options after variable expansion and argument escaping took place. Additionally, we check that escaped spaces and double quotation marks are correctly parsed. - - - - - f45f700e by Matthew Pickering at 2024-03-19T14:48:44-04:00 Read global package database from settings file Before this patch, the global package database was always assumed to be in libdir </> package.conf.d. This causes issues in GHC's build system because there are sometimes situations where the package database you need to use is not located in the same place as the settings file. * The stage1 compiler needs to use stage1 libraries, so we should set "Global Package DB" for the stage1 compiler to the stage1 package database. * Stage 2 cross compilers need to use stage2 libraries, so likewise, we should set the package database path to `_build/stage2/lib/` * The normal situation is where the stage2 compiler uses stage1 libraries. Then everything lines up. * When installing we have rearranged everything so that the settings file and package database line up properly, so then everything should continue to work as before. In this case we set the relative package db path to `package.conf.d`, so it resolves the same as before. * ghc-pkg needs to be modified as well to look in the settings file fo the package database rather than assuming the global package database location relative to the lib folder. * Cabal/cabal-install will work correctly because they query the global package database using `--print-global-package-db`. A reasonable question is why not generate the "right" settings files in the right places in GHC's build system. In order to do this you would need to engineer wrappers for all executables to point to a specific libdir. There are also situations where the same package db is used by two different compilers with two different settings files (think stage2 cross compiler and stage3 compiler). In short, this 10 line patch allows for some reasonable simplifications in Hadrian at very little cost to anything else. Fixes #24502 - - - - - 4c8f1794 by Matthew Pickering at 2024-03-19T14:48:44-04:00 hadrian: Remove stage1 testsuite wrappers logic Now instead of producing wrappers which pass the global package database argument to ghc and ghc-pkg, we write the location of the correct package database into the settings file so you can just use the intree compiler directly. - - - - - da0d8ba5 by Matthew Craven at 2024-03-19T14:49:20-04:00 Remove unused ghc-internal module "GHC.Internal.Constants" - - - - - b56d2761 by Matthew Craven at 2024-03-19T14:49:20-04:00 CorePrep: Rework lowering of BigNat# literals Don't use bigNatFromWord#, because that's terrible: * We shouldn't have to traverse a linked list at run-time to build a BigNat# literal. That's just silly! * The static List object we have to create is much larger than the actual BigNat#'s contents, bloating code size. * We have to read the corresponding interface file, which causes un-tracked implicit dependencies. (#23942) Instead, encode them into the appropriate platform-dependent sequence of bytes, and generate code that copies these bytes at run-time from an Addr# literal into a new ByteArray#. A ByteArray# literal would be the correct thing to generate, but these are not yet supported; see also #17747. Somewhat surprisingly, this change results in a slight reduction in compiler allocations, averaging around 0.5% on ghc's compiler performance tests, including when compiling programs that contain no bignum literals to begin with. The specific cause of this has not been investigated. Since this lowering no longer reads the interface file for GHC.Num.BigNat, the reasoning in Note [Depend on GHC.Num.Integer] is obsoleted. But the story of un-tracked built-in dependencies remains complex, and Note [Tracking dependencies on primitives] now exists to explain this complexity. Additionally, many empty imports have been modified to refer to this new note and comply with its guidance. Several empty imports necessary for other reasons have also been given brief explanations. Metric Decrease: MultiLayerModulesTH_OneShot - - - - - 349ea330 by Fendor at 2024-03-19T14:50:00-04:00 Eliminate thunk in 'IfaceTyCon' Heap analysis showed that `IfaceTyCon` retains a thunk to `IfaceTyConInfo`, defeating the sharing of the most common instances of `IfaceTyConInfo`. We make sure the indirection is removed by adding bang patterns to `IfaceTyCon`. Experimental results on the agda code base, where the `mi_extra_decls` were read from disk: Before this change, we observe around 8654045 instances of: `IfaceTyCon[Name,THUNK_1_0]` But these thunks almost exclusively point to a shared value! Forcing the thunk a little bit more, leads to `ghc-debug` reporting: `IfaceTyCon[Name:Name,IfaceTyConInfo]` and a noticeable reduction of live bytes (on agda ~10%). - - - - - 594bee0b by Krzysztof Gogolewski at 2024-03-19T14:50:36-04:00 Minor misc cleanups - GHC.HsToCore.Foreign.JavaScript: remove dropRuntimeRepArgs; boxed tuples don't take RuntimeRep args - GHC.HsToCore.Foreign.Call: avoid partial pattern matching - GHC.Stg.Unarise: strengthen the assertion; we can assert that non-rubbish literals are unary rather than just non-void - GHC.Tc.Gen.HsType: make sure the fsLit "literal" rule fires - users_guide/using-warnings.rst: remove -Wforall-identifier, now deprecated and does nothing - users_guide/using.rst: fix formatting - andy_cherry/test.T: remove expect_broken_for(23272...), 23272 is fixed The rest are simple cleanups. - - - - - cf55a54b by Ben Gamari at 2024-03-19T14:51:12-04:00 mk/relpath: Fix quoting Previously there were two instances in this script which lacked proper quoting. This resulted in `relpath` invocations in the binary distribution Makefile producing incorrect results on Windows, leading to confusing failures from `sed` and the production of empty package registrations. Fixes #24538. - - - - - 5ff88389 by Bryan Richter at 2024-03-19T14:51:48-04:00 testsuite: Disable T21336a on wasm - - - - - 60023351 by Ben Gamari at 2024-03-19T22:33:10-04:00 hadrian/bindist: Eliminate extraneous `dirname` invocation Previously we would call `dirname` twice per installed library file. We now instead reuse this result. This helps appreciably on Windows, where processes are quite expensive. - - - - - 616ac300 by Ben Gamari at 2024-03-19T22:33:10-04:00 hadrian: Package mingw toolchain in expected location This fixes #24525, a regression due to 41cbaf44a6ab5eb9fa676d65d32df8377898dc89. Specifically, GHC expects to find the mingw32 toolchain in the binary distribution root. However, after this patch it was packaged in the `lib/` directory. - - - - - de9daade by Ben Gamari at 2024-03-19T22:33:11-04:00 gitlab/rel_eng: More upload.sh tweaks - - - - - 1dfe12db by Ben Gamari at 2024-03-19T22:33:11-04:00 rel_eng: Drop dead prepare_docs codepath - - - - - dd2d748b by Ben Gamari at 2024-03-19T22:33:11-04:00 rel_env/recompress_all: unxz before recompressing Previously we would rather compress the xz *again*, before in addition compressing it with the desired scheme. Fixes #24545. - - - - - 9d936c57 by Ben Gamari at 2024-03-19T22:33:11-04:00 mk-ghcup-metadata: Fix directory of testsuite tarball As reported in #24546, the `dlTest` artifact should be extracted into the `testsuite` directory. - - - - - 6d398066 by Ben Gamari at 2024-03-19T22:33:11-04:00 ghcup-metadata: Don't populate dlOutput unless necessary ghcup can apparently infer the output name of an artifact from its URL. Consequently, we should only include the `dlOutput` field when it would differ from the filename of `dlUri`. Fixes #24547. - - - - - 576f8b7e by Zubin Duggal at 2024-03-19T22:33:46-04:00 Revert "Apply shellcheck suggestion to SUBST_TOOLDIR" This reverts commit c82770f57977a2b5add6e1378f234f8dd6153392. The shellcheck suggestion is spurious and results in SUBST_TOOLDIR being a no-op. `set` sets positional arguments for bash, but we want to set the variable given as the first autoconf argument. Fixes #24542 Metric decreases because the paths in the settings file are now shorter, so we allocate less when we read the settings file. ------------------------- Metric Decrease: T12425 T13035 T9198 ------------------------- - - - - - cdfe6e01 by Fendor at 2024-03-19T22:34:22-04:00 Compact serialisation of IfaceAppArgs In #24563, we identified that IfaceAppArgs serialisation tags each cons cell element with a discriminator byte. These bytes add up quickly, blowing up interface files considerably when '-fwrite-if-simplified-core' is enabled. We compact the serialisation by writing out the length of 'IfaceAppArgs', followed by serialising the elements directly without any discriminator byte. This improvement can decrease the size of some interface files by up to 35%. - - - - - 97a2bb1c by Simon Peyton Jones at 2024-03-20T17:11:29+00:00 Expand untyped splices in tcPolyExprCheck Fixes #24559 - - - - - 5f275176 by Alan Zimmerman at 2024-03-20T22:44:12-04:00 EPA: Clean up Exactprint helper functions a bit - Introduce a helper lens to compose on `EpAnn a` vs `a` versions - Rename some prime versions of functions back to non-prime They were renamed during the rework - - - - - da2a10ce by Vladislav Zavialov at 2024-03-20T22:44:48-04:00 Type operators in promoteOccName (#24570) Type operators differ from term operators in that they are lexically classified as (type) constructors, not as (type) variables. Prior to this change, promoteOccName did not account for this difference, causing a scoping issue that affected RequiredTypeArguments. type (!@#) = Bool f = idee (!@#) -- Not in scope: ‘!@#’ (BUG) Now we have a special case in promoteOccName to account for this. - - - - - 247fc0fa by Preetham Gujjula at 2024-03-21T10:19:18-04:00 docs: Remove mention of non-existent Ord instance for Complex The documentation for Data.Complex says that the Ord instance for Complex Float is deficient, but there is no Ord instance for Complex a. The Eq instance for Complex Float is similarly deficient, so we use that as an example instead. - - - - - 6fafc51e by Andrei Borzenkov at 2024-03-21T10:19:54-04:00 Fix TH handling in `pat_to_type_pat` function (#24571) There was missing case for `SplicePat` in `pat_to_type_at` function, hence patterns with splicing that checked against `forall->` doesn't work properly because they fall into the "illegal pattern" case. Code example that is now accepted: g :: forall a -> () g $([p| a |]) = () - - - - - 52072f8e by Sylvain Henry at 2024-03-21T21:01:59-04:00 Type-check default declarations before deriving clauses (#24566) See added Note and #24566. Default declarations must be type-checked before deriving clauses. - - - - - 7dfdf3d9 by Sylvain Henry at 2024-03-21T21:02:40-04:00 Lexer: small perf changes - Use unsafeChr because we know our values to be valid - Remove some unnecessary use of `ord` (return Word8 values directly) - - - - - 864922ef by Sylvain Henry at 2024-03-21T21:02:40-04:00 JS: fix some comments - - - - - 3e0b2b1f by Sebastian Graf at 2024-03-21T21:03:16-04:00 Simplifier: Re-do dependency analysis in abstractFloats (#24551) In #24551, we abstracted a string literal binding over a type variable, triggering a CoreLint error when that binding floated to top-level. The solution implemented in this patch fixes this by re-doing dependency analysis on a simplified recursive let binding that is about to be type abstracted, in order to find the minimal set of type variables to abstract over. See wrinkle (AB5) of Note [Floating and type abstraction] for more details. Fixes #24551 - - - - - 8a8ac65a by Matthew Craven at 2024-03-23T00:20:52-04:00 Improve toInteger @Word32 on 64-bit platforms On 64-bit platforms, every Word32 fits in an Int, so we can convert to Int# without having to perform the overflow check integerFromWord# uses internally. - - - - - 0c48f2b9 by Apoorv Ingle at 2024-03-23T00:21:28-04:00 Fix for #24552 (see testcase T24552) Fixes for a bug in desugaring pattern synonyms matches, introduced while working on on expanding `do`-blocks in #18324 The `matchWrapper` unecessarily (and incorrectly) filtered out the default wild patterns in a match. Now the wild pattern alternative is simply ignored by the pm check as its origin is `Generated`. The current code now matches the expected semantics according to the language spec. - - - - - b72705e9 by Simon Peyton Jones at 2024-03-23T00:22:04-04:00 Print more info about kinds in error messages This fixes #24553, where GHC unhelpfully said error: [GHC-83865] • Expected kind ‘* -> * -> *’, but ‘Foo’ has kind ‘* -> * -> *’ See Note [Showing invisible bits of types in error messages] - - - - - 8f7cfc7e by Tristan Cacqueray at 2024-03-23T00:22:44-04:00 docs: remove the don't use float hint This hint is outdated, ``Complex Float`` are now specialised, and the heap space suggestion needs more nuance so it should be explained in the unboxed/storable array documentation. - - - - - 5bd8ed53 by Andreas Klebinger at 2024-03-23T16:18:33-04:00 NCG: Fix a bug in jump shortcutting. When checking if a jump has more than one destination account for the possibility of some jumps not being representable by a BlockId. We do so by having isJumpishInstr return a `Maybe BlockId` where Nothing represents non-BlockId jump destinations. Fixes #24507 - - - - - 8d67f247 by Ben Gamari at 2024-03-23T16:19:09-04:00 docs: Drop old release notes, add for 9.12.1 - - - - - 7db8c992 by Cheng Shao at 2024-03-25T13:45:46-04:00 rts: fix clang compilation on aarch64 This patch fixes function prototypes in ARMOutlineAtomicsSymbols.h which causes "error: address argument to atomic operation must be a pointer to _Atomic type" when compiling with clang on aarch64. - - - - - 237194ce by Sylvain Henry at 2024-03-25T13:46:27-04:00 Lexer: fix imports for Alex 3.5.1 (#24583) - - - - - 810660b7 by Cheng Shao at 2024-03-25T22:19:16-04:00 libffi-tarballs: bump libffi-tarballs submodule to libffi 3.4.6 This commit bumps the libffi-tarballs submodule to libffi 3.4.6, which includes numerous upstream libffi fixes, especially https://github.com/libffi/libffi/issues/760. - - - - - d2ba41e8 by Alan Zimmerman at 2024-03-25T22:19:51-04:00 EPA: do not duplicate comments in signature RHS - - - - - 32a8103f by Rodrigo Mesquita at 2024-03-26T21:16:12-04:00 configure: Use LDFLAGS when trying linkers A user may configure `LDFLAGS` but not `LD`. When choosing a linker, we will prefer `ldd`, then `ld.gold`, then `ld.bfd` -- however, we have to check for a working linker. If either of these fail, we try the next in line. However, we were not considering the `$LDFLAGS` when checking if these linkers worked. So we would pick a linker that does not support the current $LDFLAGS and fail further down the line when we used that linker with those flags. Fixes #24565, where `LDFLAGS=-Wl,-z,pack-relative-relocs` is not supported by `ld.gold` but that was being picked still. - - - - - bf65a7c3 by Rodrigo Mesquita at 2024-03-26T21:16:48-04:00 bindist: Clean xattrs of bin and lib at configure time For issue #21506, we started cleaning the extended attributes of binaries and libraries from the bindist *after* they were installed to workaround notarisation (#17418), as part of `make install`. However, the `ghc-toolchain` binary that is now shipped with the bindist must be run at `./configure` time. Since we only cleaned the xattributes of the binaries and libs after they were installed, in some situations users would be unable to run `ghc-toolchain` from the bindist, failing at configure time (#24554). In this commit we move the xattr cleaning logic to the configure script. Fixes #24554 - - - - - cfeb70d3 by Rodrigo Mesquita at 2024-03-26T21:17:24-04:00 Revert "NCG: Fix a bug in jump shortcutting." This reverts commit 5bd8ed53dcefe10b72acb5729789e19ceb22df66. Fixes #24586 - - - - - 13223f6d by Serge S. Gulin at 2024-03-27T07:28:51-04:00 JS: `h$rts_isProfiled` is removed from `profiling` and left its version at `rts/js/config.js` - - - - - 0acfe391 by Alan Zimmerman at 2024-03-27T07:29:27-04:00 EPA: Do not extend declaration range for trailine zero len semi The lexer inserts virtual semicolons having zero width. Do not use them to extend the list span of items in a list. - - - - - cd0fb82f by Alan Zimmerman at 2024-03-27T19:33:08+00:00 EPA: Fix FamDecl range The span was incorrect if opt_datafam_kind_sig was empty - - - - - f8f384a8 by Ben Gamari at 2024-03-29T01:23:03-04:00 Fix type of _get_osfhandle foreign import Fixes #24601. - - - - - 00d3ecf0 by Alan Zimmerman at 2024-03-29T12:19:10+00:00 EPA: Extend StringLiteral range to include trailing commas This goes slightly against the exact printing philosophy where trailing decorations should be in an annotation, but the practicalities of adding it to the WarningTxt environment, and the problems caused by deviating do not make a more principles approach worthwhile. - - - - - efab3649 by brandon s allbery kf8nh at 2024-03-31T20:04:01-04:00 clarify Note [Preproccesing invocations] - - - - - c8a4c050 by Ben Gamari at 2024-04-02T12:50:35-04:00 rts: Fix TSAN_ENABLED CPP guard This should be `#if defined(TSAN_ENABLED)`, not `#if TSAN_ENABLED`, lest we suffer warnings. - - - - - e91dad93 by Cheng Shao at 2024-04-02T12:50:35-04:00 rts: fix errors when compiling with TSAN This commit fixes rts compilation errors when compiling with TSAN: - xxx_FENCE macros are redefined and trigger CPP warnings. - Use SIZEOF_W. WORD_SIZE_IN_BITS is provided by MachDeps.h which Cmm.h doesn't include by default. - - - - - a9ab9455 by Cheng Shao at 2024-04-02T12:50:35-04:00 rts: fix clang-specific errors when compiling with TSAN This commit fixes clang-specific rts compilation errors when compiling with TSAN: - clang doesn't have -Wtsan flag - Fix prototype of ghc_tsan_* helper functions - __tsan_atomic_* functions aren't clang built-ins and sanitizer/tsan_interface_atomic.h needs to be included - On macOS, TSAN runtime library is libclang_rt.tsan_osx_dynamic.dylib, not libtsan. -fsanitize-thread as a link-time flag will take care of linking the TSAN runtime library anyway so remove tsan as an rts extra library - - - - - 865bd717 by Cheng Shao at 2024-04-02T12:50:35-04:00 compiler: fix github link to __tsan_memory_order in a comment - - - - - 07cb627c by Cheng Shao at 2024-04-02T12:50:35-04:00 ci: improve TSAN CI jobs - Run TSAN jobs with +thread_sanitizer_cmm which enables Cmm instrumentation as well. - Run TSAN jobs in deb12 which ships gcc-12, a reasonably recent gcc that @bgamari confirms he's using in #GHC:matrix.org. Ideally we should be using latest clang release for latest improvements in sanitizers, though that's left as future work. - Mark TSAN jobs as manual+allow_failure in validate pipelines. The purpose is to demonstrate that we have indeed at least fixed building of TSAN mode in CI without blocking the patch to land, and once merged other people can begin playing with TSAN using their own dev setups and feature branches. - - - - - a1c18c7b by Andrei Borzenkov at 2024-04-02T12:51:11-04:00 Merge tc_infer_hs_type and tc_hs_type into one function using ExpType philosophy (#24299, #23639) This patch implements refactoring which is a prerequisite to updating kind checking of type patterns. This is a huge simplification of the main worker that checks kind of HsType. It also fixes the issues caused by previous code duplication, e.g. that we didn't add module finalizers from splices in inference mode. - - - - - 817e8936 by Rodrigo Mesquita at 2024-04-02T20:13:05-04:00 th: Hide the Language.Haskell.TH.Lib.Internal module from haddock Fixes #24562 - - - - - b36ee57b by Sylvain Henry at 2024-04-02T20:13:46-04:00 JS: reenable h$appendToHsString optimization (#24495) The optimization introducing h$appendToHsString wasn't kicking in anymore (while it did in 9.8.1) because of the changes introduced in #23270 (7e0c8b3bab30). This patch reenables the optimization by matching on case-expression, as done in Cmm for unpackCString# standard thunks. The test is also T24495 added in the next commits (two commits for ease of backporting to 9.8). - - - - - 527616e9 by Sylvain Henry at 2024-04-02T20:13:46-04:00 JS: fix h$appendToHsString implementation (#24495) h$appendToHsString needs to wrap its argument in an updatable thunk to behave like unpackAppendCString#. Otherwise if a SingleEntry thunk is passed, it is stored as-is in a CONS cell, making the resulting list impossible to deepseq (forcing the thunk doesn't update the contents of the CONS cell)! The added test checks that the optimization kicks in and that h$appendToHsString works as intended. Fix #24495 - - - - - faa30b41 by Simon Peyton Jones at 2024-04-02T20:14:22-04:00 Deal with duplicate tyvars in type declarations GHC was outright crashing before this fix: #24604 - - - - - e0b0c717 by Simon Peyton Jones at 2024-04-02T20:14:58-04:00 Try using MCoercion in exprIsConApp_maybe This is just a simple refactor that makes exprIsConApp_maybe a little bit more direct, simple, and efficient. Metrics: compile_time/bytes allocated geo. mean -0.1% minimum -2.0% maximum -0.0% Not a big gain, but worthwhile given that the code is, if anything, easier to grok. - - - - - 15f4d867 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Initial ./configure support for selecting I/O managers In this patch we just define new CPP vars, but don't yet use them or replace the existing approach. That will follow. The intention here is that every I/O manager can be enabled/disabled at GHC build time (subject to some constraints). More than one I/O manager can be enabled to be built. At least one I/O manager supporting the non-threaded RTS must be enabled as well as at least one supporting the non-threaded RTS. The I/O managers enabled here will become the choices available at runtime at RTS startup (in later patches). The choice can be made with RTS flags. There are separate sets of choices for the threaded and non-threaded RTS ways, because most I/O managers are specific to these ways. Furthermore we must establish a default I/O manager for the threaded and non-threaded RTS. Most I/O managers are platform-specific so there are checks to ensure each one can be enabled on the platform. Such checks are also where (in future) any system dependencies (e.g. libraries) can be checked. The output is a set of CPP flags (in the mk/config.h file), with one flag per named I/O manager: * IOMGR_BUILD_<name> : which ones should be built (some) * IOMGR_DEFAULT_NON_THREADED_<name> : which one is default (exactly one) * IOMGR_DEFAULT_THREADED_<name> : which one is default (exactly one) and a set of derived flags in IOManager.h * IOMGR_ENABLED_<name> : enabled for the current RTS way Note that IOMGR_BUILD_<name> just says that an I/O manager will be built for _some_ RTS way (i.e. threaded or non-threaded). The derived flags IOMGR_ENABLED_<name> in IOManager.h say if each I/O manager is enabled in the "current" RTS way. These are the ones that can be used for conditional compilation of the I/O manager code. Co-authored-by: Pi Delport <pi at well-typed.com> - - - - - 85b0f87a by Duncan Coutts at 2024-04-03T01:27:17-04:00 Change the handling of the RTS flag --io-manager= Now instead of it being just used on Windows to select between the WinIO vs the MIO or Win32-legacy I/O managers, it is now used on all platforms for selecting the I/O manager to use. Right now it remains the case that there is only an actual choice on Windows, but that will change later. Document the --io-manager flag in the user guide. This change is also reflected in the RTS flags types in the base library. Deprecate the export of IoSubSystem from GHC.RTS.Flags with a message to import it from GHC.IO.Subsystem. The way the 'IoSubSystem' is detected also changes. Instead of looking at the RTS flag, there is now a C bool global var in the RTS which gets set on startup when the I/O manager is selected. This bool var says whether the selected I/O manager classifies as "native" on Windows, which in practice means the WinIO I/O manager has been selected. Similarly, the is_io_mng_native_p RTS helper function is re-implemented in terms of the selected I/O manager, rather than based on the RTS flags. We do however remove the ./configure --native-io-manager flag because we're bringing the WinIO/MIO/Win32-legacy choice under the new general scheme for selecting I/O managers, and that new scheme involves no ./configure time user choices, just runtime RTS flag choices. - - - - - 1a8f020f by Duncan Coutts at 2024-04-03T01:27:17-04:00 Convert {init,stop,exit}IOManager to switch style Rather than ad-hoc cpp conitionals on THREADED_RTS and mingw32_HOST_OS, we use a style where we switch on the I/O manager impl, with cases for each I/O manager impl. - - - - - a5bad3d2 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Split up the CapIOManager content by I/O manager Using the new IOMGR_ENABLED_<name> CPP defines. - - - - - 1d36e609 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Convert initIOManagerAfterFork and wakeupIOManager to switch style - - - - - c2f26f36 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move most of waitRead#/Write# from cmm to C Moves it into the IOManager.c where we can follow the new pattern of switching on the selected I/O manager. - - - - - 457705a8 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move most of the delay# impl from cmm to C Moves it into the IOManager.c where we can follow the new pattern of switching on the selected I/O manager. Uses a new IOManager API: syncDelay, following the naming convention of sync* for thread-synchronous I/O & timer/delay operations. As part of porting from cmm to C, we maintain the rule that the why_blocked gets accessed using load acquire and store release atomic memory operations. There was one exception to this rule: in the delay# primop cmm code on posix (not win32), the why_blocked was being updated using a store relaxed, not a store release. I've no idea why. In this convesion I'm playing it safe here and using store release consistently. - - - - - e93058e0 by Duncan Coutts at 2024-04-03T01:27:18-04:00 insertIntoSleepingQueue is no longer public No longer defined in IOManager.h, just a private function in IOManager.c. Since it is no longer called from cmm code, just from syncDelay. It ought to get moved further into the select() I/O manager impl, rather than living in IOManager.c. On the other hand appendToIOBlockedQueue is still called from cmm code in the win32-legacy I/O manager primops async{Read,Write}#, and it is also used by the select() I/O manager. Update the CPP and comments to reflect this. - - - - - 60ce9910 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move anyPendingTimeoutsOrIO impl from .h to .c The implementation is eventually going to need to use more private things, which will drag in unwanted includes into IOManager.h, so it's better to move the impl out of the header file and into the .c file, at the slight cost of it no longer being inline. At the same time, change to the "switch (iomgr_type)" style. - - - - - f70b8108 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Take a simpler approach to gcc warnings in IOManager.c We have lots of functions with conditional implementations for different I/O managers. Some functions, for some I/O managers, naturally have implementations that do nothing or barf. When only one such I/O manager is enabled then the whole function implementation will have an implementation that does nothing or barfs. This then results in warnings from gcc that parameters are unused, or that the function should be marked with attribute noreturn (since barf does not return). The USED_IF_THREADS trick for fine-grained warning supression is fine for just two cases, but an equivalent here would need USED_IF_THE_ONLY_ENABLED_IOMGR_IS_X_OR_Y which would have combinitorial blowup. So we take a coarse grained approach and simply disable these two warnings for the whole file. So we use a GCC pragma, with its handy push/pop support: #pragma GCC diagnostic push #pragma GCC diagnostic ignored "-Wsuggest-attribute=noreturn" #pragma GCC diagnostic ignored "-Wunused-parameter" ... #pragma GCC diagnostic pop - - - - - b48805b9 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add a new trace class for the iomanager It makes sense now for it to be separate from the scheduler class of tracers. Enabled with +RTS -Do. Document the -Do debug flag in the user guide. - - - - - f0c1f862 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Have the throwTo impl go via (new) IOManager APIs rather than directly operating on the IO manager's data structures. Specifically, when thowing an async exception to a thread that is blocked waiting for I/O or waiting for a timer, then we want to cancel that I/O waiting or cancel the timer. Currently this is done directly in removeFromQueues() in RaiseAsync.c. We want it to go via proper APIs both for modularity but also to let us support multiple I/O managers. So add sync{IO,Delay}Cancel, which is the cancellation for the corresponding sync{IO,Delay}. The implementations of these use the usual "switch (iomgr_type)" style. - - - - - 4f9e9c4e by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move awaitEvent into a proper IOManager API and have the scheduler use it. Previously the scheduler calls awaitEvent directly, and awaitEvent is implemented directly in the RTS I/O managers (select, win32). This relies on the old scheme where there's a single active I/O manager for each platform and RTS way. We want to move that to go via an API in IOManager.{h,c} which can then call out to the active I/O manager. Also take the opportunity to split awaitEvent into two. The existing awaitEvent has a bool wait parameter, to say if the call should be blocking or non-blocking. We split this into two separate functions: pollCompletedTimeoutsOrIO and awaitCompletedTimeoutsOrIO. We split them for a few reasons: they have different post-conditions (specifically the await version is supposed to guarantee that there are threads runnable when it completes). Secondly, it is also anticipated that in future I/O managers the implementations of the two cases will be simpler if they are separated. - - - - - 5ad4b30f by Duncan Coutts at 2024-04-03T01:27:18-04:00 Rename awaitEvent in select and win32 I/O managers These are now just called from IOManager.c and are the per-I/O manager backend impls (whereas previously awaitEvent was the entry point). Follow the new naming convention in the IOManager.{h,c} of awaitCompletedTimeoutsOrIO, with the I/O manager's name as a suffix: so awaitCompletedTimeoutsOrIO{Select,Win32}. - - - - - d30c6bc6 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Tidy up a couple things in Select.{h,c} Use the standard #include {Begin,End}Private.h style rather than RTS_PRIVATE on individual decls. And conditionally build the code for the select I/O manager based on the new CPP IOMGR_ENABLED_SELECT rather than on THREADED_RTS. - - - - - 4161f516 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add an IOManager API for scavenging TSO blocked_info When the GC scavenges a TSO it needs to scavenge the tso->blocked_info but the blocked_info is a big union and what lives there depends on the two->why_blocked, which for I/O-related reasons is something that in principle is the responsibility of the I/O manager and not the GC. So the right thing to do is for the GC to ask the I/O manager to sscavenge the blocked_info if it encounters any I/O-related why_blocked reasons. So we add scavengeTSOIOManager in IOManager.{h,c} with the usual style. Now as it happens, right now, there is no special scavenging to do, so the implementation of scavengeTSOIOManager is a fancy no-op. That's because the select I/O manager uses only the fd and target members, which are not GC pointers, and the win32-legacy I/O manager _ought_ to be using GC-managed heap objects for the StgAsyncIOResult but it is actually usingthe C heap, so again no GC pointers. If the win32-legacy were doing this more sensibly, then scavengeTSOIOManager would be the right place to do the GC magic. Future I/O managers will need GC heap objects in the tso->blocked_info and will make use of this functionality. - - - - - 94a87d21 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add I/O manager API notifyIOManagerCapabilitiesChanged Used in setNumCapabilities. It only does anything for MIO on Posix. Previously it always invoked Haskell code, but that code only did anything on non-Windows (and non-JS), and only threaded. That currently effectively means the MIO I/O manager on Posix. So now it only invokes it for the MIO Posix case. - - - - - 3be6d591 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Select an I/O manager early in RTS startup We need to select the I/O manager to use during startup before the per-cap I/O manager initialisation. - - - - - aaa294d0 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Make struct CapIOManager be fully opaque Provide an opaque (forward) definition in Capability.h (since the cap contains a *CapIOManager) and then only provide a full definition in a new file IOManagerInternals.h. This new file is only supposed to be included by the IOManager implementation, not by its users. So that means IOManager.c and individual I/O manager implementations. The posix/Signals.c still needs direct access, but that should be eliminated. Anything that needs direct access either needs to be clearly part of an I/O manager (e.g. the sleect() one) or go via a proper API. - - - - - 877a2a80 by Duncan Coutts at 2024-04-03T01:27:18-04:00 The select() I/O manager does have some global initialisation It's just to make sure an exception CAF is a GC root. - - - - - 9c51473b by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add tracing for the main I/O manager actions Using the new tracer class. Note: The unconditional definition of showIOManager should be compatible with the debugTrace change in 7c7d1f6. Co-authored-by: Pi Delport <pi at well-typed.com> - - - - - c7d3e3a3 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Include the default I/O manager in the +RTS --info output Document the extra +RTS --info output in the user guide - - - - - 8023bad4 by Duncan Coutts at 2024-04-03T01:27:18-04:00 waitRead# / waitWrite# do not work for win32-legacy I/O manager Previously it was unclear that they did not work because the code path was shared with other I/O managers (in particular select()). Following the code carefully shows that what actually happens is that the calling thread would block forever: the thread will be put into the blocked queue, but no other action is scheduled that will ever result in it getting unblocked. It's better to just fail loudly in case anyone accidentally calls it, also it's less confusing code. - - - - - 83a74d20 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Conditionally ignore some GCC warnings Some GCC versions don't know about some warnings, and they complain that we're ignoring unknown warnings. So we try to ignore the warning based on the GCC version. - - - - - 1adc6fa4 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Accept changes to base-exports All the changes are in fact not changes at all. Previously, the IoSubSystem data type was defined in GHC.RTS.Flags and exported from both GHC.RTS.Flags and GHC.IO.SubSystem. Now, the data type is defined in GHC.IO.SubSystem and still exported from both modules. Therefore, the same exports and same instances are still available from both modules. But the base-exports records only the defining module, and so it looks like a change when it is fully compatible. Related: we do add a deprecation to the export of the type via GHC.RTS.Flags, telling people to use the export from GHC.IO.SubSystem. Also the sort order for some unrelated Show instances changed. No idea why. The same changes apply in the other versions, with a few more changes due to sort order weirdness. - - - - - 8d950968 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Accept metric decrease in T12227 I can't think of any good reason that anything in this MR should have changed the number of allocations, up or down. (Yes this is an empty commit.) Metric Decrease: T12227 - - - - - e869605e by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Several improvements to the handling of coercions * Make `mkSymCo` and `mkInstCo` smarter Fixes #23642 * Fix return role of `SelCo` in the coercion optimiser. Fixes #23617 * Make the coercion optimiser `opt_trans_rule` work better for newtypes Fixes #23619 - - - - - 1efd0714 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 FloatOut: improve floating for join point See the new Note [Floating join point bindings]. * Completely get rid of the complicated join_ceiling nonsense, which I have never understood. * Do not float join points at all, except perhaps to top level. * Some refactoring around wantToFloat, to treat Rec and NonRec more uniformly - - - - - 9c00154d by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Improve eta-expansion through call stacks See Note [Eta expanding through CallStacks] in GHC.Core.Opt.Arity This is a one-line change, that fixes an inconsistency - || isCallStackPredTy ty + || isCallStackPredTy ty || isCallStackTy ty - - - - - 95a9a172 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Spelling, layout, pretty-printing only - - - - - bdf1660f by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Improve exprIsConApp_maybe a little Eliminate a redundant case at birth. This sometimes reduces Simplifier iterations. See Note [Case elim in exprIsConApp_maybe]. - - - - - 609cd32c by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Inline GHC.HsToCore.Pmc.Solver.Types.trvVarInfo When exploring compile-time regressions after meddling with the Simplifier, I discovered that GHC.HsToCore.Pmc.Solver.Types.trvVarInfo was very delicately balanced. It's a small, heavily used, overloaded function and it's important that it inlines. By a fluke it was before, but at various times in my journey it stopped doing so. So I just added an INLINE pragma to it; no sense in depending on a delicately-balanced fluke. - - - - - ae24c9bc by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Slight improvement in WorkWrap Ensure that WorkWrap preserves lambda binders, in case of join points. Sadly I have forgotten why I made this change (it was while I was doing a lot of meddling in the Simplifier, but * it does no harm, * it is slightly more efficient, and * presumably it made something better! Anyway I have kept it in a separate commit. - - - - - e9297181 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Use named record fields for the CastIt { ... } data constructor This is a pure refactor - - - - - b4581e23 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Remove a long-commented-out line Pure refactoring - - - - - e026bdf2 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Simplifier improvements This MR started as: allow the simplifer to do more in one pass, arising from places I could see the simplifier taking two iterations where one would do. But it turned into a larger project, because these changes unexpectedly made inlining blow up, especially join points in deeply-nested cases. The main changes are below. There are also many new or rewritten Notes. Avoiding simplifying repeatedly ~~~~~~~~~~~~~~~ See Note [Avoiding simplifying repeatedly] * The SimplEnv now has a seInlineDepth field, which says how deep in unfoldings we are. See Note [Inline depth] in Simplify.Env. Currently used only for the next point: avoiding repeatedly simplifying coercions. * Avoid repeatedly simplifying coercions. see Note [Avoid re-simplifying coercions] in Simplify.Iteration As you'll see from the Note, this makes use of the seInlineDepth. * Allow Simplify.Iteration.simplAuxBind to inline used-once things. This is another part of Note [Post-inline for single-use things], and is really good for reducing simplifier iterations in situations like case K e of { K x -> blah } wher x is used once in blah. * Make GHC.Core.SimpleOpt.exprIsConApp_maybe do some simple case elimination. Note [Case elim in exprIsConApp_maybe] * Improve the case-merge transformation: - Move the main code to `GHC.Core.Utils.mergeCaseAlts`, to join `filterAlts` and friends. See Note [Merge Nested Cases] in GHC.Core.Utils. - Add a new case for `tagToEnum#`; see wrinkle (MC3). - Add a new case to look through join points: see wrinkle (MC4) postInlineUnconditionally ~~~~~~~~~~~~~~~~~~~~~~~~~ * Allow Simplify.Utils.postInlineUnconditionally to inline variables that are used exactly once. See Note [Post-inline for single-use things]. * Do not postInlineUnconditionally join point, ever. Doing so does not reduce allocation, which is the main point, and with join points that are used a lot it can bloat code. See point (1) of Note [Duplicating join points] in GHC.Core.Opt.Simplify.Iteration. * Do not postInlineUnconditionally a strict (demanded) binding. It will not allocate a thunk (it'll turn into a case instead) so again the main point of inlining it doesn't hold. Better to check per-call-site. * Improve occurrence analyis for bottoming function calls, to help postInlineUnconditionally. See Note [Bottoming function calls] in GHC.Core.Opt.OccurAnal Inlining generally ~~~~~~~~~~~~~~~~~~ * In GHC.Core.Opt.Simplify.Utils.interestingCallContext, use RhsCtxt NonRecursive (not BoringCtxt) for a plain-seq case. See Note [Seq is boring] Also, wrinkle (SB1), inline in that `seq` context only for INLINE functions (UnfWhen guidance). * In GHC.Core.Opt.Simplify.Utils.interestingArg, - return ValueArg for OtherCon [c1,c2, ...], but - return NonTrivArg for OtherCon [] This makes a function a little less likely to inline if all we know is that the argument is evaluated, but nothing else. * isConLikeUnfolding is no longer true for OtherCon {}. This propagates to exprIsConLike. Con-like-ness has /positive/ information. Join points ~~~~~~~~~~~ * Be very careful about inlining join points. See these two long Notes Note [Duplicating join points] in GHC.Core.Opt.Simplify.Iteration Note [Inlining join points] in GHC.Core.Opt.Simplify.Inline * When making join points, don't do so if the join point is so small it will immediately be inlined; check uncondInlineJoin. * In GHC.Core.Opt.Simplify.Inline.tryUnfolding, improve the inlining heuristics for join points. In general we /do not/ want to inline join points /even if they are small/. See Note [Duplicating join points] GHC.Core.Opt.Simplify.Iteration. But sometimes we do: see Note [Inlining join points] in GHC.Core.Opt.Simplify.Inline; and the new `isBetterUnfoldingThan` function. * Do not add an unfolding to a join point at birth. This is a tricky one and has a long Note [Do not add unfoldings to join points at birth] It shows up in two places - In `mkDupableAlt` do not add an inlining - (trickier) In `simplLetUnfolding` don't add an unfolding for a fresh join point I am not fully satisifed with this, but it works and is well documented. * In GHC.Core.Unfold.sizeExpr, make jumps small, so that we don't penalise having a non-inlined join point. Performance changes ~~~~~~~~~~~~~~~~~~~ * Binary sizes fall by around 2.6%, according to nofib. * Compile times improve slightly. Here are the figures over 1%. I investiate the biggest differnce in T18304. It's a very small module, just a few hundred nodes. The large percentage difffence is due to a single function that didn't quite inline before, and does now, making code size a bit bigger. I decided gains outweighed the losses. Metrics: compile_time/bytes allocated (changes over +/- 1%) ------------------------------------------------ CoOpt_Singletons(normal) -9.2% GOOD LargeRecord(normal) -23.5% GOOD MultiComponentModulesRecomp(normal) +1.2% MultiLayerModulesTH_OneShot(normal) +4.1% BAD PmSeriesS(normal) -3.8% PmSeriesV(normal) -1.5% T11195(normal) -1.3% T12227(normal) -20.4% GOOD T12545(normal) -3.2% T12707(normal) -2.1% GOOD T13253(normal) -1.2% T13253-spj(normal) +8.1% BAD T13386(normal) -3.1% GOOD T14766(normal) -2.6% GOOD T15164(normal) -1.4% T15304(normal) +1.2% T15630(normal) -8.2% T15630a(normal) NEW T15703(normal) -14.7% GOOD T16577(normal) -2.3% GOOD T17516(normal) -39.7% GOOD T18140(normal) +1.2% T18223(normal) -17.1% GOOD T18282(normal) -5.0% GOOD T18304(normal) +10.8% BAD T18923(normal) -2.9% GOOD T1969(normal) +1.0% T19695(normal) -1.5% T20049(normal) -12.7% GOOD T21839c(normal) -4.1% GOOD T3064(normal) -1.5% T3294(normal) +1.2% BAD T4801(normal) +1.2% T5030(normal) -15.2% GOOD T5321Fun(normal) -2.2% GOOD T6048(optasm) -16.8% GOOD T783(normal) -1.2% T8095(normal) -6.0% GOOD T9630(normal) -4.7% GOOD T9961(normal) +1.9% BAD WWRec(normal) -1.4% info_table_map_perf(normal) -1.3% parsing001(normal) +1.5% geo. mean -2.0% minimum -39.7% maximum +10.8% * Runtimes generally improve. In the testsuite perf/should_run gives: Metrics: runtime/bytes allocated ------------------------------------------ Conversions(normal) -0.3% T13536a(optasm) -41.7% GOOD T4830(normal) -0.1% haddock.Cabal(normal) -0.1% haddock.base(normal) -0.1% haddock.compiler(normal) -0.1% geo. mean -0.8% minimum -41.7% maximum +0.0% * For runtime, nofib is a better test. The news is mostly good. Here are the number more than +/- 0.1%: # bytes allocated ==========================++========== imaginary/digits-of-e1 || -14.40% imaginary/digits-of-e2 || -4.41% imaginary/paraffins || -0.17% imaginary/rfib || -0.15% imaginary/wheel-sieve2 || -0.10% real/compress || -0.47% real/fluid || -0.10% real/fulsom || +0.14% real/gamteb || -1.47% real/gg || -0.20% real/infer || +0.24% real/pic || -0.23% real/prolog || -0.36% real/scs || -0.46% real/smallpt || +4.03% shootout/k-nucleotide || -20.23% shootout/n-body || -0.42% shootout/spectral-norm || -0.13% spectral/boyer2 || -3.80% spectral/constraints || -0.27% spectral/hartel/ida || -0.82% spectral/mate || -20.34% spectral/para || +0.46% spectral/rewrite || +1.30% spectral/sphere || -0.14% ==========================++========== geom mean || -0.59% real/smallpt has a huge nest of local definitions, and I could not pin down a reason for a regression. But there are three big wins! Metric Decrease: CoOpt_Singletons LargeRecord T12227 T12707 T13386 T13536a T14766 T15703 T16577 T17516 T18223 T18282 T18923 T21839c T20049 T5321Fun T5030 T6048 T8095 T9630 T783 Metric Increase: MultiLayerModulesTH_OneShot T13253-spj T18304 T18698a T9961 T3294 - - - - - 27db3c5e by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Testsuite message changes from simplifier improvements - - - - - 271a7812 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Account for bottoming functions in OccurAnal This fixes #24582, a small but long-standing bug - - - - - 0fde229f by Ben Gamari at 2024-04-04T07:04:58-04:00 testsuite: Introduce template-haskell-exports test - - - - - 0c4a9686 by Luite Stegeman at 2024-04-04T07:05:39-04:00 Update correct counter in bumpTickyAllocd - - - - - 5f085d3a by Fendor at 2024-04-04T14:47:33-04:00 Replace `SizedSeq` with `FlatBag` for flattened structure LinkedLists are notoriously memory ineffiecient when all we do is traversing a structure. As 'UnlinkedBCO' has been identified as a data structure that impacts the overall memory usage of GHCi sessions, we avoid linked lists and prefer flattened structure for storing. We introduce a new memory efficient representation of sequential elements that has special support for the cases: * Empty * Singleton * Tuple Elements This improves sharing in the 'Empty' case and avoids the overhead of 'Array' until its constant overhead is justified. - - - - - 82cfe10c by Fendor at 2024-04-04T14:47:33-04:00 Compact FlatBag array representation `Array` contains three additional `Word`'s we do not need in `FlatBag`. Move `FlatBag` to `SmallArray`. Expand the API of SmallArray by `sizeofSmallArray` and add common traversal functions, such as `mapSmallArray` and `foldMapSmallArray`. Additionally, allow users to force the elements of a `SmallArray` via `rnfSmallArray`. - - - - - 36a75b80 by Andrei Borzenkov at 2024-04-04T14:48:10-04:00 Change how invisible patterns represented in haskell syntax and TH AST (#24557) Before this patch: data ArgPat p = InvisPat (LHsType p) | VisPat (LPat p) With this patch: data Pat p = ... | InvisPat (LHsType p) ... And the same transformation in the TH land. The rest of the changes is just updating code to handle new AST and writing tests to check if it is possible to create invalid states using TH. Metric Increase: MultiLayerModulesTH_OneShot - - - - - 28009fbc by Matthew Pickering at 2024-04-04T14:48:46-04:00 Fix off by one error in seekBinNoExpand and seekBin - - - - - 9b9e031b by Ben Gamari at 2024-04-04T21:30:08-04:00 compiler: Allow more types in GHCForeignImportPrim For many, many years `GHCForeignImportPrim` has suffered from the rather restrictive limitation of not allowing any non-trivial types in arguments or results. This limitation was justified by the code generator allegely barfing in the presence of such types. However, this restriction appears to originate well before the NCG rewrite and the new NCG does not appear to have any trouble with such types (see the added `T24598` test). Lift this restriction. Fixes #24598. - - - - - 1324b862 by Alan Zimmerman at 2024-04-04T21:30:44-04:00 EPA: Use EpaLocation not SrcSpan in ForeignDecls This allows us to update them for makeDeltaAst in ghc-exactprint - - - - - 19883a23 by Alan Zimmerman at 2024-04-05T16:58:17-04:00 EPA: Use EpaLocation for RecFieldsDotDot So we can update it to a delta position in makeDeltaAst if needed. - - - - - e8724327 by Matthew Pickering at 2024-04-05T16:58:53-04:00 Remove accidentally committed test.hs - - - - - 88cb3e10 by Fendor at 2024-04-08T09:03:34-04:00 Avoid UArray when indexing is not required `UnlinkedBCO`'s can occur many times in the heap. Each `UnlinkedBCO` references two `UArray`'s but never indexes them. They are only needed to encode the elements into a `ByteArray#`. The three words for the lower bound, upper bound and number of elements are essentially unused, thus we replace `UArray` with a wrapper around `ByteArray#`. This saves us up to three words for each `UnlinkedBCO`. Further, to avoid re-allocating these words for `ResolvedBCO`, we repeat the procedure for `ResolvedBCO` and add custom `Binary` and `Show` instances. For example, agda's repl session has around 360_000 UnlinkedBCO's, so avoiding these three words is already saving us around 8MB residency. - - - - - f2cc1107 by Fendor at 2024-04-08T09:04:11-04:00 Never UNPACK `FastMutInt` for counting z-encoded `FastString`s In `FastStringTable`, we count the number of z-encoded FastStrings that exist in a GHC session. We used to UNPACK the counters to not waste memory, but live retainer analysis showed that we allocate a lot of `FastMutInt`s, retained by `mkFastZString`. We lazily compute the `FastZString`, only incrementing the counter when the `FastZString` is forced. The function `mkFastStringWith` calls `mkZFastString` and boxes the `FastMutInt`, leading to the following core: mkFastStringWith = \ mk_fs _ -> = case stringTable of { FastStringTable _ n_zencs segments# _ -> ... case ((mk_fs (I# ...) (FastMutInt n_zencs)) `cast` <Co:2> :: ...) ... Marking this field as `NOUNPACK` avoids this reboxing, eliminating the allocation of a fresh `FastMutInt` on every `FastString` allocation. - - - - - c6def949 by Matthew Pickering at 2024-04-08T16:06:51-04:00 Force in_multi to avoid retaining entire hsc_env - - - - - fbb91a63 by Fendor at 2024-04-08T16:06:51-04:00 Eliminate name thunk in declaration fingerprinting Thunk analysis showed that we have about 100_000 thunks (in agda and `-fwrite-simplified-core`) pointing to the name of the name decl. Forcing this thunk fixes this issue. The thunk created here is retained by the thunk created by forkM, it is better to eagerly force this because the result (a `Name`) is already retained indirectly via the `IfaceDecl`. - - - - - 3b7b0c1c by Alan Zimmerman at 2024-04-08T16:07:27-04:00 EPA: Use EpaLocation in WarningTxt This allows us to use an EpDelta if needed when using makeDeltaAst. - - - - - 12b997df by Alan Zimmerman at 2024-04-08T16:07:27-04:00 EPA: Move DeltaPos and EpaLocation' into GHC.Types.SrcLoc This allows us to use a NoCommentsLocation for the possibly trailing comma location in a StringLiteral. This in turn allows us to correctly roundtrip via makeDeltaAst. - - - - - 868c8a78 by Fendor at 2024-04-09T08:51:50-04:00 Prefer packed representation for CompiledByteCode As there are many 'CompiledByteCode' objects alive during a GHCi session, representing its element in a more packed manner improves space behaviour at a minimal cost. When running GHCi on the agda codebase, we find around 380 live 'CompiledByteCode' objects. Packing their respective 'UnlinkedByteCode' can save quite some pointers. - - - - - be3bddde by Alan Zimmerman at 2024-04-09T08:52:26-04:00 EPA: Capture all comments in a ClassDecl Hopefully the final fix needed for #24533 - - - - - 3d0806fc by Jade at 2024-04-10T05:39:53-04:00 Validate -main-is flag using parseIdentifier Fixes #24368 - - - - - dd530bb7 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 rts: free error message before returning Fixes a memory leak in rts/linker/PEi386.c - - - - - e008a19a by Alexis King at 2024-04-10T05:40:29-04:00 linker: Avoid linear search when looking up Haskell symbols via dlsym See the primary Note [Looking up symbols in the relevant objects] for a more in-depth explanation. When dynamically loading a Haskell symbol (typical when running a splice or GHCi expression), before this commit we would search for the symbol in all dynamic libraries that were loaded. However, this could be very inefficient when too many packages are loaded (which can happen if there are many package dependencies) because the time to lookup the would be linear in the number of packages loaded. This commit drastically improves symbol loading performance by introducing a mapping from units to the handles of corresponding loaded dlls. These handles are returned by dlopen when we load a dll, and can then be used to look up in a specific dynamic library. Looking up a given Name is now much more precise because we can get lookup its unit in the mapping and lookup the symbol solely in the handles of the dynamic libraries loaded for that unit. In one measurement, the wait time before the expression was executed went from +-38 seconds down to +-2s. This commit also includes Note [Symbols may not be found in pkgs_loaded], explaining the fallback to the old behaviour in case no dll can be found in the unit mapping for a given Name. Fixes #23415 Co-authored-by: Rodrigo Mesquita (@alt-romes) - - - - - dcfaa190 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 rts: Make addDLL a wrapper around loadNativeObj Rewrite the implementation of `addDLL` as a wrapper around the more principled `loadNativeObj` rts linker function. The latter should be preferred while the former is preserved for backwards compatibility. `loadNativeObj` was previously only available on ELF platforms, so this commit further refactors the rts linker to transform loadNativeObj_ELF into loadNativeObj_POSIX, which is available in ELF and MachO platforms. The refactor made it possible to remove the `dl_mutex` mutex in favour of always using `linker_mutex` (rather than a combination of both). Lastly, we implement `loadNativeObj` for Windows too. - - - - - 12931698 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 Use symbol cache in internal interpreter too This commit makes the symbol cache that was used by the external interpreter available for the internal interpreter too. This follows from the analysis in #23415 that suggests the internal interpreter could benefit from this cache too, and that there is no good reason not to have the cache for it too. It also makes it a bit more uniform to have the symbol cache range over both the internal and external interpreter. This commit also refactors the cache into a function which is used by both `lookupSymbol` and also by `lookupSymbolInDLL`, extending the caching logic to `lookupSymbolInDLL` too. - - - - - dccd3ea1 by Ben Gamari at 2024-04-10T05:40:29-04:00 testsuite: Add test for lookupSymbolInNativeObj - - - - - 1b1a92bd by Alan Zimmerman at 2024-04-10T05:41:05-04:00 EPA: Remove unnecessary XRec in CompleteMatchSig The XRec for [LIdP pass] is not needed for exact printing, remove it. - - - - - 6e18ce2b by Ben Gamari at 2024-04-12T08:16:09-04:00 users-guide: Clarify language extension documentation Over the years the users guide's language extension documentation has gone through quite a few refactorings. In the process some of the descriptions have been rendered non-sensical. For instance, the description of `NoImplicitPrelude` actually describes the semantics of `ImplicitPrelude`. To fix this we: * ensure that all extensions are named in their "positive" sense (e.g. `ImplicitPrelude` rather than `NoImplicitPrelude`). * rework the documentation to avoid flag-oriented wording like "enable" and "disable" * ensure that the polarity of the documentation is consistent with reality. Fixes #23895. - - - - - a933aff3 by Zubin Duggal at 2024-04-12T08:16:45-04:00 driver: Make `checkHomeUnitsClosed` faster The implementation of `checkHomeUnitsClosed` was traversing every single path in the unit dependency graph - this grows exponentially and quickly grows to be infeasible on larger unit dependency graphs. Instead we replace this with a faster implementation which follows from the specificiation of the closure property - there is a closure error if there are units which are both are both (transitively) depended upon by home units and (transitively) depend on home units, but are not themselves home units. To compute the set of units required for closure, we first compute the closure of the unit dependency graph, then the transpose of this closure, and find all units that are reachable from the home units in the transpose of the closure. - - - - - 23c3e624 by Andreas Klebinger at 2024-04-12T08:17:21-04:00 RTS: Emit warning when -M < -H Fixes #24487 - - - - - d23afb8c by Ben Gamari at 2024-04-12T08:17:56-04:00 testsuite: Add broken test for CApiFFI with -fprefer-bytecode See #24634. - - - - - a4bb3a51 by Ben Gamari at 2024-04-12T08:18:32-04:00 base: Deprecate GHC.Pack As proposed in #21461. Closes #21540. - - - - - 55eb8c98 by Ben Gamari at 2024-04-12T08:19:08-04:00 ghc-internal: Fix mentions of ghc-internal in deprecation warnings Closes #24609. - - - - - b0fbd181 by Ben Gamari at 2024-04-12T08:19:44-04:00 rts: Implement set_initial_registers for AArch64 Fixes #23680. - - - - - 14c9ec62 by Ben Gamari at 2024-04-12T08:20:20-04:00 ghcup-metadata: Use Debian 9 binaries on Ubuntu 16, 17 Closes #24646. - - - - - 35a1621e by Ben Gamari at 2024-04-12T08:20:55-04:00 Bump unix submodule to 2.8.5.1 Closes #24640. - - - - - a1c24df0 by Finley McIlwaine at 2024-04-12T08:21:31-04:00 Correct default -funfolding-use-threshold in docs - - - - - 0255d03c by Oleg Grenrus at 2024-04-12T08:22:07-04:00 FastString is a __Modified__ UTF-8 - - - - - c3489547 by Matthew Pickering at 2024-04-12T13:13:44-04:00 rts: Improve tracing message when nursery is resized It is sometimes more useful to know how much bigger or smaller the nursery got when it is resized. In particular I am trying to investigate situations where we end up with fragmentation due to the nursery (#24577) - - - - - 5e4f4ba8 by Simon Peyton Jones at 2024-04-12T13:14:20-04:00 Don't generate wrappers for `type data` constructors with StrictData Previously, the logic for checking if a data constructor needs a wrapper or not would take into account whether the constructor's fields have explicit strictness (e.g., `data T = MkT !Int`), but the logic would _not_ take into account whether `StrictData` was enabled. This meant that something like `type data T = MkT Int` would incorrectly generate a wrapper for `MkT` if `StrictData` was enabled, leading to the horrible errors seen in #24620. To fix this, we disable generating wrappers for `type data` constructors altogether. Fixes #24620. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - dbdf1995 by Alex Mason at 2024-04-15T15:28:26+10:00 Implements MO_S_Mul2 and MO_U_Mul2 using the UMULH, UMULL and SMULH instructions for AArch64 Also adds a test for MO_S_Mul2 - - - - - 42bd0407 by Teo Camarasu at 2024-04-16T20:06:39-04:00 Make template-haskell a stage1 package Promoting template-haskell from a stage0 to a stage1 package means that we can much more easily refactor template-haskell. We implement this by duplicating the in-tree `template-haskell`. A new `template-haskell-next` library is autogenerated to mirror `template-haskell` `stage1:ghc` to depend on the new interface of the library including the `Binary` instances without adding an explicit dependency on `template-haskell`. This is controlled by the `bootstrap-th` cabal flag When building `template-haskell` modules as part of this vendoring we do not have access to quote syntax, so we cannot use variable quote notation (`'Just`). So we either replace these with hand-written `Name`s or hide the code behind CPP. We can remove the `th_hack` from hadrian, which was required when building stage0 packages using the in-tree `template-haskell` library. For more details see Note [Bootstrapping Template Haskell]. Resolves #23536 Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> Co-Authored-By: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org> - - - - - 3d973e47 by Ben Gamari at 2024-04-16T20:07:15-04:00 Bump parsec submodule to 3.1.17.0 - - - - - 9d38bfa0 by Simon Peyton Jones at 2024-04-16T20:07:51-04:00 Clone CoVars in CorePrep This MR addresses #24463. It's all explained in the new Note [Cloning CoVars and TyVars] - - - - - 0fe2b410 by Andreas Klebinger at 2024-04-16T20:08:27-04:00 NCG: Fix a bug where we errounously removed a required jump instruction. Add a new method to the Instruction class to check if we can eliminate a jump in favour of fallthrough control flow. Fixes #24507 - - - - - 9f99126a by Teo Camarasu at 2024-04-16T20:09:04-04:00 Fix documentation preview from doc-tarball job - Include all the .html files and assets in the job artefacts - Include all the .pdf files in the job artefacts - Mark the artefact as an "exposed" artefact meaning it turns up in the UI. Resolves #24651 - - - - - 3a0642ea by Ben Gamari at 2024-04-16T20:09:39-04:00 rts: Ignore EINTR while polling in timerfd itimer implementation While the RTS does attempt to mask signals, it may be that a foreign library unmasks them. This previously caused benign warnings which we now ignore. See #24610. - - - - - 9a53cd3f by Alan Zimmerman at 2024-04-16T20:10:15-04:00 EPA: Add additional comments field to AnnsModule This is used in exact printing to store comments coming after the `where` keyword but before any comments allocated to imports or decls. It is used in ghc-exactprint, see https://github.com/alanz/ghc-exactprint/commit/44bbed311fd8f0d053053fef195bf47c17d34fa7 - - - - - e5c43259 by Bryan Richter at 2024-04-16T20:10:51-04:00 Remove unrunnable FreeBSD CI jobs FreeBSD runner supply is inelastic. Currently there is only one, and it's unavailable because of a hardware issue. - - - - - 914eb49a by Ben Gamari at 2024-04-16T20:11:27-04:00 rel-eng: Fix mktemp usage in recompress-all We need a temporary directory, not a file. - - - - - f30e4984 by Teo Camarasu at 2024-04-16T20:12:03-04:00 Fix ghc API link in docs/index.html This was missing part of the unit ID meaning it would 404. Resolves #24674 - - - - - d7a3d6b5 by Ben Gamari at 2024-04-16T20:12:39-04:00 template-haskell: Declare TH.Lib.Internal as not-home Rather than `hide`. Closes #24659. - - - - - 5eaa46e7 by Matthew Pickering at 2024-04-19T02:14:55-04:00 testsuite: Rename isCross() predicate to needsTargetWrapper() isCross() was a misnamed because it assumed that all cross targets would provide a target wrapper, but the two most common cross targets (javascript, wasm) don't need a target wrapper. Therefore we rename this predicate to `needsTargetWrapper()` so situations in the testsuite where we can check whether running executables requires a target wrapper or not. - - - - - 55a9d699 by Simon Peyton Jones at 2024-04-19T02:15:32-04:00 Do not float HNFs out of lambdas This MR adjusts SetLevels so that it is less eager to float a HNF (lambda or constructor application) out of a lambda, unless it gets to top level. Data suggests that this change is a small net win: * nofib bytes-allocated falls by -0.09% (but a couple go up) * perf/should_compile bytes-allocated falls by -0.5% * perf/should_run bytes-allocated falls by -0.1% See !12410 for more detail. When fiddling elsewhere, I also found that this patch had a huge positive effect on the (very delicate) test perf/should_run/T21839r But that improvement doesn't show up in this MR by itself. Metric Decrease: MultiLayerModulesRecomp T15703 parsing001 - - - - - f0701585 by Alan Zimmerman at 2024-04-19T02:16:08-04:00 EPA: Fix comments in mkListSyntaxTy0 Also extend the test to confirm. Addresses #24669, 1 of 4 - - - - - b01c01d4 by Serge S. Gulin at 2024-04-19T02:16:51-04:00 JS: set image `x86_64-linux-deb11-emsdk-closure` for build - - - - - c90c6039 by Alan Zimmerman at 2024-04-19T02:17:27-04:00 EPA: Provide correct span for PatBind And remove unused parameter in checkPatBind Contributes to #24669 - - - - - bee54c24 by Krzysztof Gogolewski at 2024-04-19T11:13:00+02:00 Update quantification order following GHC haskell/haddock#23764 - - - - - 2814eb89 by Ben Gamari at 2024-04-19T18:57:05+02:00 hypsrc-test: Fix output of PositionPragmas.html - - - - - 26036f96 by Alan Zimmerman at 2024-04-19T13:11:08-04:00 EPA: Fix span for PatBuilderAppType Include the location of the prefix @ in the span for InVisPat. Also removes unnecessary annotations from HsTP. Contributes to #24669 - - - - - dba03aab by Matthew Craven at 2024-04-19T13:11:44-04:00 testsuite: Give the pre_cmd for mhu-perf more time - - - - - d31fbf6c by Krzysztof Gogolewski at 2024-04-19T21:04:09-04:00 Fix quantification order for a `op` b and a %m -> b Fixes #23764 Implements https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0640-tyop-quantification-order.rst Updates haddock submodule. - - - - - 385cd1c4 by Sebastian Graf at 2024-04-19T21:04:45-04:00 Make `seq#` a magic Id and inline it in CorePrep (#24124) We can save much code and explanation in Tag Inference and StgToCmm by making `seq#` a known-key Magic Id in `GHC.Internal.IO` and inline this definition in CorePrep. See the updated `Note [seq# magic]`. I also implemented a new `Note [Flatten case-bind]` to get better code for otherwise nested case scrutinees. I renamed the contructors of `ArgInfo` to use an `AI` prefix in order to resolve the clash between `type CpeApp = CoreExpr` and the data constructor of `ArgInfo`, as well as fixed typos in `Note [CorePrep invariants]`. Fixes #24252 and #24124. - - - - - 275e41a9 by Jade at 2024-04-20T11:10:40-04:00 Put the newline after errors instead of before them This mainly has consequences for GHCi but also slightly alters how the output of GHC on the commandline looks. Fixes: #22499 - - - - - dd339c7a by Teo Camarasu at 2024-04-20T11:11:16-04:00 Remove unecessary stage0 packages Historically quite a few packages had to be stage0 as they depended on `template-haskell` and that was stage0. In #23536 we made it so that was no longer the case. This allows us to remove a bunch of packages from this list. A few still remain. A new version of `Win32` is required by `semaphore-compat`. Including `Win32` in the stage0 set requires also including `filepath` because otherwise Hadrian's dependency logic gets confused. Once our boot compiler has a newer version of `Win32` all of these will be able to be dropped. Resolves #24652 - - - - - 2f8e3a25 by Alan Zimmerman at 2024-04-20T11:11:52-04:00 EPA: Avoid duplicated comments in splice decls Contributes to #24669 - - - - - c70b9ddb by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: fix typos and namings (fixes #24602) You may noted that I've also changed term of ``` , global "h$vt_double" ||= toJExpr IntV ``` See "IntV" and ``` WaitReadOp -> \[] [fd] -> pure $ PRPrimCall $ returnS (app "h$waidRead" [fd]) ``` See "h$waidRead" - - - - - 3db54f9b by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: trivial checks for variable presence (fixes #24602) - - - - - 777f108f by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: fs module imported twice (by emscripten and by ghc-internal). ghc-internal import wrapped in a closure to prevent conflict with emscripten (fixes #24602) Better solution is to use some JavaScript module system like AMD, CommonJS or even UMD. It will be investigated at other issues. At first glance we should try UMD (See https://github.com/umdjs/umd) - - - - - a45a5712 by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: thread.js requires h$fds and h$fdReady to be declared for static code analysis, minimal code copied from GHCJS (fixes #24602) I've just copied some old pieces of GHCJS from publicly available sources (See https://github.com/Taneb/shims/blob/a6dd0202dcdb86ad63201495b8b5d9763483eb35/src/io.js#L607). Also I didn't put details to h$fds. I took minimal and left only its object initialization: `var h$fds = {};` - - - - - ad90bf12 by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: heap and stack overflows reporting defined as js hard failure (fixes #24602) These errors were treated as a hard failure for browser application. The fix is trivial: just throw error. - - - - - 5962fa52 by Serge S. Gulin at 2024-04-21T16:33:44+03:00 JS: Stubs for code without actual implementation detected by Google Closure Compiler (fixes #24602) These errors were fixed just by introducing stubbed functions with throw for further implementation. - - - - - a0694298 by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Add externs to linker (fixes #24602) After enabling jsdoc and built-in google closure compiler types I was needed to deal with the following: 1. Define NodeJS-environment types. I've just copied minimal set of externs from semi-official repo (see https://github.com/externs/nodejs/blob/6c6882c73efcdceecf42e7ba11f1e3e5c9c041f0/v8/nodejs.js#L8). 2. Define Emscripten-environment types: `HEAP8`. Emscripten already provides some externs in our code but it supposed to be run in some module system. And its definitions do not work well in plain bundle. 3. We have some functions which purpose is to add to functions some contextual information via function properties. These functions should be marked as `modifies` to let google closure compiler remove calls if these functions are not used actually by call graph. Such functions are: `h$o`, `h$sti`, `h$init_closure`, `h$setObjInfo`. 4. STG primitives such as registries and stuff from `GHC.StgToJS`. `dXX` properties were already present at externs generator function but they are started from `7`, not from `1`. This message is related: `// fixme does closure compiler bite us here?` - - - - - e58bb29f by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: added both tests: for size and for correctness (fixes #24602) By some reason MacOS builds add to stderr messages like: Ignoring unexpected archive entry: __.SYMDEF ... However I left stderr to `/dev/null` for compatibility with linux CI builds. - - - - - 909f3a9c by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Disable js linker warning for empty symbol table to make js tests running consistent across environments - - - - - 83eb10da by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Add special preprocessor for js files due of needing to keep jsdoc comments (fixes #24602) Our js files have defined google closure compiler types at jsdoc entries but these jsdoc entries are removed by cpp preprocessor. I considered that reusing them in javascript-backend would be a nice thing. Right now haskell processor uses `-traditional` option to deal with comments and `//` operators. But now there are following compiler options: `-C` and `-CC`. You can read about them at GCC (see https://gcc.gnu.org/onlinedocs/gcc/Preprocessor-Options.html#index-CC) and CLang (see https://clang.llvm.org/docs/ClangCommandLineReference.html#cmdoption-clang-CC). It seems that `-CC` works better for javascript jsdoc than `-traditional`. At least it leaves `/* ... */` comments w/o changes. - - - - - e1cf8dc2 by brandon s allbery kf8nh at 2024-04-22T03:48:26-04:00 fix link in CODEOWNERS It seems that our local Gitlab no longer has documentation for the `CODEOWNERS` file, but the master documentation still does. Use that instead. - - - - - a27c6a49 by Fendor at 2024-04-22T10:13:03+02:00 Adapt to UserData split - - - - - 1efc5a7a by Fendor at 2024-04-22T10:13:03+02:00 Adapt to BinHandle split - - - - - 593f4e04 by Fendor at 2024-04-23T10:19:14-04:00 Add performance regression test for '-fwrite-simplified-core' - - - - - 1ba39b05 by Fendor at 2024-04-23T10:19:14-04:00 Typecheck corebindings lazily during bytecode generation This delays typechecking the corebindings until the bytecode generation happens. We also avoid allocating a thunk that is retained by `unsafeInterleaveIO`. In general, we shouldn't retain values of the hydrated `Type`, as not evaluating the bytecode object keeps it alive. It is better if we retain the unhydrated `IfaceType`. See Note [Hydrating Modules] - - - - - e916fc92 by Alan Zimmerman at 2024-04-23T10:19:50-04:00 EPA: Keep comments in a CaseAlt match The comments now live in the surrounding location, not inside the Match. Make sure we keep them. Closes #24707 - - - - - d2b17f32 by Cheng Shao at 2024-04-23T15:01:22-04:00 driver: force merge objects when building dynamic objects This patch forces the driver to always merge objects when building dynamic objects even when ar -L is supported. It is an oversight of !8887: original rationale of that patch is favoring the relatively cheap ar -L operation over object merging when ar -L is supported, which makes sense but only if we are building static objects! Omitting check for whether we are building dynamic objects will result in broken .so files with undefined reference errors at executable link time when building GHC with llvm-ar. Fixes #22210. - - - - - 209d09f5 by Julian Ospald at 2024-04-23T15:02:03-04:00 Allow non-absolute values for bootstrap GHC variable Fixes #24682 - - - - - 3fff0977 by Matthew Pickering at 2024-04-23T15:02:38-04:00 Don't depend on registerPackage function in Cabal More recent versions of Cabal modify the behaviour of libAbiHash which breaks our usage of registerPackage. It is simpler to inline the part of registerPackage that we need and avoid any additional dependency and complication using the higher-level function introduces. - - - - - c62dc317 by Cheng Shao at 2024-04-25T01:32:02-04:00 ghc-bignum: remove obsolete ln script This commit removes an obsolete ln script in ghc-bignum/gmp. See 060251c24ad160264ae8553efecbb8bed2f06360 for its original intention, but it's been obsolete for a long time, especially since the removal of the make build system. Hence the house cleaning. - - - - - 6399d52b by Cheng Shao at 2024-04-25T01:32:02-04:00 ghc-bignum: update gmp to 6.3.0 This patch bumps the gmp-tarballs submodule and updates gmp to 6.3.0. The tarball format is now xz, and gmpsrc.patch has been patched into the tarball so hadrian no longer needs to deal with patching logic when building in-tree GMP. - - - - - 65b4b92f by Cheng Shao at 2024-04-25T01:32:02-04:00 hadrian: remove obsolete Patch logic This commit removes obsolete Patch logic from hadrian, given we no longer need to patch the gmp tarball when building in-tree GMP. - - - - - 71f28958 by Cheng Shao at 2024-04-25T01:32:02-04:00 autoconf: remove obsolete patch detection This commit removes obsolete deletection logic of the patch command from autoconf scripts, given we no longer need to patch anything in the GHC build process. - - - - - daeda834 by Sylvain Henry at 2024-04-25T01:32:43-04:00 JS: correctly handle RUBBISH literals (#24664) - - - - - 8a06ddf6 by Matthew Pickering at 2024-04-25T11:16:16-04:00 Linearise ghc-internal and base build This is achieved by requesting the final package database for ghc-internal, which mandates it is fully built as a dependency of configuring the `base` package. This is at the expense of cross-package parrallelism between ghc-internal and the base package. Fixes #24436 - - - - - 94da9365 by Andrei Borzenkov at 2024-04-25T11:16:54-04:00 Fix tuple puns renaming (24702) Move tuple renaming short cutter from `isBuiltInOcc_maybe` to `isPunOcc_maybe`, so we consider incoming module. I also fixed some hidden bugs that raised after the change was done. - - - - - fa03b1fb by Fendor at 2024-04-26T18:03:13-04:00 Refactor the Binary serialisation interface The goal is simplifiy adding deduplication tables to `ModIface` interface serialisation. We identify two main points of interest that make this difficult: 1. UserData hardcodes what `Binary` instances can have deduplication tables. Moreover, it heavily uses partial functions. 2. GHC.Iface.Binary hardcodes the deduplication tables for 'Name' and 'FastString', making it difficult to add more deduplication. Instead of having a single `UserData` record with fields for all the types that can have deduplication tables, we allow to provide custom serialisers for any `Typeable`. These are wrapped in existentials and stored in a `Map` indexed by their respective `TypeRep`. The `Binary` instance of the type to deduplicate still needs to explicitly look up the decoder via `findUserDataReader` and `findUserDataWriter`, which is no worse than the status-quo. `Map` was chosen as microbenchmarks indicate it is the fastest for a small number of keys (< 10). To generalise the deduplication table serialisation mechanism, we introduce the types `ReaderTable` and `WriterTable` which provide a simple interface that is sufficient to implement a general purpose deduplication mechanism for `writeBinIface` and `readBinIface`. This allows us to provide a list of deduplication tables for serialisation that can be extended more easily, for example for `IfaceTyCon`, see the issue https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for more motivation. In addition to this refactoring, we split `UserData` into `ReaderUserData` and `WriterUserData`, to avoid partial functions and reduce overall memory usage, as we need fewer mutable variables. Bump haddock submodule to accomodate for `UserData` split. ------------------------- Metric Increase: MultiLayerModulesTH_Make MultiLayerModulesRecomp T21839c ------------------------- - - - - - bac57298 by Fendor at 2024-04-26T18:03:13-04:00 Split `BinHandle` into `ReadBinHandle` and `WriteBinHandle` A `BinHandle` contains too much information for reading data. For example, it needs to keep a `FastMutInt` and a `IORef BinData`, when the non-mutable variants would suffice. Additionally, this change has the benefit that anyone can immediately tell whether the `BinHandle` is used for reading or writing. Bump haddock submodule BinHandle split. - - - - - 4d6394dd by Simon Peyton Jones at 2024-04-26T18:03:49-04:00 Fix missing escaping-kind check in tcPatSynSig Note [Escaping kind in type signatures] explains how we deal with escaping kinds in type signatures, e.g. f :: forall r (a :: TYPE r). a where the kind of the body is (TYPE r), but `r` is not in scope outside the forall-type. I had missed this subtlety in tcPatSynSig, leading to #24686. This MR fixes it; and a similar bug in tc_top_lhs_type. (The latter is tested by T24686a.) - - - - - 981c2c2c by Alan Zimmerman at 2024-04-26T18:04:25-04:00 EPA: check-exact: check that the roundtrip reproduces the source Closes #24670 - - - - - a8616747 by Andrew Lelechenko at 2024-04-26T18:05:01-04:00 Document that setEnv is not thread-safe - - - - - 1e41de83 by Bryan Richter at 2024-04-26T18:05:37-04:00 CI: Work around frequent Signal 9 errors - - - - - a6d5f9da by Naïm Favier at 2024-04-27T17:52:40-04:00 ghc-internal: add MonadFix instance for (,) Closes https://gitlab.haskell.org/ghc/ghc/-/issues/24288, implements CLC proposal https://github.com/haskell/core-libraries-committee/issues/238. Adds a MonadFix instance for tuples, permitting value recursion in the "native" writer monad and bringing consistency with the existing instance for transformers's WriterT (and, to a lesser extent, for Solo). - - - - - 64feadcd by Rodrigo Mesquita at 2024-04-27T17:53:16-04:00 bindist: Fix xattr cleaning The original fix (725343aa) was incorrect because it used the shell bracket syntax which is the quoting syntax in autoconf, making the test for existence be incorrect and therefore `xattr` was never run. Fixes #24554 - - - - - e2094df3 by damhiya at 2024-04-28T23:52:00+09:00 Make read accepts binary integer formats CLC proposal : https://github.com/haskell/core-libraries-committee/issues/177 - - - - - c62239b7 by Sylvain Henry at 2024-04-29T10:35:00+02:00 Fix tests for T22229 - - - - - 1c2fd963 by Alan Zimmerman at 2024-04-29T23:17:00-04:00 EPA: Preserve comments in Match Pats Closes #24708 Closes #24715 Closes #24734 - - - - - 4189d17e by Sylvain Henry at 2024-04-29T23:17:42-04:00 LLVM: better unreachable default destination in Switch (#24717) See added note. Co-authored-by: Siddharth Bhat <siddu.druid at gmail.com> - - - - - a3725c88 by Cheng Shao at 2024-04-29T23:18:20-04:00 ci: enable wasm jobs for MRs with wasm label This patch enables wasm jobs for MRs with wasm label. Previously the wasm label didn't actually have any effect on the CI pipeline, and full-ci needed to be applied to run wasm jobs which was a waste of runners when working on the wasm backend, hence the fix here. - - - - - 702f7964 by Matthew Pickering at 2024-04-29T23:18:56-04:00 Make interface files and object files depend on inplace .conf file A potential fix for #24737 - - - - - 728af21e by Cheng Shao at 2024-04-30T05:30:23-04:00 utils: remove obsolete vagrant scripts Vagrantfile has long been removed in !5288. This commit further removes the obsolete vagrant scripts in the tree. - - - - - 36f2c342 by Cheng Shao at 2024-04-30T05:31:00-04:00 Update autoconf scripts Scripts taken from autoconf 948ae97ca5703224bd3eada06b7a69f40dd15a02 - - - - - ecbf22a6 by Ben Gamari at 2024-04-30T05:31:36-04:00 ghcup-metadata: Drop output_name field This is entirely redundant to the filename of the URL. There is no compelling reason to name the downloaded file differently from its source. - - - - - c56d728e by Zubin Duggal at 2024-04-30T22:45:09-04:00 testsuite: Handle exceptions in framework_fail when testdir is not initialised When `framework_fail` is called before initialising testdir, it would fail with an exception reporting the testdir not being initialised instead of the actual failure. Ensure we report the actual reason for the failure instead of failing in this way. One way this can manifest is when trying to run a test that doesn't exist using `--only` - - - - - d5bea4d6 by Alan Zimmerman at 2024-04-30T22:45:45-04:00 EPA: Fix range for GADT decl with sig only Closes #24714 - - - - - 4d78c53c by Sylvain Henry at 2024-05-01T17:23:06-04:00 Fix TH dependencies (#22229) Add a dependency between Syntax and Internal (via module reexport). - - - - - 37e38db4 by Sylvain Henry at 2024-05-01T17:23:06-04:00 Bump haddock submodule - - - - - ca13075c by Sylvain Henry at 2024-05-01T17:23:47-04:00 JS: cleanup to prepare for #24743 - - - - - 40026ac3 by Alan Zimmerman at 2024-05-01T22:45:07-04:00 EPA: Preserve comments for PrefixCon Preserve comments in fun (Con {- c1 -} a b) = undefined Closes #24736 - - - - - 92134789 by Hécate Moonlight at 2024-05-01T22:45:42-04:00 Correct `@since` metadata in HpcFlags It was introduced in base-4.20, not 4.22. Fix #24721 - - - - - a580722e by Cheng Shao at 2024-05-02T08:18:45-04:00 testsuite: fix req_target_smp predicate - - - - - ac9c5f84 by Andreas Klebinger at 2024-05-02T08:18:45-04:00 STM: Remove (unused)coarse grained locking. The STM code had a coarse grained locking mode guarded by #defines that was unused. This commit removes the code. - - - - - 917ef81b by Andreas Klebinger at 2024-05-02T08:18:45-04:00 STM: Be more optimistic when validating in-flight transactions. * Don't lock tvars when performing non-committal validation. * If we encounter a locked tvar don't consider it a failure. This means in-flight validation will only fail if committing at the moment of validation is *guaranteed* to fail. This prevents in-flight validation from failing spuriously if it happens in parallel on multiple threads or parallel to thread comitting. - - - - - 167a56a0 by Alan Zimmerman at 2024-05-02T08:19:22-04:00 EPA: fix span for empty \case(s) In instance SDecide Nat where SZero %~ (SSucc _) = Disproved (\case) Ensure the span for the HsLam covers the full construct. Closes #24748 - - - - - 9bae34d8 by doyougnu at 2024-05-02T15:41:08-04:00 testsuite: expand size testing infrastructure - closes #24191 - adds windows_skip, wasm_skip, wasm_arch, find_so, _find_so - path_from_ghcPkg, collect_size_ghc_pkg, collect_object_size, find_non_inplace functions to testsuite - adds on_windows and req_dynamic_ghc predicate to testsuite The design is to not make the testsuite too smart and simply offload to ghc-pkg for locations of object files and directories. - - - - - b85b1199 by Sylvain Henry at 2024-05-02T15:41:49-04:00 GHCi: support inlining breakpoints (#24712) When a breakpoint is inlined, its context may change (e.g. tyvars in scope). We must take this into account and not used the breakpoint tick index as its sole identifier. Each instance of a breakpoint (even with the same tick index) now gets a different "info" index. We also need to distinguish modules: - tick module: module with the break array (tick counters, status, etc.) - info module: module having the CgBreakInfo (info at occurrence site) - - - - - 649c24b9 by Oleg Grenrus at 2024-05-03T20:45:42-04:00 Expose constructors of SNat, SChar and SSymbol in ghc-internal - - - - - d603f199 by Mikolaj Konarski at 2024-05-03T20:46:19-04:00 Add DCoVarSet to PluginProv (!12037) - - - - - ba480026 by Serge S. Gulin at 2024-05-03T20:47:01-04:00 JS: Enable more efficient packing of string data (fixes #24706) - - - - - be1e60ee by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Track in-scope variables in ruleCheckProgram This small patch fixes #24726, by tracking in-scope variables properly in -drule-check. Not hard to do! - - - - - 58408c77 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Add a couple more HasCallStack constraints in SimpleOpt Just for debugging, no effect on normal code - - - - - 70e245e8 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Add comments to Prep.hs This documentation patch fixes a TODO left over from !12364 - - - - - e5687186 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Use HasDebugCallStack, rather than HasCallStack - - - - - 631cefec by Cheng Shao at 2024-05-03T20:48:17-04:00 driver: always merge objects when possible This patch makes the driver always merge objects with `ld -r` when possible, and only fall back to calling `ar -L` when merge objects command is unavailable. This completely reverts !8887 and !12313, given more fixes in Cabal seems to be needed to avoid breaking certain configurations and the maintainence cost is exceeding the behefits in this case :/ - - - - - 1dacb506 by Ben Gamari at 2024-05-03T20:48:53-04:00 Bump time submodule to 1.14 As requested in #24528. ------------------------- Metric Decrease: ghc_bignum_so rts_so Metric Increase: cabal_syntax_dir rts_so time_dir time_so ------------------------- - - - - - 4941b90e by Ben Gamari at 2024-05-03T20:48:53-04:00 Bump terminfo submodule to current master - - - - - 43d48b44 by Cheng Shao at 2024-05-03T20:49:30-04:00 wasm: use scheduler.postTask() for context switch when available This patch makes use of scheduler.postTask() for JSFFI context switch when it's available. It's a more principled approach than our MessageChannel based setImmediate() implementation, and it's available in latest version of Chromium based browsers. - - - - - 08207501 by Cheng Shao at 2024-05-03T20:50:08-04:00 testsuite: give pre_cmd for mhu-perf 5x time - - - - - bf3d4db0 by Alan Zimmerman at 2024-05-03T20:50:43-04:00 EPA: Preserve comments for pattern synonym sig Closes #24749 - - - - - c49493f2 by Matthew Pickering at 2024-05-04T06:02:57-04:00 tests: Widen acceptance window for dir and so size tests These are testing things which are sometimes out the control of a GHC developer. Therefore we shouldn't fail CI if something about these dependencies change because we can't do anything about it. It is still useful to have these statistics for visualisation in grafana though. Ticket #24759 - - - - - 9562808d by Matthew Pickering at 2024-05-04T06:02:57-04:00 Disable rts_so test It has already manifested large fluctuations and destabilising CI Fixes #24762 - - - - - fc24c5cf by Ryan Scott at 2024-05-04T06:03:33-04:00 unboxedSum{Type,Data}Name: Use GHC.Types as the module Unboxed sum constructors are now defined in the `GHC.Types` module, so if you manually quote an unboxed sum (e.g., `''Sum2#`), you will get a `Name` like: ```hs GHC.Types.Sum2# ``` The `unboxedSumTypeName` function in `template-haskell`, however, mistakenly believes that unboxed sum constructors are defined in `GHC.Prim`, so `unboxedSumTypeName 2` would return an entirely different `Name`: ```hs GHC.Prim.(#|#) ``` This is a problem for Template Haskell users, as it means that they can't be sure which `Name` is the correct one. (Similarly for `unboxedSumDataName`.) This patch fixes the implementations of `unboxedSum{Type,Data}Name` to use `GHC.Types` as the module. For consistency with `unboxedTupleTypeName`, the `unboxedSumTypeName` function now uses the non-punned syntax for unboxed sums (`Sum<N>#`) as the `OccName`. Fixes #24750. - - - - - 7eab4e01 by Alan Zimmerman at 2024-05-04T16:14:55+01:00 EPA: Widen stmtslist to include last semicolon Closes #24754 - - - - - 06f7db40 by Teo Camarasu at 2024-05-05T00:19:38-04:00 doc: Fix type error in hs_try_putmvar example - - - - - af000532 by Moritz Schuler at 2024-05-05T06:30:58-04:00 Fix parsing of module names in CLI arguments closes issue #24732 - - - - - da74e9c9 by Ben Gamari at 2024-05-05T06:31:34-04:00 ghc-platform: Add Setup.hs The Hadrian bootstrapping script relies upon `Setup.hs` to drive its build. Addresses #24761. - - - - - 35d34fde by Alan Zimmerman at 2024-05-05T12:52:40-04:00 EPA: preserve comments in class and data decls Fix checkTyClHdr which was discarding comments. Closes #24755 - - - - - 03c5dfbf by Simon Peyton Jones at 2024-05-05T12:53:15-04:00 Fix a float-out error Ticket #24768 showed that the Simplifier was accidentally destroying a join point. It turned out to be that we were sending a bottoming join point to the top, accidentally abstracting over /other/ join points. Easily fixed. - - - - - adba68e7 by John Ericson at 2024-05-05T19:35:56-04:00 Substitute bindist files with Hadrian not configure The `ghc-toolchain` overhaul will eventually replace all this stuff with something much more cleaned up, but I think it is still worth making this sort of cleanup in the meantime so other untanglings and dead code cleaning can procede. I was able to delete a fair amount of dead code doing this too. `LLVMTarget_CPP` is renamed to / merged with `LLVMTarget` because it wasn't actually turned into a valid CPP identifier. (Original to 1345c7cc42c45e63ab1726a8fd24a7e4d4222467, actually.) Progress on #23966 Co-Authored-By: Sylvain Henry <hsyl20 at gmail.com> - - - - - 18f4ff84 by Alan Zimmerman at 2024-05-05T19:36:32-04:00 EPA: fix mkHsOpTyPV duplicating comments Closes #24753 - - - - - a19201d4 by Matthew Craven at 2024-05-06T19:54:29-04:00 Add test cases for #24664 ...since none are present in the original MR !12463 fixing this issue. - - - - - 46328a49 by Alan Zimmerman at 2024-05-06T19:55:05-04:00 EPA: preserve comments in data decls Closes #24771 - - - - - 3b51995c by Andrei Borzenkov at 2024-05-07T14:39:40-04:00 Rename Solo# data constructor to MkSolo# (#24673) - data Solo# a = (# a #) + data Solo# a = MkSolo# a And `(# foo #)` syntax now becomes just a syntactic sugar for `MkSolo# a`. - - - - - 4d59abf2 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Add the cmm_cpp_is_gcc predicate to the testsuite A future C-- test called T24474-cmm-override-g0 relies on the GCC-specific behaviour of -g3 implying -dD, which, in turn, leads to it emitting #defines past the preprocessing stage. Clang, at least, does not do this, so the test would fail if ran on Clang. As the behaviour here being tested is ``-optCmmP-g3'' undoing effects of the workaround we apply as a fix for bug #24474, and the workaround was for GCC-specific behaviour, the test needs to be marked as fragile on other compilers. - - - - - 25b0b404 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Split out the C-- preprocessor, and make it pass -g0 Previously, C-- was processed with the C preprocessor program. This means that it inherited flags passed via -optc. A flag that is somewhat often passed through -optc is -g. At certain -g levels (>=2), GCC starts emitting defines *after* preprocessing, for the purposes of debug info generation. This is not useful for the C-- compiler, and, in fact, causes lexer errors. We can suppress this effect (safely, if supported) via -g0. As a workaround, in older versions of GCC (<=10), GCC only emitted defines if a certain set of -g*3 flags was passed. Newer versions check the debug level. For the former, we filter out those -g*3 flags and, for the latter, we specify -g0 on top of that. As a compatible and effective solution, this change adds a C-- preprocessor distinct from the C compiler and preprocessor, but that keeps its flags. The command line produced for C-- preprocessing now looks like: $pgmCmmP $optCs_without_g3 $g0_if_supported $optCmmP Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/24474 - - - - - 9b4129a5 by Andreas Klebinger at 2024-05-08T13:24:20-04:00 -fprof-late: Only insert cost centres on functions/non-workfree cafs. They are usually useless and doing so for data values comes with a large compile time/code size overhead. Fixes #24103 - - - - - 259b63d3 by Sebastian Graf at 2024-05-08T13:24:57-04:00 Simplifier: Preserve OccInfo on DataAlt fields when case binder is dead (#24770) See the adjusted `Note [DataAlt occ info]`. This change also has a positive repercussion on `Note [Combine case alts: awkward corner]`. Fixes #24770. We now try not to call `dataConRepStrictness` in `adjustFieldsIdInfo` when all fields are lazy anyway, leading to a 2% ghc/alloc decrease in T9675. Metric Decrease: T9675 - - - - - 31b28cdb by Sebastian Graf at 2024-05-08T13:24:57-04:00 Kill seqRule, discard dead seq# in Prep (#24334) Discarding seq#s in Core land via `seqRule` was problematic; see #24334. So instead we discard certain dead, discardable seq#s in Prep now. See the updated `Note [seq# magic]`. This fixes the symptoms of #24334. - - - - - b2682534 by Rodrigo Mesquita at 2024-05-10T01:47:51-04:00 Document NcgImpl methods Fixes #19914 - - - - - 4d3acbcf by Zejun Wu at 2024-05-10T01:48:28-04:00 Make renamer to be more flexible with parens in the LHS of the rules We used to reject LHS like `(f a) b` in RULES and requires it to be written as `f a b`. It will be handy to allow both as the expression may be more readable with extra parens in some cases when infix operator is involved. Espceially when TemplateHaskell is used, extra parens may be added out of user's control and result in "valid" rules being rejected and there are not always ways to workaround it. Fixes #24621 - - - - - ab840ce6 by Ben Gamari at 2024-05-10T01:49:04-04:00 IPE: Eliminate dependency on Read Instead of encoding the closure type as decimal string we now simply represent it as an integer, eliminating the need for `Read` in `GHC.Internal.InfoProv.Types.peekInfoProv`. Closes #24504. ------------------------- Metric Decrease: T24602_perf_size size_hello_artifact ------------------------- - - - - - a9979f55 by Cheng Shao at 2024-05-10T01:49:43-04:00 testsuite: fix testwsdeque with recent clang This patch fixes compilation of testwsdeque.c with recent versions of clang, which will fail with the error below: ``` testwsdeque.c:95:33: error: warning: format specifies type 'long' but the argument has type 'void *' [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~~ ^ testwsdeque.c:95:39: error: warning: format specifies type 'int' but the argument has type 'StgWord' (aka 'unsigned long') [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~ ^~~ | %lu testwsdeque.c:133:42: error: error: incompatible function pointer types passing 'void (void *)' to parameter of type 'OSThreadProc *' (aka 'void *(*)(void *)') [-Wincompatible-function-pointer-types] 133 | createOSThread(&ids[n], "thief", thief, (void*)(StgWord)n); | ^~~~~ /workspace/ghc/_build/stage1/lib/../lib/x86_64-linux-ghc-9.11.20240502/rts-1.0.2/include/rts/OSThreads.h:193:51: error: note: passing argument to parameter 'startProc' here 193 | OSThreadProc *startProc, void *param); | ^ 2 warnings and 1 error generated. ``` - - - - - c2b33fc9 by Rodrigo Mesquita at 2024-05-10T01:50:20-04:00 Rename pre-processor invocation args Small clean up. Uses proper names for the various groups of arguments that make up the pre-processor invocation. - - - - - 2b1af08b by Cheng Shao at 2024-05-10T01:50:55-04:00 ghc-heap: fix typo in ghc-heap cbits - - - - - fc2d6de1 by Jade at 2024-05-10T21:07:16-04:00 Improve performance of Data.List.sort(By) This patch improves the algorithm to sort lists in base. It does so using two strategies: 1) Use a four-way-merge instead of the 'default' two-way-merge. This is able to save comparisons and allocations. 2) Use `(>) a b` over `compare a b == GT` and allow inlining and specialization. This mainly benefits types with a fast (>). Note that this *may* break instances with a *malformed* Ord instance where `a > b` is *not* equal to `compare a b == GT`. CLC proposal: https://github.com/haskell/core-libraries-committee/issues/236 Fixes #24280 ------------------------- Metric Decrease: MultiLayerModulesTH_Make T10421 T13719 T15164 T18698a T18698b T1969 T9872a T9961 T18730 WWRec T12425 T15703 ------------------------- - - - - - 1012e8aa by Matthew Pickering at 2024-05-10T21:07:52-04:00 Revert "ghcup-metadata: Drop output_name field" This reverts commit ecbf22a6ac397a791204590f94c0afa82e29e79f. This breaks the ghcup metadata generation on the nightly jobs. - - - - - daff1e30 by Jannis at 2024-05-12T13:38:35-04:00 Division by constants optimization - - - - - 413217ba by Andreas Klebinger at 2024-05-12T13:39:11-04:00 Tidy: Add flag to expose unfoldings if they take dictionary arguments. Add the flag `-fexpose-overloaded-unfoldings` to be able to control this behaviour. For ghc's boot libraries file size grew by less than 1% when it was enabled. However I refrained from enabling it by default for now. I've also added a section on specialization more broadly to the users guide. ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot Metric Increase: T12425 T13386 hard_hole_fits ------------------------- - - - - - c5d89412 by Zubin Duggal at 2024-05-13T22:19:53-04:00 Don't store a GlobalRdrEnv in `mi_globals` for GHCi. GHCi only needs the `mi_globals` field for modules imported with :module +*SomeModule. It uses this field to make the top level environment in `SomeModule` available to the repl. By default, only the first target in the command line parameters is "star" loaded into GHCi. Other modules have to be manually "star" loaded into the repl. Storing the top level GlobalRdrEnv for each module is very wasteful, especially given that we will most likely never need most of these environments. Instead we store only the information needed to reconstruct the top level environment in a module, which is the `IfaceTopEnv` data structure, consisting of all import statements as well as all top level symbols defined in the module (not taking export lists into account) When a particular module is "star-loaded" into GHCi (as the first commandline target, or via an explicit `:module +*SomeModule`, we reconstruct the top level environment on demand using the `IfaceTopEnv`. - - - - - d65bf4a2 by Fendor at 2024-05-13T22:20:30-04:00 Add perf regression test for `-fwrite-if-simplified-core` - - - - - 2c0f8ddb by Andrei Borzenkov at 2024-05-13T22:21:07-04:00 Improve pattern to type pattern transformation (23739) `pat_to_type_pat` function now can handle more patterns: - TuplePat - ListPat - LitPat - NPat - ConPat Allowing these new constructors in type patterns significantly increases possible shapes of type patterns without `type` keyword. This patch also changes how lookups in `lookupOccRnConstr` are performed, because we need to fall back into types when we didn't find a constructor on data level to perform `ConPat` to type transformation properly. - - - - - be514bb4 by Cheng Shao at 2024-05-13T22:21:43-04:00 hadrian: fix hadrian building with ghc-9.10.1 - - - - - ad38e954 by Cheng Shao at 2024-05-13T22:21:43-04:00 linters: fix lint-whitespace compilation with ghc-9.10.1 - - - - - a593f284 by Andreas Klebinger at 2024-05-15T07:32:10-04:00 Expand the `inline` rule to look through casts/ticks. Fixes #24808 - - - - - b1e0c313 by Cheng Shao at 2024-05-15T07:32:46-04:00 testsuite: bump PartialDownSweep timeout to 5x on wasm32 - - - - - b2227487 by Fendor at 2024-05-15T17:14:06-04:00 Add Eq and Ord instance to `IfaceType` We add an `Ord` instance so that we can store `IfaceType` in a `Data.Map` container. This is required to deduplicate `IfaceType` while writing `.hi` files to disk. Deduplication has many beneficial consequences to both file size and memory usage, as the deduplication enables implicit sharing of values. See issue #24540 for more motivation. The `Ord` instance would be unnecessary if we used a `TrieMap` instead of `Data.Map` for the deduplication process. While in theory this is clerarly the better option, experiments on the agda code base showed that a `TrieMap` implementation has worse run-time performance characteristics. To the change itself, we mostly derive `Eq` and `Ord`. This requires us to change occurrences of `FastString` with `LexicalFastString`, since `FastString` has no `Ord` instance. We change the definition of `IfLclName` to a newtype of `LexicalFastString`, to make such changes in the future easier. Bump haddock submodule for IfLclName changes - - - - - d368f9a6 by Fendor at 2024-05-15T17:14:06-04:00 Move out LiteralMap to avoid cyclic module dependencies - - - - - 2fcc09fd by Fendor at 2024-05-15T17:14:06-04:00 Add deduplication table for `IfaceType` The type `IfaceType` is a highly redundant, tree-like data structure. While benchmarking, we realised that the high redundancy of `IfaceType` causes high memory consumption in GHCi sessions when byte code is embedded into the `.hi` file via `-fwrite-if-simplified-core` or `-fbyte-code-and-object-code`. Loading such `.hi` files from disk introduces many duplicates of memory expensive values in `IfaceType`, such as `IfaceTyCon`, `IfaceTyConApp`, `IA_Arg` and many more. We improve the memory behaviour of GHCi by adding an additional deduplication table for `IfaceType` to the serialisation of `ModIface`, similar to how we deduplicate `Name`s and `FastString`s. When reading the interface file back, the table allows us to automatically share identical values of `IfaceType`. To provide some numbers, we evaluated this patch on the agda code base. We loaded the full library from the `.hi` files, which contained the embedded core expressions (`-fwrite-if-simplified-core`). Before this patch: * Load time: 11.7 s, 2.5 GB maximum residency. After this patch: * Load time: 7.3 s, 1.7 GB maximum residency. This deduplication has the beneficial side effect to additionally reduce the size of the on-disk interface files tremendously. For example, on agda, we reduce the size of `.hi` files (with `-fwrite-if-simplified-core`): * Before: 101 MB on disk * Now: 24 MB on disk This has even a beneficial side effect on the cabal store. We reduce the size of the store on disk: * Before: 341 MB on disk * Now: 310 MB on disk Note, none of the dependencies have been compiled with `-fwrite-if-simplified-core`, but `IfaceType` occurs in multiple locations in a `ModIface`. We also add IfaceType deduplication table to .hie serialisation and refactor .hie file serialisation to use the same infrastrucutre as `putWithTables`. Bump haddock submodule to accomodate for changes to the deduplication table layout and binary interface. - - - - - 36aa7cf1 by Fendor at 2024-05-15T17:14:06-04:00 Add run-time configurability of `.hi` file compression Introduce the flag `-fwrite-if-compression=<n>` which allows to configure the compression level of writing .hi files. The motivation is that some deduplication operations are too expensive for the average use case. Hence, we introduce multiple compression levels with variable impact on performance, but still reduce the memory residency and `.hi` file size on disk considerably. We introduce three compression levels: * `1`: `Normal` mode. This is the least amount of compression. It deduplicates only `Name` and `FastString`s, and is naturally the fastest compression mode. * `2`: `Safe` mode. It has a noticeable impact on .hi file size and is marginally slower than `Normal` mode. In general, it should be safe to always use `Safe` mode. * `3`: `Full` deduplication mode. Deduplicate as much as we can, resulting in minimal .hi files, but at the cost of additional compilation time. Reading .hi files doesn't need to know the initial compression level, and can always deserialise a `ModIface`, as we write out a byte that indicates the next value has been deduplicated. This allows users to experiment with different compression levels for packages, without recompilation of dependencies. Note, the deduplication also has an additional side effect of reduced memory consumption to implicit sharing of deduplicated elements. See https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for example where that matters. ------------------------- Metric Decrease: MultiLayerModulesDefsGhciWithCore T16875 T21839c T24471 hard_hole_fits libdir ------------------------- - - - - - 1e63a6fb by Matthew Pickering at 2024-05-15T17:14:07-04:00 Introduce regression tests for `.hi` file sizes Add regression tests to track how `-fwrite-if-compression` levels affect the size of `.hi` files. - - - - - 639d742b by M Farkas-Dyck at 2024-05-15T17:14:49-04:00 TTG: ApplicativeStatement exist only in Rn and Tc Co-Authored-By: romes <rodrigo.m.mesquita at gmail.com> - - - - - aa7b336b by Jade at 2024-05-15T23:06:17-04:00 Documentation: Improve documentation for symbols exported from System.IO - - - - - c561de8f by Jade at 2024-05-15T23:06:54-04:00 Improve suggestions for language extensions - When suggesting Language extensions, also suggest Extensions which imply them - Suggest ExplicitForAll and GADTSyntax instead of more specific extensions - Rephrase suggestion to include the term 'Extension' - Also moves some flag specific definitions out of Session.hs into Flags.hs (#24478) Fixes: #24477 Fixes: #24448 Fixes: #10893 - - - - - 4c7ae2a1 by Andreas Klebinger at 2024-05-15T23:07:30-04:00 Testsuite: Check if llvm assembler is available for have_llvm - - - - - bc672166 by Torsten Schmits at 2024-05-15T23:08:06-04:00 refactor quadratic search in warnMissingHomeModules - - - - - 7875e8cb by Torsten Schmits at 2024-05-15T23:08:06-04:00 add test that runs MakeDepend on thousands of modules - - - - - b84b91f5 by Adam Gundry at 2024-05-16T15:32:06-04:00 Representation-polymorphic HasField (fixes #22156) This generalises the HasField class to support representation polymorphism, so that instead of type HasField :: forall {k} . k -> Type -> Type -> Constraint we have type HasField :: forall {k} {r_rep} {a_rep} . k -> TYPE r_rep -> TYPE a_rep -> Constraint - - - - - 05285090 by Matthew Pickering at 2024-05-16T15:32:43-04:00 Bump os-string submodule to 2.0.2.2 Closes #24786 - - - - - 886ab43a by Cheng Shao at 2024-05-17T01:34:50-04:00 rts: do not prefetch mark_closure bdescr in non-moving gc when ASSERTS_ENABLED This commit fixes a small an oversight in !12148: the prefetch logic in non-moving GC may trap in debug RTS because it calls Bdescr() for mark_closure which may be a static one. It's fine in non-debug RTS because even invalid bdescr addresses are prefetched, they will not cause segfaults, so this commit implements the most straightforward fix: don't prefetch mark_closure bdescr when assertions are enabled. - - - - - b38dcf39 by Teo Camarasu at 2024-05-17T01:34:50-04:00 rts: Allocate non-moving segments with megablocks Non-moving segments are 8 blocks long and need to be aligned. Previously we serviced allocations by grabbing 15 blocks, finding an aligned 8 block group in it and returning the rest. This proved to lead to high levels of fragmentation as a de-allocating a segment caused an 8 block gap to form, and this could not be reused for allocation. This patch introduces a segment allocator based around using entire megablocks to service segment allocations in bulk. When there are no free segments, we grab an entire megablock and fill it with aligned segments. As the megablock is free, we can easily guarantee alignment. Any unused segments are placed on a free list. It only makes sense to free segments in bulk when all of the segments in a megablock are freeable. After sweeping, we grab the free list, sort it, and find all groups of segments where they cover the megablock and free them. This introduces a period of time when free segments are not available to the mutator, but the risk that this would lead to excessive allocation is low. Right after sweep, we should have an abundance of partially full segments, and this pruning step is relatively quick. In implementing this we drop the logic that kept NONMOVING_MAX_FREE segments on the free list. We also introduce an eventlog event to log the amount of pruned/retained free segments. See Note [Segment allocation strategy] Resolves #24150 ------------------------- Metric Decrease: T13253 T19695 ------------------------- - - - - - 710665bd by Cheng Shao at 2024-05-17T01:35:30-04:00 rts: fix I/O manager compilation errors for win32 target This patch fixes I/O manager compilation errors for win32 target discovered when cross-compiling to win32 using recent clang: ``` rts/win32/ThrIOManager.c:117:7: error: error: call to undeclared function 'is_io_mng_native_p'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 117 | if (is_io_mng_native_p ()) { | ^ | 117 | if (is_io_mng_native_p ()) { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/fs.c:143:28: error: error: a function declaration without a prototype is deprecated in all versions of C [-Werror,-Wstrict-prototypes] 143 | int setErrNoFromWin32Error () { | ^ | void | 143 | int setErrNoFromWin32Error () { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:227:9: error: error: call to undeclared function 'interruptIOManagerEvent'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 227 | interruptIOManagerEvent (); | ^ | 227 | interruptIOManagerEvent (); | ^ rts/win32/ConsoleHandler.c:227:9: error: note: did you mean 'getIOManagerEvent'? | 227 | interruptIOManagerEvent (); | ^ rts/include/rts/IOInterface.h:27:10: error: note: 'getIOManagerEvent' declared here 27 | void * getIOManagerEvent (void); | ^ | 27 | void * getIOManagerEvent (void); | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:196:9: error: error: call to undeclared function 'setThreadLabel'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/win32/ConsoleHandler.c:196:9: error: note: did you mean 'postThreadLabel'? | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/eventlog/EventLog.h:118:6: error: note: 'postThreadLabel' declared here 118 | void postThreadLabel(Capability *cap, | ^ | 118 | void postThreadLabel(Capability *cap, | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) ``` - - - - - 28b9cee0 by Rodrigo Mesquita at 2024-05-17T01:36:05-04:00 configure: Check C99-compat for Cmm preprocessor Fixes #24815 - - - - - 8927e0c3 by Andreas Klebinger at 2024-05-17T01:36:41-04:00 Ensure `tcHasFixedRuntimeRep (# #)` returns True. - - - - - 04179044 by doyougnu at 2024-05-17T09:00:32-04:00 testsuite: make find_so regex less general Closes #24759 Background. In MR !12372 we began tracking shared object files and directories sizes for dependencies. However, this broke release builds because release builds alter the filenames swapping "in-place" for a hash. This was not considered in the MR and thus broke release pipelines. Furthermore, the rts_so test was found to be wildly varying and was therefore disabled in !12561. This commit fixes both of these issues: - fix the rts_so test by making the regex less general, now the rts_so test and all other foo.so tests must match "libHS<some-lib>-<version>-<hash|'in-place>-<ghc>". This prevents the rts_so test from accidentally matching different rts variants such as rts_threaded, which was the cause of the wild swings after !12372. - add logic to match either a hash or the string in-place. This should make the find_so function build agnostic. - - - - - 0962b50d by Andreas Klebinger at 2024-05-17T09:01:08-04:00 TagAnalysis: Treat all bottom ids as tagged during analysis. Ticket #24806 showed that we also need to treat dead end thunks as tagged during the analysis. - - - - - 7eb9f184 by Ben Gamari at 2024-05-17T11:23:37-04:00 Remove haddock submodule In preparation for merge into the GHC, as proposed in #23178. - - - - - 47b14dcc by Fendor at 2024-05-17T11:28:17-04:00 Adapt to `IfLclName` newtype changes (cherry picked from commit a711607e29b925f3d69e27c5fde4ba655c711ff1) - - - - - 6cc6681d by Fendor at 2024-05-17T11:28:17-04:00 Add IfaceType deduplication table to interface file serialisation Although we do not really need it in the interface file serialisation, as the deserialisation uses `getWithUserData`, we need to mirror the structure `getWithUserData` expects. Thus, we write essentially an empty `IfaceType` table at the end of the file, as the interface file doesn't reference `IfaceType`. (cherry picked from commit c9bc29c6a708483d2abc3d8ec9262510ce87ca61) - - - - - b9721206 by Ben Gamari at 2024-05-17T11:30:22-04:00 ghc-tags.yaml: Initial commit - - - - - 074e7d8f by Ben Gamari at 2024-05-17T11:31:29-04:00 fourmolu: Add configuration - - - - - 151b1736 by Ben Gamari at 2024-05-17T11:32:52-04:00 Makefile: Rework for use by haddock developers Previously the Makefile was present only for GHC's old make-based build system. Now since the make-based build system is gone we can use it for more useful ends. - - - - - a7dcf13b by Ben Gamari at 2024-05-17T11:36:14-04:00 Reformat with fourmolu Using previously-added configuration and `fourmolu -i .` Note that we exclude the test-cases (`./{hoogle,html-hypsrc,latex}-test`) as they are sensitive to formatting. - - - - - 0ea6017b by Ben Gamari at 2024-05-17T11:40:04-04:00 Add 'utils/haddock/' from commit 'a7dcf13bfbb97b20e75cc8ce650e2bb628db4660' git-subtree-dir: utils/haddock git-subtree-mainline: 7eb9f1849b1c72a1c61dee88462b4244550406f3 git-subtree-split: a7dcf13bfbb97b20e75cc8ce650e2bb628db4660 - - - - - aba1d304 by Hécate Moonlight at 2024-05-17T11:40:48-04:00 Add exceptions to the dangling notes list - - - - - 527bfbfb by Hécate Moonlight at 2024-05-17T11:40:52-04:00 Add haddock to the whitespace lint ignore list - - - - - 43274677 by Ben Gamari at 2024-05-17T11:41:20-04:00 git-blame-ignore-revs: Ignore haddock reformatting - - - - - 0e679e37 by Fendor at 2024-05-18T00:27:24-04:00 Pass cpp options to the CC builder in hadrian - - - - - bb40244e by Sylvain Henry at 2024-05-18T00:28:06-04:00 JS: fix allocation constant (fix #24746) - - - - - 646d30ab by Jade at 2024-05-18T19:23:31+02:00 Add highlighting for inline-code snippets in haddock - - - - - 64459a3e by Hécate Moonlight at 2024-05-19T08:42:27-04:00 haddock: Add a .readthedocs.yml file for online documentation - - - - - 7d3d9bbf by Serge S. Gulin at 2024-05-19T18:47:05+00:00 Unicode: General Category size test (related #24789) Added trivial size performance test which involves unicode general category usage via `read`. The `read` itself uses general category to detect spaces. The purpose for this test is to measure outcome of applying improvements at General Category representation in code discussed at #24789. - - - - - 8e04efcf by Alan Zimmerman at 2024-05-19T21:29:34-04:00 EPA: Remove redundant code Remove unused epAnnAnns function various cases for showAstData that no longer exist - - - - - 071d7a1e by Rodrigo Mesquita at 2024-05-20T10:55:16-04:00 Improve docs on closed type families in hs-boots Fixes #24776 - - - - - d9e2c119 by Torsten Schmits at 2024-05-20T10:55:52-04:00 Use default deviation for large-project test This new performance test has the purpose of detecting regressions in complexity in relation to the number of modules in a project, so 1% deviation is way too small to avoid false positives. - - - - - 20b0136a by Ben Gamari at 2024-05-22T00:31:39-04:00 ghcup-metadata: Various fixes from 9.10.1 Use Debian 12/x86-64, Debian 10/aarch64, and Debian 11/aarch64 bindists where possible. - - - - - 6838a7c3 by Sylvain Henry at 2024-05-22T00:32:23-04:00 Reverse arguments to stgCallocBytes (fix #24828) - - - - - f50f46c3 by Fendor at 2024-05-22T00:32:59-04:00 Add log messages for Iface serialisation compression level Fix the label of the number of 'IfaceType' entries in the log message. Add log message for the compression level that is used to serialise a an interface file. Adds `Outputable` instance for 'CompressionIFace'. - - - - - 3bad5d55 by Hécate Moonlight at 2024-05-22T00:33:40-04:00 base: Update doctests outputs ghc-internal: Update doctests outputs - - - - - 9317c6fb by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix the testsuites of the haddock-library - Apply all the metadata revisions from Hackage to the cabal file. - Fix the `ParserSpec.hs` file in the `spec` testsuite of haddock-library. - Make `CHANGES.md` an extra-doc-file instead of an extra-source-file. - - - - - 54073b02 by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix parser of @since pragma The testsuite contained tests for annotations of the form `@since foo-bar-0.5.0`, but the parser was written incorrectly. - - - - - ede6ede3 by Matthew Pickering at 2024-05-22T00:34:57-04:00 Fix nightly pages job It seems likely broken by 9f99126a which moved `index.html` from the root folder into `docs/` folder. Fixes #24840 - - - - - b7bcf729 by Cheng Shao at 2024-05-22T00:35:32-04:00 autoconf: remove unused context diff check This patch removes redundant autoconf check for the context diff program given it isn't actually been used anywhere, especially since make removal. - - - - - ea2fe66e by Hécate Moonlight at 2024-05-22T00:36:13-04:00 haddock: Rework the contributing guide - - - - - 0f302a94 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 haddock: Add module relationships diagrams of haddock-api and haddock-library - - - - - d1a9f34f by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add instructions - - - - - b880ee80 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add SVG outputs - - - - - 6d7e6ad8 by Ben Gamari at 2024-05-22T13:40:05-04:00 rts: Fix size of StgOrigThunkInfo frames Previously the entry code of the `stg_orig_thunk` frame failed to account for the size of the profiling header as it hard-coded the frame size. Fix this. Fixes #24809. - - - - - c645fe40 by Fendor at 2024-05-22T13:40:05-04:00 Add regression test T24809 for stg_orig_thunk_info_frame size - - - - - 4181aa40 by Andreas Klebinger at 2024-05-22T13:40:42-04:00 bindists: Check for existence of share folder before trying to copy it. This folder isn't distributed in windows bindists A lack of doing so resulted us copying loads of files twice. - - - - - d216510e by Matthew Pickering at 2024-05-22T13:40:42-04:00 Remove ad-hoc installation of mingw toolchain in relocatable bindists This reverts 616ac30026e8dd7d2ebb98d92dde071eedf5d951 The choice about whether to install mingw is taken in the installation makefile. This is also broken on non-windows systems. The actual issue was the EnableDistroToolchain variable wasn't declared in mk/config.mk and therefore the check to install mingw was failing. - - - - - 7b4c1998 by Cheng Shao at 2024-05-22T21:52:52-04:00 testsuite: fix T17920 for wasm backend T17920 was marked as fragile on wasm before; it can be trivially fixed by avoiding calling variadic printf() in cmm. - - - - - c739383b by Cheng Shao at 2024-05-22T21:53:29-04:00 testsuite: bump T22744 timeout to 5x - - - - - c4c6d714 by Cheng Shao at 2024-05-22T21:54:06-04:00 testsuite: don't attempt to detect host cpu features when testing cross ghc The testsuite driver CPU feature detection logic only detects host CPU and only makes sense when we are not testing a cross GHC. - - - - - 3d9e4ce6 by Simon Peyton Jones at 2024-05-22T21:54:43-04:00 Better skolemisation As #24810 showed, it is (a little) better to skolemise en-bloc, so that Note [Let-bound skolems] fires more often. See Note [Skolemisation en bloc] in GHC.Tc.Utils.Instantiate. - - - - - a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00 Add missing parenthesizePat in cvtp We need to ensure that the output of `cvtp` is parenthesized (at precedence `sigPrec`) so that any pattern signatures with a surrounding pattern signature can parse correctly. Fixes #24837. - - - - - 4bb2a7cc by Hécate Moonlight at 2024-05-22T21:55:59-04:00 [base] Document the memory overhead of ByteArray Add a diagram that shows the constituent parts of a ByteArray and their memory overhead. - - - - - 8b2a016a by Hécate Moonlight at 2024-05-22T21:56:38-04:00 Haddock: Add MR template for Haddock - - - - - ead75532 by Peter Trommler at 2024-05-23T02:28:05-04:00 PPC: Support ELF v2 on powerpc64 big-endian Detect ELF v2 on PowerPC 64-bit systems. Check for `_CALL_ELF` preprocessor macro. Fixes #21191 - - - - - 9d4c10f2 by Hécate Kleidukos at 2024-05-23T02:28:44-04:00 gitlab: Add @Kleidukos to CODEOWNERS for utils/haddock - - - - - 28e64170 by Preetham Gujjula at 2024-05-23T07:20:48-04:00 haddock: Add cabal-fmt to tools for `make style` - - - - - 00126a89 by Andrei Borzenkov at 2024-05-23T07:21:24-04:00 haddock: fix verbosity option parsing - - - - - a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00 base: specify tie-breaking behavior of min, max, and related list/Foldable functions - - - - - bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00 cmm: add word <-> double/float bitcast - closes: #25331 This is the last step in the project plan described in #25331. This commit: - adds bitcast operands for x86_64, LLVM, aarch64 - For PPC and i386 we resort to using the cmm implementations - renames conversion MachOps from Conv to Round|Truncate - - - - - f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor Some functions in StgToByteCode were filtering out void arguments. However, StgToByteCode is called after unarisation: the void arguments should have been removed earlier. Instead of filtering out, we assert that the args are non-void. - - - - - 03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor `layoutNativeCall` was always called with a `primRepCmmType platform` callback. Hence we can put it inside of `layoutNativeCall` rather than repeat it. - - - - - 27c430f3 by David Binder at 2024-05-24T07:52:38-04:00 haddock: Remove compatibility shims for GHC < 8.4 from haddock-library - - - - - 8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00 compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs This patch makes the STG->Cmm backend avoid saving foreign call target to local when there are no caller-save GlobalRegs. Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a foreign call, we unconditionally save the foreign call target to a temporary local first, then rely on cmmSink to clean it up later, which only happens with -fcmm-sink (implied by -O) and not in unoptimized code. And this is troublesome for the wasm backend NCG, which needs to infer a foreign call target symbol's type signature from the Cmm call site. Previously, the NCG has been emitting incorrect type signatures for unoptimized code, which happens to work with `wasm-ld` most of the time, but this is never future-proof against upstream toolchain updates, and it causes horrible breakages when LTO objects are included in linker input. Hence this patch. - - - - - 986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00 testsuite: add callee-no-local regression test - - - - - 52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00 Fix HasCallStack leftovers from !12514 / #24726 - - - - - c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00 user_guide: Fix typo in MultiWayIf chapter Close #24829 - - - - - bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - 1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Fix changelog reference to setBacktraceMechanismState (cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d) - - - - - 43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00 Float/double unboxed literal support for HexFloatLiterals (fix #22155) - - - - - 4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00 Improve test labels for binary interface file size tests Test labels for binary interface file sizes are hard to read and overly verbose at the same time. Extend the name for the metric title, but shorten it in the actual comparison table. - - - - - 14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00 Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present" This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa. - - - - - f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00 Fix default hyperlinked sources pattern Previously this didn't include the `%M` token which manifested as broken links to the hyperlinked sources of reexports of declarations defined in other packages. Fixes haddock#1628. (cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36) - - - - - 42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00 Make DocPaths a proper data type (cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c) - - - - - 53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00 haddock: Bump version to 2.30 (cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602) - - - - - e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00 haddock-api: allow base 4.20 and ghc 9.11 - - - - - e294f7a2 by PHO at 2024-05-24T12:17:55-04:00 Add a flag "threaded" for building haddock with the threaded RTS GHC isn't guaranteed to have a threaded RTS. There should be a way to build it with the vanilla one. (cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d) - - - - - 51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00 Update ticky counter event docs. Add the info about the info table address and json fields. Fixes #23200 - - - - - 98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00 Export extractPromotedList (#24866) This can be useful in plugins. - - - - - 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - 333e4352 by Berk Özkütük at 2024-06-08T17:37:13+02:00 Disambiguate closures' printing from thunks (#23507) - - - - - 4404090c by Berk Özkütük at 2024-06-08T17:37:14+02:00 Only print function closures - - - - - 13 changed files: - .ghcid - + .git-blame-ignore-revs - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/darwin/nix/sources.json - .gitlab/darwin/toolchain.nix - − .gitlab/gen-ci.cabal - .gitlab/generate-ci/gen_ci.hs - .gitlab/generate-ci/generate-job-metadata - .gitlab/generate-ci/generate-jobs - .gitlab/hie.yaml → .gitlab/generate-ci/hie.yaml - .gitlab/issue_templates/bug.md → .gitlab/issue_templates/default.md The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/da7761fec9f99abc42b60f5b7012e8a1e470d12a...4404090cae7ca440eaa81809b492c282b233cffe -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/da7761fec9f99abc42b60f5b7012e8a1e470d12a...4404090cae7ca440eaa81809b492c282b233cffe You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 15:44:45 2024 From: gitlab at gitlab.haskell.org (Adriaan Leijnse (@aidylns)) Date: Sat, 08 Jun 2024 11:44:45 -0400 Subject: [Git][ghc/ghc][wip/aidylns/remove-sourcetext-from-overloadedlabel] Fix the parser Message-ID: <66647c6d19ada_3096f931c226413848e@gitlab.mail> Adriaan Leijnse pushed to branch wip/aidylns/remove-sourcetext-from-overloadedlabel at Glasgow Haskell Compiler / GHC Commits: 6759bbe3 by Adriaan Leijnse at 2024-06-08T17:44:11+02:00 Fix the parser - - - - - 1 changed file: - compiler/GHC/Parser.y Changes: ===================================== compiler/GHC/Parser.y ===================================== @@ -3007,7 +3007,7 @@ aexp2 :: { ECP } | ipvar %shift {% fmap ecpFromExp (ams1 $1 (HsIPVar NoExtField $! unLoc $1)) } | overloaded_label {% fmap ecpFromExp - (ams1 $1 (HsOverLabel NoExtField (fst $! unLoc $1) (snd $! unLoc $1))) } + (ams1 $1 (HsOverLabel (fst $! unLoc $1) (snd $! unLoc $1))) } | literal { ECP $ mkHsLitPV $! $1 } -- This will enable overloaded strings permanently. Normally the renamer turns HsString -- into HsOverLit when -XOverloadedStrings is on. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6759bbe36281b1b1a4b9796a8dd0e51a2ee6fd49 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6759bbe36281b1b1a4b9796a8dd0e51a2ee6fd49 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 16:03:37 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Sat, 08 Jun 2024 12:03:37 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T23415-9.8 Message-ID: <666480d9bd693_3096f934f0fa81500f9@gitlab.mail> Ben Gamari pushed new branch wip/T23415-9.8 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T23415-9.8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 16:05:36 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Sat, 08 Jun 2024 12:05:36 -0400 Subject: [Git][ghc/ghc][wip/T23415-9.8] 5 commits: rts: free error message before returning Message-ID: <66648150a94c7_3096f9354977015027@gitlab.mail> Ben Gamari pushed to branch wip/T23415-9.8 at Glasgow Haskell Compiler / GHC Commits: 2f8b5542 by Rodrigo Mesquita at 2024-06-08T12:05:28-04:00 rts: free error message before returning Fixes a memory leak in rts/linker/PEi386.c (cherry picked from commit dd530bb7e22e953e4cec64a5fd6c39fddc152c6f) - - - - - fbec131e by Alexis King at 2024-06-08T12:05:28-04:00 linker: Avoid linear search when looking up Haskell symbols via dlsym See the primary Note [Looking up symbols in the relevant objects] for a more in-depth explanation. When dynamically loading a Haskell symbol (typical when running a splice or GHCi expression), before this commit we would search for the symbol in all dynamic libraries that were loaded. However, this could be very inefficient when too many packages are loaded (which can happen if there are many package dependencies) because the time to lookup the would be linear in the number of packages loaded. This commit drastically improves symbol loading performance by introducing a mapping from units to the handles of corresponding loaded dlls. These handles are returned by dlopen when we load a dll, and can then be used to look up in a specific dynamic library. Looking up a given Name is now much more precise because we can get lookup its unit in the mapping and lookup the symbol solely in the handles of the dynamic libraries loaded for that unit. In one measurement, the wait time before the expression was executed went from +-38 seconds down to +-2s. This commit also includes Note [Symbols may not be found in pkgs_loaded], explaining the fallback to the old behaviour in case no dll can be found in the unit mapping for a given Name. Fixes #23415 Co-authored-by: Rodrigo Mesquita (@alt-romes) (cherry picked from commit e008a19a7f9e8f22aada0b4e1049744f49d39aad) - - - - - e60e15ec by Rodrigo Mesquita at 2024-06-08T12:05:28-04:00 rts: Make addDLL a wrapper around loadNativeObj Rewrite the implementation of `addDLL` as a wrapper around the more principled `loadNativeObj` rts linker function. The latter should be preferred while the former is preserved for backwards compatibility. `loadNativeObj` was previously only available on ELF platforms, so this commit further refactors the rts linker to transform loadNativeObj_ELF into loadNativeObj_POSIX, which is available in ELF and MachO platforms. The refactor made it possible to remove the `dl_mutex` mutex in favour of always using `linker_mutex` (rather than a combination of both). Lastly, we implement `loadNativeObj` for Windows too. (cherry picked from commit dcfaa190e1e1182a2efe4e2f601affbb832a49bb) - - - - - 3f91d9cc by Rodrigo Mesquita at 2024-06-08T12:05:28-04:00 Use symbol cache in internal interpreter too This commit makes the symbol cache that was used by the external interpreter available for the internal interpreter too. This follows from the analysis in #23415 that suggests the internal interpreter could benefit from this cache too, and that there is no good reason not to have the cache for it too. It also makes it a bit more uniform to have the symbol cache range over both the internal and external interpreter. This commit also refactors the cache into a function which is used by both `lookupSymbol` and also by `lookupSymbolInDLL`, extending the caching logic to `lookupSymbolInDLL` too. (cherry picked from commit 12931698261a1cee6a00b731d143270cd60e5f2d) - - - - - 6c8a6930 by Ben Gamari at 2024-06-08T12:05:28-04:00 testsuite: Add test for lookupSymbolInNativeObj (cherry picked from commit dccd3ea159b03cc1972cf47ee3cf8bda73ec0c5a) - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Linker/MacOS.hs - compiler/GHC/Linker/Types.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/JS.hs - compiler/GHC/Runtime/Interpreter/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - rts/Linker.c - rts/LinkerInternals.h - rts/RtsSymbols.c - rts/include/rts/Linker.h - rts/linker/Elf.c - rts/linker/Elf.h - + rts/linker/LoadNativeObjPosix.c - + rts/linker/LoadNativeObjPosix.h - rts/linker/PEi386.c - rts/linker/PEi386.h - rts/rts.cabal.in - testsuite/tests/ghci/linking/dyn/T3372.hs - testsuite/tests/rts/linker/T2615.hs - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/Makefile - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/all.T - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/lookupSymbolInNativeObj1.c - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/lookupSymbolInNativeObj1.stdout The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d44a18fbb50ff568b89f26fd9224ddc55bb43e16...6c8a69303f4129d405872cce8acb77b0709ee58c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d44a18fbb50ff568b89f26fd9224ddc55bb43e16...6c8a69303f4129d405872cce8acb77b0709ee58c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 16:16:56 2024 From: gitlab at gitlab.haskell.org (Zubin (@wz1000)) Date: Sat, 08 Jun 2024 12:16:56 -0400 Subject: [Git][ghc/ghc][wip/faststring-no-z] wip Message-ID: <666483f8ada8b_3096f93882bd01537d4@gitlab.mail> Zubin pushed to branch wip/faststring-no-z at Glasgow Haskell Compiler / GHC Commits: 439ba6ec by Zubin Duggal at 2024-06-08T18:16:47+02:00 wip - - - - - 3 changed files: - compiler/GHC/Data/FastString.hs - compiler/GHC/Unit/Info.hs - hadrian/src/Rules/Rts.hs Changes: ===================================== compiler/GHC/Data/FastString.hs ===================================== @@ -323,7 +323,15 @@ data FastZStringTable = FastZStringTable -- ^ The number of encoded Z strings (Array# (IORef FastZStringTableSegment)) -- ^ concurrent segments -type FastZStringTableSegment = TableSegment (Int,FastZString) +type FastZStringTableSegment = TableSegment HashedFastZString + +data HashedFastZString + = HashedFastZString + {-# UNPACK #-} !Int + {-# NOUNPACK #-} !FastZString + +zStringHash :: HashedFastZString -> Int +zStringHash (HashedFastZString hash _) = hash {- Following parameters are determined based on: @@ -579,7 +587,7 @@ mkNewFastZString (FastString uniq _ sbs) = do !(I# hash#) = uniq*6364136223846793005 + 1 (# segmentRef #) = indexArray# segments# (hashToSegment# hash#) insert n fs = do - TableSegment _ counter buckets# <- maybeResizeSegment fst segmentRef + TableSegment _ counter buckets# <- maybeResizeSegment zStringHash segmentRef let idx# = hashToIndex# buckets# hash# bucket <- IO $ readArray# buckets# idx# case zbucket_match bucket hash# of @@ -588,17 +596,18 @@ mkNewFastZString (FastString uniq _ sbs) = do Just found -> return found Nothing -> do IO $ \s1# -> - case writeArray# buckets# idx# ((n,fs) : bucket) s1# of + case writeArray# buckets# idx# (HashedFastZString n fs : bucket) s1# of s2# -> (# s2#, () #) _ <- atomicFetchAddFastMut counter 1 return fs -zbucket_match :: [(Int,FastZString)] -> Int# -> Maybe FastZString +zbucket_match :: [HashedFastZString] -> Int# -> Maybe FastZString zbucket_match fs hash = go fs where go [] = Nothing - go ((I# u,x) : ls) + go (HashedFastZString (I# u) x : ls) | isTrue# (u ==# hash) = Just x | otherwise = go ls +{-# INLINE zbucket_match #-} mkFastStringBytes :: Ptr Word8 -> Int -> FastString mkFastStringBytes !ptr !len = ===================================== compiler/GHC/Unit/Info.hs ===================================== @@ -236,7 +236,7 @@ unitHsLibs namever ways0 p = map (mkDynName . addSuffix . ST.unpack) (unitLibrar -- This change elevates the need to add custom hooks -- and handling specifically for the `rts` package. addSuffix rts@"HSrts" = rts ++ (expandTag rts_tag) - addSuffix rts@"HSrts-1.0.2" = rts ++ (expandTag rts_tag) + addSuffix rts@"HSrts-1.0.3" = rts ++ (expandTag rts_tag) addSuffix other_lib = other_lib ++ (expandTag tag) expandTag t | null t = "" ===================================== hadrian/src/Rules/Rts.hs ===================================== @@ -161,7 +161,7 @@ needRtsSymLinks stage rtsWays prefix, versionlessPrefix :: String versionlessPrefix = "libHSrts" -prefix = versionlessPrefix ++ "-1.0.2" +prefix = versionlessPrefix ++ "-1.0.3" -- removeRtsDummyVersion "a/libHSrts-1.0-ghc1.2.3.4.so" -- == "a/libHSrts-ghc1.2.3.4.so" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/439ba6ec7584bd381dfc01da27e6f7b5e886a075 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/439ba6ec7584bd381dfc01da27e6f7b5e886a075 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 16:30:26 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Sat, 08 Jun 2024 12:30:26 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ast] AST: move conDetailsArity into GHC.Rename.Module Message-ID: <66648722d1ac6_3096f93b4cc94159486@gitlab.mail> Fabian Kirchner pushed to branch wip/kirchner/ast at Glasgow Haskell Compiler / GHC Commits: 5c2a4c3e by Fabian Kirchner at 2024-06-08T18:27:23+02:00 AST: move conDetailsArity into GHC.Rename.Module The function conDetailsArity is only used inside GHC.Rename.Module. We therefore move it there from Language.Haskell.Syntax.Lit. - - - - - 2 changed files: - compiler/GHC/Rename/Module.hs - compiler/Language/Haskell/Syntax/Type.hs Changes: ===================================== compiler/GHC/Rename/Module.hs ===================================== @@ -3,6 +3,7 @@ {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE LambdaCase #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} @@ -54,6 +55,7 @@ import GHC.Types.Name.Set import GHC.Types.Name.Env import GHC.Utils.Outputable import GHC.Data.Bag +import GHC.Types.Basic (Arity) import GHC.Types.Basic ( TypeOrKind(..) ) import GHC.Data.FastString import GHC.Types.SrcLoc as SrcLoc @@ -2558,6 +2560,12 @@ extendPatSynEnv dup_fields_ok has_sel val_decls local_fix_env thing = do { | otherwise = return names +conDetailsArity :: (rec -> Arity) -> HsConDetails tyarg arg rec -> Arity +conDetailsArity recToArity = \case + PrefixCon _ args -> length args + RecCon rec -> recToArity rec + InfixCon _ _ -> 2 + {- ********************************************************* * * ===================================== compiler/Language/Haskell/Syntax/Type.hs ===================================== @@ -48,7 +48,7 @@ module Language.Haskell.Syntax.Type ( ConDeclField(..), LConDeclField, - HsConDetails(..), noTypeArgs, conDetailsArity, + HsConDetails(..), noTypeArgs, FieldOcc(..), LFieldOcc, AmbiguousFieldOcc(..), LAmbiguousFieldOcc, @@ -66,7 +66,6 @@ import Language.Haskell.Syntax.Extension import GHC.Types.Name.Reader ( RdrName ) import GHC.Core.DataCon( HsSrcBang(..) ) import GHC.Core.Type (Specificity) -import GHC.Types.Basic (Arity) import GHC.Hs.Doc (LHsDoc) import GHC.Data.FastString (FastString) @@ -77,7 +76,7 @@ import Data.Maybe import Data.Eq import Data.Bool import Data.Char -import Prelude (Integer, length) +import Prelude (Integer) import Data.Ord (Ord) {- @@ -1108,12 +1107,6 @@ data HsConDetails tyarg arg rec noTypeArgs :: [Void] noTypeArgs = [] -conDetailsArity :: (rec -> Arity) -> HsConDetails tyarg arg rec -> Arity -conDetailsArity recToArity = \case - PrefixCon _ args -> length args - RecCon rec -> recToArity rec - InfixCon _ _ -> 2 - {- Note [ConDeclField pass] ~~~~~~~~~~~~~~~~~~~~~~~~~ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5c2a4c3e7d517fd1eb6f7c0fe01cfb2d9e7976a6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5c2a4c3e7d517fd1eb6f7c0fe01cfb2d9e7976a6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 16:31:50 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Sat, 08 Jun 2024 12:31:50 -0400 Subject: [Git][ghc/ghc][wip/T23415-9.8] 4 commits: linker: Avoid linear search when looking up Haskell symbols via dlsym Message-ID: <666487769719d_3096f93b8bb38160022@gitlab.mail> Ben Gamari pushed to branch wip/T23415-9.8 at Glasgow Haskell Compiler / GHC Commits: 09d3854e by Alexis King at 2024-06-08T12:31:40-04:00 linker: Avoid linear search when looking up Haskell symbols via dlsym See the primary Note [Looking up symbols in the relevant objects] for a more in-depth explanation. When dynamically loading a Haskell symbol (typical when running a splice or GHCi expression), before this commit we would search for the symbol in all dynamic libraries that were loaded. However, this could be very inefficient when too many packages are loaded (which can happen if there are many package dependencies) because the time to lookup the would be linear in the number of packages loaded. This commit drastically improves symbol loading performance by introducing a mapping from units to the handles of corresponding loaded dlls. These handles are returned by dlopen when we load a dll, and can then be used to look up in a specific dynamic library. Looking up a given Name is now much more precise because we can get lookup its unit in the mapping and lookup the symbol solely in the handles of the dynamic libraries loaded for that unit. In one measurement, the wait time before the expression was executed went from +-38 seconds down to +-2s. This commit also includes Note [Symbols may not be found in pkgs_loaded], explaining the fallback to the old behaviour in case no dll can be found in the unit mapping for a given Name. Fixes #23415 Co-authored-by: Rodrigo Mesquita (@alt-romes) (cherry picked from commit e008a19a7f9e8f22aada0b4e1049744f49d39aad) - - - - - 086e0c0d by Rodrigo Mesquita at 2024-06-08T12:31:40-04:00 rts: Make addDLL a wrapper around loadNativeObj Rewrite the implementation of `addDLL` as a wrapper around the more principled `loadNativeObj` rts linker function. The latter should be preferred while the former is preserved for backwards compatibility. `loadNativeObj` was previously only available on ELF platforms, so this commit further refactors the rts linker to transform loadNativeObj_ELF into loadNativeObj_POSIX, which is available in ELF and MachO platforms. The refactor made it possible to remove the `dl_mutex` mutex in favour of always using `linker_mutex` (rather than a combination of both). Lastly, we implement `loadNativeObj` for Windows too. (cherry picked from commit dcfaa190e1e1182a2efe4e2f601affbb832a49bb) - - - - - df38dc28 by Rodrigo Mesquita at 2024-06-08T12:31:40-04:00 Use symbol cache in internal interpreter too This commit makes the symbol cache that was used by the external interpreter available for the internal interpreter too. This follows from the analysis in #23415 that suggests the internal interpreter could benefit from this cache too, and that there is no good reason not to have the cache for it too. It also makes it a bit more uniform to have the symbol cache range over both the internal and external interpreter. This commit also refactors the cache into a function which is used by both `lookupSymbol` and also by `lookupSymbolInDLL`, extending the caching logic to `lookupSymbolInDLL` too. (cherry picked from commit 12931698261a1cee6a00b731d143270cd60e5f2d) - - - - - ab9e921a by Ben Gamari at 2024-06-08T12:31:40-04:00 testsuite: Add test for lookupSymbolInNativeObj (cherry picked from commit dccd3ea159b03cc1972cf47ee3cf8bda73ec0c5a) - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Linker/MacOS.hs - compiler/GHC/Linker/Types.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/JS.hs - compiler/GHC/Runtime/Interpreter/Types.hs - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - rts/Linker.c - rts/LinkerInternals.h - rts/RtsSymbols.c - rts/include/rts/Linker.h - rts/linker/Elf.c - rts/linker/Elf.h - + rts/linker/LoadNativeObjPosix.c - + rts/linker/LoadNativeObjPosix.h - rts/linker/PEi386.c - rts/linker/PEi386.h - rts/rts.cabal.in - testsuite/tests/ghci/linking/dyn/T3372.hs - testsuite/tests/rts/linker/T2615.hs - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/Makefile - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/all.T - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/lookupSymbolInNativeObj1.c - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/lookupSymbolInNativeObj1.stdout The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6c8a69303f4129d405872cce8acb77b0709ee58c...ab9e921aa85aaea8ed7359793e7b61e52a479645 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6c8a69303f4129d405872cce8acb77b0709ee58c...ab9e921aa85aaea8ed7359793e7b61e52a479645 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 16:50:46 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Sat, 08 Jun 2024 12:50:46 -0400 Subject: [Git][ghc/ghc][wip/T23415-9.8] 3 commits: rts: Make addDLL a wrapper around loadNativeObj Message-ID: <66648be68a8ff_3096f93f78d181663f1@gitlab.mail> Ben Gamari pushed to branch wip/T23415-9.8 at Glasgow Haskell Compiler / GHC Commits: 5f02cd9a by Rodrigo Mesquita at 2024-06-08T12:50:23-04:00 rts: Make addDLL a wrapper around loadNativeObj Rewrite the implementation of `addDLL` as a wrapper around the more principled `loadNativeObj` rts linker function. The latter should be preferred while the former is preserved for backwards compatibility. `loadNativeObj` was previously only available on ELF platforms, so this commit further refactors the rts linker to transform loadNativeObj_ELF into loadNativeObj_POSIX, which is available in ELF and MachO platforms. The refactor made it possible to remove the `dl_mutex` mutex in favour of always using `linker_mutex` (rather than a combination of both). Lastly, we implement `loadNativeObj` for Windows too. (cherry picked from commit dcfaa190e1e1182a2efe4e2f601affbb832a49bb) - - - - - 672f3917 by Rodrigo Mesquita at 2024-06-08T12:50:23-04:00 Use symbol cache in internal interpreter too This commit makes the symbol cache that was used by the external interpreter available for the internal interpreter too. This follows from the analysis in #23415 that suggests the internal interpreter could benefit from this cache too, and that there is no good reason not to have the cache for it too. It also makes it a bit more uniform to have the symbol cache range over both the internal and external interpreter. This commit also refactors the cache into a function which is used by both `lookupSymbol` and also by `lookupSymbolInDLL`, extending the caching logic to `lookupSymbolInDLL` too. (cherry picked from commit 12931698261a1cee6a00b731d143270cd60e5f2d) - - - - - 40cf835c by Ben Gamari at 2024-06-08T12:50:24-04:00 testsuite: Add test for lookupSymbolInNativeObj (cherry picked from commit dccd3ea159b03cc1972cf47ee3cf8bda73ec0c5a) - - - - - 23 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/JS.hs - compiler/GHC/Runtime/Interpreter/Types.hs - libraries/ghci/GHCi/ObjLink.hs - rts/Linker.c - rts/LinkerInternals.h - rts/RtsSymbols.c - rts/include/rts/Linker.h - rts/linker/Elf.c - rts/linker/Elf.h - + rts/linker/LoadNativeObjPosix.c - + rts/linker/LoadNativeObjPosix.h - rts/linker/PEi386.c - rts/linker/PEi386.h - rts/rts.cabal.in - testsuite/tests/ghci/linking/dyn/T3372.hs - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/Makefile - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/all.T - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/lookupSymbolInNativeObj1.c - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/lookupSymbolInNativeObj1.stdout - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/obj.c Changes: ===================================== compiler/GHC.hs ===================================== @@ -397,6 +397,7 @@ import GHC.Types.Name.Ppr import GHC.Types.TypeEnv import GHC.Types.BreakInfo import GHC.Types.PkgQual +import GHC.Types.Unique.FM import GHC.Unit import GHC.Unit.Env @@ -676,6 +677,7 @@ setTopSessionDynFlags :: GhcMonad m => DynFlags -> m () setTopSessionDynFlags dflags = do hsc_env <- getSession logger <- getLogger + lookup_cache <- liftIO $ newMVar emptyUFM -- Interpreter interp <- if @@ -705,7 +707,7 @@ setTopSessionDynFlags dflags = do } s <- liftIO $ newMVar InterpPending loader <- liftIO Loader.uninitializedLoader - return (Just (Interp (ExternalInterp (ExtIServ (ExtInterpState conf s))) loader)) + return (Just (Interp (ExternalInterp (ExtIServ (ExtInterpState conf s))) loader lookup_cache)) -- JavaScript interpreter | ArchJavaScript <- platformArch (targetPlatform dflags) @@ -723,7 +725,7 @@ setTopSessionDynFlags dflags = do , jsInterpFinderOpts = initFinderOpts dflags , jsInterpFinderCache = hsc_FC hsc_env } - return (Just (Interp (ExternalInterp (ExtJS (ExtInterpState cfg s))) loader)) + return (Just (Interp (ExternalInterp (ExtJS (ExtInterpState cfg s))) loader lookup_cache)) -- Internal interpreter | otherwise @@ -731,7 +733,7 @@ setTopSessionDynFlags dflags = do #if defined(HAVE_INTERNAL_INTERPRETER) do loader <- liftIO Loader.uninitializedLoader - return (Just (Interp InternalInterp loader)) + return (Just (Interp InternalInterp loader lookup_cache)) #else return Nothing #endif ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -2647,7 +2647,7 @@ hscCompileCoreExpr' hsc_env srcspan ds_expr = do case interp of -- always generate JS code for the JS interpreter (no bytecode!) - Interp (ExternalInterp (ExtJS i)) _ -> + Interp (ExternalInterp (ExtJS i)) _ _ -> jsCodeGen hsc_env srcspan i this_mod stg_binds_with_deps binding_id _ -> do ===================================== compiler/GHC/Runtime/Interpreter.hs ===================================== @@ -159,22 +159,22 @@ The main pieces are: - implementation of Template Haskell (GHCi.TH) - a few other things needed to run interpreted code -- top-level iserv directory, containing the codefor the external - server. This is a fairly simple wrapper, most of the functionality +- top-level iserv directory, containing the code for the external + server. This is a fairly simple wrapper, most of the functionality is provided by modules in libraries/ghci. - This module which provides the interface to the server used by the rest of GHC. -GHC works with and without -fexternal-interpreter. With the flag, all -interpreted code is run by the iserv binary. Without the flag, +GHC works with and without -fexternal-interpreter. With the flag, all +interpreted code is run by the iserv binary. Without the flag, interpreted code is run in the same process as GHC. Things that do not work with -fexternal-interpreter ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ dynCompileExpr cannot work, because we have no way to run code of an -unknown type in the remote process. This API fails with an error +unknown type in the remote process. This API fails with an error message if it is used with -fexternal-interpreter. Other Notes on Remote GHCi @@ -452,52 +452,71 @@ initObjLinker :: Interp -> IO () initObjLinker interp = interpCmd interp InitLinker lookupSymbol :: Interp -> FastString -> IO (Maybe (Ptr ())) -lookupSymbol interp str = case interpInstance interp of +lookupSymbol interp str = withSymbolCache interp str $ + case interpInstance interp of #if defined(HAVE_INTERNAL_INTERPRETER) - InternalInterp -> fmap fromRemotePtr <$> run (LookupSymbol (unpackFS str)) + InternalInterp -> fmap fromRemotePtr <$> run (LookupSymbol (unpackFS str)) #endif - - ExternalInterp ext -> case ext of - ExtIServ i -> withIServ i $ \inst -> do - -- Profiling of GHCi showed a lot of time and allocation spent - -- making cross-process LookupSymbol calls, so I added a GHC-side - -- cache which sped things up quite a lot. We have to be careful - -- to purge this cache when unloading code though. - cache <- readMVar (instLookupSymbolCache inst) - case lookupUFM cache str of - Just p -> return (Just p) - Nothing -> do - m <- uninterruptibleMask_ $ - sendMessage inst (LookupSymbol (unpackFS str)) - case m of - Nothing -> return Nothing - Just r -> do - let p = fromRemotePtr r - cache' = addToUFM cache str p - modifyMVar_ (instLookupSymbolCache inst) (const (pure cache')) - return (Just p) - - ExtJS {} -> pprPanic "lookupSymbol not supported by the JS interpreter" (ppr str) + ExternalInterp ext -> case ext of + ExtIServ i -> withIServ i $ \inst -> fmap fromRemotePtr <$> do + uninterruptibleMask_ $ + sendMessage inst (LookupSymbol (unpackFS str)) + ExtJS {} -> pprPanic "lookupSymbol not supported by the JS interpreter" (ppr str) lookupSymbolInDLL :: Interp -> RemotePtr LoadedDLL -> FastString -> IO (Maybe (Ptr ())) -lookupSymbolInDLL interp dll str = case interpInstance interp of +lookupSymbolInDLL interp dll str = withSymbolCache interp str $ + case interpInstance interp of #if defined(HAVE_INTERNAL_INTERPRETER) - InternalInterp -> fmap fromRemotePtr <$> run (LookupSymbolInDLL dll (unpackFS str)) + InternalInterp -> fmap fromRemotePtr <$> run (LookupSymbolInDLL dll (unpackFS str)) #endif - ExternalInterp _ -> panic "lookupSymbolInDLL: not implemented for external interpreter" -- FIXME + ExternalInterp ext -> case ext of + ExtIServ i -> withIServ i $ \inst -> fmap fromRemotePtr <$> do + uninterruptibleMask_ $ + sendMessage inst (LookupSymbolInDLL dll (unpackFS str)) + ExtJS {} -> pprPanic "lookupSymbol not supported by the JS interpreter" (ppr str) lookupClosure :: Interp -> String -> IO (Maybe HValueRef) lookupClosure interp str = interpCmd interp (LookupClosure str) +-- | 'withSymbolCache' tries to find a symbol in the 'interpLookupSymbolCache' +-- which maps symbols to the address where they are loaded. +-- When there's a cache hit we simply return the cached address, when there is +-- a miss we run the action which determines the symbol's address and populate +-- the cache with the answer. +withSymbolCache :: Interp + -> FastString + -- ^ The symbol we are looking up in the cache + -> IO (Maybe (Ptr ())) + -- ^ An action which determines the address of the symbol we + -- are looking up in the cache, which is run if there is a + -- cache miss. The result will be cached. + -> IO (Maybe (Ptr ())) +withSymbolCache interp str determine_addr = do + + -- Profiling of GHCi showed a lot of time and allocation spent + -- making cross-process LookupSymbol calls, so I added a GHC-side + -- cache which sped things up quite a lot. We have to be careful + -- to purge this cache when unloading code though. + -- + -- The analysis in #23415 further showed this cache should also benefit the + -- internal interpreter's loading times, and needn't be used by the external + -- interpreter only. + cache <- readMVar (interpLookupSymbolCache interp) + case lookupUFM cache str of + Just p -> return (Just p) + Nothing -> do + + maddr <- determine_addr + case maddr of + Nothing -> return Nothing + Just p -> do + let upd_cache cache' = addToUFM cache' str p + modifyMVar_ (interpLookupSymbolCache interp) (pure . upd_cache) + return (Just p) + purgeLookupSymbolCache :: Interp -> IO () -purgeLookupSymbolCache interp = case interpInstance interp of -#if defined(HAVE_INTERNAL_INTERPRETER) - InternalInterp -> pure () -#endif - ExternalInterp ext -> withExtInterpMaybe ext $ \case - Nothing -> pure () -- interpreter stopped, nothing to do - Just inst -> modifyMVar_ (instLookupSymbolCache inst) (const (pure emptyUFM)) +purgeLookupSymbolCache interp = modifyMVar_ (interpLookupSymbolCache interp) (const (pure emptyUFM)) -- | loadDLL loads a dynamic library using the OS's native linker -- (i.e. dlopen() on Unix, LoadLibrary() on Windows). It takes either @@ -563,11 +582,9 @@ spawnIServ conf = do } pending_frees <- newMVar [] - lookup_cache <- newMVar emptyUFM let inst = ExtInterpInstance { instProcess = process , instPendingFrees = pending_frees - , instLookupSymbolCache = lookup_cache , instExtra = () } pure inst ===================================== compiler/GHC/Runtime/Interpreter/JS.hs ===================================== @@ -41,7 +41,6 @@ import GHC.Utils.Panic import GHC.Utils.Error (logInfo) import GHC.Utils.Outputable (text) import GHC.Data.FastString -import GHC.Types.Unique.FM import Control.Concurrent import Control.Monad @@ -178,11 +177,9 @@ spawnJSInterp cfg = do } pending_frees <- newMVar [] - lookup_cache <- newMVar emptyUFM let inst = ExtInterpInstance { instProcess = proc , instPendingFrees = pending_frees - , instLookupSymbolCache = lookup_cache , instExtra = extra } ===================================== compiler/GHC/Runtime/Interpreter/Types.hs ===================================== @@ -51,6 +51,9 @@ data Interp = Interp , interpLoader :: !Loader -- ^ Interpreter loader + + , interpLookupSymbolCache :: !(MVar (UniqFM FastString (Ptr ()))) + -- ^ LookupSymbol cache } data InterpInstance @@ -108,9 +111,6 @@ data ExtInterpInstance c = ExtInterpInstance -- Finalizers for ForeignRefs can append values to this list -- asynchronously. - , instLookupSymbolCache :: !(MVar (UniqFM FastString (Ptr ()))) - -- ^ LookupSymbol cache - , instExtra :: !c -- ^ Instance specific extra fields } ===================================== libraries/ghci/GHCi/ObjLink.hs ===================================== @@ -74,7 +74,7 @@ lookupSymbolInDLL :: Ptr LoadedDLL -> String -> IO (Maybe (Ptr a)) lookupSymbolInDLL dll str_in = do let str = prefixUnderscore str_in withCAString str $ \c_str -> do - addr <- c_lookupSymbolInDLL dll c_str + addr <- c_lookupSymbolInNativeObj dll c_str if addr == nullPtr then return Nothing else return (Just addr) @@ -99,8 +99,6 @@ prefixUnderscore -- searches the standard locations for the appropriate library. -- loadDLL :: String -> IO (Either String (Ptr LoadedDLL)) --- Nothing => success --- Just err_msg => failure loadDLL str0 = do let -- On Windows, addDLL takes a filename without an extension, because @@ -112,7 +110,7 @@ loadDLL str0 = do -- (maybe_handle, maybe_errmsg) <- withFilePath (normalise str) $ \dll -> alloca $ \errmsg_ptr -> (,) - <$> c_addDLL dll errmsg_ptr + <$> c_loadNativeObj dll errmsg_ptr <*> peek errmsg_ptr if maybe_handle == nullPtr @@ -176,8 +174,8 @@ resolveObjs = do -- Foreign declarations to RTS entry points which does the real work; -- --------------------------------------------------------------------------- -foreign import ccall unsafe "addDLL" c_addDLL :: CFilePath -> Ptr CString -> IO (Ptr LoadedDLL) -foreign import ccall unsafe "lookupSymbolInDLL" c_lookupSymbolInDLL :: Ptr LoadedDLL -> CString -> IO (Ptr a) +foreign import ccall unsafe "loadNativeObj" c_loadNativeObj :: CFilePath -> Ptr CString -> IO (Ptr LoadedDLL) +foreign import ccall unsafe "lookupSymbolInNativeObj" c_lookupSymbolInNativeObj :: Ptr LoadedDLL -> CString -> IO (Ptr a) foreign import ccall unsafe "initLinker_" c_initLinker_ :: CInt -> IO () foreign import ccall unsafe "lookupSymbol" c_lookupSymbol :: CString -> IO (Ptr a) foreign import ccall unsafe "loadArchive" c_loadArchive :: CFilePath -> IO Int ===================================== rts/Linker.c ===================================== @@ -77,10 +77,16 @@ # include #endif +#if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) +# include "linker/LoadNativeObjPosix.h" +#endif + #if defined(dragonfly_HOST_OS) #include #endif +#define UNUSED(x) (void)(x) + /* * Note [iconv and FreeBSD] * ~~~~~~~~~~~~~~~~~~~~~~~~ @@ -130,7 +136,7 @@ extern void iconv(); - Indexing (e.g. ocVerifyImage and ocGetNames) - Initialization (e.g. ocResolve) - RunInit (e.g. ocRunInit) - - Lookup (e.g. lookupSymbol) + - Lookup (e.g. lookupSymbol/lookupSymbolInNativeObj) This is to enable lazy loading of symbols. Eager loading is problematic as it means that all symbols must be available, even those which we will @@ -417,11 +423,8 @@ static int linker_init_done = 0 ; #if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) static void *dl_prog_handle; -static regex_t re_invalid; -static regex_t re_realso; -#if defined(THREADED_RTS) -Mutex dl_mutex; // mutex to protect dlopen/dlerror critical section -#endif +regex_t re_invalid; +regex_t re_realso; #endif void initLinker (void) @@ -455,9 +458,6 @@ initLinker_ (int retain_cafs) #if defined(THREADED_RTS) initMutex(&linker_mutex); -#if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) - initMutex(&dl_mutex); -#endif #endif symhash = allocStrHashTable(); @@ -520,9 +520,6 @@ exitLinker( void ) { if (linker_init_done == 1) { regfree(&re_invalid); regfree(&re_realso); -#if defined(THREADED_RTS) - closeMutex(&dl_mutex); -#endif } #endif if (linker_init_done == 1) { @@ -556,87 +553,6 @@ exitLinker( void ) { # if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) -/* Suppose in ghci we load a temporary SO for a module containing - f = 1 - and then modify the module, recompile, and load another temporary - SO with - f = 2 - Then as we don't unload the first SO, dlsym will find the - f = 1 - symbol whereas we want the - f = 2 - symbol. We therefore need to keep our own SO handle list, and - try SOs in the right order. */ - -typedef - struct _OpenedSO { - struct _OpenedSO* next; - void *handle; - } - OpenedSO; - -/* A list thereof. */ -static OpenedSO* openedSOs = NULL; - -static void * -internal_dlopen(const char *dll_name, const char **errmsg_ptr) -{ - OpenedSO* o_so; - void *hdl; - - // omitted: RTLD_NOW - // see http://www.haskell.org/pipermail/cvs-ghc/2007-September/038570.html - IF_DEBUG(linker, - debugBelch("internal_dlopen: dll_name = '%s'\n", dll_name)); - - //-------------- Begin critical section ------------------ - // This critical section is necessary because dlerror() is not - // required to be reentrant (see POSIX -- IEEE Std 1003.1-2008) - // Also, the error message returned must be copied to preserve it - // (see POSIX also) - - ACQUIRE_LOCK(&dl_mutex); - - // When dlopen() loads a profiled dynamic library, it calls the - // ctors which will call registerCcsList() to append the defined - // CostCentreStacks to CCS_LIST. This execution path starting from - // addDLL() was only protected by dl_mutex previously. However, - // another thread may be doing other things with the RTS linker - // that transitively calls refreshProfilingCCSs() which also - // accesses CCS_LIST, and those execution paths are protected by - // linker_mutex. So there's a risk of data race that may lead to - // segfaults (#24423), and we need to ensure the ctors are also - // protected by ccs_mutex. -#if defined(PROFILING) - ACQUIRE_LOCK(&ccs_mutex); -#endif - - hdl = dlopen(dll_name, RTLD_LAZY|RTLD_LOCAL); /* see Note [RTLD_LOCAL] */ - -#if defined(PROFILING) - RELEASE_LOCK(&ccs_mutex); -#endif - - if (hdl == NULL) { - /* dlopen failed; return a ptr to the error msg. */ - char *errmsg = dlerror(); - if (errmsg == NULL) errmsg = "addDLL: unknown error"; - char *errmsg_copy = stgMallocBytes(strlen(errmsg)+1, "addDLL"); - strcpy(errmsg_copy, errmsg); - *errmsg_ptr = errmsg_copy; - } else { - o_so = stgMallocBytes(sizeof(OpenedSO), "addDLL"); - o_so->handle = hdl; - o_so->next = openedSOs; - openedSOs = o_so; - } - - RELEASE_LOCK(&dl_mutex); - //--------------- End critical section ------------------- - - return hdl; -} - /* Note [RTLD_LOCAL] ~~~~~~~~~~~~~~~~~ @@ -657,11 +573,10 @@ internal_dlopen(const char *dll_name, const char **errmsg_ptr) static void * internal_dlsym(const char *symbol) { - OpenedSO* o_so; void *v; - // We acquire dl_mutex as concurrent dl* calls may alter dlerror - ACQUIRE_LOCK(&dl_mutex); + // concurrent dl* calls may alter dlerror + ASSERT_LOCK_HELD(&linker_mutex); // clears dlerror dlerror(); @@ -669,20 +584,19 @@ internal_dlsym(const char *symbol) { // look in program first v = dlsym(dl_prog_handle, symbol); if (dlerror() == NULL) { - RELEASE_LOCK(&dl_mutex); IF_DEBUG(linker, debugBelch("internal_dlsym: found symbol '%s' in program\n", symbol)); return v; } - for (o_so = openedSOs; o_so != NULL; o_so = o_so->next) { - v = dlsym(o_so->handle, symbol); - if (dlerror() == NULL) { + for (ObjectCode *nc = loaded_objects; nc; nc = nc->next_loaded_object) { + if (nc->type == DYNAMIC_OBJECT) { + v = dlsym(nc->dlopen_handle, symbol); + if (dlerror() == NULL) { IF_DEBUG(linker, debugBelch("internal_dlsym: found symbol '%s' in shared object\n", symbol)); - RELEASE_LOCK(&dl_mutex); return v; + } } } - RELEASE_LOCK(&dl_mutex); IF_DEBUG(linker, debugBelch("internal_dlsym: looking for symbol '%s' in special cases\n", symbol)); # define SPECIAL_SYMBOL(sym) \ @@ -722,98 +636,42 @@ internal_dlsym(const char *symbol) { // we failed to find the symbol return NULL; } +# endif -void *lookupSymbolInDLL(void *handle, const char *symbol_name) +void *lookupSymbolInNativeObj(void *handle, const char *symbol_name) { + ACQUIRE_LOCK(&linker_mutex); + #if defined(OBJFORMAT_MACHO) + // The Mach-O standard says ccall symbols representing a function are prefixed with _ + // https://math-atlas.sourceforge.net/devel/assembly/MachORuntime.pdf CHECK(symbol_name[0] == '_'); symbol_name = symbol_name+1; #endif - - ACQUIRE_LOCK(&dl_mutex); // dlsym alters dlerror +#if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) void *result = dlsym(handle, symbol_name); - RELEASE_LOCK(&dl_mutex); +#elif defined(OBJFORMAT_PEi386) + void *result = lookupSymbolInDLL_PEi386(symbol_name, handle, NULL, NULL); +#else + void* result; + UNUSED(handle); + UNUSED(symbol_name); + barf("lookupSymbolInNativeObj: Unsupported platform"); +#endif + + RELEASE_LOCK(&linker_mutex); return result; } -# endif -void *addDLL(pathchar* dll_name, const char **errmsg_ptr) +const char *addDLL(pathchar* dll_name) { -# if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) - /* ------------------- ELF DLL loader ------------------- */ - -#define NMATCH 5 - regmatch_t match[NMATCH]; - void *handle; - const char *errmsg; - FILE* fp; - size_t match_length; -#define MAXLINE 1000 - char line[MAXLINE]; - int result; - - IF_DEBUG(linker, debugBelch("addDLL: dll_name = '%s'\n", dll_name)); - handle = internal_dlopen(dll_name, &errmsg); - - if (handle != NULL) { - return handle; - } - - // GHC #2615 - // On some systems (e.g., Gentoo Linux) dynamic files (e.g. libc.so) - // contain linker scripts rather than ELF-format object code. This - // code handles the situation by recognizing the real object code - // file name given in the linker script. - // - // If an "invalid ELF header" error occurs, it is assumed that the - // .so file contains a linker script instead of ELF object code. - // In this case, the code looks for the GROUP ( ... ) linker - // directive. If one is found, the first file name inside the - // parentheses is treated as the name of a dynamic library and the - // code attempts to dlopen that file. If this is also unsuccessful, - // an error message is returned. - - // see if the error message is due to an invalid ELF header - IF_DEBUG(linker, debugBelch("errmsg = '%s'\n", errmsg)); - result = regexec(&re_invalid, errmsg, (size_t) NMATCH, match, 0); - IF_DEBUG(linker, debugBelch("result = %i\n", result)); - if (result == 0) { - // success -- try to read the named file as a linker script - match_length = (size_t) stg_min((match[1].rm_eo - match[1].rm_so), - MAXLINE-1); - strncpy(line, (errmsg+(match[1].rm_so)),match_length); - line[match_length] = '\0'; // make sure string is null-terminated - IF_DEBUG(linker, debugBelch("file name = '%s'\n", line)); - if ((fp = __rts_fopen(line, "r")) == NULL) { - *errmsg_ptr = errmsg; // return original error if open fails - return NULL; - } - // try to find a GROUP or INPUT ( ... ) command - while (fgets(line, MAXLINE, fp) != NULL) { - IF_DEBUG(linker, debugBelch("input line = %s", line)); - if (regexec(&re_realso, line, (size_t) NMATCH, match, 0) == 0) { - // success -- try to dlopen the first named file - IF_DEBUG(linker, debugBelch("match%s\n","")); - line[match[2].rm_eo] = '\0'; - stgFree((void*)errmsg); // Free old message before creating new one - handle = internal_dlopen(line+match[2].rm_so, errmsg_ptr); - break; - } - // if control reaches here, no GROUP or INPUT ( ... ) directive - // was found and the original error message is returned to the - // caller - } - fclose(fp); + char *errmsg; + if (loadNativeObj(dll_name, &errmsg)) { + return NULL; + } else { + ASSERT(errmsg != NULL); + return errmsg; } - return handle; - -# elif defined(OBJFORMAT_PEi386) - // FIXME - return addDLL_PEi386(dll_name, NULL); - -# else - barf("addDLL: not implemented on this platform"); -# endif } /* ----------------------------------------------------------------------------- @@ -1246,10 +1104,10 @@ void freeObjectCode (ObjectCode *oc) } if (oc->type == DYNAMIC_OBJECT) { -#if defined(OBJFORMAT_ELF) - ACQUIRE_LOCK(&dl_mutex); - freeNativeCode_ELF(oc); - RELEASE_LOCK(&dl_mutex); +#if defined(OBJFORMAT_ELF) || defined(darwin_HOST_OS) + ACQUIRE_LOCK(&linker_mutex); + freeNativeCode_POSIX(oc); + RELEASE_LOCK(&linker_mutex); #else barf("freeObjectCode: This shouldn't happen"); #endif @@ -1911,12 +1769,20 @@ HsInt purgeObj (pathchar *path) return r; } +ObjectCode *lookupObjectByPath(pathchar *path) { + for (ObjectCode *o = objects; o; o = o->next) { + if (0 == pathcmp(o->fileName, path)) { + return o; + } + } + return NULL; +} + OStatus getObjectLoadStatus_ (pathchar *path) { - for (ObjectCode *o = objects; o; o = o->next) { - if (0 == pathcmp(o->fileName, path)) { - return o->status; - } + ObjectCode *oc = lookupObjectByPath(path); + if (oc) { + return oc->status; } return OBJECT_NOT_LOADED; } @@ -2001,27 +1867,35 @@ addSection (Section *s, SectionKind kind, SectionAlloc alloc, size, kind )); } -#define UNUSED(x) (void)(x) - -#if defined(OBJFORMAT_ELF) void * loadNativeObj (pathchar *path, char **errmsg) { + IF_DEBUG(linker, debugBelch("loadNativeObj: path = '%" PATH_FMT "'\n", path)); ACQUIRE_LOCK(&linker_mutex); - void *r = loadNativeObj_ELF(path, errmsg); - RELEASE_LOCK(&linker_mutex); - return r; -} + +#if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) + void *r = loadNativeObj_POSIX(path, errmsg); +#elif defined(OBJFORMAT_PEi386) + void *r = NULL; + *errmsg = (char*)addDLL_PEi386(path, (HINSTANCE*)&r); #else -void * STG_NORETURN -loadNativeObj (pathchar *path, char **errmsg) -{ - UNUSED(path); + void *r; UNUSED(errmsg); barf("loadNativeObj: not implemented on this platform"); -} #endif -HsInt unloadNativeObj (void *handle) +#if defined(OBJFORMAT_ELF) + if (!r) { + // Check if native object may be a linker script and try loading a native + // object from it + r = loadNativeObjFromLinkerScript_ELF(errmsg); + } +#endif + + RELEASE_LOCK(&linker_mutex); + return r; +} + +static HsInt unloadNativeObj_(void *handle) { bool unloadedAnyObj = false; @@ -2054,11 +1928,18 @@ HsInt unloadNativeObj (void *handle) if (unloadedAnyObj) { return 1; } else { - errorBelch("unloadObjNativeObj_ELF: can't find `%p' to unload", handle); + errorBelch("unloadObjNativeObj_: can't find `%p' to unload", handle); return 0; } } +HsInt unloadNativeObj(void *handle) { + ACQUIRE_LOCK(&linker_mutex); + HsInt r = unloadNativeObj_(handle); + RELEASE_LOCK(&linker_mutex); + return r; +} + /* ----------------------------------------------------------------------------- * Segment management */ ===================================== rts/LinkerInternals.h ===================================== @@ -404,10 +404,6 @@ extern Elf_Word shndx_table_uninit_label; #if defined(THREADED_RTS) extern Mutex linker_mutex; - -#if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) -extern Mutex dl_mutex; -#endif #endif /* THREADED_RTS */ /* Type of an initializer */ @@ -507,9 +503,9 @@ HsInt loadArchive_ (pathchar *path); #define USE_CONTIGUOUS_MMAP 0 #endif - HsInt isAlreadyLoaded( pathchar *path ); OStatus getObjectLoadStatus_ (pathchar *path); +ObjectCode *lookupObjectByPath(pathchar *path); HsInt loadOc( ObjectCode* oc ); ObjectCode* mkOc( ObjectType type, pathchar *path, char *image, int imageSize, bool mapped, pathchar *archiveMemberName, ===================================== rts/RtsSymbols.c ===================================== @@ -508,6 +508,7 @@ extern char **environ; SymI_HasDataProto(stg_block_putmvar) \ MAIN_CAP_SYM \ SymI_HasProto(addDLL) \ + SymI_HasProto(loadNativeObj) \ SymI_HasProto(addLibrarySearchPath) \ SymI_HasProto(removeLibrarySearchPath) \ SymI_HasProto(findSystemLibrary) \ @@ -618,7 +619,7 @@ extern char **environ; SymI_HasProto(purgeObj) \ SymI_HasProto(insertSymbol) \ SymI_HasProto(lookupSymbol) \ - SymI_HasProto(lookupSymbolInDLL) \ + SymI_HasProto(lookupSymbolInNativeObj) \ SymI_HasDataProto(stg_makeStablePtrzh) \ SymI_HasDataProto(stg_mkApUpd0zh) \ SymI_HasDataProto(stg_labelThreadzh) \ ===================================== rts/include/rts/Linker.h ===================================== @@ -90,10 +90,10 @@ void *loadNativeObj( pathchar *path, char **errmsg ); Takes the handle returned from loadNativeObj() as an argument. */ HsInt unloadNativeObj( void *handle ); -/* load a dynamic library */ -void *addDLL(pathchar* dll_name, const char **errmsg); +void *lookupSymbolInNativeObj(void *handle, const char *symbol_name); -void *lookupSymbolInDLL(void *handle, const char *symbol_name); +/* load a dynamic library */ +const char *addDLL(pathchar* dll_name); /* add a path to the library search path */ HsPtr addLibrarySearchPath(pathchar* dll_path); ===================================== rts/linker/Elf.c ===================================== @@ -27,11 +27,15 @@ #include "sm/OSMem.h" #include "linker/util.h" #include "linker/elf_util.h" +#include "linker/LoadNativeObjPosix.h" +#include #include #include #include #include +#include // regex is already used by dlopen() so this is OK + // to use here without requiring an additional lib #if defined(HAVE_DLFCN_H) #include #endif @@ -2073,155 +2077,6 @@ int ocRunFini_ELF( ObjectCode *oc ) return true; } -/* - * Shared object loading - */ - -#if defined(HAVE_DLINFO) -struct piterate_cb_info { - ObjectCode *nc; - void *l_addr; /* base virtual address of the loaded code */ -}; - -static int loadNativeObjCb_(struct dl_phdr_info *info, - size_t _size STG_UNUSED, void *data) { - struct piterate_cb_info *s = (struct piterate_cb_info *) data; - - // This logic mimicks _dl_addr_inside_object from glibc - // For reference: - // int - // internal_function - // _dl_addr_inside_object (struct link_map *l, const ElfW(Addr) addr) - // { - // int n = l->l_phnum; - // const ElfW(Addr) reladdr = addr - l->l_addr; - // - // while (--n >= 0) - // if (l->l_phdr[n].p_type == PT_LOAD - // && reladdr - l->l_phdr[n].p_vaddr >= 0 - // && reladdr - l->l_phdr[n].p_vaddr < l->l_phdr[n].p_memsz) - // return 1; - // return 0; - // } - - if ((void*) info->dlpi_addr == s->l_addr) { - int n = info->dlpi_phnum; - while (--n >= 0) { - if (info->dlpi_phdr[n].p_type == PT_LOAD) { - NativeCodeRange* ncr = - stgMallocBytes(sizeof(NativeCodeRange), "loadNativeObjCb_"); - ncr->start = (void*) ((char*) s->l_addr + info->dlpi_phdr[n].p_vaddr); - ncr->end = (void*) ((char*) ncr->start + info->dlpi_phdr[n].p_memsz); - - ncr->next = s->nc->nc_ranges; - s->nc->nc_ranges = ncr; - } - } - } - return 0; -} -#endif /* defined(HAVE_DLINFO) */ - -static void copyErrmsg(char** errmsg_dest, char* errmsg) { - if (errmsg == NULL) errmsg = "loadNativeObj_ELF: unknown error"; - *errmsg_dest = stgMallocBytes(strlen(errmsg)+1, "loadNativeObj_ELF"); - strcpy(*errmsg_dest, errmsg); -} - -// need dl_mutex -void freeNativeCode_ELF (ObjectCode *nc) { - dlclose(nc->dlopen_handle); - - NativeCodeRange *ncr = nc->nc_ranges; - while (ncr) { - NativeCodeRange* last_ncr = ncr; - ncr = ncr->next; - stgFree(last_ncr); - } -} - -void * loadNativeObj_ELF (pathchar *path, char **errmsg) -{ - ObjectCode* nc; - void *hdl, *retval; - - IF_DEBUG(linker, debugBelch("loadNativeObj_ELF %" PATH_FMT "\n", path)); - - retval = NULL; - ACQUIRE_LOCK(&dl_mutex); - - /* Loading the same object multiple times will lead to chaos - * as we will have two ObjectCodes but one underlying dlopen - * handle. Fail if this happens. - */ - if (getObjectLoadStatus_(path) != OBJECT_NOT_LOADED) { - copyErrmsg(errmsg, "loadNativeObj_ELF: Already loaded"); - goto dlopen_fail; - } - - nc = mkOc(DYNAMIC_OBJECT, path, NULL, 0, false, NULL, 0); - - foreignExportsLoadingObject(nc); - hdl = dlopen(path, RTLD_NOW|RTLD_LOCAL); - nc->dlopen_handle = hdl; - foreignExportsFinishedLoadingObject(); - if (hdl == NULL) { - /* dlopen failed; save the message in errmsg */ - copyErrmsg(errmsg, dlerror()); - goto dlopen_fail; - } - -#if defined(HAVE_DLINFO) - struct link_map *map; - if (dlinfo(hdl, RTLD_DI_LINKMAP, &map) == -1) { - /* dlinfo failed; save the message in errmsg */ - copyErrmsg(errmsg, dlerror()); - goto dlinfo_fail; - } - - hdl = NULL; // pass handle ownership to nc - - struct piterate_cb_info piterate_info = { - .nc = nc, - .l_addr = (void *) map->l_addr - }; - dl_iterate_phdr(loadNativeObjCb_, &piterate_info); - if (!nc->nc_ranges) { - copyErrmsg(errmsg, "dl_iterate_phdr failed to find obj"); - goto dl_iterate_phdr_fail; - } -#endif /* defined (HAVE_DLINFO) */ - - insertOCSectionIndices(nc); - - nc->next_loaded_object = loaded_objects; - loaded_objects = nc; - - retval = nc->dlopen_handle; - -#if defined(PROFILING) - // collect any new cost centres that were defined in the loaded object. - refreshProfilingCCSs(); -#endif - - goto success; - -dl_iterate_phdr_fail: - // already have dl_mutex - freeNativeCode_ELF(nc); -dlinfo_fail: - if (hdl) dlclose(hdl); -dlopen_fail: -success: - - RELEASE_LOCK(&dl_mutex); - - IF_DEBUG(linker, debugBelch("loadNativeObj_ELF result=%p\n", retval)); - - return retval; -} - - /* * PowerPC & X86_64 ELF specifics */ ===================================== rts/linker/Elf.h ===================================== @@ -14,7 +14,6 @@ int ocResolve_ELF ( ObjectCode* oc ); int ocRunInit_ELF ( ObjectCode* oc ); int ocRunFini_ELF ( ObjectCode* oc ); int ocAllocateExtras_ELF ( ObjectCode *oc ); -void freeNativeCode_ELF ( ObjectCode *nc ); -void *loadNativeObj_ELF ( pathchar *path, char **errmsg ); +void *loadNativeObjFromLinkerScript_ELF( char **errmsg ); #include "EndPrivate.h" ===================================== rts/linker/LoadNativeObjPosix.c ===================================== @@ -0,0 +1,210 @@ +#include "LinkerInternals.h" +#include "Rts.h" + +#if defined(OBJFORMAT_ELF) || defined(OBJFORMAT_MACHO) + +#include "CheckUnload.h" +#include "ForeignExports.h" +#include "RtsUtils.h" +#include "Profiling.h" + +#include "linker/LoadNativeObjPosix.h" + +#if defined(HAVE_DLFCN_H) +#include +#endif + +#if defined(HAVE_DLINFO) +#include +#endif + +#include + +/* + * Shared object loading + */ + +#if defined(HAVE_DLINFO) +struct piterate_cb_info { + ObjectCode *nc; + void *l_addr; /* base virtual address of the loaded code */ +}; + +static int loadNativeObjCb_(struct dl_phdr_info *info, + size_t _size STG_UNUSED, void *data) { + struct piterate_cb_info *s = (struct piterate_cb_info *) data; + + // This logic mimicks _dl_addr_inside_object from glibc + // For reference: + // int + // internal_function + // _dl_addr_inside_object (struct link_map *l, const ElfW(Addr) addr) + // { + // int n = l->l_phnum; + // const ElfW(Addr) reladdr = addr - l->l_addr; + // + // while (--n >= 0) + // if (l->l_phdr[n].p_type == PT_LOAD + // && reladdr - l->l_phdr[n].p_vaddr >= 0 + // && reladdr - l->l_phdr[n].p_vaddr < l->l_phdr[n].p_memsz) + // return 1; + // return 0; + // } + + if ((void*) info->dlpi_addr == s->l_addr) { + int n = info->dlpi_phnum; + while (--n >= 0) { + if (info->dlpi_phdr[n].p_type == PT_LOAD) { + NativeCodeRange* ncr = + stgMallocBytes(sizeof(NativeCodeRange), "loadNativeObjCb_"); + ncr->start = (void*) ((char*) s->l_addr + info->dlpi_phdr[n].p_vaddr); + ncr->end = (void*) ((char*) ncr->start + info->dlpi_phdr[n].p_memsz); + + ncr->next = s->nc->nc_ranges; + s->nc->nc_ranges = ncr; + } + } + } + return 0; +} +#endif /* defined(HAVE_DLINFO) */ + +static void copyErrmsg(char** errmsg_dest, char* errmsg) { + if (errmsg == NULL) errmsg = "loadNativeObj_POSIX: unknown error"; + *errmsg_dest = stgMallocBytes(strlen(errmsg)+1, "loadNativeObj_POSIX"); + strcpy(*errmsg_dest, errmsg); +} + +void freeNativeCode_POSIX (ObjectCode *nc) { + ASSERT_LOCK_HELD(&linker_mutex); + + dlclose(nc->dlopen_handle); + + NativeCodeRange *ncr = nc->nc_ranges; + while (ncr) { + NativeCodeRange* last_ncr = ncr; + ncr = ncr->next; + stgFree(last_ncr); + } +} + +void * loadNativeObj_POSIX (pathchar *path, char **errmsg) +{ + ObjectCode* nc; + void *hdl, *retval; + + ASSERT_LOCK_HELD(&linker_mutex); + + IF_DEBUG(linker, debugBelch("loadNativeObj_POSIX %" PATH_FMT "\n", path)); + + retval = NULL; + + + /* If we load the same object multiple times, just return the + * already-loaded handle. Note that this is broken if unloadNativeObj + * is used, as we don’t do any reference counting; see #24345. + */ + ObjectCode *existing_oc = lookupObjectByPath(path); + if (existing_oc && existing_oc->status != OBJECT_UNLOADED) { + if (existing_oc->type == DYNAMIC_OBJECT) { + retval = existing_oc->dlopen_handle; + goto success; + } + copyErrmsg(errmsg, "loadNativeObj_POSIX: already loaded as non-dynamic object"); + goto dlopen_fail; + } + + nc = mkOc(DYNAMIC_OBJECT, path, NULL, 0, false, NULL, 0); + + foreignExportsLoadingObject(nc); + + // When dlopen() loads a profiled dynamic library, it calls the ctors which + // will call registerCcsList() to append the defined CostCentreStacks to + // CCS_LIST. However, another thread may be doing other things with the RTS + // linker that transitively calls refreshProfilingCCSs() which also accesses + // CCS_LIST. So there's a risk of data race that may lead to segfaults + // (#24423), and we need to ensure the ctors are also protected by + // ccs_mutex. +#if defined(PROFILING) + ACQUIRE_LOCK(&ccs_mutex); +#endif + + // If we HAVE_DLINFO, we use RTLD_NOW rather than RTLD_LAZY because we want + // to learn eagerly about all external functions. Otherwise, there is no + // additional advantage to being eager, so it is better to be lazy and only bind + // functions when needed for better performance. + int dlopen_mode; +#if defined(HAVE_DLINFO) + dlopen_mode = RTLD_NOW; +#else + dlopen_mode = RTLD_LAZY; +#endif + + hdl = dlopen(path, dlopen_mode|RTLD_LOCAL); /* see Note [RTLD_LOCAL] */ + nc->dlopen_handle = hdl; + nc->status = OBJECT_READY; + +#if defined(PROFILING) + RELEASE_LOCK(&ccs_mutex); +#endif + + foreignExportsFinishedLoadingObject(); + + if (hdl == NULL) { + /* dlopen failed; save the message in errmsg */ + copyErrmsg(errmsg, dlerror()); + goto dlopen_fail; + } + +#if defined(HAVE_DLINFO) + struct link_map *map; + if (dlinfo(hdl, RTLD_DI_LINKMAP, &map) == -1) { + /* dlinfo failed; save the message in errmsg */ + copyErrmsg(errmsg, dlerror()); + goto dlinfo_fail; + } + + hdl = NULL; // pass handle ownership to nc + + struct piterate_cb_info piterate_info = { + .nc = nc, + .l_addr = (void *) map->l_addr + }; + dl_iterate_phdr(loadNativeObjCb_, &piterate_info); + if (!nc->nc_ranges) { + copyErrmsg(errmsg, "dl_iterate_phdr failed to find obj"); + goto dl_iterate_phdr_fail; + } +#endif /* defined (HAVE_DLINFO) */ + + insertOCSectionIndices(nc); + + nc->next_loaded_object = loaded_objects; + loaded_objects = nc; + + retval = nc->dlopen_handle; + +#if defined(PROFILING) + // collect any new cost centres that were defined in the loaded object. + refreshProfilingCCSs(); +#endif + + goto success; + +#if defined(HAVE_DLINFO) +dl_iterate_phdr_fail: +#endif + freeNativeCode_POSIX(nc); +#if defined(HAVE_DLINFO) +dlinfo_fail: +#endif + if (hdl) dlclose(hdl); +dlopen_fail: +success: + + IF_DEBUG(linker, debugBelch("loadNativeObj_POSIX result=%p\n", retval)); + + return retval; +} + +#endif /* elf + macho */ ===================================== rts/linker/LoadNativeObjPosix.h ===================================== @@ -0,0 +1,11 @@ +#pragma once + +#include "Rts.h" +#include "LinkerInternals.h" + +#include "BeginPrivate.h" + +void freeNativeCode_POSIX ( ObjectCode *nc ); +void *loadNativeObj_POSIX ( pathchar *path, char **errmsg ); + +#include "EndPrivate.h" ===================================== rts/linker/PEi386.c ===================================== @@ -867,6 +867,7 @@ error: stgFree(buf); char* errormsg = stgMallocBytes(sizeof(char) * 80, "addDLL_PEi386"); + if (loaded) *loaded = NULL; snprintf(errormsg, 80, "addDLL: %" PATH_FMT " or dependencies not loaded. (Win32 error %lu)", dll_name, GetLastError()); /* LoadLibrary failed; return a ptr to the error msg. */ return errormsg; @@ -1014,7 +1015,10 @@ bool checkAndLoadImportLibrary( pathchar* arch_name, char* member_name, FILE* f stgFree(dllName); IF_DEBUG(linker, debugBelch("loadArchive: read symbol %s from lib `%" PATH_FMT "'\n", symbol, dll)); - const char* result = addDLL(dll); + // We must call `addDLL_PEi386` directly rather than `addDLL` because `addDLL` + // is now a wrapper around `loadNativeObj` which acquires a lock which we + // already have here. + const char* result = addDLL_PEi386(dll, NULL); stgFree(image); @@ -1138,47 +1142,57 @@ SymbolAddr* lookupSymbolInDLLs ( const SymbolName* lbl, ObjectCode *dependent ) { OpenedDLL* o_dll; - SymbolAddr* sym; + SymbolAddr* res; - for (o_dll = opened_dlls; o_dll != NULL; o_dll = o_dll->next) { - /* debugBelch("look in %ls for %s\n", o_dll->name, lbl); */ + for (o_dll = opened_dlls; o_dll != NULL; o_dll = o_dll->next) + if ((res = lookupSymbolInDLL_PEi386(lbl, o_dll->instance, o_dll->name, dependent))) + return res; + return NULL; +} - sym = GetProcAddress(o_dll->instance, lbl+STRIP_LEADING_UNDERSCORE); - if (sym != NULL) { - /*debugBelch("found %s in %s\n", lbl+1,o_dll->name);*/ - return sym; - } +SymbolAddr* +lookupSymbolInDLL_PEi386 ( const SymbolName* lbl, HINSTANCE instance, pathchar* dll_name STG_UNUSED, ObjectCode *dependent) +{ + SymbolAddr* sym; - // TODO: Drop this - /* Ticket #2283. - Long description: http://support.microsoft.com/kb/132044 - tl;dr: - If C/C++ compiler sees __declspec(dllimport) ... foo ... - it generates call *__imp_foo, and __imp_foo here has exactly - the same semantics as in __imp_foo = GetProcAddress(..., "foo") - */ - if (sym == NULL && strncmp (lbl, "__imp_", 6) == 0) { - sym = GetProcAddress(o_dll->instance, - lbl + 6 + STRIP_LEADING_UNDERSCORE); - if (sym != NULL) { - SymbolAddr** indirect = m32_alloc(dependent->rw_m32, sizeof(SymbolAddr*), 8); - if (indirect == NULL) { - barf("lookupSymbolInDLLs: Failed to allocation indirection"); - } - *indirect = sym; - IF_DEBUG(linker, - debugBelch("warning: %s from %S is linked instead of %s\n", - lbl+6+STRIP_LEADING_UNDERSCORE, o_dll->name, lbl)); - return (void*) indirect; - } - } + /* debugBelch("look in %ls for %s\n", dll_name, lbl); */ - sym = GetProcAddress(o_dll->instance, lbl); + sym = GetProcAddress(instance, lbl+STRIP_LEADING_UNDERSCORE); + if (sym != NULL) { + /*debugBelch("found %s in %ls\n", lbl+STRIP_LEADING_UNDERSCORE,dll_name);*/ + return sym; + } + + // TODO: Drop this + /* Ticket #2283. + Long description: http://support.microsoft.com/kb/132044 + tl;dr: + If C/C++ compiler sees __declspec(dllimport) ... foo ... + it generates call *__imp_foo, and __imp_foo here has exactly + the same semantics as in __imp_foo = GetProcAddress(..., "foo") + */ + if (sym == NULL && strncmp (lbl, "__imp_", 6) == 0) { + sym = GetProcAddress(instance, + lbl + 6 + STRIP_LEADING_UNDERSCORE); if (sym != NULL) { - /*debugBelch("found %s in %s\n", lbl,o_dll->name);*/ - return sym; + SymbolAddr** indirect = m32_alloc(dependent->rw_m32, sizeof(SymbolAddr*), 8); + if (indirect == NULL) { + barf("lookupSymbolInDLLs: Failed to allocation indirection"); + } + *indirect = sym; + IF_DEBUG(linker, + debugBelch("warning: %s from %S is linked instead of %s\n", + lbl+6+STRIP_LEADING_UNDERSCORE, dll_name, lbl)); + return (void*) indirect; } } + + sym = GetProcAddress(instance, lbl); + if (sym != NULL) { + /*debugBelch("found %s in %s\n", lbl,dll_name);*/ + return sym; + } + return NULL; } ===================================== rts/linker/PEi386.h ===================================== @@ -60,6 +60,7 @@ bool ocRunFini_PEi386 ( ObjectCode *oc ); bool ocGetNames_PEi386 ( ObjectCode* oc ); bool ocVerifyImage_PEi386 ( ObjectCode* oc ); SymbolAddr *lookupSymbol_PEi386(SymbolName *lbl, ObjectCode *dependent, SymType *type); +SymbolAddr *lookupSymbolInDLL_PEi386 (const SymbolName* lbl, HINSTANCE instance, pathchar* dll_name, ObjectCode *dependent); /* See Note [mingw-w64 name decoration scheme] */ /* We use myindex to calculate array addresses, rather than ===================================== rts/rts.cabal.in ===================================== @@ -624,6 +624,7 @@ library linker/Elf.c linker/InitFini.c linker/LoadArchive.c + linker/LoadNativeObjPosix.c linker/M32Alloc.c linker/MMap.c linker/MachO.c ===================================== testsuite/tests/ghci/linking/dyn/T3372.hs ===================================== @@ -1,3 +1,6 @@ +-- Note: This test exercises running concurrent GHCi sessions, but +-- although this test is expected to pass, running concurrent GHCi +-- sessions is currently broken in other ways; see #24345. {-# LANGUAGE MagicHash #-} module Main where ===================================== testsuite/tests/rts/linker/lookupSymbolInNativeObj/Makefile ===================================== @@ -0,0 +1,9 @@ +TOP=../../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +lookupSymbolInNativeObj1: + '$(TEST_HC)' -shared -dynamic obj.c -o libobj.so + '$(TEST_HC)' -no-hs-main -dynamic lookupSymbolInNativeObj1.c -o main + ./main + ===================================== testsuite/tests/rts/linker/lookupSymbolInNativeObj/all.T ===================================== @@ -0,0 +1,5 @@ +test('lookupSymbolInNativeObj1', + [unless(have_dynamic(), skip), + extra_files(['obj.c'])], + makefile_test, []) + ===================================== testsuite/tests/rts/linker/lookupSymbolInNativeObj/lookupSymbolInNativeObj1.c ===================================== @@ -0,0 +1,54 @@ +#include "Rts.h" + +#if defined(mingw32_HOST_OS) +#define PATH_STR(str) L##str +#else +#define PATH_STR(str) str +#endif + +typedef void (*hello_t)(); + +int main(int argc, char *argv[]) +{ + RtsConfig conf = defaultRtsConfig; + conf.rts_opts_enabled = RtsOptsAll; + hs_init_ghc(&argc, &argv, conf); + + initLinker_(0); + + int ok; + char *errmsg; + void *obj = loadNativeObj("./libobj.so", &errmsg); + if (!obj) { + barf("loadNativeObj failed: %s", errmsg); + } + + hello_t sym; + const char* lbl; + +#if defined(darwin_HOST_OS) + // mach-o symbols are prefixed with _ + lbl = "_hello"; +#else + lbl = "hello"; +#endif + + sym = lookupSymbolInNativeObj(obj, lbl); + if (sym == NULL) { + barf("lookupSymbolInNativeObj failed unexpectedly"); + } + sym(); + +#if defined(darwin_HOST_OS) + lbl = "_hello_world"; +#else + lbl = "hello_world"; +#endif + + sym = lookupSymbolInNativeObj(obj, lbl); + if (sym != NULL) { + barf("lookupSymbolInNativeObj succeeded unexpectedly"); + } + + return 0; +} ===================================== testsuite/tests/rts/linker/lookupSymbolInNativeObj/lookupSymbolInNativeObj1.stdout ===================================== @@ -0,0 +1 @@ +hello world ===================================== testsuite/tests/rts/linker/lookupSymbolInNativeObj/obj.c ===================================== @@ -0,0 +1,5 @@ +#include + +void hello() { + printf("hello world\n"); +} View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ab9e921aa85aaea8ed7359793e7b61e52a479645...40cf835c0cc735980143d5a6bd80e56e2e19bb60 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ab9e921aa85aaea8ed7359793e7b61e52a479645...40cf835c0cc735980143d5a6bd80e56e2e19bb60 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 17:16:55 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Sat, 08 Jun 2024 13:16:55 -0400 Subject: [Git][ghc/ghc][wip/T23415-9.8] 7 commits: testsuite: Ignore stderr in T8089 Message-ID: <6664920719911_3096f9432748c171017@gitlab.mail> Ben Gamari pushed to branch wip/T23415-9.8 at Glasgow Haskell Compiler / GHC Commits: 1c08e245 by Ben Gamari at 2024-02-23T12:31:12+05:30 testsuite: Ignore stderr in T8089 Otherwise spurious "Killed: 9" messages to stderr may cause the test to fail. Fixes #24361. (cherry picked from commit e693a4e8589bad35588c51fccc87f4388e7d5874) - - - - - 06aefbc5 by Rodrigo Mesquita at 2024-06-08T13:14:37-04:00 rts: free error message before returning Fixes a memory leak in rts/linker/PEi386.c (cherry picked from commit dd530bb7e22e953e4cec64a5fd6c39fddc152c6f) - - - - - 60dea85d by Cheng Shao at 2024-06-08T13:14:51-04:00 rts: add missing ccs_mutex guard to internal_dlopen See added comment for details. Closes #24423. - - - - - a3c8a0dd by Alexis King at 2024-06-08T13:16:42-04:00 linker: Avoid linear search when looking up Haskell symbols via dlsym See the primary Note [Looking up symbols in the relevant objects] for a more in-depth explanation. When dynamically loading a Haskell symbol (typical when running a splice or GHCi expression), before this commit we would search for the symbol in all dynamic libraries that were loaded. However, this could be very inefficient when too many packages are loaded (which can happen if there are many package dependencies) because the time to lookup the would be linear in the number of packages loaded. This commit drastically improves symbol loading performance by introducing a mapping from units to the handles of corresponding loaded dlls. These handles are returned by dlopen when we load a dll, and can then be used to look up in a specific dynamic library. Looking up a given Name is now much more precise because we can get lookup its unit in the mapping and lookup the symbol solely in the handles of the dynamic libraries loaded for that unit. In one measurement, the wait time before the expression was executed went from +-38 seconds down to +-2s. This commit also includes Note [Symbols may not be found in pkgs_loaded], explaining the fallback to the old behaviour in case no dll can be found in the unit mapping for a given Name. Fixes #23415 Co-authored-by: Rodrigo Mesquita (@alt-romes) (cherry picked from commit e008a19a7f9e8f22aada0b4e1049744f49d39aad) - - - - - 3bc7c99a by Rodrigo Mesquita at 2024-06-08T13:16:43-04:00 rts: Make addDLL a wrapper around loadNativeObj Rewrite the implementation of `addDLL` as a wrapper around the more principled `loadNativeObj` rts linker function. The latter should be preferred while the former is preserved for backwards compatibility. `loadNativeObj` was previously only available on ELF platforms, so this commit further refactors the rts linker to transform loadNativeObj_ELF into loadNativeObj_POSIX, which is available in ELF and MachO platforms. The refactor made it possible to remove the `dl_mutex` mutex in favour of always using `linker_mutex` (rather than a combination of both). Lastly, we implement `loadNativeObj` for Windows too. (cherry picked from commit dcfaa190e1e1182a2efe4e2f601affbb832a49bb) - - - - - c7e9dc6d by Rodrigo Mesquita at 2024-06-08T13:16:43-04:00 Use symbol cache in internal interpreter too This commit makes the symbol cache that was used by the external interpreter available for the internal interpreter too. This follows from the analysis in #23415 that suggests the internal interpreter could benefit from this cache too, and that there is no good reason not to have the cache for it too. It also makes it a bit more uniform to have the symbol cache range over both the internal and external interpreter. This commit also refactors the cache into a function which is used by both `lookupSymbol` and also by `lookupSymbolInDLL`, extending the caching logic to `lookupSymbolInDLL` too. (cherry picked from commit 12931698261a1cee6a00b731d143270cd60e5f2d) - - - - - cb5761c0 by Ben Gamari at 2024-06-08T13:16:43-04:00 testsuite: Add test for lookupSymbolInNativeObj (cherry picked from commit dccd3ea159b03cc1972cf47ee3cf8bda73ec0c5a) - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Driver/Plugins.hs - compiler/GHC/Linker/Loader.hs - compiler/GHC/Linker/MacOS.hs - compiler/GHC/Linker/Types.hs - compiler/GHC/Runtime/Interpreter.hs - compiler/GHC/Runtime/Interpreter/JS.hs - compiler/GHC/Runtime/Interpreter/Types.hs - libraries/base/tests/all.T - libraries/ghci/GHCi/Message.hs - libraries/ghci/GHCi/ObjLink.hs - libraries/ghci/GHCi/Run.hs - rts/Linker.c - rts/LinkerInternals.h - rts/Profiling.c - rts/Profiling.h - rts/RtsSymbols.c - rts/include/rts/Linker.h - rts/linker/Elf.c - rts/linker/Elf.h - + rts/linker/LoadNativeObjPosix.c - + rts/linker/LoadNativeObjPosix.h - rts/linker/PEi386.c - rts/linker/PEi386.h - rts/rts.cabal.in - testsuite/tests/ghci/linking/dyn/T3372.hs - testsuite/tests/rts/linker/T2615.hs - + testsuite/tests/rts/linker/lookupSymbolInNativeObj/Makefile The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/40cf835c0cc735980143d5a6bd80e56e2e19bb60...cb5761c093712456dacdc9afd9f727d8174509db -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/40cf835c0cc735980143d5a6bd80e56e2e19bb60...cb5761c093712456dacdc9afd9f727d8174509db You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 17:57:16 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 08 Jun 2024 13:57:16 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw Message-ID: <66649b7c9f2e9_3096f9494c77c1790e@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - e1b52bfe by Ben Gamari at 2024-06-08T13:57:08-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 73e5e1f9 by Ben Gamari at 2024-06-08T13:57:08-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 6892cef5 by Ben Gamari at 2024-06-08T13:57:09-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 11 changed files: - CODEOWNERS - compiler/GHC/CmmToAsm/X86/Instr.hs - libraries/ghc-internal/CHANGELOG.md - libraries/ghc-internal/prologue.txt - libraries/ghc-internal/src/GHC/Internal/Exception.hs - rts/Inlines.c - rts/include/Stg.h - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 Changes: ===================================== CODEOWNERS ===================================== @@ -60,6 +60,7 @@ /libraries/base/ @hvr /libraries/ghci/ @simonmar /libraries/template-haskell/ @rae +/testsuite/tests/interface-stability/ @core-libraries [Internal utilities and libraries] /utils/iserv-proxy/ @angerman @simonmar ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -198,10 +198,13 @@ data Instr -- Moves. | MOV Format Operand Operand - -- ^ N.B. when used with the 'II64' 'Format', the source + -- ^ N.B. Due to AT&T assembler quirks, when used with 'II64' + -- 'Format' immediate source and memory target operand, the source -- operand is interpreted to be a 32-bit sign-extended value. - -- True 64-bit operands need to be moved with @MOVABS@, which we - -- currently don't use. + -- True 64-bit operands need to be either first moved to a register or moved + -- with @MOVABS@; we currently do not use this instruction in GHC. + -- See https://stackoverflow.com/questions/52434073/whats-the-difference-between-the-x86-64-att-instructions-movq-and-movabsq. + | MOVD Format Operand Operand -- ^ MOVD/MOVQ SSE2 instructions -- (bitcast between a general purpose -- register and a float register). ===================================== libraries/ghc-internal/CHANGELOG.md ===================================== @@ -1,5 +1,5 @@ # Revision history for `ghc-internal` -## 0.1.0.0 -- YYYY-mm-dd +## 9.1001.0 -- 2024-05-01 -* First version. Released on an unsuspecting world. +* Package created containing implementation moved from `base`. ===================================== libraries/ghc-internal/prologue.txt ===================================== @@ -1,3 +1,2 @@ -This package contains the @Prelude@ and its support libraries, and a large -collection of useful libraries ranging from data structures to parsing -combinators and debugging utilities. +This package contains the implementation of GHC's standard libraries and is +not intended for use by end-users. ===================================== libraries/ghc-internal/src/GHC/Internal/Exception.hs ===================================== @@ -79,7 +79,7 @@ import GHC.Internal.Exception.Type -- WARNING: You may want to use 'throwIO' instead so that your pure code -- stays exception-free. throw :: forall (r :: RuntimeRep). forall (a :: TYPE r). forall e. - (?callStack :: CallStack, Exception e) => e -> a + (HasCallStack, Exception e) => e -> a throw e = let !se = unsafePerformIO (toExceptionWithBacktrace e) in raise# se ===================================== rts/Inlines.c ===================================== @@ -1,6 +1,7 @@ -// all functions declared with EXTERN_INLINE in the header files get -// compiled for real here, just in case the definition was not inlined -// at some call site: +// All functions declared with EXTERN_INLINE in the header files get +// compiled for real here. Some of them are called by Cmm (e.g. +// recordClosureMutated) and therefore the real thing needs to reside +// in Inlines.o for Cmm ccall to work. #define KEEP_INLINES #include "rts/PosixSource.h" #include "Rts.h" ===================================== rts/include/Stg.h ===================================== @@ -114,57 +114,19 @@ * 'Portable' inlining: * INLINE_HEADER is for inline functions in header files (macros) * STATIC_INLINE is for inline functions in source files - * EXTERN_INLINE is for functions that we want to inline sometimes - * (we also compile a static version of the function; see Inlines.c) + * EXTERN_INLINE is for functions that may be called in Cmm + * (we also compile a static version of an EXTERN_INLINE function; see Inlines.c) */ -// We generally assume C99 semantics albeit these two definitions work fine even -// when gnu90 semantics are active (i.e. when __GNUC_GNU_INLINE__ is defined or -// when a GCC older than 4.2 is used) -// -// The problem, however, is with 'extern inline' whose semantics significantly -// differs between gnu90 and C99 #define INLINE_HEADER static inline #define STATIC_INLINE static inline -// Figure out whether `__attributes__((gnu_inline))` is needed -// to force gnu90-style 'external inline' semantics. -#if defined(FORCE_GNU_INLINE) -// disable auto-detection since HAVE_GNU_INLINE has been defined externally -#elif defined(__GNUC_GNU_INLINE__) && __GNUC__ == 4 && __GNUC_MINOR__ == 2 -// GCC 4.2.x didn't properly support C99 inline semantics (GCC 4.3 was the first -// release to properly support C99 inline semantics), and therefore warned when -// using 'extern inline' while in C99 mode unless `__attributes__((gnu_inline))` -// was explicitly set. -# define FORCE_GNU_INLINE 1 -#endif - -#if defined(FORCE_GNU_INLINE) -// Force compiler into gnu90 semantics -# if defined(KEEP_INLINES) -# define EXTERN_INLINE inline __attribute__((gnu_inline)) -# else -# define EXTERN_INLINE extern inline __attribute__((gnu_inline)) -# endif -#elif defined(__GNUC_GNU_INLINE__) -// we're currently in gnu90 inline mode by default and -// __attribute__((gnu_inline)) may not be supported, so better leave it off -# if defined(KEEP_INLINES) -# define EXTERN_INLINE inline -# else -# define EXTERN_INLINE extern inline -# endif -#else -// Assume C99 semantics (yes, this curiously results in swapped definitions!) -// This is the preferred branch, and at some point we may drop support for -// compilers not supporting C99 semantics altogether. +// See comment in rts/Inlines.c for explanation. # if defined(KEEP_INLINES) # define EXTERN_INLINE extern inline # else -# define EXTERN_INLINE inline +# define EXTERN_INLINE static inline # endif -#endif - /* * GCC attributes ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5319,7 +5319,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5288,7 +5288,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5465,7 +5465,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5319,7 +5319,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aae3e02fbd6b3dacf32808d5540a611e40824756...6892cef54462c3a036afc7690ec427282f1942dd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/aae3e02fbd6b3dacf32808d5540a611e40824756...6892cef54462c3a036afc7690ec427282f1942dd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 19:49:51 2024 From: gitlab at gitlab.haskell.org (Cyrill Brunner (@Adowrath)) Date: Sat, 08 Jun 2024 15:49:51 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/adowrath/removing-rdrname-from-syntax-type Message-ID: <6664b5dfa2320_f3800252c7c4661d@gitlab.mail> Cyrill Brunner pushed new branch wip/adowrath/removing-rdrname-from-syntax-type at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/adowrath/removing-rdrname-from-syntax-type You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 20:39:22 2024 From: gitlab at gitlab.haskell.org (Alexander Foremny (@aforemny)) Date: Sat, 08 Jun 2024 16:39:22 -0400 Subject: [Git][ghc/ghc][wip/aforemny/ast] AST: remove occurrences of GHC.Unit.Module.Warnings Message-ID: <6664c17aeaa7c_f38007b96c049157@gitlab.mail> Alexander Foremny pushed to branch wip/aforemny/ast at Glasgow Haskell Compiler / GHC Commits: 1d8a2b02 by Alexander Foremny at 2024-06-08T22:38:47+02:00 AST: remove occurrences of GHC.Unit.Module.Warnings - - - - - 12 changed files: - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Utils.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Unit/Module/Warnings.hs - compiler/Language/Haskell/Syntax/Decls.hs Changes: ===================================== compiler/GHC/Core/InstEnv.hs ===================================== @@ -55,7 +55,6 @@ import GHC.Types.Name.Set import GHC.Types.Basic import GHC.Types.Id import GHC.Generics (Generic) -import Data.Data ( Data ) import Data.List.NonEmpty ( NonEmpty (..), nonEmpty ) import qualified Data.List.NonEmpty as NE import Data.Maybe ( isJust ) @@ -114,7 +113,6 @@ data ClsInst -- See Note [Implementation of deprecated instances] -- in GHC.Tc.Solver.Dict } - deriving Data -- | A fuzzy comparison function for class instances, intended for sorting -- instances before displaying them to the user. ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -23,6 +23,8 @@ module GHC.Hs.Instances where import Data.Data hiding ( Fixity ) +import Language.Haskell.Syntax.Decls (WarningTxt(..)) + import GHC.Prelude import GHC.Hs.Extension import GHC.Hs.Binds @@ -34,6 +36,8 @@ import GHC.Hs.Pat import GHC.Hs.ImpExp import GHC.Parser.Annotation +import GHC.Core.InstEnv (ClsInst(..)) + -- --------------------------------------------------------------------- -- Data derivations from GHC.Hs----------------------------------------- @@ -578,3 +582,11 @@ deriving instance Data XXPatGhcTc deriving instance Data XViaStrategyPs -- --------------------------------------------------------------------- + +deriving instance Data ClsInst + +-- --------------------------------------------------------------------- + +deriving instance Data (WarningTxt GhcPs) +deriving instance Data (WarningTxt GhcRn) +deriving instance Data (WarningTxt GhcTc) ===================================== compiler/GHC/Parser.y ===================================== @@ -1994,7 +1994,7 @@ maybe_warning_pragma :: { Maybe (LWarningTxt GhcPs) } (AnnPragma (mo $1) (mc $4) (fst $ unLoc $3))} | {- empty -} { Nothing } -warning_category :: { Maybe (LocatedE InWarningCategory) } +warning_category :: { Maybe (LocatedE (InWarningCategory GhcPs)) } : 'in' STRING { Just (reLoc $ sLL $1 $> $ InWarningCategory (epTok $1) (getSTRINGs $2) (reLoc $ sL1 $2 $ mkWarningCategory (getSTRING $2))) } | {- empty -} { Nothing } ===================================== compiler/GHC/Rename/Module.hs ===================================== @@ -312,11 +312,15 @@ rnWarningTxt (WarningTxt mb_cat st wst) = do unless (validWarningCategory cat) $ addErrAt (locA loc) (TcRnInvalidWarningCategory cat) wst' <- traverse (traverse rnHsDoc) wst - pure (WarningTxt mb_cat st wst') + pure (WarningTxt (fmap rnInWarningCategory <$> mb_cat) st wst') rnWarningTxt (DeprecatedTxt st wst) = do wst' <- traverse (traverse rnHsDoc) wst pure (DeprecatedTxt st wst') +rnInWarningCategory :: InWarningCategory GhcPs -> InWarningCategory GhcRn +rnInWarningCategory (InWarningCategory {iwc_in, iwc_st, iwc_wc}) = + InWarningCategory iwc_in iwc_st iwc_wc + rnLWarningTxt :: LWarningTxt GhcPs -> RnM (LWarningTxt GhcRn) rnLWarningTxt (L loc warn) = L loc <$> rnWarningTxt warn ===================================== compiler/GHC/Rename/Utils.hs ===================================== @@ -73,7 +73,6 @@ import GHC.Data.Bag ( mapBagM, headMaybe ) import Control.Monad import GHC.Settings.Constants ( mAX_TUPLE_SIZE, mAX_CTUPLE_SIZE ) import GHC.Unit.Module -import GHC.Unit.Module.Warnings ( WarningTxt(..) ) import GHC.Iface.Load import qualified GHC.LanguageExtensions as LangExt ===================================== compiler/GHC/Tc/Deriv.hs ===================================== @@ -35,7 +35,6 @@ import GHC.Core.FamInstEnv import GHC.Tc.Gen.HsType import GHC.Core.TyCo.Rep import GHC.Core.TyCo.Ppr ( pprTyVars ) -import GHC.Unit.Module.Warnings import GHC.Rename.Bind import GHC.Rename.Env ===================================== compiler/GHC/Tc/Deriv/Utils.hs ===================================== @@ -52,7 +52,6 @@ import GHC.Core.Type import GHC.Hs import GHC.Driver.Session import GHC.Unit.Module (getModule) -import GHC.Unit.Module.Warnings import GHC.Unit.Module.ModIface (mi_fix) import GHC.Types.Fixity.Env (lookupFixity) ===================================== compiler/GHC/Tc/Errors/Types.hs ===================================== @@ -217,7 +217,6 @@ import Language.Haskell.Syntax.Basic (FieldLabelString(..)) import qualified Data.List.NonEmpty as NE import Data.Typeable (Typeable) -import GHC.Unit.Module.Warnings (WarningCategory, WarningTxt) import qualified GHC.Internal.TH.Syntax as TH import GHC.Generics ( Generic ) ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -64,7 +64,6 @@ import GHC.Core.PatSyn import GHC.Core.Multiplicity ( scaledThing ) import GHC.Unit.Module -import GHC.Unit.Module.Warnings import GHC.Types.Id import GHC.Types.Name import GHC.Types.Name.Reader ===================================== compiler/GHC/Tc/Utils/Instantiate.hs ===================================== @@ -93,7 +93,6 @@ import GHC.Utils.Unique (sameUnique) import GHC.Unit.State import GHC.Unit.External -import GHC.Unit.Module.Warnings import Data.List ( mapAccumL ) import qualified Data.List.NonEmpty as NE ===================================== compiler/GHC/Unit/Module/Warnings.hs ===================================== @@ -16,7 +16,6 @@ module GHC.Unit.Module.Warnings , mkWarningCategory , defaultWarningCategory , validWarningCategory - , InWarningCategory(..) , fromWarningCategory , WarningCategorySet @@ -60,78 +59,18 @@ import GHC.Hs.Extension import GHC.Parser.Annotation import GHC.Utils.Outputable -import GHC.Utils.Binary import GHC.Unicode import Language.Haskell.Syntax.Extension +import Language.Haskell.Syntax.Decls (WarningTxt(..), InWarningCategory(..), WarningCategory(..)) -import Data.Data import Data.List (isPrefixOf) -import GHC.Generics ( Generic ) -import Control.DeepSeq -{- -Note [Warning categories] -~~~~~~~~~~~~~~~~~~~~~~~~~ -See GHC Proposal 541 for the design of the warning categories feature: -https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0541-warning-pragmas-with-categories.rst -A WARNING pragma may be annotated with a category such as "x-partial" written -after the 'in' keyword, like this: - - {-# WARNING in "x-partial" head "This function is partial..." #-} - -This is represented by the 'Maybe (Located WarningCategory)' field in -'WarningTxt'. The parser will accept an arbitrary string as the category name, -then the renamer (in 'rnWarningTxt') will check it contains only valid -characters, so we can generate a nicer error message than a parse error. - -The corresponding warnings can then be controlled with the -Wx-partial, --Wno-x-partial, -Werror=x-partial and -Wwarn=x-partial flags. Such a flag is -distinguished from an 'unrecognisedWarning' by the flag parser testing -'validWarningCategory'. The 'x-' prefix means we can still usually report an -unrecognised warning where the user has made a mistake. - -A DEPRECATED pragma may not have a user-defined category, and is always treated -as belonging to the special category 'deprecations'. Similarly, a WARNING -pragma without a category belongs to the 'deprecations' category. -Thus the '-Wdeprecations' flag will enable all of the following: - - {-# WARNING in "deprecations" foo "This function is deprecated..." #-} - {-# WARNING foo "This function is deprecated..." #-} - {-# DEPRECATED foo "This function is deprecated..." #-} - -The '-Wwarnings-deprecations' flag is supported for backwards compatibility -purposes as being equivalent to '-Wdeprecations'. - -The '-Wextended-warnings' warning group collects together all warnings with -user-defined categories, so they can be enabled or disabled -collectively. Moreover they are treated as being part of other warning groups -such as '-Wdefault' (see 'warningGroupIncludesExtendedWarnings'). - -'DynFlags' and 'DiagOpts' each contain a set of enabled and a set of fatal -warning categories, just as they do for the finite enumeration of 'WarningFlag's -built in to GHC. These are represented as 'WarningCategorySet's to allow for -the possibility of them being infinite. - --} - -data InWarningCategory - = InWarningCategory - { iwc_in :: !(EpToken "in"), - iwc_st :: !SourceText, - iwc_wc :: (LocatedE WarningCategory) - } deriving Data - -fromWarningCategory :: WarningCategory -> InWarningCategory +fromWarningCategory :: WarningCategory -> InWarningCategory (GhcPass pass) fromWarningCategory wc = InWarningCategory noAnn NoSourceText (noLocA wc) - --- See Note [Warning categories] -newtype WarningCategory = WarningCategory FastString - deriving (Binary, Data, Eq, Outputable, Show, Uniquable, NFData) - mkWarningCategory :: FastString -> WarningCategory mkWarningCategory = WarningCategory @@ -184,6 +123,9 @@ elemWarningCategorySet :: WarningCategory -> WarningCategorySet -> Bool elemWarningCategorySet c (FiniteWarningCategorySet s) = c `elementOfUniqSet` s elemWarningCategorySet c (CofiniteWarningCategorySet s) = not (c `elementOfUniqSet` s) +-- TODO(orphans) This can eventually be moved into `Ghc.Types.Unique` +deriving instance Uniquable WarningCategory + -- | Insert an element into a warning category set. insertWarningCategorySet :: WarningCategory -> WarningCategorySet -> WarningCategorySet insertWarningCategorySet c (FiniteWarningCategorySet s) = FiniteWarningCategorySet (addOneToUniqSet s c) @@ -196,57 +138,43 @@ deleteWarningCategorySet c (CofiniteWarningCategorySet s) = CofiniteWarningCateg type LWarningTxt pass = XRec pass (WarningTxt pass) --- | Warning Text --- --- reason/explanation from a WARNING or DEPRECATED pragma -data WarningTxt pass - = WarningTxt - (Maybe (LocatedE InWarningCategory)) - -- ^ Warning category attached to this WARNING pragma, if any; - -- see Note [Warning categories] - SourceText - [LocatedE (WithHsDocIdentifiers StringLiteral pass)] - | DeprecatedTxt - SourceText - [LocatedE (WithHsDocIdentifiers StringLiteral pass)] - deriving Generic - -- | To which warning category does this WARNING or DEPRECATED pragma belong? -- See Note [Warning categories]. -warningTxtCategory :: WarningTxt pass -> WarningCategory +warningTxtCategory :: WarningTxt (GhcPass pass) -> WarningCategory warningTxtCategory (WarningTxt (Just (L _ (InWarningCategory _ _ (L _ cat)))) _ _) = cat warningTxtCategory _ = defaultWarningCategory -- | The message that the WarningTxt was specified to output -warningTxtMessage :: WarningTxt p -> [LocatedE (WithHsDocIdentifiers StringLiteral p)] +warningTxtMessage :: WarningTxt (GhcPass p) -> [LocatedE (WithHsDocIdentifiers StringLiteral (GhcPass p))] warningTxtMessage (WarningTxt _ _ m) = m warningTxtMessage (DeprecatedTxt _ m) = m -- | True if the 2 WarningTxts have the same category and messages -warningTxtSame :: WarningTxt p1 -> WarningTxt p2 -> Bool +warningTxtSame :: WarningTxt (GhcPass p1) -> WarningTxt (GhcPass p2) -> Bool warningTxtSame w1 w2 = warningTxtCategory w1 == warningTxtCategory w2 && literal_message w1 == literal_message w2 && same_type where - literal_message :: WarningTxt p -> [StringLiteral] + literal_message :: WarningTxt (GhcPass p) -> [StringLiteral] literal_message = map (hsDocString . unLoc) . warningTxtMessage same_type | DeprecatedTxt {} <- w1, DeprecatedTxt {} <- w2 = True | WarningTxt {} <- w1, WarningTxt {} <- w2 = True | otherwise = False -deriving instance Eq InWarningCategory - -deriving instance (Eq (IdP pass)) => Eq (WarningTxt pass) -deriving instance (Data pass, Data (IdP pass)) => Data (WarningTxt pass) - type instance Anno (WarningTxt (GhcPass pass)) = SrcSpanAnnP -instance Outputable InWarningCategory where +-- TODO(orphans) This can eventually be moved to `GHC.Utils.Outputable` +instance Outputable (InWarningCategory (GhcPass p)) where ppr (InWarningCategory _ _ wt) = text "in" <+> doubleQuotes (ppr wt) +type instance Anno WarningCategory = EpaLocation + +-- TODO(orphans) This can eventually be moved to `GHC.Utils.Outputable` +deriving instance Outputable WarningCategory + -instance Outputable (WarningTxt pass) where +instance Outputable (WarningTxt (GhcPass p)) where ppr (WarningTxt mcat lsrc ws) = case lsrc of NoSourceText -> pp_ws ws @@ -267,8 +195,10 @@ pp_ws ws <+> vcat (punctuate comma (map (ppr . unLoc) ws)) <+> text "]" +type instance Anno (InWarningCategory p) = EpaLocation +type instance Anno (WithHsDocIdentifiers StringLiteral p) = EpaLocation -pprWarningTxtForMsg :: WarningTxt p -> SDoc +pprWarningTxtForMsg :: WarningTxt (GhcPass p) -> SDoc pprWarningTxtForMsg (WarningTxt _ _ ws) = doubleQuotes (vcat (map (ftext . sl_fs . hsDocString . unLoc) ws)) pprWarningTxtForMsg (DeprecatedTxt _ ds) @@ -314,7 +244,7 @@ type DeclWarnOccNames pass = [(OccName, WarningTxt pass)] -- | Names that are deprecated as exports type ExportWarnNames pass = [(Name, WarningTxt pass)] -deriving instance Eq (IdP pass) => Eq (Warnings pass) +deriving instance Eq (IdP (GhcPass p)) => Eq (Warnings (GhcPass p)) emptyWarn :: Warnings p emptyWarn = WarnSome [] [] ===================================== compiler/Language/Haskell/Syntax/Decls.hs ===================================== @@ -1,3 +1,16 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} @@ -87,6 +100,8 @@ module Language.Haskell.Syntax.Decls ( -- * Grouping HsGroup(..), hsGroupInstDecls, + -- * Warnings + WarningTxt(..), InWarningCategory(..), WarningCategory(..) ) where -- friends: @@ -105,10 +120,10 @@ import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CC import GHC.Types.Fixity (LexicalFixity) import GHC.Core.Type (Specificity) -import GHC.Unit.Module.Warnings (WarningTxt) import GHC.Utils.Panic.Plain ( assert ) -import GHC.Hs.Doc (LHsDoc) -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST +import GHC.Hs.Doc (LHsDoc, WithHsDocIdentifiers) -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST +import GHC.Types.SourceText (StringLiteral, SourceText) import Control.Monad import Data.Data hiding (TyCon, Fixity, Infix) @@ -124,6 +139,11 @@ import qualified Data.List import Data.Foldable import Data.Traversable import Data.List.NonEmpty (NonEmpty (..)) +import GHC.Data.FastString (FastString) +import GHC.Generics (Generic) +import Control.DeepSeq (NFData) +import GHC.Parser.Annotation (EpToken) +import GHC.Utils.Binary(Binary) {- ************************************************************************ @@ -1783,3 +1803,87 @@ data RoleAnnotDecl pass -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | XRoleAnnotDecl !(XXRoleAnnotDecl pass) + +-- | Warning Text +-- +-- reason/explanation from a WARNING or DEPRECATED pragma +data WarningTxt pass + = WarningTxt + (Maybe (XRec pass (InWarningCategory pass))) + -- ^ Warning category attached to this WARNING pragma, if any; + -- see Note [Warning categories] + SourceText + [XRec pass (WithHsDocIdentifiers StringLiteral pass)] + | DeprecatedTxt + SourceText + [XRec pass (WithHsDocIdentifiers StringLiteral pass)] + deriving (Generic) + +deriving instance + ( Eq (XRec pass (InWarningCategory pass)), + Eq (XRec pass (WithHsDocIdentifiers StringLiteral pass)) + ) => Eq (WarningTxt pass) + +{- +Note [Warning categories] +~~~~~~~~~~~~~~~~~~~~~~~~~ +See GHC Proposal 541 for the design of the warning categories feature: +https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0541-warning-pragmas-with-categories.rst + +A WARNING pragma may be annotated with a category such as "x-partial" written +after the 'in' keyword, like this: + + {-# WARNING in "x-partial" head "This function is partial..." #-} + +This is represented by the 'Maybe (Located WarningCategory)' field in +'WarningTxt'. The parser will accept an arbitrary string as the category name, +then the renamer (in 'rnWarningTxt') will check it contains only valid +characters, so we can generate a nicer error message than a parse error. + +The corresponding warnings can then be controlled with the -Wx-partial, +-Wno-x-partial, -Werror=x-partial and -Wwarn=x-partial flags. Such a flag is +distinguished from an 'unrecognisedWarning' by the flag parser testing +'validWarningCategory'. The 'x-' prefix means we can still usually report an +unrecognised warning where the user has made a mistake. + +A DEPRECATED pragma may not have a user-defined category, and is always treated +as belonging to the special category 'deprecations'. Similarly, a WARNING +pragma without a category belongs to the 'deprecations' category. +Thus the '-Wdeprecations' flag will enable all of the following: + + {-# WARNING in "deprecations" foo "This function is deprecated..." #-} + {-# WARNING foo "This function is deprecated..." #-} + {-# DEPRECATED foo "This function is deprecated..." #-} + +The '-Wwarnings-deprecations' flag is supported for backwards compatibility +purposes as being equivalent to '-Wdeprecations'. + +The '-Wextended-warnings' warning group collects together all warnings with +user-defined categories, so they can be enabled or disabled +collectively. Moreover they are treated as being part of other warning groups +such as '-Wdefault' (see 'warningGroupIncludesExtendedWarnings'). + +'DynFlags' and 'DiagOpts' each contain a set of enabled and a set of fatal +warning categories, just as they do for the finite enumeration of 'WarningFlag's +built in to GHC. These are represented as 'WarningCategorySet's to allow for +the possibility of them being infinite. + +-} + +data InWarningCategory pass + = InWarningCategory + { iwc_in :: !(EpToken "in"), + iwc_st :: !SourceText, + iwc_wc :: (XRec pass WarningCategory) + } + +deriving instance (Eq (XRec pass WarningCategory)) => Eq (InWarningCategory pass) + +deriving instance Typeable (InWarningCategory pass) + +deriving instance (Data pass, Data (XRec pass WarningCategory)) => Data (InWarningCategory pass) + + +-- See Note [Warning categories] +newtype WarningCategory = WarningCategory FastString + deriving (Binary, Data, Eq, Show, NFData) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1d8a2b02682a4fb1b25827ee63453cc0834f3f55 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1d8a2b02682a4fb1b25827ee63453cc0834f3f55 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 20:56:00 2024 From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge)) Date: Sat, 08 Jun 2024 16:56:00 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T24789_impl Message-ID: <6664c5608c1cc_f380099f3a4493e5@gitlab.mail> Serge S. Gulin pushed new branch wip/T24789_impl at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T24789_impl You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 21:02:20 2024 From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge)) Date: Sat, 08 Jun 2024 17:02:20 -0400 Subject: [Git][ghc/ghc][wip/T24789_impl] 4 commits: Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw Message-ID: <6664c6dcc90b_f3800b1f7ec56228@gitlab.mail> Serge S. Gulin pushed to branch wip/T24789_impl at Glasgow Haskell Compiler / GHC Commits: edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 34ab1e1c by Serge S. Gulin at 2024-06-09T00:01:51+03:00 Unicode: adding compact version of GeneralCategory The following features are applied: 1. Lookup code like Cmm-switches (draft implementation proposed by Sylvain Henry @hsyl20) 2. Nested ifs (logarithmic search vs linear search) (the idea proposed by Sylvain Henry @hsyl20) 3. More compact representation via variable encoding by Huffman - - - - - 19 changed files: - CODEOWNERS - libraries/ghc-internal/src/GHC/Internal/Exception.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs - + libraries/ghc-internal/src/GHC/Internal/Unicode/Huffman.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/GeneralCategory.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/Huffman.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/HuffmanDecode.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/RangeSwitch.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/WordEncoding.hs - libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs - libraries/ghc-internal/tools/ucd2haskell/ucd.sh - libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal - rts/Inlines.c - rts/include/Stg.h - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 Changes: ===================================== CODEOWNERS ===================================== @@ -60,6 +60,7 @@ /libraries/base/ @hvr /libraries/ghci/ @simonmar /libraries/template-haskell/ @rae +/testsuite/tests/interface-stability/ @core-libraries [Internal utilities and libraries] /utils/iserv-proxy/ @angerman @simonmar ===================================== libraries/ghc-internal/src/GHC/Internal/Exception.hs ===================================== @@ -79,7 +79,7 @@ import GHC.Internal.Exception.Type -- WARNING: You may want to use 'throwIO' instead so that your pure code -- stays exception-free. throw :: forall (r :: RuntimeRep). forall (a :: TYPE r). forall e. - (?callStack :: CallStack, Exception e) => e -> a + (HasCallStack, Exception e) => e -> a throw e = let !se = unsafePerformIO (toExceptionWithBacktrace e) in raise# se ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs ===================================== @@ -1,6 +1,9 @@ {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE BangPatterns #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE UnliftedNewtypes #-} +{-# LANGUAGE BlockArguments #-} ----------------------------------------------------------------------------- -- | @@ -18,20 +21,22 @@ ----------------------------------------------------------------------------- module GHC.Internal.Unicode.Bits - ( lookupBit64, - lookupIntN - ) where + ( lookupIntN + , lookupBit64 + , newByteArrayFromWord8List + , byteArrayLookupIntN + , copyAddrToWord8List + , UnicodeByteArray + ) + where -import GHC.Internal.Base (Bool, Int(..), Word(..), Eq(..)) import GHC.Internal.Bits (finiteBitSize, popCount) -import {-# SOURCE #-} GHC.Internal.ByteOrder import GHC.Prim - (Addr#, - indexWordOffAddr#, indexWord8OffAddr#, - andI#, uncheckedIShiftRL#, - and#, word2Int#, uncheckedShiftL#, - word8ToWord#, byteSwap#) -import GHC.Internal.Num ((-)) +import GHC.Internal.ST +import GHC.Internal.Base +import GHC.Internal.Num +import GHC.Internal.List +import GHC.Internal.Word -- | @lookup64 addr index@ looks up the bit stored at bit index @index@ using a -- bitmap starting at the address @addr at . Looks up the 64-bit word containing @@ -49,9 +54,7 @@ lookupBit64 addr# (I# index#) = W# (word## `and#` bitMask##) /= 0 _ -> popCount fbs -- this is a really weird architecture wordIndex# = index# `uncheckedIShiftRL#` logFbs# - word## = case targetByteOrder of - BigEndian -> byteSwap# (indexWordOffAddr# addr# wordIndex#) - LittleEndian -> indexWordOffAddr# addr# wordIndex# + word## = byteSwap# (indexWordOffAddr# addr# wordIndex#) bitIndex# = index# `andI#` fbs# bitMask## = 1## `uncheckedShiftL#` bitIndex# @@ -71,3 +74,38 @@ lookupIntN lookupIntN addr# (I# index#) = let word## = word8ToWord# (indexWord8OffAddr# addr# index#) in I# (word2Int# word##) + +data UnicodeByteArray = UnicodeByteArray !ByteArray# + +byteArrayLookupIntN :: UnicodeByteArray -> Int -> Int +byteArrayLookupIntN ba idx + = let !(UnicodeByteArray addr) = ba + in lookupIntN (byteArrayContents# addr) idx + +newByteArrayFromWord8List :: [Word8] -> UnicodeByteArray +newByteArrayFromWord8List xs = runST $ ST \s0 -> + case newPinnedByteArray# len s0 of + !(# s1, mba #) -> + let s2 = fillByteArray mba 0# xs s1 + in case unsafeFreezeByteArray# mba s2 of + !(# s3, fba #) -> (# s3, UnicodeByteArray fba #) + where + !(I# len) = length xs + + fillByteArray _ _ [] s = s + fillByteArray mba i (y:ys) s = + let !(W8# y#) = y + s' = writeWord8Array# mba i y# s + in fillByteArray mba (i +# 1#) ys s' + +copyAddrToWord8List :: Addr# -> Int -> [Word8] +copyAddrToWord8List addr !(I# len) = runST $ ST \s0 -> + case newByteArray# len s0 of + !(# s1, mba #) -> + let s2 = copyAddrToByteArray# addr mba 0# len s1 + in case unsafeFreezeByteArray# mba s2 of + !(# s3, fba #) -> (# s3, readByteFromArray fba len #) + where + readByteFromArray :: ByteArray# -> Int# -> [Word8] + readByteFromArray ba i = + W8# (indexWord8Array# ba i) : readByteFromArray ba (i +# 1#) ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs ===================================== The diff for this file was not included because it is too large. ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Huffman.hs ===================================== @@ -0,0 +1,53 @@ +-- DO NOT EDIT IT HERE. It is automatically copied from ucd2haskell tool's Generator.HuffmanDecode +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE ExplicitForAll #-} +{-# LANGUAGE TypeApplications #-} + +module GHC.Internal.Unicode.Huffman + ( decodeHuffman + , deserializeHuffman + , HuffmanTree (..) + ) + where + +import GHC.Internal.Word (Word8) +import GHC.Internal.Bits (testBit) +import GHC.Internal.Show (Show (..)) +import GHC.Internal.Base (Bool, Eq, Functor, (.), (++), error, map) +import qualified GHC.Internal.List as L (concatMap) + +data HuffmanTree a + = HTLeaf !a + | HTNode !(HuffmanTree a) !(HuffmanTree a) + deriving stock (Show, Eq, Functor) + +deserializeHuffman :: forall a . (Word8 -> a) -> [Word8] -> HuffmanTree a +deserializeHuffman conv = (\(a, _) -> a) . go + where + go [] = error "Unable to process empty list" + go (0x00:value:rest) = (HTLeaf (conv value), rest) + go (0x01:rest) = + let + (left, rest') = go rest + (right, rest'') = go rest' + in (HTNode left right, rest'') + go v = error ("Unknown type of Huffman tree leaf: " ++ show v) + +decodeHuffman :: HuffmanTree a -> [Word8] -> [a] +decodeHuffman huffman_tree = decodeBits huffman_tree . unpackBits + where + word8ToBools :: Word8 -> [Bool] + word8ToBools w = map (testBit w) [7, 6 .. 0] + + unpackBits :: [Word8] -> [Bool] + unpackBits = L.concatMap word8ToBools + + decodeBits :: HuffmanTree a -> [Bool] -> [a] + decodeBits tree bits = decodeBits' tree bits tree + where + decodeBits' _ [] _ = [] + decodeBits' (HTLeaf c) bs tree' = c : decodeBits' tree' bs tree' + decodeBits' (HTNode l r) (b:bs) tree' = decodeBits' next bs tree' + where next = if b then r else l + ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/GeneralCategory.hs ===================================== @@ -0,0 +1,145 @@ +{-# LANGUAGE BlockArguments #-} +module Generator.GeneralCategory (GeneralCategory (..), generateGeneralCategoryCode) where + +import Generator.RangeSwitch +import Generator.WordEncoding +import Data.List (intercalate) +import Text.Printf (printf) +import Generator.Huffman (mkHuffmanTree, serializeHuffman) + +data GeneralCategory = + Lu|Ll|Lt| --LC + Lm|Lo| --L + Mn|Mc|Me| --M + Nd|Nl|No| --N + Pc|Pd|Ps|Pe|Pi|Pf|Po| --P + Sm|Sc|Sk|So| --S + Zs|Zl|Zp| --Z + Cc|Cf|Cs|Co|Cn --C + deriving (Show, Eq, Ord, Bounded, Enum, Read) + +genEnumBitmap :: + forall a. (Bounded a, Enum a, Show a) => + -- | Function name + String -> + -- | Default value + a -> + -- | List of values to encode + [a] -> + String +genEnumBitmap funcName def as = unlines + [ "{-# INLINE " <> funcName <> " #-}" + , funcName <> " :: Char -> Int" + , funcName <> " c = let n = ord c in if n >= " + <> show (length as) + <> " then " + <> show (fromEnum def) + <> " else lookup_bitmap n" + ] + +generateHaskellCode :: Int -> [GeneralCategory] -> String +generateHaskellCode max_char_length cats = + let (index_tree, all_allocs) = extract [] range_tree + in intercalate "\n" + [ "{-# NOINLINE deserialized_huffman #-}" + , "deserialized_huffman :: HuffmanTree Word8" + , "deserialized_huffman = " + , intercalate " " [" let huffman_tree =", "\"" <> mapToAddrLiteral serialized_huffman "\"#"] + , printf " in deserializeHuffman (\\x -> x) (copyAddrToWord8List huffman_tree %d)" (length serialized_huffman) + , intercalate "\n" (fmap genDecompressed (zip all_allocs [0..])) + , "" + , "{-# NOINLINE lookup_bitmap #-}" + , "lookup_bitmap :: Int -> Int" + , "lookup_bitmap n = " + , printf " (%s)" (genCode' index_tree 2) + ] + where + cases' = rangeCases max_char_length cats + huffmanTree = mkHuffmanTree $ extractLookupIntList cases' + cases_huffman_encoded = rangesToWord8 huffmanTree cases' + range_tree = buildRangeTree cases_huffman_encoded + + serialized_huffman = serializeHuffman toWord8 huffmanTree + + prefixEachLine indent ls = concatMap (\l -> "\n" ++ replicate (indent*2) ' ' ++ l) ls + + genCode' :: (Show a) => RangeTree (Either a Int) -> Int -> String + genCode' (Leaf _ _ cat) _ = show cat + genCode' (Node start _ (Leaf _ endl c_l) (Leaf startr _ c_r)) indent = + prefixEachLine indent + [ printf "({- 1 -} if n < %d then (%s) else (%s))" (endl+1) (genResult start c_l) (genResult startr c_r) + ] + + genCode' (Node start _ (Leaf _ endl c_l) node_r@(Node _ _ _ _)) indent = + prefixEachLine indent + [ printf "({- 2 -}if n < %d then (%s) else (%s))" (endl+1) (genResult start c_l) (genCode' node_r $ indent + 1) + ] + + genCode' (Node _ _ node_l@(Node _ _ _ _) (Leaf startr _ c_r)) indent = + prefixEachLine indent + [ printf "({- 3 -} if n >= %d then (%s) else (%s))" startr (genResult startr c_r) (genCode' node_l $ indent + 1) + ] + + genCode' (Node _ _ node_l@(Node _ endl _ _) node_r@(Node _ _ _ _)) indent = + prefixEachLine indent + [ printf "({- 4 -} if n < %d then (%s) else (%s))" (endl+1) (genCode' node_l $ indent + 1) (genCode' node_r $ indent + 1) + ] + + genResult :: Show a => Int -> Either a Int -> String + genResult _ (Left s) = show s + -- genResult mi (Right idx) = intercalate " " ["lookupIntN (decodeHuffman (toEnum . fromIntegral, deserialized_huffman)", "\"" <> mapToAddrLiteral as "\"#)", "(n -", show mi, ")"] + genResult mi (Right idx) = intercalate " " ["byteArrayLookupIntN", "decompressed_table_" <> show idx, "(n -", show mi, ")"] + + extract :: [[a]] -> RangeTree (Either a [a]) -> (RangeTree (Either a Int), [[a]]) + extract acc (Leaf mi ma (Left v)) = (Leaf mi ma (Left v), acc) + extract acc (Leaf mi ma (Right v)) = (Leaf mi ma (Right (length acc)), acc ++ [v]) + extract acc (Node mi ma lt rt) = + let + (e_lt, l_acc) = extract acc lt + (e_rt, r_acc) = extract l_acc rt + in (Node mi ma e_lt e_rt, r_acc) + + genDecompressed :: forall a. Show a => ([a], Int) -> String + genDecompressed (acc, idx) = + let fn_name = "decompressed_table_" <> show idx + in intercalate "\n" + [ "" + , "{-# NOINLINE " <> fn_name <> " #-}" + , fn_name <> " :: UnicodeByteArray" + , fn_name <> " =" + , intercalate " " [" let compressed = copyAddrToWord8List", "\"" <> mapToAddrLiteral acc "\"#", show (length acc)] + , printf " in newByteArrayFromWord8List (decodeHuffman deserialized_huffman compressed)" + ] + +generateGeneralCategoryCode + :: (String -> String) + -- ^-- How to generate module header where first arg us module name + -> String + -- ^-- Module name + -> Int + -- ^-- Max char length + -> [GeneralCategory] + -- ^-- imported general categories for all symbol list + -> String +generateGeneralCategoryCode mkModuleHeader moduleName char_length cats = + unlines + [ "{-# LANGUAGE NoImplicitPrelude #-}" + , "{-# LANGUAGE MagicHash #-}" + , "{-# LANGUAGE TypeApplications #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(generalCategory)" + , "where" + , "" + , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" + , "import GHC.Internal.Unicode.Bits (UnicodeByteArray, copyAddrToWord8List, newByteArrayFromWord8List, byteArrayLookupIntN)" + , "import GHC.Internal.Unicode.Huffman (HuffmanTree, decodeHuffman, deserializeHuffman)" + , "import GHC.Internal.Num ((-))" + , "import GHC.Internal.Word (Word8)" + , "" + , generateHaskellCode char_length cats + , "" + , genEnumBitmap "generalCategory" Cn (reverse cats) + ] ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/Huffman.hs ===================================== @@ -0,0 +1,83 @@ +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE PackageImports #-} + +module Generator.Huffman + ( mkHuffmanTree + , encodeHuffman + , serializeHuffman + ) + where + +import Data.List (sortBy) +import Data.Ord (comparing) +import Data.Maybe (fromJust) +import Data.Map.Strict (Map) +import qualified Data.Map.Strict as Map +import Data.Word (Word8) +import Data.Bits (shiftL, (.|.)) +import Generator.HuffmanDecode (HuffmanTree (..)) + +data HuffmanTreeFreq a + = HTFLeaf a Int + | HTFNode Int (HuffmanTreeFreq a) (HuffmanTreeFreq a) + deriving stock (Show, Eq, Functor) + +buildHuffmanTree :: Ord a => [(a, Int)] -> HuffmanTree a +buildHuffmanTree freqs = convertTree $ buildTree initialQueue + where + frequency :: HuffmanTreeFreq a -> Int + frequency (HTFLeaf _ f) = f + frequency (HTFNode f _ _) = f + + initialQueue = sortBy (comparing frequency) [HTFLeaf s f | (s, f) <- freqs] + + buildTree [] = error "impossible: empty list is not an appropriate input here" + buildTree [t] = t + buildTree (t1:t2:ts) = + let newNode = HTFNode (frequency t1 + frequency t2) t1 t2 + newQueue = insertBy (comparing frequency) newNode ts + in buildTree newQueue + + insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a] + insertBy _ x [] = [x] + insertBy cmp x ys@(y:ys') + = case cmp x y of + GT -> y : insertBy cmp x ys' + _ -> x : ys + + convertTree :: HuffmanTreeFreq a -> HuffmanTree a + convertTree (HTFLeaf value _) = HTLeaf value + convertTree (HTFNode _ left right) = HTNode (convertTree left) (convertTree right) + +serializeHuffman :: (a -> Word8) -> HuffmanTree a -> [Word8] +serializeHuffman conv (HTLeaf value) = [0x00, conv value] +serializeHuffman conv (HTNode left right) = [0x01] ++ serializeHuffman conv left ++ serializeHuffman conv right + +mkHuffmanTree :: (Ord a) => [a] -> HuffmanTree a +mkHuffmanTree = buildHuffmanTree . Map.toList . huffmanStats + where + huffmanStats :: (Ord a) => [a] -> Map a Int + huffmanStats l = Map.fromListWith (+) [(c, 1) | c <- l] + +encodeHuffman :: (Ord a) => HuffmanTree a -> [a] -> [Word8] +encodeHuffman huffmanTree = packBits . encodeBits (buildHuffmanTable huffmanTree) + where + boolsToWord8 :: [Bool] -> Word8 + boolsToWord8 = foldl (\acc b -> shiftL acc 1 .|. if b then 1 else 0) 0 + + chunksOf :: Int -> [a] -> [[a]] + chunksOf _ [] = [] + chunksOf n xs = take n xs : chunksOf n (drop n xs) + + packBits :: [Bool] -> [Word8] + packBits bits = map boolsToWord8 (chunksOf 8 bits) + + encodeBits :: (Ord a) => Map.Map a [Bool] -> [a] -> [Bool] + encodeBits huffmanTable cc = concatMap (\c -> fromJust $ Map.lookup c huffmanTable) cc + + buildHuffmanTable :: Ord a => HuffmanTree a -> Map a [Bool] + buildHuffmanTable tree = Map.fromList $ buildCodes tree [] + where + buildCodes (HTLeaf s) code = [(s, code)] + buildCodes (HTNode l r) code = buildCodes l (code ++ [False]) ++ buildCodes r (code ++ [True]) ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/HuffmanDecode.hs ===================================== @@ -0,0 +1,52 @@ +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE ExplicitForAll #-} +{-# LANGUAGE TypeApplications #-} + +module Generator.HuffmanDecode + ( decodeHuffman + , deserializeHuffman + , HuffmanTree (..) + ) + where + +import Data.Word (Word8) +import Data.Bits (testBit) +import GHC.Show (Show (..)) +import GHC.Base (Bool, Eq, Functor, (.), (++), error, map) +import qualified GHC.List as L (concatMap) + +data HuffmanTree a + = HTLeaf !a + | HTNode !(HuffmanTree a) !(HuffmanTree a) + deriving stock (Show, Eq, Functor) + +deserializeHuffman :: forall a . (Word8 -> a) -> [Word8] -> HuffmanTree a +deserializeHuffman conv = (\(a, _) -> a) . go + where + go [] = error "Unable to process empty list" + go (0x00:value:rest) = (HTLeaf (conv value), rest) + go (0x01:rest) = + let + (left, rest') = go rest + (right, rest'') = go rest' + in (HTNode left right, rest'') + go v = error ("Unknown type of Huffman tree leaf: " ++ show v) + +decodeHuffman :: HuffmanTree a -> [Word8] -> [a] +decodeHuffman huffman_tree = decodeBits huffman_tree . unpackBits + where + word8ToBools :: Word8 -> [Bool] + word8ToBools w = map (testBit w) [7, 6 .. 0] + + unpackBits :: [Word8] -> [Bool] + unpackBits = L.concatMap word8ToBools + + decodeBits :: HuffmanTree a -> [Bool] -> [a] + decodeBits tree bits = decodeBits' tree bits tree + where + decodeBits' _ [] _ = [] + decodeBits' (HTLeaf c) bs tree' = c : decodeBits' tree' bs tree' + decodeBits' (HTNode l r) (b:bs) tree' = decodeBits' next bs tree' + where next = if b then r else l + ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/RangeSwitch.hs ===================================== @@ -0,0 +1,73 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE BlockArguments #-} +module Generator.RangeSwitch + where + +import Generator.WordEncoding +import Data.Word +import Data.Bifunctor (bimap) +import Generator.Huffman (encodeHuffman) +import Generator.HuffmanDecode (HuffmanTree) + +data Case a = Case + { caseMin :: Int + , caseMax :: Int + , caseConstant :: Either a [a] + } + deriving stock (Show) + +extractLookupIntList :: [Case a] -> [a] +extractLookupIntList = concat . (fmap \(Case _ _ cc) -> either (const []) id cc) + +ranges :: (Enum a, Eq a, Show a) => [a] -> [(Int,Int,a)] +ranges = \case + [] -> [] + (x:xs) -> reverse (go 0 0 x [] xs) + where + go mi ma v rs = \case + [] -> (mi,ma,v):rs + (x:xs) + | x == v -> go mi (ma+1) v rs xs + | otherwise -> go (ma+1) (ma+1) x ((mi,ma,v):rs) xs + +cases :: Int -> [a] -> [(Int,Int,a)] -> [Case a] +cases max_rep all_cats = go + where + go = \case + [] -> [] + (r@(mi,ma,v):rs) + | rangeSize r > max_rep -> Case mi ma (Left v) : go rs + | otherwise -> go_lookup mi ma (Left v) rs + + go_lookup rmi rma mv = \case + [] -> [Case rmi rma mv] + (r@(mi,ma,v):rs) + | rangeSize r > max_rep -> Case rmi rma mv : Case mi ma (Left v) : go rs + | otherwise -> go_lookup rmi ma (Right (take (ma-rmi+1) (drop rmi all_cats))) rs + + rangeSize :: Num a => (a, a, c) -> a + rangeSize (mi, ma, _) = ma - mi + 1 + +rangeCases :: (Enum a, Eq a, Show a) => Int -> [a] -> [Case a] +rangeCases max_char_length cats = cases max_char_length cats (ranges cats) + +data RangeTree a + = Leaf Int Int a + | Node Int Int (RangeTree a) (RangeTree a) + deriving stock (Show) + +buildRangeTree :: [Case a] -> RangeTree (Either a [a]) +buildRangeTree [(Case start end cat)] = Leaf start end cat +buildRangeTree ranges' = + let + mid = length ranges' `div` 2 + (leftRanges, rightRanges) = splitAt mid ranges' + (Case startL _ _) = head leftRanges + (Case _ endR _) = last rightRanges + in Node startL endR (buildRangeTree leftRanges) (buildRangeTree rightRanges) + +rangesToWord8 :: (Show a, Enum a, Ord a) => HuffmanTree a -> [Case a] -> [Case Word8] +rangesToWord8 htree = fmap \(Case mi ma c) -> + Case mi ma $ bimap toWord8 (encodeHuffman htree) c + ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/WordEncoding.hs ===================================== @@ -0,0 +1,40 @@ +module Generator.WordEncoding where + +import Data.Word + +toWord8 :: (Show a, Enum a) => a -> Word8 +toWord8 a = let w = fromEnum a in if 0 <= w && w <= 0xff + then fromIntegral w + else error $ "Cannot convert to Word8: " <> show a + +{-| Encode a list of values as a byte map, using their 'Enum' instance. + +__Note:__ 'Enum' instance must respect the following: + +* @fromEnum minBound >= 0x00@ +* @fromEnum maxBound <= 0xff@ +-} +enumMapToAddrLiteral :: + forall a. (Bounded a, Enum a, Show a) => + -- | Values to encode + [a] -> + -- | String to append + String -> + String +enumMapToAddrLiteral xs cs = foldr go cs xs + where + go :: a -> String -> String + go x acc = '\\' : shows (toWord8 x) acc + +-- Same as enumMapToAddrLiteral but for already converted to Word8 +mapToAddrLiteral :: + forall a. (Show a) => + -- | Values to encode + [a] -> + -- | String to append + String -> + String +mapToAddrLiteral xs cs = foldr go cs xs + where + go :: a -> String -> String + go x acc = '\\' : shows x acc ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs ===================================== @@ -33,6 +33,7 @@ import Streamly.Data.Fold (Fold) import System.Directory (createDirectoryIfMissing) import System.Environment (getEnv) import System.FilePath ((), (<.>)) +import Generator.GeneralCategory (GeneralCategory(Cn), generateGeneralCategoryCode) -- import qualified Data.Set as Set import Streamly.Data.Stream (Stream) @@ -51,17 +52,6 @@ import Prelude hiding (pred) -- Types ------------------------------------------------------------------------------- -data GeneralCategory = - Lu|Ll|Lt| --LC - Lm|Lo| --L - Mn|Mc|Me| --M - Nd|Nl|No| --N - Pc|Pd|Ps|Pe|Pi|Pf|Po| --P - Sm|Sc|Sk|So| --S - Zs|Zl|Zp| --Z - Cc|Cf|Cs|Co|Cn --C - deriving (Show, Bounded, Enum, Read) - data DecompType = DTCanonical | DTCompat | DTFont | DTNoBreak | DTInitial | DTMedial | DTFinal @@ -189,57 +179,6 @@ bitMapToAddrLiteral bs cs = foldr encode cs (unfoldr mkChunks bs) toByte :: [Bool] -> Int toByte xs = sum $ map (\i -> if xs !! i then 1 `shiftL` i else 0) [0..7] -genEnumBitmap :: - forall a. (Bounded a, Enum a, Show a) => - -- | Function name - String -> - -- | Default value - a -> - -- | List of values to encode - [a] -> - String -genEnumBitmap funcName def as = unlines - [ "{-# INLINE " <> funcName <> " #-}" - , funcName <> " :: Char -> Int" - , funcName <> " c = let n = ord c in if n >= " - <> show (length as) - <> " then " - <> show (fromEnum def) - <> " else lookup_bitmap n" - - , "{-# NOINLINE lookup_bitmap #-}" - , "lookup_bitmap :: Int -> Int" - , "lookup_bitmap n = lookupIntN bitmap# n" - , " where" - , " bitmap# = \"" <> enumMapToAddrLiteral as "\"#" - ] - -{-| Encode a list of values as a byte map, using their 'Enum' instance. - -__Note:__ 'Enum' instance must respect the following: - -* @fromEnum minBound >= 0x00@ -* @fromEnum maxBound <= 0xff@ --} -enumMapToAddrLiteral :: - forall a. (Bounded a, Enum a, Show a) => - -- | Values to encode - [a] -> - -- | String to append - String -> - String -enumMapToAddrLiteral xs cs = foldr go cs xs - - where - - go :: a -> String -> String - go x acc = '\\' : shows (toWord8 x) acc - - toWord8 :: a -> Word8 - toWord8 a = let w = fromEnum a in if 0 <= w && w <= 0xff - then fromIntegral w - else error $ "Cannot convert to Word8: " <> show a - {- [NOTE] Disabled generator (normalization) -- This bit of code is duplicated but this duplication allows us to reduce 2 -- dependencies on the executable. @@ -321,21 +260,7 @@ genGeneralCategoryModule moduleName = -- Regular entry else (_generalCategory a : acc, succ (_char a)) - done (acc, _) = unlines - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(generalCategory)" - , "where" - , "" - , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" - , "import GHC.Internal.Unicode.Bits (lookupIntN)" - , "" - , genEnumBitmap "generalCategory" Cn (reverse acc) - ] + done (acc, _) = generateGeneralCategoryCode mkModuleHeader moduleName 220 acc readDecomp :: String -> (Maybe DecompType, Decomp) readDecomp s = ===================================== libraries/ghc-internal/tools/ucd2haskell/ucd.sh ===================================== @@ -71,6 +71,23 @@ run_generator() { # --core-prop XID_Continue \ # --core-prop Pattern_Syntax \ # --core-prop Pattern_White_Space + + echo "-- DO NOT EDIT IT HERE. It is automatically copied from ucd2haskell tool's Generator.HuffmanDecode" > "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + cat "$SCRIPT_DIR/exe/Generator/HuffmanDecode.hs" >> "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + + # See https://stackoverflow.com/a/22084103 + sed -i.bak -e "s/module Generator\.HuffmanDecode/module GHC.Internal.Unicode.Huffman/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import Data\.Word/import GHC.Internal.Word/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import Data\.Bits/import GHC.Internal.Bits/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import GHC\.Show/import GHC.Internal.Show/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import GHC\.Base/import GHC.Internal.Base/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import qualified GHC\.List/import qualified GHC.Internal.List/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" } # Print help text ===================================== libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal ===================================== @@ -50,7 +50,13 @@ executable ucd2haskell ghc-options: -O2 hs-source-dirs: exe main-is: UCD2Haskell.hs - other-modules: Parser.Text + other-modules: + Parser.Text + Generator.RangeSwitch + Generator.GeneralCategory + Generator.WordEncoding + Generator.Huffman + Generator.HuffmanDecode build-depends: base >= 4.7 && < 4.20 , streamly-core >= 0.2.2 && < 0.3 @@ -60,3 +66,4 @@ executable ucd2haskell , containers >= 0.5 && < 0.7 , directory >= 1.3.6 && < 1.3.8 , filepath >= 1.4.2 && < 1.5 + , ghc-prim >= 0.11 && < 0.12 ===================================== rts/Inlines.c ===================================== @@ -1,6 +1,7 @@ -// all functions declared with EXTERN_INLINE in the header files get -// compiled for real here, just in case the definition was not inlined -// at some call site: +// All functions declared with EXTERN_INLINE in the header files get +// compiled for real here. Some of them are called by Cmm (e.g. +// recordClosureMutated) and therefore the real thing needs to reside +// in Inlines.o for Cmm ccall to work. #define KEEP_INLINES #include "rts/PosixSource.h" #include "Rts.h" ===================================== rts/include/Stg.h ===================================== @@ -114,57 +114,19 @@ * 'Portable' inlining: * INLINE_HEADER is for inline functions in header files (macros) * STATIC_INLINE is for inline functions in source files - * EXTERN_INLINE is for functions that we want to inline sometimes - * (we also compile a static version of the function; see Inlines.c) + * EXTERN_INLINE is for functions that may be called in Cmm + * (we also compile a static version of an EXTERN_INLINE function; see Inlines.c) */ -// We generally assume C99 semantics albeit these two definitions work fine even -// when gnu90 semantics are active (i.e. when __GNUC_GNU_INLINE__ is defined or -// when a GCC older than 4.2 is used) -// -// The problem, however, is with 'extern inline' whose semantics significantly -// differs between gnu90 and C99 #define INLINE_HEADER static inline #define STATIC_INLINE static inline -// Figure out whether `__attributes__((gnu_inline))` is needed -// to force gnu90-style 'external inline' semantics. -#if defined(FORCE_GNU_INLINE) -// disable auto-detection since HAVE_GNU_INLINE has been defined externally -#elif defined(__GNUC_GNU_INLINE__) && __GNUC__ == 4 && __GNUC_MINOR__ == 2 -// GCC 4.2.x didn't properly support C99 inline semantics (GCC 4.3 was the first -// release to properly support C99 inline semantics), and therefore warned when -// using 'extern inline' while in C99 mode unless `__attributes__((gnu_inline))` -// was explicitly set. -# define FORCE_GNU_INLINE 1 -#endif - -#if defined(FORCE_GNU_INLINE) -// Force compiler into gnu90 semantics -# if defined(KEEP_INLINES) -# define EXTERN_INLINE inline __attribute__((gnu_inline)) -# else -# define EXTERN_INLINE extern inline __attribute__((gnu_inline)) -# endif -#elif defined(__GNUC_GNU_INLINE__) -// we're currently in gnu90 inline mode by default and -// __attribute__((gnu_inline)) may not be supported, so better leave it off -# if defined(KEEP_INLINES) -# define EXTERN_INLINE inline -# else -# define EXTERN_INLINE extern inline -# endif -#else -// Assume C99 semantics (yes, this curiously results in swapped definitions!) -// This is the preferred branch, and at some point we may drop support for -// compilers not supporting C99 semantics altogether. +// See comment in rts/Inlines.c for explanation. # if defined(KEEP_INLINES) # define EXTERN_INLINE extern inline # else -# define EXTERN_INLINE inline +# define EXTERN_INLINE static inline # endif -#endif - /* * GCC attributes ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5319,7 +5319,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5288,7 +5288,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5465,7 +5465,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5319,7 +5319,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c10e49f070034676508f4ab603db7edede89c694...34ab1e1ce13e50b4dce71a65be2c51a2171efa0b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c10e49f070034676508f4ab603db7edede89c694...34ab1e1ce13e50b4dce71a65be2c51a2171efa0b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 8 22:43:14 2024 From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge)) Date: Sat, 08 Jun 2024 18:43:14 -0400 Subject: [Git][ghc/ghc][wip/T24789_impl] Unicode: adding compact version of GeneralCategory Message-ID: <6664de8265e7c_f3800174dd346375d@gitlab.mail> Serge S. Gulin pushed to branch wip/T24789_impl at Glasgow Haskell Compiler / GHC Commits: 415c634c by Serge S. Gulin at 2024-06-09T01:42:50+03:00 Unicode: adding compact version of GeneralCategory The following features are applied: 1. Lookup code like Cmm-switches (draft implementation proposed by Sylvain Henry @hsyl20) 2. Nested ifs (logarithmic search vs linear search) (the idea proposed by Sylvain Henry @hsyl20) 3. More compact representation via variable encoding by Huffman - - - - - 12 changed files: - libraries/ghc-internal/ghc-internal.cabal - libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs - + libraries/ghc-internal/src/GHC/Internal/Unicode/Huffman.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/GeneralCategory.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/Huffman.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/HuffmanDecode.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/RangeSwitch.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/WordEncoding.hs - libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs - libraries/ghc-internal/tools/ucd2haskell/ucd.sh - libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal Changes: ===================================== libraries/ghc-internal/ghc-internal.cabal ===================================== @@ -318,6 +318,7 @@ Library GHC.Internal.Event.PSQ GHC.Internal.Event.Unique -- GHC.Internal.IOPort -- TODO: hide again after debug + GHC.Internal.Unicode.Huffman GHC.Internal.Unicode.Bits GHC.Internal.Unicode.Char.DerivedCoreProperties GHC.Internal.Unicode.Char.UnicodeData.GeneralCategory ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs ===================================== @@ -1,6 +1,9 @@ {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE BangPatterns #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE UnliftedNewtypes #-} +{-# LANGUAGE BlockArguments #-} ----------------------------------------------------------------------------- -- | @@ -18,20 +21,22 @@ ----------------------------------------------------------------------------- module GHC.Internal.Unicode.Bits - ( lookupBit64, - lookupIntN - ) where + ( lookupIntN + , lookupBit64 + , newByteArrayFromWord8List + , byteArrayLookupIntN + , copyAddrToWord8List + , UnicodeByteArray + ) + where -import GHC.Internal.Base (Bool, Int(..), Word(..), Eq(..)) import GHC.Internal.Bits (finiteBitSize, popCount) -import {-# SOURCE #-} GHC.Internal.ByteOrder import GHC.Prim - (Addr#, - indexWordOffAddr#, indexWord8OffAddr#, - andI#, uncheckedIShiftRL#, - and#, word2Int#, uncheckedShiftL#, - word8ToWord#, byteSwap#) -import GHC.Internal.Num ((-)) +import GHC.Internal.ST +import GHC.Internal.Base +import GHC.Internal.Num +import GHC.Internal.List +import GHC.Internal.Word -- | @lookup64 addr index@ looks up the bit stored at bit index @index@ using a -- bitmap starting at the address @addr at . Looks up the 64-bit word containing @@ -49,9 +54,7 @@ lookupBit64 addr# (I# index#) = W# (word## `and#` bitMask##) /= 0 _ -> popCount fbs -- this is a really weird architecture wordIndex# = index# `uncheckedIShiftRL#` logFbs# - word## = case targetByteOrder of - BigEndian -> byteSwap# (indexWordOffAddr# addr# wordIndex#) - LittleEndian -> indexWordOffAddr# addr# wordIndex# + word## = byteSwap# (indexWordOffAddr# addr# wordIndex#) bitIndex# = index# `andI#` fbs# bitMask## = 1## `uncheckedShiftL#` bitIndex# @@ -71,3 +74,38 @@ lookupIntN lookupIntN addr# (I# index#) = let word## = word8ToWord# (indexWord8OffAddr# addr# index#) in I# (word2Int# word##) + +data UnicodeByteArray = UnicodeByteArray !ByteArray# + +byteArrayLookupIntN :: UnicodeByteArray -> Int -> Int +byteArrayLookupIntN ba idx + = let !(UnicodeByteArray addr) = ba + in lookupIntN (byteArrayContents# addr) idx + +newByteArrayFromWord8List :: [Word8] -> UnicodeByteArray +newByteArrayFromWord8List xs = runST $ ST \s0 -> + case newPinnedByteArray# len s0 of + !(# s1, mba #) -> + let s2 = fillByteArray mba 0# xs s1 + in case unsafeFreezeByteArray# mba s2 of + !(# s3, fba #) -> (# s3, UnicodeByteArray fba #) + where + !(I# len) = length xs + + fillByteArray _ _ [] s = s + fillByteArray mba i (y:ys) s = + let !(W8# y#) = y + s' = writeWord8Array# mba i y# s + in fillByteArray mba (i +# 1#) ys s' + +copyAddrToWord8List :: Addr# -> Int -> [Word8] +copyAddrToWord8List addr !(I# len) = runST $ ST \s0 -> + case newByteArray# len s0 of + !(# s1, mba #) -> + let s2 = copyAddrToByteArray# addr mba 0# len s1 + in case unsafeFreezeByteArray# mba s2 of + !(# s3, fba #) -> (# s3, readByteFromArray fba len #) + where + readByteFromArray :: ByteArray# -> Int# -> [Word8] + readByteFromArray ba i = + W8# (indexWord8Array# ba i) : readByteFromArray ba (i +# 1#) ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs ===================================== The diff for this file was not included because it is too large. ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Huffman.hs ===================================== @@ -0,0 +1,53 @@ +-- DO NOT EDIT IT HERE. It is automatically copied from ucd2haskell tool's Generator.HuffmanDecode +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE ExplicitForAll #-} +{-# LANGUAGE TypeApplications #-} + +module GHC.Internal.Unicode.Huffman + ( decodeHuffman + , deserializeHuffman + , HuffmanTree (..) + ) + where + +import GHC.Internal.Word (Word8) +import GHC.Internal.Bits (testBit) +import GHC.Internal.Show (Show (..)) +import GHC.Internal.Base (Bool, Eq, Functor, (.), (++), error, map) +import qualified GHC.Internal.List as L (concatMap) + +data HuffmanTree a + = HTLeaf !a + | HTNode !(HuffmanTree a) !(HuffmanTree a) + deriving stock (Show, Eq, Functor) + +deserializeHuffman :: forall a . (Word8 -> a) -> [Word8] -> HuffmanTree a +deserializeHuffman conv = (\(a, _) -> a) . go + where + go [] = error "Unable to process empty list" + go (0x00:value:rest) = (HTLeaf (conv value), rest) + go (0x01:rest) = + let + (left, rest') = go rest + (right, rest'') = go rest' + in (HTNode left right, rest'') + go v = error ("Unknown type of Huffman tree leaf: " ++ show v) + +decodeHuffman :: HuffmanTree a -> [Word8] -> [a] +decodeHuffman huffman_tree = decodeBits huffman_tree . unpackBits + where + word8ToBools :: Word8 -> [Bool] + word8ToBools w = map (testBit w) [7, 6 .. 0] + + unpackBits :: [Word8] -> [Bool] + unpackBits = L.concatMap word8ToBools + + decodeBits :: HuffmanTree a -> [Bool] -> [a] + decodeBits tree bits = decodeBits' tree bits tree + where + decodeBits' _ [] _ = [] + decodeBits' (HTLeaf c) bs tree' = c : decodeBits' tree' bs tree' + decodeBits' (HTNode l r) (b:bs) tree' = decodeBits' next bs tree' + where next = if b then r else l + ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/GeneralCategory.hs ===================================== @@ -0,0 +1,145 @@ +{-# LANGUAGE BlockArguments #-} +module Generator.GeneralCategory (GeneralCategory (..), generateGeneralCategoryCode) where + +import Generator.RangeSwitch +import Generator.WordEncoding +import Data.List (intercalate) +import Text.Printf (printf) +import Generator.Huffman (mkHuffmanTree, serializeHuffman) + +data GeneralCategory = + Lu|Ll|Lt| --LC + Lm|Lo| --L + Mn|Mc|Me| --M + Nd|Nl|No| --N + Pc|Pd|Ps|Pe|Pi|Pf|Po| --P + Sm|Sc|Sk|So| --S + Zs|Zl|Zp| --Z + Cc|Cf|Cs|Co|Cn --C + deriving (Show, Eq, Ord, Bounded, Enum, Read) + +genEnumBitmap :: + forall a. (Bounded a, Enum a, Show a) => + -- | Function name + String -> + -- | Default value + a -> + -- | List of values to encode + [a] -> + String +genEnumBitmap funcName def as = unlines + [ "{-# INLINE " <> funcName <> " #-}" + , funcName <> " :: Char -> Int" + , funcName <> " c = let n = ord c in if n >= " + <> show (length as) + <> " then " + <> show (fromEnum def) + <> " else lookup_bitmap n" + ] + +generateHaskellCode :: Int -> [GeneralCategory] -> String +generateHaskellCode max_char_length cats = + let (index_tree, all_allocs) = extract [] range_tree + in intercalate "\n" + [ "{-# NOINLINE deserialized_huffman #-}" + , "deserialized_huffman :: HuffmanTree Word8" + , "deserialized_huffman =" + , intercalate " " [" let huffman_tree =", "\"" <> mapToAddrLiteral serialized_huffman "\"#"] + , printf " in deserializeHuffman (\\x -> x) (copyAddrToWord8List huffman_tree %d)" (length serialized_huffman) + , intercalate "\n" (fmap genDecompressed (zip all_allocs [0..])) + , "" + , "{-# NOINLINE lookup_bitmap #-}" + , "lookup_bitmap :: Int -> Int" + , "lookup_bitmap n =" + , printf " (%s)" (genCode' index_tree 2) + ] + where + cases' = rangeCases max_char_length cats + huffmanTree = mkHuffmanTree $ extractLookupIntList cases' + cases_huffman_encoded = rangesToWord8 huffmanTree cases' + range_tree = buildRangeTree cases_huffman_encoded + + serialized_huffman = serializeHuffman toWord8 huffmanTree + + prefixEachLine indent ls = concatMap (\l -> "\n" ++ replicate (indent*2) ' ' ++ l) ls + + genCode' :: (Show a) => RangeTree (Either a Int) -> Int -> String + genCode' (Leaf _ _ cat) _ = show cat + genCode' (Node start _ (Leaf _ endl c_l) (Leaf startr _ c_r)) indent = + prefixEachLine indent + [ printf "({- 1 -} if n < %d then (%s) else (%s))" (endl+1) (genResult start c_l) (genResult startr c_r) + ] + + genCode' (Node start _ (Leaf _ endl c_l) node_r@(Node _ _ _ _)) indent = + prefixEachLine indent + [ printf "({- 2 -}if n < %d then (%s) else (%s))" (endl+1) (genResult start c_l) (genCode' node_r $ indent + 1) + ] + + genCode' (Node _ _ node_l@(Node _ _ _ _) (Leaf startr _ c_r)) indent = + prefixEachLine indent + [ printf "({- 3 -} if n >= %d then (%s) else (%s))" startr (genResult startr c_r) (genCode' node_l $ indent + 1) + ] + + genCode' (Node _ _ node_l@(Node _ endl _ _) node_r@(Node _ _ _ _)) indent = + prefixEachLine indent + [ printf "({- 4 -} if n < %d then (%s) else (%s))" (endl+1) (genCode' node_l $ indent + 1) (genCode' node_r $ indent + 1) + ] + + genResult :: Show a => Int -> Either a Int -> String + genResult _ (Left s) = show s + -- genResult mi (Right idx) = intercalate " " ["lookupIntN (decodeHuffman (toEnum . fromIntegral, deserialized_huffman)", "\"" <> mapToAddrLiteral as "\"#)", "(n -", show mi, ")"] + genResult mi (Right idx) = intercalate " " ["byteArrayLookupIntN", "decompressed_table_" <> show idx, "(n -", show mi, ")"] + + extract :: [[a]] -> RangeTree (Either a [a]) -> (RangeTree (Either a Int), [[a]]) + extract acc (Leaf mi ma (Left v)) = (Leaf mi ma (Left v), acc) + extract acc (Leaf mi ma (Right v)) = (Leaf mi ma (Right (length acc)), acc ++ [v]) + extract acc (Node mi ma lt rt) = + let + (e_lt, l_acc) = extract acc lt + (e_rt, r_acc) = extract l_acc rt + in (Node mi ma e_lt e_rt, r_acc) + + genDecompressed :: forall a. Show a => ([a], Int) -> String + genDecompressed (acc, idx) = + let fn_name = "decompressed_table_" <> show idx + in intercalate "\n" + [ "" + , "{-# NOINLINE " <> fn_name <> " #-}" + , fn_name <> " :: UnicodeByteArray" + , fn_name <> " =" + , intercalate " " [" let compressed = copyAddrToWord8List", "\"" <> mapToAddrLiteral acc "\"#", show (length acc)] + , printf " in newByteArrayFromWord8List (decodeHuffman deserialized_huffman compressed)" + ] + +generateGeneralCategoryCode + :: (String -> String) + -- ^-- How to generate module header where first arg us module name + -> String + -- ^-- Module name + -> Int + -- ^-- Max char length + -> [GeneralCategory] + -- ^-- imported general categories for all symbol list + -> String +generateGeneralCategoryCode mkModuleHeader moduleName char_length cats = + unlines + [ "{-# LANGUAGE NoImplicitPrelude #-}" + , "{-# LANGUAGE MagicHash #-}" + , "{-# LANGUAGE TypeApplications #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(generalCategory)" + , "where" + , "" + , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" + , "import GHC.Internal.Unicode.Bits (UnicodeByteArray, copyAddrToWord8List, newByteArrayFromWord8List, byteArrayLookupIntN)" + , "import GHC.Internal.Unicode.Huffman (HuffmanTree, decodeHuffman, deserializeHuffman)" + , "import GHC.Internal.Num ((-))" + , "import GHC.Internal.Word (Word8)" + , "" + , generateHaskellCode char_length cats + , "" + , genEnumBitmap "generalCategory" Cn (reverse cats) + ] ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/Huffman.hs ===================================== @@ -0,0 +1,83 @@ +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE PackageImports #-} + +module Generator.Huffman + ( mkHuffmanTree + , encodeHuffman + , serializeHuffman + ) + where + +import Data.List (sortBy) +import Data.Ord (comparing) +import Data.Maybe (fromJust) +import Data.Map.Strict (Map) +import qualified Data.Map.Strict as Map +import Data.Word (Word8) +import Data.Bits (shiftL, (.|.)) +import Generator.HuffmanDecode (HuffmanTree (..)) + +data HuffmanTreeFreq a + = HTFLeaf a Int + | HTFNode Int (HuffmanTreeFreq a) (HuffmanTreeFreq a) + deriving stock (Show, Eq, Functor) + +buildHuffmanTree :: Ord a => [(a, Int)] -> HuffmanTree a +buildHuffmanTree freqs = convertTree $ buildTree initialQueue + where + frequency :: HuffmanTreeFreq a -> Int + frequency (HTFLeaf _ f) = f + frequency (HTFNode f _ _) = f + + initialQueue = sortBy (comparing frequency) [HTFLeaf s f | (s, f) <- freqs] + + buildTree [] = error "impossible: empty list is not an appropriate input here" + buildTree [t] = t + buildTree (t1:t2:ts) = + let newNode = HTFNode (frequency t1 + frequency t2) t1 t2 + newQueue = insertBy (comparing frequency) newNode ts + in buildTree newQueue + + insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a] + insertBy _ x [] = [x] + insertBy cmp x ys@(y:ys') + = case cmp x y of + GT -> y : insertBy cmp x ys' + _ -> x : ys + + convertTree :: HuffmanTreeFreq a -> HuffmanTree a + convertTree (HTFLeaf value _) = HTLeaf value + convertTree (HTFNode _ left right) = HTNode (convertTree left) (convertTree right) + +serializeHuffman :: (a -> Word8) -> HuffmanTree a -> [Word8] +serializeHuffman conv (HTLeaf value) = [0x00, conv value] +serializeHuffman conv (HTNode left right) = [0x01] ++ serializeHuffman conv left ++ serializeHuffman conv right + +mkHuffmanTree :: (Ord a) => [a] -> HuffmanTree a +mkHuffmanTree = buildHuffmanTree . Map.toList . huffmanStats + where + huffmanStats :: (Ord a) => [a] -> Map a Int + huffmanStats l = Map.fromListWith (+) [(c, 1) | c <- l] + +encodeHuffman :: (Ord a) => HuffmanTree a -> [a] -> [Word8] +encodeHuffman huffmanTree = packBits . encodeBits (buildHuffmanTable huffmanTree) + where + boolsToWord8 :: [Bool] -> Word8 + boolsToWord8 = foldl (\acc b -> shiftL acc 1 .|. if b then 1 else 0) 0 + + chunksOf :: Int -> [a] -> [[a]] + chunksOf _ [] = [] + chunksOf n xs = take n xs : chunksOf n (drop n xs) + + packBits :: [Bool] -> [Word8] + packBits bits = map boolsToWord8 (chunksOf 8 bits) + + encodeBits :: (Ord a) => Map.Map a [Bool] -> [a] -> [Bool] + encodeBits huffmanTable cc = concatMap (\c -> fromJust $ Map.lookup c huffmanTable) cc + + buildHuffmanTable :: Ord a => HuffmanTree a -> Map a [Bool] + buildHuffmanTable tree = Map.fromList $ buildCodes tree [] + where + buildCodes (HTLeaf s) code = [(s, code)] + buildCodes (HTNode l r) code = buildCodes l (code ++ [False]) ++ buildCodes r (code ++ [True]) ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/HuffmanDecode.hs ===================================== @@ -0,0 +1,52 @@ +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE ExplicitForAll #-} +{-# LANGUAGE TypeApplications #-} + +module Generator.HuffmanDecode + ( decodeHuffman + , deserializeHuffman + , HuffmanTree (..) + ) + where + +import Data.Word (Word8) +import Data.Bits (testBit) +import GHC.Show (Show (..)) +import GHC.Base (Bool, Eq, Functor, (.), (++), error, map) +import qualified GHC.List as L (concatMap) + +data HuffmanTree a + = HTLeaf !a + | HTNode !(HuffmanTree a) !(HuffmanTree a) + deriving stock (Show, Eq, Functor) + +deserializeHuffman :: forall a . (Word8 -> a) -> [Word8] -> HuffmanTree a +deserializeHuffman conv = (\(a, _) -> a) . go + where + go [] = error "Unable to process empty list" + go (0x00:value:rest) = (HTLeaf (conv value), rest) + go (0x01:rest) = + let + (left, rest') = go rest + (right, rest'') = go rest' + in (HTNode left right, rest'') + go v = error ("Unknown type of Huffman tree leaf: " ++ show v) + +decodeHuffman :: HuffmanTree a -> [Word8] -> [a] +decodeHuffman huffman_tree = decodeBits huffman_tree . unpackBits + where + word8ToBools :: Word8 -> [Bool] + word8ToBools w = map (testBit w) [7, 6 .. 0] + + unpackBits :: [Word8] -> [Bool] + unpackBits = L.concatMap word8ToBools + + decodeBits :: HuffmanTree a -> [Bool] -> [a] + decodeBits tree bits = decodeBits' tree bits tree + where + decodeBits' _ [] _ = [] + decodeBits' (HTLeaf c) bs tree' = c : decodeBits' tree' bs tree' + decodeBits' (HTNode l r) (b:bs) tree' = decodeBits' next bs tree' + where next = if b then r else l + ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/RangeSwitch.hs ===================================== @@ -0,0 +1,73 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE BlockArguments #-} +module Generator.RangeSwitch + where + +import Generator.WordEncoding +import Data.Word +import Data.Bifunctor (bimap) +import Generator.Huffman (encodeHuffman) +import Generator.HuffmanDecode (HuffmanTree) + +data Case a = Case + { caseMin :: Int + , caseMax :: Int + , caseConstant :: Either a [a] + } + deriving stock (Show) + +extractLookupIntList :: [Case a] -> [a] +extractLookupIntList = concat . (fmap \(Case _ _ cc) -> either (const []) id cc) + +ranges :: (Enum a, Eq a, Show a) => [a] -> [(Int,Int,a)] +ranges = \case + [] -> [] + (x:xs) -> reverse (go 0 0 x [] xs) + where + go mi ma v rs = \case + [] -> (mi,ma,v):rs + (x:xs) + | x == v -> go mi (ma+1) v rs xs + | otherwise -> go (ma+1) (ma+1) x ((mi,ma,v):rs) xs + +cases :: Int -> [a] -> [(Int,Int,a)] -> [Case a] +cases max_rep all_cats = go + where + go = \case + [] -> [] + (r@(mi,ma,v):rs) + | rangeSize r > max_rep -> Case mi ma (Left v) : go rs + | otherwise -> go_lookup mi ma (Left v) rs + + go_lookup rmi rma mv = \case + [] -> [Case rmi rma mv] + (r@(mi,ma,v):rs) + | rangeSize r > max_rep -> Case rmi rma mv : Case mi ma (Left v) : go rs + | otherwise -> go_lookup rmi ma (Right (take (ma-rmi+1) (drop rmi all_cats))) rs + + rangeSize :: Num a => (a, a, c) -> a + rangeSize (mi, ma, _) = ma - mi + 1 + +rangeCases :: (Enum a, Eq a, Show a) => Int -> [a] -> [Case a] +rangeCases max_char_length cats = cases max_char_length cats (ranges cats) + +data RangeTree a + = Leaf Int Int a + | Node Int Int (RangeTree a) (RangeTree a) + deriving stock (Show) + +buildRangeTree :: [Case a] -> RangeTree (Either a [a]) +buildRangeTree [(Case start end cat)] = Leaf start end cat +buildRangeTree ranges' = + let + mid = length ranges' `div` 2 + (leftRanges, rightRanges) = splitAt mid ranges' + (Case startL _ _) = head leftRanges + (Case _ endR _) = last rightRanges + in Node startL endR (buildRangeTree leftRanges) (buildRangeTree rightRanges) + +rangesToWord8 :: (Show a, Enum a, Ord a) => HuffmanTree a -> [Case a] -> [Case Word8] +rangesToWord8 htree = fmap \(Case mi ma c) -> + Case mi ma $ bimap toWord8 (encodeHuffman htree) c + ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/WordEncoding.hs ===================================== @@ -0,0 +1,40 @@ +module Generator.WordEncoding where + +import Data.Word + +toWord8 :: (Show a, Enum a) => a -> Word8 +toWord8 a = let w = fromEnum a in if 0 <= w && w <= 0xff + then fromIntegral w + else error $ "Cannot convert to Word8: " <> show a + +{-| Encode a list of values as a byte map, using their 'Enum' instance. + +__Note:__ 'Enum' instance must respect the following: + +* @fromEnum minBound >= 0x00@ +* @fromEnum maxBound <= 0xff@ +-} +enumMapToAddrLiteral :: + forall a. (Bounded a, Enum a, Show a) => + -- | Values to encode + [a] -> + -- | String to append + String -> + String +enumMapToAddrLiteral xs cs = foldr go cs xs + where + go :: a -> String -> String + go x acc = '\\' : shows (toWord8 x) acc + +-- Same as enumMapToAddrLiteral but for already converted to Word8 +mapToAddrLiteral :: + forall a. (Show a) => + -- | Values to encode + [a] -> + -- | String to append + String -> + String +mapToAddrLiteral xs cs = foldr go cs xs + where + go :: a -> String -> String + go x acc = '\\' : shows x acc ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs ===================================== @@ -33,6 +33,7 @@ import Streamly.Data.Fold (Fold) import System.Directory (createDirectoryIfMissing) import System.Environment (getEnv) import System.FilePath ((), (<.>)) +import Generator.GeneralCategory (GeneralCategory(Cn), generateGeneralCategoryCode) -- import qualified Data.Set as Set import Streamly.Data.Stream (Stream) @@ -51,17 +52,6 @@ import Prelude hiding (pred) -- Types ------------------------------------------------------------------------------- -data GeneralCategory = - Lu|Ll|Lt| --LC - Lm|Lo| --L - Mn|Mc|Me| --M - Nd|Nl|No| --N - Pc|Pd|Ps|Pe|Pi|Pf|Po| --P - Sm|Sc|Sk|So| --S - Zs|Zl|Zp| --Z - Cc|Cf|Cs|Co|Cn --C - deriving (Show, Bounded, Enum, Read) - data DecompType = DTCanonical | DTCompat | DTFont | DTNoBreak | DTInitial | DTMedial | DTFinal @@ -189,57 +179,6 @@ bitMapToAddrLiteral bs cs = foldr encode cs (unfoldr mkChunks bs) toByte :: [Bool] -> Int toByte xs = sum $ map (\i -> if xs !! i then 1 `shiftL` i else 0) [0..7] -genEnumBitmap :: - forall a. (Bounded a, Enum a, Show a) => - -- | Function name - String -> - -- | Default value - a -> - -- | List of values to encode - [a] -> - String -genEnumBitmap funcName def as = unlines - [ "{-# INLINE " <> funcName <> " #-}" - , funcName <> " :: Char -> Int" - , funcName <> " c = let n = ord c in if n >= " - <> show (length as) - <> " then " - <> show (fromEnum def) - <> " else lookup_bitmap n" - - , "{-# NOINLINE lookup_bitmap #-}" - , "lookup_bitmap :: Int -> Int" - , "lookup_bitmap n = lookupIntN bitmap# n" - , " where" - , " bitmap# = \"" <> enumMapToAddrLiteral as "\"#" - ] - -{-| Encode a list of values as a byte map, using their 'Enum' instance. - -__Note:__ 'Enum' instance must respect the following: - -* @fromEnum minBound >= 0x00@ -* @fromEnum maxBound <= 0xff@ --} -enumMapToAddrLiteral :: - forall a. (Bounded a, Enum a, Show a) => - -- | Values to encode - [a] -> - -- | String to append - String -> - String -enumMapToAddrLiteral xs cs = foldr go cs xs - - where - - go :: a -> String -> String - go x acc = '\\' : shows (toWord8 x) acc - - toWord8 :: a -> Word8 - toWord8 a = let w = fromEnum a in if 0 <= w && w <= 0xff - then fromIntegral w - else error $ "Cannot convert to Word8: " <> show a - {- [NOTE] Disabled generator (normalization) -- This bit of code is duplicated but this duplication allows us to reduce 2 -- dependencies on the executable. @@ -321,21 +260,7 @@ genGeneralCategoryModule moduleName = -- Regular entry else (_generalCategory a : acc, succ (_char a)) - done (acc, _) = unlines - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(generalCategory)" - , "where" - , "" - , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" - , "import GHC.Internal.Unicode.Bits (lookupIntN)" - , "" - , genEnumBitmap "generalCategory" Cn (reverse acc) - ] + done (acc, _) = generateGeneralCategoryCode mkModuleHeader moduleName 220 acc readDecomp :: String -> (Maybe DecompType, Decomp) readDecomp s = ===================================== libraries/ghc-internal/tools/ucd2haskell/ucd.sh ===================================== @@ -71,6 +71,23 @@ run_generator() { # --core-prop XID_Continue \ # --core-prop Pattern_Syntax \ # --core-prop Pattern_White_Space + + echo "-- DO NOT EDIT IT HERE. It is automatically copied from ucd2haskell tool's Generator.HuffmanDecode" > "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + cat "$SCRIPT_DIR/exe/Generator/HuffmanDecode.hs" >> "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + + # See https://stackoverflow.com/a/22084103 + sed -i.bak -e "s/module Generator\.HuffmanDecode/module GHC.Internal.Unicode.Huffman/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import Data\.Word/import GHC.Internal.Word/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import Data\.Bits/import GHC.Internal.Bits/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import GHC\.Show/import GHC.Internal.Show/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import GHC\.Base/import GHC.Internal.Base/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import qualified GHC\.List/import qualified GHC.Internal.List/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" } # Print help text ===================================== libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal ===================================== @@ -50,7 +50,13 @@ executable ucd2haskell ghc-options: -O2 hs-source-dirs: exe main-is: UCD2Haskell.hs - other-modules: Parser.Text + other-modules: + Parser.Text + Generator.RangeSwitch + Generator.GeneralCategory + Generator.WordEncoding + Generator.Huffman + Generator.HuffmanDecode build-depends: base >= 4.7 && < 4.20 , streamly-core >= 0.2.2 && < 0.3 @@ -60,3 +66,4 @@ executable ucd2haskell , containers >= 0.5 && < 0.7 , directory >= 1.3.6 && < 1.3.8 , filepath >= 1.4.2 && < 1.5 + , ghc-prim >= 0.11 && < 0.12 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/415c634cebce12e638e6a98039f0a1acf16e9b14 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/415c634cebce12e638e6a98039f0a1acf16e9b14 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 05:27:46 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sun, 09 Jun 2024 01:27:46 -0400 Subject: [Git][ghc/ghc][master] 2 commits: ghc-internal: Update CHANGELOG to reflect current version Message-ID: <66653d527f025_f3800489f81085867@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 2 changed files: - libraries/ghc-internal/CHANGELOG.md - libraries/ghc-internal/prologue.txt Changes: ===================================== libraries/ghc-internal/CHANGELOG.md ===================================== @@ -1,5 +1,5 @@ # Revision history for `ghc-internal` -## 0.1.0.0 -- YYYY-mm-dd +## 9.1001.0 -- 2024-05-01 -* First version. Released on an unsuspecting world. +* Package created containing implementation moved from `base`. ===================================== libraries/ghc-internal/prologue.txt ===================================== @@ -1,3 +1,2 @@ -This package contains the @Prelude@ and its support libraries, and a large -collection of useful libraries ranging from data structures to parsing -combinators and debugging utilities. +This package contains the implementation of GHC's standard libraries and is +not intended for use by end-users. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9ea90ed2e4870c7bfed3e09d0b033fc630802304...391ecff5ced86e52089c5a5c46158a22755312a9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9ea90ed2e4870c7bfed3e09d0b033fc630802304...391ecff5ced86e52089c5a5c46158a22755312a9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 05:28:27 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sun, 09 Jun 2024 01:28:27 -0400 Subject: [Git][ghc/ghc][master] compiler: Clarify comment regarding need for MOVABS Message-ID: <66653d7b4a14_f38004a440e489156@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 1 changed file: - compiler/GHC/CmmToAsm/X86/Instr.hs Changes: ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -198,10 +198,13 @@ data Instr -- Moves. | MOV Format Operand Operand - -- ^ N.B. when used with the 'II64' 'Format', the source + -- ^ N.B. Due to AT&T assembler quirks, when used with 'II64' + -- 'Format' immediate source and memory target operand, the source -- operand is interpreted to be a 32-bit sign-extended value. - -- True 64-bit operands need to be moved with @MOVABS@, which we - -- currently don't use. + -- True 64-bit operands need to be either first moved to a register or moved + -- with @MOVABS@; we currently do not use this instruction in GHC. + -- See https://stackoverflow.com/questions/52434073/whats-the-difference-between-the-x86-64-att-instructions-movq-and-movabsq. + | MOVD Format Operand Operand -- ^ MOVD/MOVQ SSE2 instructions -- (bitcast between a general purpose -- register and a float register). View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3dca3b7dbb35ed44250448b8f4ff15aa1c118280 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3dca3b7dbb35ed44250448b8f4ff15aa1c118280 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 07:51:12 2024 From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge)) Date: Sun, 09 Jun 2024 03:51:12 -0400 Subject: [Git][ghc/ghc][wip/T24789_impl] Unicode: adding compact version of GeneralCategory Message-ID: <66655ef0d3ebc_f38005c617cc1023b1@gitlab.mail> Serge S. Gulin pushed to branch wip/T24789_impl at Glasgow Haskell Compiler / GHC Commits: 2445dbfd by Serge S. Gulin at 2024-06-09T10:50:53+03:00 Unicode: adding compact version of GeneralCategory The following features are applied: 1. Lookup code like Cmm-switches (draft implementation proposed by Sylvain Henry @hsyl20) 2. Nested ifs (logarithmic search vs linear search) (the idea proposed by Sylvain Henry @hsyl20) 3. More compact representation via variable encoding by Huffman - - - - - 12 changed files: - libraries/ghc-internal/ghc-internal.cabal - libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs - + libraries/ghc-internal/src/GHC/Internal/Unicode/Huffman.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/GeneralCategory.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/Huffman.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/HuffmanDecode.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/RangeSwitch.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/WordEncoding.hs - libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs - libraries/ghc-internal/tools/ucd2haskell/ucd.sh - libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal Changes: ===================================== libraries/ghc-internal/ghc-internal.cabal ===================================== @@ -318,6 +318,7 @@ Library GHC.Internal.Event.PSQ GHC.Internal.Event.Unique -- GHC.Internal.IOPort -- TODO: hide again after debug + GHC.Internal.Unicode.Huffman GHC.Internal.Unicode.Bits GHC.Internal.Unicode.Char.DerivedCoreProperties GHC.Internal.Unicode.Char.UnicodeData.GeneralCategory ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs ===================================== @@ -1,6 +1,9 @@ {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE BangPatterns #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE UnliftedNewtypes #-} +{-# LANGUAGE BlockArguments #-} ----------------------------------------------------------------------------- -- | @@ -18,20 +21,22 @@ ----------------------------------------------------------------------------- module GHC.Internal.Unicode.Bits - ( lookupBit64, - lookupIntN - ) where + ( lookupIntN + , lookupBit64 + , newByteArrayFromWord8List + , byteArrayLookupIntN + , copyAddrToWord8List + , UnicodeByteArray + ) + where -import GHC.Internal.Base (Bool, Int(..), Word(..), Eq(..)) import GHC.Internal.Bits (finiteBitSize, popCount) -import {-# SOURCE #-} GHC.Internal.ByteOrder import GHC.Prim - (Addr#, - indexWordOffAddr#, indexWord8OffAddr#, - andI#, uncheckedIShiftRL#, - and#, word2Int#, uncheckedShiftL#, - word8ToWord#, byteSwap#) -import GHC.Internal.Num ((-)) +import GHC.Internal.ST +import GHC.Internal.Base +import GHC.Internal.Num +import GHC.Internal.List +import GHC.Internal.Word -- | @lookup64 addr index@ looks up the bit stored at bit index @index@ using a -- bitmap starting at the address @addr at . Looks up the 64-bit word containing @@ -49,9 +54,7 @@ lookupBit64 addr# (I# index#) = W# (word## `and#` bitMask##) /= 0 _ -> popCount fbs -- this is a really weird architecture wordIndex# = index# `uncheckedIShiftRL#` logFbs# - word## = case targetByteOrder of - BigEndian -> byteSwap# (indexWordOffAddr# addr# wordIndex#) - LittleEndian -> indexWordOffAddr# addr# wordIndex# + word## = byteSwap# (indexWordOffAddr# addr# wordIndex#) bitIndex# = index# `andI#` fbs# bitMask## = 1## `uncheckedShiftL#` bitIndex# @@ -71,3 +74,41 @@ lookupIntN lookupIntN addr# (I# index#) = let word## = word8ToWord# (indexWord8OffAddr# addr# index#) in I# (word2Int# word##) + +data UnicodeByteArray = UnicodeByteArray !ByteArray# + +byteArrayLookupIntN :: UnicodeByteArray -> Int -> Int +byteArrayLookupIntN ba idx + = let !(UnicodeByteArray addr) = ba + in lookupIntN (byteArrayContents# addr) idx + +newByteArrayFromWord8List :: [Word8] -> UnicodeByteArray +newByteArrayFromWord8List xs = runST $ ST \s0 -> + case newPinnedByteArray# len s0 of + !(# s1, mba #) -> + let s2 = fillByteArray mba 0# xs s1 + in case unsafeFreezeByteArray# mba s2 of + !(# s3, fba #) -> (# s3, UnicodeByteArray fba #) + where + !(I# len) = length xs + + fillByteArray _ _ [] s = s + fillByteArray mba i (y:ys) s = + let !(W8# y#) = y + s' = writeWord8Array# mba i y# s + in fillByteArray mba (i +# 1#) ys s' + +copyAddrToWord8List :: Addr# -> Int -> [Word8] +copyAddrToWord8List addr !len@(I# len') = runST $ ST \s0 -> + case newByteArray# len' s0 of + !(# s1, mba #) -> + let s2 = copyAddrToByteArray# addr mba 0# len' s1 + in case unsafeFreezeByteArray# mba s2 of + !(# s3, fba #) -> (# s3, readByteFromArray fba 0 len #) + where + readByteFromArray :: ByteArray# -> Int -> Int -> [Word8] + readByteFromArray ba !from@(I# from') to = + W8# (indexWord8Array# ba from') : + if from == (to - 1) + then [] + else readByteFromArray ba (from + 1) to ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs ===================================== The diff for this file was not included because it is too large. ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Huffman.hs ===================================== @@ -0,0 +1,53 @@ +-- DO NOT EDIT IT HERE. It is automatically copied from ucd2haskell tool's Generator.HuffmanDecode +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE ExplicitForAll #-} +{-# LANGUAGE TypeApplications #-} + +module GHC.Internal.Unicode.Huffman + ( decodeHuffman + , deserializeHuffman + , HuffmanTree (..) + ) + where + +import GHC.Internal.Word (Word8) +import GHC.Internal.Bits (testBit) +import GHC.Internal.Show (Show (..)) +import GHC.Internal.Base (Bool, Eq, Functor, (.), (++), error, map) +import qualified GHC.Internal.List as L (concatMap) + +data HuffmanTree a + = HTLeaf !a + | HTNode !(HuffmanTree a) !(HuffmanTree a) + deriving stock (Show, Eq, Functor) + +deserializeHuffman :: forall a . (Word8 -> a) -> [Word8] -> HuffmanTree a +deserializeHuffman conv = (\(a, _) -> a) . go + where + go [] = error "Unable to process empty list" + go (0x00:value:rest) = (HTLeaf (conv value), rest) + go (0x01:rest) = + let + (left, rest') = go rest + (right, rest'') = go rest' + in (HTNode left right, rest'') + go v = error ("Unknown type of Huffman tree leaf: " ++ show v) + +decodeHuffman :: HuffmanTree a -> [Word8] -> [a] +decodeHuffman huffman_tree = decodeBits huffman_tree . unpackBits + where + word8ToBools :: Word8 -> [Bool] + word8ToBools w = map (testBit w) [7, 6 .. 0] + + unpackBits :: [Word8] -> [Bool] + unpackBits = L.concatMap word8ToBools + + decodeBits :: HuffmanTree a -> [Bool] -> [a] + decodeBits tree bits = decodeBits' tree bits tree + where + decodeBits' _ [] _ = [] + decodeBits' (HTLeaf c) bs tree' = c : decodeBits' tree' bs tree' + decodeBits' (HTNode l r) (b:bs) tree' = decodeBits' next bs tree' + where next = if b then r else l + ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/GeneralCategory.hs ===================================== @@ -0,0 +1,145 @@ +{-# LANGUAGE BlockArguments #-} +module Generator.GeneralCategory (GeneralCategory (..), generateGeneralCategoryCode) where + +import Generator.RangeSwitch +import Generator.WordEncoding +import Data.List (intercalate) +import Text.Printf (printf) +import Generator.Huffman (mkHuffmanTree, serializeHuffman) + +data GeneralCategory = + Lu|Ll|Lt| --LC + Lm|Lo| --L + Mn|Mc|Me| --M + Nd|Nl|No| --N + Pc|Pd|Ps|Pe|Pi|Pf|Po| --P + Sm|Sc|Sk|So| --S + Zs|Zl|Zp| --Z + Cc|Cf|Cs|Co|Cn --C + deriving (Show, Eq, Ord, Bounded, Enum, Read) + +genEnumBitmap :: + forall a. (Bounded a, Enum a, Show a) => + -- | Function name + String -> + -- | Default value + a -> + -- | List of values to encode + [a] -> + String +genEnumBitmap funcName def as = unlines + [ "{-# INLINE " <> funcName <> " #-}" + , funcName <> " :: Char -> Int" + , funcName <> " c = let n = ord c in if n >= " + <> show (length as) + <> " then " + <> show (fromEnum def) + <> " else lookup_bitmap n" + ] + +generateHaskellCode :: Int -> [GeneralCategory] -> String +generateHaskellCode max_char_length cats = + let (index_tree, all_allocs) = extract [] range_tree + in intercalate "\n" + [ "{-# NOINLINE deserialized_huffman #-}" + , "deserialized_huffman :: HuffmanTree Word8" + , "deserialized_huffman =" + , intercalate " " [" let huffman_tree =", "\"" <> mapToAddrLiteral serialized_huffman "\"#"] + , printf " in deserializeHuffman (\\x -> x) (copyAddrToWord8List huffman_tree %d)" (length serialized_huffman) + , intercalate "\n" (fmap genDecompressed (zip all_allocs [0..])) + , "" + , "{-# NOINLINE lookup_bitmap #-}" + , "lookup_bitmap :: Int -> Int" + , "lookup_bitmap n =" + , printf " (%s)" (genCode' index_tree 2) + ] + where + cases' = rangeCases max_char_length cats + huffmanTree = mkHuffmanTree $ extractLookupIntList cases' + cases_huffman_encoded = rangesToWord8 huffmanTree cases' + range_tree = buildRangeTree cases_huffman_encoded + + serialized_huffman = serializeHuffman toWord8 huffmanTree + + prefixEachLine indent ls = concatMap (\l -> "\n" ++ replicate (indent*2) ' ' ++ l) ls + + genCode' :: (Show a) => RangeTree (Either a Int) -> Int -> String + genCode' (Leaf _ _ cat) _ = show cat + genCode' (Node start _ (Leaf _ endl c_l) (Leaf startr _ c_r)) indent = + prefixEachLine indent + [ printf "({- 1 -} if n < %d then (%s) else (%s))" (endl+1) (genResult start c_l) (genResult startr c_r) + ] + + genCode' (Node start _ (Leaf _ endl c_l) node_r@(Node _ _ _ _)) indent = + prefixEachLine indent + [ printf "({- 2 -}if n < %d then (%s) else (%s))" (endl+1) (genResult start c_l) (genCode' node_r $ indent + 1) + ] + + genCode' (Node _ _ node_l@(Node _ _ _ _) (Leaf startr _ c_r)) indent = + prefixEachLine indent + [ printf "({- 3 -} if n >= %d then (%s) else (%s))" startr (genResult startr c_r) (genCode' node_l $ indent + 1) + ] + + genCode' (Node _ _ node_l@(Node _ endl _ _) node_r@(Node _ _ _ _)) indent = + prefixEachLine indent + [ printf "({- 4 -} if n < %d then (%s) else (%s))" (endl+1) (genCode' node_l $ indent + 1) (genCode' node_r $ indent + 1) + ] + + genResult :: Show a => Int -> Either a Int -> String + genResult _ (Left s) = show s + -- genResult mi (Right idx) = intercalate " " ["lookupIntN (decodeHuffman (toEnum . fromIntegral, deserialized_huffman)", "\"" <> mapToAddrLiteral as "\"#)", "(n -", show mi, ")"] + genResult mi (Right idx) = intercalate " " ["byteArrayLookupIntN", "decompressed_table_" <> show idx, "(n -", show mi, ")"] + + extract :: [[a]] -> RangeTree (Either a [a]) -> (RangeTree (Either a Int), [[a]]) + extract acc (Leaf mi ma (Left v)) = (Leaf mi ma (Left v), acc) + extract acc (Leaf mi ma (Right v)) = (Leaf mi ma (Right (length acc)), acc ++ [v]) + extract acc (Node mi ma lt rt) = + let + (e_lt, l_acc) = extract acc lt + (e_rt, r_acc) = extract l_acc rt + in (Node mi ma e_lt e_rt, r_acc) + + genDecompressed :: forall a. Show a => ([a], Int) -> String + genDecompressed (acc, idx) = + let fn_name = "decompressed_table_" <> show idx + in intercalate "\n" + [ "" + , "{-# NOINLINE " <> fn_name <> " #-}" + , fn_name <> " :: UnicodeByteArray" + , fn_name <> " =" + , intercalate " " [" let compressed = copyAddrToWord8List", "\"" <> mapToAddrLiteral acc "\"#", show (length acc)] + , printf " in newByteArrayFromWord8List (decodeHuffman deserialized_huffman compressed)" + ] + +generateGeneralCategoryCode + :: (String -> String) + -- ^-- How to generate module header where first arg us module name + -> String + -- ^-- Module name + -> Int + -- ^-- Max char length + -> [GeneralCategory] + -- ^-- imported general categories for all symbol list + -> String +generateGeneralCategoryCode mkModuleHeader moduleName char_length cats = + unlines + [ "{-# LANGUAGE NoImplicitPrelude #-}" + , "{-# LANGUAGE MagicHash #-}" + , "{-# LANGUAGE TypeApplications #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(generalCategory)" + , "where" + , "" + , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" + , "import GHC.Internal.Unicode.Bits (UnicodeByteArray, copyAddrToWord8List, newByteArrayFromWord8List, byteArrayLookupIntN)" + , "import GHC.Internal.Unicode.Huffman (HuffmanTree, decodeHuffman, deserializeHuffman)" + , "import GHC.Internal.Num ((-))" + , "import GHC.Internal.Word (Word8)" + , "" + , generateHaskellCode char_length cats + , "" + , genEnumBitmap "generalCategory" Cn (reverse cats) + ] ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/Huffman.hs ===================================== @@ -0,0 +1,83 @@ +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE PackageImports #-} + +module Generator.Huffman + ( mkHuffmanTree + , encodeHuffman + , serializeHuffman + ) + where + +import Data.List (sortBy) +import Data.Ord (comparing) +import Data.Maybe (fromJust) +import Data.Map.Strict (Map) +import qualified Data.Map.Strict as Map +import Data.Word (Word8) +import Data.Bits (shiftL, (.|.)) +import Generator.HuffmanDecode (HuffmanTree (..)) + +data HuffmanTreeFreq a + = HTFLeaf a Int + | HTFNode Int (HuffmanTreeFreq a) (HuffmanTreeFreq a) + deriving stock (Show, Eq, Functor) + +buildHuffmanTree :: Ord a => [(a, Int)] -> HuffmanTree a +buildHuffmanTree freqs = convertTree $ buildTree initialQueue + where + frequency :: HuffmanTreeFreq a -> Int + frequency (HTFLeaf _ f) = f + frequency (HTFNode f _ _) = f + + initialQueue = sortBy (comparing frequency) [HTFLeaf s f | (s, f) <- freqs] + + buildTree [] = error "impossible: empty list is not an appropriate input here" + buildTree [t] = t + buildTree (t1:t2:ts) = + let newNode = HTFNode (frequency t1 + frequency t2) t1 t2 + newQueue = insertBy (comparing frequency) newNode ts + in buildTree newQueue + + insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a] + insertBy _ x [] = [x] + insertBy cmp x ys@(y:ys') + = case cmp x y of + GT -> y : insertBy cmp x ys' + _ -> x : ys + + convertTree :: HuffmanTreeFreq a -> HuffmanTree a + convertTree (HTFLeaf value _) = HTLeaf value + convertTree (HTFNode _ left right) = HTNode (convertTree left) (convertTree right) + +serializeHuffman :: (a -> Word8) -> HuffmanTree a -> [Word8] +serializeHuffman conv (HTLeaf value) = [0x00, conv value] +serializeHuffman conv (HTNode left right) = [0x01] ++ serializeHuffman conv left ++ serializeHuffman conv right + +mkHuffmanTree :: (Ord a) => [a] -> HuffmanTree a +mkHuffmanTree = buildHuffmanTree . Map.toList . huffmanStats + where + huffmanStats :: (Ord a) => [a] -> Map a Int + huffmanStats l = Map.fromListWith (+) [(c, 1) | c <- l] + +encodeHuffman :: (Ord a) => HuffmanTree a -> [a] -> [Word8] +encodeHuffman huffmanTree = packBits . encodeBits (buildHuffmanTable huffmanTree) + where + boolsToWord8 :: [Bool] -> Word8 + boolsToWord8 = foldl (\acc b -> shiftL acc 1 .|. if b then 1 else 0) 0 + + chunksOf :: Int -> [a] -> [[a]] + chunksOf _ [] = [] + chunksOf n xs = take n xs : chunksOf n (drop n xs) + + packBits :: [Bool] -> [Word8] + packBits bits = map boolsToWord8 (chunksOf 8 bits) + + encodeBits :: (Ord a) => Map.Map a [Bool] -> [a] -> [Bool] + encodeBits huffmanTable cc = concatMap (\c -> fromJust $ Map.lookup c huffmanTable) cc + + buildHuffmanTable :: Ord a => HuffmanTree a -> Map a [Bool] + buildHuffmanTable tree = Map.fromList $ buildCodes tree [] + where + buildCodes (HTLeaf s) code = [(s, code)] + buildCodes (HTNode l r) code = buildCodes l (code ++ [False]) ++ buildCodes r (code ++ [True]) ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/HuffmanDecode.hs ===================================== @@ -0,0 +1,52 @@ +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE ExplicitForAll #-} +{-# LANGUAGE TypeApplications #-} + +module Generator.HuffmanDecode + ( decodeHuffman + , deserializeHuffman + , HuffmanTree (..) + ) + where + +import Data.Word (Word8) +import Data.Bits (testBit) +import GHC.Show (Show (..)) +import GHC.Base (Bool, Eq, Functor, (.), (++), error, map) +import qualified GHC.List as L (concatMap) + +data HuffmanTree a + = HTLeaf !a + | HTNode !(HuffmanTree a) !(HuffmanTree a) + deriving stock (Show, Eq, Functor) + +deserializeHuffman :: forall a . (Word8 -> a) -> [Word8] -> HuffmanTree a +deserializeHuffman conv = (\(a, _) -> a) . go + where + go [] = error "Unable to process empty list" + go (0x00:value:rest) = (HTLeaf (conv value), rest) + go (0x01:rest) = + let + (left, rest') = go rest + (right, rest'') = go rest' + in (HTNode left right, rest'') + go v = error ("Unknown type of Huffman tree leaf: " ++ show v) + +decodeHuffman :: HuffmanTree a -> [Word8] -> [a] +decodeHuffman huffman_tree = decodeBits huffman_tree . unpackBits + where + word8ToBools :: Word8 -> [Bool] + word8ToBools w = map (testBit w) [7, 6 .. 0] + + unpackBits :: [Word8] -> [Bool] + unpackBits = L.concatMap word8ToBools + + decodeBits :: HuffmanTree a -> [Bool] -> [a] + decodeBits tree bits = decodeBits' tree bits tree + where + decodeBits' _ [] _ = [] + decodeBits' (HTLeaf c) bs tree' = c : decodeBits' tree' bs tree' + decodeBits' (HTNode l r) (b:bs) tree' = decodeBits' next bs tree' + where next = if b then r else l + ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/RangeSwitch.hs ===================================== @@ -0,0 +1,73 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE BlockArguments #-} +module Generator.RangeSwitch + where + +import Generator.WordEncoding +import Data.Word +import Data.Bifunctor (bimap) +import Generator.Huffman (encodeHuffman) +import Generator.HuffmanDecode (HuffmanTree) + +data Case a = Case + { caseMin :: Int + , caseMax :: Int + , caseConstant :: Either a [a] + } + deriving stock (Show) + +extractLookupIntList :: [Case a] -> [a] +extractLookupIntList = concat . (fmap \(Case _ _ cc) -> either (const []) id cc) + +ranges :: (Enum a, Eq a, Show a) => [a] -> [(Int,Int,a)] +ranges = \case + [] -> [] + (x:xs) -> reverse (go 0 0 x [] xs) + where + go mi ma v rs = \case + [] -> (mi,ma,v):rs + (x:xs) + | x == v -> go mi (ma+1) v rs xs + | otherwise -> go (ma+1) (ma+1) x ((mi,ma,v):rs) xs + +cases :: Int -> [a] -> [(Int,Int,a)] -> [Case a] +cases max_rep all_cats = go + where + go = \case + [] -> [] + (r@(mi,ma,v):rs) + | rangeSize r > max_rep -> Case mi ma (Left v) : go rs + | otherwise -> go_lookup mi ma (Left v) rs + + go_lookup rmi rma mv = \case + [] -> [Case rmi rma mv] + (r@(mi,ma,v):rs) + | rangeSize r > max_rep -> Case rmi rma mv : Case mi ma (Left v) : go rs + | otherwise -> go_lookup rmi ma (Right (take (ma-rmi+1) (drop rmi all_cats))) rs + + rangeSize :: Num a => (a, a, c) -> a + rangeSize (mi, ma, _) = ma - mi + 1 + +rangeCases :: (Enum a, Eq a, Show a) => Int -> [a] -> [Case a] +rangeCases max_char_length cats = cases max_char_length cats (ranges cats) + +data RangeTree a + = Leaf Int Int a + | Node Int Int (RangeTree a) (RangeTree a) + deriving stock (Show) + +buildRangeTree :: [Case a] -> RangeTree (Either a [a]) +buildRangeTree [(Case start end cat)] = Leaf start end cat +buildRangeTree ranges' = + let + mid = length ranges' `div` 2 + (leftRanges, rightRanges) = splitAt mid ranges' + (Case startL _ _) = head leftRanges + (Case _ endR _) = last rightRanges + in Node startL endR (buildRangeTree leftRanges) (buildRangeTree rightRanges) + +rangesToWord8 :: (Show a, Enum a, Ord a) => HuffmanTree a -> [Case a] -> [Case Word8] +rangesToWord8 htree = fmap \(Case mi ma c) -> + Case mi ma $ bimap toWord8 (encodeHuffman htree) c + ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/WordEncoding.hs ===================================== @@ -0,0 +1,40 @@ +module Generator.WordEncoding where + +import Data.Word + +toWord8 :: (Show a, Enum a) => a -> Word8 +toWord8 a = let w = fromEnum a in if 0 <= w && w <= 0xff + then fromIntegral w + else error $ "Cannot convert to Word8: " <> show a + +{-| Encode a list of values as a byte map, using their 'Enum' instance. + +__Note:__ 'Enum' instance must respect the following: + +* @fromEnum minBound >= 0x00@ +* @fromEnum maxBound <= 0xff@ +-} +enumMapToAddrLiteral :: + forall a. (Bounded a, Enum a, Show a) => + -- | Values to encode + [a] -> + -- | String to append + String -> + String +enumMapToAddrLiteral xs cs = foldr go cs xs + where + go :: a -> String -> String + go x acc = '\\' : shows (toWord8 x) acc + +-- Same as enumMapToAddrLiteral but for already converted to Word8 +mapToAddrLiteral :: + forall a. (Show a) => + -- | Values to encode + [a] -> + -- | String to append + String -> + String +mapToAddrLiteral xs cs = foldr go cs xs + where + go :: a -> String -> String + go x acc = '\\' : shows x acc ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs ===================================== @@ -33,6 +33,7 @@ import Streamly.Data.Fold (Fold) import System.Directory (createDirectoryIfMissing) import System.Environment (getEnv) import System.FilePath ((), (<.>)) +import Generator.GeneralCategory (GeneralCategory(Cn), generateGeneralCategoryCode) -- import qualified Data.Set as Set import Streamly.Data.Stream (Stream) @@ -51,17 +52,6 @@ import Prelude hiding (pred) -- Types ------------------------------------------------------------------------------- -data GeneralCategory = - Lu|Ll|Lt| --LC - Lm|Lo| --L - Mn|Mc|Me| --M - Nd|Nl|No| --N - Pc|Pd|Ps|Pe|Pi|Pf|Po| --P - Sm|Sc|Sk|So| --S - Zs|Zl|Zp| --Z - Cc|Cf|Cs|Co|Cn --C - deriving (Show, Bounded, Enum, Read) - data DecompType = DTCanonical | DTCompat | DTFont | DTNoBreak | DTInitial | DTMedial | DTFinal @@ -189,57 +179,6 @@ bitMapToAddrLiteral bs cs = foldr encode cs (unfoldr mkChunks bs) toByte :: [Bool] -> Int toByte xs = sum $ map (\i -> if xs !! i then 1 `shiftL` i else 0) [0..7] -genEnumBitmap :: - forall a. (Bounded a, Enum a, Show a) => - -- | Function name - String -> - -- | Default value - a -> - -- | List of values to encode - [a] -> - String -genEnumBitmap funcName def as = unlines - [ "{-# INLINE " <> funcName <> " #-}" - , funcName <> " :: Char -> Int" - , funcName <> " c = let n = ord c in if n >= " - <> show (length as) - <> " then " - <> show (fromEnum def) - <> " else lookup_bitmap n" - - , "{-# NOINLINE lookup_bitmap #-}" - , "lookup_bitmap :: Int -> Int" - , "lookup_bitmap n = lookupIntN bitmap# n" - , " where" - , " bitmap# = \"" <> enumMapToAddrLiteral as "\"#" - ] - -{-| Encode a list of values as a byte map, using their 'Enum' instance. - -__Note:__ 'Enum' instance must respect the following: - -* @fromEnum minBound >= 0x00@ -* @fromEnum maxBound <= 0xff@ --} -enumMapToAddrLiteral :: - forall a. (Bounded a, Enum a, Show a) => - -- | Values to encode - [a] -> - -- | String to append - String -> - String -enumMapToAddrLiteral xs cs = foldr go cs xs - - where - - go :: a -> String -> String - go x acc = '\\' : shows (toWord8 x) acc - - toWord8 :: a -> Word8 - toWord8 a = let w = fromEnum a in if 0 <= w && w <= 0xff - then fromIntegral w - else error $ "Cannot convert to Word8: " <> show a - {- [NOTE] Disabled generator (normalization) -- This bit of code is duplicated but this duplication allows us to reduce 2 -- dependencies on the executable. @@ -321,21 +260,7 @@ genGeneralCategoryModule moduleName = -- Regular entry else (_generalCategory a : acc, succ (_char a)) - done (acc, _) = unlines - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(generalCategory)" - , "where" - , "" - , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" - , "import GHC.Internal.Unicode.Bits (lookupIntN)" - , "" - , genEnumBitmap "generalCategory" Cn (reverse acc) - ] + done (acc, _) = generateGeneralCategoryCode mkModuleHeader moduleName 220 acc readDecomp :: String -> (Maybe DecompType, Decomp) readDecomp s = ===================================== libraries/ghc-internal/tools/ucd2haskell/ucd.sh ===================================== @@ -71,6 +71,23 @@ run_generator() { # --core-prop XID_Continue \ # --core-prop Pattern_Syntax \ # --core-prop Pattern_White_Space + + echo "-- DO NOT EDIT IT HERE. It is automatically copied from ucd2haskell tool's Generator.HuffmanDecode" > "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + cat "$SCRIPT_DIR/exe/Generator/HuffmanDecode.hs" >> "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + + # See https://stackoverflow.com/a/22084103 + sed -i.bak -e "s/module Generator\.HuffmanDecode/module GHC.Internal.Unicode.Huffman/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import Data\.Word/import GHC.Internal.Word/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import Data\.Bits/import GHC.Internal.Bits/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import GHC\.Show/import GHC.Internal.Show/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import GHC\.Base/import GHC.Internal.Base/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import qualified GHC\.List/import qualified GHC.Internal.List/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" } # Print help text ===================================== libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal ===================================== @@ -50,7 +50,13 @@ executable ucd2haskell ghc-options: -O2 hs-source-dirs: exe main-is: UCD2Haskell.hs - other-modules: Parser.Text + other-modules: + Parser.Text + Generator.RangeSwitch + Generator.GeneralCategory + Generator.WordEncoding + Generator.Huffman + Generator.HuffmanDecode build-depends: base >= 4.7 && < 4.20 , streamly-core >= 0.2.2 && < 0.3 @@ -60,3 +66,4 @@ executable ucd2haskell , containers >= 0.5 && < 0.7 , directory >= 1.3.6 && < 1.3.8 , filepath >= 1.4.2 && < 1.5 + , ghc-prim >= 0.11 && < 0.12 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2445dbfd8f5f826f1fcac09f06fc39101a8213ec -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2445dbfd8f5f826f1fcac09f06fc39101a8213ec You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 08:16:12 2024 From: gitlab at gitlab.haskell.org (Alexander Foremny (@aforemny)) Date: Sun, 09 Jun 2024 04:16:12 -0400 Subject: [Git][ghc/ghc][wip/aforemny/ast] 2 commits: AST: remove occurrences of GHC.Unit.Module.Warnings Message-ID: <666564cc8ede0_f380060f9ac810802c@gitlab.mail> Alexander Foremny pushed to branch wip/aforemny/ast at Glasgow Haskell Compiler / GHC Commits: 172bc6fe by Alexander Foremny at 2024-06-09T10:15:00+02:00 AST: remove occurrences of GHC.Unit.Module.Warnings - - - - - 575ddac4 by Alexander Foremny at 2024-06-09T10:15:24+02:00 AST: remove `EpToken` from InWarningCategory Since `EpToken` is specific to GHC passes, we use an extension field `XInWarningCategoryIn` to abstract over it from `Language.Haskell.Syntax.Decls.WarningCategory`. - - - - - 14 changed files: - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Utils.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Unit/Module/Warnings.hs - compiler/Language/Haskell/Syntax/Decls.hs Changes: ===================================== compiler/GHC/Core/InstEnv.hs ===================================== @@ -55,7 +55,6 @@ import GHC.Types.Name.Set import GHC.Types.Basic import GHC.Types.Id import GHC.Generics (Generic) -import Data.Data ( Data ) import Data.List.NonEmpty ( NonEmpty (..), nonEmpty ) import qualified Data.List.NonEmpty as NE import Data.Maybe ( isJust ) @@ -114,7 +113,6 @@ data ClsInst -- See Note [Implementation of deprecated instances] -- in GHC.Tc.Solver.Dict } - deriving Data -- | A fuzzy comparison function for class instances, intended for sorting -- instances before displaying them to the user. ===================================== compiler/GHC/Hs/Decls.hs ===================================== @@ -1402,3 +1402,5 @@ type instance Anno (Maybe Role) = EpAnnCO type instance Anno CCallConv = EpaLocation type instance Anno Safety = EpaLocation type instance Anno CExportSpec = EpaLocation + +type instance XInWarningCategoryIn (GhcPass _) = EpToken "in" ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -23,6 +23,8 @@ module GHC.Hs.Instances where import Data.Data hiding ( Fixity ) +import Language.Haskell.Syntax.Decls (WarningTxt(..)) + import GHC.Prelude import GHC.Hs.Extension import GHC.Hs.Binds @@ -34,6 +36,8 @@ import GHC.Hs.Pat import GHC.Hs.ImpExp import GHC.Parser.Annotation +import GHC.Core.InstEnv (ClsInst(..)) + -- --------------------------------------------------------------------- -- Data derivations from GHC.Hs----------------------------------------- @@ -578,3 +582,11 @@ deriving instance Data XXPatGhcTc deriving instance Data XViaStrategyPs -- --------------------------------------------------------------------- + +deriving instance Data ClsInst + +-- --------------------------------------------------------------------- + +deriving instance Data (WarningTxt GhcPs) +deriving instance Data (WarningTxt GhcRn) +deriving instance Data (WarningTxt GhcTc) ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -81,7 +81,7 @@ import GHC.Core.TyCon ( Role (..), Injectivity(..), tyConBndrVisForAllTyFlag ) import GHC.Core.DataCon (SrcStrictness(..), SrcUnpackedness(..)) import GHC.Builtin.Types ( constraintKindTyConName ) import GHC.Stg.InferTags.TagSig -import GHC.Parser.Annotation (noLocA) +import GHC.Parser.Annotation (NoAnn, noLocA) import GHC.Hs.Extension ( GhcRn ) import GHC.Hs.Doc ( WithHsDocIdentifiers(..) ) @@ -94,6 +94,8 @@ import GHC.Utils.Panic import GHC.Utils.Misc( dropList, filterByList, notNull, unzipWith, seqList, zipWithEqual ) +import Language.Haskell.Syntax.Decls (XInWarningCategoryIn) + import Control.Monad import System.IO.Unsafe import Control.DeepSeq @@ -597,13 +599,15 @@ ifaceDeclFingerprints hash decl unsafeDupablePerformIO . computeFingerprint (panic "ifaceDeclFingerprints") -fromIfaceWarnings :: IfaceWarnings -> Warnings GhcRn +fromIfaceWarnings + :: (NoAnn (XInWarningCategoryIn GhcRn)) + => IfaceWarnings -> Warnings GhcRn fromIfaceWarnings = \case IfWarnAll txt -> WarnAll (fromIfaceWarningTxt txt) IfWarnSome vs ds -> WarnSome [(occ, fromIfaceWarningTxt txt) | (occ, txt) <- vs] [(occ, fromIfaceWarningTxt txt) | (occ, txt) <- ds] -fromIfaceWarningTxt :: IfaceWarningTxt -> WarningTxt GhcRn +fromIfaceWarningTxt :: (NoAnn (XInWarningCategoryIn GhcRn)) => IfaceWarningTxt -> WarningTxt GhcRn fromIfaceWarningTxt = \case IfWarningTxt mb_cat src strs -> WarningTxt (noLocA . fromWarningCategory <$> mb_cat) src (noLocA <$> map fromIfaceStringLiteralWithNames strs) IfDeprecatedTxt src strs -> DeprecatedTxt src (noLocA <$> map fromIfaceStringLiteralWithNames strs) ===================================== compiler/GHC/Parser.y ===================================== @@ -1994,7 +1994,7 @@ maybe_warning_pragma :: { Maybe (LWarningTxt GhcPs) } (AnnPragma (mo $1) (mc $4) (fst $ unLoc $3))} | {- empty -} { Nothing } -warning_category :: { Maybe (LocatedE InWarningCategory) } +warning_category :: { Maybe (LocatedE (InWarningCategory GhcPs)) } : 'in' STRING { Just (reLoc $ sLL $1 $> $ InWarningCategory (epTok $1) (getSTRINGs $2) (reLoc $ sL1 $2 $ mkWarningCategory (getSTRING $2))) } | {- empty -} { Nothing } ===================================== compiler/GHC/Rename/Module.hs ===================================== @@ -312,11 +312,15 @@ rnWarningTxt (WarningTxt mb_cat st wst) = do unless (validWarningCategory cat) $ addErrAt (locA loc) (TcRnInvalidWarningCategory cat) wst' <- traverse (traverse rnHsDoc) wst - pure (WarningTxt mb_cat st wst') + pure (WarningTxt (fmap rnInWarningCategory <$> mb_cat) st wst') rnWarningTxt (DeprecatedTxt st wst) = do wst' <- traverse (traverse rnHsDoc) wst pure (DeprecatedTxt st wst') +rnInWarningCategory :: InWarningCategory GhcPs -> InWarningCategory GhcRn +rnInWarningCategory (InWarningCategory {iwc_in, iwc_st, iwc_wc}) = + InWarningCategory iwc_in iwc_st iwc_wc + rnLWarningTxt :: LWarningTxt GhcPs -> RnM (LWarningTxt GhcRn) rnLWarningTxt (L loc warn) = L loc <$> rnWarningTxt warn ===================================== compiler/GHC/Rename/Utils.hs ===================================== @@ -73,7 +73,6 @@ import GHC.Data.Bag ( mapBagM, headMaybe ) import Control.Monad import GHC.Settings.Constants ( mAX_TUPLE_SIZE, mAX_CTUPLE_SIZE ) import GHC.Unit.Module -import GHC.Unit.Module.Warnings ( WarningTxt(..) ) import GHC.Iface.Load import qualified GHC.LanguageExtensions as LangExt ===================================== compiler/GHC/Tc/Deriv.hs ===================================== @@ -35,7 +35,6 @@ import GHC.Core.FamInstEnv import GHC.Tc.Gen.HsType import GHC.Core.TyCo.Rep import GHC.Core.TyCo.Ppr ( pprTyVars ) -import GHC.Unit.Module.Warnings import GHC.Rename.Bind import GHC.Rename.Env ===================================== compiler/GHC/Tc/Deriv/Utils.hs ===================================== @@ -52,7 +52,6 @@ import GHC.Core.Type import GHC.Hs import GHC.Driver.Session import GHC.Unit.Module (getModule) -import GHC.Unit.Module.Warnings import GHC.Unit.Module.ModIface (mi_fix) import GHC.Types.Fixity.Env (lookupFixity) ===================================== compiler/GHC/Tc/Errors/Types.hs ===================================== @@ -217,7 +217,6 @@ import Language.Haskell.Syntax.Basic (FieldLabelString(..)) import qualified Data.List.NonEmpty as NE import Data.Typeable (Typeable) -import GHC.Unit.Module.Warnings (WarningCategory, WarningTxt) import qualified GHC.Internal.TH.Syntax as TH import GHC.Generics ( Generic ) ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -64,7 +64,6 @@ import GHC.Core.PatSyn import GHC.Core.Multiplicity ( scaledThing ) import GHC.Unit.Module -import GHC.Unit.Module.Warnings import GHC.Types.Id import GHC.Types.Name import GHC.Types.Name.Reader ===================================== compiler/GHC/Tc/Utils/Instantiate.hs ===================================== @@ -93,7 +93,6 @@ import GHC.Utils.Unique (sameUnique) import GHC.Unit.State import GHC.Unit.External -import GHC.Unit.Module.Warnings import Data.List ( mapAccumL ) import qualified Data.List.NonEmpty as NE ===================================== compiler/GHC/Unit/Module/Warnings.hs ===================================== @@ -16,7 +16,6 @@ module GHC.Unit.Module.Warnings , mkWarningCategory , defaultWarningCategory , validWarningCategory - , InWarningCategory(..) , fromWarningCategory , WarningCategorySet @@ -60,78 +59,20 @@ import GHC.Hs.Extension import GHC.Parser.Annotation import GHC.Utils.Outputable -import GHC.Utils.Binary import GHC.Unicode import Language.Haskell.Syntax.Extension +import Language.Haskell.Syntax.Decls (WarningTxt(..), InWarningCategory(..), XInWarningCategoryIn(), WarningCategory(..)) -import Data.Data import Data.List (isPrefixOf) -import GHC.Generics ( Generic ) -import Control.DeepSeq -{- -Note [Warning categories] -~~~~~~~~~~~~~~~~~~~~~~~~~ -See GHC Proposal 541 for the design of the warning categories feature: -https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0541-warning-pragmas-with-categories.rst -A WARNING pragma may be annotated with a category such as "x-partial" written -after the 'in' keyword, like this: - - {-# WARNING in "x-partial" head "This function is partial..." #-} - -This is represented by the 'Maybe (Located WarningCategory)' field in -'WarningTxt'. The parser will accept an arbitrary string as the category name, -then the renamer (in 'rnWarningTxt') will check it contains only valid -characters, so we can generate a nicer error message than a parse error. - -The corresponding warnings can then be controlled with the -Wx-partial, --Wno-x-partial, -Werror=x-partial and -Wwarn=x-partial flags. Such a flag is -distinguished from an 'unrecognisedWarning' by the flag parser testing -'validWarningCategory'. The 'x-' prefix means we can still usually report an -unrecognised warning where the user has made a mistake. - -A DEPRECATED pragma may not have a user-defined category, and is always treated -as belonging to the special category 'deprecations'. Similarly, a WARNING -pragma without a category belongs to the 'deprecations' category. -Thus the '-Wdeprecations' flag will enable all of the following: - - {-# WARNING in "deprecations" foo "This function is deprecated..." #-} - {-# WARNING foo "This function is deprecated..." #-} - {-# DEPRECATED foo "This function is deprecated..." #-} - -The '-Wwarnings-deprecations' flag is supported for backwards compatibility -purposes as being equivalent to '-Wdeprecations'. - -The '-Wextended-warnings' warning group collects together all warnings with -user-defined categories, so they can be enabled or disabled -collectively. Moreover they are treated as being part of other warning groups -such as '-Wdefault' (see 'warningGroupIncludesExtendedWarnings'). - -'DynFlags' and 'DiagOpts' each contain a set of enabled and a set of fatal -warning categories, just as they do for the finite enumeration of 'WarningFlag's -built in to GHC. These are represented as 'WarningCategorySet's to allow for -the possibility of them being infinite. - --} - -data InWarningCategory - = InWarningCategory - { iwc_in :: !(EpToken "in"), - iwc_st :: !SourceText, - iwc_wc :: (LocatedE WarningCategory) - } deriving Data - -fromWarningCategory :: WarningCategory -> InWarningCategory +fromWarningCategory + :: NoAnn (XInWarningCategoryIn (GhcPass pass)) + => WarningCategory -> InWarningCategory (GhcPass pass) fromWarningCategory wc = InWarningCategory noAnn NoSourceText (noLocA wc) - --- See Note [Warning categories] -newtype WarningCategory = WarningCategory FastString - deriving (Binary, Data, Eq, Outputable, Show, Uniquable, NFData) - mkWarningCategory :: FastString -> WarningCategory mkWarningCategory = WarningCategory @@ -184,6 +125,9 @@ elemWarningCategorySet :: WarningCategory -> WarningCategorySet -> Bool elemWarningCategorySet c (FiniteWarningCategorySet s) = c `elementOfUniqSet` s elemWarningCategorySet c (CofiniteWarningCategorySet s) = not (c `elementOfUniqSet` s) +-- TODO(orphans) This can eventually be moved into `Ghc.Types.Unique` +deriving instance Uniquable WarningCategory + -- | Insert an element into a warning category set. insertWarningCategorySet :: WarningCategory -> WarningCategorySet -> WarningCategorySet insertWarningCategorySet c (FiniteWarningCategorySet s) = FiniteWarningCategorySet (addOneToUniqSet s c) @@ -196,57 +140,43 @@ deleteWarningCategorySet c (CofiniteWarningCategorySet s) = CofiniteWarningCateg type LWarningTxt pass = XRec pass (WarningTxt pass) --- | Warning Text --- --- reason/explanation from a WARNING or DEPRECATED pragma -data WarningTxt pass - = WarningTxt - (Maybe (LocatedE InWarningCategory)) - -- ^ Warning category attached to this WARNING pragma, if any; - -- see Note [Warning categories] - SourceText - [LocatedE (WithHsDocIdentifiers StringLiteral pass)] - | DeprecatedTxt - SourceText - [LocatedE (WithHsDocIdentifiers StringLiteral pass)] - deriving Generic - -- | To which warning category does this WARNING or DEPRECATED pragma belong? -- See Note [Warning categories]. -warningTxtCategory :: WarningTxt pass -> WarningCategory +warningTxtCategory :: WarningTxt (GhcPass pass) -> WarningCategory warningTxtCategory (WarningTxt (Just (L _ (InWarningCategory _ _ (L _ cat)))) _ _) = cat warningTxtCategory _ = defaultWarningCategory -- | The message that the WarningTxt was specified to output -warningTxtMessage :: WarningTxt p -> [LocatedE (WithHsDocIdentifiers StringLiteral p)] +warningTxtMessage :: WarningTxt (GhcPass p) -> [LocatedE (WithHsDocIdentifiers StringLiteral (GhcPass p))] warningTxtMessage (WarningTxt _ _ m) = m warningTxtMessage (DeprecatedTxt _ m) = m -- | True if the 2 WarningTxts have the same category and messages -warningTxtSame :: WarningTxt p1 -> WarningTxt p2 -> Bool +warningTxtSame :: WarningTxt (GhcPass p1) -> WarningTxt (GhcPass p2) -> Bool warningTxtSame w1 w2 = warningTxtCategory w1 == warningTxtCategory w2 && literal_message w1 == literal_message w2 && same_type where - literal_message :: WarningTxt p -> [StringLiteral] + literal_message :: WarningTxt (GhcPass p) -> [StringLiteral] literal_message = map (hsDocString . unLoc) . warningTxtMessage same_type | DeprecatedTxt {} <- w1, DeprecatedTxt {} <- w2 = True | WarningTxt {} <- w1, WarningTxt {} <- w2 = True | otherwise = False -deriving instance Eq InWarningCategory - -deriving instance (Eq (IdP pass)) => Eq (WarningTxt pass) -deriving instance (Data pass, Data (IdP pass)) => Data (WarningTxt pass) - type instance Anno (WarningTxt (GhcPass pass)) = SrcSpanAnnP -instance Outputable InWarningCategory where +-- TODO(orphans) This can eventually be moved to `GHC.Utils.Outputable` +instance Outputable (InWarningCategory (GhcPass p)) where ppr (InWarningCategory _ _ wt) = text "in" <+> doubleQuotes (ppr wt) +type instance Anno WarningCategory = EpaLocation + +-- TODO(orphans) This can eventually be moved to `GHC.Utils.Outputable` +deriving instance Outputable WarningCategory + -instance Outputable (WarningTxt pass) where +instance Outputable (WarningTxt (GhcPass p)) where ppr (WarningTxt mcat lsrc ws) = case lsrc of NoSourceText -> pp_ws ws @@ -267,8 +197,10 @@ pp_ws ws <+> vcat (punctuate comma (map (ppr . unLoc) ws)) <+> text "]" +type instance Anno (InWarningCategory p) = EpaLocation +type instance Anno (WithHsDocIdentifiers StringLiteral p) = EpaLocation -pprWarningTxtForMsg :: WarningTxt p -> SDoc +pprWarningTxtForMsg :: WarningTxt (GhcPass p) -> SDoc pprWarningTxtForMsg (WarningTxt _ _ ws) = doubleQuotes (vcat (map (ftext . sl_fs . hsDocString . unLoc) ws)) pprWarningTxtForMsg (DeprecatedTxt _ ds) @@ -314,7 +246,10 @@ type DeclWarnOccNames pass = [(OccName, WarningTxt pass)] -- | Names that are deprecated as exports type ExportWarnNames pass = [(Name, WarningTxt pass)] -deriving instance Eq (IdP pass) => Eq (Warnings pass) +deriving instance + ( Eq (IdP (GhcPass p)), + Eq (XInWarningCategoryIn (GhcPass p)) + ) => Eq (Warnings (GhcPass p)) emptyWarn :: Warnings p emptyWarn = WarnSome [] [] ===================================== compiler/Language/Haskell/Syntax/Decls.hs ===================================== @@ -1,3 +1,16 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveGeneric #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE UndecidableInstances #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} @@ -87,6 +100,9 @@ module Language.Haskell.Syntax.Decls ( -- * Grouping HsGroup(..), hsGroupInstDecls, + -- * Warnings + WarningTxt(..), InWarningCategory(..), WarningCategory(..), + XInWarningCategoryIn(..), ) where -- friends: @@ -105,10 +121,10 @@ import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CC import GHC.Types.Fixity (LexicalFixity) import GHC.Core.Type (Specificity) -import GHC.Unit.Module.Warnings (WarningTxt) import GHC.Utils.Panic.Plain ( assert ) -import GHC.Hs.Doc (LHsDoc) -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST +import GHC.Hs.Doc (LHsDoc, WithHsDocIdentifiers) -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST +import GHC.Types.SourceText (StringLiteral, SourceText) import Control.Monad import Data.Data hiding (TyCon, Fixity, Infix) @@ -124,6 +140,14 @@ import qualified Data.List import Data.Foldable import Data.Traversable import Data.List.NonEmpty (NonEmpty (..)) +import GHC.Data.FastString (FastString) +-- TODO(no-ghc-import) OK +import GHC.Generics (Generic) +import Control.DeepSeq (NFData) +-- TODO(ghc-import) This can eventually be defined in `GHC.Utils.Binary` +import GHC.Utils.Binary (Binary) +-- TODO(no-ghc-import) OK +import GHC.TypeLits (Symbol) {- ************************************************************************ @@ -1783,3 +1807,100 @@ data RoleAnnotDecl pass -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | XRoleAnnotDecl !(XXRoleAnnotDecl pass) + +-- | Warning Text +-- +-- reason/explanation from a WARNING or DEPRECATED pragma +data WarningTxt pass + = WarningTxt + (Maybe (XRec pass (InWarningCategory pass))) + -- ^ Warning category attached to this WARNING pragma, if any; + -- see Note [Warning categories] + SourceText + [XRec pass (WithHsDocIdentifiers StringLiteral pass)] + | DeprecatedTxt + SourceText + [XRec pass (WithHsDocIdentifiers StringLiteral pass)] + deriving (Generic) + +deriving instance + ( Eq (XRec pass (InWarningCategory pass)), + Eq (XRec pass (WithHsDocIdentifiers StringLiteral pass)) + ) => Eq (WarningTxt pass) + +{- +Note [Warning categories] +~~~~~~~~~~~~~~~~~~~~~~~~~ +See GHC Proposal 541 for the design of the warning categories feature: +https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0541-warning-pragmas-with-categories.rst + +A WARNING pragma may be annotated with a category such as "x-partial" written +after the 'in' keyword, like this: + + {-# WARNING in "x-partial" head "This function is partial..." #-} + +This is represented by the 'Maybe (Located WarningCategory)' field in +'WarningTxt'. The parser will accept an arbitrary string as the category name, +then the renamer (in 'rnWarningTxt') will check it contains only valid +characters, so we can generate a nicer error message than a parse error. + +The corresponding warnings can then be controlled with the -Wx-partial, +-Wno-x-partial, -Werror=x-partial and -Wwarn=x-partial flags. Such a flag is +distinguished from an 'unrecognisedWarning' by the flag parser testing +'validWarningCategory'. The 'x-' prefix means we can still usually report an +unrecognised warning where the user has made a mistake. + +A DEPRECATED pragma may not have a user-defined category, and is always treated +as belonging to the special category 'deprecations'. Similarly, a WARNING +pragma without a category belongs to the 'deprecations' category. +Thus the '-Wdeprecations' flag will enable all of the following: + + {-# WARNING in "deprecations" foo "This function is deprecated..." #-} + {-# WARNING foo "This function is deprecated..." #-} + {-# DEPRECATED foo "This function is deprecated..." #-} + +The '-Wwarnings-deprecations' flag is supported for backwards compatibility +purposes as being equivalent to '-Wdeprecations'. + +The '-Wextended-warnings' warning group collects together all warnings with +user-defined categories, so they can be enabled or disabled +collectively. Moreover they are treated as being part of other warning groups +such as '-Wdefault' (see 'warningGroupIncludesExtendedWarnings'). + +'DynFlags' and 'DiagOpts' each contain a set of enabled and a set of fatal +warning categories, just as they do for the finite enumeration of 'WarningFlag's +built in to GHC. These are represented as 'WarningCategorySet's to allow for +the possibility of them being infinite. + +-} + +data InWarningCategory pass + = InWarningCategory + { iwc_in :: !(XInWarningCategoryIn pass), + iwc_st :: !SourceText, + iwc_wc :: (XRec pass WarningCategory) + } + + +type family XInWarningCategoryIn p + +deriving instance + ( + Eq (XInWarningCategoryIn pass), + Eq (XRec pass WarningCategory) + ) + => Eq (InWarningCategory pass) + +deriving instance Typeable (InWarningCategory pass) + +deriving instance + ( Data pass, + Data (XInWarningCategoryIn pass), + Data (XRec pass WarningCategory) + ) + => Data (InWarningCategory pass) + + +-- See Note [Warning categories] +newtype WarningCategory = WarningCategory FastString + deriving (Binary, Data, Eq, Show, NFData) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1d8a2b02682a4fb1b25827ee63453cc0834f3f55...575ddac47f7f499a0817b51709c5f5c716d36598 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1d8a2b02682a4fb1b25827ee63453cc0834f3f55...575ddac47f7f499a0817b51709c5f5c716d36598 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 08:41:29 2024 From: gitlab at gitlab.haskell.org (Alexander Foremny (@aforemny)) Date: Sun, 09 Jun 2024 04:41:29 -0400 Subject: [Git][ghc/ghc][wip/aforemny/ast] 2 commits: AST: remove occurrences of GHC.Unit.Module.Warnings Message-ID: <66656ab9b302f_1ac9ad3a1ce0504b6@gitlab.mail> Alexander Foremny pushed to branch wip/aforemny/ast at Glasgow Haskell Compiler / GHC Commits: 1faf8105 by Alexander Foremny at 2024-06-09T10:21:03+02:00 AST: remove occurrences of GHC.Unit.Module.Warnings There are a bunch of warning related functions still left in `GHC.Unit.Module.Warnings`, which we may or may not want to move to the module `Language.Haskell.Syntax.Decls`, which is now defining the data types. - - - - - 523dd664 by Alexander Foremny at 2024-06-09T10:21:38+02:00 AST: remove `EpToken` from `InWarningCategory` Since `EpToken` is specific to GHC passes, we use an extension field `XInWarningCategoryIn` to abstract over it from `Language.Haskell.Syntax.Decls.WarningCategory`. - - - - - 14 changed files: - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Utils.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Unit/Module/Warnings.hs - compiler/Language/Haskell/Syntax/Decls.hs Changes: ===================================== compiler/GHC/Core/InstEnv.hs ===================================== @@ -55,7 +55,6 @@ import GHC.Types.Name.Set import GHC.Types.Basic import GHC.Types.Id import GHC.Generics (Generic) -import Data.Data ( Data ) import Data.List.NonEmpty ( NonEmpty (..), nonEmpty ) import qualified Data.List.NonEmpty as NE import Data.Maybe ( isJust ) @@ -114,7 +113,6 @@ data ClsInst -- See Note [Implementation of deprecated instances] -- in GHC.Tc.Solver.Dict } - deriving Data -- | A fuzzy comparison function for class instances, intended for sorting -- instances before displaying them to the user. ===================================== compiler/GHC/Hs/Decls.hs ===================================== @@ -1402,3 +1402,5 @@ type instance Anno (Maybe Role) = EpAnnCO type instance Anno CCallConv = EpaLocation type instance Anno Safety = EpaLocation type instance Anno CExportSpec = EpaLocation + +type instance XInWarningCategoryIn (GhcPass _) = EpToken "in" ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -23,6 +23,8 @@ module GHC.Hs.Instances where import Data.Data hiding ( Fixity ) +import Language.Haskell.Syntax.Decls (WarningTxt(..)) + import GHC.Prelude import GHC.Hs.Extension import GHC.Hs.Binds @@ -34,6 +36,8 @@ import GHC.Hs.Pat import GHC.Hs.ImpExp import GHC.Parser.Annotation +import GHC.Core.InstEnv (ClsInst(..)) + -- --------------------------------------------------------------------- -- Data derivations from GHC.Hs----------------------------------------- @@ -578,3 +582,11 @@ deriving instance Data XXPatGhcTc deriving instance Data XViaStrategyPs -- --------------------------------------------------------------------- + +deriving instance Data ClsInst + +-- --------------------------------------------------------------------- + +deriving instance Data (WarningTxt GhcPs) +deriving instance Data (WarningTxt GhcRn) +deriving instance Data (WarningTxt GhcTc) ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -81,7 +81,7 @@ import GHC.Core.TyCon ( Role (..), Injectivity(..), tyConBndrVisForAllTyFlag ) import GHC.Core.DataCon (SrcStrictness(..), SrcUnpackedness(..)) import GHC.Builtin.Types ( constraintKindTyConName ) import GHC.Stg.InferTags.TagSig -import GHC.Parser.Annotation (noLocA) +import GHC.Parser.Annotation (NoAnn, noLocA) import GHC.Hs.Extension ( GhcRn ) import GHC.Hs.Doc ( WithHsDocIdentifiers(..) ) @@ -94,6 +94,8 @@ import GHC.Utils.Panic import GHC.Utils.Misc( dropList, filterByList, notNull, unzipWith, seqList, zipWithEqual ) +import Language.Haskell.Syntax.Decls (XInWarningCategoryIn) + import Control.Monad import System.IO.Unsafe import Control.DeepSeq @@ -597,13 +599,17 @@ ifaceDeclFingerprints hash decl unsafeDupablePerformIO . computeFingerprint (panic "ifaceDeclFingerprints") -fromIfaceWarnings :: IfaceWarnings -> Warnings GhcRn +fromIfaceWarnings + :: (NoAnn (XInWarningCategoryIn GhcRn)) + => IfaceWarnings -> Warnings GhcRn fromIfaceWarnings = \case IfWarnAll txt -> WarnAll (fromIfaceWarningTxt txt) IfWarnSome vs ds -> WarnSome [(occ, fromIfaceWarningTxt txt) | (occ, txt) <- vs] [(occ, fromIfaceWarningTxt txt) | (occ, txt) <- ds] -fromIfaceWarningTxt :: IfaceWarningTxt -> WarningTxt GhcRn +fromIfaceWarningTxt + :: (NoAnn (XInWarningCategoryIn GhcRn)) + => IfaceWarningTxt -> WarningTxt GhcRn fromIfaceWarningTxt = \case IfWarningTxt mb_cat src strs -> WarningTxt (noLocA . fromWarningCategory <$> mb_cat) src (noLocA <$> map fromIfaceStringLiteralWithNames strs) IfDeprecatedTxt src strs -> DeprecatedTxt src (noLocA <$> map fromIfaceStringLiteralWithNames strs) ===================================== compiler/GHC/Parser.y ===================================== @@ -1994,7 +1994,7 @@ maybe_warning_pragma :: { Maybe (LWarningTxt GhcPs) } (AnnPragma (mo $1) (mc $4) (fst $ unLoc $3))} | {- empty -} { Nothing } -warning_category :: { Maybe (LocatedE InWarningCategory) } +warning_category :: { Maybe (LocatedE (InWarningCategory GhcPs)) } : 'in' STRING { Just (reLoc $ sLL $1 $> $ InWarningCategory (epTok $1) (getSTRINGs $2) (reLoc $ sL1 $2 $ mkWarningCategory (getSTRING $2))) } | {- empty -} { Nothing } ===================================== compiler/GHC/Rename/Module.hs ===================================== @@ -312,11 +312,15 @@ rnWarningTxt (WarningTxt mb_cat st wst) = do unless (validWarningCategory cat) $ addErrAt (locA loc) (TcRnInvalidWarningCategory cat) wst' <- traverse (traverse rnHsDoc) wst - pure (WarningTxt mb_cat st wst') + pure (WarningTxt (fmap rnInWarningCategory <$> mb_cat) st wst') rnWarningTxt (DeprecatedTxt st wst) = do wst' <- traverse (traverse rnHsDoc) wst pure (DeprecatedTxt st wst') +rnInWarningCategory :: InWarningCategory GhcPs -> InWarningCategory GhcRn +rnInWarningCategory (InWarningCategory {iwc_in, iwc_st, iwc_wc}) = + InWarningCategory iwc_in iwc_st iwc_wc + rnLWarningTxt :: LWarningTxt GhcPs -> RnM (LWarningTxt GhcRn) rnLWarningTxt (L loc warn) = L loc <$> rnWarningTxt warn ===================================== compiler/GHC/Rename/Utils.hs ===================================== @@ -73,7 +73,6 @@ import GHC.Data.Bag ( mapBagM, headMaybe ) import Control.Monad import GHC.Settings.Constants ( mAX_TUPLE_SIZE, mAX_CTUPLE_SIZE ) import GHC.Unit.Module -import GHC.Unit.Module.Warnings ( WarningTxt(..) ) import GHC.Iface.Load import qualified GHC.LanguageExtensions as LangExt ===================================== compiler/GHC/Tc/Deriv.hs ===================================== @@ -35,7 +35,6 @@ import GHC.Core.FamInstEnv import GHC.Tc.Gen.HsType import GHC.Core.TyCo.Rep import GHC.Core.TyCo.Ppr ( pprTyVars ) -import GHC.Unit.Module.Warnings import GHC.Rename.Bind import GHC.Rename.Env ===================================== compiler/GHC/Tc/Deriv/Utils.hs ===================================== @@ -52,7 +52,6 @@ import GHC.Core.Type import GHC.Hs import GHC.Driver.Session import GHC.Unit.Module (getModule) -import GHC.Unit.Module.Warnings import GHC.Unit.Module.ModIface (mi_fix) import GHC.Types.Fixity.Env (lookupFixity) ===================================== compiler/GHC/Tc/Errors/Types.hs ===================================== @@ -217,7 +217,6 @@ import Language.Haskell.Syntax.Basic (FieldLabelString(..)) import qualified Data.List.NonEmpty as NE import Data.Typeable (Typeable) -import GHC.Unit.Module.Warnings (WarningCategory, WarningTxt) import qualified GHC.Internal.TH.Syntax as TH import GHC.Generics ( Generic ) ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -64,7 +64,6 @@ import GHC.Core.PatSyn import GHC.Core.Multiplicity ( scaledThing ) import GHC.Unit.Module -import GHC.Unit.Module.Warnings import GHC.Types.Id import GHC.Types.Name import GHC.Types.Name.Reader ===================================== compiler/GHC/Tc/Utils/Instantiate.hs ===================================== @@ -93,7 +93,6 @@ import GHC.Utils.Unique (sameUnique) import GHC.Unit.State import GHC.Unit.External -import GHC.Unit.Module.Warnings import Data.List ( mapAccumL ) import qualified Data.List.NonEmpty as NE ===================================== compiler/GHC/Unit/Module/Warnings.hs ===================================== @@ -16,7 +16,6 @@ module GHC.Unit.Module.Warnings , mkWarningCategory , defaultWarningCategory , validWarningCategory - , InWarningCategory(..) , fromWarningCategory , WarningCategorySet @@ -60,78 +59,20 @@ import GHC.Hs.Extension import GHC.Parser.Annotation import GHC.Utils.Outputable -import GHC.Utils.Binary import GHC.Unicode import Language.Haskell.Syntax.Extension +import Language.Haskell.Syntax.Decls (WarningTxt(..), InWarningCategory(..), XInWarningCategoryIn(), WarningCategory(..)) -import Data.Data import Data.List (isPrefixOf) -import GHC.Generics ( Generic ) -import Control.DeepSeq -{- -Note [Warning categories] -~~~~~~~~~~~~~~~~~~~~~~~~~ -See GHC Proposal 541 for the design of the warning categories feature: -https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0541-warning-pragmas-with-categories.rst -A WARNING pragma may be annotated with a category such as "x-partial" written -after the 'in' keyword, like this: - - {-# WARNING in "x-partial" head "This function is partial..." #-} - -This is represented by the 'Maybe (Located WarningCategory)' field in -'WarningTxt'. The parser will accept an arbitrary string as the category name, -then the renamer (in 'rnWarningTxt') will check it contains only valid -characters, so we can generate a nicer error message than a parse error. - -The corresponding warnings can then be controlled with the -Wx-partial, --Wno-x-partial, -Werror=x-partial and -Wwarn=x-partial flags. Such a flag is -distinguished from an 'unrecognisedWarning' by the flag parser testing -'validWarningCategory'. The 'x-' prefix means we can still usually report an -unrecognised warning where the user has made a mistake. - -A DEPRECATED pragma may not have a user-defined category, and is always treated -as belonging to the special category 'deprecations'. Similarly, a WARNING -pragma without a category belongs to the 'deprecations' category. -Thus the '-Wdeprecations' flag will enable all of the following: - - {-# WARNING in "deprecations" foo "This function is deprecated..." #-} - {-# WARNING foo "This function is deprecated..." #-} - {-# DEPRECATED foo "This function is deprecated..." #-} - -The '-Wwarnings-deprecations' flag is supported for backwards compatibility -purposes as being equivalent to '-Wdeprecations'. - -The '-Wextended-warnings' warning group collects together all warnings with -user-defined categories, so they can be enabled or disabled -collectively. Moreover they are treated as being part of other warning groups -such as '-Wdefault' (see 'warningGroupIncludesExtendedWarnings'). - -'DynFlags' and 'DiagOpts' each contain a set of enabled and a set of fatal -warning categories, just as they do for the finite enumeration of 'WarningFlag's -built in to GHC. These are represented as 'WarningCategorySet's to allow for -the possibility of them being infinite. - --} - -data InWarningCategory - = InWarningCategory - { iwc_in :: !(EpToken "in"), - iwc_st :: !SourceText, - iwc_wc :: (LocatedE WarningCategory) - } deriving Data - -fromWarningCategory :: WarningCategory -> InWarningCategory +fromWarningCategory + :: NoAnn (XInWarningCategoryIn (GhcPass pass)) + => WarningCategory -> InWarningCategory (GhcPass pass) fromWarningCategory wc = InWarningCategory noAnn NoSourceText (noLocA wc) - --- See Note [Warning categories] -newtype WarningCategory = WarningCategory FastString - deriving (Binary, Data, Eq, Outputable, Show, Uniquable, NFData) - mkWarningCategory :: FastString -> WarningCategory mkWarningCategory = WarningCategory @@ -184,6 +125,9 @@ elemWarningCategorySet :: WarningCategory -> WarningCategorySet -> Bool elemWarningCategorySet c (FiniteWarningCategorySet s) = c `elementOfUniqSet` s elemWarningCategorySet c (CofiniteWarningCategorySet s) = not (c `elementOfUniqSet` s) +-- TODO(orphans) This can eventually be moved into `Ghc.Types.Unique` +deriving instance Uniquable WarningCategory + -- | Insert an element into a warning category set. insertWarningCategorySet :: WarningCategory -> WarningCategorySet -> WarningCategorySet insertWarningCategorySet c (FiniteWarningCategorySet s) = FiniteWarningCategorySet (addOneToUniqSet s c) @@ -196,57 +140,43 @@ deleteWarningCategorySet c (CofiniteWarningCategorySet s) = CofiniteWarningCateg type LWarningTxt pass = XRec pass (WarningTxt pass) --- | Warning Text --- --- reason/explanation from a WARNING or DEPRECATED pragma -data WarningTxt pass - = WarningTxt - (Maybe (LocatedE InWarningCategory)) - -- ^ Warning category attached to this WARNING pragma, if any; - -- see Note [Warning categories] - SourceText - [LocatedE (WithHsDocIdentifiers StringLiteral pass)] - | DeprecatedTxt - SourceText - [LocatedE (WithHsDocIdentifiers StringLiteral pass)] - deriving Generic - -- | To which warning category does this WARNING or DEPRECATED pragma belong? -- See Note [Warning categories]. -warningTxtCategory :: WarningTxt pass -> WarningCategory +warningTxtCategory :: WarningTxt (GhcPass pass) -> WarningCategory warningTxtCategory (WarningTxt (Just (L _ (InWarningCategory _ _ (L _ cat)))) _ _) = cat warningTxtCategory _ = defaultWarningCategory -- | The message that the WarningTxt was specified to output -warningTxtMessage :: WarningTxt p -> [LocatedE (WithHsDocIdentifiers StringLiteral p)] +warningTxtMessage :: WarningTxt (GhcPass p) -> [LocatedE (WithHsDocIdentifiers StringLiteral (GhcPass p))] warningTxtMessage (WarningTxt _ _ m) = m warningTxtMessage (DeprecatedTxt _ m) = m -- | True if the 2 WarningTxts have the same category and messages -warningTxtSame :: WarningTxt p1 -> WarningTxt p2 -> Bool +warningTxtSame :: WarningTxt (GhcPass p1) -> WarningTxt (GhcPass p2) -> Bool warningTxtSame w1 w2 = warningTxtCategory w1 == warningTxtCategory w2 && literal_message w1 == literal_message w2 && same_type where - literal_message :: WarningTxt p -> [StringLiteral] + literal_message :: WarningTxt (GhcPass p) -> [StringLiteral] literal_message = map (hsDocString . unLoc) . warningTxtMessage same_type | DeprecatedTxt {} <- w1, DeprecatedTxt {} <- w2 = True | WarningTxt {} <- w1, WarningTxt {} <- w2 = True | otherwise = False -deriving instance Eq InWarningCategory - -deriving instance (Eq (IdP pass)) => Eq (WarningTxt pass) -deriving instance (Data pass, Data (IdP pass)) => Data (WarningTxt pass) - type instance Anno (WarningTxt (GhcPass pass)) = SrcSpanAnnP -instance Outputable InWarningCategory where +-- TODO(orphans) This can eventually be moved to `GHC.Utils.Outputable` +instance Outputable (InWarningCategory (GhcPass p)) where ppr (InWarningCategory _ _ wt) = text "in" <+> doubleQuotes (ppr wt) +type instance Anno WarningCategory = EpaLocation + +-- TODO(orphans) This can eventually be moved to `GHC.Utils.Outputable` +deriving instance Outputable WarningCategory + -instance Outputable (WarningTxt pass) where +instance Outputable (WarningTxt (GhcPass p)) where ppr (WarningTxt mcat lsrc ws) = case lsrc of NoSourceText -> pp_ws ws @@ -267,8 +197,10 @@ pp_ws ws <+> vcat (punctuate comma (map (ppr . unLoc) ws)) <+> text "]" +type instance Anno (InWarningCategory p) = EpaLocation +type instance Anno (WithHsDocIdentifiers StringLiteral p) = EpaLocation -pprWarningTxtForMsg :: WarningTxt p -> SDoc +pprWarningTxtForMsg :: WarningTxt (GhcPass p) -> SDoc pprWarningTxtForMsg (WarningTxt _ _ ws) = doubleQuotes (vcat (map (ftext . sl_fs . hsDocString . unLoc) ws)) pprWarningTxtForMsg (DeprecatedTxt _ ds) @@ -314,7 +246,10 @@ type DeclWarnOccNames pass = [(OccName, WarningTxt pass)] -- | Names that are deprecated as exports type ExportWarnNames pass = [(Name, WarningTxt pass)] -deriving instance Eq (IdP pass) => Eq (Warnings pass) +deriving instance + ( Eq (IdP (GhcPass p)), + Eq (XInWarningCategoryIn (GhcPass p)) + ) => Eq (Warnings (GhcPass p)) emptyWarn :: Warnings p emptyWarn = WarnSome [] [] ===================================== compiler/Language/Haskell/Syntax/Decls.hs ===================================== @@ -1,4 +1,3 @@ - {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveDataTypeable #-} @@ -87,6 +86,9 @@ module Language.Haskell.Syntax.Decls ( -- * Grouping HsGroup(..), hsGroupInstDecls, + -- * Warnings + WarningTxt(..), InWarningCategory(..), WarningCategory(..), + XInWarningCategoryIn, ) where -- friends: @@ -105,10 +107,10 @@ import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CC import GHC.Types.Fixity (LexicalFixity) import GHC.Core.Type (Specificity) -import GHC.Unit.Module.Warnings (WarningTxt) import GHC.Utils.Panic.Plain ( assert ) -import GHC.Hs.Doc (LHsDoc) -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST +import GHC.Hs.Doc (LHsDoc, WithHsDocIdentifiers) -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST +import GHC.Types.SourceText (StringLiteral, SourceText) import Control.Monad import Data.Data hiding (TyCon, Fixity, Infix) @@ -124,6 +126,12 @@ import qualified Data.List import Data.Foldable import Data.Traversable import Data.List.NonEmpty (NonEmpty (..)) +import GHC.Data.FastString (FastString) +-- TODO(no-ghc-import) OK +import GHC.Generics (Generic) +import Control.DeepSeq (NFData) +-- TODO(ghc-import) This can eventually be defined in `GHC.Utils.Binary` +import GHC.Utils.Binary (Binary) {- ************************************************************************ @@ -1783,3 +1791,100 @@ data RoleAnnotDecl pass -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | XRoleAnnotDecl !(XXRoleAnnotDecl pass) + +-- | Warning Text +-- +-- reason/explanation from a WARNING or DEPRECATED pragma +data WarningTxt pass + = WarningTxt + (Maybe (XRec pass (InWarningCategory pass))) + -- ^ Warning category attached to this WARNING pragma, if any; + -- see Note [Warning categories] + SourceText + [XRec pass (WithHsDocIdentifiers StringLiteral pass)] + | DeprecatedTxt + SourceText + [XRec pass (WithHsDocIdentifiers StringLiteral pass)] + deriving (Generic) + +deriving instance + ( Eq (XRec pass (InWarningCategory pass)), + Eq (XRec pass (WithHsDocIdentifiers StringLiteral pass)) + ) => Eq (WarningTxt pass) + +{- +Note [Warning categories] +~~~~~~~~~~~~~~~~~~~~~~~~~ +See GHC Proposal 541 for the design of the warning categories feature: +https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0541-warning-pragmas-with-categories.rst + +A WARNING pragma may be annotated with a category such as "x-partial" written +after the 'in' keyword, like this: + + {-# WARNING in "x-partial" head "This function is partial..." #-} + +This is represented by the 'Maybe (Located WarningCategory)' field in +'WarningTxt'. The parser will accept an arbitrary string as the category name, +then the renamer (in 'rnWarningTxt') will check it contains only valid +characters, so we can generate a nicer error message than a parse error. + +The corresponding warnings can then be controlled with the -Wx-partial, +-Wno-x-partial, -Werror=x-partial and -Wwarn=x-partial flags. Such a flag is +distinguished from an 'unrecognisedWarning' by the flag parser testing +'validWarningCategory'. The 'x-' prefix means we can still usually report an +unrecognised warning where the user has made a mistake. + +A DEPRECATED pragma may not have a user-defined category, and is always treated +as belonging to the special category 'deprecations'. Similarly, a WARNING +pragma without a category belongs to the 'deprecations' category. +Thus the '-Wdeprecations' flag will enable all of the following: + + {-# WARNING in "deprecations" foo "This function is deprecated..." #-} + {-# WARNING foo "This function is deprecated..." #-} + {-# DEPRECATED foo "This function is deprecated..." #-} + +The '-Wwarnings-deprecations' flag is supported for backwards compatibility +purposes as being equivalent to '-Wdeprecations'. + +The '-Wextended-warnings' warning group collects together all warnings with +user-defined categories, so they can be enabled or disabled +collectively. Moreover they are treated as being part of other warning groups +such as '-Wdefault' (see 'warningGroupIncludesExtendedWarnings'). + +'DynFlags' and 'DiagOpts' each contain a set of enabled and a set of fatal +warning categories, just as they do for the finite enumeration of 'WarningFlag's +built in to GHC. These are represented as 'WarningCategorySet's to allow for +the possibility of them being infinite. + +-} + +data InWarningCategory pass + = InWarningCategory + { iwc_in :: !(XInWarningCategoryIn pass), + iwc_st :: !SourceText, + iwc_wc :: (XRec pass WarningCategory) + } + + +type family XInWarningCategoryIn p + +deriving instance + ( + Eq (XInWarningCategoryIn pass), + Eq (XRec pass WarningCategory) + ) + => Eq (InWarningCategory pass) + +deriving instance Typeable (InWarningCategory pass) + +deriving instance + ( Data pass, + Data (XInWarningCategoryIn pass), + Data (XRec pass WarningCategory) + ) + => Data (InWarningCategory pass) + + +-- See Note [Warning categories] +newtype WarningCategory = WarningCategory FastString + deriving (Binary, Data, Eq, Show, NFData) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/575ddac47f7f499a0817b51709c5f5c716d36598...523dd6642535c234d0bfd40fe80c679db281779b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/575ddac47f7f499a0817b51709c5f5c716d36598...523dd6642535c234d0bfd40fe80c679db281779b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 08:52:22 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sun, 09 Jun 2024 04:52:22 -0400 Subject: [Git][ghc/ghc][wip/kill-pre-c11] 8 commits: Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw Message-ID: <66656d46ca3c_1ac9ad51368c5245b@gitlab.mail> Cheng Shao pushed to branch wip/kill-pre-c11 at Glasgow Haskell Compiler / GHC Commits: edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - af425a52 by Cheng Shao at 2024-06-09T08:50:11+00:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - 41919b33 by Cheng Shao at 2024-06-09T08:51:44+00:00 WIP: always assume __GNUC__ >= 4 - - - - - 23 changed files: - CODEOWNERS - compiler/GHC/CmmToAsm/X86/Instr.hs - libraries/ghc-internal/CHANGELOG.md - libraries/ghc-internal/prologue.txt - libraries/ghc-internal/src/GHC/Internal/Exception.hs - libraries/ghc-prim/cbits/atomic.c - libraries/ghc-prim/cbits/ctz.c - rts/Hash.c - rts/Inlines.c - rts/RtsStartup.c - rts/RtsSymbols.c - rts/Task.c - rts/Task.h - rts/include/Rts.h - rts/include/Stg.h - rts/include/rts/Types.h - rts/include/stg/DLL.h - rts/sm/BlockAlloc.c - rts/sm/Evac.h - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 Changes: ===================================== CODEOWNERS ===================================== @@ -60,6 +60,7 @@ /libraries/base/ @hvr /libraries/ghci/ @simonmar /libraries/template-haskell/ @rae +/testsuite/tests/interface-stability/ @core-libraries [Internal utilities and libraries] /utils/iserv-proxy/ @angerman @simonmar ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -198,10 +198,13 @@ data Instr -- Moves. | MOV Format Operand Operand - -- ^ N.B. when used with the 'II64' 'Format', the source + -- ^ N.B. Due to AT&T assembler quirks, when used with 'II64' + -- 'Format' immediate source and memory target operand, the source -- operand is interpreted to be a 32-bit sign-extended value. - -- True 64-bit operands need to be moved with @MOVABS@, which we - -- currently don't use. + -- True 64-bit operands need to be either first moved to a register or moved + -- with @MOVABS@; we currently do not use this instruction in GHC. + -- See https://stackoverflow.com/questions/52434073/whats-the-difference-between-the-x86-64-att-instructions-movq-and-movabsq. + | MOVD Format Operand Operand -- ^ MOVD/MOVQ SSE2 instructions -- (bitcast between a general purpose -- register and a float register). ===================================== libraries/ghc-internal/CHANGELOG.md ===================================== @@ -1,5 +1,5 @@ # Revision history for `ghc-internal` -## 0.1.0.0 -- YYYY-mm-dd +## 9.1001.0 -- 2024-05-01 -* First version. Released on an unsuspecting world. +* Package created containing implementation moved from `base`. ===================================== libraries/ghc-internal/prologue.txt ===================================== @@ -1,3 +1,2 @@ -This package contains the @Prelude@ and its support libraries, and a large -collection of useful libraries ranging from data structures to parsing -combinators and debugging utilities. +This package contains the implementation of GHC's standard libraries and is +not intended for use by end-users. ===================================== libraries/ghc-internal/src/GHC/Internal/Exception.hs ===================================== @@ -79,7 +79,7 @@ import GHC.Internal.Exception.Type -- WARNING: You may want to use 'throwIO' instead so that your pure code -- stays exception-free. throw :: forall (r :: RuntimeRep). forall (a :: TYPE r). forall e. - (?callStack :: CallStack, Exception e) => e -> a + (HasCallStack, Exception e) => e -> a throw e = let !se = unsafePerformIO (toExceptionWithBacktrace e) in raise# se ===================================== libraries/ghc-prim/cbits/atomic.c ===================================== @@ -163,7 +163,7 @@ hs_atomic_and64(StgWord x, StgWord64 val) #pragma GCC diagnostic push #if defined(__clang__) #pragma GCC diagnostic ignored "-Wsync-fetch-and-nand-semantics-changed" -#elif defined(__GNUC__) +#else #pragma GCC diagnostic ignored "-Wsync-nand" #endif ===================================== libraries/ghc-prim/cbits/ctz.c ===================================== @@ -31,7 +31,7 @@ hs_ctz32(StgWord x) StgWord hs_ctz64(StgWord64 x) { -#if defined(__GNUC__) && (defined(i386_HOST_ARCH) || defined(powerpc_HOST_ARCH)) +#if defined(i386_HOST_ARCH) || defined(powerpc_HOST_ARCH) /* On Linux/i386, the 64bit `__builtin_ctzll()` intrinsic doesn't get inlined by GCC but rather a short `__ctzdi2` runtime function is inserted when needed into compiled object files. ===================================== rts/Hash.c ===================================== @@ -14,18 +14,6 @@ #include "Hash.h" #include "RtsUtils.h" -/* This file needs to be compiled with vectorization enabled. Unfortunately - since we compile these things these days with cabal we can no longer - specify optimization per file. So we have to resort to pragmas. */ -#if defined(__GNUC__) || defined(__GNUG__) -#if !defined(__clang__) -#if !defined(DEBUG) -#pragma GCC push_options -#pragma GCC optimize ("O3") -#endif -#endif -#endif - #define XXH_INLINE_ALL #include "xxhash.h" @@ -563,12 +551,3 @@ int keyCountHashTable (HashTable *table) { return table->kcount; } - - -#if defined(__GNUC__) || defined(__GNUG__) -#if !defined(__clang__) -#if !defined(DEBUG) -#pragma GCC pop_options -#endif -#endif -#endif ===================================== rts/Inlines.c ===================================== @@ -1,6 +1,7 @@ -// all functions declared with EXTERN_INLINE in the header files get -// compiled for real here, just in case the definition was not inlined -// at some call site: +// All functions declared with EXTERN_INLINE in the header files get +// compiled for real here. Some of them are called by Cmm (e.g. +// recordClosureMutated) and therefore the real thing needs to reside +// in Inlines.o for Cmm ccall to work. #define KEEP_INLINES #include "rts/PosixSource.h" #include "Rts.h" ===================================== rts/RtsStartup.c ===================================== @@ -123,13 +123,7 @@ void _fpreset(void) x86_init_fpu(); } -#if defined(__GNUC__) void __attribute__((alias("_fpreset"))) fpreset(void); -#else -void fpreset(void) { - _fpreset(); -} -#endif /* Set the console's CodePage to UTF-8 if using the new I/O manager and the CP is still the default one. */ ===================================== rts/RtsSymbols.c ===================================== @@ -956,7 +956,7 @@ extern char **environ; RTS_INTCHAR_SYMBOLS // 64-bit support functions in libgcc.a -#if defined(__GNUC__) && SIZEOF_VOID_P <= 4 && !defined(_ABIN32) +#if SIZEOF_VOID_P <= 4 && !defined(_ABIN32) #define RTS_LIBGCC_SYMBOLS \ SymI_NeedsProto(__divdi3) \ SymI_NeedsProto(__udivdi3) \ @@ -967,7 +967,7 @@ extern char **environ; SymI_NeedsProto(__ashrdi3) \ SymI_NeedsProto(__lshrdi3) \ SymI_NeedsProto(__fixunsdfdi) -#elif defined(__GNUC__) && SIZEOF_VOID_P == 8 +#elif SIZEOF_VOID_P == 8 #define RTS_LIBGCC_SYMBOLS \ SymI_NeedsProto(__udivti3) \ SymI_NeedsProto(__umodti3) ===================================== rts/Task.c ===================================== @@ -52,7 +52,7 @@ Mutex all_tasks_mutex; // A thread-local-storage key that we can use to get access to the // current thread's Task structure. #if defined(THREADED_RTS) -# if defined(MYTASK_USE_TLV) +# if CC_SUPPORTS_TLS __thread Task *my_task; # else ThreadLocalKey currentTaskKey; @@ -75,7 +75,7 @@ initTaskManager (void) peakWorkerCount = 0; tasksInitialized = 1; #if defined(THREADED_RTS) -#if !defined(MYTASK_USE_TLV) +#if !CC_SUPPORTS_TLS newThreadLocalKey(¤tTaskKey); #endif initMutex(&all_tasks_mutex); @@ -109,7 +109,7 @@ freeTaskManager (void) #if defined(THREADED_RTS) closeMutex(&all_tasks_mutex); -#if !defined(MYTASK_USE_TLV) +#if !CC_SUPPORTS_TLS freeThreadLocalKey(¤tTaskKey); #endif #endif ===================================== rts/Task.h ===================================== @@ -265,11 +265,7 @@ extern uint32_t peakWorkerCount; // A thread-local-storage key that we can use to get access to the // current thread's Task structure. #if defined(THREADED_RTS) -#if ((defined(linux_HOST_OS) && \ - (defined(i386_HOST_ARCH) || defined(x86_64_HOST_ARCH))) || \ - (defined(mingw32_HOST_OS) && __GNUC__ >= 4 && __GNUC_MINOR__ >= 4)) && \ - (!defined(CC_LLVM_BACKEND)) -#define MYTASK_USE_TLV +#if CC_SUPPORTS_TLS extern __thread Task *my_task; #else extern ThreadLocalKey currentTaskKey; @@ -287,7 +283,7 @@ extern Task *my_task; INLINE_HEADER Task * myTask (void) { -#if defined(THREADED_RTS) && !defined(MYTASK_USE_TLV) +#if defined(THREADED_RTS) && !CC_SUPPORTS_TLS return (Task*) getThreadLocalVar(¤tTaskKey); #else return my_task; @@ -297,7 +293,7 @@ myTask (void) INLINE_HEADER void setMyTask (Task *task) { -#if defined(THREADED_RTS) && !defined(MYTASK_USE_TLV) +#if defined(THREADED_RTS) && !CC_SUPPORTS_TLS setThreadLocalVar(¤tTaskKey,task); #else my_task = task; ===================================== rts/include/Rts.h ===================================== @@ -54,11 +54,7 @@ extern "C" { #include "rts/Types.h" #include "rts/Time.h" -#if __GNUC__ >= 3 #define ATTRIBUTE_ALIGNED(n) __attribute__((aligned(n))) -#else -#define ATTRIBUTE_ALIGNED(n) /*nothing*/ -#endif // Symbols that are extern, but private to the RTS, are declared // with visibility "hidden" to hide them outside the RTS shared @@ -69,24 +65,11 @@ extern "C" { #define RTS_PRIVATE /* disabled: RTS_PRIVATE */ #endif -#if __GNUC__ >= 4 #define RTS_UNLIKELY(p) __builtin_expect((p),0) -#else -#define RTS_UNLIKELY(p) (p) -#endif -#if __GNUC__ >= 4 #define RTS_LIKELY(p) __builtin_expect(!!(p), 1) -#else -#define RTS_LIKELY(p) (p) -#endif -/* __builtin_unreachable is supported since GNU C 4.5 */ -#if __GNUC__ > 4 || (__GNUC__ == 4 && __GNUC_MINOR__ >= 5) #define RTS_UNREACHABLE __builtin_unreachable() -#else -#define RTS_UNREACHABLE abort() -#endif /* Prefetch primitives */ #define prefetchForRead(ptr) __builtin_prefetch(ptr, 0) @@ -377,9 +360,7 @@ TICK_VAR(2) Useful macros and inline functions -------------------------------------------------------------------------- */ -#if defined(__GNUC__) #define SUPPORTS_TYPEOF -#endif #if defined(SUPPORTS_TYPEOF) #define stg_min(a,b) ({typeof(a) _a = (a), _b = (b); _a <= _b ? _a : _b; }) ===================================== rts/include/Stg.h ===================================== @@ -114,72 +114,26 @@ * 'Portable' inlining: * INLINE_HEADER is for inline functions in header files (macros) * STATIC_INLINE is for inline functions in source files - * EXTERN_INLINE is for functions that we want to inline sometimes - * (we also compile a static version of the function; see Inlines.c) + * EXTERN_INLINE is for functions that may be called in Cmm + * (we also compile a static version of an EXTERN_INLINE function; see Inlines.c) */ -// We generally assume C99 semantics albeit these two definitions work fine even -// when gnu90 semantics are active (i.e. when __GNUC_GNU_INLINE__ is defined or -// when a GCC older than 4.2 is used) -// -// The problem, however, is with 'extern inline' whose semantics significantly -// differs between gnu90 and C99 #define INLINE_HEADER static inline #define STATIC_INLINE static inline -// Figure out whether `__attributes__((gnu_inline))` is needed -// to force gnu90-style 'external inline' semantics. -#if defined(FORCE_GNU_INLINE) -// disable auto-detection since HAVE_GNU_INLINE has been defined externally -#elif defined(__GNUC_GNU_INLINE__) && __GNUC__ == 4 && __GNUC_MINOR__ == 2 -// GCC 4.2.x didn't properly support C99 inline semantics (GCC 4.3 was the first -// release to properly support C99 inline semantics), and therefore warned when -// using 'extern inline' while in C99 mode unless `__attributes__((gnu_inline))` -// was explicitly set. -# define FORCE_GNU_INLINE 1 -#endif - -#if defined(FORCE_GNU_INLINE) -// Force compiler into gnu90 semantics -# if defined(KEEP_INLINES) -# define EXTERN_INLINE inline __attribute__((gnu_inline)) -# else -# define EXTERN_INLINE extern inline __attribute__((gnu_inline)) -# endif -#elif defined(__GNUC_GNU_INLINE__) -// we're currently in gnu90 inline mode by default and -// __attribute__((gnu_inline)) may not be supported, so better leave it off -# if defined(KEEP_INLINES) -# define EXTERN_INLINE inline -# else -# define EXTERN_INLINE extern inline -# endif -#else -// Assume C99 semantics (yes, this curiously results in swapped definitions!) -// This is the preferred branch, and at some point we may drop support for -// compilers not supporting C99 semantics altogether. +// See comment in rts/Inlines.c for explanation. # if defined(KEEP_INLINES) # define EXTERN_INLINE extern inline # else -# define EXTERN_INLINE inline +# define EXTERN_INLINE static inline # endif -#endif - /* * GCC attributes */ -#if defined(__GNUC__) #define GNU_ATTRIBUTE(at) __attribute__((at)) -#else -#define GNU_ATTRIBUTE(at) -#endif -#if __GNUC__ >= 3 #define GNUC3_ATTRIBUTE(at) __attribute__((at)) -#else -#define GNUC3_ATTRIBUTE(at) -#endif /* Used to mark a switch case that falls-through */ #if (defined(__GNUC__) && __GNUC__ >= 7) @@ -192,7 +146,7 @@ #define FALLTHROUGH ((void)0) #endif /* __GNUC__ >= 7 */ -#if !defined(DEBUG) && (__GNUC__ > 4 || (__GNUC__ == 4 && __GNUC_MINOR__ >= 3)) +#if !defined(DEBUG) #define GNUC_ATTR_HOT __attribute__((hot)) #else #define GNUC_ATTR_HOT /* nothing */ @@ -206,21 +160,11 @@ See Note [Windows Stack allocations] */ #if defined(__clang__) #define STG_NO_OPTIMIZE __attribute__((optnone)) -#elif defined(__GNUC__) || defined(__GNUG__) -#define STG_NO_OPTIMIZE __attribute__((optimize("O0"))) #else -#define STG_NO_OPTIMIZE /* nothing */ +#define STG_NO_OPTIMIZE __attribute__((optimize("O0"))) #endif -// Mark a function as accepting a printf-like format string. -#if !defined(__GNUC__) && defined(mingw32_HOST_OS) -/* On Win64, if we say "printf" then gcc thinks we are going to use - MS format specifiers like %I64d rather than %llu */ -#define STG_PRINTF_ATTR(fmt_arg, rest) GNUC3_ATTRIBUTE(format(gnu_printf, fmt_arg, rest)) -#else -/* However, on OS X, "gnu_printf" isn't recognised */ #define STG_PRINTF_ATTR(fmt_arg, rest) GNUC3_ATTRIBUTE(format(printf, fmt_arg, rest)) -#endif #define STG_RESTRICT __restrict__ @@ -242,13 +186,9 @@ # define stg__has_attribute(attr) (0) #endif -#ifdef __GNUC__ # define STG_GNUC_GUARD_VERSION(major, minor) \ ((__GNUC__ > (major)) || \ ((__GNUC__ == (major)) && (__GNUC_MINOR__ >= (minor)))) -#else -# define STG_GNUC_GUARD_VERSION(major, minor) (0) -#endif /* * The versions of the `__malloc__` attribute which take arguments are only ===================================== rts/include/rts/Types.h ===================================== @@ -19,12 +19,8 @@ // Deprecated, use uint32_t instead. typedef unsigned int nat __attribute__((deprecated)); /* uint32_t */ -/* ullong (64|128-bit) type: only include if needed (not ANSI) */ -#if defined(__GNUC__) +/* ullong (64|128-bit) type */ #define LL(x) (x##LL) -#else -#define LL(x) (x##L) -#endif typedef struct StgClosure_ StgClosure; typedef struct StgInfoTable_ StgInfoTable; ===================================== rts/include/stg/DLL.h ===================================== @@ -21,7 +21,7 @@ # define DLL_IMPORT_DATA_REF(x) (_imp__##x) # define DLL_IMPORT_DATA_VARNAME(x) *_imp__##x # endif -# if __GNUC__ && !defined(__declspec) +# if !defined(__declspec) # define DLLIMPORT # else # define DLLIMPORT __declspec(dllimport) ===================================== rts/sm/BlockAlloc.c ===================================== @@ -274,19 +274,9 @@ STATIC_INLINE uint32_t log_2(W_ n) { ASSERT(n > 0 && n < (1<> 1; - if (x == 0) return i; - } - return NUM_FREE_LISTS; -#endif } // log base 2 (ceiling), needs to support up to (2^NUM_FREE_LISTS)-1 @@ -294,18 +284,8 @@ STATIC_INLINE uint32_t log_2_ceil(W_ n) { ASSERT(n > 0 && n < (1<= n) return i; - x = x << 1; - } - return MAX_FREE_LIST; -#endif } STATIC_INLINE void ===================================== rts/sm/Evac.h ===================================== @@ -6,7 +6,7 @@ * * Documentation on the architecture of the Garbage Collector can be * found in the online commentary: - * + * * https://gitlab.haskell.org/ghc/ghc/wikis/commentary/rts/storage/gc * * ---------------------------------------------------------------------------*/ @@ -25,7 +25,7 @@ // registers EAX, EDX, and ECX instead of on the stack. Functions that // take a variable number of arguments will continue to be passed all of // their arguments on the stack. -#if __GNUC__ >= 2 && (defined(x86_64_HOST_ARCH) || defined(i386_HOST_ARCH)) +#if defined(x86_64_HOST_ARCH) || defined(i386_HOST_ARCH) #define REGPARM1 __attribute__((regparm(1))) #else #define REGPARM1 ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5319,7 +5319,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5288,7 +5288,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5465,7 +5465,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -292,7 +292,7 @@ module Control.Exception where mask_ :: forall a. GHC.Types.IO a -> GHC.Types.IO a onException :: forall a b. GHC.Types.IO a -> GHC.Types.IO b -> GHC.Types.IO a someExceptionContext :: SomeException -> GHC.Internal.Exception.Context.ExceptionContext - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -407,7 +407,7 @@ module Control.Exception.Base where patError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recConError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a recSelError :: forall (q :: GHC.Types.RuntimeRep) (a :: TYPE q). GHC.Prim.Addr# -> a - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::GHC.Internal.Stack.Types.CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a throwIO :: forall e a. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> GHC.Types.IO a throwTo :: forall e. Exception e => GHC.Internal.Conc.Sync.ThreadId -> e -> GHC.Types.IO () try :: forall e a. Exception e => GHC.Types.IO a -> GHC.Types.IO (GHC.Internal.Data.Either.Either e a) @@ -5319,7 +5319,7 @@ module GHC.Exception where prettySrcLoc :: SrcLoc -> GHC.Internal.Base.String ratioZeroDenomException :: SomeException showCCSStack :: [GHC.Internal.Base.String] -> [GHC.Internal.Base.String] - throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (?callStack::CallStack, Exception e) => e -> a + throw :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r) e. (GHC.Internal.Stack.Types.HasCallStack, Exception e) => e -> a underflowException :: SomeException module GHC.Exception.Type where View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/30dba7952e4583608d3b55a94662ded683cf84b4...41919b3380b8fad4dca6dbe98afd9b1dce977365 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/30dba7952e4583608d3b55a94662ded683cf84b4...41919b3380b8fad4dca6dbe98afd9b1dce977365 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 09:16:22 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Sun, 09 Jun 2024 05:16:22 -0400 Subject: [Git][ghc/ghc][wip/kill-pre-c11] 2 commits: WIP: always assume __GNUC__ >= 4 Message-ID: <666572e63b742_1ac9ad88502c578ba@gitlab.mail> Cheng Shao pushed to branch wip/kill-pre-c11 at Glasgow Haskell Compiler / GHC Commits: abf49dc8 by Cheng Shao at 2024-06-09T09:11:03+00:00 WIP: always assume __GNUC__ >= 4 - - - - - 68514576 by Cheng Shao at 2024-06-09T09:16:04+00:00 WIP - - - - - 11 changed files: - libraries/ghc-prim/cbits/atomic.c - libraries/ghc-prim/cbits/ctz.c - rts/Hash.c - rts/RtsStartup.c - rts/RtsSymbols.c - rts/include/Rts.h - rts/include/Stg.h - rts/include/rts/Types.h - rts/include/stg/DLL.h - rts/sm/BlockAlloc.c - rts/sm/Evac.h Changes: ===================================== libraries/ghc-prim/cbits/atomic.c ===================================== @@ -163,7 +163,7 @@ hs_atomic_and64(StgWord x, StgWord64 val) #pragma GCC diagnostic push #if defined(__clang__) #pragma GCC diagnostic ignored "-Wsync-fetch-and-nand-semantics-changed" -#elif defined(__GNUC__) +#else #pragma GCC diagnostic ignored "-Wsync-nand" #endif ===================================== libraries/ghc-prim/cbits/ctz.c ===================================== @@ -31,7 +31,7 @@ hs_ctz32(StgWord x) StgWord hs_ctz64(StgWord64 x) { -#if defined(__GNUC__) && (defined(i386_HOST_ARCH) || defined(powerpc_HOST_ARCH)) +#if defined(i386_HOST_ARCH) || defined(powerpc_HOST_ARCH) /* On Linux/i386, the 64bit `__builtin_ctzll()` intrinsic doesn't get inlined by GCC but rather a short `__ctzdi2` runtime function is inserted when needed into compiled object files. ===================================== rts/Hash.c ===================================== @@ -14,18 +14,6 @@ #include "Hash.h" #include "RtsUtils.h" -/* This file needs to be compiled with vectorization enabled. Unfortunately - since we compile these things these days with cabal we can no longer - specify optimization per file. So we have to resort to pragmas. */ -#if defined(__GNUC__) || defined(__GNUG__) -#if !defined(__clang__) -#if !defined(DEBUG) -#pragma GCC push_options -#pragma GCC optimize ("O3") -#endif -#endif -#endif - #define XXH_INLINE_ALL #include "xxhash.h" @@ -563,12 +551,3 @@ int keyCountHashTable (HashTable *table) { return table->kcount; } - - -#if defined(__GNUC__) || defined(__GNUG__) -#if !defined(__clang__) -#if !defined(DEBUG) -#pragma GCC pop_options -#endif -#endif -#endif ===================================== rts/RtsStartup.c ===================================== @@ -123,13 +123,7 @@ void _fpreset(void) x86_init_fpu(); } -#if defined(__GNUC__) void __attribute__((alias("_fpreset"))) fpreset(void); -#else -void fpreset(void) { - _fpreset(); -} -#endif /* Set the console's CodePage to UTF-8 if using the new I/O manager and the CP is still the default one. */ ===================================== rts/RtsSymbols.c ===================================== @@ -956,7 +956,7 @@ extern char **environ; RTS_INTCHAR_SYMBOLS // 64-bit support functions in libgcc.a -#if defined(__GNUC__) && SIZEOF_VOID_P <= 4 && !defined(_ABIN32) +#if SIZEOF_VOID_P <= 4 && !defined(_ABIN32) #define RTS_LIBGCC_SYMBOLS \ SymI_NeedsProto(__divdi3) \ SymI_NeedsProto(__udivdi3) \ @@ -967,7 +967,7 @@ extern char **environ; SymI_NeedsProto(__ashrdi3) \ SymI_NeedsProto(__lshrdi3) \ SymI_NeedsProto(__fixunsdfdi) -#elif defined(__GNUC__) && SIZEOF_VOID_P == 8 +#elif SIZEOF_VOID_P == 8 #define RTS_LIBGCC_SYMBOLS \ SymI_NeedsProto(__udivti3) \ SymI_NeedsProto(__umodti3) ===================================== rts/include/Rts.h ===================================== @@ -54,39 +54,22 @@ extern "C" { #include "rts/Types.h" #include "rts/Time.h" -#if __GNUC__ >= 3 #define ATTRIBUTE_ALIGNED(n) __attribute__((aligned(n))) -#else -#define ATTRIBUTE_ALIGNED(n) /*nothing*/ -#endif // Symbols that are extern, but private to the RTS, are declared // with visibility "hidden" to hide them outside the RTS shared // library. #if defined(HAS_VISIBILITY_HIDDEN) -#define RTS_PRIVATE GNUC3_ATTRIBUTE(visibility("hidden")) +#define RTS_PRIVATE __attribute__((visibility("hidden"))) #else #define RTS_PRIVATE /* disabled: RTS_PRIVATE */ #endif -#if __GNUC__ >= 4 #define RTS_UNLIKELY(p) __builtin_expect((p),0) -#else -#define RTS_UNLIKELY(p) (p) -#endif -#if __GNUC__ >= 4 #define RTS_LIKELY(p) __builtin_expect(!!(p), 1) -#else -#define RTS_LIKELY(p) (p) -#endif -/* __builtin_unreachable is supported since GNU C 4.5 */ -#if __GNUC__ > 4 || (__GNUC__ == 4 && __GNUC_MINOR__ >= 5) #define RTS_UNREACHABLE __builtin_unreachable() -#else -#define RTS_UNREACHABLE abort() -#endif /* Prefetch primitives */ #define prefetchForRead(ptr) __builtin_prefetch(ptr, 0) @@ -377,17 +360,8 @@ TICK_VAR(2) Useful macros and inline functions -------------------------------------------------------------------------- */ -#if defined(__GNUC__) -#define SUPPORTS_TYPEOF -#endif - -#if defined(SUPPORTS_TYPEOF) #define stg_min(a,b) ({typeof(a) _a = (a), _b = (b); _a <= _b ? _a : _b; }) #define stg_max(a,b) ({typeof(a) _a = (a), _b = (b); _a <= _b ? _b : _a; }) -#else -#define stg_min(a,b) ((a) <= (b) ? (a) : (b)) -#define stg_max(a,b) ((a) <= (b) ? (b) : (a)) -#endif /* -------------------------------------------------------------------------- */ ===================================== rts/include/Stg.h ===================================== @@ -128,67 +128,42 @@ # define EXTERN_INLINE static inline # endif -/* - * GCC attributes - */ -#if defined(__GNUC__) -#define GNU_ATTRIBUTE(at) __attribute__((at)) -#else -#define GNU_ATTRIBUTE(at) -#endif - -#if __GNUC__ >= 3 -#define GNUC3_ATTRIBUTE(at) __attribute__((at)) -#else -#define GNUC3_ATTRIBUTE(at) -#endif - /* Used to mark a switch case that falls-through */ #if (defined(__GNUC__) && __GNUC__ >= 7) // N.B. Don't enable fallthrough annotations when compiling with Clang. // Apparently clang doesn't enable implicitly fallthrough warnings by default // http://llvm.org/viewvc/llvm-project?revision=167655&view=revision // when compiling C and the attribute cause warnings of their own (#16019). -#define FALLTHROUGH GNU_ATTRIBUTE(fallthrough) +#define FALLTHROUGH __attribute__((fallthrough)) #else #define FALLTHROUGH ((void)0) #endif /* __GNUC__ >= 7 */ -#if !defined(DEBUG) && (__GNUC__ > 4 || (__GNUC__ == 4 && __GNUC_MINOR__ >= 3)) +#if !defined(DEBUG) #define GNUC_ATTR_HOT __attribute__((hot)) #else #define GNUC_ATTR_HOT /* nothing */ #endif -#define STG_UNUSED GNUC3_ATTRIBUTE(__unused__) -#define STG_USED GNUC3_ATTRIBUTE(__used__) -#define STG_WARN_UNUSED_RESULT GNUC3_ATTRIBUTE(warn_unused_result) +#define STG_UNUSED __attribute__((__unused__)) +#define STG_USED __attribute__((__used__)) +#define STG_WARN_UNUSED_RESULT __attribute__((warn_unused_result)) /* Prevent functions from being optimized. See Note [Windows Stack allocations] */ #if defined(__clang__) #define STG_NO_OPTIMIZE __attribute__((optnone)) -#elif defined(__GNUC__) || defined(__GNUG__) -#define STG_NO_OPTIMIZE __attribute__((optimize("O0"))) #else -#define STG_NO_OPTIMIZE /* nothing */ +#define STG_NO_OPTIMIZE __attribute__((optimize("O0"))) #endif -// Mark a function as accepting a printf-like format string. -#if !defined(__GNUC__) && defined(mingw32_HOST_OS) -/* On Win64, if we say "printf" then gcc thinks we are going to use - MS format specifiers like %I64d rather than %llu */ -#define STG_PRINTF_ATTR(fmt_arg, rest) GNUC3_ATTRIBUTE(format(gnu_printf, fmt_arg, rest)) -#else -/* However, on OS X, "gnu_printf" isn't recognised */ -#define STG_PRINTF_ATTR(fmt_arg, rest) GNUC3_ATTRIBUTE(format(printf, fmt_arg, rest)) -#endif +#define STG_PRINTF_ATTR(fmt_arg, rest) __attribute__((format(printf, fmt_arg, rest))) #define STG_RESTRICT __restrict__ -#define STG_NORETURN GNU_ATTRIBUTE(__noreturn__) +#define STG_NORETURN __attribute__((__noreturn__)) -#define STG_MALLOC GNUC3_ATTRIBUTE(__malloc__) +#define STG_MALLOC __attribute__((__malloc__)) /* Instead of relying on GCC version checks to expand attributes, * use `__has_attribute` which is supported by GCC >= 5 and Clang. Hence, the @@ -204,13 +179,9 @@ # define stg__has_attribute(attr) (0) #endif -#ifdef __GNUC__ # define STG_GNUC_GUARD_VERSION(major, minor) \ ((__GNUC__ > (major)) || \ ((__GNUC__ == (major)) && (__GNUC_MINOR__ >= (minor)))) -#else -# define STG_GNUC_GUARD_VERSION(major, minor) (0) -#endif /* * The versions of the `__malloc__` attribute which take arguments are only @@ -280,8 +251,8 @@ typedef StgFunPtr F_; #define EB_(X) extern const char X[] #define IB_(X) static const char X[] /* static (non-heap) closures (requires alignment for pointer tagging): */ -#define EC_(X) extern StgWordArray (X) GNU_ATTRIBUTE(aligned (SIZEOF_VOID_P)) -#define IC_(X) static StgWordArray (X) GNU_ATTRIBUTE(aligned (SIZEOF_VOID_P)) +#define EC_(X) extern StgWordArray (X) __attribute__((aligned (SIZEOF_VOID_P))) +#define IC_(X) static StgWordArray (X) __attribute__((aligned (SIZEOF_VOID_P))) /* writable data (does not require alignment): */ #define ERW_(X) extern StgWordArray (X) #define IRW_(X) static StgWordArray (X) @@ -289,7 +260,7 @@ typedef StgFunPtr F_; #define ERO_(X) extern const StgWordArray (X) #define IRO_(X) static const StgWordArray (X) /* stg-native functions: */ -#define IF_(f) static StgFunPtr GNUC3_ATTRIBUTE(used) f(void) +#define IF_(f) static StgFunPtr __attribute__((used)) f(void) #define FN_(f) StgFunPtr f(void) #define EF_(f) StgFunPtr f(void) /* External Cmm functions */ /* foreign functions: */ ===================================== rts/include/rts/Types.h ===================================== @@ -19,12 +19,8 @@ // Deprecated, use uint32_t instead. typedef unsigned int nat __attribute__((deprecated)); /* uint32_t */ -/* ullong (64|128-bit) type: only include if needed (not ANSI) */ -#if defined(__GNUC__) +/* ullong (64|128-bit) type */ #define LL(x) (x##LL) -#else -#define LL(x) (x##L) -#endif typedef struct StgClosure_ StgClosure; typedef struct StgInfoTable_ StgInfoTable; ===================================== rts/include/stg/DLL.h ===================================== @@ -21,7 +21,7 @@ # define DLL_IMPORT_DATA_REF(x) (_imp__##x) # define DLL_IMPORT_DATA_VARNAME(x) *_imp__##x # endif -# if __GNUC__ && !defined(__declspec) +# if !defined(__declspec) # define DLLIMPORT # else # define DLLIMPORT __declspec(dllimport) ===================================== rts/sm/BlockAlloc.c ===================================== @@ -274,19 +274,9 @@ STATIC_INLINE uint32_t log_2(W_ n) { ASSERT(n > 0 && n < (1<> 1; - if (x == 0) return i; - } - return NUM_FREE_LISTS; -#endif } // log base 2 (ceiling), needs to support up to (2^NUM_FREE_LISTS)-1 @@ -294,18 +284,8 @@ STATIC_INLINE uint32_t log_2_ceil(W_ n) { ASSERT(n > 0 && n < (1<= n) return i; - x = x << 1; - } - return MAX_FREE_LIST; -#endif } STATIC_INLINE void ===================================== rts/sm/Evac.h ===================================== @@ -6,7 +6,7 @@ * * Documentation on the architecture of the Garbage Collector can be * found in the online commentary: - * + * * https://gitlab.haskell.org/ghc/ghc/wikis/commentary/rts/storage/gc * * ---------------------------------------------------------------------------*/ @@ -25,7 +25,7 @@ // registers EAX, EDX, and ECX instead of on the stack. Functions that // take a variable number of arguments will continue to be passed all of // their arguments on the stack. -#if __GNUC__ >= 2 && (defined(x86_64_HOST_ARCH) || defined(i386_HOST_ARCH)) +#if defined(x86_64_HOST_ARCH) || defined(i386_HOST_ARCH) #define REGPARM1 __attribute__((regparm(1))) #else #define REGPARM1 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/41919b3380b8fad4dca6dbe98afd9b1dce977365...68514576e148d644dddddae3432b99f1ce4bea0d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/41919b3380b8fad4dca6dbe98afd9b1dce977365...68514576e148d644dddddae3432b99f1ce4bea0d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 09:50:26 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Sun, 09 Jun 2024 05:50:26 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/romes/ttg-zurich Message-ID: <66657ae27670c_1ac9adfcb688844b4@gitlab.mail> Rodrigo Mesquita pushed new branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/ttg-zurich You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 09:54:07 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Sun, 09 Jun 2024 05:54:07 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] 2 commits: AST: GHC.Prelude -> Prelude Message-ID: <66657bbf9f5ad_1ac9ad10fd984900e4@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: 756fc498 by Alexander Foremny at 2024-06-09T11:53:29+02:00 AST: GHC.Prelude -> Prelude Refactor occurrences to GHC.Prelude with Prelude within Language/Haskell. - - - - - 73215916 by Alexander Foremny at 2024-06-09T11:53:45+02:00 AST: remove occurrences of GHC.Unit.Module.ModuleName `GHC.Unit.Module` re-exports `ModuleName` from `Language.Haskell.Syntax.Module.Name`. - - - - - 2 changed files: - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Expr.hs-boot Changes: ===================================== compiler/Language/Haskell/Syntax/Expr.hs ===================================== @@ -26,6 +26,7 @@ import Language.Haskell.Syntax.Decls import Language.Haskell.Syntax.Pat import Language.Haskell.Syntax.Lit import Language.Haskell.Syntax.Extension +import Language.Haskell.Syntax.Module.Name (ModuleName) import Language.Haskell.Syntax.Type import Language.Haskell.Syntax.Binds @@ -33,7 +34,6 @@ import Language.Haskell.Syntax.Binds import GHC.Types.Fixity (LexicalFixity(Infix), Fixity) import GHC.Types.SourceText (StringLiteral) -import GHC.Unit.Module (ModuleName) import GHC.Data.FastString (FastString) -- libraries: ===================================== compiler/Language/Haskell/Syntax/Expr.hs-boot ===================================== @@ -9,7 +9,7 @@ module Language.Haskell.Syntax.Expr where import Language.Haskell.Syntax.Extension ( XRec ) import Data.Kind ( Type ) -import GHC.Prelude (Eq) +import Prelude (Eq) import Data.Data (Data) type role HsExpr nominal View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9cd24a53d8d5b428b16167503f4d129c1d6f4a6c...7321591682b367cf836c07ca2d275b04ceffc60c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/9cd24a53d8d5b428b16167503f4d129c1d6f4a6c...7321591682b367cf836c07ca2d275b04ceffc60c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 09:55:33 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Sun, 09 Jun 2024 05:55:33 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] 3 commits: AST: move Data instance definition for ModuleName to GHC.Unit.Types Message-ID: <66657c15422a5_1ac9ad121cf90927b0@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: 3829df8a by Fabian Kirchner at 2024-06-09T11:55:08+02:00 AST: move Data instance definition for ModuleName to GHC.Unit.Types To remove the dependency on GHC.Utils.Misc inside Language.Haskell.Syntax.Module.Name, the instance definition is moved from there into GHC.Unit.Types. - - - - - 0a10b4fc by Fabian Kirchner at 2024-06-09T11:55:15+02:00 AST: move negateOverLitVal into GHC.Hs.Lit The function negateOverLitVal is not used within Language.Haskell and therefore can be moved to the respective module inside GHC.Hs. - - - - - 50a6b2f6 by Fabian Kirchner at 2024-06-09T11:55:22+02:00 AST: move conDetailsArity into GHC.Rename.Module The function conDetailsArity is only used inside GHC.Rename.Module. We therefore move it there from Language.Haskell.Syntax.Lit. - - - - - 6 changed files: - compiler/GHC/Hs/Lit.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Lit.hs - compiler/Language/Haskell/Syntax/Module/Name.hs - compiler/Language/Haskell/Syntax/Type.hs Changes: ===================================== compiler/GHC/Hs/Lit.hs ===================================== @@ -30,6 +30,7 @@ import GHC.Core.Ppr ( {- instance OutputableBndr TyVar -} ) import GHC.Types.SourceText import GHC.Core.Type import GHC.Utils.Outputable +import GHC.Utils.Panic (panic) import GHC.Hs.Extension import Language.Haskell.Syntax.Expr ( HsExpr ) import Language.Haskell.Syntax.Extension @@ -248,3 +249,7 @@ pmPprHsLit (HsRat _ f _) = ppr f pmPprHsLit (HsFloatPrim _ f) = ppr f pmPprHsLit (HsDoublePrim _ d) = ppr d +negateOverLitVal :: OverLitVal -> OverLitVal +negateOverLitVal (HsIntegral i) = HsIntegral (negateIntegralLit i) +negateOverLitVal (HsFractional f) = HsFractional (negateFractionalLit f) +negateOverLitVal _ = panic "negateOverLitVal: argument is not a number" ===================================== compiler/GHC/Rename/Module.hs ===================================== @@ -3,6 +3,7 @@ {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE LambdaCase #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} @@ -54,6 +55,7 @@ import GHC.Types.Name.Set import GHC.Types.Name.Env import GHC.Utils.Outputable import GHC.Data.Bag +import GHC.Types.Basic (Arity) import GHC.Types.Basic ( TypeOrKind(..) ) import GHC.Data.FastString import GHC.Types.SrcLoc as SrcLoc @@ -2558,6 +2560,12 @@ extendPatSynEnv dup_fields_ok has_sel val_decls local_fix_env thing = do { | otherwise = return names +conDetailsArity :: (rec -> Arity) -> HsConDetails tyarg arg rec -> Arity +conDetailsArity recToArity = \case + PrefixCon _ args -> length args + RecCon rec -> recToArity rec + InfixCon _ _ -> 2 + {- ********************************************************* * * ===================================== compiler/GHC/Unit/Types.hs ===================================== @@ -124,6 +124,12 @@ data GenModule unit = Module } deriving (Eq,Ord,Data,Functor) +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/Lit.hs ===================================== @@ -21,7 +21,7 @@ module Language.Haskell.Syntax.Lit where import Language.Haskell.Syntax.Extension import GHC.Utils.Panic (panic) -import GHC.Types.SourceText (IntegralLit, FractionalLit, SourceText, negateIntegralLit, negateFractionalLit) +import GHC.Types.SourceText (IntegralLit, FractionalLit, SourceText) import GHC.Core.Type (Type) import GHC.Data.FastString (FastString, lexicalCompareFS) @@ -128,11 +128,6 @@ data OverLitVal | HsIsString !SourceText !FastString -- ^ String-looking literals deriving Data -negateOverLitVal :: OverLitVal -> OverLitVal -negateOverLitVal (HsIntegral i) = HsIntegral (negateIntegralLit i) -negateOverLitVal (HsFractional f) = HsFractional (negateFractionalLit f) -negateOverLitVal _ = panic "negateOverLitVal: argument is not a number" - -- Comparison operations are needed when grouping literals -- for compiling pattern-matching (module GHC.HsToCore.Match.Literal) instance (Eq (XXOverLit p)) => Eq (HsOverLit p) where ===================================== compiler/Language/Haskell/Syntax/Module/Name.hs ===================================== @@ -2,13 +2,11 @@ module Language.Haskell.Syntax.Module.Name where import Prelude -import Data.Data import Data.Char (isAlphaNum) import Control.DeepSeq import qualified Text.ParserCombinators.ReadP as Parse import System.FilePath -import GHC.Utils.Misc (abstractConstr) import GHC.Data.FastString -- | A ModuleName is essentially a simple string, e.g. @Data.List at . @@ -17,12 +15,6 @@ newtype ModuleName = ModuleName FastString deriving (Show, Eq) instance Ord ModuleName where nm1 `compare` nm2 = stableModuleNameCmp nm1 nm2 -instance Data ModuleName where - -- don't traverse? - toConstr _ = abstractConstr "ModuleName" - gunfold _ _ = error "gunfold" - dataTypeOf _ = mkNoRepType "ModuleName" - instance NFData ModuleName where rnf x = x `seq` () ===================================== compiler/Language/Haskell/Syntax/Type.hs ===================================== @@ -48,7 +48,7 @@ module Language.Haskell.Syntax.Type ( ConDeclField(..), LConDeclField, - HsConDetails(..), noTypeArgs, conDetailsArity, + HsConDetails(..), noTypeArgs, FieldOcc(..), LFieldOcc, AmbiguousFieldOcc(..), LAmbiguousFieldOcc, @@ -66,7 +66,6 @@ import Language.Haskell.Syntax.Extension import GHC.Types.Name.Reader ( RdrName ) import GHC.Core.DataCon( HsSrcBang(..) ) import GHC.Core.Type (Specificity) -import GHC.Types.Basic (Arity) import GHC.Hs.Doc (LHsDoc) import GHC.Data.FastString (FastString) @@ -77,7 +76,7 @@ import Data.Maybe import Data.Eq import Data.Bool import Data.Char -import Prelude (Integer, length) +import Prelude (Integer) import Data.Ord (Ord) {- @@ -1108,12 +1107,6 @@ data HsConDetails tyarg arg rec noTypeArgs :: [Void] noTypeArgs = [] -conDetailsArity :: (rec -> Arity) -> HsConDetails tyarg arg rec -> Arity -conDetailsArity recToArity = \case - PrefixCon _ args -> length args - RecCon rec -> recToArity rec - InfixCon _ _ -> 2 - {- Note [ConDeclField pass] ~~~~~~~~~~~~~~~~~~~~~~~~~ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7321591682b367cf836c07ca2d275b04ceffc60c...50a6b2f65ae69b5940fe22d817c59d6b41de884c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7321591682b367cf836c07ca2d275b04ceffc60c...50a6b2f65ae69b5940fe22d817c59d6b41de884c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 09:57:16 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Sun, 09 Jun 2024 05:57:16 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] AST: Remove Assert from GHC Message-ID: <66657c7c3bbc6_1ac9ad12caf509356e@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: eb469d18 by Mauricio at 2024-06-09T11:57:01+02:00 AST: Remove Assert from GHC - - - - - 1 changed file: - compiler/Language/Haskell/Syntax/Decls.hs Changes: ===================================== compiler/Language/Haskell/Syntax/Decls.hs ===================================== @@ -106,11 +106,11 @@ import GHC.Types.Fixity (LexicalFixity) import GHC.Core.Type (Specificity) import GHC.Unit.Module.Warnings (WarningTxt) -import GHC.Utils.Panic.Plain ( assert ) import GHC.Hs.Doc (LHsDoc) -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST import Control.Monad +import Control.Exception (assert) import Data.Data hiding (TyCon, Fixity, Infix) import Data.Void import Data.Maybe View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eb469d18310f338bc92365cc43b6943d05e76eed -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eb469d18310f338bc92365cc43b6943d05e76eed You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 09:58:24 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Sun, 09 Jun 2024 05:58:24 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] 6 commits: AST: GHC.Prelude -> Prelude Message-ID: <66657cc0a05e6_1ac9ad13d1fe894330@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: f5ba7b2d by Alexander Foremny at 2024-06-09T11:57:29+02:00 AST: GHC.Prelude -> Prelude Refactor occurrences to GHC.Prelude with Prelude within Language/Haskell. Progress towards #21592 - - - - - 96b57e27 by Alexander Foremny at 2024-06-09T11:57:38+02:00 AST: remove occurrences of GHC.Unit.Module.ModuleName `GHC.Unit.Module` re-exports `ModuleName` from `Language.Haskell.Syntax.Module.Name`. Progress towards #21592 - - - - - d5ed9d84 by Fabian Kirchner at 2024-06-09T11:57:44+02:00 AST: move Data instance definition for ModuleName to GHC.Unit.Types To remove the dependency on GHC.Utils.Misc inside Language.Haskell.Syntax.Module.Name, the instance definition is moved from there into GHC.Unit.Types. Progress towards #21592 - - - - - f01133ca by Fabian Kirchner at 2024-06-09T11:57:50+02:00 AST: move negateOverLitVal into GHC.Hs.Lit The function negateOverLitVal is not used within Language.Haskell and therefore can be moved to the respective module inside GHC.Hs. Progress towards #21592 - - - - - 0d194f85 by Fabian Kirchner at 2024-06-09T11:57:55+02:00 AST: move conDetailsArity into GHC.Rename.Module The function conDetailsArity is only used inside GHC.Rename.Module. We therefore move it there from Language.Haskell.Syntax.Lit. Progress towards #21592 - - - - - 2708f4ec by Mauricio at 2024-06-09T11:57:59+02:00 AST: Remove GHC.Utils.Assert from GHC Simple cleanup. Progress towards #21592 - - - - - 9 changed files: - compiler/GHC/Hs/Lit.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Expr.hs-boot - compiler/Language/Haskell/Syntax/Lit.hs - compiler/Language/Haskell/Syntax/Module/Name.hs - compiler/Language/Haskell/Syntax/Type.hs Changes: ===================================== compiler/GHC/Hs/Lit.hs ===================================== @@ -30,6 +30,7 @@ import GHC.Core.Ppr ( {- instance OutputableBndr TyVar -} ) import GHC.Types.SourceText import GHC.Core.Type import GHC.Utils.Outputable +import GHC.Utils.Panic (panic) import GHC.Hs.Extension import Language.Haskell.Syntax.Expr ( HsExpr ) import Language.Haskell.Syntax.Extension @@ -248,3 +249,7 @@ pmPprHsLit (HsRat _ f _) = ppr f pmPprHsLit (HsFloatPrim _ f) = ppr f pmPprHsLit (HsDoublePrim _ d) = ppr d +negateOverLitVal :: OverLitVal -> OverLitVal +negateOverLitVal (HsIntegral i) = HsIntegral (negateIntegralLit i) +negateOverLitVal (HsFractional f) = HsFractional (negateFractionalLit f) +negateOverLitVal _ = panic "negateOverLitVal: argument is not a number" ===================================== compiler/GHC/Rename/Module.hs ===================================== @@ -3,6 +3,7 @@ {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE LambdaCase #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} @@ -54,6 +55,7 @@ import GHC.Types.Name.Set import GHC.Types.Name.Env import GHC.Utils.Outputable import GHC.Data.Bag +import GHC.Types.Basic (Arity) import GHC.Types.Basic ( TypeOrKind(..) ) import GHC.Data.FastString import GHC.Types.SrcLoc as SrcLoc @@ -2558,6 +2560,12 @@ extendPatSynEnv dup_fields_ok has_sel val_decls local_fix_env thing = do { | otherwise = return names +conDetailsArity :: (rec -> Arity) -> HsConDetails tyarg arg rec -> Arity +conDetailsArity recToArity = \case + PrefixCon _ args -> length args + RecCon rec -> recToArity rec + InfixCon _ _ -> 2 + {- ********************************************************* * * ===================================== compiler/GHC/Unit/Types.hs ===================================== @@ -124,6 +124,12 @@ data GenModule unit = Module } deriving (Eq,Ord,Data,Functor) +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/Decls.hs ===================================== @@ -106,11 +106,11 @@ import GHC.Types.Fixity (LexicalFixity) import GHC.Core.Type (Specificity) import GHC.Unit.Module.Warnings (WarningTxt) -import GHC.Utils.Panic.Plain ( assert ) import GHC.Hs.Doc (LHsDoc) -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST import Control.Monad +import Control.Exception (assert) import Data.Data hiding (TyCon, Fixity, Infix) import Data.Void import Data.Maybe ===================================== compiler/Language/Haskell/Syntax/Expr.hs ===================================== @@ -26,6 +26,7 @@ import Language.Haskell.Syntax.Decls import Language.Haskell.Syntax.Pat import Language.Haskell.Syntax.Lit import Language.Haskell.Syntax.Extension +import Language.Haskell.Syntax.Module.Name (ModuleName) import Language.Haskell.Syntax.Type import Language.Haskell.Syntax.Binds @@ -33,7 +34,6 @@ import Language.Haskell.Syntax.Binds import GHC.Types.Fixity (LexicalFixity(Infix), Fixity) import GHC.Types.SourceText (StringLiteral) -import GHC.Unit.Module (ModuleName) import GHC.Data.FastString (FastString) -- libraries: ===================================== compiler/Language/Haskell/Syntax/Expr.hs-boot ===================================== @@ -9,7 +9,7 @@ module Language.Haskell.Syntax.Expr where import Language.Haskell.Syntax.Extension ( XRec ) import Data.Kind ( Type ) -import GHC.Prelude (Eq) +import Prelude (Eq) import Data.Data (Data) type role HsExpr nominal ===================================== compiler/Language/Haskell/Syntax/Lit.hs ===================================== @@ -21,7 +21,7 @@ module Language.Haskell.Syntax.Lit where import Language.Haskell.Syntax.Extension import GHC.Utils.Panic (panic) -import GHC.Types.SourceText (IntegralLit, FractionalLit, SourceText, negateIntegralLit, negateFractionalLit) +import GHC.Types.SourceText (IntegralLit, FractionalLit, SourceText) import GHC.Core.Type (Type) import GHC.Data.FastString (FastString, lexicalCompareFS) @@ -128,11 +128,6 @@ data OverLitVal | HsIsString !SourceText !FastString -- ^ String-looking literals deriving Data -negateOverLitVal :: OverLitVal -> OverLitVal -negateOverLitVal (HsIntegral i) = HsIntegral (negateIntegralLit i) -negateOverLitVal (HsFractional f) = HsFractional (negateFractionalLit f) -negateOverLitVal _ = panic "negateOverLitVal: argument is not a number" - -- Comparison operations are needed when grouping literals -- for compiling pattern-matching (module GHC.HsToCore.Match.Literal) instance (Eq (XXOverLit p)) => Eq (HsOverLit p) where ===================================== compiler/Language/Haskell/Syntax/Module/Name.hs ===================================== @@ -2,13 +2,11 @@ module Language.Haskell.Syntax.Module.Name where import Prelude -import Data.Data import Data.Char (isAlphaNum) import Control.DeepSeq import qualified Text.ParserCombinators.ReadP as Parse import System.FilePath -import GHC.Utils.Misc (abstractConstr) import GHC.Data.FastString -- | A ModuleName is essentially a simple string, e.g. @Data.List at . @@ -17,12 +15,6 @@ newtype ModuleName = ModuleName FastString deriving (Show, Eq) instance Ord ModuleName where nm1 `compare` nm2 = stableModuleNameCmp nm1 nm2 -instance Data ModuleName where - -- don't traverse? - toConstr _ = abstractConstr "ModuleName" - gunfold _ _ = error "gunfold" - dataTypeOf _ = mkNoRepType "ModuleName" - instance NFData ModuleName where rnf x = x `seq` () ===================================== compiler/Language/Haskell/Syntax/Type.hs ===================================== @@ -48,7 +48,7 @@ module Language.Haskell.Syntax.Type ( ConDeclField(..), LConDeclField, - HsConDetails(..), noTypeArgs, conDetailsArity, + HsConDetails(..), noTypeArgs, FieldOcc(..), LFieldOcc, AmbiguousFieldOcc(..), LAmbiguousFieldOcc, @@ -66,7 +66,6 @@ import Language.Haskell.Syntax.Extension import GHC.Types.Name.Reader ( RdrName ) import GHC.Core.DataCon( HsSrcBang(..) ) import GHC.Core.Type (Specificity) -import GHC.Types.Basic (Arity) import GHC.Hs.Doc (LHsDoc) import GHC.Data.FastString (FastString) @@ -77,7 +76,7 @@ import Data.Maybe import Data.Eq import Data.Bool import Data.Char -import Prelude (Integer, length) +import Prelude (Integer) import Data.Ord (Ord) {- @@ -1108,12 +1107,6 @@ data HsConDetails tyarg arg rec noTypeArgs :: [Void] noTypeArgs = [] -conDetailsArity :: (rec -> Arity) -> HsConDetails tyarg arg rec -> Arity -conDetailsArity recToArity = \case - PrefixCon _ args -> length args - RecCon rec -> recToArity rec - InfixCon _ _ -> 2 - {- Note [ConDeclField pass] ~~~~~~~~~~~~~~~~~~~~~~~~~ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/eb469d18310f338bc92365cc43b6943d05e76eed...2708f4ec64576ba9c24f569cdf59be6adb35f961 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/eb469d18310f338bc92365cc43b6943d05e76eed...2708f4ec64576ba9c24f569cdf59be6adb35f961 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 10:00:39 2024 From: gitlab at gitlab.haskell.org (Jacco Krijnen (@jacco)) Date: Sun, 09 Jun 2024 06:00:39 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/jacco/ast Message-ID: <66657d4716052_1ac9ad159a96095574@gitlab.mail> Jacco Krijnen pushed new branch wip/jacco/ast at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/jacco/ast You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 10:07:35 2024 From: gitlab at gitlab.haskell.org (Jacco Krijnen (@jacco)) Date: Sun, 09 Jun 2024 06:07:35 -0400 Subject: [Git][ghc/ghc][wip/jacco/ast] ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <66657ee6d4e5a_1ac9ad17b543498496@gitlab.mail> Jacco Krijnen pushed to branch wip/jacco/ast at Glasgow Haskell Compiler / GHC Commits: 29810114 by Jacco Krijnen at 2024-06-09T12:01:04+02:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/29810114123d93b84f178fdd74e2f51d8bc18e71 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/29810114123d93b84f178fdd74e2f51d8bc18e71 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 10:20:52 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Sun, 09 Jun 2024 06:20:52 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ast] AST: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Message-ID: <6665820451eb1_1ac9ad19534f89871@gitlab.mail> Fabian Kirchner pushed to branch wip/kirchner/ast at Glasgow Haskell Compiler / GHC Commits: 017c8c31 by Fabian Kirchner at 2024-06-09T12:14:59+02:00 AST: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - 25 changed files: - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion.hs-boot - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/Arity.hs - compiler/GHC/Core/TyCo/Compare.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/Core/TyCon.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Sig.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/Types/Evidence.hs - compiler/GHC/Types/Literal.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var.hs-boot - compiler/Language/Haskell/Syntax/Decls.hs - + compiler/Language/Haskell/Syntax/Specificity.hs Changes: ===================================== compiler/GHC/Core/Coercion.hs ===================================== @@ -164,6 +164,8 @@ import GHC.Utils.Misc import GHC.Utils.Outputable import GHC.Utils.Panic +import Language.Haskell.Syntax.Specificity (coreTyLamForAllTyFlag) + import Control.Monad (foldM, zipWithM) import Data.Function ( on ) import Data.Char( isDigit ) ===================================== compiler/GHC/Core/Coercion.hs-boot ===================================== @@ -12,6 +12,7 @@ import GHC.Core.Coercion.Axiom import GHC.Types.Var import GHC.Data.Pair import GHC.Utils.Misc +import Language.Haskell.Syntax.Specificity (ForAllTyFlag) mkReflCo :: Role -> Type -> Coercion mkTyConAppCo :: HasDebugCallStack => Role -> TyCon -> [Coercion] -> Coercion ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -106,6 +106,8 @@ import GHC.Data.Pair import GHC.Base (oneShot) import GHC.Data.Unboxed +import Language.Haskell.Syntax.Specificity (coreTyLamForAllTyFlag) + {- Note [Core Lint guarantee] ~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Core/Opt/Arity.hs ===================================== @@ -87,6 +87,8 @@ import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Utils.Misc +import Language.Haskell.Syntax.Specificity (coreTyLamForAllTyFlag) + import Data.Maybe( isJust ) {- ===================================== compiler/GHC/Core/TyCo/Compare.hs ===================================== @@ -42,6 +42,8 @@ import GHC.Base (reallyUnsafePtrEquality#) import qualified Data.Semigroup as S +import Language.Haskell.Syntax.Specificity (isInvisibleForAllTyFlag) + {- GHC.Core.TyCo.Compare overview ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ This module implements type equality and comparison ===================================== compiler/GHC/Core/TyCo/Ppr.hs ===================================== @@ -53,6 +53,8 @@ import GHC.Utils.Panic import GHC.Types.Basic ( PprPrec(..), topPrec, sigPrec, opPrec , funPrec, appPrec, maybeParen ) +import Language.Haskell.Syntax.Specificity (Specificity(..)) + {- %************************************************************************ %* * ===================================== compiler/GHC/Core/TyCo/Rep.hs ===================================== @@ -96,6 +96,8 @@ import qualified Data.Data as Data hiding ( TyCon ) import Data.IORef ( IORef ) -- for CoercionHole import Control.DeepSeq +import Language.Haskell.Syntax.Specificity (ForAllTyFlag(..), coreTyLamForAllTyFlag) + {- ********************************************************************** * * Type ===================================== compiler/GHC/Core/TyCo/Rep.hs-boot ===================================== @@ -3,8 +3,9 @@ module GHC.Core.TyCo.Rep where import GHC.Utils.Outputable ( Outputable ) import Data.Data ( Data ) -import {-# SOURCE #-} GHC.Types.Var( Var, VarBndr, ForAllTyFlag, FunTyFlag ) +import {-# SOURCE #-} GHC.Types.Var( Var, VarBndr, FunTyFlag ) import {-# SOURCE #-} GHC.Core.TyCon ( TyCon ) +import {-# SOURCE #-} Language.Haskell.Syntax.Specificity ( ForAllTyFlag ) data Type data Coercion ===================================== compiler/GHC/Core/TyCon.hs ===================================== @@ -183,6 +183,7 @@ import GHC.Types.Unique.Set import GHC.Unit.Module import Language.Haskell.Syntax.Basic (FieldLabelString(..)) +import Language.Haskell.Syntax.Specificity (ForAllTyFlag(..), Specificity(..), isVisibleForAllTyFlag) import qualified Data.Data as Data ===================================== compiler/GHC/Core/Type.hs ===================================== @@ -291,6 +291,8 @@ import GHC.Data.FastString import GHC.Data.Maybe ( orElse, isJust, firstJust ) +import Language.Haskell.Syntax.Specificity (Specificity(..), isInvisibleForAllTyFlag, isVisibleForAllTyFlag) + -- $type_classification -- #type_classification# -- ===================================== compiler/GHC/Core/Utils.hs ===================================== @@ -109,6 +109,8 @@ import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Utils.Misc +import Language.Haskell.Syntax.Specificity (coreTyLamForAllTyFlag) + import Data.ByteString ( ByteString ) import Data.Function ( on ) import Data.List ( sort, sortBy, partition, zipWith4, mapAccumL ) ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -90,6 +90,7 @@ import Data.Kind (Constraint) import qualified GHC.LanguageExtensions as LangExt import Language.Haskell.Syntax.Basic (FieldLabelString(..)) +import Language.Haskell.Syntax.Specificity (Specificity(..)) import Data.ByteString ( unpack ) import Control.Monad ===================================== compiler/GHC/Iface/Type.hs ===================================== @@ -100,6 +100,8 @@ import Control.Arrow (first) import Control.DeepSeq import Control.Monad ((<$!>)) +import Language.Haskell.Syntax.Specificity (ForAllTyFlag(..), Specificity, isInvisibleForAllTyFlag, isVisibleForAllTyFlag, coreTyLamForAllTyFlag) + {- ************************************************************************ * * ===================================== compiler/GHC/Tc/Errors/Types.hs ===================================== @@ -189,7 +189,7 @@ import GHC.Types.Name.Reader import GHC.Types.SourceFile (HsBootOrSig(..)) import GHC.Types.SrcLoc import GHC.Types.TyThing (TyThing) -import GHC.Types.Var (Id, TyCoVar, TyVar, TcTyVar, CoVar, Specificity) +import GHC.Types.Var (Id, TyCoVar, TyVar, TcTyVar, CoVar) import GHC.Types.Var.Env (TidyEnv) import GHC.Types.Var.Set (TyVarSet, VarSet) import GHC.Unit.Types (Module) @@ -214,6 +214,7 @@ import GHC.Data.Pair import GHC.Exception.Type (SomeException) import Language.Haskell.Syntax.Basic (FieldLabelString(..)) +import Language.Haskell.Syntax.Specificity (Specificity) import qualified Data.List.NonEmpty as NE import Data.Typeable (Typeable) ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -62,6 +62,8 @@ import GHC.Utils.Outputable as Outputable import GHC.Utils.Panic import qualified GHC.LanguageExtensions as LangExt +import Language.Haskell.Syntax.Specificity (isInferredForAllTyFlag) + import Control.Monad import Data.Function ===================================== compiler/GHC/Tc/Gen/Bind.hs ===================================== @@ -96,6 +96,8 @@ import GHC.Data.Maybe import Control.Monad import Data.Foldable (find) +import Language.Haskell.Syntax.Specificity (Specificity(..)) + {- ************************************************************************ * * ===================================== compiler/GHC/Tc/Gen/Pat.hs ===================================== @@ -75,6 +75,7 @@ import qualified Data.List.NonEmpty as NE import GHC.Data.List.SetOps ( getNth ) import Language.Haskell.Syntax.Basic (FieldLabelString(..)) +import Language.Haskell.Syntax.Specificity (isSpecifiedForAllTyFlag) import Data.List( partition ) import Data.Maybe (isJust) ===================================== compiler/GHC/Tc/Gen/Sig.hs ===================================== @@ -51,7 +51,7 @@ import GHC.Core.Type ( mkTyVarBinders ) import GHC.Core.Multiplicity import GHC.Core.TyCo.Rep( mkNakedFunTy ) -import GHC.Types.Var ( TyVar, Specificity(..), tyVarKind, binderVars, invisArgTypeLike ) +import GHC.Types.Var ( TyVar, tyVarKind, binderVars, invisArgTypeLike ) import GHC.Types.Id ( Id, idName, idType, setInlinePragma , mkLocalId, realIdUnfolding ) import GHC.Types.Basic @@ -72,6 +72,8 @@ import Data.Maybe( mapMaybe ) import qualified Data.List.NonEmpty as NE import Control.Monad( unless ) +import Language.Haskell.Syntax.Specificity (Specificity(..)) + {- ------------------------------------------------------------- Note [Overview of type signatures] ===================================== compiler/GHC/Tc/TyCl/PatSyn.hs ===================================== @@ -69,6 +69,8 @@ import Control.Monad ( zipWithM ) import Data.List( partition, mapAccumL ) import Data.List.NonEmpty (NonEmpty, nonEmpty) +import Language.Haskell.Syntax.Specificity (Specificity(..)) + {- ************************************************************************ * * ===================================== compiler/GHC/Tc/Types/Evidence.hs ===================================== @@ -85,6 +85,8 @@ import Data.IORef( IORef ) import GHC.Types.Unique.Set import GHC.Core.Multiplicity +import Language.Haskell.Syntax.Specificity (coreTyLamForAllTyFlag) + import qualified Data.Semigroup as S {- ===================================== compiler/GHC/Types/Literal.hs ===================================== @@ -87,6 +87,8 @@ import Data.Data ( Data ) import GHC.Exts( isTrue#, dataToTag#, (<#) ) import Numeric ( fromRat ) +import Language.Haskell.Syntax.Specificity (ForAllTyFlag(..)) + {- ************************************************************************ * * ===================================== compiler/GHC/Types/Var.hs ===================================== @@ -65,13 +65,6 @@ module GHC.Types.Var ( isGlobalId, isExportedId, mustHaveLocalBinding, - -- * ForAllTyFlags - ForAllTyFlag(Invisible,Required,Specified,Inferred), - Specificity(..), - isVisibleForAllTyFlag, isInvisibleForAllTyFlag, isInferredForAllTyFlag, - isSpecifiedForAllTyFlag, - coreTyLamForAllTyFlag, - -- * FunTyFlag FunTyFlag(..), isVisibleFunArg, isInvisibleFunArg, isFUNArg, mkFunTyFlag, visArg, invisArg, @@ -129,6 +122,8 @@ import GHC.Utils.Binary import GHC.Utils.Outputable import GHC.Utils.Panic +import Language.Haskell.Syntax.Specificity (ForAllTyFlag(..), Specificity(..), isInvisibleForAllTyFlag, isVisibleForAllTyFlag) + import Data.Data import Control.DeepSeq @@ -455,57 +450,6 @@ updateVarTypeM upd var * * ********************************************************************* -} --- | ForAllTyFlag --- --- Is something required to appear in source Haskell ('Required'), --- permitted by request ('Specified') (visible type application), or --- prohibited entirely from appearing in source Haskell ('Inferred')? --- See Note [VarBndrs, ForAllTyBinders, TyConBinders, and visibility] in "GHC.Core.TyCo.Rep" -data ForAllTyFlag = Invisible !Specificity - | Required - deriving (Eq, Ord, Data) - -- (<) on ForAllTyFlag means "is less visible than" - --- | Whether an 'Invisible' argument may appear in source Haskell. -data Specificity = InferredSpec - -- ^ the argument may not appear in source Haskell, it is - -- only inferred. - | SpecifiedSpec - -- ^ the argument may appear in source Haskell, but isn't - -- required. - deriving (Eq, Ord, Data) - -pattern Inferred, Specified :: ForAllTyFlag -pattern Inferred = Invisible InferredSpec -pattern Specified = Invisible SpecifiedSpec - -{-# COMPLETE Required, Specified, Inferred #-} - --- | Does this 'ForAllTyFlag' classify an argument that is written in Haskell? -isVisibleForAllTyFlag :: ForAllTyFlag -> Bool -isVisibleForAllTyFlag af = not (isInvisibleForAllTyFlag af) - --- | Does this 'ForAllTyFlag' classify an argument that is not written in Haskell? -isInvisibleForAllTyFlag :: ForAllTyFlag -> Bool -isInvisibleForAllTyFlag (Invisible {}) = True -isInvisibleForAllTyFlag Required = False - -isInferredForAllTyFlag :: ForAllTyFlag -> Bool --- More restrictive than isInvisibleForAllTyFlag -isInferredForAllTyFlag (Invisible InferredSpec) = True -isInferredForAllTyFlag _ = False - -isSpecifiedForAllTyFlag :: ForAllTyFlag -> Bool --- More restrictive than isInvisibleForAllTyFlag -isSpecifiedForAllTyFlag (Invisible SpecifiedSpec) = True -isSpecifiedForAllTyFlag _ = False - -coreTyLamForAllTyFlag :: ForAllTyFlag --- ^ The ForAllTyFlag on a (Lam a e) term, where `a` is a type variable. --- If you want other ForAllTyFlag, use a cast. --- See Note [Required foralls in Core] in GHC.Core.TyCo.Rep -coreTyLamForAllTyFlag = Specified - instance Outputable ForAllTyFlag where ppr Required = text "[req]" ppr Specified = text "[spec]" ===================================== compiler/GHC/Types/Var.hs-boot ===================================== @@ -2,13 +2,12 @@ module GHC.Types.Var where import {-# SOURCE #-} GHC.Types.Name +import Language.Haskell.Syntax.Specificity (Specificity) -data ForAllTyFlag data FunTyFlag data Var instance NamedThing Var data VarBndr var argf -data Specificity type TyVar = Var type Id = Var type TyCoVar = Id ===================================== compiler/Language/Haskell/Syntax/Decls.hs ===================================== @@ -98,13 +98,13 @@ import Language.Haskell.Syntax.Binds import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Type import Language.Haskell.Syntax.Basic (Role) +import Language.Haskell.Syntax.Specificity (Specificity) import GHC.Types.Basic (TopLevelFlag, OverlapMode, RuleName, Activation ,TyConFlavour(..), TypeOrData(..)) import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CCallTarget, CExportSpec) import GHC.Types.Fixity (LexicalFixity) -import GHC.Core.Type (Specificity) import GHC.Unit.Module.Warnings (WarningTxt) import GHC.Utils.Panic.Plain ( assert ) ===================================== compiler/Language/Haskell/Syntax/Specificity.hs ===================================== @@ -0,0 +1,68 @@ +{-# LANGUAGE MultiWayIf, PatternSynonyms #-} + +-- TODO Everthing in this module should be moved to +-- Language.Haskell.Syntax.Decls + +module Language.Haskell.Syntax.Specificity ( + -- * ForAllTyFlags + ForAllTyFlag(Invisible,Required,Specified,Inferred), + Specificity(..), + isVisibleForAllTyFlag, isInvisibleForAllTyFlag, isInferredForAllTyFlag, + isSpecifiedForAllTyFlag, + coreTyLamForAllTyFlag, + ) where + +import Prelude + +import Data.Data + +-- | ForAllTyFlag +-- +-- Is something required to appear in source Haskell ('Required'), +-- permitted by request ('Specified') (visible type application), or +-- prohibited entirely from appearing in source Haskell ('Inferred')? +-- See Note [VarBndrs, ForAllTyBinders, TyConBinders, and visibility] in "GHC.Core.TyCo.Rep" +data ForAllTyFlag = Invisible !Specificity + | Required + deriving (Eq, Ord, Data) + -- (<) on ForAllTyFlag means "is less visible than" + +-- | Whether an 'Invisible' argument may appear in source Haskell. +data Specificity = InferredSpec + -- ^ the argument may not appear in source Haskell, it is + -- only inferred. + | SpecifiedSpec + -- ^ the argument may appear in source Haskell, but isn't + -- required. + deriving (Eq, Ord, Data) + +pattern Inferred, Specified :: ForAllTyFlag +pattern Inferred = Invisible InferredSpec +pattern Specified = Invisible SpecifiedSpec + +{-# COMPLETE Required, Specified, Inferred #-} + +-- | Does this 'ForAllTyFlag' classify an argument that is written in Haskell? +isVisibleForAllTyFlag :: ForAllTyFlag -> Bool +isVisibleForAllTyFlag af = not (isInvisibleForAllTyFlag af) + +-- | Does this 'ForAllTyFlag' classify an argument that is not written in Haskell? +isInvisibleForAllTyFlag :: ForAllTyFlag -> Bool +isInvisibleForAllTyFlag (Invisible {}) = True +isInvisibleForAllTyFlag Required = False + +isInferredForAllTyFlag :: ForAllTyFlag -> Bool +-- More restrictive than isInvisibleForAllTyFlag +isInferredForAllTyFlag (Invisible InferredSpec) = True +isInferredForAllTyFlag _ = False + +isSpecifiedForAllTyFlag :: ForAllTyFlag -> Bool +-- More restrictive than isInvisibleForAllTyFlag +isSpecifiedForAllTyFlag (Invisible SpecifiedSpec) = True +isSpecifiedForAllTyFlag _ = False + +coreTyLamForAllTyFlag :: ForAllTyFlag +-- ^ The ForAllTyFlag on a (Lam a e) term, where `a` is a type variable. +-- If you want other ForAllTyFlag, use a cast. +-- See Note [Required foralls in Core] in GHC.Core.TyCo.Rep +coreTyLamForAllTyFlag = Specified View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/017c8c319cd599a199006904de5694f00cc6896b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/017c8c319cd599a199006904de5694f00cc6896b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 10:34:09 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Sun, 09 Jun 2024 06:34:09 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ast] AST: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Message-ID: <66658521956c_1ac9ad1b7261c103093@gitlab.mail> Fabian Kirchner pushed to branch wip/kirchner/ast at Glasgow Haskell Compiler / GHC Commits: 078ef121 by Fabian Kirchner at 2024-06-09T12:33:37+02:00 AST: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - 5 changed files: - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var.hs-boot - compiler/Language/Haskell/Syntax/Decls.hs - + compiler/Language/Haskell/Syntax/Specificity.hs Changes: ===================================== compiler/GHC/Core/TyCo/Rep.hs-boot ===================================== @@ -3,8 +3,9 @@ module GHC.Core.TyCo.Rep where import GHC.Utils.Outputable ( Outputable ) import Data.Data ( Data ) -import {-# SOURCE #-} GHC.Types.Var( Var, VarBndr, ForAllTyFlag, FunTyFlag ) +import {-# SOURCE #-} GHC.Types.Var( Var, VarBndr, FunTyFlag ) import {-# SOURCE #-} GHC.Core.TyCon ( TyCon ) +import Language.Haskell.Syntax.Specificity (ForAllTyFlag) data Type data Coercion ===================================== compiler/GHC/Types/Var.hs ===================================== @@ -129,6 +129,8 @@ import GHC.Utils.Binary import GHC.Utils.Outputable import GHC.Utils.Panic +import Language.Haskell.Syntax.Specificity + import Data.Data import Control.DeepSeq @@ -455,57 +457,6 @@ updateVarTypeM upd var * * ********************************************************************* -} --- | ForAllTyFlag --- --- Is something required to appear in source Haskell ('Required'), --- permitted by request ('Specified') (visible type application), or --- prohibited entirely from appearing in source Haskell ('Inferred')? --- See Note [VarBndrs, ForAllTyBinders, TyConBinders, and visibility] in "GHC.Core.TyCo.Rep" -data ForAllTyFlag = Invisible !Specificity - | Required - deriving (Eq, Ord, Data) - -- (<) on ForAllTyFlag means "is less visible than" - --- | Whether an 'Invisible' argument may appear in source Haskell. -data Specificity = InferredSpec - -- ^ the argument may not appear in source Haskell, it is - -- only inferred. - | SpecifiedSpec - -- ^ the argument may appear in source Haskell, but isn't - -- required. - deriving (Eq, Ord, Data) - -pattern Inferred, Specified :: ForAllTyFlag -pattern Inferred = Invisible InferredSpec -pattern Specified = Invisible SpecifiedSpec - -{-# COMPLETE Required, Specified, Inferred #-} - --- | Does this 'ForAllTyFlag' classify an argument that is written in Haskell? -isVisibleForAllTyFlag :: ForAllTyFlag -> Bool -isVisibleForAllTyFlag af = not (isInvisibleForAllTyFlag af) - --- | Does this 'ForAllTyFlag' classify an argument that is not written in Haskell? -isInvisibleForAllTyFlag :: ForAllTyFlag -> Bool -isInvisibleForAllTyFlag (Invisible {}) = True -isInvisibleForAllTyFlag Required = False - -isInferredForAllTyFlag :: ForAllTyFlag -> Bool --- More restrictive than isInvisibleForAllTyFlag -isInferredForAllTyFlag (Invisible InferredSpec) = True -isInferredForAllTyFlag _ = False - -isSpecifiedForAllTyFlag :: ForAllTyFlag -> Bool --- More restrictive than isInvisibleForAllTyFlag -isSpecifiedForAllTyFlag (Invisible SpecifiedSpec) = True -isSpecifiedForAllTyFlag _ = False - -coreTyLamForAllTyFlag :: ForAllTyFlag --- ^ The ForAllTyFlag on a (Lam a e) term, where `a` is a type variable. --- If you want other ForAllTyFlag, use a cast. --- See Note [Required foralls in Core] in GHC.Core.TyCo.Rep -coreTyLamForAllTyFlag = Specified - instance Outputable ForAllTyFlag where ppr Required = text "[req]" ppr Specified = text "[spec]" ===================================== compiler/GHC/Types/Var.hs-boot ===================================== @@ -2,13 +2,12 @@ module GHC.Types.Var where import {-# SOURCE #-} GHC.Types.Name +import Language.Haskell.Syntax.Specificity (Specificity, ForAllTyFlag) -data ForAllTyFlag data FunTyFlag data Var instance NamedThing Var data VarBndr var argf -data Specificity type TyVar = Var type Id = Var type TyCoVar = Id ===================================== compiler/Language/Haskell/Syntax/Decls.hs ===================================== @@ -98,13 +98,13 @@ import Language.Haskell.Syntax.Binds import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Type import Language.Haskell.Syntax.Basic (Role) +import Language.Haskell.Syntax.Specificity (Specificity) import GHC.Types.Basic (TopLevelFlag, OverlapMode, RuleName, Activation ,TyConFlavour(..), TypeOrData(..)) import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CCallTarget, CExportSpec) import GHC.Types.Fixity (LexicalFixity) -import GHC.Core.Type (Specificity) import GHC.Unit.Module.Warnings (WarningTxt) import GHC.Utils.Panic.Plain ( assert ) ===================================== compiler/Language/Haskell/Syntax/Specificity.hs ===================================== @@ -0,0 +1,68 @@ +{-# LANGUAGE MultiWayIf, PatternSynonyms #-} + +-- TODO Everthing in this module should be moved to +-- Language.Haskell.Syntax.Decls + +module Language.Haskell.Syntax.Specificity ( + -- * ForAllTyFlags + ForAllTyFlag(Invisible,Required,Specified,Inferred), + Specificity(..), + isVisibleForAllTyFlag, isInvisibleForAllTyFlag, isInferredForAllTyFlag, + isSpecifiedForAllTyFlag, + coreTyLamForAllTyFlag, + ) where + +import Prelude + +import Data.Data + +-- | ForAllTyFlag +-- +-- Is something required to appear in source Haskell ('Required'), +-- permitted by request ('Specified') (visible type application), or +-- prohibited entirely from appearing in source Haskell ('Inferred')? +-- See Note [VarBndrs, ForAllTyBinders, TyConBinders, and visibility] in "GHC.Core.TyCo.Rep" +data ForAllTyFlag = Invisible !Specificity + | Required + deriving (Eq, Ord, Data) + -- (<) on ForAllTyFlag means "is less visible than" + +-- | Whether an 'Invisible' argument may appear in source Haskell. +data Specificity = InferredSpec + -- ^ the argument may not appear in source Haskell, it is + -- only inferred. + | SpecifiedSpec + -- ^ the argument may appear in source Haskell, but isn't + -- required. + deriving (Eq, Ord, Data) + +pattern Inferred, Specified :: ForAllTyFlag +pattern Inferred = Invisible InferredSpec +pattern Specified = Invisible SpecifiedSpec + +{-# COMPLETE Required, Specified, Inferred #-} + +-- | Does this 'ForAllTyFlag' classify an argument that is written in Haskell? +isVisibleForAllTyFlag :: ForAllTyFlag -> Bool +isVisibleForAllTyFlag af = not (isInvisibleForAllTyFlag af) + +-- | Does this 'ForAllTyFlag' classify an argument that is not written in Haskell? +isInvisibleForAllTyFlag :: ForAllTyFlag -> Bool +isInvisibleForAllTyFlag (Invisible {}) = True +isInvisibleForAllTyFlag Required = False + +isInferredForAllTyFlag :: ForAllTyFlag -> Bool +-- More restrictive than isInvisibleForAllTyFlag +isInferredForAllTyFlag (Invisible InferredSpec) = True +isInferredForAllTyFlag _ = False + +isSpecifiedForAllTyFlag :: ForAllTyFlag -> Bool +-- More restrictive than isInvisibleForAllTyFlag +isSpecifiedForAllTyFlag (Invisible SpecifiedSpec) = True +isSpecifiedForAllTyFlag _ = False + +coreTyLamForAllTyFlag :: ForAllTyFlag +-- ^ The ForAllTyFlag on a (Lam a e) term, where `a` is a type variable. +-- If you want other ForAllTyFlag, use a cast. +-- See Note [Required foralls in Core] in GHC.Core.TyCo.Rep +coreTyLamForAllTyFlag = Specified View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/078ef12190b00b9001fe18d05b2beff56670afb7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/078ef12190b00b9001fe18d05b2beff56670afb7 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 11:06:42 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Sun, 09 Jun 2024 07:06:42 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/kill-parallel-haskell Message-ID: <66658cc2c4fe2_32f883182978666e7@gitlab.mail> Ben Gamari pushed new branch wip/kill-parallel-haskell at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/kill-parallel-haskell You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 11:39:49 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Sun, 09 Jun 2024 07:39:49 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/users-guide-fixes Message-ID: <666594855beed_32f88363ff88775de@gitlab.mail> Ben Gamari pushed new branch wip/users-guide-fixes at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/users-guide-fixes You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 11:46:09 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Sun, 09 Jun 2024 07:46:09 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/fix-configure Message-ID: <666596018ac5d_32f883767dfc812ad@gitlab.mail> Ben Gamari pushed new branch wip/fix-configure at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fix-configure You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 12:01:03 2024 From: gitlab at gitlab.haskell.org (HugoPeters1024 (@HugoPeters1024)) Date: Sun, 09 Jun 2024 08:01:03 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/hp/fix-typo Message-ID: <6665997f39847_32f883b47d3c1051ad@gitlab.mail> HugoPeters1024 pushed new branch wip/hp/fix-typo at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/hp/fix-typo You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 12:02:00 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sun, 09 Jun 2024 08:02:00 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: ghc-internal: Update CHANGELOG to reflect current version Message-ID: <666599b81a966_32f883be74181053a5@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 7e976dd8 by doyougnu at 2024-06-09T08:01:53-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - e42bb703 by Cheng Shao at 2024-06-09T08:01:53-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - 20 changed files: - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/JS/Ident.hs - compiler/GHC/JS/JStg/Monad.hs - compiler/GHC/JS/JStg/Syntax.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Syntax.hs - compiler/GHC/StgToJS.hs - compiler/GHC/StgToJS/Apply.hs - compiler/GHC/StgToJS/Arg.hs - compiler/GHC/StgToJS/Closure.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/FFI.hs - compiler/GHC/StgToJS/Heap.hs - compiler/GHC/StgToJS/Ids.hs - compiler/GHC/StgToJS/Linker/Linker.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/StgToJS/Object.hs - compiler/GHC/StgToJS/Prim.hs - compiler/GHC/StgToJS/Profiling.hs - compiler/GHC/StgToJS/Regs.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6892cef54462c3a036afc7690ec427282f1942dd...e42bb7032cd7e48df7b9bef343ccf692682b944f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6892cef54462c3a036afc7690ec427282f1942dd...e42bb7032cd7e48df7b9bef343ccf692682b944f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 12:18:57 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Sun, 09 Jun 2024 08:18:57 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] WIP: start adding vector shuffle primops Message-ID: <66659db1c416b_32f883f9e0841189b6@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: d46d56d4 by sheaf at 2024-06-09T14:18:00+02:00 WIP: start adding vector shuffle primops - - - - - 12 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToJS/Prim.hs - utils/genprimopcode/Lexer.x - utils/genprimopcode/Main.hs - utils/genprimopcode/Parser.y - utils/genprimopcode/ParserM.hs - utils/genprimopcode/Syntax.hs Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -4190,6 +4190,13 @@ primop VecWriteScalarOffAddrOp "writeOffAddrAs#" GenPrimOp llvm_only = True vector = ALL_VECTOR_TYPES +primop VecShuffleOp "shuffle#" GenPrimOp + VECTOR -> VECTOR -> INTVECTUPLE -> VECTOR + { Shuffle elements of the concatenation of the input two vectors + into the result vector.} + with llvm_only = True + vector = ALL_VECTOR_TYPES + ------------------------------------------------------------------------ section "Prefetch" ===================================== compiler/GHC/Cmm/MachOp.hs ===================================== @@ -171,6 +171,10 @@ data MachOp | MO_VU_Quot Length Width | MO_VU_Rem Length Width + -- Vector shuffles + | MO_V_Shuffle Length Width [Int] + | MO_VF_Shuffle Length Width [Int] + -- Floating point vector element insertion and extraction operations | MO_VF_Broadcast Length Width -- Broadcast a scalar into a vector | MO_VF_Insert Length Width -- Insert scalar into vector @@ -494,6 +498,9 @@ machOpResultType platform mop tys = MO_VU_Quot l w -> cmmVec l (cmmBits w) MO_VU_Rem l w -> cmmVec l (cmmBits w) + MO_V_Shuffle l w _ -> cmmVec l (cmmBits w) + MO_VF_Shuffle l w _ -> cmmVec l (cmmFloat w) + MO_VF_Broadcast l w -> cmmVec l (cmmFloat w) MO_VF_Insert l w -> cmmVec l (cmmFloat w) MO_VF_Extract _ w -> cmmFloat w @@ -576,6 +583,9 @@ machOpArgReps platform op = MO_FS_Conv from _ -> [from] MO_FF_Conv from _ -> [from] + MO_V_Shuffle l r _ -> [vecwidth l r, vecwidth l r] + MO_VF_Shuffle l r _ -> [vecwidth l r, vecwidth l r] + MO_V_Insert l r -> [vecwidth l r, r, W32] MO_V_Extract l r -> [vecwidth l r, W32] MO_VF_Broadcast l r -> [vecwidth l r, r] ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1104,6 +1104,8 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps MO_VS_Neg {} -> needLlvm mop MO_VU_Quot {} -> needLlvm mop MO_VU_Rem {} -> needLlvm mop + MO_V_Shuffle {} -> incorrectOperands + MO_VF_Shuffle {} -> incorrectOperands MO_VF_Broadcast {} -> incorrectOperands MO_VF_Insert {} -> incorrectOperands MO_VF_Extract {} -> incorrectOperands @@ -1246,6 +1248,18 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps MO_U_Shr rep -> shift_code rep SHR x y {-False-} MO_S_Shr rep -> shift_code rep SAR x y {-False-} + MO_V_Shuffle l w is + | avx + -> vector_shuffle_int l w x y is + | otherwise + -> sorry "Please enable the -mavx flag" + + MO_VF_Shuffle l w is + | avx + -> vector_shuffle_float l w x y is + | otherwise + -> sorry "Please enable the -mavx flag" + MO_VF_Broadcast l W32 | avx -> vector_float_broadcast_avx l W32 x y | sse4_1 -> vector_float_broadcast_sse l W32 x y | otherwise @@ -1635,6 +1649,22 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps vector_float_broadcast_sse _ _ c _ = pprPanic "Broadcast not supported for : " (pdoc platform c) + vector_shuffle_int :: Length -> Width -> CmmExpr -> CmmExpr -> [Int] -> NatM Register + vector_shuffle_int = undefined + + vector_shuffle_float :: Length -> Width -> CmmExpr -> CmmExpr -> [Int] -> NatM Register + vector_shuffle_float l w v1 v2 is = do + (r1, exp1) <- getSomeReg v1 + (r2, exp2) <- getSomeReg v2 + let fmt = VecFormat l (if w == W32 then FmtFloat else FmtDouble) w + code dst + = exp1 `appOL` (exp2 `appOL` shuffleInstructions fmt r1 r2 is dst) --VSHUFPD format imm (OpReg r1) r2) + return (Any fmt code) + + shuffleInstructions :: Format -> Reg -> Reg -> [Int] -> Reg -> OrdList Instr + shuffleInstructions _fmt _v1 _v2 _is _dst = + error "SIMD NCG TODO: lower to shuffle instructions (e.g. VSHUFPD)" + getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps sse4_1 <- sse4_1Enabled sse2 <- sse2Enabled ===================================== compiler/GHC/CmmToC.hs ===================================== @@ -800,6 +800,9 @@ pprMachOp_for_C platform mop = case mop of MO_SF_Conv _from to -> parens (machRep_F_CType to) MO_FS_Conv _from to -> parens (machRep_S_CType platform to) + MO_V_Shuffle {} -> text "__builtin_shufflevector" + MO_VF_Shuffle {} -> text "__builtin_shufflevector" + MO_RelaxedRead _ -> pprTrace "offending mop:" (text "MO_RelaxedRead") (panic $ "PprC.pprMachOp_for_C: MO_S_MulMayOflo" ===================================== compiler/GHC/CmmToLlvm/CodeGen.hs ===================================== @@ -1524,6 +1524,9 @@ genMachOp _ op [x] = case op of MO_VF_Insert _ _ -> panicOp MO_VF_Extract _ _ -> panicOp + MO_V_Shuffle {} -> panicOp + MO_VF_Shuffle {} -> panicOp + MO_VF_Add _ _ -> panicOp MO_VF_Sub _ _ -> panicOp MO_VF_Mul _ _ -> panicOp @@ -1719,6 +1722,9 @@ genMachOp_slow opt op [x, y] = case op of MO_VF_Broadcast {} -> panicOp MO_VF_Insert {} -> panicOp + MO_V_Shuffle _ _ is -> genShuffleOp is x y + MO_VF_Shuffle _ _ is -> genShuffleOp is x y + MO_VF_Neg {} -> panicOp MO_RelaxedRead {} -> panicOp @@ -1831,6 +1837,21 @@ genMachOp_slow _opt op [x, y, z] = do -- More than three expressions, invalid! genMachOp_slow _ _ _ = panic "genMachOp_slow: More than 3 expressions in MachOp!" +genShuffleOp :: [Int] -> CmmExpr -> CmmExpr -> LlvmM ExprData +genShuffleOp is x y = runExprData $ do + vx <- exprToVarW x + vy <- exprToVarW y + let tx = getVarType vx + ty = getVarType vy + Panic.massertPpr + (tx == ty) + (vcat [ text "shuffle: mismatched arg types" + , ppLlvmType tx, ppLlvmType ty ]) + let fname = fsLit "__builtin_shufflevector" + error "SIMD NCG TODO: generate a call to __builtin_shufflevector" + --fptr <- liftExprData $ getInstrinct fname ty [tx, ty] + --doExprW tx $ Call StdCall fptr (vx: vy: map ?? is) [ReadNone, NoUnwind] + -- | Generate code for a fused multiply-add operation. genFmaOp :: CmmExpr -> CmmExpr -> CmmExpr -> LlvmM ExprData genFmaOp x y z = runExprData $ do ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1,4 +1,5 @@ {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE MultiWayIf #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} @@ -1092,6 +1093,13 @@ emitPrimOp cfg primop = ty :: CmmType ty = vecCmmCat vcat w + VecShuffleOp vcat n w -> \ args -> opIntoRegs $ \ [res] -> do + checkVecCompatibility cfg vcat n w + doShuffleOp ty args res + where + ty :: CmmType + ty = vecCmmCat vcat w + -- Prefetch PrefetchByteArrayOp3 -> \args -> opIntoRegs $ \[] -> doPrefetchByteArrayOp 3 args @@ -2587,6 +2595,36 @@ doVecInsertOp ty src e idx res = do wid :: Width wid = typeWidth (vecElemType ty) +------------------------------------------------------------------------------ +-- Shuffles + +doShuffleOp :: CmmType -> [CmmExpr] -> LocalReg -> FCode () +doShuffleOp ty (v1:v2:idxs) res + | isVecType ty + = case mapMaybe idx_maybe idxs of + is + | length is == len + -> emitAssign (CmmLocal res) (CmmMachOp (mo is) [v1,v2]) + | otherwise + -> pprPanic "doShuffleOp" $ + vcat [ text "shuffle indices must be literals, 0 <= i <" <+> ppr len ] + | otherwise + = pprPanic "doShuffleOp" $ + vcat [ text "non-vector argument type:" <+> ppr ty ] + where + len = vecLength ty + wid = typeWidth $ vecElemType ty + mo = if isFloatType (vecElemType ty) + then MO_VF_Shuffle len wid + else MO_V_Shuffle len wid + idx_maybe (CmmLit (CmmInt i _)) + | let j :: Int; j = fromInteger i + , j >= 0, j < 2 * len + = Just j + idx_maybe _ = Nothing +doShuffleOp _ _ _ = + panic "doShuffleOp: wrong number of arguments" + ------------------------------------------------------------------------------ -- Helpers for translating prefetching. ===================================== compiler/GHC/StgToJS/Prim.hs ===================================== @@ -1197,6 +1197,7 @@ genPrim prof bound ty op = case op of VecIndexScalarOffAddrOp _ _ _ -> unhandledPrimop op VecReadScalarOffAddrOp _ _ _ -> unhandledPrimop op VecWriteScalarOffAddrOp _ _ _ -> unhandledPrimop op + VecShuffleOp _ _ _ -> unhandledPrimop op PrefetchByteArrayOp3 -> noOp PrefetchMutableByteArrayOp3 -> noOp ===================================== utils/genprimopcode/Lexer.x ===================================== @@ -67,6 +67,7 @@ words :- <0> "SCALAR" { mkT TSCALAR } <0> "VECTOR" { mkT TVECTOR } <0> "VECTUPLE" { mkT TVECTUPLE } + <0> "INTVECTUPLE" { mkT TINTVECTUPLE } <0> [a-z][a-zA-Z0-9\#_]* { mkTv TLowerName } <0> [A-Z][a-zA-Z0-9\#_]* { mkTv TUpperName } <0> \-? [0-9][0-9]* { mkTv (TInteger . read) } ===================================== utils/genprimopcode/Main.hs ===================================== @@ -79,6 +79,8 @@ desugarVectorSpec i = case vecOptions i of desugarTy (TyApp SCALAR []) = TyApp (TyCon repCon) [] desugarTy (TyApp VECTOR []) = TyApp (VecTyCon vecCons vecTyName) [] desugarTy (TyApp VECTUPLE []) = TyUTup (replicate n (TyApp (TyCon repCon) [])) + desugarTy (TyApp INTVECTUPLE []) + = TyUTup (replicate n (TyApp (TyCon "Int#") []) ) desugarTy (TyApp tycon ts) = TyApp tycon (map desugarTy ts) desugarTy t@(TyVar {}) = t desugarTy (TyUTup ts) = TyUTup (map desugarTy ts) ===================================== utils/genprimopcode/Parser.y ===================================== @@ -58,6 +58,7 @@ import AccessOps SCALAR { TSCALAR } VECTOR { TVECTOR } VECTUPLE { TVECTUPLE } + INTVECTUPLE { TINTVECTUPLE } bytearray_access_ops { TByteArrayAccessOps } addr_access_ops { TAddrAccessOps } thats_all_folks { TThatsAllFolks } @@ -215,6 +216,7 @@ pTycon : upperName { TyCon $1 } | SCALAR { SCALAR } | VECTOR { VECTOR } | VECTUPLE { VECTUPLE } + | INTVECTUPLE { INTVECTUPLE } { parse :: String -> Either String Info ===================================== utils/genprimopcode/ParserM.hs ===================================== @@ -124,6 +124,7 @@ data Token = TEOF | TSCALAR | TVECTOR | TVECTUPLE + | TINTVECTUPLE deriving Show -- Actions ===================================== utils/genprimopcode/Syntax.hs ===================================== @@ -87,6 +87,7 @@ data TyCon = TyCon String | SCALAR | VECTOR | VECTUPLE + | INTVECTUPLE | VecTyCon String String deriving (Eq, Ord) @@ -95,6 +96,7 @@ instance Show TyCon where show SCALAR = "SCALAR" show VECTOR = "VECTOR" show VECTUPLE = "VECTUPLE" + show INTVECTUPLE = "INTVECTUPLE" show (VecTyCon tc _) = tc -- Follow definitions of Fixity and FixityDirection in GHC View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d46d56d4f417517eb1245c45c338378f59bceb4f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d46d56d4f417517eb1245c45c338378f59bceb4f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 12:19:54 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Sun, 09 Jun 2024 08:19:54 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] remove redundant code in CmmToAsm/PPC/Instr Message-ID: <66659dea46efd_32f883ff55f01191b7@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: fbd321e8 by sheaf at 2024-06-09T14:19:42+02:00 remove redundant code in CmmToAsm/PPC/Instr - - - - - 1 changed file: - compiler/GHC/CmmToAsm/PPC/Instr.hs Changes: ===================================== compiler/GHC/CmmToAsm/PPC/Instr.hs ===================================== @@ -563,7 +563,6 @@ mkSpillInstr config reg delta slot ArchPPC -> II32 _ -> II64 RcFloatOrVector -> FF64 - _ -> panic "PPC.Instr.mkSpillInstr: no match" instr = case makeImmediate W32 True (off-delta) of Just _ -> ST Nothing -> STFAR -- pseudo instruction: 32 bit offsets @@ -588,7 +587,6 @@ mkLoadInstr config reg delta slot ArchPPC -> II32 _ -> II64 RcFloatOrVector -> FF64 - _ -> panic "PPC.Instr.mkLoadInstr: no match" instr = case makeImmediate W32 True (off-delta) of Just _ -> LD Nothing -> LDFAR -- pseudo instruction: 32 bit offsets View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fbd321e81cf7876ebb3ea50d5136fb71b9125932 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fbd321e81cf7876ebb3ea50d5136fb71b9125932 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 12:27:38 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Sun, 09 Jun 2024 08:27:38 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ast] ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Message-ID: <66659fba8c3e3_32f88311e9ab41268a0@gitlab.mail> Fabian Kirchner pushed to branch wip/kirchner/ast at Glasgow Haskell Compiler / GHC Commits: 85fe7c8b by Fabian Kirchner at 2024-06-09T14:26:50+02:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - 5 changed files: - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var.hs-boot - compiler/Language/Haskell/Syntax/Decls.hs - + compiler/Language/Haskell/Syntax/Specificity.hs Changes: ===================================== compiler/GHC/Core/TyCo/Rep.hs-boot ===================================== @@ -3,8 +3,9 @@ module GHC.Core.TyCo.Rep where import GHC.Utils.Outputable ( Outputable ) import Data.Data ( Data ) -import {-# SOURCE #-} GHC.Types.Var( Var, VarBndr, ForAllTyFlag, FunTyFlag ) +import {-# SOURCE #-} GHC.Types.Var( Var, VarBndr, FunTyFlag ) import {-# SOURCE #-} GHC.Core.TyCon ( TyCon ) +import Language.Haskell.Syntax.Specificity (ForAllTyFlag) data Type data Coercion ===================================== compiler/GHC/Types/Var.hs ===================================== @@ -129,6 +129,8 @@ import GHC.Utils.Binary import GHC.Utils.Outputable import GHC.Utils.Panic +import Language.Haskell.Syntax.Specificity + import Data.Data import Control.DeepSeq @@ -455,57 +457,6 @@ updateVarTypeM upd var * * ********************************************************************* -} --- | ForAllTyFlag --- --- Is something required to appear in source Haskell ('Required'), --- permitted by request ('Specified') (visible type application), or --- prohibited entirely from appearing in source Haskell ('Inferred')? --- See Note [VarBndrs, ForAllTyBinders, TyConBinders, and visibility] in "GHC.Core.TyCo.Rep" -data ForAllTyFlag = Invisible !Specificity - | Required - deriving (Eq, Ord, Data) - -- (<) on ForAllTyFlag means "is less visible than" - --- | Whether an 'Invisible' argument may appear in source Haskell. -data Specificity = InferredSpec - -- ^ the argument may not appear in source Haskell, it is - -- only inferred. - | SpecifiedSpec - -- ^ the argument may appear in source Haskell, but isn't - -- required. - deriving (Eq, Ord, Data) - -pattern Inferred, Specified :: ForAllTyFlag -pattern Inferred = Invisible InferredSpec -pattern Specified = Invisible SpecifiedSpec - -{-# COMPLETE Required, Specified, Inferred #-} - --- | Does this 'ForAllTyFlag' classify an argument that is written in Haskell? -isVisibleForAllTyFlag :: ForAllTyFlag -> Bool -isVisibleForAllTyFlag af = not (isInvisibleForAllTyFlag af) - --- | Does this 'ForAllTyFlag' classify an argument that is not written in Haskell? -isInvisibleForAllTyFlag :: ForAllTyFlag -> Bool -isInvisibleForAllTyFlag (Invisible {}) = True -isInvisibleForAllTyFlag Required = False - -isInferredForAllTyFlag :: ForAllTyFlag -> Bool --- More restrictive than isInvisibleForAllTyFlag -isInferredForAllTyFlag (Invisible InferredSpec) = True -isInferredForAllTyFlag _ = False - -isSpecifiedForAllTyFlag :: ForAllTyFlag -> Bool --- More restrictive than isInvisibleForAllTyFlag -isSpecifiedForAllTyFlag (Invisible SpecifiedSpec) = True -isSpecifiedForAllTyFlag _ = False - -coreTyLamForAllTyFlag :: ForAllTyFlag --- ^ The ForAllTyFlag on a (Lam a e) term, where `a` is a type variable. --- If you want other ForAllTyFlag, use a cast. --- See Note [Required foralls in Core] in GHC.Core.TyCo.Rep -coreTyLamForAllTyFlag = Specified - instance Outputable ForAllTyFlag where ppr Required = text "[req]" ppr Specified = text "[spec]" ===================================== compiler/GHC/Types/Var.hs-boot ===================================== @@ -2,13 +2,12 @@ module GHC.Types.Var where import {-# SOURCE #-} GHC.Types.Name +import Language.Haskell.Syntax.Specificity (Specificity, ForAllTyFlag) -data ForAllTyFlag data FunTyFlag data Var instance NamedThing Var data VarBndr var argf -data Specificity type TyVar = Var type Id = Var type TyCoVar = Id ===================================== compiler/Language/Haskell/Syntax/Decls.hs ===================================== @@ -98,13 +98,13 @@ import Language.Haskell.Syntax.Binds import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Type import Language.Haskell.Syntax.Basic (Role) +import Language.Haskell.Syntax.Specificity (Specificity) import GHC.Types.Basic (TopLevelFlag, OverlapMode, RuleName, Activation ,TyConFlavour(..), TypeOrData(..)) import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CCallTarget, CExportSpec) import GHC.Types.Fixity (LexicalFixity) -import GHC.Core.Type (Specificity) import GHC.Unit.Module.Warnings (WarningTxt) import GHC.Utils.Panic.Plain ( assert ) ===================================== compiler/Language/Haskell/Syntax/Specificity.hs ===================================== @@ -0,0 +1,68 @@ +{-# LANGUAGE MultiWayIf, PatternSynonyms #-} + +-- TODO Everthing in this module should be moved to +-- Language.Haskell.Syntax.Decls + +module Language.Haskell.Syntax.Specificity ( + -- * ForAllTyFlags + ForAllTyFlag(Invisible,Required,Specified,Inferred), + Specificity(..), + isVisibleForAllTyFlag, isInvisibleForAllTyFlag, isInferredForAllTyFlag, + isSpecifiedForAllTyFlag, + coreTyLamForAllTyFlag, + ) where + +import Prelude + +import Data.Data + +-- | ForAllTyFlag +-- +-- Is something required to appear in source Haskell ('Required'), +-- permitted by request ('Specified') (visible type application), or +-- prohibited entirely from appearing in source Haskell ('Inferred')? +-- See Note [VarBndrs, ForAllTyBinders, TyConBinders, and visibility] in "GHC.Core.TyCo.Rep" +data ForAllTyFlag = Invisible !Specificity + | Required + deriving (Eq, Ord, Data) + -- (<) on ForAllTyFlag means "is less visible than" + +-- | Whether an 'Invisible' argument may appear in source Haskell. +data Specificity = InferredSpec + -- ^ the argument may not appear in source Haskell, it is + -- only inferred. + | SpecifiedSpec + -- ^ the argument may appear in source Haskell, but isn't + -- required. + deriving (Eq, Ord, Data) + +pattern Inferred, Specified :: ForAllTyFlag +pattern Inferred = Invisible InferredSpec +pattern Specified = Invisible SpecifiedSpec + +{-# COMPLETE Required, Specified, Inferred #-} + +-- | Does this 'ForAllTyFlag' classify an argument that is written in Haskell? +isVisibleForAllTyFlag :: ForAllTyFlag -> Bool +isVisibleForAllTyFlag af = not (isInvisibleForAllTyFlag af) + +-- | Does this 'ForAllTyFlag' classify an argument that is not written in Haskell? +isInvisibleForAllTyFlag :: ForAllTyFlag -> Bool +isInvisibleForAllTyFlag (Invisible {}) = True +isInvisibleForAllTyFlag Required = False + +isInferredForAllTyFlag :: ForAllTyFlag -> Bool +-- More restrictive than isInvisibleForAllTyFlag +isInferredForAllTyFlag (Invisible InferredSpec) = True +isInferredForAllTyFlag _ = False + +isSpecifiedForAllTyFlag :: ForAllTyFlag -> Bool +-- More restrictive than isInvisibleForAllTyFlag +isSpecifiedForAllTyFlag (Invisible SpecifiedSpec) = True +isSpecifiedForAllTyFlag _ = False + +coreTyLamForAllTyFlag :: ForAllTyFlag +-- ^ The ForAllTyFlag on a (Lam a e) term, where `a` is a type variable. +-- If you want other ForAllTyFlag, use a cast. +-- See Note [Required foralls in Core] in GHC.Core.TyCo.Rep +coreTyLamForAllTyFlag = Specified View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/85fe7c8b99e15536f26fe6f3b16a9646a173a1a8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/85fe7c8b99e15536f26fe6f3b16a9646a173a1a8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 12:40:39 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Sun, 09 Jun 2024 08:40:39 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ast] ttg: move TopLevelFlag into Language.Haskell.Syntax.Basic Message-ID: <6665a2c766005_32f8831433a1812893b@gitlab.mail> Fabian Kirchner pushed to branch wip/kirchner/ast at Glasgow Haskell Compiler / GHC Commits: 458eeb35 by Fabian Kirchner at 2024-06-09T14:39:47+02:00 ttg: move TopLevelFlag into Language.Haskell.Syntax.Basic Progress towards #21592 - - - - - 3 changed files: - compiler/GHC/Types/Basic.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Decls.hs Changes: ===================================== compiler/GHC/Types/Basic.hs ===================================== @@ -132,7 +132,7 @@ import GHC.Utils.Binary import GHC.Types.SourceText import qualified GHC.LanguageExtensions as LangExt import {-# SOURCE #-} Language.Haskell.Syntax.Type (PromotionFlag(..), isPromoted) -import Language.Haskell.Syntax.Basic (Boxity(..), isBoxed, ConTag) +import Language.Haskell.Syntax.Basic (Boxity(..), isBoxed, ConTag, TopLevelFlag(..), isTopLevel, isNotTopLevel) import {-# SOURCE #-} Language.Haskell.Syntax.Expr (HsDoFlavour) import Control.DeepSeq ( NFData(..) ) @@ -542,19 +542,6 @@ pprRuleName rn = doubleQuotes (ftext rn) ************************************************************************ -} -data TopLevelFlag - = TopLevel - | NotTopLevel - deriving Data - -isTopLevel, isNotTopLevel :: TopLevelFlag -> Bool - -isNotTopLevel NotTopLevel = True -isNotTopLevel TopLevel = False - -isTopLevel TopLevel = True -isTopLevel NotTopLevel = False - instance Outputable TopLevelFlag where ppr TopLevel = text "" ppr NotTopLevel = text "" ===================================== compiler/Language/Haskell/Syntax/Basic.hs ===================================== @@ -96,3 +96,25 @@ data SrcUnpackedness = SrcUnpack -- ^ {-# UNPACK #-} specified | SrcNoUnpack -- ^ {-# NOUNPACK #-} specified | NoSrcUnpack -- ^ no unpack pragma deriving (Eq, Data) + + +{- +************************************************************************ +* * +Top-level/not-top level flag +* * +************************************************************************ +-} + +data TopLevelFlag + = TopLevel + | NotTopLevel + deriving Data + +isTopLevel, isNotTopLevel :: TopLevelFlag -> Bool + +isNotTopLevel NotTopLevel = True +isNotTopLevel TopLevel = False + +isTopLevel TopLevel = True +isTopLevel NotTopLevel = False ===================================== compiler/Language/Haskell/Syntax/Decls.hs ===================================== @@ -97,10 +97,10 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr import Language.Haskell.Syntax.Binds import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Type -import Language.Haskell.Syntax.Basic (Role) +import Language.Haskell.Syntax.Basic (Role, TopLevelFlag) import Language.Haskell.Syntax.Specificity (Specificity) -import GHC.Types.Basic (TopLevelFlag, OverlapMode, RuleName, Activation +import GHC.Types.Basic (OverlapMode, RuleName, Activation ,TyConFlavour(..), TypeOrData(..)) import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CCallTarget, CExportSpec) import GHC.Types.Fixity (LexicalFixity) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/458eeb35ba9b92ef2400f2385553912570465e65 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/458eeb35ba9b92ef2400f2385553912570465e65 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 12:48:11 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Sun, 09 Jun 2024 08:48:11 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ast] ttg: move TypeOrData into Language.Haskell.Syntax.Basic Message-ID: <6665a48bbc412_32f883153ef841342a0@gitlab.mail> Fabian Kirchner pushed to branch wip/kirchner/ast at Glasgow Haskell Compiler / GHC Commits: 4cfa6a53 by Fabian Kirchner at 2024-06-09T14:47:37+02:00 ttg: move TypeOrData into Language.Haskell.Syntax.Basic Progress towards #21592 - - - - - 3 changed files: - compiler/GHC/Types/Basic.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Decls.hs Changes: ===================================== compiler/GHC/Types/Basic.hs ===================================== @@ -132,7 +132,7 @@ import GHC.Utils.Binary import GHC.Types.SourceText import qualified GHC.LanguageExtensions as LangExt import {-# SOURCE #-} Language.Haskell.Syntax.Type (PromotionFlag(..), isPromoted) -import Language.Haskell.Syntax.Basic (Boxity(..), isBoxed, ConTag, TopLevelFlag(..), isTopLevel, isNotTopLevel) +import Language.Haskell.Syntax.Basic (Boxity(..), isBoxed, ConTag, TopLevelFlag(..), isTopLevel, isNotTopLevel, TypeOrData(..)) import {-# SOURCE #-} Language.Haskell.Syntax.Expr (HsDoFlavour) import Control.DeepSeq ( NFData(..) ) @@ -2207,13 +2207,6 @@ tyConFlavourAssoc_maybe :: TyConFlavour tc -> Maybe tc tyConFlavourAssoc_maybe (OpenFamilyFlavour _ mb_parent) = mb_parent tyConFlavourAssoc_maybe _ = Nothing --- | Whether something is a type or a data declaration, --- e.g. a type family or a data family. -data TypeOrData - = IAmData - | IAmType - deriving (Eq, Data) - instance Outputable TypeOrData where ppr IAmData = text "data" ppr IAmType = text "type" ===================================== compiler/Language/Haskell/Syntax/Basic.hs ===================================== @@ -118,3 +118,10 @@ isNotTopLevel TopLevel = False isTopLevel TopLevel = True isTopLevel NotTopLevel = False + +-- | Whether something is a type or a data declaration, +-- e.g. a type family or a data family. +data TypeOrData + = IAmData + | IAmType + deriving (Eq, Data) ===================================== compiler/Language/Haskell/Syntax/Decls.hs ===================================== @@ -97,11 +97,11 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr import Language.Haskell.Syntax.Binds import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Type -import Language.Haskell.Syntax.Basic (Role, TopLevelFlag) +import Language.Haskell.Syntax.Basic (Role, TopLevelFlag, TypeOrData(..)) import Language.Haskell.Syntax.Specificity (Specificity) import GHC.Types.Basic (OverlapMode, RuleName, Activation - ,TyConFlavour(..), TypeOrData(..)) + ,TyConFlavour(..)) import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CCallTarget, CExportSpec) import GHC.Types.Fixity (LexicalFixity) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4cfa6a539a2cd809919f7e8ab6e178e978ae893f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4cfa6a539a2cd809919f7e8ab6e178e978ae893f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 12:48:45 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Sun, 09 Jun 2024 08:48:45 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <6665a4ad7652f_32f8831583aa813445@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: ba31bde3 by Jacco Krijnen at 2024-06-09T14:47:56+02:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ba31bde34307f8c9405ef9b23db7385c17d029b9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ba31bde34307f8c9405ef9b23db7385c17d029b9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 13:00:35 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Sun, 09 Jun 2024 09:00:35 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ast] ttg: move TyConFlavour into Language.Haskell.Syntax.Basic Message-ID: <6665a7733041f_32f88317b5dbc14167e@gitlab.mail> Fabian Kirchner pushed to branch wip/kirchner/ast at Glasgow Haskell Compiler / GHC Commits: f3573f65 by Fabian Kirchner at 2024-06-09T14:59:21+02:00 ttg: move TyConFlavour into Language.Haskell.Syntax.Basic Progress towards #21592 - - - - - 3 changed files: - compiler/GHC/Types/Basic.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Decls.hs Changes: ===================================== compiler/GHC/Types/Basic.hs ===================================== @@ -132,7 +132,7 @@ import GHC.Utils.Binary import GHC.Types.SourceText import qualified GHC.LanguageExtensions as LangExt import {-# SOURCE #-} Language.Haskell.Syntax.Type (PromotionFlag(..), isPromoted) -import Language.Haskell.Syntax.Basic (Boxity(..), isBoxed, ConTag, TopLevelFlag(..), isTopLevel, isNotTopLevel, TypeOrData(..)) +import Language.Haskell.Syntax.Basic (Boxity(..), isBoxed, ConTag, TopLevelFlag(..), isTopLevel, isNotTopLevel, TypeOrData(..), TyConFlavour(..)) import {-# SOURCE #-} Language.Haskell.Syntax.Expr (HsDoFlavour) import Control.DeepSeq ( NFData(..) ) @@ -2153,22 +2153,6 @@ data TypeOrConstraint * * ********************************************************************* -} --- | Paints a picture of what a 'TyCon' represents, in broad strokes. --- This is used towards more informative error messages. -data TyConFlavour tc - = ClassFlavour - | TupleFlavour Boxity - | SumFlavour - | DataTypeFlavour - | NewtypeFlavour - | AbstractTypeFlavour - | OpenFamilyFlavour TypeOrData (Maybe tc) -- Just tc <=> (tc == associated class) - | ClosedTypeFamilyFlavour - | TypeSynonymFlavour - | BuiltInTypeFlavour -- ^ e.g., the @(->)@ 'TyCon'. - | PromotedDataConFlavour - deriving (Eq, Data, Functor) - instance Outputable (TyConFlavour tc) where ppr = text . go where ===================================== compiler/Language/Haskell/Syntax/Basic.hs ===================================== @@ -2,6 +2,8 @@ {-# LANGUAGE GeneralisedNewtypeDeriving #-} module Language.Haskell.Syntax.Basic where +import Prelude + import Data.Data import Data.Eq import Data.Ord @@ -125,3 +127,19 @@ data TypeOrData = IAmData | IAmType deriving (Eq, Data) + +-- | Paints a picture of what a 'TyCon' represents, in broad strokes. +-- This is used towards more informative error messages. +data TyConFlavour tc + = ClassFlavour + | TupleFlavour Boxity + | SumFlavour + | DataTypeFlavour + | NewtypeFlavour + | AbstractTypeFlavour + | OpenFamilyFlavour TypeOrData (Maybe tc) -- Just tc <=> (tc == associated class) + | ClosedTypeFamilyFlavour + | TypeSynonymFlavour + | BuiltInTypeFlavour -- ^ e.g., the @(->)@ 'TyCon'. + | PromotedDataConFlavour + deriving (Eq, Data, Functor) ===================================== compiler/Language/Haskell/Syntax/Decls.hs ===================================== @@ -97,11 +97,10 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr import Language.Haskell.Syntax.Binds import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Type -import Language.Haskell.Syntax.Basic (Role, TopLevelFlag, TypeOrData(..)) +import Language.Haskell.Syntax.Basic (Role, TopLevelFlag, TypeOrData(..), TyConFlavour(..)) import Language.Haskell.Syntax.Specificity (Specificity) -import GHC.Types.Basic (OverlapMode, RuleName, Activation - ,TyConFlavour(..)) +import GHC.Types.Basic (OverlapMode, RuleName, Activation) import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CCallTarget, CExportSpec) import GHC.Types.Fixity (LexicalFixity) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f3573f65620b17534170bf01136eec1a8f1ef2f6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f3573f65620b17534170bf01136eec1a8f1ef2f6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 13:14:43 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Sun, 09 Jun 2024 09:14:43 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] 8 commits: ttg: Remove SourceText from OverloadedLabel Message-ID: <6665aac2f0fc6_32f883197d794142172@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: 1c04f3c1 by Adriaan Leijnse at 2024-06-09T15:14:32+02:00 ttg: Remove SourceText from OverloadedLabel Progress towards #21592 - - - - - a4ca52f4 by Alexander Foremny at 2024-06-09T15:14:33+02:00 AST: GHC.Prelude -> Prelude Refactor occurrences to GHC.Prelude with Prelude within Language/Haskell. Progress towards #21592 - - - - - 08bfba21 by Alexander Foremny at 2024-06-09T15:14:33+02:00 AST: remove occurrences of GHC.Unit.Module.ModuleName `GHC.Unit.Module` re-exports `ModuleName` from `Language.Haskell.Syntax.Module.Name`. Progress towards #21592 - - - - - d367235b by Fabian Kirchner at 2024-06-09T15:14:33+02:00 AST: move Data instance definition for ModuleName to GHC.Unit.Types To remove the dependency on GHC.Utils.Misc inside Language.Haskell.Syntax.Module.Name, the instance definition is moved from there into GHC.Unit.Types. Progress towards #21592 - - - - - 21baa04f by Fabian Kirchner at 2024-06-09T15:14:33+02:00 AST: move negateOverLitVal into GHC.Hs.Lit The function negateOverLitVal is not used within Language.Haskell and therefore can be moved to the respective module inside GHC.Hs. Progress towards #21592 - - - - - 61e15aaa by Fabian Kirchner at 2024-06-09T15:14:33+02:00 AST: move conDetailsArity into GHC.Rename.Module The function conDetailsArity is only used inside GHC.Rename.Module. We therefore move it there from Language.Haskell.Syntax.Lit. Progress towards #21592 - - - - - 4c28edd4 by Mauricio at 2024-06-09T15:14:33+02:00 AST: Remove GHC.Utils.Assert from GHC Simple cleanup. Progress towards #21592 - - - - - d7e78217 by Jacco Krijnen at 2024-06-09T15:14:33+02:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Instance/Typeable.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ba31bde34307f8c9405ef9b23db7385c17d029b9...d7e7821774618dda0271ac90f03eec212cac697f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ba31bde34307f8c9405ef9b23db7385c17d029b9...d7e7821774618dda0271ac90f03eec212cac697f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 13:18:34 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Sun, 09 Jun 2024 09:18:34 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ast] 4 commits: ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Message-ID: <6665abaa3c335_32f8831ab9fa41428ac@gitlab.mail> Fabian Kirchner pushed to branch wip/kirchner/ast at Glasgow Haskell Compiler / GHC Commits: 12c61144 by Fabian Kirchner at 2024-06-09T15:18:23+02:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - 1dfd165e by Fabian Kirchner at 2024-06-09T15:18:23+02:00 ttg: move TopLevelFlag into Language.Haskell.Syntax.Basic Progress towards #21592 - - - - - bcd7dc75 by Fabian Kirchner at 2024-06-09T15:18:23+02:00 ttg: move TypeOrData into Language.Haskell.Syntax.Basic Progress towards #21592 - - - - - 2959c9ad by Fabian Kirchner at 2024-06-09T15:18:23+02:00 ttg: move TyConFlavour into Language.Haskell.Syntax.Basic Progress towards #21592 - - - - - 8 changed files: - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var.hs-boot - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Decls.hs - + compiler/Language/Haskell/Syntax/Specificity.hs - compiler/ghc.cabal.in Changes: ===================================== compiler/GHC/Core/TyCo/Rep.hs-boot ===================================== @@ -3,8 +3,9 @@ module GHC.Core.TyCo.Rep where import GHC.Utils.Outputable ( Outputable ) import Data.Data ( Data ) -import {-# SOURCE #-} GHC.Types.Var( Var, VarBndr, ForAllTyFlag, FunTyFlag ) +import {-# SOURCE #-} GHC.Types.Var( Var, VarBndr, FunTyFlag ) import {-# SOURCE #-} GHC.Core.TyCon ( TyCon ) +import Language.Haskell.Syntax.Specificity (ForAllTyFlag) data Type data Coercion ===================================== compiler/GHC/Types/Basic.hs ===================================== @@ -132,7 +132,7 @@ import GHC.Utils.Binary import GHC.Types.SourceText import qualified GHC.LanguageExtensions as LangExt import {-# SOURCE #-} Language.Haskell.Syntax.Type (PromotionFlag(..), isPromoted) -import Language.Haskell.Syntax.Basic (Boxity(..), isBoxed, ConTag) +import Language.Haskell.Syntax.Basic (Boxity(..), isBoxed, ConTag, TopLevelFlag(..), isTopLevel, isNotTopLevel, TypeOrData(..), TyConFlavour(..)) import {-# SOURCE #-} Language.Haskell.Syntax.Expr (HsDoFlavour) import Control.DeepSeq ( NFData(..) ) @@ -542,19 +542,6 @@ pprRuleName rn = doubleQuotes (ftext rn) ************************************************************************ -} -data TopLevelFlag - = TopLevel - | NotTopLevel - deriving Data - -isTopLevel, isNotTopLevel :: TopLevelFlag -> Bool - -isNotTopLevel NotTopLevel = True -isNotTopLevel TopLevel = False - -isTopLevel TopLevel = True -isTopLevel NotTopLevel = False - instance Outputable TopLevelFlag where ppr TopLevel = text "" ppr NotTopLevel = text "" @@ -2166,22 +2153,6 @@ data TypeOrConstraint * * ********************************************************************* -} --- | Paints a picture of what a 'TyCon' represents, in broad strokes. --- This is used towards more informative error messages. -data TyConFlavour tc - = ClassFlavour - | TupleFlavour Boxity - | SumFlavour - | DataTypeFlavour - | NewtypeFlavour - | AbstractTypeFlavour - | OpenFamilyFlavour TypeOrData (Maybe tc) -- Just tc <=> (tc == associated class) - | ClosedTypeFamilyFlavour - | TypeSynonymFlavour - | BuiltInTypeFlavour -- ^ e.g., the @(->)@ 'TyCon'. - | PromotedDataConFlavour - deriving (Eq, Data, Functor) - instance Outputable (TyConFlavour tc) where ppr = text . go where @@ -2220,13 +2191,6 @@ tyConFlavourAssoc_maybe :: TyConFlavour tc -> Maybe tc tyConFlavourAssoc_maybe (OpenFamilyFlavour _ mb_parent) = mb_parent tyConFlavourAssoc_maybe _ = Nothing --- | Whether something is a type or a data declaration, --- e.g. a type family or a data family. -data TypeOrData - = IAmData - | IAmType - deriving (Eq, Data) - instance Outputable TypeOrData where ppr IAmData = text "data" ppr IAmType = text "type" ===================================== compiler/GHC/Types/Var.hs ===================================== @@ -129,6 +129,8 @@ import GHC.Utils.Binary import GHC.Utils.Outputable import GHC.Utils.Panic +import Language.Haskell.Syntax.Specificity + import Data.Data import Control.DeepSeq @@ -455,57 +457,6 @@ updateVarTypeM upd var * * ********************************************************************* -} --- | ForAllTyFlag --- --- Is something required to appear in source Haskell ('Required'), --- permitted by request ('Specified') (visible type application), or --- prohibited entirely from appearing in source Haskell ('Inferred')? --- See Note [VarBndrs, ForAllTyBinders, TyConBinders, and visibility] in "GHC.Core.TyCo.Rep" -data ForAllTyFlag = Invisible !Specificity - | Required - deriving (Eq, Ord, Data) - -- (<) on ForAllTyFlag means "is less visible than" - --- | Whether an 'Invisible' argument may appear in source Haskell. -data Specificity = InferredSpec - -- ^ the argument may not appear in source Haskell, it is - -- only inferred. - | SpecifiedSpec - -- ^ the argument may appear in source Haskell, but isn't - -- required. - deriving (Eq, Ord, Data) - -pattern Inferred, Specified :: ForAllTyFlag -pattern Inferred = Invisible InferredSpec -pattern Specified = Invisible SpecifiedSpec - -{-# COMPLETE Required, Specified, Inferred #-} - --- | Does this 'ForAllTyFlag' classify an argument that is written in Haskell? -isVisibleForAllTyFlag :: ForAllTyFlag -> Bool -isVisibleForAllTyFlag af = not (isInvisibleForAllTyFlag af) - --- | Does this 'ForAllTyFlag' classify an argument that is not written in Haskell? -isInvisibleForAllTyFlag :: ForAllTyFlag -> Bool -isInvisibleForAllTyFlag (Invisible {}) = True -isInvisibleForAllTyFlag Required = False - -isInferredForAllTyFlag :: ForAllTyFlag -> Bool --- More restrictive than isInvisibleForAllTyFlag -isInferredForAllTyFlag (Invisible InferredSpec) = True -isInferredForAllTyFlag _ = False - -isSpecifiedForAllTyFlag :: ForAllTyFlag -> Bool --- More restrictive than isInvisibleForAllTyFlag -isSpecifiedForAllTyFlag (Invisible SpecifiedSpec) = True -isSpecifiedForAllTyFlag _ = False - -coreTyLamForAllTyFlag :: ForAllTyFlag --- ^ The ForAllTyFlag on a (Lam a e) term, where `a` is a type variable. --- If you want other ForAllTyFlag, use a cast. --- See Note [Required foralls in Core] in GHC.Core.TyCo.Rep -coreTyLamForAllTyFlag = Specified - instance Outputable ForAllTyFlag where ppr Required = text "[req]" ppr Specified = text "[spec]" ===================================== compiler/GHC/Types/Var.hs-boot ===================================== @@ -2,13 +2,12 @@ module GHC.Types.Var where import {-# SOURCE #-} GHC.Types.Name +import Language.Haskell.Syntax.Specificity (Specificity, ForAllTyFlag) -data ForAllTyFlag data FunTyFlag data Var instance NamedThing Var data VarBndr var argf -data Specificity type TyVar = Var type Id = Var type TyCoVar = Id ===================================== compiler/Language/Haskell/Syntax/Basic.hs ===================================== @@ -2,6 +2,8 @@ {-# LANGUAGE GeneralisedNewtypeDeriving #-} module Language.Haskell.Syntax.Basic where +import Prelude + import Data.Data import Data.Eq import Data.Ord @@ -96,3 +98,48 @@ data SrcUnpackedness = SrcUnpack -- ^ {-# UNPACK #-} specified | SrcNoUnpack -- ^ {-# NOUNPACK #-} specified | NoSrcUnpack -- ^ no unpack pragma deriving (Eq, Data) + + +{- +************************************************************************ +* * +Top-level/not-top level flag +* * +************************************************************************ +-} + +data TopLevelFlag + = TopLevel + | NotTopLevel + deriving Data + +isTopLevel, isNotTopLevel :: TopLevelFlag -> Bool + +isNotTopLevel NotTopLevel = True +isNotTopLevel TopLevel = False + +isTopLevel TopLevel = True +isTopLevel NotTopLevel = False + +-- | Whether something is a type or a data declaration, +-- e.g. a type family or a data family. +data TypeOrData + = IAmData + | IAmType + deriving (Eq, Data) + +-- | Paints a picture of what a 'TyCon' represents, in broad strokes. +-- This is used towards more informative error messages. +data TyConFlavour tc + = ClassFlavour + | TupleFlavour Boxity + | SumFlavour + | DataTypeFlavour + | NewtypeFlavour + | AbstractTypeFlavour + | OpenFamilyFlavour TypeOrData (Maybe tc) -- Just tc <=> (tc == associated class) + | ClosedTypeFamilyFlavour + | TypeSynonymFlavour + | BuiltInTypeFlavour -- ^ e.g., the @(->)@ 'TyCon'. + | PromotedDataConFlavour + deriving (Eq, Data, Functor) ===================================== compiler/Language/Haskell/Syntax/Decls.hs ===================================== @@ -97,14 +97,13 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr import Language.Haskell.Syntax.Binds import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Type -import Language.Haskell.Syntax.Basic (Role) +import Language.Haskell.Syntax.Basic (Role, TopLevelFlag, TypeOrData(..), TyConFlavour(..)) +import Language.Haskell.Syntax.Specificity (Specificity) -import GHC.Types.Basic (TopLevelFlag, OverlapMode, RuleName, Activation - ,TyConFlavour(..), TypeOrData(..)) +import GHC.Types.Basic (OverlapMode, RuleName, Activation) import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CCallTarget, CExportSpec) import GHC.Types.Fixity (LexicalFixity) -import GHC.Core.Type (Specificity) import GHC.Unit.Module.Warnings (WarningTxt) import GHC.Utils.Panic.Plain ( assert ) ===================================== compiler/Language/Haskell/Syntax/Specificity.hs ===================================== @@ -0,0 +1,68 @@ +{-# LANGUAGE MultiWayIf, PatternSynonyms #-} + +-- TODO Everthing in this module should be moved to +-- Language.Haskell.Syntax.Decls + +module Language.Haskell.Syntax.Specificity ( + -- * ForAllTyFlags + ForAllTyFlag(Invisible,Required,Specified,Inferred), + Specificity(..), + isVisibleForAllTyFlag, isInvisibleForAllTyFlag, isInferredForAllTyFlag, + isSpecifiedForAllTyFlag, + coreTyLamForAllTyFlag, + ) where + +import Prelude + +import Data.Data + +-- | ForAllTyFlag +-- +-- Is something required to appear in source Haskell ('Required'), +-- permitted by request ('Specified') (visible type application), or +-- prohibited entirely from appearing in source Haskell ('Inferred')? +-- See Note [VarBndrs, ForAllTyBinders, TyConBinders, and visibility] in "GHC.Core.TyCo.Rep" +data ForAllTyFlag = Invisible !Specificity + | Required + deriving (Eq, Ord, Data) + -- (<) on ForAllTyFlag means "is less visible than" + +-- | Whether an 'Invisible' argument may appear in source Haskell. +data Specificity = InferredSpec + -- ^ the argument may not appear in source Haskell, it is + -- only inferred. + | SpecifiedSpec + -- ^ the argument may appear in source Haskell, but isn't + -- required. + deriving (Eq, Ord, Data) + +pattern Inferred, Specified :: ForAllTyFlag +pattern Inferred = Invisible InferredSpec +pattern Specified = Invisible SpecifiedSpec + +{-# COMPLETE Required, Specified, Inferred #-} + +-- | Does this 'ForAllTyFlag' classify an argument that is written in Haskell? +isVisibleForAllTyFlag :: ForAllTyFlag -> Bool +isVisibleForAllTyFlag af = not (isInvisibleForAllTyFlag af) + +-- | Does this 'ForAllTyFlag' classify an argument that is not written in Haskell? +isInvisibleForAllTyFlag :: ForAllTyFlag -> Bool +isInvisibleForAllTyFlag (Invisible {}) = True +isInvisibleForAllTyFlag Required = False + +isInferredForAllTyFlag :: ForAllTyFlag -> Bool +-- More restrictive than isInvisibleForAllTyFlag +isInferredForAllTyFlag (Invisible InferredSpec) = True +isInferredForAllTyFlag _ = False + +isSpecifiedForAllTyFlag :: ForAllTyFlag -> Bool +-- More restrictive than isInvisibleForAllTyFlag +isSpecifiedForAllTyFlag (Invisible SpecifiedSpec) = True +isSpecifiedForAllTyFlag _ = False + +coreTyLamForAllTyFlag :: ForAllTyFlag +-- ^ The ForAllTyFlag on a (Lam a e) term, where `a` is a type variable. +-- If you want other ForAllTyFlag, use a cast. +-- See Note [Required foralls in Core] in GHC.Core.TyCo.Rep +coreTyLamForAllTyFlag = Specified ===================================== compiler/ghc.cabal.in ===================================== @@ -976,6 +976,7 @@ Library Language.Haskell.Syntax.Lit Language.Haskell.Syntax.Module.Name Language.Haskell.Syntax.Pat + Language.Haskell.Syntax.Specificity Language.Haskell.Syntax.Type autogen-modules: GHC.Platform.Constants View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f3573f65620b17534170bf01136eec1a8f1ef2f6...2959c9ad201f867c11793da4845afdbcb78c7097 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f3573f65620b17534170bf01136eec1a8f1ef2f6...2959c9ad201f867c11793da4845afdbcb78c7097 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 13:25:33 2024 From: gitlab at gitlab.haskell.org (Adriaan Leijnse (@aidylns)) Date: Sun, 09 Jun 2024 09:25:33 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/aidylns/rid-hsunboundvar-from-ast Message-ID: <6665ad4d9a47a_32f8831b962ec14338d@gitlab.mail> Adriaan Leijnse pushed new branch wip/aidylns/rid-hsunboundvar-from-ast at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/aidylns/rid-hsunboundvar-from-ast You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 13:29:52 2024 From: gitlab at gitlab.haskell.org (Maurice Scheffmacher (@mauscheff)) Date: Sun, 09 Jun 2024 09:29:52 -0400 Subject: [Git][ghc/ghc][wip/mauscheff/ast] AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Message-ID: <6665ae50c622f_32f8831c78354145244@gitlab.mail> Maurice Scheffmacher pushed to branch wip/mauscheff/ast at Glasgow Haskell Compiler / GHC Commits: 4cf41715 by Mauricio at 2024-06-09T15:29:46+02:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace - - - - - 2 changed files: - compiler/GHC/Hs/Lit.hs - compiler/Language/Haskell/Syntax/Lit.hs Changes: ===================================== compiler/GHC/Hs/Lit.hs ===================================== @@ -34,6 +34,7 @@ import GHC.Hs.Extension import Language.Haskell.Syntax.Expr ( HsExpr ) import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Lit +import GHC.Utils.Panic (panic) {- ************************************************************************ @@ -248,3 +249,19 @@ pmPprHsLit (HsRat _ f _) = ppr f pmPprHsLit (HsFloatPrim _ f) = ppr f pmPprHsLit (HsDoublePrim _ d) = ppr d +negateOverLitVal :: OverLitVal -> OverLitVal +negateOverLitVal (HsIntegral i) = HsIntegral (negateIntegralLit i) +negateOverLitVal (HsFractional f) = HsFractional (negateFractionalLit f) +negateOverLitVal _ = panic "negateOverLitVal: argument is not a number" + +instance (Ord (XXOverLit p)) => Ord (HsOverLit p) where + compare (OverLit _ val1) (OverLit _ val2) = val1 `compare` val2 + compare (XOverLit val1) (XOverLit val2) = val1 `compare` val2 + compare _ _ = panic "Ord HsOverLit" + +-- Comparison operations are needed when grouping literals +-- for compiling pattern-matching (module GHC.HsToCore.Match.Literal) +instance (Eq (XXOverLit p)) => Eq (HsOverLit p) where + (OverLit _ val1) == (OverLit _ val2) = val1 == val2 + (XOverLit val1) == (XOverLit val2) = val1 == val2 + _ == _ = panic "Eq HsOverLit" ===================================== compiler/Language/Haskell/Syntax/Lit.hs ===================================== @@ -20,8 +20,7 @@ module Language.Haskell.Syntax.Lit where import Language.Haskell.Syntax.Extension -import GHC.Utils.Panic (panic) -import GHC.Types.SourceText (IntegralLit, FractionalLit, SourceText, negateIntegralLit, negateFractionalLit) +import GHC.Types.SourceText (IntegralLit, FractionalLit, SourceText) import GHC.Core.Type (Type) import GHC.Data.FastString (FastString, lexicalCompareFS) @@ -128,29 +127,12 @@ data OverLitVal | HsIsString !SourceText !FastString -- ^ String-looking literals deriving Data -negateOverLitVal :: OverLitVal -> OverLitVal -negateOverLitVal (HsIntegral i) = HsIntegral (negateIntegralLit i) -negateOverLitVal (HsFractional f) = HsFractional (negateFractionalLit f) -negateOverLitVal _ = panic "negateOverLitVal: argument is not a number" - --- Comparison operations are needed when grouping literals --- for compiling pattern-matching (module GHC.HsToCore.Match.Literal) -instance (Eq (XXOverLit p)) => Eq (HsOverLit p) where - (OverLit _ val1) == (OverLit _ val2) = val1 == val2 - (XOverLit val1) == (XOverLit val2) = val1 == val2 - _ == _ = panic "Eq HsOverLit" - instance Eq OverLitVal where (HsIntegral i1) == (HsIntegral i2) = i1 == i2 (HsFractional f1) == (HsFractional f2) = f1 == f2 (HsIsString _ s1) == (HsIsString _ s2) = s1 == s2 _ == _ = False -instance (Ord (XXOverLit p)) => Ord (HsOverLit p) where - compare (OverLit _ val1) (OverLit _ val2) = val1 `compare` val2 - compare (XOverLit val1) (XOverLit val2) = val1 `compare` val2 - compare _ _ = panic "Ord HsOverLit" - instance Ord OverLitVal where compare (HsIntegral i1) (HsIntegral i2) = i1 `compare` i2 compare (HsIntegral _) (HsFractional _) = LT View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4cf417153d99426c741195572b65849b8badee18 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4cf417153d99426c741195572b65849b8badee18 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 13:38:25 2024 From: gitlab at gitlab.haskell.org (Melanie Brown (@mixphix)) Date: Sun, 09 Jun 2024 09:38:25 -0400 Subject: [Git][ghc/ghc][wip/prelude-for] 4486 commits: [haddock @ 2002-04-04 16:23:43 by simonmar] Message-ID: <6665b0519e175_32f8831ee16401531a3@gitlab.mail> Melanie Brown pushed to branch wip/prelude-for at Glasgow Haskell Compiler / GHC Commits: 2b39cd94 by Simon Marlow at 2002-04-04T16:23:43+00:00 [haddock @ 2002-04-04 16:23:43 by simonmar] This is Haddock, my stab at a Haskell documentation tool. It's not quite ready for release yet, but I'm putting it in the repository so others can take a look. It uses a locally modified version of the hssource parser, extended with support for GHC extensions and documentation annotations. - - - - - 99ede94f by Simon Marlow at 2002-04-04T16:24:10+00:00 [haddock @ 2002-04-04 16:24:10 by simonmar] forgot one file - - - - - 8363294c by Simon Marlow at 2002-04-05T13:58:15+00:00 [haddock @ 2002-04-05 13:58:15 by simonmar] Remap names in the exported declarations to be "closer" to the current module. eg. if an exported declaration mentions a type 'T' which is imported from module A then re-exported from the current module, then links from the type or indeed the documentation will point to the current module rather than module A. This is to support better hiding: module A won't be referred to in the generated output. - - - - - 1570cbc1 by Simon Marlow at 2002-04-05T13:58:23+00:00 [haddock @ 2002-04-05 13:58:23 by simonmar] update the TODO list - - - - - 3a62f96b by Simon Marlow at 2002-04-05T14:11:51+00:00 [haddock @ 2002-04-05 14:11:51 by simonmar] Fix the anchor for a class declaration - - - - - c5d9a471 by Simon Marlow at 2002-04-05T14:18:41+00:00 [haddock @ 2002-04-05 14:18:41 by simonmar] remove underlines on visited links - - - - - 97280525 by Simon Marlow at 2002-04-05T16:11:47+00:00 [haddock @ 2002-04-05 16:11:47 by simonmar] - Update to generate more correct HTML. - Use our own non-overloaded table combinators, as the overloaded versions were giving me a headache. The improved type safety caught several errors in the HTML generation. - - - - - 9acd3a4d by Simon Marlow at 2002-04-05T16:32:19+00:00 [haddock @ 2002-04-05 16:32:19 by simonmar] Add width property to the title, and add TD.children for the module contents page. - - - - - ec9a0847 by Simon Marlow at 2002-04-08T16:39:56+00:00 [haddock @ 2002-04-08 16:39:56 by simonmar] Fix a problem with exports of the form T(..). - - - - - e4627dc8 by Simon Marlow at 2002-04-08T16:41:38+00:00 [haddock @ 2002-04-08 16:41:37 by simonmar] - Add our own versions of Html & BlockTable for the time being. - Add support for generating an index to the HTML backend - - - - - 2d73fd75 by Simon Marlow at 2002-04-09T11:23:24+00:00 [haddock @ 2002-04-09 11:23:24 by simonmar] Add '-- /' as a synonym for '-- |', for compatibility with IDoc. - - - - - 3675464e by Simon Marlow at 2002-04-09T11:33:55+00:00 [haddock @ 2002-04-09 11:33:54 by simonmar] - add the <...> syntax for marking up URLs in documentation - Make the output for data & class declarations more compact when there aren't any documentation annotations on the individual methods or constructors respectively. - - - - - 5077f5b1 by Simon Marlow at 2002-04-09T11:36:04+00:00 [haddock @ 2002-04-09 11:36:04 by simonmar] Update the TODO list - - - - - 9e83c54d by Simon Marlow at 2002-04-10T10:50:06+00:00 [haddock @ 2002-04-10 10:50:06 by simonmar] Use explicit 'px' suffix on pixel sizes; IE seems to prefer them - - - - - 052de51c by Simon Marlow at 2002-04-10T13:23:13+00:00 [haddock @ 2002-04-10 13:23:13 by simonmar] Lex URLs as a single token to avoid having to escape special characters inside the URL string. - - - - - 47187edb by Simon Marlow at 2002-04-10T13:23:55+00:00 [haddock @ 2002-04-10 13:23:55 by simonmar] Not sure why I made the constructor name for a record declaration into a TyCls name, but change it back into a Var name anyhow. - - - - - 3dc6aa81 by Simon Marlow at 2002-04-10T13:26:10+00:00 [haddock @ 2002-04-10 13:26:09 by simonmar] Lots of changes, including: - add index support to the HTML backend - clean up the renamer, put it into a monad - propogate unresolved names to the top level and report them in a nicer way - various bugfixes - - - - - c2a70a72 by Simon Marlow at 2002-04-10T13:32:39+00:00 [haddock @ 2002-04-10 13:32:39 by simonmar] Skeleton documentation - - - - - 50c98d17 by Simon Marlow at 2002-04-10T13:37:23+00:00 [haddock @ 2002-04-10 13:37:23 by simonmar] Update the TODO list, separate into pre-1.0 and post-1.0 items - - - - - f3778be6 by Simon Marlow at 2002-04-10T14:30:58+00:00 [haddock @ 2002-04-10 14:30:58 by simonmar] Add an introduction - - - - - cfbaf9f7 by Simon Marlow at 2002-04-10T14:59:51+00:00 [haddock @ 2002-04-10 14:59:51 by simonmar] Sort the module tree - - - - - 76bd7b34 by Simon Marlow at 2002-04-10T15:50:11+00:00 [haddock @ 2002-04-10 15:50:10 by simonmar] Generate a little table of contents at the top of the module doc (only if the module actually contains some section headings, though). - - - - - bb8560a1 by Simon Marlow at 2002-04-10T16:10:26+00:00 [haddock @ 2002-04-10 16:10:26 by simonmar] Now we understand (or at least don't barf on) type signatures in patterns such as you might find when scoped type variables are in use. - - - - - 86c2a026 by Simon Marlow at 2002-04-10T16:10:49+00:00 [haddock @ 2002-04-10 16:10:49 by simonmar] more updates - - - - - 1c052b0e by Simon Marlow at 2002-04-10T16:28:05+00:00 [haddock @ 2002-04-10 16:28:05 by simonmar] Parse errors in doc strings are now reported as warnings rather that causing the whole thing to fall over. It still needs cleaning up (the warning is emitted with trace) but this will do for the time being. - - - - - ace03e8f by Simon Marlow at 2002-04-10T16:38:03+00:00 [haddock @ 2002-04-10 16:38:03 by simonmar] update again - - - - - 69006c3e by Simon Marlow at 2002-04-11T13:38:02+00:00 [haddock @ 2002-04-11 13:38:02 by simonmar] mention Opera - - - - - fe9b10f8 by Simon Marlow at 2002-04-11T13:40:31+00:00 [haddock @ 2002-04-11 13:40:30 by simonmar] - copy haddock.css into the same place as the generated HTML - new option: --css <file> specifies the style sheet to use - new option: -o <dir> specifies the directory in which to generate the output. - because Haddock now needs to know where to find its default stylesheet, we have to have a wrapper script and do the haddock-inplace thing (Makefile code copied largely from fptools/happy). - - - - - 106adbbe by Simon Marlow at 2002-04-24T15:12:41+00:00 [haddock @ 2002-04-24 15:12:41 by simonmar] Stop slurping comment lines when we see a row of dashes longer than length 2: these are useful as separators. - - - - - 995d3f9e by Simon Marlow at 2002-04-24T15:14:12+00:00 [haddock @ 2002-04-24 15:14:11 by simonmar] Grok the kind of module headers we use in fptools/libraries, and pass the "portability", "stability", and "maintainer" strings through into the generated HTML. If the module header doesn't match the pattern, then we don't include the info in the HTML. - - - - - e14da136 by Simon Marlow at 2002-04-24T15:16:57+00:00 [haddock @ 2002-04-24 15:16:57 by simonmar] Done module headers now. - - - - - 2ca8dfd4 by Simon Marlow at 2002-04-24T15:57:48+00:00 [haddock @ 2002-04-24 15:57:47 by simonmar] Handle gcons in export lists (a common extension). - - - - - 044cea81 by Simon Marlow at 2002-04-25T14:20:12+00:00 [haddock @ 2002-04-25 14:20:12 by simonmar] Add the little lambda icon - - - - - 63955027 by Simon Marlow at 2002-04-25T14:40:05+00:00 [haddock @ 2002-04-25 14:40:05 by simonmar] - Add support for named chunks of documentation which can be referenced from the export list. - Copy the icon from $libdir to the destination in HTML mode. - - - - - 36e3f913 by Simon Marlow at 2002-04-25T16:48:36+00:00 [haddock @ 2002-04-25 16:48:36 by simonmar] More keyboard bashing - - - - - 7ae18dd0 by Simon Marlow at 2002-04-26T08:43:33+00:00 [haddock @ 2002-04-26 08:43:33 by simonmar] Package util reqd. to compile with 4.08.2 - - - - - bbd5fbab by Simon Marlow at 2002-04-26T10:13:00+00:00 [haddock @ 2002-04-26 10:13:00 by simonmar] Include $(GHC_HAPPY_OPTS) when compiling HsParser - - - - - 31c53d79 by Simon Marlow at 2002-04-26T11:18:57+00:00 [haddock @ 2002-04-26 11:18:56 by simonmar] - support for fundeps (partially contributed by Brett Letner - thanks Brett). - make it build with GHC 4.08.2 - - - - - c415ce76 by Simon Marlow at 2002-04-26T13:15:02+00:00 [haddock @ 2002-04-26 13:15:02 by simonmar] Move the explicit formatting of the little table for the stability/portability/maintainer info from the HTML into the CSS, and remove the explicit table size (just right-align it). - - - - - 520ee21a by Simon Marlow at 2002-04-26T16:01:44+00:00 [haddock @ 2002-04-26 16:01:44 by simonmar] Yet more keyboard bashing - this is pretty much complete now. - - - - - 2ae37179 by Simon Marlow at 2002-04-26T16:02:14+00:00 [haddock @ 2002-04-26 16:02:14 by simonmar] Add a couple of things I forgot about - - - - - b7211e04 by Simon Marlow at 2002-04-29T15:28:12+00:00 [haddock @ 2002-04-29 15:28:12 by simonmar] bugfix for declBinders on a NewTypeDecl - - - - - 640c154a by Simon Marlow at 2002-04-29T15:28:54+00:00 [haddock @ 2002-04-29 15:28:54 by simonmar] Allow '-- |' style annotations on constructors and record fields. - - - - - 393f258a by Simon Marlow at 2002-04-29T15:37:32+00:00 [haddock @ 2002-04-29 15:37:32 by simonmar] syntax fix - - - - - 8a2c2549 by Simon Marlow at 2002-04-29T15:37:48+00:00 [haddock @ 2002-04-29 15:37:48 by simonmar] Add an example - - - - - db88f8a2 by Simon Marlow at 2002-04-29T15:55:46+00:00 [haddock @ 2002-04-29 15:55:46 by simonmar] remove a trace - - - - - 2b0248e0 by Simon Marlow at 2002-04-29T15:56:19+00:00 [haddock @ 2002-04-29 15:56:19 by simonmar] Fix for 'make install' - - - - - 120453a0 by Simon Marlow at 2002-04-29T15:56:39+00:00 [haddock @ 2002-04-29 15:56:39 by simonmar] Install the auxilliary bits - - - - - 950e6dbb by Simon Marlow at 2002-04-29T15:57:30+00:00 [haddock @ 2002-04-29 15:57:30 by simonmar] Add BinDist bits - - - - - 154b9d71 by Simon Marlow at 2002-05-01T11:02:52+00:00 [haddock @ 2002-05-01 11:02:52 by simonmar] update - - - - - ba6c39fa by Simon Marlow at 2002-05-01T11:03:26+00:00 [haddock @ 2002-05-01 11:03:26 by simonmar] Add another item - - - - - bacb5e33 by Simon Marlow at 2002-05-03T08:50:00+00:00 [haddock @ 2002-05-03 08:50:00 by simonmar] Fix some typos. - - - - - 54c87895 by Sven Panne at 2002-05-05T19:40:51+00:00 [haddock @ 2002-05-05 19:40:51 by panne] As a temporary hack/workaround for a bug in GHC's simplifier, don't pass Happy the -c option for generating the parsers in this subdir. Furthermore, disable -O for HaddocParse, too. - - - - - e6c08703 by Simon Marlow at 2002-05-06T09:51:10+00:00 [haddock @ 2002-05-06 09:51:10 by simonmar] Add RPM spec file (thanks to Tom Moertel <tom-rpms at moertel.com>) - - - - - 7b8fa8e7 by Simon Marlow at 2002-05-06T12:29:26+00:00 [haddock @ 2002-05-06 12:29:26 by simonmar] Add missing type signature (a different workaround for the bug in GHC's simplifier). - - - - - cd0e300d by Simon Marlow at 2002-05-06T12:30:09+00:00 [haddock @ 2002-05-06 12:30:09 by simonmar] Remove workaround for simplifier bug in previous revision. - - - - - 687e68fa by Simon Marlow at 2002-05-06T12:32:32+00:00 [haddock @ 2002-05-06 12:32:32 by simonmar] Allow empty data declarations (another GHC extension). - - - - - 8f29f696 by Simon Marlow at 2002-05-06T12:49:21+00:00 [haddock @ 2002-05-06 12:49:21 by simonmar] Fix silly bug in named documentation block lookup. - - - - - 8e0059af by Simon Marlow at 2002-05-06T13:02:42+00:00 [haddock @ 2002-05-06 13:02:42 by simonmar] Add another named chunk with a different name - - - - - 68f8a896 by Simon Marlow at 2002-05-06T13:32:32+00:00 [haddock @ 2002-05-06 13:32:32 by simonmar] Be more lenient about extra paragraph breaks - - - - - 65fc31db by Simon Marlow at 2002-05-07T15:36:36+00:00 [haddock @ 2002-05-07 15:36:36 by simonmar] DocEmpty is a right and left-unit of DocAppend (remove it in the smart constructor). - - - - - adc81078 by Simon Marlow at 2002-05-07T15:37:15+00:00 [haddock @ 2002-05-07 15:37:15 by simonmar] Allow code blocks to be denoted with bird-tracks in addition to [...]. - - - - - 1283a3c1 by Simon Marlow at 2002-05-08T11:21:56+00:00 [haddock @ 2002-05-08 11:21:56 by simonmar] Add a facility for specifying options that affect Haddock's treatment of the module. Options are given at the top of the module in a comma-separated list, beginning with '-- #'. eg. -- # prune, hide, ignore-exports Options currently available, with their meanings: prune: ignore declarations which have no documentation annotations ignore-exports: act as if the export list were not specified (i.e. export everything local to the module). hide: do not include this module in the generated documentation, but propagate any exported definitions to modules which re-export them. There's a slight change in the semantics for re-exporting a full module by giving 'module M' in the export list: if module M does not have the 'hide' option, then the documentation will now just contain a reference to module M rather than the full inlined contents of that module. These features, and some other changes in the pipeline, are the result of discussions between myself and Manuel Chakravarty <chak at cse.unsw.edu.au> (author of IDoc) yesterday. Also: some cleanups, use a Writer monad to collect error messages in some places instead of just printing them with trace. - - - - - a2239cf5 by Simon Marlow at 2002-05-08T11:22:30+00:00 [haddock @ 2002-05-08 11:22:30 by simonmar] Update to test new features. - - - - - 6add955f by Simon Marlow at 2002-05-08T13:37:25+00:00 [haddock @ 2002-05-08 13:37:25 by simonmar] Change the markup for typewriter-font from [...] to @... at . The reasoning is that the '@' symbol is much less likely to be needed than square brackets, and we don't want to have to escape square brackets in code fragments. This will be mildly painful in the short term, but it's better to get the change out of the way as early as possible. - - - - - cda06447 by Simon Marlow at 2002-05-08T13:39:56+00:00 [haddock @ 2002-05-08 13:39:56 by simonmar] Allow nested-style comments to be used as documentation annotations too. eg. {-| ... -} is equivalent to -- | ... An extra space can also be left after the comment opener: {- | ... -}. The only version that isn't allowed is {-# ... -}, because this syntax overlaps with Haskell pragmas; use {- # ... -} instead. - - - - - db23f65e by Simon Marlow at 2002-05-08T14:48:41+00:00 [haddock @ 2002-05-08 14:48:39 by simonmar] Add support for existential quantifiers on constructors. - - - - - adce3794 by Simon Marlow at 2002-05-08T15:43:25+00:00 [haddock @ 2002-05-08 15:43:25 by simonmar] update - - - - - 62a1f436 by Simon Marlow at 2002-05-08T15:44:10+00:00 [haddock @ 2002-05-08 15:44:10 by simonmar] Update to version 0.2 - - - - - f6a24ba3 by Simon Marlow at 2002-05-09T08:48:29+00:00 [haddock @ 2002-05-09 08:48:29 by simonmar] typo - - - - - 9f9522a4 by Simon Marlow at 2002-05-09T10:33:14+00:00 [haddock @ 2002-05-09 10:33:14 by simonmar] oops, left out '/' from the special characters in the last change. - - - - - 14abcb39 by Simon Marlow at 2002-05-09T10:34:44+00:00 [haddock @ 2002-05-09 10:34:44 by simonmar] Fix buglet - - - - - b8d878be by Simon Marlow at 2002-05-09T10:35:00+00:00 [haddock @ 2002-05-09 10:35:00 by simonmar] Give a more useful instance of Show for Module. - - - - - f7bfd626 by Simon Marlow at 2002-05-09T10:37:07+00:00 [haddock @ 2002-05-09 10:37:07 by simonmar] The last commit to Main.lhs broke the delicate balance of laziness which was being used to avoid computing the dependency graph of modules. So I finally bit the bullet and did a proper topological sort of the module graph, which turned out to be easy (stealing the Digraph module from GHC - this really ought to be in the libraries somewhere). - - - - - b481c1d0 by Simon Marlow at 2002-05-09T10:37:25+00:00 [haddock @ 2002-05-09 10:37:25 by simonmar] another item done - - - - - 032e2b42 by Simon Marlow at 2002-05-09T10:44:15+00:00 [haddock @ 2002-05-09 10:44:15 by simonmar] Don't consider a module re-export as having documentation, for the purposes of deciding whether we need a Synopsis section or not. - - - - - 5fb45e92 by Simon Marlow at 2002-05-09T11:10:55+00:00 [haddock @ 2002-05-09 11:10:55 by simonmar] Add a special case for list types in ppHsAType - - - - - 1937e428 by Simon Marlow at 2002-05-09T12:43:06+00:00 [haddock @ 2002-05-09 12:43:06 by simonmar] Type synonyms can accept a ctype on the RHS, to match GHC. - - - - - 0f16ce56 by Simon Marlow at 2002-05-09T12:45:19+00:00 [haddock @ 2002-05-09 12:45:19 by simonmar] Add 'stdcall' keyword - - - - - 29b0d7d2 by Simon Marlow at 2002-05-09T13:35:45+00:00 [haddock @ 2002-05-09 13:35:45 by simonmar] Add System Requirements section - - - - - bf14dddd by Simon Marlow at 2002-05-09T13:36:11+00:00 [haddock @ 2002-05-09 13:36:11 by simonmar] Test existential types, amongst other things - - - - - 502f8f6f by Simon Marlow at 2002-05-09T13:37:35+00:00 [haddock @ 2002-05-09 13:37:35 by simonmar] Print the module name in a doc-string parse error - - - - - ca1f8d49 by Simon Marlow at 2002-05-09T13:38:04+00:00 [haddock @ 2002-05-09 13:38:04 by simonmar] Add dependency - - - - - 8d3d91ff by Simon Marlow at 2002-05-09T15:37:57+00:00 [haddock @ 2002-05-09 15:37:57 by simonmar] Add the changelog/release notes - - - - - f3960959 by Simon Marlow at 2002-05-09T15:47:47+00:00 [haddock @ 2002-05-09 15:47:47 by simonmar] mention the backquote-style of markup - - - - - 089fb6e6 by Simon Marlow at 2002-05-09T15:59:45+00:00 [haddock @ 2002-05-09 15:59:45 by simonmar] update - - - - - bdd3be0b by Simon Marlow at 2002-05-09T15:59:56+00:00 [haddock @ 2002-05-09 15:59:56 by simonmar] Document changes since 0.1 - - - - - 00fc4af8 by Simon Marlow at 2002-05-10T08:22:48+00:00 [haddock @ 2002-05-10 08:22:48 by simonmar] oops, update to version 0.2 - - - - - a8a79041 by Simon Marlow at 2002-05-10T16:05:08+00:00 [haddock @ 2002-05-10 16:05:08 by simonmar] Only include a mini-contents if there are 2 or more sections - - - - - 06653319 by Simon Marlow at 2002-05-13T09:13:12+00:00 [haddock @ 2002-05-13 09:13:12 by simonmar] fix typos - - - - - 1402b19b by Simon Marlow at 2002-05-13T10:14:22+00:00 [haddock @ 2002-05-13 10:14:22 by simonmar] Allow backquote as the right-hand quote as well as the left-hand quote, as suggested by Dean Herrington. Clean up the grammar a litte. - - - - - dcd5320d by Simon Marlow at 2002-05-13T10:44:10+00:00 [haddock @ 2002-05-13 10:44:10 by simonmar] a couple more things, prioritise a bit - - - - - a90130c4 by Simon Marlow at 2002-05-13T15:19:03+00:00 [haddock @ 2002-05-13 15:19:03 by simonmar] Cope with datatypes which have documentation on the constructor but not the type itself, and records which have documentation on the fields but not the constructor. (Thanks to Ross Paterson for pointing out the bugs). - - - - - a774d432 by Simon Marlow at 2002-05-13T15:20:54+00:00 [haddock @ 2002-05-13 15:20:54 by simonmar] Fix one of the record examples - - - - - 2d1d5218 by Simon Marlow at 2002-05-15T12:44:35+00:00 [haddock @ 2002-05-15 12:44:35 by simonmar] Preserve the newline before a bird-track, but only within a paragraph. - - - - - 1554c09a by Simon Marlow at 2002-05-15T13:03:02+00:00 [haddock @ 2002-05-15 13:03:01 by simonmar] Reworking of the internals to support documenting function arguments (the Most Wanted new feature by the punters). The old method of keeping parsed documentation in a Name -> Doc mapping wasn't going to cut it for anntations on type components, where there's no name to attach the documentation to, so I've moved to storing all the documentation in the abstract syntax. Previously some of the documentation was left in the abstract syntax by the parser, but was later extracted into the mapping. In order to avoid having to parameterise the abstract syntax over the type of documentation stored in it, we have to parse the documentation at the same time as we parse the Haskell source (well, I suppose we could store 'Either String Doc' in the HsSyn, but that's clunky). One upshot is that documentation is now parsed eagerly, and documentation parse errors are fatal (but have better line numbers in the error message). The new story simplifies matters for the code that processes the source modules, because we don't have to maintain the extra Name->Doc mapping, and it should improve efficiency a little too. New features: - Function arguments and return values can now have doc annotations. - If you refer to a qualified name in a doc string, eg. 'IO.putStr', then Haddock will emit a hyperlink even if the identifier is not in scope, so you don't have to make sure everything referred to from the documentation is imported. - several bugs & minor infelicities fixed. - - - - - 57344dc3 by Simon Marlow at 2002-05-15T13:03:19+00:00 [haddock @ 2002-05-15 13:03:19 by simonmar] Bump to version 0.3 - - - - - b2791812 by Simon Marlow at 2002-05-15T13:03:41+00:00 [haddock @ 2002-05-15 13:03:41 by simonmar] update - - - - - fead183e by Simon Marlow at 2002-05-15T13:10:15+00:00 [haddock @ 2002-05-15 13:10:15 by simonmar] Rename Foo.hs to Test.hs, and add a Makefile - - - - - b0b1f89f by Simon Marlow at 2002-05-15T13:16:07+00:00 [haddock @ 2002-05-15 13:16:07 by simonmar] - Remove the note about function argument docs not being implemented - Note that qualified identifiers can be used to point to entities that aren't in scope. - - - - - 5665f31a by Simon Marlow at 2002-05-15T13:28:46+00:00 [haddock @ 2002-05-15 13:28:46 by simonmar] Patch to add support for GHC-style primitive strings ".."#, from Ross Paterson. - - - - - 0564505d by Simon Marlow at 2002-05-17T10:51:57+00:00 [haddock @ 2002-05-17 10:51:57 by simonmar] Fix bugs in qualified name handling (A.B.f was returned as B.f) - - - - - 10e7311c by Simon Marlow at 2002-05-21T10:24:52+00:00 [haddock @ 2002-05-21 10:24:52 by simonmar] - Use an alternate tabular layout for datatypes, which is more compact - Fix some problems with the function argument documentation - - - - - 2f91c2a6 by Simon Marlow at 2002-05-21T10:27:40+00:00 [haddock @ 2002-05-21 10:27:40 by simonmar] add a few more test cases - - - - - 01c2ddd2 by Simon Marlow at 2002-05-21T10:28:33+00:00 [haddock @ 2002-05-21 10:28:33 by simonmar] Rearrange a bit, and add support for tabular datatype rendering - - - - - a4e4c5f8 by Simon Marlow at 2002-05-27T09:03:52+00:00 [haddock @ 2002-05-27 09:03:51 by simonmar] Lots of changes: - instances of a class are listed with the class, and instances involving a datatype are listed with that type. Derived instances aren't included at the moment: the calculation to find the instance head for a derived instance is non-trivial. - some formatting changes; use rows with specified height rather than cellspacing in some places. - various fixes (source file links were wrong, amongst others) - - - - - 48722e68 by Simon Marlow at 2002-05-27T12:30:38+00:00 [haddock @ 2002-05-27 12:30:37 by simonmar] - Put function arguments *before* the doc for the function, as suggested by Sven Panne. This looks nicer when the function documentation is long. - Switch to using bold for binders at the definition site, and use underline for keywords. This makes the binder stand out more. - - - - - 657204d2 by Simon Marlow at 2002-05-27T13:19:49+00:00 [haddock @ 2002-05-27 13:19:49 by simonmar] Fix bug: we weren't renaming HsDocCommentNamed in renameDecl - - - - - 592aae66 by Simon Marlow at 2002-05-27T14:10:27+00:00 [haddock @ 2002-05-27 14:10:27 by simonmar] Fix some bugs in the rendering of qualified type signatures. - - - - - 69c8f763 by Simon Marlow at 2002-05-27T14:36:45+00:00 [haddock @ 2002-05-27 14:36:45 by simonmar] warning message tweak - - - - - 16e64e21 by Simon Marlow at 2002-05-27T14:53:53+00:00 [haddock @ 2002-05-27 14:53:53 by simonmar] hyperlinked identifiers should be in <tt> - - - - - 8d5e4783 by Simon Marlow at 2002-05-27T15:56:45+00:00 [haddock @ 2002-05-27 15:56:45 by simonmar] Do something sensible for modules which don't export anything (except instances). - - - - - 9d3ef811 by Simon Marlow at 2002-05-28T10:12:50+00:00 [haddock @ 2002-05-28 10:12:50 by simonmar] Rename the module documentation properly (bug reported by Sven Panne). - - - - - ef03a1cc by Simon Marlow at 2002-05-28T10:13:04+00:00 [haddock @ 2002-05-28 10:13:04 by simonmar] Add some more test cases - - - - - 92baa0e8 by Simon Marlow at 2002-05-28T11:17:55+00:00 [haddock @ 2002-05-28 11:17:55 by simonmar] If an identifier doesn't lex, then just replace it by a DocString. - - - - - a3156213 by Simon Marlow at 2002-05-28T16:16:19+00:00 [haddock @ 2002-05-28 16:16:19 by simonmar] Only link to names in the current module which are actually listed in the documentation. A name may be exported but not present in the documentation if it is exported as part of a 'module M' export specifier. - - - - - 31acf941 by Simon Marlow at 2002-05-28T16:17:11+00:00 [haddock @ 2002-05-28 16:17:11 by simonmar] update - - - - - 7e474ebf by Sigbjorn Finne at 2002-05-28T22:42:08+00:00 [haddock @ 2002-05-28 22:42:08 by sof] Handle lone occurrences of '/', e.g., -- | This/that. [did this in the lexer rather than in the parser, as I couldn't see a way not to introduce an S/R conflict that way.] - - - - - 093f7e53 by Simon Marlow at 2002-05-29T09:09:49+00:00 [haddock @ 2002-05-29 09:09:49 by simonmar] Back out previous change until we can find a better way to do this. - - - - - 9234389c by Simon Marlow at 2002-05-29T13:19:06+00:00 [haddock @ 2002-05-29 13:19:06 by simonmar] Make the markup syntax a little more friendly: - single quotes are now interpreted literally unless they surround a valid Haskell identifier. So for example now there's no need to escape a single quote used as an apostrophe. - text to the right of a bird track is now literal (if you want marked-up text in a code block, use @...@). - - - - - b3333526 by Simon Marlow at 2002-05-29T13:38:51+00:00 [haddock @ 2002-05-29 13:38:51 by simonmar] Document recent changes to markup syntax - - - - - f93641d6 by Simon Marlow at 2002-05-29T15:27:18+00:00 [haddock @ 2002-05-29 15:27:18 by simonmar] Include the instances in abstract data types too - - - - - 613f21e3 by Simon Marlow at 2002-06-03T13:05:58+00:00 [haddock @ 2002-06-03 13:05:57 by simonmar] Allow exporting of individual class methods and record selectors. For these we have to invent the correct type signature, which we do in the simplest possible way (i.e. no context reduction nonsense in the class case). - - - - - 14b36807 by Simon Marlow at 2002-06-03T13:20:00+00:00 [haddock @ 2002-06-03 13:20:00 by simonmar] Fix linking to qualified names again (thanks to Sven Panne for pointing out the bug). - - - - - 95b10eac by Simon Marlow at 2002-06-03T13:46:48+00:00 [haddock @ 2002-06-03 13:46:48 by simonmar] Fix for exporting record selectors from a newtype declaration - - - - - 272f932e by Simon Marlow at 2002-06-03T13:56:38+00:00 [haddock @ 2002-06-03 13:56:38 by simonmar] update to version 0.3 - - - - - 1c0a3bed by Simon Marlow at 2002-06-03T14:05:07+00:00 [haddock @ 2002-06-03 14:05:07 by simonmar] Add changes in version 0.3 - - - - - 145b4626 by Simon Marlow at 2002-06-03T14:12:38+00:00 [haddock @ 2002-06-03 14:12:38 by simonmar] Render class names as proper binders - - - - - 052106b3 by Simon Marlow at 2002-06-03T14:15:10+00:00 [haddock @ 2002-06-03 14:15:10 by simonmar] update, and separate into bugs, features, and cosmetic items. - - - - - 854f4914 by Simon Marlow at 2002-06-03T14:16:13+00:00 [haddock @ 2002-06-03 14:16:13 by simonmar] More test cases - - - - - 466922c8 by Simon Marlow at 2002-06-03T14:16:56+00:00 [haddock @ 2002-06-03 14:16:56 by simonmar] Example from the paper - - - - - 9962a045 by Simon Marlow at 2002-06-03T14:17:49+00:00 [haddock @ 2002-06-03 14:17:49 by simonmar] A debugging version of the style-sheet, which gives some tables coloured backgrounds so we can see what's going on. - - - - - f16b79db by Simon Marlow at 2002-06-03T14:19:46+00:00 [haddock @ 2002-06-03 14:19:46 by simonmar] typo - - - - - 620db27b by Simon Marlow at 2002-06-03T14:48:32+00:00 [haddock @ 2002-06-03 14:48:32 by simonmar] oops, fix markup bugs - - - - - 53fd105c by Simon Marlow at 2002-06-05T09:05:07+00:00 [haddock @ 2002-06-05 09:05:07 by simonmar] Keep foreign imports when there is no export list (bug reported by Sven Panne). - - - - - 6d98989c by Simon Marlow at 2002-06-05T09:12:02+00:00 [haddock @ 2002-06-05 09:12:02 by simonmar] Identifiers in single quotes can be symbol names too (bug reported by Hal Daume). - - - - - 001811e5 by Sven Panne at 2002-06-08T14:03:36+00:00 [haddock @ 2002-06-08 14:03:36 by panne] Tiny workaround for the fact that Haddock currently ignores HsImportSpecs: Let the local_orig_env take precedence. This is no real solution at all, but improves things sometimes, e.g. in my GLUT documentation. :-) - - - - - 504d19c9 by Simon Marlow at 2002-06-11T09:23:25+00:00 [haddock @ 2002-06-11 09:23:25 by simonmar] portability nit - - - - - e13b5af4 by Simon Marlow at 2002-06-20T12:38:07+00:00 [haddock @ 2002-06-20 12:38:07 by simonmar] Empty declaration fixes. - - - - - f467a9b6 by Simon Marlow at 2002-06-20T12:39:02+00:00 [haddock @ 2002-06-20 12:39:01 by simonmar] Add support for a "prologue" - a description for the whole library, placed on the contents page before the module list. - - - - - b8dbfe20 by Simon Marlow at 2002-06-21T12:43:06+00:00 [haddock @ 2002-06-21 12:43:06 by simonmar] When we have a single code block paragraph, don't place it in <pre>..</pre>, just use <tt>..</tt> to avoid generating extra vertical white space in some browsers. - - - - - 4831dbbd by Simon Marlow at 2002-06-21T15:50:42+00:00 [haddock @ 2002-06-21 15:50:42 by simonmar] Add support for reading and writing interface files(!) This turned out to be quite easy, and necessary to get decent hyperlinks between the documentation for separate packages in the libraries. The functionality isn't quite complete yet: for a given package of modules, you'd like to say "the HTML for these modules lives in directory <dir>" (currently they are assumed to be all in the same place). Two new flags: --dump-interface=FILE dump an interface file in FILE --read-interface=FILE read interface from FILE an interface file describes *all* the modules being processed. Only the exported names are kept in the interface: if you re-export a name from a module in another interface the signature won't be copied. This is a compromise to keep the size of the interfaces sensible. Also, I added another useful option: --no-implicit-prelude avoids trying to import the Prelude. Previously this was the default, but now importing the Prelude from elsewhere makes sense if you also read in an interface containing the Prelude module, so Haddock imports the Prelude implicitly according to the Haskell spec. - - - - - d3640a19 by Sven Panne at 2002-06-23T14:54:00+00:00 [haddock @ 2002-06-23 14:54:00 by panne] Make it compile with newer GHCs - - - - - 780c506b by Sven Panne at 2002-06-23T15:44:31+00:00 [haddock @ 2002-06-23 15:44:31 by panne] Cleaned up build root handling and added more docs - - - - - 45290d2e by Simon Marlow at 2002-06-24T14:37:43+00:00 [haddock @ 2002-06-24 14:37:42 by simonmar] When reading an interface, allow a file path offset to be specified which represents the path to the HTML files for the modules specified by that interface. The path may be either relative (to the location of the HTML for this package), or absolute. The syntax is --read-interface=PATH,FILE where PATH is the path to the HTML, and FILE is the filename containing the interface. - - - - - 4e2b9ae6 by Simon Marlow at 2002-07-03T16:01:08+00:00 [haddock @ 2002-07-03 16:01:07 by simonmar] Handle import specs properly, include 'hiding'. Haddock now has a complete implementation of the Haskell module system (more or less; I won't claim it's 100% correct). - - - - - 9a9aa1a8 by Simon Marlow at 2002-07-03T16:18:16+00:00 [haddock @ 2002-07-03 16:18:16 by simonmar] Update - - - - - 560c3026 by Simon Marlow at 2002-07-04T14:56:10+00:00 [haddock @ 2002-07-04 14:56:10 by simonmar] Clean up the code that constructs the exported declarations, and fix a couple of bugs along the way. Now if you import a class hiding one of the methods, then re-export the class, the version in the documentation will correctly have the appropriate method removed. - - - - - 2c26e77d by Simon Marlow at 2002-07-04T15:26:13+00:00 [haddock @ 2002-07-04 15:26:13 by simonmar] More bugfixes to the export handling - - - - - 03e0710d by Simon Marlow at 2002-07-09T10:12:10+00:00 [haddock @ 2002-07-09 10:12:10 by simonmar] Don't require that the list type comes from "Prelude" for it to be treated as special syntax (sometimes it comes from Data.List or maybe even GHC.Base). - - - - - 44f3891a by Simon Marlow at 2002-07-09T10:12:51+00:00 [haddock @ 2002-07-09 10:12:51 by simonmar] commented-out debugging code - - - - - 97280873 by Krasimir Angelov at 2002-07-09T16:33:33+00:00 [haddock @ 2002-07-09 16:33:31 by krasimir] 'Microsoft HTML Help' support - - - - - 3dc04655 by Simon Marlow at 2002-07-10T09:40:56+00:00 [haddock @ 2002-07-10 09:40:56 by simonmar] Fix for rendering of the (->) type constructor, from Ross Paterson. - - - - - c9f149c6 by Simon Marlow at 2002-07-10T10:26:11+00:00 [haddock @ 2002-07-10 10:26:11 by simonmar] Tweaks to the MS Help support: the extra files are now only generated if you ask for them (--ms-help). - - - - - e8acc1e6 by Simon Marlow at 2002-07-10T10:57:10+00:00 [haddock @ 2002-07-10 10:57:10 by simonmar] Document all the new options since 0.3 - - - - - 8bb85544 by Simon Marlow at 2002-07-10T10:58:31+00:00 [haddock @ 2002-07-10 10:58:31 by simonmar] Sort the options a bit - - - - - abc0dd59 by Simon Marlow at 2002-07-15T09:19:38+00:00 [haddock @ 2002-07-15 09:19:38 by simonmar] Fix a bug in mkExportItems when processing a module without an explicit export list. We were placing one copy of a declaration for each binder in the declaration, which for a data type would mean one copy of the whole declaration per constructor or record selector. - - - - - dde65bb9 by Simon Marlow at 2002-07-15T09:54:16+00:00 [haddock @ 2002-07-15 09:54:16 by simonmar] merge rev. 1.35 - - - - - bd7eb8c4 by Simon Marlow at 2002-07-15T10:14:31+00:00 [haddock @ 2002-07-15 10:14:30 by simonmar] Be a bit more liberal in the kind of commenting styles we allow, as suggested by Malcolm Wallace. Mostly this consists of allowing doc comments either side of a separator token. In an export list, a section heading is now allowed before the comma, as well as after it. eg. module M where ( T(..) -- * a section heading , f -- * another section heading , g ) In record fields, doc comments are allowed anywhere (previously a doc-next was allowed only after the comma, and a doc-before was allowed only before the comma). eg. data R = C { -- | describes 'f' f :: Int -- | describes 'g' , g :: Int } - - - - - 8f6dfe34 by Simon Marlow at 2002-07-15T10:21:56+00:00 [haddock @ 2002-07-15 10:21:56 by simonmar] Mention alternative commenting styles. - - - - - fc515bb7 by Simon Marlow at 2002-07-15T16:16:50+00:00 [haddock @ 2002-07-15 16:16:50 by simonmar] Allow multiple sections/subsections before and after a comma in the export list. Also at the same time I made the syntax a little stricter (multiple commas now aren't allowed between export specs). - - - - - 80a97e74 by Simon Marlow at 2002-07-19T09:13:10+00:00 [haddock @ 2002-07-19 09:13:10 by simonmar] Allow special id's ([], (), etc.) to be used in an import declaration. - - - - - a69d7378 by Simon Marlow at 2002-07-19T09:59:02+00:00 [haddock @ 2002-07-19 09:59:02 by simonmar] Allow special id's ([], (), etc.) to be used in an import declarations. - - - - - d205fa60 by Simon Marlow at 2002-07-19T10:00:16+00:00 [haddock @ 2002-07-19 10:00:16 by simonmar] Relax the restrictions which require doc comments to be followed by semi colons - in some cases this isn't necessary. Now you can write module M where { -- | some doc class C where {} } without needing to put a semicolon before the class declaration. - - - - - e9301e14 by Simon Marlow at 2002-07-23T08:24:09+00:00 [haddock @ 2002-07-23 08:24:09 by simonmar] A new TODO list item - - - - - e5d77586 by Simon Marlow at 2002-07-23T08:40:56+00:00 [haddock @ 2002-07-23 08:40:56 by simonmar] - update the acknowledgements - remove the paragraph that described how to use explicit layout with doc comments; it isn't relevant any more. - - - - - 78a94137 by Simon Marlow at 2002-07-23T08:43:02+00:00 [haddock @ 2002-07-23 08:43:02 by simonmar] more tests - - - - - 5c320927 by Simon Marlow at 2002-07-23T08:43:26+00:00 [haddock @ 2002-07-23 08:43:26 by simonmar] Updates for version 0.4 - - - - - 488e99ae by Simon Marlow at 2002-07-23T09:10:46+00:00 [haddock @ 2002-07-23 09:10:46 by simonmar] Fix the %changelog (rpm complained that it wasn't in the right order) - - - - - a77bb373 by Simon Marlow at 2002-07-23T09:12:38+00:00 [haddock @ 2002-07-23 09:12:38 by simonmar] Another item for the TODO list - - - - - f1ec1813 by Simon Marlow at 2002-07-23T10:18:46+00:00 [haddock @ 2002-07-23 10:18:46 by simonmar] Add a version banner when invoked with -v - - - - - 1d44cadf by Simon Marlow at 2002-07-24T09:28:19+00:00 [haddock @ 2002-07-24 09:28:19 by simonmar] Remove ^Ms - - - - - 4d8d5e94 by Simon Marlow at 2002-07-24T09:42:18+00:00 [haddock @ 2002-07-24 09:42:17 by simonmar] Patches to quieten ghc -Wall, from those nice folks at Galois. - - - - - d6edc43e by Simon Marlow at 2002-07-25T14:37:29+00:00 [haddock @ 2002-07-25 14:37:28 by simonmar] Patch to allow simple hyperlinking to an arbitrary location in another module's documentation, from Volker Stolz. Now in a doc comment: #foo# creates <a name="foo"></a> And you can use the form "M\#foo" to hyperlink to the label 'foo' in module 'M'. Note that the backslash is necessary for now. - - - - - b34d18fa by Simon Marlow at 2002-08-02T09:08:22+00:00 [haddock @ 2002-08-02 09:08:22 by simonmar] The <TT> and <PRE> environments seem to use a font that is a little too small in IE. Compensate. (suggestion from Daan Leijen). - - - - - 8106b086 by Simon Marlow at 2002-08-02T09:25:23+00:00 [haddock @ 2002-08-02 09:25:20 by simonmar] Remove <P>..</P> from around list items, to reduce excess whitespace between the items of bulleted and ordered lists. (Suggestion from Daan Leijen). - - - - - c1acff8f by Simon Marlow at 2002-08-05T09:03:49+00:00 [haddock @ 2002-08-05 09:03:49 by simonmar] update - - - - - f968661c by Simon Marlow at 2002-11-11T09:32:57+00:00 [haddock @ 2002-11-11 09:32:57 by simonmar] Fix cut-n-pasto - - - - - 12d02619 by Simon Marlow at 2002-11-13T09:49:46+00:00 [haddock @ 2002-11-13 09:49:46 by simonmar] Small bugfix in the --read-interface option parsing from Brett Letner. - - - - - 30e32d5e by Ross Paterson at 2003-01-16T15:07:57+00:00 [haddock @ 2003-01-16 15:07:57 by ross] Adjust for the new exception libraries (as well as the old ones). - - - - - 871f65df by Sven Panne at 2003-02-20T21:31:40+00:00 [haddock @ 2003-02-20 21:31:40 by panne] * Add varsyms and consyms to index * Exclude empty entries from index - - - - - bc42cc87 by Sven Panne at 2003-02-24T21:26:29+00:00 [haddock @ 2003-02-24 21:26:29 by panne] Don't convert a "newtype" to a single-constructor "data" for non-abstractly exported types, they are quite different regarding strictness/pattern matching. Now a "data" without any constructors is only emitted for an abstractly exported type, regardless if it is actually a "newtype" or a "data". - - - - - 0c2a1d99 by Sven Panne at 2003-03-08T19:02:38+00:00 [haddock @ 2003-03-08 19:02:38 by panne] Fixed some broken/redirected/canonicalized links found by a very picky link checker. - - - - - 25459269 by Sven Panne at 2003-03-09T21:13:43+00:00 [haddock @ 2003-03-09 21:13:43 by panne] Don't append a fragment to non-defining index entries, only documents with a defining occurrence have a name anchor. - - - - - 6be4db86 by Sven Panne at 2003-03-10T21:34:25+00:00 [haddock @ 2003-03-10 21:34:24 by panne] Escape fragments. This fixes e.g. links to operators. - - - - - eb12972c by Ross Paterson at 2003-04-25T10:50:06+00:00 [haddock @ 2003-04-25 10:50:05 by ross] An 80% solution to generating derived instances. A complete solution would duplicate the instance inference logic, but if a type variable occurs as a constructor argument, then we can just propagate the derived class to the variable. But we know nothing of the constraints on any type variables that occur elsewhere. For example, the declarations data Either a b = Left a | Right b deriving (Eq, Ord) data Ptr a = Ptr Addr# deriving (Eq, Ord) newtype IORef a = IORef (STRef RealWorld a) deriving Eq yield the instances (Eq a, Eq b) => Eq (Either a b) (Ord a, Ord b) => Ord (Either a b) Eq (Ptr a) Ord (Ptr a) (??? a) => Eq (IORef a) The last example shows the limits of this local analysis. Note that a type variable may be in both categories: then we know a constraint, but there may be more, or a stronger constraint, e.g. data Tree a = Node a [Tree a] deriving Eq yields (Eq a, ??? a) => Eq (Tree a) - - - - - de886f78 by Simon Marlow at 2003-04-25T11:17:55+00:00 [haddock @ 2003-04-25 11:17:55 by simonmar] Some updates, including moving the derived instance item down to the bottom of the list now that Ross has contributed some code that does the job for common cases. - - - - - 1b52cffd by Simon Marlow at 2003-04-30T14:02:32+00:00 [haddock @ 2003-04-30 14:02:32 by simonmar] When installing on Windows, run cygpath over $(HADDOCKLIB) so that haddock (a mingw program, built by GHC) can understand it. You still need to be in a cygwin environment to run Haddock, because of the shell script wrapper. - - - - - d4f638de by Simon Marlow at 2003-05-06T10:04:47+00:00 [haddock @ 2003-05-06 10:04:47 by simonmar] Catch another case of a paragraph containing just a DocMonospaced that should turn into a DocCodeBlock. - - - - - 4162b2b9 by Simon Marlow at 2003-05-06T10:11:44+00:00 [haddock @ 2003-05-06 10:11:44 by simonmar] Add some more code-block tests. - - - - - 4f5802c8 by Simon Marlow at 2003-05-06T10:14:52+00:00 [haddock @ 2003-05-06 10:14:52 by simonmar] Don't turn a single DocCodeBlock into a DocMonospaced, because that tends to remove the line breaks in the code. - - - - - ef8c45f7 by Simon Marlow at 2003-05-21T15:07:21+00:00 [haddock @ 2003-05-21 15:07:21 by simonmar] Only omit the module contents when there are no section headings at all. - - - - - bcee1e75 by Sigbjorn Finne at 2003-05-30T16:50:45+00:00 [haddock @ 2003-05-30 16:50:45 by sof] cygpath: for now, steer clear of --mixed - - - - - 30567af3 by Sigbjorn Finne at 2003-05-30T17:59:28+00:00 [haddock @ 2003-05-30 17:59:28 by sof] oops, drop test defn from prev commit - - - - - b0856e7d by Simon Marlow at 2003-06-03T09:55:26+00:00 [haddock @ 2003-06-03 09:55:26 by simonmar] Two small fixes to make the output valid HTML 4.01 (transitional). Thanks to Malcolm Wallace for pointing out the problems. - - - - - 70e137ea by Simon Marlow at 2003-07-28T13:30:35+00:00 [haddock @ 2003-07-28 13:30:35 by simonmar] Add tests for a couple of bugs. - - - - - 122bd578 by Simon Marlow at 2003-07-28T13:31:25+00:00 [haddock @ 2003-07-28 13:31:25 by simonmar] Add documentation for anchors. - - - - - 0bd27cb2 by Simon Marlow at 2003-07-28T13:31:46+00:00 [haddock @ 2003-07-28 13:31:46 by simonmar] Update - - - - - 08052d42 by Simon Marlow at 2003-07-28T13:32:12+00:00 [haddock @ 2003-07-28 13:32:12 by simonmar] layout tweak. - - - - - 13942749 by Simon Marlow at 2003-07-28T13:33:03+00:00 [haddock @ 2003-07-28 13:33:03 by simonmar] Differentiate links to types/classes from links to variables/constructors with a prefix ("t:" and "v:" respectively). - - - - - d7f493b9 by Simon Marlow at 2003-07-28T13:35:17+00:00 [haddock @ 2003-07-28 13:35:16 by simonmar] When a module A exports another module's contents via 'module B', then modules which import entities from B re-exported by A should link to B.foo rather than A.foo. See examples/Bug2.hs. - - - - - d94cf705 by Simon Marlow at 2003-07-28T13:36:14+00:00 [haddock @ 2003-07-28 13:36:14 by simonmar] Update to version 0.5 - - - - - dbb776cd by Sven Panne at 2003-07-28T14:02:43+00:00 [haddock @ 2003-07-28 14:02:43 by panne] * Updated to version 0.5 * Automagically generate configure if it is not there - - - - - 6cfeee53 by Simon Marlow at 2003-07-28T14:32:43+00:00 [haddock @ 2003-07-28 14:32:42 by simonmar] Update to avoid using hslibs with GHC >= 5.04 - - - - - a1ce838f by Simon Marlow at 2003-07-28T14:33:37+00:00 [haddock @ 2003-07-28 14:33:37 by simonmar] Update for 0.5 - - - - - c0fe6493 by Simon Marlow at 2003-07-28T14:53:22+00:00 [haddock @ 2003-07-28 14:53:22 by simonmar] Markup fix - - - - - 6ea31596 by Sven Panne at 2003-07-28T16:40:45+00:00 [haddock @ 2003-07-28 16:40:45 by panne] Make it compile with GHC >= 6.01 - - - - - afcd30fc by Simon Marlow at 2003-07-30T15:04:52+00:00 [haddock @ 2003-07-30 15:04:52 by simonmar] Pay attention to import specs when building the the import env, as well as the orig env. This may fix some wrong links in documentation when import specs are being used. - - - - - 17c3137f by Simon Marlow at 2003-07-30T16:05:41+00:00 [haddock @ 2003-07-30 16:05:40 by simonmar] Rename instances based on the import_env for the module in which they are to be displayed. This should give, in many cases, better links for the types and classes mentioned in the instance head. This involves keeping around the import_env in the iface until the end, because instances are not collected up until all the modules have been processed. Fortunately it doesn't seem to affect performance much. Instance heads are now attached to ExportDecls, rather than the HTML backend passing around a separate mapping for instances. This is a cleanup. - - - - - 3d3b5c87 by Sven Panne at 2003-08-04T10:18:24+00:00 [haddock @ 2003-08-04 10:18:24 by panne] Don't print parentheses around one-element contexts - - - - - 9e3f3f2d by Simon Marlow at 2003-08-04T12:59:47+00:00 [haddock @ 2003-08-04 12:59:47 by simonmar] A couple of TODOs. - - - - - e9d8085c by Simon Marlow at 2003-08-05T14:10:31+00:00 [haddock @ 2003-08-05 14:10:31 by simonmar] I'm not sure why, but it seems that the index entries for non-defining occurrences of entities did not have an anchor - the link just pointed to the module. This fixes it. - - - - - ff5c7d6d by Simon Marlow at 2003-08-15T14:42:59+00:00 [haddock @ 2003-08-15 14:42:59 by simonmar] Convert the lexer to Alex, and fix a bug in the process. - - - - - 1aa077bf by Simon Marlow at 2003-08-15T15:00:18+00:00 [haddock @ 2003-08-15 15:00:18 by simonmar] Update - - - - - d3de1e38 by Simon Marlow at 2003-08-15T15:01:03+00:00 [haddock @ 2003-08-15 15:01:03 by simonmar] wibbles - - - - - b40ece3b by Simon Marlow at 2003-08-18T10:04:47+00:00 [haddock @ 2003-08-18 10:04:47 by simonmar] Lex the 'mdo' keyword as 'do'. - - - - - 8f9a1146 by Simon Marlow at 2003-08-18T11:48:24+00:00 [haddock @ 2003-08-18 11:48:24 by simonmar] Two bugs from Sven. - - - - - ea54ebc0 by Simon Marlow at 2003-08-18T11:48:46+00:00 [haddock @ 2003-08-18 11:48:46 by simonmar] Fixes to the new lexer. - - - - - d5f6a4b5 by Simon Marlow at 2003-08-19T09:09:03+00:00 [haddock @ 2003-08-19 09:09:03 by simonmar] Further wibbles to the syntax. - - - - - 6bbdadb7 by Sven Panne at 2003-08-26T18:45:35+00:00 [haddock @ 2003-08-26 18:45:35 by panne] Use autoreconf instead of autoconf - - - - - 32e889cb by Sven Panne at 2003-08-26T19:01:19+00:00 [haddock @ 2003-08-26 19:01:18 by panne] Made option handling a bit more consistent with other tools, in particular: Every program in fptools should output * version info on stdout and terminate successfully when -V or --version * usage info on stdout and terminate successfully when -? or --help * usage info on stderr and terminate unsuccessfully when an unknown option is given. - - - - - 5d156a91 by Sven Panne at 2003-08-26T19:20:55+00:00 [haddock @ 2003-08-26 19:20:55 by panne] Make it *very* clear that we terminate when given a -V/--version flag - - - - - e6577265 by Sven Panne at 2003-08-27T07:50:03+00:00 [haddock @ 2003-08-27 07:50:02 by panne] * Made -D a short option for --dump-interface. * Made -m a short option for --ms-help. * Made -n a short option for --no-implicit-prelude. * Made -c a short option for --css. * Removed DocBook options from executable (they didn't do anything), but mark them as reserved in the docs. Note that the short option for DocBook output is now -S (from SGML) instead of -d. The latter is now a short option for --debug. * The order of the Options in the documentation now matches the order printed by Haddock itself. Note: Although changing the names of options is often a bad idea, I'd really like to make the options for the programs in fptools more consistent and compatible to the ones used in common GNU programs. - - - - - d303ff98 by Simon Marlow at 2003-09-10T08:23:48+00:00 [haddock @ 2003-09-10 08:23:48 by simonmar] Add doc subdir. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 9a70e46a by Simon Marlow at 2003-09-10T08:24:32+00:00 [haddock @ 2003-09-10 08:24:32 by simonmar] Install these files in $(datadir), not $(libdir), since they're architecture independent. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - bbb87e7a by Simon Marlow at 2003-09-10T08:25:31+00:00 [haddock @ 2003-09-10 08:25:31 by simonmar] Haddock's supplementary HTML bits now live in $(datadir), not $(libdir). Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 3587c24b by Simon Marlow at 2003-09-22T10:34:38+00:00 [haddock @ 2003-09-22 10:34:38 by simonmar] Allow installing of docs. - - - - - d510b517 by Sven Panne at 2003-10-11T08:10:44+00:00 [haddock @ 2003-10-11 08:10:44 by panne] Include architecture-independent files in file list - - - - - 187d7618 by Sigbjorn Finne at 2003-10-20T17:19:24+00:00 [haddock @ 2003-10-20 17:19:22 by sof] support for i-parameters + zip comprehensions - - - - - b6c7a273 by Simon Marlow at 2003-11-03T14:24:24+00:00 [haddock @ 2003-11-03 14:24:24 by simonmar] Update TODO file. - - - - - 58513e33 by Simon Marlow at 2003-11-05T11:22:04+00:00 [haddock @ 2003-11-05 11:22:04 by simonmar] Remove the last of the uses of 'trace' to emit warnings, and tidy up a couple of places where duplicate warnings were being emitted. - - - - - 33a78846 by Simon Marlow at 2003-11-05T11:30:53+00:00 [haddock @ 2003-11-05 11:30:52 by simonmar] - Suppress warnings about unknown imported modules by default. - Add a -v/--verbose flag to re-enable these warnings. The general idea is to suppress the "Warning: unknown module: Prelude" warnings which most Haddock users will see every time, and which aren't terribly useful. - - - - - a969de7f by Simon Marlow at 2003-11-05T12:30:28+00:00 [haddock @ 2003-11-05 12:30:28 by simonmar] - Remove the emboldening of index entries for defining locations. This isn't useful, and breaks abstractions. - If an entity is re-exported by a module but the module doesn't include documentation for that entity (perhaps because it is re-exported by 'module M'), then don't attempt to hyperlink to the documentation from the index. Instead, just list that module in the index, to indicate that the entity is exported from there. - - - - - f14ea82a by Simon Marlow at 2003-11-05T15:15:59+00:00 [haddock @ 2003-11-05 15:15:59 by simonmar] Index overhaul: - no more separate type/class and variable/function indices - the index now makes a distinction between different entities with the same name. One example is a type constructor with the same name as a data constructor, but another example is simply a function with the same name exported by two different modules. For example, the index entry for 'catch' now looks like this: catch 1 (Function) Control.Exception 2 (Function) GHC.Exception, Prelude, System.IO, System.IO.Error making it clear that there are two different 'catch'es, but one of them is exported by several modules. - Each index page now has the index contents (A B C ...) at the top. Please let me know if you really hate any of this. - - - - - 01a25ca6 by Simon Marlow at 2003-11-05T15:16:38+00:00 [haddock @ 2003-11-05 15:16:38 by simonmar] Update - - - - - 1a7ccb86 by Simon Marlow at 2003-11-05T17:16:05+00:00 [haddock @ 2003-11-05 17:16:04 by simonmar] Support for generating a single unified index for several packages. --use-index=URL turns off normal index generation, causes Index links to point to URL. --gen-index generates an combined index from the specified interfaces. Currently doesn't work exactly right, because the interfaces don't contain the iface_reexported info. I'll need to fix that up. - - - - - a2bca16d by Simon Marlow at 2003-11-06T10:44:52+00:00 [haddock @ 2003-11-06 10:44:52 by simonmar] Include iface_reexported in the .haddock file. This unfortunately bloats the file (40% for base). If this gets to be a problem we can always apply the dictionary trick that GHC uses for squashing .hi files. - - - - - 0a09c293 by Simon Marlow at 2003-11-06T12:39:47+00:00 [haddock @ 2003-11-06 12:39:46 by simonmar] - Add definition lists, marked up like this: -- | This is a definition list: -- -- [@foo@] The description of @foo at . -- -- [@bar@] The description of @bar at . Cunningly, the [] characters are not treated specially unless a [ is found at the beginning of a paragraph, in which case the ] becomes special in the following text. - Add --use-contents and --gen-contents, along the lines of --use-index and --gen-index added yesterday. Now we can generate a combined index and contents for the whole of the hierarchical libraries, and in theory the index/contents on the system could be updated as new packages are added. - - - - - fe1b3460 by Simon Marlow at 2003-11-06T14:47:36+00:00 [haddock @ 2003-11-06 14:47:36 by simonmar] Remove the 'Parent' button - it is of dubious use, and often points into thin air. - - - - - db6d762f by Simon Marlow at 2003-11-06T16:48:14+00:00 [haddock @ 2003-11-06 16:48:11 by simonmar] - Include the OptHide setting in the interface, so we don't include hidden modules in the combined index/contents. - Add a -k/--package flag to set the package name for the current set of modules. The package name for each module is now shown in the right-hand column of the contents, in a combined contents page. - - - - - 7d71718b by Simon Marlow at 2003-11-06T16:50:28+00:00 [haddock @ 2003-11-06 16:50:28 by simonmar] Add -k/--package docs - - - - - ef43949d by Simon Marlow at 2003-11-06T16:51:23+00:00 [haddock @ 2003-11-06 16:51:23 by simonmar] Bump to 0.6 - - - - - 1c419e06 by Simon Marlow at 2003-11-06T16:51:50+00:00 [haddock @ 2003-11-06 16:51:50 by simonmar] update - - - - - 69422327 by Simon Marlow at 2003-11-10T14:41:06+00:00 [haddock @ 2003-11-10 14:41:05 by simonmar] Re-exporting names from a different package is problematic, because we don't have access to the full documentation for the entity. Currently Haddock just ignores entities with no documentation, but this results in bogus-looking empty documentation for many of the modules in the haskell98 package. So: - the documentation will now just list the name, as a link pointing to the location of the actual documentation. - now we don't attempt to link to these re-exported entities if they are referred to by the current module. Additionally: - If there is no documentation in the current module, include just the Synopsis section (rather than just the documentation section, as it was before). This just looks nicer and was on the TODO list. - - - - - 3c3fc433 by Simon Marlow at 2003-11-10T14:51:59+00:00 [haddock @ 2003-11-10 14:51:59 by simonmar] Fix for getReExports: take into account names which are not visible because they are re-exported from a different package. - - - - - 31c8437b by Simon Marlow at 2003-11-10T15:10:53+00:00 [haddock @ 2003-11-10 15:10:53 by simonmar] Version 0.6 changes - - - - - a7c2430b by Simon Marlow at 2003-11-10T15:15:58+00:00 [haddock @ 2003-11-10 15:15:58 by simonmar] getReExports: one error case that isn't - - - - - 00cc459c by Simon Marlow at 2003-11-10T16:15:19+00:00 [haddock @ 2003-11-10 16:15:18 by simonmar] copyright update - - - - - ca62408d by Simon Marlow at 2003-11-11T09:57:25+00:00 [haddock @ 2003-11-11 09:57:25 by simonmar] Version 0.6 - - - - - 3acbf818 by Simon Marlow at 2003-11-11T12:10:44+00:00 [haddock @ 2003-11-11 12:10:44 by simonmar] Go back to producing just the documentation section, rather than just the synopsis section, for a module with no documentation annotations. One reason is that the synopsis section tries to link each entity to its documentation on the same page. Also, the doc section anchors each entity, and it lists instances which the synopsis doesn't. - - - - - 6c90abc2 by Simon Marlow at 2003-11-12T10:03:39+00:00 [haddock @ 2003-11-12 10:03:39 by simonmar] 2002 -> 2003 - - - - - 090bbc4c by Simon Marlow at 2003-11-28T12:08:00+00:00 [haddock @ 2003-11-28 12:08:00 by simonmar] update - - - - - 8096a832 by Simon Marlow at 2003-11-28T12:09:58+00:00 [haddock @ 2003-11-28 12:09:58 by simonmar] Fix some of the problems with Haddock generating pages that are too wide. Now we only specify 'nowrap' when it is necessary to avoid a code box getting squashed up by the text to the right of it. - - - - - 35294929 by Sven Panne at 2003-12-29T17:16:31+00:00 [haddock @ 2003-12-29 17:16:31 by panne] Updated my email address - - - - - cdb697bf by Simon Marlow at 2004-01-08T10:14:24+00:00 [haddock @ 2004-01-08 10:14:24 by simonmar] Add instructions for using GHC to pre-process source for feeding to Haddock. - - - - - 8dfc491f by Simon Marlow at 2004-01-09T12:45:46+00:00 [haddock @ 2004-01-09 12:45:46 by simonmar] Add -optP-P to example ghc command line. - - - - - ac41b820 by Simon Marlow at 2004-02-03T11:02:03+00:00 [haddock @ 2004-02-03 11:02:03 by simonmar] Fix bug in index generation - - - - - f4e7edcb by Simon Marlow at 2004-02-10T11:51:16+00:00 [haddock @ 2004-02-10 11:51:16 by simonmar] Don't throw away whitespace at the beginning of a line (experimental fix). - - - - - 68e212d2 by Simon Marlow at 2004-02-10T12:10:08+00:00 [haddock @ 2004-02-10 12:10:08 by simonmar] Fix for previous commit: I now realise why the whitespace was stripped from the beginning of the line. Work around it. - - - - - e7d7f2df by Sven Panne at 2004-02-10T18:38:45+00:00 [haddock @ 2004-02-10 18:38:45 by panne] Make Haddock link with the latest relocated monad transformer package - - - - - 992d4225 by Simon Marlow at 2004-02-16T10:21:35+00:00 [haddock @ 2004-02-16 10:21:35 by simonmar] Add a TODO - - - - - 1ac55326 by Simon Marlow at 2004-03-12T11:33:39+00:00 [haddock @ 2004-03-12 11:33:39 by simonmar] Add an item. - - - - - 0478e903 by Simon Marlow at 2004-03-15T12:24:05+00:00 [haddock @ 2004-03-15 12:24:05 by simonmar] Add an item. - - - - - 6f26d21a by Simon Marlow at 2004-03-18T14:21:29+00:00 [haddock @ 2004-03-18 14:21:29 by simonmar] Fix URL - - - - - 19b6bb99 by Simon Marlow at 2004-03-22T14:09:03+00:00 [haddock @ 2004-03-22 14:09:03 by simonmar] getReExports was bogus: we should really look in the import_env to find the documentation for an entity which we are re-exporting without documentation. Suggested by: Ross Paterson (patch modified by me). - - - - - 5c756031 by Simon Marlow at 2004-03-24T09:42:11+00:00 [haddock @ 2004-03-24 09:42:10 by simonmar] hiding bug from Ross Paterson (fixed in rev 1.59 of Main.hs) - - - - - 1b692e6c by Simon Marlow at 2004-03-24T10:10:50+00:00 [haddock @ 2004-03-24 10:10:50 by simonmar] mkExportItems fix & simplification: we should be looking at the actual exported names (calculated earlier) to figure out which subordinates of a declaration are exported. This means that if you export a record, and name its fields separately in the export list, the fields will still be visible in the documentation for the constructor. - - - - - 90e5e294 by Simon Marlow at 2004-03-24T10:12:08+00:00 [haddock @ 2004-03-24 10:12:08 by simonmar] Make restrictCons take into account record field names too (removing a ToDo). - - - - - 2600efa4 by Simon Marlow at 2004-03-24T10:16:17+00:00 [haddock @ 2004-03-24 10:16:17 by simonmar] Record export tests. - - - - - 6a8575c7 by Simon Marlow at 2004-03-25T09:35:14+00:00 [haddock @ 2004-03-25 09:35:14 by simonmar] restrictTo: fix for restricting a newtype with a record field. - - - - - dcf55a8d by Simon Marlow at 2004-03-25T10:01:42+00:00 [haddock @ 2004-03-25 10:01:42 by simonmar] Fix duplicate instance bug - - - - - f49aa758 by Simon Marlow at 2004-03-25T10:02:41+00:00 [haddock @ 2004-03-25 10:02:41 by simonmar] Duplicate instance bug. - - - - - 7b87344c by Simon Marlow at 2004-03-25T10:29:56+00:00 [haddock @ 2004-03-25 10:29:56 by simonmar] If a name is imported from two places, one hidden and one not, choose the unhidden one to link to. Also, when there's only a hidden module to link to, don't try linking to it. - - - - - 40f44d7b by Simon Marlow at 2004-03-25T15:17:24+00:00 [haddock @ 2004-03-25 15:17:23 by simonmar] Add support for collaspible parts of the page, with a +/- button and a bit of JavaScript. Make the instances collapsible, and collapse them by default. This makes documentation with long lists of instances (eg. the Prelude) much easier to read. Maybe we should give other documentation sections the same treatment. - - - - - 9b64dc0f by Simon Marlow at 2004-03-25T15:20:55+00:00 [haddock @ 2004-03-25 15:20:55 by simonmar] Update - - - - - c2fff7f2 by Simon Marlow at 2004-03-25T15:45:10+00:00 [haddock @ 2004-03-25 15:45:10 by simonmar] Eliminate some unnecessary spaces in the HTML rendering - - - - - b7948ff0 by Simon Marlow at 2004-03-25T16:00:37+00:00 [haddock @ 2004-03-25 16:00:36 by simonmar] Remove all that indentation in the generated HTML to keep the file sizes down. - - - - - da2bb4ca by Sven Panne at 2004-03-27T09:57:58+00:00 [haddock @ 2004-03-27 09:57:57 by panne] Added the new-born haddock.js to the build process and the documentation. - - - - - b99e6f8c by Sven Panne at 2004-03-27T10:32:20+00:00 [haddock @ 2004-03-27 10:32:20 by panne] "type" is a required attribute of the "script" element - - - - - 562b185a by Sven Panne at 2004-03-27T12:52:34+00:00 [haddock @ 2004-03-27 12:52:34 by panne] Add a doctype for the contents page, too. - - - - - f6a99c2d by Simon Marlow at 2004-04-14T10:03:25+00:00 [haddock @ 2004-04-14 10:03:25 by simonmar] fix for single-line comment syntax - - - - - de366303 by Simon Marlow at 2004-04-20T13:08:04+00:00 [haddock @ 2004-04-20 13:08:04 by simonmar] Allow a 'type' declaration to include documentation comments. These will be ignored by Haddock, but at least one user (Johannes Waldmann) finds this feature useful, and it's easy to add. - - - - - fd78f51e by Simon Marlow at 2004-05-07T15:14:56+00:00 [haddock @ 2004-05-07 15:14:56 by simonmar] - update copyright - add version to abstract - - - - - 59f53e32 by Sven Panne at 2004-05-09T14:39:53+00:00 [haddock @ 2004-05-09 14:39:53 by panne] Fix the fix for single-line comment syntax, ------------------------------------------- is now a valid comment line again. - - - - - 8b18f2fe by Simon Marlow at 2004-05-10T10:11:51+00:00 [haddock @ 2004-05-10 10:11:51 by simonmar] Update - - - - - 225a491d by Ross Paterson at 2004-05-19T13:10:23+00:00 [haddock @ 2004-05-19 13:10:23 by ross] Make the handling of "deriving" slightly smarter, by ignoring data constructor arguments that are identical to the lhs. Now handles things like data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving ... - - - - - 37588686 by Mike Thomas at 2004-05-21T06:38:14+00:00 [haddock @ 2004-05-21 06:38:14 by mthomas] Windows exe extensions (bin remains for Unix). - - - - - cf2b9152 by Simon Marlow at 2004-05-25T09:34:54+00:00 [haddock @ 2004-05-25 09:34:54 by simonmar] Add some TODO items - - - - - 4d29cdfc by Simon Marlow at 2004-05-25T10:41:46+00:00 [haddock @ 2004-05-25 10:41:46 by simonmar] Complain if -h is used with --gen-index or --gen-contents, because it'll overwrite the new index/contents. - - - - - 2e0771e0 by Mike Thomas at 2004-05-28T20:17:55+00:00 [haddock @ 2004-05-28 20:17:55 by mthomas] Windows: search for templates in executable directory. Unix: Haddock tries cwd first rather than error if no -l arg. - - - - - 8d10bde1 by Sven Panne at 2004-06-05T16:53:34+00:00 [haddock @ 2004-06-05 16:53:34 by panne] Misc. rpm spec file cleanup, including: * make BuildRoot handling more consistent * added default file attributes * consistent defines and tags - - - - - 59974349 by Sven Panne at 2004-06-05T18:01:00+00:00 [haddock @ 2004-06-05 18:01:00 by panne] More rpm spec file cleanup, including: * added some BuildRequires * changed packager to me, so people can complain at the right place :-] * consistently refer to haskell.org instead of www.haskell.org - - - - - b94d4903 by Simon Marlow at 2004-07-01T11:08:58+00:00 [haddock @ 2004-07-01 11:08:57 by simonmar] Update to the +/- buttons: use a resized image rather than a <button>. Still seeing some strange effects in Konqueror, so might need to use a fixed-size image instead. - - - - - d5278f67 by Sven Panne at 2004-07-04T15:15:55+00:00 [haddock @ 2004-07-04 15:15:55 by panne] Install pictures for +/- pictures, too (JPEG is a strange format for graphics like this, I would have expected GIF or PNG here.) Things look fine with Konqueror and Netscape on Linux now, the only downside is that the cursor doesn't change when positioned above the "button". - - - - - 46dec6c5 by Sven Panne at 2004-07-13T17:59:28+00:00 [haddock @ 2004-07-13 17:59:28 by panne] A quote is a valid part of a Haskell identifier, but it would interfere with an ECMA script string delimiter, so escape it there. - - - - - 1d7bc432 by Simon Marlow at 2004-07-22T08:54:06+00:00 [haddock @ 2004-07-22 08:54:06 by simonmar] Add single quote to $ident, so you can say eg. 'foldl'' to refer to foldl' (the longest match rule is our friend). Bug reported by Adrian Hey <ahey at iee.org> - - - - - f183618b by Krasimir Angelov at 2004-07-27T22:59:35+00:00 [haddock @ 2004-07-27 22:58:23 by krasimir] Add basic support for Microsoft HTML Help 2.0 - - - - - d515d0c2 by Krasimir Angelov at 2004-07-27T23:02:36+00:00 [haddock @ 2004-07-27 23:02:36 by krasimir] escape names in the index - - - - - a5f1be23 by Krasimir Angelov at 2004-07-27T23:05:21+00:00 [haddock @ 2004-07-27 23:05:21 by krasimir] Add jsFile, plusFile and minusFile to the file list - - - - - c4fb4881 by Krasimir Angelov at 2004-07-28T22:12:10+00:00 [haddock @ 2004-07-28 22:12:09 by krasimir] bugfix. Move contentsHtmlFile, indexHtmlFile and subIndexHtmlFile functions to HaddockUtil.hs module to make them accessible from HaddockHH2.hs - - - - - 64d30b1d by Krasimir Angelov at 2004-07-30T22:15:47+00:00 [haddock @ 2004-07-30 22:15:45 by krasimir] more stuffs - support for separated compilation of packages - the contents page now uses DHTML TreeView - fixed copyFile bug - - - - - 133c8c5c by Krasimir Angelov at 2004-07-31T12:04:38+00:00 [haddock @ 2004-07-31 12:04:37 by krasimir] make the DHtmlTree in contents page more portable. The +/- buttons are replaced with new images which looks more beatiful. - - - - - 79040963 by Krasimir Angelov at 2004-07-31T13:10:20+00:00 [haddock @ 2004-07-31 13:10:20 by krasimir] Make DHtmlTree compatible with Mozila browser - - - - - 1a55dc90 by Krasimir Angelov at 2004-07-31T14:52:55+00:00 [haddock @ 2004-07-31 14:52:55 by krasimir] fix - - - - - 85ce0237 by Krasimir Angelov at 2004-07-31T14:53:28+00:00 [haddock @ 2004-07-31 14:53:28 by krasimir] HtmlHelp 1.x - - - - - 3c0c53ba by Krasimir Angelov at 2004-07-31T20:35:21+00:00 [haddock @ 2004-07-31 20:35:21 by krasimir] Added support for DevHelp - - - - - d42b5af1 by Krasimir Angelov at 2004-07-31T21:17:51+00:00 [haddock @ 2004-07-31 21:17:51 by krasimir] Document new features in HtmlHelp - - - - - 790fe21e by Krasimir Angelov at 2004-08-01T15:14:02+00:00 [haddock @ 2004-08-01 15:14:02 by krasimir] add missing imports - - - - - fd7cc6bc by Krasimir Angelov at 2004-08-01T19:52:08+00:00 [haddock @ 2004-08-01 19:52:06 by krasimir] fix some bugs. Now I have got the entire libraries documentation in HtmlHelp 2.0 format. - - - - - 94ad7ac8 by Krasimir Angelov at 2004-08-01T19:53:50+00:00 [haddock @ 2004-08-01 19:53:50 by krasimir] I forgot to add the new +/- images - - - - - f0c65388 by Krasimir Angelov at 2004-08-02T16:25:53+00:00 [haddock @ 2004-08-02 16:25:53 by krasimir] Add root node to the table of contents. All modules in tree are not children of the root - - - - - f50bd85d by Sven Panne at 2004-08-02T18:17:46+00:00 [haddock @ 2004-08-02 18:17:46 by panne] Mainly DocBook fixes - - - - - 09527ce3 by Sven Panne at 2004-08-02T20:02:29+00:00 [haddock @ 2004-08-02 20:02:29 by panne] Fixed -o/--odir handling. Generating the output, especially the directory handling, is getting a bit convoluted nowadays... - - - - - c8fbacfa by Sven Panne at 2004-08-02T20:31:13+00:00 [haddock @ 2004-08-02 20:31:13 by panne] Warning police - - - - - 37830bff by Sven Panne at 2004-08-02T20:32:29+00:00 [haddock @ 2004-08-02 20:32:28 by panne] Nuked dead code - - - - - 13847171 by Sven Panne at 2004-08-02T21:12:27+00:00 [haddock @ 2004-08-02 21:12:25 by panne] Use pathJoin instead of low-level list-based manipulation for FilePaths - - - - - c711d61e by Sven Panne at 2004-08-02T21:16:02+00:00 [haddock @ 2004-08-02 21:16:02 by panne] Removed WinDoze CRs - - - - - b1f7dc88 by Sven Panne at 2004-08-03T19:35:59+00:00 [haddock @ 2004-08-03 19:35:59 by panne] Fixed spelling of "http-equiv" attribute - - - - - dd5f394e by Sven Panne at 2004-08-03T19:44:03+00:00 [haddock @ 2004-08-03 19:44:03 by panne] Pacify W3C validator: * Added document encoding (currently UTF-8, not sure if this is completely correct) * Fixed syntax of `id' attributes * Added necessary `alt' attribute for +/- images Small layout improvement: * Added space after +/- images (still not perfect, but better than before) - - - - - 919c47c6 by Sigbjorn Finne at 2004-08-03T19:45:11+00:00 [haddock @ 2004-08-03 19:45:11 by sof] make it compile with <= ghc-6.1 - - - - - 4d6f01d8 by Sigbjorn Finne at 2004-08-03T19:45:30+00:00 [haddock @ 2004-08-03 19:45:30 by sof] ffi wibble - - - - - 4770643a by Sven Panne at 2004-08-03T20:47:46+00:00 [haddock @ 2004-08-03 20:47:46 by panne] Fixed CSS for button style. Note that only "0" is a valid measure without a unit! - - - - - 14aaf2e5 by Sven Panne at 2004-08-03T21:07:59+00:00 [haddock @ 2004-08-03 21:07:58 by panne] Improved spacing of dynamic module tree - - - - - 97c3579a by Simon Marlow at 2004-08-09T11:03:04+00:00 [haddock @ 2004-08-09 11:03:04 by simonmar] Add FormatVersion Patch submitted by: George Russell <ger at informatik.uni-bremen.de> - - - - - af7f8c03 by Simon Marlow at 2004-08-09T11:55:07+00:00 [haddock @ 2004-08-09 11:55:05 by simonmar] Add support for a short description for each module, which is included in the contents. The short description should be given in a "Description: " field of the header. Included in this patch are changes that make the format of the header a little more flexible. From the comments: -- all fields in the header are optional and have the form -- -- [spaces1][field name][spaces] ":" -- [text]"\n" ([spaces2][space][text]"\n" | [spaces]"\n")* -- where each [spaces2] should have [spaces1] as a prefix. -- -- Thus for the key "Description", -- -- > Description : this is a -- > rather long -- > -- > description -- > -- > The module comment starts here -- -- the value will be "this is a .. description" and the rest will begin -- at "The module comment". The header fields must be in the following order: Module, Description, Copyright, License, Maintainer, Stability, Portability. Patches submitted by: George Russell <ger at informatik.uni-bremen.de>, with a few small changes be me, mostly to merge with other recent changes. ToDo: document the module header. - - - - - 7b865ad3 by Simon Marlow at 2004-08-10T14:09:57+00:00 [haddock @ 2004-08-10 14:09:57 by simonmar] Fixes for DevHelp/HtmlHelp following introduction of short module description. - - - - - 814766cd by Simon Marlow at 2004-08-10T14:33:46+00:00 [haddock @ 2004-08-10 14:33:45 by simonmar] Fixes to installation under Windows. - - - - - 39cf9ede by Simon Marlow at 2004-08-12T12:08:23+00:00 [haddock @ 2004-08-12 12:08:23 by simonmar] Avoid using string-gap tricks. - - - - - b6d78551 by Simon Marlow at 2004-08-13T10:53:21+00:00 [haddock @ 2004-08-13 10:53:21 by simonmar] Update - - - - - eaae7417 by Simon Marlow at 2004-08-13T10:53:50+00:00 [haddock @ 2004-08-13 10:53:50 by simonmar] Test for primes in quoted links - - - - - 68c34f06 by Sven Panne at 2004-08-16T19:59:38+00:00 [haddock @ 2004-08-16 19:59:36 by panne] XMLification - - - - - 7f45a6f9 by Sven Panne at 2004-08-18T16:42:54+00:00 [haddock @ 2004-08-18 16:42:54 by panne] Re-added indices + minor fixes - - - - - 8a5dd97c by Sigbjorn Finne at 2004-08-25T17:15:42+00:00 [haddock @ 2004-08-25 17:15:42 by sof] backquote HADDOCK_VERSION defn for <= ghc-6.0.x; believe this is only needed under mingw - - - - - 4b1b42ea by Sven Panne at 2004-08-26T20:08:50+00:00 [haddock @ 2004-08-26 20:08:49 by panne] SGML is dead, long live DocBook XML! Note: The BuildRequires tags in the spec files are still incomplete and the documentation about the DocBook tools needs to be updated, too. Stay tuned... - - - - - 8d52cedb by Sven Panne at 2004-08-26T21:03:19+00:00 [haddock @ 2004-08-26 21:03:19 by panne] Updated BuildRequires tags. Alas, there seems to be no real standard here, so your mileage may vary... At least the current specs should work on SuSE Linux. - - - - - e6982912 by Sigbjorn Finne at 2004-08-30T15:44:59+00:00 [haddock @ 2004-08-30 15:44:59 by sof] escape HADDOCK_VERSION double quotes on all platforms when compiling with <=6.0.x - - - - - b3fbc867 by Simon Marlow at 2004-08-31T13:09:42+00:00 [haddock @ 2004-08-31 13:09:42 by simonmar] Avoid GHC/shell versionitis and create Version.hs - - - - - c359e16a by Sven Panne at 2004-09-05T19:12:33+00:00 [haddock @ 2004-09-05 19:12:32 by panne] * HTML documentation for "foo.xml" goes into directory "foo" again, not "foo-html". This is nicer and consistent with the behaviour for building the docs from SGML. * Disabled building PostScript documentation in the spec files for now, there are some strange issues with the FO->PS conversion for some files which have to be clarified first. - - - - - c68b1eba by Sven Panne at 2004-09-24T07:04:38+00:00 [haddock @ 2004-09-24 07:04:38 by panne] Switched the default state for instances and the module hierarchy to non-collapsed. This can be reversed when we finally use cookies from JavaScript to have a more persistent state. Previously going back and forth in the documentation was simply too annoying because everything was collapsed again and therefore the documentation was not easily navigatable. - - - - - dfb32615 by Simon Marlow at 2004-09-30T08:21:29+00:00 [haddock @ 2004-09-30 08:21:29 by simonmar] Add a feature request - - - - - 45ff783c by Sven Panne at 2004-10-23T19:54:00+00:00 [haddock @ 2004-10-23 19:54:00 by panne] Improved the Cygwin/MinGW chaos a little bit. There is still confusion about host platform vs. target platform... - - - - - 5f644714 by Krasimir Angelov at 2004-10-28T16:01:51+00:00 [haddock @ 2004-10-28 16:01:51 by krasimir] update for ghc-6.3+ - - - - - 92d9753e by Sven Panne at 2004-11-01T16:39:01+00:00 [haddock @ 2004-11-01 16:39:01 by panne] Revert previous commit: It's Network.URI which should be changed, not Haddock. - - - - - 05f70f6e by Simon Marlow at 2005-01-04T16:15:51+00:00 [haddock @ 2005-01-04 16:15:51 by simonmar] parser fix: allow qualified specialids. - - - - - 47870837 by Simon Marlow at 2005-01-04T16:16:54+00:00 [haddock @ 2005-01-04 16:16:54 by simonmar] Add a test - - - - - ff11fc2c by Ross Paterson at 2005-01-10T19:18:22+00:00 [haddock @ 2005-01-10 19:18:22 by ross] Render non-ASCII characters using numeric character references, to simplify charset issues. There's a META tag saying the charset is UTF-8, but GHC outputs characters as raw bytes. Ideally we need an encoding on the input side too, primarily in comments, because source files containing non-ASCII characters aren't portable between locales. - - - - - eba2fc4e by Simon Marlow at 2005-01-11T10:44:37+00:00 [haddock @ 2005-01-11 10:44:37 by simonmar] Remove string gap - - - - - b899a381 by Ross Paterson at 2005-01-13T11:41:33+00:00 [haddock @ 2005-01-13 11:41:33 by ross] recognize SGML-style numeric character references &#ddd; or &#xhhhh; and translate them into Chars. - - - - - 106e3cf0 by Ross Paterson at 2005-01-13T14:43:41+00:00 [haddock @ 2005-01-13 14:43:41 by ross] also allow uppercase X in hexadecimal character references (like SGML) - - - - - e8f54f25 by Ross Paterson at 2005-01-13T14:44:24+00:00 [haddock @ 2005-01-13 14:44:24 by ross] Describe numeric character references. - - - - - 914ccdce by Sven Panne at 2005-01-15T18:44:48+00:00 [haddock @ 2005-01-15 18:44:45 by panne] Make Haddock compile again after the recent base package changed. The Map/Set legacy hell has been factored out, so that all modules can simply use the new non-deprecated interfaces. Probably a lot of things can be improved by a little bit of Map/Set/List algebra, this can be done later if needed. Small note: Currently the list of instances in HTML code is reversed. This will hopefully be fixed later. - - - - - 6ab20e84 by Sven Panne at 2005-01-16T12:18:26+00:00 [haddock @ 2005-01-16 12:18:26 by panne] Trim imports - - - - - efb81da9 by Sven Panne at 2005-01-16T12:58:08+00:00 [haddock @ 2005-01-16 12:58:03 by panne] Correctly handle the new order of arguments for the combining function given to fromListWith. - - - - - e27b5834 by Sven Panne at 2005-01-16T14:14:41+00:00 [haddock @ 2005-01-16 14:14:39 by panne] Data.Map.unions is left-biased. - - - - - dae3cc3e by Sven Panne at 2005-01-16T14:22:44+00:00 [haddock @ 2005-01-16 14:22:44 by panne] Added the last missing "flip" to get identical HTML output as previous versions. - - - - - 951d8408 by Sven Panne at 2005-01-16T14:37:10+00:00 [haddock @ 2005-01-16 14:37:10 by panne] Refactored Text.PrettyPrint legacy hell into a separate module. - - - - - f1c4b892 by Sven Panne at 2005-01-16T15:41:25+00:00 [haddock @ 2005-01-16 15:41:21 by panne] Cleaned up imports and dropped support for GHC < 5.03, it never worked, anyway. - - - - - 60824c6e by Simon Marlow at 2005-01-18T10:02:48+00:00 [haddock @ 2005-01-18 10:02:48 by simonmar] Add a TODO - - - - - a8c82f23 by Krasimir Angelov at 2005-01-28T23:19:39+00:00 [haddock @ 2005-01-28 23:19:39 by krasimir] import Foreign/Foreign.C are required for Windows - - - - - d8450a23 by Simon Marlow at 2005-02-02T16:23:04+00:00 [haddock @ 2005-02-02 16:23:00 by simonmar] Revamp the linking strategy in Haddock. Now name resolution is done in two phases: - first resolve everything to original names, like a Haskell compiler would. - then, figure out the "home" location for every entity, and point all the links to there. The home location is the lowest non-hidden module in the import hierarchy that documents the entity. If there are multiple candidates, one is chosen at random. Also: - Haddock should not generate any HTML with dangling links any more. Unlinked references are just rendered as plain text. - Error reporting is better: if we can't find a link destination for an entity reference, we now emit a warning. - - - - - 1cce71d0 by Simon Marlow at 2005-02-03T13:42:19+00:00 [haddock @ 2005-02-03 13:42:19 by simonmar] - add --ignore-all-exports flag, which behaves as if every module has the ignore-exports attribute (requested by Chris Ryder). - add --hide option to hide a module on the command line. - add --use-package option to get Haddock info for a package from ghc-pkg (largely untested). - remove reexports from the .haddock file, they aren't used any more. - - - - - 767123ef by Ross Paterson at 2005-02-03T16:17:37+00:00 [haddock @ 2005-02-03 16:17:37 by ross] fix typo for < 6.3 - - - - - 0c680c04 by Simon Marlow at 2005-02-04T12:03:31+00:00 [haddock @ 2005-02-04 12:03:31 by simonmar] Fix bug in renameExportItems that meant links in instances weren't being renamed properly. - - - - - ff7abe5f by Simon Marlow at 2005-02-04T12:15:53+00:00 [haddock @ 2005-02-04 12:15:52 by simonmar] Add attribute #not-home, to indicate that the current module should not be considered to be a home module for the each entity it exports, unless there is no other module that exports the entity. - - - - - fc2cfd27 by Simon Marlow at 2005-02-04T12:40:02+00:00 [haddock @ 2005-02-04 12:40:02 by simonmar] Update the documentation w.r.t. home modules and the not-home attribute. - - - - - 26b8ddf7 by Ross Paterson at 2005-02-04T13:36:06+00:00 [haddock @ 2005-02-04 13:36:05 by ross] sort lists of instances by - arity of the type constructors (so higher-kinded instances come first) - name of the class - argument types - - - - - 26bfb19c by Simon Marlow at 2005-02-23T15:57:12+00:00 [haddock @ 2005-02-23 15:57:12 by simonmar] Fix documentation regarding the module attributes. - - - - - 9c3afd02 by Simon Marlow at 2005-02-28T16:18:17+00:00 [haddock @ 2005-02-28 16:18:17 by simonmar] version 0.7 - - - - - a95fd63f by Simon Marlow at 2005-02-28T16:22:08+00:00 [haddock @ 2005-02-28 16:22:08 by simonmar] Attempt to fix the layout of the package names in the contents. Having tried just about everything, the only thing I can get to work reliably is to make the package names line up on a fixed offset from the left margin. This obviously isn't ideal, so anyone else that would like to have a go at improving it is welcome. One option is to remove the +/- buttons from the contents list and go back to a plain table. The contents page now uses CSS for layout rather than tables. It seems that most browsers have different interpretations of CSS layout, so only the simplest things lead to consistent results. - - - - - 905d42f7 by Simon Marlow at 2005-03-01T17:16:42+00:00 [haddock @ 2005-03-01 17:16:40 by simonmar] Another attempt at lining up the package names on the contents page. Now, they line up with Konqueror, and almost line up with Firefox & IE (different layout in each case). - - - - - a0e1d178 by Wolfgang Thaller at 2005-03-09T08:28:39+00:00 [haddock @ 2005-03-09 08:28:39 by wolfgang] Hack haddock's lexer to accept the output from Apple's broken version of cpp (Apple's cpp leaves #pragma set_debug_pwd directives in it's output). - - - - - 9e1eb784 by Simon Marlow at 2005-04-22T14:27:15+00:00 [haddock @ 2005-04-22 14:27:15 by simonmar] Add a TODO item - - - - - 23281f78 by Ross Paterson at 2005-05-18T12:41:59+00:00 [haddock @ 2005-05-18 12:41:59 by ross] fix 3 bugs in --use-package, and document it. - - - - - 00074a68 by Sven Panne at 2005-05-21T12:35:29+00:00 [haddock @ 2005-05-21 12:35:29 by panne] Warning/versionitis police - - - - - 341fa822 by Simon Marlow at 2005-06-15T15:43:21+00:00 [haddock @ 2005-06-15 15:43:21 by simonmar] Allow "licence" as an alternate spelling of "license" - - - - - 3b953f8b by Simon Marlow at 2005-06-16T08:14:12+00:00 [haddock @ 2005-06-16 08:14:12 by simonmar] wibble - - - - - abfd9826 by Simon Marlow at 2005-06-27T14:46:40+00:00 [haddock @ 2005-06-27 14:46:40 by simonmar] name hierarchical HTML files as A-B-C.html instead of A.B.C.html. The old way confused Apache because the extensions are sometimes interpreted as having special meanings. - - - - - a01eea00 by Simon Marlow at 2005-08-04T13:59:40+00:00 [haddock @ 2005-08-04 13:59:40 by simonmar] 0.7 changes - - - - - 170ef87e by Simon Marlow at 2005-08-04T15:08:03+00:00 [haddock @ 2005-08-04 15:08:03 by simonmar] spec file from Jens Peterson - - - - - 7621fde4 by Simon Marlow at 2005-08-04T15:59:30+00:00 [haddock @ 2005-08-04 15:59:30 by simonmar] replace mingw tests with $(Windows) - - - - - a20739bb by Sven Panne at 2005-08-05T07:01:12+00:00 [haddock @ 2005-08-05 07:01:12 by panne] Reverted to previous version (but with bumped version number), the last commit broke RPM building on SuSE systems due to differently named dependencies. As a clarification: All .spec files in the repository have to work at least on SuSE, because that's the system I'm using. And as "Mr. Building Police", I reserve me the right to keep them that way... >:-) It might very well be the case that we need different .spec files for different platforms, so packagers which are unhappy with the current .spec files should contact me, stating the actual problems. - - - - - 4afb15cf by Simon Marlow at 2005-10-05T10:51:45+00:00 [haddock @ 2005-10-05 10:51:45 by simonmar] Add a bug - - - - - 60f69f82 by Simon Marlow at 2005-10-05T12:52:03+00:00 [haddock @ 2005-10-05 12:52:03 by simonmar] Document new behaviour of -s option - - - - - f7e520ca by Simon Marlow at 2005-10-10T15:02:55+00:00 [haddock @ 2005-10-10 15:02:55 by simonmar] extractRecSel: ignore non-record constructors (fixes a crash when using datatypes with a mixture of record and non-record style constructors). - - - - - b2edbedb by Simon Marlow at 2005-10-14T09:44:21+00:00 Start CHANGES for 0.8 - - - - - 21c7ac8d by Simon Marlow at 2005-10-14T23:11:19+00:00 First cut of Cabal build system - - - - - 766cecdd by Simon Marlow at 2005-10-29T08:14:43+00:00 Add configure script and Makefile for the docs Add a separate configure script and build system for building the documentation. The configure and Makefile code is stolen from fptools. This is left as a separate build system so that the main Cabal setup doesn't require a Unix build environment or DocBook XML tools. - - - - - aa36c783 by Duncan Coutts at 2006-01-17T19:29:55+00:00 Add a --wiki=URL flag to add a per-module link to a correspondng wiki page. So each html page gets an extra link (placed next to the source code and contents links) to a corresponding wiki page. The idea is to let readers contribute their own notes, examples etc to the documentation. Also slightly tidy up the code for the --source option. - - - - - e06e2da2 by Simon Marlow at 2006-01-18T09:28:15+00:00 TODO: documnet --wiki - - - - - 17adfda9 by Duncan Coutts at 2006-01-19T20:17:59+00:00 Add an optional wiki link for each top level exported name. In each module, for each "top level" exported entity we add a hyper link to a corresponding wiki page. The link url gets the name of the exported entity as a '#'-style anchor, so if there is an anchor in the page with that name then the users browser should jump directly to it. By "top level" we mean functions, classes, class members and data types (data, type, newtype), but not data constructors, class instances or data type class membership. The link is added at the right of the page and in a small font. Hopefully this is the right balance of visibility/distraction. We also include a link to the wiki base url in the contents and index pages. - - - - - f52324bb by Duncan Coutts at 2006-01-19T20:28:27+00:00 Rewrite pathJoin to only add a path separator when necessary. When the path ends in a file seperator there is no need to add another. Now using "--wiki=http://blah.com/foo/" should do the right thing. (Code snippet adapted from Isaac's FilePath package.) - - - - - 43bb89fa by Duncan Coutts at 2006-01-21T17:15:27+00:00 Teach haddock about line pragmas and add accurate source code links Teach haddock about C and Haskell style line pragmas. Extend the lexer/parser's source location tracking to include the file name as well as line/column. This way each AST item that is tagged with a SrcLoc gets the original file name too. Use this original file name to add source links to each exported item, in the same visual style as the wiki links. Note that the per-export source links are to the defining module rather than whichever module haddock pretends it is exported from. This is what we want for source code links. The source code link URL can also contain the name of the export so one could implement jumping to the actual location of the function in the file if it were linked to an html version of the source rather than just plain text. The name can be selected with the %N wild card. So for linking to the raw source code one might use: --source=http://darcs/haskell.org/foo/%F Or for linking to html syntax highlighted code: --source=http://darcs/haskell.org/foo/%M.html#%N - - - - - edd9f229 by Duncan Coutts at 2006-01-22T00:02:00+00:00 Extend URL variable expansion syntax and add source links to the contents page Like the wiki link on the contents and index page, add a source code link too. Extend the wiki & source URL variable expansion syntax. The original syntax was: %F for the source file name (the .hs version only, not the .lhs or .hs.pp one) %M for the module name (with '.' replaced by '/') The new syntax is: %F or %{FILE} for the original source file name %M or %{MODULE} for the module name (no replacements) %N or %{NAME} for the function/type export name %K or %{KIND} for a type/value flag "t" or "v" with these extensions: %{MODULE/./c} to replace the '.' module seperator with any other char c %{VAR|some text with the % char in it} which means if the VAR is not in use in this URL context then "" else replace the given text with the '%' char replaced by the string value of the VAR. This extension allows us to construct URLs wit optional parts, since the module/file name is not available for the URL in the contents/index pages and the value/type name is not available for the URL at the top level of each module. - - - - - eb3c6ada by Duncan Coutts at 2006-01-23T13:42:34+00:00 Remove the complex substitutions and add more command line flags instead. Instead of incomprehensable URL substitutions like ${MODULE/./-|?m=%} we now use three seperate command line flags for the top level, per-module and per-entity source and wiki links. They are: --source-base, --source-module, --source-entity --comments-base, --comments-module, --comments-entity We leave -s, --source as an alias for --source-module which is how that option behaved previously. The long forms of the substitutions are still available, ${FILE} ${MODULE} etc and the only non-trivial substitution is ${MODULE/./c} to replace the '.' characters in the module name with any other character c. eg ${MODULE/./-} Seperating the source and wiki url flags has the added bonus that they can be turned on or off individually. So users can have per-module links for example without having to also have per-entity links.` - - - - - a2f0f2af by Duncan Coutts at 2006-01-23T13:54:52+00:00 Make the --help output fit in 80 columns. This is a purely cosmetic patch, feel free to ignore it. The only trickery going on is that we don't display the deprecated -s, --source flags in the help message, but we do still accept them. - - - - - 2d3a4b0c by Duncan Coutts at 2006-01-23T14:12:16+00:00 Add documentation for the new --source-* and --comments-* command line options - - - - - 1a82a297 by Simon Marlow at 2006-01-23T17:03:27+00:00 fix markup - - - - - 100d464a by Duncan Coutts at 2006-01-23T18:31:13+00:00 remove a couple TODO items that have been done The --wiki, or rather the --comment-* options are now documented. There is probably no need to have haddock invoke unlit or cpp itself since it can now pick up the line pragmas to get the source locations right. Tools like Cabal will arrange for preprocessors to be run so there is less of a need for tools like haddock to do it themselves. - - - - - 3162fa91 by Simon Marlow at 2006-01-24T14:21:56+00:00 add a test I had lying around - - - - - 98947063 by Simon Marlow at 2006-01-31T13:52:54+00:00 add scabal-version field - - - - - c41876e6 by Neil Mitchell at 2006-02-26T17:48:21+00:00 Add Hoogle output option - - - - - f86fb9c0 by Simon Marlow at 2006-03-08T09:15:20+00:00 add haskell.vim Contributed by Brad Bowman <bsb at bereft.net>, thanks! - - - - - 35d3c511 by benjamin.franksen at 2006-03-03T22:39:54+00:00 fixed libdir (/html was missing) - - - - - 4d08fd7d by Simon Marlow at 2006-03-10T11:13:31+00:00 add PatternGuards extension - - - - - 3f095e70 by Simon Marlow at 2006-03-13T11:40:42+00:00 bug fixes from Brad Bowman - - - - - 8610849d by Sven Panne at 2006-03-19T17:02:56+00:00 Fixed Cabal/RPM build - - - - - 34a994d6 by sven.panne at 2006-04-20T12:39:23+00:00 Avoid pattern guards Due to the use of pattern guards in Haddock, GHC was called with -fglasgow-exts. This in turn enables bang patterns, too, which broke the Haddock build. Removing some unnecessary pattern guards seemed to be the better way of fixing this instead of using a pragma to disable pattern guards. - - - - - bb523f51 by Ross Paterson at 2006-04-24T09:03:25+00:00 extend 'deriving' heuristic a little If an argument of a data constructor has a type variable head, it is irreducible and the same type class can be copied into the constraint. (Formerly we just did this for type variable arguments.) - - - - - dab9fe7a by Simon Marlow at 2006-04-26T10:02:31+00:00 record an idea - - - - - 748b7078 by Simon Marlow at 2006-05-08T08:28:53+00:00 add section about deriving - - - - - 11252ea1 by Simon Marlow at 2006-05-24T15:43:10+00:00 replace a fatal error in lexChar with a parseError - - - - - 382c9411 by Simon Marlow at 2006-05-24T15:45:47+00:00 add a bug - - - - - b79272f5 by Simon Marlow at 2006-05-24T15:46:29+00:00 add a bug report - - - - - 912edf65 by David Waern at 2006-07-10T19:09:23+00:00 Initial modifications -- doesn't compile - - - - - a3c7ba99 by David Waern at 2006-07-11T00:54:19+00:00 More porting work -- doesn't compile - - - - - 0a173d19 by David Waern at 2006-07-11T11:30:03+00:00 Make the repos temporarily compile and illustrate a problem - - - - - bad316de by David Waern at 2006-07-11T15:43:47+00:00 Progress on the porting process - - - - - bbf12d02 by David Waern at 2006-07-11T23:07:44+00:00 More progress on the porting -- first pass starting to shape up - - - - - de580ba2 by David Waern at 2006-07-20T17:48:30+00:00 More progress -- still on phase1 - - - - - 75a917a2 by David Waern at 2006-07-23T18:22:43+00:00 More work on pass1 -- mostly done - - - - - 6697b3f7 by David Waern at 2006-07-23T22:17:40+00:00 More work, started working on the renaming phase -- this code will need a cleanup soon :) - - - - - 82a5bcbb by David Waern at 2006-07-29T16:16:43+00:00 Add instances, build renaming environment, start on the renamer - - - - - c3f8f4f1 by David Waern at 2006-07-29T21:37:48+00:00 Complete the renamer - - - - - 7e00d464 by David Waern at 2006-07-30T21:01:57+00:00 Start porting the Html renderer - - - - - f04ce121 by David Waern at 2006-08-09T20:04:56+00:00 More Html rendering progress - - - - - 20c21b53 by David Waern at 2006-08-10T17:37:47+00:00 More progress - - - - - d7097e0d by David Waern at 2006-08-11T20:31:51+00:00 Cleanup - - - - - a7351e86 by David Waern at 2006-08-12T11:44:47+00:00 Render H98 Data declarations - - - - - 3fb2208e by David Waern at 2006-08-12T17:15:34+00:00 Perfect rendering of Test.hs - - - - - 454fd062 by David Waern at 2006-08-13T21:57:08+00:00 Misc fixes and interface load/save - - - - - 7ef7e7be by David Waern at 2006-08-14T00:56:07+00:00 Some refactoring - - - - - a7d3efef by David Waern at 2006-08-19T20:07:55+00:00 Adapt to latest GHC - - - - - 5fc3c0d7 by David Waern at 2006-08-20T21:28:11+00:00 Move interface read/write to its own module + some cleanup - - - - - 037e011c by David Waern at 2006-08-20T21:38:24+00:00 Small cleanup - - - - - da3a1023 by David Waern at 2006-09-03T16:05:22+00:00 Change mode to BatchCompile to avoid GHC API bug - - - - - 3cc9be3b by David Waern at 2006-09-03T16:06:59+00:00 Starting work on GADT rendering - - - - - 94506037 by David Waern at 2006-09-03T20:02:48+00:00 Compensate for change of export list order in GHC - - - - - c2cec4eb by David Waern at 2006-09-04T20:53:01+00:00 Rename a function - - - - - 9a9735ba by David Waern at 2006-09-05T15:51:21+00:00 Change version number to 2.0 - - - - - 3758a714 by David Waern at 2006-09-05T15:51:49+00:00 Align comment properly - - - - - 68478d9e by David Waern at 2006-09-15T18:03:00+00:00 Remove interface reading/writing code and use the GHC api for creating package environments instead - - - - - d2eedd95 by David Waern at 2006-09-15T18:05:29+00:00 Change the executable name to haddock-ghc-nolib - - - - - fcfbcf66 by David Waern at 2006-09-15T18:05:45+00:00 Small source code cleanup - - - - - d08eb017 by David Waern at 2006-09-15T18:06:21+00:00 Remove handling of --package flag - - - - - b8a4cf53 by David Waern at 2006-09-15T18:07:16+00:00 Remove commented-out code - - - - - bef0a684 by David Waern at 2006-09-15T18:37:57+00:00 Don't warn about missing links to () - - - - - e7d25fd7 by David Waern at 2006-09-15T19:50:49+00:00 Remove Interface and Binary2 modules - - - - - 9894f2a1 by David Waern at 2006-09-15T19:53:43+00:00 Remove debug printing from HaddockHtml - - - - - a0e7455d by David Waern at 2006-09-16T00:16:29+00:00 Comments only - - - - - d5b26fa7 by David Waern at 2006-09-16T00:16:57+00:00 Refactor PackageData creation code and start on building the doc env propery (unfinished) - - - - - 06aaa779 by David Waern at 2006-09-16T00:19:25+00:00 Better comments in Main.hs - - - - - 1a52d1b4 by David Waern at 2006-09-18T22:17:11+00:00 Comments and spacing change - - - - - e5a97767 by David Waern at 2006-09-21T17:02:45+00:00 Remove unnecessary fmapM import in Main - - - - - 9d0f9d3a by David Waern at 2006-09-22T18:07:07+00:00 Make import list in HaddockHtml prettier - - - - - 3452f662 by David Waern at 2006-09-22T18:08:47+00:00 Refactor context rendering - - - - - 12d0a6d0 by David Waern at 2006-09-22T18:09:52+00:00 Do proper HsType rendering (inser parentheses correctly) - - - - - 2c20c2f9 by David Waern at 2006-09-22T18:10:45+00:00 Fix a bug in Main.toHsType - - - - - c5396443 by David Waern at 2006-09-22T18:11:16+00:00 Skip external package modules sort for now - - - - - 3fb95547 by David Waern at 2006-09-22T20:35:40+00:00 Take away trailin "2" on all previously clashing type names - - - - - 2174755f by David Waern at 2006-09-22T20:51:43+00:00 Remove unused imports in Main - - - - - 1e9f7a39 by David Waern at 2006-09-22T20:52:11+00:00 Fix a comment in Main - - - - - 32d9e028 by David Waern at 2006-10-05T16:40:11+00:00 Merge with changes to ghc HEAD - - - - - 3058c8f5 by David Waern at 2006-10-05T16:41:02+00:00 Comment fixes - - - - - b9c217ec by David Waern at 2006-10-05T16:49:59+00:00 Filter out more builtin type constructors from warning messages - - - - - 67e7d252 by David Waern at 2006-10-05T19:38:22+00:00 Refactoring -- better structured pass1 - - - - - cd21c0c1 by David Waern at 2006-10-05T19:44:42+00:00 Remove read/dump interface flags - - - - - 313f9e69 by David Waern at 2006-10-05T19:49:26+00:00 Remove unused pretty printing - - - - - 480f09d1 by David Waern at 2006-12-28T13:22:24+00:00 Update to build with latest GHC HEAD - - - - - 63dccfcb by David Waern at 2007-01-05T01:38:45+00:00 Fixed a bug so that --ghc-flag works correctly - - - - - 3117dadc by David Waern at 2006-12-29T18:53:39+00:00 Automatically get the GHC lib dir - - - - - 9dc84a5c by David Waern at 2006-12-29T19:58:53+00:00 Comments - - - - - 0b0237cc by David Waern at 2007-01-05T16:48:30+00:00 Collect docs based on SrcLoc, syncing with removal of DeclEntity from GHC - - - - - a962c256 by David Waern at 2007-01-05T17:02:47+00:00 Add tabs in haddock.cabal - - - - - 0ca30c97 by David Waern at 2007-01-05T17:04:11+00:00 Add GHCUtils.hs - - - - - c0ab9abe by David Waern at 2007-01-10T11:43:08+00:00 Change package name to haddock-ghc, version 0.1 - - - - - 38e18b27 by David Waern at 2007-01-12T12:03:52+00:00 No binder name for foreign exports - - - - - d18587ab by David Waern at 2007-01-12T12:08:15+00:00 Temp record - - - - - ba6251a0 by David Waern at 2007-01-12T18:27:55+00:00 Remove read/dump-interface (again) - - - - - f4ba2b39 by David Waern at 2007-01-12T18:31:36+00:00 Remove DocOption, use the GHC type - - - - - 511be8bd by David Waern at 2007-01-12T18:32:41+00:00 Use exceptions instead of Either when loading package info - - - - - 0f2144d8 by David Waern at 2007-01-12T18:33:23+00:00 Small type change - - - - - 77507eb7 by David Waern at 2007-01-12T18:33:59+00:00 Remove interface file read/write - - - - - 0ea1e14f by David Waern at 2007-01-17T21:40:26+00:00 Add trace_ppr to GHCUtils - - - - - 3878b493 by David Waern at 2007-01-17T21:40:53+00:00 Sort external package modules and build a doc env - - - - - 8dc323fc by David Waern at 2007-01-17T21:42:41+00:00 Remove comment - - - - - f4c5b097 by David Waern at 2007-01-18T23:22:18+00:00 Add haddock-ghc.cabal and remove ghc option pragma in source file - - - - - da242b2c by David Waern at 2007-01-18T23:22:46+00:00 Remove some tabs - - - - - 288ed096 by David Waern at 2007-01-18T23:39:28+00:00 Moved the defaultErrorHandler to scope only over sortAndCheckModules for now - - - - - 4dd150fe by David Waern at 2007-02-03T21:23:56+00:00 Let restrictCons handle infix constructors - - - - - 97893442 by David Waern at 2007-02-04T16:26:00+00:00 Render infix data constructors - - - - - da89db72 by David Waern at 2007-02-04T16:26:33+00:00 CHange project name to Haddock-GHC - - - - - e93d48af by David Waern at 2007-02-04T16:59:08+00:00 Render infix type constructors properly - - - - - 357bc99b by David Waern at 2007-02-04T17:37:08+00:00 Insert spaces around infix function names - - - - - ab6cfc49 by David Waern at 2007-02-04T17:59:54+00:00 Do not list entities without documentation - - - - - 04249c7e by David Waern at 2007-02-04T19:16:25+00:00 Add GADT support (quite untested) - - - - - 2c223f8d by David Waern at 2007-02-04T19:25:10+00:00 Add package file write/save again! - - - - - b07ed218 by David Waern at 2007-02-04T19:33:02+00:00 Comment out minf_iface based stuff - - - - - 953d1fa7 by David Waern at 2007-02-05T00:12:23+00:00 Solve conflicts - - - - - 593247fc by David Waern at 2007-02-06T19:48:48+00:00 Remove -package flag, GHC's can be used instead - - - - - f658ded2 by David Waern at 2007-02-06T20:50:44+00:00 Start for support of ATs - - - - - 97f9e913 by David Waern at 2007-02-06T20:52:27+00:00 Wibble - - - - - 2ce8e4cf by David Waern at 2007-02-16T12:09:49+00:00 Add the DocOptions change - - - - - dee4a9b5 by David Waern at 2007-03-06T01:24:48+00:00 Wibble - - - - - 7cb99d18 by David Waern at 2007-03-06T01:24:58+00:00 Change version to 2.0 and executable name to haddock - - - - - c5aa02bc by David Waern at 2007-03-08T15:59:49+00:00 Go back to -B flag - - - - - 3a349201 by David Waern at 2007-03-09T13:31:59+00:00 Better exception handling and parsing of GHC flags - - - - - 05a69b71 by David Waern at 2007-03-09T17:45:44+00:00 Remove commented-out DocEntity printing - - - - - 755032cb by davve at dtek.chalmers.se at 2007-03-23T23:30:20+00:00 Remove a file that shouldn't be here - - - - - a7077e5f by davve at dtek.chalmers.se at 2007-03-24T03:58:48+00:00 Remove an import - - - - - 6f55aa8b by davve at dtek.chalmers.se at 2007-03-25T00:46:48+00:00 Start work on Haddock API - - - - - f0199480 by davve at dtek.chalmers.se at 2007-03-25T00:56:36+00:00 Prettify some comments - - - - - f952f9d1 by davve at dtek.chalmers.se at 2007-03-25T00:56:53+00:00 Remove ppr in HaddockTypes - - - - - bc594904 by davve at dtek.chalmers.se at 2007-03-25T00:57:53+00:00 Remove commented out doc env inference - - - - - 11ebf08d by davve at dtek.chalmers.se at 2007-03-25T01:23:25+00:00 De-flatten the namespace - - - - - f696b4bc by davve at dtek.chalmers.se at 2007-03-25T03:21:48+00:00 Add missing stuff to API - - - - - 9a2a04c3 by davve at dtek.chalmers.se at 2007-03-25T03:22:02+00:00 Wibble - - - - - 7d04a6d5 by davve at dtek.chalmers.se at 2007-03-25T03:22:08+00:00 Avoid a GHC bug with parseStaticFlags [] - - - - - 4d2820ba by davve at dtek.chalmers.se at 2007-03-26T04:57:01+00:00 Add fall-through case to mkExportItem - - - - - 6ebc8950 by Stefan O'Rear at 2007-03-26T04:14:53+00:00 Add shebang line to Setup.lhs - - - - - 80966ec5 by davve at dtek.chalmers.se at 2007-03-26T05:24:26+00:00 Fix stupid compile error - - - - - 1ea1385d by davve at dtek.chalmers.se at 2007-04-05T17:19:56+00:00 Do save/read of interface files properly - - - - - 0e4f6541 by David Waern at 2007-04-10T21:08:36+00:00 Add version to ghc dependency - - - - - b0499b63 by David Waern at 2007-04-10T21:37:08+00:00 Change package name to haddock - - - - - 9d50d27e by David Waern at 2007-04-24T00:22:14+00:00 Use filepath package instead of FilePath - - - - - 87c7fcdf by David Waern at 2007-07-10T21:03:04+00:00 Add new package dependencies - - - - - 4768709c by David Waern at 2007-07-11T20:37:11+00:00 Follow changes to record constructor representation - - - - - b9a02fee by Simon Marlow at 2007-05-30T14:00:48+00:00 update to compile with the latest GHC & Cabal - - - - - c0ebdc01 by David Waern at 2007-07-11T21:35:45+00:00 Fix conflicts - - - - - 97f7afd4 by David Waern at 2007-07-11T21:52:38+00:00 Follow changes to the GHC API - - - - - a5b7b58f by David Waern at 2007-07-12T20:36:48+00:00 Call parseStaticFlags before newSession - - - - - f7f50dbc by David Waern at 2007-08-01T21:52:58+00:00 Better indentation in haddock.cabal - - - - - d84e52ad by David Waern at 2007-08-02T00:08:18+00:00 Wibble - - - - - a23f494a by David Waern at 2007-08-02T00:08:24+00:00 Be better at trying to load all module dependencies (debugging) - - - - - ee917f13 by David Waern at 2007-08-03T18:48:08+00:00 Load all targets explicitly (checkModule doesn't chase dependencies anymore) - - - - - 5182d631 by David Waern at 2007-08-16T16:48:55+00:00 Finalize support for links to other packages - - - - - dfd1e3da by David Waern at 2007-08-16T16:51:11+00:00 Fix haddock comment errors in Haddock.Types - - - - - 50c0d83e by David Waern at 2007-08-16T16:51:37+00:00 Remove a debug import - - - - - d84b7c2b by David Waern at 2007-08-16T17:06:30+00:00 Rename PackageData to HaddockPackage - - - - - 3b52cb9f by David Waern at 2007-08-16T17:09:42+00:00 Simplify some comments - - - - - 66fa68d9 by David Waern at 2007-08-16T17:11:38+00:00 Comment the HaddockPackage definition - - - - - 8674c761 by David Waern at 2007-08-16T17:25:54+00:00 Improve code layout in Main - - - - - 571a3a0b by David Waern at 2007-08-16T17:32:13+00:00 Remove explict module imports in Main - - - - - d31b3cb0 by David Waern at 2007-08-16T17:36:23+00:00 Correct comments - - - - - 7f8a9f2b by David Waern at 2007-08-16T17:39:50+00:00 Fix layout problems in Haddock.Types - - - - - 9f421d7f by David Waern at 2007-08-17T11:16:48+00:00 Move options out of Main into Haddock.Options - - - - - 80042b63 by David Waern at 2007-08-17T11:26:59+00:00 Small comment/layout fixes - - - - - b141b982 by David Waern at 2007-08-17T11:28:28+00:00 Change project name from Haddock-GHC to Haddock - - - - - dbeb4a81 by David Waern at 2007-08-17T11:41:05+00:00 Add top module comment to all files - - - - - ce99cc9e by David Waern at 2007-08-17T14:53:04+00:00 Factor out typechecking phase into Haddock.Typecheck - - - - - 6bf75d9e by David Waern at 2007-08-17T16:55:35+00:00 Factor out package code to Haddock.Packages - - - - - b396db37 by David Waern at 2007-08-29T22:40:23+00:00 Major refactoring - - - - - 3d4f95ee by David Waern at 2007-08-29T23:26:24+00:00 Rename HaddockModule to Interface and a few more refactorings - - - - - c55326db by David Waern at 2007-08-29T23:48:03+00:00 Some comment cleanup - - - - - 9a84fc46 by David Waern at 2007-08-29T23:49:29+00:00 Add some modules that I forgot to add earlier - - - - - 4536dce2 by David Waern at 2007-08-29T23:55:24+00:00 Wibble - - - - - 9b7f0206 by David Waern at 2007-08-30T16:03:29+00:00 Wibble - - - - - c52c050a by David Waern at 2007-08-30T16:30:37+00:00 Rename HaddockModule to Interface - - - - - eae2995f by David Waern at 2007-08-30T16:42:59+00:00 Simplify createInterfaces - - - - - 53f99caa by David Waern at 2007-09-29T00:04:31+00:00 Add build-type: Simple to the cabal file - - - - - 0d3103a8 by David Waern at 2007-09-29T00:04:58+00:00 Add containers and array dependency - - - - - 6acf5f30 by David Waern at 2007-09-29T00:13:36+00:00 Prettify the cabal file - - - - - 87c1e378 by David Waern at 2007-09-29T13:16:39+00:00 FIX: consym data headers with more than two variables - - - - - b67fc16a by David Waern at 2007-09-29T14:01:32+00:00 FIX: prefix types used as operators should be quoted - - - - - a8f925bc by David Waern at 2007-09-29T14:02:26+00:00 Use isSymOcc from OccName instead of isConSym - - - - - fc330701 by David Waern at 2007-09-29T14:15:37+00:00 Use isLexConSym/isLexVarSym from OccName - - - - - e4f3dbad by David Waern at 2007-09-29T15:01:08+00:00 FIX: do not quote varsym type operators - - - - - 402207d2 by David Waern at 2007-09-29T15:01:50+00:00 Wibble - - - - - f9d89ef0 by David Waern at 2007-09-29T15:17:40+00:00 Take care when pp tyvars - add parens on syms - - - - - 849e2a77 by David Waern at 2007-10-01T21:56:39+00:00 Go back to using a ModuleMap instead of LookupMod - fixes a bug - - - - - 549dbac6 by David Waern at 2007-10-02T01:05:19+00:00 Improve parsing of doc options - - - - - a36021b8 by David Waern at 2007-10-02T23:05:00+00:00 FIX: double arrows in constructor contexts - - - - - d03bf347 by David Waern at 2007-10-09T16:14:05+00:00 Add a simple test suite - - - - - c252c140 by David Waern at 2007-10-17T16:02:28+00:00 Add --optghc=.. style flag passing to GHC - - - - - cce6c1b3 by David Waern at 2007-10-18T22:03:20+00:00 Add support for --read-interface again - - - - - 33d059c0 by David Waern at 2007-10-18T22:30:18+00:00 Refactoring -- get rid of Haddock.Packages - - - - - f9ed0a4c by David Waern at 2007-10-18T22:34:36+00:00 Name changes - - - - - 8a1c816f by David Waern at 2007-10-20T14:24:23+00:00 Add --ghc-version option - - - - - 4925aaa1 by David Waern at 2007-10-21T14:34:26+00:00 Add some Outputable utils - - - - - 69e7e47f by David Waern at 2007-10-21T14:35:49+00:00 FIX: Ord for OrdName was not comparing modules - - - - - 5a4ae535 by David Waern at 2007-10-21T21:18:48+00:00 Wibble - - - - - 03d48e20 by David Waern at 2007-10-24T15:52:56+00:00 Remove Main from "other modules" - - - - - c66f6d82 by David Waern at 2007-10-24T16:37:18+00:00 Make it possible to run haddock on itself - - - - - 21d156d8 by David Waern at 2007-10-25T14:02:14+00:00 Don't set boot modules as targets - - - - - f8bcf91c by David Waern at 2007-10-31T22:11:17+00:00 Add optimisation flags - - - - - 7ac758f2 by David Waern at 2007-11-04T09:48:28+00:00 Go back to loading only targets (seems to work now) - - - - - 4862aae1 by David Waern at 2007-11-05T22:24:57+00:00 Do full compilation of modules -- temporary fix for GHC API problem - - - - - 697e1517 by David Waern at 2007-11-05T22:25:50+00:00 Don't warn about not being able to link to wired/system/builtin-names - - - - - 892186da by David Waern at 2007-11-06T00:49:21+00:00 Filter out instances with TyCons that are not exported - - - - - 9548314c by David Waern at 2007-11-06T09:37:14+00:00 Wibble - - - - - 5cafd627 by David Waern at 2007-11-08T01:43:07+00:00 Filter out all non-vanilla type sigs - - - - - 04621830 by David Waern at 2007-11-08T01:45:13+00:00 Synch loading of names from .haddock files with GHC's name cache - - - - - 88d37f77 by David Waern at 2007-11-08T01:46:21+00:00 Remove commented-out code - - - - - 6409c911 by David Waern at 2007-11-08T01:56:00+00:00 Small bugfix and cleanup in getDeclFromTyCls - - - - - af59d9c2 by David Waern at 2007-11-08T02:08:44+00:00 Remove OrdName stuff - - - - - 3a615e2e by David Waern at 2007-11-08T02:13:41+00:00 Update runtests.hs following changes to haddock - - - - - 01f3314e by David Waern at 2007-11-08T02:33:01+00:00 Complain if we can't link to wired-in names - - - - - fcafb5d1 by David Waern at 2007-11-09T02:40:16+00:00 Don't exit when there are no file arguments - - - - - 194bc332 by David Waern at 2007-11-09T02:55:37+00:00 Wibble - - - - - dbe4cb55 by David Waern at 2007-11-09T02:56:14+00:00 Wibble - - - - - 82869fda by David Waern at 2007-11-10T17:01:43+00:00 Introduce InstalledInterface structure and add more stuff to the .haddock files We introduce InstalledInterface capturing the part of Interface that is stored in the interface files. We change the ppHtmlContents and ppHtmllIndex to take this structure instead of a partial Interface. We add stuff like the doc map and exported names to the .haddock file (via InstalledInterface). - - - - - d6bb57bf by David Waern at 2007-11-10T17:19:48+00:00 FIX: contents and index should include external package modules when --gen-contents/--gen-index - - - - - e8814716 by David Waern at 2007-11-11T00:29:27+00:00 Remove lDocLinkName and its use in Html backend - - - - - 6f9bd702 by David Waern at 2007-11-11T00:50:57+00:00 Do some refactoring in the html backend This also merges an old patch by Augustsson: Wed Jul 12 19:54:36 CEST 2006 lennart.augustsson at credit-suisse.com * Print type definitions like signatures if given arrows. - - - - - 09d0ce24 by Malcolm.Wallace at 2006-07-20T13:13:57+00:00 mention HsColour in the docs, next to option flags for linking to source code - - - - - 24da6c34 by Malcolm.Wallace at 2006-07-20T13:14:50+00:00 change doc references to CVS to give darcs repository location instead - - - - - 74d52cd6 by David Waern at 2007-11-11T00:55:33+00:00 Update copyright - - - - - fcaa3b4f by Duncan Coutts at 2006-09-08T13:41:00+00:00 Eliminate dep on network by doing a little cut'n'paste haddock depending on the network causes a circular dependency at least if you want to build the network lib with haddock docs. - - - - - 10cc9bda by David Waern at 2007-11-11T02:09:41+00:00 Fix conflicts - - - - - 4e3acd39 by David Waern at 2007-11-11T02:21:19+00:00 Manual merge of a patch from Duncan Coutts that removes the dependency on mtl - - - - - fa9070da by Neil Mitchell at 2006-09-29T15:52:03+00:00 Do not generate an empty table if there are no exports, this fixes a <table></table> tag being generated, which is not valid HTML 4.01 - - - - - d7431c85 by David Waern at 2007-11-11T02:28:50+00:00 Fix conflicts - - - - - f87e8f98 by Simon Marlow at 2006-10-10T11:37:16+00:00 changes for 0.8 - - - - - db929565 by Simon Marlow at 2006-10-10T12:07:12+00:00 fix the name of the source file - - - - - 8220aa4b by Simon Marlow at 2006-10-11T14:17:37+00:00 Rename haddock.js to haddock-util.js haddock.js will be run automatically by Windows when you type 'haddock' if it is found on the PATH, so rename to avoid confusion. Spotted by Adrian Hey. - - - - - 6bccdaa1 by sven.panne at 2006-10-12T15:28:23+00:00 Cabal's sdist does not generate "-src.tar.gz" files, but ".tar.gz" ones - - - - - d3f3fc19 by Simon Marlow at 2006-12-06T16:05:07+00:00 add todo item for --maintainer - - - - - 2da7e269 by Simon Marlow at 2006-12-15T15:52:00+00:00 TODO: do something better about re-exported symbols from another package - - - - - 42d85549 by David Waern at 2007-11-11T02:30:59+00:00 Fix conflicts - - - - - 5e7ef6e5 by Neil Mitchell at 2007-01-11T15:41:15+00:00 Never do spliting index files into many - - - - - f3d4aebe by Neil Mitchell at 2007-01-11T17:07:09+00:00 Add searching on the index page - - - - - bad3ab66 by Neil Mitchell at 2007-01-11T18:17:46+00:00 Delete dead code, now there is only one index page - - - - - cd09eedb by Neil Mitchell at 2007-01-11T18:21:19+00:00 Delete more stuff that is no longer required - - - - - e2806646 by David Waern at 2007-11-11T02:41:53+00:00 Fix conflicts - - - - - a872a823 by Neil Mitchell at 2007-01-11T18:51:43+00:00 Make the index be in case-insensitive alphabetic order - - - - - 8bddd9d7 by Neil Mitchell at 2007-02-06T17:49:12+00:00 Do not create empty tables for data declarations which don't have any constructors, instances or comments. Gets better HTML 4.01 compliance - - - - - 036b8120 by David Waern at 2007-11-11T02:56:58+00:00 Fix conflicts - - - - - f50c1639 by Conal Elliott at 2007-02-14T21:54:00+00:00 added substitution %{FILE///c} - - - - - 402e166a by David Waern at 2007-11-11T03:35:46+00:00 Manual merge of old patch: Sat Apr 21 04:36:43 CEST 2007 Roberto Zunino <zunrob at users.sf.net> * URL expansion for %%, %L, %{LINE} - - - - - 2f264fbd by David Waern at 2007-11-11T03:40:33+00:00 Manual merge of an old patch: Thu Apr 19 20:23:40 CEST 2007 Wolfgang Jeltsch <g9ks157k at acme.softbase.org> * bug fix When Haddock was invoked with the --ignore-all-exports flag but the ignore-exports module attribute wasn't used, hyperlinks weren't created for non-exported names. This fix might not be as clean as one would wish (since --ignore-all-exports now results in ignore_all_exports = True *and* an additional OptIgnoreExports option for every module) but at least the bug seems to be resolved now. - - - - - 7d7ae106 by sven.panne at 2007-09-02T12:18:02+00:00 Install LICENSE in the correct place - - - - - 66eaa924 by David Waern at 2007-11-11T19:02:46+00:00 Fix a bug that made haddock loop - - - - - 4ed47b58 by David Waern at 2007-11-11T19:03:09+00:00 Rename java-script file (this wasn't merge correctly) - - - - - d569534a by David Waern at 2007-11-11T19:06:44+00:00 Don't require -B <ghc-libdir> when no argument files Change readInterfaceFile to take a Maybe Session, to avoid having to pass -B <ghc-libdir> to Haddock when there're no source files to process. This is nice when computing contents/index for external packages. - - - - - 373368bc by Neil Mitchell at 2007-01-11T18:22:44+00:00 Change from tabs to spaces in the ppHtmlIndex function - - - - - 6b063a77 by Neil Mitchell at 2007-01-12T12:17:46+00:00 Rewrite much of the index searching code, previously was too slow to execute on the base library with IE, the new version guarantees less than O(log n) operations be performed, where n is the number in the list (before was always O(n)) - - - - - bfad00b7 by David Waern at 2007-11-11T23:33:53+00:00 Fix conflicts - - - - - cd2dcc09 by Neil Mitchell at 2007-01-12T12:25:01+00:00 Make the max number of results 75 instead of 50, to allow map searching in the base library to work - - - - - 3ae74764 by Neil Mitchell at 2007-01-12T12:58:17+00:00 Make the search box in a form so that enter does the default search - - - - - 142103e5 by David Waern at 2007-11-12T00:03:18+00:00 Merge patch from the old branch: Fri Aug 31 13:21:45 CEST 2007 Duncan Coutts <duncan at haskell.org> * Add category: Development to .cabal file Otherwise it appears on the hackage website in the "Unclassified" category. - - - - - 22ec2ddb by David Waern at 2007-11-25T01:55:29+00:00 A a list of small improvements to the TODO file - - - - - eb0129f4 by Wolfgang Jeltsch at 2007-12-03T23:47:55+00:00 addition of type equality support (at least for HTML generation) - - - - - 816a7e22 by David Waern at 2007-12-08T15:46:26+00:00 Handle class operators correctly when rendering predicates - - - - - 68baaad2 by David Waern at 2007-12-08T16:15:54+00:00 Code layout changes - - - - - 09b77fb4 by David Waern at 2007-12-08T16:16:03+00:00 Handle infix operators correctly in the Type -> HsType translation - - - - - 31c36da2 by David Waern at 2007-12-08T16:24:27+00:00 Add ppLParendTypes/ppLParendType - - - - - b17cc818 by David Waern at 2007-12-08T16:26:12+00:00 Use ppParendType when printing types args in predicates - - - - - ffd1f2cf by David Waern at 2007-12-08T16:45:06+00:00 Fix rendering of instance heads to handle infix operators This is also a refactoring to share this code for rendering predicates. - - - - - ff886d45 by David Waern at 2007-12-08T17:27:46+00:00 Fix rendering of class operators - - - - - e2fcbb9e by David Waern at 2007-12-08T17:59:28+00:00 Fix a bug (use ppTyName instead of ppName to print names in type apps) - - - - - 79a1056e by David Waern at 2007-12-08T21:25:18+00:00 Update tests - - - - - 867741ac by David Waern at 2007-12-08T21:25:49+00:00 Give a diff on test failure - - - - - 7e5eb274 by David Waern at 2008-01-05T14:33:45+00:00 Add DrIFT commands - - - - - 3656454d by David Waern at 2008-01-05T20:26:00+00:00 Add "cabal-version: >= 1.2" to the cabal file - - - - - 77974efc by Simon Marlow at 2007-12-20T09:52:44+00:00 add an item - - - - - f6ac1708 by Simon Marlow at 2007-12-06T14:00:10+00:00 Source links must point to the original module, not the referring module - - - - - eda1d5c9 by David Waern at 2008-01-06T14:40:52+00:00 Manual merge of a patch to the 0.8 branch Thu Dec 6 15:00:10 CET 2007 Simon Marlow <simonmar at microsoft.com> * Source links must point to the original module, not the referring module - - - - - 378f4085 by David Waern at 2008-01-06T16:03:45+00:00 Change stability from stable to experimental - - - - - 8bdafe44 by David Waern at 2008-01-06T16:14:22+00:00 Add haskell.vim (it had been removed somehow) - - - - - ea34d02e by David Waern at 2008-01-06T16:36:57+00:00 Change version to 2.0.0.0 - - - - - 34631ac0 by David Waern at 2008-01-06T16:44:57+00:00 Add missing modules to the cabal file - - - - - 9e142935 by David Waern at 2008-01-06T17:25:42+00:00 Depend on ghc >= 6.8.2 && < 6.9 - - - - - 59f9eeaa by Simon Marlow at 2007-12-20T10:43:04+00:00 add build scripts - - - - - 1c29ae30 by Simon Marlow at 2007-12-20T10:47:07+00:00 update version number - - - - - fe16a3e4 by Simon Marlow at 2007-12-20T10:48:03+00:00 update version - - - - - f688530f by Simon Marlow at 2007-12-20T10:48:29+00:00 doc updates - - - - - ce71b611 by David Waern at 2008-01-07T13:46:32+00:00 Change version in docs and spec - - - - - 03ab8d6f by David Waern at 2008-01-07T13:47:38+00:00 Manually merge over changes to CHANGES for 0.9 - - - - - 39f1b042 by David Waern at 2008-01-07T15:17:41+00:00 Remove the -use-package flag, we don't support it anyway - - - - - 7274a544 by David Waern at 2008-01-07T15:33:05+00:00 Update CHANGES for 2.0.0.0 - - - - - 96594f5d by David Waern at 2008-01-07T15:46:49+00:00 Wibble - - - - - f4c5a4c4 by David Waern at 2008-01-07T15:55:36+00:00 Change url to repo in documentation - - - - - 8a4c77f0 by David Waern at 2008-01-07T16:00:54+00:00 Update CHANGES - - - - - cb3a9288 by David Waern at 2008-01-07T16:02:55+00:00 Documentation fix - - - - - d8e45539 by David Waern at 2008-01-07T16:12:00+00:00 Update docs to say that Haddock accets .lhs files and module names - - - - - 4b5ce824 by David Waern at 2008-01-07T16:12:25+00:00 Document -B option - - - - - 47274262 by David Waern at 2008-01-07T16:23:07+00:00 Update CHANGES - - - - - 7ff314a9 by David Waern at 2008-01-07T16:23:20+00:00 Remove --use-package, --package & --no-implicit.. flags from docs - - - - - 6c3819c0 by David Waern at 2008-01-07T16:23:52+00:00 Remove --no-implicit-prelide flag - - - - - 1b14ae40 by David Waern at 2008-01-07T16:32:26+00:00 Update the "Using literate or pre-processed source" section - - - - - 0117f620 by David Waern at 2008-01-07T16:41:55+00:00 Document the --optghc flag - - - - - 087ab1cf by David Waern at 2008-01-07T16:42:10+00:00 Remove the documenation section on derived instances The problem mentioned there doesn't exist in Haddock 2.0.0.0 - - - - - 7253951e by David Waern at 2008-01-07T16:48:40+00:00 Document OPTIONS_HADDOCK - - - - - 3b6bdcf6 by David Waern at 2008-01-07T16:56:54+00:00 Wibble - - - - - 3025adf9 by David Waern at 2008-01-07T17:08:14+00:00 Wibble - - - - - 5f30f1a0 by David Waern at 2008-01-07T17:15:44+00:00 Change synopsis field to description - - - - - 1673f54b by David Waern at 2008-01-07T17:18:21+00:00 Change my email address in the cabal file - - - - - 55aa9808 by David Waern at 2008-01-07T18:18:02+00:00 Add documentation for readInterfaceFile - - - - - eaea417f by David Waern at 2008-01-07T18:21:30+00:00 Export necessary stuff from Distribution.Haddock - - - - - 7ea18759 by David Waern at 2008-01-07T18:31:49+00:00 Remove dep on Cabal - - - - - 7b79c74e by David Waern at 2008-01-07T18:33:49+00:00 Remove dep on process - - - - - ce3054e6 by David Waern at 2008-01-16T23:01:21+00:00 Add feature-requsts from Henning Thielemann to TODO - - - - - 0c08f1ec by David Waern at 2008-01-16T23:03:02+00:00 Record a bug in TODO - - - - - b04605f3 by David Waern at 2008-01-23T16:59:06+00:00 Add a bug reported by Ross to TODO - - - - - 5b17c030 by David Waern at 2008-01-23T18:05:53+00:00 A a bug report to TODO - - - - - 1c993b0d by David Waern at 2008-01-25T16:30:25+00:00 Accept test output - - - - - c22fc0d0 by David Waern at 2008-01-25T16:34:49+00:00 Accept test output - - - - - 4b795811 by David Waern at 2008-01-25T16:38:37+00:00 Change Hidden.hs (test) to use OPTIONS_HADDOCK - - - - - c124dbd9 by David Waern at 2008-01-25T16:39:23+00:00 Accept test output - - - - - ec6f6eea by David Waern at 2008-01-25T16:42:08+00:00 Add Hidden.html.ref to tests - - - - - 1dc9610c by David Waern at 2008-02-02T20:50:51+00:00 Add a comment about UNPACK bug in TODO - - - - - 2d3f7081 by David Waern at 2008-02-09T22:33:24+00:00 Change the representation of DocNames Ross Paterson reported a bug where links would point to the defining module instead of the "best" module for an identifier (e.g Int pointing to GHC.Base instead of Data.Int). This patch fixes this problem by refactoring the way renamed names are represented. Instead of representing them by: > data DocName = Link Name | NoLink Name they are now represented as such: > data DocName = Documented Name Module | Undocumented Name and the the link-env looks like this: > type LinkEnv = Map Name Module There are several reasons for this. First of all, the bug was caused by changing the module part of Names during the renaming process, without changing the Unique field. This caused names to be overwritten during the loading of .haddock files (which caches names using the NameCache of the GHC session). So we might create new Uniques during renaming to fix this (but I'm not sure that would be problem-free). Instead, we just keep the Name and add the Module where the name is best documented, since it can be useful to keep the original Name around (for e.g. source-code location info and for users of the Haddock API). Also, the names Link/NoLink don't really make sense, since wether to use links or not is entirely up to the users of DocName. In the process of following this change into H.Backends.Html I removed the assumption that binder names are Undocumented (which was just an unnecessary assumption, the OccName is the only thing needed to render these). This will probably make it possible to get rid of the renamer and replace it with a traversal from SYB or Uniplate. Since DocName has changed, InterfaceFile has changed so this patch also increments the file-format version. No backwards-compatibility is implemented. - - - - - 0f28c921 by David Waern at 2008-02-09T23:00:36+00:00 H.GHC.Utils: remove unused imports/exports - - - - - 0c44cad5 by David Waern at 2008-02-10T00:28:13+00:00 H.GHC.Utils: add some functions that were removed by mistake - - - - - e3452f49 by David Waern at 2008-02-10T00:28:48+00:00 Fix some trivial warnings in H.InterfaceFile - - - - - a6d74644 by David Waern at 2008-02-10T00:48:06+00:00 Update the version message to fit in small terminals - - - - - 76c9cd3e by David Waern at 2008-02-10T14:47:39+00:00 Remove bugs from TODO that don't apply anymore since the port - - - - - 5e10e090 by David Waern at 2008-02-10T15:22:47+00:00 Remove bugs from TODO that weren't actual bugs - - - - - fef70878 by David Waern at 2008-02-10T15:23:44+00:00 Remove yet another item from TODO that was not an actual bug - - - - - e1af47b8 by David Waern at 2008-02-11T10:25:57+00:00 Bump the version number to 2.1.0 Since the exported datatype DocName has changed, we need to bump the major version number. Let's also drop the fourth version component, it's not that useful. - - - - - e3be7825 by David Waern at 2008-04-11T14:29:04+00:00 Add a bug to TODO - - - - - cb6574be by David Waern at 2008-04-11T16:00:45+00:00 Use the in-place haddock when running tests - - - - - c6d7af0d by David Waern at 2008-04-11T16:09:16+00:00 Turn off GHC warnings when running tests - - - - - 7f61b546 by David Waern at 2008-04-11T17:24:00+00:00 Add a flag for turning off all warnings - - - - - 883b8422 by David Waern at 2008-04-12T14:02:18+00:00 Fix printing of data binders - - - - - 2a0db8fc by David Waern at 2008-04-12T18:52:46+00:00 Fix missing parenthesis in constructor args bug - - - - - 1b3ac3f9 by David Waern at 2008-04-12T18:57:23+00:00 Simplify test suite and add tests I move all tests into one single directory to simplify things, and add a test for the last bug that was fixed. - - - - - 8f178376 by David Waern at 2008-04-12T19:00:15+00:00 Add a script for copying test output to "expected" output - - - - - 193e3a03 by David Waern at 2008-04-12T19:16:37+00:00 Remove two fixed bugs from TODO - - - - - ddc9130c by David Waern at 2008-04-12T19:37:06+00:00 Update test README - - - - - 956069c0 by David Waern at 2008-05-01T12:16:14+00:00 Update version number in spec and docs - - - - - 5478621c by David Waern at 2008-05-01T12:28:12+00:00 Remove claim of backwards compatibility from docs for readInterfaceFile - - - - - 4a16dea9 by David Waern at 2008-05-01T12:33:04+00:00 Update CHANGES - - - - - 804216fb by David Waern at 2008-05-01T12:43:16+00:00 Add a synopsis - - - - - fd0c84d5 by David Waern at 2008-05-01T12:44:44+00:00 Add Haddock.DocName to the cabal file - - - - - 9f4a7439 by David Waern at 2008-05-01T12:45:53+00:00 Remove -fglasgow-exts and -fasm - - - - - aee7c145 by David Waern at 2008-05-01T12:54:01+00:00 Add LANGUAGE pragmas to source files - - - - - 9a58428b by David Waern at 2008-05-01T12:54:19+00:00 Add extensions to cabal file - - - - - 494f1bee by David Waern at 2008-05-01T13:12:09+00:00 Export DocName in the API - - - - - c938196b by David Waern at 2008-05-01T13:12:19+00:00 Add hide options to some source files - - - - - 236e86af by Neil Mitchell at 2008-06-07T20:45:10+00:00 Rewrite the --hoogle flag support - - - - - 6d910950 by Neil Mitchell at 2008-06-14T10:56:50+00:00 Simplify the newtype/data outputting in Hoogle, as haddock does it automatically - - - - - f87a95a8 by Neil Mitchell at 2008-06-14T12:10:18+00:00 Add initial structure for outputting documentation as well, but does not yet output anything - - - - - 7c3bce54 by Neil Mitchell at 2008-06-14T12:27:07+00:00 Remove <document comment> from the Hoogle output - - - - - 9504a325 by Neil Mitchell at 2008-06-16T06:33:21+00:00 Default to "main" if there is no package, otherwise will clobber hoogle's hoogle info - - - - - 4a794a79 by Neil Mitchell at 2008-06-16T06:53:29+00:00 Change packageName to packageStr, as it better reflects the information stored in it - - - - - 7abc9baf by Neil Mitchell at 2008-06-16T07:09:49+00:00 Add modulePkgInfo to Haddock.GHC.Utils, which gives back package name and version info - - - - - 8ca11514 by Neil Mitchell at 2008-06-16T07:13:48+00:00 Change Hoogle to take the package name and package version separately - - - - - a6da452d by Neil Mitchell at 2008-06-18T11:29:46+00:00 In Hoogle do not list things that are not local to this module - - - - - 974b76b7 by David Waern at 2008-06-19T18:40:13+00:00 Be more consistent with GHC API naming in H.GHC.Utils - - - - - 2facb4eb by David Waern at 2008-06-19T19:03:03+00:00 Update test output - - - - - c501de72 by David Waern at 2008-06-26T20:26:49+00:00 Use ghc-paths to get the lib dir The path can still be overridden using the -B flag. It's not longer required to pass the lib dir to the program that runs the test suite. - - - - - ac4c6836 by David Waern at 2008-06-26T20:33:08+00:00 Update CHANGES - - - - - 9d21c60a by David Waern at 2008-06-26T20:34:53+00:00 Update README - - - - - 741448f0 by David Waern at 2008-06-26T21:12:57+00:00 Improve wording in the help message - - - - - b1b42b11 by David Waern at 2008-06-30T10:16:17+00:00 Rename ForeignType - - - - - 6d6c2b34 by David Waern at 2008-06-30T10:25:09+00:00 Rename TyFamily - - - - - 8d1125ed by David Waern at 2008-06-30T10:37:21+00:00 Rename type patterns - - - - - 7610a4cb by David Waern at 2008-06-30T10:45:07+00:00 Rename associated types - - - - - 8eeba14c by David Waern at 2008-06-30T10:47:41+00:00 Remove the TODO file now that we have a trac - - - - - 1af5b25b by David Waern at 2008-07-02T18:19:28+00:00 Render type family declarations (untested) - - - - - ceb99797 by David Waern at 2008-07-02T18:24:06+00:00 Remove redundant check for summary when rendering data types - - - - - b36a58e0 by David Waern at 2008-07-02T22:01:38+00:00 More support for type families and associated types Now we just need to render the instances - - - - - 78784879 by David Waern at 2008-07-07T22:13:58+00:00 Remove filtering of instances We were filtering out all instances for types with unknown names. This was probably an attempt to filter out instances for internal types. I am removing the filtering for the moment, and will try to fix this properly later. - - - - - 3e758dad by David Waern at 2008-06-30T18:50:30+00:00 Run haddock in-place during testing - - - - - d9dab0ce by David Waern at 2008-07-08T21:04:32+00:00 Remove index.html and doc-index.html from output, they should not be versioned - - - - - 3e6c4681 by David Waern at 2008-07-08T21:06:42+00:00 Update test output following change to instance filtering - - - - - e34a3f14 by David Waern at 2008-07-12T16:48:28+00:00 Stop using the map from exported names to declarations During creation of the interface, we were using two maps: one from exported names to declarations, and one from all defined names in the module to declarations. The first contained subordinate names while the second one didn't. The first map was never used to look up names not defined in the associated module, so if we add subordinate names to the second map, we could use it everywhere. That's that this patch does. This simplifies code because we don't have to pass around two maps everywhere. We now store the map from locally defined things in the interface structure instead of the one from exported names. - - - - - 2e1d2766 by David Waern at 2008-07-12T16:55:21+00:00 Get the all locally defined names from GHC API We previously had some code to compute all locally defined names in a module including subordinate names. We don't need it since we can get the names from modInfoTyThings in the GHC API. - - - - - bf637994 by David Waern at 2008-07-13T13:09:16+00:00 Refactoring in H.Interface.Create We were creating a doc map, a declaration map and a list of entities separately by going through the HsGroup. These structures were all used to build the interface of a module. Instead of doing this, we can start by creating a list of declarations from the HsGroup, then collect the docs directly from this list (instead of using the list of entities), creating a documentation map. We no longer need the Entity data type, and we can store a single map from names to declarations and docs in the interface, instead of the declaration map and the doc map. This way, there is only one place where we filter out the declarations that we don't want, and we can remove a lot of code. Another advantage of this is that we can create the exports directly out of the list of declarations when we export the full module contents. (Previously we did a look up for each name to find the declarations). This is faster and removes another point where we depend on names to identify exported declarations, which is good because it eliminates problems with instances (which don't have names). - - - - - 547e410e by David Waern at 2008-07-13T13:34:51+00:00 Remove FastString import and FSLIT macro in H.I.Create -- they were unused - - - - - 693759d1 by David Waern at 2008-07-13T13:36:23+00:00 Remove unused import from H.I.Create - - - - - cde6e7fb by David Waern at 2008-07-13T13:51:54+00:00 Small touches - - - - - 96de8f1d by David Waern at 2008-07-20T11:21:46+00:00 Preparation for rendering instances as separate declarations We want to be able to render instances as separate declarations. So we remove the Name argument of ExportDecl, since instances are nameless. This patch also contains the first steps needed to gather type family instances and display them in the backend, but the implementation is far from complete. Because of this, we don't actually show the instances yet. - - - - - b0f824fb by David Waern at 2008-07-20T15:53:08+00:00 Follow changes to ExportDecl in Hoogle - - - - - 1192eff3 by Neil Mitchell at 2008-06-26T00:28:10+00:00 Change how the Hoogle backend outputs classes, adding the context in - - - - - 7a0d1464 by Neil Mitchell at 2008-06-26T00:28:46+00:00 Remove the indent utility function from Hoogle backend - - - - - 3361241b by Neil Mitchell at 2008-06-26T09:45:09+00:00 Add support for Hoogle writing ForeignImport/ForeignExport properly - - - - - 795ad3bf by Neil Mitchell at 2008-06-26T12:15:25+00:00 Flesh out the Hoogle code to render documentation - - - - - 23277995 by Neil Mitchell at 2008-06-26T14:56:41+00:00 Fix a bug in the Hoogle backend, unordered lists were being written out <ul>...</u> - - - - - db739b27 by Neil Mitchell at 2008-06-26T15:09:54+00:00 Remove any white space around a <li> element - - - - - f2e6bb8c by Neil Mitchell at 2008-07-10T15:30:47+00:00 Remove the TODO in the Hoogle HTML generation, was already done - - - - - 693ec9a3 by Neil Mitchell at 2008-07-10T15:53:00+00:00 Put brackets round operators in more places in the Hoogle output - - - - - 842313aa by Neil Mitchell at 2008-07-10T16:01:25+00:00 Print type signatures with brackets around the name - - - - - cf93deb0 by David Waern at 2008-07-20T17:04:22+00:00 Bump version number to 2.2.0 - - - - - 30e6a8d1 by David Waern at 2008-07-20T17:04:41+00:00 Resolve conflicts in H.B.Hoogle - - - - - 1f0071c9 by David Waern at 2008-07-23T23:05:01+00:00 Add "all" command to runtests.hs that runs all tests despite failures - - - - - f2723023 by David Waern at 2008-07-23T23:08:39+00:00 Update tests/README - - - - - c0304a11 by David Waern at 2008-07-23T23:21:15+00:00 Be compatible with GHC 6.8.3 The cabal file is converted to use the "new" syntax with explicit Library and Executable sections. We define the __GHC_PATCHLEVEL__ symbol using a conditinal cpp-options field in the cabal file. (Ideally, Cabal would define the symbol for us, like it does for __GLASGOW_HASKELL__). We use these symbols to #ifdef around a small difference between 6.8.2 and 6.8.3. Previously, we only supported GHC 6.8.2 officially but the dependencies field said "ghc <= 6.9". This was just for convenience when testing against the (then compatible) HEAD version of GHC, and was left in the release by mistake. Now, we support both GHC 6.8.2 and 6.8.3 and the dependencies field correctly reflects this. - - - - - 88a5fe71 by David Waern at 2008-07-23T23:54:16+00:00 Depend on the currently available ghc-paths versions only - - - - - 8738d97b by David Waern at 2008-07-24T10:50:44+00:00 FIX haskell/haddock#44: Propagate parenthesis level when printing documented types - - - - - 05339119 by David Waern at 2008-07-24T16:06:18+00:00 Drop unnecessary parenthesis in types, put in by the user We were putting in parenthesis were the user did. Let's remove this since it just clutters up the types. The types are readable anyway since we print parens around infix operators and do not rely on fixity levels. When doing this I discovered that we were relying on user parenthesis when printin types like (a `O` b) c. This patchs fixes this problem so that parenthesis are always inserted around an infix op application in case it is applied to further arguments, or if it's an arguments to a type constructor. Tests are updated. - - - - - b3a99828 by David Waern at 2008-07-24T10:19:43+00:00 Print parenthesis around non-atomic banged types Fixes half of haskell/haddock#44 - - - - - ab5238e0 by David Waern at 2008-07-24T22:07:49+00:00 Add a reference file for the TypeFamilies test - - - - - 1941cc11 by David Waern at 2008-07-25T17:15:53+00:00 Simplify definition of pretty and trace_ppr - - - - - e3bfa33c by David Waern at 2008-07-25T17:18:27+00:00 Warning messages Output a warning when filtering out data/type instances and associated types in instances. We don't show these in the documentation yet, and we need to let the user know. - - - - - 9b85fc89 by David Waern at 2008-07-25T17:45:40+00:00 Doc: Mention Hoogle in the Introduction - - - - - afb2dd60 by David Waern at 2008-07-25T17:49:00+00:00 Doc: update -B description - - - - - 584c0c91 by David Waern at 2008-07-25T18:11:38+00:00 Doc: describe -w flag - - - - - 77619c24 by David Waern at 2008-07-28T12:29:07+00:00 Remove TODO from cabal file - - - - - 96717d5f by David Waern at 2008-07-28T12:29:27+00:00 Support type equality predicates - - - - - c2fd2330 by David Waern at 2008-07-29T19:45:14+00:00 Move unL from H.B.Hoogle to H.GHC.Utils I like Neil's shorter unL better than unLoc from the GHC API. - - - - - c4c3bf6a by David Waern at 2008-07-29T19:47:36+00:00 Do not export ATs when not in list of subitems - - - - - bf9a7b85 by David Waern at 2008-08-03T11:42:59+00:00 Filter out ForeignExports - - - - - df59fcb0 by David Waern at 2008-08-03T14:02:51+00:00 Filter out more declarations The previous refactorings in H.I.Create introduced a few bugs. Filtering of some types of declarations that we don't handle was removed. This patch fixes this. - - - - - 2f8a958b by David Waern at 2008-08-03T15:24:07+00:00 Move reL to H.GHC.Utils so we can use it everywhere - - - - - 8ec15efd by David Waern at 2008-08-03T15:25:00+00:00 Use isVanillaLSig from GHC API instead of home brewn function - - - - - 300f93a2 by David Waern at 2008-08-03T15:25:27+00:00 Filter out separately exported ATs This is a quick and dirty hack to get rid of separately exported ATs. We haven't decided how to handle them yet. No warning message is given. - - - - - 8776d1ec by David Waern at 2008-08-03T16:21:21+00:00 Filter out more declarations and keep only vanilla type sigs in classes - - - - - ea07eada by David Waern at 2008-08-03T16:48:00+00:00 Fix layout - - - - - dd5e8199 by David Waern at 2008-08-03T16:50:52+00:00 Move some utility functions from H.I.Create to H.GHC.Utils - - - - - 4a1dbd72 by David Waern at 2008-08-03T17:39:55+00:00 Do not filter out doc declarations - - - - - 0bc8dca4 by David Waern at 2008-08-03T17:47:26+00:00 Filter out separately exported ATs (take two) - - - - - af970fe8 by David Waern at 2008-08-03T22:39:17+00:00 Update CHANGES - - - - - 5436ad24 by David Waern at 2008-08-03T22:40:20+00:00 Bump version number to 2.2.1 - - - - - d66de448 by David Waern at 2008-08-05T19:00:32+00:00 Remove version restriction on ghc-paths - - - - - 534b1364 by David Waern at 2008-08-05T19:04:35+00:00 Bump version to 2.2.2 and update CHANGES - - - - - 549188ff by David Waern at 2008-08-05T19:16:49+00:00 Fix CHANGES - - - - - 0d156bb4 by Luke Plant at 2008-08-11T15:20:59+00:00 invoking haddock clarification and help - - - - - 748295cc by David Waern at 2008-08-11T18:56:37+00:00 Doc: say that the --hoogle option is functional - - - - - 43301db4 by David Waern at 2008-08-05T19:26:08+00:00 Change ghc version dependency to >= 6.8.2 - - - - - 3e5a53b6 by David Waern at 2008-08-10T22:42:05+00:00 Make H.GHC.Utils build with GHC HEAD - - - - - 7568ace0 by David Waern at 2008-08-11T19:41:54+00:00 Import Control.OldException instead of C.Exception when using ghc >= 6.9 We should really test for base version instead, but I don't currently know which version to test for. - - - - - b71ae991 by David Waern at 2008-08-12T22:40:39+00:00 Make our .haddock file version number depend on the GHC version We need to do this, since our .haddock format can potentially change whenever GHC's version changes (even when only the patchlevel changes). - - - - - 6307ce3f by David Waern at 2008-08-12T22:49:57+00:00 Remove matching on NoteTy in AttachInstances, it has been removed - - - - - 2dbcfd5f by David Waern at 2008-08-12T23:02:02+00:00 Comment out H.GHC.loadPackages - it is unused and doesn't build with ghc >= 6.9 - - - - - c74db5c2 by David Waern at 2008-08-12T23:03:58+00:00 Hide <.> from GHC import in Hoogle only for ghc <= 6.8.3 - - - - - 69a44ebb by David Waern at 2008-08-12T23:11:12+00:00 Follow changes to parseDynamic/StaticFlags - - - - - 5881f3f0 by David Waern at 2008-08-13T21:43:58+00:00 Add __GHC_PATCHLEVEL__ symbol also when building the library - - - - - 8574dc11 by David Waern at 2008-08-13T21:44:17+00:00 Follow move of package string functions from PackageConfig to Module - - - - - c9baa77f by David Waern at 2008-08-13T21:45:29+00:00 Follow extensible exceptions changes - - - - - 9092de15 by David Waern at 2008-08-13T21:46:20+00:00 Update test following Haddock version change - - - - - ebe569a4 by David Waern at 2008-08-13T21:46:54+00:00 Follow changes to parseDynamic- parseStaticFlags in GHC - - - - - b8a5ffd3 by David Waern at 2008-08-13T21:47:36+00:00 Follow changes to Binary in GHC 6.9 - - - - - edfda1cc by David Waern at 2008-08-13T21:50:17+00:00 Change ghc version dependency to >= 6.8.2 && <= 6.9 - - - - - d59be1cf by Neil Mitchell at 2008-08-12T16:02:53+00:00 Output all items, even if they are not defined in this module - ensures map comes from Prelude, not just GHC.Base - - - - - dda93b9f by Neil Mitchell at 2008-08-12T21:37:32+00:00 Add support for type synonyms to Hoogle, was accidentally missing before (woops!) - - - - - b6ee795c by Neil Mitchell at 2008-08-13T14:03:24+00:00 Generalise Hoogle.doc and add a docWith - - - - - 415e1bb2 by Neil Mitchell at 2008-08-13T14:03:46+00:00 Make Hoogle add documentation to a package - - - - - 790a1202 by Neil Mitchell at 2008-08-18T12:52:43+00:00 Use the same method to put out signatures as class methods in the Hoogle backend - - - - - ded37eba by Neil Mitchell at 2008-08-18T12:53:04+00:00 Remove Explicit top-level forall's when pretty-printing signatures - - - - - 6468c722 by Neil Mitchell at 2008-08-20T07:59:13+00:00 Simplify the code by removing not-to-important use of <.> in the Hoogle back end - - - - - 788c3a8b by Neil Mitchell at 2008-08-21T18:20:24+00:00 In the hoogle back end, markup definition lists using <i>, not <b> - - - - - 77d4b000 by Ian Lynagh at 2008-08-14T10:49:14+00:00 Add a Makefile for GHC's build system. Still won't work yet, but we're closer - - - - - 920440d7 by Ian Lynagh at 2008-08-27T18:06:46+00:00 Add haddock.wrapper - - - - - bcda925f by Ian Lynagh at 2008-08-27T18:07:02+00:00 Add a manual Cabal flag to control the ghc-paths dependency - - - - - 04d194e2 by Ian Lynagh at 2008-08-27T20:41:27+00:00 Update extensions in Cabal file Use ScopedTypeVariables instead of PatternSignatures - - - - - 12480043 by Ian Lynagh at 2008-08-27T20:41:55+00:00 Increase the upper bound on the GHC version number - - - - - b1f809a5 by Ian Lynagh at 2008-08-27T21:32:22+00:00 Fix some warnings - - - - - aea0453d by Ian Lynagh at 2008-08-28T14:22:29+00:00 Fixes for using haddock in a GHC build tree - - - - - ad23bf86 by Ian Lynagh at 2008-08-28T21:14:27+00:00 Don't use Cabal wrappers on Windows - - - - - 35858e4c by Ian Lynagh at 2008-08-29T00:07:42+00:00 Fix in-tree haddock on Windows - - - - - c2642066 by Ian Lynagh at 2008-09-03T22:35:53+00:00 follow library changes - - - - - 2eb55d50 by Ian Lynagh at 2008-09-07T18:52:51+00:00 bindist fixes - - - - - 3daa5b59 by Ian Lynagh at 2008-09-10T16:58:18+00:00 We need to tell haddock that its datasubdir is . or it can't find package.conf - - - - - 388fd8c2 by Ian Lynagh at 2008-09-10T19:47:44+00:00 Fix haddock inplace on Windows - - - - - 70a641c1 by Ian Lynagh at 2008-09-10T22:15:44+00:00 Fix installed haddock on Windows - - - - - 83c1e997 by Neil Mitchell at 2008-09-11T10:48:55+00:00 Import GHC.Paths if not IN_GHC_TREE, seems to match the use of GHC.Paths functions much better - - - - - b452519b by Ian Lynagh at 2008-09-12T12:58:24+00:00 Add a LANGUAGE ForeignFunctionInterface pragma - - - - - afbd592c by Ian Lynagh at 2008-09-12T12:59:13+00:00 Wibble imports - - - - - 547ac4ad by Ian Lynagh at 2008-09-14T15:34:22+00:00 Add a "#!/bin/sh" to haddock.wrapper - - - - - f207a807 by Ian Lynagh at 2008-09-15T10:02:32+00:00 Use "exec" when calling haddock in the wrapper - - - - - 2ee68509 by Thomas Schilling at 2008-09-15T09:09:16+00:00 Port Haddock.Interface to new GHC API. This required one bigger change: 'readInterfaceFile' used to take an optional 'Session' argument. This was used to optionally update the name cache of an existing GHC session. This does not work with the new GHC API, because an active session requires the function to return a 'GhcMonad' action, but this is not possible if no session is provided. The solution is to use an argument of functions for reading and updating the name cache and to make the function work for any monad that embeds IO, so it's result type can adapt to the calling context. While refactoring, I tried to make the code a little more self-documenting, mostly turning comments into function names. - - - - - 3bb96431 by Thomas Schilling at 2008-09-15T09:09:37+00:00 Reflect GHC API changes. - - - - - 2e60f714 by Thomas Schilling at 2008-09-15T09:10:37+00:00 Port Haddock.GHC.Typecheck to new GHC API. - - - - - 9cfd4cff by Thomas Schilling at 2008-09-15T09:11:00+00:00 Port Haddock.GHC to new GHC API. - - - - - caffa003 by Thomas Schilling at 2008-09-15T09:11:25+00:00 Port Main to new GHC API. - - - - - 069a4608 by Ian Lynagh at 2008-09-21T11:19:00+00:00 Fix paths used on Windows frmo a GHC tree: There is no whare directory - - - - - 7ceee1f7 by Ian Lynagh at 2008-09-21T12:20:16+00:00 Fix the in-tree haddock on Windows - - - - - 0d486514 by Ian Lynagh at 2008-09-23T18:06:58+00:00 Increase the GHC upper bound from 6.11 to 6.13 - - - - - f092c414 by Neil Mitchell at 2008-09-11T14:56:07+00:00 Do not wrap __ in brackets - - - - - 036bdd13 by Ian Lynagh at 2008-09-28T01:42:35+00:00 Fix building haddock when GhcProfiled=YES - - - - - 01434a89 by David Waern at 2008-09-24T20:24:21+00:00 Add PatternSignatures LANGUAGE pragma to Main and Utils - - - - - 1671a750 by David Waern at 2008-10-02T22:57:25+00:00 For source links, get original module from declaration name instead of environment. Getting it from the environment must have been a remnant from the times when we were using unqualified names (versions 0.x). - - - - - a25dde99 by David Waern at 2008-10-02T22:59:57+00:00 Remove ifaceEnv from Interface - it's no longer used - - - - - 610993da by David Waern at 2008-10-02T23:04:58+00:00 Write a comment about source links for type instance declarations - - - - - 5a96b5d5 by Thomas Schilling at 2008-10-03T10:45:08+00:00 Follow GHC API change of parseModule. - - - - - 5a943ae5 by Ian Lynagh at 2008-10-03T15:56:58+00:00 TAG 2008-10-03 - - - - - 76cdd6ae by Thomas Schilling at 2008-10-08T12:29:50+00:00 Only load modules once when typechecking with GHC. This still doesn't fix the memory leak since the typechecked source is retained and then processed separately. To fix the leak, modules must be processed directly after typechecking. - - - - - 7074d251 by David Waern at 2008-10-09T23:53:54+00:00 Interleave typechecking with interface creation At the same time, we fix a bug where the list of interfaces were processed in the wrong order, when building the links and renaming the interfaces. - - - - - 4b9b2b2d by David Waern at 2008-10-09T23:54:49+00:00 Add some strictness annotations in Interface We add some strictness annotations to the fields of Interface, so that less GHC data is hold on to during processing. - - - - - 22035628 by David Waern at 2008-10-10T20:02:31+00:00 Remove typecheckFiles and MonadUtils import from H.GHC.Typeccheck - - - - - be637ad3 by David Waern at 2008-10-10T20:33:38+00:00 Make Haddock build with GHC 6.8.2 - - - - - 523b3404 by David Waern at 2008-10-10T21:08:09+00:00 Fix documentation for createInterfaces - - - - - e1556702 by David Waern at 2008-10-10T21:26:19+00:00 Hide H.Utils in library - - - - - a8e751c3 by David Waern at 2008-10-10T21:34:59+00:00 Add back .haddock file versioning based on GHC version It was accidentally removed in the patch for GHC 6.8.2 compatibility - - - - - 06fb3c01 by David Waern at 2008-10-10T21:47:15+00:00 Bump version number to 2.3.0 - - - - - ff087fce by David Waern at 2008-10-10T22:35:49+00:00 Add support for DocPic The support for DocPic was merged into the GHC source long ago, but the support in Haddock was forgotten. Thanks Peter Gavin for submitting this fix! - - - - - 3af85bf6 by David Waern at 2008-10-10T23:34:05+00:00 Update tests - - - - - 0966873c by Simon Marlow at 2008-10-10T14:43:04+00:00 no need for handleErrMsg now, we don't throw any ErrMsgs - - - - - f1870de3 by Clemens Fruhwirth at 2008-10-10T13:29:36+00:00 Compile with wrapper but remove it for dist-install - - - - - 7b440dc2 by David Waern at 2008-10-11T14:02:25+00:00 Remove interface from LinksInfo It was there to know the documentation home module when creating a wiki link, but we already know this since we have the DocName. - - - - - e5729e6a by David Waern at 2008-10-15T20:49:18+00:00 Wibble - - - - - b2a8e01a by David Waern at 2008-10-15T21:03:36+00:00 Use type synonyms for declarations and docs in H.I.Create - - - - - be71a15b by David Waern at 2008-10-15T21:12:17+00:00 Comment out unused type family stuff completely - - - - - 91aaf075 by David Waern at 2008-10-15T21:49:04+00:00 Wibble - - - - - 42ba4eb4 by David Waern at 2008-10-15T21:53:53+00:00 Move convenient type synonym to H.Types - - - - - db11b723 by David Waern at 2008-10-15T22:14:07+00:00 Add DeclInfo to H.Types - - - - - 193552b6 by David Waern at 2008-10-15T22:15:01+00:00 Add subordinates with docs to the declaration map The only place in the code where we want the subordinates for a declaration is right after having looked up the declaration in the map. And since we include subordinates in the map, we might as well take the opportunity to store those subordinates that belong to a particular declaration together with that declaration. We also store the documentation for each subordinate. - - - - - 31e6eebc by David Waern at 2008-10-16T17:18:47+00:00 Wibble - - - - - 0dcbd79f by David Waern at 2008-10-16T20:58:42+00:00 Fix haskell/haddock#61 We were not getting docs for re-exported class methods. This was because we were looking up the docs in a map made from the declarations in the current module being rendered. Obviously, re-exported class methods come from another module. Class methods and ATs were the only thing we were looking up using the doc map, everything else we found in the ExporItems. So now I've put subordinate docs in the ExportItem's directly, to make things a bit more consistent. To do this, I added subordinates to the the declarations in the declaration map. This was easy since we were computing subordinates anyway, to store stand-alone in the map. I added a new type synonym 'DeclInfo', which is what we call what is now stored in the map. This little refactoring removes duplicate code to retrieve subordinates and documentation from the HsGroup. - - - - - de47f20a by David Waern at 2008-10-16T22:06:35+00:00 Document function and improve its layout - - - - - e74e625a by Thomas Schilling at 2008-10-20T11:12:57+00:00 Force interface more aggressively. For running Haddock on GHC this reduces memory usage by about 50 MB on a 32 bit system. A heap profile shows total memory usage peak at about 100 MB, but actual usage is at around 300 MB even with compacting GC (+RTS -c). - - - - - b63ac9a1 by David Waern at 2008-10-20T20:25:50+00:00 Make renamer consistent Instead of explicitly making some binders Undocumented, treat all names the same way (that is, try to find a Documented name). - - - - - f6de0bb0 by Ian Lynagh at 2008-09-19T00:54:43+00:00 TAG GHC 6.10 fork - - - - - 74599cd0 by David Waern at 2008-10-20T21:13:24+00:00 Do not save hidden modules in the .haddock file We were saving interfaces of all processed modules including those hidden using {-# OPTIONS_HADDOCK hide #-} in the .haddock file. This caused broken links when generating the index for the libraries that come with GHC. This patch excludes modules with hidden documentation when writing .haddock files. It should fix the above problem. - - - - - 7b6742e9 by David Waern at 2008-10-21T19:54:52+00:00 Do not save hidden modules in the .haddock file (also for ghc >= 6.9) When writing the first patch, I forgot to do the fix in both branches of an #if macro. - - - - - b99b1951 by David Waern at 2008-10-22T20:04:18+00:00 Remove subordinate map and its usage It is not needed now that we store subordinate names in the DeclInfo map. - - - - - da97cddc by David Waern at 2008-10-22T20:11:46+00:00 Tidy up code in H.I.Create a little Remove commented out half-done type instance support, and remove DeclWithDoc synonym. - - - - - 6afa76f3 by David Waern at 2008-10-22T21:17:29+00:00 Fix warnings in H.GHC.Utils - - - - - 171ea1e8 by David Waern at 2008-10-22T21:35:04+00:00 Fix warnings in H.Utils - - - - - c8cb3b91 by David Waern at 2008-10-22T21:36:49+00:00 Wibble - - - - - 767fa06a by David Waern at 2008-10-27T19:59:04+00:00 Make named doc comments into ExportDoc instead of ExportDecl Fixes a crash when processing modules without export lists containing named docs. - - - - - e638bbc6 by David Waern at 2008-11-02T22:21:10+00:00 Add HCAR entry - - - - - 92b4ffcf by David Waern at 2008-11-02T22:44:19+00:00 Update CHANGES - - - - - 84d4da6e by David Waern at 2008-11-03T11:25:04+00:00 Add failing test for template haskell crash - - - - - 2a9cd2b1 by David Waern at 2008-11-04T21:13:44+00:00 Add tests/TH.hs - - - - - 8a59348e by David Waern at 2008-11-04T21:30:26+00:00 TAG 2.3.0 - - - - - 54f70d31 by Thomas Schilling at 2008-10-24T17:04:08+00:00 Enable framed view of the HTML documentation. This patch introduces: - A page that displays the documentation in a framed view. The left side will show a full module index. Clicking a module name will show it in the right frame. If Javascript is enabled, the left side is split again to show the modules at the top and a very short synopsis for the module currently displayed on the right. - Code to generate the mini-synopsis for each module and the mini module index ("index-frames.html"). - CSS rules for the mini-synopsis. - A very small amount of javascript to update the mini-synopsis (but only if inside a frame.) Some perhaps controversial things: - Sharing code was very difficult, so there is a small amount of code duplication. - The amount of generated pages has been doubled, since every module now also gets a mini-synopsis. The overhead should not be too much, but I haven't checked. Alternatively, the mini-synopsis could also be generated using Javascript if we properly annotate the actual synopsis. - - - - - 5d7ea5a6 by David Waern at 2008-11-04T23:20:17+00:00 Follow change to ExportDecl in frames code - - - - - 60e16308 by David Waern at 2008-11-04T23:35:26+00:00 Update CHANGES - - - - - d63fd26d by David Waern at 2008-11-04T23:37:43+00:00 Bump version number - - - - - c1660c39 by David Waern at 2008-11-04T23:44:46+00:00 Update CHANGES - - - - - 995ab384 by David Waern at 2008-11-04T23:55:21+00:00 Remove .ref files from tests/output/ - - - - - 1abbbe75 by David Waern at 2008-11-04T23:57:41+00:00 Output version info before running tests - - - - - 649b182f by David Waern at 2008-11-05T22:45:37+00:00 Add ANNOUNCE message - - - - - c36ae0bb by David Waern at 2008-11-05T23:15:35+00:00 Update ANNOUNCE - - - - - 9c4f3d40 by David Waern at 2008-11-05T23:18:30+00:00 Wibble - - - - - 5aac87ce by David Waern at 2008-11-06T21:07:48+00:00 Depend on base 4.* when using GHC >= 6.9, otherwise 3.* - - - - - b9796a74 by David Waern at 2008-11-06T21:13:40+00:00 Bump version to 2.4.1 and update CHANGES - - - - - d4b26baa by David Waern at 2008-11-06T21:26:33+00:00 Depend on base 4.0.* instead of 4.* - - - - - 2cb0903c by David Waern at 2008-11-06T21:46:53+00:00 Fix warnings in H.B.HH and H.B.HH2 - - - - - e568e89a by David Waern at 2008-11-06T21:47:12+00:00 Fix warnings in Haddock.ModuleTree - - - - - 9dc14fbd by David Waern at 2008-11-06T21:47:52+00:00 Fix warnings in Haddock.Version - - - - - 02ac197c by David Waern at 2008-11-06T21:51:31+00:00 Fix warnings in H.InterfaceFile and H.Options - - - - - 63e7439a by David Waern at 2008-11-06T21:59:45+00:00 Fix warnings in H.GHC.Typecheck - - - - - 4bca5b68 by David Waern at 2008-11-08T13:43:42+00:00 Set HscTarget to HscNothing instead of HscAsm There used to be a bug in the GHC API that prevented us from setting this value. - - - - - 07357aec by David Waern at 2008-11-09T22:27:00+00:00 Re-export NameCache and friends from Distribution.Haddock - - - - - ea554b5a by David Waern at 2008-11-09T23:14:10+00:00 Add Haddock.GHC.Utils to other-modules in library - - - - - 74aecfd7 by David Waern at 2008-11-10T01:18:57+00:00 Export DocName in the library - - - - - 241a58b3 by David Waern at 2008-11-10T01:19:18+00:00 Document the functions in H.DocName - - - - - edc2ef1b by David Waern at 2008-11-10T01:20:52+00:00 Export H.DocName in the library - - - - - 4f588d55 by David Waern at 2008-11-10T01:29:14+00:00 Make DocName an instance of NamedThing - - - - - b4647244 by David Waern at 2008-11-15T22:58:18+00:00 Reflect version bump in test suite - - - - - 4bee8ce2 by David Waern at 2008-11-15T22:58:45+00:00 Update tests For unknown reasons, test output for Bug1 and Test has changed for the better. - - - - - 1690e2f9 by David Waern at 2008-11-15T22:59:33+00:00 Store hidden modules in .haddock files We store documentation for an entity in the 'InstalledInterface' of the definition site module, and never in the same structure for a module which re-exports the entity. So when a client of the Haddock library wants to look up some documentation, he/she might need to access a hidden module. But we currently don't store hidden modules in the .haddock files. So we add the hidden modules and the Haddock options to the .haddock files. The options will be used to filter the module list to obtain the visible modules only, which is necessary for generating the contents and index for installed packages. - - - - - 8add6435 by David Waern at 2008-11-16T14:35:50+00:00 Bump major version number due to .haddock file format change - - - - - 48bfcf82 by David Waern at 2008-11-23T14:32:52+00:00 Update tests to account for version number bump - - - - - 0bbd1738 by David Waern at 2008-11-23T14:33:31+00:00 HADDOCK_DATA_DIR changed to haddock_datadir - - - - - 5088b78c by David Waern at 2008-11-23T17:13:21+00:00 FIX haskell/haddock#45: generate two anchors for each name We generate two anchor tags for each name, one where we don't escape the name and one where we URI-encode it. This is for compatibility between IE and Opera. Test output is updated. - - - - - 5ee5ca3b by Neil Mitchell at 2008-11-27T14:38:11+00:00 Drop HsDocTy annotations, they mess up pretty printing and also have a bracketing bug (#2584) - - - - - 51c014e9 by Roman Cheplyaka at 2008-11-27T22:27:36+00:00 Allow referring to a specific section within a module in a module link Fixes haskell/haddock#65 - - - - - 4094bdc5 by David Waern at 2008-11-28T21:13:33+00:00 Update tests following anchor change - - - - - f89552dd by Thomas Schilling at 2008-11-29T16:16:20+00:00 Haddock really shouldn't try to overwrite files. - - - - - 98127499 by David Waern at 2008-12-07T14:09:15+00:00 Solve conflict - - - - - 319356c5 by David Waern at 2008-10-22T21:16:55+00:00 Add -Wall -Werror to ghc-options - - - - - 3c4968c9 by David Waern at 2008-11-04T23:38:56+00:00 TAG 2.4.0 - - - - - 4b21e003 by David Waern at 2008-11-06T21:14:04+00:00 TAG 2.4.1 - - - - - 8e0cad5c by David Waern at 2008-12-07T14:12:54+00:00 Remove -Werror - - - - - 299d6deb by David Waern at 2008-12-07T14:25:18+00:00 Remove -Wall, we'll focus on warnings after 6.10.2 is out - - - - - 5f4216b6 by David Waern at 2008-12-07T20:58:05+00:00 Resolve conflict properly - - - - - 67d774e7 by Neil Mitchell at 2008-12-15T11:44:26+00:00 Make forall's in constructors explicit, i.e. data Foo = Foo {foo :: Eq a => a} - - - - - 61851792 by Neil Mitchell at 2008-12-18T15:39:39+00:00 Try and find a better package name than "main" for Hoogle, goes wrong when working on an executable rather than a library - - - - - 2fab8554 by David Waern at 2008-12-08T23:19:48+00:00 Make visible names from ExportItems Instead of a complicated calculation of visible names out of GHC's export items, we can get them straight out of the already calculated ExportItems. The ExportItems should represent exactly those items that are visible in an interface. If store all the exported sub-names in ExportDecl instead of only those with documentation, the calculation becomes very simple. So we do this change as well (should perhaps have been a separate patch). This should fix the problem with names from ghc-prim not appearing in the link environment. - - - - - 7caadd8c by Ian Lynagh at 2008-12-11T17:01:04+00:00 Wrap the GHC usage with defaultCleanupHandler This fixes a bug where haddock leaves /tmp/ghc* directories uncleaned. - - - - - 7c9fc9a5 by David Waern at 2009-01-02T21:38:27+00:00 Show re-exported names from external packages again This fixes GHC ticket 2746. In order to also link to the exported subordinate names of a declaration, we need to re-introduce the sub map in the .haddock files. - - - - - 119e4e05 by David Waern at 2009-01-06T23:34:17+00:00 Do not process boot modules We should of course not try to produce documentation for boot modules! The reason this has worked in the past is that the output of "real" modules overwrites the output of boot modules later in the process. However, this causes a subtle link environment problem. So let's get rid of this stupid behaviour. We avoid processing boot modules, but we continue to typecheck them. - - - - - c285b9d2 by David Waern at 2009-01-08T18:03:36+00:00 Export modules also when coming from external packages This seems to have regressed since a refactoring that was part of the 2.3.0 release. - - - - - 24031c17 by David Waern at 2009-01-10T15:26:26+00:00 Change version to 2.4.2 - no need to go to 2.5.0 - - - - - 864d1c3f by David Waern at 2009-01-10T15:35:20+00:00 Update tests to account for version number change - - - - - 524ba886 by David Waern at 2009-01-10T18:29:17+00:00 Add test for Template Haskell splicing - - - - - 05e6e003 by David Waern at 2009-01-10T19:35:42+00:00 Fix Trac haskell/haddock#68: Turn on compilation via C for Template Haskell packages We can't use HscNothing if we need to run code coming from modules inside the processed package during typechecking, which is the case for some packages using Template Haskell. This could be improved, to e.g. use HscInterpreted and HscNothing where possible, instead of using HscC for all modules in the package. - - - - - 2b2bafa1 by David Waern at 2009-01-10T20:22:25+00:00 Only use needsTemplateHaskell when compiling with GHC 6.10.2 or above - - - - - bedc3a93 by Ian Lynagh at 2009-01-11T14:58:41+00:00 Fix the location of INPLACE_PKG_CONF; fixes the build Spotted by Conal Elliott - - - - - 943107c8 by David Waern at 2009-01-20T19:27:39+00:00 Document H.I.Create.collectDocs better - - - - - c6252e37 by David Waern at 2009-01-20T19:29:51+00:00 Fix Trac haskell/haddock#59: TH-generated declarations disappearing This patch was contributed by Joachim Breitner (nomeata). - - - - - 3568a6af by David Waern at 2009-01-21T21:41:48+00:00 Do not indicate that a constructor argument is unboxed We only show the strictness annotation for an unboxed constructor argument. The fact that it is unboxed is an implementation detail and should not be part of the module interface. - - - - - 562a4523 by David Waern at 2009-01-22T18:53:49+00:00 Fix Trac haskell/haddock#50: do not attach docs to pragmas or other kinds of non-declarations We now filter out everything that is not a proper Haskell declaration before collecting the docs and attaching them to declarations. - - - - - 6fdf21c2 by David Waern at 2009-01-22T19:48:09+00:00 Add test for quasi quotation. No reference output yet. - - - - - dc4100fd by David Waern at 2009-01-22T19:57:47+00:00 Improve quasi-quotation test and add reference output - - - - - 908b74bb by David Waern at 2009-01-23T23:22:03+00:00 Filter out separately exported associated types in a smarter way - - - - - f6b42ecb by David Waern at 2009-01-24T16:54:39+00:00 Correct spelling mistake in error message - - - - - 24e4245d by David Waern at 2009-01-24T17:48:03+00:00 Correct comment - - - - - b5e8462f by David Waern at 2009-02-07T13:22:29+00:00 Do not show a subordinate at the top level if its parent is also exported See note in the source code for more info. - - - - - 4b09de57 by David Waern at 2009-02-07T13:53:53+00:00 Update test following change to top level subordinates - - - - - 76379896 by David Waern at 2009-02-07T13:58:04+00:00 Remove html files in the tests/output/ directory which have been accidentally added - - - - - 1a6d8b10 by Joachim Breitner at 2009-02-20T10:29:43+00:00 Typo in comment - - - - - fec367d0 by David Waern at 2009-02-24T20:21:17+00:00 Fix small bug The rule is to prefer type constructors to other things when an identifier in a doc string can refer to multiple things. This stopped working with newer GHC versions (due to a tiny change in the GHC renamer). We implement this rule in the HTML backend for now, instead of fixing it in GHC, since we will move renaming of doc strings to Haddock in the future anyway. - - - - - 9b4172eb by David Waern at 2009-02-25T20:04:38+00:00 Fix bad error handling with newer GHCs When support for GHC 6.10 was added, an error handler was installed only around the typechecking phase. This had the effect that errors thrown during dependency chasing were caught in the top-level exception handler and not printed with enough detail. With this patch we wrap the error handler around all our usage of the Ghc monad. - - - - - de2df363 by Simon Peyton Jones at 2009-02-02T16:47:42+00:00 Hide funTyConName, now exported by TypeRep - - - - - 4d40a29f by Ian Lynagh at 2009-02-12T18:57:49+00:00 Don't build the library when building in the GHC tree - - - - - 1cd0abe4 by Ian Lynagh at 2009-02-13T13:58:53+00:00 Add a ghc.mk - - - - - 3d814eeb by Ian Lynagh at 2009-02-13T18:50:28+00:00 do .depend generation for haddock with the stage1 compiler This is a bit of a hack. We mkdepend with stage1 as if .depend depends on the stage2 compiler then make goes wrong: haddock's .depend gets included, which means that make won't reload until it's built, but we can't build it without the stage2 compiler. We therefore build the stage2 compiler before its .depend file is available, and so compilation fails. - - - - - b55036a4 by Ian Lynagh at 2009-02-25T01:38:13+00:00 Give haddock a wrapper on unix in the new GHC build system - - - - - 9eabfe68 by Ian Lynagh at 2009-02-25T19:21:32+00:00 Create inplace/lib/html in the new GHC build system - - - - - 93af30c7 by Ian Lynagh at 2008-11-07T19:18:23+00:00 TAG GHC 6.10.1 release - - - - - 06e6e34a by Thomas Schilling at 2009-02-24T18:11:00+00:00 Define __GHC_PATCHLEVEL__ for recent version of GHC (stable). - - - - - 680e6ed8 by Thomas Schilling at 2009-02-24T18:12:26+00:00 'needsTemplateHaskell' is not defined in current stable GHC. - - - - - 6c5619df by David Waern at 2009-02-25T22:15:23+00:00 Hide fynTyConName only for recent GHC versions - - - - - 6b2344f1 by Ian Lynagh at 2009-02-26T00:49:56+00:00 Add the module to one of haddocks warnings - - - - - e5d11c70 by David Waern at 2009-02-27T21:37:20+00:00 Bug fix We tried to filter out subordinates that were already exported through their parent. This didn't work properly since we were in some cases looking at the grand-parent and not the parent. We now properly compute all the parent-child relations of a declaration, and use this information to get the parent of a subordinate. We also didn't consider record fields with multiple parents. This is now handled correctly. We don't currently support separately exported associated types. But when we do, they should be handled correctly by this process too. Also slightly improved the warning message that we give when filtering out subordinates. - - - - - 10a79a60 by David Waern at 2009-02-27T22:08:08+00:00 Fix error message conflict The module name is already written in the beginning of the message, as seems to be the convention in Haddock. Perhaps not so clear, but we should change it everywhere in that case. Leaving it as it is for now. - - - - - c5055c7f by David Waern at 2009-02-27T22:15:17+00:00 Shorten warning message - - - - - a72fed3a by David Waern at 2009-02-28T00:53:55+00:00 Do not show package name in warning message - - - - - a5daccb2 by Ian Lynagh at 2009-03-01T14:59:35+00:00 Install haddock in the new GHC build system - - - - - dfdb025c by Ian Lynagh at 2009-03-07T23:56:29+00:00 Relax base dependency to < 4.2, not < 4.1 - - - - - 5769c8b4 by David Waern at 2009-03-21T14:58:52+00:00 Bump .haddock file version number (due to change of format) - - - - - f1b8f67b by David Waern at 2009-03-21T14:59:26+00:00 Define __GHC_PATCHLEVEL__=1 when using ghc-6.10.1 - - - - - 23f78831 by David Waern at 2009-03-21T16:40:52+00:00 Update CHANGES - - - - - 7d2735e9 by David Waern at 2009-03-21T16:50:33+00:00 Update ANNOUNCE - - - - - 0771e00a by David Waern at 2009-03-21T16:54:40+00:00 Update ANNOUNCE, again - - - - - 81a6942a by David Waern at 2009-03-21T17:50:06+00:00 Don't be too verbose in CHANGES - - - - - 29861dcf by David Waern at 2009-03-21T18:03:31+00:00 TAG 2.4.2 - - - - - a585f285 by David Waern at 2009-03-21T19:20:29+00:00 Require Cabal >= 1.2.3 - - - - - 7c611662 by David Waern at 2009-03-21T19:21:48+00:00 TAG 2.4.2 with cabal-version >= 1.2.3 - - - - - 23b7deff by Simon Marlow at 2009-03-20T15:43:42+00:00 new GHC build system: use shell-wrappers macro - - - - - 25f8afe7 by Ian Lynagh at 2009-03-21T19:13:53+00:00 Fix (with a hack?) haddock in teh new build system - - - - - 6a29a37e by David Waern at 2009-03-24T22:10:15+00:00 Remove unnecessary LANGUAGE pragma - - - - - 954da57d by David Waern at 2009-03-24T22:21:23+00:00 Fix warnings in H.B.DevHelp - - - - - 1619f1df by David Waern at 2009-03-26T23:20:44+00:00 -Wall police in H.B.Html - - - - - b211e13b by Simon Marlow at 2009-03-24T13:00:56+00:00 install Haddock's html stuff - - - - - 78e0b107 by David Waern at 2008-12-07T19:58:53+00:00 Add verbosity flag and utils, remove "verbose" flag - - - - - 913dae06 by David Waern at 2008-12-07T20:01:05+00:00 Add some basic "verbose" mode logging in H.Interface - - - - - 1cbff3bf by David Waern at 2009-03-27T00:07:26+00:00 Fix conflicts - - - - - 22f82032 by David Waern at 2009-03-27T21:15:11+00:00 Remove H.GHC.Typecheck - - - - - 81557804 by David Waern at 2009-03-27T21:19:22+00:00 Remove docNameOrig and use getName everywhere instead - - - - - d8267213 by David Waern at 2009-03-27T21:21:46+00:00 Use docNameOcc instead of nameOccName . getName - - - - - 5d55deab by David Waern at 2009-03-27T21:33:04+00:00 Remove H.DocName and put DocName in H.Types - - - - - 8ba72611 by David Waern at 2009-03-27T22:06:26+00:00 Document DocName - - - - - 605f8ca5 by David Waern at 2009-03-27T22:45:21+00:00 -Wall police - - - - - e4da93ae by David Waern at 2009-03-27T23:12:53+00:00 -Wall police in H.B.Hoogle - - - - - bb255519 by David Waern at 2009-03-27T23:41:28+00:00 Define Foldable and Traversable instances for Located - - - - - f1195cfe by David Waern at 2009-03-27T23:51:34+00:00 Wibble - - - - - 23818d7c by David Waern at 2009-03-28T00:03:55+00:00 -Wall police in H.I.Rename - - - - - 0f050d67 by David Waern at 2009-03-28T00:15:15+00:00 -Wall police in H.I.AttachInstances - - - - - 0f3fe038 by David Waern at 2009-03-28T21:09:41+00:00 Wibble - - - - - 275d4865 by David Waern at 2009-03-28T21:27:06+00:00 Layout fix - - - - - 54ff0ef8 by David Waern at 2009-03-28T21:59:07+00:00 -Wall police in H.I.Create - - - - - 7f58b117 by David Waern at 2009-03-28T22:10:19+00:00 -Wall police in H.Interface - - - - - f0c03b44 by David Waern at 2009-03-28T22:22:59+00:00 -Wall police in Main - - - - - 29da355c by David Waern at 2009-03-28T22:23:39+00:00 Turn on -Wall -Werror - - - - - 446d3060 by David Waern at 2009-04-01T20:40:30+00:00 hlint police - - - - - 3867c9fc by David Waern at 2009-04-01T20:48:42+00:00 hlint police - - - - - bd1f1600 by David Waern at 2009-04-01T20:58:02+00:00 hlint police - - - - - e0e90866 by David Waern at 2009-04-05T12:42:53+00:00 Move H.GHC.Utils to H.GhcUtils - - - - - 9cbd426b by David Waern at 2009-04-05T12:57:21+00:00 Remove Haddock.GHC and move its (small) contents to Main - - - - - b5c2cbfd by David Waern at 2009-04-05T13:07:04+00:00 Fix whitespace and stylistic issues in Main - - - - - 3c04aa56 by porges at 2008-12-07T08:22:19+00:00 add unicode output - - - - - 607918da by David Waern at 2009-04-26T15:09:43+00:00 Resolve conflict - - - - - 4bec6b6b by Simon Marlow at 2009-05-13T10:00:31+00:00 fix markup - - - - - 436ad6f4 by Simon Marlow at 2009-03-23T11:54:45+00:00 clean up - - - - - bdcd1398 by Simon Marlow at 2009-03-24T10:36:45+00:00 new GHC build system: add $(exeext) - - - - - 9c0972f3 by Simon Marlow at 2009-03-24T11:04:31+00:00 update for new GHC build system layout - - - - - d0f3f83a by Ian Lynagh at 2009-03-29T15:31:43+00:00 GHC new build system fixes - - - - - 5a8245c2 by Ian Lynagh at 2009-04-04T20:44:23+00:00 Tweak new build system - - - - - 9c6f2d7b by Simon Marlow at 2009-05-13T10:01:27+00:00 add build instructions for GHC - - - - - 66d07c76 by Ian Lynagh at 2009-05-31T00:37:53+00:00 Quote program paths in ghc.mk - - - - - bb7de2cd by Ian Lynagh at 2009-06-03T22:57:55+00:00 Use a bang pattern on an unlifted binding - - - - - 3ad283fc by Ian Lynagh at 2009-06-13T16:17:50+00:00 Include haddock in GHC bindists - - - - - ac447ff4 by David Waern at 2009-06-24T21:07:50+00:00 Delete Haddock.Exception and move contents to Haddock.Types Only a few lines of code that mainly declares a type - why not just put it in Haddock.Types. - - - - - 4464fb9b by David Waern at 2009-06-24T22:23:23+00:00 Add Haddock module headers Add a proper Haddock module header to each module, with a more finegrained copyright. If you feel mis-accreditted, please correct any copyright notice! The maintainer field is set to haddock at projects.haskell.org. Next step is to add a brief description to each module. - - - - - 5f4c95dd by David Waern at 2009-06-24T22:39:44+00:00 Fix spelling error - - - - - 6d074cdb by David Waern at 2009-06-25T21:53:56+00:00 Document Interface and InstalledInterface better - - - - - d0cbd183 by David Waern at 2009-06-27T12:46:46+00:00 Remove misplaced whitespace in H.I.Rename - - - - - fa381c49 by David Waern at 2009-06-27T13:26:03+00:00 Fix haskell/haddock#104 - create output directory if missing - - - - - 91fb77ae by Ian Lynagh at 2009-06-25T15:59:50+00:00 TAG 2009-06-25 - - - - - 0d853f40 by Simon Peyton Jones at 2009-07-02T15:35:22+00:00 Follow extra field in ConDecl - - - - - b201735d by Ian Lynagh at 2009-07-05T16:50:35+00:00 Update Makefile for the new GHC build system - - - - - df6c0092 by Ian Lynagh at 2009-07-05T17:01:13+00:00 Resolve conflicts - - - - - 1066870a by Ian Lynagh at 2009-07-05T17:01:48+00:00 Remove the -Wwarn hack in the GHC build system - - - - - 7e856076 by Ian Lynagh at 2009-07-05T17:17:59+00:00 Fix warnings - - - - - 5d4cd958 by Ian Lynagh at 2009-07-05T19:35:40+00:00 Bump version number Cabal needs to distinguish between haddocks having a --verbose and --verbosity flag - - - - - 6ee07c99 by David Waern at 2009-07-06T20:14:57+00:00 Wibble - - - - - 2308b66f by David Waern at 2009-07-06T20:24:20+00:00 Clearer printing of versions by runtests.hs - - - - - d4b5d9ab by David Waern at 2009-07-06T21:22:42+00:00 Fix (invisible) bug introduced by unicode patch - - - - - 2caca8d8 by David Waern at 2009-07-06T21:44:10+00:00 Use HscAsm instead of HscC when using TH - - - - - 18f3b755 by David Waern at 2009-07-06T22:10:22+00:00 Update HCAR entry (by Janis) - - - - - a72ac9db by David Waern at 2009-07-06T23:01:35+00:00 Follow HsRecTy change with an #if __GLASGOW_HASKEL__ >= 611 - - - - - 549135d2 by David Waern at 2009-07-06T23:11:41+00:00 Remove unused functions from Haddock.Utils - - - - - b450134a by Isaac Dupree at 2009-07-11T14:59:00+00:00 revert to split-index for large indices - remove the search-box, because browsers have search-for-text abilities anyway. - pick 150 items in index as the arbitrary time at which to split it - notice the bug that identifiers starting with non-ASCII characters won't be listed in split-index, but don't bother to fix it yet (see ticket haskell/haddock#116, http://trac.haskell.org/haddock/ticket/116 ) - - - - - 78a5661e by Isaac Dupree at 2009-07-20T15:37:18+00:00 Implement GADT records in HTML backend - - - - - 4e163555 by Isaac Dupree at 2009-07-21T22:03:25+00:00 add test for GADT records - - - - - 79aa4d6e by David Waern at 2009-07-23T20:40:37+00:00 Update test suite following version bump - - - - - 5932c011 by David Waern at 2009-08-02T10:25:39+00:00 Fix documentation bug - - - - - a6970fca by David Waern at 2009-08-12T23:08:53+00:00 Remove support for ghc 6.8.* from .cabal file - - - - - c1695902 by Ian Lynagh at 2009-07-07T13:35:45+00:00 Fix unused import warnings - - - - - fb6df7f9 by Ian Lynagh at 2009-07-16T00:20:31+00:00 Use cProjectVersion directly rather than going through compilerInfo Fixes the build after changes in GHC - - - - - 548cdd66 by Simon Marlow at 2009-07-28T14:27:04+00:00 follow changes in GHC's ForeignType - - - - - 9395aaa0 by David Waern at 2009-08-13T22:17:33+00:00 Switch from PatternSignatures to ScopedTypeVariables in Main - - - - - eebf39bd by David Waern at 2009-08-14T17:14:28+00:00 Version .haddock files made with GHC 6.10.3/4 correclty - - - - - 58f3e735 by David Waern at 2009-08-14T17:19:37+00:00 Support GHC 6.10.* and 6.11.* only - - - - - 5f63cecc by David Waern at 2009-08-14T22:03:20+00:00 Do not version .haddock file based on GHC patchlevel version We require that the instances of Binary that we use from GHC will not change between patchlevel versions. - - - - - d519de9f by David Waern at 2009-08-14T23:50:00+00:00 Update CHANGES - - - - - 35dccf5c by David Waern at 2009-08-14T23:51:38+00:00 Update version number everywhere - - - - - 6d363fea by David Waern at 2009-08-15T09:46:49+00:00 Update ANNOUNCE - - - - - c7ee6bc2 by David Waern at 2009-08-15T09:47:13+00:00 Remove -Werror Forgot that Hackage doesn't like it. - - - - - a125c12b by David Waern at 2009-08-15T09:49:50+00:00 Require Cabal >= 1.6 - - - - - adb2f560 by Isaac Dupree at 2009-08-12T03:47:14+00:00 Cross-Package Documentation version 4 - - - - - 3d6dc04d by David Waern at 2009-08-15T23:42:57+00:00 Put all the IN_GHC_TREE stuff inside getGhcLibDir - - - - - 56624097 by David Waern at 2009-08-15T23:52:03+00:00 Add --print-ghc-libdir - - - - - f15d3ccb by David Waern at 2009-08-16T00:37:52+00:00 Read base.haddock when running tests We can now test cross-package docs. - - - - - 283f0fb9 by David Waern at 2009-08-16T00:50:59+00:00 Update test output - we now have more links - - - - - 673d1004 by David Waern at 2009-08-16T01:26:08+00:00 Read process.haddock when running tests - - - - - 0d127f82 by David Waern at 2009-08-16T01:43:04+00:00 Add a test for cross-package documentation - - - - - f94db967 by Ian Lynagh at 2009-08-16T18:42:44+00:00 Follow GHC build system changes - - - - - 5151278a by Isaac Dupree at 2009-08-16T19:58:05+00:00 make cross-package list types look nicer - - - - - c41e8228 by Isaac Dupree at 2009-08-18T01:47:47+00:00 Haddock.Convert: export more functions This lets us remove some code in Haddock.Interface.AttachInstances - - - - - 2e5fa398 by Isaac Dupree at 2009-08-18T02:11:05+00:00 switch AttachInstances to use synify code It changed an instance from showing ((,) a b) to (a, b) because my synify code is more sophisticated; I hope the latter is a good thing rather than a bad thing aesthetically, here. But this definitely reduces code duplication! - - - - - b8b07123 by Isaac Dupree at 2009-08-18T02:23:31+00:00 Find instances using GHC, which is more complete. In particular, it works cross-package. An intermediate patch also moved the instance-finding into createInterface, but that move turned out not to be necessary, so if we want to do that, it'd go in a separate patch. (Is that possible? Or will we need GHC to have loaded all the modules first, before we can go searching for the instances (e.g. if the modules are recursive or something)?) - - - - - 6959b451 by Isaac Dupree at 2009-08-17T00:37:18+00:00 fix preprocessor conditional sense - - - - - 942823af by Isaac Dupree at 2009-08-16T22:46:48+00:00 remove ghc 6.8 conditionals from Haddock.Interface - - - - - 4b3ad888 by Isaac Dupree at 2009-08-18T20:24:38+00:00 Fix GHC 6.11 build in Haddock.Convert - - - - - 0a89c5ab by Isaac Dupree at 2009-08-23T00:08:58+00:00 hacks to make it compile without fnArgDocsn - - - - - 7b3bed43 by Isaac Dupree at 2009-08-23T03:01:28+00:00 less big-Map-based proper extraction of constructor subdocs - - - - - b21c279a by Isaac Dupree at 2009-08-23T03:02:06+00:00 Html: remove unnecessary+troublesome GHC. qualifications - - - - - 96c97115 by Isaac Dupree at 2009-08-23T03:08:03+00:00 Move doc parsing/lexing into Haddock for ghc>=6.11 - - - - - e1cec02d by Isaac Dupree at 2009-08-23T05:08:14+00:00 get rid of unused DocMap parameter in Html - - - - - 66960c59 by Isaac Dupree at 2009-08-23T05:54:20+00:00 fix horrible named-docs-disappearing bug :-) - - - - - a9d7eff3 by Isaac Dupree at 2009-08-23T06:26:36+00:00 re-implement function-argument docs ..on top of the lexParseRn work. This patch doesn't change the InstalledInterface format, and thus, it does not work cross-package, but that will be easy to add subsequently. - - - - - 8bf6852c by Isaac Dupree at 2009-08-23T07:26:05+00:00 cross-package fnArgDocs. WARNING: changes .haddock binary format While breaking the format, I took the opportunity to unrename the DocMap that's saved to disk, because there's really no reason that we want to know what *another* package's favorite place to link a Name to was. (Is that true? Or might we want to know, someday?) Also, I added instance Binary Map in InterfaceFile. It makes the code a little simpler without changing anything of substance. Also it lets us add another Map hidden inside another Map (fnArgsDocs in instDocMap) without having really-convoluted serialization code. Instances are neat! I don't understand why this change to InterfaceFile seemed to subtly break binary compatibility all by itself, but no matter, I'll just roll it into the greater format-changing patch. Done! - - - - - 30115a64 by Isaac Dupree at 2009-08-23T18:22:47+00:00 Improve behavior for unfindable .haddock - - - - - aa364bda by Isaac Dupree at 2009-08-23T18:28:16+00:00 add comment for FnArgsDoc type - - - - - 49b23a99 by Isaac Dupree at 2009-08-23T21:52:48+00:00 bugfix: restore fnArgDocs for type-synonyms - - - - - f65f9467 by Isaac Dupree at 2009-08-23T22:06:55+00:00 Backends.Hoogle: eliminate warnings - - - - - a292d216 by Isaac Dupree at 2009-08-23T22:10:24+00:00 Haddock.Convert: eliminate warnings - - - - - 5546cd20 by Isaac Dupree at 2009-08-23T22:12:31+00:00 Haddock.Interface.Rename: eliminate warnings - - - - - 0a9798b6 by Isaac Dupree at 2009-08-23T22:18:47+00:00 Main.hs: remove ghc<6.9 conditionals - - - - - e8f9867f by Isaac Dupree at 2009-08-23T22:27:46+00:00 Main.hs: eliminate warnings (except for OldException) - - - - - 61c64247 by Isaac Dupree at 2009-08-23T22:41:01+00:00 move get*LibDir code in Main.hs, to +consistent code, -duplication - - - - - 948f1e69 by Isaac Dupree at 2009-08-23T23:14:26+00:00 Main.hs: OldException->Exception: which eliminates warnings - - - - - 3d5d5e03 by Isaac Dupree at 2009-08-23T23:20:11+00:00 GhcUtils: ghc >= 6.10 - - - - - 2771d657 by Isaac Dupree at 2009-08-23T23:21:55+00:00 InterfaceFile: ghc >= 6.10 - - - - - d9f2b9d1 by Isaac Dupree at 2009-08-23T23:22:58+00:00 Types: ghc >= 6.10 - - - - - ca39210e by Isaac Dupree at 2009-08-23T23:23:26+00:00 ModuleTree: ghc >= 6.10 - - - - - 883c4e59 by Isaac Dupree at 2009-08-23T23:24:04+00:00 Backends.DevHelp: ghc >= 6.10 - - - - - 04667df5 by Isaac Dupree at 2009-08-23T23:24:37+00:00 Backends.Html: ghc >= 6.10 - - - - - a9f7f25f by Isaac Dupree at 2009-08-23T23:25:24+00:00 Utils: ghc >= 6.10 - - - - - b7105022 by Isaac Dupree at 2009-08-23T23:37:47+00:00 eliminate haskell98 dependency, following GHC's example It turns out I/we already had, and it was only a matter of deleting it from the cabal file. - - - - - 292e0911 by Isaac Dupree at 2009-08-24T01:22:44+00:00 refactor out subordinatesWithNoDocs dep of inferenced-decls fix - - - - - c2ed46a2 by Isaac Dupree at 2009-08-24T01:24:03+00:00 Eradicate wrong runtime warning for type-inferenced exported-functions see the long comment in the patch for why I did it this way :-) - - - - - 4ac0b57c by David Waern at 2009-09-04T22:56:20+00:00 Clean up tyThingToHsSynSig a little Factor out noLoc and use the case construct. Also rename the function to tyThingToLHsDecl, since it doesn't just create type signatures. - - - - - 28ab9201 by David Waern at 2009-09-04T22:58:50+00:00 Wibble - - - - - 0d9fe6d0 by David Waern at 2009-09-06T18:39:30+00:00 Add more copyright owners to H.I.AttachInstances - - - - - 122441b1 by David Waern at 2009-09-06T18:44:12+00:00 Style police - - - - - 1fa79463 by David Waern at 2009-09-06T18:57:45+00:00 Move toHsInstHead to Haddock.Convert and call it synifyInstHead - - - - - 0d42a8aa by David Waern at 2009-09-06T21:11:38+00:00 Use colordiff to display test results if available - - - - - ea9d8e03 by Simon Marlow at 2009-08-24T08:46:14+00:00 Follow changes in GHC's interface file format Word32 instead of Int for FastString and Name offsets - - - - - 537e051e by Simon Marlow at 2009-07-29T14:16:53+00:00 define unpackPackageId (it was removed from GHC) - - - - - 50c63aa7 by David Waern at 2009-09-09T23:18:03+00:00 Remove commented-out code - - - - - 511631fe by David Waern at 2009-09-09T23:19:05+00:00 Correct copyright in H.I.ParseModuleHeader - - - - - 898ec768 by David Waern at 2009-09-11T11:22:29+00:00 Use Map.fromList/toList intead of fromAscList/toAscList when serializing Maps This fixes the missing docs problem. The Eq and Ord instances for Name uses the unique number in Name. This number is created at deserialization time by GHC's magic Binary instance for Name, and it is random. Thus, fromAscList can't be used at deserialization time, even though toAscList was used at serialization time. - - - - - 37bec0d5 by Simon Peyton Jones at 2009-09-11T08:28:04+00:00 Track change in HsType - - - - - eb3a97c3 by Ian Lynagh at 2009-09-11T16:07:09+00:00 Allow building with base 4.2 - - - - - bb4205ed by Ian Lynagh at 2009-09-22T13:50:02+00:00 Loosen the GHC dependency - - - - - 5c75deb2 by Ian Lynagh at 2009-09-22T14:08:39+00:00 Fix building with GHC >= 6.12 - - - - - fb131481 by David Waern at 2009-09-11T11:24:48+00:00 Update runtests.hs to work with GHC 6.11 - - - - - ac3a419d by David Waern at 2009-09-11T11:25:14+00:00 Update CrossPackageDocs test - - - - - ec65c3c6 by David Waern at 2009-09-11T11:25:40+00:00 Add reference output for CrossPackageDocs - - - - - 520c2758 by Ian Lynagh at 2009-10-25T17:26:40+00:00 Fix installation in the GHC build system - - - - - 28b3d7df by Ian Lynagh at 2009-11-05T15:57:27+00:00 GHC build system: Make *nix installation work in paths containing spaces - - - - - 5c9bb541 by David Waern at 2009-11-14T11:56:39+00:00 Track change in HsType for the right compiler version - - - - - 905097ce by David Waern at 2009-11-14T12:10:47+00:00 hlint police - - - - - 04920630 by Ian Lynagh at 2009-11-20T13:46:30+00:00 Use defaultObjectTarget rather than HscAsm This fixes haddock when we don't have a native code generator - - - - - 966eb079 by David Waern at 2009-11-15T12:32:21+00:00 Remove commented-out code - - - - - 37f00fc4 by David Waern at 2009-11-22T13:58:48+00:00 Make runtests.hs strip links before diffing Generates easier to read diffs when tests fail. The content of the links is not important anyway since it is not taken into account by the tests. - - - - - 3a9bb8ef by David Waern at 2009-11-22T14:05:06+00:00 Follow findProgramOnPath signature change in runtests.hs - - - - - b26b9e5a by David Waern at 2009-11-22T14:08:40+00:00 Follow removal of GHC.MVar from base in CrossPackageDocs - - - - - f4d90ae4 by David Waern at 2009-11-22T14:48:47+00:00 Make copy.hs strip link contents before copying No more updating of reference files when URLs in links changes. - - - - - 4c9c420d by David Waern at 2009-11-22T15:26:41+00:00 Update test reference output * More links (Int, Float etc) * Stripped link contents - - - - - a62b80e3 by David Waern at 2009-11-23T23:19:39+00:00 Update CrossPackageDocs reference output - Remove GHC.MVar import (removed from base) - Strip link contents - - - - - 43491394 by David Waern at 2009-11-23T23:20:00+00:00 Update test reference files with comments on instances - - - - - 0d370a0b by David Waern at 2009-11-23T23:25:16+00:00 Bump version number - - - - - 2293113e by David Waern at 2009-11-24T20:55:49+00:00 Comments on instances Implementing this was a little trickier than I thought, since we need to match up instances from the renamed syntax with instances represented by InstEnv.Instance. This is due to the current design of Haddock, which matches comments with declarations from the renamed syntax, while getting the list of instances of a class/family directly using the GHC API. - Works for class instances only (Haddock has no support for type family instances yet) - The comments are rendered to the right of the instance head in the HTML output - No change to the .haddock file format - Works for normal user-written instances only. No comments are added on derived or TH-generated instances - - - - - bf586f29 by David Waern at 2009-11-27T22:05:15+00:00 Whitespace police - - - - - b8f03afa by David Waern at 2009-11-27T22:11:46+00:00 Remove bad whitespace and commented-out pieces - - - - - 90b8ee90 by David Waern at 2009-11-27T22:15:04+00:00 Whitespace police - - - - - b5ede900 by David Waern at 2009-11-27T22:15:50+00:00 Whitespace police - - - - - e3fddbfe by David Waern at 2009-11-28T13:37:59+00:00 Remove Name from DocInstance It's not used. - - - - - 9502786c by David Waern at 2009-11-28T13:56:54+00:00 Require at least GHC 6.12 While regression testing Haddock, I found a bug that happens with GHC 6.10.3, but not with GHC 6.12-rc2 (haven't tried 6.10.4). I don't have time to track it down. I think we should just always require the latest major GHC version. The time spent on making Haddock work with older versions is too high compared to the time spent on bugfixing, refactoring and features. - - - - - 8fa688d8 by David Waern at 2009-11-28T15:05:03+00:00 Remove cruft due to compatibility with older GHCs - - - - - 46fbbe9d by David Waern at 2009-11-28T15:07:50+00:00 Add a documentation header to Haddock.Convert - - - - - c3d2cc4a by David Waern at 2009-11-28T15:10:14+00:00 Remove unused H.Utils.FastMutInt2 - - - - - 490aba80 by David Waern at 2009-11-28T15:36:36+00:00 Rename Distribution.Haddock into Documentation.Haddock - - - - - 33ee2397 by David Waern at 2009-11-28T15:36:47+00:00 Fix error message - - - - - a5a3b950 by David Waern at 2009-11-28T16:58:39+00:00 Add a test flag that brings in QuickCheck - - - - - fa049e13 by David Waern at 2009-11-28T19:32:18+00:00 Say that we want quickcheck 2 - - - - - f32b0d9b by David Waern at 2009-11-28T19:32:40+00:00 Add an Arbitrary instance for HsDoc - - - - - da9a8bd7 by David Waern at 2009-11-28T20:15:30+00:00 Rename HsDoc back into Doc - - - - - edb60101 by David Waern at 2009-11-28T22:16:16+00:00 Move H.Interface.Parse/Lex to H.Parse/Lex These are not just used to build Interfaces. - - - - - 0656a9b8 by David Waern at 2009-11-28T23:12:14+00:00 Update version number in test suite - - - - - 5e8c6f4a by David Waern at 2009-12-21T14:12:41+00:00 Improve doc of DocName - - - - - 7868e551 by Ian Lynagh at 2009-09-22T10:43:03+00:00 TAG GHC 6.12-branch created - - - - - 0452a3ea by Ian Lynagh at 2009-12-15T12:46:07+00:00 TAG GHC 6.12.1 release - - - - - 65e9be62 by David Waern at 2009-12-21T16:58:58+00:00 Update CHANGES - - - - - 145cee32 by David Waern at 2009-12-21T16:59:09+00:00 TAG 2.6.0 - - - - - 3c552008 by David Waern at 2009-12-22T17:11:14+00:00 Update ANNOUNCE - - - - - 931f9db4 by David Waern at 2010-01-22T19:57:17+00:00 Convert haddock.vim to use unix newlines - - - - - 4e56588f by David Waern at 2010-01-22T22:11:17+00:00 Remove unnecessary (and inexplicable) uses of nub - - - - - 744bb4d1 by David Waern at 2010-01-22T22:12:14+00:00 Follow move of parser and lexer - - - - - e34bab14 by David Waern at 2010-01-22T22:49:13+00:00 Use findProgramLocation instead of findProgramOnPath in runtests.hs - - - - - 8d39891b by Isaac Dupree at 2010-01-14T18:53:18+00:00 fix html arg-doc off-by-one and silliness - - - - - 9401f2e9 by David Waern at 2010-01-22T22:57:03+00:00 Create a test for function argument docs - - - - - 507a82d7 by David Waern at 2010-01-22T23:24:47+00:00 Put parenthesis around type signature arguments of function type - - - - - 8a305c28 by David Waern at 2010-01-23T17:26:59+00:00 Add reference file for the FunArgs test - - - - - 1309d5e1 by David Waern at 2010-01-24T16:05:08+00:00 Improve FunArg test and update Test.html.ref - - - - - 2990f055 by Yitzchak Gale at 2010-02-14T16:03:46+00:00 Do not generate illegal character in HTML ID attribute. - - - - - c5bcab7a by David Waern at 2010-02-22T22:10:30+00:00 Fix Haddock markup error in comment - - - - - c6416a73 by David Waern at 2010-02-24T22:55:08+00:00 Large additions to the Haddock API Also improved and added more doc comments. - - - - - 57d289d7 by David Waern at 2010-02-24T22:58:02+00:00 Remove unused ifaceLocals - - - - - 80528d93 by David Waern at 2010-02-25T21:05:09+00:00 Add HaddockModInfo to the API - - - - - 82806848 by David Waern at 2010-02-25T21:05:27+00:00 Wibble - - - - - 744cad4c by David Waern at 2010-02-25T23:30:59+00:00 Make it possible to run a single test - - - - - 6a806e4c by David Waern at 2010-03-14T14:19:39+00:00 Bump version number - - - - - a5a8e4a7 by David Waern at 2010-03-14T14:36:35+00:00 Update ANNOUNCE - - - - - 6f05435e by Simon Hengel at 2010-03-15T20:52:42+00:00 Add missing dependencies for 'library' in haddock.cabal - - - - - faefe2bd by David Waern at 2010-03-15T22:29:37+00:00 Solve conflicts - - - - - 9808ad52 by David Waern at 2010-03-15T22:51:21+00:00 Bump version number - - - - - eb0bf60b by David Waern at 2010-03-15T22:52:32+00:00 Update CHANGES - - - - - f95cd891 by David Waern at 2010-03-15T23:01:06+00:00 Add Paths_haddock to other-modules of library - - - - - 65997b0a by David Waern at 2010-03-15T23:14:59+00:00 Update CHANGES - - - - - 7e251731 by David Waern at 2010-03-15T23:15:30+00:00 Bump version number - - - - - c9cd0ddc by David Waern at 2010-03-16T00:28:34+00:00 Fix warning - - - - - 1cac2d93 by Simon Peyton Jones at 2010-01-04T15:22:16+00:00 Fix imports for new location of splitKindFunTys - - - - - 474f26f6 by Simon Peyton Jones at 2010-02-10T14:36:06+00:00 Update Haddock for quasiquotes - - - - - 0dcc06c0 by Simon Peyton Jones at 2010-02-10T10:59:45+00:00 Track changes in HsTyVarBndr - - - - - 2d84733a by Simon Peyton Jones at 2010-02-10T14:52:44+00:00 Track HsSyn chnages - - - - - 9e3adb8b by Ian Lynagh at 2010-02-20T17:09:42+00:00 Resolve conflicts - - - - - a3e72ff8 by Simon Peyton Jones at 2010-03-04T13:05:16+00:00 Track change in HsUtils; and use a nicer function not an internal one - - - - - 27994854 by David Waern at 2010-03-18T22:22:27+00:00 Fix build with GHC 6.12.1 - - - - - 11f6e488 by David Waern at 2010-03-18T22:24:09+00:00 Bump version in test reference files - - - - - 0ef2f11b by David Waern at 2010-03-20T00:56:30+00:00 Fix library part of cabal file when in ghc tree - - - - - 3f6146ff by Mark Lentczner at 2010-03-20T22:30:11+00:00 First, experimental XHTML rendering switch to using the xhtml package copied Html.hs to Xhtml.hs and split into sub-modules under Haddock/Backends/Xhtml and detabify moved footer into div, got ready for iface change headers converted to semantic markup contents in semantic markup summary as semantic markup description in semantic markup, info block in header fixed factored out rendering so during debug it can be readable (see renderToString) - - - - - b8ab329b by Mark Lentczner at 2010-03-20T22:54:01+00:00 apply changes to Html.hs to Xhtml/*.hs incorporate changes that were made between the time Html.hs was copied and split into Xhtml.hs and Xhtml/*.hs includes patchs after "Wibble" (!) through "Fix build with GHC 6.12.1" - - - - - 73df2433 by Ian Lynagh at 2010-03-20T21:56:37+00:00 Follow LazyUniqFM->UniqFM in GHC - - - - - db4f602b by David Waern at 2010-03-29T22:00:01+00:00 Fix build with GHC 6.12 - - - - - d8dca088 by Simon Hengel at 2010-04-02T16:39:55+00:00 Add missing dependencies to cabal file - - - - - e2adc437 by Simon Hengel at 2010-04-02T14:08:40+00:00 Add markup support for interactive examples - - - - - e882ac05 by Simon Hengel at 2010-04-02T14:11:53+00:00 Add tests for interactive examples - - - - - 5a07a6d3 by David Waern at 2010-04-07T17:05:20+00:00 Propagate source positions from Lex.x to Parse.y - - - - - 6493b46f by David Waern at 2010-04-07T21:48:57+00:00 Let runtests.hs die when haddock has not been built - - - - - 5e34423e by David Waern at 2010-04-07T22:01:13+00:00 Make runtests.hs slightly more readable - - - - - 321d59b3 by David Waern at 2010-04-07T22:13:27+00:00 Fix haskell/haddock#75 Add colons to the $ident character set. - - - - - 37b08b8d by David Waern at 2010-04-08T00:32:52+00:00 Fix haskell/haddock#118 Avoid being too greedy when lexing URL markup (<..>), in order to allow multiple URLs on the same line. Do the same thing with <<..>> and #..#. - - - - - df8feac9 by David Waern at 2010-04-08T00:57:33+00:00 Make it easier to add new package deps to test suite This is a hack - we should use Cabal to get the package details instead. - - - - - 1ca6f84b by David Waern at 2010-04-08T01:03:06+00:00 Add ghc-prim to test suite deps - - - - - 27371e3a by Simon Hengel at 2010-04-08T19:26:34+00:00 Let parsing fails on paragraphs that are immediately followed by an example This is more consistent with the way we treat code blocks. - - - - - 83096e4a by David Waern at 2010-04-08T21:20:00+00:00 Improve function name - - - - - 439983ce by David Waern at 2010-04-10T10:46:14+00:00 Fix haskell/haddock#112 No link was generated for 'Addr#' in a doc comment. The reason was simply that the identifier didn't parse. We were using parseIdentifier from the GHC API, with a parser state built from 'defaultDynFlags'. If we pass the dynflags of the module instead, the right options are turned on on while parsing the identifer (in this case -XMagicHash), and the parse succeeds. - - - - - 5c0d35d7 by David Waern at 2010-04-10T10:54:06+00:00 Rename startGhc into withGhc - - - - - dca081fa by Simon Hengel at 2010-04-12T19:09:16+00:00 Add documentation for interactive examples - - - - - c7f26bfa by David Waern at 2010-04-13T00:51:51+00:00 Slight fix to the documentation of examples - - - - - 06eb7c4c by David Waern at 2010-04-13T00:57:05+00:00 Rename Interactive Examples into Examples (and simplify explanation) - - - - - 264830cb by David Waern at 2010-05-10T20:07:27+00:00 Update CHANGES with info about 2.6.1 - - - - - 8e5d4514 by Simon Hengel at 2010-04-18T18:16:54+00:00 Add unit tests for parser - - - - - 68297f40 by David Waern at 2010-05-10T21:53:37+00:00 Improve testsuite README - - - - - f04eb6e4 by David Waern at 2010-05-11T19:14:31+00:00 Re-organise the testsuite structure - - - - - a360f710 by David Waern at 2010-05-11T19:18:03+00:00 Shorten function name - - - - - 1d5dd359 by David Waern at 2010-05-11T21:40:02+00:00 Update runtests.hs following testsuite re-organisation - - - - - ffebe217 by David Waern at 2010-05-11T21:40:10+00:00 Update runtests.hs to use base-4.2.0.1 - - - - - 635de402 by David Waern at 2010-05-11T21:41:11+00:00 Update runparsetests.hs following testsuite reorganisation - - - - - 72137910 by Ian Lynagh at 2010-05-06T20:43:06+00:00 Fix build - - - - - 1a80b76e by Ian Lynagh at 2010-05-06T22:25:29+00:00 Remove redundant import - - - - - 1031a80c by Simon Peyton Jones at 2010-05-07T13:21:09+00:00 Minor wibbles to HsBang stuff - - - - - dd8e7fe5 by Ian Lynagh at 2010-05-08T15:22:00+00:00 GHC build system: Follow "rm" variable changes - - - - - 7f5e6748 by David Waern at 2010-05-13T11:53:02+00:00 Fix build with GHC 6.12.2 - - - - - 7953d4d8 by David Waern at 2010-05-13T18:45:01+00:00 Fixes to comments only - - - - - 8ae8eb64 by David Waern at 2010-05-13T18:57:26+00:00 ModuleMap -> IfaceMap - - - - - 1c3eadc6 by David Waern at 2010-05-13T19:03:13+00:00 Fix whitespace style issues - - - - - e96783c0 by David Waern at 2010-05-13T19:08:53+00:00 Fix comment - - - - - c998a78b by David Waern at 2010-05-13T19:39:00+00:00 Position the module header the same way everywhere Silly, but nice with some consistency :-) - - - - - b48a714e by David Waern at 2010-05-13T19:41:32+00:00 Position of module header, this time in the HTML backends - - - - - f9bfb12e by David Waern at 2010-05-13T19:43:05+00:00 Two newlines between declarations in Main - - - - - 071d44c7 by David Waern at 2010-05-13T19:44:21+00:00 Newlines in Convert - - - - - 036346db by David Waern at 2010-05-13T19:46:47+00:00 Fix a few stylistic issues in H.InterfaceFile - - - - - f0b8379e by David Waern at 2010-05-13T19:47:53+00:00 Add newlines to H.ModuleTree - - - - - 27409f8e by David Waern at 2010-05-13T19:51:10+00:00 Fix stylistic issues in H.Utils - - - - - 24774a11 by David Waern at 2010-05-13T20:00:43+00:00 Structure H.Types better - - - - - 7b6f5e40 by David Waern at 2010-05-13T20:01:04+00:00 Remove bad Arbitrary instance - - - - - fac9f1f6 by David Waern at 2010-05-13T20:05:50+00:00 Get rid of H.Utils.pathJoin and use System.FilePath.joinPath instead - - - - - fe6d00c4 by David Waern at 2010-05-13T20:51:55+00:00 Export a couple of more types from the API - - - - - b2e33a5f by David Waern at 2010-05-13T21:27:51+00:00 Improve doc comment for Interface - - - - - c585f2ce by David Waern at 2010-05-13T21:30:14+00:00 Improve documentation of Haddock.Interface - - - - - e6791db2 by David Waern at 2010-05-13T22:07:35+00:00 Remove meaningless comments - - - - - 7801b390 by David Waern at 2010-05-14T17:53:33+00:00 Remove unused modules - - - - - f813e937 by David Waern at 2010-05-14T17:55:17+00:00 Re-direct compilation output to a temporary directory Also add a flag --no-tmp-comp-dir that can be used to get the old behaviour of writing compilation files to GHC's output directory (default "."). - - - - - e56737ec by David Waern at 2010-05-14T18:06:11+00:00 Wibble - - - - - e40b0447 by David Waern at 2010-05-14T19:01:52+00:00 Move flag evaluation code from Main to Haddock.Options Determining the value of "singular" flags (by e.g. taking the last occurrence of the flag) and other flag evaluation should done in Haddock.Options which is the module that is supposed to define the command line interface. This makes Main a bit easier on the eyes as well. - - - - - 27091f57 by David Waern at 2010-05-14T19:05:10+00:00 Wibble - - - - - c658cf61 by David Waern at 2010-05-14T19:06:49+00:00 Re-order things in Haddock.Options a bit - - - - - 8cfdd342 by David Waern at 2010-05-14T19:20:29+00:00 De-tabify Haddock.Options and fix other whitespace issues - - - - - 0df16b62 by David Waern at 2010-05-14T19:25:07+00:00 Improve comments - - - - - 80b38e2b by David Waern at 2010-05-14T19:26:42+00:00 Whitespace police - - - - - fe580255 by David Waern at 2010-05-14T19:31:23+00:00 Wibbles to comments - - - - - a2b43fad by David Waern at 2010-05-14T20:24:32+00:00 Move some more flag functions to Haddock.Options - - - - - 3f895547 by David Waern at 2010-05-14T20:37:12+00:00 Make renderStep a top-level function in Main - - - - - 5cdca11d by David Waern at 2010-05-14T20:39:27+00:00 Spelling in comment - - - - - ad98d14c by David Waern at 2010-05-14T20:40:26+00:00 Comment fixes - - - - - 0bb9218f by David Waern at 2010-05-14T20:49:01+00:00 Whitespace police - - - - - 0f0a533f by David Waern at 2010-05-15T16:42:29+00:00 Improve description of --dump-interface - - - - - 5b2833ac by David Waern at 2010-05-15T17:16:53+00:00 Document --no-tmp-comp-dir - - - - - 8160b170 by David Waern at 2010-05-15T17:18:59+00:00 Wibble - - - - - 570dbe33 by David Waern at 2010-05-18T21:15:38+00:00 HLint police - - - - - 204e425f by David Waern at 2010-05-18T21:16:30+00:00 HLint police - - - - - 6db657ac by David Waern at 2010-05-18T21:16:37+00:00 Wibble - - - - - b942ccd7 by Simon Marlow at 2010-06-02T08:27:30+00:00 Interrupted disappeared in GHC 6.13 (GHC ticket haskell/haddock#4100) - - - - - 3b94a819 by Simon Marlow at 2010-06-02T08:45:08+00:00 Allow base-4.3 - - - - - c5a1fb7c by Simon Marlow at 2010-06-02T09:03:04+00:00 Fix compilation with GHC 6.13 - - - - - 6181296c by David Waern at 2010-06-08T21:09:05+00:00 Display name of prologue file when parsing it fails - - - - - 7cbc6f60 by Ian Lynagh at 2010-06-13T16:20:25+00:00 Remove redundant imports - - - - - 980c804b by Simon Marlow at 2010-06-22T08:41:50+00:00 isLocalAndTypeInferenced: fix for local module names overlapping package modules - - - - - d74d4a12 by Simon Marlow at 2010-06-23T12:03:27+00:00 Unresolved identifiers in Doc get replaced with DocMonospaced rather than plain strings - - - - - d8546783 by Simon Marlow at 2010-06-30T12:45:17+00:00 LaTeX backend (new options: --latex, --latex-style=<style>) - - - - - 437afa9e by David Waern at 2010-07-01T12:02:44+00:00 Fix a few stylistic whitespace issues in LaTeX backend - - - - - 85bc1fae by David Waern at 2010-07-01T15:42:45+00:00 Make runtest.hs work with GHC 6.12.3 (we should really stop hard coding this) - - - - - 7d2eb86f by David Waern at 2010-07-01T15:43:33+00:00 Update test following Simon's patch to render unresolved names in monospaced font - - - - - 08fcbcd2 by David Waern at 2010-07-01T16:12:18+00:00 Warning police - - - - - d04a8d7a by David Waern at 2010-07-04T14:53:39+00:00 Fix a bug in attachInstances We didn't look for instance docs in all the interfaces of the package. This had the effect of instance docs not always showing up under a declaration. I took the opportunity to clean up the code in H.I.AttachInstances a bit as well. More cleanup is needed, however. - - - - - d10344eb by Simon Hengel at 2010-07-10T09:19:04+00:00 Add missing dependencies to cabal file - - - - - 24090531 by Mark Lentczner at 2010-03-21T04:51:16+00:00 add exports to Xhtml modules - - - - - 84f9a333 by Mark Lentczner at 2010-04-03T19:14:22+00:00 clean up Doc formatting code - add CSS for lists - renderToString now uses showHtml since prettyHtml messes up <pre> sections - - - - - bebccf52 by Mark Lentczner at 2010-04-04T04:51:08+00:00 tweak list css - - - - - 0c2aeb5e by Mark Lentczner at 2010-04-04T06:24:14+00:00 all decls now generate Html not HtmlTable - ppDecl return Html, and so now do all of the functions it calls - added some internal tables to some decls, which is wrong, and will have to be fixed - decl "Box" functions became "Elem" functions to make clear they aren't in a table anymore (see Layout.hs) - docBox went away, as only used in one place (and its days are numbered) - cleaned up logic in a number of places, removed dead code - added maybeDocToHtml which simplified a number of places in the code - - - - - dbf73e6e by Mark Lentczner at 2010-04-05T05:02:43+00:00 clean up processExport and place a div around each decl - - - - - e25b7e9f by Mark Lentczner at 2010-04-10T21:23:21+00:00 data decls are now a sequence of paragraphs, not a table - - - - - 89ee0294 by Mark Lentczner at 2010-04-10T21:29:16+00:00 removed commented out code that can't be maintained - - - - - d466f536 by Mark Lentczner at 2010-04-12T04:56:27+00:00 removed declWithDoc and cleaned up data decls in summary - - - - - ed755832 by Mark Lentczner at 2010-04-12T05:07:53+00:00 merge in markupExample changes - - - - - c36f51fd by Mark Lentczner at 2010-04-25T04:56:37+00:00 made record fields be an unordList, not a table - - - - - ed3a28d6 by Mark Lentczner at 2010-04-25T05:23:28+00:00 fixed surround of instance and constructor tables - - - - - 0e35bbc4 by Mark Lentczner at 2010-04-25T05:36:59+00:00 fix class member boxes in summary - - - - - 5041749b by Mark Lentczner at 2010-04-25T05:38:35+00:00 remove unused bodyBox - - - - - e91724db by Mark Lentczner at 2010-04-25T06:26:10+00:00 fixed javascript quoting/escpaing issue - - - - - f4abbb73 by Mark Lentczner at 2010-05-03T23:04:31+00:00 adjust css for current markup - - - - - e75fec4c by Mark Lentczner at 2010-05-04T06:14:34+00:00 added assoicated types and methods back into class decls - - - - - 84169323 by Mark Lentczner at 2010-05-24T13:13:42+00:00 merge in changes from the big-whitespace cleanup - - - - - 3c1c872e by Mark Lentczner at 2010-06-11T21:03:58+00:00 adjust synopsis and bottom bar spacing - - - - - 3c1f9ef7 by Mark Lentczner at 2010-06-11T21:14:44+00:00 fix missing space in "module" lines in synoposis - - - - - 9a137e6d by Mark Lentczner at 2010-06-11T21:34:08+00:00 changed tt elements to code elements - - - - - 50f71ef1 by Mark Lentczner at 2010-06-11T23:27:46+00:00 factored out ppInstances - - - - - 3b9a9de5 by Mark Lentczner at 2010-06-17T17:36:01+00:00 push single constructors (newtype) onto line with decl - - - - - e0f8f2ec by Mark Lentczner at 2010-06-17T22:20:56+00:00 remove <++> connector - - - - - 56c075dd by Mark Lentczner at 2010-07-13T05:26:21+00:00 change to new page structure - - - - - 04be6ca7 by Mark Lentczner at 2010-07-14T04:21:55+00:00 constructors and args as dl lists, built in Layout.hs - - - - - 65aeafc2 by Mark Lentczner at 2010-07-14T05:38:32+00:00 better interface to subDecls - - - - - 72032189 by Mark Lentczner at 2010-07-14T07:04:10+00:00 made subDecl tables looks just so - - - - - b782eca2 by Mark Lentczner at 2010-07-14T16:00:54+00:00 convert args to SubDecl format - - - - - cc75e98f by Mark Lentczner at 2010-07-14T16:28:53+00:00 convert instances to SubDecl - - - - - 34e2aa5a by Mark Lentczner at 2010-07-14T21:07:32+00:00 removing old table cruft from Layout.hs - - - - - d5810d95 by Mark Lentczner at 2010-07-14T21:54:58+00:00 methods and associated types in new layout scheme - - - - - 65ef9579 by Mark Lentczner at 2010-07-14T23:43:42+00:00 clean up synopsis lists - - - - - e523318f by Mark Lentczner at 2010-07-15T05:02:26+00:00 clean up of anchors - - - - - 1215dfc5 by Mark Lentczner at 2010-07-15T23:53:01+00:00 added two new themes and rough css switcher - - - - - 7f0fd36f by Mark Lentczner at 2010-07-16T04:57:38+00:00 fixed package catpion, added style menu - - - - - 0dd4999c by Mark Lentczner at 2010-07-16T20:12:39+00:00 new output for mini_ pages - - - - - 64b2810b by Mark Lentczner at 2010-07-16T20:58:41+00:00 reformat index-frames - - - - - 3173f555 by Mark Lentczner at 2010-07-16T22:41:53+00:00 convert index to new markup - - - - - b0a4b7c9 by Mark Lentczner at 2010-07-17T04:07:22+00:00 convert index.html to new markup, adjust module markup - - - - - 8261ae1e by Mark Lentczner at 2010-07-17T05:07:29+00:00 classing styling of ancillary pages - - - - - 2a4fb025 by Mark Lentczner at 2010-07-17T05:11:45+00:00 clean up Layout.hs: no more vanillaTable - - - - - 87eec685 by Mark Lentczner at 2010-07-17T05:35:16+00:00 clean up Util.hs - - - - - d304e9b0 by Mark Lentczner at 2010-07-17T05:38:50+00:00 qualify import of XHtml as XHtml - - - - - 7dc05807 by Mark Lentczner at 2010-07-17T06:17:53+00:00 factored out head element generation - - - - - 9cdaec9e by Mark Lentczner at 2010-07-17T06:44:54+00:00 refactored out main page body generation - - - - - 8a51019e by Mark Lentczner at 2010-07-17T06:48:20+00:00 moved footer into only place that used it - - - - - efa479da by Mark Lentczner at 2010-07-17T18:48:30+00:00 styling auxillary pages for tibbe and snappy themes - - - - - 81de5509 by Mark Lentczner at 2010-07-18T04:41:38+00:00 fixed alphabet on index page, and styling of it and packages in module lists - - - - - 20718c1a by Mark Lentczner at 2010-07-18T05:34:29+00:00 cleaned up div functions in Layout.hs - - - - - 60d50453 by Mark Lentczner at 2010-07-18T05:48:39+00:00 added content div to main pages - - - - - ed16561c by Mark Lentczner at 2010-07-18T06:12:22+00:00 add .doc class to documentation blocks - - - - - f5c781b0 by Mark Lentczner at 2010-07-19T05:20:53+00:00 refactoring of anchor ID and fragment handling - - - - - a69a93bf by Mark Lentczner at 2010-07-19T05:35:55+00:00 remove an explicit bold tag - replace with .def class - - - - - d76c7225 by Mark Lentczner at 2010-07-19T06:56:15+00:00 rename Haddock.Backends.Xhtml.Util to Utils - - - - - 5a58c0da by David Waern at 2010-07-21T13:30:54+00:00 Remove trailing whitespace in Haddock.Backends.Xhtml - - - - - 0652aa17 by David Waern at 2010-07-21T13:33:21+00:00 Align a few comments - - - - - 785776c3 by David Waern at 2010-07-21T13:39:04+00:00 Remove trailing whitespace in H.B.X.Decl - - - - - 71a30710 by David Waern at 2010-07-21T13:44:27+00:00 Remove more trailing whitespace - - - - - 38750394 by David Waern at 2010-07-21T13:50:43+00:00 Style police - - - - - 3023d940 by David Waern at 2010-07-21T14:01:22+00:00 Style police in H.B.X.Decl - - - - - df16e9e6 by David Waern at 2010-07-21T14:14:45+00:00 Style police in H.B.X.DocMarkup - - - - - 6020e321 by David Waern at 2010-07-21T14:17:32+00:00 More style police - - - - - 86ad8bf5 by David Waern at 2010-07-21T14:21:02+00:00 Style police in H.B.Xhtml - - - - - aea27d03 by David Waern at 2010-07-21T14:42:03+00:00 Fix warnings in LaTeX backend - - - - - 2aff34a9 by David Waern at 2010-07-21T14:50:46+00:00 Style police in LaTeX backend (mainly more newlines) - - - - - e517162d by David Waern at 2010-07-21T15:05:47+00:00 Doc sections in Main - - - - - b971aa0c by David Waern at 2010-07-21T15:06:17+00:00 Trailing whitespace in Documentation.Haddock - - - - - f11628fb by David Waern at 2010-07-21T15:07:06+00:00 Trailing whitespace in Haddock.Convert - - - - - cbaf284c by David Waern at 2010-07-21T15:08:11+00:00 Style police in Haddock.GhcUtils - - - - - 71feb77b by David Waern at 2010-07-21T15:09:06+00:00 Style police in Haddock.InterfaceFile - - - - - 0a9c80e6 by David Waern at 2010-07-21T15:11:33+00:00 Whitespace police - - - - - 6168376c by David Waern at 2010-07-21T15:16:35+00:00 Style police in Haddock.Utils - - - - - 9fe4dd90 by David Waern at 2010-07-21T15:19:31+00:00 Add -fwarn-tabs - - - - - a000d752 by Mark Lentczner at 2010-07-20T17:25:52+00:00 move CSS Theme functions into Themes.hs - - - - - b52b440f by Mark Lentczner at 2010-07-20T17:29:35+00:00 add Thomas Schilling's theme - - - - - e43fa7e8 by Mark Lentczner at 2010-07-21T04:49:34+00:00 correct icon used with Snappy theme - - - - - ba5092d3 by Mark Lentczner at 2010-07-21T04:56:47+00:00 apply Tibbe's updates to his theme - - - - - 7804eef6 by Mark Lentczner at 2010-07-21T05:15:49+00:00 space between "Style" and the downward triangle - - - - - 7131d4c6 by Mark Lentczner at 2010-07-21T17:43:35+00:00 merge with David's source cleanups - - - - - ee65f1cb by David Waern at 2010-07-22T16:50:46+00:00 Fix a bug where we allowed --hoogle, --latex, etc without input files - - - - - e413ff7a by David Waern at 2010-07-22T17:21:58+00:00 Improve function name - - - - - a0fd14f3 by Simon Marlow at 2010-06-30T15:34:32+00:00 fix warnings - - - - - 31f73d2a by David Waern at 2010-07-22T19:29:41+00:00 Solve conflicts - - - - - d563b4a5 by Simon Marlow at 2010-06-30T15:34:37+00:00 fix warning - - - - - 412b6469 by David Waern at 2010-07-22T19:31:28+00:00 Solve conflict - - - - - 35174b94 by Ian Lynagh at 2010-07-06T17:27:16+00:00 Follow mkPState argument order change - - - - - b5c3585c by Simon Marlow at 2010-07-14T08:49:21+00:00 common up code for instance rendering - - - - - d8009560 by Simon Marlow at 2010-07-14T12:37:11+00:00 fix warnings - - - - - a6d88695 by David Waern at 2010-07-24T15:33:33+00:00 Fix build with ghc < 6.13 - - - - - 94cf9de1 by David Waern at 2010-07-24T15:34:37+00:00 Remove conflict left-over - - - - - 313b15c0 by Mark Lentczner at 2010-07-21T22:09:04+00:00 reorganization of nhaddock.css with tibbe - - - - - 9defed80 by Mark Lentczner at 2010-07-21T22:42:14+00:00 further cleanup of nhaddock.css, float TOC, support aux. pages - - - - - 6d944c1b by Mark Lentczner at 2010-07-22T06:22:23+00:00 remove old HTML backend - - - - - b3e8cba5 by Mark Lentczner at 2010-07-22T06:43:32+00:00 remove --html-help support - it was old, out-of-date, and mostly missing - - - - - d2654a08 by Mark Lentczner at 2010-07-22T21:45:34+00:00 tweaks to nhaddock.css - - - - - f73b285c by Mark Lentczner at 2010-07-23T06:19:35+00:00 command like processing for theme selection The bulk of the change is threadnig the selected theme set through functions in Xhtml.hs so that the selected themes can be used when generating the page output. There isn't much going on in most of these changes, just passing it along. The real work is all done in Themes.hs. - - - - - 8bddc90d by Mark Lentczner at 2010-07-23T06:58:31+00:00 drop --themes support, add named theme support decided that --themes was silly - no one would do that, just use multiple --theme arguments made --theme a synonym for --css and -c made those arguments, if no file is found, look up the argument as the name of a built in theme all of this let's haddock be invoked with "--theme=classic" for example. - - - - - 20cafd4f by Mark Lentczner at 2010-07-23T17:44:29+00:00 rename --default-themes to --built-in-themes - - - - - 0fe41307 by Mark Lentczner at 2010-07-23T18:33:02+00:00 tweaks to theme for info table, headings, and tables - - - - - cba4fee0 by Mark Lentczner at 2010-07-23T19:13:59+00:00 tweaks for dl layout, though still not used - - - - - 463fa294 by Mark Lentczner at 2010-07-23T21:07:19+00:00 tweak look of mini pages, keywords, and preblocks - - - - - 5472fc02 by Mark Lentczner at 2010-07-24T05:36:15+00:00 slide out Synopsis drawer - - - - - 9d5d5de5 by Mark Lentczner at 2010-07-24T06:02:42+00:00 extend package header and footer to edges of page - - - - - a47c91a2 by Mark Lentczner at 2010-07-24T06:28:44+00:00 fields are def lists, tweak css for style menu, mini pages, arguments - - - - - ca20f23b by Mark Lentczner at 2010-07-24T16:55:22+00:00 excisting last vestiges of the --xhtml flag - - - - - 71fb012e by Mark Lentczner at 2010-07-25T18:47:49+00:00 change how collapsing sections are done make whole .caption be the target improve javascript for class toggling have plus/minus images come from .css, not img tags - - - - - c168c8d3 by Mark Lentczner at 2010-07-26T00:32:05+00:00 reorganize files in the html lib data dir - - - - - 93324301 by Mark Lentczner at 2010-07-26T01:27:42+00:00 cleaned up Themes.hs - - - - - ad3b5dd4 by Mark Lentczner at 2010-07-26T02:39:15+00:00 make module list use new collapsers - - - - - 1df9bfc6 by Mark Lentczner at 2010-07-27T19:09:25+00:00 remove Tibbe theme - - - - - 8b9b01b3 by Mark Lentczner at 2010-07-27T20:04:03+00:00 move themes into html dir with .theme and .std-theme extensions - - - - - a7beb965 by Mark Lentczner at 2010-07-27T21:06:34+00:00 give a class to empty dd elements so they can be hidden - - - - - a258c117 by Mark Lentczner at 2010-07-27T21:23:58+00:00 remove custom version of copyFile in Xhtml.hs - - - - - b70dba6e by Mark Lentczner at 2010-07-27T22:12:45+00:00 apply margin changes to pre and headings as per group decision, and small cleanups - - - - - e6f722a2 by Mark Lentczner at 2010-07-28T00:03:12+00:00 make info block and package bar links be floatable by placing them first in the dom tree - - - - - c8278867 by Mark Lentczner at 2010-07-28T19:01:18+00:00 styling source links on declarations - - - - - 88fdc399 by Mark Lentczner at 2010-07-29T01:12:46+00:00 styling tweaks don't generate an empty li for absent style menu in links area update css for Classic and Snappy to handle: dl lists links in package header and in declarations floating of links and info block in package and module headers - - - - - 8a75b213 by Ian Lynagh at 2010-07-30T20:21:46+00:00 Fix build in GHC tree - - - - - ce8e18b3 by Simon Hengel at 2010-08-03T18:37:26+00:00 Adapt paths to data files in cabal file - - - - - 9701a455 by Simon Hengel at 2010-08-07T13:20:27+00:00 Add missing dependency to cabal file - - - - - 01b838d1 by Mark Lentczner at 2010-07-30T20:19:40+00:00 improved synopsis drawer: on click, not hover - - - - - 7b6f3e59 by Mark Lentczner at 2010-07-30T23:38:55+00:00 put the synopsis back in the other themes - - - - - 7b2904c9 by Mark Lentczner at 2010-08-11T11:11:26+00:00 close arrows on expanded synopsis drawer - - - - - ea19e177 by Mark Lentczner at 2010-08-12T21:16:45+00:00 width and font changes removed the max width restrictions on the page as a whole and the synopsis made the main font size smaller (nominally 14pt) and then tweaked most font sizes (relative) to be more consistent - - - - - 5ced00c0 by Mark Lentczner at 2010-08-13T15:09:55+00:00 implemented YUI's CSS font approach - - - - - 2799c548 by Mark Lentczner at 2010-08-13T15:11:59+00:00 adjusted margin to 2em, 1 wasn't enough - - - - - 58f06893 by Mark Lentczner at 2010-08-13T15:48:44+00:00 removed underlining on hover for named anchors headings in interface lost thier a element, no need, just put id on heading css for a elements now only applies to those with href attribute - - - - - 7aced4c4 by Mark Lentczner at 2010-08-13T15:50:22+00:00 more space between elements - - - - - 5a3c1cce by Mark Lentczner at 2010-08-13T16:43:43+00:00 adjusted font sizes of auxilary pages per new scheme - - - - - 487539ef by Mark Lentczner at 2010-08-13T21:43:41+00:00 add Frames button and clean up frames.html - - - - - c1a140b6 by Mark Lentczner at 2010-08-13T22:17:48+00:00 move frames button to js - - - - - b0bdb68e by Mark Lentczner at 2010-08-14T03:44:46+00:00 build style menu in javascript moved to javascript, so as to not polute the content with the style menu removed menu building code in Themes.hs removed onclick in Utils.hs changed text of button in header from "Source code" to "Source" more consistent with links in rest of page - - - - - 43ab7120 by Mark Lentczner at 2010-08-16T15:15:37+00:00 font size and margin tweaks - - - - - c0b68652 by Mark Lentczner at 2010-08-17T18:19:52+00:00 clean up collapser logics javascript code for collapasble sections cleaned up rewrote class utilities in javascript to be more robust refactored utilities for generating collapsable sections made toc be same color as synopsis module list has needed clear attribute in CSS - - - - - 5d573427 by Mark Lentczner at 2010-08-17T23:06:02+00:00 don't collapse entries in module list when clicking on links - - - - - 8c307c4a by Mark Lentczner at 2010-08-17T23:21:43+00:00 add missing data file to .cabal - - - - - 414bcfcf by Mark Lentczner at 2010-08-17T23:28:47+00:00 remove synopsis when in frames - - - - - ba0fa98a by Mark Lentczner at 2010-08-18T16:16:11+00:00 layout tweeks - mini page font size, toc color, etc. - - - - - 63c1bed1 by Mark Lentczner at 2010-08-18T19:50:02+00:00 margin fiddling - - - - - c311c094 by Mark Lentczner at 2010-08-20T01:37:55+00:00 better synopsis handling logic - no flashing - - - - - f1fe5fa8 by Mark Lentczner at 2010-08-20T01:41:06+00:00 fix small layout issues mini frames should have same size top heading give info block dts some padding so they don't collide in some browsers - - - - - 0de84d77 by Mark Lentczner at 2010-08-20T02:13:09+00:00 made style changing and cookies storage robust - - - - - 1ef064f9 by Thomas Schilling at 2010-08-04T13:12:22+00:00 Make synopsis frame behave properly in Firefox. In Firefox, pressing the back button first reverted the synopsis frame, and only clicking the back button a second time would update the main frame. - - - - - dd1c9a94 by Mark Lentczner at 2010-08-21T01:46:19+00:00 remove Snappy theme - - - - - 2353a90d by Mark Lentczner at 2010-08-25T05:16:19+00:00 fix occasional v.scroll bars on pre blocks (I think) - - - - - 459b8bf1 by Simon Hengel at 2010-08-08T10:12:45+00:00 Add createInterfaces' (a more high-level alternative to createInterfaces) to Haddock API - - - - - b1b68675 by David Waern at 2010-08-26T20:31:58+00:00 Follow recent API additions with some refactorings Simon Hegel's patch prompted me to do some refactorings in Main, Haddock.Documentation and Haddock.Interface. - - - - - 264d4d67 by David Waern at 2010-08-26T21:40:59+00:00 Get rid of GhcModule and related cruft We can get everything we need directly from TypecheckedModule. - - - - - 0feacec2 by Mark Lentczner at 2010-08-26T23:44:13+00:00 fixed CSS for ordered lists and def lists in doc blocks - - - - - 2997e0c2 by Mark Lentczner at 2010-08-26T23:45:03+00:00 support both kinds of enumerated lists in doc markup The documentation for Haddock says enumerated lists can use either of (1) first item 2. second item The second form wasn't actually supported - - - - - 5d4ddeec by Mark Lentczner at 2010-08-27T21:29:48+00:00 fix broken header link margins - - - - - 614456ba by Mark Lentczner at 2010-08-27T22:16:19+00:00 fix table of contents CSS - - - - - 03f329a2 by David Waern at 2010-08-28T16:36:09+00:00 Update tests following switch to the Xhtml backend - - - - - ca689fa2 by Mark Lentczner at 2010-08-28T18:25:16+00:00 fix def lists - - - - - 18e1d3d2 by Mark Lentczner at 2010-08-28T18:26:18+00:00 push footer to bottom of window - - - - - b0ab8d82 by David Waern at 2010-08-28T22:04:32+00:00 Whitespace police - - - - - 2d217977 by David Waern at 2010-08-29T12:44:45+00:00 Remove Snappy data files - - - - - 01e27d5f by David Waern at 2010-08-29T13:03:28+00:00 Add source entity path to --read-interface You can now use this flag like this: --read-interface=<html path>,<source entity path>,<.haddock file> By "source entity path" I mean the same thing that is specified with the --source-entity flag. The purpose of this is to be able to specify the source entity path per package, to allow source links to work in the presence of cross-package documentation. When given two arguments or less the --read-interface flag behaves as before. - - - - - 20bf4aaa by David Waern at 2010-08-29T13:11:03+00:00 Naming wibbles - - - - - ad22463f by Mark Lentczner at 2010-08-29T15:14:54+00:00 make portability block be a table - solves layout issues - - - - - 97bd1ae6 by Mark Lentczner at 2010-08-29T15:17:42+00:00 update golden test for Test due to portability box change - - - - - d37e139e by Mark Lentczner at 2010-08-29T17:07:17+00:00 move TOC and Info blocks down 0.5em to improve layout issue w/Test.hs - - - - - acf52501 by David Waern at 2010-08-29T17:32:36+00:00 Allow building with ghc < 6.16 - - - - - 1cb34ed8 by Ian Lynagh at 2010-07-24T23:18:49+00:00 Flatten the dynflags before parsing - - - - - b36845b4 by Ian Lynagh at 2010-07-24T23:26:49+00:00 Follow flattenLanguageFlags -> flattenExtensionFlags rename - - - - - 7f7fcc7e by David Waern at 2010-08-29T17:46:23+00:00 Use flattenExtensionFlags with ghc >= 6.13 only - - - - - 13cf9411 by Ian Lynagh at 2010-08-01T18:09:54+00:00 Make the main haddock script versioned, and make plain "haddock" a symlink - - - - - 495cbff2 by Ian Lynagh at 2010-08-18T18:57:24+00:00 Fix installation in the GHC build system Data-files are now in subdirectories, so we need to handle that - - - - - 88ebab0a by Ian Lynagh at 2010-08-18T19:43:53+00:00 GHC build system: Add all the data files to BINDIST_EXTRAS - - - - - 65837172 by David Waern at 2010-08-29T20:12:34+00:00 Update Test - - - - - 094bbaa2 by David Waern at 2010-08-29T20:55:14+00:00 Revert update to Test - - - - - a881cfb3 by David Waern at 2010-08-31T18:24:15+00:00 Bump version number - - - - - 1fc8a3eb by David Waern at 2010-08-31T22:32:27+00:00 Update ANNOUNCE - - - - - ee1df9d0 by David Waern at 2010-08-31T22:33:11+00:00 Update CHANGES - - - - - 394cc854 by David Waern at 2010-08-31T22:33:23+00:00 Update interface file versioning to work with ghc 6.14/15 - - - - - 7d03b79b by David Waern at 2010-08-31T22:36:00+00:00 Update test output following version change - - - - - a48d82d1 by Mark Lentczner at 2010-09-01T04:29:35+00:00 sort options in doc to match --help output removed --html-help option, as it is no longer supported - - - - - 06561aeb by Mark Lentczner at 2010-09-01T05:29:32+00:00 update options documentation rewrote doc for --html added doc for --theme and --built-in-themes added --use-contents and --gen-contents - - - - - 57dea832 by Mark Lentczner at 2010-09-01T05:31:27+00:00 slight wording change about Frames mode - - - - - fa1f6da3 by David Waern at 2010-09-01T10:57:44+00:00 Update doc configure script to find docbook stylesheets on arch linux - - - - - addff770 by David Waern at 2010-09-01T11:02:29+00:00 Wibble - - - - - 8399006d by David Waern at 2010-09-01T11:19:21+00:00 Replace ghci> with >>> in example syntax - - - - - 35074cf8 by David Waern at 2010-09-01T19:03:27+00:00 Improve docs for --no-tmp-comp-dir - - - - - 0f8f8cfd by David Waern at 2010-09-02T11:22:27+00:00 Add a list of contributors to the user guide Break out everyone thanked in the `Acknowledgements` chapter into a separate contributor list and add everyone from `darcs show authors`. We consider everyone who is thanked to be a contributor as a conservative estimation :-) I have added some more contributors that I know about, who were not in the darcs history, but others may be missing. So please add anyone that you think is missing from the list. - - - - - 42ccf099 by David Waern at 2010-09-02T11:29:22+00:00 Update copyright years in license - - - - - 0d560479 by David Waern at 2010-09-02T11:38:52+00:00 Update release instructions - - - - - 72ab7796 by David Waern at 2010-09-02T19:27:08+00:00 Add a note to ANNOUNCE - - - - - bf9d9c5d by David Waern at 2010-09-02T19:27:48+00:00 H.Utils needs FFI on Win+MinGW - - - - - 048ae44a by Mark Lentczner at 2010-09-04T23:19:47+00:00 make TOC group header identifiers validate - - - - - 8c6faf36 by Simon Michael at 2010-09-22T07:12:34+00:00 add hints for cleaner darcs show authors output - - - - - 9909bd17 by Simon Michael at 2010-09-22T17:58:06+00:00 print haddock coverage info on stdout when generating docs A module's haddockable items are its exports and the module itself. The output is lightly formatted so you can align the :'s and sort for readability. - - - - - 6da72171 by David Waern at 2010-10-03T21:31:24+00:00 Style wibble - - - - - 2f8d8e4d by Tobias Brandt at 2010-08-27T07:01:21+00:00 adding the option to fully qualify identifiers - - - - - 833be6c6 by Tobias Brandt at 2010-08-27T15:50:28+00:00 adding support for local and relative name qualification - - - - - df15c4e9 by Tobias Brandt at 2010-08-27T15:56:37+00:00 corrected qualification help message - - - - - 449e9ce1 by David Waern at 2010-10-16T17:34:30+00:00 Solve conflicts - - - - - 3469bda5 by David Waern at 2010-10-16T18:42:40+00:00 Use "qual" as an abbreviation for qualification instead of "quali" for consistency - - - - - 97c2d728 by David Waern at 2010-10-16T18:47:07+00:00 Style police - - - - - ce14fbea by David Waern at 2010-10-16T21:15:25+00:00 Style police - - - - - fdf29e9d by David Waern at 2010-10-17T00:30:44+00:00 Add a pointer to the style guide - - - - - 8e6b44e8 by rrnewton at 2010-10-24T03:19:28+00:00 Change to index pages: include an 'All' option even when subdividing A-Z. - - - - - 755b131c by David Waern at 2010-11-14T19:39:36+00:00 Bump version - - - - - d0345a04 by David Waern at 2010-11-14T19:41:59+00:00 TAG 2.8.1 - - - - - f6221508 by Simon Peyton Jones at 2010-09-13T09:53:00+00:00 Adapt to minor changes in internal GHC functions - - - - - 1290713d by Ian Lynagh at 2010-09-15T10:37:18+00:00 Remove duplicate Outputable instance for Data.Map.Map - - - - - 87f69eef by Ian Lynagh at 2010-09-21T15:01:10+00:00 Bump GHC dep upper bound - - - - - af36e087 by Ian Lynagh at 2010-09-21T15:12:02+00:00 Fix up __GLASGOW_HASKELL__ tests - - - - - ad67716c by Ian Lynagh at 2010-09-21T20:31:35+00:00 Don't build haddock is HADDOCK_DOCS is NO - - - - - 63b3f1f5 by Ian Lynagh at 2010-09-21T21:39:51+00:00 Fixes for when HADDOCK_DOCS=NO - - - - - e92bfa42 by Ian Lynagh at 2010-09-29T21:15:38+00:00 Fix URL creation on Windows: Use / not \ in URLs. Fixes haskell/haddock#4353 - - - - - 66c55e05 by Ian Lynagh at 2010-09-30T17:03:34+00:00 Tidy up haddock symlink installation In particular, it now doesn't get created if we aren't installing haddock. - - - - - 549b5556 by Ian Lynagh at 2010-10-23T21:17:14+00:00 Follow extension-flattening change in GHC - - - - - d7c2f72b by David Waern at 2010-11-14T20:17:55+00:00 Bump version to 2.8.2 - - - - - 6989a3a9 by David Waern at 2010-11-14T20:26:01+00:00 Solve conflict - - - - - 055c6910 by Ian Lynagh at 2010-09-22T15:36:20+00:00 Bump GHC dep - - - - - c96c0763 by Simon Marlow at 2010-10-27T11:09:44+00:00 follow changes in the GHC API - - - - - 45907129 by David Waern at 2010-11-07T14:00:58+00:00 Update the HCAR entry - - - - - 61940b95 by David Waern at 2010-11-07T14:07:34+00:00 Make the HCAR entry smaller - - - - - aa590b7d by David Waern at 2010-11-14T21:30:59+00:00 Update HCAR entry with November 2010 version - - - - - 587f9847 by David Waern at 2010-11-14T23:48:17+00:00 Require ghc >= 7.0 - - - - - ff5c647c by David Waern at 2010-11-14T23:49:09+00:00 TAG 2.8.2 - - - - - 937fcb4f by David Waern at 2010-11-14T23:49:45+00:00 Solve conflict - - - - - 8e5d0c1a by David Waern at 2010-11-15T21:09:50+00:00 Remove code for ghc < 7 - - - - - 3d47b70a by David Waern at 2010-11-15T21:11:06+00:00 Fix bad merge - - - - - 7f4a0d8a by David Waern at 2010-11-15T21:13:57+00:00 Remove more ghc < 7 code - - - - - 9ee34b50 by David Waern at 2010-11-15T21:31:25+00:00 Match all AsyncExceptions in exception handler - - - - - 42849c70 by David Waern at 2010-11-15T21:35:31+00:00 Just say "internal error" instead of "internal Haddock or GHC error" - - - - - c88c809b by David Waern at 2010-11-15T21:44:19+00:00 Remove docNameOcc under the motto "don't name compositions" - - - - - b798fc7c by David Waern at 2010-11-15T23:27:13+00:00 Wibble - - - - - 2228197e by David Waern at 2010-11-15T23:28:24+00:00 Rename the HCAR entry file - - - - - 8a3f9090 by David Waern at 2010-11-16T00:05:29+00:00 Remove Haskell 2010 extensions from .cabal file - - - - - c7a0c597 by David Waern at 2010-11-16T00:10:28+00:00 Style wibbles - - - - - cde707a5 by David Waern at 2010-11-16T00:12:00+00:00 Remove LANGUAGE ForeignFunctionInterface pragmas - - - - - 1dbda8ed by David Waern at 2010-11-16T00:17:21+00:00 Make a little more use of DoAndIfThenElse - - - - - 4c45ff6e by David Waern at 2010-11-16T00:59:41+00:00 hlint police - - - - - d2feaf09 by David Waern at 2010-11-16T01:14:15+00:00 hlint police - - - - - 99876e97 by David Waern at 2010-11-20T19:06:00+00:00 Haddock documentation updates - - - - - 65ce6987 by David Waern at 2010-11-20T19:42:51+00:00 Follow the style guide closer in Haddock.Types and improve docs - - - - - 28ca304a by tob.brandt at 2010-11-20T17:04:40+00:00 add full qualification for undocumented names - - - - - d61341e3 by David Waern at 2010-11-20T20:04:15+00:00 Re-structure qualification code a little - - - - - 0057e4d6 by David Waern at 2010-11-20T20:07:55+00:00 Re-order functions - - - - - d7279afd by David Waern at 2010-11-21T03:39:54+00:00 Add BangPatterns to alex and happy source files - - - - - 629fe60e by tob.brandt at 2010-11-23T23:35:11+00:00 documentation for qualification - - - - - 37031cee by David Waern at 2010-11-23T21:06:44+00:00 Update CHANGES - don't mention 2.8.2, we won't release it - - - - - f2489e19 by David Waern at 2010-12-01T21:57:11+00:00 Update deps of runtests.hs to work with ghc 7.0.1 - - - - - d3657e9a by David Waern at 2010-12-01T22:04:57+00:00 Make tests compile with ghc 7.0.1 - - - - - a2f09d9b by David Waern at 2010-12-01T22:06:59+00:00 Update tests following version bump - - - - - 50883ebb by David Waern at 2010-12-06T14:09:18+00:00 Update tests following recent changes - - - - - fc2fadeb by David Waern at 2010-12-06T14:17:29+00:00 Add a flag --pretty-html for rendering indented html with newlines - - - - - 30832ef2 by David Waern at 2010-12-06T14:17:35+00:00 Use --pretty-html when running the test suite. Makes it easier to compare output - - - - - a0b81b31 by David Waern at 2010-12-06T14:18:27+00:00 Wibble - - - - - 3aaa23fe by David Waern at 2010-12-06T14:19:29+00:00 Haddockify ppHtml comments - - - - - 24bb24f0 by David Waern at 2010-12-06T14:23:15+00:00 Remove --debug. It was't used, and --verbosity should take its place - - - - - 6bc076e5 by David Waern at 2010-12-06T14:25:37+00:00 Rename golden-tests into html-tests. "golden tests" sounds strange - - - - - 53301e55 by David Waern at 2010-12-06T14:26:26+00:00 QUALI -> QUAL in the description --qual for consistency - - - - - 98b6affb by David Waern at 2010-12-06T21:54:02+00:00 Bump version - - - - - 371bf1b3 by David Waern at 2010-12-06T22:08:55+00:00 Update tests following version bump - - - - - 25be762d by David Waern at 2010-12-06T22:21:03+00:00 Update CHANGES - - - - - 7c7dac71 by David Waern at 2010-12-06T22:33:43+00:00 Update ANNOUNCE - - - - - 30d7a5f2 by Simon Peyton Jones at 2010-11-15T08:38:38+00:00 Alex generates BangPatterns, so make Lex.x accept them (It'd be better for Alex to generate this pragma.) - - - - - 605e8018 by Simon Marlow at 2010-11-17T11:37:24+00:00 Add {-# LANGUAGE BangPatterns #-} to mollify GHC - - - - - a46607ba by David Waern at 2010-12-07T14:08:10+00:00 Solve conflicts - - - - - b28cda66 by David Waern at 2010-12-09T20:41:35+00:00 Docs: Mention that \ is a special character in markup - - - - - a435bfdd by Ian Lynagh at 2010-11-17T14:01:19+00:00 TAG GHC 7.0.1 release - - - - - 5a15a05a by David Waern at 2010-12-11T17:51:19+00:00 Fix indentation problem - - - - - 4232289a by Lennart Kolmodin at 2010-12-17T18:32:03+00:00 Revise haddock.cabal given that we now require ghc-7 default-language should be Haskell2010, slight new semantics for extensions. Rewrite into clearer dependencies of base and Cabal. - - - - - a36302dc by David Waern at 2010-12-19T17:12:37+00:00 Update CHANGES - - - - - 7c8b85b3 by David Waern at 2010-12-19T17:14:24+00:00 Bump version - - - - - cff22813 by Ian Lynagh at 2011-01-05T18:24:27+00:00 Write hoogle output in utf8; fixes GHC build on Windows - - - - - c7e762ea by David Waern at 2011-01-22T00:00:35+00:00 Put title outside doc div when HTML:fying title+prologue Avoids indenting the title, and makes more sense since the title is not a doc string anyway. - - - - - 5f639054 by David Waern at 2011-01-22T16:09:44+00:00 Fix spelling error - contributed by Marco Silva - - - - - c11dce78 by Ian Lynagh at 2011-01-07T02:33:11+00:00 Follow GHC build system changes - - - - - 101cfaf5 by David Waern at 2011-01-08T14:06:44+00:00 Bump version - - - - - af62348b by David Waern at 2011-01-08T14:07:07+00:00 TAG 2.9.2 - - - - - 4d1f6461 by Ian Lynagh at 2011-01-07T23:06:57+00:00 Name the haddock script haddock-ghc-7.0.2 instead of haddock-7.0.2; haskell/haddock#4882 "7.0.2" looked like a haddock version number before - - - - - 8ee4d5d3 by Simon Peyton Jones at 2011-01-10T17:31:12+00:00 Update Haddock to reflect change in hs_tyclds field of HsGroup - - - - - 06f3e3db by Ian Lynagh at 2011-03-03T15:02:37+00:00 TAG GHC 7.0.2 release - - - - - 7de0667d by David Waern at 2011-03-10T22:47:13+00:00 Update CHANGES - - - - - 33a9f1c8 by David Waern at 2011-03-10T22:47:31+00:00 Fix build with ghc 7.0.1 - - - - - 4616f861 by David Waern at 2011-03-10T22:47:50+00:00 TAG 2.9.2-actual - - - - - 0dab5e3c by Simon Hengel at 2011-04-08T15:53:01+00:00 Set shell script for unit tests back to work - - - - - 85c54dee by Simon Hengel at 2011-04-08T16:01:24+00:00 Set unit tests back to work Here "ghci>" was still used instead of ">>>". - - - - - 1cea9b78 by Simon Hengel at 2011-04-08T16:25:36+00:00 Update runtests.hs for GHC 7.0.2 - - - - - 8e5b3bbb by Simon Hengel at 2011-04-08T16:28:49+00:00 Update Haddock version in *.html.ref - - - - - 2545e955 by Simon Hengel at 2011-04-08T17:09:28+00:00 Add support for blank lines in the result of examples Result lines that only contain the string "<BLANKLINE>" are treated as a blank line. - - - - - adf64d2e by Simon Hengel at 2011-04-08T17:36:50+00:00 Add documentation for "support for blank lines in the result of examples" - - - - - c51352ca by David Waern at 2011-05-21T23:57:56+00:00 Improve a haddock comment - - - - - 7419cf2c by David Waern at 2011-05-22T15:41:52+00:00 Use cabal's test suite support to run the test suite This gives up proper dependency tracking of the test script. - - - - - 7770070c by David Waern at 2011-05-22T01:45:44+00:00 We don't need to send DocOptions nor a flag to mkExportItems - - - - - 9d95b7b6 by David Waern at 2011-05-22T21:39:03+00:00 Fix a bug - - - - - 1f93699b by David Waern at 2011-05-22T21:40:21+00:00 Break out fullContentsOf, give it a better name and some documentation The documentation describes how we want this function to eventually behave, once we have fixed a few problems with the current implementation. - - - - - 9a86432f by David Waern at 2011-05-22T21:53:52+00:00 Fix some stylistic issues in mkExportItems - - - - - c271ff0c by David Waern at 2011-05-22T22:09:11+00:00 Indentation - - - - - 93e602b1 by David Waern at 2011-06-10T01:35:31+00:00 Add git commits since switchover: darcs format (followed by a conflict resolution): commit 6f92cdd12d1354dfbd80f8323ca333bea700896a Merge: f420cc4 28df3a1 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 19 17:54:34 2011 +0100 Merge remote branch 'origin/master' into ghc-generics commit 28df3a119f770fdfe85c687dd73d5f6712b8e7d0 Author: Max Bolingbroke <batterseapower at hotmail.com> Date: Sat May 14 22:37:02 2011 +0100 Unicode fix for getExecDir on Windows commit 89813e729be8bce26765b95419a171a7826f6d70 Merge: 6df3a04 797ab27 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 9 11:55:17 2011 +0100 Merge branch 'ghc-new-co' commit 6df3a040da3dbddee67c6e30a892f87e6b164383 Author: Ian Lynagh <igloo at earth.li> Date: Sun May 8 17:05:50 2011 +0100 Follow changes in SDoc commit f420cc48b9259f0b1afd2438b12f9a2bde57053d Author: Jose Pedro Magalhaes <jpm at cs.uu.nl> Date: Wed May 4 17:31:52 2011 +0200 Adapt haddock to the removal of HsNumTy and TypePat. commit 797ab27bdccf39c73ccad374fea265f124cb52ea Merge: 1d81436 5a91450 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:05:03 2011 +0100 Merge remote branch 'origin/master' into ghc-new-co commit 1d8143659a81cf9611668348e33fd0775c7ab1d2 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:03:46 2011 +0100 Wibbles for ghc-new-co branch commit 5a91450e2ea5a93c70bd3904b022445c9cc82488 Author: Ian Lynagh <igloo at earth.li> Date: Fri Apr 22 00:51:56 2011 +0100 Follow defaultDynFlags change in GHC - - - - - 498da5ae by David Waern at 2011-06-11T00:33:33+00:00 * Merge in git patch from Michal Terepeta >From 6fc71d067738ef4b7de159327bb6dc3d0596be29 Mon Sep 17 00:00:00 2001 From: Michal Terepeta <michal.terepeta at gmail.com> Date: Sat, 14 May 2011 19:18:22 +0200 Subject: [PATCH] Follow the change of TypeSig in GHC. This follows the change in GHC to make TypeSig take a list of names (instead of just one); GHC ticket haskell/haddock#1595. This should also improve the Haddock output in case the user writes a type signature that refers to many names: -- | Some comment.. foo, bar :: ... will now generate the expected output with one signature for both names. - - - - - 094607fe by Ian Lynagh at 2011-06-17T19:10:29+01:00 Fix build - - - - - 8fa35740 by Ian Lynagh at 2011-06-26T21:06:40+01:00 Bump GHC dep to allow 7.2 - - - - - e4d2ca3c by Ian Lynagh at 2011-07-07T23:06:28+01:00 Relax base dep - - - - - b948fde9 by Ian Lynagh at 2011-07-28T16:39:45+01:00 GHC build system: Don't install the datafiles twice - - - - - f82f6d70 by Simon Marlow at 2011-08-11T12:08:15+01:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - b341cc12 by Max Bolingbroke at 2011-08-22T20:25:27+01:00 Fix compilation with no-pred-ty GHC - - - - - 30494581 by Max Bolingbroke at 2011-08-23T10:20:54+01:00 Remaining fixes for PredTy removal - - - - - 0b197138 by Max Bolingbroke at 2011-08-26T08:27:45+01:00 Rename factKind to constraintKind - - - - - a379bec5 by Max Bolingbroke at 2011-09-04T12:54:47+01:00 Deal with change to IParam handling in GHC - - - - - f94e421b by Max Bolingbroke at 2011-09-06T17:34:31+01:00 Adapt Haddock for the ConstraintKind extension changes - - - - - 8821e5cc by Max Bolingbroke at 2011-09-09T08:24:59+01:00 Ignore associated type defaults (just as we ignore default methods) - - - - - 31a0afd4 by Max Bolingbroke at 2011-09-09T09:06:00+01:00 Merge branch 'no-pred-ty' of ssh://darcs.haskell.org/srv/darcs/haddock into no-pred-ty - - - - - dd3b530a by Max Bolingbroke at 2011-09-09T14:10:25+01:00 Merge branch 'no-pred-ty' Conflicts: src/Haddock/Convert.hs - - - - - 5f25ec96 by Max Bolingbroke at 2011-09-09T14:10:40+01:00 Replace FactTuple with ConstraintTuple - - - - - cd30b9cc by David Waern at 2011-09-26T02:17:55+02:00 Bump to version 2.9.3 - - - - - 4fbfd397 by Max Bolingbroke at 2011-09-27T14:55:21+01:00 Follow changes to BinIface Name serialization - - - - - 92257d90 by David Waern at 2011-09-30T23:45:07+02:00 Fix problem with test files not added to distribution tarball - - - - - 00255bda by David Waern at 2011-09-30T23:48:24+02:00 Merge branch 'development' - - - - - 5421264f by David Waern at 2011-10-01T01:25:39+02:00 Merge in darcs patch from Simon Meier: Wed Jun 1 19:41:16 CEST 2011 iridcode at gmail.com * prettier haddock coverage info The new coverage info rendering uses less horizontal space. This reduces the number of unnecessary line-wrappings. Moreover, the most important information, how much has been documented already, is now put up front. Hopefully, this makes it more likely that a library author is bothered by the low coverage of his modules and fixes that issue ;-) - - - - - 07d318ef by David Waern at 2011-10-01T01:34:10+02:00 Use printException instead of deprecated printExceptionAndWarnings - - - - - 40d52ee4 by David Waern at 2011-10-01T01:41:13+02:00 Merge in darcs pach: Mon Apr 11 18:09:54 JST 2011 Liyang HU <haddock at liyang.hu> * Remember collapsed sections in index.html / haddock-util.js - - - - - 279d6dd4 by David Waern at 2011-10-01T01:55:45+02:00 Merge in darcs patch: Joachim Breitner <mail at joachim-breitner.de>**20110619201645 Ignore-this: f6c51228205b0902ad5bfad5040b989a As reported on http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=578301, generating the global index takes much too long if type-level (with lots of auto-generated types) is installed. The patch avoids a quadratic runtime in the subfunction getIfaceIndex of ppHtmlIndex by using a temporary set. Runtime improvement observed here from 25.36s to 2.86s. - - - - - d1612383 by David Waern at 2011-10-01T01:56:48+02:00 Merge branch 'development' - - - - - 347520c1 by David Waern at 2011-10-01T01:56:54+02:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9a0c95e8 by David Waern at 2011-10-01T02:19:10+02:00 Improve .cabal file - - - - - 6967dc64 by Ian Lynagh at 2011-10-01T01:34:06+01:00 Follow changes to ForeignImport/ForeignExport in GHC - - - - - 565cb26b by Simon Marlow at 2011-10-04T00:15:04+02:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - 8b74f512 by David Waern at 2011-10-04T00:18:17+02:00 Requre ghc >= 7.2 - - - - - 271d360c by David Waern at 2011-10-04T00:22:50+02:00 Bump version to 2.9.4 - - - - - 37f3edb0 by David Waern at 2011-10-06T02:30:21+02:00 Add alex and happy to build-tools. - - - - - 7ac2bb6e by David Terei at 2011-10-12T14:02:55-07:00 Add safe haskell indication to haddock output - - - - - 42c91a47 by David Terei at 2011-10-12T14:06:03-07:00 Fix CSS issue with info table not being contained in module header - - - - - 0eddab6c by David Terei at 2011-10-12T14:06:58-07:00 Add safe haskell indication to haddock output - - - - - 3df058eb by David Terei at 2011-10-12T14:07:07-07:00 Fix CSS issue with info table not being contained in module header - - - - - a40a6c3f by David Waern at 2011-10-22T11:29:06+02:00 Bump .haddock file version since the format has changed recently - - - - - 8a6254be by David Waern at 2011-10-22T11:30:42+02:00 Merge branch 'development' - - - - - 642e3e02 by David Waern at 2011-10-23T21:23:39+02:00 Sort import list - - - - - 36371cf8 by David Waern at 2011-10-23T22:48:18+02:00 Remove NEW_GHC_LAYOUT conditional. - - - - - 5604b499 by David Waern at 2011-10-27T00:15:03+02:00 Add --print-ghc-path. - - - - - 463499fa by David Waern at 2011-10-27T00:16:22+02:00 Make testsuite able to find its dependencies automatically. - - - - - a3506172 by Ryan Newton at 2011-11-05T05:59:58-04:00 Improved declNames internal error. Added a case to handle DocD. - - - - - 001b8baf by David Waern at 2011-11-05T20:37:29+01:00 Rename copy.hs -> accept.hs. - - - - - 55d808d3 by David Waern at 2011-11-05T23:30:02+01:00 Fix build. - - - - - deb5c3be by David Waern at 2011-11-06T00:01:47+01:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9b663554 by David Waern at 2011-11-06T00:03:45+01:00 Merge https://github.com/rrnewton/haddock - - - - - 1abb0ff6 by David Waern at 2011-11-06T01:20:37+01:00 Use getDeclMainBinder instead of declNames. - - - - - 4b005c01 by David Waern at 2011-11-06T19:09:53+01:00 Fix build. - - - - - c2c51bc7 by Ian Lynagh at 2011-11-06T23:01:33+00:00 Remove -DNEW_GHC_LAYOUT in ghc.mk - - - - - f847d703 by Jose Pedro Magalhaes at 2011-11-11T09:07:39+00:00 New kind-polymorphic core This big patch implements a kind-polymorphic core for GHC. The current implementation focuses on making sure that all kind-monomorphic programs still work in the new core; it is not yet guaranteed that kind-polymorphic programs (using the new -XPolyKinds flag) will work. For more information, see http://haskell.org/haskellwiki/GHC/Kinds - - - - - 7d7c3b09 by Jose Pedro Magalhaes at 2011-11-16T21:42:22+01:00 Follow changes to tuple sorts in master - - - - - 8430e03e by Simon Peyton Jones at 2011-11-17T10:20:27+00:00 Remove redundant imports - - - - - d1b06832 by Ian Lynagh at 2011-11-19T01:33:21+00:00 Follow GHC build system change to the way we call rm - - - - - 9e2230ed by David Waern at 2011-11-24T15:00:24+01:00 Fix a bug in test runner and get rid of regex-compat dependency. - - - - - 52039b21 by David Waern at 2011-11-24T23:55:36+01:00 Avoid haskell98 dependency in test - - - - - 92e1220d by David Waern at 2011-11-25T00:03:33+01:00 Avoid depency on regex-compat also in accept.hs. - - - - - ddac6b6f by David Waern at 2011-11-25T02:13:38+01:00 Accept test output. - - - - - 5a720455 by David Waern at 2011-11-25T02:16:20+01:00 Some more changes to test scripts. - - - - - 170a9004 by David Waern at 2011-11-25T02:30:41+01:00 Add flag --interface-version. - - - - - d225576c by David Waern at 2011-11-25T02:39:26+01:00 Remove #ifs for older compiler versions. - - - - - f0d0a4f5 by David Waern at 2011-11-26T04:20:12+01:00 Give preference to type over data constructors for doc comment links at renaming time. Previously this was done in the backends. Also, warn when a doc comment refers to something that is in scope but which we don't have the .haddock file for. These changes mean we can make DocIdentifier [a] into DocIdentifier a. - - - - - eef0e776 by David Waern at 2011-11-26T17:01:06+01:00 Allow doc comments to link to out-of-scope things (#78). (A bug that should have been fixed long ago.) - - - - - 565ad529 by David Waern at 2011-11-26T19:56:21+01:00 Update tests. - - - - - fb3ce7b9 by David Waern at 2011-11-26T21:44:28+01:00 Cleanup. - - - - - d0328126 by David Waern at 2011-11-26T22:10:28+01:00 Fix module reference bug. - - - - - c03765f8 by David Waern at 2011-12-03T05:20:20+01:00 Slightly better behaviour on top-levels without type signatures. - Docs don't get attached to the next top-level with signature by mistake. - If there's an export list and the top-level is part of it, its doc comment shows up in the documentation. - - - - - 48461d31 by David Waern at 2011-12-03T05:38:10+01:00 Add a test for Unicode doc comments. - - - - - 549c4b4e by David Waern at 2011-12-03T19:07:55+01:00 Cleanup. - - - - - 7bfecf91 by David Waern at 2011-12-03T20:13:08+01:00 More cleanup. - - - - - 14fab722 by Ian Lynagh at 2011-12-12T21:21:35+00:00 Update dependencies and binaryInterfaceVersion - - - - - 469e6568 by Ian Lynagh at 2011-12-18T12:56:16+00:00 Fix (untested) building from source tarball without alex/happy haddock's .cabal file was declaring that it needed alex and happy to build, but in the GHC source tarballs it doesn't. - - - - - 895c9a8c by David Waern at 2011-12-27T12:57:43+01:00 Go back to having a doc, sub and decl map instead of one big decl map. This setup makes more sense since when we add value bindings to the processed declarations (for type inference), we will have multiple declarations which should share documentation. Also, we already have a separate doc map for instances which we can now merge into the main doc map. Another benefit is that we don't need the DeclInfo type any longer. - - - - - 736767d9 by David Waern at 2011-12-27T13:33:41+01:00 Merge ../../../haddock Conflicts: src/Haddock/InterfaceFile.hs - - - - - 20016f79 by David Waern at 2011-12-27T13:57:23+01:00 Bump version. - - - - - 31f276fb by David Waern at 2011-12-27T13:57:32+01:00 Merge ../ghc/utils/haddock - - - - - 95b367cd by David Waern at 2011-12-27T14:57:29+01:00 Update tests following version bump. - - - - - fa3c94cd by David Waern at 2011-12-27T14:57:51+01:00 Get rid of quite unnecessary use of different lists. - - - - - 9c4d3c54 by David Waern at 2011-12-27T15:26:42+01:00 Cleanup. - - - - - 2caf9f90 by David Waern at 2011-12-27T16:18:05+01:00 Wibbles. - - - - - 3757d09b by David Waern at 2011-12-27T20:50:26+01:00 Complete support for inferring types for top-level bindings. - - - - - 53418734 by David Waern at 2011-12-28T15:02:13+01:00 Minor fixes and cleanup. - - - - - 0c9d0385 by Ian Lynagh at 2012-01-03T18:31:29+00:00 Follow rename of Instance to ClsInst in GHC - - - - - c9bc969a by Simon Hengel at 2012-01-12T21:28:14+01:00 Make sure that generated xhtml is valid (close haskell/haddock#186) Thanks to Phyx. - - - - - 836a0b9a by David Waern at 2012-02-01T02:30:05+01:00 Fix bug introduced in my recent refactoring. - - - - - c7d733eb by David Waern at 2012-02-01T02:30:26+01:00 Cleanup mkMaps and avoid quadratic behaviour. - - - - - da3cda8f by David Waern at 2012-02-01T02:56:56+01:00 Require ghc >= 7.4. - - - - - 83a3287e by David Waern at 2012-02-01T02:57:36+01:00 Update CHANGES. - - - - - 93408f0b by Simon Hengel at 2012-02-04T00:48:04+01:00 Add reference renderings - - - - - 49d00d2c by Simon Hengel at 2012-02-04T00:48:25+01:00 Set unit tests for parser back to work - - - - - eb450980 by Simon Hengel at 2012-02-04T00:49:07+01:00 Add .gitignore - - - - - a841602c by Simon Hengel at 2012-02-04T00:49:16+01:00 Add .ghci file - - - - - 8861199d by Simon Hengel at 2012-02-04T00:49:29+01:00 tests/html-tests/copy.hs: Use mapM_ instead of mapM So we do net get a list of () on stdout when running with runhaskell. - - - - - b477d9b5 by Simon Hengel at 2012-02-04T00:49:46+01:00 Remove index files from golden tests - - - - - 9dbda34e by Simon Hengel at 2012-02-04T00:49:57+01:00 Add /tests/html-tests/tests/*index*.ref to .gitignore - - - - - a9434817 by Simon Hengel at 2012-02-04T00:50:04+01:00 Add DocWarning to Doc The Xhtml backend has special markup for that, Hoogle and LaTeX reuse what we have for DocEmphasis. - - - - - de2fb6fa by Simon Hengel at 2012-02-04T00:50:13+01:00 Add support for module warnings - - - - - 0640920e by Simon Hengel at 2012-02-04T00:50:21+01:00 Add tests for module warnings - - - - - 30ce0d77 by Simon Hengel at 2012-02-04T00:50:29+01:00 Add support for warnings - - - - - bb367960 by Simon Hengel at 2012-02-04T00:50:37+01:00 Add tests for warnings - - - - - 6af1dc2d by Simon Hengel at 2012-02-04T00:50:50+01:00 Expand type signatures in export list (fixes haskell/haddock#192) - - - - - a06cbf25 by Simon Hengel at 2012-02-04T00:51:04+01:00 Expand type signatures for modules without explicit export list - - - - - 57dda796 by Simon Hengel at 2012-02-04T00:51:15+01:00 Remove obsolete TODO - - - - - 270c3253 by David Waern at 2012-02-04T00:51:24+01:00 Fix issues in support for warnings. * Match against local names only. * Simplify (it's OK to map over the warnings). - - - - - 683634bd by David Waern at 2012-02-04T00:55:11+01:00 Some cleanup and make sure we filter warnings through exports. - - - - - 210cb4ca by David Waern at 2012-02-04T03:01:30+01:00 Merge branch 'fix-for-186' of https://github.com/sol/haddock into ghc-7.4 - - - - - e8db9031 by David Waern at 2012-02-04T03:07:51+01:00 Style police. - - - - - 261f9462 by David Waern at 2012-02-04T03:20:16+01:00 Update tests. - - - - - 823cfc7c by David Waern at 2012-02-04T03:21:12+01:00 Use mapM_ in accept.hs as well. - - - - - 873dd619 by David Waern at 2012-02-04T03:21:33+01:00 Remove copy.hs - use accept.hs instead. - - - - - 0e31a14a by David Waern at 2012-02-04T03:47:33+01:00 Use <> instead of mappend. - - - - - 2ff7544f by David Waern at 2012-02-04T03:48:55+01:00 Remove code for older ghc versions. - - - - - dacf2786 by David Waern at 2012-02-04T15:52:51+01:00 Clean up some code from last SoC project. - - - - - 00cbb117 by David Waern at 2012-02-04T21:43:49+01:00 Mostly hlint-inspired cleanup. - - - - - 7dc86cc2 by Simon Peyton Jones at 2012-02-06T09:14:41+00:00 Track changes in HsDecls - - - - - f91f82fe by Ian Lynagh at 2012-02-16T13:40:11+00:00 Follow changes in GHC caused by the CAPI CTYPE pragma - - - - - a0ea6b0b by Ian Lynagh at 2012-02-22T02:26:12+00:00 Follow changes in GHC - - - - - b23b07d1 by Simon Peyton Jones at 2012-03-02T16:36:41+00:00 Follow changes in data representation from the big PolyKinds commit - - - - - 43406022 by Simon Hengel at 2012-03-05T11:18:34+01:00 Save/restore global state for static flags when running GHC actions This is necessary if we want to run createInterfaces (from Documentation.Haddock) multiple times in the same process. - - - - - 9fba16fe by Paolo Capriotti at 2012-03-06T10:57:33+00:00 Update .gitignore. - - - - - a9325044 by Simon Peyton Jones at 2012-03-14T17:35:42+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - fd48065a by Iavor Diatchki at 2012-03-15T22:43:35-07:00 Add support for type-level literals. - - - - - 2e8206dd by Simon Peyton Jones at 2012-03-16T14:18:22+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - 93e13319 by Simon Peyton Jones at 2012-03-17T01:04:05+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock Conflicts: src/Haddock/Convert.hs - - - - - d253fa71 by Iavor Diatchki at 2012-03-19T20:12:18-07:00 Merge remote-tracking branch 'origin/master' into type-nats - - - - - fc40acc8 by Iavor Diatchki at 2012-03-19T20:31:27-07:00 Add a missing case for type literals. - - - - - fd2ad699 by Iavor Diatchki at 2012-03-24T13:28:29-07:00 Rename variable to avoid shadowing warning. - - - - - 9369dd3c by Simon Peyton Jones at 2012-03-26T09:14:23+01:00 Follow refactoring of TyClDecl/HsTyDefn - - - - - 38825ca5 by Simon Peyton Jones at 2012-03-26T09:14:37+01:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - 4324ac0f by David Waern at 2012-04-01T01:51:19+02:00 Disable unicode test. - - - - - 3165b750 by David Waern at 2012-04-01T01:51:34+02:00 Take reader environment directly from TypecheckedSource. - - - - - 213b644c by David Waern at 2012-04-01T01:55:20+02:00 Cleanup. - - - - - 3118b4ba by David Waern at 2012-04-01T02:16:15+02:00 Don't filter out unexported names from the four maps - fixes a regression. - - - - - d6524e17 by David Waern at 2012-04-01T02:40:34+02:00 Fix crash when using --qual. Naughty GHC API! - - - - - ea3c43d8 by Henning Thielemann at 2012-04-01T13:03:07+02:00 add QualOption type for distinction between qualification argument given by the user and the actual qualification for a concrete module - - - - - 5422ff05 by Henning Thielemann at 2012-04-01T16:25:02+02:00 emit an error message when the --qual option is used incorrectly - - - - - 026e3404 by David Waern at 2012-04-01T18:10:30+02:00 Don't crash on unicode strings in doc comments. - - - - - ce006632 by David Waern at 2012-04-01T20:13:35+02:00 Add test for --ignore-all-exports flag/ignore-exports pragma. - - - - - 6e4dd33c by David Waern at 2012-04-01T20:21:03+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.4 - - - - - 734ae124 by Henning Thielemann at 2012-04-01T20:22:10+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - 622f9ba5 by David Waern at 2012-04-01T21:26:13+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 55ce17cb by Henning Thielemann at 2012-04-01T22:03:25+02:00 'abbreviate' qualification style - basic support Currently we ignore the package a module is imported from. This means that a module import would shadow another one with the same module name from a different package. - - - - - c85314ef by David Waern at 2012-04-01T22:05:12+02:00 Check qualification option before processing modules. - - - - - ae4b626c by Henning Thielemann at 2012-04-02T00:19:36+02:00 abbreviated qualification: use Packages.lookupModuleInAllPackages for finding the package that a module belongs to - - - - - 60bdbcf5 by Henning Thielemann at 2012-04-02T00:25:31+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - df44301d by Henning Thielemann at 2012-04-02T00:29:05+02:00 qualification style 'abbreviated' -> 'aliased' - - - - - f4192a64 by David Waern at 2012-04-02T01:05:47+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 7ba09067 by David Terei at 2012-04-04T15:08:21-07:00 Fix reporting of modules safe haskell mode (#5989) - - - - - d0cc33d0 by David Terei at 2012-04-06T15:50:41+01:00 Fix reporting of modules safe haskell mode (#5989) - - - - - 6e3434c5 by Simon Peyton Jones at 2012-04-20T18:37:46+01:00 Track changes in HsSyn - - - - - 22014ed0 by Simon Peyton Jones at 2012-05-11T22:45:15+01:00 Follow changes to LHsTyVarBndrs - - - - - d9a07b24 by David Waern at 2012-05-15T01:46:35+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - a6c4ebc6 by David Waern at 2012-05-16T02:18:32+02:00 Update CHANGES. - - - - - 8e181d29 by David Waern at 2012-05-16T02:27:56+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - e358210d by David Waern at 2012-05-16T02:35:33+02:00 Mention the new aliased --qual mode in CHANGES. - - - - - efd36a28 by David Waern at 2012-05-16T21:33:13+02:00 Bump version number. - - - - - d6b3af14 by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for deprecated record field - - - - - 927f800e by Simon Hengel at 2012-05-17T19:08:20+02:00 Use >>= instead of fmap and join - - - - - 048b41d5 by Simon Hengel at 2012-05-17T19:08:20+02:00 newtype-wrap Doc nodes for things that may have warnings attached - - - - - e3a89fc3 by Simon Hengel at 2012-05-17T19:08:20+02:00 Attach warnings to `Documentation` type - - - - - 5d4cc43d by Simon Hengel at 2012-05-17T19:08:20+02:00 Simplify lookupWarning - - - - - cf8ae69d by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for haskell/haddock#205 - - - - - cb409b19 by Simon Peyton Jones at 2012-05-25T08:30:11+01:00 Follow changes in LHsTyVarBndrs - - - - - 2d5f4179 by Simon Hengel at 2012-05-26T19:21:29+02:00 Add Applicative instance for (GenRnM a) - - - - - e4373060 by Simon Hengel at 2012-05-26T19:21:33+02:00 Use a map for warnings, as suggested by @waern - - - - - 597a68c7 by Simon Hengel at 2012-05-27T08:48:24+02:00 Add an optional label to URLs - - - - - ef1ac7fe by Simon Hengel at 2012-05-27T08:48:24+02:00 Add support for hyperlink labels to parser - - - - - 41f2adce by Simon Hengel at 2012-05-27T08:48:24+02:00 Add golden test for hyperlinks - - - - - 83d5e764 by Simon Hengel at 2012-05-27T08:50:02+02:00 Use LANGUAGE pragmas instead of default-extensions in cabal file - - - - - ddb755e5 by Simon Hengel at 2012-05-27T08:50:02+02:00 Fix typo in comment - - - - - 110676b4 by Simon Hengel at 2012-05-27T08:50:02+02:00 Add a type signature for a where-binding - - - - - 7d9ba2a0 by Ian Lynagh at 2012-06-12T14:38:01+01:00 Follow changes in GHC - - - - - 47c704f2 by Ian Lynagh at 2012-06-12T18:52:16+01:00 Follow changes in GHC - - - - - e1efe1ab by Simon Peyton Jones at 2012-06-13T17:25:29+01:00 Follow changes for the implementation of implicit parameters - - - - - 69abc81c by Ian Lynagh at 2012-06-19T22:52:58+01:00 Follow changes in base - - - - - 9d074a21 by Paolo Capriotti at 2012-06-22T18:26:47+01:00 Use right docMap to get decl documentation. - - - - - e3292ef6 by Ian Lynagh at 2012-07-15T01:31:19+01:00 Follow changes in GHC - - - - - ceae56b0 by Ian Lynagh at 2012-07-16T21:22:48+01:00 Fix haddock following some GHC changes Passing _|_ as the Settings for defaultDynFlags no longer works well enough - - - - - 9df72735 by Paolo Capriotti at 2012-07-19T16:49:32+01:00 Forward port changes from stable. - - - - - 572f5fcf by Ian Lynagh at 2012-07-19T20:38:26+01:00 Merge branch 'master' of darcs.haskell.org:/srv/darcs//haddock - - - - - 9195aca4 by Paolo Capriotti at 2012-07-20T10:27:28+01:00 Update dependencies. - - - - - 33db3923 by Ian Lynagh at 2012-07-20T17:54:43+01:00 Build with GHC 7.7 - - - - - 925a2cea by David Waern at 2012-07-23T16:50:40+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.6 Conflicts: src/Haddock/InterfaceFile.hs - - - - - d710ef97 by David Waern at 2012-07-23T16:52:07+02:00 Bump version number. - - - - - eb0c2f83 by David Waern at 2012-07-23T16:57:58+02:00 Update CHANGES. - - - - - b3f56943 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Hide "internal" instances This fixes haskell/haddock#37 (http://trac.haskell.org/haddock/ticket/37) Precisely, we show an instance iff its class and all the types are exported by non-hidden modules. - - - - - a70aa412 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Tests for hiding instances (#37) - - - - - c0f4aa58 by Simon Hengel at 2012-07-27T13:00:13+03:00 Add an other test for hiding instances (#37) - - - - - a7ed6268 by Ian Lynagh at 2012-08-07T14:48:13+01:00 Follow changes in GHC - - - - - 0ab30d38 by Ian Lynagh at 2012-08-13T22:12:27+01:00 Improve haddock memory usage - - - - - 0eaa4e30 by Ian Lynagh at 2012-08-13T23:58:46+01:00 Improve haddock memory usage - - - - - 659d26cf by Ian Lynagh at 2012-08-14T13:16:48+01:00 Remove some temporary pragmas I accidentally recorded - - - - - d97fceb6 by Simon Hengel at 2012-08-25T13:19:34+02:00 Add missing dependency to library - - - - - 4c910697 by Simon Hengel at 2012-08-28T07:39:14+02:00 Move .ghci to project root - - - - - fc3c601a by Simon Hengel at 2012-08-28T07:39:14+02:00 accept.hs: Ignore some files - - - - - 1af9b984 by Simon Hengel at 2012-08-28T07:40:04+02:00 Update reference renderings (bump version) - - - - - 980dc253 by Simon Hengel at 2012-08-28T07:40:32+02:00 Update reference renderings (remove links for ()) - - - - - 33651dbf by Simon Hengel at 2012-08-28T07:41:50+02:00 Update documentation of `runInteractiveProcess` in reference rendering - - - - - 7ab25078 by David Waern at 2012-09-07T10:38:50+02:00 Merge branch 'hiddenInstances2' of http://github.com/feuerbach/haddock into ghc-7.6 - - - - - c3de3a4b by David Waern at 2012-09-07T14:29:27+02:00 Follow changes in GHC. - - - - - 298c43ac by David Waern at 2012-09-07T14:59:24+02:00 Update CHANGES. - - - - - e797993a by David Waern at 2012-09-07T15:21:30+02:00 Update ANNOUNCE. - - - - - d0b44790 by David Waern at 2012-09-07T15:22:43+02:00 Merge branch 'hidden-instances' into ghc-7.6 - - - - - 41a4adc8 by Simon Hengel at 2012-09-08T12:08:37+02:00 Update doc/README - - - - - 71ad1040 by Simon Hengel at 2012-09-08T12:17:17+02:00 Add documentation for URL labels - - - - - 9bb41afd by Simon Peyton Jones at 2012-09-20T18:14:26+01:00 Follow data type changes in the tc-untouchables branch Relating entirely to SynTyConRhs - - - - - b8139bfa by Simon Hengel at 2012-09-21T14:24:16+02:00 Disable Unicode test for now - - - - - a5fafdd7 by Simon Hengel at 2012-09-21T14:35:45+02:00 Update TypeOperators test for GHC 7.6.1 Type operators can't be used as type variables anymore! - - - - - 6ccf0025 by Simon Hengel at 2012-09-21T16:02:24+02:00 Remove (Monad (Either e)) instance from ref. rendering of CrossPackageDocs I do not really understand why the behavior changed, so I'll open a ticket, so that we can further investigate. - - - - - b5c6c138 by Ian Lynagh at 2012-09-27T02:00:57+01:00 Follow changes in GHC build system - - - - - b98eded0 by David Waern at 2012-09-27T15:37:02+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 76cc2051 by David Waern at 2012-09-27T15:48:19+02:00 Update hidden instances tests. - - - - - aeaa1c59 by David Waern at 2012-09-28T10:21:32+02:00 Make API buildable with GHC 7.6. - - - - - d76be1b0 by Simon Peyton Jones at 2012-09-28T15:57:05+01:00 Merge remote-tracking branch 'origin/master' into tc-untouchables - - - - - a1922af8 by David Waern at 2012-09-28T19:50:20+02:00 Fix spurious superclass constraints bug. - - - - - bc41bdbb by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove old examples - - - - - bed7d3dd by Simon Hengel at 2012-10-01T11:30:51+02:00 Adapt parsetests for GHC 7.6.1 - - - - - dcdb22bb by Simon Hengel at 2012-10-01T11:30:51+02:00 Add test-suite section for parsetests to cabal file + get rid of HUnit dependency - - - - - 1e5263c9 by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove test flag from cabal file This was not really used. - - - - - 4beee98b by David Waern at 2012-09-28T23:42:28+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 11dd2256 by Ian Lynagh at 2012-10-03T16:17:35+01:00 Follow change in GHC build system - - - - - fbd77962 by Simon Hengel at 2012-10-03T18:49:40+02:00 Remove redundant dependency from cabal file - - - - - 09218989 by Simon Hengel at 2012-10-04T16:03:05+02:00 Fix typo - - - - - 93a2d5f9 by Simon Hengel at 2012-10-04T16:11:41+02:00 Remove trailing whitespace from cabal file - - - - - c8b46cd3 by Simon Hengel at 2012-10-04T16:12:17+02:00 Export Haddock's main entry point from library - - - - - b411e77b by Simon Hengel at 2012-10-04T16:29:46+02:00 Depend on library for executable The main motivation for this is to increase build speed. In GHC's source tree the library is not build, but all modules are now required for the executable, so that GHC's validate will now detect build failures for the library. - - - - - f8f0979f by Simon Hengel at 2012-10-05T00:32:57+02:00 Set executable flag for Setup.lhs - - - - - dd045998 by Simon Hengel at 2012-10-07T16:44:06+02:00 Extend rather than set environment when running HTML tests On some platforms (e.g. ppc64) GHC requires gcc in the path. - - - - - 7b39c3ae by Simon Hengel at 2012-10-07T17:05:45+02:00 cross-package test: re-export IsString instead of Monad There is a monad instance for Q, which is not available on platforms that do not have GHCi support. This caused CrossPackageDocs to fail on those platforms. Re-exporting IsString should test the same thing, but it works on all platforms. - - - - - 0700c605 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Fix some warnings - - - - - f78eca79 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Make -Wall proof - - - - - 6beec041 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Use listToMaybe/fromMaybe instead of safeHead/maybe - - - - - 44b8ce86 by Ian Lynagh at 2012-10-08T21:59:46+01:00 Follow changes in GHC - - - - - 6da5f702 by Simon Hengel at 2012-10-09T11:16:19+02:00 Update .ghci - - - - - 9ac1a1b9 by Kazu Yamamoto at 2012-10-09T12:45:31+02:00 Add markup support for properties - - - - - 1944cb42 by Simon Hengel at 2012-10-09T12:45:31+02:00 Simplify lexing/parsing of properties In contrast to what we do for examples, we do not really need to capture the "prompt" here. - - - - - bffd8e62 by Simon Hengel at 2012-10-09T13:40:14+02:00 Add HTML test for properties - - - - - 2fe9c5cb by Simon Hengel at 2012-10-09T13:40:21+02:00 Add unit tests for properties - - - - - 874e361b by Simon Hengel at 2012-10-09T13:40:33+02:00 Bump interface version - - - - - 2506cc37 by Simon Hengel at 2012-10-09T15:15:04+02:00 Fix parser bug - - - - - 743d2b7d by Simon Hengel at 2012-10-09T15:31:06+02:00 Allow to load interface files with compatible versions - - - - - 981a1660 by Simon Hengel at 2012-10-10T10:32:05+02:00 Export more types from Documentation.Haddock (fixes haskell/haddock#216) - - - - - dff7dc76 by Simon Hengel at 2012-10-10T11:15:19+02:00 Update ANNOUNCE and CHANGES - - - - - edd2bb01 by Simon Hengel at 2012-10-10T11:22:50+02:00 Bump version - - - - - 5039163b by Simon Hengel at 2012-10-10T13:56:04+02:00 Fix typo in documentation - - - - - e4ce34da by Simon Hengel at 2012-10-10T14:28:35+02:00 Add documentation for properties - - - - - 9555ebca by Simon Hengel at 2012-10-11T10:49:04+02:00 Remove redundant if-defs, more source documentation - - - - - 87aa67e1 by Simon Hengel at 2012-10-11T12:32:51+02:00 Adapt cabal file - - - - - c44c1dee by Simon Hengel at 2012-10-11T12:41:58+02:00 Require ghc 7.6 - - - - - 8383bc34 by Simon Hengel at 2012-10-11T12:50:24+02:00 Bump version - - - - - 1030eb38 by Simon Hengel at 2012-10-11T12:55:44+02:00 Update ANNOUNCE and CHANGES - - - - - 74955088 by Simon Hengel at 2012-10-12T09:49:31+02:00 Improve note about `binaryInterfaceVersion` (thanks David) - - - - - ee30f6b7 by Simon Hengel at 2012-10-13T13:40:59+02:00 Update version in html tests, rpm spec file, and user manual - - - - - f2861f18 by Simon Hengel at 2012-10-13T14:40:33+02:00 Remove unused MonadFix constraint - - - - - dfdf1a74 by Simon Hengel at 2012-10-13T15:15:38+02:00 Minor code simplification - - - - - 4ecd1e70 by Simon Hengel at 2012-10-13T15:33:43+02:00 Increase code locality - - - - - f7df5cc9 by Simon Hengel at 2012-10-13T16:03:12+02:00 Minor code simplification - - - - - e737eb6e by Simon Hengel at 2012-10-13T19:03:04+02:00 Handle HsExplicitListTy in renameer (fixes haskell/haddock#213) - - - - - c2dc8f17 by Simon Hengel at 2012-10-13T20:46:31+02:00 Better error messages - - - - - 14d48b4c by Simon Hengel at 2012-10-14T00:21:07+02:00 Simplify RnM type - - - - - 6c2cc547 by Simon Hengel at 2012-10-14T00:23:35+02:00 Simplify lookupRn - - - - - bc77ce85 by Simon Hengel at 2012-10-14T01:51:32+02:00 Organize unite tests hierarchically - - - - - 2306d117 by Simon Hengel at 2012-10-14T10:34:58+02:00 Handle more cases in renameType - - - - - 8a864203 by Simon Hengel at 2012-10-14T11:47:59+02:00 Add mini_HiddenInstances.html.ref and mini_HiddenInstancesB.html.ref - - - - - 3a978eca by Simon Hengel at 2012-10-14T11:49:28+02:00 Add /tests/html-tests/output/ to .gitignore - - - - - db18888a by Simon Hengel at 2012-10-14T13:38:21+02:00 Allow haddock markup in deprecation messages - - - - - e7cfee9f by Simon Hengel at 2012-10-14T14:00:23+02:00 If parsing of deprecation message fails, include it verbatim - - - - - 242a85be by Simon Hengel at 2012-10-14T14:13:24+02:00 Add description for PruneWithWarning test - - - - - 43d33df1 by Simon Hengel at 2012-10-14T15:40:53+02:00 Minor formatting change - - - - - 22768c44 by Simon Hengel at 2012-10-14T16:03:43+02:00 Properly handle deprecation messages for re-exported things (fixes haskell/haddock#220) - - - - - cb4b9111 by Simon Hengel at 2012-10-14T17:30:28+02:00 Add build artifacts for documentation to .gitignore - - - - - 854cd8de by Simon Hengel at 2012-10-14T23:34:51+02:00 unit-tests: Improve readability Add IsString instance for (Doc RdrName) + use <> instead of DocAppend. - - - - - c4446d54 by Simon Hengel at 2012-10-14T23:37:21+02:00 unit-tests: Minor refactoring Rename parse to parseParas. - - - - - 04f2703c by Simon Hengel at 2012-10-15T00:36:42+02:00 Fix typo - - - - - 3d109e44 by Simon Hengel at 2012-10-15T10:30:07+02:00 Add description for DeprecatedReExport test - - - - - 84f0985c by Simon Hengel at 2012-10-15T14:54:19+02:00 Move resources to /resources directory - - - - - a5de7ca6 by Simon Hengel at 2012-10-15T15:46:18+02:00 Move HTML tests to directory /html-test/ - - - - - e21f727d by Simon Hengel at 2012-10-15T19:32:42+02:00 Move HTML reference renderings to /html-test/ref/ - - - - - 3a3c6c75 by Simon Hengel at 2012-10-15T19:32:42+02:00 Copy css, images, etc. on accept - - - - - 40ead6dc by Simon Hengel at 2012-10-15T19:32:42+02:00 Move unit tests to /test directory - - - - - 99a28231 by Simon Hengel at 2012-10-15T19:32:42+02:00 Fix Setup.lhs /usr/bin/runhaskell is not installed on all systems. - - - - - 95faf45e by Simon Hengel at 2012-10-15T19:32:42+02:00 Make test management scripts more robust * They are now independent from the current directory, and hence can be called from everywhere * On UNIX/Linux they can now be run as scripts - - - - - 027aaa2d by Simon Hengel at 2012-10-15T19:53:40+02:00 Add 'dev' flag to cabal file, that builds without -O2 That way --disable-optimization can be used, which decreases build time considerably. - - - - - e0266ede by Simon Hengel at 2012-10-15T20:03:43+02:00 Add test case for "spurious superclass constraints bug" - - - - - 52a2aa92 by Simon Hengel at 2012-10-15T20:28:55+02:00 Adapt accept.lhs, so that it ignores more index files - - - - - 53530781 by Simon Hengel at 2012-10-15T20:49:39+02:00 Rename html-test/runtests.lhs to html-test/run.lhs - - - - - 84518797 by Simon Hengel at 2012-10-15T20:49:39+02:00 Move source files for HTML tests to html-test/src - - - - - a911dc6c by Simon Hengel at 2012-10-15T20:49:39+02:00 Adapt output directory for HTML tests - - - - - d3c15857 by Ian Lynagh at 2012-10-16T16:54:43+01:00 Follow dopt->gopt rename - - - - - 956665a5 by Simon Hengel at 2012-10-18T08:42:48+02:00 Update html-test/README - - - - - 903b1029 by Simon Hengel at 2012-10-18T08:50:26+02:00 Use markdown for html-test/README - - - - - 150b4d63 by Ian Lynagh at 2012-10-18T16:36:00+01:00 Follow changes in GHC: 'flags' has been renamed 'generalFlags' - - - - - 41e04ff9 by Simon Hengel at 2012-11-28T09:54:35+01:00 Export missing types from Documentation.Haddock - - - - - 9be59237 by Ian Lynagh at 2012-11-30T23:20:47+00:00 Update dependencies - - - - - e06842f5 by Simon Hengel at 2012-12-07T20:58:05+01:00 Bump version - - - - - e3dbede0 by Simon Hengel at 2012-12-07T20:58:05+01:00 Add missing test files to cabal file (fixes haskell/haddock#230) - - - - - ee0dcca7 by Simon Hengel at 2012-12-07T20:58:05+01:00 Update CHANGES - - - - - 51601bdb by Simon Peyton Jones at 2012-12-19T17:28:35+00:00 Track changes in UNPACK pragma stuff - - - - - f2573bc1 by Richard Eisenberg at 2012-12-21T20:56:25-05:00 Implement overlapping type family instances. An ordered, overlapping type family instance is introduced by 'type instance where', followed by equations. See the new section in the user manual (7.7.2.2) for details. The canonical example is Boolean equality at the type level: type family Equals (a :: k) (b :: k) :: Bool type instance where Equals a a = True Equals a b = False A branched family instance, such as this one, checks its equations in order and applies only the first the matches. As explained in the note [Instance checking within groups] in FamInstEnv.lhs, we must be careful not to simplify, say, (Equals Int b) to False, because b might later unify with Int. This commit includes all of the commits on the overlapping-tyfams branch. SPJ requested that I combine all my commits over the past several months into one monolithic commit. The following GHC repos are affected: ghc, testsuite, utils/haddock, libraries/template-haskell, and libraries/dph. Here are some details for the interested: - The definition of CoAxiom has been moved from TyCon.lhs to a new file CoAxiom.lhs. I made this decision because of the number of definitions necessary to support BranchList. - BranchList is a GADT whose type tracks whether it is a singleton list or not-necessarily-a-singleton-list. The reason I introduced this type is to increase static checking of places where GHC code assumes that a FamInst or CoAxiom is indeed a singleton. This assumption takes place roughly 10 times throughout the code. I was worried that a future change to GHC would invalidate the assumption, and GHC might subtly fail to do the right thing. By explicitly labeling CoAxioms and FamInsts as being Unbranched (singleton) or Branched (not-necessarily-singleton), we make this assumption explicit and checkable. Furthermore, to enforce the accuracy of this label, the list of branches of a CoAxiom or FamInst is stored using a BranchList, whose constructors constrain its type index appropriately. I think that the decision to use BranchList is probably the most controversial decision I made from a code design point of view. Although I provide conversions to/from ordinary lists, it is more efficient to use the brList... functions provided in CoAxiom than always to convert. The use of these functions does not wander far from the core CoAxiom/FamInst logic. BranchLists are motivated and explained in the note [Branched axioms] in CoAxiom.lhs. - The CoAxiom type has changed significantly. You can see the new type in CoAxiom.lhs. It uses a CoAxBranch type to track branches of the CoAxiom. Correspondingly various functions producing and consuming CoAxioms had to change, including the binary layout of interface files. - To get branched axioms to work correctly, it is important to have a notion of type "apartness": two types are apart if they cannot unify, and no substitution of variables can ever get them to unify, even after type family simplification. (This is different than the normal failure to unify because of the type family bit.) This notion in encoded in tcApartTys, in Unify.lhs. Because apartness is finer-grained than unification, the tcUnifyTys now calls tcApartTys. - CoreLinting axioms has been updated, both to reflect the new form of CoAxiom and to enforce the apartness rules of branch application. The formalization of the new rules is in docs/core-spec/core-spec.pdf. - The FamInst type (in types/FamInstEnv.lhs) has changed significantly, paralleling the changes to CoAxiom. Of course, this forced minor changes in many files. - There are several new Notes in FamInstEnv.lhs, including one discussing confluent overlap and why we're not doing it. - lookupFamInstEnv, lookupFamInstEnvConflicts, and lookup_fam_inst_env' (the function that actually does the work) have all been more-or-less completely rewritten. There is a Note [lookup_fam_inst_env' implementation] describing the implementation. One of the changes that affects other files is to change the type of matches from a pair of (FamInst, [Type]) to a new datatype (which now includes the index of the matching branch). This seemed a better design. - The TySynInstD constructor in Template Haskell was updated to use the new datatype TySynEqn. I also bumped the TH version number, requiring changes to DPH cabal files. (That's why the DPH repo has an overlapping-tyfams branch.) - As SPJ requested, I refactored some of the code in HsDecls: * splitting up TyDecl into SynDecl and DataDecl, correspondingly changing HsTyDefn to HsDataDefn (with only one constructor) * splitting FamInstD into TyFamInstD and DataFamInstD and splitting FamInstDecl into DataFamInstDecl and TyFamInstDecl * making the ClsInstD take a ClsInstDecl, for parallelism with InstDecl's other constructors * changing constructor TyFamily into FamDecl * creating a FamilyDecl type that stores the details for a family declaration; this is useful because FamilyDecls can appear in classes but other decls cannot * restricting the associated types and associated type defaults for a * class to be the new, more restrictive types * splitting cid_fam_insts into cid_tyfam_insts and cid_datafam_insts, according to the new types * perhaps one or two more that I'm overlooking None of these changes has far-reaching implications. - The user manual, section 7.7.2.2, is updated to describe the new type family instances. - - - - - f788d0fb by Simon Peyton Jones at 2012-12-23T15:49:58+00:00 Track changes in HsBang - - - - - ca460a0c by Simon Peyton Jones at 2012-12-23T15:50:28+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - f078fea6 by Simon Peyton Jones at 2013-01-02T08:33:13+00:00 Use InstEnv.instanceSig rather than instanceHead (name change) - - - - - 88e41305 by Simon Peyton Jones at 2013-01-14T17:10:27+00:00 Track change to HsBang type - - - - - e1ad4e19 by Kazu Yamamoto at 2013-02-01T11:59:24+09:00 Merge branch 'ghc-7.6' into ghc-7.6-merge-2 Conflicts: haddock.cabal src/Haddock/Interface/AttachInstances.hs src/Haddock/Interface/Create.hs src/Haddock/Interface/LexParseRn.hs src/Haddock/InterfaceFile.hs src/Haddock/Types.hs Only GHC HEAD can compile this. GHC 7.6.x cannot compile this. Some test fail. - - - - - 62bec012 by Kazu Yamamoto at 2013-02-06T11:12:28+09:00 Using tcSplitSigmaTy in instanceHead' (FIXME is resolved.) - - - - - 013fd2e4 by Kazu Yamamoto at 2013-02-06T17:56:21+09:00 Refactoring instanceHead'. - - - - - 3148ce0e by Kazu Yamamoto at 2013-02-07T17:45:10+09:00 Using new syntax in html-test/src/GADTRecords.hs. - - - - - 626dabe7 by Gabor Greif at 2013-02-15T22:42:01+01:00 Typo - - - - - 1eb667ae by Ian Lynagh at 2013-02-16T17:02:07+00:00 Follow changes in base - - - - - 3ef8253a by Ian Lynagh at 2013-03-01T23:23:57+00:00 Follow changes in GHC's build system - - - - - 1a265a3c by Ian Lynagh at 2013-03-03T23:12:07+00:00 Follow changes in GHC build system - - - - - 69941c79 by Max Bolingbroke at 2013-03-10T09:38:28-07:00 Use Alex 3's Unicode support to properly lex source files as UTF-8 Signed-off-by: David Waern <david.waern at gmail.com> - - - - - ea687dad by Simon Peyton Jones at 2013-03-15T14:16:10+00:00 Adapt to tcRnGetInfo returning family instances too This API change was part of the fix to Trac haskell/haddock#4175. But it offers new information to Haddock: the type-family instances, as well as the class instances, of this type. This patch just drops the new information on the floor, but there's an open opportunity to use it in the information that Haddock displays. - - - - - 971a30b0 by Andreas Voellmy at 2013-05-19T20:47:39+01:00 Fix for haskell/haddock#7879. Changed copy of utils/haddock/html/resources/html to use "cp -RL" rather than "cp -R". This allows users to run validate in a build tree, where the build tree was setup using lndir with a relative path to the source directory. - - - - - 31fb7694 by Ian Lynagh at 2013-05-19T20:47:49+01:00 Use "cp -L" when making $(INPLACE_LIB)/latex too - - - - - e9952233 by Simon Hengel at 2013-06-01T18:06:50+02:00 Add -itest to .ghci - - - - - b06873b3 by Mateusz Kowalczyk at 2013-06-01T18:06:50+02:00 Workaround for a failing build with --enable-tests. - - - - - e7858d16 by Simon Hengel at 2013-06-01T19:29:28+02:00 Fix broken test - - - - - 0690acb1 by Richard Eisenberg at 2013-06-21T14:08:25+01:00 Updates to reflect changes in HsDecls to support closed type families. - - - - - 7fd347ec by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 53ed81b6 by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 931c4f4f by Richard Eisenberg at 2013-07-24T13:15:59+01:00 Remove (error "synifyKind") to use WithinType, to allow haddock to process base. - - - - - 55a9c804 by Richard Eisenberg at 2013-08-02T15:54:55+01:00 Changes to reflect changes in GHC's type HsTyVarBndr - - - - - b6e9226c by Mathieu Boespflug at 2013-08-04T10:39:43-07:00 Output Copright and License keys in Xhtml backend. This information is as relevant in the documentation as it is in the source files themselves. Signed-off-by: David Waern <david.waern at gmail.com> - - - - - 4c66028a by David Waern at 2013-08-04T15:27:36-07:00 Bump interface file version. - - - - - 67340163 by David Waern at 2013-08-09T16:12:51-07:00 Update tests. - - - - - 2087569b by Mateusz Kowalczyk at 2013-08-25T09:24:13+02:00 Add spec tests. This adds tests for all elements we can create during regular parsing. This also adds tests for text with unicode in it. - - - - - 97f36a11 by Mateusz Kowalczyk at 2013-08-27T06:59:12+01:00 Fix ticket haskell/haddock#247. I do the same thing that the XHTML backend does: give these no special treatment and just act as if they are regular functions. - - - - - 60681b4f by Mateusz Kowalczyk at 2013-08-27T21:22:48+02:00 LaTeX tests setup - - - - - fa4c27b2 by Mateusz Kowalczyk at 2013-09-02T23:21:43+01:00 Fixes haskell/haddock#253 - - - - - 1a202490 by Mateusz Kowalczyk at 2013-09-03T01:12:50+01:00 Use Hspec instead of nanospec This is motivated by the fact that Haddock tests are not ran by the GHC's ‘validate’ script so we're pretty liberal on dependencies in that area. Full Hspec gives us some nice features such as Quickcheck integration. - - - - - 8cde3b20 by David Luposchainsky at 2013-09-08T07:27:28-05:00 Fix AMP warnings Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - d10661f2 by Herbert Valerio Riedel at 2013-09-11T15:15:01+02:00 Update Git repo URL in `.cabal` file - - - - - 16a44eb5 by Richard Eisenberg at 2013-09-17T09:34:26-04:00 Revision to reflect new role annotation syntax in GHC. - - - - - 4b9833b9 by Herbert Valerio Riedel at 2013-09-18T10:15:28+02:00 Add missing `traverse` method for `GenLocated` As `Traversable` needs at least one of `traverse` or `sequenceA` to be overridden. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - b71fed5d by Simon Hengel at 2013-09-18T22:43:34+02:00 Add test helper - - - - - 4fc1ea86 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#231 - - - - - 435872f6 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#256 We inject -dynamic-too into flags before we run all our actions in the GHC monad. - - - - - b8b24abb by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Add new field to DynFlags - - - - - 49558795 by Simon Hengel at 2013-09-18T22:43:35+02:00 Fallback to ./resources when Cabal data is not found (so that themes are found during development) - - - - - bf79d05c by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Fixes haskell/haddock#5 - - - - - e1baebc2 by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Print missing documentation. Fixes haskell/haddock#258. - - - - - 02ea74de by Austin Seipp at 2013-10-09T10:52:22-05:00 Don't consider StaticFlags when parsing arguments. Instead, discard any static flags before parsing the command line using GHC's DynFlags parser. See http://ghc.haskell.org/trac/ghc/ticket/8276 Based off a patch from Simon Hengel. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 704fd5bb by Simon Hengel at 2013-11-09T00:15:13+01:00 Update HTML tests - - - - - f9fed49e by Simon Hengel at 2013-11-10T18:43:58+01:00 Bump version - - - - - 97ae1999 by Simon Peyton Jones at 2013-11-25T17:25:14+00:00 Track changes in HsSpliceTy data constructor - - - - - 59ad8268 by Simon Peyton Jones at 2014-01-10T18:17:43+00:00 Adapt to small change in Pretty's exports - - - - - 8b12e6aa by Simon Hengel at 2014-01-12T14:48:35-06:00 Some code simplification by using traverse - - - - - fc5ea9a2 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix warnings in test helper - - - - - 6dbb3ba5 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Add ByteString version of Attoparsec - - - - - 968d7774 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 One pass parser and tests. We remove the HTML test as it is no longer necessary. We cover the test case in spec tests and other HTML tests but keeping this around fails: this is because the new parser has different semantics there. In fact, I suspect the original behaviour was a bug that wasn't caught/fixed but simply included as-is during the testing. - - - - - 37a07c9c by Simon Hengel at 2014-01-12T14:48:35-06:00 Rename Haddock.ParseSpec to Haddock.ParserSpec - - - - - f0f68fe9 by Simon Hengel at 2014-01-12T14:48:35-06:00 Don't append newline to parseString input We also check that we have parsed everything with endOfInput. - - - - - 95d60093 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix totality, unicode, examples, paragraph parsing Also simplify specs and parsers while we're at it. Some parsers were made more generic. This commit is a part of GHC pre-merge squash, email fuuzetsu at fuuzetsu.co.uk if you need the full commit history. - - - - - 7d99108c by Simon Hengel at 2014-01-12T14:48:35-06:00 Update acceptance tests - - - - - d1b59640 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Support for bold. Conflicts: src/Haddock/Backends/Hoogle.hs src/Haddock/Interface/Rename.hs src/Haddock/Parser.hs - - - - - 4b412b39 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Allow for headings inside function documentation. LaTeX will treat the h3-h6 headings the same as we'd have to hack the style file heavily otherwise and it would make the headings tiny anyway. Hoogle upstream said they will put in the functionality on their end. Conflicts: src/Haddock/Interface/Rename.hs src/Haddock/Types.hs test/Haddock/ParserSpec.hs - - - - - fdcca428 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Per-module extension flags and language listing. Any extensions that are not enabled by a used language (Haskell2010 &c) will be shown. Furthermore, any implicitly enabled are also going to be shown. While we could eliminate this either by using the GHC API or a dirty hack, I opted not to: if a user doesn't want the implied flags to show, they are recommended to use enable extensions more carefully or individually. Perhaps this will encourage users to not enable the most powerful flags needlessly. Enabled with show-extensions. Conflicts: src/Haddock/InterfaceFile.hs - - - - - 368942a2 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Bump interface version There were some breaking changes over the last few patches so we bump the interface version. This causes a big problem with testing: 1. To generate cross package docs, we first need to generate docs for the package used. 2. To generate package docs with new interface version, we need to use Haddock which has the version bumped. 3. To get Haddock with the version bump, we first need to test cross package docs 4. GOTO 1 So the problem is the chicken and the egg problem. It seems that the only solution would be to generate some interface files on the fly but it is non-trivial. To run this test, you'll have to: * build Haddock without the test (make sure everything else passes) * rebuild the packages used in the test with your shiny new binary making sure they are visible to Haddock * remove the ‘_hidden’ suffix and re-run the tests Note: because the packages currently used for this test are those provided by GHC, it's probably non-trivial to just re-build them. Preferably something less tedious to rebuild should be used and something that is not subject to change. - - - - - 124ae7a9 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow for nesting of paragraphs under lists. The nesting rules are similar to Markdown's with the exception that we can not simply indent the first line of a hard wrapped indented paragraph and have it treated as if it was fully indented. The reason is differences in markup as some of our constructs care about whitespace while others just swallow everything up so it's just a lot easier to not bother with it rather than making arbitrary rules. Note that we now drop trailing for string entities inside of lists. They weren't needed and it makes the output look uniform whether we use a single or double newline between list elements. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - c7913535 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow escaping in URLs and pictures. Some tests were moved under parseString as they weren't about paragraph level markup. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - 32326680 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update documentation. - - - - - fbef6406 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update maintainer - - - - - b40e82f4 by Mateusz Kowalczyk at 2014-01-13T02:39:25-06:00 Fixes haskell/haddock#271 Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - f4eafbf8 by Gergő Érdi at 2014-01-19T15:35:16-06:00 Support for -XPatternSynonyms Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - a8939591 by Austin Seipp at 2014-01-29T08:09:04-06:00 Update CPP check for __GLASGOW_HASKELL__ Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 30d7e9d5 by Gergő Érdi at 2014-01-31T00:15:01+08:00 <+>: Don't insert a space when concatenating empty nodes - - - - - a25ccd4d by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Fix @ code blocks In cases where we had some horizontal space before the closing ‘@’, the parser would not accept the block as a code block and we'd get ugly output. - - - - - 0f67305a by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Update tests This updates tests due to Haddock Trac haskell/haddock#271 fix and due to removal of TypeHoles as an extension from GHC. - - - - - 157322a7 by Gergő Érdi at 2014-01-31T01:03:17+08:00 Handle infix vs prefix names correctly everywhere, by explicitly specifying the context The basic idea is that "a" and "+" are either pretty-printed as "a" and "(+)" or "`a`" and "+" - - - - - aa6d9685 by Mateusz Kowalczyk at 2014-01-30T17:21:50+00:00 Correct whitespace in ‘hidden’ test for <+> change - - - - - 121872f0 by Mateusz Kowalczyk at 2014-02-09T17:59:12+00:00 Document module header. Fixes Haddock Trac haskell/haddock#270. - - - - - e3253746 by Mateusz Kowalczyk at 2014-02-10T21:37:48+00:00 Insert a space between module link and description Fixes Haddock Trac haskell/haddock#277. - - - - - 771d2384 by Mateusz Kowalczyk at 2014-02-10T23:27:21+00:00 Ensure a space between type signature and ‘Source’ This is briefly related to Haddock Trac haskell/haddock#249 and employs effectively the suggested fix _but_ it doesn't actually fix the reported issue. This commit simply makes copying the full line a bit less of a pain. - - - - - 8cda9eff by nand at 2014-02-11T15:48:30+00:00 Add support for type/data families This adds support for type/data families with their respective instances, as well as closed type families and associated type/data families. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 3f22c510 by nand at 2014-02-11T15:53:50+00:00 Improve display of poly-kinded type operators This now displays them as (==) k a b c ... to mirror GHC's behavior, instead of the old (k == a) b c ... which was just wrong. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - effb2d6b by nand at 2014-02-11T15:56:50+00:00 Add test case for PatternSynonyms This just tests various stuff including poly-kinded patterns and operator patterns to make sure the rendering isn't broken. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - b38faf0d by Niklas Haas at 2014-02-13T21:53:32+00:00 Get rid of re-implementation of sortBy I have no idea what this was doing lying around here, and due to the usage of tuples it's actually slower, too. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - ac1e0413 by Mateusz Kowalczyk at 2014-02-13T23:57:16+00:00 Only warn about missing docs when docs are missing This fixes the ‘Missing documentation for…’ message for modules with 100% coverage. - - - - - cae2e36a by Niklas Haas at 2014-02-15T21:56:18+00:00 Add test case for inter-module type/data family instances These should show up in every place where the class is visible, and indeed they do right now. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 8bea5c3a by Mateusz Kowalczyk at 2014-02-19T05:11:34+00:00 Use a bespoke data type to indicate fixity This deals with what I imagine was an ancient TODO and makes it much clearer what the argument actually does rather than having the user chase down the comment. - - - - - 5b52d57c by Niklas Haas at 2014-02-22T21:31:03+01:00 Strip a single leading space from bird tracks (#201) This makes bird tracks in the form > foo > bar > bat parse as if they had been written as >foo >bar >bat ie. without the leading whitespace in front of every line. Ideally we also want to look into how leading whitespace affects code blocks written using the @ @ syntax, which are currently unaffected by this patch. - - - - - 5a1315a5 by Simon Hengel at 2014-02-22T21:55:35+01:00 Turn a source code comment into specs - - - - - 784cfe58 by Mateusz Kowalczyk at 2014-02-23T05:02:22+00:00 Update test case for lifted GADT type rendering The parsing of these seems to have been fixed by GHC folk and it now renders differently. IMHO it now renders in a better way so I'm updating the test to reflect this. - - - - - c3c88c2f by Mateusz Kowalczyk at 2014-02-23T06:37:14+00:00 Don't shadow ‘strip’. -Wall complains - - - - - 293031d8 by Niklas Haas at 2014-02-23T15:21:52+01:00 Make ImplicitParams render correctly (#260) This introduces a new precedence level for single contexts (because implicit param contexts always need parens around them, but other types of contexts don't necessarily, even when alone) - - - - - 4200842d by Niklas Haas at 2014-02-23T15:37:13+01:00 Lower precedence of equality constraints This drops them to the new precedence pREC_CTX, which makes single eqaulity constraints show up as (a ~ b) => ty, in line with GHC's rendering. Additional tests added to make sure other type operators render as intended. Current behavior matches GHC - - - - - b59e3227 by Niklas Haas at 2014-02-23T16:11:22+01:00 Add RankNTypes test case to ImplicitParams.hs This test actually tests what haskell/haddock#260 originally reported - I omitted the RankNTypes scenario from the original fix because I realized it's not relevant to the underlying issue and indeed, this renders as intended now. Still good to have more tests. - - - - - c373dbf7 by Mateusz Kowalczyk at 2014-02-24T06:09:54+00:00 Fix rendering of Contents when links are present Fixes Haddock Trac haskell/haddock#267. - - - - - 9ecb0e56 by Mateusz Kowalczyk at 2014-02-24T06:26:50+00:00 Fix wording in the docs - - - - - 4f4dcd8e by Mateusz Kowalczyk at 2014-02-27T03:00:33+00:00 Change rendering of duplicate record field docs See Haddock Trac haskell/haddock#195. We now change this behaviour to only rendering the documentation attached to the first instance of a duplicate field. Perhaps we could improve this by rendering the first instance that has documentation attached to it but for now, we'll stick with this. - - - - - ad8aa609 by Niklas Haas at 2014-03-08T09:43:26+01:00 Render fixity information Affects functions, type synonyms, type families, class names, data type names, constructors, data families, associated TFs/DFs, type synonyms, pattern synonyms and everything else I could think of. - - - - - 6a39c917 by Niklas Haas at 2014-03-09T07:43:39+01:00 Reorder topDeclElem to move the source/wiki links to the top They appear in the same position due to the float: right attribute but now they're always at the top of the box instead of at the bottom. - - - - - 2d34b3b4 by Niklas Haas at 2014-03-09T07:53:46+01:00 Use optLast instead of listToMaybe for sourceUrls/wikiUrls This lets you override them using eg. cabal haddock --haddock-options, which can come in handy if you want to use a different layout or URL for your source code links than cabal-install generates. - - - - - 0eff4624 by Niklas Haas at 2014-03-09T07:53:46+01:00 Differentiate between TH splices (line-links) and regular names This adds a new type of source code link, to a specific line rather than a specific declaration/name - this is used to link to the location of a TH splice that defines a certain name. Rather hefty changes throughout and still one unresolved issue (the line URLs aren't parsed from the third form of --read-interface which means they're currently restricted to same-interface links). Not sure if this issue is really worth all the hassle, especially since we could just use line links in general. This commit also contains some cleanup/clarification of the types in Haddock.Backends.Xhtml.Decl and shortens some overlong lines in the process. Notably, the Bool parameter was replaced by a Unicode type synonym to help clarify its presence in type signatures. - - - - - 66d6f77b by Niklas Haas at 2014-03-09T20:02:43+01:00 Group similar fixities together Identical fixities declared for the same line should now render using syntax like: infix 4 <, >=, >, <= - - - - - 6587f9f5 by Mateusz Kowalczyk at 2014-03-10T04:24:18+00:00 Update changelog - - - - - 7387ddad by Niklas Haas at 2014-03-11T10:26:04+01:00 Include fixity information in the Interface file This resolves fixity information not appearing across package borders. The binary file version has been increased accordingly. - - - - - ab46ef44 by Niklas Haas at 2014-03-11T10:26:04+01:00 Update changelog - - - - - 565cab6f by Niklas Haas at 2014-03-11T10:26:04+01:00 Update appearance of fixity annotations This moves them in-line with their corresponding lines, similar to a presentation envision by @hvr and described in #ghc. Redundant operator names are also omitted when no ambiguity is present. - - - - - 5d7afd67 by Niklas Haas at 2014-03-11T10:26:05+01:00 Filter family instances of hidden types Currently, this check does not extend to hidden right hand sides, although it probably should hide them in that case. - - - - - ec291b0c by Niklas Haas at 2014-03-11T10:26:05+01:00 Add documentation for --source-entity-line - - - - - 0922e581 by Niklas Haas at 2014-03-11T10:37:32+01:00 Revert "Reorder topDeclElem to move the source/wiki links to the top" This reverts commit 843c42c4179526a2ad3526e4c7d38cbf4d50001d. This change is no longer needed with the new rendering style, and it messes with copy/pasting lines. - - - - - 30618e8b by Mateusz Kowalczyk at 2014-03-11T09:41:07+00:00 Bump version to 2.15.0 - - - - - adf3f1bb by Mateusz Kowalczyk at 2014-03-11T09:41:09+00:00 Fix up some whitespace - - - - - 8905f57d by Niklas Haas at 2014-03-13T19:18:06+00:00 Hide RHS of TFs with non-exported right hand sides Not sure what to do about data families yet, since technically it would not make a lot of sense to display constructors that cannot be used by the user. - - - - - 5c44d5c2 by Niklas Haas at 2014-03-13T19:18:08+00:00 Add UnicodeSyntax alternatives for * and -> I could not find a cleaner way to do this other than checking for string equality with the given built-in types. But seeing as it's actually equivalent to string rewriting in GHC's implementation of UnicodeSyntax, it's probably fitting. - - - - - b04a63e6 by Niklas Haas at 2014-03-13T19:18:10+00:00 Display minimal complete definitions for type classes This corresponds to the new {-# MINIMAL #-} pragma present in GHC 7.8+. I also cleaned up some of the places in which ExportDecl is used to make adding fields easier in the future. Lots of test cases have been updated since they now render with minimality information. - - - - - a4a20b16 by Niklas Haas at 2014-03-13T19:18:12+00:00 Strip links from recently added html tests These were accidentally left there when the tests were originally added - - - - - d624f315 by Mateusz Kowalczyk at 2014-03-13T19:19:31+00:00 Update changelog - - - - - d27a21ac by Mateusz Kowalczyk at 2014-03-13T21:19:07+00:00 Always read in prologue files as UTF8 (#286). - - - - - 54b2fd78 by Mateusz Kowalczyk at 2014-03-13T21:28:09+00:00 Style only - - - - - fa4fe650 by Simon Hengel at 2014-03-15T09:04:18+01:00 Add Fuuzetsu maintainers field in cabal file - - - - - f83484b7 by Niklas Haas at 2014-03-15T18:20:24+00:00 Hide minimal definition for only-method classes Previously this was not covered by the All xs check since here it is not actually an All, rather a single Var n. This also adds the previously missing html-test/src/Minimal.hs. - - - - - 0099d276 by Niklas Haas at 2014-03-15T18:20:26+00:00 Fix issue haskell/haddock#281 This is a regression from the data family instances change. Data instances are now distinguished from regular lists by usage of the new class "inst", and the style has been updated to only apply to those. I've also updated the appropriate test case to test this a bit better, including GADT instances with GADT-style records. - - - - - 1f9687bd by Mateusz Kowalczyk at 2014-03-21T17:48:37+00:00 Please cabal sdist - - - - - 75542693 by Mateusz Kowalczyk at 2014-03-22T16:36:16+00:00 Drop needless --split-objs which slows us down. Involves tiny cleanup of all the dynflag bindings. Fixes haskell/haddock#292. - - - - - 31214dc3 by Herbert Valerio Riedel at 2014-03-23T18:01:01+01:00 Fix a few typos Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 0b73e638 by Mateusz Kowalczyk at 2014-03-31T05:34:36+01:00 Print kind signatures on GADTs - - - - - 2bab42f3 by Mateusz Kowalczyk at 2014-03-31T16:53:25+01:00 Add default for new PlatformConstraints field - - - - - 42647c5f by Mateusz Kowalczyk at 2014-03-31T18:29:04+01:00 Drop leading whitespace in @-style blocks. Fixes haskell/haddock#201. - - - - - 98208294 by Niklas Haas at 2014-03-31T20:09:58+02:00 Crash when exporting record selectors of data family instances This fixes bug haskell/haddock#294. This also fixes a related but never-before-mentioned bug about the display of GADT record selectors with non-polymorphic type signatures. Note: Associated data type constructors fail to show up if nothing is exported that they could be attached to. Exporting any of the data types in the instance head, or the class + data family itself, causes them to show up, but in the absence of either of these, exporting just the associated data type with the constructor itself will result in it being hidden. The only scenario I can come up that would involve this kind of situation involved OverlappingInstances, and even then it can be mitigated by just exporting the class itself, so I'm not going to solve it since the logic would most likely be very complicated. - - - - - 3832d171 by Mateusz Kowalczyk at 2014-04-01T19:07:33+01:00 Make CHANGES consistent with what's now in 2.14.2 - - - - - c386ae89 by Mateusz Kowalczyk at 2014-04-01T19:18:36+01:00 Actually bundle extra spec tests in sdist - - - - - bd57a6d3 by Mateusz Kowalczyk at 2014-04-03T21:13:48+01:00 Update test cases for GHC bug haskell/haddock#8945, Haddock haskell/haddock#188 The order of signature groups has been corrected upstream. Here we add a test case and update some existing test-cases to reflect this change. We remove grouped signature in test cases that we can (Minimal, BugDeprecated &c) so that the test is as self-contained as possible. - - - - - 708b88b1 by Mateusz Kowalczyk at 2014-04-03T21:16:07+01:00 Enforce strict GHC version in cabal file This stops people with 7.6.3 trying to install 2.15.x which clearly won't work. Unfortunately we shipped 2.14.x without realising this. - - - - - 60334f7c by Mateusz Kowalczyk at 2014-04-03T21:19:24+01:00 Initialise some new PlatformConstants fields - - - - - ea77f668 by Mateusz Kowalczyk at 2014-04-11T16:52:23+01:00 We don't actually want unicode here - - - - - 0b651cae by Mateusz Kowalczyk at 2014-04-11T18:13:30+01:00 Parse identifiers with ^ and ⋆ in them. Fixes haskell/haddock#298. - - - - - e8ad0f5f by Mateusz Kowalczyk at 2014-04-11T18:47:41+01:00 Ignore version string during HTML tests. - - - - - de489089 by Mateusz Kowalczyk at 2014-04-11T18:59:30+01:00 Update CHANGES to follow 2.14.3 - - - - - beb464a9 by Gergő Érdi at 2014-04-13T16:31:10+08:00 remove Origin flag from LHsBindsLR - - - - - cb16f07c by Herbert Valerio Riedel at 2014-04-21T17:16:50+02:00 Replace local `die` by new `System.Exit.die` Starting with GHC 7.10, System.Exit exports the new `die` which is essentially the same as Haddock.Util.die, so this commit changes Haddock.Util.die to be a simple re-export of System.Exit.die. See also https://ghc.haskell.org/trac/ghc/ticket/9016 for more details. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 9b9b23c7 by Mateusz Kowalczyk at 2014-05-03T15:40:11+02:00 Disambiguate ‘die’ in test runners. - - - - - 5d28a2b8 by Mateusz Kowalczyk at 2014-05-05T09:19:49+02:00 Prepare modules for parser split. We have to generalise the Doc (now DocH) slightly to remove the dependency on GHC-supplied type. - - - - - d3967ff3 by Mateusz Kowalczyk at 2014-05-05T11:00:41+02:00 Move parser + parser tests out to own package. We move some types out that are necessary as well and then re-export and specialise them in the core Haddock. Reason for moving out spec tests is that if we're working on the parser, we can simply work on that and we can ignore the rest of Haddock. The downside is that it's a little inconvenient if at the end of the day we want to see that everything passes. - - - - - 522a448d by Mateusz Kowalczyk at 2014-05-05T11:14:47+02:00 Move out Show and Eq instances to Types They are much more useful to the users here. - - - - - 11a6f0f2 by Mateusz Kowalczyk at 2014-05-06T13:50:31+02:00 Remove no longer necessary parser error handling. We can now drop some Maybe tests and even lets us strip an error handling monad away in a few places. - - - - - 6992c924 by Mateusz Kowalczyk at 2014-05-14T02:23:55+02:00 Please the GHC build-system. As I can not figure out how to do this properly, if we're in GHC tree, we treat the library as being the same package. If we're not in the tree, we require that the library be installed separately. - - - - - 7a8ad763 by Mateusz Kowalczyk at 2014-05-14T14:50:25+02:00 Update issue tracker URL - - - - - f616c521 by Mateusz Kowalczyk at 2014-05-14T14:53:32+02:00 Update issue tracker URL for haddock-library - - - - - 66580ded by Gergő Érdi at 2014-05-25T14:24:16+08:00 Accomodate change in PatSyn representation - - - - - 0e43b988 by Mateusz Kowalczyk at 2014-05-29T03:15:29+02:00 Revert "Accomodate change in PatSyn representation" This reverts commit 57aa591362d7c8ba21285fccd6a958629a422091. I am reverting this because I pushed it to master when it was meant to stay on a wip-branch. Sorry Gergo and everyone who had trouble due to this. - - - - - e10d7ec8 by Mateusz Kowalczyk at 2014-05-29T03:24:11+02:00 Revert "Revert "Accomodate change in PatSyn representation"" This reverts commit e110e6e70e40eed06c06676fd2e62578da01d295. Apparently as per GHC commit ac2796e6ddbd54c5762c53e2fcf29f20ea162fd5 this was actually intended. Embarrasing for me. - - - - - 5861aca9 by Mateusz Kowalczyk at 2014-06-05T19:49:27+02:00 Clear up highlighting of identifiers with ‘'’s. - - - - - d7cc420f by Simon Peyton Jones at 2014-06-06T12:41:09+01:00 Follow change in patSynSig - - - - - 938b4fd8 by Mateusz Kowalczyk at 2014-06-12T07:24:29+02:00 Slightly update the readme. Style-sheets are no longer a recent thing, dead links, old maintainers, different formats. - - - - - c7799dea by Mateusz Kowalczyk at 2014-06-18T00:05:56+02:00 Update cabal files Update repository urls, use subdir property for haddock-library and use a separate versioning scheme for haddock-library in preparation for release. - - - - - a2750b6a by Simon Hengel at 2014-06-18T11:01:18+08:00 Compatibility with older versions of base and bytestring - - - - - 009b4b03 by Simon Hengel at 2014-06-18T11:14:01+08:00 Enable travis-ci for haddock-library - - - - - 9b5862eb by Simon Hengel at 2014-06-18T11:14:01+08:00 haddock-library: Do not depend on haddock-library in test suite I think you either add src to hs-source-dirs or the library to build-depends. But doing both does not make sense (AFAICT). - - - - - fb1f3279 by Simon Hengel at 2014-06-18T11:49:05+08:00 haddock-library: Use -Wall for specs - - - - - 649340e1 by Mateusz Kowalczyk at 2014-06-18T06:58:54+02:00 Use Travis with multiple GHC versions When using HEAD, we build haddock-library directly from repository as a dependency (and thanks to --enable-tests, the tests get ran anyway). In all other cases, we manually run the tests on haddock-library only and don't test the main project. - - - - - d7eeeec2 by Mateusz Kowalczyk at 2014-06-18T07:49:04+02:00 Comment improvements + few words in cabal file - - - - - 0f8db914 by Simon Hengel at 2014-06-18T13:52:23+08:00 Use doctest to check examples in documentation - - - - - 2888a8dc by Simon Hengel at 2014-06-18T14:16:48+08:00 Remove doctest dependency (so that we can use haddock-library with doctest) - - - - - 626d5e85 by Mateusz Kowalczyk at 2014-06-18T08:41:25+02:00 Travis tweaks - - - - - 41d4f9cc by Mateusz Kowalczyk at 2014-06-18T08:58:43+02:00 Don't actually forget to install specified GHC. - - - - - c6aa512a by John MacFarlane at 2014-06-18T10:43:57-07:00 Removed reliance on LambdaCase (which breaks build with ghc 7.4). - - - - - b9b93b6f by John MacFarlane at 2014-06-18T10:54:56-07:00 Fixed haddock warnings. - - - - - a41b0ab5 by Mateusz Kowalczyk at 2014-06-19T01:20:10+02:00 Update Travis, bump version - - - - - 864bf62a by Mateusz Kowalczyk at 2014-06-25T10:36:54+02:00 Fix anchors. Closes haskell/haddock#308. - - - - - 53df91bb by Mateusz Kowalczyk at 2014-06-25T15:04:49+02:00 Drop DocParagraph from front of headers I can not remember why they were wrapped in paragraphs to begin with and it seems unnecessary now that I test it. Closes haskell/haddock#307. - - - - - 29b5f2fa by Mateusz Kowalczyk at 2014-06-25T15:17:20+02:00 Don't mangle append order for nested lists. The benefit of this is that the ‘top-level’ element of such lists is properly wrapped in <p> tags so any CSS working with these will be applied properly. It also just makes more sense. Pointed out at jgm/pandoc#1346. - - - - - 05cb6e9c by Mateusz Kowalczyk at 2014-06-25T15:19:45+02:00 Bump haddock-library to 1.1.0 for release - - - - - 70feab15 by Iavor Diatchki at 2014-07-01T03:37:07-07:00 Propagate overloading-mode for instance declarations in haddock (#9242) - - - - - d4ca34a7 by Simon Peyton Jones at 2014-07-14T16:23:15+01:00 Adapt to new definition of HsDecls.TyFamEqn This is a knock-on from the refactoring from Trac haskell/haddock#9063. I'll push the corresponding changes to GHC shortly. - - - - - f91e2276 by Edward Z. Yang at 2014-07-21T08:14:19-07:00 Track GHC PackageId to PackageKey renaming. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - b010f9ef by Edward Z. Yang at 2014-07-25T16:28:46-07:00 Track changes for module reexports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - 8b85f9f9 by Mateusz Kowalczyk at 2014-07-28T13:25:43+02:00 Catch mid-line URLs. Fixes haskell/haddock#314. - - - - - 4c613a78 by Edward Z. Yang at 2014-08-05T03:11:00-07:00 Track type signature change of lookupModuleInAllPackages Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - e80b051c by Edward Z. Yang at 2014-08-05T17:34:26+01:00 If GhcProfiled, also build Haddock profiled. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f9cccd29 by Edward Z. Yang at 2014-08-07T14:23:35+01:00 Ignore TAGS files. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 00b3af52 by Mateusz Kowalczyk at 2014-08-08T04:58:19+02:00 Update to attoparsec-0.12.1.1 There seems to be memory and speed improvement. - - - - - 5457dc71 by Mateusz Kowalczyk at 2014-08-08T18:24:02+02:00 Fix forgotten src - - - - - 3520cb04 by Mateusz Kowalczyk at 2014-08-14T20:19:07+01:00 Bump down the version for master to 2.14.4 - - - - - dc98c21b by Mateusz Kowalczyk at 2014-08-14T20:23:27+01:00 Revert "Track type signature change of lookupModuleInAllPackages" This reverts commit d59fec2c9551b5662a3507c0011e32a09a9c118f. - - - - - 3f2038c0 by Mateusz Kowalczyk at 2014-08-14T20:23:31+01:00 Revert "Track changes for module reexports." This reverts commit b99b57c0df072d12b67816b45eca2a03cb1da96d. - - - - - 56d4e49e by Mateusz Kowalczyk at 2014-08-14T20:23:42+01:00 Revert "Track GHC PackageId to PackageKey renaming." This reverts commit 8ac42d3327473939c013551750425cac191ff0fd. - - - - - 726ea3cb by Mateusz Kowalczyk at 2014-08-14T20:23:47+01:00 Revert "Adapt to new definition of HsDecls.TyFamEqn" This reverts commit cb96b4f1ed0462b4a394b9fda6612c3bea9886bd. - - - - - 61a88ff0 by Mateusz Kowalczyk at 2014-08-14T20:23:52+01:00 Revert "Propagate overloading-mode for instance declarations in haddock (#9242)" This reverts commit 8d20ca8d5a9bee73252ff2035ec45f9c03d0820c. - - - - - a32ba674 by Mateusz Kowalczyk at 2014-08-14T20:26:03+01:00 Revert "Disambiguate ‘die’ in test runners." This reverts commit dba02d6df32534aac5d257f2d28596238d248942. - - - - - f335820f by Mateusz Kowalczyk at 2014-08-14T20:26:09+01:00 Revert "Replace local `die` by new `System.Exit.die`" This reverts commit 08aa509ebac58bfb202ea79c7c41291ec280a1c5. - - - - - 107078e4 by Mateusz Kowalczyk at 2014-08-14T20:27:34+01:00 Merge branch 'reverts' This reverts any changes that were made to have Haddock compile with 7.9. When 7.10 release comes, we can simply re-apply all the patches and any patches that occur on ghc-head branch from now on. This allows us to build master with 7.8.3 - - - - - b44b3871 by Mateusz Kowalczyk at 2014-08-15T02:47:40+01:00 Fix haskell/haddock#313 by doing some list munging. I get rid of the Monoid instance because we weren't satisfying the laws. Convenience of having <> didn't outweigh the shock-factor of having it behave badly. - - - - - e1a62cde by Mateusz Kowalczyk at 2014-08-15T02:52:56+01:00 Stop testing haskell/haddock#188. Because the change is in GHC 7.9 and we now work against 7.8.3, this test no longer makes sense. We revert it until 7.10 becomes the standard version. If anything, there should be a test for this in GHC itself. - - - - - 54e8286d by Mateusz Kowalczyk at 2014-08-15T05:31:57+01:00 Add haskell/haddock#313 to CHANGES - - - - - 9df7ad5d by Simon Hengel at 2014-08-20T11:25:32+08:00 Fix warning - - - - - ee2574d6 by Simon Hengel at 2014-08-20T12:07:01+08:00 Fix travis builds - - - - - 384cf2e6 by Simon Hengel at 2014-08-20T12:14:31+08:00 Require GHC 7.8.3 - - - - - d4779863 by Simon Hengel at 2014-08-22T12:14:16+08:00 Move Haddock API to a separate package - - - - - 80f3e0e1 by Simon Hengel at 2014-08-22T14:57:38+08:00 Bump version to 2.15.0 and add version constraints - - - - - 309a94ce by Simon Hengel at 2014-08-22T15:18:06+08:00 Add deprecated compatibility module - - - - - 4d1e4e3f by Luite Stegeman at 2014-08-22T20:46:45+02:00 export things to allow customizing how the Ghc session is run - - - - - 47884591 by Luite Stegeman at 2014-08-22T20:46:51+02:00 ghc 7.8.2 compatibility - - - - - 5ea94e2c by Luite Stegeman at 2014-08-22T22:08:58+02:00 install dependencies for haddock-api on travis - - - - - 9fb845b2 by Mateusz Kowalczyk at 2014-08-23T10:09:34+01:00 Move sources under haddock-api/src - - - - - 85817dc4 by Mateusz Kowalczyk at 2014-08-23T10:10:48+01:00 Remove compat stuff - - - - - 151c6169 by Niklas Haas at 2014-08-24T08:14:10+02:00 Fix extra whitespace on signatures and update all test cases This was long overdue, now running ./accept.lhs on a clean test from master will not generate a bunch of changes. - - - - - d320e0d2 by Niklas Haas at 2014-08-24T08:14:35+02:00 Omit unnecessary foralls and fix haskell/haddock#315 This also fixes haskell/haddock#86. - - - - - bdafe108 by Mateusz Kowalczyk at 2014-08-24T15:06:46+01:00 Update CHANGES - - - - - fafa6d6e by Mateusz Kowalczyk at 2014-08-24T15:14:23+01:00 Delete few unused/irrelevant/badly-place files. - - - - - 3634923d by Duncan Coutts at 2014-08-27T13:49:31+01:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. - - - - - 539a7e70 by Herbert Valerio Riedel at 2014-08-31T11:36:32+02:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 9e3a0e5b by Mateusz Kowalczyk at 2014-08-31T12:54:43+01:00 Bump version in doc - - - - - 4a177525 by Mateusz Kowalczyk at 2014-08-31T13:01:23+01:00 Bump haddock-library version - - - - - f99c1384 by Mateusz Kowalczyk at 2014-08-31T13:05:25+01:00 Remove references to deleted files - - - - - 5e51a247 by Mateusz Kowalczyk at 2014-08-31T14:18:44+01:00 Make the doc parser not complain - - - - - 2cedb49a by Mateusz Kowalczyk at 2014-09-03T03:33:15+01:00 CONTRIBUTING file for issues - - - - - 88027143 by Mateusz Kowalczyk at 2014-09-04T00:46:59+01:00 Mention --print-missing-docs - - - - - 42f6754f by Alan Zimmerman at 2014-09-05T18:13:24-05:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e712719e by Austin Seipp at 2014-09-09T01:03:27-05:00 Fix import of 'empty' due to AMP. Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 71c29755 by Herbert Valerio Riedel at 2014-09-09T17:35:20+02:00 Bump `base` constraint for AMP - - - - - 0bf9f3ed by Mateusz Kowalczyk at 2014-09-12T19:18:32+01:00 Delete stale ANNOUNCE - - - - - cac89ee6 by Krzysztof Gogolewski at 2014-09-14T17:17:09+02:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 4d683426 by Edward Z. Yang at 2014-09-18T13:38:11-07:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 80697fd5 by Herbert Valerio Riedel at 2014-09-19T00:07:52+02:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. - - - - - c015eb70 by Herbert Valerio Riedel at 2014-09-19T00:10:36+02:00 Revert "Followup changes to addition of -fwarn-context-quantification" This reverts commit 4023817d7c0e46db012ba2eea28022626841ca9b temporarily as the respective feature hasn't landed in GHC HEAD yet, but this commit blocks later commits from being referenced in GHC HEAD. - - - - - 38ded784 by Edward Z. Yang at 2014-09-18T15:32:15-07:00 Revert "Revert "Followup changes to addition of -fwarn-context-quantification"" This reverts commit db14fd8ab4fab43694139bc203808b814eafb2dc. It's in HEAD now. - - - - - f55d59c9 by Herbert Valerio Riedel at 2014-09-26T19:18:28+02:00 Revert "Fix import of 'empty' due to AMP." This reverts commit 0cc5bc85e9fca92ab712b68a2ba2c0dd9d3d79f4 since it turns out we don't need to re-export `empty` from Control.Monad after all. - - - - - 467050f1 by David Feuer at 2014-10-09T20:07:36-04:00 Fix improper lazy IO use Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. - - - - - cc47b699 by Edward Z. Yang at 2014-10-09T21:38:19-07:00 Fix use-after-close lazy IO bug Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. Signed-off-by: David Feuer <David.Feuer at gmail.com> Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 87babcbe by Austin Seipp at 2014-10-20T20:05:27-05:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - ab259516 by Austin Seipp at 2014-10-20T20:07:01-05:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - b918093c by Mateusz Kowalczyk at 2014-10-29T03:59:39+00:00 Experimental support for collapsable headers Closes haskell/haddock#335 - - - - - 849db129 by Mateusz Kowalczyk at 2014-10-29T10:07:26+01:00 Experimental support for collapsable headers (cherry picked from commit e2ed3b9d8dfab09f1b1861dbc8e74f08e137ebcc) - - - - - a4cc4789 by Herbert Valerio Riedel at 2014-10-31T11:08:26+01:00 Collapse user-defined section by default (re haskell/haddock#335) - - - - - 9da1b33e by Yuras Shumovich at 2014-10-31T16:11:04-05:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - c625aefc by Austin Seipp at 2014-10-31T19:34:10-05:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - c7738e5e by Simon Hengel at 2014-11-02T07:25:30+08:00 Remove -fobject-code from .ghci (this slows down reloads on modifications) - - - - - d4a86e95 by Simon Hengel at 2014-11-03T09:26:11+08:00 Get rid of StandaloneDeriving - - - - - a974e311 by Simon Hengel at 2014-11-03T09:26:11+08:00 Derive more instances - - - - - 8aa0c4d7 by Simon Hengel at 2014-11-03T09:27:08+08:00 Remove unused language extensions - - - - - 3052d46a by Simon Hengel at 2014-11-03T09:30:46+08:00 Minor refactoring - - - - - 4281d3cb by Simon Hengel at 2014-11-03T09:30:46+08:00 parser: Try to parse definition lists right before text paragraphs - - - - - 8ba12bf9 by Simon Hengel at 2014-11-03T09:34:19+08:00 Add support for markdown links (closes haskell/haddock#336) - - - - - a2f8d747 by Simon Hengel at 2014-11-03T09:34:19+08:00 Allow markdown links at the beginning of a paragraph - - - - - 53b11207 by Simon Hengel at 2014-11-03T09:34:20+08:00 Update documentation - - - - - 652267c6 by Simon Hengel at 2014-11-03T09:34:20+08:00 Add support for markdown images - - - - - 9d667502 by Simon Hengel at 2014-11-03T09:34:20+08:00 Allow an optional colon after the closing bracket of definition lists This is to disambiguate them from markdown links and will be require with a future release. - - - - - 8167fc32 by Mateusz Kowalczyk at 2014-11-04T01:16:51+00:00 whitespace only - - - - - 3da62981 by Mateusz Kowalczyk at 2014-11-04T01:17:31+00:00 Fix re-exports of built-in type families Fixes haskell/haddock#310 - - - - - edc76b34 by Mateusz Kowalczyk at 2014-11-04T02:54:28+00:00 Turn some uses of error into recoverable warnings This should at the very least not abort when something weird happens. It does feel like we should have a type that carries these errors until the end however as the user might not see them unless they are printed at the end. - - - - - 0a137400 by Mateusz Kowalczyk at 2014-11-04T04:09:44+00:00 Fix warnings - - - - - d068fc21 by Mateusz Kowalczyk at 2014-11-04T21:04:07+00:00 Fix parsing of identifiers written in infix way - - - - - 1a9f2f3d by Simon Hengel at 2014-11-08T11:32:42+08:00 Minor code simplification - - - - - 6475e9b1 by Simon Hengel at 2014-11-08T17:28:33+08:00 newtype-wrap parser monad - - - - - dc1ea105 by Herbert Valerio Riedel at 2014-11-15T11:55:43+01:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - fbb1aca4 by Simon Hengel at 2014-11-16T08:51:38+08:00 State intention rather than implementation details in Haddock comment - - - - - 97851ab2 by Simon Hengel at 2014-11-16T10:20:19+08:00 (wip) Add support for @since (closes haskell/haddock#26) - - - - - 34bcd18e by Gergő Érdi at 2014-11-20T22:35:38+08:00 Update Haddock to new pattern synonym type signature syntax - - - - - 304b7dc3 by Jan Stolarek at 2014-11-20T17:48:43+01:00 Follow changes from haskell/haddock#9812 - - - - - 920f9b03 by Richard Eisenberg at 2014-11-20T16:52:50-05:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 0bfe4e78 by Alan Zimmerman at 2014-11-21T11:23:09-06:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 356ed45a by Thomas Winant at 2014-11-28T16:11:22-06:00 Support for PartialTypeSignatures - - - - - 5dc8f3b1 by Gergő Érdi at 2014-11-29T15:39:09+08:00 For pattern synonyms, render "pattern" as a keyword - - - - - fe704480 by Mateusz Kowalczyk at 2014-12-09T03:38:32+00:00 List new module in cabal file - - - - - b9ad5a29 by Mateusz Kowalczyk at 2014-12-10T00:58:24+00:00 Allow the parser to spit out meta-info Currently we only use it only for ‘since’ annotations but with these patches it should be fairly simple to add new attributes if we wish to. Closes haskell/haddock#26. It seems to work fine but due to 7.10 rush I don't have the chance to do more exhaustive testing right now. The way the meta is output (emphasis at the end of the whole comment) is fairly arbitrary and subject to bikeshedding. Note that this makes test for Bug310 fail due to interface version bump: it can't find the docs for base with this interface version so it fails. There is not much we can do to help this because it tests for ’built-in’ identifier, not something we can provide ourselves. - - - - - 765af0e3 by Mateusz Kowalczyk at 2014-12-10T01:17:19+00:00 Update doctest parts of comments - - - - - 8670272b by jpmoresmau at 2014-12-10T01:35:31+00:00 header could contain several lines Closes haskell/haddock#348 - - - - - 4f9ae4f3 by Mateusz Kowalczyk at 2014-12-12T06:22:31+00:00 Revert "Merge branch 'reverts'" This reverts commit 5c93cc347773c7634321edd5f808d5b55b46301f, reversing changes made to 5b81a9e53894d2ae591ca0c6c96199632d39eb06. Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - e974ac94 by Duncan Coutts at 2014-12-12T06:26:11+00:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. Conflicts: haddock-api/src/Haddock.hs - - - - - 2f3a2365 by Herbert Valerio Riedel at 2014-12-12T06:26:51+00:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 1dbd6390 by Alan Zimmerman at 2014-12-12T06:32:07+00:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - bb6ff1f4 by Mateusz Kowalczyk at 2014-12-12T06:35:07+00:00 Bump ‘base’ constraint Follows the similar commit made on ghc-head branch - - - - - 466fe4ab by Krzysztof Gogolewski at 2014-12-12T06:37:42+00:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 97e080c9 by Edward Z. Yang at 2014-12-12T06:39:35+00:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: haddock-api/src/Haddock/ModuleTree.hs - - - - - 20b2af56 by Herbert Valerio Riedel at 2014-12-12T06:42:50+00:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. Conflicts: haddock-library/src/Documentation/Haddock/Parser.hs - - - - - b3ad269d by Austin Seipp at 2014-12-12T06:44:14+00:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 072df0dd by Austin Seipp at 2014-12-12T06:45:01+00:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - dbb9294a by Herbert Valerio Riedel at 2014-12-12T06:46:17+00:00 Collapse user-defined section by default (re haskell/haddock#335) Conflicts: haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs - - - - - f23ab545 by Yuras Shumovich at 2014-12-12T06:46:41+00:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - 753a4b67 by Austin Seipp at 2014-12-12T06:46:51+00:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8954e8f5 by Herbert Valerio Riedel at 2014-12-12T06:50:53+00:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - d2b06d61 by Gergő Érdi at 2014-12-12T07:07:30+00:00 Update Haddock to new pattern synonym type signature syntax Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 1ff02426 by Jan Stolarek at 2014-12-12T07:13:24+00:00 Follow changes from haskell/haddock#9812 Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - 06ad7600 by Richard Eisenberg at 2014-12-12T07:13:43+00:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 8fd2aa8b by Alan Zimmerman at 2014-12-12T07:22:25+00:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Backends/LaTeX.hs haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 95c3db98 by Thomas Winant at 2014-12-12T07:35:49+00:00 Support for PartialTypeSignatures Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs haddock-api/src/Haddock/Interface/Create.hs - - - - - 45494428 by Gergő Érdi at 2014-12-12T07:36:18+00:00 For pattern synonyms, render "pattern" as a keyword - - - - - a237e3eb by Mateusz Kowalczyk at 2014-12-12T12:27:13+00:00 Various fixups and bumps for next release - - - - - 22918bcd by Herbert Valerio Riedel at 2014-12-14T10:11:47+01:00 Remove redundant wild-card pattern match (this would otherwise cause a build-failure with `-Werror`) - - - - - 1d6ce947 by Herbert Valerio Riedel at 2014-12-14T10:17:06+01:00 Treat GHC 7.10 the same as GHC 7.9 ...since the current GHC 7.9 is going to become GHC 7.10 real-soon-now anyway - - - - - f434ea89 by Herbert Valerio Riedel at 2014-12-14T18:26:50+01:00 Fixup ghc.mk (follow-up to 1739375eb23342) This makes the GHC build-system aware of the data-files to be copied into the bindist (as haddock.cabal doesn't list those anymore) - - - - - 6fb839eb by Mateusz Kowalczyk at 2014-12-17T09:28:59+00:00 Only keep one Version instead of blindly appending - - - - - 40645489 by Mateusz Kowalczyk at 2014-12-18T07:09:44+00:00 Fix dependency version - - - - - 8b3b927b by Mateusz Kowalczyk at 2014-12-18T07:14:23+00:00 Print missing docs by default Adds --no-print-missing-docs - - - - - 59666694 by Mateusz Kowalczyk at 2014-12-18T07:21:37+00:00 update changelog - - - - - aa6d168e by Mateusz Kowalczyk at 2014-12-18T07:30:58+00:00 Update docs for @since - - - - - 2d7043ee by Luite Stegeman at 2014-12-19T18:29:35-06:00 hide projectVersion from DynFlags since it clashes with Haddock.Version.projectVersion - - - - - aaa70fc0 by Luite Stegeman at 2014-12-22T15:58:43+01:00 Add missing import for standalone haddock-api package - - - - - 9ce01269 by Herbert Valerio Riedel at 2014-12-22T17:48:45+01:00 Reset ghc-head with master's tree (this is an overwriting git merge of master into ghc-head) - - - - - fcd6fec1 by Herbert Valerio Riedel at 2014-12-22T17:51:52+01:00 Bump versions for ghc-7.11 - - - - - 525ec900 by Mateusz Kowalczyk at 2014-12-23T13:36:24+00:00 travis-ci: test with HEAD - - - - - cbf494b5 by Simon Peyton Jones at 2014-12-23T15:22:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 50e01c99 by Mateusz Kowalczyk at 2014-12-29T15:28:47+00:00 Make travis use 7.10.x - - - - - 475e60b0 by Njagi Mwaniki at 2014-12-29T15:30:44+00:00 Turn the README into GitHub Markdown format. Closes haskell/haddock#354 - - - - - 8cacf48e by Luite Stegeman at 2015-01-05T16:25:37+01:00 bump haddock-api ghc dependency to allow release candidate and first release - - - - - 6ed6cf1f by Simon Peyton Jones at 2015-01-06T16:37:47+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 8b484f33 by Simon Peyton Jones at 2015-01-08T15:50:22+00:00 Track naming change in DataCon - - - - - 23c5c0b5 by Alan Zimmerman at 2015-01-16T10:15:11-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e7a5532c by JP Moresmau at 2015-01-22T17:19:03+00:00 Ignore warnings, install Cabal 1.22 - - - - - 86942c84 by jpmoresmau at 2015-01-22T17:19:04+00:00 solve dataDir ambiguity - - - - - 5ceb743e by jpmoresmau at 2015-01-22T19:17:32+00:00 support GHC 7.10: no Safe-Inferred, Foldable instance - - - - - 6a3b3fb5 by Mateusz Kowalczyk at 2015-01-22T19:32:10+00:00 Update test files Test: a correct behaviour for fields comma-separating values. I'm surprised we had no bug open for this. Maybe it affects how haskell/haddock#301 renders now but I doubt. Operators: Seems GHC is giving us a new order for operators, something must have changed on their side again. cc @haasn , this makes the fixity to the side not match the order on the LHS which is a bit unpleasant. Maybe the fixity can be made to match the GHC order? Bug335: We expand examples by default now. Bug310: Now inferred safe. - - - - - 708f8b2f by jpmoresmau at 2015-01-22T19:36:59+00:00 Links to source location of class instance definitions - - - - - 5cf8a6da by Vincent Berthoux at 2015-01-22T19:59:58+00:00 Filter '\r' from comments due to Windows problems. On Windows this was causing newline to be rendered twice in code blocks. Closes haskell/haddock#359, fixes haskell/haddock#356. - - - - - 1749e6f0 by Mateusz Kowalczyk at 2015-01-22T20:31:27+00:00 Changelog only - - - - - c8145f90 by Mateusz Kowalczyk at 2015-01-22T23:34:05+00:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. - - - - - 14248254 by Mateusz Kowalczyk at 2015-01-22T23:43:18+00:00 Sort out some module import warnings - - - - - d8a38989 by Simon Peyton Jones at 2015-01-23T07:10:16-06:00 Track naming change in DataCon (cherry picked from commit 04cf63d0195837ed52075ed7d2676e71831e8a0b) - - - - - d3ac6ae4 by Alan Zimmerman at 2015-01-23T07:17:19-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit d61bbc75890e4eb0ad508b9c2a27b91f691213e6) - - - - - 4c1ffeb0 by Simon Peyton Jones at 2015-02-10T12:10:33+00:00 Track changes in HsSyn for quasi-quotes - - - - - 775d20f7 by Mateusz Kowalczyk at 2015-03-15T08:11:48+01:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. (cherry picked from commit 8e06728afb0784128ab2df0be7a5d7a191d30ff4) - - - - - f9245e72 by Phil Ruffwind at 2015-03-16T04:32:01-04:00 Prevent Synopsis from using up too much horizontal space When long type signatures occur in the Synopsis, the element is stretched beyond the width of the window. Scrollbars don't appear, so it's impossible to read anything when this happens. - - - - - cd8fa415 by Mateusz Kowalczyk at 2015-03-17T21:59:39+00:00 Update changelog Closes haskell/haddock#151 due to 71170fc77962f10d7d001e3b8bc8b92bfeda99bc - - - - - b5248b47 by Ben Gamari at 2015-03-25T17:12:17+00:00 Make the error encountered when a package can't be found more user-friendly Closes haskell/haddock#369 - - - - - b756b772 by Mateusz Kowalczyk at 2015-03-26T16:31:40+00:00 Remove now redundant imports - - - - - 5ea5e8dd by Mateusz Kowalczyk at 2015-03-26T16:45:52+00:00 Update test to account for \r filtering - - - - - 6539bfb3 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Test for anchor defaulting I delete the old tests because it turns out that: * test runner would never put them in scope of each other even with imports so just one would suffice * test runner actually needed some hacking to keep links so in the end we would end up with no anchors making them useless - - - - - 1a01d950 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Clearly default to variables in out of scope case - - - - - 7943abe8 by Mateusz Kowalczyk at 2015-03-27T01:14:11+00:00 Fix Hoogle display of constructors Fixes haskell/haddock#361 - - - - - 6d6e587e by Mateusz Kowalczyk at 2015-03-27T01:45:18+00:00 Fully qualify names in Hoogle instances output Closes haskell/haddock#263 - - - - - 52dac365 by Mateusz Kowalczyk at 2015-03-27T01:55:01+00:00 Update changelog - - - - - ca5af9a8 by Mateusz Kowalczyk at 2015-03-27T02:43:55+00:00 Output method documentation in Hoogle backend One thing of note is that we no longer preserve grouping of methods and print each method on its own line. We could preserve it if no documentation is present for any methods in the group if someone asks for it though. Fixes haskell/haddock#259 - - - - - a33f0c10 by Mateusz Kowalczyk at 2015-03-27T03:04:21+00:00 Don't print instance safety information in Hoogle Fixes haskell/haddock#168 - - - - - df6c935a by Mateusz Kowalczyk at 2015-03-28T00:11:47+00:00 Post-release version bumps and changelog - - - - - dde8f7c0 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Loosen bounds on haddock-* - - - - - de93bf89 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Expand response files in arguments Closes haskell/haddock#285 - - - - - 1f0b0856 by Zejun Wu at 2015-04-26T16:35:35-07:00 Do not insert anchor for section headings in contents box - - - - - 860439d7 by Simon Peyton Jones at 2015-05-01T09:36:47+01:00 Track change in API of TyCon - - - - - a32f3e5f by Adam Gundry at 2015-05-04T15:32:59+01:00 Track API changes to support empty closed type familes - - - - - 77e98bee by Ben Gamari at 2015-05-06T20:17:08+01:00 Ignore doc/haddock.{ps,pdf} - - - - - 663d0204 by Murray Campbell at 2015-05-11T04:47:37-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8bb0dcf5 by Murray Campbell at 2015-05-11T06:35:06-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit 2380f07c430c525b205ce2eae6dab23c8388d899) - - - - - bad900ea by Adam Bergmark at 2015-05-11T15:29:39+01:00 haddock-library: require GHC >= 7.4 `Data.Monoid.<>` was added in base-4.5/GHC-7.4 Closes haskell/haddock#394 Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - daceff85 by Simon Peyton Jones at 2015-05-13T12:04:21+01:00 Track the new location of setRdrNameSpace - - - - - 1937d1c4 by Alan Zimmerman at 2015-05-25T21:27:15+02:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - ee0fb6c2 by Łukasz Hanuszczak at 2015-05-27T11:51:31+02:00 Create simple method for indentation parsing. - - - - - 7d6fcad5 by Łukasz Hanuszczak at 2015-05-27T21:36:13+02:00 Make nested lists count indentation according to first item. - - - - - d6819398 by Łukasz Hanuszczak at 2015-05-27T22:46:13+02:00 Add simple test case for arbitrary-depth list nesting. - - - - - 2929c54d by Łukasz Hanuszczak at 2015-06-03T02:11:31+02:00 Add arbitrary-indent spec test for parser. - - - - - 9a0a9bb0 by Mateusz Kowalczyk at 2015-06-03T05:25:29+01:00 Update docs with info on new list nesting rule Fixes haskell/haddock#278 through commits from PR haskell/haddock#401 - - - - - 12efc92c by Mateusz Kowalczyk at 2015-06-03T05:29:26+01:00 Update some meta data at the top of the docs - - - - - 765ee49f by Bartosz Nitka at 2015-06-07T08:40:59-07:00 Add some Hacking docs for getting started - - - - - 19aaf851 by Bartosz Nitka at 2015-06-07T08:44:30-07:00 Fix markdown - - - - - 2a90cb70 by Mateusz Kowalczyk at 2015-06-08T15:08:36+01:00 Refine hacking instructions slightly - - - - - 0894da6e by Thomas Winant at 2015-06-08T23:47:28-05:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 10a9bb76 by Emanuel Borsboom at 2015-06-12T02:46:23+01:00 Build executable with '-threaded' (fixes haskell/haddock#399) - - - - - 7696b94f by Mateusz Kowalczyk at 2015-06-12T02:59:19+01:00 Update changelog for -threaded Closes haskell/haddock#400 - - - - - d3c118ec by Bartosz Nitka at 2015-06-12T03:00:58+01:00 Fix haddock: internal error: spliceURL UnhelpfulSpan (#207) Inferred type signatures don't have SrcSpans, so let's use the one from the declaration. I've tested this manually on the test-case from haskell/haddock#207, but I got stuck at trying to run the test-suite. - - - - - b67e843b by Mateusz Kowalczyk at 2015-06-12T03:01:50+01:00 Changelog for haskell/haddock#207 Fixes haskell/haddock#207, closes haskell/haddock#402 - - - - - 841d785e by jpmoresmau at 2015-06-12T16:03:16+01:00 Attach to instance location the name that has the same location file Fixes haskell/haddock#383 - - - - - 98791cae by Mateusz Kowalczyk at 2015-06-12T16:08:27+01:00 Update changelog Closes haskell/haddock#398 - - - - - 7c0b5a87 by Phil Ruffwind at 2015-06-12T13:07:25-04:00 Fix alignment of Source links in instance table in Firefox Due to a Firefox bug [1], a combination of 'whitespace: nowrap' on the parent element with 'float: right' on the inner element can cause the floated element to be displaced downwards for no apparent reason. To work around this, the left side is wrapped in its own <span> and set to 'float: left'. As a precautionary measure to prevent the parent element from collapsing entirely, we also add the classic "clearfix" hack. The latter is not strictly needed but it helps prevent bugs if the layout is altered again in the future. Fixes haskell/haddock#384. Remark: line 159 of src/Haddock/Backends/Xhtml/Layout.hs was indented to prevent confusion over the operator precedence of (<+>) vs (<<). [1]: https://bugzilla.mozilla.org/show_bug.cgi?id=488725 - - - - - cfe86e73 by Mateusz Kowalczyk at 2015-06-14T10:49:01+01:00 Update tests for the CSS changes - - - - - 2d4983c1 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding for Haskell source parser module. - - - - - 29548785 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement function for tagging parsed chunks with source spans. - - - - - 6a5e4074 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement simple string chunking based on HsColour library. - - - - - 6e52291f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create basic token classification method. - - - - - da971a27 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Adapt source span tagging to work with current whitespace handling. - - - - - 4feb5a22 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add record accessors to exports of hyperlinker parser module. - - - - - a8cc4e39 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Make parser module export all types and associated accessors. - - - - - fb8d468f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple HTML renderer for parsed source file. - - - - - 80747822 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for specifying the CSS file path in HTML source renderer. - - - - - 994dc1f5 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix identifier recognition in Haskell source parser. - - - - - b1bd0430 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix comment recognition in Haskell source parser. - - - - - 11db85ae by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for recognizing compiler pragmas in source parser. - - - - - 736c7bd3 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding of module for associating tokens with AST names. - - - - - 7e149bc2 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement utility method for extracting variable identifiers from AST. - - - - - 32eb640a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple mechanism for associating tokens with AST names. - - - - - d4eba5bc by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add dummy support for hyperlinking named tokens. - - - - - 2b76141f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matcher bug causing wrong items being hyperlinked. - - - - - 2d48002e by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Constrain elements exported by hyperlinker modules. - - - - - 9715eec6 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for type token recognition. - - - - - 8fa401cb by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for binding token recognition. - - - - - d062400b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement go-to-definition mechanism for local bindings. - - - - - f4dc229b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement module export- and import-list item hyperlinking. - - - - - c9a46d58 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matching to allow parenthesized operators hyperlinking. - - - - - 03aad95a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix weird hyperlinking of parenthesized operators. - - - - - b4694a7d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for type declaration anchors. - - - - - 7358d2d2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for top-level function declaration anchors. - - - - - dfc24b24 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix external anchors to contain HTML file extension. - - - - - a045926c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Refactor the way AST names are handled within detailed tokens. - - - - - c76049b4 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement hyperlinking of imported module names. - - - - - 2d2a1572 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix parsing of single line comments with broken up newlines. - - - - - 11afdcf2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix bug with improper newline handling. - - - - - 8137f104 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issues with escaped newlines in comments. - - - - - 34759b19 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for parsing C preprocessor macros. - - - - - 09f0f847 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for parser module of source hyperlinker. - - - - - 709a8389 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for AST module of source hyperlinker. - - - - - 4df5c227 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add command line option for generating hyperlinked source. - - - - - 7a755ea2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Extend module interface with rich source token stream field. - - - - - 494f4ab1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement source tokenization during interface creation process. - - - - - 5f21c953 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create hyperlinker module and plug it into the Haddock pipeline. - - - - - 0cc8a216 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for providing custom CSS files for hyperlinked source. - - - - - a32bbdc1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for fancy highlighting upon hovering over identifier. - - - - - d16d642a by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make source hyperlinker generate output in apropriate directory. - - - - - ae12953d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create module with hyperlinker utility functions. - - - - - 6d4952c5 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make external hyperlinks point to locations specified by source URLs. - - - - - 8417555d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Rewrite source generation to fixed links and directory structure. - - - - - ce9cec01 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add basic support for cross-package hyperlink generation. - - - - - 7eaf025c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Disable generating hyperlinks for module references. - - - - - a50bf92e by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make Haddock generate source for all interfaces (also hidden ones). - - - - - f5ae2838 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Prevent source parser from throwing exception when lexing fails. - - - - - db9ffbe0 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement workaround for Chrome highlighting issues. - - - - - 0b6b453b by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate correct anchors for data constructors. - - - - - c86d38bc by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate anchors for record field declarations. - - - - - 063abf7f by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issue with hyperlink highlight styling in Chrome browser. - - - - - 880fc611 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking constructor names in patters. - - - - - c9e89b95 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record patterns. - - - - - 17a11996 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record expressions. - - - - - 0eef932d by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Make hyperlinker respect pretty-printer flag and add documentation. - - - - - f87c1776 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Unexpose hyperlinker modules in Cabal configuration. - - - - - 4c9e2b06 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Setup HSpec framework for Haddock API package. - - - - - 4b20cb30 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add basic tests related to comment parsing. - - - - - 6842e919 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add tests related to parsing basic language constructs. - - - - - 87bffb35 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add simple tests for do-notation parsing. - - - - - e7af1841 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add very simple QuickCheck properties for source parser spec. - - - - - c84efcf1 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Create simple test runner for hyperlinker tests. - - - - - 76b90447 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for basic identifier hyperlinking. - - - - - 0fbf4df6 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for operator hyperlinking. - - - - - 731aa039 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for constructor hyperlinking. - - - - - 995a78a2 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for record expressions and patterns hyperlinking. - - - - - 3566875a by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for literal syntax highlighting. - - - - - 68469a35 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add hyperlinker test runner to .cabal and .gitignore files. - - - - - aa946c93 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Adapt hyperlinker test runner to have the same interface as HTML one. - - - - - ce34da16 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Fix hyperlinker test runner file paths and add pretty-printing option. - - - - - 0d7dd65e by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add reference files for hyperlinker test cases. - - - - - efa4a1e0 by Łukasz Hanuszczak at 2015-07-01T00:47:32+02:00 Make hyperlinker test runner strip local links from generated source. - - - - - 3e96e584 by Łukasz Hanuszczak at 2015-07-01T01:14:59+02:00 Create simple script for accepting hyperlinker test case references. - - - - - 526fe610 by Łukasz Hanuszczak at 2015-07-01T01:16:41+02:00 Re-accept hyperlinker test cases with local references stripped out. - - - - - 892e2cb3 by Łukasz Hanuszczak at 2015-07-01T01:22:09+02:00 Fix bug with diffing wrong files in hyperlinker test runner. - - - - - 9ff46039 by Łukasz Hanuszczak at 2015-07-01T18:04:46+02:00 Remove unused dependencies in Haddock API spec configuration. - - - - - 47969c07 by Łukasz Hanuszczak at 2015-07-01T18:32:19+02:00 Add support for hyperlinking synonyms in patterns. - - - - - a73449e0 by Łukasz Hanuszczak at 2015-07-01T18:33:44+02:00 Create test case for hyperlinking @-patterns. - - - - - c2077ed8 by Łukasz Hanuszczak at 2015-07-01T19:06:04+02:00 Add support for hyperlinking universally quantified type variables. - - - - - 68017342 by Łukasz Hanuszczak at 2015-07-01T19:28:32+02:00 Create hyperlinker test case with quantified type variables. - - - - - 51c01a78 by Łukasz Hanuszczak at 2015-07-01T19:34:22+02:00 Add scoped type variables test for polymorphism test case. - - - - - 13181ae2 by Łukasz Hanuszczak at 2015-07-01T19:56:27+02:00 Add record wildcards test for records hyperlinking test case. - - - - - 991b81dd by Łukasz Hanuszczak at 2015-07-01T21:01:42+02:00 Document some functions in XHTML utlity module. - - - - - 98c8dfe5 by Łukasz Hanuszczak at 2015-07-01T22:25:21+02:00 Make hyperlinker render qualified names as one entity. - - - - - 75e13b9b by Łukasz Hanuszczak at 2015-07-01T22:27:38+02:00 Add qualified name test for identifiers hyperlinking test case. - - - - - de1e143f by Łukasz Hanuszczak at 2015-07-02T12:32:59+02:00 Fix crash happening when hyperlinking type family declarations. - - - - - 7a8fb175 by Łukasz Hanuszczak at 2015-07-02T12:47:03+02:00 Add support for anchoring data family constructor declarations. - - - - - 3b404e49 by Łukasz Hanuszczak at 2015-07-02T13:31:05+02:00 Improve support for hyperlinking type families. - - - - - 59eb7143 by Łukasz Hanuszczak at 2015-07-02T13:33:34+02:00 Add hyperlinker test case for checking type and type family declarations. - - - - - d1cda0c0 by Łukasz Hanuszczak at 2015-07-02T13:41:38+02:00 Fix issue with operators being recognized as preprocessor directives. - - - - - da206c9d by Łukasz Hanuszczak at 2015-07-02T17:18:12+02:00 Fix broken tests for parsing and hyperlinking hash operators. - - - - - 53750d1b by Łukasz Hanuszczak at 2015-07-02T18:53:28+02:00 Add support for anchoring signatures in type class declarations. - - - - - 1fa5bb10 by Łukasz Hanuszczak at 2015-07-02T19:04:47+02:00 Make hyperlinker generate anchors only to top-level value bindings. - - - - - a542305c by Łukasz Hanuszczak at 2015-07-02T19:05:58+02:00 Create hyperlinker test case for type classes. - - - - - b0dd4581 by Łukasz Hanuszczak at 2015-07-04T16:28:26+02:00 Update docs with information about source hyperlinking. - - - - - 9795302a by Łukasz Hanuszczak at 2015-07-04T16:52:15+02:00 Update docs on using `--read-interface` option. - - - - - 9acdc002 by Łukasz Hanuszczak at 2015-07-04T17:15:26+02:00 Remove potentially dangerous record access in hyperlinker AST module. - - - - - fb3ab7be by Łukasz Hanuszczak at 2015-07-04T17:40:10+02:00 Make Haddock generate warnings about potential misuse of hyperlinker. - - - - - a324c504 by Łukasz Hanuszczak at 2015-07-04T17:43:22+02:00 Fix incorrect specification of source style option in doc file. - - - - - 3f01a8e4 by Łukasz Hanuszczak at 2015-07-05T17:06:36+02:00 Refactor source path mapping to use modules as indices. - - - - - ac70f5b1 by Łukasz Hanuszczak at 2015-07-05T17:47:34+02:00 Fix bug where not all module interfaces were added to source mapping. - - - - - f5e57da9 by Łukasz Hanuszczak at 2015-07-06T16:39:57+02:00 Extract main hyperlinker types to separate module. - - - - - 43974905 by Łukasz Hanuszczak at 2015-07-06T16:52:13+02:00 Move source paths types to hyperlinker types module. - - - - - 3e236055 by Łukasz Hanuszczak at 2015-07-06T17:06:19+02:00 Add support for hyperlinking modules in import lists. - - - - - 58233d9f by Łukasz Hanuszczak at 2015-07-06T17:26:49+02:00 Add short documentation for hyperlinker source map type. - - - - - 14da016d by Łukasz Hanuszczak at 2015-07-06T18:07:20+02:00 Fix bug with module name being hyperlinked to `Prelude`. - - - - - 8f79db52 by Łukasz Hanuszczak at 2015-07-06T18:23:47+02:00 Fix problem with spec build in Haddock API configuration. - - - - - e7cc056c by Adam Sandberg Eriksson at 2015-07-07T23:22:21+01:00 StrictData: print correct strictness marks - - - - - e8253ca8 by Mateusz Kowalczyk at 2015-07-07T23:58:28+01:00 Update changelog - - - - - 0aba676b by Mateusz Kowalczyk at 2015-07-07T23:58:33+01:00 Relax upper bound on GHC a bit - - - - - 7a595381 by Mateusz Kowalczyk at 2015-07-07T23:58:52+01:00 Delete trailing whitespace - - - - - 50976d5e by Adam Sandberg Eriksson at 2015-07-08T15:03:04+02:00 StrictData: changes in HsBang type - - - - - 83b045fa by Mateusz Kowalczyk at 2015-07-11T14:35:18+01:00 Fix expansion icon for user-collapsible sections Closes haskell/haddock#412 - - - - - b2a3b0d1 by Mateusz Kowalczyk at 2015-07-22T22:03:21+01:00 Make some version changes after 2.16.1 release - - - - - a8294423 by Ben Gamari at 2015-07-27T13:16:07+02:00 Merge pull request haskell/haddock#422 from adamse/adamse-D1033 Merge for GHC D1033 - - - - - c0173f17 by randen at 2015-07-30T14:49:08-07:00 Break the response file by line termination rather than spaces, since spaces may be within the parameters. This simple approach avoids having the need for any quoting and/or escaping (although a newline char will not be possible in a parameter and has no escape mechanism to allow it). - - - - - 47c0ca14 by Alan Zimmerman at 2015-07-31T10:41:52+02:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - 45a9d770 by Mateusz Kowalczyk at 2015-07-31T09:47:43+01:00 Update changelog - - - - - 347a20a3 by Phil Ruffwind at 2015-08-02T23:15:26+01:00 Avoid JavaScript error during page load in non-frame mode In non-frame mode, parent.window.synopsis refers to the synopsis div rather than the nonexistent frame. Unfortunately, the script wrongly assumes that if it exists it must be a frame, leading to an error where it tries to access the nonexistent attribute 'replace' of an undefined value (synopsis.location). Closes haskell/haddock#406 - - - - - 54ebd519 by Phil Ruffwind at 2015-08-02T23:27:10+01:00 Link to the definitions to themselves Currently, the definitions already have an anchor tag that allows URLs with fragment identifiers to locate them, but it is rather inconvenient to obtain such a URL (so-called "permalink") as it would require finding the a link to the corresponding item in the Synopsis or elsewhere. This commit adds hyperlinks to the definitions themselves, allowing users to obtain links to them easily. To preserve the original aesthetics of the definitions, we alter the color of the link so as to be identical to what it was, except it now has a hover effect indicating that it is clickable. Additionally, the anchor now uses the 'id' attribute instead of the (obsolete) 'name' attribute. Closes haskell/haddock#407 - - - - - 02cc8bb7 by Phil Ruffwind at 2015-08-02T23:28:02+01:00 Fix typo in Haddock.Backends.Xhtml.Layout: divSynposis -> divSynopsis Closes haskell/haddock#408 - - - - - 2eb0a458 by Phil Ruffwind at 2015-08-02T23:30:07+01:00 Fix record field alignment when name is too long Change <dl> to <ul> and use display:table rather than floats to layout the record fields. This avoids bug haskell/haddock#301 that occurs whenever the field name gets too long. Slight aesthetic change: the entire cell of the field's source code is now shaded gray rather than just the area where text exists. Fixes haskell/haddock#301. Closes haskell/haddock#421 - - - - - 7abb3402 by Łukasz Hanuszczak at 2015-08-02T23:32:14+01:00 Add some utility definitions for generating line anchors. - - - - - e0b1d79b by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Make hyperlinked source renderer generate line anchors. - - - - - 24dd4c9f by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Re-accept test cases after adding line anchors for each of them. - - - - - 0372cfcb by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Override source line flags when source hyperlinker is enabled. - - - - - a81bcd07 by Mateusz Kowalczyk at 2015-08-02T23:58:25+01:00 Update tests to follow HTML changes - - - - - d2d7426f by Łukasz Hanuszczak at 2015-08-06T20:54:59+02:00 Fix quote syntax for promoted types. - - - - - 668cf029 by Łukasz Hanuszczak at 2015-08-06T21:12:00+02:00 Apply promoted type quoting to type-level consing. - - - - - 89f8e7c6 by Łukasz Hanuszczak at 2015-08-06T21:17:10+02:00 Extend advanced types test case with other examples. - - - - - 86494bca by Łukasz Hanuszczak at 2015-08-06T21:22:06+02:00 Rename advanced types test case and accept new output. - - - - - dbb7c7c0 by Adam Sandberg Eriksson at 2015-08-09T23:01:05+02:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 2a7704fa by Ben Gamari at 2015-08-10T13:18:05+02:00 Merge pull request haskell/haddock#433 from adamse/split-hsbang HsBang is split into HsSrcBang and HsImplBang - - - - - 891954bc by Thomas Miedema at 2015-08-15T14:51:18+02:00 Follow changes in GHC build system - - - - - b55d32ab by Mateusz Kowalczyk at 2015-08-21T18:06:09+01:00 Make Travis use 7.10.2 - - - - - 97348b51 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Move SYB utilities to standalone module. - - - - - 748ec081 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement `everywhere` transformation in SYB module. - - - - - 011cc543 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement generic transformation constructor. - - - - - b9510db2 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Create simple utility module for type specialization. - - - - - 43229fa6 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Make type of type specialization function more general. - - - - - fd844e90 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Add basic HTML test case for checking instance specialization. - - - - - 6ea0ad04 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Make HTML class instance printer take optional signature argument. - - - - - 65aa41b6 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Refactor instance head type to record instead of a meaningless tuple. - - - - - 3fc3bede by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add expandable method section for each class instance declaration. - - - - - 99ceb107 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Move dummy post-family instances for `DocName` to `Types` module. - - - - - e98f4708 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create convenience functions for type specialization module. - - - - - b947552f by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Hook type specialization logic with HTML pretty-printer. - - - - - dcaa8030 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create stub functions for sugaring specialized types. - - - - - fa84bc65 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement list syntax sugaring logic for specialized types. - - - - - e8b05b07 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement tuple syntax sugaring logic for specialized types. - - - - - 68a2e5bc by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Get rid of code duplication in type specialization module. - - - - - 4721c336 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create scaffolding of a framework for renaming specialized types. - - - - - 271b488d by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in missing cases in specialized type renaming function. - - - - - bfa5f2a4 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Remove code duplication in specialized type renamer. - - - - - ea6bd0e8 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Change state of the type renaming monad. - - - - - 77c5496e by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement simple mechanism for generating new type names. - - - - - 91bfb48b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in stub behaviour with actual environment renaming. - - - - - d244517b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix logic behind binder type renaming. - - - - - f3c5e360 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add SYB-like utility function for performing stateful queries. - - - - - eb3f9154 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create function for retrieving free variables from given type. - - - - - a94561d3 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix compilation error caused by incorrect type signature. - - - - - 8bb707cf by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Move `SetName` class definition to types module. - - - - - 5800b13b by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Hook type renamer with instance method HTML pretty-printer. - - - - - 6a480164 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some test cases for type renamer. - - - - - 839842f7 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized signatures refer to original signature declaration. - - - - - 4880f7c9 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized methods be nicely formatted again. - - - - - ab5a6a2e by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Attach source locations to the specialized class methods. - - - - - 43f8a559 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Extend instances test case to also test multi-name type signatures. - - - - - 59bc751c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix tab-based indentation in instances test case. - - - - - c2126815 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Improve placement of instance methods expander button. - - - - - 0a32e287 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add new data type declaration to instance specialization test case. - - - - - 5281af1f by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make type renamer first try single-letter names as alternatives. - - - - - 7d509475 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix type renamer bug with incorrect names being generated. - - - - - 0f35bf7c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some documentation and refactor type specialization module. - - - - - da1d0803 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix another bug where type renamer was generating incorrect names. - - - - - cd39b5cb by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Refactor type renamer to rebinding and pure renaming phases. - - - - - 850251f4 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix unwitting compilation bug. - - - - - e5e9fc01 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Integrate instance specification type into class instance definition. - - - - - 825b0ea0 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer neccessary instance specification type. - - - - - cdba44eb by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix declaration converter to use more appropriate mode for methods. - - - - - bc45c309 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug with types not being specialized at all. - - - - - 5d8e5d89 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug where instance expander was opening wrong section. - - - - - 6001ee41 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix another type renamer bug where not all names were rebound. - - - - - 5f58ce2a by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix yet another renamer bug where some names were not unique. - - - - - 8265e521 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split instance subsection layout method to top-level declarations. - - - - - e5e66298 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Rearrange layout of instance methods in generated documentation. - - - - - a50b4eea by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer used layout method. - - - - - 2ff36ec2 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach section title to the instance methods block. - - - - - 7ac15300 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Add basic tests for associated types in instances test case. - - - - - db0ea2f9 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach associated types information to instance header. - - - - - 71cad4d5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details section contain associated types information. - - - - - deee2809 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Improve look of rendered associated families in instance details. - - - - - 839d13a5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Introduce alternative type for family declarations. - - - - - d397f03f by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details record use new type for family declarations. - - - - - 2b23fe97 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split printer of type family header to separate functions. - - - - - c3498cdc by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Implement HTML renderer for pseudo-family declarations. - - - - - c12bbb04 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Apply type specializer to associated type family declarations. - - - - - 2fd69ff2 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Create helper method for specializing type signatures. - - - - - 475826e7 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Refactor specializer module to be independent from XHTML backend. - - - - - f00b431c by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add some documentation for instance head specializer. - - - - - a9fef2dc by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix bug with missing space in documentation for associated types. - - - - - 50e29056 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with incorrect instance details sections being expanded. - - - - - e6dfdd03 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by adding instance details section. - - - - - 75565b2a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make section identifier of instance details more GHC-independent. - - - - - add0c23e by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Re-accept tests after applying deterministic section identifiers. - - - - - 878f2534 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make identifier generation also architecture-independent. - - - - - 48be69f8 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with instance expander hijacking type hyperlink click. - - - - - 47830c1f by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Get rid of dreadful hashing function for generating identifiers. - - - - - 956cd5af by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Move `InstOrigin` type declaration to more appropriate module. - - - - - bf672ed3 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by changes related to instance expander. - - - - - 8f2a949a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add examples with type operators to the instances test case. - - - - - 64600a84 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add basic support for sugaring infix type operators. - - - - - 747d71b8 by Łukasz Hanuszczak at 2015-08-21T18:22:34+01:00 Add support for sugaring built-in function syntax. - - - - - d4696ffb by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Remove default methods from Hoogle class output. - - - - - bf0e09d7 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add fixity declarations in Hoogle backend output. - - - - - 90e91a51 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix bug with incorrect fixities being generated in Hoogle backend. - - - - - 48f11d35 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve class type family declarations output in Hoogle backend. - - - - - 661e8e8f by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add missing default family equations in Hoogle output. - - - - - e2d64103 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve formatting of class details output in Hoogle backend. - - - - - 490fc377 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix weird-looking Hoogle output for familyless classes. - - - - - ea115b64 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create script file for new HTML test runner. - - - - - 609913d3 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Set default behaviour if no arguments given. - - - - - dc115f67 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for providing optional arguments for test runner. - - - - - d93ec867 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve output of test runner error messages. - - - - - 0be9fe12 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for executing Haddock process in test runner. - - - - - 4e4d00d9 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add GHC path to test runner configuration. - - - - - d67a2086 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make GHC path a test runner command-line argument. - - - - - c810079a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Extend test runner configuration with Haddock arguments. - - - - - fee18845 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor test runner and create stub functions. - - - - - ff7c161f by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make test runner actually run Haddock executable. - - - - - 391f73e6 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with test runner not producing any output files. - - - - - 81a74e2d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Setup skeleton of framework for running tests. - - - - - f8a79ec4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with modules not being found in global search mode. - - - - - 7e700b4d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make Haddock standard output redirection be more configurable. - - - - - 53b4c17a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Incorporate old, ugly functions for comparing output files. - - - - - 8277c8aa by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor architecture of test runner output checking functions. - - - - - 587bb414 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement actual diffing mechanism. - - - - - 9ed2b5e4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve code style to match popular guidelines. - - - - - 14bffaf8 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make it possible to choose alternative diff tool. - - - - - 5cdfb005 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create stub methods for processing test output as XML documents. - - - - - 7ef8e12e by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement link-stripping logic as simple SYB transformation. - - - - - 8a1fcd4f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Incorporate link stripping to output diffing mechanism. - - - - - 37dba2bc by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement footer-stripping logic. - - - - - 9cd52120 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Add missing dependencies in Cabal configuration file. - - - - - e0f83c6e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix issue with output being printed in incorrect order. - - - - - 0a94fbb0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to run tests without generating diff. - - - - - 76a58c6f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor HTML test suite boilerplate to external package. - - - - - af41e6b0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utilities for storing directory configuration. - - - - - d8f0698f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move IO-dependent config of HTML test suite to test package. - - - - - 17369fa0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Enable all compiler warnings in Haddock test package configuration. - - - - - 9d03b47a by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move Haddock runner of HTML test suite to Haddock test package. - - - - - 4b3483c5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 03754194 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience wrappers to simplify in test entry points. - - - - - 27476ab7 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adjust module visibility and items they export. - - - - - c40002ba by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Remove no longer useful test option. - - - - - 55ab2541 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Change extension of test files used for diffing. - - - - - 136bf4e4 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor and simplify XHTML helper module of test package. - - - - - 69f7e3df by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix typo in link stripper of HTML test suite runner. - - - - - 0c3c1c6b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience script for running specific HTML tests. - - - - - 489e1b05 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement utility functions for conditional link stripping. - - - - - 0f985dc3 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt `hypsrc-test` module to work with new testing framework. - - - - - 927406f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement output accepting mechanism in test package. - - - - - 8545715e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utility function for recursive obtaining directory contents. - - - - - cb70381f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 019599b5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix path handling in test runner. - - - - - 399b985b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to specify ignored files for test output. - - - - - 41b3d93d by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt HTML test runner to use new ignoring functionality. - - - - - e2091c8b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix bug with not all test output files being checked. - - - - - b22134f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Specify ignored files for hyperlinker source test runner. - - - - - 3301dfa1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Copy test runner script for hyperlinked source case. - - - - - d39a6dfa by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner invoking Haddock in incorrect mode. - - - - - f32c8ff3 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix path handling in test module loader. - - - - - 10f94ee9 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make test runner ignore test packages with no modules. - - - - - 5dc4239c by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create test runner entry points for LaTeX test suite. - - - - - 58d1f7cf by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with unnecessary checking old test output. - - - - - c7ce76e1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Re-implement test acceptance functionality. - - - - - 13bbabe8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix warning about no longer needed definition. - - - - - 958a99b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Adapt Cabal configuration to execute LaTeX suite with new runner. - - - - - 550ff663 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Setup test suite for Hoogle backend. - - - - - 3aa969c4 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make Hoogle backend create output directory if needed. - - - - - eb085b02 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Add appropriate .gitignore entry and configure Hoogle test suite. - - - - - a50bf915 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner failing when run on multiple test packages. - - - - - bf5368b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create simple test cases for Hoogle backend. - - - - - 6121ba4b by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create helper function for conversion between XML and XHTML. - - - - - cb516061 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Refactor existing code to use XHTML printer instead of XML one. - - - - - e2de8c82 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Improve portability of test runner scripts. - - - - - 9563e774 by Łukasz Hanuszczak at 2015-08-22T23:43:16+02:00 Remove redundant import statement. - - - - - 55353df1 by Łukasz Hanuszczak at 2015-08-24T23:09:20+02:00 Fix bug with accepting to non-existing directory. - - - - - 00a334ca by Łukasz Hanuszczak at 2015-08-24T23:09:47+02:00 Accept output for Hoogle and LaTeX backends. - - - - - 29191d8b by Łukasz Hanuszczak at 2015-08-24T23:14:18+02:00 Get rid of obsolete testing utilities. - - - - - bbb25db3 by Łukasz Hanuszczak at 2015-08-24T23:18:50+02:00 Update sandbox setup guide to work with Haddock test package. - - - - - cfd45248 by Łukasz Hanuszczak at 2015-08-24T23:51:30+02:00 Make Travis aware of Haddock test package. - - - - - 74185b7a by Łukasz Hanuszczak at 2015-08-25T17:41:59+02:00 Fix test suite failure when used with Stack. - - - - - 18769697 by Łukasz Hanuszczak at 2015-08-25T18:02:09+02:00 Add sample Stack setup to the hacking guide. - - - - - 22715eeb by Łukasz Hanuszczak at 2015-08-25T18:04:47+02:00 Fix Markdown formatting of README file. - - - - - b49ec386 by Łukasz Hanuszczak at 2015-08-25T18:13:36+02:00 Setup Haddock executable path in Travis configuration. - - - - - 5d29eb03 by Eric Seidel at 2015-08-30T09:55:58-07:00 account for changes to ipClass - - - - - f111740a by Ben Gamari at 2015-09-02T13:20:37+02:00 Merge pull request haskell/haddock#443 from bgamari/ghc-head account for changes to ipClass - - - - - a2654bf6 by Jan Stolarek at 2015-09-03T01:32:57+02:00 Follow changes from haskell/haddock#6018 - - - - - 2678bafe by Richard Eisenberg at 2015-09-21T12:00:47-04:00 React to refactoring CoAxiom branch lists. - - - - - ebc56e24 by Edward Z. Yang at 2015-09-21T11:53:46-07:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4a8c4198 by Tamar Christina at 2015-09-27T13:59:08+02:00 Create Process: removed PhaseFailed - - - - - 7e99b790 by Oleg Grenrus at 2015-09-27T20:52:10+03:00 Generate docs for orphan instances - - - - - 32e932e2 by Oleg Grenrus at 2015-09-28T07:21:11+03:00 Have source links for orphan instances - - - - - c2eb9f4f by Oleg Grenrus at 2015-09-28T07:24:58+03:00 Print orphan instances header only if required - - - - - ff96f978 by Oleg Grenrus at 2015-09-28T07:40:54+03:00 Add orphan instances link to contents box - - - - - d72490a6 by Oleg Grenrus at 2015-09-28T16:37:44+03:00 Fix orphan instance collapsing - - - - - 25d3dfe5 by Ben Gamari at 2015-10-03T12:38:09+02:00 Merge pull request haskell/haddock#448 from Mistuke/fix-silent-death-of-runInteractive Remove PhaseFailed - - - - - 1e45e43b by Edward Z. Yang at 2015-10-11T13:10:10-07:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b1370ac1 by Adam Gundry at 2015-10-16T16:26:42+01:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 60bef421 by Simon Peyton Jones at 2015-10-26T12:52:36+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 4c1898ca by Simon Peyton Jones at 2015-10-27T14:24:56+00:00 Track change to PatSyn.patSynSig - - - - - 25108e85 by Simon Peyton Jones at 2015-10-27T17:34:18+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - 693643ac by Ben Gamari at 2015-10-28T14:33:06+01:00 Account for Typeable changes The treatment of type families changed. - - - - - cd7c2221 by Simon Peyton Jones at 2015-10-30T13:03:51+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - 712032cb by Herbert Valerio Riedel at 2015-10-31T11:01:45+01:00 Relax upper bound on `base` to allow base-4.9 - - - - - 0bfa0475 by Simon Peyton Jones at 2015-10-31T19:08:13+00:00 More adaption to wildcard-refactor - - - - - 0a3c0cb7 by Simon Peyton Jones at 2015-10-31T22:14:43+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - c4fd4ec9 by Alan Zimmerman at 2015-11-01T11:16:34+01:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 42cdd882 by Matthew Pickering at 2015-11-06T20:02:16+00:00 Change for IEThingWith - - - - - f368b7be by Ben Gamari at 2015-11-11T11:35:51+01:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - e32965b8 by Simon Peyton Jones at 2015-11-13T12:18:17+00:00 Merge with origin/head - - - - - ebcf795a by Edward Z. Yang at 2015-11-13T21:56:27-08:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4e23989f by Simon Peyton Jones at 2015-11-18T11:32:54+00:00 Wibbles to Haddock - - - - - 2289cd4a by Simon Peyton Jones at 2015-11-20T23:12:49+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor - - - - - 695975a6 by Alan Zimmerman at 2015-11-21T21:16:12+02:00 Update to match GHC wip/T11019 - - - - - bbba21e7 by Simon Peyton Jones at 2015-11-23T13:54:31+00:00 merge with origin/ghc-head - - - - - 3d664258 by Simon Peyton Jones at 2015-11-23T17:17:18+00:00 Wibble - - - - - e64cf586 by Herbert Valerio Riedel at 2015-12-05T00:29:55+01:00 Canonicalise Monad instances - - - - - a2de15a7 by Alan Zimmerman at 2015-12-05T17:33:52+02:00 Matching changes for haskell/haddock#11028 - - - - - cc29a3e4 by Alan Zimmerman at 2015-12-05T19:45:33+02:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 95dd15d1 by Richard Eisenberg at 2015-12-11T17:33:39-06:00 Update for type=kinds - - - - - cb5fd9ed by Herbert Valerio Riedel at 2015-12-14T15:07:30+00:00 Bump versions for ghc-7.11 - - - - - 4f286d96 by Simon Peyton Jones at 2015-12-14T15:10:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 13ea2733 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 098df8b8 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track changes in HsSyn for quasi-quotes - - - - - 716a64de by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track change in API of TyCon - - - - - 77a66bca by Adam Gundry at 2015-12-14T15:10:58+00:00 Track API changes to support empty closed type familes - - - - - f2808305 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track the new location of setRdrNameSpace - - - - - ba8b08a4 by Alan Zimmerman at 2015-12-14T15:10:59+00:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - a4ded87e by Thomas Winant at 2015-12-14T15:14:05+00:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 25c78107 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: print correct strictness marks - - - - - 6cbc41c4 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: changes in HsBang type - - - - - ad46821a by Alan Zimmerman at 2015-12-14T15:14:06+00:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - abc0ae5b by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 3308d06c by Thomas Miedema at 2015-12-14T15:14:07+00:00 Follow changes in GHC build system - - - - - 6c763deb by Eric Seidel at 2015-12-14T15:14:07+00:00 account for changes to ipClass - - - - - ae5b4eac by Jan Stolarek at 2015-12-14T15:17:00+00:00 Follow changes from haskell/haddock#6018 - - - - - ffbc40e0 by Richard Eisenberg at 2015-12-14T15:17:02+00:00 React to refactoring CoAxiom branch lists. - - - - - d1f531e9 by Edward Z. Yang at 2015-12-14T15:17:02+00:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 79f73754 by Tamar Christina at 2015-12-14T15:17:02+00:00 Create Process: removed PhaseFailed - - - - - 3d37bebb by Edward Z. Yang at 2015-12-14T15:20:46+00:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 5f8a9e44 by Adam Gundry at 2015-12-14T15:20:48+00:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 79dda70f by Simon Peyton Jones at 2015-12-14T15:26:02+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 959930fb by Simon Peyton Jones at 2015-12-14T15:37:50+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - e18a8df5 by Simon Peyton Jones at 2015-12-14T15:37:52+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - aa35ab52 by Simon Peyton Jones at 2015-12-14T15:40:18+00:00 More adaption to wildcard-refactor - - - - - 8ceef94b by Simon Peyton Jones at 2015-12-14T15:46:04+00:00 Track change to PatSyn.patSynSig - - - - - cd81e83d by Ben Gamari at 2015-12-14T15:46:06+00:00 Account for Typeable changes The treatment of type families changed. - - - - - 63c9117c by Herbert Valerio Riedel at 2015-12-14T15:46:34+00:00 Relax upper bound on `base` to allow base-4.9 - - - - - a484c613 by Alan Zimmerman at 2015-12-14T15:47:46+00:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 2c26fa51 by Matthew Pickering at 2015-12-14T15:47:47+00:00 Change for IEThingWith - - - - - 593baa0f by Ben Gamari at 2015-12-14T15:49:21+00:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - b6b5ca78 by Edward Z. Yang at 2015-12-14T15:49:54+00:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b5b0e072 by Alan Zimmerman at 2015-12-14T15:54:20+00:00 Update to match GHC wip/T11019 - - - - - 14ddeb68 by Simon Peyton Jones at 2015-12-14T15:54:22+00:00 Wibble - - - - - 10a90ad8 by Herbert Valerio Riedel at 2015-12-14T15:54:22+00:00 Canonicalise Monad instances - - - - - ed68ac50 by Alan Zimmerman at 2015-12-14T15:55:48+00:00 Matching changes for haskell/haddock#11028 - - - - - 3f7e5a2d by Alan Zimmerman at 2015-12-14T15:55:49+00:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 6543a73f by Richard Eisenberg at 2015-12-14T15:59:55+00:00 Update for type=kinds - - - - - 193a5c48 by Matthew Pickering at 2015-12-14T18:17:00+00:00 Changes to compile with 8.0 - - - - - add669ec by Matthew Pickering at 2015-12-14T18:47:12+00:00 Warnings - - - - - 223f3fb4 by Ben Gamari at 2015-12-15T23:45:05+01:00 Update for D1200 - - - - - d058388f by Ben Gamari at 2015-12-16T05:40:17-05:00 Types: Add Outputable[Bndr] DocName instances - - - - - 62ecd7fb by Ben Gamari at 2015-12-16T09:23:09-05:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ddbc187a by Ben Gamari at 2015-12-16T17:54:55+01:00 Update for D1200 - - - - - cec83b52 by Ben Gamari at 2015-12-16T17:54:55+01:00 Types: Add Outputable[Bndr] DocName instances - - - - - d12ecc98 by Ben Gamari at 2015-12-16T17:54:55+01:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ada1616f by Ben Gamari at 2015-12-16T17:54:58+01:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a4f0383d by Ben Gamari at 2015-12-16T23:32:38+01:00 Fix Hyperlinker GHC.con_names is now GHC.getConNames - - - - - a10e6849 by Ben Gamari at 2015-12-20T00:54:11+01:00 Merge remote-tracking branch 'mrhania/testing-framework-improvements' into ghc-head - - - - - f078b4fd by Ben Gamari at 2015-12-20T00:59:51+01:00 test: Compatibility with Cabal 1.23 - - - - - 88a511a9 by Ben Gamari at 2015-12-20T01:14:35+01:00 Merge remote-tracking branch 'phadej/orphans' into ghc-head - - - - - 4e250f36 by Ben Gamari at 2015-12-20T01:14:52+01:00 Add html-test for orphan instances output - - - - - 87fffbad by Alan Zimmerman at 2015-12-20T09:50:42+02:00 Update for GHC trac#11258 Adding locations to RdrName in FieldOcc and AmbiguousFieldOcc - - - - - 6b7e51c9 by idontgetoutmuch at 2015-12-20T21:01:47+00:00 Merge pull request haskell/haddock#1 from haskell/ghc-head Ghc head - - - - - 229c1fb5 by Dominic Steinitz at 2015-12-21T07:19:16+00:00 Handle inline math with mathjax. - - - - - 57902d66 by Dominic Steinitz at 2015-12-21T08:07:11+00:00 Fix the documentation for haddock itself. Change notation and add support for inline math. Allow newlines in display math. Add a command line option for the mathjax url (you might want to use a locally installed version). Rebase tests because of extra url and version change. Respond to (some of the) comments. Fix warnings in InterfaceFile.hs - - - - - 0e69f236 by Herbert Valerio Riedel at 2015-12-21T18:30:43+01:00 Fix-up left-over assumptions of GHC 7.12 into GHC 8.0 - - - - - c67f8444 by Simon Peyton Jones at 2015-12-22T16:26:56+00:00 Follow removal of NamedWildCard from HsType - - - - - da40327a by Ben Gamari at 2015-12-23T14:15:28+01:00 html-test/Operators: Clear up ambiguous types For reasons that aren't entirely clear a class with ambiguous types was accepted by GHC <8.0. I've added a functional dependency to clear up this ambiguity. - - - - - 541b7fa4 by Ben Gamari at 2015-12-23T14:18:51+01:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 0febc947 by Ben Gamari at 2015-12-24T00:30:20+01:00 hoogle-test/AssocTypes: Allow AmbiguousTypes GHC 8.0 complains otherwise - - - - - 25810841 by Ben Gamari at 2015-12-24T00:33:18+01:00 OrphanInstances: Accept test output - - - - - 841987f3 by Ben Gamari at 2015-12-25T11:03:11+01:00 Merge remote-tracking branch 'idontgetoutmuch/ghc-head' into ghc-head - - - - - 358391f0 by Ben Gamari at 2015-12-26T10:44:50+01:00 Add missing import - - - - - a8896885 by Ben Gamari at 2015-12-26T10:45:27+01:00 travis: Use Travis containers - - - - - 85e82134 by Herbert Valerio Riedel at 2015-12-30T17:25:39+01:00 tweak version bounds for GHC-8.1 - - - - - 672a5f75 by randen at 2016-01-01T23:45:25-08:00 The Haddock part for fully gcc-like response files " driver/Main.hs * Moved the response file handling into ResponseFile.hs, updating import section as appropriate. * driver/ResponseFile.hs * New file. In anticipation that maybe some day this could be provided by another library, and to make it possible to unit test, this functionality is pulled out of the Main.hs module, and expanded to support the style/format of response files which gcc uses. * The specification for the format of response files which gcc generates and consumes, seems to be best derived from the gcc code itself (libiberty/argv.c), so that is what has been done here. * This is intended to fix haskell/haddock#379 * driver-test/Main.hs * New file for testing code in the driver source tree * driver-test/ResponseFileSpec.hs * Tests, adapted/adopted from the same gcc code where the escaping/unescaping is from, in the hspec style of unit tests * haddock.cabal * Add the driver-test test-suite. Introduces a new library dependency (upon hspec) for the haddock driver target in the haddock.cabal file, but practically, this should not be a problem as the haddock-api tests already depend on hspec. - - - - - 498781df by Ben Gamari at 2016-01-06T13:41:04+01:00 Version bumps and changelog - - - - - 8451e46a by Ben Gamari at 2016-01-06T13:47:17+01:00 Merge remote-tracking branch 'randen/bug468' - - - - - fb2d9181 by Ben Gamari at 2016-01-06T08:14:42-05:00 Add ResponseFile to OtherModules - - - - - 2cb2d2e3 by Ben Gamari at 2016-01-06T14:35:00+01:00 Merge branch 'master' into ghc-head - - - - - 913477d4 by Eric Seidel at 2016-01-11T14:57:57-08:00 deal with un-wiring of IP class - - - - - c557a4b3 by Alan Zimmerman at 2016-01-15T11:14:35+02:00 Update to match wip/T11430 in GHC - - - - - 3e135093 by Alan Zimmerman at 2016-01-16T18:21:59+01:00 Update to match wip/T11430 in GHC - - - - - c48ef2f9 by Ben Gamari at 2016-01-18T09:50:06+01:00 Merge remote-tracking branch 'gridaphobe/ghc-head' into ghc-head - - - - - 9138a1b0 by Eric Seidel at 2016-01-18T12:50:15+01:00 deal with un-wiring of IP class (cherry picked from commit 17388b0f0029d969d79353be7737eb01c7b8dc5f) - - - - - b48c172e by Joachim Breitner at 2016-01-19T00:11:38+01:00 Make sure --mathjax affects all written HTML files This fixes haskell/haddock#475. - - - - - af61fe63 by Ryan Scott at 2016-02-07T23:25:57+01:00 Render */# instead of TYPE 'Lifted/TYPE 'Unlifted (fixes haskell/haddock#473) - - - - - b6458693 by Ben Gamari at 2016-02-07T23:29:27+01:00 Merge pull request haskell/haddock#477 from haskell/issue-475 Make sure --mathjax affects all written HTML files - - - - - adcc0071 by Ben Gamari at 2016-02-07T23:34:52+01:00 Merge branch 'master' into ghc-head - - - - - d0404e61 by Ben Gamari at 2016-02-08T12:46:49+01:00 doc: Switch to Sphinx - - - - - acb153b3 by Ben Gamari at 2016-02-08T12:46:56+01:00 Document --use-unicode flag - - - - - c20bdf1d by Ben Gamari at 2016-02-08T13:41:24+01:00 Fix GHC and haddock-library dependency bounds - - - - - 8d946801 by Ben Gamari at 2016-02-08T14:54:56+01:00 testsuite: Rework handling of output sanitization Previously un-cleaned artifacts were kept as reference output, making it difficult to tell what has changed and causing spurious changes in the version control history. Here we rework this, cleaning the output during acceptance. To accomplish this it was necessary to move to strict I/O to ensure the reference handle was closed before accept attempts to open the reference file. - - - - - c465705d by Ben Gamari at 2016-02-08T15:36:05+01:00 test: Compare on dump For reasons I don't understand the Xml representations differ despite their textual representations being identical. - - - - - 1ec0227a by Ben Gamari at 2016-02-08T15:36:05+01:00 html-test: Accept test output - - - - - eefbd63a by Ben Gamari at 2016-02-08T15:36:08+01:00 hypsrc-test: Accept test output And fix impredicative Polymorphism testcase. - - - - - d1df4372 by Ben Gamari at 2016-02-08T15:40:44+01:00 Merge branch 'fix-up-testsuite' - - - - - 206a3859 by Phil Ruffwind at 2016-02-08T17:51:21+01:00 Move the permalinks to "#" on the right side Since pull request haskell/haddock#407, the identifiers have been permalinked to themselves, but this makes it difficult to copy the identifier by double-clicking. To work around this usability problem, the permalinks are now placed on the far right adjacent to "Source", indicated by "#". Also, 'namedAnchor' now uses 'id' instead of 'name' (which is obsolete). - - - - - 6c89fa03 by Phil Ruffwind at 2016-02-08T17:54:44+01:00 Update tests for previous commit - - - - - effaa832 by Ben Gamari at 2016-02-08T17:56:17+01:00 Merge branch 'anchors-redux' - - - - - 9a2bec90 by Ben Gamari at 2016-02-08T17:58:40+01:00 Use -fprint-unicode-syntax when --use-unicode is enabled This allows GHC to render `*` as its Unicode representation, among other things. - - - - - 28ecac5b by Ben Gamari at 2016-02-11T18:53:03+01:00 Merge pull request haskell/haddock#480 from bgamari/sphinx Move documentation to ReStructuredText - - - - - 222e5920 by Ryan Scott at 2016-02-11T15:42:42-05:00 Collapse type/data family instances by default - - - - - a80ac03b by Ryan Scott at 2016-02-11T20:17:09-05:00 Ensure expanded family instances render correctly - - - - - 7f985231 by Ben Gamari at 2016-02-12T10:04:22+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - d4eda086 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Various cleanups - - - - - 79bee48d by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show kind signatures for type family variables Addresses GHC haskell/haddock#11588. - - - - - b2981d98 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show 'where ...' after closed type family Seems like we should ideally show the actual equations as well but that seems like it would be a fair amount of work - - - - - cfc0e621 by Ben Gamari at 2016-02-18T22:48:12+01:00 Merge pull request haskell/haddock#483 from bgamari/T11588 Fix GHC haskell/haddock#11588 This fixes GHC haskell/haddock#11588: * Show where ... after closed type families * Show kind signatures on type family type variables - - - - - 256e8a0d by Ben Gamari at 2016-02-18T23:15:39+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 32402036 by Richard Eisenberg at 2016-02-24T13:21:44-05:00 Follow-on changes to support RuntimeRep - - - - - 2b1c572d by Matthew Pickering at 2016-03-04T21:04:02+00:00 Remove unused functions - - - - - eb906f50 by Richard Eisenberg at 2016-03-13T21:17:20+01:00 Follow-on changes to support RuntimeRep (cherry picked from commit ab954263a793d8ced734459d6194a5d89214b66c) - - - - - 8c34ef34 by Richard Eisenberg at 2016-03-14T23:47:23-04:00 Changes due to fix for GHC#11648. - - - - - 0e022014 by Richard Eisenberg at 2016-03-15T14:06:45+01:00 Changes due to fix for GHC#11648. (cherry picked from commit bb994de1ab0c76d1aaf1e39c54158db2526d31f1) - - - - - ed3f78ab by Rik Steenkamp at 2016-04-02T22:20:36+01:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 - - - - - d3210042 by Rik Steenkamp at 2016-04-04T15:43:32+02:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 (cherry picked from commit 3ddcbd6b8e6884bd95028381176eb33bee6896fb) - - - - - 236eec90 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 692ee7e0 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. - - - - - 79619f57 by Ben Gamari at 2016-04-10T23:46:22+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. (cherry picked from commit c6d6a18d85e5e2d9bb5904e6919e8a8d7e31c4c5) - - - - - 3358ccb4 by Ben Gamari at 2016-04-10T23:47:27+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 264949b1 by Ben Gamari at 2016-04-16T17:50:23+02:00 Merge pull request haskell/haddock#482 from RyanGlScott/ghc-head Collapse type/data family instances by default - - - - - 478c483a by Ben Gamari at 2016-04-16T17:51:09+02:00 Merge pull request haskell/haddock#489 from mpickering/unused-functions Remove some unused functions - - - - - c94e55f0 by Ryan Scott at 2016-04-16T17:57:54+02:00 Collapse type/data family instances by default (cherry picked from commit 2da130a8db8f995c119b544fad807533236cf088) - - - - - 31e633d3 by Ryan Scott at 2016-04-16T17:58:06+02:00 Ensure expanded family instances render correctly (cherry picked from commit 1338b5d7c32939de6bbc31af0049477e4f847103) - - - - - 03e4d197 by Matthew Pickering at 2016-04-16T17:58:21+02:00 Remove unused functions (cherry picked from commit b89d1c2456bdb2d4208d94ded56155f7088a37d0) - - - - - ed4116f6 by Ben Gamari at 2016-04-20T10:46:57+02:00 ghc: Install files for needed --hyperlinked-source - - - - - 0be999c4 by Ben Gamari at 2016-04-20T11:37:54+02:00 ghc: Install files for needed --hyperlinked-source (cherry picked from commit 5c82c9fc2d21ddaae4a2470f1c375426968f19c6) - - - - - 4d17544c by Simon Peyton Jones at 2016-04-20T12:42:28+01:00 Track change to HsGroup This relates to a big GHC patch for Trac haskell/haddock#11348 - - - - - 1700a50d by Ben Gamari at 2016-05-01T13:19:27+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. - - - - - 0b7c8125 by Ben Gamari at 2016-05-01T13:21:43+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. (cherry picked from commit 609018dd09c4ffe27f9248b2d8b50f6196cd42b9) - - - - - af115ce0 by Ryan Scott at 2016-05-04T22:15:50-04:00 Render Haddocks for derived instances Currently, one can document top-level instance declarations, but derived instances (both those in `deriving` clauses and standalone `deriving` instances) do not enjoy the same privilege. This makes the necessary changes to the Haddock API to enable rendering Haddock comments for derived instances. This is part of a fix for Trac haskell/haddock#11768. - - - - - 76fa1edc by Ben Gamari at 2016-05-10T18:13:25+02:00 haddock-test: A bit of refactoring for debuggability - - - - - 7d4c4b20 by Ben Gamari at 2016-05-10T18:13:25+02:00 Create: Mark a comment as TODO - - - - - 2a6d0c90 by Ben Gamari at 2016-05-10T18:13:25+02:00 html-test: Update reference output - - - - - bd60913d by Ben Gamari at 2016-05-10T18:13:25+02:00 hypsrc-test: Fix reference file path in cabal file It appears the haddock insists on prefixing --hyperlinked-sourcer output with directory which the source appeared in. - - - - - c1548057 by Ben Gamari at 2016-05-10T18:22:12+02:00 doc: Update extra-source-files in Cabal file - - - - - 41d5bae3 by Ben Gamari at 2016-05-10T18:29:21+02:00 Bump versions - - - - - ca75b779 by Ben Gamari at 2016-05-11T16:03:44+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 4e3cfd62 by Ben Gamari at 2016-05-11T16:06:45+02:00 Merge remote-tracking branch 'RyanGlScott/ghc-head' into ghc-head - - - - - a2379970 by Ben Gamari at 2016-05-11T23:15:11+02:00 doc: Add clean targets - - - - - f275212e by Ben Gamari at 2016-05-11T23:15:14+02:00 doc: Add html as an all-target for ghc Otherwise the html documentation won't be installed for binary-dist. - - - - - 388fc0af by Ben Gamari at 2016-05-12T09:49:12+02:00 Update CHANGES - - - - - bad81ad5 by Ben Gamari at 2016-05-12T09:49:38+02:00 Version bump - - - - - c01688a7 by Ben Gamari at 2016-05-12T10:04:58+02:00 Revert "Version bump" This bump was a bit premature. This reverts commit 7b238d9c5be9b07aa2d10df323b5c7b8d1634dc8. - - - - - 7ed05724 by Ben Gamari at 2016-05-12T10:05:33+02:00 doc: Fix GHC clean rule Apparently GHC's build system doesn't permit wildcards in clean paths. - - - - - 5d9611f4 by Ben Gamari at 2016-05-12T17:43:50+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 653566b2 by Ben Gamari at 2016-05-14T09:57:31+02:00 Version bump to 2.17.2 - - - - - b355c439 by Ben Gamari at 2016-05-14T09:57:51+02:00 doc: Use `$(MAKE)` instead of `make` This is necessary to ensure we use gmake. - - - - - 8a18537d by Ben Gamari at 2016-05-14T10:15:45+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - b3290ef1 by Sebastian Meric de Bellefon at 2016-05-14T11:29:47-04:00 Fix haskell/haddock#303. Hide footer when printing The "Produced by Haddock" footer was overlapping the page's body when printing. This patch hides the footer with a css media rule. - - - - - b4a76f89 by Sebastian Meric de Bellefon at 2016-05-15T02:12:46-04:00 Fix haskell/haddock#280. Parsing of module header The initial newlines were counted as indentation spaces, thus disturbing the parsing of next lines - - - - - ba797c9e by Ben Gamari at 2016-05-16T14:53:46+02:00 doc: Vendorize alabaster Sphinx theme Alabaster is now the default sphinx theme and is a significant improvement over the previous default that it's worthproviding it when unavailable (e.g. Sphinx <1.3). - - - - - c9283e44 by Ben Gamari at 2016-05-16T14:55:17+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 1c9ea198 by Sebastian Méric de Bellefon at 2016-05-16T12:30:40-04:00 Merge pull request haskell/haddock#502 from Helkafen/master Fix haskell/haddock#303. Hide footer when printing - - - - - 33631016 by Ben Gamari at 2016-05-16T19:56:11+02:00 Revert "doc: Vendorize alabaster Sphinx theme" This ended up causes far too many issues to be worthwhile. We'll just have to live with inconsistent haddock documentation. This reverts commit cec21957001143794e71bcd9420283df18e7de40. - - - - - 93317d26 by Ben Gamari at 2016-05-16T19:56:11+02:00 cabal: Fix README path - - - - - c8695b22 by Ben Gamari at 2016-05-16T19:58:51+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 0b50eaaa by Ben Gamari at 2016-05-16T21:02:08+02:00 doc: Use whichever theme sphinx deems appropriate - - - - - 857c1c9c by Ben Gamari at 2016-05-16T21:07:08+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 15fc5637 by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Remove redundant imports - - - - - 132ddc6a by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Better debug output For tracking down haskell/haddock#505 - - - - - 2252a149 by Ben Gamari at 2016-05-22T12:43:59+02:00 Don't consider default class ops when looking for decls When we are looking for an operation within a class we don't care about `default`-type declarations. This was the cause of haskell/haddock#505. - - - - - 4886b2ec by Oleg Grenrus at 2016-05-24T16:19:48+03:00 UnfelpfulSpan line number omitted Kind of resolves https://github.com/haskell/haddock/issues/508 - - - - - a4befd36 by Oleg Grenrus at 2016-05-24T16:53:35+03:00 Change Hyperlinked lexer to know about DataKinds ticks - - - - - f45cb52e by David Feuer at 2016-05-24T18:48:53-04:00 Make parser state a newtype Previously, it was `data` wrapping a `Maybe`, which seems a bit silly. Obviously, this can be changed back if anyone wants to add more fields some day. - - - - - 05013dd7 by Sebastian Meric de Bellefon at 2016-05-24T22:03:55-04:00 remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) Frames are a bit broken, ignored by Hackage, and considered obsolete in general. This patch disables frames generation. The mini_*.html files are still used in the synopsis. - - - - - b8163a88 by Ben Gamari at 2016-05-25T14:44:15+02:00 Merge pull request haskell/haddock#507 from bgamari/T505 Fix haskell/haddock#505 - - - - - ea1b30c6 by Sebastian Meric de Bellefon at 2016-05-25T14:17:00-04:00 Update CHANGES - - - - - eddfc258 by Sebastian Méric de Bellefon at 2016-05-25T15:17:40-04:00 Merge pull request haskell/haddock#514 from Helkafen/frames remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) - - - - - 0e506818 by Alex Biehl at 2016-05-26T12:43:09+02:00 Remove misplaced haddock comment - - - - - a07d28c0 by Ben Gamari at 2016-05-27T11:34:59+02:00 Merge pull request haskell/haddock#515 from alexbiehl/master Remove misplaced haddock comment - - - - - 9001d267 by Ben Gamari at 2016-05-27T11:35:46+02:00 Merge pull request haskell/haddock#513 from treeowl/newtype-since Make parser state a newtype - - - - - 74e1a018 by Sebastian Méric de Bellefon at 2016-05-28T17:28:15-04:00 Merge pull request haskell/haddock#504 from Helkafen/issue-280 Fix haskell/haddock#280. Parsing of module header - - - - - 37557f4f by Alan Zimmerman at 2016-05-29T23:36:50+02:00 Matching changes for haskell/haddock#12105 - - - - - 7d09e5d6 by Sebastian Meric de Bellefon at 2016-06-03T18:07:48-04:00 Version bumps (2.17.3, 1.4.2) - - - - - 85b4bc15 by Sebastian Méric de Bellefon at 2016-06-06T18:35:13-04:00 Merge pull request haskell/haddock#521 from Helkafen/master Version bumps (2.17.3, 1.4.2) - - - - - e95f0dee by Sebastian Meric de Bellefon at 2016-06-06T19:11:35-04:00 publish haddock-test library - - - - - 4de40586 by Sebastian Méric de Bellefon at 2016-06-06T20:26:30-04:00 Merge pull request haskell/haddock#512 from phadej/oleg-fixes Fixes for haskell/haddock#508 and haskell/haddock#510 - - - - - ddfd0789 by Dominic Steinitz at 2016-06-09T09:27:28+01:00 Documentation for LaTeX markup. - - - - - 697a503a by Dominic Steinitz at 2016-06-09T09:33:59+01:00 Fix spelling mistake. - - - - - 246f6fff by Dominic Steinitz at 2016-06-09T09:37:15+01:00 Camel case MathJax. - - - - - 4684bd23 by Dominic Steinitz at 2016-06-09T09:44:53+01:00 Fix math typo and add link. - - - - - f20c037c by Simon Peyton Jones at 2016-06-13T18:26:03+01:00 Follow changes to LHsSigWcType - - - - - 0c58996d by Simon Peyton Jones at 2016-06-15T12:56:01+01:00 Follow GHC re-adding FunTy - - - - - 401b5ca7 by Sebastian Méric de Bellefon at 2016-06-15T12:16:47-04:00 Merge pull request haskell/haddock#525 from idontgetoutmuch/master Documentation for LaTeX markup. - - - - - 92d263b7 by Sebastian Méric de Bellefon at 2016-06-15T12:17:29-04:00 Merge pull request haskell/haddock#522 from Helkafen/master publish haddock-test library - - - - - 0953a2ca by Sebastian Meric de Bellefon at 2016-06-16T00:46:46-04:00 Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 65453e14 by Ben Gamari at 2016-06-16T11:16:32+02:00 ocean: Ensure that synopsis fully covers other content Previously MathJax content was being rendered on top of the synopsis due to ambiguous z-ordering. Here we explicitly give the synopsis block a higher z-index to ensure it is rendered on top. Fixes haskell/haddock#531. - - - - - 68e411a1 by Sebastian Méric de Bellefon at 2016-06-16T23:34:39-04:00 Merge pull request haskell/haddock#534 from bgamari/T531 ocean: Ensure that synopsis fully covers other content - - - - - fad6491b by Sebastian Méric de Bellefon at 2016-06-18T23:57:20-04:00 Merge pull request haskell/haddock#533 from Helkafen/master Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 6108e21b by Sebastian Meric de Bellefon at 2016-06-22T23:08:28-04:00 do not create empty src directory Fix haskell/haddock#536. - - - - - 1ef23823 by Sebastian Méric de Bellefon at 2016-06-24T00:04:48-04:00 Merge pull request haskell/haddock#537 from Helkafen/master do not create empty src directory - - - - - 966baa96 by Omari Norman at 2016-06-29T21:59:34-04:00 Add $ as a special character If this character is not escaped, documentation built with Haddock 2.17.2 will fail. This was not an issue with 2.16 series, which causes builds to fail and there is nothing in the docs or error message giving a clue about why builds that used to succeed now don't. - - - - - 324adb60 by Ben Gamari at 2016-07-01T12:18:51+02:00 GhcUtils: Changes for multi-pattern signatures - - - - - d7571675 by Ömer Sinan Ağacan at 2016-07-21T13:30:47+02:00 Add support for unboxed sums - - - - - 29d0907b by Simon Marlow at 2016-07-22T13:55:48+01:00 Disable NFData instances for GHC types when GHC >= 8.2 - - - - - 702d95f3 by Simon Marlow at 2016-08-02T15:57:30+02:00 Disable NFData instances for GHC types when GHC >= 8.0.2 (cherry picked from commit a3309e797c42dae9bccdeb17ce52fcababbaff8a) - - - - - f4fa79c3 by Ben Gamari at 2016-08-07T13:51:18+02:00 ghc.mk: Don't attempt to install html/frames.html The frames business has been removed. - - - - - 9cd63daf by Ben Gamari at 2016-08-07T13:51:40+02:00 Haddock.Types: More precise version guard This allows haddock to be built with GHC 8.0.2 pre-releases. - - - - - f3d7e03f by Mateusz Kowalczyk at 2016-08-29T20:47:45+01:00 Merge pull request haskell/haddock#538 from massysett/master Add $ as a special character - - - - - 16dbf7fd by Bartosz Nitka at 2016-09-20T19:44:04+01:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 - - - - - 7c31c1ff by Bartosz Nitka at 2016-09-27T17:32:22-04:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 (cherry picked from commit 073d899a8f94ddec698f617a38d3420160a7fd0b) - - - - - 33a90dce by Ryan Scott at 2016-09-30T20:53:41-04:00 Haddock changes for T10598 See https://ghc.haskell.org/trac/ghc/ticket/10598 - - - - - 1f32f7cb by Ben Gamari at 2016-10-13T20:01:26-04:00 Update for refactoring of NameCache - - - - - 1678ff2e by Ben Gamari at 2016-11-15T17:42:48-05:00 Bump upper bound on base - - - - - 9262a7c5 by Alan Zimmerman at 2016-12-07T21:14:28+02:00 Match changes in GHC wip/T3384 branch - - - - - ac0eaf1a by Ben Gamari at 2016-12-09T09:48:41-05:00 haddock-api: Don't use stdcall calling convention on 64-bit Windows See GHC haskell/haddock#12890. - - - - - 04afe4f7 by Alan Zimmerman at 2016-12-12T20:07:21+02:00 Matching changes for GHC wip/T12942 - - - - - e1d1701d by Ben Gamari at 2016-12-13T16:50:41-05:00 Bump base upper bound - - - - - 3d3eacd1 by Alan Zimmerman at 2017-01-10T16:59:38+02:00 HsIParamTy now has a Located name - - - - - 7dbceefd by Kyrill Briantsev at 2017-01-12T13:23:50+03:00 Prevent GHC API from doing optimization passes. - - - - - d48d1e33 by Richard Eisenberg at 2017-01-19T08:41:41-05:00 Upstream changes re levity polymorphism - - - - - 40c25ed6 by Alan Zimmerman at 2017-01-26T15:16:18+02:00 Changes to match haskell/haddock#13163 in GHC - - - - - 504f586d by Ben Gamari at 2017-02-02T17:19:37-05:00 Kill remaining static flags - - - - - 49147ea0 by Justus Adam at 2017-03-02T15:33:34+01:00 Adding MDoc to exports of Documentation.Haddock - - - - - 1cfba9b4 by Justus Adam at 2017-03-09T11:41:44+01:00 Also exposing toInstalledIface - - - - - 53f0c0dd by Ben Gamari at 2017-03-09T13:10:08-05:00 Bump for GHC 8.3 - - - - - c7902d2e by Ben Gamari at 2017-03-09T23:46:02-05:00 Bump for GHC 8.2 - - - - - 4f3a74f8 by Ben Gamari at 2017-03-10T10:21:55-05:00 Merge branch 'ghc-head' - - - - - e273b72f by Richard Eisenberg at 2017-03-14T13:34:04-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - 6ec3d436 by Richard Eisenberg at 2017-03-14T15:15:52-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - eee3cda1 by Ben Gamari at 2017-03-15T15:19:59-04:00 Adapt to EnumSet - - - - - 017cf58e by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 736d6773 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 475f84a0 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 13240b53 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - cd16d529 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 3bea97ae by Edward Z. Yang at 2017-03-15T22:50:46-07:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b2b051ce by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 0f082795 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 20ef63c9 by Edward Z. Yang at 2017-03-22T13:48:12-07:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 45692dcb by Edward Z. Yang at 2017-03-22T14:11:25-07:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4eae8caf by Ben Gamari at 2017-03-23T09:25:33-04:00 Merge commit '240bc38b94ed2d0af27333b23392d03eeb615e82' into HEAD - - - - - 0bbe03f5 by Ben Gamari at 2017-03-23T09:27:28-04:00 haddock-api: Bump bound on GHC - - - - - 65f3ac9d by Alex Biehl at 2017-03-23T17:36:11+01:00 Merge pull request haskell/haddock#581 from JustusAdam/master Adding more exports to Documentation.Haddock - - - - - 37d49a47 by Alex Biehl at 2017-03-23T17:39:14+01:00 Merge pull request haskell/haddock#568 from awson/ghc-head Prevent GHC API from doing optimization passes. - - - - - 1ed047e4 by Brian Huffman at 2017-03-23T17:45:58+01:00 Print any user-supplied kind signatures on type parameters. This applies to type parameters on data, newtype, type, and class declarations, and also to forall-bound type vars in type signatures. - - - - - 1b78ca5c by Brian Huffman at 2017-03-23T17:45:58+01:00 Update test suite to expect kind annotations on type parameters. - - - - - a856b162 by Alex Biehl at 2017-03-23T17:49:32+01:00 Include travis build indication badge - - - - - 8e2e2c56 by Ben Gamari at 2017-03-23T17:20:08-04:00 haddock-api: Bump bound on GHC - - - - - 4d2d9995 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 26d6c150b31bc4580ab17cfd07b6e7f9afe10737) - - - - - a650e20f by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 930cfbe58e2e87f5a4d431d89a3c204934e6e858) - - - - - caa282c2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 2067a2d0afa9cef381d26fb7140b67c62f433fc0) - - - - - 49684884 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 0671abfe7e8ceae2269467a30b77ed9d9656e2cc) - - - - - 4dcfeb1a by Edward Z. Yang at 2017-03-23T17:20:08-04:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 3d77b373dd5807d5d956719dd7c849a11534fa6a) - - - - - 74dd19d2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 94610e9b446324f4231fa6ad4c6ac51e4eba8c0e) - - - - - a9b19a23 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 6cc832dfb1de6088a4abcaae62b25a7e944d55c3) - - - - - d3631064 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit bf3c4d72a0fda38561376eac7eda216158783267) - - - - - ef2148fc by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 07b88c5d4e79b87a319fbb08f8ea01dbb41063c1) - - - - - 2f29518b by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 4eb765ca4205c79539d60b7afa9b7e261a4a49fe) - - - - - 37de047d by Phil Ruffwind at 2017-04-03T11:57:14+02:00 Update MathJax URL MathJax is shutting down their CDN: https://www.mathjax.org/cdn-shutting-down/ They recommend migrating to cdnjs. - - - - - e9d24ba8 by David C. Turner at 2017-04-03T14:58:01+02:00 Add highlight for :target to ocean.css - - - - - 4819a202 by Alex Biehl at 2017-04-11T19:36:48+02:00 Allow base-4.10 for haddock-test - - - - - 44cec69c by Alex Biehl at 2017-04-11T19:39:22+02:00 cabal.project for haddock-api, haddock-library and haddock-test - - - - - 935d0f6a by Alex Biehl at 2017-04-11T19:46:29+02:00 Move dist scripts to scripts/ - - - - - 128e150c by Alex Biehl at 2017-04-11T20:34:46+02:00 Add haddock to cabal.project - - - - - cc8e08ea by Alex Biehl at 2017-04-11T20:35:08+02:00 Read files for hyperlinker eagerly This also exposes Documentation.Haddock.Utf8 - - - - - 152dda78 by Alex Biehl at 2017-04-11T20:37:06+02:00 Explicit import list ofr Control.DeepSeq in Haddock.Interface.Create - - - - - 501b33c4 by Kyrill Briantsev at 2017-04-11T21:01:42+02:00 Prevent GHC API from doing optimization passes. - - - - - c9f3f5ff by Alexander Biehl at 2017-04-12T16:36:53+02:00 Add @alexbiehl as maintaner - - - - - 76f214cc by Alex Biehl at 2017-04-13T07:27:18+02:00 Disable doctest with ghc-8.3 Currently doctest doesn't support ghc-head - - - - - 46b4f5fc by Edward Z. Yang at 2017-04-22T20:38:26-07:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f0555235 by Alex Biehl at 2017-04-25T10:08:48+02:00 Travis: Use ghc-8.2.1 on master - - - - - 966ea348 by Alex Biehl at 2017-04-25T10:32:01+02:00 Travis: Verbose cabal output cf. https://travis-ci.org/haskell/haddock/jobs/225512194#L377 - - - - - 36972bcd by Alex Biehl at 2017-04-25T10:40:43+02:00 Use travis_retry for cabal invocations - - - - - b3a09d2c by Alex Biehl at 2017-04-25T17:02:20+02:00 Use new MathJax URL in html-test 18ed871afb82560d5433b2f53e31b4db9353a74e switched to a new MathJax URL but didn't update the tests. - - - - - ae331e5f by Alexander Biehl at 2017-04-25T17:02:20+02:00 Expand signatures for class declarations - - - - - e573c65a by Alexander Biehl at 2017-04-25T17:02:20+02:00 Hoogle: Correctly print classes with associated data types - - - - - 3fc6be9b by Edward Z. Yang at 2017-04-25T17:02:20+02:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit a0c4790e15a2d3fab8d830eee8fcd639fe6d39c9) - - - - - 6725c060 by Herbert Valerio Riedel at 2017-04-25T17:02:20+02:00 `html-test --accept` deltas to reference samples - - - - - 7d444d61 by Alex Biehl at 2017-04-26T07:13:50+02:00 Remove anything related to obsolete frames mode - - - - - b888972c by Alex Biehl at 2017-04-26T07:49:10+02:00 Cherry-picked remaining commits from haddock-2.17.4-release (#603) * Release haddock/haddock-api 2.17.4 and haddock-library 1.4.3 * Set version bounds for haddock-library NB: This allows GHC 8.2.1's base * Set version bounds for haddock & haddock-api The version bounds support GHC 8.2 * Merge (temporary) v2.17.3 branch into v2.17 This allows us to delete the v2.17.3 branch * Fixup changelog * Pin down haddock-api to a single version as otherwise `haddock`'s package version has no proper meaning * fix source-repo spec for haddock-api - - - - - 4161099b by Alex Biehl at 2017-04-26T11:11:20+02:00 Update changelog to reflect news in HEAD - - - - - eed72cb8 by Alex Biehl at 2017-04-26T11:11:20+02:00 Markdownify changelog - - - - - 5815cea1 by Alex Biehl at 2017-04-26T11:32:33+02:00 Bump to 2.18.0 (#605) - - - - - a551d558 by Alex Biehl at 2017-04-29T22:00:25+02:00 Update attoparsec-0.12.1.1 to attoparsec-0.13.1.0 - - - - - ea164a8d by Sergey Vinokurov at 2017-04-29T22:42:36+02:00 Improve error message - - - - - 2e10122f by Alex Biehl at 2017-04-30T10:07:46+02:00 Correctly remember collapsed sections (#608) Now the "collapsed" cookie stores which sections have changed state instead of which are collapsed. - - - - - f9b24d99 by Alex Biehl at 2017-05-01T17:40:36+02:00 Lazily decode docMap and argMap (#610) These are only used in case of a doc reexport so most of the time decoding these is wasted work. - - - - - 2372af62 by Alex Biehl at 2017-05-01T21:59:23+02:00 Fix Binary instance for InstalledInterface (#611) (#610) introduced lazy decoding for docs from InstalledInterface but forgot to remove the original calls to get and put_ - - - - - 6c633c13 by Nathan Collins at 2017-05-11T11:47:55+02:00 Improve documenation of Haddock markup (#614) * Improve documentation of Haddock markup. - document that Haddock supports inferring types top-level functions with without type signatures, but also explain why using this feature is discouraged. Looks like this feature has been around since version 2.0.0.0 in 2008! - rework the "Module description" section: - move the general discussion of field formatting to the section intro and add examples illustrating the prose for multiline fields. - mention that newlines are preserved in some multiline fields, but not in others (I also noticed that commas in the `Copyright` field are not preserved; I'll look into this bug later). - add a subsection for the module description fields documentation, and put the field keywords in code formatting (double back ticks) instead of double quotes, to be consistent with the typesetting of keywords in other parts of the documentation. - mention that "Named chunks" are not supported in the long-form "Module description" documentation. - fix formatting of keywords in the "Module attributes" section. Perhaps these errors were left over from an automatic translation to ReST from some other format as part of the transition to using Sphinx for Haddock documentation? Also, add a missing reference here; it just said "See ?"! - update footnote about special treatment for re-exporting partially imported modules not being implemented. In my tests it's not implemented at all -- I tried re-exporting both `import B hiding (f)` and `import B (a, b)` style partial imports, and in both cases got the same result as with full imports `import B`: I only get a module reference. * Rework the `Controlling the documentation structure` section. My main goal was to better explain how to use Haddock without an export list, since that's my most common use case, but I hope I improved the section overall: - remove the incomplete `Omitting the export list` section and fold it into the other sections. In particular, summarize the differences between using and not using an export list -- i.e. control over what and in what order is documented -- in the section lead. - add "realistic" examples that use the structure markup, both with and without an export list. I wanted a realistic example here to capture how it can be useful to explain the relationship between a group of functions in a section, in addition to documenting their individual APIs. - make it clear that you can associate documentation chunks with documentation sections when you aren't using an export list, and that doing it in the most obvious way -- i.e. with `-- |`, as you can in the export list -- doesn't work without an export list. It took me a while to figure this out the first time, since the docs didn't explain it at all before. - add a "no export list" example to the section header section. - add more cross references. * Add examples of gotchas for markup in `@...@`. I'm not sure this will help anyone, since I think most people first learn about `@...@` by reading other people's Haddocks, but I've documented the mistakes which I've made and then gotten confused by. * Use consistent Capitalization of Titles. Some titles were in usual title caps, and others only had the first word capitalized. I chose making them all use title caps because that seems to make the cross references look better. - - - - - d4734f45 by Ben Gamari at 2017-05-12T20:36:08+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 93883f37 by Alex Biehl at 2017-05-12T21:02:33+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 5b8f179c by Alex Biehl at 2017-05-13T12:48:10+02:00 Consequently use inClass and notInClass in haddock-library (#617) These allow attoparsec to do some clever lookup optimization - - - - - 77984b82 by Doug Wilson at 2017-05-27T17:37:38+02:00 Don't enable compilation for template haskell (#624) This is no longer necessary after ghc commit 53c78be0aab76a3107c4dacbb1d177afacdd37fa - - - - - 5a3de2b4 by Doug Wilson at 2017-05-27T19:54:53+02:00 Improve Syb code (#621) Specialize.hs and Ast.hs are modified to have their Syb code not recurse into Name or Id in HsSyn types. Specialize.hs is refactored to have fewer calls to Syb functions. Syb.hs has some foldl calls replaced with foldl' calls. There is still a lot of performance on the floor of Ast.hs. The RenamedSource is traversed many times, and lookupBySpan is very inefficient. everywhereBut and lookupBySpan dominate the runtime whenever --hyperlinked-source is passed. - - - - - 3d35a949 by Alex Biehl at 2017-05-30T19:01:37+02:00 Clear fixme comment (#625) - - - - - 2a44bd0c by Alex Biehl at 2017-05-30T19:02:12+02:00 Make haddock-library and haddock-api warning free (#626) - - - - - bd1a0e42 by Alex Biehl at 2017-06-01T10:40:33+02:00 Include `driver-test/*.hs` sdist (#630) This lead to haskell/haddock#629. - - - - - 184a3ab6 by Doug Wilson at 2017-06-03T12:02:08+02:00 Disable pattern match warnings (#628) This disables the pattern match checker which can be very expensive in some cases. The disabled warnings include: * Opt_WarnIncompletePatterns * Opt_WarnIncompleteUniPatterns * Opt_WarnIncompletePatternsRecUpd * Opt_WarnOverlappingPatterns - - - - - 0cf68004 by Alex Biehl at 2017-06-03T20:37:28+02:00 Allow user defined signatures for pattern synonyms (#631) - - - - - 7f51a58a by Alex Biehl at 2017-06-04T11:56:38+02:00 Use NameSet for isExported check (#632) - - - - - d8f044a9 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Match new AST as per GHC wip/new-tree-one-param See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow - - - - - da1254e3 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Rename extension index tags - - - - - 538c7514 by Christiaan Baaij at 2017-06-09T08:26:43+02:00 Haddock support for bundled pattern synonyms (#627) * Haddock support for bundled pattern synonyms * Add fixities to bundled pattern synonyms * Add bundled pattern synonyms to the synopsis * Store bundled pattern fixities in expItemFixities * Add test for bundled pattern synonyms * Stop threading fixities * Include bundled pattern synonyms for re-exported data types Sadly, fixity information isn't found for re-exported data types * Support for pattern synonyms * Modify tests after haskell/haddock#631 * Test some reexport variations * Also lookup bundled pattern synonyms from `InstalledInterface`s * Check isExported for bundled pattern synonyms * Pattern synonym is exported check * Always look for pattern synonyms in the current module Another overlooked cornercase * Account for types named twice in export lists Also introduce a fast function for nubbing on a `Name` and use it throughout the code base. * correct fixities for reexported pattern synonyms * Fuse concatMap and map * Remove obsolete import * Add pattern synonyms to visible exports * Fix test * Remove corner case - - - - - a050bffd by Doug Wilson at 2017-06-21T09:27:33+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#636) There is some performance improvement. GHC compiler: | version | bytes allocated | cpu_seconds --------------------------------- | before | 56057108648 | 41.0 | after | 51592019560 | 35.1 base: | version | bytes allocated | cpu_seconds --------------------------------- | before | 25174011784 | 14.6 | after | 23712637272 | 13.1 Cabal: | version | bytes allocated | cpu_seconds --------------------------------- | before | 18754966920 | 12.6 | after | 18198208864 | 11.6 - - - - - 5d06b871 by Doug Wilson at 2017-06-22T20:23:29+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#639) * Use new function getNameToInstancesIndex instead of tcRnGetInfo There is some significant performance improvement in the ghc testsuite. haddock.base: -23.3% haddock.Cabal: -16.7% haddock.compiler: -19.8% * Remove unused imports - - - - - b11bb73a by Alex Biehl at 2017-06-23T14:44:41+02:00 Lookup fixities for reexports without subordinates (#642) So we agree that reexported declarations which do not have subordinates (for example top-level functions) shouldn't have gotten fixities reexported according to the current logic. I wondered why for example Prelude.($) which is obviously reexported from GHC.Base has fixities attached (c.f. http://hackage.haskell.org/package/base-4.9.1.0/docs/Prelude.html#v:-36-). The reason is this: In mkMaps we lookup all the subordinates of top-level declarations, of course top-level functions don't have subordinates so for them the resulting list is empty. In haskell/haddock#644 I established the invariant that there won't be any empty lists in the subordinate map. Without the patch from haskell/haddock#642 top-level functions now started to fail reexporting their fixities. - - - - - d2a6dad6 by Alex Biehl at 2017-06-23T18:30:45+02:00 Don't include names with empty subordinates in maps (#644) These are unecessary anyway and just blow up interface size - - - - - 69c2aac4 by Alex Biehl at 2017-06-29T19:54:49+02:00 Make per-argument docs for class methods work again (#648) * Make per-argument docs for class methods work again * Test case - - - - - c9448d54 by Bartosz Nitka at 2017-07-02T12:12:01+02:00 Fix haddock: internal error: links: UnhelpfulSpan (#561) * Fix haddock: internal error: links: UnhelpfulSpan This fixes haskell/haddock#554 for me. I believe this is another fall out of `wildcard-refactor`, like haskell/haddock#549. * Comment to clarify why we take the methods name location - - - - - d4f29eb7 by Alex Biehl at 2017-07-03T19:43:04+02:00 Document record fields when DuplicateRecordFields is enabled (#649) - - - - - 9d6e3423 by Yuji Yamamoto at 2017-07-03T22:37:58+02:00 Fix test failures on Windows (#564) * Ignore .stack-work * Fix for windows: use nul instead of /dev/null * Fix for windows: canonicalize line separator * Also normalize osx line endings - - - - - 7d81e8b3 by Yuji Yamamoto at 2017-07-04T16:13:12+02:00 Avoid errors on non UTF-8 Windows (#566) * Avoid errors on non UTF-8 Windows Problem ==== haddock exits with errors like below: `(1)` ``` haddock: internal error: <stderr>: hPutChar: invalid argument (invalid character) ``` `(2)` ``` haddock: internal error: Language\Haskell\HsColour\Anchors.hs: hGetContents: invalid argument (invalid byte sequence) ``` `(1)` is caused by printing [the "bullet" character](http://www.fileformat.info/info/unicode/char/2022/index.htm) onto stderr. For example, this warning contains it: ``` Language\Haskell\HsColour\ANSI.hs:62:10: warning: [-Wmissing-methods] • No explicit implementation for ‘toEnum’ • In the instance declaration for ‘Enum Highlight’ ``` `(2)` is caused when the input file of `readFile` contains some Unicode characters. In the case above, '⇒' is the cause. Environment ---- OS: Windows 10 haddock: 2.17.3 GHC: 8.0.1 Solution ==== Add `hSetEncoding handle utf8` to avoid the errors. Note ==== - I found the detailed causes by these changes for debugging: - https://github.com/haskell/haddock/commit/8f29edb6b02691c1cf4c479f6c6f3f922b35a55b - https://github.com/haskell/haddock/commit/1dd23bf2065a1e1f2c14d0f4abd847c906b4ecb4 - These errors happen even after executing `chcp 65001` on the console. According to the debug code, `hGetEncoding stderr` returns `CP932` regardless of the console encoding. * Avoid 'internal error: <stderr>: hPutChar: invalid argument (invalid character)' non UTF-8 Windows Better solution for 59411754a6db41d17820733c076e6a72bcdbd82b's (1) - - - - - eded67d2 by Alex Biehl at 2017-07-07T19:17:15+02:00 Remove redudant import warning (#651) - - - - - 05114757 by Alex Biehl at 2017-07-08T00:33:12+02:00 Avoid missing home module warning (#652) * Avoid missing home module warning * Update haddock-library.cabal - - - - - e9cfc902 by Bryn Edwards at 2017-07-17T07:51:20+02:00 Fix haskell/haddock#249 (#655) - - - - - eb02792b by Herbert Valerio Riedel at 2017-07-20T09:09:15+02:00 Fix compilation of lib:haddock-library w/ GHC < 8 - - - - - 9200bfbc by Alex Biehl at 2017-07-20T09:20:38+02:00 Prepare 2.18.1 release (#657) - - - - - 46ddd22c by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Tweak haddock-api.cabal for pending release - - - - - 85e33d29 by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Avoid trivial use of LambdaCase otherwise we can't test w/ e.g. GHC 7.4.2 - - - - - 3afb4bfe by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Refactor .cabal to use sub-lib for vendored lib A practical benefit is that we can control the build-depends and also avoid some recompilation between library and test-suite. - - - - - e56a552e by Herbert Valerio Riedel at 2017-07-20T10:17:48+02:00 haddock-api: add changelog pointing to haddock's changelog This addresses https://github.com/haskell/haddock/issues/638#issuecomment-309283297 - - - - - 2222ff0d by Herbert Valerio Riedel at 2017-07-20T10:19:56+02:00 Drop obsolete/misleading `stability: experimental` This .cabal property has long been considered obsolete - - - - - 9b882905 by Alex Biehl at 2017-07-20T11:25:54+02:00 Beef up haddock description (#658) * Beef up haddock description * Handle empty lines - - - - - bb60e95c by Herbert Valerio Riedel at 2017-07-20T12:08:53+02:00 Import @aisamanra's Haddock cheatsheet from https://github.com/aisamanra/haddock-cheatsheet - - - - - 0761e456 by Herbert Valerio Riedel at 2017-07-20T12:12:55+02:00 Add cheatsheet to haddock.cabal - - - - - 2ece0f0f by Herbert Valerio Riedel at 2017-07-20T12:18:38+02:00 Mention new-build in README - - - - - 947b7865 by Herbert Valerio Riedel at 2017-07-20T12:32:16+02:00 Update README Also improves markup and removes/fixes redundant/obsolete parts [skip ci] - - - - - 785e09ad by Alex Biehl at 2017-07-27T07:28:57+02:00 Bump haddock to 2.18.2, haddock-library to 1.4.5 - - - - - e3ff1ca3 by Alex Biehl at 2017-07-31T20:15:32+02:00 Move `DocMarkup` from haddock-api to haddock-library (#659) * Move `DocMarkup` from haddock-api to haddock-library * Move more markup related functions * Markup module * CHANGELOG - - - - - cda7c20c by Alex Biehl at 2017-07-31T20:35:49+02:00 Fixup haddock - - - - - 583b6812 by Alex Biehl at 2017-07-31T21:20:45+02:00 Changelog for haddock-library - - - - - bac6a0eb by Alex Biehl at 2017-07-31T21:50:24+02:00 Prepare haddock-library-1.4.5 release - - - - - 58ce6877 by Moritz Drexl at 2017-08-05T16:44:40+02:00 Fix renaming after instance signature specializing (#660) * rework rename * Add regression test for Bug 613 * update tests * update changelog - - - - - b8137ec8 by Tim Baumann at 2017-08-06T11:33:38+02:00 Fix: Generate pattern signatures for constructors exported as patterns (#663) * Fix pretty-printing of pattern signatures Pattern synonyms can have up to two contexts, both having a different semantic meaning: The first holds the constraints required to perform the matching, the second contains the constraints provided by a successful pattern match. When the first context is empty but the second is not it is necessary to render the first, empty context. * Generate pattern synonym signatures for ctors exported as patterns This fixes haskell/haddock#653. * Simplify extractPatternSyn It is not necessary to generate the simplest type signature since it will be simplified when pretty-printed. * Add changelog entries for PR haskell/haddock#663 * Fix extractPatternSyn error message - - - - - d037086b by Alex Biehl at 2017-08-06T12:43:25+02:00 Bump haddock-library - - - - - 99d7e792 by Alex Biehl at 2017-08-06T12:44:07+02:00 Bump haddock-library in haddock-api - - - - - 94802a5b by Alex Biehl at 2017-08-06T13:18:02+02:00 Provide --show-interface option to dump interfaces (#645) * WIP: Provide --show-interface option to dump interfaces Like ghcs own --show-iface this flag dumps a binary interface file to stdout in a human (and machine) readable fashion. Currently it uses json as output format. * Fill all the jsonNull stubs * Rework Bifunctor instance of DocH, update changelog and documentation * replace changelog, bring DocMarkupH doc back * Update CHANGES.md * Update CHANGES.md * Move Control.Arrow up It would result in unused import if the Bifunctor instance is not generated. - - - - - c662e476 by Ryan Scott at 2017-08-14T21:00:21-04:00 Adapt to haskell/haddock#14060 - - - - - b891eb73 by Alex Biehl at 2017-08-16T08:24:48+02:00 Bifoldable and Bitraversable for DocH and MetaDoc - - - - - 021bb56c by Alex Biehl at 2017-08-16T09:06:40+02:00 Refactoring: Make doc renaming monadic This allows us to later throw warnings if can't find an identifier - - - - - 39fbf022 by Alex Biehl at 2017-08-19T20:35:27+02:00 Hyperlinker: Avoid linear lookup in enrichToken (#669) * Make Span strict in Position * Hyperlinker: Use a proper map to enrich tokens - - - - - e13baedd by Alex Biehl at 2017-08-21T20:05:42+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 27dd6e87 by Alex Biehl at 2017-08-21T22:06:35+02:00 Drop Avails from export list - - - - - 86b247e2 by Alex Biehl at 2017-08-22T08:44:22+02:00 Bump ghc version for haddock-api tests - - - - - d4607ca0 by Alex Biehl at 2017-08-22T08:45:17+02:00 Revert "Drop Avails from export list" This reverts commit a850ba86d88a4fb9c0bd175453a2580e544e3def. - - - - - c9c54c30 by Alex Biehl at 2017-08-22T09:26:01+02:00 IntefaceFile version - - - - - a85b7c02 by Ben Gamari at 2017-08-22T09:29:52-04:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 34e976f5 by Ben Gamari at 2017-08-22T17:40:06+02:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 577abf06 by Ryan Scott at 2017-08-23T14:47:29-04:00 Update for haskell/haddock#14131 - - - - - da68fc55 by Florian Eggenhofer at 2017-08-27T18:21:56+02:00 Generate an index for package content search (#662) Generate an index for package content search - - - - - 39e62302 by Alex Biehl at 2017-08-27T18:50:16+02:00 Content search for haddock html doc - - - - - 91fd6fb2 by Alex Biehl at 2017-08-28T18:39:58+02:00 Fix tests for content search - - - - - b4a3798a by Alex Biehl at 2017-08-28T18:44:08+02:00 Add search button to #page-menu - - - - - 25a7ca65 by Alex Biehl at 2017-08-28T18:47:43+02:00 Load javascript below the fold - - - - - 8d323c1a by Alex Biehl at 2017-08-28T18:49:22+02:00 Accept tests - - - - - c5dac557 by Alex Biehl at 2017-08-28T19:14:55+02:00 Content search css - - - - - 89a5af57 by Paolo Veronelli at 2017-08-29T07:42:13+02:00 Removed `nowrap` for interface method sigs (#674) with nowrap the interfaces method sigs would expand at libitum - - - - - a505f6f7 by Alex Biehl at 2017-08-29T08:05:33+02:00 Include subordinates in content index - - - - - 4bb698c4 by Alexander Biehl at 2017-08-29T11:40:19+02:00 QuickNav: Make docbase configurable - - - - - c783bf44 by Alexander Biehl at 2017-08-29T11:48:36+02:00 QuickNav: Also use baseUrl for doc-index.json request - - - - - 47017510 by Alex Biehl at 2017-08-29T17:56:47+02:00 Fix test fallout (again) - - - - - 924fc318 by Alex Biehl at 2017-08-30T09:24:56+02:00 Write meta.json when generating html output (#676) - - - - - 717dea52 by Alex Biehl at 2017-09-01T09:20:34+02:00 Use relative URL when no docBaseUrl given - - - - - e5d85f3b by Alex Biehl at 2017-09-01T09:35:19+02:00 Add missing js files to data-files (#677) - - - - - 95b9231a by Alex Biehl at 2017-09-01T11:01:36+02:00 Rename "Search" tab to "Quick Jump" - - - - - da0ead0b by Alex Biehl at 2017-09-01T13:03:49+02:00 Make trigger link configurable (#678) QuickNav: Configurable show/hide trigger - - - - - de7da594 by Ben Gamari at 2017-09-05T06:49:55-04:00 Account for "Remember the AvailInfo for each IE" As of GHC commit f609374a55bdcf3b79f3a299104767aae2ffbf21 GHC retains the AvailInfo associated with each IE. @alexbiehl has a patch making proper use of this change, but this is just to keep things building. - - - - - b05cd3b3 by Ben Gamari at 2017-09-14T07:55:07-04:00 Bump upper bound on base - - - - - 79db899e by Herbert Valerio Riedel at 2017-09-21T23:27:52+02:00 Make compatible with Prelude.<> export in GHC 8.4/base-4.11 - - - - - 3405dd52 by Tim Baumann at 2017-09-23T22:02:01+02:00 Add compile step that bundles and compresses JS files (#684) * Add compile step that bundles and compresses JS files Also, manage dependencies on third-party JS libraries using NPM. * Compile JS from TypeScript * Enable 'noImplicitAny' in TypeScript * QuickJump: use JSX syntax * Generate source maps from TypeScript for easier debugging * TypeScript: more accurate type * Separate quick jump css file from ocean theme - - - - - df0b5742 by Alex Biehl at 2017-09-29T21:15:40+02:00 Bump base for haddock-library and haddock-test - - - - - 62b12ea0 by Merijn Verstraaten at 2017-10-04T16:03:13+02:00 Inhibit output of coverage information for hidden modules. (#687) * Inhibit output of coverage information for hidden modules. * Add changelog entry. - - - - - 8daf8bc1 by Alexander Biehl at 2017-10-05T11:27:05+02:00 Don't use subMap in attachInstances - - - - - ad75114e by Alexander Biehl at 2017-10-05T11:27:58+02:00 Revert "Don't use subMap in attachInstances" This reverts commit 3adf5bcb1a6c5326ab33dc77b4aa229a91d91ce9. - - - - - 7d4aa02f by Alex Biehl at 2017-10-08T15:32:28+02:00 Precise Haddock: Use Avails for export resolution (#688) * Use Avails for export resolution * Support reexported modules * Factor out availExportItem * Use avails for fullModuleExports * Don't use subMap in attachInstances * lookupDocs without subMap * Completely remove subMap * Only calculate unqualified modules when explicit export list is given * Refactor * Refine comment * return * Fix * Refactoring * Split avail if declaration is not exported itself * Move avail splitting - - - - - b9b4faa8 by Alex Biehl at 2017-10-08T19:38:21+02:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 43325295 by Alex Biehl at 2017-10-08T20:18:46+02:00 Fix merge fallout - - - - - c6423cc0 by Alex Biehl at 2017-10-08T20:36:12+02:00 Copy QuickJump files over - - - - - 1db587c3 by Tim Baumann at 2017-10-09T18:33:09+02:00 Use <details> element for collapsibles (#690) * Remove unnecessary call to 'collapseSection' The call is unnecessary since there is no corresponding toggle for hiding the section of orphan instances. * Use <details> for collapsibles This makes them work even when JS is disabled. Closes haskell/haddock#560. - - - - - 1b54c64b by Tim Baumann at 2017-10-10T09:50:59+02:00 Quick Jump: Show error when loading 'doc-index.json' failed (#691) - - - - - 910f716d by Veronika Romashkina at 2017-10-24T07:36:20+02:00 Fix tiny typo in docs (#693) - - - - - b21de7e5 by Ryan Scott at 2017-10-24T13:07:15+02:00 Overhaul Haddock's rendering of kind signatures (#681) * Overhaul Haddock's rendering of kind signatures * Strip off kind signatures when specializing As an added bonus, this lets us remove an ugly hack specifically for `(->)`. Yay! * Update due to 0390e4a0f61e37bd1dcc24a36d499e92f2561b67 * @alexbiehl's suggestions * Import injectiveVarsOfBinder from GHC - - - - - 6704405c by Ryan Scott at 2017-10-28T07:10:27+02:00 Fix Haddock rendering of kind-indexed data family instances (#694) - - - - - 470f6b9c by Alex Biehl at 2017-10-30T08:45:51+01:00 Add QuickJump version to meta.json (#696) - - - - - b89eccdf by Alex Biehl at 2017-10-30T10:15:49+01:00 Put Quickjump behind --quickjump flag (#697) - - - - - 3095fb58 by Alex Biehl at 2017-10-30T19:09:06+01:00 Add build command to package.json - - - - - f223fda9 by Alex Biehl at 2017-10-30T19:10:39+01:00 Decrease threshold for fuzzy matching - - - - - 80245dda by Edward Z. Yang at 2017-10-31T20:35:05+01:00 Supported reexported-modules via --reexport flag. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 7e389742 by Alex Biehl at 2017-10-31T20:37:56+01:00 Correct missing title in changelog - - - - - 1a2a1c03 by Alex Biehl at 2017-10-31T20:59:07+01:00 Copy quickjump.css for nicer error messages - - - - - db234bb9 by Alex Biehl at 2017-10-31T21:31:18+01:00 Reexported modules: Report warnings if argument cannot be parsed or ... module cannot be found - - - - - eea8a205 by Carlo Hamalainen at 2017-10-31T21:43:14+01:00 More general type for nameCacheFromGhc. (#539) - - - - - 580eb42a by Alex Biehl at 2017-10-31T21:46:52+01:00 Remote tab - - - - - 0e599498 by Alex Biehl at 2017-10-31T21:48:55+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 7b8539bb by Alex Biehl at 2017-10-31T22:28:34+01:00 fullModuleContents traverses exports in declaration order - - - - - 0c91fbf2 by Alex Biehl at 2017-10-31T22:32:31+01:00 Remove excessive use of list comprehensions - - - - - f7356e02 by Alex Biehl at 2017-11-01T19:11:03+01:00 Make better use of AvailInfo - - - - - f3e512d5 by Alex Biehl at 2017-11-02T12:16:22+01:00 Always return documentation for exported subordinates ... event if they have no documentation (e.g. noDocForDecl) By using the information in the AvailInfo we don't need additional export checks. - - - - - 7cf58898 by Alan Zimmerman at 2017-11-07T08:28:03+02:00 Match changes for Trees that Grow in GHC - - - - - e5105a41 by Alan Zimmerman at 2017-11-08T17:21:58+02:00 Match Trees That Grow - - - - - 55178266 by Alan Zimmerman at 2017-11-11T22:20:31+02:00 Match Trees that Grow in GHC for HsExpr - - - - - 2082ab02 by Ryan Scott at 2017-11-14T15:27:03+01:00 Actually render infix type operators as infix (#703) * Actually render infix type operators as infix * Account for things like `(f :*: g) p`, too - - - - - c52ab7d0 by Alan Zimmerman at 2017-11-14T23:14:26+02:00 Clean up use of PlaceHolder, to match TTG - - - - - 81cc9851 by Moritz Angermann at 2017-11-20T07:52:49+01:00 Declare use of `Paths_haddock` module in other-modules (#705) This was detected by `-Wmissing-home-modules` - - - - - f9d27598 by Moritz Angermann at 2017-11-20T12:47:34+01:00 Drop Paths_haddock from ghc.mk (#707) With haskell/haddock#705 and haskell/haddock#706, the custom addition should not be necessary any more. # Conflicts: # ghc.mk - - - - - f34818dc by Moritz Angermann at 2017-11-20T12:47:59+01:00 Add autogen-modules (#706) > Packages using 'cabal-version: >= 1.25' and the autogenerated module Paths_* must include it also on the 'autogen-modules' field besides 'exposed-modules' and 'other-modules'. This specifies that the module does not come with the package and is generated on setup. Modules built with a custom Setup.hs script also go here to ensure that commands like sdist don't fail. # Conflicts: # haddock.cabal - - - - - bb43a0aa by Ben Gamari at 2017-11-21T15:50:12-05:00 Revert "Clean up use of PlaceHolder, to match TTG" This reverts commit 134a7bb054ea730b13c8629a76232d73e3ace049. - - - - - af9ebb2b by Ben Gamari at 2017-11-21T15:50:14-05:00 Revert "Match Trees that Grow in GHC for HsExpr" This reverts commit 9f054dc365379c66668de6719840918190ae6e44. - - - - - 5d35c3af by Ben Gamari at 2017-11-21T15:50:15-05:00 Revert "Match Trees That Grow" This reverts commit 73a26af844ac50b8bec39de11d64452a6286b00c. - - - - - 99a8e43b by Ben Gamari at 2017-11-21T16:36:06-05:00 Revert "Match changes for Trees that Grow in GHC" This reverts commit 01eeeb048acd2dd05ff6471ae148a97cf0720547. - - - - - c4d650c2 by Ben Gamari at 2017-12-04T15:06:07-05:00 Bump GHC version - - - - - 027b2274 by Ben Gamari at 2017-12-04T17:06:31-05:00 Bump GHC bound to 8.4.* - - - - - 58eaf755 by Alex Biehl at 2017-12-06T15:44:24+01:00 Update changelog - - - - - d68f5584 by Simon Peyton Jones at 2017-12-07T14:39:56+00:00 Track changes to follow Trac haskell/haddock#14529 This tracks the refactoring of HsDecl.ConDecl. - - - - - dc519d6b by Alec Theriault at 2018-01-06T08:20:43-08:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - 8285118c by Alec Theriault at 2018-01-13T12:12:37+01:00 Constructor and pattern synonym argument docs (#709) * Support Haddocks on constructor arguments This is in conjunction with https://phabricator.haskell.org/D4094. Adds support for rendering Haddock's on (non-record) constructor arguments, both for regular and GADT constructors. * Support haddocks on pattern synonym arguments It appears that GHC already parsed these - we just weren't using them. In the process of doing this, I tried to deduplicate some code around handling patterns. * Update the markup guide Add some information about the new support for commenting constructor arguments, and mention pattern synonyms and GADT-style constructors. * Overhaul LaTeX support for data/pattern decls This includes at least * fixing several bugs that resulted in invalid LaTeX * fixing GADT data declaration headers * overhaul handling of record fields * overhaul handling of GADT constructors * overhaul handling of bundled patterns * add support for constructor argument docs * Support GADT record constructors This means changes what existing HTML docs look like. As for LaTeX, looks like GADT records were never even supported. Now they are. * Clean up code/comments Made code/comments consistent between the LaTeX and XHTML backend when possible. * Update changelog * Patch post-rebase regressions * Another post-rebase change We want return values to be documentable on record GADT constructors. - - - - - ca4fabb4 by Alec Theriault at 2018-01-15T17:12:18-08:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 4c472fea by Ryan Scott at 2018-01-19T10:44:02+01:00 Fix haskell/haddock#732 (#733) - - - - - bff14dbd by Alex Biehl at 2018-01-19T15:33:30+01:00 extractDecl: Extract associated types correctly (#736) - - - - - a2a94a73 by Alex Biehl at 2018-01-19T15:34:40+01:00 extractDecl: Extract associated types correctly (#736) - - - - - 26df93dc by Alex Biehl at 2018-01-20T10:18:22+01:00 haddock-api: bump ghc to ^>= 8.4 - - - - - f65aeb1d by Alex Biehl at 2018-01-20T19:18:20+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - 0e721b97 by Alex Biehl at 2018-01-20T19:20:19+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - cb6234f6 by Ben Gamari at 2018-01-26T13:40:55-05:00 Merge remote-tracking branch 'harpocrates/fix/missing-orphan-instances' into ghc-head - - - - - 0fc28554 by Alec Theriault at 2018-02-01T14:58:18+01:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - b9123772 by Alec Theriault at 2018-02-01T14:58:18+01:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 0c12e274 by Ryan Scott at 2018-02-01T14:58:18+01:00 Fix haskell/haddock#548 by rendering datatype kinds more carefully (#702) - - - - - 8876d20b by Alec Theriault at 2018-02-01T14:58:18+01:00 Use the GHC lexer for the Hyperlinker backend (#714) * Start changing to use GHC lexer * better cpp * Change SrcSpan to RealSrcSpan * Remove error * Try to stop too many open files * wip * wip * Revert "wip" This reverts commit b605510a195f26315e3d8ca90e6d95a6737553e1. Conflicts: haddock-api/haddock-api.cabal haddock-api/src/Haddock/Interface.hs * Remove pointless 'caching' * Use dlist rather than lists when finding vars * Use a map rather than list * Delete bogus comment * Rebase followup Things now run using the GHC lexer. There are still - stray debug statements - unnecessary changes w.r.t. master * Cleaned up differences w.r.t. current Haddock HEAD Things are looking good. quasiquotes in particular look beautiful: the TH ones (with Haskell source inside) colour/link their contents too! Haven't yet begun to check for possible performance problems. * Support CPP and top-level pragmas The support for these is hackier - but no more hacky than the existing support. * Tests pass, CPP is better recognized The tests were in some cases altered: I consider the new output to be more correct than the old one.... * Fix shrinking of source without tabs in test * Replace 'Position'/'Span' with GHC counterparts Replaces 'Position' -> 'GHC.RealSrcLoc' and 'Span' -> 'GHC.RealSrcSpan'. * Nits * Forgot entry in .cabal * Update changelog - - - - - 95c6a771 by Alec Theriault at 2018-02-01T14:58:18+01:00 Clickable anchors for headings (#716) See haskell/haddock#579. This just adds an <a> tag around the heading, pointing to the heading itself. - - - - - 21463d28 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump: Matches on function names weight more than matches in ... module names. - - - - - 8023af39 by Alex Biehl at 2018-02-01T14:58:18+01:00 Treat escaped \] better in definition lists (#717) This fixes haskell/haddock#546. - - - - - e4866dc1 by Alex Biehl at 2018-02-01T14:58:18+01:00 Remove scanner, takeWhile1_ already takes care of escaping - - - - - 9bcaa49d by Alex Biehl at 2018-02-01T14:58:18+01:00 Take until line feed - - - - - 01d2af93 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Add simple framework for running parser fixtures (#668) * Add simple framework for running parser fixtures * Compatible with tree-diff-0.0.0.1 * Use parseParas to parse fixtures This allows to test all syntactic constructs available in haddock markup. - - - - - 31128417 by Alec Theriault at 2018-02-01T14:58:18+01:00 Patch flaky parser test (#720) * Patch flaky parser test This test was a great idea, but it doesn't port over too well to using the GHC lexer. GHC rewrites its input a bit - nothing surprising, but we need to guard against those cases for the test. * Change instance head * Change use site - - - - - 9704f214 by Herbert Valerio Riedel at 2018-02-01T14:58:18+01:00 Include secondary LICENSE file in source dist - - - - - 51f25074 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Grid Tables (#718) * Add table examples * Add table types and adopt simple parser Simple parser is done by Giovanni Cappellotto (@potomak) in https://github.com/haskell/haddock/pull/577 It seems to support single fine full tables, so far from full RST-grid tables, but it's good start. Table type support row- and colspans, but obviously parser is lacking. Still TODO: - Latex backend. Should we use multirow package https://ctan.org/pkg/multirow?lang=en? - Hoogle backend: ? * Implement grid-tables * Refactor table parser * Add two ill-examples * Update CHANGES.md * Basic documentation for tables * Fix documentation example - - - - - 670d6200 by Alex Biehl at 2018-02-01T14:58:18+01:00 Add grid table example to cheatsheet (pdf and svg need to be regenerated thought) - - - - - 4262dec9 by Alec Theriault at 2018-02-01T14:58:18+01:00 Fix infinite loop when specializing instance heads (#723) * Fix infinite loop when specializing instance heads The bug can only be triggered from TH, hence why it went un-noticed for so long. * Add test for haskell/haddock#679 and haskell/haddock#710 - - - - - 67ecd803 by Alec Theriault at 2018-02-01T14:58:18+01:00 Filter RTS arguments from 'ghc-options' arguments (#725) This fixes haskell/haddock#666. - - - - - 7db26992 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump Scrollable overlay - - - - - da9ff634 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Hyperlinker: Adjust parser to new PFailed constructor - - - - - 7b7cf8cb by Alexander Biehl at 2018-02-01T14:58:18+01:00 Specialize: Add missing IdP annotations - - - - - 78cd7231 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Convert: Correct pass type - - - - - a2d0f590 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Warning free compilation - - - - - cd861cf3 by Alexander Biehl at 2018-02-01T14:58:18+01:00 hadock-2.19.0 / haddock-api-2.19.0 / haddock-library-1.5.0 - - - - - c6651b72 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Adjust changelogs - - - - - 1e93da0b by Alexander Biehl at 2018-02-01T14:58:18+01:00 haddock-library: Info about breaking changes - - - - - f9b11db8 by Alec Theriault at 2018-02-02T12:36:02+01:00 Properly color pragma contents in hyperlinker The hyperlinker backend now classifies the content of pragmas as 'TkPragma'. That means that in something like '{-# INLINE foo #-}', 'foo' still gets classified as a pragma token. - - - - - c40b0043 by Alec Theriault at 2018-02-02T12:36:02+01:00 Support the new 'ITcolumn_prag' token - - - - - 4a2a4d39 by Alex Biehl at 2018-02-03T12:11:55+01:00 QuickJump: Mitigate encoding problems on Windows - - - - - bb34503a by Alex Biehl at 2018-02-04T18:39:31+01:00 Use withBinaryFile - - - - - 637605bf by Herbert Valerio Riedel at 2018-02-05T09:48:32+01:00 Try GHC 8.4.1 for Travis CI job - - - - - 7abb67e4 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 try harder to build w/ GHC 8.4.1 - - - - - 8255cc98 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 Add `SPDX-License-Identifier` as alised for "license" module header tokens C.f. SPDX 2.1 - Appendix V https://spdx.org/spdx-specification-21-web-version#h.twlc0ztnng3b The tag should appear on its own line in the source file, generally as part of a comment. SPDX-License-Identifier: <SPDX License Expression> Cherry-picked from haskell/haddock#743 - - - - - 267cd23d by Herbert Valerio Riedel at 2018-02-05T10:24:34+01:00 Make test-suite SMP compatible - - - - - 95d4bf40 by Alec Theriault at 2018-02-05T22:01:04+01:00 Hyperlink pattern synonyms and 'module' imports (#744) Links to pattern synonyms are now generated, as well as links from modules in import lists. Fixes haskell/haddock#731. - - - - - 67838dcd by Alec Theriault at 2018-02-06T08:23:36+01:00 Don't warn about missing '~' (#746) This manually filters out '~' from the list of things to warn about. It truly makes no sense to warn on this since '~' has nothing it could link to - it is magical. This fixes haskell/haddock#532. - - - - - ab6c3f9f by Alec Theriault at 2018-02-06T08:24:47+01:00 Don't barf on 'HsSpliceTy' (#745) This handles 'HsSpliceTy's by replacing them with what they expand to. IIUC everything that is happening, 'renameHsSpliceTy' should not be able to fail for the inputs we feed it from GHC. This fixes haskell/haddock#574. - - - - - 92bf95ad by Alex Biehl at 2018-02-06T08:28:23+01:00 Rename: renameHsSpliceTy ttg - - - - - 3130b1e1 by Alex Biehl at 2018-02-06T09:02:14+01:00 Expand SigDs - - - - - c72adae5 by Alex Biehl at 2018-02-06T09:20:51+01:00 fullModuleContents: support named docs - - - - - de2e4dbf by Alex Biehl at 2018-02-06T13:56:17+01:00 Hyperlinker: Also link pattern synonym arguments - - - - - b7c98237 by Alex Biehl at 2018-02-09T18:44:23+01:00 Expand SigD in a better place In https://github.com/haskell/haddock/issues/287 we found that haddock-2.19.0 would miss documentation on class methods with multiples names. This patch uses expandSigDecls in a more sensible place. - - - - - 8f598b27 by Alec Theriault at 2018-02-11T12:29:56+01:00 Add module tooltips to linked identifiers (#753) No more clicking to figure out whether your bytestring is strict or lazy! - - - - - d812e65d by Alec Theriault at 2018-02-11T12:31:44+01:00 Add 'show' option to complement 'hide' (#752) * Add 'show' option to complement 'hide' The behaviour is for flags passed in the command line to override flags in file headers. In the command line, later flags override earlier ones. Fixes haskell/haddock#751 and haskell/haddock#266. * Add a '--show-all' option - - - - - 6676cecb by Alex Biehl at 2018-02-18T11:07:15-05:00 QuickJump: Mitigate encoding problems on Windows (cherry picked from commit 86292c54bfee2343aee84559ec01f1fc68f52231) - - - - - e753dd88 by Alex Biehl at 2018-02-18T17:59:54+01:00 Use withBinaryFile - - - - - 724dc881 by Tamar Christina at 2018-02-19T05:34:49+01:00 Haddock: support splitted include paths. (#689) - - - - - 9b6d6f50 by Alex Biehl at 2018-02-19T05:57:02+01:00 Teach the HTML backend how to render methods with multiple names - - - - - a74aa754 by Alexander Biehl at 2018-02-19T10:04:34+01:00 Hoogle/Latex: Remove use of partial function - - - - - 66d8bb0e by Alec Theriault at 2018-02-25T16:04:01+01:00 Fix file handle leak (#763) (#764) Brought back some mistakenly deleted code for handling encoding and eager reading of files from e0ada1743cb722d2f82498a95b201f3ffb303137. - - - - - bb92d03d by Alex Biehl at 2018-03-02T14:21:23+01:00 Enable running test suite with stock haddock and ghc using ``` $ cabal new-run -- html-test --haddock-path=$(which haddock) --ghc-path=$(which ghc) ``` - - - - - dddb3cb2 by Alex Biehl at 2018-03-02T15:43:21+01:00 Make testsuite work with haddock-1.19.0 release (#766) - - - - - f38636ed by Alec Theriault at 2018-03-02T15:48:36+01:00 Support unicode operators, proper modules Unicode operators are a pretty big thing in Haskell, so supporting linking them seems like it outweighs the cost of the extra machinery to force Attoparsec to look for unicode. Fixes haskell/haddock#458. - - - - - 09d89f7c by Alec Theriault at 2018-03-02T15:48:43+01:00 Remove bang pattern - - - - - d150a687 by Alex Biehl at 2018-03-02T15:48:48+01:00 fix test - - - - - d6fd71a5 by Alex Biehl at 2018-03-02T16:22:38+01:00 haddock-test: Be more explicit which packages to pass We now pass `-hide-all-packages` to haddock when invoking the testsuite. This ensures we don't accidentally pick up any dependencies up through ghc.env files. - - - - - 0932c78c by Alex Biehl at 2018-03-02T17:50:38+01:00 Revert "fix test" This reverts commit 1ac2f9569242f6cb074ba6e577285a4c33ae1197. - - - - - 52516029 by Alex Biehl at 2018-03-02T18:16:50+01:00 Fix Bug548 for real - - - - - 89df9eb5 by Alex Biehl at 2018-03-05T18:28:19+01:00 Hyperlinker: Links for TyOps, class methods and associated types - - - - - d019a4cb by Ryan Scott at 2018-03-06T13:43:56-05:00 Updates for haskell/haddock#13324 - - - - - 6d5a42ce by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump haddock-2.19.0.1, haddock-api-2.19.0.1, haddock-library-1.5.0.1 - - - - - c0e6f380 by Alex Biehl at 2018-03-10T18:25:57+01:00 Update changelogs for haddock-2.19.0.1 and haddock-library-1.5.0.1 - - - - - 500da489 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Update to QC 2.11 - - - - - ce8362e9 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Restore backward-compat with base-4.5 through base-4.8 - - - - - baae4435 by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump lower bound for haddock-library - - - - - 10b7a73e by Alex Biehl at 2018-03-10T18:25:57+01:00 Haddock: Straighten out base bound - - - - - a6096f7b by Alex Biehl at 2018-03-13T08:45:06+01:00 extractDecl: Extract constructor patterns from data family instances (#776) * extractDecl: Allow extraction of data family instance constructors * extractDecl: extract data family instance constructors - - - - - ba4a0744 by Simon Jakobi at 2018-03-14T08:26:42+01:00 Readme: Update GHC version (#778) - - - - - 8de157d4 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for definition lists - - - - - 425b46f9 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for links - - - - - d53945d8 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for inline links - - - - - f1dc7c99 by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Slightly unmangle output - - - - - 0879d31c by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Prevent stdout buffering - - - - - 1f9e5f1b by Simon Jakobi at 2018-03-14T20:39:29+01:00 haddock-library.cabal: Clean up GHC options - - - - - 066b891a by Simon Jakobi at 2018-03-14T20:39:29+01:00 Make a proper definition for the <link> parser - - - - - 573d6ba7 by Alec Theriault at 2018-03-21T09:16:57+01:00 Show where instances are defined (#748) * Indicate source module of instances Above instance, we now also display a link to the module where the instance was defined. This is sometimes helpful in figuring out what to import. * Source module for type/data families too * Remove parens * Accept tests - - - - - 99b5d28b by Alex Biehl at 2018-03-21T09:20:36+01:00 Prepare changelog for next release - - - - - 482d3a93 by Alex Biehl at 2018-03-23T15:57:36+01:00 Useful cost centres, timers and allocation counters (#785) * Add some useful cost-centres for profiling * Add withTiming for each haddock phase Invoking haddock with `--optghc=-ddump-timings` now shows the amount of time spent and the number of allocated bytes for each phase. - - - - - 773b41bb by Alec Theriault at 2018-03-27T08:35:59+02:00 @since includes package name (#749) * Metadoc stores a package name This means that '@since' annotations can be package aware. * Get the package name the right way This should extract the package name for `@since` annotations the right way. I had to move `modulePackageInfo` around to do this and, in the process, I took the liberty to update it. Since it appears that finding the package name is something that can fail, I added a warning for this case. * Silence warnings * Hide package for local 'since' annotations As discussed, this is still the usual case (and we should avoid being noisy for it). Although this commit is large, it is basically only about threading a 'Maybe Package' from 'Haddock.render' all the way to 'Haddock.Backends.Xhtml.DocMarkup.renderMeta'. * Bump binary interface version * Add a '--since-qual' option This controls when to qualify since annotations with the package they come from. The default is always, but I've left an 'external' variant where only those annotations coming from outside of the current package are qualified. * Make ParserSpec work * Make Fixtures work * Use package name even if package version is not available The @since stuff needs only the package name passed in, so it makes sense to not be forced to pass in a version too. - - - - - e42c57bc by Alex Biehl at 2018-03-27T08:42:50+02:00 haddock-2.19.1, haddock-api-2.19.1, haddock-library-1.6.0 - - - - - 8373a529 by Alex Biehl at 2018-03-28T10:17:11+02:00 Bump haddock and haddock-api to 2.20.0 - - - - - 5038eddd by Jack Henahan at 2018-04-03T13:28:12+02:00 Clear search string on hide for haskell/haddock#781 (#789) - - - - - 920ca1eb by Alex Biehl at 2018-04-03T16:35:50+02:00 Travis: Build with ghc-8.4.2 (#793) - - - - - a232f0eb by Alan Zimmerman at 2018-04-07T14:14:32+02:00 Match changes in GHC for D4199 Removing HasSourceText and SourceTextX classes. - - - - - ab85060b by Alan Zimmerman at 2018-04-09T21:20:24+02:00 Match GHC changes for TTG - - - - - 739302b6 by Alan Zimmerman at 2018-04-13T13:31:44+02:00 Match GHC for TTG implemented on HsBinds, D4581 - - - - - 2f56d3cb by Ryan Scott at 2018-04-19T11:42:58-04:00 Bump upper bound on base to < 4.13 See https://ghc.haskell.org/trac/ghc/ticket/15018. - - - - - a49df92a by Alex Biehl at 2018-04-20T07:31:44+02:00 Don't treat fixity signatures like declarations - - - - - d02c103b by Ryan Scott at 2018-04-24T11:20:11-04:00 Add regression test for haskell/haddock#413 Fixes haskell/haddock#413. - - - - - c7577f52 by Ryan Scott at 2018-04-24T13:51:06-07:00 Improve the Hoogle backend's treatment of type families (#808) Fixes parts 1 and 2 of haskell/haddock#806. - - - - - d88f85b1 by Alec Theriault at 2018-04-25T11:24:07-07:00 Replace 'attoparsec' with 'parsec' (#799) * Remove attoparsec with parsec and start fixing failed parses * Make tests pass * Fix encoding issues The Haddock parser no longer needs to worry about bytestrings. All the internal parsing work in haddock-library happens over 'Text'. * Remove attoparsec vendor * Fix stuff broken in 'attoparsec' -> 'parsec' * hyperlinks * codeblocks * examples Pretty much all issues are due to attoparsec's backtracking failure behaviour vs. parsec's non-backtracking failure behaviour. * Fix small TODOs * Missing quote + Haddocks * Better handle spaces before/after paragraphs * Address review comments - - - - - fc25e2fe by Alan Zimmerman at 2018-04-27T15:36:53+02:00 Match changes in GHC for TTG - - - - - 06175f91 by Herbert Valerio Riedel at 2018-05-01T18:11:09+02:00 Merge branch 'ghc-head' with 'ghc-8.4' - - - - - 879caaa8 by Alec Theriault at 2018-05-07T18:53:15-07:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 3e0120cb by Simon Jakobi at 2018-05-07T19:00:18-07:00 Add docs for some DocH constructors (#814) - - - - - 0a32c6db by Alec Theriault at 2018-05-08T02:15:45-07:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 8816e783 by Simon Jakobi at 2018-05-08T10:48:11-07:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - ad60366f by Ryan Scott at 2018-05-10T11:19:47-04:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - 03b7cc3b by Ryan Scott at 2018-05-10T11:24:38-04:00 Wibbles - - - - - b03dd563 by Chaitanya Koparkar at 2018-05-10T11:44:58-04:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 9f298a40 by Ben Gamari at 2018-05-13T17:36:04-04:00 Account for refactoring of LitString - - - - - ea3dabe7 by Ryan Scott at 2018-05-16T09:21:43-04:00 Merge pull request haskell/haddock#826 from haskell/T825 Remove Hoogle backend hack that butchers infix datatype names - - - - - 0d234f7c by Alec Theriault at 2018-05-23T11:29:05+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 15fc9712 by Simon Jakobi at 2018-05-31T04:17:47+02:00 Adjust to new HsDocString internals - - - - - 6f1e19a8 by Ben Gamari at 2018-06-02T16:18:58-04:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 0d0355d9 by Ryan Scott at 2018-06-04T21:26:59-04:00 DerivingVia changes - - - - - 0d93475a by Simon Jakobi at 2018-06-05T19:47:05+02:00 Bump a few dependency bounds (#845) - - - - - 5cbef804 by Alec Theriault at 2018-06-05T19:47:16+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 9094c56f by Alec Theriault at 2018-06-05T22:53:25+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 70188719 by Simon Jakobi at 2018-06-08T22:20:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - 495cd1fc by Chaitanya Koparkar at 2018-06-13T23:01:34+02:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 81088732 by Ben Gamari at 2018-06-13T23:01:34+02:00 Account for refactoring of LitString - - - - - 7baf6587 by Simon Jakobi at 2018-06-13T23:05:08+02:00 Adjust to new HsDocString internals - - - - - bb61464d by Ben Gamari at 2018-06-13T23:05:22+02:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 5d8cb87f by Ryan Scott at 2018-06-13T23:39:30+02:00 DerivingVia changes - - - - - 73d373a3 by Alec Theriault at 2018-06-13T23:39:30+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 4865e254 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Remove `ITtildehsh` token - - - - - b867db54 by Alec Theriault at 2018-06-13T23:39:30+02:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 9598e392 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Add docs for some DocH constructors (#814) - - - - - 8a59035b by Alec Theriault at 2018-06-13T23:39:30+02:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 29350fc8 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - 2590bbd9 by Ryan Scott at 2018-06-13T23:39:30+02:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - a9939fdc by Ryan Scott at 2018-06-13T23:39:30+02:00 Wibbles - - - - - a22f7df4 by Alec Theriault at 2018-06-13T23:39:30+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 8741015d by Simon Jakobi at 2018-06-13T23:39:30+02:00 Bump a few dependency bounds (#845) - - - - - 4791e1cc by Alec Theriault at 2018-06-13T23:39:30+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 311d3216 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - d0577817 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Complete FixitySig and FamilyDecl pattern matches - - - - - 055b3aa7 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Fix redundant import warnings - - - - - f9ce19b1 by Simon Jakobi at 2018-06-13T23:49:52+02:00 html-test: Accept output - - - - - 04604ea7 by Simon Jakobi at 2018-06-13T23:54:37+02:00 Bump bounds on Cabal - - - - - 0713b692 by Simon Jakobi at 2018-06-14T00:00:12+02:00 Merge branch 'ghc-head' into ghc-head-update-3 - - - - - c6a56bfd by Simon Jakobi at 2018-06-14T02:33:27+02:00 Bump ghc bound for haddock-api spec test-suite - - - - - 119d04b2 by Simon Jakobi at 2018-06-14T12:37:48+02:00 Travis: `--allow-newer` for all packages - - - - - 0e876e2c by Alex Biehl at 2018-06-14T15:28:52+02:00 Merge pull request haskell/haddock#857 from sjakobi/ghc-head-update-3 Update ghc-head - - - - - 5be46454 by Alec Theriault at 2018-06-14T21:42:45+02:00 Improved handling of interfaces in 'haddock-test' (#851) This should now work with an inplace GHC where (for instance) HTML directories may not be properly recorded in the package DB. - - - - - 96ab1387 by Vladislav Zavialov at 2018-06-14T17:06:21-04:00 Handle -XStarIsType - - - - - e518f8c4 by Ben Gamari at 2018-06-14T17:48:00-04:00 Revert unintentional reversion of fix of haskell/haddock#548 - - - - - 01b9f96d by Alan Zimmerman at 2018-06-19T11:52:22+02:00 Match changes in GHC for haskell/haddock#14259 - - - - - 7f8c8298 by Ben Gamari at 2018-06-19T18:14:27-04:00 Bump GHC version to 8.6 - - - - - 11c6b5d2 by Ryan Scott at 2018-06-19T23:17:31-04:00 Remove HsEqTy and XEqTy - - - - - b33347c2 by Herbert Valerio Riedel at 2018-06-20T23:14:52+02:00 Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. - - - - - f0d2460e by Herbert Valerio Riedel at 2018-06-20T23:28:46+02:00 Update Travis CI job - - - - - ef239223 by Herbert Valerio Riedel at 2018-06-20T23:32:41+02:00 Drop GHC HEAD from CI and update GHC to 8.4.3 It's a waste of resource to even try to build this branch w/ ghc-head; so let's not do that... - - - - - 41c4a9fa by Ben Gamari at 2018-06-20T18:26:20-04:00 Bump GHC version to 8.7 - - - - - 8be593dc by Herbert Valerio Riedel at 2018-06-21T22:32:15+02:00 Update CI job to use GHC 8.7.* - - - - - b91d334a by Simon Jakobi at 2018-06-30T13:41:38+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section - - - - - f707d848 by Alec Theriault at 2018-07-05T10:43:35-04:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. - - - - - a6d2b8dc by Alec Theriault at 2018-07-06T10:06:32-04:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case - - - - - 13819f71 by Alan Zimmerman at 2018-07-15T19:33:51+02:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 - - - - - c346aa78 by Simon Jakobi at 2018-07-19T12:29:32+02:00 haddock-library: Bump bounds for containers - - - - - 722e733c by Simon Jakobi at 2018-07-19T13:36:45+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] - - - - - f0bd83fd by Alec Theriault at 2018-07-19T14:39:57+02:00 Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. - - - - - 394053a8 by Simon Jakobi at 2018-07-19T14:58:07+02:00 haddock-library: Bump bounds for containers - - - - - 1bda11a2 by Alec Theriault at 2018-07-20T09:04:03+02:00 Add HEAD.hackage overlay (#887) * Add HEAD.hackage overlay * Add HCPKG variable - - - - - c7b4ab45 by Alec Theriault at 2018-07-20T12:01:16+02:00 Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test - - - - - c05d32ad by Alec Theriault at 2018-07-20T12:01:49+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output - - - - - 24b39ee4 by Alec Theriault at 2018-07-20T12:02:16+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. - - - - - cb9d2099 by Simon Jakobi at 2018-07-20T13:39:29+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) - - - - - 133f24f5 by Alec Theriault at 2018-07-20T13:39:29+02:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) - - - - - 11024149 by Alec Theriault at 2018-07-20T13:39:29+02:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) - - - - - de0c139e by Simon Jakobi at 2018-07-20T13:39:29+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) - - - - - 6435e952 by Alec Theriault at 2018-07-20T13:39:29+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) - - - - - 1461af39 by Alec Theriault at 2018-07-20T13:39:29+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) - - - - - 69d3bde1 by Alec Theriault at 2018-07-20T13:49:47+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) - - - - - 6a5c73c7 by Alec Theriault at 2018-07-20T13:50:00+02:00 Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests - - - - - 92ca94c6 by Alec Theriault at 2018-07-20T13:55:36+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) - - - - - 981bc7fa by Simon Jakobi at 2018-07-20T15:06:06+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers - - - - - 27e7c0c5 by Simon Jakobi at 2018-07-20T15:09:05+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 49e1a415 by Simon Jakobi at 2018-07-20T16:02:02+02:00 Update the ghc-8.6 branch (#889) * Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. * README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) * Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) * Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) * tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) * Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. * Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test * Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) * Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) * Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) * Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests * Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 5ca14bed by Simon Jakobi at 2018-07-20T16:05:47+02:00 Revert "Revert "Bump GHC version to 8.6"" That commit didn't belong onto the ghc-8.6 branch. This reverts commit acbaef3b9daf1d2dea10017964bf886e77a8e967. - - - - - 2dd600dd by Simon Jakobi at 2018-07-20T16:18:21+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. - - - - - fceb2422 by Simon Jakobi at 2018-07-20T16:18:21+02:00 outOfScope: Recommend qualifying the identifier - - - - - acea5d23 by Simon Jakobi at 2018-07-20T16:19:35+02:00 outOfScope: Recommend qualifying the identifier (cherry picked from commit 73707ed58d879cc04cb644c5dab88c39ca1465b7) - - - - - 1a83ca55 by Simon Jakobi at 2018-07-20T16:19:35+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. (cherry picked from commit d504a2864a4e1982e142cf88c023e7caeea3b76f) - - - - - 48374451 by Masahiro Sakai at 2018-07-20T17:06:42+02:00 Add # as a special character (#884) '#' has special meaning used for anchors and can be escaped using backslash. Therefore it would be nice to be listed as special characters. - - - - - 5e1a5275 by Alec Theriault at 2018-07-20T23:37:24+02:00 Let `haddock-test` bypass interface version check (#890) This means `haddock-test` might * crash during deserialization * deserialize incorrectly Still - it means things _might_ work where they were previously sure not to. - - - - - 27286754 by Yuji Yamamoto at 2018-07-23T08:16:01+02:00 Avoid "invalid argument (invalid character)" on non-unicode Windows (#892) Steps to reproduce and the error message ==== ``` > stack haddock basement ... snip ... Warning: 'A' is out of scope. Warning: 'haddock: internal error: <stdout>: commitBuffer: invalid argument (invalid character) ``` Environment ==== OS: Windows 10 ver. 1709 haddock: [HEAD of ghc-8.4 when I reproduce the error](https://github.com/haskell/haddock/commit/532b209d127e4cecdbf7e9e3dcf4f653a5605b5a). (I had to use this version to avoid another probrem already fixed in HEAD) GHC: 8.4.3 stack: Version 1.7.1, Git revision 681c800873816c022739ca7ed14755e85a579565 (5807 commits) x86_64 hpack-0.28.2 Related pull request ==== https://github.com/haskell/haddock/pull/566 - - - - - 6729d361 by Alec Theriault at 2018-07-23T13:52:56-07:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). - - - - - 8cf4e6b5 by Ryan Scott at 2018-07-27T11:28:03-04:00 eqTyCon_RDR now lives in TysWiredIn After GHC commit http://git.haskell.org/ghc.git/commit/f265008fb6f70830e7e92ce563f6d83833cef071 - - - - - 1ad251a6 by Alan Zimmerman at 2018-07-30T13:28:09-04:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 (cherry picked from commit e3926b50ab8a7269fd6904b06e881745f08bc5d6) - - - - - 8aea2492 by Richard Eisenberg at 2018-08-02T10:54:17-04:00 Update against new HsImplicitBndrs - - - - - e42cada9 by Alec Theriault at 2018-08-04T17:51:30+02:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 0e852512 by Alex Biehl at 2018-08-06T13:04:02+02:00 Make --package-version optional for --hoogle generation (#899) * Make --package-version optional for --hoogle generation * Import mkVersion * It's makeVersion not mkVersion - - - - - d2abd684 by Noel Bourke at 2018-08-21T09:34:18+02:00 Remove unnecessary backslashes from docs (#908) On https://haskell-haddock.readthedocs.io/en/latest/markup.html#special-characters the backslash and backtick special characters showed up with an extra backslash before them – I think the escaping is not (or no longer) needed for those characters in rst. - - - - - 7a578a9e by Matthew Pickering at 2018-08-21T09:34:50+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - aa3d4db3 by Matthew Pickering at 2018-08-21T09:37:34+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - ede91744 by Alec Theriault at 2018-08-21T09:42:52+02:00 Better test output when Haddock crashes on a test (#902) In particular: we report the tests that crashed seperately from the tests that produced incorrect output. In order for tests to pass (and exit 0), they must not crash and must produce the right output. - - - - - 4a872b84 by Guillaume Bouchard at 2018-08-21T09:45:57+02:00 Fix a typo (#878) - - - - - 4dbf7595 by Ben Sklaroff at 2018-08-21T12:04:09-04:00 Add ITcomment_line_prag token to Hyperlinker Parser This token is necessary for parsing #line pragmas inside nested comments. Reviewers: bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D4935 - - - - - 9170b2a9 by Ben Gamari at 2018-08-21T17:55:15-04:00 Merge pull request haskell/haddock#893 from harpocrates/get-name-to-instances Accumulate explicitly which modules to load for 'attachInstances' - - - - - d57b57cc by Ben Gamari at 2018-08-21T17:59:13-04:00 Merge branch 'ghc-head' of github.com:haskell/haddock into ghc-head - - - - - 14601ca2 by Alec Theriault at 2018-08-21T19:09:37-04:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). (cherry picked from commit 5c7c596c51d69b92164e9ba920157b36ce2b2ec1) - - - - - 438c645e by Matthew Pickering at 2018-08-21T19:12:39-04:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 (cherry picked from commit e6aa8fb47b9477cc5ef5e46097524fe83e080f6d) - - - - - a80c5161 by Alec Theriault at 2018-08-21T22:06:40-07:00 Better rendering of unboxed sums/tuples * adds space after/before the '#' marks * properly reify 'HsSumTy' in 'synifyType' - - - - - 88456cc1 by Alec Theriault at 2018-08-21T22:06:40-07:00 Handle promoted tuples in 'synifyType' When we have a fully applied promoted tuple, we can expand it out properly. - - - - - fd1c1094 by Alec Theriault at 2018-08-21T22:19:34-07:00 Accept test cases - - - - - 6e80d9e0 by Alec Theriault at 2018-08-21T22:24:03-07:00 Merge pull request haskell/haddock#914 from harpocrates/feature/unboxed-stuff Better rendering of unboxed sums, unboxed tuples, promoted tuples. - - - - - 181a23f1 by Ben Gamari at 2018-08-23T15:53:48-04:00 Merge remote-tracking branch 'origin/ghc-8.6' into ghc-8.6 - - - - - 3a18c1d8 by Alec Theriault at 2018-08-27T14:15:25-07:00 Properly synify promoted list types We reconstruct promoted list literals whenever possible. That means that 'synifyType' produces '[Int, Bool, ()] instead of (Int ': (() ': (Bool ': ([] :: [Type])))) - - - - - b4794946 by Alec Theriault at 2018-09-03T07:19:55-07:00 Only look at visible types when synifying a 'HsListTy' The other types are still looked at when considering whether to make a kind signature or not. - - - - - a231fce2 by Alec Theriault at 2018-09-03T07:38:10-07:00 Merge pull request haskell/haddock#922 from harpocrates/promoted-lists Properly synify promoted list types - - - - - 0fdf044e by Ningning Xie at 2018-09-15T10:25:58-04:00 Update according to GHC Core changes - - - - - 7379b115 by Ningning Xie at 2018-09-15T15:40:18-04:00 update dataFullSig to work with Co Quantification This should have been in the previous patch, but wasn't. - - - - - cf84a046 by Alec Theriault at 2018-09-17T20:12:18-07:00 Fix/add to various docs * Add documentation for a bunch of previously undocumented options (fixes haskell/haddock#870) * Extend the documentation of `--hoogle` considerably (see haskell/haddock#807) * Describe how to add docs to `deriving` clauses (fixes haskell/haddock#912) * Fix inaccurate docs about hyperlinking infix identifiers (fixes haskell/haddock#780) - - - - - ae017935 by Alec Theriault at 2018-09-22T08:32:16-07:00 Update Travis - - - - - d95ae753 by Alec Theriault at 2018-09-22T09:34:10-07:00 Accept failing tests Also silence orphan warnings. - - - - - f3e67024 by Alec Theriault at 2018-09-22T09:41:23-07:00 Bump haddock-api-2.21.0, haddock-library-1.7.0 * Update CHANGELOGS * Update new versions in Cabal files * Purge references to ghc-8.4/master branches in README - - - - - 3f136d4a by Alec Theriault at 2018-09-22T10:53:31-07:00 Turn haddock-library into a minor release Fix some version bounds in haddock-library too. - - - - - b9def006 by Alec Theriault at 2018-09-22T13:07:35-07:00 keep cabal.project file - - - - - 4909aca7 by Alec Theriault at 2018-10-16T09:36:30-07:00 Build on 7.4 and 7.8 - - - - - 99d20a28 by Herbert Valerio Riedel at 2018-10-16T18:45:52+02:00 Minor tweak to package description - - - - - a8059618 by Herbert Valerio Riedel at 2018-10-16T18:47:24+02:00 Merge pull request haskell/haddock#945 haddock-api 2.21.0 and haddock-library 1.6.1 release - - - - - 2d9bdfc1 by Alec Theriault at 2018-10-16T10:54:21-07:00 Bump haddock-library to 1.7.0 The 1.6.1 release should've been a major bump, since types in the `Documentation.Haddock.Parser.Monad` module changed. This version makes that module internal (as it morally should be). - - - - - ed340cef by Alec Theriault at 2018-10-16T14:59:13-07:00 Merge branch 'ghc-8.4' into ghc-8.6 - - - - - 2821a8df by Alec Theriault at 2018-10-16T15:14:48-07:00 Merge branch 'ghc-8.6' into ghc-head - - - - - a722dc84 by Alec Theriault at 2018-10-16T16:28:55-07:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 63377496 by Alec Theriault at 2018-10-16T16:39:07-07:00 Update changelog - - - - - 099a0110 by Alec Theriault at 2018-10-16T16:49:28-07:00 Merge pull request haskell/haddock#942 from harpocrates/update-docs Fix & add to documentation - - - - - 0927416f by Alec Theriault at 2018-10-16T16:50:14-07:00 Set UTF-8 encoding before writing files (#934) This should fix haskell/haddock#929, as well as guard against future problems of this sort in other places. Basically replaces 'writeFile' (which selects the users default locale) with 'writeUtf8File' (which always uses utf8). - - - - - 83b7b017 by Alec Theriault at 2018-10-16T17:42:05-07:00 Output pattern synonyms in Hoogle backend (#947) * Output pattern synonyms in Hoogle backend We were previously weren't outputting _any_ pattern synonyms, bundled or not. Now, we output both. Fixes haskell/haddock#946. * Update changelog - - - - - 81e5033d by Alec Theriault at 2018-10-16T18:04:40-07:00 Release `haddock{,-api}-2.22.0` This version will accompany ghc-8.6.2 - - - - - 9661744e by Alex Biehl at 2018-10-18T08:14:32-07:00 Add NewOcean theme And make it the default theme. - - - - - 7ae6d722 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Improve appearance and readability These changes include: - use latest Haskell's logo colors - decrease #content width to improve readability - use nicer font - improve sizes and distances - - - - - 37f8703d by NunoAlexandre at 2018-10-18T08:14:32-07:00 Include custom font in the html head - - - - - 1d5e1d79 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Update html test reference files - - - - - 53b7651f by NunoAlexandre at 2018-10-18T08:14:32-07:00 Make it responsive - It makes small screens taking more space than larger ones - fixes a few issues present in small screens currently - make it look good across different screen sizes. - - - - - 6aa1aeb1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make the style consistent with hackage Several things are addressed here: - better responsive behaviour on the header - better space usage - consistent colors overall - other nit PR comments - - - - - 3a250c5c by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Place the package name before the menu links This supports the expected responsive menu design, where the package name appears above the menu links. - - - - - cae699b3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update html-test reference files The package name element in the package-header is now a div instead of a paragraph, and it is now above the menu ul.links instead of below. - - - - - 2ec7fd2d by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve synopsis style and code - Use CSS3 instead of loading pictures to show "+" and "-" symbols - Drop redundant code - - - - - 0c874c01 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Decrease space between code blocks There was too much space between code blocks as pointed out by reviewers. - - - - - 85568ce2 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Add an initial-scale property to all haddock pages This solves an issue reported about the content looking incredibly small on mobile devices. - - - - - c1538926 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Address several PR comments - Darken text color like done for hackage - Move synopsis to left side - Make table of contents stick to the left on wide screens - Wrap links to avoid page overflow - Improve expand/collapse buttons - Fix issue with content size on mobile devices - Fix issue with font-size on landscape mode - Increase width of the content - Change colors of table of contents and synopsis - Etc - - - - - e6639e5f by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make synopsis scrollable on wide screens When the synopsis is longer than the screen, you can’t see its end and you can't scroll down either, making the content unreachable. - - - - - 1f0591ff by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve information density - Reduce font size - Improve space between and within code blocks - Improve alignments - Improve spacing within sub-blocks - - - - - bf083097 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Minor adjustments Bring in some adjustments made to hackage: - link colors - page header show everything when package title is too long - - - - - 10375fc7 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix responsive triggers overlap issue The min and max width triggers have the same values, which caused the style resolution to take an intersection of both style declarations when the screen resolution had the size of the limts (say 1280px), causing an odd behaviour and look. - - - - - 95ff2f95 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix issue with menu alignment on firefox Reported and described here: https://github.com/haskell/haddock/pull/721#issuecomment-374668869 - - - - - dc86587e by Alex Biehl at 2018-10-18T08:14:32-07:00 Changelog entry for NewOcean - - - - - 27195e47 by Herbert Valerio Riedel at 2018-10-18T08:14:32-07:00 html-test --accept - - - - - 83f4f9c0 by Alex Biehl at 2018-10-18T08:14:32-07:00 Avoid name shadowing - - - - - 231487f1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font to PT Sans Also migrate some general text related changes from hackage. - - - - - 313db81a by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Use 'flex' to fix header alignment - - - - - 5087367b by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Misc of tweaks - Update link colors to hackage scheme - Tune spacing between content elements - Update footer style - Fix and improve code blocks identation - - - - - b08020df by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font in Xhtml.hs to PT Sans - - - - - 78ce06e3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve code blocks styling - Fix and improve spacing - Improve colors and borders - - - - - 81262d20 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make package-header caption backward-compatible The current html generator of this branch wraps the package-header caption as a div, which does not work (without style adjustments) with the old themes. Changing it from div to span does the trick, without needing to adjust the old stylesheets. - - - - - dc4475cb by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update test-suite reference html pages - - - - - 393d35d8 by Alec Theriault at 2018-10-18T08:25:36-07:00 Accept tests - - - - - a94484ba by Alec Theriault at 2018-10-21T10:29:29-07:00 Fix CHANGELOG - - - - - 8797eca3 by Alec Theriault at 2018-10-21T10:36:19-07:00 Update 'data-files' to include NewOcean stuff - - - - - 1ae51e4a by Simon Jakobi at 2018-10-23T11:29:14+02:00 Fix typo in a warning - - - - - 009ad8e8 by Alec Theriault at 2018-10-24T12:47:47-07:00 Update JS dependencies This was done via `npm audit fix`. I think this fixes haskell/haddock#903 along with some more serious vulnerabilities that nobody seems to have noticed. - - - - - 051994db by Alec Theriault at 2018-10-24T17:31:09-07:00 Resurrect the style-switcher This fixes haskell/haddock#810. Looks like things were broken during the quickjump refactor of the JS. For the (git) record: I do not think the style switcher is a good idea. I'm fixing it for the same reason @mzero added it; as an answer to "rumblings from some that they didn't want their pixels changed on bit" - - - - - 2a1d620f by Alec Theriault at 2018-10-24T17:38:07-07:00 Fix copy-pasta error in data-files - - - - - ed5bfb7f by Alec Theriault at 2018-10-24T20:42:14-07:00 Fix the synopsis button Here's these changes are supposed to do: * put the synopsis back on the right side * properly have it on the edge of the screen on wide screens * adjust the background of the synopsis to match the button (otherwise the grey blends in with what is underneath) * get rid of the dotted purple line * the synopsis contents are now scrollable even when in wide screens (this has been a long-standing bug) - - - - - 883fd74b by Alec Theriault at 2018-10-25T20:16:46-07:00 Avoid more conflicts in generated ids (#954) This fixes haskell/haddock#953 by passing more names into the generated ids. - - - - - ea54e331 by Alec Theriault at 2018-10-25T21:07:12-07:00 Don't hide bullets in method docs I think thst CSS was meant only to deal with fields and the effect on bullets was accidental. Fixes haskell/haddock#926. - - - - - 9a14ef4a by Alec Theriault at 2018-10-25T22:02:07-07:00 Indent more things + slightly smaller font - - - - - b9f17e29 by Alec Theriault at 2018-10-25T22:10:01-07:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 096a3cfa by Alec Theriault at 2018-10-25T22:24:38-07:00 Accept HTML output - - - - - 2669517d by Alec Theriault at 2018-10-26T09:02:35-07:00 User manual + stuff for building GHC docs - - - - - 46b27687 by Alec Theriault at 2018-10-26T09:10:59-07:00 Make 'Contents' in NewOcean scrollable This only happens if the contents block on the left is so big that it doesn't fit (vertically) on the page. If that happens, we want it to be scrollable. - - - - - 3443dd94 by Alec Theriault at 2018-10-26T09:36:46-07:00 Revert "Make 'Contents' in NewOcean scrollable" This reverts commit f909ffd8353d6463fd5dd184998a32aa98d5c922. I missed the fact this also forces the 'Contents' to always go down to the bottom of the page. - - - - - ed081424 by Alec Theriault at 2018-10-26T14:22:23-07:00 Avoid some partiality AFAICT this wasn't causing any crashes, but that's mostly because we happen not to be forcing `pkgStr` when it would diverge. We come dangerously close to doing that in `ppHtmlIndex`. Fixes haskell/haddock#569. - - - - - 6a5bec41 by Alec Theriault at 2018-10-27T10:05:04-07:00 Fix documentation in `haddock-api` (#957) * Fix misplaced Haddocks in Haddock itself Haddock should be able to generate documentation for 'haddock-api' again. * Make CI check that documentation can be built. * Add back a doc that is OK - - - - - 5100450a by Matthew Yacavone at 2018-10-27T14:51:38-04:00 More explicit foralls (GHC Proposal 0007) - - - - - 8771a6b0 by Alec Theriault at 2018-11-05T13:58:11-08:00 Only run MathJax on entities with "mathjax" class (#960) Correspondingly, we wrap all inline/diplay math in <span class="mathjax"> ... the math .... </span> This fixes haskell/haddock#959. - - - - - bd7ff5c5 by Alec Theriault at 2018-11-05T15:54:22-08:00 Deduplicate some work in 'AttachInstances' Perf only change: * avoid needlessly union-ing maps * avoid synify-ing instances twice Took this opportunity to add some docs too - - - - - cf99fd8f by Alec Theriault at 2018-11-05T15:54:22-08:00 Specialize some SYB functions Perf only change: * Add a 'SPECIALIZE' pragma to help GHC optimize a 'Data a =>' constraint * Manually specialize the needlessly general type of 'specializeTyVarBndrs' - - - - - 4f91c473 by Alec Theriault at 2018-11-05T15:54:22-08:00 Improve perf of renaming Perf only change: * don't look up type variable names (they're never in the environment) * use a difference list for accumulating missing names * more efficient 'Functor'/'Applicative' instances for 'RnM' - - - - - 4bbab0d4 by Alec Theriault at 2018-11-05T15:54:22-08:00 Faster 'Text' driven parser combinators Perf only change: * use 'getParserState'/'setParserState' to make 'Text'-optimized parser combinators * minimize uses of 'Data.Text.{pack,unpack,cons,snoc}' - - - - - fa430c02 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support hyperlink labels with inline markup The parser for pictures hasn't been properly adjusted yet. - - - - - c1431035 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support (and flatten) inline markup in image links Inline markup is supported in image links but, as per the [commonmark recommendation][0], it is stripped back to a plain text representation. [0]: https://spec.commonmark.org/0.28/#example-547 - - - - - d4ee1ba5 by Alec Theriault at 2018-11-06T12:03:24-08:00 Accept test case - - - - - 8088aeb1 by Alec Theriault at 2018-11-06T12:03:24-08:00 Fix/add to haddock-library test suite - - - - - e78f644d by Alec Theriault at 2018-11-06T13:26:31-08:00 Bump version bounds - - - - - 644335eb by Alec Theriault at 2018-11-06T13:53:30-08:00 Merge pull request haskell/haddock#875 from harpocrates/feature/markup-in-hyperlinks Inline markup in markdown-style links and images - - - - - e173ed0d by Alec Theriault at 2018-11-07T12:37:18-08:00 Fix issues around plus/minus * swap the minimize unicode to something more intuitive * use new unicode expander/collapser for instance lists * address some alignment issues in the "index" page - - - - - b2d92df7 by Alec Theriault at 2018-11-07T13:41:57-08:00 Allow "Contents" summary to scroll in a fixed div In the unfortunate event that the "Contents" summary doesn't fit vertically (like in the "Prelude"), it will be scrollable. - - - - - ca704c23 by Alec Theriault at 2018-11-07T13:45:15-08:00 Accept HTML output changes - - - - - 82c0ec6d by Alec Theriault at 2018-11-07T18:12:54-08:00 overflow-y 'scroll' -> 'auto' - - - - - 571d7657 by Alec Theriault at 2018-11-08T19:44:12-08:00 Clicking on "Contents" navigates to top of page - - - - - 8065a012 by Alec Theriault at 2018-11-08T19:44:17-08:00 Space out functions more Also, functions and data decls now have the same space before and after them. - - - - - cc650ede by Alec Theriault at 2018-11-09T08:13:35-08:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 65f8c17f by Alec Theriault at 2018-11-10T14:04:06-08:00 Update changelog - - - - - 20473847 by Alec Theriault at 2018-11-10T14:21:40-08:00 Replace oplus/ominus expander/collapser icons with triangles - - - - - 16592957 by Alec Theriault at 2018-11-10T14:35:10-08:00 Merge pull request haskell/haddock#949 from haskell/wip/new-ocean Introduce NewOcean theme. - - - - - 357cefe1 by Alec Theriault at 2018-11-10T16:02:13-08:00 Merge branch 'ghc-8.6' into ghc-head - - - - - de612267 by Alec Theriault at 2018-11-11T20:01:21-08:00 Rename 'NewOcean' theme to 'Linuwial' - - - - - 954b5baa by Alec Theriault at 2018-11-12T08:33:18-08:00 Add blockquote styling Matches b71da1feabf33efbbc517ac376bb690b5a604c2f from hackage-server. Fixes haskell/haddock#967. - - - - - d32c0b0b by Fangyi Zhou at 2018-11-12T10:24:13-08:00 Fix some broken links (#15733) Summary: For links in subpackages as well. https://phabricator.haskell.org/D5257 Test Plan: Manually verify links Reviewers: mpickering, bgamari, osa1 Reviewed By: osa1 GHC Trac Issues: haskell/haddock#15733 Differential Revision: https://phabricator.haskell.org/D5262 - - - - - 41098b1f by Alp Mestanogullari at 2018-11-15T22:40:09+01:00 Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change It got introduced in ghc/ghc at ae2c9b40f5b6bf272251d1f4107c60003f541b62. - - - - - c5c1c7e0 by Alec Theriault at 2018-11-15T13:48:13-08:00 Merge pull request haskell/haddock#970 from alpmestan/alp/fix-promotionflag Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change - - - - - 6473d3a4 by Shayan-Najd at 2018-11-23T01:38:49+01:00 [TTG: Handling Source Locations] Foundation and Pat Trac Issues haskell/haddock#15495 This patch removes the ping-pong style from HsPat (only, for now), using the plan laid out at https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/HandlingSourceLocations (solution A). - the class `HasSrcSpan`, and its functions (e.g., `cL` and `dL`), are introduced - some instances of `HasSrcSpan` are introduced - some constructors `L` are replaced with `cL` - some patterns `L` are replaced with `dL->L` view pattern - some type annotation are necessarily updated (e.g., `Pat p` --> `Pat (GhcPass p)`) - - - - - 7a088dfe by Alec Theriault at 2018-11-26T11:11:28-08:00 More uniform handling of `forall`'s in HTML/LaTeX * don't forget to print explicit `forall`'s when there are arg docs * when printing an explicit `forall`, print all tyvars Fixes haskell/haddock#973 - - - - - d735e570 by Alec Theriault at 2018-12-12T08:42:09-08:00 Fix warnings, accept output * remove redundant imports (only brought to light due to recent work for improving redundant import detection) * fix a bug that was casuing exports to appear in reverse order * fix something in haddock-library that prevented compilation on old GHC's - - - - - a3852f8a by Zejun Wu at 2018-12-14T09:37:47-05:00 Output better debug infromation on internal error in extractDecl This will make investigation of haskell/haddock#979 easier - - - - - 2eccb5b9 by Alec Theriault at 2018-12-17T09:25:10-05:00 Refactor names + unused functions (#982) This commit should not introduce any change in functionality! * consistently use `getOccString` to convert `Name`s to strings * compare names directly when possible (instead of comparing strings) * get rid of unused utility functions - - - - - e82e4df8 by Alec Theriault at 2018-12-20T16:16:30-05:00 Load plugins when compiling each module (#983) * WIP: Load (typechecker) plugins from language pragmas * Revert "Load plugins when starting a GHC session (#905)" This reverts commit 72d82e52f2a6225686d9668790ac33c1d1743193. * Simplify plugin initialization code - - - - - 96e86f38 by Alec Theriault at 2018-12-23T10:23:20-05:00 Properly synify and render promoted type variables (#985) * Synify and render properly promoted type variables Fixes haskell/haddock#923. * Accept output - - - - - 23343345 by Alec Theriault at 2018-12-27T16:39:38-05:00 Remove `haddock-test`'s dep. on `syb` (#987) The functionality is easily inlined into one short function: `gmapEverywhere`. This doesn't warrant pulling in another package. - - - - - d0734f21 by Alec Theriault at 2018-12-27T16:39:52-05:00 Address deprecation warnings in `haddock-test` (#988) Fixes haskell/haddock#885. - - - - - 4d9f144e by mynguyen at 2018-12-30T23:42:26-05:00 Visible kind application haddock update - - - - - ffe0e9ed by Alec Theriault at 2019-01-07T13:55:22-08:00 Print kinded tyvars in constructors for Hoogle (#993) Fixes haskell/haddock#992 - - - - - 2e18b55d by Alec Theriault at 2019-01-10T16:42:45-08:00 Accept new output `GHC.Maybe` -> `Data.Maybe` (#996) Since 53874834b779ad0dfbcde6650069c37926da1b79 in GHC, "GHC.Maybe" is marked as `not-home`. That changes around some test output. - - - - - 055da666 by Gabor Greif at 2019-01-22T14:41:51+01:00 Lone typofix - - - - - 01bb71c9 by Alec Theriault at 2019-01-23T11:46:46-08:00 Keep forall on H98 existential data constructors (#1003) The information about whether or not there is a source-level `forall` is already available on a `ConDecl` (as `con_forall`), so we should use it instead of always assuming `False`! Fixes haskell/haddock#1002. - - - - - f9b9bc0e by Ryan Scott at 2019-01-27T09:28:12-08:00 Fix haskell/haddock#1004 with a pinch of dropForAlls - - - - - 5cfcdd0a by Alec Theriault at 2019-01-28T16:49:57-08:00 Loosen 'QuickCheck' and 'hspec' bounds It looks like the new versions don't cause any breakage and loosening the bounds helps deps fit in one stack resolver. - - - - - 3545d3dd by Alec Theriault at 2019-01-31T01:37:25-08:00 Use `.hie` files for the Hyperlinker backend (#977) # Summary This is a large architectural change to the Hyperlinker. * extract link (and now also type) information from `.hie` instead of doing ad-hoc SYB traversals of the `RenamedSource`. Also adds a superb type-on-hover feature (#715). * re-engineer the lexer to avoid needless string conversions. By going directly through GHC's `P` monad and taking bytestring slices, we avoid a ton of allocation and have better handling of position pragmas and CPP. In terms of performance, the Haddock side of things has gotten _much_ more efficient. Unfortunately, much of this is cancelled out by the increased GHC workload for generating `.hie` files. For the full set of boot libs (including `ghc`-the-library) * the sum of total time went down by 9-10% overall * the sum of total allocations went down by 6-7% # Motivation Haddock is moving towards working entirely over `.hi` and `.hie` files. This change means we no longer need the `RenamedSource` from `TypecheckedModule` (something which is _not_ in `.hi` files). # Details Along the way a bunch of things were fixed: * Cross package (and other) links are now more reliable (#496) * The lexer tries to recover from errors on every line (instead of at CPP boundaries) * `LINE`/`COLUMN` pragmas are taken into account * filter out zero length tokens before rendering * avoid recomputing the `ModuleName`-based `SrcMap` * remove the last use of `Documentation.Haddock.Utf8` (see haskell/haddock#998) * restructure temporary folder logic for `.hi`/`.hie` model - - - - - 2ded3359 by Herbert Valerio Riedel at 2019-02-02T12:06:12+01:00 Update/modernise haddock-library.cabal file - - - - - 62b93451 by Herbert Valerio Riedel at 2019-02-02T12:19:31+01:00 Tentatively declare support for unreleased base-4.13/ghc-8.8 - - - - - 6041e767 by Herbert Valerio Riedel at 2019-02-02T16:04:32+01:00 Normalise LICENSE text w/ cabal's BSD2 template Also, correct the `.cabal` files to advertise `BSD2` instead of the incorrect `BSD3` license. - - - - - 0b459d7f by Alec Theriault at 2019-02-02T18:06:12-08:00 CI: fetch GHC from validate artifact Should help make CI be less broken - - - - - 6b5c07cf by Alec Theriault at 2019-02-02T18:06:12-08:00 Fix some Hyperlinker test suite fallout * Amend `ParserSpec` to match new Hyperlinker API - pass in compiler info - strip out null tokens * Make `hypsrc-test` pass reliably - strip out `local-*` ids - strip out `line-*` ids from the `ClangCppBug` test - re-accept output - - - - - ded34791 by Nathan Collins at 2019-02-02T18:31:23-08:00 Update README instructions for Stack No need to `stack install` Haddock to test it. Indeed, `stack install` changes the `haddock` on user's `PATH` if `~/.local/bin` is on user's `PATH` which may not be desirable when hacking on Haddock. - - - - - 723298c9 by Alec Theriault at 2019-02-03T09:11:05-08:00 Remove `Documentation.Haddock.Utf8` The circumstances under which this module appeared are completely gone. The Hyperlinker backend no longer needs this module (it uses the more efficient `Encoding` module from `ghc`). Why no deprecation? Because this module really shouldn't exist! - It isn't used in `haddock-library`/`haddock-api` anymore - It was copy pasted directly from `utf8-string` - Folks seeking a boot-lib only solution can use `ghc`'s `Encoding` - - - - - 51050006 by Alec Theriault at 2019-02-03T22:58:58-08:00 Miscellaneous improvements to `Convert` (#1020) Now that Haddock is moving towards working entirely over `.hi` and `.hie` files, all declarations and types are going to be synthesized via the `Convert` module. In preparation for this change, here are a bunch of fixes to this module: * Add kind annotations to type variables in `forall`'s whose kind is not `Type`, unless the kind can be inferred from some later use of the variable. See `implicitForAll` and `noKindTyVars` in particular if you wish to dive into this. * Properly detect `HsQualTy` in `synifyType`. This is done by following suit with what GHC's `toIfaceTypeX` does and checking the first argument of `FunTy{} :: Type` to see if it classified as a given/wanted in the typechecker (see `isPredTy`). * Beef up the logic around figuring out when an explicit `forall` is needed. This includes: observing if any of the type variables will need kind signatures, if the inferred type variable order _without_ a forall will still match the one GHC claims, and some other small things. * Add some (not yet used) functionality for default levity polymorphic type signatures. This functionality similar to `fprint-explicit-runtime-reps`. Couple other smaller fixes only worth mentioning: * Show the family result signature only when it isn't `Type` * Fix rendering of implicit parameters in the LaTeX and Hoogle backends * Better handling of the return kind of polykinded H98 data declarations * Class decls produced by `tyThingToLHsDecl` now contain associated type defaults and default method signatures when appropriate * Filter out more `forall`'s in pattern synonyms - - - - - 841980c4 by Oleg Grenrus at 2019-02-04T08:44:25-08:00 Make a fixture of weird parsing of lists (#997) The second example is interesting. If there's a list directly after the header, and that list has deeper structure, the parser is confused: It finds two lists: - One with the first nested element, - everything after it I'm not trying to fix this, as I'm not even sure this is a bug, and not a feature. - - - - - 7315c0c8 by Ryan Scott at 2019-02-04T12:17:56-08:00 Fix haskell/haddock#1015 with dataConUserTyVars (#1022) The central trick in this patch is to use `dataConUserTyVars` instead of `univ_tvs ++ ex_tvs`, which displays the foralls in a GADT constructor in a way that's more faithful to how the user originally wrote it. Fixes haskell/haddock#1015. - - - - - ee0b49a3 by Ryan Scott at 2019-02-04T15:25:17-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. - - - - - 1c850dc8 by Alan Zimmerman at 2019-02-05T21:54:18+02:00 Matching changes in GHC for haskell/haddock#16236 - - - - - ab03c38e by Simon Marlow at 2019-02-06T08:07:33+00:00 Merge pull request haskell/haddock#1014 from hvr/pr/bsd2-normalise Normalise LICENSE text w/ cabal's BSD2 template - - - - - 5a92ccae by Alec Theriault at 2019-02-10T06:21:55-05:00 Merge remote-tracking branch 'gitlab/wip/T16236-2' into ghc-head - - - - - c0485a1d by Alec Theriault at 2019-02-10T03:32:52-08:00 Removes `haddock-test`s dependency on `xml`/`xhtml` (#1027) This means that `html-test`, `latex-test`, `hoogle-test`, and `hypsrc-test` now only depend on GHC boot libs. So we should now be able to build and run these as part of GHC's testsuite. \o/ The reference output has changed very slightly, in three ways: * we don't convert quotes back into `&quot;` as the `xml` lib did * we don't add extra `&nbsp;` as the `xml` lib did * we now remove the entire footer `div` (instead of just emptying it) - - - - - 65a448e3 by Alec Theriault at 2019-02-11T12:27:41-05:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - 360ca937 by Alec Theriault at 2019-02-13T11:36:11-05:00 Clean up logic for guessing `-B` and `--lib` (#1026) Haddock built with the `in-ghc-tree` flag tries harder to find the GHC lib folder and its own resources. This should make it possible to use `in-ghc-tree`-built Haddock without having to specify the `-B` and `--lib` options (just how you can use in-tree GHC without always specifying the `-B` option). The logic to do this relies on `getExecutablePath`, so we only get this auto-detection on platforms where this function works. - - - - - d583e364 by Alec Theriault at 2019-02-16T10:41:22-05:00 Fix tests broken by GHC Changes in 19626218566ea709b5f6f287d3c296b0c4021de2 affected some of the hyperlinker output. Accepted the new output (hovering over a `..` now shows you what that wildcard binds). Also fixed some stray deprecation warnings. - - - - - da0c42cc by Vladislav Zavialov at 2019-02-17T11:39:19+03:00 Parser changes to match !380 - - - - - ab96bed7 by Ryan Scott at 2019-02-18T04:44:08-05:00 Bump ghc version to 8.9 - - - - - 44b7c714 by Alec Theriault at 2019-02-22T05:49:43-08:00 Match GHC changes for T16185 `FunTy` now has an `AnonArgFlag` that indicates whether the arrow is a `t1 => t2` or `t1 -> t2`. This commit shouldn't change any functionality in Haddock. - - - - - 2ee653b1 by Alec Theriault at 2019-02-24T18:53:33-08:00 Update .travis.yml Points to the new GHC CI artifact. - - - - - 90939d71 by Alec Theriault at 2019-02-25T00:42:41-08:00 Support value/type namespaces on identifier links Identifier links can be prefixed with a 'v' or 't' to indicate the value or type namespace of the desired identifier. For example: -- | Some link to a value: v'Data.Functor.Identity' -- -- Some link to a type: t'Data.Functor.Identity' The default is still the type (with a warning about the ambiguity) - - - - - d6ed496c by Alec Theriault at 2019-02-25T00:42:46-08:00 Better identifier parsing * '(<|>)' and '`elem`' now get parsed and rendered properly as links * 'DbModule'/'DbUnitId' now properly get split apart into two links * tuple names now get parsed properly * some more small niceties... The identifier parsing code is more precise and more efficient (although to be fair: it is also longer and in its own module). On the rendering side, we need to pipe through information about backticks/parens/neither all the way through from renaming to the backends. In terms of impact: a total of 35 modules in the entirety of the bootlib + ghc lib docs change. The only "regression" is things like '\0'. These should be changed to @\\0@ (the path by which this previously worked seems accidental). - - - - - 3c3b404c by Alec Theriault at 2019-02-25T22:12:11-08:00 Fix standalone deriving docs Docs on standalone deriving decls for classes with associated types should be associated with the class instance, not the associated type instance. Fixes haskell/haddock#1033 - - - - - d51ef69e by Alec Theriault at 2019-02-26T19:14:59-08:00 Fix bogus identifier defaulting This avoids a situation in which an identifier would get defaulted to a completely different identifier. Prior to this commit, the 'Bug1035' test case would hyperlink 'Foo' into 'Bar'! Fixes haskell/haddock#1035. - - - - - 88cbbdc7 by Ryan Scott at 2019-02-27T10:14:03-05:00 Visible dependent quantification (#16326) changes - - - - - 0dcf6cee by Xia Li-yao at 2019-02-27T21:53:27-05:00 Menu item controlling which instances are expanded/collapsed (#1007) Adds a menu item (like "Quick Jump") for options related to displaying instances. This provides functionality for: * expanding/collapsing all instances on the currently opened page * controlling whether instances are expanded/collapsed by default * controlling whether the state of instances should be "remembered" This new functionality is implemented in Typescript in `details-helper`. The built-in-themes style switcher also got a revamp so that all three of QuickJump, the style switcher, and instance preferences now have the same style and implementation structure. See also: https://mail.haskell.org/pipermail/haskell-cafe/2019-January/130495.html Fixes haskell/haddock#698. Co-authored-by: Lysxia <lysxia at gmail.com> Co-authored-by: Nathan Collins <conathan at galois.com> - - - - - 3828c0fb by Alec Theriault at 2019-02-28T12:42:49-05:00 `--show-interface` should output to stdout. (#1040) Fixes haskell/haddock#864. - - - - - a50f4cda by gbaz at 2019-03-01T07:43:16-08:00 Increase contrast of Linuwal theme (#1037) This is to address the concern that, on less nice and older screens, some of the shades of grey blend in too easily with the white background. * darken the font slightly * darken slightly the grey behind type signatures and such * add a border and round the corners on code blocks * knock the font down by one point - - - - - ab4d41de by Alec Theriault at 2019-03-03T09:23:26-08:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 12f509eb by Ben Gamari at 2019-03-04T22:13:20-05:00 Remove reference to Opt_SplitObjs flag Split-objects has been removed. - - - - - 5b3e4c9a by Ryan Scott at 2019-03-06T19:16:24-05:00 Update html-test output to reflect haskell/haddock#16391 changes - - - - - fc228af1 by Alec Theriault at 2019-03-09T08:29:23-08:00 Match changes for "Stop inferring over-polymorphic kinds" The `hsq_ext` field of `HsQTvs` is now just the implicit variables (instead of also including information about which of these variables are dependent). This commit shouldn't change any functionality in Haddock. - - - - - 6ac109eb by Alec Theriault at 2019-03-09T11:22:55-08:00 Add .hi, .dyn_hi, etc files to .gitignore Fixes haskell/haddock#1030. - - - - - b55f0c05 by Alec Theriault at 2019-03-09T11:22:55-08:00 Better support for default methods in classes * default methods now get rendered differently * default associated types get rendered * fix a forgotten `s/TypeSig/ClassOpSig/` refactor in LaTeX backend * LaTeX backend now renders default method signatures NB: there is still no way to document default class members and the NB: LaTeX backend still crashes on associated types - - - - - 10aea0cf by Alec Theriault at 2019-03-09T11:22:55-08:00 Avoid multi-line `emph` in LaTeX backend `markupWarning` often processes inputs which span across paragraphs. Unfortunately, LaTeX's `emph` is not made to handle this (and will crash). Fixes haskell/haddock#936. - - - - - d22dc2c9 by Alec Theriault at 2019-03-09T11:22:55-08:00 Many LaTeX backend fixes After this commit, we can run with `--latex` on all boot libraries without crashing (although the generated LaTeX still fails to compile in a handful of larger packages like `ghc` and `base`). * Add newlines after all block elements in LaTeX. This is important to prevent the final output from being more an more indented. See the `latext-test/src/Example` test case for a sample of this. * Support associated types in class declarations (but not yet defaults) * Several small issues for producing compiling LaTeX; - avoid empy `\haddockbeginargs` lists (ex: `type family Any`) - properly escape identifiers depending on context (ex: `Int#`) - add `vbox` around `itemize`/`enumerate` (so they can be in tables) * Several spacing fixes: - limit the width of `Pretty`-arranged monospaced code - cut out extra space characters in export lists - only escape spaces if there are _multiple_ spaces - allow type signatures to be multiline (even without docs) * Remove uninteresting and repetitive `main.tex`/`haddock.sty` files from `latex-test` test reference output. Fixes haskell/haddock#935, haskell/haddock#929 (LaTeX docs for `text` build & compile) Fixes haskell/haddock#727, haskell/haddock#930 (I think both are really about type families...) - - - - - 0e6cee00 by Alec Theriault at 2019-03-29T12:11:56-07:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - ce05434d by Alan Zimmerman at 2019-03-29T12:12:11-07:00 Matching changes in GHC for haskell/haddock#16236 (cherry picked from commit 3ee6526d4ae7bf4deb7cd1caf24b3d7355573576) - - - - - d85766b2 by Ben Gamari at 2019-03-29T12:14:04-07:00 Bump GHC to 8.8 - - - - - 5a82cbaf by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Redo ParseModuleHeader - - - - - b9033348 by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - bb55c8f4 by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove outdated `.ghci` files and `scripts` The `.ghci` files are actively annoying when trying to `cabal v2-repl`. As for the `scripts`, the distribution workflow is completely different. - - - - - 5ee244dc by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove obsolete arcanist files + STYLE Now that GHC is hosted on Gitlab, the arcanist files don't make sense anymore. The STYLE file contains nothing more than a dead link too. - - - - - d07c1928 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Redo ParseModuleHeader - - - - - 492762d2 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - af2ac773 by Ryan Scott at 2019-05-14T17:22:13-04:00 Changes for haskell/haddock#16110/#16356 - - - - - 6820ed0d by Alec Theriault at 2019-05-17T08:51:27-07:00 Unbreak haskell/haddock#1004 test case `fail` is no longer part of `Monad`. - - - - - 6bf7be98 by Alec Theriault at 2019-05-17T08:51:27-07:00 Fix haskell/haddock#1063 with better parenthesization logic for contexts The only other change in html/hoogle/hyperlinker output for the boot libraries that this caused is a fix to some Hoogle output for implicit params. ``` $ diff -r _build/docs/ old_docs diff -r _build/docs/html/libraries/base/base.txt old_docs/html/libraries/base/base.txt 13296c13296 < assertError :: (?callStack :: CallStack) => Bool -> a -> a --- > assertError :: ?callStack :: CallStack => Bool -> a -> a ``` - - - - - b5716b61 by Ryan Scott at 2019-05-22T17:24:32-04:00 Match changes with haskell/haddock#14332 - - - - - c115abf6 by Alec Theriault at 2019-05-26T16:01:58-04:00 Remove Haddock's dependency on `Cabal` At this point, Haddock depended on Cabal-the-library solely for a verbosity parser (which misleadingly accepts all sorts of verbosity options that Haddock never uses). Now, the only dependency on Cabal is for `haddock-test` (which uses Cabal to locate the Haddock interface files of a couple boot libraries). - - - - - e5b2d4a3 by Alec Theriault at 2019-05-26T16:16:25-04:00 Regression test: promoted lists in associated types When possible, associated types with promoted lists should use the promoted list literal syntax (instead of repeated applications of ': and '[]). This was fixed in 2122de5473fd5b434af690ff9ccb1a2e58491f8c. Closes haskell/haddock#466, - - - - - cc5ad5d3 by Alec Theriault at 2019-05-26T17:55:54-04:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 4b3301a6 by Alec Theriault at 2019-05-26T17:57:52-04:00 Release haddock-2.23, haddock-library-1.8.0 Tentatively adjust bounds and changelogs for the release to be bundled with GHC 8.8.1. - - - - - 69c7cfce by Matthew Pickering at 2019-05-30T10:54:27+01:00 Update hyperlinker tests for new types in .hie files - - - - - 29b7e738 by Zubin Duggal at 2019-05-30T10:57:51+01:00 update for new way to store hiefile headers - - - - - aeca5d5f by Zubin Duggal at 2019-06-04T18:57:42-04:00 update for new way to store hiefile headers - - - - - ba2ca518 by Ben Gamari at 2019-06-07T23:11:14+00:00 Update test output for introduction of Safe-Inferred - - - - - 3a975a6c by Ryan Scott at 2019-07-03T12:06:27-04:00 Changes for haskell/haddock#15247 - - - - - 0df46555 by Zubin Duggal at 2019-07-22T10:52:50+01:00 Fix haddockHypsrcTest - - - - - 2688686b by Sylvain Henry at 2019-09-12T23:19:39+02:00 Fix for GHC module renaming - - - - - 9ec0f3fc by Alec Theriault at 2019-09-20T03:21:00-04:00 Fix Travis CI, loosen .cabal bounds (#1089) Tentatively for the 2.23 release: * updated Travis CI to work again * tweaked bounds in the `.cabal` files * adjusted `extra-source-files` to properly identify test files - - - - - ca559beb by Matthías Páll Gissurarson at 2019-09-28T12:14:40-04:00 Small change in to facilitate extended typed-holes (#1090) This change has no functional effect on haddock itself, it just changes one pattern to use `_ (` rather than `_(`, so that we may use `_(` as a token for extended typed-holes later. - - - - - 02e28976 by Vladislav Zavialov at 2019-09-28T12:17:45-04:00 Remove spaces around @-patterns (#1093) This is needed to compile `haddock` when [GHC Proposal haskell/haddock#229](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0229-whitespace-bang-patterns.rst) is implemented. - - - - - 83cbbf55 by Alexis King at 2019-09-30T21:12:42-04:00 Fix the ignore-exports option (#1082) The `ignore-exports` option has been broken since haskell/haddock#688, as mentioned in https://github.com/haskell/haddock/pull/766#issue-172505043. This PR fixes it. - - - - - e127e0ab by Ben Gamari at 2019-10-06T15:12:06-04:00 Fix a few haddock issues - - - - - 3a0f5c89 by Zubin Duggal at 2019-10-07T17:56:13-04:00 Fix crash when there are no srcspans in the file due to CPP - - - - - 339c5ff8 by Alec Theriault at 2019-10-07T17:56:13-04:00 Prefer un-hyperlinked sources to no sources It is possible to fail to extract an HIE ast. This is however not a reason to produce _no_ output - we should still make a colorized HTML page. - - - - - d47ef478 by Alec Theriault at 2019-10-07T17:56:13-04:00 Add a regression test for haskell/haddock#1091 Previously, this input would crash Haddock. - - - - - ed7c8b0f by Alec Theriault at 2019-10-07T20:56:48-04:00 Add Hyperlinker test cases for TH-related stuff Hopefully this will guard against regressions around quasiquotes, TH quotes, and TH splices. - - - - - d00436ab by Andreas Klebinger at 2019-10-21T15:53:03+02:00 Refactor for withTiming changes. - - - - - 4230e712 by Ben Gamari at 2019-10-22T09:36:37-04:00 Merge pull request haskell/haddock#1101 from AndreasPK/withTimingRefactor Refactor for withTiming changes. - - - - - d155c5f4 by Ryan Scott at 2019-10-23T10:37:17-04:00 Reify oversaturated data family instances correctly (#1103) This fixes haskell/haddock#1103 by adapting the corresponding patch for GHC (see https://gitlab.haskell.org/ghc/ghc/issues/17296 and https://gitlab.haskell.org/ghc/ghc/merge_requests/1877). - - - - - 331a5adf by Sebastian Graf at 2019-10-25T17:14:40+02:00 Refactor for OutputableBndrId changes - - - - - 48a490e0 by Ben Gamari at 2019-10-27T10:16:16-04:00 Merge pull request haskell/haddock#1105 from sgraf812/wip/flexible-outputable Refactor for OutputableBndrId changes - - - - - f62a7dfc by Sebastian Graf at 2019-11-01T11:54:16+00:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - d9b242ed by Ryan Scott at 2019-11-03T13:20:03-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. (cherry picked from commit cfd682c5fd03b099a3d78c44f9279faf56a0ac70) - - - - - dfd42406 by Sebastian Graf at 2019-11-04T07:02:14-05:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - 0b15be7c by Ben Gamari at 2019-11-09T13:21:33-05:00 Import isRuntimeRepVar from Type rather than TyCoRep isRuntimeRepVar is not longer exported from TyCoRep due to ghc#17441. - - - - - 091f7283 by Ben Gamari at 2019-11-10T12:47:06-05:00 Bump to GHC 8.10 - - - - - e88c71f2 by Ben Gamari at 2019-11-14T00:22:24-05:00 Merge pull request haskell/haddock#1110 from haskell/wip/T17441 Import isRuntimeRepVar from Type rather than TyCoRep - - - - - 4e0bbc17 by Ben Gamari at 2019-11-14T00:22:45-05:00 Version bumps for GHC 8.11 - - - - - 0e85ceb4 by Ben Gamari at 2019-11-15T11:59:45-05:00 Bump to GHC 8.10 - - - - - 00d6d68b by Ben Gamari at 2019-11-16T18:35:58-05:00 Bump ghc version to 8.11 - - - - - dde1fc3f by Ben Gamari at 2019-11-16T20:40:37-05:00 Drop support for base 4.13 - - - - - f52e331d by Vladislav Zavialov at 2019-11-24T13:02:28+03:00 Update Hyperlinker.Parser.classify to use ITdollar - - - - - 1ad96198 by Vladislav Zavialov at 2019-11-28T16:12:33+03:00 Remove HasSrcSpan (#17494) - - - - - 651afd70 by Herbert Valerio Riedel at 2019-12-08T12:08:16+01:00 Document error-prone conditional definition of instances This can easily trip up people if one isn't aware of it. Usually it's better to avoid this kind of conditionality especially for typeclasses for which there's an compat-package as conditional instances like these tend to fragment the ecosystem into those packages that go the extra mile to provide backward compat via those compat-packages and those that fail to do so. - - - - - b521af56 by Herbert Valerio Riedel at 2019-12-08T12:09:54+01:00 Fix build-failure regression for base < 4.7 The `$>` operator definition is available only since base-4.7 which unfortunately wasn't caught before release to Hackage (but has been fixed up by a metadata-revision) This commit introduces a `CompatPrelude` module which allows to reduce the amount of CPP by ousting it to a central location, i.e. the new `CompatPrelude` module. This pattern also tends to reduce the tricks needed to silence unused import warnings. Addresses haskell/haddock#1119 - - - - - 556c375d by Sylvain Henry at 2020-01-02T19:01:55+01:00 Fix after Iface modules renaming - - - - - bd6c53e5 by Sylvain Henry at 2020-01-07T00:48:48+01:00 hsyl20-modules-renamer - - - - - fb23713b by Ryan Scott at 2020-01-08T07:41:13-05:00 Changes for GHC#17608 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2372 - - - - - 4a4dd382 by Ryan Scott at 2020-01-25T08:08:26-05:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - e782a44d by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename PackageConfig into UnitInfo - - - - - ba3c9f05 by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename lookupPackage - - - - - ab37f9b3 by Ben Gamari at 2020-01-29T13:00:44-05:00 Merge pull request haskell/haddock#1125 from haskell/wip/T17566-take-two Changes for GHC#17566 - - - - - 3ebd5ae0 by Ryan Scott at 2020-01-31T05:56:50-05:00 Merge branch 'wip-hsyl20-package-refactor' into ghc-head - - - - - 602a747e by Richard Eisenberg at 2020-02-04T09:05:43+00:00 Echo GHC's removal of PlaceHolder module This goes with GHC's !2083. - - - - - ccfe5679 by Sylvain Henry at 2020-02-10T10:13:56+01:00 Module hierarchy: runtime (cf haskell/haddock#13009) - - - - - 554914ce by Cale Gibbard at 2020-02-10T16:10:39-05:00 Fix build of haddock in stage1 We have to use the correct version of the GHC API, but the version of the compiler itself doesn't matter. - - - - - 5b6fa2a7 by John Ericson at 2020-02-10T16:18:07-05:00 Noramlize `tested-with` fields in cabal files - - - - - e6eb3ebe by Vladislav Zavialov at 2020-02-16T13:25:26+03:00 No MonadFail/Alternative for P - - - - - 90e181f7 by Ben Gamari at 2020-02-18T14:13:47-05:00 Merge pull request haskell/haddock#1129 from obsidiansystems/wip/fix-stage1-build Fix build of haddock in stage1 - - - - - 93b64636 by Sylvain Henry at 2020-02-19T11:20:27+01:00 Modules: Driver (#13009) - - - - - da4f6c7b by Vladislav Zavialov at 2020-02-22T15:33:02+03:00 Use RealSrcSpan in InstMap - - - - - 479b1b50 by Ben Gamari at 2020-02-23T10:28:13-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 55ecacf0 by Sylvain Henry at 2020-02-25T15:18:27+01:00 Modules: Core (#13009) - - - - - 60867b3b by Vladislav Zavialov at 2020-02-28T15:53:52+03:00 Ignore the BufLoc/BufSpan added in GHC's !2516 - - - - - 1e5506d3 by Sylvain Henry at 2020-03-02T12:32:43+01:00 Modules: Core (#13009) - - - - - 6fb53177 by Richard Eisenberg at 2020-03-09T14:49:40+00:00 Changes in GHC's !1913. - - - - - 30b792ea by Ben Gamari at 2020-03-16T12:45:02-04:00 Merge pull request haskell/haddock#1130 from hsyl20/wip/hsyl20-modules-core2 Modules: Core (#13009) - - - - - cd761ffa by Sylvain Henry at 2020-03-18T15:24:00+01:00 Modules: Types - - - - - b6646486 by Ben Gamari at 2020-03-18T14:42:43-04:00 Merge pull request haskell/haddock#1133 from hsyl20/wip/hsyl20/modules/types Modules: Types - - - - - 9325d734 by Kleidukos at 2020-03-19T12:38:31-04:00 Replace the 'caption' class so that the collapsible sections are shown - - - - - 5e2bb555 by Kleidukos at 2020-03-19T12:38:31-04:00 Force ghc-8.8.3 - - - - - c6fcd0aa by Kleidukos at 2020-03-19T12:38:31-04:00 Update test fixtures - - - - - 5c849cb1 by Sylvain Henry at 2020-03-20T09:34:39+01:00 Modules: Types - - - - - 7f439155 by Alec Theriault at 2020-03-20T20:17:01-04:00 Merge branch 'ghc-8.8' into ghc-8.10 - - - - - b7904e5c by Alina Banerjee at 2020-03-20T20:24:17-04:00 Update parsing to strip whitespace from table cells (#1074) * Update parsing to strip leading & trailing whitespace from table cells * Update fixture data to disallow whitespaces at both ends in table cells * Add test case for whitespaces stripped from both ends of table cells * Update table reference test data for html tests - - - - - b9d60a59 by Alec Theriault at 2020-03-22T11:46:42-04:00 Clean up warnings * unused imports * imports of `Data.List` without import lists * missing `CompatPrelude` file in `.cabal` - - - - - 0c317dbe by Alec Theriault at 2020-03-22T18:46:54-04:00 Fix NPM security warnings This was done by calling `npm audit fix`. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. - - - - - 6e306242 by Alec Theriault at 2020-03-22T20:10:52-04:00 Tentative 2.24 release Adjusted changelogs and versions in `.cabal` files in preparation for the upcoming release bundled with GHC 8.10. - - - - - 1bfb4645 by Ben Gamari at 2020-03-23T16:40:54-04:00 Merge commit '3c2944c037263b426c4fe60a3424c27b852ea71c' into HEAD More changes from the GHC types module refactoring. - - - - - be8c6f3d by Alec Theriault at 2020-03-26T20:10:53-04:00 Update `.travis.yml` to work with GHC 8.10.1 * Regenerated the Travis file with `haskell-ci` * Beef up `.cabal` files with more `tested-with` information - - - - - b025a9c6 by Alec Theriault at 2020-03-26T20:10:53-04:00 Update README Removed some out of date links/info, added some more useful links. * badge to Hackage * update old trac link * `ghc-head` => `ghc-8.10` * `cabal new-*` is now `cabal v2-*` and it should Just Work * `--test-option='--accept'` is the way to accept testsuite output - - - - - 564d889a by Alec Theriault at 2020-03-27T20:34:33-04:00 Fix crash in `haddock-library` on unicode space Our quickcheck tests for `haddock-library` stumbled across an edge case input that was causing Haddock to crash: it was a unicode space character. The root cause of the crash is that we were implicitly assuming that if a space character was not " \t\f\v\r", it would have to be "\n". We fix this by instead defining horizontal space as: any space character that is not '\n'. Fixes haskell/haddock#1142 - - - - - 2d360ba1 by Alec Theriault at 2020-03-27T21:57:32-04:00 Disallow qualified uses of reserved identifiers This a GHC bug (https://gitlab.haskell.org/ghc/ghc/issues/14109) too, but it is a relatively easy fix in Haddock. Note that the fix must live in `haddock-api` instead of `haddock-library` because we can only really decide if an identifier is a reserved one by asking the GHC lexer. Fixes haskell/haddock#952 - - - - - 47ae22ed by Alec Theriault at 2020-03-28T13:36:25-04:00 Remove unused `Haddock.Utils` functions * removed functions in `Haddock.Utils` that were not used anywhere (or exported from the `haddock-api` package) * moved GHC-specific utils from `Haddock.Utils` to `Haddock.GhcUtils` - - - - - c0291245 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use TTG empty extensions to remove some `error`'s None of these error cases should ever have been reachable, so this is just a matter of leveraging the type system to assert this. * Use the `NoExtCon` and `noExtCon` to handle case matches for no extension constructors, instead of throwing an `error`. * Use the extension field of `HsSpliceTy` to ensure that this variant of `HsType` cannot exist in an `HsType DocNameI`. - - - - - 0aff8dc4 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use `unLoc`/`noLoc` from GHC instead of `unL`/`reL` * `unL` is already defined by GHC as `unLoc` * `reL` is already defined by GHC as `noLoc` (in a safer way too!) * Condense `setOutputDir` and add a about exporting from GHC Fixes haskell/haddock#978 - - - - - bf6f2fb7 by Alec Theriault at 2020-03-28T13:36:25-04:00 Cleanup up GHC flags in `.cabal` files * enable more useful warning flags in `haddock-api`, handle the new warnings generated * remove `-fwarn-tabs` (now we'd use `-Wtabs`, but this has been in `-Wall` for a while now) - - - - - c576fbf1 by Alec Theriault at 2020-03-28T13:36:25-04:00 `haddock-library` document header level Document the fact the header level is going to always be between 1 and 6 inclusive. Along the way, I also optimized the parsing code a bit. - - - - - 71bce0ee by Alec Theriault at 2020-03-28T14:26:27-04:00 Disallow links in section headers This is quite straightforward to implement, since we already had a function `docToHtmlNoAnchors` (which we used to generate the link in the sidebar "Contents"). This breaks test `Bug387`, but that test case has aged badly: we now automatically generate anchors for all headings, so manually adding an anchor in a section makes no sense. Nested anchors are, as pointed out in haskell/haddock#1054, disallowed by the HTML standard. Fixes haskell/haddock#1054 - - - - - b461b0ed by Sylvain Henry at 2020-03-30T10:34:23+02:00 Modules: type checker - - - - - cd8cd1ee by Ben Gamari at 2020-03-31T12:45:02-04:00 Merge pull request haskell/haddock#1152 from hsyl20/wip/hsyl20/modules/tc Module renaming - - - - - 5e8f8ea7 by Felix Yan at 2020-04-01T17:58:06-07:00 Allow QuickCheck 2.14 Builds fine and all tests pass. - - - - - dc6b1633 by Sylvain Henry at 2020-04-05T16:43:44+02:00 Module renaming: amend previous patch - - - - - eee2f4ae by Ryan Scott at 2020-04-05T09:04:43-07:00 Fix haskell/haddock#1050 by filtering out invisible AppTy arguments This makes the `synifyType` case for `AppTy` more intelligent by taking into consideration the visibilities of each `AppTy` argument and filtering out any invisible arguments, as they aren't intended to be displayed in the source code. (See haskell/haddock#1050 for an example of what can happen if you fail to filter these out.) Along the way, I noticed that a special `synifyType` case for `AppTy t1 (CoercionTy {})` could be consolidated with the case below it, so I took the opportunity to tidy this up. - - - - - 23eb99e8 by Ben Gamari at 2020-04-07T11:19:58-04:00 Merge pull request haskell/haddock#1154 from hsyl20/wip/hsyl20/modules/tc Module renaming: amend previous patch - - - - - 072d994d by Ryan Scott at 2020-04-07T19:32:47-04:00 Make NoExtCon fields strict These changes are a part of a fix for [GHC#17992](https://gitlab.haskell.org/ghc/ghc/issues/17992). - - - - - d8ebf6c8 by Ignat Insarov at 2020-04-09T21:15:01-04:00 Recode Doc to Json. (#1159) * Recode Doc to Json. * More descriptive field labels. - - - - - 52df4b4e by Sylvain Henry at 2020-04-10T12:39:18+02:00 Module renaming - - - - - d9ab8ec8 by Cale Gibbard at 2020-04-14T11:43:34-04:00 Add instance of XCollectPat for DocNameI - - - - - 323d221d by Cale Gibbard at 2020-04-14T11:43:34-04:00 Rename XCollectPat -> CollectPass - - - - - 2df80867 by Alec Theriault at 2020-04-15T07:30:51-07:00 Prune docstrings that are never rendered When first creating a Haddock interface, trim `ifaceDocMap` and `ifaceArgMap` to not include docstrings that can never appear in the final output. Besides checking with GHC which names are exported, we also need to keep all the docs attached to instance declarations (it is much tougher to detect when an instance is fully private). This change means: * slightly smaller interface files (7% reduction on boot libs) * slightly less work to do processing docstrings that aren't used * no warnings in Haddock's output about private docstrings (see haskell/haddock#1070) I've tested manually that this does not affect any of the boot library generated docs (the only change in output was some small re-ordering in a handful of instance lists). This should mean no docstrings have been incorrectly dropped. - - - - - f49c90cc by Alec Theriault at 2020-04-15T07:30:51-07:00 Don't warn about missing links in miminal sigs When renaming the Haddock interface, never emit warnings when renaming a minimal signature. Also added some documention around `renameInterface`. Minimal signatures intentionally include references to potentially un-exported methods (see the discussion in haskell/haddock#330), so it is expected that they will not always have a link destination. On the principle that warnings should always be resolvable, this shouldn't produce a warning. See haskell/haddock#1070. - - - - - a9eda64d by Ben Gamari at 2020-04-17T09:27:35-04:00 Merge pull request haskell/haddock#1160 from hsyl20/wip/hsyl20/modules/systools Module renaming - - - - - f40d7879 by Cale Gibbard at 2020-04-20T11:30:38-04:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ttg-con-pat - - - - - a50e7753 by Ben Gamari at 2020-04-20T11:36:10-04:00 Merge pull request haskell/haddock#1165 from obsidiansystems/wip/ttg-con-pat Trees that Grow refactor (GHC !2553) - - - - - 6a24795c by Alec Theriault at 2020-04-21T08:06:45-07:00 Fallback to `hiDecl` when `extractDecl` fails Sometimes, the declaration being exported is a subdecl (for instance, a record accessor getting exported at the top-level). For these cases, Haddock has to find a way to produce some synthetic sensible top-level declaration. This is done with `extractDecl`. As is shown by haskell/haddock#1067, this is sometimes impossible to do just at a syntactic level (for instance when the subdecl is re-exported). In these cases, the only sensible thing to do is to try to reify a declaration based on a GHC `TyThing` via `hiDecl`. - - - - - eee1a8b7 by Sylvain Henry at 2020-04-24T15:46:05+02:00 Module structure - - - - - 50b9259c by Iñaki at 2020-04-25T18:38:11-04:00 Add support for custom section anchors (#1179) This allows to have stable anchors for groups, even if the set of groups in the documentation is altered. The syntax for setting the anchor of a group is -- * Group name #desiredAnchor# Which will produce an html anchor of the form '#g:desiredAnchor' Co-authored-by: Iñaki García Etxebarria <git at inaki.blueleaf.cc> - - - - - 4003c97a by Ben Gamari at 2020-04-26T09:35:15-04:00 Merge pull request haskell/haddock#1166 from hsyl20/wip/hsyl20/modules/utils Module structure - - - - - 5206ab60 by Sylvain Henry at 2020-04-27T16:47:39+02:00 Renamed UnitInfo fields - - - - - c32c333b by Sylvain Henry at 2020-04-27T17:32:58+02:00 UnitId has been renamed into Unit - - - - - 3e87db64 by Sylvain Henry at 2020-04-27T17:36:00+02:00 Fix for GHC.Unit.* modules - - - - - ae3323a7 by Ben Gamari at 2020-04-29T12:36:37-04:00 Merge pull request haskell/haddock#1183 from hsyl20/wip/hsyl20/unitid Refactoring of Unit code - - - - - b105564a by Artem Pelenitsyn at 2020-05-03T08:14:10+01:00 add dependency on exceptions because GHC.Exception was boiled down (ghc haskell/haddock#18075) - - - - - 9857eff3 by Zubin Duggal at 2020-05-04T18:48:25+01:00 Atomic update of NameCache in readHieFile - - - - - 86bbb226 by Sylvain Henry at 2020-05-14T16:36:27+02:00 Fix after Config module renaming - - - - - a4bbdbc2 by Gert-Jan Bottu at 2020-05-15T22:09:44+02:00 Explicit Specificity Support for Haddock - - - - - 46199daf by Ben Gamari at 2020-05-19T09:59:56-04:00 Merge pull request haskell/haddock#1192 from hsyl20/hsyl20/modules-config Fix after Config module renaming - - - - - f9a9d2ba by Gert-Jan Bottu at 2020-05-20T16:48:38-04:00 Explicit Specificity Support for Haddock - - - - - 55c5b7ea by Ben Gamari at 2020-05-21T00:32:02-04:00 Merge commit 'a8d7e66da4dcc3b242103271875261604be42d6e' into ghc-head - - - - - a566557f by Cale Gibbard at 2020-05-21T16:02:06-04:00 isBootSummary now produces a result of type IsBootInterface - - - - - ea52f905 by Zubin Duggal at 2020-05-24T17:55:48+01:00 update for hiefile-typeclass-info - - - - - 49ba7a67 by Willem Van Onsem at 2020-05-25T12:23:01-04:00 Use floor over round to calculate the percentage (#1195) If we compile documentation where only a small fraction is undocumented, it is misleading to see 100% coverage - 99% is more intuitive. Fixes haskell/haddock#1194 - - - - - c025ebf1 by Ben Gamari at 2020-05-29T14:32:42-04:00 Merge pull request haskell/haddock#1185 from obsidiansystems/boot-disambig isBootSummary now produces a result of type IsBootInterface - - - - - 74ab9415 by Ben Gamari at 2020-05-29T20:23:39-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - b40be944 by Ben Gamari at 2020-06-03T17:02:31-04:00 testsuite: Update expected output for simplified subsumption - - - - - 624be71c by Ryan Scott at 2020-06-05T12:43:23-04:00 Changes for GHC#18191 See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3337. - - - - - fbd8f7ce by Sylvain Henry at 2020-06-08T15:31:47+02:00 Fix after unit refactoring - - - - - 743fda4d by Ben Gamari at 2020-06-09T12:09:58-04:00 Merge pull request haskell/haddock#1202 from hsyl20/wip/hsyl20/unitid-ii Fix after unit refactoring - - - - - d07a06a9 by Ryan Scott at 2020-06-13T07:16:55-04:00 Use HsForAllTelescope (GHC#18235) - - - - - 389bb60d by Ben Gamari at 2020-06-13T15:30:52-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - 7a377f5f by Ben Gamari at 2020-06-17T14:53:16-04:00 Merge pull request haskell/haddock#1199 from bgamari/wip/ghc-8.12 haddock: Bounds bumps for GHC 8.12 - - - - - 9fd9e586 by Krzysztof Gogolewski at 2020-06-17T16:09:07-04:00 Adapt Haddock to LinearTypes See ghc/ghc!852. - - - - - 46fe7636 by Ben Gamari at 2020-06-18T14:20:02-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 35a3c9e2 by Zubin Duggal at 2020-06-21T21:19:18+05:30 Use functions exported from HsToCore - - - - - 8abe3928 by Ben Gamari at 2020-06-24T13:53:39-04:00 Merge pull request haskell/haddock#1204 from wz1000/wip/haddock-hstocore Use functions exported from GHC.HsToCore.Docs - - - - - 22f2c937 by Matthías Páll Gissurarson at 2020-06-26T19:07:03+02:00 Adapt Haddock for QualifiedDo - - - - - 3f6208d7 by Vladislav Zavialov at 2020-06-28T14:28:16+03:00 Handle LexicalNegation's ITprefixminus - - - - - 03a19f41 by Sylvain Henry at 2020-07-02T09:37:38+02:00 Rename hsctarget into backend - - - - - ea17ff23 by Andreas Klebinger at 2020-07-02T17:44:18+02:00 Update for UniqFM changes. - - - - - 9872f2f3 by Ben Gamari at 2020-07-09T10:39:19-04:00 Merge pull request haskell/haddock#1209 from AndreasPK/wip/typed_uniqfm Update for UniqFM changes. - - - - - 68f7b668 by Krzysztof Gogolewski at 2020-07-12T18:16:57+02:00 Sync with GHC removing {-# CORE #-} pragma See ghc ticket haskell/haddock#18048 - - - - - eb372681 by Sylvain Henry at 2020-07-20T11:41:30+02:00 Rename hscTarget into backend - - - - - fb7f78bf by Ben Gamari at 2020-07-21T12:15:25-04:00 Merge pull request haskell/haddock#1214 from hsyl20/wip/hsyl20/hadrian/ncg Rename hscTarget into backend - - - - - 1e8f5b56 by Ben Gamari at 2020-07-23T09:11:50-04:00 Merge commit '904dce0cafe0a241dd3ef355775db47fc12f434d' into ghc-head - - - - - d8fd1775 by Zubin Duggal at 2020-07-23T18:46:40+05:30 Update for modular ping pong - - - - - 8416f872 by Ben Gamari at 2020-07-23T09:35:03-04:00 Merge pull request haskell/haddock#1200 from wz1000/wip/wz1000-modular-ping-pong Modular ping pong - - - - - a24a8577 by Ben Gamari at 2020-07-28T15:23:36-04:00 Bump GHC version to 9.0 - - - - - 6a51c9dd by Sylvain Henry at 2020-08-05T18:47:05+02:00 Fix after Outputable refactoring - - - - - c05e1c99 by Ben Gamari at 2020-08-10T14:41:41-04:00 Merge pull request haskell/haddock#1223 from hsyl20/wip/hsyl20/dynflags/exception Fix after Outputable refactoring - - - - - d964f15b by Sylvain Henry at 2020-08-12T11:58:49+02:00 Fix after HomeUnit - - - - - 8e6d5b23 by Ben Gamari at 2020-08-12T14:25:30-04:00 Merge pull request haskell/haddock#1225 from hsyl20/wip/hsyl20/plugins/homeunit Fix after HomeUnit - - - - - 8c7880fe by Sylvain Henry at 2020-08-17T14:13:29+02:00 Remove Ord FastString instance - - - - - 8ea410db by Alex Biehl at 2020-08-19T10:56:32+02:00 Another round of `npm audit fix` (#1228) This should shut down the warnings on Github. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. Last NPM dependency audit happend in d576b2327e2bc117f912fe0a9d595e9ae62614e0 Co-authored-by: Alex Biehl <alex.biehl at target.com> - - - - - 7af6e2a8 by Ben Gamari at 2020-08-31T13:59:34-04:00 Merge pull request haskell/haddock#1226 from hsyl20/wip/hsyl20/fs_ord Remove Ord FastString instance - - - - - ffbc8702 by Alan Zimmerman at 2020-09-07T21:47:41+01:00 Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - a93f1268 by Alan Zimmerman at 2020-09-07T23:11:38+01:00 Merge pull request haskell/haddock#1232 from haskell/wip/T18639-remove-generated-pragma, Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - 1f605d50 by Ben Gamari at 2020-09-14T18:30:01-04:00 Bump GHC version to 9.1 - - - - - 6599df62 by Vladislav Zavialov at 2020-09-18T14:05:15+03:00 Bump base upper bound to 4.16 - - - - - a01b3c43 by Ben Gamari at 2020-09-22T15:41:48-04:00 Update hypsrc-test for QuickLook This appears to be a spurious change. - - - - - e9cc6cac by Vladislav Zavialov at 2020-09-26T21:00:12+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 30e3ca7c by Sylvain Henry at 2020-09-29T11:18:32-04:00 Update for parser (#1234) - - - - - b172f3e3 by Vladislav Zavialov at 2020-09-30T01:01:30+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 0b9c08d3 by Sylvain Henry at 2020-09-30T11:02:33+02:00 Adapt to GHC parser changes - - - - - b9540b7a by Sylvain Henry at 2020-10-12T09:13:38-04:00 Don't pass the HomeUnitId (#1239) - - - - - 34762e80 by HaskellMouse at 2020-10-13T12:58:04+03:00 Changed tests due to unification of `Nat` and `Natural` in the follwing merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3583 - - - - - 256f86b6 by Vladislav Zavialov at 2020-10-15T10:48:03+03:00 Add whitespace in: map ($ v) - - - - - 4a3f711b by Alan Zimmerman at 2020-10-19T08:57:27+01:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled - - - - - 072cdd21 by Alan Zimmerman at 2020-10-21T14:48:28-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 9e09a445 by Alan Zimmerman at 2020-10-21T23:53:34-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 636d7de3 by Sylvain Henry at 2020-10-26T14:31:54-04:00 GHC.Driver.Types refactoring (#1242) - - - - - a597f000 by Ryan Scott at 2020-10-29T04:18:05-04:00 Adapt to the removal of Hs{Boxed,Constraint}Tuple See ghc/ghc!4097 and GHC#18723. - - - - - b96660fb by Ryan Scott at 2020-10-30T04:53:05-04:00 Adapt to HsConDecl{H98,GADT}Details split Needed for GHC#18844. - - - - - c287d82c by Ryan Scott at 2020-10-30T19:35:59-04:00 Adapt to HsOuterTyVarBndrs These changes accompany ghc/ghc!4107, which aims to be a fix for haskell/haddock#16762. - - - - - a34c31a1 by Ryan Scott at 2020-11-13T13:38:34-05:00 Adapt to splitPiTysInvisible being renamed to splitInvisPiTys This is a part of !4434, a fix for GHC#18939. - - - - - 66ea459d by Sylvain Henry at 2020-11-16T10:59:30+01:00 Fix after Plugins moved into HscEnv - - - - - 508556d8 by Ben Gamari at 2020-11-18T15:47:40-05:00 Merge pull request haskell/haddock#1253 from hsyl20/wip/hsyl20/plugins/hscenv Fix after Plugins moved into HscEnv - - - - - 620fec1a by Andreas Klebinger at 2020-11-24T20:51:59+01:00 Update for changes in GHC's Pretty - - - - - 01cc13ab by Richard Eisenberg at 2020-11-25T23:18:35-05:00 Avoid GHC#18932. - - - - - 8d29ba21 by Cale Gibbard at 2020-11-25T23:18:35-05:00 Add type arguments to PrefixCon - - - - - 414d5f87 by Sylvain Henry at 2020-11-30T17:06:04+01:00 DynFlags's unit fields moved to HscEnv - - - - - e356668c by Ben Gamari at 2020-11-30T11:11:37-05:00 Merge pull request haskell/haddock#1258 from hsyl20/wip/hsyl20/hscenv/unitstate Unit fields moved from DynFlags to HscEnv - - - - - 7cf552f1 by Ben Gamari at 2020-12-03T10:31:27-05:00 Merge pull request haskell/haddock#1257 from AndreasPK/wip/andreask/opt_dumps Update for changes in GHC's Pretty - - - - - fc0871c3 by Veronika Romashkina at 2020-12-08T16:35:33+01:00 Fix docs links from Darcs to GitHub in intro (#1262) - - - - - 7059e808 by Veronika Romashkina at 2020-12-08T16:36:16+01:00 Use gender neutral word in docs (#1260) - - - - - 1b16e5ee by Maximilian Tagher at 2020-12-08T16:40:03+01:00 Allow scrolling search results (#1235) Closes https://github.com/haskell/haddock/issues/1231 - - - - - 8a118c01 by dependabot[bot] at 2020-12-08T16:40:25+01:00 Bump bl from 1.2.2 to 1.2.3 in /haddock-api/resources/html (#1255) Bumps [bl](https://github.com/rvagg/bl) from 1.2.2 to 1.2.3. - [Release notes](https://github.com/rvagg/bl/releases) - [Commits](https://github.com/rvagg/bl/compare/v1.2.2...v1.2.3) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - c89ff587 by Xia Li-yao at 2020-12-08T16:42:17+01:00 Allow more characters in anchor following module reference (#1220) - - - - - 14af7d64 by Xia Li-yao at 2020-12-08T16:43:05+01:00 Add dangling changes from branches ghc-8.6 and ghc-8.8 (#1243) * Fix multiple typos and inconsistencies in doc/markup.rst Note: I noticed some overlap with haskell/haddock#1112 from @wygulmage and haskell/haddock#1081 from @parsonsmatt after creating these proposed changes - mea culpa for not looking at the open PRs sooner. * Fix haskell/haddock#1113 If no Signatures, no section of index.html * Change the formatting of missing link destinations The current formatting of the missing link destination does not really help user to understand the reasons of the missing link. To address this, I've changed the formatting in two ways: - the missing link symbol name is now fully qualified. This way you immediately know which haskell module cannot be linked. It is then easier to understand why this module does not have documentation (hidden module or broken documentation). - one line per missing link, that's more readable now that symbol name can be longer due to qualification. For example, before haddock was listing missing symbol such as: ``` could not find link destinations for: Word8 Word16 mapMaybe ``` Now it is listed as: ``` could not find link destinations for: - Data.Word.Word8 - Data.Word.Word16 - Data.Maybe.mapMaybe ``` * Add `--ignore-link-symbol` command line argument This argument can be used multiples time. A missing link to a symbol listed by `--ignore-link-symbol` won't trigger "missing link" warning. * Forbid spaces in anchors (#1148) * Improve error messages with context information (#1060) Co-authored-by: Matt Audesse <matt at mattaudesse.com> Co-authored-by: Mike Pilgrem <mpilgrem at users.noreply.github.com> Co-authored-by: Guillaume Bouchard <guillaume.bouchard at tweag.io> Co-authored-by: Pepe Iborra <pepeiborra at gmail.com> - - - - - 89e3af13 by tomjaguarpaw at 2020-12-08T18:00:04+01:00 Enable two warnings (#1245) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - c3320f8d by Willem Van Onsem at 2020-12-08T18:26:55+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 685df308 by Alex Biehl at 2020-12-08T20:06:26+01:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - be3ec3c0 by Alex Biehl at 2020-12-08T20:06:26+01:00 Import intercalate - - - - - 32c33912 by Matthías Páll Gissurarson at 2020-12-08T21:15:30+01:00 Adapt Haddock for QualifiedDo - - - - - 31696088 by Alex Biehl at 2020-12-08T22:06:02+01:00 Fix haddock-library tests - - - - - fbc0998a by Alex Biehl at 2020-12-08T23:08:23+01:00 Move to GitHub CI (#1266) * Initial version of ci.yml This is a straight copy from Dmitrii Kovanikov's blog post at https://kodimensional.dev/github-actions. Will adapt to haddock in successive commits. * Delete .travis.yml * Modify to only test on ghc-8.10.{1,2} * Use actions/setup-haskell at v1.1.4 * Relax QuickCheck bound on haddock-api * Remove stack matrix for now * Nail down to ghc-8.10 branch for now * Pin index state to 2020-12-08T20:13:44Z for now * Disable macOS and Windows tests for now for speed up - - - - - 5b946b9a by tomjaguarpaw at 2020-12-10T19:01:41+01:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - bc5a408f by dependabot[bot] at 2020-12-10T19:02:16+01:00 Bump ini from 1.3.5 to 1.3.7 in /haddock-api/resources/html (#1269) Bumps [ini](https://github.com/isaacs/ini) from 1.3.5 to 1.3.7. - [Release notes](https://github.com/isaacs/ini/releases) - [Commits](https://github.com/isaacs/ini/compare/v1.3.5...v1.3.7) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - d02995f1 by Andrew Martin at 2020-12-14T16:48:40-05:00 Update for boxed rep - - - - - a381aeff by Ben Gamari at 2020-12-15T15:13:30-05:00 Revert "Enable two warnings (#1245) (#1268)" As this does not build on GHC `master`. This reverts commit 7936692badfe38f23ae95b51fb7bd7c2ff7e9bce. - - - - - a63c0a9e by Ben Gamari at 2020-12-15T15:17:59-05:00 Revert "Update for boxed rep" This reverts commit 4ffb30d8b637ccebecc81ce610f0af451ac8088d. - - - - - 53bfbb29 by Ben Gamari at 2020-12-15T15:37:24-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - bae76a30 by Ben Gamari at 2020-12-16T02:44:42+00:00 Update output for nullary TyConApp optimisation (ghc/ghc!2952) - - - - - 4b733b57 by Krzysztof Gogolewski at 2020-12-16T20:03:14+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. - - - - - ee463bd3 by Ryan Scott at 2020-12-16T16:55:23-05:00 Adapt to HsCoreTy (formerly NewHsTypeX) becoming a type synonym Needed for !4417, the fix for GHC#15706 and GHC#18914. - - - - - ed0b02f8 by tomjaguarpaw at 2020-12-19T10:17:19+00:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - d80bf8f5 by Sylvain Henry at 2020-12-21T10:09:25+01:00 Fix after binder collect changes - - - - - bf4c9d32 by Adam Gundry at 2020-12-23T21:35:01+00:00 Adapt to changes to GlobalRdrElt and AvailInfo Needed for ghc/ghc!4467 - - - - - 37736c4c by John Ericson at 2020-12-28T12:27:02-05:00 Support a new ghc --make node type for parallel backpack upsweep - - - - - 717bdeac by Vladislav Zavialov at 2020-12-29T10:50:02+03:00 Inline and fix getGADTConTypeG The getGADTConTypeG used HsRecTy, which is at odds with GHC issue haskell/haddock#18782. I noticed that getGADTConTypeG was only used in the Hoogle backend. Interestingly, when handling H98 constructors, Hoogle converts RecCon to PrefixCon (see Haddock.Backends.Hoogle.ppCtor). So I changed getGADTConTypeG to handle RecConGADT in the same manner as PrefixConGADT, and after this simplification moved it into the 'where' clause of ppCtor, to the only place where it is used. The practical effect of this change is as follows. Consider this example: data TestH98 = T98 { bar::Int } data TestGADT where TG :: { foo :: Int } -> TestGADT Before this patch, haddock --hoogle used to produce: T98 :: Int -> TestH98 [TG] :: {foo :: Int} -> TestGADT Notice how the record syntax was discarded in T98 but not TG. With this patch, we always produce signatures without record syntax: T98 :: Int -> TestH98 [TG] :: Int -> TestGADT I suspect this might also be a bugfix, as currently Hoogle doesn't seem to render GADT record constructors properly. - - - - - cb1b8c56 by Andreas Abel at 2020-12-30T21:12:37+01:00 Build instructions: haddock-library and -api first! - - - - - b947f6ad by Ben Gamari at 2020-12-31T13:04:19-05:00 Merge pull request haskell/haddock#1281 from obsidiansystems/wip/backpack-j Changes to support -j with backpack - - - - - 120e1cfd by Hécate Moonlight at 2021-01-04T19:54:58+01:00 Merge pull request haskell/haddock#1282 from andreasabel/master Build instructions: haddock-library and -api first! - - - - - fd45e41a by Ben Gamari at 2021-01-05T16:14:31-05:00 Merge remote-tracking branch 'origin/ghc-8.10' into ghc-9.0 - - - - - b471bdec by Ben Gamari at 2021-01-05T16:23:02-05:00 Merge commit '1e56f63c3197e7ca1c1e506e083c2bad25d08793' into ghc-9.0 - - - - - 81cdbc41 by Alex Biehl at 2021-01-09T12:14:41+01:00 Prepare Haddock for being a GHC Plugin - - - - - b646d952 by Alex Biehl at 2021-01-09T12:14:41+01:00 Make Haddock a GHC Plugin - - - - - cc044674 by Alex Biehl at 2021-01-09T12:14:41+01:00 Add -j[n] CLI param to Haddock executable It translates to `--ghcopt=-j[n]` - - - - - 84a04073 by Alex Biehl at 2021-01-09T12:14:41+01:00 Abstract Monad for interface creation I found that when running as a plugin the lookupName function (which runs in Ghc monad) does not work correctly from the typeCheckResultAction hook. Instead, we abstracted the monad used when creating interfaces, so that access to GHC session specific parts is explicit and so that the TcM can provide their (correct) implementation of lookupName. - - - - - 5be2c4f7 by Alex Biehl at 2021-01-09T12:14:41+01:00 Accept tests - - - - - 8cefee9d by Alex Biehl at 2021-01-09T16:10:47+01:00 Add missing dependency for mtl - - - - - 3681f919 by Ben Gamari at 2021-01-13T18:39:25-05:00 Merge remote-tracking branch 'origin/ghc-9.0' into ghc-head - - - - - 33c6b152 by Hécate Moonlight at 2021-01-14T16:04:20+01:00 Merge pull request haskell/haddock#1273 from hsyl20/wip/hsyl20/arrows Fix after binder collect changes - - - - - 70d13e8e by Joachim Breitner at 2021-01-22T19:03:45+01:00 Make haddock more robust to changes to the `Language` data type With the introduction of GHC2021, the `Languages` data type in GHC will grow. In preparation of that (and to avoid changing haddock with each new language), this change makes the code handle extensions to that data type gracefully. (cherry picked from commit c341dd7c9c3fc5ebc83a2d577c5a726f3eb152a5) - - - - - 7d6dd57a by John Ericson at 2021-01-22T22:02:02+00:00 Add `NoGhcTc` instance now that it's not closed - - - - - e5fdaf0a by Alan Zimmerman at 2021-01-23T22:57:44+00:00 Merge pull request haskell/haddock#1293 from obsidiansystems/wip/fix-18936 Add `NoGhcTc` instance now that it's not closed - - - - - 989a1e05 by Oleg Grenrus at 2021-01-24T16:11:46+03:00 Add import list to Data.List - - - - - 368e144a by Ben Gamari at 2021-01-28T22:15:48+01:00 Adapt to "Make PatSyn immutable" - - - - - abe66c21 by Alfredo Di Napoli at 2021-02-01T08:05:35+01:00 Rename pprLogErrMsg to new name - - - - - e600e75c by Hécate Moonlight at 2021-02-05T14:53:00+01:00 Move CI to ghc-9.0 - - - - - dd492961 by Vladislav Zavialov at 2021-02-05T14:53:00+01:00 Update cabal.project and README build instructions - - - - - 31bd292a by Hécate Moonlight at 2021-02-05T15:03:56+01:00 Merge pull request haskell/haddock#1296 from Kleidukos/ghc-9.0 Merge the late additions to ghc-8.10 into ghc-9.0 - - - - - 6388989e by Vladislav Zavialov at 2021-02-05T17:41:57+03:00 Cleanup: fix build warnings - - - - - f99407ef by Daniel Rogozin at 2021-02-05T18:11:48+03:00 type level characters support for haddock (required for haskell/haddock#11342) - - - - - d8c6b26f by Hécate Moonlight at 2021-02-05T17:44:50+01:00 Add a CONTRIBUTING.md file - - - - - 6a01ad98 by Hécate Moonlight at 2021-02-05T17:58:16+01:00 Merge pull request haskell/haddock#1312 from Kleidukos/proper-branch-etiquette Add a CONTRIBUTING.md file - - - - - 955eecc4 by Vladislav Zavialov at 2021-02-05T20:29:00+03:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into ghc-head - - - - - 47b3d6ab by Hécate Moonlight at 2021-02-05T19:09:38+01:00 Amend the CONTRIBUTING.md file - - - - - 23de6137 by Hécate Moonlight at 2021-02-05T19:16:49+01:00 Merge pull request haskell/haddock#1313 from Kleidukos/amend-contributing Amend the CONTRIBUTING.md file - - - - - 69026b59 by Krzysztof Gogolewski at 2021-02-05T23:05:56+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. (cherry picked from commit b4b4d896d2d68d6c48e7db7bfe95c185ca0709cb) - - - - - ea026b78 by Oleg Grenrus at 2021-02-06T17:14:45+01:00 Add import list to Data.List - - - - - 5204326f by Hécate Moonlight at 2021-02-06T17:15:44+01:00 Merge pull request haskell/haddock#1316 from Kleidukos/explicit-imports-to-data-list Add import list to Data.List - - - - - 1f4d2136 by Ben Gamari at 2021-02-06T11:53:31-05:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ghc-head-merge - - - - - 13f0d09a by Ben Gamari at 2021-02-06T11:53:45-05:00 Fix partial record selector warning - - - - - 5c115f7e by Ben Gamari at 2021-02-06T11:55:52-05:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into wip/ghc-head-merge - - - - - b6fd8b75 by Ben Gamari at 2021-02-06T12:01:31-05:00 Merge commit '41964cb2fd54b5a10f8c0f28147015b7d5ad2c02' into wip/ghc-head-merge - - - - - a967194c by Ben Gamari at 2021-02-06T18:30:35-05:00 Merge branch 'wip/ghc-head-merge' into ghc-head - - - - - 1f4c3a91 by MorrowM at 2021-02-07T01:52:33+02:00 Fix search div not scrolling - - - - - 684b1287 by Iñaki García Etxebarria at 2021-02-07T16:13:04+01:00 Add support for labeled module references Support a markdown-style way of annotating module references. For instance -- | [label]("Module.Name#anchor") will create a link that points to the same place as the module reference "Module.Name#anchor" but the text displayed on the link will be "label". - - - - - bdb55a5d by Hécate Moonlight at 2021-02-07T16:18:10+01:00 Merge pull request haskell/haddock#1319 from alexbiehl/alex/compat Backward compat: Add support for labeled module references - - - - - 6ca70991 by Hécate Moonlight at 2021-02-07T16:21:29+01:00 Merge pull request haskell/haddock#1314 from tweag/show-linear-backport Backport haskell/haddock#1238 (linear types) to ghc-9.0 - - - - - d9d73298 by Alex Biehl at 2021-02-07T17:46:25+01:00 Remove dubious parseModLink Instead construct the ModLink value directly when parsing. - - - - - 33b4d020 by Hécate Moonlight at 2021-02-07T17:52:05+01:00 Merge pull request haskell/haddock#1320 from haskell/alex/fix Remove dubious parseModLink - - - - - 54211316 by Hécate Moonlight at 2021-02-07T18:12:07+01:00 Merge pull request haskell/haddock#1318 from MorrowM/ghc-9.0 Fix search div not scrolling - - - - - 19db679e by alexbiehl-gc at 2021-02-07T18:14:46+01:00 Merge pull request haskell/haddock#1317 from bgamari/wip/ghc-head-merge Merge ghc-8.10 into ghc-head - - - - - 6bc1e9e4 by Willem Van Onsem at 2021-02-07T18:25:30+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - c8537cf8 by alexbiehl-gc at 2021-02-07T18:30:40+01:00 Merge pull request haskell/haddock#1322 from haskell/alex/forward-port simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 2d47ae4e by alexbiehl-gc at 2021-02-07T18:39:59+01:00 Merge branch 'ghc-head' into ghc-9.0 - - - - - 849e4733 by Hécate Moonlight at 2021-02-07T18:43:19+01:00 Merge pull request haskell/haddock#1321 from Kleidukos/ghc-9.0 Merge ghc-9.0 into ghc-head - - - - - ee6095d7 by Sylvain Henry at 2021-02-08T11:36:38+01:00 Update for Logger - - - - - 4ad688c9 by Alex Biehl at 2021-02-08T18:11:24+01:00 Merge pull request haskell/haddock#1310 from hsyl20/wip/hsyl20/logger2 Logger refactoring - - - - - 922a9e0e by Ben Gamari at 2021-02-08T12:54:33-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - 991649d2 by Sylvain Henry at 2021-02-09T10:55:17+01:00 Fix to build with HEAD - - - - - a8348dc2 by Hécate Moonlight at 2021-02-09T10:58:51+01:00 Merge pull request haskell/haddock#1327 from hsyl20/wip/hsyl20/logger2 Fix to build with HEAD - - - - - 0abdbca6 by Fendor at 2021-02-09T20:06:15+01:00 Add UnitId to Target record - - - - - d5790a0e by Alex Biehl at 2021-02-11T10:32:32+01:00 Stable sort for (data/newtype) instances - - - - - 8e6036f5 by Alex Biehl at 2021-02-11T10:32:32+01:00 Also make TyLit deterministic - - - - - f76d2945 by Hécate Moonlight at 2021-02-11T11:00:31+01:00 Merge pull request haskell/haddock#1329 from hsyl20/hsyl20/stabe_iface Stable sort for instances - - - - - 5e0469ea by Oleg Grenrus at 2021-02-14T15:28:15+02:00 Add import list to Data.List in Haddock.Interface.Create - - - - - fa57cd24 by Hécate Moonlight at 2021-02-14T17:19:27+01:00 Merge pull request haskell/haddock#1331 from phadej/more-explicit-data-list-imports Add import list to Data.List in Haddock.Interface.Create - - - - - f0cd629c by Hécate Moonlight at 2021-02-21T00:22:01+01:00 Merge pull request haskell/haddock#1311 from fendor/wip/add-targetUnitId-to-target Add UnitId to Target record - - - - - 674ef723 by Joachim Breitner at 2021-02-22T10:39:18+01:00 html-test: Always set language from ghc-9.2 on, the “default” langauge of GHC is expected to change more wildly. To prepare for that (and unblock https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4853), this sets the language for all the test files to `Haskell2010`. This should insolate this test suite against changes to the default. Cherry-picked from https://github.com/haskell/haddock/pull/1341 - - - - - f072d623 by Hécate Moonlight at 2021-02-22T10:56:51+01:00 Merge pull request haskell/haddock#1342 from nomeata/joachim/haskell2010-in-tests-ghc-head html-test: Always set language - - - - - caebbfca by Hécate Moonlight at 2021-02-22T11:53:07+01:00 Clean-up of Interface and Interface.Create's imports and pragmata - - - - - f6caa89d by Hécate Moonlight at 2021-02-22T11:54:58+01:00 Merge pull request haskell/haddock#1345 from Kleidukos/head/fix-interface-imports [ghc-head] Clean-up of Interface and Interface.Create's imports and pragmata - - - - - 7395c9cb by Hécate Moonlight at 2021-02-22T18:44:57+01:00 Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 6e9fb5d5 by Hécate Moonlight at 2021-02-22T18:45:28+01:00 Merge pull request haskell/haddock#1348 from Kleidukos/head/explicit-imports-interface Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 9198b118 by Alan Zimmerman at 2021-02-22T20:04:24+00:00 Context becomes a Maybe in the GHC AST This prevents noLoc's appearing in the ParsedSource. Match the change in GHC. - - - - - 0af20f64 by Hécate Moonlight at 2021-02-23T12:36:12+01:00 Fix the call-site of guessTarget in Interface.hs Explicit the imports from GHC.HsToCore.Docs - - - - - b7886885 by Hécate Moonlight at 2021-02-23T12:37:54+01:00 Merge pull request haskell/haddock#1349 from Kleidukos/fix-interface-guesstarget-call Fix the call-site of guessTarget in Interface.hs - - - - - 9cf041ba by Sylvain Henry at 2021-02-24T11:08:20+01:00 Fix haddockHypsrcTest output in ghc-head - - - - - b194182a by Hécate Moonlight at 2021-02-24T11:12:36+01:00 Merge pull request haskell/haddock#1351 from hsyl20/wip/hsyl20/fix-head Fix haddockHypsrcTest output in ghc-head - - - - - 3ce8b375 by Shayne Fletcher at 2021-03-06T09:55:03-05:00 Add ITproj to parser - - - - - d2abf762 by Ben Gamari at 2021-03-06T19:26:49-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a0f6047d by Andrew Martin at 2021-03-07T11:25:23-05:00 Update for boxed rep - - - - - 6f63c99e by Ben Gamari at 2021-03-10T13:20:21-05:00 Update for "FastString: Use FastMutInt instead of IORef Int" - - - - - e13f01df by Luke Lau at 2021-03-10T15:38:40-05:00 Implement template-haskell's putDoc This catches up to GHC using the new extractTHDocs function, which returns documentation added via the putDoc function (provided it was compiled with Opt_Haddock). Since it's already a map from names -> docs, there's no need to do traversal etc. It also matches the change from the argument map being made an IntMap rather than a Map Int - - - - - 89263d94 by Alan Zimmerman at 2021-03-15T17:15:26+00:00 Match changes in GHC AST for in-tree API Annotations As landed via https://gitlab.haskell.org/ghc/ghc/-/merge_requests/2418 - - - - - 28db1934 by Alan Zimmerman at 2021-03-15T20:40:09+00:00 Change some type family test results. It is not clear to me whether the original was printing incorrectly (since we did not have the TopLevel flag before now), or if this behaviour is expected. For the time being I am assuming the former. - - - - - 7c11c989 by Sylvain Henry at 2021-03-22T10:05:19+01:00 Fix after NameCache changes - - - - - addbde15 by Sylvain Henry at 2021-03-22T10:05:19+01:00 NameCache doesn't store a UniqSupply anymore - - - - - 15ec6cec by Ben Gamari at 2021-03-22T17:53:44-04:00 Bump GHC version to 9.2 - - - - - dbd6aa63 by Hécate Moonlight at 2021-03-24T14:28:36+01:00 Merge pull request haskell/haddock#1365 from hsyl20/wip/hsyl20/iface1 NameCache refactoring - - - - - 2d32da7e by Oleg Grenrus at 2021-03-27T01:12:00+02:00 Specialization of Data.List - - - - - 32b84fa6 by Fendor at 2021-03-27T10:50:17+01:00 Add UnitId to Target record This way we always know to which home-unit a given target belongs to. So far, there only exists a single home-unit at a time, but it enables having multiple home-units at the same time. - - - - - 54bf9f0e by Hécate Moonlight at 2021-03-28T14:08:35+02:00 Merge pull request haskell/haddock#1368 from fendor/target-unit-id-revert Add UnitId to Target record - - - - - 7dea168a by Alan Zimmerman at 2021-03-29T08:45:52+01:00 EPA : Rename ApiAnn to EpAnn - - - - - 72967f65 by Alfredo Di Napoli at 2021-03-29T09:47:01+02:00 pprError changed name in GHC - - - - - 4bc61035 by Alan Zimmerman at 2021-03-29T16:16:27-04:00 EPA : Rename ApiAnn to EpAnn - - - - - 108d031d by Ben Gamari at 2021-03-29T18:49:36-04:00 Merge commit '36418c4f70d7d2b179a77925b3ad5caedb08c9b5' into HEAD - - - - - 1444f700 by Ben Gamari at 2021-03-31T09:18:39-04:00 Merge pull request haskell/haddock#1370 from adinapoli/wip/adinapoli-diag-reason-severity Rename pprError to mkParserErr - - - - - d3087b79 by Ben Gamari at 2021-03-31T11:34:17-04:00 Merge commit 'd8d8024ad6796549a8d3b5512dabf3288d14e30f' into ghc-head - - - - - 170b79e9 by Ben Gamari at 2021-03-31T12:24:56-04:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - db0d6bae by Ben Gamari at 2021-04-10T09:34:35-04:00 Bump GHC version to 9.3 - - - - - a9f2c421 by Alan Zimmerman at 2021-04-19T18:26:46-04:00 Update for EPA changes in GHC (cherry picked from commit cafb48118f7c111020663776845897e225607b41) - - - - - 1ee4b7c7 by Sylvain Henry at 2021-05-11T10:00:06+02:00 Removal of HsVersions.h (#1388) * Update for EPA changes in GHC * Account for HsVersions.h removal Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 79e819e9 by Hécate Moonlight at 2021-05-11T10:14:47+02:00 Revert "Removal of HsVersions.h (#1388)" This reverts commit 72118896464f94d81f10c52f5d9261efcacc57a6. - - - - - 3dbd3f8b by Alan Zimmerman at 2021-05-11T10:15:17+02:00 Update for EPA changes in GHC - - - - - 2ce80c17 by Sylvain Henry at 2021-05-11T10:15:19+02:00 Account for HsVersions.h removal - - - - - 00e4c918 by Christiaan Baaij at 2021-05-13T08:21:56+02:00 Add Haddock support for the OPAQUE pragma (#1380) - - - - - 8f9049b2 by Hécate Moonlight at 2021-05-13T08:40:22+02:00 fixup! Use GHC 9.2 in CI runner - - - - - 27ddec38 by Alan Zimmerman at 2021-05-13T22:51:20+01:00 EPA: match changes from GHC T19834 - - - - - f8a1d714 by Felix Yan at 2021-05-14T17:10:04+02:00 Allow hspec 2.8 (#1389) All tests are passing. - - - - - df44453b by Divam Narula at 2021-05-20T15:42:42+02:00 Update ref, the variables got renamed. (#1391) This is due to ghc/ghc!5555 which caused a change in ModDetails in case of NoBackend. Now the initModDetails is used to recreate the ModDetails from interface and in-memory ModDetails is not used. - - - - - e46bfc87 by Alan Zimmerman at 2021-05-20T19:05:09+01:00 Remove Maybe from HsQualTy Match changes in GHC for haskell/haddock#19845 - - - - - 79bd7b62 by Shayne Fletcher at 2021-05-22T08:20:39+10:00 FieldOcc: rename extFieldOcc to foExt - - - - - 6ed68c74 by Ben Gamari at 2021-05-21T22:29:30-04:00 Merge commit '3b6a8774bdb543dad59b2618458b07feab8a55e9' into ghc-head - - - - - f9a02d34 by Alfredo Di Napoli at 2021-05-24T13:53:00+02:00 New Parser diagnostics interface - - - - - 392807d0 by Ben Gamari at 2021-05-24T09:57:40-04:00 Merge pull request haskell/haddock#1394 from adinapoli/wip/adinapoli-align-ps-messages Align Haddock to use the new Parser diagnostics interface - - - - - 33023cd8 by Ben Gamari at 2021-05-24T11:19:16-04:00 Revert "Add Haddock support for the OPAQUE pragma (#1380)" This reverts commit a1337c599ef7720b0482a25c55f11794112496dc. The GHC patch associated with this change is not yet ready to be merged. - - - - - 8c005af7 by Ben Simms at 2021-05-28T07:56:20+02:00 CI configuration for ghc-head (#1395) - - - - - 1e947612 by Hécate Moonlight at 2021-05-28T12:27:35+02:00 Use GHC 9.2 in CI runner (#1378) - - - - - e6fa10ab by CGenie at 2021-05-31T09:02:13+02:00 Add page about common errors (#1396) * Update index.rst Common errors page * Create common-errors.rst * Update common-errors.rst * Use GHC 9.2 in CI runner (#1378) * [haddock-api] remove .hspec-failures Co-authored-by: Hécate Moonlight <Kleidukos at users.noreply.github.com> - - - - - abc72a8d by Sylvain Henry at 2021-06-01T10:02:06+02:00 Adapt Haddock to Logger and Parser changes (#1399) - - - - - 91373656 by Zubin Duggal at 2021-06-01T20:45:10+02:00 Update haddockHypSrc tests since we now compute slighly more type info (#1397) - - - - - ed712822 by Marcin Szamotulski at 2021-06-02T08:54:33+02:00 Added myself to contributors - - - - - 49fdbcb7 by Marcin Szamotulski at 2021-06-02T08:57:24+02:00 Document multi component support - - - - - 9ddc8d7d by Hécate Moonlight at 2021-06-02T09:35:55+02:00 Merge pull request haskell/haddock#1379 from coot/coot/document-multi-component-support Document multi component support - - - - - 585b5c5e by Ben Simms at 2021-06-02T19:46:54+02:00 Update CONTRIBUTING.md (#1402) - - - - - 1df4a605 by Ben Simms at 2021-06-02T19:47:14+02:00 Update CONTRIBUTING.md (#1403) - - - - - 58ea43d2 by sheaf at 2021-06-02T22:09:06+02:00 Update Haddock Bug873 to account for renaming - - - - - c5d0ab23 by Vladislav Zavialov at 2021-06-10T13:35:42+03:00 HsToken in FunTy, RecConGADT - - - - - 1ae2f40c by Hécate Moonlight at 2021-06-11T11:19:09+02:00 Update the CI badges - - - - - 6fdc4de2 by Sylvain Henry at 2021-06-28T19:21:17+02:00 Fix mkParserOpts (#1411) - - - - - 18201670 by Alfredo Di Napoli at 2021-07-05T07:55:12+02:00 Rename getErrorMessages Lexer import This commit renames the Lexer import in `Hyperlinker.Parser` from `getErrorMessages` to `getPsErrorMessages` to eliminate the ambiguity with the `getErrorMessages` function defined in `GHC.Types.Error`. - - - - - 23173ca3 by Ben Gamari at 2021-07-07T11:31:44-04:00 Merge pull request haskell/haddock#1413 from adinapoli/wip/adinapoli-issue-19920 Rename getErrorMessages Lexer import - - - - - b3dc4ed8 by Alan Zimmerman at 2021-07-28T22:30:59+01:00 EPA: match changes from GHC T19834 (cherry picked from commit 2fec1b44e0ee7e263286709aa528b4ecb99ac6c2) - - - - - 5f177278 by Ben Gamari at 2021-08-06T01:17:37-04:00 Merge commit '2a966c8ca37' into HEAD - - - - - cdd81d08 by Marcin Szamotulski at 2021-08-08T17:19:06+02:00 coot/multiple packages (ghc-9.2) (#1418) - - - - - be0d71f1 by Marcin Szamotulski at 2021-08-16T08:46:03+02:00 coot/multiple package (ghc-head) (#1419) * FromJSON class Aeson style FromJSON class with Parsec based json parser. * doc-index.json file for multiple packages When creating haddock summary page for multiple packages render doc-index.json file using contents of all found 'doc-index.json' files. * Render doc-index.json When rendering html, render doc-index.json file independently of maybe_index_url option. doc-index.json file is useful now even if maybe_index_url is not `Nothing`. * base url option New `Flag_BaseURL` which configures from where static files are loaded (--base-url). If given and not equal "." static files are not coppied, as this indicates that they are not read from the the directory where we'd copy them. The default value is ".". - - - - - 3b09dbdf by Hécate Moonlight at 2021-10-07T23:26:03+02:00 Update GHC 9.2 to latest pre-release in CI - - - - - 7ac55417 by Zubin Duggal at 2021-10-11T12:10:19+02:00 Enable Haddock tests in GHC windows CI (#1428) * testsuite: strip windows line endings for haddock * hyperlinker: Work around double escaping (#19236) * deterministic SCC - - - - - 1cb81f25 by Andrew Lelechenko at 2021-10-12T15:23:19+02:00 haddock-library does not depend on bytestring or transformers (#1426) - - - - - a890b9aa by sheaf at 2021-10-15T22:19:42+02:00 update haddockHypsrcTest for GHC MR !6705 (#1430) - - - - - 42a55c6c by Sylvain Henry at 2021-10-15T22:20:10+02:00 Fix after PkgQual refactoring (#1429) - - - - - 91659238 by Alan Zimmerman at 2021-10-28T18:57:10+01:00 Update for changes in GHC for branch wip/az/no-srcspan-anno-instances - - - - - acf23e60 by Vladislav Zavialov at 2021-11-05T02:09:47+03:00 Do not use forall as an identifier See GHC ticket haskell/haddock#20609 - - - - - c565db0e by Krzysztof Gogolewski at 2021-11-27T02:42:35+01:00 Update after NoExtCon -> DataConCantHappen rename - - - - - b5f55590 by Artem Pelenitsyn at 2021-11-27T11:14:17+01:00 fix CI for 9.2 (#1436) - - - - - 25cd621e by Matthew Pickering at 2021-12-02T11:46:54+00:00 Update html-test for Data.List revert - - - - - 1d5ff85f by malteneuss at 2021-12-15T07:56:55+01:00 Add hint about inline link issue (#1444) - - - - - 791fde81 by Sylvain Henry at 2021-12-16T09:29:51+01:00 Bump ghc-head (#1445) * Update after NoExtCon -> DataConCantHappen rename * Update html-test for Data.List revert * Fix for new Plugins datatype Co-authored-by: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 44236317 by Sylvain Henry at 2021-12-17T09:39:00+01:00 Fix for new Plugins datatype - - - - - 80ada0fa by Hécate Moonlight at 2021-12-17T17:28:48+01:00 Remove ghc-head workflow (#1446) Contributions of GHC glue code are now done on the GHC gitlab, not in the GitHub repo anymore. - - - - - 49e171cd by Matthew Pickering at 2021-12-28T09:47:09+00:00 Remove use of ExtendedModSummary - - - - - 0e91b5ea by askeblad at 2022-01-04T09:18:35+01:00 update URLs - - - - - 9f13c212 by Hécate Moonlight at 2022-02-25T10:19:46+01:00 Fix solver for GHC 9.2 - - - - - 386751a1 by Meng Weng Wong at 2022-02-25T19:19:11+01:00 IDoc link has bitrotted; replaced with web.archive.org cache. (#1454) - - - - - d877cbe6 by Hécate Moonlight at 2022-02-25T19:21:58+01:00 Fix haddock user guide (#1456) - - - - - cc47f036 by Andrew Lelechenko at 2022-03-04T17:29:36+01:00 Allow text-2.0 in haddock-library (#1459) - - - - - 7b3685a3 by malteneuss at 2022-03-07T19:27:24+01:00 Add multi-line style hint to style section (#1460) - - - - - c51088b8 by John Ericson at 2022-03-11T16:46:26+01:00 Fix CollectPass instance to match TTG refactor Companion to GHC !7614 (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7614) - - - - - b882195b by Vladislav Zavialov at 2022-03-14T20:32:30+01:00 Link to (~) - - - - - 877349b8 by Christiaan Baaij at 2022-03-16T09:20:43+01:00 Add Haddock support for the OPAQUE pragma - - - - - 0ea22721 by askeblad at 2022-03-16T09:44:27+01:00 typos (#1464) - - - - - a6d13da1 by Matthew Pickering at 2022-03-22T13:41:17+00:00 Minimum changes needed for compilation with hi-haddock With hi-haddock, of course there is a much large refactoring of haddock which could be achieved but that is left for a future patch which can implemented at any time independently of GHC. - - - - - e7ac9129 by Matthew Pickering at 2022-03-22T21:17:50+00:00 Update test output - - - - - 6d916214 by Matthew Pickering at 2022-03-24T15:06:26+00:00 Merge branch 'wip/opaque_pragma' into 'ghc-head' Add Haddock support for the OPAQUE pragma See merge request ghc/haddock!2 - - - - - 42208183 by Steve Hart at 2022-03-25T20:43:50+01:00 Fix CI (#1467) * CI: Reinstall GHC with docs CI tests were failing because the GHC preinstalled to the CI environment does not include documentation, which is required for running the Haddock tests. This commit causes the CI workflow to reinstall GHC with docs so that tests can succeed. - - - - - 9676fd79 by Steve Hart at 2022-03-25T21:33:34+01:00 Make links in Synopsis functional again (#1458) Commit e41c1cbe9f0476997eac7b4a3f17cbc6b2262faf added a call to e.preventDefault() when handling click events that reach a toggle element. This prevents the browser from following hyperlinks within the Synopsis section when they are clicked by a user. This commit restores functioning hyperlinks within the Synopsis section by removing the call to e.preventDefault(), as it does not appear to be necessary, and removing it increases the flexibility of the details-helper code. - - - - - d1edd637 by sheaf at 2022-04-01T12:02:02+02:00 Keep track of promotion ticks in HsOpTy Keeping track of promotion ticks in HsOpTy allows us to properly pretty-print promoted constructors such as lists. - - - - - 9dcb2dfc by Jakob Brünker at 2022-04-01T15:46:22+00:00 Add support for \cases See merge request ghc/ghc!7873 - - - - - b0412ee5 by askeblad at 2022-04-06T17:47:57+02:00 spelling errors (#1471) - - - - - 6b18829b by Vladislav Zavialov at 2022-04-06T18:53:58+02:00 Rename [] to List - - - - - 2d046691 by Vladislav Zavialov at 2022-04-07T20:25:54+03:00 HsToken ConDeclGADT con_dcolon - - - - - 90b43da4 by Steve Hart at 2022-04-12T13:29:46+02:00 Parse Markdown links at beginning of line within a paragraph (#1470) * Catch Markdown links at beginning of line within paragraph Per Issue haskell/haddock#774, Markdown links were being parsed as ordinary text when they occurred at the beginning of a line other than the first line of the paragraph. This occurred because the parser was not interpreting a left square bracket as a special character that could delimit special markup. A space character was considered a special character, so, if a space occurred at the beginning of the new line, then the parser would interpret the space by itself and then continue parsing, thereby catching the Markdown link. '\n' was not treated as a special character, so the parser did not catch a Markdown link that may have followed. Note that this will allow for Markdown links that are not surrounded by spaces. For example, the following text includes a Markdown link that will be parsed: Hello, world[label](url) This is consistent with how the parser handles other types of markup. * Remove obsolete documentation hint Commit 6b9aeafddf20efc65d3725c16e3fc43a20aac343 should eliminate the need for the workaround suggested in the documentation. - - - - - 5b08312d by Hécate Moonlight at 2022-04-12T13:36:38+02:00 Force ghc-9.2 in the cabal.project - - - - - 0d0ea349 by dependabot[bot] at 2022-04-12T13:57:41+02:00 Bump path-parse from 1.0.5 to 1.0.7 in /haddock-api/resources/html (#1469) Bumps [path-parse](https://github.com/jbgutierrez/path-parse) from 1.0.5 to 1.0.7. - [Release notes](https://github.com/jbgutierrez/path-parse/releases) - [Commits](https://github.com/jbgutierrez/path-parse/commits/v1.0.7) --- updated-dependencies: - dependency-name: path-parse dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 2b9fc65e by dependabot[bot] at 2022-04-12T13:57:54+02:00 Bump copy-props from 2.0.4 to 2.0.5 in /haddock-api/resources/html (#1468) Bumps [copy-props](https://github.com/gulpjs/copy-props) from 2.0.4 to 2.0.5. - [Release notes](https://github.com/gulpjs/copy-props/releases) - [Changelog](https://github.com/gulpjs/copy-props/blob/master/CHANGELOG.md) - [Commits](https://github.com/gulpjs/copy-props/compare/2.0.4...2.0.5) --- updated-dependencies: - dependency-name: copy-props dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - ea98a6fb by Ben Gamari at 2022-04-23T22:54:37-04:00 Update for GHC 9.4 - - - - - 9e11864f by Ben Gamari at 2022-04-25T16:24:31-04:00 Merge remote-tracking branch 'upstream/ghc-9.2' into ghc-head - - - - - f83cc506 by Ben Gamari at 2022-04-25T17:00:25-04:00 Bump ghc version to 9.5 - - - - - e01c2e7d by Ben Gamari at 2022-04-28T16:19:04-04:00 Revert "Bump ghc-head (#1445)" This reverts commit b29a78ef6926101338f62e84f456dac8659dc9d2. This should not have been merged. - - - - - a2b5ee8c by Ben Gamari at 2022-04-28T16:19:24-04:00 Merge commit '2627a86c' into ghc-head - - - - - 0c6fe4f9 by Ben Gamari at 2022-04-29T10:05:54-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-9.4 - - - - - b6e5cb0a by Ben Gamari at 2022-04-29T11:46:06-04:00 Revert "HsToken ConDeclGADT con_dcolon" This reverts commit 24208496649a02d5f87373052c430ea4a97842c5. - - - - - 15a62888 by Ben Gamari at 2022-04-29T15:12:55-04:00 Bump base upper bound - - - - - 165b9031 by Ben Gamari at 2022-04-29T23:58:38-04:00 Update test output - - - - - e0c3e5da by Phil de Joux at 2022-05-02T14:46:38+02:00 Add hlint action .hlint.yaml with ignores & CPP. (#1475) - - - - - ead1158d by Raphael Das Gupta at 2022-05-02T14:46:48+02:00 fix grammar in docs: "can the" → "can be" (#1477) - - - - - cff97944 by Ben Gamari at 2022-05-02T18:38:56-04:00 Allow base-4.17 - - - - - e4ecb201 by Phil de Joux at 2022-05-03T13:14:55+02:00 Remove unused imports that GHC warned about. (#1480) - - - - - 222890b1 by Phil de Joux at 2022-05-03T13:15:46+02:00 Follow hlint suggestion to remove redundant bang. (#1479) - - - - - 058b671f by Phil de Joux at 2022-05-03T13:34:04+02:00 Follow hlint, remove language pragmas in libs. (#1478) - - - - - 0a645049 by Ben Simms at 2022-05-03T14:19:24+02:00 Keep track of ordered list indexes and render them (#1407) * Keep track of ordered list indexes and render them * Rename some identifiers to clarify - - - - - f0433304 by Norman Ramsey at 2022-05-04T15:13:34-04:00 update for changes in GHC API - - - - - 3740cf71 by Emily Martins at 2022-05-06T18:23:48+02:00 Add link to the readthedocs in cabal description to show on hackage. (cherry picked from commit 52e2d40d47295c02d3181aac0c53028e730f1e3b) - - - - - 5d754f1e by Hécate Moonlight at 2022-05-06T18:44:57+02:00 remove Bug873 - - - - - 968fc267 by Hécate Moonlight at 2022-05-06T18:48:28+02:00 Ignore "Use second" HLint suggestion. It increases laziness. - - - - - 02d14e97 by Jade Lovelace at 2022-05-07T17:42:08+02:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` - - - - - b22b87ed by Artem Pelenitsyn at 2022-05-08T16:19:47+02:00 fix parsing trailing quotes in backticked identifiers (#1408) (#1483) - - - - - 80ae107b by Alex Biehl at 2022-05-08T16:37:16+02:00 Fix "Defined by not used" error (cherry picked from commit 6e02a620a26c3a44f98675dd1b93b08070c36c0a) - - - - - 4c838e84 by Hécate Moonlight at 2022-05-08T16:37:16+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - fc9827b4 by Hécate Moonlight at 2022-05-08T16:40:40+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - b153b555 by Xia Li-yao at 2022-05-20T17:52:42+02:00 Hide synopsis from search when hidden (#1486) Fix haskell/haddock#1451 - - - - - f3e38b85 by Marcin Szamotulski at 2022-05-21T23:32:31+02:00 Allow to hide interfaces when rendering multiple components (#1487) This is useful when one wishes to `--gen-contents` when rendering multiple components, but one does not want to render all modules. This is in particular useful when adding base package. - - - - - f942863b by Marcin Szamotulski at 2022-05-24T08:29:59+02:00 Check if doc-index.json exists before reading it (#1488) - - - - - 31e92982 by Marcin Szamotulski at 2022-05-25T16:22:13+02:00 Version bump 2.26.1 (#1489) * Version bump 2.26.1 We extended format accepted by `--read-interface` option, which requires updating the minor version. * Update documentation of --read-interface option - - - - - 7cc873e0 by sheaf at 2022-05-25T16:42:31+02:00 Updated HaddockHypsrcTest output for record update changes (MR !7981) - - - - - cd196942 by Marcin Szamotulski at 2022-05-25T20:28:47+02:00 Use visibility to decide which interfaces are included in quickjump (#1490) This is also consistent with how html index is build. See haskell/cabal#7669 for rationale behind this decision. - - - - - 00c713c5 by Hécate Moonlight at 2022-05-26T17:09:15+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 2f3039f1 by Hécate Moonlight at 2022-05-26T17:10:59+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 63a5650c by romes at 2022-05-31T12:43:22+01:00 TTG: Match new GHC AST - - - - - dd7d1617 by romes at 2022-06-02T16:11:00+01:00 Update for IE changes in !8228 - - - - - c23aaab7 by cydparser at 2022-06-06T08:48:14+02:00 Fix and improve CI (#1495) * Pin GHC version before creating the freeze file * Use newest action versions * Improve caching * Avoid unnecessarily reinstalling GHC * Use GHC 9.2.2 for CI Co-authored-by: Cyd Wise <cwise at tripshot.com> - - - - - c156fa77 by Hécate Moonlight at 2022-06-06T11:59:35+02:00 Add Mergify configuration (#1496) - - - - - 2dba4188 by Hécate Moonlight at 2022-06-06T16:12:50+02:00 Bump haddock's version in cabal file to 2.26.1 (#1497) - - - - - d7d4b8b9 by Marcin Szamotulski at 2022-06-07T06:09:40+00:00 Render module tree per package in the content page (#1492) * Render module tree per package in the content page When rendering content page for multiple packages it is useful to split the module tree per package. Package names in this patch are inferred from haddock's interface file names. * Write PackageInfo into interface file To keep interface file format backward compatible, instead of using `Binary` instance for `InterfaceFile` we introduce functions to serialise and deserialise, which depends on the interface file version. - - - - - 77765665 by Mike Pilgrem at 2022-06-12T21:57:19+01:00 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - b0e079b0 by mergify[bot] at 2022-06-13T11:49:37+00:00 Merge pull request haskell/haddock#1108 from mpilgrem/fix783 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - 6c0292b1 by Hécate Moonlight at 2022-06-21T17:21:08+02:00 Update the contribution guide - - - - - e413b9fa by dependabot[bot] at 2022-06-21T23:38:19+02:00 Bump shell-quote from 1.6.1 to 1.7.3 in /haddock-api/resources/html (#1500) Bumps [shell-quote](https://github.com/substack/node-shell-quote) from 1.6.1 to 1.7.3. - [Release notes](https://github.com/substack/node-shell-quote/releases) - [Changelog](https://github.com/substack/node-shell-quote/blob/master/CHANGELOG.md) - [Commits](https://github.com/substack/node-shell-quote/compare/1.6.1...1.7.3) --- updated-dependencies: - dependency-name: shell-quote dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 29d0ef70 by romes at 2022-07-06T11:29:39+02:00 TTG: AST Updates for !8308 - - - - - 1bae7c87 by Alan Zimmerman at 2022-07-06T22:50:43+01:00 Match GHC changes for T21805 This brings in a newtype for FieldLabelString - - - - - 6fe8b988 by Phil de Joux at 2022-07-16T20:54:26+00:00 Bump hlint version to 3.4.1, the version with counts. (#1503) Redo the counts available with the --default option. - - - - - 48fb43af by Phil de Joux at 2022-07-19T09:32:55+02:00 Follow hlint suggestion: unused LANGUAGE pragma. (#1504) * Follow hlint suggestion: unused LANGUAGE pragma. * Ignore within modules to pass linting and pass tests. - - - - - c1cf1fa7 by Phil de Joux at 2022-07-24T13:45:59+02:00 Follow hlint suggestion: redundant $. (#1505) * Follow hlint suggestion: redundant $. * Remove $ and surplus blank lines in Operators. - - - - - 74777eb2 by Jade Lovelace at 2022-07-29T11:02:41+01:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` (cherry picked from commit ab53ccf089ea703b767581ac14be0f6c78a7678a) - - - - - faa4cfcf by Hécate Moonlight at 2022-07-29T20:31:20+02:00 Merge pull request haskell/haddock#1516 from duog/9-4-backport-fix-hyperlinks Backport 9-4: Fix hyperlinks to external items and modules (#1482) - - - - - 5d2450f3 by Ben Gamari at 2022-08-05T17:41:15-04:00 Merge remote-tracking branch 'origin/ghc-9.4' - - - - - 63954f73 by Ben Gamari at 2022-08-05T19:08:36-04:00 Clean up build and testsuite for GHC 9.4 - - - - - d4568cb8 by Hécate Moonlight at 2022-08-05T19:10:49-04:00 Bump the versions - - - - - 505583a4 by Ben Gamari at 2022-08-06T13:58:27-04:00 Merge pull request haskell/haddock#1518 from bgamari/wip/ghc-9.4-merge Merge GHC 9.4 into `main` - - - - - 5706f6a4 by Ben Gamari at 2022-08-06T22:57:21-04:00 html-test: Testsuite changes for GHC 9.4.1 - - - - - 5f2a45a2 by Ben Gamari at 2022-08-15T14:33:05-04:00 doc: Fix a few minor ReST issues Sphinx was complaining about too-short title underlines. - - - - - 220e6410 by Ben Gamari at 2022-08-15T14:41:24-04:00 Merge branch 'main' into ghc-head - - - - - fbeb1b02 by Ben Gamari at 2022-08-15T14:45:16-04:00 Updates for GHC 9.5 - - - - - eee562eb by Vladislav Zavialov at 2022-08-15T14:46:13-04:00 HsToken ConDeclGADT con_dcolon - - - - - c5f073db by Ben Gamari at 2022-08-15T16:55:35-04:00 Updates for GHC 9.5 - - - - - 3f7ab242 by Vladislav Zavialov at 2022-08-15T16:55:35-04:00 HsToken ConDeclGADT con_dcolon - - - - - a18e473d by Ben Gamari at 2022-08-16T08:35:19-04:00 Merge branch 'wip/ghc-head-bump' into ghc-head - - - - - af0ff3a4 by M Farkas-Dyck at 2022-09-15T21:16:05+00:00 Disuse `mapLoc`. - - - - - a748fc38 by Matthew Farkas-Dyck at 2022-09-17T10:44:18+00:00 Scrub partiality about `NewOrData`. - - - - - 2758fb6c by John Ericson at 2022-09-18T03:27:37+02:00 Test output changed because of change to `base` Spooky, but I guess that is intended? - - - - - a7eec128 by Torsten Schmits at 2022-09-21T11:06:55+02:00 update tests for the move of tuples to GHC.Tuple.Prim - - - - - 461e7b9d by Ross Paterson at 2022-09-24T22:01:25+00:00 match implementation of GHC proposal haskell/haddock#106 (Define Kinds Without Promotion) - - - - - f7fd77ef by sheaf at 2022-10-17T14:53:01+02:00 Update Haddock for GHC MR !8563 (configuration of diagnostics) - - - - - 3d3e85ab by Vladislav Zavialov at 2022-10-22T23:04:06+03:00 Class layout info - - - - - cbde4cb0 by Simon Peyton Jones at 2022-10-25T23:19:18+01:00 Adapt to Constraint-vs-Type See haskell/haddock#21623 and !8750 - - - - - 7108ba96 by Tom Smeding at 2022-11-01T22:33:23+01:00 Remove outdated footnote about module re-exports The footnote is invalid with GHC 9.2.4 (and possibly earlier): the described behaviour in the main text works fine. - - - - - 206c6bc7 by Hécate Moonlight at 2022-11-01T23:00:46+01:00 Merge pull request haskell/haddock#1534 from tomsmeding/patch-1 - - - - - a57b4c4b by Andrew Lelechenko at 2022-11-21T00:39:52+00:00 Support mtl-2.3 - - - - - e9d62453 by Simon Peyton Jones at 2022-11-25T13:49:12+01:00 Track small API change in TyCon.hs - - - - - eb1c73f7 by Ben Gamari at 2022-12-07T08:46:21-05:00 Update for GhC 9.6 - - - - - 063268dd by Ben Gamari at 2022-12-07T11:26:32-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 4ca722fe by Ben Gamari at 2022-12-08T14:43:26-05:00 Bump bounds to accomodate base-4.18 - - - - - 340b7511 by Vladislav Zavialov at 2022-12-10T12:31:28+00:00 HsToken in HsAppKindTy - - - - - 946226ec by Ben Gamari at 2022-12-13T20:12:56-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - fd8faa66 by Ben Gamari at 2022-12-22T13:44:28-05:00 Bump GHC version to 9.7 - - - - - 2958aa9c by Ben Gamari at 2022-12-22T14:49:16-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 9e0fefd8 by Andrei Borzenkov at 2023-01-30T14:02:04+04:00 Rename () to Unit, Rename (,,...,,) to Tuple<n> - - - - - eb3968b5 by Ben Gamari at 2023-03-10T02:32:43-05:00 Bump versions for ghc-9.6 release - - - - - 4aeead36 by Adam Gundry at 2023-03-23T13:53:47+01:00 Adapt to warning categories changes - - - - - 642d8d60 by sheaf at 2023-03-29T13:35:56+02:00 Adapt to record field refactor This commit adapts to the changes in GHC MR !8686, which overhauls the treatment of record fields in the renamer, adding separate record field namespaces and entirely removing the GreName datatype. - - - - - ac8d4333 by doyougnu at 2023-03-29T11:11:44-04:00 Update UniqMap API - - - - - 7866fc86 by Ben Orchard at 2023-04-20T11:29:33+02:00 update classify with new tokens - - - - - ffcdd683 by Finley McIlwaine at 2023-04-24T09:36:18-06:00 Remove index-state - - - - - 05b70982 by Finley McIlwaine at 2023-04-26T08:16:31-06:00 `renameInterface` space leak fixes - Change logic for accumulation of names for which link warnings will be generated - Change handling of `--ignore-link-symbol` to allow qualified and unqualified names. Added to CHANGES.md - Some formatting changes and comments here and there - - - - - e5697d7c by Finley McIlwaine at 2023-04-27T18:46:36-06:00 Messy things - ghc-debug dependency and instrumentation - cabal.project custom with-compiler - hie.yaml files - traces and such - - - - - 0b8ef80b by Finley McIlwaine at 2023-05-02T18:08:52-06:00 Stop retaining GRE closures GRE closures should never be necessary to Haddock, so we never want to keep them on the heap. Despite that, they are retained by a lot of the data structures that Haddock makes use of. - Attempt to fix that situation by adding strictness to various computations and pruning the `ifaceInstances` field of `Interface` to a much thinner data type. - Removes the `ifaceFamInstances` field, as it was never used. - Move some of the attach instances types (e.g. `SimpleType`) to the types module - - - - - 8bda991b by Finley McIlwaine at 2023-05-08T16:07:51-06:00 Memory usage fixes - Refactor `ifaceDeclMap` to drastically reduce memory footprint. We no longer store all declarations associated with a given name, since we only cared to determine if the only declaration associated with a name was a value declaration. Change the `DeclMap` type to better reflect this. - Drop pre-renaming export items after the renaming step. Since the Hoogle backend used the pre-renamed export items, this isn't trivial. We now generate Hoogle output for exported declarations during the renaming step (if Hoogle output /should/ be generated), and store that with the renamed export item. - Slightly refactor Hoogle backend to handle the above change and allow for early generation of Hoogle output. - Remove the `ifaceRnDocMap` and `ifaceRnArgMap` fields of the `Interface` type, as they were never used. - Remove some unnecessary strictness - Remove a lot of dead code from `Syb` module - - - - - 1611ac0c by Finley McIlwaine at 2023-05-09T11:51:57-06:00 Unify ErrMsgM and IfM - Delete ErrMsgM, stop accumulating warnings in a writer - Make IfM a state monad, print warnings directly to stdout, move IfM type into types module - Drop ErrMsg = String synonym - Unset IORefs from plugin after they are read, preventing unnecessary retention of interfaces - - - - - 42d696ab by Finley McIlwaine at 2023-05-11T15:52:07-06:00 Thunk leak fixes The strictness introduced in this commit was motivated by observing thunk leaks in the eventlog2html output. - Refactor attach instances list comprehension to avoid large intermediate thunks - Refactor some HTML backend list comprehensions to avoid large intermediate thunks - Avoid thunks accumulating in documentation types or documentation parser - A lot of orphan NFData instances to allow us to force documentation values - - - - - 68561cf6 by Finley McIlwaine at 2023-05-11T17:02:10-06:00 Remove GHC debug dep - - - - - 10519e3d by Finley McIlwaine at 2023-05-15T12:40:48-06:00 Force HIE file path Removes a potential retainer of `ModSummary`s - - - - - 1e4a6ec6 by Finley McIlwaine at 2023-05-15T14:20:34-06:00 Re-add index-state, with-compiler, delete hie.yamls - - - - - a2363fe9 by Hécate Moonlight at 2023-05-15T22:45:16+02:00 Merge pull request haskell/haddock#1594 from FinleyMcIlwaine/finley/ghc-9.6-mem-fixes Reduce memory usage - - - - - e8a78383 by Finley McIlwaine at 2023-05-17T12:19:16-06:00 Merge branch ghc-9.6 into ghc-head - - - - - 22e25581 by Finley McIlwaine at 2023-05-17T12:20:23-06:00 Merge branch 'ghc-head' of gitlab.haskell.org:ghc/haddock into ghc-head - - - - - 41bbf0df by Bartłomiej Cieślar at 2023-05-24T08:57:58+02:00 changes to the WarningTxt cases Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - c686ba9b by Hécate Moonlight at 2023-06-01T14:03:02-06:00 Port the remains of Hi-Haddock - - - - - 9d8a85fd by Hécate Moonlight at 2023-06-01T14:03:06-06:00 Stdout for tests - - - - - 36331d07 by Finley McIlwaine at 2023-06-01T14:06:02-06:00 Formatting, organize imports - - - - - a06059b1 by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix empty context confusion in Convert module - - - - - 379346ae by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix associated type families in Hoogle output - - - - - fc6ea7ed by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix test refs Accept several changes in Hoogle tests: Pretty printing logic no longer prints the `(Proxy (Proxy (...))` chain in Bug806 with parentheses. Since this test was only meant to verify that line breaks do not occur, accept the change. `tyThingToLHsDecl` is called for class and data declarations, which ends up "synifying" the type variables and giving unlifted types kind signatures. As a result, type variables of kind `Type -> Type` are now printed with kind signatures in Hoogle output. This could be changed by manually drop kind signatures from class variables in the Hoogle backend if the behavior is deemed unacceptable. Sometimes subordinate declarations are exported separate from their parent declarations (e.g. record selectors). In this case, a type signature is cobbled together for the export item in `extractDecl`. Since this type signature is very manually constructed, it may lack kind signatures of decls constructed from `tyThingToLHsDecl`. An example of this is the `type-sigs` Hoogle test. Change `*` to `Type` in Hoogle test refs. I don't think this will break Hoogle behavior, since it appears to not consider type signatures in search. I have not fully verified this. - - - - - e14b7e58 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix LaTeX backend test refs Changes to GHC pretty printing code have resulted in some differences to Haddock's LaTeX output. - Type variables are printed explicitly quantified in the LinearTypes test - Wildcard types in type family equations are now printed numbered, e.g. _1 _2, in the TypeFamilies3 test - Combined signatures in DefaultSignatures test are now documented as separate signatures - - - - - 41b5b296 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and test source updates - Stop using kind `*` in html test sources - Add TypeOperators where necessary to avoid warnings and future errors - Rename some test modules to match their module names - - - - - c640e2a2 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix missing deprecation warnings on record fields `lookupOccEnv` was used to resolve `OccNames` with warnings attached, but it doesn't look in the record field namespace. Thus, if a record field had a warning attached, it would not resolve and the warning map would not include it. This commit fixes by using `lookupOccEnv_WithFields` instead. - - - - - fad0c462 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and some comments - - - - - 751fd023 by Finley McIlwaine at 2023-06-01T14:11:41-06:00 Accept HTML test diffs All diffs now boil down to the expected differences resulting from declarations being reified from TyThings in hi-haddock. Surface syntax now has much less control over the syntax used in the documentation. - - - - - d835c845 by Finley McIlwaine at 2023-06-01T14:11:45-06:00 Adapt to new load' type - - - - - dcf776c4 by Finley McIlwaine at 2023-06-01T14:13:13-06:00 Update mkWarningMap and moduleWarning - - - - - 8e8432fd by Finley McIlwaine at 2023-06-01T14:28:54-06:00 Revert load' changes - - - - - aeb2982c by Finley McIlwaine at 2023-06-01T14:40:24-06:00 Accept change to Instances test in html-test Link to Data.Tuple instead of GHC.Tuple.Prim - - - - - 8adfdbac by Finley McIlwaine at 2023-06-01T15:53:17-06:00 Reset ghc dep to ^>= 9.6 - - - - - 2b1ce93d by Finley McIlwaine at 2023-06-06T07:50:04-06:00 Update CHANGES.md, user guide, recomp avoidance * Add --trace-args flag for tracing arguments received to standard output * Avoid recompiling due to changes in optimization flags * Update users guide and changes.md - - - - - f3da6676 by Finley McIlwaine at 2023-06-06T14:12:56-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - bf36c467 by Matthew Pickering at 2023-06-07T10:16:09+01:00 Revert back to e16e20d592a6f5d9ed1af17b77fafd6495242345 Neither of these MRs are ready to land yet which causes issues with other MRs which are ready to land and need haddock changes. - - - - - 421510a9 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 atSign has no unicode variant Prior to this change, atSign was defined as follows: atSign unicode = text (if unicode then "@" else "@") Yes, this is the same symbol '\64' and not your font playing tricks on you. Now we define: atSign = char '@' Both the LaTeX and the Xhtml backend are updated accordingly. - - - - - 3785c276 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 LaTeX: fix printing of type variable bindings Consider this type signature: kindOf :: forall {k} (a :: k). Proxy a -> Proxy k Prior to this fix, the LaTeX backend rendered it like this: kindOf :: forall k a. Proxy a -> Proxy k Now we preserve explicit specificity and kind annotations. - - - - - 0febf3a8 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 Add support for invisible binders in type declarations - - - - - 13e33bb3 by Finley McIlwaine at 2023-06-08T07:51:59-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - 3e5340ce by Finley McIlwaine at 2023-06-08T07:54:27-06:00 Add note about stubdir to recompilation docs - - - - - db7e84dc by Finley at 2023-06-08T08:11:03-06:00 Merge pull request haskell/haddock#1597 from haskell/finley/hi-haddock-9.6 hi-haddock for ghc 9.6 - - - - - 4e085d17 by Finley McIlwaine at 2023-06-14T13:41:06-06:00 Replace SYB traversals - - - - - 7b39aec5 by Finley McIlwaine at 2023-06-14T14:20:17-06:00 Test ref accepts, remove unused HaddockClsInst - - - - - df9c2090 by Finley McIlwaine at 2023-06-15T08:02:51-06:00 Use batchMsg for progress reporting during load With hi-haddock as is, there is an awkward silence during the load operation. This commit makes haddock use the default `batchMsg` Messager for progress reporting, and makes the default GHC verbosity level 1, so the user can see what GHC is doing. - - - - - f23679a8 by Hécate Moonlight at 2023-06-15T20:31:53+02:00 Merge pull request haskell/haddock#1600 from haskell/finley/hi-haddock-optim - - - - - a7982192 by Finley McIlwaine at 2023-06-15T15:02:16-06:00 hi-haddock squashed - - - - - c34f0c8d by Finley McIlwaine at 2023-06-15T16:22:03-06:00 Merge remote-tracking branch 'origin/ghc-9.6' into finley/hi-haddock-squashed - - - - - 40452797 by Bartłomiej Cieślar at 2023-06-16T12:26:04+02:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - e58673bf by Ben Gamari at 2023-06-16T09:33:35-04:00 Bump GHC version to 9.8 - - - - - 74bdf972 by Ben Gamari at 2023-06-16T09:36:18-04:00 Merge commit 'fcaaad06770a26d35d4aafd65772dedadf17669c' into ghc-head - - - - - 418ee3dc by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Remove NFData SourceText, IfaceWarnings updates The NFData SourceText instance is now available in GHC Handle mod_iface mi_warns now being IfaceWarnings - - - - - 62f31380 by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Accept Instances.hs test output Due to ghc!10469. - - - - - a8f2fc0e by Ben Gamari at 2023-06-20T15:48:08-04:00 Test fixes for "Fix associated data family doc structure items" Associated data families were being given their own export DocStructureItems, which resulted in them being documented separately from their classes in haddocks. This commit fixes it. - - - - - cb1ac33e by Bartłomiej Cieślar at 2023-06-21T12:56:02-04:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - 9933e10b by Ben Gamari at 2023-06-21T12:56:02-04:00 Bump GHC version to 9.8 - - - - - fe8c18b6 by Ben Gamari at 2023-06-21T15:36:29-04:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - c61a0d5b by Ben Gamari at 2023-06-21T16:10:51-04:00 Bump GHC version to 9.9 - - - - - 0c2a756e by sheaf at 2023-07-07T13:45:12+02:00 Avoid incomplete record update in Haddock Hoogle This commit avoids running into an incomplete record update warning in the Hoogle backend of Haddock. This was only noticed now, because incomplete record updates were broken in GHC 9.6. Now that they are fixed, we have to avoid running into them! - - - - - f9b952a7 by Ben Gamari at 2023-07-21T11:58:05-04:00 Bump base bound to <4.20 For GHC 9.8. - - - - - 1b27e151 by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Check for puns (see ghc#23368) - - - - - 457341fd by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Remove fake exports for (~), List, and Tuple<n> The old reasoning no longer applies, nowadays those names can be mentioned in export lists. - - - - - bf3dcddf by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Fix pretty-printing of Solo and MkSolo - - - - - 495b2241 by Matthew Pickering at 2023-09-01T13:02:07+02:00 Fix issue with duplicate reexported definitions (T23616) When a class method was reexported, it's default methods were also showing up in the generated html page. The simplest and most non-invasive fix is to not look for the default method if we are just exporting the class method.. because the backends are just showing default methods when the whole class is exported. In general it would be worthwhile to rewrite this bit of code I think as the logic and what gets included is split over `lookupDocs` and `availExportDecl` it would be clearer to combine the two. The result of lookupDocs is always just passed to availExportDecl so it seems simpler and more obvious to just write the function directly. - - - - - 6551824d by Finley McIlwaine at 2023-09-05T13:06:57-07:00 Remove fake export of `FUN` from Prelude This prevents `data FUN` from being shown at the top of the Prelude docs. Fixes \#23920 on GHC. - - - - - 9ab5a448 by Alan Zimmerman at 2023-09-08T18:26:53+01:00 Match changes in wip/az/T23885-unicode-funtycon - - - - - 4d08364e by Alan Zimmerman at 2023-10-31T19:46:45+00:00 EPA: match changes in GHC - EPA: Comments in AnchorOperation - EPA: Remove EpaEofComment - - - - - e7da0d25 by Alan Zimmerman at 2023-11-05T11:20:31+00:00 EPA: match changes in GHC, l2l cleanup - - - - - 4ceac14d by Alan Zimmerman at 2023-11-11T15:16:41+00:00 EPA: Replace Anchor with EpaLocation Match GHC - - - - - 94fb8d47 by Alan Zimmerman at 2023-11-29T18:10:26+00:00 Match GHC, No comments in EpaDelta for comments - - - - - 32d208e1 by Vladislav Zavialov at 2023-12-12T20:41:36+03:00 EPA: Match changes to LHsToken removal - - - - - eebdd316 by Apoorv Ingle at 2024-01-23T13:49:12+00:00 Changes for haskell/haddock#18324 - - - - - ae856a82 by Matthew Pickering at 2024-02-05T12:22:39+00:00 ghc-internals fallout - - - - - f8429266 by Jade at 2024-02-08T14:56:50+01:00 Adjust test for ghc MR !10993 - - - - - 6d1e2386 by Alan Zimmerman at 2024-02-13T22:00:28+03:00 EPA: Match changes to HsParTy and HsFunTy - - - - - 9c588f19 by Fendor at 2024-02-14T11:05:36+01:00 Adapt to GHC giving better Name's for linking - - - - - 778e1db3 by Andrei Borzenkov at 2024-02-16T16:12:07+03:00 Namespace specifiers for fixity signatures - - - - - d04f384f by Ben Gamari at 2024-02-21T04:59:23-05:00 hadrian/bindist: Ensure that phony rules are marked as such Otherwise make may not run the rule if file with the same name as the rule happens to exist. - - - - - efcbad2d by Ben Gamari at 2024-02-21T04:59:23-05:00 hadrian: Generate HSC2HS_EXTRAS variable in bindist installation We must generate the hsc2hs wrapper at bindist installation time since it must contain `--lflag` and `--cflag` arguments which depend upon the installation path. The solution here is to substitute these variables in the configure script (see mk/hsc2hs.in). This is then copied over a dummy wrapper in the install rules. Fixes #24050. - - - - - c540559c by Matthew Pickering at 2024-02-21T04:59:23-05:00 ci: Show --info for installed compiler - - - - - ab9281a2 by Matthew Pickering at 2024-02-21T04:59:23-05:00 configure: Correctly set --target flag for linker opts Previously we were trying to use the FP_CC_SUPPORTS_TARGET with 4 arguments, when it only takes 3 arguments. Instead we need to use the `FP_PROG_CC_LINKER_TARGET` function in order to set the linker flags. Actually fixes #24414 - - - - - 9460d504 by Rodrigo Mesquita at 2024-02-21T04:59:59-05:00 configure: Do not override existing linker flags in FP_LD_NO_FIXUP_CHAINS - - - - - 77629e76 by Andrei Borzenkov at 2024-02-21T05:00:35-05:00 Namespacing for fixity signatures (#14032) Namespace specifiers were added to syntax of fixity signatures: - sigdecl ::= infix prec ops | ... + sigdecl ::= infix prec namespace_spec ops | ... To preserve namespace during renaming MiniFixityEnv type now has separate FastStringEnv fields for names that should be on the term level and for name that should be on the type level. makeMiniFixityEnv function was changed to fill MiniFixityEnv in the right way: - signatures without namespace specifiers fill both fields - signatures with 'data' specifier fill data field only - signatures with 'type' specifier fill type field only Was added helper function lookupMiniFixityEnv that takes care about looking for a name in an appropriate namespace. Updates haddock submodule. Metric Decrease: MultiLayerModulesTH_OneShot - - - - - 84357d11 by Teo Camarasu at 2024-02-21T05:01:11-05:00 rts: only collect live words in nonmoving census when non-concurrent This avoids segfaults when the mutator modifies closures as we examine them. Resolves #24393 - - - - - 9ca56dd3 by Ian-Woo Kim at 2024-02-21T05:01:53-05:00 mutex wrap in refreshProfilingCCSs - - - - - 1387966a by Cheng Shao at 2024-02-21T05:02:32-05:00 rts: remove unused HAVE_C11_ATOMICS macro This commit removes the unused HAVE_C11_ATOMICS macro. We used to have a few places that have fallback paths when HAVE_C11_ATOMICS is not defined, but that is completely redundant, since the FP_CC_SUPPORTS__ATOMICS configure check will fail when the C compiler doesn't support C11 style atomics. There are also many places (e.g. in unreg backend, SMP.h, library cbits, etc) where we unconditionally use C11 style atomics anyway which work in even CentOS 7 (gcc 4.8), the oldest distro we test in our CI, so there's no value in keeping HAVE_C11_ATOMICS. - - - - - 0f40d68f by Andreas Klebinger at 2024-02-21T05:03:09-05:00 RTS: -Ds - make sure incall is non-zero before dereferencing it. Fixes #24445 - - - - - e5886de5 by Ben Gamari at 2024-02-21T05:03:44-05:00 rts/AdjustorPool: Use ExecPage abstraction This is just a minor cleanup I found while reviewing the implementation. - - - - - 826c5b47 by Torsten Schmits at 2024-02-21T13:17:05+01:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 09941666 by Adam Gundry at 2024-02-21T13:53:12+00:00 Define GHC2024 language edition (#24320) See https://github.com/ghc-proposals/ghc-proposals/pull/613. Also fixes #24343 and improves the documentation of language editions. Co-authored-by: Joachim Breitner <mail at joachim-breitner.de> - - - - - 2cff14d5 by Ben Gamari at 2024-02-22T09:35:56-05:00 Bump bounds - - - - - f49376b3 by Ben Gamari at 2024-02-22T09:35:56-05:00 Allow `@since` annotations in export lists Here we extend Haddock to admit `@since` annotations in export lists. These can be attached to most export list items (although not subordinate lists). These annotations supercede the declaration's `@since` annotation in produced Haddocks. - - - - - b5aa93df by Ben Gamari at 2024-02-22T12:09:06-05:00 Allow package-qualified @since declarations - - - - - 8f5957f2 by Ben Gamari at 2024-02-22T13:55:19-05:00 Documentation changes from ghc-internal restructuring Previously many declarations (e.g. `Int`) were declared to have a "home" in `Prelude`. However, now Haddock instead chooses to put these in more specific homes (e.g. `Data.Int`). Given that the "home" decision is driven by heuristics and in general these changes seem quite reasonable I am accepting them: * `Int` moved from `Prelude` to `Data.Int` * `(~)` moved from `Prelude` to `Data.Type.Equality` * `Type` moved from `GHC.Types` to `Data.Kind` * `Maybe` moved from `Prelude` to `Data.Maybe` * `Bool` moved from `Prelude` to `Data.Bool` * `Ordering` moved from `Prelude` to `Data.Ord` As well, more identifiers are now hyperlinked; it's not immediately clear *why*, but it is an improvement nevertheless. - - - - - ec33fec3 by Ben Gamari at 2024-02-22T20:36:24-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 5121a4ed by Ben Gamari at 2024-02-23T06:40:55-05:00 Allow docstrings after exports Here we extend the parser and AST to preserve docstrings following export items. We then extend Haddock to parse `@since` annotations in such docstrings, allowing changes in export structure to be properly documented. Bumps haddock submodule. - - - - - 30cfd251 by Torsten Schmits at 2024-02-24T13:00:42-05:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 0eb2265d by Hécate Moonlight at 2024-02-24T16:02:16-05:00 Improve the synopsis and description of base - - - - - 2e36f5d2 by Jade at 2024-02-24T16:02:51-05:00 Error Messages: Properly align cyclic module error Fixes: #24476 - - - - - bbfb051c by Ben Gamari at 2024-02-24T19:10:23-05:00 Allow docstrings after exports Here we extend the parser and AST to preserve docstrings following export items. We then extend Haddock to parse `@since` annotations in such docstrings, allowing changes in export structure to be properly documented. - - - - - d8d6ad8c by Ben Gamari at 2024-02-24T19:10:23-05:00 ghc-internal: Move modules into GHC.Internal.* namespace Bumps haddock submodule due to testsuite output changes. - - - - - a82af7cd by Ben Gamari at 2024-02-24T19:10:23-05:00 ghc-internal: Rewrite `@since ` to `@since base-` These will be incrementally moved to the export sites in `base` where possible. - - - - - ca3836e1 by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Migrate Haddock `not-home` pragmas from `ghc-internal` This ensures that we do not use `base` stub modules as declarations' homes when not appropriate. - - - - - c8cf3e26 by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Partially freeze exports of GHC.Base Sadly there are still a few module reexports. However, at least we have decoupled from the exports of `GHC.Internal.Base`. - - - - - 272573c6 by Ben Gamari at 2024-02-24T19:10:23-05:00 Move Haddock named chunks - - - - - 2d8a881d by Ben Gamari at 2024-02-24T19:10:23-05:00 Drop GHC.Internal.Data.Int - - - - - 55c4c385 by Ben Gamari at 2024-02-24T19:10:23-05:00 compiler: Fix mention to `GHC....` modules in wasm desugaring Really, these references should be via known-key names anyways. I have fixed the proximate issue here but have opened #24472 to track the additional needed refactoring. - - - - - 64150911 by Ben Gamari at 2024-02-24T19:10:23-05:00 Accept performance shifts from ghc-internal restructure As expected, Haddock now does more work. Less expected is that some other testcases actually get faster, presumably due to less interface file loading. As well, the size_hello_artifact test regressed a bit when debug information is enabled due to debug information for the new stub symbols. Metric Decrease: T12227 T13056 Metric Increase: haddock.Cabal haddock.base MultiLayerModulesTH_OneShot size_hello_artifact - - - - - 317a915b by Ben Gamari at 2024-02-24T19:10:23-05:00 Expose GHC.Wasm.Prim from ghc-experimental Previously this was only exposed from `ghc-internal` which violates our agreement that users shall not rely on things exposed from that package. Fixes #24479. - - - - - 3bbd2bf2 by Ben Gamari at 2024-02-24T19:10:23-05:00 compiler/tc: Small optimisation of evCallStack Don't lookupIds unless we actually need them. - - - - - 3e5c9e3c by Ben Gamari at 2024-02-24T19:10:23-05:00 compiler/tc: Use toException instead of SomeException - - - - - 125714a6 by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Factor out errorBelch This was useful when debugging - - - - - 3d6aae7c by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Clean up imports of GHC.Stack.CloneStack - - - - - 6900306e by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Move PrimMVar to GHC.Internal.MVar - - - - - 28f8a148 by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Move prettyCallStack to GHC.Internal.Stack - - - - - 4892de47 by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Explicit dependency to workaround #24436 Currently `ghc -M` fails to account for `.hs-boot` files correctly, leading to issues with cross-package one-shot builds failing. This currently manifests in `GHC.Exception` due to the boot file for `GHC.Internal.Stack`. Work around this by adding an explicit `import`, ensuring that `GHC.Internal.Stack` is built before `GHC.Exception`. See #24436. - - - - - 294c93a5 by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Use displayException in top-level exception handler Happily this also allows us to eliminate a special case for Deadlock exceptions. Implements [CLC #198](https://github.com/haskell/core-libraries-committee/issues/198). - - - - - 732db81d by Ben Gamari at 2024-02-24T19:12:18-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - cf756a25 by Ben Gamari at 2024-02-24T22:11:53-05:00 rts: Fix symbol references in Wasm RTS - - - - - 4e4d47a0 by Jade at 2024-02-26T15:17:20-05:00 GHCi: Improve response to unloading, loading and reloading modules Fixes #13869 - - - - - f3de8a3c by Zubin Duggal at 2024-02-26T15:17:57-05:00 rel-eng/fetch-gitlab.py: Fix name of aarch64 alpine 3_18 release job - - - - - c71bfdff by Cheng Shao at 2024-02-26T15:18:35-05:00 hadrian/hie-bios: pass -j to hadrian This commit passes -j to hadrian in the hadrian/hie-bios scripts. When the user starts HLS in a fresh clone that has just been configured, it takes quite a while for hie-bios to pick up the ghc flags and start actual indexing, due to the fact that the hadrian build step defaulted to -j1, so -j speeds things up and improve HLS user experience in GHC. Also add -j flag to .ghcid to speed up ghcid, and sets the Windows build root to .hie-bios which also works and unifies with other platforms, the previous build root _hie-bios was missing from .gitignore anyway. - - - - - 50bfdb46 by Cheng Shao at 2024-02-26T15:18:35-05:00 ci: enable parallelism in hadrian/ghci scripts This commit enables parallelism when the hadrian/ghci scripts are called in CI. The time bottleneck is in the hadrian build step, but previously the build step wasn't parallelized. - - - - - 61a78231 by Felix Yan at 2024-02-26T15:19:14-05:00 m4: Correctly detect GCC version When calling as `cc`, GCC does not outputs lowercased "gcc" at least in 13.2.1 version here. ``` $ cc --version cc (GCC) 13.2.1 20230801 ... ``` This fails the check and outputs the confusing message: `configure: $CC is not gcc; assuming it's a reasonably new C compiler` This patch makes it check for upper-cased "GCC" too so that it works correctly: ``` checking version of gcc... 13.2.1 ``` - - - - - 001aa539 by Teo Camarasu at 2024-02-27T13:26:46-05:00 Fix formatting in whereFrom docstring Previously it used markdown syntax rather than Haddock syntax for code quotes - - - - - e8034d15 by Teo Camarasu at 2024-02-27T13:26:46-05:00 Move ClosureType type to ghc-internal - Use ClosureType for InfoProv.ipDesc. - Use ClosureType for CloneStack.closureType. - Now ghc-heap re-exports this type from ghc-internal. See the accompanying CLC proposal: https://github.com/haskell/core-libraries-committee/issues/210 Resolves #22600 - - - - - 3da0a551 by Matthew Craven at 2024-02-27T13:27:22-05:00 StgToJS: Simplify ExprInline constructor of ExprResult Its payload was used only for a small optimization in genAlts, avoiding a few assignments for programs of this form: case NormalDataCon arg1 arg2 of x { NormalDataCon x1 x2 -> ... ; } But when compiling with optimizations, this sort of code is generally eliminated by case-of-known-constructor in Core-to-Core. So it doesn't seem worth tracking and cleaning up again in StgToJS. - - - - - 61bc92cc by Cheng Shao at 2024-02-27T16:58:42-05:00 rts: add missing ccs_mutex guard to internal_dlopen See added comment for details. Closes #24423. - - - - - dd29d3b2 by doyougnu at 2024-02-27T16:59:23-05:00 cg: Remove GHC.Cmm.DataFlow.Collections In pursuit of #15560 and #17957 and generally removing redundancy. - - - - - d3a050d2 by Cheng Shao at 2024-02-27T17:00:00-05:00 utils: remove unused lndir from tree Ever since the removal of the make build system, the in tree lndir hasn't been actually built, so this patch removes it. - - - - - 86bf7010 by Ben Gamari at 2024-02-27T19:28:10-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 74b24a9b by Teo Camarasu at 2024-02-28T16:32:58+00:00 rts: avoid checking bdescr of value outside of Haskell heap In nonmovingTidyWeaks we want to check if the key of a weak pointer lives in the non-moving heap. We do this by checking the flags of the block the key lives in. But we need to be careful with values that live outside the Haskell heap, since they will lack a block descriptor and looking for one may lead to a segfault. In this case we should just accept that it isn't on the non-moving heap. Resolves #24492 - - - - - b4cae4ec by Simon Peyton Jones at 2024-02-29T02:10:08-05:00 In mkDataConRep, ensure the in-scope set is right A small change that fixes #24489 - - - - - 3836a110 by Cheng Shao at 2024-02-29T21:25:45-05:00 testsuite: fix T23540 fragility on 32-bit platforms T23540 is fragile on 32-bit platforms. The root cause is usage of `getEvidenceTreesAtPoint`, which internally relies on `Name`'s `Ord` instance, which is indeterministic. The solution is adding a deterministic `Ord` instance for `EvidenceInfo` and sorting the evidence trees before pretty printing. Fixes #24449. - - - - - 960c8d47 by Teo Camarasu at 2024-02-29T21:26:20-05:00 Reduce AtomicModifyIORef increment count This test leads to a lot of contention when N>2 and becomes very slow. Let's reduce the amount of work we do to compensate. Resolves #24490 - - - - - 2e46c8ad by Matthew Pickering at 2024-03-01T05:48:06-05:00 hadrian: Improve parallelism in binary-dist-dir rule I noticed that the "docs" target was needed after the libraries and executables were built. We can improve the parallelism by needing everything at once so that documentation can be built immediately after a library is built for example. - - - - - cb6c11fe by Matthew Pickering at 2024-03-01T05:48:07-05:00 ci: Bump windows and freebsd boot compilers to 9.6.4 We have previously bumped the docker images to use 9.6.4, but neglected to bump the windows images until now. - - - - - 30f06996 by Matthew Pickering at 2024-03-01T05:48:07-05:00 ci: darwin: Update to 9.6.2 for boot compiler 9.6.4 is currently broken due to #24050 Also update to use LLVM-15 rather than LLVM-11, which is out of date. - - - - - d9d69e12 by Matthew Pickering at 2024-03-01T05:48:07-05:00 Bump minimum bootstrap version to 9.6 - - - - - 67ace1c5 by Matthew Pickering at 2024-03-01T05:48:07-05:00 ci: Enable more documentation building Here we enable documentation building on 1. Darwin: The sphinx toolchain was already installed so we enable html and manpages. 2. Rocky8: Full documentation (toolchain already installed) 3. Alpine: Full documetnation (toolchain already installed) 4. Windows: HTML and manpages (toolchain already installed) Fixes #24465 - - - - - 39583c39 by Matthew Pickering at 2024-03-01T05:48:42-05:00 ci: Bump ci-images to allow updated aarch64-alpine image with llvm15 and clang15 - - - - - d91d00fc by Torsten Schmits at 2024-03-01T15:01:50-05:00 Introduce ListTuplePuns extension This implements Proposal 0475, introducing the `ListTuplePuns` extension which is enabled by default. Disabling this extension makes it invalid to refer to list, tuple and sum type constructors by using built-in syntax like `[Int]`, `(Int, Int)`, `(# Int#, Int# #)` or `(# Int | Int #)`. Instead, this syntax exclusively denotes data constructors for use with `DataKinds`. The conventional way of referring to these data constructors by prefixing them with a single quote (`'(Int, Int)`) is now a parser error. Tuple declarations have been moved to `GHC.Tuple.Prim` and the `Solo` data constructor has been renamed to `MkSolo` (in a previous commit). Unboxed tuples and sums now have real source declarations in `GHC.Types`. Unit and solo types for tuples are now called `Unit`, `Unit#`, `Solo` and `Solo#`. Constraint tuples now have the unambiguous type constructors `CTuple<n>` as well as `CUnit` and `CSolo`, defined in `GHC.Classes` like before. A new parser construct has been added for the unboxed sum data constructor declarations. The type families `Tuple`, `Sum#` etc. that were intended to provide nicer syntax have been omitted from this change set due to inference problems, to be implemented at a later time. See the MR discussion for more info. Updates the submodule utils/haddock. Updates the cabal submodule due to new language extension. Metric Increase: haddock.base Metric Decrease: MultiLayerModulesTH_OneShot size_hello_artifact Proposal document: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0475-tuple-syntax.rst Merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/8820 Tracking ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/21294 - - - - - bbdb6286 by Sylvain Henry at 2024-03-01T15:01:50-05:00 JS linker: filter unboxed tuples - - - - - dec6d8d3 by Arnaud Spiwack at 2024-03-01T15:02:30-05:00 Improve error messages coming from non-linear patterns This enriched the `CtOrigin` for non-linear patterns to include data of the pattern that created the constraint (which can be quite useful if it occurs nested in a pattern) as well as an explanation why the pattern is non-restricted in (at least in some cases). - - - - - 6612388e by Arnaud Spiwack at 2024-03-01T15:02:30-05:00 Adjust documentation of linear lets according to committee decision - - - - - 1c064ef1 by Cheng Shao at 2024-03-02T17:11:19-05:00 compiler: start deprecating cmmToRawCmmHook cmmToRawCmmHook was added 4 years ago in d561c8f6244f8280a2483e8753c38e39d34c1f01. Its only user is the Asterius project, which has been archived and deprecated in favor of the ghc wasm backend. This patch starts deprecating cmmToRawCmmHook by placing a DEPRECATED pragma, and actual removal shall happen in a future GHC major release if no issue to oppose the deprecation has been raised in the meantime. - - - - - 9b74845f by Andrew Lelechenko at 2024-03-02T17:11:55-05:00 Data.List.NonEmpty.unzip: use WARNING with category instead of DEPRECATED CLC proposal: https://github.com/haskell/core-libraries-committee/issues/258 - - - - - 61bb5ff6 by Finley McIlwaine at 2024-03-04T09:01:40-08:00 add -fprof-late-overloaded and -fprof-late-overloaded-calls * Refactor late cost centre insertion for extensibility * Add two more late cost centre insertion methods that add SCCs to overloaded top level bindings and call sites with dictionary arguments. * Some tests for the basic functionality of the new insertion methods Resolves: #24500 - - - - - 82ccb801 by Andreas Klebinger at 2024-03-04T19:59:14-05:00 x86-ncg: Fix fma codegen when arguments are globals Fix a bug in the x86 ncg where results would be wrong when the desired output register and one of the input registers were the same global. Also adds a tiny optimization to make use of the memory addressing support when convenient. Fixes #24496 - - - - - 18ad1077 by Matthew Pickering at 2024-03-05T14:22:31-05:00 rel_eng: Update hackage docs upload scripts This adds the upload of ghc-internal and ghc-experimental to our scripts which upload packages to hackage. - - - - - bf47c9ba by Matthew Pickering at 2024-03-05T14:22:31-05:00 docs: Remove stray module comment from GHC.Profiling.Eras - - - - - 37d9b340 by Matthew Pickering at 2024-03-05T14:22:31-05:00 Fix ghc-internal cabal file The file mentioned some artifacts relating to the base library. I have renamed these to the new ghc-internal variants. - - - - - 23f2a478 by Matthew Pickering at 2024-03-05T14:22:31-05:00 Fix haddock source links and hyperlinked source There were a few issues with the hackage links: 1. We were using the package id rather than the package name for the package links. This is fixed by now allowing the template to mention %pkg% or %pkgid% and substituing both appropiatly. 2. The `--haddock-base-url` flag is renamed to `--haddock-for-hackage` as the new base link works on a local or remote hackage server. 3. The "src" path including too much stuff, so cross-package source links were broken as the template was getting double expanded. Fixes #24086 - - - - - 2fa336a9 by Ben Gamari at 2024-03-05T14:23:07-05:00 filepath: Bump submodule to 1.5.2.0 - - - - - 31217944 by Ben Gamari at 2024-03-05T14:23:07-05:00 os-string: Bump submodule to 2.0.2 - - - - - 4074a3f2 by Matthew Pickering at 2024-03-05T21:44:35-05:00 base: Reflect new era profiling RTS flags in GHC.RTS.Flags * -he profiling mode * -he profiling selector * --automatic-era-increment CLC proposal #254 - https://github.com/haskell/core-libraries-committee/issues/254 - - - - - a8c0e31b by Sylvain Henry at 2024-03-05T21:45:14-05:00 JS: faster implementation for some numeric primitives (#23597) Use faster implementations for the following primitives in the JS backend by not using JavaScript's BigInt: - plusInt64 - minusInt64 - minusWord64 - timesWord64 - timesInt64 Co-authored-by: Josh Meredith <joshmeredith2008 at gmail.com> - - - - - 21e3f325 by Cheng Shao at 2024-03-05T21:45:52-05:00 rts: add -xr option to control two step allocator reserved space size This patch adds a -xr RTS option to control the size of virtual memory address space reserved by the two step allocator on a 64-bit platform, see added documentation for explanation. Closes #24498. - - - - - dedcf102 by Cheng Shao at 2024-03-06T13:39:04-05:00 rts: expose HeapAlloc.h as public header This commit exposes HeapAlloc.h as a public header. The intention is to expose HEAP_ALLOCED/HEAP_ALLOCED_GC, so they can be used in assertions in other public headers, and they may also be useful for user code. - - - - - d19441d7 by Cheng Shao at 2024-03-06T13:39:04-05:00 rts: assert pointer is indeed heap allocated in Bdescr() This commit adds an assertion to Bdescr() to assert the pointer is indeed heap allocated. This is useful to rule out RTS bugs that attempt to access non-existent block descriptor of a static closure, #24492 being one such example. - - - - - 9a656a04 by Ben Gamari at 2024-03-06T13:39:39-05:00 ghc-experimental: Add dummy dependencies to work around #23942 This is a temporary measure to improve CI reliability until a proper solution is developed. Works around #23942. - - - - - 1e84b924 by Simon Peyton Jones at 2024-03-06T13:39:39-05:00 Three compile perf improvements with deep nesting These were changes are all triggered by #24471. 1. Make GHC.Core.Opt.SetLevels.lvlMFE behave better when there are many free variables. See Note [Large free-variable sets]. 2. Make GHC.Core.Opt.Arity.floatIn a bit lazier in its Cost argument. This benefits the common case where the ArityType turns out to be nullary. See Note [Care with nested expressions] 3. Make GHC.CoreToStg.Prep.cpeArg behave for deeply-nested expressions. See Note [Eta expansion of arguments in CorePrep] wrinkle (EA2). Compile times go down by up to 4.5%, and much more in artificial cases. (Geo mean of compiler/perf changes is -0.4%.) Metric Decrease: CoOpt_Read T10421 T12425 - - - - - c4b13113 by Hécate Moonlight at 2024-03-06T13:40:17-05:00 Use "module" instead of "library" when applicable in base haddocks - - - - - 9cd9efb4 by Vladislav Zavialov at 2024-03-07T13:01:54+03:00 Rephrase error message to say "visible arguments" (#24318) * Main change: make the error message generated by mkFunTysMsg more accurate by changing "value arguments" to "visible arguments". * Refactor: define a new type synonym VisArity and use it instead of Arity in a few places. It might be the case that there other places in the compiler that should talk about visible arguments rather than value arguments, but I haven't tried to find them all, focusing only on the error message reported in the ticket. - - - - - 4b6e76b5 by Patrick at 2024-03-07T22:09:30+08:00 fix haskell/haddock#24493, with module name introduced in hieAst The accompanies haddoc PR with GHC PR https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12153 Two things have been done: 1. Link is introduced to every `X` in `module X where`, since we introduce the module name to HieAst, 2. `{-# LINE 4 "hypsrc-test/src/PositionPragmas.hs" #-}` is added before the `module PositionPragmas where` in ` hypsrc-test/ref/src/PositionPragmas.html `.It ensures only a single hieAst for file `hypsrc-test/src/PositionPragmas.hs` is generated. - - - - - d523a6a7 by Ben Gamari at 2024-03-07T19:40:45-05:00 Bump array submodule - - - - - 7e55003c by Ben Gamari at 2024-03-07T19:40:45-05:00 Bump stm submodule - - - - - 32d337ef by Ben Gamari at 2024-03-07T19:40:45-05:00 Introduce exception context Here we introduce the `ExceptionContext` type and `ExceptionAnnotation` class, allowing dynamically-typed user-defined annotations to be attached to exceptions. CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/199 GHC Proposal: https://github.com/ghc-proposals/ghc-proposals/pull/330 - - - - - 39f3d922 by Ben Gamari at 2024-03-07T19:40:46-05:00 testsuite/interface-stability: Update documentation - - - - - fdea7ada by Ben Gamari at 2024-03-07T19:40:46-05:00 ghc-internal: comment formatting - - - - - 4fba42ef by Ben Gamari at 2024-03-07T19:40:46-05:00 compiler: Default and warn ExceptionContext constraints - - - - - 3886a205 by Ben Gamari at 2024-03-07T19:40:46-05:00 base: Introduce exception backtraces Here we introduce the `Backtraces` type and associated machinery for attaching these via `ExceptionContext`. These has a few compile-time regressions (`T15703` and `T9872d`) due to the additional dependencies in the exception machinery. As well, there is a surprisingly large regression in the `size_hello_artifact` test. This appears to be due to various `Integer` and `Read` bits now being reachable at link-time. I believe it should be possible to avoid this but I have accepted the change for now to get the feature merged. CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/199 GHC Proposal: https://github.com/ghc-proposals/ghc-proposals/pull/330 Metric Increase: T15703 T9872d size_hello_artifact - - - - - 18c5409f by Ben Gamari at 2024-03-07T19:40:46-05:00 users guide: Release notes for exception backtrace work - - - - - f849c5fc by Ben Gamari at 2024-03-07T19:40:46-05:00 compiler: Don't show ExceptionContext of GhcExceptions Most GhcExceptions are user-facing errors and therefore the ExceptionContext has little value. Ideally we would enable it in the DEBUG compiler but I am leaving this for future work. - - - - - dc646e6f by Sylvain Henry at 2024-03-07T19:40:46-05:00 Disable T9930fail for the JS target (cf #19174) - - - - - bfc09760 by Alan Zimmerman at 2024-03-07T19:41:22-05:00 Update showAstData to honour blanking of AnnParen Also tweak rendering of SrcSpan to remove extra blank line. - - - - - 50454a29 by Ben Gamari at 2024-03-08T03:32:42-05:00 ghc-internal: Eliminate GHC.Internal.Data.Kind This was simply reexporting things from `ghc-prim`. Instead reexport these directly from `Data.Kind`. Also add build ordering dependency to work around #23942. - - - - - 38a4b6ab by Ben Gamari at 2024-03-08T03:33:18-05:00 rts: Fix SET_HDR initialization of retainer set This fixes a regression in retainer set profiling introduced by b0293f78cb6acf2540389e22bdda420d0ab874da. Prior to that commit the heap traversal word would be initialized by `SET_HDR` using `LDV_RECORD_CREATE`. However, the commit added a `doingLDVProfiling` check in `LDV_RECORD_CREATE`, meaning that this initialization no longer happened. Given that this initialization was awkwardly indirectly anyways, I have fixed this by explicitly initializating the heap traversal word to `NULL` in `SET_PROF_HDR`. This is equivalent to the previous behavior, but much more direct. Fixes #24513. - - - - - 635abccc by Ben Gamari at 2024-03-08T17:09:06-05:00 Bump ghc version to 9.10 - - - - - 2859a637 by Ben Gamari at 2024-03-08T18:26:47-05:00 base: Use strerror_r instead of strerror As noted by #24344, `strerror` is not necessarily thread-safe. Thankfully, POSIX.1-2001 has long offered `strerror_r`, which is safe to use. Fixes #24344. CLC discussion: https://github.com/haskell/core-libraries-committee/issues/249 - - - - - 5b934048 by Ben Gamari at 2024-03-08T18:50:12-05:00 Bump base upper bound - - - - - b30d134e by Ben Gamari at 2024-03-08T18:50:44-05:00 Testsuite output update - - - - - edb9bf77 by Jade at 2024-03-09T03:39:38-05:00 Error messages: Improve Error messages for Data constructors in type signatures. This patch improves the error messages from invalid type signatures by trying to guess what the user did and suggesting an appropriate fix. Partially fixes: #17879 - - - - - cfb197e3 by Patrick at 2024-03-09T03:40:15-05:00 HieAst: add module name #24493 The main purpose of this is to tuck the module name `xxx` in `module xxx where` into the hieAst. It should fix #24493. The following have been done: 1. Renamed and update the `tcg_doc_hdr :: Maybe (LHsDoc GhcRn)` to `tcg_hdr_info :: (Maybe (LHsDoc GhcRn), Maybe (XRec GhcRn ModuleName))` To store the located module name information. 2. update the `RenamedSource` and `RenamedStuff` with extra `Maybe (XRec GhcRn ModuleName)` located module name information. 3. add test `testsuite/tests/hiefile/should_compile/T24493.hs` to ensure the module name is added and update several relevent tests. 4. accompanied submodule haddoc test update MR in https://gitlab.haskell.org/ghc/haddock/-/merge_requests/53 - - - - - 2341d81e by Vaibhav Sagar at 2024-03-09T03:40:54-05:00 GHC.Utils.Binary: fix a couple of typos - - - - - 5580e1bd by Ben Gamari at 2024-03-09T03:41:30-05:00 rts: Drop .wasm suffix from .prof file names This replicates the behavior on Windows, where `Hi.exe` will produce profiling output named `Hi.prof` instead of `Hi.exe.prof`. While in the area I also fixed the extension-stripping logic, which incorrectly rewrote `Hi.exefoo` to `Hi.foo`. Closes #24515. - - - - - 259495ee by Cheng Shao at 2024-03-09T03:41:30-05:00 testsuite: drop exe extension from .hp & .prof filenames See #24515 for details. - - - - - c477a8d2 by Ben Gamari at 2024-03-09T03:42:05-05:00 rts/linker: Enable GOT support on all platforms There is nothing platform-dependent about our GOT implementation and GOT support is needed by `T24171` on i386. - - - - - 2e592857 by Vladislav Zavialov at 2024-03-09T03:42:41-05:00 Drop outdated comment on TcRnIllformedTypePattern This should have been done in 0f0c53a501b but I missed it. - - - - - c554b4da by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/CloneStack: Bounds check array write - - - - - 15c590a5 by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/CloneStack: Don't expose helper functions in header - - - - - e831ce31 by Ben Gamari at 2024-03-09T09:39:20-05:00 base: Move internals of GHC.InfoProv into GHC.InfoProv.Types Such that we can add new helpers into GHC.InfoProv.Types without breakage. - - - - - 6948e24d by Ben Gamari at 2024-03-09T09:39:20-05:00 rts: Lazily decode IPE tables Previously we would eagerly allocate `InfoTableEnt`s for each info table registered in the info table provenance map. However, this costs considerable memory and initialization time. Instead we now lazily decode these tables. This allows us to use one-third the memory *and* opens the door to taking advantage of sharing opportunities within a module. This required considerable reworking since lookupIPE now must be passed its result buffer. - - - - - 9204a04e by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/IPE: Don't expose helper in header - - - - - 308926ff by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/IPE: Share module_name within a Node This allows us to shave a 64-bit word off of the packed IPE entry size. - - - - - bebdea05 by Ben Gamari at 2024-03-09T09:39:20-05:00 IPE: Expose unit ID in InfoTableProv Here we add the unit ID to the info table provenance structure. - - - - - 6519c9ad by Ben Gamari at 2024-03-09T09:39:35-05:00 rts: Refactor GHC.Stack.CloneStack.decode Don't allocate a Ptr constructor per frame. - - - - - ed0b69dc by Ben Gamari at 2024-03-09T09:39:35-05:00 base: Do not expose whereFrom# from GHC.Exts - - - - - 2b1faea9 by Vladislav Zavialov at 2024-03-09T17:38:21-05:00 docs: Update info on TypeAbstractions * Mention TypeAbstractions in 9.10.1-notes.rst * Set the status to "Experimental". * Add a "Since: GHC 9.x" comment to each section. - - - - - f8b88918 by Ben Gamari at 2024-03-09T21:21:46-05:00 ci-images: Bump Alpine image to bootstrap with 9.8.2 - - - - - 705e6927 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Mark T24171 as fragile due to #24512 I will fix this but not in time for 9.10.1-alpha1 - - - - - c74196e1 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Mark linker_unload_native as fragile In particular this fails on platforms without `dlinfo`. I plan to address this but not before 9.10.1-alpha1. - - - - - f4d87f7a by Ben Gamari at 2024-03-09T21:21:46-05:00 configure: Bump version to 9.10 - - - - - 88df9a5f by Ben Gamari at 2024-03-09T21:21:46-05:00 Bump transformers submodule to 0.6.1.1 - - - - - 8176d5e8 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Increase ulimit for T18623 1 MByte was just too tight and failed intermittently on some platforms (e.g. CentOS 7). Bumping the limit to 8 MByte should provide sufficient headroom. Fixes #23139. - - - - - c74b38a3 by Ben Gamari at 2024-03-09T21:21:46-05:00 base: Bump version to 4.20.0.0 - - - - - b2937fc3 by Ben Gamari at 2024-03-09T21:21:46-05:00 ghc-internal: Set initial version at 9.1001.0 This provides PVP compliance while maintaining a clear correspondence between GHC releases and `ghc-internal` versions. - - - - - 4ae7d868 by Ben Gamari at 2024-03-09T21:21:46-05:00 ghc-prim: Bump version to 0.11.0 - - - - - 50798dc6 by Ben Gamari at 2024-03-09T21:21:46-05:00 template-haskell: Bump version to 2.22.0.0 - - - - - 8564f976 by Ben Gamari at 2024-03-09T21:21:46-05:00 base-exports: Accommodate spurious whitespace changes in 32-bit output It appears that this was - - - - - 9d4f0e98 by Ben Gamari at 2024-03-09T21:21:46-05:00 users-guide: Move exception backtrace relnotes to 9.10 This was previously mistakenly added to the GHC 9.8 release notes. - - - - - 145eae60 by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/rel_eng: Fix name of Rocky8 artifact - - - - - 39c2a630 by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/rel_eng: Fix path of generate_jobs_metadata - - - - - aed034de by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/upload: Rework recompression The old `combine` approach was quite fragile due to use of filename globbing. Moreover, it didn't parallelize well. This refactoring makes the goal more obvious, parallelizes better, and is more robust. - - - - - 9bdf3586 by Ben Gamari at 2024-03-09T21:37:44-05:00 Merge branch 'ghc-9.10' into ghc-head - - - - - cec76981 by Ben Gamari at 2024-03-09T21:54:00-05:00 Bump GHC version to 9.11 - - - - - 4c59feb7 by Ben Gamari at 2024-03-09T22:15:01-05:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - dc207d06 by Ben Gamari at 2024-03-10T08:56:08-04:00 configure: Bump GHC version to 9.11 Bumps haddock submodule. - - - - - 8b2513e8 by Ben Gamari at 2024-03-11T01:20:03-04:00 rts/linker: Don't unload code when profiling is enabled The heap census may contain references (e.g. `Counter.identity`) to static data which must be available when the census is reported at the end of execution. Fixes #24512. - - - - - 7810b4c3 by Ben Gamari at 2024-03-11T01:20:03-04:00 rts/linker: Don't unload native objects when dlinfo isn't available To do so is unsafe as we have no way of identifying references to symbols provided by the object. Fixes #24513. Fixes #23993. - - - - - 0590764c by Ben Gamari at 2024-03-11T01:20:39-04:00 rel_eng/upload: Purge both $rel_name/ and $ver/ This is necessary for prereleases, where GHCup accesses the release via `$ver/` - - - - - b85a4631 by Brandon Chinn at 2024-03-12T19:25:56-04:00 Remove duplicate code normalising slashes - - - - - c91946f9 by Brandon Chinn at 2024-03-12T19:25:56-04:00 Simplify regexes with raw strings - - - - - 1a5f53c6 by Brandon Chinn at 2024-03-12T19:25:57-04:00 Don't normalize backslashes in characters - - - - - 7ea971d3 by Andrei Borzenkov at 2024-03-12T19:26:32-04:00 Fix compiler crash caused by implicit RHS quantification in type synonyms (#24470) - - - - - 39f3ac3e by Cheng Shao at 2024-03-12T19:27:11-04:00 Revert "compiler: make genSym use C-based atomic increment on non-JS 32-bit platforms" This reverts commit 615eb855416ce536e02ed935ecc5a6f25519ae16. It was originally intended to fix #24449, but it was merely sweeping the bug under the rug. 3836a110577b5c9343915fd96c1b2c64217e0082 has properly fixed the fragile test, and we no longer need the C version of genSym. Furthermore, the C implementation causes trouble when compiling with clang that targets i386 due to alignment warning and libatomic linking issue, so it makes sense to revert it. - - - - - e6bfb85c by Cheng Shao at 2024-03-12T19:27:11-04:00 compiler: fix out-of-bound memory access of genSym on 32-bit This commit fixes an unnoticed out-of-bound memory access of genSym on 32-bit. ghc_unique_inc is 32-bit sized/aligned on 32-bit platforms, but we mistakenly treat it as a Word64 pointer in genSym, and therefore will accidentally load 2 garbage higher bytes, or with a small but non-zero chance, overwrite something else in the data section depends on how the linker places the data segments. This regression was introduced in !11802 and fixed here. - - - - - 77171cd1 by Ben Orchard at 2024-03-14T09:00:40-04:00 Note mutability of array and address access primops Without an understanding of immutable vs. mutable memory, the index primop family have a potentially non-intuitive type signature: indexOffAddr :: Addr# -> Int# -> a readOffAddr :: Addr# -> Int# -> State# d -> (# State# d, a #) indexOffAddr# might seem like a free generality improvement, which it certainly is not! This change adds a brief note on mutability expectations for most index/read/write access primops. - - - - - 7da7f8f6 by Alan Zimmerman at 2024-03-14T09:01:15-04:00 EPA: Fix regression discarding comments in contexts Closes #24533 - - - - - 73be65ab by Fendor at 2024-03-19T01:42:53-04:00 Fix sharing of 'IfaceTyConInfo' during core to iface type translation During heap analysis, we noticed that during generation of 'mi_extra_decls' we have lots of duplicates for the instances: * `IfaceTyConInfo NotPromoted IfaceNormalTyCon` * `IfaceTyConInfo IsPromoted IfaceNormalTyCon` which should be shared instead of duplicated. This duplication increased the number of live bytes by around 200MB while loading the agda codebase into GHCi. These instances are created during `CoreToIface` translation, in particular `toIfaceTyCon`. The generated core looks like: toIfaceTyCon = \ tc_sjJw -> case $wtoIfaceTyCon tc_sjJw of { (# ww_sjJz, ww1_sjNL, ww2_sjNM #) -> IfaceTyCon ww_sjJz (IfaceTyConInfo ww1_sjNL ww2_sjNM) } whichs removes causes the sharing to work propery. Adding explicit sharing, with NOINLINE annotations, changes the core to: toIfaceTyCon = \ tc_sjJq -> case $wtoIfaceTyCon tc_sjJq of { (# ww_sjNB, ww1_sjNC #) -> IfaceTyCon ww_sjNB ww1_sjNC } which looks much more like sharing is happening. We confirmed via ghc-debug that all duplications were eliminated and the number of live bytes are noticeably reduced. - - - - - bd8209eb by Alan Zimmerman at 2024-03-19T01:43:28-04:00 EPA: Address more 9.10.1-alpha1 regressions from recent changes Closes #24533 Hopefully for good this time - - - - - 31bf85ee by Fendor at 2024-03-19T14:48:08-04:00 Escape multiple arguments in the settings file Uses responseFile syntax. The issue arises when GHC is installed on windows into a location that has a space, for example the user name is 'Fake User'. The $topdir will also contain a space, consequentially. When we resolve the top dir in the string `-I$topdir/mingw/include`, then `words` will turn this single argument into `-I/C/Users/Fake` and `User/.../mingw/include` which trips up the flag argument parser of various tools such as gcc or clang. We avoid this by escaping the $topdir before replacing it in `initSettngs`. Additionally, we allow to escape spaces and quotation marks for arguments in `settings` file. Add regression test case to count the number of options after variable expansion and argument escaping took place. Additionally, we check that escaped spaces and double quotation marks are correctly parsed. - - - - - f45f700e by Matthew Pickering at 2024-03-19T14:48:44-04:00 Read global package database from settings file Before this patch, the global package database was always assumed to be in libdir </> package.conf.d. This causes issues in GHC's build system because there are sometimes situations where the package database you need to use is not located in the same place as the settings file. * The stage1 compiler needs to use stage1 libraries, so we should set "Global Package DB" for the stage1 compiler to the stage1 package database. * Stage 2 cross compilers need to use stage2 libraries, so likewise, we should set the package database path to `_build/stage2/lib/` * The normal situation is where the stage2 compiler uses stage1 libraries. Then everything lines up. * When installing we have rearranged everything so that the settings file and package database line up properly, so then everything should continue to work as before. In this case we set the relative package db path to `package.conf.d`, so it resolves the same as before. * ghc-pkg needs to be modified as well to look in the settings file fo the package database rather than assuming the global package database location relative to the lib folder. * Cabal/cabal-install will work correctly because they query the global package database using `--print-global-package-db`. A reasonable question is why not generate the "right" settings files in the right places in GHC's build system. In order to do this you would need to engineer wrappers for all executables to point to a specific libdir. There are also situations where the same package db is used by two different compilers with two different settings files (think stage2 cross compiler and stage3 compiler). In short, this 10 line patch allows for some reasonable simplifications in Hadrian at very little cost to anything else. Fixes #24502 - - - - - 4c8f1794 by Matthew Pickering at 2024-03-19T14:48:44-04:00 hadrian: Remove stage1 testsuite wrappers logic Now instead of producing wrappers which pass the global package database argument to ghc and ghc-pkg, we write the location of the correct package database into the settings file so you can just use the intree compiler directly. - - - - - da0d8ba5 by Matthew Craven at 2024-03-19T14:49:20-04:00 Remove unused ghc-internal module "GHC.Internal.Constants" - - - - - b56d2761 by Matthew Craven at 2024-03-19T14:49:20-04:00 CorePrep: Rework lowering of BigNat# literals Don't use bigNatFromWord#, because that's terrible: * We shouldn't have to traverse a linked list at run-time to build a BigNat# literal. That's just silly! * The static List object we have to create is much larger than the actual BigNat#'s contents, bloating code size. * We have to read the corresponding interface file, which causes un-tracked implicit dependencies. (#23942) Instead, encode them into the appropriate platform-dependent sequence of bytes, and generate code that copies these bytes at run-time from an Addr# literal into a new ByteArray#. A ByteArray# literal would be the correct thing to generate, but these are not yet supported; see also #17747. Somewhat surprisingly, this change results in a slight reduction in compiler allocations, averaging around 0.5% on ghc's compiler performance tests, including when compiling programs that contain no bignum literals to begin with. The specific cause of this has not been investigated. Since this lowering no longer reads the interface file for GHC.Num.BigNat, the reasoning in Note [Depend on GHC.Num.Integer] is obsoleted. But the story of un-tracked built-in dependencies remains complex, and Note [Tracking dependencies on primitives] now exists to explain this complexity. Additionally, many empty imports have been modified to refer to this new note and comply with its guidance. Several empty imports necessary for other reasons have also been given brief explanations. Metric Decrease: MultiLayerModulesTH_OneShot - - - - - 349ea330 by Fendor at 2024-03-19T14:50:00-04:00 Eliminate thunk in 'IfaceTyCon' Heap analysis showed that `IfaceTyCon` retains a thunk to `IfaceTyConInfo`, defeating the sharing of the most common instances of `IfaceTyConInfo`. We make sure the indirection is removed by adding bang patterns to `IfaceTyCon`. Experimental results on the agda code base, where the `mi_extra_decls` were read from disk: Before this change, we observe around 8654045 instances of: `IfaceTyCon[Name,THUNK_1_0]` But these thunks almost exclusively point to a shared value! Forcing the thunk a little bit more, leads to `ghc-debug` reporting: `IfaceTyCon[Name:Name,IfaceTyConInfo]` and a noticeable reduction of live bytes (on agda ~10%). - - - - - 594bee0b by Krzysztof Gogolewski at 2024-03-19T14:50:36-04:00 Minor misc cleanups - GHC.HsToCore.Foreign.JavaScript: remove dropRuntimeRepArgs; boxed tuples don't take RuntimeRep args - GHC.HsToCore.Foreign.Call: avoid partial pattern matching - GHC.Stg.Unarise: strengthen the assertion; we can assert that non-rubbish literals are unary rather than just non-void - GHC.Tc.Gen.HsType: make sure the fsLit "literal" rule fires - users_guide/using-warnings.rst: remove -Wforall-identifier, now deprecated and does nothing - users_guide/using.rst: fix formatting - andy_cherry/test.T: remove expect_broken_for(23272...), 23272 is fixed The rest are simple cleanups. - - - - - cf55a54b by Ben Gamari at 2024-03-19T14:51:12-04:00 mk/relpath: Fix quoting Previously there were two instances in this script which lacked proper quoting. This resulted in `relpath` invocations in the binary distribution Makefile producing incorrect results on Windows, leading to confusing failures from `sed` and the production of empty package registrations. Fixes #24538. - - - - - 5ff88389 by Bryan Richter at 2024-03-19T14:51:48-04:00 testsuite: Disable T21336a on wasm - - - - - 60023351 by Ben Gamari at 2024-03-19T22:33:10-04:00 hadrian/bindist: Eliminate extraneous `dirname` invocation Previously we would call `dirname` twice per installed library file. We now instead reuse this result. This helps appreciably on Windows, where processes are quite expensive. - - - - - 616ac300 by Ben Gamari at 2024-03-19T22:33:10-04:00 hadrian: Package mingw toolchain in expected location This fixes #24525, a regression due to 41cbaf44a6ab5eb9fa676d65d32df8377898dc89. Specifically, GHC expects to find the mingw32 toolchain in the binary distribution root. However, after this patch it was packaged in the `lib/` directory. - - - - - de9daade by Ben Gamari at 2024-03-19T22:33:11-04:00 gitlab/rel_eng: More upload.sh tweaks - - - - - 1dfe12db by Ben Gamari at 2024-03-19T22:33:11-04:00 rel_eng: Drop dead prepare_docs codepath - - - - - dd2d748b by Ben Gamari at 2024-03-19T22:33:11-04:00 rel_env/recompress_all: unxz before recompressing Previously we would rather compress the xz *again*, before in addition compressing it with the desired scheme. Fixes #24545. - - - - - 9d936c57 by Ben Gamari at 2024-03-19T22:33:11-04:00 mk-ghcup-metadata: Fix directory of testsuite tarball As reported in #24546, the `dlTest` artifact should be extracted into the `testsuite` directory. - - - - - 6d398066 by Ben Gamari at 2024-03-19T22:33:11-04:00 ghcup-metadata: Don't populate dlOutput unless necessary ghcup can apparently infer the output name of an artifact from its URL. Consequently, we should only include the `dlOutput` field when it would differ from the filename of `dlUri`. Fixes #24547. - - - - - 576f8b7e by Zubin Duggal at 2024-03-19T22:33:46-04:00 Revert "Apply shellcheck suggestion to SUBST_TOOLDIR" This reverts commit c82770f57977a2b5add6e1378f234f8dd6153392. The shellcheck suggestion is spurious and results in SUBST_TOOLDIR being a no-op. `set` sets positional arguments for bash, but we want to set the variable given as the first autoconf argument. Fixes #24542 Metric decreases because the paths in the settings file are now shorter, so we allocate less when we read the settings file. ------------------------- Metric Decrease: T12425 T13035 T9198 ------------------------- - - - - - cdfe6e01 by Fendor at 2024-03-19T22:34:22-04:00 Compact serialisation of IfaceAppArgs In #24563, we identified that IfaceAppArgs serialisation tags each cons cell element with a discriminator byte. These bytes add up quickly, blowing up interface files considerably when '-fwrite-if-simplified-core' is enabled. We compact the serialisation by writing out the length of 'IfaceAppArgs', followed by serialising the elements directly without any discriminator byte. This improvement can decrease the size of some interface files by up to 35%. - - - - - 97a2bb1c by Simon Peyton Jones at 2024-03-20T17:11:29+00:00 Expand untyped splices in tcPolyExprCheck Fixes #24559 - - - - - 5f275176 by Alan Zimmerman at 2024-03-20T22:44:12-04:00 EPA: Clean up Exactprint helper functions a bit - Introduce a helper lens to compose on `EpAnn a` vs `a` versions - Rename some prime versions of functions back to non-prime They were renamed during the rework - - - - - da2a10ce by Vladislav Zavialov at 2024-03-20T22:44:48-04:00 Type operators in promoteOccName (#24570) Type operators differ from term operators in that they are lexically classified as (type) constructors, not as (type) variables. Prior to this change, promoteOccName did not account for this difference, causing a scoping issue that affected RequiredTypeArguments. type (!@#) = Bool f = idee (!@#) -- Not in scope: ‘!@#’ (BUG) Now we have a special case in promoteOccName to account for this. - - - - - 247fc0fa by Preetham Gujjula at 2024-03-21T10:19:18-04:00 docs: Remove mention of non-existent Ord instance for Complex The documentation for Data.Complex says that the Ord instance for Complex Float is deficient, but there is no Ord instance for Complex a. The Eq instance for Complex Float is similarly deficient, so we use that as an example instead. - - - - - 6fafc51e by Andrei Borzenkov at 2024-03-21T10:19:54-04:00 Fix TH handling in `pat_to_type_pat` function (#24571) There was missing case for `SplicePat` in `pat_to_type_at` function, hence patterns with splicing that checked against `forall->` doesn't work properly because they fall into the "illegal pattern" case. Code example that is now accepted: g :: forall a -> () g $([p| a |]) = () - - - - - 52072f8e by Sylvain Henry at 2024-03-21T21:01:59-04:00 Type-check default declarations before deriving clauses (#24566) See added Note and #24566. Default declarations must be type-checked before deriving clauses. - - - - - 7dfdf3d9 by Sylvain Henry at 2024-03-21T21:02:40-04:00 Lexer: small perf changes - Use unsafeChr because we know our values to be valid - Remove some unnecessary use of `ord` (return Word8 values directly) - - - - - 864922ef by Sylvain Henry at 2024-03-21T21:02:40-04:00 JS: fix some comments - - - - - 3e0b2b1f by Sebastian Graf at 2024-03-21T21:03:16-04:00 Simplifier: Re-do dependency analysis in abstractFloats (#24551) In #24551, we abstracted a string literal binding over a type variable, triggering a CoreLint error when that binding floated to top-level. The solution implemented in this patch fixes this by re-doing dependency analysis on a simplified recursive let binding that is about to be type abstracted, in order to find the minimal set of type variables to abstract over. See wrinkle (AB5) of Note [Floating and type abstraction] for more details. Fixes #24551 - - - - - 8a8ac65a by Matthew Craven at 2024-03-23T00:20:52-04:00 Improve toInteger @Word32 on 64-bit platforms On 64-bit platforms, every Word32 fits in an Int, so we can convert to Int# without having to perform the overflow check integerFromWord# uses internally. - - - - - 0c48f2b9 by Apoorv Ingle at 2024-03-23T00:21:28-04:00 Fix for #24552 (see testcase T24552) Fixes for a bug in desugaring pattern synonyms matches, introduced while working on on expanding `do`-blocks in #18324 The `matchWrapper` unecessarily (and incorrectly) filtered out the default wild patterns in a match. Now the wild pattern alternative is simply ignored by the pm check as its origin is `Generated`. The current code now matches the expected semantics according to the language spec. - - - - - b72705e9 by Simon Peyton Jones at 2024-03-23T00:22:04-04:00 Print more info about kinds in error messages This fixes #24553, where GHC unhelpfully said error: [GHC-83865] • Expected kind ‘* -> * -> *’, but ‘Foo’ has kind ‘* -> * -> *’ See Note [Showing invisible bits of types in error messages] - - - - - 8f7cfc7e by Tristan Cacqueray at 2024-03-23T00:22:44-04:00 docs: remove the don't use float hint This hint is outdated, ``Complex Float`` are now specialised, and the heap space suggestion needs more nuance so it should be explained in the unboxed/storable array documentation. - - - - - 5bd8ed53 by Andreas Klebinger at 2024-03-23T16:18:33-04:00 NCG: Fix a bug in jump shortcutting. When checking if a jump has more than one destination account for the possibility of some jumps not being representable by a BlockId. We do so by having isJumpishInstr return a `Maybe BlockId` where Nothing represents non-BlockId jump destinations. Fixes #24507 - - - - - 8d67f247 by Ben Gamari at 2024-03-23T16:19:09-04:00 docs: Drop old release notes, add for 9.12.1 - - - - - 7db8c992 by Cheng Shao at 2024-03-25T13:45:46-04:00 rts: fix clang compilation on aarch64 This patch fixes function prototypes in ARMOutlineAtomicsSymbols.h which causes "error: address argument to atomic operation must be a pointer to _Atomic type" when compiling with clang on aarch64. - - - - - 237194ce by Sylvain Henry at 2024-03-25T13:46:27-04:00 Lexer: fix imports for Alex 3.5.1 (#24583) - - - - - 810660b7 by Cheng Shao at 2024-03-25T22:19:16-04:00 libffi-tarballs: bump libffi-tarballs submodule to libffi 3.4.6 This commit bumps the libffi-tarballs submodule to libffi 3.4.6, which includes numerous upstream libffi fixes, especially https://github.com/libffi/libffi/issues/760. - - - - - d2ba41e8 by Alan Zimmerman at 2024-03-25T22:19:51-04:00 EPA: do not duplicate comments in signature RHS - - - - - 32a8103f by Rodrigo Mesquita at 2024-03-26T21:16:12-04:00 configure: Use LDFLAGS when trying linkers A user may configure `LDFLAGS` but not `LD`. When choosing a linker, we will prefer `ldd`, then `ld.gold`, then `ld.bfd` -- however, we have to check for a working linker. If either of these fail, we try the next in line. However, we were not considering the `$LDFLAGS` when checking if these linkers worked. So we would pick a linker that does not support the current $LDFLAGS and fail further down the line when we used that linker with those flags. Fixes #24565, where `LDFLAGS=-Wl,-z,pack-relative-relocs` is not supported by `ld.gold` but that was being picked still. - - - - - bf65a7c3 by Rodrigo Mesquita at 2024-03-26T21:16:48-04:00 bindist: Clean xattrs of bin and lib at configure time For issue #21506, we started cleaning the extended attributes of binaries and libraries from the bindist *after* they were installed to workaround notarisation (#17418), as part of `make install`. However, the `ghc-toolchain` binary that is now shipped with the bindist must be run at `./configure` time. Since we only cleaned the xattributes of the binaries and libs after they were installed, in some situations users would be unable to run `ghc-toolchain` from the bindist, failing at configure time (#24554). In this commit we move the xattr cleaning logic to the configure script. Fixes #24554 - - - - - cfeb70d3 by Rodrigo Mesquita at 2024-03-26T21:17:24-04:00 Revert "NCG: Fix a bug in jump shortcutting." This reverts commit 5bd8ed53dcefe10b72acb5729789e19ceb22df66. Fixes #24586 - - - - - 13223f6d by Serge S. Gulin at 2024-03-27T07:28:51-04:00 JS: `h$rts_isProfiled` is removed from `profiling` and left its version at `rts/js/config.js` - - - - - 0acfe391 by Alan Zimmerman at 2024-03-27T07:29:27-04:00 EPA: Do not extend declaration range for trailine zero len semi The lexer inserts virtual semicolons having zero width. Do not use them to extend the list span of items in a list. - - - - - cd0fb82f by Alan Zimmerman at 2024-03-27T19:33:08+00:00 EPA: Fix FamDecl range The span was incorrect if opt_datafam_kind_sig was empty - - - - - f8f384a8 by Ben Gamari at 2024-03-29T01:23:03-04:00 Fix type of _get_osfhandle foreign import Fixes #24601. - - - - - 00d3ecf0 by Alan Zimmerman at 2024-03-29T12:19:10+00:00 EPA: Extend StringLiteral range to include trailing commas This goes slightly against the exact printing philosophy where trailing decorations should be in an annotation, but the practicalities of adding it to the WarningTxt environment, and the problems caused by deviating do not make a more principles approach worthwhile. - - - - - efab3649 by brandon s allbery kf8nh at 2024-03-31T20:04:01-04:00 clarify Note [Preproccesing invocations] - - - - - c8a4c050 by Ben Gamari at 2024-04-02T12:50:35-04:00 rts: Fix TSAN_ENABLED CPP guard This should be `#if defined(TSAN_ENABLED)`, not `#if TSAN_ENABLED`, lest we suffer warnings. - - - - - e91dad93 by Cheng Shao at 2024-04-02T12:50:35-04:00 rts: fix errors when compiling with TSAN This commit fixes rts compilation errors when compiling with TSAN: - xxx_FENCE macros are redefined and trigger CPP warnings. - Use SIZEOF_W. WORD_SIZE_IN_BITS is provided by MachDeps.h which Cmm.h doesn't include by default. - - - - - a9ab9455 by Cheng Shao at 2024-04-02T12:50:35-04:00 rts: fix clang-specific errors when compiling with TSAN This commit fixes clang-specific rts compilation errors when compiling with TSAN: - clang doesn't have -Wtsan flag - Fix prototype of ghc_tsan_* helper functions - __tsan_atomic_* functions aren't clang built-ins and sanitizer/tsan_interface_atomic.h needs to be included - On macOS, TSAN runtime library is libclang_rt.tsan_osx_dynamic.dylib, not libtsan. -fsanitize-thread as a link-time flag will take care of linking the TSAN runtime library anyway so remove tsan as an rts extra library - - - - - 865bd717 by Cheng Shao at 2024-04-02T12:50:35-04:00 compiler: fix github link to __tsan_memory_order in a comment - - - - - 07cb627c by Cheng Shao at 2024-04-02T12:50:35-04:00 ci: improve TSAN CI jobs - Run TSAN jobs with +thread_sanitizer_cmm which enables Cmm instrumentation as well. - Run TSAN jobs in deb12 which ships gcc-12, a reasonably recent gcc that @bgamari confirms he's using in #GHC:matrix.org. Ideally we should be using latest clang release for latest improvements in sanitizers, though that's left as future work. - Mark TSAN jobs as manual+allow_failure in validate pipelines. The purpose is to demonstrate that we have indeed at least fixed building of TSAN mode in CI without blocking the patch to land, and once merged other people can begin playing with TSAN using their own dev setups and feature branches. - - - - - a1c18c7b by Andrei Borzenkov at 2024-04-02T12:51:11-04:00 Merge tc_infer_hs_type and tc_hs_type into one function using ExpType philosophy (#24299, #23639) This patch implements refactoring which is a prerequisite to updating kind checking of type patterns. This is a huge simplification of the main worker that checks kind of HsType. It also fixes the issues caused by previous code duplication, e.g. that we didn't add module finalizers from splices in inference mode. - - - - - 817e8936 by Rodrigo Mesquita at 2024-04-02T20:13:05-04:00 th: Hide the Language.Haskell.TH.Lib.Internal module from haddock Fixes #24562 - - - - - b36ee57b by Sylvain Henry at 2024-04-02T20:13:46-04:00 JS: reenable h$appendToHsString optimization (#24495) The optimization introducing h$appendToHsString wasn't kicking in anymore (while it did in 9.8.1) because of the changes introduced in #23270 (7e0c8b3bab30). This patch reenables the optimization by matching on case-expression, as done in Cmm for unpackCString# standard thunks. The test is also T24495 added in the next commits (two commits for ease of backporting to 9.8). - - - - - 527616e9 by Sylvain Henry at 2024-04-02T20:13:46-04:00 JS: fix h$appendToHsString implementation (#24495) h$appendToHsString needs to wrap its argument in an updatable thunk to behave like unpackAppendCString#. Otherwise if a SingleEntry thunk is passed, it is stored as-is in a CONS cell, making the resulting list impossible to deepseq (forcing the thunk doesn't update the contents of the CONS cell)! The added test checks that the optimization kicks in and that h$appendToHsString works as intended. Fix #24495 - - - - - faa30b41 by Simon Peyton Jones at 2024-04-02T20:14:22-04:00 Deal with duplicate tyvars in type declarations GHC was outright crashing before this fix: #24604 - - - - - e0b0c717 by Simon Peyton Jones at 2024-04-02T20:14:58-04:00 Try using MCoercion in exprIsConApp_maybe This is just a simple refactor that makes exprIsConApp_maybe a little bit more direct, simple, and efficient. Metrics: compile_time/bytes allocated geo. mean -0.1% minimum -2.0% maximum -0.0% Not a big gain, but worthwhile given that the code is, if anything, easier to grok. - - - - - 15f4d867 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Initial ./configure support for selecting I/O managers In this patch we just define new CPP vars, but don't yet use them or replace the existing approach. That will follow. The intention here is that every I/O manager can be enabled/disabled at GHC build time (subject to some constraints). More than one I/O manager can be enabled to be built. At least one I/O manager supporting the non-threaded RTS must be enabled as well as at least one supporting the non-threaded RTS. The I/O managers enabled here will become the choices available at runtime at RTS startup (in later patches). The choice can be made with RTS flags. There are separate sets of choices for the threaded and non-threaded RTS ways, because most I/O managers are specific to these ways. Furthermore we must establish a default I/O manager for the threaded and non-threaded RTS. Most I/O managers are platform-specific so there are checks to ensure each one can be enabled on the platform. Such checks are also where (in future) any system dependencies (e.g. libraries) can be checked. The output is a set of CPP flags (in the mk/config.h file), with one flag per named I/O manager: * IOMGR_BUILD_<name> : which ones should be built (some) * IOMGR_DEFAULT_NON_THREADED_<name> : which one is default (exactly one) * IOMGR_DEFAULT_THREADED_<name> : which one is default (exactly one) and a set of derived flags in IOManager.h * IOMGR_ENABLED_<name> : enabled for the current RTS way Note that IOMGR_BUILD_<name> just says that an I/O manager will be built for _some_ RTS way (i.e. threaded or non-threaded). The derived flags IOMGR_ENABLED_<name> in IOManager.h say if each I/O manager is enabled in the "current" RTS way. These are the ones that can be used for conditional compilation of the I/O manager code. Co-authored-by: Pi Delport <pi at well-typed.com> - - - - - 85b0f87a by Duncan Coutts at 2024-04-03T01:27:17-04:00 Change the handling of the RTS flag --io-manager= Now instead of it being just used on Windows to select between the WinIO vs the MIO or Win32-legacy I/O managers, it is now used on all platforms for selecting the I/O manager to use. Right now it remains the case that there is only an actual choice on Windows, but that will change later. Document the --io-manager flag in the user guide. This change is also reflected in the RTS flags types in the base library. Deprecate the export of IoSubSystem from GHC.RTS.Flags with a message to import it from GHC.IO.Subsystem. The way the 'IoSubSystem' is detected also changes. Instead of looking at the RTS flag, there is now a C bool global var in the RTS which gets set on startup when the I/O manager is selected. This bool var says whether the selected I/O manager classifies as "native" on Windows, which in practice means the WinIO I/O manager has been selected. Similarly, the is_io_mng_native_p RTS helper function is re-implemented in terms of the selected I/O manager, rather than based on the RTS flags. We do however remove the ./configure --native-io-manager flag because we're bringing the WinIO/MIO/Win32-legacy choice under the new general scheme for selecting I/O managers, and that new scheme involves no ./configure time user choices, just runtime RTS flag choices. - - - - - 1a8f020f by Duncan Coutts at 2024-04-03T01:27:17-04:00 Convert {init,stop,exit}IOManager to switch style Rather than ad-hoc cpp conitionals on THREADED_RTS and mingw32_HOST_OS, we use a style where we switch on the I/O manager impl, with cases for each I/O manager impl. - - - - - a5bad3d2 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Split up the CapIOManager content by I/O manager Using the new IOMGR_ENABLED_<name> CPP defines. - - - - - 1d36e609 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Convert initIOManagerAfterFork and wakeupIOManager to switch style - - - - - c2f26f36 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move most of waitRead#/Write# from cmm to C Moves it into the IOManager.c where we can follow the new pattern of switching on the selected I/O manager. - - - - - 457705a8 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move most of the delay# impl from cmm to C Moves it into the IOManager.c where we can follow the new pattern of switching on the selected I/O manager. Uses a new IOManager API: syncDelay, following the naming convention of sync* for thread-synchronous I/O & timer/delay operations. As part of porting from cmm to C, we maintain the rule that the why_blocked gets accessed using load acquire and store release atomic memory operations. There was one exception to this rule: in the delay# primop cmm code on posix (not win32), the why_blocked was being updated using a store relaxed, not a store release. I've no idea why. In this convesion I'm playing it safe here and using store release consistently. - - - - - e93058e0 by Duncan Coutts at 2024-04-03T01:27:18-04:00 insertIntoSleepingQueue is no longer public No longer defined in IOManager.h, just a private function in IOManager.c. Since it is no longer called from cmm code, just from syncDelay. It ought to get moved further into the select() I/O manager impl, rather than living in IOManager.c. On the other hand appendToIOBlockedQueue is still called from cmm code in the win32-legacy I/O manager primops async{Read,Write}#, and it is also used by the select() I/O manager. Update the CPP and comments to reflect this. - - - - - 60ce9910 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move anyPendingTimeoutsOrIO impl from .h to .c The implementation is eventually going to need to use more private things, which will drag in unwanted includes into IOManager.h, so it's better to move the impl out of the header file and into the .c file, at the slight cost of it no longer being inline. At the same time, change to the "switch (iomgr_type)" style. - - - - - f70b8108 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Take a simpler approach to gcc warnings in IOManager.c We have lots of functions with conditional implementations for different I/O managers. Some functions, for some I/O managers, naturally have implementations that do nothing or barf. When only one such I/O manager is enabled then the whole function implementation will have an implementation that does nothing or barfs. This then results in warnings from gcc that parameters are unused, or that the function should be marked with attribute noreturn (since barf does not return). The USED_IF_THREADS trick for fine-grained warning supression is fine for just two cases, but an equivalent here would need USED_IF_THE_ONLY_ENABLED_IOMGR_IS_X_OR_Y which would have combinitorial blowup. So we take a coarse grained approach and simply disable these two warnings for the whole file. So we use a GCC pragma, with its handy push/pop support: #pragma GCC diagnostic push #pragma GCC diagnostic ignored "-Wsuggest-attribute=noreturn" #pragma GCC diagnostic ignored "-Wunused-parameter" ... #pragma GCC diagnostic pop - - - - - b48805b9 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add a new trace class for the iomanager It makes sense now for it to be separate from the scheduler class of tracers. Enabled with +RTS -Do. Document the -Do debug flag in the user guide. - - - - - f0c1f862 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Have the throwTo impl go via (new) IOManager APIs rather than directly operating on the IO manager's data structures. Specifically, when thowing an async exception to a thread that is blocked waiting for I/O or waiting for a timer, then we want to cancel that I/O waiting or cancel the timer. Currently this is done directly in removeFromQueues() in RaiseAsync.c. We want it to go via proper APIs both for modularity but also to let us support multiple I/O managers. So add sync{IO,Delay}Cancel, which is the cancellation for the corresponding sync{IO,Delay}. The implementations of these use the usual "switch (iomgr_type)" style. - - - - - 4f9e9c4e by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move awaitEvent into a proper IOManager API and have the scheduler use it. Previously the scheduler calls awaitEvent directly, and awaitEvent is implemented directly in the RTS I/O managers (select, win32). This relies on the old scheme where there's a single active I/O manager for each platform and RTS way. We want to move that to go via an API in IOManager.{h,c} which can then call out to the active I/O manager. Also take the opportunity to split awaitEvent into two. The existing awaitEvent has a bool wait parameter, to say if the call should be blocking or non-blocking. We split this into two separate functions: pollCompletedTimeoutsOrIO and awaitCompletedTimeoutsOrIO. We split them for a few reasons: they have different post-conditions (specifically the await version is supposed to guarantee that there are threads runnable when it completes). Secondly, it is also anticipated that in future I/O managers the implementations of the two cases will be simpler if they are separated. - - - - - 5ad4b30f by Duncan Coutts at 2024-04-03T01:27:18-04:00 Rename awaitEvent in select and win32 I/O managers These are now just called from IOManager.c and are the per-I/O manager backend impls (whereas previously awaitEvent was the entry point). Follow the new naming convention in the IOManager.{h,c} of awaitCompletedTimeoutsOrIO, with the I/O manager's name as a suffix: so awaitCompletedTimeoutsOrIO{Select,Win32}. - - - - - d30c6bc6 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Tidy up a couple things in Select.{h,c} Use the standard #include {Begin,End}Private.h style rather than RTS_PRIVATE on individual decls. And conditionally build the code for the select I/O manager based on the new CPP IOMGR_ENABLED_SELECT rather than on THREADED_RTS. - - - - - 4161f516 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add an IOManager API for scavenging TSO blocked_info When the GC scavenges a TSO it needs to scavenge the tso->blocked_info but the blocked_info is a big union and what lives there depends on the two->why_blocked, which for I/O-related reasons is something that in principle is the responsibility of the I/O manager and not the GC. So the right thing to do is for the GC to ask the I/O manager to sscavenge the blocked_info if it encounters any I/O-related why_blocked reasons. So we add scavengeTSOIOManager in IOManager.{h,c} with the usual style. Now as it happens, right now, there is no special scavenging to do, so the implementation of scavengeTSOIOManager is a fancy no-op. That's because the select I/O manager uses only the fd and target members, which are not GC pointers, and the win32-legacy I/O manager _ought_ to be using GC-managed heap objects for the StgAsyncIOResult but it is actually usingthe C heap, so again no GC pointers. If the win32-legacy were doing this more sensibly, then scavengeTSOIOManager would be the right place to do the GC magic. Future I/O managers will need GC heap objects in the tso->blocked_info and will make use of this functionality. - - - - - 94a87d21 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add I/O manager API notifyIOManagerCapabilitiesChanged Used in setNumCapabilities. It only does anything for MIO on Posix. Previously it always invoked Haskell code, but that code only did anything on non-Windows (and non-JS), and only threaded. That currently effectively means the MIO I/O manager on Posix. So now it only invokes it for the MIO Posix case. - - - - - 3be6d591 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Select an I/O manager early in RTS startup We need to select the I/O manager to use during startup before the per-cap I/O manager initialisation. - - - - - aaa294d0 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Make struct CapIOManager be fully opaque Provide an opaque (forward) definition in Capability.h (since the cap contains a *CapIOManager) and then only provide a full definition in a new file IOManagerInternals.h. This new file is only supposed to be included by the IOManager implementation, not by its users. So that means IOManager.c and individual I/O manager implementations. The posix/Signals.c still needs direct access, but that should be eliminated. Anything that needs direct access either needs to be clearly part of an I/O manager (e.g. the sleect() one) or go via a proper API. - - - - - 877a2a80 by Duncan Coutts at 2024-04-03T01:27:18-04:00 The select() I/O manager does have some global initialisation It's just to make sure an exception CAF is a GC root. - - - - - 9c51473b by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add tracing for the main I/O manager actions Using the new tracer class. Note: The unconditional definition of showIOManager should be compatible with the debugTrace change in 7c7d1f6. Co-authored-by: Pi Delport <pi at well-typed.com> - - - - - c7d3e3a3 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Include the default I/O manager in the +RTS --info output Document the extra +RTS --info output in the user guide - - - - - 8023bad4 by Duncan Coutts at 2024-04-03T01:27:18-04:00 waitRead# / waitWrite# do not work for win32-legacy I/O manager Previously it was unclear that they did not work because the code path was shared with other I/O managers (in particular select()). Following the code carefully shows that what actually happens is that the calling thread would block forever: the thread will be put into the blocked queue, but no other action is scheduled that will ever result in it getting unblocked. It's better to just fail loudly in case anyone accidentally calls it, also it's less confusing code. - - - - - 83a74d20 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Conditionally ignore some GCC warnings Some GCC versions don't know about some warnings, and they complain that we're ignoring unknown warnings. So we try to ignore the warning based on the GCC version. - - - - - 1adc6fa4 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Accept changes to base-exports All the changes are in fact not changes at all. Previously, the IoSubSystem data type was defined in GHC.RTS.Flags and exported from both GHC.RTS.Flags and GHC.IO.SubSystem. Now, the data type is defined in GHC.IO.SubSystem and still exported from both modules. Therefore, the same exports and same instances are still available from both modules. But the base-exports records only the defining module, and so it looks like a change when it is fully compatible. Related: we do add a deprecation to the export of the type via GHC.RTS.Flags, telling people to use the export from GHC.IO.SubSystem. Also the sort order for some unrelated Show instances changed. No idea why. The same changes apply in the other versions, with a few more changes due to sort order weirdness. - - - - - 8d950968 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Accept metric decrease in T12227 I can't think of any good reason that anything in this MR should have changed the number of allocations, up or down. (Yes this is an empty commit.) Metric Decrease: T12227 - - - - - e869605e by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Several improvements to the handling of coercions * Make `mkSymCo` and `mkInstCo` smarter Fixes #23642 * Fix return role of `SelCo` in the coercion optimiser. Fixes #23617 * Make the coercion optimiser `opt_trans_rule` work better for newtypes Fixes #23619 - - - - - 1efd0714 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 FloatOut: improve floating for join point See the new Note [Floating join point bindings]. * Completely get rid of the complicated join_ceiling nonsense, which I have never understood. * Do not float join points at all, except perhaps to top level. * Some refactoring around wantToFloat, to treat Rec and NonRec more uniformly - - - - - 9c00154d by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Improve eta-expansion through call stacks See Note [Eta expanding through CallStacks] in GHC.Core.Opt.Arity This is a one-line change, that fixes an inconsistency - || isCallStackPredTy ty + || isCallStackPredTy ty || isCallStackTy ty - - - - - 95a9a172 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Spelling, layout, pretty-printing only - - - - - bdf1660f by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Improve exprIsConApp_maybe a little Eliminate a redundant case at birth. This sometimes reduces Simplifier iterations. See Note [Case elim in exprIsConApp_maybe]. - - - - - 609cd32c by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Inline GHC.HsToCore.Pmc.Solver.Types.trvVarInfo When exploring compile-time regressions after meddling with the Simplifier, I discovered that GHC.HsToCore.Pmc.Solver.Types.trvVarInfo was very delicately balanced. It's a small, heavily used, overloaded function and it's important that it inlines. By a fluke it was before, but at various times in my journey it stopped doing so. So I just added an INLINE pragma to it; no sense in depending on a delicately-balanced fluke. - - - - - ae24c9bc by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Slight improvement in WorkWrap Ensure that WorkWrap preserves lambda binders, in case of join points. Sadly I have forgotten why I made this change (it was while I was doing a lot of meddling in the Simplifier, but * it does no harm, * it is slightly more efficient, and * presumably it made something better! Anyway I have kept it in a separate commit. - - - - - e9297181 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Use named record fields for the CastIt { ... } data constructor This is a pure refactor - - - - - b4581e23 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Remove a long-commented-out line Pure refactoring - - - - - e026bdf2 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Simplifier improvements This MR started as: allow the simplifer to do more in one pass, arising from places I could see the simplifier taking two iterations where one would do. But it turned into a larger project, because these changes unexpectedly made inlining blow up, especially join points in deeply-nested cases. The main changes are below. There are also many new or rewritten Notes. Avoiding simplifying repeatedly ~~~~~~~~~~~~~~~ See Note [Avoiding simplifying repeatedly] * The SimplEnv now has a seInlineDepth field, which says how deep in unfoldings we are. See Note [Inline depth] in Simplify.Env. Currently used only for the next point: avoiding repeatedly simplifying coercions. * Avoid repeatedly simplifying coercions. see Note [Avoid re-simplifying coercions] in Simplify.Iteration As you'll see from the Note, this makes use of the seInlineDepth. * Allow Simplify.Iteration.simplAuxBind to inline used-once things. This is another part of Note [Post-inline for single-use things], and is really good for reducing simplifier iterations in situations like case K e of { K x -> blah } wher x is used once in blah. * Make GHC.Core.SimpleOpt.exprIsConApp_maybe do some simple case elimination. Note [Case elim in exprIsConApp_maybe] * Improve the case-merge transformation: - Move the main code to `GHC.Core.Utils.mergeCaseAlts`, to join `filterAlts` and friends. See Note [Merge Nested Cases] in GHC.Core.Utils. - Add a new case for `tagToEnum#`; see wrinkle (MC3). - Add a new case to look through join points: see wrinkle (MC4) postInlineUnconditionally ~~~~~~~~~~~~~~~~~~~~~~~~~ * Allow Simplify.Utils.postInlineUnconditionally to inline variables that are used exactly once. See Note [Post-inline for single-use things]. * Do not postInlineUnconditionally join point, ever. Doing so does not reduce allocation, which is the main point, and with join points that are used a lot it can bloat code. See point (1) of Note [Duplicating join points] in GHC.Core.Opt.Simplify.Iteration. * Do not postInlineUnconditionally a strict (demanded) binding. It will not allocate a thunk (it'll turn into a case instead) so again the main point of inlining it doesn't hold. Better to check per-call-site. * Improve occurrence analyis for bottoming function calls, to help postInlineUnconditionally. See Note [Bottoming function calls] in GHC.Core.Opt.OccurAnal Inlining generally ~~~~~~~~~~~~~~~~~~ * In GHC.Core.Opt.Simplify.Utils.interestingCallContext, use RhsCtxt NonRecursive (not BoringCtxt) for a plain-seq case. See Note [Seq is boring] Also, wrinkle (SB1), inline in that `seq` context only for INLINE functions (UnfWhen guidance). * In GHC.Core.Opt.Simplify.Utils.interestingArg, - return ValueArg for OtherCon [c1,c2, ...], but - return NonTrivArg for OtherCon [] This makes a function a little less likely to inline if all we know is that the argument is evaluated, but nothing else. * isConLikeUnfolding is no longer true for OtherCon {}. This propagates to exprIsConLike. Con-like-ness has /positive/ information. Join points ~~~~~~~~~~~ * Be very careful about inlining join points. See these two long Notes Note [Duplicating join points] in GHC.Core.Opt.Simplify.Iteration Note [Inlining join points] in GHC.Core.Opt.Simplify.Inline * When making join points, don't do so if the join point is so small it will immediately be inlined; check uncondInlineJoin. * In GHC.Core.Opt.Simplify.Inline.tryUnfolding, improve the inlining heuristics for join points. In general we /do not/ want to inline join points /even if they are small/. See Note [Duplicating join points] GHC.Core.Opt.Simplify.Iteration. But sometimes we do: see Note [Inlining join points] in GHC.Core.Opt.Simplify.Inline; and the new `isBetterUnfoldingThan` function. * Do not add an unfolding to a join point at birth. This is a tricky one and has a long Note [Do not add unfoldings to join points at birth] It shows up in two places - In `mkDupableAlt` do not add an inlining - (trickier) In `simplLetUnfolding` don't add an unfolding for a fresh join point I am not fully satisifed with this, but it works and is well documented. * In GHC.Core.Unfold.sizeExpr, make jumps small, so that we don't penalise having a non-inlined join point. Performance changes ~~~~~~~~~~~~~~~~~~~ * Binary sizes fall by around 2.6%, according to nofib. * Compile times improve slightly. Here are the figures over 1%. I investiate the biggest differnce in T18304. It's a very small module, just a few hundred nodes. The large percentage difffence is due to a single function that didn't quite inline before, and does now, making code size a bit bigger. I decided gains outweighed the losses. Metrics: compile_time/bytes allocated (changes over +/- 1%) ------------------------------------------------ CoOpt_Singletons(normal) -9.2% GOOD LargeRecord(normal) -23.5% GOOD MultiComponentModulesRecomp(normal) +1.2% MultiLayerModulesTH_OneShot(normal) +4.1% BAD PmSeriesS(normal) -3.8% PmSeriesV(normal) -1.5% T11195(normal) -1.3% T12227(normal) -20.4% GOOD T12545(normal) -3.2% T12707(normal) -2.1% GOOD T13253(normal) -1.2% T13253-spj(normal) +8.1% BAD T13386(normal) -3.1% GOOD T14766(normal) -2.6% GOOD T15164(normal) -1.4% T15304(normal) +1.2% T15630(normal) -8.2% T15630a(normal) NEW T15703(normal) -14.7% GOOD T16577(normal) -2.3% GOOD T17516(normal) -39.7% GOOD T18140(normal) +1.2% T18223(normal) -17.1% GOOD T18282(normal) -5.0% GOOD T18304(normal) +10.8% BAD T18923(normal) -2.9% GOOD T1969(normal) +1.0% T19695(normal) -1.5% T20049(normal) -12.7% GOOD T21839c(normal) -4.1% GOOD T3064(normal) -1.5% T3294(normal) +1.2% BAD T4801(normal) +1.2% T5030(normal) -15.2% GOOD T5321Fun(normal) -2.2% GOOD T6048(optasm) -16.8% GOOD T783(normal) -1.2% T8095(normal) -6.0% GOOD T9630(normal) -4.7% GOOD T9961(normal) +1.9% BAD WWRec(normal) -1.4% info_table_map_perf(normal) -1.3% parsing001(normal) +1.5% geo. mean -2.0% minimum -39.7% maximum +10.8% * Runtimes generally improve. In the testsuite perf/should_run gives: Metrics: runtime/bytes allocated ------------------------------------------ Conversions(normal) -0.3% T13536a(optasm) -41.7% GOOD T4830(normal) -0.1% haddock.Cabal(normal) -0.1% haddock.base(normal) -0.1% haddock.compiler(normal) -0.1% geo. mean -0.8% minimum -41.7% maximum +0.0% * For runtime, nofib is a better test. The news is mostly good. Here are the number more than +/- 0.1%: # bytes allocated ==========================++========== imaginary/digits-of-e1 || -14.40% imaginary/digits-of-e2 || -4.41% imaginary/paraffins || -0.17% imaginary/rfib || -0.15% imaginary/wheel-sieve2 || -0.10% real/compress || -0.47% real/fluid || -0.10% real/fulsom || +0.14% real/gamteb || -1.47% real/gg || -0.20% real/infer || +0.24% real/pic || -0.23% real/prolog || -0.36% real/scs || -0.46% real/smallpt || +4.03% shootout/k-nucleotide || -20.23% shootout/n-body || -0.42% shootout/spectral-norm || -0.13% spectral/boyer2 || -3.80% spectral/constraints || -0.27% spectral/hartel/ida || -0.82% spectral/mate || -20.34% spectral/para || +0.46% spectral/rewrite || +1.30% spectral/sphere || -0.14% ==========================++========== geom mean || -0.59% real/smallpt has a huge nest of local definitions, and I could not pin down a reason for a regression. But there are three big wins! Metric Decrease: CoOpt_Singletons LargeRecord T12227 T12707 T13386 T13536a T14766 T15703 T16577 T17516 T18223 T18282 T18923 T21839c T20049 T5321Fun T5030 T6048 T8095 T9630 T783 Metric Increase: MultiLayerModulesTH_OneShot T13253-spj T18304 T18698a T9961 T3294 - - - - - 27db3c5e by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Testsuite message changes from simplifier improvements - - - - - 271a7812 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Account for bottoming functions in OccurAnal This fixes #24582, a small but long-standing bug - - - - - 0fde229f by Ben Gamari at 2024-04-04T07:04:58-04:00 testsuite: Introduce template-haskell-exports test - - - - - 0c4a9686 by Luite Stegeman at 2024-04-04T07:05:39-04:00 Update correct counter in bumpTickyAllocd - - - - - 5f085d3a by Fendor at 2024-04-04T14:47:33-04:00 Replace `SizedSeq` with `FlatBag` for flattened structure LinkedLists are notoriously memory ineffiecient when all we do is traversing a structure. As 'UnlinkedBCO' has been identified as a data structure that impacts the overall memory usage of GHCi sessions, we avoid linked lists and prefer flattened structure for storing. We introduce a new memory efficient representation of sequential elements that has special support for the cases: * Empty * Singleton * Tuple Elements This improves sharing in the 'Empty' case and avoids the overhead of 'Array' until its constant overhead is justified. - - - - - 82cfe10c by Fendor at 2024-04-04T14:47:33-04:00 Compact FlatBag array representation `Array` contains three additional `Word`'s we do not need in `FlatBag`. Move `FlatBag` to `SmallArray`. Expand the API of SmallArray by `sizeofSmallArray` and add common traversal functions, such as `mapSmallArray` and `foldMapSmallArray`. Additionally, allow users to force the elements of a `SmallArray` via `rnfSmallArray`. - - - - - 36a75b80 by Andrei Borzenkov at 2024-04-04T14:48:10-04:00 Change how invisible patterns represented in haskell syntax and TH AST (#24557) Before this patch: data ArgPat p = InvisPat (LHsType p) | VisPat (LPat p) With this patch: data Pat p = ... | InvisPat (LHsType p) ... And the same transformation in the TH land. The rest of the changes is just updating code to handle new AST and writing tests to check if it is possible to create invalid states using TH. Metric Increase: MultiLayerModulesTH_OneShot - - - - - 28009fbc by Matthew Pickering at 2024-04-04T14:48:46-04:00 Fix off by one error in seekBinNoExpand and seekBin - - - - - 9b9e031b by Ben Gamari at 2024-04-04T21:30:08-04:00 compiler: Allow more types in GHCForeignImportPrim For many, many years `GHCForeignImportPrim` has suffered from the rather restrictive limitation of not allowing any non-trivial types in arguments or results. This limitation was justified by the code generator allegely barfing in the presence of such types. However, this restriction appears to originate well before the NCG rewrite and the new NCG does not appear to have any trouble with such types (see the added `T24598` test). Lift this restriction. Fixes #24598. - - - - - 1324b862 by Alan Zimmerman at 2024-04-04T21:30:44-04:00 EPA: Use EpaLocation not SrcSpan in ForeignDecls This allows us to update them for makeDeltaAst in ghc-exactprint - - - - - 19883a23 by Alan Zimmerman at 2024-04-05T16:58:17-04:00 EPA: Use EpaLocation for RecFieldsDotDot So we can update it to a delta position in makeDeltaAst if needed. - - - - - e8724327 by Matthew Pickering at 2024-04-05T16:58:53-04:00 Remove accidentally committed test.hs - - - - - 88cb3e10 by Fendor at 2024-04-08T09:03:34-04:00 Avoid UArray when indexing is not required `UnlinkedBCO`'s can occur many times in the heap. Each `UnlinkedBCO` references two `UArray`'s but never indexes them. They are only needed to encode the elements into a `ByteArray#`. The three words for the lower bound, upper bound and number of elements are essentially unused, thus we replace `UArray` with a wrapper around `ByteArray#`. This saves us up to three words for each `UnlinkedBCO`. Further, to avoid re-allocating these words for `ResolvedBCO`, we repeat the procedure for `ResolvedBCO` and add custom `Binary` and `Show` instances. For example, agda's repl session has around 360_000 UnlinkedBCO's, so avoiding these three words is already saving us around 8MB residency. - - - - - f2cc1107 by Fendor at 2024-04-08T09:04:11-04:00 Never UNPACK `FastMutInt` for counting z-encoded `FastString`s In `FastStringTable`, we count the number of z-encoded FastStrings that exist in a GHC session. We used to UNPACK the counters to not waste memory, but live retainer analysis showed that we allocate a lot of `FastMutInt`s, retained by `mkFastZString`. We lazily compute the `FastZString`, only incrementing the counter when the `FastZString` is forced. The function `mkFastStringWith` calls `mkZFastString` and boxes the `FastMutInt`, leading to the following core: mkFastStringWith = \ mk_fs _ -> = case stringTable of { FastStringTable _ n_zencs segments# _ -> ... case ((mk_fs (I# ...) (FastMutInt n_zencs)) `cast` <Co:2> :: ...) ... Marking this field as `NOUNPACK` avoids this reboxing, eliminating the allocation of a fresh `FastMutInt` on every `FastString` allocation. - - - - - c6def949 by Matthew Pickering at 2024-04-08T16:06:51-04:00 Force in_multi to avoid retaining entire hsc_env - - - - - fbb91a63 by Fendor at 2024-04-08T16:06:51-04:00 Eliminate name thunk in declaration fingerprinting Thunk analysis showed that we have about 100_000 thunks (in agda and `-fwrite-simplified-core`) pointing to the name of the name decl. Forcing this thunk fixes this issue. The thunk created here is retained by the thunk created by forkM, it is better to eagerly force this because the result (a `Name`) is already retained indirectly via the `IfaceDecl`. - - - - - 3b7b0c1c by Alan Zimmerman at 2024-04-08T16:07:27-04:00 EPA: Use EpaLocation in WarningTxt This allows us to use an EpDelta if needed when using makeDeltaAst. - - - - - 12b997df by Alan Zimmerman at 2024-04-08T16:07:27-04:00 EPA: Move DeltaPos and EpaLocation' into GHC.Types.SrcLoc This allows us to use a NoCommentsLocation for the possibly trailing comma location in a StringLiteral. This in turn allows us to correctly roundtrip via makeDeltaAst. - - - - - 868c8a78 by Fendor at 2024-04-09T08:51:50-04:00 Prefer packed representation for CompiledByteCode As there are many 'CompiledByteCode' objects alive during a GHCi session, representing its element in a more packed manner improves space behaviour at a minimal cost. When running GHCi on the agda codebase, we find around 380 live 'CompiledByteCode' objects. Packing their respective 'UnlinkedByteCode' can save quite some pointers. - - - - - be3bddde by Alan Zimmerman at 2024-04-09T08:52:26-04:00 EPA: Capture all comments in a ClassDecl Hopefully the final fix needed for #24533 - - - - - 3d0806fc by Jade at 2024-04-10T05:39:53-04:00 Validate -main-is flag using parseIdentifier Fixes #24368 - - - - - dd530bb7 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 rts: free error message before returning Fixes a memory leak in rts/linker/PEi386.c - - - - - e008a19a by Alexis King at 2024-04-10T05:40:29-04:00 linker: Avoid linear search when looking up Haskell symbols via dlsym See the primary Note [Looking up symbols in the relevant objects] for a more in-depth explanation. When dynamically loading a Haskell symbol (typical when running a splice or GHCi expression), before this commit we would search for the symbol in all dynamic libraries that were loaded. However, this could be very inefficient when too many packages are loaded (which can happen if there are many package dependencies) because the time to lookup the would be linear in the number of packages loaded. This commit drastically improves symbol loading performance by introducing a mapping from units to the handles of corresponding loaded dlls. These handles are returned by dlopen when we load a dll, and can then be used to look up in a specific dynamic library. Looking up a given Name is now much more precise because we can get lookup its unit in the mapping and lookup the symbol solely in the handles of the dynamic libraries loaded for that unit. In one measurement, the wait time before the expression was executed went from +-38 seconds down to +-2s. This commit also includes Note [Symbols may not be found in pkgs_loaded], explaining the fallback to the old behaviour in case no dll can be found in the unit mapping for a given Name. Fixes #23415 Co-authored-by: Rodrigo Mesquita (@alt-romes) - - - - - dcfaa190 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 rts: Make addDLL a wrapper around loadNativeObj Rewrite the implementation of `addDLL` as a wrapper around the more principled `loadNativeObj` rts linker function. The latter should be preferred while the former is preserved for backwards compatibility. `loadNativeObj` was previously only available on ELF platforms, so this commit further refactors the rts linker to transform loadNativeObj_ELF into loadNativeObj_POSIX, which is available in ELF and MachO platforms. The refactor made it possible to remove the `dl_mutex` mutex in favour of always using `linker_mutex` (rather than a combination of both). Lastly, we implement `loadNativeObj` for Windows too. - - - - - 12931698 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 Use symbol cache in internal interpreter too This commit makes the symbol cache that was used by the external interpreter available for the internal interpreter too. This follows from the analysis in #23415 that suggests the internal interpreter could benefit from this cache too, and that there is no good reason not to have the cache for it too. It also makes it a bit more uniform to have the symbol cache range over both the internal and external interpreter. This commit also refactors the cache into a function which is used by both `lookupSymbol` and also by `lookupSymbolInDLL`, extending the caching logic to `lookupSymbolInDLL` too. - - - - - dccd3ea1 by Ben Gamari at 2024-04-10T05:40:29-04:00 testsuite: Add test for lookupSymbolInNativeObj - - - - - 1b1a92bd by Alan Zimmerman at 2024-04-10T05:41:05-04:00 EPA: Remove unnecessary XRec in CompleteMatchSig The XRec for [LIdP pass] is not needed for exact printing, remove it. - - - - - 6e18ce2b by Ben Gamari at 2024-04-12T08:16:09-04:00 users-guide: Clarify language extension documentation Over the years the users guide's language extension documentation has gone through quite a few refactorings. In the process some of the descriptions have been rendered non-sensical. For instance, the description of `NoImplicitPrelude` actually describes the semantics of `ImplicitPrelude`. To fix this we: * ensure that all extensions are named in their "positive" sense (e.g. `ImplicitPrelude` rather than `NoImplicitPrelude`). * rework the documentation to avoid flag-oriented wording like "enable" and "disable" * ensure that the polarity of the documentation is consistent with reality. Fixes #23895. - - - - - a933aff3 by Zubin Duggal at 2024-04-12T08:16:45-04:00 driver: Make `checkHomeUnitsClosed` faster The implementation of `checkHomeUnitsClosed` was traversing every single path in the unit dependency graph - this grows exponentially and quickly grows to be infeasible on larger unit dependency graphs. Instead we replace this with a faster implementation which follows from the specificiation of the closure property - there is a closure error if there are units which are both are both (transitively) depended upon by home units and (transitively) depend on home units, but are not themselves home units. To compute the set of units required for closure, we first compute the closure of the unit dependency graph, then the transpose of this closure, and find all units that are reachable from the home units in the transpose of the closure. - - - - - 23c3e624 by Andreas Klebinger at 2024-04-12T08:17:21-04:00 RTS: Emit warning when -M < -H Fixes #24487 - - - - - d23afb8c by Ben Gamari at 2024-04-12T08:17:56-04:00 testsuite: Add broken test for CApiFFI with -fprefer-bytecode See #24634. - - - - - a4bb3a51 by Ben Gamari at 2024-04-12T08:18:32-04:00 base: Deprecate GHC.Pack As proposed in #21461. Closes #21540. - - - - - 55eb8c98 by Ben Gamari at 2024-04-12T08:19:08-04:00 ghc-internal: Fix mentions of ghc-internal in deprecation warnings Closes #24609. - - - - - b0fbd181 by Ben Gamari at 2024-04-12T08:19:44-04:00 rts: Implement set_initial_registers for AArch64 Fixes #23680. - - - - - 14c9ec62 by Ben Gamari at 2024-04-12T08:20:20-04:00 ghcup-metadata: Use Debian 9 binaries on Ubuntu 16, 17 Closes #24646. - - - - - 35a1621e by Ben Gamari at 2024-04-12T08:20:55-04:00 Bump unix submodule to 2.8.5.1 Closes #24640. - - - - - a1c24df0 by Finley McIlwaine at 2024-04-12T08:21:31-04:00 Correct default -funfolding-use-threshold in docs - - - - - 0255d03c by Oleg Grenrus at 2024-04-12T08:22:07-04:00 FastString is a __Modified__ UTF-8 - - - - - c3489547 by Matthew Pickering at 2024-04-12T13:13:44-04:00 rts: Improve tracing message when nursery is resized It is sometimes more useful to know how much bigger or smaller the nursery got when it is resized. In particular I am trying to investigate situations where we end up with fragmentation due to the nursery (#24577) - - - - - 5e4f4ba8 by Simon Peyton Jones at 2024-04-12T13:14:20-04:00 Don't generate wrappers for `type data` constructors with StrictData Previously, the logic for checking if a data constructor needs a wrapper or not would take into account whether the constructor's fields have explicit strictness (e.g., `data T = MkT !Int`), but the logic would _not_ take into account whether `StrictData` was enabled. This meant that something like `type data T = MkT Int` would incorrectly generate a wrapper for `MkT` if `StrictData` was enabled, leading to the horrible errors seen in #24620. To fix this, we disable generating wrappers for `type data` constructors altogether. Fixes #24620. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - dbdf1995 by Alex Mason at 2024-04-15T15:28:26+10:00 Implements MO_S_Mul2 and MO_U_Mul2 using the UMULH, UMULL and SMULH instructions for AArch64 Also adds a test for MO_S_Mul2 - - - - - 42bd0407 by Teo Camarasu at 2024-04-16T20:06:39-04:00 Make template-haskell a stage1 package Promoting template-haskell from a stage0 to a stage1 package means that we can much more easily refactor template-haskell. We implement this by duplicating the in-tree `template-haskell`. A new `template-haskell-next` library is autogenerated to mirror `template-haskell` `stage1:ghc` to depend on the new interface of the library including the `Binary` instances without adding an explicit dependency on `template-haskell`. This is controlled by the `bootstrap-th` cabal flag When building `template-haskell` modules as part of this vendoring we do not have access to quote syntax, so we cannot use variable quote notation (`'Just`). So we either replace these with hand-written `Name`s or hide the code behind CPP. We can remove the `th_hack` from hadrian, which was required when building stage0 packages using the in-tree `template-haskell` library. For more details see Note [Bootstrapping Template Haskell]. Resolves #23536 Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> Co-Authored-By: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org> - - - - - 3d973e47 by Ben Gamari at 2024-04-16T20:07:15-04:00 Bump parsec submodule to 3.1.17.0 - - - - - 9d38bfa0 by Simon Peyton Jones at 2024-04-16T20:07:51-04:00 Clone CoVars in CorePrep This MR addresses #24463. It's all explained in the new Note [Cloning CoVars and TyVars] - - - - - 0fe2b410 by Andreas Klebinger at 2024-04-16T20:08:27-04:00 NCG: Fix a bug where we errounously removed a required jump instruction. Add a new method to the Instruction class to check if we can eliminate a jump in favour of fallthrough control flow. Fixes #24507 - - - - - 9f99126a by Teo Camarasu at 2024-04-16T20:09:04-04:00 Fix documentation preview from doc-tarball job - Include all the .html files and assets in the job artefacts - Include all the .pdf files in the job artefacts - Mark the artefact as an "exposed" artefact meaning it turns up in the UI. Resolves #24651 - - - - - 3a0642ea by Ben Gamari at 2024-04-16T20:09:39-04:00 rts: Ignore EINTR while polling in timerfd itimer implementation While the RTS does attempt to mask signals, it may be that a foreign library unmasks them. This previously caused benign warnings which we now ignore. See #24610. - - - - - 9a53cd3f by Alan Zimmerman at 2024-04-16T20:10:15-04:00 EPA: Add additional comments field to AnnsModule This is used in exact printing to store comments coming after the `where` keyword but before any comments allocated to imports or decls. It is used in ghc-exactprint, see https://github.com/alanz/ghc-exactprint/commit/44bbed311fd8f0d053053fef195bf47c17d34fa7 - - - - - e5c43259 by Bryan Richter at 2024-04-16T20:10:51-04:00 Remove unrunnable FreeBSD CI jobs FreeBSD runner supply is inelastic. Currently there is only one, and it's unavailable because of a hardware issue. - - - - - 914eb49a by Ben Gamari at 2024-04-16T20:11:27-04:00 rel-eng: Fix mktemp usage in recompress-all We need a temporary directory, not a file. - - - - - f30e4984 by Teo Camarasu at 2024-04-16T20:12:03-04:00 Fix ghc API link in docs/index.html This was missing part of the unit ID meaning it would 404. Resolves #24674 - - - - - d7a3d6b5 by Ben Gamari at 2024-04-16T20:12:39-04:00 template-haskell: Declare TH.Lib.Internal as not-home Rather than `hide`. Closes #24659. - - - - - 5eaa46e7 by Matthew Pickering at 2024-04-19T02:14:55-04:00 testsuite: Rename isCross() predicate to needsTargetWrapper() isCross() was a misnamed because it assumed that all cross targets would provide a target wrapper, but the two most common cross targets (javascript, wasm) don't need a target wrapper. Therefore we rename this predicate to `needsTargetWrapper()` so situations in the testsuite where we can check whether running executables requires a target wrapper or not. - - - - - 55a9d699 by Simon Peyton Jones at 2024-04-19T02:15:32-04:00 Do not float HNFs out of lambdas This MR adjusts SetLevels so that it is less eager to float a HNF (lambda or constructor application) out of a lambda, unless it gets to top level. Data suggests that this change is a small net win: * nofib bytes-allocated falls by -0.09% (but a couple go up) * perf/should_compile bytes-allocated falls by -0.5% * perf/should_run bytes-allocated falls by -0.1% See !12410 for more detail. When fiddling elsewhere, I also found that this patch had a huge positive effect on the (very delicate) test perf/should_run/T21839r But that improvement doesn't show up in this MR by itself. Metric Decrease: MultiLayerModulesRecomp T15703 parsing001 - - - - - f0701585 by Alan Zimmerman at 2024-04-19T02:16:08-04:00 EPA: Fix comments in mkListSyntaxTy0 Also extend the test to confirm. Addresses #24669, 1 of 4 - - - - - b01c01d4 by Serge S. Gulin at 2024-04-19T02:16:51-04:00 JS: set image `x86_64-linux-deb11-emsdk-closure` for build - - - - - c90c6039 by Alan Zimmerman at 2024-04-19T02:17:27-04:00 EPA: Provide correct span for PatBind And remove unused parameter in checkPatBind Contributes to #24669 - - - - - bee54c24 by Krzysztof Gogolewski at 2024-04-19T11:13:00+02:00 Update quantification order following GHC haskell/haddock#23764 - - - - - 2814eb89 by Ben Gamari at 2024-04-19T18:57:05+02:00 hypsrc-test: Fix output of PositionPragmas.html - - - - - 26036f96 by Alan Zimmerman at 2024-04-19T13:11:08-04:00 EPA: Fix span for PatBuilderAppType Include the location of the prefix @ in the span for InVisPat. Also removes unnecessary annotations from HsTP. Contributes to #24669 - - - - - dba03aab by Matthew Craven at 2024-04-19T13:11:44-04:00 testsuite: Give the pre_cmd for mhu-perf more time - - - - - d31fbf6c by Krzysztof Gogolewski at 2024-04-19T21:04:09-04:00 Fix quantification order for a `op` b and a %m -> b Fixes #23764 Implements https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0640-tyop-quantification-order.rst Updates haddock submodule. - - - - - 385cd1c4 by Sebastian Graf at 2024-04-19T21:04:45-04:00 Make `seq#` a magic Id and inline it in CorePrep (#24124) We can save much code and explanation in Tag Inference and StgToCmm by making `seq#` a known-key Magic Id in `GHC.Internal.IO` and inline this definition in CorePrep. See the updated `Note [seq# magic]`. I also implemented a new `Note [Flatten case-bind]` to get better code for otherwise nested case scrutinees. I renamed the contructors of `ArgInfo` to use an `AI` prefix in order to resolve the clash between `type CpeApp = CoreExpr` and the data constructor of `ArgInfo`, as well as fixed typos in `Note [CorePrep invariants]`. Fixes #24252 and #24124. - - - - - 275e41a9 by Jade at 2024-04-20T11:10:40-04:00 Put the newline after errors instead of before them This mainly has consequences for GHCi but also slightly alters how the output of GHC on the commandline looks. Fixes: #22499 - - - - - dd339c7a by Teo Camarasu at 2024-04-20T11:11:16-04:00 Remove unecessary stage0 packages Historically quite a few packages had to be stage0 as they depended on `template-haskell` and that was stage0. In #23536 we made it so that was no longer the case. This allows us to remove a bunch of packages from this list. A few still remain. A new version of `Win32` is required by `semaphore-compat`. Including `Win32` in the stage0 set requires also including `filepath` because otherwise Hadrian's dependency logic gets confused. Once our boot compiler has a newer version of `Win32` all of these will be able to be dropped. Resolves #24652 - - - - - 2f8e3a25 by Alan Zimmerman at 2024-04-20T11:11:52-04:00 EPA: Avoid duplicated comments in splice decls Contributes to #24669 - - - - - c70b9ddb by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: fix typos and namings (fixes #24602) You may noted that I've also changed term of ``` , global "h$vt_double" ||= toJExpr IntV ``` See "IntV" and ``` WaitReadOp -> \[] [fd] -> pure $ PRPrimCall $ returnS (app "h$waidRead" [fd]) ``` See "h$waidRead" - - - - - 3db54f9b by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: trivial checks for variable presence (fixes #24602) - - - - - 777f108f by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: fs module imported twice (by emscripten and by ghc-internal). ghc-internal import wrapped in a closure to prevent conflict with emscripten (fixes #24602) Better solution is to use some JavaScript module system like AMD, CommonJS or even UMD. It will be investigated at other issues. At first glance we should try UMD (See https://github.com/umdjs/umd) - - - - - a45a5712 by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: thread.js requires h$fds and h$fdReady to be declared for static code analysis, minimal code copied from GHCJS (fixes #24602) I've just copied some old pieces of GHCJS from publicly available sources (See https://github.com/Taneb/shims/blob/a6dd0202dcdb86ad63201495b8b5d9763483eb35/src/io.js#L607). Also I didn't put details to h$fds. I took minimal and left only its object initialization: `var h$fds = {};` - - - - - ad90bf12 by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: heap and stack overflows reporting defined as js hard failure (fixes #24602) These errors were treated as a hard failure for browser application. The fix is trivial: just throw error. - - - - - 5962fa52 by Serge S. Gulin at 2024-04-21T16:33:44+03:00 JS: Stubs for code without actual implementation detected by Google Closure Compiler (fixes #24602) These errors were fixed just by introducing stubbed functions with throw for further implementation. - - - - - a0694298 by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Add externs to linker (fixes #24602) After enabling jsdoc and built-in google closure compiler types I was needed to deal with the following: 1. Define NodeJS-environment types. I've just copied minimal set of externs from semi-official repo (see https://github.com/externs/nodejs/blob/6c6882c73efcdceecf42e7ba11f1e3e5c9c041f0/v8/nodejs.js#L8). 2. Define Emscripten-environment types: `HEAP8`. Emscripten already provides some externs in our code but it supposed to be run in some module system. And its definitions do not work well in plain bundle. 3. We have some functions which purpose is to add to functions some contextual information via function properties. These functions should be marked as `modifies` to let google closure compiler remove calls if these functions are not used actually by call graph. Such functions are: `h$o`, `h$sti`, `h$init_closure`, `h$setObjInfo`. 4. STG primitives such as registries and stuff from `GHC.StgToJS`. `dXX` properties were already present at externs generator function but they are started from `7`, not from `1`. This message is related: `// fixme does closure compiler bite us here?` - - - - - e58bb29f by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: added both tests: for size and for correctness (fixes #24602) By some reason MacOS builds add to stderr messages like: Ignoring unexpected archive entry: __.SYMDEF ... However I left stderr to `/dev/null` for compatibility with linux CI builds. - - - - - 909f3a9c by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Disable js linker warning for empty symbol table to make js tests running consistent across environments - - - - - 83eb10da by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Add special preprocessor for js files due of needing to keep jsdoc comments (fixes #24602) Our js files have defined google closure compiler types at jsdoc entries but these jsdoc entries are removed by cpp preprocessor. I considered that reusing them in javascript-backend would be a nice thing. Right now haskell processor uses `-traditional` option to deal with comments and `//` operators. But now there are following compiler options: `-C` and `-CC`. You can read about them at GCC (see https://gcc.gnu.org/onlinedocs/gcc/Preprocessor-Options.html#index-CC) and CLang (see https://clang.llvm.org/docs/ClangCommandLineReference.html#cmdoption-clang-CC). It seems that `-CC` works better for javascript jsdoc than `-traditional`. At least it leaves `/* ... */` comments w/o changes. - - - - - e1cf8dc2 by brandon s allbery kf8nh at 2024-04-22T03:48:26-04:00 fix link in CODEOWNERS It seems that our local Gitlab no longer has documentation for the `CODEOWNERS` file, but the master documentation still does. Use that instead. - - - - - a27c6a49 by Fendor at 2024-04-22T10:13:03+02:00 Adapt to UserData split - - - - - 1efc5a7a by Fendor at 2024-04-22T10:13:03+02:00 Adapt to BinHandle split - - - - - 593f4e04 by Fendor at 2024-04-23T10:19:14-04:00 Add performance regression test for '-fwrite-simplified-core' - - - - - 1ba39b05 by Fendor at 2024-04-23T10:19:14-04:00 Typecheck corebindings lazily during bytecode generation This delays typechecking the corebindings until the bytecode generation happens. We also avoid allocating a thunk that is retained by `unsafeInterleaveIO`. In general, we shouldn't retain values of the hydrated `Type`, as not evaluating the bytecode object keeps it alive. It is better if we retain the unhydrated `IfaceType`. See Note [Hydrating Modules] - - - - - e916fc92 by Alan Zimmerman at 2024-04-23T10:19:50-04:00 EPA: Keep comments in a CaseAlt match The comments now live in the surrounding location, not inside the Match. Make sure we keep them. Closes #24707 - - - - - d2b17f32 by Cheng Shao at 2024-04-23T15:01:22-04:00 driver: force merge objects when building dynamic objects This patch forces the driver to always merge objects when building dynamic objects even when ar -L is supported. It is an oversight of !8887: original rationale of that patch is favoring the relatively cheap ar -L operation over object merging when ar -L is supported, which makes sense but only if we are building static objects! Omitting check for whether we are building dynamic objects will result in broken .so files with undefined reference errors at executable link time when building GHC with llvm-ar. Fixes #22210. - - - - - 209d09f5 by Julian Ospald at 2024-04-23T15:02:03-04:00 Allow non-absolute values for bootstrap GHC variable Fixes #24682 - - - - - 3fff0977 by Matthew Pickering at 2024-04-23T15:02:38-04:00 Don't depend on registerPackage function in Cabal More recent versions of Cabal modify the behaviour of libAbiHash which breaks our usage of registerPackage. It is simpler to inline the part of registerPackage that we need and avoid any additional dependency and complication using the higher-level function introduces. - - - - - c62dc317 by Cheng Shao at 2024-04-25T01:32:02-04:00 ghc-bignum: remove obsolete ln script This commit removes an obsolete ln script in ghc-bignum/gmp. See 060251c24ad160264ae8553efecbb8bed2f06360 for its original intention, but it's been obsolete for a long time, especially since the removal of the make build system. Hence the house cleaning. - - - - - 6399d52b by Cheng Shao at 2024-04-25T01:32:02-04:00 ghc-bignum: update gmp to 6.3.0 This patch bumps the gmp-tarballs submodule and updates gmp to 6.3.0. The tarball format is now xz, and gmpsrc.patch has been patched into the tarball so hadrian no longer needs to deal with patching logic when building in-tree GMP. - - - - - 65b4b92f by Cheng Shao at 2024-04-25T01:32:02-04:00 hadrian: remove obsolete Patch logic This commit removes obsolete Patch logic from hadrian, given we no longer need to patch the gmp tarball when building in-tree GMP. - - - - - 71f28958 by Cheng Shao at 2024-04-25T01:32:02-04:00 autoconf: remove obsolete patch detection This commit removes obsolete deletection logic of the patch command from autoconf scripts, given we no longer need to patch anything in the GHC build process. - - - - - daeda834 by Sylvain Henry at 2024-04-25T01:32:43-04:00 JS: correctly handle RUBBISH literals (#24664) - - - - - 8a06ddf6 by Matthew Pickering at 2024-04-25T11:16:16-04:00 Linearise ghc-internal and base build This is achieved by requesting the final package database for ghc-internal, which mandates it is fully built as a dependency of configuring the `base` package. This is at the expense of cross-package parrallelism between ghc-internal and the base package. Fixes #24436 - - - - - 94da9365 by Andrei Borzenkov at 2024-04-25T11:16:54-04:00 Fix tuple puns renaming (24702) Move tuple renaming short cutter from `isBuiltInOcc_maybe` to `isPunOcc_maybe`, so we consider incoming module. I also fixed some hidden bugs that raised after the change was done. - - - - - fa03b1fb by Fendor at 2024-04-26T18:03:13-04:00 Refactor the Binary serialisation interface The goal is simplifiy adding deduplication tables to `ModIface` interface serialisation. We identify two main points of interest that make this difficult: 1. UserData hardcodes what `Binary` instances can have deduplication tables. Moreover, it heavily uses partial functions. 2. GHC.Iface.Binary hardcodes the deduplication tables for 'Name' and 'FastString', making it difficult to add more deduplication. Instead of having a single `UserData` record with fields for all the types that can have deduplication tables, we allow to provide custom serialisers for any `Typeable`. These are wrapped in existentials and stored in a `Map` indexed by their respective `TypeRep`. The `Binary` instance of the type to deduplicate still needs to explicitly look up the decoder via `findUserDataReader` and `findUserDataWriter`, which is no worse than the status-quo. `Map` was chosen as microbenchmarks indicate it is the fastest for a small number of keys (< 10). To generalise the deduplication table serialisation mechanism, we introduce the types `ReaderTable` and `WriterTable` which provide a simple interface that is sufficient to implement a general purpose deduplication mechanism for `writeBinIface` and `readBinIface`. This allows us to provide a list of deduplication tables for serialisation that can be extended more easily, for example for `IfaceTyCon`, see the issue https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for more motivation. In addition to this refactoring, we split `UserData` into `ReaderUserData` and `WriterUserData`, to avoid partial functions and reduce overall memory usage, as we need fewer mutable variables. Bump haddock submodule to accomodate for `UserData` split. ------------------------- Metric Increase: MultiLayerModulesTH_Make MultiLayerModulesRecomp T21839c ------------------------- - - - - - bac57298 by Fendor at 2024-04-26T18:03:13-04:00 Split `BinHandle` into `ReadBinHandle` and `WriteBinHandle` A `BinHandle` contains too much information for reading data. For example, it needs to keep a `FastMutInt` and a `IORef BinData`, when the non-mutable variants would suffice. Additionally, this change has the benefit that anyone can immediately tell whether the `BinHandle` is used for reading or writing. Bump haddock submodule BinHandle split. - - - - - 4d6394dd by Simon Peyton Jones at 2024-04-26T18:03:49-04:00 Fix missing escaping-kind check in tcPatSynSig Note [Escaping kind in type signatures] explains how we deal with escaping kinds in type signatures, e.g. f :: forall r (a :: TYPE r). a where the kind of the body is (TYPE r), but `r` is not in scope outside the forall-type. I had missed this subtlety in tcPatSynSig, leading to #24686. This MR fixes it; and a similar bug in tc_top_lhs_type. (The latter is tested by T24686a.) - - - - - 981c2c2c by Alan Zimmerman at 2024-04-26T18:04:25-04:00 EPA: check-exact: check that the roundtrip reproduces the source Closes #24670 - - - - - a8616747 by Andrew Lelechenko at 2024-04-26T18:05:01-04:00 Document that setEnv is not thread-safe - - - - - 1e41de83 by Bryan Richter at 2024-04-26T18:05:37-04:00 CI: Work around frequent Signal 9 errors - - - - - a6d5f9da by Naïm Favier at 2024-04-27T17:52:40-04:00 ghc-internal: add MonadFix instance for (,) Closes https://gitlab.haskell.org/ghc/ghc/-/issues/24288, implements CLC proposal https://github.com/haskell/core-libraries-committee/issues/238. Adds a MonadFix instance for tuples, permitting value recursion in the "native" writer monad and bringing consistency with the existing instance for transformers's WriterT (and, to a lesser extent, for Solo). - - - - - 64feadcd by Rodrigo Mesquita at 2024-04-27T17:53:16-04:00 bindist: Fix xattr cleaning The original fix (725343aa) was incorrect because it used the shell bracket syntax which is the quoting syntax in autoconf, making the test for existence be incorrect and therefore `xattr` was never run. Fixes #24554 - - - - - e2094df3 by damhiya at 2024-04-28T23:52:00+09:00 Make read accepts binary integer formats CLC proposal : https://github.com/haskell/core-libraries-committee/issues/177 - - - - - c62239b7 by Sylvain Henry at 2024-04-29T10:35:00+02:00 Fix tests for T22229 - - - - - 1c2fd963 by Alan Zimmerman at 2024-04-29T23:17:00-04:00 EPA: Preserve comments in Match Pats Closes #24708 Closes #24715 Closes #24734 - - - - - 4189d17e by Sylvain Henry at 2024-04-29T23:17:42-04:00 LLVM: better unreachable default destination in Switch (#24717) See added note. Co-authored-by: Siddharth Bhat <siddu.druid at gmail.com> - - - - - a3725c88 by Cheng Shao at 2024-04-29T23:18:20-04:00 ci: enable wasm jobs for MRs with wasm label This patch enables wasm jobs for MRs with wasm label. Previously the wasm label didn't actually have any effect on the CI pipeline, and full-ci needed to be applied to run wasm jobs which was a waste of runners when working on the wasm backend, hence the fix here. - - - - - 702f7964 by Matthew Pickering at 2024-04-29T23:18:56-04:00 Make interface files and object files depend on inplace .conf file A potential fix for #24737 - - - - - 728af21e by Cheng Shao at 2024-04-30T05:30:23-04:00 utils: remove obsolete vagrant scripts Vagrantfile has long been removed in !5288. This commit further removes the obsolete vagrant scripts in the tree. - - - - - 36f2c342 by Cheng Shao at 2024-04-30T05:31:00-04:00 Update autoconf scripts Scripts taken from autoconf 948ae97ca5703224bd3eada06b7a69f40dd15a02 - - - - - ecbf22a6 by Ben Gamari at 2024-04-30T05:31:36-04:00 ghcup-metadata: Drop output_name field This is entirely redundant to the filename of the URL. There is no compelling reason to name the downloaded file differently from its source. - - - - - c56d728e by Zubin Duggal at 2024-04-30T22:45:09-04:00 testsuite: Handle exceptions in framework_fail when testdir is not initialised When `framework_fail` is called before initialising testdir, it would fail with an exception reporting the testdir not being initialised instead of the actual failure. Ensure we report the actual reason for the failure instead of failing in this way. One way this can manifest is when trying to run a test that doesn't exist using `--only` - - - - - d5bea4d6 by Alan Zimmerman at 2024-04-30T22:45:45-04:00 EPA: Fix range for GADT decl with sig only Closes #24714 - - - - - 4d78c53c by Sylvain Henry at 2024-05-01T17:23:06-04:00 Fix TH dependencies (#22229) Add a dependency between Syntax and Internal (via module reexport). - - - - - 37e38db4 by Sylvain Henry at 2024-05-01T17:23:06-04:00 Bump haddock submodule - - - - - ca13075c by Sylvain Henry at 2024-05-01T17:23:47-04:00 JS: cleanup to prepare for #24743 - - - - - 40026ac3 by Alan Zimmerman at 2024-05-01T22:45:07-04:00 EPA: Preserve comments for PrefixCon Preserve comments in fun (Con {- c1 -} a b) = undefined Closes #24736 - - - - - 92134789 by Hécate Moonlight at 2024-05-01T22:45:42-04:00 Correct `@since` metadata in HpcFlags It was introduced in base-4.20, not 4.22. Fix #24721 - - - - - a580722e by Cheng Shao at 2024-05-02T08:18:45-04:00 testsuite: fix req_target_smp predicate - - - - - ac9c5f84 by Andreas Klebinger at 2024-05-02T08:18:45-04:00 STM: Remove (unused)coarse grained locking. The STM code had a coarse grained locking mode guarded by #defines that was unused. This commit removes the code. - - - - - 917ef81b by Andreas Klebinger at 2024-05-02T08:18:45-04:00 STM: Be more optimistic when validating in-flight transactions. * Don't lock tvars when performing non-committal validation. * If we encounter a locked tvar don't consider it a failure. This means in-flight validation will only fail if committing at the moment of validation is *guaranteed* to fail. This prevents in-flight validation from failing spuriously if it happens in parallel on multiple threads or parallel to thread comitting. - - - - - 167a56a0 by Alan Zimmerman at 2024-05-02T08:19:22-04:00 EPA: fix span for empty \case(s) In instance SDecide Nat where SZero %~ (SSucc _) = Disproved (\case) Ensure the span for the HsLam covers the full construct. Closes #24748 - - - - - 9bae34d8 by doyougnu at 2024-05-02T15:41:08-04:00 testsuite: expand size testing infrastructure - closes #24191 - adds windows_skip, wasm_skip, wasm_arch, find_so, _find_so - path_from_ghcPkg, collect_size_ghc_pkg, collect_object_size, find_non_inplace functions to testsuite - adds on_windows and req_dynamic_ghc predicate to testsuite The design is to not make the testsuite too smart and simply offload to ghc-pkg for locations of object files and directories. - - - - - b85b1199 by Sylvain Henry at 2024-05-02T15:41:49-04:00 GHCi: support inlining breakpoints (#24712) When a breakpoint is inlined, its context may change (e.g. tyvars in scope). We must take this into account and not used the breakpoint tick index as its sole identifier. Each instance of a breakpoint (even with the same tick index) now gets a different "info" index. We also need to distinguish modules: - tick module: module with the break array (tick counters, status, etc.) - info module: module having the CgBreakInfo (info at occurrence site) - - - - - 649c24b9 by Oleg Grenrus at 2024-05-03T20:45:42-04:00 Expose constructors of SNat, SChar and SSymbol in ghc-internal - - - - - d603f199 by Mikolaj Konarski at 2024-05-03T20:46:19-04:00 Add DCoVarSet to PluginProv (!12037) - - - - - ba480026 by Serge S. Gulin at 2024-05-03T20:47:01-04:00 JS: Enable more efficient packing of string data (fixes #24706) - - - - - be1e60ee by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Track in-scope variables in ruleCheckProgram This small patch fixes #24726, by tracking in-scope variables properly in -drule-check. Not hard to do! - - - - - 58408c77 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Add a couple more HasCallStack constraints in SimpleOpt Just for debugging, no effect on normal code - - - - - 70e245e8 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Add comments to Prep.hs This documentation patch fixes a TODO left over from !12364 - - - - - e5687186 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Use HasDebugCallStack, rather than HasCallStack - - - - - 631cefec by Cheng Shao at 2024-05-03T20:48:17-04:00 driver: always merge objects when possible This patch makes the driver always merge objects with `ld -r` when possible, and only fall back to calling `ar -L` when merge objects command is unavailable. This completely reverts !8887 and !12313, given more fixes in Cabal seems to be needed to avoid breaking certain configurations and the maintainence cost is exceeding the behefits in this case :/ - - - - - 1dacb506 by Ben Gamari at 2024-05-03T20:48:53-04:00 Bump time submodule to 1.14 As requested in #24528. ------------------------- Metric Decrease: ghc_bignum_so rts_so Metric Increase: cabal_syntax_dir rts_so time_dir time_so ------------------------- - - - - - 4941b90e by Ben Gamari at 2024-05-03T20:48:53-04:00 Bump terminfo submodule to current master - - - - - 43d48b44 by Cheng Shao at 2024-05-03T20:49:30-04:00 wasm: use scheduler.postTask() for context switch when available This patch makes use of scheduler.postTask() for JSFFI context switch when it's available. It's a more principled approach than our MessageChannel based setImmediate() implementation, and it's available in latest version of Chromium based browsers. - - - - - 08207501 by Cheng Shao at 2024-05-03T20:50:08-04:00 testsuite: give pre_cmd for mhu-perf 5x time - - - - - bf3d4db0 by Alan Zimmerman at 2024-05-03T20:50:43-04:00 EPA: Preserve comments for pattern synonym sig Closes #24749 - - - - - c49493f2 by Matthew Pickering at 2024-05-04T06:02:57-04:00 tests: Widen acceptance window for dir and so size tests These are testing things which are sometimes out the control of a GHC developer. Therefore we shouldn't fail CI if something about these dependencies change because we can't do anything about it. It is still useful to have these statistics for visualisation in grafana though. Ticket #24759 - - - - - 9562808d by Matthew Pickering at 2024-05-04T06:02:57-04:00 Disable rts_so test It has already manifested large fluctuations and destabilising CI Fixes #24762 - - - - - fc24c5cf by Ryan Scott at 2024-05-04T06:03:33-04:00 unboxedSum{Type,Data}Name: Use GHC.Types as the module Unboxed sum constructors are now defined in the `GHC.Types` module, so if you manually quote an unboxed sum (e.g., `''Sum2#`), you will get a `Name` like: ```hs GHC.Types.Sum2# ``` The `unboxedSumTypeName` function in `template-haskell`, however, mistakenly believes that unboxed sum constructors are defined in `GHC.Prim`, so `unboxedSumTypeName 2` would return an entirely different `Name`: ```hs GHC.Prim.(#|#) ``` This is a problem for Template Haskell users, as it means that they can't be sure which `Name` is the correct one. (Similarly for `unboxedSumDataName`.) This patch fixes the implementations of `unboxedSum{Type,Data}Name` to use `GHC.Types` as the module. For consistency with `unboxedTupleTypeName`, the `unboxedSumTypeName` function now uses the non-punned syntax for unboxed sums (`Sum<N>#`) as the `OccName`. Fixes #24750. - - - - - 7eab4e01 by Alan Zimmerman at 2024-05-04T16:14:55+01:00 EPA: Widen stmtslist to include last semicolon Closes #24754 - - - - - 06f7db40 by Teo Camarasu at 2024-05-05T00:19:38-04:00 doc: Fix type error in hs_try_putmvar example - - - - - af000532 by Moritz Schuler at 2024-05-05T06:30:58-04:00 Fix parsing of module names in CLI arguments closes issue #24732 - - - - - da74e9c9 by Ben Gamari at 2024-05-05T06:31:34-04:00 ghc-platform: Add Setup.hs The Hadrian bootstrapping script relies upon `Setup.hs` to drive its build. Addresses #24761. - - - - - 35d34fde by Alan Zimmerman at 2024-05-05T12:52:40-04:00 EPA: preserve comments in class and data decls Fix checkTyClHdr which was discarding comments. Closes #24755 - - - - - 03c5dfbf by Simon Peyton Jones at 2024-05-05T12:53:15-04:00 Fix a float-out error Ticket #24768 showed that the Simplifier was accidentally destroying a join point. It turned out to be that we were sending a bottoming join point to the top, accidentally abstracting over /other/ join points. Easily fixed. - - - - - adba68e7 by John Ericson at 2024-05-05T19:35:56-04:00 Substitute bindist files with Hadrian not configure The `ghc-toolchain` overhaul will eventually replace all this stuff with something much more cleaned up, but I think it is still worth making this sort of cleanup in the meantime so other untanglings and dead code cleaning can procede. I was able to delete a fair amount of dead code doing this too. `LLVMTarget_CPP` is renamed to / merged with `LLVMTarget` because it wasn't actually turned into a valid CPP identifier. (Original to 1345c7cc42c45e63ab1726a8fd24a7e4d4222467, actually.) Progress on #23966 Co-Authored-By: Sylvain Henry <hsyl20 at gmail.com> - - - - - 18f4ff84 by Alan Zimmerman at 2024-05-05T19:36:32-04:00 EPA: fix mkHsOpTyPV duplicating comments Closes #24753 - - - - - a19201d4 by Matthew Craven at 2024-05-06T19:54:29-04:00 Add test cases for #24664 ...since none are present in the original MR !12463 fixing this issue. - - - - - 46328a49 by Alan Zimmerman at 2024-05-06T19:55:05-04:00 EPA: preserve comments in data decls Closes #24771 - - - - - 3b51995c by Andrei Borzenkov at 2024-05-07T14:39:40-04:00 Rename Solo# data constructor to MkSolo# (#24673) - data Solo# a = (# a #) + data Solo# a = MkSolo# a And `(# foo #)` syntax now becomes just a syntactic sugar for `MkSolo# a`. - - - - - 4d59abf2 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Add the cmm_cpp_is_gcc predicate to the testsuite A future C-- test called T24474-cmm-override-g0 relies on the GCC-specific behaviour of -g3 implying -dD, which, in turn, leads to it emitting #defines past the preprocessing stage. Clang, at least, does not do this, so the test would fail if ran on Clang. As the behaviour here being tested is ``-optCmmP-g3'' undoing effects of the workaround we apply as a fix for bug #24474, and the workaround was for GCC-specific behaviour, the test needs to be marked as fragile on other compilers. - - - - - 25b0b404 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Split out the C-- preprocessor, and make it pass -g0 Previously, C-- was processed with the C preprocessor program. This means that it inherited flags passed via -optc. A flag that is somewhat often passed through -optc is -g. At certain -g levels (>=2), GCC starts emitting defines *after* preprocessing, for the purposes of debug info generation. This is not useful for the C-- compiler, and, in fact, causes lexer errors. We can suppress this effect (safely, if supported) via -g0. As a workaround, in older versions of GCC (<=10), GCC only emitted defines if a certain set of -g*3 flags was passed. Newer versions check the debug level. For the former, we filter out those -g*3 flags and, for the latter, we specify -g0 on top of that. As a compatible and effective solution, this change adds a C-- preprocessor distinct from the C compiler and preprocessor, but that keeps its flags. The command line produced for C-- preprocessing now looks like: $pgmCmmP $optCs_without_g3 $g0_if_supported $optCmmP Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/24474 - - - - - 9b4129a5 by Andreas Klebinger at 2024-05-08T13:24:20-04:00 -fprof-late: Only insert cost centres on functions/non-workfree cafs. They are usually useless and doing so for data values comes with a large compile time/code size overhead. Fixes #24103 - - - - - 259b63d3 by Sebastian Graf at 2024-05-08T13:24:57-04:00 Simplifier: Preserve OccInfo on DataAlt fields when case binder is dead (#24770) See the adjusted `Note [DataAlt occ info]`. This change also has a positive repercussion on `Note [Combine case alts: awkward corner]`. Fixes #24770. We now try not to call `dataConRepStrictness` in `adjustFieldsIdInfo` when all fields are lazy anyway, leading to a 2% ghc/alloc decrease in T9675. Metric Decrease: T9675 - - - - - 31b28cdb by Sebastian Graf at 2024-05-08T13:24:57-04:00 Kill seqRule, discard dead seq# in Prep (#24334) Discarding seq#s in Core land via `seqRule` was problematic; see #24334. So instead we discard certain dead, discardable seq#s in Prep now. See the updated `Note [seq# magic]`. This fixes the symptoms of #24334. - - - - - b2682534 by Rodrigo Mesquita at 2024-05-10T01:47:51-04:00 Document NcgImpl methods Fixes #19914 - - - - - 4d3acbcf by Zejun Wu at 2024-05-10T01:48:28-04:00 Make renamer to be more flexible with parens in the LHS of the rules We used to reject LHS like `(f a) b` in RULES and requires it to be written as `f a b`. It will be handy to allow both as the expression may be more readable with extra parens in some cases when infix operator is involved. Espceially when TemplateHaskell is used, extra parens may be added out of user's control and result in "valid" rules being rejected and there are not always ways to workaround it. Fixes #24621 - - - - - ab840ce6 by Ben Gamari at 2024-05-10T01:49:04-04:00 IPE: Eliminate dependency on Read Instead of encoding the closure type as decimal string we now simply represent it as an integer, eliminating the need for `Read` in `GHC.Internal.InfoProv.Types.peekInfoProv`. Closes #24504. ------------------------- Metric Decrease: T24602_perf_size size_hello_artifact ------------------------- - - - - - a9979f55 by Cheng Shao at 2024-05-10T01:49:43-04:00 testsuite: fix testwsdeque with recent clang This patch fixes compilation of testwsdeque.c with recent versions of clang, which will fail with the error below: ``` testwsdeque.c:95:33: error: warning: format specifies type 'long' but the argument has type 'void *' [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~~ ^ testwsdeque.c:95:39: error: warning: format specifies type 'int' but the argument has type 'StgWord' (aka 'unsigned long') [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~ ^~~ | %lu testwsdeque.c:133:42: error: error: incompatible function pointer types passing 'void (void *)' to parameter of type 'OSThreadProc *' (aka 'void *(*)(void *)') [-Wincompatible-function-pointer-types] 133 | createOSThread(&ids[n], "thief", thief, (void*)(StgWord)n); | ^~~~~ /workspace/ghc/_build/stage1/lib/../lib/x86_64-linux-ghc-9.11.20240502/rts-1.0.2/include/rts/OSThreads.h:193:51: error: note: passing argument to parameter 'startProc' here 193 | OSThreadProc *startProc, void *param); | ^ 2 warnings and 1 error generated. ``` - - - - - c2b33fc9 by Rodrigo Mesquita at 2024-05-10T01:50:20-04:00 Rename pre-processor invocation args Small clean up. Uses proper names for the various groups of arguments that make up the pre-processor invocation. - - - - - 2b1af08b by Cheng Shao at 2024-05-10T01:50:55-04:00 ghc-heap: fix typo in ghc-heap cbits - - - - - fc2d6de1 by Jade at 2024-05-10T21:07:16-04:00 Improve performance of Data.List.sort(By) This patch improves the algorithm to sort lists in base. It does so using two strategies: 1) Use a four-way-merge instead of the 'default' two-way-merge. This is able to save comparisons and allocations. 2) Use `(>) a b` over `compare a b == GT` and allow inlining and specialization. This mainly benefits types with a fast (>). Note that this *may* break instances with a *malformed* Ord instance where `a > b` is *not* equal to `compare a b == GT`. CLC proposal: https://github.com/haskell/core-libraries-committee/issues/236 Fixes #24280 ------------------------- Metric Decrease: MultiLayerModulesTH_Make T10421 T13719 T15164 T18698a T18698b T1969 T9872a T9961 T18730 WWRec T12425 T15703 ------------------------- - - - - - 1012e8aa by Matthew Pickering at 2024-05-10T21:07:52-04:00 Revert "ghcup-metadata: Drop output_name field" This reverts commit ecbf22a6ac397a791204590f94c0afa82e29e79f. This breaks the ghcup metadata generation on the nightly jobs. - - - - - daff1e30 by Jannis at 2024-05-12T13:38:35-04:00 Division by constants optimization - - - - - 413217ba by Andreas Klebinger at 2024-05-12T13:39:11-04:00 Tidy: Add flag to expose unfoldings if they take dictionary arguments. Add the flag `-fexpose-overloaded-unfoldings` to be able to control this behaviour. For ghc's boot libraries file size grew by less than 1% when it was enabled. However I refrained from enabling it by default for now. I've also added a section on specialization more broadly to the users guide. ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot Metric Increase: T12425 T13386 hard_hole_fits ------------------------- - - - - - c5d89412 by Zubin Duggal at 2024-05-13T22:19:53-04:00 Don't store a GlobalRdrEnv in `mi_globals` for GHCi. GHCi only needs the `mi_globals` field for modules imported with :module +*SomeModule. It uses this field to make the top level environment in `SomeModule` available to the repl. By default, only the first target in the command line parameters is "star" loaded into GHCi. Other modules have to be manually "star" loaded into the repl. Storing the top level GlobalRdrEnv for each module is very wasteful, especially given that we will most likely never need most of these environments. Instead we store only the information needed to reconstruct the top level environment in a module, which is the `IfaceTopEnv` data structure, consisting of all import statements as well as all top level symbols defined in the module (not taking export lists into account) When a particular module is "star-loaded" into GHCi (as the first commandline target, or via an explicit `:module +*SomeModule`, we reconstruct the top level environment on demand using the `IfaceTopEnv`. - - - - - d65bf4a2 by Fendor at 2024-05-13T22:20:30-04:00 Add perf regression test for `-fwrite-if-simplified-core` - - - - - 2c0f8ddb by Andrei Borzenkov at 2024-05-13T22:21:07-04:00 Improve pattern to type pattern transformation (23739) `pat_to_type_pat` function now can handle more patterns: - TuplePat - ListPat - LitPat - NPat - ConPat Allowing these new constructors in type patterns significantly increases possible shapes of type patterns without `type` keyword. This patch also changes how lookups in `lookupOccRnConstr` are performed, because we need to fall back into types when we didn't find a constructor on data level to perform `ConPat` to type transformation properly. - - - - - be514bb4 by Cheng Shao at 2024-05-13T22:21:43-04:00 hadrian: fix hadrian building with ghc-9.10.1 - - - - - ad38e954 by Cheng Shao at 2024-05-13T22:21:43-04:00 linters: fix lint-whitespace compilation with ghc-9.10.1 - - - - - a593f284 by Andreas Klebinger at 2024-05-15T07:32:10-04:00 Expand the `inline` rule to look through casts/ticks. Fixes #24808 - - - - - b1e0c313 by Cheng Shao at 2024-05-15T07:32:46-04:00 testsuite: bump PartialDownSweep timeout to 5x on wasm32 - - - - - b2227487 by Fendor at 2024-05-15T17:14:06-04:00 Add Eq and Ord instance to `IfaceType` We add an `Ord` instance so that we can store `IfaceType` in a `Data.Map` container. This is required to deduplicate `IfaceType` while writing `.hi` files to disk. Deduplication has many beneficial consequences to both file size and memory usage, as the deduplication enables implicit sharing of values. See issue #24540 for more motivation. The `Ord` instance would be unnecessary if we used a `TrieMap` instead of `Data.Map` for the deduplication process. While in theory this is clerarly the better option, experiments on the agda code base showed that a `TrieMap` implementation has worse run-time performance characteristics. To the change itself, we mostly derive `Eq` and `Ord`. This requires us to change occurrences of `FastString` with `LexicalFastString`, since `FastString` has no `Ord` instance. We change the definition of `IfLclName` to a newtype of `LexicalFastString`, to make such changes in the future easier. Bump haddock submodule for IfLclName changes - - - - - d368f9a6 by Fendor at 2024-05-15T17:14:06-04:00 Move out LiteralMap to avoid cyclic module dependencies - - - - - 2fcc09fd by Fendor at 2024-05-15T17:14:06-04:00 Add deduplication table for `IfaceType` The type `IfaceType` is a highly redundant, tree-like data structure. While benchmarking, we realised that the high redundancy of `IfaceType` causes high memory consumption in GHCi sessions when byte code is embedded into the `.hi` file via `-fwrite-if-simplified-core` or `-fbyte-code-and-object-code`. Loading such `.hi` files from disk introduces many duplicates of memory expensive values in `IfaceType`, such as `IfaceTyCon`, `IfaceTyConApp`, `IA_Arg` and many more. We improve the memory behaviour of GHCi by adding an additional deduplication table for `IfaceType` to the serialisation of `ModIface`, similar to how we deduplicate `Name`s and `FastString`s. When reading the interface file back, the table allows us to automatically share identical values of `IfaceType`. To provide some numbers, we evaluated this patch on the agda code base. We loaded the full library from the `.hi` files, which contained the embedded core expressions (`-fwrite-if-simplified-core`). Before this patch: * Load time: 11.7 s, 2.5 GB maximum residency. After this patch: * Load time: 7.3 s, 1.7 GB maximum residency. This deduplication has the beneficial side effect to additionally reduce the size of the on-disk interface files tremendously. For example, on agda, we reduce the size of `.hi` files (with `-fwrite-if-simplified-core`): * Before: 101 MB on disk * Now: 24 MB on disk This has even a beneficial side effect on the cabal store. We reduce the size of the store on disk: * Before: 341 MB on disk * Now: 310 MB on disk Note, none of the dependencies have been compiled with `-fwrite-if-simplified-core`, but `IfaceType` occurs in multiple locations in a `ModIface`. We also add IfaceType deduplication table to .hie serialisation and refactor .hie file serialisation to use the same infrastrucutre as `putWithTables`. Bump haddock submodule to accomodate for changes to the deduplication table layout and binary interface. - - - - - 36aa7cf1 by Fendor at 2024-05-15T17:14:06-04:00 Add run-time configurability of `.hi` file compression Introduce the flag `-fwrite-if-compression=<n>` which allows to configure the compression level of writing .hi files. The motivation is that some deduplication operations are too expensive for the average use case. Hence, we introduce multiple compression levels with variable impact on performance, but still reduce the memory residency and `.hi` file size on disk considerably. We introduce three compression levels: * `1`: `Normal` mode. This is the least amount of compression. It deduplicates only `Name` and `FastString`s, and is naturally the fastest compression mode. * `2`: `Safe` mode. It has a noticeable impact on .hi file size and is marginally slower than `Normal` mode. In general, it should be safe to always use `Safe` mode. * `3`: `Full` deduplication mode. Deduplicate as much as we can, resulting in minimal .hi files, but at the cost of additional compilation time. Reading .hi files doesn't need to know the initial compression level, and can always deserialise a `ModIface`, as we write out a byte that indicates the next value has been deduplicated. This allows users to experiment with different compression levels for packages, without recompilation of dependencies. Note, the deduplication also has an additional side effect of reduced memory consumption to implicit sharing of deduplicated elements. See https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for example where that matters. ------------------------- Metric Decrease: MultiLayerModulesDefsGhciWithCore T16875 T21839c T24471 hard_hole_fits libdir ------------------------- - - - - - 1e63a6fb by Matthew Pickering at 2024-05-15T17:14:07-04:00 Introduce regression tests for `.hi` file sizes Add regression tests to track how `-fwrite-if-compression` levels affect the size of `.hi` files. - - - - - 639d742b by M Farkas-Dyck at 2024-05-15T17:14:49-04:00 TTG: ApplicativeStatement exist only in Rn and Tc Co-Authored-By: romes <rodrigo.m.mesquita at gmail.com> - - - - - aa7b336b by Jade at 2024-05-15T23:06:17-04:00 Documentation: Improve documentation for symbols exported from System.IO - - - - - c561de8f by Jade at 2024-05-15T23:06:54-04:00 Improve suggestions for language extensions - When suggesting Language extensions, also suggest Extensions which imply them - Suggest ExplicitForAll and GADTSyntax instead of more specific extensions - Rephrase suggestion to include the term 'Extension' - Also moves some flag specific definitions out of Session.hs into Flags.hs (#24478) Fixes: #24477 Fixes: #24448 Fixes: #10893 - - - - - 4c7ae2a1 by Andreas Klebinger at 2024-05-15T23:07:30-04:00 Testsuite: Check if llvm assembler is available for have_llvm - - - - - bc672166 by Torsten Schmits at 2024-05-15T23:08:06-04:00 refactor quadratic search in warnMissingHomeModules - - - - - 7875e8cb by Torsten Schmits at 2024-05-15T23:08:06-04:00 add test that runs MakeDepend on thousands of modules - - - - - b84b91f5 by Adam Gundry at 2024-05-16T15:32:06-04:00 Representation-polymorphic HasField (fixes #22156) This generalises the HasField class to support representation polymorphism, so that instead of type HasField :: forall {k} . k -> Type -> Type -> Constraint we have type HasField :: forall {k} {r_rep} {a_rep} . k -> TYPE r_rep -> TYPE a_rep -> Constraint - - - - - 05285090 by Matthew Pickering at 2024-05-16T15:32:43-04:00 Bump os-string submodule to 2.0.2.2 Closes #24786 - - - - - 886ab43a by Cheng Shao at 2024-05-17T01:34:50-04:00 rts: do not prefetch mark_closure bdescr in non-moving gc when ASSERTS_ENABLED This commit fixes a small an oversight in !12148: the prefetch logic in non-moving GC may trap in debug RTS because it calls Bdescr() for mark_closure which may be a static one. It's fine in non-debug RTS because even invalid bdescr addresses are prefetched, they will not cause segfaults, so this commit implements the most straightforward fix: don't prefetch mark_closure bdescr when assertions are enabled. - - - - - b38dcf39 by Teo Camarasu at 2024-05-17T01:34:50-04:00 rts: Allocate non-moving segments with megablocks Non-moving segments are 8 blocks long and need to be aligned. Previously we serviced allocations by grabbing 15 blocks, finding an aligned 8 block group in it and returning the rest. This proved to lead to high levels of fragmentation as a de-allocating a segment caused an 8 block gap to form, and this could not be reused for allocation. This patch introduces a segment allocator based around using entire megablocks to service segment allocations in bulk. When there are no free segments, we grab an entire megablock and fill it with aligned segments. As the megablock is free, we can easily guarantee alignment. Any unused segments are placed on a free list. It only makes sense to free segments in bulk when all of the segments in a megablock are freeable. After sweeping, we grab the free list, sort it, and find all groups of segments where they cover the megablock and free them. This introduces a period of time when free segments are not available to the mutator, but the risk that this would lead to excessive allocation is low. Right after sweep, we should have an abundance of partially full segments, and this pruning step is relatively quick. In implementing this we drop the logic that kept NONMOVING_MAX_FREE segments on the free list. We also introduce an eventlog event to log the amount of pruned/retained free segments. See Note [Segment allocation strategy] Resolves #24150 ------------------------- Metric Decrease: T13253 T19695 ------------------------- - - - - - 710665bd by Cheng Shao at 2024-05-17T01:35:30-04:00 rts: fix I/O manager compilation errors for win32 target This patch fixes I/O manager compilation errors for win32 target discovered when cross-compiling to win32 using recent clang: ``` rts/win32/ThrIOManager.c:117:7: error: error: call to undeclared function 'is_io_mng_native_p'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 117 | if (is_io_mng_native_p ()) { | ^ | 117 | if (is_io_mng_native_p ()) { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/fs.c:143:28: error: error: a function declaration without a prototype is deprecated in all versions of C [-Werror,-Wstrict-prototypes] 143 | int setErrNoFromWin32Error () { | ^ | void | 143 | int setErrNoFromWin32Error () { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:227:9: error: error: call to undeclared function 'interruptIOManagerEvent'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 227 | interruptIOManagerEvent (); | ^ | 227 | interruptIOManagerEvent (); | ^ rts/win32/ConsoleHandler.c:227:9: error: note: did you mean 'getIOManagerEvent'? | 227 | interruptIOManagerEvent (); | ^ rts/include/rts/IOInterface.h:27:10: error: note: 'getIOManagerEvent' declared here 27 | void * getIOManagerEvent (void); | ^ | 27 | void * getIOManagerEvent (void); | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:196:9: error: error: call to undeclared function 'setThreadLabel'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/win32/ConsoleHandler.c:196:9: error: note: did you mean 'postThreadLabel'? | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/eventlog/EventLog.h:118:6: error: note: 'postThreadLabel' declared here 118 | void postThreadLabel(Capability *cap, | ^ | 118 | void postThreadLabel(Capability *cap, | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) ``` - - - - - 28b9cee0 by Rodrigo Mesquita at 2024-05-17T01:36:05-04:00 configure: Check C99-compat for Cmm preprocessor Fixes #24815 - - - - - 8927e0c3 by Andreas Klebinger at 2024-05-17T01:36:41-04:00 Ensure `tcHasFixedRuntimeRep (# #)` returns True. - - - - - 04179044 by doyougnu at 2024-05-17T09:00:32-04:00 testsuite: make find_so regex less general Closes #24759 Background. In MR !12372 we began tracking shared object files and directories sizes for dependencies. However, this broke release builds because release builds alter the filenames swapping "in-place" for a hash. This was not considered in the MR and thus broke release pipelines. Furthermore, the rts_so test was found to be wildly varying and was therefore disabled in !12561. This commit fixes both of these issues: - fix the rts_so test by making the regex less general, now the rts_so test and all other foo.so tests must match "libHS<some-lib>-<version>-<hash|'in-place>-<ghc>". This prevents the rts_so test from accidentally matching different rts variants such as rts_threaded, which was the cause of the wild swings after !12372. - add logic to match either a hash or the string in-place. This should make the find_so function build agnostic. - - - - - 0962b50d by Andreas Klebinger at 2024-05-17T09:01:08-04:00 TagAnalysis: Treat all bottom ids as tagged during analysis. Ticket #24806 showed that we also need to treat dead end thunks as tagged during the analysis. - - - - - 7eb9f184 by Ben Gamari at 2024-05-17T11:23:37-04:00 Remove haddock submodule In preparation for merge into the GHC, as proposed in #23178. - - - - - 47b14dcc by Fendor at 2024-05-17T11:28:17-04:00 Adapt to `IfLclName` newtype changes (cherry picked from commit a711607e29b925f3d69e27c5fde4ba655c711ff1) - - - - - 6cc6681d by Fendor at 2024-05-17T11:28:17-04:00 Add IfaceType deduplication table to interface file serialisation Although we do not really need it in the interface file serialisation, as the deserialisation uses `getWithUserData`, we need to mirror the structure `getWithUserData` expects. Thus, we write essentially an empty `IfaceType` table at the end of the file, as the interface file doesn't reference `IfaceType`. (cherry picked from commit c9bc29c6a708483d2abc3d8ec9262510ce87ca61) - - - - - b9721206 by Ben Gamari at 2024-05-17T11:30:22-04:00 ghc-tags.yaml: Initial commit - - - - - 074e7d8f by Ben Gamari at 2024-05-17T11:31:29-04:00 fourmolu: Add configuration - - - - - 151b1736 by Ben Gamari at 2024-05-17T11:32:52-04:00 Makefile: Rework for use by haddock developers Previously the Makefile was present only for GHC's old make-based build system. Now since the make-based build system is gone we can use it for more useful ends. - - - - - a7dcf13b by Ben Gamari at 2024-05-17T11:36:14-04:00 Reformat with fourmolu Using previously-added configuration and `fourmolu -i .` Note that we exclude the test-cases (`./{hoogle,html-hypsrc,latex}-test`) as they are sensitive to formatting. - - - - - 0ea6017b by Ben Gamari at 2024-05-17T11:40:04-04:00 Add 'utils/haddock/' from commit 'a7dcf13bfbb97b20e75cc8ce650e2bb628db4660' git-subtree-dir: utils/haddock git-subtree-mainline: 7eb9f1849b1c72a1c61dee88462b4244550406f3 git-subtree-split: a7dcf13bfbb97b20e75cc8ce650e2bb628db4660 - - - - - aba1d304 by Hécate Moonlight at 2024-05-17T11:40:48-04:00 Add exceptions to the dangling notes list - - - - - 527bfbfb by Hécate Moonlight at 2024-05-17T11:40:52-04:00 Add haddock to the whitespace lint ignore list - - - - - 43274677 by Ben Gamari at 2024-05-17T11:41:20-04:00 git-blame-ignore-revs: Ignore haddock reformatting - - - - - 0e679e37 by Fendor at 2024-05-18T00:27:24-04:00 Pass cpp options to the CC builder in hadrian - - - - - bb40244e by Sylvain Henry at 2024-05-18T00:28:06-04:00 JS: fix allocation constant (fix #24746) - - - - - 646d30ab by Jade at 2024-05-18T19:23:31+02:00 Add highlighting for inline-code snippets in haddock - - - - - 64459a3e by Hécate Moonlight at 2024-05-19T08:42:27-04:00 haddock: Add a .readthedocs.yml file for online documentation - - - - - 7d3d9bbf by Serge S. Gulin at 2024-05-19T18:47:05+00:00 Unicode: General Category size test (related #24789) Added trivial size performance test which involves unicode general category usage via `read`. The `read` itself uses general category to detect spaces. The purpose for this test is to measure outcome of applying improvements at General Category representation in code discussed at #24789. - - - - - 8e04efcf by Alan Zimmerman at 2024-05-19T21:29:34-04:00 EPA: Remove redundant code Remove unused epAnnAnns function various cases for showAstData that no longer exist - - - - - 071d7a1e by Rodrigo Mesquita at 2024-05-20T10:55:16-04:00 Improve docs on closed type families in hs-boots Fixes #24776 - - - - - d9e2c119 by Torsten Schmits at 2024-05-20T10:55:52-04:00 Use default deviation for large-project test This new performance test has the purpose of detecting regressions in complexity in relation to the number of modules in a project, so 1% deviation is way too small to avoid false positives. - - - - - 20b0136a by Ben Gamari at 2024-05-22T00:31:39-04:00 ghcup-metadata: Various fixes from 9.10.1 Use Debian 12/x86-64, Debian 10/aarch64, and Debian 11/aarch64 bindists where possible. - - - - - 6838a7c3 by Sylvain Henry at 2024-05-22T00:32:23-04:00 Reverse arguments to stgCallocBytes (fix #24828) - - - - - f50f46c3 by Fendor at 2024-05-22T00:32:59-04:00 Add log messages for Iface serialisation compression level Fix the label of the number of 'IfaceType' entries in the log message. Add log message for the compression level that is used to serialise a an interface file. Adds `Outputable` instance for 'CompressionIFace'. - - - - - 3bad5d55 by Hécate Moonlight at 2024-05-22T00:33:40-04:00 base: Update doctests outputs ghc-internal: Update doctests outputs - - - - - 9317c6fb by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix the testsuites of the haddock-library - Apply all the metadata revisions from Hackage to the cabal file. - Fix the `ParserSpec.hs` file in the `spec` testsuite of haddock-library. - Make `CHANGES.md` an extra-doc-file instead of an extra-source-file. - - - - - 54073b02 by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix parser of @since pragma The testsuite contained tests for annotations of the form `@since foo-bar-0.5.0`, but the parser was written incorrectly. - - - - - ede6ede3 by Matthew Pickering at 2024-05-22T00:34:57-04:00 Fix nightly pages job It seems likely broken by 9f99126a which moved `index.html` from the root folder into `docs/` folder. Fixes #24840 - - - - - b7bcf729 by Cheng Shao at 2024-05-22T00:35:32-04:00 autoconf: remove unused context diff check This patch removes redundant autoconf check for the context diff program given it isn't actually been used anywhere, especially since make removal. - - - - - ea2fe66e by Hécate Moonlight at 2024-05-22T00:36:13-04:00 haddock: Rework the contributing guide - - - - - 0f302a94 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 haddock: Add module relationships diagrams of haddock-api and haddock-library - - - - - d1a9f34f by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add instructions - - - - - b880ee80 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add SVG outputs - - - - - 6d7e6ad8 by Ben Gamari at 2024-05-22T13:40:05-04:00 rts: Fix size of StgOrigThunkInfo frames Previously the entry code of the `stg_orig_thunk` frame failed to account for the size of the profiling header as it hard-coded the frame size. Fix this. Fixes #24809. - - - - - c645fe40 by Fendor at 2024-05-22T13:40:05-04:00 Add regression test T24809 for stg_orig_thunk_info_frame size - - - - - 4181aa40 by Andreas Klebinger at 2024-05-22T13:40:42-04:00 bindists: Check for existence of share folder before trying to copy it. This folder isn't distributed in windows bindists A lack of doing so resulted us copying loads of files twice. - - - - - d216510e by Matthew Pickering at 2024-05-22T13:40:42-04:00 Remove ad-hoc installation of mingw toolchain in relocatable bindists This reverts 616ac30026e8dd7d2ebb98d92dde071eedf5d951 The choice about whether to install mingw is taken in the installation makefile. This is also broken on non-windows systems. The actual issue was the EnableDistroToolchain variable wasn't declared in mk/config.mk and therefore the check to install mingw was failing. - - - - - 7b4c1998 by Cheng Shao at 2024-05-22T21:52:52-04:00 testsuite: fix T17920 for wasm backend T17920 was marked as fragile on wasm before; it can be trivially fixed by avoiding calling variadic printf() in cmm. - - - - - c739383b by Cheng Shao at 2024-05-22T21:53:29-04:00 testsuite: bump T22744 timeout to 5x - - - - - c4c6d714 by Cheng Shao at 2024-05-22T21:54:06-04:00 testsuite: don't attempt to detect host cpu features when testing cross ghc The testsuite driver CPU feature detection logic only detects host CPU and only makes sense when we are not testing a cross GHC. - - - - - 3d9e4ce6 by Simon Peyton Jones at 2024-05-22T21:54:43-04:00 Better skolemisation As #24810 showed, it is (a little) better to skolemise en-bloc, so that Note [Let-bound skolems] fires more often. See Note [Skolemisation en bloc] in GHC.Tc.Utils.Instantiate. - - - - - a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00 Add missing parenthesizePat in cvtp We need to ensure that the output of `cvtp` is parenthesized (at precedence `sigPrec`) so that any pattern signatures with a surrounding pattern signature can parse correctly. Fixes #24837. - - - - - 4bb2a7cc by Hécate Moonlight at 2024-05-22T21:55:59-04:00 [base] Document the memory overhead of ByteArray Add a diagram that shows the constituent parts of a ByteArray and their memory overhead. - - - - - 8b2a016a by Hécate Moonlight at 2024-05-22T21:56:38-04:00 Haddock: Add MR template for Haddock - - - - - ead75532 by Peter Trommler at 2024-05-23T02:28:05-04:00 PPC: Support ELF v2 on powerpc64 big-endian Detect ELF v2 on PowerPC 64-bit systems. Check for `_CALL_ELF` preprocessor macro. Fixes #21191 - - - - - 9d4c10f2 by Hécate Kleidukos at 2024-05-23T02:28:44-04:00 gitlab: Add @Kleidukos to CODEOWNERS for utils/haddock - - - - - 28e64170 by Preetham Gujjula at 2024-05-23T07:20:48-04:00 haddock: Add cabal-fmt to tools for `make style` - - - - - 00126a89 by Andrei Borzenkov at 2024-05-23T07:21:24-04:00 haddock: fix verbosity option parsing - - - - - a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00 base: specify tie-breaking behavior of min, max, and related list/Foldable functions - - - - - bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00 cmm: add word <-> double/float bitcast - closes: #25331 This is the last step in the project plan described in #25331. This commit: - adds bitcast operands for x86_64, LLVM, aarch64 - For PPC and i386 we resort to using the cmm implementations - renames conversion MachOps from Conv to Round|Truncate - - - - - f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor Some functions in StgToByteCode were filtering out void arguments. However, StgToByteCode is called after unarisation: the void arguments should have been removed earlier. Instead of filtering out, we assert that the args are non-void. - - - - - 03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor `layoutNativeCall` was always called with a `primRepCmmType platform` callback. Hence we can put it inside of `layoutNativeCall` rather than repeat it. - - - - - 27c430f3 by David Binder at 2024-05-24T07:52:38-04:00 haddock: Remove compatibility shims for GHC < 8.4 from haddock-library - - - - - 8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00 compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs This patch makes the STG->Cmm backend avoid saving foreign call target to local when there are no caller-save GlobalRegs. Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a foreign call, we unconditionally save the foreign call target to a temporary local first, then rely on cmmSink to clean it up later, which only happens with -fcmm-sink (implied by -O) and not in unoptimized code. And this is troublesome for the wasm backend NCG, which needs to infer a foreign call target symbol's type signature from the Cmm call site. Previously, the NCG has been emitting incorrect type signatures for unoptimized code, which happens to work with `wasm-ld` most of the time, but this is never future-proof against upstream toolchain updates, and it causes horrible breakages when LTO objects are included in linker input. Hence this patch. - - - - - 986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00 testsuite: add callee-no-local regression test - - - - - 52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00 Fix HasCallStack leftovers from !12514 / #24726 - - - - - c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00 user_guide: Fix typo in MultiWayIf chapter Close #24829 - - - - - bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - 1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Fix changelog reference to setBacktraceMechanismState (cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d) - - - - - 43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00 Float/double unboxed literal support for HexFloatLiterals (fix #22155) - - - - - 4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00 Improve test labels for binary interface file size tests Test labels for binary interface file sizes are hard to read and overly verbose at the same time. Extend the name for the metric title, but shorten it in the actual comparison table. - - - - - 14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00 Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present" This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa. - - - - - f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00 Fix default hyperlinked sources pattern Previously this didn't include the `%M` token which manifested as broken links to the hyperlinked sources of reexports of declarations defined in other packages. Fixes haddock#1628. (cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36) - - - - - 42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00 Make DocPaths a proper data type (cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c) - - - - - 53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00 haddock: Bump version to 2.30 (cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602) - - - - - e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00 haddock-api: allow base 4.20 and ghc 9.11 - - - - - e294f7a2 by PHO at 2024-05-24T12:17:55-04:00 Add a flag "threaded" for building haddock with the threaded RTS GHC isn't guaranteed to have a threaded RTS. There should be a way to build it with the vanilla one. (cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d) - - - - - 51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00 Update ticky counter event docs. Add the info about the info table address and json fields. Fixes #23200 - - - - - 98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00 Export extractPromotedList (#24866) This can be useful in plugins. - - - - - 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 31be87ae by Melanie Brown at 2024-06-09T09:31:28-04:00 export GHC.Internal.Data.Traversable.for from Prelude - - - - - 20 changed files: - .ghcid - + .git-blame-ignore-revs - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/darwin/nix/sources.json - .gitlab/darwin/toolchain.nix - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - + .gitlab/merge_request_templates/Haddock.md - .gitlab/rel_eng/default.nix - .gitlab/rel_eng/fetch-gitlab-artifacts/fetch_gitlab.py - .gitlab/rel_eng/mk-ghcup-metadata/README.mkd - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - + .gitlab/rel_eng/recompress-all - .gitlab/rel_eng/upload.sh - .gitlab/rel_eng/upload_ghc_libs.py - .gitmodules - CODEOWNERS - compiler/GHC.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7887a9826fb0699b3bf4dd578948cf287160f091...31be87aebf12d4a4b56cccd0ce8de5a46c3ee833 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7887a9826fb0699b3bf4dd578948cf287160f091...31be87aebf12d4a4b56cccd0ce8de5a46c3ee833 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 13:42:41 2024 From: gitlab at gitlab.haskell.org (Melanie Brown (@mixphix)) Date: Sun, 09 Jun 2024 09:42:41 -0400 Subject: [Git][ghc/ghc][wip/prelude-for] export GHC.Internal.Data.Traversable.for from Prelude Message-ID: <6665b151fc46_32f883222531015828f@gitlab.mail> Melanie Brown pushed to branch wip/prelude-for at Glasgow Haskell Compiler / GHC Commits: 57585b58 by Melanie Brown at 2024-06-09T09:42:13-04:00 export GHC.Internal.Data.Traversable.for from Prelude - - - - - 1 changed file: - libraries/base/src/Prelude.hs Changes: ===================================== libraries/base/src/Prelude.hs ===================================== @@ -94,7 +94,7 @@ module Prelude ( sum), -- :: Num a => t a -> a -- toList) -- :: Foldable t => t a -> [a] - Traversable(traverse, sequenceA, mapM, sequence), + Traversable(traverse, sequenceA, mapM, sequence), for, -- ** Miscellaneous functions id, const, (.), flip, ($), until, @@ -173,7 +173,7 @@ import GHC.Internal.Data.Foldable ( Foldable(..) ) import qualified GHC.Internal.Data.Foldable as Foldable import GHC.Internal.Data.Functor ( (<$>) ) import GHC.Internal.Data.Maybe -import GHC.Internal.Data.Traversable ( Traversable(..) ) +import GHC.Internal.Data.Traversable ( Traversable(..), for ) import GHC.Internal.Data.Tuple import GHC.Internal.Base hiding ( foldr, mapM, sequence ) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/57585b5817e3aec532e53ec60b1760fcebfbf927 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/57585b5817e3aec532e53ec60b1760fcebfbf927 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 13:46:02 2024 From: gitlab at gitlab.haskell.org (Melanie Brown (@mixphix)) Date: Sun, 09 Jun 2024 09:46:02 -0400 Subject: [Git][ghc/ghc][wip/prelude-for] 3 commits: ghc-internal: Update prologue.txt to reflect package description Message-ID: <6665b21a6d46a_32f883237b84015872f@gitlab.mail> Melanie Brown pushed to branch wip/prelude-for at Glasgow Haskell Compiler / GHC Commits: 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - a8184e1b by Melanie Brown at 2024-06-09T13:45:58+00:00 export GHC.Internal.Data.Traversable.for from Prelude - - - - - 3 changed files: - compiler/GHC/CmmToAsm/X86/Instr.hs - libraries/base/src/Prelude.hs - libraries/ghc-internal/prologue.txt Changes: ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -198,10 +198,13 @@ data Instr -- Moves. | MOV Format Operand Operand - -- ^ N.B. when used with the 'II64' 'Format', the source + -- ^ N.B. Due to AT&T assembler quirks, when used with 'II64' + -- 'Format' immediate source and memory target operand, the source -- operand is interpreted to be a 32-bit sign-extended value. - -- True 64-bit operands need to be moved with @MOVABS@, which we - -- currently don't use. + -- True 64-bit operands need to be either first moved to a register or moved + -- with @MOVABS@; we currently do not use this instruction in GHC. + -- See https://stackoverflow.com/questions/52434073/whats-the-difference-between-the-x86-64-att-instructions-movq-and-movabsq. + | MOVD Format Operand Operand -- ^ MOVD/MOVQ SSE2 instructions -- (bitcast between a general purpose -- register and a float register). ===================================== libraries/base/src/Prelude.hs ===================================== @@ -94,7 +94,7 @@ module Prelude ( sum), -- :: Num a => t a -> a -- toList) -- :: Foldable t => t a -> [a] - Traversable(traverse, sequenceA, mapM, sequence), + Traversable(traverse, sequenceA, mapM, sequence), for, -- ** Miscellaneous functions id, const, (.), flip, ($), until, @@ -173,7 +173,7 @@ import GHC.Internal.Data.Foldable ( Foldable(..) ) import qualified GHC.Internal.Data.Foldable as Foldable import GHC.Internal.Data.Functor ( (<$>) ) import GHC.Internal.Data.Maybe -import GHC.Internal.Data.Traversable ( Traversable(..) ) +import GHC.Internal.Data.Traversable ( Traversable(..), for ) import GHC.Internal.Data.Tuple import GHC.Internal.Base hiding ( foldr, mapM, sequence ) ===================================== libraries/ghc-internal/prologue.txt ===================================== @@ -1,3 +1,2 @@ -This package contains the @Prelude@ and its support libraries, and a large -collection of useful libraries ranging from data structures to parsing -combinators and debugging utilities. +This package contains the implementation of GHC's standard libraries and is +not intended for use by end-users. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57585b5817e3aec532e53ec60b1760fcebfbf927...a8184e1bdd247d7145976431823b47bc8b39bede -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57585b5817e3aec532e53ec60b1760fcebfbf927...a8184e1bdd247d7145976431823b47bc8b39bede You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 13:58:36 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Sun, 09 Jun 2024 09:58:36 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] 2 commits: ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Message-ID: <6665b50cd4752_32f88325ecca0161894@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: 1403d8aa by Fabian Kirchner at 2024-06-09T15:40:58+02:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - 0075a8b8 by Fabian Kirchner at 2024-06-09T15:58:20+02:00 ttg: Move some AST types into Language.Haskell.Syntax.Basic In particular, we move: * TopLevelFlag * TypeOrData * TyConFlavour Progress towards #21592 - - - - - 8 changed files: - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var.hs-boot - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Decls.hs - + compiler/Language/Haskell/Syntax/Specificity.hs - compiler/ghc.cabal.in Changes: ===================================== compiler/GHC/Core/TyCo/Rep.hs-boot ===================================== @@ -3,8 +3,9 @@ module GHC.Core.TyCo.Rep where import GHC.Utils.Outputable ( Outputable ) import Data.Data ( Data ) -import {-# SOURCE #-} GHC.Types.Var( Var, VarBndr, ForAllTyFlag, FunTyFlag ) +import {-# SOURCE #-} GHC.Types.Var( Var, VarBndr, FunTyFlag ) import {-# SOURCE #-} GHC.Core.TyCon ( TyCon ) +import Language.Haskell.Syntax.Specificity (ForAllTyFlag) data Type data Coercion ===================================== compiler/GHC/Types/Basic.hs ===================================== @@ -14,7 +14,9 @@ types that \end{itemize} -} -{-# OPTIONS_GHC -Wno-orphans #-} -- Outputable PromotionFlag, Binary PromotionFlag, Outputable Boxity, Binay Boxity +{-# OPTIONS_GHC -Wno-orphans #-} +-- Outputable PromotionFlag, Binary PromotionFlag, Outputable Boxity, Binay Boxity, +-- Outputable ForAllTyFlag, Specificity, et friends... {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE MultiParamTypeClasses #-} @@ -132,7 +134,8 @@ import GHC.Utils.Binary import GHC.Types.SourceText import qualified GHC.LanguageExtensions as LangExt import {-# SOURCE #-} Language.Haskell.Syntax.Type (PromotionFlag(..), isPromoted) -import Language.Haskell.Syntax.Basic (Boxity(..), isBoxed, ConTag) +import Language.Haskell.Syntax.Basic (Boxity(..), isBoxed, ConTag, TopLevelFlag(..), isTopLevel, isNotTopLevel, TypeOrData(..), TyConFlavour(..)) +import Language.Haskell.Syntax.Specificity import {-# SOURCE #-} Language.Haskell.Syntax.Expr (HsDoFlavour) import Control.DeepSeq ( NFData(..) ) @@ -542,19 +545,6 @@ pprRuleName rn = doubleQuotes (ftext rn) ************************************************************************ -} -data TopLevelFlag - = TopLevel - | NotTopLevel - deriving Data - -isTopLevel, isNotTopLevel :: TopLevelFlag -> Bool - -isNotTopLevel NotTopLevel = True -isNotTopLevel TopLevel = False - -isTopLevel TopLevel = True -isTopLevel NotTopLevel = False - instance Outputable TopLevelFlag where ppr TopLevel = text "" ppr NotTopLevel = text "" @@ -2166,22 +2156,6 @@ data TypeOrConstraint * * ********************************************************************* -} --- | Paints a picture of what a 'TyCon' represents, in broad strokes. --- This is used towards more informative error messages. -data TyConFlavour tc - = ClassFlavour - | TupleFlavour Boxity - | SumFlavour - | DataTypeFlavour - | NewtypeFlavour - | AbstractTypeFlavour - | OpenFamilyFlavour TypeOrData (Maybe tc) -- Just tc <=> (tc == associated class) - | ClosedTypeFamilyFlavour - | TypeSynonymFlavour - | BuiltInTypeFlavour -- ^ e.g., the @(->)@ 'TyCon'. - | PromotedDataConFlavour - deriving (Eq, Data, Functor) - instance Outputable (TyConFlavour tc) where ppr = text . go where @@ -2220,17 +2194,50 @@ tyConFlavourAssoc_maybe :: TyConFlavour tc -> Maybe tc tyConFlavourAssoc_maybe (OpenFamilyFlavour _ mb_parent) = mb_parent tyConFlavourAssoc_maybe _ = Nothing --- | Whether something is a type or a data declaration, --- e.g. a type family or a data family. -data TypeOrData - = IAmData - | IAmType - deriving (Eq, Data) - instance Outputable TypeOrData where ppr IAmData = text "data" ppr IAmType = text "type" +{- ********************************************************************* +* * +* ForAllTyFlag +* * +********************************************************************* -} + +instance Outputable ForAllTyFlag where + ppr Required = text "[req]" + ppr Specified = text "[spec]" + ppr Inferred = text "[infrd]" + +instance Binary Specificity where + put_ bh SpecifiedSpec = putByte bh 0 + put_ bh InferredSpec = putByte bh 1 + + get bh = do + h <- getByte bh + case h of + 0 -> return SpecifiedSpec + _ -> return InferredSpec + +instance Binary ForAllTyFlag where + put_ bh Required = putByte bh 0 + put_ bh Specified = putByte bh 1 + put_ bh Inferred = putByte bh 2 + + get bh = do + h <- getByte bh + case h of + 0 -> return Required + 1 -> return Specified + _ -> return Inferred + +instance NFData Specificity where + rnf SpecifiedSpec = () + rnf InferredSpec = () +instance NFData ForAllTyFlag where + rnf (Invisible spec) = rnf spec + rnf Required = () + {- ********************************************************************* * * Defaulting options ===================================== compiler/GHC/Types/Var.hs ===================================== @@ -130,7 +130,7 @@ import GHC.Utils.Outputable import GHC.Utils.Panic import Data.Data -import Control.DeepSeq +import Language.Haskell.Syntax.Specificity {- ************************************************************************ @@ -449,97 +449,6 @@ updateVarTypeM upd var result = do { ty' <- upd (varType var) ; return (var { varType = ty' }) } -{- ********************************************************************* -* * -* ForAllTyFlag -* * -********************************************************************* -} - --- | ForAllTyFlag --- --- Is something required to appear in source Haskell ('Required'), --- permitted by request ('Specified') (visible type application), or --- prohibited entirely from appearing in source Haskell ('Inferred')? --- See Note [VarBndrs, ForAllTyBinders, TyConBinders, and visibility] in "GHC.Core.TyCo.Rep" -data ForAllTyFlag = Invisible !Specificity - | Required - deriving (Eq, Ord, Data) - -- (<) on ForAllTyFlag means "is less visible than" - --- | Whether an 'Invisible' argument may appear in source Haskell. -data Specificity = InferredSpec - -- ^ the argument may not appear in source Haskell, it is - -- only inferred. - | SpecifiedSpec - -- ^ the argument may appear in source Haskell, but isn't - -- required. - deriving (Eq, Ord, Data) - -pattern Inferred, Specified :: ForAllTyFlag -pattern Inferred = Invisible InferredSpec -pattern Specified = Invisible SpecifiedSpec - -{-# COMPLETE Required, Specified, Inferred #-} - --- | Does this 'ForAllTyFlag' classify an argument that is written in Haskell? -isVisibleForAllTyFlag :: ForAllTyFlag -> Bool -isVisibleForAllTyFlag af = not (isInvisibleForAllTyFlag af) - --- | Does this 'ForAllTyFlag' classify an argument that is not written in Haskell? -isInvisibleForAllTyFlag :: ForAllTyFlag -> Bool -isInvisibleForAllTyFlag (Invisible {}) = True -isInvisibleForAllTyFlag Required = False - -isInferredForAllTyFlag :: ForAllTyFlag -> Bool --- More restrictive than isInvisibleForAllTyFlag -isInferredForAllTyFlag (Invisible InferredSpec) = True -isInferredForAllTyFlag _ = False - -isSpecifiedForAllTyFlag :: ForAllTyFlag -> Bool --- More restrictive than isInvisibleForAllTyFlag -isSpecifiedForAllTyFlag (Invisible SpecifiedSpec) = True -isSpecifiedForAllTyFlag _ = False - -coreTyLamForAllTyFlag :: ForAllTyFlag --- ^ The ForAllTyFlag on a (Lam a e) term, where `a` is a type variable. --- If you want other ForAllTyFlag, use a cast. --- See Note [Required foralls in Core] in GHC.Core.TyCo.Rep -coreTyLamForAllTyFlag = Specified - -instance Outputable ForAllTyFlag where - ppr Required = text "[req]" - ppr Specified = text "[spec]" - ppr Inferred = text "[infrd]" - -instance Binary Specificity where - put_ bh SpecifiedSpec = putByte bh 0 - put_ bh InferredSpec = putByte bh 1 - - get bh = do - h <- getByte bh - case h of - 0 -> return SpecifiedSpec - _ -> return InferredSpec - -instance Binary ForAllTyFlag where - put_ bh Required = putByte bh 0 - put_ bh Specified = putByte bh 1 - put_ bh Inferred = putByte bh 2 - - get bh = do - h <- getByte bh - case h of - 0 -> return Required - 1 -> return Specified - _ -> return Inferred - -instance NFData Specificity where - rnf SpecifiedSpec = () - rnf InferredSpec = () -instance NFData ForAllTyFlag where - rnf (Invisible spec) = rnf spec - rnf Required = () - {- ********************************************************************* * * * FunTyFlag ===================================== compiler/GHC/Types/Var.hs-boot ===================================== @@ -2,13 +2,12 @@ module GHC.Types.Var where import {-# SOURCE #-} GHC.Types.Name +import Language.Haskell.Syntax.Specificity (Specificity) -data ForAllTyFlag data FunTyFlag data Var instance NamedThing Var data VarBndr var argf -data Specificity type TyVar = Var type Id = Var type TyCoVar = Id ===================================== compiler/Language/Haskell/Syntax/Basic.hs ===================================== @@ -2,11 +2,8 @@ {-# LANGUAGE GeneralisedNewtypeDeriving #-} module Language.Haskell.Syntax.Basic where +import Prelude import Data.Data -import Data.Eq -import Data.Ord -import Data.Bool -import Data.Int (Int) import GHC.Data.FastString (FastString) import Control.DeepSeq @@ -96,3 +93,48 @@ data SrcUnpackedness = SrcUnpack -- ^ {-# UNPACK #-} specified | SrcNoUnpack -- ^ {-# NOUNPACK #-} specified | NoSrcUnpack -- ^ no unpack pragma deriving (Eq, Data) + + +{- +************************************************************************ +* * +Top-level/not-top level flag +* * +************************************************************************ +-} + +data TopLevelFlag + = TopLevel + | NotTopLevel + deriving Data + +isTopLevel, isNotTopLevel :: TopLevelFlag -> Bool + +isNotTopLevel NotTopLevel = True +isNotTopLevel TopLevel = False + +isTopLevel TopLevel = True +isTopLevel NotTopLevel = False + +-- | Whether something is a type or a data declaration, +-- e.g. a type family or a data family. +data TypeOrData + = IAmData + | IAmType + deriving (Eq, Data) + +-- | Paints a picture of what a 'TyCon' represents, in broad strokes. +-- This is used towards more informative error messages. +data TyConFlavour tc + = ClassFlavour + | TupleFlavour Boxity + | SumFlavour + | DataTypeFlavour + | NewtypeFlavour + | AbstractTypeFlavour + | OpenFamilyFlavour TypeOrData (Maybe tc) -- Just tc <=> (tc == associated class) + | ClosedTypeFamilyFlavour + | TypeSynonymFlavour + | BuiltInTypeFlavour -- ^ e.g., the @(->)@ 'TyCon'. + | PromotedDataConFlavour + deriving (Eq, Data, Functor) ===================================== compiler/Language/Haskell/Syntax/Decls.hs ===================================== @@ -97,14 +97,13 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr import Language.Haskell.Syntax.Binds import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Type -import Language.Haskell.Syntax.Basic (Role) +import Language.Haskell.Syntax.Basic (Role, TopLevelFlag, TypeOrData(..), TyConFlavour(..)) +import Language.Haskell.Syntax.Specificity (Specificity) -import GHC.Types.Basic (TopLevelFlag, OverlapMode, RuleName, Activation - ,TyConFlavour(..), TypeOrData(..)) +import GHC.Types.Basic (OverlapMode, RuleName, Activation) import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CCallTarget, CExportSpec) import GHC.Types.Fixity (LexicalFixity) -import GHC.Core.Type (Specificity) import GHC.Unit.Module.Warnings (WarningTxt) import GHC.Hs.Doc (LHsDoc) -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST ===================================== compiler/Language/Haskell/Syntax/Specificity.hs ===================================== @@ -0,0 +1,68 @@ +{-# LANGUAGE MultiWayIf, PatternSynonyms #-} + +-- TODO Everthing in this module should be moved to +-- Language.Haskell.Syntax.Decls + +module Language.Haskell.Syntax.Specificity ( + -- * ForAllTyFlags + ForAllTyFlag(Invisible,Required,Specified,Inferred), + Specificity(..), + isVisibleForAllTyFlag, isInvisibleForAllTyFlag, isInferredForAllTyFlag, + isSpecifiedForAllTyFlag, + coreTyLamForAllTyFlag, + ) where + +import Prelude + +import Data.Data + +-- | ForAllTyFlag +-- +-- Is something required to appear in source Haskell ('Required'), +-- permitted by request ('Specified') (visible type application), or +-- prohibited entirely from appearing in source Haskell ('Inferred')? +-- See Note [VarBndrs, ForAllTyBinders, TyConBinders, and visibility] in "GHC.Core.TyCo.Rep" +data ForAllTyFlag = Invisible !Specificity + | Required + deriving (Eq, Ord, Data) + -- (<) on ForAllTyFlag means "is less visible than" + +-- | Whether an 'Invisible' argument may appear in source Haskell. +data Specificity = InferredSpec + -- ^ the argument may not appear in source Haskell, it is + -- only inferred. + | SpecifiedSpec + -- ^ the argument may appear in source Haskell, but isn't + -- required. + deriving (Eq, Ord, Data) + +pattern Inferred, Specified :: ForAllTyFlag +pattern Inferred = Invisible InferredSpec +pattern Specified = Invisible SpecifiedSpec + +{-# COMPLETE Required, Specified, Inferred #-} + +-- | Does this 'ForAllTyFlag' classify an argument that is written in Haskell? +isVisibleForAllTyFlag :: ForAllTyFlag -> Bool +isVisibleForAllTyFlag af = not (isInvisibleForAllTyFlag af) + +-- | Does this 'ForAllTyFlag' classify an argument that is not written in Haskell? +isInvisibleForAllTyFlag :: ForAllTyFlag -> Bool +isInvisibleForAllTyFlag (Invisible {}) = True +isInvisibleForAllTyFlag Required = False + +isInferredForAllTyFlag :: ForAllTyFlag -> Bool +-- More restrictive than isInvisibleForAllTyFlag +isInferredForAllTyFlag (Invisible InferredSpec) = True +isInferredForAllTyFlag _ = False + +isSpecifiedForAllTyFlag :: ForAllTyFlag -> Bool +-- More restrictive than isInvisibleForAllTyFlag +isSpecifiedForAllTyFlag (Invisible SpecifiedSpec) = True +isSpecifiedForAllTyFlag _ = False + +coreTyLamForAllTyFlag :: ForAllTyFlag +-- ^ The ForAllTyFlag on a (Lam a e) term, where `a` is a type variable. +-- If you want other ForAllTyFlag, use a cast. +-- See Note [Required foralls in Core] in GHC.Core.TyCo.Rep +coreTyLamForAllTyFlag = Specified ===================================== compiler/ghc.cabal.in ===================================== @@ -976,6 +976,7 @@ Library Language.Haskell.Syntax.Lit Language.Haskell.Syntax.Module.Name Language.Haskell.Syntax.Pat + Language.Haskell.Syntax.Specificity Language.Haskell.Syntax.Type autogen-modules: GHC.Platform.Constants View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d7e7821774618dda0271ac90f03eec212cac697f...0075a8b851ed08ec39456fe16387c75504fb2fdc -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d7e7821774618dda0271ac90f03eec212cac697f...0075a8b851ed08ec39456fe16387c75504fb2fdc You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 14:02:38 2024 From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge)) Date: Sun, 09 Jun 2024 10:02:38 -0400 Subject: [Git][ghc/ghc][wip/T24789_impl] 4 commits: ghc-internal: Update CHANGELOG to reflect current version Message-ID: <6665b5fe766c3_32f88327ba1a416532@gitlab.mail> Serge S. Gulin pushed to branch wip/T24789_impl at Glasgow Haskell Compiler / GHC Commits: 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - eade9d16 by Serge S. Gulin at 2024-06-09T17:01:22+03:00 Unicode: adding compact version of GeneralCategory The following features are applied: 1. Lookup code like Cmm-switches (draft implementation proposed by Sylvain Henry @hsyl20) 2. Nested ifs (logarithmic search vs linear search) (the idea proposed by Sylvain Henry @hsyl20) 3. More compact representation via variable encoding by Huffman - - - - - 15 changed files: - compiler/GHC/CmmToAsm/X86/Instr.hs - libraries/ghc-internal/CHANGELOG.md - libraries/ghc-internal/ghc-internal.cabal - libraries/ghc-internal/prologue.txt - libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs - + libraries/ghc-internal/src/GHC/Internal/Unicode/Huffman.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/GeneralCategory.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/Huffman.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/HuffmanDecode.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/RangeSwitch.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/Generator/WordEncoding.hs - libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs - libraries/ghc-internal/tools/ucd2haskell/ucd.sh - libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal Changes: ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -198,10 +198,13 @@ data Instr -- Moves. | MOV Format Operand Operand - -- ^ N.B. when used with the 'II64' 'Format', the source + -- ^ N.B. Due to AT&T assembler quirks, when used with 'II64' + -- 'Format' immediate source and memory target operand, the source -- operand is interpreted to be a 32-bit sign-extended value. - -- True 64-bit operands need to be moved with @MOVABS@, which we - -- currently don't use. + -- True 64-bit operands need to be either first moved to a register or moved + -- with @MOVABS@; we currently do not use this instruction in GHC. + -- See https://stackoverflow.com/questions/52434073/whats-the-difference-between-the-x86-64-att-instructions-movq-and-movabsq. + | MOVD Format Operand Operand -- ^ MOVD/MOVQ SSE2 instructions -- (bitcast between a general purpose -- register and a float register). ===================================== libraries/ghc-internal/CHANGELOG.md ===================================== @@ -1,5 +1,5 @@ # Revision history for `ghc-internal` -## 0.1.0.0 -- YYYY-mm-dd +## 9.1001.0 -- 2024-05-01 -* First version. Released on an unsuspecting world. +* Package created containing implementation moved from `base`. ===================================== libraries/ghc-internal/ghc-internal.cabal ===================================== @@ -318,6 +318,7 @@ Library GHC.Internal.Event.PSQ GHC.Internal.Event.Unique -- GHC.Internal.IOPort -- TODO: hide again after debug + GHC.Internal.Unicode.Huffman GHC.Internal.Unicode.Bits GHC.Internal.Unicode.Char.DerivedCoreProperties GHC.Internal.Unicode.Char.UnicodeData.GeneralCategory ===================================== libraries/ghc-internal/prologue.txt ===================================== @@ -1,3 +1,2 @@ -This package contains the @Prelude@ and its support libraries, and a large -collection of useful libraries ranging from data structures to parsing -combinators and debugging utilities. +This package contains the implementation of GHC's standard libraries and is +not intended for use by end-users. ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Bits.hs ===================================== @@ -1,6 +1,9 @@ {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE BangPatterns #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE UnliftedNewtypes #-} +{-# LANGUAGE BlockArguments #-} ----------------------------------------------------------------------------- -- | @@ -18,20 +21,22 @@ ----------------------------------------------------------------------------- module GHC.Internal.Unicode.Bits - ( lookupBit64, - lookupIntN - ) where + ( lookupIntN + , lookupBit64 + , newByteArrayFromWord8List + , byteArrayLookupIntN + , copyAddrToWord8List + , UnicodeByteArray + ) + where -import GHC.Internal.Base (Bool, Int(..), Word(..), Eq(..)) import GHC.Internal.Bits (finiteBitSize, popCount) -import {-# SOURCE #-} GHC.Internal.ByteOrder import GHC.Prim - (Addr#, - indexWordOffAddr#, indexWord8OffAddr#, - andI#, uncheckedIShiftRL#, - and#, word2Int#, uncheckedShiftL#, - word8ToWord#, byteSwap#) -import GHC.Internal.Num ((-)) +import GHC.Internal.ST +import GHC.Internal.Base +import GHC.Internal.Num +import GHC.Internal.List +import GHC.Internal.Word -- | @lookup64 addr index@ looks up the bit stored at bit index @index@ using a -- bitmap starting at the address @addr at . Looks up the 64-bit word containing @@ -49,9 +54,7 @@ lookupBit64 addr# (I# index#) = W# (word## `and#` bitMask##) /= 0 _ -> popCount fbs -- this is a really weird architecture wordIndex# = index# `uncheckedIShiftRL#` logFbs# - word## = case targetByteOrder of - BigEndian -> byteSwap# (indexWordOffAddr# addr# wordIndex#) - LittleEndian -> indexWordOffAddr# addr# wordIndex# + word## = byteSwap# (indexWordOffAddr# addr# wordIndex#) bitIndex# = index# `andI#` fbs# bitMask## = 1## `uncheckedShiftL#` bitIndex# @@ -71,3 +74,41 @@ lookupIntN lookupIntN addr# (I# index#) = let word## = word8ToWord# (indexWord8OffAddr# addr# index#) in I# (word2Int# word##) + +data UnicodeByteArray = UnicodeByteArray !ByteArray# + +byteArrayLookupIntN :: UnicodeByteArray -> Int -> Int +byteArrayLookupIntN ba idx + = let !(UnicodeByteArray addr) = ba + in lookupIntN (byteArrayContents# addr) idx + +newByteArrayFromWord8List :: [Word8] -> UnicodeByteArray +newByteArrayFromWord8List xs = runST $ ST \s0 -> + case newPinnedByteArray# len s0 of + !(# s1, mba #) -> + let s2 = fillByteArray mba 0# xs s1 + in case unsafeFreezeByteArray# mba s2 of + !(# s3, fba #) -> (# s3, UnicodeByteArray fba #) + where + !(I# len) = length xs + + fillByteArray _ _ [] s = s + fillByteArray mba i (y:ys) s = + let !(W8# y#) = y + s' = writeWord8Array# mba i y# s + in fillByteArray mba (i +# 1#) ys s' + +copyAddrToWord8List :: Addr# -> Int -> [Word8] +copyAddrToWord8List addr !len@(I# len') = runST $ ST \s0 -> + case newByteArray# len' s0 of + !(# s1, mba #) -> + let s2 = copyAddrToByteArray# addr mba 0# len' s1 + in case unsafeFreezeByteArray# mba s2 of + !(# s3, fba #) -> (# s3, readByteFromArray fba 0 len #) + where + readByteFromArray :: ByteArray# -> Int -> Int -> [Word8] + readByteFromArray ba !from@(I# from') to = + W8# (indexWord8Array# ba from') : + if from == (to - 1) + then [] + else readByteFromArray ba (from + 1) to ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs ===================================== The diff for this file was not included because it is too large. ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Huffman.hs ===================================== @@ -0,0 +1,53 @@ +-- DO NOT EDIT IT HERE. It is automatically copied from ucd2haskell tool's Generator.HuffmanDecode +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE ExplicitForAll #-} +{-# LANGUAGE TypeApplications #-} + +module GHC.Internal.Unicode.Huffman + ( decodeHuffman + , deserializeHuffman + , HuffmanTree (..) + ) + where + +import GHC.Internal.Word (Word8) +import GHC.Internal.Bits (testBit) +import GHC.Internal.Show (Show (..)) +import GHC.Internal.Base (Bool, Eq, Functor, (.), (++), error, map) +import qualified GHC.Internal.List as L (concatMap) + +data HuffmanTree a + = HTLeaf !a + | HTNode !(HuffmanTree a) !(HuffmanTree a) + deriving stock (Show, Eq, Functor) + +deserializeHuffman :: forall a . (Word8 -> a) -> [Word8] -> HuffmanTree a +deserializeHuffman conv = (\(a, _) -> a) . go + where + go [] = error "Unable to process empty list" + go (0x00:value:rest) = (HTLeaf (conv value), rest) + go (0x01:rest) = + let + (left, rest') = go rest + (right, rest'') = go rest' + in (HTNode left right, rest'') + go v = error ("Unknown type of Huffman tree leaf: " ++ show v) + +decodeHuffman :: HuffmanTree a -> [Word8] -> [a] +decodeHuffman huffman_tree = decodeBits huffman_tree . unpackBits + where + word8ToBools :: Word8 -> [Bool] + word8ToBools w = map (testBit w) [7, 6 .. 0] + + unpackBits :: [Word8] -> [Bool] + unpackBits = L.concatMap word8ToBools + + decodeBits :: HuffmanTree a -> [Bool] -> [a] + decodeBits tree bits = decodeBits' tree bits tree + where + decodeBits' _ [] _ = [] + decodeBits' (HTLeaf c) bs tree' = c : decodeBits' tree' bs tree' + decodeBits' (HTNode l r) (b:bs) tree' = decodeBits' next bs tree' + where next = if b then r else l + ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/GeneralCategory.hs ===================================== @@ -0,0 +1,150 @@ +{-# LANGUAGE BlockArguments #-} +module Generator.GeneralCategory (GeneralCategory (..), generateGeneralCategoryCode) where + +import Generator.RangeSwitch +import Generator.WordEncoding +import Data.List (intercalate) +import Text.Printf (printf) +import Generator.Huffman (mkHuffmanTree, serializeHuffman) + +data GeneralCategory = + Lu|Ll|Lt| --LC + Lm|Lo| --L + Mn|Mc|Me| --M + Nd|Nl|No| --N + Pc|Pd|Ps|Pe|Pi|Pf|Po| --P + Sm|Sc|Sk|So| --S + Zs|Zl|Zp| --Z + Cc|Cf|Cs|Co|Cn --C + deriving (Show, Eq, Ord, Bounded, Enum, Read) + +genEnumBitmap :: + forall a. (Bounded a, Enum a, Show a) => + -- | Function name + String -> + -- | Default value + a -> + -- | List of values to encode + [a] -> + String +genEnumBitmap funcName def as = unlines + [ "{-# INLINE " <> funcName <> " #-}" + , funcName <> " :: Char -> Int" + , funcName <> " c = let n = ord c in if n >= " + <> show (length as) + <> " then " + <> show (fromEnum def) + <> " else lookup_bitmap n" + ] + +generateHaskellCode :: Int -> [GeneralCategory] -> String +generateHaskellCode max_char_length cats = + let (index_tree, all_allocs) = extract [] range_tree + in intercalate "\n" + [ "{-" + , "Huffman Cases" + , printf (printCases cases_huffman_encoded) + , "Huffman Cases => Nested Ifs" + , printf (printRangeTree range_tree) + , "-}" + , "{-# NOINLINE deserialized_huffman #-}" + , "deserialized_huffman :: HuffmanTree Word8" + , "deserialized_huffman =" + , intercalate " " [" let huffman_tree =", "\"" <> mapToAddrLiteral serialized_huffman "\"#"] + , printf " in deserializeHuffman (\\x -> x) (copyAddrToWord8List huffman_tree %d)" (length serialized_huffman) + , intercalate "\n" (fmap genDecompressed (zip all_allocs [0..])) + , "{-# NOINLINE lookup_bitmap #-}" + , "lookup_bitmap :: Int -> Int" + , "lookup_bitmap n =" + , printf " (%s)" (genCode' index_tree 2) + ] + where + cases' = rangeCases max_char_length cats + huffmanTree = mkHuffmanTree $ extractLookupIntList cases' + cases_huffman_encoded = rangesToWord8 huffmanTree cases' + range_tree = buildRangeTree cases_huffman_encoded + + serialized_huffman = serializeHuffman toWord8 huffmanTree + + prefixEachLine indent ls = concatMap (\l -> "\n" ++ replicate (indent*2) ' ' ++ l) ls + + genCode' :: (Show a) => RangeTree (Either a Int) -> Int -> String + genCode' (Leaf _ _ cat) _ = show cat + genCode' (Node start _ (Leaf _ endl c_l) (Leaf startr _ c_r)) indent = + prefixEachLine indent + [ printf "({- 1 -} if n < %d then (%s) else (%s))" (endl+1) (genResult start c_l) (genResult startr c_r) + ] + + genCode' (Node start _ (Leaf _ endl c_l) node_r@(Node _ _ _ _)) indent = + prefixEachLine indent + [ printf "({- 2 -}if n < %d then (%s) else (%s))" (endl+1) (genResult start c_l) (genCode' node_r $ indent + 1) + ] + + genCode' (Node _ _ node_l@(Node _ _ _ _) (Leaf startr _ c_r)) indent = + prefixEachLine indent + [ printf "({- 3 -} if n >= %d then (%s) else (%s))" startr (genResult startr c_r) (genCode' node_l $ indent + 1) + ] + + genCode' (Node _ _ node_l@(Node _ endl _ _) node_r@(Node _ _ _ _)) indent = + prefixEachLine indent + [ printf "({- 4 -} if n < %d then (%s) else (%s))" (endl+1) (genCode' node_l $ indent + 1) (genCode' node_r $ indent + 1) + ] + + genResult :: Show a => Int -> Either a Int -> String + genResult _ (Left s) = show s + -- genResult mi (Right idx) = intercalate " " ["lookupIntN (decodeHuffman (toEnum . fromIntegral, deserialized_huffman)", "\"" <> mapToAddrLiteral as "\"#)", "(n -", show mi, ")"] + genResult mi (Right idx) = intercalate " " ["byteArrayLookupIntN", "decompressed_table_" <> show idx, "(n -", show mi, ")"] + + extract :: [[a]] -> RangeTree (Either a [a]) -> (RangeTree (Either a Int), [[a]]) + extract acc (Leaf mi ma (Left v)) = (Leaf mi ma (Left v), acc) + extract acc (Leaf mi ma (Right v)) = (Leaf mi ma (Right (length acc)), acc ++ [v]) + extract acc (Node mi ma lt rt) = + let + (e_lt, l_acc) = extract acc lt + (e_rt, r_acc) = extract l_acc rt + in (Node mi ma e_lt e_rt, r_acc) + + genDecompressed :: forall a. Show a => ([a], Int) -> String + genDecompressed (acc, idx) = + let fn_name = "decompressed_table_" <> show idx + in intercalate "\n" + [ "" + , "{-# NOINLINE " <> fn_name <> " #-}" + , fn_name <> " :: UnicodeByteArray" + , fn_name <> " =" + , intercalate " " [" let compressed = copyAddrToWord8List", "\"" <> mapToAddrLiteral acc "\"#", show (length acc)] + , printf " in newByteArrayFromWord8List (decodeHuffman deserialized_huffman compressed)" + ] + +generateGeneralCategoryCode + :: (String -> String) + -- ^-- How to generate module header where first arg us module name + -> String + -- ^-- Module name + -> Int + -- ^-- Max char length + -> [GeneralCategory] + -- ^-- imported general categories for all symbol list + -> String +generateGeneralCategoryCode mkModuleHeader moduleName char_length cats = + unlines + [ "{-# LANGUAGE NoImplicitPrelude #-}" + , "{-# LANGUAGE MagicHash #-}" + , "{-# LANGUAGE TypeApplications #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(generalCategory)" + , "where" + , "" + , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" + , "import GHC.Internal.Unicode.Bits (UnicodeByteArray, copyAddrToWord8List, newByteArrayFromWord8List, byteArrayLookupIntN)" + , "import GHC.Internal.Unicode.Huffman (HuffmanTree, decodeHuffman, deserializeHuffman)" + , "import GHC.Internal.Num ((-))" + , "import GHC.Internal.Word (Word8)" + , "" + , generateHaskellCode char_length cats + , "" + , genEnumBitmap "generalCategory" Cn (reverse cats) + ] ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/Huffman.hs ===================================== @@ -0,0 +1,83 @@ +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE PackageImports #-} + +module Generator.Huffman + ( mkHuffmanTree + , encodeHuffman + , serializeHuffman + ) + where + +import Data.List (sortBy) +import Data.Ord (comparing) +import Data.Maybe (fromJust) +import Data.Map.Strict (Map) +import qualified Data.Map.Strict as Map +import Data.Word (Word8) +import Data.Bits (shiftL, (.|.)) +import Generator.HuffmanDecode (HuffmanTree (..)) + +data HuffmanTreeFreq a + = HTFLeaf a Int + | HTFNode Int (HuffmanTreeFreq a) (HuffmanTreeFreq a) + deriving stock (Show, Eq, Functor) + +buildHuffmanTree :: Ord a => [(a, Int)] -> HuffmanTree a +buildHuffmanTree freqs = convertTree $ buildTree initialQueue + where + frequency :: HuffmanTreeFreq a -> Int + frequency (HTFLeaf _ f) = f + frequency (HTFNode f _ _) = f + + initialQueue = sortBy (comparing frequency) [HTFLeaf s f | (s, f) <- freqs] + + buildTree [] = error "impossible: empty list is not an appropriate input here" + buildTree [t] = t + buildTree (t1:t2:ts) = + let newNode = HTFNode (frequency t1 + frequency t2) t1 t2 + newQueue = insertBy (comparing frequency) newNode ts + in buildTree newQueue + + insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a] + insertBy _ x [] = [x] + insertBy cmp x ys@(y:ys') + = case cmp x y of + GT -> y : insertBy cmp x ys' + _ -> x : ys + + convertTree :: HuffmanTreeFreq a -> HuffmanTree a + convertTree (HTFLeaf value _) = HTLeaf value + convertTree (HTFNode _ left right) = HTNode (convertTree left) (convertTree right) + +serializeHuffman :: (a -> Word8) -> HuffmanTree a -> [Word8] +serializeHuffman conv (HTLeaf value) = [0x00, conv value] +serializeHuffman conv (HTNode left right) = [0x01] ++ serializeHuffman conv left ++ serializeHuffman conv right + +mkHuffmanTree :: (Ord a) => [a] -> HuffmanTree a +mkHuffmanTree = buildHuffmanTree . Map.toList . huffmanStats + where + huffmanStats :: (Ord a) => [a] -> Map a Int + huffmanStats l = Map.fromListWith (+) [(c, 1) | c <- l] + +encodeHuffman :: (Ord a) => HuffmanTree a -> [a] -> [Word8] +encodeHuffman huffmanTree = packBits . encodeBits (buildHuffmanTable huffmanTree) + where + boolsToWord8 :: [Bool] -> Word8 + boolsToWord8 = foldl (\acc b -> shiftL acc 1 .|. if b then 1 else 0) 0 + + chunksOf :: Int -> [a] -> [[a]] + chunksOf _ [] = [] + chunksOf n xs = take n xs : chunksOf n (drop n xs) + + packBits :: [Bool] -> [Word8] + packBits bits = map boolsToWord8 (chunksOf 8 bits) + + encodeBits :: (Ord a) => Map.Map a [Bool] -> [a] -> [Bool] + encodeBits huffmanTable cc = concatMap (\c -> fromJust $ Map.lookup c huffmanTable) cc + + buildHuffmanTable :: Ord a => HuffmanTree a -> Map a [Bool] + buildHuffmanTable tree = Map.fromList $ buildCodes tree [] + where + buildCodes (HTLeaf s) code = [(s, code)] + buildCodes (HTNode l r) code = buildCodes l (code ++ [False]) ++ buildCodes r (code ++ [True]) ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/HuffmanDecode.hs ===================================== @@ -0,0 +1,52 @@ +{-# LANGUAGE DeriveFunctor #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE ExplicitForAll #-} +{-# LANGUAGE TypeApplications #-} + +module Generator.HuffmanDecode + ( decodeHuffman + , deserializeHuffman + , HuffmanTree (..) + ) + where + +import Data.Word (Word8) +import Data.Bits (testBit) +import GHC.Show (Show (..)) +import GHC.Base (Bool, Eq, Functor, (.), (++), error, map) +import qualified GHC.List as L (concatMap) + +data HuffmanTree a + = HTLeaf !a + | HTNode !(HuffmanTree a) !(HuffmanTree a) + deriving stock (Show, Eq, Functor) + +deserializeHuffman :: forall a . (Word8 -> a) -> [Word8] -> HuffmanTree a +deserializeHuffman conv = (\(a, _) -> a) . go + where + go [] = error "Unable to process empty list" + go (0x00:value:rest) = (HTLeaf (conv value), rest) + go (0x01:rest) = + let + (left, rest') = go rest + (right, rest'') = go rest' + in (HTNode left right, rest'') + go v = error ("Unknown type of Huffman tree leaf: " ++ show v) + +decodeHuffman :: HuffmanTree a -> [Word8] -> [a] +decodeHuffman huffman_tree = decodeBits huffman_tree . unpackBits + where + word8ToBools :: Word8 -> [Bool] + word8ToBools w = map (testBit w) [7, 6 .. 0] + + unpackBits :: [Word8] -> [Bool] + unpackBits = L.concatMap word8ToBools + + decodeBits :: HuffmanTree a -> [Bool] -> [a] + decodeBits tree bits = decodeBits' tree bits tree + where + decodeBits' _ [] _ = [] + decodeBits' (HTLeaf c) bs tree' = c : decodeBits' tree' bs tree' + decodeBits' (HTNode l r) (b:bs) tree' = decodeBits' next bs tree' + where next = if b then r else l + ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/RangeSwitch.hs ===================================== @@ -0,0 +1,97 @@ +{-# LANGUAGE LambdaCase #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE BlockArguments #-} +module Generator.RangeSwitch + where + +import Generator.WordEncoding +import Data.Word +import Data.Bifunctor (bimap) +import Generator.Huffman (encodeHuffman) +import Generator.HuffmanDecode (HuffmanTree) + +data Case a = Case + { caseMin :: Int + , caseMax :: Int + , caseConstant :: Either a [a] + } + deriving stock (Show) + +extractLookupIntList :: [Case a] -> [a] +extractLookupIntList = concat . (fmap \(Case _ _ cc) -> either (const []) id cc) + +ranges :: (Enum a, Eq a, Show a) => [a] -> [(Int,Int,a)] +ranges = \case + [] -> [] + (x:xs) -> reverse (go 0 0 x [] xs) + where + go mi ma v rs = \case + [] -> (mi,ma,v):rs + (x:xs) + | x == v -> go mi (ma+1) v rs xs + | otherwise -> go (ma+1) (ma+1) x ((mi,ma,v):rs) xs + +cases :: Int -> [a] -> [(Int,Int,a)] -> [Case a] +cases max_rep all_cats = go + where + go = \case + [] -> [] + (r@(mi,ma,v):rs) + | rangeSize r > max_rep -> Case mi ma (Left v) : go rs + | otherwise -> go_lookup mi ma (Left v) rs + + go_lookup rmi rma mv = \case + [] -> [Case rmi rma mv] + (r@(mi,ma,v):rs) + | rangeSize r > max_rep -> Case rmi rma mv : Case mi ma (Left v) : go rs + | otherwise -> go_lookup rmi ma (Right (take (ma-rmi+1) (drop rmi all_cats))) rs + + rangeSize :: Num a => (a, a, c) -> a + rangeSize (mi, ma, _) = ma - mi + 1 + +rangeCases :: (Enum a, Eq a, Show a) => Int -> [a] -> [Case a] +rangeCases max_char_length cats = cases max_char_length cats (ranges cats) + +data RangeTree a + = Leaf Int Int a + | Node Int Int (RangeTree a) (RangeTree a) + deriving stock (Show) + +buildRangeTree :: [Case a] -> RangeTree (Either a [a]) +buildRangeTree [(Case start end cat)] = Leaf start end cat +buildRangeTree ranges' = + let + mid = length ranges' `div` 2 + (leftRanges, rightRanges) = splitAt mid ranges' + (Case startL _ _) = head leftRanges + (Case _ endR _) = last rightRanges + in Node startL endR (buildRangeTree leftRanges) (buildRangeTree rightRanges) + +rangesToWord8 :: (Show a, Enum a, Ord a) => HuffmanTree a -> [Case a] -> [Case Word8] +rangesToWord8 htree = fmap \(Case mi ma c) -> + Case mi ma $ bimap toWord8 (encodeHuffman htree) c + +printCases :: Enum a => [Case a] -> String +printCases cases' = printCases' cases' + where + printCases' :: Enum a => [Case a] -> String + printCases' [] = " | otherwise = 29\n" + printCases' (Case mi ma mv : rs) = + case mv of + Right vv -> mconcat [" | n < ", show (ma + 1), " = lookupIntN \"...\"# (n - ", show mi, ") -- array size: ", show (fromIntegral (length vv) / fromIntegral (ma - mi + 1)) ++ " " ++ show (length vv), "\n"] ++ printCases' rs + Left v -> mconcat [" | n < ", show (ma + 1), " = ", show (fromEnum v), "\n"] ++ printCases' rs + +printRangeTree :: Show a => RangeTree (Either a [a]) -> String +printRangeTree tree = printWithIndent tree 0 + where + printWithIndent :: Show a => RangeTree (Either a [a]) -> Int -> String + printWithIndent (Leaf start end value) indent = + replicate indent ' ' ++ "Leaf " ++ show start ++ " " ++ show end ++ shown_value ++ "\n" + where + shown_value = case value of + Left x -> " " ++ show x + Right vv -> " -- array size: " ++ show (fromIntegral (length vv) / fromIntegral (end - start + 1)) ++ " " ++ show (length vv) + printWithIndent (Node start end left right) indent = + replicate indent ' ' ++ "Node " ++ show start ++ " " ++ show end ++ "\n" ++ + printWithIndent left (indent + 2) ++ + printWithIndent right (indent + 2) ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Generator/WordEncoding.hs ===================================== @@ -0,0 +1,40 @@ +module Generator.WordEncoding where + +import Data.Word + +toWord8 :: (Show a, Enum a) => a -> Word8 +toWord8 a = let w = fromEnum a in if 0 <= w && w <= 0xff + then fromIntegral w + else error $ "Cannot convert to Word8: " <> show a + +{-| Encode a list of values as a byte map, using their 'Enum' instance. + +__Note:__ 'Enum' instance must respect the following: + +* @fromEnum minBound >= 0x00@ +* @fromEnum maxBound <= 0xff@ +-} +enumMapToAddrLiteral :: + forall a. (Bounded a, Enum a, Show a) => + -- | Values to encode + [a] -> + -- | String to append + String -> + String +enumMapToAddrLiteral xs cs = foldr go cs xs + where + go :: a -> String -> String + go x acc = '\\' : shows (toWord8 x) acc + +-- Same as enumMapToAddrLiteral but for already converted to Word8 +mapToAddrLiteral :: + forall a. (Show a) => + -- | Values to encode + [a] -> + -- | String to append + String -> + String +mapToAddrLiteral xs cs = foldr go cs xs + where + go :: a -> String -> String + go x acc = '\\' : shows x acc ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs ===================================== @@ -33,6 +33,7 @@ import Streamly.Data.Fold (Fold) import System.Directory (createDirectoryIfMissing) import System.Environment (getEnv) import System.FilePath ((), (<.>)) +import Generator.GeneralCategory (GeneralCategory(Cn), generateGeneralCategoryCode) -- import qualified Data.Set as Set import Streamly.Data.Stream (Stream) @@ -51,17 +52,6 @@ import Prelude hiding (pred) -- Types ------------------------------------------------------------------------------- -data GeneralCategory = - Lu|Ll|Lt| --LC - Lm|Lo| --L - Mn|Mc|Me| --M - Nd|Nl|No| --N - Pc|Pd|Ps|Pe|Pi|Pf|Po| --P - Sm|Sc|Sk|So| --S - Zs|Zl|Zp| --Z - Cc|Cf|Cs|Co|Cn --C - deriving (Show, Bounded, Enum, Read) - data DecompType = DTCanonical | DTCompat | DTFont | DTNoBreak | DTInitial | DTMedial | DTFinal @@ -189,57 +179,6 @@ bitMapToAddrLiteral bs cs = foldr encode cs (unfoldr mkChunks bs) toByte :: [Bool] -> Int toByte xs = sum $ map (\i -> if xs !! i then 1 `shiftL` i else 0) [0..7] -genEnumBitmap :: - forall a. (Bounded a, Enum a, Show a) => - -- | Function name - String -> - -- | Default value - a -> - -- | List of values to encode - [a] -> - String -genEnumBitmap funcName def as = unlines - [ "{-# INLINE " <> funcName <> " #-}" - , funcName <> " :: Char -> Int" - , funcName <> " c = let n = ord c in if n >= " - <> show (length as) - <> " then " - <> show (fromEnum def) - <> " else lookup_bitmap n" - - , "{-# NOINLINE lookup_bitmap #-}" - , "lookup_bitmap :: Int -> Int" - , "lookup_bitmap n = lookupIntN bitmap# n" - , " where" - , " bitmap# = \"" <> enumMapToAddrLiteral as "\"#" - ] - -{-| Encode a list of values as a byte map, using their 'Enum' instance. - -__Note:__ 'Enum' instance must respect the following: - -* @fromEnum minBound >= 0x00@ -* @fromEnum maxBound <= 0xff@ --} -enumMapToAddrLiteral :: - forall a. (Bounded a, Enum a, Show a) => - -- | Values to encode - [a] -> - -- | String to append - String -> - String -enumMapToAddrLiteral xs cs = foldr go cs xs - - where - - go :: a -> String -> String - go x acc = '\\' : shows (toWord8 x) acc - - toWord8 :: a -> Word8 - toWord8 a = let w = fromEnum a in if 0 <= w && w <= 0xff - then fromIntegral w - else error $ "Cannot convert to Word8: " <> show a - {- [NOTE] Disabled generator (normalization) -- This bit of code is duplicated but this duplication allows us to reduce 2 -- dependencies on the executable. @@ -321,21 +260,7 @@ genGeneralCategoryModule moduleName = -- Regular entry else (_generalCategory a : acc, succ (_char a)) - done (acc, _) = unlines - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(generalCategory)" - , "where" - , "" - , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" - , "import GHC.Internal.Unicode.Bits (lookupIntN)" - , "" - , genEnumBitmap "generalCategory" Cn (reverse acc) - ] + done (acc, _) = generateGeneralCategoryCode mkModuleHeader moduleName 220 (reverse acc) readDecomp :: String -> (Maybe DecompType, Decomp) readDecomp s = ===================================== libraries/ghc-internal/tools/ucd2haskell/ucd.sh ===================================== @@ -71,6 +71,23 @@ run_generator() { # --core-prop XID_Continue \ # --core-prop Pattern_Syntax \ # --core-prop Pattern_White_Space + + echo "-- DO NOT EDIT IT HERE. It is automatically copied from ucd2haskell tool's Generator.HuffmanDecode" > "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + cat "$SCRIPT_DIR/exe/Generator/HuffmanDecode.hs" >> "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + + # See https://stackoverflow.com/a/22084103 + sed -i.bak -e "s/module Generator\.HuffmanDecode/module GHC.Internal.Unicode.Huffman/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import Data\.Word/import GHC.Internal.Word/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import Data\.Bits/import GHC.Internal.Bits/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import GHC\.Show/import GHC.Internal.Show/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import GHC\.Base/import GHC.Internal.Base/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" + sed -i.bak -e "s/import qualified GHC\.List/import qualified GHC.Internal.List/" "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs" + rm "$GHC_MODULE_PATH/GHC/Internal/Unicode/Huffman.hs.bak" } # Print help text ===================================== libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal ===================================== @@ -50,7 +50,13 @@ executable ucd2haskell ghc-options: -O2 hs-source-dirs: exe main-is: UCD2Haskell.hs - other-modules: Parser.Text + other-modules: + Parser.Text + Generator.RangeSwitch + Generator.GeneralCategory + Generator.WordEncoding + Generator.Huffman + Generator.HuffmanDecode build-depends: base >= 4.7 && < 4.20 , streamly-core >= 0.2.2 && < 0.3 @@ -60,3 +66,4 @@ executable ucd2haskell , containers >= 0.5 && < 0.7 , directory >= 1.3.6 && < 1.3.8 , filepath >= 1.4.2 && < 1.5 + , ghc-prim >= 0.11 && < 0.12 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2445dbfd8f5f826f1fcac09f06fc39101a8213ec...eade9d168e76d8484d849ab6b994d94fd85168d4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/2445dbfd8f5f826f1fcac09f06fc39101a8213ec...eade9d168e76d8484d849ab6b994d94fd85168d4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 14:45:19 2024 From: gitlab at gitlab.haskell.org (Zubin (@wz1000)) Date: Sun, 09 Jun 2024 10:45:19 -0400 Subject: [Git][ghc/ghc][wip/faststring-no-z] fixes Message-ID: <6665bfff84abb_32f88330ad220186610@gitlab.mail> Zubin pushed to branch wip/faststring-no-z at Glasgow Haskell Compiler / GHC Commits: 5a655108 by Zubin Duggal at 2024-06-09T16:44:49+02:00 fixes - - - - - 3 changed files: - compiler/GHC/Data/FastString.hs - ghc/Main.hs - rts/configure.ac Changes: ===================================== compiler/GHC/Data/FastString.hs ===================================== @@ -94,6 +94,7 @@ module GHC.Data.FastString -- ** Internal getFastStringTable, + getFastZStringTable, getFastStringZEncCounter, -- * PtrStrings @@ -358,6 +359,7 @@ hashToIndex# buckets# hash# = !(I# segmentBits#) = segmentBits size# = sizeofMutableArray# buckets# +{-# INLINE maybeResizeSegment #-} maybeResizeSegment :: forall a. (a -> Int) -> IORef (TableSegment a) -> IO (TableSegment a) maybeResizeSegment hashElem segmentRef = do segment@(TableSegment lock counter old#) <- readIORef segmentRef @@ -564,6 +566,9 @@ bucket_match fs sbs = go fs -- Non-inlining causes a small, but measurable performance regression, so let's force it. {-# INLINE bucket_match #-} + +{-# INLINE mkNewFastZString #-} + mkNewFastZString :: FastString -> IO FastZString mkNewFastZString (FastString uniq _ sbs) = do TableSegment lock _ buckets# <- readIORef segmentRef @@ -575,9 +580,9 @@ mkNewFastZString (FastString uniq _ sbs) = do -- The withMVar below is not dupable. It can lead to deadlock if it is -- only run partially and putMVar is not called after takeMVar. noDuplicate - n <- get_uid + _ <- get_uid let !new_fs = mkZFastString sbs - withMVar lock $ \_ -> insert n new_fs + withMVar lock $ \_ -> insert (I# hash#) new_fs where !(FastZStringTable uid segments#) = zstringTable get_uid = atomicFetchAddFastMut uid 1 @@ -706,6 +711,8 @@ unpackFS fs = utf8DecodeShortByteString $ fs_sbs fs zEncodeFS :: FastString -> FastZString zEncodeFS fs = inlinePerformIO $ mkNewFastZString fs +{-# INLINE zEncodeFS #-} + appendFS :: FastString -> FastString -> FastString appendFS fs1 fs2 = mkFastStringShortByteString $ (Semi.<>) (fs_sbs fs1) (fs_sbs fs2) @@ -742,6 +749,17 @@ getFastStringTable = where !(FastStringTable _ segments#) = stringTable +getFastZStringTable :: IO [[[FastZString]]] +getFastZStringTable = + forM [0 .. numSegments - 1] $ \(I# i#) -> do + let (# segmentRef #) = indexArray# segments# i# + TableSegment _ _ buckets# <- readIORef segmentRef + let bucketSize = I# (sizeofMutableArray# buckets#) + forM [0 .. bucketSize - 1] $ \(I# j#) -> + fmap (map (\(HashedFastZString _ s) -> s)) $ IO $ readArray# buckets# j# + where + !(FastZStringTable _ segments#) = zstringTable + getFastStringZEncCounter :: IO Int getFastStringZEncCounter = readFastMutInt counter where (FastZStringTable counter _) = zstringTable ===================================== ghc/Main.hs ===================================== @@ -1032,10 +1032,15 @@ dumpFinalStats logger = do when (logHasDumpFlag logger Opt_D_dump_faststrings) $ do fss <- getFastStringTable + fzss <- getFastZStringTable let ppr_table = fmap ppr_segment (fss `zip` [0..]) ppr_segment (s,n) = hang (text "Segment" <+> int n) 2 (vcat (fmap ppr_bucket (s `zip` [0..]))) ppr_bucket (b,n) = hang (text "Bucket" <+> int n) 2 (vcat (fmap ftext b)) putDumpFileMaybe logger Opt_D_dump_faststrings "FastStrings" FormatText (vcat ppr_table) + let ppr_table' = fmap ppr_segment' (fzss `zip` [0..]) + ppr_segment' (s,n) = hang (text "Segment" <+> int n) 2 (vcat (fmap ppr_bucket' (s `zip` [0..]))) + ppr_bucket' (b,n) = hang (text "Bucket" <+> int n) 2 (vcat (fmap (text . zString) b)) + putDumpFileMaybe logger Opt_D_dump_faststrings "FastZStrings" FormatText (vcat ppr_table') dumpFastStringStats :: Logger -> IO () dumpFastStringStats logger = do @@ -1053,6 +1058,7 @@ dumpFastStringStats logger = do , text "smallest segment: " <+> int (minimum bucketsPerSegment) , text "longest bucket: " <+> int (maximum entriesPerBucket) , text "has z-encoding: " <+> (hasZ `pcntOf` entries) + , text "z-encodings: " <+> int (hasZ) ]) -- we usually get more "has z-encoding" than "z-encoded", because -- when we z-encode a string it might hash to the exact same string, ===================================== rts/configure.ac ===================================== @@ -6,7 +6,7 @@ # see what flags are available. (Better yet, read the documentation!) # -AC_INIT([GHC run-time system], [1.0.2], [libraries at haskell.org], [rts]) +AC_INIT([GHC run-time system], [1.0.3], [libraries at haskell.org], [rts]) AC_CONFIG_MACRO_DIRS([../m4]) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5a6551084c439d95b42ff9b5f4b2633e447df688 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5a6551084c439d95b42ff9b5f4b2633e447df688 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 15:23:34 2024 From: gitlab at gitlab.haskell.org (Patrick (@soulomoon)) Date: Sun, 09 Jun 2024 11:23:34 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/add-entityinfo-hiefile-#24544 Message-ID: <6665c8f633646_32f88336f4854204943@gitlab.mail> Patrick pushed new branch wip/add-entityinfo-hiefile-#24544 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/add-entityinfo-hiefile-%2324544 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 16:45:47 2024 From: gitlab at gitlab.haskell.org (Alexander Foremny (@aforemny)) Date: Sun, 09 Jun 2024 12:45:47 -0400 Subject: [Git][ghc/ghc][wip/aforemny/ast] 4 commits: AST: remove `GHC.Types.SourceText` from `Language.Haskell.Syntax.Binds` Message-ID: <6665dc3b77b72_283f399b1ef0221b@gitlab.mail> Alexander Foremny pushed to branch wip/aforemny/ast at Glasgow Haskell Compiler / GHC Commits: f2ec2f73 by Alexander Foremny at 2024-06-09T10:52:57+02:00 AST: remove `GHC.Types.SourceText` from `Language.Haskell.Syntax.Binds` The `SCCFunSig` tracks the optional cost centre name as a `GHC.Types.SourceText.StringLiteral`. Since we want to keep it in the AST, we introduce an extension field `XSCCFunSigCC`. We have NOT merged it into the existing extension field `XSCCFunSig`. - - - - - f3216652 by Alexander Foremny at 2024-06-09T10:56:01+02:00 AST: remove `GHC.Types.SourceText.StringLiteral` from `Language.Haskell.Syntax.Expr` The `HsPragSCC` tracks the set cost centre SCC pragma as a `GHC.Types.SourceText.StringLiteral`. Since we want to keep it in the AST, we introduce an extension field `XSCCCC`. We have NOT merged it into the existing extension field `XSCC`. - - - - - eb734893 by Alexander Foremny at 2024-06-09T11:34:09+02:00 AST: remove `GHC.Types.SourceText.StringLiteral` from `Language.Haskell.Syntax.Decls` This commit does not really remove it, but argues that it will likely be moved out when `WithHsDocIdentifiers` is moved out. - - - - - 9565c263 by Alexander Foremny at 2024-06-09T12:01:21+02:00 AST: remove `GHC.Types.SourceText.SourceText` from `Language.Haskell.Syntax.Decls` Introduces an extension field each for the constructors of `WarningTxt` to abstract over `SourceText`. - - - - - 7 changed files: - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Unit/Module/Warnings.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Extension.hs Changes: ===================================== compiler/GHC/Hs/Binds.hs ===================================== @@ -714,6 +714,7 @@ type instance XSpecSig (GhcPass p) = [AddEpAnn] type instance XSpecInstSig (GhcPass p) = ([AddEpAnn], SourceText) type instance XMinimalSig (GhcPass p) = ([AddEpAnn], SourceText) type instance XSCCFunSig (GhcPass p) = ([AddEpAnn], SourceText) +type instance XSCCFunSigCC (GhcPass p) = StringLiteral type instance XCompleteMatchSig (GhcPass p) = ([AddEpAnn], SourceText) -- SourceText: Note [Pragma source text] in "GHC.Types.SourceText" type instance XXSig GhcPs = DataConCantHappen ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -429,6 +429,7 @@ instance NoAnn AnnsIf where -- --------------------------------------------------------------------- type instance XSCC (GhcPass _) = (AnnPragma, SourceText) +type instance XSCCCC (GhcPass _) = StringLiteral type instance XXPragE (GhcPass _) = DataConCantHappen type instance XCDotFieldOcc (GhcPass _) = AnnFieldLabel ===================================== compiler/GHC/Unit/Module/Warnings.hs ===================================== @@ -62,7 +62,7 @@ import GHC.Utils.Outputable import GHC.Unicode import Language.Haskell.Syntax.Extension -import Language.Haskell.Syntax.Decls (WarningTxt(..), InWarningCategory(..), XInWarningCategoryIn(), WarningCategory(..)) +import Language.Haskell.Syntax.Decls (WarningTxt(..), XWarningTxt, XDeprecatedTxt, InWarningCategory(..), XInWarningCategory, XInWarningCategoryIn(), WarningCategory(..)) import Data.List (isPrefixOf) @@ -73,6 +73,8 @@ fromWarningCategory => WarningCategory -> InWarningCategory (GhcPass pass) fromWarningCategory wc = InWarningCategory noAnn NoSourceText (noLocA wc) +type instance XInWarningCategory (GhcPass p) = SourceText + mkWarningCategory :: FastString -> WarningCategory mkWarningCategory = WarningCategory @@ -190,6 +192,9 @@ instance Outputable (WarningTxt (GhcPass p)) where NoSourceText -> pp_ws ds SourceText src -> ftext src <+> pp_ws ds <+> text "#-}" +type instance XWarningTxt (GhcPass p) = SourceText +type instance XDeprecatedTxt (GhcPass p) = SourceText + pp_ws :: [LocatedE (WithHsDocIdentifiers StringLiteral pass)] -> SDoc pp_ws [l] = ppr $ unLoc l pp_ws ws @@ -248,6 +253,9 @@ type ExportWarnNames pass = [(Name, WarningTxt pass)] deriving instance ( Eq (IdP (GhcPass p)), + Eq (XWarningTxt (GhcPass p)), + Eq (XDeprecatedTxt (GhcPass p)), + Eq (XInWarningCategory (GhcPass p)), Eq (XInWarningCategoryIn (GhcPass p)) ) => Eq (Warnings (GhcPass p)) ===================================== compiler/Language/Haskell/Syntax/Binds.hs ===================================== @@ -37,7 +37,6 @@ import GHC.Data.Bag (Bag) import GHC.Types.Basic (InlinePragma) import GHC.Data.BooleanFormula (LBooleanFormula) -import GHC.Types.SourceText (StringLiteral) import Data.Void import Data.Bool @@ -478,7 +477,7 @@ data Sig pass | SCCFunSig (XSCCFunSig pass) (LIdP pass) -- Function name - (Maybe (XRec pass StringLiteral)) + (Maybe (XRec pass (XSCCFunSigCC pass))) -- cost centre name -- | A complete match pragma -- -- > {-# COMPLETE C, D [:: T] #-} ===================================== compiler/Language/Haskell/Syntax/Decls.hs ===================================== @@ -87,8 +87,8 @@ module Language.Haskell.Syntax.Decls ( -- * Grouping HsGroup(..), hsGroupInstDecls, -- * Warnings - WarningTxt(..), InWarningCategory(..), WarningCategory(..), - XInWarningCategoryIn, + WarningTxt(..), XWarningTxt, XDeprecatedTxt, InWarningCategory(..), + XInWarningCategory, WarningCategory(..), XInWarningCategoryIn, ) where -- friends: @@ -110,7 +110,8 @@ import GHC.Core.Type (Specificity) import GHC.Utils.Panic.Plain ( assert ) import GHC.Hs.Doc (LHsDoc, WithHsDocIdentifiers) -- ROMES:TODO Discuss in #21592 whether this is parsed AST or base AST -import GHC.Types.SourceText (StringLiteral, SourceText) +-- TODO(ghc-import): `StringLiteral` is only used in `WithHsDocIdentifiers`, which presumably get moved out themselves. +import GHC.Types.SourceText (StringLiteral) import Control.Monad import Data.Data hiding (TyCon, Fixity, Infix) @@ -1800,15 +1801,21 @@ data WarningTxt pass (Maybe (XRec pass (InWarningCategory pass))) -- ^ Warning category attached to this WARNING pragma, if any; -- see Note [Warning categories] - SourceText + (XWarningTxt pass) [XRec pass (WithHsDocIdentifiers StringLiteral pass)] | DeprecatedTxt - SourceText + (XDeprecatedTxt pass) [XRec pass (WithHsDocIdentifiers StringLiteral pass)] deriving (Generic) +type family XWarningTxt p + +type family XDeprecatedTxt p + deriving instance - ( Eq (XRec pass (InWarningCategory pass)), + ( Eq (XWarningTxt pass), + Eq (XDeprecatedTxt pass), + Eq (XRec pass (InWarningCategory pass)), Eq (XRec pass (WithHsDocIdentifiers StringLiteral pass)) ) => Eq (WarningTxt pass) @@ -1861,15 +1868,17 @@ the possibility of them being infinite. data InWarningCategory pass = InWarningCategory { iwc_in :: !(XInWarningCategoryIn pass), - iwc_st :: !SourceText, + iwc_st :: !(XInWarningCategory pass), iwc_wc :: (XRec pass WarningCategory) } +type family XInWarningCategory p type family XInWarningCategoryIn p deriving instance ( + Eq (XInWarningCategory pass), Eq (XInWarningCategoryIn pass), Eq (XRec pass WarningCategory) ) @@ -1879,6 +1888,7 @@ deriving instance Typeable (InWarningCategory pass) deriving instance ( Data pass, + Data (XInWarningCategory pass), Data (XInWarningCategoryIn pass), Data (XRec pass WarningCategory) ) ===================================== compiler/Language/Haskell/Syntax/Expr.hs ===================================== @@ -32,7 +32,7 @@ import Language.Haskell.Syntax.Binds -- others: import GHC.Types.Fixity (LexicalFixity(Infix), Fixity) -import GHC.Types.SourceText (StringLiteral, SourceText) +import GHC.Types.SourceText (SourceText) import GHC.Data.FastString (FastString) @@ -598,7 +598,7 @@ data DotFieldOcc p -- | A pragma, written as {-# ... #-}, that may appear within an expression. data HsPragE p = HsPragSCC (XSCC p) - StringLiteral -- "set cost centre" SCC pragma + (XSCCCC p) -- "set cost centre" SCC pragma -- | - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnOpen', -- 'GHC.Parser.Annotation.AnnOpen' @'{-\# GENERATED'@, ===================================== compiler/Language/Haskell/Syntax/Extension.hs ===================================== @@ -214,6 +214,7 @@ type family XSpecSig x type family XSpecInstSig x type family XMinimalSig x type family XSCCFunSig x +type family XSCCFunSigCC x type family XCompleteMatchSig x type family XXSig x @@ -458,6 +459,7 @@ type family XXDotFieldOcc x -- ------------------------------------- -- HsPragE type families type family XSCC x +type family XSCCCC x type family XXPragE x View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/523dd6642535c234d0bfd40fe80c679db281779b...9565c2630e20a1b5d0ea57d26a6550a9c96c0fba -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/523dd6642535c234d0bfd40fe80c679db281779b...9565c2630e20a1b5d0ea57d26a6550a9c96c0fba You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 16:52:27 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Sun, 09 Jun 2024 12:52:27 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/kirchner/ttg-zurich Message-ID: <6665ddcb517a1_283f39a7286c22355@gitlab.mail> Fabian Kirchner pushed new branch wip/kirchner/ttg-zurich at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/kirchner/ttg-zurich You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 16:55:20 2024 From: gitlab at gitlab.haskell.org (Cyrill Brunner (@Adowrath)) Date: Sun, 09 Jun 2024 12:55:20 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/adowrath/ast-migrate-hs-src-bang Message-ID: <6665de78cae09_283f39af8a20227d6@gitlab.mail> Cyrill Brunner pushed new branch wip/adowrath/ast-migrate-hs-src-bang at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/adowrath/ast-migrate-hs-src-bang You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 17:15:38 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Sun, 09 Jun 2024 13:15:38 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] 4 commits: ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Message-ID: <6665e33aa690f_283f39ec228c282b0@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: 1b781d60 by Fabian Kirchner at 2024-06-09T19:06:53+02:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - f3df7507 by Fabian Kirchner at 2024-06-09T19:06:57+02:00 ttg: Move some AST types into Language.Haskell.Syntax.Basic In particular, we move: * TopLevelFlag * TypeOrData * TyConFlavour Progress towards #21592 - - - - - 73a4f29b by Adowrath at 2024-06-09T19:07:13+02:00 ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type Progress towards #21592 This splits HsSrcBang up, creating the new HsBang within `Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness and strictness information, while `HsSrcBang` only adds the SourceText for usage within the compiler directly. Inside the AST, to preserve the SourceText, it is hidden behind the pre-existing extension point `XBindTy`. All other occurrences of `HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when interacting with the `BindTy` constructor, the hidden `SourceText` is extracted/inserted into the `XBindTy` extension point. `GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for convenience. A constructor function `mkHsSrcBang` that takes all individual components has been added. Two exceptions has been made though: - The `Outputable HsSrcBang` instance is replaced by `Outputable HsBang`. While being only GHC-internal, the only place it's used is in outputting `HsBangTy` constructors -- which already have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just to ignore the `SourceText` anyway. - The error `TcRnUnexpectedAnnotation` did not use the `SourceText`, so it too now only holds a `HsBang`. - - - - - f0de696f by Mauricio at 2024-06-09T19:15:00+02:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/CoreToIface.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Build.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var.hs-boot - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Lit.hs - + compiler/Language/Haskell/Syntax/Specificity.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/ghc.cabal.in - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0075a8b851ed08ec39456fe16387c75504fb2fdc...f0de696f3be8774ff0ee606c0d49964e09a7e426 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0075a8b851ed08ec39456fe16387c75504fb2fdc...f0de696f3be8774ff0ee606c0d49964e09a7e426 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 17:18:44 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Sun, 09 Jun 2024 13:18:44 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Message-ID: <6665e3f48f4c1_283f3910193883125a@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: 68abf0c8 by Mauricio at 2024-06-09T19:18:36+02:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - 2 changed files: - compiler/GHC/Hs/Lit.hs - compiler/Language/Haskell/Syntax/Lit.hs Changes: ===================================== compiler/GHC/Hs/Lit.hs ===================================== @@ -35,6 +35,7 @@ import GHC.Hs.Extension import Language.Haskell.Syntax.Expr ( HsExpr ) import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Lit +import GHC.Utils.Panic (panic) {- ************************************************************************ @@ -253,3 +254,15 @@ negateOverLitVal :: OverLitVal -> OverLitVal negateOverLitVal (HsIntegral i) = HsIntegral (negateIntegralLit i) negateOverLitVal (HsFractional f) = HsFractional (negateFractionalLit f) negateOverLitVal _ = panic "negateOverLitVal: argument is not a number" + +instance (Ord (XXOverLit p)) => Ord (HsOverLit p) where + compare (OverLit _ val1) (OverLit _ val2) = val1 `compare` val2 + compare (XOverLit val1) (XOverLit val2) = val1 `compare` val2 + compare _ _ = panic "Ord HsOverLit" + +-- Comparison operations are needed when grouping literals +-- for compiling pattern-matching (module GHC.HsToCore.Match.Literal) +instance (Eq (XXOverLit p)) => Eq (HsOverLit p) where + (OverLit _ val1) == (OverLit _ val2) = val1 == val2 + (XOverLit val1) == (XOverLit val2) = val1 == val2 + _ == _ = panic "Eq HsOverLit" ===================================== compiler/Language/Haskell/Syntax/Lit.hs ===================================== @@ -20,7 +20,6 @@ module Language.Haskell.Syntax.Lit where import Language.Haskell.Syntax.Extension -import GHC.Utils.Panic (panic) import GHC.Types.SourceText (IntegralLit, FractionalLit, SourceText) import GHC.Core.Type (Type) @@ -128,24 +127,12 @@ data OverLitVal | HsIsString !SourceText !FastString -- ^ String-looking literals deriving Data --- Comparison operations are needed when grouping literals --- for compiling pattern-matching (module GHC.HsToCore.Match.Literal) -instance (Eq (XXOverLit p)) => Eq (HsOverLit p) where - (OverLit _ val1) == (OverLit _ val2) = val1 == val2 - (XOverLit val1) == (XOverLit val2) = val1 == val2 - _ == _ = panic "Eq HsOverLit" - instance Eq OverLitVal where (HsIntegral i1) == (HsIntegral i2) = i1 == i2 (HsFractional f1) == (HsFractional f2) = f1 == f2 (HsIsString _ s1) == (HsIsString _ s2) = s1 == s2 _ == _ = False -instance (Ord (XXOverLit p)) => Ord (HsOverLit p) where - compare (OverLit _ val1) (OverLit _ val2) = val1 `compare` val2 - compare (XOverLit val1) (XOverLit val2) = val1 `compare` val2 - compare _ _ = panic "Ord HsOverLit" - instance Ord OverLitVal where compare (HsIntegral i1) (HsIntegral i2) = i1 `compare` i2 compare (HsIntegral _) (HsFractional _) = LT View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/68abf0c8cb2aa9e17e2dcf7e1fe1126437753172 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/68abf0c8cb2aa9e17e2dcf7e1fe1126437753172 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 17:22:20 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Sun, 09 Jun 2024 13:22:20 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ttg-zurich] Split TTG orphans from internal `Fixity` data type Message-ID: <6665e4cc20cd3_283f3911829f432731@gitlab.mail> Fabian Kirchner pushed to branch wip/kirchner/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: be146de9 by romes at 2024-06-09T19:22:00+02:00 Split TTG orphans from internal `Fixity` data type Filling in missing instances and creating a separate "semantic" datatype are two different layers of abstraction, and so we should create two different modules for them. Fixed tests and updated Haddock submodule. Fixed arrow desugaring bug. (This was dead code before.) - - - - - 30 changed files: - compiler/GHC/Builtin/PrimOps.hs - + compiler/GHC/Hs/Basic.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Fixity.hs - compiler/GHC/Types/Fixity/Env.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/ghc.cabal.in - testsuite/tests/count-deps/CountDepsAst.stdout The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/be146de9b7f1c967fff72d4215c9521bbdf7ae06 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/be146de9b7f1c967fff72d4215c9521bbdf7ae06 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 18:07:34 2024 From: gitlab at gitlab.haskell.org (Cyrill Brunner (@Adowrath)) Date: Sun, 09 Jun 2024 14:07:34 -0400 Subject: [Git][ghc/ghc] Deleted branch wip/adowrath/removing-rdrname-from-syntax-type Message-ID: <6665ef66d49bf_283f3916e6968404ad@gitlab.mail> Cyrill Brunner deleted branch wip/adowrath/removing-rdrname-from-syntax-type at Glasgow Haskell Compiler / GHC -- You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 19:28:07 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 09 Jun 2024 15:28:07 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/supersven/fix-MO_XX_Conv-folding Message-ID: <666602477ec78_283f392138f60455bc@gitlab.mail> Sven Tennie pushed new branch wip/supersven/fix-MO_XX_Conv-folding at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/supersven/fix-MO_XX_Conv-folding You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 19:35:42 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 09 Jun 2024 15:35:42 -0400 Subject: [Git][ghc/ghc][wip/supersven/ghc-9.10-riscv-ncg] 2 commits: Increase C compiler happiness Message-ID: <6666040eb5f15_283f3923650e047773@gitlab.mail> Sven Tennie pushed to branch wip/supersven/ghc-9.10-riscv-ncg at Glasgow Haskell Compiler / GHC Commits: 08812af4 by Sven Tennie at 2024-06-09T10:10:39+00:00 Increase C compiler happiness New warnings (-Werror) prevented the validate flavour from being built. - - - - - 5d82e908 by Sven Tennie at 2024-06-09T19:33:09+00:00 Ignore signedness for MO_XX_Conv MO_XX_Conv is used on (unsigned) words, too. Interpreting them as signed may lead to weird conversions / sign-extensions: E.g. on RISCV64 this conversion happened for a Word64#: %MO_XX_Conv_W32_W64(4294967293 :: W32) -> CmmLit (CmmInt (-3) W64) - - - - - 4 changed files: - compiler/GHC/Cmm/Opt.hs - rts/adjustor/LibffiAdjustor.c - rts/linker/Elf.c - rts/linker/elf_reloc_riscv64.c Changes: ===================================== compiler/GHC/Cmm/Opt.hs ===================================== @@ -68,7 +68,7 @@ cmmMachOpFoldM _ op [CmmLit (CmmInt x rep)] MO_SF_Conv _from to -> CmmLit (CmmFloat (fromInteger x) to) MO_SS_Conv from to -> CmmLit (CmmInt (narrowS from x) to) MO_UU_Conv from to -> CmmLit (CmmInt (narrowU from x) to) - MO_XX_Conv from to -> CmmLit (CmmInt (narrowS from x) to) + MO_XX_Conv from to -> CmmLit (CmmInt (narrowU from x) to) _ -> panic $ "cmmMachOpFoldM: unknown unary op: " ++ show op ===================================== rts/adjustor/LibffiAdjustor.c ===================================== @@ -197,8 +197,9 @@ createAdjustor (int cconv, // On Linux the parameters of __builtin___clear_cache are currently unused. // Add them anyways for future compatibility. (I.e. the parameters couldn't // be checked during development.) + // TODO: Check the upper boundary e.g. with a debugger. __builtin___clear_cache((void *)code, - (void *)code + instrCount * sizeof(uint64_t)); + (void *)((uint64_t *) code + instrCount)); // Memory barrier to ensure nothing circumvents the fence.i / cache flush. SEQ_CST_FENCE(); #endif ===================================== rts/linker/Elf.c ===================================== @@ -1128,9 +1128,9 @@ end: return result; } -// the aarch64 linker uses relocacteObjectCodeAarch64, -// see elf_reloc_aarch64.{h,c} -#if !defined(aarch64_HOST_ARCH) +// the aarch64 and riscv64 linkers use relocacteObjectCodeAarch64, +// see elf_reloc_aarch64.{h,c}, elf_reloc_riscv64.{h,c} +#if !defined(aarch64_HOST_ARCH) && !defined(riscv64_HOST_ARCH) /* Do ELF relocations which lack an explicit addend. All x86-linux and arm-linux relocations appear to be of this form. */ ===================================== rts/linker/elf_reloc_riscv64.c ===================================== @@ -114,6 +114,7 @@ char *relocationTypeToString(Elf64_Xword type) { #define Page(x) ((x) & ~0xFFF) +STG_NORETURN int32_t decodeAddendRISCV64(Section *section STG_UNUSED, Elf_Rel *rel STG_UNUSED) { debugBelch("decodeAddendRISCV64: Relocations with explicit addend are not " @@ -430,7 +431,7 @@ int32_t computeAddend(ElfRelocationATable * relaTab, unsigned relNo, Elf_Rel *re // relocations aren't pure, but this is how LLVM does it. And, calculating // the lower 12 bit without any relation ship to the GOT entry's address // makes no sense either. - for (unsigned i = relNo; i >= 0 ; i--) { + for (int64_t i = relNo; i >= 0 ; i--) { Elf_Rela *rel_prime = &relaTab->relocations[i]; addr_t P_prime = @@ -459,7 +460,7 @@ int32_t computeAddend(ElfRelocationATable * relaTab, unsigned relNo, Elf_Rel *re IF_DEBUG(linker, debugBelch( "Found matching relocation: %s (P: 0x%lx, S: 0x%lx, " - "sym-name: %s) -> %s (P: 0x%lx, S: 0x%lx, sym-name: %s, relNo: %u)", + "sym-name: %s) -> %s (P: 0x%lx, S: %p, sym-name: %s, relNo: %ld)", relocationTypeToString(rel->r_info), P, S, symbol->name, relocationTypeToString(rel_prime->r_info), P_prime, symbol_prime->addr, symbol_prime->name, i)); @@ -492,7 +493,7 @@ int32_t computeAddend(ElfRelocationATable * relaTab, unsigned relNo, Elf_Rel *re SymbolExtra *symbolExtra = makeSymbolExtra(oc, ELF_R_SYM(rel->r_info), S); addr_t* FAKE_GOT_S = &symbolExtra->addr; IF_DEBUG(linker, debugBelch("R_RISCV_CALL_PLT w/ SymbolExtra = %p , " - "entry = 0x%lx\n", + "entry = %p\n", symbolExtra, FAKE_GOT_S)); GOT_Target = (addr_t) FAKE_GOT_S; } @@ -515,7 +516,6 @@ int32_t computeAddend(ElfRelocationATable * relaTab, unsigned relNo, Elf_Rel *re case R_RISCV_ADD32: FALLTHROUGH; case R_RISCV_ADD64: - FALLTHROUGH; return S + A; // Add V when the value is set case R_RISCV_SUB6: FALLTHROUGH; @@ -526,7 +526,6 @@ int32_t computeAddend(ElfRelocationATable * relaTab, unsigned relNo, Elf_Rel *re case R_RISCV_SUB32: FALLTHROUGH; case R_RISCV_SUB64: - FALLTHROUGH; return S + A; // Subtract from V when value is set case R_RISCV_SET6: FALLTHROUGH; @@ -535,7 +534,6 @@ int32_t computeAddend(ElfRelocationATable * relaTab, unsigned relNo, Elf_Rel *re case R_RISCV_SET16: FALLTHROUGH; case R_RISCV_SET32: - FALLTHROUGH; return S + A; case R_RISCV_RELAX: case R_RISCV_ALIGN: @@ -563,7 +561,7 @@ int32_t computeAddend(ElfRelocationATable * relaTab, unsigned relNo, Elf_Rel *re addr_t* FAKE_GOT_S = &symbolExtra->addr; addr_t res = (addr_t) FAKE_GOT_S + A - P; IF_DEBUG(linker, debugBelch("R_RISCV_GOT_HI20 w/ SymbolExtra = %p , " - "entry = 0x%lx , reloc-addend = 0x%lu ", + "entry = %p , reloc-addend = 0x%lu ", symbolExtra, FAKE_GOT_S, res)); return res; } @@ -640,12 +638,13 @@ void flushInstructionCacheRISCV64(ObjectCode *oc) { /* The main object code */ void *codeBegin = oc->image + oc->misalignment; - __builtin___clear_cache(codeBegin, codeBegin + oc->fileSize); + // TODO: Check the upper boundary e.g. with a debugger. + __builtin___clear_cache(codeBegin, (void*) ((uint64_t*) codeBegin + oc->fileSize)); /* Jump Islands */ + // TODO: Check the upper boundary e.g. with a debugger. __builtin___clear_cache((void *)oc->symbol_extras, - (void *)oc->symbol_extras + - sizeof(SymbolExtra) * oc->n_symbol_extras); + (void *)(oc->symbol_extras + oc->n_symbol_extras)); // Memory barrier to ensure nothing circumvents the fence.i / cache flushes. SEQ_CST_FENCE(); View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/53da5e54a2021cc9042a9a3274dcd5bf840c6d6c...5d82e90884a61740476d00bbf000a8d31143c37f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/53da5e54a2021cc9042a9a3274dcd5bf840c6d6c...5d82e90884a61740476d00bbf000a8d31143c37f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 22:13:21 2024 From: gitlab at gitlab.haskell.org (Alexander Foremny (@aforemny)) Date: Sun, 09 Jun 2024 18:13:21 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/aforemny/parameterize-source-text-lits-over-pass Message-ID: <66662901ccba1_235737eb2d64237bd@gitlab.mail> Alexander Foremny pushed new branch wip/aforemny/parameterize-source-text-lits-over-pass at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/aforemny/parameterize-source-text-lits-over-pass You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 22:37:30 2024 From: gitlab at gitlab.haskell.org (Alexander Foremny (@aforemny)) Date: Sun, 09 Jun 2024 18:37:30 -0400 Subject: [Git][ghc/ghc][wip/aforemny/parameterize-source-text-lits-over-pass] 4 commits: AST: StringLiteral -> StringLit (type) Message-ID: <66662eaaa45b7_235737119133c23951@gitlab.mail> Alexander Foremny pushed to branch wip/aforemny/parameterize-source-text-lits-over-pass at Glasgow Haskell Compiler / GHC Commits: 3db2fd41 by Alexander Foremny at 2024-06-10T00:18:33+02:00 AST: StringLiteral -> StringLit (type) `GHC.Types.SourceText.StringLiteral` does not abbreviate "Literal", while `GHC.Types.SourceText.{IntegralLit,FractionalLit}` do. To increase consistency, `StringLiteral` was renamed to `StringLit`. - - - - - 36bb8780 by Alexander Foremny at 2024-06-10T00:18:37+02:00 AST: StringLiteral -> SL (data constructor) `GHC.Types.SourceText.StringLit` has data constructor `StringLiteral`, while `GHC.Types.SourceText.{IntegralLit,FractionalLit}` have data constructors `{IL,FL}`. To increase consistency, the data constructor `StringLiteral` was renamed to `SL`. - - - - - 7bf2b5df by Alexander Foremny at 2024-06-10T00:18:37+02:00 AST: use `StringLit` for `HsIsString` While `OverLitVal`'s data constructors `HsIntegral`, `HsFractional` carried `IntegralLit`, `FractionalLit` types, `HsIsString` carries only `SourceText` and `FastString`. We will want to parameterize over `SourceText`, which `StringLit`s will support. So we change `HsIsString` to carry a `StringLit`. - - - - - 96c93239 by Alexander Foremny at 2024-06-10T00:35:48+02:00 AST: parameterize `GHC.Types.SourceText`'s literals over `pass` In order to move `GHC.Types.SourceText.SourceText` out of `Language.Haskell`, we parameterize `GHC.Types.SourceText`'s literals by `pass`, and replace, say, `IntegralLit`'s `SourceText` field by `XIntegralLit pass`. - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Pmc/Solver/Types.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/HaddockLex.x - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/ThToHs.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a0b0dccfad472073fbf2edbee68bd9e788134908...96c93239e3083abcf8f0352b490c4f8999cd3e27 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a0b0dccfad472073fbf2edbee68bd9e788134908...96c93239e3083abcf8f0352b490c4f8999cd3e27 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 9 22:57:07 2024 From: gitlab at gitlab.haskell.org (Zubin (@wz1000)) Date: Sun, 09 Jun 2024 18:57:07 -0400 Subject: [Git][ghc/ghc][wip/faststring-no-z] fixes Message-ID: <66663342f345b_23573713922082412f@gitlab.mail> Zubin pushed to branch wip/faststring-no-z at Glasgow Haskell Compiler / GHC Commits: 71e095da by Zubin Duggal at 2024-06-10T00:56:53+02:00 fixes - - - - - 4 changed files: - compiler/GHC/Data/FastString.hs - ghc/Main.hs - rts/configure.ac - testsuite/tests/th/T10279.stderr Changes: ===================================== compiler/GHC/Data/FastString.hs ===================================== @@ -94,6 +94,7 @@ module GHC.Data.FastString -- ** Internal getFastStringTable, + getFastZStringTable, getFastStringZEncCounter, -- * PtrStrings @@ -358,6 +359,7 @@ hashToIndex# buckets# hash# = !(I# segmentBits#) = segmentBits size# = sizeofMutableArray# buckets# +{-# INLINE maybeResizeSegment #-} maybeResizeSegment :: forall a. (a -> Int) -> IORef (TableSegment a) -> IO (TableSegment a) maybeResizeSegment hashElem segmentRef = do segment@(TableSegment lock counter old#) <- readIORef segmentRef @@ -564,6 +566,9 @@ bucket_match fs sbs = go fs -- Non-inlining causes a small, but measurable performance regression, so let's force it. {-# INLINE bucket_match #-} + +{-# INLINE mkNewFastZString #-} + mkNewFastZString :: FastString -> IO FastZString mkNewFastZString (FastString uniq _ sbs) = do TableSegment lock _ buckets# <- readIORef segmentRef @@ -575,9 +580,9 @@ mkNewFastZString (FastString uniq _ sbs) = do -- The withMVar below is not dupable. It can lead to deadlock if it is -- only run partially and putMVar is not called after takeMVar. noDuplicate - n <- get_uid + _ <- get_uid let !new_fs = mkZFastString sbs - withMVar lock $ \_ -> insert n new_fs + withMVar lock $ \_ -> insert (I# hash#) new_fs where !(FastZStringTable uid segments#) = zstringTable get_uid = atomicFetchAddFastMut uid 1 @@ -706,6 +711,8 @@ unpackFS fs = utf8DecodeShortByteString $ fs_sbs fs zEncodeFS :: FastString -> FastZString zEncodeFS fs = inlinePerformIO $ mkNewFastZString fs +{-# INLINE zEncodeFS #-} + appendFS :: FastString -> FastString -> FastString appendFS fs1 fs2 = mkFastStringShortByteString $ (Semi.<>) (fs_sbs fs1) (fs_sbs fs2) @@ -742,6 +749,17 @@ getFastStringTable = where !(FastStringTable _ segments#) = stringTable +getFastZStringTable :: IO [[[FastZString]]] +getFastZStringTable = + forM [0 .. numSegments - 1] $ \(I# i#) -> do + let (# segmentRef #) = indexArray# segments# i# + TableSegment _ _ buckets# <- readIORef segmentRef + let bucketSize = I# (sizeofMutableArray# buckets#) + forM [0 .. bucketSize - 1] $ \(I# j#) -> + fmap (map (\(HashedFastZString _ s) -> s)) $ IO $ readArray# buckets# j# + where + !(FastZStringTable _ segments#) = zstringTable + getFastStringZEncCounter :: IO Int getFastStringZEncCounter = readFastMutInt counter where (FastZStringTable counter _) = zstringTable ===================================== ghc/Main.hs ===================================== @@ -1032,10 +1032,15 @@ dumpFinalStats logger = do when (logHasDumpFlag logger Opt_D_dump_faststrings) $ do fss <- getFastStringTable + fzss <- getFastZStringTable let ppr_table = fmap ppr_segment (fss `zip` [0..]) ppr_segment (s,n) = hang (text "Segment" <+> int n) 2 (vcat (fmap ppr_bucket (s `zip` [0..]))) ppr_bucket (b,n) = hang (text "Bucket" <+> int n) 2 (vcat (fmap ftext b)) putDumpFileMaybe logger Opt_D_dump_faststrings "FastStrings" FormatText (vcat ppr_table) + let ppr_table' = fmap ppr_segment' (fzss `zip` [0..]) + ppr_segment' (s,n) = hang (text "Segment" <+> int n) 2 (vcat (fmap ppr_bucket' (s `zip` [0..]))) + ppr_bucket' (b,n) = hang (text "Bucket" <+> int n) 2 (vcat (fmap (text . zString) b)) + putDumpFileMaybe logger Opt_D_dump_faststrings "FastZStrings" FormatText (vcat ppr_table') dumpFastStringStats :: Logger -> IO () dumpFastStringStats logger = do @@ -1053,6 +1058,7 @@ dumpFastStringStats logger = do , text "smallest segment: " <+> int (minimum bucketsPerSegment) , text "longest bucket: " <+> int (maximum entriesPerBucket) , text "has z-encoding: " <+> (hasZ `pcntOf` entries) + , text "z-encodings: " <+> int (hasZ) ]) -- we usually get more "has z-encoding" than "z-encoded", because -- when we z-encode a string it might hash to the exact same string, ===================================== rts/configure.ac ===================================== @@ -6,7 +6,7 @@ # see what flags are available. (Better yet, read the documentation!) # -AC_INIT([GHC run-time system], [1.0.2], [libraries at haskell.org], [rts]) +AC_INIT([GHC run-time system], [1.0.3], [libraries at haskell.org], [rts]) AC_CONFIG_MACRO_DIRS([../m4]) ===================================== testsuite/tests/th/T10279.stderr ===================================== @@ -1,11 +1,11 @@ T10279.hs:10:9: error: [GHC-51294] • Failed to load interface for ‘A’. - no unit id matching ‘rts-1.0.2’ was found + no unit id matching ‘rts-1.0.3’ was found (This unit ID looks like the source package ID; the real unit ID is ‘rts’) • In the untyped splice: $(conE (Name (mkOccName "Foo") - (NameG VarName (mkPkgName "rts-1.0.2") (mkModName "A")))) + (NameG VarName (mkPkgName "rts-1.0.3") (mkModName "A")))) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/71e095da3745c7f1d30d89cbb59c22dc80801d23 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/71e095da3745c7f1d30d89cbb59c22dc80801d23 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 01:02:37 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sun, 09 Jun 2024 21:02:37 -0400 Subject: [Git][ghc/ghc][master] JS: establish single source of truth for symbols Message-ID: <666650ad29140_2357372629dd0359aa@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - 19 changed files: - compiler/GHC/JS/Ident.hs - compiler/GHC/JS/JStg/Monad.hs - compiler/GHC/JS/JStg/Syntax.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Syntax.hs - compiler/GHC/StgToJS.hs - compiler/GHC/StgToJS/Apply.hs - compiler/GHC/StgToJS/Arg.hs - compiler/GHC/StgToJS/Closure.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/FFI.hs - compiler/GHC/StgToJS/Heap.hs - compiler/GHC/StgToJS/Ids.hs - compiler/GHC/StgToJS/Linker/Linker.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/StgToJS/Object.hs - compiler/GHC/StgToJS/Prim.hs - compiler/GHC/StgToJS/Profiling.hs - compiler/GHC/StgToJS/Regs.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6bd850e887b82c5a28bdacf5870d3dc2fc0f5091 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6bd850e887b82c5a28bdacf5870d3dc2fc0f5091 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 01:03:20 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sun, 09 Jun 2024 21:03:20 -0400 Subject: [Git][ghc/ghc][master] rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS Message-ID: <666650d844e8c_235737276012c3907c@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - 2 changed files: - rts/Task.c - rts/Task.h Changes: ===================================== rts/Task.c ===================================== @@ -52,7 +52,7 @@ Mutex all_tasks_mutex; // A thread-local-storage key that we can use to get access to the // current thread's Task structure. #if defined(THREADED_RTS) -# if defined(MYTASK_USE_TLV) +# if CC_SUPPORTS_TLS __thread Task *my_task; # else ThreadLocalKey currentTaskKey; @@ -75,7 +75,7 @@ initTaskManager (void) peakWorkerCount = 0; tasksInitialized = 1; #if defined(THREADED_RTS) -#if !defined(MYTASK_USE_TLV) +#if !CC_SUPPORTS_TLS newThreadLocalKey(¤tTaskKey); #endif initMutex(&all_tasks_mutex); @@ -109,7 +109,7 @@ freeTaskManager (void) #if defined(THREADED_RTS) closeMutex(&all_tasks_mutex); -#if !defined(MYTASK_USE_TLV) +#if !CC_SUPPORTS_TLS freeThreadLocalKey(¤tTaskKey); #endif #endif ===================================== rts/Task.h ===================================== @@ -265,11 +265,7 @@ extern uint32_t peakWorkerCount; // A thread-local-storage key that we can use to get access to the // current thread's Task structure. #if defined(THREADED_RTS) -#if ((defined(linux_HOST_OS) && \ - (defined(i386_HOST_ARCH) || defined(x86_64_HOST_ARCH))) || \ - (defined(mingw32_HOST_OS) && __GNUC__ >= 4 && __GNUC_MINOR__ >= 4)) && \ - (!defined(CC_LLVM_BACKEND)) -#define MYTASK_USE_TLV +#if CC_SUPPORTS_TLS extern __thread Task *my_task; #else extern ThreadLocalKey currentTaskKey; @@ -287,7 +283,7 @@ extern Task *my_task; INLINE_HEADER Task * myTask (void) { -#if defined(THREADED_RTS) && !defined(MYTASK_USE_TLV) +#if defined(THREADED_RTS) && !CC_SUPPORTS_TLS return (Task*) getThreadLocalVar(¤tTaskKey); #else return my_task; @@ -297,7 +293,7 @@ myTask (void) INLINE_HEADER void setMyTask (Task *task) { -#if defined(THREADED_RTS) && !defined(MYTASK_USE_TLV) +#if defined(THREADED_RTS) && !CC_SUPPORTS_TLS setThreadLocalVar(¤tTaskKey,task); #else my_task = task; View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f3017dd3a7e3a2bd8a4f0b9f86268ff403f8f7c6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f3017dd3a7e3a2bd8a4f0b9f86268ff403f8f7c6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 01:34:09 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sun, 09 Jun 2024 21:34:09 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 12 commits: JS: establish single source of truth for symbols Message-ID: <66665811817cd_2357372bf28fc40918@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - 332bc366 by Ben Gamari at 2024-06-09T21:34:01-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - b774430e by qqwy at 2024-06-09T21:34:02-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set - - - - - d0bfd4ee by qqwy at 2024-06-09T21:34:02-04:00 Document __GLASGOW_HASKELL_ASSERTS_IGNORED__ in the users's guide - - - - - 0babc8c6 by qqwy at 2024-06-09T21:34:03-04:00 fixup! Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set - - - - - 88b5d741 by qqwy at 2024-06-09T21:34:03-04:00 Add a test for the usage of the __GLASGOW_HASKELL_ASSERTIONS_IGNORED__ CPP macro - - - - - 20f5fad3 by qqwy at 2024-06-09T21:34:03-04:00 fixup! Document __GLASGOW_HASKELL_ASSERTS_IGNORED__ in the users's guide - - - - - 49d44b11 by qqwy at 2024-06-09T21:34:03-04:00 fixup! Add a test for the usage of the __GLASGOW_HASKELL_ASSERTIONS_IGNORED__ CPP macro - - - - - c66d61f2 by Ben Gamari at 2024-06-09T21:34:03-04:00 Fix documentation typos (RST syntax) in the documentation of __GLASGOW_HASKELL_ASSERTS_IGNORED__ - - - - - ad36e4e9 by qqwy at 2024-06-09T21:34:03-04:00 fixup! Fix documentation typos (RST syntax) in the documentation of __GLASGOW_HASKELL_ASSERTS_IGNORED__ - - - - - ac41d111 by Hugo Peters at 2024-06-09T21:34:03-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 20 changed files: - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/JS/Ident.hs - compiler/GHC/JS/JStg/Monad.hs - compiler/GHC/JS/JStg/Syntax.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Syntax.hs - compiler/GHC/StgToJS.hs - compiler/GHC/StgToJS/Apply.hs - compiler/GHC/StgToJS/Arg.hs - compiler/GHC/StgToJS/Closure.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/FFI.hs - compiler/GHC/StgToJS/Heap.hs - compiler/GHC/StgToJS/Ids.hs - compiler/GHC/StgToJS/Linker/Linker.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/StgToJS/Object.hs - compiler/GHC/StgToJS/Prim.hs - compiler/GHC/StgToJS/Profiling.hs - compiler/GHC/StgToJS/Regs.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e42bb7032cd7e48df7b9bef343ccf692682b944f...ac41d11121f447dd7e6c7fbe3ec31760f1bcb2f8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/e42bb7032cd7e48df7b9bef343ccf692682b944f...ac41d11121f447dd7e6c7fbe3ec31760f1bcb2f8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 06:25:32 2024 From: gitlab at gitlab.haskell.org (Alexander Foremny (@aforemny)) Date: Mon, 10 Jun 2024 02:25:32 -0400 Subject: [Git][ghc/ghc][wip/aforemny/parameterize-source-text-lits-over-pass] 2 commits: AST: use `StringLit` for `HsIsString` Message-ID: <66669c5c64afc_2f53811251de467654@gitlab.mail> Alexander Foremny pushed to branch wip/aforemny/parameterize-source-text-lits-over-pass at Glasgow Haskell Compiler / GHC Commits: 9c69de8c by Alexander Foremny at 2024-06-10T08:22:03+02:00 AST: use `StringLit` for `HsIsString` While `OverLitVal`'s data constructors `HsIntegral`, `HsFractional` carried `IntegralLit`, `FractionalLit` types, `HsIsString` carries only `SourceText` and `FastString`. We will want to parameterize over `SourceText`, which `StringLit`s will support. So we change `HsIsString` to carry a `StringLit`. - - - - - fd42439c by Alexander Foremny at 2024-06-10T08:23:41+02:00 AST: parameterize `GHC.Types.SourceText`'s literals over `pass` In order to move `GHC.Types.SourceText.SourceText` out of `Language.Haskell`, we parameterize `GHC.Types.SourceText`'s literals by `pass`, and replace, say, `IntegralLit`'s `SourceText` field by `XIntegralLit pass`. - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Pmc/Solver/Types.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/HaddockLex.x - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/ThToHs.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/96c93239e3083abcf8f0352b490c4f8999cd3e27...fd42439c2bcb38dd889c27c0a0216573566702cd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/96c93239e3083abcf8f0352b490c4f8999cd3e27...fd42439c2bcb38dd889c27c0a0216573566702cd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 06:35:33 2024 From: gitlab at gitlab.haskell.org (Alexander Foremny (@aforemny)) Date: Mon, 10 Jun 2024 02:35:33 -0400 Subject: [Git][ghc/ghc][wip/aforemny/parameterize-source-text-lits-over-pass] 22 commits: Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw Message-ID: <66669eb5a724e_2f5381137f770698ec@gitlab.mail> Alexander Foremny pushed to branch wip/aforemny/parameterize-source-text-lits-over-pass at Glasgow Haskell Compiler / GHC Commits: edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 1c04f3c1 by Adriaan Leijnse at 2024-06-09T15:14:32+02:00 ttg: Remove SourceText from OverloadedLabel Progress towards #21592 - - - - - a4ca52f4 by Alexander Foremny at 2024-06-09T15:14:33+02:00 AST: GHC.Prelude -> Prelude Refactor occurrences to GHC.Prelude with Prelude within Language/Haskell. Progress towards #21592 - - - - - 08bfba21 by Alexander Foremny at 2024-06-09T15:14:33+02:00 AST: remove occurrences of GHC.Unit.Module.ModuleName `GHC.Unit.Module` re-exports `ModuleName` from `Language.Haskell.Syntax.Module.Name`. Progress towards #21592 - - - - - d367235b by Fabian Kirchner at 2024-06-09T15:14:33+02:00 AST: move Data instance definition for ModuleName to GHC.Unit.Types To remove the dependency on GHC.Utils.Misc inside Language.Haskell.Syntax.Module.Name, the instance definition is moved from there into GHC.Unit.Types. Progress towards #21592 - - - - - 21baa04f by Fabian Kirchner at 2024-06-09T15:14:33+02:00 AST: move negateOverLitVal into GHC.Hs.Lit The function negateOverLitVal is not used within Language.Haskell and therefore can be moved to the respective module inside GHC.Hs. Progress towards #21592 - - - - - 61e15aaa by Fabian Kirchner at 2024-06-09T15:14:33+02:00 AST: move conDetailsArity into GHC.Rename.Module The function conDetailsArity is only used inside GHC.Rename.Module. We therefore move it there from Language.Haskell.Syntax.Lit. Progress towards #21592 - - - - - 4c28edd4 by Mauricio at 2024-06-09T15:14:33+02:00 AST: Remove GHC.Utils.Assert from GHC Simple cleanup. Progress towards #21592 - - - - - d7e78217 by Jacco Krijnen at 2024-06-09T15:14:33+02:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 1b781d60 by Fabian Kirchner at 2024-06-09T19:06:53+02:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - f3df7507 by Fabian Kirchner at 2024-06-09T19:06:57+02:00 ttg: Move some AST types into Language.Haskell.Syntax.Basic In particular, we move: * TopLevelFlag * TypeOrData * TyConFlavour Progress towards #21592 - - - - - 73a4f29b by Adowrath at 2024-06-09T19:07:13+02:00 ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type Progress towards #21592 This splits HsSrcBang up, creating the new HsBang within `Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness and strictness information, while `HsSrcBang` only adds the SourceText for usage within the compiler directly. Inside the AST, to preserve the SourceText, it is hidden behind the pre-existing extension point `XBindTy`. All other occurrences of `HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when interacting with the `BindTy` constructor, the hidden `SourceText` is extracted/inserted into the `XBindTy` extension point. `GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for convenience. A constructor function `mkHsSrcBang` that takes all individual components has been added. Two exceptions has been made though: - The `Outputable HsSrcBang` instance is replaced by `Outputable HsBang`. While being only GHC-internal, the only place it's used is in outputting `HsBangTy` constructors -- which already have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just to ignore the `SourceText` anyway. - The error `TcRnUnexpectedAnnotation` did not use the `SourceText`, so it too now only holds a `HsBang`. - - - - - 68abf0c8 by Mauricio at 2024-06-09T19:18:36+02:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - fcdb7818 by Alexander Foremny at 2024-06-10T08:27:29+02:00 AST: StringLiteral -> StringLit (type) `GHC.Types.SourceText.StringLiteral` does not abbreviate "Literal", while `GHC.Types.SourceText.{IntegralLit,FractionalLit}` do. To increase consistency, `StringLiteral` was renamed to `StringLit`. - - - - - d6d00153 by Alexander Foremny at 2024-06-10T08:27:30+02:00 AST: StringLiteral -> SL (data constructor) `GHC.Types.SourceText.StringLit` has data constructor `StringLiteral`, while `GHC.Types.SourceText.{IntegralLit,FractionalLit}` have data constructors `{IL,FL}`. To increase consistency, the data constructor `StringLiteral` was renamed to `SL`. - - - - - b4b9c3ac by Alexander Foremny at 2024-06-10T08:30:07+02:00 AST: use `StringLit` for `HsIsString` While `OverLitVal`'s data constructors `HsIntegral`, `HsFractional` carried `IntegralLit`, `FractionalLit` types, `HsIsString` carries only `SourceText` and `FastString`. We will want to parameterize over `SourceText`, which `StringLit`s will support. So we change `HsIsString` to carry a `StringLit`. - - - - - 61f98f62 by Alexander Foremny at 2024-06-10T08:34:59+02:00 AST: parameterize `GHC.Types.SourceText`'s literals over `pass` In order to move `GHC.Types.SourceText.SourceText` out of `Language.Haskell`, we parameterize `GHC.Types.SourceText`'s literals by `pass`, and replace, say, `IntegralLit`'s `SourceText` field by `XIntegralLit pass`. - - - - - 30 changed files: - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/CoreToIface.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver/Types.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fd42439c2bcb38dd889c27c0a0216573566702cd...61f98f622842296db099099dd29172309af23068 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fd42439c2bcb38dd889c27c0a0216573566702cd...61f98f622842296db099099dd29172309af23068 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 08:02:01 2024 From: gitlab at gitlab.haskell.org (Zubin (@wz1000)) Date: Mon, 10 Jun 2024 04:02:01 -0400 Subject: [Git][ghc/ghc][wip/faststring-no-z] fixes Message-ID: <6666b2f9fd19_2f53811e3c10485488@gitlab.mail> Zubin pushed to branch wip/faststring-no-z at Glasgow Haskell Compiler / GHC Commits: 7bf4bf0a by Zubin Duggal at 2024-06-10T10:01:46+02:00 fixes - - - - - 5 changed files: - compiler/GHC/Data/FastString.hs - ghc/Main.hs - rts/configure.ac - testsuite/tests/th/T10279.hs - testsuite/tests/th/T10279.stderr Changes: ===================================== compiler/GHC/Data/FastString.hs ===================================== @@ -94,6 +94,7 @@ module GHC.Data.FastString -- ** Internal getFastStringTable, + getFastZStringTable, getFastStringZEncCounter, -- * PtrStrings @@ -358,6 +359,7 @@ hashToIndex# buckets# hash# = !(I# segmentBits#) = segmentBits size# = sizeofMutableArray# buckets# +{-# INLINE maybeResizeSegment #-} maybeResizeSegment :: forall a. (a -> Int) -> IORef (TableSegment a) -> IO (TableSegment a) maybeResizeSegment hashElem segmentRef = do segment@(TableSegment lock counter old#) <- readIORef segmentRef @@ -564,6 +566,9 @@ bucket_match fs sbs = go fs -- Non-inlining causes a small, but measurable performance regression, so let's force it. {-# INLINE bucket_match #-} + +{-# INLINE mkNewFastZString #-} + mkNewFastZString :: FastString -> IO FastZString mkNewFastZString (FastString uniq _ sbs) = do TableSegment lock _ buckets# <- readIORef segmentRef @@ -575,9 +580,9 @@ mkNewFastZString (FastString uniq _ sbs) = do -- The withMVar below is not dupable. It can lead to deadlock if it is -- only run partially and putMVar is not called after takeMVar. noDuplicate - n <- get_uid + _ <- get_uid let !new_fs = mkZFastString sbs - withMVar lock $ \_ -> insert n new_fs + withMVar lock $ \_ -> insert (I# hash#) new_fs where !(FastZStringTable uid segments#) = zstringTable get_uid = atomicFetchAddFastMut uid 1 @@ -706,6 +711,8 @@ unpackFS fs = utf8DecodeShortByteString $ fs_sbs fs zEncodeFS :: FastString -> FastZString zEncodeFS fs = inlinePerformIO $ mkNewFastZString fs +{-# INLINE zEncodeFS #-} + appendFS :: FastString -> FastString -> FastString appendFS fs1 fs2 = mkFastStringShortByteString $ (Semi.<>) (fs_sbs fs1) (fs_sbs fs2) @@ -742,6 +749,17 @@ getFastStringTable = where !(FastStringTable _ segments#) = stringTable +getFastZStringTable :: IO [[[FastZString]]] +getFastZStringTable = + forM [0 .. numSegments - 1] $ \(I# i#) -> do + let (# segmentRef #) = indexArray# segments# i# + TableSegment _ _ buckets# <- readIORef segmentRef + let bucketSize = I# (sizeofMutableArray# buckets#) + forM [0 .. bucketSize - 1] $ \(I# j#) -> + fmap (map (\(HashedFastZString _ s) -> s)) $ IO $ readArray# buckets# j# + where + !(FastZStringTable _ segments#) = zstringTable + getFastStringZEncCounter :: IO Int getFastStringZEncCounter = readFastMutInt counter where (FastZStringTable counter _) = zstringTable ===================================== ghc/Main.hs ===================================== @@ -1032,10 +1032,15 @@ dumpFinalStats logger = do when (logHasDumpFlag logger Opt_D_dump_faststrings) $ do fss <- getFastStringTable + fzss <- getFastZStringTable let ppr_table = fmap ppr_segment (fss `zip` [0..]) ppr_segment (s,n) = hang (text "Segment" <+> int n) 2 (vcat (fmap ppr_bucket (s `zip` [0..]))) ppr_bucket (b,n) = hang (text "Bucket" <+> int n) 2 (vcat (fmap ftext b)) putDumpFileMaybe logger Opt_D_dump_faststrings "FastStrings" FormatText (vcat ppr_table) + let ppr_table' = fmap ppr_segment' (fzss `zip` [0..]) + ppr_segment' (s,n) = hang (text "Segment" <+> int n) 2 (vcat (fmap ppr_bucket' (s `zip` [0..]))) + ppr_bucket' (b,n) = hang (text "Bucket" <+> int n) 2 (vcat (fmap (text . zString) b)) + putDumpFileMaybe logger Opt_D_dump_faststrings "FastZStrings" FormatText (vcat ppr_table') dumpFastStringStats :: Logger -> IO () dumpFastStringStats logger = do @@ -1053,6 +1058,7 @@ dumpFastStringStats logger = do , text "smallest segment: " <+> int (minimum bucketsPerSegment) , text "longest bucket: " <+> int (maximum entriesPerBucket) , text "has z-encoding: " <+> (hasZ `pcntOf` entries) + , text "z-encodings: " <+> int (hasZ) ]) -- we usually get more "has z-encoding" than "z-encoded", because -- when we z-encode a string it might hash to the exact same string, ===================================== rts/configure.ac ===================================== @@ -6,7 +6,7 @@ # see what flags are available. (Better yet, read the documentation!) # -AC_INIT([GHC run-time system], [1.0.2], [libraries at haskell.org], [rts]) +AC_INIT([GHC run-time system], [1.0.3], [libraries at haskell.org], [rts]) AC_CONFIG_MACRO_DIRS([../m4]) ===================================== testsuite/tests/th/T10279.hs ===================================== @@ -7,4 +7,4 @@ import Language.Haskell.TH.Syntax -- error message doesn't recognize it as a source package ID, -- (This is OK, since it will look obviously wrong when they -- try to find the package in their package database.) -blah = $(conE (Name (mkOccName "Foo") (NameG VarName (mkPkgName "rts-1.0.2") (mkModName "A")))) +blah = $(conE (Name (mkOccName "Foo") (NameG VarName (mkPkgName "rts-1.0.3") (mkModName "A")))) ===================================== testsuite/tests/th/T10279.stderr ===================================== @@ -1,11 +1,11 @@ T10279.hs:10:9: error: [GHC-51294] • Failed to load interface for ‘A’. - no unit id matching ‘rts-1.0.2’ was found + no unit id matching ‘rts-1.0.3’ was found (This unit ID looks like the source package ID; the real unit ID is ‘rts’) • In the untyped splice: $(conE (Name (mkOccName "Foo") - (NameG VarName (mkPkgName "rts-1.0.2") (mkModName "A")))) + (NameG VarName (mkPkgName "rts-1.0.3") (mkModName "A")))) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7bf4bf0ad072cd24b78930f494b889ce50e117b1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7bf4bf0ad072cd24b78930f494b889ce50e117b1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 08:18:18 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Mon, 10 Jun 2024 04:18:18 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Message-ID: <6666b6ca11eb7_2f53812144928933e0@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: 11873fd4 by Mauricio at 2024-06-10T10:14:49+02:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - 2 changed files: - compiler/GHC/Hs/Lit.hs - compiler/Language/Haskell/Syntax/Lit.hs Changes: ===================================== compiler/GHC/Hs/Lit.hs ===================================== @@ -253,3 +253,15 @@ negateOverLitVal :: OverLitVal -> OverLitVal negateOverLitVal (HsIntegral i) = HsIntegral (negateIntegralLit i) negateOverLitVal (HsFractional f) = HsFractional (negateFractionalLit f) negateOverLitVal _ = panic "negateOverLitVal: argument is not a number" + +instance (Ord (XXOverLit p)) => Ord (HsOverLit p) where + compare (OverLit _ val1) (OverLit _ val2) = val1 `compare` val2 + compare (XOverLit val1) (XOverLit val2) = val1 `compare` val2 + compare _ _ = panic "Ord HsOverLit" + +-- Comparison operations are needed when grouping literals +-- for compiling pattern-matching (module GHC.HsToCore.Match.Literal) +instance (Eq (XXOverLit p)) => Eq (HsOverLit p) where + (OverLit _ val1) == (OverLit _ val2) = val1 == val2 + (XOverLit val1) == (XOverLit val2) = val1 == val2 + _ == _ = panic "Eq HsOverLit" ===================================== compiler/Language/Haskell/Syntax/Lit.hs ===================================== @@ -20,7 +20,6 @@ module Language.Haskell.Syntax.Lit where import Language.Haskell.Syntax.Extension -import GHC.Utils.Panic (panic) import GHC.Types.SourceText (IntegralLit, FractionalLit, SourceText) import GHC.Core.Type (Type) @@ -128,24 +127,12 @@ data OverLitVal | HsIsString !SourceText !FastString -- ^ String-looking literals deriving Data --- Comparison operations are needed when grouping literals --- for compiling pattern-matching (module GHC.HsToCore.Match.Literal) -instance (Eq (XXOverLit p)) => Eq (HsOverLit p) where - (OverLit _ val1) == (OverLit _ val2) = val1 == val2 - (XOverLit val1) == (XOverLit val2) = val1 == val2 - _ == _ = panic "Eq HsOverLit" - instance Eq OverLitVal where (HsIntegral i1) == (HsIntegral i2) = i1 == i2 (HsFractional f1) == (HsFractional f2) = f1 == f2 (HsIsString _ s1) == (HsIsString _ s2) = s1 == s2 _ == _ = False -instance (Ord (XXOverLit p)) => Ord (HsOverLit p) where - compare (OverLit _ val1) (OverLit _ val2) = val1 `compare` val2 - compare (XOverLit val1) (XOverLit val2) = val1 `compare` val2 - compare _ _ = panic "Ord HsOverLit" - instance Ord OverLitVal where compare (HsIntegral i1) (HsIntegral i2) = i1 `compare` i2 compare (HsIntegral _) (HsFractional _) = LT View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/11873fd4e5113185fe2f0880da00f6b2b2c3971f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/11873fd4e5113185fe2f0880da00f6b2b2c3971f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 08:25:26 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Mon, 10 Jun 2024 04:25:26 -0400 Subject: [Git][ghc/ghc][wip/jacco/ast] fixup! ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <6666b876c7eef_3bc70d854bc3404f@gitlab.mail> Rodrigo Mesquita pushed to branch wip/jacco/ast at Glasgow Haskell Compiler / GHC Commits: a1276759 by Rodrigo Mesquita at 2024-06-10T10:24:57+02:00 fixup! ttg: Use List instead of Bag in AST for LHsBindsLR - - - - - 1 changed file: - utils/check-exact/Utils.hs Changes: ===================================== utils/check-exact/Utils.hs ===================================== @@ -486,7 +486,7 @@ hsDeclsClassDecl dec = case dec of decls = orderedDecls sortKey $ Map.fromList [(ClsSigTag, map (\(L l s) -> (srs l, L l (SigD noExtField s))) sigs), - (ClsMethodTag, map (\(L l s) -> (srs l, L l (ValD noExtField s))) (bagToList methods)), + (ClsMethodTag, map (\(L l s) -> (srs l, L l (ValD noExtField s))) methods), (ClsAtTag, map (\(L l s) -> (srs l, L l (TyClD noExtField $ FamDecl noExtField s))) ats), (ClsAtdTag, map (\(L l s) -> (srs l, L l (InstD noExtField $ TyFamInstD noExtField s))) at_defs) ] @@ -510,12 +510,12 @@ partitionWithSortKey [LTyFamInstDecl GhcPs], [LDataFamInstDecl GhcPs], [LDocDecl GhcPs]) partitionWithSortKey = go where - go [] = ([], emptyBag, [], [], [], [], []) + go [] = ([], [], [], [], [], [], []) go ((L l decl) : ds) = let (tags, bs, ss, ts, tfis, dfis, docs) = go ds in case decl of ValD _ b - -> (ClsMethodTag:tags, L l b `consBag` bs, ss, ts, tfis, dfis, docs) + -> (ClsMethodTag:tags, L l b : bs, ss, ts, tfis, dfis, docs) SigD _ s -> (ClsSigTag:tags, bs, L l s : ss, ts, tfis, dfis, docs) TyClD _ (FamDecl _ t) @@ -553,7 +553,7 @@ hsDeclsLocalBinds :: HsLocalBinds GhcPs -> [LHsDecl GhcPs] hsDeclsLocalBinds lb = case lb of HsValBinds _ (ValBinds sortKey bs sigs) -> let - bds = map wrapDecl (bagToList bs) + bds = map wrapDecl bs sds = map wrapSig sigs in orderedDeclsBinds sortKey bds sds @@ -564,7 +564,7 @@ hsDeclsLocalBinds lb = case lb of hsDeclsValBinds :: (HsValBindsLR GhcPs GhcPs) -> [LHsDecl GhcPs] hsDeclsValBinds (ValBinds sortKey bs sigs) = let - bds = map wrapDecl (bagToList bs) + bds = map wrapDecl bs sds = map wrapSig sigs in orderedDeclsBinds sortKey bds sds View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a127675955f154e7e49fd6e0141484d3bfd25e14 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a127675955f154e7e49fd6e0141484d3bfd25e14 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 08:29:03 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Mon, 10 Jun 2024 04:29:03 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] 5 commits: ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <6666b94ff0a2b_3bc70d2357f835083@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: f52e9f6f by Jacco Krijnen at 2024-06-10T10:23:09+02:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 1126ffeb by Fabian Kirchner at 2024-06-10T10:23:09+02:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - 44ddf792 by Fabian Kirchner at 2024-06-10T10:23:09+02:00 ttg: Move some AST types into Language.Haskell.Syntax.Basic In particular, we move: * TopLevelFlag * TypeOrData * TyConFlavour Progress towards #21592 - - - - - e899ad60 by Adowrath at 2024-06-10T10:23:09+02:00 ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type Progress towards #21592 This splits HsSrcBang up, creating the new HsBang within `Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness and strictness information, while `HsSrcBang` only adds the SourceText for usage within the compiler directly. Inside the AST, to preserve the SourceText, it is hidden behind the pre-existing extension point `XBindTy`. All other occurrences of `HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when interacting with the `BindTy` constructor, the hidden `SourceText` is extracted/inserted into the `XBindTy` extension point. `GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for convenience. A constructor function `mkHsSrcBang` that takes all individual components has been added. Two exceptions has been made though: - The `Outputable HsSrcBang` instance is replaced by `Outputable HsBang`. While being only GHC-internal, the only place it's used is in outputting `HsBangTy` constructors -- which already have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just to ignore the `SourceText` anyway. - The error `TcRnUnexpectedAnnotation` did not use the `SourceText`, so it too now only holds a `HsBang`. - - - - - 56a90f15 by Mauricio at 2024-06-10T10:23:09+02:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/CoreToIface.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/11873fd4e5113185fe2f0880da00f6b2b2c3971f...56a90f156c27d010be9104f20683d4b3371f76a6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/11873fd4e5113185fe2f0880da00f6b2b2c3971f...56a90f156c27d010be9104f20683d4b3371f76a6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 08:39:37 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Mon, 10 Jun 2024 04:39:37 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/romes/ast-ohne-faststring Message-ID: <6666bbc97b53b_3bc70d4291543933d@gitlab.mail> Rodrigo Mesquita pushed new branch wip/romes/ast-ohne-faststring at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/ast-ohne-faststring You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 09:25:34 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Mon, 10 Jun 2024 05:25:34 -0400 Subject: [Git][ghc/ghc][wip/kill-pre-c11] 5 commits: JS: establish single source of truth for symbols Message-ID: <6666c68e1375e_3bc70db65e04704b1@gitlab.mail> Cheng Shao pushed to branch wip/kill-pre-c11 at Glasgow Haskell Compiler / GHC Commits: 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - 9a9506fb by Cheng Shao at 2024-06-10T08:42:13+00:00 WIP: always assume __GNUC__ >= 4 - - - - - 403542c6 by Cheng Shao at 2024-06-10T08:42:13+00:00 WIP - - - - - aed79a24 by Cheng Shao at 2024-06-10T09:25:19+00:00 WIP - - - - - 19 changed files: - compiler/GHC/JS/Ident.hs - compiler/GHC/JS/JStg/Monad.hs - compiler/GHC/JS/JStg/Syntax.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Syntax.hs - compiler/GHC/StgToJS.hs - compiler/GHC/StgToJS/Apply.hs - compiler/GHC/StgToJS/Arg.hs - compiler/GHC/StgToJS/Closure.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/FFI.hs - compiler/GHC/StgToJS/Heap.hs - compiler/GHC/StgToJS/Ids.hs - compiler/GHC/StgToJS/Linker/Linker.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/StgToJS/Object.hs - compiler/GHC/StgToJS/Prim.hs - compiler/GHC/StgToJS/Profiling.hs - compiler/GHC/StgToJS/Regs.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/68514576e148d644dddddae3432b99f1ce4bea0d...aed79a2465dd6f6ba8dd32f981e9c129013009d1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/68514576e148d644dddddae3432b99f1ce4bea0d...aed79a2465dd6f6ba8dd32f981e9c129013009d1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 09:36:07 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Mon, 10 Jun 2024 05:36:07 -0400 Subject: [Git][ghc/ghc][wip/romes/ast-ohne-faststring] 6 commits: ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <6666c9078223f_3bc70dde434c77732@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ast-ohne-faststring at Glasgow Haskell Compiler / GHC Commits: f52e9f6f by Jacco Krijnen at 2024-06-10T10:23:09+02:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 1126ffeb by Fabian Kirchner at 2024-06-10T10:23:09+02:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - 44ddf792 by Fabian Kirchner at 2024-06-10T10:23:09+02:00 ttg: Move some AST types into Language.Haskell.Syntax.Basic In particular, we move: * TopLevelFlag * TypeOrData * TyConFlavour Progress towards #21592 - - - - - e899ad60 by Adowrath at 2024-06-10T10:23:09+02:00 ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type Progress towards #21592 This splits HsSrcBang up, creating the new HsBang within `Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness and strictness information, while `HsSrcBang` only adds the SourceText for usage within the compiler directly. Inside the AST, to preserve the SourceText, it is hidden behind the pre-existing extension point `XBindTy`. All other occurrences of `HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when interacting with the `BindTy` constructor, the hidden `SourceText` is extracted/inserted into the `XBindTy` extension point. `GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for convenience. A constructor function `mkHsSrcBang` that takes all individual components has been added. Two exceptions has been made though: - The `Outputable HsSrcBang` instance is replaced by `Outputable HsBang`. While being only GHC-internal, the only place it's used is in outputting `HsBangTy` constructors -- which already have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just to ignore the `SourceText` anyway. - The error `TcRnUnexpectedAnnotation` did not use the `SourceText`, so it too now only holds a `HsBang`. - - - - - 56a90f15 by Mauricio at 2024-06-10T10:23:09+02:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - 6a0cc6c8 by Rodrigo Mesquita at 2024-06-10T11:35:51+02:00 ttg: Start using Text over FastString in the AST Towards the goal of making the AST independent of GHC, this commit starts the task of replacing usages of `FastString` with `Text` in the AST (Language.Haskell.* modules). Even though we /do/ want to use FastStrings -- critically in Names or Ids -- there is no particular reason for the FastStrings that occur in the AST proper to be FastStrings. Primarily, ... Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Data/StringBuffer.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Eval.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/65917c2647e45e0010a09dde4f8ac2fb8c961939...6a0cc6c873aecafe607b66f2f4225857ba5c6f30 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/65917c2647e45e0010a09dde4f8ac2fb8c961939...6a0cc6c873aecafe607b66f2f4225857ba5c6f30 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 09:38:03 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Mon, 10 Jun 2024 05:38:03 -0400 Subject: [Git][ghc/ghc][wip/jacco/ast] ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <6666c97b7ad_3bc70de77a4878467@gitlab.mail> Rodrigo Mesquita pushed to branch wip/jacco/ast at Glasgow Haskell Compiler / GHC Commits: b9b67921 by Jacco Krijnen at 2024-06-10T11:37:50+02:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b9b67921c30f7dce58d456b87d54bd661b7a0630 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b9b67921c30f7dce58d456b87d54bd661b7a0630 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 09:38:23 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Mon, 10 Jun 2024 05:38:23 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] 5 commits: ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <6666c98f1be4_3bc70df1ac34790d1@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: 1ccd023a by Jacco Krijnen at 2024-06-10T11:37:15+02:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 62b585cc by Fabian Kirchner at 2024-06-10T11:37:15+02:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - 051e17c2 by Fabian Kirchner at 2024-06-10T11:37:16+02:00 ttg: Move some AST types into Language.Haskell.Syntax.Basic In particular, we move: * TopLevelFlag * TypeOrData * TyConFlavour Progress towards #21592 - - - - - cd4ab6d8 by Adowrath at 2024-06-10T11:37:16+02:00 ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type Progress towards #21592 This splits HsSrcBang up, creating the new HsBang within `Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness and strictness information, while `HsSrcBang` only adds the SourceText for usage within the compiler directly. Inside the AST, to preserve the SourceText, it is hidden behind the pre-existing extension point `XBindTy`. All other occurrences of `HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when interacting with the `BindTy` constructor, the hidden `SourceText` is extracted/inserted into the `XBindTy` extension point. `GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for convenience. A constructor function `mkHsSrcBang` that takes all individual components has been added. Two exceptions has been made though: - The `Outputable HsSrcBang` instance is replaced by `Outputable HsBang`. While being only GHC-internal, the only place it's used is in outputting `HsBangTy` constructors -- which already have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just to ignore the `SourceText` anyway. - The error `TcRnUnexpectedAnnotation` did not use the `SourceText`, so it too now only holds a `HsBang`. - - - - - 10d3ad93 by Mauricio at 2024-06-10T11:37:16+02:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/CoreToIface.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/56a90f156c27d010be9104f20683d4b3371f76a6...10d3ad93a80d13d2b8c02eb6f41a322f3c039a50 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/56a90f156c27d010be9104f20683d4b3371f76a6...10d3ad93a80d13d2b8c02eb6f41a322f3c039a50 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 09:38:53 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Mon, 10 Jun 2024 05:38:53 -0400 Subject: [Git][ghc/ghc][wip/romes/ast-ohne-faststring] 6 commits: ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <6666c9ad5ff92_3bc70d102b2f47981f@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ast-ohne-faststring at Glasgow Haskell Compiler / GHC Commits: 1ccd023a by Jacco Krijnen at 2024-06-10T11:37:15+02:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 62b585cc by Fabian Kirchner at 2024-06-10T11:37:15+02:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - 051e17c2 by Fabian Kirchner at 2024-06-10T11:37:16+02:00 ttg: Move some AST types into Language.Haskell.Syntax.Basic In particular, we move: * TopLevelFlag * TypeOrData * TyConFlavour Progress towards #21592 - - - - - cd4ab6d8 by Adowrath at 2024-06-10T11:37:16+02:00 ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type Progress towards #21592 This splits HsSrcBang up, creating the new HsBang within `Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness and strictness information, while `HsSrcBang` only adds the SourceText for usage within the compiler directly. Inside the AST, to preserve the SourceText, it is hidden behind the pre-existing extension point `XBindTy`. All other occurrences of `HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when interacting with the `BindTy` constructor, the hidden `SourceText` is extracted/inserted into the `XBindTy` extension point. `GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for convenience. A constructor function `mkHsSrcBang` that takes all individual components has been added. Two exceptions has been made though: - The `Outputable HsSrcBang` instance is replaced by `Outputable HsBang`. While being only GHC-internal, the only place it's used is in outputting `HsBangTy` constructors -- which already have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just to ignore the `SourceText` anyway. - The error `TcRnUnexpectedAnnotation` did not use the `SourceText`, so it too now only holds a `HsBang`. - - - - - 10d3ad93 by Mauricio at 2024-06-10T11:37:16+02:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - 124aa9ef by Rodrigo Mesquita at 2024-06-10T11:38:41+02:00 ttg: Start using Text over FastString in the AST Towards the goal of making the AST independent of GHC, this commit starts the task of replacing usages of `FastString` with `Text` in the AST (Language.Haskell.* modules). Even though we /do/ want to use FastStrings -- critically in Names or Ids -- there is no particular reason for the FastStrings that occur in the AST proper to be FastStrings. Primarily, ... Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Data/StringBuffer.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Eval.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6a0cc6c873aecafe607b66f2f4225857ba5c6f30...124aa9ef78819760905056e92f70b761f84d8e10 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6a0cc6c873aecafe607b66f2f4225857ba5c6f30...124aa9ef78819760905056e92f70b761f84d8e10 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 09:48:36 2024 From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge)) Date: Mon, 10 Jun 2024 05:48:36 -0400 Subject: [Git][ghc/ghc][wip/T24789_impl] 4 commits: JS: establish single source of truth for symbols Message-ID: <6666cbf46ebfb_3bc70d12315bc85684@gitlab.mail> Serge S. Gulin pushed to branch wip/T24789_impl at Glasgow Haskell Compiler / GHC Commits: 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - 08b85abf by Serge S. Gulin at 2024-06-10T12:48:23+03:00 Unicode: adding compact version of GeneralCategory The following features are applied: 1. Lookup code like Cmm-switches (draft implementation proposed by Sylvain Henry @hsyl20) 2. Nested ifs (logarithmic search vs linear search) (the idea proposed by Sylvain Henry @hsyl20) 3. More compact representation via variable encoding by Huffman - - - - - df691802 by Serge S. Gulin at 2024-06-10T12:48:24+03:00 Unicode: disable Huffman - - - - - 19 changed files: - compiler/GHC/JS/Ident.hs - compiler/GHC/JS/JStg/Monad.hs - compiler/GHC/JS/JStg/Syntax.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Syntax.hs - compiler/GHC/StgToJS.hs - compiler/GHC/StgToJS/Apply.hs - compiler/GHC/StgToJS/Arg.hs - compiler/GHC/StgToJS/Closure.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/FFI.hs - compiler/GHC/StgToJS/Heap.hs - compiler/GHC/StgToJS/Ids.hs - compiler/GHC/StgToJS/Linker/Linker.hs - compiler/GHC/StgToJS/Literal.hs - compiler/GHC/StgToJS/Object.hs - compiler/GHC/StgToJS/Prim.hs - compiler/GHC/StgToJS/Profiling.hs - compiler/GHC/StgToJS/Regs.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/eade9d168e76d8484d849ab6b994d94fd85168d4...df6918029d0d472e6a08ab2078485846fd9aa192 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/eade9d168e76d8484d849ab6b994d94fd85168d4...df6918029d0d472e6a08ab2078485846fd9aa192 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 10:11:38 2024 From: gitlab at gitlab.haskell.org (Alexander Foremny (@aforemny)) Date: Mon, 10 Jun 2024 06:11:38 -0400 Subject: [Git][ghc/ghc][wip/aforemny/parameterize-source-text-lits-over-pass] 9 commits: ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <6666d15a87e79_3bc70d15b155c89845@gitlab.mail> Alexander Foremny pushed to branch wip/aforemny/parameterize-source-text-lits-over-pass at Glasgow Haskell Compiler / GHC Commits: 1ccd023a by Jacco Krijnen at 2024-06-10T11:37:15+02:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 62b585cc by Fabian Kirchner at 2024-06-10T11:37:15+02:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - 051e17c2 by Fabian Kirchner at 2024-06-10T11:37:16+02:00 ttg: Move some AST types into Language.Haskell.Syntax.Basic In particular, we move: * TopLevelFlag * TypeOrData * TyConFlavour Progress towards #21592 - - - - - cd4ab6d8 by Adowrath at 2024-06-10T11:37:16+02:00 ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type Progress towards #21592 This splits HsSrcBang up, creating the new HsBang within `Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness and strictness information, while `HsSrcBang` only adds the SourceText for usage within the compiler directly. Inside the AST, to preserve the SourceText, it is hidden behind the pre-existing extension point `XBindTy`. All other occurrences of `HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when interacting with the `BindTy` constructor, the hidden `SourceText` is extracted/inserted into the `XBindTy` extension point. `GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for convenience. A constructor function `mkHsSrcBang` that takes all individual components has been added. Two exceptions has been made though: - The `Outputable HsSrcBang` instance is replaced by `Outputable HsBang`. While being only GHC-internal, the only place it's used is in outputting `HsBangTy` constructors -- which already have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just to ignore the `SourceText` anyway. - The error `TcRnUnexpectedAnnotation` did not use the `SourceText`, so it too now only holds a `HsBang`. - - - - - 10d3ad93 by Mauricio at 2024-06-10T11:37:16+02:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - 3be9f119 by Alexander Foremny at 2024-06-10T12:08:37+02:00 ttg: StringLiteral -> StringLit (type) `GHC.Types.SourceText.StringLiteral` does not abbreviate "Literal", while `GHC.Types.SourceText.{IntegralLit,FractionalLit}` do. To increase consistency, `StringLiteral` was renamed to `StringLit`. - - - - - 3fbeaa57 by Alexander Foremny at 2024-06-10T12:08:41+02:00 ttg: StringLiteral -> SL (data constructor) `GHC.Types.SourceText.StringLit` has data constructor `StringLiteral`, while `GHC.Types.SourceText.{IntegralLit,FractionalLit}` have data constructors `{IL,FL}`. To increase consistency, the data constructor `StringLiteral` was renamed to `SL`. - - - - - f184b084 by Alexander Foremny at 2024-06-10T12:08:43+02:00 ttg: use `StringLit` for `HsIsString` While `OverLitVal`'s data constructors `HsIntegral`, `HsFractional` carried `IntegralLit`, `FractionalLit` types, `HsIsString` carries only `SourceText` and `FastString`. We will want to parameterize over `SourceText`, which `StringLit`s will support. So we change `HsIsString` to carry a `StringLit`. - - - - - f3c2baf1 by Alexander Foremny at 2024-06-10T12:11:04+02:00 ttg: parameterize `GHC.Types.SourceText`'s literals over `pass` In order to move `GHC.Types.SourceText.SourceText` out of `Language.Haskell`, we parameterize `GHC.Types.SourceText`'s literals by `pass`, and replace, say, `IntegralLit`'s `SourceText` field by `XIntegralLit pass`. - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/CoreToIface.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver/Types.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/HaddockLex.x The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/61f98f622842296db099099dd29172309af23068...f3c2baf141dd99c5daa0981c76b76916d564958e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/61f98f622842296db099099dd29172309af23068...f3c2baf141dd99c5daa0981c76b76916d564958e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 10:13:39 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 10 Jun 2024 06:13:39 -0400 Subject: [Git][ghc/ghc][wip/T24676] Wibbles Message-ID: <6666d1d392b9c_3bc70d16a0260917e7@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24676 at Glasgow Haskell Compiler / GHC Commits: 0e7bc76b by Simon Peyton Jones at 2024-06-10T11:11:35+01:00 Wibbles * Documentation * Accept simpl017 error message change - - - - - 3 changed files: - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Utils/Unify.hs - testsuite/tests/simplCore/should_compile/simpl017.stderr Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -113,7 +113,7 @@ Note [Instantiation variables are short lived] * An instantation variable is a mutable meta-type-variable, whose level number is QLInstVar. -* Ordinary unifcation variables always stand for monotypes; only instantiation +* Ordinary unification variables always stand for monotypes; only instantiation variables can be unified with a polytype (by `qlUnify`). * When we start typechecking the argments of the call, in tcValArgs, we will @@ -1884,13 +1884,12 @@ foldQLInstVars check_tv ty qlUnify :: TcType -> TcType -> TcM () -- Unify ty1 with ty2: --- * It unifies /only/ instantiation variables. --- It does not itself unify ordinary unification variables, --- although it calls unifyKind which can do so. (It'd be ok for it to --- unify ordinary unification variables, subject to the usual checks.) --- * It never produces errors, even for mis-matched types +-- * It can unify both instantiation variables (possibly with polytypes), +-- and ordinary unification variables (but only with monotypes) -- * It does not return a coercion (unlike unifyType); it is called --- for the sole purpose of unifying instantiation variables +-- for the sole purpose of unifying instantiation variables, although it +-- may also (opportunistically) unify regular unification variables. +-- * It never produces errors, even for mis-matched types -- * It may return without having made the argument types equal, of course; -- it just makes best efforts. qlUnify ty1 ty2 @@ -1899,10 +1898,7 @@ qlUnify ty1 ty2 where go :: TcType -> TcType -> TcM () - -- The TyVarSets give the variables bound by enclosing foralls - -- for the corresponding type. Don't unify with these. go (TyVarTy tv) ty2 --- | isQLInstTyVar tv = go_kappa tv ty2 | isMetaTyVar tv = go_kappa tv ty2 -- Only unify QL instantiation variables -- See (UQL3) in Note [QuickLook unification] @@ -1967,7 +1963,6 @@ qlUnify ty1 ty2 -- otherwise we'll fail to unify and emit a coercion. -- Just an optimisation: emitting a coercion is fine go_flexi kappa (TyVarTy tv2) --- | isQLInstTyVar tv2, lhsPriority tv2 > lhsPriority kappa | lhsPriority tv2 > lhsPriority kappa = go_flexi1 tv2 (TyVarTy kappa) go_flexi kappa ty2 @@ -1978,6 +1973,7 @@ qlUnify ty1 ty2 simpleUnifyCheck UC_QuickLook kappa ty2 = do { co <- unifyKind (Just (TypeThing ty2)) ty2_kind kappa_kind -- unifyKind: see (UQL2) in Note [QuickLook unification] + -- and (MIV2) in Note [Monomorphise instantiation variables] ; let ty2' = mkCastTy ty2 co ; traceTc "qlUnify:update" $ ppr kappa <+> text ":=" <+> ppr ty2 @@ -1995,19 +1991,11 @@ In qlUnify, if we find (kappa ~ ty), we are going to update kappa := ty. That is the entire point of qlUnify! Wrinkles: (UQL1) Before unifying an instantiation variable in `go_flexi`, we must check - the usual unification conditions: see `GHC.Tc.Utils.Unify.simpleUnifyCheck` + the usual unification conditions, by calling `GHC.Tc.Utils.Unify.simpleUnifyCheck` In particular: - * We must not make an occurs-check; we use occCheckExpand for that. - * We must not unify a concrete type variable with a non-concrete type. - - `simpleUnifyCheck` also checks for various other things, including - - foralls; but we specifically *want* to unify foralls here! - - level mis-match; but instantiation variables are at the innermoest - level anyway, so this would always succeed - - type families; relates to a very specific and exotic performance - question, that is unlikely to bite here + * Level mis-match (UQL2) What if kappa and ty have different kinds? We simply call the ordinary unifier and use the coercion to connect the two. @@ -2020,22 +2008,32 @@ That is the entire point of qlUnify! Wrinkles: BUT: unifyKind has emitted constraint(s) into the Tc monad, so we may as well use them. (An alternative; use uType directly, if the result is not Refl, discard the constraints and the coercion, and do not update the instantiation - variable.) + variable. But see "Sadly discarded design alternative" below.) -(UQL3) qlUnify (and Quick Look generally) is only unifies instantiation - variables, not regular unification variables. Why? Nothing fundamental. - ToDo: unfinished - - Because instantiation variables don't really have a settled level yet; +(UQL3) Instantiation variables don't really have a settled level yet; they have level QLInstVar (see Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. - So we should be worried that we might unify + You might worry that we might unify alpha[1] := Maybe kappa[qlinst] and later this kappa turns out to be a level-2 variable, and we have committed - a skolem-escape error. Boo! + a skolem-escape error. + + But happily this can't happen: QL instantiation variables have level infinity, + and we never unify a variable with a type from a deeper level. + +Sadly discarded design alternative +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +It is very tempting to use `unifyType` rather than `qlUnify`, killing off the +latter. (Extending `unifyType` slightly to allow it to unify an instantiation +variable with a polytype is easy.). But I could not see how to make it work: + + * `unifyType` makes the types /equal/, and returns a coercion, and it is hard to + marry that up with DeepSubsumption. Absent deep subsumption, this approach + might just work. - Solution: Quick Look only unifies instantiation variables, and the regular - unifier wont' do this unification because QL instantiation variables have - level infinity. + * I considered making a wrapper for `uType`, which simply discards any deferred + equality constraints. But we can't do that: in a heterogeneous equality we might + have unified a unification variable (alpha := ty |> co), where `co` is only bound + by those constraints. -} {- ********************************************************************* ===================================== compiler/GHC/Tc/Utils/Unify.hs ===================================== @@ -2533,12 +2533,16 @@ lhsPriority tv case tcTyVarDetails tv of RuntimeUnk -> 0 SkolemTv {} -> 0 - MetaTv { mtv_info = info } -> case info of - CycleBreakerTv -> 0 - TyVarTv -> 1 - ConcreteTv {} -> 2 - TauTv -> 3 - RuntimeUnkTv -> 4 + MetaTv { mtv_info = info, mtv_tclvl = lvl } + | QLInstVar <- lvl + -> 5 -- Eliminate instantiation variables first + | otherwise + -> case info of + CycleBreakerTv -> 0 + TyVarTv -> 1 + ConcreteTv {} -> 2 + TauTv -> 3 + RuntimeUnkTv -> 4 {- Note [Unification preconditions] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -2908,10 +2912,15 @@ simpleUnifyCheck caller lhs_tv rhs UC_QuickLook -> isQLInstTyVar lhs_tv _ -> isRuntimeUnkTyVar lhs_tv - fam_ok = case caller of - UC_Solver -> True - UC_QuickLook -> True - UC_OnTheFly -> False + -- This fam_ok thing relates to a very specific perf problem + -- See Note [Prevent unification with type families] + -- A couple of QuickLook regression tests rely on unifying with type + -- families, so we let it through there (not very principled, but let's + -- see if it bites us) + fam_ok = case caller of + UC_Solver -> True + UC_QuickLook -> True + UC_OnTheFly -> False go (TyVarTy tv) | lhs_tv == tv = False ===================================== testsuite/tests/simplCore/should_compile/simpl017.stderr ===================================== @@ -1,25 +1,20 @@ - -simpl017.hs:55:5: error: [GHC-83865] - • Couldn't match type: [E m i] -> E' v0 m a - with: forall v. [E m i] -> E' v m a - Expected: m (forall v. [E m i] -> E' v m a) - Actual: m ([E m i] -> E' v0 m a) - • In a stmt of a 'do' block: return f +simpl017.hs:55:12: error: [GHC-46956] + • Couldn't match type ‘v0’ with ‘v’ + Expected: [E m i] -> E' v m a + Actual: [E m i] -> E' v0 m a + because type variable ‘v’ would escape its scope + This (rigid, skolem) type variable is bound by + a type expected by the context: + forall v. [E m i] -> E' v m a + at simpl017.hs:55:12 + • In the first argument of ‘return’, namely ‘f’ + In a stmt of a 'do' block: return f In the first argument of ‘E’, namely ‘(do let ix :: [E m i] -> m i ix [i] = runE i {-# INLINE f #-} .... return f)’ - In the expression: - E (do let ix :: [E m i] -> m i - ix [i] = runE i - {-# INLINE f #-} - .... - return f) • Relevant bindings include f :: [E m i] -> E' v0 m a (bound at simpl017.hs:54:9) - ix :: [E m i] -> m i (bound at simpl017.hs:52:9) - a :: arr i a (bound at simpl017.hs:50:11) - liftArray :: arr i a -> E m (forall v. [E m i] -> E' v m a) - (bound at simpl017.hs:50:1) + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0e7bc76bd62e2f3eda4b73db1feda9cb370fc3ce -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0e7bc76bd62e2f3eda4b73db1feda9cb370fc3ce You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 10:20:24 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Mon, 10 Jun 2024 06:20:24 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] 4 commits: ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Message-ID: <6666d3689a3ea_3bc70d1970814984c8@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: e5d1ee20 by Fabian Kirchner at 2024-06-10T12:20:00+02:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - e1c36eb6 by Fabian Kirchner at 2024-06-10T12:20:00+02:00 ttg: Move some AST types into Language.Haskell.Syntax.Basic In particular, we move: * TopLevelFlag * TypeOrData * TyConFlavour Progress towards #21592 - - - - - 34732024 by Adowrath at 2024-06-10T12:20:00+02:00 ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type Progress towards #21592 This splits HsSrcBang up, creating the new HsBang within `Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness and strictness information, while `HsSrcBang` only adds the SourceText for usage within the compiler directly. Inside the AST, to preserve the SourceText, it is hidden behind the pre-existing extension point `XBindTy`. All other occurrences of `HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when interacting with the `BindTy` constructor, the hidden `SourceText` is extracted/inserted into the `XBindTy` extension point. `GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for convenience. A constructor function `mkHsSrcBang` that takes all individual components has been added. Two exceptions has been made though: - The `Outputable HsSrcBang` instance is replaced by `Outputable HsBang`. While being only GHC-internal, the only place it's used is in outputting `HsBangTy` constructors -- which already have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just to ignore the `SourceText` anyway. - The error `TcRnUnexpectedAnnotation` did not use the `SourceText`, so it too now only holds a `HsBang`. - - - - - 6c9268b2 by Mauricio at 2024-06-10T12:20:00+02:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/CoreToIface.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Build.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var.hs-boot - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Lit.hs - + compiler/Language/Haskell/Syntax/Specificity.hs - compiler/Language/Haskell/Syntax/Type.hs - compiler/ghc.cabal.in - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Backends/LaTeX.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/10d3ad93a80d13d2b8c02eb6f41a322f3c039a50...6c9268b23214709c9c11ca43bab21cd633e87a03 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/10d3ad93a80d13d2b8c02eb6f41a322f3c039a50...6c9268b23214709c9c11ca43bab21cd633e87a03 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 10:20:53 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Mon, 10 Jun 2024 06:20:53 -0400 Subject: [Git][ghc/ghc][wip/romes/ast-ohne-faststring] 5 commits: ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Message-ID: <6666d3858634e_3bc70d1a3e6ec990be@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ast-ohne-faststring at Glasgow Haskell Compiler / GHC Commits: e5d1ee20 by Fabian Kirchner at 2024-06-10T12:20:00+02:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - e1c36eb6 by Fabian Kirchner at 2024-06-10T12:20:00+02:00 ttg: Move some AST types into Language.Haskell.Syntax.Basic In particular, we move: * TopLevelFlag * TypeOrData * TyConFlavour Progress towards #21592 - - - - - 34732024 by Adowrath at 2024-06-10T12:20:00+02:00 ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type Progress towards #21592 This splits HsSrcBang up, creating the new HsBang within `Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness and strictness information, while `HsSrcBang` only adds the SourceText for usage within the compiler directly. Inside the AST, to preserve the SourceText, it is hidden behind the pre-existing extension point `XBindTy`. All other occurrences of `HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when interacting with the `BindTy` constructor, the hidden `SourceText` is extracted/inserted into the `XBindTy` extension point. `GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for convenience. A constructor function `mkHsSrcBang` that takes all individual components has been added. Two exceptions has been made though: - The `Outputable HsSrcBang` instance is replaced by `Outputable HsBang`. While being only GHC-internal, the only place it's used is in outputting `HsBangTy` constructors -- which already have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just to ignore the `SourceText` anyway. - The error `TcRnUnexpectedAnnotation` did not use the `SourceText`, so it too now only holds a `HsBang`. - - - - - 6c9268b2 by Mauricio at 2024-06-10T12:20:00+02:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - 373fc016 by Rodrigo Mesquita at 2024-06-10T12:20:43+02:00 ttg: Start using Text over FastString in the AST Towards the goal of making the AST independent of GHC, this commit starts the task of replacing usages of `FastString` with `Text` in the AST (Language.Haskell.* modules). Even though we /do/ want to use FastStrings -- critically in Names or Ids -- there is no particular reason for the FastStrings that occur in the AST proper to be FastStrings. Primarily, ... Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/CoreToIface.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Data/StringBuffer.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Build.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var.hs-boot - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Decls.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/124aa9ef78819760905056e92f70b761f84d8e10...373fc01607be18425f3f3cd2b690d72c41efd297 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/124aa9ef78819760905056e92f70b761f84d8e10...373fc01607be18425f3f3cd2b690d72c41efd297 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 10:22:52 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Mon, 10 Jun 2024 06:22:52 -0400 Subject: [Git][ghc/ghc][wip/jacco/ast] ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <6666d3fcd9a7e_3bc70d1b03c6c994e9@gitlab.mail> Rodrigo Mesquita pushed to branch wip/jacco/ast at Glasgow Haskell Compiler / GHC Commits: defa7d57 by Jacco Krijnen at 2024-06-10T12:22:43+02:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/defa7d577f4f4a03eda19ff34822929810c8cdc4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/defa7d577f4f4a03eda19ff34822929810c8cdc4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 10:28:20 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Mon, 10 Jun 2024 06:28:20 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/time-splices Message-ID: <6666d54459ed_3bc70d1ccd5481026ac@gitlab.mail> Ben Gamari pushed new branch wip/time-splices at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/time-splices You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 10:28:47 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Mon, 10 Jun 2024 06:28:47 -0400 Subject: [Git][ghc/ghc][wip/time-splices] compiler: Time splice execution Message-ID: <6666d55f9345f_3bc70d1cf6ba0102887@gitlab.mail> Ben Gamari pushed to branch wip/time-splices at Glasgow Haskell Compiler / GHC Commits: 50a8cc33 by Ben Gamari at 2024-06-10T06:28:38-04:00 compiler: Time splice execution - - - - - 2 changed files: - compiler/GHC/Rename/Splice.hs - compiler/GHC/Tc/Utils/Monad.hs Changes: ===================================== compiler/GHC/Rename/Splice.hs ===================================== @@ -360,7 +360,8 @@ runRnSplice :: UntypedSpliceFlavour -> HsUntypedSplice GhcRn -> TcRn (res, [ForeignRef (TH.Q ())]) runRnSplice flavour run_meta ppr_res splice - = do { hooks <- hsc_hooks <$> getTopEnv + = withTimingTcRn (text "splice") (\(x,_) -> () `seq` x) + do { hooks <- hsc_hooks <$> getTopEnv ; splice' <- case runRnSpliceHook hooks of Nothing -> return splice Just h -> h splice ===================================== compiler/GHC/Tc/Utils/Monad.hs ===================================== @@ -43,6 +43,7 @@ module GHC.Tc.Utils.Monad( -- * Debugging traceTc, traceRn, traceOptTcRn, dumpOptTcRn, dumpTcRn, + withTTimingTcRn, getNamePprCtx, printForUserTcRn, traceIf, traceOptIf, @@ -852,6 +853,15 @@ dumpTcRn useUserStyle flag title fmt doc = do else mkDumpStyle name_ppr_ctx liftIO $ logDumpFile logger sty flag title fmt real_doc +withTimingTcRn + :: SDoc -- ^ name of the phase + -> (a -> ()) -- ^ a function to force the result + -> TcRn a + -> TcRn a +withTimingTcRn what force action = do + logger <- getLogger + withTiming logger what force action + -- | Add current location if -dppr-debug -- (otherwise the full location is usually way too much) wrapDocLoc :: SDoc -> TcRn SDoc View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/50a8cc330117e3771e56777aedc28ae48fe79619 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/50a8cc330117e3771e56777aedc28ae48fe79619 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 11:05:06 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 10 Jun 2024 07:05:06 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: users-guide: Fix stylistic issues in 9.12 release notes Message-ID: <6666dde26c2d2_3bc70d27a5c54131410@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 438906c8 by Ben Gamari at 2024-06-10T07:04:57-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - c8b1473e by Hugo Peters at 2024-06-10T07:04:58-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 2 changed files: - compiler/GHC/Core/Opt/Simplify.hs - docs/users_guide/9.12.1-notes.rst Changes: ===================================== compiler/GHC/Core/Opt/Simplify.hs ===================================== @@ -199,7 +199,7 @@ simplifyPgm logger unit_env name_ppr_ctx opts -- Subtract 1 from iteration_no to get the -- number of iterations we actually completed - return ( "Simplifier baled out", iteration_no - 1 + return ( "Simplifier bailed out", iteration_no - 1 , totalise counts_so_far , guts_no_binds { mg_binds = binds, mg_rules = local_rules } ) ===================================== docs/users_guide/9.12.1-notes.rst ===================================== @@ -31,10 +31,10 @@ Language This means that code using :extension:`UnliftedDatatypes` or :extension:`UnliftedNewtypes` can now use :extension:`OverloadedRecordDot`. -- Unboxed Float#/Double# literals now support the HexFloatLiterals extension +- Unboxed ``Float#``/``Double#`` literals now support the HexFloatLiterals extension (`#22155 `_). -- UnliftedFFITypes: GHC will now accept ffi types like: ``(# #) -> T`` where ``(# #)`` +- :extension:`UnliftedFFITypes`: GHC will now accept FFI types like: ``(# #) -> T`` where ``(# #)`` is used as the one and only function argument. Compiler View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ac41d11121f447dd7e6c7fbe3ec31760f1bcb2f8...c8b1473e3cec68b1d3922e9325cc45c98adb12cd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ac41d11121f447dd7e6c7fbe3ec31760f1bcb2f8...c8b1473e3cec68b1d3922e9325cc45c98adb12cd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 11:43:08 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Mon, 10 Jun 2024 07:43:08 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ttg-zurich] Split TTG orphans from internal `Fixity` data type Message-ID: <6666e6cc8be2b_3bc70d2df4894154899@gitlab.mail> Fabian Kirchner pushed to branch wip/kirchner/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: 46162d98 by romes at 2024-06-10T13:42:32+02:00 Split TTG orphans from internal `Fixity` data type Filling in missing instances and creating a separate "semantic" datatype are two different layers of abstraction, and so we should create two different modules for them. Fixed arrow desugaring bug. (This was dead code before.) - - - - - 30 changed files: - compiler/GHC/Builtin/PrimOps.hs - + compiler/GHC/Hs/Basic.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Fixity.hs - compiler/GHC/Types/Fixity/Env.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Extension.hs - compiler/ghc.cabal.in - testsuite/tests/count-deps/CountDepsAst.stdout The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/46162d98caad98e565bc2c316415450f63d2b20e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/46162d98caad98e565bc2c316415450f63d2b20e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 12:11:23 2024 From: gitlab at gitlab.haskell.org (Alexander Foremny (@aforemny)) Date: Mon, 10 Jun 2024 08:11:23 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/aforemny/ttg-remove-source-text Message-ID: <6666ed6bc9256_151ed350d7285589e@gitlab.mail> Alexander Foremny pushed new branch wip/aforemny/ttg-remove-source-text at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/aforemny/ttg-remove-source-text You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 12:14:18 2024 From: gitlab at gitlab.haskell.org (Krzysztof Gogolewski (@monoidal)) Date: Mon, 10 Jun 2024 08:14:18 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T24769 Message-ID: <6666ee1abee66_151ed364a1f46009e@gitlab.mail> Krzysztof Gogolewski pushed new branch wip/T24769 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T24769 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 12:15:21 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Mon, 10 Jun 2024 08:15:21 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ttg-zurich] 9 commits: Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw Message-ID: <6666ee599966f_151ed36b154860442@gitlab.mail> Fabian Kirchner pushed to branch wip/kirchner/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - 1416bd64 by romes at 2024-06-10T14:15:06+02:00 Split TTG orphans from internal `Fixity` data type Filling in missing instances and creating a separate "semantic" datatype are two different layers of abstraction, and so we should create two different modules for them. Fixed arrow desugaring bug. (This was dead code before.) - - - - - 30 changed files: - CODEOWNERS - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - + compiler/GHC/Hs/Basic.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/JS/Ident.hs - compiler/GHC/JS/JStg/Monad.hs - compiler/GHC/JS/JStg/Syntax.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Syntax.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/StgToJS.hs - compiler/GHC/StgToJS/Apply.hs - compiler/GHC/StgToJS/Arg.hs - compiler/GHC/StgToJS/Closure.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/FFI.hs - compiler/GHC/StgToJS/Heap.hs - compiler/GHC/StgToJS/Ids.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/46162d98caad98e565bc2c316415450f63d2b20e...1416bd6416a7c67fedc8c0515f771b642cc0df58 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/46162d98caad98e565bc2c316415450f63d2b20e...1416bd6416a7c67fedc8c0515f771b642cc0df58 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 12:24:10 2024 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Mon, 10 Jun 2024 08:24:10 -0400 Subject: [Git][ghc/ghc][wip/expansions-appdo] Make ApplicativeDo work with HsExpansions Message-ID: <6666f06aa5a38_151ed3897a24663ac@gitlab.mail> Apoorv Ingle pushed to branch wip/expansions-appdo at Glasgow Haskell Compiler / GHC Commits: 57d640c5 by Apoorv Ingle at 2024-06-09T14:54:40-05:00 Make ApplicativeDo work with HsExpansions testcase added: T24406 Issues Fixed: #24406, #16135 Code Changes: - Remove `XStmtLR GhcTc` as `XStmtLR GhcRn` is now compiled to `HsExpr GhcTc` - The expanded statements are guided by `GHC.Hs.Expr.TcFunInfo` which is used to decide if the `XExpr GhcRn` is to be typechecked using `tcApp` or `tcExpr` Note [Expanding HsDo with XXExprGhcRn] explains the change in more detail - - - - - 29 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Do.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Zonk/Type.hs - testsuite/tests/ado/T13242a.stderr - testsuite/tests/ado/T16135.hs - − testsuite/tests/ado/T16135.stderr - + testsuite/tests/ado/T24406.hs - testsuite/tests/ado/ado002.stderr - testsuite/tests/ado/ado003.stderr - testsuite/tests/ado/ado004.stderr - testsuite/tests/ado/all.T - testsuite/tests/determinism/determ021/determ021.stdout - testsuite/tests/ghci.debugger/scripts/break029.stdout - testsuite/tests/hiefile/should_run/T23540.stdout Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -473,11 +473,14 @@ type instance XXExpr GhcTc = XXExprGhcTc * * ********************************************************************* -} +-- | Hint to the typechecker how to typecheck the expanded expression +data TCFunInfo = TcApp | TcExpr + -- | The different source constructs that we use to instantiate the "original" field -- in an `XXExprGhcRn original expansion` data HsThingRn = OrigExpr (HsExpr GhcRn) - | OrigStmt (ExprLStmt GhcRn) - | OrigPat (LPat GhcRn) + | OrigStmt (ExprLStmt GhcRn) HsDoFlavour -- ^ which kind of do-block did this statement come from + | OrigPat (LPat GhcRn) (Maybe (HsDoFlavour, ExprLStmt GhcRn)) isHsThingRnExpr, isHsThingRnStmt, isHsThingRnPat :: HsThingRn -> Bool isHsThingRnExpr (OrigExpr{}) = True @@ -491,7 +494,10 @@ isHsThingRnPat _ = False data XXExprGhcRn = ExpandedThingRn { xrn_orig :: HsThingRn -- The original source thing - , xrn_expanded :: HsExpr GhcRn } -- The compiler generated expanded thing + , xrn_expanded :: HsExpr GhcRn -- The compiler generated expanded thing + , xrn_TCFunInfo :: TCFunInfo } -- A Hint to the type checker of how to proceed + -- TcApp <=> use GHC.Tc.Gen.Expr.tcApp + -- TcExpr <=> use GHC.Tc.Gen.Expr.tcExpr | PopErrCtxt -- A hint for typechecker to pop {-# UNPACK #-} !(LHsExpr GhcRn) -- the top of the error context stack @@ -515,22 +521,25 @@ mkExpandedExpr :: HsExpr GhcRn -- ^ source expression -> HsExpr GhcRn -- ^ expanded expression -> HsExpr GhcRn -- ^ suitably wrapped 'XXExprGhcRn' -mkExpandedExpr oExpr eExpr = XExpr (ExpandedThingRn (OrigExpr oExpr) eExpr) +mkExpandedExpr oExpr eExpr = XExpr (ExpandedThingRn (OrigExpr oExpr) eExpr TcExpr) -- | Build an expression using the extension constructor `XExpr`, -- and the two components of the expansion: original do stmt and -- expanded expression mkExpandedStmt :: ExprLStmt GhcRn -- ^ source statement + -> HsDoFlavour + -> TCFunInfo -> HsExpr GhcRn -- ^ expanded expression -> HsExpr GhcRn -- ^ suitably wrapped 'XXExprGhcRn' -mkExpandedStmt oStmt eExpr = XExpr (ExpandedThingRn (OrigStmt oStmt) eExpr) +mkExpandedStmt oStmt flav tc_fun eExpr = XExpr (ExpandedThingRn (OrigStmt oStmt flav) eExpr tc_fun) mkExpandedPatRn - :: LPat GhcRn -- ^ source pattern - -> HsExpr GhcRn -- ^ expanded expression - -> HsExpr GhcRn -- ^ suitably wrapped 'XXExprGhcRn' -mkExpandedPatRn oPat eExpr = XExpr (ExpandedThingRn (OrigPat oPat) eExpr) + :: LPat GhcRn -- ^ source pattern + -> Maybe (HsDoFlavour, ExprLStmt GhcRn) -- ^ pattern statement origin + -> HsExpr GhcRn -- ^ expanded expression + -> HsExpr GhcRn -- ^ suitably wrapped 'XXExprGhcRn' +mkExpandedPatRn oPat mb_stmt_info eExpr = XExpr (ExpandedThingRn (OrigPat oPat mb_stmt_info) eExpr TcExpr) -- | Build an expression using the extension constructor `XExpr`, -- and the two components of the expansion: original do stmt and @@ -538,17 +547,21 @@ mkExpandedPatRn oPat eExpr = XExpr (ExpandedThingRn (OrigPat oPat) eExpr) mkExpandedStmtAt :: SrcSpanAnnA -- ^ Location for the expansion expression -> ExprLStmt GhcRn -- ^ source statement + -> HsDoFlavour + -> TCFunInfo -> HsExpr GhcRn -- ^ expanded expression -> LHsExpr GhcRn -- ^ suitably wrapped located 'XXExprGhcRn' -mkExpandedStmtAt loc oStmt eExpr = L loc $ mkExpandedStmt oStmt eExpr +mkExpandedStmtAt loc oStmt flav tcFun eExpr = L loc $ mkExpandedStmt oStmt flav tcFun eExpr -- | Wrap the expanded version of the expression with a pop. mkExpandedStmtPopAt :: SrcSpanAnnA -- ^ Location for the expansion statement -> ExprLStmt GhcRn -- ^ source statement + -> HsDoFlavour + -> TCFunInfo -> HsExpr GhcRn -- ^ expanded expression -> LHsExpr GhcRn -- ^ suitably wrapped 'XXExprGhcRn' -mkExpandedStmtPopAt loc oStmt eExpr = mkPopErrCtxtExprAt loc $ mkExpandedStmtAt loc oStmt eExpr +mkExpandedStmtPopAt loc oStmt flav tc_fun eExpr = mkPopErrCtxtExprAt loc $ mkExpandedStmtAt loc oStmt flav tc_fun eExpr data XXExprGhcTc @@ -593,9 +606,10 @@ mkExpandedExprTc oExpr eExpr = XExpr (ExpandedThingTc (OrigExpr oExpr) eExpr) -- expanded typechecked expression. mkExpandedStmtTc :: ExprLStmt GhcRn -- ^ source do statement + -> HsDoFlavour -> HsExpr GhcTc -- ^ expanded typechecked expression -> HsExpr GhcTc -- ^ suitably wrapped 'XXExprGhcRn' -mkExpandedStmtTc oStmt eExpr = XExpr (ExpandedThingTc (OrigStmt oStmt) eExpr) +mkExpandedStmtTc oStmt flav eExpr = XExpr (ExpandedThingTc (OrigStmt oStmt flav) eExpr) {- ********************************************************************* * * @@ -836,13 +850,13 @@ instance Outputable HsThingRn where ppr thing = case thing of OrigExpr x -> ppr_builder ":" x - OrigStmt x -> ppr_builder ":" x - OrigPat x -> ppr_builder ":" x + OrigStmt x _ -> ppr_builder ":" x + OrigPat x _ -> ppr_builder ":" x where ppr_builder prefix x = ifPprDebug (braces (text prefix <+> parens (ppr x))) (ppr x) instance Outputable XXExprGhcRn where - ppr (ExpandedThingRn o e) = ifPprDebug (braces $ vcat [ppr o, ppr e]) (ppr o) - ppr (PopErrCtxt e) = ifPprDebug (braces (text "" <+> ppr e)) (ppr e) + ppr (ExpandedThingRn o e _) = ifPprDebug (braces $ vcat [ppr o, text ";;" , ppr e]) (ppr o) + ppr (PopErrCtxt e) = ifPprDebug (braces (text "" <+> ppr e)) (ppr e) instance Outputable XXExprGhcTc where ppr (WrapExpr (HsWrap co_fn e)) @@ -882,7 +896,7 @@ ppr_infix_expr (XExpr x) = case ghcPass @p of ppr_infix_expr _ = Nothing ppr_infix_expr_rn :: XXExprGhcRn -> Maybe SDoc -ppr_infix_expr_rn (ExpandedThingRn thing _) = ppr_infix_hs_expansion thing +ppr_infix_expr_rn (ExpandedThingRn thing _ _) = ppr_infix_hs_expansion thing ppr_infix_expr_rn (PopErrCtxt (L _ a)) = ppr_infix_expr a ppr_infix_expr_tc :: XXExprGhcTc -> Maybe SDoc @@ -993,7 +1007,7 @@ hsExprNeedsParens prec = go go_x_tc (HsBinTick _ _ (L _ e)) = hsExprNeedsParens prec e go_x_rn :: XXExprGhcRn -> Bool - go_x_rn (ExpandedThingRn thing _) = hsExpandedNeedsParens thing + go_x_rn (ExpandedThingRn thing _ _) = hsExpandedNeedsParens thing go_x_rn (PopErrCtxt (L _ a)) = hsExprNeedsParens prec a hsExpandedNeedsParens :: HsThingRn -> Bool @@ -1045,7 +1059,7 @@ isAtomicHsExpr (XExpr x) go_x_tc (HsBinTick {}) = False go_x_rn :: XXExprGhcRn -> Bool - go_x_rn (ExpandedThingRn thing _) = isAtomicExpandedThingRn thing + go_x_rn (ExpandedThingRn thing _ _) = isAtomicExpandedThingRn thing go_x_rn (PopErrCtxt (L _ a)) = isAtomicHsExpr a isAtomicExpandedThingRn :: HsThingRn -> Bool @@ -1568,7 +1582,7 @@ pprMatch (Match { m_pats = pats, m_ctxt = ctxt, m_grhss = grhss }) <+> pprInfixOcc fun <+> pprParendLPat opPrec p2 _ -> pprPanic "pprMatch" (ppr ctxt $$ ppr pats) - + StmtCtxt _ -> (char '\\', pats) LamAlt LamSingle -> (char '\\', pats) ArrowMatchCtxt (ArrowLamAlt LamSingle) -> (char '\\', pats) LamAlt LamCases -> lam_cases_result @@ -1609,6 +1623,7 @@ matchSeparator IfAlt = text "->" matchSeparator ArrowMatchCtxt{} = text "->" matchSeparator PatBindRhs = text "=" matchSeparator PatBindGuards = text "=" +matchSeparator (StmtCtxt (HsDoStmt{})) = text "->" matchSeparator StmtCtxt{} = text "<-" matchSeparator RecUpd = text "=" -- This can be printed by the pattern matchSeparator PatSyn = text "<-" -- match checker trace @@ -1668,7 +1683,7 @@ data XBindStmtTc = XBindStmtTc type instance XApplicativeStmt (GhcPass _) GhcPs = NoExtField type instance XApplicativeStmt (GhcPass _) GhcRn = NoExtField -type instance XApplicativeStmt (GhcPass _) GhcTc = Type +type instance XApplicativeStmt (GhcPass _) GhcTc = DataConCantHappen type instance XBodyStmt (GhcPass _) GhcPs b = NoExtField type instance XBodyStmt (GhcPass _) GhcRn b = NoExtField @@ -1690,7 +1705,7 @@ type instance XRecStmt (GhcPass _) GhcTc b = RecStmtTc type instance XXStmtLR (GhcPass _) GhcPs b = DataConCantHappen type instance XXStmtLR (GhcPass x) GhcRn b = ApplicativeStmt (GhcPass x) GhcRn -type instance XXStmtLR (GhcPass x) GhcTc b = ApplicativeStmt (GhcPass x) GhcTc +type instance XXStmtLR (GhcPass x) GhcTc b = DataConCantHappen -- | 'ApplicativeStmt' represents an applicative expression built with -- '<$>' and '<*>'. It is generated by the renamer, and is desugared into the @@ -1731,7 +1746,7 @@ data ApplicativeArg idL | ApplicativeArgMany -- do { stmts; return vars } { xarg_app_arg_many :: XApplicativeArgMany idL , app_stmts :: [ExprLStmt idL] -- stmts - , final_expr :: HsExpr idL -- return (v1,..,vn), or just (v1,..,vn) + , final_expr :: LHsExpr idL -- return (v1,..,vn), or just (v1,..,vn) , bv_pattern :: LPat idL -- (v1,...,vn) , stmt_context :: HsDoFlavour -- ^ context of the do expression, used in pprArg @@ -1750,7 +1765,7 @@ type instance XXParStmtBlock (GhcPass pL) (GhcPass pR) = DataConCantHappen type instance XApplicativeArgOne GhcPs = NoExtField type instance XApplicativeArgOne GhcRn = FailOperator GhcRn -type instance XApplicativeArgOne GhcTc = FailOperator GhcTc +type instance XApplicativeArgOne GhcTc = DataConCantHappen type instance XApplicativeArgMany (GhcPass _) = NoExtField type instance XXApplicativeArg (GhcPass _) = DataConCantHappen @@ -1796,7 +1811,6 @@ pprStmt (RecStmt { recS_stmts = segment, recS_rec_ids = rec_ids pprStmt (XStmtLR x) = case ghcPass :: GhcPass idR of GhcRn -> pprApplicativeStmt x - GhcTc -> pprApplicativeStmt x where pprApplicativeStmt :: (OutputableBndrId idL, OutputableBndrId idR) => ApplicativeStmt (GhcPass idL) (GhcPass idR) -> SDoc @@ -1817,7 +1831,6 @@ pprStmt (XStmtLR x) = case ghcPass :: GhcPass idR of flattenStmt :: ExprLStmt (GhcPass idL) -> [SDoc] flattenStmt (L _ (XStmtLR x)) = case ghcPass :: GhcPass idL of GhcRn | (ApplicativeStmt _ args _) <- x -> concatMap flattenArg args - GhcTc | (ApplicativeStmt _ args _) <- x -> concatMap flattenArg args flattenStmt stmt = [ppr stmt] flattenArg :: (a, ApplicativeArg (GhcPass idL)) -> [SDoc] @@ -1846,13 +1859,13 @@ instance (OutputableBndrId idL) pprArg :: forall idL . (OutputableBndrId idL) => ApplicativeArg (GhcPass idL) -> SDoc pprArg (ApplicativeArgOne _ pat expr isBody) - | isBody = ppr expr -- See Note [Applicative BodyStmt] - | otherwise = pprBindStmt pat expr + | isBody = whenPprDebug (text "[AppStmt]") <+> ppr expr -- See Note [Applicative BodyStmt] + | otherwise = whenPprDebug (text "[AppStmt]") <+> pprBindStmt pat expr pprArg (ApplicativeArgMany _ stmts return pat ctxt) = ppr pat <+> text "<-" <+> pprDo ctxt (stmts ++ - [noLocA (LastStmt noExtField (noLocA return) Nothing noSyntaxExpr)]) + [noLocA (LastStmt noExtField return Nothing noSyntaxExpr)]) pprTransformStmt :: (OutputableBndrId p) => [IdP (GhcPass p)] -> LHsExpr (GhcPass p) ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -569,6 +569,7 @@ deriving instance Eq (IE GhcTc) -- --------------------------------------------------------------------- deriving instance Data HsThingRn +deriving instance Data TCFunInfo deriving instance Data XXExprGhcRn deriving instance Data XXExprGhcTc deriving instance Data XXPatGhcTc ===================================== compiler/GHC/Hs/Utils.hs ===================================== @@ -1188,7 +1188,6 @@ collectStmtBinders flag = \case RecStmt { recS_stmts = L _ ss } -> collectLStmtsBinders flag ss XStmtLR x -> case ghcPass :: GhcPass idR of GhcRn -> collectApplicativeStmtBndrs x - GhcTc -> collectApplicativeStmtBndrs x where collectApplicativeStmtBndrs :: ApplicativeStmt (GhcPass idL) a -> [IdP (GhcPass idL)] collectApplicativeStmtBndrs (ApplicativeStmt _ args _) = concatMap (collectArgBinders . snd) args @@ -1781,7 +1780,6 @@ lStmtsImplicits = hs_lstmts hs_stmt (BindStmt _ pat _) = lPatImplicits pat hs_stmt (XStmtLR x) = case ghcPass :: GhcPass idR of GhcRn -> hs_applicative_stmt x - GhcTc -> hs_applicative_stmt x hs_stmt (LetStmt _ binds) = hs_local_binds binds hs_stmt (BodyStmt {}) = [] hs_stmt (LastStmt {}) = [] ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -315,7 +315,7 @@ dsExpr (HsOverLit _ lit) dsExpr e@(XExpr ext_expr_tc) = case ext_expr_tc of ExpandedThingTc o e - | OrigStmt (L loc _) <- o + | OrigStmt (L loc _) _ <- o -> putSrcSpanDsA loc $ dsExpr e | otherwise -> dsExpr e WrapExpr {} -> dsHsWrapped e @@ -463,10 +463,10 @@ dsExpr (HsLet _ binds body) = do -- because the interpretation of `stmts' depends on what sort of thing it is. -- dsExpr (HsDo res_ty ListComp (L _ stmts)) = dsListComp stmts res_ty -dsExpr (HsDo res_ty ctx at DoExpr{} (L _ stmts)) = dsDo ctx stmts res_ty -dsExpr (HsDo res_ty ctx at GhciStmtCtxt (L _ stmts)) = dsDo ctx stmts res_ty -dsExpr (HsDo res_ty ctx at MDoExpr{} (L _ stmts)) = dsDo ctx stmts res_ty dsExpr (HsDo _ MonadComp (L _ stmts)) = dsMonadComp stmts +dsExpr (HsDo res_ty ctx at GhciStmtCtxt (L _ stmts)) = dsDo ctx stmts res_ty +dsExpr (HsDo _ DoExpr{} (L _ stmts)) = pprPanic "shouldn't happen dsDo DoExpr" (ppr stmts) +dsExpr (HsDo _ MDoExpr{} (L _ stmts)) = pprPanic "shouldn't happen dsDo MDoExpr" (ppr stmts) dsExpr (HsIf _ guard_expr then_expr else_expr) = do { pred <- dsLExpr guard_expr @@ -823,37 +823,6 @@ dsDo ctx stmts res_ty -- which ignores the return_op in the LastStmt, -- so we must apply the return_op explicitly - go _ (XStmtLR (ApplicativeStmt body_ty args mb_join)) stmts - = do { - let - (pats, rhss) = unzip (map (do_arg . snd) args) - - do_arg (ApplicativeArgOne fail_op pat expr _) = - ((pat, fail_op), dsLExpr expr) - do_arg (ApplicativeArgMany _ stmts ret pat _) = - ((pat, Nothing), dsDo ctx (stmts ++ [noLocA $ mkLastStmt (noLocA ret)]) res_ty) - - ; rhss' <- sequence rhss - - ; body' <- dsLExpr $ noLocA $ HsDo body_ty ctx (noLocA stmts) - - ; let match_args (pat, fail_op) (vs,body) - = putSrcSpanDs (getLocA pat) $ - do { var <- selectSimpleMatchVarL ManyTy pat - ; match <- matchSinglePatVar var Nothing (StmtCtxt (HsDoStmt ctx)) pat - body_ty (cantFailMatchResult body) - ; match_code <- dsHandleMonadicFailure ctx pat body_ty match fail_op - ; return (var:vs, match_code) - } - - ; (vars, body) <- foldrM match_args ([],body') pats - ; let fun' = mkLams vars body - ; let mk_ap_call l (op,r) = dsSyntaxExpr op [l,r] - ; expr <- foldlM mk_ap_call fun' (zip (map fst args) rhss') - ; case mb_join of - Nothing -> return expr - Just join_op -> dsSyntaxExpr join_op [expr] } - go _ (ParStmt {}) _ = panic "dsDo ParStmt" go _ (TransStmt {}) _ = panic "dsDo TransStmt" ===================================== compiler/GHC/HsToCore/GuardedRHSs.hs ===================================== @@ -144,8 +144,6 @@ matchGuards (LastStmt {} : _) _ _ _ _ = panic "matchGuards LastStmt" matchGuards (ParStmt {} : _) _ _ _ _ = panic "matchGuards ParStmt" matchGuards (TransStmt {} : _) _ _ _ _ = panic "matchGuards TransStmt" matchGuards (RecStmt {} : _) _ _ _ _ = panic "matchGuards RecStmt" -matchGuards (XStmtLR ApplicativeStmt {} : _) _ _ _ _ = - panic "matchGuards ApplicativeLastStmt" {- Should {\em fail} if @e@ returns @D@ ===================================== compiler/GHC/HsToCore/ListComp.hs ===================================== @@ -257,9 +257,6 @@ deListComp (ParStmt _ stmtss_w_bndrs _ _ : quals) list deListComp (RecStmt {} : _) _ = panic "deListComp RecStmt" -deListComp (XStmtLR ApplicativeStmt {} : _) _ = - panic "deListComp ApplicativeStmt" - deBindComp :: LPat GhcTc -> CoreExpr -> [ExprStmt GhcTc] @@ -352,8 +349,6 @@ dfListComp c_id n_id (BindStmt _ pat list1 : quals) = do dfListComp _ _ (ParStmt {} : _) = panic "dfListComp ParStmt" dfListComp _ _ (RecStmt {} : _) = panic "dfListComp RecStmt" -dfListComp _ _ (XStmtLR ApplicativeStmt {} : _) = - panic "dfListComp ApplicativeStmt" dfBindComp :: Id -> Id -- 'c' and 'n' -> (LPat GhcTc, CoreExpr) @@ -580,7 +575,6 @@ dsMcStmt (ParStmt bind_ty blocks mzip_op bind_op) stmts_rest = do { exp <- dsInnerMonadComp stmts bndrs return_op ; return (exp, mkBigCoreVarTupTy bndrs) } -dsMcStmt stmt@(XStmtLR ApplicativeStmt {}) _ = pprPanic "dsMcStmt: unexpected stmt" (ppr stmt) dsMcStmt stmt@(RecStmt {}) _ = pprPanic "dsMcStmt: unexpected stmt" (ppr stmt) matchTuple :: [Id] -> CoreExpr -> DsM CoreExpr ===================================== compiler/GHC/HsToCore/Pmc/Desugar.hs ===================================== @@ -373,7 +373,6 @@ desugarGuard guard = case guard of ParStmt {} -> panic "desugarGuard ParStmt" TransStmt {} -> panic "desugarGuard TransStmt" RecStmt {} -> panic "desugarGuard RecStmt" - XStmtLR ApplicativeStmt{} -> panic "desugarGuard ApplicativeLastStmt" sequenceGrdDagMapM :: Applicative f => (a -> f GrdDag) -> [a] -> f GrdDag sequenceGrdDagMapM f as = sequenceGrdDags <$> traverse f as ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -1684,7 +1684,7 @@ repE (HsProjection _ xs) = repProjection (fmap (field_label . unLoc . dfoLabel . repE (HsEmbTy _ t) = do t1 <- repLTy (hswc_body t) rep2 typeEName [unC t1] -repE e@(XExpr (ExpandedThingRn o x)) +repE e@(XExpr (ExpandedThingRn o x _)) | OrigExpr e <- o = do { rebindable_on <- lift $ xoptM LangExt.RebindableSyntax ; if rebindable_on -- See Note [Quotation and rebindable syntax] ===================================== compiler/GHC/HsToCore/Ticks.hs ===================================== @@ -611,7 +611,7 @@ addTickHsExpr (HsDo srcloc cxt (L l stmts)) _ -> Nothing addTickHsExpanded :: HsThingRn -> HsExpr GhcTc -> TM (HsExpr GhcTc) -addTickHsExpanded o@(OrigStmt (L pos LastStmt{})) e +addTickHsExpanded o@(OrigStmt (L pos LastStmt{}) _) e -- LastStmt always gets a tick for breakpoint and hpc coverage = do d <- getDensity case d of @@ -752,33 +752,10 @@ addTickStmt isGuard stmt@(RecStmt {}) ; return (stmt { recS_stmts = noLocA stmts', recS_ret_fn = ret' , recS_mfix_fn = mfix', recS_bind_fn = bind' }) } -addTickStmt isGuard (XStmtLR (ApplicativeStmt body_ty args mb_join)) = do - args' <- mapM (addTickApplicativeArg isGuard) args - return (XStmtLR (ApplicativeStmt body_ty args' mb_join)) - addTick :: Maybe (Bool -> BoxLabel) -> LHsExpr GhcTc -> TM (LHsExpr GhcTc) addTick isGuard e | Just fn <- isGuard = addBinTickLHsExpr fn e | otherwise = addTickLHsExprRHS e -addTickApplicativeArg - :: Maybe (Bool -> BoxLabel) -> (SyntaxExpr GhcTc, ApplicativeArg GhcTc) - -> TM (SyntaxExpr GhcTc, ApplicativeArg GhcTc) -addTickApplicativeArg isGuard (op, arg) = - liftM2 (,) (addTickSyntaxExpr hpcSrcSpan op) (addTickArg arg) - where - addTickArg (ApplicativeArgOne m_fail pat expr isBody) = - ApplicativeArgOne - <$> mapM (addTickSyntaxExpr hpcSrcSpan) m_fail - <*> addTickLPat pat - <*> addTickLHsExpr expr - <*> pure isBody - addTickArg (ApplicativeArgMany x stmts ret pat ctxt) = - (ApplicativeArgMany x) - <$> addTickLStmts isGuard stmts - <*> (unLoc <$> addTickLHsExpr (L (noAnnSrcSpan hpcSrcSpan) ret)) - <*> addTickLPat pat - <*> pure ctxt - addTickStmtAndBinders :: Maybe (Bool -> BoxLabel) -> ParStmtBlock GhcTc GhcTc -> TM (ParStmtBlock GhcTc GhcTc) addTickStmtAndBinders isGuard (ParStmtBlock x stmts ids returnExpr) = @@ -967,8 +944,6 @@ addTickCmdStmt stmt@(RecStmt {}) ; bind' <- addTickSyntaxExpr hpcSrcSpan (recS_bind_fn stmt) ; return (stmt { recS_stmts = noLocA stmts', recS_ret_fn = ret' , recS_mfix_fn = mfix', recS_bind_fn = bind' }) } -addTickCmdStmt (XStmtLR (ApplicativeStmt{})) = - panic "ToDo: addTickCmdStmt ApplicativeLastStmt" -- Others should never happen in a command context. addTickCmdStmt stmt = pprPanic "addTickHsCmd" (ppr stmt) ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1372,7 +1372,6 @@ instance ( ToHie (LocatedA (body (GhcPass p))) ] XStmtLR x -> case hiePass @p of HieRn -> extApplicativeStmt x - HieTc -> extApplicativeStmt x where node = case hiePass @p of HieTc -> makeNodeA stmt span ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -1965,15 +1965,10 @@ ApplicativeDo touches a few phases in the compiler: don't exist in the source code. See ApplicativeStmt and ApplicativeArg in HsExpr. -* Typechecker: ApplicativeDo passes through the typechecker much like any - other form of expression. The only crux is that the typechecker has to - be aware of the special ApplicativeDo statements in the do-notation, and - typecheck them appropriately. - Relevant module: GHC.Tc.Gen.Match - -* Desugarer: Any do-block which contains applicative statements is desugared - as outlined above, to use the Applicative combinators. - Relevant module: GHC.HsToCore.Expr +* Typechecker: All the ApplicativeDo statements are expanded on the fly + to its actual semantics (as shown above) with appropriate user syntax. The typechecker + then checks the syntax as any other form of expression. + Relevant module: GHC.Tc.Gen.Do , GHC.Tc.Gen.Match.tcStmts -} @@ -2221,12 +2216,12 @@ stmtTreeToStmts monad_names ctxt (StmtTreeApplicative trees) tail tail_fvs = do (stmts',fvs2) <- stmtTreeToStmts monad_names ctxt tree [] pvarset (mb_ret, fvs1) <- if | L _ (XStmtLR ApplicativeStmt{}) <- last stmts' -> - return (unLoc tup, emptyNameSet) + return (tup, emptyNameSet) | otherwise -> do -- Need 'pureAName' and not 'returnMName' here, so that it requires -- 'Applicative' and not 'Monad' whenever possible (until #20540 is fixed). (ret, _) <- lookupQualifiedDoExpr (HsDoStmt ctxt) pureAName - let expr = HsApp noExtField (noLocA ret) tup + let expr = noLocA (HsApp noExtField (noLocA ret) tup) return (expr, emptyFVs) return ( ApplicativeArgMany { xarg_app_arg_many = noExtField ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -465,9 +465,9 @@ tcValArgs do_ql args -- Now check the argument ; arg' <- tcScalingUsage mult $ do { traceTc "tcEValArg" $ - vcat [ ppr ctxt - , text "arg type:" <+> ppr arg_ty - , text "arg:" <+> ppr arg ] + vcat [ ppr ctxt + , text "arg type:" <+> ppr arg_ty + , text "arg:" <+> ppr arg ] ; tcEValArg ctxt arg arg_ty } ; return (eva { eva_arg = ValArg arg' @@ -537,7 +537,7 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args fun_orig | VAExpansion (OrigStmt{}) _ _ <- fun_ctxt = DoOrigin - | VAExpansion (OrigPat pat) _ _ <- fun_ctxt + | VAExpansion (OrigPat pat _) _ _ <- fun_ctxt = DoPatOrigin pat | VAExpansion (OrigExpr e) _ _ <- fun_ctxt = exprCtOrigin e @@ -733,7 +733,6 @@ tcInstFun do_ql inst_final (tc_fun, fun_ctxt) fun_sigma rn_args matchActualFunTy herald (Just $ HsExprTcThing tc_fun) (n_val_args, fun_sigma) fun_ty - ; (delta', arg') <- if do_ql then addArgCtxt ctxt arg $ -- Context needed for constraints @@ -796,23 +795,32 @@ addArgCtxt :: AppCtxt -> LHsExpr GhcRn addArgCtxt ctxt (L arg_loc arg) thing_inside = do { in_generated_code <- inGeneratedCode ; case ctxt of - VACall fun arg_no _ | not in_generated_code + VACall{} + | XExpr (PopErrCtxt{}) <- arg + -> thing_inside + VACall{} + | XExpr (ExpandedThingRn o _ _) <- arg + , isHsThingRnStmt o || isHsThingRnPat o + -> thing_inside + + VACall fun arg_no _ + | not in_generated_code -> do setSrcSpanA arg_loc $ addErrCtxt (funAppCtxt fun arg arg_no) $ thing_inside - VAExpansion (OrigStmt (L _ stmt@(BindStmt {}))) _ loc + VAExpansion (OrigStmt (L _ stmt@(BindStmt {})) flav) _ loc | isGeneratedSrcSpan (locA arg_loc) -- This arg is the second argument to generated (>>=) -> setSrcSpan loc $ - addStmtCtxt stmt $ + addStmtCtxt stmt flav $ thing_inside - | otherwise -- This arg is the first argument to generated (>>=) + | otherwise -- This arg is the first argument to generated (>>=) -> setSrcSpanA arg_loc $ - addStmtCtxt stmt $ + addStmtCtxt stmt flav $ thing_inside - VAExpansion (OrigStmt (L loc stmt)) _ _ + VAExpansion (OrigStmt (L loc stmt) flav) _ _ -> setSrcSpanA loc $ - addStmtCtxt stmt $ + addStmtCtxt stmt flav $ thing_inside _ -> setSrcSpanA arg_loc $ @@ -943,7 +951,7 @@ expr_to_type earg = | otherwise = not_in_scope where occ = occName rdr not_in_scope = failWith $ mkTcRnNotInScope rdr NotInScope - go (L l (XExpr (ExpandedThingRn (OrigExpr orig) _))) = + go (L l (XExpr (ExpandedThingRn (OrigExpr orig) _ _))) = -- Use the original, user-written expression (before expansion). -- Example. Say we have vfun :: forall a -> blah -- and the call vfun (Maybe [1,2,3]) ===================================== compiler/GHC/Tc/Gen/Do.hs ===================================== @@ -21,8 +21,8 @@ module GHC.Tc.Gen.Do (expandDoStmts) where import GHC.Prelude -import GHC.Rename.Utils ( wrapGenSpan, genHsExpApps, genHsApp, genHsLet, - genHsLamDoExp, genHsCaseAltDoExp, genWildPat ) +import GHC.Rename.Utils ( wrapGenSpan, genHsExpApps, genHsApp, genHsLet, genLHsApp, + genHsLamDoExp, genHsCaseAltDoExp ) import GHC.Tc.Utils.Monad import GHC.Tc.Gen.Pat import GHC.Tc.Utils.TcMType @@ -53,66 +53,56 @@ import Data.List ((\\)) -- so that they can be typechecked. -- See Note [Expanding HsDo with XXExprGhcRn] below for `HsDo` specific commentary -- and Note [Handling overloaded and rebindable constructs] for high level commentary -expandDoStmts :: HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (LHsExpr GhcRn) -expandDoStmts doFlav stmts = do expanded_expr <- expand_do_stmts doFlav stmts - case expanded_expr of - L _ (XExpr (PopErrCtxt e)) -> return e - -- The first expanded stmt doesn't need a pop as - -- it would otherwise pop the "In the expression do ... " from - -- the error context - _ -> return expanded_expr +expandDoStmts :: HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (HsExpr GhcRn) +expandDoStmts doFlav stmts = unLoc <$> expand_do_stmts False doFlav stmts -- | The main work horse for expanding do block statements into applications of binds and thens -- See Note [Expanding HsDo with XXExprGhcRn] -expand_do_stmts :: HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (LHsExpr GhcRn) +expand_do_stmts :: Bool -> HsDoFlavour -> [ExprLStmt GhcRn] -> TcM (LHsExpr GhcRn) -expand_do_stmts ListComp _ = +expand_do_stmts _ ListComp _ = pprPanic "expand_do_stmts: impossible happened. ListComp" empty -- handeled by `GHC.Tc.Gen.Match.tcLcStmt` -expand_do_stmts _ [] = pprPanic "expand_do_stmts: impossible happened. Empty stmts" empty +expand_do_stmts _ _ [] = pprPanic "expand_do_stmts: impossible happened. Empty stmts" empty -expand_do_stmts _ (stmt@(L _ (TransStmt {})):_) = +expand_do_stmts _ _ (stmt@(L _ (TransStmt {})):_) = pprPanic "expand_do_stmts: TransStmt" $ ppr stmt -- handeled by `GHC.Tc.Gen.Match.tcLcStmt` -expand_do_stmts _ (stmt@(L _ (ParStmt {})):_) = +expand_do_stmts _ _ (stmt@(L _ (ParStmt {})):_) = pprPanic "expand_do_stmts: ParStmt" $ ppr stmt -- handeled by `GHC.Tc.Gen.Match.tcLcStmt` -expand_do_stmts _ (stmt@(L _ (XStmtLR ApplicativeStmt{})): _) = - pprPanic "expand_do_stmts: Applicative Stmt" $ ppr stmt - -- Handeled by tcSyntaxOp see `GHC.Tc.Gen.Match.tcStmtsAndThen` - - -expand_do_stmts _ [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_expr))] +expand_do_stmts addPop flav [stmt@(L loc (LastStmt _ (L body_loc body) _ ret_expr))] -- See Note [Expanding HsDo with XXExprGhcRn] Equation (5) below -- last statement of a list comprehension, needs to explicitly return it -- See `checkLastStmt` and `Syntax.Expr.StmtLR.LastStmt` | NoSyntaxExprRn <- ret_expr -- Last statement is just body if we are not in ListComp context. See Syntax.Expr.LastStmt - = do traceTc "expand_do_stmts last" (ppr ret_expr) - return $ mkExpandedStmtPopAt loc stmt body + = return $ if addPop then mkExpandedStmtPopAt loc stmt flav TcExpr body + else mkExpandedStmtAt loc stmt flav TcExpr body | SyntaxExprRn ret <- ret_expr -- -- ------------------------------------------------ -- return e ~~> return e -- to make T18324 work - = do traceTc "expand_do_stmts last" (ppr ret_expr) - let expansion = genHsApp ret (L body_loc body) - return $ mkExpandedStmtPopAt loc stmt expansion + = do let expansion = genHsApp ret (L body_loc body) + return $ if addPop then mkExpandedStmtPopAt loc stmt flav TcExpr expansion + else mkExpandedStmtAt loc stmt flav TcExpr expansion -expand_do_stmts do_or_lc (stmt@(L loc (LetStmt _ bs)) : lstmts) = +expand_do_stmts addPop doFlavour (stmt@(L loc (LetStmt _ bs)) : lstmts) = -- See Note [Expanding HsDo with XXExprGhcRn] Equation (3) below -- stmts ~~> stmts' -- ------------------------------------------------ -- let x = e ; stmts ~~> let x = e in stmts' - do expand_stmts <- expand_do_stmts do_or_lc lstmts + do expand_stmts <- expand_do_stmts True doFlavour lstmts let expansion = genHsLet bs expand_stmts - return $ mkExpandedStmtPopAt loc stmt expansion + return $ if addPop then mkExpandedStmtPopAt loc stmt doFlavour TcExpr expansion + else mkExpandedStmtAt loc stmt doFlavour TcExpr expansion -expand_do_stmts do_or_lc (stmt@(L loc (BindStmt xbsrn pat e)): lstmts) +expand_do_stmts addPop doFlavour (stmt@(L loc (BindStmt xbsrn pat e)): lstmts) | SyntaxExprRn bind_op <- xbsrn_bindOp xbsrn , fail_op <- xbsrn_failOp xbsrn -- See Note [Expanding HsDo with XXExprGhcRn] Equation (2) below @@ -121,29 +111,31 @@ expand_do_stmts do_or_lc (stmt@(L loc (BindStmt xbsrn pat e)): lstmts) -- _ -> fail "Pattern match failure .." -- ------------------------------------------------------- -- pat <- e ; stmts ~~> (>>=) e f - = do expand_stmts <- expand_do_stmts do_or_lc lstmts - failable_expr <- mk_failable_expr do_or_lc pat expand_stmts fail_op + = do expand_stmts <- expand_do_stmts True doFlavour lstmts + failable_expr <- mk_failable_expr doFlavour Nothing pat expand_stmts fail_op let expansion = genHsExpApps bind_op -- (>>=) [ e , failable_expr ] - return $ mkExpandedStmtPopAt loc stmt expansion + return $ if addPop then mkExpandedStmtPopAt loc stmt doFlavour TcApp expansion + else mkExpandedStmtAt loc stmt doFlavour TcApp expansion | otherwise = pprPanic "expand_do_stmts: The impossible happened, missing bind operator from renamer" (text "stmt" <+> ppr stmt) -expand_do_stmts do_or_lc (stmt@(L loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) = +expand_do_stmts addPop doFlavour (stmt@(L loc (BodyStmt _ e (SyntaxExprRn then_op) _)) : lstmts) = -- See Note [BodyStmt] in Language.Haskell.Syntax.Expr -- See Note [Expanding HsDo with XXExprGhcRn] Equation (1) below -- stmts ~~> stmts' -- ---------------------------------------------- -- e ; stmts ~~> (>>) e stmts' - do expand_stmts_expr <- expand_do_stmts do_or_lc lstmts + do expand_stmts_expr <- expand_do_stmts True doFlavour lstmts let expansion = genHsExpApps then_op -- (>>) [ e , expand_stmts_expr ] - return $ mkExpandedStmtPopAt loc stmt expansion + return $ if addPop then mkExpandedStmtPopAt loc stmt doFlavour TcApp expansion + else mkExpandedStmtAt loc stmt doFlavour TcApp expansion -expand_do_stmts do_or_lc +expand_do_stmts _ doFlavour ((L loc (RecStmt { recS_stmts = L stmts_loc rec_stmts , recS_later_ids = later_ids -- forward referenced local ids , recS_rec_ids = local_ids -- ids referenced outside of the rec block @@ -163,12 +155,12 @@ expand_do_stmts do_or_lc -- -> do { rec_stmts -- ; return (local_only_ids ++ later_ids) } )) -- (\ [ local_only_ids ++ later_ids ] -> stmts') - do expand_stmts <- expand_do_stmts do_or_lc lstmts + do expand_stmts <- expand_do_stmts True doFlavour lstmts -- NB: No need to wrap the expansion with an ExpandedStmt -- as we want to flatten the rec block statements into its parent do block anyway return $ mkHsApps (wrapGenSpan bind_fun) -- (>>=) [ (wrapGenSpan mfix_fun) `mkHsApp` mfix_expr -- (mfix (do block)) - , genHsLamDoExp do_or_lc [ mkBigLHsVarPatTup all_ids ] -- (\ x -> + , genHsLamDoExp doFlavour [ mkBigLHsVarPatTup all_ids ] -- (\ x -> expand_stmts -- stmts') ] where @@ -184,33 +176,112 @@ expand_do_stmts do_or_lc do_stmts :: XRec GhcRn [ExprLStmt GhcRn] do_stmts = L stmts_loc $ rec_stmts ++ [return_stmt] do_block :: LHsExpr GhcRn - do_block = L loc $ HsDo noExtField do_or_lc do_stmts + do_block = L loc $ HsDo noExtField doFlavour do_stmts mfix_expr :: LHsExpr GhcRn - mfix_expr = genHsLamDoExp do_or_lc [ wrapGenSpan (LazyPat noExtField $ mkBigLHsVarPatTup all_ids) ] + mfix_expr = genHsLamDoExp doFlavour [ wrapGenSpan (LazyPat noExtField $ mkBigLHsVarPatTup all_ids) ] $ do_block -- NB: LazyPat because we do not want to eagerly evaluate the pattern -- and potentially loop forever -expand_do_stmts _ stmts = pprPanic "expand_do_stmts: impossible happened" $ (ppr stmts) +expand_do_stmts addPop doFlavour ((L _ (XStmtLR (ApplicativeStmt _ args mb_join))): lstmts) = +-- See Note [Applicative BodyStmt] +-- +-- stmts ~~> stmts' +-- ------------------------------------------------------------------------- +-- [(fmap, \ x -> e1), (<*>, e2), (<*>, e3), .. ] ; stmts ~~> (\ x -> stmts') <$> e1 <*> e2 ... +-- +-- Very similar to HsToCore.Expr.dsDo + +-- args are [(<$>, e1), (<*>, e2), .., ] + do { xexpr <- expand_do_stmts False doFlavour lstmts + -- extracts pats and arg bodies (rhss) from args + + ; (pats_can_fail, rhss) <- unzip <$> mapM (do_arg . snd) args + + -- add blocks for failable patterns + ; body_with_fails <- foldrM match_args xexpr (zip pats_can_fail rhss) + + -- builds (body <$> e1 <*> e2 ...) + ; let expand_ado_expr = foldl mk_apps body_with_fails (zip (map fst args) rhss) + + -- wrap the expanded expression with a `join` if needed + ; let final_expr = case mb_join of + Just (SyntaxExprRn join_op) + -> genLHsApp join_op expand_ado_expr + _ -> expand_ado_expr + ; traceTc "expand_do_stmts AppStmt" (vcat [ text "args:" <+> ppr args + , text "lstmts:" <+> ppr lstmts + , text "mb_join:" <+> ppr mb_join + , text "expansion:" <+> ppr final_expr]) + ; return $ final_expr + + } + where + do_arg :: ApplicativeArg GhcRn -> TcM ((LPat GhcRn, FailOperator GhcRn), LHsExpr GhcRn) + do_arg (ApplicativeArgOne + { xarg_app_arg_one = mb_fail_op + , app_arg_pattern = pat + , arg_expr = (L rhs_loc rhs) + , is_body_stmt = is_body_stmt + }) = + do let xx_expr = if addPop then mkExpandedStmtPopAt rhs_loc stmt doFlavour TcExpr rhs + else mkExpandedStmtAt rhs_loc stmt doFlavour TcExpr rhs + traceTc "do_arg" (text "OneArg" <+> vcat [ppr pat, ppr xx_expr]) + return ((pat, mb_fail_op) + , xx_expr) + where stmt = if is_body_stmt + then (L rhs_loc (BodyStmt NoExtField (L rhs_loc rhs) NoSyntaxExprRn NoSyntaxExprRn)) + else (L rhs_loc (BindStmt xbsn pat (L rhs_loc rhs))) + do_arg (ApplicativeArgMany _ stmts ret@(L ret_loc _) pat ctxt) = + do { xx_expr <- expand_do_stmts False ctxt $ stmts ++ [L ret_loc $ mkLastStmt ret] + ; traceTc "do_arg" (text "ManyArg" <+> vcat [ppr stmts, text "--", ppr xx_expr]) + ; return ((pat, Nothing) + , xx_expr) } + + match_args :: ((LPat GhcRn, FailOperator GhcRn), LHsExpr GhcRn) -> LHsExpr GhcRn -> TcM (LHsExpr GhcRn) + match_args ((pat, fail_op), stmt_expr) body = mk_failable_expr doFlavour stmt_ctxt pat body fail_op + where stmt_ctxt = case unLoc stmt_expr of + XExpr (ExpandedThingRn (OrigStmt s _) _ _) -> Just (doFlavour, s) + _ -> Nothing + + mk_apps :: LHsExpr GhcRn -> (SyntaxExprRn, LHsExpr GhcRn) -> LHsExpr GhcRn + mk_apps l_expr (op, r_expr) = + case op of + SyntaxExprRn op -> wrapGenSpan $ genHsExpApps op [ l_expr, r_expr ] + NoSyntaxExprRn -> pprPanic "expand_do_stmts applicative op:" (ppr op) + + xbsn :: XBindStmtRn + xbsn = XBindStmtRn NoSyntaxExprRn Nothing + + +expand_do_stmts _ _ stmts = pprPanic "expand_do_stmts: impossible happened" $ (ppr stmts) -- checks the pattern `pat`for irrefutability which decides if we need to wrap it with a fail block -mk_failable_expr :: HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (LHsExpr GhcRn) -mk_failable_expr doFlav pat@(L loc _) expr fail_op = +mk_failable_expr :: HsDoFlavour -> Maybe (HsDoFlavour, ExprLStmt GhcRn) + -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (LHsExpr GhcRn) +mk_failable_expr doFlav mb_stmt_info lpat@(L loc pat) expr fail_op = do { is_strict <- xoptM LangExt.Strict - ; irrf_pat <- isIrrefutableHsPatRnTcM is_strict pat - ; traceTc "mk_failable_expr" (vcat [ text "pat:" <+> ppr pat + ; irrf_pat <- isIrrefutableHsPatRnTcM is_strict lpat + ; traceTc "mk_failable_expr" (vcat [ text "pat:" <+> ppr lpat , text "isIrrefutable:" <+> ppr irrf_pat ]) ; if irrf_pat -- don't wrap with fail block if -- the pattern is irrefutable - then return $ genHsLamDoExp doFlav [pat] expr - else L loc <$> mk_fail_block doFlav pat expr fail_op + then case pat of + (WildPat{}) -> return $ genHsLamDoExp doFlav [L noSrcSpanA pat] expr + _ -> return $ case mb_stmt_info of + Nothing -> genHsLamDoExp doFlav [lpat] expr + Just (f, s) -> wrapGenSpan (mkExpandedStmt s f TcExpr + (unLoc $ (genHsLamDoExp f [lpat] + $ wrapGenSpan (mkPopErrCtxtExpr expr)))) + else L loc <$> mk_fail_block doFlav mb_stmt_info lpat expr fail_op } -- makes the fail block with a given fail_op -mk_fail_block :: HsDoFlavour -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (HsExpr GhcRn) -mk_fail_block doFlav pat@(L ploc _) e (Just (SyntaxExprRn fail_op)) = +mk_fail_block :: HsDoFlavour -> Maybe (HsDoFlavour, ExprLStmt GhcRn) + -> LPat GhcRn -> LHsExpr GhcRn -> FailOperator GhcRn -> TcM (HsExpr GhcRn) +mk_fail_block doFlav mb_stmt_info pat@(L ploc _) e (Just (SyntaxExprRn fail_op)) = do dflags <- getDynFlags return $ HsLam noAnn LamCases $ mkMatchGroup (doExpansionOrigin doFlav) -- \ (wrapGenSpan [ genHsCaseAltDoExp doFlav pat e -- pat -> expr @@ -218,22 +289,22 @@ mk_fail_block doFlav pat@(L ploc _) e (Just (SyntaxExprRn fail_op)) = ]) where fail_alt_case :: DynFlags -> LPat GhcRn -> HsExpr GhcRn -> LMatch GhcRn (LHsExpr GhcRn) - fail_alt_case dflags pat fail_op = genHsCaseAltDoExp doFlav genWildPat $ + fail_alt_case dflags pat fail_op = genHsCaseAltDoExp doFlav (L ploc $ WildPat noExtField) $ L ploc (fail_op_expr dflags pat fail_op) fail_op_expr :: DynFlags -> LPat GhcRn -> HsExpr GhcRn -> HsExpr GhcRn fail_op_expr dflags pat fail_op - = mkExpandedPatRn pat $ + = mkExpandedPatRn pat mb_stmt_info $ genHsApp fail_op (mk_fail_msg_expr dflags pat) mk_fail_msg_expr :: DynFlags -> LPat GhcRn -> LHsExpr GhcRn mk_fail_msg_expr dflags pat = nlHsLit $ mkHsString $ showPpr dflags $ - text "Pattern match failure in" <+> pprHsDoFlavour (DoExpr Nothing) + text "Pattern match failure in" <+> pprHsDoFlavour doFlav <+> text "at" <+> ppr (getLocA pat) -mk_fail_block _ _ _ _ = pprPanic "mk_fail_block: impossible happened" empty +mk_fail_block _ _ _ _ _ = pprPanic "mk_fail_block: impossible happened" empty {- Note [Expanding HsDo with XXExprGhcRn] @@ -302,12 +373,29 @@ They capture the essence of statement expansions as implemented in `expand_do_st (5) DO【 s 】 = s + (4) DO【 AppStmt s; ss 】 + = APPSTMT【 (AppStmt s, ss) 】 + + RECDO【 _ 】 maps a sequence of recursively dependent monadic statements and converts it into an expression paired with the variables that the rec finds a fix point of. (6) RECDO【 ss 】 = (vars, mfix (\~vars -> (>>=) (DO【 ss 】) (return vars))) where vars are all the variables free in ss + APPSTMT【 _ 】 expands the applicative statements as given in Note [ApplicativeDo] in GHC.Rename.Expr (dsDo) + The applicative statement is generated by GHC.Rename.Expr.postProcessStmtsForApplicativeDo + + + (7) APPSTMT 【 (AppStmt (s1 | s2 ... | sn), ss) 】 + = join (\argpat (s1) .. argpat(sn) -> DO 【 ss 】) + <$> ‹ExpansionStmt s1› argexpr(arg_1) + <*> ... + <*> ‹PopErrCtxt› ‹ExpansionStmt s1› argexpr(arg_n) + + where argpat (p <- s) = p + argexpr(p <- s) = s + For a concrete example, consider a `do`-block written by the user ===================================== compiler/GHC/Tc/Gen/Expr.hs ===================================== @@ -710,27 +710,25 @@ tcXExpr (PopErrCtxt (L loc e)) res_ty setSrcSpanA loc $ tcExpr e res_ty -tcXExpr xe@(ExpandedThingRn o e') res_ty - | OrigStmt ls@(L loc s at LetStmt{}) <- o +tcXExpr xe@(ExpandedThingRn o e' tc_info) res_ty + | OrigStmt ls@(L loc s at LetStmt{}) flav <- o , HsLet x binds e <- e' = do { (binds', wrapper, e') <- setSrcSpanA loc $ - addStmtCtxt s $ + addStmtCtxt s flav $ tcLocalBinds binds $ tcMonoExprNC e res_ty -- NB: Do not call tcMonoExpr here as it adds -- a duplicate error context - ; return $ mkExpandedStmtTc ls (HsLet x binds' (mkLHsWrap wrapper e')) + ; return $ mkExpandedStmtTc ls flav (HsLet x binds' (mkLHsWrap wrapper e')) } - | OrigStmt ls@(L loc s at LastStmt{}) <- o - = setSrcSpanA loc $ - addStmtCtxt s $ - mkExpandedStmtTc ls <$> tcExpr e' res_ty - -- It is important that we call tcExpr (and not tcApp) here as - -- `e` is the last statement's body expression - -- and not a HsApp of a generated (>>) or (>>=) - -- This improves error messages e.g. tests: DoExpansion1, DoExpansion2, DoExpansion3 - | OrigStmt ls@(L loc _) <- o + | OrigStmt ls@(L loc s) flav <- o + , TcExpr <- tc_info = setSrcSpanA loc $ - mkExpandedStmtTc ls <$> tcApp (XExpr xe) res_ty + addStmtCtxt s flav $ + mkExpandedStmtTc ls flav <$> tcExpr e' res_ty + | OrigStmt ls@(L loc _) flav <- o + , TcApp <- tc_info + = setSrcSpanA loc $ + mkExpandedStmtTc ls flav <$> tcApp (XExpr xe) res_ty tcXExpr xe res_ty = tcApp (XExpr xe) res_ty ===================================== compiler/GHC/Tc/Gen/Head.hs ===================================== @@ -240,7 +240,7 @@ appCtxtLoc (VACall _ _ l) = l insideExpansion :: AppCtxt -> Bool insideExpansion (VAExpansion {}) = True -insideExpansion (VACall {}) = False -- but what if the VACall has a generated context? +insideExpansion (VACall _ _ src) = isGeneratedSrcSpan src instance Outputable AppCtxt where ppr (VAExpansion e l _) = text "VAExpansion" <+> ppr e <+> ppr l @@ -292,7 +292,7 @@ splitHsApps e = go e (top_ctxt 0 e) [] top_ctxt n (HsPragE _ _ fun) = top_lctxt n fun top_ctxt n (HsAppType _ fun _) = top_lctxt (n+1) fun top_ctxt n (HsApp _ fun _) = top_lctxt (n+1) fun - top_ctxt n (XExpr (ExpandedThingRn o _)) + top_ctxt n (XExpr (ExpandedThingRn o _ _)) | OrigExpr fun <- o = VACall fun n noSrcSpan top_ctxt n other_fun = VACall other_fun n noSrcSpan @@ -317,19 +317,19 @@ splitHsApps e = go e (top_ctxt 0 e) [] HsQuasiQuote _ _ (L l _) -> set l ctxt -- l :: SrcAnn NoEpAnns -- See Note [Looking through ExpandedThingRn] - go (XExpr (ExpandedThingRn o e)) ctxt args + go (XExpr (ExpandedThingRn o e _)) ctxt args | isHsThingRnExpr o = go e (VAExpansion o (appCtxtLoc ctxt) (appCtxtLoc ctxt)) (EWrap (EExpand o) : args) - | OrigStmt (L _ stmt) <- o -- so that we set `(>>)` as generated + | OrigStmt (L _ stmt) _ <- o -- so that we set `(>>)` as generated , BodyStmt{} <- stmt -- and get the right unused bind warnings = go e (VAExpansion o generatedSrcSpan generatedSrcSpan) -- See Part 3. in Note [Expanding HsDo with XXExprGhcRn] (EWrap (EExpand o) : args) -- in `GHC.Tc.Gen.Do` - | OrigPat (L loc _) <- o -- so that we set the compiler generated fail context + | OrigPat (L loc _) _ <- o -- so that we set the compiler generated fail context = go e (VAExpansion o (locA loc) (locA loc)) -- to be originating from a failable pattern -- See Part 1. Wrinkle 2. of (EWrap (EExpand o) : args) -- Note [Expanding HsDo with XXExprGhcRn] @@ -893,17 +893,20 @@ tcInferAppHead_maybe fun _ -> return Nothing addHeadCtxt :: AppCtxt -> TcM a -> TcM a -addHeadCtxt (VAExpansion (OrigStmt (L loc stmt)) _ _) thing_inside = - do setSrcSpanA loc $ - addStmtCtxt stmt +addHeadCtxt (VAExpansion (OrigStmt (L loc stmt) flav) _ _) thing_inside = + do traceTc "addHeadCtxt stmt" (ppr stmt) + setSrcSpanA loc $ + addStmtCtxt stmt flav $ thing_inside addHeadCtxt fun_ctxt thing_inside | not (isGoodSrcSpan fun_loc) -- noSrcSpan => no arguments = thing_inside -- => context is already set | otherwise = setSrcSpan fun_loc $ - do case fun_ctxt of + do traceTc "addHeadCtxt fun_loc" (ppr fun_ctxt) + case fun_ctxt of VAExpansion (OrigExpr orig) _ _ -> addExprCtxt orig thing_inside + VAExpansion (OrigPat _ (Just (flav, stmt))) _ _ -> addStmtCtxt (unLoc stmt) flav $ thing_inside _ -> thing_inside where fun_loc = appCtxtLoc fun_ctxt @@ -1587,9 +1590,9 @@ mis-match in the number of value arguments. * * ********************************************************************* -} -addStmtCtxt :: ExprStmt GhcRn -> TcRn a -> TcRn a -addStmtCtxt stmt thing_inside - = do let err_doc = pprStmtInCtxt (HsDoStmt (DoExpr Nothing)) stmt +addStmtCtxt :: ExprStmt GhcRn -> HsDoFlavour -> TcRn a -> TcRn a +addStmtCtxt stmt flav thing_inside + = do let err_doc = pprStmtInCtxt (HsDoStmt flav) stmt addErrCtxt err_doc thing_inside where pprStmtInCtxt :: HsStmtContextRn -> StmtLR GhcRn GhcRn (LHsExpr GhcRn) -> SDoc @@ -1602,6 +1605,7 @@ addExprCtxt :: HsExpr GhcRn -> TcRn a -> TcRn a addExprCtxt e thing_inside = case e of HsUnboundVar {} -> thing_inside + XExpr (ExpandedThingRn (OrigStmt stmt flav) _ _) -> addStmtCtxt (unLoc stmt) flav thing_inside _ -> addErrCtxt (exprCtxt e) thing_inside -- The HsUnboundVar special case addresses situations like -- f x = _ ===================================== compiler/GHC/Tc/Gen/Match.hs ===================================== @@ -78,13 +78,9 @@ import GHC.Types.SrcLoc import GHC.Types.Basic( VisArity, isDoExpansionGenerated ) import Control.Monad -import Control.Arrow ( second ) import qualified Data.List.NonEmpty as NE import Data.Maybe (mapMaybe) -import qualified GHC.LanguageExtensions as LangExt - - {- ************************************************************************ * * @@ -353,20 +349,16 @@ tcDoStmts ListComp (L l stmts) res_ty (mkCheckExpType elt_ty) ; return $ mkHsWrapCo co (HsDo list_ty ListComp (L l stmts')) } -tcDoStmts doExpr@(DoExpr _) ss@(L l stmts) res_ty - = do { isApplicativeDo <- xoptM LangExt.ApplicativeDo - ; if isApplicativeDo - then do { stmts' <- tcStmts (HsDoStmt doExpr) tcDoStmt stmts res_ty - ; res_ty <- readExpType res_ty - ; return (HsDo res_ty doExpr (L l stmts')) } - else do { expanded_expr <- expandDoStmts doExpr stmts - -- Do expansion on the fly - ; mkExpandedExprTc (HsDo noExtField doExpr ss) <$> tcExpr (unLoc expanded_expr) res_ty } +tcDoStmts doExpr@(DoExpr _) ss@(L _ stmts) res_ty + = do { traceTc "tcDoStmts" $ text "original:" <+> ppr ss + ; expanded_expr <- expandDoStmts doExpr stmts -- Do expansion on the fly + ; traceTc "tcDoStmts" $ text "expansion:" <+> ppr expanded_expr + ; mkExpandedExprTc (HsDo noExtField doExpr ss) <$> tcExpr expanded_expr res_ty } tcDoStmts mDoExpr@(MDoExpr _) ss@(L _ stmts) res_ty = do { expanded_expr <- expandDoStmts mDoExpr stmts -- Do expansion on the fly - ; mkExpandedExprTc (HsDo noExtField mDoExpr ss) <$> tcExpr (unLoc expanded_expr) res_ty } + ; mkExpandedExprTc (HsDo noExtField mDoExpr ss) <$> tcExpr expanded_expr res_ty } tcDoStmts MonadComp (L l stmts) res_ty = do { stmts' <- tcStmts (HsDoStmt MonadComp) tcMcStmt stmts res_ty @@ -997,18 +989,6 @@ tcDoStmt ctxt (RecStmt { recS_stmts = L l stmts, recS_later_ids = later_names , recS_ret_ty = stmts_ty} }, thing) }} -tcDoStmt ctxt (XStmtLR (ApplicativeStmt _ pairs mb_join)) res_ty thing_inside - = do { let tc_app_stmts ty = tcApplicativeStmts ctxt pairs ty $ - thing_inside . mkCheckExpType - ; ((pairs', body_ty, thing), mb_join') <- case mb_join of - Nothing -> (, Nothing) <$> tc_app_stmts res_ty - Just join_op -> - second Just <$> - (tcSyntaxOp DoOrigin join_op [SynRho] res_ty $ - \ [rhs_ty] [rhs_mult] -> tcScalingUsage rhs_mult $ tc_app_stmts (mkCheckExpType rhs_ty)) - - ; return (XStmtLR $ ApplicativeStmt body_ty pairs' mb_join', thing) } - tcDoStmt _ stmt _ _ = pprPanic "tcDoStmt: unexpected Stmt" (ppr stmt) @@ -1084,87 +1064,6 @@ To achieve this we: all branches. This step is done with bindLocalNames. -} -tcApplicativeStmts - :: HsStmtContextRn - -> [(SyntaxExpr GhcRn, ApplicativeArg GhcRn)] - -> ExpRhoType -- rhs_ty - -> (TcRhoType -> TcM t) -- thing_inside - -> TcM ([(SyntaxExpr GhcTc, ApplicativeArg GhcTc)], Type, t) - -tcApplicativeStmts ctxt pairs rhs_ty thing_inside - = do { body_ty <- newFlexiTyVarTy liftedTypeKind - ; let arity = length pairs - ; ts <- replicateM (arity-1) $ newInferExpType - ; exp_tys <- replicateM arity $ newFlexiTyVarTy liftedTypeKind - ; pat_tys <- replicateM arity $ newFlexiTyVarTy liftedTypeKind - ; let fun_ty = mkVisFunTysMany pat_tys body_ty - - -- NB. do the <$>,<*> operators first, we don't want type errors here - -- i.e. goOps before goArgs - -- See Note [Treat rebindable syntax first] - ; let (ops, args) = unzip pairs - ; ops' <- goOps fun_ty (zip3 ops (ts ++ [rhs_ty]) exp_tys) - - -- Typecheck each ApplicativeArg separately - -- See Note [ApplicativeDo and constraints] - ; args' <- mapM (goArg body_ty) (zip3 args pat_tys exp_tys) - - -- Bring into scope all the things bound by the args, - -- and typecheck the thing_inside - -- See Note [ApplicativeDo and constraints] - ; res <- tcExtendIdEnv (concatMap get_arg_bndrs args') $ - thing_inside body_ty - - ; return (zip ops' args', body_ty, res) } - where - goOps _ [] = return [] - goOps t_left ((op,t_i,exp_ty) : ops) - = do { (_, op') - <- tcSyntaxOp DoOrigin op - [synKnownType t_left, synKnownType exp_ty] t_i $ - \ _ _ -> return () - ; t_i <- readExpType t_i - ; ops' <- goOps t_i ops - ; return (op' : ops') } - - goArg :: Type -> (ApplicativeArg GhcRn, Type, Type) - -> TcM (ApplicativeArg GhcTc) - - goArg body_ty (ApplicativeArgOne - { xarg_app_arg_one = fail_op - , app_arg_pattern = pat - , arg_expr = rhs - , .. - }, pat_ty, exp_ty) - = setSrcSpan (combineSrcSpans (getLocA pat) (getLocA rhs)) $ - addErrCtxt (pprStmtInCtxt ctxt (mkRnBindStmt pat rhs)) $ - do { rhs' <- tcCheckMonoExprNC rhs exp_ty - ; (pat', _) <- tcCheckPat (StmtCtxt ctxt) pat (unrestricted pat_ty) $ - return () - ; fail_op' <- fmap join . forM fail_op $ \fail -> - tcMonadFailOp (DoPatOrigin pat) pat' fail body_ty - - ; return (ApplicativeArgOne - { xarg_app_arg_one = fail_op' - , app_arg_pattern = pat' - , arg_expr = rhs' - , .. } - ) } - - goArg _body_ty (ApplicativeArgMany x stmts ret pat ctxt, pat_ty, exp_ty) - = do { (stmts', (ret',pat')) <- - tcStmtsAndThen (HsDoStmt ctxt) tcDoStmt stmts (mkCheckExpType exp_ty) $ - \res_ty -> do - { ret' <- tcExpr ret res_ty - ; (pat', _) <- tcCheckPat (StmtCtxt (HsDoStmt ctxt)) pat (unrestricted pat_ty) $ - return () - ; return (ret', pat') - } - ; return (ApplicativeArgMany x stmts' ret' pat' ctxt) } - - get_arg_bndrs :: ApplicativeArg GhcTc -> [Id] - get_arg_bndrs (ApplicativeArgOne { app_arg_pattern = pat }) = collectPatBinders CollNoDictBinders pat - get_arg_bndrs (ApplicativeArgMany { bv_pattern = pat }) = collectPatBinders CollNoDictBinders pat {- Note [ApplicativeDo and constraints] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Tc/Types/Origin.hs ===================================== @@ -751,9 +751,9 @@ exprCtOrigin (HsUntypedSplice {}) = Shouldn'tHappenOrigin "TH untyped splice" exprCtOrigin (HsProc {}) = Shouldn'tHappenOrigin "proc" exprCtOrigin (HsStatic {}) = Shouldn'tHappenOrigin "static expression" exprCtOrigin (HsEmbTy {}) = Shouldn'tHappenOrigin "type expression" -exprCtOrigin (XExpr (ExpandedThingRn thing _)) | OrigExpr a <- thing = exprCtOrigin a - | OrigStmt _ <- thing = DoOrigin - | OrigPat p <- thing = DoPatOrigin p +exprCtOrigin (XExpr (ExpandedThingRn thing _ _)) | OrigExpr a <- thing = exprCtOrigin a + | OrigStmt _ _ <- thing = DoOrigin + | OrigPat p _ <- thing = DoPatOrigin p exprCtOrigin (XExpr (PopErrCtxt {})) = Shouldn'tHappenOrigin "PopErrCtxt" -- | Extract a suitable CtOrigin from a MatchGroup ===================================== compiler/GHC/Tc/Zonk/Type.hs ===================================== @@ -97,7 +97,6 @@ import GHC.Tc.Types.BasicTypes import GHC.Data.Maybe import GHC.Data.Bag -import Control.Monad import Control.Monad.Trans.Class ( lift ) import Data.Semigroup import Data.List.NonEmpty ( NonEmpty ) @@ -1409,54 +1408,6 @@ zonkStmt zBody (BindStmt xbs pat body) }) new_pat new_body } --- Scopes: join > ops (in reverse order) > pats (in forward order) --- > rest of stmts -zonkStmt _zBody (XStmtLR (ApplicativeStmt body_ty args mb_join)) - = do { new_mb_join <- zonk_join mb_join - ; new_args <- zonk_args args - ; new_body_ty <- noBinders $ zonkTcTypeToTypeX body_ty - ; return $ XStmtLR $ ApplicativeStmt new_body_ty new_args new_mb_join } - where - zonk_join Nothing = return Nothing - zonk_join (Just j) = Just <$> zonkSyntaxExpr j - - get_pat :: (SyntaxExpr GhcTc, ApplicativeArg GhcTc) -> LPat GhcTc - get_pat (_, ApplicativeArgOne _ pat _ _) = pat - get_pat (_, ApplicativeArgMany _ _ _ pat _) = pat - - replace_pat :: LPat GhcTc - -> (SyntaxExpr GhcTc, ApplicativeArg GhcTc) - -> (SyntaxExpr GhcTc, ApplicativeArg GhcTc) - replace_pat pat (op, ApplicativeArgOne fail_op _ a isBody) - = (op, ApplicativeArgOne fail_op pat a isBody) - replace_pat pat (op, ApplicativeArgMany x a b _ c) - = (op, ApplicativeArgMany x a b pat c) - - zonk_args args - = do { new_args_rev <- zonk_args_rev (reverse args) - ; new_pats <- zonkPats (map get_pat args) - ; return $ zipWithEqual "zonkStmt" replace_pat - new_pats (reverse new_args_rev) } - - -- these need to go backward, because if any operators are higher-rank, - -- later operators may introduce skolems that are in scope for earlier - -- arguments - zonk_args_rev ((op, arg) : args) - = do { new_op <- zonkSyntaxExpr op - ; new_arg <- noBinders $ zonk_arg arg - ; new_args <- zonk_args_rev args - ; return $ (new_op, new_arg) : new_args } - zonk_args_rev [] = return [] - - zonk_arg (ApplicativeArgOne fail_op pat expr isBody) - = do { new_expr <- zonkLExpr expr - ; new_fail <- forM fail_op $ don'tBind . zonkSyntaxExpr - ; return (ApplicativeArgOne new_fail pat new_expr isBody) } - zonk_arg (ApplicativeArgMany x stmts ret pat ctxt) - = runZonkBndrT (zonkStmts zonkLExpr stmts) $ \ new_stmts -> - do { new_ret <- zonkExpr ret - ; return (ApplicativeArgMany x new_stmts new_ret pat ctxt) } - ------------------------------------------------------------------------- zonkRecFields :: HsRecordBinds GhcTc -> ZonkTcM (HsRecordBinds GhcTc) zonkRecFields (HsRecFields flds dd) ===================================== testsuite/tests/ado/T13242a.stderr ===================================== @@ -1,13 +1,13 @@ - T13242a.hs:10:5: error: [GHC-46956] • Couldn't match expected type ‘a0’ with actual type ‘a’ - • because type variable ‘a’ would escape its scope - This (rigid, skolem) type variable is bound by - a pattern with constructor: A :: forall a. Eq a => a -> T, - in a pattern binding in - a 'do' block - at T13242a.hs:10:3-5 - • In the expression: + because type variable ‘a’ would escape its scope + This (rigid, skolem) type variable is bound by + a pattern with constructor: A :: forall a. Eq a => a -> T, + in a pattern binding in + a 'do' block + at T13242a.hs:10:3-5 + • In a stmt of a 'do' block: A x <- undefined + In the expression: do A x <- undefined _ <- return 'a' _ <- return 'b' @@ -29,7 +29,7 @@ T13242a.hs:13:13: error: [GHC-39999] instance Eq Ordering -- Defined in ‘GHC.Classes’ instance Eq Integer -- Defined in ‘GHC.Num.Integer’ ...plus 23 others - ...plus five instances involving out-of-scope types + ...plus six instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In a stmt of a 'do' block: return (x == x) In the expression: @@ -43,3 +43,4 @@ T13242a.hs:13:13: error: [GHC-39999] _ <- return 'a' _ <- return 'b' return (x == x) + ===================================== testsuite/tests/ado/T16135.hs ===================================== @@ -1,5 +1,9 @@ {-# LANGUAGE ExistentialQuantification, ApplicativeDo #-} +{- This testcase failed before we treated Do statements via HsExpansions + This test passes after #24406 +-} + module Bug where data T f = forall a. MkT (f a) ===================================== testsuite/tests/ado/T16135.stderr deleted ===================================== @@ -1,19 +0,0 @@ -T16135.hs:11:18: error: [GHC-83865] - • Couldn't match type ‘a0’ with ‘a’ - Expected: f a0 - Actual: f a - ‘a0’ is untouchable - inside the constraints: Functor f - bound by the type signature for: - runf :: forall (f :: * -> *). Functor f => IO (T f) - at T16135.hs:7:1-39 - ‘a’ is a rigid type variable bound by - a pattern with constructor: - MkT :: forall {k} (f :: k -> *) (a :: k). f a -> T f, - in a pattern binding in - a 'do' block - at T16135.hs:10:5-10 - • In the first argument of ‘MkT’, namely ‘fa’ - In the second argument of ‘($)’, namely ‘MkT fa’ - In a stmt of a 'do' block: return $ MkT fa - • Relevant bindings include fa :: f a (bound at T16135.hs:10:9) ===================================== testsuite/tests/ado/T24406.hs ===================================== @@ -0,0 +1,14 @@ +{-# LANGUAGE ImpredicativeTypes, ApplicativeDo #-} +module T where + +t :: IO (forall a. a -> a) +t = return id + +p :: (forall a. a -> a) -> (Bool, Int) +p f = (f True, f 3) + +-- This typechecks (with QL) +foo1 = t >>= \x -> return (p x) + +-- But this did not not type check: +foo2 = do { x <- t ; return (p x) } ===================================== testsuite/tests/ado/ado002.stderr ===================================== @@ -1,4 +1,3 @@ - ado002.hs:8:8: error: [GHC-83865] • Couldn't match expected type: Char -> IO b0 with actual type: IO Char @@ -24,30 +23,39 @@ ado002.hs:9:3: error: [GHC-83865] y <- getChar 'a' print (x, y) -ado002.hs:15:11: error: [GHC-83865] - • Couldn't match expected type ‘Int’ with actual type ‘Char’ - • In the expression: y - In a stmt of a 'do' block: return (y, x) +ado002.hs:13:8: error: [GHC-83865] + • Couldn't match type ‘Char’ with ‘Int’ + Expected: IO Int + Actual: IO Char + • In a stmt of a 'do' block: x <- getChar In the expression: do x <- getChar y <- getChar return (y, x) + In an equation for ‘g’: + g = do x <- getChar + y <- getChar + return (y, x) -ado002.hs:15:13: error: [GHC-83865] - • Couldn't match expected type ‘Int’ with actual type ‘Char’ - • In the expression: x - In a stmt of a 'do' block: return (y, x) +ado002.hs:14:8: error: [GHC-83865] + • Couldn't match type ‘Char’ with ‘Int’ + Expected: IO Int + Actual: IO Char + • In a stmt of a 'do' block: y <- getChar In the expression: do x <- getChar y <- getChar return (y, x) + In an equation for ‘g’: + g = do x <- getChar + y <- getChar + return (y, x) -ado002.hs:23:9: error: [GHC-83865] - • Couldn't match expected type: Char -> IO a0 - with actual type: IO Char - • The function ‘getChar’ is applied to one visible argument, - but its type ‘IO Char’ has none - In a stmt of a 'do' block: x5 <- getChar x4 +ado002.hs:20:9: error: [GHC-83865] + • Couldn't match type ‘Char’ with ‘Int’ + Expected: IO Int + Actual: IO Char + • In a stmt of a 'do' block: x2 <- getChar In the expression: do x1 <- getChar x2 <- getChar @@ -55,11 +63,17 @@ ado002.hs:23:9: error: [GHC-83865] x4 <- getChar x5 <- getChar x4 return (x2, x4) + In an equation for ‘h’: + h = do x1 <- getChar + x2 <- getChar + x3 <- const (return ()) x1 + x4 <- getChar + x5 <- getChar x4 + return (x2, x4) -ado002.hs:24:11: error: [GHC-83865] +ado002.hs:23:3: error: [GHC-83865] • Couldn't match expected type ‘Int’ with actual type ‘Char’ - • In the expression: x2 - In a stmt of a 'do' block: return (x2, x4) + • In a stmt of a 'do' block: x4 <- getChar In the expression: do x1 <- getChar x2 <- getChar @@ -67,11 +81,20 @@ ado002.hs:24:11: error: [GHC-83865] x4 <- getChar x5 <- getChar x4 return (x2, x4) + In an equation for ‘h’: + h = do x1 <- getChar + x2 <- getChar + x3 <- const (return ()) x1 + x4 <- getChar + x5 <- getChar x4 + return (x2, x4) -ado002.hs:24:14: error: [GHC-83865] - • Couldn't match expected type ‘Int’ with actual type ‘Char’ - • In the expression: x4 - In a stmt of a 'do' block: return (x2, x4) +ado002.hs:23:9: error: [GHC-83865] + • Couldn't match expected type: Char -> IO a0 + with actual type: IO Char + • The function ‘getChar’ is applied to one visible argument, + but its type ‘IO Char’ has none + In a stmt of a 'do' block: x5 <- getChar x4 In the expression: do x1 <- getChar x2 <- getChar @@ -79,3 +102,4 @@ ado002.hs:24:14: error: [GHC-83865] x4 <- getChar x5 <- getChar x4 return (x2, x4) + ===================================== testsuite/tests/ado/ado003.stderr ===================================== @@ -1,7 +1,7 @@ -ado003.hs:7:3: error: [GHC-83865] - • Couldn't match expected type ‘Int’ with actual type ‘Char’ - • In the pattern: 'a' +ado003.hs:7:18: error: [GHC-83865] + • Couldn't match expected type ‘Char’ with actual type ‘Int’ + • In the first argument of ‘return’, namely ‘(3 :: Int)’ In a stmt of a 'do' block: 'a' <- return (3 :: Int) In the expression: do x <- getChar ===================================== testsuite/tests/ado/ado004.stderr ===================================== @@ -8,24 +8,24 @@ TYPE SIGNATURES test1c :: forall (f :: * -> *). Applicative f => (Int -> f Int) -> f Int test2 :: - forall {f :: * -> *} {t} {b}. - (Applicative f, Num t, Num b) => + forall {f :: * -> *} {b} {t}. + (Applicative f, Num b, Num t) => (t -> f b) -> f b test2a :: - forall {f :: * -> *} {t} {b}. - (Functor f, Num t, Num b) => + forall {f :: * -> *} {b} {t}. + (Functor f, Num b, Num t) => (t -> f b) -> f b test2b :: forall {f :: * -> *} {t} {a}. (Applicative f, Num t) => (t -> a) -> f a test2c :: - forall {f :: * -> *} {t} {b}. - (Functor f, Num t, Num b) => + forall {f :: * -> *} {b} {t}. + (Functor f, Num b, Num t) => (t -> f b) -> f b test2d :: - forall {f :: * -> *} {t} {b} {a}. - (Functor f, Num t, Num b) => + forall {f :: * -> *} {b} {t} {a}. + (Functor f, Num b, Num t) => (t -> f a) -> f b test3 :: forall {m :: * -> *} {t1} {t2} {a}. @@ -44,4 +44,4 @@ TYPE SIGNATURES (Monad m, Num (m a)) => (m a -> m (m a)) -> p -> m a Dependent modules: [] -Dependent packages: [base-4.16.0.0] +Dependent packages: [base-4.20.0.0] ===================================== testsuite/tests/ado/all.T ===================================== @@ -20,6 +20,7 @@ test('T15344', normal, compile_and_run, ['']) test('T16628', normal, compile_fail, ['']) test('T17835', normal, compile, ['']) test('T20540', normal, compile, ['']) -test('T16135', [when(compiler_debugged(),expect_broken(16135))], compile_fail, ['']) +test('T16135', normal, compile, ['']) test('T22483', normal, compile, ['-Wall']) test('OrPatStrictness', normal, compile_and_run, ['']) +test('T24406', normal, compile, ['']) ===================================== testsuite/tests/determinism/determ021/determ021.stdout ===================================== @@ -1,16 +1,16 @@ [1 of 1] Compiling A ( A.hs, A.o ) TYPE SIGNATURES test2 :: - forall {f :: * -> *} {t} {b}. - (Applicative f, Num t, Num b) => + forall {f :: * -> *} {b} {t}. + (Applicative f, Num b, Num t) => (t -> f b) -> f b Dependent modules: [] -Dependent packages: [base-4.16.0.0] +Dependent packages: [base-4.20.0.0] [1 of 1] Compiling A ( A.hs, A.o ) TYPE SIGNATURES test2 :: - forall {f :: * -> *} {t} {b}. - (Applicative f, Num t, Num b) => + forall {f :: * -> *} {b} {t}. + (Applicative f, Num b, Num t) => (t -> f b) -> f b Dependent modules: [] -Dependent packages: [base-4.16.0.0] +Dependent packages: [base-4.20.0.0] ===================================== testsuite/tests/ghci.debugger/scripts/break029.stdout ===================================== @@ -1,9 +1,9 @@ Stopped in Main.f, break029.hs:(4,7)-(6,16) _result :: IO Int = _ x :: Int = 3 -Stopped in Main.f, break029.hs:5:8-21 -_result :: IO Int = _ -x :: Int = 3 +Stopped in Main.f, break029.hs:6:3-16 +_result :: Int = _ +y :: Int = _ Stopped in Main.f, break029.hs:6:11-15 _result :: Int = _ y :: Int = _ ===================================== testsuite/tests/hiefile/should_run/T23540.stdout ===================================== @@ -28,22 +28,6 @@ At point (15,8), we found: ========================== At point (30,8), we found: ========================== -┌ -│ $dMonad at T23540.hs:1:1, of type: Monad Identity -│ is an evidence variable bound by a let, depending on: [$fMonadIdentity] -│ with scope: ModuleScope -│ -│ Defined at -└ -| -`- ┌ - │ $fMonadIdentity at T23540.hs:25:10-23, of type: Monad Identity - │ is an evidence variable bound by an instance of class Monad - │ with scope: ModuleScope - │ - │ Defined at T23540.hs:25:10 - └ - ========================== At point (43,8), we found: ========================== @@ -123,38 +107,6 @@ At point (49,14), we found: ========================== At point (61,7), we found: ========================== -┌ -│ $dApplicative at T23540.hs:1:1, of type: Applicative Identity' -│ is an evidence variable bound by a let, depending on: [$fApplicativeIdentity'] -│ with scope: ModuleScope -│ -│ Defined at -└ -| -`- ┌ - │ $fApplicativeIdentity' at T23540.hs:56:10-30, of type: Applicative Identity' - │ is an evidence variable bound by an instance of class Applicative - │ with scope: ModuleScope - │ - │ Defined at T23540.hs:56:10 - └ - -┌ -│ $dFunctor at T23540.hs:1:1, of type: Functor Identity' -│ is an evidence variable bound by a let, depending on: [$fFunctorIdentity'] -│ with scope: ModuleScope -│ -│ Defined at -└ -| -`- ┌ - │ $fFunctorIdentity' at T23540.hs:54:10-26, of type: Functor Identity' - │ is an evidence variable bound by an instance of class Functor - │ with scope: ModuleScope - │ - │ Defined at T23540.hs:54:10 - └ - ========================== At point (69,4), we found: ========================== View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/57d640c5ed21e7f2c84a87ebb50d9f1ad0ca7752 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/57d640c5ed21e7f2c84a87ebb50d9f1ad0ca7752 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 12:27:00 2024 From: gitlab at gitlab.haskell.org (Krzysztof Gogolewski (@monoidal)) Date: Mon, 10 Jun 2024 08:27:00 -0400 Subject: [Git][ghc/ghc][wip/T24769] WIP on 24769; needs a note Message-ID: <6666f114eb64a_151ed39ca0f46679c@gitlab.mail> Krzysztof Gogolewski pushed to branch wip/T24769 at Glasgow Haskell Compiler / GHC Commits: 023aac51 by Krzysztof Gogolewski at 2024-06-10T14:25:56+02:00 WIP on 24769; needs a note Co-authored-by: Richard Eisenberg <reisenberg at janestreet.com> - - - - - 17 changed files: - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Solver.hs - testsuite/tests/rep-poly/T23176.stderr - + testsuite/tests/rep-poly/T23505.hs - + testsuite/tests/rep-poly/T23505.stderr - + testsuite/tests/rep-poly/T24769a.hs - + testsuite/tests/rep-poly/T24769a.stderr - + testsuite/tests/rep-poly/T24769b.hs - + testsuite/tests/rep-poly/T24769b.stderr - + testsuite/tests/rep-poly/T24769c.hs - + testsuite/tests/rep-poly/T24769c.stderr - + testsuite/tests/rep-poly/T24769c_aux.hs - + testsuite/tests/rep-poly/T24769d.hs - + testsuite/tests/rep-poly/T24769d.stderr - + testsuite/tests/rep-poly/T24769e.script - + testsuite/tests/rep-poly/T24769e.stdout - testsuite/tests/rep-poly/all.T Changes: ===================================== compiler/GHC/Tc/Gen/Bind.hs ===================================== @@ -52,7 +52,7 @@ import GHC.Tc.Gen.Pat import GHC.Tc.Utils.TcMType import GHC.Tc.Instance.Family( tcGetFamInstEnvs ) import GHC.Tc.Utils.TcType -import GHC.Tc.Validity (checkValidType, checkEscapingKind) +import GHC.Tc.Validity (checkValidType) import GHC.Tc.Zonk.TcType import GHC.Core.Reduction ( Reduction(..) ) import GHC.Core.Multiplicity @@ -1013,9 +1013,7 @@ mkInferredPolyId residual insoluble qtvs inferred_theta poly_name mb_sig_inst mo ; unless insoluble $ addErrCtxtM (mk_inf_msg poly_name inferred_poly_ty) $ - do { checkEscapingKind inferred_poly_ty - -- See Note [Inferred type with escaping kind] - ; checkValidType (InfSigCtxt poly_name) inferred_poly_ty } + checkValidType (InfSigCtxt poly_name) inferred_poly_ty -- See Note [Validity of inferred types] -- unless insoluble: if we found an insoluble error in the -- function definition, don't do this check; otherwise @@ -1259,22 +1257,6 @@ Examples that might fail: or multi-parameter type classes - an inferred type that includes unboxed tuples -Note [Inferred type with escaping kind] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Check for an inferred type with an escaping kind; e.g. #23051 - forall {k} {f :: k -> RuntimeRep} {g :: k} {a :: TYPE (f g)}. a -where the kind of the body of the forall mentions `f` and `g` which -are bound by the forall. No no no. - -This check, mkInferredPolyId, is really in the wrong place: -`inferred_poly_ty` doesn't obey the PKTI and it would be better not to -generalise it in the first place; see #20686. But for now it works. - -I considered adjusting the generalisation in GHC.Tc.Solver to directly check for -escaping kind variables; instead, promoting or defaulting them. But that -gets into the defaulting swamp and is a non-trivial and unforced -change, so I have left it alone for now. - Note [Impedance matching] ~~~~~~~~~~~~~~~~~~~~~~~~~ Consider ===================================== compiler/GHC/Tc/Solver.hs ===================================== @@ -1324,6 +1324,10 @@ simplifyInfer rhs_tclvl infer_mode sigs name_taus wanteds psig_theta = [ pred | sig <- partial_sigs , pred <- sig_inst_theta sig ] + ; zonked_kinds <- mapM (TcM.liftZonkM . TcM.zonkTcType . typeKind . snd) name_taus + ; _ <- promoteTyVarSet (tyCoVarsOfTypes zonked_kinds) + -- Promote free variables in the kind (#24769) + ; dep_vars <- candidateQTyVarsOfTypes (psig_tv_tys ++ psig_theta ++ map snd name_taus) ; skol_info <- mkSkolemInfo (InferSkol name_taus) @@ -1837,6 +1841,7 @@ decidePromotedTyVars :: InferMode -- (c) Connected by an equality or fundep to -- * a type variable at level < N, or -- * A tyvar subject to (a), (b) or (c) +-- (d) Free in kind (e.g. we can't generalize over r in 'forall (a :: TYPE r). a') -- Having found all such level-N tyvars that we can't generalise, -- promote them, to eliminate them from further consideration. -- @@ -1867,6 +1872,8 @@ decidePromotedTyVars infer_mode name_taus psigs candidates co_vars = coVarsOfTypes (psig_tys ++ taus ++ candidates) co_var_tvs = closeOverKinds co_vars + escapingKindVars = mapUnionVarSet (\x -> tyCoVarsOfType (typeKind x)) taus + mono_tvs0 = filterVarSet (not . isQuantifiableTv tc_lvl) $ tyCoVarsOfTypes candidates -- We need to grab all the non-quantifiable tyvars in the @@ -1881,7 +1888,9 @@ decidePromotedTyVars infer_mode name_taus psigs candidates -- are in the equality constraint with alpha. Actual test case: -- typecheck/should_compile/tc213 - mono_tvs1 = mono_tvs0 `unionVarSet` co_var_tvs + mono_tvs0a = mono_tvs0 `unionVarSet` escapingKindVars + + mono_tvs1 = mono_tvs0a `unionVarSet` co_var_tvs -- mono_tvs1 is now the set of variables from an outer scope -- (that's mono_tvs0) and the set of covars, closed over kinds. @@ -1916,6 +1925,7 @@ decidePromotedTyVars infer_mode name_taus psigs candidates mono_tvs = (mono_tvs2 `unionVarSet` constrained_tvs) `delVarSetList` psig_qtvs + `unionVarSet` escapingKindVars -- (`delVarSetList` psig_qtvs): if the user has explicitly -- asked for quantification, then that request "wins" -- over the MR. ===================================== testsuite/tests/rep-poly/T23176.stderr ===================================== @@ -1,30 +1,45 @@ +T23176.hs:5:1: error: [GHC-55287] + The binder ‘f’ does not have a fixed runtime representation. + Its type is: + w :: TYPE (r1 s1) -T23176.hs:5:1: error: [GHC-52083] - The binder ‘f’ - cannot be assigned a fixed runtime representation, not even by defaulting. - Suggested fix: Add a type signature. +T23176.hs:5:19: error: [GHC-94185] + • Can't quantify over ‘s’ + bound by the partial type signature: + :: (_ :: TYPE (r s)) + • In the expression: outOfScope :: (_ :: TYPE (r s)) + In an equation for ‘f’: f = outOfScope :: (_ :: TYPE (r s)) -T23176.hs:5:1: error: [GHC-52083] - The binder ‘f’ - cannot be assigned a fixed runtime representation, not even by defaulting. - Suggested fix: Add a type signature. +T23176.hs:5:19: error: [GHC-94185] + • Can't quantify over ‘r’ + bound by the partial type signature: + :: (_ :: TYPE (r s)) + • In the expression: outOfScope :: (_ :: TYPE (r s)) + In an equation for ‘f’: f = outOfScope :: (_ :: TYPE (r s)) -T23176.hs:5:1: error: [GHC-52083] - The binder ‘f’ - cannot be assigned a fixed runtime representation, not even by defaulting. - Suggested fix: Add a type signature. +T23176.hs:6:1: error: [GHC-55287] + The binder ‘g’ does not have a fixed runtime representation. + Its type is: + forall {w :: TYPE (r0 s0)}. w :: TYPE (r0 s0) -T23176.hs:6:1: error: [GHC-52083] - The pattern binding - cannot be assigned a fixed runtime representation, not even by defaulting. - Suggested fix: Add a type signature. +T23176.hs:6:12: error: [GHC-55287] + • The pattern binding does not have a fixed runtime representation. + Its type is: + w :: TYPE (r0 s0) + • In the expression: outOfScope :: (_ :: TYPE (r s)) + In a pattern binding: (g :: _) = outOfScope :: (_ :: TYPE (r s)) -T23176.hs:6:1: error: [GHC-52083] - The pattern binding - cannot be assigned a fixed runtime representation, not even by defaulting. - Suggested fix: Add a type signature. +T23176.hs:6:26: error: [GHC-94185] + • Can't quantify over ‘s’ + bound by the partial type signature: + :: (_ :: TYPE (r s)) + • In the expression: outOfScope :: (_ :: TYPE (r s)) + In a pattern binding: (g :: _) = outOfScope :: (_ :: TYPE (r s)) + +T23176.hs:6:26: error: [GHC-94185] + • Can't quantify over ‘r’ + bound by the partial type signature: + :: (_ :: TYPE (r s)) + • In the expression: outOfScope :: (_ :: TYPE (r s)) + In a pattern binding: (g :: _) = outOfScope :: (_ :: TYPE (r s)) -T23176.hs:6:1: error: [GHC-52083] - The pattern binding - cannot be assigned a fixed runtime representation, not even by defaulting. - Suggested fix: Add a type signature. ===================================== testsuite/tests/rep-poly/T23505.hs ===================================== @@ -0,0 +1,5 @@ +module M where + +import GHC.Exts + +f = f :: (_ :: TYPE r) ===================================== testsuite/tests/rep-poly/T23505.stderr ===================================== @@ -0,0 +1,23 @@ +T23505.hs:5:1: error: [GHC-55287] + The binder ‘f’ does not have a fixed runtime representation. + Its type is: + forall {t :: TYPE r0}. t :: TYPE r0 + +T23505.hs:5:10: error: [GHC-94185] + • Can't quantify over ‘r’ + bound by the partial type signature: :: (_ :: TYPE r) + • In the expression: f :: (_ :: TYPE r) + In an equation for ‘f’: f = f :: (_ :: TYPE r) + +T23505.hs:5:11: error: [GHC-88464] + • Found type wildcard ‘_’ standing for ‘t :: TYPE r0’ + Where: ‘r0’ is an ambiguous type variable + ‘t’ is a rigid type variable bound by + the inferred type of f :: t + at T23505.hs:5:1-22 + To use the inferred type, enable PartialTypeSignatures + • In an expression type signature: (_ :: TYPE r) + In the expression: f :: (_ :: TYPE r) + In an equation for ‘f’: f = f :: (_ :: TYPE r) + • Relevant bindings include f :: t (bound at T23505.hs:5:1) + ===================================== testsuite/tests/rep-poly/T24769a.hs ===================================== @@ -0,0 +1,5 @@ +module T24769a where + +import GHC.Exts + +f = f :: (_ :: TYPE (r s)) ===================================== testsuite/tests/rep-poly/T24769a.stderr ===================================== @@ -0,0 +1,33 @@ +T24769a.hs:5:1: error: [GHC-55287] + The binder ‘f’ does not have a fixed runtime representation. + Its type is: + forall {t :: TYPE (r0 s0)}. t :: TYPE (r0 s0) + +T24769a.hs:5:10: error: [GHC-94185] + • Can't quantify over ‘s’ + bound by the partial type signature: + :: (_ :: TYPE (r s)) + • In the expression: f :: (_ :: TYPE (r s)) + In an equation for ‘f’: f = f :: (_ :: TYPE (r s)) + +T24769a.hs:5:10: error: [GHC-94185] + • Can't quantify over ‘r’ + bound by the partial type signature: + :: (_ :: TYPE (r s)) + • In the expression: f :: (_ :: TYPE (r s)) + In an equation for ‘f’: f = f :: (_ :: TYPE (r s)) + +T24769a.hs:5:11: error: [GHC-88464] + • Found type wildcard ‘_’ standing for ‘t :: TYPE (r0 s0)’ + Where: ‘r0’ is an ambiguous type variable + ‘k0’ is an ambiguous type variable + ‘s0’ is an ambiguous type variable + ‘t’ is a rigid type variable bound by + the inferred type of f :: t + at T24769a.hs:5:1-26 + To use the inferred type, enable PartialTypeSignatures + • In an expression type signature: (_ :: TYPE (r s)) + In the expression: f :: (_ :: TYPE (r s)) + In an equation for ‘f’: f = f :: (_ :: TYPE (r s)) + • Relevant bindings include f :: t (bound at T24769a.hs:5:1) + ===================================== testsuite/tests/rep-poly/T24769b.hs ===================================== @@ -0,0 +1,6 @@ +module T24769b where + +import GHC.Exts + +f :: (_ :: TYPE r) +f = f ===================================== testsuite/tests/rep-poly/T24769b.stderr ===================================== @@ -0,0 +1,4 @@ +T24769b.hs:6:1: error: [GHC-94185] + Can't quantify over ‘r’ + bound by the partial type signature: f :: (_ :: TYPE r) + ===================================== testsuite/tests/rep-poly/T24769c.hs ===================================== @@ -0,0 +1,5 @@ +{-# LANGUAGE TemplateHaskell, PartialTypeSignatures #-} +module T24769c where + +import T24769c_aux +h = $$g ===================================== testsuite/tests/rep-poly/T24769c.stderr ===================================== @@ -0,0 +1,20 @@ +[1 of 2] Compiling T24769c_aux ( T24769c_aux.hs, T24769c_aux.o ) +T24769c_aux.hs:8:13: warning: [GHC-88464] [-Wpartial-type-signatures (in -Wdefault)] + • Found type wildcard ‘_’ standing for ‘w :: TYPE (r s)’ + Where: ‘r’, ‘s’, ‘w’ are rigid type variables bound by + the inferred type of g :: Code Q w + at T24769c_aux.hs:(9,1)-(11,22) + • In the second argument of ‘Code’, namely ‘_’ + In the type signature: g :: Code Q _ + +[2 of 2] Compiling T24769c ( T24769c.hs, T24769c.o ) +T24769c.hs:5:1: error: [GHC-52083] + The binder ‘h’ + cannot be assigned a fixed runtime representation, not even by defaulting. + Suggested fix: Add a type signature. + +T24769c.hs:5:1: error: [GHC-52083] + The binder ‘h’ + cannot be assigned a fixed runtime representation, not even by defaulting. + Suggested fix: Add a type signature. + ===================================== testsuite/tests/rep-poly/T24769c_aux.hs ===================================== @@ -0,0 +1,11 @@ +{-# LANGUAGE TemplateHaskell, PartialTypeSignatures #-} +module T24769c_aux where + +import Data.Kind +import GHC.Exts +import Language.Haskell.TH (Code, Q) + +g :: Code Q _ +g = [||let f :: forall (r :: Type -> RuntimeRep) s (a :: TYPE (r s)). () -> a + f = f + in f () ||] ===================================== testsuite/tests/rep-poly/T24769d.hs ===================================== @@ -0,0 +1,8 @@ +{-# LANGUAGE PartialTypeSignatures #-} +module T24769d where + +import GHC.Exts +import GHC.Stack + +f :: forall r (a :: TYPE r). (HasCallStack, _) => a +f = undefined ===================================== testsuite/tests/rep-poly/T24769d.stderr ===================================== @@ -0,0 +1,5 @@ +T24769d.hs:8:1: error: [GHC-94185] + Can't quantify over ‘r’ + bound by the partial type signature: + f :: forall r (a :: TYPE r). (HasCallStack, _) => a + ===================================== testsuite/tests/rep-poly/T24769e.script ===================================== @@ -0,0 +1,3 @@ +:m GHC.Exts Data.Kind +f :: forall (r :: Type -> RuntimeRep) s (a :: TYPE (r s)). () -> a; f = f +:t f () ===================================== testsuite/tests/rep-poly/T24769e.stdout ===================================== @@ -0,0 +1 @@ +f () :: forall {a :: TYPE (r0 s0)}. a ===================================== testsuite/tests/rep-poly/all.T ===================================== @@ -37,6 +37,7 @@ test('T23153', normal, compile_fail, ['']) test('T23154', normal, compile_fail, ['']) test('T23176', normal, compile_fail, ['-XPartialTypeSignatures -fdefer-out-of-scope-variables']) test('T23903', normal, compile_fail, ['']) +test('T23505', normal, compile_fail, ['']) test('EtaExpandDataCon', normal, compile, ['-O']) test('EtaExpandStupid1', normal, compile, ['-Wno-deprecated-flags']) @@ -107,6 +108,11 @@ test('RepPolyWrappedVar', normal, compile_fail, ['']) test('RepPolyWrappedVar2', [js_skip], compile, ['']) test('UnliftedNewtypesCoerceFail', normal, compile_fail, ['']) test('UnliftedNewtypesLevityBinder', normal, compile_fail, ['']) +test('T24769a', normal, compile_fail, ['']) +test('T24769b', normal, compile_fail, ['']) +test('T24769c', [extra_files(['T24769c_aux.hs'])], multimod_compile_fail, ['T24769c', '']) +test('T24769d', normal, compile_fail, ['']) +test('T24769e', normal, ghci_script, ['T24769e.script']) ############################################################################### ## The following tests require rewriting in RuntimeReps, ## View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/023aac51fcfa3be08da2e380ee765871d83a2fe8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/023aac51fcfa3be08da2e380ee765871d83a2fe8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 12:31:03 2024 From: gitlab at gitlab.haskell.org (Alexander Foremny (@aforemny)) Date: Mon, 10 Jun 2024 08:31:03 -0400 Subject: [Git][ghc/ghc][wip/aforemny/ttg-remove-source-text] ttg: remove `GHC.Types.SourceText` imports from `Language.Haskell` Message-ID: <6666f206f38e9_151ed3b19d7467160@gitlab.mail> Alexander Foremny pushed to branch wip/aforemny/ttg-remove-source-text at Glasgow Haskell Compiler / GHC Commits: 69d76531 by Alexander Foremny at 2024-06-10T14:26:08+02:00 ttg: remove `GHC.Types.SourceText` imports from `Language.Haskell` To remove `GHC.Types.SourceText` from `Language.Haskell`, we move `SourceText`'s literals to `Language.Haskell.Syntax.Lit`. A temporary hs-boot file has been added for `Language.Haskell.Syntax.Lit` because without it, currently, we are unable to break cyclic module imports. Breaking cyclic module imports between `GHC` and `Language.Haskell` should not exist in the end of things, so that file can be removed before merging. Additionally, this commit changes the implementation of `Eq (XXOverLit pass)` and `Eq (OverLitVal pass)` to not use `panic` anymore. Additionally, a module `GHC.Utils.Outputable.Instances` is introduced that, similar to `GHC.Hs.Instances`, collects (unavoidable) orphan instances for `Outputable`. - - - - - 25 changed files: - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver/Types.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Parser/HaddockLex.x - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/SourceText.hs - compiler/GHC/Unit/Module/Warnings.hs - + compiler/GHC/Utils/Outputable/Instances.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Lit.hs - + compiler/Language/Haskell/Syntax/Lit.hs-boot - compiler/ghc.cabal.in Changes: ===================================== compiler/GHC/Core/InstEnv.hs ===================================== @@ -56,7 +56,6 @@ import GHC.Types.Name.Set import GHC.Types.Basic import GHC.Types.Id import GHC.Generics (Generic) -import Data.Data ( Data ) import Data.List.NonEmpty ( NonEmpty (..), nonEmpty ) import qualified Data.List.NonEmpty as NE import Data.Maybe ( isJust ) @@ -115,7 +114,6 @@ data ClsInst -- See Note [Implementation of deprecated instances] -- in GHC.Tc.Solver.Dict } - deriving Data -- | A fuzzy comparison function for class instances, intended for sorting -- instances before displaying them to the user. ===================================== compiler/GHC/Hs/Binds.hs ===================================== @@ -30,8 +30,9 @@ module GHC.Hs.Binds import GHC.Prelude -import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Binds +import Language.Haskell.Syntax.Extension +import Language.Haskell.Syntax.Lit import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprFunBind, pprPatBind ) import {-# SOURCE #-} GHC.Hs.Pat (pprLPat ) ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -21,8 +21,11 @@ module GHC.Hs.Instances where -- UndecidableInstances ? +import Language.Haskell.Syntax.Lit + import Data.Data hiding ( Fixity ) +import GHC.Core.InstEnv import GHC.Prelude import GHC.Hs.Extension import GHC.Hs.Binds @@ -32,7 +35,9 @@ import GHC.Hs.Lit import GHC.Hs.Type import GHC.Hs.Pat import GHC.Hs.ImpExp +import GHC.Types.PkgQual import GHC.Parser.Annotation +import GHC.Unit.Module.Warnings -- --------------------------------------------------------------------- -- Data derivations from GHC.Hs----------------------------------------- @@ -578,3 +583,29 @@ deriving instance Data XXPatGhcTc deriving instance Data XViaStrategyPs -- --------------------------------------------------------------------- + +deriving instance Data (IntegralLit GhcPs) +deriving instance Data (IntegralLit GhcRn) +deriving instance Data (IntegralLit GhcTc) + +deriving instance Data (FractionalLit GhcPs) +deriving instance Data (FractionalLit GhcRn) +deriving instance Data (FractionalLit GhcTc) + +deriving instance Data (StringLit GhcPs) +deriving instance Data (StringLit GhcRn) +deriving instance Data (StringLit GhcTc) + +deriving instance Data (OverLitVal GhcPs) +deriving instance Data (OverLitVal GhcRn) +deriving instance Data (OverLitVal GhcTc) + +deriving instance Data (RawPkgQual GhcPs) +deriving instance Data (RawPkgQual GhcRn) +deriving instance Data (RawPkgQual GhcTc) + +deriving instance Data (WarningTxt GhcPs) +deriving instance Data (WarningTxt GhcRn) +deriving instance Data (WarningTxt GhcTc) + +deriving instance Data ClsInst ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -31,7 +31,6 @@ import GHC.HsToCore.Arrows import GHC.HsToCore.Monad import GHC.HsToCore.Pmc import GHC.HsToCore.Errors.Types -import GHC.Types.SourceText import GHC.Types.Name hiding (varName) import GHC.Core.FamInstEnv( topNormaliseType ) import GHC.HsToCore.Quote ===================================== compiler/GHC/HsToCore/Match.hs ===================================== @@ -29,10 +29,6 @@ import {-#SOURCE#-} GHC.HsToCore.Expr (dsExpr) import GHC.Types.Basic -import GHC.Types.SourceText - ( FractionalLit, - IntegralLit(il_value), - StringLit(sl_fs) ) import GHC.Driver.DynFlags import GHC.Hs import GHC.Hs.Syn.Type ===================================== compiler/GHC/HsToCore/Pmc/Desugar.hs ===================================== @@ -45,7 +45,6 @@ import GHC.Core.TyCo.Compare( eqType ) import GHC.Core.Type import GHC.Data.Maybe import qualified GHC.LanguageExtensions as LangExt -import GHC.Types.SourceText (FractionalLit(..)) import Control.Monad (zipWithM, replicateM) import Data.List (elemIndex) import Data.List.NonEmpty ( NonEmpty(..) ) ===================================== compiler/GHC/HsToCore/Pmc/Solver/Types.hs ===================================== @@ -68,7 +68,7 @@ import GHC.Builtin.Types.Prim import GHC.Tc.Solver.InertSet (InertSet, emptyInert) import GHC.Tc.Utils.TcType (isStringTy) import GHC.Types.CompleteMatch (CompleteMatch(..)) -import GHC.Types.SourceText (SourceText(..), FractionalLit, FractionalExponentBase(..)) +import GHC.Types.SourceText (SourceText(..)) import Numeric (fromRat) import Data.Foldable (find) import Data.Ratio ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -67,7 +67,6 @@ import GHC.Types.SourceFile import GHC.Types.TyThing import GHC.Types.HpcInfo import GHC.Types.CompleteMatch -import GHC.Types.SourceText import GHC.Types.SrcLoc ( unLoc ) import GHC.Utils.Outputable ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -95,6 +95,8 @@ import GHC.Utils.Panic import GHC.Utils.Misc( dropList, filterByList, notNull, unzipWith, seqList, zipWithEqual ) +import Language.Haskell.Syntax.Lit + import Control.Monad import System.IO.Unsafe import Control.DeepSeq ===================================== compiler/GHC/Parser/HaddockLex.x ===================================== @@ -10,7 +10,6 @@ import GHC.Hs.Doc import GHC.Parser.Lexer import GHC.Parser.Annotation import GHC.Types.SrcLoc -import GHC.Types.SourceText import GHC.Data.StringBuffer import qualified GHC.Data.Strict as Strict import GHC.Types.Name.Reader @@ -27,6 +26,8 @@ import Data.ByteString ( ByteString ) import qualified Data.ByteString as BS import qualified GHC.LanguageExtensions as LangExt + +import Language.Haskell.Syntax.Lit } -- ----------------------------------------------------------------------------- ===================================== compiler/GHC/Rename/Module.hs ===================================== @@ -22,7 +22,6 @@ import GHC.Prelude hiding ( head ) import {-# SOURCE #-} GHC.Rename.Expr( rnLExpr ) import {-# SOURCE #-} GHC.Rename.Splice ( rnSpliceDecl, rnTopSpliceDecls ) -import GHC.Types.SourceText (StringLit) import GHC.Hs import GHC.Types.FieldLabel import GHC.Types.Name.Reader ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -75,7 +75,6 @@ import GHC.Types.Hint import GHC.Types.SourceFile import GHC.Types.SrcLoc as SrcLoc import GHC.Types.Basic ( TopLevelFlag(..) ) -import GHC.Types.SourceText import GHC.Types.Id import GHC.Types.HpcInfo import GHC.Types.PkgQual ===================================== compiler/GHC/Rename/Pat.hs ===================================== @@ -67,7 +67,6 @@ import GHC.Types.Name.Reader import GHC.Types.Unique.Set import GHC.Types.Basic -import GHC.Types.SourceText import GHC.Utils.Misc import GHC.Data.FastString ( uniqCompareFS ) import GHC.Data.List.SetOps( removeDups ) ===================================== compiler/GHC/Rename/Utils.hs ===================================== @@ -59,7 +59,7 @@ import GHC.Types.Name.Env import GHC.Core.DataCon import GHC.Types.SrcLoc as SrcLoc import GHC.Types.SourceFile -import GHC.Types.SourceText ( SourceText(..), IntegralLit ) +import GHC.Types.SourceText (SourceText(..)) import GHC.Utils.Outputable import GHC.Utils.Misc import GHC.Unit.Module.ModIface ===================================== compiler/GHC/Tc/Gen/Bind.hs ===================================== @@ -66,7 +66,6 @@ import GHC.Builtin.Types ( mkConstraintTupleTy, multiplicityTy, oneDataConTy ) import GHC.Builtin.Types.Prim import GHC.Unit.Module -import GHC.Types.SourceText import GHC.Types.Id import GHC.Types.Var as Var import GHC.Types.Var.Set ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -135,7 +135,6 @@ import GHC.Core.UsageEnv import GHC.Types.Var import GHC.Types.Id as Id import GHC.Types.Name -import GHC.Types.SourceText import GHC.Types.Var.Set import GHC.Builtin.Types ===================================== compiler/GHC/Types/PkgQual.hs ===================================== @@ -9,6 +9,7 @@ import GHC.Unit.Types import GHC.Utils.Outputable import Language.Haskell.Syntax.Extension +import {-# SOURCE #-} Language.Haskell.Syntax.Lit import Data.Data @@ -17,10 +18,6 @@ data RawPkgQual pass = NoRawPkgQual -- ^ No package qualifier | RawPkgQual (StringLit pass) -- ^ Raw package qualifier string. -deriving instance - (Data pass, XStringLit pass ~ (SourceText, Maybe NoCommentsLocation)) - => Data (RawPkgQual pass) - -- | Package-qualifier after renaming -- -- Renaming detects if "this" or the unit-id of the home-unit was used as a ===================================== compiler/GHC/Types/SourceText.hs ===================================== @@ -11,14 +11,6 @@ module GHC.Types.SourceText ( SourceText (..) , NoCommentsLocation , pprWithSourceText - - -- * Literals - , IntegralLit(..) - , FractionalLit(..) - , StringLit(..) - , rationalFromFractionalLit - , FractionalExponentBase(..) - ) where @@ -30,13 +22,10 @@ import GHC.Utils.Outputable import GHC.Utils.Binary import GHC.Utils.Panic -import Data.Function (on) import Data.Data import GHC.Types.SrcLoc import Control.DeepSeq -import Language.Haskell.Syntax.Extension - {- Note [Pragma source text] ~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -128,135 +117,3 @@ instance Binary SourceText where pprWithSourceText :: SourceText -> SDoc -> SDoc pprWithSourceText NoSourceText d = d pprWithSourceText (SourceText src) _ = ftext src - ------------------------------------------------- --- Literals ------------------------------------------------- - --- | Integral Literal --- --- Used (instead of Integer) to represent negative zegative zero which is --- required for NegativeLiterals extension to correctly parse `-0::Double` --- as negative zero. See also #13211. -data IntegralLit pass = IL - { il_text :: XIntegralLit pass - , il_neg :: Bool -- See Note [Negative zero] in GHC.Rename.Pat - , il_value :: Integer - } - -deriving instance (Data pass, XIntegralLit pass ~ SourceText) - => Data (IntegralLit pass) - -deriving instance (XIntegralLit pass ~ SourceText) => Show (IntegralLit pass) - --- | Fractional Literal --- --- Used (instead of Rational) to represent exactly the floating point literal that we --- encountered in the user's source program. This allows us to pretty-print exactly what --- the user wrote, which is important e.g. for floating point numbers that can't represented --- as Doubles (we used to via Double for pretty-printing). See also #2245. --- Note [FractionalLit representation] in GHC.HsToCore.Match.Literal --- The actual value then is: sign * fl_signi * (fl_exp_base^fl_exp) --- where sign = if fl_neg then (-1) else 1 --- --- For example FL { fl_neg = True, fl_signi = 5.3, fl_exp = 4, fl_exp_base = Base10 } --- denotes -5300 - -data FractionalLit pass = FL - { fl_text :: XFractionalLit pass -- ^ How the value was written in the source - , fl_neg :: Bool -- See Note [Negative zero] - , fl_signi :: Rational -- The significand component of the literal - , fl_exp :: Integer -- The exponent component of the literal - , fl_exp_base :: FractionalExponentBase -- See Note [fractional exponent bases] - } - -deriving instance (Data pass, XFractionalLit pass ~ SourceText) - => Data (FractionalLit pass) - --- | The Show instance is required for the derived GHC.Parser.Lexer.Token instance when DEBUG is on -deriving instance (XFractionalLit pass ~ SourceText) => Show (FractionalLit pass) - --- See Note [FractionalLit representation] in GHC.HsToCore.Match.Literal -data FractionalExponentBase - = Base2 -- Used in hex fractional literals - | Base10 - deriving (Eq, Ord, Data, Show) - -mkRationalWithExponentBase :: Rational -> Integer -> FractionalExponentBase -> Rational -mkRationalWithExponentBase i e feb = i * (eb ^^ e) - where eb = case feb of Base2 -> 2 ; Base10 -> 10 - -rationalFromFractionalLit :: FractionalLit pass -> Rational -rationalFromFractionalLit (FL _ _ i e expBase) = - mkRationalWithExponentBase i e expBase - -{- Note [fractional exponent bases] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -For hexadecimal rationals of -the form 0x0.3p10 the exponent is given on base 2 rather than -base 10. These are the only options, hence the sum type. See also #15646. --} - - --- Comparison operations are needed when grouping literals --- for compiling pattern-matching (module GHC.HsToCore.Match.Literal) - -instance Eq (IntegralLit pass) where - (==) = (==) `on` il_value - -instance Ord (IntegralLit pass) where - compare = compare `on` il_value - -instance (XIntegralLit pass ~ SourceText) => Outputable (IntegralLit pass) where - ppr (IL (SourceText src) _ _) = ftext src - ppr (IL NoSourceText _ value) = text (show value) - - --- | Compare fractional lits with small exponents for value equality but --- large values for syntactic equality. -compareFractionalLit :: FractionalLit pass -> FractionalLit pass -> Ordering -compareFractionalLit fl1 fl2 - | fl_exp fl1 < 100 && fl_exp fl2 < 100 && fl_exp fl1 >= -100 && fl_exp fl2 >= -100 - = rationalFromFractionalLit fl1 `compare` rationalFromFractionalLit fl2 - | otherwise = (compare `on` (\x -> (fl_signi x, fl_exp x, fl_exp_base x))) fl1 fl2 - --- | Be wary of using this instance to compare for equal *values* when exponents are --- large. The same value expressed in different syntactic form won't compare as equal when --- any of the exponents is >= 100. -instance Eq (FractionalLit pass) where - (==) fl1 fl2 = case compare fl1 fl2 of - EQ -> True - _ -> False - --- | Be wary of using this instance to compare for equal *values* when exponents are --- large. The same value expressed in different syntactic form won't compare as equal when --- any of the exponents is >= 100. -instance Ord (FractionalLit pass) where - compare = compareFractionalLit - -instance (XFractionalLit pass ~ SourceText) - => Outputable (FractionalLit pass) where - ppr (fl@(FL {})) = - pprWithSourceText (fl_text fl) $ - rational $ mkRationalWithExponentBase (fl_signi fl) (fl_exp fl) (fl_exp_base fl) - --- | A String Literal in the source, including its original raw format for use by --- source to source manipulation tools. -data StringLit pass = SL - { sl_st :: XStringLit pass, -- literal raw source. - -- See Note [Literal source text] - sl_fs :: FastString -- literal string value - } - -instance Eq (StringLit pass) where - (SL _ a) == (SL _ b) = a == b - -instance Ord (StringLit pass) where - (SL _ a) `compare` (SL _ b) = a `lexicalCompareFS` b - -deriving instance (Data pass, XStringLit pass ~ (SourceText, Maybe NoCommentsLocation)) - => Data (StringLit pass) - -instance (XStringLit pass ~ (SourceText, Maybe NoCommentsLocation)) - => Outputable (StringLit pass) where - ppr sl = pprWithSourceText (fst (sl_st sl)) (doubleQuotes $ ftext $ sl_fs sl) ===================================== compiler/GHC/Unit/Module/Warnings.hs ===================================== @@ -60,10 +60,12 @@ import GHC.Hs.Extension import GHC.Parser.Annotation import GHC.Utils.Outputable +import GHC.Utils.Outputable.Instances () import GHC.Utils.Binary import GHC.Unicode import Language.Haskell.Syntax.Extension +import Language.Haskell.Syntax.Lit import Data.Data import Data.List (isPrefixOf) @@ -237,11 +239,6 @@ warningTxtSame w1 w2 deriving instance Eq InWarningCategory deriving instance (Eq (IdP (GhcPass pass))) => Eq (WarningTxt (GhcPass pass)) -deriving instance - ( Data (GhcPass p), - (XStringLit (GhcPass p) ~ (SourceText, Maybe NoCommentsLocation)), - Data (IdP (GhcPass p))) - => Data (WarningTxt (GhcPass p)) type instance Anno (WarningTxt (GhcPass pass)) = SrcSpanAnnP ===================================== compiler/GHC/Utils/Outputable/Instances.hs ===================================== @@ -0,0 +1,23 @@ +{-# OPTIONS_GHC -fno-warn-orphans #-} +module GHC.Utils.Outputable.Instances where + +import GHC.Prelude +import GHC.Types.SourceText (SourceText(..), pprWithSourceText) +import GHC.Types.SrcLoc (NoCommentsLocation) +import GHC.Utils.Outputable +import Language.Haskell.Syntax.Extension +import Language.Haskell.Syntax.Lit + +instance (XIntegralLit pass ~ SourceText) => Outputable (IntegralLit pass) where + ppr (IL (SourceText src) _ _) = ftext src + ppr (IL NoSourceText _ value) = text (show value) + +instance (XFractionalLit pass ~ SourceText) + => Outputable (FractionalLit pass) where + ppr (fl@(FL {})) = + pprWithSourceText (fl_text fl) $ + rational $ mkRationalWithExponentBase (fl_signi fl) (fl_exp fl) (fl_exp_base fl) + +instance (XStringLit pass ~ (SourceText, Maybe NoCommentsLocation)) + => Outputable (StringLit pass) where + ppr sl = pprWithSourceText (fst (sl_st sl)) (doubleQuotes $ ftext $ sl_fs sl) ===================================== compiler/Language/Haskell/Syntax/Binds.hs ===================================== @@ -30,13 +30,13 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Pat ( LPat ) import Language.Haskell.Syntax.Extension +import Language.Haskell.Syntax.Lit import Language.Haskell.Syntax.Type import GHC.Types.Fixity (Fixity) import GHC.Types.Basic (InlinePragma) import GHC.Data.BooleanFormula (LBooleanFormula) -import GHC.Types.SourceText (StringLit) import Data.Void import Data.Bool ===================================== compiler/Language/Haskell/Syntax/Expr.hs ===================================== @@ -32,7 +32,6 @@ import Language.Haskell.Syntax.Binds -- others: import GHC.Types.Fixity (LexicalFixity(Infix), Fixity) -import GHC.Types.SourceText (StringLit) import GHC.Data.FastString (FastString) ===================================== compiler/Language/Haskell/Syntax/Lit.hs ===================================== @@ -18,21 +18,16 @@ -- | Source-language literals module Language.Haskell.Syntax.Lit where +import Prelude import Language.Haskell.Syntax.Extension -import GHC.Types.SourceText (IntegralLit, FractionalLit, StringLit, SourceText, NoCommentsLocation) import GHC.Core.Type (Type) -import GHC.Utils.Panic (panic) -import GHC.Data.FastString (FastString) +import GHC.Data.FastString (FastString, lexicalCompareFS) import Data.ByteString (ByteString) import Data.Data hiding ( Fixity ) -import Data.Bool -import Data.Ord -import Data.Eq -import Data.Char -import Prelude (Maybe, Integer) +import Data.Function (on) {- ************************************************************************ @@ -127,14 +122,12 @@ data OverLitVal pass | HsFractional !(FractionalLit pass) -- ^ Frac-looking literals | HsIsString !(StringLit pass) -- ^ String-looking literals -deriving instance (Data pass, XIntegralLit pass ~ SourceText, XFractionalLit pass ~ SourceText, XStringLit pass ~ (SourceText, Maybe NoCommentsLocation)) => Data (OverLitVal pass) - -- Comparison operations are needed when grouping literals -- for compiling pattern-matching (module GHC.HsToCore.Match.Literal) instance (Eq (XXOverLit pass)) => Eq (HsOverLit pass) where (OverLit _ val1) == (OverLit _ val2) = val1 == val2 (XOverLit val1) == (XOverLit val2) = val1 == val2 - _ == _ = panic "Eq HsOverLit" + _ == _ = False instance Eq (OverLitVal pass) where (HsIntegral i1) == (HsIntegral i2) = i1 == i2 @@ -145,7 +138,8 @@ instance Eq (OverLitVal pass) where instance (Ord (XXOverLit pass)) => Ord (HsOverLit pass) where compare (OverLit _ val1) (OverLit _ val2) = val1 `compare` val2 compare (XOverLit val1) (XOverLit val2) = val1 `compare` val2 - compare _ _ = panic "Ord HsOverLit" + compare (OverLit _ _) (XOverLit _) = GT + compare (XOverLit _) (OverLit _ _) = LT instance Ord (OverLitVal pass) where compare (HsIntegral i1) (HsIntegral i2) = i1 `compare` i2 @@ -157,3 +151,115 @@ instance Ord (OverLitVal pass) where compare (HsIsString s1) (HsIsString s2) = s1 `compare` s2 compare (HsIsString _) (HsIntegral _) = GT compare (HsIsString _) (HsFractional _) = GT + +------------------------------------------------ +-- Literals +------------------------------------------------ + +-- | Integral Literal +-- +-- Used (instead of Integer) to represent negative zegative zero which is +-- required for NegativeLiterals extension to correctly parse `-0::Double` +-- as negative zero. See also #13211. +data IntegralLit pass = IL + { il_text :: XIntegralLit pass + , il_neg :: Bool -- See Note [Negative zero] in GHC.Rename.Pat + , il_value :: Integer + } + +-- Comparison operations are needed when grouping literals +-- for compiling pattern-matching (module GHC.HsToCore.Match.Literal) + +instance Eq (IntegralLit pass) where + (==) = (==) `on` il_value + +instance Ord (IntegralLit pass) where + compare = compare `on` il_value + +-- | The Show instance is required for the derived GHC.Parser.Lexer.Token instance when DEBUG is on +deriving instance Show (XIntegralLit pass) => Show (IntegralLit pass) + +-- | Fractional Literal +-- +-- Used (instead of Rational) to represent exactly the floating point literal that we +-- encountered in the user's source program. This allows us to pretty-print exactly what +-- the user wrote, which is important e.g. for floating point numbers that can't represented +-- as Doubles (we used to via Double for pretty-printing). See also #2245. +-- Note [FractionalLit representation] in GHC.HsToCore.Match.Literal +-- The actual value then is: sign * fl_signi * (fl_exp_base^fl_exp) +-- where sign = if fl_neg then (-1) else 1 +-- +-- For example FL { fl_neg = True, fl_signi = 5.3, fl_exp = 4, fl_exp_base = Base10 } +-- denotes -5300 + +data FractionalLit pass = FL + { fl_text :: XFractionalLit pass -- ^ How the value was written in the source + , fl_neg :: Bool -- See Note [Negative zero] + , fl_signi :: Rational -- The significand component of the literal + , fl_exp :: Integer -- The exponent component of the literal + , fl_exp_base :: FractionalExponentBase -- See Note [fractional exponent bases] + } + +-- See Note [FractionalLit representation] in GHC.HsToCore.Match.Literal +data FractionalExponentBase + = Base2 -- Used in hex fractional literals + | Base10 + deriving (Eq, Ord, Data, Show) + +-- TODO +{- Note [fractional exponent bases] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +For hexadecimal rationals of +the form 0x0.3p10 the exponent is given on base 2 rather than +base 10. These are the only options, hence the sum type. See also #15646. +-} + +-- | Be wary of using this instance to compare for equal *values* when exponents are +-- large. The same value expressed in different syntactic form won't compare as equal when +-- any of the exponents is >= 100. +instance Eq (FractionalLit pass) where + (==) fl1 fl2 = case compare fl1 fl2 of + EQ -> True + _ -> False + +-- | Be wary of using this instance to compare for equal *values* when exponents are +-- large. The same value expressed in different syntactic form won't compare as equal when +-- any of the exponents is >= 100. +instance Ord (FractionalLit pass) where + compare = compareFractionalLit + +-- | The Show instance is required for the derived GHC.Parser.Lexer.Token instance when DEBUG is on +deriving instance Show (XFractionalLit pass) => Show (FractionalLit pass) + +-- | Compare fractional lits with small exponents for value equality but +-- large values for syntactic equality. +compareFractionalLit :: FractionalLit pass -> FractionalLit pass -> Ordering +compareFractionalLit fl1 fl2 + | fl_exp fl1 < 100 && fl_exp fl2 < 100 && fl_exp fl1 >= -100 && fl_exp fl2 >= -100 + = rationalFromFractionalLit fl1 `compare` rationalFromFractionalLit fl2 + | otherwise = (compare `on` (\x -> (fl_signi x, fl_exp x, fl_exp_base x))) fl1 fl2 + +rationalFromFractionalLit :: FractionalLit pass -> Rational +rationalFromFractionalLit (FL _ _ i e expBase) = + mkRationalWithExponentBase i e expBase + +mkRationalWithExponentBase :: Rational -> Integer -> FractionalExponentBase -> Rational +mkRationalWithExponentBase i e feb = i * (eb ^^ e) + where eb = case feb of Base2 -> 2 ; Base10 -> 10 + +-- | A String Literal in the source, including its original raw format for use by +-- source to source manipulation tools. +data StringLit pass = SL + { sl_st :: XStringLit pass, -- literal raw source. + -- See Note [Literal source text] + sl_fs :: FastString -- literal string value + } + +instance Eq (StringLit pass) where + (SL _ a) == (SL _ b) = a == b + +instance Ord (StringLit pass) where + (SL _ a) `compare` (SL _ b) = a `lexicalCompareFS` b + +-- | The Show instance is required for the derived GHC.Parser.Lexer.Token instance when DEBUG is on +deriving instance Show (XStringLit pass) => Show (StringLit pass) ===================================== compiler/Language/Haskell/Syntax/Lit.hs-boot ===================================== @@ -0,0 +1,41 @@ +{-# LANGUAGE UndecidableInstances #-} +module Language.Haskell.Syntax.Lit where + +import GHC.Data.FastString +import Language.Haskell.Syntax.Extension +import Prelude + +data IntegralLit pass = IL + { il_text :: XIntegralLit pass + , il_neg :: Bool + , il_value :: Integer + } + +instance Eq (IntegralLit pass) +instance Ord (IntegralLit pass) + +data FractionalLit pass = FL + { fl_text :: XFractionalLit pass + , fl_neg :: Bool + , fl_signi :: Rational + , fl_exp :: Integer + , fl_exp_base :: FractionalExponentBase + } + +instance Eq (FractionalLit pass) +instance Ord (FractionalLit pass) + +data FractionalExponentBase + = Base2 + | Base10 + +instance Eq FractionalExponentBase +instance Ord FractionalExponentBase + +data StringLit pass = SL + { sl_st :: XStringLit pass, + + sl_fs :: FastString + } +instance Eq (StringLit pass) +instance Ord (StringLit pass) ===================================== compiler/ghc.cabal.in ===================================== @@ -949,6 +949,7 @@ Library GHC.Utils.Monad.Codensity GHC.Utils.Monad.State.Strict GHC.Utils.Outputable + GHC.Utils.Outputable.Instances GHC.Utils.Panic GHC.Utils.Panic.Plain GHC.Utils.Ppr View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/69d7653130c1be7289600474ecd5f997fde1cdb7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/69d7653130c1be7289600474ecd5f997fde1cdb7 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 12:33:58 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Mon, 10 Jun 2024 08:33:58 -0400 Subject: [Git][ghc/ghc][wip/supersven/fix-MO_XX_Conv-folding] 33 commits: Add AArch64 CLZ, CTZ, RBIT primop implementations. Message-ID: <6666f2b652ce6_151ed3c4ee1071043@gitlab.mail> Sven Tennie pushed to branch wip/supersven/fix-MO_XX_Conv-folding at Glasgow Haskell Compiler / GHC Commits: 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - 14e8d474 by Sven Tennie at 2024-06-10T12:33:54+00:00 Ignore signedness for MO_XX_Conv MO_XX_Conv is used on (unsigned) words, too. Interpreting them as signed may lead to weird conversions / sign-extensions: E.g. on RISCV64 this conversion happened for a Word64#: %MO_XX_Conv_W32_W64(4294967293 :: W32) -> CmmLit (CmmInt (-3) W64) - - - - - 30 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - CODEOWNERS - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Driver/Config/StgToCmm.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Session.hs - compiler/GHC/JS/Ident.hs - compiler/GHC/JS/JStg/Monad.hs - compiler/GHC/JS/JStg/Syntax.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Syntax.hs - compiler/GHC/Linker/Static.hs - compiler/GHC/StgToCmm/Config.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToJS.hs - compiler/GHC/StgToJS/Apply.hs - compiler/GHC/StgToJS/Arg.hs - compiler/GHC/StgToJS/Closure.hs - compiler/GHC/StgToJS/Expr.hs - compiler/GHC/StgToJS/FFI.hs - compiler/GHC/StgToJS/Heap.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a97c58c85262274ab01a6dbee6781e338f8b1e72...14e8d474da90773297f595ca4676b50c9c52ea05 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a97c58c85262274ab01a6dbee6781e338f8b1e72...14e8d474da90773297f595ca4676b50c9c52ea05 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 12:52:39 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Mon, 10 Jun 2024 08:52:39 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/wasm-page-sized-mblock Message-ID: <6666f71744fa9_151ed31022fc8907f8@gitlab.mail> Cheng Shao pushed new branch wip/wasm-page-sized-mblock at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/wasm-page-sized-mblock You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 13:09:07 2024 From: gitlab at gitlab.haskell.org (Alexander Foremny (@aforemny)) Date: Mon, 10 Jun 2024 09:09:07 -0400 Subject: [Git][ghc/ghc][wip/aforemny/ttg-remove-source-text] ttg: remove `GHC.Types.SourceText` imports from `Language.Haskell` Message-ID: <6666faf35e5fb_151ed313b4ab01116c9@gitlab.mail> Alexander Foremny pushed to branch wip/aforemny/ttg-remove-source-text at Glasgow Haskell Compiler / GHC Commits: 9f5ff22e by Alexander Foremny at 2024-06-10T15:08:41+02:00 ttg: remove `GHC.Types.SourceText` imports from `Language.Haskell` To remove `GHC.Types.SourceText` from `Language.Haskell`, we move `SourceText`'s literals to `Language.Haskell.Syntax.Lit`. A temporary hs-boot file has been added for `Language.Haskell.Syntax.Lit` because without it, currently, we are unable to break cyclic module imports. Breaking cyclic module imports between `GHC` and `Language.Haskell` should not exist in the end of things, so that file can be removed before merging. Additionally, this commit changes the implementation of `Eq (XXOverLit pass)` and `Eq (OverLitVal pass)` to not use `panic` anymore. Additionally, a module `GHC.Utils.Outputable.Instances` is introduced that, similar to `GHC.Hs.Instances`, collects (unavoidable) orphan instances for `Outputable`. - - - - - 26 changed files: - compiler/GHC/Core/InstEnv.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Pmc/Solver/Types.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Parser/HaddockLex.x - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Pat.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Types/PkgQual.hs - compiler/GHC/Types/SourceText.hs - compiler/GHC/Unit/Module/Warnings.hs - + compiler/GHC/Utils/Outputable/Instances.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Lit.hs - + compiler/Language/Haskell/Syntax/Lit.hs-boot - compiler/ghc.cabal.in - utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs Changes: ===================================== compiler/GHC/Core/InstEnv.hs ===================================== @@ -56,7 +56,6 @@ import GHC.Types.Name.Set import GHC.Types.Basic import GHC.Types.Id import GHC.Generics (Generic) -import Data.Data ( Data ) import Data.List.NonEmpty ( NonEmpty (..), nonEmpty ) import qualified Data.List.NonEmpty as NE import Data.Maybe ( isJust ) @@ -115,7 +114,6 @@ data ClsInst -- See Note [Implementation of deprecated instances] -- in GHC.Tc.Solver.Dict } - deriving Data -- | A fuzzy comparison function for class instances, intended for sorting -- instances before displaying them to the user. ===================================== compiler/GHC/Hs/Binds.hs ===================================== @@ -30,8 +30,9 @@ module GHC.Hs.Binds import GHC.Prelude -import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Binds +import Language.Haskell.Syntax.Extension +import Language.Haskell.Syntax.Lit import {-# SOURCE #-} GHC.Hs.Expr ( pprExpr, pprFunBind, pprPatBind ) import {-# SOURCE #-} GHC.Hs.Pat (pprLPat ) ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -21,8 +21,11 @@ module GHC.Hs.Instances where -- UndecidableInstances ? +import Language.Haskell.Syntax.Lit + import Data.Data hiding ( Fixity ) +import GHC.Core.InstEnv import GHC.Prelude import GHC.Hs.Extension import GHC.Hs.Binds @@ -32,7 +35,9 @@ import GHC.Hs.Lit import GHC.Hs.Type import GHC.Hs.Pat import GHC.Hs.ImpExp +import GHC.Types.PkgQual import GHC.Parser.Annotation +import GHC.Unit.Module.Warnings -- --------------------------------------------------------------------- -- Data derivations from GHC.Hs----------------------------------------- @@ -578,3 +583,29 @@ deriving instance Data XXPatGhcTc deriving instance Data XViaStrategyPs -- --------------------------------------------------------------------- + +deriving instance Data (IntegralLit GhcPs) +deriving instance Data (IntegralLit GhcRn) +deriving instance Data (IntegralLit GhcTc) + +deriving instance Data (FractionalLit GhcPs) +deriving instance Data (FractionalLit GhcRn) +deriving instance Data (FractionalLit GhcTc) + +deriving instance Data (StringLit GhcPs) +deriving instance Data (StringLit GhcRn) +deriving instance Data (StringLit GhcTc) + +deriving instance Data (OverLitVal GhcPs) +deriving instance Data (OverLitVal GhcRn) +deriving instance Data (OverLitVal GhcTc) + +deriving instance Data (RawPkgQual GhcPs) +deriving instance Data (RawPkgQual GhcRn) +deriving instance Data (RawPkgQual GhcTc) + +deriving instance Data (WarningTxt GhcPs) +deriving instance Data (WarningTxt GhcRn) +deriving instance Data (WarningTxt GhcTc) + +deriving instance Data ClsInst ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -31,7 +31,6 @@ import GHC.HsToCore.Arrows import GHC.HsToCore.Monad import GHC.HsToCore.Pmc import GHC.HsToCore.Errors.Types -import GHC.Types.SourceText import GHC.Types.Name hiding (varName) import GHC.Core.FamInstEnv( topNormaliseType ) import GHC.HsToCore.Quote ===================================== compiler/GHC/HsToCore/Match.hs ===================================== @@ -29,10 +29,6 @@ import {-#SOURCE#-} GHC.HsToCore.Expr (dsExpr) import GHC.Types.Basic -import GHC.Types.SourceText - ( FractionalLit, - IntegralLit(il_value), - StringLit(sl_fs) ) import GHC.Driver.DynFlags import GHC.Hs import GHC.Hs.Syn.Type ===================================== compiler/GHC/HsToCore/Pmc/Desugar.hs ===================================== @@ -45,7 +45,6 @@ import GHC.Core.TyCo.Compare( eqType ) import GHC.Core.Type import GHC.Data.Maybe import qualified GHC.LanguageExtensions as LangExt -import GHC.Types.SourceText (FractionalLit(..)) import Control.Monad (zipWithM, replicateM) import Data.List (elemIndex) import Data.List.NonEmpty ( NonEmpty(..) ) ===================================== compiler/GHC/HsToCore/Pmc/Solver/Types.hs ===================================== @@ -68,7 +68,7 @@ import GHC.Builtin.Types.Prim import GHC.Tc.Solver.InertSet (InertSet, emptyInert) import GHC.Tc.Utils.TcType (isStringTy) import GHC.Types.CompleteMatch (CompleteMatch(..)) -import GHC.Types.SourceText (SourceText(..), FractionalLit, FractionalExponentBase(..)) +import GHC.Types.SourceText (SourceText(..)) import Numeric (fromRat) import Data.Foldable (find) import Data.Ratio ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -67,7 +67,6 @@ import GHC.Types.SourceFile import GHC.Types.TyThing import GHC.Types.HpcInfo import GHC.Types.CompleteMatch -import GHC.Types.SourceText import GHC.Types.SrcLoc ( unLoc ) import GHC.Utils.Outputable ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -95,6 +95,8 @@ import GHC.Utils.Panic import GHC.Utils.Misc( dropList, filterByList, notNull, unzipWith, seqList, zipWithEqual ) +import Language.Haskell.Syntax.Lit + import Control.Monad import System.IO.Unsafe import Control.DeepSeq ===================================== compiler/GHC/Parser/HaddockLex.x ===================================== @@ -10,7 +10,6 @@ import GHC.Hs.Doc import GHC.Parser.Lexer import GHC.Parser.Annotation import GHC.Types.SrcLoc -import GHC.Types.SourceText import GHC.Data.StringBuffer import qualified GHC.Data.Strict as Strict import GHC.Types.Name.Reader @@ -27,6 +26,8 @@ import Data.ByteString ( ByteString ) import qualified Data.ByteString as BS import qualified GHC.LanguageExtensions as LangExt + +import Language.Haskell.Syntax.Lit } -- ----------------------------------------------------------------------------- ===================================== compiler/GHC/Rename/Module.hs ===================================== @@ -22,7 +22,6 @@ import GHC.Prelude hiding ( head ) import {-# SOURCE #-} GHC.Rename.Expr( rnLExpr ) import {-# SOURCE #-} GHC.Rename.Splice ( rnSpliceDecl, rnTopSpliceDecls ) -import GHC.Types.SourceText (StringLit) import GHC.Hs import GHC.Types.FieldLabel import GHC.Types.Name.Reader ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -75,7 +75,6 @@ import GHC.Types.Hint import GHC.Types.SourceFile import GHC.Types.SrcLoc as SrcLoc import GHC.Types.Basic ( TopLevelFlag(..) ) -import GHC.Types.SourceText import GHC.Types.Id import GHC.Types.HpcInfo import GHC.Types.PkgQual ===================================== compiler/GHC/Rename/Pat.hs ===================================== @@ -67,7 +67,6 @@ import GHC.Types.Name.Reader import GHC.Types.Unique.Set import GHC.Types.Basic -import GHC.Types.SourceText import GHC.Utils.Misc import GHC.Data.FastString ( uniqCompareFS ) import GHC.Data.List.SetOps( removeDups ) ===================================== compiler/GHC/Rename/Utils.hs ===================================== @@ -59,7 +59,7 @@ import GHC.Types.Name.Env import GHC.Core.DataCon import GHC.Types.SrcLoc as SrcLoc import GHC.Types.SourceFile -import GHC.Types.SourceText ( SourceText(..), IntegralLit ) +import GHC.Types.SourceText (SourceText(..)) import GHC.Utils.Outputable import GHC.Utils.Misc import GHC.Unit.Module.ModIface ===================================== compiler/GHC/Tc/Gen/Bind.hs ===================================== @@ -66,7 +66,6 @@ import GHC.Builtin.Types ( mkConstraintTupleTy, multiplicityTy, oneDataConTy ) import GHC.Builtin.Types.Prim import GHC.Unit.Module -import GHC.Types.SourceText import GHC.Types.Id import GHC.Types.Var as Var import GHC.Types.Var.Set ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -135,7 +135,6 @@ import GHC.Core.UsageEnv import GHC.Types.Var import GHC.Types.Id as Id import GHC.Types.Name -import GHC.Types.SourceText import GHC.Types.Var.Set import GHC.Builtin.Types ===================================== compiler/GHC/Types/PkgQual.hs ===================================== @@ -9,6 +9,7 @@ import GHC.Unit.Types import GHC.Utils.Outputable import Language.Haskell.Syntax.Extension +import {-# SOURCE #-} Language.Haskell.Syntax.Lit import Data.Data @@ -17,10 +18,6 @@ data RawPkgQual pass = NoRawPkgQual -- ^ No package qualifier | RawPkgQual (StringLit pass) -- ^ Raw package qualifier string. -deriving instance - (Data pass, XStringLit pass ~ (SourceText, Maybe NoCommentsLocation)) - => Data (RawPkgQual pass) - -- | Package-qualifier after renaming -- -- Renaming detects if "this" or the unit-id of the home-unit was used as a ===================================== compiler/GHC/Types/SourceText.hs ===================================== @@ -11,14 +11,6 @@ module GHC.Types.SourceText ( SourceText (..) , NoCommentsLocation , pprWithSourceText - - -- * Literals - , IntegralLit(..) - , FractionalLit(..) - , StringLit(..) - , rationalFromFractionalLit - , FractionalExponentBase(..) - ) where @@ -30,13 +22,10 @@ import GHC.Utils.Outputable import GHC.Utils.Binary import GHC.Utils.Panic -import Data.Function (on) import Data.Data import GHC.Types.SrcLoc import Control.DeepSeq -import Language.Haskell.Syntax.Extension - {- Note [Pragma source text] ~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -128,135 +117,3 @@ instance Binary SourceText where pprWithSourceText :: SourceText -> SDoc -> SDoc pprWithSourceText NoSourceText d = d pprWithSourceText (SourceText src) _ = ftext src - ------------------------------------------------- --- Literals ------------------------------------------------- - --- | Integral Literal --- --- Used (instead of Integer) to represent negative zegative zero which is --- required for NegativeLiterals extension to correctly parse `-0::Double` --- as negative zero. See also #13211. -data IntegralLit pass = IL - { il_text :: XIntegralLit pass - , il_neg :: Bool -- See Note [Negative zero] in GHC.Rename.Pat - , il_value :: Integer - } - -deriving instance (Data pass, XIntegralLit pass ~ SourceText) - => Data (IntegralLit pass) - -deriving instance (XIntegralLit pass ~ SourceText) => Show (IntegralLit pass) - --- | Fractional Literal --- --- Used (instead of Rational) to represent exactly the floating point literal that we --- encountered in the user's source program. This allows us to pretty-print exactly what --- the user wrote, which is important e.g. for floating point numbers that can't represented --- as Doubles (we used to via Double for pretty-printing). See also #2245. --- Note [FractionalLit representation] in GHC.HsToCore.Match.Literal --- The actual value then is: sign * fl_signi * (fl_exp_base^fl_exp) --- where sign = if fl_neg then (-1) else 1 --- --- For example FL { fl_neg = True, fl_signi = 5.3, fl_exp = 4, fl_exp_base = Base10 } --- denotes -5300 - -data FractionalLit pass = FL - { fl_text :: XFractionalLit pass -- ^ How the value was written in the source - , fl_neg :: Bool -- See Note [Negative zero] - , fl_signi :: Rational -- The significand component of the literal - , fl_exp :: Integer -- The exponent component of the literal - , fl_exp_base :: FractionalExponentBase -- See Note [fractional exponent bases] - } - -deriving instance (Data pass, XFractionalLit pass ~ SourceText) - => Data (FractionalLit pass) - --- | The Show instance is required for the derived GHC.Parser.Lexer.Token instance when DEBUG is on -deriving instance (XFractionalLit pass ~ SourceText) => Show (FractionalLit pass) - --- See Note [FractionalLit representation] in GHC.HsToCore.Match.Literal -data FractionalExponentBase - = Base2 -- Used in hex fractional literals - | Base10 - deriving (Eq, Ord, Data, Show) - -mkRationalWithExponentBase :: Rational -> Integer -> FractionalExponentBase -> Rational -mkRationalWithExponentBase i e feb = i * (eb ^^ e) - where eb = case feb of Base2 -> 2 ; Base10 -> 10 - -rationalFromFractionalLit :: FractionalLit pass -> Rational -rationalFromFractionalLit (FL _ _ i e expBase) = - mkRationalWithExponentBase i e expBase - -{- Note [fractional exponent bases] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -For hexadecimal rationals of -the form 0x0.3p10 the exponent is given on base 2 rather than -base 10. These are the only options, hence the sum type. See also #15646. --} - - --- Comparison operations are needed when grouping literals --- for compiling pattern-matching (module GHC.HsToCore.Match.Literal) - -instance Eq (IntegralLit pass) where - (==) = (==) `on` il_value - -instance Ord (IntegralLit pass) where - compare = compare `on` il_value - -instance (XIntegralLit pass ~ SourceText) => Outputable (IntegralLit pass) where - ppr (IL (SourceText src) _ _) = ftext src - ppr (IL NoSourceText _ value) = text (show value) - - --- | Compare fractional lits with small exponents for value equality but --- large values for syntactic equality. -compareFractionalLit :: FractionalLit pass -> FractionalLit pass -> Ordering -compareFractionalLit fl1 fl2 - | fl_exp fl1 < 100 && fl_exp fl2 < 100 && fl_exp fl1 >= -100 && fl_exp fl2 >= -100 - = rationalFromFractionalLit fl1 `compare` rationalFromFractionalLit fl2 - | otherwise = (compare `on` (\x -> (fl_signi x, fl_exp x, fl_exp_base x))) fl1 fl2 - --- | Be wary of using this instance to compare for equal *values* when exponents are --- large. The same value expressed in different syntactic form won't compare as equal when --- any of the exponents is >= 100. -instance Eq (FractionalLit pass) where - (==) fl1 fl2 = case compare fl1 fl2 of - EQ -> True - _ -> False - --- | Be wary of using this instance to compare for equal *values* when exponents are --- large. The same value expressed in different syntactic form won't compare as equal when --- any of the exponents is >= 100. -instance Ord (FractionalLit pass) where - compare = compareFractionalLit - -instance (XFractionalLit pass ~ SourceText) - => Outputable (FractionalLit pass) where - ppr (fl@(FL {})) = - pprWithSourceText (fl_text fl) $ - rational $ mkRationalWithExponentBase (fl_signi fl) (fl_exp fl) (fl_exp_base fl) - --- | A String Literal in the source, including its original raw format for use by --- source to source manipulation tools. -data StringLit pass = SL - { sl_st :: XStringLit pass, -- literal raw source. - -- See Note [Literal source text] - sl_fs :: FastString -- literal string value - } - -instance Eq (StringLit pass) where - (SL _ a) == (SL _ b) = a == b - -instance Ord (StringLit pass) where - (SL _ a) `compare` (SL _ b) = a `lexicalCompareFS` b - -deriving instance (Data pass, XStringLit pass ~ (SourceText, Maybe NoCommentsLocation)) - => Data (StringLit pass) - -instance (XStringLit pass ~ (SourceText, Maybe NoCommentsLocation)) - => Outputable (StringLit pass) where - ppr sl = pprWithSourceText (fst (sl_st sl)) (doubleQuotes $ ftext $ sl_fs sl) ===================================== compiler/GHC/Unit/Module/Warnings.hs ===================================== @@ -60,10 +60,12 @@ import GHC.Hs.Extension import GHC.Parser.Annotation import GHC.Utils.Outputable +import GHC.Utils.Outputable.Instances () import GHC.Utils.Binary import GHC.Unicode import Language.Haskell.Syntax.Extension +import Language.Haskell.Syntax.Lit import Data.Data import Data.List (isPrefixOf) @@ -237,11 +239,6 @@ warningTxtSame w1 w2 deriving instance Eq InWarningCategory deriving instance (Eq (IdP (GhcPass pass))) => Eq (WarningTxt (GhcPass pass)) -deriving instance - ( Data (GhcPass p), - (XStringLit (GhcPass p) ~ (SourceText, Maybe NoCommentsLocation)), - Data (IdP (GhcPass p))) - => Data (WarningTxt (GhcPass p)) type instance Anno (WarningTxt (GhcPass pass)) = SrcSpanAnnP ===================================== compiler/GHC/Utils/Outputable/Instances.hs ===================================== @@ -0,0 +1,23 @@ +{-# OPTIONS_GHC -fno-warn-orphans #-} +module GHC.Utils.Outputable.Instances where + +import GHC.Prelude +import GHC.Types.SourceText (SourceText(..), pprWithSourceText) +import GHC.Types.SrcLoc (NoCommentsLocation) +import GHC.Utils.Outputable +import Language.Haskell.Syntax.Extension +import Language.Haskell.Syntax.Lit + +instance (XIntegralLit pass ~ SourceText) => Outputable (IntegralLit pass) where + ppr (IL (SourceText src) _ _) = ftext src + ppr (IL NoSourceText _ value) = text (show value) + +instance (XFractionalLit pass ~ SourceText) + => Outputable (FractionalLit pass) where + ppr (fl@(FL {})) = + pprWithSourceText (fl_text fl) $ + rational $ mkRationalWithExponentBase (fl_signi fl) (fl_exp fl) (fl_exp_base fl) + +instance (XStringLit pass ~ (SourceText, Maybe NoCommentsLocation)) + => Outputable (StringLit pass) where + ppr sl = pprWithSourceText (fst (sl_st sl)) (doubleQuotes $ ftext $ sl_fs sl) ===================================== compiler/Language/Haskell/Syntax/Binds.hs ===================================== @@ -30,13 +30,13 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Pat ( LPat ) import Language.Haskell.Syntax.Extension +import Language.Haskell.Syntax.Lit import Language.Haskell.Syntax.Type import GHC.Types.Fixity (Fixity) import GHC.Types.Basic (InlinePragma) import GHC.Data.BooleanFormula (LBooleanFormula) -import GHC.Types.SourceText (StringLit) import Data.Void import Data.Bool ===================================== compiler/Language/Haskell/Syntax/Expr.hs ===================================== @@ -32,7 +32,6 @@ import Language.Haskell.Syntax.Binds -- others: import GHC.Types.Fixity (LexicalFixity(Infix), Fixity) -import GHC.Types.SourceText (StringLit) import GHC.Data.FastString (FastString) ===================================== compiler/Language/Haskell/Syntax/Lit.hs ===================================== @@ -18,21 +18,16 @@ -- | Source-language literals module Language.Haskell.Syntax.Lit where +import Prelude import Language.Haskell.Syntax.Extension -import GHC.Types.SourceText (IntegralLit, FractionalLit, StringLit, SourceText, NoCommentsLocation) import GHC.Core.Type (Type) -import GHC.Utils.Panic (panic) -import GHC.Data.FastString (FastString) +import GHC.Data.FastString (FastString, lexicalCompareFS) import Data.ByteString (ByteString) import Data.Data hiding ( Fixity ) -import Data.Bool -import Data.Ord -import Data.Eq -import Data.Char -import Prelude (Maybe, Integer) +import Data.Function (on) {- ************************************************************************ @@ -127,14 +122,12 @@ data OverLitVal pass | HsFractional !(FractionalLit pass) -- ^ Frac-looking literals | HsIsString !(StringLit pass) -- ^ String-looking literals -deriving instance (Data pass, XIntegralLit pass ~ SourceText, XFractionalLit pass ~ SourceText, XStringLit pass ~ (SourceText, Maybe NoCommentsLocation)) => Data (OverLitVal pass) - -- Comparison operations are needed when grouping literals -- for compiling pattern-matching (module GHC.HsToCore.Match.Literal) instance (Eq (XXOverLit pass)) => Eq (HsOverLit pass) where (OverLit _ val1) == (OverLit _ val2) = val1 == val2 (XOverLit val1) == (XOverLit val2) = val1 == val2 - _ == _ = panic "Eq HsOverLit" + _ == _ = False instance Eq (OverLitVal pass) where (HsIntegral i1) == (HsIntegral i2) = i1 == i2 @@ -145,7 +138,8 @@ instance Eq (OverLitVal pass) where instance (Ord (XXOverLit pass)) => Ord (HsOverLit pass) where compare (OverLit _ val1) (OverLit _ val2) = val1 `compare` val2 compare (XOverLit val1) (XOverLit val2) = val1 `compare` val2 - compare _ _ = panic "Ord HsOverLit" + compare (OverLit _ _) (XOverLit _) = GT + compare (XOverLit _) (OverLit _ _) = LT instance Ord (OverLitVal pass) where compare (HsIntegral i1) (HsIntegral i2) = i1 `compare` i2 @@ -157,3 +151,115 @@ instance Ord (OverLitVal pass) where compare (HsIsString s1) (HsIsString s2) = s1 `compare` s2 compare (HsIsString _) (HsIntegral _) = GT compare (HsIsString _) (HsFractional _) = GT + +------------------------------------------------ +-- Literals +------------------------------------------------ + +-- | Integral Literal +-- +-- Used (instead of Integer) to represent negative zegative zero which is +-- required for NegativeLiterals extension to correctly parse `-0::Double` +-- as negative zero. See also #13211. +data IntegralLit pass = IL + { il_text :: XIntegralLit pass + , il_neg :: Bool -- See Note [Negative zero] in GHC.Rename.Pat + , il_value :: Integer + } + +-- Comparison operations are needed when grouping literals +-- for compiling pattern-matching (module GHC.HsToCore.Match.Literal) + +instance Eq (IntegralLit pass) where + (==) = (==) `on` il_value + +instance Ord (IntegralLit pass) where + compare = compare `on` il_value + +-- | The Show instance is required for the derived GHC.Parser.Lexer.Token instance when DEBUG is on +deriving instance Show (XIntegralLit pass) => Show (IntegralLit pass) + +-- | Fractional Literal +-- +-- Used (instead of Rational) to represent exactly the floating point literal that we +-- encountered in the user's source program. This allows us to pretty-print exactly what +-- the user wrote, which is important e.g. for floating point numbers that can't represented +-- as Doubles (we used to via Double for pretty-printing). See also #2245. +-- Note [FractionalLit representation] in GHC.HsToCore.Match.Literal +-- The actual value then is: sign * fl_signi * (fl_exp_base^fl_exp) +-- where sign = if fl_neg then (-1) else 1 +-- +-- For example FL { fl_neg = True, fl_signi = 5.3, fl_exp = 4, fl_exp_base = Base10 } +-- denotes -5300 + +data FractionalLit pass = FL + { fl_text :: XFractionalLit pass -- ^ How the value was written in the source + , fl_neg :: Bool -- See Note [Negative zero] + , fl_signi :: Rational -- The significand component of the literal + , fl_exp :: Integer -- The exponent component of the literal + , fl_exp_base :: FractionalExponentBase -- See Note [fractional exponent bases] + } + +-- See Note [FractionalLit representation] in GHC.HsToCore.Match.Literal +data FractionalExponentBase + = Base2 -- Used in hex fractional literals + | Base10 + deriving (Eq, Ord, Data, Show) + +-- TODO +{- Note [fractional exponent bases] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +For hexadecimal rationals of +the form 0x0.3p10 the exponent is given on base 2 rather than +base 10. These are the only options, hence the sum type. See also #15646. +-} + +-- | Be wary of using this instance to compare for equal *values* when exponents are +-- large. The same value expressed in different syntactic form won't compare as equal when +-- any of the exponents is >= 100. +instance Eq (FractionalLit pass) where + (==) fl1 fl2 = case compare fl1 fl2 of + EQ -> True + _ -> False + +-- | Be wary of using this instance to compare for equal *values* when exponents are +-- large. The same value expressed in different syntactic form won't compare as equal when +-- any of the exponents is >= 100. +instance Ord (FractionalLit pass) where + compare = compareFractionalLit + +-- | The Show instance is required for the derived GHC.Parser.Lexer.Token instance when DEBUG is on +deriving instance Show (XFractionalLit pass) => Show (FractionalLit pass) + +-- | Compare fractional lits with small exponents for value equality but +-- large values for syntactic equality. +compareFractionalLit :: FractionalLit pass -> FractionalLit pass -> Ordering +compareFractionalLit fl1 fl2 + | fl_exp fl1 < 100 && fl_exp fl2 < 100 && fl_exp fl1 >= -100 && fl_exp fl2 >= -100 + = rationalFromFractionalLit fl1 `compare` rationalFromFractionalLit fl2 + | otherwise = (compare `on` (\x -> (fl_signi x, fl_exp x, fl_exp_base x))) fl1 fl2 + +rationalFromFractionalLit :: FractionalLit pass -> Rational +rationalFromFractionalLit (FL _ _ i e expBase) = + mkRationalWithExponentBase i e expBase + +mkRationalWithExponentBase :: Rational -> Integer -> FractionalExponentBase -> Rational +mkRationalWithExponentBase i e feb = i * (eb ^^ e) + where eb = case feb of Base2 -> 2 ; Base10 -> 10 + +-- | A String Literal in the source, including its original raw format for use by +-- source to source manipulation tools. +data StringLit pass = SL + { sl_st :: XStringLit pass, -- literal raw source. + -- See Note [Literal source text] + sl_fs :: FastString -- literal string value + } + +instance Eq (StringLit pass) where + (SL _ a) == (SL _ b) = a == b + +instance Ord (StringLit pass) where + (SL _ a) `compare` (SL _ b) = a `lexicalCompareFS` b + +-- | The Show instance is required for the derived GHC.Parser.Lexer.Token instance when DEBUG is on +deriving instance Show (XStringLit pass) => Show (StringLit pass) ===================================== compiler/Language/Haskell/Syntax/Lit.hs-boot ===================================== @@ -0,0 +1,41 @@ +{-# LANGUAGE UndecidableInstances #-} +module Language.Haskell.Syntax.Lit where + +import GHC.Data.FastString +import Language.Haskell.Syntax.Extension +import Prelude + +data IntegralLit pass = IL + { il_text :: XIntegralLit pass + , il_neg :: Bool + , il_value :: Integer + } + +instance Eq (IntegralLit pass) +instance Ord (IntegralLit pass) + +data FractionalLit pass = FL + { fl_text :: XFractionalLit pass + , fl_neg :: Bool + , fl_signi :: Rational + , fl_exp :: Integer + , fl_exp_base :: FractionalExponentBase + } + +instance Eq (FractionalLit pass) +instance Ord (FractionalLit pass) + +data FractionalExponentBase + = Base2 + | Base10 + +instance Eq FractionalExponentBase +instance Ord FractionalExponentBase + +data StringLit pass = SL + { sl_st :: XStringLit pass, + + sl_fs :: FastString + } +instance Eq (StringLit pass) +instance Ord (StringLit pass) ===================================== compiler/ghc.cabal.in ===================================== @@ -949,6 +949,7 @@ Library GHC.Utils.Monad.Codensity GHC.Utils.Monad.State.Strict GHC.Utils.Outputable + GHC.Utils.Outputable.Instances GHC.Utils.Panic GHC.Utils.Panic.Plain GHC.Utils.Ppr ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs ===================================== @@ -36,6 +36,8 @@ import GHC.Utils.Error (pprLocMsgEnvelopeDefault) import GHC.Utils.Outputable (text, ($$)) import GHC.Utils.Panic (panic) +import Language.Haskell.Syntax.Lit + import Haddock.Backends.Hyperlinker.Types as T import Haddock.GhcUtils View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f5ff22e8c988d661a8ec33701333867f3403411 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9f5ff22e8c988d661a8ec33701333867f3403411 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 13:40:44 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Mon, 10 Jun 2024 09:40:44 -0400 Subject: [Git][ghc/ghc][wip/supersven/ghc-9.10-riscv-ncg] 234 commits: Add release notes entry for GHC proposal 575 Message-ID: <6667025c8b824_151ed31a8f60013017c@gitlab.mail> Sven Tennie pushed to branch wip/supersven/ghc-9.10-riscv-ncg at Glasgow Haskell Compiler / GHC Commits: b9b3b007 by Matthew Craven at 2024-04-15T10:57:59-04:00 Add release notes entry for GHC proposal 575 - - - - - 26b6c7fd by Matthew Craven at 2024-04-15T10:59:17-04:00 Users' guide: Fix base-ref links containing symbols - - - - - f15a854e by Alan Zimmerman at 2024-04-21T09:59:45+01:00 EPA: Add additional comments field to AnnsModule This is used in exact printing to store comments coming after the `where` keyword but before any comments allocated to imports or decls. It is used in ghc-exactprint, see https://github.com/alanz/ghc-exactprint/commit/44bbed311fd8f0d053053fef195bf47c17d34fa7 - - - - - c8d25501 by Alan Zimmerman at 2024-04-21T10:41:35+01:00 EPA: Fix comments in mkListSyntaxTy0 Also extend the test to confirm. Addresses #24669, 1 of 4 (cherry picked from commit f07015858fd79dca41983dbf3a249dfecd8d2eea) - - - - - 7d6ae7aa by Alan Zimmerman at 2024-04-21T11:39:48+01:00 EPA: Provide correct span for PatBind And remove unused parameter in checkPatBind Contributes to #24669 (cherry picked from commit c90c60390aa3949b400f26ee0534273c56e19005) - - - - - 64013156 by Alan Zimmerman at 2024-04-21T12:43:22+01:00 EPA: Fix span for PatBuilderAppType Include the location of the prefix @ in the span for InVisPat. Also removes unnecessary annotations from HsTP. Contributes to #24669 (cherry picked from commit 26036f96919b1a8b99715dd99724163012c719fc) - - - - - 898fcbd2 by Alan Zimmerman at 2024-04-21T13:49:41+01:00 EPA: Avoid duplicated comments in splice decls Contributes to #24669 (cherry picked from commit 2f8e3a254a20f4573aec26fc85ab74b51d661472) - - - - - 9f509a09 by Alan Zimmerman at 2024-04-21T15:32:17+01:00 EPA: Extend StringLiteral range to include trailing commas This goes slightly against the exact printing philosophy where trailing decorations should be in an annotation, but the practicalities of adding it to the WarningTxt environment, and the problems caused by deviating do not make a more principles approach worthwhile. (cherry picked from commit 00d3ecf0775c1a3f1ab8495e5e125f21d450394e) - - - - - 45cc3064 by Ben Gamari at 2024-04-24T11:00:59-04:00 Merge remote-tracking branch 'origin/wip/az/ghc-9.10-backports-1' into HEAD - - - - - d9cd4bde by Ben Gamari at 2024-04-24T11:01:34-04:00 ghc-internal: Fix mentions of ghc-internal in deprecation warnings Closes #24609. (cherry picked from commit 55eb8c98895308d2dd025f7bd64c0b80fce6ace3) - - - - - b8f9880c by Zubin Duggal at 2024-04-24T11:01:34-04:00 driver: Make `checkHomeUnitsClosed` faster The implementation of `checkHomeUnitsClosed` was traversing every single path in the unit dependency graph - this grows exponentially and quickly grows to be infeasible on larger unit dependency graphs. Instead we replace this with a faster implementation which follows from the specificiation of the closure property - there is a closure error if there are units which are both are both (transitively) depended upon by home units and (transitively) depend on home units, but are not themselves home units. To compute the set of units required for closure, we first compute the closure of the unit dependency graph, then the transpose of this closure, and find all units that are reachable from the home units in the transpose of the closure. (cherry picked from commit a933aff37992ea311a60be878379e7abf650e9fb) - - - - - 6d6c2640 by Ben Gamari at 2024-04-24T11:01:37-04:00 template-haskell: Declare TH.Lib.Internal as not-home Rather than `hide`. Closes #24659. (cherry picked from commit d7a3d6b5ee5e0c16af295579da3c54d8f0c37a05) - - - - - 88e31848 by Teo Camarasu at 2024-04-24T11:01:37-04:00 Fix ghc API link in docs/index.html This was missing part of the unit ID meaning it would 404. Resolves #24674 (cherry picked from commit f30e4984fb048818051465698ef8e4e20dacb577) - - - - - 1261ec2f by Simon Peyton Jones at 2024-04-24T11:01:37-04:00 Clone CoVars in CorePrep This MR addresses #24463. It's all explained in the new Note [Cloning CoVars and TyVars] (cherry picked from commit 9d38bfa0c0f910208822579acaa999f87c2f8c65) - - - - - bcb5a91d by Jade at 2024-04-24T11:06:13-04:00 Put the newline after errors instead of before them This mainly has consequences for GHCi but also slightly alters how the output of GHC on the commandline looks. Fixes: #22499 (cherry picked from commit 275e41a902f4aec8552707ec9924f2d0a20346d0) - - - - - be59c02c by Ben Gamari at 2024-04-25T12:51:45-04:00 Bump Cabal submodule to 3.12 - - - - - 5f4848c0 by Cheng Shao at 2024-04-25T12:54:20-04:00 ghc-bignum: remove obsolete ln script This commit removes an obsolete ln script in ghc-bignum/gmp. See 060251c24ad160264ae8553efecbb8bed2f06360 for its original intention, but it's been obsolete for a long time, especially since the removal of the make build system. Hence the house cleaning. (cherry picked from commit c62dc317c21026396a7a5581b90d17ef4c44f9ac) - - - - - f845a792 by Cheng Shao at 2024-04-25T12:54:22-04:00 ghc-bignum: update gmp to 6.3.0 This patch bumps the gmp-tarballs submodule and updates gmp to 6.3.0. The tarball format is now xz, and gmpsrc.patch has been patched into the tarball so hadrian no longer needs to deal with patching logic when building in-tree GMP. (cherry picked from commit 6399d52ba10d510a94c9db6552a4ea8aae8e003b) - - - - - 92065500 by Cheng Shao at 2024-04-25T12:54:23-04:00 hadrian: remove obsolete Patch logic This commit removes obsolete Patch logic from hadrian, given we no longer need to patch the gmp tarball when building in-tree GMP. (cherry picked from commit 65b4b92fa1e1989d055108a6077cc9119ee28acd) - - - - - 1e77ded1 by Cheng Shao at 2024-04-25T12:54:24-04:00 autoconf: remove obsolete patch detection This commit removes obsolete deletection logic of the patch command from autoconf scripts, given we no longer need to patch anything in the GHC build process. (cherry picked from commit 71f28958454872db9c21c7d974dd0f0a7c7e8f3d) - - - - - bb67e8d5 by Sylvain Henry at 2024-04-25T12:56:03-04:00 JS: correctly handle RUBBISH literals (#24664) (cherry picked from commit daeda83478d5b800d29661408dd67cc4b23df374) - - - - - 57b07e02 by Ben Gamari at 2024-04-26T09:26:51-04:00 docs: Don't use str.isascii `str.isascii` is only supported in Python 3.7 and later. - - - - - 2c6375b9 by Hécate Moonlight at 2024-05-01T01:44:10+02:00 Add missing entries in the base-4.20 release notes - - - - - b8c66bf3 by Rodrigo Mesquita at 2024-05-08T02:08:37-04:00 bindist: Fix xattr cleaning The original fix (725343aa) was incorrect because it used the shell bracket syntax which is the quoting syntax in autoconf, making the test for existence be incorrect and therefore `xattr` was never run. Fixes #24554 (cherry picked from commit e03760db6713068ad8ba953d2252ec12b3278c9b) - - - - - 250c5df7 by Ben Gamari at 2024-05-08T02:08:37-04:00 ghcup-metadata: Drop output_name field This is entirely redundant to the filename of the URL. There is no compelling reason to name the downloaded file differently from its source. - - - - - 7b327164 by Alan Zimmerman at 2024-05-08T02:08:37-04:00 EPA: check-exact: check that the roundtrip reproduces the source Closes #24670 (cherry picked from commit 981c2c2c5017cb7ae47babff4d2163324d7cbde6) - - - - - a8c27c7c by Alan Zimmerman at 2024-05-08T02:09:14-04:00 EPA: Preserve comments in Match Pats Closes #24708 Closes #24715 Closes #24734 (cherry picked from commit 1c2fd963d6fd78d1c752a21348c7db85f5d64df2) - - - - - e8603c75 by Alan Zimmerman at 2024-05-08T02:09:27-04:00 EPA: Preserve comments for PrefixCon Preserve comments in fun (Con {- c1 -} a b) = undefined Closes #24736 (cherry picked from commit 40026ac30fcdbe84a551f445f5e20691c0527ded) - - - - - 015a0430 by Alan Zimmerman at 2024-05-08T02:09:27-04:00 EPA: fix span for empty \case(s) In instance SDecide Nat where SZero %~ (SSucc _) = Disproved (\case) Ensure the span for the HsLam covers the full construct. Closes #24748 (cherry picked from commit 167a56a003106ed84742e3970cc2189ffb98b0c7) - - - - - c5a65a7f by Alan Zimmerman at 2024-05-08T02:09:27-04:00 EPA: preserve comments in class and data decls Fix checkTyClHdr which was discarding comments. Closes #24755 (cherry picked from commit 35d34fde62cd9e0002ac42f10bf705552f5c654e) - - - - - 43a7dc68 by Alan Zimmerman at 2024-05-08T02:09:27-04:00 EPA: fix mkHsOpTyPV duplicating comments Closes #24753 (cherry picked from commit 18f4ff84b323236f6dfd07f3bbc2842308a01e91) - - - - - 01eeecec by Alan Zimmerman at 2024-05-08T02:09:27-04:00 EPA: preserve comments in data decls Closes #24771 (cherry picked from commit 46328a49d988143111ab530d7907b9426b58311a) - - - - - 2c7a0cf7 by Simon Peyton Jones at 2024-05-08T02:09:27-04:00 Track in-scope variables in ruleCheckProgram This small patch fixes #24726, by tracking in-scope variables properly in -drule-check. Not hard to do! (cherry picked from commit be1e60eec0ec37da41643af17d78c698ab2a7083) - - - - - 4896c50b by Andrew Lelechenko at 2024-05-08T02:09:27-04:00 Document that setEnv is not thread-safe (cherry picked from commit a86167471a7a471fb75ae9ba6c641bd1e74bc16d) - - - - - 843f95b1 by Matthew Pickering at 2024-05-08T02:09:27-04:00 Don't depend on registerPackage function in Cabal More recent versions of Cabal modify the behaviour of libAbiHash which breaks our usage of registerPackage. It is simpler to inline the part of registerPackage that we need and avoid any additional dependency and complication using the higher-level function introduces. (cherry picked from commit 3fff09779d5830549ae455a15907b7bb9fe7859a) - - - - - 720ff1f9 by Hécate Moonlight at 2024-05-08T02:09:27-04:00 Correct `@since` metadata in HpcFlags It was introduced in base-4.20, not 4.22. Fix #24721 (cherry picked from commit 9213478931b18402998c18f5c4e6f0ee09054b18) - - - - - 7f9b05a8 by Teo Camarasu at 2024-05-08T02:09:27-04:00 doc: Fix type error in hs_try_putmvar example (cherry picked from commit 06f7db4001e4eee0f3076d949876f8f4af0eb6fb) - - - - - d5f45368 by Cheng Shao at 2024-05-08T09:39:29+01:00 driver: always merge objects when possible This patch makes the driver always merge objects with `ld -r` when possible, and only fall back to calling `ar -L` when merge objects command is unavailable. This completely reverts !8887 and !12313, given more fixes in Cabal seems to be needed to avoid breaking certain configurations and the maintainence cost is exceeding the behefits in this case :/ (cherry picked from commit 631cefec222e2db951c58db0b15a8d80ef5549cb) - - - - - 255f44e7 by Alan Zimmerman at 2024-05-08T20:07:57+01:00 EPA: Fix range for GADT decl with sig only Closes #24714 (cherry picked from commit d5bea4d6bce785b1d09f1b8faad7451af23b728d) - - - - - ea1bca98 by Alan Zimmerman at 2024-05-08T20:36:04+01:00 EPA: Preserve comments for pattern synonym sig Closes #24749 (cherry picked from commit bf3d4db0894233ec72f092a4a34bce9ed4ff4e21) - - - - - 2cb0fb44 by Alan Zimmerman at 2024-05-08T20:36:33+01:00 EPA: Widen stmtslist to include last semicolon Closes #24754 (cherry picked from commit 7eab4e019205cfced90f06242a9afa23dfcaa70b) - - - - - 776fa6e1 by Alan Zimmerman at 2024-05-08T20:49:33+01:00 EPA: Keep comments in a CaseAlt match The comments now live in the surrounding location, not inside the Match. Make sure we keep them. Closes #24707 (cherry picked from commit e916fc9215e66b15c7e2387cc087a9d1cc57bf77) - - - - - c192d254 by Ben Gamari at 2024-05-09T11:49:25-04:00 Revert "ghcup-metadata: Drop output_name field" This reverts commit 250c5df7875658f172804f511cd7eb325392f347. - - - - - 923e21bc by Ben Gamari at 2024-05-09T11:49:26-04:00 ghcup-metadata: Drop output_name This is entirely redundant to the filename of the URL. There is no compelling reason to name the downloaded file differently from its source. - - - - - 78092043 by Ryan Scott at 2024-05-09T11:49:26-04:00 unboxedSum{Type,Data}Name: Use GHC.Types as the module Unboxed sum constructors are now defined in the `GHC.Types` module, so if you manually quote an unboxed sum (e.g., `''Sum2#`), you will get a `Name` like: ```hs GHC.Types.Sum2# ``` The `unboxedSumTypeName` function in `template-haskell`, however, mistakenly believes that unboxed sum constructors are defined in `GHC.Prim`, so `unboxedSumTypeName 2` would return an entirely different `Name`: ```hs GHC.Prim.(#|#) ``` This is a problem for Template Haskell users, as it means that they can't be sure which `Name` is the correct one. (Similarly for `unboxedSumDataName`.) This patch fixes the implementations of `unboxedSum{Type,Data}Name` to use `GHC.Types` as the module. For consistency with `unboxedTupleTypeName`, the `unboxedSumTypeName` function now uses the non-punned syntax for unboxed sums (`Sum<N>#`) as the `OccName`. Fixes #24750. - - - - - 2cc6968a by Andrei Borzenkov at 2024-05-09T11:51:06-04:00 Fix tuple puns renaming (24702) Move tuple renaming short cutter from `isBuiltInOcc_maybe` to `isPunOcc_maybe`, so we consider incoming module. I also fixed some hidden bugs that raised after the change was done. (cherry picked from commit 94da936507c685aa8101a714e7619b4d428d0187) - - - - - 017c52b7 by Ben Gamari at 2024-05-09T18:39:46-04:00 Bump version to 9.10.1 - - - - - d07219d8 by Ben Gamari at 2024-05-09T22:52:06-04:00 generate_bootstrap_plans: Update - - - - - 6d779c0f by Ben Gamari at 2024-05-10T00:36:54-04:00 base: Fix release date in changelog - - - - - 0d2160de by Ben Gamari at 2024-05-13T11:54:20-04:00 releng/uploads: .gz files are release artifacts - - - - - b63f7ba0 by Ben Gamari at 2024-05-23T17:33:27-04:00 base: Fix changelog reference to setBacktraceMechanismState - - - - - 6ccd1c03 by Ben Gamari at 2024-05-23T17:33:27-04:00 ghcup-metadata: update to reflect upstream preferences - - - - - a5325ded by Ben Gamari at 2024-05-23T17:33:27-04:00 Bump haddock version Somehow the submodule bump which performed the version increment of `haddock` and friends in was lost in the pre-release shuffle. Fix this. Closes #24827. - - - - - 559e73fb by Ben Gamari at 2024-05-28T09:37:46-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - e6b940c3 by Ben Gamari at 2024-05-28T14:31:42-04:00 Bump haddock submodule with fix to #24853 It appears that this reversion was not merged to ghc-9.10, again breaking quick-jump in `base`'s Haddocks. Also bump version to 2.31 Fixes #24853. - - - - - c453ac59 by Ben Gamari at 2024-05-29T07:28:32-04:00 base: Bump version We are bumping the version by a patch-level to upload to Hackage to fix Haddock issues with the 9.10 release. See #24875. - - - - - 1b157ab3 by Ben Gamari at 2024-05-29T10:41:50-04:00 testsuite: Normalize version of base in T19847a - - - - - 2fe96b6e by Zubin Duggal at 2024-05-30T18:06:57+05:30 Bump haddock submodule to fix #24907 - - - - - 0c301d33 by Zubin Duggal at 2024-05-31T13:01:18+05:30 Bump haddock submodule to fix #24912 - - - - - 934a8bb9 by Zubin Duggal at 2024-05-31T13:01:18+05:30 base: Add changelog entry for 4.20.0.1 - - - - - c99aea68 by Moritz Angermann at 2024-06-10T13:40:05+00:00 Add RV64 backend - - - - - 6fb8713e by Moritz Angermann at 2024-06-10T13:40:05+00:00 Add RV64 notes - - - - - a3e621b4 by Moritz Angermann at 2024-06-10T13:40:05+00:00 Fixup Rebase mistake - - - - - 54fa33e3 by Sven Tennie at 2024-06-10T13:40:05+00:00 Remove TAB character The whitespace linter doesn't like it. - - - - - f2ab5fc9 by Sven Tennie at 2024-06-10T13:40:05+00:00 Fix compiler warning about importing GHC.Utils.Panic.Plain in CodeGen.Platform.h - - - - - bc731d6a by Sven Tennie at 2024-06-10T13:40:05+00:00 Pretty-print registers by their alias names The alias name is easier to memorize and simplifies reasoning about what's going on. - - - - - e931b9a6 by Sven Tennie at 2024-06-10T13:40:05+00:00 Fix getAmode: Only signed 12bit immediates The symptom to find this was a too big immediate in a LW instruction in test arr020: Error: illegal operands `lw t0,4016(t0)' - - - - - a1ae283c by Ben Gamari at 2024-06-10T13:40:05+00:00 testsuite/driver: Add basic support for testing cross-compilers - - - - - f6e582cf by Sven Tennie at 2024-06-10T13:40:05+00:00 Add OR and ORI instructions ORR doesn't exist on RISCV. OR with register load is used when the immediate is too big for ORI (i.e. >12bits.) - - - - - 847fe8a2 by Sven Tennie at 2024-06-10T13:40:05+00:00 Refine TODO comment: Stack frame header size is 2 * 8 byte The stack frame header should contain two registers: ra and previous fp - - - - - 52f6ff5a by Sven Tennie at 2024-06-10T13:40:05+00:00 Fix MOV with immediate There are three cases: - Fits in a 12bit immediate slot -> ADDI - Fits in 32bit -> %hi / %lo piecewise loading - Else: Let the assembler solve this issue for now, LI - - - - - 5dcf9960 by Sven Tennie at 2024-06-10T13:40:05+00:00 Add DIV and REM REM calculates the remainder and replaces the more complex logic copied from AARCH64. - - - - - 9f82ee62 by Sven Tennie at 2024-06-10T13:40:05+00:00 Fix: LDRB -> LB, LDRH -> LH A simple translation of these instructions from ARM to RISCV. Add panic-ing pattern matches to fetch the outstanding STR and LDR cases. - - - - - 0d8b8195 by Sven Tennie at 2024-06-10T13:40:05+00:00 Implement MO_S_Shr and truncateReg These store and load on the stack to move values in changed widths into registers. - - - - - 21c3d4b3 by Sven Tennie at 2024-06-10T13:40:05+00:00 CmmInt 0 should refer to zero register A constant 0 can always be taken from the zero register. - - - - - 09fe423e by Sven Tennie at 2024-06-10T13:40:06+00:00 Fix signed shift right This includes overhauling the sign extension and width truncation logic. - - - - - 2561b085 by Sven Tennie at 2024-06-10T13:40:06+00:00 Replace SXTH & SXTB Both do not exist on RISCV64. While touching the sign extension code, also fix the integer calling convention in this sense and update the sign extension note. - - - - - 34cfb757 by Sven Tennie at 2024-06-10T13:40:06+00:00 Allow truncation to from smaller to larger Width This is used as inverse of sign extension to 64bit at many places. - - - - - f026aeba by Sven Tennie at 2024-06-10T13:40:06+00:00 Implement MO_NOT: Replace MVN MVN does not exist in RV64. Replace it by pseudo-instr not's effective assembly. - - - - - 6e31a23c by Sven Tennie at 2024-06-10T13:40:06+00:00 Replace UXTB & UXTH, Fix UDIV Replace UXTB and UXTB with truncateReg as these instructions do not exist in RISCV64. UDIV is named DIVU in RISCV64. - - - - - 3bb11e53 by Sven Tennie at 2024-06-10T13:40:06+00:00 Implement XOR Delete EOR which does not exist on RISCV64. - - - - - ec82d581 by Sven Tennie at 2024-06-10T13:40:06+00:00 Rename UDIV -> DIVU That's how unsigned div is called on RISCV64. This should avoid confusion. - - - - - dbce457f by Sven Tennie at 2024-06-10T13:40:06+00:00 Delete unused EON It does not exist on RISCV64. - - - - - 84a4fd9f by Sven Tennie at 2024-06-10T13:40:06+00:00 WIP: MO_S_MulMayOflo - - - - - 576f2194 by Moritz Angermann at 2024-06-10T13:40:06+00:00 float: first stab at supporting float ins - - - - - 3c9c8cfb by Sven Tennie at 2024-06-10T13:40:06+00:00 Fix & test MulMayOflo - - - - - b58e31ff by Sven Tennie at 2024-06-10T13:40:06+00:00 Cleanup the MulMayOflo story - - - - - a90c3797 by Sven Tennie at 2024-06-10T13:40:06+00:00 Implement MO_ReadBarrier and MO_WriteBarrier The levels are taken from SMP.h write_barrier() and load_load_barrier(). - - - - - 374a9b7d by Sven Tennie at 2024-06-10T13:40:06+00:00 Implement MO_AtomicRead and MO_AtomicWrite - - - - - 5f8a7fe8 by Sven Tennie at 2024-06-10T13:40:06+00:00 Implement register -> stack spilling - - - - - ddd050d1 by Sven Tennie at 2024-06-10T13:40:06+00:00 Add free reg counts for trivColorable - - - - - 898c6fc0 by Sven Tennie at 2024-06-10T13:40:06+00:00 Fix immediate operand related guards For most operations, the immediate's boundaries are those of a 12bit integer. - - - - - a12b198c by Sven Tennie at 2024-06-10T13:40:06+00:00 Assign x31 to be IP register And, use it for register spilling. - - - - - 84ba5914 by Sven Tennie at 2024-06-10T13:40:06+00:00 Implement MO_FS_Conv and MO_SF_Conv (integer <-> float conversion) - - - - - 5ff878f4 by Sven Tennie at 2024-06-10T13:40:06+00:00 Fix MO_U_Shr (UBFX does not exist in RISCV ISA) - - - - - ac0aa8a6 by Sven Tennie at 2024-06-10T13:40:06+00:00 Fix (CmmLit (CmmInt w i)) where i doesn't fit in w - - - - - 3668e3d5 by Sven Tennie at 2024-06-10T13:40:06+00:00 Implement MOV for ImmInt immediates These cases were likely just forgotten. - - - - - e472f8d8 by Sven Tennie at 2024-06-10T13:40:06+00:00 Load integers in their positive representation and don't sign extend unsigned values in foreign C calls Otherwise, the sign bits mess up everything! - - - - - b0ff6f91 by Sven Tennie at 2024-06-10T13:40:06+00:00 Just narrow all CmmLit . CmmInt to the expected width There may appear immediates that don't fit the size. Just truncate them with narrowU. Otherwise, some bit operations fail for the highest bit. - - - - - 5bcf8890 by Sven Tennie at 2024-06-10T13:40:06+00:00 Implement MO_UU_Conv Expect zero extended (!) register. If the source Width is smaller or equal to the target Width just move (copy) the value. Otherwise (target Width is smaller), truncate it. We don't need to care about sign-extension, as this mach op is unsigned. - - - - - bb8f93dd by Sven Tennie at 2024-06-10T13:40:06+00:00 CmmLoad: Load sub-words unsigned (no sign-extension) The contract is that each operation should leave sub-words zero-extended. This fixes the test (test-primops): // Failed: // 0::W64 - (~(zext[W32→W64](load[W32](0x8c::W64)))) // ((0 :: bits64) - (~%zx64(bits32[buffer + (140 :: bits64)]))) // 0x8f8e8d8d /= 0xffffffff8f8e8d8d test(bits64 buffer) { bits64 ret; ret = ((0 :: bits64) - (~%zx64(bits32[buffer + (140 :: bits64)]))); return (ret); } - - - - - 56918220 by Sven Tennie at 2024-06-10T13:40:06+00:00 Annotate more instructions - - - - - 40bed354 by Sven Tennie at 2024-06-10T13:40:06+00:00 Truncate after left shift Shifted values may exceed the target Width. - - - - - 8bda632f by Sven Tennie at 2024-06-10T13:40:06+00:00 MO_SS_Conv: Don't give up the highest bit for sign According to this test, reducing the value for the sign is not correct. narrow[W32→W8](sext[W16→W32](load[W16](0x223972::W64))) test ( bits64 buffer ) { bits64 ret; (ret) = prim %popcnt8(%lobits8(%sx32(bits16[buffer + (2242930 :: bits64)]))); return (ret); } 4 /= 5 - - - - - aeb92507 by Sven Tennie at 2024-06-10T13:40:06+00:00 Unsigned remainder (modulo): REMU - - - - - 596be5e6 by Sven Tennie at 2024-06-10T13:40:06+00:00 Fix loading 12bit < imm <= 32bit immediates The prior version sign extended the immediate. - - - - - e37ca908 by Sven Tennie at 2024-06-10T13:40:06+00:00 WIP: Check C calling convention - - - - - db2dc5f7 by Sven Tennie at 2024-06-10T13:40:06+00:00 Fix & test C calling convention (parameters) I think the gist is: Sub-word ints are sign-extended, sub-word words are give as is, because they were truncated before. - - - - - 09ef0698 by Sven Tennie at 2024-06-10T13:40:06+00:00 Truncate C return values to their expected width Otherwise, values that may be too big are floating around. - - - - - d60fa557 by Sven Tennie at 2024-06-10T13:40:06+00:00 Single precision float comparisons - - - - - 828ade68 by Sven Tennie at 2024-06-10T13:40:06+00:00 Float conditional jumps - - - - - 84e10c66 by Sven Tennie at 2024-06-10T13:40:06+00:00 Fix float absolute (fabs) - - - - - 9bdd4da7 by Sven Tennie at 2024-06-10T13:40:06+00:00 Fix float negation - - - - - f0f6418f by Sven Tennie at 2024-06-10T13:40:06+00:00 Fix unsigned float loading - - - - - 8683177f by Sven Tennie at 2024-06-10T13:40:06+00:00 Fix float comparisions - - - - - b4691499 by Sven Tennie at 2024-06-10T13:40:06+00:00 Fix float calling convention (a bit) If fp regs are taken, use go regs instead. - - - - - ea6106bd by Sven Tennie at 2024-06-10T13:40:06+00:00 Add calling conv test for doubles - - - - - d86cadff by Sven Tennie at 2024-06-10T13:40:07+00:00 Fix float -> int conversion (width) - - - - - 4ba84881 by Sven Tennie at 2024-06-10T13:40:07+00:00 MO_FS_Conv: Truncate register after conversion Otherwise, sign-extension bits may stay around. - - - - - 442db0d6 by Sven Tennie at 2024-06-10T13:40:07+00:00 Fix float operation attributes This is its own little hell... - - - - - 687d9340 by Sven Tennie at 2024-06-10T13:40:07+00:00 Fix MO_FF_CONV The instruction needs precision suffixes to be valid. - - - - - 250669e6 by Sven Tennie at 2024-06-10T13:40:07+00:00 Fix wrong fcvt widths - - - - - 29a4c09d by Sven Tennie at 2024-06-10T13:40:07+00:00 Sign-extend branche conditionals W32 -> W64 Otherwise, negative ints are used as positive ints. - - - - - f60612fd by Sven Tennie at 2024-06-10T13:40:07+00:00 Fix float NE: Needed width - - - - - 53a06812 by Sven Tennie at 2024-06-10T13:40:07+00:00 Fix TrivColorable register counts - - - - - 844d3302 by Sven Tennie at 2024-06-10T13:40:07+00:00 Fix MulMayOflo test - - - - - a0759b2f by Sven Tennie at 2024-06-10T13:40:07+00:00 Adjust stackFrameHeaderSize - - - - - 9c8df4fd by Sven Tennie at 2024-06-10T13:40:07+00:00 Delete unnecessary Ppr cases - - - - - f1a7c7d3 by Sven Tennie at 2024-06-10T13:40:07+00:00 Suppress orphan instance warning Similar to other archs, this seems to be the expected place. - - - - - 3f61c22e by Sven Tennie at 2024-06-10T13:40:07+00:00 Delete commented-out code - - - - - 7b198296 by Sven Tennie at 2024-06-10T13:40:07+00:00 Adjust panix message - - - - - a8dab5b7 by Sven Tennie at 2024-06-10T13:40:07+00:00 Add TODOs - - - - - a8e128ac by Sven Tennie at 2024-06-10T13:40:07+00:00 Formatting - - - - - fc8c7389 by Sven Tennie at 2024-06-10T13:40:07+00:00 Eta reduction - - - - - a3820072 by Sven Tennie at 2024-06-10T13:40:07+00:00 Remove unused LANGUAGE pragma - - - - - dbf912ca by Sven Tennie at 2024-06-10T13:40:07+00:00 Syntax cleanup - - - - - 28459d29 by Sven Tennie at 2024-06-10T13:40:07+00:00 Update comments - - - - - cfa5fc07 by Sven Tennie at 2024-06-10T13:40:07+00:00 Remove unused function: toImm - - - - - fa2a5b8f by Sven Tennie at 2024-06-10T13:40:07+00:00 Remove unused function: withTempIntReg - - - - - d937acbe by Sven Tennie at 2024-06-10T13:40:07+00:00 Remove doubled comment - - - - - 960f4fec by Sven Tennie at 2024-06-10T13:40:07+00:00 Refactor ss_conv to mute incomplete-pattern-match warning - - - - - 0e1d450a by Sven Tennie at 2024-06-10T13:40:07+00:00 Advertise code-gen capability in Hadrian - - - - - 31e52f3c by Sven Tennie at 2024-06-10T13:40:07+00:00 Define DWARF regs - - - - - 8d096129 by Sven Tennie at 2024-06-10T13:40:07+00:00 Reduce duplication in conditionals All non-W64 width had the same code. - - - - - 641771ab by Sven Tennie at 2024-06-10T13:40:07+00:00 Add TODOS - - - - - 7a83c486 by Sven Tennie at 2024-06-10T13:40:07+00:00 Far branches - - - - - 3393c122 by Sven Tennie at 2024-06-10T13:40:07+00:00 Far unconditional jumps / branches Introduce B_FAR. - - - - - 539410e3 by Sven Tennie at 2024-06-10T13:40:07+00:00 Fix DWARF labels Some were missing... - - - - - 5b741a33 by Sven Tennie at 2024-06-10T13:40:07+00:00 Add TODOs - - - - - 2321bc03 by Sven Tennie at 2024-06-10T13:40:07+00:00 Cleanup makeFarBranches - - - - - c2bb0ca7 by Sven Tennie at 2024-06-10T13:40:07+00:00 WIP: Add GHC Linker This is likely not correct, yet. - - - - - 5e57df13 by Sven Tennie at 2024-06-10T13:40:07+00:00 Runtime linker LLVM style - - - - - 3a86cd38 by Sven Tennie at 2024-06-10T13:40:07+00:00 Linker: Delete invalid check - - - - - bc3ad1aa by Sven Tennie at 2024-06-10T13:40:07+00:00 Linker: Add missing cases - - - - - aaf6a879 by Sven Tennie at 2024-06-10T13:40:07+00:00 Linker: Trace int size issue - - - - - c9cd0a82 by Sven Tennie at 2024-06-10T13:40:07+00:00 Linker: warnings - - - - - 120cfe19 by Sven Tennie at 2024-06-10T13:40:07+00:00 Linker: Add missing relocation - - - - - 015e3443 by Sven Tennie at 2024-06-10T13:40:07+00:00 Linker: Missing break statement - - - - - 15637126 by Sven Tennie at 2024-06-10T13:40:08+00:00 Add missing relocation - - - - - af793f5b by Sven Tennie at 2024-06-10T13:40:08+00:00 Add R_RISCV_JAL encoding - - - - - c40060d6 by Sven Tennie at 2024-06-10T13:40:08+00:00 Linker: Cleanup relocations, Add missing - - - - - fecc49a0 by Sven Tennie at 2024-06-10T13:40:08+00:00 Linker: Fix R_RISCV_SET8 - - - - - 11e2eff3 by Sven Tennie at 2024-06-10T13:40:08+00:00 Linker: Fix U-Type assertion Instructions are 32 bits wide in RISCV(64). - - - - - d3b08cc1 by Sven Tennie at 2024-06-10T13:40:08+00:00 Linker: Delete unused variable - - - - - 281a6b31 by Sven Tennie at 2024-06-10T13:40:08+00:00 Linker: Fix PLT jumps - - - - - 22125ec7 by Sven Tennie at 2024-06-10T13:40:08+00:00 Linker: Belch only when asked - - - - - 6e368605 by Sven Tennie at 2024-06-10T13:40:08+00:00 linker: More fixing - - - - - c464b1dd by Sven Tennie at 2024-06-10T13:40:08+00:00 Linker: Add local labels to the GOT - - - - - dae860d3 by Sven Tennie at 2024-06-10T13:40:08+00:00 Linker: uint32_t addend This seems to be a good representation: - We're dealing with negative values as well (e.g. negative PC offset) - We cannot deal with more than 20 + 12 = 32 bits - - - - - b9aef261 by Sven Tennie at 2024-06-10T13:40:08+00:00 Linker: Rework debug traces - - - - - 6a85de65 by Sven Tennie at 2024-06-10T13:40:08+00:00 Ensure __clzdi2 builtin is around - - - - - 04a85878 by Sven Tennie at 2024-06-10T13:40:08+00:00 Add symbol prototype for __ctzdi2 - - - - - 00f47c8d by Sven Tennie at 2024-06-10T13:40:08+00:00 Add comment - - - - - 30679fa8 by Sven Tennie at 2024-06-10T13:40:08+00:00 Only trace message on flag - - - - - c4a0748d by Sven Tennie at 2024-06-10T13:40:08+00:00 Check int size on 32 bit width We're handing around 32bit integers. - - - - - da63cd99 by Sven Tennie at 2024-06-10T13:40:08+00:00 Linker: Use SymbolExtras for GOT relative relocations to local symbols This is (hopefully!) faster than emitting real GOT entries for all local labels (which was implemented before.) - - - - - 9a84ff17 by Sven Tennie at 2024-06-10T13:40:08+00:00 Linker: Optimize lookup of dependent relocation Always iteration over everything was a real performance issue. Now, start with the second relocation and go back to the first one. Expect it in the same section. - - - - - 66e7ad23 by Sven Tennie at 2024-06-10T13:40:08+00:00 Beauify allMachRegNos - - - - - fe278d67 by Sven Tennie at 2024-06-10T13:40:08+00:00 Delete unused function strImmLit - - - - - a337e9c5 by Sven Tennie at 2024-06-10T13:40:08+00:00 Introduce constant firstFpRegNo Makes usages more readable. - - - - - 73b8a7fb by Sven Tennie at 2024-06-10T13:40:08+00:00 Add TODOs - - - - - 83851509 by Sven Tennie at 2024-06-10T13:40:08+00:00 Cleanup register constants - - - - - 5cc53f8e by Sven Tennie at 2024-06-10T13:40:08+00:00 Make reg numbers less magic - - - - - 66dac7fc by Sven Tennie at 2024-06-10T13:40:08+00:00 More on RegNo - - - - - d8758f0d by Sven Tennie at 2024-06-10T13:40:08+00:00 Improve comment - - - - - b9305f3b by Sven Tennie at 2024-06-10T13:40:08+00:00 Remove unused / non-existent addressing mode - - - - - 0359dd88 by Sven Tennie at 2024-06-10T13:40:08+00:00 Reformat / cleanup - - - - - 22cf3a9c by Sven Tennie at 2024-06-10T13:40:08+00:00 Add TODOs - - - - - f743d4ce by Sven Tennie at 2024-06-10T13:40:08+00:00 More on RegNos - - - - - f0920d2e by Sven Tennie at 2024-06-10T13:40:08+00:00 Trim trailing whitespace - - - - - 194a42c8 by Sven Tennie at 2024-06-10T13:40:08+00:00 No sign extension attribute in RISCV instructions RISCV takes the meaning of reduced instruction set much more serious: One cannot sign extend an operant in the same instruction. Delete this unused code - We're handling sign extension differently. - - - - - d556fc68 by Sven Tennie at 2024-06-10T13:40:08+00:00 There are no shifts in RISCV instructions Remove this unused code. RISCV does everything in small steps... - - - - - 14f18e06 by Sven Tennie at 2024-06-10T13:40:08+00:00 pprReg: Remove unused parameter - - - - - 10754464 by Sven Tennie at 2024-06-10T13:40:08+00:00 Cleanup Cond - - - - - 65df2ce8 by Sven Tennie at 2024-06-10T13:40:08+00:00 More cleanup Mostly haddock, formatting, minor refactorings - - - - - dfb40f6e by Sven Tennie at 2024-06-10T13:40:08+00:00 Implement takeRegRegMoveInstr - - - - - a3a4f4df by Sven Tennie at 2024-06-10T13:40:08+00:00 Cleanup mkStackAllocInstr & mkStackDeallocInstr - - - - - 4ea4eacd by Sven Tennie at 2024-06-10T13:40:08+00:00 Move Reg definitions to Regs module - - - - - 9169aacb by Sven Tennie at 2024-06-10T13:40:08+00:00 Typo - - - - - 89e19ff6 by Sven Tennie at 2024-06-10T13:40:08+00:00 Circumvent "incomplete pattern match" warning - - - - - ee6c1f29 by Sven Tennie at 2024-06-10T13:40:08+00:00 Delete commented out / dead code - - - - - b89e5f37 by Sven Tennie at 2024-06-10T13:40:08+00:00 Add TODOs - - - - - ab226689 by Sven Tennie at 2024-06-10T13:40:08+00:00 Reduce duplication in stack alloc / free - - - - - 8240722f by Sven Tennie at 2024-06-10T13:40:09+00:00 Delete unused instructions As they are unused, we don't even know if using them would work at all. - - - - - a65bbb91 by Sven Tennie at 2024-06-10T13:40:09+00:00 Lint - - - - - 7f3d593a by Sven Tennie at 2024-06-10T13:40:09+00:00 Fix odd register move reduction Probably, there're OpRegs with wrong format around. - - - - - 43c62192 by Sven Tennie at 2024-06-10T13:40:09+00:00 Re-implement takeRegRegMoveInstr - - - - - d9bb9186 by Sven Tennie at 2024-06-10T13:40:09+00:00 Implement switch (case) jump tables - - - - - 808f411e by Sven Tennie at 2024-06-10T13:40:09+00:00 adjustor: Fence for generated code - - - - - 12f34c40 by Sven Tennie at 2024-06-10T13:40:09+00:00 Skip divbyzero test (like most archs) - - - - - 3fb2fe86 by Sven Tennie at 2024-06-10T13:40:09+00:00 More instruction cache flushing Flush in the Linker, which creates code in the PLT. And, cleanup the link code by using built-ins instead of inline assembly. - - - - - 37bf4573 by Sven Tennie at 2024-06-10T13:40:09+00:00 Add todos - - - - - 4d7f3054 by Sven Tennie at 2024-06-10T13:40:09+00:00 Cleanup Delete dead code, useless/obsolete comments ... - - - - - 986dcae6 by Sven Tennie at 2024-06-10T13:40:09+00:00 Remove unused constructors Aarch64 and RISCV64 are just too different... - - - - - 7e231cd0 by Sven Tennie at 2024-06-10T13:40:09+00:00 Remove more dead code - - - - - 2e457c69 by Sven Tennie at 2024-06-10T13:40:09+00:00 Replace duplicated source Note by reference - - - - - beb267c5 by Sven Tennie at 2024-06-10T13:40:09+00:00 Delete commented out code - - - - - 6f567ed9 by Sven Tennie at 2024-06-10T13:40:09+00:00 TLabel was unused / unsupported - - - - - f6b4f8d5 by Sven Tennie at 2024-06-10T13:40:09+00:00 Cleanup immediate pretty printing - - - - - 758bbc7e by Sven Tennie at 2024-06-10T13:40:09+00:00 Cleanup C calling conv code - - - - - d2869385 by Sven Tennie at 2024-06-10T13:40:09+00:00 Fix invalid Haddock - - - - - 1e984da1 by Sven Tennie at 2024-06-10T13:40:09+00:00 Fix linker issue Local symbols don't get GOT entries. Fake them with extra symbols instead. Such that R_RISCV_CALL_PLT has an address to load and jump to. - - - - - 22b3c5ac by Sven Tennie at 2024-06-10T13:40:09+00:00 Add missing relocation to name (string) mapping - - - - - 6c8cc7d6 by Sven Tennie at 2024-06-10T13:40:09+00:00 Increase Clang happiness Otherwise, it newer versions refuse to build. - - - - - 917898e7 by Sven Tennie at 2024-06-10T13:40:09+00:00 Implement -falignment-sanitisation - - - - - 81105374 by Sven Tennie at 2024-06-10T13:40:09+00:00 Ensure there's always a well defined skip label (far branches) Just th be sure, we don't accidentally land somewhere unexpected. - - - - - 51497c5a by Sven Tennie at 2024-06-10T13:40:09+00:00 Move alignment check - - - - - 7fc1a7ab by Sven Tennie at 2024-06-10T13:40:09+00:00 Add TODO (reminder) about fences - - - - - 904d0074 by Sven Tennie at 2024-06-10T13:40:09+00:00 Fix type of makeFarBranches It changed during releases - - - - - a84c4c68 by Sven Tennie at 2024-06-10T13:40:09+00:00 Fix MulMayOflo test A merge/rebase issue... - - - - - 5202c002 by Sven Tennie at 2024-06-10T13:40:09+00:00 GHC 9.10 rebasing FIXUP - - - - - f569612d by Sven Tennie at 2024-06-10T13:40:09+00:00 Add fused multiplication/addition (FMA) - - - - - 58a1d506 by Sven Tennie at 2024-06-10T13:40:09+00:00 Increase C compiler happiness New warnings (-Werror) prevented the validate flavour from being built. - - - - - 782cdda1 by Sven Tennie at 2024-06-10T13:40:09+00:00 Ignore signedness for MO_XX_Conv MO_XX_Conv is used on (unsigned) words, too. Interpreting them as signed may lead to weird conversions / sign-extensions: E.g. on RISCV64 this conversion happened for a Word64#: %MO_XX_Conv_W32_W64(4294967293 :: W32) -> CmmLit (CmmInt (-3) W64) - - - - - 14 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitlab/rel_eng/upload.sh - compiler/CodeGen.Platform.h - compiler/GHC/Builtin/Types.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Dwarf/Constants.hs - compiler/GHC/CmmToAsm/PIC.hs - + compiler/GHC/CmmToAsm/RV64-notes.md - + compiler/GHC/CmmToAsm/RV64.hs - + compiler/GHC/CmmToAsm/RV64/CodeGen.hs - + compiler/GHC/CmmToAsm/RV64/Cond.hs - + compiler/GHC/CmmToAsm/RV64/Instr.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5d82e90884a61740476d00bbf000a8d31143c37f...782cdda1edd69138635b29d0108d8bc42d8ee6a7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5d82e90884a61740476d00bbf000a8d31143c37f...782cdda1edd69138635b29d0108d8bc42d8ee6a7 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 13:49:02 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Mon, 10 Jun 2024 09:49:02 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/t24974 Message-ID: <6667044e3b513_151ed31c346e0132221@gitlab.mail> Matthew Pickering pushed new branch wip/t24974 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/t24974 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 14:33:41 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 10 Jun 2024 10:33:41 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T24944 Message-ID: <66670ec53e425_151ed324a1fa81592d1@gitlab.mail> Simon Peyton Jones pushed new branch wip/T24944 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T24944 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 15:04:29 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Mon, 10 Jun 2024 11:04:29 -0400 Subject: [Git][ghc/ghc][wip/supersven/ghc-9.10-riscv-ncg] Fix MO_XX_Conv Message-ID: <666715fdb5f3b_151ed32a906441681d2@gitlab.mail> Sven Tennie pushed to branch wip/supersven/ghc-9.10-riscv-ncg at Glasgow Haskell Compiler / GHC Commits: f93e1323 by Sven Tennie at 2024-06-10T15:03:21+00:00 Fix MO_XX_Conv Conversion to smaller Widths are actually a truncation. - - - - - 1 changed file: - compiler/GHC/CmmToAsm/RV64/CodeGen.hs Changes: ===================================== compiler/GHC/CmmToAsm/RV64/CodeGen.hs ===================================== @@ -618,7 +618,14 @@ getRegister' config plat expr = MO_FF_Conv from to -> return $ Any (floatFormat to) (\dst -> code `snocOL` annExpr e (FCVT (OpReg to dst) (OpReg from reg))) -- Conversions + -- TODO: Duplication with MO_UU_Conv + MO_XX_Conv from to | to < from -> pure $ Any (intFormat to) (\dst -> + code `snocOL` + annExpr e (MOV (OpReg from dst) (OpReg from reg)) `appOL` + truncateReg from to dst + ) MO_XX_Conv _from to -> swizzleRegisterRep (intFormat to) <$> getRegister e + MO_AlignmentCheck align wordWidth -> do reg <- getRegister' config plat e addAlignmentCheck align wordWidth reg View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f93e13239e0805213faf64c90672b14576619d35 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f93e13239e0805213faf64c90672b14576619d35 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 16:04:09 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Mon, 10 Jun 2024 12:04:09 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] 2 commits: emit ymm/zmm when appropriate Message-ID: <666723f91e165_151ed3375279c18684a@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 35121e83 by sheaf at 2024-06-10T12:19:37+02:00 emit ymm/zmm when appropriate - - - - - 75ec79c1 by sheaf at 2024-06-10T18:03:15+02:00 fix reg2reg for vectors - - - - - 11 changed files: - compiler/GHC/Cmm/Reg.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs Changes: ===================================== compiler/GHC/Cmm/Reg.hs ===================================== @@ -97,7 +97,7 @@ pprReg :: CmmReg -> SDoc pprReg r = case r of CmmLocal local -> pprLocalReg local - CmmGlobal (GlobalRegUse global _) -> pprGlobalReg global + CmmGlobal (GlobalRegUse global ty) -> pprGlobalReg global <> dcolon <> ppr ty cmmRegType :: CmmReg -> CmmType cmmRegType (CmmLocal reg) = localRegType reg ===================================== compiler/GHC/CmmToAsm/AArch64/Instr.hs ===================================== @@ -433,8 +433,10 @@ isMetaInstr instr -- | Copy the value in a register to another one. -- Must work for all register classes. -mkRegRegMoveInstr :: Reg -> Reg -> Instr -mkRegRegMoveInstr src dst = ANN (text "Reg->Reg Move: " <> ppr src <> text " -> " <> ppr dst) $ MOV (OpReg W64 dst) (OpReg W64 src) +mkRegRegMoveInstr :: Format -> Reg -> Reg -> Instr +mkRegRegMoveInstr _fmt src dst + = ANN (text "Reg->Reg Move: " <> ppr src <> text " -> " <> ppr dst) $ MOV (OpReg W64 dst) (OpReg W64 src) + -- SIMD NCG TODO: incorrect for vector formats -- | Take the source and destination from this reg -> reg move instruction -- or Nothing if it's not one ===================================== compiler/GHC/CmmToAsm/Instr.hs ===================================== @@ -134,6 +134,7 @@ class Instruction instr where -- Must work for all register classes. mkRegRegMoveInstr :: Platform + -> Format -> Reg -- ^ source register -> Reg -- ^ destination register -> instr ===================================== compiler/GHC/CmmToAsm/PPC/Instr.hs ===================================== @@ -664,12 +664,14 @@ isMetaInstr instr -- | Copy the value in a register to another one. -- Must work for all register classes. mkRegRegMoveInstr - :: Reg + :: Format + -> Reg -> Reg -> Instr -mkRegRegMoveInstr src dst +mkRegRegMoveInstr _fmt src dst = MR dst src + -- SIMD NCG TODO: handle vector format -- | Make an unconditional jump instruction. ===================================== compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs ===================================== @@ -161,14 +161,14 @@ cleanForward _ _ _ acc [] cleanForward platform blockId assoc acc (li1 : li2 : instrs) | LiveInstr (SPILL reg1 _ slot1) _ <- li1 - , LiveInstr (RELOAD slot2 reg2 _) _ <- li2 + , LiveInstr (RELOAD slot2 reg2 fmt) _ <- li2 , slot1 == slot2 = do modify $ \s -> s { sCleanedReloadsAcc = sCleanedReloadsAcc s + 1 } cleanForward platform blockId assoc acc - -- SIMD NCG TODO: is mkRegRegMoveInstr here OK for vectors? - $ li1 : LiveInstr (mkRegRegMoveInstr platform reg1 reg2) Nothing + $ li1 : LiveInstr (mkRegRegMoveInstr platform fmt reg1 reg2) Nothing : instrs + -- SIMD NCG TODO: is this "fmt" correct? cleanForward platform blockId assoc acc (li@(LiveInstr i1 _) : instrs) | Just (r1, r2) <- takeRegRegMoveInstr i1 @@ -230,7 +230,7 @@ cleanReload -> LiveInstr instr -> CleanM (Assoc Store, Maybe (LiveInstr instr)) -cleanReload platform blockId assoc li@(LiveInstr (RELOAD slot reg _) _) +cleanReload platform blockId assoc li@(LiveInstr (RELOAD slot reg fmt) _) -- If the reg we're reloading already has the same value as the slot -- then we can erase the instruction outright. @@ -248,7 +248,8 @@ cleanReload platform blockId assoc li@(LiveInstr (RELOAD slot reg _) _) $ assoc return ( assoc' - , Just $ LiveInstr (mkRegRegMoveInstr platform reg2 reg) Nothing) + , Just $ LiveInstr (mkRegRegMoveInstr platform fmt reg2 reg) Nothing) + -- SIMD NCG TODO: is this fmt correct? -- Gotta keep this instr. | otherwise ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -712,7 +712,7 @@ saveClobberedTemps clobbered dying setFreeRegsR (frAllocateReg platform my_reg freeRegs) let new_assign = addToUFM_Directly assig temp (InReg (RealRegUsage my_reg fmt)) - let instr = mkRegRegMoveInstr platform + let instr = mkRegRegMoveInstr platform fmt (RegReal reg) (RegReal my_reg) return (new_assign,(instr : instrs)) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs ===================================== @@ -363,10 +363,9 @@ makeMove delta vreg src dst let platform = ncgPlatform config case (src, dst) of - (InReg (RealRegUsage s _), InReg (RealRegUsage d _)) -> + (InReg (RealRegUsage s _), InReg (RealRegUsage d fmt)) -> do recordSpill (SpillJoinRR vreg) - -- SIMD NCG TODO: does reg-2-reg work for vector registers? - return $ [mkRegRegMoveInstr platform (RegReal s) (RegReal d)] + return $ [mkRegRegMoveInstr platform fmt (RegReal s) (RegReal d)] (InMem s, InReg (RealRegUsage d cls)) -> do recordSpill (SpillJoinRM vreg) return $ mkLoadInstr config (RegReal d) cls delta s ===================================== compiler/GHC/CmmToAsm/Reg/Liveness.hs ===================================== @@ -153,8 +153,8 @@ instance Instruction instr => Instruction (InstrSR instr) where Instr instr -> isMetaInstr instr _ -> False - mkRegRegMoveInstr platform r1 r2 - = Instr (mkRegRegMoveInstr platform r1 r2) + mkRegRegMoveInstr platform fmt r1 r2 + = Instr (mkRegRegMoveInstr platform fmt r1 r2) takeRegRegMoveInstr i = case i of ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1569,6 +1569,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps CmmInt 1 _ -> exp `snocOL` (MOVH format (OpReg r) (OpAddr addr)) `snocOL` (MOV FF64 (OpAddr addr) (OpReg dst)) + -- SIMD NCG TODO: avoid going via the stack here? _ -> panic "Error in offset while unpacking" return (Any format code) vector_float_unpack _ w c e ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -911,17 +911,15 @@ isMetaInstr instr -- | Make a reg-reg move instruction. mkRegRegMoveInstr :: Platform + -> Format -> Reg -> Reg -> Instr -mkRegRegMoveInstr platform src dst - = case targetClassOfReg platform src of - RcInteger -> case platformArch platform of - ArchX86 -> MOV II32 (OpReg src) (OpReg dst) - ArchX86_64 -> MOV II64 (OpReg src) (OpReg dst) - _ -> panic "X86.mkRegRegMoveInstr: Bad arch" - RcFloatOrVector -> MOV FF64 (OpReg src) (OpReg dst) +mkRegRegMoveInstr _platform fmt src dst = + case fmt of + VecFormat {} -> MOVU fmt (OpReg src) (OpReg dst) + _ -> MOV fmt (OpReg src) (OpReg dst) -- | Check whether an instruction represents a reg-reg move. -- The register allocator attempts to eliminate reg->reg moves whenever it can, ===================================== compiler/GHC/CmmToAsm/X86/Ppr.hs ===================================== @@ -301,7 +301,7 @@ pprReg platform f r ppr32_reg_no :: Format -> Int -> doc ppr32_reg_no II8 = ppr32_reg_byte ppr32_reg_no II16 = ppr32_reg_word - ppr32_reg_no _ = ppr32_reg_long + ppr32_reg_no fmt = ppr32_reg_long fmt ppr32_reg_byte i = case i of { @@ -319,20 +319,20 @@ pprReg platform f r _ -> text "very naughty I386 word register" } - ppr32_reg_long i = + ppr32_reg_long fmt i = case i of { 0 -> text "%eax"; 1 -> text "%ebx"; 2 -> text "%ecx"; 3 -> text "%edx"; 4 -> text "%esi"; 5 -> text "%edi"; 6 -> text "%ebp"; 7 -> text "%esp"; - _ -> ppr_reg_float i + _ -> ppr_reg_float fmt i } ppr64_reg_no :: Format -> Int -> doc ppr64_reg_no II8 = ppr64_reg_byte ppr64_reg_no II16 = ppr64_reg_word ppr64_reg_no II32 = ppr64_reg_long - ppr64_reg_no _ = ppr64_reg_quad + ppr64_reg_no fmt = ppr64_reg_quad fmt ppr64_reg_byte i = case i of { @@ -373,7 +373,7 @@ pprReg platform f r _ -> text "very naughty x86_64 register" } - ppr64_reg_quad i = + ppr64_reg_quad fmt i = case i of { 0 -> text "%rax"; 1 -> text "%rbx"; 2 -> text "%rcx"; 3 -> text "%rdx"; @@ -383,11 +383,35 @@ pprReg platform f r 10 -> text "%r10"; 11 -> text "%r11"; 12 -> text "%r12"; 13 -> text "%r13"; 14 -> text "%r14"; 15 -> text "%r15"; - _ -> ppr_reg_float i + _ -> ppr_reg_float fmt i } -ppr_reg_float :: IsLine doc => Int -> doc -ppr_reg_float i = case i of +ppr_reg_float :: IsLine doc => Format -> Int -> doc +ppr_reg_float fmt i + | W256 <- size + = case i of + 16 -> text "%ymm0" ; 17 -> text "%ymm1" + 18 -> text "%ymm2" ; 19 -> text "%ymm3" + 20 -> text "%ymm4" ; 21 -> text "%ymm5" + 22 -> text "%ymm6" ; 23 -> text "%ymm7" + 24 -> text "%ymm8" ; 25 -> text "%ymm9" + 26 -> text "%ymm10"; 27 -> text "%ymm11" + 28 -> text "%ymm12"; 29 -> text "%ymm13" + 30 -> text "%ymm14"; 31 -> text "%ymm15" + _ -> text "very naughty x86 register" + | W512 <- size + = case i of + 16 -> text "%zmm0" ; 17 -> text "%zmm1" + 18 -> text "%zmm2" ; 19 -> text "%zmm3" + 20 -> text "%zmm4" ; 21 -> text "%zmm5" + 22 -> text "%zmm6" ; 23 -> text "%zmm7" + 24 -> text "%zmm8" ; 25 -> text "%zmm9" + 26 -> text "%zmm10"; 27 -> text "%zmm11" + 28 -> text "%zmm12"; 29 -> text "%zmm13" + 30 -> text "%zmm14"; 31 -> text "%zmm15" + _ -> text "very naughty x86 register" + | otherwise + = case i of 16 -> text "%xmm0" ; 17 -> text "%xmm1" 18 -> text "%xmm2" ; 19 -> text "%xmm3" 20 -> text "%xmm4" ; 21 -> text "%xmm5" @@ -397,6 +421,7 @@ ppr_reg_float i = case i of 28 -> text "%xmm12"; 29 -> text "%xmm13" 30 -> text "%xmm14"; 31 -> text "%xmm15" _ -> text "very naughty x86 register" + where size = formatToWidth fmt pprFormat :: IsLine doc => Format -> doc pprFormat x = case x of View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fbd321e81cf7876ebb3ea50d5136fb71b9125932...75ec79c179a2c4999fbff4b7e4baa1d12621d6a2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fbd321e81cf7876ebb3ea50d5136fb71b9125932...75ec79c179a2c4999fbff4b7e4baa1d12621d6a2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 16:09:53 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Mon, 10 Jun 2024 12:09:53 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] WIP: lower vector shuffle instruction on X86 Message-ID: <666725512d3c1_1a8c2105cac8481d@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: be86b5a0 by sheaf at 2024-06-10T18:09:34+02:00 WIP: lower vector shuffle instruction on X86 - - - - - 6 changed files: - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/StgToCmm/Prim.hs - testsuite/tests/codeGen/should_run/all.T Changes: ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1659,12 +1659,75 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps (r2, exp2) <- getSomeReg v2 let fmt = VecFormat l (if w == W32 then FmtFloat else FmtDouble) w code dst - = exp1 `appOL` (exp2 `appOL` shuffleInstructions fmt r1 r2 is dst) --VSHUFPD format imm (OpReg r1) r2) + = exp1 `appOL` (exp2 `appOL` shuffleInstructions fmt r1 r2 is dst) return (Any fmt code) shuffleInstructions :: Format -> Reg -> Reg -> [Int] -> Reg -> OrdList Instr - shuffleInstructions _fmt _v1 _v2 _is _dst = - error "SIMD NCG TODO: lower to shuffle instructions (e.g. VSHUFPD)" + shuffleInstructions fmt v1 v2 is dst = + case fmt of + VecFormat 2 FmtDouble _ -> + case is of + [i1, i2] -> case (i1, i2) of + (i, j) | i == j + -> let v = if i < 2 then v1 else v2 + mov = if i == 0 || i == 2 then MOVL else MOVH + in unitOL (mov fmt (OpReg v) (OpReg dst)) `snocOL` + SHUFPD fmt (ImmInt 0b00) (OpReg dst) dst + (0,1) -> unitOL (MOVU fmt (OpReg v1) (OpReg dst)) + (2,3) -> unitOL (MOVU fmt (OpReg v2) (OpReg dst)) + (1,0) -> unitOL (VSHUFPD fmt (ImmInt 0b01) (OpReg v1) v1 dst) + (3,2) -> unitOL (VSHUFPD fmt (ImmInt 0b01) (OpReg v2) v2 dst) + (0,2) -> unitOL (VSHUFPD fmt (ImmInt 0b00) (OpReg v2) v1 dst) + (2,0) -> unitOL (VSHUFPD fmt (ImmInt 0b00) (OpReg v1) v2 dst) + (0,3) -> unitOL (VSHUFPD fmt (ImmInt 0b10) (OpReg v2) v1 dst) + (3,0) -> unitOL (VSHUFPD fmt (ImmInt 0b10) (OpReg v1) v2 dst) + (1,2) -> unitOL (VSHUFPD fmt (ImmInt 0b01) (OpReg v2) v1 dst) + (2,1) -> unitOL (VSHUFPD fmt (ImmInt 0b01) (OpReg v1) v2 dst) + (1,3) -> unitOL (VSHUFPD fmt (ImmInt 0b11) (OpReg v2) v1 dst) + (3,1) -> unitOL (VSHUFPD fmt (ImmInt 0b11) (OpReg v1) v2 dst) + _ -> pprPanic "vector shuffle: indices out of bounds 0 <= i <= 3" (ppr is) + _ -> pprPanic "vector shuffle: wrong number of indices (expected 2)" (ppr is) + VecFormat 4 FmtFloat _ -> + case is of + -- indices 0 <= i <= 7 + [i1, i2, i3, i4] + | all ( <= 3 ) is + , let imm = i1 + i2 `shiftL` 2 + i3 `shiftL` 4 + i4 `shiftL` 6 + -> unitOL (VSHUFPS fmt (ImmInt imm) (OpReg v1) v1 dst) + | all ( >= 4 ) is + , let [j1, j2, j3, j4] = map ( subtract 4 ) is + imm = j1 + j2 `shiftL` 2 + j3 `shiftL` 4 + j4 `shiftL` 6 + -> unitOL (VSHUFPS fmt (ImmInt imm) (OpReg v2) v2 dst) + | i1 <= 3, i2 <= 3 + , i3 >= 4, i4 >= 4 + , let imm = i1 + i2 `shiftL` 2 + (i3 - 4) `shiftL` 4 + (i4 - 4) `shiftL` 6 + -> unitOL (VSHUFPS fmt (ImmInt imm) (OpReg v1) v2 dst) + | i1 >= 4, i2 >= 4 + , i3 <= 3, i4 <= 3 + , let imm = i3 + i4 `shiftL` 2 + (i1 - 4) `shiftL` 4 + (i2 - 4) `shiftL` 6 + -> unitOL (VSHUFPS fmt (ImmInt imm) (OpReg v2) v1 dst) + | otherwise + -> + -- Fall-back code with 4 INSERTPS operations. + -- SIMD NCG TODO: handle more cases with better lowering. + let -- bits: ss_dd_zzzz + -- ss: pick source location + -- dd: pick destination location + -- zzzz: pick locations to be zeroed + insertImm src dst = shiftL ( src `mod` 4 ) 6 + .|. shiftL dst 4 + vec src = if src >= 4 then v2 else v1 + in unitOL + (INSERTPS fmt (OpImm $ ImmInt $ insertImm i1 0 .|. 0b1110) (OpReg $ vec i1) dst) + `snocOL` + (INSERTPS fmt (OpImm $ ImmInt $ insertImm i2 1) (OpReg $ vec i2) dst) + `snocOL` + (INSERTPS fmt (OpImm $ ImmInt $ insertImm i3 2) (OpReg $ vec i3) dst) + `snocOL` + (INSERTPS fmt (OpImm $ ImmInt $ insertImm i4 3) (OpReg $ vec i4) dst) + _ -> pprPanic "vector shuffle: wrong number of indices (expected 4)" (ppr is) + _ -> + pprPanic "vector shuffle: unsupported format" (ppr fmt) getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps sse4_1 <- sse4_1Enabled ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -378,9 +378,9 @@ data Instr | VPSHUFD Format Imm Operand Reg | PSHUFD Format Imm Operand Reg | SHUFPS Format Imm Operand Reg - | VSHUFPS Format Imm Operand Reg + | VSHUFPS Format Imm Operand Reg Reg | SHUFPD Format Imm Operand Reg - | VSHUFPD Format Imm Operand Reg + | VSHUFPD Format Imm Operand Reg Reg -- SIMD NCG TODO: don't store the Format (or only what we need) -- in order to emit these instructions. @@ -522,10 +522,10 @@ regUsageOfInstr platform instr -> mkRU fmt (use_R src [dst]) [dst] SHUFPS fmt _off src dst -> mkRU fmt (use_R src [dst]) [dst] - VSHUFPD fmt _off src dst - -> mkRU fmt (use_R src [dst]) [dst] - VSHUFPS fmt _off src dst - -> mkRU fmt (use_R src [dst]) [dst] + VSHUFPD fmt _off src1 src2 dst + -> mkRU fmt (use_R src1 [src2]) [dst] + VSHUFPS fmt _off src1 src2 dst + -> mkRU fmt (use_R src1 [src2]) [dst] PSLLDQ fmt off dst -> mkRU fmt (use_R off []) [dst] @@ -729,10 +729,10 @@ patchRegsOfInstr instr env -> SHUFPS fmt off (patchOp src) (env dst) SHUFPD fmt off src dst -> SHUFPD fmt off (patchOp src) (env dst) - VSHUFPS fmt off src dst - -> VSHUFPS fmt off (patchOp src) (env dst) - VSHUFPD fmt off src dst - -> VSHUFPD fmt off (patchOp src) (env dst) + VSHUFPS fmt off src1 src2 dst + -> VSHUFPS fmt off (patchOp src1) (env src2) (env dst) + VSHUFPD fmt off src1 src2 dst + -> VSHUFPD fmt off (patchOp src1) (env src2) (env dst) PSLLDQ fmt off dst -> PSLLDQ fmt (patchOp off) (env dst) ===================================== compiler/GHC/CmmToAsm/X86/Ppr.hs ===================================== @@ -973,10 +973,10 @@ pprInstr platform i = case i of -> pprShuf (text "shufps") format offset src dst SHUFPD format offset src dst -> pprShuf (text "shufpd") format offset src dst - VSHUFPS format offset src dst - -> pprShuf (text "vshufps") format offset src dst - VSHUFPD format offset src dst - -> pprShuf (text "vshufpd") format offset src dst + VSHUFPS format offset src1 src2 dst + -> pprVShuf (text "vshufps") format offset src1 src2 dst + VSHUFPD format offset src1 src2 dst + -> pprVShuf (text "vshufpd") format offset src1 src2 dst PSLLDQ format offset dst -> pprShiftLeft (text "pslldq") format offset dst PSRLDQ format offset dst @@ -1248,6 +1248,19 @@ pprInstr platform i = case i of pprReg platform format reg3 ] + pprVShuf :: Line doc -> Format -> Imm -> Operand -> Reg -> Reg -> doc + pprVShuf name format imm1 op2 reg3 reg4 + = line $ hcat [ + pprGenMnemonic name format, + pprDollImm imm1, + comma, + pprOperand platform format op2, + comma, + pprReg platform format reg3, + comma, + pprReg platform format reg4 + ] + pprShiftLeft :: Line doc -> Format -> Operand -> Reg -> doc pprShiftLeft name format off reg = line $ hcat [ ===================================== compiler/GHC/CmmToLlvm/CodeGen.hs ===================================== @@ -1841,16 +1841,16 @@ genShuffleOp :: [Int] -> CmmExpr -> CmmExpr -> LlvmM ExprData genShuffleOp is x y = runExprData $ do vx <- exprToVarW x vy <- exprToVarW y + mask <- exprToVarW $ CmmLit $ CmmVec $ map ((`CmmInt` W32) . fromIntegral) is let tx = getVarType vx ty = getVarType vy Panic.massertPpr (tx == ty) (vcat [ text "shuffle: mismatched arg types" , ppLlvmType tx, ppLlvmType ty ]) - let fname = fsLit "__builtin_shufflevector" - error "SIMD NCG TODO: generate a call to __builtin_shufflevector" - --fptr <- liftExprData $ getInstrinct fname ty [tx, ty] - --doExprW tx $ Call StdCall fptr (vx: vy: map ?? is) [ReadNone, NoUnwind] + let fname = fsLit "shufflevector" + fptr <- liftExprData $ getInstrinct fname ty [tx, ty] + doExprW tx $ Call StdCall fptr [vx, vy, mask] [ReadNone, NoUnwind] -- | Generate code for a fused multiply-add operation. genFmaOp :: CmmExpr -> CmmExpr -> CmmExpr -> LlvmM ExprData ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1095,10 +1095,7 @@ emitPrimOp cfg primop = VecShuffleOp vcat n w -> \ args -> opIntoRegs $ \ [res] -> do checkVecCompatibility cfg vcat n w - doShuffleOp ty args res - where - ty :: CmmType - ty = vecCmmCat vcat w + doShuffleOp (vecVmmType vcat n w) args res -- Prefetch PrefetchByteArrayOp3 -> \args -> opIntoRegs $ \[] -> ===================================== testsuite/tests/codeGen/should_run/all.T ===================================== @@ -101,6 +101,8 @@ test('simd004', when(unregisterised(), skip), compile_and_run, ['']) test('simd005', when(unregisterised(), skip), compile_and_run, ['']) test('simd006', when(unregisterised(), skip), compile_and_run, ['']) test('simd007', when(unregisterised(), skip), compile_and_run, ['']) +test('simd009', [when(unregisterised(), skip), extra_files(['Simd009b.hs', 'Simd009c.hs'])] + ,multimod_compile_and_run, ['simd009', '']) test('T1852', normal, compile_and_run, ['']) test('T1861', extra_run_opts('0'), compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/be86b5a0e500a8654bde98ef347d14b69a27cca1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/be86b5a0e500a8654bde98ef347d14b69a27cca1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 16:14:02 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 10 Jun 2024 12:14:02 -0400 Subject: [Git][ghc/ghc][wip/T24676] Respond to RAE Message-ID: <6667264ad1d37_1a8c2239b8c8986d@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24676 at Glasgow Haskell Compiler / GHC Commits: 6de7178f by Simon Peyton Jones at 2024-06-10T17:13:48+01:00 Respond to RAE - - - - - 2 changed files: - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Utils/Instantiate.hs Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -1900,10 +1900,8 @@ qlUnify ty1 ty2 -> TcM () go (TyVarTy tv) ty2 | isMetaTyVar tv = go_kappa tv ty2 - -- Only unify QL instantiation variables - -- See (UQL3) in Note [QuickLook unification] go ty1 (TyVarTy tv) - | isQLInstTyVar tv = go_kappa tv ty1 + | isMetaTyVar tv = go_kappa tv ty1 go (CastTy ty1 _) ty2 = go ty1 ty2 go ty1 (CastTy ty2 _) = go ty1 ty2 @@ -1929,7 +1927,7 @@ qlUnify ty1 ty2 -- We look at the multiplicity too, although the chances of getting -- impredicative instantiation info from there seems...remote. go (FunTy { ft_af = af1, ft_arg = arg1, ft_res = res1, ft_mult = mult1 }) - (FunTy { ft_af = af2, ft_arg = arg2, ft_res = res2, ft_mult = mult2 }) + (FunTy { ft_af = af2, ft_arg = arg2, ft_res = res2, ft_mult = mult2 }) | af1 == af2 -- Match the arrow TyCon = do { when (isVisibleFunArg af1) (go arg1 arg2) ; when (isFUNArg af1) (go mult1 mult2) @@ -1947,7 +1945,7 @@ qlUnify ty1 ty2 = do { go t1a t2a; go t1b t2b } go _ _ = return () - + -- Don't look under foralls; see (UQL4) of Note [QuickLook unification] ---------------- go_kappa kappa ty2 @@ -1991,11 +1989,11 @@ In qlUnify, if we find (kappa ~ ty), we are going to update kappa := ty. That is the entire point of qlUnify! Wrinkles: (UQL1) Before unifying an instantiation variable in `go_flexi`, we must check - the usual unification conditions, by calling `GHC.Tc.Utils.Unify.simpleUnifyCheck` - In particular: - * We must not make an occurs-check; we use occCheckExpand for that. - * We must not unify a concrete type variable with a non-concrete type. - * Level mis-match + the usual unification conditions, by calling `GHC.Tc.Utils.Unify.simpleUnifyCheck`. + For example that checks for + * An occurs-check + * Level mis-match + * An attempt to unify a concrete type variable with a non-concrete type. (UQL2) What if kappa and ty have different kinds? We simply call the ordinary unifier and use the coercion to connect the two. @@ -2020,6 +2018,27 @@ That is the entire point of qlUnify! Wrinkles: But happily this can't happen: QL instantiation variables have level infinity, and we never unify a variable with a type from a deeper level. +(UQL4) Should we look under foralls in qlUnify? The use-case would be + (forall a. beta[qlinst] -> a) ~ (forall a. (forall b. b->b) -> a) + where we might hope for + beta := forall b. b + + But in fact we don't attempt this: + + * The normal on-the-fly unifier doesn't look under foralls, so why + should qlUnify? + + * Looking under foralls means we'd have to track the bound variables on both + sides. Tiresome but not a show stopper. + + * We might call the *regular* unifier (via unifyKind) under foralls, and that + doesn't know about those bound variables (it controls scope through level + numbers) so it might go totally wrong. At least we'd have to instantaite + the forall-types with skolems (with level numbers). Maybe more. + + It's just not worth the trouble, we think (for now at least). + + Sadly discarded design alternative ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ It is very tempting to use `unifyType` rather than `qlUnify`, killing off the ===================================== compiler/GHC/Tc/Utils/Instantiate.hs ===================================== @@ -431,7 +431,7 @@ right here. But note * There is little point in trying to optimise for - (s ~# t), because this has kind Constraint#, not Constraint, and so will not be - in the theta instantiated in instCalll + in the theta instantiated in instCall - (s ~~ t), becaues heterogeneous equality is rare, and more complicated. Anyway, for now we don't take advantage of these potential effects. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6de7178f4e820ca15e70e7a15585bb923de705cf -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6de7178f4e820ca15e70e7a15585bb923de705cf You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 16:27:23 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 10 Jun 2024 12:27:23 -0400 Subject: [Git][ghc/ghc][wip/T24887] 46 commits: Migrate `Finder` component to `OsPath`, fixed #24616 Message-ID: <6667296b46e5e_1a8c2462cd89589c@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24887 at Glasgow Haskell Compiler / GHC Commits: c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - 6927b9ea by Simon Peyton Jones at 2024-06-10T17:27:13+01:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - 30 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - + compiler/GHC/Data/OsPath.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Config/Cmm.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cb61d38413529de5a41a5d57fb4a4b80fb2b8d4a...6927b9ea7a4de0fe803e567d2f7297d2700b3f1a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cb61d38413529de5a41a5d57fb4a4b80fb2b8d4a...6927b9ea7a4de0fe803e567d2f7297d2700b3f1a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 16:39:20 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 10 Jun 2024 12:39:20 -0400 Subject: [Git][ghc/ghc][wip/T24676] 79 commits: rts: ensure gc_thread/gen_workspace is allocated with proper alignment Message-ID: <66672c385b631_251c75192670365c6@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24676 at Glasgow Haskell Compiler / GHC Commits: 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - afd88e56 by Simon Peyton Jones at 2024-06-10T17:38:58+01:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6de7178f4e820ca15e70e7a15585bb923de705cf...afd88e56d20c4880818e4aeec8a3d347ee747e0e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6de7178f4e820ca15e70e7a15585bb923de705cf...afd88e56d20c4880818e4aeec8a3d347ee747e0e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 10 17:07:28 2024 From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge)) Date: Mon, 10 Jun 2024 13:07:28 -0400 Subject: [Git][ghc/ghc][wip/T24789_impl] Unicode: disable Huffman Message-ID: <666732d0dba10_251c756a294443258@gitlab.mail> Serge S. Gulin pushed to branch wip/T24789_impl at Glasgow Haskell Compiler / GHC Commits: 7f783d98 by Serge S. Gulin at 2024-06-10T20:06:59+03:00 Unicode: disable Huffman - - - - - 0 changed files: The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7f783d986f0ae585621308bbf9acbc66d91e84f5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7f783d986f0ae585621308bbf9acbc66d91e84f5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 06:29:16 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Tue, 11 Jun 2024 02:29:16 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T14030 Message-ID: <6667eebc97b74_332e523fd16c53286@gitlab.mail> Sebastian Graf pushed new branch wip/T14030 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T14030 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 06:44:56 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Tue, 11 Jun 2024 02:44:56 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/sgraf-T12457 Message-ID: <6667f268401b6_332e525d1cf45547e@gitlab.mail> Sebastian Graf pushed new branch wip/sgraf-T12457 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/sgraf-T12457 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 06:55:04 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Tue, 11 Jun 2024 02:55:04 -0400 Subject: [Git][ghc/ghc][wip/T14030] Implement the "Derive Lift instances for data types in templste-haskell" proposal (#14030) Message-ID: <6667f4c8af0ea_332e5272a448556be@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: 82e2a9e8 by Sebastian Graf at 2024-06-11T08:52:08+02:00 Implement the "Derive Lift instances for data types in templste-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. - - - - - 3 changed files: - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs ===================================== @@ -12,6 +12,8 @@ {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UnboxedSums #-} {-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE DeriveLift #-} +{-# LANGUAGE StandaloneDeriving #-} {-# OPTIONS_GHC -fno-warn-inline-rule-shadowing #-} -- | This module gives the definition of the 'Lift' class. @@ -39,7 +41,7 @@ module GHC.Internal.TH.Lift where import GHC.Internal.TH.Syntax -import GHC.Internal.TH.Lib () -- See wrinkle (W4) of Note [Tracking dependencies on primitives] +import GHC.Internal.TH.Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives] import GHC.Internal.Lexeme ( startsVarSym, startsVarId ) import GHC.Internal.Data.Either @@ -52,7 +54,7 @@ import GHC.Internal.Integer import GHC.Internal.Real import GHC.Internal.Word import GHC.Internal.Int -import GHC.Internal.Data.Data +import GHC.Internal.Data.Data hiding (Fixity) import GHC.Internal.Natural -- | A 'Lift' instance can have any of its values turned into a Template @@ -424,6 +426,116 @@ rightName = 'Right nonemptyName :: Name nonemptyName = '(:|) +----------------------------------------------------- +-- +-- Lifting the TH AST +-- +----------------------------------------------------- + +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ModName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameSpace +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NamespaceSpecifier +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PkgName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameFlavour +-- | @since template-haskell-2.22.1.0 +deriving instance Lift OccName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Name + +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Specificity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift a => Lift (TyVarBndr a) +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TyLit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Type + +-- | @since template-haskell-2.22.1.0 +instance Lift Bytes where + lift = litE . BytesPrimL + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 + +deriving instance Lift Lit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pat +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Clause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivClause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivStrategy +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Overlap +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FunDep +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Safety +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Callconv +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Foreign +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FixityDirection +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Fixity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Inline +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleMatch +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Phases +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleBndr +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnTarget +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pragma +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceUnpackedness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Bang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Con +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TySynEqn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FamilyResultSig +-- | @since template-haskell-2.22.1.0 +deriving instance Lift InjectivityAnn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift BndrVis +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TypeFamilyHead +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Role +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynArgs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynDir +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Dec +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Range +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Exp +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Match +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Guard +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Stmt +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Body + ----------------------------------------------------- -- -- Generic Lift implementations ===================================== libraries/template-haskell/changelog.md ===================================== @@ -1,5 +1,9 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) +## 2.22.1.0 + + * `Lift` instances were added for the `template-haskell` AST. + ## 2.22.0.0 * The kind of `Code` was changed from `forall r. (Type -> Type) -> TYPE r -> Type` ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -3,7 +3,7 @@ -- template-haskell.cabal. name: template-haskell -version: 2.22.0.0 +version: 2.22.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/82e2a9e8d3339c4a21cddc015a42e369d723902b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/82e2a9e8d3339c4a21cddc015a42e369d723902b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 08:39:48 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 11 Jun 2024 04:39:48 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] 11 commits: ttg: Remove SourceText from OverloadedLabel Message-ID: <66680d545972f_1d181b31f81c107679@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: 399a283a by Adriaan Leijnse at 2024-06-11T09:39:37+01:00 ttg: Remove SourceText from OverloadedLabel Progress towards #21592 - - - - - 6c43d68e by Alexander Foremny at 2024-06-11T09:39:37+01:00 AST: GHC.Prelude -> Prelude Refactor occurrences to GHC.Prelude with Prelude within Language/Haskell. Progress towards #21592 - - - - - 4d6994a2 by Alexander Foremny at 2024-06-11T09:39:37+01:00 AST: remove occurrences of GHC.Unit.Module.ModuleName `GHC.Unit.Module` re-exports `ModuleName` from `Language.Haskell.Syntax.Module.Name`. Progress towards #21592 - - - - - 73da13cc by Fabian Kirchner at 2024-06-11T09:39:37+01:00 AST: move Data instance definition for ModuleName to GHC.Unit.Types To remove the dependency on GHC.Utils.Misc inside Language.Haskell.Syntax.Module.Name, the instance definition is moved from there into GHC.Unit.Types. Progress towards #21592 - - - - - 7856ec00 by Fabian Kirchner at 2024-06-11T09:39:37+01:00 AST: move negateOverLitVal into GHC.Hs.Lit The function negateOverLitVal is not used within Language.Haskell and therefore can be moved to the respective module inside GHC.Hs. Progress towards #21592 - - - - - 97ca97f8 by Fabian Kirchner at 2024-06-11T09:39:37+01:00 AST: move conDetailsArity into GHC.Rename.Module The function conDetailsArity is only used inside GHC.Rename.Module. We therefore move it there from Language.Haskell.Syntax.Lit. Progress towards #21592 - - - - - 3de5a691 by Mauricio at 2024-06-11T09:39:38+01:00 AST: Remove GHC.Utils.Assert from GHC Simple cleanup. Progress towards #21592 - - - - - 4339d2c4 by Fabian Kirchner at 2024-06-11T09:39:38+01:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - a4766629 by Fabian Kirchner at 2024-06-11T09:39:38+01:00 ttg: Move some AST types into Language.Haskell.Syntax.Basic In particular, we move: * TopLevelFlag * TypeOrData * TyConFlavour Progress towards #21592 - - - - - cd2c2930 by Adowrath at 2024-06-11T09:39:38+01:00 ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type Progress towards #21592 This splits HsSrcBang up, creating the new HsBang within `Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness and strictness information, while `HsSrcBang` only adds the SourceText for usage within the compiler directly. Inside the AST, to preserve the SourceText, it is hidden behind the pre-existing extension point `XBindTy`. All other occurrences of `HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when interacting with the `BindTy` constructor, the hidden `SourceText` is extracted/inserted into the `XBindTy` extension point. `GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for convenience. A constructor function `mkHsSrcBang` that takes all individual components has been added. Two exceptions has been made though: - The `Outputable HsSrcBang` instance is replaced by `Outputable HsBang`. While being only GHC-internal, the only place it's used is in outputting `HsBangTy` constructors -- which already have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just to ignore the `SourceText` anyway. - The error `TcRnUnexpectedAnnotation` did not use the `SourceText`, so it too now only holds a `HsBang`. - - - - - 374e13f6 by Mauricio at 2024-06-11T09:39:38+01:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/CoreToIface.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Build.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var.hs-boot - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Basic.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6c9268b23214709c9c11ca43bab21cd633e87a03...374e13f6adb411de4ff3020a4676fd778fd3473a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6c9268b23214709c9c11ca43bab21cd633e87a03...374e13f6adb411de4ff3020a4676fd778fd3473a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 09:25:48 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 11 Jun 2024 05:25:48 -0400 Subject: [Git][ghc/ghc][master] users-guide: Fix stylistic issues in 9.12 release notes Message-ID: <6668181c1c1d0_1d181ba7f3f01214a@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 1 changed file: - docs/users_guide/9.12.1-notes.rst Changes: ===================================== docs/users_guide/9.12.1-notes.rst ===================================== @@ -31,10 +31,10 @@ Language This means that code using :extension:`UnliftedDatatypes` or :extension:`UnliftedNewtypes` can now use :extension:`OverloadedRecordDot`. -- Unboxed Float#/Double# literals now support the HexFloatLiterals extension +- Unboxed ``Float#``/``Double#`` literals now support the HexFloatLiterals extension (`#22155 `_). -- UnliftedFFITypes: GHC will now accept ffi types like: ``(# #) -> T`` where ``(# #)`` +- :extension:`UnliftedFFITypes`: GHC will now accept FFI types like: ``(# #) -> T`` where ``(# #)`` is used as the one and only function argument. Compiler View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e17d7e8caf6363552ebcc6971418fc5291aa5d85 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e17d7e8caf6363552ebcc6971418fc5291aa5d85 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 09:26:25 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 11 Jun 2024 05:26:25 -0400 Subject: [Git][ghc/ghc][master] fix typo in the simplifier debug output: Message-ID: <66681840f2444_1d181bbd3b981245c@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 1 changed file: - compiler/GHC/Core/Opt/Simplify.hs Changes: ===================================== compiler/GHC/Core/Opt/Simplify.hs ===================================== @@ -199,7 +199,7 @@ simplifyPgm logger unit_env name_ppr_ctx opts -- Subtract 1 from iteration_no to get the -- number of iterations we actually completed - return ( "Simplifier baled out", iteration_no - 1 + return ( "Simplifier bailed out", iteration_no - 1 , totalise counts_so_far , guts_no_binds { mg_binds = binds, mg_rules = local_rules } ) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8a8a982aa5417391e24a4317fe953a265f0c4024 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8a8a982aa5417391e24a4317fe953a265f0c4024 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 09:49:38 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Tue, 11 Jun 2024 05:49:38 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] NCG SIMD: fix shuffle lowering Message-ID: <66681db2bddd1_1d181bf5d3f41264a0@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 16faf448 by sheaf at 2024-06-11T11:38:23+02:00 NCG SIMD: fix shuffle lowering - - - - - 5 changed files: - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - + testsuite/tests/codeGen/should_run/Simd009b.hs - + testsuite/tests/codeGen/should_run/Simd009c.hs - + testsuite/tests/codeGen/should_run/simd009.hs Changes: ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1668,11 +1668,10 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps VecFormat 2 FmtDouble _ -> case is of [i1, i2] -> case (i1, i2) of - (i, j) | i == j - -> let v = if i < 2 then v1 else v2 - mov = if i == 0 || i == 2 then MOVL else MOVH - in unitOL (mov fmt (OpReg v) (OpReg dst)) `snocOL` - SHUFPD fmt (ImmInt 0b00) (OpReg dst) dst + (0,0) -> unitOL (VSHUFPD fmt (ImmInt 0b00) (OpReg v1) v1 dst) + (1,1) -> unitOL (VSHUFPD fmt (ImmInt 0b11) (OpReg v1) v1 dst) + (2,2) -> unitOL (VSHUFPD fmt (ImmInt 0b00) (OpReg v2) v2 dst) + (3,3) -> unitOL (VSHUFPD fmt (ImmInt 0b11) (OpReg v2) v2 dst) (0,1) -> unitOL (MOVU fmt (OpReg v1) (OpReg dst)) (2,3) -> unitOL (MOVU fmt (OpReg v2) (OpReg dst)) (1,0) -> unitOL (VSHUFPD fmt (ImmInt 0b01) (OpReg v1) v1 dst) @@ -1680,9 +1679,9 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps (0,2) -> unitOL (VSHUFPD fmt (ImmInt 0b00) (OpReg v2) v1 dst) (2,0) -> unitOL (VSHUFPD fmt (ImmInt 0b00) (OpReg v1) v2 dst) (0,3) -> unitOL (VSHUFPD fmt (ImmInt 0b10) (OpReg v2) v1 dst) - (3,0) -> unitOL (VSHUFPD fmt (ImmInt 0b10) (OpReg v1) v2 dst) + (3,0) -> unitOL (VSHUFPD fmt (ImmInt 0b01) (OpReg v1) v2 dst) (1,2) -> unitOL (VSHUFPD fmt (ImmInt 0b01) (OpReg v2) v1 dst) - (2,1) -> unitOL (VSHUFPD fmt (ImmInt 0b01) (OpReg v1) v2 dst) + (2,1) -> unitOL (VSHUFPD fmt (ImmInt 0b10) (OpReg v1) v2 dst) (1,3) -> unitOL (VSHUFPD fmt (ImmInt 0b11) (OpReg v2) v1 dst) (3,1) -> unitOL (VSHUFPD fmt (ImmInt 0b11) (OpReg v1) v2 dst) _ -> pprPanic "vector shuffle: indices out of bounds 0 <= i <= 3" (ppr is) @@ -1701,11 +1700,11 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps | i1 <= 3, i2 <= 3 , i3 >= 4, i4 >= 4 , let imm = i1 + i2 `shiftL` 2 + (i3 - 4) `shiftL` 4 + (i4 - 4) `shiftL` 6 - -> unitOL (VSHUFPS fmt (ImmInt imm) (OpReg v1) v2 dst) + -> unitOL (VSHUFPS fmt (ImmInt imm) (OpReg v2) v1 dst) | i1 >= 4, i2 >= 4 , i3 <= 3, i4 <= 3 - , let imm = i3 + i4 `shiftL` 2 + (i1 - 4) `shiftL` 4 + (i2 - 4) `shiftL` 6 - -> unitOL (VSHUFPS fmt (ImmInt imm) (OpReg v2) v1 dst) + , let imm = (i1 - 4) + (i2 - 4) `shiftL` 2 + i3 `shiftL` 4 + i4 `shiftL` 6 + -> unitOL (VSHUFPS fmt (ImmInt imm) (OpReg v1) v2 dst) | otherwise -> -- Fall-back code with 4 INSERTPS operations. ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -48,9 +48,7 @@ import GHC.CmmToAsm.Format import GHC.CmmToAsm.Types import GHC.CmmToAsm.Utils import GHC.CmmToAsm.Instr (RegUsage(..), noUsage) -import GHC.Platform.Reg.Class import GHC.Platform.Reg -import GHC.CmmToAsm.Reg.Target import GHC.CmmToAsm.Config import GHC.Cmm.BlockId @@ -500,7 +498,7 @@ regUsageOfInstr platform instr VBROADCAST fmt src dst -> mkRU fmt (use_EA src []) [dst] VEXTRACT fmt off src dst -> mkRU fmt ((use_R off []) ++ [src]) (use_R dst []) INSERTPS fmt off src dst - -> mkRU fmt ((use_R off []) ++ (use_R src []) ++ [dst]) [dst] + -> mkRU fmt ((use_R off []) ++ (use_R src [])) [dst] VMOVU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) MOVU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) ===================================== testsuite/tests/codeGen/should_run/Simd009b.hs ===================================== @@ -0,0 +1,70 @@ +{-# OPTIONS_GHC -O2 #-} +{-# OPTIONS_GHC -msse #-} +{-# OPTIONS_GHC -msse2 #-} +{-# OPTIONS_GHC -msse4 #-} +{-# OPTIONS_GHC -mavx #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE RecordWildCards #-} + +module Simd009b where + +import Control.Monad ( unless ) +import Data.Foldable ( for_ ) +import GHC.Exts + +data FloatX4 = FX4# FloatX4# + +instance Show FloatX4 where + show (FX4# f) = case (unpackFloatX4# f) of + (# a, b, c, d #) -> show ((F# a), (F# b), (F# c), (F# d)) + + +instance Eq FloatX4 where + (FX4# a) == (FX4# b) + = case (unpackFloatX4# a) of + (# a1, a2, a3, a4 #) -> + case (unpackFloatX4# b) of + (# b1, b2, b3, b4 #) -> (F# a1) == (F# b1) && + (F# a2) == (F# b2) && + (F# a3) == (F# b3) && + (F# a4) == (F# b4) + +data DoubleX2 = DX2# DoubleX2# + +instance Show DoubleX2 where + show (DX2# d) = case (unpackDoubleX2# d) of + (# a, b #) -> show ((D# a), (D# b)) + +instance Eq DoubleX2 where + (DX2# a) == (DX2# b) + = case (unpackDoubleX2# a) of + (# a1, a2 #) -> + case (unpackDoubleX2# b) of + (# b1, b2 #) -> (D# a1) == (D# b1) && + (D# a2) == (D# b2) + +myShuffleDoubleX2 :: DoubleX2# -> DoubleX2# -> (# Int#, Int# #) -> DoubleX2# +myShuffleDoubleX2 v1 v2 (# i1, i2 #) = + case unpackDoubleX2# v1 of + (# d1, d2 #) -> + case unpackDoubleX2# v2 of + (# d3, d4 #) -> + let ds = [ D# d1, D# d2, D# d3, D# d4 ] + D# x = ds !! I# i1 + D# y = ds !! I# i2 + in packDoubleX2# (# x, y #) + +myShuffleFloatX4 :: FloatX4# -> FloatX4# -> (# Int#, Int#, Int#, Int# #) -> FloatX4# +myShuffleFloatX4 v1 v2 (# i1, i2, i3, i4 #) = + case unpackFloatX4# v1 of + (# f1, f2, f3, f4 #) -> + case unpackFloatX4# v2 of + (# f5, f6, f7, f8 #) -> + let fs = [ F# f1, F# f2, F# f3, F# f4 + , F# f5, F# f6, F# f7, F# f8 ] + F# x = fs !! I# i1 + F# y = fs !! I# i2 + F# z = fs !! I# i3 + F# w = fs !! I# i4 + in packFloatX4# (# x, y, z, w #) ===================================== testsuite/tests/codeGen/should_run/Simd009c.hs ===================================== @@ -0,0 +1,53 @@ +{-# OPTIONS_GHC -O2 #-} +{-# OPTIONS_GHC -msse #-} +{-# OPTIONS_GHC -msse2 #-} +{-# OPTIONS_GHC -msse4 #-} +{-# OPTIONS_GHC -mavx #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE TemplateHaskell #-} + +module Simd009c where + +import Control.Monad ( unless ) +import Data.Foldable ( for_ ) +import GHC.Exts +import Language.Haskell.TH ( CodeQ ) +import Language.Haskell.TH.Syntax ( Lift(liftTyped) ) + +import Simd009b + +floatX4ShuffleTest :: CodeQ FloatX4 -> CodeQ FloatX4 -> CodeQ (Int, Int, Int, Int) -> CodeQ (IO ()) +floatX4ShuffleTest v1 v2 ijkl = + [|| + do + let (I# i#, I# j#, I# k#, I# l#) = $$ijkl + FX4# v1# = $$v1 + FX4# v2# = $$v2 + s1 = shuffleFloatX4# v1# v2# (# i#, j#, k#, l# #) + s2 = myShuffleFloatX4 v1# v2# (# i#, j#, k#, l# #) + unless (FX4# s1 == FX4# s2) $ do + putStrLn $ "Failed test: FloatX4# shuffle " ++ show (I# i#, I# j#, I# k#, I# l# ) + putStrLn $ " SIMD: " ++ show (FX4# s1) + putStrLn $ "reference: " ++ show (FX4# s2) + ||] + +doubleX2ShuffleTest :: CodeQ DoubleX2 -> CodeQ DoubleX2 -> CodeQ (Int, Int) -> CodeQ (IO ()) +doubleX2ShuffleTest v1 v2 ij = + [|| + do + let (I# i#, I# j#) = $$ij + DX2# v1# = $$v1 + DX2# v2# = $$v2 + s1 = shuffleDoubleX2# v1# v2# (# i#, j# #) + s2 = myShuffleDoubleX2 v1# v2# (# i#, j# #) + unless (DX2# s1 == DX2# s2) $ do + putStrLn $ "Failed test:DoubleX2# shuffle " ++ show (I# i#, I# j#) + putStrLn $ " SIMD: " ++ show (DX2# s1) + putStrLn $ "reference: " ++ show (DX2# s2) + ||] + +forQ_ :: Lift i => [i] -> (CodeQ i -> CodeQ (IO ())) -> CodeQ (IO ()) +forQ_ [] _ = [|| return () ||] +forQ_ (i:is) f = [|| $$( f (liftTyped i) ) *> $$( forQ_ is f ) ||] ===================================== testsuite/tests/codeGen/should_run/simd009.hs ===================================== @@ -0,0 +1,32 @@ +{-# OPTIONS_GHC -msse #-} +{-# OPTIONS_GHC -msse2 #-} +{-# OPTIONS_GHC -msse4 #-} +{-# OPTIONS_GHC -mavx #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE TemplateHaskell #-} +-- test shuffle instructions + +import Control.Monad ( unless ) +import Data.Foldable ( for_ ) +import GHC.Exts +import Language.Haskell.TH ( CodeQ ) + +import Simd009b +import Simd009c + +main :: IO () +main = do + let x = packDoubleX2# (# 1.1##, 2.2## #) + y = packDoubleX2# (# 3.3##, 4.4## #) + a = packFloatX4# (# 1.1#, 2.2#, 3.3#, 4.4# #) + b = packFloatX4# (# 5.5#, 6.6#, 7.7#, 8.8# #) + $$(forQ_ [(i,j) | i <- [0..3], j <- [0..3]] (doubleX2ShuffleTest [|| DX2# x ||] [|| DX2# y ||]) ) + $$(forQ_ [ (0,0,0,0), (3,3,3,3), (7,7,7,7) + , (0,1,2,3), (4,5,6,7) + , (3,2,1,0), (7,6,5,4) + , (0,1,4,5), (4,5,0,1) + , (2,1,7,6), (7,6,2,1) + , (1,2,7,7), (6,6,3,2) + ] (floatX4ShuffleTest [|| FX4# a ||] [|| FX4# b ||]) ) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/16faf448673a302c7c0a54d36e8f61a7519afcac -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/16faf448673a302c7c0a54d36e8f61a7519afcac You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 09:57:34 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 11 Jun 2024 05:57:34 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: users-guide: Fix stylistic issues in 9.12 release notes Message-ID: <66681f8df0dfd_1d181b10e9088130167@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - e7a991de by Hécate Moonlight at 2024-06-11T05:57:16-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - 534a8c49 by Hécate Kleidukos at 2024-06-11T05:57:18-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - 89d8017a by qqwy at 2024-06-11T05:57:19-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 36fafc5b by Ryan Hendrickson at 2024-06-11T05:57:24-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 20 changed files: - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/Tc/Errors/Ppr.hs - docs/users_guide/9.12.1-notes.rst - docs/users_guide/exts/assert.rst - docs/users_guide/phases.rst - + testsuite/tests/driver/cpp_assertions_ignored/Makefile - + testsuite/tests/driver/cpp_assertions_ignored/all.T - + testsuite/tests/driver/cpp_assertions_ignored/cpp_assertions_ignored.stdout - + testsuite/tests/driver/cpp_assertions_ignored/main.hs - testsuite/tests/th/T17820d.stderr - testsuite/tests/th/T23829_hasty_b.stderr - utils/haddock/Makefile - utils/haddock/README.md - utils/haddock/doc/intro.rst - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/resources/html/package.json - utils/haddock/haddock-library/haddock-library.cabal - utils/haddock/haddock-test/haddock-test.cabal - utils/haddock/haddock.cabal Changes: ===================================== compiler/GHC/Core/Opt/Simplify.hs ===================================== @@ -199,7 +199,7 @@ simplifyPgm logger unit_env name_ppr_ctx opts -- Subtract 1 from iteration_no to get the -- number of iterations we actually completed - return ( "Simplifier baled out", iteration_no - 1 + return ( "Simplifier bailed out", iteration_no - 1 , totalise counts_so_far , guts_no_binds { mg_binds = binds, mg_rules = local_rules } ) ===================================== compiler/GHC/SysTools/Cpp.hs ===================================== @@ -168,6 +168,9 @@ doCpp logger tmpfs dflags unit_env opts input_fn output_fn = do backend_defs <- applyCDefs (backendCDefs $ backend dflags) logger dflags let th_defs = [ "-D__GLASGOW_HASKELL_TH__" ] + + let asserts_def = [ "-D__GLASGOW_HASKELL_ASSERTS_IGNORED__" | gopt Opt_IgnoreAsserts dflags] + -- Default CPP defines in Haskell source ghcVersionH <- getGhcVersionPathName dflags unit_env let hsSourceCppOpts = [ "-include", ghcVersionH ] @@ -197,6 +200,7 @@ doCpp logger tmpfs dflags unit_env opts input_fn output_fn = do ++ map GHC.SysTools.Option target_defs ++ map GHC.SysTools.Option backend_defs ++ map GHC.SysTools.Option th_defs + ++ map GHC.SysTools.Option asserts_def ++ map GHC.SysTools.Option hscpp_opts ++ map GHC.SysTools.Option sse_defs ++ map GHC.SysTools.Option fma_def ===================================== compiler/GHC/Tc/Errors/Ppr.hs ===================================== @@ -1417,9 +1417,16 @@ instance Diagnostic TcRnMessage where , interpp'SP errorVars ] TcRnBadlyStaged reason bind_lvl use_lvl -> mkSimpleDecorated $ - text "Stage error:" <+> pprStageCheckReason reason <+> - hsep [text "is bound at stage" <+> ppr bind_lvl, - text "but used at stage" <+> ppr use_lvl] + vcat $ + [ text "Stage error:" <+> pprStageCheckReason reason <+> + hsep [text "is bound at stage" <+> ppr bind_lvl, + text "but used at stage" <+> ppr use_lvl] + ] ++ + [ hsep [ text "Hint: quoting" <+> thBrackets (ppUnless (isValName n) "t") (ppr n) + , text "or an enclosing expression would allow the quotation to be used in an earlier stage" + ] + | StageCheckSplice n <- [reason] + ] TcRnBadlyStagedType name bind_lvl use_lvl -> mkSimpleDecorated $ text "Badly staged type:" <+> ppr name <+> ===================================== docs/users_guide/9.12.1-notes.rst ===================================== @@ -31,10 +31,10 @@ Language This means that code using :extension:`UnliftedDatatypes` or :extension:`UnliftedNewtypes` can now use :extension:`OverloadedRecordDot`. -- Unboxed Float#/Double# literals now support the HexFloatLiterals extension +- Unboxed ``Float#``/``Double#`` literals now support the HexFloatLiterals extension (`#22155 `_). -- UnliftedFFITypes: GHC will now accept ffi types like: ``(# #) -> T`` where ``(# #)`` +- :extension:`UnliftedFFITypes`: GHC will now accept FFI types like: ``(# #) -> T`` where ``(# #)`` is used as the one and only function argument. Compiler @@ -75,6 +75,13 @@ Compiler `_). This does not affect existing support of apple systems on x86_64/aarch64. +- The flag :ghc-flag:`-fignore-asserts` will now also enable the + :extension:`CPP` macro ``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` (`#24967 + `_). + This enables people to write their own custom assertion functions. + See :ref:`assertions`. + + GHCi ~~~~ ===================================== docs/users_guide/exts/assert.rst ===================================== @@ -50,4 +50,20 @@ allows enabling assertions even when optimisation is turned on. Assertion failures can be caught, see the documentation for the :base-ref:`Control.Exception.` library for the details. - +The ``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` CPP macro +===================================================== + +When code is compiled with assertions ignored (using :ghc-flag:`-fignore-asserts` or :ghc-flag:`-O`), +the :extension:`CPP` macro ``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` will be defined. +This can be used to conditionally compile your own custom assert-like functions. +For example: :: + + checkedAdd :: Word -> Word -> Word + #ifdef __GLASGOW_HASKELL_ASSERTS_IGNORED__ + checkedAdd lhs rhs = lhs + rhs + #else + checkedAdd lhs rhs + | res < lhs || res < rhs = raise OverflowException + | otherwise = res + where res = lhs + rhs + #endif ===================================== docs/users_guide/phases.rst ===================================== @@ -508,6 +508,13 @@ defined by your local GHC installation, the following trick is useful: is added, so for example when using version 3.7 of LLVM, ``__GLASGOW_HASKELL_LLVM__==307``). +``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` + .. index:: + single: __GLASGOW_HASKELL_ASSERTS_IGNORED__ + + Only defined when :ghc-flag:`-fignore-asserts` is specified. + This can be used to create your own assertions, see :ref:`assertions` + ``__PARALLEL_HASKELL__`` .. index:: single: __PARALLEL_HASKELL__ ===================================== testsuite/tests/driver/cpp_assertions_ignored/Makefile ===================================== @@ -0,0 +1,11 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +cpp_assertions_ignored: + echo "Without -fignore-asserts" + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 main.hs + (./main 2>&1); true + echo "With -fignore-asserts" + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -fignore-asserts main.hs + ./main 2>&1 ===================================== testsuite/tests/driver/cpp_assertions_ignored/all.T ===================================== @@ -0,0 +1,4 @@ +test('cpp_assertions_ignored', + [ extra_files(['main.hs']) + ], + makefile_test, ['cpp_assertions_ignored']) ===================================== testsuite/tests/driver/cpp_assertions_ignored/cpp_assertions_ignored.stdout ===================================== @@ -0,0 +1,4 @@ +Without -fignore-asserts +Assertions Enabled +With -fignore-asserts +Assertions Ignored ===================================== testsuite/tests/driver/cpp_assertions_ignored/main.hs ===================================== @@ -0,0 +1,14 @@ +{-# LANGUAGE CPP #-} +import Control.Exception (assert) + +main = + if assertsEnabled + then putStrLn "Assertions Enabled" + else putStrLn "Assertions Ignored" + +assertsEnabled :: Bool +#ifdef __GLASGOW_HASKELL_ASSERTS_IGNORED__ +assertsEnabled = False +#else +assertsEnabled = True +#endif ===================================== testsuite/tests/th/T17820d.stderr ===================================== @@ -1,7 +1,8 @@ - T17820d.hs:6:38: error: [GHC-28914] • Stage error: ‘foo’ is bound at stage 2 but used at stage 1 + Hint: quoting [| foo |] or an enclosing expression would allow the quotation to be used in an earlier stage • In the untyped splice: $(const [| 0 |] foo) In the Template Haskell quotation [d| data D = MkD {foo :: Int} blargh = $(const [| 0 |] foo) |] + ===================================== testsuite/tests/th/T23829_hasty_b.stderr ===================================== @@ -1,6 +1,7 @@ - T23829_hasty_b.hs:8:42: error: [GHC-28914] • Stage error: ‘ty’ is bound at stage 2 but used at stage 1 + Hint: quoting [t| ty |] or an enclosing expression would allow the quotation to be used in an earlier stage • In the untyped splice: $ty In the Template Haskell quotation [t| forall (ty :: TypeQ). Proxy $ty |] + ===================================== utils/haddock/Makefile ===================================== @@ -8,18 +8,17 @@ test: ## Run the test suite @cabal test lint: ## Run the code linter (HLint) - @find driver haddock-api haddock-library haddock-test hoogle-test hypsrc-test latex-test \ - -name "*.hs" | xargs -P $(PROCS) -I {} hlint --refactor-options="-i" --refactor {} + @find driver haddock-api haddock-library -name "*.hs" | xargs -P $(PROCS) -I {} hlint --refactor-options="-i" --refactor {} style: ## Run the code styler (fourmolu and cabal-fmt) @cabal-fmt -i **/*.cabal @fourmolu -q --mode inplace driver haddock-api haddock-library style-check: ## Check the code's style (fourmolu and cabal-fmt) - @cabal-fmt -i **/*.cabal + @cabal-fmt -c **/*.cabal @fourmolu -q --mode check driver haddock-api haddock-library -style-quick: ## Run the code styler on modified files +style-quick: ## Run the code styler on modified files tracked by git @cabal-fmt -i **/*.cabal @git diff origin --name-only driver haddock-api haddock-library | xargs -P $(PROCS) -I {} fourmolu -q -i {} @@ -29,9 +28,12 @@ tags: ## Generate ctags and etags for the source code (ghc-tags) help: ## Display this help message @grep -E '^[a-zA-Z_-]+:.*?## .*$$' $(MAKEFILE_LIST) | awk 'BEGIN {FS = ":.* ?## "}; {printf "\033[36m%-30s\033[0m %s\n", $$1, $$2}' -PROCS := $(shell nproc) - .PHONY: all $(MAKECMDGOALS) .DEFAULT_GOAL := help +ifeq ($(UNAME), Darwin) + PROCS := $(shell sysctl -n hw.logicalcpu) +else + PROCS := $(shell nproc) +endif ===================================== utils/haddock/README.md ===================================== @@ -1,4 +1,4 @@ -# Haddock [![CI][CI badge]][CI page] [![Hackage][Hackage badge]][Hackage page] +# Haddock [![Hackage][Hackage badge]][Hackage page] Haddock is the standard tool for generating documentation from Haskell code. Full documentation about Haddock itself can be found in the `doc/` subdirectory, @@ -25,8 +25,6 @@ See [CONTRIBUTING.md](CONTRIBUTING.md) to see how to make contributions to the project. -[CI page]: https://github.com/haskell/haddock/actions/workflows/ci.yml -[CI badge]: https://github.com/haskell/haddock/actions/workflows/ci.yml/badge.svg [Hackage page]: https://hackage.haskell.org/package/haddock [Hackage badge]: https://img.shields.io/hackage/v/haddock.svg [reST]: https://www.sphinx-doc.org/en/master/usage/restructuredtext/index.html ===================================== utils/haddock/doc/intro.rst ===================================== @@ -62,9 +62,7 @@ Obtaining Haddock Haddock is distributed with GHC distributions, and will automatically be provided if you use `ghcup `__, for instance. -Up-to-date sources can also be obtained from our public GitHub -repository. The Haddock sources are at -``https://github.com/haskell/haddock``. +Haddock lives in the GHC repository, which you can consult at ``https://gitlab.haskell.org/ghc/ghc``. License ------- @@ -99,12 +97,6 @@ code, except where otherwise indicated. (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -Contributors ------------- - -A list of contributors to the project can be seen at -``https://github.com/haskell/haddock/graphs/contributors``. - Acknowledgements ---------------- ===================================== utils/haddock/haddock-api/haddock-api.cabal ===================================== @@ -7,13 +7,12 @@ description: Haddock is a documentation-generation tool for Haskell license: BSD-2-Clause license-file: LICENSE author: Simon Marlow, David Waern -maintainer: Alec Theriault , Alex Biehl , Simon Hengel , Mateusz Kowalczyk +maintainer: Haddock Team homepage: http://www.haskell.org/haddock/ -bug-reports: https://github.com/haskell/haddock/issues +bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new copyright: (c) Simon Marlow, David Waern category: Documentation build-type: Simple -tested-with: GHC==9.6.* extra-source-files: CHANGES.md @@ -39,6 +38,11 @@ data-files: html/Linuwial.std-theme/synopsis.png latex/haddock.sty +source-repository head + type: git + location: https://gitlab.haskell.org/ghc/ghc.git + subdir: utils/haddock/haddock-api + library default-language: Haskell2010 @@ -203,8 +207,3 @@ test-suite spec build-tool-depends: hspec-discover:hspec-discover ^>= 2.9 - -source-repository head - type: git - subdir: haddock-api - location: https://github.com/haskell/haddock.git ===================================== utils/haddock/haddock-api/resources/html/package.json ===================================== @@ -8,7 +8,8 @@ }, "repository": { "type": "git", - "url": "https://github.com/haskell/haddock.git" + "url": "https://gitlab.haskell.org/ghc/ghc.git" + "directory": "utils/haddock" }, "author": "Tim Baumann ", "contributors": [ ===================================== utils/haddock/haddock-library/haddock-library.cabal ===================================== @@ -2,7 +2,6 @@ cabal-version: 3.0 name: haddock-library version: 1.11.0 synopsis: Library exposing some functionality of Haddock. - description: Haddock is a documentation-generation tool for Haskell libraries. These modules expose some functionality of it without pulling in the GHC @@ -13,16 +12,10 @@ description: Haddock is a documentation-generation tool for Haskell license: BSD-2-Clause license-file: LICENSE -maintainer: Alec Theriault , Alex Biehl , Simon Hengel , Mateusz Kowalczyk +maintainer: Haddock Team homepage: http://www.haskell.org/haddock/ -bug-reports: https://github.com/haskell/haddock/issues +bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new category: Documentation -tested-with: GHC == 8.4.4 - , GHC == 8.6.5 - , GHC == 8.8.3 - , GHC == 8.10.1 - , GHC == 9.0.1 - , GHC == 9.2.0 extra-doc-files: CHANGES.md @@ -31,6 +24,11 @@ extra-source-files: fixtures/examples/*.input fixtures/examples/*.parsed +source-repository head + type: git + location: https://gitlab.haskell.org/ghc/ghc.git + subdir: utils/haddock/haddock-library + common lib-defaults default-language: Haskell2010 @@ -113,8 +111,3 @@ test-suite fixtures , filepath ^>= 1.4.1.2 , optparse-applicative >= 0.15 && < 0.19 , tree-diff ^>= 0.2 || ^>= 0.3 - -source-repository head - type: git - subdir: haddock-library - location: https://github.com/haskell/haddock.git ===================================== utils/haddock/haddock-test/haddock-test.cabal ===================================== @@ -6,11 +6,10 @@ license: BSD-2-Clause author: Simon Marlow, David Waern maintainer: Simon Hengel , Mateusz Kowalczyk homepage: http://www.haskell.org/haddock/ -bug-reports: https://github.com/haskell/haddock/issues +bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new copyright: (c) Simon Marlow, David Waern category: Documentation build-type: Simple -tested-with: GHC==9.6.* stability: experimental library ===================================== utils/haddock/haddock.cabal ===================================== @@ -29,13 +29,12 @@ description: license: BSD-3-Clause license-file: LICENSE author: Simon Marlow, David Waern -maintainer: Alec Theriault , Alex Biehl , Simon Hengel , Mateusz Kowalczyk +maintainer: Haddock Team homepage: http://www.haskell.org/haddock/ -bug-reports: https://github.com/haskell/haddock/issues +bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new copyright: (c) Simon Marlow, David Waern category: Documentation build-type: Simple -tested-with: GHC==9.6.* extra-source-files: CHANGES.md @@ -65,6 +64,11 @@ flag threaded default: True manual: True +source-repository head + type: git + location: https://gitlab.haskell.org/ghc/ghc.git + subdir: utils/haddock + executable haddock default-language: Haskell2010 main-is: Main.hs @@ -193,7 +197,3 @@ test-suite hoogle-test main-is: Main.hs hs-source-dirs: hoogle-test build-depends: base, filepath, haddock-test == 0.0.1 - -source-repository head - type: git - location: https://github.com/haskell/haddock.git View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c8b1473e3cec68b1d3922e9325cc45c98adb12cd...36fafc5becb619b5c597aa853f7d4bec0fe88631 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c8b1473e3cec68b1d3922e9325cc45c98adb12cd...36fafc5becb619b5c597aa853f7d4bec0fe88631 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 15:43:25 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 11 Jun 2024 11:43:25 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/clc275 Message-ID: <6668709d42fd6_1d181b42a5d38230362@gitlab.mail> Ben Gamari pushed new branch wip/clc275 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/clc275 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 15:46:11 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 11 Jun 2024 11:46:11 -0400 Subject: [Git][ghc/ghc][wip/clc275] Add changelog entry Message-ID: <66687143bc353_1d181b43747502333c8@gitlab.mail> Ben Gamari pushed to branch wip/clc275 at Glasgow Haskell Compiler / GHC Commits: 82d50ec4 by Ben Gamari at 2024-06-11T15:46:06+00:00 Add changelog entry - - - - - 1 changed file: - libraries/base/changelog.md Changes: ===================================== libraries/base/changelog.md ===================================== @@ -7,6 +7,7 @@ * Make `read` accept binary integer notation ([CLC proposal #177](https://github.com/haskell/core-libraries-committee/issues/177)) * Improve the performance of `Data.List.sort` using an improved merging strategy. Instead of `compare`, `sort` now uses `(>)` which may break *malformed* `Ord` instances ([CLC proposal #236](https://github.com/haskell/core-libraries-committee/issues/236)) * Add `firstA` and `secondA` to `Data.Bitraversable`. ([CLC proposal #172](https://github.com/haskell/core-libraries-committee/issues/172)) + * `System.IO.Error.ioError` and `Control.Exception.ioError` now both carry `HasCallStack` constraints ([CLC proposal #275](https://github.com/haskell/core-libraries-committee/issues/275)) ## 4.20.0.0 *TBA* * Deprecate `GHC.Pack` ([#21461](https://gitlab.haskell.org/ghc/ghc/-/issues/21461)) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/82d50ec4dc8387ea9ca9a3b601ee8e3e55d3b890 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/82d50ec4dc8387ea9ca9a3b601ee8e3e55d3b890 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 15:53:00 2024 From: gitlab at gitlab.haskell.org (Ben Gamari (@bgamari)) Date: Tue, 11 Jun 2024 11:53:00 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/bdescr/june-2024 Message-ID: <666872dcb3220_1d181b45e8608255535@gitlab.mail> Ben Gamari pushed new branch wip/bdescr/june-2024 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/bdescr/june-2024 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 16:32:29 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 11 Jun 2024 12:32:29 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T24978 Message-ID: <66687c1de2085_1d181b4b750442691ce@gitlab.mail> Simon Peyton Jones pushed new branch wip/T24978 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T24978 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 16:38:01 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 11 Jun 2024 12:38:01 -0400 Subject: [Git][ghc/ghc][wip/T24868] 115 commits: base: specify tie-breaking behavior of min, max, and related list/Foldable functions Message-ID: <66687d69aa01c_1d181b4cd2c9827301e@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24868 at Glasgow Haskell Compiler / GHC Commits: a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00 base: specify tie-breaking behavior of min, max, and related list/Foldable functions - - - - - bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00 cmm: add word <-> double/float bitcast - closes: #25331 This is the last step in the project plan described in #25331. This commit: - adds bitcast operands for x86_64, LLVM, aarch64 - For PPC and i386 we resort to using the cmm implementations - renames conversion MachOps from Conv to Round|Truncate - - - - - f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor Some functions in StgToByteCode were filtering out void arguments. However, StgToByteCode is called after unarisation: the void arguments should have been removed earlier. Instead of filtering out, we assert that the args are non-void. - - - - - 03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor `layoutNativeCall` was always called with a `primRepCmmType platform` callback. Hence we can put it inside of `layoutNativeCall` rather than repeat it. - - - - - 27c430f3 by David Binder at 2024-05-24T07:52:38-04:00 haddock: Remove compatibility shims for GHC < 8.4 from haddock-library - - - - - 8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00 compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs This patch makes the STG->Cmm backend avoid saving foreign call target to local when there are no caller-save GlobalRegs. Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a foreign call, we unconditionally save the foreign call target to a temporary local first, then rely on cmmSink to clean it up later, which only happens with -fcmm-sink (implied by -O) and not in unoptimized code. And this is troublesome for the wasm backend NCG, which needs to infer a foreign call target symbol's type signature from the Cmm call site. Previously, the NCG has been emitting incorrect type signatures for unoptimized code, which happens to work with `wasm-ld` most of the time, but this is never future-proof against upstream toolchain updates, and it causes horrible breakages when LTO objects are included in linker input. Hence this patch. - - - - - 986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00 testsuite: add callee-no-local regression test - - - - - 52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00 Fix HasCallStack leftovers from !12514 / #24726 - - - - - c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00 user_guide: Fix typo in MultiWayIf chapter Close #24829 - - - - - bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - 1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Fix changelog reference to setBacktraceMechanismState (cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d) - - - - - 43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00 Float/double unboxed literal support for HexFloatLiterals (fix #22155) - - - - - 4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00 Improve test labels for binary interface file size tests Test labels for binary interface file sizes are hard to read and overly verbose at the same time. Extend the name for the metric title, but shorten it in the actual comparison table. - - - - - 14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00 Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present" This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa. - - - - - f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00 Fix default hyperlinked sources pattern Previously this didn't include the `%M` token which manifested as broken links to the hyperlinked sources of reexports of declarations defined in other packages. Fixes haddock#1628. (cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36) - - - - - 42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00 Make DocPaths a proper data type (cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c) - - - - - 53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00 haddock: Bump version to 2.30 (cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602) - - - - - e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00 haddock-api: allow base 4.20 and ghc 9.11 - - - - - e294f7a2 by PHO at 2024-05-24T12:17:55-04:00 Add a flag "threaded" for building haddock with the threaded RTS GHC isn't guaranteed to have a threaded RTS. There should be a way to build it with the vanilla one. (cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d) - - - - - 51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00 Update ticky counter event docs. Add the info about the info table address and json fields. Fixes #23200 - - - - - 98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00 Export extractPromotedList (#24866) This can be useful in plugins. - - - - - 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 37f06381 by Simon Peyton Jones at 2024-06-11T12:24:36+01:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - ed82f015 by Simon Peyton Jones at 2024-06-11T12:34:24+01:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 5c9317a0 by Simon Peyton Jones at 2024-06-11T17:37:26+01:00 Wibble - - - - - 30 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f2e10a2ca9132a1670256a1ca9ab6eb2d1177e50...5c9317a0289f9a9cff098c6864bdbc553f06b202 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f2e10a2ca9132a1670256a1ca9ab6eb2d1177e50...5c9317a0289f9a9cff098c6864bdbc553f06b202 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 16:57:39 2024 From: gitlab at gitlab.haskell.org (Jacco Krijnen (@jacco)) Date: Tue, 11 Jun 2024 12:57:39 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/jacco/haddock/running-tests Message-ID: <66688202f2fea_1d181b4fe22e42791c7@gitlab.mail> Jacco Krijnen pushed new branch wip/jacco/haddock/running-tests at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/jacco/haddock/running-tests You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 16:58:25 2024 From: gitlab at gitlab.haskell.org (Jacco Krijnen (@jacco)) Date: Tue, 11 Jun 2024 12:58:25 -0400 Subject: [Git][ghc/ghc][wip/jacco/haddock/running-tests] Document how to run haddocks tests (#24976) Message-ID: <66688231bc2e0_1d181b502870827931f@gitlab.mail> Jacco Krijnen pushed to branch wip/jacco/haddock/running-tests at Glasgow Haskell Compiler / GHC Commits: 80bf8260 by Jacco Krijnen at 2024-06-11T18:58:08+02:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - 2 changed files: - utils/haddock/CONTRIBUTING.md - utils/haddock/cabal.project Changes: ===================================== utils/haddock/CONTRIBUTING.md ===================================== @@ -28,6 +28,17 @@ Then, run the following command from the top-level: $ ./hadrian/build -j --flavour=Quick --freeze1 _build/stage1/bin/haddock ``` +### Running the test suites + +Currently, this cannot be done with hadrian but has to be done with a +`cabal-install` built from `master`. + +``` +cabal test -w /_build/stage1/bin/ghc +``` + +For more details, see https://gitlab.haskell.org/ghc/ghc/-/issues/24976. + ## Working with the codebase The project provides a Makefile with rules to accompany you during development: ===================================== utils/haddock/cabal.project ===================================== @@ -1,5 +1,3 @@ -with-compiler: ghc-9.7 - packages: ./ ./haddock-api ./haddock-library View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/80bf8260b3928a63a31a5485c65be768c6258657 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/80bf8260b3928a63a31a5485c65be768c6258657 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 17:00:53 2024 From: gitlab at gitlab.haskell.org (Jacco Krijnen (@jacco)) Date: Tue, 11 Jun 2024 13:00:53 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/jacco/haddock/codeblock-highlighting Message-ID: <666882c57b2b2_1d181b5093c1027954d@gitlab.mail> Jacco Krijnen pushed new branch wip/jacco/haddock/codeblock-highlighting at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/jacco/haddock/codeblock-highlighting You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 17:03:11 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 11 Jun 2024 13:03:11 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] 11 commits: ttg: Remove SourceText from OverloadedLabel Message-ID: <6668834f34d9b_1d181b518ba3c2828e8@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: bf50e2cb by Adriaan Leijnse at 2024-06-11T18:02:56+01:00 ttg: Remove SourceText from OverloadedLabel Progress towards #21592 - - - - - 2246aaf8 by Alexander Foremny at 2024-06-11T18:02:56+01:00 AST: GHC.Prelude -> Prelude Refactor occurrences to GHC.Prelude with Prelude within Language/Haskell. Progress towards #21592 - - - - - a6ab91fd by Alexander Foremny at 2024-06-11T18:02:56+01:00 AST: remove occurrences of GHC.Unit.Module.ModuleName `GHC.Unit.Module` re-exports `ModuleName` from `Language.Haskell.Syntax.Module.Name`. Progress towards #21592 - - - - - f10ff6cb by Fabian Kirchner at 2024-06-11T18:02:56+01:00 AST: move Data instance definition for ModuleName to GHC.Unit.Types To remove the dependency on GHC.Utils.Misc inside Language.Haskell.Syntax.Module.Name, the instance definition is moved from there into GHC.Unit.Types. Progress towards #21592 - - - - - 36bfdac2 by Fabian Kirchner at 2024-06-11T18:02:57+01:00 AST: move negateOverLitVal into GHC.Hs.Lit The function negateOverLitVal is not used within Language.Haskell and therefore can be moved to the respective module inside GHC.Hs. Progress towards #21592 - - - - - 4880d4a6 by Fabian Kirchner at 2024-06-11T18:02:57+01:00 AST: move conDetailsArity into GHC.Rename.Module The function conDetailsArity is only used inside GHC.Rename.Module. We therefore move it there from Language.Haskell.Syntax.Lit. Progress towards #21592 - - - - - 4f100df4 by Mauricio at 2024-06-11T18:02:57+01:00 AST: Remove GHC.Utils.Assert from GHC Simple cleanup. Progress towards #21592 - - - - - 46c2015b by Fabian Kirchner at 2024-06-11T18:02:57+01:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - 49827d79 by Fabian Kirchner at 2024-06-11T18:02:57+01:00 ttg: Move some AST types into Language.Haskell.Syntax.Basic In particular, we move: * TopLevelFlag * TypeOrData * TyConFlavour Progress towards #21592 - - - - - 836dcb70 by Adowrath at 2024-06-11T18:02:58+01:00 ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type Progress towards #21592 This splits HsSrcBang up, creating the new HsBang within `Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness and strictness information, while `HsSrcBang` only adds the SourceText for usage within the compiler directly. Inside the AST, to preserve the SourceText, it is hidden behind the pre-existing extension point `XBindTy`. All other occurrences of `HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when interacting with the `BindTy` constructor, the hidden `SourceText` is extracted/inserted into the `XBindTy` extension point. `GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for convenience. A constructor function `mkHsSrcBang` that takes all individual components has been added. Two exceptions has been made though: - The `Outputable HsSrcBang` instance is replaced by `Outputable HsBang`. While being only GHC-internal, the only place it's used is in outputting `HsBangTy` constructors -- which already have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just to ignore the `SourceText` anyway. - The error `TcRnUnexpectedAnnotation` did not use the `SourceText`, so it too now only holds a `HsBang`. - - - - - 06bbb4ac by Mauricio at 2024-06-11T18:02:58+01:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/CoreToIface.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Build.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var.hs-boot - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Basic.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/374e13f6adb411de4ff3020a4676fd778fd3473a...06bbb4aceee1aec62993960a656f242e92a78511 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/374e13f6adb411de4ff3020a4676fd778fd3473a...06bbb4aceee1aec62993960a656f242e92a78511 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 18:49:33 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 11 Jun 2024 14:49:33 -0400 Subject: [Git][ghc/ghc][wip/romes/ast-ohne-faststring] 6 commits: A handful of progress Message-ID: <66689c3dada9a_1d181b6063eec2982c9@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ast-ohne-faststring at Glasgow Haskell Compiler / GHC Commits: 97fee659 by Rodrigo Mesquita at 2024-06-10T19:28:32+02:00 A handful of progress - - - - - b7e90ce1 by Rodrigo Mesquita at 2024-06-10T19:55:35+02:00 more - - - - - d93f3bbf by Rodrigo Mesquita at 2024-06-10T19:57:21+02:00 CType Text rather than FastString Todo: maybe don't use decode/encode utf8 in binary instance? - - - - - 673aaf23 by Rodrigo Mesquita at 2024-06-10T20:07:00+02:00 Parser getSTRING progress - - - - - 67efb99d by Rodrigo Mesquita at 2024-06-10T20:15:29+02:00 HsLit Text-backed Strings - - - - - 254e565f by Rodrigo Mesquita at 2024-06-11T19:49:22+01:00 the biggest boy - - - - - 30 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Data/FastString.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Pmc/Solver/Types.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Errors/Ppr.hs - compiler/GHC/Parser/Errors/Types.hs - compiler/GHC/Parser/HaddockLex.x - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/ForeignCall.hs - compiler/GHC/Types/Literal.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/373fc01607be18425f3f3cd2b690d72c41efd297...254e565f44fc7fc34263c150abf8d589489822dc -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/373fc01607be18425f3f3cd2b690d72c41efd297...254e565f44fc7fc34263c150abf8d589489822dc You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 20:35:04 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 11 Jun 2024 16:35:04 -0400 Subject: [Git][ghc/ghc][wip/T24978] Wibbles Message-ID: <6668b4f864e91_1d181b6cf40f830174e@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24978 at Glasgow Haskell Compiler / GHC Commits: 777c1ad6 by Simon Peyton Jones at 2024-06-11T21:34:37+01:00 Wibbles - - - - - 3 changed files: - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/Types/Var.hs Changes: ===================================== compiler/GHC/Core/TyCo/Rep.hs ===================================== @@ -990,6 +990,22 @@ instance Outputable FunSel where ppr SelArg = text "arg" ppr SelRes = text "res" +instance Binary UnivCoProvenance where + put_ bh PhantomProv = putByte bh 1 + put_ bh ProofIrrelProv = putByte bh 2 + put_ bh (PluginProv a) = do { putByte bh 3 + ; put_ bh a } + + get bh = do + tag <- getByte bh + case tag of + 1 -> return PhantomProv + 2 -> return ProofIrrelProv + 3 -> do a <- get bh + return $ PluginProv a + _ -> panic ("get UnivCoProvenance " ++ show tag) + + instance Binary CoSel where put_ bh (SelTyCon n r) = do { putByte bh 0; put_ bh n; put_ bh r } put_ bh SelForAll = putByte bh 1 ===================================== compiler/GHC/Iface/Type.hs ===================================== @@ -2477,22 +2477,6 @@ instance Binary IfaceCoercion where return $ IfaceAxiomRuleCo a b _ -> panic ("get IfaceCoercion " ++ show tag) -instance Binary UnivCoProvenance where - put_ bh PhantomProv = putByte bh 1 - put_ bh ProofIrrelProv = putByte bh 2 - put_ bh (PluginProv a) = do { putByte bh 3 - ; put_ bh a } - - get bh = do - tag <- getByte bh - case tag of - 1 -> return PhantomProv - 2 -> return ProofIrrelProv - 3 -> do a <- get bh - return $ PluginProv a - _ -> panic ("get IfaceUnivCoProv " ++ show tag) - - instance Binary (DefMethSpec IfaceType) where put_ bh VanillaDM = putByte bh 0 put_ bh (GenericDM t) = putByte bh 1 >> put_ bh t ===================================== compiler/GHC/Types/Var.hs ===================================== @@ -377,7 +377,7 @@ instance NamedThing Var where instance NFData Var where rnf v = v `seq` () - + instance Uniquable Var where getUnique = varUnique View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/777c1ad62f6aa3d1738644d23ea8fa67993603d2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/777c1ad62f6aa3d1738644d23ea8fa67993603d2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 21:28:20 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 11 Jun 2024 17:28:20 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] 11 commits: ttg: Remove SourceText from OverloadedLabel Message-ID: <6668c1746e54_1d181b73b606c30241@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: ca8f2f50 by Adriaan Leijnse at 2024-06-11T22:28:07+01:00 ttg: Remove SourceText from OverloadedLabel Progress towards #21592 - - - - - d57b8d16 by Alexander Foremny at 2024-06-11T22:28:07+01:00 AST: GHC.Prelude -> Prelude Refactor occurrences to GHC.Prelude with Prelude within Language/Haskell. Progress towards #21592 - - - - - a8e5d827 by Alexander Foremny at 2024-06-11T22:28:07+01:00 AST: remove occurrences of GHC.Unit.Module.ModuleName `GHC.Unit.Module` re-exports `ModuleName` from `Language.Haskell.Syntax.Module.Name`. Progress towards #21592 - - - - - 092be2da by Fabian Kirchner at 2024-06-11T22:28:07+01:00 AST: move Data instance definition for ModuleName to GHC.Unit.Types To remove the dependency on GHC.Utils.Misc inside Language.Haskell.Syntax.Module.Name, the instance definition is moved from there into GHC.Unit.Types. Progress towards #21592 - - - - - aad9db93 by Fabian Kirchner at 2024-06-11T22:28:07+01:00 AST: move negateOverLitVal into GHC.Hs.Lit The function negateOverLitVal is not used within Language.Haskell and therefore can be moved to the respective module inside GHC.Hs. Progress towards #21592 - - - - - 049aa8b1 by Fabian Kirchner at 2024-06-11T22:28:07+01:00 AST: move conDetailsArity into GHC.Rename.Module The function conDetailsArity is only used inside GHC.Rename.Module. We therefore move it there from Language.Haskell.Syntax.Lit. Progress towards #21592 - - - - - c272ed94 by Mauricio at 2024-06-11T22:28:07+01:00 AST: Remove GHC.Utils.Assert from GHC Simple cleanup. Progress towards #21592 - - - - - 48c4eedb by Fabian Kirchner at 2024-06-11T22:28:07+01:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - c4540fef by Fabian Kirchner at 2024-06-11T22:28:08+01:00 ttg: Move some AST types into Language.Haskell.Syntax.Basic In particular, we move: * TopLevelFlag * TypeOrData * TyConFlavour Progress towards #21592 - - - - - 06cc0692 by Adowrath at 2024-06-11T22:28:08+01:00 ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type Progress towards #21592 This splits HsSrcBang up, creating the new HsBang within `Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness and strictness information, while `HsSrcBang` only adds the SourceText for usage within the compiler directly. Inside the AST, to preserve the SourceText, it is hidden behind the pre-existing extension point `XBindTy`. All other occurrences of `HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when interacting with the `BindTy` constructor, the hidden `SourceText` is extracted/inserted into the `XBindTy` extension point. `GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for convenience. A constructor function `mkHsSrcBang` that takes all individual components has been added. Two exceptions has been made though: - The `Outputable HsSrcBang` instance is replaced by `Outputable HsBang`. While being only GHC-internal, the only place it's used is in outputting `HsBangTy` constructors -- which already have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just to ignore the `SourceText` anyway. - The error `TcRnUnexpectedAnnotation` did not use the `SourceText`, so it too now only holds a `HsBang`. - - - - - b6c6b315 by Mauricio at 2024-06-11T22:28:08+01:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/CoreToIface.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/TyCl.hs - compiler/GHC/Tc/TyCl/Build.hs - compiler/GHC/Tc/Types/Origin.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/Id/Make.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var.hs-boot - compiler/GHC/Unit/Types.hs - compiler/Language/Haskell/Syntax/Basic.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/06bbb4aceee1aec62993960a656f242e92a78511...b6c6b315ecd0df35c87cb6d1a64edbcbfca55002 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/06bbb4aceee1aec62993960a656f242e92a78511...b6c6b315ecd0df35c87cb6d1a64edbcbfca55002 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 22:01:07 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 11 Jun 2024 18:01:07 -0400 Subject: [Git][ghc/ghc][wip/T24978] Wibble Message-ID: <6668c923b202c_12d7f715915482338@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24978 at Glasgow Haskell Compiler / GHC Commits: 252f2991 by Simon Peyton Jones at 2024-06-11T23:00:52+01:00 Wibble - - - - - 1 changed file: - compiler/GHC/Tc/Utils/TcMType.hs Changes: ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -1564,9 +1564,10 @@ collect_cand_qtvs_co orig_ty cur_lvl bound = go_co go_co dv (FunCo _ _ _ w co1 co2) = foldlM go_co dv [w, co1, co2] go_co dv (AxiomInstCo _ _ cos) = foldlM go_co dv cos go_co dv (AxiomRuleCo _ cos) = foldlM go_co dv cos - go_co dv (UnivCo { uco_lty = t1, uco_rty = t2 }) + go_co dv (UnivCo { uco_lty = t1, uco_rty = t2, uco_cvs = cvs }) = do { dv1 <- collect_cand_qtvs orig_ty True cur_lvl bound dv t1 - ; collect_cand_qtvs orig_ty True cur_lvl bound dv1 t2 } + ; dv2 <- collect_cand_qtvs orig_ty True cur_lvl bound dv1 t2 + ; strictFoldDVarSet zt_cv (return dv2) cvs } go_co dv (SymCo co) = go_co dv co go_co dv (TransCo co1 co2) = foldlM go_co dv [co1, co2] go_co dv (SelCo _ co) = go_co dv co View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/252f2991c2e031586bb6869129bd51f0300a344c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/252f2991c2e031586bb6869129bd51f0300a344c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 11 22:18:15 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 11 Jun 2024 18:18:15 -0400 Subject: [Git][ghc/ghc][wip/T24978] Wibble imports Message-ID: <6668cd27a077c_12d7f73a1eac82853@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24978 at Glasgow Haskell Compiler / GHC Commits: 401dea0a by Simon Peyton Jones at 2024-06-11T23:18:02+01:00 Wibble imports - - - - - 3 changed files: - compiler/GHC/Tc/TyCl/Utils.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs Changes: ===================================== compiler/GHC/Tc/TyCl/Utils.hs ===================================== @@ -39,7 +39,7 @@ import GHC.Builtin.Uniques ( mkBuiltinUnique ) import GHC.Hs -import GHC.Core.TyCo.Rep( Type(..), Coercion(..), MCoercion(..), UnivCoProvenance(..) ) +import GHC.Core.TyCo.Rep( Type(..), Coercion(..), MCoercion(..) ) import GHC.Core.Multiplicity import GHC.Core.Predicate import GHC.Core.Make( rEC_SEL_ERROR_ID ) ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Create.hs ===================================== @@ -57,7 +57,6 @@ import Data.Traversable (for) import Control.Arrow (first, (&&&)) import GHC hiding (lookupName) import GHC.Builtin.Names -import GHC.Builtin.Types import GHC.Builtin.Types.Prim import GHC.Core.ConLike (ConLike (..)) import GHC.Data.FastString (FastString, bytesFS, unpackFS) @@ -65,7 +64,6 @@ import GHC.Driver.Ppr import GHC.HsToCore.Docs hiding (mkMaps) import GHC.Iface.Syntax import GHC.Types.Avail -import GHC.Types.Basic import GHC.Types.Name import GHC.Types.Name.Set import GHC.Types.SafeHaskell ===================================== utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs ===================================== @@ -56,7 +56,7 @@ import GHC.Types.Unique.FM import GHC.Unit.State import GHC.Utils.Binary -import GHC.Iface.Type (IfaceType, getIfaceType, putIfaceType) +import GHC.Iface.Type (IfaceType, putIfaceType) import Haddock.Options (Visibility (..)) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/401dea0a019e0469c99f44b9747a130c5e130845 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/401dea0a019e0469c99f44b9747a130c5e130845 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 03:29:31 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Tue, 11 Jun 2024 23:29:31 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/fabu/T24026-early-reject-type-failing-rules Message-ID: <6669161be030d_12d7f728f7c9c1021f8@gitlab.mail> Fabricio Nascimento pushed new branch wip/fabu/T24026-early-reject-type-failing-rules at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fabu/T24026-early-reject-type-failing-rules You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 03:49:40 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Tue, 11 Jun 2024 23:49:40 -0400 Subject: [Git][ghc/ghc][wip/fabu/T24026-early-reject-type-failing-rules] compiler: Rejects RULES whose LHS immediately fails to type-check Message-ID: <66691ad490d27_12d7f72c44c881112a8@gitlab.mail> Fabricio Nascimento pushed to branch wip/fabu/T24026-early-reject-type-failing-rules at Glasgow Haskell Compiler / GHC Commits: fbcdad20 by Fabricio de Sousa Nascimento at 2024-06-12T12:48:34+09:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - 7 changed files: - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/Tc/Gen/Rule.hs - + testsuite/tests/typecheck/T24026/T24026a.hs - + testsuite/tests/typecheck/T24026/T24026a.stderr - + testsuite/tests/typecheck/T24026/T24026b.hs - + testsuite/tests/typecheck/T24026/T24026b.stderr - + testsuite/tests/typecheck/T24026/all.T Changes: ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -1032,8 +1032,8 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs where extra_tvs = [ v | v <- extra_vars, isTyVar v ] extra_dicts = - [ mkLocalId (localiseName (idName d)) ManyTy (idType d) - | d <- extra_vars, isDictId d ] + [ mkLocalIdOrCoVar (localiseName (idName d)) ManyTy (idType d) + | d <- extra_vars, isEvVar d ] extra_vars = [ v | v <- exprsFreeVarsList args ===================================== compiler/GHC/Tc/Gen/Rule.hs ===================================== @@ -108,11 +108,12 @@ tcRules decls = mapM (wrapLocMA tcRuleDecls) decls tcRuleDecls :: RuleDecls GhcRn -> TcM (RuleDecls GhcTc) tcRuleDecls (HsRules { rds_ext = src , rds_rules = decls }) - = do { tc_decls <- mapM (wrapLocMA tcRule) decls + = do { tc_decls_list <- mapM (wrapLocMA tcRule) decls + ; let tc_decls = concatMap (\(L loc e) -> map (L loc) e) tc_decls_list ; return $ HsRules { rds_ext = src , rds_rules = tc_decls } } -tcRule :: RuleDecl GhcRn -> TcM (RuleDecl GhcTc) +tcRule :: RuleDecl GhcRn -> TcM ([RuleDecl GhcTc]) tcRule (HsRule { rd_ext = ext , rd_name = rname@(L _ name) , rd_act = act @@ -181,14 +182,20 @@ tcRule (HsRule { rd_ext = ext ; (rhs_implic, rhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs rhs_wanted ; emitImplications (lhs_implic `unionBags` rhs_implic) - ; return $ HsRule { rd_ext = ext + -- This prevents GHC to crash downstream trying to apply a RULE that won't type check. + -- For example when we turn on `-fdefer-type-errors` on an invalid rule. See #24026. + ; if anyBag insolubleImplic lhs_implic + then + return [] + else + return $ [HsRule { rd_ext = ext , rd_name = rname , rd_act = act , rd_tyvs = ty_bndrs -- preserved for ppr-ing , rd_tmvs = map (noLocA . RuleBndr noAnn . noLocA) (qtkvs ++ tpl_ids) , rd_lhs = mkHsDictLet lhs_binds lhs' - , rd_rhs = mkHsDictLet rhs_binds rhs' } } + , rd_rhs = mkHsDictLet rhs_binds rhs' } ]} generateRuleConstraints :: FastString -> Maybe [LHsTyVarBndr () GhcRn] -> [LRuleBndr GhcRn] ===================================== testsuite/tests/typecheck/T24026/T24026a.hs ===================================== @@ -0,0 +1,6 @@ +module T24026a where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026a.stderr ===================================== @@ -0,0 +1,9 @@ +T24026a.hs:3:11: warning: [GHC-95396] [-Winline-rule-shadowing (in -Wdefault)] + Rule "f" may never fire because ‘f’ might inline first + Suggested fix: Add an INLINE[n] or NOINLINE[n] pragma for ‘f’ + +T24026a.hs:3:37: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/T24026b.hs ===================================== @@ -0,0 +1,6 @@ +module T24026b where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026b.stderr ===================================== @@ -0,0 +1,5 @@ +T24026b.hs:3:37: error: [GHC-83865] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/all.T ===================================== @@ -0,0 +1,2 @@ +test('T24026a', normal, compile, ['-dlint -fdefer-type-errors']) +test('T24026b', normal, compile_fail, ['']) \ No newline at end of file View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fbcdad20e1dffd012559332e21e793f4ccf61cc3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fbcdad20e1dffd012559332e21e793f4ccf61cc3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 06:33:47 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Wed, 12 Jun 2024 02:33:47 -0400 Subject: [Git][ghc/ghc][wip/romes/ast-ohne-faststring] the biggest boy Message-ID: <6669414b30dd4_12d7f740d88201167b@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ast-ohne-faststring at Glasgow Haskell Compiler / GHC Commits: d9408cc5 by Rodrigo Mesquita at 2024-06-12T07:33:23+01:00 the biggest boy - - - - - 27 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Foreign/C.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Match/Literal.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Header.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/ThToHs.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/Lit.hs - utils/check-exact/ExactPrint.hs - utils/check-exact/check-exact.cabal - utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs - utils/haddock/haddock-api/src/Haddock/Convert.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -2031,7 +2031,7 @@ pprUntypedSplice True n (HsUntypedSpliceExpr _ e) = ppr_splice (text "$") n e pprUntypedSplice False n (HsUntypedSpliceExpr _ e) = ppr_splice empty n e pprUntypedSplice _ _ (HsQuasiQuote _ q s) = ppr_quasi q (unLoc s) -ppr_quasi :: OutputableBndr p => p -> FastString -> SDoc +ppr_quasi :: OutputableBndr p => p -> T.Text -> SDoc ppr_quasi quoter quote = char '[' <> ppr quoter <> vbar <> ppr quote <> text "|]" @@ -2411,6 +2411,7 @@ type instance Anno (FieldLabelStrings (GhcPass p)) = EpAnnCO type instance Anno FieldLabelString = SrcSpanAnnN type instance Anno FastString = EpAnnCO +type instance Anno T.Text = EpAnnCO -- Used in HsQuasiQuote and perhaps elsewhere type instance Anno (DotFieldOcc (GhcPass p)) = EpAnnCO ===================================== compiler/GHC/Hs/Lit.hs ===================================== @@ -37,7 +37,6 @@ import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Lit import qualified Data.Text as T -import GHC.Data.FastString (unpackFS) {- ************************************************************************ @@ -223,7 +222,7 @@ instance OutputableBndrId p instance Outputable OverLitVal where ppr (HsIntegral i) = pprWithSourceText (il_text i) (integer (il_value i)) ppr (HsFractional f) = ppr f - ppr (HsIsString st s) = pprWithSourceText st (pprHsString (unpackFS s)) + ppr (HsIsString st s) = pprWithSourceText st (pprHsString (T.unpack s)) -- | pmPprHsLit pretty prints literals and is used when pretty printing pattern -- match warnings. All are printed the same (i.e., without hashes if they are ===================================== compiler/GHC/Hs/Utils.hs ===================================== @@ -331,7 +331,7 @@ nlParPat p = noLocA (gParPat p) mkHsIntegral :: IntegralLit -> HsOverLit GhcPs mkHsFractional :: FractionalLit -> HsOverLit GhcPs -mkHsIsString :: SourceText -> FastString -> HsOverLit GhcPs +mkHsIsString :: SourceText -> T.Text -> HsOverLit GhcPs mkHsDo :: HsDoFlavour -> LocatedL [ExprLStmt GhcPs] -> HsExpr GhcPs mkHsDoAnns :: HsDoFlavour -> LocatedL [ExprLStmt GhcPs] -> AnnList -> HsExpr GhcPs mkHsComp :: HsDoFlavour -> [ExprLStmt GhcPs] -> LHsExpr GhcPs ===================================== compiler/GHC/HsToCore/Expr.hs ===================================== @@ -69,6 +69,7 @@ import GHC.Utils.Panic import GHC.Core.PatSyn import Control.Monad import GHC.Types.Error +import GHC.Data.FastString {- ************************************************************************ @@ -611,7 +612,7 @@ ds_prag_expr (HsPragSCC _ cc) expr = do then do mod_name <- getModule count <- goptM Opt_ProfCountEntries - let nm = sl_fs cc + let nm = mkFastStringText $ sl_fs cc flavour <- mkExprCCFlavour <$> getCCIndexDsM nm Tick (ProfNote (mkUserCC nm mod_name (getLocA expr) flavour) count True) <$> dsLExpr expr ===================================== compiler/GHC/HsToCore/Foreign/C.hs ===================================== @@ -60,6 +60,7 @@ import GHC.Utils.Encoding import Data.Maybe import Data.List (nub) +import qualified Data.Text as T dsCFExport:: Id -- Either the exported Id, -- or the foreign-export-dynamic constructor @@ -344,7 +345,7 @@ toCType = f False -- anything, as it may be the synonym that is annotated. | Just tycon <- tyConAppTyConPicky_maybe t , Just (CType _ mHeader (_,cType)) <- tyConCType_maybe tycon - = (mHeader, ftext cType) + = (mHeader, text $ T.unpack cType) -- If we don't know a C type for this type, then try looking -- through one layer of type synonym etc. | Just t' <- coreView t ===================================== compiler/GHC/HsToCore/Match.hs ===================================== @@ -1292,7 +1292,7 @@ patGroup _ (NPat _ (L _ (OverLit {ol_val=oval})) mb_neg _) = | is_neg -> PgN $! negateFractionalLit f | otherwise -> PgN f (HsIsString _ s, _) -> assert (isNothing mb_neg) $ - PgOverS s + PgOverS (mkFastStringText s) patGroup _ (NPlusKPat _ _ (L _ (OverLit {ol_val=oval})) _ _ _) = case oval of HsIntegral i -> PgNpK (il_value i) ===================================== compiler/GHC/HsToCore/Match/Literal.hs ===================================== @@ -71,6 +71,8 @@ import Control.Monad import Data.Int import Data.List.NonEmpty (NonEmpty(..)) import qualified Data.List.NonEmpty as NEL +import qualified Data.Text as T +import qualified Data.Text.Encoding as T import Data.Word import GHC.Real ( Ratio(..), numerator, denominator ) @@ -120,7 +122,7 @@ dsLit l = do HsFloatPrim _ fl -> return (Lit (LitFloat (rationalFromFractionalLit fl))) HsDoublePrim _ fl -> return (Lit (LitDouble (rationalFromFractionalLit fl))) HsChar _ c -> return (mkCharExpr c) - HsString _ str -> mkStringExprFS str + HsString _ str -> mkStringExprFS (mkFastStringText str) HsInteger _ i _ -> return (mkIntegerExpr platform i) HsInt _ i -> return (mkIntExpr platform (il_value i)) HsRat _ fl ty -> dsFractionalLitToRational fl ty @@ -538,10 +540,10 @@ tidyLitPat :: HsLit GhcTc -> Pat GhcTc -- * We get rid of HsChar right here tidyLitPat (HsChar src c) = unLoc (mkCharLitPat src c) tidyLitPat (HsString src s) - | lengthFS s <= 1 -- Short string literals only + | T.length s <= 1 -- Short string literals only = unLoc $ foldr (\c pat -> mkPrefixConPat consDataCon [mkCharLitPat src c, pat] [charTy]) - (mkNilPat charTy) (unpackFS s) + (mkNilPat charTy) (T.unpack s) -- The stringTy is the type of the whole pattern, not -- the type to instantiate (:) or [] with! tidyLitPat lit = LitPat noExtField lit @@ -588,7 +590,7 @@ tidyNPat (OverLit (OverLitTc False _ ty) val) mb_neg _eq outer_ty (Just _, HsIntegral i) -> Just (-(il_value i)) _ -> Nothing - mb_str_lit :: Maybe FastString + mb_str_lit :: Maybe T.Text mb_str_lit = case (mb_neg, val) of (Nothing, HsIsString _ s) -> Just s _ -> Nothing @@ -670,7 +672,7 @@ hsLitKey _ (HsCharPrim _ c) = mkLitChar c hsLitKey _ (HsFloatPrim _ fl) = mkLitFloat (rationalFromFractionalLit fl) hsLitKey _ (HsDoublePrim _ fl) = mkLitDouble (rationalFromFractionalLit fl) -hsLitKey _ (HsString _ s) = LitString (bytesFS s) +hsLitKey _ (HsString _ s) = LitString (T.encodeUtf8 s) hsLitKey _ l = pprPanic "hsLitKey" (ppr l) {- ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -99,6 +99,7 @@ import Data.Function import Control.Monad.Trans.Reader import Control.Monad.Trans.Class import GHC.Types.Name.Reader (RdrName(..)) +import qualified Data.Text as T data MetaWrappers = MetaWrappers { -- Applies its argument to a type argument `m` and dictionary `Quote m` @@ -1132,7 +1133,7 @@ rep_sccFun nm Nothing loc = do rep_sccFun nm (Just (L _ str)) loc = do nm1 <- lookupLOcc nm - str1 <- coreStringLit (sl_fs str) + str1 <- coreStringLit (mkFastStringText $ sl_fs str) scc <- repPragSCCFunNamed nm1 str1 return [(loc, scc)] @@ -1477,7 +1478,7 @@ repTyLit :: HsTyLit (GhcPass p) -> MetaM (Core (M TH.TyLit)) repTyLit (HsNumTy _ i) = do platform <- getPlatform rep2 numTyLitName [mkIntegerExpr platform i] -repTyLit (HsStrTy _ s) = do { s' <- mkStringExprFS s +repTyLit (HsStrTy _ s) = do { s' <- mkStringExprFS (mkFastStringText s) ; rep2 strTyLitName [s'] } repTyLit (HsCharTy _ c) = do { c' <- return (mkCharExpr c) @@ -1909,7 +1910,7 @@ rep_implicit_param_bind (L loc (IPBind _ (L _ n) (L _ rhs))) ; return (locA loc, ipb) } rep_implicit_param_name :: HsIPName -> MetaM (Core String) -rep_implicit_param_name (HsIPName name) = coreStringLit name +rep_implicit_param_name (HsIPName name) = coreStringLit (mkFastStringText name) rep_val_binds :: HsValBinds GhcRn -> MetaM [(SrcSpan, Core (M TH.Dec))] -- Assumes: all the binders of the binding are already in the meta-env @@ -3001,7 +3002,7 @@ mk_integer i = return $ HsInteger NoSourceText i integerTy mk_rational :: FractionalLit -> MetaM (HsLit GhcRn) mk_rational r = do rat_ty <- lookupType rationalTyConName return $ HsRat noExtField r rat_ty -mk_string :: FastString -> MetaM (HsLit GhcRn) +mk_string :: T.Text -> MetaM (HsLit GhcRn) mk_string s = return $ HsString NoSourceText s mk_char :: Char -> MetaM (HsLit GhcRn) ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -52,6 +52,9 @@ module GHC.Iface.Syntax ( import GHC.Prelude import GHC.Data.FastString +import Data.Text (Text) +import qualified Data.Text as T +import qualified Data.Text.Encoding as T import GHC.Builtin.Names ( unrestrictedFunTyConKey, liftedTypeKindTyConKey, constraintKindTyConKey ) import GHC.Types.Unique ( hasKey ) @@ -369,7 +372,7 @@ data IfaceWarningTxt | IfDeprecatedTxt SourceText [(IfaceStringLiteral, [IfExtName])] data IfaceStringLiteral - = IfStringLiteral SourceText FastString + = IfStringLiteral SourceText Text data IfaceAnnotation = IfaceAnnotation { @@ -612,7 +615,7 @@ fromIfaceStringLiteralWithNames :: (IfaceStringLiteral, [IfExtName]) -> WithHsDo fromIfaceStringLiteralWithNames (str, names) = WithHsDocIdentifiers (fromIfaceStringLiteral str) (map noLoc names) fromIfaceStringLiteral :: IfaceStringLiteral -> StringLiteral -fromIfaceStringLiteral (IfStringLiteral st fs) = StringLiteral st (fastStringToText fs) Nothing +fromIfaceStringLiteral (IfStringLiteral st fs) = StringLiteral st fs Nothing {- @@ -783,7 +786,7 @@ instance Outputable IfaceWarningTxt where pp_with_name = ppr . fst instance Outputable IfaceStringLiteral where - ppr (IfStringLiteral st fs) = pprWithSourceText st (ftext fs) + ppr (IfStringLiteral st fs) = pprWithSourceText st (text $ T.unpack fs) instance Outputable IfaceAnnotation where ppr (IfaceAnnotation target value) = ppr target <+> colon <+> ppr value @@ -2358,8 +2361,8 @@ instance Binary IfaceWarningTxt where _ -> pure IfDeprecatedTxt <*> get bh <*> get bh instance Binary IfaceStringLiteral where - put_ bh (IfStringLiteral a1 a2) = put_ bh a1 *> put_ bh a2 - get bh = IfStringLiteral <$> get bh <*> get bh + put_ bh (IfStringLiteral a1 a2) = put_ bh a1 *> put_ bh (T.encodeUtf8 a2) + get bh = IfStringLiteral <$> get bh <*> (T.decodeUtf8 <$> get bh) instance Binary IfaceAnnotation where put_ bh (IfaceAnnotation a1 a2) = do ===================================== compiler/GHC/Parser.y ===================================== @@ -2744,8 +2744,8 @@ explicit_activation :: { ([AddEpAnn],Activation) } -- In brackets quasiquote :: { Located (HsUntypedSplice GhcPs) } : TH_QUASIQUOTE { let { loc = getLoc $1 ; ITquasiQuote (quoter, quote, quoteSpan) = unLoc $1 - ; quoterId = mkUnqual varName quoter } - in sL1 $1 (HsQuasiQuote noExtField quoterId (L (noAnnSrcSpan (mkSrcSpanPs quoteSpan)) quote)) } +; quoterId = mkUnqual varName quoter } +in sL1 $1 (HsQuasiQuote noExtField quoterId (L (noAnnSrcSpan (mkSrcSpanPs quoteSpan)) quote)) } | TH_QQUASIQUOTE { let { loc = getLoc $1 ; ITqQuasiQuote (qual, quoter, quote, quoteSpan) = unLoc $1 ; quoterId = mkQual varName (qual, quoter) } @@ -3982,7 +3982,7 @@ consym :: { LocatedN RdrName } literal :: { Located (HsLit GhcPs) } : CHAR { sL1 $1 $ HsChar (getCHARs $1) $ getCHAR $1 } | STRING { sL1 $1 $ HsString (getSTRINGs $1) - $ getSTRING $1 } + $ T.pack $ getSTRING $1 } | PRIMINTEGER { sL1 $1 $ HsIntPrim (getPRIMINTEGERs $1) $ getPRIMINTEGER $1 } | PRIMWORD { sL1 $1 $ HsWordPrim (getPRIMWORDs $1) @@ -4148,7 +4148,7 @@ getOVERLAPS_PRAGs (L _ (IToverlaps_prag src)) = src getINCOHERENT_PRAGs (L _ (ITincoherent_prag src)) = src getCTYPEs (L _ (ITctype src)) = src -getStringLiteral l = StringLiteral (getSTRINGs l) (getSTRING l) Nothing +getStringLiteral l = StringLiteral (getSTRINGs l) (T.pack $ getSTRING l) Nothing isUnicode :: Located Token -> Bool isUnicode (L _ (ITforall iu)) = iu == UnicodeSyntax ===================================== compiler/GHC/Parser/Header.hs ===================================== @@ -139,7 +139,7 @@ mkPrelImports this_mod loc implicit_prelude import_decls -- allow explicit "base" package qualifier (#19082, #17045) && case ideclPkgQual decl of NoRawPkgQual -> True - RawPkgQual b -> sl_fs b == unitIdFS baseUnitId + RawPkgQual b -> sl_fs b == fastStringToText (unitIdFS baseUnitId) loc' = noAnnSrcSpan loc ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -984,11 +984,11 @@ data Token | ITdollar -- prefix $ | ITdollardollar -- prefix $$ | ITtyQuote -- '' - | ITquasiQuote (FastString,FastString,PsSpan) + | ITquasiQuote (FastString,Text,PsSpan) -- ITquasiQuote(quoter, quote, loc) -- represents a quasi-quote of the form -- [quoter| quote |] - | ITqQuasiQuote (FastString,FastString,FastString,PsSpan) + | ITqQuasiQuote (FastString,FastString,Text,PsSpan) -- ITqQuasiQuote(Qual, quoter, quote, loc) -- represents a qualified quasi-quote of the form -- [Qual.quoter| quote |] @@ -1720,7 +1720,7 @@ qvarid, qconid :: StringBuffer -> Int -> Token qvarid buf len = ITqvarid $! splitQualName buf len False qconid buf len = ITqconid $! splitQualName buf len False -splitQualName :: StringBuffer -> Int -> Bool -> (FastString,FastString) +splitQualName :: StringBuffer -> Int -> Bool -> (FastString, FastString) -- takes a StringBuffer and a length, and returns the module name -- and identifier parts of a qualified name. Splits at the *last* dot, -- because of hierarchical module names. @@ -2491,7 +2491,7 @@ lex_qquasiquote_tok span buf len _buf2 = do return (L (mkPsSpan (psSpanStart span) end) (ITqQuasiQuote (qual, quoter, - mkFastString (reverse quote), + T.pack (reverse quote), mkPsSpan quoteStart end))) lex_quasiquote_tok :: Action @@ -2504,7 +2504,7 @@ lex_quasiquote_tok span buf len _buf2 = do end <- getParsedLoc return (L (mkPsSpan (psSpanStart span) end) (ITquasiQuote (mkFastString quoter, - mkFastString (reverse quote), + T.pack (reverse quote), mkPsSpan quoteStart end))) lex_quasiquote :: RealSrcLoc -> String -> P String ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -364,7 +364,7 @@ rnExpr (HsOverLabel src v) , fvs ) } where hs_ty_arg = mkEmptyWildCardBndrs $ wrapGenSpan $ - HsTyLit noExtField (HsStrTy NoSourceText (mkFastStringText v)) + HsTyLit noExtField (HsStrTy NoSourceText v) rnExpr (HsLit x lit@(HsString src s)) = do { opt_OverloadedStrings <- xoptM LangExt.OverloadedStrings ===================================== compiler/GHC/Rename/Names.hs ===================================== @@ -446,7 +446,7 @@ rnImportDecl this_mod renameRawPkgQual :: UnitEnv -> ModuleName -> RawPkgQual -> PkgQual renameRawPkgQual unit_env mn = \case NoRawPkgQual -> NoPkgQual - RawPkgQual p -> renamePkgQual unit_env mn (Just (sl_fs p)) + RawPkgQual p -> renamePkgQual unit_env mn (Just (mkFastStringText $ sl_fs p)) -- | Rename raw package imports renamePkgQual :: UnitEnv -> ModuleName -> Maybe FastString -> PkgQual ===================================== compiler/GHC/Rename/Splice.hs ===================================== @@ -70,6 +70,7 @@ import GHCi.RemoteTypes ( ForeignRef ) import qualified GHC.Internal.TH.Syntax as TH (Q) import qualified GHC.LanguageExtensions as LangExt +import qualified Data.Text as T {- ************************************************************************ @@ -414,7 +415,7 @@ makePending flavour n (HsQuasiQuote _ quoter quote) ------------------ mkQuasiQuoteExpr :: UntypedSpliceFlavour -> Name - -> XRec GhcPs FastString + -> XRec GhcPs T.Text -> LHsExpr GhcRn -- Return the expression (quoter "...quote...") -- which is what we must run in a quasi-quote ===================================== compiler/GHC/Rename/Utils.hs ===================================== @@ -748,7 +748,7 @@ genHsIntegralLit :: (NoAnn an) => IntegralLit -> LocatedAn an (HsExpr GhcRn) genHsIntegralLit = genLHsLit . HsInt noExtField genHsTyLit :: FastString -> HsType GhcRn -genHsTyLit = HsTyLit noExtField . HsStrTy NoSourceText +genHsTyLit = HsTyLit noExtField . HsStrTy NoSourceText . fastStringToText genSimpleConPat :: Name -> [LPat GhcRn] -> LPat GhcRn -- The pattern (C p1 .. pn) ===================================== compiler/GHC/Tc/Gen/Bind.hs ===================================== @@ -690,7 +690,7 @@ funBindTicks loc fun_id mod sigs -- by the renamer , let cc_str | Just cc_str <- mb_cc_str - = sl_fs $ unLoc cc_str + = mkFastStringText $ sl_fs $ unLoc cc_str | otherwise = getOccFS (Var.varName fun_id) cc_name = concatFS [moduleNameFS (moduleName mod), fsLit ".", cc_str] ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -1225,7 +1225,7 @@ tcHsType _ rn_ty@(HsTyLit _ (HsNumTy _ n)) exp_kind tcHsType _ rn_ty@(HsTyLit _ (HsStrTy _ s)) exp_kind = do { checkWiredInTyCon typeSymbolKindCon - ; checkExpKind rn_ty (mkStrLitTy s) typeSymbolKind exp_kind } + ; checkExpKind rn_ty (mkStrLitTy $ mkFastStringText s) typeSymbolKind exp_kind } tcHsType _ rn_ty@(HsTyLit _ (HsCharTy _ c)) exp_kind = do { checkWiredInTyCon charTyCon ; checkExpKind rn_ty (mkCharLitTy c) charTy exp_kind } ===================================== compiler/GHC/Tc/Solver/Dict.hs ===================================== @@ -50,6 +50,7 @@ import GHC.Utils.Misc import GHC.Unit.Module import GHC.Data.Bag +import GHC.Data.FastString import GHC.Driver.DynFlags @@ -149,7 +150,7 @@ canDictCt ev cls tys = Stage $ do { -- First we emit a new constraint that will capture the -- given CallStack. - let new_loc = setCtLocOrigin loc (IPOccOrigin (HsIPName ip_name)) + let new_loc = setCtLocOrigin loc (IPOccOrigin (HsIPName $ fastStringToText ip_name)) -- We change the origin to IPOccOrigin so -- this rule does not fire again. -- See Note [Overview of implicit CallStacks] ===================================== compiler/GHC/ThToHs.hs ===================================== @@ -1362,9 +1362,7 @@ cvtOverLit (IntegerL i) cvtOverLit (RationalL r) = do { force r; return $ mkHsFractional (mkTHFractionalLit r) } cvtOverLit (StringL s) - = do { let { s' = mkFastString s } - ; force s' - ; return $ mkHsIsString (quotedSourceText s) s' + = do { force s; return $ mkHsIsString (quotedSourceText s) (T.pack s) } cvtOverLit _ = panic "Convert.cvtOverLit: Unexpected overloaded literal" -- An Integer is like an (overloaded) '3' in a Haskell source program ===================================== compiler/Language/Haskell/Syntax/Expr.hs ===================================== @@ -36,8 +36,6 @@ import Language.Haskell.Syntax.Binds import GHC.Types.Fixity (LexicalFixity(Infix), Fixity) import GHC.Types.SourceText (StringLiteral) -import GHC.Data.FastString (FastString) - -- libraries: import Data.Data hiding (Fixity(..)) import Data.Bool @@ -1436,7 +1434,7 @@ data HsUntypedSplice id | HsQuasiQuote -- See Note [Quasi-quote overview] (XQuasiQuote id) (IdP id) -- The quoter (the bit between `[` and `|`) - (XRec id FastString) -- The enclosed string + (XRec id Text) -- The enclosed string | XUntypedSplice !(XXUntypedSplice id) -- Extension point; see Note [Trees That Grow] -- in Language.Haskell.Syntax.Extension ===================================== compiler/Language/Haskell/Syntax/Lit.hs ===================================== @@ -23,8 +23,6 @@ import Language.Haskell.Syntax.Extension import GHC.Types.SourceText (IntegralLit, FractionalLit, SourceText) import GHC.Core.Type (Type) -import GHC.Data.FastString (FastString, lexicalCompareFS) - import Data.ByteString (ByteString) import Data.Data hiding ( Fixity ) import Data.Bool @@ -125,7 +123,7 @@ data HsOverLit p data OverLitVal = HsIntegral !IntegralLit -- ^ Integer-looking literals; | HsFractional !FractionalLit -- ^ Frac-looking literals - | HsIsString !SourceText !FastString -- ^ String-looking literals + | HsIsString !SourceText !Text -- ^ String-looking literals deriving Data instance Eq OverLitVal where @@ -141,6 +139,6 @@ instance Ord OverLitVal where compare (HsFractional f1) (HsFractional f2) = f1 `compare` f2 compare (HsFractional _) (HsIntegral _) = GT compare (HsFractional _) (HsIsString _ _) = LT - compare (HsIsString _ s1) (HsIsString _ s2) = s1 `lexicalCompareFS` s2 + compare (HsIsString _ s1) (HsIsString _ s2) = s1 `compare` s2 compare (HsIsString _ _) (HsIntegral _) = GT compare (HsIsString _ _) (HsFractional _) = GT ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -68,6 +68,7 @@ import qualified Data.List.NonEmpty as NE import qualified Data.Map.Strict as Map import Data.Maybe ( isJust, mapMaybe ) import Data.Void +import qualified Data.Text as T import Lookup import Utils @@ -2126,7 +2127,7 @@ instance ExactPrint StringLiteral where setAnnotationAnchor a _ _ _ = a exact (StringLiteral src fs mcomma) = do - printSourceTextAA src (show (unpackFS fs)) + printSourceTextAA src (show fs) mcomma' <- mapM (\r -> printStringAtNC r ",") mcomma return (StringLiteral src fs mcomma') @@ -2137,7 +2138,7 @@ instance ExactPrint FastString where setAnnotationAnchor a _ _ _ = a -- TODO: https://ghc.haskell.org/trac/ghc/ticket/10313 applies. - -- exact fs = printStringAdvance (show (unpackFS fs)) + -- exact fs = printStringAdvance (show fs) exact fs = printStringAdvance (unpackFS fs) >> return fs -- --------------------------------------------------------------------- @@ -2703,7 +2704,7 @@ instance ExactPrint HsIPName where getAnnotationEntry = const NoEntryVal setAnnotationAnchor a _ _ _ = a - exact i@(HsIPName fs) = printStringAdvance ("?" ++ (unpackFS fs)) >> return i + exact i@(HsIPName fs) = printStringAdvance ("?" ++ (T.unpack fs)) >> return i -- --------------------------------------------------------------------- -- Managing lists which have been separated, e.g. Sigs and Binds @@ -2962,12 +2963,12 @@ instance ExactPrint (HsExpr GhcPs) where exact x@(HsOverLabel src l) = do printStringAtLsDelta (SameLine 0) "#" case src of - NoSourceText -> printStringAtLsDelta (SameLine 0) (unpackFS l) + NoSourceText -> printStringAtLsDelta (SameLine 0) (T.unpack l) SourceText txt -> printStringAtLsDelta (SameLine 0) (unpackFS txt) return x exact x@(HsIPVar _ (HsIPName n)) - = printStringAdvance ("?" ++ unpackFS n) >> return x + = printStringAdvance ("?" ++ T.unpack n) >> return x exact x@(HsOverLit _an ol) = do let str = case ol_val ol of @@ -3276,7 +3277,7 @@ instance ExactPrint (HsPragE GhcPs) where exact (HsPragSCC (an,st) sl) = do an0 <- markAnnOpenP' an st "{-# SCC" - let txt = sourceTextToString (sl_st sl) (unpackFS $ sl_fs sl) + let txt = sourceTextToString (sl_st sl) (T.unpack $ sl_fs sl) an1 <- markEpAnnLMS'' an0 lapr_rest AnnVal (Just txt) -- optional an2 <- markEpAnnLMS'' an1 lapr_rest AnnValStr (Just txt) -- optional an3 <- markAnnCloseP' an2 @@ -3304,7 +3305,7 @@ instance ExactPrint (HsUntypedSplice GhcPs) where unless pMarkLayout $ setLayoutOffsetP 0 printStringAdvance -- Note: Lexer.x does not provide unicode alternative. 2017-02-26 - ("[" ++ (showPprUnsafe q) ++ "|" ++ (unpackFS fs) ++ "|]") + ("[" ++ (showPprUnsafe q) ++ "|" ++ (T.unpack fs) ++ "|]") unless pMarkLayout $ setLayoutOffsetP oldOffset return (HsQuasiQuote an q (L l fs)) @@ -4482,7 +4483,7 @@ instance ExactPrint (LocatedP CType) where Nothing -> return an0 Just (Header srcH _h) -> markEpAnnLMS an0 lapr_rest AnnHeader (Just (toSourceTextWithSuffix srcH "" "")) - an2 <- markEpAnnLMS an1 lapr_rest AnnVal (Just (toSourceTextWithSuffix stct (unpackFS ct) "")) + an2 <- markEpAnnLMS an1 lapr_rest AnnVal (Just (toSourceTextWithSuffix stct (T.unpack ct) "")) an3 <- markAnnCloseP an2 return (L an3 (CType stp mh (stct,ct))) ===================================== utils/check-exact/check-exact.cabal ===================================== @@ -29,6 +29,7 @@ Executable check-exact Utils Build-Depends: base >= 4 && < 5, bytestring, + text, containers, directory, filepath, ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Parser.hs ===================================== @@ -136,7 +136,7 @@ parse dflags fpath bs = case unP (go False []) initState of L _ (ITstring _ file) <- tryP wrappedLexer L spF ITclose_prag <- tryP wrappedLexer - let newLoc = mkRealSrcLoc file (fromIntegral line - 1) (srcSpanEndCol spF) + let newLoc = mkRealSrcLoc (mkFastString file) (fromIntegral line - 1) (srcSpanEndCol spF) (bEnd'', _) <- lift getInput lift $ setInput (bEnd'', newLoc) ===================================== utils/haddock/haddock-api/src/Haddock/Convert.hs ===================================== @@ -87,6 +87,7 @@ import Haddock.Types import Data.Either (lefts, partitionEithers, rights) import Data.Maybe (catMaybes, mapMaybe, maybeToList) +import GHC.Data.FastString (fastStringToText) -- | Whether or not to default 'RuntimeRep' variables to 'LiftedRep'. Check -- out Note [Defaulting RuntimeRep variables] in GHC.Iface.Type for the @@ -754,7 +755,7 @@ synifyType _ vs (TyConApp tc tys) = | tc `hasKey` ipClassKey , [name, ty] <- tys , Just x <- isStrLitTy name = - noLocA $ HsIParamTy noAnn (noLocA $ HsIPName x) (synifyType WithinType vs ty) + noLocA $ HsIParamTy noAnn (noLocA $ HsIPName (fastStringToText x)) (synifyType WithinType vs ty) -- and equalities | tc `hasKey` eqTyConKey , [ty1, ty2] <- tys = @@ -1005,7 +1006,7 @@ synifyPatSynType ps = synifyTyLit :: TyLit -> HsTyLit GhcRn synifyTyLit (NumTyLit n) = HsNumTy NoSourceText n -synifyTyLit (StrTyLit s) = HsStrTy NoSourceText s +synifyTyLit (StrTyLit s) = HsStrTy NoSourceText (fastStringToText s) synifyTyLit (CharTyLit c) = HsCharTy NoSourceText c synifyKindSig :: Kind -> LHsKind GhcRn ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Create.hs ===================================== @@ -57,15 +57,13 @@ import Data.Traversable (for) import Control.Arrow (first, (&&&)) import GHC hiding (lookupName) import GHC.Builtin.Names -import GHC.Builtin.Types import GHC.Builtin.Types.Prim import GHC.Core.ConLike (ConLike (..)) -import GHC.Data.FastString (FastString, bytesFS, unpackFS) +import GHC.Data.FastString (unpackFS) import GHC.Driver.Ppr import GHC.HsToCore.Docs hiding (mkMaps) import GHC.Iface.Syntax import GHC.Types.Avail -import GHC.Types.Basic import GHC.Types.Name import GHC.Types.Name.Set import GHC.Types.SafeHaskell @@ -75,6 +73,8 @@ import GHC.Unit.Module.ModIface import GHC.Unit.State (PackageName (..), UnitState) import qualified GHC.Utils.Outputable as O import GHC.Utils.Panic (pprPanic) +import qualified Data.Text as T +import qualified Data.Text.Encoding as T createInterface1 :: MonadIO m @@ -324,8 +324,8 @@ parseWarning dflags w = case w of dstToDoc :: (IfaceStringLiteral, [Name]) -> HsDoc GhcRn dstToDoc ((IfStringLiteral _ fs), ids) = WithHsDocIdentifiers (fsToDoc fs) (map noLoc ids) - fsToDoc :: FastString -> HsDocString - fsToDoc fs = GeneratedDocString $ HsDocStringChunk (bytesFS fs) + fsToDoc :: T.Text -> HsDocString + fsToDoc fs = GeneratedDocString $ HsDocStringChunk (T.encodeUtf8 fs) format x bs = DocWarning . DocParagraph . DocAppend (DocString x) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d9408cc56ae54d0bd86a27308fe97dbf635fe727 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d9408cc56ae54d0bd86a27308fe97dbf635fe727 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 06:45:45 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Wed, 12 Jun 2024 02:45:45 -0400 Subject: [Git][ghc/ghc][wip/jacco/ast] ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <66694419ea572_12d7f7434016c11936@gitlab.mail> Rodrigo Mesquita pushed to branch wip/jacco/ast at Glasgow Haskell Compiler / GHC Commits: 33680119 by Jacco Krijnen at 2024-06-12T07:45:36+01:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/33680119842161055fad20b3ebadaa1e2964f800 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/33680119842161055fad20b3ebadaa1e2964f800 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 07:08:38 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Jun 2024 03:08:38 -0400 Subject: [Git][ghc/ghc][master] haddock: Correct the Makefile to take into account Darwin systems Message-ID: <66694976ad1ea_b01b01ed8f44606d@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - 1 changed file: - utils/haddock/Makefile Changes: ===================================== utils/haddock/Makefile ===================================== @@ -8,18 +8,17 @@ test: ## Run the test suite @cabal test lint: ## Run the code linter (HLint) - @find driver haddock-api haddock-library haddock-test hoogle-test hypsrc-test latex-test \ - -name "*.hs" | xargs -P $(PROCS) -I {} hlint --refactor-options="-i" --refactor {} + @find driver haddock-api haddock-library -name "*.hs" | xargs -P $(PROCS) -I {} hlint --refactor-options="-i" --refactor {} style: ## Run the code styler (fourmolu and cabal-fmt) @cabal-fmt -i **/*.cabal @fourmolu -q --mode inplace driver haddock-api haddock-library style-check: ## Check the code's style (fourmolu and cabal-fmt) - @cabal-fmt -i **/*.cabal + @cabal-fmt -c **/*.cabal @fourmolu -q --mode check driver haddock-api haddock-library -style-quick: ## Run the code styler on modified files +style-quick: ## Run the code styler on modified files tracked by git @cabal-fmt -i **/*.cabal @git diff origin --name-only driver haddock-api haddock-library | xargs -P $(PROCS) -I {} fourmolu -q -i {} @@ -29,9 +28,12 @@ tags: ## Generate ctags and etags for the source code (ghc-tags) help: ## Display this help message @grep -E '^[a-zA-Z_-]+:.*?## .*$$' $(MAKEFILE_LIST) | awk 'BEGIN {FS = ":.* ?## "}; {printf "\033[36m%-30s\033[0m %s\n", $$1, $$2}' -PROCS := $(shell nproc) - .PHONY: all $(MAKECMDGOALS) .DEFAULT_GOAL := help +ifeq ($(UNAME), Darwin) + PROCS := $(shell sysctl -n hw.logicalcpu) +else + PROCS := $(shell nproc) +endif View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/16475bb8c8a99e6012e70ad0ff443102479e5899 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/16475bb8c8a99e6012e70ad0ff443102479e5899 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 07:09:17 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Jun 2024 03:09:17 -0400 Subject: [Git][ghc/ghc][master] haddock: Remove obsolete links to github.com/haskell/haddock in the docs Message-ID: <6669499d5e0f5_b01b037467851251@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - 7 changed files: - utils/haddock/README.md - utils/haddock/doc/intro.rst - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/resources/html/package.json - utils/haddock/haddock-library/haddock-library.cabal - utils/haddock/haddock-test/haddock-test.cabal - utils/haddock/haddock.cabal Changes: ===================================== utils/haddock/README.md ===================================== @@ -1,4 +1,4 @@ -# Haddock [![CI][CI badge]][CI page] [![Hackage][Hackage badge]][Hackage page] +# Haddock [![Hackage][Hackage badge]][Hackage page] Haddock is the standard tool for generating documentation from Haskell code. Full documentation about Haddock itself can be found in the `doc/` subdirectory, @@ -25,8 +25,6 @@ See [CONTRIBUTING.md](CONTRIBUTING.md) to see how to make contributions to the project. -[CI page]: https://github.com/haskell/haddock/actions/workflows/ci.yml -[CI badge]: https://github.com/haskell/haddock/actions/workflows/ci.yml/badge.svg [Hackage page]: https://hackage.haskell.org/package/haddock [Hackage badge]: https://img.shields.io/hackage/v/haddock.svg [reST]: https://www.sphinx-doc.org/en/master/usage/restructuredtext/index.html ===================================== utils/haddock/doc/intro.rst ===================================== @@ -62,9 +62,7 @@ Obtaining Haddock Haddock is distributed with GHC distributions, and will automatically be provided if you use `ghcup `__, for instance. -Up-to-date sources can also be obtained from our public GitHub -repository. The Haddock sources are at -``https://github.com/haskell/haddock``. +Haddock lives in the GHC repository, which you can consult at ``https://gitlab.haskell.org/ghc/ghc``. License ------- @@ -99,12 +97,6 @@ code, except where otherwise indicated. (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -Contributors ------------- - -A list of contributors to the project can be seen at -``https://github.com/haskell/haddock/graphs/contributors``. - Acknowledgements ---------------- ===================================== utils/haddock/haddock-api/haddock-api.cabal ===================================== @@ -7,13 +7,12 @@ description: Haddock is a documentation-generation tool for Haskell license: BSD-2-Clause license-file: LICENSE author: Simon Marlow, David Waern -maintainer: Alec Theriault , Alex Biehl , Simon Hengel , Mateusz Kowalczyk +maintainer: Haddock Team homepage: http://www.haskell.org/haddock/ -bug-reports: https://github.com/haskell/haddock/issues +bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new copyright: (c) Simon Marlow, David Waern category: Documentation build-type: Simple -tested-with: GHC==9.6.* extra-source-files: CHANGES.md @@ -39,6 +38,11 @@ data-files: html/Linuwial.std-theme/synopsis.png latex/haddock.sty +source-repository head + type: git + location: https://gitlab.haskell.org/ghc/ghc.git + subdir: utils/haddock/haddock-api + library default-language: Haskell2010 @@ -203,8 +207,3 @@ test-suite spec build-tool-depends: hspec-discover:hspec-discover ^>= 2.9 - -source-repository head - type: git - subdir: haddock-api - location: https://github.com/haskell/haddock.git ===================================== utils/haddock/haddock-api/resources/html/package.json ===================================== @@ -8,7 +8,8 @@ }, "repository": { "type": "git", - "url": "https://github.com/haskell/haddock.git" + "url": "https://gitlab.haskell.org/ghc/ghc.git" + "directory": "utils/haddock" }, "author": "Tim Baumann ", "contributors": [ ===================================== utils/haddock/haddock-library/haddock-library.cabal ===================================== @@ -2,7 +2,6 @@ cabal-version: 3.0 name: haddock-library version: 1.11.0 synopsis: Library exposing some functionality of Haddock. - description: Haddock is a documentation-generation tool for Haskell libraries. These modules expose some functionality of it without pulling in the GHC @@ -13,16 +12,10 @@ description: Haddock is a documentation-generation tool for Haskell license: BSD-2-Clause license-file: LICENSE -maintainer: Alec Theriault , Alex Biehl , Simon Hengel , Mateusz Kowalczyk +maintainer: Haddock Team homepage: http://www.haskell.org/haddock/ -bug-reports: https://github.com/haskell/haddock/issues +bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new category: Documentation -tested-with: GHC == 8.4.4 - , GHC == 8.6.5 - , GHC == 8.8.3 - , GHC == 8.10.1 - , GHC == 9.0.1 - , GHC == 9.2.0 extra-doc-files: CHANGES.md @@ -31,6 +24,11 @@ extra-source-files: fixtures/examples/*.input fixtures/examples/*.parsed +source-repository head + type: git + location: https://gitlab.haskell.org/ghc/ghc.git + subdir: utils/haddock/haddock-library + common lib-defaults default-language: Haskell2010 @@ -113,8 +111,3 @@ test-suite fixtures , filepath ^>= 1.4.1.2 , optparse-applicative >= 0.15 && < 0.19 , tree-diff ^>= 0.2 || ^>= 0.3 - -source-repository head - type: git - subdir: haddock-library - location: https://github.com/haskell/haddock.git ===================================== utils/haddock/haddock-test/haddock-test.cabal ===================================== @@ -6,11 +6,10 @@ license: BSD-2-Clause author: Simon Marlow, David Waern maintainer: Simon Hengel , Mateusz Kowalczyk homepage: http://www.haskell.org/haddock/ -bug-reports: https://github.com/haskell/haddock/issues +bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new copyright: (c) Simon Marlow, David Waern category: Documentation build-type: Simple -tested-with: GHC==9.6.* stability: experimental library ===================================== utils/haddock/haddock.cabal ===================================== @@ -29,13 +29,12 @@ description: license: BSD-3-Clause license-file: LICENSE author: Simon Marlow, David Waern -maintainer: Alec Theriault , Alex Biehl , Simon Hengel , Mateusz Kowalczyk +maintainer: Haddock Team homepage: http://www.haskell.org/haddock/ -bug-reports: https://github.com/haskell/haddock/issues +bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new copyright: (c) Simon Marlow, David Waern category: Documentation build-type: Simple -tested-with: GHC==9.6.* extra-source-files: CHANGES.md @@ -65,6 +64,11 @@ flag threaded default: True manual: True +source-repository head + type: git + location: https://gitlab.haskell.org/ghc/ghc.git + subdir: utils/haddock + executable haddock default-language: Haskell2010 main-is: Main.hs @@ -193,7 +197,3 @@ test-suite hoogle-test main-is: Main.hs hs-source-dirs: hoogle-test build-depends: base, filepath, haddock-test == 0.0.1 - -source-repository head - type: git - location: https://github.com/haskell/haddock.git View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a2f60da575598ae413cc553460c0c2c1ebce9d2c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a2f60da575598ae413cc553460c0c2c1ebce9d2c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 07:10:16 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Jun 2024 03:10:16 -0400 Subject: [Git][ghc/ghc][master] Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. Message-ID: <666949d89d10e_b01b0570eb857961@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 8 changed files: - compiler/GHC/SysTools/Cpp.hs - docs/users_guide/9.12.1-notes.rst - docs/users_guide/exts/assert.rst - docs/users_guide/phases.rst - + testsuite/tests/driver/cpp_assertions_ignored/Makefile - + testsuite/tests/driver/cpp_assertions_ignored/all.T - + testsuite/tests/driver/cpp_assertions_ignored/cpp_assertions_ignored.stdout - + testsuite/tests/driver/cpp_assertions_ignored/main.hs Changes: ===================================== compiler/GHC/SysTools/Cpp.hs ===================================== @@ -168,6 +168,9 @@ doCpp logger tmpfs dflags unit_env opts input_fn output_fn = do backend_defs <- applyCDefs (backendCDefs $ backend dflags) logger dflags let th_defs = [ "-D__GLASGOW_HASKELL_TH__" ] + + let asserts_def = [ "-D__GLASGOW_HASKELL_ASSERTS_IGNORED__" | gopt Opt_IgnoreAsserts dflags] + -- Default CPP defines in Haskell source ghcVersionH <- getGhcVersionPathName dflags unit_env let hsSourceCppOpts = [ "-include", ghcVersionH ] @@ -197,6 +200,7 @@ doCpp logger tmpfs dflags unit_env opts input_fn output_fn = do ++ map GHC.SysTools.Option target_defs ++ map GHC.SysTools.Option backend_defs ++ map GHC.SysTools.Option th_defs + ++ map GHC.SysTools.Option asserts_def ++ map GHC.SysTools.Option hscpp_opts ++ map GHC.SysTools.Option sse_defs ++ map GHC.SysTools.Option fma_def ===================================== docs/users_guide/9.12.1-notes.rst ===================================== @@ -75,6 +75,13 @@ Compiler `_). This does not affect existing support of apple systems on x86_64/aarch64. +- The flag :ghc-flag:`-fignore-asserts` will now also enable the + :extension:`CPP` macro ``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` (`#24967 + `_). + This enables people to write their own custom assertion functions. + See :ref:`assertions`. + + GHCi ~~~~ ===================================== docs/users_guide/exts/assert.rst ===================================== @@ -50,4 +50,20 @@ allows enabling assertions even when optimisation is turned on. Assertion failures can be caught, see the documentation for the :base-ref:`Control.Exception.` library for the details. - +The ``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` CPP macro +===================================================== + +When code is compiled with assertions ignored (using :ghc-flag:`-fignore-asserts` or :ghc-flag:`-O`), +the :extension:`CPP` macro ``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` will be defined. +This can be used to conditionally compile your own custom assert-like functions. +For example: :: + + checkedAdd :: Word -> Word -> Word + #ifdef __GLASGOW_HASKELL_ASSERTS_IGNORED__ + checkedAdd lhs rhs = lhs + rhs + #else + checkedAdd lhs rhs + | res < lhs || res < rhs = raise OverflowException + | otherwise = res + where res = lhs + rhs + #endif ===================================== docs/users_guide/phases.rst ===================================== @@ -508,6 +508,13 @@ defined by your local GHC installation, the following trick is useful: is added, so for example when using version 3.7 of LLVM, ``__GLASGOW_HASKELL_LLVM__==307``). +``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` + .. index:: + single: __GLASGOW_HASKELL_ASSERTS_IGNORED__ + + Only defined when :ghc-flag:`-fignore-asserts` is specified. + This can be used to create your own assertions, see :ref:`assertions` + ``__PARALLEL_HASKELL__`` .. index:: single: __PARALLEL_HASKELL__ ===================================== testsuite/tests/driver/cpp_assertions_ignored/Makefile ===================================== @@ -0,0 +1,11 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +cpp_assertions_ignored: + echo "Without -fignore-asserts" + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 main.hs + (./main 2>&1); true + echo "With -fignore-asserts" + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -fignore-asserts main.hs + ./main 2>&1 ===================================== testsuite/tests/driver/cpp_assertions_ignored/all.T ===================================== @@ -0,0 +1,4 @@ +test('cpp_assertions_ignored', + [ extra_files(['main.hs']) + ], + makefile_test, ['cpp_assertions_ignored']) ===================================== testsuite/tests/driver/cpp_assertions_ignored/cpp_assertions_ignored.stdout ===================================== @@ -0,0 +1,4 @@ +Without -fignore-asserts +Assertions Enabled +With -fignore-asserts +Assertions Ignored ===================================== testsuite/tests/driver/cpp_assertions_ignored/main.hs ===================================== @@ -0,0 +1,14 @@ +{-# LANGUAGE CPP #-} +import Control.Exception (assert) + +main = + if assertsEnabled + then putStrLn "Assertions Enabled" + else putStrLn "Assertions Ignored" + +assertsEnabled :: Bool +#ifdef __GLASGOW_HASKELL_ASSERTS_IGNORED__ +assertsEnabled = False +#else +assertsEnabled = True +#endif View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/de4395cdf596f9e3d5e4ccd16e6c2eb94106f3ae -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/de4395cdf596f9e3d5e4ccd16e6c2eb94106f3ae You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 07:11:11 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Jun 2024 03:11:11 -0400 Subject: [Git][ghc/ghc][master] compiler: add hint to TcRnBadlyStaged message Message-ID: <66694a0fbbff4_b01b07a7fc46028c@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 3 changed files: - compiler/GHC/Tc/Errors/Ppr.hs - testsuite/tests/th/T17820d.stderr - testsuite/tests/th/T23829_hasty_b.stderr Changes: ===================================== compiler/GHC/Tc/Errors/Ppr.hs ===================================== @@ -1417,9 +1417,16 @@ instance Diagnostic TcRnMessage where , interpp'SP errorVars ] TcRnBadlyStaged reason bind_lvl use_lvl -> mkSimpleDecorated $ - text "Stage error:" <+> pprStageCheckReason reason <+> - hsep [text "is bound at stage" <+> ppr bind_lvl, - text "but used at stage" <+> ppr use_lvl] + vcat $ + [ text "Stage error:" <+> pprStageCheckReason reason <+> + hsep [text "is bound at stage" <+> ppr bind_lvl, + text "but used at stage" <+> ppr use_lvl] + ] ++ + [ hsep [ text "Hint: quoting" <+> thBrackets (ppUnless (isValName n) "t") (ppr n) + , text "or an enclosing expression would allow the quotation to be used in an earlier stage" + ] + | StageCheckSplice n <- [reason] + ] TcRnBadlyStagedType name bind_lvl use_lvl -> mkSimpleDecorated $ text "Badly staged type:" <+> ppr name <+> ===================================== testsuite/tests/th/T17820d.stderr ===================================== @@ -1,7 +1,8 @@ - T17820d.hs:6:38: error: [GHC-28914] • Stage error: ‘foo’ is bound at stage 2 but used at stage 1 + Hint: quoting [| foo |] or an enclosing expression would allow the quotation to be used in an earlier stage • In the untyped splice: $(const [| 0 |] foo) In the Template Haskell quotation [d| data D = MkD {foo :: Int} blargh = $(const [| 0 |] foo) |] + ===================================== testsuite/tests/th/T23829_hasty_b.stderr ===================================== @@ -1,6 +1,7 @@ - T23829_hasty_b.hs:8:42: error: [GHC-28914] • Stage error: ‘ty’ is bound at stage 2 but used at stage 1 + Hint: quoting [t| ty |] or an enclosing expression would allow the quotation to be used in an earlier stage • In the untyped splice: $ty In the Template Haskell quotation [t| forall (ty :: TypeQ). Proxy $ty |] + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0e9c4deea7411e735e3e0bd6f6726773eca4ab2b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0e9c4deea7411e735e3e0bd6f6726773eca4ab2b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 07:41:35 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Jun 2024 03:41:35 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 12 commits: haddock: Correct the Makefile to take into account Darwin systems Message-ID: <6669512f277fd_b01b0d126e4657b0@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - c1315b20 by Simon Peyton Jones at 2024-06-12T03:41:08-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 44717c8e by George Thomas at 2024-06-12T03:41:15-04:00 Fix non-compiling extensible record `HasField` example - - - - - bd1cf71d by Zubin Duggal at 2024-06-12T03:41:16-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 6298544e by Zubin Duggal at 2024-06-12T03:41:16-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - 51b4ac8a by Simon Peyton Jones at 2024-06-12T03:41:17-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - 09afa98a by Liam Goodacre at 2024-06-12T03:41:18-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4246baec by Jan Hrček at 2024-06-12T03:41:23-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 3e19b803 by Cheng Shao at 2024-06-12T03:41:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - 23 changed files: - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/36fafc5becb619b5c597aa853f7d4bec0fe88631...3e19b803291a9ab526a19514d2bdfd71722a89a1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/36fafc5becb619b5c597aa853f7d4bec0fe88631...3e19b803291a9ab526a19514d2bdfd71722a89a1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 07:45:58 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 12 Jun 2024 03:45:58 -0400 Subject: [Git][ghc/ghc][wip/T24868] Wibbles Message-ID: <6669523655c5c_b01b0e78ce07973f@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24868 at Glasgow Haskell Compiler / GHC Commits: 9d260d49 by Simon Peyton Jones at 2024-06-12T08:45:44+01:00 Wibbles - - - - - 3 changed files: - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Tc/Zonk/TcType.hs - testsuite/tests/typecheck/should_fail/GivenForallLoop.stderr Changes: ===================================== compiler/GHC/Core/TyCo/Tidy.hs ===================================== @@ -288,7 +288,7 @@ trimTidyEnv (occ_env, var_env) tcvs -- | Grabs the free type variables, tidies them -- and then uses 'tidyType' to work over the type itself tidyOpenTypesX :: TidyEnv -> [Type] -> (TidyEnv, [Type]) --- See Note [Tidying open types] +-- See Note [Tidying open types] tidyOpenTypesX env tys = (env1, tidyTypes inner_env tys) where @@ -299,7 +299,7 @@ tidyOpenTypesX env tys --------------- tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) --- See Note [Tidying open types] +-- See Note [Tidying open types] tidyOpenTypeX env ty = (env1, tidyType inner_env ty) where ===================================== compiler/GHC/Tc/Zonk/TcType.hs ===================================== @@ -654,13 +654,17 @@ tidyCtEvidence :: TidyEnv -> CtEvidence -> CtEvidence -- NB: we do not tidy the ctev_evar field because we don't -- show it in error messages tidyCtEvidence env ctev - = ctev { ctev_pred = tidyType env $ ctev_pred ctev } - -- No need for tidyOpenType because all the free tyvars are already tidied + = ctev { ctev_pred = tidyOpenType env $ ctev_pred ctev } + -- tidyOpenType: for (beta ~ (forall a. a->a), don't gratuitously + -- rename the 'forall a' just because of an 'a' in scope somewhere + -- else entirely. tidyHole :: TidyEnv -> Hole -> Hole tidyHole env h@(Hole { hole_ty = ty }) - = h { hole_ty = tidyType env ty } - -- No need for tidyOpenType because all the free tyvars are already tidied + = h { hole_ty = tidyOpenType env ty } + -- tidyOpenType: for, say, (b -> (forall a. a->a)), don't gratuitously + -- rename the 'forall a' just because of an 'a' in scope somewhere + -- else entirely. tidyDelayedError :: TidyEnv -> DelayedError -> DelayedError tidyDelayedError env (DE_Hole hole) = DE_Hole $ tidyHole env hole ===================================== testsuite/tests/typecheck/should_fail/GivenForallLoop.stderr ===================================== @@ -1,16 +1,16 @@ GivenForallLoop.hs:8:11: error: [GHC-25897] • Could not deduce ‘a ~ b’ - from the context: a ~ (forall b. F a b) + from the context: a ~ (forall b1. F a b1) bound by the type signature for: - loopy :: forall a b. (a ~ (forall b. F a b)) => a -> b + loopy :: forall a b. (a ~ (forall b1. F a b1)) => a -> b at GivenForallLoop.hs:7:1-42 ‘a’ is a rigid type variable bound by the type signature for: - loopy :: forall a b. (a ~ (forall b. F a b)) => a -> b + loopy :: forall a b. (a ~ (forall b1. F a b1)) => a -> b at GivenForallLoop.hs:7:1-42 ‘b’ is a rigid type variable bound by the type signature for: - loopy :: forall a b. (a ~ (forall b. F a b)) => a -> b + loopy :: forall a b. (a ~ (forall b1. F a b1)) => a -> b at GivenForallLoop.hs:7:1-42 • In the expression: x In an equation for ‘loopy’: loopy x = x View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9d260d499affe2920658f7a3b111e18fe34ab690 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9d260d499affe2920658f7a3b111e18fe34ab690 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 09:07:04 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Wed, 12 Jun 2024 05:07:04 -0400 Subject: [Git][ghc/ghc][wip/T14030] 2 commits: Derive previously hand-written `Lift` instances (#14030) Message-ID: <6669653852157_b01b01974b9410074@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: 89b16654 by Sebastian Graf at 2024-06-12T11:06:48+02:00 Derive previously hand-written `Lift` instances (#14030) This is possible now that #22229 is fixed. - - - - - 5c975702 by Sebastian Graf at 2024-06-12T11:06:48+02:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. - - - - - 3 changed files: - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs ===================================== @@ -12,6 +12,8 @@ {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UnboxedSums #-} {-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE DeriveLift #-} +{-# LANGUAGE StandaloneDeriving #-} {-# OPTIONS_GHC -fno-warn-inline-rule-shadowing #-} -- | This module gives the definition of the 'Lift' class. @@ -39,7 +41,7 @@ module GHC.Internal.TH.Lift where import GHC.Internal.TH.Syntax -import GHC.Internal.TH.Lib () -- See wrinkle (W4) of Note [Tracking dependencies on primitives] +import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives] import GHC.Internal.Lexeme ( startsVarSym, startsVarId ) import GHC.Internal.Data.Either @@ -52,7 +54,7 @@ import GHC.Internal.Integer import GHC.Internal.Real import GHC.Internal.Word import GHC.Internal.Int -import GHC.Internal.Data.Data +import GHC.Internal.Data.Data hiding (Fixity) import GHC.Internal.Natural -- | A 'Lift' instance can have any of its values turned into a Template @@ -201,205 +203,77 @@ instance Lift Addr# where lift x = return (LitE (StringPrimL (map (fromIntegral . ord) (unpackCString# x)))) -instance Lift a => Lift (Maybe a) where - liftTyped x = unsafeCodeCoerce (lift x) - - lift Nothing = return (ConE nothingName) - lift (Just x) = liftM (ConE justName `AppE`) (lift x) - -instance (Lift a, Lift b) => Lift (Either a b) where - liftTyped x = unsafeCodeCoerce (lift x) +deriving instance Lift a => Lift (Maybe a) - lift (Left x) = liftM (ConE leftName `AppE`) (lift x) - lift (Right y) = liftM (ConE rightName `AppE`) (lift y) +deriving instance (Lift a, Lift b) => Lift (Either a b) -instance Lift a => Lift [a] where - liftTyped x = unsafeCodeCoerce (lift x) - lift xs = do { xs' <- mapM lift xs; return (ListE xs') } +deriving instance Lift a => Lift [a] liftString :: Quote m => String -> m Exp -- Used in GHC.Tc.Gen.Expr to short-circuit the lifting for strings liftString s = return (LitE (StringL s)) -- | @since template-haskell-2.15.0.0 -instance Lift a => Lift (NonEmpty a) where - liftTyped x = unsafeCodeCoerce (lift x) - - lift (x :| xs) = do - x' <- lift x - xs' <- lift xs - return (InfixE (Just x') (ConE nonemptyName) (Just xs')) +deriving instance Lift a => Lift (NonEmpty a) -- | @since template-haskell-2.15.0.0 -instance Lift Void where - liftTyped = liftCode . absurd - lift = pure . absurd - -instance Lift () where - liftTyped x = unsafeCodeCoerce (lift x) - lift () = return (ConE (tupleDataName 0)) - -instance (Lift a, Lift b) => Lift (a, b) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b) - = liftM TupE $ sequence $ map (fmap Just) [lift a, lift b] - -instance (Lift a, Lift b, Lift c) => Lift (a, b, c) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c) - = liftM TupE $ sequence $ map (fmap Just) [lift a, lift b, lift c] - -instance (Lift a, Lift b, Lift c, Lift d) => Lift (a, b, c, d) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d) - = liftM TupE $ sequence $ map (fmap Just) [lift a, lift b, lift c, lift d] - -instance (Lift a, Lift b, Lift c, Lift d, Lift e) - => Lift (a, b, c, d, e) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d, e) - = liftM TupE $ sequence $ map (fmap Just) [ lift a, lift b - , lift c, lift d, lift e ] - -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) - => Lift (a, b, c, d, e, f) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d, e, f) - = liftM TupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f ] - -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) - => Lift (a, b, c, d, e, f, g) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d, e, f, g) - = liftM TupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f, lift g ] +deriving instance Lift Void + +deriving instance Lift () +deriving instance (Lift a, Lift b) + => Lift (a, b) +deriving instance (Lift a, Lift b, Lift c) + => Lift (a, b, c) +deriving instance (Lift a, Lift b, Lift c, Lift d) + => Lift (a, b, c, d) +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e) + => Lift (a, b, c, d, e) +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) + => Lift (a, b, c, d, e, f) +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) + => Lift (a, b, c, d, e, f, g) -- | @since template-haskell-2.16.0.0 -instance Lift (# #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# #) = return (ConE (unboxedTupleTypeName 0)) +deriving instance Lift (# #) -- | @since template-haskell-2.16.0.0 -instance (Lift a) => Lift (# a #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [lift a] - +deriving instance (Lift a) + => Lift (# a #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b) => Lift (# a, b #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [lift a, lift b] - +deriving instance (Lift a, Lift b) + => Lift (# a, b #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c) - => Lift (# a, b, c #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [lift a, lift b, lift c] - +deriving instance (Lift a, Lift b, Lift c) + => Lift (# a, b, c #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d) - => Lift (# a, b, c, d #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b - , lift c, lift d ] - +deriving instance (Lift a, Lift b, Lift c, Lift d) + => Lift (# a, b, c, d #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e) - => Lift (# a, b, c, d, e #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d, e #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b - , lift c, lift d, lift e ] - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e) + => Lift (# a, b, c, d, e #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) - => Lift (# a, b, c, d, e, f #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d, e, f #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f ] - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) + => Lift (# a, b, c, d, e, f #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) - => Lift (# a, b, c, d, e, f, g #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d, e, f, g #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f - , lift g ] - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) + => Lift (# a, b, c, d, e, f, g #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b) => Lift (# a | b #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 2 - (# | y #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 2 - +deriving instance (Lift a, Lift b) => Lift (# a | b #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c) - => Lift (# a | b | c #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 3 - (# | y | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 3 - (# | | y #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 3 - +deriving instance (Lift a, Lift b, Lift c) + => Lift (# a | b | c #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d) - => Lift (# a | b | c | d #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 4 - (# | y | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 4 - (# | | y | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 4 - (# | | | y #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 4 - +deriving instance (Lift a, Lift b, Lift c, Lift d) + => Lift (# a | b | c | d #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e) - => Lift (# a | b | c | d | e #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 5 - (# | y | | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 5 - (# | | y | | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 5 - (# | | | y | #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 5 - (# | | | | y #) -> UnboxedSumE <$> lift y <*> pure 5 <*> pure 5 - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e) + => Lift (# a | b | c | d | e #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) - => Lift (# a | b | c | d | e | f #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 6 - (# | y | | | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 6 - (# | | y | | | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 6 - (# | | | y | | #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 6 - (# | | | | y | #) -> UnboxedSumE <$> lift y <*> pure 5 <*> pure 6 - (# | | | | | y #) -> UnboxedSumE <$> lift y <*> pure 6 <*> pure 6 - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) + => Lift (# a | b | c | d | e | f #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) - => Lift (# a | b | c | d | e | f | g #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 7 - (# | y | | | | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 7 - (# | | y | | | | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 7 - (# | | | y | | | #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 7 - (# | | | | y | | #) -> UnboxedSumE <$> lift y <*> pure 5 <*> pure 7 - (# | | | | | y | #) -> UnboxedSumE <$> lift y <*> pure 6 <*> pure 7 - (# | | | | | | y #) -> UnboxedSumE <$> lift y <*> pure 7 <*> pure 7 - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) + => Lift (# a | b | c | d | e | f | g #) -- TH has a special form for literal strings, -- which we should take advantage of. -- NB: the lhs of the rule has no args, so that @@ -424,6 +298,135 @@ rightName = 'Right nonemptyName :: Name nonemptyName = '(:|) +----------------------------------------------------- +-- +-- Lifting the TH AST +-- +----------------------------------------------------- + +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Loc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DocLoc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ModName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift GHC.Internal.TH.Syntax.Module +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameSpace +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NamespaceSpecifier +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PkgName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameFlavour +-- | @since template-haskell-2.22.1.0 +deriving instance Lift OccName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Name +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameIs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Specificity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift BndrVis +-- | @since template-haskell-2.22.1.0 +deriving instance Lift a => Lift (TyVarBndr a) +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TyLit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Type +-- | @since template-haskell-2.22.1.0 +instance Lift Bytes where + lift = Lib.litE . BytesPrimL + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Lit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pat +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Clause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivClause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivStrategy +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Overlap +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FunDep +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Safety +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Callconv +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Foreign +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ForeignSrcLang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FixityDirection +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Fixity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Inline +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleMatch +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Phases +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleBndr +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnTarget +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pragma +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceUnpackedness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DecidedStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Bang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Con +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TySynEqn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FamilyResultSig +-- | @since template-haskell-2.22.1.0 +deriving instance Lift InjectivityAnn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TypeFamilyHead +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Role +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynArgs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynDir +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Dec +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Range +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Exp +-- | @since template-haskell-2.22.1.0 +instance Lift (TExp a) where + lift (TExp e) = [| TExp $(lift e) |] + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Match +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Guard +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Stmt +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Body +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Info +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnLookup +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Extension + ----------------------------------------------------- -- -- Generic Lift implementations ===================================== libraries/template-haskell/changelog.md ===================================== @@ -1,5 +1,9 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) +## 2.22.1.0 + + * `Lift` instances were added for the `template-haskell` AST. + ## 2.22.0.0 * The kind of `Code` was changed from `forall r. (Type -> Type) -> TYPE r -> Type` ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -3,7 +3,7 @@ -- template-haskell.cabal. name: template-haskell -version: 2.22.0.0 +version: 2.22.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/82e2a9e8d3339c4a21cddc015a42e369d723902b...5c97570230b53254b4732801ce6757387dcfd60a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/82e2a9e8d3339c4a21cddc015a42e369d723902b...5c97570230b53254b4732801ce6757387dcfd60a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 09:09:52 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Wed, 12 Jun 2024 05:09:52 -0400 Subject: [Git][ghc/ghc][wip/T14030] 2 commits: Derive previously hand-written `Lift` instances (#14030) Message-ID: <666965e0c04e6_b01b01a777301014fe@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: 8432a8d7 by Sebastian Graf at 2024-06-12T11:09:36+02:00 Derive previously hand-written `Lift` instances (#14030) This is possible now that #22229 is fixed. - - - - - 3c4307bd by Sebastian Graf at 2024-06-12T11:09:36+02:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. - - - - - 3 changed files: - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs ===================================== @@ -12,6 +12,8 @@ {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UnboxedSums #-} {-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE DeriveLift #-} +{-# LANGUAGE StandaloneDeriving #-} {-# OPTIONS_GHC -fno-warn-inline-rule-shadowing #-} -- | This module gives the definition of the 'Lift' class. @@ -39,7 +41,7 @@ module GHC.Internal.TH.Lift where import GHC.Internal.TH.Syntax -import GHC.Internal.TH.Lib () -- See wrinkle (W4) of Note [Tracking dependencies on primitives] +import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives] import GHC.Internal.Lexeme ( startsVarSym, startsVarId ) import GHC.Internal.Data.Either @@ -52,7 +54,7 @@ import GHC.Internal.Integer import GHC.Internal.Real import GHC.Internal.Word import GHC.Internal.Int -import GHC.Internal.Data.Data +import GHC.Internal.Data.Data hiding (Fixity) import GHC.Internal.Natural -- | A 'Lift' instance can have any of its values turned into a Template @@ -186,11 +188,7 @@ instance Lift Char# where liftTyped x = unsafeCodeCoerce (lift x) lift x = return (LitE (CharPrimL (C# x))) -instance Lift Bool where - liftTyped x = unsafeCodeCoerce (lift x) - - lift True = return (ConE trueName) - lift False = return (ConE falseName) +deriving instance Lift Bool -- | Produces an 'Addr#' literal from the NUL-terminated C-string starting at -- the given memory address. @@ -201,205 +199,77 @@ instance Lift Addr# where lift x = return (LitE (StringPrimL (map (fromIntegral . ord) (unpackCString# x)))) -instance Lift a => Lift (Maybe a) where - liftTyped x = unsafeCodeCoerce (lift x) - - lift Nothing = return (ConE nothingName) - lift (Just x) = liftM (ConE justName `AppE`) (lift x) +deriving instance Lift a => Lift (Maybe a) -instance (Lift a, Lift b) => Lift (Either a b) where - liftTyped x = unsafeCodeCoerce (lift x) - - lift (Left x) = liftM (ConE leftName `AppE`) (lift x) - lift (Right y) = liftM (ConE rightName `AppE`) (lift y) +deriving instance (Lift a, Lift b) => Lift (Either a b) -instance Lift a => Lift [a] where - liftTyped x = unsafeCodeCoerce (lift x) - lift xs = do { xs' <- mapM lift xs; return (ListE xs') } +deriving instance Lift a => Lift [a] liftString :: Quote m => String -> m Exp -- Used in GHC.Tc.Gen.Expr to short-circuit the lifting for strings liftString s = return (LitE (StringL s)) -- | @since template-haskell-2.15.0.0 -instance Lift a => Lift (NonEmpty a) where - liftTyped x = unsafeCodeCoerce (lift x) - - lift (x :| xs) = do - x' <- lift x - xs' <- lift xs - return (InfixE (Just x') (ConE nonemptyName) (Just xs')) +deriving instance Lift a => Lift (NonEmpty a) -- | @since template-haskell-2.15.0.0 -instance Lift Void where - liftTyped = liftCode . absurd - lift = pure . absurd - -instance Lift () where - liftTyped x = unsafeCodeCoerce (lift x) - lift () = return (ConE (tupleDataName 0)) - -instance (Lift a, Lift b) => Lift (a, b) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b) - = liftM TupE $ sequence $ map (fmap Just) [lift a, lift b] - -instance (Lift a, Lift b, Lift c) => Lift (a, b, c) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c) - = liftM TupE $ sequence $ map (fmap Just) [lift a, lift b, lift c] - -instance (Lift a, Lift b, Lift c, Lift d) => Lift (a, b, c, d) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d) - = liftM TupE $ sequence $ map (fmap Just) [lift a, lift b, lift c, lift d] - -instance (Lift a, Lift b, Lift c, Lift d, Lift e) - => Lift (a, b, c, d, e) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d, e) - = liftM TupE $ sequence $ map (fmap Just) [ lift a, lift b - , lift c, lift d, lift e ] - -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) - => Lift (a, b, c, d, e, f) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d, e, f) - = liftM TupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f ] - -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) - => Lift (a, b, c, d, e, f, g) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d, e, f, g) - = liftM TupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f, lift g ] +deriving instance Lift Void + +deriving instance Lift () +deriving instance (Lift a, Lift b) + => Lift (a, b) +deriving instance (Lift a, Lift b, Lift c) + => Lift (a, b, c) +deriving instance (Lift a, Lift b, Lift c, Lift d) + => Lift (a, b, c, d) +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e) + => Lift (a, b, c, d, e) +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) + => Lift (a, b, c, d, e, f) +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) + => Lift (a, b, c, d, e, f, g) -- | @since template-haskell-2.16.0.0 -instance Lift (# #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# #) = return (ConE (unboxedTupleTypeName 0)) +deriving instance Lift (# #) -- | @since template-haskell-2.16.0.0 -instance (Lift a) => Lift (# a #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [lift a] - +deriving instance (Lift a) + => Lift (# a #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b) => Lift (# a, b #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [lift a, lift b] - +deriving instance (Lift a, Lift b) + => Lift (# a, b #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c) - => Lift (# a, b, c #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [lift a, lift b, lift c] - +deriving instance (Lift a, Lift b, Lift c) + => Lift (# a, b, c #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d) - => Lift (# a, b, c, d #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b - , lift c, lift d ] - +deriving instance (Lift a, Lift b, Lift c, Lift d) + => Lift (# a, b, c, d #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e) - => Lift (# a, b, c, d, e #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d, e #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b - , lift c, lift d, lift e ] - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e) + => Lift (# a, b, c, d, e #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) - => Lift (# a, b, c, d, e, f #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d, e, f #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f ] - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) + => Lift (# a, b, c, d, e, f #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) - => Lift (# a, b, c, d, e, f, g #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d, e, f, g #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f - , lift g ] - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) + => Lift (# a, b, c, d, e, f, g #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b) => Lift (# a | b #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 2 - (# | y #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 2 - +deriving instance (Lift a, Lift b) => Lift (# a | b #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c) - => Lift (# a | b | c #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 3 - (# | y | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 3 - (# | | y #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 3 - +deriving instance (Lift a, Lift b, Lift c) + => Lift (# a | b | c #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d) - => Lift (# a | b | c | d #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 4 - (# | y | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 4 - (# | | y | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 4 - (# | | | y #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 4 - +deriving instance (Lift a, Lift b, Lift c, Lift d) + => Lift (# a | b | c | d #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e) - => Lift (# a | b | c | d | e #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 5 - (# | y | | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 5 - (# | | y | | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 5 - (# | | | y | #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 5 - (# | | | | y #) -> UnboxedSumE <$> lift y <*> pure 5 <*> pure 5 - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e) + => Lift (# a | b | c | d | e #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) - => Lift (# a | b | c | d | e | f #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 6 - (# | y | | | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 6 - (# | | y | | | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 6 - (# | | | y | | #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 6 - (# | | | | y | #) -> UnboxedSumE <$> lift y <*> pure 5 <*> pure 6 - (# | | | | | y #) -> UnboxedSumE <$> lift y <*> pure 6 <*> pure 6 - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) + => Lift (# a | b | c | d | e | f #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) - => Lift (# a | b | c | d | e | f | g #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 7 - (# | y | | | | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 7 - (# | | y | | | | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 7 - (# | | | y | | | #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 7 - (# | | | | y | | #) -> UnboxedSumE <$> lift y <*> pure 5 <*> pure 7 - (# | | | | | y | #) -> UnboxedSumE <$> lift y <*> pure 6 <*> pure 7 - (# | | | | | | y #) -> UnboxedSumE <$> lift y <*> pure 7 <*> pure 7 - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) + => Lift (# a | b | c | d | e | f | g #) -- TH has a special form for literal strings, -- which we should take advantage of. -- NB: the lhs of the rule has no args, so that @@ -424,6 +294,135 @@ rightName = 'Right nonemptyName :: Name nonemptyName = '(:|) +----------------------------------------------------- +-- +-- Lifting the TH AST +-- +----------------------------------------------------- + +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Loc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DocLoc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ModName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift GHC.Internal.TH.Syntax.Module +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameSpace +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NamespaceSpecifier +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PkgName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameFlavour +-- | @since template-haskell-2.22.1.0 +deriving instance Lift OccName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Name +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameIs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Specificity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift BndrVis +-- | @since template-haskell-2.22.1.0 +deriving instance Lift a => Lift (TyVarBndr a) +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TyLit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Type +-- | @since template-haskell-2.22.1.0 +instance Lift Bytes where + lift = Lib.litE . BytesPrimL + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Lit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pat +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Clause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivClause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivStrategy +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Overlap +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FunDep +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Safety +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Callconv +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Foreign +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ForeignSrcLang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FixityDirection +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Fixity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Inline +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleMatch +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Phases +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleBndr +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnTarget +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pragma +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceUnpackedness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DecidedStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Bang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Con +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TySynEqn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FamilyResultSig +-- | @since template-haskell-2.22.1.0 +deriving instance Lift InjectivityAnn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TypeFamilyHead +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Role +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynArgs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynDir +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Dec +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Range +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Exp +-- | @since template-haskell-2.22.1.0 +instance Lift (TExp a) where + lift (TExp e) = [| TExp $(lift e) |] + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Match +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Guard +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Stmt +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Body +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Info +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnLookup +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Extension + ----------------------------------------------------- -- -- Generic Lift implementations ===================================== libraries/template-haskell/changelog.md ===================================== @@ -1,5 +1,9 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) +## 2.22.1.0 + + * `Lift` instances were added for the `template-haskell` AST. + ## 2.22.0.0 * The kind of `Code` was changed from `forall r. (Type -> Type) -> TYPE r -> Type` ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -3,7 +3,7 @@ -- template-haskell.cabal. name: template-haskell -version: 2.22.0.0 +version: 2.22.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5c97570230b53254b4732801ce6757387dcfd60a...3c4307bd013ba5dbf9cb3b1b017026252fcaf715 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5c97570230b53254b4732801ce6757387dcfd60a...3c4307bd013ba5dbf9cb3b1b017026252fcaf715 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 09:26:36 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Wed, 12 Jun 2024 05:26:36 -0400 Subject: [Git][ghc/ghc][wip/fabu/T24026-early-reject-type-failing-rules] compiler: Rejects RULES whose LHS immediately fails to type-check Message-ID: <666969ccc13a8_b01b01d6b324107669@gitlab.mail> Fabricio Nascimento pushed to branch wip/fabu/T24026-early-reject-type-failing-rules at Glasgow Haskell Compiler / GHC Commits: 18598666 by Fabricio de Sousa Nascimento at 2024-06-12T18:24:21+09:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - 7 changed files: - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/Tc/Gen/Rule.hs - + testsuite/tests/typecheck/T24026/T24026a.hs - + testsuite/tests/typecheck/T24026/T24026a.stderr - + testsuite/tests/typecheck/T24026/T24026b.hs - + testsuite/tests/typecheck/T24026/T24026b.stderr - + testsuite/tests/typecheck/T24026/all.T Changes: ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -1031,9 +1031,12 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs extra_bndrs = scopedSort extra_tvs ++ extra_dicts where extra_tvs = [ v | v <- extra_vars, isTyVar v ] + + -- isEvVar: this includes coercions, matching what + -- happens in `split_lets` (isDictId, isCoVar) extra_dicts = - [ mkLocalId (localiseName (idName d)) ManyTy (idType d) - | d <- extra_vars, isDictId d ] + [ mkLocalIdOrCoVar (localiseName (idName d)) ManyTy (idType d) + | d <- extra_vars, isEvVar d ] extra_vars = [ v | v <- exprsFreeVarsList args ===================================== compiler/GHC/Tc/Gen/Rule.hs ===================================== @@ -108,11 +108,13 @@ tcRules decls = mapM (wrapLocMA tcRuleDecls) decls tcRuleDecls :: RuleDecls GhcRn -> TcM (RuleDecls GhcTc) tcRuleDecls (HsRules { rds_ext = src , rds_rules = decls }) - = do { tc_decls <- mapM (wrapLocMA tcRule) decls + = do { maybe_tc_decls <- mapM (wrapLocMA tcRule) decls + ; let tc_decls = [L loc rule | (L loc (Just rule)) <- maybe_tc_decls] ; return $ HsRules { rds_ext = src , rds_rules = tc_decls } } -tcRule :: RuleDecl GhcRn -> TcM (RuleDecl GhcTc) + +tcRule :: RuleDecl GhcRn -> TcM (Maybe (RuleDecl GhcTc)) tcRule (HsRule { rd_ext = ext , rd_name = rname@(L _ name) , rd_act = act @@ -181,14 +183,22 @@ tcRule (HsRule { rd_ext = ext ; (rhs_implic, rhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs rhs_wanted ; emitImplications (lhs_implic `unionBags` rhs_implic) - ; return $ HsRule { rd_ext = ext + + -- insolubleImplic: if the LHS has an outright type error, drop the rule entirely + -- The error will be reported; but if `-fdefer-type-errors` is on we don't want + -- to continue, else we get a compiler crash (#24026) + ; if anyBag insolubleImplic lhs_implic + then + return Nothing -- The RULE LHS does not type-check and will be dropped. + else + return . Just $ HsRule { rd_ext = ext , rd_name = rname , rd_act = act , rd_tyvs = ty_bndrs -- preserved for ppr-ing , rd_tmvs = map (noLocA . RuleBndr noAnn . noLocA) (qtkvs ++ tpl_ids) , rd_lhs = mkHsDictLet lhs_binds lhs' - , rd_rhs = mkHsDictLet rhs_binds rhs' } } + , rd_rhs = mkHsDictLet rhs_binds rhs' }} generateRuleConstraints :: FastString -> Maybe [LHsTyVarBndr () GhcRn] -> [LRuleBndr GhcRn] ===================================== testsuite/tests/typecheck/T24026/T24026a.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026a where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026a.stderr ===================================== @@ -0,0 +1,9 @@ +T24026a.hs:4:11: warning: [GHC-95396] [-Winline-rule-shadowing (in -Wdefault)] + Rule "f" may never fire because ‘f’ might inline first + Suggested fix: Add an INLINE[n] or NOINLINE[n] pragma for ‘f’ + +T24026a.hs:4:37: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/T24026b.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026b where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026b.stderr ===================================== @@ -0,0 +1,5 @@ +T24026b.hs:4:37: error: [GHC-83865] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/all.T ===================================== @@ -0,0 +1,2 @@ +test('T24026a', normal, compile, ['-dlint -fdefer-type-errors']) +test('T24026b', normal, compile_fail, ['']) \ No newline at end of file View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/185986663d5ba14b00f836dfd1a915efdf36c94f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/185986663d5ba14b00f836dfd1a915efdf36c94f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 09:27:00 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Wed, 12 Jun 2024 05:27:00 -0400 Subject: [Git][ghc/ghc][wip/fabu/T24026-early-reject-type-failing-rules] 7 commits: users-guide: Fix stylistic issues in 9.12 release notes Message-ID: <666969e4dbd88_b01b01e272f41084ae@gitlab.mail> Fabricio Nascimento pushed to branch wip/fabu/T24026-early-reject-type-failing-rules at Glasgow Haskell Compiler / GHC Commits: e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 0b524559 by Fabricio de Sousa Nascimento at 2024-06-12T09:26:50+00:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - 27 changed files: - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Rule.hs - docs/users_guide/9.12.1-notes.rst - docs/users_guide/exts/assert.rst - docs/users_guide/phases.rst - + testsuite/tests/driver/cpp_assertions_ignored/Makefile - + testsuite/tests/driver/cpp_assertions_ignored/all.T - + testsuite/tests/driver/cpp_assertions_ignored/cpp_assertions_ignored.stdout - + testsuite/tests/driver/cpp_assertions_ignored/main.hs - testsuite/tests/th/T17820d.stderr - testsuite/tests/th/T23829_hasty_b.stderr - + testsuite/tests/typecheck/T24026/T24026a.hs - + testsuite/tests/typecheck/T24026/T24026a.stderr - + testsuite/tests/typecheck/T24026/T24026b.hs - + testsuite/tests/typecheck/T24026/T24026b.stderr - + testsuite/tests/typecheck/T24026/all.T - utils/haddock/Makefile - utils/haddock/README.md - utils/haddock/doc/intro.rst - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/resources/html/package.json - utils/haddock/haddock-library/haddock-library.cabal - utils/haddock/haddock-test/haddock-test.cabal - utils/haddock/haddock.cabal Changes: ===================================== compiler/GHC/Core/Opt/Simplify.hs ===================================== @@ -199,7 +199,7 @@ simplifyPgm logger unit_env name_ppr_ctx opts -- Subtract 1 from iteration_no to get the -- number of iterations we actually completed - return ( "Simplifier baled out", iteration_no - 1 + return ( "Simplifier bailed out", iteration_no - 1 , totalise counts_so_far , guts_no_binds { mg_binds = binds, mg_rules = local_rules } ) ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -1031,9 +1031,12 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs extra_bndrs = scopedSort extra_tvs ++ extra_dicts where extra_tvs = [ v | v <- extra_vars, isTyVar v ] + + -- isEvVar: this includes coercions, matching what + -- happens in `split_lets` (isDictId, isCoVar) extra_dicts = - [ mkLocalId (localiseName (idName d)) ManyTy (idType d) - | d <- extra_vars, isDictId d ] + [ mkLocalIdOrCoVar (localiseName (idName d)) ManyTy (idType d) + | d <- extra_vars, isEvVar d ] extra_vars = [ v | v <- exprsFreeVarsList args ===================================== compiler/GHC/SysTools/Cpp.hs ===================================== @@ -168,6 +168,9 @@ doCpp logger tmpfs dflags unit_env opts input_fn output_fn = do backend_defs <- applyCDefs (backendCDefs $ backend dflags) logger dflags let th_defs = [ "-D__GLASGOW_HASKELL_TH__" ] + + let asserts_def = [ "-D__GLASGOW_HASKELL_ASSERTS_IGNORED__" | gopt Opt_IgnoreAsserts dflags] + -- Default CPP defines in Haskell source ghcVersionH <- getGhcVersionPathName dflags unit_env let hsSourceCppOpts = [ "-include", ghcVersionH ] @@ -197,6 +200,7 @@ doCpp logger tmpfs dflags unit_env opts input_fn output_fn = do ++ map GHC.SysTools.Option target_defs ++ map GHC.SysTools.Option backend_defs ++ map GHC.SysTools.Option th_defs + ++ map GHC.SysTools.Option asserts_def ++ map GHC.SysTools.Option hscpp_opts ++ map GHC.SysTools.Option sse_defs ++ map GHC.SysTools.Option fma_def ===================================== compiler/GHC/Tc/Errors/Ppr.hs ===================================== @@ -1417,9 +1417,16 @@ instance Diagnostic TcRnMessage where , interpp'SP errorVars ] TcRnBadlyStaged reason bind_lvl use_lvl -> mkSimpleDecorated $ - text "Stage error:" <+> pprStageCheckReason reason <+> - hsep [text "is bound at stage" <+> ppr bind_lvl, - text "but used at stage" <+> ppr use_lvl] + vcat $ + [ text "Stage error:" <+> pprStageCheckReason reason <+> + hsep [text "is bound at stage" <+> ppr bind_lvl, + text "but used at stage" <+> ppr use_lvl] + ] ++ + [ hsep [ text "Hint: quoting" <+> thBrackets (ppUnless (isValName n) "t") (ppr n) + , text "or an enclosing expression would allow the quotation to be used in an earlier stage" + ] + | StageCheckSplice n <- [reason] + ] TcRnBadlyStagedType name bind_lvl use_lvl -> mkSimpleDecorated $ text "Badly staged type:" <+> ppr name <+> ===================================== compiler/GHC/Tc/Gen/Rule.hs ===================================== @@ -108,11 +108,13 @@ tcRules decls = mapM (wrapLocMA tcRuleDecls) decls tcRuleDecls :: RuleDecls GhcRn -> TcM (RuleDecls GhcTc) tcRuleDecls (HsRules { rds_ext = src , rds_rules = decls }) - = do { tc_decls <- mapM (wrapLocMA tcRule) decls + = do { maybe_tc_decls <- mapM (wrapLocMA tcRule) decls + ; let tc_decls = [L loc rule | (L loc (Just rule)) <- maybe_tc_decls] ; return $ HsRules { rds_ext = src , rds_rules = tc_decls } } -tcRule :: RuleDecl GhcRn -> TcM (RuleDecl GhcTc) + +tcRule :: RuleDecl GhcRn -> TcM (Maybe (RuleDecl GhcTc)) tcRule (HsRule { rd_ext = ext , rd_name = rname@(L _ name) , rd_act = act @@ -181,14 +183,22 @@ tcRule (HsRule { rd_ext = ext ; (rhs_implic, rhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs rhs_wanted ; emitImplications (lhs_implic `unionBags` rhs_implic) - ; return $ HsRule { rd_ext = ext + + -- insolubleImplic: if the LHS has an outright type error, drop the rule entirely + -- The error will be reported; but if `-fdefer-type-errors` is on we don't want + -- to continue, else we get a compiler crash (#24026) + ; if anyBag insolubleImplic lhs_implic + then + return Nothing -- The RULE LHS does not type-check and will be dropped. + else + return . Just $ HsRule { rd_ext = ext , rd_name = rname , rd_act = act , rd_tyvs = ty_bndrs -- preserved for ppr-ing , rd_tmvs = map (noLocA . RuleBndr noAnn . noLocA) (qtkvs ++ tpl_ids) , rd_lhs = mkHsDictLet lhs_binds lhs' - , rd_rhs = mkHsDictLet rhs_binds rhs' } } + , rd_rhs = mkHsDictLet rhs_binds rhs' }} generateRuleConstraints :: FastString -> Maybe [LHsTyVarBndr () GhcRn] -> [LRuleBndr GhcRn] ===================================== docs/users_guide/9.12.1-notes.rst ===================================== @@ -31,10 +31,10 @@ Language This means that code using :extension:`UnliftedDatatypes` or :extension:`UnliftedNewtypes` can now use :extension:`OverloadedRecordDot`. -- Unboxed Float#/Double# literals now support the HexFloatLiterals extension +- Unboxed ``Float#``/``Double#`` literals now support the HexFloatLiterals extension (`#22155 `_). -- UnliftedFFITypes: GHC will now accept ffi types like: ``(# #) -> T`` where ``(# #)`` +- :extension:`UnliftedFFITypes`: GHC will now accept FFI types like: ``(# #) -> T`` where ``(# #)`` is used as the one and only function argument. Compiler @@ -75,6 +75,13 @@ Compiler `_). This does not affect existing support of apple systems on x86_64/aarch64. +- The flag :ghc-flag:`-fignore-asserts` will now also enable the + :extension:`CPP` macro ``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` (`#24967 + `_). + This enables people to write their own custom assertion functions. + See :ref:`assertions`. + + GHCi ~~~~ ===================================== docs/users_guide/exts/assert.rst ===================================== @@ -50,4 +50,20 @@ allows enabling assertions even when optimisation is turned on. Assertion failures can be caught, see the documentation for the :base-ref:`Control.Exception.` library for the details. - +The ``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` CPP macro +===================================================== + +When code is compiled with assertions ignored (using :ghc-flag:`-fignore-asserts` or :ghc-flag:`-O`), +the :extension:`CPP` macro ``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` will be defined. +This can be used to conditionally compile your own custom assert-like functions. +For example: :: + + checkedAdd :: Word -> Word -> Word + #ifdef __GLASGOW_HASKELL_ASSERTS_IGNORED__ + checkedAdd lhs rhs = lhs + rhs + #else + checkedAdd lhs rhs + | res < lhs || res < rhs = raise OverflowException + | otherwise = res + where res = lhs + rhs + #endif ===================================== docs/users_guide/phases.rst ===================================== @@ -508,6 +508,13 @@ defined by your local GHC installation, the following trick is useful: is added, so for example when using version 3.7 of LLVM, ``__GLASGOW_HASKELL_LLVM__==307``). +``__GLASGOW_HASKELL_ASSERTS_IGNORED__`` + .. index:: + single: __GLASGOW_HASKELL_ASSERTS_IGNORED__ + + Only defined when :ghc-flag:`-fignore-asserts` is specified. + This can be used to create your own assertions, see :ref:`assertions` + ``__PARALLEL_HASKELL__`` .. index:: single: __PARALLEL_HASKELL__ ===================================== testsuite/tests/driver/cpp_assertions_ignored/Makefile ===================================== @@ -0,0 +1,11 @@ +TOP=../../.. +include $(TOP)/mk/boilerplate.mk +include $(TOP)/mk/test.mk + +cpp_assertions_ignored: + echo "Without -fignore-asserts" + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 main.hs + (./main 2>&1); true + echo "With -fignore-asserts" + '$(TEST_HC)' $(TEST_HC_OPTS) -v0 -fignore-asserts main.hs + ./main 2>&1 ===================================== testsuite/tests/driver/cpp_assertions_ignored/all.T ===================================== @@ -0,0 +1,4 @@ +test('cpp_assertions_ignored', + [ extra_files(['main.hs']) + ], + makefile_test, ['cpp_assertions_ignored']) ===================================== testsuite/tests/driver/cpp_assertions_ignored/cpp_assertions_ignored.stdout ===================================== @@ -0,0 +1,4 @@ +Without -fignore-asserts +Assertions Enabled +With -fignore-asserts +Assertions Ignored ===================================== testsuite/tests/driver/cpp_assertions_ignored/main.hs ===================================== @@ -0,0 +1,14 @@ +{-# LANGUAGE CPP #-} +import Control.Exception (assert) + +main = + if assertsEnabled + then putStrLn "Assertions Enabled" + else putStrLn "Assertions Ignored" + +assertsEnabled :: Bool +#ifdef __GLASGOW_HASKELL_ASSERTS_IGNORED__ +assertsEnabled = False +#else +assertsEnabled = True +#endif ===================================== testsuite/tests/th/T17820d.stderr ===================================== @@ -1,7 +1,8 @@ - T17820d.hs:6:38: error: [GHC-28914] • Stage error: ‘foo’ is bound at stage 2 but used at stage 1 + Hint: quoting [| foo |] or an enclosing expression would allow the quotation to be used in an earlier stage • In the untyped splice: $(const [| 0 |] foo) In the Template Haskell quotation [d| data D = MkD {foo :: Int} blargh = $(const [| 0 |] foo) |] + ===================================== testsuite/tests/th/T23829_hasty_b.stderr ===================================== @@ -1,6 +1,7 @@ - T23829_hasty_b.hs:8:42: error: [GHC-28914] • Stage error: ‘ty’ is bound at stage 2 but used at stage 1 + Hint: quoting [t| ty |] or an enclosing expression would allow the quotation to be used in an earlier stage • In the untyped splice: $ty In the Template Haskell quotation [t| forall (ty :: TypeQ). Proxy $ty |] + ===================================== testsuite/tests/typecheck/T24026/T24026a.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026a where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026a.stderr ===================================== @@ -0,0 +1,9 @@ +T24026a.hs:4:11: warning: [GHC-95396] [-Winline-rule-shadowing (in -Wdefault)] + Rule "f" may never fire because ‘f’ might inline first + Suggested fix: Add an INLINE[n] or NOINLINE[n] pragma for ‘f’ + +T24026a.hs:4:37: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/T24026b.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026b where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026b.stderr ===================================== @@ -0,0 +1,5 @@ +T24026b.hs:4:37: error: [GHC-83865] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/all.T ===================================== @@ -0,0 +1,2 @@ +test('T24026a', normal, compile, ['-dlint -fdefer-type-errors']) +test('T24026b', normal, compile_fail, ['']) \ No newline at end of file ===================================== utils/haddock/Makefile ===================================== @@ -8,18 +8,17 @@ test: ## Run the test suite @cabal test lint: ## Run the code linter (HLint) - @find driver haddock-api haddock-library haddock-test hoogle-test hypsrc-test latex-test \ - -name "*.hs" | xargs -P $(PROCS) -I {} hlint --refactor-options="-i" --refactor {} + @find driver haddock-api haddock-library -name "*.hs" | xargs -P $(PROCS) -I {} hlint --refactor-options="-i" --refactor {} style: ## Run the code styler (fourmolu and cabal-fmt) @cabal-fmt -i **/*.cabal @fourmolu -q --mode inplace driver haddock-api haddock-library style-check: ## Check the code's style (fourmolu and cabal-fmt) - @cabal-fmt -i **/*.cabal + @cabal-fmt -c **/*.cabal @fourmolu -q --mode check driver haddock-api haddock-library -style-quick: ## Run the code styler on modified files +style-quick: ## Run the code styler on modified files tracked by git @cabal-fmt -i **/*.cabal @git diff origin --name-only driver haddock-api haddock-library | xargs -P $(PROCS) -I {} fourmolu -q -i {} @@ -29,9 +28,12 @@ tags: ## Generate ctags and etags for the source code (ghc-tags) help: ## Display this help message @grep -E '^[a-zA-Z_-]+:.*?## .*$$' $(MAKEFILE_LIST) | awk 'BEGIN {FS = ":.* ?## "}; {printf "\033[36m%-30s\033[0m %s\n", $$1, $$2}' -PROCS := $(shell nproc) - .PHONY: all $(MAKECMDGOALS) .DEFAULT_GOAL := help +ifeq ($(UNAME), Darwin) + PROCS := $(shell sysctl -n hw.logicalcpu) +else + PROCS := $(shell nproc) +endif ===================================== utils/haddock/README.md ===================================== @@ -1,4 +1,4 @@ -# Haddock [![CI][CI badge]][CI page] [![Hackage][Hackage badge]][Hackage page] +# Haddock [![Hackage][Hackage badge]][Hackage page] Haddock is the standard tool for generating documentation from Haskell code. Full documentation about Haddock itself can be found in the `doc/` subdirectory, @@ -25,8 +25,6 @@ See [CONTRIBUTING.md](CONTRIBUTING.md) to see how to make contributions to the project. -[CI page]: https://github.com/haskell/haddock/actions/workflows/ci.yml -[CI badge]: https://github.com/haskell/haddock/actions/workflows/ci.yml/badge.svg [Hackage page]: https://hackage.haskell.org/package/haddock [Hackage badge]: https://img.shields.io/hackage/v/haddock.svg [reST]: https://www.sphinx-doc.org/en/master/usage/restructuredtext/index.html ===================================== utils/haddock/doc/intro.rst ===================================== @@ -62,9 +62,7 @@ Obtaining Haddock Haddock is distributed with GHC distributions, and will automatically be provided if you use `ghcup `__, for instance. -Up-to-date sources can also be obtained from our public GitHub -repository. The Haddock sources are at -``https://github.com/haskell/haddock``. +Haddock lives in the GHC repository, which you can consult at ``https://gitlab.haskell.org/ghc/ghc``. License ------- @@ -99,12 +97,6 @@ code, except where otherwise indicated. (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -Contributors ------------- - -A list of contributors to the project can be seen at -``https://github.com/haskell/haddock/graphs/contributors``. - Acknowledgements ---------------- ===================================== utils/haddock/haddock-api/haddock-api.cabal ===================================== @@ -7,13 +7,12 @@ description: Haddock is a documentation-generation tool for Haskell license: BSD-2-Clause license-file: LICENSE author: Simon Marlow, David Waern -maintainer: Alec Theriault , Alex Biehl , Simon Hengel , Mateusz Kowalczyk +maintainer: Haddock Team homepage: http://www.haskell.org/haddock/ -bug-reports: https://github.com/haskell/haddock/issues +bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new copyright: (c) Simon Marlow, David Waern category: Documentation build-type: Simple -tested-with: GHC==9.6.* extra-source-files: CHANGES.md @@ -39,6 +38,11 @@ data-files: html/Linuwial.std-theme/synopsis.png latex/haddock.sty +source-repository head + type: git + location: https://gitlab.haskell.org/ghc/ghc.git + subdir: utils/haddock/haddock-api + library default-language: Haskell2010 @@ -203,8 +207,3 @@ test-suite spec build-tool-depends: hspec-discover:hspec-discover ^>= 2.9 - -source-repository head - type: git - subdir: haddock-api - location: https://github.com/haskell/haddock.git ===================================== utils/haddock/haddock-api/resources/html/package.json ===================================== @@ -8,7 +8,8 @@ }, "repository": { "type": "git", - "url": "https://github.com/haskell/haddock.git" + "url": "https://gitlab.haskell.org/ghc/ghc.git" + "directory": "utils/haddock" }, "author": "Tim Baumann ", "contributors": [ ===================================== utils/haddock/haddock-library/haddock-library.cabal ===================================== @@ -2,7 +2,6 @@ cabal-version: 3.0 name: haddock-library version: 1.11.0 synopsis: Library exposing some functionality of Haddock. - description: Haddock is a documentation-generation tool for Haskell libraries. These modules expose some functionality of it without pulling in the GHC @@ -13,16 +12,10 @@ description: Haddock is a documentation-generation tool for Haskell license: BSD-2-Clause license-file: LICENSE -maintainer: Alec Theriault , Alex Biehl , Simon Hengel , Mateusz Kowalczyk +maintainer: Haddock Team homepage: http://www.haskell.org/haddock/ -bug-reports: https://github.com/haskell/haddock/issues +bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new category: Documentation -tested-with: GHC == 8.4.4 - , GHC == 8.6.5 - , GHC == 8.8.3 - , GHC == 8.10.1 - , GHC == 9.0.1 - , GHC == 9.2.0 extra-doc-files: CHANGES.md @@ -31,6 +24,11 @@ extra-source-files: fixtures/examples/*.input fixtures/examples/*.parsed +source-repository head + type: git + location: https://gitlab.haskell.org/ghc/ghc.git + subdir: utils/haddock/haddock-library + common lib-defaults default-language: Haskell2010 @@ -113,8 +111,3 @@ test-suite fixtures , filepath ^>= 1.4.1.2 , optparse-applicative >= 0.15 && < 0.19 , tree-diff ^>= 0.2 || ^>= 0.3 - -source-repository head - type: git - subdir: haddock-library - location: https://github.com/haskell/haddock.git ===================================== utils/haddock/haddock-test/haddock-test.cabal ===================================== @@ -6,11 +6,10 @@ license: BSD-2-Clause author: Simon Marlow, David Waern maintainer: Simon Hengel , Mateusz Kowalczyk homepage: http://www.haskell.org/haddock/ -bug-reports: https://github.com/haskell/haddock/issues +bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new copyright: (c) Simon Marlow, David Waern category: Documentation build-type: Simple -tested-with: GHC==9.6.* stability: experimental library ===================================== utils/haddock/haddock.cabal ===================================== @@ -29,13 +29,12 @@ description: license: BSD-3-Clause license-file: LICENSE author: Simon Marlow, David Waern -maintainer: Alec Theriault , Alex Biehl , Simon Hengel , Mateusz Kowalczyk +maintainer: Haddock Team homepage: http://www.haskell.org/haddock/ -bug-reports: https://github.com/haskell/haddock/issues +bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new copyright: (c) Simon Marlow, David Waern category: Documentation build-type: Simple -tested-with: GHC==9.6.* extra-source-files: CHANGES.md @@ -65,6 +64,11 @@ flag threaded default: True manual: True +source-repository head + type: git + location: https://gitlab.haskell.org/ghc/ghc.git + subdir: utils/haddock + executable haddock default-language: Haskell2010 main-is: Main.hs @@ -193,7 +197,3 @@ test-suite hoogle-test main-is: Main.hs hs-source-dirs: hoogle-test build-depends: base, filepath, haddock-test == 0.0.1 - -source-repository head - type: git - location: https://github.com/haskell/haddock.git View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/185986663d5ba14b00f836dfd1a915efdf36c94f...0b5245592b3dec53f0bf3a45c8eaf6aa8b56c65d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/185986663d5ba14b00f836dfd1a915efdf36c94f...0b5245592b3dec53f0bf3a45c8eaf6aa8b56c65d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 09:46:46 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Wed, 12 Jun 2024 05:46:46 -0400 Subject: [Git][ghc/ghc][wip/fabu/T24026-early-reject-type-failing-rules] compiler: Rejects RULES whose LHS immediately fails to type-check Message-ID: <66696e861239e_b01b02146624117539@gitlab.mail> Fabricio Nascimento pushed to branch wip/fabu/T24026-early-reject-type-failing-rules at Glasgow Haskell Compiler / GHC Commits: a0f0b870 by Fabricio de Sousa Nascimento at 2024-06-12T18:46:13+09:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - 7 changed files: - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/Tc/Gen/Rule.hs - + testsuite/tests/typecheck/T24026/T24026a.hs - + testsuite/tests/typecheck/T24026/T24026a.stderr - + testsuite/tests/typecheck/T24026/T24026b.hs - + testsuite/tests/typecheck/T24026/T24026b.stderr - + testsuite/tests/typecheck/T24026/all.T Changes: ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -1031,9 +1031,12 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs extra_bndrs = scopedSort extra_tvs ++ extra_dicts where extra_tvs = [ v | v <- extra_vars, isTyVar v ] + + -- isEvVar: this includes coercions, matching what + -- happens in `split_lets` (isDictId, isCoVar) extra_dicts = - [ mkLocalId (localiseName (idName d)) ManyTy (idType d) - | d <- extra_vars, isDictId d ] + [ mkLocalIdOrCoVar (localiseName (idName d)) ManyTy (idType d) + | d <- extra_vars, isEvVar d ] extra_vars = [ v | v <- exprsFreeVarsList args ===================================== compiler/GHC/Tc/Gen/Rule.hs ===================================== @@ -108,11 +108,13 @@ tcRules decls = mapM (wrapLocMA tcRuleDecls) decls tcRuleDecls :: RuleDecls GhcRn -> TcM (RuleDecls GhcTc) tcRuleDecls (HsRules { rds_ext = src , rds_rules = decls }) - = do { tc_decls <- mapM (wrapLocMA tcRule) decls + = do { maybe_tc_decls <- mapM (wrapLocMA tcRule) decls + ; let tc_decls = [L loc rule | (L loc (Just rule)) <- maybe_tc_decls] ; return $ HsRules { rds_ext = src , rds_rules = tc_decls } } -tcRule :: RuleDecl GhcRn -> TcM (RuleDecl GhcTc) + +tcRule :: RuleDecl GhcRn -> TcM (Maybe (RuleDecl GhcTc)) tcRule (HsRule { rd_ext = ext , rd_name = rname@(L _ name) , rd_act = act @@ -181,14 +183,22 @@ tcRule (HsRule { rd_ext = ext ; (rhs_implic, rhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs rhs_wanted ; emitImplications (lhs_implic `unionBags` rhs_implic) - ; return $ HsRule { rd_ext = ext + + -- insolubleImplic: if the LHS has an outright type error, drop the rule entirely + -- The error will be reported; but if `-fdefer-type-errors` is on we don't want + -- to continue, else we get a compiler crash (#24026) + ; if anyBag insolubleImplic lhs_implic + then + return Nothing -- The RULE LHS does not type-check and will be dropped. + else + return . Just $ HsRule { rd_ext = ext , rd_name = rname , rd_act = act , rd_tyvs = ty_bndrs -- preserved for ppr-ing , rd_tmvs = map (noLocA . RuleBndr noAnn . noLocA) (qtkvs ++ tpl_ids) , rd_lhs = mkHsDictLet lhs_binds lhs' - , rd_rhs = mkHsDictLet rhs_binds rhs' } } + , rd_rhs = mkHsDictLet rhs_binds rhs' }} generateRuleConstraints :: FastString -> Maybe [LHsTyVarBndr () GhcRn] -> [LRuleBndr GhcRn] ===================================== testsuite/tests/typecheck/T24026/T24026a.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026a where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026a.stderr ===================================== @@ -0,0 +1,9 @@ +T24026a.hs:4:11: warning: [GHC-95396] [-Winline-rule-shadowing (in -Wdefault)] + Rule "f" may never fire because ‘f’ might inline first + Suggested fix: Add an INLINE[n] or NOINLINE[n] pragma for ‘f’ + +T24026a.hs:4:37: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/T24026b.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026b where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026b.stderr ===================================== @@ -0,0 +1,5 @@ +T24026b.hs:4:37: error: [GHC-83865] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/all.T ===================================== @@ -0,0 +1,2 @@ +test('T24026a', normal, compile, ['-dlint -fdefer-type-errors']) +test('T24026b', normal, compile_fail, ['']) \ No newline at end of file View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a0f0b87008c1e391a1324a34969603eddb046a43 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a0f0b87008c1e391a1324a34969603eddb046a43 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 10:35:25 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Wed, 12 Jun 2024 06:35:25 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] slight improvement to vector unpack Message-ID: <666979ed8ef55_b01b027d8b54125992@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 7c08ed94 by sheaf at 2024-06-12T12:34:40+02:00 slight improvement to vector unpack - - - - - 1 changed file: - compiler/GHC/CmmToAsm/X86/CodeGen.hs Changes: ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1552,7 +1552,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps imm = litToImm lit code dst = case lit of - CmmInt 0 _ -> exp `snocOL` (VMOVU format (OpReg r) (OpReg dst)) + CmmInt 0 _ -> exp `snocOL` (MOV FF32 (OpReg r) (OpReg dst)) CmmInt _ _ -> exp `snocOL` (VPSHUFD format imm (OpReg r) dst) _ -> panic "Error in offset while unpacking" return (Any format code) @@ -1564,8 +1564,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps code dst = case lit of CmmInt 0 _ -> exp `snocOL` - (MOVL format (OpReg r) (OpAddr addr)) `snocOL` - (MOV FF64 (OpAddr addr) (OpReg dst)) + (MOV FF64 (OpReg r) (OpReg dst)) CmmInt 1 _ -> exp `snocOL` (MOVH format (OpReg r) (OpAddr addr)) `snocOL` (MOV FF64 (OpAddr addr) (OpReg dst)) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7c08ed94c0c102f2cbe1691088890c3b2ff1b3c6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7c08ed94c0c102f2cbe1691088890c3b2ff1b3c6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 10:50:42 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Wed, 12 Jun 2024 06:50:42 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] 4131 commits: [haddock @ 2002-04-04 16:23:43 by simonmar] Message-ID: <66697d825c39d_b01b02abf0ac134591@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 2b39cd94 by Simon Marlow at 2002-04-04T16:23:43+00:00 [haddock @ 2002-04-04 16:23:43 by simonmar] This is Haddock, my stab at a Haskell documentation tool. It's not quite ready for release yet, but I'm putting it in the repository so others can take a look. It uses a locally modified version of the hssource parser, extended with support for GHC extensions and documentation annotations. - - - - - 99ede94f by Simon Marlow at 2002-04-04T16:24:10+00:00 [haddock @ 2002-04-04 16:24:10 by simonmar] forgot one file - - - - - 8363294c by Simon Marlow at 2002-04-05T13:58:15+00:00 [haddock @ 2002-04-05 13:58:15 by simonmar] Remap names in the exported declarations to be "closer" to the current module. eg. if an exported declaration mentions a type 'T' which is imported from module A then re-exported from the current module, then links from the type or indeed the documentation will point to the current module rather than module A. This is to support better hiding: module A won't be referred to in the generated output. - - - - - 1570cbc1 by Simon Marlow at 2002-04-05T13:58:23+00:00 [haddock @ 2002-04-05 13:58:23 by simonmar] update the TODO list - - - - - 3a62f96b by Simon Marlow at 2002-04-05T14:11:51+00:00 [haddock @ 2002-04-05 14:11:51 by simonmar] Fix the anchor for a class declaration - - - - - c5d9a471 by Simon Marlow at 2002-04-05T14:18:41+00:00 [haddock @ 2002-04-05 14:18:41 by simonmar] remove underlines on visited links - - - - - 97280525 by Simon Marlow at 2002-04-05T16:11:47+00:00 [haddock @ 2002-04-05 16:11:47 by simonmar] - Update to generate more correct HTML. - Use our own non-overloaded table combinators, as the overloaded versions were giving me a headache. The improved type safety caught several errors in the HTML generation. - - - - - 9acd3a4d by Simon Marlow at 2002-04-05T16:32:19+00:00 [haddock @ 2002-04-05 16:32:19 by simonmar] Add width property to the title, and add TD.children for the module contents page. - - - - - ec9a0847 by Simon Marlow at 2002-04-08T16:39:56+00:00 [haddock @ 2002-04-08 16:39:56 by simonmar] Fix a problem with exports of the form T(..). - - - - - e4627dc8 by Simon Marlow at 2002-04-08T16:41:38+00:00 [haddock @ 2002-04-08 16:41:37 by simonmar] - Add our own versions of Html & BlockTable for the time being. - Add support for generating an index to the HTML backend - - - - - 2d73fd75 by Simon Marlow at 2002-04-09T11:23:24+00:00 [haddock @ 2002-04-09 11:23:24 by simonmar] Add '-- /' as a synonym for '-- |', for compatibility with IDoc. - - - - - 3675464e by Simon Marlow at 2002-04-09T11:33:55+00:00 [haddock @ 2002-04-09 11:33:54 by simonmar] - add the <...> syntax for marking up URLs in documentation - Make the output for data & class declarations more compact when there aren't any documentation annotations on the individual methods or constructors respectively. - - - - - 5077f5b1 by Simon Marlow at 2002-04-09T11:36:04+00:00 [haddock @ 2002-04-09 11:36:04 by simonmar] Update the TODO list - - - - - 9e83c54d by Simon Marlow at 2002-04-10T10:50:06+00:00 [haddock @ 2002-04-10 10:50:06 by simonmar] Use explicit 'px' suffix on pixel sizes; IE seems to prefer them - - - - - 052de51c by Simon Marlow at 2002-04-10T13:23:13+00:00 [haddock @ 2002-04-10 13:23:13 by simonmar] Lex URLs as a single token to avoid having to escape special characters inside the URL string. - - - - - 47187edb by Simon Marlow at 2002-04-10T13:23:55+00:00 [haddock @ 2002-04-10 13:23:55 by simonmar] Not sure why I made the constructor name for a record declaration into a TyCls name, but change it back into a Var name anyhow. - - - - - 3dc6aa81 by Simon Marlow at 2002-04-10T13:26:10+00:00 [haddock @ 2002-04-10 13:26:09 by simonmar] Lots of changes, including: - add index support to the HTML backend - clean up the renamer, put it into a monad - propogate unresolved names to the top level and report them in a nicer way - various bugfixes - - - - - c2a70a72 by Simon Marlow at 2002-04-10T13:32:39+00:00 [haddock @ 2002-04-10 13:32:39 by simonmar] Skeleton documentation - - - - - 50c98d17 by Simon Marlow at 2002-04-10T13:37:23+00:00 [haddock @ 2002-04-10 13:37:23 by simonmar] Update the TODO list, separate into pre-1.0 and post-1.0 items - - - - - f3778be6 by Simon Marlow at 2002-04-10T14:30:58+00:00 [haddock @ 2002-04-10 14:30:58 by simonmar] Add an introduction - - - - - cfbaf9f7 by Simon Marlow at 2002-04-10T14:59:51+00:00 [haddock @ 2002-04-10 14:59:51 by simonmar] Sort the module tree - - - - - 76bd7b34 by Simon Marlow at 2002-04-10T15:50:11+00:00 [haddock @ 2002-04-10 15:50:10 by simonmar] Generate a little table of contents at the top of the module doc (only if the module actually contains some section headings, though). - - - - - bb8560a1 by Simon Marlow at 2002-04-10T16:10:26+00:00 [haddock @ 2002-04-10 16:10:26 by simonmar] Now we understand (or at least don't barf on) type signatures in patterns such as you might find when scoped type variables are in use. - - - - - 86c2a026 by Simon Marlow at 2002-04-10T16:10:49+00:00 [haddock @ 2002-04-10 16:10:49 by simonmar] more updates - - - - - 1c052b0e by Simon Marlow at 2002-04-10T16:28:05+00:00 [haddock @ 2002-04-10 16:28:05 by simonmar] Parse errors in doc strings are now reported as warnings rather that causing the whole thing to fall over. It still needs cleaning up (the warning is emitted with trace) but this will do for the time being. - - - - - ace03e8f by Simon Marlow at 2002-04-10T16:38:03+00:00 [haddock @ 2002-04-10 16:38:03 by simonmar] update again - - - - - 69006c3e by Simon Marlow at 2002-04-11T13:38:02+00:00 [haddock @ 2002-04-11 13:38:02 by simonmar] mention Opera - - - - - fe9b10f8 by Simon Marlow at 2002-04-11T13:40:31+00:00 [haddock @ 2002-04-11 13:40:30 by simonmar] - copy haddock.css into the same place as the generated HTML - new option: --css <file> specifies the style sheet to use - new option: -o <dir> specifies the directory in which to generate the output. - because Haddock now needs to know where to find its default stylesheet, we have to have a wrapper script and do the haddock-inplace thing (Makefile code copied largely from fptools/happy). - - - - - 106adbbe by Simon Marlow at 2002-04-24T15:12:41+00:00 [haddock @ 2002-04-24 15:12:41 by simonmar] Stop slurping comment lines when we see a row of dashes longer than length 2: these are useful as separators. - - - - - 995d3f9e by Simon Marlow at 2002-04-24T15:14:12+00:00 [haddock @ 2002-04-24 15:14:11 by simonmar] Grok the kind of module headers we use in fptools/libraries, and pass the "portability", "stability", and "maintainer" strings through into the generated HTML. If the module header doesn't match the pattern, then we don't include the info in the HTML. - - - - - e14da136 by Simon Marlow at 2002-04-24T15:16:57+00:00 [haddock @ 2002-04-24 15:16:57 by simonmar] Done module headers now. - - - - - 2ca8dfd4 by Simon Marlow at 2002-04-24T15:57:48+00:00 [haddock @ 2002-04-24 15:57:47 by simonmar] Handle gcons in export lists (a common extension). - - - - - 044cea81 by Simon Marlow at 2002-04-25T14:20:12+00:00 [haddock @ 2002-04-25 14:20:12 by simonmar] Add the little lambda icon - - - - - 63955027 by Simon Marlow at 2002-04-25T14:40:05+00:00 [haddock @ 2002-04-25 14:40:05 by simonmar] - Add support for named chunks of documentation which can be referenced from the export list. - Copy the icon from $libdir to the destination in HTML mode. - - - - - 36e3f913 by Simon Marlow at 2002-04-25T16:48:36+00:00 [haddock @ 2002-04-25 16:48:36 by simonmar] More keyboard bashing - - - - - 7ae18dd0 by Simon Marlow at 2002-04-26T08:43:33+00:00 [haddock @ 2002-04-26 08:43:33 by simonmar] Package util reqd. to compile with 4.08.2 - - - - - bbd5fbab by Simon Marlow at 2002-04-26T10:13:00+00:00 [haddock @ 2002-04-26 10:13:00 by simonmar] Include $(GHC_HAPPY_OPTS) when compiling HsParser - - - - - 31c53d79 by Simon Marlow at 2002-04-26T11:18:57+00:00 [haddock @ 2002-04-26 11:18:56 by simonmar] - support for fundeps (partially contributed by Brett Letner - thanks Brett). - make it build with GHC 4.08.2 - - - - - c415ce76 by Simon Marlow at 2002-04-26T13:15:02+00:00 [haddock @ 2002-04-26 13:15:02 by simonmar] Move the explicit formatting of the little table for the stability/portability/maintainer info from the HTML into the CSS, and remove the explicit table size (just right-align it). - - - - - 520ee21a by Simon Marlow at 2002-04-26T16:01:44+00:00 [haddock @ 2002-04-26 16:01:44 by simonmar] Yet more keyboard bashing - this is pretty much complete now. - - - - - 2ae37179 by Simon Marlow at 2002-04-26T16:02:14+00:00 [haddock @ 2002-04-26 16:02:14 by simonmar] Add a couple of things I forgot about - - - - - b7211e04 by Simon Marlow at 2002-04-29T15:28:12+00:00 [haddock @ 2002-04-29 15:28:12 by simonmar] bugfix for declBinders on a NewTypeDecl - - - - - 640c154a by Simon Marlow at 2002-04-29T15:28:54+00:00 [haddock @ 2002-04-29 15:28:54 by simonmar] Allow '-- |' style annotations on constructors and record fields. - - - - - 393f258a by Simon Marlow at 2002-04-29T15:37:32+00:00 [haddock @ 2002-04-29 15:37:32 by simonmar] syntax fix - - - - - 8a2c2549 by Simon Marlow at 2002-04-29T15:37:48+00:00 [haddock @ 2002-04-29 15:37:48 by simonmar] Add an example - - - - - db88f8a2 by Simon Marlow at 2002-04-29T15:55:46+00:00 [haddock @ 2002-04-29 15:55:46 by simonmar] remove a trace - - - - - 2b0248e0 by Simon Marlow at 2002-04-29T15:56:19+00:00 [haddock @ 2002-04-29 15:56:19 by simonmar] Fix for 'make install' - - - - - 120453a0 by Simon Marlow at 2002-04-29T15:56:39+00:00 [haddock @ 2002-04-29 15:56:39 by simonmar] Install the auxilliary bits - - - - - 950e6dbb by Simon Marlow at 2002-04-29T15:57:30+00:00 [haddock @ 2002-04-29 15:57:30 by simonmar] Add BinDist bits - - - - - 154b9d71 by Simon Marlow at 2002-05-01T11:02:52+00:00 [haddock @ 2002-05-01 11:02:52 by simonmar] update - - - - - ba6c39fa by Simon Marlow at 2002-05-01T11:03:26+00:00 [haddock @ 2002-05-01 11:03:26 by simonmar] Add another item - - - - - bacb5e33 by Simon Marlow at 2002-05-03T08:50:00+00:00 [haddock @ 2002-05-03 08:50:00 by simonmar] Fix some typos. - - - - - 54c87895 by Sven Panne at 2002-05-05T19:40:51+00:00 [haddock @ 2002-05-05 19:40:51 by panne] As a temporary hack/workaround for a bug in GHC's simplifier, don't pass Happy the -c option for generating the parsers in this subdir. Furthermore, disable -O for HaddocParse, too. - - - - - e6c08703 by Simon Marlow at 2002-05-06T09:51:10+00:00 [haddock @ 2002-05-06 09:51:10 by simonmar] Add RPM spec file (thanks to Tom Moertel <tom-rpms at moertel.com>) - - - - - 7b8fa8e7 by Simon Marlow at 2002-05-06T12:29:26+00:00 [haddock @ 2002-05-06 12:29:26 by simonmar] Add missing type signature (a different workaround for the bug in GHC's simplifier). - - - - - cd0e300d by Simon Marlow at 2002-05-06T12:30:09+00:00 [haddock @ 2002-05-06 12:30:09 by simonmar] Remove workaround for simplifier bug in previous revision. - - - - - 687e68fa by Simon Marlow at 2002-05-06T12:32:32+00:00 [haddock @ 2002-05-06 12:32:32 by simonmar] Allow empty data declarations (another GHC extension). - - - - - 8f29f696 by Simon Marlow at 2002-05-06T12:49:21+00:00 [haddock @ 2002-05-06 12:49:21 by simonmar] Fix silly bug in named documentation block lookup. - - - - - 8e0059af by Simon Marlow at 2002-05-06T13:02:42+00:00 [haddock @ 2002-05-06 13:02:42 by simonmar] Add another named chunk with a different name - - - - - 68f8a896 by Simon Marlow at 2002-05-06T13:32:32+00:00 [haddock @ 2002-05-06 13:32:32 by simonmar] Be more lenient about extra paragraph breaks - - - - - 65fc31db by Simon Marlow at 2002-05-07T15:36:36+00:00 [haddock @ 2002-05-07 15:36:36 by simonmar] DocEmpty is a right and left-unit of DocAppend (remove it in the smart constructor). - - - - - adc81078 by Simon Marlow at 2002-05-07T15:37:15+00:00 [haddock @ 2002-05-07 15:37:15 by simonmar] Allow code blocks to be denoted with bird-tracks in addition to [...]. - - - - - 1283a3c1 by Simon Marlow at 2002-05-08T11:21:56+00:00 [haddock @ 2002-05-08 11:21:56 by simonmar] Add a facility for specifying options that affect Haddock's treatment of the module. Options are given at the top of the module in a comma-separated list, beginning with '-- #'. eg. -- # prune, hide, ignore-exports Options currently available, with their meanings: prune: ignore declarations which have no documentation annotations ignore-exports: act as if the export list were not specified (i.e. export everything local to the module). hide: do not include this module in the generated documentation, but propagate any exported definitions to modules which re-export them. There's a slight change in the semantics for re-exporting a full module by giving 'module M' in the export list: if module M does not have the 'hide' option, then the documentation will now just contain a reference to module M rather than the full inlined contents of that module. These features, and some other changes in the pipeline, are the result of discussions between myself and Manuel Chakravarty <chak at cse.unsw.edu.au> (author of IDoc) yesterday. Also: some cleanups, use a Writer monad to collect error messages in some places instead of just printing them with trace. - - - - - a2239cf5 by Simon Marlow at 2002-05-08T11:22:30+00:00 [haddock @ 2002-05-08 11:22:30 by simonmar] Update to test new features. - - - - - 6add955f by Simon Marlow at 2002-05-08T13:37:25+00:00 [haddock @ 2002-05-08 13:37:25 by simonmar] Change the markup for typewriter-font from [...] to @... at . The reasoning is that the '@' symbol is much less likely to be needed than square brackets, and we don't want to have to escape square brackets in code fragments. This will be mildly painful in the short term, but it's better to get the change out of the way as early as possible. - - - - - cda06447 by Simon Marlow at 2002-05-08T13:39:56+00:00 [haddock @ 2002-05-08 13:39:56 by simonmar] Allow nested-style comments to be used as documentation annotations too. eg. {-| ... -} is equivalent to -- | ... An extra space can also be left after the comment opener: {- | ... -}. The only version that isn't allowed is {-# ... -}, because this syntax overlaps with Haskell pragmas; use {- # ... -} instead. - - - - - db23f65e by Simon Marlow at 2002-05-08T14:48:41+00:00 [haddock @ 2002-05-08 14:48:39 by simonmar] Add support for existential quantifiers on constructors. - - - - - adce3794 by Simon Marlow at 2002-05-08T15:43:25+00:00 [haddock @ 2002-05-08 15:43:25 by simonmar] update - - - - - 62a1f436 by Simon Marlow at 2002-05-08T15:44:10+00:00 [haddock @ 2002-05-08 15:44:10 by simonmar] Update to version 0.2 - - - - - f6a24ba3 by Simon Marlow at 2002-05-09T08:48:29+00:00 [haddock @ 2002-05-09 08:48:29 by simonmar] typo - - - - - 9f9522a4 by Simon Marlow at 2002-05-09T10:33:14+00:00 [haddock @ 2002-05-09 10:33:14 by simonmar] oops, left out '/' from the special characters in the last change. - - - - - 14abcb39 by Simon Marlow at 2002-05-09T10:34:44+00:00 [haddock @ 2002-05-09 10:34:44 by simonmar] Fix buglet - - - - - b8d878be by Simon Marlow at 2002-05-09T10:35:00+00:00 [haddock @ 2002-05-09 10:35:00 by simonmar] Give a more useful instance of Show for Module. - - - - - f7bfd626 by Simon Marlow at 2002-05-09T10:37:07+00:00 [haddock @ 2002-05-09 10:37:07 by simonmar] The last commit to Main.lhs broke the delicate balance of laziness which was being used to avoid computing the dependency graph of modules. So I finally bit the bullet and did a proper topological sort of the module graph, which turned out to be easy (stealing the Digraph module from GHC - this really ought to be in the libraries somewhere). - - - - - b481c1d0 by Simon Marlow at 2002-05-09T10:37:25+00:00 [haddock @ 2002-05-09 10:37:25 by simonmar] another item done - - - - - 032e2b42 by Simon Marlow at 2002-05-09T10:44:15+00:00 [haddock @ 2002-05-09 10:44:15 by simonmar] Don't consider a module re-export as having documentation, for the purposes of deciding whether we need a Synopsis section or not. - - - - - 5fb45e92 by Simon Marlow at 2002-05-09T11:10:55+00:00 [haddock @ 2002-05-09 11:10:55 by simonmar] Add a special case for list types in ppHsAType - - - - - 1937e428 by Simon Marlow at 2002-05-09T12:43:06+00:00 [haddock @ 2002-05-09 12:43:06 by simonmar] Type synonyms can accept a ctype on the RHS, to match GHC. - - - - - 0f16ce56 by Simon Marlow at 2002-05-09T12:45:19+00:00 [haddock @ 2002-05-09 12:45:19 by simonmar] Add 'stdcall' keyword - - - - - 29b0d7d2 by Simon Marlow at 2002-05-09T13:35:45+00:00 [haddock @ 2002-05-09 13:35:45 by simonmar] Add System Requirements section - - - - - bf14dddd by Simon Marlow at 2002-05-09T13:36:11+00:00 [haddock @ 2002-05-09 13:36:11 by simonmar] Test existential types, amongst other things - - - - - 502f8f6f by Simon Marlow at 2002-05-09T13:37:35+00:00 [haddock @ 2002-05-09 13:37:35 by simonmar] Print the module name in a doc-string parse error - - - - - ca1f8d49 by Simon Marlow at 2002-05-09T13:38:04+00:00 [haddock @ 2002-05-09 13:38:04 by simonmar] Add dependency - - - - - 8d3d91ff by Simon Marlow at 2002-05-09T15:37:57+00:00 [haddock @ 2002-05-09 15:37:57 by simonmar] Add the changelog/release notes - - - - - f3960959 by Simon Marlow at 2002-05-09T15:47:47+00:00 [haddock @ 2002-05-09 15:47:47 by simonmar] mention the backquote-style of markup - - - - - 089fb6e6 by Simon Marlow at 2002-05-09T15:59:45+00:00 [haddock @ 2002-05-09 15:59:45 by simonmar] update - - - - - bdd3be0b by Simon Marlow at 2002-05-09T15:59:56+00:00 [haddock @ 2002-05-09 15:59:56 by simonmar] Document changes since 0.1 - - - - - 00fc4af8 by Simon Marlow at 2002-05-10T08:22:48+00:00 [haddock @ 2002-05-10 08:22:48 by simonmar] oops, update to version 0.2 - - - - - a8a79041 by Simon Marlow at 2002-05-10T16:05:08+00:00 [haddock @ 2002-05-10 16:05:08 by simonmar] Only include a mini-contents if there are 2 or more sections - - - - - 06653319 by Simon Marlow at 2002-05-13T09:13:12+00:00 [haddock @ 2002-05-13 09:13:12 by simonmar] fix typos - - - - - 1402b19b by Simon Marlow at 2002-05-13T10:14:22+00:00 [haddock @ 2002-05-13 10:14:22 by simonmar] Allow backquote as the right-hand quote as well as the left-hand quote, as suggested by Dean Herrington. Clean up the grammar a litte. - - - - - dcd5320d by Simon Marlow at 2002-05-13T10:44:10+00:00 [haddock @ 2002-05-13 10:44:10 by simonmar] a couple more things, prioritise a bit - - - - - a90130c4 by Simon Marlow at 2002-05-13T15:19:03+00:00 [haddock @ 2002-05-13 15:19:03 by simonmar] Cope with datatypes which have documentation on the constructor but not the type itself, and records which have documentation on the fields but not the constructor. (Thanks to Ross Paterson for pointing out the bugs). - - - - - a774d432 by Simon Marlow at 2002-05-13T15:20:54+00:00 [haddock @ 2002-05-13 15:20:54 by simonmar] Fix one of the record examples - - - - - 2d1d5218 by Simon Marlow at 2002-05-15T12:44:35+00:00 [haddock @ 2002-05-15 12:44:35 by simonmar] Preserve the newline before a bird-track, but only within a paragraph. - - - - - 1554c09a by Simon Marlow at 2002-05-15T13:03:02+00:00 [haddock @ 2002-05-15 13:03:01 by simonmar] Reworking of the internals to support documenting function arguments (the Most Wanted new feature by the punters). The old method of keeping parsed documentation in a Name -> Doc mapping wasn't going to cut it for anntations on type components, where there's no name to attach the documentation to, so I've moved to storing all the documentation in the abstract syntax. Previously some of the documentation was left in the abstract syntax by the parser, but was later extracted into the mapping. In order to avoid having to parameterise the abstract syntax over the type of documentation stored in it, we have to parse the documentation at the same time as we parse the Haskell source (well, I suppose we could store 'Either String Doc' in the HsSyn, but that's clunky). One upshot is that documentation is now parsed eagerly, and documentation parse errors are fatal (but have better line numbers in the error message). The new story simplifies matters for the code that processes the source modules, because we don't have to maintain the extra Name->Doc mapping, and it should improve efficiency a little too. New features: - Function arguments and return values can now have doc annotations. - If you refer to a qualified name in a doc string, eg. 'IO.putStr', then Haddock will emit a hyperlink even if the identifier is not in scope, so you don't have to make sure everything referred to from the documentation is imported. - several bugs & minor infelicities fixed. - - - - - 57344dc3 by Simon Marlow at 2002-05-15T13:03:19+00:00 [haddock @ 2002-05-15 13:03:19 by simonmar] Bump to version 0.3 - - - - - b2791812 by Simon Marlow at 2002-05-15T13:03:41+00:00 [haddock @ 2002-05-15 13:03:41 by simonmar] update - - - - - fead183e by Simon Marlow at 2002-05-15T13:10:15+00:00 [haddock @ 2002-05-15 13:10:15 by simonmar] Rename Foo.hs to Test.hs, and add a Makefile - - - - - b0b1f89f by Simon Marlow at 2002-05-15T13:16:07+00:00 [haddock @ 2002-05-15 13:16:07 by simonmar] - Remove the note about function argument docs not being implemented - Note that qualified identifiers can be used to point to entities that aren't in scope. - - - - - 5665f31a by Simon Marlow at 2002-05-15T13:28:46+00:00 [haddock @ 2002-05-15 13:28:46 by simonmar] Patch to add support for GHC-style primitive strings ".."#, from Ross Paterson. - - - - - 0564505d by Simon Marlow at 2002-05-17T10:51:57+00:00 [haddock @ 2002-05-17 10:51:57 by simonmar] Fix bugs in qualified name handling (A.B.f was returned as B.f) - - - - - 10e7311c by Simon Marlow at 2002-05-21T10:24:52+00:00 [haddock @ 2002-05-21 10:24:52 by simonmar] - Use an alternate tabular layout for datatypes, which is more compact - Fix some problems with the function argument documentation - - - - - 2f91c2a6 by Simon Marlow at 2002-05-21T10:27:40+00:00 [haddock @ 2002-05-21 10:27:40 by simonmar] add a few more test cases - - - - - 01c2ddd2 by Simon Marlow at 2002-05-21T10:28:33+00:00 [haddock @ 2002-05-21 10:28:33 by simonmar] Rearrange a bit, and add support for tabular datatype rendering - - - - - a4e4c5f8 by Simon Marlow at 2002-05-27T09:03:52+00:00 [haddock @ 2002-05-27 09:03:51 by simonmar] Lots of changes: - instances of a class are listed with the class, and instances involving a datatype are listed with that type. Derived instances aren't included at the moment: the calculation to find the instance head for a derived instance is non-trivial. - some formatting changes; use rows with specified height rather than cellspacing in some places. - various fixes (source file links were wrong, amongst others) - - - - - 48722e68 by Simon Marlow at 2002-05-27T12:30:38+00:00 [haddock @ 2002-05-27 12:30:37 by simonmar] - Put function arguments *before* the doc for the function, as suggested by Sven Panne. This looks nicer when the function documentation is long. - Switch to using bold for binders at the definition site, and use underline for keywords. This makes the binder stand out more. - - - - - 657204d2 by Simon Marlow at 2002-05-27T13:19:49+00:00 [haddock @ 2002-05-27 13:19:49 by simonmar] Fix bug: we weren't renaming HsDocCommentNamed in renameDecl - - - - - 592aae66 by Simon Marlow at 2002-05-27T14:10:27+00:00 [haddock @ 2002-05-27 14:10:27 by simonmar] Fix some bugs in the rendering of qualified type signatures. - - - - - 69c8f763 by Simon Marlow at 2002-05-27T14:36:45+00:00 [haddock @ 2002-05-27 14:36:45 by simonmar] warning message tweak - - - - - 16e64e21 by Simon Marlow at 2002-05-27T14:53:53+00:00 [haddock @ 2002-05-27 14:53:53 by simonmar] hyperlinked identifiers should be in <tt> - - - - - 8d5e4783 by Simon Marlow at 2002-05-27T15:56:45+00:00 [haddock @ 2002-05-27 15:56:45 by simonmar] Do something sensible for modules which don't export anything (except instances). - - - - - 9d3ef811 by Simon Marlow at 2002-05-28T10:12:50+00:00 [haddock @ 2002-05-28 10:12:50 by simonmar] Rename the module documentation properly (bug reported by Sven Panne). - - - - - ef03a1cc by Simon Marlow at 2002-05-28T10:13:04+00:00 [haddock @ 2002-05-28 10:13:04 by simonmar] Add some more test cases - - - - - 92baa0e8 by Simon Marlow at 2002-05-28T11:17:55+00:00 [haddock @ 2002-05-28 11:17:55 by simonmar] If an identifier doesn't lex, then just replace it by a DocString. - - - - - a3156213 by Simon Marlow at 2002-05-28T16:16:19+00:00 [haddock @ 2002-05-28 16:16:19 by simonmar] Only link to names in the current module which are actually listed in the documentation. A name may be exported but not present in the documentation if it is exported as part of a 'module M' export specifier. - - - - - 31acf941 by Simon Marlow at 2002-05-28T16:17:11+00:00 [haddock @ 2002-05-28 16:17:11 by simonmar] update - - - - - 7e474ebf by Sigbjorn Finne at 2002-05-28T22:42:08+00:00 [haddock @ 2002-05-28 22:42:08 by sof] Handle lone occurrences of '/', e.g., -- | This/that. [did this in the lexer rather than in the parser, as I couldn't see a way not to introduce an S/R conflict that way.] - - - - - 093f7e53 by Simon Marlow at 2002-05-29T09:09:49+00:00 [haddock @ 2002-05-29 09:09:49 by simonmar] Back out previous change until we can find a better way to do this. - - - - - 9234389c by Simon Marlow at 2002-05-29T13:19:06+00:00 [haddock @ 2002-05-29 13:19:06 by simonmar] Make the markup syntax a little more friendly: - single quotes are now interpreted literally unless they surround a valid Haskell identifier. So for example now there's no need to escape a single quote used as an apostrophe. - text to the right of a bird track is now literal (if you want marked-up text in a code block, use @...@). - - - - - b3333526 by Simon Marlow at 2002-05-29T13:38:51+00:00 [haddock @ 2002-05-29 13:38:51 by simonmar] Document recent changes to markup syntax - - - - - f93641d6 by Simon Marlow at 2002-05-29T15:27:18+00:00 [haddock @ 2002-05-29 15:27:18 by simonmar] Include the instances in abstract data types too - - - - - 613f21e3 by Simon Marlow at 2002-06-03T13:05:58+00:00 [haddock @ 2002-06-03 13:05:57 by simonmar] Allow exporting of individual class methods and record selectors. For these we have to invent the correct type signature, which we do in the simplest possible way (i.e. no context reduction nonsense in the class case). - - - - - 14b36807 by Simon Marlow at 2002-06-03T13:20:00+00:00 [haddock @ 2002-06-03 13:20:00 by simonmar] Fix linking to qualified names again (thanks to Sven Panne for pointing out the bug). - - - - - 95b10eac by Simon Marlow at 2002-06-03T13:46:48+00:00 [haddock @ 2002-06-03 13:46:48 by simonmar] Fix for exporting record selectors from a newtype declaration - - - - - 272f932e by Simon Marlow at 2002-06-03T13:56:38+00:00 [haddock @ 2002-06-03 13:56:38 by simonmar] update to version 0.3 - - - - - 1c0a3bed by Simon Marlow at 2002-06-03T14:05:07+00:00 [haddock @ 2002-06-03 14:05:07 by simonmar] Add changes in version 0.3 - - - - - 145b4626 by Simon Marlow at 2002-06-03T14:12:38+00:00 [haddock @ 2002-06-03 14:12:38 by simonmar] Render class names as proper binders - - - - - 052106b3 by Simon Marlow at 2002-06-03T14:15:10+00:00 [haddock @ 2002-06-03 14:15:10 by simonmar] update, and separate into bugs, features, and cosmetic items. - - - - - 854f4914 by Simon Marlow at 2002-06-03T14:16:13+00:00 [haddock @ 2002-06-03 14:16:13 by simonmar] More test cases - - - - - 466922c8 by Simon Marlow at 2002-06-03T14:16:56+00:00 [haddock @ 2002-06-03 14:16:56 by simonmar] Example from the paper - - - - - 9962a045 by Simon Marlow at 2002-06-03T14:17:49+00:00 [haddock @ 2002-06-03 14:17:49 by simonmar] A debugging version of the style-sheet, which gives some tables coloured backgrounds so we can see what's going on. - - - - - f16b79db by Simon Marlow at 2002-06-03T14:19:46+00:00 [haddock @ 2002-06-03 14:19:46 by simonmar] typo - - - - - 620db27b by Simon Marlow at 2002-06-03T14:48:32+00:00 [haddock @ 2002-06-03 14:48:32 by simonmar] oops, fix markup bugs - - - - - 53fd105c by Simon Marlow at 2002-06-05T09:05:07+00:00 [haddock @ 2002-06-05 09:05:07 by simonmar] Keep foreign imports when there is no export list (bug reported by Sven Panne). - - - - - 6d98989c by Simon Marlow at 2002-06-05T09:12:02+00:00 [haddock @ 2002-06-05 09:12:02 by simonmar] Identifiers in single quotes can be symbol names too (bug reported by Hal Daume). - - - - - 001811e5 by Sven Panne at 2002-06-08T14:03:36+00:00 [haddock @ 2002-06-08 14:03:36 by panne] Tiny workaround for the fact that Haddock currently ignores HsImportSpecs: Let the local_orig_env take precedence. This is no real solution at all, but improves things sometimes, e.g. in my GLUT documentation. :-) - - - - - 504d19c9 by Simon Marlow at 2002-06-11T09:23:25+00:00 [haddock @ 2002-06-11 09:23:25 by simonmar] portability nit - - - - - e13b5af4 by Simon Marlow at 2002-06-20T12:38:07+00:00 [haddock @ 2002-06-20 12:38:07 by simonmar] Empty declaration fixes. - - - - - f467a9b6 by Simon Marlow at 2002-06-20T12:39:02+00:00 [haddock @ 2002-06-20 12:39:01 by simonmar] Add support for a "prologue" - a description for the whole library, placed on the contents page before the module list. - - - - - b8dbfe20 by Simon Marlow at 2002-06-21T12:43:06+00:00 [haddock @ 2002-06-21 12:43:06 by simonmar] When we have a single code block paragraph, don't place it in <pre>..</pre>, just use <tt>..</tt> to avoid generating extra vertical white space in some browsers. - - - - - 4831dbbd by Simon Marlow at 2002-06-21T15:50:42+00:00 [haddock @ 2002-06-21 15:50:42 by simonmar] Add support for reading and writing interface files(!) This turned out to be quite easy, and necessary to get decent hyperlinks between the documentation for separate packages in the libraries. The functionality isn't quite complete yet: for a given package of modules, you'd like to say "the HTML for these modules lives in directory <dir>" (currently they are assumed to be all in the same place). Two new flags: --dump-interface=FILE dump an interface file in FILE --read-interface=FILE read interface from FILE an interface file describes *all* the modules being processed. Only the exported names are kept in the interface: if you re-export a name from a module in another interface the signature won't be copied. This is a compromise to keep the size of the interfaces sensible. Also, I added another useful option: --no-implicit-prelude avoids trying to import the Prelude. Previously this was the default, but now importing the Prelude from elsewhere makes sense if you also read in an interface containing the Prelude module, so Haddock imports the Prelude implicitly according to the Haskell spec. - - - - - d3640a19 by Sven Panne at 2002-06-23T14:54:00+00:00 [haddock @ 2002-06-23 14:54:00 by panne] Make it compile with newer GHCs - - - - - 780c506b by Sven Panne at 2002-06-23T15:44:31+00:00 [haddock @ 2002-06-23 15:44:31 by panne] Cleaned up build root handling and added more docs - - - - - 45290d2e by Simon Marlow at 2002-06-24T14:37:43+00:00 [haddock @ 2002-06-24 14:37:42 by simonmar] When reading an interface, allow a file path offset to be specified which represents the path to the HTML files for the modules specified by that interface. The path may be either relative (to the location of the HTML for this package), or absolute. The syntax is --read-interface=PATH,FILE where PATH is the path to the HTML, and FILE is the filename containing the interface. - - - - - 4e2b9ae6 by Simon Marlow at 2002-07-03T16:01:08+00:00 [haddock @ 2002-07-03 16:01:07 by simonmar] Handle import specs properly, include 'hiding'. Haddock now has a complete implementation of the Haskell module system (more or less; I won't claim it's 100% correct). - - - - - 9a9aa1a8 by Simon Marlow at 2002-07-03T16:18:16+00:00 [haddock @ 2002-07-03 16:18:16 by simonmar] Update - - - - - 560c3026 by Simon Marlow at 2002-07-04T14:56:10+00:00 [haddock @ 2002-07-04 14:56:10 by simonmar] Clean up the code that constructs the exported declarations, and fix a couple of bugs along the way. Now if you import a class hiding one of the methods, then re-export the class, the version in the documentation will correctly have the appropriate method removed. - - - - - 2c26e77d by Simon Marlow at 2002-07-04T15:26:13+00:00 [haddock @ 2002-07-04 15:26:13 by simonmar] More bugfixes to the export handling - - - - - 03e0710d by Simon Marlow at 2002-07-09T10:12:10+00:00 [haddock @ 2002-07-09 10:12:10 by simonmar] Don't require that the list type comes from "Prelude" for it to be treated as special syntax (sometimes it comes from Data.List or maybe even GHC.Base). - - - - - 44f3891a by Simon Marlow at 2002-07-09T10:12:51+00:00 [haddock @ 2002-07-09 10:12:51 by simonmar] commented-out debugging code - - - - - 97280873 by Krasimir Angelov at 2002-07-09T16:33:33+00:00 [haddock @ 2002-07-09 16:33:31 by krasimir] 'Microsoft HTML Help' support - - - - - 3dc04655 by Simon Marlow at 2002-07-10T09:40:56+00:00 [haddock @ 2002-07-10 09:40:56 by simonmar] Fix for rendering of the (->) type constructor, from Ross Paterson. - - - - - c9f149c6 by Simon Marlow at 2002-07-10T10:26:11+00:00 [haddock @ 2002-07-10 10:26:11 by simonmar] Tweaks to the MS Help support: the extra files are now only generated if you ask for them (--ms-help). - - - - - e8acc1e6 by Simon Marlow at 2002-07-10T10:57:10+00:00 [haddock @ 2002-07-10 10:57:10 by simonmar] Document all the new options since 0.3 - - - - - 8bb85544 by Simon Marlow at 2002-07-10T10:58:31+00:00 [haddock @ 2002-07-10 10:58:31 by simonmar] Sort the options a bit - - - - - abc0dd59 by Simon Marlow at 2002-07-15T09:19:38+00:00 [haddock @ 2002-07-15 09:19:38 by simonmar] Fix a bug in mkExportItems when processing a module without an explicit export list. We were placing one copy of a declaration for each binder in the declaration, which for a data type would mean one copy of the whole declaration per constructor or record selector. - - - - - dde65bb9 by Simon Marlow at 2002-07-15T09:54:16+00:00 [haddock @ 2002-07-15 09:54:16 by simonmar] merge rev. 1.35 - - - - - bd7eb8c4 by Simon Marlow at 2002-07-15T10:14:31+00:00 [haddock @ 2002-07-15 10:14:30 by simonmar] Be a bit more liberal in the kind of commenting styles we allow, as suggested by Malcolm Wallace. Mostly this consists of allowing doc comments either side of a separator token. In an export list, a section heading is now allowed before the comma, as well as after it. eg. module M where ( T(..) -- * a section heading , f -- * another section heading , g ) In record fields, doc comments are allowed anywhere (previously a doc-next was allowed only after the comma, and a doc-before was allowed only before the comma). eg. data R = C { -- | describes 'f' f :: Int -- | describes 'g' , g :: Int } - - - - - 8f6dfe34 by Simon Marlow at 2002-07-15T10:21:56+00:00 [haddock @ 2002-07-15 10:21:56 by simonmar] Mention alternative commenting styles. - - - - - fc515bb7 by Simon Marlow at 2002-07-15T16:16:50+00:00 [haddock @ 2002-07-15 16:16:50 by simonmar] Allow multiple sections/subsections before and after a comma in the export list. Also at the same time I made the syntax a little stricter (multiple commas now aren't allowed between export specs). - - - - - 80a97e74 by Simon Marlow at 2002-07-19T09:13:10+00:00 [haddock @ 2002-07-19 09:13:10 by simonmar] Allow special id's ([], (), etc.) to be used in an import declaration. - - - - - a69d7378 by Simon Marlow at 2002-07-19T09:59:02+00:00 [haddock @ 2002-07-19 09:59:02 by simonmar] Allow special id's ([], (), etc.) to be used in an import declarations. - - - - - d205fa60 by Simon Marlow at 2002-07-19T10:00:16+00:00 [haddock @ 2002-07-19 10:00:16 by simonmar] Relax the restrictions which require doc comments to be followed by semi colons - in some cases this isn't necessary. Now you can write module M where { -- | some doc class C where {} } without needing to put a semicolon before the class declaration. - - - - - e9301e14 by Simon Marlow at 2002-07-23T08:24:09+00:00 [haddock @ 2002-07-23 08:24:09 by simonmar] A new TODO list item - - - - - e5d77586 by Simon Marlow at 2002-07-23T08:40:56+00:00 [haddock @ 2002-07-23 08:40:56 by simonmar] - update the acknowledgements - remove the paragraph that described how to use explicit layout with doc comments; it isn't relevant any more. - - - - - 78a94137 by Simon Marlow at 2002-07-23T08:43:02+00:00 [haddock @ 2002-07-23 08:43:02 by simonmar] more tests - - - - - 5c320927 by Simon Marlow at 2002-07-23T08:43:26+00:00 [haddock @ 2002-07-23 08:43:26 by simonmar] Updates for version 0.4 - - - - - 488e99ae by Simon Marlow at 2002-07-23T09:10:46+00:00 [haddock @ 2002-07-23 09:10:46 by simonmar] Fix the %changelog (rpm complained that it wasn't in the right order) - - - - - a77bb373 by Simon Marlow at 2002-07-23T09:12:38+00:00 [haddock @ 2002-07-23 09:12:38 by simonmar] Another item for the TODO list - - - - - f1ec1813 by Simon Marlow at 2002-07-23T10:18:46+00:00 [haddock @ 2002-07-23 10:18:46 by simonmar] Add a version banner when invoked with -v - - - - - 1d44cadf by Simon Marlow at 2002-07-24T09:28:19+00:00 [haddock @ 2002-07-24 09:28:19 by simonmar] Remove ^Ms - - - - - 4d8d5e94 by Simon Marlow at 2002-07-24T09:42:18+00:00 [haddock @ 2002-07-24 09:42:17 by simonmar] Patches to quieten ghc -Wall, from those nice folks at Galois. - - - - - d6edc43e by Simon Marlow at 2002-07-25T14:37:29+00:00 [haddock @ 2002-07-25 14:37:28 by simonmar] Patch to allow simple hyperlinking to an arbitrary location in another module's documentation, from Volker Stolz. Now in a doc comment: #foo# creates <a name="foo"></a> And you can use the form "M\#foo" to hyperlink to the label 'foo' in module 'M'. Note that the backslash is necessary for now. - - - - - b34d18fa by Simon Marlow at 2002-08-02T09:08:22+00:00 [haddock @ 2002-08-02 09:08:22 by simonmar] The <TT> and <PRE> environments seem to use a font that is a little too small in IE. Compensate. (suggestion from Daan Leijen). - - - - - 8106b086 by Simon Marlow at 2002-08-02T09:25:23+00:00 [haddock @ 2002-08-02 09:25:20 by simonmar] Remove <P>..</P> from around list items, to reduce excess whitespace between the items of bulleted and ordered lists. (Suggestion from Daan Leijen). - - - - - c1acff8f by Simon Marlow at 2002-08-05T09:03:49+00:00 [haddock @ 2002-08-05 09:03:49 by simonmar] update - - - - - f968661c by Simon Marlow at 2002-11-11T09:32:57+00:00 [haddock @ 2002-11-11 09:32:57 by simonmar] Fix cut-n-pasto - - - - - 12d02619 by Simon Marlow at 2002-11-13T09:49:46+00:00 [haddock @ 2002-11-13 09:49:46 by simonmar] Small bugfix in the --read-interface option parsing from Brett Letner. - - - - - 30e32d5e by Ross Paterson at 2003-01-16T15:07:57+00:00 [haddock @ 2003-01-16 15:07:57 by ross] Adjust for the new exception libraries (as well as the old ones). - - - - - 871f65df by Sven Panne at 2003-02-20T21:31:40+00:00 [haddock @ 2003-02-20 21:31:40 by panne] * Add varsyms and consyms to index * Exclude empty entries from index - - - - - bc42cc87 by Sven Panne at 2003-02-24T21:26:29+00:00 [haddock @ 2003-02-24 21:26:29 by panne] Don't convert a "newtype" to a single-constructor "data" for non-abstractly exported types, they are quite different regarding strictness/pattern matching. Now a "data" without any constructors is only emitted for an abstractly exported type, regardless if it is actually a "newtype" or a "data". - - - - - 0c2a1d99 by Sven Panne at 2003-03-08T19:02:38+00:00 [haddock @ 2003-03-08 19:02:38 by panne] Fixed some broken/redirected/canonicalized links found by a very picky link checker. - - - - - 25459269 by Sven Panne at 2003-03-09T21:13:43+00:00 [haddock @ 2003-03-09 21:13:43 by panne] Don't append a fragment to non-defining index entries, only documents with a defining occurrence have a name anchor. - - - - - 6be4db86 by Sven Panne at 2003-03-10T21:34:25+00:00 [haddock @ 2003-03-10 21:34:24 by panne] Escape fragments. This fixes e.g. links to operators. - - - - - eb12972c by Ross Paterson at 2003-04-25T10:50:06+00:00 [haddock @ 2003-04-25 10:50:05 by ross] An 80% solution to generating derived instances. A complete solution would duplicate the instance inference logic, but if a type variable occurs as a constructor argument, then we can just propagate the derived class to the variable. But we know nothing of the constraints on any type variables that occur elsewhere. For example, the declarations data Either a b = Left a | Right b deriving (Eq, Ord) data Ptr a = Ptr Addr# deriving (Eq, Ord) newtype IORef a = IORef (STRef RealWorld a) deriving Eq yield the instances (Eq a, Eq b) => Eq (Either a b) (Ord a, Ord b) => Ord (Either a b) Eq (Ptr a) Ord (Ptr a) (??? a) => Eq (IORef a) The last example shows the limits of this local analysis. Note that a type variable may be in both categories: then we know a constraint, but there may be more, or a stronger constraint, e.g. data Tree a = Node a [Tree a] deriving Eq yields (Eq a, ??? a) => Eq (Tree a) - - - - - de886f78 by Simon Marlow at 2003-04-25T11:17:55+00:00 [haddock @ 2003-04-25 11:17:55 by simonmar] Some updates, including moving the derived instance item down to the bottom of the list now that Ross has contributed some code that does the job for common cases. - - - - - 1b52cffd by Simon Marlow at 2003-04-30T14:02:32+00:00 [haddock @ 2003-04-30 14:02:32 by simonmar] When installing on Windows, run cygpath over $(HADDOCKLIB) so that haddock (a mingw program, built by GHC) can understand it. You still need to be in a cygwin environment to run Haddock, because of the shell script wrapper. - - - - - d4f638de by Simon Marlow at 2003-05-06T10:04:47+00:00 [haddock @ 2003-05-06 10:04:47 by simonmar] Catch another case of a paragraph containing just a DocMonospaced that should turn into a DocCodeBlock. - - - - - 4162b2b9 by Simon Marlow at 2003-05-06T10:11:44+00:00 [haddock @ 2003-05-06 10:11:44 by simonmar] Add some more code-block tests. - - - - - 4f5802c8 by Simon Marlow at 2003-05-06T10:14:52+00:00 [haddock @ 2003-05-06 10:14:52 by simonmar] Don't turn a single DocCodeBlock into a DocMonospaced, because that tends to remove the line breaks in the code. - - - - - ef8c45f7 by Simon Marlow at 2003-05-21T15:07:21+00:00 [haddock @ 2003-05-21 15:07:21 by simonmar] Only omit the module contents when there are no section headings at all. - - - - - bcee1e75 by Sigbjorn Finne at 2003-05-30T16:50:45+00:00 [haddock @ 2003-05-30 16:50:45 by sof] cygpath: for now, steer clear of --mixed - - - - - 30567af3 by Sigbjorn Finne at 2003-05-30T17:59:28+00:00 [haddock @ 2003-05-30 17:59:28 by sof] oops, drop test defn from prev commit - - - - - b0856e7d by Simon Marlow at 2003-06-03T09:55:26+00:00 [haddock @ 2003-06-03 09:55:26 by simonmar] Two small fixes to make the output valid HTML 4.01 (transitional). Thanks to Malcolm Wallace for pointing out the problems. - - - - - 70e137ea by Simon Marlow at 2003-07-28T13:30:35+00:00 [haddock @ 2003-07-28 13:30:35 by simonmar] Add tests for a couple of bugs. - - - - - 122bd578 by Simon Marlow at 2003-07-28T13:31:25+00:00 [haddock @ 2003-07-28 13:31:25 by simonmar] Add documentation for anchors. - - - - - 0bd27cb2 by Simon Marlow at 2003-07-28T13:31:46+00:00 [haddock @ 2003-07-28 13:31:46 by simonmar] Update - - - - - 08052d42 by Simon Marlow at 2003-07-28T13:32:12+00:00 [haddock @ 2003-07-28 13:32:12 by simonmar] layout tweak. - - - - - 13942749 by Simon Marlow at 2003-07-28T13:33:03+00:00 [haddock @ 2003-07-28 13:33:03 by simonmar] Differentiate links to types/classes from links to variables/constructors with a prefix ("t:" and "v:" respectively). - - - - - d7f493b9 by Simon Marlow at 2003-07-28T13:35:17+00:00 [haddock @ 2003-07-28 13:35:16 by simonmar] When a module A exports another module's contents via 'module B', then modules which import entities from B re-exported by A should link to B.foo rather than A.foo. See examples/Bug2.hs. - - - - - d94cf705 by Simon Marlow at 2003-07-28T13:36:14+00:00 [haddock @ 2003-07-28 13:36:14 by simonmar] Update to version 0.5 - - - - - dbb776cd by Sven Panne at 2003-07-28T14:02:43+00:00 [haddock @ 2003-07-28 14:02:43 by panne] * Updated to version 0.5 * Automagically generate configure if it is not there - - - - - 6cfeee53 by Simon Marlow at 2003-07-28T14:32:43+00:00 [haddock @ 2003-07-28 14:32:42 by simonmar] Update to avoid using hslibs with GHC >= 5.04 - - - - - a1ce838f by Simon Marlow at 2003-07-28T14:33:37+00:00 [haddock @ 2003-07-28 14:33:37 by simonmar] Update for 0.5 - - - - - c0fe6493 by Simon Marlow at 2003-07-28T14:53:22+00:00 [haddock @ 2003-07-28 14:53:22 by simonmar] Markup fix - - - - - 6ea31596 by Sven Panne at 2003-07-28T16:40:45+00:00 [haddock @ 2003-07-28 16:40:45 by panne] Make it compile with GHC >= 6.01 - - - - - afcd30fc by Simon Marlow at 2003-07-30T15:04:52+00:00 [haddock @ 2003-07-30 15:04:52 by simonmar] Pay attention to import specs when building the the import env, as well as the orig env. This may fix some wrong links in documentation when import specs are being used. - - - - - 17c3137f by Simon Marlow at 2003-07-30T16:05:41+00:00 [haddock @ 2003-07-30 16:05:40 by simonmar] Rename instances based on the import_env for the module in which they are to be displayed. This should give, in many cases, better links for the types and classes mentioned in the instance head. This involves keeping around the import_env in the iface until the end, because instances are not collected up until all the modules have been processed. Fortunately it doesn't seem to affect performance much. Instance heads are now attached to ExportDecls, rather than the HTML backend passing around a separate mapping for instances. This is a cleanup. - - - - - 3d3b5c87 by Sven Panne at 2003-08-04T10:18:24+00:00 [haddock @ 2003-08-04 10:18:24 by panne] Don't print parentheses around one-element contexts - - - - - 9e3f3f2d by Simon Marlow at 2003-08-04T12:59:47+00:00 [haddock @ 2003-08-04 12:59:47 by simonmar] A couple of TODOs. - - - - - e9d8085c by Simon Marlow at 2003-08-05T14:10:31+00:00 [haddock @ 2003-08-05 14:10:31 by simonmar] I'm not sure why, but it seems that the index entries for non-defining occurrences of entities did not have an anchor - the link just pointed to the module. This fixes it. - - - - - ff5c7d6d by Simon Marlow at 2003-08-15T14:42:59+00:00 [haddock @ 2003-08-15 14:42:59 by simonmar] Convert the lexer to Alex, and fix a bug in the process. - - - - - 1aa077bf by Simon Marlow at 2003-08-15T15:00:18+00:00 [haddock @ 2003-08-15 15:00:18 by simonmar] Update - - - - - d3de1e38 by Simon Marlow at 2003-08-15T15:01:03+00:00 [haddock @ 2003-08-15 15:01:03 by simonmar] wibbles - - - - - b40ece3b by Simon Marlow at 2003-08-18T10:04:47+00:00 [haddock @ 2003-08-18 10:04:47 by simonmar] Lex the 'mdo' keyword as 'do'. - - - - - 8f9a1146 by Simon Marlow at 2003-08-18T11:48:24+00:00 [haddock @ 2003-08-18 11:48:24 by simonmar] Two bugs from Sven. - - - - - ea54ebc0 by Simon Marlow at 2003-08-18T11:48:46+00:00 [haddock @ 2003-08-18 11:48:46 by simonmar] Fixes to the new lexer. - - - - - d5f6a4b5 by Simon Marlow at 2003-08-19T09:09:03+00:00 [haddock @ 2003-08-19 09:09:03 by simonmar] Further wibbles to the syntax. - - - - - 6bbdadb7 by Sven Panne at 2003-08-26T18:45:35+00:00 [haddock @ 2003-08-26 18:45:35 by panne] Use autoreconf instead of autoconf - - - - - 32e889cb by Sven Panne at 2003-08-26T19:01:19+00:00 [haddock @ 2003-08-26 19:01:18 by panne] Made option handling a bit more consistent with other tools, in particular: Every program in fptools should output * version info on stdout and terminate successfully when -V or --version * usage info on stdout and terminate successfully when -? or --help * usage info on stderr and terminate unsuccessfully when an unknown option is given. - - - - - 5d156a91 by Sven Panne at 2003-08-26T19:20:55+00:00 [haddock @ 2003-08-26 19:20:55 by panne] Make it *very* clear that we terminate when given a -V/--version flag - - - - - e6577265 by Sven Panne at 2003-08-27T07:50:03+00:00 [haddock @ 2003-08-27 07:50:02 by panne] * Made -D a short option for --dump-interface. * Made -m a short option for --ms-help. * Made -n a short option for --no-implicit-prelude. * Made -c a short option for --css. * Removed DocBook options from executable (they didn't do anything), but mark them as reserved in the docs. Note that the short option for DocBook output is now -S (from SGML) instead of -d. The latter is now a short option for --debug. * The order of the Options in the documentation now matches the order printed by Haddock itself. Note: Although changing the names of options is often a bad idea, I'd really like to make the options for the programs in fptools more consistent and compatible to the ones used in common GNU programs. - - - - - d303ff98 by Simon Marlow at 2003-09-10T08:23:48+00:00 [haddock @ 2003-09-10 08:23:48 by simonmar] Add doc subdir. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 9a70e46a by Simon Marlow at 2003-09-10T08:24:32+00:00 [haddock @ 2003-09-10 08:24:32 by simonmar] Install these files in $(datadir), not $(libdir), since they're architecture independent. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - bbb87e7a by Simon Marlow at 2003-09-10T08:25:31+00:00 [haddock @ 2003-09-10 08:25:31 by simonmar] Haddock's supplementary HTML bits now live in $(datadir), not $(libdir). Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 3587c24b by Simon Marlow at 2003-09-22T10:34:38+00:00 [haddock @ 2003-09-22 10:34:38 by simonmar] Allow installing of docs. - - - - - d510b517 by Sven Panne at 2003-10-11T08:10:44+00:00 [haddock @ 2003-10-11 08:10:44 by panne] Include architecture-independent files in file list - - - - - 187d7618 by Sigbjorn Finne at 2003-10-20T17:19:24+00:00 [haddock @ 2003-10-20 17:19:22 by sof] support for i-parameters + zip comprehensions - - - - - b6c7a273 by Simon Marlow at 2003-11-03T14:24:24+00:00 [haddock @ 2003-11-03 14:24:24 by simonmar] Update TODO file. - - - - - 58513e33 by Simon Marlow at 2003-11-05T11:22:04+00:00 [haddock @ 2003-11-05 11:22:04 by simonmar] Remove the last of the uses of 'trace' to emit warnings, and tidy up a couple of places where duplicate warnings were being emitted. - - - - - 33a78846 by Simon Marlow at 2003-11-05T11:30:53+00:00 [haddock @ 2003-11-05 11:30:52 by simonmar] - Suppress warnings about unknown imported modules by default. - Add a -v/--verbose flag to re-enable these warnings. The general idea is to suppress the "Warning: unknown module: Prelude" warnings which most Haddock users will see every time, and which aren't terribly useful. - - - - - a969de7f by Simon Marlow at 2003-11-05T12:30:28+00:00 [haddock @ 2003-11-05 12:30:28 by simonmar] - Remove the emboldening of index entries for defining locations. This isn't useful, and breaks abstractions. - If an entity is re-exported by a module but the module doesn't include documentation for that entity (perhaps because it is re-exported by 'module M'), then don't attempt to hyperlink to the documentation from the index. Instead, just list that module in the index, to indicate that the entity is exported from there. - - - - - f14ea82a by Simon Marlow at 2003-11-05T15:15:59+00:00 [haddock @ 2003-11-05 15:15:59 by simonmar] Index overhaul: - no more separate type/class and variable/function indices - the index now makes a distinction between different entities with the same name. One example is a type constructor with the same name as a data constructor, but another example is simply a function with the same name exported by two different modules. For example, the index entry for 'catch' now looks like this: catch 1 (Function) Control.Exception 2 (Function) GHC.Exception, Prelude, System.IO, System.IO.Error making it clear that there are two different 'catch'es, but one of them is exported by several modules. - Each index page now has the index contents (A B C ...) at the top. Please let me know if you really hate any of this. - - - - - 01a25ca6 by Simon Marlow at 2003-11-05T15:16:38+00:00 [haddock @ 2003-11-05 15:16:38 by simonmar] Update - - - - - 1a7ccb86 by Simon Marlow at 2003-11-05T17:16:05+00:00 [haddock @ 2003-11-05 17:16:04 by simonmar] Support for generating a single unified index for several packages. --use-index=URL turns off normal index generation, causes Index links to point to URL. --gen-index generates an combined index from the specified interfaces. Currently doesn't work exactly right, because the interfaces don't contain the iface_reexported info. I'll need to fix that up. - - - - - a2bca16d by Simon Marlow at 2003-11-06T10:44:52+00:00 [haddock @ 2003-11-06 10:44:52 by simonmar] Include iface_reexported in the .haddock file. This unfortunately bloats the file (40% for base). If this gets to be a problem we can always apply the dictionary trick that GHC uses for squashing .hi files. - - - - - 0a09c293 by Simon Marlow at 2003-11-06T12:39:47+00:00 [haddock @ 2003-11-06 12:39:46 by simonmar] - Add definition lists, marked up like this: -- | This is a definition list: -- -- [@foo@] The description of @foo at . -- -- [@bar@] The description of @bar at . Cunningly, the [] characters are not treated specially unless a [ is found at the beginning of a paragraph, in which case the ] becomes special in the following text. - Add --use-contents and --gen-contents, along the lines of --use-index and --gen-index added yesterday. Now we can generate a combined index and contents for the whole of the hierarchical libraries, and in theory the index/contents on the system could be updated as new packages are added. - - - - - fe1b3460 by Simon Marlow at 2003-11-06T14:47:36+00:00 [haddock @ 2003-11-06 14:47:36 by simonmar] Remove the 'Parent' button - it is of dubious use, and often points into thin air. - - - - - db6d762f by Simon Marlow at 2003-11-06T16:48:14+00:00 [haddock @ 2003-11-06 16:48:11 by simonmar] - Include the OptHide setting in the interface, so we don't include hidden modules in the combined index/contents. - Add a -k/--package flag to set the package name for the current set of modules. The package name for each module is now shown in the right-hand column of the contents, in a combined contents page. - - - - - 7d71718b by Simon Marlow at 2003-11-06T16:50:28+00:00 [haddock @ 2003-11-06 16:50:28 by simonmar] Add -k/--package docs - - - - - ef43949d by Simon Marlow at 2003-11-06T16:51:23+00:00 [haddock @ 2003-11-06 16:51:23 by simonmar] Bump to 0.6 - - - - - 1c419e06 by Simon Marlow at 2003-11-06T16:51:50+00:00 [haddock @ 2003-11-06 16:51:50 by simonmar] update - - - - - 69422327 by Simon Marlow at 2003-11-10T14:41:06+00:00 [haddock @ 2003-11-10 14:41:05 by simonmar] Re-exporting names from a different package is problematic, because we don't have access to the full documentation for the entity. Currently Haddock just ignores entities with no documentation, but this results in bogus-looking empty documentation for many of the modules in the haskell98 package. So: - the documentation will now just list the name, as a link pointing to the location of the actual documentation. - now we don't attempt to link to these re-exported entities if they are referred to by the current module. Additionally: - If there is no documentation in the current module, include just the Synopsis section (rather than just the documentation section, as it was before). This just looks nicer and was on the TODO list. - - - - - 3c3fc433 by Simon Marlow at 2003-11-10T14:51:59+00:00 [haddock @ 2003-11-10 14:51:59 by simonmar] Fix for getReExports: take into account names which are not visible because they are re-exported from a different package. - - - - - 31c8437b by Simon Marlow at 2003-11-10T15:10:53+00:00 [haddock @ 2003-11-10 15:10:53 by simonmar] Version 0.6 changes - - - - - a7c2430b by Simon Marlow at 2003-11-10T15:15:58+00:00 [haddock @ 2003-11-10 15:15:58 by simonmar] getReExports: one error case that isn't - - - - - 00cc459c by Simon Marlow at 2003-11-10T16:15:19+00:00 [haddock @ 2003-11-10 16:15:18 by simonmar] copyright update - - - - - ca62408d by Simon Marlow at 2003-11-11T09:57:25+00:00 [haddock @ 2003-11-11 09:57:25 by simonmar] Version 0.6 - - - - - 3acbf818 by Simon Marlow at 2003-11-11T12:10:44+00:00 [haddock @ 2003-11-11 12:10:44 by simonmar] Go back to producing just the documentation section, rather than just the synopsis section, for a module with no documentation annotations. One reason is that the synopsis section tries to link each entity to its documentation on the same page. Also, the doc section anchors each entity, and it lists instances which the synopsis doesn't. - - - - - 6c90abc2 by Simon Marlow at 2003-11-12T10:03:39+00:00 [haddock @ 2003-11-12 10:03:39 by simonmar] 2002 -> 2003 - - - - - 090bbc4c by Simon Marlow at 2003-11-28T12:08:00+00:00 [haddock @ 2003-11-28 12:08:00 by simonmar] update - - - - - 8096a832 by Simon Marlow at 2003-11-28T12:09:58+00:00 [haddock @ 2003-11-28 12:09:58 by simonmar] Fix some of the problems with Haddock generating pages that are too wide. Now we only specify 'nowrap' when it is necessary to avoid a code box getting squashed up by the text to the right of it. - - - - - 35294929 by Sven Panne at 2003-12-29T17:16:31+00:00 [haddock @ 2003-12-29 17:16:31 by panne] Updated my email address - - - - - cdb697bf by Simon Marlow at 2004-01-08T10:14:24+00:00 [haddock @ 2004-01-08 10:14:24 by simonmar] Add instructions for using GHC to pre-process source for feeding to Haddock. - - - - - 8dfc491f by Simon Marlow at 2004-01-09T12:45:46+00:00 [haddock @ 2004-01-09 12:45:46 by simonmar] Add -optP-P to example ghc command line. - - - - - ac41b820 by Simon Marlow at 2004-02-03T11:02:03+00:00 [haddock @ 2004-02-03 11:02:03 by simonmar] Fix bug in index generation - - - - - f4e7edcb by Simon Marlow at 2004-02-10T11:51:16+00:00 [haddock @ 2004-02-10 11:51:16 by simonmar] Don't throw away whitespace at the beginning of a line (experimental fix). - - - - - 68e212d2 by Simon Marlow at 2004-02-10T12:10:08+00:00 [haddock @ 2004-02-10 12:10:08 by simonmar] Fix for previous commit: I now realise why the whitespace was stripped from the beginning of the line. Work around it. - - - - - e7d7f2df by Sven Panne at 2004-02-10T18:38:45+00:00 [haddock @ 2004-02-10 18:38:45 by panne] Make Haddock link with the latest relocated monad transformer package - - - - - 992d4225 by Simon Marlow at 2004-02-16T10:21:35+00:00 [haddock @ 2004-02-16 10:21:35 by simonmar] Add a TODO - - - - - 1ac55326 by Simon Marlow at 2004-03-12T11:33:39+00:00 [haddock @ 2004-03-12 11:33:39 by simonmar] Add an item. - - - - - 0478e903 by Simon Marlow at 2004-03-15T12:24:05+00:00 [haddock @ 2004-03-15 12:24:05 by simonmar] Add an item. - - - - - 6f26d21a by Simon Marlow at 2004-03-18T14:21:29+00:00 [haddock @ 2004-03-18 14:21:29 by simonmar] Fix URL - - - - - 19b6bb99 by Simon Marlow at 2004-03-22T14:09:03+00:00 [haddock @ 2004-03-22 14:09:03 by simonmar] getReExports was bogus: we should really look in the import_env to find the documentation for an entity which we are re-exporting without documentation. Suggested by: Ross Paterson (patch modified by me). - - - - - 5c756031 by Simon Marlow at 2004-03-24T09:42:11+00:00 [haddock @ 2004-03-24 09:42:10 by simonmar] hiding bug from Ross Paterson (fixed in rev 1.59 of Main.hs) - - - - - 1b692e6c by Simon Marlow at 2004-03-24T10:10:50+00:00 [haddock @ 2004-03-24 10:10:50 by simonmar] mkExportItems fix & simplification: we should be looking at the actual exported names (calculated earlier) to figure out which subordinates of a declaration are exported. This means that if you export a record, and name its fields separately in the export list, the fields will still be visible in the documentation for the constructor. - - - - - 90e5e294 by Simon Marlow at 2004-03-24T10:12:08+00:00 [haddock @ 2004-03-24 10:12:08 by simonmar] Make restrictCons take into account record field names too (removing a ToDo). - - - - - 2600efa4 by Simon Marlow at 2004-03-24T10:16:17+00:00 [haddock @ 2004-03-24 10:16:17 by simonmar] Record export tests. - - - - - 6a8575c7 by Simon Marlow at 2004-03-25T09:35:14+00:00 [haddock @ 2004-03-25 09:35:14 by simonmar] restrictTo: fix for restricting a newtype with a record field. - - - - - dcf55a8d by Simon Marlow at 2004-03-25T10:01:42+00:00 [haddock @ 2004-03-25 10:01:42 by simonmar] Fix duplicate instance bug - - - - - f49aa758 by Simon Marlow at 2004-03-25T10:02:41+00:00 [haddock @ 2004-03-25 10:02:41 by simonmar] Duplicate instance bug. - - - - - 7b87344c by Simon Marlow at 2004-03-25T10:29:56+00:00 [haddock @ 2004-03-25 10:29:56 by simonmar] If a name is imported from two places, one hidden and one not, choose the unhidden one to link to. Also, when there's only a hidden module to link to, don't try linking to it. - - - - - 40f44d7b by Simon Marlow at 2004-03-25T15:17:24+00:00 [haddock @ 2004-03-25 15:17:23 by simonmar] Add support for collaspible parts of the page, with a +/- button and a bit of JavaScript. Make the instances collapsible, and collapse them by default. This makes documentation with long lists of instances (eg. the Prelude) much easier to read. Maybe we should give other documentation sections the same treatment. - - - - - 9b64dc0f by Simon Marlow at 2004-03-25T15:20:55+00:00 [haddock @ 2004-03-25 15:20:55 by simonmar] Update - - - - - c2fff7f2 by Simon Marlow at 2004-03-25T15:45:10+00:00 [haddock @ 2004-03-25 15:45:10 by simonmar] Eliminate some unnecessary spaces in the HTML rendering - - - - - b7948ff0 by Simon Marlow at 2004-03-25T16:00:37+00:00 [haddock @ 2004-03-25 16:00:36 by simonmar] Remove all that indentation in the generated HTML to keep the file sizes down. - - - - - da2bb4ca by Sven Panne at 2004-03-27T09:57:58+00:00 [haddock @ 2004-03-27 09:57:57 by panne] Added the new-born haddock.js to the build process and the documentation. - - - - - b99e6f8c by Sven Panne at 2004-03-27T10:32:20+00:00 [haddock @ 2004-03-27 10:32:20 by panne] "type" is a required attribute of the "script" element - - - - - 562b185a by Sven Panne at 2004-03-27T12:52:34+00:00 [haddock @ 2004-03-27 12:52:34 by panne] Add a doctype for the contents page, too. - - - - - f6a99c2d by Simon Marlow at 2004-04-14T10:03:25+00:00 [haddock @ 2004-04-14 10:03:25 by simonmar] fix for single-line comment syntax - - - - - de366303 by Simon Marlow at 2004-04-20T13:08:04+00:00 [haddock @ 2004-04-20 13:08:04 by simonmar] Allow a 'type' declaration to include documentation comments. These will be ignored by Haddock, but at least one user (Johannes Waldmann) finds this feature useful, and it's easy to add. - - - - - fd78f51e by Simon Marlow at 2004-05-07T15:14:56+00:00 [haddock @ 2004-05-07 15:14:56 by simonmar] - update copyright - add version to abstract - - - - - 59f53e32 by Sven Panne at 2004-05-09T14:39:53+00:00 [haddock @ 2004-05-09 14:39:53 by panne] Fix the fix for single-line comment syntax, ------------------------------------------- is now a valid comment line again. - - - - - 8b18f2fe by Simon Marlow at 2004-05-10T10:11:51+00:00 [haddock @ 2004-05-10 10:11:51 by simonmar] Update - - - - - 225a491d by Ross Paterson at 2004-05-19T13:10:23+00:00 [haddock @ 2004-05-19 13:10:23 by ross] Make the handling of "deriving" slightly smarter, by ignoring data constructor arguments that are identical to the lhs. Now handles things like data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving ... - - - - - 37588686 by Mike Thomas at 2004-05-21T06:38:14+00:00 [haddock @ 2004-05-21 06:38:14 by mthomas] Windows exe extensions (bin remains for Unix). - - - - - cf2b9152 by Simon Marlow at 2004-05-25T09:34:54+00:00 [haddock @ 2004-05-25 09:34:54 by simonmar] Add some TODO items - - - - - 4d29cdfc by Simon Marlow at 2004-05-25T10:41:46+00:00 [haddock @ 2004-05-25 10:41:46 by simonmar] Complain if -h is used with --gen-index or --gen-contents, because it'll overwrite the new index/contents. - - - - - 2e0771e0 by Mike Thomas at 2004-05-28T20:17:55+00:00 [haddock @ 2004-05-28 20:17:55 by mthomas] Windows: search for templates in executable directory. Unix: Haddock tries cwd first rather than error if no -l arg. - - - - - 8d10bde1 by Sven Panne at 2004-06-05T16:53:34+00:00 [haddock @ 2004-06-05 16:53:34 by panne] Misc. rpm spec file cleanup, including: * make BuildRoot handling more consistent * added default file attributes * consistent defines and tags - - - - - 59974349 by Sven Panne at 2004-06-05T18:01:00+00:00 [haddock @ 2004-06-05 18:01:00 by panne] More rpm spec file cleanup, including: * added some BuildRequires * changed packager to me, so people can complain at the right place :-] * consistently refer to haskell.org instead of www.haskell.org - - - - - b94d4903 by Simon Marlow at 2004-07-01T11:08:58+00:00 [haddock @ 2004-07-01 11:08:57 by simonmar] Update to the +/- buttons: use a resized image rather than a <button>. Still seeing some strange effects in Konqueror, so might need to use a fixed-size image instead. - - - - - d5278f67 by Sven Panne at 2004-07-04T15:15:55+00:00 [haddock @ 2004-07-04 15:15:55 by panne] Install pictures for +/- pictures, too (JPEG is a strange format for graphics like this, I would have expected GIF or PNG here.) Things look fine with Konqueror and Netscape on Linux now, the only downside is that the cursor doesn't change when positioned above the "button". - - - - - 46dec6c5 by Sven Panne at 2004-07-13T17:59:28+00:00 [haddock @ 2004-07-13 17:59:28 by panne] A quote is a valid part of a Haskell identifier, but it would interfere with an ECMA script string delimiter, so escape it there. - - - - - 1d7bc432 by Simon Marlow at 2004-07-22T08:54:06+00:00 [haddock @ 2004-07-22 08:54:06 by simonmar] Add single quote to $ident, so you can say eg. 'foldl'' to refer to foldl' (the longest match rule is our friend). Bug reported by Adrian Hey <ahey at iee.org> - - - - - f183618b by Krasimir Angelov at 2004-07-27T22:59:35+00:00 [haddock @ 2004-07-27 22:58:23 by krasimir] Add basic support for Microsoft HTML Help 2.0 - - - - - d515d0c2 by Krasimir Angelov at 2004-07-27T23:02:36+00:00 [haddock @ 2004-07-27 23:02:36 by krasimir] escape names in the index - - - - - a5f1be23 by Krasimir Angelov at 2004-07-27T23:05:21+00:00 [haddock @ 2004-07-27 23:05:21 by krasimir] Add jsFile, plusFile and minusFile to the file list - - - - - c4fb4881 by Krasimir Angelov at 2004-07-28T22:12:10+00:00 [haddock @ 2004-07-28 22:12:09 by krasimir] bugfix. Move contentsHtmlFile, indexHtmlFile and subIndexHtmlFile functions to HaddockUtil.hs module to make them accessible from HaddockHH2.hs - - - - - 64d30b1d by Krasimir Angelov at 2004-07-30T22:15:47+00:00 [haddock @ 2004-07-30 22:15:45 by krasimir] more stuffs - support for separated compilation of packages - the contents page now uses DHTML TreeView - fixed copyFile bug - - - - - 133c8c5c by Krasimir Angelov at 2004-07-31T12:04:38+00:00 [haddock @ 2004-07-31 12:04:37 by krasimir] make the DHtmlTree in contents page more portable. The +/- buttons are replaced with new images which looks more beatiful. - - - - - 79040963 by Krasimir Angelov at 2004-07-31T13:10:20+00:00 [haddock @ 2004-07-31 13:10:20 by krasimir] Make DHtmlTree compatible with Mozila browser - - - - - 1a55dc90 by Krasimir Angelov at 2004-07-31T14:52:55+00:00 [haddock @ 2004-07-31 14:52:55 by krasimir] fix - - - - - 85ce0237 by Krasimir Angelov at 2004-07-31T14:53:28+00:00 [haddock @ 2004-07-31 14:53:28 by krasimir] HtmlHelp 1.x - - - - - 3c0c53ba by Krasimir Angelov at 2004-07-31T20:35:21+00:00 [haddock @ 2004-07-31 20:35:21 by krasimir] Added support for DevHelp - - - - - d42b5af1 by Krasimir Angelov at 2004-07-31T21:17:51+00:00 [haddock @ 2004-07-31 21:17:51 by krasimir] Document new features in HtmlHelp - - - - - 790fe21e by Krasimir Angelov at 2004-08-01T15:14:02+00:00 [haddock @ 2004-08-01 15:14:02 by krasimir] add missing imports - - - - - fd7cc6bc by Krasimir Angelov at 2004-08-01T19:52:08+00:00 [haddock @ 2004-08-01 19:52:06 by krasimir] fix some bugs. Now I have got the entire libraries documentation in HtmlHelp 2.0 format. - - - - - 94ad7ac8 by Krasimir Angelov at 2004-08-01T19:53:50+00:00 [haddock @ 2004-08-01 19:53:50 by krasimir] I forgot to add the new +/- images - - - - - f0c65388 by Krasimir Angelov at 2004-08-02T16:25:53+00:00 [haddock @ 2004-08-02 16:25:53 by krasimir] Add root node to the table of contents. All modules in tree are not children of the root - - - - - f50bd85d by Sven Panne at 2004-08-02T18:17:46+00:00 [haddock @ 2004-08-02 18:17:46 by panne] Mainly DocBook fixes - - - - - 09527ce3 by Sven Panne at 2004-08-02T20:02:29+00:00 [haddock @ 2004-08-02 20:02:29 by panne] Fixed -o/--odir handling. Generating the output, especially the directory handling, is getting a bit convoluted nowadays... - - - - - c8fbacfa by Sven Panne at 2004-08-02T20:31:13+00:00 [haddock @ 2004-08-02 20:31:13 by panne] Warning police - - - - - 37830bff by Sven Panne at 2004-08-02T20:32:29+00:00 [haddock @ 2004-08-02 20:32:28 by panne] Nuked dead code - - - - - 13847171 by Sven Panne at 2004-08-02T21:12:27+00:00 [haddock @ 2004-08-02 21:12:25 by panne] Use pathJoin instead of low-level list-based manipulation for FilePaths - - - - - c711d61e by Sven Panne at 2004-08-02T21:16:02+00:00 [haddock @ 2004-08-02 21:16:02 by panne] Removed WinDoze CRs - - - - - b1f7dc88 by Sven Panne at 2004-08-03T19:35:59+00:00 [haddock @ 2004-08-03 19:35:59 by panne] Fixed spelling of "http-equiv" attribute - - - - - dd5f394e by Sven Panne at 2004-08-03T19:44:03+00:00 [haddock @ 2004-08-03 19:44:03 by panne] Pacify W3C validator: * Added document encoding (currently UTF-8, not sure if this is completely correct) * Fixed syntax of `id' attributes * Added necessary `alt' attribute for +/- images Small layout improvement: * Added space after +/- images (still not perfect, but better than before) - - - - - 919c47c6 by Sigbjorn Finne at 2004-08-03T19:45:11+00:00 [haddock @ 2004-08-03 19:45:11 by sof] make it compile with <= ghc-6.1 - - - - - 4d6f01d8 by Sigbjorn Finne at 2004-08-03T19:45:30+00:00 [haddock @ 2004-08-03 19:45:30 by sof] ffi wibble - - - - - 4770643a by Sven Panne at 2004-08-03T20:47:46+00:00 [haddock @ 2004-08-03 20:47:46 by panne] Fixed CSS for button style. Note that only "0" is a valid measure without a unit! - - - - - 14aaf2e5 by Sven Panne at 2004-08-03T21:07:59+00:00 [haddock @ 2004-08-03 21:07:58 by panne] Improved spacing of dynamic module tree - - - - - 97c3579a by Simon Marlow at 2004-08-09T11:03:04+00:00 [haddock @ 2004-08-09 11:03:04 by simonmar] Add FormatVersion Patch submitted by: George Russell <ger at informatik.uni-bremen.de> - - - - - af7f8c03 by Simon Marlow at 2004-08-09T11:55:07+00:00 [haddock @ 2004-08-09 11:55:05 by simonmar] Add support for a short description for each module, which is included in the contents. The short description should be given in a "Description: " field of the header. Included in this patch are changes that make the format of the header a little more flexible. From the comments: -- all fields in the header are optional and have the form -- -- [spaces1][field name][spaces] ":" -- [text]"\n" ([spaces2][space][text]"\n" | [spaces]"\n")* -- where each [spaces2] should have [spaces1] as a prefix. -- -- Thus for the key "Description", -- -- > Description : this is a -- > rather long -- > -- > description -- > -- > The module comment starts here -- -- the value will be "this is a .. description" and the rest will begin -- at "The module comment". The header fields must be in the following order: Module, Description, Copyright, License, Maintainer, Stability, Portability. Patches submitted by: George Russell <ger at informatik.uni-bremen.de>, with a few small changes be me, mostly to merge with other recent changes. ToDo: document the module header. - - - - - 7b865ad3 by Simon Marlow at 2004-08-10T14:09:57+00:00 [haddock @ 2004-08-10 14:09:57 by simonmar] Fixes for DevHelp/HtmlHelp following introduction of short module description. - - - - - 814766cd by Simon Marlow at 2004-08-10T14:33:46+00:00 [haddock @ 2004-08-10 14:33:45 by simonmar] Fixes to installation under Windows. - - - - - 39cf9ede by Simon Marlow at 2004-08-12T12:08:23+00:00 [haddock @ 2004-08-12 12:08:23 by simonmar] Avoid using string-gap tricks. - - - - - b6d78551 by Simon Marlow at 2004-08-13T10:53:21+00:00 [haddock @ 2004-08-13 10:53:21 by simonmar] Update - - - - - eaae7417 by Simon Marlow at 2004-08-13T10:53:50+00:00 [haddock @ 2004-08-13 10:53:50 by simonmar] Test for primes in quoted links - - - - - 68c34f06 by Sven Panne at 2004-08-16T19:59:38+00:00 [haddock @ 2004-08-16 19:59:36 by panne] XMLification - - - - - 7f45a6f9 by Sven Panne at 2004-08-18T16:42:54+00:00 [haddock @ 2004-08-18 16:42:54 by panne] Re-added indices + minor fixes - - - - - 8a5dd97c by Sigbjorn Finne at 2004-08-25T17:15:42+00:00 [haddock @ 2004-08-25 17:15:42 by sof] backquote HADDOCK_VERSION defn for <= ghc-6.0.x; believe this is only needed under mingw - - - - - 4b1b42ea by Sven Panne at 2004-08-26T20:08:50+00:00 [haddock @ 2004-08-26 20:08:49 by panne] SGML is dead, long live DocBook XML! Note: The BuildRequires tags in the spec files are still incomplete and the documentation about the DocBook tools needs to be updated, too. Stay tuned... - - - - - 8d52cedb by Sven Panne at 2004-08-26T21:03:19+00:00 [haddock @ 2004-08-26 21:03:19 by panne] Updated BuildRequires tags. Alas, there seems to be no real standard here, so your mileage may vary... At least the current specs should work on SuSE Linux. - - - - - e6982912 by Sigbjorn Finne at 2004-08-30T15:44:59+00:00 [haddock @ 2004-08-30 15:44:59 by sof] escape HADDOCK_VERSION double quotes on all platforms when compiling with <=6.0.x - - - - - b3fbc867 by Simon Marlow at 2004-08-31T13:09:42+00:00 [haddock @ 2004-08-31 13:09:42 by simonmar] Avoid GHC/shell versionitis and create Version.hs - - - - - c359e16a by Sven Panne at 2004-09-05T19:12:33+00:00 [haddock @ 2004-09-05 19:12:32 by panne] * HTML documentation for "foo.xml" goes into directory "foo" again, not "foo-html". This is nicer and consistent with the behaviour for building the docs from SGML. * Disabled building PostScript documentation in the spec files for now, there are some strange issues with the FO->PS conversion for some files which have to be clarified first. - - - - - c68b1eba by Sven Panne at 2004-09-24T07:04:38+00:00 [haddock @ 2004-09-24 07:04:38 by panne] Switched the default state for instances and the module hierarchy to non-collapsed. This can be reversed when we finally use cookies from JavaScript to have a more persistent state. Previously going back and forth in the documentation was simply too annoying because everything was collapsed again and therefore the documentation was not easily navigatable. - - - - - dfb32615 by Simon Marlow at 2004-09-30T08:21:29+00:00 [haddock @ 2004-09-30 08:21:29 by simonmar] Add a feature request - - - - - 45ff783c by Sven Panne at 2004-10-23T19:54:00+00:00 [haddock @ 2004-10-23 19:54:00 by panne] Improved the Cygwin/MinGW chaos a little bit. There is still confusion about host platform vs. target platform... - - - - - 5f644714 by Krasimir Angelov at 2004-10-28T16:01:51+00:00 [haddock @ 2004-10-28 16:01:51 by krasimir] update for ghc-6.3+ - - - - - 92d9753e by Sven Panne at 2004-11-01T16:39:01+00:00 [haddock @ 2004-11-01 16:39:01 by panne] Revert previous commit: It's Network.URI which should be changed, not Haddock. - - - - - 05f70f6e by Simon Marlow at 2005-01-04T16:15:51+00:00 [haddock @ 2005-01-04 16:15:51 by simonmar] parser fix: allow qualified specialids. - - - - - 47870837 by Simon Marlow at 2005-01-04T16:16:54+00:00 [haddock @ 2005-01-04 16:16:54 by simonmar] Add a test - - - - - ff11fc2c by Ross Paterson at 2005-01-10T19:18:22+00:00 [haddock @ 2005-01-10 19:18:22 by ross] Render non-ASCII characters using numeric character references, to simplify charset issues. There's a META tag saying the charset is UTF-8, but GHC outputs characters as raw bytes. Ideally we need an encoding on the input side too, primarily in comments, because source files containing non-ASCII characters aren't portable between locales. - - - - - eba2fc4e by Simon Marlow at 2005-01-11T10:44:37+00:00 [haddock @ 2005-01-11 10:44:37 by simonmar] Remove string gap - - - - - b899a381 by Ross Paterson at 2005-01-13T11:41:33+00:00 [haddock @ 2005-01-13 11:41:33 by ross] recognize SGML-style numeric character references &#ddd; or &#xhhhh; and translate them into Chars. - - - - - 106e3cf0 by Ross Paterson at 2005-01-13T14:43:41+00:00 [haddock @ 2005-01-13 14:43:41 by ross] also allow uppercase X in hexadecimal character references (like SGML) - - - - - e8f54f25 by Ross Paterson at 2005-01-13T14:44:24+00:00 [haddock @ 2005-01-13 14:44:24 by ross] Describe numeric character references. - - - - - 914ccdce by Sven Panne at 2005-01-15T18:44:48+00:00 [haddock @ 2005-01-15 18:44:45 by panne] Make Haddock compile again after the recent base package changed. The Map/Set legacy hell has been factored out, so that all modules can simply use the new non-deprecated interfaces. Probably a lot of things can be improved by a little bit of Map/Set/List algebra, this can be done later if needed. Small note: Currently the list of instances in HTML code is reversed. This will hopefully be fixed later. - - - - - 6ab20e84 by Sven Panne at 2005-01-16T12:18:26+00:00 [haddock @ 2005-01-16 12:18:26 by panne] Trim imports - - - - - efb81da9 by Sven Panne at 2005-01-16T12:58:08+00:00 [haddock @ 2005-01-16 12:58:03 by panne] Correctly handle the new order of arguments for the combining function given to fromListWith. - - - - - e27b5834 by Sven Panne at 2005-01-16T14:14:41+00:00 [haddock @ 2005-01-16 14:14:39 by panne] Data.Map.unions is left-biased. - - - - - dae3cc3e by Sven Panne at 2005-01-16T14:22:44+00:00 [haddock @ 2005-01-16 14:22:44 by panne] Added the last missing "flip" to get identical HTML output as previous versions. - - - - - 951d8408 by Sven Panne at 2005-01-16T14:37:10+00:00 [haddock @ 2005-01-16 14:37:10 by panne] Refactored Text.PrettyPrint legacy hell into a separate module. - - - - - f1c4b892 by Sven Panne at 2005-01-16T15:41:25+00:00 [haddock @ 2005-01-16 15:41:21 by panne] Cleaned up imports and dropped support for GHC < 5.03, it never worked, anyway. - - - - - 60824c6e by Simon Marlow at 2005-01-18T10:02:48+00:00 [haddock @ 2005-01-18 10:02:48 by simonmar] Add a TODO - - - - - a8c82f23 by Krasimir Angelov at 2005-01-28T23:19:39+00:00 [haddock @ 2005-01-28 23:19:39 by krasimir] import Foreign/Foreign.C are required for Windows - - - - - d8450a23 by Simon Marlow at 2005-02-02T16:23:04+00:00 [haddock @ 2005-02-02 16:23:00 by simonmar] Revamp the linking strategy in Haddock. Now name resolution is done in two phases: - first resolve everything to original names, like a Haskell compiler would. - then, figure out the "home" location for every entity, and point all the links to there. The home location is the lowest non-hidden module in the import hierarchy that documents the entity. If there are multiple candidates, one is chosen at random. Also: - Haddock should not generate any HTML with dangling links any more. Unlinked references are just rendered as plain text. - Error reporting is better: if we can't find a link destination for an entity reference, we now emit a warning. - - - - - 1cce71d0 by Simon Marlow at 2005-02-03T13:42:19+00:00 [haddock @ 2005-02-03 13:42:19 by simonmar] - add --ignore-all-exports flag, which behaves as if every module has the ignore-exports attribute (requested by Chris Ryder). - add --hide option to hide a module on the command line. - add --use-package option to get Haddock info for a package from ghc-pkg (largely untested). - remove reexports from the .haddock file, they aren't used any more. - - - - - 767123ef by Ross Paterson at 2005-02-03T16:17:37+00:00 [haddock @ 2005-02-03 16:17:37 by ross] fix typo for < 6.3 - - - - - 0c680c04 by Simon Marlow at 2005-02-04T12:03:31+00:00 [haddock @ 2005-02-04 12:03:31 by simonmar] Fix bug in renameExportItems that meant links in instances weren't being renamed properly. - - - - - ff7abe5f by Simon Marlow at 2005-02-04T12:15:53+00:00 [haddock @ 2005-02-04 12:15:52 by simonmar] Add attribute #not-home, to indicate that the current module should not be considered to be a home module for the each entity it exports, unless there is no other module that exports the entity. - - - - - fc2cfd27 by Simon Marlow at 2005-02-04T12:40:02+00:00 [haddock @ 2005-02-04 12:40:02 by simonmar] Update the documentation w.r.t. home modules and the not-home attribute. - - - - - 26b8ddf7 by Ross Paterson at 2005-02-04T13:36:06+00:00 [haddock @ 2005-02-04 13:36:05 by ross] sort lists of instances by - arity of the type constructors (so higher-kinded instances come first) - name of the class - argument types - - - - - 26bfb19c by Simon Marlow at 2005-02-23T15:57:12+00:00 [haddock @ 2005-02-23 15:57:12 by simonmar] Fix documentation regarding the module attributes. - - - - - 9c3afd02 by Simon Marlow at 2005-02-28T16:18:17+00:00 [haddock @ 2005-02-28 16:18:17 by simonmar] version 0.7 - - - - - a95fd63f by Simon Marlow at 2005-02-28T16:22:08+00:00 [haddock @ 2005-02-28 16:22:08 by simonmar] Attempt to fix the layout of the package names in the contents. Having tried just about everything, the only thing I can get to work reliably is to make the package names line up on a fixed offset from the left margin. This obviously isn't ideal, so anyone else that would like to have a go at improving it is welcome. One option is to remove the +/- buttons from the contents list and go back to a plain table. The contents page now uses CSS for layout rather than tables. It seems that most browsers have different interpretations of CSS layout, so only the simplest things lead to consistent results. - - - - - 905d42f7 by Simon Marlow at 2005-03-01T17:16:42+00:00 [haddock @ 2005-03-01 17:16:40 by simonmar] Another attempt at lining up the package names on the contents page. Now, they line up with Konqueror, and almost line up with Firefox & IE (different layout in each case). - - - - - a0e1d178 by Wolfgang Thaller at 2005-03-09T08:28:39+00:00 [haddock @ 2005-03-09 08:28:39 by wolfgang] Hack haddock's lexer to accept the output from Apple's broken version of cpp (Apple's cpp leaves #pragma set_debug_pwd directives in it's output). - - - - - 9e1eb784 by Simon Marlow at 2005-04-22T14:27:15+00:00 [haddock @ 2005-04-22 14:27:15 by simonmar] Add a TODO item - - - - - 23281f78 by Ross Paterson at 2005-05-18T12:41:59+00:00 [haddock @ 2005-05-18 12:41:59 by ross] fix 3 bugs in --use-package, and document it. - - - - - 00074a68 by Sven Panne at 2005-05-21T12:35:29+00:00 [haddock @ 2005-05-21 12:35:29 by panne] Warning/versionitis police - - - - - 341fa822 by Simon Marlow at 2005-06-15T15:43:21+00:00 [haddock @ 2005-06-15 15:43:21 by simonmar] Allow "licence" as an alternate spelling of "license" - - - - - 3b953f8b by Simon Marlow at 2005-06-16T08:14:12+00:00 [haddock @ 2005-06-16 08:14:12 by simonmar] wibble - - - - - abfd9826 by Simon Marlow at 2005-06-27T14:46:40+00:00 [haddock @ 2005-06-27 14:46:40 by simonmar] name hierarchical HTML files as A-B-C.html instead of A.B.C.html. The old way confused Apache because the extensions are sometimes interpreted as having special meanings. - - - - - a01eea00 by Simon Marlow at 2005-08-04T13:59:40+00:00 [haddock @ 2005-08-04 13:59:40 by simonmar] 0.7 changes - - - - - 170ef87e by Simon Marlow at 2005-08-04T15:08:03+00:00 [haddock @ 2005-08-04 15:08:03 by simonmar] spec file from Jens Peterson - - - - - 7621fde4 by Simon Marlow at 2005-08-04T15:59:30+00:00 [haddock @ 2005-08-04 15:59:30 by simonmar] replace mingw tests with $(Windows) - - - - - a20739bb by Sven Panne at 2005-08-05T07:01:12+00:00 [haddock @ 2005-08-05 07:01:12 by panne] Reverted to previous version (but with bumped version number), the last commit broke RPM building on SuSE systems due to differently named dependencies. As a clarification: All .spec files in the repository have to work at least on SuSE, because that's the system I'm using. And as "Mr. Building Police", I reserve me the right to keep them that way... >:-) It might very well be the case that we need different .spec files for different platforms, so packagers which are unhappy with the current .spec files should contact me, stating the actual problems. - - - - - 4afb15cf by Simon Marlow at 2005-10-05T10:51:45+00:00 [haddock @ 2005-10-05 10:51:45 by simonmar] Add a bug - - - - - 60f69f82 by Simon Marlow at 2005-10-05T12:52:03+00:00 [haddock @ 2005-10-05 12:52:03 by simonmar] Document new behaviour of -s option - - - - - f7e520ca by Simon Marlow at 2005-10-10T15:02:55+00:00 [haddock @ 2005-10-10 15:02:55 by simonmar] extractRecSel: ignore non-record constructors (fixes a crash when using datatypes with a mixture of record and non-record style constructors). - - - - - b2edbedb by Simon Marlow at 2005-10-14T09:44:21+00:00 Start CHANGES for 0.8 - - - - - 21c7ac8d by Simon Marlow at 2005-10-14T23:11:19+00:00 First cut of Cabal build system - - - - - 766cecdd by Simon Marlow at 2005-10-29T08:14:43+00:00 Add configure script and Makefile for the docs Add a separate configure script and build system for building the documentation. The configure and Makefile code is stolen from fptools. This is left as a separate build system so that the main Cabal setup doesn't require a Unix build environment or DocBook XML tools. - - - - - aa36c783 by Duncan Coutts at 2006-01-17T19:29:55+00:00 Add a --wiki=URL flag to add a per-module link to a correspondng wiki page. So each html page gets an extra link (placed next to the source code and contents links) to a corresponding wiki page. The idea is to let readers contribute their own notes, examples etc to the documentation. Also slightly tidy up the code for the --source option. - - - - - e06e2da2 by Simon Marlow at 2006-01-18T09:28:15+00:00 TODO: documnet --wiki - - - - - 17adfda9 by Duncan Coutts at 2006-01-19T20:17:59+00:00 Add an optional wiki link for each top level exported name. In each module, for each "top level" exported entity we add a hyper link to a corresponding wiki page. The link url gets the name of the exported entity as a '#'-style anchor, so if there is an anchor in the page with that name then the users browser should jump directly to it. By "top level" we mean functions, classes, class members and data types (data, type, newtype), but not data constructors, class instances or data type class membership. The link is added at the right of the page and in a small font. Hopefully this is the right balance of visibility/distraction. We also include a link to the wiki base url in the contents and index pages. - - - - - f52324bb by Duncan Coutts at 2006-01-19T20:28:27+00:00 Rewrite pathJoin to only add a path separator when necessary. When the path ends in a file seperator there is no need to add another. Now using "--wiki=http://blah.com/foo/" should do the right thing. (Code snippet adapted from Isaac's FilePath package.) - - - - - 43bb89fa by Duncan Coutts at 2006-01-21T17:15:27+00:00 Teach haddock about line pragmas and add accurate source code links Teach haddock about C and Haskell style line pragmas. Extend the lexer/parser's source location tracking to include the file name as well as line/column. This way each AST item that is tagged with a SrcLoc gets the original file name too. Use this original file name to add source links to each exported item, in the same visual style as the wiki links. Note that the per-export source links are to the defining module rather than whichever module haddock pretends it is exported from. This is what we want for source code links. The source code link URL can also contain the name of the export so one could implement jumping to the actual location of the function in the file if it were linked to an html version of the source rather than just plain text. The name can be selected with the %N wild card. So for linking to the raw source code one might use: --source=http://darcs/haskell.org/foo/%F Or for linking to html syntax highlighted code: --source=http://darcs/haskell.org/foo/%M.html#%N - - - - - edd9f229 by Duncan Coutts at 2006-01-22T00:02:00+00:00 Extend URL variable expansion syntax and add source links to the contents page Like the wiki link on the contents and index page, add a source code link too. Extend the wiki & source URL variable expansion syntax. The original syntax was: %F for the source file name (the .hs version only, not the .lhs or .hs.pp one) %M for the module name (with '.' replaced by '/') The new syntax is: %F or %{FILE} for the original source file name %M or %{MODULE} for the module name (no replacements) %N or %{NAME} for the function/type export name %K or %{KIND} for a type/value flag "t" or "v" with these extensions: %{MODULE/./c} to replace the '.' module seperator with any other char c %{VAR|some text with the % char in it} which means if the VAR is not in use in this URL context then "" else replace the given text with the '%' char replaced by the string value of the VAR. This extension allows us to construct URLs wit optional parts, since the module/file name is not available for the URL in the contents/index pages and the value/type name is not available for the URL at the top level of each module. - - - - - eb3c6ada by Duncan Coutts at 2006-01-23T13:42:34+00:00 Remove the complex substitutions and add more command line flags instead. Instead of incomprehensable URL substitutions like ${MODULE/./-|?m=%} we now use three seperate command line flags for the top level, per-module and per-entity source and wiki links. They are: --source-base, --source-module, --source-entity --comments-base, --comments-module, --comments-entity We leave -s, --source as an alias for --source-module which is how that option behaved previously. The long forms of the substitutions are still available, ${FILE} ${MODULE} etc and the only non-trivial substitution is ${MODULE/./c} to replace the '.' characters in the module name with any other character c. eg ${MODULE/./-} Seperating the source and wiki url flags has the added bonus that they can be turned on or off individually. So users can have per-module links for example without having to also have per-entity links.` - - - - - a2f0f2af by Duncan Coutts at 2006-01-23T13:54:52+00:00 Make the --help output fit in 80 columns. This is a purely cosmetic patch, feel free to ignore it. The only trickery going on is that we don't display the deprecated -s, --source flags in the help message, but we do still accept them. - - - - - 2d3a4b0c by Duncan Coutts at 2006-01-23T14:12:16+00:00 Add documentation for the new --source-* and --comments-* command line options - - - - - 1a82a297 by Simon Marlow at 2006-01-23T17:03:27+00:00 fix markup - - - - - 100d464a by Duncan Coutts at 2006-01-23T18:31:13+00:00 remove a couple TODO items that have been done The --wiki, or rather the --comment-* options are now documented. There is probably no need to have haddock invoke unlit or cpp itself since it can now pick up the line pragmas to get the source locations right. Tools like Cabal will arrange for preprocessors to be run so there is less of a need for tools like haddock to do it themselves. - - - - - 3162fa91 by Simon Marlow at 2006-01-24T14:21:56+00:00 add a test I had lying around - - - - - 98947063 by Simon Marlow at 2006-01-31T13:52:54+00:00 add scabal-version field - - - - - c41876e6 by Neil Mitchell at 2006-02-26T17:48:21+00:00 Add Hoogle output option - - - - - f86fb9c0 by Simon Marlow at 2006-03-08T09:15:20+00:00 add haskell.vim Contributed by Brad Bowman <bsb at bereft.net>, thanks! - - - - - 35d3c511 by benjamin.franksen at 2006-03-03T22:39:54+00:00 fixed libdir (/html was missing) - - - - - 4d08fd7d by Simon Marlow at 2006-03-10T11:13:31+00:00 add PatternGuards extension - - - - - 3f095e70 by Simon Marlow at 2006-03-13T11:40:42+00:00 bug fixes from Brad Bowman - - - - - 8610849d by Sven Panne at 2006-03-19T17:02:56+00:00 Fixed Cabal/RPM build - - - - - 34a994d6 by sven.panne at 2006-04-20T12:39:23+00:00 Avoid pattern guards Due to the use of pattern guards in Haddock, GHC was called with -fglasgow-exts. This in turn enables bang patterns, too, which broke the Haddock build. Removing some unnecessary pattern guards seemed to be the better way of fixing this instead of using a pragma to disable pattern guards. - - - - - bb523f51 by Ross Paterson at 2006-04-24T09:03:25+00:00 extend 'deriving' heuristic a little If an argument of a data constructor has a type variable head, it is irreducible and the same type class can be copied into the constraint. (Formerly we just did this for type variable arguments.) - - - - - dab9fe7a by Simon Marlow at 2006-04-26T10:02:31+00:00 record an idea - - - - - 748b7078 by Simon Marlow at 2006-05-08T08:28:53+00:00 add section about deriving - - - - - 11252ea1 by Simon Marlow at 2006-05-24T15:43:10+00:00 replace a fatal error in lexChar with a parseError - - - - - 382c9411 by Simon Marlow at 2006-05-24T15:45:47+00:00 add a bug - - - - - b79272f5 by Simon Marlow at 2006-05-24T15:46:29+00:00 add a bug report - - - - - 912edf65 by David Waern at 2006-07-10T19:09:23+00:00 Initial modifications -- doesn't compile - - - - - a3c7ba99 by David Waern at 2006-07-11T00:54:19+00:00 More porting work -- doesn't compile - - - - - 0a173d19 by David Waern at 2006-07-11T11:30:03+00:00 Make the repos temporarily compile and illustrate a problem - - - - - bad316de by David Waern at 2006-07-11T15:43:47+00:00 Progress on the porting process - - - - - bbf12d02 by David Waern at 2006-07-11T23:07:44+00:00 More progress on the porting -- first pass starting to shape up - - - - - de580ba2 by David Waern at 2006-07-20T17:48:30+00:00 More progress -- still on phase1 - - - - - 75a917a2 by David Waern at 2006-07-23T18:22:43+00:00 More work on pass1 -- mostly done - - - - - 6697b3f7 by David Waern at 2006-07-23T22:17:40+00:00 More work, started working on the renaming phase -- this code will need a cleanup soon :) - - - - - 82a5bcbb by David Waern at 2006-07-29T16:16:43+00:00 Add instances, build renaming environment, start on the renamer - - - - - c3f8f4f1 by David Waern at 2006-07-29T21:37:48+00:00 Complete the renamer - - - - - 7e00d464 by David Waern at 2006-07-30T21:01:57+00:00 Start porting the Html renderer - - - - - f04ce121 by David Waern at 2006-08-09T20:04:56+00:00 More Html rendering progress - - - - - 20c21b53 by David Waern at 2006-08-10T17:37:47+00:00 More progress - - - - - d7097e0d by David Waern at 2006-08-11T20:31:51+00:00 Cleanup - - - - - a7351e86 by David Waern at 2006-08-12T11:44:47+00:00 Render H98 Data declarations - - - - - 3fb2208e by David Waern at 2006-08-12T17:15:34+00:00 Perfect rendering of Test.hs - - - - - 454fd062 by David Waern at 2006-08-13T21:57:08+00:00 Misc fixes and interface load/save - - - - - 7ef7e7be by David Waern at 2006-08-14T00:56:07+00:00 Some refactoring - - - - - a7d3efef by David Waern at 2006-08-19T20:07:55+00:00 Adapt to latest GHC - - - - - 5fc3c0d7 by David Waern at 2006-08-20T21:28:11+00:00 Move interface read/write to its own module + some cleanup - - - - - 037e011c by David Waern at 2006-08-20T21:38:24+00:00 Small cleanup - - - - - da3a1023 by David Waern at 2006-09-03T16:05:22+00:00 Change mode to BatchCompile to avoid GHC API bug - - - - - 3cc9be3b by David Waern at 2006-09-03T16:06:59+00:00 Starting work on GADT rendering - - - - - 94506037 by David Waern at 2006-09-03T20:02:48+00:00 Compensate for change of export list order in GHC - - - - - c2cec4eb by David Waern at 2006-09-04T20:53:01+00:00 Rename a function - - - - - 9a9735ba by David Waern at 2006-09-05T15:51:21+00:00 Change version number to 2.0 - - - - - 3758a714 by David Waern at 2006-09-05T15:51:49+00:00 Align comment properly - - - - - 68478d9e by David Waern at 2006-09-15T18:03:00+00:00 Remove interface reading/writing code and use the GHC api for creating package environments instead - - - - - d2eedd95 by David Waern at 2006-09-15T18:05:29+00:00 Change the executable name to haddock-ghc-nolib - - - - - fcfbcf66 by David Waern at 2006-09-15T18:05:45+00:00 Small source code cleanup - - - - - d08eb017 by David Waern at 2006-09-15T18:06:21+00:00 Remove handling of --package flag - - - - - b8a4cf53 by David Waern at 2006-09-15T18:07:16+00:00 Remove commented-out code - - - - - bef0a684 by David Waern at 2006-09-15T18:37:57+00:00 Don't warn about missing links to () - - - - - e7d25fd7 by David Waern at 2006-09-15T19:50:49+00:00 Remove Interface and Binary2 modules - - - - - 9894f2a1 by David Waern at 2006-09-15T19:53:43+00:00 Remove debug printing from HaddockHtml - - - - - a0e7455d by David Waern at 2006-09-16T00:16:29+00:00 Comments only - - - - - d5b26fa7 by David Waern at 2006-09-16T00:16:57+00:00 Refactor PackageData creation code and start on building the doc env propery (unfinished) - - - - - 06aaa779 by David Waern at 2006-09-16T00:19:25+00:00 Better comments in Main.hs - - - - - 1a52d1b4 by David Waern at 2006-09-18T22:17:11+00:00 Comments and spacing change - - - - - e5a97767 by David Waern at 2006-09-21T17:02:45+00:00 Remove unnecessary fmapM import in Main - - - - - 9d0f9d3a by David Waern at 2006-09-22T18:07:07+00:00 Make import list in HaddockHtml prettier - - - - - 3452f662 by David Waern at 2006-09-22T18:08:47+00:00 Refactor context rendering - - - - - 12d0a6d0 by David Waern at 2006-09-22T18:09:52+00:00 Do proper HsType rendering (inser parentheses correctly) - - - - - 2c20c2f9 by David Waern at 2006-09-22T18:10:45+00:00 Fix a bug in Main.toHsType - - - - - c5396443 by David Waern at 2006-09-22T18:11:16+00:00 Skip external package modules sort for now - - - - - 3fb95547 by David Waern at 2006-09-22T20:35:40+00:00 Take away trailin "2" on all previously clashing type names - - - - - 2174755f by David Waern at 2006-09-22T20:51:43+00:00 Remove unused imports in Main - - - - - 1e9f7a39 by David Waern at 2006-09-22T20:52:11+00:00 Fix a comment in Main - - - - - 32d9e028 by David Waern at 2006-10-05T16:40:11+00:00 Merge with changes to ghc HEAD - - - - - 3058c8f5 by David Waern at 2006-10-05T16:41:02+00:00 Comment fixes - - - - - b9c217ec by David Waern at 2006-10-05T16:49:59+00:00 Filter out more builtin type constructors from warning messages - - - - - 67e7d252 by David Waern at 2006-10-05T19:38:22+00:00 Refactoring -- better structured pass1 - - - - - cd21c0c1 by David Waern at 2006-10-05T19:44:42+00:00 Remove read/dump interface flags - - - - - 313f9e69 by David Waern at 2006-10-05T19:49:26+00:00 Remove unused pretty printing - - - - - 480f09d1 by David Waern at 2006-12-28T13:22:24+00:00 Update to build with latest GHC HEAD - - - - - 63dccfcb by David Waern at 2007-01-05T01:38:45+00:00 Fixed a bug so that --ghc-flag works correctly - - - - - 3117dadc by David Waern at 2006-12-29T18:53:39+00:00 Automatically get the GHC lib dir - - - - - 9dc84a5c by David Waern at 2006-12-29T19:58:53+00:00 Comments - - - - - 0b0237cc by David Waern at 2007-01-05T16:48:30+00:00 Collect docs based on SrcLoc, syncing with removal of DeclEntity from GHC - - - - - a962c256 by David Waern at 2007-01-05T17:02:47+00:00 Add tabs in haddock.cabal - - - - - 0ca30c97 by David Waern at 2007-01-05T17:04:11+00:00 Add GHCUtils.hs - - - - - c0ab9abe by David Waern at 2007-01-10T11:43:08+00:00 Change package name to haddock-ghc, version 0.1 - - - - - 38e18b27 by David Waern at 2007-01-12T12:03:52+00:00 No binder name for foreign exports - - - - - d18587ab by David Waern at 2007-01-12T12:08:15+00:00 Temp record - - - - - ba6251a0 by David Waern at 2007-01-12T18:27:55+00:00 Remove read/dump-interface (again) - - - - - f4ba2b39 by David Waern at 2007-01-12T18:31:36+00:00 Remove DocOption, use the GHC type - - - - - 511be8bd by David Waern at 2007-01-12T18:32:41+00:00 Use exceptions instead of Either when loading package info - - - - - 0f2144d8 by David Waern at 2007-01-12T18:33:23+00:00 Small type change - - - - - 77507eb7 by David Waern at 2007-01-12T18:33:59+00:00 Remove interface file read/write - - - - - 0ea1e14f by David Waern at 2007-01-17T21:40:26+00:00 Add trace_ppr to GHCUtils - - - - - 3878b493 by David Waern at 2007-01-17T21:40:53+00:00 Sort external package modules and build a doc env - - - - - 8dc323fc by David Waern at 2007-01-17T21:42:41+00:00 Remove comment - - - - - f4c5b097 by David Waern at 2007-01-18T23:22:18+00:00 Add haddock-ghc.cabal and remove ghc option pragma in source file - - - - - da242b2c by David Waern at 2007-01-18T23:22:46+00:00 Remove some tabs - - - - - 288ed096 by David Waern at 2007-01-18T23:39:28+00:00 Moved the defaultErrorHandler to scope only over sortAndCheckModules for now - - - - - 4dd150fe by David Waern at 2007-02-03T21:23:56+00:00 Let restrictCons handle infix constructors - - - - - 97893442 by David Waern at 2007-02-04T16:26:00+00:00 Render infix data constructors - - - - - da89db72 by David Waern at 2007-02-04T16:26:33+00:00 CHange project name to Haddock-GHC - - - - - e93d48af by David Waern at 2007-02-04T16:59:08+00:00 Render infix type constructors properly - - - - - 357bc99b by David Waern at 2007-02-04T17:37:08+00:00 Insert spaces around infix function names - - - - - ab6cfc49 by David Waern at 2007-02-04T17:59:54+00:00 Do not list entities without documentation - - - - - 04249c7e by David Waern at 2007-02-04T19:16:25+00:00 Add GADT support (quite untested) - - - - - 2c223f8d by David Waern at 2007-02-04T19:25:10+00:00 Add package file write/save again! - - - - - b07ed218 by David Waern at 2007-02-04T19:33:02+00:00 Comment out minf_iface based stuff - - - - - 953d1fa7 by David Waern at 2007-02-05T00:12:23+00:00 Solve conflicts - - - - - 593247fc by David Waern at 2007-02-06T19:48:48+00:00 Remove -package flag, GHC's can be used instead - - - - - f658ded2 by David Waern at 2007-02-06T20:50:44+00:00 Start for support of ATs - - - - - 97f9e913 by David Waern at 2007-02-06T20:52:27+00:00 Wibble - - - - - 2ce8e4cf by David Waern at 2007-02-16T12:09:49+00:00 Add the DocOptions change - - - - - dee4a9b5 by David Waern at 2007-03-06T01:24:48+00:00 Wibble - - - - - 7cb99d18 by David Waern at 2007-03-06T01:24:58+00:00 Change version to 2.0 and executable name to haddock - - - - - c5aa02bc by David Waern at 2007-03-08T15:59:49+00:00 Go back to -B flag - - - - - 3a349201 by David Waern at 2007-03-09T13:31:59+00:00 Better exception handling and parsing of GHC flags - - - - - 05a69b71 by David Waern at 2007-03-09T17:45:44+00:00 Remove commented-out DocEntity printing - - - - - 755032cb by davve at dtek.chalmers.se at 2007-03-23T23:30:20+00:00 Remove a file that shouldn't be here - - - - - a7077e5f by davve at dtek.chalmers.se at 2007-03-24T03:58:48+00:00 Remove an import - - - - - 6f55aa8b by davve at dtek.chalmers.se at 2007-03-25T00:46:48+00:00 Start work on Haddock API - - - - - f0199480 by davve at dtek.chalmers.se at 2007-03-25T00:56:36+00:00 Prettify some comments - - - - - f952f9d1 by davve at dtek.chalmers.se at 2007-03-25T00:56:53+00:00 Remove ppr in HaddockTypes - - - - - bc594904 by davve at dtek.chalmers.se at 2007-03-25T00:57:53+00:00 Remove commented out doc env inference - - - - - 11ebf08d by davve at dtek.chalmers.se at 2007-03-25T01:23:25+00:00 De-flatten the namespace - - - - - f696b4bc by davve at dtek.chalmers.se at 2007-03-25T03:21:48+00:00 Add missing stuff to API - - - - - 9a2a04c3 by davve at dtek.chalmers.se at 2007-03-25T03:22:02+00:00 Wibble - - - - - 7d04a6d5 by davve at dtek.chalmers.se at 2007-03-25T03:22:08+00:00 Avoid a GHC bug with parseStaticFlags [] - - - - - 4d2820ba by davve at dtek.chalmers.se at 2007-03-26T04:57:01+00:00 Add fall-through case to mkExportItem - - - - - 6ebc8950 by Stefan O'Rear at 2007-03-26T04:14:53+00:00 Add shebang line to Setup.lhs - - - - - 80966ec5 by davve at dtek.chalmers.se at 2007-03-26T05:24:26+00:00 Fix stupid compile error - - - - - 1ea1385d by davve at dtek.chalmers.se at 2007-04-05T17:19:56+00:00 Do save/read of interface files properly - - - - - 0e4f6541 by David Waern at 2007-04-10T21:08:36+00:00 Add version to ghc dependency - - - - - b0499b63 by David Waern at 2007-04-10T21:37:08+00:00 Change package name to haddock - - - - - 9d50d27e by David Waern at 2007-04-24T00:22:14+00:00 Use filepath package instead of FilePath - - - - - 87c7fcdf by David Waern at 2007-07-10T21:03:04+00:00 Add new package dependencies - - - - - 4768709c by David Waern at 2007-07-11T20:37:11+00:00 Follow changes to record constructor representation - - - - - b9a02fee by Simon Marlow at 2007-05-30T14:00:48+00:00 update to compile with the latest GHC & Cabal - - - - - c0ebdc01 by David Waern at 2007-07-11T21:35:45+00:00 Fix conflicts - - - - - 97f7afd4 by David Waern at 2007-07-11T21:52:38+00:00 Follow changes to the GHC API - - - - - a5b7b58f by David Waern at 2007-07-12T20:36:48+00:00 Call parseStaticFlags before newSession - - - - - f7f50dbc by David Waern at 2007-08-01T21:52:58+00:00 Better indentation in haddock.cabal - - - - - d84e52ad by David Waern at 2007-08-02T00:08:18+00:00 Wibble - - - - - a23f494a by David Waern at 2007-08-02T00:08:24+00:00 Be better at trying to load all module dependencies (debugging) - - - - - ee917f13 by David Waern at 2007-08-03T18:48:08+00:00 Load all targets explicitly (checkModule doesn't chase dependencies anymore) - - - - - 5182d631 by David Waern at 2007-08-16T16:48:55+00:00 Finalize support for links to other packages - - - - - dfd1e3da by David Waern at 2007-08-16T16:51:11+00:00 Fix haddock comment errors in Haddock.Types - - - - - 50c0d83e by David Waern at 2007-08-16T16:51:37+00:00 Remove a debug import - - - - - d84b7c2b by David Waern at 2007-08-16T17:06:30+00:00 Rename PackageData to HaddockPackage - - - - - 3b52cb9f by David Waern at 2007-08-16T17:09:42+00:00 Simplify some comments - - - - - 66fa68d9 by David Waern at 2007-08-16T17:11:38+00:00 Comment the HaddockPackage definition - - - - - 8674c761 by David Waern at 2007-08-16T17:25:54+00:00 Improve code layout in Main - - - - - 571a3a0b by David Waern at 2007-08-16T17:32:13+00:00 Remove explict module imports in Main - - - - - d31b3cb0 by David Waern at 2007-08-16T17:36:23+00:00 Correct comments - - - - - 7f8a9f2b by David Waern at 2007-08-16T17:39:50+00:00 Fix layout problems in Haddock.Types - - - - - 9f421d7f by David Waern at 2007-08-17T11:16:48+00:00 Move options out of Main into Haddock.Options - - - - - 80042b63 by David Waern at 2007-08-17T11:26:59+00:00 Small comment/layout fixes - - - - - b141b982 by David Waern at 2007-08-17T11:28:28+00:00 Change project name from Haddock-GHC to Haddock - - - - - dbeb4a81 by David Waern at 2007-08-17T11:41:05+00:00 Add top module comment to all files - - - - - ce99cc9e by David Waern at 2007-08-17T14:53:04+00:00 Factor out typechecking phase into Haddock.Typecheck - - - - - 6bf75d9e by David Waern at 2007-08-17T16:55:35+00:00 Factor out package code to Haddock.Packages - - - - - b396db37 by David Waern at 2007-08-29T22:40:23+00:00 Major refactoring - - - - - 3d4f95ee by David Waern at 2007-08-29T23:26:24+00:00 Rename HaddockModule to Interface and a few more refactorings - - - - - c55326db by David Waern at 2007-08-29T23:48:03+00:00 Some comment cleanup - - - - - 9a84fc46 by David Waern at 2007-08-29T23:49:29+00:00 Add some modules that I forgot to add earlier - - - - - 4536dce2 by David Waern at 2007-08-29T23:55:24+00:00 Wibble - - - - - 9b7f0206 by David Waern at 2007-08-30T16:03:29+00:00 Wibble - - - - - c52c050a by David Waern at 2007-08-30T16:30:37+00:00 Rename HaddockModule to Interface - - - - - eae2995f by David Waern at 2007-08-30T16:42:59+00:00 Simplify createInterfaces - - - - - 53f99caa by David Waern at 2007-09-29T00:04:31+00:00 Add build-type: Simple to the cabal file - - - - - 0d3103a8 by David Waern at 2007-09-29T00:04:58+00:00 Add containers and array dependency - - - - - 6acf5f30 by David Waern at 2007-09-29T00:13:36+00:00 Prettify the cabal file - - - - - 87c1e378 by David Waern at 2007-09-29T13:16:39+00:00 FIX: consym data headers with more than two variables - - - - - b67fc16a by David Waern at 2007-09-29T14:01:32+00:00 FIX: prefix types used as operators should be quoted - - - - - a8f925bc by David Waern at 2007-09-29T14:02:26+00:00 Use isSymOcc from OccName instead of isConSym - - - - - fc330701 by David Waern at 2007-09-29T14:15:37+00:00 Use isLexConSym/isLexVarSym from OccName - - - - - e4f3dbad by David Waern at 2007-09-29T15:01:08+00:00 FIX: do not quote varsym type operators - - - - - 402207d2 by David Waern at 2007-09-29T15:01:50+00:00 Wibble - - - - - f9d89ef0 by David Waern at 2007-09-29T15:17:40+00:00 Take care when pp tyvars - add parens on syms - - - - - 849e2a77 by David Waern at 2007-10-01T21:56:39+00:00 Go back to using a ModuleMap instead of LookupMod - fixes a bug - - - - - 549dbac6 by David Waern at 2007-10-02T01:05:19+00:00 Improve parsing of doc options - - - - - a36021b8 by David Waern at 2007-10-02T23:05:00+00:00 FIX: double arrows in constructor contexts - - - - - d03bf347 by David Waern at 2007-10-09T16:14:05+00:00 Add a simple test suite - - - - - c252c140 by David Waern at 2007-10-17T16:02:28+00:00 Add --optghc=.. style flag passing to GHC - - - - - cce6c1b3 by David Waern at 2007-10-18T22:03:20+00:00 Add support for --read-interface again - - - - - 33d059c0 by David Waern at 2007-10-18T22:30:18+00:00 Refactoring -- get rid of Haddock.Packages - - - - - f9ed0a4c by David Waern at 2007-10-18T22:34:36+00:00 Name changes - - - - - 8a1c816f by David Waern at 2007-10-20T14:24:23+00:00 Add --ghc-version option - - - - - 4925aaa1 by David Waern at 2007-10-21T14:34:26+00:00 Add some Outputable utils - - - - - 69e7e47f by David Waern at 2007-10-21T14:35:49+00:00 FIX: Ord for OrdName was not comparing modules - - - - - 5a4ae535 by David Waern at 2007-10-21T21:18:48+00:00 Wibble - - - - - 03d48e20 by David Waern at 2007-10-24T15:52:56+00:00 Remove Main from "other modules" - - - - - c66f6d82 by David Waern at 2007-10-24T16:37:18+00:00 Make it possible to run haddock on itself - - - - - 21d156d8 by David Waern at 2007-10-25T14:02:14+00:00 Don't set boot modules as targets - - - - - f8bcf91c by David Waern at 2007-10-31T22:11:17+00:00 Add optimisation flags - - - - - 7ac758f2 by David Waern at 2007-11-04T09:48:28+00:00 Go back to loading only targets (seems to work now) - - - - - 4862aae1 by David Waern at 2007-11-05T22:24:57+00:00 Do full compilation of modules -- temporary fix for GHC API problem - - - - - 697e1517 by David Waern at 2007-11-05T22:25:50+00:00 Don't warn about not being able to link to wired/system/builtin-names - - - - - 892186da by David Waern at 2007-11-06T00:49:21+00:00 Filter out instances with TyCons that are not exported - - - - - 9548314c by David Waern at 2007-11-06T09:37:14+00:00 Wibble - - - - - 5cafd627 by David Waern at 2007-11-08T01:43:07+00:00 Filter out all non-vanilla type sigs - - - - - 04621830 by David Waern at 2007-11-08T01:45:13+00:00 Synch loading of names from .haddock files with GHC's name cache - - - - - 88d37f77 by David Waern at 2007-11-08T01:46:21+00:00 Remove commented-out code - - - - - 6409c911 by David Waern at 2007-11-08T01:56:00+00:00 Small bugfix and cleanup in getDeclFromTyCls - - - - - af59d9c2 by David Waern at 2007-11-08T02:08:44+00:00 Remove OrdName stuff - - - - - 3a615e2e by David Waern at 2007-11-08T02:13:41+00:00 Update runtests.hs following changes to haddock - - - - - 01f3314e by David Waern at 2007-11-08T02:33:01+00:00 Complain if we can't link to wired-in names - - - - - fcafb5d1 by David Waern at 2007-11-09T02:40:16+00:00 Don't exit when there are no file arguments - - - - - 194bc332 by David Waern at 2007-11-09T02:55:37+00:00 Wibble - - - - - dbe4cb55 by David Waern at 2007-11-09T02:56:14+00:00 Wibble - - - - - 82869fda by David Waern at 2007-11-10T17:01:43+00:00 Introduce InstalledInterface structure and add more stuff to the .haddock files We introduce InstalledInterface capturing the part of Interface that is stored in the interface files. We change the ppHtmlContents and ppHtmllIndex to take this structure instead of a partial Interface. We add stuff like the doc map and exported names to the .haddock file (via InstalledInterface). - - - - - d6bb57bf by David Waern at 2007-11-10T17:19:48+00:00 FIX: contents and index should include external package modules when --gen-contents/--gen-index - - - - - e8814716 by David Waern at 2007-11-11T00:29:27+00:00 Remove lDocLinkName and its use in Html backend - - - - - 6f9bd702 by David Waern at 2007-11-11T00:50:57+00:00 Do some refactoring in the html backend This also merges an old patch by Augustsson: Wed Jul 12 19:54:36 CEST 2006 lennart.augustsson at credit-suisse.com * Print type definitions like signatures if given arrows. - - - - - 09d0ce24 by Malcolm.Wallace at 2006-07-20T13:13:57+00:00 mention HsColour in the docs, next to option flags for linking to source code - - - - - 24da6c34 by Malcolm.Wallace at 2006-07-20T13:14:50+00:00 change doc references to CVS to give darcs repository location instead - - - - - 74d52cd6 by David Waern at 2007-11-11T00:55:33+00:00 Update copyright - - - - - fcaa3b4f by Duncan Coutts at 2006-09-08T13:41:00+00:00 Eliminate dep on network by doing a little cut'n'paste haddock depending on the network causes a circular dependency at least if you want to build the network lib with haddock docs. - - - - - 10cc9bda by David Waern at 2007-11-11T02:09:41+00:00 Fix conflicts - - - - - 4e3acd39 by David Waern at 2007-11-11T02:21:19+00:00 Manual merge of a patch from Duncan Coutts that removes the dependency on mtl - - - - - fa9070da by Neil Mitchell at 2006-09-29T15:52:03+00:00 Do not generate an empty table if there are no exports, this fixes a <table></table> tag being generated, which is not valid HTML 4.01 - - - - - d7431c85 by David Waern at 2007-11-11T02:28:50+00:00 Fix conflicts - - - - - f87e8f98 by Simon Marlow at 2006-10-10T11:37:16+00:00 changes for 0.8 - - - - - db929565 by Simon Marlow at 2006-10-10T12:07:12+00:00 fix the name of the source file - - - - - 8220aa4b by Simon Marlow at 2006-10-11T14:17:37+00:00 Rename haddock.js to haddock-util.js haddock.js will be run automatically by Windows when you type 'haddock' if it is found on the PATH, so rename to avoid confusion. Spotted by Adrian Hey. - - - - - 6bccdaa1 by sven.panne at 2006-10-12T15:28:23+00:00 Cabal's sdist does not generate "-src.tar.gz" files, but ".tar.gz" ones - - - - - d3f3fc19 by Simon Marlow at 2006-12-06T16:05:07+00:00 add todo item for --maintainer - - - - - 2da7e269 by Simon Marlow at 2006-12-15T15:52:00+00:00 TODO: do something better about re-exported symbols from another package - - - - - 42d85549 by David Waern at 2007-11-11T02:30:59+00:00 Fix conflicts - - - - - 5e7ef6e5 by Neil Mitchell at 2007-01-11T15:41:15+00:00 Never do spliting index files into many - - - - - f3d4aebe by Neil Mitchell at 2007-01-11T17:07:09+00:00 Add searching on the index page - - - - - bad3ab66 by Neil Mitchell at 2007-01-11T18:17:46+00:00 Delete dead code, now there is only one index page - - - - - cd09eedb by Neil Mitchell at 2007-01-11T18:21:19+00:00 Delete more stuff that is no longer required - - - - - e2806646 by David Waern at 2007-11-11T02:41:53+00:00 Fix conflicts - - - - - a872a823 by Neil Mitchell at 2007-01-11T18:51:43+00:00 Make the index be in case-insensitive alphabetic order - - - - - 8bddd9d7 by Neil Mitchell at 2007-02-06T17:49:12+00:00 Do not create empty tables for data declarations which don't have any constructors, instances or comments. Gets better HTML 4.01 compliance - - - - - 036b8120 by David Waern at 2007-11-11T02:56:58+00:00 Fix conflicts - - - - - f50c1639 by Conal Elliott at 2007-02-14T21:54:00+00:00 added substitution %{FILE///c} - - - - - 402e166a by David Waern at 2007-11-11T03:35:46+00:00 Manual merge of old patch: Sat Apr 21 04:36:43 CEST 2007 Roberto Zunino <zunrob at users.sf.net> * URL expansion for %%, %L, %{LINE} - - - - - 2f264fbd by David Waern at 2007-11-11T03:40:33+00:00 Manual merge of an old patch: Thu Apr 19 20:23:40 CEST 2007 Wolfgang Jeltsch <g9ks157k at acme.softbase.org> * bug fix When Haddock was invoked with the --ignore-all-exports flag but the ignore-exports module attribute wasn't used, hyperlinks weren't created for non-exported names. This fix might not be as clean as one would wish (since --ignore-all-exports now results in ignore_all_exports = True *and* an additional OptIgnoreExports option for every module) but at least the bug seems to be resolved now. - - - - - 7d7ae106 by sven.panne at 2007-09-02T12:18:02+00:00 Install LICENSE in the correct place - - - - - 66eaa924 by David Waern at 2007-11-11T19:02:46+00:00 Fix a bug that made haddock loop - - - - - 4ed47b58 by David Waern at 2007-11-11T19:03:09+00:00 Rename java-script file (this wasn't merge correctly) - - - - - d569534a by David Waern at 2007-11-11T19:06:44+00:00 Don't require -B <ghc-libdir> when no argument files Change readInterfaceFile to take a Maybe Session, to avoid having to pass -B <ghc-libdir> to Haddock when there're no source files to process. This is nice when computing contents/index for external packages. - - - - - 373368bc by Neil Mitchell at 2007-01-11T18:22:44+00:00 Change from tabs to spaces in the ppHtmlIndex function - - - - - 6b063a77 by Neil Mitchell at 2007-01-12T12:17:46+00:00 Rewrite much of the index searching code, previously was too slow to execute on the base library with IE, the new version guarantees less than O(log n) operations be performed, where n is the number in the list (before was always O(n)) - - - - - bfad00b7 by David Waern at 2007-11-11T23:33:53+00:00 Fix conflicts - - - - - cd2dcc09 by Neil Mitchell at 2007-01-12T12:25:01+00:00 Make the max number of results 75 instead of 50, to allow map searching in the base library to work - - - - - 3ae74764 by Neil Mitchell at 2007-01-12T12:58:17+00:00 Make the search box in a form so that enter does the default search - - - - - 142103e5 by David Waern at 2007-11-12T00:03:18+00:00 Merge patch from the old branch: Fri Aug 31 13:21:45 CEST 2007 Duncan Coutts <duncan at haskell.org> * Add category: Development to .cabal file Otherwise it appears on the hackage website in the "Unclassified" category. - - - - - 22ec2ddb by David Waern at 2007-11-25T01:55:29+00:00 A a list of small improvements to the TODO file - - - - - eb0129f4 by Wolfgang Jeltsch at 2007-12-03T23:47:55+00:00 addition of type equality support (at least for HTML generation) - - - - - 816a7e22 by David Waern at 2007-12-08T15:46:26+00:00 Handle class operators correctly when rendering predicates - - - - - 68baaad2 by David Waern at 2007-12-08T16:15:54+00:00 Code layout changes - - - - - 09b77fb4 by David Waern at 2007-12-08T16:16:03+00:00 Handle infix operators correctly in the Type -> HsType translation - - - - - 31c36da2 by David Waern at 2007-12-08T16:24:27+00:00 Add ppLParendTypes/ppLParendType - - - - - b17cc818 by David Waern at 2007-12-08T16:26:12+00:00 Use ppParendType when printing types args in predicates - - - - - ffd1f2cf by David Waern at 2007-12-08T16:45:06+00:00 Fix rendering of instance heads to handle infix operators This is also a refactoring to share this code for rendering predicates. - - - - - ff886d45 by David Waern at 2007-12-08T17:27:46+00:00 Fix rendering of class operators - - - - - e2fcbb9e by David Waern at 2007-12-08T17:59:28+00:00 Fix a bug (use ppTyName instead of ppName to print names in type apps) - - - - - 79a1056e by David Waern at 2007-12-08T21:25:18+00:00 Update tests - - - - - 867741ac by David Waern at 2007-12-08T21:25:49+00:00 Give a diff on test failure - - - - - 7e5eb274 by David Waern at 2008-01-05T14:33:45+00:00 Add DrIFT commands - - - - - 3656454d by David Waern at 2008-01-05T20:26:00+00:00 Add "cabal-version: >= 1.2" to the cabal file - - - - - 77974efc by Simon Marlow at 2007-12-20T09:52:44+00:00 add an item - - - - - f6ac1708 by Simon Marlow at 2007-12-06T14:00:10+00:00 Source links must point to the original module, not the referring module - - - - - eda1d5c9 by David Waern at 2008-01-06T14:40:52+00:00 Manual merge of a patch to the 0.8 branch Thu Dec 6 15:00:10 CET 2007 Simon Marlow <simonmar at microsoft.com> * Source links must point to the original module, not the referring module - - - - - 378f4085 by David Waern at 2008-01-06T16:03:45+00:00 Change stability from stable to experimental - - - - - 8bdafe44 by David Waern at 2008-01-06T16:14:22+00:00 Add haskell.vim (it had been removed somehow) - - - - - ea34d02e by David Waern at 2008-01-06T16:36:57+00:00 Change version to 2.0.0.0 - - - - - 34631ac0 by David Waern at 2008-01-06T16:44:57+00:00 Add missing modules to the cabal file - - - - - 9e142935 by David Waern at 2008-01-06T17:25:42+00:00 Depend on ghc >= 6.8.2 && < 6.9 - - - - - 59f9eeaa by Simon Marlow at 2007-12-20T10:43:04+00:00 add build scripts - - - - - 1c29ae30 by Simon Marlow at 2007-12-20T10:47:07+00:00 update version number - - - - - fe16a3e4 by Simon Marlow at 2007-12-20T10:48:03+00:00 update version - - - - - f688530f by Simon Marlow at 2007-12-20T10:48:29+00:00 doc updates - - - - - ce71b611 by David Waern at 2008-01-07T13:46:32+00:00 Change version in docs and spec - - - - - 03ab8d6f by David Waern at 2008-01-07T13:47:38+00:00 Manually merge over changes to CHANGES for 0.9 - - - - - 39f1b042 by David Waern at 2008-01-07T15:17:41+00:00 Remove the -use-package flag, we don't support it anyway - - - - - 7274a544 by David Waern at 2008-01-07T15:33:05+00:00 Update CHANGES for 2.0.0.0 - - - - - 96594f5d by David Waern at 2008-01-07T15:46:49+00:00 Wibble - - - - - f4c5a4c4 by David Waern at 2008-01-07T15:55:36+00:00 Change url to repo in documentation - - - - - 8a4c77f0 by David Waern at 2008-01-07T16:00:54+00:00 Update CHANGES - - - - - cb3a9288 by David Waern at 2008-01-07T16:02:55+00:00 Documentation fix - - - - - d8e45539 by David Waern at 2008-01-07T16:12:00+00:00 Update docs to say that Haddock accets .lhs files and module names - - - - - 4b5ce824 by David Waern at 2008-01-07T16:12:25+00:00 Document -B option - - - - - 47274262 by David Waern at 2008-01-07T16:23:07+00:00 Update CHANGES - - - - - 7ff314a9 by David Waern at 2008-01-07T16:23:20+00:00 Remove --use-package, --package & --no-implicit.. flags from docs - - - - - 6c3819c0 by David Waern at 2008-01-07T16:23:52+00:00 Remove --no-implicit-prelide flag - - - - - 1b14ae40 by David Waern at 2008-01-07T16:32:26+00:00 Update the "Using literate or pre-processed source" section - - - - - 0117f620 by David Waern at 2008-01-07T16:41:55+00:00 Document the --optghc flag - - - - - 087ab1cf by David Waern at 2008-01-07T16:42:10+00:00 Remove the documenation section on derived instances The problem mentioned there doesn't exist in Haddock 2.0.0.0 - - - - - 7253951e by David Waern at 2008-01-07T16:48:40+00:00 Document OPTIONS_HADDOCK - - - - - 3b6bdcf6 by David Waern at 2008-01-07T16:56:54+00:00 Wibble - - - - - 3025adf9 by David Waern at 2008-01-07T17:08:14+00:00 Wibble - - - - - 5f30f1a0 by David Waern at 2008-01-07T17:15:44+00:00 Change synopsis field to description - - - - - 1673f54b by David Waern at 2008-01-07T17:18:21+00:00 Change my email address in the cabal file - - - - - 55aa9808 by David Waern at 2008-01-07T18:18:02+00:00 Add documentation for readInterfaceFile - - - - - eaea417f by David Waern at 2008-01-07T18:21:30+00:00 Export necessary stuff from Distribution.Haddock - - - - - 7ea18759 by David Waern at 2008-01-07T18:31:49+00:00 Remove dep on Cabal - - - - - 7b79c74e by David Waern at 2008-01-07T18:33:49+00:00 Remove dep on process - - - - - ce3054e6 by David Waern at 2008-01-16T23:01:21+00:00 Add feature-requsts from Henning Thielemann to TODO - - - - - 0c08f1ec by David Waern at 2008-01-16T23:03:02+00:00 Record a bug in TODO - - - - - b04605f3 by David Waern at 2008-01-23T16:59:06+00:00 Add a bug reported by Ross to TODO - - - - - 5b17c030 by David Waern at 2008-01-23T18:05:53+00:00 A a bug report to TODO - - - - - 1c993b0d by David Waern at 2008-01-25T16:30:25+00:00 Accept test output - - - - - c22fc0d0 by David Waern at 2008-01-25T16:34:49+00:00 Accept test output - - - - - 4b795811 by David Waern at 2008-01-25T16:38:37+00:00 Change Hidden.hs (test) to use OPTIONS_HADDOCK - - - - - c124dbd9 by David Waern at 2008-01-25T16:39:23+00:00 Accept test output - - - - - ec6f6eea by David Waern at 2008-01-25T16:42:08+00:00 Add Hidden.html.ref to tests - - - - - 1dc9610c by David Waern at 2008-02-02T20:50:51+00:00 Add a comment about UNPACK bug in TODO - - - - - 2d3f7081 by David Waern at 2008-02-09T22:33:24+00:00 Change the representation of DocNames Ross Paterson reported a bug where links would point to the defining module instead of the "best" module for an identifier (e.g Int pointing to GHC.Base instead of Data.Int). This patch fixes this problem by refactoring the way renamed names are represented. Instead of representing them by: > data DocName = Link Name | NoLink Name they are now represented as such: > data DocName = Documented Name Module | Undocumented Name and the the link-env looks like this: > type LinkEnv = Map Name Module There are several reasons for this. First of all, the bug was caused by changing the module part of Names during the renaming process, without changing the Unique field. This caused names to be overwritten during the loading of .haddock files (which caches names using the NameCache of the GHC session). So we might create new Uniques during renaming to fix this (but I'm not sure that would be problem-free). Instead, we just keep the Name and add the Module where the name is best documented, since it can be useful to keep the original Name around (for e.g. source-code location info and for users of the Haddock API). Also, the names Link/NoLink don't really make sense, since wether to use links or not is entirely up to the users of DocName. In the process of following this change into H.Backends.Html I removed the assumption that binder names are Undocumented (which was just an unnecessary assumption, the OccName is the only thing needed to render these). This will probably make it possible to get rid of the renamer and replace it with a traversal from SYB or Uniplate. Since DocName has changed, InterfaceFile has changed so this patch also increments the file-format version. No backwards-compatibility is implemented. - - - - - 0f28c921 by David Waern at 2008-02-09T23:00:36+00:00 H.GHC.Utils: remove unused imports/exports - - - - - 0c44cad5 by David Waern at 2008-02-10T00:28:13+00:00 H.GHC.Utils: add some functions that were removed by mistake - - - - - e3452f49 by David Waern at 2008-02-10T00:28:48+00:00 Fix some trivial warnings in H.InterfaceFile - - - - - a6d74644 by David Waern at 2008-02-10T00:48:06+00:00 Update the version message to fit in small terminals - - - - - 76c9cd3e by David Waern at 2008-02-10T14:47:39+00:00 Remove bugs from TODO that don't apply anymore since the port - - - - - 5e10e090 by David Waern at 2008-02-10T15:22:47+00:00 Remove bugs from TODO that weren't actual bugs - - - - - fef70878 by David Waern at 2008-02-10T15:23:44+00:00 Remove yet another item from TODO that was not an actual bug - - - - - e1af47b8 by David Waern at 2008-02-11T10:25:57+00:00 Bump the version number to 2.1.0 Since the exported datatype DocName has changed, we need to bump the major version number. Let's also drop the fourth version component, it's not that useful. - - - - - e3be7825 by David Waern at 2008-04-11T14:29:04+00:00 Add a bug to TODO - - - - - cb6574be by David Waern at 2008-04-11T16:00:45+00:00 Use the in-place haddock when running tests - - - - - c6d7af0d by David Waern at 2008-04-11T16:09:16+00:00 Turn off GHC warnings when running tests - - - - - 7f61b546 by David Waern at 2008-04-11T17:24:00+00:00 Add a flag for turning off all warnings - - - - - 883b8422 by David Waern at 2008-04-12T14:02:18+00:00 Fix printing of data binders - - - - - 2a0db8fc by David Waern at 2008-04-12T18:52:46+00:00 Fix missing parenthesis in constructor args bug - - - - - 1b3ac3f9 by David Waern at 2008-04-12T18:57:23+00:00 Simplify test suite and add tests I move all tests into one single directory to simplify things, and add a test for the last bug that was fixed. - - - - - 8f178376 by David Waern at 2008-04-12T19:00:15+00:00 Add a script for copying test output to "expected" output - - - - - 193e3a03 by David Waern at 2008-04-12T19:16:37+00:00 Remove two fixed bugs from TODO - - - - - ddc9130c by David Waern at 2008-04-12T19:37:06+00:00 Update test README - - - - - 956069c0 by David Waern at 2008-05-01T12:16:14+00:00 Update version number in spec and docs - - - - - 5478621c by David Waern at 2008-05-01T12:28:12+00:00 Remove claim of backwards compatibility from docs for readInterfaceFile - - - - - 4a16dea9 by David Waern at 2008-05-01T12:33:04+00:00 Update CHANGES - - - - - 804216fb by David Waern at 2008-05-01T12:43:16+00:00 Add a synopsis - - - - - fd0c84d5 by David Waern at 2008-05-01T12:44:44+00:00 Add Haddock.DocName to the cabal file - - - - - 9f4a7439 by David Waern at 2008-05-01T12:45:53+00:00 Remove -fglasgow-exts and -fasm - - - - - aee7c145 by David Waern at 2008-05-01T12:54:01+00:00 Add LANGUAGE pragmas to source files - - - - - 9a58428b by David Waern at 2008-05-01T12:54:19+00:00 Add extensions to cabal file - - - - - 494f1bee by David Waern at 2008-05-01T13:12:09+00:00 Export DocName in the API - - - - - c938196b by David Waern at 2008-05-01T13:12:19+00:00 Add hide options to some source files - - - - - 236e86af by Neil Mitchell at 2008-06-07T20:45:10+00:00 Rewrite the --hoogle flag support - - - - - 6d910950 by Neil Mitchell at 2008-06-14T10:56:50+00:00 Simplify the newtype/data outputting in Hoogle, as haddock does it automatically - - - - - f87a95a8 by Neil Mitchell at 2008-06-14T12:10:18+00:00 Add initial structure for outputting documentation as well, but does not yet output anything - - - - - 7c3bce54 by Neil Mitchell at 2008-06-14T12:27:07+00:00 Remove <document comment> from the Hoogle output - - - - - 9504a325 by Neil Mitchell at 2008-06-16T06:33:21+00:00 Default to "main" if there is no package, otherwise will clobber hoogle's hoogle info - - - - - 4a794a79 by Neil Mitchell at 2008-06-16T06:53:29+00:00 Change packageName to packageStr, as it better reflects the information stored in it - - - - - 7abc9baf by Neil Mitchell at 2008-06-16T07:09:49+00:00 Add modulePkgInfo to Haddock.GHC.Utils, which gives back package name and version info - - - - - 8ca11514 by Neil Mitchell at 2008-06-16T07:13:48+00:00 Change Hoogle to take the package name and package version separately - - - - - a6da452d by Neil Mitchell at 2008-06-18T11:29:46+00:00 In Hoogle do not list things that are not local to this module - - - - - 974b76b7 by David Waern at 2008-06-19T18:40:13+00:00 Be more consistent with GHC API naming in H.GHC.Utils - - - - - 2facb4eb by David Waern at 2008-06-19T19:03:03+00:00 Update test output - - - - - c501de72 by David Waern at 2008-06-26T20:26:49+00:00 Use ghc-paths to get the lib dir The path can still be overridden using the -B flag. It's not longer required to pass the lib dir to the program that runs the test suite. - - - - - ac4c6836 by David Waern at 2008-06-26T20:33:08+00:00 Update CHANGES - - - - - 9d21c60a by David Waern at 2008-06-26T20:34:53+00:00 Update README - - - - - 741448f0 by David Waern at 2008-06-26T21:12:57+00:00 Improve wording in the help message - - - - - b1b42b11 by David Waern at 2008-06-30T10:16:17+00:00 Rename ForeignType - - - - - 6d6c2b34 by David Waern at 2008-06-30T10:25:09+00:00 Rename TyFamily - - - - - 8d1125ed by David Waern at 2008-06-30T10:37:21+00:00 Rename type patterns - - - - - 7610a4cb by David Waern at 2008-06-30T10:45:07+00:00 Rename associated types - - - - - 8eeba14c by David Waern at 2008-06-30T10:47:41+00:00 Remove the TODO file now that we have a trac - - - - - 1af5b25b by David Waern at 2008-07-02T18:19:28+00:00 Render type family declarations (untested) - - - - - ceb99797 by David Waern at 2008-07-02T18:24:06+00:00 Remove redundant check for summary when rendering data types - - - - - b36a58e0 by David Waern at 2008-07-02T22:01:38+00:00 More support for type families and associated types Now we just need to render the instances - - - - - 78784879 by David Waern at 2008-07-07T22:13:58+00:00 Remove filtering of instances We were filtering out all instances for types with unknown names. This was probably an attempt to filter out instances for internal types. I am removing the filtering for the moment, and will try to fix this properly later. - - - - - 3e758dad by David Waern at 2008-06-30T18:50:30+00:00 Run haddock in-place during testing - - - - - d9dab0ce by David Waern at 2008-07-08T21:04:32+00:00 Remove index.html and doc-index.html from output, they should not be versioned - - - - - 3e6c4681 by David Waern at 2008-07-08T21:06:42+00:00 Update test output following change to instance filtering - - - - - e34a3f14 by David Waern at 2008-07-12T16:48:28+00:00 Stop using the map from exported names to declarations During creation of the interface, we were using two maps: one from exported names to declarations, and one from all defined names in the module to declarations. The first contained subordinate names while the second one didn't. The first map was never used to look up names not defined in the associated module, so if we add subordinate names to the second map, we could use it everywhere. That's that this patch does. This simplifies code because we don't have to pass around two maps everywhere. We now store the map from locally defined things in the interface structure instead of the one from exported names. - - - - - 2e1d2766 by David Waern at 2008-07-12T16:55:21+00:00 Get the all locally defined names from GHC API We previously had some code to compute all locally defined names in a module including subordinate names. We don't need it since we can get the names from modInfoTyThings in the GHC API. - - - - - bf637994 by David Waern at 2008-07-13T13:09:16+00:00 Refactoring in H.Interface.Create We were creating a doc map, a declaration map and a list of entities separately by going through the HsGroup. These structures were all used to build the interface of a module. Instead of doing this, we can start by creating a list of declarations from the HsGroup, then collect the docs directly from this list (instead of using the list of entities), creating a documentation map. We no longer need the Entity data type, and we can store a single map from names to declarations and docs in the interface, instead of the declaration map and the doc map. This way, there is only one place where we filter out the declarations that we don't want, and we can remove a lot of code. Another advantage of this is that we can create the exports directly out of the list of declarations when we export the full module contents. (Previously we did a look up for each name to find the declarations). This is faster and removes another point where we depend on names to identify exported declarations, which is good because it eliminates problems with instances (which don't have names). - - - - - 547e410e by David Waern at 2008-07-13T13:34:51+00:00 Remove FastString import and FSLIT macro in H.I.Create -- they were unused - - - - - 693759d1 by David Waern at 2008-07-13T13:36:23+00:00 Remove unused import from H.I.Create - - - - - cde6e7fb by David Waern at 2008-07-13T13:51:54+00:00 Small touches - - - - - 96de8f1d by David Waern at 2008-07-20T11:21:46+00:00 Preparation for rendering instances as separate declarations We want to be able to render instances as separate declarations. So we remove the Name argument of ExportDecl, since instances are nameless. This patch also contains the first steps needed to gather type family instances and display them in the backend, but the implementation is far from complete. Because of this, we don't actually show the instances yet. - - - - - b0f824fb by David Waern at 2008-07-20T15:53:08+00:00 Follow changes to ExportDecl in Hoogle - - - - - 1192eff3 by Neil Mitchell at 2008-06-26T00:28:10+00:00 Change how the Hoogle backend outputs classes, adding the context in - - - - - 7a0d1464 by Neil Mitchell at 2008-06-26T00:28:46+00:00 Remove the indent utility function from Hoogle backend - - - - - 3361241b by Neil Mitchell at 2008-06-26T09:45:09+00:00 Add support for Hoogle writing ForeignImport/ForeignExport properly - - - - - 795ad3bf by Neil Mitchell at 2008-06-26T12:15:25+00:00 Flesh out the Hoogle code to render documentation - - - - - 23277995 by Neil Mitchell at 2008-06-26T14:56:41+00:00 Fix a bug in the Hoogle backend, unordered lists were being written out <ul>...</u> - - - - - db739b27 by Neil Mitchell at 2008-06-26T15:09:54+00:00 Remove any white space around a <li> element - - - - - f2e6bb8c by Neil Mitchell at 2008-07-10T15:30:47+00:00 Remove the TODO in the Hoogle HTML generation, was already done - - - - - 693ec9a3 by Neil Mitchell at 2008-07-10T15:53:00+00:00 Put brackets round operators in more places in the Hoogle output - - - - - 842313aa by Neil Mitchell at 2008-07-10T16:01:25+00:00 Print type signatures with brackets around the name - - - - - cf93deb0 by David Waern at 2008-07-20T17:04:22+00:00 Bump version number to 2.2.0 - - - - - 30e6a8d1 by David Waern at 2008-07-20T17:04:41+00:00 Resolve conflicts in H.B.Hoogle - - - - - 1f0071c9 by David Waern at 2008-07-23T23:05:01+00:00 Add "all" command to runtests.hs that runs all tests despite failures - - - - - f2723023 by David Waern at 2008-07-23T23:08:39+00:00 Update tests/README - - - - - c0304a11 by David Waern at 2008-07-23T23:21:15+00:00 Be compatible with GHC 6.8.3 The cabal file is converted to use the "new" syntax with explicit Library and Executable sections. We define the __GHC_PATCHLEVEL__ symbol using a conditinal cpp-options field in the cabal file. (Ideally, Cabal would define the symbol for us, like it does for __GLASGOW_HASKELL__). We use these symbols to #ifdef around a small difference between 6.8.2 and 6.8.3. Previously, we only supported GHC 6.8.2 officially but the dependencies field said "ghc <= 6.9". This was just for convenience when testing against the (then compatible) HEAD version of GHC, and was left in the release by mistake. Now, we support both GHC 6.8.2 and 6.8.3 and the dependencies field correctly reflects this. - - - - - 88a5fe71 by David Waern at 2008-07-23T23:54:16+00:00 Depend on the currently available ghc-paths versions only - - - - - 8738d97b by David Waern at 2008-07-24T10:50:44+00:00 FIX haskell/haddock#44: Propagate parenthesis level when printing documented types - - - - - 05339119 by David Waern at 2008-07-24T16:06:18+00:00 Drop unnecessary parenthesis in types, put in by the user We were putting in parenthesis were the user did. Let's remove this since it just clutters up the types. The types are readable anyway since we print parens around infix operators and do not rely on fixity levels. When doing this I discovered that we were relying on user parenthesis when printin types like (a `O` b) c. This patchs fixes this problem so that parenthesis are always inserted around an infix op application in case it is applied to further arguments, or if it's an arguments to a type constructor. Tests are updated. - - - - - b3a99828 by David Waern at 2008-07-24T10:19:43+00:00 Print parenthesis around non-atomic banged types Fixes half of haskell/haddock#44 - - - - - ab5238e0 by David Waern at 2008-07-24T22:07:49+00:00 Add a reference file for the TypeFamilies test - - - - - 1941cc11 by David Waern at 2008-07-25T17:15:53+00:00 Simplify definition of pretty and trace_ppr - - - - - e3bfa33c by David Waern at 2008-07-25T17:18:27+00:00 Warning messages Output a warning when filtering out data/type instances and associated types in instances. We don't show these in the documentation yet, and we need to let the user know. - - - - - 9b85fc89 by David Waern at 2008-07-25T17:45:40+00:00 Doc: Mention Hoogle in the Introduction - - - - - afb2dd60 by David Waern at 2008-07-25T17:49:00+00:00 Doc: update -B description - - - - - 584c0c91 by David Waern at 2008-07-25T18:11:38+00:00 Doc: describe -w flag - - - - - 77619c24 by David Waern at 2008-07-28T12:29:07+00:00 Remove TODO from cabal file - - - - - 96717d5f by David Waern at 2008-07-28T12:29:27+00:00 Support type equality predicates - - - - - c2fd2330 by David Waern at 2008-07-29T19:45:14+00:00 Move unL from H.B.Hoogle to H.GHC.Utils I like Neil's shorter unL better than unLoc from the GHC API. - - - - - c4c3bf6a by David Waern at 2008-07-29T19:47:36+00:00 Do not export ATs when not in list of subitems - - - - - bf9a7b85 by David Waern at 2008-08-03T11:42:59+00:00 Filter out ForeignExports - - - - - df59fcb0 by David Waern at 2008-08-03T14:02:51+00:00 Filter out more declarations The previous refactorings in H.I.Create introduced a few bugs. Filtering of some types of declarations that we don't handle was removed. This patch fixes this. - - - - - 2f8a958b by David Waern at 2008-08-03T15:24:07+00:00 Move reL to H.GHC.Utils so we can use it everywhere - - - - - 8ec15efd by David Waern at 2008-08-03T15:25:00+00:00 Use isVanillaLSig from GHC API instead of home brewn function - - - - - 300f93a2 by David Waern at 2008-08-03T15:25:27+00:00 Filter out separately exported ATs This is a quick and dirty hack to get rid of separately exported ATs. We haven't decided how to handle them yet. No warning message is given. - - - - - 8776d1ec by David Waern at 2008-08-03T16:21:21+00:00 Filter out more declarations and keep only vanilla type sigs in classes - - - - - ea07eada by David Waern at 2008-08-03T16:48:00+00:00 Fix layout - - - - - dd5e8199 by David Waern at 2008-08-03T16:50:52+00:00 Move some utility functions from H.I.Create to H.GHC.Utils - - - - - 4a1dbd72 by David Waern at 2008-08-03T17:39:55+00:00 Do not filter out doc declarations - - - - - 0bc8dca4 by David Waern at 2008-08-03T17:47:26+00:00 Filter out separately exported ATs (take two) - - - - - af970fe8 by David Waern at 2008-08-03T22:39:17+00:00 Update CHANGES - - - - - 5436ad24 by David Waern at 2008-08-03T22:40:20+00:00 Bump version number to 2.2.1 - - - - - d66de448 by David Waern at 2008-08-05T19:00:32+00:00 Remove version restriction on ghc-paths - - - - - 534b1364 by David Waern at 2008-08-05T19:04:35+00:00 Bump version to 2.2.2 and update CHANGES - - - - - 549188ff by David Waern at 2008-08-05T19:16:49+00:00 Fix CHANGES - - - - - 0d156bb4 by Luke Plant at 2008-08-11T15:20:59+00:00 invoking haddock clarification and help - - - - - 748295cc by David Waern at 2008-08-11T18:56:37+00:00 Doc: say that the --hoogle option is functional - - - - - 43301db4 by David Waern at 2008-08-05T19:26:08+00:00 Change ghc version dependency to >= 6.8.2 - - - - - 3e5a53b6 by David Waern at 2008-08-10T22:42:05+00:00 Make H.GHC.Utils build with GHC HEAD - - - - - 7568ace0 by David Waern at 2008-08-11T19:41:54+00:00 Import Control.OldException instead of C.Exception when using ghc >= 6.9 We should really test for base version instead, but I don't currently know which version to test for. - - - - - b71ae991 by David Waern at 2008-08-12T22:40:39+00:00 Make our .haddock file version number depend on the GHC version We need to do this, since our .haddock format can potentially change whenever GHC's version changes (even when only the patchlevel changes). - - - - - 6307ce3f by David Waern at 2008-08-12T22:49:57+00:00 Remove matching on NoteTy in AttachInstances, it has been removed - - - - - 2dbcfd5f by David Waern at 2008-08-12T23:02:02+00:00 Comment out H.GHC.loadPackages - it is unused and doesn't build with ghc >= 6.9 - - - - - c74db5c2 by David Waern at 2008-08-12T23:03:58+00:00 Hide <.> from GHC import in Hoogle only for ghc <= 6.8.3 - - - - - 69a44ebb by David Waern at 2008-08-12T23:11:12+00:00 Follow changes to parseDynamic/StaticFlags - - - - - 5881f3f0 by David Waern at 2008-08-13T21:43:58+00:00 Add __GHC_PATCHLEVEL__ symbol also when building the library - - - - - 8574dc11 by David Waern at 2008-08-13T21:44:17+00:00 Follow move of package string functions from PackageConfig to Module - - - - - c9baa77f by David Waern at 2008-08-13T21:45:29+00:00 Follow extensible exceptions changes - - - - - 9092de15 by David Waern at 2008-08-13T21:46:20+00:00 Update test following Haddock version change - - - - - ebe569a4 by David Waern at 2008-08-13T21:46:54+00:00 Follow changes to parseDynamic- parseStaticFlags in GHC - - - - - b8a5ffd3 by David Waern at 2008-08-13T21:47:36+00:00 Follow changes to Binary in GHC 6.9 - - - - - edfda1cc by David Waern at 2008-08-13T21:50:17+00:00 Change ghc version dependency to >= 6.8.2 && <= 6.9 - - - - - d59be1cf by Neil Mitchell at 2008-08-12T16:02:53+00:00 Output all items, even if they are not defined in this module - ensures map comes from Prelude, not just GHC.Base - - - - - dda93b9f by Neil Mitchell at 2008-08-12T21:37:32+00:00 Add support for type synonyms to Hoogle, was accidentally missing before (woops!) - - - - - b6ee795c by Neil Mitchell at 2008-08-13T14:03:24+00:00 Generalise Hoogle.doc and add a docWith - - - - - 415e1bb2 by Neil Mitchell at 2008-08-13T14:03:46+00:00 Make Hoogle add documentation to a package - - - - - 790a1202 by Neil Mitchell at 2008-08-18T12:52:43+00:00 Use the same method to put out signatures as class methods in the Hoogle backend - - - - - ded37eba by Neil Mitchell at 2008-08-18T12:53:04+00:00 Remove Explicit top-level forall's when pretty-printing signatures - - - - - 6468c722 by Neil Mitchell at 2008-08-20T07:59:13+00:00 Simplify the code by removing not-to-important use of <.> in the Hoogle back end - - - - - 788c3a8b by Neil Mitchell at 2008-08-21T18:20:24+00:00 In the hoogle back end, markup definition lists using <i>, not <b> - - - - - 77d4b000 by Ian Lynagh at 2008-08-14T10:49:14+00:00 Add a Makefile for GHC's build system. Still won't work yet, but we're closer - - - - - 920440d7 by Ian Lynagh at 2008-08-27T18:06:46+00:00 Add haddock.wrapper - - - - - bcda925f by Ian Lynagh at 2008-08-27T18:07:02+00:00 Add a manual Cabal flag to control the ghc-paths dependency - - - - - 04d194e2 by Ian Lynagh at 2008-08-27T20:41:27+00:00 Update extensions in Cabal file Use ScopedTypeVariables instead of PatternSignatures - - - - - 12480043 by Ian Lynagh at 2008-08-27T20:41:55+00:00 Increase the upper bound on the GHC version number - - - - - b1f809a5 by Ian Lynagh at 2008-08-27T21:32:22+00:00 Fix some warnings - - - - - aea0453d by Ian Lynagh at 2008-08-28T14:22:29+00:00 Fixes for using haddock in a GHC build tree - - - - - ad23bf86 by Ian Lynagh at 2008-08-28T21:14:27+00:00 Don't use Cabal wrappers on Windows - - - - - 35858e4c by Ian Lynagh at 2008-08-29T00:07:42+00:00 Fix in-tree haddock on Windows - - - - - c2642066 by Ian Lynagh at 2008-09-03T22:35:53+00:00 follow library changes - - - - - 2eb55d50 by Ian Lynagh at 2008-09-07T18:52:51+00:00 bindist fixes - - - - - 3daa5b59 by Ian Lynagh at 2008-09-10T16:58:18+00:00 We need to tell haddock that its datasubdir is . or it can't find package.conf - - - - - 388fd8c2 by Ian Lynagh at 2008-09-10T19:47:44+00:00 Fix haddock inplace on Windows - - - - - 70a641c1 by Ian Lynagh at 2008-09-10T22:15:44+00:00 Fix installed haddock on Windows - - - - - 83c1e997 by Neil Mitchell at 2008-09-11T10:48:55+00:00 Import GHC.Paths if not IN_GHC_TREE, seems to match the use of GHC.Paths functions much better - - - - - b452519b by Ian Lynagh at 2008-09-12T12:58:24+00:00 Add a LANGUAGE ForeignFunctionInterface pragma - - - - - afbd592c by Ian Lynagh at 2008-09-12T12:59:13+00:00 Wibble imports - - - - - 547ac4ad by Ian Lynagh at 2008-09-14T15:34:22+00:00 Add a "#!/bin/sh" to haddock.wrapper - - - - - f207a807 by Ian Lynagh at 2008-09-15T10:02:32+00:00 Use "exec" when calling haddock in the wrapper - - - - - 2ee68509 by Thomas Schilling at 2008-09-15T09:09:16+00:00 Port Haddock.Interface to new GHC API. This required one bigger change: 'readInterfaceFile' used to take an optional 'Session' argument. This was used to optionally update the name cache of an existing GHC session. This does not work with the new GHC API, because an active session requires the function to return a 'GhcMonad' action, but this is not possible if no session is provided. The solution is to use an argument of functions for reading and updating the name cache and to make the function work for any monad that embeds IO, so it's result type can adapt to the calling context. While refactoring, I tried to make the code a little more self-documenting, mostly turning comments into function names. - - - - - 3bb96431 by Thomas Schilling at 2008-09-15T09:09:37+00:00 Reflect GHC API changes. - - - - - 2e60f714 by Thomas Schilling at 2008-09-15T09:10:37+00:00 Port Haddock.GHC.Typecheck to new GHC API. - - - - - 9cfd4cff by Thomas Schilling at 2008-09-15T09:11:00+00:00 Port Haddock.GHC to new GHC API. - - - - - caffa003 by Thomas Schilling at 2008-09-15T09:11:25+00:00 Port Main to new GHC API. - - - - - 069a4608 by Ian Lynagh at 2008-09-21T11:19:00+00:00 Fix paths used on Windows frmo a GHC tree: There is no whare directory - - - - - 7ceee1f7 by Ian Lynagh at 2008-09-21T12:20:16+00:00 Fix the in-tree haddock on Windows - - - - - 0d486514 by Ian Lynagh at 2008-09-23T18:06:58+00:00 Increase the GHC upper bound from 6.11 to 6.13 - - - - - f092c414 by Neil Mitchell at 2008-09-11T14:56:07+00:00 Do not wrap __ in brackets - - - - - 036bdd13 by Ian Lynagh at 2008-09-28T01:42:35+00:00 Fix building haddock when GhcProfiled=YES - - - - - 01434a89 by David Waern at 2008-09-24T20:24:21+00:00 Add PatternSignatures LANGUAGE pragma to Main and Utils - - - - - 1671a750 by David Waern at 2008-10-02T22:57:25+00:00 For source links, get original module from declaration name instead of environment. Getting it from the environment must have been a remnant from the times when we were using unqualified names (versions 0.x). - - - - - a25dde99 by David Waern at 2008-10-02T22:59:57+00:00 Remove ifaceEnv from Interface - it's no longer used - - - - - 610993da by David Waern at 2008-10-02T23:04:58+00:00 Write a comment about source links for type instance declarations - - - - - 5a96b5d5 by Thomas Schilling at 2008-10-03T10:45:08+00:00 Follow GHC API change of parseModule. - - - - - 5a943ae5 by Ian Lynagh at 2008-10-03T15:56:58+00:00 TAG 2008-10-03 - - - - - 76cdd6ae by Thomas Schilling at 2008-10-08T12:29:50+00:00 Only load modules once when typechecking with GHC. This still doesn't fix the memory leak since the typechecked source is retained and then processed separately. To fix the leak, modules must be processed directly after typechecking. - - - - - 7074d251 by David Waern at 2008-10-09T23:53:54+00:00 Interleave typechecking with interface creation At the same time, we fix a bug where the list of interfaces were processed in the wrong order, when building the links and renaming the interfaces. - - - - - 4b9b2b2d by David Waern at 2008-10-09T23:54:49+00:00 Add some strictness annotations in Interface We add some strictness annotations to the fields of Interface, so that less GHC data is hold on to during processing. - - - - - 22035628 by David Waern at 2008-10-10T20:02:31+00:00 Remove typecheckFiles and MonadUtils import from H.GHC.Typeccheck - - - - - be637ad3 by David Waern at 2008-10-10T20:33:38+00:00 Make Haddock build with GHC 6.8.2 - - - - - 523b3404 by David Waern at 2008-10-10T21:08:09+00:00 Fix documentation for createInterfaces - - - - - e1556702 by David Waern at 2008-10-10T21:26:19+00:00 Hide H.Utils in library - - - - - a8e751c3 by David Waern at 2008-10-10T21:34:59+00:00 Add back .haddock file versioning based on GHC version It was accidentally removed in the patch for GHC 6.8.2 compatibility - - - - - 06fb3c01 by David Waern at 2008-10-10T21:47:15+00:00 Bump version number to 2.3.0 - - - - - ff087fce by David Waern at 2008-10-10T22:35:49+00:00 Add support for DocPic The support for DocPic was merged into the GHC source long ago, but the support in Haddock was forgotten. Thanks Peter Gavin for submitting this fix! - - - - - 3af85bf6 by David Waern at 2008-10-10T23:34:05+00:00 Update tests - - - - - 0966873c by Simon Marlow at 2008-10-10T14:43:04+00:00 no need for handleErrMsg now, we don't throw any ErrMsgs - - - - - f1870de3 by Clemens Fruhwirth at 2008-10-10T13:29:36+00:00 Compile with wrapper but remove it for dist-install - - - - - 7b440dc2 by David Waern at 2008-10-11T14:02:25+00:00 Remove interface from LinksInfo It was there to know the documentation home module when creating a wiki link, but we already know this since we have the DocName. - - - - - e5729e6a by David Waern at 2008-10-15T20:49:18+00:00 Wibble - - - - - b2a8e01a by David Waern at 2008-10-15T21:03:36+00:00 Use type synonyms for declarations and docs in H.I.Create - - - - - be71a15b by David Waern at 2008-10-15T21:12:17+00:00 Comment out unused type family stuff completely - - - - - 91aaf075 by David Waern at 2008-10-15T21:49:04+00:00 Wibble - - - - - 42ba4eb4 by David Waern at 2008-10-15T21:53:53+00:00 Move convenient type synonym to H.Types - - - - - db11b723 by David Waern at 2008-10-15T22:14:07+00:00 Add DeclInfo to H.Types - - - - - 193552b6 by David Waern at 2008-10-15T22:15:01+00:00 Add subordinates with docs to the declaration map The only place in the code where we want the subordinates for a declaration is right after having looked up the declaration in the map. And since we include subordinates in the map, we might as well take the opportunity to store those subordinates that belong to a particular declaration together with that declaration. We also store the documentation for each subordinate. - - - - - 31e6eebc by David Waern at 2008-10-16T17:18:47+00:00 Wibble - - - - - 0dcbd79f by David Waern at 2008-10-16T20:58:42+00:00 Fix haskell/haddock#61 We were not getting docs for re-exported class methods. This was because we were looking up the docs in a map made from the declarations in the current module being rendered. Obviously, re-exported class methods come from another module. Class methods and ATs were the only thing we were looking up using the doc map, everything else we found in the ExporItems. So now I've put subordinate docs in the ExportItem's directly, to make things a bit more consistent. To do this, I added subordinates to the the declarations in the declaration map. This was easy since we were computing subordinates anyway, to store stand-alone in the map. I added a new type synonym 'DeclInfo', which is what we call what is now stored in the map. This little refactoring removes duplicate code to retrieve subordinates and documentation from the HsGroup. - - - - - de47f20a by David Waern at 2008-10-16T22:06:35+00:00 Document function and improve its layout - - - - - e74e625a by Thomas Schilling at 2008-10-20T11:12:57+00:00 Force interface more aggressively. For running Haddock on GHC this reduces memory usage by about 50 MB on a 32 bit system. A heap profile shows total memory usage peak at about 100 MB, but actual usage is at around 300 MB even with compacting GC (+RTS -c). - - - - - b63ac9a1 by David Waern at 2008-10-20T20:25:50+00:00 Make renamer consistent Instead of explicitly making some binders Undocumented, treat all names the same way (that is, try to find a Documented name). - - - - - f6de0bb0 by Ian Lynagh at 2008-09-19T00:54:43+00:00 TAG GHC 6.10 fork - - - - - 74599cd0 by David Waern at 2008-10-20T21:13:24+00:00 Do not save hidden modules in the .haddock file We were saving interfaces of all processed modules including those hidden using {-# OPTIONS_HADDOCK hide #-} in the .haddock file. This caused broken links when generating the index for the libraries that come with GHC. This patch excludes modules with hidden documentation when writing .haddock files. It should fix the above problem. - - - - - 7b6742e9 by David Waern at 2008-10-21T19:54:52+00:00 Do not save hidden modules in the .haddock file (also for ghc >= 6.9) When writing the first patch, I forgot to do the fix in both branches of an #if macro. - - - - - b99b1951 by David Waern at 2008-10-22T20:04:18+00:00 Remove subordinate map and its usage It is not needed now that we store subordinate names in the DeclInfo map. - - - - - da97cddc by David Waern at 2008-10-22T20:11:46+00:00 Tidy up code in H.I.Create a little Remove commented out half-done type instance support, and remove DeclWithDoc synonym. - - - - - 6afa76f3 by David Waern at 2008-10-22T21:17:29+00:00 Fix warnings in H.GHC.Utils - - - - - 171ea1e8 by David Waern at 2008-10-22T21:35:04+00:00 Fix warnings in H.Utils - - - - - c8cb3b91 by David Waern at 2008-10-22T21:36:49+00:00 Wibble - - - - - 767fa06a by David Waern at 2008-10-27T19:59:04+00:00 Make named doc comments into ExportDoc instead of ExportDecl Fixes a crash when processing modules without export lists containing named docs. - - - - - e638bbc6 by David Waern at 2008-11-02T22:21:10+00:00 Add HCAR entry - - - - - 92b4ffcf by David Waern at 2008-11-02T22:44:19+00:00 Update CHANGES - - - - - 84d4da6e by David Waern at 2008-11-03T11:25:04+00:00 Add failing test for template haskell crash - - - - - 2a9cd2b1 by David Waern at 2008-11-04T21:13:44+00:00 Add tests/TH.hs - - - - - 8a59348e by David Waern at 2008-11-04T21:30:26+00:00 TAG 2.3.0 - - - - - 54f70d31 by Thomas Schilling at 2008-10-24T17:04:08+00:00 Enable framed view of the HTML documentation. This patch introduces: - A page that displays the documentation in a framed view. The left side will show a full module index. Clicking a module name will show it in the right frame. If Javascript is enabled, the left side is split again to show the modules at the top and a very short synopsis for the module currently displayed on the right. - Code to generate the mini-synopsis for each module and the mini module index ("index-frames.html"). - CSS rules for the mini-synopsis. - A very small amount of javascript to update the mini-synopsis (but only if inside a frame.) Some perhaps controversial things: - Sharing code was very difficult, so there is a small amount of code duplication. - The amount of generated pages has been doubled, since every module now also gets a mini-synopsis. The overhead should not be too much, but I haven't checked. Alternatively, the mini-synopsis could also be generated using Javascript if we properly annotate the actual synopsis. - - - - - 5d7ea5a6 by David Waern at 2008-11-04T23:20:17+00:00 Follow change to ExportDecl in frames code - - - - - 60e16308 by David Waern at 2008-11-04T23:35:26+00:00 Update CHANGES - - - - - d63fd26d by David Waern at 2008-11-04T23:37:43+00:00 Bump version number - - - - - c1660c39 by David Waern at 2008-11-04T23:44:46+00:00 Update CHANGES - - - - - 995ab384 by David Waern at 2008-11-04T23:55:21+00:00 Remove .ref files from tests/output/ - - - - - 1abbbe75 by David Waern at 2008-11-04T23:57:41+00:00 Output version info before running tests - - - - - 649b182f by David Waern at 2008-11-05T22:45:37+00:00 Add ANNOUNCE message - - - - - c36ae0bb by David Waern at 2008-11-05T23:15:35+00:00 Update ANNOUNCE - - - - - 9c4f3d40 by David Waern at 2008-11-05T23:18:30+00:00 Wibble - - - - - 5aac87ce by David Waern at 2008-11-06T21:07:48+00:00 Depend on base 4.* when using GHC >= 6.9, otherwise 3.* - - - - - b9796a74 by David Waern at 2008-11-06T21:13:40+00:00 Bump version to 2.4.1 and update CHANGES - - - - - d4b26baa by David Waern at 2008-11-06T21:26:33+00:00 Depend on base 4.0.* instead of 4.* - - - - - 2cb0903c by David Waern at 2008-11-06T21:46:53+00:00 Fix warnings in H.B.HH and H.B.HH2 - - - - - e568e89a by David Waern at 2008-11-06T21:47:12+00:00 Fix warnings in Haddock.ModuleTree - - - - - 9dc14fbd by David Waern at 2008-11-06T21:47:52+00:00 Fix warnings in Haddock.Version - - - - - 02ac197c by David Waern at 2008-11-06T21:51:31+00:00 Fix warnings in H.InterfaceFile and H.Options - - - - - 63e7439a by David Waern at 2008-11-06T21:59:45+00:00 Fix warnings in H.GHC.Typecheck - - - - - 4bca5b68 by David Waern at 2008-11-08T13:43:42+00:00 Set HscTarget to HscNothing instead of HscAsm There used to be a bug in the GHC API that prevented us from setting this value. - - - - - 07357aec by David Waern at 2008-11-09T22:27:00+00:00 Re-export NameCache and friends from Distribution.Haddock - - - - - ea554b5a by David Waern at 2008-11-09T23:14:10+00:00 Add Haddock.GHC.Utils to other-modules in library - - - - - 74aecfd7 by David Waern at 2008-11-10T01:18:57+00:00 Export DocName in the library - - - - - 241a58b3 by David Waern at 2008-11-10T01:19:18+00:00 Document the functions in H.DocName - - - - - edc2ef1b by David Waern at 2008-11-10T01:20:52+00:00 Export H.DocName in the library - - - - - 4f588d55 by David Waern at 2008-11-10T01:29:14+00:00 Make DocName an instance of NamedThing - - - - - b4647244 by David Waern at 2008-11-15T22:58:18+00:00 Reflect version bump in test suite - - - - - 4bee8ce2 by David Waern at 2008-11-15T22:58:45+00:00 Update tests For unknown reasons, test output for Bug1 and Test has changed for the better. - - - - - 1690e2f9 by David Waern at 2008-11-15T22:59:33+00:00 Store hidden modules in .haddock files We store documentation for an entity in the 'InstalledInterface' of the definition site module, and never in the same structure for a module which re-exports the entity. So when a client of the Haddock library wants to look up some documentation, he/she might need to access a hidden module. But we currently don't store hidden modules in the .haddock files. So we add the hidden modules and the Haddock options to the .haddock files. The options will be used to filter the module list to obtain the visible modules only, which is necessary for generating the contents and index for installed packages. - - - - - 8add6435 by David Waern at 2008-11-16T14:35:50+00:00 Bump major version number due to .haddock file format change - - - - - 48bfcf82 by David Waern at 2008-11-23T14:32:52+00:00 Update tests to account for version number bump - - - - - 0bbd1738 by David Waern at 2008-11-23T14:33:31+00:00 HADDOCK_DATA_DIR changed to haddock_datadir - - - - - 5088b78c by David Waern at 2008-11-23T17:13:21+00:00 FIX haskell/haddock#45: generate two anchors for each name We generate two anchor tags for each name, one where we don't escape the name and one where we URI-encode it. This is for compatibility between IE and Opera. Test output is updated. - - - - - 5ee5ca3b by Neil Mitchell at 2008-11-27T14:38:11+00:00 Drop HsDocTy annotations, they mess up pretty printing and also have a bracketing bug (#2584) - - - - - 51c014e9 by Roman Cheplyaka at 2008-11-27T22:27:36+00:00 Allow referring to a specific section within a module in a module link Fixes haskell/haddock#65 - - - - - 4094bdc5 by David Waern at 2008-11-28T21:13:33+00:00 Update tests following anchor change - - - - - f89552dd by Thomas Schilling at 2008-11-29T16:16:20+00:00 Haddock really shouldn't try to overwrite files. - - - - - 98127499 by David Waern at 2008-12-07T14:09:15+00:00 Solve conflict - - - - - 319356c5 by David Waern at 2008-10-22T21:16:55+00:00 Add -Wall -Werror to ghc-options - - - - - 3c4968c9 by David Waern at 2008-11-04T23:38:56+00:00 TAG 2.4.0 - - - - - 4b21e003 by David Waern at 2008-11-06T21:14:04+00:00 TAG 2.4.1 - - - - - 8e0cad5c by David Waern at 2008-12-07T14:12:54+00:00 Remove -Werror - - - - - 299d6deb by David Waern at 2008-12-07T14:25:18+00:00 Remove -Wall, we'll focus on warnings after 6.10.2 is out - - - - - 5f4216b6 by David Waern at 2008-12-07T20:58:05+00:00 Resolve conflict properly - - - - - 67d774e7 by Neil Mitchell at 2008-12-15T11:44:26+00:00 Make forall's in constructors explicit, i.e. data Foo = Foo {foo :: Eq a => a} - - - - - 61851792 by Neil Mitchell at 2008-12-18T15:39:39+00:00 Try and find a better package name than "main" for Hoogle, goes wrong when working on an executable rather than a library - - - - - 2fab8554 by David Waern at 2008-12-08T23:19:48+00:00 Make visible names from ExportItems Instead of a complicated calculation of visible names out of GHC's export items, we can get them straight out of the already calculated ExportItems. The ExportItems should represent exactly those items that are visible in an interface. If store all the exported sub-names in ExportDecl instead of only those with documentation, the calculation becomes very simple. So we do this change as well (should perhaps have been a separate patch). This should fix the problem with names from ghc-prim not appearing in the link environment. - - - - - 7caadd8c by Ian Lynagh at 2008-12-11T17:01:04+00:00 Wrap the GHC usage with defaultCleanupHandler This fixes a bug where haddock leaves /tmp/ghc* directories uncleaned. - - - - - 7c9fc9a5 by David Waern at 2009-01-02T21:38:27+00:00 Show re-exported names from external packages again This fixes GHC ticket 2746. In order to also link to the exported subordinate names of a declaration, we need to re-introduce the sub map in the .haddock files. - - - - - 119e4e05 by David Waern at 2009-01-06T23:34:17+00:00 Do not process boot modules We should of course not try to produce documentation for boot modules! The reason this has worked in the past is that the output of "real" modules overwrites the output of boot modules later in the process. However, this causes a subtle link environment problem. So let's get rid of this stupid behaviour. We avoid processing boot modules, but we continue to typecheck them. - - - - - c285b9d2 by David Waern at 2009-01-08T18:03:36+00:00 Export modules also when coming from external packages This seems to have regressed since a refactoring that was part of the 2.3.0 release. - - - - - 24031c17 by David Waern at 2009-01-10T15:26:26+00:00 Change version to 2.4.2 - no need to go to 2.5.0 - - - - - 864d1c3f by David Waern at 2009-01-10T15:35:20+00:00 Update tests to account for version number change - - - - - 524ba886 by David Waern at 2009-01-10T18:29:17+00:00 Add test for Template Haskell splicing - - - - - 05e6e003 by David Waern at 2009-01-10T19:35:42+00:00 Fix Trac haskell/haddock#68: Turn on compilation via C for Template Haskell packages We can't use HscNothing if we need to run code coming from modules inside the processed package during typechecking, which is the case for some packages using Template Haskell. This could be improved, to e.g. use HscInterpreted and HscNothing where possible, instead of using HscC for all modules in the package. - - - - - 2b2bafa1 by David Waern at 2009-01-10T20:22:25+00:00 Only use needsTemplateHaskell when compiling with GHC 6.10.2 or above - - - - - bedc3a93 by Ian Lynagh at 2009-01-11T14:58:41+00:00 Fix the location of INPLACE_PKG_CONF; fixes the build Spotted by Conal Elliott - - - - - 943107c8 by David Waern at 2009-01-20T19:27:39+00:00 Document H.I.Create.collectDocs better - - - - - c6252e37 by David Waern at 2009-01-20T19:29:51+00:00 Fix Trac haskell/haddock#59: TH-generated declarations disappearing This patch was contributed by Joachim Breitner (nomeata). - - - - - 3568a6af by David Waern at 2009-01-21T21:41:48+00:00 Do not indicate that a constructor argument is unboxed We only show the strictness annotation for an unboxed constructor argument. The fact that it is unboxed is an implementation detail and should not be part of the module interface. - - - - - 562a4523 by David Waern at 2009-01-22T18:53:49+00:00 Fix Trac haskell/haddock#50: do not attach docs to pragmas or other kinds of non-declarations We now filter out everything that is not a proper Haskell declaration before collecting the docs and attaching them to declarations. - - - - - 6fdf21c2 by David Waern at 2009-01-22T19:48:09+00:00 Add test for quasi quotation. No reference output yet. - - - - - dc4100fd by David Waern at 2009-01-22T19:57:47+00:00 Improve quasi-quotation test and add reference output - - - - - 908b74bb by David Waern at 2009-01-23T23:22:03+00:00 Filter out separately exported associated types in a smarter way - - - - - f6b42ecb by David Waern at 2009-01-24T16:54:39+00:00 Correct spelling mistake in error message - - - - - 24e4245d by David Waern at 2009-01-24T17:48:03+00:00 Correct comment - - - - - b5e8462f by David Waern at 2009-02-07T13:22:29+00:00 Do not show a subordinate at the top level if its parent is also exported See note in the source code for more info. - - - - - 4b09de57 by David Waern at 2009-02-07T13:53:53+00:00 Update test following change to top level subordinates - - - - - 76379896 by David Waern at 2009-02-07T13:58:04+00:00 Remove html files in the tests/output/ directory which have been accidentally added - - - - - 1a6d8b10 by Joachim Breitner at 2009-02-20T10:29:43+00:00 Typo in comment - - - - - fec367d0 by David Waern at 2009-02-24T20:21:17+00:00 Fix small bug The rule is to prefer type constructors to other things when an identifier in a doc string can refer to multiple things. This stopped working with newer GHC versions (due to a tiny change in the GHC renamer). We implement this rule in the HTML backend for now, instead of fixing it in GHC, since we will move renaming of doc strings to Haddock in the future anyway. - - - - - 9b4172eb by David Waern at 2009-02-25T20:04:38+00:00 Fix bad error handling with newer GHCs When support for GHC 6.10 was added, an error handler was installed only around the typechecking phase. This had the effect that errors thrown during dependency chasing were caught in the top-level exception handler and not printed with enough detail. With this patch we wrap the error handler around all our usage of the Ghc monad. - - - - - de2df363 by Simon Peyton Jones at 2009-02-02T16:47:42+00:00 Hide funTyConName, now exported by TypeRep - - - - - 4d40a29f by Ian Lynagh at 2009-02-12T18:57:49+00:00 Don't build the library when building in the GHC tree - - - - - 1cd0abe4 by Ian Lynagh at 2009-02-13T13:58:53+00:00 Add a ghc.mk - - - - - 3d814eeb by Ian Lynagh at 2009-02-13T18:50:28+00:00 do .depend generation for haddock with the stage1 compiler This is a bit of a hack. We mkdepend with stage1 as if .depend depends on the stage2 compiler then make goes wrong: haddock's .depend gets included, which means that make won't reload until it's built, but we can't build it without the stage2 compiler. We therefore build the stage2 compiler before its .depend file is available, and so compilation fails. - - - - - b55036a4 by Ian Lynagh at 2009-02-25T01:38:13+00:00 Give haddock a wrapper on unix in the new GHC build system - - - - - 9eabfe68 by Ian Lynagh at 2009-02-25T19:21:32+00:00 Create inplace/lib/html in the new GHC build system - - - - - 93af30c7 by Ian Lynagh at 2008-11-07T19:18:23+00:00 TAG GHC 6.10.1 release - - - - - 06e6e34a by Thomas Schilling at 2009-02-24T18:11:00+00:00 Define __GHC_PATCHLEVEL__ for recent version of GHC (stable). - - - - - 680e6ed8 by Thomas Schilling at 2009-02-24T18:12:26+00:00 'needsTemplateHaskell' is not defined in current stable GHC. - - - - - 6c5619df by David Waern at 2009-02-25T22:15:23+00:00 Hide fynTyConName only for recent GHC versions - - - - - 6b2344f1 by Ian Lynagh at 2009-02-26T00:49:56+00:00 Add the module to one of haddocks warnings - - - - - e5d11c70 by David Waern at 2009-02-27T21:37:20+00:00 Bug fix We tried to filter out subordinates that were already exported through their parent. This didn't work properly since we were in some cases looking at the grand-parent and not the parent. We now properly compute all the parent-child relations of a declaration, and use this information to get the parent of a subordinate. We also didn't consider record fields with multiple parents. This is now handled correctly. We don't currently support separately exported associated types. But when we do, they should be handled correctly by this process too. Also slightly improved the warning message that we give when filtering out subordinates. - - - - - 10a79a60 by David Waern at 2009-02-27T22:08:08+00:00 Fix error message conflict The module name is already written in the beginning of the message, as seems to be the convention in Haddock. Perhaps not so clear, but we should change it everywhere in that case. Leaving it as it is for now. - - - - - c5055c7f by David Waern at 2009-02-27T22:15:17+00:00 Shorten warning message - - - - - a72fed3a by David Waern at 2009-02-28T00:53:55+00:00 Do not show package name in warning message - - - - - a5daccb2 by Ian Lynagh at 2009-03-01T14:59:35+00:00 Install haddock in the new GHC build system - - - - - dfdb025c by Ian Lynagh at 2009-03-07T23:56:29+00:00 Relax base dependency to < 4.2, not < 4.1 - - - - - 5769c8b4 by David Waern at 2009-03-21T14:58:52+00:00 Bump .haddock file version number (due to change of format) - - - - - f1b8f67b by David Waern at 2009-03-21T14:59:26+00:00 Define __GHC_PATCHLEVEL__=1 when using ghc-6.10.1 - - - - - 23f78831 by David Waern at 2009-03-21T16:40:52+00:00 Update CHANGES - - - - - 7d2735e9 by David Waern at 2009-03-21T16:50:33+00:00 Update ANNOUNCE - - - - - 0771e00a by David Waern at 2009-03-21T16:54:40+00:00 Update ANNOUNCE, again - - - - - 81a6942a by David Waern at 2009-03-21T17:50:06+00:00 Don't be too verbose in CHANGES - - - - - 29861dcf by David Waern at 2009-03-21T18:03:31+00:00 TAG 2.4.2 - - - - - a585f285 by David Waern at 2009-03-21T19:20:29+00:00 Require Cabal >= 1.2.3 - - - - - 7c611662 by David Waern at 2009-03-21T19:21:48+00:00 TAG 2.4.2 with cabal-version >= 1.2.3 - - - - - 23b7deff by Simon Marlow at 2009-03-20T15:43:42+00:00 new GHC build system: use shell-wrappers macro - - - - - 25f8afe7 by Ian Lynagh at 2009-03-21T19:13:53+00:00 Fix (with a hack?) haddock in teh new build system - - - - - 6a29a37e by David Waern at 2009-03-24T22:10:15+00:00 Remove unnecessary LANGUAGE pragma - - - - - 954da57d by David Waern at 2009-03-24T22:21:23+00:00 Fix warnings in H.B.DevHelp - - - - - 1619f1df by David Waern at 2009-03-26T23:20:44+00:00 -Wall police in H.B.Html - - - - - b211e13b by Simon Marlow at 2009-03-24T13:00:56+00:00 install Haddock's html stuff - - - - - 78e0b107 by David Waern at 2008-12-07T19:58:53+00:00 Add verbosity flag and utils, remove "verbose" flag - - - - - 913dae06 by David Waern at 2008-12-07T20:01:05+00:00 Add some basic "verbose" mode logging in H.Interface - - - - - 1cbff3bf by David Waern at 2009-03-27T00:07:26+00:00 Fix conflicts - - - - - 22f82032 by David Waern at 2009-03-27T21:15:11+00:00 Remove H.GHC.Typecheck - - - - - 81557804 by David Waern at 2009-03-27T21:19:22+00:00 Remove docNameOrig and use getName everywhere instead - - - - - d8267213 by David Waern at 2009-03-27T21:21:46+00:00 Use docNameOcc instead of nameOccName . getName - - - - - 5d55deab by David Waern at 2009-03-27T21:33:04+00:00 Remove H.DocName and put DocName in H.Types - - - - - 8ba72611 by David Waern at 2009-03-27T22:06:26+00:00 Document DocName - - - - - 605f8ca5 by David Waern at 2009-03-27T22:45:21+00:00 -Wall police - - - - - e4da93ae by David Waern at 2009-03-27T23:12:53+00:00 -Wall police in H.B.Hoogle - - - - - bb255519 by David Waern at 2009-03-27T23:41:28+00:00 Define Foldable and Traversable instances for Located - - - - - f1195cfe by David Waern at 2009-03-27T23:51:34+00:00 Wibble - - - - - 23818d7c by David Waern at 2009-03-28T00:03:55+00:00 -Wall police in H.I.Rename - - - - - 0f050d67 by David Waern at 2009-03-28T00:15:15+00:00 -Wall police in H.I.AttachInstances - - - - - 0f3fe038 by David Waern at 2009-03-28T21:09:41+00:00 Wibble - - - - - 275d4865 by David Waern at 2009-03-28T21:27:06+00:00 Layout fix - - - - - 54ff0ef8 by David Waern at 2009-03-28T21:59:07+00:00 -Wall police in H.I.Create - - - - - 7f58b117 by David Waern at 2009-03-28T22:10:19+00:00 -Wall police in H.Interface - - - - - f0c03b44 by David Waern at 2009-03-28T22:22:59+00:00 -Wall police in Main - - - - - 29da355c by David Waern at 2009-03-28T22:23:39+00:00 Turn on -Wall -Werror - - - - - 446d3060 by David Waern at 2009-04-01T20:40:30+00:00 hlint police - - - - - 3867c9fc by David Waern at 2009-04-01T20:48:42+00:00 hlint police - - - - - bd1f1600 by David Waern at 2009-04-01T20:58:02+00:00 hlint police - - - - - e0e90866 by David Waern at 2009-04-05T12:42:53+00:00 Move H.GHC.Utils to H.GhcUtils - - - - - 9cbd426b by David Waern at 2009-04-05T12:57:21+00:00 Remove Haddock.GHC and move its (small) contents to Main - - - - - b5c2cbfd by David Waern at 2009-04-05T13:07:04+00:00 Fix whitespace and stylistic issues in Main - - - - - 3c04aa56 by porges at 2008-12-07T08:22:19+00:00 add unicode output - - - - - 607918da by David Waern at 2009-04-26T15:09:43+00:00 Resolve conflict - - - - - 4bec6b6b by Simon Marlow at 2009-05-13T10:00:31+00:00 fix markup - - - - - 436ad6f4 by Simon Marlow at 2009-03-23T11:54:45+00:00 clean up - - - - - bdcd1398 by Simon Marlow at 2009-03-24T10:36:45+00:00 new GHC build system: add $(exeext) - - - - - 9c0972f3 by Simon Marlow at 2009-03-24T11:04:31+00:00 update for new GHC build system layout - - - - - d0f3f83a by Ian Lynagh at 2009-03-29T15:31:43+00:00 GHC new build system fixes - - - - - 5a8245c2 by Ian Lynagh at 2009-04-04T20:44:23+00:00 Tweak new build system - - - - - 9c6f2d7b by Simon Marlow at 2009-05-13T10:01:27+00:00 add build instructions for GHC - - - - - 66d07c76 by Ian Lynagh at 2009-05-31T00:37:53+00:00 Quote program paths in ghc.mk - - - - - bb7de2cd by Ian Lynagh at 2009-06-03T22:57:55+00:00 Use a bang pattern on an unlifted binding - - - - - 3ad283fc by Ian Lynagh at 2009-06-13T16:17:50+00:00 Include haddock in GHC bindists - - - - - ac447ff4 by David Waern at 2009-06-24T21:07:50+00:00 Delete Haddock.Exception and move contents to Haddock.Types Only a few lines of code that mainly declares a type - why not just put it in Haddock.Types. - - - - - 4464fb9b by David Waern at 2009-06-24T22:23:23+00:00 Add Haddock module headers Add a proper Haddock module header to each module, with a more finegrained copyright. If you feel mis-accreditted, please correct any copyright notice! The maintainer field is set to haddock at projects.haskell.org. Next step is to add a brief description to each module. - - - - - 5f4c95dd by David Waern at 2009-06-24T22:39:44+00:00 Fix spelling error - - - - - 6d074cdb by David Waern at 2009-06-25T21:53:56+00:00 Document Interface and InstalledInterface better - - - - - d0cbd183 by David Waern at 2009-06-27T12:46:46+00:00 Remove misplaced whitespace in H.I.Rename - - - - - fa381c49 by David Waern at 2009-06-27T13:26:03+00:00 Fix haskell/haddock#104 - create output directory if missing - - - - - 91fb77ae by Ian Lynagh at 2009-06-25T15:59:50+00:00 TAG 2009-06-25 - - - - - 0d853f40 by Simon Peyton Jones at 2009-07-02T15:35:22+00:00 Follow extra field in ConDecl - - - - - b201735d by Ian Lynagh at 2009-07-05T16:50:35+00:00 Update Makefile for the new GHC build system - - - - - df6c0092 by Ian Lynagh at 2009-07-05T17:01:13+00:00 Resolve conflicts - - - - - 1066870a by Ian Lynagh at 2009-07-05T17:01:48+00:00 Remove the -Wwarn hack in the GHC build system - - - - - 7e856076 by Ian Lynagh at 2009-07-05T17:17:59+00:00 Fix warnings - - - - - 5d4cd958 by Ian Lynagh at 2009-07-05T19:35:40+00:00 Bump version number Cabal needs to distinguish between haddocks having a --verbose and --verbosity flag - - - - - 6ee07c99 by David Waern at 2009-07-06T20:14:57+00:00 Wibble - - - - - 2308b66f by David Waern at 2009-07-06T20:24:20+00:00 Clearer printing of versions by runtests.hs - - - - - d4b5d9ab by David Waern at 2009-07-06T21:22:42+00:00 Fix (invisible) bug introduced by unicode patch - - - - - 2caca8d8 by David Waern at 2009-07-06T21:44:10+00:00 Use HscAsm instead of HscC when using TH - - - - - 18f3b755 by David Waern at 2009-07-06T22:10:22+00:00 Update HCAR entry (by Janis) - - - - - a72ac9db by David Waern at 2009-07-06T23:01:35+00:00 Follow HsRecTy change with an #if __GLASGOW_HASKEL__ >= 611 - - - - - 549135d2 by David Waern at 2009-07-06T23:11:41+00:00 Remove unused functions from Haddock.Utils - - - - - b450134a by Isaac Dupree at 2009-07-11T14:59:00+00:00 revert to split-index for large indices - remove the search-box, because browsers have search-for-text abilities anyway. - pick 150 items in index as the arbitrary time at which to split it - notice the bug that identifiers starting with non-ASCII characters won't be listed in split-index, but don't bother to fix it yet (see ticket haskell/haddock#116, http://trac.haskell.org/haddock/ticket/116 ) - - - - - 78a5661e by Isaac Dupree at 2009-07-20T15:37:18+00:00 Implement GADT records in HTML backend - - - - - 4e163555 by Isaac Dupree at 2009-07-21T22:03:25+00:00 add test for GADT records - - - - - 79aa4d6e by David Waern at 2009-07-23T20:40:37+00:00 Update test suite following version bump - - - - - 5932c011 by David Waern at 2009-08-02T10:25:39+00:00 Fix documentation bug - - - - - a6970fca by David Waern at 2009-08-12T23:08:53+00:00 Remove support for ghc 6.8.* from .cabal file - - - - - c1695902 by Ian Lynagh at 2009-07-07T13:35:45+00:00 Fix unused import warnings - - - - - fb6df7f9 by Ian Lynagh at 2009-07-16T00:20:31+00:00 Use cProjectVersion directly rather than going through compilerInfo Fixes the build after changes in GHC - - - - - 548cdd66 by Simon Marlow at 2009-07-28T14:27:04+00:00 follow changes in GHC's ForeignType - - - - - 9395aaa0 by David Waern at 2009-08-13T22:17:33+00:00 Switch from PatternSignatures to ScopedTypeVariables in Main - - - - - eebf39bd by David Waern at 2009-08-14T17:14:28+00:00 Version .haddock files made with GHC 6.10.3/4 correclty - - - - - 58f3e735 by David Waern at 2009-08-14T17:19:37+00:00 Support GHC 6.10.* and 6.11.* only - - - - - 5f63cecc by David Waern at 2009-08-14T22:03:20+00:00 Do not version .haddock file based on GHC patchlevel version We require that the instances of Binary that we use from GHC will not change between patchlevel versions. - - - - - d519de9f by David Waern at 2009-08-14T23:50:00+00:00 Update CHANGES - - - - - 35dccf5c by David Waern at 2009-08-14T23:51:38+00:00 Update version number everywhere - - - - - 6d363fea by David Waern at 2009-08-15T09:46:49+00:00 Update ANNOUNCE - - - - - c7ee6bc2 by David Waern at 2009-08-15T09:47:13+00:00 Remove -Werror Forgot that Hackage doesn't like it. - - - - - a125c12b by David Waern at 2009-08-15T09:49:50+00:00 Require Cabal >= 1.6 - - - - - adb2f560 by Isaac Dupree at 2009-08-12T03:47:14+00:00 Cross-Package Documentation version 4 - - - - - 3d6dc04d by David Waern at 2009-08-15T23:42:57+00:00 Put all the IN_GHC_TREE stuff inside getGhcLibDir - - - - - 56624097 by David Waern at 2009-08-15T23:52:03+00:00 Add --print-ghc-libdir - - - - - f15d3ccb by David Waern at 2009-08-16T00:37:52+00:00 Read base.haddock when running tests We can now test cross-package docs. - - - - - 283f0fb9 by David Waern at 2009-08-16T00:50:59+00:00 Update test output - we now have more links - - - - - 673d1004 by David Waern at 2009-08-16T01:26:08+00:00 Read process.haddock when running tests - - - - - 0d127f82 by David Waern at 2009-08-16T01:43:04+00:00 Add a test for cross-package documentation - - - - - f94db967 by Ian Lynagh at 2009-08-16T18:42:44+00:00 Follow GHC build system changes - - - - - 5151278a by Isaac Dupree at 2009-08-16T19:58:05+00:00 make cross-package list types look nicer - - - - - c41e8228 by Isaac Dupree at 2009-08-18T01:47:47+00:00 Haddock.Convert: export more functions This lets us remove some code in Haddock.Interface.AttachInstances - - - - - 2e5fa398 by Isaac Dupree at 2009-08-18T02:11:05+00:00 switch AttachInstances to use synify code It changed an instance from showing ((,) a b) to (a, b) because my synify code is more sophisticated; I hope the latter is a good thing rather than a bad thing aesthetically, here. But this definitely reduces code duplication! - - - - - b8b07123 by Isaac Dupree at 2009-08-18T02:23:31+00:00 Find instances using GHC, which is more complete. In particular, it works cross-package. An intermediate patch also moved the instance-finding into createInterface, but that move turned out not to be necessary, so if we want to do that, it'd go in a separate patch. (Is that possible? Or will we need GHC to have loaded all the modules first, before we can go searching for the instances (e.g. if the modules are recursive or something)?) - - - - - 6959b451 by Isaac Dupree at 2009-08-17T00:37:18+00:00 fix preprocessor conditional sense - - - - - 942823af by Isaac Dupree at 2009-08-16T22:46:48+00:00 remove ghc 6.8 conditionals from Haddock.Interface - - - - - 4b3ad888 by Isaac Dupree at 2009-08-18T20:24:38+00:00 Fix GHC 6.11 build in Haddock.Convert - - - - - 0a89c5ab by Isaac Dupree at 2009-08-23T00:08:58+00:00 hacks to make it compile without fnArgDocsn - - - - - 7b3bed43 by Isaac Dupree at 2009-08-23T03:01:28+00:00 less big-Map-based proper extraction of constructor subdocs - - - - - b21c279a by Isaac Dupree at 2009-08-23T03:02:06+00:00 Html: remove unnecessary+troublesome GHC. qualifications - - - - - 96c97115 by Isaac Dupree at 2009-08-23T03:08:03+00:00 Move doc parsing/lexing into Haddock for ghc>=6.11 - - - - - e1cec02d by Isaac Dupree at 2009-08-23T05:08:14+00:00 get rid of unused DocMap parameter in Html - - - - - 66960c59 by Isaac Dupree at 2009-08-23T05:54:20+00:00 fix horrible named-docs-disappearing bug :-) - - - - - a9d7eff3 by Isaac Dupree at 2009-08-23T06:26:36+00:00 re-implement function-argument docs ..on top of the lexParseRn work. This patch doesn't change the InstalledInterface format, and thus, it does not work cross-package, but that will be easy to add subsequently. - - - - - 8bf6852c by Isaac Dupree at 2009-08-23T07:26:05+00:00 cross-package fnArgDocs. WARNING: changes .haddock binary format While breaking the format, I took the opportunity to unrename the DocMap that's saved to disk, because there's really no reason that we want to know what *another* package's favorite place to link a Name to was. (Is that true? Or might we want to know, someday?) Also, I added instance Binary Map in InterfaceFile. It makes the code a little simpler without changing anything of substance. Also it lets us add another Map hidden inside another Map (fnArgsDocs in instDocMap) without having really-convoluted serialization code. Instances are neat! I don't understand why this change to InterfaceFile seemed to subtly break binary compatibility all by itself, but no matter, I'll just roll it into the greater format-changing patch. Done! - - - - - 30115a64 by Isaac Dupree at 2009-08-23T18:22:47+00:00 Improve behavior for unfindable .haddock - - - - - aa364bda by Isaac Dupree at 2009-08-23T18:28:16+00:00 add comment for FnArgsDoc type - - - - - 49b23a99 by Isaac Dupree at 2009-08-23T21:52:48+00:00 bugfix: restore fnArgDocs for type-synonyms - - - - - f65f9467 by Isaac Dupree at 2009-08-23T22:06:55+00:00 Backends.Hoogle: eliminate warnings - - - - - a292d216 by Isaac Dupree at 2009-08-23T22:10:24+00:00 Haddock.Convert: eliminate warnings - - - - - 5546cd20 by Isaac Dupree at 2009-08-23T22:12:31+00:00 Haddock.Interface.Rename: eliminate warnings - - - - - 0a9798b6 by Isaac Dupree at 2009-08-23T22:18:47+00:00 Main.hs: remove ghc<6.9 conditionals - - - - - e8f9867f by Isaac Dupree at 2009-08-23T22:27:46+00:00 Main.hs: eliminate warnings (except for OldException) - - - - - 61c64247 by Isaac Dupree at 2009-08-23T22:41:01+00:00 move get*LibDir code in Main.hs, to +consistent code, -duplication - - - - - 948f1e69 by Isaac Dupree at 2009-08-23T23:14:26+00:00 Main.hs: OldException->Exception: which eliminates warnings - - - - - 3d5d5e03 by Isaac Dupree at 2009-08-23T23:20:11+00:00 GhcUtils: ghc >= 6.10 - - - - - 2771d657 by Isaac Dupree at 2009-08-23T23:21:55+00:00 InterfaceFile: ghc >= 6.10 - - - - - d9f2b9d1 by Isaac Dupree at 2009-08-23T23:22:58+00:00 Types: ghc >= 6.10 - - - - - ca39210e by Isaac Dupree at 2009-08-23T23:23:26+00:00 ModuleTree: ghc >= 6.10 - - - - - 883c4e59 by Isaac Dupree at 2009-08-23T23:24:04+00:00 Backends.DevHelp: ghc >= 6.10 - - - - - 04667df5 by Isaac Dupree at 2009-08-23T23:24:37+00:00 Backends.Html: ghc >= 6.10 - - - - - a9f7f25f by Isaac Dupree at 2009-08-23T23:25:24+00:00 Utils: ghc >= 6.10 - - - - - b7105022 by Isaac Dupree at 2009-08-23T23:37:47+00:00 eliminate haskell98 dependency, following GHC's example It turns out I/we already had, and it was only a matter of deleting it from the cabal file. - - - - - 292e0911 by Isaac Dupree at 2009-08-24T01:22:44+00:00 refactor out subordinatesWithNoDocs dep of inferenced-decls fix - - - - - c2ed46a2 by Isaac Dupree at 2009-08-24T01:24:03+00:00 Eradicate wrong runtime warning for type-inferenced exported-functions see the long comment in the patch for why I did it this way :-) - - - - - 4ac0b57c by David Waern at 2009-09-04T22:56:20+00:00 Clean up tyThingToHsSynSig a little Factor out noLoc and use the case construct. Also rename the function to tyThingToLHsDecl, since it doesn't just create type signatures. - - - - - 28ab9201 by David Waern at 2009-09-04T22:58:50+00:00 Wibble - - - - - 0d9fe6d0 by David Waern at 2009-09-06T18:39:30+00:00 Add more copyright owners to H.I.AttachInstances - - - - - 122441b1 by David Waern at 2009-09-06T18:44:12+00:00 Style police - - - - - 1fa79463 by David Waern at 2009-09-06T18:57:45+00:00 Move toHsInstHead to Haddock.Convert and call it synifyInstHead - - - - - 0d42a8aa by David Waern at 2009-09-06T21:11:38+00:00 Use colordiff to display test results if available - - - - - ea9d8e03 by Simon Marlow at 2009-08-24T08:46:14+00:00 Follow changes in GHC's interface file format Word32 instead of Int for FastString and Name offsets - - - - - 537e051e by Simon Marlow at 2009-07-29T14:16:53+00:00 define unpackPackageId (it was removed from GHC) - - - - - 50c63aa7 by David Waern at 2009-09-09T23:18:03+00:00 Remove commented-out code - - - - - 511631fe by David Waern at 2009-09-09T23:19:05+00:00 Correct copyright in H.I.ParseModuleHeader - - - - - 898ec768 by David Waern at 2009-09-11T11:22:29+00:00 Use Map.fromList/toList intead of fromAscList/toAscList when serializing Maps This fixes the missing docs problem. The Eq and Ord instances for Name uses the unique number in Name. This number is created at deserialization time by GHC's magic Binary instance for Name, and it is random. Thus, fromAscList can't be used at deserialization time, even though toAscList was used at serialization time. - - - - - 37bec0d5 by Simon Peyton Jones at 2009-09-11T08:28:04+00:00 Track change in HsType - - - - - eb3a97c3 by Ian Lynagh at 2009-09-11T16:07:09+00:00 Allow building with base 4.2 - - - - - bb4205ed by Ian Lynagh at 2009-09-22T13:50:02+00:00 Loosen the GHC dependency - - - - - 5c75deb2 by Ian Lynagh at 2009-09-22T14:08:39+00:00 Fix building with GHC >= 6.12 - - - - - fb131481 by David Waern at 2009-09-11T11:24:48+00:00 Update runtests.hs to work with GHC 6.11 - - - - - ac3a419d by David Waern at 2009-09-11T11:25:14+00:00 Update CrossPackageDocs test - - - - - ec65c3c6 by David Waern at 2009-09-11T11:25:40+00:00 Add reference output for CrossPackageDocs - - - - - 520c2758 by Ian Lynagh at 2009-10-25T17:26:40+00:00 Fix installation in the GHC build system - - - - - 28b3d7df by Ian Lynagh at 2009-11-05T15:57:27+00:00 GHC build system: Make *nix installation work in paths containing spaces - - - - - 5c9bb541 by David Waern at 2009-11-14T11:56:39+00:00 Track change in HsType for the right compiler version - - - - - 905097ce by David Waern at 2009-11-14T12:10:47+00:00 hlint police - - - - - 04920630 by Ian Lynagh at 2009-11-20T13:46:30+00:00 Use defaultObjectTarget rather than HscAsm This fixes haddock when we don't have a native code generator - - - - - 966eb079 by David Waern at 2009-11-15T12:32:21+00:00 Remove commented-out code - - - - - 37f00fc4 by David Waern at 2009-11-22T13:58:48+00:00 Make runtests.hs strip links before diffing Generates easier to read diffs when tests fail. The content of the links is not important anyway since it is not taken into account by the tests. - - - - - 3a9bb8ef by David Waern at 2009-11-22T14:05:06+00:00 Follow findProgramOnPath signature change in runtests.hs - - - - - b26b9e5a by David Waern at 2009-11-22T14:08:40+00:00 Follow removal of GHC.MVar from base in CrossPackageDocs - - - - - f4d90ae4 by David Waern at 2009-11-22T14:48:47+00:00 Make copy.hs strip link contents before copying No more updating of reference files when URLs in links changes. - - - - - 4c9c420d by David Waern at 2009-11-22T15:26:41+00:00 Update test reference output * More links (Int, Float etc) * Stripped link contents - - - - - a62b80e3 by David Waern at 2009-11-23T23:19:39+00:00 Update CrossPackageDocs reference output - Remove GHC.MVar import (removed from base) - Strip link contents - - - - - 43491394 by David Waern at 2009-11-23T23:20:00+00:00 Update test reference files with comments on instances - - - - - 0d370a0b by David Waern at 2009-11-23T23:25:16+00:00 Bump version number - - - - - 2293113e by David Waern at 2009-11-24T20:55:49+00:00 Comments on instances Implementing this was a little trickier than I thought, since we need to match up instances from the renamed syntax with instances represented by InstEnv.Instance. This is due to the current design of Haddock, which matches comments with declarations from the renamed syntax, while getting the list of instances of a class/family directly using the GHC API. - Works for class instances only (Haddock has no support for type family instances yet) - The comments are rendered to the right of the instance head in the HTML output - No change to the .haddock file format - Works for normal user-written instances only. No comments are added on derived or TH-generated instances - - - - - bf586f29 by David Waern at 2009-11-27T22:05:15+00:00 Whitespace police - - - - - b8f03afa by David Waern at 2009-11-27T22:11:46+00:00 Remove bad whitespace and commented-out pieces - - - - - 90b8ee90 by David Waern at 2009-11-27T22:15:04+00:00 Whitespace police - - - - - b5ede900 by David Waern at 2009-11-27T22:15:50+00:00 Whitespace police - - - - - e3fddbfe by David Waern at 2009-11-28T13:37:59+00:00 Remove Name from DocInstance It's not used. - - - - - 9502786c by David Waern at 2009-11-28T13:56:54+00:00 Require at least GHC 6.12 While regression testing Haddock, I found a bug that happens with GHC 6.10.3, but not with GHC 6.12-rc2 (haven't tried 6.10.4). I don't have time to track it down. I think we should just always require the latest major GHC version. The time spent on making Haddock work with older versions is too high compared to the time spent on bugfixing, refactoring and features. - - - - - 8fa688d8 by David Waern at 2009-11-28T15:05:03+00:00 Remove cruft due to compatibility with older GHCs - - - - - 46fbbe9d by David Waern at 2009-11-28T15:07:50+00:00 Add a documentation header to Haddock.Convert - - - - - c3d2cc4a by David Waern at 2009-11-28T15:10:14+00:00 Remove unused H.Utils.FastMutInt2 - - - - - 490aba80 by David Waern at 2009-11-28T15:36:36+00:00 Rename Distribution.Haddock into Documentation.Haddock - - - - - 33ee2397 by David Waern at 2009-11-28T15:36:47+00:00 Fix error message - - - - - a5a3b950 by David Waern at 2009-11-28T16:58:39+00:00 Add a test flag that brings in QuickCheck - - - - - fa049e13 by David Waern at 2009-11-28T19:32:18+00:00 Say that we want quickcheck 2 - - - - - f32b0d9b by David Waern at 2009-11-28T19:32:40+00:00 Add an Arbitrary instance for HsDoc - - - - - da9a8bd7 by David Waern at 2009-11-28T20:15:30+00:00 Rename HsDoc back into Doc - - - - - edb60101 by David Waern at 2009-11-28T22:16:16+00:00 Move H.Interface.Parse/Lex to H.Parse/Lex These are not just used to build Interfaces. - - - - - 0656a9b8 by David Waern at 2009-11-28T23:12:14+00:00 Update version number in test suite - - - - - 5e8c6f4a by David Waern at 2009-12-21T14:12:41+00:00 Improve doc of DocName - - - - - 7868e551 by Ian Lynagh at 2009-09-22T10:43:03+00:00 TAG GHC 6.12-branch created - - - - - 0452a3ea by Ian Lynagh at 2009-12-15T12:46:07+00:00 TAG GHC 6.12.1 release - - - - - 65e9be62 by David Waern at 2009-12-21T16:58:58+00:00 Update CHANGES - - - - - 145cee32 by David Waern at 2009-12-21T16:59:09+00:00 TAG 2.6.0 - - - - - 3c552008 by David Waern at 2009-12-22T17:11:14+00:00 Update ANNOUNCE - - - - - 931f9db4 by David Waern at 2010-01-22T19:57:17+00:00 Convert haddock.vim to use unix newlines - - - - - 4e56588f by David Waern at 2010-01-22T22:11:17+00:00 Remove unnecessary (and inexplicable) uses of nub - - - - - 744bb4d1 by David Waern at 2010-01-22T22:12:14+00:00 Follow move of parser and lexer - - - - - e34bab14 by David Waern at 2010-01-22T22:49:13+00:00 Use findProgramLocation instead of findProgramOnPath in runtests.hs - - - - - 8d39891b by Isaac Dupree at 2010-01-14T18:53:18+00:00 fix html arg-doc off-by-one and silliness - - - - - 9401f2e9 by David Waern at 2010-01-22T22:57:03+00:00 Create a test for function argument docs - - - - - 507a82d7 by David Waern at 2010-01-22T23:24:47+00:00 Put parenthesis around type signature arguments of function type - - - - - 8a305c28 by David Waern at 2010-01-23T17:26:59+00:00 Add reference file for the FunArgs test - - - - - 1309d5e1 by David Waern at 2010-01-24T16:05:08+00:00 Improve FunArg test and update Test.html.ref - - - - - 2990f055 by Yitzchak Gale at 2010-02-14T16:03:46+00:00 Do not generate illegal character in HTML ID attribute. - - - - - c5bcab7a by David Waern at 2010-02-22T22:10:30+00:00 Fix Haddock markup error in comment - - - - - c6416a73 by David Waern at 2010-02-24T22:55:08+00:00 Large additions to the Haddock API Also improved and added more doc comments. - - - - - 57d289d7 by David Waern at 2010-02-24T22:58:02+00:00 Remove unused ifaceLocals - - - - - 80528d93 by David Waern at 2010-02-25T21:05:09+00:00 Add HaddockModInfo to the API - - - - - 82806848 by David Waern at 2010-02-25T21:05:27+00:00 Wibble - - - - - 744cad4c by David Waern at 2010-02-25T23:30:59+00:00 Make it possible to run a single test - - - - - 6a806e4c by David Waern at 2010-03-14T14:19:39+00:00 Bump version number - - - - - a5a8e4a7 by David Waern at 2010-03-14T14:36:35+00:00 Update ANNOUNCE - - - - - 6f05435e by Simon Hengel at 2010-03-15T20:52:42+00:00 Add missing dependencies for 'library' in haddock.cabal - - - - - faefe2bd by David Waern at 2010-03-15T22:29:37+00:00 Solve conflicts - - - - - 9808ad52 by David Waern at 2010-03-15T22:51:21+00:00 Bump version number - - - - - eb0bf60b by David Waern at 2010-03-15T22:52:32+00:00 Update CHANGES - - - - - f95cd891 by David Waern at 2010-03-15T23:01:06+00:00 Add Paths_haddock to other-modules of library - - - - - 65997b0a by David Waern at 2010-03-15T23:14:59+00:00 Update CHANGES - - - - - 7e251731 by David Waern at 2010-03-15T23:15:30+00:00 Bump version number - - - - - c9cd0ddc by David Waern at 2010-03-16T00:28:34+00:00 Fix warning - - - - - 1cac2d93 by Simon Peyton Jones at 2010-01-04T15:22:16+00:00 Fix imports for new location of splitKindFunTys - - - - - 474f26f6 by Simon Peyton Jones at 2010-02-10T14:36:06+00:00 Update Haddock for quasiquotes - - - - - 0dcc06c0 by Simon Peyton Jones at 2010-02-10T10:59:45+00:00 Track changes in HsTyVarBndr - - - - - 2d84733a by Simon Peyton Jones at 2010-02-10T14:52:44+00:00 Track HsSyn chnages - - - - - 9e3adb8b by Ian Lynagh at 2010-02-20T17:09:42+00:00 Resolve conflicts - - - - - a3e72ff8 by Simon Peyton Jones at 2010-03-04T13:05:16+00:00 Track change in HsUtils; and use a nicer function not an internal one - - - - - 27994854 by David Waern at 2010-03-18T22:22:27+00:00 Fix build with GHC 6.12.1 - - - - - 11f6e488 by David Waern at 2010-03-18T22:24:09+00:00 Bump version in test reference files - - - - - 0ef2f11b by David Waern at 2010-03-20T00:56:30+00:00 Fix library part of cabal file when in ghc tree - - - - - 3f6146ff by Mark Lentczner at 2010-03-20T22:30:11+00:00 First, experimental XHTML rendering switch to using the xhtml package copied Html.hs to Xhtml.hs and split into sub-modules under Haddock/Backends/Xhtml and detabify moved footer into div, got ready for iface change headers converted to semantic markup contents in semantic markup summary as semantic markup description in semantic markup, info block in header fixed factored out rendering so during debug it can be readable (see renderToString) - - - - - b8ab329b by Mark Lentczner at 2010-03-20T22:54:01+00:00 apply changes to Html.hs to Xhtml/*.hs incorporate changes that were made between the time Html.hs was copied and split into Xhtml.hs and Xhtml/*.hs includes patchs after "Wibble" (!) through "Fix build with GHC 6.12.1" - - - - - 73df2433 by Ian Lynagh at 2010-03-20T21:56:37+00:00 Follow LazyUniqFM->UniqFM in GHC - - - - - db4f602b by David Waern at 2010-03-29T22:00:01+00:00 Fix build with GHC 6.12 - - - - - d8dca088 by Simon Hengel at 2010-04-02T16:39:55+00:00 Add missing dependencies to cabal file - - - - - e2adc437 by Simon Hengel at 2010-04-02T14:08:40+00:00 Add markup support for interactive examples - - - - - e882ac05 by Simon Hengel at 2010-04-02T14:11:53+00:00 Add tests for interactive examples - - - - - 5a07a6d3 by David Waern at 2010-04-07T17:05:20+00:00 Propagate source positions from Lex.x to Parse.y - - - - - 6493b46f by David Waern at 2010-04-07T21:48:57+00:00 Let runtests.hs die when haddock has not been built - - - - - 5e34423e by David Waern at 2010-04-07T22:01:13+00:00 Make runtests.hs slightly more readable - - - - - 321d59b3 by David Waern at 2010-04-07T22:13:27+00:00 Fix haskell/haddock#75 Add colons to the $ident character set. - - - - - 37b08b8d by David Waern at 2010-04-08T00:32:52+00:00 Fix haskell/haddock#118 Avoid being too greedy when lexing URL markup (<..>), in order to allow multiple URLs on the same line. Do the same thing with <<..>> and #..#. - - - - - df8feac9 by David Waern at 2010-04-08T00:57:33+00:00 Make it easier to add new package deps to test suite This is a hack - we should use Cabal to get the package details instead. - - - - - 1ca6f84b by David Waern at 2010-04-08T01:03:06+00:00 Add ghc-prim to test suite deps - - - - - 27371e3a by Simon Hengel at 2010-04-08T19:26:34+00:00 Let parsing fails on paragraphs that are immediately followed by an example This is more consistent with the way we treat code blocks. - - - - - 83096e4a by David Waern at 2010-04-08T21:20:00+00:00 Improve function name - - - - - 439983ce by David Waern at 2010-04-10T10:46:14+00:00 Fix haskell/haddock#112 No link was generated for 'Addr#' in a doc comment. The reason was simply that the identifier didn't parse. We were using parseIdentifier from the GHC API, with a parser state built from 'defaultDynFlags'. If we pass the dynflags of the module instead, the right options are turned on on while parsing the identifer (in this case -XMagicHash), and the parse succeeds. - - - - - 5c0d35d7 by David Waern at 2010-04-10T10:54:06+00:00 Rename startGhc into withGhc - - - - - dca081fa by Simon Hengel at 2010-04-12T19:09:16+00:00 Add documentation for interactive examples - - - - - c7f26bfa by David Waern at 2010-04-13T00:51:51+00:00 Slight fix to the documentation of examples - - - - - 06eb7c4c by David Waern at 2010-04-13T00:57:05+00:00 Rename Interactive Examples into Examples (and simplify explanation) - - - - - 264830cb by David Waern at 2010-05-10T20:07:27+00:00 Update CHANGES with info about 2.6.1 - - - - - 8e5d4514 by Simon Hengel at 2010-04-18T18:16:54+00:00 Add unit tests for parser - - - - - 68297f40 by David Waern at 2010-05-10T21:53:37+00:00 Improve testsuite README - - - - - f04eb6e4 by David Waern at 2010-05-11T19:14:31+00:00 Re-organise the testsuite structure - - - - - a360f710 by David Waern at 2010-05-11T19:18:03+00:00 Shorten function name - - - - - 1d5dd359 by David Waern at 2010-05-11T21:40:02+00:00 Update runtests.hs following testsuite re-organisation - - - - - ffebe217 by David Waern at 2010-05-11T21:40:10+00:00 Update runtests.hs to use base-4.2.0.1 - - - - - 635de402 by David Waern at 2010-05-11T21:41:11+00:00 Update runparsetests.hs following testsuite reorganisation - - - - - 72137910 by Ian Lynagh at 2010-05-06T20:43:06+00:00 Fix build - - - - - 1a80b76e by Ian Lynagh at 2010-05-06T22:25:29+00:00 Remove redundant import - - - - - 1031a80c by Simon Peyton Jones at 2010-05-07T13:21:09+00:00 Minor wibbles to HsBang stuff - - - - - dd8e7fe5 by Ian Lynagh at 2010-05-08T15:22:00+00:00 GHC build system: Follow "rm" variable changes - - - - - 7f5e6748 by David Waern at 2010-05-13T11:53:02+00:00 Fix build with GHC 6.12.2 - - - - - 7953d4d8 by David Waern at 2010-05-13T18:45:01+00:00 Fixes to comments only - - - - - 8ae8eb64 by David Waern at 2010-05-13T18:57:26+00:00 ModuleMap -> IfaceMap - - - - - 1c3eadc6 by David Waern at 2010-05-13T19:03:13+00:00 Fix whitespace style issues - - - - - e96783c0 by David Waern at 2010-05-13T19:08:53+00:00 Fix comment - - - - - c998a78b by David Waern at 2010-05-13T19:39:00+00:00 Position the module header the same way everywhere Silly, but nice with some consistency :-) - - - - - b48a714e by David Waern at 2010-05-13T19:41:32+00:00 Position of module header, this time in the HTML backends - - - - - f9bfb12e by David Waern at 2010-05-13T19:43:05+00:00 Two newlines between declarations in Main - - - - - 071d44c7 by David Waern at 2010-05-13T19:44:21+00:00 Newlines in Convert - - - - - 036346db by David Waern at 2010-05-13T19:46:47+00:00 Fix a few stylistic issues in H.InterfaceFile - - - - - f0b8379e by David Waern at 2010-05-13T19:47:53+00:00 Add newlines to H.ModuleTree - - - - - 27409f8e by David Waern at 2010-05-13T19:51:10+00:00 Fix stylistic issues in H.Utils - - - - - 24774a11 by David Waern at 2010-05-13T20:00:43+00:00 Structure H.Types better - - - - - 7b6f5e40 by David Waern at 2010-05-13T20:01:04+00:00 Remove bad Arbitrary instance - - - - - fac9f1f6 by David Waern at 2010-05-13T20:05:50+00:00 Get rid of H.Utils.pathJoin and use System.FilePath.joinPath instead - - - - - fe6d00c4 by David Waern at 2010-05-13T20:51:55+00:00 Export a couple of more types from the API - - - - - b2e33a5f by David Waern at 2010-05-13T21:27:51+00:00 Improve doc comment for Interface - - - - - c585f2ce by David Waern at 2010-05-13T21:30:14+00:00 Improve documentation of Haddock.Interface - - - - - e6791db2 by David Waern at 2010-05-13T22:07:35+00:00 Remove meaningless comments - - - - - 7801b390 by David Waern at 2010-05-14T17:53:33+00:00 Remove unused modules - - - - - f813e937 by David Waern at 2010-05-14T17:55:17+00:00 Re-direct compilation output to a temporary directory Also add a flag --no-tmp-comp-dir that can be used to get the old behaviour of writing compilation files to GHC's output directory (default "."). - - - - - e56737ec by David Waern at 2010-05-14T18:06:11+00:00 Wibble - - - - - e40b0447 by David Waern at 2010-05-14T19:01:52+00:00 Move flag evaluation code from Main to Haddock.Options Determining the value of "singular" flags (by e.g. taking the last occurrence of the flag) and other flag evaluation should done in Haddock.Options which is the module that is supposed to define the command line interface. This makes Main a bit easier on the eyes as well. - - - - - 27091f57 by David Waern at 2010-05-14T19:05:10+00:00 Wibble - - - - - c658cf61 by David Waern at 2010-05-14T19:06:49+00:00 Re-order things in Haddock.Options a bit - - - - - 8cfdd342 by David Waern at 2010-05-14T19:20:29+00:00 De-tabify Haddock.Options and fix other whitespace issues - - - - - 0df16b62 by David Waern at 2010-05-14T19:25:07+00:00 Improve comments - - - - - 80b38e2b by David Waern at 2010-05-14T19:26:42+00:00 Whitespace police - - - - - fe580255 by David Waern at 2010-05-14T19:31:23+00:00 Wibbles to comments - - - - - a2b43fad by David Waern at 2010-05-14T20:24:32+00:00 Move some more flag functions to Haddock.Options - - - - - 3f895547 by David Waern at 2010-05-14T20:37:12+00:00 Make renderStep a top-level function in Main - - - - - 5cdca11d by David Waern at 2010-05-14T20:39:27+00:00 Spelling in comment - - - - - ad98d14c by David Waern at 2010-05-14T20:40:26+00:00 Comment fixes - - - - - 0bb9218f by David Waern at 2010-05-14T20:49:01+00:00 Whitespace police - - - - - 0f0a533f by David Waern at 2010-05-15T16:42:29+00:00 Improve description of --dump-interface - - - - - 5b2833ac by David Waern at 2010-05-15T17:16:53+00:00 Document --no-tmp-comp-dir - - - - - 8160b170 by David Waern at 2010-05-15T17:18:59+00:00 Wibble - - - - - 570dbe33 by David Waern at 2010-05-18T21:15:38+00:00 HLint police - - - - - 204e425f by David Waern at 2010-05-18T21:16:30+00:00 HLint police - - - - - 6db657ac by David Waern at 2010-05-18T21:16:37+00:00 Wibble - - - - - b942ccd7 by Simon Marlow at 2010-06-02T08:27:30+00:00 Interrupted disappeared in GHC 6.13 (GHC ticket haskell/haddock#4100) - - - - - 3b94a819 by Simon Marlow at 2010-06-02T08:45:08+00:00 Allow base-4.3 - - - - - c5a1fb7c by Simon Marlow at 2010-06-02T09:03:04+00:00 Fix compilation with GHC 6.13 - - - - - 6181296c by David Waern at 2010-06-08T21:09:05+00:00 Display name of prologue file when parsing it fails - - - - - 7cbc6f60 by Ian Lynagh at 2010-06-13T16:20:25+00:00 Remove redundant imports - - - - - 980c804b by Simon Marlow at 2010-06-22T08:41:50+00:00 isLocalAndTypeInferenced: fix for local module names overlapping package modules - - - - - d74d4a12 by Simon Marlow at 2010-06-23T12:03:27+00:00 Unresolved identifiers in Doc get replaced with DocMonospaced rather than plain strings - - - - - d8546783 by Simon Marlow at 2010-06-30T12:45:17+00:00 LaTeX backend (new options: --latex, --latex-style=<style>) - - - - - 437afa9e by David Waern at 2010-07-01T12:02:44+00:00 Fix a few stylistic whitespace issues in LaTeX backend - - - - - 85bc1fae by David Waern at 2010-07-01T15:42:45+00:00 Make runtest.hs work with GHC 6.12.3 (we should really stop hard coding this) - - - - - 7d2eb86f by David Waern at 2010-07-01T15:43:33+00:00 Update test following Simon's patch to render unresolved names in monospaced font - - - - - 08fcbcd2 by David Waern at 2010-07-01T16:12:18+00:00 Warning police - - - - - d04a8d7a by David Waern at 2010-07-04T14:53:39+00:00 Fix a bug in attachInstances We didn't look for instance docs in all the interfaces of the package. This had the effect of instance docs not always showing up under a declaration. I took the opportunity to clean up the code in H.I.AttachInstances a bit as well. More cleanup is needed, however. - - - - - d10344eb by Simon Hengel at 2010-07-10T09:19:04+00:00 Add missing dependencies to cabal file - - - - - 24090531 by Mark Lentczner at 2010-03-21T04:51:16+00:00 add exports to Xhtml modules - - - - - 84f9a333 by Mark Lentczner at 2010-04-03T19:14:22+00:00 clean up Doc formatting code - add CSS for lists - renderToString now uses showHtml since prettyHtml messes up <pre> sections - - - - - bebccf52 by Mark Lentczner at 2010-04-04T04:51:08+00:00 tweak list css - - - - - 0c2aeb5e by Mark Lentczner at 2010-04-04T06:24:14+00:00 all decls now generate Html not HtmlTable - ppDecl return Html, and so now do all of the functions it calls - added some internal tables to some decls, which is wrong, and will have to be fixed - decl "Box" functions became "Elem" functions to make clear they aren't in a table anymore (see Layout.hs) - docBox went away, as only used in one place (and its days are numbered) - cleaned up logic in a number of places, removed dead code - added maybeDocToHtml which simplified a number of places in the code - - - - - dbf73e6e by Mark Lentczner at 2010-04-05T05:02:43+00:00 clean up processExport and place a div around each decl - - - - - e25b7e9f by Mark Lentczner at 2010-04-10T21:23:21+00:00 data decls are now a sequence of paragraphs, not a table - - - - - 89ee0294 by Mark Lentczner at 2010-04-10T21:29:16+00:00 removed commented out code that can't be maintained - - - - - d466f536 by Mark Lentczner at 2010-04-12T04:56:27+00:00 removed declWithDoc and cleaned up data decls in summary - - - - - ed755832 by Mark Lentczner at 2010-04-12T05:07:53+00:00 merge in markupExample changes - - - - - c36f51fd by Mark Lentczner at 2010-04-25T04:56:37+00:00 made record fields be an unordList, not a table - - - - - ed3a28d6 by Mark Lentczner at 2010-04-25T05:23:28+00:00 fixed surround of instance and constructor tables - - - - - 0e35bbc4 by Mark Lentczner at 2010-04-25T05:36:59+00:00 fix class member boxes in summary - - - - - 5041749b by Mark Lentczner at 2010-04-25T05:38:35+00:00 remove unused bodyBox - - - - - e91724db by Mark Lentczner at 2010-04-25T06:26:10+00:00 fixed javascript quoting/escpaing issue - - - - - f4abbb73 by Mark Lentczner at 2010-05-03T23:04:31+00:00 adjust css for current markup - - - - - e75fec4c by Mark Lentczner at 2010-05-04T06:14:34+00:00 added assoicated types and methods back into class decls - - - - - 84169323 by Mark Lentczner at 2010-05-24T13:13:42+00:00 merge in changes from the big-whitespace cleanup - - - - - 3c1c872e by Mark Lentczner at 2010-06-11T21:03:58+00:00 adjust synopsis and bottom bar spacing - - - - - 3c1f9ef7 by Mark Lentczner at 2010-06-11T21:14:44+00:00 fix missing space in "module" lines in synoposis - - - - - 9a137e6d by Mark Lentczner at 2010-06-11T21:34:08+00:00 changed tt elements to code elements - - - - - 50f71ef1 by Mark Lentczner at 2010-06-11T23:27:46+00:00 factored out ppInstances - - - - - 3b9a9de5 by Mark Lentczner at 2010-06-17T17:36:01+00:00 push single constructors (newtype) onto line with decl - - - - - e0f8f2ec by Mark Lentczner at 2010-06-17T22:20:56+00:00 remove <++> connector - - - - - 56c075dd by Mark Lentczner at 2010-07-13T05:26:21+00:00 change to new page structure - - - - - 04be6ca7 by Mark Lentczner at 2010-07-14T04:21:55+00:00 constructors and args as dl lists, built in Layout.hs - - - - - 65aeafc2 by Mark Lentczner at 2010-07-14T05:38:32+00:00 better interface to subDecls - - - - - 72032189 by Mark Lentczner at 2010-07-14T07:04:10+00:00 made subDecl tables looks just so - - - - - b782eca2 by Mark Lentczner at 2010-07-14T16:00:54+00:00 convert args to SubDecl format - - - - - cc75e98f by Mark Lentczner at 2010-07-14T16:28:53+00:00 convert instances to SubDecl - - - - - 34e2aa5a by Mark Lentczner at 2010-07-14T21:07:32+00:00 removing old table cruft from Layout.hs - - - - - d5810d95 by Mark Lentczner at 2010-07-14T21:54:58+00:00 methods and associated types in new layout scheme - - - - - 65ef9579 by Mark Lentczner at 2010-07-14T23:43:42+00:00 clean up synopsis lists - - - - - e523318f by Mark Lentczner at 2010-07-15T05:02:26+00:00 clean up of anchors - - - - - 1215dfc5 by Mark Lentczner at 2010-07-15T23:53:01+00:00 added two new themes and rough css switcher - - - - - 7f0fd36f by Mark Lentczner at 2010-07-16T04:57:38+00:00 fixed package catpion, added style menu - - - - - 0dd4999c by Mark Lentczner at 2010-07-16T20:12:39+00:00 new output for mini_ pages - - - - - 64b2810b by Mark Lentczner at 2010-07-16T20:58:41+00:00 reformat index-frames - - - - - 3173f555 by Mark Lentczner at 2010-07-16T22:41:53+00:00 convert index to new markup - - - - - b0a4b7c9 by Mark Lentczner at 2010-07-17T04:07:22+00:00 convert index.html to new markup, adjust module markup - - - - - 8261ae1e by Mark Lentczner at 2010-07-17T05:07:29+00:00 classing styling of ancillary pages - - - - - 2a4fb025 by Mark Lentczner at 2010-07-17T05:11:45+00:00 clean up Layout.hs: no more vanillaTable - - - - - 87eec685 by Mark Lentczner at 2010-07-17T05:35:16+00:00 clean up Util.hs - - - - - d304e9b0 by Mark Lentczner at 2010-07-17T05:38:50+00:00 qualify import of XHtml as XHtml - - - - - 7dc05807 by Mark Lentczner at 2010-07-17T06:17:53+00:00 factored out head element generation - - - - - 9cdaec9e by Mark Lentczner at 2010-07-17T06:44:54+00:00 refactored out main page body generation - - - - - 8a51019e by Mark Lentczner at 2010-07-17T06:48:20+00:00 moved footer into only place that used it - - - - - efa479da by Mark Lentczner at 2010-07-17T18:48:30+00:00 styling auxillary pages for tibbe and snappy themes - - - - - 81de5509 by Mark Lentczner at 2010-07-18T04:41:38+00:00 fixed alphabet on index page, and styling of it and packages in module lists - - - - - 20718c1a by Mark Lentczner at 2010-07-18T05:34:29+00:00 cleaned up div functions in Layout.hs - - - - - 60d50453 by Mark Lentczner at 2010-07-18T05:48:39+00:00 added content div to main pages - - - - - ed16561c by Mark Lentczner at 2010-07-18T06:12:22+00:00 add .doc class to documentation blocks - - - - - f5c781b0 by Mark Lentczner at 2010-07-19T05:20:53+00:00 refactoring of anchor ID and fragment handling - - - - - a69a93bf by Mark Lentczner at 2010-07-19T05:35:55+00:00 remove an explicit bold tag - replace with .def class - - - - - d76c7225 by Mark Lentczner at 2010-07-19T06:56:15+00:00 rename Haddock.Backends.Xhtml.Util to Utils - - - - - 5a58c0da by David Waern at 2010-07-21T13:30:54+00:00 Remove trailing whitespace in Haddock.Backends.Xhtml - - - - - 0652aa17 by David Waern at 2010-07-21T13:33:21+00:00 Align a few comments - - - - - 785776c3 by David Waern at 2010-07-21T13:39:04+00:00 Remove trailing whitespace in H.B.X.Decl - - - - - 71a30710 by David Waern at 2010-07-21T13:44:27+00:00 Remove more trailing whitespace - - - - - 38750394 by David Waern at 2010-07-21T13:50:43+00:00 Style police - - - - - 3023d940 by David Waern at 2010-07-21T14:01:22+00:00 Style police in H.B.X.Decl - - - - - df16e9e6 by David Waern at 2010-07-21T14:14:45+00:00 Style police in H.B.X.DocMarkup - - - - - 6020e321 by David Waern at 2010-07-21T14:17:32+00:00 More style police - - - - - 86ad8bf5 by David Waern at 2010-07-21T14:21:02+00:00 Style police in H.B.Xhtml - - - - - aea27d03 by David Waern at 2010-07-21T14:42:03+00:00 Fix warnings in LaTeX backend - - - - - 2aff34a9 by David Waern at 2010-07-21T14:50:46+00:00 Style police in LaTeX backend (mainly more newlines) - - - - - e517162d by David Waern at 2010-07-21T15:05:47+00:00 Doc sections in Main - - - - - b971aa0c by David Waern at 2010-07-21T15:06:17+00:00 Trailing whitespace in Documentation.Haddock - - - - - f11628fb by David Waern at 2010-07-21T15:07:06+00:00 Trailing whitespace in Haddock.Convert - - - - - cbaf284c by David Waern at 2010-07-21T15:08:11+00:00 Style police in Haddock.GhcUtils - - - - - 71feb77b by David Waern at 2010-07-21T15:09:06+00:00 Style police in Haddock.InterfaceFile - - - - - 0a9c80e6 by David Waern at 2010-07-21T15:11:33+00:00 Whitespace police - - - - - 6168376c by David Waern at 2010-07-21T15:16:35+00:00 Style police in Haddock.Utils - - - - - 9fe4dd90 by David Waern at 2010-07-21T15:19:31+00:00 Add -fwarn-tabs - - - - - a000d752 by Mark Lentczner at 2010-07-20T17:25:52+00:00 move CSS Theme functions into Themes.hs - - - - - b52b440f by Mark Lentczner at 2010-07-20T17:29:35+00:00 add Thomas Schilling's theme - - - - - e43fa7e8 by Mark Lentczner at 2010-07-21T04:49:34+00:00 correct icon used with Snappy theme - - - - - ba5092d3 by Mark Lentczner at 2010-07-21T04:56:47+00:00 apply Tibbe's updates to his theme - - - - - 7804eef6 by Mark Lentczner at 2010-07-21T05:15:49+00:00 space between "Style" and the downward triangle - - - - - 7131d4c6 by Mark Lentczner at 2010-07-21T17:43:35+00:00 merge with David's source cleanups - - - - - ee65f1cb by David Waern at 2010-07-22T16:50:46+00:00 Fix a bug where we allowed --hoogle, --latex, etc without input files - - - - - e413ff7a by David Waern at 2010-07-22T17:21:58+00:00 Improve function name - - - - - a0fd14f3 by Simon Marlow at 2010-06-30T15:34:32+00:00 fix warnings - - - - - 31f73d2a by David Waern at 2010-07-22T19:29:41+00:00 Solve conflicts - - - - - d563b4a5 by Simon Marlow at 2010-06-30T15:34:37+00:00 fix warning - - - - - 412b6469 by David Waern at 2010-07-22T19:31:28+00:00 Solve conflict - - - - - 35174b94 by Ian Lynagh at 2010-07-06T17:27:16+00:00 Follow mkPState argument order change - - - - - b5c3585c by Simon Marlow at 2010-07-14T08:49:21+00:00 common up code for instance rendering - - - - - d8009560 by Simon Marlow at 2010-07-14T12:37:11+00:00 fix warnings - - - - - a6d88695 by David Waern at 2010-07-24T15:33:33+00:00 Fix build with ghc < 6.13 - - - - - 94cf9de1 by David Waern at 2010-07-24T15:34:37+00:00 Remove conflict left-over - - - - - 313b15c0 by Mark Lentczner at 2010-07-21T22:09:04+00:00 reorganization of nhaddock.css with tibbe - - - - - 9defed80 by Mark Lentczner at 2010-07-21T22:42:14+00:00 further cleanup of nhaddock.css, float TOC, support aux. pages - - - - - 6d944c1b by Mark Lentczner at 2010-07-22T06:22:23+00:00 remove old HTML backend - - - - - b3e8cba5 by Mark Lentczner at 2010-07-22T06:43:32+00:00 remove --html-help support - it was old, out-of-date, and mostly missing - - - - - d2654a08 by Mark Lentczner at 2010-07-22T21:45:34+00:00 tweaks to nhaddock.css - - - - - f73b285c by Mark Lentczner at 2010-07-23T06:19:35+00:00 command like processing for theme selection The bulk of the change is threadnig the selected theme set through functions in Xhtml.hs so that the selected themes can be used when generating the page output. There isn't much going on in most of these changes, just passing it along. The real work is all done in Themes.hs. - - - - - 8bddc90d by Mark Lentczner at 2010-07-23T06:58:31+00:00 drop --themes support, add named theme support decided that --themes was silly - no one would do that, just use multiple --theme arguments made --theme a synonym for --css and -c made those arguments, if no file is found, look up the argument as the name of a built in theme all of this let's haddock be invoked with "--theme=classic" for example. - - - - - 20cafd4f by Mark Lentczner at 2010-07-23T17:44:29+00:00 rename --default-themes to --built-in-themes - - - - - 0fe41307 by Mark Lentczner at 2010-07-23T18:33:02+00:00 tweaks to theme for info table, headings, and tables - - - - - cba4fee0 by Mark Lentczner at 2010-07-23T19:13:59+00:00 tweaks for dl layout, though still not used - - - - - 463fa294 by Mark Lentczner at 2010-07-23T21:07:19+00:00 tweak look of mini pages, keywords, and preblocks - - - - - 5472fc02 by Mark Lentczner at 2010-07-24T05:36:15+00:00 slide out Synopsis drawer - - - - - 9d5d5de5 by Mark Lentczner at 2010-07-24T06:02:42+00:00 extend package header and footer to edges of page - - - - - a47c91a2 by Mark Lentczner at 2010-07-24T06:28:44+00:00 fields are def lists, tweak css for style menu, mini pages, arguments - - - - - ca20f23b by Mark Lentczner at 2010-07-24T16:55:22+00:00 excisting last vestiges of the --xhtml flag - - - - - 71fb012e by Mark Lentczner at 2010-07-25T18:47:49+00:00 change how collapsing sections are done make whole .caption be the target improve javascript for class toggling have plus/minus images come from .css, not img tags - - - - - c168c8d3 by Mark Lentczner at 2010-07-26T00:32:05+00:00 reorganize files in the html lib data dir - - - - - 93324301 by Mark Lentczner at 2010-07-26T01:27:42+00:00 cleaned up Themes.hs - - - - - ad3b5dd4 by Mark Lentczner at 2010-07-26T02:39:15+00:00 make module list use new collapsers - - - - - 1df9bfc6 by Mark Lentczner at 2010-07-27T19:09:25+00:00 remove Tibbe theme - - - - - 8b9b01b3 by Mark Lentczner at 2010-07-27T20:04:03+00:00 move themes into html dir with .theme and .std-theme extensions - - - - - a7beb965 by Mark Lentczner at 2010-07-27T21:06:34+00:00 give a class to empty dd elements so they can be hidden - - - - - a258c117 by Mark Lentczner at 2010-07-27T21:23:58+00:00 remove custom version of copyFile in Xhtml.hs - - - - - b70dba6e by Mark Lentczner at 2010-07-27T22:12:45+00:00 apply margin changes to pre and headings as per group decision, and small cleanups - - - - - e6f722a2 by Mark Lentczner at 2010-07-28T00:03:12+00:00 make info block and package bar links be floatable by placing them first in the dom tree - - - - - c8278867 by Mark Lentczner at 2010-07-28T19:01:18+00:00 styling source links on declarations - - - - - 88fdc399 by Mark Lentczner at 2010-07-29T01:12:46+00:00 styling tweaks don't generate an empty li for absent style menu in links area update css for Classic and Snappy to handle: dl lists links in package header and in declarations floating of links and info block in package and module headers - - - - - 8a75b213 by Ian Lynagh at 2010-07-30T20:21:46+00:00 Fix build in GHC tree - - - - - ce8e18b3 by Simon Hengel at 2010-08-03T18:37:26+00:00 Adapt paths to data files in cabal file - - - - - 9701a455 by Simon Hengel at 2010-08-07T13:20:27+00:00 Add missing dependency to cabal file - - - - - 01b838d1 by Mark Lentczner at 2010-07-30T20:19:40+00:00 improved synopsis drawer: on click, not hover - - - - - 7b6f3e59 by Mark Lentczner at 2010-07-30T23:38:55+00:00 put the synopsis back in the other themes - - - - - 7b2904c9 by Mark Lentczner at 2010-08-11T11:11:26+00:00 close arrows on expanded synopsis drawer - - - - - ea19e177 by Mark Lentczner at 2010-08-12T21:16:45+00:00 width and font changes removed the max width restrictions on the page as a whole and the synopsis made the main font size smaller (nominally 14pt) and then tweaked most font sizes (relative) to be more consistent - - - - - 5ced00c0 by Mark Lentczner at 2010-08-13T15:09:55+00:00 implemented YUI's CSS font approach - - - - - 2799c548 by Mark Lentczner at 2010-08-13T15:11:59+00:00 adjusted margin to 2em, 1 wasn't enough - - - - - 58f06893 by Mark Lentczner at 2010-08-13T15:48:44+00:00 removed underlining on hover for named anchors headings in interface lost thier a element, no need, just put id on heading css for a elements now only applies to those with href attribute - - - - - 7aced4c4 by Mark Lentczner at 2010-08-13T15:50:22+00:00 more space between elements - - - - - 5a3c1cce by Mark Lentczner at 2010-08-13T16:43:43+00:00 adjusted font sizes of auxilary pages per new scheme - - - - - 487539ef by Mark Lentczner at 2010-08-13T21:43:41+00:00 add Frames button and clean up frames.html - - - - - c1a140b6 by Mark Lentczner at 2010-08-13T22:17:48+00:00 move frames button to js - - - - - b0bdb68e by Mark Lentczner at 2010-08-14T03:44:46+00:00 build style menu in javascript moved to javascript, so as to not polute the content with the style menu removed menu building code in Themes.hs removed onclick in Utils.hs changed text of button in header from "Source code" to "Source" more consistent with links in rest of page - - - - - 43ab7120 by Mark Lentczner at 2010-08-16T15:15:37+00:00 font size and margin tweaks - - - - - c0b68652 by Mark Lentczner at 2010-08-17T18:19:52+00:00 clean up collapser logics javascript code for collapasble sections cleaned up rewrote class utilities in javascript to be more robust refactored utilities for generating collapsable sections made toc be same color as synopsis module list has needed clear attribute in CSS - - - - - 5d573427 by Mark Lentczner at 2010-08-17T23:06:02+00:00 don't collapse entries in module list when clicking on links - - - - - 8c307c4a by Mark Lentczner at 2010-08-17T23:21:43+00:00 add missing data file to .cabal - - - - - 414bcfcf by Mark Lentczner at 2010-08-17T23:28:47+00:00 remove synopsis when in frames - - - - - ba0fa98a by Mark Lentczner at 2010-08-18T16:16:11+00:00 layout tweeks - mini page font size, toc color, etc. - - - - - 63c1bed1 by Mark Lentczner at 2010-08-18T19:50:02+00:00 margin fiddling - - - - - c311c094 by Mark Lentczner at 2010-08-20T01:37:55+00:00 better synopsis handling logic - no flashing - - - - - f1fe5fa8 by Mark Lentczner at 2010-08-20T01:41:06+00:00 fix small layout issues mini frames should have same size top heading give info block dts some padding so they don't collide in some browsers - - - - - 0de84d77 by Mark Lentczner at 2010-08-20T02:13:09+00:00 made style changing and cookies storage robust - - - - - 1ef064f9 by Thomas Schilling at 2010-08-04T13:12:22+00:00 Make synopsis frame behave properly in Firefox. In Firefox, pressing the back button first reverted the synopsis frame, and only clicking the back button a second time would update the main frame. - - - - - dd1c9a94 by Mark Lentczner at 2010-08-21T01:46:19+00:00 remove Snappy theme - - - - - 2353a90d by Mark Lentczner at 2010-08-25T05:16:19+00:00 fix occasional v.scroll bars on pre blocks (I think) - - - - - 459b8bf1 by Simon Hengel at 2010-08-08T10:12:45+00:00 Add createInterfaces' (a more high-level alternative to createInterfaces) to Haddock API - - - - - b1b68675 by David Waern at 2010-08-26T20:31:58+00:00 Follow recent API additions with some refactorings Simon Hegel's patch prompted me to do some refactorings in Main, Haddock.Documentation and Haddock.Interface. - - - - - 264d4d67 by David Waern at 2010-08-26T21:40:59+00:00 Get rid of GhcModule and related cruft We can get everything we need directly from TypecheckedModule. - - - - - 0feacec2 by Mark Lentczner at 2010-08-26T23:44:13+00:00 fixed CSS for ordered lists and def lists in doc blocks - - - - - 2997e0c2 by Mark Lentczner at 2010-08-26T23:45:03+00:00 support both kinds of enumerated lists in doc markup The documentation for Haddock says enumerated lists can use either of (1) first item 2. second item The second form wasn't actually supported - - - - - 5d4ddeec by Mark Lentczner at 2010-08-27T21:29:48+00:00 fix broken header link margins - - - - - 614456ba by Mark Lentczner at 2010-08-27T22:16:19+00:00 fix table of contents CSS - - - - - 03f329a2 by David Waern at 2010-08-28T16:36:09+00:00 Update tests following switch to the Xhtml backend - - - - - ca689fa2 by Mark Lentczner at 2010-08-28T18:25:16+00:00 fix def lists - - - - - 18e1d3d2 by Mark Lentczner at 2010-08-28T18:26:18+00:00 push footer to bottom of window - - - - - b0ab8d82 by David Waern at 2010-08-28T22:04:32+00:00 Whitespace police - - - - - 2d217977 by David Waern at 2010-08-29T12:44:45+00:00 Remove Snappy data files - - - - - 01e27d5f by David Waern at 2010-08-29T13:03:28+00:00 Add source entity path to --read-interface You can now use this flag like this: --read-interface=<html path>,<source entity path>,<.haddock file> By "source entity path" I mean the same thing that is specified with the --source-entity flag. The purpose of this is to be able to specify the source entity path per package, to allow source links to work in the presence of cross-package documentation. When given two arguments or less the --read-interface flag behaves as before. - - - - - 20bf4aaa by David Waern at 2010-08-29T13:11:03+00:00 Naming wibbles - - - - - ad22463f by Mark Lentczner at 2010-08-29T15:14:54+00:00 make portability block be a table - solves layout issues - - - - - 97bd1ae6 by Mark Lentczner at 2010-08-29T15:17:42+00:00 update golden test for Test due to portability box change - - - - - d37e139e by Mark Lentczner at 2010-08-29T17:07:17+00:00 move TOC and Info blocks down 0.5em to improve layout issue w/Test.hs - - - - - acf52501 by David Waern at 2010-08-29T17:32:36+00:00 Allow building with ghc < 6.16 - - - - - 1cb34ed8 by Ian Lynagh at 2010-07-24T23:18:49+00:00 Flatten the dynflags before parsing - - - - - b36845b4 by Ian Lynagh at 2010-07-24T23:26:49+00:00 Follow flattenLanguageFlags -> flattenExtensionFlags rename - - - - - 7f7fcc7e by David Waern at 2010-08-29T17:46:23+00:00 Use flattenExtensionFlags with ghc >= 6.13 only - - - - - 13cf9411 by Ian Lynagh at 2010-08-01T18:09:54+00:00 Make the main haddock script versioned, and make plain "haddock" a symlink - - - - - 495cbff2 by Ian Lynagh at 2010-08-18T18:57:24+00:00 Fix installation in the GHC build system Data-files are now in subdirectories, so we need to handle that - - - - - 88ebab0a by Ian Lynagh at 2010-08-18T19:43:53+00:00 GHC build system: Add all the data files to BINDIST_EXTRAS - - - - - 65837172 by David Waern at 2010-08-29T20:12:34+00:00 Update Test - - - - - 094bbaa2 by David Waern at 2010-08-29T20:55:14+00:00 Revert update to Test - - - - - a881cfb3 by David Waern at 2010-08-31T18:24:15+00:00 Bump version number - - - - - 1fc8a3eb by David Waern at 2010-08-31T22:32:27+00:00 Update ANNOUNCE - - - - - ee1df9d0 by David Waern at 2010-08-31T22:33:11+00:00 Update CHANGES - - - - - 394cc854 by David Waern at 2010-08-31T22:33:23+00:00 Update interface file versioning to work with ghc 6.14/15 - - - - - 7d03b79b by David Waern at 2010-08-31T22:36:00+00:00 Update test output following version change - - - - - a48d82d1 by Mark Lentczner at 2010-09-01T04:29:35+00:00 sort options in doc to match --help output removed --html-help option, as it is no longer supported - - - - - 06561aeb by Mark Lentczner at 2010-09-01T05:29:32+00:00 update options documentation rewrote doc for --html added doc for --theme and --built-in-themes added --use-contents and --gen-contents - - - - - 57dea832 by Mark Lentczner at 2010-09-01T05:31:27+00:00 slight wording change about Frames mode - - - - - fa1f6da3 by David Waern at 2010-09-01T10:57:44+00:00 Update doc configure script to find docbook stylesheets on arch linux - - - - - addff770 by David Waern at 2010-09-01T11:02:29+00:00 Wibble - - - - - 8399006d by David Waern at 2010-09-01T11:19:21+00:00 Replace ghci> with >>> in example syntax - - - - - 35074cf8 by David Waern at 2010-09-01T19:03:27+00:00 Improve docs for --no-tmp-comp-dir - - - - - 0f8f8cfd by David Waern at 2010-09-02T11:22:27+00:00 Add a list of contributors to the user guide Break out everyone thanked in the `Acknowledgements` chapter into a separate contributor list and add everyone from `darcs show authors`. We consider everyone who is thanked to be a contributor as a conservative estimation :-) I have added some more contributors that I know about, who were not in the darcs history, but others may be missing. So please add anyone that you think is missing from the list. - - - - - 42ccf099 by David Waern at 2010-09-02T11:29:22+00:00 Update copyright years in license - - - - - 0d560479 by David Waern at 2010-09-02T11:38:52+00:00 Update release instructions - - - - - 72ab7796 by David Waern at 2010-09-02T19:27:08+00:00 Add a note to ANNOUNCE - - - - - bf9d9c5d by David Waern at 2010-09-02T19:27:48+00:00 H.Utils needs FFI on Win+MinGW - - - - - 048ae44a by Mark Lentczner at 2010-09-04T23:19:47+00:00 make TOC group header identifiers validate - - - - - 8c6faf36 by Simon Michael at 2010-09-22T07:12:34+00:00 add hints for cleaner darcs show authors output - - - - - 9909bd17 by Simon Michael at 2010-09-22T17:58:06+00:00 print haddock coverage info on stdout when generating docs A module's haddockable items are its exports and the module itself. The output is lightly formatted so you can align the :'s and sort for readability. - - - - - 6da72171 by David Waern at 2010-10-03T21:31:24+00:00 Style wibble - - - - - 2f8d8e4d by Tobias Brandt at 2010-08-27T07:01:21+00:00 adding the option to fully qualify identifiers - - - - - 833be6c6 by Tobias Brandt at 2010-08-27T15:50:28+00:00 adding support for local and relative name qualification - - - - - df15c4e9 by Tobias Brandt at 2010-08-27T15:56:37+00:00 corrected qualification help message - - - - - 449e9ce1 by David Waern at 2010-10-16T17:34:30+00:00 Solve conflicts - - - - - 3469bda5 by David Waern at 2010-10-16T18:42:40+00:00 Use "qual" as an abbreviation for qualification instead of "quali" for consistency - - - - - 97c2d728 by David Waern at 2010-10-16T18:47:07+00:00 Style police - - - - - ce14fbea by David Waern at 2010-10-16T21:15:25+00:00 Style police - - - - - fdf29e9d by David Waern at 2010-10-17T00:30:44+00:00 Add a pointer to the style guide - - - - - 8e6b44e8 by rrnewton at 2010-10-24T03:19:28+00:00 Change to index pages: include an 'All' option even when subdividing A-Z. - - - - - 755b131c by David Waern at 2010-11-14T19:39:36+00:00 Bump version - - - - - d0345a04 by David Waern at 2010-11-14T19:41:59+00:00 TAG 2.8.1 - - - - - f6221508 by Simon Peyton Jones at 2010-09-13T09:53:00+00:00 Adapt to minor changes in internal GHC functions - - - - - 1290713d by Ian Lynagh at 2010-09-15T10:37:18+00:00 Remove duplicate Outputable instance for Data.Map.Map - - - - - 87f69eef by Ian Lynagh at 2010-09-21T15:01:10+00:00 Bump GHC dep upper bound - - - - - af36e087 by Ian Lynagh at 2010-09-21T15:12:02+00:00 Fix up __GLASGOW_HASKELL__ tests - - - - - ad67716c by Ian Lynagh at 2010-09-21T20:31:35+00:00 Don't build haddock is HADDOCK_DOCS is NO - - - - - 63b3f1f5 by Ian Lynagh at 2010-09-21T21:39:51+00:00 Fixes for when HADDOCK_DOCS=NO - - - - - e92bfa42 by Ian Lynagh at 2010-09-29T21:15:38+00:00 Fix URL creation on Windows: Use / not \ in URLs. Fixes haskell/haddock#4353 - - - - - 66c55e05 by Ian Lynagh at 2010-09-30T17:03:34+00:00 Tidy up haddock symlink installation In particular, it now doesn't get created if we aren't installing haddock. - - - - - 549b5556 by Ian Lynagh at 2010-10-23T21:17:14+00:00 Follow extension-flattening change in GHC - - - - - d7c2f72b by David Waern at 2010-11-14T20:17:55+00:00 Bump version to 2.8.2 - - - - - 6989a3a9 by David Waern at 2010-11-14T20:26:01+00:00 Solve conflict - - - - - 055c6910 by Ian Lynagh at 2010-09-22T15:36:20+00:00 Bump GHC dep - - - - - c96c0763 by Simon Marlow at 2010-10-27T11:09:44+00:00 follow changes in the GHC API - - - - - 45907129 by David Waern at 2010-11-07T14:00:58+00:00 Update the HCAR entry - - - - - 61940b95 by David Waern at 2010-11-07T14:07:34+00:00 Make the HCAR entry smaller - - - - - aa590b7d by David Waern at 2010-11-14T21:30:59+00:00 Update HCAR entry with November 2010 version - - - - - 587f9847 by David Waern at 2010-11-14T23:48:17+00:00 Require ghc >= 7.0 - - - - - ff5c647c by David Waern at 2010-11-14T23:49:09+00:00 TAG 2.8.2 - - - - - 937fcb4f by David Waern at 2010-11-14T23:49:45+00:00 Solve conflict - - - - - 8e5d0c1a by David Waern at 2010-11-15T21:09:50+00:00 Remove code for ghc < 7 - - - - - 3d47b70a by David Waern at 2010-11-15T21:11:06+00:00 Fix bad merge - - - - - 7f4a0d8a by David Waern at 2010-11-15T21:13:57+00:00 Remove more ghc < 7 code - - - - - 9ee34b50 by David Waern at 2010-11-15T21:31:25+00:00 Match all AsyncExceptions in exception handler - - - - - 42849c70 by David Waern at 2010-11-15T21:35:31+00:00 Just say "internal error" instead of "internal Haddock or GHC error" - - - - - c88c809b by David Waern at 2010-11-15T21:44:19+00:00 Remove docNameOcc under the motto "don't name compositions" - - - - - b798fc7c by David Waern at 2010-11-15T23:27:13+00:00 Wibble - - - - - 2228197e by David Waern at 2010-11-15T23:28:24+00:00 Rename the HCAR entry file - - - - - 8a3f9090 by David Waern at 2010-11-16T00:05:29+00:00 Remove Haskell 2010 extensions from .cabal file - - - - - c7a0c597 by David Waern at 2010-11-16T00:10:28+00:00 Style wibbles - - - - - cde707a5 by David Waern at 2010-11-16T00:12:00+00:00 Remove LANGUAGE ForeignFunctionInterface pragmas - - - - - 1dbda8ed by David Waern at 2010-11-16T00:17:21+00:00 Make a little more use of DoAndIfThenElse - - - - - 4c45ff6e by David Waern at 2010-11-16T00:59:41+00:00 hlint police - - - - - d2feaf09 by David Waern at 2010-11-16T01:14:15+00:00 hlint police - - - - - 99876e97 by David Waern at 2010-11-20T19:06:00+00:00 Haddock documentation updates - - - - - 65ce6987 by David Waern at 2010-11-20T19:42:51+00:00 Follow the style guide closer in Haddock.Types and improve docs - - - - - 28ca304a by tob.brandt at 2010-11-20T17:04:40+00:00 add full qualification for undocumented names - - - - - d61341e3 by David Waern at 2010-11-20T20:04:15+00:00 Re-structure qualification code a little - - - - - 0057e4d6 by David Waern at 2010-11-20T20:07:55+00:00 Re-order functions - - - - - d7279afd by David Waern at 2010-11-21T03:39:54+00:00 Add BangPatterns to alex and happy source files - - - - - 629fe60e by tob.brandt at 2010-11-23T23:35:11+00:00 documentation for qualification - - - - - 37031cee by David Waern at 2010-11-23T21:06:44+00:00 Update CHANGES - don't mention 2.8.2, we won't release it - - - - - f2489e19 by David Waern at 2010-12-01T21:57:11+00:00 Update deps of runtests.hs to work with ghc 7.0.1 - - - - - d3657e9a by David Waern at 2010-12-01T22:04:57+00:00 Make tests compile with ghc 7.0.1 - - - - - a2f09d9b by David Waern at 2010-12-01T22:06:59+00:00 Update tests following version bump - - - - - 50883ebb by David Waern at 2010-12-06T14:09:18+00:00 Update tests following recent changes - - - - - fc2fadeb by David Waern at 2010-12-06T14:17:29+00:00 Add a flag --pretty-html for rendering indented html with newlines - - - - - 30832ef2 by David Waern at 2010-12-06T14:17:35+00:00 Use --pretty-html when running the test suite. Makes it easier to compare output - - - - - a0b81b31 by David Waern at 2010-12-06T14:18:27+00:00 Wibble - - - - - 3aaa23fe by David Waern at 2010-12-06T14:19:29+00:00 Haddockify ppHtml comments - - - - - 24bb24f0 by David Waern at 2010-12-06T14:23:15+00:00 Remove --debug. It was't used, and --verbosity should take its place - - - - - 6bc076e5 by David Waern at 2010-12-06T14:25:37+00:00 Rename golden-tests into html-tests. "golden tests" sounds strange - - - - - 53301e55 by David Waern at 2010-12-06T14:26:26+00:00 QUALI -> QUAL in the description --qual for consistency - - - - - 98b6affb by David Waern at 2010-12-06T21:54:02+00:00 Bump version - - - - - 371bf1b3 by David Waern at 2010-12-06T22:08:55+00:00 Update tests following version bump - - - - - 25be762d by David Waern at 2010-12-06T22:21:03+00:00 Update CHANGES - - - - - 7c7dac71 by David Waern at 2010-12-06T22:33:43+00:00 Update ANNOUNCE - - - - - 30d7a5f2 by Simon Peyton Jones at 2010-11-15T08:38:38+00:00 Alex generates BangPatterns, so make Lex.x accept them (It'd be better for Alex to generate this pragma.) - - - - - 605e8018 by Simon Marlow at 2010-11-17T11:37:24+00:00 Add {-# LANGUAGE BangPatterns #-} to mollify GHC - - - - - a46607ba by David Waern at 2010-12-07T14:08:10+00:00 Solve conflicts - - - - - b28cda66 by David Waern at 2010-12-09T20:41:35+00:00 Docs: Mention that \ is a special character in markup - - - - - a435bfdd by Ian Lynagh at 2010-11-17T14:01:19+00:00 TAG GHC 7.0.1 release - - - - - 5a15a05a by David Waern at 2010-12-11T17:51:19+00:00 Fix indentation problem - - - - - 4232289a by Lennart Kolmodin at 2010-12-17T18:32:03+00:00 Revise haddock.cabal given that we now require ghc-7 default-language should be Haskell2010, slight new semantics for extensions. Rewrite into clearer dependencies of base and Cabal. - - - - - a36302dc by David Waern at 2010-12-19T17:12:37+00:00 Update CHANGES - - - - - 7c8b85b3 by David Waern at 2010-12-19T17:14:24+00:00 Bump version - - - - - cff22813 by Ian Lynagh at 2011-01-05T18:24:27+00:00 Write hoogle output in utf8; fixes GHC build on Windows - - - - - c7e762ea by David Waern at 2011-01-22T00:00:35+00:00 Put title outside doc div when HTML:fying title+prologue Avoids indenting the title, and makes more sense since the title is not a doc string anyway. - - - - - 5f639054 by David Waern at 2011-01-22T16:09:44+00:00 Fix spelling error - contributed by Marco Silva - - - - - c11dce78 by Ian Lynagh at 2011-01-07T02:33:11+00:00 Follow GHC build system changes - - - - - 101cfaf5 by David Waern at 2011-01-08T14:06:44+00:00 Bump version - - - - - af62348b by David Waern at 2011-01-08T14:07:07+00:00 TAG 2.9.2 - - - - - 4d1f6461 by Ian Lynagh at 2011-01-07T23:06:57+00:00 Name the haddock script haddock-ghc-7.0.2 instead of haddock-7.0.2; haskell/haddock#4882 "7.0.2" looked like a haddock version number before - - - - - 8ee4d5d3 by Simon Peyton Jones at 2011-01-10T17:31:12+00:00 Update Haddock to reflect change in hs_tyclds field of HsGroup - - - - - 06f3e3db by Ian Lynagh at 2011-03-03T15:02:37+00:00 TAG GHC 7.0.2 release - - - - - 7de0667d by David Waern at 2011-03-10T22:47:13+00:00 Update CHANGES - - - - - 33a9f1c8 by David Waern at 2011-03-10T22:47:31+00:00 Fix build with ghc 7.0.1 - - - - - 4616f861 by David Waern at 2011-03-10T22:47:50+00:00 TAG 2.9.2-actual - - - - - 0dab5e3c by Simon Hengel at 2011-04-08T15:53:01+00:00 Set shell script for unit tests back to work - - - - - 85c54dee by Simon Hengel at 2011-04-08T16:01:24+00:00 Set unit tests back to work Here "ghci>" was still used instead of ">>>". - - - - - 1cea9b78 by Simon Hengel at 2011-04-08T16:25:36+00:00 Update runtests.hs for GHC 7.0.2 - - - - - 8e5b3bbb by Simon Hengel at 2011-04-08T16:28:49+00:00 Update Haddock version in *.html.ref - - - - - 2545e955 by Simon Hengel at 2011-04-08T17:09:28+00:00 Add support for blank lines in the result of examples Result lines that only contain the string "<BLANKLINE>" are treated as a blank line. - - - - - adf64d2e by Simon Hengel at 2011-04-08T17:36:50+00:00 Add documentation for "support for blank lines in the result of examples" - - - - - c51352ca by David Waern at 2011-05-21T23:57:56+00:00 Improve a haddock comment - - - - - 7419cf2c by David Waern at 2011-05-22T15:41:52+00:00 Use cabal's test suite support to run the test suite This gives up proper dependency tracking of the test script. - - - - - 7770070c by David Waern at 2011-05-22T01:45:44+00:00 We don't need to send DocOptions nor a flag to mkExportItems - - - - - 9d95b7b6 by David Waern at 2011-05-22T21:39:03+00:00 Fix a bug - - - - - 1f93699b by David Waern at 2011-05-22T21:40:21+00:00 Break out fullContentsOf, give it a better name and some documentation The documentation describes how we want this function to eventually behave, once we have fixed a few problems with the current implementation. - - - - - 9a86432f by David Waern at 2011-05-22T21:53:52+00:00 Fix some stylistic issues in mkExportItems - - - - - c271ff0c by David Waern at 2011-05-22T22:09:11+00:00 Indentation - - - - - 93e602b1 by David Waern at 2011-06-10T01:35:31+00:00 Add git commits since switchover: darcs format (followed by a conflict resolution): commit 6f92cdd12d1354dfbd80f8323ca333bea700896a Merge: f420cc4 28df3a1 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 19 17:54:34 2011 +0100 Merge remote branch 'origin/master' into ghc-generics commit 28df3a119f770fdfe85c687dd73d5f6712b8e7d0 Author: Max Bolingbroke <batterseapower at hotmail.com> Date: Sat May 14 22:37:02 2011 +0100 Unicode fix for getExecDir on Windows commit 89813e729be8bce26765b95419a171a7826f6d70 Merge: 6df3a04 797ab27 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 9 11:55:17 2011 +0100 Merge branch 'ghc-new-co' commit 6df3a040da3dbddee67c6e30a892f87e6b164383 Author: Ian Lynagh <igloo at earth.li> Date: Sun May 8 17:05:50 2011 +0100 Follow changes in SDoc commit f420cc48b9259f0b1afd2438b12f9a2bde57053d Author: Jose Pedro Magalhaes <jpm at cs.uu.nl> Date: Wed May 4 17:31:52 2011 +0200 Adapt haddock to the removal of HsNumTy and TypePat. commit 797ab27bdccf39c73ccad374fea265f124cb52ea Merge: 1d81436 5a91450 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:05:03 2011 +0100 Merge remote branch 'origin/master' into ghc-new-co commit 1d8143659a81cf9611668348e33fd0775c7ab1d2 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:03:46 2011 +0100 Wibbles for ghc-new-co branch commit 5a91450e2ea5a93c70bd3904b022445c9cc82488 Author: Ian Lynagh <igloo at earth.li> Date: Fri Apr 22 00:51:56 2011 +0100 Follow defaultDynFlags change in GHC - - - - - 498da5ae by David Waern at 2011-06-11T00:33:33+00:00 * Merge in git patch from Michal Terepeta >From 6fc71d067738ef4b7de159327bb6dc3d0596be29 Mon Sep 17 00:00:00 2001 From: Michal Terepeta <michal.terepeta at gmail.com> Date: Sat, 14 May 2011 19:18:22 +0200 Subject: [PATCH] Follow the change of TypeSig in GHC. This follows the change in GHC to make TypeSig take a list of names (instead of just one); GHC ticket haskell/haddock#1595. This should also improve the Haddock output in case the user writes a type signature that refers to many names: -- | Some comment.. foo, bar :: ... will now generate the expected output with one signature for both names. - - - - - 094607fe by Ian Lynagh at 2011-06-17T19:10:29+01:00 Fix build - - - - - 8fa35740 by Ian Lynagh at 2011-06-26T21:06:40+01:00 Bump GHC dep to allow 7.2 - - - - - e4d2ca3c by Ian Lynagh at 2011-07-07T23:06:28+01:00 Relax base dep - - - - - b948fde9 by Ian Lynagh at 2011-07-28T16:39:45+01:00 GHC build system: Don't install the datafiles twice - - - - - f82f6d70 by Simon Marlow at 2011-08-11T12:08:15+01:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - b341cc12 by Max Bolingbroke at 2011-08-22T20:25:27+01:00 Fix compilation with no-pred-ty GHC - - - - - 30494581 by Max Bolingbroke at 2011-08-23T10:20:54+01:00 Remaining fixes for PredTy removal - - - - - 0b197138 by Max Bolingbroke at 2011-08-26T08:27:45+01:00 Rename factKind to constraintKind - - - - - a379bec5 by Max Bolingbroke at 2011-09-04T12:54:47+01:00 Deal with change to IParam handling in GHC - - - - - f94e421b by Max Bolingbroke at 2011-09-06T17:34:31+01:00 Adapt Haddock for the ConstraintKind extension changes - - - - - 8821e5cc by Max Bolingbroke at 2011-09-09T08:24:59+01:00 Ignore associated type defaults (just as we ignore default methods) - - - - - 31a0afd4 by Max Bolingbroke at 2011-09-09T09:06:00+01:00 Merge branch 'no-pred-ty' of ssh://darcs.haskell.org/srv/darcs/haddock into no-pred-ty - - - - - dd3b530a by Max Bolingbroke at 2011-09-09T14:10:25+01:00 Merge branch 'no-pred-ty' Conflicts: src/Haddock/Convert.hs - - - - - 5f25ec96 by Max Bolingbroke at 2011-09-09T14:10:40+01:00 Replace FactTuple with ConstraintTuple - - - - - cd30b9cc by David Waern at 2011-09-26T02:17:55+02:00 Bump to version 2.9.3 - - - - - 4fbfd397 by Max Bolingbroke at 2011-09-27T14:55:21+01:00 Follow changes to BinIface Name serialization - - - - - 92257d90 by David Waern at 2011-09-30T23:45:07+02:00 Fix problem with test files not added to distribution tarball - - - - - 00255bda by David Waern at 2011-09-30T23:48:24+02:00 Merge branch 'development' - - - - - 5421264f by David Waern at 2011-10-01T01:25:39+02:00 Merge in darcs patch from Simon Meier: Wed Jun 1 19:41:16 CEST 2011 iridcode at gmail.com * prettier haddock coverage info The new coverage info rendering uses less horizontal space. This reduces the number of unnecessary line-wrappings. Moreover, the most important information, how much has been documented already, is now put up front. Hopefully, this makes it more likely that a library author is bothered by the low coverage of his modules and fixes that issue ;-) - - - - - 07d318ef by David Waern at 2011-10-01T01:34:10+02:00 Use printException instead of deprecated printExceptionAndWarnings - - - - - 40d52ee4 by David Waern at 2011-10-01T01:41:13+02:00 Merge in darcs pach: Mon Apr 11 18:09:54 JST 2011 Liyang HU <haddock at liyang.hu> * Remember collapsed sections in index.html / haddock-util.js - - - - - 279d6dd4 by David Waern at 2011-10-01T01:55:45+02:00 Merge in darcs patch: Joachim Breitner <mail at joachim-breitner.de>**20110619201645 Ignore-this: f6c51228205b0902ad5bfad5040b989a As reported on http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=578301, generating the global index takes much too long if type-level (with lots of auto-generated types) is installed. The patch avoids a quadratic runtime in the subfunction getIfaceIndex of ppHtmlIndex by using a temporary set. Runtime improvement observed here from 25.36s to 2.86s. - - - - - d1612383 by David Waern at 2011-10-01T01:56:48+02:00 Merge branch 'development' - - - - - 347520c1 by David Waern at 2011-10-01T01:56:54+02:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9a0c95e8 by David Waern at 2011-10-01T02:19:10+02:00 Improve .cabal file - - - - - 6967dc64 by Ian Lynagh at 2011-10-01T01:34:06+01:00 Follow changes to ForeignImport/ForeignExport in GHC - - - - - 565cb26b by Simon Marlow at 2011-10-04T00:15:04+02:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - 8b74f512 by David Waern at 2011-10-04T00:18:17+02:00 Requre ghc >= 7.2 - - - - - 271d360c by David Waern at 2011-10-04T00:22:50+02:00 Bump version to 2.9.4 - - - - - 37f3edb0 by David Waern at 2011-10-06T02:30:21+02:00 Add alex and happy to build-tools. - - - - - 7ac2bb6e by David Terei at 2011-10-12T14:02:55-07:00 Add safe haskell indication to haddock output - - - - - 42c91a47 by David Terei at 2011-10-12T14:06:03-07:00 Fix CSS issue with info table not being contained in module header - - - - - 0eddab6c by David Terei at 2011-10-12T14:06:58-07:00 Add safe haskell indication to haddock output - - - - - 3df058eb by David Terei at 2011-10-12T14:07:07-07:00 Fix CSS issue with info table not being contained in module header - - - - - a40a6c3f by David Waern at 2011-10-22T11:29:06+02:00 Bump .haddock file version since the format has changed recently - - - - - 8a6254be by David Waern at 2011-10-22T11:30:42+02:00 Merge branch 'development' - - - - - 642e3e02 by David Waern at 2011-10-23T21:23:39+02:00 Sort import list - - - - - 36371cf8 by David Waern at 2011-10-23T22:48:18+02:00 Remove NEW_GHC_LAYOUT conditional. - - - - - 5604b499 by David Waern at 2011-10-27T00:15:03+02:00 Add --print-ghc-path. - - - - - 463499fa by David Waern at 2011-10-27T00:16:22+02:00 Make testsuite able to find its dependencies automatically. - - - - - a3506172 by Ryan Newton at 2011-11-05T05:59:58-04:00 Improved declNames internal error. Added a case to handle DocD. - - - - - 001b8baf by David Waern at 2011-11-05T20:37:29+01:00 Rename copy.hs -> accept.hs. - - - - - 55d808d3 by David Waern at 2011-11-05T23:30:02+01:00 Fix build. - - - - - deb5c3be by David Waern at 2011-11-06T00:01:47+01:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9b663554 by David Waern at 2011-11-06T00:03:45+01:00 Merge https://github.com/rrnewton/haddock - - - - - 1abb0ff6 by David Waern at 2011-11-06T01:20:37+01:00 Use getDeclMainBinder instead of declNames. - - - - - 4b005c01 by David Waern at 2011-11-06T19:09:53+01:00 Fix build. - - - - - c2c51bc7 by Ian Lynagh at 2011-11-06T23:01:33+00:00 Remove -DNEW_GHC_LAYOUT in ghc.mk - - - - - f847d703 by Jose Pedro Magalhaes at 2011-11-11T09:07:39+00:00 New kind-polymorphic core This big patch implements a kind-polymorphic core for GHC. The current implementation focuses on making sure that all kind-monomorphic programs still work in the new core; it is not yet guaranteed that kind-polymorphic programs (using the new -XPolyKinds flag) will work. For more information, see http://haskell.org/haskellwiki/GHC/Kinds - - - - - 7d7c3b09 by Jose Pedro Magalhaes at 2011-11-16T21:42:22+01:00 Follow changes to tuple sorts in master - - - - - 8430e03e by Simon Peyton Jones at 2011-11-17T10:20:27+00:00 Remove redundant imports - - - - - d1b06832 by Ian Lynagh at 2011-11-19T01:33:21+00:00 Follow GHC build system change to the way we call rm - - - - - 9e2230ed by David Waern at 2011-11-24T15:00:24+01:00 Fix a bug in test runner and get rid of regex-compat dependency. - - - - - 52039b21 by David Waern at 2011-11-24T23:55:36+01:00 Avoid haskell98 dependency in test - - - - - 92e1220d by David Waern at 2011-11-25T00:03:33+01:00 Avoid depency on regex-compat also in accept.hs. - - - - - ddac6b6f by David Waern at 2011-11-25T02:13:38+01:00 Accept test output. - - - - - 5a720455 by David Waern at 2011-11-25T02:16:20+01:00 Some more changes to test scripts. - - - - - 170a9004 by David Waern at 2011-11-25T02:30:41+01:00 Add flag --interface-version. - - - - - d225576c by David Waern at 2011-11-25T02:39:26+01:00 Remove #ifs for older compiler versions. - - - - - f0d0a4f5 by David Waern at 2011-11-26T04:20:12+01:00 Give preference to type over data constructors for doc comment links at renaming time. Previously this was done in the backends. Also, warn when a doc comment refers to something that is in scope but which we don't have the .haddock file for. These changes mean we can make DocIdentifier [a] into DocIdentifier a. - - - - - eef0e776 by David Waern at 2011-11-26T17:01:06+01:00 Allow doc comments to link to out-of-scope things (#78). (A bug that should have been fixed long ago.) - - - - - 565ad529 by David Waern at 2011-11-26T19:56:21+01:00 Update tests. - - - - - fb3ce7b9 by David Waern at 2011-11-26T21:44:28+01:00 Cleanup. - - - - - d0328126 by David Waern at 2011-11-26T22:10:28+01:00 Fix module reference bug. - - - - - c03765f8 by David Waern at 2011-12-03T05:20:20+01:00 Slightly better behaviour on top-levels without type signatures. - Docs don't get attached to the next top-level with signature by mistake. - If there's an export list and the top-level is part of it, its doc comment shows up in the documentation. - - - - - 48461d31 by David Waern at 2011-12-03T05:38:10+01:00 Add a test for Unicode doc comments. - - - - - 549c4b4e by David Waern at 2011-12-03T19:07:55+01:00 Cleanup. - - - - - 7bfecf91 by David Waern at 2011-12-03T20:13:08+01:00 More cleanup. - - - - - 14fab722 by Ian Lynagh at 2011-12-12T21:21:35+00:00 Update dependencies and binaryInterfaceVersion - - - - - 469e6568 by Ian Lynagh at 2011-12-18T12:56:16+00:00 Fix (untested) building from source tarball without alex/happy haddock's .cabal file was declaring that it needed alex and happy to build, but in the GHC source tarballs it doesn't. - - - - - 895c9a8c by David Waern at 2011-12-27T12:57:43+01:00 Go back to having a doc, sub and decl map instead of one big decl map. This setup makes more sense since when we add value bindings to the processed declarations (for type inference), we will have multiple declarations which should share documentation. Also, we already have a separate doc map for instances which we can now merge into the main doc map. Another benefit is that we don't need the DeclInfo type any longer. - - - - - 736767d9 by David Waern at 2011-12-27T13:33:41+01:00 Merge ../../../haddock Conflicts: src/Haddock/InterfaceFile.hs - - - - - 20016f79 by David Waern at 2011-12-27T13:57:23+01:00 Bump version. - - - - - 31f276fb by David Waern at 2011-12-27T13:57:32+01:00 Merge ../ghc/utils/haddock - - - - - 95b367cd by David Waern at 2011-12-27T14:57:29+01:00 Update tests following version bump. - - - - - fa3c94cd by David Waern at 2011-12-27T14:57:51+01:00 Get rid of quite unnecessary use of different lists. - - - - - 9c4d3c54 by David Waern at 2011-12-27T15:26:42+01:00 Cleanup. - - - - - 2caf9f90 by David Waern at 2011-12-27T16:18:05+01:00 Wibbles. - - - - - 3757d09b by David Waern at 2011-12-27T20:50:26+01:00 Complete support for inferring types for top-level bindings. - - - - - 53418734 by David Waern at 2011-12-28T15:02:13+01:00 Minor fixes and cleanup. - - - - - 0c9d0385 by Ian Lynagh at 2012-01-03T18:31:29+00:00 Follow rename of Instance to ClsInst in GHC - - - - - c9bc969a by Simon Hengel at 2012-01-12T21:28:14+01:00 Make sure that generated xhtml is valid (close haskell/haddock#186) Thanks to Phyx. - - - - - 836a0b9a by David Waern at 2012-02-01T02:30:05+01:00 Fix bug introduced in my recent refactoring. - - - - - c7d733eb by David Waern at 2012-02-01T02:30:26+01:00 Cleanup mkMaps and avoid quadratic behaviour. - - - - - da3cda8f by David Waern at 2012-02-01T02:56:56+01:00 Require ghc >= 7.4. - - - - - 83a3287e by David Waern at 2012-02-01T02:57:36+01:00 Update CHANGES. - - - - - 93408f0b by Simon Hengel at 2012-02-04T00:48:04+01:00 Add reference renderings - - - - - 49d00d2c by Simon Hengel at 2012-02-04T00:48:25+01:00 Set unit tests for parser back to work - - - - - eb450980 by Simon Hengel at 2012-02-04T00:49:07+01:00 Add .gitignore - - - - - a841602c by Simon Hengel at 2012-02-04T00:49:16+01:00 Add .ghci file - - - - - 8861199d by Simon Hengel at 2012-02-04T00:49:29+01:00 tests/html-tests/copy.hs: Use mapM_ instead of mapM So we do net get a list of () on stdout when running with runhaskell. - - - - - b477d9b5 by Simon Hengel at 2012-02-04T00:49:46+01:00 Remove index files from golden tests - - - - - 9dbda34e by Simon Hengel at 2012-02-04T00:49:57+01:00 Add /tests/html-tests/tests/*index*.ref to .gitignore - - - - - a9434817 by Simon Hengel at 2012-02-04T00:50:04+01:00 Add DocWarning to Doc The Xhtml backend has special markup for that, Hoogle and LaTeX reuse what we have for DocEmphasis. - - - - - de2fb6fa by Simon Hengel at 2012-02-04T00:50:13+01:00 Add support for module warnings - - - - - 0640920e by Simon Hengel at 2012-02-04T00:50:21+01:00 Add tests for module warnings - - - - - 30ce0d77 by Simon Hengel at 2012-02-04T00:50:29+01:00 Add support for warnings - - - - - bb367960 by Simon Hengel at 2012-02-04T00:50:37+01:00 Add tests for warnings - - - - - 6af1dc2d by Simon Hengel at 2012-02-04T00:50:50+01:00 Expand type signatures in export list (fixes haskell/haddock#192) - - - - - a06cbf25 by Simon Hengel at 2012-02-04T00:51:04+01:00 Expand type signatures for modules without explicit export list - - - - - 57dda796 by Simon Hengel at 2012-02-04T00:51:15+01:00 Remove obsolete TODO - - - - - 270c3253 by David Waern at 2012-02-04T00:51:24+01:00 Fix issues in support for warnings. * Match against local names only. * Simplify (it's OK to map over the warnings). - - - - - 683634bd by David Waern at 2012-02-04T00:55:11+01:00 Some cleanup and make sure we filter warnings through exports. - - - - - 210cb4ca by David Waern at 2012-02-04T03:01:30+01:00 Merge branch 'fix-for-186' of https://github.com/sol/haddock into ghc-7.4 - - - - - e8db9031 by David Waern at 2012-02-04T03:07:51+01:00 Style police. - - - - - 261f9462 by David Waern at 2012-02-04T03:20:16+01:00 Update tests. - - - - - 823cfc7c by David Waern at 2012-02-04T03:21:12+01:00 Use mapM_ in accept.hs as well. - - - - - 873dd619 by David Waern at 2012-02-04T03:21:33+01:00 Remove copy.hs - use accept.hs instead. - - - - - 0e31a14a by David Waern at 2012-02-04T03:47:33+01:00 Use <> instead of mappend. - - - - - 2ff7544f by David Waern at 2012-02-04T03:48:55+01:00 Remove code for older ghc versions. - - - - - dacf2786 by David Waern at 2012-02-04T15:52:51+01:00 Clean up some code from last SoC project. - - - - - 00cbb117 by David Waern at 2012-02-04T21:43:49+01:00 Mostly hlint-inspired cleanup. - - - - - 7dc86cc2 by Simon Peyton Jones at 2012-02-06T09:14:41+00:00 Track changes in HsDecls - - - - - f91f82fe by Ian Lynagh at 2012-02-16T13:40:11+00:00 Follow changes in GHC caused by the CAPI CTYPE pragma - - - - - a0ea6b0b by Ian Lynagh at 2012-02-22T02:26:12+00:00 Follow changes in GHC - - - - - b23b07d1 by Simon Peyton Jones at 2012-03-02T16:36:41+00:00 Follow changes in data representation from the big PolyKinds commit - - - - - 43406022 by Simon Hengel at 2012-03-05T11:18:34+01:00 Save/restore global state for static flags when running GHC actions This is necessary if we want to run createInterfaces (from Documentation.Haddock) multiple times in the same process. - - - - - 9fba16fe by Paolo Capriotti at 2012-03-06T10:57:33+00:00 Update .gitignore. - - - - - a9325044 by Simon Peyton Jones at 2012-03-14T17:35:42+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - fd48065a by Iavor Diatchki at 2012-03-15T22:43:35-07:00 Add support for type-level literals. - - - - - 2e8206dd by Simon Peyton Jones at 2012-03-16T14:18:22+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - 93e13319 by Simon Peyton Jones at 2012-03-17T01:04:05+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock Conflicts: src/Haddock/Convert.hs - - - - - d253fa71 by Iavor Diatchki at 2012-03-19T20:12:18-07:00 Merge remote-tracking branch 'origin/master' into type-nats - - - - - fc40acc8 by Iavor Diatchki at 2012-03-19T20:31:27-07:00 Add a missing case for type literals. - - - - - fd2ad699 by Iavor Diatchki at 2012-03-24T13:28:29-07:00 Rename variable to avoid shadowing warning. - - - - - 9369dd3c by Simon Peyton Jones at 2012-03-26T09:14:23+01:00 Follow refactoring of TyClDecl/HsTyDefn - - - - - 38825ca5 by Simon Peyton Jones at 2012-03-26T09:14:37+01:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - 4324ac0f by David Waern at 2012-04-01T01:51:19+02:00 Disable unicode test. - - - - - 3165b750 by David Waern at 2012-04-01T01:51:34+02:00 Take reader environment directly from TypecheckedSource. - - - - - 213b644c by David Waern at 2012-04-01T01:55:20+02:00 Cleanup. - - - - - 3118b4ba by David Waern at 2012-04-01T02:16:15+02:00 Don't filter out unexported names from the four maps - fixes a regression. - - - - - d6524e17 by David Waern at 2012-04-01T02:40:34+02:00 Fix crash when using --qual. Naughty GHC API! - - - - - ea3c43d8 by Henning Thielemann at 2012-04-01T13:03:07+02:00 add QualOption type for distinction between qualification argument given by the user and the actual qualification for a concrete module - - - - - 5422ff05 by Henning Thielemann at 2012-04-01T16:25:02+02:00 emit an error message when the --qual option is used incorrectly - - - - - 026e3404 by David Waern at 2012-04-01T18:10:30+02:00 Don't crash on unicode strings in doc comments. - - - - - ce006632 by David Waern at 2012-04-01T20:13:35+02:00 Add test for --ignore-all-exports flag/ignore-exports pragma. - - - - - 6e4dd33c by David Waern at 2012-04-01T20:21:03+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.4 - - - - - 734ae124 by Henning Thielemann at 2012-04-01T20:22:10+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - 622f9ba5 by David Waern at 2012-04-01T21:26:13+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 55ce17cb by Henning Thielemann at 2012-04-01T22:03:25+02:00 'abbreviate' qualification style - basic support Currently we ignore the package a module is imported from. This means that a module import would shadow another one with the same module name from a different package. - - - - - c85314ef by David Waern at 2012-04-01T22:05:12+02:00 Check qualification option before processing modules. - - - - - ae4b626c by Henning Thielemann at 2012-04-02T00:19:36+02:00 abbreviated qualification: use Packages.lookupModuleInAllPackages for finding the package that a module belongs to - - - - - 60bdbcf5 by Henning Thielemann at 2012-04-02T00:25:31+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - df44301d by Henning Thielemann at 2012-04-02T00:29:05+02:00 qualification style 'abbreviated' -> 'aliased' - - - - - f4192a64 by David Waern at 2012-04-02T01:05:47+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 7ba09067 by David Terei at 2012-04-04T15:08:21-07:00 Fix reporting of modules safe haskell mode (#5989) - - - - - d0cc33d0 by David Terei at 2012-04-06T15:50:41+01:00 Fix reporting of modules safe haskell mode (#5989) - - - - - 6e3434c5 by Simon Peyton Jones at 2012-04-20T18:37:46+01:00 Track changes in HsSyn - - - - - 22014ed0 by Simon Peyton Jones at 2012-05-11T22:45:15+01:00 Follow changes to LHsTyVarBndrs - - - - - d9a07b24 by David Waern at 2012-05-15T01:46:35+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - a6c4ebc6 by David Waern at 2012-05-16T02:18:32+02:00 Update CHANGES. - - - - - 8e181d29 by David Waern at 2012-05-16T02:27:56+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - e358210d by David Waern at 2012-05-16T02:35:33+02:00 Mention the new aliased --qual mode in CHANGES. - - - - - efd36a28 by David Waern at 2012-05-16T21:33:13+02:00 Bump version number. - - - - - d6b3af14 by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for deprecated record field - - - - - 927f800e by Simon Hengel at 2012-05-17T19:08:20+02:00 Use >>= instead of fmap and join - - - - - 048b41d5 by Simon Hengel at 2012-05-17T19:08:20+02:00 newtype-wrap Doc nodes for things that may have warnings attached - - - - - e3a89fc3 by Simon Hengel at 2012-05-17T19:08:20+02:00 Attach warnings to `Documentation` type - - - - - 5d4cc43d by Simon Hengel at 2012-05-17T19:08:20+02:00 Simplify lookupWarning - - - - - cf8ae69d by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for haskell/haddock#205 - - - - - cb409b19 by Simon Peyton Jones at 2012-05-25T08:30:11+01:00 Follow changes in LHsTyVarBndrs - - - - - 2d5f4179 by Simon Hengel at 2012-05-26T19:21:29+02:00 Add Applicative instance for (GenRnM a) - - - - - e4373060 by Simon Hengel at 2012-05-26T19:21:33+02:00 Use a map for warnings, as suggested by @waern - - - - - 597a68c7 by Simon Hengel at 2012-05-27T08:48:24+02:00 Add an optional label to URLs - - - - - ef1ac7fe by Simon Hengel at 2012-05-27T08:48:24+02:00 Add support for hyperlink labels to parser - - - - - 41f2adce by Simon Hengel at 2012-05-27T08:48:24+02:00 Add golden test for hyperlinks - - - - - 83d5e764 by Simon Hengel at 2012-05-27T08:50:02+02:00 Use LANGUAGE pragmas instead of default-extensions in cabal file - - - - - ddb755e5 by Simon Hengel at 2012-05-27T08:50:02+02:00 Fix typo in comment - - - - - 110676b4 by Simon Hengel at 2012-05-27T08:50:02+02:00 Add a type signature for a where-binding - - - - - 7d9ba2a0 by Ian Lynagh at 2012-06-12T14:38:01+01:00 Follow changes in GHC - - - - - 47c704f2 by Ian Lynagh at 2012-06-12T18:52:16+01:00 Follow changes in GHC - - - - - e1efe1ab by Simon Peyton Jones at 2012-06-13T17:25:29+01:00 Follow changes for the implementation of implicit parameters - - - - - 69abc81c by Ian Lynagh at 2012-06-19T22:52:58+01:00 Follow changes in base - - - - - 9d074a21 by Paolo Capriotti at 2012-06-22T18:26:47+01:00 Use right docMap to get decl documentation. - - - - - e3292ef6 by Ian Lynagh at 2012-07-15T01:31:19+01:00 Follow changes in GHC - - - - - ceae56b0 by Ian Lynagh at 2012-07-16T21:22:48+01:00 Fix haddock following some GHC changes Passing _|_ as the Settings for defaultDynFlags no longer works well enough - - - - - 9df72735 by Paolo Capriotti at 2012-07-19T16:49:32+01:00 Forward port changes from stable. - - - - - 572f5fcf by Ian Lynagh at 2012-07-19T20:38:26+01:00 Merge branch 'master' of darcs.haskell.org:/srv/darcs//haddock - - - - - 9195aca4 by Paolo Capriotti at 2012-07-20T10:27:28+01:00 Update dependencies. - - - - - 33db3923 by Ian Lynagh at 2012-07-20T17:54:43+01:00 Build with GHC 7.7 - - - - - 925a2cea by David Waern at 2012-07-23T16:50:40+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.6 Conflicts: src/Haddock/InterfaceFile.hs - - - - - d710ef97 by David Waern at 2012-07-23T16:52:07+02:00 Bump version number. - - - - - eb0c2f83 by David Waern at 2012-07-23T16:57:58+02:00 Update CHANGES. - - - - - b3f56943 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Hide "internal" instances This fixes haskell/haddock#37 (http://trac.haskell.org/haddock/ticket/37) Precisely, we show an instance iff its class and all the types are exported by non-hidden modules. - - - - - a70aa412 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Tests for hiding instances (#37) - - - - - c0f4aa58 by Simon Hengel at 2012-07-27T13:00:13+03:00 Add an other test for hiding instances (#37) - - - - - a7ed6268 by Ian Lynagh at 2012-08-07T14:48:13+01:00 Follow changes in GHC - - - - - 0ab30d38 by Ian Lynagh at 2012-08-13T22:12:27+01:00 Improve haddock memory usage - - - - - 0eaa4e30 by Ian Lynagh at 2012-08-13T23:58:46+01:00 Improve haddock memory usage - - - - - 659d26cf by Ian Lynagh at 2012-08-14T13:16:48+01:00 Remove some temporary pragmas I accidentally recorded - - - - - d97fceb6 by Simon Hengel at 2012-08-25T13:19:34+02:00 Add missing dependency to library - - - - - 4c910697 by Simon Hengel at 2012-08-28T07:39:14+02:00 Move .ghci to project root - - - - - fc3c601a by Simon Hengel at 2012-08-28T07:39:14+02:00 accept.hs: Ignore some files - - - - - 1af9b984 by Simon Hengel at 2012-08-28T07:40:04+02:00 Update reference renderings (bump version) - - - - - 980dc253 by Simon Hengel at 2012-08-28T07:40:32+02:00 Update reference renderings (remove links for ()) - - - - - 33651dbf by Simon Hengel at 2012-08-28T07:41:50+02:00 Update documentation of `runInteractiveProcess` in reference rendering - - - - - 7ab25078 by David Waern at 2012-09-07T10:38:50+02:00 Merge branch 'hiddenInstances2' of http://github.com/feuerbach/haddock into ghc-7.6 - - - - - c3de3a4b by David Waern at 2012-09-07T14:29:27+02:00 Follow changes in GHC. - - - - - 298c43ac by David Waern at 2012-09-07T14:59:24+02:00 Update CHANGES. - - - - - e797993a by David Waern at 2012-09-07T15:21:30+02:00 Update ANNOUNCE. - - - - - d0b44790 by David Waern at 2012-09-07T15:22:43+02:00 Merge branch 'hidden-instances' into ghc-7.6 - - - - - 41a4adc8 by Simon Hengel at 2012-09-08T12:08:37+02:00 Update doc/README - - - - - 71ad1040 by Simon Hengel at 2012-09-08T12:17:17+02:00 Add documentation for URL labels - - - - - 9bb41afd by Simon Peyton Jones at 2012-09-20T18:14:26+01:00 Follow data type changes in the tc-untouchables branch Relating entirely to SynTyConRhs - - - - - b8139bfa by Simon Hengel at 2012-09-21T14:24:16+02:00 Disable Unicode test for now - - - - - a5fafdd7 by Simon Hengel at 2012-09-21T14:35:45+02:00 Update TypeOperators test for GHC 7.6.1 Type operators can't be used as type variables anymore! - - - - - 6ccf0025 by Simon Hengel at 2012-09-21T16:02:24+02:00 Remove (Monad (Either e)) instance from ref. rendering of CrossPackageDocs I do not really understand why the behavior changed, so I'll open a ticket, so that we can further investigate. - - - - - b5c6c138 by Ian Lynagh at 2012-09-27T02:00:57+01:00 Follow changes in GHC build system - - - - - b98eded0 by David Waern at 2012-09-27T15:37:02+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 76cc2051 by David Waern at 2012-09-27T15:48:19+02:00 Update hidden instances tests. - - - - - aeaa1c59 by David Waern at 2012-09-28T10:21:32+02:00 Make API buildable with GHC 7.6. - - - - - d76be1b0 by Simon Peyton Jones at 2012-09-28T15:57:05+01:00 Merge remote-tracking branch 'origin/master' into tc-untouchables - - - - - a1922af8 by David Waern at 2012-09-28T19:50:20+02:00 Fix spurious superclass constraints bug. - - - - - bc41bdbb by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove old examples - - - - - bed7d3dd by Simon Hengel at 2012-10-01T11:30:51+02:00 Adapt parsetests for GHC 7.6.1 - - - - - dcdb22bb by Simon Hengel at 2012-10-01T11:30:51+02:00 Add test-suite section for parsetests to cabal file + get rid of HUnit dependency - - - - - 1e5263c9 by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove test flag from cabal file This was not really used. - - - - - 4beee98b by David Waern at 2012-09-28T23:42:28+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 11dd2256 by Ian Lynagh at 2012-10-03T16:17:35+01:00 Follow change in GHC build system - - - - - fbd77962 by Simon Hengel at 2012-10-03T18:49:40+02:00 Remove redundant dependency from cabal file - - - - - 09218989 by Simon Hengel at 2012-10-04T16:03:05+02:00 Fix typo - - - - - 93a2d5f9 by Simon Hengel at 2012-10-04T16:11:41+02:00 Remove trailing whitespace from cabal file - - - - - c8b46cd3 by Simon Hengel at 2012-10-04T16:12:17+02:00 Export Haddock's main entry point from library - - - - - b411e77b by Simon Hengel at 2012-10-04T16:29:46+02:00 Depend on library for executable The main motivation for this is to increase build speed. In GHC's source tree the library is not build, but all modules are now required for the executable, so that GHC's validate will now detect build failures for the library. - - - - - f8f0979f by Simon Hengel at 2012-10-05T00:32:57+02:00 Set executable flag for Setup.lhs - - - - - dd045998 by Simon Hengel at 2012-10-07T16:44:06+02:00 Extend rather than set environment when running HTML tests On some platforms (e.g. ppc64) GHC requires gcc in the path. - - - - - 7b39c3ae by Simon Hengel at 2012-10-07T17:05:45+02:00 cross-package test: re-export IsString instead of Monad There is a monad instance for Q, which is not available on platforms that do not have GHCi support. This caused CrossPackageDocs to fail on those platforms. Re-exporting IsString should test the same thing, but it works on all platforms. - - - - - 0700c605 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Fix some warnings - - - - - f78eca79 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Make -Wall proof - - - - - 6beec041 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Use listToMaybe/fromMaybe instead of safeHead/maybe - - - - - 44b8ce86 by Ian Lynagh at 2012-10-08T21:59:46+01:00 Follow changes in GHC - - - - - 6da5f702 by Simon Hengel at 2012-10-09T11:16:19+02:00 Update .ghci - - - - - 9ac1a1b9 by Kazu Yamamoto at 2012-10-09T12:45:31+02:00 Add markup support for properties - - - - - 1944cb42 by Simon Hengel at 2012-10-09T12:45:31+02:00 Simplify lexing/parsing of properties In contrast to what we do for examples, we do not really need to capture the "prompt" here. - - - - - bffd8e62 by Simon Hengel at 2012-10-09T13:40:14+02:00 Add HTML test for properties - - - - - 2fe9c5cb by Simon Hengel at 2012-10-09T13:40:21+02:00 Add unit tests for properties - - - - - 874e361b by Simon Hengel at 2012-10-09T13:40:33+02:00 Bump interface version - - - - - 2506cc37 by Simon Hengel at 2012-10-09T15:15:04+02:00 Fix parser bug - - - - - 743d2b7d by Simon Hengel at 2012-10-09T15:31:06+02:00 Allow to load interface files with compatible versions - - - - - 981a1660 by Simon Hengel at 2012-10-10T10:32:05+02:00 Export more types from Documentation.Haddock (fixes haskell/haddock#216) - - - - - dff7dc76 by Simon Hengel at 2012-10-10T11:15:19+02:00 Update ANNOUNCE and CHANGES - - - - - edd2bb01 by Simon Hengel at 2012-10-10T11:22:50+02:00 Bump version - - - - - 5039163b by Simon Hengel at 2012-10-10T13:56:04+02:00 Fix typo in documentation - - - - - e4ce34da by Simon Hengel at 2012-10-10T14:28:35+02:00 Add documentation for properties - - - - - 9555ebca by Simon Hengel at 2012-10-11T10:49:04+02:00 Remove redundant if-defs, more source documentation - - - - - 87aa67e1 by Simon Hengel at 2012-10-11T12:32:51+02:00 Adapt cabal file - - - - - c44c1dee by Simon Hengel at 2012-10-11T12:41:58+02:00 Require ghc 7.6 - - - - - 8383bc34 by Simon Hengel at 2012-10-11T12:50:24+02:00 Bump version - - - - - 1030eb38 by Simon Hengel at 2012-10-11T12:55:44+02:00 Update ANNOUNCE and CHANGES - - - - - 74955088 by Simon Hengel at 2012-10-12T09:49:31+02:00 Improve note about `binaryInterfaceVersion` (thanks David) - - - - - ee30f6b7 by Simon Hengel at 2012-10-13T13:40:59+02:00 Update version in html tests, rpm spec file, and user manual - - - - - f2861f18 by Simon Hengel at 2012-10-13T14:40:33+02:00 Remove unused MonadFix constraint - - - - - dfdf1a74 by Simon Hengel at 2012-10-13T15:15:38+02:00 Minor code simplification - - - - - 4ecd1e70 by Simon Hengel at 2012-10-13T15:33:43+02:00 Increase code locality - - - - - f7df5cc9 by Simon Hengel at 2012-10-13T16:03:12+02:00 Minor code simplification - - - - - e737eb6e by Simon Hengel at 2012-10-13T19:03:04+02:00 Handle HsExplicitListTy in renameer (fixes haskell/haddock#213) - - - - - c2dc8f17 by Simon Hengel at 2012-10-13T20:46:31+02:00 Better error messages - - - - - 14d48b4c by Simon Hengel at 2012-10-14T00:21:07+02:00 Simplify RnM type - - - - - 6c2cc547 by Simon Hengel at 2012-10-14T00:23:35+02:00 Simplify lookupRn - - - - - bc77ce85 by Simon Hengel at 2012-10-14T01:51:32+02:00 Organize unite tests hierarchically - - - - - 2306d117 by Simon Hengel at 2012-10-14T10:34:58+02:00 Handle more cases in renameType - - - - - 8a864203 by Simon Hengel at 2012-10-14T11:47:59+02:00 Add mini_HiddenInstances.html.ref and mini_HiddenInstancesB.html.ref - - - - - 3a978eca by Simon Hengel at 2012-10-14T11:49:28+02:00 Add /tests/html-tests/output/ to .gitignore - - - - - db18888a by Simon Hengel at 2012-10-14T13:38:21+02:00 Allow haddock markup in deprecation messages - - - - - e7cfee9f by Simon Hengel at 2012-10-14T14:00:23+02:00 If parsing of deprecation message fails, include it verbatim - - - - - 242a85be by Simon Hengel at 2012-10-14T14:13:24+02:00 Add description for PruneWithWarning test - - - - - 43d33df1 by Simon Hengel at 2012-10-14T15:40:53+02:00 Minor formatting change - - - - - 22768c44 by Simon Hengel at 2012-10-14T16:03:43+02:00 Properly handle deprecation messages for re-exported things (fixes haskell/haddock#220) - - - - - cb4b9111 by Simon Hengel at 2012-10-14T17:30:28+02:00 Add build artifacts for documentation to .gitignore - - - - - 854cd8de by Simon Hengel at 2012-10-14T23:34:51+02:00 unit-tests: Improve readability Add IsString instance for (Doc RdrName) + use <> instead of DocAppend. - - - - - c4446d54 by Simon Hengel at 2012-10-14T23:37:21+02:00 unit-tests: Minor refactoring Rename parse to parseParas. - - - - - 04f2703c by Simon Hengel at 2012-10-15T00:36:42+02:00 Fix typo - - - - - 3d109e44 by Simon Hengel at 2012-10-15T10:30:07+02:00 Add description for DeprecatedReExport test - - - - - 84f0985c by Simon Hengel at 2012-10-15T14:54:19+02:00 Move resources to /resources directory - - - - - a5de7ca6 by Simon Hengel at 2012-10-15T15:46:18+02:00 Move HTML tests to directory /html-test/ - - - - - e21f727d by Simon Hengel at 2012-10-15T19:32:42+02:00 Move HTML reference renderings to /html-test/ref/ - - - - - 3a3c6c75 by Simon Hengel at 2012-10-15T19:32:42+02:00 Copy css, images, etc. on accept - - - - - 40ead6dc by Simon Hengel at 2012-10-15T19:32:42+02:00 Move unit tests to /test directory - - - - - 99a28231 by Simon Hengel at 2012-10-15T19:32:42+02:00 Fix Setup.lhs /usr/bin/runhaskell is not installed on all systems. - - - - - 95faf45e by Simon Hengel at 2012-10-15T19:32:42+02:00 Make test management scripts more robust * They are now independent from the current directory, and hence can be called from everywhere * On UNIX/Linux they can now be run as scripts - - - - - 027aaa2d by Simon Hengel at 2012-10-15T19:53:40+02:00 Add 'dev' flag to cabal file, that builds without -O2 That way --disable-optimization can be used, which decreases build time considerably. - - - - - e0266ede by Simon Hengel at 2012-10-15T20:03:43+02:00 Add test case for "spurious superclass constraints bug" - - - - - 52a2aa92 by Simon Hengel at 2012-10-15T20:28:55+02:00 Adapt accept.lhs, so that it ignores more index files - - - - - 53530781 by Simon Hengel at 2012-10-15T20:49:39+02:00 Rename html-test/runtests.lhs to html-test/run.lhs - - - - - 84518797 by Simon Hengel at 2012-10-15T20:49:39+02:00 Move source files for HTML tests to html-test/src - - - - - a911dc6c by Simon Hengel at 2012-10-15T20:49:39+02:00 Adapt output directory for HTML tests - - - - - d3c15857 by Ian Lynagh at 2012-10-16T16:54:43+01:00 Follow dopt->gopt rename - - - - - 956665a5 by Simon Hengel at 2012-10-18T08:42:48+02:00 Update html-test/README - - - - - 903b1029 by Simon Hengel at 2012-10-18T08:50:26+02:00 Use markdown for html-test/README - - - - - 150b4d63 by Ian Lynagh at 2012-10-18T16:36:00+01:00 Follow changes in GHC: 'flags' has been renamed 'generalFlags' - - - - - 41e04ff9 by Simon Hengel at 2012-11-28T09:54:35+01:00 Export missing types from Documentation.Haddock - - - - - 9be59237 by Ian Lynagh at 2012-11-30T23:20:47+00:00 Update dependencies - - - - - e06842f5 by Simon Hengel at 2012-12-07T20:58:05+01:00 Bump version - - - - - e3dbede0 by Simon Hengel at 2012-12-07T20:58:05+01:00 Add missing test files to cabal file (fixes haskell/haddock#230) - - - - - ee0dcca7 by Simon Hengel at 2012-12-07T20:58:05+01:00 Update CHANGES - - - - - 51601bdb by Simon Peyton Jones at 2012-12-19T17:28:35+00:00 Track changes in UNPACK pragma stuff - - - - - f2573bc1 by Richard Eisenberg at 2012-12-21T20:56:25-05:00 Implement overlapping type family instances. An ordered, overlapping type family instance is introduced by 'type instance where', followed by equations. See the new section in the user manual (7.7.2.2) for details. The canonical example is Boolean equality at the type level: type family Equals (a :: k) (b :: k) :: Bool type instance where Equals a a = True Equals a b = False A branched family instance, such as this one, checks its equations in order and applies only the first the matches. As explained in the note [Instance checking within groups] in FamInstEnv.lhs, we must be careful not to simplify, say, (Equals Int b) to False, because b might later unify with Int. This commit includes all of the commits on the overlapping-tyfams branch. SPJ requested that I combine all my commits over the past several months into one monolithic commit. The following GHC repos are affected: ghc, testsuite, utils/haddock, libraries/template-haskell, and libraries/dph. Here are some details for the interested: - The definition of CoAxiom has been moved from TyCon.lhs to a new file CoAxiom.lhs. I made this decision because of the number of definitions necessary to support BranchList. - BranchList is a GADT whose type tracks whether it is a singleton list or not-necessarily-a-singleton-list. The reason I introduced this type is to increase static checking of places where GHC code assumes that a FamInst or CoAxiom is indeed a singleton. This assumption takes place roughly 10 times throughout the code. I was worried that a future change to GHC would invalidate the assumption, and GHC might subtly fail to do the right thing. By explicitly labeling CoAxioms and FamInsts as being Unbranched (singleton) or Branched (not-necessarily-singleton), we make this assumption explicit and checkable. Furthermore, to enforce the accuracy of this label, the list of branches of a CoAxiom or FamInst is stored using a BranchList, whose constructors constrain its type index appropriately. I think that the decision to use BranchList is probably the most controversial decision I made from a code design point of view. Although I provide conversions to/from ordinary lists, it is more efficient to use the brList... functions provided in CoAxiom than always to convert. The use of these functions does not wander far from the core CoAxiom/FamInst logic. BranchLists are motivated and explained in the note [Branched axioms] in CoAxiom.lhs. - The CoAxiom type has changed significantly. You can see the new type in CoAxiom.lhs. It uses a CoAxBranch type to track branches of the CoAxiom. Correspondingly various functions producing and consuming CoAxioms had to change, including the binary layout of interface files. - To get branched axioms to work correctly, it is important to have a notion of type "apartness": two types are apart if they cannot unify, and no substitution of variables can ever get them to unify, even after type family simplification. (This is different than the normal failure to unify because of the type family bit.) This notion in encoded in tcApartTys, in Unify.lhs. Because apartness is finer-grained than unification, the tcUnifyTys now calls tcApartTys. - CoreLinting axioms has been updated, both to reflect the new form of CoAxiom and to enforce the apartness rules of branch application. The formalization of the new rules is in docs/core-spec/core-spec.pdf. - The FamInst type (in types/FamInstEnv.lhs) has changed significantly, paralleling the changes to CoAxiom. Of course, this forced minor changes in many files. - There are several new Notes in FamInstEnv.lhs, including one discussing confluent overlap and why we're not doing it. - lookupFamInstEnv, lookupFamInstEnvConflicts, and lookup_fam_inst_env' (the function that actually does the work) have all been more-or-less completely rewritten. There is a Note [lookup_fam_inst_env' implementation] describing the implementation. One of the changes that affects other files is to change the type of matches from a pair of (FamInst, [Type]) to a new datatype (which now includes the index of the matching branch). This seemed a better design. - The TySynInstD constructor in Template Haskell was updated to use the new datatype TySynEqn. I also bumped the TH version number, requiring changes to DPH cabal files. (That's why the DPH repo has an overlapping-tyfams branch.) - As SPJ requested, I refactored some of the code in HsDecls: * splitting up TyDecl into SynDecl and DataDecl, correspondingly changing HsTyDefn to HsDataDefn (with only one constructor) * splitting FamInstD into TyFamInstD and DataFamInstD and splitting FamInstDecl into DataFamInstDecl and TyFamInstDecl * making the ClsInstD take a ClsInstDecl, for parallelism with InstDecl's other constructors * changing constructor TyFamily into FamDecl * creating a FamilyDecl type that stores the details for a family declaration; this is useful because FamilyDecls can appear in classes but other decls cannot * restricting the associated types and associated type defaults for a * class to be the new, more restrictive types * splitting cid_fam_insts into cid_tyfam_insts and cid_datafam_insts, according to the new types * perhaps one or two more that I'm overlooking None of these changes has far-reaching implications. - The user manual, section 7.7.2.2, is updated to describe the new type family instances. - - - - - f788d0fb by Simon Peyton Jones at 2012-12-23T15:49:58+00:00 Track changes in HsBang - - - - - ca460a0c by Simon Peyton Jones at 2012-12-23T15:50:28+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - f078fea6 by Simon Peyton Jones at 2013-01-02T08:33:13+00:00 Use InstEnv.instanceSig rather than instanceHead (name change) - - - - - 88e41305 by Simon Peyton Jones at 2013-01-14T17:10:27+00:00 Track change to HsBang type - - - - - e1ad4e19 by Kazu Yamamoto at 2013-02-01T11:59:24+09:00 Merge branch 'ghc-7.6' into ghc-7.6-merge-2 Conflicts: haddock.cabal src/Haddock/Interface/AttachInstances.hs src/Haddock/Interface/Create.hs src/Haddock/Interface/LexParseRn.hs src/Haddock/InterfaceFile.hs src/Haddock/Types.hs Only GHC HEAD can compile this. GHC 7.6.x cannot compile this. Some test fail. - - - - - 62bec012 by Kazu Yamamoto at 2013-02-06T11:12:28+09:00 Using tcSplitSigmaTy in instanceHead' (FIXME is resolved.) - - - - - 013fd2e4 by Kazu Yamamoto at 2013-02-06T17:56:21+09:00 Refactoring instanceHead'. - - - - - 3148ce0e by Kazu Yamamoto at 2013-02-07T17:45:10+09:00 Using new syntax in html-test/src/GADTRecords.hs. - - - - - 626dabe7 by Gabor Greif at 2013-02-15T22:42:01+01:00 Typo - - - - - 1eb667ae by Ian Lynagh at 2013-02-16T17:02:07+00:00 Follow changes in base - - - - - 3ef8253a by Ian Lynagh at 2013-03-01T23:23:57+00:00 Follow changes in GHC's build system - - - - - 1a265a3c by Ian Lynagh at 2013-03-03T23:12:07+00:00 Follow changes in GHC build system - - - - - 69941c79 by Max Bolingbroke at 2013-03-10T09:38:28-07:00 Use Alex 3's Unicode support to properly lex source files as UTF-8 Signed-off-by: David Waern <david.waern at gmail.com> - - - - - ea687dad by Simon Peyton Jones at 2013-03-15T14:16:10+00:00 Adapt to tcRnGetInfo returning family instances too This API change was part of the fix to Trac haskell/haddock#4175. But it offers new information to Haddock: the type-family instances, as well as the class instances, of this type. This patch just drops the new information on the floor, but there's an open opportunity to use it in the information that Haddock displays. - - - - - 971a30b0 by Andreas Voellmy at 2013-05-19T20:47:39+01:00 Fix for haskell/haddock#7879. Changed copy of utils/haddock/html/resources/html to use "cp -RL" rather than "cp -R". This allows users to run validate in a build tree, where the build tree was setup using lndir with a relative path to the source directory. - - - - - 31fb7694 by Ian Lynagh at 2013-05-19T20:47:49+01:00 Use "cp -L" when making $(INPLACE_LIB)/latex too - - - - - e9952233 by Simon Hengel at 2013-06-01T18:06:50+02:00 Add -itest to .ghci - - - - - b06873b3 by Mateusz Kowalczyk at 2013-06-01T18:06:50+02:00 Workaround for a failing build with --enable-tests. - - - - - e7858d16 by Simon Hengel at 2013-06-01T19:29:28+02:00 Fix broken test - - - - - 0690acb1 by Richard Eisenberg at 2013-06-21T14:08:25+01:00 Updates to reflect changes in HsDecls to support closed type families. - - - - - 7fd347ec by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 53ed81b6 by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 931c4f4f by Richard Eisenberg at 2013-07-24T13:15:59+01:00 Remove (error "synifyKind") to use WithinType, to allow haddock to process base. - - - - - 55a9c804 by Richard Eisenberg at 2013-08-02T15:54:55+01:00 Changes to reflect changes in GHC's type HsTyVarBndr - - - - - b6e9226c by Mathieu Boespflug at 2013-08-04T10:39:43-07:00 Output Copright and License keys in Xhtml backend. This information is as relevant in the documentation as it is in the source files themselves. Signed-off-by: David Waern <david.waern at gmail.com> - - - - - 4c66028a by David Waern at 2013-08-04T15:27:36-07:00 Bump interface file version. - - - - - 67340163 by David Waern at 2013-08-09T16:12:51-07:00 Update tests. - - - - - 2087569b by Mateusz Kowalczyk at 2013-08-25T09:24:13+02:00 Add spec tests. This adds tests for all elements we can create during regular parsing. This also adds tests for text with unicode in it. - - - - - 97f36a11 by Mateusz Kowalczyk at 2013-08-27T06:59:12+01:00 Fix ticket haskell/haddock#247. I do the same thing that the XHTML backend does: give these no special treatment and just act as if they are regular functions. - - - - - 60681b4f by Mateusz Kowalczyk at 2013-08-27T21:22:48+02:00 LaTeX tests setup - - - - - fa4c27b2 by Mateusz Kowalczyk at 2013-09-02T23:21:43+01:00 Fixes haskell/haddock#253 - - - - - 1a202490 by Mateusz Kowalczyk at 2013-09-03T01:12:50+01:00 Use Hspec instead of nanospec This is motivated by the fact that Haddock tests are not ran by the GHC's ‘validate’ script so we're pretty liberal on dependencies in that area. Full Hspec gives us some nice features such as Quickcheck integration. - - - - - 8cde3b20 by David Luposchainsky at 2013-09-08T07:27:28-05:00 Fix AMP warnings Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - d10661f2 by Herbert Valerio Riedel at 2013-09-11T15:15:01+02:00 Update Git repo URL in `.cabal` file - - - - - 16a44eb5 by Richard Eisenberg at 2013-09-17T09:34:26-04:00 Revision to reflect new role annotation syntax in GHC. - - - - - 4b9833b9 by Herbert Valerio Riedel at 2013-09-18T10:15:28+02:00 Add missing `traverse` method for `GenLocated` As `Traversable` needs at least one of `traverse` or `sequenceA` to be overridden. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - b71fed5d by Simon Hengel at 2013-09-18T22:43:34+02:00 Add test helper - - - - - 4fc1ea86 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#231 - - - - - 435872f6 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#256 We inject -dynamic-too into flags before we run all our actions in the GHC monad. - - - - - b8b24abb by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Add new field to DynFlags - - - - - 49558795 by Simon Hengel at 2013-09-18T22:43:35+02:00 Fallback to ./resources when Cabal data is not found (so that themes are found during development) - - - - - bf79d05c by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Fixes haskell/haddock#5 - - - - - e1baebc2 by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Print missing documentation. Fixes haskell/haddock#258. - - - - - 02ea74de by Austin Seipp at 2013-10-09T10:52:22-05:00 Don't consider StaticFlags when parsing arguments. Instead, discard any static flags before parsing the command line using GHC's DynFlags parser. See http://ghc.haskell.org/trac/ghc/ticket/8276 Based off a patch from Simon Hengel. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 704fd5bb by Simon Hengel at 2013-11-09T00:15:13+01:00 Update HTML tests - - - - - f9fed49e by Simon Hengel at 2013-11-10T18:43:58+01:00 Bump version - - - - - 97ae1999 by Simon Peyton Jones at 2013-11-25T17:25:14+00:00 Track changes in HsSpliceTy data constructor - - - - - 59ad8268 by Simon Peyton Jones at 2014-01-10T18:17:43+00:00 Adapt to small change in Pretty's exports - - - - - 8b12e6aa by Simon Hengel at 2014-01-12T14:48:35-06:00 Some code simplification by using traverse - - - - - fc5ea9a2 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix warnings in test helper - - - - - 6dbb3ba5 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Add ByteString version of Attoparsec - - - - - 968d7774 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 One pass parser and tests. We remove the HTML test as it is no longer necessary. We cover the test case in spec tests and other HTML tests but keeping this around fails: this is because the new parser has different semantics there. In fact, I suspect the original behaviour was a bug that wasn't caught/fixed but simply included as-is during the testing. - - - - - 37a07c9c by Simon Hengel at 2014-01-12T14:48:35-06:00 Rename Haddock.ParseSpec to Haddock.ParserSpec - - - - - f0f68fe9 by Simon Hengel at 2014-01-12T14:48:35-06:00 Don't append newline to parseString input We also check that we have parsed everything with endOfInput. - - - - - 95d60093 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix totality, unicode, examples, paragraph parsing Also simplify specs and parsers while we're at it. Some parsers were made more generic. This commit is a part of GHC pre-merge squash, email fuuzetsu at fuuzetsu.co.uk if you need the full commit history. - - - - - 7d99108c by Simon Hengel at 2014-01-12T14:48:35-06:00 Update acceptance tests - - - - - d1b59640 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Support for bold. Conflicts: src/Haddock/Backends/Hoogle.hs src/Haddock/Interface/Rename.hs src/Haddock/Parser.hs - - - - - 4b412b39 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Allow for headings inside function documentation. LaTeX will treat the h3-h6 headings the same as we'd have to hack the style file heavily otherwise and it would make the headings tiny anyway. Hoogle upstream said they will put in the functionality on their end. Conflicts: src/Haddock/Interface/Rename.hs src/Haddock/Types.hs test/Haddock/ParserSpec.hs - - - - - fdcca428 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Per-module extension flags and language listing. Any extensions that are not enabled by a used language (Haskell2010 &c) will be shown. Furthermore, any implicitly enabled are also going to be shown. While we could eliminate this either by using the GHC API or a dirty hack, I opted not to: if a user doesn't want the implied flags to show, they are recommended to use enable extensions more carefully or individually. Perhaps this will encourage users to not enable the most powerful flags needlessly. Enabled with show-extensions. Conflicts: src/Haddock/InterfaceFile.hs - - - - - 368942a2 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Bump interface version There were some breaking changes over the last few patches so we bump the interface version. This causes a big problem with testing: 1. To generate cross package docs, we first need to generate docs for the package used. 2. To generate package docs with new interface version, we need to use Haddock which has the version bumped. 3. To get Haddock with the version bump, we first need to test cross package docs 4. GOTO 1 So the problem is the chicken and the egg problem. It seems that the only solution would be to generate some interface files on the fly but it is non-trivial. To run this test, you'll have to: * build Haddock without the test (make sure everything else passes) * rebuild the packages used in the test with your shiny new binary making sure they are visible to Haddock * remove the ‘_hidden’ suffix and re-run the tests Note: because the packages currently used for this test are those provided by GHC, it's probably non-trivial to just re-build them. Preferably something less tedious to rebuild should be used and something that is not subject to change. - - - - - 124ae7a9 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow for nesting of paragraphs under lists. The nesting rules are similar to Markdown's with the exception that we can not simply indent the first line of a hard wrapped indented paragraph and have it treated as if it was fully indented. The reason is differences in markup as some of our constructs care about whitespace while others just swallow everything up so it's just a lot easier to not bother with it rather than making arbitrary rules. Note that we now drop trailing for string entities inside of lists. They weren't needed and it makes the output look uniform whether we use a single or double newline between list elements. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - c7913535 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow escaping in URLs and pictures. Some tests were moved under parseString as they weren't about paragraph level markup. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - 32326680 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update documentation. - - - - - fbef6406 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update maintainer - - - - - b40e82f4 by Mateusz Kowalczyk at 2014-01-13T02:39:25-06:00 Fixes haskell/haddock#271 Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - f4eafbf8 by Gergő Érdi at 2014-01-19T15:35:16-06:00 Support for -XPatternSynonyms Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - a8939591 by Austin Seipp at 2014-01-29T08:09:04-06:00 Update CPP check for __GLASGOW_HASKELL__ Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 30d7e9d5 by Gergő Érdi at 2014-01-31T00:15:01+08:00 <+>: Don't insert a space when concatenating empty nodes - - - - - a25ccd4d by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Fix @ code blocks In cases where we had some horizontal space before the closing ‘@’, the parser would not accept the block as a code block and we'd get ugly output. - - - - - 0f67305a by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Update tests This updates tests due to Haddock Trac haskell/haddock#271 fix and due to removal of TypeHoles as an extension from GHC. - - - - - 157322a7 by Gergő Érdi at 2014-01-31T01:03:17+08:00 Handle infix vs prefix names correctly everywhere, by explicitly specifying the context The basic idea is that "a" and "+" are either pretty-printed as "a" and "(+)" or "`a`" and "+" - - - - - aa6d9685 by Mateusz Kowalczyk at 2014-01-30T17:21:50+00:00 Correct whitespace in ‘hidden’ test for <+> change - - - - - 121872f0 by Mateusz Kowalczyk at 2014-02-09T17:59:12+00:00 Document module header. Fixes Haddock Trac haskell/haddock#270. - - - - - e3253746 by Mateusz Kowalczyk at 2014-02-10T21:37:48+00:00 Insert a space between module link and description Fixes Haddock Trac haskell/haddock#277. - - - - - 771d2384 by Mateusz Kowalczyk at 2014-02-10T23:27:21+00:00 Ensure a space between type signature and ‘Source’ This is briefly related to Haddock Trac haskell/haddock#249 and employs effectively the suggested fix _but_ it doesn't actually fix the reported issue. This commit simply makes copying the full line a bit less of a pain. - - - - - 8cda9eff by nand at 2014-02-11T15:48:30+00:00 Add support for type/data families This adds support for type/data families with their respective instances, as well as closed type families and associated type/data families. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 3f22c510 by nand at 2014-02-11T15:53:50+00:00 Improve display of poly-kinded type operators This now displays them as (==) k a b c ... to mirror GHC's behavior, instead of the old (k == a) b c ... which was just wrong. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - effb2d6b by nand at 2014-02-11T15:56:50+00:00 Add test case for PatternSynonyms This just tests various stuff including poly-kinded patterns and operator patterns to make sure the rendering isn't broken. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - b38faf0d by Niklas Haas at 2014-02-13T21:53:32+00:00 Get rid of re-implementation of sortBy I have no idea what this was doing lying around here, and due to the usage of tuples it's actually slower, too. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - ac1e0413 by Mateusz Kowalczyk at 2014-02-13T23:57:16+00:00 Only warn about missing docs when docs are missing This fixes the ‘Missing documentation for…’ message for modules with 100% coverage. - - - - - cae2e36a by Niklas Haas at 2014-02-15T21:56:18+00:00 Add test case for inter-module type/data family instances These should show up in every place where the class is visible, and indeed they do right now. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 8bea5c3a by Mateusz Kowalczyk at 2014-02-19T05:11:34+00:00 Use a bespoke data type to indicate fixity This deals with what I imagine was an ancient TODO and makes it much clearer what the argument actually does rather than having the user chase down the comment. - - - - - 5b52d57c by Niklas Haas at 2014-02-22T21:31:03+01:00 Strip a single leading space from bird tracks (#201) This makes bird tracks in the form > foo > bar > bat parse as if they had been written as >foo >bar >bat ie. without the leading whitespace in front of every line. Ideally we also want to look into how leading whitespace affects code blocks written using the @ @ syntax, which are currently unaffected by this patch. - - - - - 5a1315a5 by Simon Hengel at 2014-02-22T21:55:35+01:00 Turn a source code comment into specs - - - - - 784cfe58 by Mateusz Kowalczyk at 2014-02-23T05:02:22+00:00 Update test case for lifted GADT type rendering The parsing of these seems to have been fixed by GHC folk and it now renders differently. IMHO it now renders in a better way so I'm updating the test to reflect this. - - - - - c3c88c2f by Mateusz Kowalczyk at 2014-02-23T06:37:14+00:00 Don't shadow ‘strip’. -Wall complains - - - - - 293031d8 by Niklas Haas at 2014-02-23T15:21:52+01:00 Make ImplicitParams render correctly (#260) This introduces a new precedence level for single contexts (because implicit param contexts always need parens around them, but other types of contexts don't necessarily, even when alone) - - - - - 4200842d by Niklas Haas at 2014-02-23T15:37:13+01:00 Lower precedence of equality constraints This drops them to the new precedence pREC_CTX, which makes single eqaulity constraints show up as (a ~ b) => ty, in line with GHC's rendering. Additional tests added to make sure other type operators render as intended. Current behavior matches GHC - - - - - b59e3227 by Niklas Haas at 2014-02-23T16:11:22+01:00 Add RankNTypes test case to ImplicitParams.hs This test actually tests what haskell/haddock#260 originally reported - I omitted the RankNTypes scenario from the original fix because I realized it's not relevant to the underlying issue and indeed, this renders as intended now. Still good to have more tests. - - - - - c373dbf7 by Mateusz Kowalczyk at 2014-02-24T06:09:54+00:00 Fix rendering of Contents when links are present Fixes Haddock Trac haskell/haddock#267. - - - - - 9ecb0e56 by Mateusz Kowalczyk at 2014-02-24T06:26:50+00:00 Fix wording in the docs - - - - - 4f4dcd8e by Mateusz Kowalczyk at 2014-02-27T03:00:33+00:00 Change rendering of duplicate record field docs See Haddock Trac haskell/haddock#195. We now change this behaviour to only rendering the documentation attached to the first instance of a duplicate field. Perhaps we could improve this by rendering the first instance that has documentation attached to it but for now, we'll stick with this. - - - - - ad8aa609 by Niklas Haas at 2014-03-08T09:43:26+01:00 Render fixity information Affects functions, type synonyms, type families, class names, data type names, constructors, data families, associated TFs/DFs, type synonyms, pattern synonyms and everything else I could think of. - - - - - 6a39c917 by Niklas Haas at 2014-03-09T07:43:39+01:00 Reorder topDeclElem to move the source/wiki links to the top They appear in the same position due to the float: right attribute but now they're always at the top of the box instead of at the bottom. - - - - - 2d34b3b4 by Niklas Haas at 2014-03-09T07:53:46+01:00 Use optLast instead of listToMaybe for sourceUrls/wikiUrls This lets you override them using eg. cabal haddock --haddock-options, which can come in handy if you want to use a different layout or URL for your source code links than cabal-install generates. - - - - - 0eff4624 by Niklas Haas at 2014-03-09T07:53:46+01:00 Differentiate between TH splices (line-links) and regular names This adds a new type of source code link, to a specific line rather than a specific declaration/name - this is used to link to the location of a TH splice that defines a certain name. Rather hefty changes throughout and still one unresolved issue (the line URLs aren't parsed from the third form of --read-interface which means they're currently restricted to same-interface links). Not sure if this issue is really worth all the hassle, especially since we could just use line links in general. This commit also contains some cleanup/clarification of the types in Haddock.Backends.Xhtml.Decl and shortens some overlong lines in the process. Notably, the Bool parameter was replaced by a Unicode type synonym to help clarify its presence in type signatures. - - - - - 66d6f77b by Niklas Haas at 2014-03-09T20:02:43+01:00 Group similar fixities together Identical fixities declared for the same line should now render using syntax like: infix 4 <, >=, >, <= - - - - - 6587f9f5 by Mateusz Kowalczyk at 2014-03-10T04:24:18+00:00 Update changelog - - - - - 7387ddad by Niklas Haas at 2014-03-11T10:26:04+01:00 Include fixity information in the Interface file This resolves fixity information not appearing across package borders. The binary file version has been increased accordingly. - - - - - ab46ef44 by Niklas Haas at 2014-03-11T10:26:04+01:00 Update changelog - - - - - 565cab6f by Niklas Haas at 2014-03-11T10:26:04+01:00 Update appearance of fixity annotations This moves them in-line with their corresponding lines, similar to a presentation envision by @hvr and described in #ghc. Redundant operator names are also omitted when no ambiguity is present. - - - - - 5d7afd67 by Niklas Haas at 2014-03-11T10:26:05+01:00 Filter family instances of hidden types Currently, this check does not extend to hidden right hand sides, although it probably should hide them in that case. - - - - - ec291b0c by Niklas Haas at 2014-03-11T10:26:05+01:00 Add documentation for --source-entity-line - - - - - 0922e581 by Niklas Haas at 2014-03-11T10:37:32+01:00 Revert "Reorder topDeclElem to move the source/wiki links to the top" This reverts commit 843c42c4179526a2ad3526e4c7d38cbf4d50001d. This change is no longer needed with the new rendering style, and it messes with copy/pasting lines. - - - - - 30618e8b by Mateusz Kowalczyk at 2014-03-11T09:41:07+00:00 Bump version to 2.15.0 - - - - - adf3f1bb by Mateusz Kowalczyk at 2014-03-11T09:41:09+00:00 Fix up some whitespace - - - - - 8905f57d by Niklas Haas at 2014-03-13T19:18:06+00:00 Hide RHS of TFs with non-exported right hand sides Not sure what to do about data families yet, since technically it would not make a lot of sense to display constructors that cannot be used by the user. - - - - - 5c44d5c2 by Niklas Haas at 2014-03-13T19:18:08+00:00 Add UnicodeSyntax alternatives for * and -> I could not find a cleaner way to do this other than checking for string equality with the given built-in types. But seeing as it's actually equivalent to string rewriting in GHC's implementation of UnicodeSyntax, it's probably fitting. - - - - - b04a63e6 by Niklas Haas at 2014-03-13T19:18:10+00:00 Display minimal complete definitions for type classes This corresponds to the new {-# MINIMAL #-} pragma present in GHC 7.8+. I also cleaned up some of the places in which ExportDecl is used to make adding fields easier in the future. Lots of test cases have been updated since they now render with minimality information. - - - - - a4a20b16 by Niklas Haas at 2014-03-13T19:18:12+00:00 Strip links from recently added html tests These were accidentally left there when the tests were originally added - - - - - d624f315 by Mateusz Kowalczyk at 2014-03-13T19:19:31+00:00 Update changelog - - - - - d27a21ac by Mateusz Kowalczyk at 2014-03-13T21:19:07+00:00 Always read in prologue files as UTF8 (#286). - - - - - 54b2fd78 by Mateusz Kowalczyk at 2014-03-13T21:28:09+00:00 Style only - - - - - fa4fe650 by Simon Hengel at 2014-03-15T09:04:18+01:00 Add Fuuzetsu maintainers field in cabal file - - - - - f83484b7 by Niklas Haas at 2014-03-15T18:20:24+00:00 Hide minimal definition for only-method classes Previously this was not covered by the All xs check since here it is not actually an All, rather a single Var n. This also adds the previously missing html-test/src/Minimal.hs. - - - - - 0099d276 by Niklas Haas at 2014-03-15T18:20:26+00:00 Fix issue haskell/haddock#281 This is a regression from the data family instances change. Data instances are now distinguished from regular lists by usage of the new class "inst", and the style has been updated to only apply to those. I've also updated the appropriate test case to test this a bit better, including GADT instances with GADT-style records. - - - - - 1f9687bd by Mateusz Kowalczyk at 2014-03-21T17:48:37+00:00 Please cabal sdist - - - - - 75542693 by Mateusz Kowalczyk at 2014-03-22T16:36:16+00:00 Drop needless --split-objs which slows us down. Involves tiny cleanup of all the dynflag bindings. Fixes haskell/haddock#292. - - - - - 31214dc3 by Herbert Valerio Riedel at 2014-03-23T18:01:01+01:00 Fix a few typos Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 0b73e638 by Mateusz Kowalczyk at 2014-03-31T05:34:36+01:00 Print kind signatures on GADTs - - - - - 2bab42f3 by Mateusz Kowalczyk at 2014-03-31T16:53:25+01:00 Add default for new PlatformConstraints field - - - - - 42647c5f by Mateusz Kowalczyk at 2014-03-31T18:29:04+01:00 Drop leading whitespace in @-style blocks. Fixes haskell/haddock#201. - - - - - 98208294 by Niklas Haas at 2014-03-31T20:09:58+02:00 Crash when exporting record selectors of data family instances This fixes bug haskell/haddock#294. This also fixes a related but never-before-mentioned bug about the display of GADT record selectors with non-polymorphic type signatures. Note: Associated data type constructors fail to show up if nothing is exported that they could be attached to. Exporting any of the data types in the instance head, or the class + data family itself, causes them to show up, but in the absence of either of these, exporting just the associated data type with the constructor itself will result in it being hidden. The only scenario I can come up that would involve this kind of situation involved OverlappingInstances, and even then it can be mitigated by just exporting the class itself, so I'm not going to solve it since the logic would most likely be very complicated. - - - - - 3832d171 by Mateusz Kowalczyk at 2014-04-01T19:07:33+01:00 Make CHANGES consistent with what's now in 2.14.2 - - - - - c386ae89 by Mateusz Kowalczyk at 2014-04-01T19:18:36+01:00 Actually bundle extra spec tests in sdist - - - - - bd57a6d3 by Mateusz Kowalczyk at 2014-04-03T21:13:48+01:00 Update test cases for GHC bug haskell/haddock#8945, Haddock haskell/haddock#188 The order of signature groups has been corrected upstream. Here we add a test case and update some existing test-cases to reflect this change. We remove grouped signature in test cases that we can (Minimal, BugDeprecated &c) so that the test is as self-contained as possible. - - - - - 708b88b1 by Mateusz Kowalczyk at 2014-04-03T21:16:07+01:00 Enforce strict GHC version in cabal file This stops people with 7.6.3 trying to install 2.15.x which clearly won't work. Unfortunately we shipped 2.14.x without realising this. - - - - - 60334f7c by Mateusz Kowalczyk at 2014-04-03T21:19:24+01:00 Initialise some new PlatformConstants fields - - - - - ea77f668 by Mateusz Kowalczyk at 2014-04-11T16:52:23+01:00 We don't actually want unicode here - - - - - 0b651cae by Mateusz Kowalczyk at 2014-04-11T18:13:30+01:00 Parse identifiers with ^ and ⋆ in them. Fixes haskell/haddock#298. - - - - - e8ad0f5f by Mateusz Kowalczyk at 2014-04-11T18:47:41+01:00 Ignore version string during HTML tests. - - - - - de489089 by Mateusz Kowalczyk at 2014-04-11T18:59:30+01:00 Update CHANGES to follow 2.14.3 - - - - - beb464a9 by Gergő Érdi at 2014-04-13T16:31:10+08:00 remove Origin flag from LHsBindsLR - - - - - cb16f07c by Herbert Valerio Riedel at 2014-04-21T17:16:50+02:00 Replace local `die` by new `System.Exit.die` Starting with GHC 7.10, System.Exit exports the new `die` which is essentially the same as Haddock.Util.die, so this commit changes Haddock.Util.die to be a simple re-export of System.Exit.die. See also https://ghc.haskell.org/trac/ghc/ticket/9016 for more details. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 9b9b23c7 by Mateusz Kowalczyk at 2014-05-03T15:40:11+02:00 Disambiguate ‘die’ in test runners. - - - - - 5d28a2b8 by Mateusz Kowalczyk at 2014-05-05T09:19:49+02:00 Prepare modules for parser split. We have to generalise the Doc (now DocH) slightly to remove the dependency on GHC-supplied type. - - - - - d3967ff3 by Mateusz Kowalczyk at 2014-05-05T11:00:41+02:00 Move parser + parser tests out to own package. We move some types out that are necessary as well and then re-export and specialise them in the core Haddock. Reason for moving out spec tests is that if we're working on the parser, we can simply work on that and we can ignore the rest of Haddock. The downside is that it's a little inconvenient if at the end of the day we want to see that everything passes. - - - - - 522a448d by Mateusz Kowalczyk at 2014-05-05T11:14:47+02:00 Move out Show and Eq instances to Types They are much more useful to the users here. - - - - - 11a6f0f2 by Mateusz Kowalczyk at 2014-05-06T13:50:31+02:00 Remove no longer necessary parser error handling. We can now drop some Maybe tests and even lets us strip an error handling monad away in a few places. - - - - - 6992c924 by Mateusz Kowalczyk at 2014-05-14T02:23:55+02:00 Please the GHC build-system. As I can not figure out how to do this properly, if we're in GHC tree, we treat the library as being the same package. If we're not in the tree, we require that the library be installed separately. - - - - - 7a8ad763 by Mateusz Kowalczyk at 2014-05-14T14:50:25+02:00 Update issue tracker URL - - - - - f616c521 by Mateusz Kowalczyk at 2014-05-14T14:53:32+02:00 Update issue tracker URL for haddock-library - - - - - 66580ded by Gergő Érdi at 2014-05-25T14:24:16+08:00 Accomodate change in PatSyn representation - - - - - 0e43b988 by Mateusz Kowalczyk at 2014-05-29T03:15:29+02:00 Revert "Accomodate change in PatSyn representation" This reverts commit 57aa591362d7c8ba21285fccd6a958629a422091. I am reverting this because I pushed it to master when it was meant to stay on a wip-branch. Sorry Gergo and everyone who had trouble due to this. - - - - - e10d7ec8 by Mateusz Kowalczyk at 2014-05-29T03:24:11+02:00 Revert "Revert "Accomodate change in PatSyn representation"" This reverts commit e110e6e70e40eed06c06676fd2e62578da01d295. Apparently as per GHC commit ac2796e6ddbd54c5762c53e2fcf29f20ea162fd5 this was actually intended. Embarrasing for me. - - - - - 5861aca9 by Mateusz Kowalczyk at 2014-06-05T19:49:27+02:00 Clear up highlighting of identifiers with ‘'’s. - - - - - d7cc420f by Simon Peyton Jones at 2014-06-06T12:41:09+01:00 Follow change in patSynSig - - - - - 938b4fd8 by Mateusz Kowalczyk at 2014-06-12T07:24:29+02:00 Slightly update the readme. Style-sheets are no longer a recent thing, dead links, old maintainers, different formats. - - - - - c7799dea by Mateusz Kowalczyk at 2014-06-18T00:05:56+02:00 Update cabal files Update repository urls, use subdir property for haddock-library and use a separate versioning scheme for haddock-library in preparation for release. - - - - - a2750b6a by Simon Hengel at 2014-06-18T11:01:18+08:00 Compatibility with older versions of base and bytestring - - - - - 009b4b03 by Simon Hengel at 2014-06-18T11:14:01+08:00 Enable travis-ci for haddock-library - - - - - 9b5862eb by Simon Hengel at 2014-06-18T11:14:01+08:00 haddock-library: Do not depend on haddock-library in test suite I think you either add src to hs-source-dirs or the library to build-depends. But doing both does not make sense (AFAICT). - - - - - fb1f3279 by Simon Hengel at 2014-06-18T11:49:05+08:00 haddock-library: Use -Wall for specs - - - - - 649340e1 by Mateusz Kowalczyk at 2014-06-18T06:58:54+02:00 Use Travis with multiple GHC versions When using HEAD, we build haddock-library directly from repository as a dependency (and thanks to --enable-tests, the tests get ran anyway). In all other cases, we manually run the tests on haddock-library only and don't test the main project. - - - - - d7eeeec2 by Mateusz Kowalczyk at 2014-06-18T07:49:04+02:00 Comment improvements + few words in cabal file - - - - - 0f8db914 by Simon Hengel at 2014-06-18T13:52:23+08:00 Use doctest to check examples in documentation - - - - - 2888a8dc by Simon Hengel at 2014-06-18T14:16:48+08:00 Remove doctest dependency (so that we can use haddock-library with doctest) - - - - - 626d5e85 by Mateusz Kowalczyk at 2014-06-18T08:41:25+02:00 Travis tweaks - - - - - 41d4f9cc by Mateusz Kowalczyk at 2014-06-18T08:58:43+02:00 Don't actually forget to install specified GHC. - - - - - c6aa512a by John MacFarlane at 2014-06-18T10:43:57-07:00 Removed reliance on LambdaCase (which breaks build with ghc 7.4). - - - - - b9b93b6f by John MacFarlane at 2014-06-18T10:54:56-07:00 Fixed haddock warnings. - - - - - a41b0ab5 by Mateusz Kowalczyk at 2014-06-19T01:20:10+02:00 Update Travis, bump version - - - - - 864bf62a by Mateusz Kowalczyk at 2014-06-25T10:36:54+02:00 Fix anchors. Closes haskell/haddock#308. - - - - - 53df91bb by Mateusz Kowalczyk at 2014-06-25T15:04:49+02:00 Drop DocParagraph from front of headers I can not remember why they were wrapped in paragraphs to begin with and it seems unnecessary now that I test it. Closes haskell/haddock#307. - - - - - 29b5f2fa by Mateusz Kowalczyk at 2014-06-25T15:17:20+02:00 Don't mangle append order for nested lists. The benefit of this is that the ‘top-level’ element of such lists is properly wrapped in <p> tags so any CSS working with these will be applied properly. It also just makes more sense. Pointed out at jgm/pandoc#1346. - - - - - 05cb6e9c by Mateusz Kowalczyk at 2014-06-25T15:19:45+02:00 Bump haddock-library to 1.1.0 for release - - - - - 70feab15 by Iavor Diatchki at 2014-07-01T03:37:07-07:00 Propagate overloading-mode for instance declarations in haddock (#9242) - - - - - d4ca34a7 by Simon Peyton Jones at 2014-07-14T16:23:15+01:00 Adapt to new definition of HsDecls.TyFamEqn This is a knock-on from the refactoring from Trac haskell/haddock#9063. I'll push the corresponding changes to GHC shortly. - - - - - f91e2276 by Edward Z. Yang at 2014-07-21T08:14:19-07:00 Track GHC PackageId to PackageKey renaming. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - b010f9ef by Edward Z. Yang at 2014-07-25T16:28:46-07:00 Track changes for module reexports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - 8b85f9f9 by Mateusz Kowalczyk at 2014-07-28T13:25:43+02:00 Catch mid-line URLs. Fixes haskell/haddock#314. - - - - - 4c613a78 by Edward Z. Yang at 2014-08-05T03:11:00-07:00 Track type signature change of lookupModuleInAllPackages Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - e80b051c by Edward Z. Yang at 2014-08-05T17:34:26+01:00 If GhcProfiled, also build Haddock profiled. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f9cccd29 by Edward Z. Yang at 2014-08-07T14:23:35+01:00 Ignore TAGS files. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 00b3af52 by Mateusz Kowalczyk at 2014-08-08T04:58:19+02:00 Update to attoparsec-0.12.1.1 There seems to be memory and speed improvement. - - - - - 5457dc71 by Mateusz Kowalczyk at 2014-08-08T18:24:02+02:00 Fix forgotten src - - - - - 3520cb04 by Mateusz Kowalczyk at 2014-08-14T20:19:07+01:00 Bump down the version for master to 2.14.4 - - - - - dc98c21b by Mateusz Kowalczyk at 2014-08-14T20:23:27+01:00 Revert "Track type signature change of lookupModuleInAllPackages" This reverts commit d59fec2c9551b5662a3507c0011e32a09a9c118f. - - - - - 3f2038c0 by Mateusz Kowalczyk at 2014-08-14T20:23:31+01:00 Revert "Track changes for module reexports." This reverts commit b99b57c0df072d12b67816b45eca2a03cb1da96d. - - - - - 56d4e49e by Mateusz Kowalczyk at 2014-08-14T20:23:42+01:00 Revert "Track GHC PackageId to PackageKey renaming." This reverts commit 8ac42d3327473939c013551750425cac191ff0fd. - - - - - 726ea3cb by Mateusz Kowalczyk at 2014-08-14T20:23:47+01:00 Revert "Adapt to new definition of HsDecls.TyFamEqn" This reverts commit cb96b4f1ed0462b4a394b9fda6612c3bea9886bd. - - - - - 61a88ff0 by Mateusz Kowalczyk at 2014-08-14T20:23:52+01:00 Revert "Propagate overloading-mode for instance declarations in haddock (#9242)" This reverts commit 8d20ca8d5a9bee73252ff2035ec45f9c03d0820c. - - - - - a32ba674 by Mateusz Kowalczyk at 2014-08-14T20:26:03+01:00 Revert "Disambiguate ‘die’ in test runners." This reverts commit dba02d6df32534aac5d257f2d28596238d248942. - - - - - f335820f by Mateusz Kowalczyk at 2014-08-14T20:26:09+01:00 Revert "Replace local `die` by new `System.Exit.die`" This reverts commit 08aa509ebac58bfb202ea79c7c41291ec280a1c5. - - - - - 107078e4 by Mateusz Kowalczyk at 2014-08-14T20:27:34+01:00 Merge branch 'reverts' This reverts any changes that were made to have Haddock compile with 7.9. When 7.10 release comes, we can simply re-apply all the patches and any patches that occur on ghc-head branch from now on. This allows us to build master with 7.8.3 - - - - - b44b3871 by Mateusz Kowalczyk at 2014-08-15T02:47:40+01:00 Fix haskell/haddock#313 by doing some list munging. I get rid of the Monoid instance because we weren't satisfying the laws. Convenience of having <> didn't outweigh the shock-factor of having it behave badly. - - - - - e1a62cde by Mateusz Kowalczyk at 2014-08-15T02:52:56+01:00 Stop testing haskell/haddock#188. Because the change is in GHC 7.9 and we now work against 7.8.3, this test no longer makes sense. We revert it until 7.10 becomes the standard version. If anything, there should be a test for this in GHC itself. - - - - - 54e8286d by Mateusz Kowalczyk at 2014-08-15T05:31:57+01:00 Add haskell/haddock#313 to CHANGES - - - - - 9df7ad5d by Simon Hengel at 2014-08-20T11:25:32+08:00 Fix warning - - - - - ee2574d6 by Simon Hengel at 2014-08-20T12:07:01+08:00 Fix travis builds - - - - - 384cf2e6 by Simon Hengel at 2014-08-20T12:14:31+08:00 Require GHC 7.8.3 - - - - - d4779863 by Simon Hengel at 2014-08-22T12:14:16+08:00 Move Haddock API to a separate package - - - - - 80f3e0e1 by Simon Hengel at 2014-08-22T14:57:38+08:00 Bump version to 2.15.0 and add version constraints - - - - - 309a94ce by Simon Hengel at 2014-08-22T15:18:06+08:00 Add deprecated compatibility module - - - - - 4d1e4e3f by Luite Stegeman at 2014-08-22T20:46:45+02:00 export things to allow customizing how the Ghc session is run - - - - - 47884591 by Luite Stegeman at 2014-08-22T20:46:51+02:00 ghc 7.8.2 compatibility - - - - - 5ea94e2c by Luite Stegeman at 2014-08-22T22:08:58+02:00 install dependencies for haddock-api on travis - - - - - 9fb845b2 by Mateusz Kowalczyk at 2014-08-23T10:09:34+01:00 Move sources under haddock-api/src - - - - - 85817dc4 by Mateusz Kowalczyk at 2014-08-23T10:10:48+01:00 Remove compat stuff - - - - - 151c6169 by Niklas Haas at 2014-08-24T08:14:10+02:00 Fix extra whitespace on signatures and update all test cases This was long overdue, now running ./accept.lhs on a clean test from master will not generate a bunch of changes. - - - - - d320e0d2 by Niklas Haas at 2014-08-24T08:14:35+02:00 Omit unnecessary foralls and fix haskell/haddock#315 This also fixes haskell/haddock#86. - - - - - bdafe108 by Mateusz Kowalczyk at 2014-08-24T15:06:46+01:00 Update CHANGES - - - - - fafa6d6e by Mateusz Kowalczyk at 2014-08-24T15:14:23+01:00 Delete few unused/irrelevant/badly-place files. - - - - - 3634923d by Duncan Coutts at 2014-08-27T13:49:31+01:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. - - - - - 539a7e70 by Herbert Valerio Riedel at 2014-08-31T11:36:32+02:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 9e3a0e5b by Mateusz Kowalczyk at 2014-08-31T12:54:43+01:00 Bump version in doc - - - - - 4a177525 by Mateusz Kowalczyk at 2014-08-31T13:01:23+01:00 Bump haddock-library version - - - - - f99c1384 by Mateusz Kowalczyk at 2014-08-31T13:05:25+01:00 Remove references to deleted files - - - - - 5e51a247 by Mateusz Kowalczyk at 2014-08-31T14:18:44+01:00 Make the doc parser not complain - - - - - 2cedb49a by Mateusz Kowalczyk at 2014-09-03T03:33:15+01:00 CONTRIBUTING file for issues - - - - - 88027143 by Mateusz Kowalczyk at 2014-09-04T00:46:59+01:00 Mention --print-missing-docs - - - - - 42f6754f by Alan Zimmerman at 2014-09-05T18:13:24-05:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e712719e by Austin Seipp at 2014-09-09T01:03:27-05:00 Fix import of 'empty' due to AMP. Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 71c29755 by Herbert Valerio Riedel at 2014-09-09T17:35:20+02:00 Bump `base` constraint for AMP - - - - - 0bf9f3ed by Mateusz Kowalczyk at 2014-09-12T19:18:32+01:00 Delete stale ANNOUNCE - - - - - cac89ee6 by Krzysztof Gogolewski at 2014-09-14T17:17:09+02:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 4d683426 by Edward Z. Yang at 2014-09-18T13:38:11-07:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 80697fd5 by Herbert Valerio Riedel at 2014-09-19T00:07:52+02:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. - - - - - c015eb70 by Herbert Valerio Riedel at 2014-09-19T00:10:36+02:00 Revert "Followup changes to addition of -fwarn-context-quantification" This reverts commit 4023817d7c0e46db012ba2eea28022626841ca9b temporarily as the respective feature hasn't landed in GHC HEAD yet, but this commit blocks later commits from being referenced in GHC HEAD. - - - - - 38ded784 by Edward Z. Yang at 2014-09-18T15:32:15-07:00 Revert "Revert "Followup changes to addition of -fwarn-context-quantification"" This reverts commit db14fd8ab4fab43694139bc203808b814eafb2dc. It's in HEAD now. - - - - - f55d59c9 by Herbert Valerio Riedel at 2014-09-26T19:18:28+02:00 Revert "Fix import of 'empty' due to AMP." This reverts commit 0cc5bc85e9fca92ab712b68a2ba2c0dd9d3d79f4 since it turns out we don't need to re-export `empty` from Control.Monad after all. - - - - - 467050f1 by David Feuer at 2014-10-09T20:07:36-04:00 Fix improper lazy IO use Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. - - - - - cc47b699 by Edward Z. Yang at 2014-10-09T21:38:19-07:00 Fix use-after-close lazy IO bug Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. Signed-off-by: David Feuer <David.Feuer at gmail.com> Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 87babcbe by Austin Seipp at 2014-10-20T20:05:27-05:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - ab259516 by Austin Seipp at 2014-10-20T20:07:01-05:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - b918093c by Mateusz Kowalczyk at 2014-10-29T03:59:39+00:00 Experimental support for collapsable headers Closes haskell/haddock#335 - - - - - 849db129 by Mateusz Kowalczyk at 2014-10-29T10:07:26+01:00 Experimental support for collapsable headers (cherry picked from commit e2ed3b9d8dfab09f1b1861dbc8e74f08e137ebcc) - - - - - a4cc4789 by Herbert Valerio Riedel at 2014-10-31T11:08:26+01:00 Collapse user-defined section by default (re haskell/haddock#335) - - - - - 9da1b33e by Yuras Shumovich at 2014-10-31T16:11:04-05:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - c625aefc by Austin Seipp at 2014-10-31T19:34:10-05:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - c7738e5e by Simon Hengel at 2014-11-02T07:25:30+08:00 Remove -fobject-code from .ghci (this slows down reloads on modifications) - - - - - d4a86e95 by Simon Hengel at 2014-11-03T09:26:11+08:00 Get rid of StandaloneDeriving - - - - - a974e311 by Simon Hengel at 2014-11-03T09:26:11+08:00 Derive more instances - - - - - 8aa0c4d7 by Simon Hengel at 2014-11-03T09:27:08+08:00 Remove unused language extensions - - - - - 3052d46a by Simon Hengel at 2014-11-03T09:30:46+08:00 Minor refactoring - - - - - 4281d3cb by Simon Hengel at 2014-11-03T09:30:46+08:00 parser: Try to parse definition lists right before text paragraphs - - - - - 8ba12bf9 by Simon Hengel at 2014-11-03T09:34:19+08:00 Add support for markdown links (closes haskell/haddock#336) - - - - - a2f8d747 by Simon Hengel at 2014-11-03T09:34:19+08:00 Allow markdown links at the beginning of a paragraph - - - - - 53b11207 by Simon Hengel at 2014-11-03T09:34:20+08:00 Update documentation - - - - - 652267c6 by Simon Hengel at 2014-11-03T09:34:20+08:00 Add support for markdown images - - - - - 9d667502 by Simon Hengel at 2014-11-03T09:34:20+08:00 Allow an optional colon after the closing bracket of definition lists This is to disambiguate them from markdown links and will be require with a future release. - - - - - 8167fc32 by Mateusz Kowalczyk at 2014-11-04T01:16:51+00:00 whitespace only - - - - - 3da62981 by Mateusz Kowalczyk at 2014-11-04T01:17:31+00:00 Fix re-exports of built-in type families Fixes haskell/haddock#310 - - - - - edc76b34 by Mateusz Kowalczyk at 2014-11-04T02:54:28+00:00 Turn some uses of error into recoverable warnings This should at the very least not abort when something weird happens. It does feel like we should have a type that carries these errors until the end however as the user might not see them unless they are printed at the end. - - - - - 0a137400 by Mateusz Kowalczyk at 2014-11-04T04:09:44+00:00 Fix warnings - - - - - d068fc21 by Mateusz Kowalczyk at 2014-11-04T21:04:07+00:00 Fix parsing of identifiers written in infix way - - - - - 1a9f2f3d by Simon Hengel at 2014-11-08T11:32:42+08:00 Minor code simplification - - - - - 6475e9b1 by Simon Hengel at 2014-11-08T17:28:33+08:00 newtype-wrap parser monad - - - - - dc1ea105 by Herbert Valerio Riedel at 2014-11-15T11:55:43+01:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - fbb1aca4 by Simon Hengel at 2014-11-16T08:51:38+08:00 State intention rather than implementation details in Haddock comment - - - - - 97851ab2 by Simon Hengel at 2014-11-16T10:20:19+08:00 (wip) Add support for @since (closes haskell/haddock#26) - - - - - 34bcd18e by Gergő Érdi at 2014-11-20T22:35:38+08:00 Update Haddock to new pattern synonym type signature syntax - - - - - 304b7dc3 by Jan Stolarek at 2014-11-20T17:48:43+01:00 Follow changes from haskell/haddock#9812 - - - - - 920f9b03 by Richard Eisenberg at 2014-11-20T16:52:50-05:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 0bfe4e78 by Alan Zimmerman at 2014-11-21T11:23:09-06:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 356ed45a by Thomas Winant at 2014-11-28T16:11:22-06:00 Support for PartialTypeSignatures - - - - - 5dc8f3b1 by Gergő Érdi at 2014-11-29T15:39:09+08:00 For pattern synonyms, render "pattern" as a keyword - - - - - fe704480 by Mateusz Kowalczyk at 2014-12-09T03:38:32+00:00 List new module in cabal file - - - - - b9ad5a29 by Mateusz Kowalczyk at 2014-12-10T00:58:24+00:00 Allow the parser to spit out meta-info Currently we only use it only for ‘since’ annotations but with these patches it should be fairly simple to add new attributes if we wish to. Closes haskell/haddock#26. It seems to work fine but due to 7.10 rush I don't have the chance to do more exhaustive testing right now. The way the meta is output (emphasis at the end of the whole comment) is fairly arbitrary and subject to bikeshedding. Note that this makes test for Bug310 fail due to interface version bump: it can't find the docs for base with this interface version so it fails. There is not much we can do to help this because it tests for ’built-in’ identifier, not something we can provide ourselves. - - - - - 765af0e3 by Mateusz Kowalczyk at 2014-12-10T01:17:19+00:00 Update doctest parts of comments - - - - - 8670272b by jpmoresmau at 2014-12-10T01:35:31+00:00 header could contain several lines Closes haskell/haddock#348 - - - - - 4f9ae4f3 by Mateusz Kowalczyk at 2014-12-12T06:22:31+00:00 Revert "Merge branch 'reverts'" This reverts commit 5c93cc347773c7634321edd5f808d5b55b46301f, reversing changes made to 5b81a9e53894d2ae591ca0c6c96199632d39eb06. Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - e974ac94 by Duncan Coutts at 2014-12-12T06:26:11+00:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. Conflicts: haddock-api/src/Haddock.hs - - - - - 2f3a2365 by Herbert Valerio Riedel at 2014-12-12T06:26:51+00:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 1dbd6390 by Alan Zimmerman at 2014-12-12T06:32:07+00:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - bb6ff1f4 by Mateusz Kowalczyk at 2014-12-12T06:35:07+00:00 Bump ‘base’ constraint Follows the similar commit made on ghc-head branch - - - - - 466fe4ab by Krzysztof Gogolewski at 2014-12-12T06:37:42+00:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 97e080c9 by Edward Z. Yang at 2014-12-12T06:39:35+00:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: haddock-api/src/Haddock/ModuleTree.hs - - - - - 20b2af56 by Herbert Valerio Riedel at 2014-12-12T06:42:50+00:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. Conflicts: haddock-library/src/Documentation/Haddock/Parser.hs - - - - - b3ad269d by Austin Seipp at 2014-12-12T06:44:14+00:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 072df0dd by Austin Seipp at 2014-12-12T06:45:01+00:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - dbb9294a by Herbert Valerio Riedel at 2014-12-12T06:46:17+00:00 Collapse user-defined section by default (re haskell/haddock#335) Conflicts: haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs - - - - - f23ab545 by Yuras Shumovich at 2014-12-12T06:46:41+00:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - 753a4b67 by Austin Seipp at 2014-12-12T06:46:51+00:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8954e8f5 by Herbert Valerio Riedel at 2014-12-12T06:50:53+00:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - d2b06d61 by Gergő Érdi at 2014-12-12T07:07:30+00:00 Update Haddock to new pattern synonym type signature syntax Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 1ff02426 by Jan Stolarek at 2014-12-12T07:13:24+00:00 Follow changes from haskell/haddock#9812 Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - 06ad7600 by Richard Eisenberg at 2014-12-12T07:13:43+00:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 8fd2aa8b by Alan Zimmerman at 2014-12-12T07:22:25+00:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Backends/LaTeX.hs haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 95c3db98 by Thomas Winant at 2014-12-12T07:35:49+00:00 Support for PartialTypeSignatures Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs haddock-api/src/Haddock/Interface/Create.hs - - - - - 45494428 by Gergő Érdi at 2014-12-12T07:36:18+00:00 For pattern synonyms, render "pattern" as a keyword - - - - - a237e3eb by Mateusz Kowalczyk at 2014-12-12T12:27:13+00:00 Various fixups and bumps for next release - - - - - 22918bcd by Herbert Valerio Riedel at 2014-12-14T10:11:47+01:00 Remove redundant wild-card pattern match (this would otherwise cause a build-failure with `-Werror`) - - - - - 1d6ce947 by Herbert Valerio Riedel at 2014-12-14T10:17:06+01:00 Treat GHC 7.10 the same as GHC 7.9 ...since the current GHC 7.9 is going to become GHC 7.10 real-soon-now anyway - - - - - f434ea89 by Herbert Valerio Riedel at 2014-12-14T18:26:50+01:00 Fixup ghc.mk (follow-up to 1739375eb23342) This makes the GHC build-system aware of the data-files to be copied into the bindist (as haddock.cabal doesn't list those anymore) - - - - - 6fb839eb by Mateusz Kowalczyk at 2014-12-17T09:28:59+00:00 Only keep one Version instead of blindly appending - - - - - 40645489 by Mateusz Kowalczyk at 2014-12-18T07:09:44+00:00 Fix dependency version - - - - - 8b3b927b by Mateusz Kowalczyk at 2014-12-18T07:14:23+00:00 Print missing docs by default Adds --no-print-missing-docs - - - - - 59666694 by Mateusz Kowalczyk at 2014-12-18T07:21:37+00:00 update changelog - - - - - aa6d168e by Mateusz Kowalczyk at 2014-12-18T07:30:58+00:00 Update docs for @since - - - - - 2d7043ee by Luite Stegeman at 2014-12-19T18:29:35-06:00 hide projectVersion from DynFlags since it clashes with Haddock.Version.projectVersion - - - - - aaa70fc0 by Luite Stegeman at 2014-12-22T15:58:43+01:00 Add missing import for standalone haddock-api package - - - - - 9ce01269 by Herbert Valerio Riedel at 2014-12-22T17:48:45+01:00 Reset ghc-head with master's tree (this is an overwriting git merge of master into ghc-head) - - - - - fcd6fec1 by Herbert Valerio Riedel at 2014-12-22T17:51:52+01:00 Bump versions for ghc-7.11 - - - - - 525ec900 by Mateusz Kowalczyk at 2014-12-23T13:36:24+00:00 travis-ci: test with HEAD - - - - - cbf494b5 by Simon Peyton Jones at 2014-12-23T15:22:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 50e01c99 by Mateusz Kowalczyk at 2014-12-29T15:28:47+00:00 Make travis use 7.10.x - - - - - 475e60b0 by Njagi Mwaniki at 2014-12-29T15:30:44+00:00 Turn the README into GitHub Markdown format. Closes haskell/haddock#354 - - - - - 8cacf48e by Luite Stegeman at 2015-01-05T16:25:37+01:00 bump haddock-api ghc dependency to allow release candidate and first release - - - - - 6ed6cf1f by Simon Peyton Jones at 2015-01-06T16:37:47+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 8b484f33 by Simon Peyton Jones at 2015-01-08T15:50:22+00:00 Track naming change in DataCon - - - - - 23c5c0b5 by Alan Zimmerman at 2015-01-16T10:15:11-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e7a5532c by JP Moresmau at 2015-01-22T17:19:03+00:00 Ignore warnings, install Cabal 1.22 - - - - - 86942c84 by jpmoresmau at 2015-01-22T17:19:04+00:00 solve dataDir ambiguity - - - - - 5ceb743e by jpmoresmau at 2015-01-22T19:17:32+00:00 support GHC 7.10: no Safe-Inferred, Foldable instance - - - - - 6a3b3fb5 by Mateusz Kowalczyk at 2015-01-22T19:32:10+00:00 Update test files Test: a correct behaviour for fields comma-separating values. I'm surprised we had no bug open for this. Maybe it affects how haskell/haddock#301 renders now but I doubt. Operators: Seems GHC is giving us a new order for operators, something must have changed on their side again. cc @haasn , this makes the fixity to the side not match the order on the LHS which is a bit unpleasant. Maybe the fixity can be made to match the GHC order? Bug335: We expand examples by default now. Bug310: Now inferred safe. - - - - - 708f8b2f by jpmoresmau at 2015-01-22T19:36:59+00:00 Links to source location of class instance definitions - - - - - 5cf8a6da by Vincent Berthoux at 2015-01-22T19:59:58+00:00 Filter '\r' from comments due to Windows problems. On Windows this was causing newline to be rendered twice in code blocks. Closes haskell/haddock#359, fixes haskell/haddock#356. - - - - - 1749e6f0 by Mateusz Kowalczyk at 2015-01-22T20:31:27+00:00 Changelog only - - - - - c8145f90 by Mateusz Kowalczyk at 2015-01-22T23:34:05+00:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. - - - - - 14248254 by Mateusz Kowalczyk at 2015-01-22T23:43:18+00:00 Sort out some module import warnings - - - - - d8a38989 by Simon Peyton Jones at 2015-01-23T07:10:16-06:00 Track naming change in DataCon (cherry picked from commit 04cf63d0195837ed52075ed7d2676e71831e8a0b) - - - - - d3ac6ae4 by Alan Zimmerman at 2015-01-23T07:17:19-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit d61bbc75890e4eb0ad508b9c2a27b91f691213e6) - - - - - 4c1ffeb0 by Simon Peyton Jones at 2015-02-10T12:10:33+00:00 Track changes in HsSyn for quasi-quotes - - - - - 775d20f7 by Mateusz Kowalczyk at 2015-03-15T08:11:48+01:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. (cherry picked from commit 8e06728afb0784128ab2df0be7a5d7a191d30ff4) - - - - - f9245e72 by Phil Ruffwind at 2015-03-16T04:32:01-04:00 Prevent Synopsis from using up too much horizontal space When long type signatures occur in the Synopsis, the element is stretched beyond the width of the window. Scrollbars don't appear, so it's impossible to read anything when this happens. - - - - - cd8fa415 by Mateusz Kowalczyk at 2015-03-17T21:59:39+00:00 Update changelog Closes haskell/haddock#151 due to 71170fc77962f10d7d001e3b8bc8b92bfeda99bc - - - - - b5248b47 by Ben Gamari at 2015-03-25T17:12:17+00:00 Make the error encountered when a package can't be found more user-friendly Closes haskell/haddock#369 - - - - - b756b772 by Mateusz Kowalczyk at 2015-03-26T16:31:40+00:00 Remove now redundant imports - - - - - 5ea5e8dd by Mateusz Kowalczyk at 2015-03-26T16:45:52+00:00 Update test to account for \r filtering - - - - - 6539bfb3 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Test for anchor defaulting I delete the old tests because it turns out that: * test runner would never put them in scope of each other even with imports so just one would suffice * test runner actually needed some hacking to keep links so in the end we would end up with no anchors making them useless - - - - - 1a01d950 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Clearly default to variables in out of scope case - - - - - 7943abe8 by Mateusz Kowalczyk at 2015-03-27T01:14:11+00:00 Fix Hoogle display of constructors Fixes haskell/haddock#361 - - - - - 6d6e587e by Mateusz Kowalczyk at 2015-03-27T01:45:18+00:00 Fully qualify names in Hoogle instances output Closes haskell/haddock#263 - - - - - 52dac365 by Mateusz Kowalczyk at 2015-03-27T01:55:01+00:00 Update changelog - - - - - ca5af9a8 by Mateusz Kowalczyk at 2015-03-27T02:43:55+00:00 Output method documentation in Hoogle backend One thing of note is that we no longer preserve grouping of methods and print each method on its own line. We could preserve it if no documentation is present for any methods in the group if someone asks for it though. Fixes haskell/haddock#259 - - - - - a33f0c10 by Mateusz Kowalczyk at 2015-03-27T03:04:21+00:00 Don't print instance safety information in Hoogle Fixes haskell/haddock#168 - - - - - df6c935a by Mateusz Kowalczyk at 2015-03-28T00:11:47+00:00 Post-release version bumps and changelog - - - - - dde8f7c0 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Loosen bounds on haddock-* - - - - - de93bf89 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Expand response files in arguments Closes haskell/haddock#285 - - - - - 1f0b0856 by Zejun Wu at 2015-04-26T16:35:35-07:00 Do not insert anchor for section headings in contents box - - - - - 860439d7 by Simon Peyton Jones at 2015-05-01T09:36:47+01:00 Track change in API of TyCon - - - - - a32f3e5f by Adam Gundry at 2015-05-04T15:32:59+01:00 Track API changes to support empty closed type familes - - - - - 77e98bee by Ben Gamari at 2015-05-06T20:17:08+01:00 Ignore doc/haddock.{ps,pdf} - - - - - 663d0204 by Murray Campbell at 2015-05-11T04:47:37-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8bb0dcf5 by Murray Campbell at 2015-05-11T06:35:06-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit 2380f07c430c525b205ce2eae6dab23c8388d899) - - - - - bad900ea by Adam Bergmark at 2015-05-11T15:29:39+01:00 haddock-library: require GHC >= 7.4 `Data.Monoid.<>` was added in base-4.5/GHC-7.4 Closes haskell/haddock#394 Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - daceff85 by Simon Peyton Jones at 2015-05-13T12:04:21+01:00 Track the new location of setRdrNameSpace - - - - - 1937d1c4 by Alan Zimmerman at 2015-05-25T21:27:15+02:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - ee0fb6c2 by Łukasz Hanuszczak at 2015-05-27T11:51:31+02:00 Create simple method for indentation parsing. - - - - - 7d6fcad5 by Łukasz Hanuszczak at 2015-05-27T21:36:13+02:00 Make nested lists count indentation according to first item. - - - - - d6819398 by Łukasz Hanuszczak at 2015-05-27T22:46:13+02:00 Add simple test case for arbitrary-depth list nesting. - - - - - 2929c54d by Łukasz Hanuszczak at 2015-06-03T02:11:31+02:00 Add arbitrary-indent spec test for parser. - - - - - 9a0a9bb0 by Mateusz Kowalczyk at 2015-06-03T05:25:29+01:00 Update docs with info on new list nesting rule Fixes haskell/haddock#278 through commits from PR haskell/haddock#401 - - - - - 12efc92c by Mateusz Kowalczyk at 2015-06-03T05:29:26+01:00 Update some meta data at the top of the docs - - - - - 765ee49f by Bartosz Nitka at 2015-06-07T08:40:59-07:00 Add some Hacking docs for getting started - - - - - 19aaf851 by Bartosz Nitka at 2015-06-07T08:44:30-07:00 Fix markdown - - - - - 2a90cb70 by Mateusz Kowalczyk at 2015-06-08T15:08:36+01:00 Refine hacking instructions slightly - - - - - 0894da6e by Thomas Winant at 2015-06-08T23:47:28-05:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 10a9bb76 by Emanuel Borsboom at 2015-06-12T02:46:23+01:00 Build executable with '-threaded' (fixes haskell/haddock#399) - - - - - 7696b94f by Mateusz Kowalczyk at 2015-06-12T02:59:19+01:00 Update changelog for -threaded Closes haskell/haddock#400 - - - - - d3c118ec by Bartosz Nitka at 2015-06-12T03:00:58+01:00 Fix haddock: internal error: spliceURL UnhelpfulSpan (#207) Inferred type signatures don't have SrcSpans, so let's use the one from the declaration. I've tested this manually on the test-case from haskell/haddock#207, but I got stuck at trying to run the test-suite. - - - - - b67e843b by Mateusz Kowalczyk at 2015-06-12T03:01:50+01:00 Changelog for haskell/haddock#207 Fixes haskell/haddock#207, closes haskell/haddock#402 - - - - - 841d785e by jpmoresmau at 2015-06-12T16:03:16+01:00 Attach to instance location the name that has the same location file Fixes haskell/haddock#383 - - - - - 98791cae by Mateusz Kowalczyk at 2015-06-12T16:08:27+01:00 Update changelog Closes haskell/haddock#398 - - - - - 7c0b5a87 by Phil Ruffwind at 2015-06-12T13:07:25-04:00 Fix alignment of Source links in instance table in Firefox Due to a Firefox bug [1], a combination of 'whitespace: nowrap' on the parent element with 'float: right' on the inner element can cause the floated element to be displaced downwards for no apparent reason. To work around this, the left side is wrapped in its own <span> and set to 'float: left'. As a precautionary measure to prevent the parent element from collapsing entirely, we also add the classic "clearfix" hack. The latter is not strictly needed but it helps prevent bugs if the layout is altered again in the future. Fixes haskell/haddock#384. Remark: line 159 of src/Haddock/Backends/Xhtml/Layout.hs was indented to prevent confusion over the operator precedence of (<+>) vs (<<). [1]: https://bugzilla.mozilla.org/show_bug.cgi?id=488725 - - - - - cfe86e73 by Mateusz Kowalczyk at 2015-06-14T10:49:01+01:00 Update tests for the CSS changes - - - - - 2d4983c1 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding for Haskell source parser module. - - - - - 29548785 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement function for tagging parsed chunks with source spans. - - - - - 6a5e4074 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement simple string chunking based on HsColour library. - - - - - 6e52291f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create basic token classification method. - - - - - da971a27 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Adapt source span tagging to work with current whitespace handling. - - - - - 4feb5a22 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add record accessors to exports of hyperlinker parser module. - - - - - a8cc4e39 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Make parser module export all types and associated accessors. - - - - - fb8d468f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple HTML renderer for parsed source file. - - - - - 80747822 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for specifying the CSS file path in HTML source renderer. - - - - - 994dc1f5 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix identifier recognition in Haskell source parser. - - - - - b1bd0430 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix comment recognition in Haskell source parser. - - - - - 11db85ae by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for recognizing compiler pragmas in source parser. - - - - - 736c7bd3 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding of module for associating tokens with AST names. - - - - - 7e149bc2 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement utility method for extracting variable identifiers from AST. - - - - - 32eb640a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple mechanism for associating tokens with AST names. - - - - - d4eba5bc by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add dummy support for hyperlinking named tokens. - - - - - 2b76141f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matcher bug causing wrong items being hyperlinked. - - - - - 2d48002e by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Constrain elements exported by hyperlinker modules. - - - - - 9715eec6 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for type token recognition. - - - - - 8fa401cb by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for binding token recognition. - - - - - d062400b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement go-to-definition mechanism for local bindings. - - - - - f4dc229b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement module export- and import-list item hyperlinking. - - - - - c9a46d58 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matching to allow parenthesized operators hyperlinking. - - - - - 03aad95a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix weird hyperlinking of parenthesized operators. - - - - - b4694a7d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for type declaration anchors. - - - - - 7358d2d2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for top-level function declaration anchors. - - - - - dfc24b24 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix external anchors to contain HTML file extension. - - - - - a045926c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Refactor the way AST names are handled within detailed tokens. - - - - - c76049b4 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement hyperlinking of imported module names. - - - - - 2d2a1572 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix parsing of single line comments with broken up newlines. - - - - - 11afdcf2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix bug with improper newline handling. - - - - - 8137f104 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issues with escaped newlines in comments. - - - - - 34759b19 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for parsing C preprocessor macros. - - - - - 09f0f847 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for parser module of source hyperlinker. - - - - - 709a8389 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for AST module of source hyperlinker. - - - - - 4df5c227 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add command line option for generating hyperlinked source. - - - - - 7a755ea2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Extend module interface with rich source token stream field. - - - - - 494f4ab1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement source tokenization during interface creation process. - - - - - 5f21c953 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create hyperlinker module and plug it into the Haddock pipeline. - - - - - 0cc8a216 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for providing custom CSS files for hyperlinked source. - - - - - a32bbdc1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for fancy highlighting upon hovering over identifier. - - - - - d16d642a by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make source hyperlinker generate output in apropriate directory. - - - - - ae12953d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create module with hyperlinker utility functions. - - - - - 6d4952c5 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make external hyperlinks point to locations specified by source URLs. - - - - - 8417555d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Rewrite source generation to fixed links and directory structure. - - - - - ce9cec01 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add basic support for cross-package hyperlink generation. - - - - - 7eaf025c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Disable generating hyperlinks for module references. - - - - - a50bf92e by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make Haddock generate source for all interfaces (also hidden ones). - - - - - f5ae2838 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Prevent source parser from throwing exception when lexing fails. - - - - - db9ffbe0 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement workaround for Chrome highlighting issues. - - - - - 0b6b453b by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate correct anchors for data constructors. - - - - - c86d38bc by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate anchors for record field declarations. - - - - - 063abf7f by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issue with hyperlink highlight styling in Chrome browser. - - - - - 880fc611 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking constructor names in patters. - - - - - c9e89b95 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record patterns. - - - - - 17a11996 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record expressions. - - - - - 0eef932d by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Make hyperlinker respect pretty-printer flag and add documentation. - - - - - f87c1776 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Unexpose hyperlinker modules in Cabal configuration. - - - - - 4c9e2b06 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Setup HSpec framework for Haddock API package. - - - - - 4b20cb30 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add basic tests related to comment parsing. - - - - - 6842e919 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add tests related to parsing basic language constructs. - - - - - 87bffb35 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add simple tests for do-notation parsing. - - - - - e7af1841 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add very simple QuickCheck properties for source parser spec. - - - - - c84efcf1 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Create simple test runner for hyperlinker tests. - - - - - 76b90447 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for basic identifier hyperlinking. - - - - - 0fbf4df6 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for operator hyperlinking. - - - - - 731aa039 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for constructor hyperlinking. - - - - - 995a78a2 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for record expressions and patterns hyperlinking. - - - - - 3566875a by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for literal syntax highlighting. - - - - - 68469a35 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add hyperlinker test runner to .cabal and .gitignore files. - - - - - aa946c93 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Adapt hyperlinker test runner to have the same interface as HTML one. - - - - - ce34da16 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Fix hyperlinker test runner file paths and add pretty-printing option. - - - - - 0d7dd65e by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add reference files for hyperlinker test cases. - - - - - efa4a1e0 by Łukasz Hanuszczak at 2015-07-01T00:47:32+02:00 Make hyperlinker test runner strip local links from generated source. - - - - - 3e96e584 by Łukasz Hanuszczak at 2015-07-01T01:14:59+02:00 Create simple script for accepting hyperlinker test case references. - - - - - 526fe610 by Łukasz Hanuszczak at 2015-07-01T01:16:41+02:00 Re-accept hyperlinker test cases with local references stripped out. - - - - - 892e2cb3 by Łukasz Hanuszczak at 2015-07-01T01:22:09+02:00 Fix bug with diffing wrong files in hyperlinker test runner. - - - - - 9ff46039 by Łukasz Hanuszczak at 2015-07-01T18:04:46+02:00 Remove unused dependencies in Haddock API spec configuration. - - - - - 47969c07 by Łukasz Hanuszczak at 2015-07-01T18:32:19+02:00 Add support for hyperlinking synonyms in patterns. - - - - - a73449e0 by Łukasz Hanuszczak at 2015-07-01T18:33:44+02:00 Create test case for hyperlinking @-patterns. - - - - - c2077ed8 by Łukasz Hanuszczak at 2015-07-01T19:06:04+02:00 Add support for hyperlinking universally quantified type variables. - - - - - 68017342 by Łukasz Hanuszczak at 2015-07-01T19:28:32+02:00 Create hyperlinker test case with quantified type variables. - - - - - 51c01a78 by Łukasz Hanuszczak at 2015-07-01T19:34:22+02:00 Add scoped type variables test for polymorphism test case. - - - - - 13181ae2 by Łukasz Hanuszczak at 2015-07-01T19:56:27+02:00 Add record wildcards test for records hyperlinking test case. - - - - - 991b81dd by Łukasz Hanuszczak at 2015-07-01T21:01:42+02:00 Document some functions in XHTML utlity module. - - - - - 98c8dfe5 by Łukasz Hanuszczak at 2015-07-01T22:25:21+02:00 Make hyperlinker render qualified names as one entity. - - - - - 75e13b9b by Łukasz Hanuszczak at 2015-07-01T22:27:38+02:00 Add qualified name test for identifiers hyperlinking test case. - - - - - de1e143f by Łukasz Hanuszczak at 2015-07-02T12:32:59+02:00 Fix crash happening when hyperlinking type family declarations. - - - - - 7a8fb175 by Łukasz Hanuszczak at 2015-07-02T12:47:03+02:00 Add support for anchoring data family constructor declarations. - - - - - 3b404e49 by Łukasz Hanuszczak at 2015-07-02T13:31:05+02:00 Improve support for hyperlinking type families. - - - - - 59eb7143 by Łukasz Hanuszczak at 2015-07-02T13:33:34+02:00 Add hyperlinker test case for checking type and type family declarations. - - - - - d1cda0c0 by Łukasz Hanuszczak at 2015-07-02T13:41:38+02:00 Fix issue with operators being recognized as preprocessor directives. - - - - - da206c9d by Łukasz Hanuszczak at 2015-07-02T17:18:12+02:00 Fix broken tests for parsing and hyperlinking hash operators. - - - - - 53750d1b by Łukasz Hanuszczak at 2015-07-02T18:53:28+02:00 Add support for anchoring signatures in type class declarations. - - - - - 1fa5bb10 by Łukasz Hanuszczak at 2015-07-02T19:04:47+02:00 Make hyperlinker generate anchors only to top-level value bindings. - - - - - a542305c by Łukasz Hanuszczak at 2015-07-02T19:05:58+02:00 Create hyperlinker test case for type classes. - - - - - b0dd4581 by Łukasz Hanuszczak at 2015-07-04T16:28:26+02:00 Update docs with information about source hyperlinking. - - - - - 9795302a by Łukasz Hanuszczak at 2015-07-04T16:52:15+02:00 Update docs on using `--read-interface` option. - - - - - 9acdc002 by Łukasz Hanuszczak at 2015-07-04T17:15:26+02:00 Remove potentially dangerous record access in hyperlinker AST module. - - - - - fb3ab7be by Łukasz Hanuszczak at 2015-07-04T17:40:10+02:00 Make Haddock generate warnings about potential misuse of hyperlinker. - - - - - a324c504 by Łukasz Hanuszczak at 2015-07-04T17:43:22+02:00 Fix incorrect specification of source style option in doc file. - - - - - 3f01a8e4 by Łukasz Hanuszczak at 2015-07-05T17:06:36+02:00 Refactor source path mapping to use modules as indices. - - - - - ac70f5b1 by Łukasz Hanuszczak at 2015-07-05T17:47:34+02:00 Fix bug where not all module interfaces were added to source mapping. - - - - - f5e57da9 by Łukasz Hanuszczak at 2015-07-06T16:39:57+02:00 Extract main hyperlinker types to separate module. - - - - - 43974905 by Łukasz Hanuszczak at 2015-07-06T16:52:13+02:00 Move source paths types to hyperlinker types module. - - - - - 3e236055 by Łukasz Hanuszczak at 2015-07-06T17:06:19+02:00 Add support for hyperlinking modules in import lists. - - - - - 58233d9f by Łukasz Hanuszczak at 2015-07-06T17:26:49+02:00 Add short documentation for hyperlinker source map type. - - - - - 14da016d by Łukasz Hanuszczak at 2015-07-06T18:07:20+02:00 Fix bug with module name being hyperlinked to `Prelude`. - - - - - 8f79db52 by Łukasz Hanuszczak at 2015-07-06T18:23:47+02:00 Fix problem with spec build in Haddock API configuration. - - - - - e7cc056c by Adam Sandberg Eriksson at 2015-07-07T23:22:21+01:00 StrictData: print correct strictness marks - - - - - e8253ca8 by Mateusz Kowalczyk at 2015-07-07T23:58:28+01:00 Update changelog - - - - - 0aba676b by Mateusz Kowalczyk at 2015-07-07T23:58:33+01:00 Relax upper bound on GHC a bit - - - - - 7a595381 by Mateusz Kowalczyk at 2015-07-07T23:58:52+01:00 Delete trailing whitespace - - - - - 50976d5e by Adam Sandberg Eriksson at 2015-07-08T15:03:04+02:00 StrictData: changes in HsBang type - - - - - 83b045fa by Mateusz Kowalczyk at 2015-07-11T14:35:18+01:00 Fix expansion icon for user-collapsible sections Closes haskell/haddock#412 - - - - - b2a3b0d1 by Mateusz Kowalczyk at 2015-07-22T22:03:21+01:00 Make some version changes after 2.16.1 release - - - - - a8294423 by Ben Gamari at 2015-07-27T13:16:07+02:00 Merge pull request haskell/haddock#422 from adamse/adamse-D1033 Merge for GHC D1033 - - - - - c0173f17 by randen at 2015-07-30T14:49:08-07:00 Break the response file by line termination rather than spaces, since spaces may be within the parameters. This simple approach avoids having the need for any quoting and/or escaping (although a newline char will not be possible in a parameter and has no escape mechanism to allow it). - - - - - 47c0ca14 by Alan Zimmerman at 2015-07-31T10:41:52+02:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - 45a9d770 by Mateusz Kowalczyk at 2015-07-31T09:47:43+01:00 Update changelog - - - - - 347a20a3 by Phil Ruffwind at 2015-08-02T23:15:26+01:00 Avoid JavaScript error during page load in non-frame mode In non-frame mode, parent.window.synopsis refers to the synopsis div rather than the nonexistent frame. Unfortunately, the script wrongly assumes that if it exists it must be a frame, leading to an error where it tries to access the nonexistent attribute 'replace' of an undefined value (synopsis.location). Closes haskell/haddock#406 - - - - - 54ebd519 by Phil Ruffwind at 2015-08-02T23:27:10+01:00 Link to the definitions to themselves Currently, the definitions already have an anchor tag that allows URLs with fragment identifiers to locate them, but it is rather inconvenient to obtain such a URL (so-called "permalink") as it would require finding the a link to the corresponding item in the Synopsis or elsewhere. This commit adds hyperlinks to the definitions themselves, allowing users to obtain links to them easily. To preserve the original aesthetics of the definitions, we alter the color of the link so as to be identical to what it was, except it now has a hover effect indicating that it is clickable. Additionally, the anchor now uses the 'id' attribute instead of the (obsolete) 'name' attribute. Closes haskell/haddock#407 - - - - - 02cc8bb7 by Phil Ruffwind at 2015-08-02T23:28:02+01:00 Fix typo in Haddock.Backends.Xhtml.Layout: divSynposis -> divSynopsis Closes haskell/haddock#408 - - - - - 2eb0a458 by Phil Ruffwind at 2015-08-02T23:30:07+01:00 Fix record field alignment when name is too long Change <dl> to <ul> and use display:table rather than floats to layout the record fields. This avoids bug haskell/haddock#301 that occurs whenever the field name gets too long. Slight aesthetic change: the entire cell of the field's source code is now shaded gray rather than just the area where text exists. Fixes haskell/haddock#301. Closes haskell/haddock#421 - - - - - 7abb3402 by Łukasz Hanuszczak at 2015-08-02T23:32:14+01:00 Add some utility definitions for generating line anchors. - - - - - e0b1d79b by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Make hyperlinked source renderer generate line anchors. - - - - - 24dd4c9f by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Re-accept test cases after adding line anchors for each of them. - - - - - 0372cfcb by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Override source line flags when source hyperlinker is enabled. - - - - - a81bcd07 by Mateusz Kowalczyk at 2015-08-02T23:58:25+01:00 Update tests to follow HTML changes - - - - - d2d7426f by Łukasz Hanuszczak at 2015-08-06T20:54:59+02:00 Fix quote syntax for promoted types. - - - - - 668cf029 by Łukasz Hanuszczak at 2015-08-06T21:12:00+02:00 Apply promoted type quoting to type-level consing. - - - - - 89f8e7c6 by Łukasz Hanuszczak at 2015-08-06T21:17:10+02:00 Extend advanced types test case with other examples. - - - - - 86494bca by Łukasz Hanuszczak at 2015-08-06T21:22:06+02:00 Rename advanced types test case and accept new output. - - - - - dbb7c7c0 by Adam Sandberg Eriksson at 2015-08-09T23:01:05+02:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 2a7704fa by Ben Gamari at 2015-08-10T13:18:05+02:00 Merge pull request haskell/haddock#433 from adamse/split-hsbang HsBang is split into HsSrcBang and HsImplBang - - - - - 891954bc by Thomas Miedema at 2015-08-15T14:51:18+02:00 Follow changes in GHC build system - - - - - b55d32ab by Mateusz Kowalczyk at 2015-08-21T18:06:09+01:00 Make Travis use 7.10.2 - - - - - 97348b51 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Move SYB utilities to standalone module. - - - - - 748ec081 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement `everywhere` transformation in SYB module. - - - - - 011cc543 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement generic transformation constructor. - - - - - b9510db2 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Create simple utility module for type specialization. - - - - - 43229fa6 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Make type of type specialization function more general. - - - - - fd844e90 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Add basic HTML test case for checking instance specialization. - - - - - 6ea0ad04 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Make HTML class instance printer take optional signature argument. - - - - - 65aa41b6 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Refactor instance head type to record instead of a meaningless tuple. - - - - - 3fc3bede by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add expandable method section for each class instance declaration. - - - - - 99ceb107 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Move dummy post-family instances for `DocName` to `Types` module. - - - - - e98f4708 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create convenience functions for type specialization module. - - - - - b947552f by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Hook type specialization logic with HTML pretty-printer. - - - - - dcaa8030 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create stub functions for sugaring specialized types. - - - - - fa84bc65 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement list syntax sugaring logic for specialized types. - - - - - e8b05b07 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement tuple syntax sugaring logic for specialized types. - - - - - 68a2e5bc by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Get rid of code duplication in type specialization module. - - - - - 4721c336 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create scaffolding of a framework for renaming specialized types. - - - - - 271b488d by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in missing cases in specialized type renaming function. - - - - - bfa5f2a4 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Remove code duplication in specialized type renamer. - - - - - ea6bd0e8 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Change state of the type renaming monad. - - - - - 77c5496e by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement simple mechanism for generating new type names. - - - - - 91bfb48b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in stub behaviour with actual environment renaming. - - - - - d244517b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix logic behind binder type renaming. - - - - - f3c5e360 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add SYB-like utility function for performing stateful queries. - - - - - eb3f9154 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create function for retrieving free variables from given type. - - - - - a94561d3 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix compilation error caused by incorrect type signature. - - - - - 8bb707cf by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Move `SetName` class definition to types module. - - - - - 5800b13b by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Hook type renamer with instance method HTML pretty-printer. - - - - - 6a480164 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some test cases for type renamer. - - - - - 839842f7 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized signatures refer to original signature declaration. - - - - - 4880f7c9 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized methods be nicely formatted again. - - - - - ab5a6a2e by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Attach source locations to the specialized class methods. - - - - - 43f8a559 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Extend instances test case to also test multi-name type signatures. - - - - - 59bc751c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix tab-based indentation in instances test case. - - - - - c2126815 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Improve placement of instance methods expander button. - - - - - 0a32e287 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add new data type declaration to instance specialization test case. - - - - - 5281af1f by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make type renamer first try single-letter names as alternatives. - - - - - 7d509475 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix type renamer bug with incorrect names being generated. - - - - - 0f35bf7c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some documentation and refactor type specialization module. - - - - - da1d0803 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix another bug where type renamer was generating incorrect names. - - - - - cd39b5cb by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Refactor type renamer to rebinding and pure renaming phases. - - - - - 850251f4 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix unwitting compilation bug. - - - - - e5e9fc01 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Integrate instance specification type into class instance definition. - - - - - 825b0ea0 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer neccessary instance specification type. - - - - - cdba44eb by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix declaration converter to use more appropriate mode for methods. - - - - - bc45c309 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug with types not being specialized at all. - - - - - 5d8e5d89 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug where instance expander was opening wrong section. - - - - - 6001ee41 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix another type renamer bug where not all names were rebound. - - - - - 5f58ce2a by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix yet another renamer bug where some names were not unique. - - - - - 8265e521 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split instance subsection layout method to top-level declarations. - - - - - e5e66298 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Rearrange layout of instance methods in generated documentation. - - - - - a50b4eea by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer used layout method. - - - - - 2ff36ec2 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach section title to the instance methods block. - - - - - 7ac15300 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Add basic tests for associated types in instances test case. - - - - - db0ea2f9 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach associated types information to instance header. - - - - - 71cad4d5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details section contain associated types information. - - - - - deee2809 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Improve look of rendered associated families in instance details. - - - - - 839d13a5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Introduce alternative type for family declarations. - - - - - d397f03f by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details record use new type for family declarations. - - - - - 2b23fe97 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split printer of type family header to separate functions. - - - - - c3498cdc by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Implement HTML renderer for pseudo-family declarations. - - - - - c12bbb04 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Apply type specializer to associated type family declarations. - - - - - 2fd69ff2 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Create helper method for specializing type signatures. - - - - - 475826e7 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Refactor specializer module to be independent from XHTML backend. - - - - - f00b431c by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add some documentation for instance head specializer. - - - - - a9fef2dc by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix bug with missing space in documentation for associated types. - - - - - 50e29056 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with incorrect instance details sections being expanded. - - - - - e6dfdd03 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by adding instance details section. - - - - - 75565b2a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make section identifier of instance details more GHC-independent. - - - - - add0c23e by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Re-accept tests after applying deterministic section identifiers. - - - - - 878f2534 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make identifier generation also architecture-independent. - - - - - 48be69f8 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with instance expander hijacking type hyperlink click. - - - - - 47830c1f by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Get rid of dreadful hashing function for generating identifiers. - - - - - 956cd5af by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Move `InstOrigin` type declaration to more appropriate module. - - - - - bf672ed3 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by changes related to instance expander. - - - - - 8f2a949a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add examples with type operators to the instances test case. - - - - - 64600a84 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add basic support for sugaring infix type operators. - - - - - 747d71b8 by Łukasz Hanuszczak at 2015-08-21T18:22:34+01:00 Add support for sugaring built-in function syntax. - - - - - d4696ffb by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Remove default methods from Hoogle class output. - - - - - bf0e09d7 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add fixity declarations in Hoogle backend output. - - - - - 90e91a51 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix bug with incorrect fixities being generated in Hoogle backend. - - - - - 48f11d35 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve class type family declarations output in Hoogle backend. - - - - - 661e8e8f by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add missing default family equations in Hoogle output. - - - - - e2d64103 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve formatting of class details output in Hoogle backend. - - - - - 490fc377 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix weird-looking Hoogle output for familyless classes. - - - - - ea115b64 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create script file for new HTML test runner. - - - - - 609913d3 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Set default behaviour if no arguments given. - - - - - dc115f67 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for providing optional arguments for test runner. - - - - - d93ec867 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve output of test runner error messages. - - - - - 0be9fe12 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for executing Haddock process in test runner. - - - - - 4e4d00d9 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add GHC path to test runner configuration. - - - - - d67a2086 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make GHC path a test runner command-line argument. - - - - - c810079a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Extend test runner configuration with Haddock arguments. - - - - - fee18845 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor test runner and create stub functions. - - - - - ff7c161f by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make test runner actually run Haddock executable. - - - - - 391f73e6 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with test runner not producing any output files. - - - - - 81a74e2d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Setup skeleton of framework for running tests. - - - - - f8a79ec4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with modules not being found in global search mode. - - - - - 7e700b4d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make Haddock standard output redirection be more configurable. - - - - - 53b4c17a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Incorporate old, ugly functions for comparing output files. - - - - - 8277c8aa by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor architecture of test runner output checking functions. - - - - - 587bb414 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement actual diffing mechanism. - - - - - 9ed2b5e4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve code style to match popular guidelines. - - - - - 14bffaf8 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make it possible to choose alternative diff tool. - - - - - 5cdfb005 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create stub methods for processing test output as XML documents. - - - - - 7ef8e12e by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement link-stripping logic as simple SYB transformation. - - - - - 8a1fcd4f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Incorporate link stripping to output diffing mechanism. - - - - - 37dba2bc by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement footer-stripping logic. - - - - - 9cd52120 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Add missing dependencies in Cabal configuration file. - - - - - e0f83c6e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix issue with output being printed in incorrect order. - - - - - 0a94fbb0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to run tests without generating diff. - - - - - 76a58c6f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor HTML test suite boilerplate to external package. - - - - - af41e6b0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utilities for storing directory configuration. - - - - - d8f0698f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move IO-dependent config of HTML test suite to test package. - - - - - 17369fa0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Enable all compiler warnings in Haddock test package configuration. - - - - - 9d03b47a by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move Haddock runner of HTML test suite to Haddock test package. - - - - - 4b3483c5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 03754194 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience wrappers to simplify in test entry points. - - - - - 27476ab7 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adjust module visibility and items they export. - - - - - c40002ba by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Remove no longer useful test option. - - - - - 55ab2541 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Change extension of test files used for diffing. - - - - - 136bf4e4 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor and simplify XHTML helper module of test package. - - - - - 69f7e3df by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix typo in link stripper of HTML test suite runner. - - - - - 0c3c1c6b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience script for running specific HTML tests. - - - - - 489e1b05 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement utility functions for conditional link stripping. - - - - - 0f985dc3 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt `hypsrc-test` module to work with new testing framework. - - - - - 927406f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement output accepting mechanism in test package. - - - - - 8545715e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utility function for recursive obtaining directory contents. - - - - - cb70381f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 019599b5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix path handling in test runner. - - - - - 399b985b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to specify ignored files for test output. - - - - - 41b3d93d by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt HTML test runner to use new ignoring functionality. - - - - - e2091c8b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix bug with not all test output files being checked. - - - - - b22134f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Specify ignored files for hyperlinker source test runner. - - - - - 3301dfa1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Copy test runner script for hyperlinked source case. - - - - - d39a6dfa by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner invoking Haddock in incorrect mode. - - - - - f32c8ff3 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix path handling in test module loader. - - - - - 10f94ee9 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make test runner ignore test packages with no modules. - - - - - 5dc4239c by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create test runner entry points for LaTeX test suite. - - - - - 58d1f7cf by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with unnecessary checking old test output. - - - - - c7ce76e1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Re-implement test acceptance functionality. - - - - - 13bbabe8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix warning about no longer needed definition. - - - - - 958a99b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Adapt Cabal configuration to execute LaTeX suite with new runner. - - - - - 550ff663 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Setup test suite for Hoogle backend. - - - - - 3aa969c4 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make Hoogle backend create output directory if needed. - - - - - eb085b02 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Add appropriate .gitignore entry and configure Hoogle test suite. - - - - - a50bf915 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner failing when run on multiple test packages. - - - - - bf5368b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create simple test cases for Hoogle backend. - - - - - 6121ba4b by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create helper function for conversion between XML and XHTML. - - - - - cb516061 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Refactor existing code to use XHTML printer instead of XML one. - - - - - e2de8c82 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Improve portability of test runner scripts. - - - - - 9563e774 by Łukasz Hanuszczak at 2015-08-22T23:43:16+02:00 Remove redundant import statement. - - - - - 55353df1 by Łukasz Hanuszczak at 2015-08-24T23:09:20+02:00 Fix bug with accepting to non-existing directory. - - - - - 00a334ca by Łukasz Hanuszczak at 2015-08-24T23:09:47+02:00 Accept output for Hoogle and LaTeX backends. - - - - - 29191d8b by Łukasz Hanuszczak at 2015-08-24T23:14:18+02:00 Get rid of obsolete testing utilities. - - - - - bbb25db3 by Łukasz Hanuszczak at 2015-08-24T23:18:50+02:00 Update sandbox setup guide to work with Haddock test package. - - - - - cfd45248 by Łukasz Hanuszczak at 2015-08-24T23:51:30+02:00 Make Travis aware of Haddock test package. - - - - - 74185b7a by Łukasz Hanuszczak at 2015-08-25T17:41:59+02:00 Fix test suite failure when used with Stack. - - - - - 18769697 by Łukasz Hanuszczak at 2015-08-25T18:02:09+02:00 Add sample Stack setup to the hacking guide. - - - - - 22715eeb by Łukasz Hanuszczak at 2015-08-25T18:04:47+02:00 Fix Markdown formatting of README file. - - - - - b49ec386 by Łukasz Hanuszczak at 2015-08-25T18:13:36+02:00 Setup Haddock executable path in Travis configuration. - - - - - 5d29eb03 by Eric Seidel at 2015-08-30T09:55:58-07:00 account for changes to ipClass - - - - - f111740a by Ben Gamari at 2015-09-02T13:20:37+02:00 Merge pull request haskell/haddock#443 from bgamari/ghc-head account for changes to ipClass - - - - - a2654bf6 by Jan Stolarek at 2015-09-03T01:32:57+02:00 Follow changes from haskell/haddock#6018 - - - - - 2678bafe by Richard Eisenberg at 2015-09-21T12:00:47-04:00 React to refactoring CoAxiom branch lists. - - - - - ebc56e24 by Edward Z. Yang at 2015-09-21T11:53:46-07:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4a8c4198 by Tamar Christina at 2015-09-27T13:59:08+02:00 Create Process: removed PhaseFailed - - - - - 7e99b790 by Oleg Grenrus at 2015-09-27T20:52:10+03:00 Generate docs for orphan instances - - - - - 32e932e2 by Oleg Grenrus at 2015-09-28T07:21:11+03:00 Have source links for orphan instances - - - - - c2eb9f4f by Oleg Grenrus at 2015-09-28T07:24:58+03:00 Print orphan instances header only if required - - - - - ff96f978 by Oleg Grenrus at 2015-09-28T07:40:54+03:00 Add orphan instances link to contents box - - - - - d72490a6 by Oleg Grenrus at 2015-09-28T16:37:44+03:00 Fix orphan instance collapsing - - - - - 25d3dfe5 by Ben Gamari at 2015-10-03T12:38:09+02:00 Merge pull request haskell/haddock#448 from Mistuke/fix-silent-death-of-runInteractive Remove PhaseFailed - - - - - 1e45e43b by Edward Z. Yang at 2015-10-11T13:10:10-07:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b1370ac1 by Adam Gundry at 2015-10-16T16:26:42+01:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 60bef421 by Simon Peyton Jones at 2015-10-26T12:52:36+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 4c1898ca by Simon Peyton Jones at 2015-10-27T14:24:56+00:00 Track change to PatSyn.patSynSig - - - - - 25108e85 by Simon Peyton Jones at 2015-10-27T17:34:18+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - 693643ac by Ben Gamari at 2015-10-28T14:33:06+01:00 Account for Typeable changes The treatment of type families changed. - - - - - cd7c2221 by Simon Peyton Jones at 2015-10-30T13:03:51+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - 712032cb by Herbert Valerio Riedel at 2015-10-31T11:01:45+01:00 Relax upper bound on `base` to allow base-4.9 - - - - - 0bfa0475 by Simon Peyton Jones at 2015-10-31T19:08:13+00:00 More adaption to wildcard-refactor - - - - - 0a3c0cb7 by Simon Peyton Jones at 2015-10-31T22:14:43+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - c4fd4ec9 by Alan Zimmerman at 2015-11-01T11:16:34+01:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 42cdd882 by Matthew Pickering at 2015-11-06T20:02:16+00:00 Change for IEThingWith - - - - - f368b7be by Ben Gamari at 2015-11-11T11:35:51+01:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - e32965b8 by Simon Peyton Jones at 2015-11-13T12:18:17+00:00 Merge with origin/head - - - - - ebcf795a by Edward Z. Yang at 2015-11-13T21:56:27-08:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4e23989f by Simon Peyton Jones at 2015-11-18T11:32:54+00:00 Wibbles to Haddock - - - - - 2289cd4a by Simon Peyton Jones at 2015-11-20T23:12:49+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor - - - - - 695975a6 by Alan Zimmerman at 2015-11-21T21:16:12+02:00 Update to match GHC wip/T11019 - - - - - bbba21e7 by Simon Peyton Jones at 2015-11-23T13:54:31+00:00 merge with origin/ghc-head - - - - - 3d664258 by Simon Peyton Jones at 2015-11-23T17:17:18+00:00 Wibble - - - - - e64cf586 by Herbert Valerio Riedel at 2015-12-05T00:29:55+01:00 Canonicalise Monad instances - - - - - a2de15a7 by Alan Zimmerman at 2015-12-05T17:33:52+02:00 Matching changes for haskell/haddock#11028 - - - - - cc29a3e4 by Alan Zimmerman at 2015-12-05T19:45:33+02:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 95dd15d1 by Richard Eisenberg at 2015-12-11T17:33:39-06:00 Update for type=kinds - - - - - cb5fd9ed by Herbert Valerio Riedel at 2015-12-14T15:07:30+00:00 Bump versions for ghc-7.11 - - - - - 4f286d96 by Simon Peyton Jones at 2015-12-14T15:10:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 13ea2733 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 098df8b8 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track changes in HsSyn for quasi-quotes - - - - - 716a64de by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track change in API of TyCon - - - - - 77a66bca by Adam Gundry at 2015-12-14T15:10:58+00:00 Track API changes to support empty closed type familes - - - - - f2808305 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track the new location of setRdrNameSpace - - - - - ba8b08a4 by Alan Zimmerman at 2015-12-14T15:10:59+00:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - a4ded87e by Thomas Winant at 2015-12-14T15:14:05+00:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 25c78107 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: print correct strictness marks - - - - - 6cbc41c4 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: changes in HsBang type - - - - - ad46821a by Alan Zimmerman at 2015-12-14T15:14:06+00:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - abc0ae5b by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 3308d06c by Thomas Miedema at 2015-12-14T15:14:07+00:00 Follow changes in GHC build system - - - - - 6c763deb by Eric Seidel at 2015-12-14T15:14:07+00:00 account for changes to ipClass - - - - - ae5b4eac by Jan Stolarek at 2015-12-14T15:17:00+00:00 Follow changes from haskell/haddock#6018 - - - - - ffbc40e0 by Richard Eisenberg at 2015-12-14T15:17:02+00:00 React to refactoring CoAxiom branch lists. - - - - - d1f531e9 by Edward Z. Yang at 2015-12-14T15:17:02+00:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 79f73754 by Tamar Christina at 2015-12-14T15:17:02+00:00 Create Process: removed PhaseFailed - - - - - 3d37bebb by Edward Z. Yang at 2015-12-14T15:20:46+00:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 5f8a9e44 by Adam Gundry at 2015-12-14T15:20:48+00:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 79dda70f by Simon Peyton Jones at 2015-12-14T15:26:02+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 959930fb by Simon Peyton Jones at 2015-12-14T15:37:50+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - e18a8df5 by Simon Peyton Jones at 2015-12-14T15:37:52+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - aa35ab52 by Simon Peyton Jones at 2015-12-14T15:40:18+00:00 More adaption to wildcard-refactor - - - - - 8ceef94b by Simon Peyton Jones at 2015-12-14T15:46:04+00:00 Track change to PatSyn.patSynSig - - - - - cd81e83d by Ben Gamari at 2015-12-14T15:46:06+00:00 Account for Typeable changes The treatment of type families changed. - - - - - 63c9117c by Herbert Valerio Riedel at 2015-12-14T15:46:34+00:00 Relax upper bound on `base` to allow base-4.9 - - - - - a484c613 by Alan Zimmerman at 2015-12-14T15:47:46+00:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 2c26fa51 by Matthew Pickering at 2015-12-14T15:47:47+00:00 Change for IEThingWith - - - - - 593baa0f by Ben Gamari at 2015-12-14T15:49:21+00:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - b6b5ca78 by Edward Z. Yang at 2015-12-14T15:49:54+00:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b5b0e072 by Alan Zimmerman at 2015-12-14T15:54:20+00:00 Update to match GHC wip/T11019 - - - - - 14ddeb68 by Simon Peyton Jones at 2015-12-14T15:54:22+00:00 Wibble - - - - - 10a90ad8 by Herbert Valerio Riedel at 2015-12-14T15:54:22+00:00 Canonicalise Monad instances - - - - - ed68ac50 by Alan Zimmerman at 2015-12-14T15:55:48+00:00 Matching changes for haskell/haddock#11028 - - - - - 3f7e5a2d by Alan Zimmerman at 2015-12-14T15:55:49+00:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 6543a73f by Richard Eisenberg at 2015-12-14T15:59:55+00:00 Update for type=kinds - - - - - 193a5c48 by Matthew Pickering at 2015-12-14T18:17:00+00:00 Changes to compile with 8.0 - - - - - add669ec by Matthew Pickering at 2015-12-14T18:47:12+00:00 Warnings - - - - - 223f3fb4 by Ben Gamari at 2015-12-15T23:45:05+01:00 Update for D1200 - - - - - d058388f by Ben Gamari at 2015-12-16T05:40:17-05:00 Types: Add Outputable[Bndr] DocName instances - - - - - 62ecd7fb by Ben Gamari at 2015-12-16T09:23:09-05:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ddbc187a by Ben Gamari at 2015-12-16T17:54:55+01:00 Update for D1200 - - - - - cec83b52 by Ben Gamari at 2015-12-16T17:54:55+01:00 Types: Add Outputable[Bndr] DocName instances - - - - - d12ecc98 by Ben Gamari at 2015-12-16T17:54:55+01:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ada1616f by Ben Gamari at 2015-12-16T17:54:58+01:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a4f0383d by Ben Gamari at 2015-12-16T23:32:38+01:00 Fix Hyperlinker GHC.con_names is now GHC.getConNames - - - - - a10e6849 by Ben Gamari at 2015-12-20T00:54:11+01:00 Merge remote-tracking branch 'mrhania/testing-framework-improvements' into ghc-head - - - - - f078b4fd by Ben Gamari at 2015-12-20T00:59:51+01:00 test: Compatibility with Cabal 1.23 - - - - - 88a511a9 by Ben Gamari at 2015-12-20T01:14:35+01:00 Merge remote-tracking branch 'phadej/orphans' into ghc-head - - - - - 4e250f36 by Ben Gamari at 2015-12-20T01:14:52+01:00 Add html-test for orphan instances output - - - - - 87fffbad by Alan Zimmerman at 2015-12-20T09:50:42+02:00 Update for GHC trac#11258 Adding locations to RdrName in FieldOcc and AmbiguousFieldOcc - - - - - 6b7e51c9 by idontgetoutmuch at 2015-12-20T21:01:47+00:00 Merge pull request haskell/haddock#1 from haskell/ghc-head Ghc head - - - - - 229c1fb5 by Dominic Steinitz at 2015-12-21T07:19:16+00:00 Handle inline math with mathjax. - - - - - 57902d66 by Dominic Steinitz at 2015-12-21T08:07:11+00:00 Fix the documentation for haddock itself. Change notation and add support for inline math. Allow newlines in display math. Add a command line option for the mathjax url (you might want to use a locally installed version). Rebase tests because of extra url and version change. Respond to (some of the) comments. Fix warnings in InterfaceFile.hs - - - - - 0e69f236 by Herbert Valerio Riedel at 2015-12-21T18:30:43+01:00 Fix-up left-over assumptions of GHC 7.12 into GHC 8.0 - - - - - c67f8444 by Simon Peyton Jones at 2015-12-22T16:26:56+00:00 Follow removal of NamedWildCard from HsType - - - - - da40327a by Ben Gamari at 2015-12-23T14:15:28+01:00 html-test/Operators: Clear up ambiguous types For reasons that aren't entirely clear a class with ambiguous types was accepted by GHC <8.0. I've added a functional dependency to clear up this ambiguity. - - - - - 541b7fa4 by Ben Gamari at 2015-12-23T14:18:51+01:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 0febc947 by Ben Gamari at 2015-12-24T00:30:20+01:00 hoogle-test/AssocTypes: Allow AmbiguousTypes GHC 8.0 complains otherwise - - - - - 25810841 by Ben Gamari at 2015-12-24T00:33:18+01:00 OrphanInstances: Accept test output - - - - - 841987f3 by Ben Gamari at 2015-12-25T11:03:11+01:00 Merge remote-tracking branch 'idontgetoutmuch/ghc-head' into ghc-head - - - - - 358391f0 by Ben Gamari at 2015-12-26T10:44:50+01:00 Add missing import - - - - - a8896885 by Ben Gamari at 2015-12-26T10:45:27+01:00 travis: Use Travis containers - - - - - 85e82134 by Herbert Valerio Riedel at 2015-12-30T17:25:39+01:00 tweak version bounds for GHC-8.1 - - - - - 672a5f75 by randen at 2016-01-01T23:45:25-08:00 The Haddock part for fully gcc-like response files " driver/Main.hs * Moved the response file handling into ResponseFile.hs, updating import section as appropriate. * driver/ResponseFile.hs * New file. In anticipation that maybe some day this could be provided by another library, and to make it possible to unit test, this functionality is pulled out of the Main.hs module, and expanded to support the style/format of response files which gcc uses. * The specification for the format of response files which gcc generates and consumes, seems to be best derived from the gcc code itself (libiberty/argv.c), so that is what has been done here. * This is intended to fix haskell/haddock#379 * driver-test/Main.hs * New file for testing code in the driver source tree * driver-test/ResponseFileSpec.hs * Tests, adapted/adopted from the same gcc code where the escaping/unescaping is from, in the hspec style of unit tests * haddock.cabal * Add the driver-test test-suite. Introduces a new library dependency (upon hspec) for the haddock driver target in the haddock.cabal file, but practically, this should not be a problem as the haddock-api tests already depend on hspec. - - - - - 498781df by Ben Gamari at 2016-01-06T13:41:04+01:00 Version bumps and changelog - - - - - 8451e46a by Ben Gamari at 2016-01-06T13:47:17+01:00 Merge remote-tracking branch 'randen/bug468' - - - - - fb2d9181 by Ben Gamari at 2016-01-06T08:14:42-05:00 Add ResponseFile to OtherModules - - - - - 2cb2d2e3 by Ben Gamari at 2016-01-06T14:35:00+01:00 Merge branch 'master' into ghc-head - - - - - 913477d4 by Eric Seidel at 2016-01-11T14:57:57-08:00 deal with un-wiring of IP class - - - - - c557a4b3 by Alan Zimmerman at 2016-01-15T11:14:35+02:00 Update to match wip/T11430 in GHC - - - - - 3e135093 by Alan Zimmerman at 2016-01-16T18:21:59+01:00 Update to match wip/T11430 in GHC - - - - - c48ef2f9 by Ben Gamari at 2016-01-18T09:50:06+01:00 Merge remote-tracking branch 'gridaphobe/ghc-head' into ghc-head - - - - - 9138a1b0 by Eric Seidel at 2016-01-18T12:50:15+01:00 deal with un-wiring of IP class (cherry picked from commit 17388b0f0029d969d79353be7737eb01c7b8dc5f) - - - - - b48c172e by Joachim Breitner at 2016-01-19T00:11:38+01:00 Make sure --mathjax affects all written HTML files This fixes haskell/haddock#475. - - - - - af61fe63 by Ryan Scott at 2016-02-07T23:25:57+01:00 Render */# instead of TYPE 'Lifted/TYPE 'Unlifted (fixes haskell/haddock#473) - - - - - b6458693 by Ben Gamari at 2016-02-07T23:29:27+01:00 Merge pull request haskell/haddock#477 from haskell/issue-475 Make sure --mathjax affects all written HTML files - - - - - adcc0071 by Ben Gamari at 2016-02-07T23:34:52+01:00 Merge branch 'master' into ghc-head - - - - - d0404e61 by Ben Gamari at 2016-02-08T12:46:49+01:00 doc: Switch to Sphinx - - - - - acb153b3 by Ben Gamari at 2016-02-08T12:46:56+01:00 Document --use-unicode flag - - - - - c20bdf1d by Ben Gamari at 2016-02-08T13:41:24+01:00 Fix GHC and haddock-library dependency bounds - - - - - 8d946801 by Ben Gamari at 2016-02-08T14:54:56+01:00 testsuite: Rework handling of output sanitization Previously un-cleaned artifacts were kept as reference output, making it difficult to tell what has changed and causing spurious changes in the version control history. Here we rework this, cleaning the output during acceptance. To accomplish this it was necessary to move to strict I/O to ensure the reference handle was closed before accept attempts to open the reference file. - - - - - c465705d by Ben Gamari at 2016-02-08T15:36:05+01:00 test: Compare on dump For reasons I don't understand the Xml representations differ despite their textual representations being identical. - - - - - 1ec0227a by Ben Gamari at 2016-02-08T15:36:05+01:00 html-test: Accept test output - - - - - eefbd63a by Ben Gamari at 2016-02-08T15:36:08+01:00 hypsrc-test: Accept test output And fix impredicative Polymorphism testcase. - - - - - d1df4372 by Ben Gamari at 2016-02-08T15:40:44+01:00 Merge branch 'fix-up-testsuite' - - - - - 206a3859 by Phil Ruffwind at 2016-02-08T17:51:21+01:00 Move the permalinks to "#" on the right side Since pull request haskell/haddock#407, the identifiers have been permalinked to themselves, but this makes it difficult to copy the identifier by double-clicking. To work around this usability problem, the permalinks are now placed on the far right adjacent to "Source", indicated by "#". Also, 'namedAnchor' now uses 'id' instead of 'name' (which is obsolete). - - - - - 6c89fa03 by Phil Ruffwind at 2016-02-08T17:54:44+01:00 Update tests for previous commit - - - - - effaa832 by Ben Gamari at 2016-02-08T17:56:17+01:00 Merge branch 'anchors-redux' - - - - - 9a2bec90 by Ben Gamari at 2016-02-08T17:58:40+01:00 Use -fprint-unicode-syntax when --use-unicode is enabled This allows GHC to render `*` as its Unicode representation, among other things. - - - - - 28ecac5b by Ben Gamari at 2016-02-11T18:53:03+01:00 Merge pull request haskell/haddock#480 from bgamari/sphinx Move documentation to ReStructuredText - - - - - 222e5920 by Ryan Scott at 2016-02-11T15:42:42-05:00 Collapse type/data family instances by default - - - - - a80ac03b by Ryan Scott at 2016-02-11T20:17:09-05:00 Ensure expanded family instances render correctly - - - - - 7f985231 by Ben Gamari at 2016-02-12T10:04:22+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - d4eda086 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Various cleanups - - - - - 79bee48d by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show kind signatures for type family variables Addresses GHC haskell/haddock#11588. - - - - - b2981d98 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show 'where ...' after closed type family Seems like we should ideally show the actual equations as well but that seems like it would be a fair amount of work - - - - - cfc0e621 by Ben Gamari at 2016-02-18T22:48:12+01:00 Merge pull request haskell/haddock#483 from bgamari/T11588 Fix GHC haskell/haddock#11588 This fixes GHC haskell/haddock#11588: * Show where ... after closed type families * Show kind signatures on type family type variables - - - - - 256e8a0d by Ben Gamari at 2016-02-18T23:15:39+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 32402036 by Richard Eisenberg at 2016-02-24T13:21:44-05:00 Follow-on changes to support RuntimeRep - - - - - 2b1c572d by Matthew Pickering at 2016-03-04T21:04:02+00:00 Remove unused functions - - - - - eb906f50 by Richard Eisenberg at 2016-03-13T21:17:20+01:00 Follow-on changes to support RuntimeRep (cherry picked from commit ab954263a793d8ced734459d6194a5d89214b66c) - - - - - 8c34ef34 by Richard Eisenberg at 2016-03-14T23:47:23-04:00 Changes due to fix for GHC#11648. - - - - - 0e022014 by Richard Eisenberg at 2016-03-15T14:06:45+01:00 Changes due to fix for GHC#11648. (cherry picked from commit bb994de1ab0c76d1aaf1e39c54158db2526d31f1) - - - - - ed3f78ab by Rik Steenkamp at 2016-04-02T22:20:36+01:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 - - - - - d3210042 by Rik Steenkamp at 2016-04-04T15:43:32+02:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 (cherry picked from commit 3ddcbd6b8e6884bd95028381176eb33bee6896fb) - - - - - 236eec90 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 692ee7e0 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. - - - - - 79619f57 by Ben Gamari at 2016-04-10T23:46:22+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. (cherry picked from commit c6d6a18d85e5e2d9bb5904e6919e8a8d7e31c4c5) - - - - - 3358ccb4 by Ben Gamari at 2016-04-10T23:47:27+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 264949b1 by Ben Gamari at 2016-04-16T17:50:23+02:00 Merge pull request haskell/haddock#482 from RyanGlScott/ghc-head Collapse type/data family instances by default - - - - - 478c483a by Ben Gamari at 2016-04-16T17:51:09+02:00 Merge pull request haskell/haddock#489 from mpickering/unused-functions Remove some unused functions - - - - - c94e55f0 by Ryan Scott at 2016-04-16T17:57:54+02:00 Collapse type/data family instances by default (cherry picked from commit 2da130a8db8f995c119b544fad807533236cf088) - - - - - 31e633d3 by Ryan Scott at 2016-04-16T17:58:06+02:00 Ensure expanded family instances render correctly (cherry picked from commit 1338b5d7c32939de6bbc31af0049477e4f847103) - - - - - 03e4d197 by Matthew Pickering at 2016-04-16T17:58:21+02:00 Remove unused functions (cherry picked from commit b89d1c2456bdb2d4208d94ded56155f7088a37d0) - - - - - ed4116f6 by Ben Gamari at 2016-04-20T10:46:57+02:00 ghc: Install files for needed --hyperlinked-source - - - - - 0be999c4 by Ben Gamari at 2016-04-20T11:37:54+02:00 ghc: Install files for needed --hyperlinked-source (cherry picked from commit 5c82c9fc2d21ddaae4a2470f1c375426968f19c6) - - - - - 4d17544c by Simon Peyton Jones at 2016-04-20T12:42:28+01:00 Track change to HsGroup This relates to a big GHC patch for Trac haskell/haddock#11348 - - - - - 1700a50d by Ben Gamari at 2016-05-01T13:19:27+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. - - - - - 0b7c8125 by Ben Gamari at 2016-05-01T13:21:43+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. (cherry picked from commit 609018dd09c4ffe27f9248b2d8b50f6196cd42b9) - - - - - af115ce0 by Ryan Scott at 2016-05-04T22:15:50-04:00 Render Haddocks for derived instances Currently, one can document top-level instance declarations, but derived instances (both those in `deriving` clauses and standalone `deriving` instances) do not enjoy the same privilege. This makes the necessary changes to the Haddock API to enable rendering Haddock comments for derived instances. This is part of a fix for Trac haskell/haddock#11768. - - - - - 76fa1edc by Ben Gamari at 2016-05-10T18:13:25+02:00 haddock-test: A bit of refactoring for debuggability - - - - - 7d4c4b20 by Ben Gamari at 2016-05-10T18:13:25+02:00 Create: Mark a comment as TODO - - - - - 2a6d0c90 by Ben Gamari at 2016-05-10T18:13:25+02:00 html-test: Update reference output - - - - - bd60913d by Ben Gamari at 2016-05-10T18:13:25+02:00 hypsrc-test: Fix reference file path in cabal file It appears the haddock insists on prefixing --hyperlinked-sourcer output with directory which the source appeared in. - - - - - c1548057 by Ben Gamari at 2016-05-10T18:22:12+02:00 doc: Update extra-source-files in Cabal file - - - - - 41d5bae3 by Ben Gamari at 2016-05-10T18:29:21+02:00 Bump versions - - - - - ca75b779 by Ben Gamari at 2016-05-11T16:03:44+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 4e3cfd62 by Ben Gamari at 2016-05-11T16:06:45+02:00 Merge remote-tracking branch 'RyanGlScott/ghc-head' into ghc-head - - - - - a2379970 by Ben Gamari at 2016-05-11T23:15:11+02:00 doc: Add clean targets - - - - - f275212e by Ben Gamari at 2016-05-11T23:15:14+02:00 doc: Add html as an all-target for ghc Otherwise the html documentation won't be installed for binary-dist. - - - - - 388fc0af by Ben Gamari at 2016-05-12T09:49:12+02:00 Update CHANGES - - - - - bad81ad5 by Ben Gamari at 2016-05-12T09:49:38+02:00 Version bump - - - - - c01688a7 by Ben Gamari at 2016-05-12T10:04:58+02:00 Revert "Version bump" This bump was a bit premature. This reverts commit 7b238d9c5be9b07aa2d10df323b5c7b8d1634dc8. - - - - - 7ed05724 by Ben Gamari at 2016-05-12T10:05:33+02:00 doc: Fix GHC clean rule Apparently GHC's build system doesn't permit wildcards in clean paths. - - - - - 5d9611f4 by Ben Gamari at 2016-05-12T17:43:50+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 653566b2 by Ben Gamari at 2016-05-14T09:57:31+02:00 Version bump to 2.17.2 - - - - - b355c439 by Ben Gamari at 2016-05-14T09:57:51+02:00 doc: Use `$(MAKE)` instead of `make` This is necessary to ensure we use gmake. - - - - - 8a18537d by Ben Gamari at 2016-05-14T10:15:45+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - b3290ef1 by Sebastian Meric de Bellefon at 2016-05-14T11:29:47-04:00 Fix haskell/haddock#303. Hide footer when printing The "Produced by Haddock" footer was overlapping the page's body when printing. This patch hides the footer with a css media rule. - - - - - b4a76f89 by Sebastian Meric de Bellefon at 2016-05-15T02:12:46-04:00 Fix haskell/haddock#280. Parsing of module header The initial newlines were counted as indentation spaces, thus disturbing the parsing of next lines - - - - - ba797c9e by Ben Gamari at 2016-05-16T14:53:46+02:00 doc: Vendorize alabaster Sphinx theme Alabaster is now the default sphinx theme and is a significant improvement over the previous default that it's worthproviding it when unavailable (e.g. Sphinx <1.3). - - - - - c9283e44 by Ben Gamari at 2016-05-16T14:55:17+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 1c9ea198 by Sebastian Méric de Bellefon at 2016-05-16T12:30:40-04:00 Merge pull request haskell/haddock#502 from Helkafen/master Fix haskell/haddock#303. Hide footer when printing - - - - - 33631016 by Ben Gamari at 2016-05-16T19:56:11+02:00 Revert "doc: Vendorize alabaster Sphinx theme" This ended up causes far too many issues to be worthwhile. We'll just have to live with inconsistent haddock documentation. This reverts commit cec21957001143794e71bcd9420283df18e7de40. - - - - - 93317d26 by Ben Gamari at 2016-05-16T19:56:11+02:00 cabal: Fix README path - - - - - c8695b22 by Ben Gamari at 2016-05-16T19:58:51+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 0b50eaaa by Ben Gamari at 2016-05-16T21:02:08+02:00 doc: Use whichever theme sphinx deems appropriate - - - - - 857c1c9c by Ben Gamari at 2016-05-16T21:07:08+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 15fc5637 by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Remove redundant imports - - - - - 132ddc6a by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Better debug output For tracking down haskell/haddock#505 - - - - - 2252a149 by Ben Gamari at 2016-05-22T12:43:59+02:00 Don't consider default class ops when looking for decls When we are looking for an operation within a class we don't care about `default`-type declarations. This was the cause of haskell/haddock#505. - - - - - 4886b2ec by Oleg Grenrus at 2016-05-24T16:19:48+03:00 UnfelpfulSpan line number omitted Kind of resolves https://github.com/haskell/haddock/issues/508 - - - - - a4befd36 by Oleg Grenrus at 2016-05-24T16:53:35+03:00 Change Hyperlinked lexer to know about DataKinds ticks - - - - - f45cb52e by David Feuer at 2016-05-24T18:48:53-04:00 Make parser state a newtype Previously, it was `data` wrapping a `Maybe`, which seems a bit silly. Obviously, this can be changed back if anyone wants to add more fields some day. - - - - - 05013dd7 by Sebastian Meric de Bellefon at 2016-05-24T22:03:55-04:00 remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) Frames are a bit broken, ignored by Hackage, and considered obsolete in general. This patch disables frames generation. The mini_*.html files are still used in the synopsis. - - - - - b8163a88 by Ben Gamari at 2016-05-25T14:44:15+02:00 Merge pull request haskell/haddock#507 from bgamari/T505 Fix haskell/haddock#505 - - - - - ea1b30c6 by Sebastian Meric de Bellefon at 2016-05-25T14:17:00-04:00 Update CHANGES - - - - - eddfc258 by Sebastian Méric de Bellefon at 2016-05-25T15:17:40-04:00 Merge pull request haskell/haddock#514 from Helkafen/frames remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) - - - - - 0e506818 by Alex Biehl at 2016-05-26T12:43:09+02:00 Remove misplaced haddock comment - - - - - a07d28c0 by Ben Gamari at 2016-05-27T11:34:59+02:00 Merge pull request haskell/haddock#515 from alexbiehl/master Remove misplaced haddock comment - - - - - 9001d267 by Ben Gamari at 2016-05-27T11:35:46+02:00 Merge pull request haskell/haddock#513 from treeowl/newtype-since Make parser state a newtype - - - - - 74e1a018 by Sebastian Méric de Bellefon at 2016-05-28T17:28:15-04:00 Merge pull request haskell/haddock#504 from Helkafen/issue-280 Fix haskell/haddock#280. Parsing of module header - - - - - 37557f4f by Alan Zimmerman at 2016-05-29T23:36:50+02:00 Matching changes for haskell/haddock#12105 - - - - - 7d09e5d6 by Sebastian Meric de Bellefon at 2016-06-03T18:07:48-04:00 Version bumps (2.17.3, 1.4.2) - - - - - 85b4bc15 by Sebastian Méric de Bellefon at 2016-06-06T18:35:13-04:00 Merge pull request haskell/haddock#521 from Helkafen/master Version bumps (2.17.3, 1.4.2) - - - - - e95f0dee by Sebastian Meric de Bellefon at 2016-06-06T19:11:35-04:00 publish haddock-test library - - - - - 4de40586 by Sebastian Méric de Bellefon at 2016-06-06T20:26:30-04:00 Merge pull request haskell/haddock#512 from phadej/oleg-fixes Fixes for haskell/haddock#508 and haskell/haddock#510 - - - - - ddfd0789 by Dominic Steinitz at 2016-06-09T09:27:28+01:00 Documentation for LaTeX markup. - - - - - 697a503a by Dominic Steinitz at 2016-06-09T09:33:59+01:00 Fix spelling mistake. - - - - - 246f6fff by Dominic Steinitz at 2016-06-09T09:37:15+01:00 Camel case MathJax. - - - - - 4684bd23 by Dominic Steinitz at 2016-06-09T09:44:53+01:00 Fix math typo and add link. - - - - - f20c037c by Simon Peyton Jones at 2016-06-13T18:26:03+01:00 Follow changes to LHsSigWcType - - - - - 0c58996d by Simon Peyton Jones at 2016-06-15T12:56:01+01:00 Follow GHC re-adding FunTy - - - - - 401b5ca7 by Sebastian Méric de Bellefon at 2016-06-15T12:16:47-04:00 Merge pull request haskell/haddock#525 from idontgetoutmuch/master Documentation for LaTeX markup. - - - - - 92d263b7 by Sebastian Méric de Bellefon at 2016-06-15T12:17:29-04:00 Merge pull request haskell/haddock#522 from Helkafen/master publish haddock-test library - - - - - 0953a2ca by Sebastian Meric de Bellefon at 2016-06-16T00:46:46-04:00 Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 65453e14 by Ben Gamari at 2016-06-16T11:16:32+02:00 ocean: Ensure that synopsis fully covers other content Previously MathJax content was being rendered on top of the synopsis due to ambiguous z-ordering. Here we explicitly give the synopsis block a higher z-index to ensure it is rendered on top. Fixes haskell/haddock#531. - - - - - 68e411a1 by Sebastian Méric de Bellefon at 2016-06-16T23:34:39-04:00 Merge pull request haskell/haddock#534 from bgamari/T531 ocean: Ensure that synopsis fully covers other content - - - - - fad6491b by Sebastian Méric de Bellefon at 2016-06-18T23:57:20-04:00 Merge pull request haskell/haddock#533 from Helkafen/master Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 6108e21b by Sebastian Meric de Bellefon at 2016-06-22T23:08:28-04:00 do not create empty src directory Fix haskell/haddock#536. - - - - - 1ef23823 by Sebastian Méric de Bellefon at 2016-06-24T00:04:48-04:00 Merge pull request haskell/haddock#537 from Helkafen/master do not create empty src directory - - - - - 966baa96 by Omari Norman at 2016-06-29T21:59:34-04:00 Add $ as a special character If this character is not escaped, documentation built with Haddock 2.17.2 will fail. This was not an issue with 2.16 series, which causes builds to fail and there is nothing in the docs or error message giving a clue about why builds that used to succeed now don't. - - - - - 324adb60 by Ben Gamari at 2016-07-01T12:18:51+02:00 GhcUtils: Changes for multi-pattern signatures - - - - - d7571675 by Ömer Sinan Ağacan at 2016-07-21T13:30:47+02:00 Add support for unboxed sums - - - - - 29d0907b by Simon Marlow at 2016-07-22T13:55:48+01:00 Disable NFData instances for GHC types when GHC >= 8.2 - - - - - 702d95f3 by Simon Marlow at 2016-08-02T15:57:30+02:00 Disable NFData instances for GHC types when GHC >= 8.0.2 (cherry picked from commit a3309e797c42dae9bccdeb17ce52fcababbaff8a) - - - - - f4fa79c3 by Ben Gamari at 2016-08-07T13:51:18+02:00 ghc.mk: Don't attempt to install html/frames.html The frames business has been removed. - - - - - 9cd63daf by Ben Gamari at 2016-08-07T13:51:40+02:00 Haddock.Types: More precise version guard This allows haddock to be built with GHC 8.0.2 pre-releases. - - - - - f3d7e03f by Mateusz Kowalczyk at 2016-08-29T20:47:45+01:00 Merge pull request haskell/haddock#538 from massysett/master Add $ as a special character - - - - - 16dbf7fd by Bartosz Nitka at 2016-09-20T19:44:04+01:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 - - - - - 7c31c1ff by Bartosz Nitka at 2016-09-27T17:32:22-04:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 (cherry picked from commit 073d899a8f94ddec698f617a38d3420160a7fd0b) - - - - - 33a90dce by Ryan Scott at 2016-09-30T20:53:41-04:00 Haddock changes for T10598 See https://ghc.haskell.org/trac/ghc/ticket/10598 - - - - - 1f32f7cb by Ben Gamari at 2016-10-13T20:01:26-04:00 Update for refactoring of NameCache - - - - - 1678ff2e by Ben Gamari at 2016-11-15T17:42:48-05:00 Bump upper bound on base - - - - - 9262a7c5 by Alan Zimmerman at 2016-12-07T21:14:28+02:00 Match changes in GHC wip/T3384 branch - - - - - ac0eaf1a by Ben Gamari at 2016-12-09T09:48:41-05:00 haddock-api: Don't use stdcall calling convention on 64-bit Windows See GHC haskell/haddock#12890. - - - - - 04afe4f7 by Alan Zimmerman at 2016-12-12T20:07:21+02:00 Matching changes for GHC wip/T12942 - - - - - e1d1701d by Ben Gamari at 2016-12-13T16:50:41-05:00 Bump base upper bound - - - - - 3d3eacd1 by Alan Zimmerman at 2017-01-10T16:59:38+02:00 HsIParamTy now has a Located name - - - - - 7dbceefd by Kyrill Briantsev at 2017-01-12T13:23:50+03:00 Prevent GHC API from doing optimization passes. - - - - - d48d1e33 by Richard Eisenberg at 2017-01-19T08:41:41-05:00 Upstream changes re levity polymorphism - - - - - 40c25ed6 by Alan Zimmerman at 2017-01-26T15:16:18+02:00 Changes to match haskell/haddock#13163 in GHC - - - - - 504f586d by Ben Gamari at 2017-02-02T17:19:37-05:00 Kill remaining static flags - - - - - 49147ea0 by Justus Adam at 2017-03-02T15:33:34+01:00 Adding MDoc to exports of Documentation.Haddock - - - - - 1cfba9b4 by Justus Adam at 2017-03-09T11:41:44+01:00 Also exposing toInstalledIface - - - - - 53f0c0dd by Ben Gamari at 2017-03-09T13:10:08-05:00 Bump for GHC 8.3 - - - - - c7902d2e by Ben Gamari at 2017-03-09T23:46:02-05:00 Bump for GHC 8.2 - - - - - 4f3a74f8 by Ben Gamari at 2017-03-10T10:21:55-05:00 Merge branch 'ghc-head' - - - - - e273b72f by Richard Eisenberg at 2017-03-14T13:34:04-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - 6ec3d436 by Richard Eisenberg at 2017-03-14T15:15:52-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - eee3cda1 by Ben Gamari at 2017-03-15T15:19:59-04:00 Adapt to EnumSet - - - - - 017cf58e by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 736d6773 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 475f84a0 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 13240b53 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - cd16d529 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 3bea97ae by Edward Z. Yang at 2017-03-15T22:50:46-07:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b2b051ce by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 0f082795 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 20ef63c9 by Edward Z. Yang at 2017-03-22T13:48:12-07:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 45692dcb by Edward Z. Yang at 2017-03-22T14:11:25-07:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4eae8caf by Ben Gamari at 2017-03-23T09:25:33-04:00 Merge commit '240bc38b94ed2d0af27333b23392d03eeb615e82' into HEAD - - - - - 0bbe03f5 by Ben Gamari at 2017-03-23T09:27:28-04:00 haddock-api: Bump bound on GHC - - - - - 65f3ac9d by Alex Biehl at 2017-03-23T17:36:11+01:00 Merge pull request haskell/haddock#581 from JustusAdam/master Adding more exports to Documentation.Haddock - - - - - 37d49a47 by Alex Biehl at 2017-03-23T17:39:14+01:00 Merge pull request haskell/haddock#568 from awson/ghc-head Prevent GHC API from doing optimization passes. - - - - - 1ed047e4 by Brian Huffman at 2017-03-23T17:45:58+01:00 Print any user-supplied kind signatures on type parameters. This applies to type parameters on data, newtype, type, and class declarations, and also to forall-bound type vars in type signatures. - - - - - 1b78ca5c by Brian Huffman at 2017-03-23T17:45:58+01:00 Update test suite to expect kind annotations on type parameters. - - - - - a856b162 by Alex Biehl at 2017-03-23T17:49:32+01:00 Include travis build indication badge - - - - - 8e2e2c56 by Ben Gamari at 2017-03-23T17:20:08-04:00 haddock-api: Bump bound on GHC - - - - - 4d2d9995 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 26d6c150b31bc4580ab17cfd07b6e7f9afe10737) - - - - - a650e20f by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 930cfbe58e2e87f5a4d431d89a3c204934e6e858) - - - - - caa282c2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 2067a2d0afa9cef381d26fb7140b67c62f433fc0) - - - - - 49684884 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 0671abfe7e8ceae2269467a30b77ed9d9656e2cc) - - - - - 4dcfeb1a by Edward Z. Yang at 2017-03-23T17:20:08-04:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 3d77b373dd5807d5d956719dd7c849a11534fa6a) - - - - - 74dd19d2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 94610e9b446324f4231fa6ad4c6ac51e4eba8c0e) - - - - - a9b19a23 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 6cc832dfb1de6088a4abcaae62b25a7e944d55c3) - - - - - d3631064 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit bf3c4d72a0fda38561376eac7eda216158783267) - - - - - ef2148fc by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 07b88c5d4e79b87a319fbb08f8ea01dbb41063c1) - - - - - 2f29518b by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 4eb765ca4205c79539d60b7afa9b7e261a4a49fe) - - - - - 37de047d by Phil Ruffwind at 2017-04-03T11:57:14+02:00 Update MathJax URL MathJax is shutting down their CDN: https://www.mathjax.org/cdn-shutting-down/ They recommend migrating to cdnjs. - - - - - e9d24ba8 by David C. Turner at 2017-04-03T14:58:01+02:00 Add highlight for :target to ocean.css - - - - - 4819a202 by Alex Biehl at 2017-04-11T19:36:48+02:00 Allow base-4.10 for haddock-test - - - - - 44cec69c by Alex Biehl at 2017-04-11T19:39:22+02:00 cabal.project for haddock-api, haddock-library and haddock-test - - - - - 935d0f6a by Alex Biehl at 2017-04-11T19:46:29+02:00 Move dist scripts to scripts/ - - - - - 128e150c by Alex Biehl at 2017-04-11T20:34:46+02:00 Add haddock to cabal.project - - - - - cc8e08ea by Alex Biehl at 2017-04-11T20:35:08+02:00 Read files for hyperlinker eagerly This also exposes Documentation.Haddock.Utf8 - - - - - 152dda78 by Alex Biehl at 2017-04-11T20:37:06+02:00 Explicit import list ofr Control.DeepSeq in Haddock.Interface.Create - - - - - 501b33c4 by Kyrill Briantsev at 2017-04-11T21:01:42+02:00 Prevent GHC API from doing optimization passes. - - - - - c9f3f5ff by Alexander Biehl at 2017-04-12T16:36:53+02:00 Add @alexbiehl as maintaner - - - - - 76f214cc by Alex Biehl at 2017-04-13T07:27:18+02:00 Disable doctest with ghc-8.3 Currently doctest doesn't support ghc-head - - - - - 46b4f5fc by Edward Z. Yang at 2017-04-22T20:38:26-07:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f0555235 by Alex Biehl at 2017-04-25T10:08:48+02:00 Travis: Use ghc-8.2.1 on master - - - - - 966ea348 by Alex Biehl at 2017-04-25T10:32:01+02:00 Travis: Verbose cabal output cf. https://travis-ci.org/haskell/haddock/jobs/225512194#L377 - - - - - 36972bcd by Alex Biehl at 2017-04-25T10:40:43+02:00 Use travis_retry for cabal invocations - - - - - b3a09d2c by Alex Biehl at 2017-04-25T17:02:20+02:00 Use new MathJax URL in html-test 18ed871afb82560d5433b2f53e31b4db9353a74e switched to a new MathJax URL but didn't update the tests. - - - - - ae331e5f by Alexander Biehl at 2017-04-25T17:02:20+02:00 Expand signatures for class declarations - - - - - e573c65a by Alexander Biehl at 2017-04-25T17:02:20+02:00 Hoogle: Correctly print classes with associated data types - - - - - 3fc6be9b by Edward Z. Yang at 2017-04-25T17:02:20+02:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit a0c4790e15a2d3fab8d830eee8fcd639fe6d39c9) - - - - - 6725c060 by Herbert Valerio Riedel at 2017-04-25T17:02:20+02:00 `html-test --accept` deltas to reference samples - - - - - 7d444d61 by Alex Biehl at 2017-04-26T07:13:50+02:00 Remove anything related to obsolete frames mode - - - - - b888972c by Alex Biehl at 2017-04-26T07:49:10+02:00 Cherry-picked remaining commits from haddock-2.17.4-release (#603) * Release haddock/haddock-api 2.17.4 and haddock-library 1.4.3 * Set version bounds for haddock-library NB: This allows GHC 8.2.1's base * Set version bounds for haddock & haddock-api The version bounds support GHC 8.2 * Merge (temporary) v2.17.3 branch into v2.17 This allows us to delete the v2.17.3 branch * Fixup changelog * Pin down haddock-api to a single version as otherwise `haddock`'s package version has no proper meaning * fix source-repo spec for haddock-api - - - - - 4161099b by Alex Biehl at 2017-04-26T11:11:20+02:00 Update changelog to reflect news in HEAD - - - - - eed72cb8 by Alex Biehl at 2017-04-26T11:11:20+02:00 Markdownify changelog - - - - - 5815cea1 by Alex Biehl at 2017-04-26T11:32:33+02:00 Bump to 2.18.0 (#605) - - - - - a551d558 by Alex Biehl at 2017-04-29T22:00:25+02:00 Update attoparsec-0.12.1.1 to attoparsec-0.13.1.0 - - - - - ea164a8d by Sergey Vinokurov at 2017-04-29T22:42:36+02:00 Improve error message - - - - - 2e10122f by Alex Biehl at 2017-04-30T10:07:46+02:00 Correctly remember collapsed sections (#608) Now the "collapsed" cookie stores which sections have changed state instead of which are collapsed. - - - - - f9b24d99 by Alex Biehl at 2017-05-01T17:40:36+02:00 Lazily decode docMap and argMap (#610) These are only used in case of a doc reexport so most of the time decoding these is wasted work. - - - - - 2372af62 by Alex Biehl at 2017-05-01T21:59:23+02:00 Fix Binary instance for InstalledInterface (#611) (#610) introduced lazy decoding for docs from InstalledInterface but forgot to remove the original calls to get and put_ - - - - - 6c633c13 by Nathan Collins at 2017-05-11T11:47:55+02:00 Improve documenation of Haddock markup (#614) * Improve documentation of Haddock markup. - document that Haddock supports inferring types top-level functions with without type signatures, but also explain why using this feature is discouraged. Looks like this feature has been around since version 2.0.0.0 in 2008! - rework the "Module description" section: - move the general discussion of field formatting to the section intro and add examples illustrating the prose for multiline fields. - mention that newlines are preserved in some multiline fields, but not in others (I also noticed that commas in the `Copyright` field are not preserved; I'll look into this bug later). - add a subsection for the module description fields documentation, and put the field keywords in code formatting (double back ticks) instead of double quotes, to be consistent with the typesetting of keywords in other parts of the documentation. - mention that "Named chunks" are not supported in the long-form "Module description" documentation. - fix formatting of keywords in the "Module attributes" section. Perhaps these errors were left over from an automatic translation to ReST from some other format as part of the transition to using Sphinx for Haddock documentation? Also, add a missing reference here; it just said "See ?"! - update footnote about special treatment for re-exporting partially imported modules not being implemented. In my tests it's not implemented at all -- I tried re-exporting both `import B hiding (f)` and `import B (a, b)` style partial imports, and in both cases got the same result as with full imports `import B`: I only get a module reference. * Rework the `Controlling the documentation structure` section. My main goal was to better explain how to use Haddock without an export list, since that's my most common use case, but I hope I improved the section overall: - remove the incomplete `Omitting the export list` section and fold it into the other sections. In particular, summarize the differences between using and not using an export list -- i.e. control over what and in what order is documented -- in the section lead. - add "realistic" examples that use the structure markup, both with and without an export list. I wanted a realistic example here to capture how it can be useful to explain the relationship between a group of functions in a section, in addition to documenting their individual APIs. - make it clear that you can associate documentation chunks with documentation sections when you aren't using an export list, and that doing it in the most obvious way -- i.e. with `-- |`, as you can in the export list -- doesn't work without an export list. It took me a while to figure this out the first time, since the docs didn't explain it at all before. - add a "no export list" example to the section header section. - add more cross references. * Add examples of gotchas for markup in `@...@`. I'm not sure this will help anyone, since I think most people first learn about `@...@` by reading other people's Haddocks, but I've documented the mistakes which I've made and then gotten confused by. * Use consistent Capitalization of Titles. Some titles were in usual title caps, and others only had the first word capitalized. I chose making them all use title caps because that seems to make the cross references look better. - - - - - d4734f45 by Ben Gamari at 2017-05-12T20:36:08+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 93883f37 by Alex Biehl at 2017-05-12T21:02:33+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 5b8f179c by Alex Biehl at 2017-05-13T12:48:10+02:00 Consequently use inClass and notInClass in haddock-library (#617) These allow attoparsec to do some clever lookup optimization - - - - - 77984b82 by Doug Wilson at 2017-05-27T17:37:38+02:00 Don't enable compilation for template haskell (#624) This is no longer necessary after ghc commit 53c78be0aab76a3107c4dacbb1d177afacdd37fa - - - - - 5a3de2b4 by Doug Wilson at 2017-05-27T19:54:53+02:00 Improve Syb code (#621) Specialize.hs and Ast.hs are modified to have their Syb code not recurse into Name or Id in HsSyn types. Specialize.hs is refactored to have fewer calls to Syb functions. Syb.hs has some foldl calls replaced with foldl' calls. There is still a lot of performance on the floor of Ast.hs. The RenamedSource is traversed many times, and lookupBySpan is very inefficient. everywhereBut and lookupBySpan dominate the runtime whenever --hyperlinked-source is passed. - - - - - 3d35a949 by Alex Biehl at 2017-05-30T19:01:37+02:00 Clear fixme comment (#625) - - - - - 2a44bd0c by Alex Biehl at 2017-05-30T19:02:12+02:00 Make haddock-library and haddock-api warning free (#626) - - - - - bd1a0e42 by Alex Biehl at 2017-06-01T10:40:33+02:00 Include `driver-test/*.hs` sdist (#630) This lead to haskell/haddock#629. - - - - - 184a3ab6 by Doug Wilson at 2017-06-03T12:02:08+02:00 Disable pattern match warnings (#628) This disables the pattern match checker which can be very expensive in some cases. The disabled warnings include: * Opt_WarnIncompletePatterns * Opt_WarnIncompleteUniPatterns * Opt_WarnIncompletePatternsRecUpd * Opt_WarnOverlappingPatterns - - - - - 0cf68004 by Alex Biehl at 2017-06-03T20:37:28+02:00 Allow user defined signatures for pattern synonyms (#631) - - - - - 7f51a58a by Alex Biehl at 2017-06-04T11:56:38+02:00 Use NameSet for isExported check (#632) - - - - - d8f044a9 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Match new AST as per GHC wip/new-tree-one-param See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow - - - - - da1254e3 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Rename extension index tags - - - - - 538c7514 by Christiaan Baaij at 2017-06-09T08:26:43+02:00 Haddock support for bundled pattern synonyms (#627) * Haddock support for bundled pattern synonyms * Add fixities to bundled pattern synonyms * Add bundled pattern synonyms to the synopsis * Store bundled pattern fixities in expItemFixities * Add test for bundled pattern synonyms * Stop threading fixities * Include bundled pattern synonyms for re-exported data types Sadly, fixity information isn't found for re-exported data types * Support for pattern synonyms * Modify tests after haskell/haddock#631 * Test some reexport variations * Also lookup bundled pattern synonyms from `InstalledInterface`s * Check isExported for bundled pattern synonyms * Pattern synonym is exported check * Always look for pattern synonyms in the current module Another overlooked cornercase * Account for types named twice in export lists Also introduce a fast function for nubbing on a `Name` and use it throughout the code base. * correct fixities for reexported pattern synonyms * Fuse concatMap and map * Remove obsolete import * Add pattern synonyms to visible exports * Fix test * Remove corner case - - - - - a050bffd by Doug Wilson at 2017-06-21T09:27:33+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#636) There is some performance improvement. GHC compiler: | version | bytes allocated | cpu_seconds --------------------------------- | before | 56057108648 | 41.0 | after | 51592019560 | 35.1 base: | version | bytes allocated | cpu_seconds --------------------------------- | before | 25174011784 | 14.6 | after | 23712637272 | 13.1 Cabal: | version | bytes allocated | cpu_seconds --------------------------------- | before | 18754966920 | 12.6 | after | 18198208864 | 11.6 - - - - - 5d06b871 by Doug Wilson at 2017-06-22T20:23:29+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#639) * Use new function getNameToInstancesIndex instead of tcRnGetInfo There is some significant performance improvement in the ghc testsuite. haddock.base: -23.3% haddock.Cabal: -16.7% haddock.compiler: -19.8% * Remove unused imports - - - - - b11bb73a by Alex Biehl at 2017-06-23T14:44:41+02:00 Lookup fixities for reexports without subordinates (#642) So we agree that reexported declarations which do not have subordinates (for example top-level functions) shouldn't have gotten fixities reexported according to the current logic. I wondered why for example Prelude.($) which is obviously reexported from GHC.Base has fixities attached (c.f. http://hackage.haskell.org/package/base-4.9.1.0/docs/Prelude.html#v:-36-). The reason is this: In mkMaps we lookup all the subordinates of top-level declarations, of course top-level functions don't have subordinates so for them the resulting list is empty. In haskell/haddock#644 I established the invariant that there won't be any empty lists in the subordinate map. Without the patch from haskell/haddock#642 top-level functions now started to fail reexporting their fixities. - - - - - d2a6dad6 by Alex Biehl at 2017-06-23T18:30:45+02:00 Don't include names with empty subordinates in maps (#644) These are unecessary anyway and just blow up interface size - - - - - 69c2aac4 by Alex Biehl at 2017-06-29T19:54:49+02:00 Make per-argument docs for class methods work again (#648) * Make per-argument docs for class methods work again * Test case - - - - - c9448d54 by Bartosz Nitka at 2017-07-02T12:12:01+02:00 Fix haddock: internal error: links: UnhelpfulSpan (#561) * Fix haddock: internal error: links: UnhelpfulSpan This fixes haskell/haddock#554 for me. I believe this is another fall out of `wildcard-refactor`, like haskell/haddock#549. * Comment to clarify why we take the methods name location - - - - - d4f29eb7 by Alex Biehl at 2017-07-03T19:43:04+02:00 Document record fields when DuplicateRecordFields is enabled (#649) - - - - - 9d6e3423 by Yuji Yamamoto at 2017-07-03T22:37:58+02:00 Fix test failures on Windows (#564) * Ignore .stack-work * Fix for windows: use nul instead of /dev/null * Fix for windows: canonicalize line separator * Also normalize osx line endings - - - - - 7d81e8b3 by Yuji Yamamoto at 2017-07-04T16:13:12+02:00 Avoid errors on non UTF-8 Windows (#566) * Avoid errors on non UTF-8 Windows Problem ==== haddock exits with errors like below: `(1)` ``` haddock: internal error: <stderr>: hPutChar: invalid argument (invalid character) ``` `(2)` ``` haddock: internal error: Language\Haskell\HsColour\Anchors.hs: hGetContents: invalid argument (invalid byte sequence) ``` `(1)` is caused by printing [the "bullet" character](http://www.fileformat.info/info/unicode/char/2022/index.htm) onto stderr. For example, this warning contains it: ``` Language\Haskell\HsColour\ANSI.hs:62:10: warning: [-Wmissing-methods] • No explicit implementation for ‘toEnum’ • In the instance declaration for ‘Enum Highlight’ ``` `(2)` is caused when the input file of `readFile` contains some Unicode characters. In the case above, '⇒' is the cause. Environment ---- OS: Windows 10 haddock: 2.17.3 GHC: 8.0.1 Solution ==== Add `hSetEncoding handle utf8` to avoid the errors. Note ==== - I found the detailed causes by these changes for debugging: - https://github.com/haskell/haddock/commit/8f29edb6b02691c1cf4c479f6c6f3f922b35a55b - https://github.com/haskell/haddock/commit/1dd23bf2065a1e1f2c14d0f4abd847c906b4ecb4 - These errors happen even after executing `chcp 65001` on the console. According to the debug code, `hGetEncoding stderr` returns `CP932` regardless of the console encoding. * Avoid 'internal error: <stderr>: hPutChar: invalid argument (invalid character)' non UTF-8 Windows Better solution for 59411754a6db41d17820733c076e6a72bcdbd82b's (1) - - - - - eded67d2 by Alex Biehl at 2017-07-07T19:17:15+02:00 Remove redudant import warning (#651) - - - - - 05114757 by Alex Biehl at 2017-07-08T00:33:12+02:00 Avoid missing home module warning (#652) * Avoid missing home module warning * Update haddock-library.cabal - - - - - e9cfc902 by Bryn Edwards at 2017-07-17T07:51:20+02:00 Fix haskell/haddock#249 (#655) - - - - - eb02792b by Herbert Valerio Riedel at 2017-07-20T09:09:15+02:00 Fix compilation of lib:haddock-library w/ GHC < 8 - - - - - 9200bfbc by Alex Biehl at 2017-07-20T09:20:38+02:00 Prepare 2.18.1 release (#657) - - - - - 46ddd22c by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Tweak haddock-api.cabal for pending release - - - - - 85e33d29 by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Avoid trivial use of LambdaCase otherwise we can't test w/ e.g. GHC 7.4.2 - - - - - 3afb4bfe by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Refactor .cabal to use sub-lib for vendored lib A practical benefit is that we can control the build-depends and also avoid some recompilation between library and test-suite. - - - - - e56a552e by Herbert Valerio Riedel at 2017-07-20T10:17:48+02:00 haddock-api: add changelog pointing to haddock's changelog This addresses https://github.com/haskell/haddock/issues/638#issuecomment-309283297 - - - - - 2222ff0d by Herbert Valerio Riedel at 2017-07-20T10:19:56+02:00 Drop obsolete/misleading `stability: experimental` This .cabal property has long been considered obsolete - - - - - 9b882905 by Alex Biehl at 2017-07-20T11:25:54+02:00 Beef up haddock description (#658) * Beef up haddock description * Handle empty lines - - - - - bb60e95c by Herbert Valerio Riedel at 2017-07-20T12:08:53+02:00 Import @aisamanra's Haddock cheatsheet from https://github.com/aisamanra/haddock-cheatsheet - - - - - 0761e456 by Herbert Valerio Riedel at 2017-07-20T12:12:55+02:00 Add cheatsheet to haddock.cabal - - - - - 2ece0f0f by Herbert Valerio Riedel at 2017-07-20T12:18:38+02:00 Mention new-build in README - - - - - 947b7865 by Herbert Valerio Riedel at 2017-07-20T12:32:16+02:00 Update README Also improves markup and removes/fixes redundant/obsolete parts [skip ci] - - - - - 785e09ad by Alex Biehl at 2017-07-27T07:28:57+02:00 Bump haddock to 2.18.2, haddock-library to 1.4.5 - - - - - e3ff1ca3 by Alex Biehl at 2017-07-31T20:15:32+02:00 Move `DocMarkup` from haddock-api to haddock-library (#659) * Move `DocMarkup` from haddock-api to haddock-library * Move more markup related functions * Markup module * CHANGELOG - - - - - cda7c20c by Alex Biehl at 2017-07-31T20:35:49+02:00 Fixup haddock - - - - - 583b6812 by Alex Biehl at 2017-07-31T21:20:45+02:00 Changelog for haddock-library - - - - - bac6a0eb by Alex Biehl at 2017-07-31T21:50:24+02:00 Prepare haddock-library-1.4.5 release - - - - - 58ce6877 by Moritz Drexl at 2017-08-05T16:44:40+02:00 Fix renaming after instance signature specializing (#660) * rework rename * Add regression test for Bug 613 * update tests * update changelog - - - - - b8137ec8 by Tim Baumann at 2017-08-06T11:33:38+02:00 Fix: Generate pattern signatures for constructors exported as patterns (#663) * Fix pretty-printing of pattern signatures Pattern synonyms can have up to two contexts, both having a different semantic meaning: The first holds the constraints required to perform the matching, the second contains the constraints provided by a successful pattern match. When the first context is empty but the second is not it is necessary to render the first, empty context. * Generate pattern synonym signatures for ctors exported as patterns This fixes haskell/haddock#653. * Simplify extractPatternSyn It is not necessary to generate the simplest type signature since it will be simplified when pretty-printed. * Add changelog entries for PR haskell/haddock#663 * Fix extractPatternSyn error message - - - - - d037086b by Alex Biehl at 2017-08-06T12:43:25+02:00 Bump haddock-library - - - - - 99d7e792 by Alex Biehl at 2017-08-06T12:44:07+02:00 Bump haddock-library in haddock-api - - - - - 94802a5b by Alex Biehl at 2017-08-06T13:18:02+02:00 Provide --show-interface option to dump interfaces (#645) * WIP: Provide --show-interface option to dump interfaces Like ghcs own --show-iface this flag dumps a binary interface file to stdout in a human (and machine) readable fashion. Currently it uses json as output format. * Fill all the jsonNull stubs * Rework Bifunctor instance of DocH, update changelog and documentation * replace changelog, bring DocMarkupH doc back * Update CHANGES.md * Update CHANGES.md * Move Control.Arrow up It would result in unused import if the Bifunctor instance is not generated. - - - - - c662e476 by Ryan Scott at 2017-08-14T21:00:21-04:00 Adapt to haskell/haddock#14060 - - - - - b891eb73 by Alex Biehl at 2017-08-16T08:24:48+02:00 Bifoldable and Bitraversable for DocH and MetaDoc - - - - - 021bb56c by Alex Biehl at 2017-08-16T09:06:40+02:00 Refactoring: Make doc renaming monadic This allows us to later throw warnings if can't find an identifier - - - - - 39fbf022 by Alex Biehl at 2017-08-19T20:35:27+02:00 Hyperlinker: Avoid linear lookup in enrichToken (#669) * Make Span strict in Position * Hyperlinker: Use a proper map to enrich tokens - - - - - e13baedd by Alex Biehl at 2017-08-21T20:05:42+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 27dd6e87 by Alex Biehl at 2017-08-21T22:06:35+02:00 Drop Avails from export list - - - - - 86b247e2 by Alex Biehl at 2017-08-22T08:44:22+02:00 Bump ghc version for haddock-api tests - - - - - d4607ca0 by Alex Biehl at 2017-08-22T08:45:17+02:00 Revert "Drop Avails from export list" This reverts commit a850ba86d88a4fb9c0bd175453a2580e544e3def. - - - - - c9c54c30 by Alex Biehl at 2017-08-22T09:26:01+02:00 IntefaceFile version - - - - - a85b7c02 by Ben Gamari at 2017-08-22T09:29:52-04:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 34e976f5 by Ben Gamari at 2017-08-22T17:40:06+02:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 577abf06 by Ryan Scott at 2017-08-23T14:47:29-04:00 Update for haskell/haddock#14131 - - - - - da68fc55 by Florian Eggenhofer at 2017-08-27T18:21:56+02:00 Generate an index for package content search (#662) Generate an index for package content search - - - - - 39e62302 by Alex Biehl at 2017-08-27T18:50:16+02:00 Content search for haddock html doc - - - - - 91fd6fb2 by Alex Biehl at 2017-08-28T18:39:58+02:00 Fix tests for content search - - - - - b4a3798a by Alex Biehl at 2017-08-28T18:44:08+02:00 Add search button to #page-menu - - - - - 25a7ca65 by Alex Biehl at 2017-08-28T18:47:43+02:00 Load javascript below the fold - - - - - 8d323c1a by Alex Biehl at 2017-08-28T18:49:22+02:00 Accept tests - - - - - c5dac557 by Alex Biehl at 2017-08-28T19:14:55+02:00 Content search css - - - - - 89a5af57 by Paolo Veronelli at 2017-08-29T07:42:13+02:00 Removed `nowrap` for interface method sigs (#674) with nowrap the interfaces method sigs would expand at libitum - - - - - a505f6f7 by Alex Biehl at 2017-08-29T08:05:33+02:00 Include subordinates in content index - - - - - 4bb698c4 by Alexander Biehl at 2017-08-29T11:40:19+02:00 QuickNav: Make docbase configurable - - - - - c783bf44 by Alexander Biehl at 2017-08-29T11:48:36+02:00 QuickNav: Also use baseUrl for doc-index.json request - - - - - 47017510 by Alex Biehl at 2017-08-29T17:56:47+02:00 Fix test fallout (again) - - - - - 924fc318 by Alex Biehl at 2017-08-30T09:24:56+02:00 Write meta.json when generating html output (#676) - - - - - 717dea52 by Alex Biehl at 2017-09-01T09:20:34+02:00 Use relative URL when no docBaseUrl given - - - - - e5d85f3b by Alex Biehl at 2017-09-01T09:35:19+02:00 Add missing js files to data-files (#677) - - - - - 95b9231a by Alex Biehl at 2017-09-01T11:01:36+02:00 Rename "Search" tab to "Quick Jump" - - - - - da0ead0b by Alex Biehl at 2017-09-01T13:03:49+02:00 Make trigger link configurable (#678) QuickNav: Configurable show/hide trigger - - - - - de7da594 by Ben Gamari at 2017-09-05T06:49:55-04:00 Account for "Remember the AvailInfo for each IE" As of GHC commit f609374a55bdcf3b79f3a299104767aae2ffbf21 GHC retains the AvailInfo associated with each IE. @alexbiehl has a patch making proper use of this change, but this is just to keep things building. - - - - - b05cd3b3 by Ben Gamari at 2017-09-14T07:55:07-04:00 Bump upper bound on base - - - - - 79db899e by Herbert Valerio Riedel at 2017-09-21T23:27:52+02:00 Make compatible with Prelude.<> export in GHC 8.4/base-4.11 - - - - - 3405dd52 by Tim Baumann at 2017-09-23T22:02:01+02:00 Add compile step that bundles and compresses JS files (#684) * Add compile step that bundles and compresses JS files Also, manage dependencies on third-party JS libraries using NPM. * Compile JS from TypeScript * Enable 'noImplicitAny' in TypeScript * QuickJump: use JSX syntax * Generate source maps from TypeScript for easier debugging * TypeScript: more accurate type * Separate quick jump css file from ocean theme - - - - - df0b5742 by Alex Biehl at 2017-09-29T21:15:40+02:00 Bump base for haddock-library and haddock-test - - - - - 62b12ea0 by Merijn Verstraaten at 2017-10-04T16:03:13+02:00 Inhibit output of coverage information for hidden modules. (#687) * Inhibit output of coverage information for hidden modules. * Add changelog entry. - - - - - 8daf8bc1 by Alexander Biehl at 2017-10-05T11:27:05+02:00 Don't use subMap in attachInstances - - - - - ad75114e by Alexander Biehl at 2017-10-05T11:27:58+02:00 Revert "Don't use subMap in attachInstances" This reverts commit 3adf5bcb1a6c5326ab33dc77b4aa229a91d91ce9. - - - - - 7d4aa02f by Alex Biehl at 2017-10-08T15:32:28+02:00 Precise Haddock: Use Avails for export resolution (#688) * Use Avails for export resolution * Support reexported modules * Factor out availExportItem * Use avails for fullModuleExports * Don't use subMap in attachInstances * lookupDocs without subMap * Completely remove subMap * Only calculate unqualified modules when explicit export list is given * Refactor * Refine comment * return * Fix * Refactoring * Split avail if declaration is not exported itself * Move avail splitting - - - - - b9b4faa8 by Alex Biehl at 2017-10-08T19:38:21+02:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 43325295 by Alex Biehl at 2017-10-08T20:18:46+02:00 Fix merge fallout - - - - - c6423cc0 by Alex Biehl at 2017-10-08T20:36:12+02:00 Copy QuickJump files over - - - - - 1db587c3 by Tim Baumann at 2017-10-09T18:33:09+02:00 Use <details> element for collapsibles (#690) * Remove unnecessary call to 'collapseSection' The call is unnecessary since there is no corresponding toggle for hiding the section of orphan instances. * Use <details> for collapsibles This makes them work even when JS is disabled. Closes haskell/haddock#560. - - - - - 1b54c64b by Tim Baumann at 2017-10-10T09:50:59+02:00 Quick Jump: Show error when loading 'doc-index.json' failed (#691) - - - - - 910f716d by Veronika Romashkina at 2017-10-24T07:36:20+02:00 Fix tiny typo in docs (#693) - - - - - b21de7e5 by Ryan Scott at 2017-10-24T13:07:15+02:00 Overhaul Haddock's rendering of kind signatures (#681) * Overhaul Haddock's rendering of kind signatures * Strip off kind signatures when specializing As an added bonus, this lets us remove an ugly hack specifically for `(->)`. Yay! * Update due to 0390e4a0f61e37bd1dcc24a36d499e92f2561b67 * @alexbiehl's suggestions * Import injectiveVarsOfBinder from GHC - - - - - 6704405c by Ryan Scott at 2017-10-28T07:10:27+02:00 Fix Haddock rendering of kind-indexed data family instances (#694) - - - - - 470f6b9c by Alex Biehl at 2017-10-30T08:45:51+01:00 Add QuickJump version to meta.json (#696) - - - - - b89eccdf by Alex Biehl at 2017-10-30T10:15:49+01:00 Put Quickjump behind --quickjump flag (#697) - - - - - 3095fb58 by Alex Biehl at 2017-10-30T19:09:06+01:00 Add build command to package.json - - - - - f223fda9 by Alex Biehl at 2017-10-30T19:10:39+01:00 Decrease threshold for fuzzy matching - - - - - 80245dda by Edward Z. Yang at 2017-10-31T20:35:05+01:00 Supported reexported-modules via --reexport flag. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 7e389742 by Alex Biehl at 2017-10-31T20:37:56+01:00 Correct missing title in changelog - - - - - 1a2a1c03 by Alex Biehl at 2017-10-31T20:59:07+01:00 Copy quickjump.css for nicer error messages - - - - - db234bb9 by Alex Biehl at 2017-10-31T21:31:18+01:00 Reexported modules: Report warnings if argument cannot be parsed or ... module cannot be found - - - - - eea8a205 by Carlo Hamalainen at 2017-10-31T21:43:14+01:00 More general type for nameCacheFromGhc. (#539) - - - - - 580eb42a by Alex Biehl at 2017-10-31T21:46:52+01:00 Remote tab - - - - - 0e599498 by Alex Biehl at 2017-10-31T21:48:55+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 7b8539bb by Alex Biehl at 2017-10-31T22:28:34+01:00 fullModuleContents traverses exports in declaration order - - - - - 0c91fbf2 by Alex Biehl at 2017-10-31T22:32:31+01:00 Remove excessive use of list comprehensions - - - - - f7356e02 by Alex Biehl at 2017-11-01T19:11:03+01:00 Make better use of AvailInfo - - - - - f3e512d5 by Alex Biehl at 2017-11-02T12:16:22+01:00 Always return documentation for exported subordinates ... event if they have no documentation (e.g. noDocForDecl) By using the information in the AvailInfo we don't need additional export checks. - - - - - 7cf58898 by Alan Zimmerman at 2017-11-07T08:28:03+02:00 Match changes for Trees that Grow in GHC - - - - - e5105a41 by Alan Zimmerman at 2017-11-08T17:21:58+02:00 Match Trees That Grow - - - - - 55178266 by Alan Zimmerman at 2017-11-11T22:20:31+02:00 Match Trees that Grow in GHC for HsExpr - - - - - 2082ab02 by Ryan Scott at 2017-11-14T15:27:03+01:00 Actually render infix type operators as infix (#703) * Actually render infix type operators as infix * Account for things like `(f :*: g) p`, too - - - - - c52ab7d0 by Alan Zimmerman at 2017-11-14T23:14:26+02:00 Clean up use of PlaceHolder, to match TTG - - - - - 81cc9851 by Moritz Angermann at 2017-11-20T07:52:49+01:00 Declare use of `Paths_haddock` module in other-modules (#705) This was detected by `-Wmissing-home-modules` - - - - - f9d27598 by Moritz Angermann at 2017-11-20T12:47:34+01:00 Drop Paths_haddock from ghc.mk (#707) With haskell/haddock#705 and haskell/haddock#706, the custom addition should not be necessary any more. # Conflicts: # ghc.mk - - - - - f34818dc by Moritz Angermann at 2017-11-20T12:47:59+01:00 Add autogen-modules (#706) > Packages using 'cabal-version: >= 1.25' and the autogenerated module Paths_* must include it also on the 'autogen-modules' field besides 'exposed-modules' and 'other-modules'. This specifies that the module does not come with the package and is generated on setup. Modules built with a custom Setup.hs script also go here to ensure that commands like sdist don't fail. # Conflicts: # haddock.cabal - - - - - bb43a0aa by Ben Gamari at 2017-11-21T15:50:12-05:00 Revert "Clean up use of PlaceHolder, to match TTG" This reverts commit 134a7bb054ea730b13c8629a76232d73e3ace049. - - - - - af9ebb2b by Ben Gamari at 2017-11-21T15:50:14-05:00 Revert "Match Trees that Grow in GHC for HsExpr" This reverts commit 9f054dc365379c66668de6719840918190ae6e44. - - - - - 5d35c3af by Ben Gamari at 2017-11-21T15:50:15-05:00 Revert "Match Trees That Grow" This reverts commit 73a26af844ac50b8bec39de11d64452a6286b00c. - - - - - 99a8e43b by Ben Gamari at 2017-11-21T16:36:06-05:00 Revert "Match changes for Trees that Grow in GHC" This reverts commit 01eeeb048acd2dd05ff6471ae148a97cf0720547. - - - - - c4d650c2 by Ben Gamari at 2017-12-04T15:06:07-05:00 Bump GHC version - - - - - 027b2274 by Ben Gamari at 2017-12-04T17:06:31-05:00 Bump GHC bound to 8.4.* - - - - - 58eaf755 by Alex Biehl at 2017-12-06T15:44:24+01:00 Update changelog - - - - - d68f5584 by Simon Peyton Jones at 2017-12-07T14:39:56+00:00 Track changes to follow Trac haskell/haddock#14529 This tracks the refactoring of HsDecl.ConDecl. - - - - - dc519d6b by Alec Theriault at 2018-01-06T08:20:43-08:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - 8285118c by Alec Theriault at 2018-01-13T12:12:37+01:00 Constructor and pattern synonym argument docs (#709) * Support Haddocks on constructor arguments This is in conjunction with https://phabricator.haskell.org/D4094. Adds support for rendering Haddock's on (non-record) constructor arguments, both for regular and GADT constructors. * Support haddocks on pattern synonym arguments It appears that GHC already parsed these - we just weren't using them. In the process of doing this, I tried to deduplicate some code around handling patterns. * Update the markup guide Add some information about the new support for commenting constructor arguments, and mention pattern synonyms and GADT-style constructors. * Overhaul LaTeX support for data/pattern decls This includes at least * fixing several bugs that resulted in invalid LaTeX * fixing GADT data declaration headers * overhaul handling of record fields * overhaul handling of GADT constructors * overhaul handling of bundled patterns * add support for constructor argument docs * Support GADT record constructors This means changes what existing HTML docs look like. As for LaTeX, looks like GADT records were never even supported. Now they are. * Clean up code/comments Made code/comments consistent between the LaTeX and XHTML backend when possible. * Update changelog * Patch post-rebase regressions * Another post-rebase change We want return values to be documentable on record GADT constructors. - - - - - ca4fabb4 by Alec Theriault at 2018-01-15T17:12:18-08:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 4c472fea by Ryan Scott at 2018-01-19T10:44:02+01:00 Fix haskell/haddock#732 (#733) - - - - - bff14dbd by Alex Biehl at 2018-01-19T15:33:30+01:00 extractDecl: Extract associated types correctly (#736) - - - - - a2a94a73 by Alex Biehl at 2018-01-19T15:34:40+01:00 extractDecl: Extract associated types correctly (#736) - - - - - 26df93dc by Alex Biehl at 2018-01-20T10:18:22+01:00 haddock-api: bump ghc to ^>= 8.4 - - - - - f65aeb1d by Alex Biehl at 2018-01-20T19:18:20+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - 0e721b97 by Alex Biehl at 2018-01-20T19:20:19+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - cb6234f6 by Ben Gamari at 2018-01-26T13:40:55-05:00 Merge remote-tracking branch 'harpocrates/fix/missing-orphan-instances' into ghc-head - - - - - 0fc28554 by Alec Theriault at 2018-02-01T14:58:18+01:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - b9123772 by Alec Theriault at 2018-02-01T14:58:18+01:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 0c12e274 by Ryan Scott at 2018-02-01T14:58:18+01:00 Fix haskell/haddock#548 by rendering datatype kinds more carefully (#702) - - - - - 8876d20b by Alec Theriault at 2018-02-01T14:58:18+01:00 Use the GHC lexer for the Hyperlinker backend (#714) * Start changing to use GHC lexer * better cpp * Change SrcSpan to RealSrcSpan * Remove error * Try to stop too many open files * wip * wip * Revert "wip" This reverts commit b605510a195f26315e3d8ca90e6d95a6737553e1. Conflicts: haddock-api/haddock-api.cabal haddock-api/src/Haddock/Interface.hs * Remove pointless 'caching' * Use dlist rather than lists when finding vars * Use a map rather than list * Delete bogus comment * Rebase followup Things now run using the GHC lexer. There are still - stray debug statements - unnecessary changes w.r.t. master * Cleaned up differences w.r.t. current Haddock HEAD Things are looking good. quasiquotes in particular look beautiful: the TH ones (with Haskell source inside) colour/link their contents too! Haven't yet begun to check for possible performance problems. * Support CPP and top-level pragmas The support for these is hackier - but no more hacky than the existing support. * Tests pass, CPP is better recognized The tests were in some cases altered: I consider the new output to be more correct than the old one.... * Fix shrinking of source without tabs in test * Replace 'Position'/'Span' with GHC counterparts Replaces 'Position' -> 'GHC.RealSrcLoc' and 'Span' -> 'GHC.RealSrcSpan'. * Nits * Forgot entry in .cabal * Update changelog - - - - - 95c6a771 by Alec Theriault at 2018-02-01T14:58:18+01:00 Clickable anchors for headings (#716) See haskell/haddock#579. This just adds an <a> tag around the heading, pointing to the heading itself. - - - - - 21463d28 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump: Matches on function names weight more than matches in ... module names. - - - - - 8023af39 by Alex Biehl at 2018-02-01T14:58:18+01:00 Treat escaped \] better in definition lists (#717) This fixes haskell/haddock#546. - - - - - e4866dc1 by Alex Biehl at 2018-02-01T14:58:18+01:00 Remove scanner, takeWhile1_ already takes care of escaping - - - - - 9bcaa49d by Alex Biehl at 2018-02-01T14:58:18+01:00 Take until line feed - - - - - 01d2af93 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Add simple framework for running parser fixtures (#668) * Add simple framework for running parser fixtures * Compatible with tree-diff-0.0.0.1 * Use parseParas to parse fixtures This allows to test all syntactic constructs available in haddock markup. - - - - - 31128417 by Alec Theriault at 2018-02-01T14:58:18+01:00 Patch flaky parser test (#720) * Patch flaky parser test This test was a great idea, but it doesn't port over too well to using the GHC lexer. GHC rewrites its input a bit - nothing surprising, but we need to guard against those cases for the test. * Change instance head * Change use site - - - - - 9704f214 by Herbert Valerio Riedel at 2018-02-01T14:58:18+01:00 Include secondary LICENSE file in source dist - - - - - 51f25074 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Grid Tables (#718) * Add table examples * Add table types and adopt simple parser Simple parser is done by Giovanni Cappellotto (@potomak) in https://github.com/haskell/haddock/pull/577 It seems to support single fine full tables, so far from full RST-grid tables, but it's good start. Table type support row- and colspans, but obviously parser is lacking. Still TODO: - Latex backend. Should we use multirow package https://ctan.org/pkg/multirow?lang=en? - Hoogle backend: ? * Implement grid-tables * Refactor table parser * Add two ill-examples * Update CHANGES.md * Basic documentation for tables * Fix documentation example - - - - - 670d6200 by Alex Biehl at 2018-02-01T14:58:18+01:00 Add grid table example to cheatsheet (pdf and svg need to be regenerated thought) - - - - - 4262dec9 by Alec Theriault at 2018-02-01T14:58:18+01:00 Fix infinite loop when specializing instance heads (#723) * Fix infinite loop when specializing instance heads The bug can only be triggered from TH, hence why it went un-noticed for so long. * Add test for haskell/haddock#679 and haskell/haddock#710 - - - - - 67ecd803 by Alec Theriault at 2018-02-01T14:58:18+01:00 Filter RTS arguments from 'ghc-options' arguments (#725) This fixes haskell/haddock#666. - - - - - 7db26992 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump Scrollable overlay - - - - - da9ff634 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Hyperlinker: Adjust parser to new PFailed constructor - - - - - 7b7cf8cb by Alexander Biehl at 2018-02-01T14:58:18+01:00 Specialize: Add missing IdP annotations - - - - - 78cd7231 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Convert: Correct pass type - - - - - a2d0f590 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Warning free compilation - - - - - cd861cf3 by Alexander Biehl at 2018-02-01T14:58:18+01:00 hadock-2.19.0 / haddock-api-2.19.0 / haddock-library-1.5.0 - - - - - c6651b72 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Adjust changelogs - - - - - 1e93da0b by Alexander Biehl at 2018-02-01T14:58:18+01:00 haddock-library: Info about breaking changes - - - - - f9b11db8 by Alec Theriault at 2018-02-02T12:36:02+01:00 Properly color pragma contents in hyperlinker The hyperlinker backend now classifies the content of pragmas as 'TkPragma'. That means that in something like '{-# INLINE foo #-}', 'foo' still gets classified as a pragma token. - - - - - c40b0043 by Alec Theriault at 2018-02-02T12:36:02+01:00 Support the new 'ITcolumn_prag' token - - - - - 4a2a4d39 by Alex Biehl at 2018-02-03T12:11:55+01:00 QuickJump: Mitigate encoding problems on Windows - - - - - bb34503a by Alex Biehl at 2018-02-04T18:39:31+01:00 Use withBinaryFile - - - - - 637605bf by Herbert Valerio Riedel at 2018-02-05T09:48:32+01:00 Try GHC 8.4.1 for Travis CI job - - - - - 7abb67e4 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 try harder to build w/ GHC 8.4.1 - - - - - 8255cc98 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 Add `SPDX-License-Identifier` as alised for "license" module header tokens C.f. SPDX 2.1 - Appendix V https://spdx.org/spdx-specification-21-web-version#h.twlc0ztnng3b The tag should appear on its own line in the source file, generally as part of a comment. SPDX-License-Identifier: <SPDX License Expression> Cherry-picked from haskell/haddock#743 - - - - - 267cd23d by Herbert Valerio Riedel at 2018-02-05T10:24:34+01:00 Make test-suite SMP compatible - - - - - 95d4bf40 by Alec Theriault at 2018-02-05T22:01:04+01:00 Hyperlink pattern synonyms and 'module' imports (#744) Links to pattern synonyms are now generated, as well as links from modules in import lists. Fixes haskell/haddock#731. - - - - - 67838dcd by Alec Theriault at 2018-02-06T08:23:36+01:00 Don't warn about missing '~' (#746) This manually filters out '~' from the list of things to warn about. It truly makes no sense to warn on this since '~' has nothing it could link to - it is magical. This fixes haskell/haddock#532. - - - - - ab6c3f9f by Alec Theriault at 2018-02-06T08:24:47+01:00 Don't barf on 'HsSpliceTy' (#745) This handles 'HsSpliceTy's by replacing them with what they expand to. IIUC everything that is happening, 'renameHsSpliceTy' should not be able to fail for the inputs we feed it from GHC. This fixes haskell/haddock#574. - - - - - 92bf95ad by Alex Biehl at 2018-02-06T08:28:23+01:00 Rename: renameHsSpliceTy ttg - - - - - 3130b1e1 by Alex Biehl at 2018-02-06T09:02:14+01:00 Expand SigDs - - - - - c72adae5 by Alex Biehl at 2018-02-06T09:20:51+01:00 fullModuleContents: support named docs - - - - - de2e4dbf by Alex Biehl at 2018-02-06T13:56:17+01:00 Hyperlinker: Also link pattern synonym arguments - - - - - b7c98237 by Alex Biehl at 2018-02-09T18:44:23+01:00 Expand SigD in a better place In https://github.com/haskell/haddock/issues/287 we found that haddock-2.19.0 would miss documentation on class methods with multiples names. This patch uses expandSigDecls in a more sensible place. - - - - - 8f598b27 by Alec Theriault at 2018-02-11T12:29:56+01:00 Add module tooltips to linked identifiers (#753) No more clicking to figure out whether your bytestring is strict or lazy! - - - - - d812e65d by Alec Theriault at 2018-02-11T12:31:44+01:00 Add 'show' option to complement 'hide' (#752) * Add 'show' option to complement 'hide' The behaviour is for flags passed in the command line to override flags in file headers. In the command line, later flags override earlier ones. Fixes haskell/haddock#751 and haskell/haddock#266. * Add a '--show-all' option - - - - - 6676cecb by Alex Biehl at 2018-02-18T11:07:15-05:00 QuickJump: Mitigate encoding problems on Windows (cherry picked from commit 86292c54bfee2343aee84559ec01f1fc68f52231) - - - - - e753dd88 by Alex Biehl at 2018-02-18T17:59:54+01:00 Use withBinaryFile - - - - - 724dc881 by Tamar Christina at 2018-02-19T05:34:49+01:00 Haddock: support splitted include paths. (#689) - - - - - 9b6d6f50 by Alex Biehl at 2018-02-19T05:57:02+01:00 Teach the HTML backend how to render methods with multiple names - - - - - a74aa754 by Alexander Biehl at 2018-02-19T10:04:34+01:00 Hoogle/Latex: Remove use of partial function - - - - - 66d8bb0e by Alec Theriault at 2018-02-25T16:04:01+01:00 Fix file handle leak (#763) (#764) Brought back some mistakenly deleted code for handling encoding and eager reading of files from e0ada1743cb722d2f82498a95b201f3ffb303137. - - - - - bb92d03d by Alex Biehl at 2018-03-02T14:21:23+01:00 Enable running test suite with stock haddock and ghc using ``` $ cabal new-run -- html-test --haddock-path=$(which haddock) --ghc-path=$(which ghc) ``` - - - - - dddb3cb2 by Alex Biehl at 2018-03-02T15:43:21+01:00 Make testsuite work with haddock-1.19.0 release (#766) - - - - - f38636ed by Alec Theriault at 2018-03-02T15:48:36+01:00 Support unicode operators, proper modules Unicode operators are a pretty big thing in Haskell, so supporting linking them seems like it outweighs the cost of the extra machinery to force Attoparsec to look for unicode. Fixes haskell/haddock#458. - - - - - 09d89f7c by Alec Theriault at 2018-03-02T15:48:43+01:00 Remove bang pattern - - - - - d150a687 by Alex Biehl at 2018-03-02T15:48:48+01:00 fix test - - - - - d6fd71a5 by Alex Biehl at 2018-03-02T16:22:38+01:00 haddock-test: Be more explicit which packages to pass We now pass `-hide-all-packages` to haddock when invoking the testsuite. This ensures we don't accidentally pick up any dependencies up through ghc.env files. - - - - - 0932c78c by Alex Biehl at 2018-03-02T17:50:38+01:00 Revert "fix test" This reverts commit 1ac2f9569242f6cb074ba6e577285a4c33ae1197. - - - - - 52516029 by Alex Biehl at 2018-03-02T18:16:50+01:00 Fix Bug548 for real - - - - - 89df9eb5 by Alex Biehl at 2018-03-05T18:28:19+01:00 Hyperlinker: Links for TyOps, class methods and associated types - - - - - d019a4cb by Ryan Scott at 2018-03-06T13:43:56-05:00 Updates for haskell/haddock#13324 - - - - - 6d5a42ce by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump haddock-2.19.0.1, haddock-api-2.19.0.1, haddock-library-1.5.0.1 - - - - - c0e6f380 by Alex Biehl at 2018-03-10T18:25:57+01:00 Update changelogs for haddock-2.19.0.1 and haddock-library-1.5.0.1 - - - - - 500da489 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Update to QC 2.11 - - - - - ce8362e9 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Restore backward-compat with base-4.5 through base-4.8 - - - - - baae4435 by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump lower bound for haddock-library - - - - - 10b7a73e by Alex Biehl at 2018-03-10T18:25:57+01:00 Haddock: Straighten out base bound - - - - - a6096f7b by Alex Biehl at 2018-03-13T08:45:06+01:00 extractDecl: Extract constructor patterns from data family instances (#776) * extractDecl: Allow extraction of data family instance constructors * extractDecl: extract data family instance constructors - - - - - ba4a0744 by Simon Jakobi at 2018-03-14T08:26:42+01:00 Readme: Update GHC version (#778) - - - - - 8de157d4 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for definition lists - - - - - 425b46f9 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for links - - - - - d53945d8 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for inline links - - - - - f1dc7c99 by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Slightly unmangle output - - - - - 0879d31c by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Prevent stdout buffering - - - - - 1f9e5f1b by Simon Jakobi at 2018-03-14T20:39:29+01:00 haddock-library.cabal: Clean up GHC options - - - - - 066b891a by Simon Jakobi at 2018-03-14T20:39:29+01:00 Make a proper definition for the <link> parser - - - - - 573d6ba7 by Alec Theriault at 2018-03-21T09:16:57+01:00 Show where instances are defined (#748) * Indicate source module of instances Above instance, we now also display a link to the module where the instance was defined. This is sometimes helpful in figuring out what to import. * Source module for type/data families too * Remove parens * Accept tests - - - - - 99b5d28b by Alex Biehl at 2018-03-21T09:20:36+01:00 Prepare changelog for next release - - - - - 482d3a93 by Alex Biehl at 2018-03-23T15:57:36+01:00 Useful cost centres, timers and allocation counters (#785) * Add some useful cost-centres for profiling * Add withTiming for each haddock phase Invoking haddock with `--optghc=-ddump-timings` now shows the amount of time spent and the number of allocated bytes for each phase. - - - - - 773b41bb by Alec Theriault at 2018-03-27T08:35:59+02:00 @since includes package name (#749) * Metadoc stores a package name This means that '@since' annotations can be package aware. * Get the package name the right way This should extract the package name for `@since` annotations the right way. I had to move `modulePackageInfo` around to do this and, in the process, I took the liberty to update it. Since it appears that finding the package name is something that can fail, I added a warning for this case. * Silence warnings * Hide package for local 'since' annotations As discussed, this is still the usual case (and we should avoid being noisy for it). Although this commit is large, it is basically only about threading a 'Maybe Package' from 'Haddock.render' all the way to 'Haddock.Backends.Xhtml.DocMarkup.renderMeta'. * Bump binary interface version * Add a '--since-qual' option This controls when to qualify since annotations with the package they come from. The default is always, but I've left an 'external' variant where only those annotations coming from outside of the current package are qualified. * Make ParserSpec work * Make Fixtures work * Use package name even if package version is not available The @since stuff needs only the package name passed in, so it makes sense to not be forced to pass in a version too. - - - - - e42c57bc by Alex Biehl at 2018-03-27T08:42:50+02:00 haddock-2.19.1, haddock-api-2.19.1, haddock-library-1.6.0 - - - - - 8373a529 by Alex Biehl at 2018-03-28T10:17:11+02:00 Bump haddock and haddock-api to 2.20.0 - - - - - 5038eddd by Jack Henahan at 2018-04-03T13:28:12+02:00 Clear search string on hide for haskell/haddock#781 (#789) - - - - - 920ca1eb by Alex Biehl at 2018-04-03T16:35:50+02:00 Travis: Build with ghc-8.4.2 (#793) - - - - - a232f0eb by Alan Zimmerman at 2018-04-07T14:14:32+02:00 Match changes in GHC for D4199 Removing HasSourceText and SourceTextX classes. - - - - - ab85060b by Alan Zimmerman at 2018-04-09T21:20:24+02:00 Match GHC changes for TTG - - - - - 739302b6 by Alan Zimmerman at 2018-04-13T13:31:44+02:00 Match GHC for TTG implemented on HsBinds, D4581 - - - - - 2f56d3cb by Ryan Scott at 2018-04-19T11:42:58-04:00 Bump upper bound on base to < 4.13 See https://ghc.haskell.org/trac/ghc/ticket/15018. - - - - - a49df92a by Alex Biehl at 2018-04-20T07:31:44+02:00 Don't treat fixity signatures like declarations - - - - - d02c103b by Ryan Scott at 2018-04-24T11:20:11-04:00 Add regression test for haskell/haddock#413 Fixes haskell/haddock#413. - - - - - c7577f52 by Ryan Scott at 2018-04-24T13:51:06-07:00 Improve the Hoogle backend's treatment of type families (#808) Fixes parts 1 and 2 of haskell/haddock#806. - - - - - d88f85b1 by Alec Theriault at 2018-04-25T11:24:07-07:00 Replace 'attoparsec' with 'parsec' (#799) * Remove attoparsec with parsec and start fixing failed parses * Make tests pass * Fix encoding issues The Haddock parser no longer needs to worry about bytestrings. All the internal parsing work in haddock-library happens over 'Text'. * Remove attoparsec vendor * Fix stuff broken in 'attoparsec' -> 'parsec' * hyperlinks * codeblocks * examples Pretty much all issues are due to attoparsec's backtracking failure behaviour vs. parsec's non-backtracking failure behaviour. * Fix small TODOs * Missing quote + Haddocks * Better handle spaces before/after paragraphs * Address review comments - - - - - fc25e2fe by Alan Zimmerman at 2018-04-27T15:36:53+02:00 Match changes in GHC for TTG - - - - - 06175f91 by Herbert Valerio Riedel at 2018-05-01T18:11:09+02:00 Merge branch 'ghc-head' with 'ghc-8.4' - - - - - 879caaa8 by Alec Theriault at 2018-05-07T18:53:15-07:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 3e0120cb by Simon Jakobi at 2018-05-07T19:00:18-07:00 Add docs for some DocH constructors (#814) - - - - - 0a32c6db by Alec Theriault at 2018-05-08T02:15:45-07:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 8816e783 by Simon Jakobi at 2018-05-08T10:48:11-07:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - ad60366f by Ryan Scott at 2018-05-10T11:19:47-04:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - 03b7cc3b by Ryan Scott at 2018-05-10T11:24:38-04:00 Wibbles - - - - - b03dd563 by Chaitanya Koparkar at 2018-05-10T11:44:58-04:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 9f298a40 by Ben Gamari at 2018-05-13T17:36:04-04:00 Account for refactoring of LitString - - - - - ea3dabe7 by Ryan Scott at 2018-05-16T09:21:43-04:00 Merge pull request haskell/haddock#826 from haskell/T825 Remove Hoogle backend hack that butchers infix datatype names - - - - - 0d234f7c by Alec Theriault at 2018-05-23T11:29:05+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 15fc9712 by Simon Jakobi at 2018-05-31T04:17:47+02:00 Adjust to new HsDocString internals - - - - - 6f1e19a8 by Ben Gamari at 2018-06-02T16:18:58-04:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 0d0355d9 by Ryan Scott at 2018-06-04T21:26:59-04:00 DerivingVia changes - - - - - 0d93475a by Simon Jakobi at 2018-06-05T19:47:05+02:00 Bump a few dependency bounds (#845) - - - - - 5cbef804 by Alec Theriault at 2018-06-05T19:47:16+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 9094c56f by Alec Theriault at 2018-06-05T22:53:25+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 70188719 by Simon Jakobi at 2018-06-08T22:20:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - 495cd1fc by Chaitanya Koparkar at 2018-06-13T23:01:34+02:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 81088732 by Ben Gamari at 2018-06-13T23:01:34+02:00 Account for refactoring of LitString - - - - - 7baf6587 by Simon Jakobi at 2018-06-13T23:05:08+02:00 Adjust to new HsDocString internals - - - - - bb61464d by Ben Gamari at 2018-06-13T23:05:22+02:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 5d8cb87f by Ryan Scott at 2018-06-13T23:39:30+02:00 DerivingVia changes - - - - - 73d373a3 by Alec Theriault at 2018-06-13T23:39:30+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 4865e254 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Remove `ITtildehsh` token - - - - - b867db54 by Alec Theriault at 2018-06-13T23:39:30+02:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 9598e392 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Add docs for some DocH constructors (#814) - - - - - 8a59035b by Alec Theriault at 2018-06-13T23:39:30+02:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 29350fc8 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - 2590bbd9 by Ryan Scott at 2018-06-13T23:39:30+02:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - a9939fdc by Ryan Scott at 2018-06-13T23:39:30+02:00 Wibbles - - - - - a22f7df4 by Alec Theriault at 2018-06-13T23:39:30+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 8741015d by Simon Jakobi at 2018-06-13T23:39:30+02:00 Bump a few dependency bounds (#845) - - - - - 4791e1cc by Alec Theriault at 2018-06-13T23:39:30+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 311d3216 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - d0577817 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Complete FixitySig and FamilyDecl pattern matches - - - - - 055b3aa7 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Fix redundant import warnings - - - - - f9ce19b1 by Simon Jakobi at 2018-06-13T23:49:52+02:00 html-test: Accept output - - - - - 04604ea7 by Simon Jakobi at 2018-06-13T23:54:37+02:00 Bump bounds on Cabal - - - - - 0713b692 by Simon Jakobi at 2018-06-14T00:00:12+02:00 Merge branch 'ghc-head' into ghc-head-update-3 - - - - - c6a56bfd by Simon Jakobi at 2018-06-14T02:33:27+02:00 Bump ghc bound for haddock-api spec test-suite - - - - - 119d04b2 by Simon Jakobi at 2018-06-14T12:37:48+02:00 Travis: `--allow-newer` for all packages - - - - - 0e876e2c by Alex Biehl at 2018-06-14T15:28:52+02:00 Merge pull request haskell/haddock#857 from sjakobi/ghc-head-update-3 Update ghc-head - - - - - 5be46454 by Alec Theriault at 2018-06-14T21:42:45+02:00 Improved handling of interfaces in 'haddock-test' (#851) This should now work with an inplace GHC where (for instance) HTML directories may not be properly recorded in the package DB. - - - - - 96ab1387 by Vladislav Zavialov at 2018-06-14T17:06:21-04:00 Handle -XStarIsType - - - - - e518f8c4 by Ben Gamari at 2018-06-14T17:48:00-04:00 Revert unintentional reversion of fix of haskell/haddock#548 - - - - - 01b9f96d by Alan Zimmerman at 2018-06-19T11:52:22+02:00 Match changes in GHC for haskell/haddock#14259 - - - - - 7f8c8298 by Ben Gamari at 2018-06-19T18:14:27-04:00 Bump GHC version to 8.6 - - - - - 11c6b5d2 by Ryan Scott at 2018-06-19T23:17:31-04:00 Remove HsEqTy and XEqTy - - - - - b33347c2 by Herbert Valerio Riedel at 2018-06-20T23:14:52+02:00 Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. - - - - - f0d2460e by Herbert Valerio Riedel at 2018-06-20T23:28:46+02:00 Update Travis CI job - - - - - ef239223 by Herbert Valerio Riedel at 2018-06-20T23:32:41+02:00 Drop GHC HEAD from CI and update GHC to 8.4.3 It's a waste of resource to even try to build this branch w/ ghc-head; so let's not do that... - - - - - 41c4a9fa by Ben Gamari at 2018-06-20T18:26:20-04:00 Bump GHC version to 8.7 - - - - - 8be593dc by Herbert Valerio Riedel at 2018-06-21T22:32:15+02:00 Update CI job to use GHC 8.7.* - - - - - b91d334a by Simon Jakobi at 2018-06-30T13:41:38+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section - - - - - f707d848 by Alec Theriault at 2018-07-05T10:43:35-04:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. - - - - - a6d2b8dc by Alec Theriault at 2018-07-06T10:06:32-04:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case - - - - - 13819f71 by Alan Zimmerman at 2018-07-15T19:33:51+02:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 - - - - - c346aa78 by Simon Jakobi at 2018-07-19T12:29:32+02:00 haddock-library: Bump bounds for containers - - - - - 722e733c by Simon Jakobi at 2018-07-19T13:36:45+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] - - - - - f0bd83fd by Alec Theriault at 2018-07-19T14:39:57+02:00 Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. - - - - - 394053a8 by Simon Jakobi at 2018-07-19T14:58:07+02:00 haddock-library: Bump bounds for containers - - - - - 1bda11a2 by Alec Theriault at 2018-07-20T09:04:03+02:00 Add HEAD.hackage overlay (#887) * Add HEAD.hackage overlay * Add HCPKG variable - - - - - c7b4ab45 by Alec Theriault at 2018-07-20T12:01:16+02:00 Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test - - - - - c05d32ad by Alec Theriault at 2018-07-20T12:01:49+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output - - - - - 24b39ee4 by Alec Theriault at 2018-07-20T12:02:16+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. - - - - - cb9d2099 by Simon Jakobi at 2018-07-20T13:39:29+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) - - - - - 133f24f5 by Alec Theriault at 2018-07-20T13:39:29+02:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) - - - - - 11024149 by Alec Theriault at 2018-07-20T13:39:29+02:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) - - - - - de0c139e by Simon Jakobi at 2018-07-20T13:39:29+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) - - - - - 6435e952 by Alec Theriault at 2018-07-20T13:39:29+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) - - - - - 1461af39 by Alec Theriault at 2018-07-20T13:39:29+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) - - - - - 69d3bde1 by Alec Theriault at 2018-07-20T13:49:47+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) - - - - - 6a5c73c7 by Alec Theriault at 2018-07-20T13:50:00+02:00 Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests - - - - - 92ca94c6 by Alec Theriault at 2018-07-20T13:55:36+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) - - - - - 981bc7fa by Simon Jakobi at 2018-07-20T15:06:06+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers - - - - - 27e7c0c5 by Simon Jakobi at 2018-07-20T15:09:05+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 49e1a415 by Simon Jakobi at 2018-07-20T16:02:02+02:00 Update the ghc-8.6 branch (#889) * Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. * README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) * Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) * Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) * tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) * Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. * Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test * Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) * Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) * Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) * Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests * Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 5ca14bed by Simon Jakobi at 2018-07-20T16:05:47+02:00 Revert "Revert "Bump GHC version to 8.6"" That commit didn't belong onto the ghc-8.6 branch. This reverts commit acbaef3b9daf1d2dea10017964bf886e77a8e967. - - - - - 2dd600dd by Simon Jakobi at 2018-07-20T16:18:21+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. - - - - - fceb2422 by Simon Jakobi at 2018-07-20T16:18:21+02:00 outOfScope: Recommend qualifying the identifier - - - - - acea5d23 by Simon Jakobi at 2018-07-20T16:19:35+02:00 outOfScope: Recommend qualifying the identifier (cherry picked from commit 73707ed58d879cc04cb644c5dab88c39ca1465b7) - - - - - 1a83ca55 by Simon Jakobi at 2018-07-20T16:19:35+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. (cherry picked from commit d504a2864a4e1982e142cf88c023e7caeea3b76f) - - - - - 48374451 by Masahiro Sakai at 2018-07-20T17:06:42+02:00 Add # as a special character (#884) '#' has special meaning used for anchors and can be escaped using backslash. Therefore it would be nice to be listed as special characters. - - - - - 5e1a5275 by Alec Theriault at 2018-07-20T23:37:24+02:00 Let `haddock-test` bypass interface version check (#890) This means `haddock-test` might * crash during deserialization * deserialize incorrectly Still - it means things _might_ work where they were previously sure not to. - - - - - 27286754 by Yuji Yamamoto at 2018-07-23T08:16:01+02:00 Avoid "invalid argument (invalid character)" on non-unicode Windows (#892) Steps to reproduce and the error message ==== ``` > stack haddock basement ... snip ... Warning: 'A' is out of scope. Warning: 'haddock: internal error: <stdout>: commitBuffer: invalid argument (invalid character) ``` Environment ==== OS: Windows 10 ver. 1709 haddock: [HEAD of ghc-8.4 when I reproduce the error](https://github.com/haskell/haddock/commit/532b209d127e4cecdbf7e9e3dcf4f653a5605b5a). (I had to use this version to avoid another probrem already fixed in HEAD) GHC: 8.4.3 stack: Version 1.7.1, Git revision 681c800873816c022739ca7ed14755e85a579565 (5807 commits) x86_64 hpack-0.28.2 Related pull request ==== https://github.com/haskell/haddock/pull/566 - - - - - 6729d361 by Alec Theriault at 2018-07-23T13:52:56-07:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). - - - - - 8cf4e6b5 by Ryan Scott at 2018-07-27T11:28:03-04:00 eqTyCon_RDR now lives in TysWiredIn After GHC commit http://git.haskell.org/ghc.git/commit/f265008fb6f70830e7e92ce563f6d83833cef071 - - - - - 1ad251a6 by Alan Zimmerman at 2018-07-30T13:28:09-04:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 (cherry picked from commit e3926b50ab8a7269fd6904b06e881745f08bc5d6) - - - - - 8aea2492 by Richard Eisenberg at 2018-08-02T10:54:17-04:00 Update against new HsImplicitBndrs - - - - - e42cada9 by Alec Theriault at 2018-08-04T17:51:30+02:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 0e852512 by Alex Biehl at 2018-08-06T13:04:02+02:00 Make --package-version optional for --hoogle generation (#899) * Make --package-version optional for --hoogle generation * Import mkVersion * It's makeVersion not mkVersion - - - - - d2abd684 by Noel Bourke at 2018-08-21T09:34:18+02:00 Remove unnecessary backslashes from docs (#908) On https://haskell-haddock.readthedocs.io/en/latest/markup.html#special-characters the backslash and backtick special characters showed up with an extra backslash before them – I think the escaping is not (or no longer) needed for those characters in rst. - - - - - 7a578a9e by Matthew Pickering at 2018-08-21T09:34:50+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - aa3d4db3 by Matthew Pickering at 2018-08-21T09:37:34+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - ede91744 by Alec Theriault at 2018-08-21T09:42:52+02:00 Better test output when Haddock crashes on a test (#902) In particular: we report the tests that crashed seperately from the tests that produced incorrect output. In order for tests to pass (and exit 0), they must not crash and must produce the right output. - - - - - 4a872b84 by Guillaume Bouchard at 2018-08-21T09:45:57+02:00 Fix a typo (#878) - - - - - 4dbf7595 by Ben Sklaroff at 2018-08-21T12:04:09-04:00 Add ITcomment_line_prag token to Hyperlinker Parser This token is necessary for parsing #line pragmas inside nested comments. Reviewers: bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D4935 - - - - - 9170b2a9 by Ben Gamari at 2018-08-21T17:55:15-04:00 Merge pull request haskell/haddock#893 from harpocrates/get-name-to-instances Accumulate explicitly which modules to load for 'attachInstances' - - - - - d57b57cc by Ben Gamari at 2018-08-21T17:59:13-04:00 Merge branch 'ghc-head' of github.com:haskell/haddock into ghc-head - - - - - 14601ca2 by Alec Theriault at 2018-08-21T19:09:37-04:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). (cherry picked from commit 5c7c596c51d69b92164e9ba920157b36ce2b2ec1) - - - - - 438c645e by Matthew Pickering at 2018-08-21T19:12:39-04:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 (cherry picked from commit e6aa8fb47b9477cc5ef5e46097524fe83e080f6d) - - - - - a80c5161 by Alec Theriault at 2018-08-21T22:06:40-07:00 Better rendering of unboxed sums/tuples * adds space after/before the '#' marks * properly reify 'HsSumTy' in 'synifyType' - - - - - 88456cc1 by Alec Theriault at 2018-08-21T22:06:40-07:00 Handle promoted tuples in 'synifyType' When we have a fully applied promoted tuple, we can expand it out properly. - - - - - fd1c1094 by Alec Theriault at 2018-08-21T22:19:34-07:00 Accept test cases - - - - - 6e80d9e0 by Alec Theriault at 2018-08-21T22:24:03-07:00 Merge pull request haskell/haddock#914 from harpocrates/feature/unboxed-stuff Better rendering of unboxed sums, unboxed tuples, promoted tuples. - - - - - 181a23f1 by Ben Gamari at 2018-08-23T15:53:48-04:00 Merge remote-tracking branch 'origin/ghc-8.6' into ghc-8.6 - - - - - 3a18c1d8 by Alec Theriault at 2018-08-27T14:15:25-07:00 Properly synify promoted list types We reconstruct promoted list literals whenever possible. That means that 'synifyType' produces '[Int, Bool, ()] instead of (Int ': (() ': (Bool ': ([] :: [Type])))) - - - - - b4794946 by Alec Theriault at 2018-09-03T07:19:55-07:00 Only look at visible types when synifying a 'HsListTy' The other types are still looked at when considering whether to make a kind signature or not. - - - - - a231fce2 by Alec Theriault at 2018-09-03T07:38:10-07:00 Merge pull request haskell/haddock#922 from harpocrates/promoted-lists Properly synify promoted list types - - - - - 0fdf044e by Ningning Xie at 2018-09-15T10:25:58-04:00 Update according to GHC Core changes - - - - - 7379b115 by Ningning Xie at 2018-09-15T15:40:18-04:00 update dataFullSig to work with Co Quantification This should have been in the previous patch, but wasn't. - - - - - cf84a046 by Alec Theriault at 2018-09-17T20:12:18-07:00 Fix/add to various docs * Add documentation for a bunch of previously undocumented options (fixes haskell/haddock#870) * Extend the documentation of `--hoogle` considerably (see haskell/haddock#807) * Describe how to add docs to `deriving` clauses (fixes haskell/haddock#912) * Fix inaccurate docs about hyperlinking infix identifiers (fixes haskell/haddock#780) - - - - - ae017935 by Alec Theriault at 2018-09-22T08:32:16-07:00 Update Travis - - - - - d95ae753 by Alec Theriault at 2018-09-22T09:34:10-07:00 Accept failing tests Also silence orphan warnings. - - - - - f3e67024 by Alec Theriault at 2018-09-22T09:41:23-07:00 Bump haddock-api-2.21.0, haddock-library-1.7.0 * Update CHANGELOGS * Update new versions in Cabal files * Purge references to ghc-8.4/master branches in README - - - - - 3f136d4a by Alec Theriault at 2018-09-22T10:53:31-07:00 Turn haddock-library into a minor release Fix some version bounds in haddock-library too. - - - - - b9def006 by Alec Theriault at 2018-09-22T13:07:35-07:00 keep cabal.project file - - - - - 4909aca7 by Alec Theriault at 2018-10-16T09:36:30-07:00 Build on 7.4 and 7.8 - - - - - 99d20a28 by Herbert Valerio Riedel at 2018-10-16T18:45:52+02:00 Minor tweak to package description - - - - - a8059618 by Herbert Valerio Riedel at 2018-10-16T18:47:24+02:00 Merge pull request haskell/haddock#945 haddock-api 2.21.0 and haddock-library 1.6.1 release - - - - - 2d9bdfc1 by Alec Theriault at 2018-10-16T10:54:21-07:00 Bump haddock-library to 1.7.0 The 1.6.1 release should've been a major bump, since types in the `Documentation.Haddock.Parser.Monad` module changed. This version makes that module internal (as it morally should be). - - - - - ed340cef by Alec Theriault at 2018-10-16T14:59:13-07:00 Merge branch 'ghc-8.4' into ghc-8.6 - - - - - 2821a8df by Alec Theriault at 2018-10-16T15:14:48-07:00 Merge branch 'ghc-8.6' into ghc-head - - - - - a722dc84 by Alec Theriault at 2018-10-16T16:28:55-07:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 63377496 by Alec Theriault at 2018-10-16T16:39:07-07:00 Update changelog - - - - - 099a0110 by Alec Theriault at 2018-10-16T16:49:28-07:00 Merge pull request haskell/haddock#942 from harpocrates/update-docs Fix & add to documentation - - - - - 0927416f by Alec Theriault at 2018-10-16T16:50:14-07:00 Set UTF-8 encoding before writing files (#934) This should fix haskell/haddock#929, as well as guard against future problems of this sort in other places. Basically replaces 'writeFile' (which selects the users default locale) with 'writeUtf8File' (which always uses utf8). - - - - - 83b7b017 by Alec Theriault at 2018-10-16T17:42:05-07:00 Output pattern synonyms in Hoogle backend (#947) * Output pattern synonyms in Hoogle backend We were previously weren't outputting _any_ pattern synonyms, bundled or not. Now, we output both. Fixes haskell/haddock#946. * Update changelog - - - - - 81e5033d by Alec Theriault at 2018-10-16T18:04:40-07:00 Release `haddock{,-api}-2.22.0` This version will accompany ghc-8.6.2 - - - - - 9661744e by Alex Biehl at 2018-10-18T08:14:32-07:00 Add NewOcean theme And make it the default theme. - - - - - 7ae6d722 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Improve appearance and readability These changes include: - use latest Haskell's logo colors - decrease #content width to improve readability - use nicer font - improve sizes and distances - - - - - 37f8703d by NunoAlexandre at 2018-10-18T08:14:32-07:00 Include custom font in the html head - - - - - 1d5e1d79 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Update html test reference files - - - - - 53b7651f by NunoAlexandre at 2018-10-18T08:14:32-07:00 Make it responsive - It makes small screens taking more space than larger ones - fixes a few issues present in small screens currently - make it look good across different screen sizes. - - - - - 6aa1aeb1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make the style consistent with hackage Several things are addressed here: - better responsive behaviour on the header - better space usage - consistent colors overall - other nit PR comments - - - - - 3a250c5c by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Place the package name before the menu links This supports the expected responsive menu design, where the package name appears above the menu links. - - - - - cae699b3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update html-test reference files The package name element in the package-header is now a div instead of a paragraph, and it is now above the menu ul.links instead of below. - - - - - 2ec7fd2d by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve synopsis style and code - Use CSS3 instead of loading pictures to show "+" and "-" symbols - Drop redundant code - - - - - 0c874c01 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Decrease space between code blocks There was too much space between code blocks as pointed out by reviewers. - - - - - 85568ce2 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Add an initial-scale property to all haddock pages This solves an issue reported about the content looking incredibly small on mobile devices. - - - - - c1538926 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Address several PR comments - Darken text color like done for hackage - Move synopsis to left side - Make table of contents stick to the left on wide screens - Wrap links to avoid page overflow - Improve expand/collapse buttons - Fix issue with content size on mobile devices - Fix issue with font-size on landscape mode - Increase width of the content - Change colors of table of contents and synopsis - Etc - - - - - e6639e5f by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make synopsis scrollable on wide screens When the synopsis is longer than the screen, you can’t see its end and you can't scroll down either, making the content unreachable. - - - - - 1f0591ff by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve information density - Reduce font size - Improve space between and within code blocks - Improve alignments - Improve spacing within sub-blocks - - - - - bf083097 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Minor adjustments Bring in some adjustments made to hackage: - link colors - page header show everything when package title is too long - - - - - 10375fc7 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix responsive triggers overlap issue The min and max width triggers have the same values, which caused the style resolution to take an intersection of both style declarations when the screen resolution had the size of the limts (say 1280px), causing an odd behaviour and look. - - - - - 95ff2f95 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix issue with menu alignment on firefox Reported and described here: https://github.com/haskell/haddock/pull/721#issuecomment-374668869 - - - - - dc86587e by Alex Biehl at 2018-10-18T08:14:32-07:00 Changelog entry for NewOcean - - - - - 27195e47 by Herbert Valerio Riedel at 2018-10-18T08:14:32-07:00 html-test --accept - - - - - 83f4f9c0 by Alex Biehl at 2018-10-18T08:14:32-07:00 Avoid name shadowing - - - - - 231487f1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font to PT Sans Also migrate some general text related changes from hackage. - - - - - 313db81a by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Use 'flex' to fix header alignment - - - - - 5087367b by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Misc of tweaks - Update link colors to hackage scheme - Tune spacing between content elements - Update footer style - Fix and improve code blocks identation - - - - - b08020df by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font in Xhtml.hs to PT Sans - - - - - 78ce06e3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve code blocks styling - Fix and improve spacing - Improve colors and borders - - - - - 81262d20 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make package-header caption backward-compatible The current html generator of this branch wraps the package-header caption as a div, which does not work (without style adjustments) with the old themes. Changing it from div to span does the trick, without needing to adjust the old stylesheets. - - - - - dc4475cb by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update test-suite reference html pages - - - - - 393d35d8 by Alec Theriault at 2018-10-18T08:25:36-07:00 Accept tests - - - - - a94484ba by Alec Theriault at 2018-10-21T10:29:29-07:00 Fix CHANGELOG - - - - - 8797eca3 by Alec Theriault at 2018-10-21T10:36:19-07:00 Update 'data-files' to include NewOcean stuff - - - - - 1ae51e4a by Simon Jakobi at 2018-10-23T11:29:14+02:00 Fix typo in a warning - - - - - 009ad8e8 by Alec Theriault at 2018-10-24T12:47:47-07:00 Update JS dependencies This was done via `npm audit fix`. I think this fixes haskell/haddock#903 along with some more serious vulnerabilities that nobody seems to have noticed. - - - - - 051994db by Alec Theriault at 2018-10-24T17:31:09-07:00 Resurrect the style-switcher This fixes haskell/haddock#810. Looks like things were broken during the quickjump refactor of the JS. For the (git) record: I do not think the style switcher is a good idea. I'm fixing it for the same reason @mzero added it; as an answer to "rumblings from some that they didn't want their pixels changed on bit" - - - - - 2a1d620f by Alec Theriault at 2018-10-24T17:38:07-07:00 Fix copy-pasta error in data-files - - - - - ed5bfb7f by Alec Theriault at 2018-10-24T20:42:14-07:00 Fix the synopsis button Here's these changes are supposed to do: * put the synopsis back on the right side * properly have it on the edge of the screen on wide screens * adjust the background of the synopsis to match the button (otherwise the grey blends in with what is underneath) * get rid of the dotted purple line * the synopsis contents are now scrollable even when in wide screens (this has been a long-standing bug) - - - - - 883fd74b by Alec Theriault at 2018-10-25T20:16:46-07:00 Avoid more conflicts in generated ids (#954) This fixes haskell/haddock#953 by passing more names into the generated ids. - - - - - ea54e331 by Alec Theriault at 2018-10-25T21:07:12-07:00 Don't hide bullets in method docs I think thst CSS was meant only to deal with fields and the effect on bullets was accidental. Fixes haskell/haddock#926. - - - - - 9a14ef4a by Alec Theriault at 2018-10-25T22:02:07-07:00 Indent more things + slightly smaller font - - - - - b9f17e29 by Alec Theriault at 2018-10-25T22:10:01-07:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 096a3cfa by Alec Theriault at 2018-10-25T22:24:38-07:00 Accept HTML output - - - - - 2669517d by Alec Theriault at 2018-10-26T09:02:35-07:00 User manual + stuff for building GHC docs - - - - - 46b27687 by Alec Theriault at 2018-10-26T09:10:59-07:00 Make 'Contents' in NewOcean scrollable This only happens if the contents block on the left is so big that it doesn't fit (vertically) on the page. If that happens, we want it to be scrollable. - - - - - 3443dd94 by Alec Theriault at 2018-10-26T09:36:46-07:00 Revert "Make 'Contents' in NewOcean scrollable" This reverts commit f909ffd8353d6463fd5dd184998a32aa98d5c922. I missed the fact this also forces the 'Contents' to always go down to the bottom of the page. - - - - - ed081424 by Alec Theriault at 2018-10-26T14:22:23-07:00 Avoid some partiality AFAICT this wasn't causing any crashes, but that's mostly because we happen not to be forcing `pkgStr` when it would diverge. We come dangerously close to doing that in `ppHtmlIndex`. Fixes haskell/haddock#569. - - - - - 6a5bec41 by Alec Theriault at 2018-10-27T10:05:04-07:00 Fix documentation in `haddock-api` (#957) * Fix misplaced Haddocks in Haddock itself Haddock should be able to generate documentation for 'haddock-api' again. * Make CI check that documentation can be built. * Add back a doc that is OK - - - - - 5100450a by Matthew Yacavone at 2018-10-27T14:51:38-04:00 More explicit foralls (GHC Proposal 0007) - - - - - 8771a6b0 by Alec Theriault at 2018-11-05T13:58:11-08:00 Only run MathJax on entities with "mathjax" class (#960) Correspondingly, we wrap all inline/diplay math in <span class="mathjax"> ... the math .... </span> This fixes haskell/haddock#959. - - - - - bd7ff5c5 by Alec Theriault at 2018-11-05T15:54:22-08:00 Deduplicate some work in 'AttachInstances' Perf only change: * avoid needlessly union-ing maps * avoid synify-ing instances twice Took this opportunity to add some docs too - - - - - cf99fd8f by Alec Theriault at 2018-11-05T15:54:22-08:00 Specialize some SYB functions Perf only change: * Add a 'SPECIALIZE' pragma to help GHC optimize a 'Data a =>' constraint * Manually specialize the needlessly general type of 'specializeTyVarBndrs' - - - - - 4f91c473 by Alec Theriault at 2018-11-05T15:54:22-08:00 Improve perf of renaming Perf only change: * don't look up type variable names (they're never in the environment) * use a difference list for accumulating missing names * more efficient 'Functor'/'Applicative' instances for 'RnM' - - - - - 4bbab0d4 by Alec Theriault at 2018-11-05T15:54:22-08:00 Faster 'Text' driven parser combinators Perf only change: * use 'getParserState'/'setParserState' to make 'Text'-optimized parser combinators * minimize uses of 'Data.Text.{pack,unpack,cons,snoc}' - - - - - fa430c02 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support hyperlink labels with inline markup The parser for pictures hasn't been properly adjusted yet. - - - - - c1431035 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support (and flatten) inline markup in image links Inline markup is supported in image links but, as per the [commonmark recommendation][0], it is stripped back to a plain text representation. [0]: https://spec.commonmark.org/0.28/#example-547 - - - - - d4ee1ba5 by Alec Theriault at 2018-11-06T12:03:24-08:00 Accept test case - - - - - 8088aeb1 by Alec Theriault at 2018-11-06T12:03:24-08:00 Fix/add to haddock-library test suite - - - - - e78f644d by Alec Theriault at 2018-11-06T13:26:31-08:00 Bump version bounds - - - - - 644335eb by Alec Theriault at 2018-11-06T13:53:30-08:00 Merge pull request haskell/haddock#875 from harpocrates/feature/markup-in-hyperlinks Inline markup in markdown-style links and images - - - - - e173ed0d by Alec Theriault at 2018-11-07T12:37:18-08:00 Fix issues around plus/minus * swap the minimize unicode to something more intuitive * use new unicode expander/collapser for instance lists * address some alignment issues in the "index" page - - - - - b2d92df7 by Alec Theriault at 2018-11-07T13:41:57-08:00 Allow "Contents" summary to scroll in a fixed div In the unfortunate event that the "Contents" summary doesn't fit vertically (like in the "Prelude"), it will be scrollable. - - - - - ca704c23 by Alec Theriault at 2018-11-07T13:45:15-08:00 Accept HTML output changes - - - - - 82c0ec6d by Alec Theriault at 2018-11-07T18:12:54-08:00 overflow-y 'scroll' -> 'auto' - - - - - 571d7657 by Alec Theriault at 2018-11-08T19:44:12-08:00 Clicking on "Contents" navigates to top of page - - - - - 8065a012 by Alec Theriault at 2018-11-08T19:44:17-08:00 Space out functions more Also, functions and data decls now have the same space before and after them. - - - - - cc650ede by Alec Theriault at 2018-11-09T08:13:35-08:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 65f8c17f by Alec Theriault at 2018-11-10T14:04:06-08:00 Update changelog - - - - - 20473847 by Alec Theriault at 2018-11-10T14:21:40-08:00 Replace oplus/ominus expander/collapser icons with triangles - - - - - 16592957 by Alec Theriault at 2018-11-10T14:35:10-08:00 Merge pull request haskell/haddock#949 from haskell/wip/new-ocean Introduce NewOcean theme. - - - - - 357cefe1 by Alec Theriault at 2018-11-10T16:02:13-08:00 Merge branch 'ghc-8.6' into ghc-head - - - - - de612267 by Alec Theriault at 2018-11-11T20:01:21-08:00 Rename 'NewOcean' theme to 'Linuwial' - - - - - 954b5baa by Alec Theriault at 2018-11-12T08:33:18-08:00 Add blockquote styling Matches b71da1feabf33efbbc517ac376bb690b5a604c2f from hackage-server. Fixes haskell/haddock#967. - - - - - d32c0b0b by Fangyi Zhou at 2018-11-12T10:24:13-08:00 Fix some broken links (#15733) Summary: For links in subpackages as well. https://phabricator.haskell.org/D5257 Test Plan: Manually verify links Reviewers: mpickering, bgamari, osa1 Reviewed By: osa1 GHC Trac Issues: haskell/haddock#15733 Differential Revision: https://phabricator.haskell.org/D5262 - - - - - 41098b1f by Alp Mestanogullari at 2018-11-15T22:40:09+01:00 Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change It got introduced in ghc/ghc at ae2c9b40f5b6bf272251d1f4107c60003f541b62. - - - - - c5c1c7e0 by Alec Theriault at 2018-11-15T13:48:13-08:00 Merge pull request haskell/haddock#970 from alpmestan/alp/fix-promotionflag Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change - - - - - 6473d3a4 by Shayan-Najd at 2018-11-23T01:38:49+01:00 [TTG: Handling Source Locations] Foundation and Pat Trac Issues haskell/haddock#15495 This patch removes the ping-pong style from HsPat (only, for now), using the plan laid out at https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/HandlingSourceLocations (solution A). - the class `HasSrcSpan`, and its functions (e.g., `cL` and `dL`), are introduced - some instances of `HasSrcSpan` are introduced - some constructors `L` are replaced with `cL` - some patterns `L` are replaced with `dL->L` view pattern - some type annotation are necessarily updated (e.g., `Pat p` --> `Pat (GhcPass p)`) - - - - - 7a088dfe by Alec Theriault at 2018-11-26T11:11:28-08:00 More uniform handling of `forall`'s in HTML/LaTeX * don't forget to print explicit `forall`'s when there are arg docs * when printing an explicit `forall`, print all tyvars Fixes haskell/haddock#973 - - - - - d735e570 by Alec Theriault at 2018-12-12T08:42:09-08:00 Fix warnings, accept output * remove redundant imports (only brought to light due to recent work for improving redundant import detection) * fix a bug that was casuing exports to appear in reverse order * fix something in haddock-library that prevented compilation on old GHC's - - - - - a3852f8a by Zejun Wu at 2018-12-14T09:37:47-05:00 Output better debug infromation on internal error in extractDecl This will make investigation of haskell/haddock#979 easier - - - - - 2eccb5b9 by Alec Theriault at 2018-12-17T09:25:10-05:00 Refactor names + unused functions (#982) This commit should not introduce any change in functionality! * consistently use `getOccString` to convert `Name`s to strings * compare names directly when possible (instead of comparing strings) * get rid of unused utility functions - - - - - e82e4df8 by Alec Theriault at 2018-12-20T16:16:30-05:00 Load plugins when compiling each module (#983) * WIP: Load (typechecker) plugins from language pragmas * Revert "Load plugins when starting a GHC session (#905)" This reverts commit 72d82e52f2a6225686d9668790ac33c1d1743193. * Simplify plugin initialization code - - - - - 96e86f38 by Alec Theriault at 2018-12-23T10:23:20-05:00 Properly synify and render promoted type variables (#985) * Synify and render properly promoted type variables Fixes haskell/haddock#923. * Accept output - - - - - 23343345 by Alec Theriault at 2018-12-27T16:39:38-05:00 Remove `haddock-test`'s dep. on `syb` (#987) The functionality is easily inlined into one short function: `gmapEverywhere`. This doesn't warrant pulling in another package. - - - - - d0734f21 by Alec Theriault at 2018-12-27T16:39:52-05:00 Address deprecation warnings in `haddock-test` (#988) Fixes haskell/haddock#885. - - - - - 4d9f144e by mynguyen at 2018-12-30T23:42:26-05:00 Visible kind application haddock update - - - - - ffe0e9ed by Alec Theriault at 2019-01-07T13:55:22-08:00 Print kinded tyvars in constructors for Hoogle (#993) Fixes haskell/haddock#992 - - - - - 2e18b55d by Alec Theriault at 2019-01-10T16:42:45-08:00 Accept new output `GHC.Maybe` -> `Data.Maybe` (#996) Since 53874834b779ad0dfbcde6650069c37926da1b79 in GHC, "GHC.Maybe" is marked as `not-home`. That changes around some test output. - - - - - 055da666 by Gabor Greif at 2019-01-22T14:41:51+01:00 Lone typofix - - - - - 01bb71c9 by Alec Theriault at 2019-01-23T11:46:46-08:00 Keep forall on H98 existential data constructors (#1003) The information about whether or not there is a source-level `forall` is already available on a `ConDecl` (as `con_forall`), so we should use it instead of always assuming `False`! Fixes haskell/haddock#1002. - - - - - f9b9bc0e by Ryan Scott at 2019-01-27T09:28:12-08:00 Fix haskell/haddock#1004 with a pinch of dropForAlls - - - - - 5cfcdd0a by Alec Theriault at 2019-01-28T16:49:57-08:00 Loosen 'QuickCheck' and 'hspec' bounds It looks like the new versions don't cause any breakage and loosening the bounds helps deps fit in one stack resolver. - - - - - 3545d3dd by Alec Theriault at 2019-01-31T01:37:25-08:00 Use `.hie` files for the Hyperlinker backend (#977) # Summary This is a large architectural change to the Hyperlinker. * extract link (and now also type) information from `.hie` instead of doing ad-hoc SYB traversals of the `RenamedSource`. Also adds a superb type-on-hover feature (#715). * re-engineer the lexer to avoid needless string conversions. By going directly through GHC's `P` monad and taking bytestring slices, we avoid a ton of allocation and have better handling of position pragmas and CPP. In terms of performance, the Haddock side of things has gotten _much_ more efficient. Unfortunately, much of this is cancelled out by the increased GHC workload for generating `.hie` files. For the full set of boot libs (including `ghc`-the-library) * the sum of total time went down by 9-10% overall * the sum of total allocations went down by 6-7% # Motivation Haddock is moving towards working entirely over `.hi` and `.hie` files. This change means we no longer need the `RenamedSource` from `TypecheckedModule` (something which is _not_ in `.hi` files). # Details Along the way a bunch of things were fixed: * Cross package (and other) links are now more reliable (#496) * The lexer tries to recover from errors on every line (instead of at CPP boundaries) * `LINE`/`COLUMN` pragmas are taken into account * filter out zero length tokens before rendering * avoid recomputing the `ModuleName`-based `SrcMap` * remove the last use of `Documentation.Haddock.Utf8` (see haskell/haddock#998) * restructure temporary folder logic for `.hi`/`.hie` model - - - - - 2ded3359 by Herbert Valerio Riedel at 2019-02-02T12:06:12+01:00 Update/modernise haddock-library.cabal file - - - - - 62b93451 by Herbert Valerio Riedel at 2019-02-02T12:19:31+01:00 Tentatively declare support for unreleased base-4.13/ghc-8.8 - - - - - 6041e767 by Herbert Valerio Riedel at 2019-02-02T16:04:32+01:00 Normalise LICENSE text w/ cabal's BSD2 template Also, correct the `.cabal` files to advertise `BSD2` instead of the incorrect `BSD3` license. - - - - - 0b459d7f by Alec Theriault at 2019-02-02T18:06:12-08:00 CI: fetch GHC from validate artifact Should help make CI be less broken - - - - - 6b5c07cf by Alec Theriault at 2019-02-02T18:06:12-08:00 Fix some Hyperlinker test suite fallout * Amend `ParserSpec` to match new Hyperlinker API - pass in compiler info - strip out null tokens * Make `hypsrc-test` pass reliably - strip out `local-*` ids - strip out `line-*` ids from the `ClangCppBug` test - re-accept output - - - - - ded34791 by Nathan Collins at 2019-02-02T18:31:23-08:00 Update README instructions for Stack No need to `stack install` Haddock to test it. Indeed, `stack install` changes the `haddock` on user's `PATH` if `~/.local/bin` is on user's `PATH` which may not be desirable when hacking on Haddock. - - - - - 723298c9 by Alec Theriault at 2019-02-03T09:11:05-08:00 Remove `Documentation.Haddock.Utf8` The circumstances under which this module appeared are completely gone. The Hyperlinker backend no longer needs this module (it uses the more efficient `Encoding` module from `ghc`). Why no deprecation? Because this module really shouldn't exist! - It isn't used in `haddock-library`/`haddock-api` anymore - It was copy pasted directly from `utf8-string` - Folks seeking a boot-lib only solution can use `ghc`'s `Encoding` - - - - - 51050006 by Alec Theriault at 2019-02-03T22:58:58-08:00 Miscellaneous improvements to `Convert` (#1020) Now that Haddock is moving towards working entirely over `.hi` and `.hie` files, all declarations and types are going to be synthesized via the `Convert` module. In preparation for this change, here are a bunch of fixes to this module: * Add kind annotations to type variables in `forall`'s whose kind is not `Type`, unless the kind can be inferred from some later use of the variable. See `implicitForAll` and `noKindTyVars` in particular if you wish to dive into this. * Properly detect `HsQualTy` in `synifyType`. This is done by following suit with what GHC's `toIfaceTypeX` does and checking the first argument of `FunTy{} :: Type` to see if it classified as a given/wanted in the typechecker (see `isPredTy`). * Beef up the logic around figuring out when an explicit `forall` is needed. This includes: observing if any of the type variables will need kind signatures, if the inferred type variable order _without_ a forall will still match the one GHC claims, and some other small things. * Add some (not yet used) functionality for default levity polymorphic type signatures. This functionality similar to `fprint-explicit-runtime-reps`. Couple other smaller fixes only worth mentioning: * Show the family result signature only when it isn't `Type` * Fix rendering of implicit parameters in the LaTeX and Hoogle backends * Better handling of the return kind of polykinded H98 data declarations * Class decls produced by `tyThingToLHsDecl` now contain associated type defaults and default method signatures when appropriate * Filter out more `forall`'s in pattern synonyms - - - - - 841980c4 by Oleg Grenrus at 2019-02-04T08:44:25-08:00 Make a fixture of weird parsing of lists (#997) The second example is interesting. If there's a list directly after the header, and that list has deeper structure, the parser is confused: It finds two lists: - One with the first nested element, - everything after it I'm not trying to fix this, as I'm not even sure this is a bug, and not a feature. - - - - - 7315c0c8 by Ryan Scott at 2019-02-04T12:17:56-08:00 Fix haskell/haddock#1015 with dataConUserTyVars (#1022) The central trick in this patch is to use `dataConUserTyVars` instead of `univ_tvs ++ ex_tvs`, which displays the foralls in a GADT constructor in a way that's more faithful to how the user originally wrote it. Fixes haskell/haddock#1015. - - - - - ee0b49a3 by Ryan Scott at 2019-02-04T15:25:17-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. - - - - - 1c850dc8 by Alan Zimmerman at 2019-02-05T21:54:18+02:00 Matching changes in GHC for haskell/haddock#16236 - - - - - ab03c38e by Simon Marlow at 2019-02-06T08:07:33+00:00 Merge pull request haskell/haddock#1014 from hvr/pr/bsd2-normalise Normalise LICENSE text w/ cabal's BSD2 template - - - - - 5a92ccae by Alec Theriault at 2019-02-10T06:21:55-05:00 Merge remote-tracking branch 'gitlab/wip/T16236-2' into ghc-head - - - - - c0485a1d by Alec Theriault at 2019-02-10T03:32:52-08:00 Removes `haddock-test`s dependency on `xml`/`xhtml` (#1027) This means that `html-test`, `latex-test`, `hoogle-test`, and `hypsrc-test` now only depend on GHC boot libs. So we should now be able to build and run these as part of GHC's testsuite. \o/ The reference output has changed very slightly, in three ways: * we don't convert quotes back into `&quot;` as the `xml` lib did * we don't add extra `&nbsp;` as the `xml` lib did * we now remove the entire footer `div` (instead of just emptying it) - - - - - 65a448e3 by Alec Theriault at 2019-02-11T12:27:41-05:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - 360ca937 by Alec Theriault at 2019-02-13T11:36:11-05:00 Clean up logic for guessing `-B` and `--lib` (#1026) Haddock built with the `in-ghc-tree` flag tries harder to find the GHC lib folder and its own resources. This should make it possible to use `in-ghc-tree`-built Haddock without having to specify the `-B` and `--lib` options (just how you can use in-tree GHC without always specifying the `-B` option). The logic to do this relies on `getExecutablePath`, so we only get this auto-detection on platforms where this function works. - - - - - d583e364 by Alec Theriault at 2019-02-16T10:41:22-05:00 Fix tests broken by GHC Changes in 19626218566ea709b5f6f287d3c296b0c4021de2 affected some of the hyperlinker output. Accepted the new output (hovering over a `..` now shows you what that wildcard binds). Also fixed some stray deprecation warnings. - - - - - da0c42cc by Vladislav Zavialov at 2019-02-17T11:39:19+03:00 Parser changes to match !380 - - - - - ab96bed7 by Ryan Scott at 2019-02-18T04:44:08-05:00 Bump ghc version to 8.9 - - - - - 44b7c714 by Alec Theriault at 2019-02-22T05:49:43-08:00 Match GHC changes for T16185 `FunTy` now has an `AnonArgFlag` that indicates whether the arrow is a `t1 => t2` or `t1 -> t2`. This commit shouldn't change any functionality in Haddock. - - - - - 2ee653b1 by Alec Theriault at 2019-02-24T18:53:33-08:00 Update .travis.yml Points to the new GHC CI artifact. - - - - - 90939d71 by Alec Theriault at 2019-02-25T00:42:41-08:00 Support value/type namespaces on identifier links Identifier links can be prefixed with a 'v' or 't' to indicate the value or type namespace of the desired identifier. For example: -- | Some link to a value: v'Data.Functor.Identity' -- -- Some link to a type: t'Data.Functor.Identity' The default is still the type (with a warning about the ambiguity) - - - - - d6ed496c by Alec Theriault at 2019-02-25T00:42:46-08:00 Better identifier parsing * '(<|>)' and '`elem`' now get parsed and rendered properly as links * 'DbModule'/'DbUnitId' now properly get split apart into two links * tuple names now get parsed properly * some more small niceties... The identifier parsing code is more precise and more efficient (although to be fair: it is also longer and in its own module). On the rendering side, we need to pipe through information about backticks/parens/neither all the way through from renaming to the backends. In terms of impact: a total of 35 modules in the entirety of the bootlib + ghc lib docs change. The only "regression" is things like '\0'. These should be changed to @\\0@ (the path by which this previously worked seems accidental). - - - - - 3c3b404c by Alec Theriault at 2019-02-25T22:12:11-08:00 Fix standalone deriving docs Docs on standalone deriving decls for classes with associated types should be associated with the class instance, not the associated type instance. Fixes haskell/haddock#1033 - - - - - d51ef69e by Alec Theriault at 2019-02-26T19:14:59-08:00 Fix bogus identifier defaulting This avoids a situation in which an identifier would get defaulted to a completely different identifier. Prior to this commit, the 'Bug1035' test case would hyperlink 'Foo' into 'Bar'! Fixes haskell/haddock#1035. - - - - - 88cbbdc7 by Ryan Scott at 2019-02-27T10:14:03-05:00 Visible dependent quantification (#16326) changes - - - - - 0dcf6cee by Xia Li-yao at 2019-02-27T21:53:27-05:00 Menu item controlling which instances are expanded/collapsed (#1007) Adds a menu item (like "Quick Jump") for options related to displaying instances. This provides functionality for: * expanding/collapsing all instances on the currently opened page * controlling whether instances are expanded/collapsed by default * controlling whether the state of instances should be "remembered" This new functionality is implemented in Typescript in `details-helper`. The built-in-themes style switcher also got a revamp so that all three of QuickJump, the style switcher, and instance preferences now have the same style and implementation structure. See also: https://mail.haskell.org/pipermail/haskell-cafe/2019-January/130495.html Fixes haskell/haddock#698. Co-authored-by: Lysxia <lysxia at gmail.com> Co-authored-by: Nathan Collins <conathan at galois.com> - - - - - 3828c0fb by Alec Theriault at 2019-02-28T12:42:49-05:00 `--show-interface` should output to stdout. (#1040) Fixes haskell/haddock#864. - - - - - a50f4cda by gbaz at 2019-03-01T07:43:16-08:00 Increase contrast of Linuwal theme (#1037) This is to address the concern that, on less nice and older screens, some of the shades of grey blend in too easily with the white background. * darken the font slightly * darken slightly the grey behind type signatures and such * add a border and round the corners on code blocks * knock the font down by one point - - - - - ab4d41de by Alec Theriault at 2019-03-03T09:23:26-08:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 12f509eb by Ben Gamari at 2019-03-04T22:13:20-05:00 Remove reference to Opt_SplitObjs flag Split-objects has been removed. - - - - - 5b3e4c9a by Ryan Scott at 2019-03-06T19:16:24-05:00 Update html-test output to reflect haskell/haddock#16391 changes - - - - - fc228af1 by Alec Theriault at 2019-03-09T08:29:23-08:00 Match changes for "Stop inferring over-polymorphic kinds" The `hsq_ext` field of `HsQTvs` is now just the implicit variables (instead of also including information about which of these variables are dependent). This commit shouldn't change any functionality in Haddock. - - - - - 6ac109eb by Alec Theriault at 2019-03-09T11:22:55-08:00 Add .hi, .dyn_hi, etc files to .gitignore Fixes haskell/haddock#1030. - - - - - b55f0c05 by Alec Theriault at 2019-03-09T11:22:55-08:00 Better support for default methods in classes * default methods now get rendered differently * default associated types get rendered * fix a forgotten `s/TypeSig/ClassOpSig/` refactor in LaTeX backend * LaTeX backend now renders default method signatures NB: there is still no way to document default class members and the NB: LaTeX backend still crashes on associated types - - - - - 10aea0cf by Alec Theriault at 2019-03-09T11:22:55-08:00 Avoid multi-line `emph` in LaTeX backend `markupWarning` often processes inputs which span across paragraphs. Unfortunately, LaTeX's `emph` is not made to handle this (and will crash). Fixes haskell/haddock#936. - - - - - d22dc2c9 by Alec Theriault at 2019-03-09T11:22:55-08:00 Many LaTeX backend fixes After this commit, we can run with `--latex` on all boot libraries without crashing (although the generated LaTeX still fails to compile in a handful of larger packages like `ghc` and `base`). * Add newlines after all block elements in LaTeX. This is important to prevent the final output from being more an more indented. See the `latext-test/src/Example` test case for a sample of this. * Support associated types in class declarations (but not yet defaults) * Several small issues for producing compiling LaTeX; - avoid empy `\haddockbeginargs` lists (ex: `type family Any`) - properly escape identifiers depending on context (ex: `Int#`) - add `vbox` around `itemize`/`enumerate` (so they can be in tables) * Several spacing fixes: - limit the width of `Pretty`-arranged monospaced code - cut out extra space characters in export lists - only escape spaces if there are _multiple_ spaces - allow type signatures to be multiline (even without docs) * Remove uninteresting and repetitive `main.tex`/`haddock.sty` files from `latex-test` test reference output. Fixes haskell/haddock#935, haskell/haddock#929 (LaTeX docs for `text` build & compile) Fixes haskell/haddock#727, haskell/haddock#930 (I think both are really about type families...) - - - - - 0e6cee00 by Alec Theriault at 2019-03-29T12:11:56-07:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - ce05434d by Alan Zimmerman at 2019-03-29T12:12:11-07:00 Matching changes in GHC for haskell/haddock#16236 (cherry picked from commit 3ee6526d4ae7bf4deb7cd1caf24b3d7355573576) - - - - - d85766b2 by Ben Gamari at 2019-03-29T12:14:04-07:00 Bump GHC to 8.8 - - - - - 5a82cbaf by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Redo ParseModuleHeader - - - - - b9033348 by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - bb55c8f4 by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove outdated `.ghci` files and `scripts` The `.ghci` files are actively annoying when trying to `cabal v2-repl`. As for the `scripts`, the distribution workflow is completely different. - - - - - 5ee244dc by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove obsolete arcanist files + STYLE Now that GHC is hosted on Gitlab, the arcanist files don't make sense anymore. The STYLE file contains nothing more than a dead link too. - - - - - d07c1928 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Redo ParseModuleHeader - - - - - 492762d2 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - af2ac773 by Ryan Scott at 2019-05-14T17:22:13-04:00 Changes for haskell/haddock#16110/#16356 - - - - - 6820ed0d by Alec Theriault at 2019-05-17T08:51:27-07:00 Unbreak haskell/haddock#1004 test case `fail` is no longer part of `Monad`. - - - - - 6bf7be98 by Alec Theriault at 2019-05-17T08:51:27-07:00 Fix haskell/haddock#1063 with better parenthesization logic for contexts The only other change in html/hoogle/hyperlinker output for the boot libraries that this caused is a fix to some Hoogle output for implicit params. ``` $ diff -r _build/docs/ old_docs diff -r _build/docs/html/libraries/base/base.txt old_docs/html/libraries/base/base.txt 13296c13296 < assertError :: (?callStack :: CallStack) => Bool -> a -> a --- > assertError :: ?callStack :: CallStack => Bool -> a -> a ``` - - - - - b5716b61 by Ryan Scott at 2019-05-22T17:24:32-04:00 Match changes with haskell/haddock#14332 - - - - - c115abf6 by Alec Theriault at 2019-05-26T16:01:58-04:00 Remove Haddock's dependency on `Cabal` At this point, Haddock depended on Cabal-the-library solely for a verbosity parser (which misleadingly accepts all sorts of verbosity options that Haddock never uses). Now, the only dependency on Cabal is for `haddock-test` (which uses Cabal to locate the Haddock interface files of a couple boot libraries). - - - - - e5b2d4a3 by Alec Theriault at 2019-05-26T16:16:25-04:00 Regression test: promoted lists in associated types When possible, associated types with promoted lists should use the promoted list literal syntax (instead of repeated applications of ': and '[]). This was fixed in 2122de5473fd5b434af690ff9ccb1a2e58491f8c. Closes haskell/haddock#466, - - - - - cc5ad5d3 by Alec Theriault at 2019-05-26T17:55:54-04:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 4b3301a6 by Alec Theriault at 2019-05-26T17:57:52-04:00 Release haddock-2.23, haddock-library-1.8.0 Tentatively adjust bounds and changelogs for the release to be bundled with GHC 8.8.1. - - - - - 69c7cfce by Matthew Pickering at 2019-05-30T10:54:27+01:00 Update hyperlinker tests for new types in .hie files - - - - - 29b7e738 by Zubin Duggal at 2019-05-30T10:57:51+01:00 update for new way to store hiefile headers - - - - - aeca5d5f by Zubin Duggal at 2019-06-04T18:57:42-04:00 update for new way to store hiefile headers - - - - - ba2ca518 by Ben Gamari at 2019-06-07T23:11:14+00:00 Update test output for introduction of Safe-Inferred - - - - - 3a975a6c by Ryan Scott at 2019-07-03T12:06:27-04:00 Changes for haskell/haddock#15247 - - - - - 0df46555 by Zubin Duggal at 2019-07-22T10:52:50+01:00 Fix haddockHypsrcTest - - - - - 2688686b by Sylvain Henry at 2019-09-12T23:19:39+02:00 Fix for GHC module renaming - - - - - 9ec0f3fc by Alec Theriault at 2019-09-20T03:21:00-04:00 Fix Travis CI, loosen .cabal bounds (#1089) Tentatively for the 2.23 release: * updated Travis CI to work again * tweaked bounds in the `.cabal` files * adjusted `extra-source-files` to properly identify test files - - - - - ca559beb by Matthías Páll Gissurarson at 2019-09-28T12:14:40-04:00 Small change in to facilitate extended typed-holes (#1090) This change has no functional effect on haddock itself, it just changes one pattern to use `_ (` rather than `_(`, so that we may use `_(` as a token for extended typed-holes later. - - - - - 02e28976 by Vladislav Zavialov at 2019-09-28T12:17:45-04:00 Remove spaces around @-patterns (#1093) This is needed to compile `haddock` when [GHC Proposal haskell/haddock#229](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0229-whitespace-bang-patterns.rst) is implemented. - - - - - 83cbbf55 by Alexis King at 2019-09-30T21:12:42-04:00 Fix the ignore-exports option (#1082) The `ignore-exports` option has been broken since haskell/haddock#688, as mentioned in https://github.com/haskell/haddock/pull/766#issue-172505043. This PR fixes it. - - - - - e127e0ab by Ben Gamari at 2019-10-06T15:12:06-04:00 Fix a few haddock issues - - - - - 3a0f5c89 by Zubin Duggal at 2019-10-07T17:56:13-04:00 Fix crash when there are no srcspans in the file due to CPP - - - - - 339c5ff8 by Alec Theriault at 2019-10-07T17:56:13-04:00 Prefer un-hyperlinked sources to no sources It is possible to fail to extract an HIE ast. This is however not a reason to produce _no_ output - we should still make a colorized HTML page. - - - - - d47ef478 by Alec Theriault at 2019-10-07T17:56:13-04:00 Add a regression test for haskell/haddock#1091 Previously, this input would crash Haddock. - - - - - ed7c8b0f by Alec Theriault at 2019-10-07T20:56:48-04:00 Add Hyperlinker test cases for TH-related stuff Hopefully this will guard against regressions around quasiquotes, TH quotes, and TH splices. - - - - - d00436ab by Andreas Klebinger at 2019-10-21T15:53:03+02:00 Refactor for withTiming changes. - - - - - 4230e712 by Ben Gamari at 2019-10-22T09:36:37-04:00 Merge pull request haskell/haddock#1101 from AndreasPK/withTimingRefactor Refactor for withTiming changes. - - - - - d155c5f4 by Ryan Scott at 2019-10-23T10:37:17-04:00 Reify oversaturated data family instances correctly (#1103) This fixes haskell/haddock#1103 by adapting the corresponding patch for GHC (see https://gitlab.haskell.org/ghc/ghc/issues/17296 and https://gitlab.haskell.org/ghc/ghc/merge_requests/1877). - - - - - 331a5adf by Sebastian Graf at 2019-10-25T17:14:40+02:00 Refactor for OutputableBndrId changes - - - - - 48a490e0 by Ben Gamari at 2019-10-27T10:16:16-04:00 Merge pull request haskell/haddock#1105 from sgraf812/wip/flexible-outputable Refactor for OutputableBndrId changes - - - - - f62a7dfc by Sebastian Graf at 2019-11-01T11:54:16+00:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - d9b242ed by Ryan Scott at 2019-11-03T13:20:03-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. (cherry picked from commit cfd682c5fd03b099a3d78c44f9279faf56a0ac70) - - - - - dfd42406 by Sebastian Graf at 2019-11-04T07:02:14-05:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - 0b15be7c by Ben Gamari at 2019-11-09T13:21:33-05:00 Import isRuntimeRepVar from Type rather than TyCoRep isRuntimeRepVar is not longer exported from TyCoRep due to ghc#17441. - - - - - 091f7283 by Ben Gamari at 2019-11-10T12:47:06-05:00 Bump to GHC 8.10 - - - - - e88c71f2 by Ben Gamari at 2019-11-14T00:22:24-05:00 Merge pull request haskell/haddock#1110 from haskell/wip/T17441 Import isRuntimeRepVar from Type rather than TyCoRep - - - - - 4e0bbc17 by Ben Gamari at 2019-11-14T00:22:45-05:00 Version bumps for GHC 8.11 - - - - - 0e85ceb4 by Ben Gamari at 2019-11-15T11:59:45-05:00 Bump to GHC 8.10 - - - - - 00d6d68b by Ben Gamari at 2019-11-16T18:35:58-05:00 Bump ghc version to 8.11 - - - - - dde1fc3f by Ben Gamari at 2019-11-16T20:40:37-05:00 Drop support for base 4.13 - - - - - f52e331d by Vladislav Zavialov at 2019-11-24T13:02:28+03:00 Update Hyperlinker.Parser.classify to use ITdollar - - - - - 1ad96198 by Vladislav Zavialov at 2019-11-28T16:12:33+03:00 Remove HasSrcSpan (#17494) - - - - - 651afd70 by Herbert Valerio Riedel at 2019-12-08T12:08:16+01:00 Document error-prone conditional definition of instances This can easily trip up people if one isn't aware of it. Usually it's better to avoid this kind of conditionality especially for typeclasses for which there's an compat-package as conditional instances like these tend to fragment the ecosystem into those packages that go the extra mile to provide backward compat via those compat-packages and those that fail to do so. - - - - - b521af56 by Herbert Valerio Riedel at 2019-12-08T12:09:54+01:00 Fix build-failure regression for base < 4.7 The `$>` operator definition is available only since base-4.7 which unfortunately wasn't caught before release to Hackage (but has been fixed up by a metadata-revision) This commit introduces a `CompatPrelude` module which allows to reduce the amount of CPP by ousting it to a central location, i.e. the new `CompatPrelude` module. This pattern also tends to reduce the tricks needed to silence unused import warnings. Addresses haskell/haddock#1119 - - - - - 556c375d by Sylvain Henry at 2020-01-02T19:01:55+01:00 Fix after Iface modules renaming - - - - - bd6c53e5 by Sylvain Henry at 2020-01-07T00:48:48+01:00 hsyl20-modules-renamer - - - - - fb23713b by Ryan Scott at 2020-01-08T07:41:13-05:00 Changes for GHC#17608 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2372 - - - - - 4a4dd382 by Ryan Scott at 2020-01-25T08:08:26-05:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - e782a44d by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename PackageConfig into UnitInfo - - - - - ba3c9f05 by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename lookupPackage - - - - - ab37f9b3 by Ben Gamari at 2020-01-29T13:00:44-05:00 Merge pull request haskell/haddock#1125 from haskell/wip/T17566-take-two Changes for GHC#17566 - - - - - 3ebd5ae0 by Ryan Scott at 2020-01-31T05:56:50-05:00 Merge branch 'wip-hsyl20-package-refactor' into ghc-head - - - - - 602a747e by Richard Eisenberg at 2020-02-04T09:05:43+00:00 Echo GHC's removal of PlaceHolder module This goes with GHC's !2083. - - - - - ccfe5679 by Sylvain Henry at 2020-02-10T10:13:56+01:00 Module hierarchy: runtime (cf haskell/haddock#13009) - - - - - 554914ce by Cale Gibbard at 2020-02-10T16:10:39-05:00 Fix build of haddock in stage1 We have to use the correct version of the GHC API, but the version of the compiler itself doesn't matter. - - - - - 5b6fa2a7 by John Ericson at 2020-02-10T16:18:07-05:00 Noramlize `tested-with` fields in cabal files - - - - - e6eb3ebe by Vladislav Zavialov at 2020-02-16T13:25:26+03:00 No MonadFail/Alternative for P - - - - - 90e181f7 by Ben Gamari at 2020-02-18T14:13:47-05:00 Merge pull request haskell/haddock#1129 from obsidiansystems/wip/fix-stage1-build Fix build of haddock in stage1 - - - - - 93b64636 by Sylvain Henry at 2020-02-19T11:20:27+01:00 Modules: Driver (#13009) - - - - - da4f6c7b by Vladislav Zavialov at 2020-02-22T15:33:02+03:00 Use RealSrcSpan in InstMap - - - - - 479b1b50 by Ben Gamari at 2020-02-23T10:28:13-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 55ecacf0 by Sylvain Henry at 2020-02-25T15:18:27+01:00 Modules: Core (#13009) - - - - - 60867b3b by Vladislav Zavialov at 2020-02-28T15:53:52+03:00 Ignore the BufLoc/BufSpan added in GHC's !2516 - - - - - 1e5506d3 by Sylvain Henry at 2020-03-02T12:32:43+01:00 Modules: Core (#13009) - - - - - 6fb53177 by Richard Eisenberg at 2020-03-09T14:49:40+00:00 Changes in GHC's !1913. - - - - - 30b792ea by Ben Gamari at 2020-03-16T12:45:02-04:00 Merge pull request haskell/haddock#1130 from hsyl20/wip/hsyl20-modules-core2 Modules: Core (#13009) - - - - - cd761ffa by Sylvain Henry at 2020-03-18T15:24:00+01:00 Modules: Types - - - - - b6646486 by Ben Gamari at 2020-03-18T14:42:43-04:00 Merge pull request haskell/haddock#1133 from hsyl20/wip/hsyl20/modules/types Modules: Types - - - - - 9325d734 by Kleidukos at 2020-03-19T12:38:31-04:00 Replace the 'caption' class so that the collapsible sections are shown - - - - - 5e2bb555 by Kleidukos at 2020-03-19T12:38:31-04:00 Force ghc-8.8.3 - - - - - c6fcd0aa by Kleidukos at 2020-03-19T12:38:31-04:00 Update test fixtures - - - - - 5c849cb1 by Sylvain Henry at 2020-03-20T09:34:39+01:00 Modules: Types - - - - - 7f439155 by Alec Theriault at 2020-03-20T20:17:01-04:00 Merge branch 'ghc-8.8' into ghc-8.10 - - - - - b7904e5c by Alina Banerjee at 2020-03-20T20:24:17-04:00 Update parsing to strip whitespace from table cells (#1074) * Update parsing to strip leading & trailing whitespace from table cells * Update fixture data to disallow whitespaces at both ends in table cells * Add test case for whitespaces stripped from both ends of table cells * Update table reference test data for html tests - - - - - b9d60a59 by Alec Theriault at 2020-03-22T11:46:42-04:00 Clean up warnings * unused imports * imports of `Data.List` without import lists * missing `CompatPrelude` file in `.cabal` - - - - - 0c317dbe by Alec Theriault at 2020-03-22T18:46:54-04:00 Fix NPM security warnings This was done by calling `npm audit fix`. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. - - - - - 6e306242 by Alec Theriault at 2020-03-22T20:10:52-04:00 Tentative 2.24 release Adjusted changelogs and versions in `.cabal` files in preparation for the upcoming release bundled with GHC 8.10. - - - - - 1bfb4645 by Ben Gamari at 2020-03-23T16:40:54-04:00 Merge commit '3c2944c037263b426c4fe60a3424c27b852ea71c' into HEAD More changes from the GHC types module refactoring. - - - - - be8c6f3d by Alec Theriault at 2020-03-26T20:10:53-04:00 Update `.travis.yml` to work with GHC 8.10.1 * Regenerated the Travis file with `haskell-ci` * Beef up `.cabal` files with more `tested-with` information - - - - - b025a9c6 by Alec Theriault at 2020-03-26T20:10:53-04:00 Update README Removed some out of date links/info, added some more useful links. * badge to Hackage * update old trac link * `ghc-head` => `ghc-8.10` * `cabal new-*` is now `cabal v2-*` and it should Just Work * `--test-option='--accept'` is the way to accept testsuite output - - - - - 564d889a by Alec Theriault at 2020-03-27T20:34:33-04:00 Fix crash in `haddock-library` on unicode space Our quickcheck tests for `haddock-library` stumbled across an edge case input that was causing Haddock to crash: it was a unicode space character. The root cause of the crash is that we were implicitly assuming that if a space character was not " \t\f\v\r", it would have to be "\n". We fix this by instead defining horizontal space as: any space character that is not '\n'. Fixes haskell/haddock#1142 - - - - - 2d360ba1 by Alec Theriault at 2020-03-27T21:57:32-04:00 Disallow qualified uses of reserved identifiers This a GHC bug (https://gitlab.haskell.org/ghc/ghc/issues/14109) too, but it is a relatively easy fix in Haddock. Note that the fix must live in `haddock-api` instead of `haddock-library` because we can only really decide if an identifier is a reserved one by asking the GHC lexer. Fixes haskell/haddock#952 - - - - - 47ae22ed by Alec Theriault at 2020-03-28T13:36:25-04:00 Remove unused `Haddock.Utils` functions * removed functions in `Haddock.Utils` that were not used anywhere (or exported from the `haddock-api` package) * moved GHC-specific utils from `Haddock.Utils` to `Haddock.GhcUtils` - - - - - c0291245 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use TTG empty extensions to remove some `error`'s None of these error cases should ever have been reachable, so this is just a matter of leveraging the type system to assert this. * Use the `NoExtCon` and `noExtCon` to handle case matches for no extension constructors, instead of throwing an `error`. * Use the extension field of `HsSpliceTy` to ensure that this variant of `HsType` cannot exist in an `HsType DocNameI`. - - - - - 0aff8dc4 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use `unLoc`/`noLoc` from GHC instead of `unL`/`reL` * `unL` is already defined by GHC as `unLoc` * `reL` is already defined by GHC as `noLoc` (in a safer way too!) * Condense `setOutputDir` and add a about exporting from GHC Fixes haskell/haddock#978 - - - - - bf6f2fb7 by Alec Theriault at 2020-03-28T13:36:25-04:00 Cleanup up GHC flags in `.cabal` files * enable more useful warning flags in `haddock-api`, handle the new warnings generated * remove `-fwarn-tabs` (now we'd use `-Wtabs`, but this has been in `-Wall` for a while now) - - - - - c576fbf1 by Alec Theriault at 2020-03-28T13:36:25-04:00 `haddock-library` document header level Document the fact the header level is going to always be between 1 and 6 inclusive. Along the way, I also optimized the parsing code a bit. - - - - - 71bce0ee by Alec Theriault at 2020-03-28T14:26:27-04:00 Disallow links in section headers This is quite straightforward to implement, since we already had a function `docToHtmlNoAnchors` (which we used to generate the link in the sidebar "Contents"). This breaks test `Bug387`, but that test case has aged badly: we now automatically generate anchors for all headings, so manually adding an anchor in a section makes no sense. Nested anchors are, as pointed out in haskell/haddock#1054, disallowed by the HTML standard. Fixes haskell/haddock#1054 - - - - - b461b0ed by Sylvain Henry at 2020-03-30T10:34:23+02:00 Modules: type checker - - - - - cd8cd1ee by Ben Gamari at 2020-03-31T12:45:02-04:00 Merge pull request haskell/haddock#1152 from hsyl20/wip/hsyl20/modules/tc Module renaming - - - - - 5e8f8ea7 by Felix Yan at 2020-04-01T17:58:06-07:00 Allow QuickCheck 2.14 Builds fine and all tests pass. - - - - - dc6b1633 by Sylvain Henry at 2020-04-05T16:43:44+02:00 Module renaming: amend previous patch - - - - - eee2f4ae by Ryan Scott at 2020-04-05T09:04:43-07:00 Fix haskell/haddock#1050 by filtering out invisible AppTy arguments This makes the `synifyType` case for `AppTy` more intelligent by taking into consideration the visibilities of each `AppTy` argument and filtering out any invisible arguments, as they aren't intended to be displayed in the source code. (See haskell/haddock#1050 for an example of what can happen if you fail to filter these out.) Along the way, I noticed that a special `synifyType` case for `AppTy t1 (CoercionTy {})` could be consolidated with the case below it, so I took the opportunity to tidy this up. - - - - - 23eb99e8 by Ben Gamari at 2020-04-07T11:19:58-04:00 Merge pull request haskell/haddock#1154 from hsyl20/wip/hsyl20/modules/tc Module renaming: amend previous patch - - - - - 072d994d by Ryan Scott at 2020-04-07T19:32:47-04:00 Make NoExtCon fields strict These changes are a part of a fix for [GHC#17992](https://gitlab.haskell.org/ghc/ghc/issues/17992). - - - - - d8ebf6c8 by Ignat Insarov at 2020-04-09T21:15:01-04:00 Recode Doc to Json. (#1159) * Recode Doc to Json. * More descriptive field labels. - - - - - 52df4b4e by Sylvain Henry at 2020-04-10T12:39:18+02:00 Module renaming - - - - - d9ab8ec8 by Cale Gibbard at 2020-04-14T11:43:34-04:00 Add instance of XCollectPat for DocNameI - - - - - 323d221d by Cale Gibbard at 2020-04-14T11:43:34-04:00 Rename XCollectPat -> CollectPass - - - - - 2df80867 by Alec Theriault at 2020-04-15T07:30:51-07:00 Prune docstrings that are never rendered When first creating a Haddock interface, trim `ifaceDocMap` and `ifaceArgMap` to not include docstrings that can never appear in the final output. Besides checking with GHC which names are exported, we also need to keep all the docs attached to instance declarations (it is much tougher to detect when an instance is fully private). This change means: * slightly smaller interface files (7% reduction on boot libs) * slightly less work to do processing docstrings that aren't used * no warnings in Haddock's output about private docstrings (see haskell/haddock#1070) I've tested manually that this does not affect any of the boot library generated docs (the only change in output was some small re-ordering in a handful of instance lists). This should mean no docstrings have been incorrectly dropped. - - - - - f49c90cc by Alec Theriault at 2020-04-15T07:30:51-07:00 Don't warn about missing links in miminal sigs When renaming the Haddock interface, never emit warnings when renaming a minimal signature. Also added some documention around `renameInterface`. Minimal signatures intentionally include references to potentially un-exported methods (see the discussion in haskell/haddock#330), so it is expected that they will not always have a link destination. On the principle that warnings should always be resolvable, this shouldn't produce a warning. See haskell/haddock#1070. - - - - - a9eda64d by Ben Gamari at 2020-04-17T09:27:35-04:00 Merge pull request haskell/haddock#1160 from hsyl20/wip/hsyl20/modules/systools Module renaming - - - - - f40d7879 by Cale Gibbard at 2020-04-20T11:30:38-04:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ttg-con-pat - - - - - a50e7753 by Ben Gamari at 2020-04-20T11:36:10-04:00 Merge pull request haskell/haddock#1165 from obsidiansystems/wip/ttg-con-pat Trees that Grow refactor (GHC !2553) - - - - - 6a24795c by Alec Theriault at 2020-04-21T08:06:45-07:00 Fallback to `hiDecl` when `extractDecl` fails Sometimes, the declaration being exported is a subdecl (for instance, a record accessor getting exported at the top-level). For these cases, Haddock has to find a way to produce some synthetic sensible top-level declaration. This is done with `extractDecl`. As is shown by haskell/haddock#1067, this is sometimes impossible to do just at a syntactic level (for instance when the subdecl is re-exported). In these cases, the only sensible thing to do is to try to reify a declaration based on a GHC `TyThing` via `hiDecl`. - - - - - eee1a8b7 by Sylvain Henry at 2020-04-24T15:46:05+02:00 Module structure - - - - - 50b9259c by Iñaki at 2020-04-25T18:38:11-04:00 Add support for custom section anchors (#1179) This allows to have stable anchors for groups, even if the set of groups in the documentation is altered. The syntax for setting the anchor of a group is -- * Group name #desiredAnchor# Which will produce an html anchor of the form '#g:desiredAnchor' Co-authored-by: Iñaki García Etxebarria <git at inaki.blueleaf.cc> - - - - - 4003c97a by Ben Gamari at 2020-04-26T09:35:15-04:00 Merge pull request haskell/haddock#1166 from hsyl20/wip/hsyl20/modules/utils Module structure - - - - - 5206ab60 by Sylvain Henry at 2020-04-27T16:47:39+02:00 Renamed UnitInfo fields - - - - - c32c333b by Sylvain Henry at 2020-04-27T17:32:58+02:00 UnitId has been renamed into Unit - - - - - 3e87db64 by Sylvain Henry at 2020-04-27T17:36:00+02:00 Fix for GHC.Unit.* modules - - - - - ae3323a7 by Ben Gamari at 2020-04-29T12:36:37-04:00 Merge pull request haskell/haddock#1183 from hsyl20/wip/hsyl20/unitid Refactoring of Unit code - - - - - b105564a by Artem Pelenitsyn at 2020-05-03T08:14:10+01:00 add dependency on exceptions because GHC.Exception was boiled down (ghc haskell/haddock#18075) - - - - - 9857eff3 by Zubin Duggal at 2020-05-04T18:48:25+01:00 Atomic update of NameCache in readHieFile - - - - - 86bbb226 by Sylvain Henry at 2020-05-14T16:36:27+02:00 Fix after Config module renaming - - - - - a4bbdbc2 by Gert-Jan Bottu at 2020-05-15T22:09:44+02:00 Explicit Specificity Support for Haddock - - - - - 46199daf by Ben Gamari at 2020-05-19T09:59:56-04:00 Merge pull request haskell/haddock#1192 from hsyl20/hsyl20/modules-config Fix after Config module renaming - - - - - f9a9d2ba by Gert-Jan Bottu at 2020-05-20T16:48:38-04:00 Explicit Specificity Support for Haddock - - - - - 55c5b7ea by Ben Gamari at 2020-05-21T00:32:02-04:00 Merge commit 'a8d7e66da4dcc3b242103271875261604be42d6e' into ghc-head - - - - - a566557f by Cale Gibbard at 2020-05-21T16:02:06-04:00 isBootSummary now produces a result of type IsBootInterface - - - - - ea52f905 by Zubin Duggal at 2020-05-24T17:55:48+01:00 update for hiefile-typeclass-info - - - - - 49ba7a67 by Willem Van Onsem at 2020-05-25T12:23:01-04:00 Use floor over round to calculate the percentage (#1195) If we compile documentation where only a small fraction is undocumented, it is misleading to see 100% coverage - 99% is more intuitive. Fixes haskell/haddock#1194 - - - - - c025ebf1 by Ben Gamari at 2020-05-29T14:32:42-04:00 Merge pull request haskell/haddock#1185 from obsidiansystems/boot-disambig isBootSummary now produces a result of type IsBootInterface - - - - - 74ab9415 by Ben Gamari at 2020-05-29T20:23:39-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - b40be944 by Ben Gamari at 2020-06-03T17:02:31-04:00 testsuite: Update expected output for simplified subsumption - - - - - 624be71c by Ryan Scott at 2020-06-05T12:43:23-04:00 Changes for GHC#18191 See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3337. - - - - - fbd8f7ce by Sylvain Henry at 2020-06-08T15:31:47+02:00 Fix after unit refactoring - - - - - 743fda4d by Ben Gamari at 2020-06-09T12:09:58-04:00 Merge pull request haskell/haddock#1202 from hsyl20/wip/hsyl20/unitid-ii Fix after unit refactoring - - - - - d07a06a9 by Ryan Scott at 2020-06-13T07:16:55-04:00 Use HsForAllTelescope (GHC#18235) - - - - - 389bb60d by Ben Gamari at 2020-06-13T15:30:52-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - 7a377f5f by Ben Gamari at 2020-06-17T14:53:16-04:00 Merge pull request haskell/haddock#1199 from bgamari/wip/ghc-8.12 haddock: Bounds bumps for GHC 8.12 - - - - - 9fd9e586 by Krzysztof Gogolewski at 2020-06-17T16:09:07-04:00 Adapt Haddock to LinearTypes See ghc/ghc!852. - - - - - 46fe7636 by Ben Gamari at 2020-06-18T14:20:02-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 35a3c9e2 by Zubin Duggal at 2020-06-21T21:19:18+05:30 Use functions exported from HsToCore - - - - - 8abe3928 by Ben Gamari at 2020-06-24T13:53:39-04:00 Merge pull request haskell/haddock#1204 from wz1000/wip/haddock-hstocore Use functions exported from GHC.HsToCore.Docs - - - - - 22f2c937 by Matthías Páll Gissurarson at 2020-06-26T19:07:03+02:00 Adapt Haddock for QualifiedDo - - - - - 3f6208d7 by Vladislav Zavialov at 2020-06-28T14:28:16+03:00 Handle LexicalNegation's ITprefixminus - - - - - 03a19f41 by Sylvain Henry at 2020-07-02T09:37:38+02:00 Rename hsctarget into backend - - - - - ea17ff23 by Andreas Klebinger at 2020-07-02T17:44:18+02:00 Update for UniqFM changes. - - - - - 9872f2f3 by Ben Gamari at 2020-07-09T10:39:19-04:00 Merge pull request haskell/haddock#1209 from AndreasPK/wip/typed_uniqfm Update for UniqFM changes. - - - - - 68f7b668 by Krzysztof Gogolewski at 2020-07-12T18:16:57+02:00 Sync with GHC removing {-# CORE #-} pragma See ghc ticket haskell/haddock#18048 - - - - - eb372681 by Sylvain Henry at 2020-07-20T11:41:30+02:00 Rename hscTarget into backend - - - - - fb7f78bf by Ben Gamari at 2020-07-21T12:15:25-04:00 Merge pull request haskell/haddock#1214 from hsyl20/wip/hsyl20/hadrian/ncg Rename hscTarget into backend - - - - - 1e8f5b56 by Ben Gamari at 2020-07-23T09:11:50-04:00 Merge commit '904dce0cafe0a241dd3ef355775db47fc12f434d' into ghc-head - - - - - d8fd1775 by Zubin Duggal at 2020-07-23T18:46:40+05:30 Update for modular ping pong - - - - - 8416f872 by Ben Gamari at 2020-07-23T09:35:03-04:00 Merge pull request haskell/haddock#1200 from wz1000/wip/wz1000-modular-ping-pong Modular ping pong - - - - - a24a8577 by Ben Gamari at 2020-07-28T15:23:36-04:00 Bump GHC version to 9.0 - - - - - 6a51c9dd by Sylvain Henry at 2020-08-05T18:47:05+02:00 Fix after Outputable refactoring - - - - - c05e1c99 by Ben Gamari at 2020-08-10T14:41:41-04:00 Merge pull request haskell/haddock#1223 from hsyl20/wip/hsyl20/dynflags/exception Fix after Outputable refactoring - - - - - d964f15b by Sylvain Henry at 2020-08-12T11:58:49+02:00 Fix after HomeUnit - - - - - 8e6d5b23 by Ben Gamari at 2020-08-12T14:25:30-04:00 Merge pull request haskell/haddock#1225 from hsyl20/wip/hsyl20/plugins/homeunit Fix after HomeUnit - - - - - 8c7880fe by Sylvain Henry at 2020-08-17T14:13:29+02:00 Remove Ord FastString instance - - - - - 8ea410db by Alex Biehl at 2020-08-19T10:56:32+02:00 Another round of `npm audit fix` (#1228) This should shut down the warnings on Github. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. Last NPM dependency audit happend in d576b2327e2bc117f912fe0a9d595e9ae62614e0 Co-authored-by: Alex Biehl <alex.biehl at target.com> - - - - - 7af6e2a8 by Ben Gamari at 2020-08-31T13:59:34-04:00 Merge pull request haskell/haddock#1226 from hsyl20/wip/hsyl20/fs_ord Remove Ord FastString instance - - - - - ffbc8702 by Alan Zimmerman at 2020-09-07T21:47:41+01:00 Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - a93f1268 by Alan Zimmerman at 2020-09-07T23:11:38+01:00 Merge pull request haskell/haddock#1232 from haskell/wip/T18639-remove-generated-pragma, Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - 1f605d50 by Ben Gamari at 2020-09-14T18:30:01-04:00 Bump GHC version to 9.1 - - - - - 6599df62 by Vladislav Zavialov at 2020-09-18T14:05:15+03:00 Bump base upper bound to 4.16 - - - - - a01b3c43 by Ben Gamari at 2020-09-22T15:41:48-04:00 Update hypsrc-test for QuickLook This appears to be a spurious change. - - - - - e9cc6cac by Vladislav Zavialov at 2020-09-26T21:00:12+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 30e3ca7c by Sylvain Henry at 2020-09-29T11:18:32-04:00 Update for parser (#1234) - - - - - b172f3e3 by Vladislav Zavialov at 2020-09-30T01:01:30+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 0b9c08d3 by Sylvain Henry at 2020-09-30T11:02:33+02:00 Adapt to GHC parser changes - - - - - b9540b7a by Sylvain Henry at 2020-10-12T09:13:38-04:00 Don't pass the HomeUnitId (#1239) - - - - - 34762e80 by HaskellMouse at 2020-10-13T12:58:04+03:00 Changed tests due to unification of `Nat` and `Natural` in the follwing merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3583 - - - - - 256f86b6 by Vladislav Zavialov at 2020-10-15T10:48:03+03:00 Add whitespace in: map ($ v) - - - - - 4a3f711b by Alan Zimmerman at 2020-10-19T08:57:27+01:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled - - - - - 072cdd21 by Alan Zimmerman at 2020-10-21T14:48:28-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 9e09a445 by Alan Zimmerman at 2020-10-21T23:53:34-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 636d7de3 by Sylvain Henry at 2020-10-26T14:31:54-04:00 GHC.Driver.Types refactoring (#1242) - - - - - a597f000 by Ryan Scott at 2020-10-29T04:18:05-04:00 Adapt to the removal of Hs{Boxed,Constraint}Tuple See ghc/ghc!4097 and GHC#18723. - - - - - b96660fb by Ryan Scott at 2020-10-30T04:53:05-04:00 Adapt to HsConDecl{H98,GADT}Details split Needed for GHC#18844. - - - - - c287d82c by Ryan Scott at 2020-10-30T19:35:59-04:00 Adapt to HsOuterTyVarBndrs These changes accompany ghc/ghc!4107, which aims to be a fix for haskell/haddock#16762. - - - - - a34c31a1 by Ryan Scott at 2020-11-13T13:38:34-05:00 Adapt to splitPiTysInvisible being renamed to splitInvisPiTys This is a part of !4434, a fix for GHC#18939. - - - - - 66ea459d by Sylvain Henry at 2020-11-16T10:59:30+01:00 Fix after Plugins moved into HscEnv - - - - - 508556d8 by Ben Gamari at 2020-11-18T15:47:40-05:00 Merge pull request haskell/haddock#1253 from hsyl20/wip/hsyl20/plugins/hscenv Fix after Plugins moved into HscEnv - - - - - 620fec1a by Andreas Klebinger at 2020-11-24T20:51:59+01:00 Update for changes in GHC's Pretty - - - - - 01cc13ab by Richard Eisenberg at 2020-11-25T23:18:35-05:00 Avoid GHC#18932. - - - - - 8d29ba21 by Cale Gibbard at 2020-11-25T23:18:35-05:00 Add type arguments to PrefixCon - - - - - 414d5f87 by Sylvain Henry at 2020-11-30T17:06:04+01:00 DynFlags's unit fields moved to HscEnv - - - - - e356668c by Ben Gamari at 2020-11-30T11:11:37-05:00 Merge pull request haskell/haddock#1258 from hsyl20/wip/hsyl20/hscenv/unitstate Unit fields moved from DynFlags to HscEnv - - - - - 7cf552f1 by Ben Gamari at 2020-12-03T10:31:27-05:00 Merge pull request haskell/haddock#1257 from AndreasPK/wip/andreask/opt_dumps Update for changes in GHC's Pretty - - - - - fc0871c3 by Veronika Romashkina at 2020-12-08T16:35:33+01:00 Fix docs links from Darcs to GitHub in intro (#1262) - - - - - 7059e808 by Veronika Romashkina at 2020-12-08T16:36:16+01:00 Use gender neutral word in docs (#1260) - - - - - 1b16e5ee by Maximilian Tagher at 2020-12-08T16:40:03+01:00 Allow scrolling search results (#1235) Closes https://github.com/haskell/haddock/issues/1231 - - - - - 8a118c01 by dependabot[bot] at 2020-12-08T16:40:25+01:00 Bump bl from 1.2.2 to 1.2.3 in /haddock-api/resources/html (#1255) Bumps [bl](https://github.com/rvagg/bl) from 1.2.2 to 1.2.3. - [Release notes](https://github.com/rvagg/bl/releases) - [Commits](https://github.com/rvagg/bl/compare/v1.2.2...v1.2.3) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - c89ff587 by Xia Li-yao at 2020-12-08T16:42:17+01:00 Allow more characters in anchor following module reference (#1220) - - - - - 14af7d64 by Xia Li-yao at 2020-12-08T16:43:05+01:00 Add dangling changes from branches ghc-8.6 and ghc-8.8 (#1243) * Fix multiple typos and inconsistencies in doc/markup.rst Note: I noticed some overlap with haskell/haddock#1112 from @wygulmage and haskell/haddock#1081 from @parsonsmatt after creating these proposed changes - mea culpa for not looking at the open PRs sooner. * Fix haskell/haddock#1113 If no Signatures, no section of index.html * Change the formatting of missing link destinations The current formatting of the missing link destination does not really help user to understand the reasons of the missing link. To address this, I've changed the formatting in two ways: - the missing link symbol name is now fully qualified. This way you immediately know which haskell module cannot be linked. It is then easier to understand why this module does not have documentation (hidden module or broken documentation). - one line per missing link, that's more readable now that symbol name can be longer due to qualification. For example, before haddock was listing missing symbol such as: ``` could not find link destinations for: Word8 Word16 mapMaybe ``` Now it is listed as: ``` could not find link destinations for: - Data.Word.Word8 - Data.Word.Word16 - Data.Maybe.mapMaybe ``` * Add `--ignore-link-symbol` command line argument This argument can be used multiples time. A missing link to a symbol listed by `--ignore-link-symbol` won't trigger "missing link" warning. * Forbid spaces in anchors (#1148) * Improve error messages with context information (#1060) Co-authored-by: Matt Audesse <matt at mattaudesse.com> Co-authored-by: Mike Pilgrem <mpilgrem at users.noreply.github.com> Co-authored-by: Guillaume Bouchard <guillaume.bouchard at tweag.io> Co-authored-by: Pepe Iborra <pepeiborra at gmail.com> - - - - - 89e3af13 by tomjaguarpaw at 2020-12-08T18:00:04+01:00 Enable two warnings (#1245) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - c3320f8d by Willem Van Onsem at 2020-12-08T18:26:55+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 685df308 by Alex Biehl at 2020-12-08T20:06:26+01:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - be3ec3c0 by Alex Biehl at 2020-12-08T20:06:26+01:00 Import intercalate - - - - - 32c33912 by Matthías Páll Gissurarson at 2020-12-08T21:15:30+01:00 Adapt Haddock for QualifiedDo - - - - - 31696088 by Alex Biehl at 2020-12-08T22:06:02+01:00 Fix haddock-library tests - - - - - fbc0998a by Alex Biehl at 2020-12-08T23:08:23+01:00 Move to GitHub CI (#1266) * Initial version of ci.yml This is a straight copy from Dmitrii Kovanikov's blog post at https://kodimensional.dev/github-actions. Will adapt to haddock in successive commits. * Delete .travis.yml * Modify to only test on ghc-8.10.{1,2} * Use actions/setup-haskell at v1.1.4 * Relax QuickCheck bound on haddock-api * Remove stack matrix for now * Nail down to ghc-8.10 branch for now * Pin index state to 2020-12-08T20:13:44Z for now * Disable macOS and Windows tests for now for speed up - - - - - 5b946b9a by tomjaguarpaw at 2020-12-10T19:01:41+01:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - bc5a408f by dependabot[bot] at 2020-12-10T19:02:16+01:00 Bump ini from 1.3.5 to 1.3.7 in /haddock-api/resources/html (#1269) Bumps [ini](https://github.com/isaacs/ini) from 1.3.5 to 1.3.7. - [Release notes](https://github.com/isaacs/ini/releases) - [Commits](https://github.com/isaacs/ini/compare/v1.3.5...v1.3.7) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - d02995f1 by Andrew Martin at 2020-12-14T16:48:40-05:00 Update for boxed rep - - - - - a381aeff by Ben Gamari at 2020-12-15T15:13:30-05:00 Revert "Enable two warnings (#1245) (#1268)" As this does not build on GHC `master`. This reverts commit 7936692badfe38f23ae95b51fb7bd7c2ff7e9bce. - - - - - a63c0a9e by Ben Gamari at 2020-12-15T15:17:59-05:00 Revert "Update for boxed rep" This reverts commit 4ffb30d8b637ccebecc81ce610f0af451ac8088d. - - - - - 53bfbb29 by Ben Gamari at 2020-12-15T15:37:24-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - bae76a30 by Ben Gamari at 2020-12-16T02:44:42+00:00 Update output for nullary TyConApp optimisation (ghc/ghc!2952) - - - - - 4b733b57 by Krzysztof Gogolewski at 2020-12-16T20:03:14+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. - - - - - ee463bd3 by Ryan Scott at 2020-12-16T16:55:23-05:00 Adapt to HsCoreTy (formerly NewHsTypeX) becoming a type synonym Needed for !4417, the fix for GHC#15706 and GHC#18914. - - - - - ed0b02f8 by tomjaguarpaw at 2020-12-19T10:17:19+00:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - d80bf8f5 by Sylvain Henry at 2020-12-21T10:09:25+01:00 Fix after binder collect changes - - - - - bf4c9d32 by Adam Gundry at 2020-12-23T21:35:01+00:00 Adapt to changes to GlobalRdrElt and AvailInfo Needed for ghc/ghc!4467 - - - - - 37736c4c by John Ericson at 2020-12-28T12:27:02-05:00 Support a new ghc --make node type for parallel backpack upsweep - - - - - 717bdeac by Vladislav Zavialov at 2020-12-29T10:50:02+03:00 Inline and fix getGADTConTypeG The getGADTConTypeG used HsRecTy, which is at odds with GHC issue haskell/haddock#18782. I noticed that getGADTConTypeG was only used in the Hoogle backend. Interestingly, when handling H98 constructors, Hoogle converts RecCon to PrefixCon (see Haddock.Backends.Hoogle.ppCtor). So I changed getGADTConTypeG to handle RecConGADT in the same manner as PrefixConGADT, and after this simplification moved it into the 'where' clause of ppCtor, to the only place where it is used. The practical effect of this change is as follows. Consider this example: data TestH98 = T98 { bar::Int } data TestGADT where TG :: { foo :: Int } -> TestGADT Before this patch, haddock --hoogle used to produce: T98 :: Int -> TestH98 [TG] :: {foo :: Int} -> TestGADT Notice how the record syntax was discarded in T98 but not TG. With this patch, we always produce signatures without record syntax: T98 :: Int -> TestH98 [TG] :: Int -> TestGADT I suspect this might also be a bugfix, as currently Hoogle doesn't seem to render GADT record constructors properly. - - - - - cb1b8c56 by Andreas Abel at 2020-12-30T21:12:37+01:00 Build instructions: haddock-library and -api first! - - - - - b947f6ad by Ben Gamari at 2020-12-31T13:04:19-05:00 Merge pull request haskell/haddock#1281 from obsidiansystems/wip/backpack-j Changes to support -j with backpack - - - - - 120e1cfd by Hécate Moonlight at 2021-01-04T19:54:58+01:00 Merge pull request haskell/haddock#1282 from andreasabel/master Build instructions: haddock-library and -api first! - - - - - fd45e41a by Ben Gamari at 2021-01-05T16:14:31-05:00 Merge remote-tracking branch 'origin/ghc-8.10' into ghc-9.0 - - - - - b471bdec by Ben Gamari at 2021-01-05T16:23:02-05:00 Merge commit '1e56f63c3197e7ca1c1e506e083c2bad25d08793' into ghc-9.0 - - - - - 81cdbc41 by Alex Biehl at 2021-01-09T12:14:41+01:00 Prepare Haddock for being a GHC Plugin - - - - - b646d952 by Alex Biehl at 2021-01-09T12:14:41+01:00 Make Haddock a GHC Plugin - - - - - cc044674 by Alex Biehl at 2021-01-09T12:14:41+01:00 Add -j[n] CLI param to Haddock executable It translates to `--ghcopt=-j[n]` - - - - - 84a04073 by Alex Biehl at 2021-01-09T12:14:41+01:00 Abstract Monad for interface creation I found that when running as a plugin the lookupName function (which runs in Ghc monad) does not work correctly from the typeCheckResultAction hook. Instead, we abstracted the monad used when creating interfaces, so that access to GHC session specific parts is explicit and so that the TcM can provide their (correct) implementation of lookupName. - - - - - 5be2c4f7 by Alex Biehl at 2021-01-09T12:14:41+01:00 Accept tests - - - - - 8cefee9d by Alex Biehl at 2021-01-09T16:10:47+01:00 Add missing dependency for mtl - - - - - 3681f919 by Ben Gamari at 2021-01-13T18:39:25-05:00 Merge remote-tracking branch 'origin/ghc-9.0' into ghc-head - - - - - 33c6b152 by Hécate Moonlight at 2021-01-14T16:04:20+01:00 Merge pull request haskell/haddock#1273 from hsyl20/wip/hsyl20/arrows Fix after binder collect changes - - - - - 70d13e8e by Joachim Breitner at 2021-01-22T19:03:45+01:00 Make haddock more robust to changes to the `Language` data type With the introduction of GHC2021, the `Languages` data type in GHC will grow. In preparation of that (and to avoid changing haddock with each new language), this change makes the code handle extensions to that data type gracefully. (cherry picked from commit c341dd7c9c3fc5ebc83a2d577c5a726f3eb152a5) - - - - - 7d6dd57a by John Ericson at 2021-01-22T22:02:02+00:00 Add `NoGhcTc` instance now that it's not closed - - - - - e5fdaf0a by Alan Zimmerman at 2021-01-23T22:57:44+00:00 Merge pull request haskell/haddock#1293 from obsidiansystems/wip/fix-18936 Add `NoGhcTc` instance now that it's not closed - - - - - 989a1e05 by Oleg Grenrus at 2021-01-24T16:11:46+03:00 Add import list to Data.List - - - - - 368e144a by Ben Gamari at 2021-01-28T22:15:48+01:00 Adapt to "Make PatSyn immutable" - - - - - abe66c21 by Alfredo Di Napoli at 2021-02-01T08:05:35+01:00 Rename pprLogErrMsg to new name - - - - - e600e75c by Hécate Moonlight at 2021-02-05T14:53:00+01:00 Move CI to ghc-9.0 - - - - - dd492961 by Vladislav Zavialov at 2021-02-05T14:53:00+01:00 Update cabal.project and README build instructions - - - - - 31bd292a by Hécate Moonlight at 2021-02-05T15:03:56+01:00 Merge pull request haskell/haddock#1296 from Kleidukos/ghc-9.0 Merge the late additions to ghc-8.10 into ghc-9.0 - - - - - 6388989e by Vladislav Zavialov at 2021-02-05T17:41:57+03:00 Cleanup: fix build warnings - - - - - f99407ef by Daniel Rogozin at 2021-02-05T18:11:48+03:00 type level characters support for haddock (required for haskell/haddock#11342) - - - - - d8c6b26f by Hécate Moonlight at 2021-02-05T17:44:50+01:00 Add a CONTRIBUTING.md file - - - - - 6a01ad98 by Hécate Moonlight at 2021-02-05T17:58:16+01:00 Merge pull request haskell/haddock#1312 from Kleidukos/proper-branch-etiquette Add a CONTRIBUTING.md file - - - - - 955eecc4 by Vladislav Zavialov at 2021-02-05T20:29:00+03:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into ghc-head - - - - - 47b3d6ab by Hécate Moonlight at 2021-02-05T19:09:38+01:00 Amend the CONTRIBUTING.md file - - - - - 23de6137 by Hécate Moonlight at 2021-02-05T19:16:49+01:00 Merge pull request haskell/haddock#1313 from Kleidukos/amend-contributing Amend the CONTRIBUTING.md file - - - - - 69026b59 by Krzysztof Gogolewski at 2021-02-05T23:05:56+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. (cherry picked from commit b4b4d896d2d68d6c48e7db7bfe95c185ca0709cb) - - - - - ea026b78 by Oleg Grenrus at 2021-02-06T17:14:45+01:00 Add import list to Data.List - - - - - 5204326f by Hécate Moonlight at 2021-02-06T17:15:44+01:00 Merge pull request haskell/haddock#1316 from Kleidukos/explicit-imports-to-data-list Add import list to Data.List - - - - - 1f4d2136 by Ben Gamari at 2021-02-06T11:53:31-05:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ghc-head-merge - - - - - 13f0d09a by Ben Gamari at 2021-02-06T11:53:45-05:00 Fix partial record selector warning - - - - - 5c115f7e by Ben Gamari at 2021-02-06T11:55:52-05:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into wip/ghc-head-merge - - - - - b6fd8b75 by Ben Gamari at 2021-02-06T12:01:31-05:00 Merge commit '41964cb2fd54b5a10f8c0f28147015b7d5ad2c02' into wip/ghc-head-merge - - - - - a967194c by Ben Gamari at 2021-02-06T18:30:35-05:00 Merge branch 'wip/ghc-head-merge' into ghc-head - - - - - 1f4c3a91 by MorrowM at 2021-02-07T01:52:33+02:00 Fix search div not scrolling - - - - - 684b1287 by Iñaki García Etxebarria at 2021-02-07T16:13:04+01:00 Add support for labeled module references Support a markdown-style way of annotating module references. For instance -- | [label]("Module.Name#anchor") will create a link that points to the same place as the module reference "Module.Name#anchor" but the text displayed on the link will be "label". - - - - - bdb55a5d by Hécate Moonlight at 2021-02-07T16:18:10+01:00 Merge pull request haskell/haddock#1319 from alexbiehl/alex/compat Backward compat: Add support for labeled module references - - - - - 6ca70991 by Hécate Moonlight at 2021-02-07T16:21:29+01:00 Merge pull request haskell/haddock#1314 from tweag/show-linear-backport Backport haskell/haddock#1238 (linear types) to ghc-9.0 - - - - - d9d73298 by Alex Biehl at 2021-02-07T17:46:25+01:00 Remove dubious parseModLink Instead construct the ModLink value directly when parsing. - - - - - 33b4d020 by Hécate Moonlight at 2021-02-07T17:52:05+01:00 Merge pull request haskell/haddock#1320 from haskell/alex/fix Remove dubious parseModLink - - - - - 54211316 by Hécate Moonlight at 2021-02-07T18:12:07+01:00 Merge pull request haskell/haddock#1318 from MorrowM/ghc-9.0 Fix search div not scrolling - - - - - 19db679e by alexbiehl-gc at 2021-02-07T18:14:46+01:00 Merge pull request haskell/haddock#1317 from bgamari/wip/ghc-head-merge Merge ghc-8.10 into ghc-head - - - - - 6bc1e9e4 by Willem Van Onsem at 2021-02-07T18:25:30+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - c8537cf8 by alexbiehl-gc at 2021-02-07T18:30:40+01:00 Merge pull request haskell/haddock#1322 from haskell/alex/forward-port simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 2d47ae4e by alexbiehl-gc at 2021-02-07T18:39:59+01:00 Merge branch 'ghc-head' into ghc-9.0 - - - - - 849e4733 by Hécate Moonlight at 2021-02-07T18:43:19+01:00 Merge pull request haskell/haddock#1321 from Kleidukos/ghc-9.0 Merge ghc-9.0 into ghc-head - - - - - ee6095d7 by Sylvain Henry at 2021-02-08T11:36:38+01:00 Update for Logger - - - - - 4ad688c9 by Alex Biehl at 2021-02-08T18:11:24+01:00 Merge pull request haskell/haddock#1310 from hsyl20/wip/hsyl20/logger2 Logger refactoring - - - - - 922a9e0e by Ben Gamari at 2021-02-08T12:54:33-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - 991649d2 by Sylvain Henry at 2021-02-09T10:55:17+01:00 Fix to build with HEAD - - - - - a8348dc2 by Hécate Moonlight at 2021-02-09T10:58:51+01:00 Merge pull request haskell/haddock#1327 from hsyl20/wip/hsyl20/logger2 Fix to build with HEAD - - - - - 0abdbca6 by Fendor at 2021-02-09T20:06:15+01:00 Add UnitId to Target record - - - - - d5790a0e by Alex Biehl at 2021-02-11T10:32:32+01:00 Stable sort for (data/newtype) instances - - - - - 8e6036f5 by Alex Biehl at 2021-02-11T10:32:32+01:00 Also make TyLit deterministic - - - - - f76d2945 by Hécate Moonlight at 2021-02-11T11:00:31+01:00 Merge pull request haskell/haddock#1329 from hsyl20/hsyl20/stabe_iface Stable sort for instances - - - - - 5e0469ea by Oleg Grenrus at 2021-02-14T15:28:15+02:00 Add import list to Data.List in Haddock.Interface.Create - - - - - fa57cd24 by Hécate Moonlight at 2021-02-14T17:19:27+01:00 Merge pull request haskell/haddock#1331 from phadej/more-explicit-data-list-imports Add import list to Data.List in Haddock.Interface.Create - - - - - f0cd629c by Hécate Moonlight at 2021-02-21T00:22:01+01:00 Merge pull request haskell/haddock#1311 from fendor/wip/add-targetUnitId-to-target Add UnitId to Target record - - - - - 674ef723 by Joachim Breitner at 2021-02-22T10:39:18+01:00 html-test: Always set language from ghc-9.2 on, the “default” langauge of GHC is expected to change more wildly. To prepare for that (and unblock https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4853), this sets the language for all the test files to `Haskell2010`. This should insolate this test suite against changes to the default. Cherry-picked from https://github.com/haskell/haddock/pull/1341 - - - - - f072d623 by Hécate Moonlight at 2021-02-22T10:56:51+01:00 Merge pull request haskell/haddock#1342 from nomeata/joachim/haskell2010-in-tests-ghc-head html-test: Always set language - - - - - caebbfca by Hécate Moonlight at 2021-02-22T11:53:07+01:00 Clean-up of Interface and Interface.Create's imports and pragmata - - - - - f6caa89d by Hécate Moonlight at 2021-02-22T11:54:58+01:00 Merge pull request haskell/haddock#1345 from Kleidukos/head/fix-interface-imports [ghc-head] Clean-up of Interface and Interface.Create's imports and pragmata - - - - - 7395c9cb by Hécate Moonlight at 2021-02-22T18:44:57+01:00 Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 6e9fb5d5 by Hécate Moonlight at 2021-02-22T18:45:28+01:00 Merge pull request haskell/haddock#1348 from Kleidukos/head/explicit-imports-interface Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 9198b118 by Alan Zimmerman at 2021-02-22T20:04:24+00:00 Context becomes a Maybe in the GHC AST This prevents noLoc's appearing in the ParsedSource. Match the change in GHC. - - - - - 0af20f64 by Hécate Moonlight at 2021-02-23T12:36:12+01:00 Fix the call-site of guessTarget in Interface.hs Explicit the imports from GHC.HsToCore.Docs - - - - - b7886885 by Hécate Moonlight at 2021-02-23T12:37:54+01:00 Merge pull request haskell/haddock#1349 from Kleidukos/fix-interface-guesstarget-call Fix the call-site of guessTarget in Interface.hs - - - - - 9cf041ba by Sylvain Henry at 2021-02-24T11:08:20+01:00 Fix haddockHypsrcTest output in ghc-head - - - - - b194182a by Hécate Moonlight at 2021-02-24T11:12:36+01:00 Merge pull request haskell/haddock#1351 from hsyl20/wip/hsyl20/fix-head Fix haddockHypsrcTest output in ghc-head - - - - - 3ce8b375 by Shayne Fletcher at 2021-03-06T09:55:03-05:00 Add ITproj to parser - - - - - d2abf762 by Ben Gamari at 2021-03-06T19:26:49-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a0f6047d by Andrew Martin at 2021-03-07T11:25:23-05:00 Update for boxed rep - - - - - 6f63c99e by Ben Gamari at 2021-03-10T13:20:21-05:00 Update for "FastString: Use FastMutInt instead of IORef Int" - - - - - e13f01df by Luke Lau at 2021-03-10T15:38:40-05:00 Implement template-haskell's putDoc This catches up to GHC using the new extractTHDocs function, which returns documentation added via the putDoc function (provided it was compiled with Opt_Haddock). Since it's already a map from names -> docs, there's no need to do traversal etc. It also matches the change from the argument map being made an IntMap rather than a Map Int - - - - - 89263d94 by Alan Zimmerman at 2021-03-15T17:15:26+00:00 Match changes in GHC AST for in-tree API Annotations As landed via https://gitlab.haskell.org/ghc/ghc/-/merge_requests/2418 - - - - - 28db1934 by Alan Zimmerman at 2021-03-15T20:40:09+00:00 Change some type family test results. It is not clear to me whether the original was printing incorrectly (since we did not have the TopLevel flag before now), or if this behaviour is expected. For the time being I am assuming the former. - - - - - 7c11c989 by Sylvain Henry at 2021-03-22T10:05:19+01:00 Fix after NameCache changes - - - - - addbde15 by Sylvain Henry at 2021-03-22T10:05:19+01:00 NameCache doesn't store a UniqSupply anymore - - - - - 15ec6cec by Ben Gamari at 2021-03-22T17:53:44-04:00 Bump GHC version to 9.2 - - - - - dbd6aa63 by Hécate Moonlight at 2021-03-24T14:28:36+01:00 Merge pull request haskell/haddock#1365 from hsyl20/wip/hsyl20/iface1 NameCache refactoring - - - - - 2d32da7e by Oleg Grenrus at 2021-03-27T01:12:00+02:00 Specialization of Data.List - - - - - 32b84fa6 by Fendor at 2021-03-27T10:50:17+01:00 Add UnitId to Target record This way we always know to which home-unit a given target belongs to. So far, there only exists a single home-unit at a time, but it enables having multiple home-units at the same time. - - - - - 54bf9f0e by Hécate Moonlight at 2021-03-28T14:08:35+02:00 Merge pull request haskell/haddock#1368 from fendor/target-unit-id-revert Add UnitId to Target record - - - - - 7dea168a by Alan Zimmerman at 2021-03-29T08:45:52+01:00 EPA : Rename ApiAnn to EpAnn - - - - - 72967f65 by Alfredo Di Napoli at 2021-03-29T09:47:01+02:00 pprError changed name in GHC - - - - - 4bc61035 by Alan Zimmerman at 2021-03-29T16:16:27-04:00 EPA : Rename ApiAnn to EpAnn - - - - - 108d031d by Ben Gamari at 2021-03-29T18:49:36-04:00 Merge commit '36418c4f70d7d2b179a77925b3ad5caedb08c9b5' into HEAD - - - - - 1444f700 by Ben Gamari at 2021-03-31T09:18:39-04:00 Merge pull request haskell/haddock#1370 from adinapoli/wip/adinapoli-diag-reason-severity Rename pprError to mkParserErr - - - - - d3087b79 by Ben Gamari at 2021-03-31T11:34:17-04:00 Merge commit 'd8d8024ad6796549a8d3b5512dabf3288d14e30f' into ghc-head - - - - - 170b79e9 by Ben Gamari at 2021-03-31T12:24:56-04:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - db0d6bae by Ben Gamari at 2021-04-10T09:34:35-04:00 Bump GHC version to 9.3 - - - - - a9f2c421 by Alan Zimmerman at 2021-04-19T18:26:46-04:00 Update for EPA changes in GHC (cherry picked from commit cafb48118f7c111020663776845897e225607b41) - - - - - 1ee4b7c7 by Sylvain Henry at 2021-05-11T10:00:06+02:00 Removal of HsVersions.h (#1388) * Update for EPA changes in GHC * Account for HsVersions.h removal Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 79e819e9 by Hécate Moonlight at 2021-05-11T10:14:47+02:00 Revert "Removal of HsVersions.h (#1388)" This reverts commit 72118896464f94d81f10c52f5d9261efcacc57a6. - - - - - 3dbd3f8b by Alan Zimmerman at 2021-05-11T10:15:17+02:00 Update for EPA changes in GHC - - - - - 2ce80c17 by Sylvain Henry at 2021-05-11T10:15:19+02:00 Account for HsVersions.h removal - - - - - 00e4c918 by Christiaan Baaij at 2021-05-13T08:21:56+02:00 Add Haddock support for the OPAQUE pragma (#1380) - - - - - 8f9049b2 by Hécate Moonlight at 2021-05-13T08:40:22+02:00 fixup! Use GHC 9.2 in CI runner - - - - - 27ddec38 by Alan Zimmerman at 2021-05-13T22:51:20+01:00 EPA: match changes from GHC T19834 - - - - - f8a1d714 by Felix Yan at 2021-05-14T17:10:04+02:00 Allow hspec 2.8 (#1389) All tests are passing. - - - - - df44453b by Divam Narula at 2021-05-20T15:42:42+02:00 Update ref, the variables got renamed. (#1391) This is due to ghc/ghc!5555 which caused a change in ModDetails in case of NoBackend. Now the initModDetails is used to recreate the ModDetails from interface and in-memory ModDetails is not used. - - - - - e46bfc87 by Alan Zimmerman at 2021-05-20T19:05:09+01:00 Remove Maybe from HsQualTy Match changes in GHC for haskell/haddock#19845 - - - - - 79bd7b62 by Shayne Fletcher at 2021-05-22T08:20:39+10:00 FieldOcc: rename extFieldOcc to foExt - - - - - 6ed68c74 by Ben Gamari at 2021-05-21T22:29:30-04:00 Merge commit '3b6a8774bdb543dad59b2618458b07feab8a55e9' into ghc-head - - - - - f9a02d34 by Alfredo Di Napoli at 2021-05-24T13:53:00+02:00 New Parser diagnostics interface - - - - - 392807d0 by Ben Gamari at 2021-05-24T09:57:40-04:00 Merge pull request haskell/haddock#1394 from adinapoli/wip/adinapoli-align-ps-messages Align Haddock to use the new Parser diagnostics interface - - - - - 33023cd8 by Ben Gamari at 2021-05-24T11:19:16-04:00 Revert "Add Haddock support for the OPAQUE pragma (#1380)" This reverts commit a1337c599ef7720b0482a25c55f11794112496dc. The GHC patch associated with this change is not yet ready to be merged. - - - - - 8c005af7 by Ben Simms at 2021-05-28T07:56:20+02:00 CI configuration for ghc-head (#1395) - - - - - 1e947612 by Hécate Moonlight at 2021-05-28T12:27:35+02:00 Use GHC 9.2 in CI runner (#1378) - - - - - e6fa10ab by CGenie at 2021-05-31T09:02:13+02:00 Add page about common errors (#1396) * Update index.rst Common errors page * Create common-errors.rst * Update common-errors.rst * Use GHC 9.2 in CI runner (#1378) * [haddock-api] remove .hspec-failures Co-authored-by: Hécate Moonlight <Kleidukos at users.noreply.github.com> - - - - - abc72a8d by Sylvain Henry at 2021-06-01T10:02:06+02:00 Adapt Haddock to Logger and Parser changes (#1399) - - - - - 91373656 by Zubin Duggal at 2021-06-01T20:45:10+02:00 Update haddockHypSrc tests since we now compute slighly more type info (#1397) - - - - - ed712822 by Marcin Szamotulski at 2021-06-02T08:54:33+02:00 Added myself to contributors - - - - - 49fdbcb7 by Marcin Szamotulski at 2021-06-02T08:57:24+02:00 Document multi component support - - - - - 9ddc8d7d by Hécate Moonlight at 2021-06-02T09:35:55+02:00 Merge pull request haskell/haddock#1379 from coot/coot/document-multi-component-support Document multi component support - - - - - 585b5c5e by Ben Simms at 2021-06-02T19:46:54+02:00 Update CONTRIBUTING.md (#1402) - - - - - 1df4a605 by Ben Simms at 2021-06-02T19:47:14+02:00 Update CONTRIBUTING.md (#1403) - - - - - 58ea43d2 by sheaf at 2021-06-02T22:09:06+02:00 Update Haddock Bug873 to account for renaming - - - - - c5d0ab23 by Vladislav Zavialov at 2021-06-10T13:35:42+03:00 HsToken in FunTy, RecConGADT - - - - - 1ae2f40c by Hécate Moonlight at 2021-06-11T11:19:09+02:00 Update the CI badges - - - - - 6fdc4de2 by Sylvain Henry at 2021-06-28T19:21:17+02:00 Fix mkParserOpts (#1411) - - - - - 18201670 by Alfredo Di Napoli at 2021-07-05T07:55:12+02:00 Rename getErrorMessages Lexer import This commit renames the Lexer import in `Hyperlinker.Parser` from `getErrorMessages` to `getPsErrorMessages` to eliminate the ambiguity with the `getErrorMessages` function defined in `GHC.Types.Error`. - - - - - 23173ca3 by Ben Gamari at 2021-07-07T11:31:44-04:00 Merge pull request haskell/haddock#1413 from adinapoli/wip/adinapoli-issue-19920 Rename getErrorMessages Lexer import - - - - - b3dc4ed8 by Alan Zimmerman at 2021-07-28T22:30:59+01:00 EPA: match changes from GHC T19834 (cherry picked from commit 2fec1b44e0ee7e263286709aa528b4ecb99ac6c2) - - - - - 5f177278 by Ben Gamari at 2021-08-06T01:17:37-04:00 Merge commit '2a966c8ca37' into HEAD - - - - - cdd81d08 by Marcin Szamotulski at 2021-08-08T17:19:06+02:00 coot/multiple packages (ghc-9.2) (#1418) - - - - - be0d71f1 by Marcin Szamotulski at 2021-08-16T08:46:03+02:00 coot/multiple package (ghc-head) (#1419) * FromJSON class Aeson style FromJSON class with Parsec based json parser. * doc-index.json file for multiple packages When creating haddock summary page for multiple packages render doc-index.json file using contents of all found 'doc-index.json' files. * Render doc-index.json When rendering html, render doc-index.json file independently of maybe_index_url option. doc-index.json file is useful now even if maybe_index_url is not `Nothing`. * base url option New `Flag_BaseURL` which configures from where static files are loaded (--base-url). If given and not equal "." static files are not coppied, as this indicates that they are not read from the the directory where we'd copy them. The default value is ".". - - - - - 3b09dbdf by Hécate Moonlight at 2021-10-07T23:26:03+02:00 Update GHC 9.2 to latest pre-release in CI - - - - - 7ac55417 by Zubin Duggal at 2021-10-11T12:10:19+02:00 Enable Haddock tests in GHC windows CI (#1428) * testsuite: strip windows line endings for haddock * hyperlinker: Work around double escaping (#19236) * deterministic SCC - - - - - 1cb81f25 by Andrew Lelechenko at 2021-10-12T15:23:19+02:00 haddock-library does not depend on bytestring or transformers (#1426) - - - - - a890b9aa by sheaf at 2021-10-15T22:19:42+02:00 update haddockHypsrcTest for GHC MR !6705 (#1430) - - - - - 42a55c6c by Sylvain Henry at 2021-10-15T22:20:10+02:00 Fix after PkgQual refactoring (#1429) - - - - - 91659238 by Alan Zimmerman at 2021-10-28T18:57:10+01:00 Update for changes in GHC for branch wip/az/no-srcspan-anno-instances - - - - - acf23e60 by Vladislav Zavialov at 2021-11-05T02:09:47+03:00 Do not use forall as an identifier See GHC ticket haskell/haddock#20609 - - - - - c565db0e by Krzysztof Gogolewski at 2021-11-27T02:42:35+01:00 Update after NoExtCon -> DataConCantHappen rename - - - - - b5f55590 by Artem Pelenitsyn at 2021-11-27T11:14:17+01:00 fix CI for 9.2 (#1436) - - - - - 25cd621e by Matthew Pickering at 2021-12-02T11:46:54+00:00 Update html-test for Data.List revert - - - - - 1d5ff85f by malteneuss at 2021-12-15T07:56:55+01:00 Add hint about inline link issue (#1444) - - - - - 791fde81 by Sylvain Henry at 2021-12-16T09:29:51+01:00 Bump ghc-head (#1445) * Update after NoExtCon -> DataConCantHappen rename * Update html-test for Data.List revert * Fix for new Plugins datatype Co-authored-by: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 44236317 by Sylvain Henry at 2021-12-17T09:39:00+01:00 Fix for new Plugins datatype - - - - - 80ada0fa by Hécate Moonlight at 2021-12-17T17:28:48+01:00 Remove ghc-head workflow (#1446) Contributions of GHC glue code are now done on the GHC gitlab, not in the GitHub repo anymore. - - - - - 49e171cd by Matthew Pickering at 2021-12-28T09:47:09+00:00 Remove use of ExtendedModSummary - - - - - 0e91b5ea by askeblad at 2022-01-04T09:18:35+01:00 update URLs - - - - - 9f13c212 by Hécate Moonlight at 2022-02-25T10:19:46+01:00 Fix solver for GHC 9.2 - - - - - 386751a1 by Meng Weng Wong at 2022-02-25T19:19:11+01:00 IDoc link has bitrotted; replaced with web.archive.org cache. (#1454) - - - - - d877cbe6 by Hécate Moonlight at 2022-02-25T19:21:58+01:00 Fix haddock user guide (#1456) - - - - - cc47f036 by Andrew Lelechenko at 2022-03-04T17:29:36+01:00 Allow text-2.0 in haddock-library (#1459) - - - - - 7b3685a3 by malteneuss at 2022-03-07T19:27:24+01:00 Add multi-line style hint to style section (#1460) - - - - - c51088b8 by John Ericson at 2022-03-11T16:46:26+01:00 Fix CollectPass instance to match TTG refactor Companion to GHC !7614 (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7614) - - - - - b882195b by Vladislav Zavialov at 2022-03-14T20:32:30+01:00 Link to (~) - - - - - 877349b8 by Christiaan Baaij at 2022-03-16T09:20:43+01:00 Add Haddock support for the OPAQUE pragma - - - - - 0ea22721 by askeblad at 2022-03-16T09:44:27+01:00 typos (#1464) - - - - - a6d13da1 by Matthew Pickering at 2022-03-22T13:41:17+00:00 Minimum changes needed for compilation with hi-haddock With hi-haddock, of course there is a much large refactoring of haddock which could be achieved but that is left for a future patch which can implemented at any time independently of GHC. - - - - - e7ac9129 by Matthew Pickering at 2022-03-22T21:17:50+00:00 Update test output - - - - - 6d916214 by Matthew Pickering at 2022-03-24T15:06:26+00:00 Merge branch 'wip/opaque_pragma' into 'ghc-head' Add Haddock support for the OPAQUE pragma See merge request ghc/haddock!2 - - - - - 42208183 by Steve Hart at 2022-03-25T20:43:50+01:00 Fix CI (#1467) * CI: Reinstall GHC with docs CI tests were failing because the GHC preinstalled to the CI environment does not include documentation, which is required for running the Haddock tests. This commit causes the CI workflow to reinstall GHC with docs so that tests can succeed. - - - - - 9676fd79 by Steve Hart at 2022-03-25T21:33:34+01:00 Make links in Synopsis functional again (#1458) Commit e41c1cbe9f0476997eac7b4a3f17cbc6b2262faf added a call to e.preventDefault() when handling click events that reach a toggle element. This prevents the browser from following hyperlinks within the Synopsis section when they are clicked by a user. This commit restores functioning hyperlinks within the Synopsis section by removing the call to e.preventDefault(), as it does not appear to be necessary, and removing it increases the flexibility of the details-helper code. - - - - - d1edd637 by sheaf at 2022-04-01T12:02:02+02:00 Keep track of promotion ticks in HsOpTy Keeping track of promotion ticks in HsOpTy allows us to properly pretty-print promoted constructors such as lists. - - - - - 9dcb2dfc by Jakob Brünker at 2022-04-01T15:46:22+00:00 Add support for \cases See merge request ghc/ghc!7873 - - - - - b0412ee5 by askeblad at 2022-04-06T17:47:57+02:00 spelling errors (#1471) - - - - - 6b18829b by Vladislav Zavialov at 2022-04-06T18:53:58+02:00 Rename [] to List - - - - - 2d046691 by Vladislav Zavialov at 2022-04-07T20:25:54+03:00 HsToken ConDeclGADT con_dcolon - - - - - 90b43da4 by Steve Hart at 2022-04-12T13:29:46+02:00 Parse Markdown links at beginning of line within a paragraph (#1470) * Catch Markdown links at beginning of line within paragraph Per Issue haskell/haddock#774, Markdown links were being parsed as ordinary text when they occurred at the beginning of a line other than the first line of the paragraph. This occurred because the parser was not interpreting a left square bracket as a special character that could delimit special markup. A space character was considered a special character, so, if a space occurred at the beginning of the new line, then the parser would interpret the space by itself and then continue parsing, thereby catching the Markdown link. '\n' was not treated as a special character, so the parser did not catch a Markdown link that may have followed. Note that this will allow for Markdown links that are not surrounded by spaces. For example, the following text includes a Markdown link that will be parsed: Hello, world[label](url) This is consistent with how the parser handles other types of markup. * Remove obsolete documentation hint Commit 6b9aeafddf20efc65d3725c16e3fc43a20aac343 should eliminate the need for the workaround suggested in the documentation. - - - - - 5b08312d by Hécate Moonlight at 2022-04-12T13:36:38+02:00 Force ghc-9.2 in the cabal.project - - - - - 0d0ea349 by dependabot[bot] at 2022-04-12T13:57:41+02:00 Bump path-parse from 1.0.5 to 1.0.7 in /haddock-api/resources/html (#1469) Bumps [path-parse](https://github.com/jbgutierrez/path-parse) from 1.0.5 to 1.0.7. - [Release notes](https://github.com/jbgutierrez/path-parse/releases) - [Commits](https://github.com/jbgutierrez/path-parse/commits/v1.0.7) --- updated-dependencies: - dependency-name: path-parse dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 2b9fc65e by dependabot[bot] at 2022-04-12T13:57:54+02:00 Bump copy-props from 2.0.4 to 2.0.5 in /haddock-api/resources/html (#1468) Bumps [copy-props](https://github.com/gulpjs/copy-props) from 2.0.4 to 2.0.5. - [Release notes](https://github.com/gulpjs/copy-props/releases) - [Changelog](https://github.com/gulpjs/copy-props/blob/master/CHANGELOG.md) - [Commits](https://github.com/gulpjs/copy-props/compare/2.0.4...2.0.5) --- updated-dependencies: - dependency-name: copy-props dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - ea98a6fb by Ben Gamari at 2022-04-23T22:54:37-04:00 Update for GHC 9.4 - - - - - 9e11864f by Ben Gamari at 2022-04-25T16:24:31-04:00 Merge remote-tracking branch 'upstream/ghc-9.2' into ghc-head - - - - - f83cc506 by Ben Gamari at 2022-04-25T17:00:25-04:00 Bump ghc version to 9.5 - - - - - e01c2e7d by Ben Gamari at 2022-04-28T16:19:04-04:00 Revert "Bump ghc-head (#1445)" This reverts commit b29a78ef6926101338f62e84f456dac8659dc9d2. This should not have been merged. - - - - - a2b5ee8c by Ben Gamari at 2022-04-28T16:19:24-04:00 Merge commit '2627a86c' into ghc-head - - - - - 0c6fe4f9 by Ben Gamari at 2022-04-29T10:05:54-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-9.4 - - - - - b6e5cb0a by Ben Gamari at 2022-04-29T11:46:06-04:00 Revert "HsToken ConDeclGADT con_dcolon" This reverts commit 24208496649a02d5f87373052c430ea4a97842c5. - - - - - 15a62888 by Ben Gamari at 2022-04-29T15:12:55-04:00 Bump base upper bound - - - - - 165b9031 by Ben Gamari at 2022-04-29T23:58:38-04:00 Update test output - - - - - e0c3e5da by Phil de Joux at 2022-05-02T14:46:38+02:00 Add hlint action .hlint.yaml with ignores & CPP. (#1475) - - - - - ead1158d by Raphael Das Gupta at 2022-05-02T14:46:48+02:00 fix grammar in docs: "can the" → "can be" (#1477) - - - - - cff97944 by Ben Gamari at 2022-05-02T18:38:56-04:00 Allow base-4.17 - - - - - e4ecb201 by Phil de Joux at 2022-05-03T13:14:55+02:00 Remove unused imports that GHC warned about. (#1480) - - - - - 222890b1 by Phil de Joux at 2022-05-03T13:15:46+02:00 Follow hlint suggestion to remove redundant bang. (#1479) - - - - - 058b671f by Phil de Joux at 2022-05-03T13:34:04+02:00 Follow hlint, remove language pragmas in libs. (#1478) - - - - - 0a645049 by Ben Simms at 2022-05-03T14:19:24+02:00 Keep track of ordered list indexes and render them (#1407) * Keep track of ordered list indexes and render them * Rename some identifiers to clarify - - - - - f0433304 by Norman Ramsey at 2022-05-04T15:13:34-04:00 update for changes in GHC API - - - - - 3740cf71 by Emily Martins at 2022-05-06T18:23:48+02:00 Add link to the readthedocs in cabal description to show on hackage. (cherry picked from commit 52e2d40d47295c02d3181aac0c53028e730f1e3b) - - - - - 5d754f1e by Hécate Moonlight at 2022-05-06T18:44:57+02:00 remove Bug873 - - - - - 968fc267 by Hécate Moonlight at 2022-05-06T18:48:28+02:00 Ignore "Use second" HLint suggestion. It increases laziness. - - - - - 02d14e97 by Jade Lovelace at 2022-05-07T17:42:08+02:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` - - - - - b22b87ed by Artem Pelenitsyn at 2022-05-08T16:19:47+02:00 fix parsing trailing quotes in backticked identifiers (#1408) (#1483) - - - - - 80ae107b by Alex Biehl at 2022-05-08T16:37:16+02:00 Fix "Defined by not used" error (cherry picked from commit 6e02a620a26c3a44f98675dd1b93b08070c36c0a) - - - - - 4c838e84 by Hécate Moonlight at 2022-05-08T16:37:16+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - fc9827b4 by Hécate Moonlight at 2022-05-08T16:40:40+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - b153b555 by Xia Li-yao at 2022-05-20T17:52:42+02:00 Hide synopsis from search when hidden (#1486) Fix haskell/haddock#1451 - - - - - f3e38b85 by Marcin Szamotulski at 2022-05-21T23:32:31+02:00 Allow to hide interfaces when rendering multiple components (#1487) This is useful when one wishes to `--gen-contents` when rendering multiple components, but one does not want to render all modules. This is in particular useful when adding base package. - - - - - f942863b by Marcin Szamotulski at 2022-05-24T08:29:59+02:00 Check if doc-index.json exists before reading it (#1488) - - - - - 31e92982 by Marcin Szamotulski at 2022-05-25T16:22:13+02:00 Version bump 2.26.1 (#1489) * Version bump 2.26.1 We extended format accepted by `--read-interface` option, which requires updating the minor version. * Update documentation of --read-interface option - - - - - 7cc873e0 by sheaf at 2022-05-25T16:42:31+02:00 Updated HaddockHypsrcTest output for record update changes (MR !7981) - - - - - cd196942 by Marcin Szamotulski at 2022-05-25T20:28:47+02:00 Use visibility to decide which interfaces are included in quickjump (#1490) This is also consistent with how html index is build. See haskell/cabal#7669 for rationale behind this decision. - - - - - 00c713c5 by Hécate Moonlight at 2022-05-26T17:09:15+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 2f3039f1 by Hécate Moonlight at 2022-05-26T17:10:59+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 63a5650c by romes at 2022-05-31T12:43:22+01:00 TTG: Match new GHC AST - - - - - dd7d1617 by romes at 2022-06-02T16:11:00+01:00 Update for IE changes in !8228 - - - - - c23aaab7 by cydparser at 2022-06-06T08:48:14+02:00 Fix and improve CI (#1495) * Pin GHC version before creating the freeze file * Use newest action versions * Improve caching * Avoid unnecessarily reinstalling GHC * Use GHC 9.2.2 for CI Co-authored-by: Cyd Wise <cwise at tripshot.com> - - - - - c156fa77 by Hécate Moonlight at 2022-06-06T11:59:35+02:00 Add Mergify configuration (#1496) - - - - - 2dba4188 by Hécate Moonlight at 2022-06-06T16:12:50+02:00 Bump haddock's version in cabal file to 2.26.1 (#1497) - - - - - d7d4b8b9 by Marcin Szamotulski at 2022-06-07T06:09:40+00:00 Render module tree per package in the content page (#1492) * Render module tree per package in the content page When rendering content page for multiple packages it is useful to split the module tree per package. Package names in this patch are inferred from haddock's interface file names. * Write PackageInfo into interface file To keep interface file format backward compatible, instead of using `Binary` instance for `InterfaceFile` we introduce functions to serialise and deserialise, which depends on the interface file version. - - - - - 77765665 by Mike Pilgrem at 2022-06-12T21:57:19+01:00 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - b0e079b0 by mergify[bot] at 2022-06-13T11:49:37+00:00 Merge pull request haskell/haddock#1108 from mpilgrem/fix783 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - 6c0292b1 by Hécate Moonlight at 2022-06-21T17:21:08+02:00 Update the contribution guide - - - - - e413b9fa by dependabot[bot] at 2022-06-21T23:38:19+02:00 Bump shell-quote from 1.6.1 to 1.7.3 in /haddock-api/resources/html (#1500) Bumps [shell-quote](https://github.com/substack/node-shell-quote) from 1.6.1 to 1.7.3. - [Release notes](https://github.com/substack/node-shell-quote/releases) - [Changelog](https://github.com/substack/node-shell-quote/blob/master/CHANGELOG.md) - [Commits](https://github.com/substack/node-shell-quote/compare/1.6.1...1.7.3) --- updated-dependencies: - dependency-name: shell-quote dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 29d0ef70 by romes at 2022-07-06T11:29:39+02:00 TTG: AST Updates for !8308 - - - - - 1bae7c87 by Alan Zimmerman at 2022-07-06T22:50:43+01:00 Match GHC changes for T21805 This brings in a newtype for FieldLabelString - - - - - 6fe8b988 by Phil de Joux at 2022-07-16T20:54:26+00:00 Bump hlint version to 3.4.1, the version with counts. (#1503) Redo the counts available with the --default option. - - - - - 48fb43af by Phil de Joux at 2022-07-19T09:32:55+02:00 Follow hlint suggestion: unused LANGUAGE pragma. (#1504) * Follow hlint suggestion: unused LANGUAGE pragma. * Ignore within modules to pass linting and pass tests. - - - - - c1cf1fa7 by Phil de Joux at 2022-07-24T13:45:59+02:00 Follow hlint suggestion: redundant $. (#1505) * Follow hlint suggestion: redundant $. * Remove $ and surplus blank lines in Operators. - - - - - 74777eb2 by Jade Lovelace at 2022-07-29T11:02:41+01:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` (cherry picked from commit ab53ccf089ea703b767581ac14be0f6c78a7678a) - - - - - faa4cfcf by Hécate Moonlight at 2022-07-29T20:31:20+02:00 Merge pull request haskell/haddock#1516 from duog/9-4-backport-fix-hyperlinks Backport 9-4: Fix hyperlinks to external items and modules (#1482) - - - - - 5d2450f3 by Ben Gamari at 2022-08-05T17:41:15-04:00 Merge remote-tracking branch 'origin/ghc-9.4' - - - - - 63954f73 by Ben Gamari at 2022-08-05T19:08:36-04:00 Clean up build and testsuite for GHC 9.4 - - - - - d4568cb8 by Hécate Moonlight at 2022-08-05T19:10:49-04:00 Bump the versions - - - - - 505583a4 by Ben Gamari at 2022-08-06T13:58:27-04:00 Merge pull request haskell/haddock#1518 from bgamari/wip/ghc-9.4-merge Merge GHC 9.4 into `main` - - - - - 5706f6a4 by Ben Gamari at 2022-08-06T22:57:21-04:00 html-test: Testsuite changes for GHC 9.4.1 - - - - - 5f2a45a2 by Ben Gamari at 2022-08-15T14:33:05-04:00 doc: Fix a few minor ReST issues Sphinx was complaining about too-short title underlines. - - - - - 220e6410 by Ben Gamari at 2022-08-15T14:41:24-04:00 Merge branch 'main' into ghc-head - - - - - fbeb1b02 by Ben Gamari at 2022-08-15T14:45:16-04:00 Updates for GHC 9.5 - - - - - eee562eb by Vladislav Zavialov at 2022-08-15T14:46:13-04:00 HsToken ConDeclGADT con_dcolon - - - - - c5f073db by Ben Gamari at 2022-08-15T16:55:35-04:00 Updates for GHC 9.5 - - - - - 3f7ab242 by Vladislav Zavialov at 2022-08-15T16:55:35-04:00 HsToken ConDeclGADT con_dcolon - - - - - a18e473d by Ben Gamari at 2022-08-16T08:35:19-04:00 Merge branch 'wip/ghc-head-bump' into ghc-head - - - - - af0ff3a4 by M Farkas-Dyck at 2022-09-15T21:16:05+00:00 Disuse `mapLoc`. - - - - - a748fc38 by Matthew Farkas-Dyck at 2022-09-17T10:44:18+00:00 Scrub partiality about `NewOrData`. - - - - - 2758fb6c by John Ericson at 2022-09-18T03:27:37+02:00 Test output changed because of change to `base` Spooky, but I guess that is intended? - - - - - a7eec128 by Torsten Schmits at 2022-09-21T11:06:55+02:00 update tests for the move of tuples to GHC.Tuple.Prim - - - - - 461e7b9d by Ross Paterson at 2022-09-24T22:01:25+00:00 match implementation of GHC proposal haskell/haddock#106 (Define Kinds Without Promotion) - - - - - f7fd77ef by sheaf at 2022-10-17T14:53:01+02:00 Update Haddock for GHC MR !8563 (configuration of diagnostics) - - - - - 3d3e85ab by Vladislav Zavialov at 2022-10-22T23:04:06+03:00 Class layout info - - - - - cbde4cb0 by Simon Peyton Jones at 2022-10-25T23:19:18+01:00 Adapt to Constraint-vs-Type See haskell/haddock#21623 and !8750 - - - - - 7108ba96 by Tom Smeding at 2022-11-01T22:33:23+01:00 Remove outdated footnote about module re-exports The footnote is invalid with GHC 9.2.4 (and possibly earlier): the described behaviour in the main text works fine. - - - - - 206c6bc7 by Hécate Moonlight at 2022-11-01T23:00:46+01:00 Merge pull request haskell/haddock#1534 from tomsmeding/patch-1 - - - - - a57b4c4b by Andrew Lelechenko at 2022-11-21T00:39:52+00:00 Support mtl-2.3 - - - - - e9d62453 by Simon Peyton Jones at 2022-11-25T13:49:12+01:00 Track small API change in TyCon.hs - - - - - eb1c73f7 by Ben Gamari at 2022-12-07T08:46:21-05:00 Update for GhC 9.6 - - - - - 063268dd by Ben Gamari at 2022-12-07T11:26:32-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 4ca722fe by Ben Gamari at 2022-12-08T14:43:26-05:00 Bump bounds to accomodate base-4.18 - - - - - 340b7511 by Vladislav Zavialov at 2022-12-10T12:31:28+00:00 HsToken in HsAppKindTy - - - - - 946226ec by Ben Gamari at 2022-12-13T20:12:56-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - fd8faa66 by Ben Gamari at 2022-12-22T13:44:28-05:00 Bump GHC version to 9.7 - - - - - 2958aa9c by Ben Gamari at 2022-12-22T14:49:16-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 9e0fefd8 by Andrei Borzenkov at 2023-01-30T14:02:04+04:00 Rename () to Unit, Rename (,,...,,) to Tuple<n> - - - - - eb3968b5 by Ben Gamari at 2023-03-10T02:32:43-05:00 Bump versions for ghc-9.6 release - - - - - 4aeead36 by Adam Gundry at 2023-03-23T13:53:47+01:00 Adapt to warning categories changes - - - - - 642d8d60 by sheaf at 2023-03-29T13:35:56+02:00 Adapt to record field refactor This commit adapts to the changes in GHC MR !8686, which overhauls the treatment of record fields in the renamer, adding separate record field namespaces and entirely removing the GreName datatype. - - - - - ac8d4333 by doyougnu at 2023-03-29T11:11:44-04:00 Update UniqMap API - - - - - 7866fc86 by Ben Orchard at 2023-04-20T11:29:33+02:00 update classify with new tokens - - - - - ffcdd683 by Finley McIlwaine at 2023-04-24T09:36:18-06:00 Remove index-state - - - - - 05b70982 by Finley McIlwaine at 2023-04-26T08:16:31-06:00 `renameInterface` space leak fixes - Change logic for accumulation of names for which link warnings will be generated - Change handling of `--ignore-link-symbol` to allow qualified and unqualified names. Added to CHANGES.md - Some formatting changes and comments here and there - - - - - e5697d7c by Finley McIlwaine at 2023-04-27T18:46:36-06:00 Messy things - ghc-debug dependency and instrumentation - cabal.project custom with-compiler - hie.yaml files - traces and such - - - - - 0b8ef80b by Finley McIlwaine at 2023-05-02T18:08:52-06:00 Stop retaining GRE closures GRE closures should never be necessary to Haddock, so we never want to keep them on the heap. Despite that, they are retained by a lot of the data structures that Haddock makes use of. - Attempt to fix that situation by adding strictness to various computations and pruning the `ifaceInstances` field of `Interface` to a much thinner data type. - Removes the `ifaceFamInstances` field, as it was never used. - Move some of the attach instances types (e.g. `SimpleType`) to the types module - - - - - 8bda991b by Finley McIlwaine at 2023-05-08T16:07:51-06:00 Memory usage fixes - Refactor `ifaceDeclMap` to drastically reduce memory footprint. We no longer store all declarations associated with a given name, since we only cared to determine if the only declaration associated with a name was a value declaration. Change the `DeclMap` type to better reflect this. - Drop pre-renaming export items after the renaming step. Since the Hoogle backend used the pre-renamed export items, this isn't trivial. We now generate Hoogle output for exported declarations during the renaming step (if Hoogle output /should/ be generated), and store that with the renamed export item. - Slightly refactor Hoogle backend to handle the above change and allow for early generation of Hoogle output. - Remove the `ifaceRnDocMap` and `ifaceRnArgMap` fields of the `Interface` type, as they were never used. - Remove some unnecessary strictness - Remove a lot of dead code from `Syb` module - - - - - 1611ac0c by Finley McIlwaine at 2023-05-09T11:51:57-06:00 Unify ErrMsgM and IfM - Delete ErrMsgM, stop accumulating warnings in a writer - Make IfM a state monad, print warnings directly to stdout, move IfM type into types module - Drop ErrMsg = String synonym - Unset IORefs from plugin after they are read, preventing unnecessary retention of interfaces - - - - - 42d696ab by Finley McIlwaine at 2023-05-11T15:52:07-06:00 Thunk leak fixes The strictness introduced in this commit was motivated by observing thunk leaks in the eventlog2html output. - Refactor attach instances list comprehension to avoid large intermediate thunks - Refactor some HTML backend list comprehensions to avoid large intermediate thunks - Avoid thunks accumulating in documentation types or documentation parser - A lot of orphan NFData instances to allow us to force documentation values - - - - - 68561cf6 by Finley McIlwaine at 2023-05-11T17:02:10-06:00 Remove GHC debug dep - - - - - 10519e3d by Finley McIlwaine at 2023-05-15T12:40:48-06:00 Force HIE file path Removes a potential retainer of `ModSummary`s - - - - - 1e4a6ec6 by Finley McIlwaine at 2023-05-15T14:20:34-06:00 Re-add index-state, with-compiler, delete hie.yamls - - - - - a2363fe9 by Hécate Moonlight at 2023-05-15T22:45:16+02:00 Merge pull request haskell/haddock#1594 from FinleyMcIlwaine/finley/ghc-9.6-mem-fixes Reduce memory usage - - - - - e8a78383 by Finley McIlwaine at 2023-05-17T12:19:16-06:00 Merge branch ghc-9.6 into ghc-head - - - - - 22e25581 by Finley McIlwaine at 2023-05-17T12:20:23-06:00 Merge branch 'ghc-head' of gitlab.haskell.org:ghc/haddock into ghc-head - - - - - 41bbf0df by Bartłomiej Cieślar at 2023-05-24T08:57:58+02:00 changes to the WarningTxt cases Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - c686ba9b by Hécate Moonlight at 2023-06-01T14:03:02-06:00 Port the remains of Hi-Haddock - - - - - 9d8a85fd by Hécate Moonlight at 2023-06-01T14:03:06-06:00 Stdout for tests - - - - - 36331d07 by Finley McIlwaine at 2023-06-01T14:06:02-06:00 Formatting, organize imports - - - - - a06059b1 by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix empty context confusion in Convert module - - - - - 379346ae by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix associated type families in Hoogle output - - - - - fc6ea7ed by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix test refs Accept several changes in Hoogle tests: Pretty printing logic no longer prints the `(Proxy (Proxy (...))` chain in Bug806 with parentheses. Since this test was only meant to verify that line breaks do not occur, accept the change. `tyThingToLHsDecl` is called for class and data declarations, which ends up "synifying" the type variables and giving unlifted types kind signatures. As a result, type variables of kind `Type -> Type` are now printed with kind signatures in Hoogle output. This could be changed by manually drop kind signatures from class variables in the Hoogle backend if the behavior is deemed unacceptable. Sometimes subordinate declarations are exported separate from their parent declarations (e.g. record selectors). In this case, a type signature is cobbled together for the export item in `extractDecl`. Since this type signature is very manually constructed, it may lack kind signatures of decls constructed from `tyThingToLHsDecl`. An example of this is the `type-sigs` Hoogle test. Change `*` to `Type` in Hoogle test refs. I don't think this will break Hoogle behavior, since it appears to not consider type signatures in search. I have not fully verified this. - - - - - e14b7e58 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix LaTeX backend test refs Changes to GHC pretty printing code have resulted in some differences to Haddock's LaTeX output. - Type variables are printed explicitly quantified in the LinearTypes test - Wildcard types in type family equations are now printed numbered, e.g. _1 _2, in the TypeFamilies3 test - Combined signatures in DefaultSignatures test are now documented as separate signatures - - - - - 41b5b296 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and test source updates - Stop using kind `*` in html test sources - Add TypeOperators where necessary to avoid warnings and future errors - Rename some test modules to match their module names - - - - - c640e2a2 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix missing deprecation warnings on record fields `lookupOccEnv` was used to resolve `OccNames` with warnings attached, but it doesn't look in the record field namespace. Thus, if a record field had a warning attached, it would not resolve and the warning map would not include it. This commit fixes by using `lookupOccEnv_WithFields` instead. - - - - - fad0c462 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and some comments - - - - - 751fd023 by Finley McIlwaine at 2023-06-01T14:11:41-06:00 Accept HTML test diffs All diffs now boil down to the expected differences resulting from declarations being reified from TyThings in hi-haddock. Surface syntax now has much less control over the syntax used in the documentation. - - - - - d835c845 by Finley McIlwaine at 2023-06-01T14:11:45-06:00 Adapt to new load' type - - - - - dcf776c4 by Finley McIlwaine at 2023-06-01T14:13:13-06:00 Update mkWarningMap and moduleWarning - - - - - 8e8432fd by Finley McIlwaine at 2023-06-01T14:28:54-06:00 Revert load' changes - - - - - aeb2982c by Finley McIlwaine at 2023-06-01T14:40:24-06:00 Accept change to Instances test in html-test Link to Data.Tuple instead of GHC.Tuple.Prim - - - - - 8adfdbac by Finley McIlwaine at 2023-06-01T15:53:17-06:00 Reset ghc dep to ^>= 9.6 - - - - - 2b1ce93d by Finley McIlwaine at 2023-06-06T07:50:04-06:00 Update CHANGES.md, user guide, recomp avoidance * Add --trace-args flag for tracing arguments received to standard output * Avoid recompiling due to changes in optimization flags * Update users guide and changes.md - - - - - f3da6676 by Finley McIlwaine at 2023-06-06T14:12:56-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - bf36c467 by Matthew Pickering at 2023-06-07T10:16:09+01:00 Revert back to e16e20d592a6f5d9ed1af17b77fafd6495242345 Neither of these MRs are ready to land yet which causes issues with other MRs which are ready to land and need haddock changes. - - - - - 421510a9 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 atSign has no unicode variant Prior to this change, atSign was defined as follows: atSign unicode = text (if unicode then "@" else "@") Yes, this is the same symbol '\64' and not your font playing tricks on you. Now we define: atSign = char '@' Both the LaTeX and the Xhtml backend are updated accordingly. - - - - - 3785c276 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 LaTeX: fix printing of type variable bindings Consider this type signature: kindOf :: forall {k} (a :: k). Proxy a -> Proxy k Prior to this fix, the LaTeX backend rendered it like this: kindOf :: forall k a. Proxy a -> Proxy k Now we preserve explicit specificity and kind annotations. - - - - - 0febf3a8 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 Add support for invisible binders in type declarations - - - - - 13e33bb3 by Finley McIlwaine at 2023-06-08T07:51:59-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - 3e5340ce by Finley McIlwaine at 2023-06-08T07:54:27-06:00 Add note about stubdir to recompilation docs - - - - - db7e84dc by Finley at 2023-06-08T08:11:03-06:00 Merge pull request haskell/haddock#1597 from haskell/finley/hi-haddock-9.6 hi-haddock for ghc 9.6 - - - - - 4e085d17 by Finley McIlwaine at 2023-06-14T13:41:06-06:00 Replace SYB traversals - - - - - 7b39aec5 by Finley McIlwaine at 2023-06-14T14:20:17-06:00 Test ref accepts, remove unused HaddockClsInst - - - - - df9c2090 by Finley McIlwaine at 2023-06-15T08:02:51-06:00 Use batchMsg for progress reporting during load With hi-haddock as is, there is an awkward silence during the load operation. This commit makes haddock use the default `batchMsg` Messager for progress reporting, and makes the default GHC verbosity level 1, so the user can see what GHC is doing. - - - - - f23679a8 by Hécate Moonlight at 2023-06-15T20:31:53+02:00 Merge pull request haskell/haddock#1600 from haskell/finley/hi-haddock-optim - - - - - a7982192 by Finley McIlwaine at 2023-06-15T15:02:16-06:00 hi-haddock squashed - - - - - c34f0c8d by Finley McIlwaine at 2023-06-15T16:22:03-06:00 Merge remote-tracking branch 'origin/ghc-9.6' into finley/hi-haddock-squashed - - - - - 40452797 by Bartłomiej Cieślar at 2023-06-16T12:26:04+02:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - e58673bf by Ben Gamari at 2023-06-16T09:33:35-04:00 Bump GHC version to 9.8 - - - - - 74bdf972 by Ben Gamari at 2023-06-16T09:36:18-04:00 Merge commit 'fcaaad06770a26d35d4aafd65772dedadf17669c' into ghc-head - - - - - 418ee3dc by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Remove NFData SourceText, IfaceWarnings updates The NFData SourceText instance is now available in GHC Handle mod_iface mi_warns now being IfaceWarnings - - - - - 62f31380 by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Accept Instances.hs test output Due to ghc!10469. - - - - - a8f2fc0e by Ben Gamari at 2023-06-20T15:48:08-04:00 Test fixes for "Fix associated data family doc structure items" Associated data families were being given their own export DocStructureItems, which resulted in them being documented separately from their classes in haddocks. This commit fixes it. - - - - - cb1ac33e by Bartłomiej Cieślar at 2023-06-21T12:56:02-04:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - 9933e10b by Ben Gamari at 2023-06-21T12:56:02-04:00 Bump GHC version to 9.8 - - - - - fe8c18b6 by Ben Gamari at 2023-06-21T15:36:29-04:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - c61a0d5b by Ben Gamari at 2023-06-21T16:10:51-04:00 Bump GHC version to 9.9 - - - - - 0c2a756e by sheaf at 2023-07-07T13:45:12+02:00 Avoid incomplete record update in Haddock Hoogle This commit avoids running into an incomplete record update warning in the Hoogle backend of Haddock. This was only noticed now, because incomplete record updates were broken in GHC 9.6. Now that they are fixed, we have to avoid running into them! - - - - - f9b952a7 by Ben Gamari at 2023-07-21T11:58:05-04:00 Bump base bound to <4.20 For GHC 9.8. - - - - - 1b27e151 by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Check for puns (see ghc#23368) - - - - - 457341fd by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Remove fake exports for (~), List, and Tuple<n> The old reasoning no longer applies, nowadays those names can be mentioned in export lists. - - - - - bf3dcddf by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Fix pretty-printing of Solo and MkSolo - - - - - 495b2241 by Matthew Pickering at 2023-09-01T13:02:07+02:00 Fix issue with duplicate reexported definitions (T23616) When a class method was reexported, it's default methods were also showing up in the generated html page. The simplest and most non-invasive fix is to not look for the default method if we are just exporting the class method.. because the backends are just showing default methods when the whole class is exported. In general it would be worthwhile to rewrite this bit of code I think as the logic and what gets included is split over `lookupDocs` and `availExportDecl` it would be clearer to combine the two. The result of lookupDocs is always just passed to availExportDecl so it seems simpler and more obvious to just write the function directly. - - - - - 6551824d by Finley McIlwaine at 2023-09-05T13:06:57-07:00 Remove fake export of `FUN` from Prelude This prevents `data FUN` from being shown at the top of the Prelude docs. Fixes \#23920 on GHC. - - - - - 9ab5a448 by Alan Zimmerman at 2023-09-08T18:26:53+01:00 Match changes in wip/az/T23885-unicode-funtycon - - - - - 4d08364e by Alan Zimmerman at 2023-10-31T19:46:45+00:00 EPA: match changes in GHC - EPA: Comments in AnchorOperation - EPA: Remove EpaEofComment - - - - - e7da0d25 by Alan Zimmerman at 2023-11-05T11:20:31+00:00 EPA: match changes in GHC, l2l cleanup - - - - - 4ceac14d by Alan Zimmerman at 2023-11-11T15:16:41+00:00 EPA: Replace Anchor with EpaLocation Match GHC - - - - - 94fb8d47 by Alan Zimmerman at 2023-11-29T18:10:26+00:00 Match GHC, No comments in EpaDelta for comments - - - - - 32d208e1 by Vladislav Zavialov at 2023-12-12T20:41:36+03:00 EPA: Match changes to LHsToken removal - - - - - eebdd316 by Apoorv Ingle at 2024-01-23T13:49:12+00:00 Changes for haskell/haddock#18324 - - - - - ae856a82 by Matthew Pickering at 2024-02-05T12:22:39+00:00 ghc-internals fallout - - - - - f8429266 by Jade at 2024-02-08T14:56:50+01:00 Adjust test for ghc MR !10993 - - - - - 6d1e2386 by Alan Zimmerman at 2024-02-13T22:00:28+03:00 EPA: Match changes to HsParTy and HsFunTy - - - - - 9c588f19 by Fendor at 2024-02-14T11:05:36+01:00 Adapt to GHC giving better Name's for linking - - - - - 778e1db3 by Andrei Borzenkov at 2024-02-16T16:12:07+03:00 Namespace specifiers for fixity signatures - - - - - 826c5b47 by Torsten Schmits at 2024-02-21T13:17:05+01:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 2cff14d5 by Ben Gamari at 2024-02-22T09:35:56-05:00 Bump bounds - - - - - f49376b3 by Ben Gamari at 2024-02-22T09:35:56-05:00 Allow `@since` annotations in export lists Here we extend Haddock to admit `@since` annotations in export lists. These can be attached to most export list items (although not subordinate lists). These annotations supercede the declaration's `@since` annotation in produced Haddocks. - - - - - b5aa93df by Ben Gamari at 2024-02-22T12:09:06-05:00 Allow package-qualified @since declarations - - - - - 8f5957f2 by Ben Gamari at 2024-02-22T13:55:19-05:00 Documentation changes from ghc-internal restructuring Previously many declarations (e.g. `Int`) were declared to have a "home" in `Prelude`. However, now Haddock instead chooses to put these in more specific homes (e.g. `Data.Int`). Given that the "home" decision is driven by heuristics and in general these changes seem quite reasonable I am accepting them: * `Int` moved from `Prelude` to `Data.Int` * `(~)` moved from `Prelude` to `Data.Type.Equality` * `Type` moved from `GHC.Types` to `Data.Kind` * `Maybe` moved from `Prelude` to `Data.Maybe` * `Bool` moved from `Prelude` to `Data.Bool` * `Ordering` moved from `Prelude` to `Data.Ord` As well, more identifiers are now hyperlinked; it's not immediately clear *why*, but it is an improvement nevertheless. - - - - - ec33fec3 by Ben Gamari at 2024-02-22T20:36:24-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 30cfd251 by Torsten Schmits at 2024-02-24T13:00:42-05:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 732db81d by Ben Gamari at 2024-02-24T19:12:18-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 86bf7010 by Ben Gamari at 2024-02-27T19:28:10-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 4b6e76b5 by Patrick at 2024-03-07T22:09:30+08:00 fix haskell/haddock#24493, with module name introduced in hieAst The accompanies haddoc PR with GHC PR https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12153 Two things have been done: 1. Link is introduced to every `X` in `module X where`, since we introduce the module name to HieAst, 2. `{-# LINE 4 "hypsrc-test/src/PositionPragmas.hs" #-}` is added before the `module PositionPragmas where` in ` hypsrc-test/ref/src/PositionPragmas.html `.It ensures only a single hieAst for file `hypsrc-test/src/PositionPragmas.hs` is generated. - - - - - 635abccc by Ben Gamari at 2024-03-08T17:09:06-05:00 Bump ghc version to 9.10 - - - - - 5b934048 by Ben Gamari at 2024-03-08T18:50:12-05:00 Bump base upper bound - - - - - b30d134e by Ben Gamari at 2024-03-08T18:50:44-05:00 Testsuite output update - - - - - 9bdf3586 by Ben Gamari at 2024-03-09T21:37:44-05:00 Merge branch 'ghc-9.10' into ghc-head - - - - - cec76981 by Ben Gamari at 2024-03-09T21:54:00-05:00 Bump GHC version to 9.11 - - - - - 4c59feb7 by Ben Gamari at 2024-03-09T22:15:01-05:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - bee54c24 by Krzysztof Gogolewski at 2024-04-19T11:13:00+02:00 Update quantification order following GHC haskell/haddock#23764 - - - - - 2814eb89 by Ben Gamari at 2024-04-19T18:57:05+02:00 hypsrc-test: Fix output of PositionPragmas.html - - - - - a27c6a49 by Fendor at 2024-04-22T10:13:03+02:00 Adapt to UserData split - - - - - 1efc5a7a by Fendor at 2024-04-22T10:13:03+02:00 Adapt to BinHandle split - - - - - c62239b7 by Sylvain Henry at 2024-04-29T10:35:00+02:00 Fix tests for T22229 - - - - - b2682534 by Rodrigo Mesquita at 2024-05-10T01:47:51-04:00 Document NcgImpl methods Fixes #19914 - - - - - 4d3acbcf by Zejun Wu at 2024-05-10T01:48:28-04:00 Make renamer to be more flexible with parens in the LHS of the rules We used to reject LHS like `(f a) b` in RULES and requires it to be written as `f a b`. It will be handy to allow both as the expression may be more readable with extra parens in some cases when infix operator is involved. Espceially when TemplateHaskell is used, extra parens may be added out of user's control and result in "valid" rules being rejected and there are not always ways to workaround it. Fixes #24621 - - - - - ab840ce6 by Ben Gamari at 2024-05-10T01:49:04-04:00 IPE: Eliminate dependency on Read Instead of encoding the closure type as decimal string we now simply represent it as an integer, eliminating the need for `Read` in `GHC.Internal.InfoProv.Types.peekInfoProv`. Closes #24504. ------------------------- Metric Decrease: T24602_perf_size size_hello_artifact ------------------------- - - - - - a9979f55 by Cheng Shao at 2024-05-10T01:49:43-04:00 testsuite: fix testwsdeque with recent clang This patch fixes compilation of testwsdeque.c with recent versions of clang, which will fail with the error below: ``` testwsdeque.c:95:33: error: warning: format specifies type 'long' but the argument has type 'void *' [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~~ ^ testwsdeque.c:95:39: error: warning: format specifies type 'int' but the argument has type 'StgWord' (aka 'unsigned long') [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~ ^~~ | %lu testwsdeque.c:133:42: error: error: incompatible function pointer types passing 'void (void *)' to parameter of type 'OSThreadProc *' (aka 'void *(*)(void *)') [-Wincompatible-function-pointer-types] 133 | createOSThread(&ids[n], "thief", thief, (void*)(StgWord)n); | ^~~~~ /workspace/ghc/_build/stage1/lib/../lib/x86_64-linux-ghc-9.11.20240502/rts-1.0.2/include/rts/OSThreads.h:193:51: error: note: passing argument to parameter 'startProc' here 193 | OSThreadProc *startProc, void *param); | ^ 2 warnings and 1 error generated. ``` - - - - - c2b33fc9 by Rodrigo Mesquita at 2024-05-10T01:50:20-04:00 Rename pre-processor invocation args Small clean up. Uses proper names for the various groups of arguments that make up the pre-processor invocation. - - - - - 2b1af08b by Cheng Shao at 2024-05-10T01:50:55-04:00 ghc-heap: fix typo in ghc-heap cbits - - - - - fc2d6de1 by Jade at 2024-05-10T21:07:16-04:00 Improve performance of Data.List.sort(By) This patch improves the algorithm to sort lists in base. It does so using two strategies: 1) Use a four-way-merge instead of the 'default' two-way-merge. This is able to save comparisons and allocations. 2) Use `(>) a b` over `compare a b == GT` and allow inlining and specialization. This mainly benefits types with a fast (>). Note that this *may* break instances with a *malformed* Ord instance where `a > b` is *not* equal to `compare a b == GT`. CLC proposal: https://github.com/haskell/core-libraries-committee/issues/236 Fixes #24280 ------------------------- Metric Decrease: MultiLayerModulesTH_Make T10421 T13719 T15164 T18698a T18698b T1969 T9872a T9961 T18730 WWRec T12425 T15703 ------------------------- - - - - - 1012e8aa by Matthew Pickering at 2024-05-10T21:07:52-04:00 Revert "ghcup-metadata: Drop output_name field" This reverts commit ecbf22a6ac397a791204590f94c0afa82e29e79f. This breaks the ghcup metadata generation on the nightly jobs. - - - - - daff1e30 by Jannis at 2024-05-12T13:38:35-04:00 Division by constants optimization - - - - - 413217ba by Andreas Klebinger at 2024-05-12T13:39:11-04:00 Tidy: Add flag to expose unfoldings if they take dictionary arguments. Add the flag `-fexpose-overloaded-unfoldings` to be able to control this behaviour. For ghc's boot libraries file size grew by less than 1% when it was enabled. However I refrained from enabling it by default for now. I've also added a section on specialization more broadly to the users guide. ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot Metric Increase: T12425 T13386 hard_hole_fits ------------------------- - - - - - c5d89412 by Zubin Duggal at 2024-05-13T22:19:53-04:00 Don't store a GlobalRdrEnv in `mi_globals` for GHCi. GHCi only needs the `mi_globals` field for modules imported with :module +*SomeModule. It uses this field to make the top level environment in `SomeModule` available to the repl. By default, only the first target in the command line parameters is "star" loaded into GHCi. Other modules have to be manually "star" loaded into the repl. Storing the top level GlobalRdrEnv for each module is very wasteful, especially given that we will most likely never need most of these environments. Instead we store only the information needed to reconstruct the top level environment in a module, which is the `IfaceTopEnv` data structure, consisting of all import statements as well as all top level symbols defined in the module (not taking export lists into account) When a particular module is "star-loaded" into GHCi (as the first commandline target, or via an explicit `:module +*SomeModule`, we reconstruct the top level environment on demand using the `IfaceTopEnv`. - - - - - d65bf4a2 by Fendor at 2024-05-13T22:20:30-04:00 Add perf regression test for `-fwrite-if-simplified-core` - - - - - 2c0f8ddb by Andrei Borzenkov at 2024-05-13T22:21:07-04:00 Improve pattern to type pattern transformation (23739) `pat_to_type_pat` function now can handle more patterns: - TuplePat - ListPat - LitPat - NPat - ConPat Allowing these new constructors in type patterns significantly increases possible shapes of type patterns without `type` keyword. This patch also changes how lookups in `lookupOccRnConstr` are performed, because we need to fall back into types when we didn't find a constructor on data level to perform `ConPat` to type transformation properly. - - - - - be514bb4 by Cheng Shao at 2024-05-13T22:21:43-04:00 hadrian: fix hadrian building with ghc-9.10.1 - - - - - ad38e954 by Cheng Shao at 2024-05-13T22:21:43-04:00 linters: fix lint-whitespace compilation with ghc-9.10.1 - - - - - a593f284 by Andreas Klebinger at 2024-05-15T07:32:10-04:00 Expand the `inline` rule to look through casts/ticks. Fixes #24808 - - - - - b1e0c313 by Cheng Shao at 2024-05-15T07:32:46-04:00 testsuite: bump PartialDownSweep timeout to 5x on wasm32 - - - - - b2227487 by Fendor at 2024-05-15T17:14:06-04:00 Add Eq and Ord instance to `IfaceType` We add an `Ord` instance so that we can store `IfaceType` in a `Data.Map` container. This is required to deduplicate `IfaceType` while writing `.hi` files to disk. Deduplication has many beneficial consequences to both file size and memory usage, as the deduplication enables implicit sharing of values. See issue #24540 for more motivation. The `Ord` instance would be unnecessary if we used a `TrieMap` instead of `Data.Map` for the deduplication process. While in theory this is clerarly the better option, experiments on the agda code base showed that a `TrieMap` implementation has worse run-time performance characteristics. To the change itself, we mostly derive `Eq` and `Ord`. This requires us to change occurrences of `FastString` with `LexicalFastString`, since `FastString` has no `Ord` instance. We change the definition of `IfLclName` to a newtype of `LexicalFastString`, to make such changes in the future easier. Bump haddock submodule for IfLclName changes - - - - - d368f9a6 by Fendor at 2024-05-15T17:14:06-04:00 Move out LiteralMap to avoid cyclic module dependencies - - - - - 2fcc09fd by Fendor at 2024-05-15T17:14:06-04:00 Add deduplication table for `IfaceType` The type `IfaceType` is a highly redundant, tree-like data structure. While benchmarking, we realised that the high redundancy of `IfaceType` causes high memory consumption in GHCi sessions when byte code is embedded into the `.hi` file via `-fwrite-if-simplified-core` or `-fbyte-code-and-object-code`. Loading such `.hi` files from disk introduces many duplicates of memory expensive values in `IfaceType`, such as `IfaceTyCon`, `IfaceTyConApp`, `IA_Arg` and many more. We improve the memory behaviour of GHCi by adding an additional deduplication table for `IfaceType` to the serialisation of `ModIface`, similar to how we deduplicate `Name`s and `FastString`s. When reading the interface file back, the table allows us to automatically share identical values of `IfaceType`. To provide some numbers, we evaluated this patch on the agda code base. We loaded the full library from the `.hi` files, which contained the embedded core expressions (`-fwrite-if-simplified-core`). Before this patch: * Load time: 11.7 s, 2.5 GB maximum residency. After this patch: * Load time: 7.3 s, 1.7 GB maximum residency. This deduplication has the beneficial side effect to additionally reduce the size of the on-disk interface files tremendously. For example, on agda, we reduce the size of `.hi` files (with `-fwrite-if-simplified-core`): * Before: 101 MB on disk * Now: 24 MB on disk This has even a beneficial side effect on the cabal store. We reduce the size of the store on disk: * Before: 341 MB on disk * Now: 310 MB on disk Note, none of the dependencies have been compiled with `-fwrite-if-simplified-core`, but `IfaceType` occurs in multiple locations in a `ModIface`. We also add IfaceType deduplication table to .hie serialisation and refactor .hie file serialisation to use the same infrastrucutre as `putWithTables`. Bump haddock submodule to accomodate for changes to the deduplication table layout and binary interface. - - - - - 36aa7cf1 by Fendor at 2024-05-15T17:14:06-04:00 Add run-time configurability of `.hi` file compression Introduce the flag `-fwrite-if-compression=<n>` which allows to configure the compression level of writing .hi files. The motivation is that some deduplication operations are too expensive for the average use case. Hence, we introduce multiple compression levels with variable impact on performance, but still reduce the memory residency and `.hi` file size on disk considerably. We introduce three compression levels: * `1`: `Normal` mode. This is the least amount of compression. It deduplicates only `Name` and `FastString`s, and is naturally the fastest compression mode. * `2`: `Safe` mode. It has a noticeable impact on .hi file size and is marginally slower than `Normal` mode. In general, it should be safe to always use `Safe` mode. * `3`: `Full` deduplication mode. Deduplicate as much as we can, resulting in minimal .hi files, but at the cost of additional compilation time. Reading .hi files doesn't need to know the initial compression level, and can always deserialise a `ModIface`, as we write out a byte that indicates the next value has been deduplicated. This allows users to experiment with different compression levels for packages, without recompilation of dependencies. Note, the deduplication also has an additional side effect of reduced memory consumption to implicit sharing of deduplicated elements. See https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for example where that matters. ------------------------- Metric Decrease: MultiLayerModulesDefsGhciWithCore T16875 T21839c T24471 hard_hole_fits libdir ------------------------- - - - - - 1e63a6fb by Matthew Pickering at 2024-05-15T17:14:07-04:00 Introduce regression tests for `.hi` file sizes Add regression tests to track how `-fwrite-if-compression` levels affect the size of `.hi` files. - - - - - 639d742b by M Farkas-Dyck at 2024-05-15T17:14:49-04:00 TTG: ApplicativeStatement exist only in Rn and Tc Co-Authored-By: romes <rodrigo.m.mesquita at gmail.com> - - - - - aa7b336b by Jade at 2024-05-15T23:06:17-04:00 Documentation: Improve documentation for symbols exported from System.IO - - - - - c561de8f by Jade at 2024-05-15T23:06:54-04:00 Improve suggestions for language extensions - When suggesting Language extensions, also suggest Extensions which imply them - Suggest ExplicitForAll and GADTSyntax instead of more specific extensions - Rephrase suggestion to include the term 'Extension' - Also moves some flag specific definitions out of Session.hs into Flags.hs (#24478) Fixes: #24477 Fixes: #24448 Fixes: #10893 - - - - - 4c7ae2a1 by Andreas Klebinger at 2024-05-15T23:07:30-04:00 Testsuite: Check if llvm assembler is available for have_llvm - - - - - bc672166 by Torsten Schmits at 2024-05-15T23:08:06-04:00 refactor quadratic search in warnMissingHomeModules - - - - - 7875e8cb by Torsten Schmits at 2024-05-15T23:08:06-04:00 add test that runs MakeDepend on thousands of modules - - - - - b84b91f5 by Adam Gundry at 2024-05-16T15:32:06-04:00 Representation-polymorphic HasField (fixes #22156) This generalises the HasField class to support representation polymorphism, so that instead of type HasField :: forall {k} . k -> Type -> Type -> Constraint we have type HasField :: forall {k} {r_rep} {a_rep} . k -> TYPE r_rep -> TYPE a_rep -> Constraint - - - - - 05285090 by Matthew Pickering at 2024-05-16T15:32:43-04:00 Bump os-string submodule to 2.0.2.2 Closes #24786 - - - - - 886ab43a by Cheng Shao at 2024-05-17T01:34:50-04:00 rts: do not prefetch mark_closure bdescr in non-moving gc when ASSERTS_ENABLED This commit fixes a small an oversight in !12148: the prefetch logic in non-moving GC may trap in debug RTS because it calls Bdescr() for mark_closure which may be a static one. It's fine in non-debug RTS because even invalid bdescr addresses are prefetched, they will not cause segfaults, so this commit implements the most straightforward fix: don't prefetch mark_closure bdescr when assertions are enabled. - - - - - b38dcf39 by Teo Camarasu at 2024-05-17T01:34:50-04:00 rts: Allocate non-moving segments with megablocks Non-moving segments are 8 blocks long and need to be aligned. Previously we serviced allocations by grabbing 15 blocks, finding an aligned 8 block group in it and returning the rest. This proved to lead to high levels of fragmentation as a de-allocating a segment caused an 8 block gap to form, and this could not be reused for allocation. This patch introduces a segment allocator based around using entire megablocks to service segment allocations in bulk. When there are no free segments, we grab an entire megablock and fill it with aligned segments. As the megablock is free, we can easily guarantee alignment. Any unused segments are placed on a free list. It only makes sense to free segments in bulk when all of the segments in a megablock are freeable. After sweeping, we grab the free list, sort it, and find all groups of segments where they cover the megablock and free them. This introduces a period of time when free segments are not available to the mutator, but the risk that this would lead to excessive allocation is low. Right after sweep, we should have an abundance of partially full segments, and this pruning step is relatively quick. In implementing this we drop the logic that kept NONMOVING_MAX_FREE segments on the free list. We also introduce an eventlog event to log the amount of pruned/retained free segments. See Note [Segment allocation strategy] Resolves #24150 ------------------------- Metric Decrease: T13253 T19695 ------------------------- - - - - - 710665bd by Cheng Shao at 2024-05-17T01:35:30-04:00 rts: fix I/O manager compilation errors for win32 target This patch fixes I/O manager compilation errors for win32 target discovered when cross-compiling to win32 using recent clang: ``` rts/win32/ThrIOManager.c:117:7: error: error: call to undeclared function 'is_io_mng_native_p'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 117 | if (is_io_mng_native_p ()) { | ^ | 117 | if (is_io_mng_native_p ()) { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/fs.c:143:28: error: error: a function declaration without a prototype is deprecated in all versions of C [-Werror,-Wstrict-prototypes] 143 | int setErrNoFromWin32Error () { | ^ | void | 143 | int setErrNoFromWin32Error () { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:227:9: error: error: call to undeclared function 'interruptIOManagerEvent'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 227 | interruptIOManagerEvent (); | ^ | 227 | interruptIOManagerEvent (); | ^ rts/win32/ConsoleHandler.c:227:9: error: note: did you mean 'getIOManagerEvent'? | 227 | interruptIOManagerEvent (); | ^ rts/include/rts/IOInterface.h:27:10: error: note: 'getIOManagerEvent' declared here 27 | void * getIOManagerEvent (void); | ^ | 27 | void * getIOManagerEvent (void); | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:196:9: error: error: call to undeclared function 'setThreadLabel'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/win32/ConsoleHandler.c:196:9: error: note: did you mean 'postThreadLabel'? | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/eventlog/EventLog.h:118:6: error: note: 'postThreadLabel' declared here 118 | void postThreadLabel(Capability *cap, | ^ | 118 | void postThreadLabel(Capability *cap, | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) ``` - - - - - 28b9cee0 by Rodrigo Mesquita at 2024-05-17T01:36:05-04:00 configure: Check C99-compat for Cmm preprocessor Fixes #24815 - - - - - 8927e0c3 by Andreas Klebinger at 2024-05-17T01:36:41-04:00 Ensure `tcHasFixedRuntimeRep (# #)` returns True. - - - - - 04179044 by doyougnu at 2024-05-17T09:00:32-04:00 testsuite: make find_so regex less general Closes #24759 Background. In MR !12372 we began tracking shared object files and directories sizes for dependencies. However, this broke release builds because release builds alter the filenames swapping "in-place" for a hash. This was not considered in the MR and thus broke release pipelines. Furthermore, the rts_so test was found to be wildly varying and was therefore disabled in !12561. This commit fixes both of these issues: - fix the rts_so test by making the regex less general, now the rts_so test and all other foo.so tests must match "libHS<some-lib>-<version>-<hash|'in-place>-<ghc>". This prevents the rts_so test from accidentally matching different rts variants such as rts_threaded, which was the cause of the wild swings after !12372. - add logic to match either a hash or the string in-place. This should make the find_so function build agnostic. - - - - - 0962b50d by Andreas Klebinger at 2024-05-17T09:01:08-04:00 TagAnalysis: Treat all bottom ids as tagged during analysis. Ticket #24806 showed that we also need to treat dead end thunks as tagged during the analysis. - - - - - 7eb9f184 by Ben Gamari at 2024-05-17T11:23:37-04:00 Remove haddock submodule In preparation for merge into the GHC, as proposed in #23178. - - - - - 47b14dcc by Fendor at 2024-05-17T11:28:17-04:00 Adapt to `IfLclName` newtype changes (cherry picked from commit a711607e29b925f3d69e27c5fde4ba655c711ff1) - - - - - 6cc6681d by Fendor at 2024-05-17T11:28:17-04:00 Add IfaceType deduplication table to interface file serialisation Although we do not really need it in the interface file serialisation, as the deserialisation uses `getWithUserData`, we need to mirror the structure `getWithUserData` expects. Thus, we write essentially an empty `IfaceType` table at the end of the file, as the interface file doesn't reference `IfaceType`. (cherry picked from commit c9bc29c6a708483d2abc3d8ec9262510ce87ca61) - - - - - b9721206 by Ben Gamari at 2024-05-17T11:30:22-04:00 ghc-tags.yaml: Initial commit - - - - - 074e7d8f by Ben Gamari at 2024-05-17T11:31:29-04:00 fourmolu: Add configuration - - - - - 151b1736 by Ben Gamari at 2024-05-17T11:32:52-04:00 Makefile: Rework for use by haddock developers Previously the Makefile was present only for GHC's old make-based build system. Now since the make-based build system is gone we can use it for more useful ends. - - - - - a7dcf13b by Ben Gamari at 2024-05-17T11:36:14-04:00 Reformat with fourmolu Using previously-added configuration and `fourmolu -i .` Note that we exclude the test-cases (`./{hoogle,html-hypsrc,latex}-test`) as they are sensitive to formatting. - - - - - 0ea6017b by Ben Gamari at 2024-05-17T11:40:04-04:00 Add 'utils/haddock/' from commit 'a7dcf13bfbb97b20e75cc8ce650e2bb628db4660' git-subtree-dir: utils/haddock git-subtree-mainline: 7eb9f1849b1c72a1c61dee88462b4244550406f3 git-subtree-split: a7dcf13bfbb97b20e75cc8ce650e2bb628db4660 - - - - - aba1d304 by Hécate Moonlight at 2024-05-17T11:40:48-04:00 Add exceptions to the dangling notes list - - - - - 527bfbfb by Hécate Moonlight at 2024-05-17T11:40:52-04:00 Add haddock to the whitespace lint ignore list - - - - - 43274677 by Ben Gamari at 2024-05-17T11:41:20-04:00 git-blame-ignore-revs: Ignore haddock reformatting - - - - - 0e679e37 by Fendor at 2024-05-18T00:27:24-04:00 Pass cpp options to the CC builder in hadrian - - - - - bb40244e by Sylvain Henry at 2024-05-18T00:28:06-04:00 JS: fix allocation constant (fix #24746) - - - - - 646d30ab by Jade at 2024-05-18T19:23:31+02:00 Add highlighting for inline-code snippets in haddock - - - - - 64459a3e by Hécate Moonlight at 2024-05-19T08:42:27-04:00 haddock: Add a .readthedocs.yml file for online documentation - - - - - 7d3d9bbf by Serge S. Gulin at 2024-05-19T18:47:05+00:00 Unicode: General Category size test (related #24789) Added trivial size performance test which involves unicode general category usage via `read`. The `read` itself uses general category to detect spaces. The purpose for this test is to measure outcome of applying improvements at General Category representation in code discussed at #24789. - - - - - 8e04efcf by Alan Zimmerman at 2024-05-19T21:29:34-04:00 EPA: Remove redundant code Remove unused epAnnAnns function various cases for showAstData that no longer exist - - - - - 071d7a1e by Rodrigo Mesquita at 2024-05-20T10:55:16-04:00 Improve docs on closed type families in hs-boots Fixes #24776 - - - - - d9e2c119 by Torsten Schmits at 2024-05-20T10:55:52-04:00 Use default deviation for large-project test This new performance test has the purpose of detecting regressions in complexity in relation to the number of modules in a project, so 1% deviation is way too small to avoid false positives. - - - - - 20b0136a by Ben Gamari at 2024-05-22T00:31:39-04:00 ghcup-metadata: Various fixes from 9.10.1 Use Debian 12/x86-64, Debian 10/aarch64, and Debian 11/aarch64 bindists where possible. - - - - - 6838a7c3 by Sylvain Henry at 2024-05-22T00:32:23-04:00 Reverse arguments to stgCallocBytes (fix #24828) - - - - - f50f46c3 by Fendor at 2024-05-22T00:32:59-04:00 Add log messages for Iface serialisation compression level Fix the label of the number of 'IfaceType' entries in the log message. Add log message for the compression level that is used to serialise a an interface file. Adds `Outputable` instance for 'CompressionIFace'. - - - - - 3bad5d55 by Hécate Moonlight at 2024-05-22T00:33:40-04:00 base: Update doctests outputs ghc-internal: Update doctests outputs - - - - - 9317c6fb by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix the testsuites of the haddock-library - Apply all the metadata revisions from Hackage to the cabal file. - Fix the `ParserSpec.hs` file in the `spec` testsuite of haddock-library. - Make `CHANGES.md` an extra-doc-file instead of an extra-source-file. - - - - - 54073b02 by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix parser of @since pragma The testsuite contained tests for annotations of the form `@since foo-bar-0.5.0`, but the parser was written incorrectly. - - - - - ede6ede3 by Matthew Pickering at 2024-05-22T00:34:57-04:00 Fix nightly pages job It seems likely broken by 9f99126a which moved `index.html` from the root folder into `docs/` folder. Fixes #24840 - - - - - b7bcf729 by Cheng Shao at 2024-05-22T00:35:32-04:00 autoconf: remove unused context diff check This patch removes redundant autoconf check for the context diff program given it isn't actually been used anywhere, especially since make removal. - - - - - ea2fe66e by Hécate Moonlight at 2024-05-22T00:36:13-04:00 haddock: Rework the contributing guide - - - - - 0f302a94 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 haddock: Add module relationships diagrams of haddock-api and haddock-library - - - - - d1a9f34f by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add instructions - - - - - b880ee80 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add SVG outputs - - - - - 6d7e6ad8 by Ben Gamari at 2024-05-22T13:40:05-04:00 rts: Fix size of StgOrigThunkInfo frames Previously the entry code of the `stg_orig_thunk` frame failed to account for the size of the profiling header as it hard-coded the frame size. Fix this. Fixes #24809. - - - - - c645fe40 by Fendor at 2024-05-22T13:40:05-04:00 Add regression test T24809 for stg_orig_thunk_info_frame size - - - - - 4181aa40 by Andreas Klebinger at 2024-05-22T13:40:42-04:00 bindists: Check for existence of share folder before trying to copy it. This folder isn't distributed in windows bindists A lack of doing so resulted us copying loads of files twice. - - - - - d216510e by Matthew Pickering at 2024-05-22T13:40:42-04:00 Remove ad-hoc installation of mingw toolchain in relocatable bindists This reverts 616ac30026e8dd7d2ebb98d92dde071eedf5d951 The choice about whether to install mingw is taken in the installation makefile. This is also broken on non-windows systems. The actual issue was the EnableDistroToolchain variable wasn't declared in mk/config.mk and therefore the check to install mingw was failing. - - - - - 7b4c1998 by Cheng Shao at 2024-05-22T21:52:52-04:00 testsuite: fix T17920 for wasm backend T17920 was marked as fragile on wasm before; it can be trivially fixed by avoiding calling variadic printf() in cmm. - - - - - c739383b by Cheng Shao at 2024-05-22T21:53:29-04:00 testsuite: bump T22744 timeout to 5x - - - - - c4c6d714 by Cheng Shao at 2024-05-22T21:54:06-04:00 testsuite: don't attempt to detect host cpu features when testing cross ghc The testsuite driver CPU feature detection logic only detects host CPU and only makes sense when we are not testing a cross GHC. - - - - - 3d9e4ce6 by Simon Peyton Jones at 2024-05-22T21:54:43-04:00 Better skolemisation As #24810 showed, it is (a little) better to skolemise en-bloc, so that Note [Let-bound skolems] fires more often. See Note [Skolemisation en bloc] in GHC.Tc.Utils.Instantiate. - - - - - a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00 Add missing parenthesizePat in cvtp We need to ensure that the output of `cvtp` is parenthesized (at precedence `sigPrec`) so that any pattern signatures with a surrounding pattern signature can parse correctly. Fixes #24837. - - - - - 4bb2a7cc by Hécate Moonlight at 2024-05-22T21:55:59-04:00 [base] Document the memory overhead of ByteArray Add a diagram that shows the constituent parts of a ByteArray and their memory overhead. - - - - - 8b2a016a by Hécate Moonlight at 2024-05-22T21:56:38-04:00 Haddock: Add MR template for Haddock - - - - - ead75532 by Peter Trommler at 2024-05-23T02:28:05-04:00 PPC: Support ELF v2 on powerpc64 big-endian Detect ELF v2 on PowerPC 64-bit systems. Check for `_CALL_ELF` preprocessor macro. Fixes #21191 - - - - - 9d4c10f2 by Hécate Kleidukos at 2024-05-23T02:28:44-04:00 gitlab: Add @Kleidukos to CODEOWNERS for utils/haddock - - - - - 28e64170 by Preetham Gujjula at 2024-05-23T07:20:48-04:00 haddock: Add cabal-fmt to tools for `make style` - - - - - 00126a89 by Andrei Borzenkov at 2024-05-23T07:21:24-04:00 haddock: fix verbosity option parsing - - - - - a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00 base: specify tie-breaking behavior of min, max, and related list/Foldable functions - - - - - bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00 cmm: add word <-> double/float bitcast - closes: #25331 This is the last step in the project plan described in #25331. This commit: - adds bitcast operands for x86_64, LLVM, aarch64 - For PPC and i386 we resort to using the cmm implementations - renames conversion MachOps from Conv to Round|Truncate - - - - - f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor Some functions in StgToByteCode were filtering out void arguments. However, StgToByteCode is called after unarisation: the void arguments should have been removed earlier. Instead of filtering out, we assert that the args are non-void. - - - - - 03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor `layoutNativeCall` was always called with a `primRepCmmType platform` callback. Hence we can put it inside of `layoutNativeCall` rather than repeat it. - - - - - 27c430f3 by David Binder at 2024-05-24T07:52:38-04:00 haddock: Remove compatibility shims for GHC < 8.4 from haddock-library - - - - - 8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00 compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs This patch makes the STG->Cmm backend avoid saving foreign call target to local when there are no caller-save GlobalRegs. Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a foreign call, we unconditionally save the foreign call target to a temporary local first, then rely on cmmSink to clean it up later, which only happens with -fcmm-sink (implied by -O) and not in unoptimized code. And this is troublesome for the wasm backend NCG, which needs to infer a foreign call target symbol's type signature from the Cmm call site. Previously, the NCG has been emitting incorrect type signatures for unoptimized code, which happens to work with `wasm-ld` most of the time, but this is never future-proof against upstream toolchain updates, and it causes horrible breakages when LTO objects are included in linker input. Hence this patch. - - - - - 986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00 testsuite: add callee-no-local regression test - - - - - 52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00 Fix HasCallStack leftovers from !12514 / #24726 - - - - - c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00 user_guide: Fix typo in MultiWayIf chapter Close #24829 - - - - - bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - 1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Fix changelog reference to setBacktraceMechanismState (cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d) - - - - - 43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00 Float/double unboxed literal support for HexFloatLiterals (fix #22155) - - - - - 4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00 Improve test labels for binary interface file size tests Test labels for binary interface file sizes are hard to read and overly verbose at the same time. Extend the name for the metric title, but shorten it in the actual comparison table. - - - - - 14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00 Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present" This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa. - - - - - f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00 Fix default hyperlinked sources pattern Previously this didn't include the `%M` token which manifested as broken links to the hyperlinked sources of reexports of declarations defined in other packages. Fixes haddock#1628. (cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36) - - - - - 42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00 Make DocPaths a proper data type (cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c) - - - - - 53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00 haddock: Bump version to 2.30 (cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602) - - - - - e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00 haddock-api: allow base 4.20 and ghc 9.11 - - - - - e294f7a2 by PHO at 2024-05-24T12:17:55-04:00 Add a flag "threaded" for building haddock with the threaded RTS GHC isn't guaranteed to have a threaded RTS. There should be a way to build it with the vanilla one. (cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d) - - - - - 51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00 Update ticky counter event docs. Add the info about the info table address and json fields. Fixes #23200 - - - - - 98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00 Export extractPromotedList (#24866) This can be useful in plugins. - - - - - 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - c416033e by sheaf at 2024-06-12T12:48:31+02:00 Rebase of first attempt of NCG SIMD support This commit contains most of the changes from the commit: Add support for SIMD operations in the NCG This adds support for constructing vector types from Float#, Double# etc and performing arithmetic operations on them This commit is meant to serve as a base from which to figure out register allocation issues. - - - - - 0c5a8ade by sheaf at 2024-06-12T12:48:34+02:00 Add QuickCheck-like test for SIMD operations - - - - - ddd4007d by sheaf at 2024-06-12T12:48:34+02:00 SIMD NCG: add stack spilling test - - - - - 2e84279a by sheaf at 2024-06-12T12:48:34+02:00 SIMD NCG: fix pack & insert for DoubleX2 - - - - - 7f22f476 by sheaf at 2024-06-12T12:49:33+02:00 SIMD NCG WIP: fix stack spilling - - - - - 73ee4f33 by sheaf at 2024-06-12T12:49:36+02:00 SIMD NCG: accept simd006 - - - - - b71b6f77 by sheaf at 2024-06-12T12:49:36+02:00 WIP: fix mkSpillInstr/mkLoadInstr panics - - - - - 70391584 by sheaf at 2024-06-12T12:49:36+02:00 improve RegClass - - - - - 63e98a32 by sheaf at 2024-06-12T12:49:36+02:00 set up basics for AArch64 SIMD - - - - - 6f3822e6 by sheaf at 2024-06-12T12:49:36+02:00 use MOVU instructions for spill/unspill - - - - - 7a776f8f by sheaf at 2024-06-12T12:49:37+02:00 WIP: start adding vector shuffle primops - - - - - 2e4fcf43 by sheaf at 2024-06-12T12:49:37+02:00 remove redundant code in CmmToAsm/PPC/Instr - - - - - a6401dfb by sheaf at 2024-06-12T12:49:37+02:00 emit ymm/zmm when appropriate - - - - - 98e6b7c1 by sheaf at 2024-06-12T12:49:37+02:00 fix reg2reg for vectors - - - - - 7f99991e by sheaf at 2024-06-12T12:49:37+02:00 WIP: lower vector shuffle instruction on X86 - - - - - 2a9957d3 by sheaf at 2024-06-12T12:49:37+02:00 NCG SIMD: fix shuffle lowering - - - - - 572cb217 by sheaf at 2024-06-12T12:49:37+02:00 slight improvement to vector unpack - - - - - 381ec9f9 by sheaf at 2024-06-12T12:49:37+02:00 fix whitespace - - - - - 30 changed files: - + .git-blame-ignore-revs - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - + .gitlab/merge_request_templates/Haddock.md - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitmodules - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/Config.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7c08ed94c0c102f2cbe1691088890c3b2ff1b3c6...381ec9f9a9c8a9fb15e32627a99c90caada5d90f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7c08ed94c0c102f2cbe1691088890c3b2ff1b3c6...381ec9f9a9c8a9fb15e32627a99c90caada5d90f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 11:12:23 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Wed, 12 Jun 2024 07:12:23 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] 18 commits: Rebase of first attempt of NCG SIMD support Message-ID: <6669829767adf_b01b02eac660136739@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 8c70497a by sheaf at 2024-06-12T13:12:16+02:00 Rebase of first attempt of NCG SIMD support This commit contains most of the changes from the commit: Add support for SIMD operations in the NCG This adds support for constructing vector types from Float#, Double# etc and performing arithmetic operations on them This commit is meant to serve as a base from which to figure out register allocation issues. - - - - - 040c8199 by sheaf at 2024-06-12T13:12:16+02:00 Add QuickCheck-like test for SIMD operations - - - - - 96c58fec by sheaf at 2024-06-12T13:12:16+02:00 SIMD NCG: add stack spilling test - - - - - 294a0ae5 by sheaf at 2024-06-12T13:12:16+02:00 SIMD NCG: fix pack & insert for DoubleX2 - - - - - 1b751223 by sheaf at 2024-06-12T13:12:16+02:00 SIMD NCG WIP: fix stack spilling - - - - - c8ca1325 by sheaf at 2024-06-12T13:12:16+02:00 SIMD NCG: accept simd006 - - - - - 0cee3fc4 by sheaf at 2024-06-12T13:12:17+02:00 WIP: fix mkSpillInstr/mkLoadInstr panics - - - - - e5f4de96 by sheaf at 2024-06-12T13:12:17+02:00 improve RegClass - - - - - 8750825f by sheaf at 2024-06-12T13:12:17+02:00 set up basics for AArch64 SIMD - - - - - b5ae1105 by sheaf at 2024-06-12T13:12:17+02:00 use MOVU instructions for spill/unspill - - - - - 070a1d0b by sheaf at 2024-06-12T13:12:17+02:00 WIP: start adding vector shuffle primops - - - - - 1506d777 by sheaf at 2024-06-12T13:12:18+02:00 remove redundant code in CmmToAsm/PPC/Instr - - - - - 3f0ce48f by sheaf at 2024-06-12T13:12:18+02:00 emit ymm/zmm when appropriate - - - - - 8f52b2b7 by sheaf at 2024-06-12T13:12:18+02:00 fix reg2reg for vectors - - - - - 5f16f8f4 by sheaf at 2024-06-12T13:12:18+02:00 WIP: lower vector shuffle instruction on X86 - - - - - a90e9df9 by sheaf at 2024-06-12T13:12:18+02:00 NCG SIMD: fix shuffle lowering - - - - - e3fcf56e by sheaf at 2024-06-12T13:12:18+02:00 slight improvement to vector unpack - - - - - 598dca07 by sheaf at 2024-06-12T13:12:18+02:00 fix whitespace - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Reg.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Regs.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/PPC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/PPC/Regs.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Coalesce.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Reg/Linear/PPC.hs - compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs - compiler/GHC/CmmToAsm/Reg/Linear/State.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/381ec9f9a9c8a9fb15e32627a99c90caada5d90f...598dca076acdd985a79453335940822a625557f9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/381ec9f9a9c8a9fb15e32627a99c90caada5d90f...598dca076acdd985a79453335940822a625557f9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 12:57:35 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 12 Jun 2024 08:57:35 -0400 Subject: [Git][ghc/ghc][wip/T24978] Put [Coercion] in UnivCo Message-ID: <66699b3fd679b_167e4db223e82156b@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24978 at Glasgow Haskell Compiler / GHC Commits: e2142bf4 by Simon Peyton Jones at 2024-06-12T13:57:08+01:00 Put [Coercion] in UnivCo - - - - - 19 changed files: - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/Coercion.hs-boot - compiler/GHC/Core/Coercion/Opt.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/TyCo/Subst.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Iface/Syntax.hs - compiler/GHC/Iface/Type.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Tc/Utils/TcMType.hs - testsuite/tests/pmcheck/should_compile/T11195.hs - testsuite/tests/tcplugins/CtIdPlugin.hs - testsuite/tests/tcplugins/RewritePlugin.hs - testsuite/tests/tcplugins/TyFamPlugin.hs Changes: ===================================== compiler/GHC/Core/Coercion.hs ===================================== @@ -1104,16 +1104,16 @@ mkHoleCo h = HoleCo h -- | Make a universal coercion between two arbitrary types. mkUnivCo :: UnivCoProvenance - -> DCoVarSet -- Free coercion variables of the evidence for this coercion + -> [Coercion] -- ^ Coercions on which this depends -> Role -- ^ role of the built coercion, "r" -> Type -- ^ t1 :: k1 -> Type -- ^ t2 :: k2 -> Coercion -- ^ :: t1 ~r t2 -mkUnivCo prov cvs role ty1 ty2 +mkUnivCo prov deps role ty1 ty2 | ty1 `eqType` ty2 = mkReflCo role ty1 | otherwise = UnivCo { uco_prov = prov, uco_role = role , uco_lty = ty1, uco_rty = ty2 - , uco_cvs = cvs } + , uco_deps = deps } -- | Create a symmetric version of the given 'Coercion' that asserts -- equality between the same types but in the other "direction", so @@ -1400,8 +1400,7 @@ mkProofIrrelCo :: Role -- ^ role of the created coercion, "r" -- the individual coercions are. mkProofIrrelCo r co g _ | isGReflCo co = mkReflCo r (mkCoercionTy g) -- kco is a kind coercion, thus @isGReflCo@ rather than @isReflCo@ -mkProofIrrelCo r kco g1 g2 = mkUnivCo ProofIrrelProv - (coVarsOfCoDSet kco) r +mkProofIrrelCo r kco g1 g2 = mkUnivCo ProofIrrelProv [kco] r (mkCoercionTy g1) (mkCoercionTy g2) {- @@ -1469,7 +1468,7 @@ setNominalRole_maybe r co -- types. mkPhantomCo :: Coercion -> Type -> Type -> Coercion mkPhantomCo h t1 t2 - = mkUnivCo PhantomProv (coVarsOfCoDSet h) Phantom t1 t2 + = mkUnivCo PhantomProv [h] Phantom t1 t2 -- takes any coercion and turns it into a Phantom coercion toPhantomCo :: Coercion -> Coercion @@ -2404,8 +2403,8 @@ seqCo (CoVarCo cv) = cv `seq` () seqCo (HoleCo h) = coHoleCoVar h `seq` () seqCo (AxiomInstCo con ind cos) = con `seq` ind `seq` seqCos cos seqCo (UnivCo { uco_prov = p, uco_role = r - , uco_lty = t1, uco_rty = t2, uco_cvs = cvs }) - = p `seq` r `seq` seqType t1 `seq` seqType t2 `seq` seqDVarSet cvs + , uco_lty = t1, uco_rty = t2, uco_deps = deps }) + = p `seq` r `seq` seqType t1 `seq` seqType t2 `seq` seqCos deps seqCo (SymCo co) = seqCo co seqCo (TransCo co1 co2) = seqCo co1 `seq` seqCo co2 seqCo (SelCo n co) = n `seq` seqCo co ===================================== compiler/GHC/Core/Coercion.hs-boot ===================================== @@ -10,7 +10,6 @@ import {-# SOURCE #-} GHC.Core.TyCon import GHC.Types.Basic ( LeftOrRight ) import GHC.Core.Coercion.Axiom import GHC.Types.Var -import GHC.Types.Var.Set( DCoVarSet ) import GHC.Data.Pair import GHC.Utils.Misc @@ -24,7 +23,7 @@ mkFunCo2 :: Role -> FunTyFlag -> FunTyFlag -> CoercionN -> Coercion -> Coerc mkCoVarCo :: CoVar -> Coercion mkAxiomInstCo :: CoAxiom Branched -> BranchIndex -> [Coercion] -> Coercion mkPhantomCo :: Coercion -> Type -> Type -> Coercion -mkUnivCo :: UnivCoProvenance -> DCoVarSet -> Role -> Type -> Type -> Coercion +mkUnivCo :: UnivCoProvenance -> [Coercion] -> Role -> Type -> Type -> Coercion mkSymCo :: Coercion -> Coercion mkTransCo :: Coercion -> Coercion -> Coercion mkSelCo :: HasDebugCallStack => CoSel -> Coercion -> Coercion ===================================== compiler/GHC/Core/Coercion/Opt.hs ===================================== @@ -15,7 +15,6 @@ import GHC.Tc.Utils.TcType ( exactTyCoVarsOfType ) import GHC.Core.TyCo.Rep import GHC.Core.TyCo.Subst import GHC.Core.TyCo.Compare( eqType, eqForAllVis ) -import GHC.Core.TyCo.FVs( coVarsOfCoDSet ) import GHC.Core.Coercion import GHC.Core.Type as Type hiding( substTyVarBndr, substTy ) import GHC.Core.TyCon @@ -372,8 +371,8 @@ opt_co4 env sym rep r (AxiomInstCo con ind cos) -- Note that the_co does *not* have sym pushed into it opt_co4 env sym rep r (UnivCo { uco_prov = prov, uco_lty = t1 - , uco_rty = t2, uco_cvs = cvs }) - = opt_univ env sym prov cvs (chooseRole rep r) t1 t2 + , uco_rty = t2, uco_deps = deps }) + = opt_univ env sym prov deps (chooseRole rep r) t1 t2 opt_co4 env sym rep r (TransCo co1 co2) -- sym (g `o` h) = sym h `o` sym g @@ -528,7 +527,7 @@ in GHC.Core.Coercion. -- be a phantom, but the output sure will be. opt_phantom :: LiftingContext -> SymFlag -> Coercion -> NormalCo opt_phantom env sym co - = opt_univ env sym PhantomProv (coVarsOfCoDSet co) Phantom ty1 ty2 + = opt_univ env sym PhantomProv [mkKindCo co] Phantom ty1 ty2 where Pair ty1 ty2 = coercionKind co @@ -564,20 +563,19 @@ See #19509. -} opt_univ :: LiftingContext -> SymFlag -> UnivCoProvenance - -> DCoVarSet -- Fully substituted by liftingContextSubst + -> [Coercion] -> Role -> Type -> Type -> Coercion -opt_univ env sym prov cvs role ty1 ty2 - | sym = opt_univ1 env prov cvs' role ty2 ty1 - | otherwise = opt_univ1 env prov cvs' role ty1 ty2 - where - cvs' = substDCoVarSet (liftingContextSubst env) cvs - -opt_univ1 :: LiftingContext -> UnivCoProvenance - -> DCoVarSet -- Fully substituted by liftingContextSubst - -> Role -> Type -> Type - -> Coercion -opt_univ1 env PhantomProv cvs' _r ty1 ty2 - = mkUnivCo PhantomProv cvs' Phantom ty1' ty2' +opt_univ env sym prov deps role ty1 ty2 + = let ty1' = substTyUnchecked (lcSubstLeft env) ty1 + ty2' = substTyUnchecked (lcSubstRight env) ty2 + deps' = map (opt_co1 env sym) deps + (ty1'', ty2'') = swapSym sym (ty1', ty2') + in + mkUnivCo prov deps' role ty1'' ty2'' + +{- +opt_univ env PhantomProv cvs _r ty1 ty2 + = mkUnivCo PhantomProv cvs Phantom ty1' ty2' where ty1' = substTy (lcSubstLeft env) ty1 ty2' = substTy (lcSubstRight env) ty2 @@ -638,6 +636,7 @@ opt_univ1 env prov cvs' role oty1 oty2 ty2 = substTyUnchecked (lcSubstRight env) oty2 in mkUnivCo prov cvs' role ty1 ty2 +-} ------------- opt_transList :: HasDebugCallStack => InScopeSet -> [NormalCo] -> [NormalCo] -> [NormalCo] @@ -724,12 +723,12 @@ opt_trans_rule is in_co1@(InstCo co1 ty1) in_co2@(InstCo co2 ty2) mkInstCo (opt_trans is co1 co2) ty1 opt_trans_rule _ - in_co1@(UnivCo { uco_prov = p1, uco_role = r1, uco_lty = tyl1, uco_cvs = cvs1 }) - in_co2@(UnivCo { uco_prov = p2, uco_role = r2, uco_rty = tyr2, uco_cvs = cvs2 }) + in_co1@(UnivCo { uco_prov = p1, uco_role = r1, uco_lty = tyl1, uco_deps = deps1 }) + in_co2@(UnivCo { uco_prov = p2, uco_role = r2, uco_rty = tyr2, uco_deps = deps2 }) | p1 == p2 -- If the provenances are different, opt'ing will be very confusing = assert (r1 == r2) $ fireTransRule "UnivCo" in_co1 in_co2 $ - mkUnivCo p1 (cvs1 `unionDVarSet` cvs2) r1 tyl1 tyr2 + mkUnivCo p1 (deps1 ++ deps2) r1 tyl1 tyr2 -- Push transitivity down through matching top-level constructors. opt_trans_rule is in_co1@(TyConAppCo r1 tc1 cos1) in_co2@(TyConAppCo r2 tc2 cos2) ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -2462,13 +2462,10 @@ lintCoercion co@(FunCo { fco_role = r, fco_afl = afl, fco_afr = afr -- See Note [Bad unsafe coercion] lintCoercion co@(UnivCo { uco_role = r - , uco_lty = ty1, uco_rty = ty2, uco_cvs = cvs }) + , uco_lty = ty1, uco_rty = ty2, uco_deps = deps }) = do { ty1' <- lintType ty1 ; ty2' <- lintType ty2 - ; subst <- getSubst - ; mapM_ (checkTyCoVarInScope subst) (dVarSetElems cvs) - -- Don't bother to return substituted fvs; - -- they don't matter to Lint + ; deps' <- mapM lintCoercion deps ; let k1 = typeKind ty1' k2 = typeKind ty2' @@ -2476,7 +2473,7 @@ lintCoercion co@(UnivCo { uco_role = r && isTYPEorCONSTRAINT k2) (checkTypes ty1 ty2) - ; return (co { uco_lty = ty1', uco_rty = ty2' }) } + ; return (co { uco_lty = ty1', uco_rty = ty2', uco_deps = deps' }) } where report s = hang (text $ "Unsafe coercion: " ++ s) 2 (vcat [ text "From:" <+> ppr ty1 ===================================== compiler/GHC/Core/TyCo/FVs.hs ===================================== @@ -652,8 +652,8 @@ tyCoFVsOfCo (HoleCo h) fv_cand in_scope acc = tyCoFVsOfCoVar (coHoleCoVar h) fv_cand in_scope acc -- See Note [CoercionHoles and coercion free variables] tyCoFVsOfCo (AxiomInstCo _ _ cos) fv_cand in_scope acc = tyCoFVsOfCos cos fv_cand in_scope acc -tyCoFVsOfCo (UnivCo { uco_lty = t1, uco_rty = t2, uco_cvs = cvs}) fv_cand in_scope acc - = (tyCoFVsOfCVs cvs `unionFV` tyCoFVsOfType t1 +tyCoFVsOfCo (UnivCo { uco_lty = t1, uco_rty = t2, uco_deps = deps}) fv_cand in_scope acc + = (tyCoFVsOfCos deps `unionFV` tyCoFVsOfType t1 `unionFV` tyCoFVsOfType t2) fv_cand in_scope acc tyCoFVsOfCo (SymCo co) fv_cand in_scope acc = tyCoFVsOfCo co fv_cand in_scope acc tyCoFVsOfCo (TransCo co1 co2) fv_cand in_scope acc = (tyCoFVsOfCo co1 `unionFV` tyCoFVsOfCo co2) fv_cand in_scope acc @@ -668,10 +668,6 @@ tyCoFVsOfCoVar :: CoVar -> FV tyCoFVsOfCoVar v fv_cand in_scope acc = (unitFV v `unionFV` tyCoFVsOfType (varType v)) fv_cand in_scope acc -tyCoFVsOfCVs :: DCoVarSet -> FV -tyCoFVsOfCVs cvs _ _ (have, haveSet) - = (dVarSetElems cvs ++ have, dVarSetToVarSet cvs `unionVarSet` haveSet) - tyCoFVsOfCos :: [Coercion] -> FV tyCoFVsOfCos [] fv_cand in_scope acc = emptyFV fv_cand in_scope acc tyCoFVsOfCos (co:cos) fv_cand in_scope acc = (tyCoFVsOfCo co `unionFV` tyCoFVsOfCos cos) fv_cand in_scope acc @@ -706,8 +702,8 @@ almost_devoid_co_var_of_co (CoVarCo v) cv = v /= cv almost_devoid_co_var_of_co (HoleCo h) cv = (coHoleCoVar h) /= cv almost_devoid_co_var_of_co (AxiomInstCo _ _ cos) cv = almost_devoid_co_var_of_cos cos cv -almost_devoid_co_var_of_co (UnivCo { uco_lty = t1, uco_rty = t2, uco_cvs = cvs }) cv - = not (cv `elemDVarSet` cvs) +almost_devoid_co_var_of_co (UnivCo { uco_lty = t1, uco_rty = t2, uco_deps = deps }) cv + = almost_devoid_co_var_of_cos deps cv && almost_devoid_co_var_of_type t1 cv && almost_devoid_co_var_of_type t2 cv almost_devoid_co_var_of_co (SymCo co) cv ===================================== compiler/GHC/Core/TyCo/Rep.hs ===================================== @@ -77,7 +77,7 @@ import {-# SOURCE #-} GHC.Core.Type( chooseFunTyFlag, typeKind, typeTypeOrConstr -- friends: import GHC.Types.Var -import GHC.Types.Var.Set( DCoVarSet, dVarSetElems, elemVarSet ) +import GHC.Types.Var.Set( elemVarSet ) import GHC.Core.TyCon import GHC.Core.Coercion.Axiom @@ -915,9 +915,7 @@ data Coercion | UnivCo { uco_prov :: UnivCoProvenance , uco_role :: Role , uco_lty, uco_rty :: Type - , uco_cvs :: !DCoVarSet -- Free coercion variables - -- The set must contain all the in-scope coercion variables - -- that the the proof represented by the coercion makes use of. + , uco_deps :: [Coercion] -- Coercions on which it depends -- See Note [The importance of tracking free coercion variables]. } -- Of kind (lty ~role rty) @@ -1956,9 +1954,9 @@ foldTyCo (TyCoFolder { tcf_view = view go_co env (CoVarCo cv) = covar env cv go_co env (AxiomInstCo _ _ args) = go_cos env args go_co env (HoleCo hole) = cohole env hole - go_co env (UnivCo { uco_lty = t1, uco_rty = t2, uco_cvs = cvs }) + go_co env (UnivCo { uco_lty = t1, uco_rty = t2, uco_deps = deps }) = go_ty env t1 `mappend` go_ty env t2 - `mappend` go_cvs env cvs + `mappend` go_cos env deps go_co env (SymCo co) = go_co env co go_co env (TransCo c1 c2) = go_co env c1 `mappend` go_co env c2 go_co env (AxiomRuleCo _ cos) = go_cos env cos @@ -1977,10 +1975,6 @@ foldTyCo (TyCoFolder { tcf_view = view where env' = tycobinder env tv Inferred - -- See Note [Use explicit recursion in foldTyCo] - go_cvs env cvs = foldr (add_one env) mempty (dVarSetElems cvs) - add_one env cv acc = covar env cv `mappend` acc - -- | A view function that looks through nothing. noView :: Type -> Maybe Type noView _ = Nothing ===================================== compiler/GHC/Core/TyCo/Subst.hs ===================================== @@ -878,8 +878,7 @@ subst_co subst co go :: Coercion -> Coercion go (Refl ty) = mkNomReflCo $! (go_ty ty) go (GRefl r ty mco) = (mkGReflCo r $! (go_ty ty)) $! (go_mco mco) - go (TyConAppCo r tc args)= let args' = map go args - in args' `seqList` mkTyConAppCo r tc args' + go (TyConAppCo r tc args)= mkTyConAppCo r tc $! go_cos args go (AppCo co arg) = (mkAppCo $! go co) $! go arg go (ForAllCo tv visL visR kind_co co) = case substForAllCoBndrUnchecked subst tv kind_co of @@ -889,8 +888,8 @@ subst_co subst co go (CoVarCo cv) = substCoVar subst cv go (AxiomInstCo con ind cos) = mkAxiomInstCo con ind $! map go cos go (UnivCo { uco_prov = p, uco_role = r - , uco_lty = t1, uco_rty = t2, uco_cvs = cvs }) - = ((((mkUnivCo $! p) $! go_cvs cvs) $! r) $! + , uco_lty = t1, uco_rty = t2, uco_deps = deps }) + = ((((mkUnivCo $! p) $! go_cos deps) $! r) $! (go_ty t1)) $! (go_ty t2) go (SymCo co) = mkSymCo $! (go co) go (TransCo co1 co2) = (mkTransCo $! (go co1)) $! (go co2) @@ -903,7 +902,8 @@ subst_co subst co in cs1 `seqList` AxiomRuleCo c cs1 go (HoleCo h) = HoleCo $! go_hole h - go_cvs cvs = substDCoVarSet subst cvs + go_cos cos = let cos' = map go cos + in cos' `seqList` cos' -- See Note [Substituting in a coercion hole] go_hole h@(CoercionHole { ch_co_var = cv }) ===================================== compiler/GHC/Core/TyCo/Tidy.hs ===================================== @@ -239,7 +239,7 @@ tidyCo env@(_, subst) co go (AxiomInstCo con ind cos) = AxiomInstCo con ind $! strictMap go cos go co@(UnivCo { uco_lty = t1, uco_rty = t2 }) = co { uco_lty = tidyType env t1, uco_rty = tidyType env t2 } - -- Don't bother to tidy the uco_cvs field + -- Don't bother to tidy the uco_deps field go (SymCo co) = SymCo $! go co go (TransCo co1 co2) = (TransCo $! go co1) $! go co2 go (SelCo d co) = SelCo d $! go co ===================================== compiler/GHC/Core/Type.hs ===================================== @@ -967,9 +967,9 @@ mapTyCoX (TyCoMapper { tcm_tyvar = tyvar go_co !env (CoVarCo cv) = covar env cv go_co !env (HoleCo hole) = cohole env hole go_co !env (UnivCo { uco_prov = p, uco_role = r - , uco_lty = t1, uco_rty = t2, uco_cvs = cvs }) + , uco_lty = t1, uco_rty = t2, uco_deps = deps }) = mkUnivCo <$> pure p - <*> go_fcvs env (dVarSetElems cvs) + <*> go_cos env deps <*> pure r <*> go_ty env t1 <*> go_ty env t2 go_co !env (SymCo co) = mkSymCo <$> go_co env co @@ -1000,12 +1000,6 @@ mapTyCoX (TyCoMapper { tcm_tyvar = tyvar ; return $ mkForAllCo tv' visL visR kind_co' co' } -- See Note [Efficiency for ForAllCo case of mapTyCoX] - -- See Note [Use explicit recursion in mapTyCo] - go_fcvs :: env -> [CoVar] -> m DTyCoVarSet - go_fcvs _ [] = return emptyDVarSet - go_fcvs env (cv:cvs) = do { co <- covar env cv - ; cvs' <- go_fcvs env cvs - ; return (tyCoVarsOfCoDSet co `unionDVarSet` cvs') } {- Note [Use explicit recursion in mapTyCo] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/CoreToIface.hs ===================================== @@ -88,7 +88,6 @@ import GHC.Utils.Panic import GHC.Utils.Misc import Data.Maybe ( isNothing, catMaybes ) -import Data.List ( partition ) {- Note [Avoiding space leaks in toIface*] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -299,12 +298,8 @@ toIfaceCoercionX fr co go (SubCo co) = IfaceSubCo (go co) go (AxiomRuleCo co cs) = IfaceAxiomRuleCo (mkIfLclName (coaxrName co)) (map go cs) go (AxiomInstCo c i cs) = IfaceAxiomInstCo (coAxiomName c) i (map go cs) - go (UnivCo { uco_prov = p, uco_role = r, uco_lty = t1, uco_rty = t2, uco_cvs = cvs }) - = IfaceUnivCo p r - (toIfaceTypeX fr t1) (toIfaceTypeX fr t2) - (map toIfaceCoVar bound_cvs) free_cvs - where - (free_cvs, bound_cvs) = partition (`elemVarSet` fr) (dVarSetElems cvs) + go (UnivCo { uco_prov = p, uco_role = r, uco_lty = t1, uco_rty = t2, uco_deps = deps }) + = IfaceUnivCo p r (toIfaceTypeX fr t1) (toIfaceTypeX fr t2) (map go deps) go co@(TyConAppCo r tc cos) = assertPpr (isNothing (tyConAppFunCo_maybe r tc cos)) (ppr co) $ ===================================== compiler/GHC/Iface/Rename.hs ===================================== @@ -676,8 +676,8 @@ rnIfaceCo (IfaceCoVarCo lcl) = IfaceCoVarCo <$> pure lcl rnIfaceCo (IfaceHoleCo lcl) = IfaceHoleCo <$> pure lcl rnIfaceCo (IfaceAxiomInstCo n i cs) = IfaceAxiomInstCo <$> rnIfaceGlobal n <*> pure i <*> mapM rnIfaceCo cs -rnIfaceCo (IfaceUnivCo s r t1 t2 cvs fcvs) - = IfaceUnivCo s r <$> rnIfaceType t1 <*> rnIfaceType t2 <*> pure cvs <*> pure fcvs +rnIfaceCo (IfaceUnivCo s r t1 t2 deps) + = IfaceUnivCo s r <$> rnIfaceType t1 <*> rnIfaceType t2 <*> mapM rnIfaceCo deps -- Renaming affects only type constructors, not coercion variables, -- so no need to recurse into the free-var fields rnIfaceCo (IfaceSymCo c) ===================================== compiler/GHC/Iface/Syntax.hs ===================================== @@ -1783,9 +1783,9 @@ freeNamesIfCoercion (IfaceCoVarCo _) = emptyNameSet freeNamesIfCoercion (IfaceHoleCo _) = emptyNameSet freeNamesIfCoercion (IfaceAxiomInstCo ax _ cos) = unitNameSet ax &&& fnList freeNamesIfCoercion cos -freeNamesIfCoercion (IfaceUnivCo _ _ t1 t2 _ _) +freeNamesIfCoercion (IfaceUnivCo _ _ t1 t2 _) = freeNamesIfType t1 &&& freeNamesIfType t2 - -- Ignoring free-var fields, which are all local, + -- Ignoring uco_deps field, which are all local, -- and don't contribute to dependency analysis freeNamesIfCoercion (IfaceSymCo c) = freeNamesIfCoercion c ===================================== compiler/GHC/Iface/Type.hs ===================================== @@ -481,9 +481,7 @@ data IfaceCoercion -- ^ There are only a fixed number of CoAxiomRules, so it suffices -- to use an IfaceLclName to distinguish them. -- See Note [Adding built-in type families] in GHC.Builtin.Types.Literals - | IfaceUnivCo UnivCoProvenance Role IfaceType IfaceType [IfLclName] [Var] - -- ^ Local covars and open (free) covars resp - -- See Note [Free TyVars and CoVars in IfaceType] + | IfaceUnivCo UnivCoProvenance Role IfaceType IfaceType [IfaceCoercion] | IfaceSymCo IfaceCoercion | IfaceTransCo IfaceCoercion IfaceCoercion | IfaceSelCo CoSel IfaceCoercion @@ -701,9 +699,7 @@ substIfaceType env ty go_co (IfaceCoVarCo cv) = IfaceCoVarCo cv go_co (IfaceHoleCo cv) = IfaceHoleCo cv go_co (IfaceAxiomInstCo a i cos) = IfaceAxiomInstCo a i (go_cos cos) - go_co (IfaceUnivCo prov r t1 t2 cvs fvs) = IfaceUnivCo prov r (go t1) (go t2) cvs fvs - -- Don't bother to substitute in free vars - -- See Note [Substitution on IfaceType] + go_co (IfaceUnivCo p r t1 t2 ds) = IfaceUnivCo p r (go t1) (go t2) (go_cos ds) go_co (IfaceSymCo co) = IfaceSymCo (go_co co) go_co (IfaceTransCo co1 co2) = IfaceTransCo (go_co co1) (go_co co2) go_co (IfaceSelCo n co) = IfaceSelCo n (go_co co) @@ -2003,9 +1999,9 @@ ppr_co _ (IfaceFreeCoVar covar) = ppr covar ppr_co _ (IfaceCoVarCo covar) = ppr covar ppr_co _ (IfaceHoleCo covar) = braces (ppr covar) -ppr_co _ (IfaceUnivCo prov role ty1 ty2 cvs fvs) +ppr_co _ (IfaceUnivCo prov role ty1 ty2 ds) = text "Univ" <> (parens $ - sep [ ppr role <+> ppr prov <> ppr cvs <> ppr fvs + sep [ ppr role <+> ppr prov <> ppr ds , dcolon <+> ppr ty1 <> comma <+> ppr ty2 ]) ppr_co ctxt_prec (IfaceInstCo co ty) @@ -2370,15 +2366,13 @@ instance Binary IfaceCoercion where put_ bh a put_ bh b put_ bh c - put_ bh (IfaceUnivCo a b c d cvs fcvs) = do + put_ bh (IfaceUnivCo a b c d deps) = do putByte bh 9 put_ bh a put_ bh b put_ bh c put_ bh d - assertPpr (null fcvs) (ppr cvs $$ ppr fcvs) $ - -- See Note [Free TyVars and CoVars in IfaceType] - put_ bh cvs + put_ bh deps put_ bh (IfaceSymCo a) = do putByte bh 10 put_ bh a @@ -2452,8 +2446,8 @@ instance Binary IfaceCoercion where b <- get bh c <- get bh d <- get bh - cvs <- get bh - return $ IfaceUnivCo a b c d cvs [] + deps <- get bh + return $ IfaceUnivCo a b c d deps 10-> do a <- get bh return $ IfaceSymCo a 11-> do a <- get bh @@ -2516,8 +2510,7 @@ instance NFData IfaceCoercion where IfaceCoVarCo f1 -> rnf f1 IfaceAxiomInstCo f1 f2 f3 -> rnf f1 `seq` rnf f2 `seq` rnf f3 IfaceAxiomRuleCo f1 f2 -> rnf f1 `seq` rnf f2 - IfaceUnivCo f1 f2 f3 f4 cvs fcvs -> rnf f1 `seq` f2 `seq` rnf f3 `seq` rnf f4 - `seq` rnf cvs `seq` rnf fcvs + IfaceUnivCo f1 f2 f3 f4 deps -> rnf f1 `seq` f2 `seq` rnf f3 `seq` rnf f4 `seq` rnf deps IfaceSymCo f1 -> rnf f1 IfaceTransCo f1 f2 -> rnf f1 `seq` rnf f2 IfaceSelCo f1 f2 -> rnf f1 `seq` rnf f2 ===================================== compiler/GHC/IfaceToCore.hs ===================================== @@ -1471,15 +1471,13 @@ tcIfaceCo = go go (IfaceForAllCo tv visL visR k c) = do { k' <- go k ; bindIfaceBndr tv $ \ tv' -> ForAllCo tv' visL visR k' <$> go c } - go (IfaceCoVarCo n) = CoVarCo <$> go_var n - go (IfaceAxiomInstCo n i cs) = AxiomInstCo <$> tcIfaceCoAxiom n <*> pure i <*> mapM go cs - go (IfaceUnivCo p r t1 t2 cvs fcvs) - = do { t1' <- tcIfaceType t1; t2' <- tcIfaceType t2 - ; cvs' <- assertPpr (null fcvs) (ppr fcvs) $ - mapM tcIfaceLclId cvs - ; return (UnivCo { uco_prov = p, uco_role = r - , uco_lty = t1', uco_rty = t2' - , uco_cvs = mkDVarSet cvs' }) } + go (IfaceCoVarCo n) = CoVarCo <$> go_var n + go (IfaceAxiomInstCo n i cs) = AxiomInstCo <$> tcIfaceCoAxiom n <*> pure i <*> mapM go cs + go (IfaceUnivCo p r t1 t2 ds) = do { t1' <- tcIfaceType t1; t2' <- tcIfaceType t2 + ; ds' <- mapM go ds + ; return (UnivCo { uco_prov = p, uco_role = r + , uco_lty = t1', uco_rty = t2' + , uco_deps = ds' }) } go (IfaceSymCo c) = SymCo <$> go c go (IfaceTransCo c1 c2) = TransCo <$> go c1 <*> go c2 ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -1564,10 +1564,10 @@ collect_cand_qtvs_co orig_ty cur_lvl bound = go_co go_co dv (FunCo _ _ _ w co1 co2) = foldlM go_co dv [w, co1, co2] go_co dv (AxiomInstCo _ _ cos) = foldlM go_co dv cos go_co dv (AxiomRuleCo _ cos) = foldlM go_co dv cos - go_co dv (UnivCo { uco_lty = t1, uco_rty = t2, uco_cvs = cvs }) + go_co dv (UnivCo { uco_lty = t1, uco_rty = t2, uco_deps = deps }) = do { dv1 <- collect_cand_qtvs orig_ty True cur_lvl bound dv t1 ; dv2 <- collect_cand_qtvs orig_ty True cur_lvl bound dv1 t2 - ; strictFoldDVarSet zt_cv (return dv2) cvs } + ; foldM go_co dv2 deps } go_co dv (SymCo co) = go_co dv co go_co dv (TransCo co1 co2) = foldlM go_co dv [co1, co2] go_co dv (SelCo _ co) = go_co dv co ===================================== testsuite/tests/pmcheck/should_compile/T11195.hs ===================================== @@ -75,18 +75,10 @@ opt_trans_rule is in_co1@(InstCo co1 ty1) in_co2@(InstCo co2 ty2) | ty1 `eqCoercion` ty2 , co1 `compatible_co` co2 = undefined -opt_trans_rule is in_co1@(UnivCo p1 r1 tyl1 _tyr1 _fvs1) - in_co2@(UnivCo p2 r2 _tyl2 tyr2 _fvs2) - | Just prov' <- opt_trans_prov p1 p2 = undefined - where +opt_trans_rule is (UnivCo { uco_prov = p1 }) + (UnivCo ( uco_prov = p2 }) + | p1 == p2 = undefined -- if the provenances are different, opt'ing will be very confusing - opt_trans_prov PhantomProv PhantomProv - = Just $ PhantomProv - opt_trans_prov ProofIrrelProv ProofIrrelProv - = Just $ ProofIrrelProv - opt_trans_prov (PluginProv str1 _) (PluginProv str2 _) - | str1 == str2 = Just p1 - opt_trans_prov _ _ = Nothing -- Push transitivity down through matching top-level constructors. opt_trans_rule is in_co1@(TyConAppCo r1 tc1 cos1) ===================================== testsuite/tests/tcplugins/CtIdPlugin.hs ===================================== @@ -42,7 +42,7 @@ solver :: [String] -> PluginDefs -> EvBindsVar -> [Ct] -> [Ct] -> TcPluginM TcPluginSolveResult solver _args defs ev givens wanteds = do - let pluginCo = mkUnivCo (PluginProv "CtIdPlugin" emptyUniqDSet) Representational -- Empty is fine. This plugin does not use "givens". + let pluginCo = mkUnivCo (PluginProv "CtIdPlugin") emptyUniqDSet Representational -- Empty is fine. This plugin does not use "givens". let substEvidence ct ct' = evCast (ctEvExpr $ ctEvidence ct') $ pluginCo (ctPred ct') (ctPred ct) ===================================== testsuite/tests/tcplugins/RewritePlugin.hs ===================================== @@ -87,5 +87,5 @@ mkTyFamReduction :: TyCon -> [ Type ] -> Type -> Reduction mkTyFamReduction tyCon args res = Reduction co res where co :: Coercion - co = mkUnivCo ( PluginProv "RewritePlugin" emptyUniqDSet) Nominal -- Empty is fine. This plugin does not use "givens". + co = mkUnivCo ( PluginProv "RewritePlugin") emptyUniqDSet Nominal -- Empty is fine. This plugin does not use "givens". ( mkTyConApp tyCon args ) res ===================================== testsuite/tests/tcplugins/TyFamPlugin.hs ===================================== @@ -80,6 +80,6 @@ solveCt ( PluginDefs {..} ) ct@( classifyPredType . ctPred -> EqPred NomEq lhs r , let evTerm :: EvTerm evTerm = EvExpr . Coercion - $ mkUnivCo ( PluginProv "TyFamPlugin" emptyUniqDSet) Nominal lhs rhs -- Empty is fine. This plugin does not use "givens". + $ mkUnivCo ( PluginProv "TyFamPlugin") emptyUniqDSet Nominal lhs rhs -- Empty is fine. This plugin does not use "givens". = pure $ Just ( evTerm, ct ) solveCt _ ct = pure Nothing View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e2142bf459a39d1c9ac18c1719b4127ff314d840 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e2142bf459a39d1c9ac18c1719b4127ff314d840 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 13:04:32 2024 From: gitlab at gitlab.haskell.org (Hannes Siebenhandl (@fendor)) Date: Wed, 12 Jun 2024 09:04:32 -0400 Subject: [Git][ghc/ghc][wip/fendor/ghc-iface-sharing-avoid-reserialisation] 53 commits: Migrate `Finder` component to `OsPath`, fixed #24616 Message-ID: <66699ce0b1c30_167e4dc93d1c21832@gitlab.mail> Hannes Siebenhandl pushed to branch wip/fendor/ghc-iface-sharing-avoid-reserialisation at Glasgow Haskell Compiler / GHC Commits: c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - c5e7b418 by Fendor at 2024-06-12T15:04:12+02:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - c3d98201 by Fendor at 2024-06-12T15:04:12+02:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-linux job, where the number of allocated bytes seems to be lower than in other jobs. - - - - - 30 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core/Opt/Simplify.hs - + compiler/GHC/Data/OsPath.hs - compiler/GHC/Data/Strict.hs - compiler/GHC/Driver/Backpack.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/Config/Cmm.hs - compiler/GHC/Driver/Config/Finder.hs - compiler/GHC/Driver/Config/StgToCmm.hs - compiler/GHC/Driver/DynFlags.hs - compiler/GHC/Driver/Flags.hs - compiler/GHC/Driver/Main.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/12d59b3b208ca8a88eecc88e9b4fa5fc651e55bc...c3d98201a9e63a7a178090678806636f7b5ce230 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/12d59b3b208ca8a88eecc88e9b4fa5fc651e55bc...c3d98201a9e63a7a178090678806636f7b5ce230 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 13:14:50 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Wed, 12 Jun 2024 09:14:50 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] fix regUsageOfInstr INSERTPS Message-ID: <66699f4ae22a7_167e4de817f022832@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: fa5e2b59 by sheaf at 2024-06-12T15:14:54+02:00 fix regUsageOfInstr INSERTPS - - - - - 3 changed files: - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs Changes: ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1648,7 +1648,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps (insertps 48) where insertps off = - INSERTPS f (OpImm $ litToImm $ CmmInt off W32) (OpAddr addr) dst + INSERTPS f (litToImm $ CmmInt off W32) (OpAddr addr) dst in return $ Any f code vector_float_broadcast_sse _ _ c _ @@ -1721,13 +1721,13 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps .|. shiftL dst 4 vec src = if src >= 4 then v2 else v1 in unitOL - (INSERTPS fmt (OpImm $ ImmInt $ insertImm i1 0 .|. 0b1110) (OpReg $ vec i1) dst) + (INSERTPS fmt (ImmInt $ insertImm i1 0 .|. 0b1110) (OpReg $ vec i1) dst) `snocOL` - (INSERTPS fmt (OpImm $ ImmInt $ insertImm i2 1) (OpReg $ vec i2) dst) + (INSERTPS fmt (ImmInt $ insertImm i2 1) (OpReg $ vec i2) dst) `snocOL` - (INSERTPS fmt (OpImm $ ImmInt $ insertImm i3 2) (OpReg $ vec i3) dst) + (INSERTPS fmt (ImmInt $ insertImm i3 2) (OpReg $ vec i3) dst) `snocOL` - (INSERTPS fmt (OpImm $ ImmInt $ insertImm i4 3) (OpReg $ vec i4) dst) + (INSERTPS fmt (ImmInt $ insertImm i4 3) (OpReg $ vec i4) dst) _ -> pprPanic "vector shuffle: wrong number of indices (expected 4)" (ppr is) _ -> pprPanic "vector shuffle: unsupported format" (ppr fmt) @@ -1770,7 +1770,7 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps imm = litToImm offset code dst = exp `appOL` (fn dst) `snocOL` - (INSERTPS fmt (OpImm imm) (OpReg r) dst) + (INSERTPS fmt imm (OpReg r) dst) in return $ Any fmt code -- DoubleX2 vector_float_insert len at 2 W64 vecExpr valExpr (CmmLit offset) ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -361,8 +361,8 @@ data Instr -- NOTE: Instructions follow the AT&T syntax -- Constructors and deconstructors | VBROADCAST Format AddrMode Reg - | VEXTRACT Format Operand Reg Operand - | INSERTPS Format Operand Operand Reg + | VEXTRACT Format Imm Reg Operand + | INSERTPS Format Imm Operand Reg -- move operations | VMOVU Format Operand Operand @@ -505,9 +505,18 @@ regUsageOfInstr platform instr -- vector instructions VBROADCAST fmt src dst -> mkRU fmt (use_EA src []) [dst] - VEXTRACT fmt off src dst -> mkRU fmt ((use_R off []) ++ [src]) (use_R dst []) - INSERTPS fmt off src dst - -> mkRU fmt ((use_R off []) ++ (use_R src [])) [dst] + VEXTRACT fmt _off src dst -> mkRU fmt [src] (use_R dst []) + INSERTPS fmt (ImmInt off) src dst + -> mkRU fmt ((use_R src []) ++ [dst | not doesNotReadDst]) [dst] + where + -- Compute whether the instruction reads the destination register or not. + -- Immediate bits: ss_dd_zzzz s = src pos, d = dst pos, z = zeroed components. + doesNotReadDst = and [ testBit off i | i <- [0, 1, 2, 3], i /= pos ] + -- Check whether the positions in which we are not inserting + -- are being zeroed. + where pos = ( off `shiftR` 4 ) .&. 0b11 + INSERTPS fmt _off src dst + -> mkRU fmt ((use_R src []) ++ [dst]) [dst] VMOVU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) MOVU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) @@ -713,9 +722,9 @@ patchRegsOfInstr instr env -- vector instructions VBROADCAST fmt src dst -> VBROADCAST fmt (lookupAddr src) (env dst) VEXTRACT fmt off src dst - -> VEXTRACT fmt (patchOp off) (env src) (patchOp dst) + -> VEXTRACT fmt off (env src) (patchOp dst) INSERTPS fmt off src dst - -> INSERTPS fmt (patchOp off) (patchOp src) (env dst) + -> INSERTPS fmt off (patchOp src) (env dst) VMOVU fmt src dst -> VMOVU fmt (patchOp src) (patchOp dst) MOVU fmt src dst -> MOVU fmt (patchOp src) (patchOp dst) ===================================== compiler/GHC/CmmToAsm/X86/Ppr.hs ===================================== @@ -965,7 +965,7 @@ pprInstr platform i = case i of VPXOR format s1 s2 dst -> pprXor (text "vpxor") format s1 s2 dst VEXTRACT format offset from to - -> pprFormatOpRegOp (text "vextract") format offset from to + -> pprFormatImmRegOp (text "vextract") format offset from to INSERTPS format offset addr dst -> pprInsert (text "insertps") format offset addr dst VPSHUFD format offset src dst @@ -1098,11 +1098,11 @@ pprInstr platform i = case i of pprOperand platform out_fmt op2 ] - pprFormatOpRegOp :: Line doc -> Format -> Operand -> Reg -> Operand -> doc - pprFormatOpRegOp name format off reg1 op2 + pprFormatImmRegOp :: Line doc -> Format -> Imm -> Reg -> Operand -> doc + pprFormatImmRegOp name format off reg1 op2 = line $ hcat [ pprMnemonic name format, - pprOperand platform format off, + pprDollImm off, comma, pprReg platform format reg1, comma, @@ -1252,11 +1252,11 @@ pprInstr platform i = case i of pprReg platform format reg3 ] - pprInsert :: Line doc -> Format -> Operand -> Operand -> Reg -> doc + pprInsert :: Line doc -> Format -> Imm -> Operand -> Reg -> doc pprInsert name format off src dst = line $ hcat [ pprGenMnemonic name format, - pprOperand platform format off, + pprDollImm off, comma, pprOperand platform format src, comma, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fa5e2b59dd27f21470c3ca4053fc986fe6a670e9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fa5e2b59dd27f21470c3ca4053fc986fe6a670e9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 13:55:42 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 12 Jun 2024 09:55:42 -0400 Subject: [Git][ghc/ghc][wip/T24978] Wibble Message-ID: <6669a8deed7ac_167e4d1492824270f3@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24978 at Glasgow Haskell Compiler / GHC Commits: 7f1277fa by Simon Peyton Jones at 2024-06-12T14:55:24+01:00 Wibble - - - - - 1 changed file: - compiler/GHC/Tc/Utils/TcMType.hs Changes: ===================================== compiler/GHC/Tc/Utils/TcMType.hs ===================================== @@ -1591,9 +1591,6 @@ collect_cand_qtvs_co orig_ty cur_lvl bound = go_co go_mco dv MRefl = return dv go_mco dv (MCo co) = go_co dv co - zt_cv :: CoVar -> TcM CandidatesQTvs -> TcM CandidatesQTvs - zt_cv cv mdvs = do { dvs <- mdvs; go_cv dvs cv } - go_cv :: CandidatesQTvs -> CoVar -> TcM CandidatesQTvs go_cv dv@(DV { dv_cvs = cvs }) cv | is_bound cv = return dv View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7f1277fa179cc1e9450f05c3c20dbeedc00c70ab -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7f1277fa179cc1e9450f05c3c20dbeedc00c70ab You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 15:11:01 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Wed, 12 Jun 2024 11:11:01 -0400 Subject: [Git][ghc/ghc][wip/T14030] 3 commits: Derive previously hand-written `Lift` instances (#14030) Message-ID: <6669ba85e8667_167e4d1e1e9b0429c4@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: 2481be6b by Sebastian Graf at 2024-06-12T17:08:29+02:00 Derive previously hand-written `Lift` instances (#14030) This is possible now that #22229 is fixed. - - - - - 6f80a12c by Sebastian Graf at 2024-06-12T17:10:39+02:00 Remove RULE TH:lift (#24983) This RULE bears the risk of making `lift` output dependent on optimisation level and is superseded by the overlapping `Lift [Char]` instance. Fixes #24983. - - - - - 4ee6eb87 by Sebastian Graf at 2024-06-12T17:10:39+02:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. - - - - - 7 changed files: - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - testsuite/tests/ghci/scripts/T21110.stderr - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/th/T3600.stderr - testsuite/tests/th/TH_Lift.hs Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs ===================================== @@ -12,6 +12,9 @@ {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UnboxedSums #-} {-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE DeriveLift #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE FlexibleInstances #-} {-# OPTIONS_GHC -fno-warn-inline-rule-shadowing #-} -- | This module gives the definition of the 'Lift' class. @@ -39,7 +42,7 @@ module GHC.Internal.TH.Lift where import GHC.Internal.TH.Syntax -import GHC.Internal.TH.Lib () -- See wrinkle (W4) of Note [Tracking dependencies on primitives] +import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives] import GHC.Internal.Lexeme ( startsVarSym, startsVarId ) import GHC.Internal.Data.Either @@ -52,7 +55,7 @@ import GHC.Internal.Integer import GHC.Internal.Real import GHC.Internal.Word import GHC.Internal.Int -import GHC.Internal.Data.Data +import GHC.Internal.Data.Data hiding (Fixity) import GHC.Internal.Natural -- | A 'Lift' instance can have any of its values turned into a Template @@ -95,6 +98,11 @@ class Lift (t :: TYPE r) where -- @since template-haskell-2.16.0.0 liftTyped :: Quote m => t -> Code m t +----------------------------------------------------- +-- +-- Manual instances for lifting to Literals +-- +----------------------------------------------------- -- If you add any instances here, consider updating test th/TH_Lift instance Lift Integer where @@ -186,12 +194,6 @@ instance Lift Char# where liftTyped x = unsafeCodeCoerce (lift x) lift x = return (LitE (CharPrimL (C# x))) -instance Lift Bool where - liftTyped x = unsafeCodeCoerce (lift x) - - lift True = return (ConE trueName) - lift False = return (ConE falseName) - -- | Produces an 'Addr#' literal from the NUL-terminated C-string starting at -- the given memory address. -- @@ -201,213 +203,81 @@ instance Lift Addr# where lift x = return (LitE (StringPrimL (map (fromIntegral . ord) (unpackCString# x)))) -instance Lift a => Lift (Maybe a) where - liftTyped x = unsafeCodeCoerce (lift x) - - lift Nothing = return (ConE nothingName) - lift (Just x) = liftM (ConE justName `AppE`) (lift x) - -instance (Lift a, Lift b) => Lift (Either a b) where - liftTyped x = unsafeCodeCoerce (lift x) - - lift (Left x) = liftM (ConE leftName `AppE`) (lift x) - lift (Right y) = liftM (ConE rightName `AppE`) (lift y) - -instance Lift a => Lift [a] where - liftTyped x = unsafeCodeCoerce (lift x) - lift xs = do { xs' <- mapM lift xs; return (ListE xs') } +instance {-# OVERLAPPING #-} Lift [Char] where + lift = liftString + liftTyped = unsafeCodeCoerce . lift liftString :: Quote m => String -> m Exp -- Used in GHC.Tc.Gen.Expr to short-circuit the lifting for strings liftString s = return (LitE (StringL s)) --- | @since template-haskell-2.15.0.0 -instance Lift a => Lift (NonEmpty a) where - liftTyped x = unsafeCodeCoerce (lift x) - - lift (x :| xs) = do - x' <- lift x - xs' <- lift xs - return (InfixE (Just x') (ConE nonemptyName) (Just xs')) +----------------------------------------------------- +-- +-- Derived instances for base data types +-- +----------------------------------------------------- +deriving instance {-# OVERLAPPABLE #-} Lift a => Lift [a] +deriving instance Lift Bool +deriving instance Lift a => Lift (Maybe a) +deriving instance (Lift a, Lift b) => Lift (Either a b) -- | @since template-haskell-2.15.0.0 -instance Lift Void where - liftTyped = liftCode . absurd - lift = pure . absurd - -instance Lift () where - liftTyped x = unsafeCodeCoerce (lift x) - lift () = return (ConE (tupleDataName 0)) - -instance (Lift a, Lift b) => Lift (a, b) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b) - = liftM TupE $ sequence $ map (fmap Just) [lift a, lift b] - -instance (Lift a, Lift b, Lift c) => Lift (a, b, c) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c) - = liftM TupE $ sequence $ map (fmap Just) [lift a, lift b, lift c] - -instance (Lift a, Lift b, Lift c, Lift d) => Lift (a, b, c, d) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d) - = liftM TupE $ sequence $ map (fmap Just) [lift a, lift b, lift c, lift d] - -instance (Lift a, Lift b, Lift c, Lift d, Lift e) - => Lift (a, b, c, d, e) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d, e) - = liftM TupE $ sequence $ map (fmap Just) [ lift a, lift b - , lift c, lift d, lift e ] - -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) - => Lift (a, b, c, d, e, f) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d, e, f) - = liftM TupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f ] - -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) - => Lift (a, b, c, d, e, f, g) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d, e, f, g) - = liftM TupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f, lift g ] - +deriving instance Lift a => Lift (NonEmpty a) +-- | @since template-haskell-2.15.0.0 +deriving instance Lift Void +deriving instance Lift () +deriving instance (Lift a, Lift b) + => Lift (a, b) +deriving instance (Lift a, Lift b, Lift c) + => Lift (a, b, c) +deriving instance (Lift a, Lift b, Lift c, Lift d) + => Lift (a, b, c, d) +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e) + => Lift (a, b, c, d, e) +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) + => Lift (a, b, c, d, e, f) +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) + => Lift (a, b, c, d, e, f, g) -- | @since template-haskell-2.16.0.0 -instance Lift (# #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# #) = return (ConE (unboxedTupleTypeName 0)) - +deriving instance Lift (# #) -- | @since template-haskell-2.16.0.0 -instance (Lift a) => Lift (# a #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [lift a] - +deriving instance (Lift a) + => Lift (# a #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b) => Lift (# a, b #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [lift a, lift b] - +deriving instance (Lift a, Lift b) + => Lift (# a, b #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c) - => Lift (# a, b, c #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [lift a, lift b, lift c] - +deriving instance (Lift a, Lift b, Lift c) + => Lift (# a, b, c #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d) - => Lift (# a, b, c, d #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b - , lift c, lift d ] - +deriving instance (Lift a, Lift b, Lift c, Lift d) + => Lift (# a, b, c, d #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e) - => Lift (# a, b, c, d, e #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d, e #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b - , lift c, lift d, lift e ] - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e) + => Lift (# a, b, c, d, e #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) - => Lift (# a, b, c, d, e, f #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d, e, f #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f ] - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) + => Lift (# a, b, c, d, e, f #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) - => Lift (# a, b, c, d, e, f, g #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d, e, f, g #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f - , lift g ] - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) + => Lift (# a, b, c, d, e, f, g #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b) => Lift (# a | b #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 2 - (# | y #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 2 - +deriving instance (Lift a, Lift b) => Lift (# a | b #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c) - => Lift (# a | b | c #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 3 - (# | y | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 3 - (# | | y #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 3 - +deriving instance (Lift a, Lift b, Lift c) + => Lift (# a | b | c #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d) - => Lift (# a | b | c | d #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 4 - (# | y | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 4 - (# | | y | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 4 - (# | | | y #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 4 - +deriving instance (Lift a, Lift b, Lift c, Lift d) + => Lift (# a | b | c | d #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e) - => Lift (# a | b | c | d | e #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 5 - (# | y | | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 5 - (# | | y | | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 5 - (# | | | y | #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 5 - (# | | | | y #) -> UnboxedSumE <$> lift y <*> pure 5 <*> pure 5 - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e) + => Lift (# a | b | c | d | e #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) - => Lift (# a | b | c | d | e | f #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 6 - (# | y | | | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 6 - (# | | y | | | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 6 - (# | | | y | | #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 6 - (# | | | | y | #) -> UnboxedSumE <$> lift y <*> pure 5 <*> pure 6 - (# | | | | | y #) -> UnboxedSumE <$> lift y <*> pure 6 <*> pure 6 - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) + => Lift (# a | b | c | d | e | f #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) - => Lift (# a | b | c | d | e | f | g #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 7 - (# | y | | | | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 7 - (# | | y | | | | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 7 - (# | | | y | | | #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 7 - (# | | | | y | | #) -> UnboxedSumE <$> lift y <*> pure 5 <*> pure 7 - (# | | | | | y | #) -> UnboxedSumE <$> lift y <*> pure 6 <*> pure 7 - (# | | | | | | y #) -> UnboxedSumE <$> lift y <*> pure 7 <*> pure 7 - --- TH has a special form for literal strings, --- which we should take advantage of. --- NB: the lhs of the rule has no args, so that --- the rule will apply to a 'lift' all on its own --- which happens to be the way the type checker --- creates it. -{-# RULES "TH:liftString" lift = \s -> return (LitE (StringL s)) #-} - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) + => Lift (# a | b | c | d | e | f | g #) trueName, falseName :: Name trueName = 'True @@ -424,6 +294,135 @@ rightName = 'Right nonemptyName :: Name nonemptyName = '(:|) +----------------------------------------------------- +-- +-- Lifting the TH AST +-- +----------------------------------------------------- + +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Loc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DocLoc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ModName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift GHC.Internal.TH.Syntax.Module +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameSpace +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NamespaceSpecifier +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PkgName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameFlavour +-- | @since template-haskell-2.22.1.0 +deriving instance Lift OccName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Name +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameIs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Specificity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift BndrVis +-- | @since template-haskell-2.22.1.0 +deriving instance Lift a => Lift (TyVarBndr a) +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TyLit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Type +-- | @since template-haskell-2.22.1.0 +instance Lift Bytes where + lift = Lib.litE . BytesPrimL + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Lit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pat +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Clause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivClause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivStrategy +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Overlap +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FunDep +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Safety +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Callconv +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Foreign +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ForeignSrcLang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FixityDirection +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Fixity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Inline +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleMatch +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Phases +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleBndr +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnTarget +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pragma +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceUnpackedness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DecidedStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Bang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Con +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TySynEqn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FamilyResultSig +-- | @since template-haskell-2.22.1.0 +deriving instance Lift InjectivityAnn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TypeFamilyHead +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Role +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynArgs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynDir +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Dec +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Range +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Exp +-- | @since template-haskell-2.22.1.0 +instance Lift (TExp a) where + lift (TExp e) = [| TExp $(lift e) |] + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Match +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Guard +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Stmt +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Body +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Info +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnLookup +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Extension + ----------------------------------------------------- -- -- Generic Lift implementations ===================================== libraries/template-haskell/changelog.md ===================================== @@ -1,5 +1,9 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) +## 2.22.1.0 + + * `Lift` instances were added for the `template-haskell` AST. + ## 2.22.0.0 * The kind of `Code` was changed from `forall r. (Type -> Type) -> TYPE r -> Type` ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -3,7 +3,7 @@ -- template-haskell.cabal. name: template-haskell -version: 2.22.0.0 +version: 2.22.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE ===================================== testsuite/tests/ghci/scripts/T21110.stderr ===================================== @@ -1,5 +1,5 @@ - : warning: [GHC-42258] [-Wunused-packages] The following packages were specified via -package or -package-id flags, but were not needed for compilation: - - template-haskell-2.22.0.0 (exposed by flag -package template-haskell) + - template-haskell-2.22.1.0 (exposed by flag -package template-haskell) + ===================================== testsuite/tests/interface-stability/template-haskell-exports.stdout ===================================== @@ -2420,28 +2420,88 @@ instance GHC.Internal.Show.Show GHC.Internal.LanguageExtensions.Extension -- Def instance GHC.Internal.Show.Show GHC.Internal.TH.Ppr.ForallVisFlag -- Defined in ‘GHC.Internal.TH.Ppr’ instance [safe] GHC.Internal.Show.Show GHC.Internal.TH.PprLib.Doc -- Defined in ‘GHC.Internal.TH.PprLib’ instance GHC.Internal.Show.Show GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.ForeignSrcLang’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnLookup -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnTarget -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.BndrVis -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Body -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Bool -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bytes -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Callconv -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Char -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Clause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Con -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Dec -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DecidedStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivClause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivStrategy -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DocLoc -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Double -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (GHC.Internal.Data.Either.Either a b) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Exp -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.LanguageExtensions.Extension -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FamilyResultSig -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Fixity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FixityDirection -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Float -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Foreign -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FunDep -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Guard -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Info -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.InjectivityAnn -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Inline -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Int -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int16 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int32 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int64 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int8 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Integer.Integer -- Defined in ‘GHC.Internal.TH.Lift’ -instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift [a] -- Defined in ‘GHC.Internal.TH.Lift’ +instance [overlappable] forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift [a] -- Defined in ‘GHC.Internal.TH.Lift’ +instance [overlapping] GHC.Internal.TH.Lift.Lift [GHC.Types.Char] -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Lit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Loc -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Match -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Maybe.Maybe a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.ModName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Module -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Name -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameFlavour -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameIs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameSpace -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NamespaceSpecifier -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Natural.Natural -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.OccName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Overlap -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pat -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynArgs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynDir -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Phases -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PkgName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pragma -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Range -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.Real.Integral a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Real.Ratio a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Role -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleBndr -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleMatch -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Safety -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceUnpackedness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Specificity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Stmt -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TExp a) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (a, b) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c) => GHC.Internal.TH.Lift.Lift (a, b, c) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d) => GHC.Internal.TH.Lift.Lift (a, b, c, d) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f g. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f, GHC.Internal.TH.Lift.Lift g) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f, g) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TyLit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TySynEqn -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TyVarBndr a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Type -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TypeFamilyHead -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift () -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Word -- Defined in ‘GHC.Internal.TH.Lift’ ===================================== testsuite/tests/th/T3600.stderr ===================================== @@ -1,2 +1,2 @@ T3600.hs:5:2-7: Splicing declarations - test ======> myFunction = (testFun1 [], testFun2 [], testFun2 "x") + test ======> myFunction = (testFun1 [], testFun2 "", testFun2 "x") ===================================== testsuite/tests/th/TH_Lift.hs ===================================== @@ -80,3 +80,8 @@ o = $( (\x -> [| x |]) (True, 'x', 4 :: Int) ) p :: NonEmpty Char p = $( (\x -> [| x |]) ('a' :| "bcde") ) +exp :: Exp +exp = $( [| 3 + 4 |] >>= lift ) + +texp :: TExp Int +texp = $$( examineCode [|| 3 + 4 ||] `bindCode` liftTyped ) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3c4307bd013ba5dbf9cb3b1b017026252fcaf715...4ee6eb870e6fdd801edae627c66da1b57f32a8b7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3c4307bd013ba5dbf9cb3b1b017026252fcaf715...4ee6eb870e6fdd801edae627c66da1b57f32a8b7 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 15:24:35 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 12 Jun 2024 11:24:35 -0400 Subject: [Git][ghc/ghc][wip/T24978] Wibbles Message-ID: <6669bdb37baf4_167e4d205536452481@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24978 at Glasgow Haskell Compiler / GHC Commits: c2f2f171 by Simon Peyton Jones at 2024-06-12T16:21:32+01:00 Wibbles - - - - - 5 changed files: - compiler/GHC/Core/Coercion/Opt.hs - testsuite/tests/pmcheck/should_compile/T11195.hs - testsuite/tests/tcplugins/CtIdPlugin.hs - testsuite/tests/tcplugins/RewritePlugin.hs - testsuite/tests/tcplugins/TyFamPlugin.hs Changes: ===================================== compiler/GHC/Core/Coercion/Opt.hs ===================================== @@ -526,6 +526,10 @@ in GHC.Core.Coercion. -- | Optimize a phantom coercion. The input coercion may not necessarily -- be a phantom, but the output sure will be. opt_phantom :: LiftingContext -> SymFlag -> Coercion -> NormalCo +opt_phantom env sym (UnivCo { uco_prov = prov, uco_lty = t1 + , uco_rty = t2, uco_deps = deps }) + = opt_univ env sym prov deps Phantom t1 t2 + opt_phantom env sym co = opt_univ env sym PhantomProv [mkKindCo co] Phantom ty1 ty2 where ===================================== testsuite/tests/pmcheck/should_compile/T11195.hs ===================================== @@ -76,7 +76,7 @@ opt_trans_rule is in_co1@(InstCo co1 ty1) in_co2@(InstCo co2 ty2) , co1 `compatible_co` co2 = undefined opt_trans_rule is (UnivCo { uco_prov = p1 }) - (UnivCo ( uco_prov = p2 }) + (UnivCo { uco_prov = p2 }) | p1 == p2 = undefined -- if the provenances are different, opt'ing will be very confusing ===================================== testsuite/tests/tcplugins/CtIdPlugin.hs ===================================== @@ -42,7 +42,7 @@ solver :: [String] -> PluginDefs -> EvBindsVar -> [Ct] -> [Ct] -> TcPluginM TcPluginSolveResult solver _args defs ev givens wanteds = do - let pluginCo = mkUnivCo (PluginProv "CtIdPlugin") emptyUniqDSet Representational -- Empty is fine. This plugin does not use "givens". + let pluginCo = mkUnivCo (PluginProv "CtIdPlugin") [] Representational -- Empty is fine. This plugin does not use "givens". let substEvidence ct ct' = evCast (ctEvExpr $ ctEvidence ct') $ pluginCo (ctPred ct') (ctPred ct) ===================================== testsuite/tests/tcplugins/RewritePlugin.hs ===================================== @@ -87,5 +87,5 @@ mkTyFamReduction :: TyCon -> [ Type ] -> Type -> Reduction mkTyFamReduction tyCon args res = Reduction co res where co :: Coercion - co = mkUnivCo ( PluginProv "RewritePlugin") emptyUniqDSet Nominal -- Empty is fine. This plugin does not use "givens". + co = mkUnivCo ( PluginProv "RewritePlugin") [] Nominal -- Empty is fine. This plugin does not use "givens". ( mkTyConApp tyCon args ) res ===================================== testsuite/tests/tcplugins/TyFamPlugin.hs ===================================== @@ -80,6 +80,6 @@ solveCt ( PluginDefs {..} ) ct@( classifyPredType . ctPred -> EqPred NomEq lhs r , let evTerm :: EvTerm evTerm = EvExpr . Coercion - $ mkUnivCo ( PluginProv "TyFamPlugin") emptyUniqDSet Nominal lhs rhs -- Empty is fine. This plugin does not use "givens". + $ mkUnivCo ( PluginProv "TyFamPlugin") [] Nominal lhs rhs -- Empty is fine. This plugin does not use "givens". = pure $ Just ( evTerm, ct ) solveCt _ ct = pure Nothing View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c2f2f17111f808fb0af473ed153310d2fc37d5e0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c2f2f17111f808fb0af473ed153310d2fc37d5e0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 16:09:05 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Wed, 12 Jun 2024 12:09:05 -0400 Subject: [Git][ghc/ghc][wip/jacco/ast] ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <6669c821beb78_167e4d25cabc8579e0@gitlab.mail> Rodrigo Mesquita pushed to branch wip/jacco/ast at Glasgow Haskell Compiler / GHC Commits: ae3f3146 by Jacco Krijnen at 2024-06-12T17:08:55+01:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ae3f3146832367c7e7e58c0df73a6aafd503447f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ae3f3146832367c7e7e58c0df73a6aafd503447f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 16:11:53 2024 From: gitlab at gitlab.haskell.org (Jade (@Jade)) Date: Wed, 12 Jun 2024 12:11:53 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/jade/ast Message-ID: <6669c8c994739_167e4d26bda9458779@gitlab.mail> Jade pushed new branch wip/jade/ast at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/jade/ast You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 16:18:18 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Wed, 12 Jun 2024 12:18:18 -0400 Subject: [Git][ghc/ghc][wip/supersven/riscv64-ncg] Fix MO_XX_Conv Message-ID: <6669ca4a42324_167e4d279d720591fa@gitlab.mail> Sven Tennie pushed to branch wip/supersven/riscv64-ncg at Glasgow Haskell Compiler / GHC Commits: 42f544e7 by Sven Tennie at 2024-06-12T10:07:46+00:00 Fix MO_XX_Conv Conversion to smaller Widths are actually a truncation. - - - - - 1 changed file: - compiler/GHC/CmmToAsm/RV64/CodeGen.hs Changes: ===================================== compiler/GHC/CmmToAsm/RV64/CodeGen.hs ===================================== @@ -616,7 +616,14 @@ getRegister' config plat expr = MO_FF_Conv from to -> return $ Any (floatFormat to) (\dst -> code `snocOL` annExpr e (FCVT (OpReg to dst) (OpReg from reg))) -- Conversions + -- TODO: Duplication with MO_UU_Conv + MO_XX_Conv from to | to < from -> pure $ Any (intFormat to) (\dst -> + code `snocOL` + annExpr e (MOV (OpReg from dst) (OpReg from reg)) `appOL` + truncateReg from to dst + ) MO_XX_Conv _from to -> swizzleRegisterRep (intFormat to) <$> getRegister e + MO_AlignmentCheck align wordWidth -> do reg <- getRegister' config plat e addAlignmentCheck align wordWidth reg View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/42f544e7670cc533373593b8a9483e762cdfe4f8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/42f544e7670cc533373593b8a9483e762cdfe4f8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 16:45:52 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 12 Jun 2024 12:45:52 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T24938 Message-ID: <6669d0c090926_167e4d2be6cc8616be@gitlab.mail> Simon Peyton Jones pushed new branch wip/T24938 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T24938 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 16:52:06 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Jun 2024 12:52:06 -0400 Subject: [Git][ghc/ghc][master] Fix a QuickLook bug Message-ID: <6669d236d5562_167e4d2e5084c6714d@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 18 changed files: - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Utils/Concrete.hs - compiler/GHC/Tc/Utils/Instantiate.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Utils/TcType.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2747cd34e5ae6a9216bacb196d1d45c710c5daff -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2747cd34e5ae6a9216bacb196d1d45c710c5daff You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 16:52:50 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Jun 2024 12:52:50 -0400 Subject: [Git][ghc/ghc][master] Fix non-compiling extensible record `HasField` example Message-ID: <6669d2621ee48_167e4d2fe3fb070417@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 1 changed file: - docs/users_guide/exts/hasfield.rst Changes: ===================================== docs/users_guide/exts/hasfield.rst ===================================== @@ -131,7 +131,7 @@ string in the type-level list of fields: :: Nil :: Record '[] Cons :: Proxy x -> a -> Record xs -> Record ('(x, a) ': xs) - instance HasField x (Record ('(x, a) ': xs)) a where + instance {-# OVERLAPPING #-} HasField x (Record ('(x, a) ': xs)) a where getField (Cons _ v _) = v instance HasField x (Record xs) a => HasField x (Record ('(y, b) ': xs)) a where getField (Cons _ _ r) = getField @x r View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1b1523b1701bd14005048d190d92e808c7d3f7e4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1b1523b1701bd14005048d190d92e808c7d3f7e4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 16:53:43 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Jun 2024 12:53:43 -0400 Subject: [Git][ghc/ghc][master] 2 commits: haddock: Fix hyperlinker source urls (#24907) Message-ID: <6669d29729358_167e4d2e8413875150@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - 4 changed files: - utils/haddock/haddock-api/src/Haddock.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Utils.hs - utils/haddock/haddock-api/src/Haddock/Options.hs Changes: ===================================== utils/haddock/haddock-api/src/Haddock.hs ===================================== @@ -394,11 +394,14 @@ render log' dflags unit_state flags sinceQual qual ifaces packages extSrcMap = d | Flag_HyperlinkedSource `elem` flags = Just hypSrcModuleUrlFormat | otherwise = srcModule + -- These urls have a template for the module %M srcMap = Map.union - (Map.map SrcExternal extSrcMap) + (Map.map (SrcExternal . hypSrcPkgUrlToModuleFormat) extSrcMap) (Map.fromList [ (ifaceMod iface, SrcLocal) | iface <- ifaces ]) - pkgSrcMap = Map.mapKeys moduleUnit extSrcMap + -- These urls have a template for the module %M and the name %N + pkgSrcMap = Map.map (hypSrcModuleUrlToNameFormat . hypSrcPkgUrlToModuleFormat) + $ Map.mapKeys moduleUnit extSrcMap pkgSrcMap' | Flag_HyperlinkedSource `elem` flags , Just k <- pkgKey @@ -408,6 +411,7 @@ render log' dflags unit_state flags sinceQual qual ifaces packages extSrcMap = d = Map.insert k srcNameUrl pkgSrcMap | otherwise = pkgSrcMap + -- These urls have a template for the module %M and the line %L -- TODO: Get these from the interface files as with srcMap pkgSrcLMap' | Flag_HyperlinkedSource `elem` flags ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Renderer.hs ===================================== @@ -275,7 +275,7 @@ hyperlink (srcs, srcs') ident = case ident of Html.anchor content ! [Html.href $ hypSrcModuleNameUrl mdl name] Just (SrcExternal path) -> - let hyperlinkUrl = makeHyperlinkUrl path hypSrcModuleNameUrl mdl name + let hyperlinkUrl = hypSrcModuleUrlToNameFormat $ makeHyperlinkUrl path in Html.anchor content ! [Html.href $ spliceURL (Just mdl) (Just name) Nothing hyperlinkUrl] Nothing -> content @@ -288,7 +288,7 @@ hyperlink (srcs, srcs') ident = case ident of Html.anchor content ! [Html.href $ hypSrcModuleUrl' moduleName] Just (SrcExternal path) -> - let hyperlinkUrl = makeHyperlinkUrl path hypSrcModuleUrl' moduleName + let hyperlinkUrl = makeHyperlinkUrl path in Html.anchor content ! [Html.href $ spliceURL' (Just moduleName) Nothing Nothing hyperlinkUrl] Nothing -> content ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Utils.hs ===================================== @@ -13,6 +13,8 @@ module Haddock.Backends.Hyperlinker.Utils , hypSrcModuleUrlFormat , hypSrcModuleNameUrlFormat , hypSrcModuleLineUrlFormat + , hypSrcModuleUrlToNameFormat + , hypSrcPkgUrlToModuleFormat , spliceURL , spliceURL' @@ -82,6 +84,12 @@ hypSrcModuleNameUrlFormat = hypSrcModuleUrlFormat ++ "#" ++ nameFormat hypSrcModuleLineUrlFormat :: String hypSrcModuleLineUrlFormat = hypSrcModuleUrlFormat ++ "#" ++ lineFormat +hypSrcModuleUrlToNameFormat :: String -> String +hypSrcModuleUrlToNameFormat url = url ++ "#" ++ nameFormat + +hypSrcPkgUrlToModuleFormat :: String -> String +hypSrcPkgUrlToModuleFormat url = url moduleFormat + moduleFormat :: String moduleFormat = "%{MODULE}.html" ===================================== utils/haddock/haddock-api/src/Haddock/Options.hs ===================================== @@ -563,7 +563,7 @@ readIfaceArgs flags = [parseIfaceOption s | Flag_ReadInterface s <- flags] (src, ',' : rest') -> let src' = case src of "" -> Nothing - _ -> Just (src ++ "/%M.html") + _ -> Just src docPaths = DocPaths { docPathsHtml = fpath , docPathsSources = src' } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1b1523b1701bd14005048d190d92e808c7d3f7e4...954f864c33852f6511f295d941c45c3c6193dad1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1b1523b1701bd14005048d190d92e808c7d3f7e4...954f864c33852f6511f295d941c45c3c6193dad1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 16:54:43 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Jun 2024 12:54:43 -0400 Subject: [Git][ghc/ghc][master] Prioritise nominal equalities Message-ID: <6669d2d367e64_167e4d34522a479841@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - 16 changed files: - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/InertSet.hs - compiler/GHC/Tc/Solver/Rewrite.hs - compiler/GHC/Tc/Solver/Solve.hs - compiler/GHC/Tc/Types.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Types/Id.hs - + testsuite/tests/typecheck/should_compile/T24887.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -49,6 +49,7 @@ import GHC.Core.DataCon import GHC.Core.Ppr import GHC.Core.Coercion import GHC.Core.Type as Type +import GHC.Core.Predicate( isCoVarType ) import GHC.Core.Multiplicity import GHC.Core.UsageEnv import GHC.Core.TyCo.Rep -- checks validity of types/coercions ===================================== compiler/GHC/Core/Make.hs ===================================== @@ -67,9 +67,10 @@ import GHC.Types.Unique.Supply import GHC.Core import GHC.Core.Utils ( exprType, mkSingleAltCase, bindNonRec ) import GHC.Core.Type -import GHC.Core.TyCo.Compare( eqType ) -import GHC.Core.Coercion ( isCoVar ) -import GHC.Core.DataCon ( DataCon, dataConWorkId ) +import GHC.Core.Predicate ( isCoVarType ) +import GHC.Core.TyCo.Compare ( eqType ) +import GHC.Core.Coercion ( isCoVar ) +import GHC.Core.DataCon ( DataCon, dataConWorkId ) import GHC.Core.Multiplicity import GHC.Builtin.Types ===================================== compiler/GHC/Core/Predicate.hs ===================================== @@ -12,7 +12,7 @@ module GHC.Core.Predicate ( -- Equality predicates EqRel(..), eqRelRole, - isEqPrimPred, isEqPred, + isEqPrimPred, isNomEqPred, isReprEqPrimPred, isEqPred, isCoVarType, getEqPredTys, getEqPredTys_maybe, getEqPredRole, predTypeEqRel, mkPrimEqPred, mkReprPrimEqPred, mkPrimEqPredRole, @@ -60,7 +60,7 @@ data Pred -- | A typeclass predicate. = ClassPred Class [Type] - -- | A type equality predicate. + -- | A type equality predicate, (t1 ~#N t2) or (t1 ~#R t2) | EqPred EqRel Type Type -- | An irreducible predicate. @@ -80,7 +80,7 @@ classifyPredType :: PredType -> Pred classifyPredType ev_ty = case splitTyConApp_maybe ev_ty of Just (tc, [_, _, ty1, ty2]) | tc `hasKey` eqReprPrimTyConKey -> EqPred ReprEq ty1 ty2 - | tc `hasKey` eqPrimTyConKey -> EqPred NomEq ty1 ty2 + | tc `hasKey` eqPrimTyConKey -> EqPred NomEq ty1 ty2 Just (tc, tys) | Just clas <- tyConClass_maybe tc @@ -189,16 +189,21 @@ getEqPredTys_maybe ty _ -> Nothing getEqPredRole :: PredType -> Role +-- Precondition: the PredType is (s ~#N t) or (s ~#R t) getEqPredRole ty = eqRelRole (predTypeEqRel ty) -- | Get the equality relation relevant for a pred type. -predTypeEqRel :: PredType -> EqRel +-- Precondition: the PredType is (s ~#N t) or (s ~#R t) +predTypeEqRel :: HasDebugCallStack => PredType -> EqRel predTypeEqRel ty - | Just (tc, _) <- splitTyConApp_maybe ty - , tc `hasKey` eqReprPrimTyConKey - = ReprEq - | otherwise - = NomEq + = case splitTyConApp_maybe ty of + Just (tc, _) | tc `hasKey` eqReprPrimTyConKey + -> ReprEq + | otherwise + -> assertPpr (tc `hasKey` eqPrimTyConKey) (ppr ty) + NomEq + _ -> pprPanic "predTypeEqRel" (ppr ty) + {------------------------------------------- Predicates on PredType @@ -219,20 +224,51 @@ see Note [Equality superclasses in quantified constraints] in GHC.Tc.Solver.Dict. -} +-- | Does this type classify a core (unlifted) Coercion? +-- At either role nominal or representational +-- (t1 ~# t2) or (t1 ~R# t2) +-- See Note [Types for coercions, predicates, and evidence] in "GHC.Core.TyCo.Rep" +isCoVarType :: Type -> Bool + -- ToDo: should we check saturation? +isCoVarType ty = isEqPrimPred ty + isEvVarType :: Type -> Bool --- True of (a) predicates, of kind Constraint, such as (Eq a), and (a ~ b) --- (b) coercion types, such as (t1 ~# t2) or (t1 ~R# t2) +-- True of (a) predicates, of kind Constraint, such as (Eq t), and (s ~ t) +-- (b) coercion types, such as (s ~# t) or (s ~R# t) -- See Note [Types for coercions, predicates, and evidence] in GHC.Core.TyCo.Rep -- See Note [Evidence for quantified constraints] isEvVarType ty = isCoVarType ty || isPredTy ty +isEqPrimPred :: PredType -> Bool +-- True of (s ~# t) (s ~R# t) +isEqPrimPred ty + | Just tc <- tyConAppTyCon_maybe ty + = tc `hasKey` eqPrimTyConKey || tc `hasKey` eqReprPrimTyConKey + | otherwise + = False + +isReprEqPrimPred :: PredType -> Bool +isReprEqPrimPred ty + | Just tc <- tyConAppTyCon_maybe ty + = tc `hasKey` eqReprPrimTyConKey + | otherwise + = False + +isNomEqPred :: PredType -> Bool +-- A nominal equality, primitive or not (s ~# t), (s ~ t), or (s ~~ t) +isNomEqPred ty + | Just tc <- tyConAppTyCon_maybe ty + = tc `hasKey` eqPrimTyConKey || tc `hasKey` heqTyConKey || tc `hasKey` eqTyConKey + | otherwise + = False + isClassPred :: PredType -> Bool isClassPred ty = case tyConAppTyCon_maybe ty of Just tc -> isClassTyCon tc _ -> False isEqPred :: PredType -> Bool -isEqPred ty -- True of (a ~ b) and (a ~~ b) +isEqPred ty -- True of (s ~ t) and (s ~~ t) -- ToDo: should we check saturation? | Just tc <- tyConAppTyCon_maybe ty , Just cls <- tyConClass_maybe tc @@ -240,10 +276,6 @@ isEqPred ty -- True of (a ~ b) and (a ~~ b) | otherwise = False -isEqPrimPred :: PredType -> Bool -isEqPrimPred ty = isCoVarType ty - -- True of (a ~# b) (a ~R# b) - isEqualityClass :: Class -> Bool -- True of (~), (~~), and Coercible -- These all have a single primitive-equality superclass, either (~N# or ~R#) ===================================== compiler/GHC/Core/SimpleOpt.hs ===================================== @@ -29,27 +29,32 @@ import GHC.Core.Unfold import GHC.Core.Unfold.Make import GHC.Core.Make ( FloatBind(..), mkWildValBinder ) import GHC.Core.Opt.OccurAnal( occurAnalyseExpr, occurAnalysePgm, zapLambdaBndrs ) +import GHC.Core.DataCon +import GHC.Core.Coercion.Opt ( optCoercion, OptCoercionOpts (..) ) +import GHC.Core.Type hiding ( substTy, extendTvSubst, extendCvSubst, extendTvSubstList + , isInScope, substTyVarBndr, cloneTyVarBndr ) +import GHC.Core.Predicate( isCoVarType ) +import GHC.Core.Coercion hiding ( substCo, substCoVarBndr ) + import GHC.Types.Literal import GHC.Types.Id import GHC.Types.Id.Info ( realUnfoldingInfo, setUnfoldingInfo, setRuleInfo, IdInfo (..) ) import GHC.Types.Var ( isNonCoVarId ) import GHC.Types.Var.Set import GHC.Types.Var.Env -import GHC.Core.DataCon import GHC.Types.Demand( etaConvertDmdSig, topSubDmd ) import GHC.Types.Tickish -import GHC.Core.Coercion.Opt ( optCoercion, OptCoercionOpts (..) ) -import GHC.Core.Type hiding ( substTy, extendTvSubst, extendCvSubst, extendTvSubstList - , isInScope, substTyVarBndr, cloneTyVarBndr ) -import GHC.Core.Coercion hiding ( substCo, substCoVarBndr ) +import GHC.Types.Basic + import GHC.Builtin.Types import GHC.Builtin.Names -import GHC.Types.Basic + import GHC.Unit.Module ( Module ) import GHC.Utils.Encoding import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Utils.Misc + import GHC.Data.Maybe ( orElse ) import GHC.Data.Graph.UnVar import Data.List (mapAccumL) ===================================== compiler/GHC/Core/Type.hs ===================================== @@ -113,7 +113,7 @@ module GHC.Core.Type ( isForAllTy_ty, isForAllTy_co, isForAllTy_invis_ty, isPiTy, isTauTy, isFamFreeTy, - isCoVarType, isAtomicTy, + isAtomicTy, isValidJoinPointType, tyConAppNeedsKindSig, @@ -2493,18 +2493,6 @@ isTerminatingType ty = case tyConAppTyCon_maybe ty of Just tc -> isClassTyCon tc && not (isNewTyCon tc) _ -> False --- | Does this type classify a core (unlifted) Coercion? --- At either role nominal or representational --- (t1 ~# t2) or (t1 ~R# t2) --- See Note [Types for coercions, predicates, and evidence] in "GHC.Core.TyCo.Rep" -isCoVarType :: Type -> Bool - -- ToDo: should we check saturation? -isCoVarType ty - | Just tc <- tyConAppTyCon_maybe ty - = tc `hasKey` eqPrimTyConKey || tc `hasKey` eqReprPrimTyConKey - | otherwise - = False - isPrimitiveType :: Type -> Bool -- ^ Returns true of types that are opaque to Haskell. isPrimitiveType ty = case splitTyConApp_maybe ty of ===================================== compiler/GHC/Core/Utils.hs ===================================== @@ -74,6 +74,7 @@ import GHC.Core.Ppr import GHC.Core.FVs( bindFreeVars ) import GHC.Core.DataCon import GHC.Core.Type as Type +import GHC.Core.Predicate( isCoVarType ) import GHC.Core.FamInstEnv import GHC.Core.TyCo.Compare( eqType, eqTypeX ) import GHC.Core.Coercion ===================================== compiler/GHC/Tc/Solver/Dict.hs ===================================== @@ -84,7 +84,7 @@ solveDict dict_ct@(DictCt { di_ev = ev, di_cls = cls, di_tys = tys }) = solveEqualityDict ev cls tys | otherwise - = assertPpr (ctEvRole ev == Nominal) (ppr ev $$ ppr cls $$ ppr tys) $ + = assertPpr (ctEvRewriteRole ev == Nominal) (ppr ev $$ ppr cls $$ ppr tys) $ do { simpleStage $ traceTcS "solveDict" (ppr dict_ct) ; tryInertDicts dict_ct ===================================== compiler/GHC/Tc/Solver/Equality.hs ===================================== @@ -1092,11 +1092,29 @@ There are two ways in which decomposing (N ty1) ~r (N ty2) could be incomplete: have a nominal role. Thus, decomposing the wanted will yield [W] Int ~N Age, which is unsatisfiable. Unwrapping, though, leads to a solution. - Conclusion: always unwrap newtypes before attempting to decompose + CONCLUSION: always unwrap newtypes before attempting to decompose them. This is done in can_eq_nc. Of course, we can't unwrap if the data constructor isn't in scope. See Note [Unwrap newtypes first]. -* Incompleteness example (EX2): available Givens +* Incompleteness example (EX2): see #24887 + data family D a + data instance D Int = MkD1 (D Char) + data instance D Bool = MkD2 (D Char) + Now suppose we have + [W] g1: D Int ~R# D a + [W] g2: a ~# Bool + If we solve g2 first, giving a:=Bool, then we can solve g1 easily: + D Int ~R# D Char ~R# D Bool + by newtype unwrapping. + + BUT: if we instead attempt to solve g1 first, we can unwrap the LHS (only) + leaving [W] D Char ~#R D Bool + If we decompose now, we'll get (Char ~R# Bool), which is insoluble. + + CONCLUSION: prioritise nominal equalites in the work list. + See Note [Prioritise equalities] in GHC.Tc.Solver.InertSet. + +* Incompleteness example (EX3): available Givens newtype Nt a = Mk Bool -- NB: a is not used in the RHS, type role Nt representational -- but the user gives it an R role anyway @@ -1110,7 +1128,7 @@ There are two ways in which decomposing (N ty1) ~r (N ty2) could be incomplete: Givens for class constraints: see Note [Instance and Given overlap] in GHC.Tc.Solver.Dict. - Conclusion: don't decompose [W] N s ~R N t, if there are any Given + CONCLUSION: don't decompose [W] N s ~R N t, if there are any Given equalities that could later solve it. But what precisely does it mean to say "any Given equalities that could @@ -2536,7 +2554,7 @@ rewriteEqEvidence new_rewriters old_ev swapped (Reduction lhs_co nlhs) (Reductio | CtWanted { ctev_dest = dest , ctev_rewriters = rewriters } <- old_ev , let rewriters' = rewriters S.<> new_rewriters - = do { (new_ev, hole_co) <- newWantedEq loc rewriters' (ctEvRole old_ev) nlhs nrhs + = do { (new_ev, hole_co) <- newWantedEq loc rewriters' (ctEvRewriteRole old_ev) nlhs nrhs ; let co = maybeSymCo swapped $ lhs_co `mkTransCo` hole_co `mkTransCo` mkSymCo rhs_co ; setWantedEq dest co @@ -2602,7 +2620,7 @@ tryInertEqs work_item@(EqCt { eq_ev = ev, eq_eq_rel = eq_rel }) -> do { setEvBindIfWanted ev True $ evCoercion (maybeSymCo swapped $ downgradeRole (eqRelRole eq_rel) - (ctEvRole ev_i) + (ctEvRewriteRole ev_i) (ctEvCoercion ev_i)) ; stopWith ev "Solved from inert" } ===================================== compiler/GHC/Tc/Solver/InertSet.hs ===================================== @@ -133,9 +133,16 @@ It's very important to process equalities over class constraints: E.g. a CIrredCan can be a hetero-kinded (t1 ~ t2), which may become homo-kinded when kicked out, and hence we want to prioritise it. -Among the equalities we prioritise ones with an empty rewriter set; -see Note [Wanteds rewrite Wanteds] in GHC.Tc.Types.Constraint, wrinkle (W1). +Further refinements: +* Among the equalities we prioritise ones with an empty rewriter set; + see Note [Wanteds rewrite Wanteds] in GHC.Tc.Types.Constraint, wrinkle (W1). + +* Among equalities with an empty rewriter set, we prioritise nominal equalities. + * They have more rewriting power, so doing them first is better. + * Prioritising them ameliorates the incompleteness of newtype + solving: see (Ex2) in Note [Decomposing newtype equalities] in + GHC.Tc.Solver.Equality. Note [Prioritise class equalities] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -168,12 +175,14 @@ See GHC.Tc.Solver.Monad.deferTcSForAllEq -- See Note [WorkList priorities] data WorkList - = WL { wl_eqs :: [Ct] -- CEqCan, CDictCan, CIrredCan - -- Given and Wanted - -- Contains both equality constraints and their - -- class-level variants (a~b) and (a~~b); - -- See Note [Prioritise equalities] - -- See Note [Prioritise class equalities] + = WL { wl_eqs_N :: [Ct] -- /Nominal/ equalities (s ~#N t), (s ~ t), (s ~~ t) + -- with empty rewriter set + , wl_eqs_X :: [Ct] -- CEqCan, CDictCan, CIrredCan + -- with empty rewriter set + -- All other equalities: contains both equality constraints and + -- their class-level variants (a~b) and (a~~b); + -- See Note [Prioritise equalities] + -- See Note [Prioritise class equalities] , wl_rw_eqs :: [Ct] -- Like wl_eqs, but ones that have a non-empty -- rewriter set; or, more precisely, did when @@ -182,48 +191,69 @@ data WorkList -- see Note [Prioritise Wanteds with empty RewriterSet] -- in GHC.Tc.Types.Constraint for more details. - , wl_rest :: [Ct] + , wl_rest :: [Ct] , wl_implics :: Bag Implication -- See Note [Residual implications] } appendWorkList :: WorkList -> WorkList -> WorkList appendWorkList - (WL { wl_eqs = eqs1, wl_rw_eqs = rw_eqs1 + (WL { wl_eqs_N = eqs1_N, wl_eqs_X = eqs1_X, wl_rw_eqs = rw_eqs1 , wl_rest = rest1, wl_implics = implics1 }) - (WL { wl_eqs = eqs2, wl_rw_eqs = rw_eqs2 + (WL { wl_eqs_N = eqs2_N, wl_eqs_X = eqs2_X, wl_rw_eqs = rw_eqs2 , wl_rest = rest2, wl_implics = implics2 }) - = WL { wl_eqs = eqs1 ++ eqs2 + = WL { wl_eqs_N = eqs1_N ++ eqs2_N + , wl_eqs_X = eqs1_X ++ eqs2_X , wl_rw_eqs = rw_eqs1 ++ rw_eqs2 , wl_rest = rest1 ++ rest2 , wl_implics = implics1 `unionBags` implics2 } workListSize :: WorkList -> Int -workListSize (WL { wl_eqs = eqs, wl_rw_eqs = rw_eqs, wl_rest = rest }) - = length eqs + length rw_eqs + length rest +workListSize (WL { wl_eqs_N = eqs_N, wl_eqs_X = eqs_X, wl_rw_eqs = rw_eqs, wl_rest = rest }) + = length eqs_N + length eqs_X + length rw_eqs + length rest extendWorkListEq :: RewriterSet -> Ct -> WorkList -> WorkList -extendWorkListEq rewriters ct wl +extendWorkListEq rewriters ct + wl@(WL { wl_eqs_N = eqs_N, wl_eqs_X = eqs_X, wl_rw_eqs = rw_eqs }) | isEmptyRewriterSet rewriters -- A wanted that has not been rewritten -- isEmptyRewriterSet: see Note [Prioritise Wanteds with empty RewriterSet] -- in GHC.Tc.Types.Constraint - = wl { wl_eqs = ct : wl_eqs wl } + = if isNomEqPred (ctPred ct) + then wl { wl_eqs_N = ct : eqs_N } + else wl { wl_eqs_X = ct : eqs_X } + | otherwise - = wl { wl_rw_eqs = ct : wl_rw_eqs wl } + = wl { wl_rw_eqs = ct : rw_eqs } extendWorkListEqs :: RewriterSet -> Bag Ct -> WorkList -> WorkList -- Add [eq1,...,eqn] to the work-list -- They all have the same rewriter set -- The constraints will be solved in left-to-right order: --- see Note [Work-list ordering] in GHC.Tc.Solved.Equality -extendWorkListEqs rewriters eqs wl +-- see Note [Work-list ordering] in GHC.Tc.Solver.Equality +-- +-- Precondition: new_eqs is non-empty +extendWorkListEqs rewriters new_eqs + wl@(WL { wl_eqs_N = eqs_N, wl_eqs_X = eqs_X, wl_rw_eqs = rw_eqs }) | isEmptyRewriterSet rewriters -- isEmptyRewriterSet: see Note [Prioritise Wanteds with empty RewriterSet] -- in GHC.Tc.Types.Constraint - = wl { wl_eqs = foldr (:) (wl_eqs wl) eqs } - -- The foldr just appends wl_eqs to the bag of eqs + = case partitionBag is_nominal new_eqs of + (new_eqs_N, new_eqs_X) + | isEmptyBag new_eqs_N -> wl { wl_eqs_X = new_eqs_X `push_on_front` eqs_X } + | isEmptyBag new_eqs_X -> wl { wl_eqs_N = new_eqs_N `push_on_front` eqs_N } + | otherwise -> wl { wl_eqs_N = new_eqs_N `push_on_front` eqs_N + , wl_eqs_X = new_eqs_X `push_on_front` eqs_X } + -- These isEmptyBag tests are just trying + -- to avoid creating unnecessary thunks + | otherwise - = wl { wl_rw_eqs = foldr (:) (wl_rw_eqs wl) eqs } + = wl { wl_rw_eqs = new_eqs `push_on_front` rw_eqs } + where + push_on_front :: Bag Ct -> [Ct] -> [Ct] + -- push_on_front puts the new equlities on the front of the queue + push_on_front new_eqs eqs = foldr (:) eqs new_eqs + + is_nominal ct = isNomEqPred (ctPred ct) extendWorkListNonEq :: Ct -> WorkList -> WorkList -- Extension by non equality @@ -255,26 +285,33 @@ extendWorkListCts :: Cts -> WorkList -> WorkList extendWorkListCts cts wl = foldr extendWorkListCt wl cts isEmptyWorkList :: WorkList -> Bool -isEmptyWorkList (WL { wl_eqs = eqs, wl_rest = rest, wl_implics = implics }) - = null eqs && null rest && isEmptyBag implics +isEmptyWorkList (WL { wl_eqs_N = eqs_N, wl_eqs_X = eqs_X + , wl_rest = rest, wl_implics = implics }) + = null eqs_N && null eqs_X && null rest && isEmptyBag implics emptyWorkList :: WorkList -emptyWorkList = WL { wl_eqs = [], wl_rw_eqs = [], wl_rest = [], wl_implics = emptyBag } +emptyWorkList = WL { wl_eqs_N = [], wl_eqs_X = [] + , wl_rw_eqs = [], wl_rest = [], wl_implics = emptyBag } selectWorkItem :: WorkList -> Maybe (Ct, WorkList) -- See Note [Prioritise equalities] -selectWorkItem wl@(WL { wl_eqs = eqs, wl_rw_eqs = rw_eqs, wl_rest = rest }) - | ct:cts <- eqs = Just (ct, wl { wl_eqs = cts }) +selectWorkItem wl@(WL { wl_eqs_N = eqs_N, wl_eqs_X = eqs_X + , wl_rw_eqs = rw_eqs, wl_rest = rest }) + | ct:cts <- eqs_N = Just (ct, wl { wl_eqs_N = cts }) + | ct:cts <- eqs_X = Just (ct, wl { wl_eqs_X = cts }) | ct:cts <- rw_eqs = Just (ct, wl { wl_rw_eqs = cts }) | ct:cts <- rest = Just (ct, wl { wl_rest = cts }) | otherwise = Nothing -- Pretty printing instance Outputable WorkList where - ppr (WL { wl_eqs = eqs, wl_rw_eqs = rw_eqs, wl_rest = rest, wl_implics = implics }) + ppr (WL { wl_eqs_N = eqs_N, wl_eqs_X = eqs_X, wl_rw_eqs = rw_eqs + , wl_rest = rest, wl_implics = implics }) = text "WL" <+> (braces $ - vcat [ ppUnless (null eqs) $ - text "Eqs =" <+> vcat (map ppr eqs) + vcat [ ppUnless (null eqs_N) $ + text "Eqs_N =" <+> vcat (map ppr eqs_N) + , ppUnless (null eqs_X) $ + text "Eqs_X =" <+> vcat (map ppr eqs_X) , ppUnless (null rw_eqs) $ text "RwEqs =" <+> vcat (map ppr rw_eqs) , ppUnless (null rest) $ ===================================== compiler/GHC/Tc/Solver/Rewrite.hs ===================================== @@ -81,7 +81,7 @@ liftTcS thing_inside -- the rewriting operation runRewriteCtEv :: CtEvidence -> RewriteM a -> TcS (a, RewriterSet) runRewriteCtEv ev - = runRewrite (ctEvLoc ev) (ctEvFlavour ev) (ctEvEqRel ev) + = runRewrite (ctEvLoc ev) (ctEvFlavour ev) (ctEvRewriteEqRel ev) -- Run thing_inside (which does the rewriting) -- Also returns the set of Wanteds which rewrote a Wanted; @@ -160,10 +160,18 @@ recordRewriter other = pprPanic "recordRewriter" (ppr other) Note [Rewriter EqRels] ~~~~~~~~~~~~~~~~~~~~~~~ When rewriting, we need to know which equality relation -- nominal -or representation -- we should be respecting. The only difference is -that we rewrite variables by representational equalities when re_eq_rel -is ReprEq, and that we unwrap newtypes when rewriting w.r.t. -representational equality. +or representational -- we should be respecting. This is controlled +by the `re_eq_rel` field of RewriteEnv. + +* When rewriting primitive /representational/ equalities, (t1 ~# t2), + we set re_eq_rel=ReprEq. +* For all other constraints, we set re_eq_rel=NomEq + +See Note [The rewrite-role of a constraint] in GHC.Tc.Types.Constraint. + +The only difference is that when re_eq_rel=ReprEq +* we rewrite variables by representational equalities +* we unwrap newtypes Note [Rewriter CtLoc] ~~~~~~~~~~~~~~~~~~~~~~ @@ -233,7 +241,7 @@ rewriteForErrors ev ty ; result@(redn, rewriters) <- runRewrite (ctEvLoc ev) (ctEvFlavour ev) NomEq (rewrite_one ty) ; traceTcS "rewriteForErrors }" (ppr $ reductionReducedType redn) - ; return $ case ctEvEqRel ev of + ; return $ case ctEvRewriteEqRel ev of NomEq -> result ReprEq -> (mkSubRedn redn, rewriters) } ===================================== compiler/GHC/Tc/Solver/Solve.hs ===================================== @@ -545,18 +545,21 @@ finish_rewrite ev@(CtGiven { ctev_evar = old_evar, ctev_loc = loc }) ; continueWith new_ev } where -- mkEvCast optimises ReflCo - new_tm = mkEvCast (evId old_evar) - (downgradeRole Representational (ctEvRole ev) co) + ev_rw_role = ctEvRewriteRole ev + new_tm = assert (coercionRole co == ev_rw_role) + mkEvCast (evId old_evar) + (downgradeRole Representational ev_rw_role co) finish_rewrite ev@(CtWanted { ctev_dest = dest , ctev_loc = loc , ctev_rewriters = rewriters }) (Reduction co new_pred) new_rewriters = do { mb_new_ev <- newWanted loc rewriters' new_pred - ; massert (coercionRole co == ctEvRole ev) + ; let ev_rw_role = ctEvRewriteRole ev + ; massert (coercionRole co == ev_rw_role) ; setWantedEvTerm dest True $ mkEvCast (getEvExpr mb_new_ev) - (downgradeRole Representational (ctEvRole ev) (mkSymCo co)) + (downgradeRole Representational ev_rw_role (mkSymCo co)) ; case mb_new_ev of Fresh new_ev -> continueWith new_ev Cached _ -> stopWith ev "Cached wanted" } ===================================== compiler/GHC/Tc/Types.hs ===================================== @@ -319,9 +319,8 @@ data RewriteEnv -- See Note [Rewriter CtLoc] in GHC.Tc.Solver.Rewrite. , re_flavour :: !CtFlavour , re_eq_rel :: !EqRel - -- ^ At what role are we rewriting? - -- - -- See Note [Rewriter EqRels] in GHC.Tc.Solver.Rewrite + -- ^ At what role are we rewriting? + -- See Note [Rewriter EqRels] in GHC.Tc.Solver.Rewrite , re_rewriters :: !(TcRef RewriterSet) -- ^ See Note [Wanteds rewrite Wanteds] } ===================================== compiler/GHC/Tc/Types/Constraint.hs ===================================== @@ -83,7 +83,7 @@ module GHC.Tc.Types.Constraint ( ctEvExpr, ctEvTerm, ctEvCoercion, ctEvEvId, ctEvRewriters, ctEvUnique, tcEvDestUnique, mkKindEqLoc, toKindLoc, toInvisibleLoc, mkGivenLoc, - ctEvRole, setCtEvPredType, setCtEvLoc, arisesFromGivens, + ctEvRewriteRole, ctEvRewriteEqRel, setCtEvPredType, setCtEvLoc, arisesFromGivens, tyCoVarsOfCtEvList, tyCoVarsOfCtEv, tyCoVarsOfCtEvsList, -- RewriterSet @@ -1967,6 +1967,18 @@ For Givens we make new EvVars and bind them immediately. Two main reasons: So a Given has EvVar inside it rather than (as previously) an EvTerm. +Note [The rewrite-role of a constraint] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The rewrite-role of a constraint says what can rewrite that constraint: + +* If the rewrite-role = Nominal, only a nominal equality can rewrite it + +* If the rewrite-rule = Representational, either a nominal or + representational equality can rewrit it. + +Notice that the constraint may itself not be an equality at all. +For example, the rewrite-role of (Eq [a]) is Nominal; only nominal +equalities can rewrite it. -} -- | A place for type-checking evidence to go after it is generated. @@ -2006,12 +2018,21 @@ ctEvOrigin :: CtEvidence -> CtOrigin ctEvOrigin = ctLocOrigin . ctEvLoc -- | Get the equality relation relevant for a 'CtEvidence' -ctEvEqRel :: CtEvidence -> EqRel +ctEvEqRel :: HasDebugCallStack => CtEvidence -> EqRel ctEvEqRel = predTypeEqRel . ctEvPred --- | Get the role relevant for a 'CtEvidence' -ctEvRole :: CtEvidence -> Role -ctEvRole = eqRelRole . ctEvEqRel +-- | Get the rewrite-role relevant for a 'CtEvidence' +-- See Note [The rewrite-role of a constraint] +ctEvRewriteRole :: HasDebugCallStack => CtEvidence -> Role +ctEvRewriteRole = eqRelRole . ctEvRewriteEqRel + +ctEvRewriteEqRel :: CtEvidence -> EqRel +-- ^ Return the rewrite-role of an abitrary CtEvidence +-- See Note [The rewrite-role of a constraint] +-- We return ReprEq for (a ~R# b) and NomEq for all other preds +ctEvRewriteEqRel ev + | isReprEqPrimPred (ctEvPred ev) = ReprEq + | otherwise = NomEq ctEvTerm :: CtEvidence -> EvTerm ctEvTerm ev = EvExpr (ctEvExpr ev) @@ -2167,8 +2188,8 @@ ctEvFlavour (CtGiven {}) = Given type CtFlavourRole = (CtFlavour, EqRel) -- | Extract the flavour, role, and boxity from a 'CtEvidence' -ctEvFlavourRole :: CtEvidence -> CtFlavourRole -ctEvFlavourRole ev = (ctEvFlavour ev, ctEvEqRel ev) +ctEvFlavourRole :: HasDebugCallStack => CtEvidence -> CtFlavourRole +ctEvFlavourRole ev = (ctEvFlavour ev, ctEvRewriteEqRel ev) -- | Extract the flavour and role from a 'Ct' eqCtFlavourRole :: EqCt -> CtFlavourRole @@ -2180,7 +2201,7 @@ dictCtFlavourRole (DictCt { di_ev = ev }) = (ctEvFlavour ev, NomEq) -- | Extract the flavour and role from a 'Ct' -ctFlavourRole :: Ct -> CtFlavourRole +ctFlavourRole :: HasDebugCallStack => Ct -> CtFlavourRole -- Uses short-cuts to role for special cases ctFlavourRole (CDictCan di_ct) = dictCtFlavourRole di_ct ctFlavourRole (CEqCan eq_ct) = eqCtFlavourRole eq_ct ===================================== compiler/GHC/Types/Id.hs ===================================== @@ -146,27 +146,32 @@ import GHC.Types.Var( Id, CoVar, JoinId, import qualified GHC.Types.Var as Var import GHC.Core.Type -import GHC.Types.RepType +import GHC.Core.Predicate( isCoVarType ) import GHC.Core.DataCon +import GHC.Core.Class +import GHC.Core.Multiplicity + +import GHC.Types.RepType import GHC.Types.Demand import GHC.Types.Cpr import GHC.Types.Name -import GHC.Unit.Module -import GHC.Core.Class -import {-# SOURCE #-} GHC.Builtin.PrimOps (PrimOp) import GHC.Types.ForeignCall -import GHC.Data.Maybe import GHC.Types.SrcLoc import GHC.Types.Unique + +import GHC.Stg.InferTags.TagSig + +import GHC.Unit.Module +import {-# SOURCE #-} GHC.Builtin.PrimOps (PrimOp) import GHC.Builtin.Uniques (mkBuiltinUnique) import GHC.Types.Unique.Supply + +import GHC.Data.Maybe import GHC.Data.FastString -import GHC.Core.Multiplicity import GHC.Utils.Misc import GHC.Utils.Outputable import GHC.Utils.Panic -import GHC.Stg.InferTags.TagSig -- infixl so you can say (id `set` a `set` b) infixl 1 `setIdUnfolding`, ===================================== testsuite/tests/typecheck/should_compile/T24887.hs ===================================== @@ -0,0 +1,62 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE ScopedTypeVariables, TypeAbstractions #-} + +module Data.Array.Nested.Internal where + +import Data.Coerce (coerce) + + +type family Id (b :: Bool) where + Id b = b + +newtype Ranked b a = MkRanked (Mixed b a) + + +data family Mixed (b :: Bool) a + +newtype instance Mixed b1 (Mixed b2 a) = M_Nest (Mixed False a) + +newtype instance Mixed b (Ranked c a) = M_Ranked (Mixed b (Mixed (Id c) a)) +-- +-- newtype MixedNT b c a = M_Ranked (Mixed b (Mixed (Id c) a)) +-- And we Mixed b (Ranked c a) ~N MixedNT b c a + +idMixed :: Mixed b a -> Mixed b a +idMixed = undefined + +bar :: forall a b c. Mixed b (Ranked c a) -> Mixed b (Ranked c a) +bar (M_Ranked @_ @c @a arr) + = coerce (idMixed arr) -- fails + -- = coerce (idMixed @_ @(Mixed (Id c) a) arr) -- ok + -- = coerce (id arr) -- ok + -- = let r = idMixed arr in coerce r -- ok + +{- + +arr :: Mixed b (Mixed (Id c) a) + +idMixed arr :: Mixed b (Mixed (Id c) a) + +coerce does + [W] (Mixed b (Mixed (Id c) a)) ~R (Mixed b (Ranked c a)) +--> Unwrap lHS + [W] Mixed False a ~R (Mixed b (Ranked c a)) +--> Unwrap RHS + [W] Mixed False a ~R Mixed b (Mixed (Id c) a) +--> Unwrap RHS again + [W] Mixed False a ~R Mixed False a + + +That is true if + Mixed (Id c) a ~N Ranked c a + +Also + Mixed b (Ranked c a) ~N MixedNT b c a + + [W] (Mixed b (Mixed (Id c) a)) ~R (Mixed b (Ranked c a)) +--> + [W] (Mixed b (Mixed (Id c) a)) ~R (MixedNT b c a) +--> unwrap NT + [W] (Mixed b (Mixed (Id c) a)) ~R (Mixed b (Mixed (Id c) a)) +-} ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -917,3 +917,4 @@ test('T24566', [], makefile_test, []) test('T23764', normal, compile, ['']) test('T23739a', normal, compile, ['']) test('T24810', normal, compile, ['']) +test('T24887', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b0b641771ef22d6259cc093d1fcb380f602cf370 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b0b641771ef22d6259cc093d1fcb380f602cf370 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 16:55:50 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Jun 2024 12:55:50 -0400 Subject: [Git][ghc/ghc][master] compiler: missing-deriving-strategies suggested fix Message-ID: <6669d31673201_167e4d36cc8188634a@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 24 changed files: - compiler/GHC/Rename/Module.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Types/Hint.hs - compiler/GHC/Types/Hint/Ppr.hs - docs/users_guide/using-warnings.rst - testsuite/tests/rename/should_compile/T15798a.hs → testsuite/tests/deriving/should_compile/T15798a.hs - + testsuite/tests/deriving/should_compile/T15798a.stderr - testsuite/tests/rename/should_compile/T15798b.hs → testsuite/tests/deriving/should_compile/T15798b.hs - + testsuite/tests/deriving/should_compile/T15798b.stderr - testsuite/tests/rename/should_compile/T15798c.hs → testsuite/tests/deriving/should_compile/T15798c.hs - + testsuite/tests/deriving/should_compile/T15798c.stderr - + testsuite/tests/deriving/should_compile/T24955a.hs - + testsuite/tests/deriving/should_compile/T24955a.stderr - + testsuite/tests/deriving/should_compile/T24955b.hs - + testsuite/tests/deriving/should_compile/T24955b.stderr - + testsuite/tests/deriving/should_compile/T24955c.hs - + testsuite/tests/deriving/should_compile/T24955c.stderr - testsuite/tests/deriving/should_compile/all.T - − testsuite/tests/rename/should_compile/T15798a.stderr - − testsuite/tests/rename/should_compile/T15798b.stderr - − testsuite/tests/rename/should_compile/T15798c.stderr - testsuite/tests/rename/should_compile/all.T Changes: ===================================== compiler/GHC/Rename/Module.hs ===================================== @@ -1128,12 +1128,10 @@ rnSrcDerivDecl (DerivDecl (inst_warn_ps, ann) ty mds overlap) ; addNoNestedForallsContextsErr ctxt NFC_StandaloneDerivedInstanceHead (getLHsInstDeclHead $ dropWildCards ty') - ; warnNoDerivStrat mds' loc ; inst_warn_rn <- mapM rnLWarningTxt inst_warn_ps ; return (DerivDecl (inst_warn_rn, ann) ty' mds' overlap, fvs) } where ctxt = DerivDeclCtx - loc = getLocA nowc_ty nowc_ty = dropWildCards ty {- @@ -2108,18 +2106,6 @@ The main parts of the implementation are: -} -warnNoDerivStrat :: Maybe (LDerivStrategy GhcRn) - -> SrcSpan - -> RnM () -warnNoDerivStrat mds loc - = do { dyn_flags <- getDynFlags - ; case mds of - Nothing -> - addDiagnosticAt loc $ TcRnNoDerivStratSpecified - (xopt LangExt.DerivingStrategies dyn_flags) - _ -> pure () - } - rnLHsDerivingClause :: HsDocContext -> LHsDerivingClause GhcPs -> RnM (LHsDerivingClause GhcRn, FreeVars) rnLHsDerivingClause doc @@ -2129,7 +2115,6 @@ rnLHsDerivingClause doc , deriv_clause_tys = dct })) = do { (dcs', dct', fvs) <- rnLDerivStrategy doc dcs $ rn_deriv_clause_tys dct - ; warnNoDerivStrat dcs' (locA loc) ; pure ( L loc (HsDerivingClause { deriv_clause_ext = noExtField , deriv_clause_strategy = dcs' , deriv_clause_tys = dct' }) ===================================== compiler/GHC/Tc/Deriv.hs ===================================== @@ -48,6 +48,7 @@ import GHC.Core.Type import GHC.Utils.Error import GHC.Core.DataCon import GHC.Data.Maybe +import GHC.Types.Hint (AssumedDerivingStrategy(..)) import GHC.Types.Name.Reader import GHC.Types.Name import GHC.Types.Name.Set as NameSet @@ -71,6 +72,8 @@ import Control.Monad import Control.Monad.Trans.Class import Control.Monad.Trans.Reader import Data.List (partition, find) +import Data.Map.Strict (Map) +import qualified Data.Map.Strict as Map {- ************************************************************************ @@ -415,6 +418,76 @@ in derived code. @makeDerivSpecs@ fishes around to find the info about needed derived instances. -} +mechanismToAssumedStrategy :: DerivSpecMechanism -> Maybe AssumedDerivingStrategy +mechanismToAssumedStrategy = \case + DerivSpecStock{} -> Just AssumedStockStrategy + DerivSpecAnyClass{} -> Just AssumedAnyclassStrategy + DerivSpecNewtype{} -> Just AssumedNewtypeStrategy + DerivSpecVia{} -> Nothing -- `via` is never assumed, it is always explicit + +warnNoDerivingClauseStrategy + :: Maybe (LDerivStrategy GhcTc) + -- ^ The given deriving strategy, if any. + -> [(LHsSigType GhcRn, EarlyDerivSpec)] + -- ^ The given deriving predicates of a deriving clause (for example 'Show' & + -- 'Eq' in @deriving (Show, Eq)@) along with the 'EarlyDerivSpec' which we + -- use to find out what deriving strategy was actually used. + -- See comments of 'TcRnNoDerivingClauseStrategySpecified'. + -> TcM () +warnNoDerivingClauseStrategy Just{} _early_deriv_specs = pure () +warnNoDerivingClauseStrategy Nothing early_deriv_specs = do + let all_assumed_strategies :: Map AssumedDerivingStrategy [LHsSigType GhcRn] + all_assumed_strategies = + Map.unionsWith (++) (map early_deriv_spec_to_assumed_strategies early_deriv_specs) + + dyn_flags <- getDynFlags + addDiagnosticTc $ + TcRnNoDerivStratSpecified (xopt LangExt.DerivingStrategies dyn_flags) $ + TcRnNoDerivingClauseStrategySpecified all_assumed_strategies + + where + deriv_spec_to_assumed_strategy :: LHsSigType GhcRn + -> DerivSpec theta + -> Map AssumedDerivingStrategy [LHsSigType GhcRn] + deriv_spec_to_assumed_strategy deriv_head deriv_spec = + Map.fromList + [ (strat, [deriv_head]) + | strat <- maybeToList $ mechanismToAssumedStrategy (ds_mechanism deriv_spec) + ] + + early_deriv_spec_to_assumed_strategies :: (LHsSigType GhcRn, EarlyDerivSpec) + -> Map AssumedDerivingStrategy [LHsSigType GhcRn] + early_deriv_spec_to_assumed_strategies (deriv_head, InferTheta deriv_spec) = + deriv_spec_to_assumed_strategy deriv_head deriv_spec + early_deriv_spec_to_assumed_strategies (deriv_head, GivenTheta deriv_spec) = + deriv_spec_to_assumed_strategy deriv_head deriv_spec + +warnNoStandaloneDerivingStrategy + :: Maybe (LDerivStrategy GhcTc) + -- ^ The given deriving strategy, if any. + -> LHsSigWcType GhcRn + -- ^ The standalone deriving declaration's signature for example, the: + -- C a => C (T a) + -- part of the standalone deriving instance: + -- deriving instance C a => C (T a) + -> EarlyDerivSpec + -- ^ We extract the assumed deriving strategy from this. + -> TcM () +warnNoStandaloneDerivingStrategy Just{} _deriv_ty _early_deriv_spec = pure () +warnNoStandaloneDerivingStrategy Nothing deriv_ty early_deriv_spec = + case mechanismToAssumedStrategy $ early_deriv_spec_mechanism early_deriv_spec of + Nothing -> pure () + Just assumed_strategy -> do + dyn_flags <- getDynFlags + addDiagnosticTc $ + TcRnNoDerivStratSpecified (xopt LangExt.DerivingStrategies dyn_flags) $ + TcRnNoStandaloneDerivingStrategySpecified assumed_strategy deriv_ty + + where + early_deriv_spec_mechanism :: EarlyDerivSpec -> DerivSpecMechanism + early_deriv_spec_mechanism (InferTheta deriv_spec) = ds_mechanism deriv_spec + early_deriv_spec_mechanism (GivenTheta deriv_spec) = ds_mechanism deriv_spec + makeDerivSpecs :: [DerivInfo] -> [LDerivDecl GhcRn] -> TcM [EarlyDerivSpec] @@ -433,10 +506,10 @@ makeDerivSpecs deriv_infos deriv_decls ; eqns2 <- mapM (recoverM (pure Nothing) . deriveStandalone) deriv_decls ; return $ concat eqns1 ++ catMaybes eqns2 } where - deriv_clause_preds :: LDerivClauseTys GhcRn -> [LHsSigType GhcRn] - deriv_clause_preds (L _ dct) = case dct of - DctSingle _ ty -> [ty] - DctMulti _ tys -> tys + deriv_clause_preds :: LDerivClauseTys GhcRn -> LocatedC [LHsSigType GhcRn] + deriv_clause_preds (L loc dct) = case dct of + DctSingle _ ty -> L loc [ty] + DctMulti _ tys -> L loc tys ------------------------------------------------------------------ -- | Process the derived classes in a single @deriving@ clause. @@ -444,10 +517,13 @@ deriveClause :: TyCon -> [(Name, TcTyVar)] -- Scoped type variables taken from tcTyConScopedTyVars -- See Note [Scoped tyvars in a TcTyCon] in "GHC.Core.TyCon" -> Maybe (LDerivStrategy GhcRn) - -> [LHsSigType GhcRn] -> SDoc + -> LocatedC [LHsSigType GhcRn] + -- ^ The location refers to the @(Show, Eq)@ part of @deriving (Show, Eq)@. + -> SDoc -> TcM [EarlyDerivSpec] -deriveClause rep_tc scoped_tvs mb_lderiv_strat deriv_preds err_ctxt - = addErrCtxt err_ctxt $ do +deriveClause rep_tc scoped_tvs mb_lderiv_strat (L loc deriv_preds) err_ctxt + = setSrcSpanA loc $ + addErrCtxt err_ctxt $ do traceTc "deriveClause" $ vcat [ text "tvs" <+> ppr tvs , text "scoped_tvs" <+> ppr scoped_tvs @@ -456,15 +532,21 @@ deriveClause rep_tc scoped_tvs mb_lderiv_strat deriv_preds err_ctxt , text "mb_lderiv_strat" <+> ppr mb_lderiv_strat ] tcExtendNameTyVarEnv scoped_tvs $ do (mb_lderiv_strat', via_tvs) <- tcDerivStrategy mb_lderiv_strat - tcExtendTyVarEnv via_tvs $ + earlyDerivSpecs <- tcExtendTyVarEnv via_tvs $ -- Moreover, when using DerivingVia one can bind type variables in -- the `via` type as well, so these type variables must also be -- brought into scope. - mapMaybeM (derivePred tc tys mb_lderiv_strat' via_tvs) deriv_preds + mapMaybeM + (\deriv_pred -> + do maybe_early_deriv_spec <- derivePred tc tys mb_lderiv_strat' via_tvs deriv_pred + pure $ fmap (deriv_pred,) maybe_early_deriv_spec) + deriv_preds -- After typechecking the `via` type once, we then typecheck all -- of the classes associated with that `via` type in the -- `deriving` clause. -- See also Note [Don't typecheck too much in DerivingVia]. + warnNoDerivingClauseStrategy mb_lderiv_strat' earlyDerivSpecs + return (snd <$> earlyDerivSpecs) where tvs = tyConTyVars rep_tc (tc, tys) = case tyConFamInstSig_maybe rep_tc of @@ -678,10 +760,16 @@ deriveStandalone (L loc (DerivDecl (warn, _) deriv_ty mb_lderiv_strat overlap_mo ; if className cls == typeableClassName then do warnUselessTypeable return Nothing - else Just <$> mkEqnHelp (fmap unLoc overlap_mode) - tvs' cls inst_tys' - deriv_ctxt' mb_deriv_strat' - (fmap unLoc warn) } + else do early_deriv_spec <- + mkEqnHelp (fmap unLoc overlap_mode) + tvs' cls inst_tys' + deriv_ctxt' mb_deriv_strat' + (fmap unLoc warn) + warnNoStandaloneDerivingStrategy + mb_lderiv_strat + deriv_ty + early_deriv_spec + pure (Just early_deriv_spec) } -- Typecheck the type in a standalone deriving declaration. -- ===================================== compiler/GHC/Tc/Errors/Ppr.hs ===================================== @@ -3038,9 +3038,13 @@ instance Diagnostic TcRnMessage where _ -> [suggestExtension LangExt.DerivingStrategies] TcRnIllegalMultipleDerivClauses{} -> [suggestExtension LangExt.DerivingStrategies] - TcRnNoDerivStratSpecified isDSEnabled -> if isDSEnabled - then noHints - else [suggestExtension LangExt.DerivingStrategies] + TcRnNoDerivStratSpecified is_ds_enabled info -> do + let explicit_strategy_hint = case info of + TcRnNoDerivingClauseStrategySpecified assumed_derivings -> + SuggestExplicitDerivingClauseStrategies assumed_derivings + TcRnNoStandaloneDerivingStrategySpecified assumed_strategy deriv_sig -> + SuggestExplicitStandaloneDerivingStrategy assumed_strategy deriv_sig + explicit_strategy_hint : [suggestExtension LangExt.DerivingStrategies | not is_ds_enabled] TcRnStupidThetaInGadt{} -> noHints TcRnShadowedTyVarNameInFamResult{} ===================================== compiler/GHC/Tc/Errors/Types.hs ===================================== @@ -53,6 +53,7 @@ module GHC.Tc.Errors.Types ( , Exported(..) , HsDocContext(..) , FixedRuntimeRepErrorInfo(..) + , TcRnNoDerivStratSpecifiedInfo(..) , ErrorItem(..), errorItemOrigin, errorItemEqRel, errorItemPred, errorItemCtLoc @@ -180,7 +181,7 @@ import GHC.Tc.Utils.TcType (TcType, TcSigmaType, TcPredType, import GHC.Types.Basic import GHC.Types.Error import GHC.Types.Avail -import GHC.Types.Hint (UntickedPromotedThing(..)) +import GHC.Types.Hint (UntickedPromotedThing(..), AssumedDerivingStrategy(..)) import GHC.Types.ForeignCall (CLabelString) import GHC.Types.Id.Info ( RecSelParent(..) ) import GHC.Types.Name (NamedThing(..), Name, OccName, getSrcLoc, getSrcSpan) @@ -219,6 +220,7 @@ import qualified Data.List.NonEmpty as NE import Data.Typeable (Typeable) import GHC.Unit.Module.Warnings (WarningCategory, WarningTxt) import qualified GHC.Internal.TH.Syntax as TH +import Data.Map.Strict (Map) import GHC.Generics ( Generic ) import GHC.Types.Name.Env (NameEnv) @@ -3265,20 +3267,22 @@ data TcRnMessage where -} TcRnIllegalMultipleDerivClauses :: TcRnMessage - {-| TcRnNoDerivStratSpecified is a warning implied by -Wmissing-deriving-strategies - and triggered by deriving clause without specified deriving strategy. + {-| TcRnNoDerivStratSpecified is a warning implied by + -Wmissing-deriving-strategies and triggered by deriving without + mentioning a strategy. - Example: + See 'TcRnNoDerivStratSpecifiedInfo' cases for examples. - data T = T - deriving Eq - - Test cases: rename/should_compile/T15798a - rename/should_compile/T15798b - rename/should_compile/T15798c + Test cases: deriving/should_compile/T15798a + deriving/should_compile/T15798b + deriving/should_compile/T15798c + deriving/should_compile/T24955a + deriving/should_compile/T24955b + deriving/should_compile/T24955c -} TcRnNoDerivStratSpecified - :: Bool -- True if DerivingStrategies is enabled + :: Bool -- ^ True if DerivingStrategies is enabled + -> TcRnNoDerivStratSpecifiedInfo -> TcRnMessage {-| TcRnStupidThetaInGadt is an error triggered by data contexts in GADT-style @@ -6740,3 +6744,48 @@ data TypeCannotBeMarshaledReason | NotSimpleUnliftedType | NotBoxedKindAny deriving Generic + +data TcRnNoDerivStratSpecifiedInfo where + {-| 'TcRnNoDerivStratSpecified TcRnNoDerivingClauseStrategySpecified' is + a warning implied by -Wmissing-deriving-strategies and triggered by a + deriving clause without a specified deriving strategy. + + Example: + + newtype T = T Int + deriving (Eq, Ord, Show) + + Here we would suggest fixing the deriving clause to: + + deriving stock (Show) + deriving newtype (Eq, Ord) + + Test cases: deriving/should_compile/T15798a + deriving/should_compile/T15798c + deriving/should_compile/T24955a + deriving/should_compile/T24955b + -} + TcRnNoDerivingClauseStrategySpecified + :: Map AssumedDerivingStrategy [LHsSigType GhcRn] + -> TcRnNoDerivStratSpecifiedInfo + + {-| 'TcRnNoDerivStratSpecified TcRnNoStandaloneDerivingStrategySpecified' is + a warning implied by -Wmissing-deriving-strategies and triggered by a + standalone deriving declaration without a specified deriving strategy. + + Example: + + data T a = T a + deriving instance Show a => Show (T a) + + Here we would suggest fixing the instance to: + + deriving stock instance Show a => Show (T a) + + Test cases: deriving/should_compile/T15798b + deriving/should_compile/T24955c + -} + TcRnNoStandaloneDerivingStrategySpecified + :: AssumedDerivingStrategy + -> LHsSigWcType GhcRn -- ^ The instance signature (e.g @Show a => Show (T a)@) + -> TcRnNoDerivStratSpecifiedInfo ===================================== compiler/GHC/Types/Hint.hs ===================================== @@ -10,6 +10,7 @@ module GHC.Types.Hint ( , SimilarName(..) , StarIsType(..) , UntickedPromotedThing(..) + , AssumedDerivingStrategy(..) , pprUntickedConstructor, isBareSymbol , suggestExtension , suggestExtensionWithInfo @@ -22,7 +23,7 @@ module GHC.Types.Hint ( ) where import Language.Haskell.Syntax.Expr (LHsExpr) -import Language.Haskell.Syntax (LPat, LIdP) +import Language.Haskell.Syntax (LPat, LIdP, LHsSigType, LHsSigWcType) import GHC.Prelude @@ -46,6 +47,7 @@ import GHC.Utils.Outputable import GHC.Data.FastString (fsLit, FastString) import Data.Typeable ( Typeable ) +import Data.Map.Strict (Map) -- | The bindings we have available in scope when -- suggesting an explicit type signature. @@ -477,6 +479,40 @@ data GhcHint {-| Suggest binding explicitly; e.g data T @k (a :: F k) = .... -} | SuggestBindTyVarExplicitly Name + {-| Suggest using explicit deriving strategies for a deriving clause. + + Triggered by: 'GHC.Tc.Errors.Types.TcRnNoDerivingClauseStrategySpecified'. + + See comment of 'TcRnNoDerivingClauseStrategySpecified' for context. + -} + | SuggestExplicitDerivingClauseStrategies + (Map AssumedDerivingStrategy [LHsSigType GhcRn]) + -- ^ Those deriving clauses that we assumed a particular strategy for. + + {-| Suggest using an explicit deriving strategy for a standalone deriving instance. + + Triggered by: 'GHC.Tc.Errors.Types.TcRnNoStandaloneDerivingStrategySpecified'. + + See comment of 'TcRnNoStandaloneDerivingStrategySpecified' for context. + -} + | SuggestExplicitStandaloneDerivingStrategy + AssumedDerivingStrategy -- ^ The deriving strategy we assumed + (LHsSigWcType GhcRn) -- ^ The instance signature (e.g 'Show a => Show (T a)') + +-- | The deriving strategy that was assumed when not explicitly listed in the +-- source. This is used solely by the missing-deriving-strategies warning. +-- There's no `Via` case because we never assume that. +data AssumedDerivingStrategy + = AssumedStockStrategy + | AssumedAnyclassStrategy + | AssumedNewtypeStrategy + deriving (Eq, Ord) + +instance Outputable AssumedDerivingStrategy where + ppr AssumedStockStrategy = text "stock" + ppr AssumedAnyclassStrategy = text "anyclass" + ppr AssumedNewtypeStrategy = text "newtype" + -- | An 'InstantiationSuggestion' for a '.hsig' file. This is generated -- by GHC in case of a 'DriverUnexpectedSignature' and suggests a way -- to instantiate a particular signature, where the first argument is ===================================== compiler/GHC/Types/Hint/Ppr.hs ===================================== @@ -1,7 +1,7 @@ {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} -{-# OPTIONS_GHC -Wno-orphans #-} -- instance Outputable GhcHint +{-# OPTIONS_GHC -Wno-orphans #-} {- instance Outputable GhcHint -} module GHC.Types.Hint.Ppr ( perhapsAsPat @@ -28,10 +28,10 @@ import GHC.Utils.Outputable import GHC.Driver.Flags import qualified Data.List.NonEmpty as NE +import qualified Data.Map.Strict as Map import qualified GHC.LanguageExtensions as LangExt - instance Outputable GhcHint where ppr = \case UnknownHint m @@ -270,6 +270,19 @@ instance Outputable GhcHint where SuggestBindTyVarExplicitly tv -> text "bind" <+> quotes (ppr tv) <+> text "explicitly with" <+> quotes (char '@' <> ppr tv) + SuggestExplicitDerivingClauseStrategies assumed_derivings -> + hang + (text "Use explicit deriving strategies:") + 2 + (vcat $ map pp_derivings (Map.toList assumed_derivings)) + where + pp_derivings (strat, preds) = + hsep [text "deriving", ppr strat, parens (pprWithCommas ppr preds)] + SuggestExplicitStandaloneDerivingStrategy strat deriv_sig -> + hang + (text "Use an explicit deriving strategy:") + 2 + (hsep [text "deriving", ppr strat, text "instance", ppr deriv_sig]) perhapsAsPat :: SDoc perhapsAsPat = text "Perhaps you meant an as-pattern, which must not be surrounded by whitespace" ===================================== docs/users_guide/using-warnings.rst ===================================== @@ -1109,7 +1109,7 @@ of ``-W(no-)*``. d a = x a -- would not warn .. ghc-flag:: -Wmissing-deriving-strategies - :shortdesc: warn when a deriving clause is missing a deriving strategy + :shortdesc: warn when deriving without mentioning a deriving strategy :type: dynamic :reverse: -Wno-missing-deriving-strategies :category: @@ -1125,8 +1125,11 @@ of ``-W(no-)*``. deriving (Eq) The compiler will warn here that the deriving clause doesn't specify a - strategy. If the warning is enabled, but :extension:`DerivingStrategies` is - not enabled, the compiler will suggest turning on the + strategy. The suggested fix will show which deriving strategies were + assumed. + + If the warning is enabled, but :extension:`DerivingStrategies` is not + enabled, the compiler will suggest turning on the :extension:`DerivingStrategies` extension. .. ghc-flag:: -Wmissing-fields ===================================== testsuite/tests/rename/should_compile/T15798a.hs → testsuite/tests/deriving/should_compile/T15798a.hs ===================================== ===================================== testsuite/tests/deriving/should_compile/T15798a.stderr ===================================== @@ -0,0 +1,6 @@ +T15798a.hs:11:12: warning: [GHC-55631] [-Wmissing-deriving-strategies] + • No deriving strategy specified. Did you want stock, newtype, or anyclass? + • In the data declaration for ‘Bar’ + Suggested fix: + Use explicit deriving strategies: deriving stock (Eq, Show) + ===================================== testsuite/tests/rename/should_compile/T15798b.hs → testsuite/tests/deriving/should_compile/T15798b.hs ===================================== ===================================== testsuite/tests/deriving/should_compile/T15798b.stderr ===================================== @@ -0,0 +1,8 @@ +T15798b.hs:9:1: warning: [GHC-55631] [-Wmissing-deriving-strategies] + • No deriving strategy specified. Did you want stock, newtype, or anyclass? + • In the stand-alone deriving instance for ‘Eq a => Eq (Foo a)’ + Suggested fixes: + • Use an explicit deriving strategy: + deriving stock instance Eq a => Eq (Foo a) + • Perhaps you intended to use the ‘DerivingStrategies’ extension (implied by ‘DerivingVia’) + ===================================== testsuite/tests/rename/should_compile/T15798c.hs → testsuite/tests/deriving/should_compile/T15798c.hs ===================================== ===================================== testsuite/tests/deriving/should_compile/T15798c.stderr ===================================== @@ -0,0 +1,7 @@ +T15798c.hs:6:12: warning: [GHC-55631] [-Wmissing-deriving-strategies] + • No deriving strategy specified. Did you want stock, newtype, or anyclass? + • In the data declaration for ‘Foo’ + Suggested fixes: + • Use explicit deriving strategies: deriving stock (Eq) + • Perhaps you intended to use the ‘DerivingStrategies’ extension (implied by ‘DerivingVia’) + ===================================== testsuite/tests/deriving/should_compile/T24955a.hs ===================================== @@ -0,0 +1,10 @@ +{-# OPTIONS_GHC -Wmissing-deriving-strategies #-} + +module T24955a () where + +-- Listing multiple classes which use different assumed strategies. +-- The suggested fixes should list: +-- deriving stock (Show, Read) +-- deriving newtype (Eq, Ord) +newtype N = N Int + deriving (Show, Eq, Read, Ord) ===================================== testsuite/tests/deriving/should_compile/T24955a.stderr ===================================== @@ -0,0 +1,9 @@ +T24955a.hs:10:12: warning: [GHC-55631] [-Wmissing-deriving-strategies] + • No deriving strategy specified. Did you want stock, newtype, or anyclass? + • In the newtype declaration for ‘N’ + Suggested fixes: + • Use explicit deriving strategies: + deriving stock (Show, Read) + deriving newtype (Eq, Ord) + • Perhaps you intended to use the ‘DerivingStrategies’ extension (implied by ‘DerivingVia’) + ===================================== testsuite/tests/deriving/should_compile/T24955b.hs ===================================== @@ -0,0 +1,11 @@ +{-# OPTIONS_GHC -Wmissing-deriving-strategies #-} +{-# LANGUAGE FunctionalDependencies #-} + +module T24955b () where + +class C a b | b -> a + +instance C Int Int + +newtype N = N Int + deriving (C Int) ===================================== testsuite/tests/deriving/should_compile/T24955b.stderr ===================================== @@ -0,0 +1,7 @@ +T24955b.hs:11:12: warning: [GHC-55631] [-Wmissing-deriving-strategies] + • No deriving strategy specified. Did you want stock, newtype, or anyclass? + • In the newtype declaration for ‘N’ + Suggested fixes: + • Use explicit deriving strategies: deriving newtype (C Int) + • Perhaps you intended to use the ‘DerivingStrategies’ extension (implied by ‘DerivingVia’) + ===================================== testsuite/tests/deriving/should_compile/T24955c.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE StandaloneDeriving #-} + +{-# OPTIONS_GHC -Wmissing-deriving-strategies #-} + +module T24955c () where + +data Foo a = Foo a + +deriving instance Eq a => Eq (Foo a) ===================================== testsuite/tests/deriving/should_compile/T24955c.stderr ===================================== @@ -0,0 +1,8 @@ +T24955c.hs:9:1: warning: [GHC-55631] [-Wmissing-deriving-strategies] + • No deriving strategy specified. Did you want stock, newtype, or anyclass? + • In the stand-alone deriving instance for ‘Eq a => Eq (Foo a)’ + Suggested fixes: + • Use an explicit deriving strategy: + deriving stock instance Eq a => Eq (Foo a) + • Perhaps you intended to use the ‘DerivingStrategies’ extension (implied by ‘DerivingVia’) + ===================================== testsuite/tests/deriving/should_compile/all.T ===================================== @@ -144,3 +144,9 @@ test('T22696a', normal, compile, ['']) test('T22696c', normal, compile, ['']) test('T23329', normal, multimod_compile, ['T23329', '-v0']) test('T17328', [extra_files(['T17328a.hs'])], multimod_compile, ['T17328', '-v0']) +test('T15798a', normal, compile, ['']) +test('T15798b', normal, compile, ['']) +test('T15798c', normal, compile, ['']) +test('T24955a', normal, compile, ['']) +test('T24955b', normal, compile, ['']) +test('T24955c', normal, compile, ['']) ===================================== testsuite/tests/rename/should_compile/T15798a.stderr deleted ===================================== @@ -1,3 +0,0 @@ - -T15798a.hs:11:3: warning: [GHC-55631] [-Wmissing-deriving-strategies] - No deriving strategy specified. Did you want stock, newtype, or anyclass? ===================================== testsuite/tests/rename/should_compile/T15798b.stderr deleted ===================================== @@ -1,5 +0,0 @@ - -T15798b.hs:9:19: warning: [GHC-55631] [-Wmissing-deriving-strategies] - No deriving strategy specified. Did you want stock, newtype, or anyclass? - Suggested fix: - Perhaps you intended to use the ‘DerivingStrategies’ extension (implied by ‘DerivingVia’) ===================================== testsuite/tests/rename/should_compile/T15798c.stderr deleted ===================================== @@ -1,5 +0,0 @@ - -T15798c.hs:6:3: warning: [GHC-55631] [-Wmissing-deriving-strategies] - No deriving strategy specified. Did you want stock, newtype, or anyclass? - Suggested fix: - Perhaps you intended to use the ‘DerivingStrategies’ extension (implied by ‘DerivingVia’) ===================================== testsuite/tests/rename/should_compile/all.T ===================================== @@ -164,9 +164,6 @@ test('T15149', [], multimod_compile, ['T15149', '-v0']) test('T15214', normal, compile, ['']) test('T13064', normal, compile, ['']) test('T15994', [], makefile_test, ['T15994']) -test('T15798a', normal, compile, ['']) -test('T15798b', normal, compile, ['']) -test('T15798c', normal, compile, ['']) test('T16116a', normal, compile, ['']) test('T15957', normal, compile, ['-Werror -Wredundant-record-wildcards -Wunused-record-wildcards']) test('T17244A', normal, compile, ['-Wno-error=compat-unqualified-imports']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cb7c1b83004acc3505d1ffa7c82b5956e6a98b6a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cb7c1b83004acc3505d1ffa7c82b5956e6a98b6a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 16:56:40 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Jun 2024 12:56:40 -0400 Subject: [Git][ghc/ghc][master] Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat Message-ID: <6669d3486320_167e4d37acb7091116@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 1 changed file: - compiler/Language/Haskell/Syntax/Pat.hs Changes: ===================================== compiler/Language/Haskell/Syntax/Pat.hs ===================================== @@ -60,7 +60,8 @@ type LPat p = XRec p (Pat p) data Pat p = ------------ Simple patterns --------------- WildPat (XWildPat p) - -- ^ Wildcard Pattern (@_@) + -- ^ Wildcard Pattern, i.e. @_@ + | VarPat (XVarPat p) (LIdP p) -- ^ Variable Pattern, e.g. @x@ @@ -70,7 +71,7 @@ data Pat p (LPat p) -- ^ Lazy Pattern, e.g. @~x@ -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnTilde' + -- exactprint: the location of @~@ is captured using 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnTilde' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation @@ -79,7 +80,7 @@ data Pat p (LPat p) -- ^ As pattern, e.g. @x\@pat@ -- - -- - Location of '@' is captured by 'GHC.Parser.Annotation.EpToken' @"\@"@ + -- exactprint: the location of @\@@ is captured using 'GHC.Parser.Annotation.EpToken' @"\@"@ -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation @@ -87,9 +88,7 @@ data Pat p (LPat p) -- ^ Parenthesised pattern, e.g. @(x)@ -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : - -- 'GHC.Parser.Annotation.AnnOpen' @'('@, - -- 'GHC.Parser.Annotation.AnnClose' @')'@ + -- exactprint: the location of parentheses is captured using 'GHC.Parser.Annotation.EpToken' @"("@ and 'GHC.Parser.Annotation.EpToken' @")"@ -- See Note [Parens in HsSyn] in GHC.Hs.Expr @@ -98,31 +97,31 @@ data Pat p (LPat p) -- ^ Bang pattern, e.g. @!x@ -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang' + -- exactprint: the location of @!@ is captured using 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnBang' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation ------------ Lists, tuples, arrays --------------- | ListPat (XListPat p) [LPat p] - -- ^ Syntactic List, e.g. @[x]@ or @[x,y]@ (but not @[]@ nor @(x:xs)@ which are represented using 'ConPat') + -- ^ Syntactic List, e.g. @[x]@ or @[x,y]@. + -- Note that @[]@ and @(x:xs)@ patterns are both represented using 'ConPat'. -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : - -- 'GHC.Parser.Annotation.AnnOpen' @'['@, - -- 'GHC.Parser.Annotation.AnnClose' @']'@ + -- exactprint: the location of brackets is captured using 'GHC.Parser.Annotation.AnnKeywordId' : + -- 'GHC.Parser.Annotation.AnnOpenS' and 'GHC.Parser.Annotation.AnnCloseS' respectively. -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation - | -- | Tuple pattern, e.g. @(x, y)@ + | -- | Tuple pattern, e.g. @(x, y)@ (boxed tuples) or @(# x, y #)@ (requires @-XUnboxedTuples@) -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : - -- 'GHC.Parser.Annotation.AnnOpen' @'('@ or @'(#'@, - -- 'GHC.Parser.Annotation.AnnClose' @')'@ or @'#)'@ + -- exactprint: the location of parens is captured using 'GHC.Parser.Annotation.AnnKeywordId' : + -- 'GHC.Parser.Annotation.AnnOpenP' and 'GHC.Parser.Annotation.AnnCloseP' in case of boxed tuples + -- or 'GHC.Parser.Annotation.AnnOpenPH' and 'GHC.Parser.Annotation.AnnClosePH' in case of unboxed tuples. -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation TuplePat (XTuplePat p) -- ^ After typechecking, holds the types of the tuple components [LPat p] -- ^ Tuple sub-patterns - Boxity -- ^ UnitPat is TuplePat [] + Boxity -- You might think that the post typechecking Type was redundant, -- because we can get the pattern type by getting the types of the @@ -143,7 +142,9 @@ data Pat p | OrPat (XOrPat p) (NonEmpty (LPat p)) - -- ^ Or Pattern + -- ^ Or Pattern, e.g. @(pat_1; ...; pat_n)@. Used by @-XOrPatterns@ + -- + -- @since 9.12.1 | SumPat (XSumPat p) -- after typechecker, types of the alternative (LPat p) -- Sum sub-pattern @@ -152,9 +153,8 @@ data Pat p -- ^ Anonymous sum pattern, e.g. @(# x | #)@. Used by @-XUnboxedSums@ -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : - -- 'GHC.Parser.Annotation.AnnOpen' @'(#'@, - -- 'GHC.Parser.Annotation.AnnClose' @'#)'@ + -- exactprint: the location of @(#@ and @#)@ is captured using 'GHC.Parser.Annotation.AnnKeywordId' : + -- 'GHC.Parser.Annotation.AnnOpenPH' and 'GHC.Parser.Annotation.AnnClosePH' respectively. -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation @@ -164,7 +164,7 @@ data Pat p pat_con :: XRec p (ConLikeP p), pat_args :: HsConPatDetails p } - -- ^ Constructor Pattern, e.g. @[]@ or @Nothing@ + -- ^ Constructor Pattern, e.g. @()@, @[]@ or @Nothing@ ------------ View patterns --------------- @@ -173,7 +173,7 @@ data Pat p (LPat p) -- ^ View Pattern, e.g. @someFun -> pat at . Used by @-XViewPatterns@ -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnRarrow' + -- exactprint: the location of @->@ is captured using 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnRarrow' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation @@ -181,13 +181,7 @@ data Pat p | SplicePat (XSplicePat p) (HsUntypedSplice p) - -- ^ Splice Pattern (Includes quasi-quotes @$(...)@) - -- - -- - 'GHC.Parser.Annotation.AnnKeywordId': - -- 'GHC.Parser.Annotation.AnnOpen' @'$('@ - -- 'GHC.Parser.Annotation.AnnClose' @')'@ - - -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation + -- ^ Splice Pattern, e.g. @$(pat)@ ------------ Literal and n+k patterns --------------- | LitPat (XLitPat p) @@ -209,10 +203,12 @@ data Pat p -- ^ Natural Pattern, used for all overloaded literals, including overloaded Strings -- with @-XOverloadedStrings@ -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnVal' @'+'@ + -- exactprint: the location of @-@ (for negative literals) is captured using 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnMinus' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation - | NPlusKPat (XNPlusKPat p) -- Type of overall pattern + + | -- | n+k pattern, e.g. @n+1@, used by @-XNPlusKPatterns@ + NPlusKPat (XNPlusKPat p) -- Type of overall pattern (LIdP p) -- n+k pattern (XRec p (HsOverLit p)) -- It'll always be an HsIntegral (HsOverLit p) -- See Note [NPlusK patterns] in GHC.Tc.Gen.Pat @@ -221,7 +217,6 @@ data Pat p (SyntaxExpr p) -- (>=) function, of type t1->t2->Bool (SyntaxExpr p) -- Name of '-' (see GHC.Rename.Env.lookupSyntax) - -- ^ n+k pattern, e.g. @n+1@, enabled by @-XNPlusKPatterns@ extension ------------ Pattern type signatures --------------- @@ -232,19 +227,22 @@ data Pat p -- ^ Pattern with a type signature, e.g. @x :: Int@ -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' + -- exactprint: the location of @::@ is captured using 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnDcolon' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation - | -- | Embed the syntax of types into patterns. - -- Used with @-XRequiredTypeArguments@, e.g. @fn (type t) = rhs@ + | -- | Embed the syntax of types into patterns, e.g. @fn (type t) = rhs at . + -- Enabled by @-XExplicitNamespaces@ in conjunction with @-XRequiredTypeArguments at . + -- + -- exactprint: the location of the @type@ keyword is captured using 'GHC.Parser.Annotation.EpToken' @"type"@ EmbTyPat (XEmbTyPat p) (HsTyPat (NoGhcTc p)) | InvisPat (XInvisPat p) (HsTyPat (NoGhcTc p)) - -- ^ Type abstraction which brings into scope type variables associated with invisible forall. Used by @-XTypeAbstractions at . + -- ^ Type abstraction which brings into scope type variables associated with invisible forall. + -- E.g. @fn \@t ... = rhs at . Used by @-XTypeAbstractions at . -- - -- The location of @\@@ is captured by 'GHC.Parser.Annotation.EpToken' @"\@"@ + -- exactprint: the location of @\@@ is captured by 'GHC.Parser.Annotation.EpToken' @"\@"@ -- See Note [Invisible binders in functions] in GHC.Hs.Pat View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4e36d3a3540514c873f12b4a2123d4a75b1bdd44 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4e36d3a3540514c873f12b4a2123d4a75b1bdd44 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 16:57:09 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Jun 2024 12:57:09 -0400 Subject: [Git][ghc/ghc][master] rts: use page sized mblocks on wasm Message-ID: <6669d365df28c_167e4d38e45b0913f@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - 4 changed files: - + libraries/ghc-compact/tests/T18757.stdout-wasm32-unknown-wasi - rts/include/rts/Constants.h - rts/sm/NonMoving.h - rts/wasm/OSMem.c Changes: ===================================== libraries/ghc-compact/tests/T18757.stdout-wasm32-unknown-wasi ===================================== @@ -0,0 +1 @@ +[61420,61420,61420,60388,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132,60132] ===================================== rts/include/rts/Constants.h ===================================== @@ -170,7 +170,11 @@ #define BLOCK_SHIFT 12 /* The size of a megablock (2^MBLOCK_SHIFT bytes) */ +#if defined(wasm32_HOST_ARCH) +#define MBLOCK_SHIFT 16 +#else #define MBLOCK_SHIFT 20 +#endif /* ----------------------------------------------------------------------------- Bitmap/size fields (used in info tables) ===================================== rts/sm/NonMoving.h ===================================== @@ -17,7 +17,12 @@ #include "BeginPrivate.h" // Segments +#if defined(wasm32_HOST_ARCH) +#define NONMOVING_SEGMENT_BITS 14ULL // 2^14 = 16kByte +#else #define NONMOVING_SEGMENT_BITS 15ULL // 2^15 = 32kByte +#endif + // Mask to find base of segment #define NONMOVING_SEGMENT_MASK (((uintptr_t)1 << NONMOVING_SEGMENT_BITS) - 1) // In bytes ===================================== rts/wasm/OSMem.c ===================================== @@ -32,14 +32,8 @@ // libc allocator's certain invariants. But dlmalloc permits this // behavior! // -// Therefore, we bypass dlmalloc, and directly call memory.grow to -// allocate megablocks. We even patch dlmalloc in the libc sysroot -// shipped in our wasi-sdk release, so that whenever dlmalloc calls -// sbrk(), it extends the linear memory to align to the megablock -// size, so to avoid space waste as much as possible. Our wasi-libc -// patch doesn't impact ABI interoperability, and when stock clang -// compiles code that calls malloc() to wasm objects, those objects -// would just link fine with our build products. +// Therefore, we bypass dlmalloc, and directly call sbrk() to +// allocate megablocks. // // One remaining question is how to free a megablock. Wasm spec // doesn't allow shrinking the linear memory, so the logic of @@ -49,12 +43,13 @@ // megablock on Wasm. #include "Rts.h" - -#include "RtsUtils.h" #include "sm/OSMem.h" -#include "rts/storage/HeapAlloc.h" -#include <__macro_PAGESIZE.h> +#include + +#define PAGESIZE (0x10000) + +GHC_STATIC_ASSERT(MBLOCK_SIZE == PAGESIZE, "MBLOCK_SIZE must be equal to wasm page size"); void osMemInit(void) { @@ -63,13 +58,7 @@ void osMemInit(void) void * osGetMBlocks(uint32_t n) { - size_t base = __builtin_wasm_memory_size(0) * PAGESIZE; - size_t start = MBLOCK_ROUND_UP(base); - size_t end = start + (n << MBLOCK_SHIFT); - ptrdiff_t delta = (end - base) / PAGESIZE; - if (__builtin_wasm_memory_grow(0, delta) == SIZE_MAX) - barf("osGetMBlocks failed"); - return start; + return sbrk(PAGESIZE * n); } void osBindMBlocksToNode( View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/558353f4e22643b94b9710a45c3364c518d57b46 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/558353f4e22643b94b9710a45c3364c518d57b46 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 17:26:53 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Jun 2024 13:26:53 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 11 commits: Fix a QuickLook bug Message-ID: <6669da5d11cc2_167e4d3d045b4935ed@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - 5601ef61 by Matthew Pickering at 2024-06-12T13:26:38-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 4024e2f4 by Hécate Kleidukos at 2024-06-12T13:26:43-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - 80e1935a by Matthew Pickering at 2024-06-12T13:26:44-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 24 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Builtin/Names.hs - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3e19b803291a9ab526a19514d2bdfd71722a89a1...80e1935ae702345b011fb3eac43a699dadd91338 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3e19b803291a9ab526a19514d2bdfd71722a89a1...80e1935ae702345b011fb3eac43a699dadd91338 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 22:54:16 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 12 Jun 2024 18:54:16 -0400 Subject: [Git][ghc/ghc][wip/T24978] Add Given builtin deductions Message-ID: <666a271885328_2b8a4b1e9c0e01660c2@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24978 at Glasgow Haskell Compiler / GHC Commits: 0d1908ce by Simon Peyton Jones at 2024-06-12T23:53:13+01:00 Add Given builtin deductions Addresses #24845. Needs documentation - - - - - 6 changed files: - compiler/GHC/Core/Coercion.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Types/Constraint.hs Changes: ===================================== compiler/GHC/Core/Coercion.hs ===================================== @@ -1459,6 +1459,7 @@ setNominalRole_maybe r co setNominalRole_maybe_helper co@(UnivCo { uco_prov = prov }) | case prov of PhantomProv {} -> False -- should always be phantom ProofIrrelProv {} -> True -- it's always safe + BuiltinProv {} -> True -- always nominal PluginProv {} -> False -- who knows? This choice is conservative. = Just $ co { uco_role = Nominal } setNominalRole_maybe_helper _ = Nothing ===================================== compiler/GHC/Core/TyCo/Rep.hs ===================================== @@ -912,13 +912,14 @@ data Coercion -- The number coercions should match exactly the expectations -- of the CoAxiomRule (i.e., the rule is fully saturated). - | UnivCo { uco_prov :: UnivCoProvenance - , uco_role :: Role - , uco_lty, uco_rty :: Type - , uco_deps :: [Coercion] -- Coercions on which it depends - -- See Note [The importance of tracking free coercion variables]. - } - -- Of kind (lty ~role rty) + | UnivCo -- See Note [UnivCo] + -- Of kind (lty ~role rty) + { uco_prov :: UnivCoProvenance + , uco_role :: Role + , uco_lty, uco_rty :: Type + , uco_deps :: [Coercion] -- Coercions on which it depends + -- See Note [The importance of tracking UnivCo dependencies] + } | SymCo Coercion -- :: e -> e | TransCo Coercion Coercion -- :: e -> e -> e @@ -988,22 +989,6 @@ instance Outputable FunSel where ppr SelArg = text "arg" ppr SelRes = text "res" -instance Binary UnivCoProvenance where - put_ bh PhantomProv = putByte bh 1 - put_ bh ProofIrrelProv = putByte bh 2 - put_ bh (PluginProv a) = do { putByte bh 3 - ; put_ bh a } - - get bh = do - tag <- getByte bh - case tag of - 1 -> return PhantomProv - 2 -> return ProofIrrelProv - 3 -> do a <- get bh - return $ PluginProv a - _ -> panic ("get UnivCoProvenance " ++ show tag) - - instance Binary CoSel where put_ bh (SelTyCon n r) = do { putByte bh 0; put_ bh n; put_ bh r } put_ bh SelForAll = putByte bh 1 @@ -1539,16 +1524,29 @@ in nominal ways. If not, having w be representational is OK. %************************************************************************ %* * - UnivCoProvenance + UnivCo %* * %************************************************************************ +Note [UnivCo] +~~~~~~~~~~~~~ A UnivCo is a coercion whose proof does not directly express its role and kind (indeed for some UnivCos, like PluginProv, there /is/ no proof). -The different kinds of UnivCo are described by UnivCoProvenance. Really -each is entirely separate, but they all share the need to represent their -role and kind, which is done in the UnivCo constructor. +The different kinds of UnivCo are described by UnivCoProvenance. Really each +is entirely separate, but they all share the need to represent these fields: + + UnivCo + { uco_prov :: UnivCoProvenance + , uco_role :: Role + , uco_lty, uco_rty :: Type + , uco_deps :: [Coercion] -- Coercions on which it depends + +Here, + * uco_role, uco_lty, uco_rty express the type of the coercoin + * uco_prov says where it came from + * uco_deps specifies the coercions on which this proof (which is not + explicity given) depends. See -} @@ -1572,17 +1570,124 @@ data UnivCoProvenance -- ^ From a plugin, which asserts that this coercion is sound. -- The string and the variable set are for the use by the plugin. + | BuiltinProv -- The proof comes form GHC's knowledge of arithmetic + -- or strings; e.g. from (co : a+b ~ 0) we can deduce that + -- (a ~ 0) and (b ~ 0), with a BuiltinProv proof. + deriving (Eq, Ord, Data.Data) -- Why Ord? See Note [Ord instance of IfaceType] in GHC.Iface.Type instance Outputable UnivCoProvenance where + ppr BuiltinProv = text "(builtin)" ppr PhantomProv = text "(phantom)" - ppr ProofIrrelProv = text "(proof irrel.)" + ppr ProofIrrelProv = text "(proof irrel)" ppr (PluginProv str) = parens (text "plugin" <+> brackets (text str)) instance NFData UnivCoProvenance where rnf p = p `seq` () +instance Binary UnivCoProvenance where + put_ bh BuiltinProv = putByte bh 1 + put_ bh PhantomProv = putByte bh 2 + put_ bh ProofIrrelProv = putByte bh 3 + put_ bh (PluginProv a) = putByte bh 4 >> put_ bh a + get bh = do + tag <- getByte bh + case tag of + 1 -> return BuiltinProv + 2 -> return PhantomProv + 3 -> return ProofIrrelProv + 4 -> do a <- get bh + return $ PluginProv a + _ -> panic ("get UnivCoProvenance " ++ show tag) + + +{- Note [Phantom coercions] +~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider + data T a = T1 | T2 +Then we have + T s ~R T t +for any old s,t. The witness for this is (TyConAppCo T Rep co), +where (co :: s ~P t) is a phantom coercion built with PhantomProv. +The role of the UnivCo is always Phantom. The Coercion stored is the +(nominal) kind coercion between the types + kind(s) ~N kind (t) + +Note [ProofIrrelProv] +~~~~~~~~~~~~~~~~~~~~~ +A ProofIrrelProv is a coercion between coercions. For example: + + data G a where + MkG :: G Bool + +In core, we get + + G :: * -> * + MkG :: forall (a :: *). (a ~ Bool) -> G a + +Now, consider 'MkG -- that is, MkG used in a type -- and suppose we want +a proof that ('MkG a1 co1) ~ ('MkG a2 co2). This will have to be + + TyConAppCo Nominal MkG [co3, co4] + where + co3 :: co1 ~ co2 + co4 :: a1 ~ a2 + +Note that + co1 :: a1 ~ Bool + co2 :: a2 ~ Bool + +Here, + co3 = UnivCo ProofIrrelProv Nominal (CoercionTy co1) (CoercionTy co2) [co5] + where + co5 :: (a1 ~ Bool) ~ (a2 ~ Bool) + co5 = TyConAppCo Nominal (~#) [<*>, <*>, co4, ] + + +Note [The importance of tracking UnivCo dependencies] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +It is vital that `UnivCo` (a coercion that lacks a proper proof) +tracks the coercions on which it depends. To see why, consider this program: + + type S :: Nat -> Nat + + data T (a::Nat) where + T1 :: T 0 + T2 :: ... + + f :: T a -> S (a+1) -> S 1 + f = /\a (x:T a) (y:a). + case x of + T1 (gco : a ~# 0) -> y |> wco + +For this to typecheck we need `wco :: S (a+1) ~# S 1`, given that `gco : a ~# 0`. +To prove that we need to know that `a+1 = 1` if `a=0`, which a plugin might know. +So it solves `wco` by providing a `UnivCo (PluginProv "my-plugin") (a+1) 1 [gco]`. + + But the `uco_deps` in `PluginProv` must mention `gco`! + +Why? Otherwise we might float the entire expression (y |> wco) out of the +the case alternative for `T1` which brings `gco` into scope. If this +happens then we aren't far from a segmentation fault or much worse. +See #23923 for a real-world example of this happening. + +So it is /crucial/ for the `UnivCo` to mention, in `uco_deps`, the coercion +variables used by the plugin to justify the `UnivCo` that it builds. You +should think of it like `TyConAppCo`: the `UnivCo` proof contstructor is +applied to a list of coercions, just as `TyConAppCo` is + +It's very convenient to record a full coercion, not just a set of free coercion +variables, because during typechecking those coercions might contain coercion +holes `HoleCo`, which get filled in later. +-} + +{- ********************************************************************** +%* * + Coercion holes +%* * +%********************************************************************* -} + -- | A coercion to be filled in by the type-checker. See Note [Coercion holes] data CoercionHole = CoercionHole { ch_co_var :: CoVar @@ -1618,19 +1723,7 @@ instance Outputable CoercionHole where instance Uniquable CoercionHole where getUnique (CoercionHole { ch_co_var = cv }) = getUnique cv -{- Note [Phantom coercions] -~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Consider - data T a = T1 | T2 -Then we have - T s ~R T t -for any old s,t. The witness for this is (TyConAppCo T Rep co), -where (co :: s ~P t) is a phantom coercion built with PhantomProv. -The role of the UnivCo is always Phantom. The Coercion stored is the -(nominal) kind coercion between the types - kind(s) ~N kind (t) - -Note [Coercion holes] +{- Note [Coercion holes] ~~~~~~~~~~~~~~~~~~~~~~~~ During typechecking, constraint solving for type classes works by - Generate an evidence Id, d7 :: Num a @@ -1705,84 +1798,10 @@ constraint from floating] in GHC.Tc.Solver, item (4): Here co2 is a CoercionHole. But we /must/ know that it is free in co1, because that's all that stops it floating outside the implication. - - -Note [ProofIrrelProv] -~~~~~~~~~~~~~~~~~~~~~ -A ProofIrrelProv is a coercion between coercions. For example: - - data G a where - MkG :: G Bool - -In core, we get - - G :: * -> * - MkG :: forall (a :: *). (a ~ Bool) -> G a - -Now, consider 'MkG -- that is, MkG used in a type -- and suppose we want -a proof that ('MkG a1 co1) ~ ('MkG a2 co2). This will have to be - - TyConAppCo Nominal MkG [co3, co4] - where - co3 :: co1 ~ co2 - co4 :: a1 ~ a2 - -Note that - co1 :: a1 ~ Bool - co2 :: a2 ~ Bool - -Here, - co3 = UnivCo (ProofIrrelProv co5) Nominal (CoercionTy co1) (CoercionTy co2) - where - co5 :: (a1 ~ Bool) ~ (a2 ~ Bool) - co5 = TyConAppCo Nominal (~#) [<*>, <*>, co4, ] - - -Note [The importance of tracking free coercion variables] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -It is vital that `UnivCo` (a coercion that lacks a proper proof) -tracks its free coercion variables. To see why, consider this program: - - type S :: Nat -> Nat - - data T (a::Nat) where - T1 :: T 0 - T2 :: ... - - f :: T a -> S (a+1) -> S 1 - f = /\a (x:T a) (y:a). - case x of - T1 (gco : a ~# 0) -> y |> wco - -For this to typecheck we need `wco :: S (a+1) ~# S 1`, given that `gco : a ~# 0`. -To prove that we need to know that `a+1 = 1` if `a=0`, which a plugin might know. -So it solves `wco` by providing a `UnivCo (PluginProv "my-plugin" gcvs) (a+1) 1`. - - But the `gcvs` in `PluginProv` must mention `gco`. - -Why? Otherwise we might float the entire expression (y |> wco) out of the -the case alternative for `T1` which brings `gco` into scope. If this -happens then we aren't far from a segmentation fault or much worse. -See #23923 for a real-world example of this happening. - -So it is /crucial/ for the `PluginProv` to mention, in `gcvs`, the coercion -variables used by the plugin to justify the `UnivCo` that it builds. - -Note that we don't need to track -* the coercion's free *type* variables -* coercion variables free in kinds (we only need the "shallow" free covars) - -This means that we may float past type variables which the original -proof had as free variables. While surprising, this doesn't jeopardise -the validity of the coercion, which only depends upon the scoping -relative to the free coercion variables. - -(The free coercion variables are kept as a DCoVarSet in UnivCo, -since these sets are included in interface files.) - -} + {- ********************************************************************* * * foldType and foldCoercion ===================================== compiler/GHC/Tc/Solver/Dict.hs ===================================== @@ -1396,16 +1396,16 @@ parameters, is that we simply produce new Wanted equalities. So for example class D a b | a -> b where ... Inert: - d1 :g D Int Bool + [G] d1 : D Int Bool WorkItem: - d2 :w D Int alpha + [W] d2 : D Int alpha We generate the extra work item - cv :w alpha ~ Bool + [W] cv : alpha ~ Bool where 'cv' is currently unused. However, this new item can perhaps be spontaneously solved to become given and react with d2, discharging it in favour of a new constraint d2' thus: - d2' :w D Int Bool + [W[ d2' : D Int Bool d2 := d2' |> D Int cv Now d2' can be discharged from d1 @@ -1415,20 +1415,20 @@ using those extra equalities. If that were the case with the same inert set and work item we might discard d2 directly: - cv :w alpha ~ Bool + [W] cv : alpha ~ Bool d2 := d1 |> D Int cv But in general it's a bit painful to figure out the necessary coercion, so we just take the first approach. Here is a better example. Consider: class C a b c | a -> b And: - [Given] d1 : C T Int Char - [Wanted] d2 : C T beta Int + [G] d1 : C T Int Char + [W] d2 : C T beta Int In this case, it's *not even possible* to solve the wanted immediately. So we should simply output the functional dependency and add this guy [but NOT its superclasses] back in the worklist. Even worse: - [Given] d1 : C T Int beta - [Wanted] d2: C T beta Int + [G] d1 : C T Int beta + [W] d2: C T beta Int Then it is solvable, but its very hard to detect this on the spot. It's exactly the same with implicit parameters, except that the ===================================== compiler/GHC/Tc/Solver/Equality.hs ===================================== @@ -115,7 +115,7 @@ solveEquality ev eq_rel ty1 ty2 ; solveIrred irred_ct } ; Right eq_ct -> do { tryInertEqs eq_ct - ; tryFunDeps eq_ct + ; tryFunDeps eq_rel eq_ct ; tryQCsEqCt eq_ct ; simpleStage (updInertEqs eq_ct) ; stopWithStage (eqCtEvidence eq_ct) "Kept inert EqCt" } } } @@ -2973,29 +2973,47 @@ tryFamFamInjectivity ev eq_rel fun_tc1 fun_args1 fun_tc2 fun_args2 mco = return False -------------------- -tryFunDeps :: EqCt -> SolverStage () -tryFunDeps work_item@(EqCt { eq_lhs = lhs, eq_ev = ev }) +tryFunDeps :: EqRel -> EqCt -> SolverStage () +tryFunDeps eq_rel work_item@(EqCt { eq_lhs = lhs, eq_ev = ev }) + | NomEq <- eq_rel + , TyFamLHS tc args <- lhs = Stage $ - case lhs of - TyFamLHS tc args -> do { inerts <- getInertCans - ; imp1 <- improveLocalFunEqs inerts tc args work_item - ; imp2 <- improveTopFunEqs tc args work_item - ; if (imp1 || imp2) - then startAgainWith (mkNonCanonical ev) - else continueWith () } - TyVarLHS {} -> continueWith () + do { inerts <- getInertCans + ; imp1 <- improveLocalFunEqs inerts tc args work_item + ; imp2 <- improveTopFunEqs tc args work_item + ; if (imp1 || imp2) + then startAgainWith (mkNonCanonical ev) + else continueWith () } + | otherwise + = nopStage () -------------------- improveTopFunEqs :: TyCon -> [TcType] -> EqCt -> TcS Bool -- See Note [FunDep and implicit parameter reactions] -improveTopFunEqs fam_tc args (EqCt { eq_ev = ev, eq_rhs = rhs }) +improveTopFunEqs fam_tc args (EqCt { eq_ev = ev, eq_rhs = rhs_ty }) | isGiven ev - = return False -- See Note [No Given/Given fundeps] + = improveGivenTopFunEqs fam_tc args ev rhs_ty + | otherwise + = improveWantedTopFunEqs fam_tc args ev rhs_ty +improveGivenTopFunEqs :: TyCon -> [TcType] -> CtEvidence -> Xi -> TcS Bool +improveGivenTopFunEqs fam_tc args ev rhs_ty + | Just ops <- isBuiltInSynFamTyCon_maybe fam_tc + = do { emitNewGivens (ctEvLoc ev) $ + [ (Nominal, s, t, new_co) + | Pair s t <- sfInteractTop ops args rhs_ty + , let new_co = mkUnivCo BuiltinProv [given_co] Nominal s t ] + ; return False } | otherwise + = return False -- See Note [No Given/Given fundeps] + where + given_co :: Coercion = ctEvCoercion ev + +improveWantedTopFunEqs :: TyCon -> [TcType] -> CtEvidence -> Xi -> TcS Bool +improveWantedTopFunEqs fam_tc args ev rhs_ty = do { fam_envs <- getFamInstEnvs - ; eqns <- improve_top_fun_eqs fam_envs fam_tc args rhs - ; traceTcS "improveTopFunEqs" (vcat [ ppr fam_tc <+> ppr args <+> ppr rhs + ; eqns <- improve_top_fun_eqs fam_envs fam_tc args rhs_ty + ; traceTcS "improveTopFunEqs" (vcat [ ppr fam_tc <+> ppr args <+> ppr rhs_ty , ppr eqns ]) ; unifyFunDeps ev Nominal $ \uenv -> uPairsTcM (bump_depth uenv) (reverse eqns) } @@ -3008,7 +3026,7 @@ improveTopFunEqs fam_tc args (EqCt { eq_ev = ev, eq_rhs = rhs }) -- See #14778 improve_top_fun_eqs :: FamInstEnvs - -> TyCon -> [TcType] -> TcType + -> TyCon -> [TcType] -> Xi -> TcS [TypeEqn] improve_top_fun_eqs fam_envs fam_tc args rhs_ty | Just ops <- isBuiltInSynFamTyCon_maybe fam_tc ===================================== compiler/GHC/Tc/Solver/Monad.hs ===================================== @@ -34,7 +34,7 @@ module GHC.Tc.Solver.Monad ( -- The pipeline StopOrContinue(..), continueWith, stopWith, startAgainWith, SolverStage(Stage, runSolverStage), simpleStage, - stopWithStage, + stopWithStage, nopStage, -- Tracing etc panicTcS, traceTcS, tryEarlyAbortTcS, @@ -284,6 +284,9 @@ instance Monad SolverStage where Stop ev d -> return (Stop ev d) ContinueWith x -> runSolverStage (k x) } +nopStage :: a -> SolverStage a +nopStage res = Stage (continueWith res) + simpleStage :: TcS a -> SolverStage a -- Always does a ContinueWith; no Stop or StartAgain simpleStage thing = Stage (do { res <- thing; continueWith res }) ===================================== compiler/GHC/Tc/Types/Constraint.hs ===================================== @@ -2022,7 +2022,7 @@ ctEvTerm ev = EvExpr (ctEvExpr ev) -- return an empty set. ctEvRewriters :: CtEvidence -> RewriterSet ctEvRewriters (CtWanted { ctev_rewriters = rewriters }) = rewriters -ctEvRewriters _other = emptyRewriterSet +ctEvRewriters (CtGiven {}) = emptyRewriterSet ctEvExpr :: HasDebugCallStack => CtEvidence -> EvExpr ctEvExpr ev@(CtWanted { ctev_dest = HoleDest _ }) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0d1908cefe56a6743e295c42d6e9fa3f41119bac -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0d1908cefe56a6743e295c42d6e9fa3f41119bac You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 12 22:54:39 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 12 Jun 2024 18:54:39 -0400 Subject: [Git][ghc/ghc][wip/T24938] 9 commits: Fix a QuickLook bug Message-ID: <666a272f5f4f2_2b8a4b1f6a71016636b@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24938 at Glasgow Haskell Compiler / GHC Commits: 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - 4fb3d0c0 by Simon Peyton Jones at 2024-06-12T23:48:39+01:00 Fix untouchability test Addresses #24938 more documentation to come - - - - - 22 changed files: - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/60d43697560598e89de20df3981736fdcf6d25df...4fb3d0c0b6dd7344ffb3679f9db3ea63707ce18b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/60d43697560598e89de20df3981736fdcf6d25df...4fb3d0c0b6dd7344ffb3679f9db3ea63707ce18b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 03:07:23 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Jun 2024 23:07:23 -0400 Subject: [Git][ghc/ghc][master] compiler: Make ghc-experimental not wired in Message-ID: <666a626be3ac0_3eeef69d013484971@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 3 changed files: - compiler/GHC/Builtin/Names.hs - compiler/GHC/Unit/Types.hs - libraries/ghc-experimental/ghc-experimental.cabal Changes: ===================================== compiler/GHC/Builtin/Names.hs ===================================== @@ -669,10 +669,6 @@ gHC_INTERNAL_OVER_LABELS = mkGhcInternalModule (fsLit "GHC.Internal.OverloadedLa gHC_INTERNAL_RECORDS :: Module gHC_INTERNAL_RECORDS = mkGhcInternalModule (fsLit "GHC.Internal.Records") -dATA_TUPLE_EXPERIMENTAL, dATA_SUM_EXPERIMENTAL :: Module -dATA_TUPLE_EXPERIMENTAL = mkExperimentalModule (fsLit "Data.Tuple.Experimental") -dATA_SUM_EXPERIMENTAL = mkExperimentalModule (fsLit "Data.Sum.Experimental") - rOOT_MAIN :: Module rOOT_MAIN = mkMainModule (fsLit ":Main") -- Root module for initialisation @@ -714,9 +710,6 @@ mkMainModule m = mkModule mainUnit (mkModuleNameFS m) mkMainModule_ :: ModuleName -> Module mkMainModule_ m = mkModule mainUnit m -mkExperimentalModule :: FastString -> Module -mkExperimentalModule m = mkModule experimentalUnit (mkModuleNameFS m) - {- ************************************************************************ * * ===================================== compiler/GHC/Unit/Types.hs ===================================== @@ -77,7 +77,6 @@ module GHC.Unit.Types , mainUnit , thisGhcUnit , interactiveUnit - , experimentalUnit , isInteractiveModule , wiredInUnitIds @@ -594,11 +593,10 @@ Make sure you change 'GHC.Unit.State.findWiredInUnits' if you add an entry here. -} bignumUnitId, primUnitId, ghcInternalUnitId, baseUnitId, rtsUnitId, - mainUnitId, thisGhcUnitId, interactiveUnitId, - experimentalUnitId :: UnitId + mainUnitId, thisGhcUnitId, interactiveUnitId :: UnitId bignumUnit, primUnit, ghcInternalUnit, baseUnit, rtsUnit, - mainUnit, thisGhcUnit, interactiveUnit, experimentalUnit :: Unit + mainUnit, thisGhcUnit, interactiveUnit :: Unit primUnitId = UnitId (fsLit "ghc-prim") bignumUnitId = UnitId (fsLit "ghc-bignum") @@ -607,7 +605,6 @@ baseUnitId = UnitId (fsLit "base") rtsUnitId = UnitId (fsLit "rts") thisGhcUnitId = UnitId (fsLit cProjectUnitId) -- See Note [GHC's Unit Id] interactiveUnitId = UnitId (fsLit "interactive") -experimentalUnitId = UnitId (fsLit "ghc-experimental") primUnit = RealUnit (Definite primUnitId) bignumUnit = RealUnit (Definite bignumUnitId) @@ -616,7 +613,6 @@ baseUnit = RealUnit (Definite baseUnitId) rtsUnit = RealUnit (Definite rtsUnitId) thisGhcUnit = RealUnit (Definite thisGhcUnitId) interactiveUnit = RealUnit (Definite interactiveUnitId) -experimentalUnit = RealUnit (Definite experimentalUnitId) -- | This is the package Id for the current program. It is the default -- package Id if you don't specify a package name. We don't add this prefix @@ -634,7 +630,6 @@ wiredInUnitIds = , ghcInternalUnitId , baseUnitId , rtsUnitId - , experimentalUnitId ] -- NB: ghc is no longer part of the wired-in units since its unit-id, given -- by hadrian or cabal, is no longer overwritten and now matches both the ===================================== libraries/ghc-experimental/ghc-experimental.cabal ===================================== @@ -35,4 +35,3 @@ library ghc-prim >= 0.11 && < 0.12 hs-source-dirs: src default-language: Haskell2010 - ghc-options: -this-unit-id ghc-experimental View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b3cc5366e84bd3b74a7ac6f80cd0f4d8f65d0d4a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b3cc5366e84bd3b74a7ac6f80cd0f4d8f65d0d4a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 03:08:06 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Jun 2024 23:08:06 -0400 Subject: [Git][ghc/ghc][master] base: Use a more appropriate unicode arrow for the ByteArray diagram Message-ID: <666a62961018d_3eeef6b7962088262@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - 1 changed file: - libraries/base/src/Data/Array/Byte.hs Changes: ===================================== libraries/base/src/Data/Array/Byte.hs ===================================== @@ -48,7 +48,7 @@ import Prelude -- The memory representation of a 'ByteArray' is: -- -- > ╭─────────────┬───╮ ╭────────┬──────┬─────────╮ --- > │ Constructor │ * ┼─➤│ Header │ Size │ Payload │ +-- > │ Constructor │ * ┼─►│ Header │ Size │ Payload │ -- > ╰─────────────┴───╯ ╰────────┴──────┴─────────╯ -- -- And its overhead is the following: View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/700eeab911d2103ddc95ad428d974355e080bb72 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/700eeab911d2103ddc95ad428d974355e080bb72 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 03:08:46 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 12 Jun 2024 23:08:46 -0400 Subject: [Git][ghc/ghc][master] ghcup-metadata: Fix debian version ranges Message-ID: <666a62be6d5f_3eeef6d0b75492834@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 1 changed file: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py Changes: ===================================== .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py ===================================== @@ -217,7 +217,7 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): a64 = { "Linux_Debian": { "< 10": deb9 , "( >= 10 && < 11 )": deb10 , "( >= 11 && < 12 )": deb11 - , ">= 11": deb12 + , ">= 12": deb12 , "unknown_versioning": deb11 } , "Linux_Ubuntu" : { "unknown_versioning": ubuntu2004 , "( >= 16 && < 18 )": deb9 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cca7de25e989af82ffd267fd69d65df7ddda940a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cca7de25e989af82ffd267fd69d65df7ddda940a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 07:25:41 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 13 Jun 2024 03:25:41 -0400 Subject: [Git][ghc/ghc][wip/jacco/ast] ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <666a9ef5eafed_13569eb73018745a7@gitlab.mail> Rodrigo Mesquita pushed to branch wip/jacco/ast at Glasgow Haskell Compiler / GHC Commits: 64cde514 by Jacco Krijnen at 2024-06-13T08:25:33+01:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/64cde5147671f8aa7c63986bd0b1adc1bed091f2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/64cde5147671f8aa7c63986bd0b1adc1bed091f2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 07:46:01 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Thu, 13 Jun 2024 03:46:01 -0400 Subject: [Git][ghc/ghc][wip/fabu/T24026-early-reject-type-failing-rules] 12 commits: Fix a QuickLook bug Message-ID: <666aa3b9dd8c1_13569ef09dd086587@gitlab.mail> Fabricio Nascimento pushed to branch wip/fabu/T24026-early-reject-type-failing-rules at Glasgow Haskell Compiler / GHC Commits: 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - cdbaf1d9 by Fabricio de Sousa Nascimento at 2024-06-13T07:45:56+00:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - 26 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Builtin/Names.hs - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a0f0b87008c1e391a1324a34969603eddb046a43...cdbaf1d9646a3a45afaedea5fd77483b84ddc8d9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/a0f0b87008c1e391a1324a34969603eddb046a43...cdbaf1d9646a3a45afaedea5fd77483b84ddc8d9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 09:57:23 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 13 Jun 2024 05:57:23 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] 6 commits: Add Int64X2 SIMD operations Message-ID: <666ac283c6e4f_13569e1fffeb41382eb@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: c4bb80ee by Jaro Reinders at 2024-06-13T10:53:26+02:00 Add Int64X2 SIMD operations - - - - - cc1e5dd6 by sheaf at 2024-06-13T11:21:57+02:00 SIMD: need LLVM for Aarch64/PPC (for now) - - - - - 1e1cf8db by sheaf at 2024-06-13T11:22:12+02:00 fixup Jaro - - - - - 1c30e783 by sheaf at 2024-06-13T11:22:25+02:00 fixup: shuffle base exports - - - - - 9693e1da by sheaf at 2024-06-13T11:22:45+02:00 improve cgrun083 - - - - - db9a19a6 by sheaf at 2024-06-13T11:56:02+02:00 move SIMD tests - - - - - 30 changed files: - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/StgToCmm/Prim.hs - libraries/base/src/GHC/Exts.hs - testsuite/tests/codeGen/should_run/all.T - − testsuite/tests/codeGen/should_run/cgrun083.stdout - testsuite/tests/codeGen/should_run/Simd009b.hs → testsuite/tests/simd/should_run/Simd009b.hs - testsuite/tests/codeGen/should_run/Simd009c.hs → testsuite/tests/simd/should_run/Simd009c.hs - + testsuite/tests/simd/should_run/all.T - testsuite/tests/codeGen/should_run/simd000.hs → testsuite/tests/simd/should_run/simd000.hs - testsuite/tests/codeGen/should_run/simd000.stdout → testsuite/tests/simd/should_run/simd000.stdout - testsuite/tests/codeGen/should_run/simd001.hs → testsuite/tests/simd/should_run/simd001.hs - testsuite/tests/codeGen/should_run/simd001.stdout → testsuite/tests/simd/should_run/simd001.stdout - testsuite/tests/codeGen/should_run/simd002.hs → testsuite/tests/simd/should_run/simd002.hs - testsuite/tests/codeGen/should_run/simd002.stdout → testsuite/tests/simd/should_run/simd002.stdout - testsuite/tests/codeGen/should_run/simd003.hs → testsuite/tests/simd/should_run/simd003.hs - testsuite/tests/codeGen/should_run/simd003.stdout → testsuite/tests/simd/should_run/simd003.stdout - testsuite/tests/codeGen/should_run/simd004.hs → testsuite/tests/simd/should_run/simd004.hs - testsuite/tests/codeGen/should_run/simd004.stdout → testsuite/tests/simd/should_run/simd004.stdout - testsuite/tests/codeGen/should_run/simd005.hs → testsuite/tests/simd/should_run/simd005.hs - testsuite/tests/codeGen/should_run/simd005.stdout → testsuite/tests/simd/should_run/simd005.stdout - testsuite/tests/codeGen/should_run/simd006.hs → testsuite/tests/simd/should_run/simd006.hs - testsuite/tests/codeGen/should_run/simd006.stdout → testsuite/tests/simd/should_run/simd006.stdout The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fa5e2b59dd27f21470c3ca4053fc986fe6a670e9...db9a19a6e10287e60619751c76710e80aae5687a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/fa5e2b59dd27f21470c3ca4053fc986fe6a670e9...db9a19a6e10287e60619751c76710e80aae5687a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 10:02:17 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Thu, 13 Jun 2024 06:02:17 -0400 Subject: [Git][ghc/ghc][wip/T24938] Wibbles Message-ID: <666ac3a931fa7_1199fe19f4ec322d2@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24938 at Glasgow Haskell Compiler / GHC Commits: 046e255d by Simon Peyton Jones at 2024-06-13T11:02:03+01:00 Wibbles - - - - - 9 changed files: - testsuite/tests/indexed-types/should_fail/T13784.stderr - testsuite/tests/linters/notes.stdout - testsuite/tests/patsyn/should_fail/T11010.stderr - testsuite/tests/typecheck/should_compile/LocalGivenEqs2.hs - testsuite/tests/typecheck/should_compile/LocalGivenEqs2.stderr - testsuite/tests/typecheck/should_compile/T24938a.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T22645.stderr - testsuite/tests/typecheck/should_fail/T24938.stderr Changes: ===================================== testsuite/tests/indexed-types/should_fail/T13784.stderr ===================================== @@ -1,6 +1,10 @@ - T13784.hs:29:28: error: [GHC-25897] - • Couldn't match type ‘as’ with ‘a : Divide a as’ + • Could not deduce ‘as ~ (a : Divide a as)’ + from the context: (a : as) ~ (a1 : as1) + bound by a pattern with constructor: + :* :: forall a (as :: [*]). a -> Product as -> Product (a : as), + in an equation for ‘divide’ + at T13784.hs:29:13-19 Expected: Product (Divide a (a : as)) Actual: Product as1 ‘as’ is a rigid type variable bound by @@ -36,3 +40,4 @@ T13784.hs:33:29: error: [GHC-83865] • Relevant bindings include divide :: Product (a : as) -> (b, Product (Divide b (a : as))) (bound at T13784.hs:33:5) + ===================================== testsuite/tests/linters/notes.stdout ===================================== @@ -1,39 +1,39 @@ ref compiler/GHC/Core/Coercion/Axiom.hs:472:2: Note [RoughMap and rm_empty] ref compiler/GHC/Core/Opt/OccurAnal.hs:1157:7: Note [Loop breaking] -ref compiler/GHC/Core/Opt/SetLevels.hs:1586:30: Note [Top level scope] -ref compiler/GHC/Core/Opt/Simplify/Iteration.hs:2832:13: Note [Case binder next] -ref compiler/GHC/Core/Opt/Simplify/Iteration.hs:4023:8: Note [Lambda-bound unfoldings] -ref compiler/GHC/Core/Opt/Simplify/Utils.hs:1342:37: Note [Gentle mode] +ref compiler/GHC/Core/Opt/SetLevels.hs:1688:30: Note [Top level scope] +ref compiler/GHC/Core/Opt/Simplify/Iteration.hs:2937:13: Note [Case binder next] +ref compiler/GHC/Core/Opt/Simplify/Iteration.hs:4253:8: Note [Lambda-bound unfoldings] +ref compiler/GHC/Core/Opt/Simplify/Utils.hs:1406:37: Note [Gentle mode] ref compiler/GHC/Core/Opt/Specialise.hs:1763:29: Note [Arity decrease] -ref compiler/GHC/Core/TyCo/Rep.hs:1652:31: Note [What prevents a constraint from floating] -ref compiler/GHC/Driver/DynFlags.hs:1251:52: Note [Eta-reduction in -O0] -ref compiler/GHC/Driver/Main.hs:1749:34: Note [simpleTidyPgm - mkBootModDetailsTc] -ref compiler/GHC/Hs/Expr.hs:191:63: Note [Pending Splices] -ref compiler/GHC/Hs/Expr.hs:1727:87: Note [Lifecycle of a splice] -ref compiler/GHC/Hs/Expr.hs:1763:7: Note [Pending Splices] -ref compiler/GHC/Hs/Extension.hs:147:5: Note [Strict argument type constraints] -ref compiler/GHC/Hs/Pat.hs:141:74: Note [Lifecycle of a splice] +ref compiler/GHC/Core/TyCo/Rep.hs:1677:31: Note [What prevents a constraint from floating] +ref compiler/GHC/Driver/DynFlags.hs:1225:52: Note [Eta-reduction in -O0] +ref compiler/GHC/Driver/Main.hs:1751:34: Note [simpleTidyPgm - mkBootModDetailsTc] +ref compiler/GHC/Hs/Expr.hs:192:63: Note [Pending Splices] +ref compiler/GHC/Hs/Expr.hs:1955:87: Note [Lifecycle of a splice] +ref compiler/GHC/Hs/Expr.hs:1991:7: Note [Pending Splices] +ref compiler/GHC/Hs/Extension.hs:144:5: Note [Strict argument type constraints] +ref compiler/GHC/Hs/Pat.hs:152:74: Note [Lifecycle of a splice] ref compiler/GHC/HsToCore/Pmc/Solver.hs:856:20: Note [COMPLETE sets on data families] -ref compiler/GHC/HsToCore/Quote.hs:1487:7: Note [How brackets and nested splices are handled] -ref compiler/GHC/Stg/Unarise.hs:438:32: Note [Renaming during unarisation] -ref compiler/GHC/Tc/Gen/HsType.hs:556:56: Note [Skolem escape prevention] -ref compiler/GHC/Tc/Gen/HsType.hs:2676:7: Note [Matching a kind signature with a declaration] -ref compiler/GHC/Tc/Gen/Pat.hs:174:20: Note [Typing patterns in pattern bindings] -ref compiler/GHC/Tc/Gen/Pat.hs:1163:7: Note [Matching polytyped patterns] -ref compiler/GHC/Tc/Gen/Sig.hs:80:10: Note [Overview of type signatures] +ref compiler/GHC/HsToCore/Quote.hs:1504:7: Note [How brackets and nested splices are handled] +ref compiler/GHC/Stg/Unarise.hs:451:32: Note [Renaming during unarisation] +ref compiler/GHC/Tc/Gen/HsType.hs:561:56: Note [Skolem escape prevention] +ref compiler/GHC/Tc/Gen/HsType.hs:2707:7: Note [Matching a kind signature with a declaration] +ref compiler/GHC/Tc/Gen/Pat.hs:286:20: Note [Typing patterns in pattern bindings] +ref compiler/GHC/Tc/Gen/Pat.hs:1395:7: Note [Matching polytyped patterns] +ref compiler/GHC/Tc/Gen/Sig.hs:77:10: Note [Overview of type signatures] ref compiler/GHC/Tc/Gen/Splice.hs:358:16: Note [How brackets and nested splices are handled] ref compiler/GHC/Tc/Gen/Splice.hs:533:35: Note [PendingRnSplice] -ref compiler/GHC/Tc/Gen/Splice.hs:657:7: Note [How brackets and nested splices are handled] -ref compiler/GHC/Tc/Gen/Splice.hs:891:11: Note [How brackets and nested splices are handled] +ref compiler/GHC/Tc/Gen/Splice.hs:660:7: Note [How brackets and nested splices are handled] +ref compiler/GHC/Tc/Gen/Splice.hs:904:11: Note [How brackets and nested splices are handled] ref compiler/GHC/Tc/Instance/Family.hs:406:35: Note [Constrained family instances] -ref compiler/GHC/Tc/Solver/Rewrite.hs:1010:7: Note [Stability of rewriting] +ref compiler/GHC/Tc/Solver/Rewrite.hs:1014:7: Note [Stability of rewriting] ref compiler/GHC/Tc/TyCl.hs:1316:6: Note [Unification variables need fresh Names] ref compiler/GHC/Tc/Types/Constraint.hs:206:38: Note [NonCanonical Semantics] -ref compiler/GHC/Types/Demand.hs:301:25: Note [Preserving Boxity of results is rarely a win] +ref compiler/GHC/Types/Demand.hs:303:25: Note [Preserving Boxity of results is rarely a win] ref compiler/GHC/Unit/Module/Deps.hs:83:13: Note [Structure of dep_boot_mods] ref compiler/GHC/Utils/Monad.hs:410:34: Note [multiShotIO] -ref compiler/Language/Haskell/Syntax/Binds.hs:200:31: Note [fun_id in Match] -ref configure.ac:203:10: Note [Linking ghc-bin against threaded stage0 RTS] +ref compiler/Language/Haskell/Syntax/Binds.hs:220:31: Note [fun_id in Match] +ref configure.ac:191:10: Note [Linking ghc-bin against threaded stage0 RTS] ref docs/core-spec/core-spec.mng:177:6: Note [TyBinders] ref hadrian/src/Expression.hs:145:30: Note [Linking ghc-bin against threaded stage0 RTS] ref linters/lint-notes/Notes.hs:32:29: Note [" <> T.unpack x <> "] @@ -43,26 +43,24 @@ ref testsuite/tests/perf/should_run/all.T:8:6: Note [Solving from instanc ref testsuite/tests/polykinds/CuskFam.hs:16:11: Note [Unifying implicit CUSK variables] ref testsuite/tests/simplCore/should_compile/T5776.hs:16:7: Note [Simplifying RULE lhs constraints] ref testsuite/tests/simplCore/should_compile/simpl018.hs:3:7: Note [Float coercions] -ref testsuite/tests/typecheck/should_compile/LocalGivenEqs.hs:7:7: Note [When does an implication have given equalities?] -ref testsuite/tests/typecheck/should_compile/LocalGivenEqs2.hs:4:6: Note [When does an implication have given equalities?] ref testsuite/tests/typecheck/should_compile/T9117.hs:3:12: Note [Order of Coercible Instances] ref testsuite/tests/typecheck/should_compile/tc200.hs:5:7: Note [Multiple instantiation] ref testsuite/tests/typecheck/should_compile/tc228.hs:9:7: Note [Inference and implication constraints] ref testsuite/tests/typecheck/should_compile/tc231.hs:12:16: Note [Important subtlety in oclose] ref testsuite/tests/typecheck/should_fail/UnliftedNewtypesMultiFieldGadt.hs:11:28: Note [Kind-checking the field type] ref testsuite/tests/typecheck/should_fail/tcfail093.hs:13:7: Note [Important subtlety in oclose] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Eta reduction for data family axioms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:: Note [Exporting built-in items] -ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:: Note [Exporting built-in items] -ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:: Note [Exporting built-in items] -ref utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs:: Note [The DocModule story] -ref utils/haddock/haddock-api/src/Haddock/Types.hs:: Note [Pass sensitive types] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1068:13: Note [Eta reduction for data family axioms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1085:0: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1101:7: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1108:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1117:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1131:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1145:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1147:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1156:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:117:11: Note [Exporting built-in items] +ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:182:9: Note [Exporting built-in items] +ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:252:7: Note [Exporting built-in items] +ref utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs:118:3: Note [The DocModule story] +ref utils/haddock/haddock-api/src/Haddock/Types.hs:17:3: Note [Pass sensitive types] ===================================== testsuite/tests/patsyn/should_fail/T11010.stderr ===================================== @@ -1,6 +1,8 @@ - T11010.hs:9:34: error: [GHC-25897] - • Couldn't match type ‘a1’ with ‘Int’ + • Could not deduce ‘a1 ~ Int’ + from the context: a ~ Int + bound by the signature for pattern synonym ‘IntFun’ + at T11010.hs:9:1-36 Expected: a -> b Actual: a1 -> b ‘a1’ is a rigid type variable bound by @@ -15,3 +17,4 @@ T11010.hs:9:34: error: [GHC-25897] | 9 | pattern IntFun str f x = Fun str f x | ^ + ===================================== testsuite/tests/typecheck/should_compile/LocalGivenEqs2.hs ===================================== @@ -1,9 +1,7 @@ {-# LANGUAGE TypeFamilies, GADTSyntax, ExistentialQuantification #-} --- This is a simple case that exercises the LocalGivenEqs bullet --- of Note [Tracking Given equalities] in GHC.Tc.Solver.InertSet --- If a future change rejects this, that's not the end of the world, but it's nice --- to be able to infer `f`. +-- This one should be rejected. +-- See Note [Tracking Given equalities] in GHC.Tc.Solver.InertSet module LocalGivenEqs2 where ===================================== testsuite/tests/typecheck/should_compile/LocalGivenEqs2.stderr ===================================== @@ -1 +1,16 @@ - \ No newline at end of file +LocalGivenEqs2.hs:14:15: error: [GHC-25897] + • Could not deduce ‘p ~ Bool’ + from the context: F a ~ G b + bound by a pattern with constructor: + MkT :: forall a b. (F a ~ G b) => a -> b -> T, + in an equation for ‘f’ + at LocalGivenEqs2.hs:14:4-10 + ‘p’ is a rigid type variable bound by + the inferred type of f :: T -> p + at LocalGivenEqs2.hs:14:1-18 + • In the expression: True + In an equation for ‘f’: f (MkT _ _) = True + • Relevant bindings include + f :: T -> p (bound at LocalGivenEqs2.hs:14:1) + Suggested fix: Consider giving ‘f’ a type signature + ===================================== testsuite/tests/typecheck/should_compile/T24938a.hs ===================================== @@ -1,6 +1,6 @@ {-# LANGUAGE TypeFamilies, GADTs #-} -module Foo where +module T24938a where type family F a ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -918,5 +918,5 @@ test('T23764', normal, compile, ['']) test('T23739a', normal, compile, ['']) test('T24810', normal, compile, ['']) test('T24887', normal, compile, ['']) -test('T2938a', normal, compile, ['']) +test('T24938a', normal, compile, ['']) ===================================== testsuite/tests/typecheck/should_fail/T22645.stderr ===================================== @@ -1,6 +1,9 @@ - T22645.hs:9:5: error: [GHC-25897] - • Couldn't match type ‘a’ with ‘b’ arising from a use of ‘coerce’ + • Could not deduce ‘a ~ b’ arising from a use of ‘coerce’ + from the context: Coercible a b + bound by the type signature for: + p :: forall a b. Coercible a b => T Maybe a -> T Maybe b + at T22645.hs:8:1-44 ‘a’ is a rigid type variable bound by the type signature for: p :: forall a b. Coercible a b => T Maybe a -> T Maybe b @@ -13,3 +16,4 @@ T22645.hs:9:5: error: [GHC-25897] In an equation for ‘p’: p = coerce • Relevant bindings include p :: T Maybe a -> T Maybe b (bound at T22645.hs:9:1) + ===================================== testsuite/tests/typecheck/should_fail/T24938.stderr ===================================== @@ -1 +1,19 @@ - \ No newline at end of file +T24938.hs:30:16: error: [GHC-25897] + • Could not deduce ‘p ~ GHC.Types.Bool’ + from the context: Nt String ~ Mt Int + bound by a pattern with constructor: + Refl :: forall {k} (a :: k). Eq a a, + in a case alternative + at T24938.hs:28:5-8 + ‘p’ is a rigid type variable bound by + the inferred type of foo :: p -> Eq (Mt Int) (Nt String) -> t + at T24938.hs:(26,1)-(33,17) + • In the expression: p + In the expression: if p then useIntAndRaise x else use x + In an equation for ‘bar’: + bar x = if p then useIntAndRaise x else use x + • Relevant bindings include + p :: p (bound at T24938.hs:26:5) + foo :: p -> Eq (Mt Int) (Nt String) -> t (bound at T24938.hs:26:1) + Suggested fix: Consider giving ‘foo’ a type signature + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/046e255d023c2954d475d14d19c784a9a76341a7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/046e255d023c2954d475d14d19c784a9a76341a7 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 13:45:25 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Thu, 13 Jun 2024 09:45:25 -0400 Subject: [Git][ghc/ghc][wip/T14030] 2 commits: Derive previously hand-written `Lift` instances (#14030) Message-ID: <666af7f59b35f_1199fe1eeef70101362@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: 25d80b82 by Sebastian Graf at 2024-06-13T10:38:50+02:00 Derive previously hand-written `Lift` instances (#14030) This is possible now that #22229 is fixed. - - - - - 0487e457 by Sebastian Graf at 2024-06-13T15:44:47+02:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. - - - - - 6 changed files: - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - testsuite/tests/ghci/scripts/T21110.stderr - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/th/TH_Lift.hs Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs ===================================== @@ -12,6 +12,9 @@ {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UnboxedSums #-} {-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE DeriveLift #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE FlexibleInstances #-} {-# OPTIONS_GHC -fno-warn-inline-rule-shadowing #-} -- | This module gives the definition of the 'Lift' class. @@ -39,7 +42,7 @@ module GHC.Internal.TH.Lift where import GHC.Internal.TH.Syntax -import GHC.Internal.TH.Lib () -- See wrinkle (W4) of Note [Tracking dependencies on primitives] +import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives] import GHC.Internal.Lexeme ( startsVarSym, startsVarId ) import GHC.Internal.Data.Either @@ -52,7 +55,7 @@ import GHC.Internal.Integer import GHC.Internal.Real import GHC.Internal.Word import GHC.Internal.Int -import GHC.Internal.Data.Data +import GHC.Internal.Data.Data hiding (Fixity) import GHC.Internal.Natural -- | A 'Lift' instance can have any of its values turned into a Template @@ -95,6 +98,11 @@ class Lift (t :: TYPE r) where -- @since template-haskell-2.16.0.0 liftTyped :: Quote m => t -> Code m t +----------------------------------------------------- +-- +-- Manual instances for lifting to Literals +-- +----------------------------------------------------- -- If you add any instances here, consider updating test th/TH_Lift instance Lift Integer where @@ -186,12 +194,6 @@ instance Lift Char# where liftTyped x = unsafeCodeCoerce (lift x) lift x = return (LitE (CharPrimL (C# x))) -instance Lift Bool where - liftTyped x = unsafeCodeCoerce (lift x) - - lift True = return (ConE trueName) - lift False = return (ConE falseName) - -- | Produces an 'Addr#' literal from the NUL-terminated C-string starting at -- the given memory address. -- @@ -201,18 +203,6 @@ instance Lift Addr# where lift x = return (LitE (StringPrimL (map (fromIntegral . ord) (unpackCString# x)))) -instance Lift a => Lift (Maybe a) where - liftTyped x = unsafeCodeCoerce (lift x) - - lift Nothing = return (ConE nothingName) - lift (Just x) = liftM (ConE justName `AppE`) (lift x) - -instance (Lift a, Lift b) => Lift (Either a b) where - liftTyped x = unsafeCodeCoerce (lift x) - - lift (Left x) = liftM (ConE leftName `AppE`) (lift x) - lift (Right y) = liftM (ConE rightName `AppE`) (lift y) - instance Lift a => Lift [a] where liftTyped x = unsafeCodeCoerce (lift x) lift xs = do { xs' <- mapM lift xs; return (ListE xs') } @@ -221,193 +211,85 @@ liftString :: Quote m => String -> m Exp -- Used in GHC.Tc.Gen.Expr to short-circuit the lifting for strings liftString s = return (LitE (StringL s)) --- | @since template-haskell-2.15.0.0 -instance Lift a => Lift (NonEmpty a) where - liftTyped x = unsafeCodeCoerce (lift x) +-- TH has a special form for literal strings, +-- which we should take advantage of. +-- NB: the lhs of the rule has no args, so that +-- the rule will apply to a 'lift' all on its own +-- which happens to be the way the type checker +-- creates it. +-- SG: This RULE is tested by T3600. +-- In #24983 I advocated defining an overlapping instance +-- to replace this RULE. However, doing so breaks drv023 +-- which would need to declare an instance derived from `Lift @[a]` as +-- incoherent. So this RULE it is. +{-# RULES "TH:liftString" lift = liftString #-} - lift (x :| xs) = do - x' <- lift x - xs' <- lift xs - return (InfixE (Just x') (ConE nonemptyName) (Just xs')) +----------------------------------------------------- +-- +-- Derived instances for base data types +-- +----------------------------------------------------- +deriving instance Lift Bool +deriving instance Lift a => Lift (Maybe a) +deriving instance (Lift a, Lift b) => Lift (Either a b) -- | @since template-haskell-2.15.0.0 -instance Lift Void where - liftTyped = liftCode . absurd - lift = pure . absurd - -instance Lift () where - liftTyped x = unsafeCodeCoerce (lift x) - lift () = return (ConE (tupleDataName 0)) - -instance (Lift a, Lift b) => Lift (a, b) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b) - = liftM TupE $ sequence $ map (fmap Just) [lift a, lift b] - -instance (Lift a, Lift b, Lift c) => Lift (a, b, c) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c) - = liftM TupE $ sequence $ map (fmap Just) [lift a, lift b, lift c] - -instance (Lift a, Lift b, Lift c, Lift d) => Lift (a, b, c, d) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d) - = liftM TupE $ sequence $ map (fmap Just) [lift a, lift b, lift c, lift d] - -instance (Lift a, Lift b, Lift c, Lift d, Lift e) - => Lift (a, b, c, d, e) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d, e) - = liftM TupE $ sequence $ map (fmap Just) [ lift a, lift b - , lift c, lift d, lift e ] - -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) - => Lift (a, b, c, d, e, f) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d, e, f) - = liftM TupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f ] - -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) - => Lift (a, b, c, d, e, f, g) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d, e, f, g) - = liftM TupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f, lift g ] - +deriving instance Lift a => Lift (NonEmpty a) +-- | @since template-haskell-2.15.0.0 +deriving instance Lift Void +deriving instance Lift () +deriving instance (Lift a, Lift b) + => Lift (a, b) +deriving instance (Lift a, Lift b, Lift c) + => Lift (a, b, c) +deriving instance (Lift a, Lift b, Lift c, Lift d) + => Lift (a, b, c, d) +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e) + => Lift (a, b, c, d, e) +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) + => Lift (a, b, c, d, e, f) +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) + => Lift (a, b, c, d, e, f, g) -- | @since template-haskell-2.16.0.0 -instance Lift (# #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# #) = return (ConE (unboxedTupleTypeName 0)) - +deriving instance Lift (# #) -- | @since template-haskell-2.16.0.0 -instance (Lift a) => Lift (# a #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [lift a] - +deriving instance (Lift a) + => Lift (# a #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b) => Lift (# a, b #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [lift a, lift b] - +deriving instance (Lift a, Lift b) + => Lift (# a, b #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c) - => Lift (# a, b, c #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [lift a, lift b, lift c] - +deriving instance (Lift a, Lift b, Lift c) + => Lift (# a, b, c #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d) - => Lift (# a, b, c, d #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b - , lift c, lift d ] - +deriving instance (Lift a, Lift b, Lift c, Lift d) + => Lift (# a, b, c, d #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e) - => Lift (# a, b, c, d, e #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d, e #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b - , lift c, lift d, lift e ] - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e) + => Lift (# a, b, c, d, e #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) - => Lift (# a, b, c, d, e, f #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d, e, f #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f ] - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) + => Lift (# a, b, c, d, e, f #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) - => Lift (# a, b, c, d, e, f, g #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d, e, f, g #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f - , lift g ] - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) + => Lift (# a, b, c, d, e, f, g #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b) => Lift (# a | b #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 2 - (# | y #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 2 - +deriving instance (Lift a, Lift b) => Lift (# a | b #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c) - => Lift (# a | b | c #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 3 - (# | y | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 3 - (# | | y #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 3 - +deriving instance (Lift a, Lift b, Lift c) + => Lift (# a | b | c #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d) - => Lift (# a | b | c | d #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 4 - (# | y | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 4 - (# | | y | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 4 - (# | | | y #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 4 - +deriving instance (Lift a, Lift b, Lift c, Lift d) + => Lift (# a | b | c | d #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e) - => Lift (# a | b | c | d | e #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 5 - (# | y | | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 5 - (# | | y | | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 5 - (# | | | y | #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 5 - (# | | | | y #) -> UnboxedSumE <$> lift y <*> pure 5 <*> pure 5 - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e) + => Lift (# a | b | c | d | e #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) - => Lift (# a | b | c | d | e | f #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 6 - (# | y | | | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 6 - (# | | y | | | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 6 - (# | | | y | | #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 6 - (# | | | | y | #) -> UnboxedSumE <$> lift y <*> pure 5 <*> pure 6 - (# | | | | | y #) -> UnboxedSumE <$> lift y <*> pure 6 <*> pure 6 - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) + => Lift (# a | b | c | d | e | f #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) - => Lift (# a | b | c | d | e | f | g #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 7 - (# | y | | | | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 7 - (# | | y | | | | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 7 - (# | | | y | | | #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 7 - (# | | | | y | | #) -> UnboxedSumE <$> lift y <*> pure 5 <*> pure 7 - (# | | | | | y | #) -> UnboxedSumE <$> lift y <*> pure 6 <*> pure 7 - (# | | | | | | y #) -> UnboxedSumE <$> lift y <*> pure 7 <*> pure 7 - --- TH has a special form for literal strings, --- which we should take advantage of. --- NB: the lhs of the rule has no args, so that --- the rule will apply to a 'lift' all on its own --- which happens to be the way the type checker --- creates it. -{-# RULES "TH:liftString" lift = \s -> return (LitE (StringL s)) #-} - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) + => Lift (# a | b | c | d | e | f | g #) trueName, falseName :: Name trueName = 'True @@ -424,6 +306,135 @@ rightName = 'Right nonemptyName :: Name nonemptyName = '(:|) +----------------------------------------------------- +-- +-- Lifting the TH AST +-- +----------------------------------------------------- + +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Loc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DocLoc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ModName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift GHC.Internal.TH.Syntax.Module +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameSpace +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NamespaceSpecifier +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PkgName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameFlavour +-- | @since template-haskell-2.22.1.0 +deriving instance Lift OccName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Name +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameIs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Specificity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift BndrVis +-- | @since template-haskell-2.22.1.0 +deriving instance Lift a => Lift (TyVarBndr a) +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TyLit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Type +-- | @since template-haskell-2.22.1.0 +instance Lift Bytes where + lift = Lib.litE . BytesPrimL + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Lit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pat +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Clause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivClause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivStrategy +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Overlap +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FunDep +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Safety +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Callconv +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Foreign +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ForeignSrcLang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FixityDirection +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Fixity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Inline +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleMatch +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Phases +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleBndr +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnTarget +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pragma +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceUnpackedness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DecidedStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Bang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Con +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TySynEqn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FamilyResultSig +-- | @since template-haskell-2.22.1.0 +deriving instance Lift InjectivityAnn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TypeFamilyHead +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Role +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynArgs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynDir +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Dec +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Range +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Exp +-- | @since template-haskell-2.22.1.0 +instance Lift (TExp a) where + lift (TExp e) = [| TExp $(lift e) |] + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Match +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Guard +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Stmt +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Body +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Info +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnLookup +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Extension + ----------------------------------------------------- -- -- Generic Lift implementations ===================================== libraries/template-haskell/changelog.md ===================================== @@ -1,5 +1,9 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) +## 2.22.1.0 + + * `Lift` instances were added for the `template-haskell` AST. + ## 2.22.0.0 * The kind of `Code` was changed from `forall r. (Type -> Type) -> TYPE r -> Type` ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -3,7 +3,7 @@ -- template-haskell.cabal. name: template-haskell -version: 2.22.0.0 +version: 2.22.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE ===================================== testsuite/tests/ghci/scripts/T21110.stderr ===================================== @@ -1,5 +1,5 @@ - : warning: [GHC-42258] [-Wunused-packages] The following packages were specified via -package or -package-id flags, but were not needed for compilation: - - template-haskell-2.22.0.0 (exposed by flag -package template-haskell) + - template-haskell-2.22.1.0 (exposed by flag -package template-haskell) + ===================================== testsuite/tests/interface-stability/template-haskell-exports.stdout ===================================== @@ -2420,28 +2420,88 @@ instance GHC.Internal.Show.Show GHC.Internal.LanguageExtensions.Extension -- Def instance GHC.Internal.Show.Show GHC.Internal.TH.Ppr.ForallVisFlag -- Defined in ‘GHC.Internal.TH.Ppr’ instance [safe] GHC.Internal.Show.Show GHC.Internal.TH.PprLib.Doc -- Defined in ‘GHC.Internal.TH.PprLib’ instance GHC.Internal.Show.Show GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.ForeignSrcLang’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnLookup -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnTarget -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.BndrVis -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Body -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Bool -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bytes -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Callconv -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Char -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Clause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Con -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Dec -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DecidedStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivClause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivStrategy -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DocLoc -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Double -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (GHC.Internal.Data.Either.Either a b) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Exp -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.LanguageExtensions.Extension -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FamilyResultSig -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Fixity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FixityDirection -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Float -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Foreign -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FunDep -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Guard -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Info -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.InjectivityAnn -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Inline -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Int -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int16 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int32 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int64 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int8 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Integer.Integer -- Defined in ‘GHC.Internal.TH.Lift’ -instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift [a] -- Defined in ‘GHC.Internal.TH.Lift’ +instance [overlappable] forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift [a] -- Defined in ‘GHC.Internal.TH.Lift’ +instance [overlapping] GHC.Internal.TH.Lift.Lift [GHC.Types.Char] -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Lit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Loc -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Match -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Maybe.Maybe a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.ModName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Module -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Name -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameFlavour -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameIs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameSpace -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NamespaceSpecifier -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Natural.Natural -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.OccName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Overlap -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pat -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynArgs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynDir -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Phases -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PkgName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pragma -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Range -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.Real.Integral a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Real.Ratio a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Role -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleBndr -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleMatch -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Safety -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceUnpackedness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Specificity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Stmt -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TExp a) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (a, b) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c) => GHC.Internal.TH.Lift.Lift (a, b, c) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d) => GHC.Internal.TH.Lift.Lift (a, b, c, d) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f g. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f, GHC.Internal.TH.Lift.Lift g) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f, g) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TyLit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TySynEqn -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TyVarBndr a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Type -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TypeFamilyHead -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift () -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Word -- Defined in ‘GHC.Internal.TH.Lift’ ===================================== testsuite/tests/th/TH_Lift.hs ===================================== @@ -80,3 +80,8 @@ o = $( (\x -> [| x |]) (True, 'x', 4 :: Int) ) p :: NonEmpty Char p = $( (\x -> [| x |]) ('a' :| "bcde") ) +exp :: Exp +exp = $( [| 3 + 4 |] >>= lift ) + +texp :: TExp Int +texp = $$( examineCode [|| 3 + 4 ||] `bindCode` liftTyped ) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4ee6eb870e6fdd801edae627c66da1b57f32a8b7...0487e4577552c7f47e8bbecb328d38260e69a072 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4ee6eb870e6fdd801edae627c66da1b57f32a8b7...0487e4577552c7f47e8bbecb328d38260e69a072 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 14:00:58 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Thu, 13 Jun 2024 10:00:58 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/fabu/T24452-confusing-error Message-ID: <666afb9a5344c_1199fe2168b9810424d@gitlab.mail> Fabricio Nascimento pushed new branch wip/fabu/T24452-confusing-error at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/fabu/T24452-confusing-error You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 14:34:25 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Thu, 13 Jun 2024 10:34:25 -0400 Subject: [Git][ghc/ghc][wip/T14030] 2 commits: Derive previously hand-written `Lift` instances (#14030) Message-ID: <666b037130eae_1199fe257ce5011052e@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: 02ad5a85 by Sebastian Graf at 2024-06-13T16:34:11+02:00 Derive previously hand-written `Lift` instances (#14030) This is possible now that #22229 is fixed. - - - - - 79b15a43 by Sebastian Graf at 2024-06-13T16:34:11+02:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. - - - - - 6 changed files: - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - testsuite/tests/ghci/scripts/T21110.stderr - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/th/TH_Lift.hs Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs ===================================== @@ -12,6 +12,9 @@ {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UnboxedSums #-} {-# LANGUAGE UnboxedTuples #-} +{-# LANGUAGE DeriveLift #-} +{-# LANGUAGE StandaloneDeriving #-} +{-# LANGUAGE FlexibleInstances #-} {-# OPTIONS_GHC -fno-warn-inline-rule-shadowing #-} -- | This module gives the definition of the 'Lift' class. @@ -39,7 +42,7 @@ module GHC.Internal.TH.Lift where import GHC.Internal.TH.Syntax -import GHC.Internal.TH.Lib () -- See wrinkle (W4) of Note [Tracking dependencies on primitives] +import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives] import GHC.Internal.Lexeme ( startsVarSym, startsVarId ) import GHC.Internal.Data.Either @@ -47,12 +50,11 @@ import GHC.Internal.Type.Reflection import GHC.Internal.Data.Bool import GHC.Internal.Base hiding (Type, Module, inline) import GHC.Internal.Data.Foldable -import GHC.Internal.Data.Functor import GHC.Internal.Integer import GHC.Internal.Real import GHC.Internal.Word import GHC.Internal.Int -import GHC.Internal.Data.Data +import GHC.Internal.Data.Data hiding (Fixity) import GHC.Internal.Natural -- | A 'Lift' instance can have any of its values turned into a Template @@ -95,6 +97,11 @@ class Lift (t :: TYPE r) where -- @since template-haskell-2.16.0.0 liftTyped :: Quote m => t -> Code m t +----------------------------------------------------- +-- +-- Manual instances for lifting to Literals +-- +----------------------------------------------------- -- If you add any instances here, consider updating test th/TH_Lift instance Lift Integer where @@ -186,12 +193,6 @@ instance Lift Char# where liftTyped x = unsafeCodeCoerce (lift x) lift x = return (LitE (CharPrimL (C# x))) -instance Lift Bool where - liftTyped x = unsafeCodeCoerce (lift x) - - lift True = return (ConE trueName) - lift False = return (ConE falseName) - -- | Produces an 'Addr#' literal from the NUL-terminated C-string starting at -- the given memory address. -- @@ -201,18 +202,6 @@ instance Lift Addr# where lift x = return (LitE (StringPrimL (map (fromIntegral . ord) (unpackCString# x)))) -instance Lift a => Lift (Maybe a) where - liftTyped x = unsafeCodeCoerce (lift x) - - lift Nothing = return (ConE nothingName) - lift (Just x) = liftM (ConE justName `AppE`) (lift x) - -instance (Lift a, Lift b) => Lift (Either a b) where - liftTyped x = unsafeCodeCoerce (lift x) - - lift (Left x) = liftM (ConE leftName `AppE`) (lift x) - lift (Right y) = liftM (ConE rightName `AppE`) (lift y) - instance Lift a => Lift [a] where liftTyped x = unsafeCodeCoerce (lift x) lift xs = do { xs' <- mapM lift xs; return (ListE xs') } @@ -221,193 +210,85 @@ liftString :: Quote m => String -> m Exp -- Used in GHC.Tc.Gen.Expr to short-circuit the lifting for strings liftString s = return (LitE (StringL s)) --- | @since template-haskell-2.15.0.0 -instance Lift a => Lift (NonEmpty a) where - liftTyped x = unsafeCodeCoerce (lift x) +-- TH has a special form for literal strings, +-- which we should take advantage of. +-- NB: the lhs of the rule has no args, so that +-- the rule will apply to a 'lift' all on its own +-- which happens to be the way the type checker +-- creates it. +-- SG: This RULE is tested by T3600. +-- In #24983 I advocated defining an overlapping instance +-- to replace this RULE. However, doing so breaks drv023 +-- which would need to declare an instance derived from `Lift @[a]` as +-- incoherent. So this RULE it is. +{-# RULES "TH:liftString" lift = liftString #-} - lift (x :| xs) = do - x' <- lift x - xs' <- lift xs - return (InfixE (Just x') (ConE nonemptyName) (Just xs')) +----------------------------------------------------- +-- +-- Derived instances for base data types +-- +----------------------------------------------------- +deriving instance Lift Bool +deriving instance Lift a => Lift (Maybe a) +deriving instance (Lift a, Lift b) => Lift (Either a b) -- | @since template-haskell-2.15.0.0 -instance Lift Void where - liftTyped = liftCode . absurd - lift = pure . absurd - -instance Lift () where - liftTyped x = unsafeCodeCoerce (lift x) - lift () = return (ConE (tupleDataName 0)) - -instance (Lift a, Lift b) => Lift (a, b) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b) - = liftM TupE $ sequence $ map (fmap Just) [lift a, lift b] - -instance (Lift a, Lift b, Lift c) => Lift (a, b, c) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c) - = liftM TupE $ sequence $ map (fmap Just) [lift a, lift b, lift c] - -instance (Lift a, Lift b, Lift c, Lift d) => Lift (a, b, c, d) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d) - = liftM TupE $ sequence $ map (fmap Just) [lift a, lift b, lift c, lift d] - -instance (Lift a, Lift b, Lift c, Lift d, Lift e) - => Lift (a, b, c, d, e) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d, e) - = liftM TupE $ sequence $ map (fmap Just) [ lift a, lift b - , lift c, lift d, lift e ] - -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) - => Lift (a, b, c, d, e, f) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d, e, f) - = liftM TupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f ] - -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) - => Lift (a, b, c, d, e, f, g) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (a, b, c, d, e, f, g) - = liftM TupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f, lift g ] - +deriving instance Lift a => Lift (NonEmpty a) +-- | @since template-haskell-2.15.0.0 +deriving instance Lift Void +deriving instance Lift () +deriving instance (Lift a, Lift b) + => Lift (a, b) +deriving instance (Lift a, Lift b, Lift c) + => Lift (a, b, c) +deriving instance (Lift a, Lift b, Lift c, Lift d) + => Lift (a, b, c, d) +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e) + => Lift (a, b, c, d, e) +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) + => Lift (a, b, c, d, e, f) +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) + => Lift (a, b, c, d, e, f, g) -- | @since template-haskell-2.16.0.0 -instance Lift (# #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# #) = return (ConE (unboxedTupleTypeName 0)) - +deriving instance Lift (# #) -- | @since template-haskell-2.16.0.0 -instance (Lift a) => Lift (# a #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [lift a] - +deriving instance (Lift a) + => Lift (# a #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b) => Lift (# a, b #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [lift a, lift b] - +deriving instance (Lift a, Lift b) + => Lift (# a, b #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c) - => Lift (# a, b, c #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [lift a, lift b, lift c] - +deriving instance (Lift a, Lift b, Lift c) + => Lift (# a, b, c #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d) - => Lift (# a, b, c, d #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b - , lift c, lift d ] - +deriving instance (Lift a, Lift b, Lift c, Lift d) + => Lift (# a, b, c, d #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e) - => Lift (# a, b, c, d, e #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d, e #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b - , lift c, lift d, lift e ] - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e) + => Lift (# a, b, c, d, e #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) - => Lift (# a, b, c, d, e, f #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d, e, f #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f ] - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) + => Lift (# a, b, c, d, e, f #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) - => Lift (# a, b, c, d, e, f, g #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift (# a, b, c, d, e, f, g #) - = liftM UnboxedTupE $ sequence $ map (fmap Just) [ lift a, lift b, lift c - , lift d, lift e, lift f - , lift g ] - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) + => Lift (# a, b, c, d, e, f, g #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b) => Lift (# a | b #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 2 - (# | y #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 2 - +deriving instance (Lift a, Lift b) => Lift (# a | b #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c) - => Lift (# a | b | c #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 3 - (# | y | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 3 - (# | | y #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 3 - +deriving instance (Lift a, Lift b, Lift c) + => Lift (# a | b | c #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d) - => Lift (# a | b | c | d #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 4 - (# | y | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 4 - (# | | y | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 4 - (# | | | y #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 4 - +deriving instance (Lift a, Lift b, Lift c, Lift d) + => Lift (# a | b | c | d #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e) - => Lift (# a | b | c | d | e #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 5 - (# | y | | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 5 - (# | | y | | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 5 - (# | | | y | #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 5 - (# | | | | y #) -> UnboxedSumE <$> lift y <*> pure 5 <*> pure 5 - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e) + => Lift (# a | b | c | d | e #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) - => Lift (# a | b | c | d | e | f #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 6 - (# | y | | | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 6 - (# | | y | | | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 6 - (# | | | y | | #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 6 - (# | | | | y | #) -> UnboxedSumE <$> lift y <*> pure 5 <*> pure 6 - (# | | | | | y #) -> UnboxedSumE <$> lift y <*> pure 6 <*> pure 6 - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) + => Lift (# a | b | c | d | e | f #) -- | @since template-haskell-2.16.0.0 -instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) - => Lift (# a | b | c | d | e | f | g #) where - liftTyped x = unsafeCodeCoerce (lift x) - lift x - = case x of - (# y | | | | | | #) -> UnboxedSumE <$> lift y <*> pure 1 <*> pure 7 - (# | y | | | | | #) -> UnboxedSumE <$> lift y <*> pure 2 <*> pure 7 - (# | | y | | | | #) -> UnboxedSumE <$> lift y <*> pure 3 <*> pure 7 - (# | | | y | | | #) -> UnboxedSumE <$> lift y <*> pure 4 <*> pure 7 - (# | | | | y | | #) -> UnboxedSumE <$> lift y <*> pure 5 <*> pure 7 - (# | | | | | y | #) -> UnboxedSumE <$> lift y <*> pure 6 <*> pure 7 - (# | | | | | | y #) -> UnboxedSumE <$> lift y <*> pure 7 <*> pure 7 - --- TH has a special form for literal strings, --- which we should take advantage of. --- NB: the lhs of the rule has no args, so that --- the rule will apply to a 'lift' all on its own --- which happens to be the way the type checker --- creates it. -{-# RULES "TH:liftString" lift = \s -> return (LitE (StringL s)) #-} - +deriving instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) + => Lift (# a | b | c | d | e | f | g #) trueName, falseName :: Name trueName = 'True @@ -424,6 +305,135 @@ rightName = 'Right nonemptyName :: Name nonemptyName = '(:|) +----------------------------------------------------- +-- +-- Lifting the TH AST +-- +----------------------------------------------------- + +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Loc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DocLoc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ModName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift GHC.Internal.TH.Syntax.Module +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameSpace +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NamespaceSpecifier +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PkgName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameFlavour +-- | @since template-haskell-2.22.1.0 +deriving instance Lift OccName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Name +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameIs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Specificity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift BndrVis +-- | @since template-haskell-2.22.1.0 +deriving instance Lift a => Lift (TyVarBndr a) +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TyLit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Type +-- | @since template-haskell-2.22.1.0 +instance Lift Bytes where + lift = Lib.litE . BytesPrimL + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Lit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pat +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Clause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivClause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivStrategy +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Overlap +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FunDep +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Safety +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Callconv +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Foreign +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ForeignSrcLang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FixityDirection +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Fixity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Inline +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleMatch +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Phases +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleBndr +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnTarget +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pragma +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceUnpackedness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DecidedStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Bang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Con +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TySynEqn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FamilyResultSig +-- | @since template-haskell-2.22.1.0 +deriving instance Lift InjectivityAnn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TypeFamilyHead +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Role +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynArgs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynDir +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Dec +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Range +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Exp +-- | @since template-haskell-2.22.1.0 +instance Lift (TExp a) where + lift (TExp e) = [| TExp $(lift e) |] + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Match +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Guard +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Stmt +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Body +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Info +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnLookup +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Extension + ----------------------------------------------------- -- -- Generic Lift implementations ===================================== libraries/template-haskell/changelog.md ===================================== @@ -1,5 +1,9 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) +## 2.22.1.0 + + * `Lift` instances were added for the `template-haskell` AST. + ## 2.22.0.0 * The kind of `Code` was changed from `forall r. (Type -> Type) -> TYPE r -> Type` ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -3,7 +3,7 @@ -- template-haskell.cabal. name: template-haskell -version: 2.22.0.0 +version: 2.22.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE ===================================== testsuite/tests/ghci/scripts/T21110.stderr ===================================== @@ -1,5 +1,5 @@ - : warning: [GHC-42258] [-Wunused-packages] The following packages were specified via -package or -package-id flags, but were not needed for compilation: - - template-haskell-2.22.0.0 (exposed by flag -package template-haskell) + - template-haskell-2.22.1.0 (exposed by flag -package template-haskell) + ===================================== testsuite/tests/interface-stability/template-haskell-exports.stdout ===================================== @@ -2420,28 +2420,88 @@ instance GHC.Internal.Show.Show GHC.Internal.LanguageExtensions.Extension -- Def instance GHC.Internal.Show.Show GHC.Internal.TH.Ppr.ForallVisFlag -- Defined in ‘GHC.Internal.TH.Ppr’ instance [safe] GHC.Internal.Show.Show GHC.Internal.TH.PprLib.Doc -- Defined in ‘GHC.Internal.TH.PprLib’ instance GHC.Internal.Show.Show GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.ForeignSrcLang’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnLookup -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnTarget -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.BndrVis -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Body -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Bool -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bytes -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Callconv -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Char -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Clause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Con -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Dec -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DecidedStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivClause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivStrategy -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DocLoc -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Double -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (GHC.Internal.Data.Either.Either a b) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Exp -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.LanguageExtensions.Extension -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FamilyResultSig -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Fixity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FixityDirection -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Float -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Foreign -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FunDep -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Guard -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Info -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.InjectivityAnn -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Inline -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Int -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int16 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int32 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int64 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int8 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Integer.Integer -- Defined in ‘GHC.Internal.TH.Lift’ -instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift [a] -- Defined in ‘GHC.Internal.TH.Lift’ +instance [overlappable] forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift [a] -- Defined in ‘GHC.Internal.TH.Lift’ +instance [overlapping] GHC.Internal.TH.Lift.Lift [GHC.Types.Char] -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Lit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Loc -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Match -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Maybe.Maybe a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.ModName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Module -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Name -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameFlavour -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameIs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameSpace -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NamespaceSpecifier -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Natural.Natural -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.OccName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Overlap -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pat -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynArgs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynDir -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Phases -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PkgName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pragma -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Range -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.Real.Integral a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Real.Ratio a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Role -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleBndr -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleMatch -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Safety -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceUnpackedness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Specificity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Stmt -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TExp a) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (a, b) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c) => GHC.Internal.TH.Lift.Lift (a, b, c) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d) => GHC.Internal.TH.Lift.Lift (a, b, c, d) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f g. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f, GHC.Internal.TH.Lift.Lift g) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f, g) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TyLit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TySynEqn -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TyVarBndr a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Type -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TypeFamilyHead -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift () -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Word -- Defined in ‘GHC.Internal.TH.Lift’ ===================================== testsuite/tests/th/TH_Lift.hs ===================================== @@ -80,3 +80,8 @@ o = $( (\x -> [| x |]) (True, 'x', 4 :: Int) ) p :: NonEmpty Char p = $( (\x -> [| x |]) ('a' :| "bcde") ) +exp :: Exp +exp = $( [| 3 + 4 |] >>= lift ) + +texp :: TExp Int +texp = $$( examineCode [|| 3 + 4 ||] `bindCode` liftTyped ) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0487e4577552c7f47e8bbecb328d38260e69a072...79b15a4302361fcf746739f1817e3f66d60d9d9e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0487e4577552c7f47e8bbecb328d38260e69a072...79b15a4302361fcf746739f1817e3f66d60d9d9e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 14:44:50 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Thu, 13 Jun 2024 10:44:50 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T24623 Message-ID: <666b05e2ec078_1199fe27923201182fb@gitlab.mail> Simon Peyton Jones pushed new branch wip/T24623 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T24623 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 14:59:10 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Thu, 13 Jun 2024 10:59:10 -0400 Subject: [Git][ghc/ghc][wip/T24676] 18 commits: users-guide: Fix stylistic issues in 9.12 release notes Message-ID: <666b093eaa915_1199fe29e24041257f@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24676 at Glasgow Haskell Compiler / GHC Commits: e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - c2d1563e by Simon Peyton Jones at 2024-06-13T15:58:36+01:00 Small documentation update in Quick Look - - - - - 26 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Builtin/Names.hs - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Head.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Gen/Pat.hs - compiler/GHC/Tc/Solver/Dict.hs - compiler/GHC/Tc/Solver/Equality.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/afd88e56d20c4880818e4aeec8a3d347ee747e0e...c2d1563ea37977f01627c3cabfb8199d15bc5287 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/afd88e56d20c4880818e4aeec8a3d347ee747e0e...c2d1563ea37977f01627c3cabfb8199d15bc5287 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 15:10:13 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 13 Jun 2024 11:10:13 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] 3 commits: TODO: MOV stuff Message-ID: <666b0bd536d8_1199fe2be130413362c@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 64611d0d by sheaf at 2024-06-13T13:38:09+02:00 TODO: MOV stuff - - - - - f5032fc9 by sheaf at 2024-06-13T17:09:40+02:00 X86 NCG SIMD: refactoring - - - - - 68d896f4 by sheaf at 2024-06-13T17:09:54+02:00 SIMD tests: fixup - - - - - 11 changed files: - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Platform/Reg/Class.hs - compiler/GHC/StgToCmm/Prim.hs - testsuite/tests/simd/should_run/Simd009c.hs - testsuite/tests/simd/should_run/all.T Changes: ===================================== compiler/GHC/CmmToAsm/Format.hs ===================================== @@ -23,6 +23,7 @@ module GHC.CmmToAsm.Format ( cmmTypeFormat, formatToWidth, formatInBytes, + scalarWidth, isIntScalarFormat, ) @@ -79,7 +80,6 @@ data Format | FF64 | VecFormat !Length -- ^ number of elements !ScalarFormat -- ^ format of each element - !Width -- ^ size of each element deriving (Show, Eq, Ord) pattern IntegerFormat :: Format @@ -98,13 +98,14 @@ isIntegerFormat = \case instance Outputable Format where ppr fmt = text (show fmt) -data ScalarFormat = FmtInt8 - | FmtInt16 - | FmtInt32 - | FmtInt64 - | FmtFloat - | FmtDouble - deriving (Show, Eq, Ord) +data ScalarFormat + = FmtInt8 + | FmtInt16 + | FmtInt32 + | FmtInt64 + | FmtFloat + | FmtDouble + deriving (Show, Eq, Ord) isIntScalarFormat :: ScalarFormat -> Bool isIntScalarFormat FmtInt8 = True @@ -165,27 +166,37 @@ vecFormat ty = elemTy = vecElemType ty in if isFloatType elemTy then case typeWidth elemTy of - W32 -> VecFormat l FmtFloat W32 - W64 -> VecFormat l FmtDouble W64 + W32 -> VecFormat l FmtFloat + W64 -> VecFormat l FmtDouble _ -> pprPanic "Incorrect vector element width" (ppr elemTy) else case typeWidth elemTy of - W8 -> VecFormat l FmtInt8 W8 - W16 -> VecFormat l FmtInt16 W16 - W32 -> VecFormat l FmtInt32 W32 - W64 -> VecFormat l FmtInt64 W64 + W8 -> VecFormat l FmtInt8 + W16 -> VecFormat l FmtInt16 + W32 -> VecFormat l FmtInt32 + W64 -> VecFormat l FmtInt64 _ -> pprPanic "Incorrect vector element width" (ppr elemTy) -- | Get the Width of a Format. formatToWidth :: Format -> Width formatToWidth format = case format of - II8 -> W8 - II16 -> W16 - II32 -> W32 - II64 -> W64 - FF32 -> W32 - FF64 -> W64 - VecFormat l _ w -> widthFromBytes (l*widthInBytes w) + II8 -> W8 + II16 -> W16 + II32 -> W32 + II64 -> W64 + FF32 -> W32 + FF64 -> W64 + VecFormat l s -> + widthFromBytes (l * widthInBytes (scalarWidth s)) + +scalarWidth :: ScalarFormat -> Width +scalarWidth = \case + FmtInt8 -> W8 + FmtInt16 -> W16 + FmtInt32 -> W32 + FmtInt64 -> W64 + FmtFloat -> W32 + FmtDouble -> W64 formatInBytes :: Format -> Int formatInBytes = widthInBytes . formatToWidth ===================================== compiler/GHC/CmmToAsm/PPC/Ppr.hs ===================================== @@ -221,7 +221,7 @@ pprFormat x II64 -> text "d" FF32 -> text "fs" FF64 -> text "fd" - VecFormat _ _ _ -> panic "PPC pprFormat: VecFormat" + VecFormat {} -> panic "PPC pprFormat: VecFormat" pprCond :: IsLine doc => Cond -> doc pprCond c @@ -384,7 +384,7 @@ pprInstr platform instr = case instr of II64 -> text "d" FF32 -> text "fs" FF64 -> text "fd" - VecFormat _ _ _ -> panic "PPC pprInstr: VecFormat" + VecFormat {} -> panic "PPC pprInstr: VecFormat" ), case addr of AddrRegImm _ _ -> empty AddrRegReg _ _ -> char 'x', @@ -427,7 +427,7 @@ pprInstr platform instr = case instr of II64 -> text "d" FF32 -> text "fs" FF64 -> text "fd" - VecFormat _ _ _ -> panic "PPC pprInstr: VecFormat" + VecFormat {} -> panic "PPC pprInstr: VecFormat" ), case addr of AddrRegImm _ _ -> empty AddrRegReg _ _ -> char 'x', ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -399,17 +399,6 @@ linearRA block_live block_id = go [] [] (accInstr', new_fixups) <- raInsn block_live accInstr block_id instr go accInstr' (new_fixups ++ accFixups) instrs --- TODO: move to proper place -classOfReg :: Platform -> Reg -> RegClass -classOfReg platform (RegReal x) = targetClassOfRealReg platform x -classOfReg _ (RegVirtual x) = classOfVirtualReg x - --- TODO: move to proper place --- TODO: on some platforms we can be more lenient, --- e.g. on X86 Float/Double/Vec are compatible -compatibleReg :: Platform -> Reg -> Reg -> Bool -compatibleReg platform r1 r2 = classOfReg platform r1 == classOfReg platform r2 - -- | Do allocation for a single instruction. raInsn :: OutputableRegConstraint freeRegs instr @@ -434,7 +423,6 @@ raInsn _ new_instrs _ (LiveInstr ii@(Instr i) Nothing) raInsn block_live new_instrs id (LiveInstr (Instr instr) (Just live)) = do assig <- getAssigR :: RegM freeRegs (UniqFM Reg Loc) - platform <- getPlatform -- If we have a reg->reg move between virtual registers, where the -- src register is not live after this instruction, and the dst @@ -447,8 +435,7 @@ raInsn block_live new_instrs id (LiveInstr (Instr instr) (Just live)) Just (src,dst) | Just (_, fmt) <- lookupUFM (liveDieRead live) src, isVirtualReg dst, not (dst `elemUFM` assig), - isRealReg src || isInReg src assig, - compatibleReg platform src dst -> do + isRealReg src || isInReg src assig -> do case src of RegReal rr -> setAssigR (addToUFM assig dst (InReg $ RealRegUsage rr fmt)) -- if src is a fixed reg, then we just map dest to this @@ -888,7 +875,9 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc -- trimmed down datatype that only keeps track of e.g. -- how many stack slots something uses up. vr_fmt = case r of - VirtualRegVec {} -> VecFormat 2 FmtDouble W64 + VirtualRegVec {} -> VecFormat 2 FmtDouble + -- SIMD NCG TODO: handle 256 and 512 by adding + -- new virtual register constructors. _ -> II64 -- Can we put the variable into a register it already was? ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1046,6 +1046,8 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps MO_WF_Bitcast W32 -> bitcast II32 FF32 x MO_FW_Bitcast W64 -> bitcast FF64 II64 x MO_WF_Bitcast W64 -> bitcast II64 FF64 x + MO_WF_Bitcast {} -> incorrectOperands + MO_FW_Bitcast {} -> incorrectOperands -- widenings MO_UU_Conv W8 W32 -> integerExtend W8 W32 MOVZxL x @@ -1084,42 +1086,84 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps MO_XX_Conv W32 W64 | not is32Bit -> integerExtend W32 W64 MOV x MO_FF_Conv W32 W64 -> coerceFP2FP W64 x - - MO_FF_Conv W64 W32 -> coerceFP2FP W32 x + MO_FF_Conv {} -> incorrectOperands + MO_UU_Conv {} -> incorrectOperands + MO_SS_Conv {} -> incorrectOperands + MO_XX_Conv {} -> incorrectOperands + MO_FS_Truncate from to -> coerceFP2Int from to x MO_SF_Round from to -> coerceInt2FP from to x - -- SIMD NCG TODO (optional): implement these vector operations as well - -- (they are integer vector operations). - MO_V_Insert {} -> needLlvm mop - MO_V_Extract {} -> needLlvm mop - MO_V_Add {} -> needLlvm mop - MO_V_Sub {} -> needLlvm mop - MO_V_Mul {} -> needLlvm mop - MO_VS_Quot {} -> needLlvm mop - MO_VS_Rem {} -> needLlvm mop - MO_VS_Neg {} -> needLlvm mop - MO_VU_Quot {} -> needLlvm mop - MO_VU_Rem {} -> needLlvm mop - MO_V_Shuffle {} -> incorrectOperands - MO_VF_Shuffle {} -> incorrectOperands - MO_VF_Broadcast {} -> incorrectOperands - MO_VF_Insert {} -> incorrectOperands + MO_VF_Neg l w | avx -> vector_float_negate_avx l w x + | sse && sse2 -> vector_float_negate_sse l w x + | otherwise + -> sorry "Please enable the -mavx or -msse, -msse2 flag" + -- SIMD NCG TODO + MO_VS_Neg {} -> needLlvm mop + + -- Binary MachOps + MO_Add {} -> incorrectOperands + MO_Sub {} -> incorrectOperands + MO_Eq {} -> incorrectOperands + MO_Ne {} -> incorrectOperands + MO_Mul {} -> incorrectOperands + MO_S_MulMayOflo {} -> incorrectOperands + MO_S_Quot {} -> incorrectOperands + MO_S_Rem {} -> incorrectOperands + MO_U_Quot {} -> incorrectOperands + MO_U_Rem {} -> incorrectOperands + MO_S_Ge {} -> incorrectOperands + MO_S_Le {} -> incorrectOperands + MO_S_Gt {} -> incorrectOperands + MO_S_Lt {} -> incorrectOperands + MO_U_Ge {} -> incorrectOperands + MO_U_Le {} -> incorrectOperands + MO_U_Gt {} -> incorrectOperands + MO_U_Lt {} -> incorrectOperands + MO_F_Add {} -> incorrectOperands + MO_F_Sub {} -> incorrectOperands + MO_F_Mul {} -> incorrectOperands + MO_F_Quot {} -> incorrectOperands + MO_F_Eq {} -> incorrectOperands + MO_F_Ne {} -> incorrectOperands + MO_F_Ge {} -> incorrectOperands + MO_F_Le {} -> incorrectOperands + MO_F_Gt {} -> incorrectOperands + MO_F_Lt {} -> incorrectOperands + MO_And {} -> incorrectOperands + MO_Or {} -> incorrectOperands + MO_Xor {} -> incorrectOperands + MO_Shl {} -> incorrectOperands + MO_U_Shr {} -> incorrectOperands + MO_S_Shr {} -> incorrectOperands + + MO_V_Extract {} -> incorrectOperands + MO_V_Add {} -> incorrectOperands + MO_V_Sub {} -> incorrectOperands + MO_V_Mul {} -> incorrectOperands + MO_VS_Quot {} -> incorrectOperands + MO_VS_Rem {} -> incorrectOperands + MO_VU_Quot {} -> incorrectOperands + MO_VU_Rem {} -> incorrectOperands + MO_V_Shuffle {} -> incorrectOperands + MO_VF_Shuffle {} -> incorrectOperands + MO_VF_Extract {} -> incorrectOperands MO_VF_Add {} -> incorrectOperands MO_VF_Sub {} -> incorrectOperands MO_VF_Mul {} -> incorrectOperands MO_VF_Quot {} -> incorrectOperands + MO_V_Broadcast {} -> incorrectOperands + MO_VF_Broadcast {} -> incorrectOperands - MO_VF_Neg l w | avx -> vector_float_negate_avx l w x - | sse && sse2 -> vector_float_negate_sse l w x - | otherwise - -> sorry "Please enable the -mavx or -msse, -msse2 flag" - + -- Ternary MachOps + MO_FMA {} -> incorrectOperands + MO_VF_Insert {} -> incorrectOperands + MO_V_Insert {} -> incorrectOperands - _other -> pprPanic "getRegister" (pprMachOp mop) + --_other -> pprPanic "getRegister" (pprMachOp mop) where triv_ucode :: (Format -> Operand -> Instr) -> Format -> NatM Register triv_ucode instr format = trivialUCode format (instr format) x @@ -1163,12 +1207,12 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps vector_float_negate_avx :: Length -> Width -> CmmExpr -> NatM Register vector_float_negate_avx l w expr = do - tmp <- getNewRegNat (VecFormat l FmtFloat w) + tmp <- getNewRegNat (VecFormat l FmtFloat) (reg, exp) <- getSomeReg expr Amode addr addr_code <- memConstant (mkAlignment $ widthInBytes W32) (CmmFloat 0.0 W32) let format = case w of - W32 -> VecFormat l FmtFloat w - W64 -> VecFormat l FmtDouble w + W32 -> VecFormat l FmtFloat + W64 -> VecFormat l FmtDouble _ -> pprPanic "Cannot negate vector of width" (ppr w) code dst = case w of W32 -> exp `appOL` addr_code `snocOL` @@ -1183,11 +1227,11 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps vector_float_negate_sse :: Length -> Width -> CmmExpr -> NatM Register vector_float_negate_sse l w expr = do - tmp <- getNewRegNat (VecFormat l FmtFloat w) + tmp <- getNewRegNat (VecFormat l FmtFloat) (reg, exp) <- getSomeReg expr let format = case w of - W32 -> VecFormat l FmtFloat w - W64 -> VecFormat l FmtDouble w + W32 -> VecFormat l FmtFloat + W64 -> VecFormat l FmtDouble _ -> pprPanic "Cannot negate vector of width" (ppr w) code dst = exp `snocOL` (XOR format (OpReg tmp) (OpReg tmp)) `snocOL` @@ -1253,12 +1297,6 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps MO_U_Shr rep -> shift_code rep SHR x y {-False-} MO_S_Shr rep -> shift_code rep SAR x y {-False-} - MO_V_Shuffle l w is - | avx - -> vector_shuffle_int l w x y is - | otherwise - -> sorry "Please enable the -mavx flag" - MO_VF_Shuffle l w is | avx -> vector_shuffle_float l w x y is @@ -1269,23 +1307,27 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps | sse4_1 -> vector_float_broadcast_sse l W32 x y | otherwise -> sorry "Please enable the -mavx or -msse4 flag" - MO_VF_Broadcast l W64 | sse2 -> vector_float_broadcast_avx l W64 x y | otherwise -> sorry "Please enable the -msse2 flag" - + MO_VF_Broadcast {} -> incorrectOperands + MO_V_Broadcast l W64 | sse2 -> vector_int_broadcast l W64 x y | otherwise -> sorry "Please enable the -msse2 flag" + -- SIMD NCG TODO: W32, W16, W8 + MO_V_Broadcast {} -> needLlvm mop MO_VF_Extract l W32 | avx -> vector_float_unpack l W32 x y | sse -> vector_float_unpack_sse l W32 x y | otherwise -> sorry "Please enable the -mavx or -msse flag" - MO_VF_Extract l W64 | sse2 -> vector_float_unpack l W64 x y | otherwise -> sorry "Please enable the -msse2 flag" - + MO_VF_Extract {} -> incorrectOperands + MO_V_Extract l W64 | sse2 -> vector_int_unpack_sse l W64 x y | otherwise -> sorry "Please enable the -msse2 flag" + -- SIMD NCG TODO: W32, W16, W8 + MO_V_Extract {} -> needLlvm mop MO_VF_Add l w | avx -> vector_float_op_avx VA_Add l w x y | sse && w == W32 -> vector_float_op_sse VA_Add l w x y @@ -1311,10 +1353,38 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps | otherwise -> sorry "Please enable the -mavx or -msse flag" - MO_VF_Insert {} -> incorrectOperands + -- SIMD NCG TODO: integer vector operations + MO_V_Shuffle {} -> needLlvm mop + MO_V_Add {} -> needLlvm mop + MO_V_Sub {} -> needLlvm mop + MO_V_Mul {} -> needLlvm mop + MO_VS_Quot {} -> needLlvm mop + MO_VS_Rem {} -> needLlvm mop + MO_VU_Quot {} -> needLlvm mop + MO_VU_Rem {} -> needLlvm mop + + -- Unary MachOps + MO_S_Neg {} -> incorrectOperands + MO_F_Neg {} -> incorrectOperands + MO_Not {} -> incorrectOperands + MO_SF_Round {} -> incorrectOperands + MO_FS_Truncate {} -> incorrectOperands + MO_SS_Conv {} -> incorrectOperands + MO_XX_Conv {} -> incorrectOperands + MO_FF_Conv {} -> incorrectOperands + MO_UU_Conv {} -> incorrectOperands + MO_WF_Bitcast {} -> incorrectOperands + MO_FW_Bitcast {} -> incorrectOperands + MO_RelaxedRead {} -> incorrectOperands + MO_AlignmentCheck {} -> incorrectOperands + MO_VS_Neg {} -> incorrectOperands + MO_VF_Neg {} -> incorrectOperands + + -- Ternary MachOps + MO_FMA {} -> incorrectOperands + MO_V_Insert {} -> incorrectOperands + MO_VF_Insert {} -> incorrectOperands - - _other -> pprPanic "getRegister(x86) - binary CmmMachOp (1)" (pprMachOp mop) where -------------------- triv_op width instr = trivialCode width op (Just op) x y @@ -1511,8 +1581,8 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps (reg1, exp1) <- getSomeReg expr1 (reg2, exp2) <- getSomeReg expr2 let format = case w of - W32 -> VecFormat l FmtFloat W32 - W64 -> VecFormat l FmtDouble W64 + W32 -> VecFormat l FmtFloat + W64 -> VecFormat l FmtDouble _ -> pprPanic "Operation not supported for width " (ppr w) code dst = case op of VA_Add -> arithInstr VADD @@ -1535,8 +1605,8 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps (reg1, exp1) <- getSomeReg expr1 (reg2, exp2) <- getSomeReg expr2 let format = case w of - W32 -> VecFormat l FmtFloat W32 - W64 -> VecFormat l FmtDouble W64 + W32 -> VecFormat l FmtFloat + W64 -> VecFormat l FmtDouble _ -> pprPanic "Operation not supported for width " (ppr w) code dst = case op of VA_Add -> arithInstr ADD @@ -1559,26 +1629,26 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps vector_float_unpack l W32 expr (CmmLit lit) = do (r, exp) <- getSomeReg expr - let format = VecFormat l FmtFloat W32 + let format = VecFormat l FmtFloat imm = litToImm lit code dst = case lit of - CmmInt 0 _ -> exp `snocOL` (MOV FF32 (OpReg r) (OpReg dst)) + CmmInt 0 _ -> exp `snocOL` (MOVSD FF32 (OpReg r) (OpReg dst)) CmmInt _ _ -> exp `snocOL` (VPSHUFD format imm (OpReg r) dst) _ -> panic "Error in offset while unpacking" return (Any format code) vector_float_unpack l W64 expr (CmmLit lit) = do (r, exp) <- getSomeReg expr - let format = VecFormat l FmtDouble W64 + let format = VecFormat l FmtDouble addr = spRel platform 0 code dst = case lit of CmmInt 0 _ -> exp `snocOL` - (MOV FF64 (OpReg r) (OpReg dst)) + (MOVSD FF64 (OpReg r) (OpReg dst)) CmmInt 1 _ -> exp `snocOL` (MOVH format (OpReg r) (OpAddr addr)) `snocOL` - (MOV FF64 (OpAddr addr) (OpReg dst)) + (MOVSD FF64 (OpAddr addr) (OpReg dst)) -- SIMD NCG TODO: avoid going via the stack here? _ -> panic "Error in offset while unpacking" return (Any format code) @@ -1594,7 +1664,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps vector_float_unpack_sse l W32 expr (CmmLit lit) = do (r,exp) <- getSomeReg expr - let format = VecFormat l FmtFloat W32 + let format = VecFormat l FmtFloat imm = litToImm lit code dst = case lit of @@ -1614,7 +1684,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps = do fn <- getAnyReg expr1 (r', exp) <- getSomeReg expr2 - let f = VecFormat len FmtFloat W32 + let f = VecFormat len FmtFloat addr = spRel platform 0 in return $ Any f (\r -> exp `appOL` (fn r) `snocOL` @@ -1624,7 +1694,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps = do fn <- getAnyReg expr1 (r', exp) <- getSomeReg expr2 - let f = VecFormat len FmtDouble W64 + let f = VecFormat len FmtDouble addr = spRel platform 0 in return $ Any f (\r -> exp `appOL` (fn r) `snocOL` @@ -1643,15 +1713,15 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps = do fn <- getAnyReg expr1 -- destination (r, exp) <- getSomeReg expr2 -- source - let f = VecFormat len FmtFloat W32 + let f = VecFormat len FmtFloat addr = spRel platform 0 code dst = exp `appOL` (fn dst) `snocOL` (MOVU f (OpReg r) (OpAddr addr)) `snocOL` (insertps 0) `snocOL` - (insertps 8) `snocOL` (insertps 16) `snocOL` - (insertps 24) + (insertps 32) `snocOL` + (insertps 48) where insertps off = INSERTPS f (litToImm $ CmmInt off W32) (OpAddr addr) dst @@ -1659,7 +1729,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps in return $ Any f code vector_float_broadcast_sse _ _ c _ = pprPanic "Broadcast not supported for : " (pdoc platform c) - + vector_int_broadcast :: Length -> Width -> CmmExpr @@ -1669,10 +1739,10 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps = do fn <- getAnyReg expr1 (val, exp) <- getSomeReg expr2 - let fmt = VecFormat len FmtInt64 W64 + let fmt = VecFormat len FmtInt64 return $ Any fmt (\dst -> exp `appOL` (fn dst) `snocOL` - (MOV fmt (OpReg val) (OpReg dst)) `snocOL` + (MOV II64 (OpReg val) (OpReg dst)) `snocOL` (PUNPCKLQDQ fmt (OpReg dst) dst)) vector_int_broadcast _ _ c _ = pprPanic "Broadcast not supported for : " (pdoc platform c) @@ -1686,7 +1756,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps vector_int_unpack_sse l at 2 W64 expr (CmmLit lit) = do (r, exp) <- getSomeReg expr - let fmt = VecFormat l FmtInt64 W64 + let fmt = VecFormat l FmtInt64 tmp <- getNewRegNat fmt let code dst = case lit of @@ -1700,14 +1770,11 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps vector_int_unpack_sse _ w c e = pprPanic "Unpack not supported for : " (pdoc platform c $$ pdoc platform e $$ ppr w) - vector_shuffle_int :: Length -> Width -> CmmExpr -> CmmExpr -> [Int] -> NatM Register - vector_shuffle_int = undefined - vector_shuffle_float :: Length -> Width -> CmmExpr -> CmmExpr -> [Int] -> NatM Register vector_shuffle_float l w v1 v2 is = do (r1, exp1) <- getSomeReg v1 (r2, exp2) <- getSomeReg v2 - let fmt = VecFormat l (if w == W32 then FmtFloat else FmtDouble) w + let fmt = VecFormat l (if w == W32 then FmtFloat else FmtDouble) code dst = exp1 `appOL` (exp2 `appOL` shuffleInstructions fmt r1 r2 is dst) return (Any fmt code) @@ -1715,7 +1782,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps shuffleInstructions :: Format -> Reg -> Reg -> [Int] -> Reg -> OrdList Instr shuffleInstructions fmt v1 v2 is dst = case fmt of - VecFormat 2 FmtDouble _ -> + VecFormat 2 FmtDouble -> case is of [i1, i2] -> case (i1, i2) of (0,0) -> unitOL (VSHUFPD fmt (ImmInt 0b00) (OpReg v1) v1 dst) @@ -1736,7 +1803,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps (3,1) -> unitOL (VSHUFPD fmt (ImmInt 0b11) (OpReg v1) v2 dst) _ -> pprPanic "vector shuffle: indices out of bounds 0 <= i <= 3" (ppr is) _ -> pprPanic "vector shuffle: wrong number of indices (expected 2)" (ppr is) - VecFormat 4 FmtFloat _ -> + VecFormat 4 FmtFloat -> case is of -- indices 0 <= i <= 7 [i1, i2, i3, i4] @@ -1815,7 +1882,7 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps = do fn <- getAnyReg vecExpr (r, exp) <- getSomeReg valExpr - let fmt = VecFormat len FmtFloat W32 + let fmt = VecFormat len FmtFloat imm = litToImm offset code dst = exp `appOL` (fn dst) `snocOL` @@ -1826,17 +1893,17 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps = do (valReg, valExp) <- getSomeReg valExpr (vecReg, vecExp) <- getSomeReg vecExpr - let fmt = VecFormat len FmtDouble W64 + let fmt = VecFormat len FmtDouble code dst = case offset of -- TODO: why not just index by element rather than by byte? CmmInt 0 _ -> valExp `appOL` vecExp `snocOL` - (MOV fmt (OpReg valReg) (OpReg dst)) `snocOL` + (MOVSD FF64 (OpReg valReg) (OpReg dst)) `snocOL` (SHUFPD fmt (ImmInt 0b00) (OpReg vecReg) dst) - CmmInt 8 _ -> valExp `appOL` + CmmInt 16 _ -> valExp `appOL` vecExp `snocOL` - (MOV fmt (OpReg vecReg) (OpReg dst)) `snocOL` + (MOVSD FF64 (OpReg vecReg) (OpReg dst)) `snocOL` (SHUFPD fmt (ImmInt 0b00) (OpReg valReg) dst) _ -> pprPanic "MO_VF_Insert DoubleX2: unsupported offset" (ppr offset) in return $ Any fmt code @@ -1865,7 +1932,7 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps pprTraceM "vecExpr:" (pdoc platform vecExpr) (valReg, valExp) <- getSomeReg valExpr (vecReg, vecExp) <- getSomeReg vecExpr - let fmt = VecFormat len FmtInt64 W64 + let fmt = VecFormat len FmtInt64 tmp <- getNewRegNat fmt pprTraceM "tmp:" (ppr tmp) let code dst @@ -1875,11 +1942,11 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps (MOVHLPS fmt (OpReg vecReg) tmp) `snocOL` (MOV II64 (OpReg valReg) (OpReg dst)) `snocOL` (PUNPCKLQDQ fmt (OpReg tmp) dst) - CmmInt 8 _ -> valExp `appOL` - vecExp `snocOL` - (MOV fmt (OpReg vecReg) (OpReg dst)) `snocOL` - (MOV II64 (OpReg valReg) (OpReg tmp)) `snocOL` - (PUNPCKLQDQ fmt (OpReg tmp) dst) + CmmInt 16 _ -> valExp `appOL` + vecExp `snocOL` + (MOV fmt (OpReg vecReg) (OpReg dst)) `snocOL` + (MOV II64 (OpReg valReg) (OpReg tmp)) `snocOL` + (PUNPCKLQDQ fmt (OpReg tmp) dst) _ -> pprPanic "MO_V_Insert Int64X2: unsupported offset" (ppr offset) in return $ Any fmt code vector_int_insert_sse len width _ _ offset @@ -2024,13 +2091,16 @@ getAnyReg expr = do anyReg :: Register -> NatM (Reg -> InstrBlock) anyReg (Any _ code) = return code -anyReg (Fixed rep reg fcode) = return (\dst -> fcode `snocOL` reg2reg rep reg dst) +anyReg (Fixed rep reg fcode) = do + platform <- getPlatform + return (\dst -> fcode `snocOL` mkRegRegMoveInstr platform rep reg dst) -- A bit like getSomeReg, but we want a reg that can be byte-addressed. -- Fixed registers might not be byte-addressable, so we make sure we've -- got a temporary, inserting an extra reg copy if necessary. getByteReg :: CmmExpr -> NatM (Reg, InstrBlock) getByteReg expr = do + platform <- getPlatform is32Bit <- is32BitPlatform if is32Bit then do r <- getRegister expr @@ -2042,7 +2112,7 @@ getByteReg expr = do | isVirtualReg reg -> return (reg,code) | otherwise -> do tmp <- getNewRegNat rep - return (tmp, code `snocOL` reg2reg rep reg tmp) + return (tmp, code `snocOL` mkRegRegMoveInstr platform rep reg tmp) -- ToDo: could optimise slightly by checking for -- byte-addressable real registers, but that will -- happen very rarely if at all. @@ -2063,18 +2133,10 @@ getNonClobberedReg expr = do | reg `elem` instrClobberedRegs platform -> do tmp <- getNewRegNat rep - return (tmp, code `snocOL` reg2reg rep reg tmp) + return (tmp, code `snocOL` mkRegRegMoveInstr platform rep reg tmp) | otherwise -> return (reg, code) -reg2reg :: Format -> Reg -> Reg -> Instr -reg2reg format@(VecFormat _ FmtFloat W32) src dst - = VMOVU format (OpReg src) (OpReg dst) -reg2reg format@(VecFormat _ FmtDouble W64) src dst - = VMOVU format (OpReg src) (OpReg dst) -reg2reg format src dst - = MOV format (OpReg src) (OpReg dst) - -------------------------------------------------------------------------------- -- | Convert a 'CmmExpr' representing a memory address into an 'Amode'. @@ -3427,7 +3489,7 @@ genCCall64 addr conv dest_regs args = do tmp <- getNewRegNat arg_fmt let code' = code `appOL` arg_code tmp - acode' = acode `snocOL` reg2reg arg_fmt tmp r + acode' = acode `snocOL` mkRegRegMoveInstr platform arg_fmt tmp r return (code',acode') arg_rep = cmmExprType platform arg ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -370,6 +370,9 @@ data Instr | MOVL Format Operand Operand | MOVH Format Operand Operand | MOVA Format Operand Operand + | MOVDQU Format Operand Operand + | VMOVDQU Format Operand Operand + | MOVSD Format Operand Operand -- logic operations | VPXOR Format Reg Reg Reg @@ -526,6 +529,10 @@ regUsageOfInstr platform instr MOVA fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) MOVL fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) MOVH fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) + MOVDQU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) + VMOVDQU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) + MOVSD fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) + VPXOR fmt s1 s2 dst -> mkRU fmt [s1,s2] [dst] VADD fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] @@ -739,6 +746,10 @@ patchRegsOfInstr instr env MOVA fmt src dst -> MOVA fmt (patchOp src) (patchOp dst) MOVL fmt src dst -> MOVL fmt (patchOp src) (patchOp dst) MOVH fmt src dst -> MOVH fmt (patchOp src) (patchOp dst) + MOVDQU fmt src dst -> MOVDQU fmt (patchOp src) (patchOp dst) + VMOVDQU fmt src dst -> VMOVDQU fmt (patchOp src) (patchOp dst) + MOVSD fmt src dst -> MOVSD fmt (patchOp src) (patchOp dst) + VPXOR fmt s1 s2 dst -> VPXOR fmt (env s1) (env s2) (env dst) VADD fmt s1 s2 dst -> VADD fmt (patchOp s1) (env s2) (env dst) @@ -763,7 +774,7 @@ patchRegsOfInstr instr env -> PSLLDQ fmt (patchOp off) (env dst) PSRLDQ fmt off dst -> PSRLDQ fmt (patchOp off) (env dst) - + MOVHLPS fmt src dst -> MOVHLPS fmt (patchOp src) (env dst) PUNPCKLQDQ fmt src dst @@ -945,11 +956,20 @@ mkRegRegMoveInstr -> Reg -> Reg -> Instr - -mkRegRegMoveInstr _platform fmt src dst = - case fmt of - VecFormat {} -> MOVU fmt (OpReg src) (OpReg dst) - _ -> MOV fmt (OpReg src) (OpReg dst) +mkRegRegMoveInstr _platform fmt@(VecFormat _ s) src dst + | isIntScalarFormat s + = if widthInBytes (formatToWidth fmt) <= 128 + then MOVDQU fmt (OpReg src) (OpReg dst) + else VMOVDQU fmt (OpReg src) (OpReg dst) + | otherwise + = if widthInBytes (formatToWidth fmt) <= 128 + then MOVU fmt (OpReg src) (OpReg dst) + else VMOVU fmt (OpReg src) (OpReg dst) +mkRegRegMoveInstr _platform fmt src dst + | isFloatFormat fmt + = MOVSD fmt (OpReg src) (OpReg dst) + | otherwise + = MOV fmt (OpReg src) (OpReg dst) -- | Check whether an instruction represents a reg-reg move. -- The register allocator attempts to eliminate reg->reg moves whenever it can, @@ -959,8 +979,24 @@ takeRegRegMoveInstr :: Instr -> Maybe (Reg,Reg) -takeRegRegMoveInstr (MOV _ (OpReg r1) (OpReg r2)) - = Just (r1,r2) +takeRegRegMoveInstr (MOV fmt (OpReg r1) (OpReg r2)) + -- MOV zeroes the upper part of vector registers, + -- so it is not a real "move" in that case. + | not (isVecFormat fmt) + = Just (r1,r2) +takeRegRegMoveInstr (MOVSD fmt (OpReg r1) (OpReg r2)) + | not (isVecFormat fmt) + = Just (r1,r2) +takeRegRegMoveInstr (MOVA _ (OpReg r1) (OpReg r2)) + = Just (r1, r2) +takeRegRegMoveInstr (MOVU _ (OpReg r1) (OpReg r2)) + = Just (r1, r2) +takeRegRegMoveInstr (VMOVU _ (OpReg r1) (OpReg r2)) + = Just (r1, r2) +takeRegRegMoveInstr (MOVDQU _ (OpReg r1) (OpReg r2)) + = Just (r1, r2) +takeRegRegMoveInstr (VMOVDQU _ (OpReg r1) (OpReg r2)) + = Just (r1, r2) takeRegRegMoveInstr _ = Nothing ===================================== compiler/GHC/CmmToAsm/X86/Ppr.hs ===================================== @@ -431,13 +431,13 @@ pprFormat x = case x of II64 -> text "q" FF32 -> text "ss" -- "scalar single-precision float" (SSE2) FF64 -> text "sd" -- "scalar double-precision float" (SSE2) - VecFormat _ FmtFloat W32 -> text "ps" - VecFormat _ FmtDouble W64 -> text "pd" + VecFormat _ FmtFloat -> text "ps" + VecFormat _ FmtDouble -> text "pd" -- TODO: this is shady because it only works for certain instructions - VecFormat _ FmtInt8 W8 -> text "b" - VecFormat _ FmtInt16 W16 -> text "w" - VecFormat _ FmtInt32 W32 -> text "l" - VecFormat _ FmtInt64 W64 -> text "q" + VecFormat _ FmtInt8 -> text "b" + VecFormat _ FmtInt16 -> text "w" + VecFormat _ FmtInt32 -> text "l" + VecFormat _ FmtInt64 -> text "q" pprFormat_x87 :: IsLine doc => Format -> doc pprFormat_x87 x = case x of @@ -715,9 +715,9 @@ pprInstr platform i = case i of XOR FF64 src dst -> pprOpOp (text "xorpd") FF64 src dst - XOR format@(VecFormat _ sfmt _) src dst | isIntScalarFormat sfmt + XOR format@(VecFormat _ sfmt) src dst | isIntScalarFormat sfmt -> pprOpOp (text "pxor") format src dst - + XOR format src dst -> pprFormatOpOp (text "xor") format src dst @@ -968,6 +968,14 @@ pprInstr platform i = case i of -> pprFormatOpOp (text "movl") format from to MOVH format from to -> pprFormatOpOp (text "movh") format from to + + MOVDQU format from to + -> pprOpOp (text "movdqu") format from to + VMOVDQU format from to + -> pprOpOp (text "vmovdqu") format from to + MOVSD format from to + -> pprOpOp (text "movsd") format from to + VPXOR format s1 s2 dst -> pprXor (text "vpxor") format s1 s2 dst VEXTRACT format offset from to @@ -1045,9 +1053,9 @@ pprInstr platform i = case i of pprBroadcastFormat :: Format -> Line doc pprBroadcastFormat x = case x of - VecFormat _ FmtFloat W32 -> text "ss" - VecFormat _ FmtDouble W64 -> text "sd" - -- TODO: Add Ints and remove panic + VecFormat _ FmtFloat -> text "ss" + VecFormat _ FmtDouble -> text "sd" + -- SIMD NCG TODO: Add Ints and remove panic VecFormat {} -> panic "Incorrect width" _ -> panic "Scalar Format invading vector operation" @@ -1061,7 +1069,6 @@ pprInstr platform i = case i of pprOperand platform format op1 ] - pprFormatOp_ :: Line doc -> Format -> Operand -> doc pprFormatOp_ name format op1 = line $ hcat [ @@ -1153,7 +1160,7 @@ pprInstr platform i = case i of comma, pprReg platform (archWordFormat (target32Bit platform)) reg2 ] - + pprOpReg :: Line doc -> Format -> Operand -> Reg -> doc pprOpReg name format op reg = line $ hcat [ ===================================== compiler/GHC/CmmToLlvm/CodeGen.hs ===================================== @@ -1521,6 +1521,7 @@ genMachOp _ op [x] = case op of MO_VU_Rem _ _ -> panicOp MO_VF_Broadcast _ _ -> panicOp + MO_V_Broadcast _ _ -> panicOp MO_VF_Insert _ _ -> panicOp MO_VF_Extract _ _ -> panicOp @@ -1722,6 +1723,7 @@ genMachOp_slow opt op [x, y] = case op of MO_VS_Neg {} -> panicOp + MO_V_Broadcast {} -> panicOp MO_VF_Broadcast {} -> panicOp MO_VF_Insert {} -> panicOp ===================================== compiler/GHC/Platform/Reg/Class.hs ===================================== @@ -11,7 +11,7 @@ import GHC.Prelude import GHC.Utils.Outputable as Outputable import GHC.Types.Unique -import GHC.Builtin.Uniques +import GHC.Builtin.Uniques ( mkRegClassUnique ) -- | The class of a register. ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -2653,7 +2653,7 @@ doVecPackOp ty z es res = do where -- vector indices are always 32-bits -- TODO: consider indexing by element rather than by byte - iLit = CmmLit (CmmInt ((toInteger i) * 8) W32) + iLit = CmmLit (CmmInt ((toInteger i) * 16) W32) len :: Length len = vecLength ty ===================================== testsuite/tests/simd/should_run/Simd009c.hs ===================================== @@ -13,6 +13,7 @@ module Simd009c where import Control.Monad ( unless ) import Data.Foldable ( for_ ) import GHC.Exts +import GHC.Prim import Language.Haskell.TH ( CodeQ ) import Language.Haskell.TH.Syntax ( Lift(liftTyped) ) ===================================== testsuite/tests/simd/should_run/all.T ===================================== @@ -1,6 +1,7 @@ # N.B. Only the X86 NCG and LLVM backends support SIMD operations for now. setTestOpts([ unless(arch('x86_64'), only_ways(llvm_ways)) , when(unregisterised(), skip) + , js_skip, when(arch('wasm32'), skip) ]) test('simd000', [], compile_and_run, ['']) @@ -12,5 +13,5 @@ test('simd005', [], compile_and_run, ['']) test('simd006', [], compile_and_run, ['']) test('simd007', [], compile_and_run, ['']) test('simd008', [], compile_and_run, ['']) -test('simd009', [extra_files(['Simd009b.hs', 'Simd009c.hs'])], multimod_compile_and_run, ['simd009', '']) +test('simd009', [req_th, extra_files(['Simd009b.hs', 'Simd009c.hs'])], multimod_compile_and_run, ['simd009', '']) test('simd010', [], compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/db9a19a6e10287e60619751c76710e80aae5687a...68d896f4f1b1db0dcaa263503910de475906a72f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/db9a19a6e10287e60619751c76710e80aae5687a...68d896f4f1b1db0dcaa263503910de475906a72f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 15:15:18 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 13 Jun 2024 11:15:18 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: compiler: Make ghc-experimental not wired in Message-ID: <666b0d0649977_1199fe2d42c70134488@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - c29a3ad2 by Pierre Le Marre at 2024-06-13T11:14:51-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 565f6192 by Jacco Krijnen at 2024-06-13T11:14:52-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - 17 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Builtin/Names.hs - compiler/GHC/Unit/Types.hs - libraries/base/src/Data/Array/Byte.hs - libraries/ghc-experimental/ghc-experimental.cabal - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs - − libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs - libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell/ModuleGenerators.hs - libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal - utils/haddock/CONTRIBUTING.md - utils/haddock/cabal.project Changes: ===================================== .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py ===================================== @@ -217,7 +217,7 @@ def mk_new_yaml(release_mode, version, date, pipeline_type, job_map): a64 = { "Linux_Debian": { "< 10": deb9 , "( >= 10 && < 11 )": deb10 , "( >= 11 && < 12 )": deb11 - , ">= 11": deb12 + , ">= 12": deb12 , "unknown_versioning": deb11 } , "Linux_Ubuntu" : { "unknown_versioning": ubuntu2004 , "( >= 16 && < 18 )": deb9 ===================================== compiler/GHC/Builtin/Names.hs ===================================== @@ -669,10 +669,6 @@ gHC_INTERNAL_OVER_LABELS = mkGhcInternalModule (fsLit "GHC.Internal.OverloadedLa gHC_INTERNAL_RECORDS :: Module gHC_INTERNAL_RECORDS = mkGhcInternalModule (fsLit "GHC.Internal.Records") -dATA_TUPLE_EXPERIMENTAL, dATA_SUM_EXPERIMENTAL :: Module -dATA_TUPLE_EXPERIMENTAL = mkExperimentalModule (fsLit "Data.Tuple.Experimental") -dATA_SUM_EXPERIMENTAL = mkExperimentalModule (fsLit "Data.Sum.Experimental") - rOOT_MAIN :: Module rOOT_MAIN = mkMainModule (fsLit ":Main") -- Root module for initialisation @@ -714,9 +710,6 @@ mkMainModule m = mkModule mainUnit (mkModuleNameFS m) mkMainModule_ :: ModuleName -> Module mkMainModule_ m = mkModule mainUnit m -mkExperimentalModule :: FastString -> Module -mkExperimentalModule m = mkModule experimentalUnit (mkModuleNameFS m) - {- ************************************************************************ * * ===================================== compiler/GHC/Unit/Types.hs ===================================== @@ -77,7 +77,6 @@ module GHC.Unit.Types , mainUnit , thisGhcUnit , interactiveUnit - , experimentalUnit , isInteractiveModule , wiredInUnitIds @@ -594,11 +593,10 @@ Make sure you change 'GHC.Unit.State.findWiredInUnits' if you add an entry here. -} bignumUnitId, primUnitId, ghcInternalUnitId, baseUnitId, rtsUnitId, - mainUnitId, thisGhcUnitId, interactiveUnitId, - experimentalUnitId :: UnitId + mainUnitId, thisGhcUnitId, interactiveUnitId :: UnitId bignumUnit, primUnit, ghcInternalUnit, baseUnit, rtsUnit, - mainUnit, thisGhcUnit, interactiveUnit, experimentalUnit :: Unit + mainUnit, thisGhcUnit, interactiveUnit :: Unit primUnitId = UnitId (fsLit "ghc-prim") bignumUnitId = UnitId (fsLit "ghc-bignum") @@ -607,7 +605,6 @@ baseUnitId = UnitId (fsLit "base") rtsUnitId = UnitId (fsLit "rts") thisGhcUnitId = UnitId (fsLit cProjectUnitId) -- See Note [GHC's Unit Id] interactiveUnitId = UnitId (fsLit "interactive") -experimentalUnitId = UnitId (fsLit "ghc-experimental") primUnit = RealUnit (Definite primUnitId) bignumUnit = RealUnit (Definite bignumUnitId) @@ -616,7 +613,6 @@ baseUnit = RealUnit (Definite baseUnitId) rtsUnit = RealUnit (Definite rtsUnitId) thisGhcUnit = RealUnit (Definite thisGhcUnitId) interactiveUnit = RealUnit (Definite interactiveUnitId) -experimentalUnit = RealUnit (Definite experimentalUnitId) -- | This is the package Id for the current program. It is the default -- package Id if you don't specify a package name. We don't add this prefix @@ -634,7 +630,6 @@ wiredInUnitIds = , ghcInternalUnitId , baseUnitId , rtsUnitId - , experimentalUnitId ] -- NB: ghc is no longer part of the wired-in units since its unit-id, given -- by hadrian or cabal, is no longer overwritten and now matches both the ===================================== libraries/base/src/Data/Array/Byte.hs ===================================== @@ -48,7 +48,7 @@ import Prelude -- The memory representation of a 'ByteArray' is: -- -- > ╭─────────────┬───╮ ╭────────┬──────┬─────────╮ --- > │ Constructor │ * ┼─➤│ Header │ Size │ Payload │ +-- > │ Constructor │ * ┼─►│ Header │ Size │ Payload │ -- > ╰─────────────┴───╯ ╰────────┴──────┴─────────╯ -- -- And its overhead is the following: ===================================== libraries/ghc-experimental/ghc-experimental.cabal ===================================== @@ -35,4 +35,3 @@ library ghc-prim >= 0.11 && < 0.12 hs-source-dirs: src default-language: Haskell2010 - ghc-options: -this-unit-id ghc-experimental ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs ===================================== @@ -8,9 +8,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.DerivedCoreProperties --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs ===================================== @@ -8,9 +8,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.UnicodeData.GeneralCategory --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs ===================================== @@ -7,9 +7,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.UnicodeData.SimpleLowerCaseMapping --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs ===================================== @@ -7,9 +7,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.UnicodeData.SimpleTitleCaseMapping --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs ===================================== @@ -7,9 +7,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.UnicodeData.SimpleUpperCaseMapping --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs ===================================== @@ -6,9 +6,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Version --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs deleted ===================================== @@ -1,1127 +0,0 @@ -{-# LANGUAGE LambdaCase #-} - --- | --- Module : Parser.Text --- Copyright : (c) 2020 Composewell Technologies and Contributors --- (c) 2016-2017 Harendra Kumar --- (c) 2014-2015 Antonio Nikishaev --- License : BSD-3-Clause --- Maintainer : streamly at composewell.com --- Stability : internal - --- This code was taken from https://github.com/composewell/unicode-data. --- The original Unicode database parser was taken from --- https://github.com/composewell/unicode-transforms but was completely --- rewritten from scratch to parse from UCD text files instead of XML, only --- some types remain the same. That code in turn was originally taken from --- https://github.com/llelf/prose (Antonio Nikishaev) and heavily modified by --- Harendra Kumar. --- -module Parser.Text (genModules) where - -import Control.Exception (catch, IOException) -import Control.Monad (void) -import Data.Bits (Bits(..)) -import Data.Word (Word8) -import Data.Char (chr, ord, isSpace) -import Data.Functor ((<&>)) -import Data.Function ((&)) -import Data.List (intersperse, unfoldr) -import Data.List.Split (splitWhen) -import Numeric (showHex) -import Streamly.Data.Fold (Fold) -import System.Directory (createDirectoryIfMissing) -import System.Environment (getEnv) -import System.FilePath ((), (<.>)) - --- import qualified Data.Set as Set -import Streamly.Data.Stream (Stream) -import qualified Streamly.Data.Stream.Prelude as Stream -import qualified Streamly.Data.Fold as Fold -import qualified Streamly.Internal.Data.Fold as Fold -import qualified Streamly.Data.Unfold as Unfold -import qualified Streamly.FileSystem.Handle as Handle -import qualified Streamly.Unicode.Stream as Unicode -import qualified Streamly.Internal.Unicode.Stream as Unicode -import qualified System.IO as Sys - -import Prelude hiding (pred) - -------------------------------------------------------------------------------- --- Types -------------------------------------------------------------------------------- - -data GeneralCategory = - Lu|Ll|Lt| --LC - Lm|Lo| --L - Mn|Mc|Me| --M - Nd|Nl|No| --N - Pc|Pd|Ps|Pe|Pi|Pf|Po| --P - Sm|Sc|Sk|So| --S - Zs|Zl|Zp| --Z - Cc|Cf|Cs|Co|Cn --C - deriving (Show, Bounded, Enum, Read) - -data DecompType = - DTCanonical | DTCompat | DTFont - | DTNoBreak | DTInitial | DTMedial | DTFinal - | DTIsolated | DTCircle | DTSuper | DTSub - | DTVertical | DTWide | DTNarrow - | DTSmall | DTSquare | DTFraction - deriving (Show, Eq) - -data Decomp = DCSelf | DC [Char] deriving (Show, Eq) - --- data DType = Canonical | Kompat - -data DetailedChar = - DetailedChar - { _char :: Char - , _name :: String - , _generalCategory :: GeneralCategory - , _combiningClass :: Int - , _decompositionType :: Maybe DecompType - , _decomposition :: Decomp - , _simpleUppercaseMapping :: Maybe Char - , _simpleLowercaseMapping :: Maybe Char - , _simpleTitlecaseMapping :: Maybe Char - } - deriving (Show) - -{- [NOTE] Used by disabled generator - --- See: https://www.unicode.org/reports/tr44/#Default_Values_Table -mkDefaultDetailedChar :: Char -> DetailedChar -mkDefaultDetailedChar c = DetailedChar - { _char = c - , _name = mempty - , _generalCategory = Cn - , _combiningClass = 0 - , _decompositionType = Nothing - , _decomposition = DCSelf - , _simpleUppercaseMapping = Nothing - , _simpleLowercaseMapping = Nothing - , _simpleTitlecaseMapping = Nothing } --} - -------------------------------------------------------------------------------- --- Helpers -------------------------------------------------------------------------------- - -headerRule :: String -headerRule = "-----------------------------------------------------------------------------" - -mkModuleHeader :: String -> String -mkModuleHeader modName = - unlines - [ headerRule - , "-- |" - , "-- Module : " <> modName - , "-- Copyright : (c) 2020 Composewell Technologies and Contributors" - , "-- License : BSD-3-Clause" - -- [FIXME] Update maintainer - , "-- Maintainer : streamly at composewell.com" - , "-- Stability : internal" - , headerRule - ] - -readCodePoint :: String -> Char -readCodePoint = chr . read . ("0x"<>) - -readCodePointM :: String -> Maybe Char -readCodePointM "" = Nothing -readCodePointM u = Just (readCodePoint u) - -genSignature :: String -> String -genSignature = (<> " :: Char -> Bool") - --- | Check that var is between minimum and maximum of orderList -genRangeCheck :: String -> [Int] -> String -genRangeCheck var ordList = - var - <> " >= " - <> show (minimum ordList) - <> " && " <> var <> " <= " <> show (maximum ordList) - -genBitmap :: String -> [Int] -> String -genBitmap funcName ordList = - unlines - [ "{-# INLINE " <> funcName <> " #-}" - , genSignature funcName - , funcName <> " = \\c -> let n = ord c in " - <> genRangeCheck "n" ordList <> " && lookupBit64 bitmap# n" - , " where" - , " bitmap# = \"" <> bitMapToAddrLiteral (positionsToBitMap ordList) "\"#" - ] - -positionsToBitMap :: [Int] -> [Bool] -positionsToBitMap = go 0 - - where - - go _ [] = [] - go i xxs@(x:xs) - | i < x = False : go (i + 1) xxs - | otherwise = True : go (i + 1) xs - -bitMapToAddrLiteral :: - -- | Values to encode - [Bool] -> - -- | String to append - String -> - String -bitMapToAddrLiteral bs cs = foldr encode cs (unfoldr mkChunks bs) - - where - - mkChunks :: [a] -> Maybe ([a], [a]) - mkChunks [] = Nothing - mkChunks xs = Just $ splitAt 8 xs - - encode :: [Bool] -> String -> String - encode chunk acc = '\\' : shows (toByte (padTo8 chunk)) acc - - padTo8 :: [Bool] -> [Bool] - padTo8 xs - | length xs >= 8 = xs - | otherwise = xs <> replicate (8 - length xs) False - - toByte :: [Bool] -> Int - toByte xs = sum $ map (\i -> if xs !! i then 1 `shiftL` i else 0) [0..7] - -genEnumBitmap :: - forall a. (Bounded a, Enum a, Show a) => - -- | Function name - String -> - -- | Default value - a -> - -- | List of values to encode - [a] -> - String -genEnumBitmap funcName def as = unlines - [ "{-# INLINE " <> funcName <> " #-}" - , funcName <> " :: Char -> Int" - , funcName <> " c = let n = ord c in if n >= " - <> show (length as) - <> " then " - <> show (fromEnum def) - <> " else lookup_bitmap n" - - , "{-# NOINLINE lookup_bitmap #-}" - , "lookup_bitmap :: Int -> Int" - , "lookup_bitmap n = lookupIntN bitmap# n" - , " where" - , " bitmap# = \"" <> enumMapToAddrLiteral as "\"#" - ] - -{-| Encode a list of values as a byte map, using their 'Enum' instance. - -__Note:__ 'Enum' instance must respect the following: - -* @fromEnum minBound >= 0x00@ -* @fromEnum maxBound <= 0xff@ --} -enumMapToAddrLiteral :: - forall a. (Bounded a, Enum a, Show a) => - -- | Values to encode - [a] -> - -- | String to append - String -> - String -enumMapToAddrLiteral xs cs = foldr go cs xs - - where - - go :: a -> String -> String - go x acc = '\\' : shows (toWord8 x) acc - - toWord8 :: a -> Word8 - toWord8 a = let w = fromEnum a in if 0 <= w && w <= 0xff - then fromIntegral w - else error $ "Cannot convert to Word8: " <> show a - -{- [NOTE] Disabled generator (normalization) --- This bit of code is duplicated but this duplication allows us to reduce 2 --- dependencies on the executable. - -jamoLCount :: Int -jamoLCount = 19 - -jamoVCount :: Int -jamoVCount = 21 - -jamoTCount :: Int -jamoTCount = 28 - -hangulFirst :: Int -hangulFirst = 0xac00 - -hangulLast :: Int -hangulLast = hangulFirst + jamoLCount * jamoVCount * jamoTCount - 1 - -isHangul :: Char -> Bool -isHangul c = n >= hangulFirst && n <= hangulLast - where n = ord c --} - -genUnicodeVersion :: FilePath -> IO () -genUnicodeVersion outdir = do - version <- catch - (getEnv "UNICODE_VERSION") - (\(_ :: IOException) -> return "") - Stream.fold f (Stream.fromList (body version)) - where - moduleName = "GHC.Internal.Unicode.Version" - f = moduleFileEmitter Nothing outdir - (moduleName, \_ -> Fold.foldMap (<> "\n")) - body :: String -> [String] - body version = - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(unicodeVersion)" - , "where" - , "" - , "import {-# SOURCE #-} GHC.Internal.Data.Version" - , "" - , "-- | Version of Unicode standard used by @base@:" - , "-- [" <> version <> "](https://www.unicode.org/versions/Unicode" <> version <> "/)." - , "--" - , "-- @since base-4.15.0.0" - , "unicodeVersion :: Version" - , "unicodeVersion = makeVersion [" <> mkVersion version <> "]" ] - mkVersion = foldr (\c acc -> case c of {'.' -> ',':' ':acc; _ -> c:acc}) mempty - -------------------------------------------------------------------------------- --- Parsers -------------------------------------------------------------------------------- - -------------------------------------------------------------------------------- --- Parsing UnicodeData.txt -------------------------------------------------------------------------------- - -genGeneralCategoryModule - :: Monad m - => String - -> Fold m DetailedChar String -genGeneralCategoryModule moduleName = - done <$> Fold.foldl' step initial - - where - - -- (categories, expected char) - initial = ([], '\0') - - step (acc, p) a = if p < _char a - -- Fill missing char entry with default category Cn - -- See: https://www.unicode.org/reports/tr44/#Default_Values_Table - then step (Cn : acc, succ p) a - -- Regular entry - else (_generalCategory a : acc, succ (_char a)) - - done (acc, _) = unlines - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(generalCategory)" - , "where" - , "" - , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" - , "import GHC.Internal.Unicode.Bits (lookupIntN)" - , "" - , genEnumBitmap "generalCategory" Cn (reverse acc) - ] - -readDecomp :: String -> (Maybe DecompType, Decomp) -readDecomp s = - if null wrds - then (Nothing, DCSelf) - else decmps wrds - - where - - decmps [] = error "Unreachable flow point" - decmps y@(x:xs) = - case dtmap x of - DTCanonical -> (,) (Just DTCanonical) (readCP y) - other -> (,) (Just other) (readCP xs) - - wrds = words s - - readCP ws = DC $ map readCodePoint ws - - dtmap "" = DTCompat - dtmap "" = DTCircle - dtmap "" = DTFinal - dtmap "" = DTFont - dtmap "" = DTFraction - dtmap "" = DTInitial - dtmap "" = DTIsolated - dtmap "" = DTMedial - dtmap "" = DTNarrow - dtmap "" = DTNoBreak - dtmap "" = DTSmall - dtmap "" = DTSquare - dtmap "" = DTSub - dtmap "" = DTSuper - dtmap "" = DTVertical - dtmap "" = DTWide - dtmap _ = DTCanonical - -{- [NOTE] Disabled generators - -filterNonHangul :: Monad m => Fold m DetailedChar a -> Fold m DetailedChar a -filterNonHangul = Fold.filter (not . isHangul . _char) - -filterDecomposableType :: - Monad m => DType -> Fold m DetailedChar a -> Fold m DetailedChar a -filterDecomposableType dtype = - Fold.filter ((/= DCSelf) . _decomposition) - . Fold.filter (predicate . _decompositionType) - - where - - predicate = - case dtype of - Canonical -> (== Just DTCanonical) - Kompat -> const True - -genDecomposableModule :: - Monad m => String -> DType -> Fold m DetailedChar String -genDecomposableModule moduleName dtype = - filterNonHangul - $ filterDecomposableType dtype $ done <$> Fold.foldl' step initial - - where - - initial = [] - - step st a = ord (_char a) : st - - done st = - unlines - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(isDecomposable)" - , "where" - , "" - , "import Data.Char (ord)" - , "import GHC.Internal.Unicode.Bits (lookupBit64)" - , "" - , genBitmap "isDecomposable" (reverse st) - ] - -genCombiningClassModule :: Monad m => String -> Fold m DetailedChar String -genCombiningClassModule moduleName = - Fold.filter (\dc -> _combiningClass dc /= 0) - $ done <$> Fold.foldl' step initial - - where - - initial = ([], []) - - step (st1, st2) a = (genCombiningClassDef a : st1, ord (_char a) : st2) - - done (st1, st2) = - unlines - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(combiningClass, isCombining)" - , "where" - , "" - , "import Data.Char (ord)" - , "import GHC.Internal.Unicode.Bits (lookupBit64)" - , "" - , "combiningClass :: Char -> Int" - , unlines (reverse st1) - , "combiningClass _ = 0\n" - , "" - , genBitmap "isCombining" (reverse st2) - ] - - genCombiningClassDef dc = - "combiningClass " - <> show (_char dc) <> " = " <> show (_combiningClass dc) - -genDecomposeDefModule :: - Monad m - => String - -> [String] - -> [String] - -> DType - -> (Int -> Bool) - -> Fold m DetailedChar String -genDecomposeDefModule moduleName before after dtype pred = - Fold.filter (pred . ord . _char) - $ filterNonHangul - $ filterDecomposableType dtype $ done <$> Fold.foldl' step initial - - where - - decomposeChar c DCSelf = [c] - decomposeChar _c (DC ds) = ds - - genHeader = - [ "{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(decompose)" - , "where" - , "" - ] - genSign = - [ "-- Note: this is a partial function we do not expect to call" - , "-- this if isDecomposable returns false." - , "{-# NOINLINE decompose #-}" - , "decompose :: Char -> [Char]" - ] - initial = [] - - step st dc = genDecomposeDef dc : st - - done st = - let body = mconcat [genHeader, before, genSign, reverse st, after] - in unlines body - - genDecomposeDef dc = - "decompose " - <> show (_char dc) - <> " = " <> show (decomposeChar (_char dc) (_decomposition dc)) - -genCompositionsModule :: - Monad m - => String - -> [Int] - -> [Int] - -> Fold m DetailedChar String -genCompositionsModule moduleName compExclu non0CC = - Fold.filter (not . flip elem compExclu . ord . _char) - $ filterNonHangul - $ Fold.filter (isDecompositionLen2 . _decomposition) - $ filterDecomposableType Canonical $ done <$> Fold.foldl' step initial - - where - - isDecompositionLen2 DCSelf = False - isDecompositionLen2 (DC ds) = length ds == 2 - - genComposePairDef name dc = - name - <> " " - <> show (head d01) - <> " " <> show (d01 !! 1) <> " = Just " <> show (_char dc) - - where - - d01 = decompPair dc - - decompPair dc = - case _decomposition dc of - DCSelf -> error "toCompFormat: DCSelf" - (DC ds) -> - if length ds == 2 - then ds - else error "toCompFormat: length /= 2" - - initial = ([], [], []) - - step (dec, sp, ss) dc = (dec1, sp1, ss1) - - where - - d01 = decompPair dc - d1Ord = ord $ d01 !! 1 - dec1 = genComposePairDef "compose" dc : dec - sp1 = - if d1Ord `notElem` non0CC - then genComposePairDef "composeStarters" dc : sp - else sp - ss1 = - if d1Ord `notElem` non0CC - then d1Ord : ss - else ss - - header = - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(compose, composeStarters, isSecondStarter)" - , "where" - , "" - , "import GHC.Internal.Base (Char, ord)" - , "import GHC.Internal.Unicode.Bits (lookupBit64)" - , "" - ] - - composePair decomps = - [ "{-# NOINLINE compose #-}" - , "compose :: Char -> Char -> Maybe Char" - , unlines decomps - , "compose _ _ = " <> "Nothing" <> "\n" - , "" - ] - - composeStarterPair starterPairs = - [ "composeStarters :: Char -> Char -> Maybe Char" - , unlines starterPairs - , "composeStarters _ _ = " <> "Nothing" <> "\n" - , "" - ] - - isSecondStarter secondStarters = - [genBitmap "isSecondStarter" secondStarters] - - done (dec, sp, ss) = - unlines - $ header - <> composePair (reverse dec) - <> composeStarterPair (reverse sp) - <> isSecondStarter (Set.toList (Set.fromList ss)) --} -genSimpleCaseMappingModule - :: Monad m - => String - -> String - -> (DetailedChar -> Maybe Char) - -> Fold m DetailedChar String -genSimpleCaseMappingModule moduleName funcName field = - done <$> Fold.foldl' step initial - - where - - genHeader = - [ "{-# LANGUAGE NoImplicitPrelude, LambdaCase #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(" <> funcName <> ")" - , "where" - , "" - , "import GHC.Internal.Base (Char)" - , "" - ] - genSign = - [ "{-# NOINLINE " <> funcName <> " #-}" - , funcName <> " :: Char -> Char" - , funcName <> " = \\case" - ] - initial = [] - - step ds dc = case mkEntry dc of - Nothing -> ds - Just d -> d : ds - - after = [" c -> c"] - - done st = - let body = mconcat [genHeader, genSign, reverse st, after] - in unlines body - - mkEntry dc = field dc <&> \c -> mconcat - [ " '\\x" - , showHexChar (_char dc) "' -> '\\x" - , showHexChar c "'" - ] - - showHexChar c = showHex (ord c) - -genCorePropertiesModule :: - Monad m => String -> (String -> Bool) -> Fold m (String, [Int]) String -genCorePropertiesModule moduleName isProp = - Fold.filter (\(name, _) -> isProp name) $ done <$> Fold.foldl' step initial - - where - - prop2FuncName x = "is" <> x - - initial = ([], []) - - step (props, bitmaps) (name, bits) = - (name : props, genBitmap (prop2FuncName name) bits : bitmaps) - - done (props, bitmaps) = unlines $ header props <> bitmaps - - header exports = - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(" <> unwords (intersperse "," (map prop2FuncName exports)) <> ")" - , "where" - , "" - , "import GHC.Internal.Base (Bool, Char, Ord(..), (&&), ord)" - , "import GHC.Internal.Unicode.Bits (lookupBit64)" - , "" - ] - -{- [NOTE] Disabled generator -genUnicode002TestResults :: Monad m => Fold m DetailedChar String -genUnicode002TestResults = done <$> Fold.foldl' step initial - - where - - header = "Code C P S U L A D" - -- (output, expected char) - initial = ([], '\0') - -- [TODO] Increase the number of tested char? - -- maxChar = '\xF0000' -- First codepoint of the last private use areas. - -- maxChar = '\xFFFF' -- Last codepoint of BMP. - maxChar = chr 6553 -- Value in GHC 9.2.2 base test - - step (acc, c) dc = if c > maxChar - then (acc, c) - else if c < _char dc - -- Fill missing char entry with default values - -- See: https://www.unicode.org/reports/tr44/#Default_Values_Table - then step (mkEntry (mkDefaultDetailedChar c) : acc, succ c) dc - -- Regular entry - else (mkEntry dc : acc, succ (_char dc)) - - done (acc, _) = unlines (header : reverse acc) - - mkEntry dc = mconcat - [ showCode (_char dc) - -- [TODO] General category - , showBool (isControl' dc) - , showBool (isPrint' dc) - , showBool (isSpace' dc) - -- [TODO] isSeparator - , showBool (isUpper' dc) - , showBool (isLower' dc) - , showBool (isAlpha' dc) - -- [TODO] isAlphaNum - , showBool (isDigit' dc) - -- [TODO] isNumber - -- [TODO] isMark - -- [TODO] isPunctuation - -- [TODO] isSymbol - ] - - padding = length (show (ord maxChar)) - showCode c = take padding (shows (ord c) (repeat ' ')) - -- [TODO] use showHex - -- showCode c = - -- let code = showHex (ord c) mempty - -- in replicate (padding - length code) '0' <> code - showBool b = if b then " T" else " F" - - -- [NOTE] The following functions replicates Data.Char. Keep them up to date! - - isControl' dc = case _generalCategory dc of - Cc -> True -- Control - _ -> False - - isPrint' dc = case _generalCategory dc of - Zl -> False -- LineSeparator - Zp -> False -- ParagraphSeparator - Cc -> False -- Control - Cf -> False -- Format - Cs -> False -- Surrogate - Co -> False -- PrivateUse - Cn -> False -- NotAssigned - _ -> True - - isSpace' dc = case _char dc of - '\t' -> True - '\n' -> True - '\v' -> True - '\f' -> True - '\r' -> True - _ -> case _generalCategory dc of - Zs -> True -- Space - _ -> False - - isUpper' dc = case _generalCategory dc of - Lu -> True -- UppercaseLetter - Lt -> True -- TitlecaseLetter - _ -> False - - isLower' dc = case _generalCategory dc of - Ll -> True -- LowercaseLetter - _ -> False - - isAlpha' dc = case _generalCategory dc of - Lu -> True -- UppercaseLetter - Ll -> True -- LowercaseLetter - Lt -> True -- TitlecaseLetter - Lm -> True -- ModifierLetter - Lo -> True -- OtherLetter - _ -> False - - isDigit' dc = let c = _char dc - in (fromIntegral (ord c - ord '0') :: Word) <= 9 --} - -------------------------------------------------------------------------------- --- Parsing property files -------------------------------------------------------------------------------- - -type PropertyLine = (String, [Int]) - -trim :: String -> String -trim = takeWhile (not . isSpace) . dropWhile isSpace - -emptyPropertyLine :: PropertyLine -emptyPropertyLine = ("", []) - -combinePropertyLines :: PropertyLine -> PropertyLine -> PropertyLine -combinePropertyLines t1@(n1, o1) t2@(n2, o2) - | n1 == "" = t2 - | n2 == "" = t1 - | n1 == n2 = (n1, o1 <> o2) - | otherwise = error $ "Cannot group " <> n1 <> " with " <> n2 - -parsePropertyLine :: String -> PropertyLine -parsePropertyLine ln - | null ln = emptyPropertyLine - | head ln == '#' = emptyPropertyLine - | otherwise = parseLineJ ln - - where - - parseLineJ :: String -> (String, [Int]) - parseLineJ line = - let (rangeLn, line1) = span (/= ';') line - propLn = takeWhile (/= '#') (tail line1) - in (trim propLn, parseRange (trim rangeLn)) - - parseRange :: String -> [Int] - parseRange rng = - if '.' `elem` rng - then let low = read $ "0x" <> takeWhile (/= '.') rng - high = - read $ "0x" <> reverse (takeWhile (/= '.') (reverse rng)) - in [low .. high] - else [read $ "0x" <> rng] - -isDivider :: String -> Bool -isDivider x = x == "# ================================================" - -parsePropertyLines :: (Monad m) => Stream m String -> Stream m PropertyLine -parsePropertyLines = - Stream.splitOn isDivider - $ Fold.lmap parsePropertyLine - $ Fold.foldl' combinePropertyLines emptyPropertyLine - --- | A range entry in @UnicodeData.txt at . -data UnicodeDataRange - = SingleCode !DetailedChar - -- ^ Regular entry for one code point - | FirstCode !String !DetailedChar - -- ^ A partial range for entry with a name as: @\@ - | CompleteRange !String !DetailedChar !DetailedChar - -- ^ A complete range, requiring 2 continuous entries with respective names: - -- - -- * @\@ - -- * @\@ - -{-| Parse UnicodeData.txt lines - -Parse ranges according to https://www.unicode.org/reports/tr44/#Code_Point_Ranges. - -__Note:__ this does /not/ fill missing char entries, -i.e. entries with no explicit entry nor within a range. --} -parseUnicodeDataLines :: forall m. (Monad m) => Stream m String -> Stream m DetailedChar -parseUnicodeDataLines - = Stream.unfoldMany (Unfold.unfoldr unitToRange) - . Stream.foldMany ( Fold.lmap parseDetailedChar - $ Fold.foldt' step initial id) - - where - - step :: Maybe UnicodeDataRange - -> DetailedChar - -> Fold.Step (Maybe UnicodeDataRange) (Maybe UnicodeDataRange) - step Nothing dc = case span (/= ',') (_name dc) of - (range, ", First>") -> Fold.Partial (Just (FirstCode range dc)) - _ -> Fold.Done (Just (SingleCode dc)) - step (Just (FirstCode range1 dc1)) dc2 = case span (/= ',') (_name dc2) of - (range2, ", Last>") -> if range1 == range2 && _char dc1 < _char dc2 - then Fold.Done (Just (CompleteRange range1 dc1 dc2)) - else error $ "Cannot create range: incompatible ranges" <> show (dc1, dc2) - _ -> error $ "Cannot create range: missing entry correspong to: " <> show range1 - step _ _ = error "impossible case" - - initial :: Fold.Step (Maybe UnicodeDataRange) (Maybe UnicodeDataRange) - initial = Fold.Partial Nothing - - unitToRange :: Maybe UnicodeDataRange -> Maybe (DetailedChar, Maybe UnicodeDataRange) - unitToRange = fmap $ \case - SingleCode dc -> (dc, Nothing) - FirstCode _ dc -> error $ "Incomplete range: " <> show dc - CompleteRange range dc1 dc2 -> if _char dc1 < _char dc2 - -- [TODO] Create the proper name - then (dc1{_name="TODO"}, Just (CompleteRange range dc1{_char=succ (_char dc1)} dc2)) - else (dc2{_name="TODO"}, Nothing) - --- | Parse a single entry of @UnicodeData.txt@ -parseDetailedChar :: String -> DetailedChar -parseDetailedChar line = case splitWhen (== ';') line of - char - :name - :gc - :combining - :_bidi - :decomposition - :_decimal - :_digit - :_numeric - :_bidiM - :_uni1Name - :_iso - :sUpper - :sLower - :sTitle - :_ -> - let (dctype, dcval) = readDecomp decomposition - in DetailedChar - { _char = readCodePoint char - , _name = name - , _generalCategory = read gc - , _combiningClass = read combining - , _decompositionType = dctype - , _decomposition = dcval - , _simpleUppercaseMapping = readCodePointM sUpper - , _simpleLowercaseMapping = readCodePointM sLower - , _simpleTitlecaseMapping = readCodePointM sTitle - } - _ -> error ("Unsupported line: " <> line) - -------------------------------------------------------------------------------- --- Generation -------------------------------------------------------------------------------- - -readLinesFromFile :: String -> Stream IO String -readLinesFromFile file = - withFile file Sys.ReadMode - $ \h -> Handle.read h & Unicode.decodeUtf8 & Unicode.lines Fold.toList - - where - withFile file_ mode = - Stream.bracketIO (Sys.openFile file_ mode) (Sys.hClose) - - -moduleToFileName :: String -> String -moduleToFileName = map (\x -> if x == '.' then '/' else x) - -dirFromFileName :: String -> String -dirFromFileName = reverse . dropWhile (/= '/') . reverse - -data FileRecipe a - = ModuleRecipe - -- ^ A recipe to create a Haskell module file. - String - -- ^ Module name - (String -> Fold IO a String) - -- ^ Function that generate the module, given the module name. - | TestOutputRecipe - -- ^ A recipe to create a test output file. - String - -- ^ Test name - (Fold IO a String) - -- ^ Test output generator - --- ModuleRecipe is a tuple of the module name and a function that generates the --- module using the module name -type ModuleRecipe a = (String, String -> Fold IO a String) -type TestOutputRecipe a = (FilePath, Fold IO a String) - --- GeneratorRecipe is a list of ModuleRecipe -type GeneratorRecipe a = [FileRecipe a] - -moduleFileEmitter :: Maybe FilePath -> FilePath -> ModuleRecipe a -> Fold IO a () -moduleFileEmitter mfile outdir (modName, fldGen) = Fold.rmapM action $ fldGen modName - - where - - pretext version = case mfile of - Just file -> mconcat - [ "-- DO NOT EDIT: This file is automatically generated by the internal tool ucd2haskell,\n" - , "-- with data from: https://www.unicode.org/Public/" - , version - , "/ucd/" - , file - ,".\n\n" - ] - Nothing -> "-- DO NOT EDIT: This file is automatically generated by the internal tool ucd2haskell.\n\n" - outfile = outdir moduleToFileName modName <.> ".hs" - outfiledir = dirFromFileName outfile - action c = do - version <- - catch - (getEnv "UNICODE_VERSION") - (\(_ :: IOException) -> return "") - createDirectoryIfMissing True outfiledir - writeFile outfile (pretext version <> c) - -testOutputFileEmitter :: FilePath -> TestOutputRecipe a -> Fold IO a () -testOutputFileEmitter outdir (name, fldGen) = Fold.rmapM action fldGen - - where - - outfile = outdir "tests" name <.> ".stdout" - outfiledir = dirFromFileName outfile - action c - = createDirectoryIfMissing True outfiledir - *> writeFile outfile c - -runGenerator :: - FilePath - -> FilePath - -> (Stream IO String -> Stream IO a) - -> FilePath - -> GeneratorRecipe a - -> IO () -runGenerator indir file transformLines outdir recipes = - readLinesFromFile (indir <> file) & transformLines & Stream.fold combinedFld - - where - - generatedFolds = recipes <&> \case - ModuleRecipe name f -> moduleFileEmitter (Just file) outdir (name, f) - TestOutputRecipe name f -> testOutputFileEmitter outdir (name, f) - combinedFld = void $ Fold.distribute generatedFolds - -genModules :: String -> String -> [String] -> IO () -genModules indir outdir props = do - genUnicodeVersion outdir - - -- [NOTE] Disabled generator - -- compExclu <- - -- readLinesFromFile (indir <> "DerivedNormalizationProps.txt") - -- & parsePropertyLines - -- & Stream.find (\(name, _) -> name == "Full_Composition_Exclusion") - -- & fmap (snd . fromMaybe ("", [])) - - -- [NOTE] Disabled generator - -- non0CC <- - -- readLinesFromFile (indir <> "extracted/DerivedCombiningClass.txt") - -- & parsePropertyLines - -- & Stream.filter (\(name, _) -> name /= "0") - -- & Stream.map snd - -- & Stream.fold (Fold.foldl' (<>) []) - - runGenerator - indir - "UnicodeData.txt" - parseUnicodeDataLines - outdir - -- [NOTE] Disabled generators - -- [ uncurry ModuleRecipe compositions compExclu non0CC - -- , uncurry ModuleRecipe combiningClass - -- , uncurry ModuleRecipe decomposable - -- , uncurry ModuleRecipe decomposableK - -- , uncurry ModuleRecipe decompositions - -- , uncurry ModuleRecipe decompositionsK2 - -- , uncurry ModuleRecipe decompositionsK - [ uncurry ModuleRecipe generalCategory - , uncurry ModuleRecipe simpleUpperCaseMapping - , uncurry ModuleRecipe simpleLowerCaseMapping - , uncurry ModuleRecipe simpleTitleCaseMapping - -- , uncurry TestOutputRecipe unicode002Test - ] - - -- [NOTE] Disabled generator - -- runGenerator - -- indir - -- "PropList.txt" - -- parsePropertyLines - -- outdir - -- [ uncurry ModuleRecipe propList ] - - runGenerator - indir - "DerivedCoreProperties.txt" - parsePropertyLines - outdir - [ uncurry ModuleRecipe derivedCoreProperties ] - - where - - -- [NOTE] Disabled generator - -- propList = - -- ("GHC.Internal.Unicode.Char.PropList" - -- , (`genCorePropertiesModule` (`elem` props))) - - derivedCoreProperties = - ("GHC.Internal.Unicode.Char.DerivedCoreProperties" - , (`genCorePropertiesModule` (`elem` props))) - - -- [NOTE] Disabled generator - -- compositions exc non0 = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.Compositions" - -- , \m -> genCompositionsModule m exc non0) - - -- [NOTE] Disabled generator - -- combiningClass = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.CombiningClass" - -- , genCombiningClassModule) - - -- [NOTE] Disabled generator - -- decomposable = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.Decomposable" - -- , (`genDecomposableModule` Canonical)) - - -- [NOTE] Disabled generator - -- decomposableK = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.DecomposableK" - -- , (`genDecomposableModule` Kompat)) - - -- [NOTE] Disabled generator - -- decompositions = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.Decompositions" - -- , \m -> genDecomposeDefModule m [] [] Canonical (const True)) - - -- [NOTE] Disabled generator - -- decompositionsK2 = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.DecompositionsK2" - -- , \m -> genDecomposeDefModule m [] [] Kompat (>= 60000)) - - -- [NOTE] Disabled generator - -- decompositionsK = - -- let pre = ["import qualified " <> fst decompositionsK2 <> " as DK2", ""] - -- post = ["decompose c = DK2.decompose c"] - -- in ( "GHC.Internal.Unicode.Char.UnicodeData.DecompositionsK" - -- , \m -> genDecomposeDefModule m pre post Kompat (< 60000)) - - generalCategory = - ( "GHC.Internal.Unicode.Char.UnicodeData.GeneralCategory" - , genGeneralCategoryModule) - - simpleUpperCaseMapping = - ( "GHC.Internal.Unicode.Char.UnicodeData.SimpleUpperCaseMapping" - , \m -> genSimpleCaseMappingModule m "toSimpleUpperCase" _simpleUppercaseMapping) - - simpleLowerCaseMapping = - ( "GHC.Internal.Unicode.Char.UnicodeData.SimpleLowerCaseMapping" - , \m -> genSimpleCaseMappingModule m "toSimpleLowerCase" _simpleLowercaseMapping) - - simpleTitleCaseMapping = - ( "GHC.Internal.Unicode.Char.UnicodeData.SimpleTitleCaseMapping" - , \m -> genSimpleCaseMappingModule m "toSimpleTitleCase" _simpleTitlecaseMapping) - - -- unicode002Test = - -- ( "unicode002" - -- , genUnicode002TestResults) ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell.hs ===================================== @@ -2,14 +2,17 @@ -- Module : Main -- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers " -- Stability : internal -- module Main where -import WithCli (HasArguments(..), withCli) -import Parser.Text (genModules) +import qualified Data.ByteString.Char8 as B8 +import qualified Data.ByteString.Short as BS import GHC.Generics (Generic) +import WithCli (HasArguments(..), withCli) + +import UCD2Haskell.ModuleGenerators (genModules) data CLIOptions = CLIOptions @@ -20,7 +23,10 @@ data CLIOptions = deriving (Show, Generic, HasArguments) cliClient :: CLIOptions -> IO () -cliClient opts = genModules (input opts) (output opts) (core_prop opts) +cliClient opts = genModules + opts.input + opts.output + (BS.toShort . B8.pack <$> opts.core_prop) main :: IO () main = withCli cliClient ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell/ModuleGenerators.hs ===================================== @@ -0,0 +1,517 @@ +-- | +-- Module : UCD2Haskell.ModuleGenerators +-- Copyright : (c) 2020 Composewell Technologies and Contributors +-- (c) 2016-2017 Harendra Kumar +-- (c) 2014-2015 Antonio Nikishaev +-- (c) 2022-2024 Pierre Le Marre +-- License : BSD-3-Clause +-- Maintainer : The GHC Developers " +-- Stability : internal + +-- Code history: +-- +-- This code was adapted from https://github.com/composewell/unicode-data/ +-- (around commit c4aa52ed932ad8badf97296858932c3389b275b8) by Pierre Le Marre. +-- The original Unicode database parser was taken from +-- https://github.com/composewell/unicode-transforms but was completely +-- rewritten from scratch to parse from UCD text files instead of XML, only +-- some types remain the same. That code in turn was originally taken from +-- https://github.com/llelf/prose (Antonio Nikishaev) and heavily modified by +-- Harendra Kumar. +-- +module UCD2Haskell.ModuleGenerators (genModules) where + +import Control.Exception (catch, IOException) +import Data.Bits (Bits(..)) +import Data.Word (Word8) +import Data.Char (ord) +import Data.Functor ((<&>), ($>)) +import Data.List (intersperse, unfoldr) +import System.Directory (createDirectoryIfMissing) +import System.Environment (getEnv) +import System.FilePath ((), (<.>)) +import Data.String (IsString) +import Data.Foldable (Foldable(..)) + +import qualified Data.ByteString.Builder as BB +import qualified Data.ByteString as B +import qualified Data.ByteString.Lazy as BL +import qualified Data.ByteString.Short as BS + +import qualified Unicode.CharacterDatabase.Parser.Common as C +import qualified Unicode.CharacterDatabase.Parser.UnicodeData as UD +import qualified Unicode.CharacterDatabase.Parser.Properties.Multiple as P + +import Prelude hiding (pred) + +-------------------------------------------------------------------------------- +-- Helpers +-------------------------------------------------------------------------------- + +unlinesBB :: [BB.Builder] -> BB.Builder +unlinesBB = (<> "\n") . mconcat . intersperse "\n" + +unwordsBB :: [BB.Builder] -> BB.Builder +unwordsBB = mconcat . intersperse " " + +headerRule :: BB.Builder +headerRule = "-----------------------------------------------------------------------------" + +mkModuleHeader :: BB.Builder -> BB.Builder +mkModuleHeader modName = + unlinesBB + [ headerRule + , "-- |" + , "-- Module : " <> modName + , "-- License : BSD-3-Clause" + , "-- Maintainer : The GHC Developers " + , "-- Stability : internal" + , headerRule + ] + +genSignature :: BB.Builder -> BB.Builder +genSignature = (<> " :: Char -> Bool") + +-- | Check that var is between minimum and maximum of orderList +genRangeCheck :: BB.Builder -> [Int] -> BB.Builder +genRangeCheck var ordList = + var + <> " >= " + <> BB.intDec (minimum ordList) + <> " && " <> var <> " <= " <> BB.intDec (maximum ordList) + +genBitmap :: BB.Builder -> [Int] -> BB.Builder +genBitmap funcName ordList = + unlinesBB + [ "{-# INLINE " <> funcName <> " #-}" + , genSignature funcName + , funcName <> " = \\c -> let n = ord c in " + <> genRangeCheck "n" ordList <> " && lookupBit64 bitmap# n" + , " where" + , " bitmap# = \"" <> bitMapToAddrLiteral (positionsToBitMap ordList) "\"#" + ] + +positionsToBitMap :: [Int] -> [Bool] +positionsToBitMap = go 0 + + where + + go _ [] = [] + go i xxs@(x:xs) + | i < x = False : go (i + 1) xxs + | otherwise = True : go (i + 1) xs + +bitMapToAddrLiteral :: + -- | Values to encode + [Bool] -> + -- | String to append + BB.Builder -> + BB.Builder +bitMapToAddrLiteral bs cs = foldr encode cs (unfoldr mkChunks bs) + + where + + mkChunks :: [a] -> Maybe ([a], [a]) + mkChunks [] = Nothing + mkChunks xs = Just $ splitAt 8 xs + + encode :: [Bool] -> BB.Builder -> BB.Builder + encode chunk acc = BB.char7 '\\' <> BB.intDec (toByte (padTo8 chunk)) <> acc + + padTo8 :: [Bool] -> [Bool] + padTo8 xs + | length xs >= 8 = xs + | otherwise = xs <> replicate (8 - length xs) False + + toByte :: [Bool] -> Int + toByte xs = sum $ map (\i -> if xs !! i then 1 `shiftL` i else 0) [0..7] + +genEnumBitmap :: + forall a. (Bounded a, Enum a, Show a) => + -- | Function name + BB.Builder -> + -- | Default value + a -> + -- | List of values to encode + [a] -> + BB.Builder +genEnumBitmap funcName def as = unlinesBB + [ "{-# INLINE " <> funcName <> " #-}" + , funcName <> " :: Char -> Int" + , funcName <> " c = let n = ord c in if n >= " + <> BB.intDec (length as) + <> " then " + <> BB.intDec (fromEnum def) + <> " else lookup_bitmap n" + + , "{-# NOINLINE lookup_bitmap #-}" + , "lookup_bitmap :: Int -> Int" + , "lookup_bitmap n = lookupIntN bitmap# n" + , " where" + , " bitmap# = \"" <> enumMapToAddrLiteral as "\"#" + ] + +{-| Encode a list of values as a byte map, using their 'Enum' instance. + +__Note:__ 'Enum' instance must respect the following: + +* @fromEnum minBound >= 0x00@ +* @fromEnum maxBound <= 0xff@ +-} +enumMapToAddrLiteral :: + forall a. (Bounded a, Enum a, Show a) => + -- | Values to encode + [a] -> + -- | String to append + BB.Builder -> + BB.Builder +enumMapToAddrLiteral xs cs = foldr go cs xs + + where + + go :: a -> BB.Builder -> BB.Builder + go x acc = BB.char7 '\\' <> BB.word8Dec (toWord8 x) <> acc + + toWord8 :: a -> Word8 + toWord8 a = let w = fromEnum a in if 0 <= w && w <= 0xff + then fromIntegral w + else error $ "Cannot convert to Word8: " <> show a + +genUnicodeVersion :: FilePath -> IO () +genUnicodeVersion outdir = do + version <- catch + (getEnv "UNICODE_VERSION") + (\(_ :: IOException) -> return "") + runFold f [body version] + where + moduleName :: (IsString a) => a + moduleName = "GHC.Internal.Unicode.Version" + f = moduleFileEmitter Nothing outdir + (moduleName, \_ -> Fold (\_ x -> x) mempty id) + body :: String -> BB.Builder + body version = unlinesBB + [ "{-# LANGUAGE NoImplicitPrelude #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(unicodeVersion)" + , "where" + , "" + , "import {-# SOURCE #-} GHC.Internal.Data.Version" + , "" + , "-- | Version of Unicode standard used by @base@:" + , "-- [" <> BB.string7 version <> "](https://www.unicode.org/versions/Unicode" <> BB.string7 version <> "/)." + , "--" + , "-- @since base-4.15.0.0" + , "unicodeVersion :: Version" + , "unicodeVersion = makeVersion [" <> mkVersion version <> "]" ] + mkVersion = foldMap (\c -> case c of {'.' -> BB.char7 ',' <> BB.char7 ' '; _ -> BB.char7 c}) + +-------------------------------------------------------------------------------- +-- Fold +-------------------------------------------------------------------------------- + +data Fold a b = forall s. Fold + { _step :: s -> a -> s + , _initial :: s + , _final :: s -> b } + +data Pair a b = Pair !a !b + +teeWith :: (a -> b -> c) -> Fold x a -> Fold x b -> Fold x c +teeWith f (Fold stepL initialL finalL) (Fold stepR initialR finalR) = + Fold step initial final + where + step (Pair sL sR) x = Pair (stepL sL x) (stepR sR x) + initial = Pair initialL initialR + final (Pair sL sR) = f (finalL sL) (finalR sR) + +distribute :: [Fold a b] -> Fold a [b] +distribute = foldr (teeWith (:)) (Fold const () (const [])) + +rmapFold :: (b -> c) -> Fold a b -> Fold a c +rmapFold f (Fold step initial final) = Fold step initial (f . final) + +runFold :: Fold a b -> [a] -> b +runFold (Fold step initial final) = final . foldl' step initial + +-------------------------------------------------------------------------------- +-- Modules generators +-------------------------------------------------------------------------------- + +data GeneralCategoryAcc = GeneralCategoryAcc + { _categories :: ![UD.GeneralCategory] + , _expectedChar :: !Char + } + +genGeneralCategoryModule :: BB.Builder -> Fold UD.Entry BB.Builder +genGeneralCategoryModule moduleName = Fold step initial done + + where + + -- (categories, expected char) + initial = GeneralCategoryAcc [] '\0' + + step (GeneralCategoryAcc acc p) e@(UD.Entry r d) + | p < r.start + -- Fill missing char entry with default category Cn + -- See: https://www.unicode.org/reports/tr44/#Default_Values_Table + = step (GeneralCategoryAcc (replicate (ord r.start - ord p) UD.Cn <> acc) r.start) e + -- Regular entry + | otherwise = case r of + C.SingleChar ch -> GeneralCategoryAcc + (d.generalCategory : acc) + (succ ch) + C.CharRange ch1 ch2 -> GeneralCategoryAcc + (replicate (ord ch2 - ord ch1 + 1) d.generalCategory <> acc) + (succ ch2) + + done (GeneralCategoryAcc acc _) = unlinesBB + [ "{-# LANGUAGE NoImplicitPrelude #-}" + , "{-# LANGUAGE MagicHash #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(generalCategory)" + , "where" + , "" + , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" + , "import GHC.Internal.Unicode.Bits (lookupIntN)" + , "" + , genEnumBitmap "generalCategory" UD.Cn (reverse acc) + ] + +genSimpleCaseMappingModule + :: BB.Builder + -> BB.Builder + -> (UD.CharDetails -> Maybe Char) + -> Fold UD.Entry BB.Builder +genSimpleCaseMappingModule moduleName funcName field = + Fold step initial done + + where + + genHeader = + [ "{-# LANGUAGE NoImplicitPrelude, LambdaCase #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(" <> funcName <> ")" + , "where" + , "" + , "import GHC.Internal.Base (Char)" + , "" + ] + genSign = + [ "{-# NOINLINE " <> funcName <> " #-}" + , funcName <> " :: Char -> Char" + , funcName <> " = \\case" + ] + initial = [] + + step ds dc = case mkEntry dc of + Nothing -> ds + Just d -> d : ds + + after = [" c -> c"] + + done st = + let body = mconcat [genHeader, genSign, reverse st, after] + in unlinesBB body + + mkEntry (UD.Entry r dc) = case r of + C.SingleChar ch -> field dc <&> \c -> mconcat + [ " '\\x" + , showHexChar ch + , "' -> '\\x" + , showHexChar c + , "'" + ] + C.CharRange{} -> field dc $> error ("genSimpleCaseMappingModule: unexpected char range: " <> show r) + + showHexChar c = BB.wordHex (fromIntegral (ord c)) + +data PropertiesAcc = PropertiesAcc + { _properties :: ![BS.ShortByteString] + , _bitmaps :: ![BB.Builder] + , _currentBitmap :: ![[Int]] } + +genCorePropertiesModule :: + BB.Builder -> (BS.ShortByteString -> Bool) -> Fold P.Entry BB.Builder +genCorePropertiesModule moduleName isProp = Fold step initial done + where + prop2FuncName x = "is" <> BB.shortByteString x + + initial = PropertiesAcc [] [] [] + + step acc@(PropertiesAcc props bitmaps bits) P.Entry{..} + | not (isProp property) = acc -- property filtered out + | otherwise = case props of + prop' : _ + | prop' == property -> PropertiesAcc props bitmaps (rangeToBits range : bits) + | otherwise -> PropertiesAcc + { _properties = property : props + , _bitmaps = genBitmap' prop' bits : bitmaps + , _currentBitmap = [rangeToBits range] } + _ -> PropertiesAcc [property] bitmaps [rangeToBits range] + + rangeToBits = \case + C.SingleChar ch -> [ord ch] + C.CharRange ch1 ch2 -> [ord ch1 .. ord ch2] + + genBitmap' prop bits = genBitmap (prop2FuncName prop) (mconcat (reverse bits)) + + done (PropertiesAcc props bitmaps bits) = unlinesBB (header props <> bitmaps') + where + lastProp = case props of + prop : _ -> prop + [] -> error "impossible" + bitmaps' = genBitmap' lastProp bits : bitmaps + + header exports = + [ "{-# LANGUAGE NoImplicitPrelude #-}" + , "{-# LANGUAGE MagicHash #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(" <> unwordsBB (intersperse "," (map prop2FuncName exports)) <> ")" + , "where" + , "" + , "import GHC.Internal.Base (Bool, Char, Ord(..), (&&), ord)" + , "import GHC.Internal.Unicode.Bits (lookupBit64)" + , "" + ] + +-------------------------------------------------------------------------------- +-- Generation +-------------------------------------------------------------------------------- + +moduleToFileName :: String -> String +moduleToFileName = map (\x -> if x == '.' then '/' else x) + +dirFromFileName :: String -> String +dirFromFileName = reverse . dropWhile (/= '/') . reverse + +data FileRecipe a + = ModuleRecipe + -- ^ A recipe to create a Haskell module file. + String + -- ^ Module name + (BB.Builder -> Fold a BB.Builder) + -- ^ Function that generate the module, given the module name. + | TestOutputRecipe + -- ^ A recipe to create a test output file. + String + -- ^ Test name + (Fold a BB.Builder) + -- ^ Test output generator + +-- ModuleRecipe is a tuple of the module name and a function that generates the +-- module using the module name +type ModuleRecipe a = (String, BB.Builder -> Fold a BB.Builder) +type TestOutputRecipe a = (FilePath, Fold a BB.Builder) + +-- GeneratorRecipe is a list of ModuleRecipe +type GeneratorRecipe a = [FileRecipe a] + +moduleFileEmitter :: Maybe FilePath -> FilePath -> ModuleRecipe a -> Fold a (IO ()) +moduleFileEmitter mfile outdir (modName, fldGen) = rmapFold action $ fldGen (BB.string7 modName) + + where + + pretext version = case mfile of + Just file -> mconcat + [ "-- DO NOT EDIT: This file is automatically generated by the internal tool ucd2haskell,\n" + , "-- with data from: https://www.unicode.org/Public/" + , BB.string7 version + , "/ucd/" + , BB.string7 file + ,".\n\n" + ] + Nothing -> "-- DO NOT EDIT: This file is automatically generated by the internal tool ucd2haskell.\n\n" + outfile = outdir moduleToFileName modName <.> ".hs" + outfiledir = dirFromFileName outfile + action c = do + version <- + catch + (getEnv "UNICODE_VERSION") + (\(_ :: IOException) -> return "") + createDirectoryIfMissing True outfiledir + B.writeFile outfile (BL.toStrict (BB.toLazyByteString (pretext version <> c))) + +testOutputFileEmitter :: FilePath -> TestOutputRecipe a -> Fold a (IO ()) +testOutputFileEmitter outdir (name, fldGen) = rmapFold action fldGen + + where + + outfile = outdir "tests" name <.> ".stdout" + outfiledir = dirFromFileName outfile + action c + = createDirectoryIfMissing True outfiledir + *> B.writeFile outfile (BL.toStrict (BB.toLazyByteString c)) + +runGenerator :: + FilePath + -> FilePath + -> (B.ByteString -> [a]) + -> FilePath + -> GeneratorRecipe a + -> IO () +runGenerator indir file transformLines outdir recipes = do + raw <- B.readFile (indir <> file) + sequence_ (runFold combinedFld (transformLines raw)) + + where + + generatedFolds = recipes <&> \case + ModuleRecipe name f -> moduleFileEmitter (Just file) outdir (name, f) + TestOutputRecipe name f -> testOutputFileEmitter outdir (name, f) + combinedFld = distribute generatedFolds + +genModules :: FilePath -> FilePath -> [BS.ShortByteString] -> IO () +genModules indir outdir props = do + genUnicodeVersion outdir + + runGenerator + indir + "UnicodeData.txt" + UD.parse + outdir + [ generalCategory + , simpleUpperCaseMapping + , simpleLowerCaseMapping + , simpleTitleCaseMapping + ] + + runGenerator + indir + "DerivedCoreProperties.txt" + P.parse + outdir + [ derivedCoreProperties ] + + where + + derivedCoreProperties = ModuleRecipe + "GHC.Internal.Unicode.Char.DerivedCoreProperties" + (`genCorePropertiesModule` (`elem` props)) + + generalCategory = ModuleRecipe + "GHC.Internal.Unicode.Char.UnicodeData.GeneralCategory" + genGeneralCategoryModule + + simpleUpperCaseMapping = ModuleRecipe + "GHC.Internal.Unicode.Char.UnicodeData.SimpleUpperCaseMapping" + (\m -> genSimpleCaseMappingModule m "toSimpleUpperCase" UD.simpleUpperCaseMapping) + + simpleLowerCaseMapping = ModuleRecipe + "GHC.Internal.Unicode.Char.UnicodeData.SimpleLowerCaseMapping" + (\m -> genSimpleCaseMappingModule m "toSimpleLowerCase" UD.simpleLowerCaseMapping) + + simpleTitleCaseMapping = ModuleRecipe + "GHC.Internal.Unicode.Char.UnicodeData.SimpleTitleCaseMapping" + (\m -> genSimpleCaseMappingModule m "toSimpleTitleCase" UD.simpleTitleCaseMapping) ===================================== libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal ===================================== @@ -1,6 +1,6 @@ cabal-version: 2.2 name: ucd2haskell -version: 0.3.0 +version: 0.4.0 synopsis: Converter from Unicode character database to Haskell. description: The Haskell data structures are generated programmatically from the @@ -10,12 +10,12 @@ description: license: BSD-3-Clause license-file: LICENSE author: Composewell Technologies and Contributors -maintainer: streamly at composewell.com -copyright: 2020 Composewell Technologies and Contributors +maintainer: The GHC Developers +bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new category: Data,Text,Unicode stability: Experimental build-type: Simple -tested-with: GHC==9.2.2 +tested-with: GHC==9.8.2 extra-source-files: README.md @@ -23,18 +23,14 @@ extra-source-files: common default-extensions default-extensions: - BangPatterns DeriveGeneric - MagicHash - RecordWildCards - ScopedTypeVariables - TupleSections - FlexibleContexts - - -- Experimental, may lead to issues DeriveAnyClass - TemplateHaskell - UnboxedTuples + ExistentialQuantification + LambdaCase + OverloadedStrings + OverloadedRecordDot + ScopedTypeVariables + RecordWildCards common compile-options ghc-options: -Wall @@ -42,21 +38,20 @@ common compile-options -fwarn-incomplete-record-updates -fwarn-incomplete-uni-patterns -fwarn-tabs - default-language: Haskell2010 + default-language: GHC2021 executable ucd2haskell import: default-extensions, compile-options - default-language: Haskell2010 ghc-options: -O2 hs-source-dirs: exe main-is: UCD2Haskell.hs - other-modules: Parser.Text + other-modules: UCD2Haskell.ModuleGenerators build-depends: - base >= 4.7 && < 4.20 - , streamly-core >= 0.2.2 && < 0.3 - , streamly >= 0.10 && < 0.11 - , split >= 0.2.3 && < 0.3 - , getopt-generics >= 0.13 && < 0.14 - , containers >= 0.5 && < 0.7 - , directory >= 1.3.6 && < 1.3.8 - , filepath >= 1.4.2 && < 1.5 + base >= 4.7 && < 5 + , bytestring >= 0.11 && < 0.13 + , containers >= 0.5 && < 0.7 + , directory >= 1.3.6 && < 1.3.8 + , filepath >= 1.4.2 && < 1.5 + , getopt-generics >= 0.13 && < 0.14 + , split >= 0.2.3 && < 0.3 + , unicode-data-parser >= 0.2.0 && < 0.4 ===================================== utils/haddock/CONTRIBUTING.md ===================================== @@ -28,6 +28,17 @@ Then, run the following command from the top-level: $ ./hadrian/build -j --flavour=Quick --freeze1 _build/stage1/bin/haddock ``` +### Running the test suites + +Currently, this cannot be done with hadrian but has to be done with a +`cabal-install` built from `master`. + +``` +cabal test -w /_build/stage1/bin/ghc +``` + +For more details, see https://gitlab.haskell.org/ghc/ghc/-/issues/24976. + ## Working with the codebase The project provides a Makefile with rules to accompany you during development: ===================================== utils/haddock/cabal.project ===================================== @@ -1,5 +1,3 @@ -with-compiler: ghc-9.7 - packages: ./ ./haddock-api ./haddock-library View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/80e1935ae702345b011fb3eac43a699dadd91338...565f6192ef575d484f0448b715f09c7c83eda45e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/80e1935ae702345b011fb3eac43a699dadd91338...565f6192ef575d484f0448b715f09c7c83eda45e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 15:48:18 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 13 Jun 2024 11:48:18 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] fix X86 takeRegRegMove Message-ID: <666b14c2da2c1_3a1a3825f3dc41395@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 6ca1b8e0 by sheaf at 2024-06-13T17:48:07+02:00 fix X86 takeRegRegMove - - - - - 12 changed files: - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/AArch64.hs - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/PPC.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Coalesce.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/Stats.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/X86/Instr.hs Changes: ===================================== compiler/GHC/CmmToAsm.hs ===================================== @@ -240,6 +240,7 @@ finishNativeGen logger config modLoc bufh us ngs -- dump global NCG stats for graph coloring allocator let stats = concat (ngs_colorStats ngs) + platform = ncgPlatform config unless (null stats) $ do -- build the global register conflict graph @@ -250,7 +251,7 @@ finishNativeGen logger config modLoc bufh us ngs dump_stats (Color.pprStats stats graphGlobal) - let platform = ncgPlatform config + putDumpFileMaybe logger Opt_D_dump_asm_conflicts "Register conflict graph" FormatText @@ -265,7 +266,7 @@ finishNativeGen logger config modLoc bufh us ngs -- dump global NCG stats for linear allocator let linearStats = concat (ngs_linearStats ngs) unless (null linearStats) $ - dump_stats (Linear.pprStats (concat (ngs_natives ngs)) linearStats) + dump_stats (Linear.pprStats platform (concat (ngs_natives ngs)) linearStats) -- write out the imports let ctx = ncgAsmContext config ===================================== compiler/GHC/CmmToAsm/AArch64.hs ===================================== @@ -54,7 +54,7 @@ instance Instruction AArch64.Instr where takeDeltaInstr = AArch64.takeDeltaInstr isMetaInstr = AArch64.isMetaInstr mkRegRegMoveInstr _ = AArch64.mkRegRegMoveInstr - takeRegRegMoveInstr = AArch64.takeRegRegMoveInstr + takeRegRegMoveInstr _ = AArch64.takeRegRegMoveInstr mkJumpInstr = AArch64.mkJumpInstr mkStackAllocInstr = AArch64.mkStackAllocInstr mkStackDeallocInstr = AArch64.mkStackDeallocInstr ===================================== compiler/GHC/CmmToAsm/Instr.hs ===================================== @@ -142,7 +142,8 @@ class Instruction instr where -- | Take the source and destination from this reg -> reg move instruction -- or Nothing if it's not one takeRegRegMoveInstr - :: instr + :: Platform + -> instr -> Maybe (Reg, Reg) -- | Make an unconditional jump instruction. ===================================== compiler/GHC/CmmToAsm/PPC.hs ===================================== @@ -53,7 +53,7 @@ instance Instruction PPC.Instr where takeDeltaInstr = PPC.takeDeltaInstr isMetaInstr = PPC.isMetaInstr mkRegRegMoveInstr _ = PPC.mkRegRegMoveInstr - takeRegRegMoveInstr = PPC.takeRegRegMoveInstr + takeRegRegMoveInstr _ = PPC.takeRegRegMoveInstr mkJumpInstr = PPC.mkJumpInstr mkStackAllocInstr = PPC.mkStackAllocInstr mkStackDeallocInstr = PPC.mkStackDeallocInstr ===================================== compiler/GHC/CmmToAsm/Reg/Graph.hs ===================================== @@ -140,7 +140,7 @@ regAlloc_spin config spinCount triv regsFree slotsFree slotsCount debug_codeGrap -- Build the register conflict graph from the cmm code. (graph :: Color.Graph VirtualReg RegClass RealReg) - <- {-# SCC "BuildGraph" #-} buildGraph code + <- {-# SCC "BuildGraph" #-} buildGraph platform code -- VERY IMPORTANT: -- We really do want the graph to be fully evaluated _before_ we @@ -188,7 +188,7 @@ regAlloc_spin config spinCount triv regsFree slotsFree slotsCount debug_codeGrap = reg let (code_coalesced :: [LiveCmmDecl statics instr]) - = map (patchEraseLive patchF) code + = map (patchEraseLive platform patchF) code -- Check whether we've found a coloring. if isEmptyUniqSet rsSpill @@ -234,7 +234,7 @@ regAlloc_spin config spinCount triv regsFree slotsFree slotsCount debug_codeGrap , raSpillClean = code_spillclean , raFinal = code_final , raSRMs = foldl' addSRM (0, 0, 0) - $ map countSRMs code_spillclean + $ map (countSRMs platform) code_spillclean , raPlatform = platform } @@ -304,14 +304,15 @@ regAlloc_spin config spinCount triv regsFree slotsFree slotsCount debug_codeGrap -- | Build a graph from the liveness and coalesce information in this code. buildGraph :: Instruction instr - => [LiveCmmDecl statics instr] + => Platform + -> [LiveCmmDecl statics instr] -> UniqSM (Color.Graph VirtualReg RegClass RealReg) -buildGraph code +buildGraph platform code = do -- Slurp out the conflicts and reg->reg moves from this code. let (conflictList, moveList) = - unzip $ map slurpConflicts code + unzip $ map (slurpConflicts platform) code -- Slurp out the spill/reload coalesces. let moveList2 = map slurpReloadCoalesce code @@ -393,7 +394,7 @@ patchRegsFromGraph -> LiveCmmDecl statics instr -> LiveCmmDecl statics instr patchRegsFromGraph platform graph code - = patchEraseLive patchF code + = patchEraseLive platform patchF code where -- Function to lookup the hardreg for a virtual reg from the graph. patchF reg ===================================== compiler/GHC/CmmToAsm/Reg/Graph/Coalesce.hs ===================================== @@ -14,6 +14,7 @@ import GHC.Data.Bag import GHC.Data.Graph.Directed import GHC.Types.Unique.FM import GHC.Types.Unique.Supply +import GHC.Platform (Platform) -- | Do register coalescing on this top level thing @@ -24,18 +25,19 @@ import GHC.Types.Unique.Supply -- safely erased. regCoalesce :: Instruction instr - => [LiveCmmDecl statics instr] + => Platform + -> [LiveCmmDecl statics instr] -> UniqSM [LiveCmmDecl statics instr] -regCoalesce code +regCoalesce platform code = do let joins = foldl' unionBags emptyBag - $ map slurpJoinMovs code + $ map (slurpJoinMovs platform) code let alloc = foldl' buildAlloc emptyUFM $ bagToList joins - let patched = map (patchEraseLive (sinkReg alloc)) code + let patched = map (patchEraseLive platform (sinkReg alloc)) code return patched @@ -66,10 +68,11 @@ sinkReg fm r -- eliminate the move. slurpJoinMovs :: Instruction instr - => LiveCmmDecl statics instr + => Platform + -> LiveCmmDecl statics instr -> Bag (Reg, Reg) -slurpJoinMovs live +slurpJoinMovs platform live = slurpCmm emptyBag live where slurpCmm rs CmmData{} @@ -83,7 +86,7 @@ slurpJoinMovs live slurpLI rs (LiveInstr _ Nothing) = rs slurpLI rs (LiveInstr instr (Just live)) - | Just (r1, r2) <- takeRegRegMoveInstr instr + | Just (r1, r2) <- takeRegRegMoveInstr platform instr , elemUFM r1 $ liveDieRead live , elemUFM r2 $ liveBorn live ===================================== compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs ===================================== @@ -171,7 +171,7 @@ cleanForward platform blockId assoc acc (li1 : li2 : instrs) -- SIMD NCG TODO: is this "fmt" correct? cleanForward platform blockId assoc acc (li@(LiveInstr i1 _) : instrs) - | Just (r1, r2) <- takeRegRegMoveInstr i1 + | Just (r1, r2) <- takeRegRegMoveInstr platform i1 = if r1 == r2 -- Erase any left over nop reg reg moves while we're here -- this will also catch any nop moves that the previous case ===================================== compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs ===================================== @@ -312,27 +312,29 @@ pprStatsLifeConflict stats graph -- Lets us see how well the register allocator has done. countSRMs :: Instruction instr - => LiveCmmDecl statics instr -> (Int, Int, Int) + => Platform + -> LiveCmmDecl statics instr -> (Int, Int, Int) -countSRMs cmm - = execState (mapBlockTopM countSRM_block cmm) (0, 0, 0) +countSRMs platform cmm + = execState (mapBlockTopM (countSRM_block platform) cmm) (0, 0, 0) countSRM_block :: Instruction instr - => GenBasicBlock (LiveInstr instr) + => Platform + -> GenBasicBlock (LiveInstr instr) -> State (Int, Int, Int) (GenBasicBlock (LiveInstr instr)) -countSRM_block (BasicBlock i instrs) - = do instrs' <- mapM countSRM_instr instrs +countSRM_block platform (BasicBlock i instrs) + = do instrs' <- mapM (countSRM_instr platform) instrs return $ BasicBlock i instrs' countSRM_instr :: Instruction instr - => LiveInstr instr -> State (Int, Int, Int) (LiveInstr instr) + => Platform -> LiveInstr instr -> State (Int, Int, Int) (LiveInstr instr) -countSRM_instr li +countSRM_instr platform li | LiveInstr SPILL{} _ <- li = do modify $ \(s, r, m) -> (s + 1, r, m) return li @@ -342,7 +344,7 @@ countSRM_instr li return li | LiveInstr instr _ <- li - , Just _ <- takeRegRegMoveInstr instr + , Just _ <- takeRegRegMoveInstr platform instr = do modify $ \(s, r, m) -> (s, r, m + 1) return li ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -422,6 +422,7 @@ raInsn _ new_instrs _ (LiveInstr ii@(Instr i) Nothing) raInsn block_live new_instrs id (LiveInstr (Instr instr) (Just live)) = do + platform <- getPlatform assig <- getAssigR :: RegM freeRegs (UniqFM Reg Loc) -- If we have a reg->reg move between virtual registers, where the @@ -431,7 +432,7 @@ raInsn block_live new_instrs id (LiveInstr (Instr instr) (Just live)) -- then we can eliminate the instruction. -- (we can't eliminate it if the source register is on the stack, because -- we do not want to use one spill slot for different virtual registers) - case takeRegRegMoveInstr instr of + case takeRegRegMoveInstr platform instr of Just (src,dst) | Just (_, fmt) <- lookupUFM (liveDieRead live) src, isVirtualReg dst, not (dst `elemUFM` assig), @@ -585,7 +586,7 @@ genRaInsn block_live new_instrs block_id instr r_dying w_dying = do -- erase reg->reg moves where the source and destination are the same. -- If the src temp didn't die in this instr but happened to be allocated -- to the same real reg as the destination, then we can erase the move anyway. - let squashed_instr = case takeRegRegMoveInstr patched_instr of + let squashed_instr = case takeRegRegMoveInstr platform patched_instr of Just (src, dst) | src == dst -> [] _ -> [patched_instr] ===================================== compiler/GHC/CmmToAsm/Reg/Linear/Stats.hs ===================================== @@ -18,6 +18,7 @@ import GHC.Types.Unique.FM import GHC.Utils.Outputable import GHC.Utils.Monad.State.Strict +import GHC.Platform (Platform) -- | Build a map of how many times each reg was alloced, clobbered, loaded etc. binSpillReasons @@ -38,9 +39,10 @@ binSpillReasons reasons -- | Count reg-reg moves remaining in this code. countRegRegMovesNat :: Instruction instr - => NatCmmDecl statics instr -> Int + => Platform + -> NatCmmDecl statics instr -> Int -countRegRegMovesNat cmm +countRegRegMovesNat platform cmm = execState (mapGenBlockTopM countBlock cmm) 0 where countBlock b@(BasicBlock _ instrs) @@ -48,7 +50,7 @@ countRegRegMovesNat cmm return b countInstr instr - | Just _ <- takeRegRegMoveInstr instr + | Just _ <- takeRegRegMoveInstr platform instr = do modify (+ 1) return instr @@ -59,9 +61,9 @@ countRegRegMovesNat cmm -- | Pretty print some RegAllocStats pprStats :: Instruction instr - => [NatCmmDecl statics instr] -> [RegAllocStats] -> SDoc + => Platform -> [NatCmmDecl statics instr] -> [RegAllocStats] -> SDoc -pprStats code statss +pprStats platform code statss = let -- sum up all the instrs inserted by the spiller -- See Note [UniqFM and the register allocator] spills :: UniqFM Unique [Int] @@ -75,7 +77,7 @@ pprStats code statss -- See Note [Unique Determinism and code generation] -- count how many reg-reg-moves remain in the code - moves = sum $ map countRegRegMovesNat code + moves = sum $ map (countRegRegMovesNat platform) code pprSpill (reg, spills) = parens $ (hcat $ punctuate (text ", ") (doubleQuotes (ppr reg) : map ppr spills)) ===================================== compiler/GHC/CmmToAsm/Reg/Liveness.hs ===================================== @@ -156,9 +156,9 @@ instance Instruction instr => Instruction (InstrSR instr) where mkRegRegMoveInstr platform fmt r1 r2 = Instr (mkRegRegMoveInstr platform fmt r1 r2) - takeRegRegMoveInstr i + takeRegRegMoveInstr platform i = case i of - Instr instr -> takeRegRegMoveInstr instr + Instr instr -> takeRegRegMoveInstr platform instr _ -> Nothing mkJumpInstr target = map Instr (mkJumpInstr target) @@ -327,10 +327,11 @@ mapGenBlockTopM f (CmmProc header label live (ListGraph blocks)) -- slurpConflicts :: Instruction instr - => LiveCmmDecl statics instr + => Platform + -> LiveCmmDecl statics instr -> (Bag (UniqFM Reg (Reg, Format)), Bag (Reg, Reg)) -slurpConflicts live +slurpConflicts platform live = slurpCmm (emptyBag, emptyBag) live where slurpCmm rs CmmData{} = rs @@ -380,7 +381,7 @@ slurpConflicts live -- rsConflicts = plusUFM rsLiveNext rsOrphans - in case takeRegRegMoveInstr instr of + in case takeRegRegMoveInstr platform instr of Just rr -> slurpLIs rsLiveNext ( consBag rsConflicts conflicts , consBag rr moves) lis @@ -609,10 +610,11 @@ eraseDeltasLive cmm -- also erase reg -> reg moves when the destination dies in this instr. patchEraseLive :: Instruction instr - => (Reg -> Reg) + => Platform + -> (Reg -> Reg) -> LiveCmmDecl statics instr -> LiveCmmDecl statics instr -patchEraseLive patchF cmm +patchEraseLive platform patchF cmm = patchCmm cmm where patchCmm cmm at CmmData{} = cmm @@ -636,7 +638,7 @@ patchEraseLive patchF cmm patchInstrs (li : lis) | LiveInstr i (Just live) <- li' - , Just (r1, r2) <- takeRegRegMoveInstr i + , Just (r1, r2) <- takeRegRegMoveInstr platform i , eatMe r1 r2 live = patchInstrs lis ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -67,6 +67,7 @@ import GHC.Types.Basic (Alignment) import GHC.Cmm.DebugBlock (UnwindTable) import Data.Maybe (fromMaybe) +import GHC.CmmToAsm.Reg.Target (targetClassOfReg) -- Format of an x86/x86_64 memory address, in bytes. -- @@ -976,29 +977,33 @@ mkRegRegMoveInstr _platform fmt src dst -- by assigning the src and dest temporaries to the same real register. -- takeRegRegMoveInstr - :: Instr + :: Platform + -> Instr -> Maybe (Reg,Reg) -takeRegRegMoveInstr (MOV fmt (OpReg r1) (OpReg r2)) +takeRegRegMoveInstr platform (MOV fmt (OpReg r1) (OpReg r2)) -- MOV zeroes the upper part of vector registers, -- so it is not a real "move" in that case. | not (isVecFormat fmt) + -- Don't eliminate a move between e.g. RAX and XMM, + -- even though we might be using XMM to store a scalar integer value. + , targetClassOfReg platform r1 == targetClassOfReg platform r2 = Just (r1,r2) -takeRegRegMoveInstr (MOVSD fmt (OpReg r1) (OpReg r2)) +takeRegRegMoveInstr _ (MOVSD fmt (OpReg r1) (OpReg r2)) | not (isVecFormat fmt) = Just (r1,r2) -takeRegRegMoveInstr (MOVA _ (OpReg r1) (OpReg r2)) +takeRegRegMoveInstr _ (MOVA _ (OpReg r1) (OpReg r2)) = Just (r1, r2) -takeRegRegMoveInstr (MOVU _ (OpReg r1) (OpReg r2)) +takeRegRegMoveInstr _ (MOVU _ (OpReg r1) (OpReg r2)) = Just (r1, r2) -takeRegRegMoveInstr (VMOVU _ (OpReg r1) (OpReg r2)) +takeRegRegMoveInstr _ (VMOVU _ (OpReg r1) (OpReg r2)) = Just (r1, r2) -takeRegRegMoveInstr (MOVDQU _ (OpReg r1) (OpReg r2)) +takeRegRegMoveInstr _ (MOVDQU _ (OpReg r1) (OpReg r2)) = Just (r1, r2) -takeRegRegMoveInstr (VMOVDQU _ (OpReg r1) (OpReg r2)) +takeRegRegMoveInstr _ (VMOVDQU _ (OpReg r1) (OpReg r2)) = Just (r1, r2) -takeRegRegMoveInstr _ = Nothing +takeRegRegMoveInstr _ _ = Nothing -- | Make an unconditional branch instruction. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ca1b8e083cee1fff5e9516bbd15f39c83de3344 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6ca1b8e083cee1fff5e9516bbd15f39c83de3344 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 15:57:53 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 13 Jun 2024 11:57:53 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/romes/bswap Message-ID: <666b170174f02_3a1a3846498448541@gitlab.mail> Rodrigo Mesquita pushed new branch wip/romes/bswap at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/bswap You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 17:08:47 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Thu, 13 Jun 2024 13:08:47 -0400 Subject: [Git][ghc/ghc][wip/T14030] Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) Message-ID: <666b279f97940_3a1a38cfc58871766@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: cf983566 by Sebastian Graf at 2024-06-13T19:08:33+02:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. - - - - - 6 changed files: - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - testsuite/tests/ghci/scripts/T21110.stderr - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/th/TH_Lift.hs Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs ===================================== @@ -42,7 +42,7 @@ module GHC.Internal.TH.Lift where import GHC.Internal.TH.Syntax -import GHC.Internal.TH.Lib () -- See wrinkle (W4) of Note [Tracking dependencies on primitives] +import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives] import GHC.Internal.Lexeme ( startsVarSym, startsVarId ) import GHC.Internal.Data.Either @@ -54,7 +54,7 @@ import GHC.Internal.Integer import GHC.Internal.Real import GHC.Internal.Word import GHC.Internal.Int -import GHC.Internal.Data.Data +import GHC.Internal.Data.Data hiding (Fixity) import GHC.Internal.Natural -- | A 'Lift' instance can have any of its values turned into a Template @@ -305,6 +305,135 @@ rightName = 'Right nonemptyName :: Name nonemptyName = '(:|) +----------------------------------------------------- +-- +-- Lifting the TH AST +-- +----------------------------------------------------- + +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Loc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DocLoc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ModName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift GHC.Internal.TH.Syntax.Module +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameSpace +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NamespaceSpecifier +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PkgName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameFlavour +-- | @since template-haskell-2.22.1.0 +deriving instance Lift OccName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Name +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameIs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Specificity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift BndrVis +-- | @since template-haskell-2.22.1.0 +deriving instance Lift a => Lift (TyVarBndr a) +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TyLit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Type +-- | @since template-haskell-2.22.1.0 +instance Lift Bytes where + lift = Lib.litE . BytesPrimL + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Lit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pat +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Clause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivClause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivStrategy +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Overlap +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FunDep +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Safety +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Callconv +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Foreign +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ForeignSrcLang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FixityDirection +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Fixity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Inline +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleMatch +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Phases +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleBndr +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnTarget +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pragma +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceUnpackedness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DecidedStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Bang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Con +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TySynEqn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FamilyResultSig +-- | @since template-haskell-2.22.1.0 +deriving instance Lift InjectivityAnn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TypeFamilyHead +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Role +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynArgs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynDir +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Dec +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Range +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Exp +-- | @since template-haskell-2.22.1.0 +instance Lift (TExp a) where + lift (TExp e) = [| TExp $(lift e) |] + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Match +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Guard +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Stmt +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Body +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Info +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnLookup +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Extension + ----------------------------------------------------- -- -- Generic Lift implementations ===================================== libraries/template-haskell/changelog.md ===================================== @@ -1,5 +1,9 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) +## 2.22.1.0 + + * `Lift` instances were added for the `template-haskell` AST. + ## 2.22.0.0 * The kind of `Code` was changed from `forall r. (Type -> Type) -> TYPE r -> Type` ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -3,7 +3,7 @@ -- template-haskell.cabal. name: template-haskell -version: 2.22.0.0 +version: 2.22.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE ===================================== testsuite/tests/ghci/scripts/T21110.stderr ===================================== @@ -1,5 +1,5 @@ - : warning: [GHC-42258] [-Wunused-packages] The following packages were specified via -package or -package-id flags, but were not needed for compilation: - - template-haskell-2.22.0.0 (exposed by flag -package template-haskell) + - template-haskell-2.22.1.0 (exposed by flag -package template-haskell) + ===================================== testsuite/tests/interface-stability/template-haskell-exports.stdout ===================================== @@ -2420,11 +2420,37 @@ instance GHC.Internal.Show.Show GHC.Internal.LanguageExtensions.Extension -- Def instance GHC.Internal.Show.Show GHC.Internal.TH.Ppr.ForallVisFlag -- Defined in ‘GHC.Internal.TH.Ppr’ instance [safe] GHC.Internal.Show.Show GHC.Internal.TH.PprLib.Doc -- Defined in ‘GHC.Internal.TH.PprLib’ instance GHC.Internal.Show.Show GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.ForeignSrcLang’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnLookup -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnTarget -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.BndrVis -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Body -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Bool -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bytes -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Callconv -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Char -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Clause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Con -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Dec -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DecidedStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivClause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivStrategy -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DocLoc -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Double -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (GHC.Internal.Data.Either.Either a b) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Exp -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.LanguageExtensions.Extension -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FamilyResultSig -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Fixity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FixityDirection -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Float -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Foreign -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FunDep -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Guard -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Info -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.InjectivityAnn -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Inline -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Int -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int16 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int32 -- Defined in ‘GHC.Internal.TH.Lift’ @@ -2432,16 +2458,49 @@ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int64 -- Defined in ‘GHC.I instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int8 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Integer.Integer -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift [a] -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Lit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Loc -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Match -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Maybe.Maybe a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.ModName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Module -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Name -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameFlavour -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameIs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameSpace -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NamespaceSpecifier -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Natural.Natural -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.OccName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Overlap -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pat -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynArgs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynDir -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Phases -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PkgName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pragma -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Range -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.Real.Integral a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Real.Ratio a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Role -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleBndr -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleMatch -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Safety -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceUnpackedness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Specificity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Stmt -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TExp a) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (a, b) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c) => GHC.Internal.TH.Lift.Lift (a, b, c) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d) => GHC.Internal.TH.Lift.Lift (a, b, c, d) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f g. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f, GHC.Internal.TH.Lift.Lift g) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f, g) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TyLit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TySynEqn -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TyVarBndr a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Type -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TypeFamilyHead -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift () -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Word -- Defined in ‘GHC.Internal.TH.Lift’ ===================================== testsuite/tests/th/TH_Lift.hs ===================================== @@ -80,3 +80,8 @@ o = $( (\x -> [| x |]) (True, 'x', 4 :: Int) ) p :: NonEmpty Char p = $( (\x -> [| x |]) ('a' :| "bcde") ) +exp :: Exp +exp = $( [| 3 + 4 |] >>= lift ) + +texp :: TExp Int +texp = $$( examineCode [|| 3 + 4 ||] `bindCode` liftTyped ) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cf98356676ad6c8dc2c084aede5fc96ba3bb1e9b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cf98356676ad6c8dc2c084aede5fc96ba3bb1e9b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 19:36:16 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 13 Jun 2024 15:36:16 -0400 Subject: [Git][ghc/ghc][master] ucd2haskell: remove Streamly dependency + misc Message-ID: <666b4a2fefe56_3a1a3822cd9481021bc@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 10 changed files: - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs - − libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs - libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell/ModuleGenerators.hs - libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs ===================================== @@ -8,9 +8,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.DerivedCoreProperties --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs ===================================== @@ -8,9 +8,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.UnicodeData.GeneralCategory --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs ===================================== @@ -7,9 +7,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.UnicodeData.SimpleLowerCaseMapping --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs ===================================== @@ -7,9 +7,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.UnicodeData.SimpleTitleCaseMapping --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs ===================================== @@ -7,9 +7,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.UnicodeData.SimpleUpperCaseMapping --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs ===================================== @@ -6,9 +6,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Version --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs deleted ===================================== @@ -1,1127 +0,0 @@ -{-# LANGUAGE LambdaCase #-} - --- | --- Module : Parser.Text --- Copyright : (c) 2020 Composewell Technologies and Contributors --- (c) 2016-2017 Harendra Kumar --- (c) 2014-2015 Antonio Nikishaev --- License : BSD-3-Clause --- Maintainer : streamly at composewell.com --- Stability : internal - --- This code was taken from https://github.com/composewell/unicode-data. --- The original Unicode database parser was taken from --- https://github.com/composewell/unicode-transforms but was completely --- rewritten from scratch to parse from UCD text files instead of XML, only --- some types remain the same. That code in turn was originally taken from --- https://github.com/llelf/prose (Antonio Nikishaev) and heavily modified by --- Harendra Kumar. --- -module Parser.Text (genModules) where - -import Control.Exception (catch, IOException) -import Control.Monad (void) -import Data.Bits (Bits(..)) -import Data.Word (Word8) -import Data.Char (chr, ord, isSpace) -import Data.Functor ((<&>)) -import Data.Function ((&)) -import Data.List (intersperse, unfoldr) -import Data.List.Split (splitWhen) -import Numeric (showHex) -import Streamly.Data.Fold (Fold) -import System.Directory (createDirectoryIfMissing) -import System.Environment (getEnv) -import System.FilePath ((), (<.>)) - --- import qualified Data.Set as Set -import Streamly.Data.Stream (Stream) -import qualified Streamly.Data.Stream.Prelude as Stream -import qualified Streamly.Data.Fold as Fold -import qualified Streamly.Internal.Data.Fold as Fold -import qualified Streamly.Data.Unfold as Unfold -import qualified Streamly.FileSystem.Handle as Handle -import qualified Streamly.Unicode.Stream as Unicode -import qualified Streamly.Internal.Unicode.Stream as Unicode -import qualified System.IO as Sys - -import Prelude hiding (pred) - -------------------------------------------------------------------------------- --- Types -------------------------------------------------------------------------------- - -data GeneralCategory = - Lu|Ll|Lt| --LC - Lm|Lo| --L - Mn|Mc|Me| --M - Nd|Nl|No| --N - Pc|Pd|Ps|Pe|Pi|Pf|Po| --P - Sm|Sc|Sk|So| --S - Zs|Zl|Zp| --Z - Cc|Cf|Cs|Co|Cn --C - deriving (Show, Bounded, Enum, Read) - -data DecompType = - DTCanonical | DTCompat | DTFont - | DTNoBreak | DTInitial | DTMedial | DTFinal - | DTIsolated | DTCircle | DTSuper | DTSub - | DTVertical | DTWide | DTNarrow - | DTSmall | DTSquare | DTFraction - deriving (Show, Eq) - -data Decomp = DCSelf | DC [Char] deriving (Show, Eq) - --- data DType = Canonical | Kompat - -data DetailedChar = - DetailedChar - { _char :: Char - , _name :: String - , _generalCategory :: GeneralCategory - , _combiningClass :: Int - , _decompositionType :: Maybe DecompType - , _decomposition :: Decomp - , _simpleUppercaseMapping :: Maybe Char - , _simpleLowercaseMapping :: Maybe Char - , _simpleTitlecaseMapping :: Maybe Char - } - deriving (Show) - -{- [NOTE] Used by disabled generator - --- See: https://www.unicode.org/reports/tr44/#Default_Values_Table -mkDefaultDetailedChar :: Char -> DetailedChar -mkDefaultDetailedChar c = DetailedChar - { _char = c - , _name = mempty - , _generalCategory = Cn - , _combiningClass = 0 - , _decompositionType = Nothing - , _decomposition = DCSelf - , _simpleUppercaseMapping = Nothing - , _simpleLowercaseMapping = Nothing - , _simpleTitlecaseMapping = Nothing } --} - -------------------------------------------------------------------------------- --- Helpers -------------------------------------------------------------------------------- - -headerRule :: String -headerRule = "-----------------------------------------------------------------------------" - -mkModuleHeader :: String -> String -mkModuleHeader modName = - unlines - [ headerRule - , "-- |" - , "-- Module : " <> modName - , "-- Copyright : (c) 2020 Composewell Technologies and Contributors" - , "-- License : BSD-3-Clause" - -- [FIXME] Update maintainer - , "-- Maintainer : streamly at composewell.com" - , "-- Stability : internal" - , headerRule - ] - -readCodePoint :: String -> Char -readCodePoint = chr . read . ("0x"<>) - -readCodePointM :: String -> Maybe Char -readCodePointM "" = Nothing -readCodePointM u = Just (readCodePoint u) - -genSignature :: String -> String -genSignature = (<> " :: Char -> Bool") - --- | Check that var is between minimum and maximum of orderList -genRangeCheck :: String -> [Int] -> String -genRangeCheck var ordList = - var - <> " >= " - <> show (minimum ordList) - <> " && " <> var <> " <= " <> show (maximum ordList) - -genBitmap :: String -> [Int] -> String -genBitmap funcName ordList = - unlines - [ "{-# INLINE " <> funcName <> " #-}" - , genSignature funcName - , funcName <> " = \\c -> let n = ord c in " - <> genRangeCheck "n" ordList <> " && lookupBit64 bitmap# n" - , " where" - , " bitmap# = \"" <> bitMapToAddrLiteral (positionsToBitMap ordList) "\"#" - ] - -positionsToBitMap :: [Int] -> [Bool] -positionsToBitMap = go 0 - - where - - go _ [] = [] - go i xxs@(x:xs) - | i < x = False : go (i + 1) xxs - | otherwise = True : go (i + 1) xs - -bitMapToAddrLiteral :: - -- | Values to encode - [Bool] -> - -- | String to append - String -> - String -bitMapToAddrLiteral bs cs = foldr encode cs (unfoldr mkChunks bs) - - where - - mkChunks :: [a] -> Maybe ([a], [a]) - mkChunks [] = Nothing - mkChunks xs = Just $ splitAt 8 xs - - encode :: [Bool] -> String -> String - encode chunk acc = '\\' : shows (toByte (padTo8 chunk)) acc - - padTo8 :: [Bool] -> [Bool] - padTo8 xs - | length xs >= 8 = xs - | otherwise = xs <> replicate (8 - length xs) False - - toByte :: [Bool] -> Int - toByte xs = sum $ map (\i -> if xs !! i then 1 `shiftL` i else 0) [0..7] - -genEnumBitmap :: - forall a. (Bounded a, Enum a, Show a) => - -- | Function name - String -> - -- | Default value - a -> - -- | List of values to encode - [a] -> - String -genEnumBitmap funcName def as = unlines - [ "{-# INLINE " <> funcName <> " #-}" - , funcName <> " :: Char -> Int" - , funcName <> " c = let n = ord c in if n >= " - <> show (length as) - <> " then " - <> show (fromEnum def) - <> " else lookup_bitmap n" - - , "{-# NOINLINE lookup_bitmap #-}" - , "lookup_bitmap :: Int -> Int" - , "lookup_bitmap n = lookupIntN bitmap# n" - , " where" - , " bitmap# = \"" <> enumMapToAddrLiteral as "\"#" - ] - -{-| Encode a list of values as a byte map, using their 'Enum' instance. - -__Note:__ 'Enum' instance must respect the following: - -* @fromEnum minBound >= 0x00@ -* @fromEnum maxBound <= 0xff@ --} -enumMapToAddrLiteral :: - forall a. (Bounded a, Enum a, Show a) => - -- | Values to encode - [a] -> - -- | String to append - String -> - String -enumMapToAddrLiteral xs cs = foldr go cs xs - - where - - go :: a -> String -> String - go x acc = '\\' : shows (toWord8 x) acc - - toWord8 :: a -> Word8 - toWord8 a = let w = fromEnum a in if 0 <= w && w <= 0xff - then fromIntegral w - else error $ "Cannot convert to Word8: " <> show a - -{- [NOTE] Disabled generator (normalization) --- This bit of code is duplicated but this duplication allows us to reduce 2 --- dependencies on the executable. - -jamoLCount :: Int -jamoLCount = 19 - -jamoVCount :: Int -jamoVCount = 21 - -jamoTCount :: Int -jamoTCount = 28 - -hangulFirst :: Int -hangulFirst = 0xac00 - -hangulLast :: Int -hangulLast = hangulFirst + jamoLCount * jamoVCount * jamoTCount - 1 - -isHangul :: Char -> Bool -isHangul c = n >= hangulFirst && n <= hangulLast - where n = ord c --} - -genUnicodeVersion :: FilePath -> IO () -genUnicodeVersion outdir = do - version <- catch - (getEnv "UNICODE_VERSION") - (\(_ :: IOException) -> return "") - Stream.fold f (Stream.fromList (body version)) - where - moduleName = "GHC.Internal.Unicode.Version" - f = moduleFileEmitter Nothing outdir - (moduleName, \_ -> Fold.foldMap (<> "\n")) - body :: String -> [String] - body version = - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(unicodeVersion)" - , "where" - , "" - , "import {-# SOURCE #-} GHC.Internal.Data.Version" - , "" - , "-- | Version of Unicode standard used by @base@:" - , "-- [" <> version <> "](https://www.unicode.org/versions/Unicode" <> version <> "/)." - , "--" - , "-- @since base-4.15.0.0" - , "unicodeVersion :: Version" - , "unicodeVersion = makeVersion [" <> mkVersion version <> "]" ] - mkVersion = foldr (\c acc -> case c of {'.' -> ',':' ':acc; _ -> c:acc}) mempty - -------------------------------------------------------------------------------- --- Parsers -------------------------------------------------------------------------------- - -------------------------------------------------------------------------------- --- Parsing UnicodeData.txt -------------------------------------------------------------------------------- - -genGeneralCategoryModule - :: Monad m - => String - -> Fold m DetailedChar String -genGeneralCategoryModule moduleName = - done <$> Fold.foldl' step initial - - where - - -- (categories, expected char) - initial = ([], '\0') - - step (acc, p) a = if p < _char a - -- Fill missing char entry with default category Cn - -- See: https://www.unicode.org/reports/tr44/#Default_Values_Table - then step (Cn : acc, succ p) a - -- Regular entry - else (_generalCategory a : acc, succ (_char a)) - - done (acc, _) = unlines - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(generalCategory)" - , "where" - , "" - , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" - , "import GHC.Internal.Unicode.Bits (lookupIntN)" - , "" - , genEnumBitmap "generalCategory" Cn (reverse acc) - ] - -readDecomp :: String -> (Maybe DecompType, Decomp) -readDecomp s = - if null wrds - then (Nothing, DCSelf) - else decmps wrds - - where - - decmps [] = error "Unreachable flow point" - decmps y@(x:xs) = - case dtmap x of - DTCanonical -> (,) (Just DTCanonical) (readCP y) - other -> (,) (Just other) (readCP xs) - - wrds = words s - - readCP ws = DC $ map readCodePoint ws - - dtmap "" = DTCompat - dtmap "" = DTCircle - dtmap "" = DTFinal - dtmap "" = DTFont - dtmap "" = DTFraction - dtmap "" = DTInitial - dtmap "" = DTIsolated - dtmap "" = DTMedial - dtmap "" = DTNarrow - dtmap "" = DTNoBreak - dtmap "" = DTSmall - dtmap "" = DTSquare - dtmap "" = DTSub - dtmap "" = DTSuper - dtmap "" = DTVertical - dtmap "" = DTWide - dtmap _ = DTCanonical - -{- [NOTE] Disabled generators - -filterNonHangul :: Monad m => Fold m DetailedChar a -> Fold m DetailedChar a -filterNonHangul = Fold.filter (not . isHangul . _char) - -filterDecomposableType :: - Monad m => DType -> Fold m DetailedChar a -> Fold m DetailedChar a -filterDecomposableType dtype = - Fold.filter ((/= DCSelf) . _decomposition) - . Fold.filter (predicate . _decompositionType) - - where - - predicate = - case dtype of - Canonical -> (== Just DTCanonical) - Kompat -> const True - -genDecomposableModule :: - Monad m => String -> DType -> Fold m DetailedChar String -genDecomposableModule moduleName dtype = - filterNonHangul - $ filterDecomposableType dtype $ done <$> Fold.foldl' step initial - - where - - initial = [] - - step st a = ord (_char a) : st - - done st = - unlines - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(isDecomposable)" - , "where" - , "" - , "import Data.Char (ord)" - , "import GHC.Internal.Unicode.Bits (lookupBit64)" - , "" - , genBitmap "isDecomposable" (reverse st) - ] - -genCombiningClassModule :: Monad m => String -> Fold m DetailedChar String -genCombiningClassModule moduleName = - Fold.filter (\dc -> _combiningClass dc /= 0) - $ done <$> Fold.foldl' step initial - - where - - initial = ([], []) - - step (st1, st2) a = (genCombiningClassDef a : st1, ord (_char a) : st2) - - done (st1, st2) = - unlines - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(combiningClass, isCombining)" - , "where" - , "" - , "import Data.Char (ord)" - , "import GHC.Internal.Unicode.Bits (lookupBit64)" - , "" - , "combiningClass :: Char -> Int" - , unlines (reverse st1) - , "combiningClass _ = 0\n" - , "" - , genBitmap "isCombining" (reverse st2) - ] - - genCombiningClassDef dc = - "combiningClass " - <> show (_char dc) <> " = " <> show (_combiningClass dc) - -genDecomposeDefModule :: - Monad m - => String - -> [String] - -> [String] - -> DType - -> (Int -> Bool) - -> Fold m DetailedChar String -genDecomposeDefModule moduleName before after dtype pred = - Fold.filter (pred . ord . _char) - $ filterNonHangul - $ filterDecomposableType dtype $ done <$> Fold.foldl' step initial - - where - - decomposeChar c DCSelf = [c] - decomposeChar _c (DC ds) = ds - - genHeader = - [ "{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(decompose)" - , "where" - , "" - ] - genSign = - [ "-- Note: this is a partial function we do not expect to call" - , "-- this if isDecomposable returns false." - , "{-# NOINLINE decompose #-}" - , "decompose :: Char -> [Char]" - ] - initial = [] - - step st dc = genDecomposeDef dc : st - - done st = - let body = mconcat [genHeader, before, genSign, reverse st, after] - in unlines body - - genDecomposeDef dc = - "decompose " - <> show (_char dc) - <> " = " <> show (decomposeChar (_char dc) (_decomposition dc)) - -genCompositionsModule :: - Monad m - => String - -> [Int] - -> [Int] - -> Fold m DetailedChar String -genCompositionsModule moduleName compExclu non0CC = - Fold.filter (not . flip elem compExclu . ord . _char) - $ filterNonHangul - $ Fold.filter (isDecompositionLen2 . _decomposition) - $ filterDecomposableType Canonical $ done <$> Fold.foldl' step initial - - where - - isDecompositionLen2 DCSelf = False - isDecompositionLen2 (DC ds) = length ds == 2 - - genComposePairDef name dc = - name - <> " " - <> show (head d01) - <> " " <> show (d01 !! 1) <> " = Just " <> show (_char dc) - - where - - d01 = decompPair dc - - decompPair dc = - case _decomposition dc of - DCSelf -> error "toCompFormat: DCSelf" - (DC ds) -> - if length ds == 2 - then ds - else error "toCompFormat: length /= 2" - - initial = ([], [], []) - - step (dec, sp, ss) dc = (dec1, sp1, ss1) - - where - - d01 = decompPair dc - d1Ord = ord $ d01 !! 1 - dec1 = genComposePairDef "compose" dc : dec - sp1 = - if d1Ord `notElem` non0CC - then genComposePairDef "composeStarters" dc : sp - else sp - ss1 = - if d1Ord `notElem` non0CC - then d1Ord : ss - else ss - - header = - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(compose, composeStarters, isSecondStarter)" - , "where" - , "" - , "import GHC.Internal.Base (Char, ord)" - , "import GHC.Internal.Unicode.Bits (lookupBit64)" - , "" - ] - - composePair decomps = - [ "{-# NOINLINE compose #-}" - , "compose :: Char -> Char -> Maybe Char" - , unlines decomps - , "compose _ _ = " <> "Nothing" <> "\n" - , "" - ] - - composeStarterPair starterPairs = - [ "composeStarters :: Char -> Char -> Maybe Char" - , unlines starterPairs - , "composeStarters _ _ = " <> "Nothing" <> "\n" - , "" - ] - - isSecondStarter secondStarters = - [genBitmap "isSecondStarter" secondStarters] - - done (dec, sp, ss) = - unlines - $ header - <> composePair (reverse dec) - <> composeStarterPair (reverse sp) - <> isSecondStarter (Set.toList (Set.fromList ss)) --} -genSimpleCaseMappingModule - :: Monad m - => String - -> String - -> (DetailedChar -> Maybe Char) - -> Fold m DetailedChar String -genSimpleCaseMappingModule moduleName funcName field = - done <$> Fold.foldl' step initial - - where - - genHeader = - [ "{-# LANGUAGE NoImplicitPrelude, LambdaCase #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(" <> funcName <> ")" - , "where" - , "" - , "import GHC.Internal.Base (Char)" - , "" - ] - genSign = - [ "{-# NOINLINE " <> funcName <> " #-}" - , funcName <> " :: Char -> Char" - , funcName <> " = \\case" - ] - initial = [] - - step ds dc = case mkEntry dc of - Nothing -> ds - Just d -> d : ds - - after = [" c -> c"] - - done st = - let body = mconcat [genHeader, genSign, reverse st, after] - in unlines body - - mkEntry dc = field dc <&> \c -> mconcat - [ " '\\x" - , showHexChar (_char dc) "' -> '\\x" - , showHexChar c "'" - ] - - showHexChar c = showHex (ord c) - -genCorePropertiesModule :: - Monad m => String -> (String -> Bool) -> Fold m (String, [Int]) String -genCorePropertiesModule moduleName isProp = - Fold.filter (\(name, _) -> isProp name) $ done <$> Fold.foldl' step initial - - where - - prop2FuncName x = "is" <> x - - initial = ([], []) - - step (props, bitmaps) (name, bits) = - (name : props, genBitmap (prop2FuncName name) bits : bitmaps) - - done (props, bitmaps) = unlines $ header props <> bitmaps - - header exports = - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(" <> unwords (intersperse "," (map prop2FuncName exports)) <> ")" - , "where" - , "" - , "import GHC.Internal.Base (Bool, Char, Ord(..), (&&), ord)" - , "import GHC.Internal.Unicode.Bits (lookupBit64)" - , "" - ] - -{- [NOTE] Disabled generator -genUnicode002TestResults :: Monad m => Fold m DetailedChar String -genUnicode002TestResults = done <$> Fold.foldl' step initial - - where - - header = "Code C P S U L A D" - -- (output, expected char) - initial = ([], '\0') - -- [TODO] Increase the number of tested char? - -- maxChar = '\xF0000' -- First codepoint of the last private use areas. - -- maxChar = '\xFFFF' -- Last codepoint of BMP. - maxChar = chr 6553 -- Value in GHC 9.2.2 base test - - step (acc, c) dc = if c > maxChar - then (acc, c) - else if c < _char dc - -- Fill missing char entry with default values - -- See: https://www.unicode.org/reports/tr44/#Default_Values_Table - then step (mkEntry (mkDefaultDetailedChar c) : acc, succ c) dc - -- Regular entry - else (mkEntry dc : acc, succ (_char dc)) - - done (acc, _) = unlines (header : reverse acc) - - mkEntry dc = mconcat - [ showCode (_char dc) - -- [TODO] General category - , showBool (isControl' dc) - , showBool (isPrint' dc) - , showBool (isSpace' dc) - -- [TODO] isSeparator - , showBool (isUpper' dc) - , showBool (isLower' dc) - , showBool (isAlpha' dc) - -- [TODO] isAlphaNum - , showBool (isDigit' dc) - -- [TODO] isNumber - -- [TODO] isMark - -- [TODO] isPunctuation - -- [TODO] isSymbol - ] - - padding = length (show (ord maxChar)) - showCode c = take padding (shows (ord c) (repeat ' ')) - -- [TODO] use showHex - -- showCode c = - -- let code = showHex (ord c) mempty - -- in replicate (padding - length code) '0' <> code - showBool b = if b then " T" else " F" - - -- [NOTE] The following functions replicates Data.Char. Keep them up to date! - - isControl' dc = case _generalCategory dc of - Cc -> True -- Control - _ -> False - - isPrint' dc = case _generalCategory dc of - Zl -> False -- LineSeparator - Zp -> False -- ParagraphSeparator - Cc -> False -- Control - Cf -> False -- Format - Cs -> False -- Surrogate - Co -> False -- PrivateUse - Cn -> False -- NotAssigned - _ -> True - - isSpace' dc = case _char dc of - '\t' -> True - '\n' -> True - '\v' -> True - '\f' -> True - '\r' -> True - _ -> case _generalCategory dc of - Zs -> True -- Space - _ -> False - - isUpper' dc = case _generalCategory dc of - Lu -> True -- UppercaseLetter - Lt -> True -- TitlecaseLetter - _ -> False - - isLower' dc = case _generalCategory dc of - Ll -> True -- LowercaseLetter - _ -> False - - isAlpha' dc = case _generalCategory dc of - Lu -> True -- UppercaseLetter - Ll -> True -- LowercaseLetter - Lt -> True -- TitlecaseLetter - Lm -> True -- ModifierLetter - Lo -> True -- OtherLetter - _ -> False - - isDigit' dc = let c = _char dc - in (fromIntegral (ord c - ord '0') :: Word) <= 9 --} - -------------------------------------------------------------------------------- --- Parsing property files -------------------------------------------------------------------------------- - -type PropertyLine = (String, [Int]) - -trim :: String -> String -trim = takeWhile (not . isSpace) . dropWhile isSpace - -emptyPropertyLine :: PropertyLine -emptyPropertyLine = ("", []) - -combinePropertyLines :: PropertyLine -> PropertyLine -> PropertyLine -combinePropertyLines t1@(n1, o1) t2@(n2, o2) - | n1 == "" = t2 - | n2 == "" = t1 - | n1 == n2 = (n1, o1 <> o2) - | otherwise = error $ "Cannot group " <> n1 <> " with " <> n2 - -parsePropertyLine :: String -> PropertyLine -parsePropertyLine ln - | null ln = emptyPropertyLine - | head ln == '#' = emptyPropertyLine - | otherwise = parseLineJ ln - - where - - parseLineJ :: String -> (String, [Int]) - parseLineJ line = - let (rangeLn, line1) = span (/= ';') line - propLn = takeWhile (/= '#') (tail line1) - in (trim propLn, parseRange (trim rangeLn)) - - parseRange :: String -> [Int] - parseRange rng = - if '.' `elem` rng - then let low = read $ "0x" <> takeWhile (/= '.') rng - high = - read $ "0x" <> reverse (takeWhile (/= '.') (reverse rng)) - in [low .. high] - else [read $ "0x" <> rng] - -isDivider :: String -> Bool -isDivider x = x == "# ================================================" - -parsePropertyLines :: (Monad m) => Stream m String -> Stream m PropertyLine -parsePropertyLines = - Stream.splitOn isDivider - $ Fold.lmap parsePropertyLine - $ Fold.foldl' combinePropertyLines emptyPropertyLine - --- | A range entry in @UnicodeData.txt at . -data UnicodeDataRange - = SingleCode !DetailedChar - -- ^ Regular entry for one code point - | FirstCode !String !DetailedChar - -- ^ A partial range for entry with a name as: @\@ - | CompleteRange !String !DetailedChar !DetailedChar - -- ^ A complete range, requiring 2 continuous entries with respective names: - -- - -- * @\@ - -- * @\@ - -{-| Parse UnicodeData.txt lines - -Parse ranges according to https://www.unicode.org/reports/tr44/#Code_Point_Ranges. - -__Note:__ this does /not/ fill missing char entries, -i.e. entries with no explicit entry nor within a range. --} -parseUnicodeDataLines :: forall m. (Monad m) => Stream m String -> Stream m DetailedChar -parseUnicodeDataLines - = Stream.unfoldMany (Unfold.unfoldr unitToRange) - . Stream.foldMany ( Fold.lmap parseDetailedChar - $ Fold.foldt' step initial id) - - where - - step :: Maybe UnicodeDataRange - -> DetailedChar - -> Fold.Step (Maybe UnicodeDataRange) (Maybe UnicodeDataRange) - step Nothing dc = case span (/= ',') (_name dc) of - (range, ", First>") -> Fold.Partial (Just (FirstCode range dc)) - _ -> Fold.Done (Just (SingleCode dc)) - step (Just (FirstCode range1 dc1)) dc2 = case span (/= ',') (_name dc2) of - (range2, ", Last>") -> if range1 == range2 && _char dc1 < _char dc2 - then Fold.Done (Just (CompleteRange range1 dc1 dc2)) - else error $ "Cannot create range: incompatible ranges" <> show (dc1, dc2) - _ -> error $ "Cannot create range: missing entry correspong to: " <> show range1 - step _ _ = error "impossible case" - - initial :: Fold.Step (Maybe UnicodeDataRange) (Maybe UnicodeDataRange) - initial = Fold.Partial Nothing - - unitToRange :: Maybe UnicodeDataRange -> Maybe (DetailedChar, Maybe UnicodeDataRange) - unitToRange = fmap $ \case - SingleCode dc -> (dc, Nothing) - FirstCode _ dc -> error $ "Incomplete range: " <> show dc - CompleteRange range dc1 dc2 -> if _char dc1 < _char dc2 - -- [TODO] Create the proper name - then (dc1{_name="TODO"}, Just (CompleteRange range dc1{_char=succ (_char dc1)} dc2)) - else (dc2{_name="TODO"}, Nothing) - --- | Parse a single entry of @UnicodeData.txt@ -parseDetailedChar :: String -> DetailedChar -parseDetailedChar line = case splitWhen (== ';') line of - char - :name - :gc - :combining - :_bidi - :decomposition - :_decimal - :_digit - :_numeric - :_bidiM - :_uni1Name - :_iso - :sUpper - :sLower - :sTitle - :_ -> - let (dctype, dcval) = readDecomp decomposition - in DetailedChar - { _char = readCodePoint char - , _name = name - , _generalCategory = read gc - , _combiningClass = read combining - , _decompositionType = dctype - , _decomposition = dcval - , _simpleUppercaseMapping = readCodePointM sUpper - , _simpleLowercaseMapping = readCodePointM sLower - , _simpleTitlecaseMapping = readCodePointM sTitle - } - _ -> error ("Unsupported line: " <> line) - -------------------------------------------------------------------------------- --- Generation -------------------------------------------------------------------------------- - -readLinesFromFile :: String -> Stream IO String -readLinesFromFile file = - withFile file Sys.ReadMode - $ \h -> Handle.read h & Unicode.decodeUtf8 & Unicode.lines Fold.toList - - where - withFile file_ mode = - Stream.bracketIO (Sys.openFile file_ mode) (Sys.hClose) - - -moduleToFileName :: String -> String -moduleToFileName = map (\x -> if x == '.' then '/' else x) - -dirFromFileName :: String -> String -dirFromFileName = reverse . dropWhile (/= '/') . reverse - -data FileRecipe a - = ModuleRecipe - -- ^ A recipe to create a Haskell module file. - String - -- ^ Module name - (String -> Fold IO a String) - -- ^ Function that generate the module, given the module name. - | TestOutputRecipe - -- ^ A recipe to create a test output file. - String - -- ^ Test name - (Fold IO a String) - -- ^ Test output generator - --- ModuleRecipe is a tuple of the module name and a function that generates the --- module using the module name -type ModuleRecipe a = (String, String -> Fold IO a String) -type TestOutputRecipe a = (FilePath, Fold IO a String) - --- GeneratorRecipe is a list of ModuleRecipe -type GeneratorRecipe a = [FileRecipe a] - -moduleFileEmitter :: Maybe FilePath -> FilePath -> ModuleRecipe a -> Fold IO a () -moduleFileEmitter mfile outdir (modName, fldGen) = Fold.rmapM action $ fldGen modName - - where - - pretext version = case mfile of - Just file -> mconcat - [ "-- DO NOT EDIT: This file is automatically generated by the internal tool ucd2haskell,\n" - , "-- with data from: https://www.unicode.org/Public/" - , version - , "/ucd/" - , file - ,".\n\n" - ] - Nothing -> "-- DO NOT EDIT: This file is automatically generated by the internal tool ucd2haskell.\n\n" - outfile = outdir moduleToFileName modName <.> ".hs" - outfiledir = dirFromFileName outfile - action c = do - version <- - catch - (getEnv "UNICODE_VERSION") - (\(_ :: IOException) -> return "") - createDirectoryIfMissing True outfiledir - writeFile outfile (pretext version <> c) - -testOutputFileEmitter :: FilePath -> TestOutputRecipe a -> Fold IO a () -testOutputFileEmitter outdir (name, fldGen) = Fold.rmapM action fldGen - - where - - outfile = outdir "tests" name <.> ".stdout" - outfiledir = dirFromFileName outfile - action c - = createDirectoryIfMissing True outfiledir - *> writeFile outfile c - -runGenerator :: - FilePath - -> FilePath - -> (Stream IO String -> Stream IO a) - -> FilePath - -> GeneratorRecipe a - -> IO () -runGenerator indir file transformLines outdir recipes = - readLinesFromFile (indir <> file) & transformLines & Stream.fold combinedFld - - where - - generatedFolds = recipes <&> \case - ModuleRecipe name f -> moduleFileEmitter (Just file) outdir (name, f) - TestOutputRecipe name f -> testOutputFileEmitter outdir (name, f) - combinedFld = void $ Fold.distribute generatedFolds - -genModules :: String -> String -> [String] -> IO () -genModules indir outdir props = do - genUnicodeVersion outdir - - -- [NOTE] Disabled generator - -- compExclu <- - -- readLinesFromFile (indir <> "DerivedNormalizationProps.txt") - -- & parsePropertyLines - -- & Stream.find (\(name, _) -> name == "Full_Composition_Exclusion") - -- & fmap (snd . fromMaybe ("", [])) - - -- [NOTE] Disabled generator - -- non0CC <- - -- readLinesFromFile (indir <> "extracted/DerivedCombiningClass.txt") - -- & parsePropertyLines - -- & Stream.filter (\(name, _) -> name /= "0") - -- & Stream.map snd - -- & Stream.fold (Fold.foldl' (<>) []) - - runGenerator - indir - "UnicodeData.txt" - parseUnicodeDataLines - outdir - -- [NOTE] Disabled generators - -- [ uncurry ModuleRecipe compositions compExclu non0CC - -- , uncurry ModuleRecipe combiningClass - -- , uncurry ModuleRecipe decomposable - -- , uncurry ModuleRecipe decomposableK - -- , uncurry ModuleRecipe decompositions - -- , uncurry ModuleRecipe decompositionsK2 - -- , uncurry ModuleRecipe decompositionsK - [ uncurry ModuleRecipe generalCategory - , uncurry ModuleRecipe simpleUpperCaseMapping - , uncurry ModuleRecipe simpleLowerCaseMapping - , uncurry ModuleRecipe simpleTitleCaseMapping - -- , uncurry TestOutputRecipe unicode002Test - ] - - -- [NOTE] Disabled generator - -- runGenerator - -- indir - -- "PropList.txt" - -- parsePropertyLines - -- outdir - -- [ uncurry ModuleRecipe propList ] - - runGenerator - indir - "DerivedCoreProperties.txt" - parsePropertyLines - outdir - [ uncurry ModuleRecipe derivedCoreProperties ] - - where - - -- [NOTE] Disabled generator - -- propList = - -- ("GHC.Internal.Unicode.Char.PropList" - -- , (`genCorePropertiesModule` (`elem` props))) - - derivedCoreProperties = - ("GHC.Internal.Unicode.Char.DerivedCoreProperties" - , (`genCorePropertiesModule` (`elem` props))) - - -- [NOTE] Disabled generator - -- compositions exc non0 = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.Compositions" - -- , \m -> genCompositionsModule m exc non0) - - -- [NOTE] Disabled generator - -- combiningClass = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.CombiningClass" - -- , genCombiningClassModule) - - -- [NOTE] Disabled generator - -- decomposable = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.Decomposable" - -- , (`genDecomposableModule` Canonical)) - - -- [NOTE] Disabled generator - -- decomposableK = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.DecomposableK" - -- , (`genDecomposableModule` Kompat)) - - -- [NOTE] Disabled generator - -- decompositions = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.Decompositions" - -- , \m -> genDecomposeDefModule m [] [] Canonical (const True)) - - -- [NOTE] Disabled generator - -- decompositionsK2 = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.DecompositionsK2" - -- , \m -> genDecomposeDefModule m [] [] Kompat (>= 60000)) - - -- [NOTE] Disabled generator - -- decompositionsK = - -- let pre = ["import qualified " <> fst decompositionsK2 <> " as DK2", ""] - -- post = ["decompose c = DK2.decompose c"] - -- in ( "GHC.Internal.Unicode.Char.UnicodeData.DecompositionsK" - -- , \m -> genDecomposeDefModule m pre post Kompat (< 60000)) - - generalCategory = - ( "GHC.Internal.Unicode.Char.UnicodeData.GeneralCategory" - , genGeneralCategoryModule) - - simpleUpperCaseMapping = - ( "GHC.Internal.Unicode.Char.UnicodeData.SimpleUpperCaseMapping" - , \m -> genSimpleCaseMappingModule m "toSimpleUpperCase" _simpleUppercaseMapping) - - simpleLowerCaseMapping = - ( "GHC.Internal.Unicode.Char.UnicodeData.SimpleLowerCaseMapping" - , \m -> genSimpleCaseMappingModule m "toSimpleLowerCase" _simpleLowercaseMapping) - - simpleTitleCaseMapping = - ( "GHC.Internal.Unicode.Char.UnicodeData.SimpleTitleCaseMapping" - , \m -> genSimpleCaseMappingModule m "toSimpleTitleCase" _simpleTitlecaseMapping) - - -- unicode002Test = - -- ( "unicode002" - -- , genUnicode002TestResults) ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell.hs ===================================== @@ -2,14 +2,17 @@ -- Module : Main -- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers " -- Stability : internal -- module Main where -import WithCli (HasArguments(..), withCli) -import Parser.Text (genModules) +import qualified Data.ByteString.Char8 as B8 +import qualified Data.ByteString.Short as BS import GHC.Generics (Generic) +import WithCli (HasArguments(..), withCli) + +import UCD2Haskell.ModuleGenerators (genModules) data CLIOptions = CLIOptions @@ -20,7 +23,10 @@ data CLIOptions = deriving (Show, Generic, HasArguments) cliClient :: CLIOptions -> IO () -cliClient opts = genModules (input opts) (output opts) (core_prop opts) +cliClient opts = genModules + opts.input + opts.output + (BS.toShort . B8.pack <$> opts.core_prop) main :: IO () main = withCli cliClient ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell/ModuleGenerators.hs ===================================== @@ -0,0 +1,517 @@ +-- | +-- Module : UCD2Haskell.ModuleGenerators +-- Copyright : (c) 2020 Composewell Technologies and Contributors +-- (c) 2016-2017 Harendra Kumar +-- (c) 2014-2015 Antonio Nikishaev +-- (c) 2022-2024 Pierre Le Marre +-- License : BSD-3-Clause +-- Maintainer : The GHC Developers " +-- Stability : internal + +-- Code history: +-- +-- This code was adapted from https://github.com/composewell/unicode-data/ +-- (around commit c4aa52ed932ad8badf97296858932c3389b275b8) by Pierre Le Marre. +-- The original Unicode database parser was taken from +-- https://github.com/composewell/unicode-transforms but was completely +-- rewritten from scratch to parse from UCD text files instead of XML, only +-- some types remain the same. That code in turn was originally taken from +-- https://github.com/llelf/prose (Antonio Nikishaev) and heavily modified by +-- Harendra Kumar. +-- +module UCD2Haskell.ModuleGenerators (genModules) where + +import Control.Exception (catch, IOException) +import Data.Bits (Bits(..)) +import Data.Word (Word8) +import Data.Char (ord) +import Data.Functor ((<&>), ($>)) +import Data.List (intersperse, unfoldr) +import System.Directory (createDirectoryIfMissing) +import System.Environment (getEnv) +import System.FilePath ((), (<.>)) +import Data.String (IsString) +import Data.Foldable (Foldable(..)) + +import qualified Data.ByteString.Builder as BB +import qualified Data.ByteString as B +import qualified Data.ByteString.Lazy as BL +import qualified Data.ByteString.Short as BS + +import qualified Unicode.CharacterDatabase.Parser.Common as C +import qualified Unicode.CharacterDatabase.Parser.UnicodeData as UD +import qualified Unicode.CharacterDatabase.Parser.Properties.Multiple as P + +import Prelude hiding (pred) + +-------------------------------------------------------------------------------- +-- Helpers +-------------------------------------------------------------------------------- + +unlinesBB :: [BB.Builder] -> BB.Builder +unlinesBB = (<> "\n") . mconcat . intersperse "\n" + +unwordsBB :: [BB.Builder] -> BB.Builder +unwordsBB = mconcat . intersperse " " + +headerRule :: BB.Builder +headerRule = "-----------------------------------------------------------------------------" + +mkModuleHeader :: BB.Builder -> BB.Builder +mkModuleHeader modName = + unlinesBB + [ headerRule + , "-- |" + , "-- Module : " <> modName + , "-- License : BSD-3-Clause" + , "-- Maintainer : The GHC Developers " + , "-- Stability : internal" + , headerRule + ] + +genSignature :: BB.Builder -> BB.Builder +genSignature = (<> " :: Char -> Bool") + +-- | Check that var is between minimum and maximum of orderList +genRangeCheck :: BB.Builder -> [Int] -> BB.Builder +genRangeCheck var ordList = + var + <> " >= " + <> BB.intDec (minimum ordList) + <> " && " <> var <> " <= " <> BB.intDec (maximum ordList) + +genBitmap :: BB.Builder -> [Int] -> BB.Builder +genBitmap funcName ordList = + unlinesBB + [ "{-# INLINE " <> funcName <> " #-}" + , genSignature funcName + , funcName <> " = \\c -> let n = ord c in " + <> genRangeCheck "n" ordList <> " && lookupBit64 bitmap# n" + , " where" + , " bitmap# = \"" <> bitMapToAddrLiteral (positionsToBitMap ordList) "\"#" + ] + +positionsToBitMap :: [Int] -> [Bool] +positionsToBitMap = go 0 + + where + + go _ [] = [] + go i xxs@(x:xs) + | i < x = False : go (i + 1) xxs + | otherwise = True : go (i + 1) xs + +bitMapToAddrLiteral :: + -- | Values to encode + [Bool] -> + -- | String to append + BB.Builder -> + BB.Builder +bitMapToAddrLiteral bs cs = foldr encode cs (unfoldr mkChunks bs) + + where + + mkChunks :: [a] -> Maybe ([a], [a]) + mkChunks [] = Nothing + mkChunks xs = Just $ splitAt 8 xs + + encode :: [Bool] -> BB.Builder -> BB.Builder + encode chunk acc = BB.char7 '\\' <> BB.intDec (toByte (padTo8 chunk)) <> acc + + padTo8 :: [Bool] -> [Bool] + padTo8 xs + | length xs >= 8 = xs + | otherwise = xs <> replicate (8 - length xs) False + + toByte :: [Bool] -> Int + toByte xs = sum $ map (\i -> if xs !! i then 1 `shiftL` i else 0) [0..7] + +genEnumBitmap :: + forall a. (Bounded a, Enum a, Show a) => + -- | Function name + BB.Builder -> + -- | Default value + a -> + -- | List of values to encode + [a] -> + BB.Builder +genEnumBitmap funcName def as = unlinesBB + [ "{-# INLINE " <> funcName <> " #-}" + , funcName <> " :: Char -> Int" + , funcName <> " c = let n = ord c in if n >= " + <> BB.intDec (length as) + <> " then " + <> BB.intDec (fromEnum def) + <> " else lookup_bitmap n" + + , "{-# NOINLINE lookup_bitmap #-}" + , "lookup_bitmap :: Int -> Int" + , "lookup_bitmap n = lookupIntN bitmap# n" + , " where" + , " bitmap# = \"" <> enumMapToAddrLiteral as "\"#" + ] + +{-| Encode a list of values as a byte map, using their 'Enum' instance. + +__Note:__ 'Enum' instance must respect the following: + +* @fromEnum minBound >= 0x00@ +* @fromEnum maxBound <= 0xff@ +-} +enumMapToAddrLiteral :: + forall a. (Bounded a, Enum a, Show a) => + -- | Values to encode + [a] -> + -- | String to append + BB.Builder -> + BB.Builder +enumMapToAddrLiteral xs cs = foldr go cs xs + + where + + go :: a -> BB.Builder -> BB.Builder + go x acc = BB.char7 '\\' <> BB.word8Dec (toWord8 x) <> acc + + toWord8 :: a -> Word8 + toWord8 a = let w = fromEnum a in if 0 <= w && w <= 0xff + then fromIntegral w + else error $ "Cannot convert to Word8: " <> show a + +genUnicodeVersion :: FilePath -> IO () +genUnicodeVersion outdir = do + version <- catch + (getEnv "UNICODE_VERSION") + (\(_ :: IOException) -> return "") + runFold f [body version] + where + moduleName :: (IsString a) => a + moduleName = "GHC.Internal.Unicode.Version" + f = moduleFileEmitter Nothing outdir + (moduleName, \_ -> Fold (\_ x -> x) mempty id) + body :: String -> BB.Builder + body version = unlinesBB + [ "{-# LANGUAGE NoImplicitPrelude #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(unicodeVersion)" + , "where" + , "" + , "import {-# SOURCE #-} GHC.Internal.Data.Version" + , "" + , "-- | Version of Unicode standard used by @base@:" + , "-- [" <> BB.string7 version <> "](https://www.unicode.org/versions/Unicode" <> BB.string7 version <> "/)." + , "--" + , "-- @since base-4.15.0.0" + , "unicodeVersion :: Version" + , "unicodeVersion = makeVersion [" <> mkVersion version <> "]" ] + mkVersion = foldMap (\c -> case c of {'.' -> BB.char7 ',' <> BB.char7 ' '; _ -> BB.char7 c}) + +-------------------------------------------------------------------------------- +-- Fold +-------------------------------------------------------------------------------- + +data Fold a b = forall s. Fold + { _step :: s -> a -> s + , _initial :: s + , _final :: s -> b } + +data Pair a b = Pair !a !b + +teeWith :: (a -> b -> c) -> Fold x a -> Fold x b -> Fold x c +teeWith f (Fold stepL initialL finalL) (Fold stepR initialR finalR) = + Fold step initial final + where + step (Pair sL sR) x = Pair (stepL sL x) (stepR sR x) + initial = Pair initialL initialR + final (Pair sL sR) = f (finalL sL) (finalR sR) + +distribute :: [Fold a b] -> Fold a [b] +distribute = foldr (teeWith (:)) (Fold const () (const [])) + +rmapFold :: (b -> c) -> Fold a b -> Fold a c +rmapFold f (Fold step initial final) = Fold step initial (f . final) + +runFold :: Fold a b -> [a] -> b +runFold (Fold step initial final) = final . foldl' step initial + +-------------------------------------------------------------------------------- +-- Modules generators +-------------------------------------------------------------------------------- + +data GeneralCategoryAcc = GeneralCategoryAcc + { _categories :: ![UD.GeneralCategory] + , _expectedChar :: !Char + } + +genGeneralCategoryModule :: BB.Builder -> Fold UD.Entry BB.Builder +genGeneralCategoryModule moduleName = Fold step initial done + + where + + -- (categories, expected char) + initial = GeneralCategoryAcc [] '\0' + + step (GeneralCategoryAcc acc p) e@(UD.Entry r d) + | p < r.start + -- Fill missing char entry with default category Cn + -- See: https://www.unicode.org/reports/tr44/#Default_Values_Table + = step (GeneralCategoryAcc (replicate (ord r.start - ord p) UD.Cn <> acc) r.start) e + -- Regular entry + | otherwise = case r of + C.SingleChar ch -> GeneralCategoryAcc + (d.generalCategory : acc) + (succ ch) + C.CharRange ch1 ch2 -> GeneralCategoryAcc + (replicate (ord ch2 - ord ch1 + 1) d.generalCategory <> acc) + (succ ch2) + + done (GeneralCategoryAcc acc _) = unlinesBB + [ "{-# LANGUAGE NoImplicitPrelude #-}" + , "{-# LANGUAGE MagicHash #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(generalCategory)" + , "where" + , "" + , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" + , "import GHC.Internal.Unicode.Bits (lookupIntN)" + , "" + , genEnumBitmap "generalCategory" UD.Cn (reverse acc) + ] + +genSimpleCaseMappingModule + :: BB.Builder + -> BB.Builder + -> (UD.CharDetails -> Maybe Char) + -> Fold UD.Entry BB.Builder +genSimpleCaseMappingModule moduleName funcName field = + Fold step initial done + + where + + genHeader = + [ "{-# LANGUAGE NoImplicitPrelude, LambdaCase #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(" <> funcName <> ")" + , "where" + , "" + , "import GHC.Internal.Base (Char)" + , "" + ] + genSign = + [ "{-# NOINLINE " <> funcName <> " #-}" + , funcName <> " :: Char -> Char" + , funcName <> " = \\case" + ] + initial = [] + + step ds dc = case mkEntry dc of + Nothing -> ds + Just d -> d : ds + + after = [" c -> c"] + + done st = + let body = mconcat [genHeader, genSign, reverse st, after] + in unlinesBB body + + mkEntry (UD.Entry r dc) = case r of + C.SingleChar ch -> field dc <&> \c -> mconcat + [ " '\\x" + , showHexChar ch + , "' -> '\\x" + , showHexChar c + , "'" + ] + C.CharRange{} -> field dc $> error ("genSimpleCaseMappingModule: unexpected char range: " <> show r) + + showHexChar c = BB.wordHex (fromIntegral (ord c)) + +data PropertiesAcc = PropertiesAcc + { _properties :: ![BS.ShortByteString] + , _bitmaps :: ![BB.Builder] + , _currentBitmap :: ![[Int]] } + +genCorePropertiesModule :: + BB.Builder -> (BS.ShortByteString -> Bool) -> Fold P.Entry BB.Builder +genCorePropertiesModule moduleName isProp = Fold step initial done + where + prop2FuncName x = "is" <> BB.shortByteString x + + initial = PropertiesAcc [] [] [] + + step acc@(PropertiesAcc props bitmaps bits) P.Entry{..} + | not (isProp property) = acc -- property filtered out + | otherwise = case props of + prop' : _ + | prop' == property -> PropertiesAcc props bitmaps (rangeToBits range : bits) + | otherwise -> PropertiesAcc + { _properties = property : props + , _bitmaps = genBitmap' prop' bits : bitmaps + , _currentBitmap = [rangeToBits range] } + _ -> PropertiesAcc [property] bitmaps [rangeToBits range] + + rangeToBits = \case + C.SingleChar ch -> [ord ch] + C.CharRange ch1 ch2 -> [ord ch1 .. ord ch2] + + genBitmap' prop bits = genBitmap (prop2FuncName prop) (mconcat (reverse bits)) + + done (PropertiesAcc props bitmaps bits) = unlinesBB (header props <> bitmaps') + where + lastProp = case props of + prop : _ -> prop + [] -> error "impossible" + bitmaps' = genBitmap' lastProp bits : bitmaps + + header exports = + [ "{-# LANGUAGE NoImplicitPrelude #-}" + , "{-# LANGUAGE MagicHash #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(" <> unwordsBB (intersperse "," (map prop2FuncName exports)) <> ")" + , "where" + , "" + , "import GHC.Internal.Base (Bool, Char, Ord(..), (&&), ord)" + , "import GHC.Internal.Unicode.Bits (lookupBit64)" + , "" + ] + +-------------------------------------------------------------------------------- +-- Generation +-------------------------------------------------------------------------------- + +moduleToFileName :: String -> String +moduleToFileName = map (\x -> if x == '.' then '/' else x) + +dirFromFileName :: String -> String +dirFromFileName = reverse . dropWhile (/= '/') . reverse + +data FileRecipe a + = ModuleRecipe + -- ^ A recipe to create a Haskell module file. + String + -- ^ Module name + (BB.Builder -> Fold a BB.Builder) + -- ^ Function that generate the module, given the module name. + | TestOutputRecipe + -- ^ A recipe to create a test output file. + String + -- ^ Test name + (Fold a BB.Builder) + -- ^ Test output generator + +-- ModuleRecipe is a tuple of the module name and a function that generates the +-- module using the module name +type ModuleRecipe a = (String, BB.Builder -> Fold a BB.Builder) +type TestOutputRecipe a = (FilePath, Fold a BB.Builder) + +-- GeneratorRecipe is a list of ModuleRecipe +type GeneratorRecipe a = [FileRecipe a] + +moduleFileEmitter :: Maybe FilePath -> FilePath -> ModuleRecipe a -> Fold a (IO ()) +moduleFileEmitter mfile outdir (modName, fldGen) = rmapFold action $ fldGen (BB.string7 modName) + + where + + pretext version = case mfile of + Just file -> mconcat + [ "-- DO NOT EDIT: This file is automatically generated by the internal tool ucd2haskell,\n" + , "-- with data from: https://www.unicode.org/Public/" + , BB.string7 version + , "/ucd/" + , BB.string7 file + ,".\n\n" + ] + Nothing -> "-- DO NOT EDIT: This file is automatically generated by the internal tool ucd2haskell.\n\n" + outfile = outdir moduleToFileName modName <.> ".hs" + outfiledir = dirFromFileName outfile + action c = do + version <- + catch + (getEnv "UNICODE_VERSION") + (\(_ :: IOException) -> return "") + createDirectoryIfMissing True outfiledir + B.writeFile outfile (BL.toStrict (BB.toLazyByteString (pretext version <> c))) + +testOutputFileEmitter :: FilePath -> TestOutputRecipe a -> Fold a (IO ()) +testOutputFileEmitter outdir (name, fldGen) = rmapFold action fldGen + + where + + outfile = outdir "tests" name <.> ".stdout" + outfiledir = dirFromFileName outfile + action c + = createDirectoryIfMissing True outfiledir + *> B.writeFile outfile (BL.toStrict (BB.toLazyByteString c)) + +runGenerator :: + FilePath + -> FilePath + -> (B.ByteString -> [a]) + -> FilePath + -> GeneratorRecipe a + -> IO () +runGenerator indir file transformLines outdir recipes = do + raw <- B.readFile (indir <> file) + sequence_ (runFold combinedFld (transformLines raw)) + + where + + generatedFolds = recipes <&> \case + ModuleRecipe name f -> moduleFileEmitter (Just file) outdir (name, f) + TestOutputRecipe name f -> testOutputFileEmitter outdir (name, f) + combinedFld = distribute generatedFolds + +genModules :: FilePath -> FilePath -> [BS.ShortByteString] -> IO () +genModules indir outdir props = do + genUnicodeVersion outdir + + runGenerator + indir + "UnicodeData.txt" + UD.parse + outdir + [ generalCategory + , simpleUpperCaseMapping + , simpleLowerCaseMapping + , simpleTitleCaseMapping + ] + + runGenerator + indir + "DerivedCoreProperties.txt" + P.parse + outdir + [ derivedCoreProperties ] + + where + + derivedCoreProperties = ModuleRecipe + "GHC.Internal.Unicode.Char.DerivedCoreProperties" + (`genCorePropertiesModule` (`elem` props)) + + generalCategory = ModuleRecipe + "GHC.Internal.Unicode.Char.UnicodeData.GeneralCategory" + genGeneralCategoryModule + + simpleUpperCaseMapping = ModuleRecipe + "GHC.Internal.Unicode.Char.UnicodeData.SimpleUpperCaseMapping" + (\m -> genSimpleCaseMappingModule m "toSimpleUpperCase" UD.simpleUpperCaseMapping) + + simpleLowerCaseMapping = ModuleRecipe + "GHC.Internal.Unicode.Char.UnicodeData.SimpleLowerCaseMapping" + (\m -> genSimpleCaseMappingModule m "toSimpleLowerCase" UD.simpleLowerCaseMapping) + + simpleTitleCaseMapping = ModuleRecipe + "GHC.Internal.Unicode.Char.UnicodeData.SimpleTitleCaseMapping" + (\m -> genSimpleCaseMappingModule m "toSimpleTitleCase" UD.simpleTitleCaseMapping) ===================================== libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal ===================================== @@ -1,6 +1,6 @@ cabal-version: 2.2 name: ucd2haskell -version: 0.3.0 +version: 0.4.0 synopsis: Converter from Unicode character database to Haskell. description: The Haskell data structures are generated programmatically from the @@ -10,12 +10,12 @@ description: license: BSD-3-Clause license-file: LICENSE author: Composewell Technologies and Contributors -maintainer: streamly at composewell.com -copyright: 2020 Composewell Technologies and Contributors +maintainer: The GHC Developers +bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new category: Data,Text,Unicode stability: Experimental build-type: Simple -tested-with: GHC==9.2.2 +tested-with: GHC==9.8.2 extra-source-files: README.md @@ -23,18 +23,14 @@ extra-source-files: common default-extensions default-extensions: - BangPatterns DeriveGeneric - MagicHash - RecordWildCards - ScopedTypeVariables - TupleSections - FlexibleContexts - - -- Experimental, may lead to issues DeriveAnyClass - TemplateHaskell - UnboxedTuples + ExistentialQuantification + LambdaCase + OverloadedStrings + OverloadedRecordDot + ScopedTypeVariables + RecordWildCards common compile-options ghc-options: -Wall @@ -42,21 +38,20 @@ common compile-options -fwarn-incomplete-record-updates -fwarn-incomplete-uni-patterns -fwarn-tabs - default-language: Haskell2010 + default-language: GHC2021 executable ucd2haskell import: default-extensions, compile-options - default-language: Haskell2010 ghc-options: -O2 hs-source-dirs: exe main-is: UCD2Haskell.hs - other-modules: Parser.Text + other-modules: UCD2Haskell.ModuleGenerators build-depends: - base >= 4.7 && < 4.20 - , streamly-core >= 0.2.2 && < 0.3 - , streamly >= 0.10 && < 0.11 - , split >= 0.2.3 && < 0.3 - , getopt-generics >= 0.13 && < 0.14 - , containers >= 0.5 && < 0.7 - , directory >= 1.3.6 && < 1.3.8 - , filepath >= 1.4.2 && < 1.5 + base >= 4.7 && < 5 + , bytestring >= 0.11 && < 0.13 + , containers >= 0.5 && < 0.7 + , directory >= 1.3.6 && < 1.3.8 + , filepath >= 1.4.2 && < 1.5 + , getopt-generics >= 0.13 && < 0.14 + , split >= 0.2.3 && < 0.3 + , unicode-data-parser >= 0.2.0 && < 0.4 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7b23ce8b48a169ba15d5ab585505f43d71363d38 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7b23ce8b48a169ba15d5ab585505f43d71363d38 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 19:36:36 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 13 Jun 2024 15:36:36 -0400 Subject: [Git][ghc/ghc][master] Document how to run haddocks tests (#24976) Message-ID: <666b4a44b713e_3a1a382353fac103678@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - 2 changed files: - utils/haddock/CONTRIBUTING.md - utils/haddock/cabal.project Changes: ===================================== utils/haddock/CONTRIBUTING.md ===================================== @@ -28,6 +28,17 @@ Then, run the following command from the top-level: $ ./hadrian/build -j --flavour=Quick --freeze1 _build/stage1/bin/haddock ``` +### Running the test suites + +Currently, this cannot be done with hadrian but has to be done with a +`cabal-install` built from `master`. + +``` +cabal test -w /_build/stage1/bin/ghc +``` + +For more details, see https://gitlab.haskell.org/ghc/ghc/-/issues/24976. + ## Working with the codebase The project provides a Makefile with rules to accompany you during development: ===================================== utils/haddock/cabal.project ===================================== @@ -1,5 +1,3 @@ -with-compiler: ghc-9.7 - packages: ./ ./haddock-api ./haddock-library View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4570319fc2631c97490a337242a3b6c50f3072e4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4570319fc2631c97490a337242a3b6c50f3072e4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 13 23:08:36 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 13 Jun 2024 19:08:36 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: ucd2haskell: remove Streamly dependency + misc Message-ID: <666b7bf438abb_3e6ca2f50000979c0@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - 0ee9cb08 by amesgen at 2024-06-13T19:08:06-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - 696b9a34 by amesgen at 2024-06-13T19:08:06-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - 912181bd by Simon Peyton Jones at 2024-06-13T19:08:06-04:00 Small documentation update in Quick Look - - - - - 14 changed files: - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/Tc/Gen/App.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs - − libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs - libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell/ModuleGenerators.hs - libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal - utils/haddock/CONTRIBUTING.md - utils/haddock/cabal.project Changes: ===================================== compiler/GHC/CmmToAsm/Wasm/FromCmm.hs ===================================== @@ -1045,22 +1045,16 @@ lower_CmmExpr_Typed lbl ty expr = do lower_CmmExpr_Ptr :: CLabel -> CmmExpr -> WasmCodeGenM w (WasmExpr w w, Int) lower_CmmExpr_Ptr lbl ptr = do ty_word <- wasmWordTypeM - case ptr of - CmmLit (CmmLabelOff lbl o) - | o >= 0 -> do - instrs <- - lower_CmmExpr_Typed - lbl - ty_word - (CmmLit $ CmmLabel lbl) - pure (instrs, o) - CmmMachOp (MO_Add _) [base, CmmLit (CmmInt o _)] - | o >= 0 -> do - instrs <- lower_CmmExpr_Typed lbl ty_word base - pure (instrs, fromInteger o) - _ -> do - instrs <- lower_CmmExpr_Typed lbl ty_word ptr - pure (instrs, 0) + let (ptr', o) = case ptr of + CmmLit (CmmLabelOff lbl o) + | o >= 0 -> (CmmLit $ CmmLabel lbl, o) + CmmRegOff reg o + | o >= 0 -> (CmmReg reg, o) + CmmMachOp (MO_Add _) [base, CmmLit (CmmInt o _)] + | o >= 0 -> (base, fromInteger o) + _ -> (ptr, 0) + instrs <- lower_CmmExpr_Typed lbl ty_word ptr' + pure (instrs, o) -- | Push a series of values onto the wasm value stack, returning the -- result stack type. ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -271,6 +271,12 @@ tcApp works like this: Otherwise, delegate back to tcExpr, which infers an (instantiated) TcRhoType + This isn't perfect. Consider this (which uses visible type application): + (let { f :: forall a. a -> a; f x = x } in f) @Int + Since 'let' is not among the special cases for tcInferAppHead, + we'll delegate back to tcExpr, which will instantiate f's type + and the type application to @Int will fail. Too bad! + 3. Use tcInstFun to instantiate the function, Quick-Looking as we go. This implements the |-inst judgement in Fig 4, plus the modification in Fig 5, of the QL paper: "A quick look at impredicativity" (ICFP'20). @@ -325,16 +331,15 @@ application; but it also does a couple of gruesome final checks: * Horrible newtype check * Special case for tagToEnum - -Some cases that /won't/ work: - -1. Consider this (which uses visible type application): - - (let { f :: forall a. a -> a; f x = x } in f) @Int - - Since 'let' is not among the special cases for tcInferAppHead, - we'll delegate back to tcExpr, which will instantiate f's type - and the type application to @Int will fail. Too bad! +(TCAPP2) There is a lurking difficulty in the above plan: + * Before calling tcInstFun, we set the ambient level in the monad + to QLInstVar (Step 2 above). + * Then, when kind-checking the visible type args of the application, + we may perhaps build an implication constraint. + * That means we'll try to add 1 to the ambient level; which is a no-op. + * So skolem escape checks won't work right. + This is pretty exotic, so I'm just deferring it for now, leaving + this note to alert you to the possiblity. Note [Quick Look for particular Ids] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -401,7 +406,7 @@ tcApp rn_expr exp_res_ty -- Step 3: Instantiate the function type (taking a quick look at args) ; do_ql <- wantQuickLook rn_fun ; (inst_args, app_res_rho) - <- setQLInstLevel do_ql $ -- See (TCAPP1) in + <- setQLInstLevel do_ql $ -- See (TCAPP1) and (TCAPP2) in -- Note [tcApp: typechecking applications] tcInstFun do_ql True tc_head fun_sigma rn_args @@ -2008,6 +2013,8 @@ That is the entire point of qlUnify! Wrinkles: discard the constraints and the coercion, and do not update the instantiation variable. But see "Sadly discarded design alternative" below.) + See also (TCAPP2) in Note [tcApp: typechecking applications]. + (UQL3) Instantiation variables don't really have a settled level yet; they have level QLInstVar (see Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. You might worry that we might unify ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs ===================================== @@ -8,9 +8,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.DerivedCoreProperties --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs ===================================== @@ -8,9 +8,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.UnicodeData.GeneralCategory --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs ===================================== @@ -7,9 +7,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.UnicodeData.SimpleLowerCaseMapping --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs ===================================== @@ -7,9 +7,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.UnicodeData.SimpleTitleCaseMapping --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs ===================================== @@ -7,9 +7,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.UnicodeData.SimpleUpperCaseMapping --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs ===================================== @@ -6,9 +6,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Version --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs deleted ===================================== @@ -1,1127 +0,0 @@ -{-# LANGUAGE LambdaCase #-} - --- | --- Module : Parser.Text --- Copyright : (c) 2020 Composewell Technologies and Contributors --- (c) 2016-2017 Harendra Kumar --- (c) 2014-2015 Antonio Nikishaev --- License : BSD-3-Clause --- Maintainer : streamly at composewell.com --- Stability : internal - --- This code was taken from https://github.com/composewell/unicode-data. --- The original Unicode database parser was taken from --- https://github.com/composewell/unicode-transforms but was completely --- rewritten from scratch to parse from UCD text files instead of XML, only --- some types remain the same. That code in turn was originally taken from --- https://github.com/llelf/prose (Antonio Nikishaev) and heavily modified by --- Harendra Kumar. --- -module Parser.Text (genModules) where - -import Control.Exception (catch, IOException) -import Control.Monad (void) -import Data.Bits (Bits(..)) -import Data.Word (Word8) -import Data.Char (chr, ord, isSpace) -import Data.Functor ((<&>)) -import Data.Function ((&)) -import Data.List (intersperse, unfoldr) -import Data.List.Split (splitWhen) -import Numeric (showHex) -import Streamly.Data.Fold (Fold) -import System.Directory (createDirectoryIfMissing) -import System.Environment (getEnv) -import System.FilePath ((), (<.>)) - --- import qualified Data.Set as Set -import Streamly.Data.Stream (Stream) -import qualified Streamly.Data.Stream.Prelude as Stream -import qualified Streamly.Data.Fold as Fold -import qualified Streamly.Internal.Data.Fold as Fold -import qualified Streamly.Data.Unfold as Unfold -import qualified Streamly.FileSystem.Handle as Handle -import qualified Streamly.Unicode.Stream as Unicode -import qualified Streamly.Internal.Unicode.Stream as Unicode -import qualified System.IO as Sys - -import Prelude hiding (pred) - -------------------------------------------------------------------------------- --- Types -------------------------------------------------------------------------------- - -data GeneralCategory = - Lu|Ll|Lt| --LC - Lm|Lo| --L - Mn|Mc|Me| --M - Nd|Nl|No| --N - Pc|Pd|Ps|Pe|Pi|Pf|Po| --P - Sm|Sc|Sk|So| --S - Zs|Zl|Zp| --Z - Cc|Cf|Cs|Co|Cn --C - deriving (Show, Bounded, Enum, Read) - -data DecompType = - DTCanonical | DTCompat | DTFont - | DTNoBreak | DTInitial | DTMedial | DTFinal - | DTIsolated | DTCircle | DTSuper | DTSub - | DTVertical | DTWide | DTNarrow - | DTSmall | DTSquare | DTFraction - deriving (Show, Eq) - -data Decomp = DCSelf | DC [Char] deriving (Show, Eq) - --- data DType = Canonical | Kompat - -data DetailedChar = - DetailedChar - { _char :: Char - , _name :: String - , _generalCategory :: GeneralCategory - , _combiningClass :: Int - , _decompositionType :: Maybe DecompType - , _decomposition :: Decomp - , _simpleUppercaseMapping :: Maybe Char - , _simpleLowercaseMapping :: Maybe Char - , _simpleTitlecaseMapping :: Maybe Char - } - deriving (Show) - -{- [NOTE] Used by disabled generator - --- See: https://www.unicode.org/reports/tr44/#Default_Values_Table -mkDefaultDetailedChar :: Char -> DetailedChar -mkDefaultDetailedChar c = DetailedChar - { _char = c - , _name = mempty - , _generalCategory = Cn - , _combiningClass = 0 - , _decompositionType = Nothing - , _decomposition = DCSelf - , _simpleUppercaseMapping = Nothing - , _simpleLowercaseMapping = Nothing - , _simpleTitlecaseMapping = Nothing } --} - -------------------------------------------------------------------------------- --- Helpers -------------------------------------------------------------------------------- - -headerRule :: String -headerRule = "-----------------------------------------------------------------------------" - -mkModuleHeader :: String -> String -mkModuleHeader modName = - unlines - [ headerRule - , "-- |" - , "-- Module : " <> modName - , "-- Copyright : (c) 2020 Composewell Technologies and Contributors" - , "-- License : BSD-3-Clause" - -- [FIXME] Update maintainer - , "-- Maintainer : streamly at composewell.com" - , "-- Stability : internal" - , headerRule - ] - -readCodePoint :: String -> Char -readCodePoint = chr . read . ("0x"<>) - -readCodePointM :: String -> Maybe Char -readCodePointM "" = Nothing -readCodePointM u = Just (readCodePoint u) - -genSignature :: String -> String -genSignature = (<> " :: Char -> Bool") - --- | Check that var is between minimum and maximum of orderList -genRangeCheck :: String -> [Int] -> String -genRangeCheck var ordList = - var - <> " >= " - <> show (minimum ordList) - <> " && " <> var <> " <= " <> show (maximum ordList) - -genBitmap :: String -> [Int] -> String -genBitmap funcName ordList = - unlines - [ "{-# INLINE " <> funcName <> " #-}" - , genSignature funcName - , funcName <> " = \\c -> let n = ord c in " - <> genRangeCheck "n" ordList <> " && lookupBit64 bitmap# n" - , " where" - , " bitmap# = \"" <> bitMapToAddrLiteral (positionsToBitMap ordList) "\"#" - ] - -positionsToBitMap :: [Int] -> [Bool] -positionsToBitMap = go 0 - - where - - go _ [] = [] - go i xxs@(x:xs) - | i < x = False : go (i + 1) xxs - | otherwise = True : go (i + 1) xs - -bitMapToAddrLiteral :: - -- | Values to encode - [Bool] -> - -- | String to append - String -> - String -bitMapToAddrLiteral bs cs = foldr encode cs (unfoldr mkChunks bs) - - where - - mkChunks :: [a] -> Maybe ([a], [a]) - mkChunks [] = Nothing - mkChunks xs = Just $ splitAt 8 xs - - encode :: [Bool] -> String -> String - encode chunk acc = '\\' : shows (toByte (padTo8 chunk)) acc - - padTo8 :: [Bool] -> [Bool] - padTo8 xs - | length xs >= 8 = xs - | otherwise = xs <> replicate (8 - length xs) False - - toByte :: [Bool] -> Int - toByte xs = sum $ map (\i -> if xs !! i then 1 `shiftL` i else 0) [0..7] - -genEnumBitmap :: - forall a. (Bounded a, Enum a, Show a) => - -- | Function name - String -> - -- | Default value - a -> - -- | List of values to encode - [a] -> - String -genEnumBitmap funcName def as = unlines - [ "{-# INLINE " <> funcName <> " #-}" - , funcName <> " :: Char -> Int" - , funcName <> " c = let n = ord c in if n >= " - <> show (length as) - <> " then " - <> show (fromEnum def) - <> " else lookup_bitmap n" - - , "{-# NOINLINE lookup_bitmap #-}" - , "lookup_bitmap :: Int -> Int" - , "lookup_bitmap n = lookupIntN bitmap# n" - , " where" - , " bitmap# = \"" <> enumMapToAddrLiteral as "\"#" - ] - -{-| Encode a list of values as a byte map, using their 'Enum' instance. - -__Note:__ 'Enum' instance must respect the following: - -* @fromEnum minBound >= 0x00@ -* @fromEnum maxBound <= 0xff@ --} -enumMapToAddrLiteral :: - forall a. (Bounded a, Enum a, Show a) => - -- | Values to encode - [a] -> - -- | String to append - String -> - String -enumMapToAddrLiteral xs cs = foldr go cs xs - - where - - go :: a -> String -> String - go x acc = '\\' : shows (toWord8 x) acc - - toWord8 :: a -> Word8 - toWord8 a = let w = fromEnum a in if 0 <= w && w <= 0xff - then fromIntegral w - else error $ "Cannot convert to Word8: " <> show a - -{- [NOTE] Disabled generator (normalization) --- This bit of code is duplicated but this duplication allows us to reduce 2 --- dependencies on the executable. - -jamoLCount :: Int -jamoLCount = 19 - -jamoVCount :: Int -jamoVCount = 21 - -jamoTCount :: Int -jamoTCount = 28 - -hangulFirst :: Int -hangulFirst = 0xac00 - -hangulLast :: Int -hangulLast = hangulFirst + jamoLCount * jamoVCount * jamoTCount - 1 - -isHangul :: Char -> Bool -isHangul c = n >= hangulFirst && n <= hangulLast - where n = ord c --} - -genUnicodeVersion :: FilePath -> IO () -genUnicodeVersion outdir = do - version <- catch - (getEnv "UNICODE_VERSION") - (\(_ :: IOException) -> return "") - Stream.fold f (Stream.fromList (body version)) - where - moduleName = "GHC.Internal.Unicode.Version" - f = moduleFileEmitter Nothing outdir - (moduleName, \_ -> Fold.foldMap (<> "\n")) - body :: String -> [String] - body version = - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(unicodeVersion)" - , "where" - , "" - , "import {-# SOURCE #-} GHC.Internal.Data.Version" - , "" - , "-- | Version of Unicode standard used by @base@:" - , "-- [" <> version <> "](https://www.unicode.org/versions/Unicode" <> version <> "/)." - , "--" - , "-- @since base-4.15.0.0" - , "unicodeVersion :: Version" - , "unicodeVersion = makeVersion [" <> mkVersion version <> "]" ] - mkVersion = foldr (\c acc -> case c of {'.' -> ',':' ':acc; _ -> c:acc}) mempty - -------------------------------------------------------------------------------- --- Parsers -------------------------------------------------------------------------------- - -------------------------------------------------------------------------------- --- Parsing UnicodeData.txt -------------------------------------------------------------------------------- - -genGeneralCategoryModule - :: Monad m - => String - -> Fold m DetailedChar String -genGeneralCategoryModule moduleName = - done <$> Fold.foldl' step initial - - where - - -- (categories, expected char) - initial = ([], '\0') - - step (acc, p) a = if p < _char a - -- Fill missing char entry with default category Cn - -- See: https://www.unicode.org/reports/tr44/#Default_Values_Table - then step (Cn : acc, succ p) a - -- Regular entry - else (_generalCategory a : acc, succ (_char a)) - - done (acc, _) = unlines - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(generalCategory)" - , "where" - , "" - , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" - , "import GHC.Internal.Unicode.Bits (lookupIntN)" - , "" - , genEnumBitmap "generalCategory" Cn (reverse acc) - ] - -readDecomp :: String -> (Maybe DecompType, Decomp) -readDecomp s = - if null wrds - then (Nothing, DCSelf) - else decmps wrds - - where - - decmps [] = error "Unreachable flow point" - decmps y@(x:xs) = - case dtmap x of - DTCanonical -> (,) (Just DTCanonical) (readCP y) - other -> (,) (Just other) (readCP xs) - - wrds = words s - - readCP ws = DC $ map readCodePoint ws - - dtmap "" = DTCompat - dtmap "" = DTCircle - dtmap "" = DTFinal - dtmap "" = DTFont - dtmap "" = DTFraction - dtmap "" = DTInitial - dtmap "" = DTIsolated - dtmap "" = DTMedial - dtmap "" = DTNarrow - dtmap "" = DTNoBreak - dtmap "" = DTSmall - dtmap "" = DTSquare - dtmap "" = DTSub - dtmap "" = DTSuper - dtmap "" = DTVertical - dtmap "" = DTWide - dtmap _ = DTCanonical - -{- [NOTE] Disabled generators - -filterNonHangul :: Monad m => Fold m DetailedChar a -> Fold m DetailedChar a -filterNonHangul = Fold.filter (not . isHangul . _char) - -filterDecomposableType :: - Monad m => DType -> Fold m DetailedChar a -> Fold m DetailedChar a -filterDecomposableType dtype = - Fold.filter ((/= DCSelf) . _decomposition) - . Fold.filter (predicate . _decompositionType) - - where - - predicate = - case dtype of - Canonical -> (== Just DTCanonical) - Kompat -> const True - -genDecomposableModule :: - Monad m => String -> DType -> Fold m DetailedChar String -genDecomposableModule moduleName dtype = - filterNonHangul - $ filterDecomposableType dtype $ done <$> Fold.foldl' step initial - - where - - initial = [] - - step st a = ord (_char a) : st - - done st = - unlines - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(isDecomposable)" - , "where" - , "" - , "import Data.Char (ord)" - , "import GHC.Internal.Unicode.Bits (lookupBit64)" - , "" - , genBitmap "isDecomposable" (reverse st) - ] - -genCombiningClassModule :: Monad m => String -> Fold m DetailedChar String -genCombiningClassModule moduleName = - Fold.filter (\dc -> _combiningClass dc /= 0) - $ done <$> Fold.foldl' step initial - - where - - initial = ([], []) - - step (st1, st2) a = (genCombiningClassDef a : st1, ord (_char a) : st2) - - done (st1, st2) = - unlines - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(combiningClass, isCombining)" - , "where" - , "" - , "import Data.Char (ord)" - , "import GHC.Internal.Unicode.Bits (lookupBit64)" - , "" - , "combiningClass :: Char -> Int" - , unlines (reverse st1) - , "combiningClass _ = 0\n" - , "" - , genBitmap "isCombining" (reverse st2) - ] - - genCombiningClassDef dc = - "combiningClass " - <> show (_char dc) <> " = " <> show (_combiningClass dc) - -genDecomposeDefModule :: - Monad m - => String - -> [String] - -> [String] - -> DType - -> (Int -> Bool) - -> Fold m DetailedChar String -genDecomposeDefModule moduleName before after dtype pred = - Fold.filter (pred . ord . _char) - $ filterNonHangul - $ filterDecomposableType dtype $ done <$> Fold.foldl' step initial - - where - - decomposeChar c DCSelf = [c] - decomposeChar _c (DC ds) = ds - - genHeader = - [ "{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(decompose)" - , "where" - , "" - ] - genSign = - [ "-- Note: this is a partial function we do not expect to call" - , "-- this if isDecomposable returns false." - , "{-# NOINLINE decompose #-}" - , "decompose :: Char -> [Char]" - ] - initial = [] - - step st dc = genDecomposeDef dc : st - - done st = - let body = mconcat [genHeader, before, genSign, reverse st, after] - in unlines body - - genDecomposeDef dc = - "decompose " - <> show (_char dc) - <> " = " <> show (decomposeChar (_char dc) (_decomposition dc)) - -genCompositionsModule :: - Monad m - => String - -> [Int] - -> [Int] - -> Fold m DetailedChar String -genCompositionsModule moduleName compExclu non0CC = - Fold.filter (not . flip elem compExclu . ord . _char) - $ filterNonHangul - $ Fold.filter (isDecompositionLen2 . _decomposition) - $ filterDecomposableType Canonical $ done <$> Fold.foldl' step initial - - where - - isDecompositionLen2 DCSelf = False - isDecompositionLen2 (DC ds) = length ds == 2 - - genComposePairDef name dc = - name - <> " " - <> show (head d01) - <> " " <> show (d01 !! 1) <> " = Just " <> show (_char dc) - - where - - d01 = decompPair dc - - decompPair dc = - case _decomposition dc of - DCSelf -> error "toCompFormat: DCSelf" - (DC ds) -> - if length ds == 2 - then ds - else error "toCompFormat: length /= 2" - - initial = ([], [], []) - - step (dec, sp, ss) dc = (dec1, sp1, ss1) - - where - - d01 = decompPair dc - d1Ord = ord $ d01 !! 1 - dec1 = genComposePairDef "compose" dc : dec - sp1 = - if d1Ord `notElem` non0CC - then genComposePairDef "composeStarters" dc : sp - else sp - ss1 = - if d1Ord `notElem` non0CC - then d1Ord : ss - else ss - - header = - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(compose, composeStarters, isSecondStarter)" - , "where" - , "" - , "import GHC.Internal.Base (Char, ord)" - , "import GHC.Internal.Unicode.Bits (lookupBit64)" - , "" - ] - - composePair decomps = - [ "{-# NOINLINE compose #-}" - , "compose :: Char -> Char -> Maybe Char" - , unlines decomps - , "compose _ _ = " <> "Nothing" <> "\n" - , "" - ] - - composeStarterPair starterPairs = - [ "composeStarters :: Char -> Char -> Maybe Char" - , unlines starterPairs - , "composeStarters _ _ = " <> "Nothing" <> "\n" - , "" - ] - - isSecondStarter secondStarters = - [genBitmap "isSecondStarter" secondStarters] - - done (dec, sp, ss) = - unlines - $ header - <> composePair (reverse dec) - <> composeStarterPair (reverse sp) - <> isSecondStarter (Set.toList (Set.fromList ss)) --} -genSimpleCaseMappingModule - :: Monad m - => String - -> String - -> (DetailedChar -> Maybe Char) - -> Fold m DetailedChar String -genSimpleCaseMappingModule moduleName funcName field = - done <$> Fold.foldl' step initial - - where - - genHeader = - [ "{-# LANGUAGE NoImplicitPrelude, LambdaCase #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(" <> funcName <> ")" - , "where" - , "" - , "import GHC.Internal.Base (Char)" - , "" - ] - genSign = - [ "{-# NOINLINE " <> funcName <> " #-}" - , funcName <> " :: Char -> Char" - , funcName <> " = \\case" - ] - initial = [] - - step ds dc = case mkEntry dc of - Nothing -> ds - Just d -> d : ds - - after = [" c -> c"] - - done st = - let body = mconcat [genHeader, genSign, reverse st, after] - in unlines body - - mkEntry dc = field dc <&> \c -> mconcat - [ " '\\x" - , showHexChar (_char dc) "' -> '\\x" - , showHexChar c "'" - ] - - showHexChar c = showHex (ord c) - -genCorePropertiesModule :: - Monad m => String -> (String -> Bool) -> Fold m (String, [Int]) String -genCorePropertiesModule moduleName isProp = - Fold.filter (\(name, _) -> isProp name) $ done <$> Fold.foldl' step initial - - where - - prop2FuncName x = "is" <> x - - initial = ([], []) - - step (props, bitmaps) (name, bits) = - (name : props, genBitmap (prop2FuncName name) bits : bitmaps) - - done (props, bitmaps) = unlines $ header props <> bitmaps - - header exports = - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(" <> unwords (intersperse "," (map prop2FuncName exports)) <> ")" - , "where" - , "" - , "import GHC.Internal.Base (Bool, Char, Ord(..), (&&), ord)" - , "import GHC.Internal.Unicode.Bits (lookupBit64)" - , "" - ] - -{- [NOTE] Disabled generator -genUnicode002TestResults :: Monad m => Fold m DetailedChar String -genUnicode002TestResults = done <$> Fold.foldl' step initial - - where - - header = "Code C P S U L A D" - -- (output, expected char) - initial = ([], '\0') - -- [TODO] Increase the number of tested char? - -- maxChar = '\xF0000' -- First codepoint of the last private use areas. - -- maxChar = '\xFFFF' -- Last codepoint of BMP. - maxChar = chr 6553 -- Value in GHC 9.2.2 base test - - step (acc, c) dc = if c > maxChar - then (acc, c) - else if c < _char dc - -- Fill missing char entry with default values - -- See: https://www.unicode.org/reports/tr44/#Default_Values_Table - then step (mkEntry (mkDefaultDetailedChar c) : acc, succ c) dc - -- Regular entry - else (mkEntry dc : acc, succ (_char dc)) - - done (acc, _) = unlines (header : reverse acc) - - mkEntry dc = mconcat - [ showCode (_char dc) - -- [TODO] General category - , showBool (isControl' dc) - , showBool (isPrint' dc) - , showBool (isSpace' dc) - -- [TODO] isSeparator - , showBool (isUpper' dc) - , showBool (isLower' dc) - , showBool (isAlpha' dc) - -- [TODO] isAlphaNum - , showBool (isDigit' dc) - -- [TODO] isNumber - -- [TODO] isMark - -- [TODO] isPunctuation - -- [TODO] isSymbol - ] - - padding = length (show (ord maxChar)) - showCode c = take padding (shows (ord c) (repeat ' ')) - -- [TODO] use showHex - -- showCode c = - -- let code = showHex (ord c) mempty - -- in replicate (padding - length code) '0' <> code - showBool b = if b then " T" else " F" - - -- [NOTE] The following functions replicates Data.Char. Keep them up to date! - - isControl' dc = case _generalCategory dc of - Cc -> True -- Control - _ -> False - - isPrint' dc = case _generalCategory dc of - Zl -> False -- LineSeparator - Zp -> False -- ParagraphSeparator - Cc -> False -- Control - Cf -> False -- Format - Cs -> False -- Surrogate - Co -> False -- PrivateUse - Cn -> False -- NotAssigned - _ -> True - - isSpace' dc = case _char dc of - '\t' -> True - '\n' -> True - '\v' -> True - '\f' -> True - '\r' -> True - _ -> case _generalCategory dc of - Zs -> True -- Space - _ -> False - - isUpper' dc = case _generalCategory dc of - Lu -> True -- UppercaseLetter - Lt -> True -- TitlecaseLetter - _ -> False - - isLower' dc = case _generalCategory dc of - Ll -> True -- LowercaseLetter - _ -> False - - isAlpha' dc = case _generalCategory dc of - Lu -> True -- UppercaseLetter - Ll -> True -- LowercaseLetter - Lt -> True -- TitlecaseLetter - Lm -> True -- ModifierLetter - Lo -> True -- OtherLetter - _ -> False - - isDigit' dc = let c = _char dc - in (fromIntegral (ord c - ord '0') :: Word) <= 9 --} - -------------------------------------------------------------------------------- --- Parsing property files -------------------------------------------------------------------------------- - -type PropertyLine = (String, [Int]) - -trim :: String -> String -trim = takeWhile (not . isSpace) . dropWhile isSpace - -emptyPropertyLine :: PropertyLine -emptyPropertyLine = ("", []) - -combinePropertyLines :: PropertyLine -> PropertyLine -> PropertyLine -combinePropertyLines t1@(n1, o1) t2@(n2, o2) - | n1 == "" = t2 - | n2 == "" = t1 - | n1 == n2 = (n1, o1 <> o2) - | otherwise = error $ "Cannot group " <> n1 <> " with " <> n2 - -parsePropertyLine :: String -> PropertyLine -parsePropertyLine ln - | null ln = emptyPropertyLine - | head ln == '#' = emptyPropertyLine - | otherwise = parseLineJ ln - - where - - parseLineJ :: String -> (String, [Int]) - parseLineJ line = - let (rangeLn, line1) = span (/= ';') line - propLn = takeWhile (/= '#') (tail line1) - in (trim propLn, parseRange (trim rangeLn)) - - parseRange :: String -> [Int] - parseRange rng = - if '.' `elem` rng - then let low = read $ "0x" <> takeWhile (/= '.') rng - high = - read $ "0x" <> reverse (takeWhile (/= '.') (reverse rng)) - in [low .. high] - else [read $ "0x" <> rng] - -isDivider :: String -> Bool -isDivider x = x == "# ================================================" - -parsePropertyLines :: (Monad m) => Stream m String -> Stream m PropertyLine -parsePropertyLines = - Stream.splitOn isDivider - $ Fold.lmap parsePropertyLine - $ Fold.foldl' combinePropertyLines emptyPropertyLine - --- | A range entry in @UnicodeData.txt at . -data UnicodeDataRange - = SingleCode !DetailedChar - -- ^ Regular entry for one code point - | FirstCode !String !DetailedChar - -- ^ A partial range for entry with a name as: @\@ - | CompleteRange !String !DetailedChar !DetailedChar - -- ^ A complete range, requiring 2 continuous entries with respective names: - -- - -- * @\@ - -- * @\@ - -{-| Parse UnicodeData.txt lines - -Parse ranges according to https://www.unicode.org/reports/tr44/#Code_Point_Ranges. - -__Note:__ this does /not/ fill missing char entries, -i.e. entries with no explicit entry nor within a range. --} -parseUnicodeDataLines :: forall m. (Monad m) => Stream m String -> Stream m DetailedChar -parseUnicodeDataLines - = Stream.unfoldMany (Unfold.unfoldr unitToRange) - . Stream.foldMany ( Fold.lmap parseDetailedChar - $ Fold.foldt' step initial id) - - where - - step :: Maybe UnicodeDataRange - -> DetailedChar - -> Fold.Step (Maybe UnicodeDataRange) (Maybe UnicodeDataRange) - step Nothing dc = case span (/= ',') (_name dc) of - (range, ", First>") -> Fold.Partial (Just (FirstCode range dc)) - _ -> Fold.Done (Just (SingleCode dc)) - step (Just (FirstCode range1 dc1)) dc2 = case span (/= ',') (_name dc2) of - (range2, ", Last>") -> if range1 == range2 && _char dc1 < _char dc2 - then Fold.Done (Just (CompleteRange range1 dc1 dc2)) - else error $ "Cannot create range: incompatible ranges" <> show (dc1, dc2) - _ -> error $ "Cannot create range: missing entry correspong to: " <> show range1 - step _ _ = error "impossible case" - - initial :: Fold.Step (Maybe UnicodeDataRange) (Maybe UnicodeDataRange) - initial = Fold.Partial Nothing - - unitToRange :: Maybe UnicodeDataRange -> Maybe (DetailedChar, Maybe UnicodeDataRange) - unitToRange = fmap $ \case - SingleCode dc -> (dc, Nothing) - FirstCode _ dc -> error $ "Incomplete range: " <> show dc - CompleteRange range dc1 dc2 -> if _char dc1 < _char dc2 - -- [TODO] Create the proper name - then (dc1{_name="TODO"}, Just (CompleteRange range dc1{_char=succ (_char dc1)} dc2)) - else (dc2{_name="TODO"}, Nothing) - --- | Parse a single entry of @UnicodeData.txt@ -parseDetailedChar :: String -> DetailedChar -parseDetailedChar line = case splitWhen (== ';') line of - char - :name - :gc - :combining - :_bidi - :decomposition - :_decimal - :_digit - :_numeric - :_bidiM - :_uni1Name - :_iso - :sUpper - :sLower - :sTitle - :_ -> - let (dctype, dcval) = readDecomp decomposition - in DetailedChar - { _char = readCodePoint char - , _name = name - , _generalCategory = read gc - , _combiningClass = read combining - , _decompositionType = dctype - , _decomposition = dcval - , _simpleUppercaseMapping = readCodePointM sUpper - , _simpleLowercaseMapping = readCodePointM sLower - , _simpleTitlecaseMapping = readCodePointM sTitle - } - _ -> error ("Unsupported line: " <> line) - -------------------------------------------------------------------------------- --- Generation -------------------------------------------------------------------------------- - -readLinesFromFile :: String -> Stream IO String -readLinesFromFile file = - withFile file Sys.ReadMode - $ \h -> Handle.read h & Unicode.decodeUtf8 & Unicode.lines Fold.toList - - where - withFile file_ mode = - Stream.bracketIO (Sys.openFile file_ mode) (Sys.hClose) - - -moduleToFileName :: String -> String -moduleToFileName = map (\x -> if x == '.' then '/' else x) - -dirFromFileName :: String -> String -dirFromFileName = reverse . dropWhile (/= '/') . reverse - -data FileRecipe a - = ModuleRecipe - -- ^ A recipe to create a Haskell module file. - String - -- ^ Module name - (String -> Fold IO a String) - -- ^ Function that generate the module, given the module name. - | TestOutputRecipe - -- ^ A recipe to create a test output file. - String - -- ^ Test name - (Fold IO a String) - -- ^ Test output generator - --- ModuleRecipe is a tuple of the module name and a function that generates the --- module using the module name -type ModuleRecipe a = (String, String -> Fold IO a String) -type TestOutputRecipe a = (FilePath, Fold IO a String) - --- GeneratorRecipe is a list of ModuleRecipe -type GeneratorRecipe a = [FileRecipe a] - -moduleFileEmitter :: Maybe FilePath -> FilePath -> ModuleRecipe a -> Fold IO a () -moduleFileEmitter mfile outdir (modName, fldGen) = Fold.rmapM action $ fldGen modName - - where - - pretext version = case mfile of - Just file -> mconcat - [ "-- DO NOT EDIT: This file is automatically generated by the internal tool ucd2haskell,\n" - , "-- with data from: https://www.unicode.org/Public/" - , version - , "/ucd/" - , file - ,".\n\n" - ] - Nothing -> "-- DO NOT EDIT: This file is automatically generated by the internal tool ucd2haskell.\n\n" - outfile = outdir moduleToFileName modName <.> ".hs" - outfiledir = dirFromFileName outfile - action c = do - version <- - catch - (getEnv "UNICODE_VERSION") - (\(_ :: IOException) -> return "") - createDirectoryIfMissing True outfiledir - writeFile outfile (pretext version <> c) - -testOutputFileEmitter :: FilePath -> TestOutputRecipe a -> Fold IO a () -testOutputFileEmitter outdir (name, fldGen) = Fold.rmapM action fldGen - - where - - outfile = outdir "tests" name <.> ".stdout" - outfiledir = dirFromFileName outfile - action c - = createDirectoryIfMissing True outfiledir - *> writeFile outfile c - -runGenerator :: - FilePath - -> FilePath - -> (Stream IO String -> Stream IO a) - -> FilePath - -> GeneratorRecipe a - -> IO () -runGenerator indir file transformLines outdir recipes = - readLinesFromFile (indir <> file) & transformLines & Stream.fold combinedFld - - where - - generatedFolds = recipes <&> \case - ModuleRecipe name f -> moduleFileEmitter (Just file) outdir (name, f) - TestOutputRecipe name f -> testOutputFileEmitter outdir (name, f) - combinedFld = void $ Fold.distribute generatedFolds - -genModules :: String -> String -> [String] -> IO () -genModules indir outdir props = do - genUnicodeVersion outdir - - -- [NOTE] Disabled generator - -- compExclu <- - -- readLinesFromFile (indir <> "DerivedNormalizationProps.txt") - -- & parsePropertyLines - -- & Stream.find (\(name, _) -> name == "Full_Composition_Exclusion") - -- & fmap (snd . fromMaybe ("", [])) - - -- [NOTE] Disabled generator - -- non0CC <- - -- readLinesFromFile (indir <> "extracted/DerivedCombiningClass.txt") - -- & parsePropertyLines - -- & Stream.filter (\(name, _) -> name /= "0") - -- & Stream.map snd - -- & Stream.fold (Fold.foldl' (<>) []) - - runGenerator - indir - "UnicodeData.txt" - parseUnicodeDataLines - outdir - -- [NOTE] Disabled generators - -- [ uncurry ModuleRecipe compositions compExclu non0CC - -- , uncurry ModuleRecipe combiningClass - -- , uncurry ModuleRecipe decomposable - -- , uncurry ModuleRecipe decomposableK - -- , uncurry ModuleRecipe decompositions - -- , uncurry ModuleRecipe decompositionsK2 - -- , uncurry ModuleRecipe decompositionsK - [ uncurry ModuleRecipe generalCategory - , uncurry ModuleRecipe simpleUpperCaseMapping - , uncurry ModuleRecipe simpleLowerCaseMapping - , uncurry ModuleRecipe simpleTitleCaseMapping - -- , uncurry TestOutputRecipe unicode002Test - ] - - -- [NOTE] Disabled generator - -- runGenerator - -- indir - -- "PropList.txt" - -- parsePropertyLines - -- outdir - -- [ uncurry ModuleRecipe propList ] - - runGenerator - indir - "DerivedCoreProperties.txt" - parsePropertyLines - outdir - [ uncurry ModuleRecipe derivedCoreProperties ] - - where - - -- [NOTE] Disabled generator - -- propList = - -- ("GHC.Internal.Unicode.Char.PropList" - -- , (`genCorePropertiesModule` (`elem` props))) - - derivedCoreProperties = - ("GHC.Internal.Unicode.Char.DerivedCoreProperties" - , (`genCorePropertiesModule` (`elem` props))) - - -- [NOTE] Disabled generator - -- compositions exc non0 = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.Compositions" - -- , \m -> genCompositionsModule m exc non0) - - -- [NOTE] Disabled generator - -- combiningClass = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.CombiningClass" - -- , genCombiningClassModule) - - -- [NOTE] Disabled generator - -- decomposable = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.Decomposable" - -- , (`genDecomposableModule` Canonical)) - - -- [NOTE] Disabled generator - -- decomposableK = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.DecomposableK" - -- , (`genDecomposableModule` Kompat)) - - -- [NOTE] Disabled generator - -- decompositions = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.Decompositions" - -- , \m -> genDecomposeDefModule m [] [] Canonical (const True)) - - -- [NOTE] Disabled generator - -- decompositionsK2 = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.DecompositionsK2" - -- , \m -> genDecomposeDefModule m [] [] Kompat (>= 60000)) - - -- [NOTE] Disabled generator - -- decompositionsK = - -- let pre = ["import qualified " <> fst decompositionsK2 <> " as DK2", ""] - -- post = ["decompose c = DK2.decompose c"] - -- in ( "GHC.Internal.Unicode.Char.UnicodeData.DecompositionsK" - -- , \m -> genDecomposeDefModule m pre post Kompat (< 60000)) - - generalCategory = - ( "GHC.Internal.Unicode.Char.UnicodeData.GeneralCategory" - , genGeneralCategoryModule) - - simpleUpperCaseMapping = - ( "GHC.Internal.Unicode.Char.UnicodeData.SimpleUpperCaseMapping" - , \m -> genSimpleCaseMappingModule m "toSimpleUpperCase" _simpleUppercaseMapping) - - simpleLowerCaseMapping = - ( "GHC.Internal.Unicode.Char.UnicodeData.SimpleLowerCaseMapping" - , \m -> genSimpleCaseMappingModule m "toSimpleLowerCase" _simpleLowercaseMapping) - - simpleTitleCaseMapping = - ( "GHC.Internal.Unicode.Char.UnicodeData.SimpleTitleCaseMapping" - , \m -> genSimpleCaseMappingModule m "toSimpleTitleCase" _simpleTitlecaseMapping) - - -- unicode002Test = - -- ( "unicode002" - -- , genUnicode002TestResults) ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell.hs ===================================== @@ -2,14 +2,17 @@ -- Module : Main -- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers " -- Stability : internal -- module Main where -import WithCli (HasArguments(..), withCli) -import Parser.Text (genModules) +import qualified Data.ByteString.Char8 as B8 +import qualified Data.ByteString.Short as BS import GHC.Generics (Generic) +import WithCli (HasArguments(..), withCli) + +import UCD2Haskell.ModuleGenerators (genModules) data CLIOptions = CLIOptions @@ -20,7 +23,10 @@ data CLIOptions = deriving (Show, Generic, HasArguments) cliClient :: CLIOptions -> IO () -cliClient opts = genModules (input opts) (output opts) (core_prop opts) +cliClient opts = genModules + opts.input + opts.output + (BS.toShort . B8.pack <$> opts.core_prop) main :: IO () main = withCli cliClient ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell/ModuleGenerators.hs ===================================== @@ -0,0 +1,517 @@ +-- | +-- Module : UCD2Haskell.ModuleGenerators +-- Copyright : (c) 2020 Composewell Technologies and Contributors +-- (c) 2016-2017 Harendra Kumar +-- (c) 2014-2015 Antonio Nikishaev +-- (c) 2022-2024 Pierre Le Marre +-- License : BSD-3-Clause +-- Maintainer : The GHC Developers " +-- Stability : internal + +-- Code history: +-- +-- This code was adapted from https://github.com/composewell/unicode-data/ +-- (around commit c4aa52ed932ad8badf97296858932c3389b275b8) by Pierre Le Marre. +-- The original Unicode database parser was taken from +-- https://github.com/composewell/unicode-transforms but was completely +-- rewritten from scratch to parse from UCD text files instead of XML, only +-- some types remain the same. That code in turn was originally taken from +-- https://github.com/llelf/prose (Antonio Nikishaev) and heavily modified by +-- Harendra Kumar. +-- +module UCD2Haskell.ModuleGenerators (genModules) where + +import Control.Exception (catch, IOException) +import Data.Bits (Bits(..)) +import Data.Word (Word8) +import Data.Char (ord) +import Data.Functor ((<&>), ($>)) +import Data.List (intersperse, unfoldr) +import System.Directory (createDirectoryIfMissing) +import System.Environment (getEnv) +import System.FilePath ((), (<.>)) +import Data.String (IsString) +import Data.Foldable (Foldable(..)) + +import qualified Data.ByteString.Builder as BB +import qualified Data.ByteString as B +import qualified Data.ByteString.Lazy as BL +import qualified Data.ByteString.Short as BS + +import qualified Unicode.CharacterDatabase.Parser.Common as C +import qualified Unicode.CharacterDatabase.Parser.UnicodeData as UD +import qualified Unicode.CharacterDatabase.Parser.Properties.Multiple as P + +import Prelude hiding (pred) + +-------------------------------------------------------------------------------- +-- Helpers +-------------------------------------------------------------------------------- + +unlinesBB :: [BB.Builder] -> BB.Builder +unlinesBB = (<> "\n") . mconcat . intersperse "\n" + +unwordsBB :: [BB.Builder] -> BB.Builder +unwordsBB = mconcat . intersperse " " + +headerRule :: BB.Builder +headerRule = "-----------------------------------------------------------------------------" + +mkModuleHeader :: BB.Builder -> BB.Builder +mkModuleHeader modName = + unlinesBB + [ headerRule + , "-- |" + , "-- Module : " <> modName + , "-- License : BSD-3-Clause" + , "-- Maintainer : The GHC Developers " + , "-- Stability : internal" + , headerRule + ] + +genSignature :: BB.Builder -> BB.Builder +genSignature = (<> " :: Char -> Bool") + +-- | Check that var is between minimum and maximum of orderList +genRangeCheck :: BB.Builder -> [Int] -> BB.Builder +genRangeCheck var ordList = + var + <> " >= " + <> BB.intDec (minimum ordList) + <> " && " <> var <> " <= " <> BB.intDec (maximum ordList) + +genBitmap :: BB.Builder -> [Int] -> BB.Builder +genBitmap funcName ordList = + unlinesBB + [ "{-# INLINE " <> funcName <> " #-}" + , genSignature funcName + , funcName <> " = \\c -> let n = ord c in " + <> genRangeCheck "n" ordList <> " && lookupBit64 bitmap# n" + , " where" + , " bitmap# = \"" <> bitMapToAddrLiteral (positionsToBitMap ordList) "\"#" + ] + +positionsToBitMap :: [Int] -> [Bool] +positionsToBitMap = go 0 + + where + + go _ [] = [] + go i xxs@(x:xs) + | i < x = False : go (i + 1) xxs + | otherwise = True : go (i + 1) xs + +bitMapToAddrLiteral :: + -- | Values to encode + [Bool] -> + -- | String to append + BB.Builder -> + BB.Builder +bitMapToAddrLiteral bs cs = foldr encode cs (unfoldr mkChunks bs) + + where + + mkChunks :: [a] -> Maybe ([a], [a]) + mkChunks [] = Nothing + mkChunks xs = Just $ splitAt 8 xs + + encode :: [Bool] -> BB.Builder -> BB.Builder + encode chunk acc = BB.char7 '\\' <> BB.intDec (toByte (padTo8 chunk)) <> acc + + padTo8 :: [Bool] -> [Bool] + padTo8 xs + | length xs >= 8 = xs + | otherwise = xs <> replicate (8 - length xs) False + + toByte :: [Bool] -> Int + toByte xs = sum $ map (\i -> if xs !! i then 1 `shiftL` i else 0) [0..7] + +genEnumBitmap :: + forall a. (Bounded a, Enum a, Show a) => + -- | Function name + BB.Builder -> + -- | Default value + a -> + -- | List of values to encode + [a] -> + BB.Builder +genEnumBitmap funcName def as = unlinesBB + [ "{-# INLINE " <> funcName <> " #-}" + , funcName <> " :: Char -> Int" + , funcName <> " c = let n = ord c in if n >= " + <> BB.intDec (length as) + <> " then " + <> BB.intDec (fromEnum def) + <> " else lookup_bitmap n" + + , "{-# NOINLINE lookup_bitmap #-}" + , "lookup_bitmap :: Int -> Int" + , "lookup_bitmap n = lookupIntN bitmap# n" + , " where" + , " bitmap# = \"" <> enumMapToAddrLiteral as "\"#" + ] + +{-| Encode a list of values as a byte map, using their 'Enum' instance. + +__Note:__ 'Enum' instance must respect the following: + +* @fromEnum minBound >= 0x00@ +* @fromEnum maxBound <= 0xff@ +-} +enumMapToAddrLiteral :: + forall a. (Bounded a, Enum a, Show a) => + -- | Values to encode + [a] -> + -- | String to append + BB.Builder -> + BB.Builder +enumMapToAddrLiteral xs cs = foldr go cs xs + + where + + go :: a -> BB.Builder -> BB.Builder + go x acc = BB.char7 '\\' <> BB.word8Dec (toWord8 x) <> acc + + toWord8 :: a -> Word8 + toWord8 a = let w = fromEnum a in if 0 <= w && w <= 0xff + then fromIntegral w + else error $ "Cannot convert to Word8: " <> show a + +genUnicodeVersion :: FilePath -> IO () +genUnicodeVersion outdir = do + version <- catch + (getEnv "UNICODE_VERSION") + (\(_ :: IOException) -> return "") + runFold f [body version] + where + moduleName :: (IsString a) => a + moduleName = "GHC.Internal.Unicode.Version" + f = moduleFileEmitter Nothing outdir + (moduleName, \_ -> Fold (\_ x -> x) mempty id) + body :: String -> BB.Builder + body version = unlinesBB + [ "{-# LANGUAGE NoImplicitPrelude #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(unicodeVersion)" + , "where" + , "" + , "import {-# SOURCE #-} GHC.Internal.Data.Version" + , "" + , "-- | Version of Unicode standard used by @base@:" + , "-- [" <> BB.string7 version <> "](https://www.unicode.org/versions/Unicode" <> BB.string7 version <> "/)." + , "--" + , "-- @since base-4.15.0.0" + , "unicodeVersion :: Version" + , "unicodeVersion = makeVersion [" <> mkVersion version <> "]" ] + mkVersion = foldMap (\c -> case c of {'.' -> BB.char7 ',' <> BB.char7 ' '; _ -> BB.char7 c}) + +-------------------------------------------------------------------------------- +-- Fold +-------------------------------------------------------------------------------- + +data Fold a b = forall s. Fold + { _step :: s -> a -> s + , _initial :: s + , _final :: s -> b } + +data Pair a b = Pair !a !b + +teeWith :: (a -> b -> c) -> Fold x a -> Fold x b -> Fold x c +teeWith f (Fold stepL initialL finalL) (Fold stepR initialR finalR) = + Fold step initial final + where + step (Pair sL sR) x = Pair (stepL sL x) (stepR sR x) + initial = Pair initialL initialR + final (Pair sL sR) = f (finalL sL) (finalR sR) + +distribute :: [Fold a b] -> Fold a [b] +distribute = foldr (teeWith (:)) (Fold const () (const [])) + +rmapFold :: (b -> c) -> Fold a b -> Fold a c +rmapFold f (Fold step initial final) = Fold step initial (f . final) + +runFold :: Fold a b -> [a] -> b +runFold (Fold step initial final) = final . foldl' step initial + +-------------------------------------------------------------------------------- +-- Modules generators +-------------------------------------------------------------------------------- + +data GeneralCategoryAcc = GeneralCategoryAcc + { _categories :: ![UD.GeneralCategory] + , _expectedChar :: !Char + } + +genGeneralCategoryModule :: BB.Builder -> Fold UD.Entry BB.Builder +genGeneralCategoryModule moduleName = Fold step initial done + + where + + -- (categories, expected char) + initial = GeneralCategoryAcc [] '\0' + + step (GeneralCategoryAcc acc p) e@(UD.Entry r d) + | p < r.start + -- Fill missing char entry with default category Cn + -- See: https://www.unicode.org/reports/tr44/#Default_Values_Table + = step (GeneralCategoryAcc (replicate (ord r.start - ord p) UD.Cn <> acc) r.start) e + -- Regular entry + | otherwise = case r of + C.SingleChar ch -> GeneralCategoryAcc + (d.generalCategory : acc) + (succ ch) + C.CharRange ch1 ch2 -> GeneralCategoryAcc + (replicate (ord ch2 - ord ch1 + 1) d.generalCategory <> acc) + (succ ch2) + + done (GeneralCategoryAcc acc _) = unlinesBB + [ "{-# LANGUAGE NoImplicitPrelude #-}" + , "{-# LANGUAGE MagicHash #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(generalCategory)" + , "where" + , "" + , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" + , "import GHC.Internal.Unicode.Bits (lookupIntN)" + , "" + , genEnumBitmap "generalCategory" UD.Cn (reverse acc) + ] + +genSimpleCaseMappingModule + :: BB.Builder + -> BB.Builder + -> (UD.CharDetails -> Maybe Char) + -> Fold UD.Entry BB.Builder +genSimpleCaseMappingModule moduleName funcName field = + Fold step initial done + + where + + genHeader = + [ "{-# LANGUAGE NoImplicitPrelude, LambdaCase #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(" <> funcName <> ")" + , "where" + , "" + , "import GHC.Internal.Base (Char)" + , "" + ] + genSign = + [ "{-# NOINLINE " <> funcName <> " #-}" + , funcName <> " :: Char -> Char" + , funcName <> " = \\case" + ] + initial = [] + + step ds dc = case mkEntry dc of + Nothing -> ds + Just d -> d : ds + + after = [" c -> c"] + + done st = + let body = mconcat [genHeader, genSign, reverse st, after] + in unlinesBB body + + mkEntry (UD.Entry r dc) = case r of + C.SingleChar ch -> field dc <&> \c -> mconcat + [ " '\\x" + , showHexChar ch + , "' -> '\\x" + , showHexChar c + , "'" + ] + C.CharRange{} -> field dc $> error ("genSimpleCaseMappingModule: unexpected char range: " <> show r) + + showHexChar c = BB.wordHex (fromIntegral (ord c)) + +data PropertiesAcc = PropertiesAcc + { _properties :: ![BS.ShortByteString] + , _bitmaps :: ![BB.Builder] + , _currentBitmap :: ![[Int]] } + +genCorePropertiesModule :: + BB.Builder -> (BS.ShortByteString -> Bool) -> Fold P.Entry BB.Builder +genCorePropertiesModule moduleName isProp = Fold step initial done + where + prop2FuncName x = "is" <> BB.shortByteString x + + initial = PropertiesAcc [] [] [] + + step acc@(PropertiesAcc props bitmaps bits) P.Entry{..} + | not (isProp property) = acc -- property filtered out + | otherwise = case props of + prop' : _ + | prop' == property -> PropertiesAcc props bitmaps (rangeToBits range : bits) + | otherwise -> PropertiesAcc + { _properties = property : props + , _bitmaps = genBitmap' prop' bits : bitmaps + , _currentBitmap = [rangeToBits range] } + _ -> PropertiesAcc [property] bitmaps [rangeToBits range] + + rangeToBits = \case + C.SingleChar ch -> [ord ch] + C.CharRange ch1 ch2 -> [ord ch1 .. ord ch2] + + genBitmap' prop bits = genBitmap (prop2FuncName prop) (mconcat (reverse bits)) + + done (PropertiesAcc props bitmaps bits) = unlinesBB (header props <> bitmaps') + where + lastProp = case props of + prop : _ -> prop + [] -> error "impossible" + bitmaps' = genBitmap' lastProp bits : bitmaps + + header exports = + [ "{-# LANGUAGE NoImplicitPrelude #-}" + , "{-# LANGUAGE MagicHash #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(" <> unwordsBB (intersperse "," (map prop2FuncName exports)) <> ")" + , "where" + , "" + , "import GHC.Internal.Base (Bool, Char, Ord(..), (&&), ord)" + , "import GHC.Internal.Unicode.Bits (lookupBit64)" + , "" + ] + +-------------------------------------------------------------------------------- +-- Generation +-------------------------------------------------------------------------------- + +moduleToFileName :: String -> String +moduleToFileName = map (\x -> if x == '.' then '/' else x) + +dirFromFileName :: String -> String +dirFromFileName = reverse . dropWhile (/= '/') . reverse + +data FileRecipe a + = ModuleRecipe + -- ^ A recipe to create a Haskell module file. + String + -- ^ Module name + (BB.Builder -> Fold a BB.Builder) + -- ^ Function that generate the module, given the module name. + | TestOutputRecipe + -- ^ A recipe to create a test output file. + String + -- ^ Test name + (Fold a BB.Builder) + -- ^ Test output generator + +-- ModuleRecipe is a tuple of the module name and a function that generates the +-- module using the module name +type ModuleRecipe a = (String, BB.Builder -> Fold a BB.Builder) +type TestOutputRecipe a = (FilePath, Fold a BB.Builder) + +-- GeneratorRecipe is a list of ModuleRecipe +type GeneratorRecipe a = [FileRecipe a] + +moduleFileEmitter :: Maybe FilePath -> FilePath -> ModuleRecipe a -> Fold a (IO ()) +moduleFileEmitter mfile outdir (modName, fldGen) = rmapFold action $ fldGen (BB.string7 modName) + + where + + pretext version = case mfile of + Just file -> mconcat + [ "-- DO NOT EDIT: This file is automatically generated by the internal tool ucd2haskell,\n" + , "-- with data from: https://www.unicode.org/Public/" + , BB.string7 version + , "/ucd/" + , BB.string7 file + ,".\n\n" + ] + Nothing -> "-- DO NOT EDIT: This file is automatically generated by the internal tool ucd2haskell.\n\n" + outfile = outdir moduleToFileName modName <.> ".hs" + outfiledir = dirFromFileName outfile + action c = do + version <- + catch + (getEnv "UNICODE_VERSION") + (\(_ :: IOException) -> return "") + createDirectoryIfMissing True outfiledir + B.writeFile outfile (BL.toStrict (BB.toLazyByteString (pretext version <> c))) + +testOutputFileEmitter :: FilePath -> TestOutputRecipe a -> Fold a (IO ()) +testOutputFileEmitter outdir (name, fldGen) = rmapFold action fldGen + + where + + outfile = outdir "tests" name <.> ".stdout" + outfiledir = dirFromFileName outfile + action c + = createDirectoryIfMissing True outfiledir + *> B.writeFile outfile (BL.toStrict (BB.toLazyByteString c)) + +runGenerator :: + FilePath + -> FilePath + -> (B.ByteString -> [a]) + -> FilePath + -> GeneratorRecipe a + -> IO () +runGenerator indir file transformLines outdir recipes = do + raw <- B.readFile (indir <> file) + sequence_ (runFold combinedFld (transformLines raw)) + + where + + generatedFolds = recipes <&> \case + ModuleRecipe name f -> moduleFileEmitter (Just file) outdir (name, f) + TestOutputRecipe name f -> testOutputFileEmitter outdir (name, f) + combinedFld = distribute generatedFolds + +genModules :: FilePath -> FilePath -> [BS.ShortByteString] -> IO () +genModules indir outdir props = do + genUnicodeVersion outdir + + runGenerator + indir + "UnicodeData.txt" + UD.parse + outdir + [ generalCategory + , simpleUpperCaseMapping + , simpleLowerCaseMapping + , simpleTitleCaseMapping + ] + + runGenerator + indir + "DerivedCoreProperties.txt" + P.parse + outdir + [ derivedCoreProperties ] + + where + + derivedCoreProperties = ModuleRecipe + "GHC.Internal.Unicode.Char.DerivedCoreProperties" + (`genCorePropertiesModule` (`elem` props)) + + generalCategory = ModuleRecipe + "GHC.Internal.Unicode.Char.UnicodeData.GeneralCategory" + genGeneralCategoryModule + + simpleUpperCaseMapping = ModuleRecipe + "GHC.Internal.Unicode.Char.UnicodeData.SimpleUpperCaseMapping" + (\m -> genSimpleCaseMappingModule m "toSimpleUpperCase" UD.simpleUpperCaseMapping) + + simpleLowerCaseMapping = ModuleRecipe + "GHC.Internal.Unicode.Char.UnicodeData.SimpleLowerCaseMapping" + (\m -> genSimpleCaseMappingModule m "toSimpleLowerCase" UD.simpleLowerCaseMapping) + + simpleTitleCaseMapping = ModuleRecipe + "GHC.Internal.Unicode.Char.UnicodeData.SimpleTitleCaseMapping" + (\m -> genSimpleCaseMappingModule m "toSimpleTitleCase" UD.simpleTitleCaseMapping) ===================================== libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal ===================================== @@ -1,6 +1,6 @@ cabal-version: 2.2 name: ucd2haskell -version: 0.3.0 +version: 0.4.0 synopsis: Converter from Unicode character database to Haskell. description: The Haskell data structures are generated programmatically from the @@ -10,12 +10,12 @@ description: license: BSD-3-Clause license-file: LICENSE author: Composewell Technologies and Contributors -maintainer: streamly at composewell.com -copyright: 2020 Composewell Technologies and Contributors +maintainer: The GHC Developers +bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new category: Data,Text,Unicode stability: Experimental build-type: Simple -tested-with: GHC==9.2.2 +tested-with: GHC==9.8.2 extra-source-files: README.md @@ -23,18 +23,14 @@ extra-source-files: common default-extensions default-extensions: - BangPatterns DeriveGeneric - MagicHash - RecordWildCards - ScopedTypeVariables - TupleSections - FlexibleContexts - - -- Experimental, may lead to issues DeriveAnyClass - TemplateHaskell - UnboxedTuples + ExistentialQuantification + LambdaCase + OverloadedStrings + OverloadedRecordDot + ScopedTypeVariables + RecordWildCards common compile-options ghc-options: -Wall @@ -42,21 +38,20 @@ common compile-options -fwarn-incomplete-record-updates -fwarn-incomplete-uni-patterns -fwarn-tabs - default-language: Haskell2010 + default-language: GHC2021 executable ucd2haskell import: default-extensions, compile-options - default-language: Haskell2010 ghc-options: -O2 hs-source-dirs: exe main-is: UCD2Haskell.hs - other-modules: Parser.Text + other-modules: UCD2Haskell.ModuleGenerators build-depends: - base >= 4.7 && < 4.20 - , streamly-core >= 0.2.2 && < 0.3 - , streamly >= 0.10 && < 0.11 - , split >= 0.2.3 && < 0.3 - , getopt-generics >= 0.13 && < 0.14 - , containers >= 0.5 && < 0.7 - , directory >= 1.3.6 && < 1.3.8 - , filepath >= 1.4.2 && < 1.5 + base >= 4.7 && < 5 + , bytestring >= 0.11 && < 0.13 + , containers >= 0.5 && < 0.7 + , directory >= 1.3.6 && < 1.3.8 + , filepath >= 1.4.2 && < 1.5 + , getopt-generics >= 0.13 && < 0.14 + , split >= 0.2.3 && < 0.3 + , unicode-data-parser >= 0.2.0 && < 0.4 ===================================== utils/haddock/CONTRIBUTING.md ===================================== @@ -28,6 +28,17 @@ Then, run the following command from the top-level: $ ./hadrian/build -j --flavour=Quick --freeze1 _build/stage1/bin/haddock ``` +### Running the test suites + +Currently, this cannot be done with hadrian but has to be done with a +`cabal-install` built from `master`. + +``` +cabal test -w /_build/stage1/bin/ghc +``` + +For more details, see https://gitlab.haskell.org/ghc/ghc/-/issues/24976. + ## Working with the codebase The project provides a Makefile with rules to accompany you during development: ===================================== utils/haddock/cabal.project ===================================== @@ -1,5 +1,3 @@ -with-compiler: ghc-9.7 - packages: ./ ./haddock-api ./haddock-library View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/565f6192ef575d484f0448b715f09c7c83eda45e...912181bdccd99a2902fe26902881f151123ba3b8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/565f6192ef575d484f0448b715f09c7c83eda45e...912181bdccd99a2902fe26902881f151123ba3b8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 02:03:56 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Thu, 13 Jun 2024 22:03:56 -0400 Subject: [Git][ghc/ghc][wip/fabu/T24026-early-reject-type-failing-rules] compiler: Rejects RULES whose LHS immediately fails to type-check Message-ID: <666ba50c119b5_3e6ca225c676c10402b@gitlab.mail> Fabricio Nascimento pushed to branch wip/fabu/T24026-early-reject-type-failing-rules at Glasgow Haskell Compiler / GHC Commits: 0cb8c8ff by Fabricio de Sousa Nascimento at 2024-06-14T10:49:31+09:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - 7 changed files: - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/Tc/Gen/Rule.hs - + testsuite/tests/typecheck/T24026/T24026a.hs - + testsuite/tests/typecheck/T24026/T24026a.stderr - + testsuite/tests/typecheck/T24026/T24026b.hs - + testsuite/tests/typecheck/T24026/T24026b.stderr - + testsuite/tests/typecheck/T24026/all.T Changes: ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -1031,9 +1031,12 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs extra_bndrs = scopedSort extra_tvs ++ extra_dicts where extra_tvs = [ v | v <- extra_vars, isTyVar v ] + + -- isEvVar: this includes coercions, matching what + -- happens in `split_lets` (isDictId, isCoVar) extra_dicts = - [ mkLocalId (localiseName (idName d)) ManyTy (idType d) - | d <- extra_vars, isDictId d ] + [ mkLocalIdOrCoVar (localiseName (idName d)) ManyTy (idType d) + | d <- extra_vars, isEvVar d ] extra_vars = [ v | v <- exprsFreeVarsList args ===================================== compiler/GHC/Tc/Gen/Rule.hs ===================================== @@ -108,11 +108,13 @@ tcRules decls = mapM (wrapLocMA tcRuleDecls) decls tcRuleDecls :: RuleDecls GhcRn -> TcM (RuleDecls GhcTc) tcRuleDecls (HsRules { rds_ext = src , rds_rules = decls }) - = do { tc_decls <- mapM (wrapLocMA tcRule) decls + = do { maybe_tc_decls <- mapM (wrapLocMA tcRule) decls + ; let tc_decls = [L loc rule | (L loc (Just rule)) <- maybe_tc_decls] ; return $ HsRules { rds_ext = src , rds_rules = tc_decls } } -tcRule :: RuleDecl GhcRn -> TcM (RuleDecl GhcTc) + +tcRule :: RuleDecl GhcRn -> TcM (Maybe (RuleDecl GhcTc)) tcRule (HsRule { rd_ext = ext , rd_name = rname@(L _ name) , rd_act = act @@ -181,14 +183,23 @@ tcRule (HsRule { rd_ext = ext ; (rhs_implic, rhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs rhs_wanted ; emitImplications (lhs_implic `unionBags` rhs_implic) - ; return $ HsRule { rd_ext = ext + + -- The error will be reported when lhs_implic is solved. But meanwhile we should drop + -- this (ill-typed) rule entirely; with `-fdefer-type-errors`, we will proceed with + -- compilation regardless of the error, and an ill-typed LHS may cause follow-on + -- errors (#24026) + ; if anyBag insolubleImplic lhs_implic + then + return Nothing -- The RULE LHS does not type-check and will be dropped. + else + return . Just $ HsRule { rd_ext = ext , rd_name = rname , rd_act = act , rd_tyvs = ty_bndrs -- preserved for ppr-ing , rd_tmvs = map (noLocA . RuleBndr noAnn . noLocA) (qtkvs ++ tpl_ids) , rd_lhs = mkHsDictLet lhs_binds lhs' - , rd_rhs = mkHsDictLet rhs_binds rhs' } } + , rd_rhs = mkHsDictLet rhs_binds rhs' }} generateRuleConstraints :: FastString -> Maybe [LHsTyVarBndr () GhcRn] -> [LRuleBndr GhcRn] ===================================== testsuite/tests/typecheck/T24026/T24026a.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026a where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026a.stderr ===================================== @@ -0,0 +1,9 @@ +T24026a.hs:4:11: warning: [GHC-95396] [-Winline-rule-shadowing (in -Wdefault)] + Rule "f" may never fire because ‘f’ might inline first + Suggested fix: Add an INLINE[n] or NOINLINE[n] pragma for ‘f’ + +T24026a.hs:4:37: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/T24026b.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026b where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026b.stderr ===================================== @@ -0,0 +1,5 @@ +T24026b.hs:4:37: error: [GHC-83865] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/all.T ===================================== @@ -0,0 +1,2 @@ +test('T24026a', normal, compile, ['-dlint -fdefer-type-errors']) +test('T24026b', normal, compile_fail, ['']) \ No newline at end of file View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0cb8c8ff9f474f70f1bdeb3c3e65175ae73851ad -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0cb8c8ff9f474f70f1bdeb3c3e65175ae73851ad You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 02:07:17 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Thu, 13 Jun 2024 22:07:17 -0400 Subject: [Git][ghc/ghc][wip/fabu/T24026-early-reject-type-failing-rules] compiler: Rejects RULES whose LHS immediately fails to type-check Message-ID: <666ba5d5b1f76_3e6ca2273673c105075@gitlab.mail> Fabricio Nascimento pushed to branch wip/fabu/T24026-early-reject-type-failing-rules at Glasgow Haskell Compiler / GHC Commits: 2d96f436 by Fabricio de Sousa Nascimento at 2024-06-14T11:07:00+09:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - 7 changed files: - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/Tc/Gen/Rule.hs - + testsuite/tests/typecheck/T24026/T24026a.hs - + testsuite/tests/typecheck/T24026/T24026a.stderr - + testsuite/tests/typecheck/T24026/T24026b.hs - + testsuite/tests/typecheck/T24026/T24026b.stderr - + testsuite/tests/typecheck/T24026/all.T Changes: ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -1031,9 +1031,12 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs extra_bndrs = scopedSort extra_tvs ++ extra_dicts where extra_tvs = [ v | v <- extra_vars, isTyVar v ] + + -- isEvVar: this includes coercions, matching what + -- happens in `split_lets` (isDictId, isCoVar) extra_dicts = - [ mkLocalId (localiseName (idName d)) ManyTy (idType d) - | d <- extra_vars, isDictId d ] + [ mkLocalIdOrCoVar (localiseName (idName d)) ManyTy (idType d) + | d <- extra_vars, isEvVar d ] extra_vars = [ v | v <- exprsFreeVarsList args ===================================== compiler/GHC/Tc/Gen/Rule.hs ===================================== @@ -108,11 +108,13 @@ tcRules decls = mapM (wrapLocMA tcRuleDecls) decls tcRuleDecls :: RuleDecls GhcRn -> TcM (RuleDecls GhcTc) tcRuleDecls (HsRules { rds_ext = src , rds_rules = decls }) - = do { tc_decls <- mapM (wrapLocMA tcRule) decls + = do { maybe_tc_decls <- mapM (wrapLocMA tcRule) decls + ; let tc_decls = [L loc rule | (L loc (Just rule)) <- maybe_tc_decls] ; return $ HsRules { rds_ext = src , rds_rules = tc_decls } } -tcRule :: RuleDecl GhcRn -> TcM (RuleDecl GhcTc) + +tcRule :: RuleDecl GhcRn -> TcM (Maybe (RuleDecl GhcTc)) tcRule (HsRule { rd_ext = ext , rd_name = rname@(L _ name) , rd_act = act @@ -181,7 +183,16 @@ tcRule (HsRule { rd_ext = ext ; (rhs_implic, rhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs rhs_wanted ; emitImplications (lhs_implic `unionBags` rhs_implic) - ; return $ HsRule { rd_ext = ext + + -- The error will be reported when lhs_implic is solved. But meanwhile we should drop + -- this (ill-typed) rule entirely; with `-fdefer-type-errors`, we will proceed with + -- compilation regardless of the error, and an ill-typed LHS may cause follow-on + -- errors (#24026) + ; if anyBag insolubleImplic lhs_implic + then + return Nothing -- The RULE LHS does not type-check and will be dropped. + else + return . Just $ HsRule { rd_ext = ext , rd_name = rname , rd_act = act , rd_tyvs = ty_bndrs -- preserved for ppr-ing ===================================== testsuite/tests/typecheck/T24026/T24026a.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026a where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026a.stderr ===================================== @@ -0,0 +1,9 @@ +T24026a.hs:4:11: warning: [GHC-95396] [-Winline-rule-shadowing (in -Wdefault)] + Rule "f" may never fire because ‘f’ might inline first + Suggested fix: Add an INLINE[n] or NOINLINE[n] pragma for ‘f’ + +T24026a.hs:4:37: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/T24026b.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026b where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026b.stderr ===================================== @@ -0,0 +1,5 @@ +T24026b.hs:4:37: error: [GHC-83865] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/all.T ===================================== @@ -0,0 +1,2 @@ +test('T24026a', normal, compile, ['-dlint -fdefer-type-errors']) +test('T24026b', normal, compile_fail, ['']) \ No newline at end of file View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2d96f436ab6e4f4ab20f29054cbf2c8553039e59 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2d96f436ab6e4f4ab20f29054cbf2c8553039e59 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 04:28:48 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 14 Jun 2024 00:28:48 -0400 Subject: [Git][ghc/ghc][master] 2 commits: compiler: refactor lower_CmmExpr_Ptr Message-ID: <666bc700b423c_31403c68ec5053293@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - 1 changed file: - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs Changes: ===================================== compiler/GHC/CmmToAsm/Wasm/FromCmm.hs ===================================== @@ -1045,22 +1045,16 @@ lower_CmmExpr_Typed lbl ty expr = do lower_CmmExpr_Ptr :: CLabel -> CmmExpr -> WasmCodeGenM w (WasmExpr w w, Int) lower_CmmExpr_Ptr lbl ptr = do ty_word <- wasmWordTypeM - case ptr of - CmmLit (CmmLabelOff lbl o) - | o >= 0 -> do - instrs <- - lower_CmmExpr_Typed - lbl - ty_word - (CmmLit $ CmmLabel lbl) - pure (instrs, o) - CmmMachOp (MO_Add _) [base, CmmLit (CmmInt o _)] - | o >= 0 -> do - instrs <- lower_CmmExpr_Typed lbl ty_word base - pure (instrs, fromInteger o) - _ -> do - instrs <- lower_CmmExpr_Typed lbl ty_word ptr - pure (instrs, 0) + let (ptr', o) = case ptr of + CmmLit (CmmLabelOff lbl o) + | o >= 0 -> (CmmLit $ CmmLabel lbl, o) + CmmRegOff reg o + | o >= 0 -> (CmmReg reg, o) + CmmMachOp (MO_Add _) [base, CmmLit (CmmInt o _)] + | o >= 0 -> (base, fromInteger o) + _ -> (ptr, 0) + instrs <- lower_CmmExpr_Typed lbl ty_word ptr' + pure (instrs, o) -- | Push a series of values onto the wasm value stack, returning the -- result stack type. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4570319fc2631c97490a337242a3b6c50f3072e4...def46c8ccddf036851482172919ec392c05f6cc5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4570319fc2631c97490a337242a3b6c50f3072e4...def46c8ccddf036851482172919ec392c05f6cc5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 04:29:23 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 14 Jun 2024 00:29:23 -0400 Subject: [Git][ghc/ghc][master] Small documentation update in Quick Look Message-ID: <666bc72350922_31403c7d58205614f@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 1 changed file: - compiler/GHC/Tc/Gen/App.hs Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -271,6 +271,12 @@ tcApp works like this: Otherwise, delegate back to tcExpr, which infers an (instantiated) TcRhoType + This isn't perfect. Consider this (which uses visible type application): + (let { f :: forall a. a -> a; f x = x } in f) @Int + Since 'let' is not among the special cases for tcInferAppHead, + we'll delegate back to tcExpr, which will instantiate f's type + and the type application to @Int will fail. Too bad! + 3. Use tcInstFun to instantiate the function, Quick-Looking as we go. This implements the |-inst judgement in Fig 4, plus the modification in Fig 5, of the QL paper: "A quick look at impredicativity" (ICFP'20). @@ -325,16 +331,15 @@ application; but it also does a couple of gruesome final checks: * Horrible newtype check * Special case for tagToEnum - -Some cases that /won't/ work: - -1. Consider this (which uses visible type application): - - (let { f :: forall a. a -> a; f x = x } in f) @Int - - Since 'let' is not among the special cases for tcInferAppHead, - we'll delegate back to tcExpr, which will instantiate f's type - and the type application to @Int will fail. Too bad! +(TCAPP2) There is a lurking difficulty in the above plan: + * Before calling tcInstFun, we set the ambient level in the monad + to QLInstVar (Step 2 above). + * Then, when kind-checking the visible type args of the application, + we may perhaps build an implication constraint. + * That means we'll try to add 1 to the ambient level; which is a no-op. + * So skolem escape checks won't work right. + This is pretty exotic, so I'm just deferring it for now, leaving + this note to alert you to the possiblity. Note [Quick Look for particular Ids] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -401,7 +406,7 @@ tcApp rn_expr exp_res_ty -- Step 3: Instantiate the function type (taking a quick look at args) ; do_ql <- wantQuickLook rn_fun ; (inst_args, app_res_rho) - <- setQLInstLevel do_ql $ -- See (TCAPP1) in + <- setQLInstLevel do_ql $ -- See (TCAPP1) and (TCAPP2) in -- Note [tcApp: typechecking applications] tcInstFun do_ql True tc_head fun_sigma rn_args @@ -2008,6 +2013,8 @@ That is the entire point of qlUnify! Wrinkles: discard the constraints and the coercion, and do not update the instantiation variable. But see "Sadly discarded design alternative" below.) + See also (TCAPP2) in Note [tcApp: typechecking applications]. + (UQL3) Instantiation variables don't really have a settled level yet; they have level QLInstVar (see Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. You might worry that we might unify View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ce76bf7851d4ec7a3ebd414a1991b3e71dfbc8c8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/ce76bf7851d4ec7a3ebd414a1991b3e71dfbc8c8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 08:42:17 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Fri, 14 Jun 2024 04:42:17 -0400 Subject: [Git][ghc/ghc][wip/fabu/T24026-early-reject-type-failing-rules] compiler: Rejects RULES whose LHS immediately fails to type-check Message-ID: <666c026997ae3_31403c25f59f4753c8@gitlab.mail> Fabricio Nascimento pushed to branch wip/fabu/T24026-early-reject-type-failing-rules at Glasgow Haskell Compiler / GHC Commits: de0abf36 by Fabricio de Sousa Nascimento at 2024-06-14T17:41:03+09:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - 7 changed files: - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/Tc/Gen/Rule.hs - + testsuite/tests/typecheck/T24026/T24026a.hs - + testsuite/tests/typecheck/T24026/T24026a.stderr - + testsuite/tests/typecheck/T24026/T24026b.hs - + testsuite/tests/typecheck/T24026/T24026b.stderr - + testsuite/tests/typecheck/T24026/all.T Changes: ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -1031,9 +1031,12 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs extra_bndrs = scopedSort extra_tvs ++ extra_dicts where extra_tvs = [ v | v <- extra_vars, isTyVar v ] + + -- isEvVar: this includes coercions, matching what + -- happens in `split_lets` (isDictId, isCoVar) extra_dicts = - [ mkLocalId (localiseName (idName d)) ManyTy (idType d) - | d <- extra_vars, isDictId d ] + [ mkLocalIdOrCoVar (localiseName (idName d)) ManyTy (idType d) + | d <- extra_vars, isEvVar d ] extra_vars = [ v | v <- exprsFreeVarsList args ===================================== compiler/GHC/Tc/Gen/Rule.hs ===================================== @@ -108,11 +108,13 @@ tcRules decls = mapM (wrapLocMA tcRuleDecls) decls tcRuleDecls :: RuleDecls GhcRn -> TcM (RuleDecls GhcTc) tcRuleDecls (HsRules { rds_ext = src , rds_rules = decls }) - = do { tc_decls <- mapM (wrapLocMA tcRule) decls + = do { maybe_tc_decls <- mapM (wrapLocMA tcRule) decls + ; let tc_decls = [L loc rule | (L loc (Just rule)) <- maybe_tc_decls] ; return $ HsRules { rds_ext = src , rds_rules = tc_decls } } -tcRule :: RuleDecl GhcRn -> TcM (RuleDecl GhcTc) + +tcRule :: RuleDecl GhcRn -> TcM (Maybe (RuleDecl GhcTc)) tcRule (HsRule { rd_ext = ext , rd_name = rname@(L _ name) , rd_act = act @@ -181,7 +183,17 @@ tcRule (HsRule { rd_ext = ext ; (rhs_implic, rhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs rhs_wanted ; emitImplications (lhs_implic `unionBags` rhs_implic) - ; return $ HsRule { rd_ext = ext + + -- A type error on the LHS of a rule will be reported earlier while solving for + -- lhs_implic. However, we should also drop the rule entirely for cases where + -- compilation continues regardless of the error. For example with + -- `-fdefer-type-errors`, where this ill-typed LHS rule may cause follow-on errors + -- (#24026). + ; if anyBag insolubleImplic lhs_implic + then + return Nothing -- The RULE LHS does not type-check and will be dropped. + else + return . Just $ HsRule { rd_ext = ext , rd_name = rname , rd_act = act , rd_tyvs = ty_bndrs -- preserved for ppr-ing ===================================== testsuite/tests/typecheck/T24026/T24026a.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026a where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026a.stderr ===================================== @@ -0,0 +1,9 @@ +T24026a.hs:4:11: warning: [GHC-95396] [-Winline-rule-shadowing (in -Wdefault)] + Rule "f" may never fire because ‘f’ might inline first + Suggested fix: Add an INLINE[n] or NOINLINE[n] pragma for ‘f’ + +T24026a.hs:4:37: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/T24026b.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026b where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026b.stderr ===================================== @@ -0,0 +1,5 @@ +T24026b.hs:4:37: error: [GHC-83865] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/all.T ===================================== @@ -0,0 +1,2 @@ +test('T24026a', normal, compile, ['-dlint -fdefer-type-errors']) +test('T24026b', normal, compile_fail, ['']) \ No newline at end of file View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/de0abf3607d31f1e8ab0b9265a540338b2f81c31 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/de0abf3607d31f1e8ab0b9265a540338b2f81c31 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 08:43:17 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Fri, 14 Jun 2024 04:43:17 -0400 Subject: [Git][ghc/ghc][wip/fabu/T24026-early-reject-type-failing-rules] 6 commits: ucd2haskell: remove Streamly dependency + misc Message-ID: <666c02a53e8c6_31403c2692420761e5@gitlab.mail> Fabricio Nascimento pushed to branch wip/fabu/T24026-early-reject-type-failing-rules at Glasgow Haskell Compiler / GHC Commits: 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 7677c545 by Fabricio de Sousa Nascimento at 2024-06-14T08:42:55+00:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - 21 changed files: - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Rule.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs - libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs - − libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs - libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell.hs - + libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell/ModuleGenerators.hs - libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal - + testsuite/tests/typecheck/T24026/T24026a.hs - + testsuite/tests/typecheck/T24026/T24026a.stderr - + testsuite/tests/typecheck/T24026/T24026b.hs - + testsuite/tests/typecheck/T24026/T24026b.stderr - + testsuite/tests/typecheck/T24026/all.T - utils/haddock/CONTRIBUTING.md - utils/haddock/cabal.project Changes: ===================================== compiler/GHC/CmmToAsm/Wasm/FromCmm.hs ===================================== @@ -1045,22 +1045,16 @@ lower_CmmExpr_Typed lbl ty expr = do lower_CmmExpr_Ptr :: CLabel -> CmmExpr -> WasmCodeGenM w (WasmExpr w w, Int) lower_CmmExpr_Ptr lbl ptr = do ty_word <- wasmWordTypeM - case ptr of - CmmLit (CmmLabelOff lbl o) - | o >= 0 -> do - instrs <- - lower_CmmExpr_Typed - lbl - ty_word - (CmmLit $ CmmLabel lbl) - pure (instrs, o) - CmmMachOp (MO_Add _) [base, CmmLit (CmmInt o _)] - | o >= 0 -> do - instrs <- lower_CmmExpr_Typed lbl ty_word base - pure (instrs, fromInteger o) - _ -> do - instrs <- lower_CmmExpr_Typed lbl ty_word ptr - pure (instrs, 0) + let (ptr', o) = case ptr of + CmmLit (CmmLabelOff lbl o) + | o >= 0 -> (CmmLit $ CmmLabel lbl, o) + CmmRegOff reg o + | o >= 0 -> (CmmReg reg, o) + CmmMachOp (MO_Add _) [base, CmmLit (CmmInt o _)] + | o >= 0 -> (base, fromInteger o) + _ -> (ptr, 0) + instrs <- lower_CmmExpr_Typed lbl ty_word ptr' + pure (instrs, o) -- | Push a series of values onto the wasm value stack, returning the -- result stack type. ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -1031,9 +1031,12 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs extra_bndrs = scopedSort extra_tvs ++ extra_dicts where extra_tvs = [ v | v <- extra_vars, isTyVar v ] + + -- isEvVar: this includes coercions, matching what + -- happens in `split_lets` (isDictId, isCoVar) extra_dicts = - [ mkLocalId (localiseName (idName d)) ManyTy (idType d) - | d <- extra_vars, isDictId d ] + [ mkLocalIdOrCoVar (localiseName (idName d)) ManyTy (idType d) + | d <- extra_vars, isEvVar d ] extra_vars = [ v | v <- exprsFreeVarsList args ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -271,6 +271,12 @@ tcApp works like this: Otherwise, delegate back to tcExpr, which infers an (instantiated) TcRhoType + This isn't perfect. Consider this (which uses visible type application): + (let { f :: forall a. a -> a; f x = x } in f) @Int + Since 'let' is not among the special cases for tcInferAppHead, + we'll delegate back to tcExpr, which will instantiate f's type + and the type application to @Int will fail. Too bad! + 3. Use tcInstFun to instantiate the function, Quick-Looking as we go. This implements the |-inst judgement in Fig 4, plus the modification in Fig 5, of the QL paper: "A quick look at impredicativity" (ICFP'20). @@ -325,16 +331,15 @@ application; but it also does a couple of gruesome final checks: * Horrible newtype check * Special case for tagToEnum - -Some cases that /won't/ work: - -1. Consider this (which uses visible type application): - - (let { f :: forall a. a -> a; f x = x } in f) @Int - - Since 'let' is not among the special cases for tcInferAppHead, - we'll delegate back to tcExpr, which will instantiate f's type - and the type application to @Int will fail. Too bad! +(TCAPP2) There is a lurking difficulty in the above plan: + * Before calling tcInstFun, we set the ambient level in the monad + to QLInstVar (Step 2 above). + * Then, when kind-checking the visible type args of the application, + we may perhaps build an implication constraint. + * That means we'll try to add 1 to the ambient level; which is a no-op. + * So skolem escape checks won't work right. + This is pretty exotic, so I'm just deferring it for now, leaving + this note to alert you to the possiblity. Note [Quick Look for particular Ids] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -401,7 +406,7 @@ tcApp rn_expr exp_res_ty -- Step 3: Instantiate the function type (taking a quick look at args) ; do_ql <- wantQuickLook rn_fun ; (inst_args, app_res_rho) - <- setQLInstLevel do_ql $ -- See (TCAPP1) in + <- setQLInstLevel do_ql $ -- See (TCAPP1) and (TCAPP2) in -- Note [tcApp: typechecking applications] tcInstFun do_ql True tc_head fun_sigma rn_args @@ -2008,6 +2013,8 @@ That is the entire point of qlUnify! Wrinkles: discard the constraints and the coercion, and do not update the instantiation variable. But see "Sadly discarded design alternative" below.) + See also (TCAPP2) in Note [tcApp: typechecking applications]. + (UQL3) Instantiation variables don't really have a settled level yet; they have level QLInstVar (see Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. You might worry that we might unify ===================================== compiler/GHC/Tc/Gen/Rule.hs ===================================== @@ -108,11 +108,13 @@ tcRules decls = mapM (wrapLocMA tcRuleDecls) decls tcRuleDecls :: RuleDecls GhcRn -> TcM (RuleDecls GhcTc) tcRuleDecls (HsRules { rds_ext = src , rds_rules = decls }) - = do { tc_decls <- mapM (wrapLocMA tcRule) decls + = do { maybe_tc_decls <- mapM (wrapLocMA tcRule) decls + ; let tc_decls = [L loc rule | (L loc (Just rule)) <- maybe_tc_decls] ; return $ HsRules { rds_ext = src , rds_rules = tc_decls } } -tcRule :: RuleDecl GhcRn -> TcM (RuleDecl GhcTc) + +tcRule :: RuleDecl GhcRn -> TcM (Maybe (RuleDecl GhcTc)) tcRule (HsRule { rd_ext = ext , rd_name = rname@(L _ name) , rd_act = act @@ -181,7 +183,17 @@ tcRule (HsRule { rd_ext = ext ; (rhs_implic, rhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs rhs_wanted ; emitImplications (lhs_implic `unionBags` rhs_implic) - ; return $ HsRule { rd_ext = ext + + -- A type error on the LHS of a rule will be reported earlier while solving for + -- lhs_implic. However, we should also drop the rule entirely for cases where + -- compilation continues regardless of the error. For example with + -- `-fdefer-type-errors`, where this ill-typed LHS rule may cause follow-on errors + -- (#24026). + ; if anyBag insolubleImplic lhs_implic + then + return Nothing -- The RULE LHS does not type-check and will be dropped. + else + return . Just $ HsRule { rd_ext = ext , rd_name = rname , rd_act = act , rd_tyvs = ty_bndrs -- preserved for ppr-ing ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/DerivedCoreProperties.hs ===================================== @@ -8,9 +8,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.DerivedCoreProperties --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/GeneralCategory.hs ===================================== @@ -8,9 +8,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.UnicodeData.GeneralCategory --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleLowerCaseMapping.hs ===================================== @@ -7,9 +7,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.UnicodeData.SimpleLowerCaseMapping --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleTitleCaseMapping.hs ===================================== @@ -7,9 +7,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.UnicodeData.SimpleTitleCaseMapping --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Char/UnicodeData/SimpleUpperCaseMapping.hs ===================================== @@ -7,9 +7,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Char.UnicodeData.SimpleUpperCaseMapping --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/src/GHC/Internal/Unicode/Version.hs ===================================== @@ -6,9 +6,8 @@ ----------------------------------------------------------------------------- -- | -- Module : GHC.Internal.Unicode.Version --- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers -- Stability : internal ----------------------------------------------------------------------------- ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/Parser/Text.hs deleted ===================================== @@ -1,1127 +0,0 @@ -{-# LANGUAGE LambdaCase #-} - --- | --- Module : Parser.Text --- Copyright : (c) 2020 Composewell Technologies and Contributors --- (c) 2016-2017 Harendra Kumar --- (c) 2014-2015 Antonio Nikishaev --- License : BSD-3-Clause --- Maintainer : streamly at composewell.com --- Stability : internal - --- This code was taken from https://github.com/composewell/unicode-data. --- The original Unicode database parser was taken from --- https://github.com/composewell/unicode-transforms but was completely --- rewritten from scratch to parse from UCD text files instead of XML, only --- some types remain the same. That code in turn was originally taken from --- https://github.com/llelf/prose (Antonio Nikishaev) and heavily modified by --- Harendra Kumar. --- -module Parser.Text (genModules) where - -import Control.Exception (catch, IOException) -import Control.Monad (void) -import Data.Bits (Bits(..)) -import Data.Word (Word8) -import Data.Char (chr, ord, isSpace) -import Data.Functor ((<&>)) -import Data.Function ((&)) -import Data.List (intersperse, unfoldr) -import Data.List.Split (splitWhen) -import Numeric (showHex) -import Streamly.Data.Fold (Fold) -import System.Directory (createDirectoryIfMissing) -import System.Environment (getEnv) -import System.FilePath ((), (<.>)) - --- import qualified Data.Set as Set -import Streamly.Data.Stream (Stream) -import qualified Streamly.Data.Stream.Prelude as Stream -import qualified Streamly.Data.Fold as Fold -import qualified Streamly.Internal.Data.Fold as Fold -import qualified Streamly.Data.Unfold as Unfold -import qualified Streamly.FileSystem.Handle as Handle -import qualified Streamly.Unicode.Stream as Unicode -import qualified Streamly.Internal.Unicode.Stream as Unicode -import qualified System.IO as Sys - -import Prelude hiding (pred) - -------------------------------------------------------------------------------- --- Types -------------------------------------------------------------------------------- - -data GeneralCategory = - Lu|Ll|Lt| --LC - Lm|Lo| --L - Mn|Mc|Me| --M - Nd|Nl|No| --N - Pc|Pd|Ps|Pe|Pi|Pf|Po| --P - Sm|Sc|Sk|So| --S - Zs|Zl|Zp| --Z - Cc|Cf|Cs|Co|Cn --C - deriving (Show, Bounded, Enum, Read) - -data DecompType = - DTCanonical | DTCompat | DTFont - | DTNoBreak | DTInitial | DTMedial | DTFinal - | DTIsolated | DTCircle | DTSuper | DTSub - | DTVertical | DTWide | DTNarrow - | DTSmall | DTSquare | DTFraction - deriving (Show, Eq) - -data Decomp = DCSelf | DC [Char] deriving (Show, Eq) - --- data DType = Canonical | Kompat - -data DetailedChar = - DetailedChar - { _char :: Char - , _name :: String - , _generalCategory :: GeneralCategory - , _combiningClass :: Int - , _decompositionType :: Maybe DecompType - , _decomposition :: Decomp - , _simpleUppercaseMapping :: Maybe Char - , _simpleLowercaseMapping :: Maybe Char - , _simpleTitlecaseMapping :: Maybe Char - } - deriving (Show) - -{- [NOTE] Used by disabled generator - --- See: https://www.unicode.org/reports/tr44/#Default_Values_Table -mkDefaultDetailedChar :: Char -> DetailedChar -mkDefaultDetailedChar c = DetailedChar - { _char = c - , _name = mempty - , _generalCategory = Cn - , _combiningClass = 0 - , _decompositionType = Nothing - , _decomposition = DCSelf - , _simpleUppercaseMapping = Nothing - , _simpleLowercaseMapping = Nothing - , _simpleTitlecaseMapping = Nothing } --} - -------------------------------------------------------------------------------- --- Helpers -------------------------------------------------------------------------------- - -headerRule :: String -headerRule = "-----------------------------------------------------------------------------" - -mkModuleHeader :: String -> String -mkModuleHeader modName = - unlines - [ headerRule - , "-- |" - , "-- Module : " <> modName - , "-- Copyright : (c) 2020 Composewell Technologies and Contributors" - , "-- License : BSD-3-Clause" - -- [FIXME] Update maintainer - , "-- Maintainer : streamly at composewell.com" - , "-- Stability : internal" - , headerRule - ] - -readCodePoint :: String -> Char -readCodePoint = chr . read . ("0x"<>) - -readCodePointM :: String -> Maybe Char -readCodePointM "" = Nothing -readCodePointM u = Just (readCodePoint u) - -genSignature :: String -> String -genSignature = (<> " :: Char -> Bool") - --- | Check that var is between minimum and maximum of orderList -genRangeCheck :: String -> [Int] -> String -genRangeCheck var ordList = - var - <> " >= " - <> show (minimum ordList) - <> " && " <> var <> " <= " <> show (maximum ordList) - -genBitmap :: String -> [Int] -> String -genBitmap funcName ordList = - unlines - [ "{-# INLINE " <> funcName <> " #-}" - , genSignature funcName - , funcName <> " = \\c -> let n = ord c in " - <> genRangeCheck "n" ordList <> " && lookupBit64 bitmap# n" - , " where" - , " bitmap# = \"" <> bitMapToAddrLiteral (positionsToBitMap ordList) "\"#" - ] - -positionsToBitMap :: [Int] -> [Bool] -positionsToBitMap = go 0 - - where - - go _ [] = [] - go i xxs@(x:xs) - | i < x = False : go (i + 1) xxs - | otherwise = True : go (i + 1) xs - -bitMapToAddrLiteral :: - -- | Values to encode - [Bool] -> - -- | String to append - String -> - String -bitMapToAddrLiteral bs cs = foldr encode cs (unfoldr mkChunks bs) - - where - - mkChunks :: [a] -> Maybe ([a], [a]) - mkChunks [] = Nothing - mkChunks xs = Just $ splitAt 8 xs - - encode :: [Bool] -> String -> String - encode chunk acc = '\\' : shows (toByte (padTo8 chunk)) acc - - padTo8 :: [Bool] -> [Bool] - padTo8 xs - | length xs >= 8 = xs - | otherwise = xs <> replicate (8 - length xs) False - - toByte :: [Bool] -> Int - toByte xs = sum $ map (\i -> if xs !! i then 1 `shiftL` i else 0) [0..7] - -genEnumBitmap :: - forall a. (Bounded a, Enum a, Show a) => - -- | Function name - String -> - -- | Default value - a -> - -- | List of values to encode - [a] -> - String -genEnumBitmap funcName def as = unlines - [ "{-# INLINE " <> funcName <> " #-}" - , funcName <> " :: Char -> Int" - , funcName <> " c = let n = ord c in if n >= " - <> show (length as) - <> " then " - <> show (fromEnum def) - <> " else lookup_bitmap n" - - , "{-# NOINLINE lookup_bitmap #-}" - , "lookup_bitmap :: Int -> Int" - , "lookup_bitmap n = lookupIntN bitmap# n" - , " where" - , " bitmap# = \"" <> enumMapToAddrLiteral as "\"#" - ] - -{-| Encode a list of values as a byte map, using their 'Enum' instance. - -__Note:__ 'Enum' instance must respect the following: - -* @fromEnum minBound >= 0x00@ -* @fromEnum maxBound <= 0xff@ --} -enumMapToAddrLiteral :: - forall a. (Bounded a, Enum a, Show a) => - -- | Values to encode - [a] -> - -- | String to append - String -> - String -enumMapToAddrLiteral xs cs = foldr go cs xs - - where - - go :: a -> String -> String - go x acc = '\\' : shows (toWord8 x) acc - - toWord8 :: a -> Word8 - toWord8 a = let w = fromEnum a in if 0 <= w && w <= 0xff - then fromIntegral w - else error $ "Cannot convert to Word8: " <> show a - -{- [NOTE] Disabled generator (normalization) --- This bit of code is duplicated but this duplication allows us to reduce 2 --- dependencies on the executable. - -jamoLCount :: Int -jamoLCount = 19 - -jamoVCount :: Int -jamoVCount = 21 - -jamoTCount :: Int -jamoTCount = 28 - -hangulFirst :: Int -hangulFirst = 0xac00 - -hangulLast :: Int -hangulLast = hangulFirst + jamoLCount * jamoVCount * jamoTCount - 1 - -isHangul :: Char -> Bool -isHangul c = n >= hangulFirst && n <= hangulLast - where n = ord c --} - -genUnicodeVersion :: FilePath -> IO () -genUnicodeVersion outdir = do - version <- catch - (getEnv "UNICODE_VERSION") - (\(_ :: IOException) -> return "") - Stream.fold f (Stream.fromList (body version)) - where - moduleName = "GHC.Internal.Unicode.Version" - f = moduleFileEmitter Nothing outdir - (moduleName, \_ -> Fold.foldMap (<> "\n")) - body :: String -> [String] - body version = - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(unicodeVersion)" - , "where" - , "" - , "import {-# SOURCE #-} GHC.Internal.Data.Version" - , "" - , "-- | Version of Unicode standard used by @base@:" - , "-- [" <> version <> "](https://www.unicode.org/versions/Unicode" <> version <> "/)." - , "--" - , "-- @since base-4.15.0.0" - , "unicodeVersion :: Version" - , "unicodeVersion = makeVersion [" <> mkVersion version <> "]" ] - mkVersion = foldr (\c acc -> case c of {'.' -> ',':' ':acc; _ -> c:acc}) mempty - -------------------------------------------------------------------------------- --- Parsers -------------------------------------------------------------------------------- - -------------------------------------------------------------------------------- --- Parsing UnicodeData.txt -------------------------------------------------------------------------------- - -genGeneralCategoryModule - :: Monad m - => String - -> Fold m DetailedChar String -genGeneralCategoryModule moduleName = - done <$> Fold.foldl' step initial - - where - - -- (categories, expected char) - initial = ([], '\0') - - step (acc, p) a = if p < _char a - -- Fill missing char entry with default category Cn - -- See: https://www.unicode.org/reports/tr44/#Default_Values_Table - then step (Cn : acc, succ p) a - -- Regular entry - else (_generalCategory a : acc, succ (_char a)) - - done (acc, _) = unlines - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(generalCategory)" - , "where" - , "" - , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" - , "import GHC.Internal.Unicode.Bits (lookupIntN)" - , "" - , genEnumBitmap "generalCategory" Cn (reverse acc) - ] - -readDecomp :: String -> (Maybe DecompType, Decomp) -readDecomp s = - if null wrds - then (Nothing, DCSelf) - else decmps wrds - - where - - decmps [] = error "Unreachable flow point" - decmps y@(x:xs) = - case dtmap x of - DTCanonical -> (,) (Just DTCanonical) (readCP y) - other -> (,) (Just other) (readCP xs) - - wrds = words s - - readCP ws = DC $ map readCodePoint ws - - dtmap "" = DTCompat - dtmap "" = DTCircle - dtmap "" = DTFinal - dtmap "" = DTFont - dtmap "" = DTFraction - dtmap "" = DTInitial - dtmap "" = DTIsolated - dtmap "" = DTMedial - dtmap "" = DTNarrow - dtmap "" = DTNoBreak - dtmap "" = DTSmall - dtmap "" = DTSquare - dtmap "" = DTSub - dtmap "" = DTSuper - dtmap "" = DTVertical - dtmap "" = DTWide - dtmap _ = DTCanonical - -{- [NOTE] Disabled generators - -filterNonHangul :: Monad m => Fold m DetailedChar a -> Fold m DetailedChar a -filterNonHangul = Fold.filter (not . isHangul . _char) - -filterDecomposableType :: - Monad m => DType -> Fold m DetailedChar a -> Fold m DetailedChar a -filterDecomposableType dtype = - Fold.filter ((/= DCSelf) . _decomposition) - . Fold.filter (predicate . _decompositionType) - - where - - predicate = - case dtype of - Canonical -> (== Just DTCanonical) - Kompat -> const True - -genDecomposableModule :: - Monad m => String -> DType -> Fold m DetailedChar String -genDecomposableModule moduleName dtype = - filterNonHangul - $ filterDecomposableType dtype $ done <$> Fold.foldl' step initial - - where - - initial = [] - - step st a = ord (_char a) : st - - done st = - unlines - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(isDecomposable)" - , "where" - , "" - , "import Data.Char (ord)" - , "import GHC.Internal.Unicode.Bits (lookupBit64)" - , "" - , genBitmap "isDecomposable" (reverse st) - ] - -genCombiningClassModule :: Monad m => String -> Fold m DetailedChar String -genCombiningClassModule moduleName = - Fold.filter (\dc -> _combiningClass dc /= 0) - $ done <$> Fold.foldl' step initial - - where - - initial = ([], []) - - step (st1, st2) a = (genCombiningClassDef a : st1, ord (_char a) : st2) - - done (st1, st2) = - unlines - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(combiningClass, isCombining)" - , "where" - , "" - , "import Data.Char (ord)" - , "import GHC.Internal.Unicode.Bits (lookupBit64)" - , "" - , "combiningClass :: Char -> Int" - , unlines (reverse st1) - , "combiningClass _ = 0\n" - , "" - , genBitmap "isCombining" (reverse st2) - ] - - genCombiningClassDef dc = - "combiningClass " - <> show (_char dc) <> " = " <> show (_combiningClass dc) - -genDecomposeDefModule :: - Monad m - => String - -> [String] - -> [String] - -> DType - -> (Int -> Bool) - -> Fold m DetailedChar String -genDecomposeDefModule moduleName before after dtype pred = - Fold.filter (pred . ord . _char) - $ filterNonHangul - $ filterDecomposableType dtype $ done <$> Fold.foldl' step initial - - where - - decomposeChar c DCSelf = [c] - decomposeChar _c (DC ds) = ds - - genHeader = - [ "{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(decompose)" - , "where" - , "" - ] - genSign = - [ "-- Note: this is a partial function we do not expect to call" - , "-- this if isDecomposable returns false." - , "{-# NOINLINE decompose #-}" - , "decompose :: Char -> [Char]" - ] - initial = [] - - step st dc = genDecomposeDef dc : st - - done st = - let body = mconcat [genHeader, before, genSign, reverse st, after] - in unlines body - - genDecomposeDef dc = - "decompose " - <> show (_char dc) - <> " = " <> show (decomposeChar (_char dc) (_decomposition dc)) - -genCompositionsModule :: - Monad m - => String - -> [Int] - -> [Int] - -> Fold m DetailedChar String -genCompositionsModule moduleName compExclu non0CC = - Fold.filter (not . flip elem compExclu . ord . _char) - $ filterNonHangul - $ Fold.filter (isDecompositionLen2 . _decomposition) - $ filterDecomposableType Canonical $ done <$> Fold.foldl' step initial - - where - - isDecompositionLen2 DCSelf = False - isDecompositionLen2 (DC ds) = length ds == 2 - - genComposePairDef name dc = - name - <> " " - <> show (head d01) - <> " " <> show (d01 !! 1) <> " = Just " <> show (_char dc) - - where - - d01 = decompPair dc - - decompPair dc = - case _decomposition dc of - DCSelf -> error "toCompFormat: DCSelf" - (DC ds) -> - if length ds == 2 - then ds - else error "toCompFormat: length /= 2" - - initial = ([], [], []) - - step (dec, sp, ss) dc = (dec1, sp1, ss1) - - where - - d01 = decompPair dc - d1Ord = ord $ d01 !! 1 - dec1 = genComposePairDef "compose" dc : dec - sp1 = - if d1Ord `notElem` non0CC - then genComposePairDef "composeStarters" dc : sp - else sp - ss1 = - if d1Ord `notElem` non0CC - then d1Ord : ss - else ss - - header = - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(compose, composeStarters, isSecondStarter)" - , "where" - , "" - , "import GHC.Internal.Base (Char, ord)" - , "import GHC.Internal.Unicode.Bits (lookupBit64)" - , "" - ] - - composePair decomps = - [ "{-# NOINLINE compose #-}" - , "compose :: Char -> Char -> Maybe Char" - , unlines decomps - , "compose _ _ = " <> "Nothing" <> "\n" - , "" - ] - - composeStarterPair starterPairs = - [ "composeStarters :: Char -> Char -> Maybe Char" - , unlines starterPairs - , "composeStarters _ _ = " <> "Nothing" <> "\n" - , "" - ] - - isSecondStarter secondStarters = - [genBitmap "isSecondStarter" secondStarters] - - done (dec, sp, ss) = - unlines - $ header - <> composePair (reverse dec) - <> composeStarterPair (reverse sp) - <> isSecondStarter (Set.toList (Set.fromList ss)) --} -genSimpleCaseMappingModule - :: Monad m - => String - -> String - -> (DetailedChar -> Maybe Char) - -> Fold m DetailedChar String -genSimpleCaseMappingModule moduleName funcName field = - done <$> Fold.foldl' step initial - - where - - genHeader = - [ "{-# LANGUAGE NoImplicitPrelude, LambdaCase #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(" <> funcName <> ")" - , "where" - , "" - , "import GHC.Internal.Base (Char)" - , "" - ] - genSign = - [ "{-# NOINLINE " <> funcName <> " #-}" - , funcName <> " :: Char -> Char" - , funcName <> " = \\case" - ] - initial = [] - - step ds dc = case mkEntry dc of - Nothing -> ds - Just d -> d : ds - - after = [" c -> c"] - - done st = - let body = mconcat [genHeader, genSign, reverse st, after] - in unlines body - - mkEntry dc = field dc <&> \c -> mconcat - [ " '\\x" - , showHexChar (_char dc) "' -> '\\x" - , showHexChar c "'" - ] - - showHexChar c = showHex (ord c) - -genCorePropertiesModule :: - Monad m => String -> (String -> Bool) -> Fold m (String, [Int]) String -genCorePropertiesModule moduleName isProp = - Fold.filter (\(name, _) -> isProp name) $ done <$> Fold.foldl' step initial - - where - - prop2FuncName x = "is" <> x - - initial = ([], []) - - step (props, bitmaps) (name, bits) = - (name : props, genBitmap (prop2FuncName name) bits : bitmaps) - - done (props, bitmaps) = unlines $ header props <> bitmaps - - header exports = - [ "{-# LANGUAGE NoImplicitPrelude #-}" - , "{-# LANGUAGE MagicHash #-}" - , "{-# OPTIONS_HADDOCK hide #-}" - , "" - , mkModuleHeader moduleName - , "module " <> moduleName - , "(" <> unwords (intersperse "," (map prop2FuncName exports)) <> ")" - , "where" - , "" - , "import GHC.Internal.Base (Bool, Char, Ord(..), (&&), ord)" - , "import GHC.Internal.Unicode.Bits (lookupBit64)" - , "" - ] - -{- [NOTE] Disabled generator -genUnicode002TestResults :: Monad m => Fold m DetailedChar String -genUnicode002TestResults = done <$> Fold.foldl' step initial - - where - - header = "Code C P S U L A D" - -- (output, expected char) - initial = ([], '\0') - -- [TODO] Increase the number of tested char? - -- maxChar = '\xF0000' -- First codepoint of the last private use areas. - -- maxChar = '\xFFFF' -- Last codepoint of BMP. - maxChar = chr 6553 -- Value in GHC 9.2.2 base test - - step (acc, c) dc = if c > maxChar - then (acc, c) - else if c < _char dc - -- Fill missing char entry with default values - -- See: https://www.unicode.org/reports/tr44/#Default_Values_Table - then step (mkEntry (mkDefaultDetailedChar c) : acc, succ c) dc - -- Regular entry - else (mkEntry dc : acc, succ (_char dc)) - - done (acc, _) = unlines (header : reverse acc) - - mkEntry dc = mconcat - [ showCode (_char dc) - -- [TODO] General category - , showBool (isControl' dc) - , showBool (isPrint' dc) - , showBool (isSpace' dc) - -- [TODO] isSeparator - , showBool (isUpper' dc) - , showBool (isLower' dc) - , showBool (isAlpha' dc) - -- [TODO] isAlphaNum - , showBool (isDigit' dc) - -- [TODO] isNumber - -- [TODO] isMark - -- [TODO] isPunctuation - -- [TODO] isSymbol - ] - - padding = length (show (ord maxChar)) - showCode c = take padding (shows (ord c) (repeat ' ')) - -- [TODO] use showHex - -- showCode c = - -- let code = showHex (ord c) mempty - -- in replicate (padding - length code) '0' <> code - showBool b = if b then " T" else " F" - - -- [NOTE] The following functions replicates Data.Char. Keep them up to date! - - isControl' dc = case _generalCategory dc of - Cc -> True -- Control - _ -> False - - isPrint' dc = case _generalCategory dc of - Zl -> False -- LineSeparator - Zp -> False -- ParagraphSeparator - Cc -> False -- Control - Cf -> False -- Format - Cs -> False -- Surrogate - Co -> False -- PrivateUse - Cn -> False -- NotAssigned - _ -> True - - isSpace' dc = case _char dc of - '\t' -> True - '\n' -> True - '\v' -> True - '\f' -> True - '\r' -> True - _ -> case _generalCategory dc of - Zs -> True -- Space - _ -> False - - isUpper' dc = case _generalCategory dc of - Lu -> True -- UppercaseLetter - Lt -> True -- TitlecaseLetter - _ -> False - - isLower' dc = case _generalCategory dc of - Ll -> True -- LowercaseLetter - _ -> False - - isAlpha' dc = case _generalCategory dc of - Lu -> True -- UppercaseLetter - Ll -> True -- LowercaseLetter - Lt -> True -- TitlecaseLetter - Lm -> True -- ModifierLetter - Lo -> True -- OtherLetter - _ -> False - - isDigit' dc = let c = _char dc - in (fromIntegral (ord c - ord '0') :: Word) <= 9 --} - -------------------------------------------------------------------------------- --- Parsing property files -------------------------------------------------------------------------------- - -type PropertyLine = (String, [Int]) - -trim :: String -> String -trim = takeWhile (not . isSpace) . dropWhile isSpace - -emptyPropertyLine :: PropertyLine -emptyPropertyLine = ("", []) - -combinePropertyLines :: PropertyLine -> PropertyLine -> PropertyLine -combinePropertyLines t1@(n1, o1) t2@(n2, o2) - | n1 == "" = t2 - | n2 == "" = t1 - | n1 == n2 = (n1, o1 <> o2) - | otherwise = error $ "Cannot group " <> n1 <> " with " <> n2 - -parsePropertyLine :: String -> PropertyLine -parsePropertyLine ln - | null ln = emptyPropertyLine - | head ln == '#' = emptyPropertyLine - | otherwise = parseLineJ ln - - where - - parseLineJ :: String -> (String, [Int]) - parseLineJ line = - let (rangeLn, line1) = span (/= ';') line - propLn = takeWhile (/= '#') (tail line1) - in (trim propLn, parseRange (trim rangeLn)) - - parseRange :: String -> [Int] - parseRange rng = - if '.' `elem` rng - then let low = read $ "0x" <> takeWhile (/= '.') rng - high = - read $ "0x" <> reverse (takeWhile (/= '.') (reverse rng)) - in [low .. high] - else [read $ "0x" <> rng] - -isDivider :: String -> Bool -isDivider x = x == "# ================================================" - -parsePropertyLines :: (Monad m) => Stream m String -> Stream m PropertyLine -parsePropertyLines = - Stream.splitOn isDivider - $ Fold.lmap parsePropertyLine - $ Fold.foldl' combinePropertyLines emptyPropertyLine - --- | A range entry in @UnicodeData.txt at . -data UnicodeDataRange - = SingleCode !DetailedChar - -- ^ Regular entry for one code point - | FirstCode !String !DetailedChar - -- ^ A partial range for entry with a name as: @\@ - | CompleteRange !String !DetailedChar !DetailedChar - -- ^ A complete range, requiring 2 continuous entries with respective names: - -- - -- * @\@ - -- * @\@ - -{-| Parse UnicodeData.txt lines - -Parse ranges according to https://www.unicode.org/reports/tr44/#Code_Point_Ranges. - -__Note:__ this does /not/ fill missing char entries, -i.e. entries with no explicit entry nor within a range. --} -parseUnicodeDataLines :: forall m. (Monad m) => Stream m String -> Stream m DetailedChar -parseUnicodeDataLines - = Stream.unfoldMany (Unfold.unfoldr unitToRange) - . Stream.foldMany ( Fold.lmap parseDetailedChar - $ Fold.foldt' step initial id) - - where - - step :: Maybe UnicodeDataRange - -> DetailedChar - -> Fold.Step (Maybe UnicodeDataRange) (Maybe UnicodeDataRange) - step Nothing dc = case span (/= ',') (_name dc) of - (range, ", First>") -> Fold.Partial (Just (FirstCode range dc)) - _ -> Fold.Done (Just (SingleCode dc)) - step (Just (FirstCode range1 dc1)) dc2 = case span (/= ',') (_name dc2) of - (range2, ", Last>") -> if range1 == range2 && _char dc1 < _char dc2 - then Fold.Done (Just (CompleteRange range1 dc1 dc2)) - else error $ "Cannot create range: incompatible ranges" <> show (dc1, dc2) - _ -> error $ "Cannot create range: missing entry correspong to: " <> show range1 - step _ _ = error "impossible case" - - initial :: Fold.Step (Maybe UnicodeDataRange) (Maybe UnicodeDataRange) - initial = Fold.Partial Nothing - - unitToRange :: Maybe UnicodeDataRange -> Maybe (DetailedChar, Maybe UnicodeDataRange) - unitToRange = fmap $ \case - SingleCode dc -> (dc, Nothing) - FirstCode _ dc -> error $ "Incomplete range: " <> show dc - CompleteRange range dc1 dc2 -> if _char dc1 < _char dc2 - -- [TODO] Create the proper name - then (dc1{_name="TODO"}, Just (CompleteRange range dc1{_char=succ (_char dc1)} dc2)) - else (dc2{_name="TODO"}, Nothing) - --- | Parse a single entry of @UnicodeData.txt@ -parseDetailedChar :: String -> DetailedChar -parseDetailedChar line = case splitWhen (== ';') line of - char - :name - :gc - :combining - :_bidi - :decomposition - :_decimal - :_digit - :_numeric - :_bidiM - :_uni1Name - :_iso - :sUpper - :sLower - :sTitle - :_ -> - let (dctype, dcval) = readDecomp decomposition - in DetailedChar - { _char = readCodePoint char - , _name = name - , _generalCategory = read gc - , _combiningClass = read combining - , _decompositionType = dctype - , _decomposition = dcval - , _simpleUppercaseMapping = readCodePointM sUpper - , _simpleLowercaseMapping = readCodePointM sLower - , _simpleTitlecaseMapping = readCodePointM sTitle - } - _ -> error ("Unsupported line: " <> line) - -------------------------------------------------------------------------------- --- Generation -------------------------------------------------------------------------------- - -readLinesFromFile :: String -> Stream IO String -readLinesFromFile file = - withFile file Sys.ReadMode - $ \h -> Handle.read h & Unicode.decodeUtf8 & Unicode.lines Fold.toList - - where - withFile file_ mode = - Stream.bracketIO (Sys.openFile file_ mode) (Sys.hClose) - - -moduleToFileName :: String -> String -moduleToFileName = map (\x -> if x == '.' then '/' else x) - -dirFromFileName :: String -> String -dirFromFileName = reverse . dropWhile (/= '/') . reverse - -data FileRecipe a - = ModuleRecipe - -- ^ A recipe to create a Haskell module file. - String - -- ^ Module name - (String -> Fold IO a String) - -- ^ Function that generate the module, given the module name. - | TestOutputRecipe - -- ^ A recipe to create a test output file. - String - -- ^ Test name - (Fold IO a String) - -- ^ Test output generator - --- ModuleRecipe is a tuple of the module name and a function that generates the --- module using the module name -type ModuleRecipe a = (String, String -> Fold IO a String) -type TestOutputRecipe a = (FilePath, Fold IO a String) - --- GeneratorRecipe is a list of ModuleRecipe -type GeneratorRecipe a = [FileRecipe a] - -moduleFileEmitter :: Maybe FilePath -> FilePath -> ModuleRecipe a -> Fold IO a () -moduleFileEmitter mfile outdir (modName, fldGen) = Fold.rmapM action $ fldGen modName - - where - - pretext version = case mfile of - Just file -> mconcat - [ "-- DO NOT EDIT: This file is automatically generated by the internal tool ucd2haskell,\n" - , "-- with data from: https://www.unicode.org/Public/" - , version - , "/ucd/" - , file - ,".\n\n" - ] - Nothing -> "-- DO NOT EDIT: This file is automatically generated by the internal tool ucd2haskell.\n\n" - outfile = outdir moduleToFileName modName <.> ".hs" - outfiledir = dirFromFileName outfile - action c = do - version <- - catch - (getEnv "UNICODE_VERSION") - (\(_ :: IOException) -> return "") - createDirectoryIfMissing True outfiledir - writeFile outfile (pretext version <> c) - -testOutputFileEmitter :: FilePath -> TestOutputRecipe a -> Fold IO a () -testOutputFileEmitter outdir (name, fldGen) = Fold.rmapM action fldGen - - where - - outfile = outdir "tests" name <.> ".stdout" - outfiledir = dirFromFileName outfile - action c - = createDirectoryIfMissing True outfiledir - *> writeFile outfile c - -runGenerator :: - FilePath - -> FilePath - -> (Stream IO String -> Stream IO a) - -> FilePath - -> GeneratorRecipe a - -> IO () -runGenerator indir file transformLines outdir recipes = - readLinesFromFile (indir <> file) & transformLines & Stream.fold combinedFld - - where - - generatedFolds = recipes <&> \case - ModuleRecipe name f -> moduleFileEmitter (Just file) outdir (name, f) - TestOutputRecipe name f -> testOutputFileEmitter outdir (name, f) - combinedFld = void $ Fold.distribute generatedFolds - -genModules :: String -> String -> [String] -> IO () -genModules indir outdir props = do - genUnicodeVersion outdir - - -- [NOTE] Disabled generator - -- compExclu <- - -- readLinesFromFile (indir <> "DerivedNormalizationProps.txt") - -- & parsePropertyLines - -- & Stream.find (\(name, _) -> name == "Full_Composition_Exclusion") - -- & fmap (snd . fromMaybe ("", [])) - - -- [NOTE] Disabled generator - -- non0CC <- - -- readLinesFromFile (indir <> "extracted/DerivedCombiningClass.txt") - -- & parsePropertyLines - -- & Stream.filter (\(name, _) -> name /= "0") - -- & Stream.map snd - -- & Stream.fold (Fold.foldl' (<>) []) - - runGenerator - indir - "UnicodeData.txt" - parseUnicodeDataLines - outdir - -- [NOTE] Disabled generators - -- [ uncurry ModuleRecipe compositions compExclu non0CC - -- , uncurry ModuleRecipe combiningClass - -- , uncurry ModuleRecipe decomposable - -- , uncurry ModuleRecipe decomposableK - -- , uncurry ModuleRecipe decompositions - -- , uncurry ModuleRecipe decompositionsK2 - -- , uncurry ModuleRecipe decompositionsK - [ uncurry ModuleRecipe generalCategory - , uncurry ModuleRecipe simpleUpperCaseMapping - , uncurry ModuleRecipe simpleLowerCaseMapping - , uncurry ModuleRecipe simpleTitleCaseMapping - -- , uncurry TestOutputRecipe unicode002Test - ] - - -- [NOTE] Disabled generator - -- runGenerator - -- indir - -- "PropList.txt" - -- parsePropertyLines - -- outdir - -- [ uncurry ModuleRecipe propList ] - - runGenerator - indir - "DerivedCoreProperties.txt" - parsePropertyLines - outdir - [ uncurry ModuleRecipe derivedCoreProperties ] - - where - - -- [NOTE] Disabled generator - -- propList = - -- ("GHC.Internal.Unicode.Char.PropList" - -- , (`genCorePropertiesModule` (`elem` props))) - - derivedCoreProperties = - ("GHC.Internal.Unicode.Char.DerivedCoreProperties" - , (`genCorePropertiesModule` (`elem` props))) - - -- [NOTE] Disabled generator - -- compositions exc non0 = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.Compositions" - -- , \m -> genCompositionsModule m exc non0) - - -- [NOTE] Disabled generator - -- combiningClass = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.CombiningClass" - -- , genCombiningClassModule) - - -- [NOTE] Disabled generator - -- decomposable = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.Decomposable" - -- , (`genDecomposableModule` Canonical)) - - -- [NOTE] Disabled generator - -- decomposableK = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.DecomposableK" - -- , (`genDecomposableModule` Kompat)) - - -- [NOTE] Disabled generator - -- decompositions = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.Decompositions" - -- , \m -> genDecomposeDefModule m [] [] Canonical (const True)) - - -- [NOTE] Disabled generator - -- decompositionsK2 = - -- ( "GHC.Internal.Unicode.Char.UnicodeData.DecompositionsK2" - -- , \m -> genDecomposeDefModule m [] [] Kompat (>= 60000)) - - -- [NOTE] Disabled generator - -- decompositionsK = - -- let pre = ["import qualified " <> fst decompositionsK2 <> " as DK2", ""] - -- post = ["decompose c = DK2.decompose c"] - -- in ( "GHC.Internal.Unicode.Char.UnicodeData.DecompositionsK" - -- , \m -> genDecomposeDefModule m pre post Kompat (< 60000)) - - generalCategory = - ( "GHC.Internal.Unicode.Char.UnicodeData.GeneralCategory" - , genGeneralCategoryModule) - - simpleUpperCaseMapping = - ( "GHC.Internal.Unicode.Char.UnicodeData.SimpleUpperCaseMapping" - , \m -> genSimpleCaseMappingModule m "toSimpleUpperCase" _simpleUppercaseMapping) - - simpleLowerCaseMapping = - ( "GHC.Internal.Unicode.Char.UnicodeData.SimpleLowerCaseMapping" - , \m -> genSimpleCaseMappingModule m "toSimpleLowerCase" _simpleLowercaseMapping) - - simpleTitleCaseMapping = - ( "GHC.Internal.Unicode.Char.UnicodeData.SimpleTitleCaseMapping" - , \m -> genSimpleCaseMappingModule m "toSimpleTitleCase" _simpleTitlecaseMapping) - - -- unicode002Test = - -- ( "unicode002" - -- , genUnicode002TestResults) ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell.hs ===================================== @@ -2,14 +2,17 @@ -- Module : Main -- Copyright : (c) 2020 Composewell Technologies and Contributors -- License : BSD-3-Clause --- Maintainer : streamly at composewell.com +-- Maintainer : The GHC Developers " -- Stability : internal -- module Main where -import WithCli (HasArguments(..), withCli) -import Parser.Text (genModules) +import qualified Data.ByteString.Char8 as B8 +import qualified Data.ByteString.Short as BS import GHC.Generics (Generic) +import WithCli (HasArguments(..), withCli) + +import UCD2Haskell.ModuleGenerators (genModules) data CLIOptions = CLIOptions @@ -20,7 +23,10 @@ data CLIOptions = deriving (Show, Generic, HasArguments) cliClient :: CLIOptions -> IO () -cliClient opts = genModules (input opts) (output opts) (core_prop opts) +cliClient opts = genModules + opts.input + opts.output + (BS.toShort . B8.pack <$> opts.core_prop) main :: IO () main = withCli cliClient ===================================== libraries/ghc-internal/tools/ucd2haskell/exe/UCD2Haskell/ModuleGenerators.hs ===================================== @@ -0,0 +1,517 @@ +-- | +-- Module : UCD2Haskell.ModuleGenerators +-- Copyright : (c) 2020 Composewell Technologies and Contributors +-- (c) 2016-2017 Harendra Kumar +-- (c) 2014-2015 Antonio Nikishaev +-- (c) 2022-2024 Pierre Le Marre +-- License : BSD-3-Clause +-- Maintainer : The GHC Developers " +-- Stability : internal + +-- Code history: +-- +-- This code was adapted from https://github.com/composewell/unicode-data/ +-- (around commit c4aa52ed932ad8badf97296858932c3389b275b8) by Pierre Le Marre. +-- The original Unicode database parser was taken from +-- https://github.com/composewell/unicode-transforms but was completely +-- rewritten from scratch to parse from UCD text files instead of XML, only +-- some types remain the same. That code in turn was originally taken from +-- https://github.com/llelf/prose (Antonio Nikishaev) and heavily modified by +-- Harendra Kumar. +-- +module UCD2Haskell.ModuleGenerators (genModules) where + +import Control.Exception (catch, IOException) +import Data.Bits (Bits(..)) +import Data.Word (Word8) +import Data.Char (ord) +import Data.Functor ((<&>), ($>)) +import Data.List (intersperse, unfoldr) +import System.Directory (createDirectoryIfMissing) +import System.Environment (getEnv) +import System.FilePath ((), (<.>)) +import Data.String (IsString) +import Data.Foldable (Foldable(..)) + +import qualified Data.ByteString.Builder as BB +import qualified Data.ByteString as B +import qualified Data.ByteString.Lazy as BL +import qualified Data.ByteString.Short as BS + +import qualified Unicode.CharacterDatabase.Parser.Common as C +import qualified Unicode.CharacterDatabase.Parser.UnicodeData as UD +import qualified Unicode.CharacterDatabase.Parser.Properties.Multiple as P + +import Prelude hiding (pred) + +-------------------------------------------------------------------------------- +-- Helpers +-------------------------------------------------------------------------------- + +unlinesBB :: [BB.Builder] -> BB.Builder +unlinesBB = (<> "\n") . mconcat . intersperse "\n" + +unwordsBB :: [BB.Builder] -> BB.Builder +unwordsBB = mconcat . intersperse " " + +headerRule :: BB.Builder +headerRule = "-----------------------------------------------------------------------------" + +mkModuleHeader :: BB.Builder -> BB.Builder +mkModuleHeader modName = + unlinesBB + [ headerRule + , "-- |" + , "-- Module : " <> modName + , "-- License : BSD-3-Clause" + , "-- Maintainer : The GHC Developers " + , "-- Stability : internal" + , headerRule + ] + +genSignature :: BB.Builder -> BB.Builder +genSignature = (<> " :: Char -> Bool") + +-- | Check that var is between minimum and maximum of orderList +genRangeCheck :: BB.Builder -> [Int] -> BB.Builder +genRangeCheck var ordList = + var + <> " >= " + <> BB.intDec (minimum ordList) + <> " && " <> var <> " <= " <> BB.intDec (maximum ordList) + +genBitmap :: BB.Builder -> [Int] -> BB.Builder +genBitmap funcName ordList = + unlinesBB + [ "{-# INLINE " <> funcName <> " #-}" + , genSignature funcName + , funcName <> " = \\c -> let n = ord c in " + <> genRangeCheck "n" ordList <> " && lookupBit64 bitmap# n" + , " where" + , " bitmap# = \"" <> bitMapToAddrLiteral (positionsToBitMap ordList) "\"#" + ] + +positionsToBitMap :: [Int] -> [Bool] +positionsToBitMap = go 0 + + where + + go _ [] = [] + go i xxs@(x:xs) + | i < x = False : go (i + 1) xxs + | otherwise = True : go (i + 1) xs + +bitMapToAddrLiteral :: + -- | Values to encode + [Bool] -> + -- | String to append + BB.Builder -> + BB.Builder +bitMapToAddrLiteral bs cs = foldr encode cs (unfoldr mkChunks bs) + + where + + mkChunks :: [a] -> Maybe ([a], [a]) + mkChunks [] = Nothing + mkChunks xs = Just $ splitAt 8 xs + + encode :: [Bool] -> BB.Builder -> BB.Builder + encode chunk acc = BB.char7 '\\' <> BB.intDec (toByte (padTo8 chunk)) <> acc + + padTo8 :: [Bool] -> [Bool] + padTo8 xs + | length xs >= 8 = xs + | otherwise = xs <> replicate (8 - length xs) False + + toByte :: [Bool] -> Int + toByte xs = sum $ map (\i -> if xs !! i then 1 `shiftL` i else 0) [0..7] + +genEnumBitmap :: + forall a. (Bounded a, Enum a, Show a) => + -- | Function name + BB.Builder -> + -- | Default value + a -> + -- | List of values to encode + [a] -> + BB.Builder +genEnumBitmap funcName def as = unlinesBB + [ "{-# INLINE " <> funcName <> " #-}" + , funcName <> " :: Char -> Int" + , funcName <> " c = let n = ord c in if n >= " + <> BB.intDec (length as) + <> " then " + <> BB.intDec (fromEnum def) + <> " else lookup_bitmap n" + + , "{-# NOINLINE lookup_bitmap #-}" + , "lookup_bitmap :: Int -> Int" + , "lookup_bitmap n = lookupIntN bitmap# n" + , " where" + , " bitmap# = \"" <> enumMapToAddrLiteral as "\"#" + ] + +{-| Encode a list of values as a byte map, using their 'Enum' instance. + +__Note:__ 'Enum' instance must respect the following: + +* @fromEnum minBound >= 0x00@ +* @fromEnum maxBound <= 0xff@ +-} +enumMapToAddrLiteral :: + forall a. (Bounded a, Enum a, Show a) => + -- | Values to encode + [a] -> + -- | String to append + BB.Builder -> + BB.Builder +enumMapToAddrLiteral xs cs = foldr go cs xs + + where + + go :: a -> BB.Builder -> BB.Builder + go x acc = BB.char7 '\\' <> BB.word8Dec (toWord8 x) <> acc + + toWord8 :: a -> Word8 + toWord8 a = let w = fromEnum a in if 0 <= w && w <= 0xff + then fromIntegral w + else error $ "Cannot convert to Word8: " <> show a + +genUnicodeVersion :: FilePath -> IO () +genUnicodeVersion outdir = do + version <- catch + (getEnv "UNICODE_VERSION") + (\(_ :: IOException) -> return "") + runFold f [body version] + where + moduleName :: (IsString a) => a + moduleName = "GHC.Internal.Unicode.Version" + f = moduleFileEmitter Nothing outdir + (moduleName, \_ -> Fold (\_ x -> x) mempty id) + body :: String -> BB.Builder + body version = unlinesBB + [ "{-# LANGUAGE NoImplicitPrelude #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(unicodeVersion)" + , "where" + , "" + , "import {-# SOURCE #-} GHC.Internal.Data.Version" + , "" + , "-- | Version of Unicode standard used by @base@:" + , "-- [" <> BB.string7 version <> "](https://www.unicode.org/versions/Unicode" <> BB.string7 version <> "/)." + , "--" + , "-- @since base-4.15.0.0" + , "unicodeVersion :: Version" + , "unicodeVersion = makeVersion [" <> mkVersion version <> "]" ] + mkVersion = foldMap (\c -> case c of {'.' -> BB.char7 ',' <> BB.char7 ' '; _ -> BB.char7 c}) + +-------------------------------------------------------------------------------- +-- Fold +-------------------------------------------------------------------------------- + +data Fold a b = forall s. Fold + { _step :: s -> a -> s + , _initial :: s + , _final :: s -> b } + +data Pair a b = Pair !a !b + +teeWith :: (a -> b -> c) -> Fold x a -> Fold x b -> Fold x c +teeWith f (Fold stepL initialL finalL) (Fold stepR initialR finalR) = + Fold step initial final + where + step (Pair sL sR) x = Pair (stepL sL x) (stepR sR x) + initial = Pair initialL initialR + final (Pair sL sR) = f (finalL sL) (finalR sR) + +distribute :: [Fold a b] -> Fold a [b] +distribute = foldr (teeWith (:)) (Fold const () (const [])) + +rmapFold :: (b -> c) -> Fold a b -> Fold a c +rmapFold f (Fold step initial final) = Fold step initial (f . final) + +runFold :: Fold a b -> [a] -> b +runFold (Fold step initial final) = final . foldl' step initial + +-------------------------------------------------------------------------------- +-- Modules generators +-------------------------------------------------------------------------------- + +data GeneralCategoryAcc = GeneralCategoryAcc + { _categories :: ![UD.GeneralCategory] + , _expectedChar :: !Char + } + +genGeneralCategoryModule :: BB.Builder -> Fold UD.Entry BB.Builder +genGeneralCategoryModule moduleName = Fold step initial done + + where + + -- (categories, expected char) + initial = GeneralCategoryAcc [] '\0' + + step (GeneralCategoryAcc acc p) e@(UD.Entry r d) + | p < r.start + -- Fill missing char entry with default category Cn + -- See: https://www.unicode.org/reports/tr44/#Default_Values_Table + = step (GeneralCategoryAcc (replicate (ord r.start - ord p) UD.Cn <> acc) r.start) e + -- Regular entry + | otherwise = case r of + C.SingleChar ch -> GeneralCategoryAcc + (d.generalCategory : acc) + (succ ch) + C.CharRange ch1 ch2 -> GeneralCategoryAcc + (replicate (ord ch2 - ord ch1 + 1) d.generalCategory <> acc) + (succ ch2) + + done (GeneralCategoryAcc acc _) = unlinesBB + [ "{-# LANGUAGE NoImplicitPrelude #-}" + , "{-# LANGUAGE MagicHash #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(generalCategory)" + , "where" + , "" + , "import GHC.Internal.Base (Char, Int, Ord(..), ord)" + , "import GHC.Internal.Unicode.Bits (lookupIntN)" + , "" + , genEnumBitmap "generalCategory" UD.Cn (reverse acc) + ] + +genSimpleCaseMappingModule + :: BB.Builder + -> BB.Builder + -> (UD.CharDetails -> Maybe Char) + -> Fold UD.Entry BB.Builder +genSimpleCaseMappingModule moduleName funcName field = + Fold step initial done + + where + + genHeader = + [ "{-# LANGUAGE NoImplicitPrelude, LambdaCase #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(" <> funcName <> ")" + , "where" + , "" + , "import GHC.Internal.Base (Char)" + , "" + ] + genSign = + [ "{-# NOINLINE " <> funcName <> " #-}" + , funcName <> " :: Char -> Char" + , funcName <> " = \\case" + ] + initial = [] + + step ds dc = case mkEntry dc of + Nothing -> ds + Just d -> d : ds + + after = [" c -> c"] + + done st = + let body = mconcat [genHeader, genSign, reverse st, after] + in unlinesBB body + + mkEntry (UD.Entry r dc) = case r of + C.SingleChar ch -> field dc <&> \c -> mconcat + [ " '\\x" + , showHexChar ch + , "' -> '\\x" + , showHexChar c + , "'" + ] + C.CharRange{} -> field dc $> error ("genSimpleCaseMappingModule: unexpected char range: " <> show r) + + showHexChar c = BB.wordHex (fromIntegral (ord c)) + +data PropertiesAcc = PropertiesAcc + { _properties :: ![BS.ShortByteString] + , _bitmaps :: ![BB.Builder] + , _currentBitmap :: ![[Int]] } + +genCorePropertiesModule :: + BB.Builder -> (BS.ShortByteString -> Bool) -> Fold P.Entry BB.Builder +genCorePropertiesModule moduleName isProp = Fold step initial done + where + prop2FuncName x = "is" <> BB.shortByteString x + + initial = PropertiesAcc [] [] [] + + step acc@(PropertiesAcc props bitmaps bits) P.Entry{..} + | not (isProp property) = acc -- property filtered out + | otherwise = case props of + prop' : _ + | prop' == property -> PropertiesAcc props bitmaps (rangeToBits range : bits) + | otherwise -> PropertiesAcc + { _properties = property : props + , _bitmaps = genBitmap' prop' bits : bitmaps + , _currentBitmap = [rangeToBits range] } + _ -> PropertiesAcc [property] bitmaps [rangeToBits range] + + rangeToBits = \case + C.SingleChar ch -> [ord ch] + C.CharRange ch1 ch2 -> [ord ch1 .. ord ch2] + + genBitmap' prop bits = genBitmap (prop2FuncName prop) (mconcat (reverse bits)) + + done (PropertiesAcc props bitmaps bits) = unlinesBB (header props <> bitmaps') + where + lastProp = case props of + prop : _ -> prop + [] -> error "impossible" + bitmaps' = genBitmap' lastProp bits : bitmaps + + header exports = + [ "{-# LANGUAGE NoImplicitPrelude #-}" + , "{-# LANGUAGE MagicHash #-}" + , "{-# OPTIONS_HADDOCK hide #-}" + , "" + , mkModuleHeader moduleName + , "module " <> moduleName + , "(" <> unwordsBB (intersperse "," (map prop2FuncName exports)) <> ")" + , "where" + , "" + , "import GHC.Internal.Base (Bool, Char, Ord(..), (&&), ord)" + , "import GHC.Internal.Unicode.Bits (lookupBit64)" + , "" + ] + +-------------------------------------------------------------------------------- +-- Generation +-------------------------------------------------------------------------------- + +moduleToFileName :: String -> String +moduleToFileName = map (\x -> if x == '.' then '/' else x) + +dirFromFileName :: String -> String +dirFromFileName = reverse . dropWhile (/= '/') . reverse + +data FileRecipe a + = ModuleRecipe + -- ^ A recipe to create a Haskell module file. + String + -- ^ Module name + (BB.Builder -> Fold a BB.Builder) + -- ^ Function that generate the module, given the module name. + | TestOutputRecipe + -- ^ A recipe to create a test output file. + String + -- ^ Test name + (Fold a BB.Builder) + -- ^ Test output generator + +-- ModuleRecipe is a tuple of the module name and a function that generates the +-- module using the module name +type ModuleRecipe a = (String, BB.Builder -> Fold a BB.Builder) +type TestOutputRecipe a = (FilePath, Fold a BB.Builder) + +-- GeneratorRecipe is a list of ModuleRecipe +type GeneratorRecipe a = [FileRecipe a] + +moduleFileEmitter :: Maybe FilePath -> FilePath -> ModuleRecipe a -> Fold a (IO ()) +moduleFileEmitter mfile outdir (modName, fldGen) = rmapFold action $ fldGen (BB.string7 modName) + + where + + pretext version = case mfile of + Just file -> mconcat + [ "-- DO NOT EDIT: This file is automatically generated by the internal tool ucd2haskell,\n" + , "-- with data from: https://www.unicode.org/Public/" + , BB.string7 version + , "/ucd/" + , BB.string7 file + ,".\n\n" + ] + Nothing -> "-- DO NOT EDIT: This file is automatically generated by the internal tool ucd2haskell.\n\n" + outfile = outdir moduleToFileName modName <.> ".hs" + outfiledir = dirFromFileName outfile + action c = do + version <- + catch + (getEnv "UNICODE_VERSION") + (\(_ :: IOException) -> return "") + createDirectoryIfMissing True outfiledir + B.writeFile outfile (BL.toStrict (BB.toLazyByteString (pretext version <> c))) + +testOutputFileEmitter :: FilePath -> TestOutputRecipe a -> Fold a (IO ()) +testOutputFileEmitter outdir (name, fldGen) = rmapFold action fldGen + + where + + outfile = outdir "tests" name <.> ".stdout" + outfiledir = dirFromFileName outfile + action c + = createDirectoryIfMissing True outfiledir + *> B.writeFile outfile (BL.toStrict (BB.toLazyByteString c)) + +runGenerator :: + FilePath + -> FilePath + -> (B.ByteString -> [a]) + -> FilePath + -> GeneratorRecipe a + -> IO () +runGenerator indir file transformLines outdir recipes = do + raw <- B.readFile (indir <> file) + sequence_ (runFold combinedFld (transformLines raw)) + + where + + generatedFolds = recipes <&> \case + ModuleRecipe name f -> moduleFileEmitter (Just file) outdir (name, f) + TestOutputRecipe name f -> testOutputFileEmitter outdir (name, f) + combinedFld = distribute generatedFolds + +genModules :: FilePath -> FilePath -> [BS.ShortByteString] -> IO () +genModules indir outdir props = do + genUnicodeVersion outdir + + runGenerator + indir + "UnicodeData.txt" + UD.parse + outdir + [ generalCategory + , simpleUpperCaseMapping + , simpleLowerCaseMapping + , simpleTitleCaseMapping + ] + + runGenerator + indir + "DerivedCoreProperties.txt" + P.parse + outdir + [ derivedCoreProperties ] + + where + + derivedCoreProperties = ModuleRecipe + "GHC.Internal.Unicode.Char.DerivedCoreProperties" + (`genCorePropertiesModule` (`elem` props)) + + generalCategory = ModuleRecipe + "GHC.Internal.Unicode.Char.UnicodeData.GeneralCategory" + genGeneralCategoryModule + + simpleUpperCaseMapping = ModuleRecipe + "GHC.Internal.Unicode.Char.UnicodeData.SimpleUpperCaseMapping" + (\m -> genSimpleCaseMappingModule m "toSimpleUpperCase" UD.simpleUpperCaseMapping) + + simpleLowerCaseMapping = ModuleRecipe + "GHC.Internal.Unicode.Char.UnicodeData.SimpleLowerCaseMapping" + (\m -> genSimpleCaseMappingModule m "toSimpleLowerCase" UD.simpleLowerCaseMapping) + + simpleTitleCaseMapping = ModuleRecipe + "GHC.Internal.Unicode.Char.UnicodeData.SimpleTitleCaseMapping" + (\m -> genSimpleCaseMappingModule m "toSimpleTitleCase" UD.simpleTitleCaseMapping) ===================================== libraries/ghc-internal/tools/ucd2haskell/ucd2haskell.cabal ===================================== @@ -1,6 +1,6 @@ cabal-version: 2.2 name: ucd2haskell -version: 0.3.0 +version: 0.4.0 synopsis: Converter from Unicode character database to Haskell. description: The Haskell data structures are generated programmatically from the @@ -10,12 +10,12 @@ description: license: BSD-3-Clause license-file: LICENSE author: Composewell Technologies and Contributors -maintainer: streamly at composewell.com -copyright: 2020 Composewell Technologies and Contributors +maintainer: The GHC Developers +bug-reports: https://gitlab.haskell.org/ghc/ghc/-/issues/new category: Data,Text,Unicode stability: Experimental build-type: Simple -tested-with: GHC==9.2.2 +tested-with: GHC==9.8.2 extra-source-files: README.md @@ -23,18 +23,14 @@ extra-source-files: common default-extensions default-extensions: - BangPatterns DeriveGeneric - MagicHash - RecordWildCards - ScopedTypeVariables - TupleSections - FlexibleContexts - - -- Experimental, may lead to issues DeriveAnyClass - TemplateHaskell - UnboxedTuples + ExistentialQuantification + LambdaCase + OverloadedStrings + OverloadedRecordDot + ScopedTypeVariables + RecordWildCards common compile-options ghc-options: -Wall @@ -42,21 +38,20 @@ common compile-options -fwarn-incomplete-record-updates -fwarn-incomplete-uni-patterns -fwarn-tabs - default-language: Haskell2010 + default-language: GHC2021 executable ucd2haskell import: default-extensions, compile-options - default-language: Haskell2010 ghc-options: -O2 hs-source-dirs: exe main-is: UCD2Haskell.hs - other-modules: Parser.Text + other-modules: UCD2Haskell.ModuleGenerators build-depends: - base >= 4.7 && < 4.20 - , streamly-core >= 0.2.2 && < 0.3 - , streamly >= 0.10 && < 0.11 - , split >= 0.2.3 && < 0.3 - , getopt-generics >= 0.13 && < 0.14 - , containers >= 0.5 && < 0.7 - , directory >= 1.3.6 && < 1.3.8 - , filepath >= 1.4.2 && < 1.5 + base >= 4.7 && < 5 + , bytestring >= 0.11 && < 0.13 + , containers >= 0.5 && < 0.7 + , directory >= 1.3.6 && < 1.3.8 + , filepath >= 1.4.2 && < 1.5 + , getopt-generics >= 0.13 && < 0.14 + , split >= 0.2.3 && < 0.3 + , unicode-data-parser >= 0.2.0 && < 0.4 ===================================== testsuite/tests/typecheck/T24026/T24026a.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026a where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026a.stderr ===================================== @@ -0,0 +1,9 @@ +T24026a.hs:4:11: warning: [GHC-95396] [-Winline-rule-shadowing (in -Wdefault)] + Rule "f" may never fire because ‘f’ might inline first + Suggested fix: Add an INLINE[n] or NOINLINE[n] pragma for ‘f’ + +T24026a.hs:4:37: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/T24026b.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026b where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026b.stderr ===================================== @@ -0,0 +1,5 @@ +T24026b.hs:4:37: error: [GHC-83865] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/all.T ===================================== @@ -0,0 +1,2 @@ +test('T24026a', normal, compile, ['-dlint -fdefer-type-errors']) +test('T24026b', normal, compile_fail, ['']) \ No newline at end of file ===================================== utils/haddock/CONTRIBUTING.md ===================================== @@ -28,6 +28,17 @@ Then, run the following command from the top-level: $ ./hadrian/build -j --flavour=Quick --freeze1 _build/stage1/bin/haddock ``` +### Running the test suites + +Currently, this cannot be done with hadrian but has to be done with a +`cabal-install` built from `master`. + +``` +cabal test -w /_build/stage1/bin/ghc +``` + +For more details, see https://gitlab.haskell.org/ghc/ghc/-/issues/24976. + ## Working with the codebase The project provides a Makefile with rules to accompany you during development: ===================================== utils/haddock/cabal.project ===================================== @@ -1,5 +1,3 @@ -with-compiler: ghc-9.7 - packages: ./ ./haddock-api ./haddock-library View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/de0abf3607d31f1e8ab0b9265a540338b2f81c31...7677c545f69ef3fbbd56cbd7319a46bf6a98a56f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/de0abf3607d31f1e8ab0b9265a540338b2f81c31...7677c545f69ef3fbbd56cbd7319a46bf6a98a56f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 10:33:21 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 14 Jun 2024 06:33:21 -0400 Subject: [Git][ghc/ghc][wip/T24623] Comments Message-ID: <666c1c7175524_205b2f7ec1d8101f0@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24623 at Glasgow Haskell Compiler / GHC Commits: 4bfc49f9 by Simon Peyton Jones at 2024-06-14T11:33:01+01:00 Comments - - - - - 4 changed files: - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/WorkWrap.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Types/Demand.hs Changes: ===================================== compiler/GHC/Core/Opt/DmdAnal.hs ===================================== @@ -1086,6 +1086,7 @@ dmdAnalRhsSig top_lvl rec_flag env let_subdmd id rhs (final_env, weak_fvs, final_id, final_rhs) where ww_arity = workWrapArity id rhs + -- See Note [WorkWrap arity and join points, point (1)] body_subdmd | isJoinId id = let_subdmd | otherwise = topSubDmd @@ -1235,47 +1236,97 @@ Consider B -> j 4 C -> (p,7)) -If j was a vanilla function definition, we'd analyse its body with -evalDmd, and think that it was lazy in p. But for join points we can -do better! We know that j's body will (if called at all) be evaluated -with the demand that consumes the entire join-binding, in this case -the argument demand from g. Whizzo! g evaluates both components of -its argument pair, so p will certainly be evaluated if j is called. +If j was a vanilla function definition, we'd analyse its body with evalDmd, and +think that it was lazy in p. But for join points we can do better! We know +that j's body will (if called at all) be evaluated with the demand that consumes +the entire join-binding, in this case the argument demand from g. Whizzo! g +evaluates both components of its argument pair, so p will certainly be evaluated +if j is called. -For f to be strict in p, we need /all/ paths to evaluate p; in this -case the C branch does so too, so we are fine. So, as usual, we need -to transport demands on free variables to the call site(s). Compare -Note [Lazy and unleashable free variables]. +For f to be strict in p, we need /all/ paths to evaluate p; in this case the C +branch does so too, so we are fine. So, as usual, we need to transport demands +on free variables to the call site(s). Compare Note [Lazy and unleashable free +variables]. -The implementation is easy. When analysing a join point, we can -analyse its body with the demand from the entire join-binding (written -let_dmd here). +The implementation is easy: see `body_subdmd` in`dmdAnalRhsSig`. When analysing +a join point, we can analyse its body (after stripping off the join binders, +here just 'y') with the demand from the entire join-binding (written `let_subdmd` +here). Another win for join points! #13543. -However, note that the strictness signature for a join point can -look a little puzzling. E.g. +BUT see Note [Worker/wrapper arity and join points]. +Note we may analyse the rhs of a join point with a demand that is either +bigger than, or smaller than, the number of lambdas syntactically visible. +* More lambdas than call demands: + join j x = \p q r -> blah in ... + in a context with demand Top. + +* More call demands than lambdas: + (join j x = h in ..(j 2)..(j 3)) a b c + +Note [Worker/wrapper arity and join points] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider (join j x = \y. error "urk") (in case v of ) ( A -> j 3 ) x ( B -> j 4 ) ( C -> \y. blah ) -The entire thing is in a C(1,L) context, so j's strictness signature -will be [A]b -meaning one absent argument, returns bottom. That seems odd because -there's a \y inside. But it's right because when consumed in a C(1,L) -context the RHS of the join point is indeed bottom. +The entire thing is in a C(1,L) context, so we will analyse j's body, namely + \y. error "urk" +with demand C(C(1,L)). See `rhs_subdmd` in `dmdAnalRhsSig`. That will produce +a demand signature of b: and indeed `j` diverges when given two arguments. + +BUT we do /not/ want to worker/wrapper `j` with two arguments. Suppose we have + join j2 :: Int -> Int -> blah + j2 x = rhs + in ...(j2 3)...(j2 4)... + +where j2's join-arity is 1, so calls to `j` will all have /one/ argument. +Suppose the entire expression is in a called context (like `j` above) and `j2` +gets the demand signature , that is, strict in both arguments. + +we worker/wrapper'd `j2` with two args we'd get + join $wj2 x# y# = let x = I# x#; y = I# y# in rhs + j2 x = \y. case x of I# x# -> case y of I# y# -> $wj2 x# y# + in ...(j2 3)...(j2 4)... +But now `$wj2`is no longer a join point. Boo. + +Instead if we w/w at all, we want to do so only with /one/ argument: + join $wj2 x# = let x = I# x# in rhs + j2 x = case x of I# x# -> $wj2 x# + in ...(j2 3)...(j2 4)... +Now all is fine. BUT in `finaliseArgBoxities` we should trim y's boxity, +to reflect the fact tta we aren't going to unbox `y` at all. -Note [Demand signatures are computed for a threshold arity based on idArity] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Given a binding { f = rhs }, we compute a "threshold arity", and do demand -analysis based on a call with that many value arguments. +Conclusion: -The threshold we use is +(1) The "worker/wrapper arity" of an Id is + * For non-join-points: idArity + * The join points: the join arity (Id part only of course) + This is the number of args we will use in worker/wrapper. + See `ww_arity` in `dmdAnalRhsSig`, and the function workWrapArity. -* Ordinary bindings: idArity f. +(2) A join point's demand-signature arity may exceed the Id's worker/wrapper + arity. See the `arity_ok` assertion in `mkWwBodies`. + +(3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond + the worker/wrapper arity. + +(4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper + arity (re)-computed by workWrapArity. + +Note [The demand for the RHS of a binding] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Given a binding { f = rhs }, in `dmdAnalRhsSig` we compute a `rhs_subdmd` in +which to analyse `rhs`. + +The demand we use is: + +* Ordinary bindings: a call-demand of depth (idArity f). Why idArity arguments? Because that's a conservative estimate of how many arguments we must feed a function before it does anything interesting with them. Also it elegantly subsumes the trivial RHS and PAP case. E.g. for @@ -1285,22 +1336,17 @@ The threshold we use is idArity is /at least/ the number of manifest lambdas, but might be higher for PAPs and trivial RHS (see Note [Demand analysis for trivial right-hand sides]). -* Join points: the value-binder subset of the JoinArity. This can - be less than the number of visible lambdas; e.g. - join j x = \y. blah - in ...(jump j 2)....(jump j 3).... - We know that j will never be applied to more than 1 arg (its join - arity, and we don't eta-expand join points, so here a threshold - of 1 is the best we can do. +* Join points: a call-demand of depth (value-binder subset of JoinArity), + wrapped around the incoming demand for the entire expression; see + Note [Demand analysis for join points] Note that the idArity of a function varies independently of its cardinality properties (cf. Note [idArity varies independently of dmdTypeDepth]), so we -implicitly encode the arity for when a demand signature is sound to unleash -in its 'dmdTypeDepth', not in its idArity (cf. Note [Understanding DmdType -and DmdSig] in GHC.Types.Demand). It is unsound to unleash a demand -signature when the incoming number of arguments is less than that. See -GHC.Types.Demand Note [What are demand signatures?] for more details on -soundness. +implicitly encode the arity for when a demand signature is sound to unleash in +its 'dmdTypeDepth', not in its idArity (cf. Note [Understanding DmdType and +DmdSig] in GHC.Types.Demand). It is unsound to unleash a demand signature when +the incoming number of arguments is less than that. See GHC.Types.Demand +Note [DmdSig: demand signatures, and demand-sig arity]. Note that there might, in principle, be functions for which we might want to analyse for more incoming arguments than idArity. Example: @@ -1929,7 +1975,7 @@ finaliseArgBoxities :: AnalEnv -> Id -> Arity -- Then: -- dmds' is the same as dmds (including length), except for boxity info -- rhs' is the same as rhs, except for dmd info on lambda binders --- NB: length dmds might be greater than ww_arity +-- NB: For join points, length dmds might be greater than ww_arity finaliseArgBoxities env fn ww_arity arg_dmds div rhs -- Check for an OPAQUE function: see Note [OPAQUE pragma] @@ -1952,8 +1998,7 @@ finaliseArgBoxities env fn ww_arity arg_dmds div rhs = (arg_dmds, rhs) -- The normal case - | otherwise -- NB: ww_arity might be less than - -- manifest arity for join points + | otherwise = -- pprTrace "finaliseArgBoxities" ( -- vcat [text "function:" <+> ppr fn -- , text "max" <+> ppr max_wkr_args @@ -1979,6 +2024,7 @@ finaliseArgBoxities env fn ww_arity arg_dmds div rhs arg_dmds' = ww_arg_dmds ++ map trimBoxity (drop ww_arity arg_dmds) -- If ww_arity < length arg_dmds, the leftover ones -- will not be w/w'd, so trimBoxity them + -- See Note [Worker/wrapper arity and join points] point (3) -- This is the key line, which uses almost-circular programming -- The remaining budget from one layer becomes the initial ===================================== compiler/GHC/Core/Opt/WorkWrap.hs ===================================== @@ -797,6 +797,7 @@ splitFun ww_opts fn_id rhs uf_opts = so_uf_opts (wo_simple_opts ww_opts) fn_info = idInfo fn_id ww_arity = workWrapArity fn_id rhs + -- workWrapArity: see (4) in Note [Worker/wrapper arity and join points] in DmdAnal (wrap_dmds, div) = splitDmdSig (dmdSigInfo fn_info) ===================================== compiler/GHC/Core/Opt/WorkWrap/Utils.hs ===================================== @@ -294,7 +294,7 @@ isWorkerSmallEnough max_worker_args old_n_args vars -- it takes <= 82 arguments afterwards. workWrapArity :: Id -> CoreExpr -> Arity --- See Note [Demand signatures are computed for a threshold arity based on idArity] +-- See Note [Worker/wrapper arity and join points] in DmdAnal workWrapArity fn rhs = case idJoinPointHood fn of JoinPoint join_arity -> count isId $ fst $ collectNBinders join_arity rhs ===================================== compiler/GHC/Types/Demand.hs ===================================== @@ -2084,6 +2084,11 @@ body of the function. * * ************************************************************************ +Note [DmdSig: demand signatures, and demand-sig arity] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +See also + * Note [Demand signatures semantically] + * Note [Understanding DmdType and DmdSig] In a let-bound Id we record its demand signature. In principle, this demand signature is a demand transformer, mapping a demand on the Id into a DmdType, which gives @@ -2094,20 +2099,22 @@ a demand on the Id into a DmdType, which gives However, in fact we store in the Id an extremely emasculated demand transformer, namely - - a single DmdType + a single DmdType (Nevertheless we dignify DmdSig as a distinct type.) -This DmdType gives the demands unleashed by the Id when it is applied -to as many arguments as are given in by the arg demands in the DmdType. +The DmdSig for an Id is a semantic thing. Suppose a function `f` has a DmdSig of + DmdSig (DmdType (fv_dmds,res) [d1..dn]) +Here `n` is called the "demand-sig arity" of the DmdSig. The signature means: + * If you apply `f` to n arguments (the demand-sig-arity) + * then you can unleash demands d1..dn on the arguments + * and demands fv_dmds on the free variables. Also see Note [Demand type Divergence] for the meaning of a Divergence in a -strictness signature. +demand signature. -If an Id is applied to less arguments than its arity, it means that -the demand on the function at a call site is weaker than the vanilla -call demand, used for signature inference. Therefore we place a top -demand on all arguments. Otherwise, the demand is specified by Id's -signature. +If `f` is applied to fewer value arguments than its demand-sig arity, it means +that the demand on the function at a call site is weaker than the vanilla call +demand, used for signature inference. Therefore we place a top demand on all +arguments. For example, the demand transformer described by the demand signature DmdSig (DmdType {x -> <1L>} <1P(L,L)>) @@ -2118,6 +2125,61 @@ and 1P(L,L) on the second. If this same function is applied to one arg, all we can say is that it uses x with 1L, and its arg with demand 1P(L,L). +Note [Demand signatures semantically] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Demand analysis interprets expressions in the abstract domain of demand +transformers. Given a (sub-)demand that denotes the evaluation context, the +abstract transformer of an expression gives us back a demand type denoting +how other things (like arguments and free vars) were used when the expression +was evaluated. Here's an example: + + f x y = + if x + expensive + then \z -> z + y * ... + else \z -> z * ... + +The abstract transformer (let's call it F_e) of the if expression (let's +call it e) would transform an incoming (undersaturated!) head demand 1A into +a demand type like {x-><1L>,y->}. In pictures: + + Demand ---F_e---> DmdType + <1A> {x-><1L>,y->} + +Let's assume that the demand transformers we compute for an expression are +correct wrt. to some concrete semantics for Core. How do demand signatures fit +in? They are strange beasts, given that they come with strict rules when to +it's sound to unleash them. + +Fortunately, we can formalise the rules with Galois connections. Consider +f's strictness signature, {}<1L>. It's a single-point approximation of +the actual abstract transformer of f's RHS for arity 2. So, what happens is that +we abstract *once more* from the abstract domain we already are in, replacing +the incoming Demand by a simple lattice with two elements denoting incoming +arity: A_2 = {<2, >=2} (where '<2' is the top element and >=2 the bottom +element). Here's the diagram: + + A_2 -----f_f----> DmdType + ^ | + | α γ | + | v + SubDemand --F_f----> DmdType + +With + α(C(1,C(1,_))) = >=2 + α(_) = <2 + γ(ty) = ty +and F_f being the abstract transformer of f's RHS and f_f being the abstracted +abstract transformer computable from our demand signature simply by + + f_f(>=2) = {}<1L> + f_f(<2) = multDmdType C_0N {}<1L> + +where multDmdType makes a proper top element out of the given demand type. + +In practice, the A_n domain is not just a simple Bool, but a Card, which is +exactly the Card with which we have to multDmdType. The Card for arity n +is computed by calling @peelManyCalls n@, which corresponds to α above. + Note [Understanding DmdType and DmdSig] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Demand types are sound approximations of an expression's semantics relative to @@ -2130,9 +2192,9 @@ Here is a table with demand types resulting from different incoming demands we put that expression under. Note the monotonicity; a stronger incoming demand yields a more precise demand type: - incoming demand | demand type + incoming demand | demand type -------------------------------- - 1A | {} + 1A | {} C(1,C(1,L)) | <1P(L)>{} C(1,C(1,1P(1P(L),A))) | <1P(A)>{} @@ -2154,11 +2216,11 @@ being a newtype wrapper around DmdType, it actually encodes two things: * A demand type that is sound to unleash when the minimum arity requirement is met. -Here comes the subtle part: The threshold is encoded in the wrapped demand -type's depth! So in mkDmdSigForArity we make sure to trim the list of -argument demands to the given threshold arity. Call sites will make sure that -this corresponds to the arity of the call demand that elicited the wrapped -demand type. See also Note [What are demand signatures?]. +Here comes the subtle part: The threshold is encoded in the demand-sig arity! +So in mkDmdSigForArity we make sure to trim the list of argument demands to the +given threshold arity. Call sites will make sure that this corresponds to the +arity of the call demand that elicited the wrapped demand type. See also Note +[What are demand signatures?]. -} -- | The depth of the wrapped 'DmdType' encodes the arity at which it is safe @@ -2369,61 +2431,6 @@ dmdTransformDictSelSig (DmdSig (DmdType _ [_ :* prod])) call_sd dmdTransformDictSelSig sig sd = pprPanic "dmdTransformDictSelSig: no args" (ppr sig $$ ppr sd) {- -Note [What are demand signatures?] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Demand analysis interprets expressions in the abstract domain of demand -transformers. Given a (sub-)demand that denotes the evaluation context, the -abstract transformer of an expression gives us back a demand type denoting -how other things (like arguments and free vars) were used when the expression -was evaluated. Here's an example: - - f x y = - if x + expensive - then \z -> z + y * ... - else \z -> z * ... - -The abstract transformer (let's call it F_e) of the if expression (let's -call it e) would transform an incoming (undersaturated!) head demand 1A into -a demand type like {x-><1L>,y->}. In pictures: - - Demand ---F_e---> DmdType - <1A> {x-><1L>,y->} - -Let's assume that the demand transformers we compute for an expression are -correct wrt. to some concrete semantics for Core. How do demand signatures fit -in? They are strange beasts, given that they come with strict rules when to -it's sound to unleash them. - -Fortunately, we can formalise the rules with Galois connections. Consider -f's strictness signature, {}<1L>. It's a single-point approximation of -the actual abstract transformer of f's RHS for arity 2. So, what happens is that -we abstract *once more* from the abstract domain we already are in, replacing -the incoming Demand by a simple lattice with two elements denoting incoming -arity: A_2 = {<2, >=2} (where '<2' is the top element and >=2 the bottom -element). Here's the diagram: - - A_2 -----f_f----> DmdType - ^ | - | α γ | - | v - SubDemand --F_f----> DmdType - -With - α(C(1,C(1,_))) = >=2 - α(_) = <2 - γ(ty) = ty -and F_f being the abstract transformer of f's RHS and f_f being the abstracted -abstract transformer computable from our demand signature simply by - - f_f(>=2) = {}<1L> - f_f(<2) = multDmdType C_0N {}<1L> - -where multDmdType makes a proper top element out of the given demand type. - -In practice, the A_n domain is not just a simple Bool, but a Card, which is -exactly the Card with which we have to multDmdType. The Card for arity n -is computed by calling @peelManyCalls n@, which corresponds to α above. - Note [Demand transformer for a dictionary selector] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Suppose we have a superclass selector 'sc_sel' and a class method View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4bfc49f93cd7760e4375549375742d37d956c0e1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4bfc49f93cd7760e4375549375742d37d956c0e1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 10:36:26 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 14 Jun 2024 06:36:26 -0400 Subject: [Git][ghc/ghc][wip/T24623] Wibble note Message-ID: <666c1d2a9af6e_205b2f8ff264119ba@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24623 at Glasgow Haskell Compiler / GHC Commits: bca8931c by Simon Peyton Jones at 2024-06-14T11:36:13+01:00 Wibble note - - - - - 1 changed file: - compiler/GHC/Types/Demand.hs Changes: ===================================== compiler/GHC/Types/Demand.hs ===================================== @@ -2089,6 +2089,7 @@ Note [DmdSig: demand signatures, and demand-sig arity] See also * Note [Demand signatures semantically] * Note [Understanding DmdType and DmdSig] + In a let-bound Id we record its demand signature. In principle, this demand signature is a demand transformer, mapping a demand on the Id into a DmdType, which gives View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bca8931c24da9f51fd0548e3943f69c5e853b2bc -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bca8931c24da9f51fd0548e3943f69c5e853b2bc You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 11:48:27 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Fri, 14 Jun 2024 07:48:27 -0400 Subject: [Git][ghc/ghc][wip/T14030] Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) Message-ID: <666c2e0bcfa5d_205b2f11e9f28281bb@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: 90eb495b by Sebastian Graf at 2024-06-14T13:47:21+02:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. - - - - - 8 changed files: - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - testsuite/tests/ghci/scripts/T21110.stderr - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/th/TH_Lift.hs - + testsuite/tests/th/TH_Lift.stderr - testsuite/tests/th/all.T Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs ===================================== @@ -42,7 +42,7 @@ module GHC.Internal.TH.Lift where import GHC.Internal.TH.Syntax -import GHC.Internal.TH.Lib () -- See wrinkle (W4) of Note [Tracking dependencies on primitives] +import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives] import GHC.Internal.Lexeme ( startsVarSym, startsVarId ) import GHC.Internal.Data.Either @@ -54,8 +54,9 @@ import GHC.Internal.Integer import GHC.Internal.Real import GHC.Internal.Word import GHC.Internal.Int -import GHC.Internal.Data.Data +import GHC.Internal.Data.Data hiding (Fixity) import GHC.Internal.Natural +import GHC.Internal.ForeignPtr -- | A 'Lift' instance can have any of its values turned into a Template -- Haskell expression. This is needed when a value used within a Template @@ -305,6 +306,140 @@ rightName = 'Right nonemptyName :: Name nonemptyName = '(:|) +----------------------------------------------------- +-- +-- Lifting the TH AST +-- +----------------------------------------------------- + +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Loc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DocLoc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ModName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift GHC.Internal.TH.Syntax.Module +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameSpace +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NamespaceSpecifier +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PkgName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameFlavour +-- | @since template-haskell-2.22.1.0 +deriving instance Lift OccName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Name +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameIs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Specificity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift BndrVis +-- | @since template-haskell-2.22.1.0 +deriving instance Lift a => Lift (TyVarBndr a) +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TyLit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Type +-- | @since template-haskell-2.22.1.0 +instance Lift Bytes where + lift bytes = -- See Note [Why FinalPtr] + [| Bytes + { bytesPtr = ForeignPtr $(Lib.litE (BytesPrimL bytes)) FinalPtr + , bytesOffset = 0 + , bytesSize = $(lift (bytesSize bytes)) + } + |] +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Lit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pat +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Clause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivClause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivStrategy +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Overlap +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FunDep +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Safety +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Callconv +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Foreign +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ForeignSrcLang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FixityDirection +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Fixity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Inline +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleMatch +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Phases +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleBndr +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnTarget +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pragma +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceUnpackedness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DecidedStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Bang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Con +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TySynEqn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FamilyResultSig +-- | @since template-haskell-2.22.1.0 +deriving instance Lift InjectivityAnn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TypeFamilyHead +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Role +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynArgs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynDir +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Dec +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Range +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Exp +-- | @since template-haskell-2.22.1.0 +instance Lift (TExp a) where + lift (TExp e) = [| TExp $(lift e) |] + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Match +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Guard +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Stmt +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Body +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Info +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnLookup +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Extension + ----------------------------------------------------- -- -- Generic Lift implementations ===================================== libraries/template-haskell/changelog.md ===================================== @@ -1,5 +1,9 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) +## 2.22.1.0 + + * `Lift` instances were added for the `template-haskell` AST. + ## 2.22.0.0 * The kind of `Code` was changed from `forall r. (Type -> Type) -> TYPE r -> Type` ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -3,7 +3,7 @@ -- template-haskell.cabal. name: template-haskell -version: 2.22.0.0 +version: 2.22.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE ===================================== testsuite/tests/ghci/scripts/T21110.stderr ===================================== @@ -1,5 +1,5 @@ - : warning: [GHC-42258] [-Wunused-packages] The following packages were specified via -package or -package-id flags, but were not needed for compilation: - - template-haskell-2.22.0.0 (exposed by flag -package template-haskell) + - template-haskell-2.22.1.0 (exposed by flag -package template-haskell) + ===================================== testsuite/tests/interface-stability/template-haskell-exports.stdout ===================================== @@ -2420,11 +2420,37 @@ instance GHC.Internal.Show.Show GHC.Internal.LanguageExtensions.Extension -- Def instance GHC.Internal.Show.Show GHC.Internal.TH.Ppr.ForallVisFlag -- Defined in ‘GHC.Internal.TH.Ppr’ instance [safe] GHC.Internal.Show.Show GHC.Internal.TH.PprLib.Doc -- Defined in ‘GHC.Internal.TH.PprLib’ instance GHC.Internal.Show.Show GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.ForeignSrcLang’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnLookup -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnTarget -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.BndrVis -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Body -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Bool -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bytes -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Callconv -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Char -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Clause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Con -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Dec -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DecidedStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivClause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivStrategy -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DocLoc -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Double -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (GHC.Internal.Data.Either.Either a b) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Exp -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.LanguageExtensions.Extension -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FamilyResultSig -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Fixity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FixityDirection -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Float -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Foreign -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FunDep -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Guard -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Info -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.InjectivityAnn -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Inline -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Int -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int16 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int32 -- Defined in ‘GHC.Internal.TH.Lift’ @@ -2432,16 +2458,49 @@ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int64 -- Defined in ‘GHC.I instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int8 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Integer.Integer -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift [a] -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Lit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Loc -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Match -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Maybe.Maybe a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.ModName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Module -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Name -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameFlavour -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameIs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameSpace -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NamespaceSpecifier -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Natural.Natural -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.OccName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Overlap -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pat -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynArgs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynDir -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Phases -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PkgName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pragma -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Range -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.Real.Integral a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Real.Ratio a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Role -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleBndr -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleMatch -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Safety -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceUnpackedness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Specificity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Stmt -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TExp a) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (a, b) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c) => GHC.Internal.TH.Lift.Lift (a, b, c) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d) => GHC.Internal.TH.Lift.Lift (a, b, c, d) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f g. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f, GHC.Internal.TH.Lift.Lift g) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f, g) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TyLit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TySynEqn -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TyVarBndr a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Type -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TypeFamilyHead -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift () -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Word -- Defined in ‘GHC.Internal.TH.Lift’ ===================================== testsuite/tests/th/TH_Lift.hs ===================================== @@ -1,6 +1,7 @@ -- test Lifting instances {-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE MagicHash #-} module TH_Lift where @@ -10,6 +11,8 @@ import Data.Word import Data.Int import Numeric.Natural import Data.List.NonEmpty +import qualified Data.ByteString as B +import qualified Data.ByteString.Internal as B a :: Integer a = $( (\x -> [| x |]) (5 :: Integer) ) @@ -80,3 +83,17 @@ o = $( (\x -> [| x |]) (True, 'x', 4 :: Int) ) p :: NonEmpty Char p = $( (\x -> [| x |]) ('a' :| "bcde") ) +exp :: Exp +exp = $( [| 3 + 4 |] >>= lift ) + +texp :: TExp Int +texp = $$( examineCode [|| 3 + 4 ||] `bindCode` liftTyped ) + +bytes :: Bytes +bytes = $(do + let (fp, offset, size) = B.toForeignPtr (B.pack [72, 101, 108, 108, 111]) -- "hello"# + let bytes = Bytes { bytesPtr = fp + , bytesOffset = fromIntegral offset + , bytesSize = fromIntegral size + } + lift bytes) ===================================== testsuite/tests/th/TH_Lift.stderr ===================================== @@ -0,0 +1,197 @@ +TH_Lift.hs:18:6-39: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Integer) + ======> + 5 +TH_Lift.hs:21:6-35: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int) + ======> + 5 +TH_Lift.hs:24:7-37: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int8) + ======> + 5 +TH_Lift.hs:27:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int16) + ======> + 5 +TH_Lift.hs:30:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int32) + ======> + 5 +TH_Lift.hs:33:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int64) + ======> + 5 +TH_Lift.hs:36:6-36: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word) + ======> + 5 +TH_Lift.hs:39:6-37: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word8) + ======> + 5 +TH_Lift.hs:42:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word16) + ======> + 5 +TH_Lift.hs:45:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word32) + ======> + 5 +TH_Lift.hs:48:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word64) + ======> + 5 +TH_Lift.hs:51:7-40: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Natural) + ======> + 5 +TH_Lift.hs:54:6-44: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 % 3 :: Rational) + ======> + 1.6666666666666667 +TH_Lift.hs:57:7-39: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (pi :: Float) + ======> + 3.1415927410125732 +TH_Lift.hs:60:7-40: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (pi :: Double) + ======> + 3.141592653589793 +TH_Lift.hs:63:6-28: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + 'x' + ======> + 'x' +TH_Lift.hs:66:6-29: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + True + ======> + True +TH_Lift.hs:69:6-35: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (Just 'x') + ======> + Just 'x' +TH_Lift.hs:72:6-58: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (Right False :: Either Char Bool) + ======> + Right False +TH_Lift.hs:75:6-29: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + "hi!" + ======> + "hi!" +TH_Lift.hs:78:6-27: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + () + ======> + () +TH_Lift.hs:81:6-46: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (True, 'x', 4 :: Int) + ======> + (,,) True 'x' 4 +TH_Lift.hs:84:6-41: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + ('a' :| "bcde") + ======> + (:|) 'a' "bcde" +TH_Lift.hs:87:8-31: Splicing expression + [| 3 + 4 |] >>= lift + ======> + InfixE + (Just (LitE (IntegerL 3))) + (VarE + (Name + (OccName "+") + (NameG + VarName (PkgName "ghc-internal") (ModName "GHC.Internal.Num")))) + (Just (LitE (IntegerL 4))) +TH_Lift.hs:(93,10)-(99,13): Splicing expression + do let (fp, offset, size) + = B.toForeignPtr (B.pack [72, 101, 108, 108, 111]) + let bytes + = Bytes + {bytesPtr = fp, bytesOffset = fromIntegral offset, + bytesSize = fromIntegral size} + lift bytes + ======> + Bytes + {bytesPtr = GHC.Internal.ForeignPtr.ForeignPtr + "Hello"# GHC.Internal.ForeignPtr.FinalPtr, + bytesOffset = 0, bytesSize = 5} +TH_Lift.hs:90:10-59: Splicing expression + examineCode [|| 3 + 4 ||] `bindCode` liftTyped + ======> + TExp + (InfixE + (Just (LitE (IntegerL 3))) + (VarE + (Name + (OccName "+") + (NameG + VarName (PkgName "ghc-internal") (ModName "GHC.Internal.Num")))) + (Just (LitE (IntegerL 4)))) ===================================== testsuite/tests/th/all.T ===================================== @@ -318,7 +318,7 @@ test('T1476', normal, compile, ['-v0']) test('T1476b', normal, compile, ['-v0']) test('T8031', normal, compile, ['-v0']) test('T8624', only_ways(['normal']), makefile_test, ['T8624']) -test('TH_Lift', normal, compile, ['-v0']) +test('TH_Lift', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques']) test('T10047', only_ways(['ghci']), ghci_script, ['T10047.script']) test('T10019', only_ways(['ghci']), ghci_script, ['T10019.script']) test('T10267', [], multimod_compile_fail, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/90eb495b75e5e7178a8855d403f9c74cff6914f9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/90eb495b75e5e7178a8855d403f9c74cff6914f9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 11:54:22 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 14 Jun 2024 07:54:22 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] SIMD: add vector FMA primops Message-ID: <666c2f6e94274_205b2f13f29c8314fa@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: cd3c0b64 by sheaf at 2024-06-14T13:54:06+02:00 SIMD: add vector FMA primops - - - - - 16 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/StgToJS/Prim.hs - libraries/base/src/GHC/Exts.hs - testsuite/tests/simd/should_run/all.T - + testsuite/tests/simd/should_run/simd011.hs - + testsuite/tests/simd/should_run/simd011.stdout Changes: ===================================== compiler/GHC/Builtin/primops.txt.pp ===================================== @@ -4190,6 +4190,31 @@ primop VecWriteScalarOffAddrOp "writeOffAddrAs#" GenPrimOp llvm_only = True vector = ALL_VECTOR_TYPES +primop VecFMAdd "fmadd#" GenPrimOp + VECTOR -> VECTOR -> VECTOR -> VECTOR + {Fused multiply-add operation @x*y+z at . See "GHC.Prim#fma".} + with + llvm_only = True + vector = FLOAT_VECTOR_TYPES +primop VecFMSub "fmsub#" GenPrimOp + VECTOR -> VECTOR -> VECTOR -> VECTOR + {Fused multiply-subtract operation @x*y-z at . See "GHC.Prim#fma".} + with + llvm_only = True + vector = FLOAT_VECTOR_TYPES +primop VecFNMAdd "fnmadd#" GenPrimOp + VECTOR -> VECTOR -> VECTOR -> VECTOR + {Fused negate-multiply-add operation @-x*y+z at . See "GHC.Prim#fma".} + with + llvm_only = True + vector = FLOAT_VECTOR_TYPES +primop VecFNMSub "fnmsub#" GenPrimOp + VECTOR -> VECTOR -> VECTOR -> VECTOR + {Fused negate-multiply-subtract operation @-x*y-z at . See "GHC.Prim#fma".} + with + llvm_only = True + vector = FLOAT_VECTOR_TYPES + primop VecShuffleOp "shuffle#" GenPrimOp VECTOR -> VECTOR -> INTVECTUPLE -> VECTOR { Shuffle elements of the concatenation of the input two vectors ===================================== compiler/GHC/Cmm/MachOp.hs ===================================== @@ -116,7 +116,7 @@ data MachOp -- Floating-point fused multiply-add operations -- | Fused multiply-add, see 'FMASign'. - | MO_FMA FMASign Width + | MO_FMA FMASign Length Width -- Floating point comparison | MO_F_Eq Width @@ -465,7 +465,7 @@ machOpResultType platform mop tys = MO_F_Quot r -> cmmFloat r MO_F_Neg r -> cmmFloat r - MO_FMA _ r -> cmmFloat r + MO_FMA _ l r -> if l == 1 then cmmFloat r else cmmVec l (cmmFloat r) MO_F_Eq {} -> comparisonResultRep platform MO_F_Ne {} -> comparisonResultRep platform @@ -567,7 +567,7 @@ machOpArgReps platform op = MO_F_Quot r -> [r,r] MO_F_Neg r -> [r] - MO_FMA _ r -> [r,r,r] + MO_FMA _ l r -> [vecwidth l r, vecwidth l r, vecwidth l r] MO_F_Eq r -> [r,r] MO_F_Ne r -> [r,r] ===================================== compiler/GHC/Cmm/Parser.y ===================================== @@ -1051,10 +1051,10 @@ machOps = listToUFM $ ( "fmul", MO_F_Mul ), ( "fquot", MO_F_Quot ), - ( "fmadd" , MO_FMA FMAdd ), - ( "fmsub" , MO_FMA FMSub ), - ( "fnmadd", MO_FMA FNMAdd ), - ( "fnmsub", MO_FMA FNMSub ), + ( "fmadd" , MO_FMA FMAdd 1), + ( "fmsub" , MO_FMA FMSub 1), + ( "fnmadd", MO_FMA FNMAdd 1), + ( "fnmsub", MO_FMA FNMSub 1), ( "feq", MO_F_Eq ), ( "fne", MO_F_Ne ), ===================================== compiler/GHC/CmmToAsm/AArch64/CodeGen.hs ===================================== @@ -1218,11 +1218,15 @@ getRegister' config plat expr -- x86 fnmadd - x * y + z <=> AArch64 fmsub : d = - r1 * r2 + r3 -- x86 fnmsub - x * y - z <=> AArch64 fnmadd: d = - r1 * r2 - r3 - MO_FMA var w -> case var of - FMAdd -> float3Op w (\d n m a -> unitOL $ FMA FMAdd d n m a) - FMSub -> float3Op w (\d n m a -> unitOL $ FMA FNMSub d n m a) - FNMAdd -> float3Op w (\d n m a -> unitOL $ FMA FMSub d n m a) - FNMSub -> float3Op w (\d n m a -> unitOL $ FMA FNMAdd d n m a) + MO_FMA var l w + | l == 1 + -> case var of + FMAdd -> float3Op w (\d n m a -> unitOL $ FMA FMAdd d n m a) + FMSub -> float3Op w (\d n m a -> unitOL $ FMA FNMSub d n m a) + FNMAdd -> float3Op w (\d n m a -> unitOL $ FMA FMSub d n m a) + FNMSub -> float3Op w (\d n m a -> unitOL $ FMA FNMAdd d n m a) + | otherwise + -> vectorsNeedLlvm MO_V_Insert {} -> vectorsNeedLlvm MO_VF_Insert {} -> vectorsNeedLlvm ===================================== compiler/GHC/CmmToAsm/Format.hs ===================================== @@ -19,6 +19,7 @@ module GHC.CmmToAsm.Format ( floatFormat, isIntFormat, isFloatFormat, + vecFormat, isVecFormat, cmmTypeFormat, formatToWidth, ===================================== compiler/GHC/CmmToAsm/PPC/CodeGen.hs ===================================== @@ -687,12 +687,14 @@ getRegister' _ _ (CmmMachOp mop [x, y, z]) -- ternary PrimOps -- x86 fnmadd - x * y + z ~~ PPC fnmsub rt = -(ra * rc - rb) -- x86 fnmsub - x * y - z ~~ PPC fnmadd rt = -(ra * rc + rb) - MO_FMA variant w -> + MO_FMA variant l w | l == 1 -> case variant of FMAdd -> fma_code w (FMADD FMAdd) x y z FMSub -> fma_code w (FMADD FMSub) x y z FNMAdd -> fma_code w (FMADD FNMAdd) x y z FNMSub -> fma_code w (FMADD FNMSub) x y z + | otherwise + -> vectorsNeedLlvm MO_V_Insert {} -> vectorsNeedLlvm MO_VF_Insert {} -> vectorsNeedLlvm ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1851,18 +1851,22 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps sse <- sseEnabled case mop of -- Floating point fused multiply-add operations @ ± x*y ± z@ - MO_FMA var w -> genFMA3Code w var x y z + MO_FMA var l w + | l * widthInBits w > 256 + -> sorry "Please use -fllvm for wide vector FMA support" + | otherwise + -> genFMA3Code l w var x y z -- Ternary vector operations MO_VF_Insert l W32 | sse4_1 && sse -> vector_float_insert l W32 x y z | otherwise - -> sorry "Please enable the -msse4 and -msse flag" + -> sorry "Please enable the -msse4 and -msse flags" MO_VF_Insert l W64 | sse2 && sse -> vector_float_insert l W64 x y z | otherwise - -> sorry "Please enable the -msse2 and -msse flag" + -> sorry "Please enable the -msse2 and -msse flags" MO_V_Insert l W64 | sse2 && sse -> vector_int_insert_sse l W64 x y z | otherwise - -> sorry "Please enable the -msse2 and -msse flag" + -> sorry "Please enable the -msse2 and -msse flags" _other -> pprPanic "getRegister(x86) - ternary CmmMachOp (1)" (pprMachOp mop) @@ -4029,10 +4033,12 @@ _ `regClashesWithOp` _ = False -- | Generate code for a fused multiply-add operation, of the form @± x * y ± z@, -- with 3 operands (FMA3 instruction set). -genFMA3Code :: Width +genFMA3Code :: Length + -> Width -> FMASign -> CmmExpr -> CmmExpr -> CmmExpr -> NatM Register -genFMA3Code w signs x y z = do +genFMA3Code l w signs x y z = do + platform <- getPlatform -- For the FMA instruction, we want to compute x * y + z -- -- There are three possible instructions we could emit: @@ -4059,7 +4065,11 @@ genFMA3Code w signs x y z = do -- only possible if the other arguments don't use the destination register. -- We check for this and if there is a conflict we move the result only after -- the computation. See #24496 how this went wrong in the past. - let rep = floatFormat w + let rep + | l == 1 + = floatFormat w + | otherwise + = vecFormat (cmmVec l $ cmmFloat w) (y_reg, y_code) <- getNonClobberedReg y (z_op, z_code) <- getNonClobberedOperand z x_code <- getAnyReg x @@ -4069,17 +4079,17 @@ genFMA3Code w signs x y z = do code, code_direct, code_mov :: Reg -> InstrBlock -- Ideal: Compute the result directly into dst - code_direct dst = x_code dst `snocOL` + code_direct dst = x_code dst `snocOL` fma213 z_op y_reg dst -- Fallback: Compute the result into a tmp reg and then move it. code_mov dst = x_code x_tmp `snocOL` fma213 z_op y_reg x_tmp `snocOL` - MOV rep (OpReg x_tmp) (OpReg dst) + mkRegRegMoveInstr platform rep x_tmp dst code dst = - y_code `appOL` - z_code `appOL` - ( if arg_regs_conflict then code_mov dst else code_direct dst ) + y_code `appOL` + z_code `appOL` + ( if arg_regs_conflict then code_mov dst else code_direct dst ) where ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -285,7 +285,7 @@ data Instr -- | FMA3 fused multiply-add operations. | FMA3 Format FMASign FMAPermutation Operand Reg Reg -- src3 (r/m), src2 (r), dst/src1 (r) - -- The is exactly reversed from how intel lists the arguments. + -- This is exactly reversed from how intel lists the arguments. -- use ADD, SUB, and SQRT for arithmetic. In both cases, operands -- are Operand Reg. ===================================== compiler/GHC/CmmToC.hs ===================================== @@ -727,7 +727,7 @@ pprMachOp_for_C platform mop = case mop of MO_F_Quot _ -> char '/' -- Floating-point fused multiply-add operations - MO_FMA FMAdd w -> + MO_FMA FMAdd 1 w -> case w of W32 -> text "fmaf" W64 -> text "fma" @@ -736,10 +736,15 @@ pprMachOp_for_C platform mop = case mop of (text "FMAdd") (panic $ "PprC.pprMachOp_for_C: FMAdd unsupported" ++ "at width " ++ show w) - MO_FMA var _width -> - pprTrace "offending mop:" - (text $ "FMA " ++ show var) - (panic $ "PprC.pprMachOp_for_C: should have been handled earlier!") + MO_FMA var l width + | l == 1 + -> pprTrace "offending mop:" + (text $ "FMA " ++ show var) + (panic $ "PprC.pprMachOp_for_C: should have been handled earlier!") + | otherwise + -> pprTrace "offending mop:" + (text $ "FMA " ++ show var ++ " " ++ show l ++ " " ++ show width) + (panic $ "PprC.pprMachOp_for_C: unsupported vector operation") -- Signed comparisons MO_S_Ge _ -> text ">=" ===================================== compiler/GHC/CmmToLlvm/CodeGen.hs ===================================== @@ -1491,7 +1491,7 @@ genMachOp _ op [x] = case op of MO_F_Mul _ -> panicOp MO_F_Quot _ -> panicOp - MO_FMA _ _ -> panicOp + MO_FMA _ _ _ -> panicOp MO_F_Eq _ -> panicOp MO_F_Ne _ -> panicOp @@ -1681,7 +1681,7 @@ genMachOp_slow opt op [x, y] = case op of MO_F_Mul _ -> genBinMach LM_MO_FMul MO_F_Quot _ -> genBinMach LM_MO_FDiv - MO_FMA _ _ -> panicOp + MO_FMA _ _ _ -> panicOp MO_And _ -> genBinMach LM_MO_And MO_Or _ -> genBinMach LM_MO_Or @@ -1822,13 +1822,11 @@ genMachOp_slow opt op [x, y] = case op of ++ "with two arguments! (" ++ show op ++ ")" genMachOp_slow _opt op [x, y, z] = do - platform <- getPlatform let - neg x = CmmMachOp (MO_F_Neg (cmmExprWidth platform x)) [x] panicOp = panic $ "LLVM.CodeGen.genMachOp_slow: non-ternary op encountered" ++ "with three arguments! (" ++ show op ++ ")" case op of - MO_FMA var _ -> + MO_FMA var lg width -> case var of -- LLVM only has the fmadd variant. FMAdd -> genFmaOp x y z @@ -1837,6 +1835,12 @@ genMachOp_slow _opt op [x, y, z] = do FMSub -> genFmaOp x y (neg z) FNMAdd -> genFmaOp (neg x) y z FNMSub -> genFmaOp (neg x) y (neg z) + where + neg x + | lg == 1 + = CmmMachOp (MO_F_Neg width) [x] + | otherwise + = CmmMachOp (MO_VF_Neg lg width) [x] _ -> panicOp -- More than three expressions, invalid! @@ -1873,7 +1877,13 @@ genFmaOp x y z = runExprData $ do let fname = case tx of LMFloat -> fsLit "llvm.fma.f32" LMDouble -> fsLit "llvm.fma.f64" - _ -> pprPanic "fma: type not LMFloat or LMDouble" (ppLlvmType tx) + LMVector 4 LMFloat -> fsLit "llvm.fma.v4f32" + LMVector 8 LMFloat -> fsLit "llvm.fma.v8f32" + LMVector 16 LMFloat -> fsLit "llvm.fma.v16f32" + LMVector 2 LMDouble -> fsLit "llvm.fma.v2f64" + LMVector 4 LMDouble -> fsLit "llvm.fma.v4f64" + LMVector 8 LMDouble -> fsLit "llvm.fma.v8f64" + _ -> pprPanic "CmmToLlvm.genFmaOp: unsupported type" (ppLlvmType tx) fptr <- liftExprData $ getInstrinct fname ty [tx, ty, tz] doExprW tx $ Call StdCall fptr [vx, vy, vz] [ReadNone, NoUnwind] ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -1503,10 +1503,10 @@ emitPrimOp cfg primop = DoubleDivOp -> opTranslate (MO_F_Quot W64) DoubleNegOp -> opTranslate (MO_F_Neg W64) - DoubleFMAdd -> fmaOp FMAdd W64 - DoubleFMSub -> fmaOp FMSub W64 - DoubleFNMAdd -> fmaOp FNMAdd W64 - DoubleFNMSub -> fmaOp FNMSub W64 + DoubleFMAdd -> fmaOp FMAdd 1 W64 + DoubleFMSub -> fmaOp FMSub 1 W64 + DoubleFNMAdd -> fmaOp FNMAdd 1 W64 + DoubleFNMSub -> fmaOp FNMSub 1 W64 -- Float ops @@ -1523,10 +1523,10 @@ emitPrimOp cfg primop = FloatDivOp -> opTranslate (MO_F_Quot W32) FloatNegOp -> opTranslate (MO_F_Neg W32) - FloatFMAdd -> fmaOp FMAdd W32 - FloatFMSub -> fmaOp FMSub W32 - FloatFNMAdd -> fmaOp FNMAdd W32 - FloatFNMSub -> fmaOp FNMSub W32 + FloatFMAdd -> fmaOp FMAdd 1 W32 + FloatFMSub -> fmaOp FMSub 1 W32 + FloatFNMAdd -> fmaOp FNMAdd 1 W32 + FloatFNMSub -> fmaOp FNMSub 1 W32 -- Vector ops @@ -1554,6 +1554,12 @@ emitPrimOp cfg primop = (VecRemOp WordVec n w) -> opTranslate (MO_VU_Rem n w) (VecNegOp WordVec _ _) -> \_ -> panic "unsupported primop" + -- Vector FMA instructions + VecFMAdd _ n w -> fmaOp FMAdd n w + VecFMSub _ n w -> fmaOp FMSub n w + VecFNMAdd _ n w -> fmaOp FNMAdd n w + VecFNMSub _ n w -> fmaOp FNMSub n w + -- Conversions IntToDoubleOp -> opTranslate (MO_SF_Round (wordWidth platform) W64) @@ -1851,10 +1857,11 @@ emitPrimOp cfg primop = allowFMA = stgToCmmAllowFMAInstr cfg - fmaOp :: FMASign -> Width -> [CmmActual] -> PrimopCmmEmit - fmaOp signs w args@[arg_x, arg_y, arg_z] - | allowFMA signs - = opTranslate (MO_FMA signs w) args + fmaOp :: FMASign -> Length -> Width -> [CmmActual] -> PrimopCmmEmit + fmaOp signs l w args@[arg_x, arg_y, arg_z] + | allowFMA signs + || l > 1 -- (always use the MachOp for vector FMA) + = opTranslate (MO_FMA signs l w) args | otherwise = case signs of @@ -1863,12 +1870,16 @@ emitPrimOp cfg primop = -- Other fused multiply-add operations are implemented in terms of fmadd -- This is sound: it does not lose any precision. - FMSub -> fmaOp FMAdd w [arg_x, arg_y, neg arg_z] - FNMAdd -> fmaOp FMAdd w [neg arg_x, arg_y, arg_z] - FNMSub -> fmaOp FMAdd w [neg arg_x, arg_y, neg arg_z] + FMSub -> fmaOp FMAdd l w [arg_x, arg_y, neg arg_z] + FNMAdd -> fmaOp FMAdd l w [neg arg_x, arg_y, arg_z] + FNMSub -> fmaOp FMAdd l w [neg arg_x, arg_y, neg arg_z] where - neg x = CmmMachOp (MO_F_Neg w) [x] - fmaOp _ _ _ = panic "fmaOp: wrong number of arguments (expected 3)" + neg x + | l == 1 + = CmmMachOp (MO_F_Neg w) [x] + | otherwise + = CmmMachOp (MO_VF_Neg l w) [x] + fmaOp _ _ _ _ = panic "fmaOp: wrong number of arguments (expected 3)" data PrimopCmmEmit -- | Out of line fake primop that's actually just a foreign call to other ===================================== compiler/GHC/StgToJS/Prim.hs ===================================== @@ -1192,6 +1192,11 @@ genPrim prof bound ty op = case op of VecReadOffAddrOp _ _ _ -> unhandledPrimop op VecWriteOffAddrOp _ _ _ -> unhandledPrimop op + VecFMAdd {} -> unhandledPrimop op + VecFMSub {} -> unhandledPrimop op + VecFNMAdd {} -> unhandledPrimop op + VecFNMSub {} -> unhandledPrimop op + VecIndexScalarByteArrayOp _ _ _ -> unhandledPrimop op VecReadScalarByteArrayOp _ _ _ -> unhandledPrimop op VecWriteScalarByteArrayOp _ _ _ -> unhandledPrimop op ===================================== libraries/base/src/GHC/Exts.hs ===================================== @@ -120,7 +120,32 @@ import GHC.Prim hiding , dataToTagSmall#, dataToTagLarge# -- whereFrom# is similarly internal. , whereFrom# - -- Don't re-export SIMD shuffle primops (to avoid changing GHC.Exts) + -- Don't re-export vector FMA instructions + , fmaddFloatX4# + , fmsubFloatX4# + , fnmaddFloatX4# + , fnmsubFloatX4# + , fmaddFloatX8# + , fmsubFloatX8# + , fnmaddFloatX8# + , fnmsubFloatX8# + , fmaddFloatX16# + , fmsubFloatX16# + , fnmaddFloatX16# + , fnmsubFloatX16# + , fmaddDoubleX2# + , fmsubDoubleX2# + , fnmaddDoubleX2# + , fnmsubDoubleX2# + , fmaddDoubleX4# + , fmsubDoubleX4# + , fnmaddDoubleX4# + , fnmsubDoubleX4# + , fmaddDoubleX8# + , fmsubDoubleX8# + , fnmaddDoubleX8# + , fnmsubDoubleX8# + -- Don't re-export SIMD shuffle primops , shuffleDoubleX2# , shuffleDoubleX4# , shuffleDoubleX8# ===================================== testsuite/tests/simd/should_run/all.T ===================================== @@ -15,3 +15,4 @@ test('simd007', [], compile_and_run, ['']) test('simd008', [], compile_and_run, ['']) test('simd009', [req_th, extra_files(['Simd009b.hs', 'Simd009c.hs'])], multimod_compile_and_run, ['simd009', '']) test('simd010', [], compile_and_run, ['']) +test('simd011', [when(have_cpu_feature('fma'), extra_hc_opts('-mfma'))], compile_and_run, ['']) ===================================== testsuite/tests/simd/should_run/simd011.hs ===================================== @@ -0,0 +1,43 @@ +{-# OPTIONS_GHC -O2 #-} +{-# OPTIONS_GHC -msse2 #-} +{-# OPTIONS_GHC -msse4 #-} +{-# LANGUAGE MagicHash #-} +{-# LANGUAGE UnboxedTuples #-} +-- tests for vector FMA instructions + +import GHC.Exts +import GHC.Prim + + +main :: IO () +main = do + + -- FloatX4# + let + !f1 = packFloatX4# (# 1.1#, 2.2#, 3.3#, 4.4# #) + !f2 = packFloatX4# (# 10.1#, 20.2#, 30.3#, 40.4# #) + !f3 = packFloatX4# (# 1000.0#, 2000.0#, 3000.0#, 4000.0# #) + + case unpackFloatX4# (fmaddFloatX4# f1 f2 f3) of + (# a, b, c, d #) -> print (F# a, F# b, F# c, F# d) + case unpackFloatX4# (fmsubFloatX4# f1 f2 f3) of + (# a, b, c, d #) -> print (F# a, F# b, F# c, F# d) + case unpackFloatX4# (fnmaddFloatX4# f1 f2 f3) of + (# a, b, c, d #) -> print (F# a, F# b, F# c, F# d) + case unpackFloatX4# (fnmsubFloatX4# f1 f2 f3) of + (# a, b, c, d #) -> print (F# a, F# b, F# c, F# d) + + -- DoubleX2# + let + !d1 = packDoubleX2# (# 1.1##, 2.2## #) + !d2 = packDoubleX2# (# 10.1##, 20.2## #) + !d3 = packDoubleX2# (# 1000.0##, 2000.0## #) + + case unpackDoubleX2# (fmaddDoubleX2# d1 d2 d3) of + (# a, b #) -> print (D# a, D# b) + case unpackDoubleX2# (fmsubDoubleX2# d1 d2 d3) of + (# a, b #) -> print (D# a, D# b) + case unpackDoubleX2# (fnmaddDoubleX2# d1 d2 d3) of + (# a, b #) -> print (D# a, D# b) + case unpackDoubleX2# (fnmsubDoubleX2# d1 d2 d3) of + (# a, b #) -> print (D# a, D# b) ===================================== testsuite/tests/simd/should_run/simd011.stdout ===================================== @@ -0,0 +1,8 @@ +(1011.11,2044.4401,3099.99,4177.7603) +(-988.89,-1955.5599,-2900.01,-3822.24) +(988.89,1955.5599,2900.01,3822.24) +(-1011.11,-2044.4401,-3099.99,-4177.7603) +(1011.11,2044.44) +(-988.89,-1955.56) +(988.89,1955.56) +(-1011.11,-2044.44) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cd3c0b64c180bb6f50f2ed63d2565e00a1888ecd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cd3c0b64c180bb6f50f2ed63d2565e00a1888ecd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 13:34:16 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 14 Jun 2024 09:34:16 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: compiler: refactor lower_CmmExpr_Ptr Message-ID: <666c46d8e038d_34061abce9b8775cd@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 38b7de9c by Simon Peyton Jones at 2024-06-14T09:34:10-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 14411df7 by Simon Peyton Jones at 2024-06-14T09:34:10-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - a1f361c0 by Simon Peyton Jones at 2024-06-14T09:34:10-04:00 Wibble - - - - - 82a88b45 by Simon Peyton Jones at 2024-06-14T09:34:10-04:00 Wibbles - - - - - 4048d490 by Simon Peyton Jones at 2024-06-14T09:34:11-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - 30 changed files: - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Types/Name/Occurrence.hs - compiler/GHC/Types/Var/Env.hs - testsuite/tests/dependent/should_compile/T15743e.stderr - testsuite/tests/dependent/should_fail/T16326_Fail4.stderr - testsuite/tests/dependent/should_fail/T16326_Fail5.stderr - testsuite/tests/indexed-types/should_fail/T13877.stderr - testsuite/tests/indexed-types/should_fail/T14369.stderr - testsuite/tests/patsyn/should_fail/T15695.stderr - testsuite/tests/polykinds/T11520.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/912181bdccd99a2902fe26902881f151123ba3b8...4048d490cf4c6e7d4d5e7cdc92f2b7d1c25477e1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/912181bdccd99a2902fe26902881f151123ba3b8...4048d490cf4c6e7d4d5e7cdc92f2b7d1c25477e1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 13:50:35 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 14 Jun 2024 09:50:35 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] SIMD: cleanup Message-ID: <666c4aab8f57d_34061afa80ac8722c@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 6669eee7 by sheaf at 2024-06-14T15:50:19+02:00 SIMD: cleanup - - - - - 18 changed files: - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - compiler/GHC/CmmToAsm/X86/Regs.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Llvm/Ppr.hs - compiler/GHC/Llvm/Syntax.hs - compiler/GHC/Platform/Reg.hs - compiler/GHC/StgToCmm/Prim.hs - compiler/GHC/Types/Unique/FM.hs Changes: ===================================== compiler/GHC/CmmToAsm/AArch64/Instr.hs ===================================== @@ -151,7 +151,9 @@ regUsageOfInstr platform instr = case instr of -- registers as well, as they show up. usage (src, dst) = RU (map (,II64) $ filter (interesting platform) src) (map (,II64) $ filter (interesting platform) dst) - -- SIMD NCG TODO: remove this hack + -- SIMD NCG TODO: the format here is used for register spilling/unspilling. + -- As the AArch64 NCG does not currently support SIMD registers, + -- we simply use II64 format for all instructions. regAddr :: AddrMode -> [Reg] regAddr (AddrRegReg r1 r2) = [r1, r2] ===================================== compiler/GHC/CmmToAsm/PPC/Instr.hs ===================================== @@ -393,7 +393,9 @@ regUsageOfInstr platform instr where usage (src, dst) = RU (map (,II64) $ filter (interesting platform) src) (map (,II64) $ filter (interesting platform) dst) - -- SIMD NCG TODO: remove this hack + -- SIMD NCG TODO: the format here is used for register spilling/unspilling. + -- As the PowerPC NCG does not currently support SIMD registers, + -- we simply use II64 format for all instructions. regAddr (AddrRegReg r1 r2) = [r1, r2] regAddr (AddrRegImm r1 _) = [r1] ===================================== compiler/GHC/CmmToAsm/PPC/Ppr.hs ===================================== @@ -196,12 +196,12 @@ pprReg :: forall doc. IsLine doc => Reg -> doc pprReg r = case r of - RegReal (RealRegSingle i) -> ppr_reg_no i - RegVirtual (VirtualRegI u) -> text "%vI_" <> pprUniqueAlways u - RegVirtual (VirtualRegHi u) -> text "%vHi_" <> pprUniqueAlways u - RegVirtual (VirtualRegF u) -> text "%vF_" <> pprUniqueAlways u - RegVirtual (VirtualRegD u) -> text "%vD_" <> pprUniqueAlways u - RegVirtual (VirtualRegVec u) -> text "%vVec_" <> pprUniqueAlways u + RegReal (RealRegSingle i) -> ppr_reg_no i + RegVirtual (VirtualRegI u) -> text "%vI_" <> pprUniqueAlways u + RegVirtual (VirtualRegHi u) -> text "%vHi_" <> pprUniqueAlways u + RegVirtual (VirtualRegF u) -> text "%vF_" <> pprUniqueAlways u + RegVirtual (VirtualRegD u) -> text "%vD_" <> pprUniqueAlways u + RegVirtual (VirtualRegV128 u) -> text "%vV128_" <> pprUniqueAlways u where ppr_reg_no :: Int -> doc ===================================== compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs ===================================== @@ -168,7 +168,6 @@ cleanForward platform blockId assoc acc (li1 : li2 : instrs) cleanForward platform blockId assoc acc $ li1 : LiveInstr (mkRegRegMoveInstr platform fmt reg1 reg2) Nothing : instrs - -- SIMD NCG TODO: is this "fmt" correct? cleanForward platform blockId assoc acc (li@(LiveInstr i1 _) : instrs) | Just (r1, r2) <- takeRegRegMoveInstr platform i1 @@ -249,7 +248,6 @@ cleanReload platform blockId assoc li@(LiveInstr (RELOAD slot reg fmt) _) return ( assoc' , Just $ LiveInstr (mkRegRegMoveInstr platform fmt reg2 reg) Nothing) - -- SIMD NCG TODO: is this fmt correct? -- Gotta keep this instr. | otherwise ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -871,14 +871,12 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc freeRegs <- getFreeRegsR let regclass = classOfVirtualReg r freeRegs_thisClass = frGetFreeRegs platform regclass freeRegs :: [RealReg] - -- SIMD NCG TODO: this is not the right thing to be doing, - -- and is indicative we should not use Format but a more - -- trimmed down datatype that only keeps track of e.g. - -- how many stack slots something uses up. vr_fmt = case r of - VirtualRegVec {} -> VecFormat 2 FmtDouble - -- SIMD NCG TODO: handle 256 and 512 by adding - -- new virtual register constructors. + VirtualRegV128 {} -> VecFormat 2 FmtDouble + -- It doesn't really matter whether we use e.g. v2f64 or v4f32 + -- or v4i32 etc here. This is perhaps a sign that 'Format' + -- is not the right type to use here, but that is a battle + -- for another day. _ -> II64 -- Can we put the variable into a register it already was? ===================================== compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs ===================================== @@ -55,9 +55,7 @@ getStackSlotFor fs@(StackMap _ reserved) _fmt regUnique getStackSlotFor (StackMap freeSlot reserved) fmt regUnique = let - nbSlots = case fmt of - VecFormat {} -> 2 -- SIMD NCG TODO: panic for unsupported vectors - _ -> 1 + nbSlots = formatInBytes fmt `div` 8 in (StackMap (freeSlot+nbSlots) (addToUFM reserved regUnique freeSlot), freeSlot) ===================================== compiler/GHC/CmmToAsm/Reg/Liveness.hs ===================================== @@ -64,7 +64,6 @@ import Data.List (mapAccumL, partition) import Data.Maybe import Data.IntSet (IntSet) import GHC.CmmToAsm.Format -import GHC.Types.Unique (Uniquable) ----------------------------------------------------------------------------- type RegSet = UniqSet Reg @@ -681,10 +680,6 @@ patchRegsLiveInstr patchF li , liveDieWrite = mapKeysUFM patchF $ liveDieWrite live }) -- See Note [Unique Determinism and code generation] --- SIMD NCG TODO: move this to Unique.FM module -mapKeysUFM :: Uniquable a => (t -> a) -> UniqFM key (t, b) -> UniqFM a (a, b) -mapKeysUFM f m = listToUFM $ map ( \ (r, fmt) -> let r' = f r in (r', (r', fmt)) ) $ nonDetEltsUFM m - -------------------------------------------------------------------------------- -- | Convert a NatCmmDecl to a LiveCmmDecl, with liveness information ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1,4 +1,5 @@ {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE NondecreasingIndentation #-} @@ -1298,10 +1299,14 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps MO_S_Shr rep -> shift_code rep SAR x y {-False-} MO_VF_Shuffle l w is - | avx - -> vector_shuffle_float l w x y is + | l * widthInBytes w == 128 + -> if + | avx + -> vector_shuffle_float l w x y is + | otherwise + -> sorry "Please enable the -mavx flag" | otherwise - -> sorry "Please enable the -mavx flag" + -> sorry "Please use -fllvm for wide shuffle instructions" MO_VF_Broadcast l W32 | avx -> vector_float_broadcast_avx l W32 x y | sse4_1 -> vector_float_broadcast_sse l W32 x y @@ -1641,15 +1646,12 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps = do (r, exp) <- getSomeReg expr let format = VecFormat l FmtDouble - addr = spRel platform 0 code dst = case lit of CmmInt 0 _ -> exp `snocOL` (MOVSD FF64 (OpReg r) (OpReg dst)) CmmInt 1 _ -> exp `snocOL` - (MOVH format (OpReg r) (OpAddr addr)) `snocOL` - (MOVSD FF64 (OpAddr addr) (OpReg dst)) - -- SIMD NCG TODO: avoid going via the stack here? + (MOVHLPS format (OpReg r) dst) _ -> panic "Error in offset while unpacking" return (Any format code) vector_float_unpack _ w c e @@ -1676,10 +1678,10 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps = pprPanic "Unpack not supported for : " (pdoc platform c $$ pdoc platform e $$ ppr w) ----------------------- vector_float_broadcast_avx :: Length - -> Width - -> CmmExpr - -> CmmExpr - -> NatM Register + -> Width + -> CmmExpr + -> CmmExpr + -> NatM Register vector_float_broadcast_avx len W32 expr1 expr2 = do fn <- getAnyReg expr1 @@ -1731,10 +1733,10 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps = pprPanic "Broadcast not supported for : " (pdoc platform c) vector_int_broadcast :: Length - -> Width - -> CmmExpr - -> CmmExpr - -> NatM Register + -> Width + -> CmmExpr + -> CmmExpr + -> NatM Register vector_int_broadcast len W64 expr1 expr2 = do fn <- getAnyReg expr1 @@ -1749,10 +1751,10 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps ----------------------- vector_int_unpack_sse :: Length - -> Width - -> CmmExpr - -> CmmExpr - -> NatM Register + -> Width + -> CmmExpr + -> CmmExpr + -> NatM Register vector_int_unpack_sse l at 2 W64 expr (CmmLit lit) = do (r, exp) <- getSomeReg expr @@ -1803,9 +1805,10 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps (3,1) -> unitOL (VSHUFPD fmt (ImmInt 0b11) (OpReg v1) v2 dst) _ -> pprPanic "vector shuffle: indices out of bounds 0 <= i <= 3" (ppr is) _ -> pprPanic "vector shuffle: wrong number of indices (expected 2)" (ppr is) - VecFormat 4 FmtFloat -> + VecFormat 4 FmtFloat + -- indices 0 <= i <= 7 + | all ( (>= 0) <&&> (<= 7) ) is -> case is of - -- indices 0 <= i <= 7 [i1, i2, i3, i4] | all ( <= 3 ) is , let imm = i1 + i2 `shiftL` 2 + i3 `shiftL` 4 + i4 `shiftL` 6 @@ -1842,6 +1845,8 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps `snocOL` (INSERTPS fmt (ImmInt $ insertImm i4 3) (OpReg $ vec i4) dst) _ -> pprPanic "vector shuffle: wrong number of indices (expected 4)" (ppr is) + | otherwise + -> pprPanic "vector shuffle: indices out of bounds 0 <= i <= 7" (ppr is) _ -> pprPanic "vector shuffle: unsupported format" (ppr fmt) @@ -1882,12 +1887,12 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps -> CmmExpr -> NatM Register -- FloatX4 - vector_float_insert len at 4 W32 vecExpr valExpr (CmmLit offset) + vector_float_insert len at 4 W32 vecExpr valExpr (CmmLit (CmmInt offset _)) = do fn <- getAnyReg vecExpr (r, exp) <- getSomeReg valExpr let fmt = VecFormat len FmtFloat - imm = litToImm offset + imm = litToImm (CmmInt (offset `shiftL` 4) W32) code dst = exp `appOL` (fn dst) `snocOL` (INSERTPS fmt imm (OpReg r) dst) @@ -1900,15 +1905,14 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps let fmt = VecFormat len FmtDouble code dst = case offset of - -- TODO: why not just index by element rather than by byte? - CmmInt 0 _ -> valExp `appOL` - vecExp `snocOL` - (MOVSD FF64 (OpReg valReg) (OpReg dst)) `snocOL` - (SHUFPD fmt (ImmInt 0b00) (OpReg vecReg) dst) - CmmInt 16 _ -> valExp `appOL` - vecExp `snocOL` - (MOVSD FF64 (OpReg vecReg) (OpReg dst)) `snocOL` - (SHUFPD fmt (ImmInt 0b00) (OpReg valReg) dst) + CmmInt 0 _ -> valExp `appOL` + vecExp `snocOL` + (MOVSD FF64 (OpReg valReg) (OpReg dst)) `snocOL` + (SHUFPD fmt (ImmInt 0b00) (OpReg vecReg) dst) + CmmInt 1 _ -> valExp `appOL` + vecExp `snocOL` + (MOVSD FF64 (OpReg vecReg) (OpReg dst)) `snocOL` + (SHUFPD fmt (ImmInt 0b00) (OpReg valReg) dst) _ -> pprPanic "MO_VF_Insert DoubleX2: unsupported offset" (ppr offset) in return $ Any fmt code -- For DoubleX4: use VSHUFPD. @@ -1941,16 +1945,16 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps pprTraceM "tmp:" (ppr tmp) let code dst = case offset of - CmmInt 0 _ -> valExp `appOL` - vecExp `snocOL` - (MOVHLPS fmt (OpReg vecReg) tmp) `snocOL` - (MOV II64 (OpReg valReg) (OpReg dst)) `snocOL` - (PUNPCKLQDQ fmt (OpReg tmp) dst) - CmmInt 16 _ -> valExp `appOL` - vecExp `snocOL` - (MOV fmt (OpReg vecReg) (OpReg dst)) `snocOL` - (MOV II64 (OpReg valReg) (OpReg tmp)) `snocOL` - (PUNPCKLQDQ fmt (OpReg tmp) dst) + CmmInt 0 _ -> valExp `appOL` + vecExp `snocOL` + (MOVHLPS fmt (OpReg vecReg) tmp) `snocOL` + (MOV II64 (OpReg valReg) (OpReg dst)) `snocOL` + (PUNPCKLQDQ fmt (OpReg tmp) dst) + CmmInt 1 _ -> valExp `appOL` + vecExp `snocOL` + (MOV fmt (OpReg vecReg) (OpReg dst)) `snocOL` + (MOV II64 (OpReg valReg) (OpReg tmp)) `snocOL` + (PUNPCKLQDQ fmt (OpReg tmp) dst) _ -> pprPanic "MO_V_Insert Int64X2: unsupported offset" (ppr offset) in return $ Any fmt code vector_int_insert_sse len width _ _ offset ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -391,8 +391,6 @@ data Instr | VSHUFPS Format Imm Operand Reg Reg | SHUFPD Format Imm Operand Reg | VSHUFPD Format Imm Operand Reg Reg - -- SIMD NCG TODO: don't store the Format (or only what we need) - -- in order to emit these instructions. | MOVHLPS Format Operand Reg | PUNPCKLQDQ Format Operand Reg @@ -874,9 +872,11 @@ mkSpillInstr config reg fmt delta slot = let off = spillSlotToOffset platform slot - delta in case fmt of VecFormat {} - -- SIMD NCG TODO: panic for unsupported VecFormats (& same in mkLoadInstr) + | formatInBytes fmt > 16 + -> [VMOVU fmt (OpReg reg) (OpAddr (spRel platform off))] + | otherwise -> [MOVU fmt (OpReg reg) (OpAddr (spRel platform off))] - -- NB: not using MOVA because we have no guarantees about the stack + -- NB: not using MOVA, because we have no guarantees about the stack -- being sufficiently aligned, including even numbered stack slots. _ -> [MOV fmt (OpReg reg) (OpAddr (spRel platform off))] where platform = ncgPlatform config @@ -894,9 +894,11 @@ mkLoadInstr config reg fmt delta slot = let off = spillSlotToOffset platform slot - delta in case fmt of VecFormat {} - -- SIMD NCG TODO: panic for unsupported VecFormats (& same in mkLoadInstr) + | formatInBytes fmt > 16 + -> [VMOVU fmt (OpAddr (spRel platform off)) (OpReg reg)] + | otherwise -> [MOVU fmt (OpAddr (spRel platform off)) (OpReg reg)] - -- NB: not using MOVA because we have no guarantees about the stack + -- NB: not using MOVA, because we have no guarantees about the stack -- being sufficiently aligned, including even numbered stack slots. _ -> [MOV fmt (OpAddr (spRel platform off)) (OpReg reg)] @@ -985,8 +987,9 @@ takeRegRegMoveInstr platform (MOV fmt (OpReg r1) (OpReg r2)) -- MOV zeroes the upper part of vector registers, -- so it is not a real "move" in that case. | not (isVecFormat fmt) - -- Don't eliminate a move between e.g. RAX and XMM, - -- even though we might be using XMM to store a scalar integer value. + -- Don't eliminate a move between e.g. RAX and XMM: + -- even though we might be using XMM to store a scalar integer value, + -- some instructions only support XMM registers. , targetClassOfReg platform r1 == targetClassOfReg platform r2 = Just (r1,r2) takeRegRegMoveInstr _ (MOVSD fmt (OpReg r1) (OpReg r2)) ===================================== compiler/GHC/CmmToAsm/X86/Ppr.hs ===================================== @@ -295,7 +295,7 @@ pprReg platform f r RegVirtual (VirtualRegHi u) -> text "%vHi_" <> pprUniqueAlways u RegVirtual (VirtualRegF u) -> text "%vF_" <> pprUniqueAlways u RegVirtual (VirtualRegD u) -> text "%vD_" <> pprUniqueAlways u - RegVirtual (VirtualRegVec u) -> text "%vVec_" <> pprUniqueAlways u + RegVirtual (VirtualRegV128 u) -> text "%vVec_" <> pprUniqueAlways u where ppr32_reg_no :: Format -> Int -> doc @@ -1051,13 +1051,15 @@ pprInstr platform i = case i of char '\t' <> name <> pprBroadcastFormat format <> space pprBroadcastFormat :: Format -> Line doc - pprBroadcastFormat x - = case x of - VecFormat _ FmtFloat -> text "ss" - VecFormat _ FmtDouble -> text "sd" - -- SIMD NCG TODO: Add Ints and remove panic - VecFormat {} -> panic "Incorrect width" - _ -> panic "Scalar Format invading vector operation" + pprBroadcastFormat (VecFormat _ f) + = case f of + FmtFloat -> text "ss" + FmtDouble -> text "sd" + FmtInt8 -> text "b" + FmtInt16 -> text "w" + FmtInt32 -> text "d" + FmtInt64 -> text "q" + pprBroadcastFormat _ = panic "Scalar Format invading vector operation" pprFormatImmOp :: Line doc -> Format -> Imm -> Operand -> doc pprFormatImmOp name format imm op1 ===================================== compiler/GHC/CmmToAsm/X86/RegInfo.hs ===================================== @@ -31,7 +31,7 @@ mkVirtualReg u format FF64 -> VirtualRegD u --TODO: -- Add VirtualRegAVX and inspect VecFormat and allocate - VecFormat {} -> VirtualRegVec u + VecFormat {} -> VirtualRegV128 u _other -> VirtualRegI u regDotColor :: Platform -> RealReg -> SDoc ===================================== compiler/GHC/CmmToAsm/X86/Regs.hs ===================================== @@ -81,7 +81,7 @@ virtualRegSqueeze cls vr -> case vr of VirtualRegD{} -> 1 VirtualRegF{} -> 0 - VirtualRegVec{} -> 1 + VirtualRegV128{} -> 1 _other -> 0 ===================================== compiler/GHC/CmmToLlvm/CodeGen.hs ===================================== @@ -1850,16 +1850,13 @@ genShuffleOp :: [Int] -> CmmExpr -> CmmExpr -> LlvmM ExprData genShuffleOp is x y = runExprData $ do vx <- exprToVarW x vy <- exprToVarW y - mask <- exprToVarW $ CmmLit $ CmmVec $ map ((`CmmInt` W32) . fromIntegral) is let tx = getVarType vx ty = getVarType vy Panic.massertPpr (tx == ty) (vcat [ text "shuffle: mismatched arg types" , ppLlvmType tx, ppLlvmType ty ]) - let fname = fsLit "shufflevector" - fptr <- liftExprData $ getInstrinct fname ty [tx, ty] - doExprW tx $ Call StdCall fptr [vx, vy, mask] [ReadNone, NoUnwind] + doExprW tx $ Shuffle vx vy is -- | Generate code for a fused multiply-add operation. genFmaOp :: CmmExpr -> CmmExpr -> CmmExpr -> LlvmM ExprData ===================================== compiler/GHC/Llvm/Ppr.hs ===================================== @@ -281,6 +281,7 @@ ppLlvmExpression opts expr Extract vec idx -> ppExtract opts vec idx ExtractV struct idx -> ppExtractV opts struct idx Insert vec elt idx -> ppInsert opts vec elt idx + Shuffle v1 v2 idxs -> ppShuffle opts v1 v2 idxs GetElemPtr inb ptr indexes -> ppGetElementPtr opts inb ptr indexes Load ptr align -> ppLoad opts ptr align ALoad ord st ptr -> ppALoad opts ord st ptr @@ -577,6 +578,15 @@ ppInsert opts vec elt idx = {-# SPECIALIZE ppInsert :: LlvmCgConfig -> LlvmVar -> LlvmVar -> LlvmVar -> SDoc #-} {-# SPECIALIZE ppInsert :: LlvmCgConfig -> LlvmVar -> LlvmVar -> LlvmVar -> HLine #-} -- see Note [SPECIALIZE to HDoc] in GHC.Utils.Outputable +ppShuffle :: IsLine doc => LlvmCgConfig -> LlvmVar -> LlvmVar -> [Int] -> doc +ppShuffle opts v1 v2 idxs = + text "shufflevector" + <+> ppLlvmType (getVarType v1) <+> ppName opts v1 <> comma + <+> ppLlvmType (getVarType v2) <+> ppName opts v2 <> comma + <+> ppLlvmType (LMVector (length idxs) (LMInt 32)) <+> ppLit opts (LMVectorLit $ map ((`LMIntLit` (LMInt 32)) . fromIntegral) idxs) +{-# SPECIALIZE ppShuffle :: LlvmCgConfig -> LlvmVar -> LlvmVar -> [Int] -> SDoc #-} +{-# SPECIALIZE ppShuffle :: LlvmCgConfig -> LlvmVar -> LlvmVar -> [Int] -> HLine #-} -- see Note [SPECIALIZE to HDoc] in GHC.Utils.Outputable + ppMetaAnnotExpr :: IsLine doc => LlvmCgConfig -> [MetaAnnot] -> LlvmExpression -> doc ppMetaAnnotExpr opts meta expr = ppLlvmExpression opts expr <> ppMetaAnnots opts meta ===================================== compiler/GHC/Llvm/Syntax.hs ===================================== @@ -237,6 +237,10 @@ data LlvmExpression -} | Insert LlvmVar LlvmVar LlvmVar + {- | Shuffle two vectors into a destination vector using given indices + -} + | Shuffle LlvmVar LlvmVar [Int] + {- | Allocate amount * sizeof(tp) bytes on the heap * tp: LlvmType to reserve room for ===================================== compiler/GHC/Platform/Reg.hs ===================================== @@ -1,3 +1,5 @@ +{-# LANGUAGE MagicHash #-} + -- | An architecture independent description of a register. -- This needs to stay architecture independent because it is used -- by NCGMonad and the register allocators, which are shared @@ -27,6 +29,7 @@ module GHC.Platform.Reg ( where import GHC.Prelude +import GHC.Exts ( Int(I#), dataToTag# ) import GHC.Utils.Outputable import GHC.Utils.Panic @@ -53,66 +56,44 @@ type RegNo -- Virtual regs can be of either class, so that info is attached. -- data VirtualReg - = VirtualRegI {-# UNPACK #-} !Unique - | VirtualRegHi {-# UNPACK #-} !Unique -- High part of 2-word register - | VirtualRegF {-# UNPACK #-} !Unique - | VirtualRegD {-# UNPACK #-} !Unique - | VirtualRegVec {-# UNPACK #-} !Unique - deriving (Eq, Show) - --- This is laborious, but necessary. We can't derive Ord because --- Unique doesn't have an Ord instance. Note nonDetCmpUnique in the --- implementation. See Note [No Ord for Unique] + -- | Integer virtual register + = VirtualRegI { virtualRegUnique :: {-# UNPACK #-} !Unique } + -- | High part of 2-word virtual register + | VirtualRegHi { virtualRegUnique :: {-# UNPACK #-} !Unique } + -- | Float virtual register + | VirtualRegF { virtualRegUnique :: {-# UNPACK #-} !Unique } + -- | Double virtual register + | VirtualRegD { virtualRegUnique :: {-# UNPACK #-} !Unique } + -- | 128-bit wide vector virtual register + | VirtualRegV128 { virtualRegUnique :: {-# UNPACK #-} !Unique } + deriving (Eq, Show) + +-- We can't derive Ord, because Unique doesn't have an Ord instance. +-- Note nonDetCmpUnique in the implementation. See Note [No Ord for Unique]. -- This is non-deterministic but we do not currently support deterministic -- code-generation. See Note [Unique Determinism and code generation] instance Ord VirtualReg where - compare (VirtualRegI a) (VirtualRegI b) = nonDetCmpUnique a b - compare (VirtualRegHi a) (VirtualRegHi b) = nonDetCmpUnique a b - compare (VirtualRegF a) (VirtualRegF b) = nonDetCmpUnique a b - compare (VirtualRegD a) (VirtualRegD b) = nonDetCmpUnique a b - compare (VirtualRegVec a) (VirtualRegVec b) = nonDetCmpUnique a b - - compare VirtualRegI{} _ = LT - compare _ VirtualRegI{} = GT - compare VirtualRegHi{} _ = LT - compare _ VirtualRegHi{} = GT - compare VirtualRegF{} _ = LT - compare _ VirtualRegF{} = GT - compare VirtualRegVec{} _ = LT - compare _ VirtualRegVec{} = GT - + compare vr1 vr2 = + case compare (I# (dataToTag# vr1)) (I# (dataToTag# vr2)) of + LT -> LT + GT -> GT + EQ -> nonDetCmpUnique (virtualRegUnique vr1) (virtualRegUnique vr2) instance Uniquable VirtualReg where - getUnique reg - = case reg of - VirtualRegI u -> u - VirtualRegHi u -> u - VirtualRegF u -> u - VirtualRegD u -> u - VirtualRegVec u -> u + getUnique = virtualRegUnique instance Outputable VirtualReg where ppr reg = case reg of - VirtualRegI u -> text "%vI_" <> pprUniqueAlways u - VirtualRegHi u -> text "%vHi_" <> pprUniqueAlways u - -- this code is kinda wrong on x86 - -- because float and double occupy the same register set - -- namely SSE2 register xmm0 .. xmm15 - VirtualRegF u -> text "%vFloat_" <> pprUniqueAlways u - VirtualRegD u -> text "%vDouble_" <> pprUniqueAlways u - VirtualRegVec u -> text "%vVec_" <> pprUniqueAlways u - + VirtualRegI u -> text "%vI_" <> pprUniqueAlways u + VirtualRegHi u -> text "%vHi_" <> pprUniqueAlways u + VirtualRegF u -> text "%vFloat_" <> pprUniqueAlways u + VirtualRegD u -> text "%vDouble_" <> pprUniqueAlways u + VirtualRegV128 u -> text "%vV128_" <> pprUniqueAlways u renameVirtualReg :: Unique -> VirtualReg -> VirtualReg -renameVirtualReg u r - = case r of - VirtualRegI _ -> VirtualRegI u - VirtualRegHi _ -> VirtualRegHi u - VirtualRegF _ -> VirtualRegF u - VirtualRegD _ -> VirtualRegD u - VirtualRegVec _ -> VirtualRegVec u +renameVirtualReg u r = r { virtualRegUnique = u } classOfVirtualReg :: VirtualReg -> RegClass classOfVirtualReg vr @@ -121,7 +102,7 @@ classOfVirtualReg vr VirtualRegHi{} -> RcInteger VirtualRegF{} -> RcFloatOrVector VirtualRegD{} -> RcFloatOrVector - VirtualRegVec{} -> RcFloatOrVector + VirtualRegV128{} -> RcFloatOrVector -- Determine the upper-half vreg for a 64-bit quantity on a 32-bit platform ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -2651,7 +2651,7 @@ doVecPackOp ty z es res = do vecPack src [] _ = emitAssign (CmmLocal res) (CmmReg (CmmLocal src)) - -- SIMD NCG TODO (optional): it should be possible to emit better code + -- SIMD NCG TODO: it should be possible to emit better code -- for "pack" than doing a bunch of vector insertions in a row. vecPack src (e : es) i = do dst <- newTemp ty @@ -2663,8 +2663,7 @@ doVecPackOp ty z es res = do vecPack dst es (i + 1) where -- vector indices are always 32-bits - -- TODO: consider indexing by element rather than by byte - iLit = CmmLit (CmmInt ((toInteger i) * 16) W32) + iLit = CmmLit (CmmInt (toInteger i) W32) len :: Length len = vecLength ty ===================================== compiler/GHC/Types/Unique/FM.hs ===================================== @@ -71,6 +71,7 @@ module GHC.Types.Unique.FM ( nonDetStrictFoldUFM_Directly, anyUFM, allUFM, seqEltsUFM, mapUFM, mapUFM_Directly, strictMapUFM, + mapKeysUFM, mapMaybeUFM, mapMaybeWithKeyUFM, elemUFM, elemUFM_Directly, filterUFM, filterUFM_Directly, partitionUFM, @@ -397,6 +398,10 @@ mapMaybeWithKeyUFM f (UFM m) = UFM (M.mapMaybeWithKey (f . mkUniqueGrimily) m) mapUFM_Directly :: (Unique -> elt1 -> elt2) -> UniqFM key elt1 -> UniqFM key elt2 mapUFM_Directly f (UFM m) = UFM (M.mapWithKey (f . mkUniqueGrimily) m) +-- | Map over the keys in a 'UniqFM'. +mapKeysUFM :: Uniquable key' => (key -> key') -> UniqFM key (key, b) -> UniqFM key' (key', b) +mapKeysUFM f m = listToUFM $ map ( \ (r, fmt) -> let r' = f r in (r', (r', fmt)) ) $ nonDetEltsUFM m + strictMapUFM :: (a -> b) -> UniqFM k a -> UniqFM k b strictMapUFM f (UFM a) = UFM $ MS.map f a View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6669eee7d5d242044fc0b17ff72c42755c4f4778 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6669eee7d5d242044fc0b17ff72c42755c4f4778 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 15:10:26 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Fri, 14 Jun 2024 11:10:26 -0400 Subject: [Git][ghc/ghc][wip/T14030] Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) Message-ID: <666c5d62caece_16c74b18b03c1394@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: 42fdf7f0 by Sebastian Graf at 2024-06-14T17:09:36+02:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. - - - - - 8 changed files: - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - testsuite/tests/ghci/scripts/T21110.stderr - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/th/TH_Lift.hs - + testsuite/tests/th/TH_Lift.stderr - testsuite/tests/th/all.T Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs ===================================== @@ -42,7 +42,7 @@ module GHC.Internal.TH.Lift where import GHC.Internal.TH.Syntax -import GHC.Internal.TH.Lib () -- See wrinkle (W4) of Note [Tracking dependencies on primitives] +import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives] import GHC.Internal.Lexeme ( startsVarSym, startsVarId ) import GHC.Internal.Data.Either @@ -54,8 +54,9 @@ import GHC.Internal.Integer import GHC.Internal.Real import GHC.Internal.Word import GHC.Internal.Int -import GHC.Internal.Data.Data +import GHC.Internal.Data.Data hiding (Fixity) import GHC.Internal.Natural +import GHC.Internal.ForeignPtr -- | A 'Lift' instance can have any of its values turned into a Template -- Haskell expression. This is needed when a value used within a Template @@ -305,6 +306,141 @@ rightName = 'Right nonemptyName :: Name nonemptyName = '(:|) +----------------------------------------------------- +-- +-- Lifting the TH AST +-- +----------------------------------------------------- + +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Loc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DocLoc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ModName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift GHC.Internal.TH.Syntax.Module +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameSpace +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NamespaceSpecifier +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PkgName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameFlavour +-- | @since template-haskell-2.22.1.0 +deriving instance Lift OccName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Name +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameIs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Specificity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift BndrVis +-- | @since template-haskell-2.22.1.0 +deriving instance Lift a => Lift (TyVarBndr a) +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TyLit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Type +-- | @since template-haskell-2.22.1.0 +instance Lift Bytes where + liftTyped x = unsafeCodeCoerce (lift x) + lift bytes = -- See Note [Why FinalPtr] + [| Bytes + { bytesPtr = ForeignPtr $(Lib.litE (BytesPrimL bytes)) FinalPtr + , bytesOffset = 0 + , bytesSize = $(lift (bytesSize bytes)) + } + |] +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Lit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pat +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Clause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivClause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivStrategy +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Overlap +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FunDep +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Safety +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Callconv +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Foreign +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ForeignSrcLang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FixityDirection +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Fixity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Inline +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleMatch +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Phases +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleBndr +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnTarget +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pragma +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceUnpackedness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DecidedStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Bang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Con +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TySynEqn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FamilyResultSig +-- | @since template-haskell-2.22.1.0 +deriving instance Lift InjectivityAnn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TypeFamilyHead +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Role +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynArgs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynDir +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Dec +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Range +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Exp +-- | @since template-haskell-2.22.1.0 +instance Lift (TExp a) where + lift (TExp e) = [| TExp $(lift e) |] + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Match +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Guard +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Stmt +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Body +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Info +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnLookup +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Extension + ----------------------------------------------------- -- -- Generic Lift implementations ===================================== libraries/template-haskell/changelog.md ===================================== @@ -1,5 +1,9 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) +## 2.22.1.0 + + * `Lift` instances were added for the `template-haskell` AST. + ## 2.22.0.0 * The kind of `Code` was changed from `forall r. (Type -> Type) -> TYPE r -> Type` ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -3,7 +3,7 @@ -- template-haskell.cabal. name: template-haskell -version: 2.22.0.0 +version: 2.22.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE ===================================== testsuite/tests/ghci/scripts/T21110.stderr ===================================== @@ -1,5 +1,5 @@ - : warning: [GHC-42258] [-Wunused-packages] The following packages were specified via -package or -package-id flags, but were not needed for compilation: - - template-haskell-2.22.0.0 (exposed by flag -package template-haskell) + - template-haskell-2.22.1.0 (exposed by flag -package template-haskell) + ===================================== testsuite/tests/interface-stability/template-haskell-exports.stdout ===================================== @@ -2420,11 +2420,37 @@ instance GHC.Internal.Show.Show GHC.Internal.LanguageExtensions.Extension -- Def instance GHC.Internal.Show.Show GHC.Internal.TH.Ppr.ForallVisFlag -- Defined in ‘GHC.Internal.TH.Ppr’ instance [safe] GHC.Internal.Show.Show GHC.Internal.TH.PprLib.Doc -- Defined in ‘GHC.Internal.TH.PprLib’ instance GHC.Internal.Show.Show GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.ForeignSrcLang’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnLookup -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnTarget -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.BndrVis -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Body -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Bool -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bytes -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Callconv -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Char -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Clause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Con -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Dec -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DecidedStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivClause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivStrategy -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DocLoc -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Double -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (GHC.Internal.Data.Either.Either a b) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Exp -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.LanguageExtensions.Extension -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FamilyResultSig -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Fixity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FixityDirection -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Float -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Foreign -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FunDep -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Guard -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Info -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.InjectivityAnn -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Inline -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Int -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int16 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int32 -- Defined in ‘GHC.Internal.TH.Lift’ @@ -2432,16 +2458,49 @@ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int64 -- Defined in ‘GHC.I instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int8 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Integer.Integer -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift [a] -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Lit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Loc -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Match -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Maybe.Maybe a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.ModName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Module -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Name -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameFlavour -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameIs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameSpace -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NamespaceSpecifier -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Natural.Natural -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.OccName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Overlap -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pat -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynArgs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynDir -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Phases -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PkgName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pragma -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Range -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.Real.Integral a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Real.Ratio a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Role -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleBndr -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleMatch -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Safety -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceUnpackedness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Specificity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Stmt -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TExp a) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (a, b) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c) => GHC.Internal.TH.Lift.Lift (a, b, c) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d) => GHC.Internal.TH.Lift.Lift (a, b, c, d) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f g. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f, GHC.Internal.TH.Lift.Lift g) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f, g) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TyLit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TySynEqn -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TyVarBndr a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Type -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TypeFamilyHead -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift () -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Word -- Defined in ‘GHC.Internal.TH.Lift’ ===================================== testsuite/tests/th/TH_Lift.hs ===================================== @@ -1,6 +1,7 @@ -- test Lifting instances {-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE MagicHash #-} module TH_Lift where @@ -10,6 +11,8 @@ import Data.Word import Data.Int import Numeric.Natural import Data.List.NonEmpty +import qualified Data.ByteString as B +import qualified Data.ByteString.Internal as B a :: Integer a = $( (\x -> [| x |]) (5 :: Integer) ) @@ -80,3 +83,17 @@ o = $( (\x -> [| x |]) (True, 'x', 4 :: Int) ) p :: NonEmpty Char p = $( (\x -> [| x |]) ('a' :| "bcde") ) +exp :: Exp +exp = $( [| 3 + 4 |] >>= lift ) + +texp :: TExp Int +texp = $$( examineCode [|| 3 + 4 ||] `bindCode` liftTyped ) + +bytes :: Bytes +bytes = $(do + let (fp, offset, size) = B.toForeignPtr (B.pack [72, 101, 108, 108, 111]) -- "hello"# + let bytes = Bytes { bytesPtr = fp + , bytesOffset = fromIntegral offset + , bytesSize = fromIntegral size + } + lift bytes) ===================================== testsuite/tests/th/TH_Lift.stderr ===================================== @@ -0,0 +1,197 @@ +TH_Lift.hs:18:6-39: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Integer) + ======> + 5 +TH_Lift.hs:21:6-35: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int) + ======> + 5 +TH_Lift.hs:24:7-37: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int8) + ======> + 5 +TH_Lift.hs:27:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int16) + ======> + 5 +TH_Lift.hs:30:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int32) + ======> + 5 +TH_Lift.hs:33:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int64) + ======> + 5 +TH_Lift.hs:36:6-36: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word) + ======> + 5 +TH_Lift.hs:39:6-37: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word8) + ======> + 5 +TH_Lift.hs:42:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word16) + ======> + 5 +TH_Lift.hs:45:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word32) + ======> + 5 +TH_Lift.hs:48:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word64) + ======> + 5 +TH_Lift.hs:51:7-40: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Natural) + ======> + 5 +TH_Lift.hs:54:6-44: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 % 3 :: Rational) + ======> + 1.6666666666666667 +TH_Lift.hs:57:7-39: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (pi :: Float) + ======> + 3.1415927410125732 +TH_Lift.hs:60:7-40: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (pi :: Double) + ======> + 3.141592653589793 +TH_Lift.hs:63:6-28: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + 'x' + ======> + 'x' +TH_Lift.hs:66:6-29: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + True + ======> + True +TH_Lift.hs:69:6-35: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (Just 'x') + ======> + Just 'x' +TH_Lift.hs:72:6-58: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (Right False :: Either Char Bool) + ======> + Right False +TH_Lift.hs:75:6-29: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + "hi!" + ======> + "hi!" +TH_Lift.hs:78:6-27: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + () + ======> + () +TH_Lift.hs:81:6-46: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (True, 'x', 4 :: Int) + ======> + (,,) True 'x' 4 +TH_Lift.hs:84:6-41: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + ('a' :| "bcde") + ======> + (:|) 'a' "bcde" +TH_Lift.hs:87:8-31: Splicing expression + [| 3 + 4 |] >>= lift + ======> + InfixE + (Just (LitE (IntegerL 3))) + (VarE + (Name + (OccName "+") + (NameG + VarName (PkgName "ghc-internal") (ModName "GHC.Internal.Num")))) + (Just (LitE (IntegerL 4))) +TH_Lift.hs:(93,10)-(99,13): Splicing expression + do let (fp, offset, size) + = B.toForeignPtr (B.pack [72, 101, 108, 108, 111]) + let bytes + = Bytes + {bytesPtr = fp, bytesOffset = fromIntegral offset, + bytesSize = fromIntegral size} + lift bytes + ======> + Bytes + {bytesPtr = GHC.Internal.ForeignPtr.ForeignPtr + "Hello"# GHC.Internal.ForeignPtr.FinalPtr, + bytesOffset = 0, bytesSize = 5} +TH_Lift.hs:90:10-59: Splicing expression + examineCode [|| 3 + 4 ||] `bindCode` liftTyped + ======> + TExp + (InfixE + (Just (LitE (IntegerL 3))) + (VarE + (Name + (OccName "+") + (NameG + VarName (PkgName "ghc-internal") (ModName "GHC.Internal.Num")))) + (Just (LitE (IntegerL 4)))) ===================================== testsuite/tests/th/all.T ===================================== @@ -318,7 +318,7 @@ test('T1476', normal, compile, ['-v0']) test('T1476b', normal, compile, ['-v0']) test('T8031', normal, compile, ['-v0']) test('T8624', only_ways(['normal']), makefile_test, ['T8624']) -test('TH_Lift', normal, compile, ['-v0']) +test('TH_Lift', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques']) test('T10047', only_ways(['ghci']), ghci_script, ['T10047.script']) test('T10019', only_ways(['ghci']), ghci_script, ['T10019.script']) test('T10267', [], multimod_compile_fail, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/42fdf7f08cc44c90d75f29f8c5338829f15aed28 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/42fdf7f08cc44c90d75f29f8c5338829f15aed28 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 15:21:34 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 14 Jun 2024 11:21:34 -0400 Subject: [Git][ghc/ghc][wip/romes/bswap] ncg(aarch64): Implement MO_BSwap using REV Message-ID: <666c5ffdd02d8_16c74b4508f89562@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/bswap at Glasgow Haskell Compiler / GHC Commits: 9b65c166 by Rodrigo Mesquita at 2024-06-14T16:20:52+01:00 ncg(aarch64): Implement MO_BSwap using REV Implements MO_BSwap by producing assembly to do the byte swapping instead of producing a foreign call a C function. In `tar`, the hot loop for `deserialise` got almost 4x faster by avoiding the foreign call which caused spilling live variables to the stack -- this means the loop did 4x more memory read/writing than necessary in that particular case! - - - - - 4 changed files: - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs Changes: ===================================== compiler/GHC/Cmm/Parser.y ===================================== @@ -1147,10 +1147,12 @@ callishMachOps platform = listToUFM $ ( "prefetch1", (MO_Prefetch_Data 1,)), ( "prefetch2", (MO_Prefetch_Data 2,)), ( "prefetch3", (MO_Prefetch_Data 3,)) + ] ++ concat [ allWidths "popcnt" MO_PopCnt , allWidths "pdep" MO_Pdep , allWidths "pext" MO_Pext + , allWidths "bswap" MO_BSwap , allWidths "cmpxchg" MO_Cmpxchg , allWidths "xchg" MO_Xchg , allWidths "load_relaxed" (\w -> MO_AtomicRead w MemOrderAcquire) ===================================== compiler/GHC/CmmToAsm/AArch64/CodeGen.hs ===================================== @@ -1546,7 +1546,7 @@ genCondBranch _ true false expr = do -- range within 64bit. genCCall - :: ForeignTarget -- function to call + :: ForeignTarget -- function to call (or primop) -> [CmmFormal] -- where to put the result -> [CmmActual] -- arguments (of mixed type) -> BlockId -- The block we are in @@ -2014,7 +2014,15 @@ genCCall target dest_regs arg_regs bid = do MO_PopCnt w -> mkCCall (popCntLabel w) MO_Pdep w -> mkCCall (pdepLabel w) MO_Pext w -> mkCCall (pextLabel w) - MO_BSwap w -> mkCCall (bSwapLabel w) + MO_BSwap w + | [src_reg] <- arg_regs + , [dst_reg] <- dest_regs -> do + (src, _fmt_p, code_p) <- getSomeReg src_reg + platform <- getPlatform + let dst = getRegisterReg platform (CmmLocal dst_reg) + code = code_p `snocOL` REV (OpReg w dst) (OpReg w src) + return (code, Nothing) + | otherwise -> panic "mal-formed ByteSwap" -- -- Atomic read-modify-write. MO_AtomicRead w ord ===================================== compiler/GHC/CmmToAsm/AArch64/Instr.hs ===================================== @@ -102,6 +102,7 @@ regUsageOfInstr platform instr = case instr of UXTH dst src -> usage (regOp src, regOp dst) CLZ dst src -> usage (regOp src, regOp dst) RBIT dst src -> usage (regOp src, regOp dst) + REV dst src -> usage (regOp src, regOp dst) -- 3. Logical and Move Instructions ------------------------------------------ AND dst src1 src2 -> usage (regOp src1 ++ regOp src2, regOp dst) ASR dst src1 src2 -> usage (regOp src1 ++ regOp src2, regOp dst) @@ -238,7 +239,8 @@ patchRegsOfInstr instr env = case instr of SXTH o1 o2 -> SXTH (patchOp o1) (patchOp o2) UXTH o1 o2 -> UXTH (patchOp o1) (patchOp o2) CLZ o1 o2 -> CLZ (patchOp o1) (patchOp o2) - RBIT o1 o2 -> RBIT (patchOp o1) (patchOp o2) + RBIT o1 o2 -> RBIT (patchOp o1) (patchOp o2) + REV o1 o2 -> REV (patchOp o1) (patchOp o2) -- 3. Logical and Move Instructions ---------------------------------------- AND o1 o2 o3 -> AND (patchOp o1) (patchOp o2) (patchOp o3) @@ -599,6 +601,7 @@ data Instr | UBFX Operand Operand Operand Operand -- rd = rn[i,j] | CLZ Operand Operand -- rd = countLeadingZeros(rn) | RBIT Operand Operand -- rd = reverseBits(rn) + | REV Operand Operand -- rd = bswap(rn) -- 3. Logical and Move Instructions ---------------------------------------- | AND Operand Operand Operand -- rd = rn & op2 @@ -686,6 +689,7 @@ instrCon i = UBFX{} -> "UBFX" CLZ{} -> "CLZ" RBIT{} -> "RBIT" + REV{} -> "REV" AND{} -> "AND" ASR{} -> "ASR" EOR{} -> "EOR" ===================================== compiler/GHC/CmmToAsm/AArch64/Ppr.hs ===================================== @@ -397,7 +397,12 @@ pprInstr platform instr = case instr of SBFM o1 o2 o3 o4 -> op4 (text "\tsbfm") o1 o2 o3 o4 UBFM o1 o2 o3 o4 -> op4 (text "\tubfm") o1 o2 o3 o4 CLZ o1 o2 -> op2 (text "\tclz") o1 o2 - RBIT o1 o2 -> op2 (text "\trbit") o1 o2 + RBIT o1 o2 -> op2 (text "\trbit") o1 o2 + REV (OpReg W8 (RegReal (RealRegSingle i))) _ | i < 32 -> + {- swapping a single byte is a no-op -} empty + REV o1@(OpReg W16 (RegReal (RealRegSingle i))) o2 | i < 32 -> + op2 (text "\trev16") o1 o2 + REV o1 o2 -> op2 (text "\trev") o1 o2 -- signed and unsigned bitfield extract SBFX o1 o2 o3 o4 -> op4 (text "\tsbfx") o1 o2 o3 o4 UBFX o1 o2 o3 o4 -> op4 (text "\tubfx") o1 o2 o3 o4 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9b65c16696995c9c930c18467a9ef0f675a85282 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9b65c16696995c9c930c18467a9ef0f675a85282 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 15:32:00 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 14 Jun 2024 11:32:00 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] WIP: improve broadcast, especially on LLVM Message-ID: <666c62706dd2f_16c74b65859c116fd@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: df28c0e5 by sheaf at 2024-06-14T17:31:32+02:00 WIP: improve broadcast, especially on LLVM - - - - - 6 changed files: - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/StgToCmm/Prim.hs - testsuite/tests/simd/should_run/simd008.hs Changes: ===================================== compiler/GHC/Cmm/MachOp.hs ===================================== @@ -596,10 +596,10 @@ machOpArgReps platform op = MO_V_Shuffle l r _ -> [vecwidth l r, vecwidth l r] MO_VF_Shuffle l r _ -> [vecwidth l r, vecwidth l r] - MO_V_Broadcast l r -> [vecwidth l r, r] + MO_V_Broadcast _ r -> [r] MO_V_Insert l r -> [vecwidth l r, r, W32] MO_V_Extract l r -> [vecwidth l r, W32] - MO_VF_Broadcast l r -> [vecwidth l r, r] + MO_VF_Broadcast _ r -> [r] MO_VF_Insert l r -> [vecwidth l r, r, W32] MO_VF_Extract l r -> [vecwidth l r, W32] -- SIMD vector indices are always 32 bit ===================================== compiler/GHC/Cmm/Opt.hs ===================================== @@ -79,6 +79,10 @@ cmmMachOpFoldM -> MachOp -> [CmmExpr] -> Maybe CmmExpr +cmmMachOpFoldM _ (MO_V_Broadcast {}) _ = Nothing + -- SIMD NCG TODO: constant folding doesn't work correctly for Broadcast instructions, + -- perhaps due to the fact that the argument is a scalar but the result is a vector. +cmmMachOpFoldM _ (MO_VF_Broadcast {}) _ = Nothing cmmMachOpFoldM _ op [CmmLit (CmmInt x rep)] = Just $! case op of @@ -93,7 +97,6 @@ cmmMachOpFoldM _ op [CmmLit (CmmInt x rep)] MO_SS_Conv from to -> CmmLit (CmmInt (narrowS from x) to) MO_UU_Conv from to -> CmmLit (CmmInt (narrowU from x) to) MO_XX_Conv from to -> CmmLit (CmmInt (narrowS from x) to) - _ -> panic $ "cmmMachOpFoldM: unknown unary op: " ++ show op -- Eliminate shifts that are wider than the shiftee ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1008,6 +1008,7 @@ getRegister' _ is32Bit (CmmMachOp (MO_Add W64) [CmmReg (CmmGlobal (GlobalRegUse LEA II64 (OpAddr (ripRel (litToImm displacement))) (OpReg dst)) getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps + sse4_1 <- sse4_1Enabled sse2 <- sse2Enabled sse <- sseEnabled avx <- avxEnabled @@ -1104,6 +1105,19 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps -- SIMD NCG TODO MO_VS_Neg {} -> needLlvm mop + MO_VF_Broadcast l W32 | avx -> vector_float_broadcast_avx l W32 x + | sse4_1 -> vector_float_broadcast_sse l W32 x + | otherwise + -> sorry "Please enable the -mavx or -msse4 flag" + MO_VF_Broadcast l W64 | sse2 -> vector_float_broadcast_avx l W64 x + | otherwise -> sorry "Please enable the -msse2 flag" + MO_VF_Broadcast {} -> incorrectOperands + + MO_V_Broadcast l W64 | sse2 -> vector_int_broadcast l W64 x + | otherwise -> sorry "Please enable the -msse2 flag" + -- SIMD NCG TODO: W32, W16, W8 + MO_V_Broadcast {} -> needLlvm mop + -- Binary MachOps MO_Add {} -> incorrectOperands MO_Sub {} -> incorrectOperands @@ -1156,8 +1170,6 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps MO_VF_Sub {} -> incorrectOperands MO_VF_Mul {} -> incorrectOperands MO_VF_Quot {} -> incorrectOperands - MO_V_Broadcast {} -> incorrectOperands - MO_VF_Broadcast {} -> incorrectOperands -- Ternary MachOps MO_FMA {} -> incorrectOperands @@ -1240,9 +1252,74 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps (SUB format (OpReg reg) (OpReg dst)) return (Any format code) + ----------------------- + vector_float_broadcast_avx :: Length + -> Width + -> CmmExpr + -> NatM Register + vector_float_broadcast_avx len W32 expr + = do + (reg, exp) <- getSomeReg expr + let f = VecFormat len FmtFloat + addr = spRel platform 0 + in return $ Any f (\dst -> exp `snocOL` + (MOVU f (OpReg reg) (OpAddr addr)) `snocOL` + (VBROADCAST f addr dst)) + vector_float_broadcast_avx len W64 expr + = do + (reg, exp) <- getSomeReg expr + let f = VecFormat len FmtDouble + addr = spRel platform 0 + in return $ Any f (\dst -> exp `snocOL` + (MOVU f (OpReg reg) (OpAddr addr)) `snocOL` + (MOVL f (OpAddr addr) (OpReg dst)) `snocOL` + (MOVH f (OpAddr addr) (OpReg dst))) + vector_float_broadcast_avx _ _ c + = pprPanic "Broadcast not supported for : " (pdoc platform c) + ----------------------- + vector_float_broadcast_sse :: Length + -> Width + -> CmmExpr + -> NatM Register + vector_float_broadcast_sse len W32 expr + = do + (reg, exp) <- getSomeReg expr + let f = VecFormat len FmtFloat + addr = spRel platform 0 + code dst = exp `snocOL` + (MOVU f (OpReg reg) (OpAddr addr)) `snocOL` + (insertps $ 0b1110) `snocOL` + (insertps $ 16) `snocOL` + (insertps $ 32) `snocOL` + (insertps $ 48) + where + insertps imm = + INSERTPS f (ImmInt imm) (OpAddr addr) dst + + in return $ Any f code + vector_float_broadcast_sse _ _ c + = pprPanic "Broadcast not supported for : " (pdoc platform c) + + vector_int_broadcast :: Length + -> Width + -> CmmExpr + -> NatM Register + vector_int_broadcast len W64 expr + = do + (reg, exp) <- getSomeReg expr + let fmt = VecFormat len FmtInt64 + return $ Any fmt (\dst -> exp `snocOL` + (MOV II64 (OpReg reg) (OpReg dst)) `snocOL` + (PUNPCKLQDQ fmt (OpReg dst) dst) `snocOL` + (PUNPCKLQDQ fmt (OpReg dst) dst) `snocOL` + (PUNPCKLQDQ fmt (OpReg dst) dst) `snocOL` + (PUNPCKLQDQ fmt (OpReg dst) dst) + ) + vector_int_broadcast _ _ c + = pprPanic "Broadcast not supported for : " (pdoc platform c) + getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps - sse4_1 <- sse4_1Enabled sse2 <- sse2Enabled sse <- sseEnabled avx <- avxEnabled @@ -1299,7 +1376,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps MO_S_Shr rep -> shift_code rep SAR x y {-False-} MO_VF_Shuffle l w is - | l * widthInBytes w == 128 + | l * widthInBits w == 128 -> if | avx -> vector_shuffle_float l w x y is @@ -1308,19 +1385,6 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps | otherwise -> sorry "Please use -fllvm for wide shuffle instructions" - MO_VF_Broadcast l W32 | avx -> vector_float_broadcast_avx l W32 x y - | sse4_1 -> vector_float_broadcast_sse l W32 x y - | otherwise - -> sorry "Please enable the -mavx or -msse4 flag" - MO_VF_Broadcast l W64 | sse2 -> vector_float_broadcast_avx l W64 x y - | otherwise -> sorry "Please enable the -msse2 flag" - MO_VF_Broadcast {} -> incorrectOperands - - MO_V_Broadcast l W64 | sse2 -> vector_int_broadcast l W64 x y - | otherwise -> sorry "Please enable the -msse2 flag" - -- SIMD NCG TODO: W32, W16, W8 - MO_V_Broadcast {} -> needLlvm mop - MO_VF_Extract l W32 | avx -> vector_float_unpack l W32 x y | sse -> vector_float_unpack_sse l W32 x y | otherwise @@ -1384,6 +1448,8 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps MO_AlignmentCheck {} -> incorrectOperands MO_VS_Neg {} -> incorrectOperands MO_VF_Neg {} -> incorrectOperands + MO_V_Broadcast {} -> incorrectOperands + MO_VF_Broadcast {} -> incorrectOperands -- Ternary MachOps MO_FMA {} -> incorrectOperands @@ -1677,78 +1743,6 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps vector_float_unpack_sse _ w c e = pprPanic "Unpack not supported for : " (pdoc platform c $$ pdoc platform e $$ ppr w) ----------------------- - vector_float_broadcast_avx :: Length - -> Width - -> CmmExpr - -> CmmExpr - -> NatM Register - vector_float_broadcast_avx len W32 expr1 expr2 - = do - fn <- getAnyReg expr1 - (r', exp) <- getSomeReg expr2 - let f = VecFormat len FmtFloat - addr = spRel platform 0 - in return $ Any f (\r -> exp `appOL` - (fn r) `snocOL` - (MOVU f (OpReg r') (OpAddr addr)) `snocOL` - (VBROADCAST f addr r)) - vector_float_broadcast_avx len W64 expr1 expr2 - = do - fn <- getAnyReg expr1 - (r', exp) <- getSomeReg expr2 - let f = VecFormat len FmtDouble - addr = spRel platform 0 - in return $ Any f (\r -> exp `appOL` - (fn r) `snocOL` - (MOVU f (OpReg r') (OpAddr addr)) `snocOL` - (MOVL f (OpAddr addr) (OpReg r)) `snocOL` - (MOVH f (OpAddr addr) (OpReg r))) - vector_float_broadcast_avx _ _ c _ - = pprPanic "Broadcast not supported for : " (pdoc platform c) - ----------------------- - vector_float_broadcast_sse :: Length - -> Width - -> CmmExpr - -> CmmExpr - -> NatM Register - vector_float_broadcast_sse len W32 expr1 expr2 - = do - fn <- getAnyReg expr1 -- destination - (r, exp) <- getSomeReg expr2 -- source - let f = VecFormat len FmtFloat - addr = spRel platform 0 - code dst = exp `appOL` - (fn dst) `snocOL` - (MOVU f (OpReg r) (OpAddr addr)) `snocOL` - (insertps 0) `snocOL` - (insertps 16) `snocOL` - (insertps 32) `snocOL` - (insertps 48) - where - insertps off = - INSERTPS f (litToImm $ CmmInt off W32) (OpAddr addr) dst - - in return $ Any f code - vector_float_broadcast_sse _ _ c _ - = pprPanic "Broadcast not supported for : " (pdoc platform c) - - vector_int_broadcast :: Length - -> Width - -> CmmExpr - -> CmmExpr - -> NatM Register - vector_int_broadcast len W64 expr1 expr2 - = do - fn <- getAnyReg expr1 - (val, exp) <- getSomeReg expr2 - let fmt = VecFormat len FmtInt64 - return $ Any fmt (\dst -> exp `appOL` - (fn dst) `snocOL` - (MOV II64 (OpReg val) (OpReg dst)) `snocOL` - (PUNPCKLQDQ fmt (OpReg dst) dst)) - vector_int_broadcast _ _ c _ - = pprPanic "Broadcast not supported for : " (pdoc platform c) - ----------------------- vector_int_unpack_sse :: Length -> Width ===================================== compiler/GHC/CmmToLlvm/CodeGen.hs ===================================== @@ -1460,6 +1460,9 @@ genMachOp _ op [x] = case op of all0s = LMLitVar $ LMVectorLit (replicate len all0) in negateVec vecty all0s LM_MO_FSub + MO_V_Broadcast l w -> genBroadcastOp l w x + MO_VF_Broadcast l w -> genBroadcastOp l w x + MO_RelaxedRead w -> exprToVar (CmmLoad x (cmmBits w) NaturallyAligned) MO_AlignmentCheck _ _ -> panic "-falignment-sanitisation is not supported by -fllvm" @@ -1520,8 +1523,6 @@ genMachOp _ op [x] = case op of MO_VU_Quot _ _ -> panicOp MO_VU_Rem _ _ -> panicOp - MO_VF_Broadcast _ _ -> panicOp - MO_V_Broadcast _ _ -> panicOp MO_VF_Insert _ _ -> panicOp MO_VF_Extract _ _ -> panicOp @@ -1719,12 +1720,11 @@ genMachOp_slow opt op [x, y] = case op of MO_WF_Bitcast _to -> panicOp MO_FW_Bitcast _to -> panicOp - MO_V_Insert {} -> panicOp - MO_VS_Neg {} -> panicOp - MO_V_Broadcast {} -> panicOp - MO_VF_Broadcast {} -> panicOp + MO_VF_Broadcast {} -> panicOp + MO_V_Broadcast {} -> panicOp + MO_V_Insert {} -> panicOp MO_VF_Insert {} -> panicOp MO_V_Shuffle _ _ is -> genShuffleOp is x y @@ -1818,12 +1818,12 @@ genMachOp_slow opt op [x, y] = case op of pprPanic "isSMulOK: Not bit type! " $ lparen <> ppr word <> rparen - panicOp = panic $ "LLVM.CodeGen.genMachOp_slow: non-binary op encountered" + panicOp = panic $ "LLVM.CodeGen.genMachOp_slow: non-binary op encountered " ++ "with two arguments! (" ++ show op ++ ")" genMachOp_slow _opt op [x, y, z] = do let - panicOp = panic $ "LLVM.CodeGen.genMachOp_slow: non-ternary op encountered" + panicOp = panic $ "LLVM.CodeGen.genMachOp_slow: non-ternary op encountered " ++ "with three arguments! (" ++ show op ++ ")" case op of MO_FMA var lg width -> @@ -1846,6 +1846,21 @@ genMachOp_slow _opt op [x, y, z] = do -- More than three expressions, invalid! genMachOp_slow _ _ _ = panic "genMachOp_slow: More than 3 expressions in MachOp!" +genBroadcastOp :: Int -> Width -> CmmExpr -> LlvmM ExprData +genBroadcastOp lg _width x = runExprData $ do + -- To broadcast a scalar x as a vector v: + -- 1. insert x at the 0 position of the zero vector + -- 2. shuffle x into all positions + var_x <- exprToVarW x + let tx = getVarType var_x + tv = LMVector lg tx + z = if isFloat tx + then LMFloatLit 0 tx + else LMIntLit 0 tx + zs = LMLitVar $ LMVectorLit $ replicate lg z + w <- doExprW tv $ Insert zs var_x (LMLitVar $ LMIntLit 0 (LMInt 32)) + doExprW tv $ Shuffle w w (replicate lg 0) + genShuffleOp :: [Int] -> CmmExpr -> CmmExpr -> LlvmM ExprData genShuffleOp is x y = runExprData $ do vx <- exprToVarW x ===================================== compiler/GHC/StgToCmm/Prim.hs ===================================== @@ -949,16 +949,8 @@ emitPrimOp cfg primop = -- SIMD primops (VecBroadcastOp vcat n w) -> \[e] -> opIntoRegs $ \[res] -> do checkVecCompatibility cfg vcat n w - doVecBroadcastOp ty zeros e res + doVecBroadcastOp ty e res where - zeros :: CmmExpr - zeros = CmmLit $ CmmVec (replicate n zero) - - zero :: CmmLit - zero = case vcat of - IntVec -> CmmInt 0 w - WordVec -> CmmInt 0 w - FloatVec -> CmmFloat 0 w ty :: CmmType ty = vecVmmType vcat n w @@ -2612,28 +2604,17 @@ checkVecCompatibility cfg vcat l w = -- Helpers for translating vector packing and unpacking. doVecBroadcastOp :: CmmType -- Type of vector - -> CmmExpr -- Initial vector - -> CmmExpr -- Elements + -> CmmExpr -- Element -> CmmFormal -- Destination for result -> FCode () -doVecBroadcastOp ty z es res = do - dst <- newTemp ty - emitAssign (CmmLocal dst) z - vecBroadcast dst es 0 +doVecBroadcastOp ty e dst + | isFloatType (vecElemType ty) + = emitAssign (CmmLocal dst) (CmmMachOp (MO_VF_Broadcast len wid) [e]) + | otherwise + = emitAssign (CmmLocal dst) (CmmMachOp (MO_V_Broadcast len wid) [e]) where - vecBroadcast :: CmmFormal -> CmmExpr -> Int -> FCode () - vecBroadcast src e _ = do - dst <- newTemp ty - if isFloatType (vecElemType ty) - then emitAssign (CmmLocal dst) (CmmMachOp (MO_VF_Broadcast len wid) - [CmmReg (CmmLocal src), e]) - else emitAssign (CmmLocal dst) (CmmMachOp (MO_V_Broadcast len wid) - [CmmReg (CmmLocal src), e]) - emitAssign (CmmLocal res) (CmmReg (CmmLocal dst)) - len :: Length len = vecLength ty - wid :: Width wid = typeWidth (vecElemType ty) ===================================== testsuite/tests/simd/should_run/simd008.hs ===================================== @@ -1,6 +1,5 @@ {-# OPTIONS_GHC -mavx #-} {-# OPTIONS_GHC -msse4 #-} -{-# OPTIONS_GHC -ddump-asm-native -ddump-asm-regalloc -ddump-asm-liveness #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE ExtendedLiterals #-} View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/df28c0e55e4a921024ac2a7d26d6d3e3bc3393f8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/df28c0e55e4a921024ac2a7d26d6d3e3bc3393f8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 15:54:33 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 14 Jun 2024 11:54:33 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] more tidying Message-ID: <666c67b9a40b3_16c74ba3c5a02544a@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: d565519c by sheaf at 2024-06-14T17:54:19+02:00 more tidying - - - - - 5 changed files: - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs - − compiler/ghc-llvm-version.h - libraries/base/src/GHC/Base.hs Changes: ===================================== compiler/GHC/Cmm/CallConv.hs ===================================== @@ -236,8 +236,6 @@ realArgRegsCover platform realDoubleRegs platform ++ realLongRegs platform -- we don't save XMM registers if they are not used for parameter passing --- SLD TODO: do we need to save xmm/ymm registers now as well? - {- ===================================== compiler/GHC/CmmToAsm/Format.hs ===================================== @@ -54,7 +54,7 @@ These include: * 'Format.ScalarFormat': The format of a 'Format.VecFormat'\'s scalar. - * 'RegClass.RegClass': Whether a register is an integer, float-point, or vector register + * 'RegClass.RegClass': Whether a register is an integer or a floating point/vector register. -} -- It looks very like the old MachRep, but it's now of purely local ===================================== compiler/GHC/CmmToAsm/X86/RegInfo.hs ===================================== @@ -29,8 +29,7 @@ mkVirtualReg u format -- For now we map both to being allocated as "Double" Registers -- on X86/X86_64 FF64 -> VirtualRegD u - --TODO: - -- Add VirtualRegAVX and inspect VecFormat and allocate + -- SIMD NCG TODO: add support for 256 and 512-wide vectors. VecFormat {} -> VirtualRegV128 u _other -> VirtualRegI u ===================================== compiler/ghc-llvm-version.h deleted ===================================== @@ -1,11 +0,0 @@ -/* compiler/ghc-llvm-version.h. Generated from ghc-llvm-version.h.in by configure. */ -#if !defined(__GHC_LLVM_VERSION_H__) -#define __GHC_LLVM_VERSION_H__ - -/* The maximum supported LLVM version number */ -#define sUPPORTED_LLVM_VERSION_MAX (16) - -/* The minimum supported LLVM version number */ -#define sUPPORTED_LLVM_VERSION_MIN (13) - -#endif /* __GHC_LLVM_VERSION_H__ */ ===================================== libraries/base/src/GHC/Base.hs ===================================== @@ -139,11 +139,71 @@ module GHC.Base ) where import GHC.Internal.Base -import GHC.Prim hiding (dataToTagLarge#, dataToTagSmall#, whereFrom#) - -- Hide dataToTagLarge# because it is expected to break for - -- GHC-internal reasons in the near future, and shouldn't - -- be exposed from base (not even GHC.Exts) - -- whereFrom# is similarly internal. +import GHC.Prim hiding + ( + -- Hide dataToTag# ops because they are expected to break for + -- GHC-internal reasons in the near future, and shouldn't + -- be exposed from base + dataToTagSmall#, dataToTagLarge# + -- whereFrom# is similarly internal. + , whereFrom# + -- Don't re-export vector FMA instructions + , fmaddFloatX4# + , fmsubFloatX4# + , fnmaddFloatX4# + , fnmsubFloatX4# + , fmaddFloatX8# + , fmsubFloatX8# + , fnmaddFloatX8# + , fnmsubFloatX8# + , fmaddFloatX16# + , fmsubFloatX16# + , fnmaddFloatX16# + , fnmsubFloatX16# + , fmaddDoubleX2# + , fmsubDoubleX2# + , fnmaddDoubleX2# + , fnmsubDoubleX2# + , fmaddDoubleX4# + , fmsubDoubleX4# + , fnmaddDoubleX4# + , fnmsubDoubleX4# + , fmaddDoubleX8# + , fmsubDoubleX8# + , fnmaddDoubleX8# + , fnmsubDoubleX8# + -- Don't re-export SIMD shuffle primops + , shuffleDoubleX2# + , shuffleDoubleX4# + , shuffleDoubleX8# + , shuffleFloatX16# + , shuffleFloatX4# + , shuffleFloatX8# + , shuffleInt16X16# + , shuffleInt16X32# + , shuffleInt16X8# + , shuffleInt32X16# + , shuffleInt32X4# + , shuffleInt32X8# + , shuffleInt64X2# + , shuffleInt64X4# + , shuffleInt64X8# + , shuffleInt8X16# + , shuffleInt8X32# + , shuffleInt8X64# + , shuffleWord16X16# + , shuffleWord16X32# + , shuffleWord16X8# + , shuffleWord32X16# + , shuffleWord32X4# + , shuffleWord32X8# + , shuffleWord64X2# + , shuffleWord64X4# + , shuffleWord64X8# + , shuffleWord8X16# + , shuffleWord8X32# + , shuffleWord8X64# + ) import GHC.Prim.Ext import GHC.Prim.PtrEq View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d565519c80be8d180ec6cfd19fc81947ba1999a0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d565519c80be8d180ec6cfd19fc81947ba1999a0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 15:55:23 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 14 Jun 2024 11:55:23 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/romes/parse_bswap Message-ID: <666c67ebb8191_16c74bb4bf2c25783@gitlab.mail> Rodrigo Mesquita pushed new branch wip/romes/parse_bswap at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/parse_bswap You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 16:35:20 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 14 Jun 2024 12:35:20 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T24725 Message-ID: <666c7148f1dd8_16c74b108304433715@gitlab.mail> Simon Peyton Jones pushed new branch wip/T24725 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T24725 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 17:45:03 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 14 Jun 2024 13:45:03 -0400 Subject: [Git][ghc/ghc][wip/jade/ast] 25 commits: JS: establish single source of truth for symbols Message-ID: <666c819f1b5f4_16c74b1a18f6445129@gitlab.mail> Rodrigo Mesquita pushed to branch wip/jade/ast at Glasgow Haskell Compiler / GHC Commits: 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 50ff0d4d by Jade at 2024-06-14T18:44:47+01:00 Refactor FieldOcc vs AmbiguousFieldOcc with TTG Improves the design of FieldOcc vs AmbiguousFieldOcc, and removes a dependency on `RdrName` from the Language.Haskell.* namespace (#21592). The design: * The FieldOcc constructor of FieldOcc always refers to an unambiguous field occurrence. * During renaming, a FieldOcc may be ambiguous and only be resolvable during Typechecking * Therefore, we extend (with TTG) `FieldOcc GhcRn` with a constructor `AmbiguousFieldOcc` that constructs a definitely ambiguous `FieldOcc`. * During typechecking, all ambiguous field occurrences must be resolved, so the `AmbiguousFieldOcc` constructor no longer exists See Note [Lifecycle of a FieldOcc] Co-authored-by: Rodrigo Mesquita <rodrigo.m.mesquita at gmail.com> - - - - - 30 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Builtin/Names.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/JS/Ident.hs - compiler/GHC/JS/JStg/Monad.hs - compiler/GHC/JS/JStg/Syntax.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Syntax.hs - compiler/GHC/Parser/PostProcess.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3e02be25b7f9ae46010247a547baff3b72ca5a90...50ff0d4dd4f9010b59919ffce993cc9769b7e398 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3e02be25b7f9ae46010247a547baff3b72ca5a90...50ff0d4dd4f9010b59919ffce993cc9769b7e398 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 18:21:44 2024 From: gitlab at gitlab.haskell.org (Fabian Kirchner (@kirchner)) Date: Fri, 14 Jun 2024 14:21:44 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ttg-zurich] 23 commits: users-guide: Fix stylistic issues in 9.12 release notes Message-ID: <666c8a38cb093_16c74b1f764d44592d@gitlab.mail> Fabian Kirchner pushed to branch wip/kirchner/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - b2035eec by romes at 2024-06-14T20:21:28+02:00 Split TTG orphans from internal `Fixity` data type Filling in missing instances and creating a separate "semantic" datatype are two different layers of abstraction, and so we should create two different modules for them. Fixed arrow desugaring bug. (This was dead code before.) Co-authored-by: Fabian Kirchner <kirchner at posteo.de> - - - - - 30 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Driver/Config/Core/Lint.hs - + compiler/GHC/Hs/Basic.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/HsType.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1416bd6416a7c67fedc8c0515f771b642cc0df58...b2035eecfdcaa8b122113523e4e8fe76f58d7341 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1416bd6416a7c67fedc8c0515f771b642cc0df58...b2035eecfdcaa8b122113523e4e8fe76f58d7341 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 18:44:51 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 14 Jun 2024 14:44:51 -0400 Subject: [Git][ghc/ghc][master] 4 commits: Add hack for #24623 Message-ID: <666c8fa398769_16c74b2371570507ed@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 30 changed files: - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Types/Name/Occurrence.hs - compiler/GHC/Types/Var/Env.hs - testsuite/tests/dependent/should_compile/T15743e.stderr - testsuite/tests/dependent/should_fail/T16326_Fail4.stderr - testsuite/tests/dependent/should_fail/T16326_Fail5.stderr - testsuite/tests/indexed-types/should_fail/T13877.stderr - testsuite/tests/indexed-types/should_fail/T14369.stderr - testsuite/tests/patsyn/should_fail/T15695.stderr - testsuite/tests/polykinds/T11520.stderr - testsuite/tests/polykinds/T14846.stderr - testsuite/tests/polykinds/T15787.stderr - testsuite/tests/polykinds/T7278.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ce76bf7851d4ec7a3ebd414a1991b3e71dfbc8c8...e5d24cc28a00a7af40539b47b54d71636bb77ae8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ce76bf7851d4ec7a3ebd414a1991b3e71dfbc8c8...e5d24cc28a00a7af40539b47b54d71636bb77ae8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 18:45:49 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 14 Jun 2024 14:45:49 -0400 Subject: [Git][ghc/ghc][master] Localise a case-binder in SpecConstr.mkSeqs Message-ID: <666c8fddf09a2_16c74b2527b9455557@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - 4 changed files: - compiler/GHC/Core/Opt/SpecConstr.hs - + testsuite/tests/simplCore/should_compile/T24944.hs - + testsuite/tests/simplCore/should_compile/T24944a.hs - testsuite/tests/simplCore/should_compile/all.T Changes: ===================================== compiler/GHC/Core/Opt/SpecConstr.hs ===================================== @@ -639,6 +639,17 @@ That is we make the specialized function strict in arguments representing strict fields. See Note [Call-by-value for worker args] for why we do this. +(SCF1) The arg_id might be an /imported/ Id like M.foo_acf (see #24944). + We don't want to make + case M.foo_acf of M.foo_acf { DEFAULT -> blah } + because the binder of a case-expression should never be imported. Rather, + we must localise it thus: + case M.foo_acf of foo_acf { DEFAULT -> blah } + We keep the same unique, so in the next round of simplification we'll replace + any M.foo_acf's in `blah` by `foo_acf`. + + c.f. Note [Localise pattern binders] in GHC.HsToCore.Utils. + Note [Specialising on dictionaries] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ In #21386, SpecConstr saw this call: @@ -2030,8 +2041,8 @@ generaliseDictPats qvars pats | otherwise = return (extra_qvs, pat) --- See Note [SpecConstr and strict fields] mkSeqs :: [Var] -> Type -> CoreExpr -> CoreExpr +-- See Note [SpecConstr and strict fields] mkSeqs seqees res_ty rhs = foldr addEval rhs seqees where @@ -2039,7 +2050,11 @@ mkSeqs seqees res_ty rhs = addEval arg_id rhs -- Argument representing strict field and it's worth passing via cbv | shouldStrictifyIdForCbv arg_id - = Case (Var arg_id) arg_id res_ty ([Alt DEFAULT [] rhs]) + = Case (Var arg_id) + (localiseId arg_id) -- See (SCF1) in Note [SpecConstr and strict fields] + res_ty + ([Alt DEFAULT [] rhs]) + | otherwise = rhs ===================================== testsuite/tests/simplCore/should_compile/T24944.hs ===================================== @@ -0,0 +1,26 @@ +module T24944 where + +import T24944a + +data DataCon = DC TyCon + +data AltCon = DataAlt DataCon | LitAlt + +data GenStgAlt pass = GenStgAlt + { alt_con :: !AltCon + } + +data Type = TyVarTy | FunTy | TyConApp TyCon + +mkStgAltTypeFromStgAlts :: Type -> [GenStgAlt Int] -> Maybe TyCon +mkStgAltTypeFromStgAlts bndr_ty alts + = let may = case bndr_ty of + TyConApp tc -> Just tc + FunTy -> Just myTyCon + TyVarTy -> Nothing + in case may of + Just (TyCon { tyConDetails = AlgTyCon True }) + -> case alt_con <$> alts of + DataAlt (DC con) : _ -> Just con + _ -> Nothing + _ -> Nothing ===================================== testsuite/tests/simplCore/should_compile/T24944a.hs ===================================== @@ -0,0 +1,20 @@ +module T24944a where + +data TyCon = TyCon { + tyConNullaryTy :: TyCon, + tyConDetails :: !TyConDetails + } + +data TyConDetails = + AlgTyCon Bool + | PrimTyCon Int + | PromotedDataCon + +myTyCon :: TyCon +myTyCon = TyCon { tyConDetails = PrimTyCon 1 + , tyConNullaryTy = id' myTyCon + } + +id' :: TyCon -> TyCon +id' a = a +{-# NOINLINE id' #-} ===================================== testsuite/tests/simplCore/should_compile/all.T ===================================== @@ -522,3 +522,6 @@ test('T24726', normal, compile, ['-dcore-lint -dsuppress-uniques']) test('T24768', normal, compile, ['-O']) test('T24770', [ grep_errmsg(r'Dead') ], compile, ['-O']) test('T24808', [ grep_errmsg(r'myFunction') ], compile, ['-O -ddump-simpl']) + +# T24944 needs -O2 because it's about SpecConstr +test('T24944', [extra_files(['T24944a.hs'])], multimod_compile, ['T24944', '-v0 -O2']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/246bc3a43a57b7c9ea907bd9ef15b7ef7c490681 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/246bc3a43a57b7c9ea907bd9ef15b7ef7c490681 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 18:53:55 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 14 Jun 2024 14:53:55 -0400 Subject: [Git][ghc/ghc][wip/T24623] Wibbles Message-ID: <666c91c3805c9_16c74b2761a9059537@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24623 at Glasgow Haskell Compiler / GHC Commits: d92d78a5 by Simon Peyton Jones at 2024-06-14T19:53:30+01:00 Wibbles - - - - - 4 changed files: - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/WorkWrap.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Types/Demand.hs Changes: ===================================== compiler/GHC/Core/Opt/DmdAnal.hs ===================================== @@ -1081,30 +1081,30 @@ dmdAnalRhsSig -- Process the RHS of the binding, add the strictness signature -- to the Id, and augment the environment with the signature as well. -- See Note [NOINLINE and strictness] -dmdAnalRhsSig top_lvl rec_flag env let_subdmd id rhs +dmdAnalRhsSig top_lvl rec_flag env let_sd id rhs = -- pprTrace "dmdAnalRhsSig" (ppr id $$ ppr let_dmd $$ ppr rhs_dmds $$ ppr sig $$ ppr weak_fvs) $ (final_env, weak_fvs, final_id, final_rhs) where ww_arity = workWrapArity id rhs -- See Note [WorkWrap arity and join points, point (1)] - body_subdmd | isJoinId id = let_subdmd - | otherwise = topSubDmd + body_sd | isJoinId id = let_sd + | otherwise = topSubDmd -- See Note [Demand analysis for join points] -- See Note [Invariants on join points] invariant 2b, in GHC.Core -- ww_arity matches the join arity of the join point - adjusted_body_subdmd = unboxedWhenSmall env rec_flag (resultType_maybe id) body_subdmd + adjusted_body_sd = unboxedWhenSmall env rec_flag (resultType_maybe id) body_sd -- See Note [Unboxed demand on function bodies returning small products] - rhs_subdmd = mkCalledOnceDmds ww_arity adjusted_body_subdmd + rhs_sd = mkCalledOnceDmds ww_arity adjusted_body_sd - WithDmdType rhs_dmd_ty rhs' = dmdAnal env rhs_subdmd rhs + WithDmdType rhs_dmd_ty rhs' = dmdAnal env rhs_sd rhs DmdType rhs_env rhs_dmds = rhs_dmd_ty (final_rhs_dmds, final_rhs) = finaliseArgBoxities env id ww_arity rhs_dmds (de_div rhs_env) rhs' - dmd_sig_arity = ww_arity + calledOnceArity body_subdmd + dmd_sig_arity = ww_arity + calledOnceArity body_sd sig = mkDmdSigForArity dmd_sig_arity (DmdType sig_env final_rhs_dmds) opts = ae_opts env @@ -1248,9 +1248,9 @@ branch does so too, so we are fine. So, as usual, we need to transport demands on free variables to the call site(s). Compare Note [Lazy and unleashable free variables]. -The implementation is easy: see `body_subdmd` in`dmdAnalRhsSig`. When analysing +The implementation is easy: see `body_sd` in`dmdAnalRhsSig`. When analysing a join point, we can analyse its body (after stripping off the join binders, -here just 'y') with the demand from the entire join-binding (written `let_subdmd` +here just 'y') with the demand from the entire join-binding (written `let_sd` here). Another win for join points! #13543. @@ -1277,7 +1277,7 @@ Consider The entire thing is in a C(1,L) context, so we will analyse j's body, namely \y. error "urk" -with demand C(C(1,L)). See `rhs_subdmd` in `dmdAnalRhsSig`. That will produce +with demand C(C(1,L)). See `rhs_sd` in `dmdAnalRhsSig`. That will produce a demand signature of b: and indeed `j` diverges when given two arguments. BUT we do /not/ want to worker/wrapper `j` with two arguments. Suppose we have @@ -1321,7 +1321,7 @@ Conclusion: Note [The demand for the RHS of a binding] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Given a binding { f = rhs }, in `dmdAnalRhsSig` we compute a `rhs_subdmd` in +Given a binding { f = rhs }, in `dmdAnalRhsSig` we compute a `rhs_sd` in which to analyse `rhs`. The demand we use is: @@ -2009,12 +2009,9 @@ finaliseArgBoxities env fn ww_arity arg_dmds div rhs -- of the function, both because that's kosher, and because CPR analysis -- uses the info on the binders directly. where - opts = ae_opts env - (bndrs, _body) = collectBinders rhs -- length bndrs >= ww_arity - unarise_arity = sum [ unariseArity (idType b) | b <- bndrs, isId b ] - max_wkr_args = dmd_max_worker_args opts `max` unarise_arity - -- This is the budget initialisation step of - -- Note [Worker argument budget] + opts = ae_opts env + (bndrs, _body) = collectBinders rhs + -- NB: in the interesting code path, count isId bndrs >= ww_arity arg_triples :: [(Type, StrictnessMark, Demand)] arg_triples = take ww_arity $ @@ -2030,6 +2027,10 @@ finaliseArgBoxities env fn ww_arity arg_dmds div rhs -- The remaining budget from one layer becomes the initial -- budget for the next layer down. See Note [Worker argument budget] (remaining_budget, ww_arg_dmds) = go_args (MkB max_wkr_args remaining_budget) arg_triples + unarise_arity = sum [ unariseArity (idType b) | b <- bndrs, isId b ] + max_wkr_args = dmd_max_worker_args opts `max` unarise_arity + -- This is the budget initialisation step of + -- Note [Worker argument budget] get_dmd :: Id -> Demand get_dmd bndr ===================================== compiler/GHC/Core/Opt/WorkWrap.hs ===================================== @@ -762,7 +762,7 @@ splitFun ww_opts fn_id rhs = warnPprTrace (not (wrap_dmds `lengthIs` (arityInfo fn_info))) "splitFun" (ppr fn_id <+> (ppr wrap_dmds $$ ppr cpr)) $ - do { mb_stuff <- mkWwBodies ww_opts fn_id arg_vars (exprType body) wrap_dmds cpr + do { mb_stuff <- mkWwBodies ww_opts fn_id ww_arity arg_vars (exprType body) wrap_dmds cpr ; case mb_stuff of Nothing -> -- No useful wrapper; leave the binding alone return [(fn_id, rhs)] ===================================== compiler/GHC/Core/Opt/WorkWrap/Utils.hs ===================================== @@ -159,6 +159,7 @@ nop_fn body = body mkWwBodies :: WwOpts -> Id -- ^ The original function + -> Arity -- ^ Worker/wrapper arity -> [Var] -- ^ Manifest args of original function -> Type -- ^ Result type of the original function, -- after being stripped of args @@ -205,7 +206,7 @@ mkWwBodies :: WwOpts -- and beta-redexes]), which allows us to apply the same split to function body -- and its unfolding(s) alike. -- -mkWwBodies opts fun_id arg_vars res_ty demands res_cpr +mkWwBodies opts fun_id ww_arity arg_vars res_ty demands res_cpr = do { massertPpr arity_ok (text "wrong wrapper arity" $$ ppr fun_id $$ ppr arg_vars $$ ppr res_ty $$ ppr demands) @@ -271,8 +272,7 @@ mkWwBodies opts fun_id arg_vars res_ty demands res_cpr | otherwise = False - ww_arity = count isId arg_vars -- Work/wrap arity - n_dmds = length demands + n_dmds = length demands arity_ok | isJoinId fun_id = ww_arity <= n_dmds | otherwise = ww_arity == n_dmds ===================================== compiler/GHC/Types/Demand.hs ===================================== @@ -1041,11 +1041,7 @@ peelManyCalls k sd = go k C_11 sd calledOnceArity :: SubDemand -> Arity calledOnceArity sd = go 0 sd where - go n (Call C_11 sd) = go (n+1) sd - -- NB: /Not/ viewCall, because we'd go infinitely deep on a Poly without - -- knowing the type arity (the upper bound for the threshold). - -- Besides, we only really are interested in C_11 or C_01 Calls for - -- which we'll never use Poly anyway (cf. 'CardNonOnce'). + go n (viewCall -> Call C_11 sd) = go (n+1) sd go n _ = n -- | Extract the 'SubDemand' of a 'Demand'. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d92d78a5021a10571a1629afa335c70a562eb62b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d92d78a5021a10571a1629afa335c70a562eb62b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 14 22:16:12 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 14 Jun 2024 18:16:12 -0400 Subject: [Git][ghc/ghc][wip/T24623] Wibbles Message-ID: <666cc12cd8785_aa801441d9837675@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24623 at Glasgow Haskell Compiler / GHC Commits: 631c09b5 by Simon Peyton Jones at 2024-06-14T23:15:57+01:00 Wibbles - - - - - 2 changed files: - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Types/Demand.hs Changes: ===================================== compiler/GHC/Core/Opt/DmdAnal.hs ===================================== @@ -1008,7 +1008,7 @@ dmdTransform :: AnalEnv -- ^ The analysis environment -> DmdType -- ^ The demand type unleashed by the variable in this -- context. The returned DmdEnv includes the demand on -- this function plus demand on its free variables --- See Note [What are demand signatures?] in "GHC.Types.Demand" +-- See Note [DmdSig: demand signatures, and demand-sig arity] in "GHC.Types.Demand" dmdTransform env var sd -- Data constructors | Just con <- isDataConWorkId_maybe var @@ -1086,7 +1086,7 @@ dmdAnalRhsSig top_lvl rec_flag env let_sd id rhs (final_env, weak_fvs, final_id, final_rhs) where ww_arity = workWrapArity id rhs - -- See Note [WorkWrap arity and join points, point (1)] + -- See Note [Worker/wrapper arity and join points] point (1) body_sd | isJoinId id = let_sd | otherwise = topSubDmd ===================================== compiler/GHC/Types/Demand.hs ===================================== @@ -1041,8 +1041,8 @@ peelManyCalls k sd = go k C_11 sd calledOnceArity :: SubDemand -> Arity calledOnceArity sd = go 0 sd where - go n (viewCall -> Call C_11 sd) = go (n+1) sd - go n _ = n + go n (viewCall -> Just (C_11, sd)) = go (n+1) sd + go n _ = n -- | Extract the 'SubDemand' of a 'Demand'. -- PRECONDITION: The SubDemand must be used in a context where the expression @@ -2216,8 +2216,8 @@ being a newtype wrapper around DmdType, it actually encodes two things: Here comes the subtle part: The threshold is encoded in the demand-sig arity! So in mkDmdSigForArity we make sure to trim the list of argument demands to the given threshold arity. Call sites will make sure that this corresponds to the -arity of the call demand that elicited the wrapped demand type. See also Note -[What are demand signatures?]. +arity of the call demand that elicited the wrapped demand type. See also +Note [DmdSig: demand signatures, and demand-sig arity] -} -- | The depth of the wrapped 'DmdType' encodes the arity at which it is safe @@ -2379,7 +2379,7 @@ etaConvertDmdSig arity (DmdSig dmd_ty) -- whether it diverges. -- -- See Note [Understanding DmdType and DmdSig] --- and Note [What are demand signatures?]. +-- and Note [DmdSig: demand signatures, and demand-sig arity] type DmdTransformer = SubDemand -> DmdType -- | Extrapolate a demand signature ('DmdSig') into a 'DmdTransformer'. @@ -2390,7 +2390,7 @@ dmdTransformSig :: DmdSig -> DmdTransformer dmdTransformSig (DmdSig dmd_ty@(DmdType _ arg_ds)) sd = multDmdType (fst $ peelManyCalls (length arg_ds) sd) dmd_ty -- see Note [Demands from unsaturated function calls] - -- and Note [What are demand signatures?] + -- and Note [DmdSig: demand signatures, and demand-sig arity] -- | A special 'DmdTransformer' for data constructors that feeds product -- demands into the constructor arguments. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/631c09b57186e84e451cd8abb36db1f5d72c7ff6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/631c09b57186e84e451cd8abb36db1f5d72c7ff6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 15 02:20:31 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 14 Jun 2024 22:20:31 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: Add hack for #24623 Message-ID: <666cfa6f1acfe_27b70174dbe0281cb@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - 6b7ea284 by Sylvain Henry at 2024-06-14T22:20:15-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - 3bb45f05 by Rodrigo Mesquita at 2024-06-14T22:20:15-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - 30 changed files: - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Types/Name/Occurrence.hs - compiler/GHC/Types/Var/Env.hs - testsuite/tests/dependent/should_compile/T15743e.stderr - testsuite/tests/dependent/should_fail/T16326_Fail4.stderr - testsuite/tests/dependent/should_fail/T16326_Fail5.stderr - testsuite/tests/indexed-types/should_fail/T13877.stderr - testsuite/tests/indexed-types/should_fail/T14369.stderr - testsuite/tests/patsyn/should_fail/T15695.stderr - testsuite/tests/polykinds/T11520.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4048d490cf4c6e7d4d5e7cdc92f2b7d1c25477e1...3bb45f0523c4a8bde8639dd8bf694791afcc0d11 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4048d490cf4c6e7d4d5e7cdc92f2b7d1c25477e1...3bb45f0523c4a8bde8639dd8bf694791afcc0d11 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 15 06:57:05 2024 From: gitlab at gitlab.haskell.org (Peter Trommler (@trommler)) Date: Sat, 15 Jun 2024 02:57:05 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T23034 Message-ID: <666d3b415be44_3d5ad164d9c4302a@gitlab.mail> Peter Trommler pushed new branch wip/T23034 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T23034 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 15 07:20:53 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 15 Jun 2024 03:20:53 -0400 Subject: [Git][ghc/ghc][master] PPC: display foreign label in panic message (cf #23969) Message-ID: <666d40d5c4bbe_3d5ad5c4720480f9@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - 1 changed file: - compiler/GHC/CmmToAsm/PPC/Ppr.hs Changes: ===================================== compiler/GHC/CmmToAsm/PPC/Ppr.hs ===================================== @@ -587,7 +587,7 @@ pprInstr platform instr = case instr of JMP lbl _ -- We never jump to ForeignLabels; if we ever do, c.f. handling for "BL" - | isForeignLabel lbl -> panic "PPC.Ppr.pprInstr: JMP to ForeignLabel" + | isForeignLabel lbl -> pprPanic "PPC.Ppr.pprInstr: JMP to ForeignLabel" (pprDebugCLabel platform lbl) | otherwise -> line $ hcat [ -- an alias for b that takes a CLabel text "\tb\t", View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a59943803a3933e06efa11dc1c2f8c8ded8a4720 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a59943803a3933e06efa11dc1c2f8c8ded8a4720 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 15 07:21:36 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sat, 15 Jun 2024 03:21:36 -0400 Subject: [Git][ghc/ghc][master] cmm: Parse MO_BSwap primitive operation Message-ID: <666d410061847_3d5ad74db2851226@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - 1 changed file: - compiler/GHC/Cmm/Parser.y Changes: ===================================== compiler/GHC/Cmm/Parser.y ===================================== @@ -1151,6 +1151,7 @@ callishMachOps platform = listToUFM $ [ allWidths "popcnt" MO_PopCnt , allWidths "pdep" MO_Pdep , allWidths "pext" MO_Pext + , allWidths "bswap" MO_BSwap , allWidths "cmpxchg" MO_Cmpxchg , allWidths "xchg" MO_Xchg , allWidths "load_relaxed" (\w -> MO_AtomicRead w MemOrderAcquire) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bd95553a0912ad71a3ca4317c66764f014abf697 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bd95553a0912ad71a3ca4317c66764f014abf697 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 15 12:24:39 2024 From: gitlab at gitlab.haskell.org (Hannes Siebenhandl (@fendor)) Date: Sat, 15 Jun 2024 08:24:39 -0400 Subject: [Git][ghc/ghc][wip/fendor/ghc-iface-sharing-avoid-reserialisation] Avoid unneccessarily re-serialising the `ModIface` Message-ID: <666d88071644e_15cf782f279781243a6@gitlab.mail> Hannes Siebenhandl pushed to branch wip/fendor/ghc-iface-sharing-avoid-reserialisation at Glasgow Haskell Compiler / GHC Commits: f5f09617 by Fendor at 2024-06-15T14:23:02+02:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The test T16875 fails on i386-linux-debian10 for the same reason. - - - - - 15 changed files: - compiler/GHC.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -98,7 +98,35 @@ module GHC ( lookupGlobalName, findGlobalAnns, mkNamePprCtxForModule, - ModIface, ModIface_(..), + ModIface, + ModIface_( + mi_module, + mi_sig_of, + mi_hsc_src, + mi_src_hash, + mi_hi_bytes, + mi_deps, + mi_usages, + mi_exports, + mi_used_th, + mi_fixities, + mi_warns, + mi_anns, + mi_insts, + mi_fam_insts, + mi_rules, + mi_decls, + mi_extra_decls, + mi_top_env, + mi_hpc, + mi_trust, + mi_trust_pkg, + mi_complete_matches, + mi_docs, + mi_final_exts, + mi_ext_fields + ), + pattern ModIface, SafeHaskellMode(..), -- * Printing ===================================== compiler/GHC/Iface/Binary.hs ===================================== @@ -63,6 +63,8 @@ import Data.Map.Strict (Map) import Data.Word import System.IO.Unsafe import Data.Typeable (Typeable) +import qualified GHC.Data.Strict as Strict +import Data.Function ((&)) -- --------------------------------------------------------------------------- @@ -173,22 +175,27 @@ readBinIface profile name_cache checkHiWay traceBinIface hi_path = do mod_iface <- getIfaceWithExtFields name_cache bh - return mod_iface - { mi_src_hash = src_hash - } + return $ mod_iface + & addSourceFingerprint src_hash + getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface getIfaceWithExtFields name_cache bh = do - extFields_p <- get bh + -- Start offset for the byte array that contains the serialised 'ModIface'. + start <- tellBinReader bh + extFields_p_rel <- getRelBin bh mod_iface <- getWithUserData name_cache bh - seekBinReader bh extFields_p + seekBinReaderRel bh extFields_p_rel extFields <- get bh - pure mod_iface - { mi_ext_fields = extFields - } - + -- Store the 'ModIface' byte array, so that we can avoid serialisation if + -- the 'ModIface' isn't modified. + -- See Note [Sharing of ModIface] + modIfaceBinData <- freezeBinHandle bh start + pure $ mod_iface + & set_mi_ext_fields extFields + & set_mi_hi_bytes (FullIfaceBinHandle $ Strict.Just modIfaceBinData) -- | This performs a get action after reading the dictionary and symbol -- table. It is necessary to run this before trying to deserialise any @@ -218,7 +225,7 @@ getTables name_cache bh = do -- add it to the 'ReaderUserData' of 'ReadBinHandle'. decodeReaderTable :: Typeable a => ReaderTable a -> ReadBinHandle -> IO ReadBinHandle decodeReaderTable tbl bh0 = do - table <- Binary.forwardGet bh (getTable tbl bh0) + table <- Binary.forwardGetRel bh (getTable tbl bh0) let binaryReader = mkReaderFromTable tbl table pure $ addReaderToUserData binaryReader bh0 @@ -260,11 +267,18 @@ writeBinIface profile traceBinIface compressionLevel hi_path mod_iface = do -- And send the result to the file writeBinMem bh hi_path --- | Puts the 'ModIface' +-- | Puts the 'ModIface' to the 'WriteBinHandle'. +-- +-- This avoids serialisation of the 'ModIface' if the fields 'mi_hi_bytes' contains a +-- 'Just' value. This field is populated by reading the 'ModIface' using +-- 'getIfaceWithExtFields' and not modifying it in any way afterwards. putIfaceWithExtFields :: TraceBinIFace -> CompressionIFace -> WriteBinHandle -> ModIface -> IO () putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface = - forwardPut_ bh (\_ -> put_ bh (mi_ext_fields mod_iface)) $ do - putWithUserData traceBinIface compressionLevel bh mod_iface + case mi_hi_bytes mod_iface of + FullIfaceBinHandle Strict.Nothing -> do + forwardPutRel_ bh (\_ -> put_ bh (mi_ext_fields mod_iface)) $ do + putWithUserData traceBinIface compressionLevel bh mod_iface + FullIfaceBinHandle (Strict.Just binData) -> putFullBinData bh binData -- | Put a piece of data with an initialised `UserData` field. This -- is necessary if you want to serialise Names or FastStrings. @@ -339,7 +353,7 @@ putAllTables _ [] act = do a <- act pure ([], a) putAllTables bh (x : xs) act = do - (r, (res, a)) <- forwardPut bh (const $ putTable x bh) $ do + (r, (res, a)) <- forwardPutRel bh (const $ putTable x bh) $ do putAllTables bh xs act pure (r : res, a) @@ -491,7 +505,7 @@ to the table we need to deserialise first. What deduplication tables exist and the order of serialisation is currently statically specified in 'putWithTables'. 'putWithTables' also takes care of the serialisation of used deduplication tables. The deserialisation of the deduplication tables happens 'getTables', using 'Binary' utility -functions such as 'forwardGet'. +functions such as 'forwardGetRel'. Here, a visualisation of the table structure we currently have (ignoring 'ExtensibleFields'): @@ -592,7 +606,6 @@ initWriteIfaceType compressionLevel = do putGenericSymTab sym_tab bh ty _ -> putIfaceType bh ty - fullIfaceTypeSerialiser sym_tab bh ty = do put_ bh ifaceTypeSharedByte putGenericSymTab sym_tab bh ty ===================================== compiler/GHC/Iface/Ext/Binary.hs ===================================== @@ -228,7 +228,7 @@ readHieFileContents bh0 name_cache = do get bh1 where get_dictionary tbl bin_handle = do - fsTable <- Binary.forwardGet bin_handle (getTable tbl bin_handle) + fsTable <- Binary.forwardGetRel bin_handle (getTable tbl bin_handle) let fsReader = mkReaderFromTable tbl fsTable bhFs = addReaderToUserData fsReader bin_handle ===================================== compiler/GHC/Iface/Ext/Fields.hs ===================================== @@ -41,7 +41,7 @@ instance Binary ExtensibleFields where -- to point to the start of each payload: forM_ header_entries $ \(field_p_p, dat) -> do field_p <- tellBinWriter bh - putAt bh field_p_p field_p + putAtRel bh field_p_p field_p seekBinWriter bh field_p put_ bh dat @@ -50,11 +50,11 @@ instance Binary ExtensibleFields where -- Get the names and field pointers: header_entries <- replicateM n $ - (,) <$> get bh <*> get bh + (,) <$> get bh <*> getRelBin bh -- Seek to and get each field's payload: fields <- forM header_entries $ \(name, field_p) -> do - seekBinReader bh field_p + seekBinReaderRel bh field_p dat <- get bh return (name, dat) ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -117,6 +117,7 @@ import System.FilePath import System.Directory import GHC.Driver.Env.KnotVars import GHC.Iface.Errors.Types +import Data.Function ((&)) {- ************************************************************************ @@ -515,14 +516,12 @@ loadInterface doc_str mod from ; new_eps_anns <- tcIfaceAnnotations (mi_anns iface) ; new_eps_complete_matches <- tcIfaceCompleteMatches (mi_complete_matches iface) - ; let { final_iface = iface { - mi_decls = panic "No mi_decls in PIT", - mi_insts = panic "No mi_insts in PIT", - mi_fam_insts = panic "No mi_fam_insts in PIT", - mi_rules = panic "No mi_rules in PIT", - mi_anns = panic "No mi_anns in PIT" - } - } + ; let final_iface = iface + & set_mi_decls (panic "No mi_decls in PIT") + & set_mi_insts (panic "No mi_insts in PIT") + & set_mi_fam_insts (panic "No mi_fam_insts in PIT") + & set_mi_rules (panic "No mi_rules in PIT") + & set_mi_anns (panic "No mi_anns in PIT") ; let bad_boot = mi_boot iface == IsBoot && isJust (lookupKnotVars (if_rec_types gbl_env) mod) @@ -1018,13 +1017,13 @@ readIface dflags name_cache wanted_mod file_path = do -- See Note [GHC.Prim] in primops.txt.pp. ghcPrimIface :: ModIface ghcPrimIface - = empty_iface { - mi_exports = ghcPrimExports, - mi_decls = [], - mi_fixities = fixities, - mi_final_exts = (mi_final_exts empty_iface){ mi_fix_fn = mkIfaceFixCache fixities }, - mi_docs = Just ghcPrimDeclDocs -- See Note [GHC.Prim Docs] - } + = empty_iface + & set_mi_exports ghcPrimExports + & set_mi_decls [] + & set_mi_fixities fixities + & set_mi_final_exts ((mi_final_exts empty_iface){ mi_fix_fn = mkIfaceFixCache fixities }) + & set_mi_docs (Just ghcPrimDeclDocs) -- See Note [GHC.Prim Docs] + where empty_iface = emptyFullModIface gHC_PRIM @@ -1108,7 +1107,7 @@ pprModIfaceSimple unit_state iface = -- -- The UnitState is used to pretty-print units pprModIface :: UnitState -> ModIface -> SDoc -pprModIface unit_state iface at ModIface{ mi_final_exts = exts } +pprModIface unit_state iface = vcat [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) @@ -1149,6 +1148,7 @@ pprModIface unit_state iface at ModIface{ mi_final_exts = exts } , text "extensible fields:" $$ nest 2 (pprExtensibleFields (mi_ext_fields iface)) ] where + exts = mi_final_exts iface pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" pp_hsc_src HsSrcFile = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -145,7 +145,7 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos = do full_iface <- {-# SCC "addFingerprints" #-} - addFingerprints hsc_env partial_iface{ mi_decls = decls } + addFingerprints hsc_env (set_mi_decls decls partial_iface) -- Debug printing let unit_state = hsc_units hsc_env @@ -154,8 +154,24 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos = do final_iface <- shareIface (hsc_NC hsc_env) (flagsToIfCompression $ hsc_dflags hsc_env) full_iface return final_iface +-- | Compress an 'ModIface' and share as many values as possible, depending on the 'CompressionIFace' level. +-- See Note [Sharing of ModIface]. +-- +-- We compress the 'ModIface' by serialising the 'ModIface' to an in-memory byte array, and then deserialising it. +-- The deserialisation will deduplicate certain values depending on the 'CompressionIFace' level. +-- See Note [Deduplication during iface binary serialisation] for how we do that. +-- +-- Additionally, we cache the serialised byte array, so if the 'ModIface' is not modified +-- after calling 'shareIface', 'writeBinIface' will reuse that buffer without serialising the 'ModIface' again. +-- Modifying the 'ModIface' forces us to re-serialise it again. shareIface :: NameCache -> CompressionIFace -> ModIface -> IO ModIface -shareIface _ NormalCompression mi = pure mi +shareIface _ NormalCompression mi = do + -- In 'NormalCompression', the sharing isn't reducing the memory usage, as 'Name's and 'FastString's are + -- already shared, and at this compression level, we don't compress/share anything else. + -- Thus, for a brief moment we simply double the memory residency for no reason. + -- Therefore, we only try to share expensive values if the compression mode is higher than + -- 'NormalCompression' + pure mi shareIface nc compressionLevel mi = do bh <- openBinMem initBinMemSize start <- tellBinWriter bh @@ -163,10 +179,7 @@ shareIface nc compressionLevel mi = do rbh <- shrinkBinBuffer bh seekBinReader rbh start res <- getIfaceWithExtFields nc rbh - let resiface = res - { mi_src_hash = mi_src_hash mi - , mi_globals = mi_globals mi - } + let resiface = restoreFromOldModIface mi res forceModIface resiface return resiface @@ -327,40 +340,40 @@ mkIface_ hsc_env icomplete_matches = map mkIfaceCompleteMatch complete_matches !rdrs = maybeGlobalRdrEnv rdr_env - ModIface { - mi_module = this_mod, + emptyPartialModIface this_mod -- Need to record this because it depends on the -instantiated-with flag -- which could change - mi_sig_of = if semantic_mod == this_mod - then Nothing - else Just semantic_mod, - mi_hsc_src = hsc_src, - mi_deps = deps, - mi_usages = usages, - mi_exports = mkIfaceExports exports, + & set_mi_sig_of (if semantic_mod == this_mod + then Nothing + else Just semantic_mod) + & set_mi_hsc_src hsc_src + & set_mi_deps deps + & set_mi_usages usages + & set_mi_exports (mkIfaceExports exports) -- Sort these lexicographically, so that -- the result is stable across compilations - mi_insts = sortBy cmp_inst iface_insts, - mi_fam_insts = sortBy cmp_fam_inst iface_fam_insts, - mi_rules = sortBy cmp_rule iface_rules, - - mi_fixities = fixities, - mi_warns = warns, - mi_anns = annotations, - mi_top_env = rdrs, - mi_used_th = used_th, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_hpc = isHpcUsed hpc_info, - mi_trust = trust_info, - mi_trust_pkg = pkg_trust_req, - mi_complete_matches = icomplete_matches, - mi_docs = docs, - mi_final_exts = (), - mi_ext_fields = emptyExtensibleFields, - mi_src_hash = ms_hs_hash mod_summary - } + & set_mi_insts (sortBy cmp_inst iface_insts) + & set_mi_fam_insts (sortBy cmp_fam_inst iface_fam_insts) + & set_mi_rules (sortBy cmp_rule iface_rules) + + & set_mi_fixities fixities + & set_mi_warns warns + & set_mi_anns annotations + & set_mi_top_env rdrs + & set_mi_used_th used_th + & set_mi_decls decls + & set_mi_extra_decls extra_decls + & set_mi_hpc (isHpcUsed hpc_info) + & set_mi_trust trust_info + & set_mi_trust_pkg pkg_trust_req + & set_mi_complete_matches (icomplete_matches) + & set_mi_docs docs + & set_mi_final_exts () + & set_mi_ext_fields emptyExtensibleFields + & set_mi_src_hash (ms_hs_hash mod_summary) + & set_mi_hi_bytes PartialIfaceBinHandle + where cmp_rule = lexicalCompareFS `on` ifRuleName -- Compare these lexicographically by OccName, *not* by unique, @@ -536,3 +549,22 @@ That is, in Y, In the result of mkIfaceExports, the names are grouped by defining module, so we may need to split up a single Avail into multiple ones. -} + +{- +Note [Sharing of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +A 'ModIface' contains many duplicated values such as 'Name', 'FastString' and 'IfaceType'. +'Name's and 'FastString's are already deduplicated by default using the 'NameCache' and +'FastStringTable' respectively. +However, 'IfaceType' can be quite expensive in terms of memory usage. +To improve the sharing of 'IfaceType', we introduced deduplication tables during +serialisation of 'ModIface', see Note [Deduplication during iface binary serialisation]. + +We can improve the sharing of 'ModIface' at run-time as well, by serialising the 'ModIface' to +an in-memory buffer, and then deserialising it again. +This implicitly shares duplicated values. + +To avoid re-serialising the 'ModIface' when writing it to disk, we save the serialised 'ModIface' buffer +in 'mi_hi_bytes_' field of said 'ModIface'. This buffer is written to disk directly in 'putIfaceWithExtFields'. +If we have to modify the 'ModIface' after 'shareIface' is called, the buffer needs to be discarded. +-} ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -1281,7 +1281,8 @@ addFingerprints hsc_env iface0 , mi_fix_fn = fix_fn , mi_hash_fn = lookupOccEnv local_env } - final_iface = iface0 { mi_decls = sorted_decls, mi_extra_decls = sorted_extra_decls, mi_final_exts = final_iface_exts } + final_iface = completePartialModIface iface0 + sorted_decls sorted_extra_decls final_iface_exts -- return final_iface ===================================== compiler/GHC/Iface/Rename.hs ===================================== @@ -44,6 +44,7 @@ import GHC.Utils.Panic import qualified Data.Traversable as T import Data.IORef +import Data.Function ((&)) tcRnMsgMaybe :: IO (Either (Messages TcRnMessage) a) -> TcM a tcRnMsgMaybe do_this = do @@ -108,13 +109,14 @@ rnModIface hsc_env insts nsubst iface = deps <- rnDependencies (mi_deps iface) -- TODO: -- mi_rules - return iface { mi_module = mod - , mi_sig_of = sig_of - , mi_insts = insts - , mi_fam_insts = fams - , mi_exports = exports - , mi_decls = decls - , mi_deps = deps } + return $ iface + & set_mi_module mod + & set_mi_sig_of sig_of + & set_mi_insts insts + & set_mi_fam_insts fams + & set_mi_exports exports + & set_mi_decls decls + & set_mi_deps deps -- | Rename just the exports of a 'ModIface'. Useful when we're doing -- shaping prior to signature merging. ===================================== compiler/GHC/Tc/Errors/Hole.hs ===================================== @@ -76,7 +76,7 @@ import GHC.Tc.Utils.Unify ( tcSubTypeSigma ) import GHC.HsToCore.Docs ( extractDocs ) import GHC.Hs.Doc -import GHC.Unit.Module.ModIface ( ModIface_(..) ) +import GHC.Unit.Module.ModIface ( mi_docs ) import GHC.Iface.Load ( loadInterfaceForName ) import GHC.Builtin.Utils (knownKeyNames) ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -1562,7 +1562,8 @@ lookupDeclDoc nm = do -- Wasn't in the current module. Try searching other external ones! mIface <- getExternalModIface nm case mIface of - Just ModIface { mi_docs = Just Docs{docs_decls = dmap} } -> + Just iface + | Just Docs{docs_decls = dmap} <- mi_docs iface -> pure $ renderHsDocStrings . map hsDocString <$> lookupUniqMap dmap nm _ -> pure Nothing @@ -1578,7 +1579,8 @@ lookupArgDoc i nm = do Nothing -> do mIface <- getExternalModIface nm case mIface of - Just ModIface { mi_docs = Just Docs{docs_args = amap} } -> + Just iface + | Just Docs{docs_args = amap} <- mi_docs iface-> pure $ renderHsDocString . hsDocString <$> (lookupUniqMap amap nm >>= IntMap.lookup i) _ -> pure Nothing ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -87,6 +87,7 @@ import Control.Monad import Data.List (find) import GHC.Iface.Errors.Types +import Data.Function ((&)) checkHsigDeclM :: ModIface -> TyThing -> TyThing -> TcRn () checkHsigDeclM sig_iface sig_thing real_thing = do @@ -369,8 +370,8 @@ tcRnMergeSignatures hsc_env hpm orig_tcg_env iface = thinModIface :: [AvailInfo] -> ModIface -> ModIface thinModIface avails iface = - iface { - mi_exports = avails, + iface + & set_mi_exports avails -- mi_fixities = ..., -- mi_warns = ..., -- mi_anns = ..., @@ -378,10 +379,9 @@ thinModIface avails iface = -- perhaps there might be two IfaceTopBndr that are the same -- OccName but different Name. Requires better understanding -- of invariants here. - mi_decls = exported_decls ++ non_exported_decls ++ dfun_decls + & set_mi_decls (exported_decls ++ non_exported_decls ++ dfun_decls) -- mi_insts = ..., -- mi_fam_insts = ..., - } where decl_pred occs decl = nameOccName (ifName decl) `elemOccSet` occs filter_decls occs = filter (decl_pred occs . snd) (mi_decls iface) ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -4,10 +4,68 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE PatternSynonyms #-} + module GHC.Unit.Module.ModIface ( ModIface - , ModIface_ (..) + , ModIface_ + ( mi_module + , mi_sig_of + , mi_hsc_src + , mi_deps + , mi_usages + , mi_exports + , mi_used_th + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_extra_decls + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_hpc + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_final_exts + , mi_ext_fields + , mi_src_hash + , mi_hi_bytes + ) + , pattern ModIface + , restoreFromOldModIface + , addSourceFingerprint + , set_mi_module + , set_mi_sig_of + , set_mi_hsc_src + , set_mi_src_hash + , set_mi_hi_bytes + , set_mi_deps + , set_mi_usages + , set_mi_exports + , set_mi_used_th + , set_mi_fixities + , set_mi_warns + , set_mi_anns + , set_mi_insts + , set_mi_fam_insts + , set_mi_rules + , set_mi_decls + , set_mi_extra_decls + , set_mi_top_env + , set_mi_hpc + , set_mi_trust + , set_mi_trust_pkg + , set_mi_complete_matches + , set_mi_docs + , set_mi_final_exts + , set_mi_ext_fields + , completePartialModIface + , IfaceBinHandle(..) , PartialModIface , ModIfaceBackend (..) , IfaceDeclExts @@ -47,6 +105,7 @@ import GHC.Types.Fixity import GHC.Types.Fixity.Env import GHC.Types.HpcInfo import GHC.Types.Name +import GHC.Types.Name.Reader (IfGlobalRdrEnv) import GHC.Types.SafeHaskell import GHC.Types.SourceFile import GHC.Types.Unique.DSet @@ -59,7 +118,7 @@ import GHC.Utils.Binary import Control.DeepSeq import Control.Exception -import GHC.Types.Name.Reader (IfGlobalRdrEnv) +import qualified GHC.Data.Strict as Strict {- Note [Interface file stages] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -141,7 +200,17 @@ type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where IfaceBackendExts 'ModIfaceCore = () IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend - +-- | In-memory byte array representation of a 'ModIface'. +-- +-- See Note [Sharing of ModIface] for why we need this. +data IfaceBinHandle (phase :: ModIfacePhase) where + -- | A partial 'ModIface' cannot be serialised to disk. + PartialIfaceBinHandle :: IfaceBinHandle 'ModIfaceCore + -- | Optional 'FullBinData' that can be serialised to disk directly. + -- + -- See Note [Private fields in ModIface] for when this fields needs to be cleared + -- (e.g., set to 'Nothing'). + FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal -- | A 'ModIface' plus a 'ModDetails' summarises everything we know -- about a compiled module. The 'ModIface' is the stuff *before* linking, @@ -155,62 +224,65 @@ type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where -- -- See Note [Strictness in ModIface] to learn about why some fields are -- strict and others are not. +-- +-- See Note [Private fields in ModIface] to learn why we don't export any of the +-- fields. data ModIface_ (phase :: ModIfacePhase) - = ModIface { - mi_module :: !Module, -- ^ Name of the module we are for - mi_sig_of :: !(Maybe Module), -- ^ Are we a sig of another mod? + = PrivateModIface { + mi_module_ :: !Module, -- ^ Name of the module we are for + mi_sig_of_ :: !(Maybe Module), -- ^ Are we a sig of another mod? - mi_hsc_src :: !HscSource, -- ^ Boot? Signature? + mi_hsc_src_ :: !HscSource, -- ^ Boot? Signature? - mi_deps :: Dependencies, + mi_deps_ :: Dependencies, -- ^ The dependencies of the module. This is -- consulted for directly-imported modules, but not -- for anything else (hence lazy) - mi_usages :: [Usage], + mi_usages_ :: [Usage], -- ^ Usages; kept sorted so that it's easy to decide -- whether to write a new iface file (changing usages -- doesn't affect the hash of this module) -- NOT STRICT! we read this field lazily from the interface file -- It is *only* consulted by the recompilation checker - mi_exports :: ![IfaceExport], + mi_exports_ :: ![IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier -- Records the modules that are the declaration points for things -- exported by this module, and the 'OccName's of those things - mi_used_th :: !Bool, + mi_used_th_ :: !Bool, -- ^ Module required TH splices when it was compiled. -- This disables recompilation avoidance (see #481). - mi_fixities :: [(OccName,Fixity)], + mi_fixities_ :: [(OccName,Fixity)], -- ^ Fixities -- NOT STRICT! we read this field lazily from the interface file - mi_warns :: IfaceWarnings, + mi_warns_ :: IfaceWarnings, -- ^ Warnings -- NOT STRICT! we read this field lazily from the interface file - mi_anns :: [IfaceAnnotation], + mi_anns_ :: [IfaceAnnotation], -- ^ Annotations -- NOT STRICT! we read this field lazily from the interface file - mi_decls :: [IfaceDeclExts phase], + mi_decls_ :: [IfaceDeclExts phase], -- ^ Type, class and variable declarations -- The hash of an Id changes if its fixity or deprecations change -- (as well as its type of course) -- Ditto data constructors, class operations, except that -- the hash of the parent class/tycon changes - mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], + mi_extra_decls_ :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], -- ^ Extra variable definitions which are **NOT** exposed but when -- combined with mi_decls allows us to restart code generation. -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] - mi_top_env :: !(Maybe IfaceTopEnv), + mi_top_env_ :: !(Maybe IfaceTopEnv), -- ^ Just enough information to reconstruct the top level environment in -- the /original source/ code for this module. which -- is NOT the same as mi_exports, nor mi_decls (which @@ -226,36 +298,36 @@ data ModIface_ (phase :: ModIfacePhase) -- 'HomeModInfo', but that leads to more plumbing. -- Instance declarations and rules - mi_insts :: [IfaceClsInst], -- ^ Sorted class instance - mi_fam_insts :: [IfaceFamInst], -- ^ Sorted family instances - mi_rules :: [IfaceRule], -- ^ Sorted rules + mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance + mi_fam_insts_ :: [IfaceFamInst], -- ^ Sorted family instances + mi_rules_ :: [IfaceRule], -- ^ Sorted rules - mi_hpc :: !AnyHpcUsage, + mi_hpc_ :: !AnyHpcUsage, -- ^ True if this program uses Hpc at any point in the program. - mi_trust :: !IfaceTrustInfo, + mi_trust_ :: !IfaceTrustInfo, -- ^ Safe Haskell Trust information for this module. - mi_trust_pkg :: !Bool, + mi_trust_pkg_ :: !Bool, -- ^ Do we require the package this module resides in be trusted -- to trust this module? This is used for the situation where a -- module is Safe (so doesn't require the package be trusted -- itself) but imports some trustworthy modules from its own -- package (which does require its own package be trusted). -- See Note [Trust Own Package] in GHC.Rename.Names - mi_complete_matches :: ![IfaceCompleteMatch], + mi_complete_matches_ :: ![IfaceCompleteMatch], - mi_docs :: !(Maybe Docs), + mi_docs_ :: !(Maybe Docs), -- ^ Docstrings and related data for use by haddock, the ghci -- @:doc@ command, and other tools. -- -- @Just _@ @<=>@ the module was built with @-haddock at . - mi_final_exts :: !(IfaceBackendExts phase), + mi_final_exts_ :: !(IfaceBackendExts phase), -- ^ Either `()` or `ModIfaceBackend` for -- a fully instantiated interface. - mi_ext_fields :: !ExtensibleFields, + mi_ext_fields_ :: !ExtensibleFields, -- ^ Additional optional fields, where the Map key represents -- the field name, resulting in a (size, serialized data) pair. -- Because the data is intended to be serialized through the @@ -264,8 +336,13 @@ data ModIface_ (phase :: ModIfacePhase) -- chosen over `ByteString`s. -- - mi_src_hash :: !Fingerprint + mi_src_hash_ :: !Fingerprint, -- ^ Hash of the .hs source, used for recompilation checking. + mi_hi_bytes_ :: !(IfaceBinHandle phase) + -- ^ A serialised in-memory buffer of this 'ModIface'. + -- If this handle is given, we can avoid serialising the 'ModIface' + -- when writing this 'ModIface' to disk, and write this buffer to disk instead. + -- See Note [Sharing of ModIface]. } -- Enough information to reconstruct the top level environment for a module @@ -354,34 +431,40 @@ renameFreeHoles fhs insts = -- See Note [Strictness in ModIface] about where we use lazyPut vs put instance Binary ModIface where - put_ bh (ModIface { - mi_module = mod, - mi_sig_of = sig_of, - mi_hsc_src = hsc_src, - mi_src_hash = _src_hash, -- Don't `put_` this in the instance + put_ bh (PrivateModIface { + mi_module_ = mod, + mi_sig_of_ = sig_of, + mi_hsc_src_ = hsc_src, + mi_src_hash_ = _src_hash, -- Don't `put_` this in the instance -- because we are going to write it -- out separately in the actual file - mi_deps = deps, - mi_usages = usages, - mi_exports = exports, - mi_used_th = used_th, - mi_fixities = fixities, - mi_warns = warns, - mi_anns = anns, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_insts = insts, - mi_fam_insts = fam_insts, - mi_rules = rules, - mi_hpc = hpc_info, - mi_trust = trust, - mi_trust_pkg = trust_pkg, - mi_complete_matches = complete_matches, - mi_docs = docs, - mi_ext_fields = _ext_fields, -- Don't `put_` this in the instance so we + mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself + -- may contain an in-memory byte array buffer for this + -- 'ModIface'. If we used 'put_' on this 'ModIface', then + -- we likely have a good reason, and do not want to reuse + -- the byte array. + -- See Note [Private fields in ModIface] + mi_deps_ = deps, + mi_usages_ = usages, + mi_exports_ = exports, + mi_used_th_ = used_th, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_anns_ = anns, + mi_decls_ = decls, + mi_extra_decls_ = extra_decls, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_hpc_ = hpc_info, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, + mi_complete_matches_ = complete_matches, + mi_docs_ = docs, + mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file - mi_final_exts = ModIfaceBackend { + mi_final_exts_ = ModIfaceBackend { mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, mi_flag_hash = flag_hash, @@ -455,34 +538,39 @@ instance Binary ModIface where trust_pkg <- get bh complete_matches <- get bh docs <- lazyGetMaybe bh - return (ModIface { - mi_module = mod, - mi_sig_of = sig_of, - mi_hsc_src = hsc_src, - mi_src_hash = fingerprint0, -- placeholder because this is dealt + return (PrivateModIface { + mi_module_ = mod, + mi_sig_of_ = sig_of, + mi_hsc_src_ = hsc_src, + mi_src_hash_ = fingerprint0, -- placeholder because this is dealt -- with specially when the file is read - mi_deps = deps, - mi_usages = usages, - mi_exports = exports, - mi_used_th = used_th, - mi_anns = anns, - mi_fixities = fixities, - mi_warns = warns, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_top_env = Nothing, - mi_insts = insts, - mi_fam_insts = fam_insts, - mi_rules = rules, - mi_hpc = hpc_info, - mi_trust = trust, - mi_trust_pkg = trust_pkg, + mi_hi_bytes_ = + -- We can't populate this field here, as we are + -- missing the 'mi_ext_fields_' field, which is + -- handled in 'getIfaceWithExtFields'. + FullIfaceBinHandle Strict.Nothing, + mi_deps_ = deps, + mi_usages_ = usages, + mi_exports_ = exports, + mi_used_th_ = used_th, + mi_anns_ = anns, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_decls_ = decls, + mi_extra_decls_ = extra_decls, + mi_top_env_ = Nothing, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_hpc_ = hpc_info, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, -- And build the cached values - mi_complete_matches = complete_matches, - mi_docs = docs, - mi_ext_fields = emptyExtensibleFields, -- placeholder because this is dealt + mi_complete_matches_ = complete_matches, + mi_docs_ = docs, + mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read - mi_final_exts = ModIfaceBackend { + mi_final_exts_ = ModIfaceBackend { mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, mi_flag_hash = flag_hash, @@ -499,42 +587,46 @@ instance Binary ModIface where mi_hash_fn = mkIfaceHashCache decls }}) + -- | The original names declared of a certain module that are exported type IfaceExport = AvailInfo emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod - = ModIface { mi_module = mod, - mi_sig_of = Nothing, - mi_hsc_src = HsSrcFile, - mi_src_hash = fingerprint0, - mi_deps = noDependencies, - mi_usages = [], - mi_exports = [], - mi_used_th = False, - mi_fixities = [], - mi_warns = IfWarnSome [] [], - mi_anns = [], - mi_insts = [], - mi_fam_insts = [], - mi_rules = [], - mi_decls = [], - mi_extra_decls = Nothing, - mi_top_env = Nothing, - mi_hpc = False, - mi_trust = noIfaceTrustInfo, - mi_trust_pkg = False, - mi_complete_matches = [], - mi_docs = Nothing, - mi_final_exts = (), - mi_ext_fields = emptyExtensibleFields - } + = PrivateModIface + { mi_module_ = mod, + mi_sig_of_ = Nothing, + mi_hsc_src_ = HsSrcFile, + mi_src_hash_ = fingerprint0, + mi_hi_bytes_ = PartialIfaceBinHandle, + mi_deps_ = noDependencies, + mi_usages_ = [], + mi_exports_ = [], + mi_used_th_ = False, + mi_fixities_ = [], + mi_warns_ = IfWarnSome [] [], + mi_anns_ = [], + mi_insts_ = [], + mi_fam_insts_ = [], + mi_rules_ = [], + mi_decls_ = [], + mi_extra_decls_ = Nothing, + mi_top_env_ = Nothing, + mi_hpc_ = False, + mi_trust_ = noIfaceTrustInfo, + mi_trust_pkg_ = False, + mi_complete_matches_ = [], + mi_docs_ = Nothing, + mi_final_exts_ = (), + mi_ext_fields_ = emptyExtensibleFields + } emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) - { mi_decls = [] - , mi_final_exts = ModIfaceBackend + { mi_decls_ = [] + , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + , mi_final_exts_ = ModIfaceBackend { mi_iface_hash = fingerprint0, mi_mod_hash = fingerprint0, mi_flag_hash = fingerprint0, @@ -569,36 +661,38 @@ emptyIfaceHashCache _occ = Nothing instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (ModIface{ mi_module, mi_sig_of, mi_hsc_src, mi_deps, mi_usages - , mi_exports, mi_used_th, mi_fixities, mi_warns, mi_anns - , mi_decls, mi_extra_decls, mi_top_env, mi_insts - , mi_fam_insts, mi_rules, mi_hpc, mi_trust, mi_trust_pkg - , mi_complete_matches, mi_docs, mi_final_exts - , mi_ext_fields, mi_src_hash }) - = rnf mi_module - `seq` rnf mi_sig_of - `seq` mi_hsc_src - `seq` mi_deps - `seq` mi_usages - `seq` mi_exports - `seq` rnf mi_used_th - `seq` mi_fixities - `seq` rnf mi_warns - `seq` rnf mi_anns - `seq` rnf mi_decls - `seq` rnf mi_extra_decls - `seq` rnf mi_top_env - `seq` rnf mi_insts - `seq` rnf mi_fam_insts - `seq` rnf mi_rules - `seq` rnf mi_hpc - `seq` mi_trust - `seq` rnf mi_trust_pkg - `seq` rnf mi_complete_matches - `seq` rnf mi_docs - `seq` mi_final_exts - `seq` mi_ext_fields - `seq` rnf mi_src_hash + rnf (PrivateModIface + { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_, mi_usages_ + , mi_exports_, mi_used_th_, mi_fixities_, mi_warns_, mi_anns_ + , mi_decls_, mi_extra_decls_, mi_top_env_, mi_insts_ + , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_ + , mi_complete_matches_, mi_docs_, mi_final_exts_ + , mi_ext_fields_, mi_src_hash_ }) + = rnf mi_module_ + `seq` rnf mi_sig_of_ + `seq` mi_hsc_src_ + `seq` mi_hi_bytes_ + `seq` mi_deps_ + `seq` mi_usages_ + `seq` mi_exports_ + `seq` rnf mi_used_th_ + `seq` mi_fixities_ + `seq` rnf mi_warns_ + `seq` rnf mi_anns_ + `seq` rnf mi_decls_ + `seq` rnf mi_extra_decls_ + `seq` rnf mi_top_env_ + `seq` rnf mi_insts_ + `seq` rnf mi_fam_insts_ + `seq` rnf mi_rules_ + `seq` rnf mi_hpc_ + `seq` mi_trust_ + `seq` rnf mi_trust_pkg_ + `seq` rnf mi_complete_matches_ + `seq` rnf mi_docs_ + `seq` mi_final_exts_ + `seq` mi_ext_fields_ + `seq` rnf mi_src_hash_ `seq` () instance NFData (ModIfaceBackend) where @@ -638,5 +732,286 @@ type WhetherHasOrphans = Bool -- | Does this module define family instances? type WhetherHasFamInst = Bool +-- ---------------------------------------------------------------------------- +-- Modify a 'ModIface'. +-- ---------------------------------------------------------------------------- + +{- +Note [Private fields in ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The fields of 'ModIface' are private, e.g., not exported, to make the API +impossible to misuse. A 'ModIface' can be "compressed" in-memory using +'shareIface', which serialises the 'ModIface' to an in-memory buffer. +This has the advantage of reducing memory usage of 'ModIface', reducing the +overall memory usage of GHC. +See Note [Sharing of ModIface]. + +This in-memory buffer can be reused, if and only if the 'ModIface' is not +modified after it has been "compressed"/shared via 'shareIface'. Instead of +serialising 'ModIface', we simply write the in-memory buffer to disk directly. + +However, we can't rely that a 'ModIface' isn't modified after 'shareIface' has +been called. Thus, we make all fields of 'ModIface' private and modification +only happens via exported update functions, such as 'set_mi_decls'. +These functions unconditionally clear any in-memory buffer if used, forcing us +to serialise the 'ModIface' to disk again. +-} + +-- | Given a 'PartialModIface', turn it into a 'ModIface' by completing +-- missing fields. +completePartialModIface :: PartialModIface + -> [(Fingerprint, IfaceDecl)] + -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] + -> ModIfaceBackend + -> ModIface +completePartialModIface partial decls extra_decls final_exts = partial + { mi_decls_ = decls + , mi_extra_decls_ = extra_decls + , mi_final_exts_ = final_exts + , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + } + +-- | Add a source fingerprint to a 'ModIface_' without invalidating the byte array +-- buffer 'mi_hi_bytes'. +-- This is a variant of 'set_mi_src_hash' which does invalidate the buffer. +-- +-- The 'mi_src_hash' is computed outside of 'ModIface_' based on the 'ModSummary'. +addSourceFingerprint :: Fingerprint -> ModIface_ phase -> ModIface_ phase +addSourceFingerprint val iface = iface { mi_src_hash_ = val } + +-- | Copy fields that aren't serialised to disk to the new 'ModIface_'. +-- This includes especially hashes that are usually stored in the interface +-- file header and 'mi_top_env'. +-- +-- We need this function after calling 'shareIface', to make sure the +-- 'ModIface_' doesn't lose any information. This function does not discard +-- the in-memory byte array buffer 'mi_hi_bytes'. +restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase +restoreFromOldModIface old new = new + { mi_top_env_ = mi_top_env_ old + , mi_hsc_src_ = mi_hsc_src_ old + , mi_src_hash_ = mi_src_hash_ old + } + +set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase +set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } + +set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase +set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } + +set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase +set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } + +set_mi_src_hash :: Fingerprint -> ModIface_ phase -> ModIface_ phase +set_mi_src_hash val iface = clear_mi_hi_bytes $ iface { mi_src_hash_ = val } + +set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase +set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } + +set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase +set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } + +set_mi_usages :: [Usage] -> ModIface_ phase -> ModIface_ phase +set_mi_usages val iface = clear_mi_hi_bytes $ iface { mi_usages_ = val } +set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase +set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } + +set_mi_used_th :: Bool -> ModIface_ phase -> ModIface_ phase +set_mi_used_th val iface = clear_mi_hi_bytes $ iface { mi_used_th_ = val } + +set_mi_fixities :: [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase +set_mi_fixities val iface = clear_mi_hi_bytes $ iface { mi_fixities_ = val } + +set_mi_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase +set_mi_warns val iface = clear_mi_hi_bytes $ iface { mi_warns_ = val } + +set_mi_anns :: [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase +set_mi_anns val iface = clear_mi_hi_bytes $ iface { mi_anns_ = val } + +set_mi_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase +set_mi_insts val iface = clear_mi_hi_bytes $ iface { mi_insts_ = val } + +set_mi_fam_insts :: [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase +set_mi_fam_insts val iface = clear_mi_hi_bytes $ iface { mi_fam_insts_ = val } + +set_mi_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase +set_mi_rules val iface = clear_mi_hi_bytes $ iface { mi_rules_ = val } + +set_mi_decls :: [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase +set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls_ = val } + +set_mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase +set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val } + +set_mi_top_env :: Maybe IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } + +set_mi_hpc :: AnyHpcUsage -> ModIface_ phase -> ModIface_ phase +set_mi_hpc val iface = clear_mi_hi_bytes $ iface { mi_hpc_ = val } + +set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase +set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val } + +set_mi_trust_pkg :: Bool -> ModIface_ phase -> ModIface_ phase +set_mi_trust_pkg val iface = clear_mi_hi_bytes $ iface { mi_trust_pkg_ = val } + +set_mi_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase +set_mi_complete_matches val iface = clear_mi_hi_bytes $ iface { mi_complete_matches_ = val } + +set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase +set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } + +set_mi_final_exts :: IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase +set_mi_final_exts val iface = clear_mi_hi_bytes $ iface { mi_final_exts_ = val } + +set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase +set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } + +-- | Invalidate any byte array buffer we might have. +clear_mi_hi_bytes :: ModIface_ phase -> ModIface_ phase +clear_mi_hi_bytes iface = iface + { mi_hi_bytes_ = case mi_hi_bytes iface of + PartialIfaceBinHandle -> PartialIfaceBinHandle + FullIfaceBinHandle _ -> FullIfaceBinHandle Strict.Nothing + } + +-- ---------------------------------------------------------------------------- +-- 'ModIface' pattern synonyms to keep breakage low. +-- ---------------------------------------------------------------------------- + +{- +Note [Inline Pattern synonym of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The introduction of the 'ModIface' pattern synonym originally caused an increase +in allocated bytes in multiple performance tests. +In some benchmarks, it was a 2~3% increase. + +Without {-# INLINE ModIface #-}, the generated core reveals the reason for this increase. +We show the core for the 'mi_module' record selector: + +@ + mi_module + = \ @phase iface -> $w$mModIface iface mi_module1 + + $w$mModIface + = \ @phase iface cont -> + case iface of + { PrivateModIface a b ... z -> + cont + a + b + ... + z + } + + mi_module1 + = \ @phase + a + _ + ... + _ -> + a +@ + +Thus, we can see the '$w$mModIface' is not inlined, leading to an increase in +the allocated bytes. + +However, with the pragma, the correct core is generated: + +@ + mi_module = mi_module_ +@ + +-} +-- See Note [Inline Pattern synonym of ModIface] for why we have all these +-- inline pragmas. +{-# INLINE ModIface #-} +{-# INLINE mi_module #-} +{-# INLINE mi_sig_of #-} +{-# INLINE mi_hsc_src #-} +{-# INLINE mi_deps #-} +{-# INLINE mi_usages #-} +{-# INLINE mi_exports #-} +{-# INLINE mi_used_th #-} +{-# INLINE mi_fixities #-} +{-# INLINE mi_warns #-} +{-# INLINE mi_anns #-} +{-# INLINE mi_decls #-} +{-# INLINE mi_extra_decls #-} +{-# INLINE mi_top_env #-} +{-# INLINE mi_insts #-} +{-# INLINE mi_fam_insts #-} +{-# INLINE mi_rules #-} +{-# INLINE mi_hpc #-} +{-# INLINE mi_trust #-} +{-# INLINE mi_trust_pkg #-} +{-# INLINE mi_complete_matches #-} +{-# INLINE mi_docs #-} +{-# INLINE mi_final_exts #-} +{-# INLINE mi_ext_fields #-} +{-# INLINE mi_src_hash #-} +{-# INLINE mi_hi_bytes #-} + +pattern ModIface :: + Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] -> + [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> + [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> + Maybe IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> + AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> + IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> + ModIface_ phase +pattern ModIface + { mi_module + , mi_sig_of + , mi_hsc_src + , mi_deps + , mi_usages + , mi_exports + , mi_used_th + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_extra_decls + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_hpc + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_final_exts + , mi_ext_fields + , mi_src_hash + , mi_hi_bytes + } <- PrivateModIface + { mi_module_ = mi_module + , mi_sig_of_ = mi_sig_of + , mi_hsc_src_ = mi_hsc_src + , mi_deps_ = mi_deps + , mi_usages_ = mi_usages + , mi_exports_ = mi_exports + , mi_used_th_ = mi_used_th + , mi_fixities_ = mi_fixities + , mi_warns_ = mi_warns + , mi_anns_ = mi_anns + , mi_decls_ = mi_decls + , mi_extra_decls_ = mi_extra_decls + , mi_top_env_ = mi_top_env + , mi_insts_ = mi_insts + , mi_fam_insts_ = mi_fam_insts + , mi_rules_ = mi_rules + , mi_hpc_ = mi_hpc + , mi_trust_ = mi_trust + , mi_trust_pkg_ = mi_trust_pkg + , mi_complete_matches_ = mi_complete_matches + , mi_docs_ = mi_docs + , mi_final_exts_ = mi_final_exts + , mi_ext_fields_ = mi_ext_fields + , mi_src_hash_ = mi_src_hash + , mi_hi_bytes_ = mi_hi_bytes + } ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -19,7 +19,7 @@ -- http://www.cs.york.ac.uk/fp/nhc98/ module GHC.Utils.Binary - ( {-type-} Bin, + ( {-type-} Bin, RelBin(..), getRelBin, {-class-} Binary(..), {-type-} ReadBinHandle, WriteBinHandle, SymbolTable, Dictionary, @@ -32,6 +32,7 @@ module GHC.Utils.Binary seekBinWriter, seekBinReader, + seekBinReaderRel, tellBinReader, tellBinWriter, castBin, @@ -47,7 +48,9 @@ module GHC.Utils.Binary readBinMemN, putAt, getAt, + putAtRel, forwardPut, forwardPut_, forwardGet, + forwardPutRel, forwardPutRel_, forwardGetRel, -- * For writing instances putByte, @@ -102,6 +105,8 @@ module GHC.Utils.Binary BindingName(..), simpleBindingNameWriter, simpleBindingNameReader, + FullBinData(..), freezeBinHandle, thawBinHandle, putFullBinData, + BinArray, ) where import GHC.Prelude @@ -119,7 +124,6 @@ import GHC.Types.SrcLoc import GHC.Types.Unique import qualified GHC.Data.Strict as Strict import GHC.Utils.Outputable( JoinPointHood(..) ) -import GHC.Utils.Misc ( HasCallStack, HasDebugCallStack ) import Control.DeepSeq import Control.Monad ( when, (<$!>), unless, forM_, void ) @@ -195,6 +199,62 @@ dataHandle (BinData size bin) = do handleData :: WriteBinHandle -> IO BinData handleData (WriteBinMem _ ixr _ binr) = BinData <$> readFastMutInt ixr <*> readIORef binr +--------------------------------------------------------------- +-- FullBinData +--------------------------------------------------------------- + +-- | 'FullBinData' stores a slice to a 'BinArray'. +-- +-- It requires less memory than 'ReadBinHandle', and can be constructed from +-- a 'ReadBinHandle' via 'freezeBinHandle' and turned back into a +-- 'ReadBinHandle' using 'thawBinHandle'. +-- Additionally, the byte array slice can be put into a 'WriteBinHandle' without extra +-- conversions via 'putFullBinData'. +data FullBinData = FullBinData + { fbd_readerUserData :: ReaderUserData + -- ^ 'ReaderUserData' that can be used to resume reading. + , fbd_off_s :: {-# UNPACK #-} !Int + -- ^ start offset + , fbd_off_e :: {-# UNPACK #-} !Int + -- ^ end offset + , fbd_size :: {-# UNPACK #-} !Int + -- ^ total buffer size + , fbd_buffer :: {-# UNPACK #-} !BinArray + } + +-- Equality and Ord assume that two distinct buffers are different, even if they compare the same things. +instance Eq FullBinData where + (FullBinData _ b c d e) == (FullBinData _ b1 c1 d1 e1) = b == b1 && c == c1 && d == d1 && e == e1 + +instance Ord FullBinData where + compare (FullBinData _ b c d e) (FullBinData _ b1 c1 d1 e1) = + compare b b1 `mappend` compare c c1 `mappend` compare d d1 `mappend` compare e e1 + +-- | Write the 'FullBinData' slice into the 'WriteBinHandle'. +putFullBinData :: WriteBinHandle -> FullBinData -> IO () +putFullBinData bh (FullBinData _ o1 o2 _sz ba) = do + let sz = o2 - o1 + putPrim bh sz $ \dest -> + unsafeWithForeignPtr (ba `plusForeignPtr` o1) $ \orig -> + copyBytes dest orig sz + +-- | Freeze a 'ReadBinHandle' and a start index into a 'FullBinData'. +-- +-- 'FullBinData' stores a slice starting from the 'Bin a' location to the current +-- offset of the 'ReadBinHandle'. +freezeBinHandle :: ReadBinHandle -> Bin a -> IO FullBinData +freezeBinHandle (ReadBinMem user_data ixr sz binr) (BinPtr start) = do + ix <- readFastMutInt ixr + pure (FullBinData user_data start ix sz binr) + +-- | Turn the 'FullBinData' into a 'ReadBinHandle', setting the 'ReadBinHandle' +-- offset to the start of the 'FullBinData' and restore the 'ReaderUserData' that was +-- obtained from 'freezeBinHandle'. +thawBinHandle :: FullBinData -> IO ReadBinHandle +thawBinHandle (FullBinData user_data ix _end sz ba) = do + ixr <- newFastMutInt ix + return $ ReadBinMem user_data ixr sz ba + --------------------------------------------------------------- -- BinHandle --------------------------------------------------------------- @@ -288,9 +348,47 @@ unsafeUnpackBinBuffer (BS.BS arr len) = do newtype Bin a = BinPtr Int deriving (Eq, Ord, Show, Bounded) +-- | Like a 'Bin' but is used to store relative offset pointers. +-- Relative offset pointers store a relative location, but also contain an +-- anchor that allow to obtain the absolute offset. +data RelBin a = RelBin + { relBin_anchor :: {-# UNPACK #-} !(Bin a) + -- ^ Absolute position from where we read 'relBin_offset'. + , relBin_offset :: {-# UNPACK #-} !(RelBinPtr a) + -- ^ Relative offset to 'relBin_anchor'. + -- The absolute position of the 'RelBin' is @relBin_anchor + relBin_offset@ + } + deriving (Eq, Ord, Show, Bounded) + +-- | A 'RelBinPtr' is like a 'Bin', but contains a relative offset pointer +-- instead of an absolute offset. +newtype RelBinPtr a = RelBinPtr (Bin a) + deriving (Eq, Ord, Show, Bounded) + castBin :: Bin a -> Bin b castBin (BinPtr i) = BinPtr i +-- | Read a relative offset location and wrap it in 'RelBin'. +-- +-- The resulting 'RelBin' can be translated into an absolute offset location using +-- 'makeAbsoluteBin' +getRelBin :: ReadBinHandle -> IO (RelBin a) +getRelBin bh = do + start <- tellBinReader bh + off <- get bh + pure $ RelBin start off + +makeAbsoluteBin :: RelBin a -> Bin a +makeAbsoluteBin (RelBin (BinPtr !start) (RelBinPtr (BinPtr !offset))) = + BinPtr $ start + offset + +makeRelativeBin :: RelBin a -> RelBinPtr a +makeRelativeBin (RelBin _ offset) = offset + +toRelBin :: Bin (RelBinPtr a) -> Bin a -> RelBin a +toRelBin (BinPtr !start) (BinPtr !goal) = + RelBin (BinPtr start) (RelBinPtr $ BinPtr $ goal - start) + --------------------------------------------------------------- -- class Binary --------------------------------------------------------------- @@ -311,6 +409,9 @@ class Binary a where putAt :: Binary a => WriteBinHandle -> Bin a -> a -> IO () putAt bh p x = do seekBinWriter bh p; put_ bh x; return () +putAtRel :: WriteBinHandle -> Bin (RelBinPtr a) -> Bin a -> IO () +putAtRel bh from to = putAt bh from (makeRelativeBin $ toRelBin from to) + getAt :: Binary a => ReadBinHandle -> Bin a -> IO a getAt bh p = do seekBinReader bh p; get bh @@ -344,7 +445,7 @@ freezeWriteHandle wbm = do , rbm_arr_r = rbm_arr_r } --- Copy the BinBuffer to a new BinBuffer which is exactly the right size. +-- | Copy the BinBuffer to a new BinBuffer which is exactly the right size. -- This performs a copy of the underlying buffer. -- The buffer may be truncated if the offset is not at the end of the written -- output. @@ -398,6 +499,13 @@ seekBinReader (ReadBinMem _ ix_r sz_r _) (BinPtr !p) = do then panic "seekBinReader: seek out of range" else writeFastMutInt ix_r p +seekBinReaderRel :: ReadBinHandle -> RelBin a -> IO () +seekBinReaderRel (ReadBinMem _ ix_r sz_r _) relBin = do + let (BinPtr !p) = makeAbsoluteBin relBin + if (p > sz_r) + then panic "seekBinReaderRel: seek out of range" + else writeFastMutInt ix_r p + writeBinMem :: WriteBinHandle -> FilePath -> IO () writeBinMem (WriteBinMem _ ix_r _ arr_r) fn = do h <- openBinaryFile fn WriteMode @@ -1118,12 +1226,17 @@ instance Binary (Bin a) where put_ bh (BinPtr i) = putWord32 bh (fromIntegral i :: Word32) get bh = do i <- getWord32 bh; return (BinPtr (fromIntegral (i :: Word32))) +-- Instance uses fixed-width encoding to allow inserting +-- Bin placeholders in the stream. +instance Binary (RelBinPtr a) where + put_ bh (RelBinPtr i) = put_ bh i + get bh = RelBinPtr <$> get bh -- ----------------------------------------------------------------------------- -- Forward reading/writing --- | "forwardPut put_A put_B" outputs A after B but allows A to be read before B --- by using a forward reference +-- | @'forwardPut' put_A put_B@ outputs A after B but allows A to be read before B +-- by using a forward reference. forwardPut :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a,b) forwardPut bh put_A put_B = do -- write placeholder pointer to A @@ -1146,6 +1259,8 @@ forwardPut_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () forwardPut_ bh put_A put_B = void $ forwardPut bh put_A put_B -- | Read a value stored using a forward reference +-- +-- The forward reference is expected to be an absolute offset. forwardGet :: ReadBinHandle -> IO a -> IO a forwardGet bh get_A = do -- read forward reference @@ -1158,6 +1273,48 @@ forwardGet bh get_A = do seekBinReader bh p_a pure r +-- | @'forwardPutRel' put_A put_B@ outputs A after B but allows A to be read before B +-- by using a forward reference. +-- +-- This forward reference is a relative offset that allows us to skip over the +-- result of 'put_A'. +forwardPutRel :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a,b) +forwardPutRel bh put_A put_B = do + -- write placeholder pointer to A + pre_a <- tellBinWriter bh + put_ bh pre_a + + -- write B + r_b <- put_B + + -- update A's pointer + a <- tellBinWriter bh + putAtRel bh pre_a a + seekBinNoExpandWriter bh a + + -- write A + r_a <- put_A r_b + pure (r_a,r_b) + +-- | Like 'forwardGetRel', but discard the result. +forwardPutRel_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () +forwardPutRel_ bh put_A put_B = void $ forwardPutRel bh put_A put_B + +-- | Read a value stored using a forward reference. +-- +-- The forward reference is expected to be a relative offset. +forwardGetRel :: ReadBinHandle -> IO a -> IO a +forwardGetRel bh get_A = do + -- read forward reference + p <- getRelBin bh + -- store current position + p_a <- tellBinReader bh + -- go read the forward value, then seek back + seekBinReader bh $ makeAbsoluteBin p + r <- get_A + seekBinReader bh p_a + pure r + -- ----------------------------------------------------------------------------- -- Lazy reading/writing @@ -1167,19 +1324,19 @@ lazyPut = lazyPut' put_ lazyGet :: Binary a => ReadBinHandle -> IO a lazyGet = lazyGet' get -lazyPut' :: HasDebugCallStack => (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO () +lazyPut' :: (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO () lazyPut' f bh a = do -- output the obj with a ptr to skip over it: pre_a <- tellBinWriter bh put_ bh pre_a -- save a slot for the ptr f bh a -- dump the object q <- tellBinWriter bh -- q = ptr to after object - putAt bh pre_a q -- fill in slot before a with ptr to q + putAtRel bh pre_a q -- fill in slot before a with ptr to q seekBinWriter bh q -- finally carry on writing at q -lazyGet' :: HasDebugCallStack => (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a +lazyGet' :: (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a lazyGet' f bh = do - p <- get bh -- a BinPtr + p <- getRelBin bh -- a BinPtr p_a <- tellBinReader bh a <- unsafeInterleaveIO $ do -- NB: Use a fresh rbm_off_r variable in the child thread, for thread @@ -1188,7 +1345,7 @@ lazyGet' f bh = do let bh' = bh { rbm_off_r = off_r } seekBinReader bh' p_a f bh' - seekBinReader bh p -- skip over the object for now + seekBinReader bh (makeAbsoluteBin p) -- skip over the object for now return a -- | Serialize the constructor strictly but lazily serialize a value inside a @@ -1324,7 +1481,7 @@ mkReader f = BinaryReader -- | Find the 'BinaryReader' for the 'Binary' instance for the type identified by 'Proxy a'. -- -- If no 'BinaryReader' has been configured before, this function will panic. -findUserDataReader :: forall a . (HasCallStack, Refl.Typeable a) => Proxy a -> ReadBinHandle -> BinaryReader a +findUserDataReader :: forall a . Refl.Typeable a => Proxy a -> ReadBinHandle -> BinaryReader a findUserDataReader query bh = case Map.lookup (Refl.someTypeRep query) (ud_reader_data $ getReaderUserData bh) of Nothing -> panic $ "Failed to find BinaryReader for the key: " ++ show (Refl.someTypeRep query) @@ -1346,7 +1503,7 @@ findUserDataReader query bh = -- | Find the 'BinaryWriter' for the 'Binary' instance for the type identified by 'Proxy a'. -- -- If no 'BinaryWriter' has been configured before, this function will panic. -findUserDataWriter :: forall a . (HasCallStack, Refl.Typeable a) => Proxy a -> WriteBinHandle -> BinaryWriter a +findUserDataWriter :: forall a . Refl.Typeable a => Proxy a -> WriteBinHandle -> BinaryWriter a findUserDataWriter query bh = case Map.lookup (Refl.someTypeRep query) (ud_writer_data $ getWriterUserData bh) of Nothing -> panic $ "Failed to find BinaryWriter for the key: " ++ show (Refl.someTypeRep query) @@ -1482,13 +1639,13 @@ putGenericSymbolTable gen_sym_tab serialiser bh = do mapM_ (\n -> serialiser bh n) (reverse todo) loop snd <$> - (forwardPut bh (const $ readFastMutInt symtab_next >>= put_ bh) $ + (forwardPutRel bh (const $ readFastMutInt symtab_next >>= put_ bh) $ loop) -- | Read the elements of a 'GenericSymbolTable' from disk into a 'SymbolTable'. getGenericSymbolTable :: forall a . (ReadBinHandle -> IO a) -> ReadBinHandle -> IO (SymbolTable a) getGenericSymbolTable deserialiser bh = do - sz <- forwardGet bh (get bh) :: IO Int + sz <- forwardGetRel bh (get bh) :: IO Int mut_arr <- newArray_ (0, sz-1) :: IO (IOArray Int a) forM_ [0..(sz-1)] $ \i -> do f <- deserialiser bh ===================================== testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs ===================================== @@ -64,9 +64,10 @@ metaPlugin' _ meta = pprPanic "meta" (showAstData BlankSrcSpan BlankEpAnnotation interfaceLoadPlugin' :: [CommandLineOption] -> ModIface -> IfM lcl ModIface interfaceLoadPlugin' [name, "interface"] iface - = return $ iface { mi_exports = filter (availNotNamedAs name) - (mi_exports iface) - } + = return $ set_mi_exports (filter (availNotNamedAs name) + (mi_exports iface)) + iface + interfaceLoadPlugin' _ iface = return iface availNotNamedAs :: String -> AvailInfo -> Bool ===================================== utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs ===================================== @@ -56,7 +56,7 @@ import GHC.Types.Unique.FM import GHC.Unit.State import GHC.Utils.Binary -import GHC.Iface.Type (IfaceType, getIfaceType, putIfaceType) +import GHC.Iface.Type (IfaceType, putIfaceType) import Haddock.Options (Visibility (..)) @@ -200,7 +200,7 @@ writeInterfaceFile filename iface = do -- write the iface type pointer at the front of the file ifacetype_p <- tellBinWriter bh - putAt bh ifacetype_p_p ifacetype_p + putAtRel bh ifacetype_p_p ifacetype_p seekBinWriter bh ifacetype_p -- write the symbol table itself @@ -208,7 +208,7 @@ writeInterfaceFile filename iface = do -- write the symtab pointer at the front of the file symtab_p <- tellBinWriter bh - putAt bh symtab_p_p symtab_p + putAtRel bh symtab_p_p symtab_p seekBinWriter bh symtab_p -- write the symbol table itself @@ -218,7 +218,7 @@ writeInterfaceFile filename iface = do -- write the dictionary pointer at the fornt of the file dict_p <- tellBinWriter bh - putAt bh dict_p_p dict_p + putAtRel bh dict_p_p dict_p seekBinWriter bh dict_p -- write the dictionary itself View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f5f0961718fc023c2f293aab56cd1f3c927c4455 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f5f0961718fc023c2f293aab56cd1f3c927c4455 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 15 12:24:54 2024 From: gitlab at gitlab.haskell.org (Hannes Siebenhandl (@fendor)) Date: Sat, 15 Jun 2024 08:24:54 -0400 Subject: [Git][ghc/ghc][wip/fendor/ghc-iface-sharing-avoid-reserialisation] 25 commits: Fix a QuickLook bug Message-ID: <666d8816b4f70_15cf782f381d81249ba@gitlab.mail> Hannes Siebenhandl pushed to branch wip/fendor/ghc-iface-sharing-avoid-reserialisation at Glasgow Haskell Compiler / GHC Commits: 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - fca4b83b by Fendor at 2024-06-15T14:24:32+02:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 146d298e by Fendor at 2024-06-15T14:24:32+02:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The test T16875 fails on i386-linux-debian10 for the same reason. - - - - - 30 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f5f0961718fc023c2f293aab56cd1f3c927c4455...146d298ecaa3b343b35b2a56713d1b022ce77728 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f5f0961718fc023c2f293aab56cd1f3c927c4455...146d298ecaa3b343b35b2a56713d1b022ce77728 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 15 15:33:18 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Sat, 15 Jun 2024 11:33:18 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] 58 commits: Fix a QuickLook bug Message-ID: <666db43eec0be_15cf7849f06c41371ef@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - 15dc097c by sheaf at 2024-06-15T10:54:35+02:00 Rebase of first attempt of NCG SIMD support This commit contains most of the changes from the commit: Add support for SIMD operations in the NCG This adds support for constructing vector types from Float#, Double# etc and performing arithmetic operations on them This commit is meant to serve as a base from which to figure out register allocation issues. - - - - - b625b251 by sheaf at 2024-06-15T10:54:35+02:00 Add QuickCheck-like test for SIMD operations - - - - - 2128fed2 by sheaf at 2024-06-15T10:54:35+02:00 SIMD NCG: add stack spilling test - - - - - 4f57cdbb by sheaf at 2024-06-15T10:54:35+02:00 SIMD NCG: fix pack & insert for DoubleX2 - - - - - 179fec9f by sheaf at 2024-06-15T10:54:35+02:00 SIMD NCG WIP: fix stack spilling - - - - - d2f88396 by sheaf at 2024-06-15T10:54:35+02:00 SIMD NCG: accept simd006 - - - - - 16f74f1d by sheaf at 2024-06-15T10:54:35+02:00 WIP: fix mkSpillInstr/mkLoadInstr panics - - - - - 34ca88fb by sheaf at 2024-06-15T10:54:36+02:00 improve RegClass - - - - - e37a497e by sheaf at 2024-06-15T10:54:36+02:00 set up basics for AArch64 SIMD - - - - - fe37c01f by sheaf at 2024-06-15T10:54:36+02:00 use MOVU instructions for spill/unspill - - - - - a8c0c7f8 by sheaf at 2024-06-15T10:54:36+02:00 WIP: start adding vector shuffle primops - - - - - 9348b7b5 by sheaf at 2024-06-15T10:54:36+02:00 remove redundant code in CmmToAsm/PPC/Instr - - - - - b8776883 by sheaf at 2024-06-15T10:54:36+02:00 emit ymm/zmm when appropriate - - - - - a1569cd8 by sheaf at 2024-06-15T10:54:36+02:00 fix reg2reg for vectors - - - - - e32e1f98 by sheaf at 2024-06-15T10:54:36+02:00 WIP: lower vector shuffle instruction on X86 - - - - - 50e263ac by sheaf at 2024-06-15T10:54:37+02:00 NCG SIMD: fix shuffle lowering - - - - - d20d5a5c by sheaf at 2024-06-15T10:54:37+02:00 slight improvement to vector unpack - - - - - 14cac3df by sheaf at 2024-06-15T10:54:37+02:00 fix whitespace - - - - - a98460b7 by sheaf at 2024-06-15T10:54:37+02:00 fix regUsageOfInstr INSERTPS - - - - - 8569e03f by Jaro Reinders at 2024-06-15T10:54:37+02:00 Add Int64X2 SIMD operations - - - - - f0162997 by sheaf at 2024-06-15T10:54:37+02:00 SIMD: need LLVM for Aarch64/PPC (for now) - - - - - 16f04126 by sheaf at 2024-06-15T10:54:37+02:00 fixup Jaro - - - - - f6373450 by sheaf at 2024-06-15T10:54:37+02:00 fixup: shuffle base exports - - - - - 0b7d6da4 by sheaf at 2024-06-15T10:54:37+02:00 improve cgrun083 - - - - - af98820d by sheaf at 2024-06-15T10:54:37+02:00 move SIMD tests - - - - - 9a379ac0 by sheaf at 2024-06-15T10:54:38+02:00 TODO: MOV stuff - - - - - c9900fb0 by sheaf at 2024-06-15T10:54:38+02:00 X86 NCG SIMD: refactoring - - - - - cf7b246a by sheaf at 2024-06-15T10:54:38+02:00 SIMD tests: fixup - - - - - e0164e1d by sheaf at 2024-06-15T10:54:38+02:00 fix X86 takeRegRegMove - - - - - a695af5f by sheaf at 2024-06-15T10:54:38+02:00 SIMD: add vector FMA primops - - - - - f8440fb3 by sheaf at 2024-06-15T10:54:39+02:00 SIMD: cleanup - - - - - 8bbff8d2 by sheaf at 2024-06-15T10:54:39+02:00 WIP: improve broadcast, especially on LLVM - - - - - fb48978d by sheaf at 2024-06-15T10:54:39+02:00 more tidying - - - - - 81fa6e17 by sheaf at 2024-06-15T16:21:22+02:00 SIMD: refactor Format datatype - - - - - baa104c6 by sheaf at 2024-06-15T17:32:35+02:00 Introduce RegFormat instead of using (Reg, Format) - - - - - 30 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Reg.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/AArch64.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Regs.hs - compiler/GHC/CmmToAsm/Config.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/PPC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/PPC/Regs.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Coalesce.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d565519c80be8d180ec6cfd19fc81947ba1999a0...baa104c6ba96284ecc96eb82eb0f8581abb65b84 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d565519c80be8d180ec6cfd19fc81947ba1999a0...baa104c6ba96284ecc96eb82eb0f8581abb65b84 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 15 16:35:40 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Sat, 15 Jun 2024 12:35:40 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] 2 commits: SIMD: refactor Format datatype Message-ID: <666dc2dc84786_15cf7850eaa1014102b@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 84c46f16 by sheaf at 2024-06-15T18:34:58+02:00 SIMD: refactor Format datatype - - - - - 62168cfc by sheaf at 2024-06-15T18:34:58+02:00 Introduce RegFormat instead of using (Reg, Format) - - - - - 19 changed files: - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/PPC.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/PPC/Regs.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Coalesce.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/Types/Unique/FM.hs - compiler/GHC/Types/Unique/Set.hs Changes: ===================================== compiler/GHC/CmmToAsm/AArch64/Instr.hs ===================================== @@ -149,8 +149,8 @@ regUsageOfInstr platform instr = case instr of -- filtering the usage is necessary, otherwise the register -- allocator will try to allocate pre-defined fixed stg -- registers as well, as they show up. - usage (src, dst) = RU (map (,II64) $ filter (interesting platform) src) - (map (,II64) $ filter (interesting platform) dst) + usage (src, dst) = RU (map (\r -> RegFormat r II64) $ filter (interesting platform) src) + (map (\r -> RegFormat r II64) $ filter (interesting platform) dst) -- SIMD NCG TODO: the format here is used for register spilling/unspilling. -- As the AArch64 NCG does not currently support SIMD registers, -- we simply use II64 format for all instructions. ===================================== compiler/GHC/CmmToAsm/Format.hs ===================================== @@ -1,7 +1,13 @@ +{-# LANGUAGE DataKinds #-} {-# LANGUAGE LambdaCase #-} +{-# LANGUAGE MagicHash #-} {-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE ViewPatterns #-} +{-# OPTIONS_GHC -Wno-duplicate-exports #-} + -- Allow bundling II8, II16... with both Format and ScalarFormat + -- | Formats on this architecture -- A Format is a combination of width and class -- @@ -13,19 +19,23 @@ -- properly. eg SPARC doesn't care about FF80. -- module GHC.CmmToAsm.Format ( - Format(.., IntegerFormat), + Format(Format, VecFormat, II8, II16, II32, II64, FF32, FF64, ..), ScalarFormat(..), intFormat, floatFormat, isIntFormat, + isIntScalarFormat, isFloatFormat, + isFloatScalarFormat, vecFormat, isVecFormat, cmmTypeFormat, formatToWidth, formatInBytes, - scalarWidth, - isIntScalarFormat, + RegFormat(..), + takeVirtualRegs, + takeRealRegs, + mapRegFormatSet, ) where @@ -33,9 +43,15 @@ where import GHC.Prelude import GHC.Cmm +import GHC.Platform.Reg ( Reg(..), RealReg, VirtualReg ) +import GHC.Types.Unique ( Uniquable(..) ) +import GHC.Types.Unique.Set import GHC.Utils.Outputable import GHC.Utils.Panic +import Data.Coerce +import Data.Word (Word8) + {- Note [GHC's data format representations] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ GHC has severals types that represent various aspects of data format. @@ -71,54 +87,57 @@ These include: -- here. I've removed them from the x86 version, we'll see what happens --SDM -- ToDo: quite a few occurrences of Format could usefully be replaced by Width - -data Format - = II8 - | II16 - | II32 - | II64 - | FF32 - | FF64 - | VecFormat !Length -- ^ number of elements - !ScalarFormat -- ^ format of each element - deriving (Show, Eq, Ord) - -pattern IntegerFormat :: Format -pattern IntegerFormat <- ( isIntegerFormat -> True ) -{-# COMPLETE IntegerFormat, FF32, FF64, VecFormat #-} - -isIntegerFormat :: Format -> Bool -isIntegerFormat = \case - II8 -> True - II16 -> True - II32 -> True - II64 -> True - _ -> False - - +newtype Format = MkFormat { formatBits :: Word8 } + deriving (Eq, Ord) +newtype ScalarFormat = ScalarFormat { scalarFormatBits :: Word8 } + deriving (Eq, Ord) + +pattern II8, II16, II32, II64, FF32, FF64 :: Coercible a Word8 => a +pattern II8 <- ( coerce -> ( 0b0_000 :: Word8 ) ) where { II8 = coerce (0b0_000 :: Word8) } +pattern II16 <- ( coerce -> ( 0b0_001 :: Word8 ) ) where { II16 = coerce (0b0_001 :: Word8) } +pattern II32 <- ( coerce -> ( 0b0_010 :: Word8 ) ) where { II32 = coerce (0b0_010 :: Word8) } +pattern II64 <- ( coerce -> ( 0b0_011 :: Word8 ) ) where { II64 = coerce (0b0_011 :: Word8) } +pattern FF32 <- ( coerce -> ( 0b1_010 :: Word8 ) ) where { FF32 = coerce (0b1_010 :: Word8) } +pattern FF64 <- ( coerce -> ( 0b1_011 :: Word8 ) ) where { FF64 = coerce (0b1_011 :: Word8) } + +pattern Format :: Length -> ScalarFormat -> Format +pattern Format lg b <- ( getFormat -> (# _, lg, b #) ) + where + Format lg b = MkFormat $ scalarFormatBits b .|. ( fromIntegral ( finiteBitSize lg - 1 - countLeadingZeros lg ) `shiftL` 4 ) +pattern VecFormat :: Length -> ScalarFormat -> Format +pattern VecFormat lg b <- ( getFormat -> (# True, lg, b #) ) + where + VecFormat lg b = Format lg b + +{-# COMPLETE Format :: Format #-} +{-# COMPLETE II8, II16, II32, II64, FF32, FF64, VecFormat :: Format #-} +{-# COMPLETE II8, II16, II32, II64, FF32, FF64 :: ScalarFormat #-} +getFormat :: Format -> (# Bool, Length, ScalarFormat #) +getFormat ( MkFormat b ) = (# lg > 1, lg, ScalarFormat (b .&. 0b0000_1111) #) + where + lg = bit ( fromIntegral b `shiftR` 4 ) + +instance Show ScalarFormat where + show = \case + II8 -> "II8" + II16 -> "II16" + II32 -> "II32" + II64 -> "II64" + FF32 -> "FF32" + FF64 -> "FF64" +instance Show Format where + show (Format l f) + | l == 1 + = show f + | otherwise + = "V" ++ show l ++ show f instance Outputable Format where ppr fmt = text (show fmt) -data ScalarFormat - = FmtInt8 - | FmtInt16 - | FmtInt32 - | FmtInt64 - | FmtFloat - | FmtDouble - deriving (Show, Eq, Ord) - -isIntScalarFormat :: ScalarFormat -> Bool -isIntScalarFormat FmtInt8 = True -isIntScalarFormat FmtInt16 = True -isIntScalarFormat FmtInt32 = True -isIntScalarFormat FmtInt64 = True -isIntScalarFormat _ = False - -- | Get the integer format of this width. intFormat :: Width -> Format intFormat width - = case width of + = case width of W8 -> II8 W16 -> II16 W32 -> II32 @@ -130,36 +149,37 @@ intFormat width -- | Check if a format represents a vector isVecFormat :: Format -> Bool isVecFormat (VecFormat {}) = True -isVecFormat _ = False +isVecFormat _ = False -- | Get the float format of this width. floatFormat :: Width -> Format floatFormat width = case width of - W32 -> FF32 - W64 -> FF64 + W32 -> FF32 + W64 -> FF64 + other -> pprPanic "Format.floatFormat" (ppr other) - other -> pprPanic "Format.floatFormat" (ppr other) - --- | Check if a format represent an integer value. +-- | Check if a format represents a scalar integer value. isIntFormat :: Format -> Bool -isIntFormat = not . isFloatFormat +isIntFormat(Format l f) + = l == 1 && isIntScalarFormat f +isIntScalarFormat :: ScalarFormat -> Bool +isIntScalarFormat = not . isFloatScalarFormat --- | Check if a format represents a floating point value. +-- | Check if a format represents a scalar floating point value. isFloatFormat :: Format -> Bool -isFloatFormat format - = case format of - FF32 -> True - FF64 -> True - _ -> False +isFloatFormat (Format l f) + = l == 1 && isFloatScalarFormat f +isFloatScalarFormat :: ScalarFormat -> Bool +isFloatScalarFormat (ScalarFormat b) = testBit b 3 -- | Convert a Cmm type to a Format. cmmTypeFormat :: CmmType -> Format cmmTypeFormat ty - | isFloatType ty = floatFormat (typeWidth ty) - | isVecType ty = vecFormat ty - | otherwise = intFormat (typeWidth ty) + | isFloatType ty = floatFormat (typeWidth ty) + | isVecType ty = vecFormat ty + | otherwise = intFormat (typeWidth ty) vecFormat :: CmmType -> Format vecFormat ty = @@ -167,37 +187,65 @@ vecFormat ty = elemTy = vecElemType ty in if isFloatType elemTy then case typeWidth elemTy of - W32 -> VecFormat l FmtFloat - W64 -> VecFormat l FmtDouble + W32 -> Format l FF32 + W64 -> Format l FF64 _ -> pprPanic "Incorrect vector element width" (ppr elemTy) else case typeWidth elemTy of - W8 -> VecFormat l FmtInt8 - W16 -> VecFormat l FmtInt16 - W32 -> VecFormat l FmtInt32 - W64 -> VecFormat l FmtInt64 + W8 -> Format l II8 + W16 -> Format l II16 + W32 -> Format l II32 + W64 -> Format l II64 _ -> pprPanic "Incorrect vector element width" (ppr elemTy) -- | Get the Width of a Format. formatToWidth :: Format -> Width -formatToWidth format - = case format of - II8 -> W8 - II16 -> W16 - II32 -> W32 - II64 -> W64 - FF32 -> W32 - FF64 -> W64 - VecFormat l s -> - widthFromBytes (l * widthInBytes (scalarWidth s)) - -scalarWidth :: ScalarFormat -> Width -scalarWidth = \case - FmtInt8 -> W8 - FmtInt16 -> W16 - FmtInt32 -> W32 - FmtInt64 -> W64 - FmtFloat -> W32 - FmtDouble -> W64 +formatToWidth (Format l f) + | l == 1 + = go f + | otherwise + = widthFromBytes (l * widthInBytes (go f)) + where + go = \case + II8 -> W8 + II16 -> W16 + II32 -> W32 + II64 -> W64 + FF32 -> W32 + FF64 -> W64 formatInBytes :: Format -> Int formatInBytes = widthInBytes . formatToWidth + +-------------------------------------------------------------------------------- + +-- | A typed register: a register, together with the specific format we +-- are using it at. +data RegFormat + = RegFormat + { regFormatReg :: {-# UNPACK #-} !Reg + , regFormatFormat :: !Format + } + +instance Show RegFormat where + show (RegFormat reg fmt) = show reg ++ "::" ++ show fmt + +instance Uniquable RegFormat where + getUnique = getUnique . regFormatReg + +instance Outputable RegFormat where + ppr (RegFormat reg fmt) = ppr reg <+> dcolon <+> ppr fmt + +-- | Take all the virtual registers from this set. +takeVirtualRegs :: UniqSet RegFormat -> UniqSet VirtualReg +takeVirtualRegs = mapMaybeUniqSet_sameUnique $ + \ case { RegFormat { regFormatReg = RegVirtual vr } -> Just vr; _ -> Nothing } + -- See Note [Unique Determinism and code generation] + +-- | Take all the real registers from this set. +takeRealRegs :: UniqSet RegFormat -> UniqSet RealReg +takeRealRegs = mapMaybeUniqSet_sameUnique $ + \ case { RegFormat { regFormatReg = RegReal rr } -> Just rr; _ -> Nothing } + -- See Note [Unique Determinism and code generation] + +mapRegFormatSet :: (Reg -> Reg) -> UniqSet RegFormat -> UniqSet RegFormat +mapRegFormatSet f = mapUniqSet ( \ ( RegFormat r fmt ) -> RegFormat ( f r ) fmt ) ===================================== compiler/GHC/CmmToAsm/Instr.hs ===================================== @@ -30,8 +30,8 @@ import GHC.CmmToAsm.Format -- data RegUsage = RU { - reads :: [(Reg, Format)], - writes :: [(Reg, Format)] + reads :: [RegFormat], + writes :: [RegFormat] } deriving Show ===================================== compiler/GHC/CmmToAsm/PPC.hs ===================================== @@ -48,8 +48,8 @@ instance Instruction PPC.Instr where jumpDestsOfInstr = PPC.jumpDestsOfInstr canFallthroughTo = PPC.canFallthroughTo patchJumpInstr = PPC.patchJumpInstr - mkSpillInstr cfg reg _ i j = PPC.mkSpillInstr cfg reg i j - mkLoadInstr cfg reg _ i j = PPC.mkLoadInstr cfg reg i j + mkSpillInstr = PPC.mkSpillInstr + mkLoadInstr = PPC.mkLoadInstr takeDeltaInstr = PPC.takeDeltaInstr isMetaInstr = PPC.isMetaInstr mkRegRegMoveInstr _ = PPC.mkRegRegMoveInstr ===================================== compiler/GHC/CmmToAsm/PPC/Instr.hs ===================================== @@ -41,9 +41,7 @@ import GHC.CmmToAsm.PPC.Cond import GHC.CmmToAsm.Types import GHC.CmmToAsm.Instr (RegUsage(..), noUsage) import GHC.CmmToAsm.Format -import GHC.CmmToAsm.Reg.Target import GHC.CmmToAsm.Config -import GHC.Platform.Reg.Class import GHC.Platform.Reg import GHC.Platform.Regs @@ -68,8 +66,8 @@ import Data.Maybe (fromMaybe) -- archWordFormat :: Bool -> Format archWordFormat is32Bit - | is32Bit = II32 - | otherwise = II64 + | is32Bit = II32 + | otherwise = II64 mkStackAllocInstr :: Platform -> Int -> [Instr] @@ -391,8 +389,8 @@ regUsageOfInstr platform instr FMADD _ _ rt ra rc rb -> usage ([ra, rc, rb], [rt]) _ -> noUsage where - usage (src, dst) = RU (map (,II64) $ filter (interesting platform) src) - (map (,II64) $ filter (interesting platform) dst) + usage (src, dst) = RU (map (\ r -> RegFormat r II64) $ filter (interesting platform) src) + (map (\ r -> RegFormat r II64) $ filter (interesting platform) dst) -- SIMD NCG TODO: the format here is used for register spilling/unspilling. -- As the PowerPC NCG does not currently support SIMD registers, -- we simply use II64 format for all instructions. @@ -551,21 +549,16 @@ patchJumpInstr insn patchF mkSpillInstr :: NCGConfig -> Reg -- register to spill + -> Format -> Int -- current stack delta -> Int -- spill slot to use -> [Instr] -mkSpillInstr config reg delta slot +mkSpillInstr config reg fmt delta slot = let platform = ncgPlatform config off = spillSlotToOffset platform slot - arch = platformArch platform in - let fmt = case targetClassOfReg platform reg of - RcInteger -> case arch of - ArchPPC -> II32 - _ -> II64 - RcFloatOrVector -> FF64 - instr = case makeImmediate W32 True (off-delta) of + let instr = case makeImmediate W32 True (off-delta) of Just _ -> ST Nothing -> STFAR -- pseudo instruction: 32 bit offsets @@ -575,21 +568,16 @@ mkSpillInstr config reg delta slot mkLoadInstr :: NCGConfig -> Reg -- register to load + -> Format -> Int -- current stack delta -> Int -- spill slot to use -> [Instr] -mkLoadInstr config reg delta slot +mkLoadInstr config reg fmt delta slot = let platform = ncgPlatform config off = spillSlotToOffset platform slot - arch = platformArch platform in - let fmt = case targetClassOfReg platform reg of - RcInteger -> case arch of - ArchPPC -> II32 - _ -> II64 - RcFloatOrVector -> FF64 - instr = case makeImmediate W32 True (off-delta) of + let instr = case makeImmediate W32 True (off-delta) of Just _ -> LD Nothing -> LDFAR -- pseudo instruction: 32 bit offsets ===================================== compiler/GHC/CmmToAsm/PPC/Regs.hs ===================================== @@ -108,13 +108,14 @@ realRegSqueeze cls rr mkVirtualReg :: Unique -> Format -> VirtualReg -mkVirtualReg u format - | not (isFloatFormat format) = VirtualRegI u - | otherwise - = case format of - FF32 -> VirtualRegD u - FF64 -> VirtualRegD u - _ -> panic "mkVirtualReg" +mkVirtualReg u fmt = + case fmt of + VecFormat {} -> panic "mkVirtualReg: vector register" + _ | not (isFloatFormat fmt) + -> VirtualRegI u + FF32 -> VirtualRegD u + FF64 -> VirtualRegD u + _ -> panic "mkVirtualReg" regDotColor :: RealReg -> SDoc regDotColor reg ===================================== compiler/GHC/CmmToAsm/Reg/Graph.hs ===================================== @@ -21,6 +21,7 @@ import GHC.CmmToAsm.Reg.Graph.TrivColorable import GHC.CmmToAsm.Instr import GHC.CmmToAsm.Reg.Target import GHC.CmmToAsm.Config +import GHC.CmmToAsm.Format import GHC.CmmToAsm.Types import GHC.Platform.Reg.Class import GHC.Platform.Reg @@ -336,21 +337,21 @@ buildGraph platform code -- | Add some conflict edges to the graph. -- Conflicts between virtual and real regs are recorded as exclusions. graphAddConflictSet - :: RegMap (Reg, fmt) + :: UniqSet RegFormat -> Color.Graph VirtualReg RegClass RealReg -> Color.Graph VirtualReg RegClass RealReg graphAddConflictSet regs graph - = let virtuals = mkUniqSet - [ vr | (RegVirtual vr, _) <- nonDetEltsUFM regs ] + = let virtuals = takeVirtualRegs regs + reals = takeRealRegs regs graph1 = Color.addConflicts virtuals classOfVirtualReg graph graph2 = foldr (\(r1, r2) -> Color.addExclusion r1 classOfVirtualReg r2) graph1 [ (vr, rr) - | (RegVirtual vr, _) <- nonDetEltsUFM regs - , (RegReal rr, _) <- nonDetEltsUFM regs] + | vr <- nonDetEltsUniqSet virtuals + , rr <- nonDetEltsUniqSet reals ] -- See Note [Unique Determinism and code generation] in graph2 ===================================== compiler/GHC/CmmToAsm/Reg/Graph/Coalesce.hs ===================================== @@ -15,6 +15,8 @@ import GHC.Data.Graph.Directed import GHC.Types.Unique.FM import GHC.Types.Unique.Supply import GHC.Platform (Platform) +import GHC.Types.Unique.Set +import GHC.Types.Unique (getUnique) -- | Do register coalescing on this top level thing @@ -87,8 +89,8 @@ slurpJoinMovs platform live slurpLI rs (LiveInstr _ Nothing) = rs slurpLI rs (LiveInstr instr (Just live)) | Just (r1, r2) <- takeRegRegMoveInstr platform instr - , elemUFM r1 $ liveDieRead live - , elemUFM r2 $ liveBorn live + , elemUniqSet_Directly (getUnique r1) $ liveDieRead live + , elemUniqSet_Directly (getUnique r2) $ liveBorn live -- only coalesce movs between two virtuals for now, -- else we end up with allocatable regs in the live ===================================== compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs ===================================== @@ -17,6 +17,8 @@ import GHC.Cmm hiding (RegSet) import GHC.Cmm.BlockId import GHC.Cmm.Dataflow.Label +import GHC.Data.List.SetOps (nubOrdBy) + import GHC.Utils.Monad import GHC.Utils.Monad.State.Strict import GHC.Types.Unique @@ -27,11 +29,14 @@ import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Platform -import Data.List (nub, (\\), intersect) +import Data.Function ( on ) +import Data.List (intersectBy) import Data.Maybe import Data.IntSet (IntSet) import qualified Data.IntSet as IntSet -import GHC.CmmToAsm.Format +import GHC.CmmToAsm.Format ( RegFormat(RegFormat, regFormatReg) ) + + -- | Spill all these virtual regs to stack slots. @@ -139,7 +144,7 @@ regSpill_top platform regSlotMap cmm -- then record the fact that these slots are now live in those blocks -- in the given slotmap. patchLiveSlot - :: BlockMap IntSet -> BlockId -> RegMap (Reg, Format) -> BlockMap IntSet + :: BlockMap IntSet -> BlockId -> UniqSet RegFormat-> BlockMap IntSet patchLiveSlot slotMap blockId regsLive = let @@ -148,9 +153,8 @@ regSpill_top platform regSlotMap cmm $ mapLookup blockId slotMap moreSlotsLive = IntSet.fromList - $ mapMaybe (lookupUFM regSlotMap) - $ map fst - $ nonDetEltsUFM regsLive + $ mapMaybe (lookupUFM regSlotMap . regFormatReg) + $ nonDetEltsUniqSet regsLive -- See Note [Unique Determinism and code generation] slotMap' @@ -190,18 +194,20 @@ regSpill_instr platform regSlotMap (LiveInstr instr (Just _)) = do -- sometimes a register is listed as being read more than once, -- nub this so we don't end up inserting two lots of spill code. - let rsRead_ = nub rlRead - let rsWritten_ = nub rlWritten + let rsRead_ = nubOrdBy (nonDetCmpUnique `on` getUnique) rlRead + rsWritten_ = nubOrdBy (nonDetCmpUnique `on` getUnique) rlWritten -- if a reg is modified, it appears in both lists, want to undo this.. - let rsRead = rsRead_ \\ rsWritten_ - let rsWritten = rsWritten_ \\ rsRead_ - let rsModify = intersect rsRead_ rsWritten_ + let rsModify = intersectBy ((==) `on` getUnique) rsRead_ rsWritten_ + modified = mkUniqSet rsModify + rsRead = filter (\ r -> not $ elementOfUniqSet r modified) rsRead_ + rsWritten = filter (\ r -> not $ elementOfUniqSet r modified) rsWritten_ + -- work out if any of the regs being used are currently being spilled. - let rsSpillRead = filter (\(r,_) -> elemUFM r regSlotMap) rsRead - let rsSpillWritten = filter (\(r,_) -> elemUFM r regSlotMap) rsWritten - let rsSpillModify = filter (\(r,_) -> elemUFM r regSlotMap) rsModify + let rsSpillRead = filter (\r -> elemUFM (regFormatReg r) regSlotMap) rsRead + let rsSpillWritten = filter (\r -> elemUFM (regFormatReg r) regSlotMap) rsWritten + let rsSpillModify = filter (\r -> elemUFM (regFormatReg r) regSlotMap) rsModify -- rewrite the instr and work out spill code. (instr1, prepost1) <- mapAccumLM (spillRead regSlotMap) instr rsSpillRead @@ -226,10 +232,10 @@ spillRead :: Instruction instr => UniqFM Reg Int -> instr - -> (Reg, Format) + -> RegFormat -> SpillM (instr, ([LiveInstr instr'], [LiveInstr instr'])) -spillRead regSlotMap instr (reg, fmt) +spillRead regSlotMap instr (RegFormat reg fmt) | Just slot <- lookupUFM regSlotMap reg = do (instr', nReg) <- patchInstr reg instr @@ -249,10 +255,10 @@ spillWrite :: Instruction instr => UniqFM Reg Int -> instr - -> (Reg, Format) + -> RegFormat -> SpillM (instr, ([LiveInstr instr'], [LiveInstr instr'])) -spillWrite regSlotMap instr (reg, fmt) +spillWrite regSlotMap instr (RegFormat reg fmt) | Just slot <- lookupUFM regSlotMap reg = do (instr', nReg) <- patchInstr reg instr @@ -272,10 +278,10 @@ spillModify :: Instruction instr => UniqFM Reg Int -> instr - -> (Reg, Format) + -> RegFormat -> SpillM (instr, ([LiveInstr instr'], [LiveInstr instr'])) -spillModify regSlotMap instr (reg, fmt) +spillModify regSlotMap instr (RegFormat reg fmt) | Just slot <- lookupUFM regSlotMap reg = do (instr', nReg) <- patchInstr reg instr ===================================== compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs ===================================== @@ -36,6 +36,7 @@ module GHC.CmmToAsm.Reg.Graph.SpillClean ( import GHC.Prelude import GHC.CmmToAsm.Reg.Liveness +import GHC.CmmToAsm.Format import GHC.CmmToAsm.Instr import GHC.Platform.Reg @@ -215,7 +216,7 @@ cleanForward platform blockId assoc acc (li : instrs) -- Writing to a reg changes its value. | LiveInstr instr _ <- li , RU _ written <- regUsageOfInstr platform instr - = let assoc' = foldr delAssoc assoc (map SReg $ nub $ map fst written) + = let assoc' = foldr delAssoc assoc (map SReg $ nub $ map regFormatReg written) in cleanForward platform blockId assoc' (li : acc) instrs ===================================== compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs ===================================== @@ -1,4 +1,5 @@ {-# LANGUAGE GADTs #-} +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE ScopedTypeVariables #-} module GHC.CmmToAsm.Reg.Graph.SpillCost ( @@ -34,6 +35,7 @@ import GHC.Utils.Panic import GHC.Platform import GHC.Utils.Monad.State.Strict import GHC.CmmToAsm.CFG +import GHC.CmmToAsm.Format import Data.List (nub, minimumBy) import Data.Maybe @@ -99,7 +101,7 @@ slurpSpillCostInfo platform cfg cmm countBlock info freqMap (BasicBlock blockId instrs) | LiveInfo _ _ blockLive _ <- info , Just rsLiveEntry <- mapLookup blockId blockLive - , rsLiveEntry_virt <- takeVirtuals rsLiveEntry + , rsLiveEntry_virt <- takeVirtualRegs rsLiveEntry = countLIs (ceiling $ blockFreq freqMap blockId) rsLiveEntry_virt instrs | otherwise @@ -129,13 +131,13 @@ slurpSpillCostInfo platform cfg cmm -- Increment counts for what regs were read/written from. let (RU read written) = regUsageOfInstr platform instr - mapM_ (incUses scale) $ mapMaybe takeVirtualReg $ nub $ map fst read - mapM_ (incDefs scale) $ mapMaybe takeVirtualReg $ nub $ map fst written + mapM_ (incUses scale) $ nub $ mapMaybe (takeVirtualReg . regFormatReg) read + mapM_ (incDefs scale) $ nub $ mapMaybe (takeVirtualReg . regFormatReg) written -- Compute liveness for entry to next instruction. - let liveDieRead_virt = takeVirtuals (liveDieRead live) - let liveDieWrite_virt = takeVirtuals (liveDieWrite live) - let liveBorn_virt = takeVirtuals (liveBorn live) + let liveDieRead_virt = takeVirtualRegs (liveDieRead live) + let liveDieWrite_virt = takeVirtualRegs (liveDieWrite live) + let liveBorn_virt = takeVirtualRegs (liveBorn live) let rsLiveAcross = rsLiveEntry `minusUniqSet` liveDieRead_virt @@ -157,13 +159,6 @@ slurpSpillCostInfo platform cfg cmm | otherwise = 1.0 -- Only if no cfg given --- | Take all the virtual registers from this set. -takeVirtuals :: RegMap (Reg, fmt) -> UniqSet VirtualReg -takeVirtuals m = mkUniqSet - [ vr | (RegVirtual vr, _) <- nonDetEltsUFM m ] - -- See Note [Unique Determinism and code generation] - - -- | Choose a node to spill from this graph chooseSpill :: SpillCostInfo ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -117,6 +117,7 @@ import GHC.CmmToAsm.Reg.Liveness import GHC.CmmToAsm.Reg.Utils import GHC.CmmToAsm.Instr import GHC.CmmToAsm.Config +import GHC.CmmToAsm.Format import GHC.CmmToAsm.Types import GHC.Platform.Reg import GHC.Platform.Reg.Class (RegClass(..)) @@ -128,6 +129,7 @@ import GHC.Cmm hiding (RegSet) import GHC.Data.Graph.Directed import GHC.Types.Unique import GHC.Types.Unique.FM +import GHC.Types.Unique.Set import GHC.Types.Unique.Supply import GHC.Utils.Outputable import GHC.Utils.Panic @@ -136,7 +138,6 @@ import GHC.Platform import Data.Maybe import Data.List (partition, nub) import Control.Monad -import GHC.CmmToAsm.Format -- ----------------------------------------------------------------------------- -- Top level of the register allocator @@ -203,7 +204,7 @@ linearRegAlloc :: forall instr. (Instruction instr) => NCGConfig -> [BlockId] -- ^ entry points - -> BlockMap (UniqFM Reg (Reg, Format)) + -> BlockMap (UniqSet RegFormat) -- ^ live regs on entry to each basic block -> [SCC (LiveBasicBlock instr)] -- ^ instructions annotated with "deaths" @@ -242,7 +243,7 @@ linearRegAlloc' => NCGConfig -> freeRegs -> [BlockId] -- ^ entry points - -> BlockMap (UniqFM Reg (Reg, Format)) -- ^ live regs on entry to each basic block + -> BlockMap (UniqSet RegFormat) -- ^ live regs on entry to each basic block -> [SCC (LiveBasicBlock instr)] -- ^ instructions annotated with "deaths" -> UniqSM ([NatBasicBlock instr], RegAllocStats, Int) @@ -256,7 +257,7 @@ linearRegAlloc' config initFreeRegs entry_ids block_live sccs linearRA_SCCs :: OutputableRegConstraint freeRegs instr => [BlockId] - -> BlockMap (UniqFM Reg (Reg, Format)) + -> BlockMap (UniqSet RegFormat) -> [NatBasicBlock instr] -> [SCC (LiveBasicBlock instr)] -> RegM freeRegs [NatBasicBlock instr] @@ -291,7 +292,7 @@ linearRA_SCCs entry_ids block_live blocksAcc (CyclicSCC blocks : sccs) process :: forall freeRegs instr. (OutputableRegConstraint freeRegs instr) => [BlockId] - -> BlockMap (UniqFM Reg (Reg, Format)) + -> BlockMap (UniqSet RegFormat) -> [GenBasicBlock (LiveInstr instr)] -> RegM freeRegs [[NatBasicBlock instr]] process entry_ids block_live = @@ -330,7 +331,7 @@ process entry_ids block_live = -- processBlock :: OutputableRegConstraint freeRegs instr - => BlockMap (UniqFM Reg (Reg, Format)) -- ^ live regs on entry to each basic block + => BlockMap (UniqSet RegFormat) -- ^ live regs on entry to each basic block -> LiveBasicBlock instr -- ^ block to do register allocation on -> RegM freeRegs [NatBasicBlock instr] -- ^ block with registers allocated @@ -347,7 +348,7 @@ processBlock block_live (BasicBlock id instrs) -- | Load the freeregs and current reg assignment into the RegM state -- for the basic block with this BlockId. initBlock :: FR freeRegs - => BlockId -> BlockMap (UniqFM Reg (Reg, Format)) -> RegM freeRegs () + => BlockId -> BlockMap (UniqSet RegFormat) -> RegM freeRegs () initBlock id block_live = do platform <- getPlatform block_assig <- getBlockAssigR @@ -364,7 +365,7 @@ initBlock id block_live setFreeRegsR (frInitFreeRegs platform) Just live -> setFreeRegsR $ foldl' (flip $ frAllocateReg platform) (frInitFreeRegs platform) - [ r | ( RegReal r, _ ) <- nonDetEltsUFM live ] + (nonDetEltsUniqSet $ takeRealRegs live) -- See Note [Unique Determinism and code generation] setAssigR emptyRegMap @@ -377,7 +378,7 @@ initBlock id block_live -- | Do allocation for a sequence of instructions. linearRA :: forall freeRegs instr. (OutputableRegConstraint freeRegs instr) - => BlockMap (UniqFM Reg (Reg, Format)) -- ^ map of what vregs are live on entry to each block. + => BlockMap (UniqSet RegFormat) -- ^ map of what vregs are live on entry to each block. -> BlockId -- ^ id of the current block, for debugging. -> [LiveInstr instr] -- ^ liveness annotated instructions in this block. -> RegM freeRegs @@ -402,7 +403,7 @@ linearRA block_live block_id = go [] [] -- | Do allocation for a single instruction. raInsn :: OutputableRegConstraint freeRegs instr - => BlockMap (UniqFM Reg (Reg, Format)) -- ^ map of what vregs are love on entry to each block. + => BlockMap (UniqSet RegFormat) -- ^ map of what vregs are love on entry to each block. -> [instr] -- ^ accumulator for instructions already processed. -> BlockId -- ^ the id of the current block, for debugging -> LiveInstr instr -- ^ the instr to have its regs allocated, with liveness info. @@ -433,7 +434,7 @@ raInsn block_live new_instrs id (LiveInstr (Instr instr) (Just live)) -- (we can't eliminate it if the source register is on the stack, because -- we do not want to use one spill slot for different virtual registers) case takeRegRegMoveInstr platform instr of - Just (src,dst) | Just (_, fmt) <- lookupUFM (liveDieRead live) src, + Just (src,dst) | Just (RegFormat _ fmt) <- lookupUniqSet_Directly (liveDieRead live) (getUnique src), isVirtualReg dst, not (dst `elemUFM` assig), isRealReg src || isInReg src assig -> do @@ -457,8 +458,8 @@ raInsn block_live new_instrs id (LiveInstr (Instr instr) (Just live)) return (new_instrs, []) _ -> genRaInsn block_live new_instrs id instr - (map fst $ nonDetEltsUFM $ liveDieRead live) - (map fst $ nonDetEltsUFM $ liveDieWrite live) + (map regFormatReg $ nonDetEltsUniqSet $ liveDieRead live) + (map regFormatReg $ nonDetEltsUniqSet $ liveDieWrite live) -- See Note [Unique Determinism and code generation] raInsn _ _ _ instr @@ -487,7 +488,7 @@ isInReg src assig | Just (InReg _) <- lookupUFM assig src = True genRaInsn :: forall freeRegs instr. (OutputableRegConstraint freeRegs instr) - => BlockMap (UniqFM Reg (Reg, Format)) + => BlockMap (UniqSet RegFormat) -> [instr] -> BlockId -> instr @@ -500,13 +501,13 @@ genRaInsn block_live new_instrs block_id instr r_dying w_dying = do platform <- getPlatform case regUsageOfInstr platform instr of { RU read written -> do - let real_written = [ rr | (RegReal rr, _) <- written ] :: [RealReg] - let virt_written = [ vr | (RegVirtual vr, _) <- written ] + let real_written = [ rr | RegFormat { regFormatReg = RegReal rr } <- written ] :: [RealReg] + let virt_written = [ vr | RegFormat { regFormatReg = RegVirtual vr } <- written ] -- we don't need to do anything with real registers that are -- only read by this instr. (the list is typically ~2 elements, -- so using nub isn't a problem). - let virt_read = nub [ vr | (RegVirtual vr, _) <- read ] :: [VirtualReg] + let virt_read = nub [ vr | RegFormat { regFormatReg = RegVirtual vr }<- read ] :: [VirtualReg] -- do -- let real_read = nub [ rr | (RegReal rr) <- read] @@ -872,7 +873,7 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc let regclass = classOfVirtualReg r freeRegs_thisClass = frGetFreeRegs platform regclass freeRegs :: [RealReg] vr_fmt = case r of - VirtualRegV128 {} -> VecFormat 2 FmtDouble + VirtualRegV128 {} -> VecFormat 2 FF64 -- It doesn't really matter whether we use e.g. v2f64 or v4f32 -- or v4i32 etc here. This is perhaps a sign that 'Format' -- is not the right type to use here, but that is a battle ===================================== compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs ===================================== @@ -32,13 +32,14 @@ import GHC.Types.Unique.FM import GHC.Utils.Outputable import GHC.CmmToAsm.Format +import GHC.Types.Unique.Set -- | For a jump instruction at the end of a block, generate fixup code so its -- vregs are in the correct regs for its destination. -- joinToTargets :: (FR freeRegs, Instruction instr) - => BlockMap (RegMap (Reg, Format)) -- ^ maps the unique of the blockid to the set of vregs + => BlockMap (UniqSet RegFormat) -- ^ maps the unique of the blockid to the set of vregs -- that are known to be live on the entry to each block. -> BlockId -- ^ id of the current block @@ -62,7 +63,7 @@ joinToTargets block_live id instr ----- joinToTargets' :: (FR freeRegs, Instruction instr) - => BlockMap (RegMap (Reg, Format)) -- ^ maps the unique of the blockid to the set of vregs + => BlockMap (UniqSet RegFormat) -- ^ maps the unique of the blockid to the set of vregs -- that are known to be live on the entry to each block. -> [NatBasicBlock instr] -- ^ acc blocks of fixup code. @@ -90,7 +91,7 @@ joinToTargets' block_live new_blocks block_id instr (dest:dests) -- adjust the current assignment to remove any vregs that are not live -- on entry to the destination block. let Just live_set = mapLookup dest block_live - let still_live uniq _ = uniq `elemUFM_Directly` live_set + let still_live uniq _ = uniq `elemUniqSet_Directly` live_set let adjusted_assig = filterUFM_Directly still_live assig -- and free up those registers which are now free. @@ -99,7 +100,7 @@ joinToTargets' block_live new_blocks block_id instr (dest:dests) -- This is non-deterministic but we do not -- currently support deterministic code-generation. -- See Note [Unique Determinism and code generation] - , not (elemUFM_Directly reg live_set) + , not (elemUniqSet_Directly reg live_set) , r <- regsOfLoc loc ] case lookupBlockAssignment dest block_assig of @@ -116,7 +117,7 @@ joinToTargets' block_live new_blocks block_id instr (dest:dests) -- this is the first time we jumped to this block. joinToTargets_first :: (FR freeRegs, Instruction instr) - => BlockMap (UniqFM Reg (Reg, Format)) + => BlockMap (UniqSet RegFormat) -> [NatBasicBlock instr] -> BlockId -> instr @@ -145,7 +146,7 @@ joinToTargets_first block_live new_blocks block_id instr dest dests -- we've jumped to this block before joinToTargets_again :: (Instruction instr, FR freeRegs) - => BlockMap (UniqFM Reg (Reg, Format)) + => BlockMap (UniqSet RegFormat) -> [NatBasicBlock instr] -> BlockId -> instr ===================================== compiler/GHC/CmmToAsm/Reg/Liveness.hs ===================================== @@ -64,6 +64,7 @@ import Data.List (mapAccumL, partition) import Data.Maybe import Data.IntSet (IntSet) import GHC.CmmToAsm.Format +import GHC.Types.Unique (Uniquable(..)) ----------------------------------------------------------------------------- type RegSet = UniqSet Reg @@ -110,8 +111,8 @@ instance Instruction instr => Instruction (InstrSR instr) where regUsageOfInstr platform i = case i of Instr instr -> regUsageOfInstr platform instr - SPILL reg fmt _ -> RU [(reg, fmt)] [] - RELOAD _ reg fmt -> RU [] [(reg, fmt)] + SPILL reg fmt _ -> RU [RegFormat reg fmt] [] + RELOAD _ reg fmt -> RU [] [RegFormat reg fmt] patchRegsOfInstr i f = case i of @@ -187,9 +188,9 @@ data LiveInstr instr data Liveness = Liveness - { liveBorn :: RegMap (Reg, Format) -- ^ registers born in this instruction (written to for first time). - , liveDieRead :: RegMap (Reg, Format) -- ^ registers that died because they were read for the last time. - , liveDieWrite :: RegMap (Reg, Format) } -- ^ registers that died because they were clobbered by something. + { liveBorn :: UniqSet RegFormat -- ^ registers born in this instruction (written to for first time). + , liveDieRead :: UniqSet RegFormat -- ^ registers that died because they were read for the last time. + , liveDieWrite :: UniqSet RegFormat} -- ^ registers that died because they were clobbered by something. -- | Stash regs live on entry to each basic block in the info part of the cmm code. @@ -198,7 +199,7 @@ data LiveInfo (LabelMap RawCmmStatics) -- cmm info table static stuff [BlockId] -- entry points (first one is the -- entry point for the proc). - (BlockMap (UniqFM Reg (Reg, Format))) -- argument locals live on entry to this block + (BlockMap (UniqSet RegFormat)) -- argument locals live on entry to this block (BlockMap IntSet) -- stack slots live on entry to this block @@ -244,11 +245,11 @@ instance Outputable instr , pprRegs (text "# w_dying: ") (liveDieWrite live) ] $+$ space) - where pprRegs :: Outputable a => SDoc -> RegMap a -> SDoc + where pprRegs :: SDoc -> UniqSet RegFormat -> SDoc pprRegs name regs - | isNullUFM regs = empty + | isEmptyUniqSet regs = empty | otherwise = name <> - (pprUFM regs (hcat . punctuate space . map ppr)) + (pprUFM (getUniqSet regs) (hcat . punctuate space . map ppr)) instance OutputableP env instr => OutputableP env (LiveInstr instr) where pdoc env i = ppr (fmap (pdoc env) i) @@ -328,7 +329,7 @@ slurpConflicts :: Instruction instr => Platform -> LiveCmmDecl statics instr - -> (Bag (UniqFM Reg (Reg, Format)), Bag (Reg, Reg)) + -> (Bag (UniqSet RegFormat), Bag (Reg, Reg)) slurpConflicts platform live = slurpCmm (emptyBag, emptyBag) live @@ -362,23 +363,23 @@ slurpConflicts platform live = let -- regs that die because they are read for the last time at the start of an instruction -- are not live across it. - rsLiveAcross = rsLiveEntry `minusUFM` (liveDieRead live) + rsLiveAcross = rsLiveEntry `minusUniqSet` (liveDieRead live) -- regs live on entry to the next instruction. -- be careful of orphans, make sure to delete dying regs _after_ unioning -- in the ones that are born here. - rsLiveNext = (rsLiveAcross `plusUFM` (liveBorn live)) - `minusUFM` (liveDieWrite live) + rsLiveNext = (rsLiveAcross `unionUniqSets` (liveBorn live)) + `minusUniqSet` (liveDieWrite live) -- orphan vregs are the ones that die in the same instruction they are born in. -- these are likely to be results that are never used, but we still -- need to assign a hreg to them.. - rsOrphans = intersectUFM + rsOrphans = intersectUniqSets (liveBorn live) - (plusUFM (liveDieWrite live) (liveDieRead live)) + (unionUniqSets (liveDieWrite live) (liveDieRead live)) -- - rsConflicts = plusUFM rsLiveNext rsOrphans + rsConflicts = unionUniqSets rsLiveNext rsOrphans in case takeRegRegMoveInstr platform instr of Just rr -> slurpLIs rsLiveNext @@ -622,7 +623,7 @@ patchEraseLive platform patchF cmm | LiveInfo static id blockMap mLiveSlots <- info = let -- See Note [Unique Determinism and code generation] - blockMap' = mapMap (mapKeysUFM patchF) blockMap + blockMap' = mapMap (mapRegFormatSet patchF) blockMap info' = LiveInfo static id blockMap' mLiveSlots in CmmProc info' label live $ map patchSCC sccs @@ -651,8 +652,8 @@ patchEraseLive platform patchF cmm | r1 == r2 = True -- destination reg is never used - | elemUFM r2 (liveBorn live) - , elemUFM r2 (liveDieRead live) || elemUFM r2 (liveDieWrite live) + | elemUniqSet_Directly (getUnique r2) (liveBorn live) + , elemUniqSet_Directly (getUnique r2) (liveDieRead live) || elemUniqSet_Directly (getUnique r2) (liveDieWrite live) = True | otherwise = False @@ -675,9 +676,9 @@ patchRegsLiveInstr patchF li (patchRegsOfInstr instr patchF) (Just live { -- WARNING: have to go via lists here because patchF changes the uniq in the Reg - liveBorn = mapKeysUFM patchF $ liveBorn live - , liveDieRead = mapKeysUFM patchF $ liveDieRead live - , liveDieWrite = mapKeysUFM patchF $ liveDieWrite live }) + liveBorn = mapRegFormatSet patchF $ liveBorn live + , liveDieRead = mapRegFormatSet patchF $ liveDieRead live + , liveDieWrite = mapRegFormatSet patchF $ liveDieWrite live }) -- See Note [Unique Determinism and code generation] -------------------------------------------------------------------------------- @@ -867,7 +868,7 @@ computeLiveness -> [SCC (LiveBasicBlock instr)] -> ([SCC (LiveBasicBlock instr)], -- instructions annotated with list of registers -- which are "dead after this instruction". - BlockMap (UniqFM Reg (Reg, Format))) -- blocks annotated with set of live registers + BlockMap (UniqSet RegFormat)) -- blocks annotated with set of live registers -- on entry to the block. computeLiveness platform sccs @@ -882,11 +883,11 @@ computeLiveness platform sccs livenessSCCs :: Instruction instr => Platform - -> BlockMap (UniqFM Reg (Reg, Format)) + -> BlockMap (UniqSet RegFormat) -> [SCC (LiveBasicBlock instr)] -- accum -> [SCC (LiveBasicBlock instr)] -> ( [SCC (LiveBasicBlock instr)] - , BlockMap (UniqFM Reg (Reg, Format))) + , BlockMap (UniqSet RegFormat)) livenessSCCs _ blockmap done [] = (done, blockmap) @@ -915,8 +916,8 @@ livenessSCCs platform blockmap done linearLiveness :: Instruction instr - => BlockMap (UniqFM Reg (Reg, Format)) -> [LiveBasicBlock instr] - -> (BlockMap (UniqFM Reg (Reg, Format)), [LiveBasicBlock instr]) + => BlockMap (UniqSet RegFormat) -> [LiveBasicBlock instr] + -> (BlockMap (UniqSet RegFormat), [LiveBasicBlock instr]) linearLiveness = mapAccumL (livenessBlock platform) @@ -935,14 +936,14 @@ livenessSCCs platform blockmap done livenessBlock :: Instruction instr => Platform - -> BlockMap (UniqFM Reg (Reg, Format)) + -> BlockMap (UniqSet RegFormat) -> LiveBasicBlock instr - -> (BlockMap (UniqFM Reg (Reg, Format)), LiveBasicBlock instr) + -> (BlockMap (UniqSet RegFormat), LiveBasicBlock instr) livenessBlock platform blockmap (BasicBlock block_id instrs) = let (regsLiveOnEntry, instrs1) - = livenessBack platform emptyUFM blockmap [] (reverse instrs) + = livenessBack platform emptyUniqSet blockmap [] (reverse instrs) blockmap' = mapInsert block_id regsLiveOnEntry blockmap instrs2 = livenessForward platform regsLiveOnEntry instrs1 @@ -957,7 +958,7 @@ livenessBlock platform blockmap (BasicBlock block_id instrs) livenessForward :: Instruction instr => Platform - -> UniqFM Reg (Reg, Format) -- regs live on this instr + -> UniqSet RegFormat -- regs live on this instr -> [LiveInstr instr] -> [LiveInstr instr] livenessForward _ _ [] = [] @@ -967,14 +968,13 @@ livenessForward platform rsLiveEntry (li@(LiveInstr instr mLive) : lis) RU _ written = regUsageOfInstr platform instr -- Regs that are written to but weren't live on entry to this instruction -- are recorded as being born here. - rsBorn = listToUFM - $ map ( \ ( r, fmt ) -> ( r, ( r, fmt ) ) ) - $ filter (\( r, _) -> not $ elemUFM r rsLiveEntry) + rsBorn = mkUniqSet + $ filter (\ r -> not $ elemUniqSet_Directly (getUnique r) rsLiveEntry) $ written - rsLiveNext = (rsLiveEntry `plusUFM` rsBorn) - `minusUFM` (liveDieRead live) - `minusUFM` (liveDieWrite live) + rsLiveNext = (rsLiveEntry `unionUniqSets` rsBorn) + `minusUniqSet` (liveDieRead live) + `minusUniqSet` (liveDieWrite live) in LiveInstr instr (Just live { liveBorn = rsBorn }) : livenessForward platform rsLiveNext lis @@ -989,11 +989,11 @@ livenessForward platform rsLiveEntry (li@(LiveInstr instr mLive) : lis) livenessBack :: Instruction instr => Platform - -> UniqFM Reg (Reg, Format) -- regs live on this instr - -> BlockMap (UniqFM Reg (Reg, Format)) -- regs live on entry to other BBs + -> UniqSet RegFormat -- regs live on this instr + -> BlockMap (UniqSet RegFormat) -- regs live on entry to other BBs -> [LiveInstr instr] -- instructions (accum) -> [LiveInstr instr] -- instructions - -> (UniqFM Reg (Reg, Format), [LiveInstr instr]) + -> (UniqSet RegFormat, [LiveInstr instr]) livenessBack _ liveregs _ done [] = (liveregs, done) @@ -1006,10 +1006,10 @@ livenessBack platform liveregs blockmap acc (instr : instrs) liveness1 :: Instruction instr => Platform - -> UniqFM Reg (Reg, Format) - -> BlockMap (UniqFM Reg (Reg, Format)) + -> UniqSet RegFormat + -> BlockMap (UniqSet RegFormat) -> LiveInstr instr - -> (UniqFM Reg (Reg, Format), LiveInstr instr) + -> (UniqSet RegFormat, LiveInstr instr) liveness1 _ liveregs _ (LiveInstr instr _) | isMetaInstr instr @@ -1020,14 +1020,14 @@ liveness1 platform liveregs blockmap (LiveInstr instr _) | not_a_branch = (liveregs1, LiveInstr instr (Just $ Liveness - { liveBorn = emptyUFM + { liveBorn = emptyUniqSet , liveDieRead = r_dying , liveDieWrite = w_dying })) | otherwise = (liveregs_br, LiveInstr instr (Just $ Liveness - { liveBorn = emptyUFM + { liveBorn = emptyUniqSet , liveDieRead = r_dying_br , liveDieWrite = w_dying })) @@ -1036,18 +1036,21 @@ liveness1 platform liveregs blockmap (LiveInstr instr _) -- registers that were written here are dead going backwards. -- registers that were read here are live going backwards. - liveregs1 = (liveregs `delListFromUFM` (map fst written)) - `addListToUFM` (map (\(r, fmt) -> (r, (r,fmt))) read) + liveregs1 = (liveregs `delListFromUniqSet` written) + `addListToUniqSet` read -- registers that are not live beyond this point, are recorded -- as dying here. - r_dying = listToUFM - [ (reg, (reg, fmt)) | (reg, fmt) <- read, reg `notElem` map fst written, - not (elemUFM reg liveregs) ] + r_dying = mkUniqSet + [ reg + | reg@(RegFormat r _) <- read + , not $ any (\ w -> getUnique w == getUnique r) written + , not (elementOfUniqSet reg liveregs) ] - w_dying = listToUFM - [ (reg, (reg, fmt)) | (reg, fmt) <- written, - not (elemUFM reg liveregs) ] + w_dying = mkUniqSet + [ reg + | reg <- written + , not (elementOfUniqSet reg liveregs) ] -- union in the live regs from all the jump destinations of this -- instruction. @@ -1057,14 +1060,14 @@ liveness1 platform liveregs blockmap (LiveInstr instr _) targetLiveRegs target = case mapLookup target blockmap of Just ra -> ra - Nothing -> emptyUFM + Nothing -> emptyUniqSet - live_from_branch = plusUFMList (map targetLiveRegs targets) + live_from_branch = unionManyUniqSets (map targetLiveRegs targets) - liveregs_br = liveregs1 `plusUFM` live_from_branch + liveregs_br = liveregs1 `unionUniqSets` live_from_branch -- registers that are live only in the branch targets should -- be listed as dying here. - live_branch_only = live_from_branch `minusUFM` liveregs - r_dying_br = r_dying `plusUFM` live_branch_only + live_branch_only = live_from_branch `minusUniqSet` liveregs + r_dying_br = (r_dying `unionUniqSets` live_branch_only) -- See Note [Unique Determinism and code generation] ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1220,12 +1220,12 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps vector_float_negate_avx :: Length -> Width -> CmmExpr -> NatM Register vector_float_negate_avx l w expr = do - tmp <- getNewRegNat (VecFormat l FmtFloat) + tmp <- getNewRegNat (VecFormat l FF32) (reg, exp) <- getSomeReg expr Amode addr addr_code <- memConstant (mkAlignment $ widthInBytes W32) (CmmFloat 0.0 W32) let format = case w of - W32 -> VecFormat l FmtFloat - W64 -> VecFormat l FmtDouble + W32 -> VecFormat l FF32 + W64 -> VecFormat l FF64 _ -> pprPanic "Cannot negate vector of width" (ppr w) code dst = case w of W32 -> exp `appOL` addr_code `snocOL` @@ -1240,11 +1240,11 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps vector_float_negate_sse :: Length -> Width -> CmmExpr -> NatM Register vector_float_negate_sse l w expr = do - tmp <- getNewRegNat (VecFormat l FmtFloat) + tmp <- getNewRegNat (VecFormat l FF32) (reg, exp) <- getSomeReg expr let format = case w of - W32 -> VecFormat l FmtFloat - W64 -> VecFormat l FmtDouble + W32 -> VecFormat l FF32 + W64 -> VecFormat l FF64 _ -> pprPanic "Cannot negate vector of width" (ppr w) code dst = exp `snocOL` (XOR format (OpReg tmp) (OpReg tmp)) `snocOL` @@ -1260,7 +1260,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps vector_float_broadcast_avx len W32 expr = do (reg, exp) <- getSomeReg expr - let f = VecFormat len FmtFloat + let f = VecFormat len FF32 addr = spRel platform 0 in return $ Any f (\dst -> exp `snocOL` (MOVU f (OpReg reg) (OpAddr addr)) `snocOL` @@ -1268,7 +1268,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps vector_float_broadcast_avx len W64 expr = do (reg, exp) <- getSomeReg expr - let f = VecFormat len FmtDouble + let f = VecFormat len FF64 addr = spRel platform 0 in return $ Any f (\dst -> exp `snocOL` (MOVU f (OpReg reg) (OpAddr addr)) `snocOL` @@ -1284,7 +1284,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps vector_float_broadcast_sse len W32 expr = do (reg, exp) <- getSomeReg expr - let f = VecFormat len FmtFloat + let f = VecFormat len FF32 addr = spRel platform 0 code dst = exp `snocOL` (MOVU f (OpReg reg) (OpAddr addr)) `snocOL` @@ -1307,7 +1307,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps vector_int_broadcast len W64 expr = do (reg, exp) <- getSomeReg expr - let fmt = VecFormat len FmtInt64 + let fmt = VecFormat len II64 return $ Any fmt (\dst -> exp `snocOL` (MOV II64 (OpReg reg) (OpReg dst)) `snocOL` (PUNPCKLQDQ fmt (OpReg dst) dst) `snocOL` @@ -1652,8 +1652,8 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps (reg1, exp1) <- getSomeReg expr1 (reg2, exp2) <- getSomeReg expr2 let format = case w of - W32 -> VecFormat l FmtFloat - W64 -> VecFormat l FmtDouble + W32 -> VecFormat l FF32 + W64 -> VecFormat l FF64 _ -> pprPanic "Operation not supported for width " (ppr w) code dst = case op of VA_Add -> arithInstr VADD @@ -1676,8 +1676,8 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps (reg1, exp1) <- getSomeReg expr1 (reg2, exp2) <- getSomeReg expr2 let format = case w of - W32 -> VecFormat l FmtFloat - W64 -> VecFormat l FmtDouble + W32 -> VecFormat l FF32 + W64 -> VecFormat l FF64 _ -> pprPanic "Operation not supported for width " (ppr w) code dst = case op of VA_Add -> arithInstr ADD @@ -1700,7 +1700,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps vector_float_unpack l W32 expr (CmmLit lit) = do (r, exp) <- getSomeReg expr - let format = VecFormat l FmtFloat + let format = VecFormat l FF32 imm = litToImm lit code dst = case lit of @@ -1711,7 +1711,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps vector_float_unpack l W64 expr (CmmLit lit) = do (r, exp) <- getSomeReg expr - let format = VecFormat l FmtDouble + let format = VecFormat l FF64 code dst = case lit of CmmInt 0 _ -> exp `snocOL` @@ -1732,7 +1732,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps vector_float_unpack_sse l W32 expr (CmmLit lit) = do (r,exp) <- getSomeReg expr - let format = VecFormat l FmtFloat + let format = VecFormat l FF32 imm = litToImm lit code dst = case lit of @@ -1752,7 +1752,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps vector_int_unpack_sse l at 2 W64 expr (CmmLit lit) = do (r, exp) <- getSomeReg expr - let fmt = VecFormat l FmtInt64 + let fmt = VecFormat l II64 tmp <- getNewRegNat fmt let code dst = case lit of @@ -1770,7 +1770,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps vector_shuffle_float l w v1 v2 is = do (r1, exp1) <- getSomeReg v1 (r2, exp2) <- getSomeReg v2 - let fmt = VecFormat l (if w == W32 then FmtFloat else FmtDouble) + let fmt = VecFormat l (if w == W32 then FF32 else FF64) code dst = exp1 `appOL` (exp2 `appOL` shuffleInstructions fmt r1 r2 is dst) return (Any fmt code) @@ -1778,7 +1778,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps shuffleInstructions :: Format -> Reg -> Reg -> [Int] -> Reg -> OrdList Instr shuffleInstructions fmt v1 v2 is dst = case fmt of - VecFormat 2 FmtDouble -> + VecFormat 2 FF64 -> case is of [i1, i2] -> case (i1, i2) of (0,0) -> unitOL (VSHUFPD fmt (ImmInt 0b00) (OpReg v1) v1 dst) @@ -1799,7 +1799,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps (3,1) -> unitOL (VSHUFPD fmt (ImmInt 0b11) (OpReg v1) v2 dst) _ -> pprPanic "vector shuffle: indices out of bounds 0 <= i <= 3" (ppr is) _ -> pprPanic "vector shuffle: wrong number of indices (expected 2)" (ppr is) - VecFormat 4 FmtFloat + VecFormat 4 FF32 -- indices 0 <= i <= 7 | all ( (>= 0) <&&> (<= 7) ) is -> case is of @@ -1885,7 +1885,7 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps = do fn <- getAnyReg vecExpr (r, exp) <- getSomeReg valExpr - let fmt = VecFormat len FmtFloat + let fmt = VecFormat len FF32 imm = litToImm (CmmInt (offset `shiftL` 4) W32) code dst = exp `appOL` (fn dst) `snocOL` @@ -1896,7 +1896,7 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps = do (valReg, valExp) <- getSomeReg valExpr (vecReg, vecExp) <- getSomeReg vecExpr - let fmt = VecFormat len FmtDouble + let fmt = VecFormat len FF64 code dst = case offset of CmmInt 0 _ -> valExp `appOL` @@ -1934,7 +1934,7 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps pprTraceM "vecExpr:" (pdoc platform vecExpr) (valReg, valExp) <- getSomeReg valExpr (vecReg, vecExp) <- getSomeReg vecExpr - let fmt = VecFormat len FmtInt64 + let fmt = VecFormat len II64 tmp <- getNewRegNat fmt pprTraceM "tmp:" (ppr tmp) let code dst @@ -2382,7 +2382,7 @@ addAlignmentCheck align reg = where check :: Format -> Reg -> InstrBlock check fmt reg = - assert (not $ isFloatFormat fmt) $ + assert (isIntFormat fmt) $ toOL [ TEST fmt (OpImm $ ImmInt $ align-1) (OpReg reg) , JXX_GBL NE $ ImmCLbl mkBadAlignmentLabel ] ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -629,11 +629,10 @@ regUsageOfInstr platform instr use_index EAIndexNone tl = tl use_index (EAIndex i _) tl = i : tl - mkRUR fmt src = src' `seq` RU (map (,fmt) src') [] + mkRUR fmt src = src' `seq` RU (map (\ r -> RegFormat r fmt) src') [] where src' = filter (interesting platform) src - - mkRU fmt src dst = src' `seq` dst' `seq` RU (map (,fmt) src') (map (,fmt) dst') + mkRU fmt src dst = src' `seq` dst' `seq` RU (map (\ r -> RegFormat r fmt) src') (map (\ r -> RegFormat r fmt) dst') where src' = filter (interesting platform) src dst' = filter (interesting platform) dst ===================================== compiler/GHC/CmmToAsm/X86/Ppr.hs ===================================== @@ -431,13 +431,13 @@ pprFormat x = case x of II64 -> text "q" FF32 -> text "ss" -- "scalar single-precision float" (SSE2) FF64 -> text "sd" -- "scalar double-precision float" (SSE2) - VecFormat _ FmtFloat -> text "ps" - VecFormat _ FmtDouble -> text "pd" + VecFormat _ FF32 -> text "ps" + VecFormat _ FF64 -> text "pd" -- TODO: this is shady because it only works for certain instructions - VecFormat _ FmtInt8 -> text "b" - VecFormat _ FmtInt16 -> text "w" - VecFormat _ FmtInt32 -> text "l" - VecFormat _ FmtInt64 -> text "q" + VecFormat _ II8 -> text "b" + VecFormat _ II16 -> text "w" + VecFormat _ II32 -> text "l" + VecFormat _ II64 -> text "q" pprFormat_x87 :: IsLine doc => Format -> doc pprFormat_x87 x = case x of @@ -781,9 +781,9 @@ pprInstr platform i = case i of BT format imm src -> pprFormatImmOp (text "bt") format imm src - CMP format src dst - | isFloatFormat format -> pprFormatOpOp (text "ucomi") format src dst -- SSE2 - | otherwise -> pprFormatOpOp (text "cmp") format src dst + CMP fmt@(Format _ s) src dst + | isFloatScalarFormat s -> pprFormatOpOp (text "ucomi") fmt src dst -- SSE2 + | otherwise -> pprFormatOpOp (text "cmp") fmt src dst TEST format src dst -> pprFormatOpOp (text "test") format' src dst @@ -1051,14 +1051,13 @@ pprInstr platform i = case i of char '\t' <> name <> pprBroadcastFormat format <> space pprBroadcastFormat :: Format -> Line doc - pprBroadcastFormat (VecFormat _ f) - = case f of - FmtFloat -> text "ss" - FmtDouble -> text "sd" - FmtInt8 -> text "b" - FmtInt16 -> text "w" - FmtInt32 -> text "d" - FmtInt64 -> text "q" + pprBroadcastFormat (VecFormat _ f) = case f of + FF32 -> text "ss" + FF64 -> text "sd" + II8 -> text "b" + II16 -> text "w" + II32 -> text "d" + II64 -> text "q" pprBroadcastFormat _ = panic "Scalar Format invading vector operation" pprFormatImmOp :: Line doc -> Format -> Imm -> Operand -> doc ===================================== compiler/GHC/Types/Unique/FM.hs ===================================== @@ -71,8 +71,7 @@ module GHC.Types.Unique.FM ( nonDetStrictFoldUFM_Directly, anyUFM, allUFM, seqEltsUFM, mapUFM, mapUFM_Directly, strictMapUFM, - mapKeysUFM, - mapMaybeUFM, mapMaybeWithKeyUFM, + mapMaybeUFM, mapMaybeUFM_sameUnique, mapMaybeWithKeyUFM, elemUFM, elemUFM_Directly, filterUFM, filterUFM_Directly, partitionUFM, sizeUFM, @@ -390,7 +389,12 @@ mapUFM :: (elt1 -> elt2) -> UniqFM key elt1 -> UniqFM key elt2 mapUFM f (UFM m) = UFM (M.map f m) mapMaybeUFM :: (elt1 -> Maybe elt2) -> UniqFM key elt1 -> UniqFM key elt2 -mapMaybeUFM f (UFM m) = UFM (M.mapMaybe f m) +mapMaybeUFM = mapMaybeUFM_sameUnique + +-- | Like 'Data.Map.mapMaybe', but you must ensure the passed-in function does +-- not modify the unique. +mapMaybeUFM_sameUnique :: (elt1 -> Maybe elt2) -> UniqFM key1 elt1 -> UniqFM key2 elt2 +mapMaybeUFM_sameUnique f (UFM m) = UFM (M.mapMaybe f m) mapMaybeWithKeyUFM :: (Unique -> elt1 -> Maybe elt2) -> UniqFM key elt1 -> UniqFM key elt2 mapMaybeWithKeyUFM f (UFM m) = UFM (M.mapMaybeWithKey (f . mkUniqueGrimily) m) @@ -398,10 +402,6 @@ mapMaybeWithKeyUFM f (UFM m) = UFM (M.mapMaybeWithKey (f . mkUniqueGrimily) m) mapUFM_Directly :: (Unique -> elt1 -> elt2) -> UniqFM key elt1 -> UniqFM key elt2 mapUFM_Directly f (UFM m) = UFM (M.mapWithKey (f . mkUniqueGrimily) m) --- | Map over the keys in a 'UniqFM'. -mapKeysUFM :: Uniquable key' => (key -> key') -> UniqFM key (key, b) -> UniqFM key' (key', b) -mapKeysUFM f m = listToUFM $ map ( \ (r, fmt) -> let r' = f r in (r', (r', fmt)) ) $ nonDetEltsUFM m - strictMapUFM :: (a -> b) -> UniqFM k a -> UniqFM k b strictMapUFM f (UFM a) = UFM $ MS.map f a ===================================== compiler/GHC/Types/Unique/Set.hs ===================================== @@ -44,6 +44,7 @@ module GHC.Types.Unique.Set ( nonDetEltsUniqSet, nonDetKeysUniqSet, nonDetStrictFoldUniqSet, + mapMaybeUniqSet_sameUnique, -- UniqueSet UniqueSet(..), @@ -205,6 +206,11 @@ nonDetStrictFoldUniqSet c n (UniqSet s) = nonDetStrictFoldUFM c n s mapUniqSet :: Uniquable b => (a -> b) -> UniqSet a -> UniqSet b mapUniqSet f = mkUniqSet . map f . nonDetEltsUniqSet +-- | Like 'Data.Set.mapMaybe', but you must ensure the passed in function +-- does not change the 'Unique'. +mapMaybeUniqSet_sameUnique :: (a -> Maybe b) -> UniqSet a -> UniqSet b +mapMaybeUniqSet_sameUnique f (UniqSet a) = UniqSet $ mapMaybeUFM_sameUnique f a + -- Two 'UniqSet's are considered equal if they contain the same -- uniques. instance Eq (UniqSet a) where View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/baa104c6ba96284ecc96eb82eb0f8581abb65b84...62168cfcccf795af856a9a096af78c599502477c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/baa104c6ba96284ecc96eb82eb0f8581abb65b84...62168cfcccf795af856a9a096af78c599502477c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 15 17:19:55 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sat, 15 Jun 2024 13:19:55 -0400 Subject: [Git][ghc/ghc][wip/supersven/ghc-9.10-riscv-ncg] 3 commits: Add comment Message-ID: <666dcd3ba3055_15cf78576f69c149795@gitlab.mail> Sven Tennie pushed to branch wip/supersven/ghc-9.10-riscv-ncg at Glasgow Haskell Compiler / GHC Commits: ed3ab385 by Sven Tennie at 2024-06-15T16:00:04+00:00 Add comment - - - - - 5d9729a6 by Sven Tennie at 2024-06-15T16:34:11+00:00 Drop unnecessary testsuite driver changes - - - - - 68248914 by Sven Tennie at 2024-06-15T17:18:00+00:00 Expect elf.h as system include This (hopefully) fixes this error on Darwin: ``` rts/linker/elf_reloc_riscv64.c:6:10: error: error: non-portable path to file '"Elf.h"'; specified path differs in case from file name on disk [-Werror,-Wnonportable-include-path] | 6 | #include "elf.h" | ^ ^~~~~~~ "Elf.h" ``` - - - - - 4 changed files: - compiler/GHC/CmmToAsm/PIC.hs - rts/linker/elf_reloc_riscv64.c - testsuite/driver/runtests.py - testsuite/driver/testlib.py Changes: ===================================== compiler/GHC/CmmToAsm/PIC.hs ===================================== @@ -169,10 +169,10 @@ cmmMakePicReference config lbl | ArchAArch64 <- platformArch platform = CmmLit $ CmmLabel lbl + -- as on AArch64, there's no pic base register. | ArchRISCV64 <- platformArch platform = CmmLit $ CmmLabel lbl - | OSAIX <- platformOS platform = CmmMachOp (MO_Add W32) [ CmmReg (CmmGlobal $ GlobalRegUse PicBaseReg (bWord platform)) ===================================== rts/linker/elf_reloc_riscv64.c ===================================== @@ -3,7 +3,7 @@ #include "Rts.h" #include "Stg.h" #include "SymbolExtras.h" -#include "elf.h" +#include #include "elf_plt.h" #include "elf_util.h" #include "rts/Messages.h" ===================================== testsuite/driver/runtests.py ===================================== @@ -78,7 +78,6 @@ parser.add_argument("--metrics-file", help="file in which to save (append) the p parser.add_argument("--summary-file", help="file in which to save the (human-readable) summary") parser.add_argument("--unexpected-output-dir", help="directory in which to place unexpected output") parser.add_argument("--target-wrapper", help="wrapper executable to use when executing binaries compiled for the target") -parser.add_argument("--no-print-summary", action="store_true", help="should we print the summary?") parser.add_argument("--only", action="append", help="just this test (can be give multiple --only= flags)") parser.add_argument("--way", action="append", help="just this way") parser.add_argument("--skipway", action="append", help="skip this way") ===================================== testsuite/driver/testlib.py ===================================== @@ -95,10 +95,6 @@ def isCross() -> bool: """ Are we testing a cross-compiler? """ return config.target_wrapper is not None -def isCross() -> bool: - """ Are we testing a cross-compiler? """ - return config.target_wrapper is not None - def isCompilerStatsTest() -> bool: opts = getTestOpts() return bool(opts.is_compiler_stats_test) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f93e13239e0805213faf64c90672b14576619d35...68248914206de3db164c16b15a29d0361fed2802 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/f93e13239e0805213faf64c90672b14576619d35...68248914206de3db164c16b15a29d0361fed2802 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 15 18:27:48 2024 From: gitlab at gitlab.haskell.org (Jens Petersen (@juhp)) Date: Sat, 15 Jun 2024 14:27:48 -0400 Subject: [Git][ghc/ghc][wip/T23034] 11 commits: Add hack for #24623 Message-ID: <666ddd24a5808_15cf78614f3241569d3@gitlab.mail> Jens Petersen pushed to branch wip/T23034 at Glasgow Haskell Compiler / GHC Commits: 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - 3b00cf99 by Peter Trommler at 2024-06-15T18:27:45+00:00 Add testcase for #23034 - - - - - a6133f3f by Peter Trommler at 2024-06-15T18:27:45+00:00 Delete test file - - - - - 05a5c688 by Peter Trommler at 2024-06-15T18:27:45+00:00 Compile test with optimisation - - - - - 6d3d8a7a by Peter Trommler at 2024-06-15T18:27:45+00:00 PPC NCG: Fix sign hints in C calls - - - - - 30 changed files: - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Solver/Monad.hs - compiler/GHC/Tc/Types/Constraint.hs - compiler/GHC/Tc/Utils/TcMType.hs - compiler/GHC/Tc/Validity.hs - compiler/GHC/Tc/Zonk/TcType.hs - compiler/GHC/Types/Name/Occurrence.hs - compiler/GHC/Types/Var/Env.hs - + testsuite/tests/codeGen/should_run/T23034.h - + testsuite/tests/codeGen/should_run/T23034.hs - + testsuite/tests/codeGen/should_run/T23034.stdout - + testsuite/tests/codeGen/should_run/T23034_c.c - testsuite/tests/codeGen/should_run/all.T - testsuite/tests/dependent/should_compile/T15743e.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3f128c7d6c145985e3e12fda173e7e9a5a9c03f7...6d3d8a7a7045813d8d9583851738ccb44a6b6e3c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3f128c7d6c145985e3e12fda173e7e9a5a9c03f7...6d3d8a7a7045813d8d9583851738ccb44a6b6e3c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 15 20:18:24 2024 From: gitlab at gitlab.haskell.org (Bodigrim (@Bodigrim)) Date: Sat, 15 Jun 2024 16:18:24 -0400 Subject: [Git][ghc/ghc][wip/Data.List.compareLength] 38 commits: Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw Message-ID: <666df710388b8_15cf78701f4f8159026@gitlab.mail> Bodigrim pushed to branch wip/Data.List.compareLength at Glasgow Haskell Compiler / GHC Commits: edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - cb1d4cef by Andrew Lelechenko at 2024-06-15T21:15:23+01:00 Implement Data.List.compareLength and Data.List.NonEmpty.compareLength `compareLength xs n` is a safer and faster alternative to `compare (length xs) n`. The latter would force and traverse the entire spine (potentially diverging), while the former traverses as few elements as possible. The implementation is carefully designed to maintain as much laziness as possible. As per https://github.com/haskell/core-libraries-committee/issues/257 - - - - - 30 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - CODEOWNERS - compiler/GHC/Builtin/Names.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/JS/Ident.hs - compiler/GHC/JS/JStg/Monad.hs - compiler/GHC/JS/JStg/Syntax.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Syntax.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3feaa3e45860ca7130e3c4c86dc96ebb319455e6...cb1d4cef42afee07ea339f6faca785148e904d06 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3feaa3e45860ca7130e3c4c86dc96ebb319455e6...cb1d4cef42afee07ea339f6faca785148e904d06 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 15 20:39:49 2024 From: gitlab at gitlab.haskell.org (Serge S. Gulin (@gulin.serge)) Date: Sat, 15 Jun 2024 16:39:49 -0400 Subject: [Git][ghc/ghc][wip/T24789_impl] 30 commits: users-guide: Fix stylistic issues in 9.12 release notes Message-ID: <666dfc155d1e0_15cf7873a71841608f5@gitlab.mail> Serge S. Gulin pushed to branch wip/T24789_impl at Glasgow Haskell Compiler / GHC Commits: e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e8086e37 by Serge S. Gulin at 2024-06-15T23:14:19+03:00 Unicode: adding compact version of GeneralCategory (resolves #24789) The following features are applied: 1. Lookup code like Cmm-switches (draft implementation proposed by Sylvain Henry @hsyl20) 2. Nested ifs (logarithmic search vs linear search) (the idea proposed by Sylvain Henry @hsyl20) ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - 30 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Builtin/Names.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Names.hs - compiler/GHC/Runtime/Debugger.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/SysTools/Cpp.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Errors.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Errors/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7f783d986f0ae585621308bbf9acbc66d91e84f5...e8086e374a97cbc61f5bcc3e7623ce5f940f9906 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7f783d986f0ae585621308bbf9acbc66d91e84f5...e8086e374a97cbc61f5bcc3e7623ce5f940f9906 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sat Jun 15 21:07:14 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Sat, 15 Jun 2024 17:07:14 -0400 Subject: [Git][ghc/ghc][wip/T24725] Wibbles Message-ID: <666e0282a64e7_15cf787813de416833d@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24725 at Glasgow Haskell Compiler / GHC Commits: 691fb238 by Simon Peyton Jones at 2024-06-15T12:04:14+01:00 Wibbles - - - - - 2 changed files: - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/TyCo/Compare.hs Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -52,7 +52,7 @@ import GHC.Core.Type as Type import GHC.Core.Multiplicity import GHC.Core.UsageEnv import GHC.Core.TyCo.Rep -- checks validity of types/coercions -import GHC.Core.TyCo.Compare ( eqType, eqTypeIgnoringMultiplicity, eqForAllVis ) +import GHC.Core.TyCo.Compare ( eqType, eqTypes, eqTypeIgnoringMultiplicity, eqForAllVis ) import GHC.Core.TyCo.Subst import GHC.Core.TyCo.FVs import GHC.Core.TyCo.Ppr @@ -2801,7 +2801,7 @@ lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches extra_checks | isNewTyCon tc - = do { CoAxBranch { cab_tvs = tvs + = do { CoAxBranch { cab_tvs = ax_tvs , cab_eta_tvs = eta_tvs , cab_cvs = cvs , cab_roles = roles @@ -2809,14 +2809,10 @@ lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches <- case branch_list of [branch] -> return branch _ -> failWithL (text "multi-branch axiom with newtype") - ; let ax_lhs = mkInfForAllTys tvs $ - mkTyConApp tc lhs_tys - nt_tvs = takeList tvs (tyConTyVars tc) - -- axiom may be eta-reduced: Note [Newtype eta] in GHC.Core.TyCon - nt_lhs = mkInfForAllTys nt_tvs $ - mkTyConApp tc (mkTyVarTys nt_tvs) - -- See Note [Newtype eta] in GHC.Core.TyCon - ; lintL (ax_lhs `eqType` nt_lhs) + + -- The LHS of the axiom is (N lhs_tys) + -- We expect it to be (N ax_tvs) + ; lintL (mkTyVarTys ax_tvs `eqTypes` lhs_tys) (text "Newtype axiom LHS does not match newtype definition") ; lintL (null cvs) (text "Newtype axiom binds coercion variables") @@ -2825,7 +2821,7 @@ lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches (text "Newtype axiom has eta-tvs") ; lintL (ax_role == Representational) (text "Newtype axiom role not representational") - ; lintL (roles `equalLength` tvs) + ; lintL (roles `equalLength` ax_tvs) (text "Newtype axiom roles list is the wrong length." $$ text "roles:" <+> sep (map ppr roles)) ; lintL (roles == takeList roles (tyConRoles tc)) ===================================== compiler/GHC/Core/TyCo/Compare.hs ===================================== @@ -122,33 +122,13 @@ tcEqTyConApps tc1 args1 tc2 args2 -- as differences in earlier (dependent) arguments -{- -Note [Specialising generic_eq_type] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -The type equality predicates in Type are hit pretty hard during typechecking. -Consequently we take pains to ensure that these paths are compiled to -efficient, minimally-allocating code. - -To this end we place an INLINE on tc_eq_type, ensuring that it is inlined into -its publicly-visible interfaces (e.g. tcEqType). In addition to eliminating -some dynamic branches, this allows the simplifier to eliminate the closure -allocations that would otherwise be necessary to capture the two boolean "mode" -flags. This reduces allocations by a good fraction of a percent when compiling -Cabal. - -See #19226. --} - --- | This flag controls whether we expand synonyms during comparison -data SynFlag = ExpandSynonyms | KeepSynonyms - -- | Type equality on lists of types, looking through type synonyms eqTypes :: [Type] -> [Type] -> Bool eqTypes [] [] = True eqTypes (t1:ts1) (t2:ts2) = eqType t1 t2 && eqTypes ts1 ts2 eqTypes _ _ = False -eqVarBndrs :: RnEnv2 -> [Var] -> [Var] -> Maybe RnEnv2 +eqVarBndrs :: HasCallStack => RnEnv2 -> [Var] -> [Var] -> Maybe RnEnv2 -- Check that the var lists are the same length -- and have matching kinds; if so, extend the RnEnv2 -- Returns Nothing if they don't match @@ -165,26 +145,26 @@ initRnEnv ta tb = mkRnEnv2 $ mkInScopeSet $ -- | Type equality comparing both visible and invisible arguments, -- expanding synonyms and respecting multiplicities. -eqType :: Type -> Type -> Bool +eqType :: HasCallStack => Type -> Type -> Bool eqType ta tb = eqTypeX (initRnEnv ta tb) ta tb eqTypeNoKindCheck :: Type -> Type -> Bool eqTypeNoKindCheck ta tb = eq_type_x (initRnEnv ta tb) ta tb -- | Compare types with respect to a (presumably) non-empty 'RnEnv2'. -eqTypeX :: RnEnv2 -> Type -> Type -> Bool +eqTypeX :: HasCallStack => RnEnv2 -> Type -> Type -> Bool eqTypeX env ta tb = eq_type_x env ta tb && eq_type_x env (typeKind ta) (typeKind tb) eq_type_x :: RnEnv2 -> Type -> Type -> Bool -eq_type_x = generic_eq_type_x ExpandSynonyms RespectMultiplicities +eq_type_x = generic_eq_type ExpandSynonyms RespectMultiplicities eqTypeIgnoringMultiplicity :: Type -> Type -> Bool eqTypeIgnoringMultiplicity ta tb = eq init_env ta tb && eq init_env (typeKind ta) (typeKind tb) where - eq = generic_eq_type_x ExpandSynonyms IgnoreMultiplicities + eq = generic_eq_type ExpandSynonyms IgnoreMultiplicities init_env = initRnEnv ta tb -- | Like 'pickyEqTypeVis', but returns a Bool for convenience @@ -193,18 +173,37 @@ pickyEqType :: Type -> Type -> Bool -- So (pickyEqType String [Char]) returns False -- This ignores kinds and coercions, because this is used only for printing. pickyEqType ta tb - = generic_eq_type_x KeepSynonyms RespectMultiplicities (initRnEnv ta tb) ta tb + = generic_eq_type KeepSynonyms RespectMultiplicities (initRnEnv ta tb) ta tb + +{- Note [Specialising generic_eq_type] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The type equality predicates in Type are hit pretty hard during typechecking. +Consequently we take pains to ensure that these paths are compiled to +efficient, minimally-allocating code. + +To this end we place an INLINE on tc_eq_type, ensuring that it is inlined into +its publicly-visible interfaces (e.g. tcEqType). In addition to eliminating +some dynamic branches, this allows the simplifier to eliminate the closure +allocations that would otherwise be necessary to capture the two boolean "mode" +flags. This reduces allocations by a good fraction of a percent when compiling +Cabal. + +See #19226. +-} + +-- | This flag controls whether we expand synonyms during comparison +data SynFlag = ExpandSynonyms | KeepSynonyms -- --------------------------------------------------------------- -- | Real worker for 'eqType'. No kind check! -- Inline it at the (handful of local) call sites -- The "generic" bit refers to the flag paramerisation -generic_eq_type_x :: SynFlag -> MultiplicityFlag +generic_eq_type :: SynFlag -> MultiplicityFlag -> RnEnv2 -> Type -> Type -> Bool -- See Note [Computing equality on types] in Type -{-# INLINE generic_eq_type_x #-} -- See Note [Specialising tc_eq_type]. -generic_eq_type_x syn_flag mult_flag +{-# INLINE generic_eq_type #-} -- See Note [Specialising generic_eq_type]. +generic_eq_type syn_flag mult_flag = go where go_with_kc :: RnEnv2 -> Type -> Type -> Bool @@ -213,6 +212,8 @@ generic_eq_type_x syn_flag mult_flag go :: RnEnv2 -> Type -> Type -> Bool -- See Note [Comparing nullary type synonyms] + go _ t1 t2 | 1# <- reallyUnsafePtrEquality# t1 t2 = True + go _ (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = True go env t1 t2 | ExpandSynonyms <- syn_flag, Just t1' <- coreView t1 = go env t1' t2 @@ -227,8 +228,8 @@ generic_eq_type_x syn_flag mult_flag go env (ForAllTy (Bndr tv1 vis1) ty1) (ForAllTy (Bndr tv2 vis2) ty2) = vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] - && go (rnBndr2 env tv1 tv2) ty1 ty2 && go env (varType tv1) (varType tv2) -- Always do kind-check + && go (rnBndr2 env tv1 tv2) ty1 ty2 -- Make sure we handle all FunTy cases since falling through to the -- AppTy case means that tcSplitAppTyNoView_maybe may see an unzonked View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/691fb23802a952bf06b58a7021b72340d5a75cfd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/691fb23802a952bf06b58a7021b72340d5a75cfd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 16 12:09:31 2024 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Sun, 16 Jun 2024 08:09:31 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/az/T24862-match-pats-loc Message-ID: <666ed5fbb7f69_25132a122f73093467@gitlab.mail> Alan Zimmerman pushed new branch wip/az/T24862-match-pats-loc at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/az/T24862-match-pats-loc You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 16 12:12:51 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 16 Jun 2024 08:12:51 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/supersven/AArch64-delete-unused-RegNos Message-ID: <666ed6c3e93ea_25132a13498dc9841b@gitlab.mail> Sven Tennie pushed new branch wip/supersven/AArch64-delete-unused-RegNos at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/supersven/AArch64-delete-unused-RegNos You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 16 12:35:49 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 16 Jun 2024 08:35:49 -0400 Subject: [Git][ghc/ghc][wip/supersven/ghc-9.10-riscv-ncg] 8 commits: Cleanup register allocation module Message-ID: <666edc25c182f_25132a18034401069d0@gitlab.mail> Sven Tennie pushed to branch wip/supersven/ghc-9.10-riscv-ncg at Glasgow Haskell Compiler / GHC Commits: aff59a72 by Sven Tennie at 2024-06-15T18:27:48+00:00 Cleanup register allocation module - - - - - 8fae51e1 by Sven Tennie at 2024-06-16T12:21:19+00:00 Cleanup free register management - - - - - dd8b2f27 by Sven Tennie at 2024-06-16T12:22:24+00:00 Delete superfluous $ - - - - - 6818bea8 by Sven Tennie at 2024-06-16T12:23:34+00:00 Reformat - - - - - 21d10d75 by Sven Tennie at 2024-06-16T12:25:55+00:00 Add RA to the list of potentially clobbered registers - - - - - d3dcbac0 by Sven Tennie at 2024-06-16T12:27:04+00:00 Haddock and formatting - - - - - 1b2787d2 by Sven Tennie at 2024-06-16T12:29:31+00:00 Delete LLVM lit tests Unfortunately, we aren't using them in the GHC project. - - - - - 0b64352b by Sven Tennie at 2024-06-16T12:33:07+00:00 Increase C compiler happiness Mark unused parameter with STG_UNUSED. - - - - - 9 changed files: - compiler/GHC/CmmToAsm/RV64.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Regs.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs - compiler/GHC/CmmToAsm/Reg/Linear/RV64.hs - rts/linker/elf_reloc_aarch64.c - − tests/compiler/cmm/shift_right.cmm - − tests/compiler/cmm/zero.cmm Changes: ===================================== compiler/GHC/CmmToAsm/RV64.hs ===================================== @@ -1,61 +1,57 @@ {-# OPTIONS_GHC -fno-warn-orphans #-} -- | Native code generator for RiscV64 architectures -module GHC.CmmToAsm.RV64 - ( ncgRV64 ) -where - -import GHC.Prelude +module GHC.CmmToAsm.RV64 (ncgRV64) where +import GHC.CmmToAsm.Config import GHC.CmmToAsm.Instr import GHC.CmmToAsm.Monad -import GHC.CmmToAsm.Config +import GHC.CmmToAsm.RV64.CodeGen qualified as RV64 +import GHC.CmmToAsm.RV64.Instr qualified as RV64 +import GHC.CmmToAsm.RV64.Ppr qualified as RV64 +import GHC.CmmToAsm.RV64.RegInfo qualified as RV64 +import GHC.CmmToAsm.RV64.Regs qualified as RV64 import GHC.CmmToAsm.Types +import GHC.Prelude import GHC.Utils.Outputable (ftext) -import qualified GHC.CmmToAsm.RV64.Instr as RV64 -import qualified GHC.CmmToAsm.RV64.Ppr as RV64 -import qualified GHC.CmmToAsm.RV64.CodeGen as RV64 -import qualified GHC.CmmToAsm.RV64.Regs as RV64 -import qualified GHC.CmmToAsm.RV64.RegInfo as RV64 - ncgRV64 :: NCGConfig -> NcgImpl RawCmmStatics RV64.Instr RV64.JumpDest -ncgRV64 config - = NcgImpl { - ncgConfig = config - ,cmmTopCodeGen = RV64.cmmTopCodeGen - ,generateJumpTableForInstr = RV64.generateJumpTableForInstr config - ,getJumpDestBlockId = RV64.getJumpDestBlockId - ,canShortcut = RV64.canShortcut - ,shortcutStatics = RV64.shortcutStatics - ,shortcutJump = RV64.shortcutJump - ,pprNatCmmDeclS = RV64.pprNatCmmDecl config - ,pprNatCmmDeclH = RV64.pprNatCmmDecl config - ,maxSpillSlots = RV64.maxSpillSlots config - ,allocatableRegs = RV64.allocatableRegs platform - ,ncgAllocMoreStack = RV64.allocMoreStack platform - ,ncgMakeFarBranches = RV64.makeFarBranches - ,extractUnwindPoints = const [] - ,invertCondBranches = \_ _ -> id - } - where - platform = ncgPlatform config +ncgRV64 config = + NcgImpl + { ncgConfig = config, + cmmTopCodeGen = RV64.cmmTopCodeGen, + generateJumpTableForInstr = RV64.generateJumpTableForInstr config, + getJumpDestBlockId = RV64.getJumpDestBlockId, + canShortcut = RV64.canShortcut, + shortcutStatics = RV64.shortcutStatics, + shortcutJump = RV64.shortcutJump, + pprNatCmmDeclS = RV64.pprNatCmmDecl config, + pprNatCmmDeclH = RV64.pprNatCmmDecl config, + maxSpillSlots = RV64.maxSpillSlots config, + allocatableRegs = RV64.allocatableRegs platform, + ncgAllocMoreStack = RV64.allocMoreStack platform, + ncgMakeFarBranches = RV64.makeFarBranches, + extractUnwindPoints = const [], + invertCondBranches = \_ _ -> id + } + where + platform = ncgPlatform config --- | Instruction instance for RV64 +-- | `Instruction` instance for RV64 instance Instruction RV64.Instr where - regUsageOfInstr = RV64.regUsageOfInstr - patchRegsOfInstr = RV64.patchRegsOfInstr - isJumpishInstr = RV64.isJumpishInstr - jumpDestsOfInstr = RV64.jumpDestsOfInstr - patchJumpInstr = RV64.patchJumpInstr - mkSpillInstr = RV64.mkSpillInstr - mkLoadInstr = RV64.mkLoadInstr - takeDeltaInstr = RV64.takeDeltaInstr - isMetaInstr = RV64.isMetaInstr - mkRegRegMoveInstr _ = RV64.mkRegRegMoveInstr - takeRegRegMoveInstr = RV64.takeRegRegMoveInstr - mkJumpInstr = RV64.mkJumpInstr - mkStackAllocInstr = RV64.mkStackAllocInstr - mkStackDeallocInstr = RV64.mkStackDeallocInstr - mkComment = pure . RV64.COMMENT . ftext - pprInstr = RV64.pprInstr + regUsageOfInstr = RV64.regUsageOfInstr + patchRegsOfInstr = RV64.patchRegsOfInstr + isJumpishInstr = RV64.isJumpishInstr + jumpDestsOfInstr = RV64.jumpDestsOfInstr + patchJumpInstr = RV64.patchJumpInstr + mkSpillInstr = RV64.mkSpillInstr + mkLoadInstr = RV64.mkLoadInstr + takeDeltaInstr = RV64.takeDeltaInstr + isMetaInstr = RV64.isMetaInstr + mkRegRegMoveInstr _ = RV64.mkRegRegMoveInstr + takeRegRegMoveInstr = RV64.takeRegRegMoveInstr + mkJumpInstr = RV64.mkJumpInstr + mkStackAllocInstr = RV64.mkStackAllocInstr + mkStackDeallocInstr = RV64.mkStackDeallocInstr + mkComment = pure . RV64.COMMENT . ftext + pprInstr = RV64.pprInstr ===================================== compiler/GHC/CmmToAsm/RV64/Instr.hs ===================================== @@ -1,8 +1,6 @@ {-# OPTIONS_GHC -fno-warn-orphans #-} -module GHC.CmmToAsm.RV64.Instr - -where +module GHC.CmmToAsm.RV64.Instr where import GHC.Prelude @@ -49,8 +47,7 @@ stackFrameHeaderSize = 2 * spillSlotSize spillSlotSize :: Int spillSlotSize = 8 --- | The number of bytes that the stack pointer should be aligned --- to. +-- | The number of bytes that the stack pointer should be aligned to. stackAlign :: Int stackAlign = 16 @@ -60,11 +57,14 @@ maxSpillSlots config = ((ncgSpillPreallocSize config - stackFrameHeaderSize) `div` spillSlotSize) - 1 --- | Convert a spill slot number to a *byte* offset, with no sign. +-- | Convert a spill slot number to a *byte* offset. spillSlotToOffset :: Int -> Int spillSlotToOffset slot = stackFrameHeaderSize + spillSlotSize * slot +instance Outputable RegUsage where + ppr (RU reads writes) = text "RegUsage(reads:" <+> ppr reads <> comma <+> text "writes:" <+> ppr writes <> char ')' + -- | Get the registers that are being used by this instruction. -- regUsage doesn't need to do any trickery for jumps and such. -- Just state precisely the regs read and written by that insn. @@ -72,12 +72,9 @@ spillSlotToOffset slot -- allocation goes, are taken care of by the register allocator. -- -- RegUsage = RU [] [] - -instance Outputable RegUsage where - ppr (RU reads writes) = text "RegUsage(reads:" <+> ppr reads <> comma <+> text "writes:" <+> ppr writes <> char ')' - regUsageOfInstr :: Platform -> Instr -> RegUsage regUsageOfInstr platform instr = case instr of + -- 0. Meta Instructions ANN _ i -> regUsageOfInstr platform i COMMENT{} -> usage ([], []) MULTILINE_COMMENT{} -> usage ([], []) @@ -122,7 +119,6 @@ regUsageOfInstr platform instr = case instr of CSET dst l r _ -> usage (regOp l ++ regOp r, regOp dst) -- 7. Load and Store Instructions -------------------------------------------- STR _ src dst -> usage (regOp src ++ regOp dst, []) - -- STLR _ src dst L -> usage (regOp src ++ regOp dst, []) LDR _ dst src -> usage (regOp src, regOp dst) LDRU _ dst src -> usage (regOp src, regOp dst) @@ -160,41 +156,21 @@ regUsageOfInstr platform instr = case instr of -- Is this register interesting for the register allocator? interesting :: Platform -> Reg -> Bool interesting _ (RegVirtual _) = True - interesting _ (RegReal (RealRegSingle (-1))) = False interesting platform (RegReal (RealRegSingle i)) = freeReg platform i --- Save caller save registers --- This is x0-x18 --- --- For SIMD/FP Registers: --- Registers v8-v15 must be preserved by a callee across subroutine calls; --- the remaining registers (v0-v7, v16-v31) do not need to be preserved (or --- should be preserved by the caller). Additionally, only the bottom 64 bits --- of each value stored in v8-v15 need to be preserved [7]; it is the --- responsibility of the caller to preserve larger values. +-- | Caller-saved registers (according to calling convention) -- --- .---------------------------------------------------------------------------------------------------------------------------------------------------------------. --- | 0 | 1 | 2 | 3 | 4 | 5 | 6 | 7 | 8 | 9 | 10 | 11 | 12 | 13 | 14 | 15 | 16 | 17 | 18 | 19 | 20 | 21 | 22 | 23 | 24 | 25 | 26 | 27 | 28 | 29 | 30 | 31 | --- | 32 | 33 | 34 | 35 | 36 | 37 | 38 | 39 | 40 | 41 | 42 | 42 | 44 | 45 | 46 | 47 | 48 | 49 | 50 | 51 | 52 | 53 | 54 | 55 | 56 | 57 | 58 | 59 | 60 | 61 | 62 | 63 | --- |== General Purpose registers ==================================================================================================================================| --- | ZR | RA | SP | GP | TP | <- tmp r. -> | FP | <- | <---- argument passing -------------> | -- callee saved ------------------------------> | <--- tmp regs --> | --- | -- | -- | -- | -- | -- | <- free r. > | -- | BR | <---- free registers ---------------> | SP | HP | R1 | R2 | R3 | R4 | R5 | R6 | R7 | SL | <-- free regs --> | --- |== SIMD/FP Registers ==========================================================================================================================================| --- | <--- temporary registers -----------> | <------ | <---- argument passing -------------> | -- callee saved ------------------------------> | <--- tmp regs --> | --- | <---------- free registers ---------> | F1 | F2 | <---- free registers ---------------> | F3 | F4 | F5 | F6 | D1 | D2 | D3 | D4 | D5 | D6 | -- | -- | -- | -- | --- '---------------------------------------------------------------------------------------------------------------------------------------------------------------' --- ZR: Zero, RA: Return Address, SP: Stack Pointer, GP: Global Pointer, TP: Thread Pointer, FP: Frame Pointer --- BR: Base, SL: SpLim +-- These registers may be clobbered after a jump. callerSavedRegisters :: [Reg] callerSavedRegisters = - map regSingle [t0RegNo .. t2RegNo] + [regSingle raRegNo] + ++ map regSingle [t0RegNo .. t2RegNo] ++ map regSingle [a0RegNo .. a7RegNo] ++ map regSingle [t3RegNo .. t6RegNo] ++ map regSingle [ft0RegNo .. ft7RegNo] ++ map regSingle [fa0RegNo .. fa7RegNo] --- | Apply a given mapping to all the register references in this --- instruction. +-- | Apply a given mapping to all the register references in this instruction. patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr patchRegsOfInstr instr env = case instr of -- 0. Meta Instructions @@ -525,6 +501,7 @@ allocMoreStack platform slots proc@(CmmProc info lbl live (ListGraph code)) = do -- This most notably leaves out B. (Bit Manipulation) instructions. data Instr + -- 0. Pseudo Instructions -------------------------------------------------- -- comment pseudo-op = COMMENT SDoc | MULTILINE_COMMENT SDoc @@ -550,7 +527,6 @@ data Instr -- benefit of subsequent passes | DELTA Int - -- 0. Pseudo Instructions -------------------------------------------------- | PUSH_STACK_FRAME | POP_STACK_FRAME ===================================== compiler/GHC/CmmToAsm/RV64/Regs.hs ===================================== @@ -22,6 +22,11 @@ import GHC.Platform x0RegNo :: RegNo x0RegNo = 0 +-- | return address register +x1RegNo, raRegNo :: RegNo +x1RegNo = 1 +raRegNo = x1RegNo + x5RegNo, t0RegNo :: RegNo x5RegNo = 5 t0RegNo = x5RegNo ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -222,7 +222,7 @@ linearRegAlloc config entry_ids block_live sccs ArchAlpha -> panic "linearRegAlloc ArchAlpha" ArchMipseb -> panic "linearRegAlloc ArchMipseb" ArchMipsel -> panic "linearRegAlloc ArchMipsel" - ArchRISCV64 -> go $ (frInitFreeRegs platform :: RV64.FreeRegs) + ArchRISCV64 -> go (frInitFreeRegs platform :: RV64.FreeRegs) ArchLoongArch64-> panic "linearRegAlloc ArchLoongArch64" ArchJavaScript -> panic "linearRegAlloc ArchJavaScript" ArchWasm32 -> panic "linearRegAlloc ArchWasm32" ===================================== compiler/GHC/CmmToAsm/Reg/Linear/FreeRegs.hs ===================================== @@ -67,10 +67,10 @@ instance FR AArch64.FreeRegs where frReleaseReg = \_ -> AArch64.releaseReg instance FR RV64.FreeRegs where - frAllocateReg = \_ -> RV64.allocateReg - frGetFreeRegs = \_ -> RV64.getFreeRegs + frAllocateReg = const RV64.allocateReg + frGetFreeRegs = const RV64.getFreeRegs frInitFreeRegs = RV64.initFreeRegs - frReleaseReg = \_ -> RV64.releaseReg + frReleaseReg = const RV64.releaseReg maxSpillSlots :: NCGConfig -> Int maxSpillSlots config = case platformArch (ncgPlatform config) of ===================================== compiler/GHC/CmmToAsm/Reg/Linear/RV64.hs ===================================== @@ -1,65 +1,96 @@ -module GHC.CmmToAsm.Reg.Linear.RV64 where - -import GHC.Prelude +-- | Functions to implement the @FR@ (as in "free regs") type class. +-- +-- For LLVM GHC calling convention (used registers), see +-- https://github.com/llvm/llvm-project/blob/6ab900f8746e7d8e24afafb5886a40801f6799f4/llvm/lib/Target/RISCV/RISCVISelLowering.cpp#L13638-L13685 +module GHC.CmmToAsm.Reg.Linear.RV64 + ( allocateReg, + getFreeRegs, + initFreeRegs, + releaseReg, + FreeRegs (..), + ) +where +import Data.Word import GHC.CmmToAsm.RV64.Regs -import GHC.Platform.Reg.Class +import GHC.Platform import GHC.Platform.Reg - +import GHC.Platform.Reg.Class +import GHC.Prelude +import GHC.Stack import GHC.Utils.Outputable import GHC.Utils.Panic -import GHC.Platform - -import Data.Word - -import GHC.Stack -data FreeRegs = FreeRegs !Word32 !Word32 +-- | Bitmaps to indicate which registers are free (currently unused) +-- +-- The bit index represents the `RegNo`, in case of floating point registers +-- with an offset of 32. The register is free when the bit is set. +data FreeRegs + = FreeRegs + -- | integer/general purpose registers (`RcInteger`) + !Word32 + -- | floating point registers (`RcDouble`) + !Word32 instance Show FreeRegs where - show (FreeRegs g f) = "FreeRegs: " ++ showBits g ++ "; " ++ showBits f - -instance Outputable FreeRegs where - ppr (FreeRegs g f) = text " " <+> foldr (\i x -> pad_int i <+> x) (text "") [0..31] - $$ text "GPR" <+> foldr (\i x -> show_bit g i <+> x) (text "") [0..31] - $$ text "FPR" <+> foldr (\i x -> show_bit f i <+> x) (text "") [0..31] - where pad_int i | i < 10 = char ' ' <> int i - pad_int i = int i - -- remember bit = 1 means it's available. - show_bit bits bit | testBit bits bit = text " " - show_bit _ _ = text " x" - -noFreeRegs :: FreeRegs -noFreeRegs = FreeRegs 0 0 + show (FreeRegs g f) = "FreeRegs 0b" ++ showBits g ++ " 0b" ++ showBits f +-- | Show bits as a `String` of @1 at s and @0 at s showBits :: Word32 -> String -showBits w = map (\i -> if testBit w i then '1' else '0') [0..31] +showBits w = map (\i -> if testBit w i then '1' else '0') [0 .. 31] --- FR instance implementation (See Linear.FreeRegs) -allocateReg :: HasCallStack => RealReg -> FreeRegs -> FreeRegs -allocateReg (RealRegSingle r) (FreeRegs g f) - | r > 31 && testBit f (r - 32) = FreeRegs g (clearBit f (r - 32)) - | r < 32 && testBit g r = FreeRegs (clearBit g r) f - | r > 31 = panic $ "Linear.RV64.allocReg: double allocation of float reg v" ++ show (r - 32) ++ "; " ++ showBits f - | otherwise = pprPanic "Linear.RV64.allocReg" $ text ("double allocation of gp reg x" ++ show r ++ "; " ++ showBits g) - --- For LLVM Interop, see https://github.com/llvm/llvm-project/blob/6ab900f8746e7d8e24afafb5886a40801f6799f4/llvm/lib/Target/RISCV/RISCVISelLowering.cpp#L13638-L13685 -getFreeRegs :: RegClass -> FreeRegs -> [RealReg] -getFreeRegs cls (FreeRegs g f) - | RcFloat <- cls = [] -- For now we only support double and integer registers, floats will need to be promoted. - | RcDouble <- cls = go 32 f [0..31] - | RcInteger <- cls = go 0 g ([5..7] ++ [10..17] ++ [28..31]) +instance Outputable FreeRegs where + ppr (FreeRegs g f) = + text " " + <+> foldr (\i x -> pad_int i <+> x) (text "") [0 .. 31] + $$ text "GPR" + <+> foldr (\i x -> show_bit g i <+> x) (text "") [0 .. 31] + $$ text "FPR" + <+> foldr (\i x -> show_bit f i <+> x) (text "") [0 .. 31] where - go _ _ [] = [] - go off x (i:is) | testBit x i = RealRegSingle (off + i) : (go off x $! is) - | otherwise = go off x $! is + pad_int i | i < 10 = char ' ' <> int i + pad_int i = int i + -- remember bit = 1 means it's available. + show_bit bits bit | testBit bits bit = text " " + show_bit _ _ = text " x" +-- | Set bits of all allocatable registers to 1 initFreeRegs :: Platform -> FreeRegs initFreeRegs platform = foldl' (flip releaseReg) noFreeRegs (allocatableRegs platform) + where + noFreeRegs :: FreeRegs + noFreeRegs = FreeRegs 0 0 + +-- | Get all free `RealReg`s (i.e. those where the corresponding bit is 1) +getFreeRegs :: RegClass -> FreeRegs -> [RealReg] +getFreeRegs cls (FreeRegs g f) + | RcFloat <- cls = [] -- For now we only support double and integer registers, floats will need to be promoted. + | RcDouble <- cls = go 32 f allocatableDoubleRegs + | RcInteger <- cls = go 0 g allocatableIntRegs + where + go _ _ [] = [] + go off x (i : is) + | testBit x i = RealRegSingle (off + i) : (go off x $! is) + | otherwise = go off x $! is + -- The lists of allocatable registers are manually crafted: Register + -- allocation is pretty hot code. We don't want to iterate and map like + -- `initFreeRegs` all the time! (The register mappings aren't supposed to + -- change often.) + allocatableIntRegs = [5 .. 7] ++ [10 .. 17] ++ [28 .. 30] + allocatableDoubleRegs = [0 .. 7] ++ [10 .. 17] ++ [28 .. 31] + +-- | Set corresponding register bit to 0 +allocateReg :: (HasCallStack) => RealReg -> FreeRegs -> FreeRegs +allocateReg (RealRegSingle r) (FreeRegs g f) + | r > 31 && testBit f (r - 32) = FreeRegs g (clearBit f (r - 32)) + | r < 32 && testBit g r = FreeRegs (clearBit g r) f + | r > 31 = panic $ "Linear.RV64.allocReg: double allocation of float reg v" ++ show (r - 32) ++ "; " ++ showBits f + | otherwise = pprPanic "Linear.RV64.allocReg" $ text ("double allocation of gp reg x" ++ show r ++ "; " ++ showBits g) -releaseReg :: HasCallStack => RealReg -> FreeRegs -> FreeRegs +-- | Set corresponding register bit to 1 +releaseReg :: (HasCallStack) => RealReg -> FreeRegs -> FreeRegs releaseReg (RealRegSingle r) (FreeRegs g f) - | r > 31 && testBit f (r - 32) = pprPanic "Linear.RV64.releaseReg" (text "can't release non-allocated reg v" <> int (r - 32)) + | r > 31 && testBit f (r - 32) = pprPanic "Linear.RV64.releaseReg" (text "can't release non-allocated reg v" <> int (r - 32)) | r < 32 && testBit g r = pprPanic "Linear.RV64.releaseReg" (text "can't release non-allocated reg x" <> int r) | r > 31 = FreeRegs g (setBit f (r - 32)) - | otherwise = FreeRegs (setBit g r) f \ No newline at end of file + | otherwise = FreeRegs (setBit g r) f ===================================== rts/linker/elf_reloc_aarch64.c ===================================== @@ -339,7 +339,7 @@ relocateObjectCodeAarch64(ObjectCode * oc) { return EXIT_SUCCESS; } -void flushInstructionCacheAarch64(ObjectCode * oc) { +void flushInstructionCacheAarch64(ObjectCode * oc STG_UNUSED) { // Looks like we don't need this on Aarch64. /* no-op */ } ===================================== tests/compiler/cmm/shift_right.cmm deleted ===================================== @@ -1,24 +0,0 @@ -// RUN: "$HC" -debug -dppr-debug -cpp -dcmm-lint -keep-s-file -O0 -c "$1" && cat "${1%%.*}.s" | FileCheck "$1" -check-prefix=CHECK-RV64 -// RUN: "$CC" "${1%%.*}.o" -o "${1%%.*}.exe" -// RUN: "$EXEC" "${1%%.cmm}.exe" - -#include "Cmm.h" -#include "Types.h" - -main() { - I64 buffer; - I32 a, b, c, d; - - I64 arr; - (arr) = foreign "C" malloc(1024); - bits64[arr] = 2; - - a = I32[arr]; - b = %mul(a, 32 :: I32); - c = %neg(b); - d = %shra(c, 4::I64); - - foreign "C" printf("a: %hd b: %hd c: %hd d: %hd", a, b, c, d); - - foreign "C" exit(d == -4 :: I32); -} ===================================== tests/compiler/cmm/zero.cmm deleted ===================================== @@ -1,14 +0,0 @@ -// RUN: "$HC" -cpp -dcmm-lint -keep-s-file -c "$1" && cat "${1%%.*}.s" | FileCheck "$1" -check-prefix=CHECK-RV64 -// RUN: "$CC" "${1%%.*}.o" -o "${1%%.*}.exe" -// RUN: "$EXEC" "${1%%.cmm}.exe" - -#include "Cmm.h" -#include "Types.h" - -main(){ - I64 zero; - // Should refer to the zero register - // CHECK-RV64: addi t0, zero, 0 - zero = 0; - foreign "C" exit(zero); -} View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/68248914206de3db164c16b15a29d0361fed2802...0b64352ba474f1fe1bab41b6620afdcdd2994d97 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/68248914206de3db164c16b15a29d0361fed2802...0b64352ba474f1fe1bab41b6620afdcdd2994d97 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 16 15:55:11 2024 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Sun, 16 Jun 2024 11:55:11 -0400 Subject: [Git][ghc/ghc][wip/az/T24862-match-pats-loc] EPA: Add location to Match Pats list Message-ID: <666f0adf78582_112fee14e7c48353ac@gitlab.mail> Alan Zimmerman pushed to branch wip/az/T24862-match-pats-loc at Glasgow Haskell Compiler / GHC Commits: 30802cd5 by Alan Zimmerman at 2024-06-16T16:54:51+01:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - 30 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/Language/Haskell/Syntax/Expr.hs - testsuite/tests/ghc-api/exactprint/T22919.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/30802cd5942e69b6fa55b6a03d6b891ed5d868ec -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/30802cd5942e69b6fa55b6a03d6b891ed5d868ec You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 16 17:32:06 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 16 Jun 2024 13:32:06 -0400 Subject: [Git][ghc/ghc][wip/supersven/ghc-9.10-riscv-ncg] 5 commits: Revert formatting-only change in elf_got.c Message-ID: <666f2196cbf81_1a6c0e6826d0650a1@gitlab.mail> Sven Tennie pushed to branch wip/supersven/ghc-9.10-riscv-ncg at Glasgow Haskell Compiler / GHC Commits: decac423 by Sven Tennie at 2024-06-16T12:57:52+00:00 Revert formatting-only change in elf_got.c - - - - - ee06f4bf by Sven Tennie at 2024-06-16T12:58:13+00:00 Add CODEOWNERS entry - - - - - 05e0f4dd by Sven Tennie at 2024-06-16T13:47:24+00:00 Cleanup RegInfo - - - - - 2d336c47 by Sven Tennie at 2024-06-16T13:51:45+00:00 Delete ToDo - - - - - 0cdebb64 by Sven Tennie at 2024-06-16T13:58:05+00:00 fixup! Cleanup RegInfo - - - - - 4 changed files: - CODEOWNERS - compiler/GHC/CmmToAsm/RV64/RegInfo.hs - compiler/GHC/Driver/DynFlags.hs - rts/linker/elf_got.c Changes: ===================================== CODEOWNERS ===================================== @@ -40,6 +40,7 @@ /compiler/GHC/HsToCore/Foreign/Wasm.hs @TerrorJack /compiler/GHC/Tc/Deriv/ @RyanGlScott /compiler/GHC/CmmToAsm/ @simonmar @bgamari @AndreasK +/compiler/GHC/CmmToAsm/RV64/ @supersven @angerman /compiler/GHC/CmmToAsm/Wasm/ @TerrorJack /compiler/GHC/CmmToLlvm/ @angerman /compiler/GHC/StgToCmm/ @simonmar @osa1 ===================================== compiler/GHC/CmmToAsm/RV64/RegInfo.hs ===================================== @@ -1,31 +1,41 @@ -module GHC.CmmToAsm.RV64.RegInfo where +-- | Minimum viable implementation of jump short-cutting: No short-cutting. +-- +-- The functions here simply implement the no-short-cutting case. Implementing +-- the real behaviour would be a great optimization in future. +module GHC.CmmToAsm.RV64.RegInfo + ( getJumpDestBlockId, + canShortcut, + shortcutStatics, + shortcutJump, + JumpDest (..), + ) +where -import GHC.Prelude - -import GHC.CmmToAsm.RV64.Instr -import GHC.Cmm.BlockId import GHC.Cmm - +import GHC.Cmm.BlockId +import GHC.CmmToAsm.RV64.Instr +import GHC.Prelude import GHC.Utils.Outputable -data JumpDest = DestBlockId BlockId +newtype JumpDest = DestBlockId BlockId --- Debug Instance instance Outputable JumpDest where ppr (DestBlockId bid) = text "jd:" <> ppr bid --- TODO: documen what this does. See Ticket 19914 +-- | Extract BlockId +-- +-- Never `Nothing` for Riscv64 NCG. getJumpDestBlockId :: JumpDest -> Maybe BlockId getJumpDestBlockId (DestBlockId bid) = Just bid --- TODO: document what this does. See Ticket 19914 +-- No `Instr`s can bet shortcut (for now) canShortcut :: Instr -> Maybe JumpDest canShortcut _ = Nothing --- TODO: document what this does. See Ticket 19914 +-- Identity of the provided `RawCmmStatics` shortcutStatics :: (BlockId -> Maybe JumpDest) -> RawCmmStatics -> RawCmmStatics shortcutStatics _ other_static = other_static --- TODO: document what this does. See Ticket 19914 +-- Identity of the provided `Instr` shortcutJump :: (BlockId -> Maybe JumpDest) -> Instr -> Instr -shortcutJump _ other = other \ No newline at end of file +shortcutJump _ other = other ===================================== compiler/GHC/Driver/DynFlags.hs ===================================== @@ -1325,7 +1325,6 @@ default_PIC platform = (OSDarwin, ArchAArch64) -> [Opt_PIC] (OSLinux, ArchAArch64) -> [Opt_PIC, Opt_ExternalDynamicRefs] (OSLinux, ArchARM {}) -> [Opt_PIC, Opt_ExternalDynamicRefs] - -- TODO: Check if we need ExternalDynamicRefs on RISCV64 (OSLinux, ArchRISCV64 {}) -> [Opt_PIC, Opt_ExternalDynamicRefs] (OSOpenBSD, ArchX86_64) -> [Opt_PIC] -- Due to PIE support in -- OpenBSD since 5.3 release ===================================== rts/linker/elf_got.c ===================================== @@ -9,20 +9,22 @@ * Check if we need a global offset table slot for a * given symbol */ -bool needGotSlot(Elf_Sym *symbol) { - /* using global here should give an upper bound */ - /* I don't believe we need to relocate STB_LOCAL - * symbols via the GOT; however I'm unsure about - * STB_WEAK. - * - * Any more restrictive filter here would result - * in a smaller GOT, which is preferable. - */ - return ELF_ST_BIND(symbol->st_info) == STB_GLOBAL || - ELF_ST_BIND(symbol->st_info) == STB_WEAK - // Section symbols exist primarily for relocation - // and as such may need a GOT slot. - || ELF_ST_TYPE(symbol->st_info) == STT_SECTION; +bool +needGotSlot(Elf_Sym * symbol) { + /* using global here should give an upper bound */ + /* I don't believe we need to relocate STB_LOCAL + * symbols via the GOT; however I'm unsure about + * STB_WEAK. + * + * Any more restrictive filter here would result + * in a smaller GOT, which is preferable. + */ + return ELF_ST_BIND(symbol->st_info) == STB_GLOBAL + || ELF_ST_BIND(symbol->st_info) == STB_WEAK + // Section symbols exist primarily for relocation + // and as such may need a GOT slot. + || ELF_ST_TYPE(symbol->st_info) == STT_SECTION; + } bool View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0b64352ba474f1fe1bab41b6620afdcdd2994d97...0cdebb64c50626c203a42fa16af11e6ebc8be64b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/0b64352ba474f1fe1bab41b6620afdcdd2994d97...0cdebb64c50626c203a42fa16af11e6ebc8be64b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 16 17:48:56 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Sun, 16 Jun 2024 13:48:56 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/supersven/AArch64-simplify-BL-instruction Message-ID: <666f25884f626_1a6c0e92254867189@gitlab.mail> Sven Tennie pushed new branch wip/supersven/AArch64-simplify-BL-instruction at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/supersven/AArch64-simplify-BL-instruction You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 16 18:37:46 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sun, 16 Jun 2024 14:37:46 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: PPC: display foreign label in panic message (cf #23969) Message-ID: <666f30fad456b_1a6c0eebae6072784@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - cc673e77 by Andrew Lelechenko at 2024-06-16T14:37:29-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 5b92a7b6 by Alan Zimmerman at 2024-06-16T14:37:31-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - 30 changed files: - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3bb45f0523c4a8bde8639dd8bf694791afcc0d11...5b92a7b68f004935c961995736575380d1c3dd79 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3bb45f0523c4a8bde8639dd8bf694791afcc0d11...5b92a7b68f004935c961995736575380d1c3dd79 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 16 19:47:52 2024 From: gitlab at gitlab.haskell.org (Hannes Siebenhandl (@fendor)) Date: Sun, 16 Jun 2024 15:47:52 -0400 Subject: [Git][ghc/ghc][wip/perf-ci] 96 commits: utils: add hie.yaml config file for ghc-config Message-ID: <666f4168824d1_2102e793603429187@gitlab.mail> Hannes Siebenhandl pushed to branch wip/perf-ci at Glasgow Haskell Compiler / GHC Commits: 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - 67519efa by Fendor at 2024-06-15T14:25:10+02:00 testsuite: Add support to capture performance metrics via 'perf' Performance metrics collected via 'perf' can be more accurate for run-time performance than GHC's rts, due to the usage of hardware counters. We allow performance tests to also record PMU events according to 'perf list'. - - - - - 4df78e91 by Fendor at 2024-06-15T14:25:10+02:00 hadrian: Pass 'perf' program to the test suite if it can be found Currently, we only look for 'perf' on '$PATH' with no way of customisation. This might change in the future. - - - - - 6a690e7e by Fendor at 2024-06-15T14:25:55+02:00 gitlab-ci: Add nightly job for running the testsuite with perf profiling support - - - - - cff7c854 by Fendor at 2024-06-15T14:26:01+02:00 Enable perf profiling for compiler performance tests - - - - - 30 changed files: - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/37aefa11f42de8169c7ea60a99d4b162096080c2...cff7c854d6b3b494c71a15dc3f8a41b19c49796c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/37aefa11f42de8169c7ea60a99d4b162096080c2...cff7c854d6b3b494c71a15dc3f8a41b19c49796c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 16 20:08:39 2024 From: gitlab at gitlab.haskell.org (Adam Gundry (@adamgundry)) Date: Sun, 16 Jun 2024 16:08:39 -0400 Subject: [Git][ghc/ghc][wip/amg/module-cycle-error] Use structured error representation when reloading a nonexistent module Message-ID: <666f4647b3463_2102e7d3faf43480@gitlab.mail> Adam Gundry pushed to branch wip/amg/module-cycle-error at Glasgow Haskell Compiler / GHC Commits: 407640d3 by Adam Gundry at 2024-06-16T21:07:48+01:00 Use structured error representation when reloading a nonexistent module - - - - - 3 changed files: - compiler/GHC/Driver/Make.hs - testsuite/tests/ghc-e/should_fail/T18441fail5.stderr - testsuite/tests/ghci/scripts/ghci021.stderr Changes: ===================================== compiler/GHC/Driver/Make.hs ===================================== @@ -723,9 +723,9 @@ load' mhmi_cache how_much diag_wrapper mHscMessage mod_graph = do checkMod m and_then | m `Set.member` all_home_mods = and_then | otherwise = do - liftIO $ errorMsg logger - (text "no such module:" <+> quotes (ppr (moduleUnit m) <> colon <> ppr (moduleName m))) - return Failed + throwOneError $ mkPlainErrorMsgEnvelope noSrcSpan + $ GhcDriverMessage + $ DriverModuleNotFound (moduleName m) checkHowMuch how_much $ do ===================================== testsuite/tests/ghc-e/should_fail/T18441fail5.stderr ===================================== @@ -1,3 +1,4 @@ +: error: [GHC-82272] + module ‘Abcde’ cannot be found locally -: error: no such module: ‘main:Abcde’ 1 ===================================== testsuite/tests/ghci/scripts/ghci021.stderr ===================================== @@ -1,2 +1,3 @@ +: error: [GHC-82272] + module ‘ThisDoesNotExist’ cannot be found locally -: error: no such module: ‘main:ThisDoesNotExist’ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/407640d39aba1a20bf8aebe64ec63942394ce24c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/407640d39aba1a20bf8aebe64ec63942394ce24c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 16 20:14:45 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Sun, 16 Jun 2024 16:14:45 -0400 Subject: [Git][ghc/ghc][wip/T14030] 42 commits: StgToCmm: refactor opTranslate and friends Message-ID: <666f47b5c35fc_2102e7e9ea5835314@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - 2ed8ed6a by Sebastian Graf at 2024-06-16T20:14:37+00:00 Derive previously hand-written `Lift` instances (#14030) This is possible now that #22229 is fixed. - - - - - 223aedd6 by Sebastian Graf at 2024-06-16T20:14:37+00:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. - - - - - 30 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - CODEOWNERS - compiler/GHC/Builtin/Names.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Driver/Config/StgToCmm.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/JS/Ident.hs - compiler/GHC/JS/JStg/Monad.hs - compiler/GHC/JS/JStg/Syntax.hs - compiler/GHC/JS/Make.hs - compiler/GHC/JS/Syntax.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/42fdf7f08cc44c90d75f29f8c5338829f15aed28...223aedd653f6bacdee9bdd13cd0e77f1eb7678e4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/42fdf7f08cc44c90d75f29f8c5338829f15aed28...223aedd653f6bacdee9bdd13cd0e77f1eb7678e4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 16 20:44:15 2024 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Sun, 16 Jun 2024 16:44:15 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/az/T12842-ttg-fixity Message-ID: <666f4e9f60e87_2102e712bf3f845295@gitlab.mail> Alan Zimmerman pushed new branch wip/az/T12842-ttg-fixity at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/az/T12842-ttg-fixity You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 16 21:58:07 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sun, 16 Jun 2024 17:58:07 -0400 Subject: [Git][ghc/ghc][master] Make flip representation polymorphic, similar to ($) and (&) Message-ID: <666f5fef92b00_2102e721a1c685738d@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 10 changed files: - libraries/base/changelog.md - libraries/ghc-internal/src/GHC/Internal/Base.hs - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/typecheck/should_compile/abstract_refinement_hole_fits.stderr - testsuite/tests/typecheck/should_compile/holes.stderr - testsuite/tests/typecheck/should_compile/holes3.stderr - testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr Changes: ===================================== libraries/base/changelog.md ===================================== @@ -3,6 +3,7 @@ ## 4.21.0.0 *TBA* * Add the `MonadFix` instance for `(,) a`, similar to the one for `Writer a` ([CLC proposal #238](https://github.com/haskell/core-libraries-committee/issues/238)) * Improve `toInteger :: Word32 -> Integer` on 64-bit platforms ([CLC proposal #259](https://github.com/haskell/core-libraries-committee/issues/259)) + * Make `flip` representation polymorphic ([CLC proposal #245](https://github.com/haskell/core-libraries-committee/issues/245)) * The `HasField` class now supports representation polymorphism ([CLC proposal #194](https://github.com/haskell/core-libraries-committee/issues/194)) * Make `read` accept binary integer notation ([CLC proposal #177](https://github.com/haskell/core-libraries-committee/issues/177)) * Improve the performance of `Data.List.sort` using an improved merging strategy. Instead of `compare`, `sort` now uses `(>)` which may break *malformed* `Ord` instances ([CLC proposal #236](https://github.com/haskell/core-libraries-committee/issues/236)) ===================================== libraries/ghc-internal/src/GHC/Internal/Base.hs ===================================== @@ -2184,7 +2184,7 @@ const x _ = x -- -- >>> let (.>) = flip (.) in (+1) .> show $ 5 -- "6" -flip :: (a -> b -> c) -> b -> a -> c +flip :: forall repc a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c flip f x y = f y x -- Note: Before base-4.19, ($) was not representation polymorphic ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -1095,7 +1095,7 @@ module Data.Function where applyWhen :: forall a. GHC.Types.Bool -> (a -> a) -> a -> a const :: forall a b. a -> b -> a fix :: forall a. (a -> a) -> a - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c id :: forall a. a -> a on :: forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c @@ -3714,7 +3714,7 @@ module GHC.Base where fetchXorIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) fetchXorWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #) finalizeWeak# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c float2Double# :: Float# -> Double# float2Int# :: Float# -> Int# fmaddDouble# :: Double# -> Double# -> Double# -> Double# @@ -10127,7 +10127,7 @@ module Prelude where errorWithoutStackTrace :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r). [Char] -> a even :: forall a. Integral a => a -> Bool filter :: forall a. (a -> Bool) -> [a] -> [a] - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c fromIntegral :: forall a b. (Integral a, Num b) => a -> b fst :: forall a b. (a, b) -> a gcd :: forall a. Integral a => a -> a -> a ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -1095,7 +1095,7 @@ module Data.Function where applyWhen :: forall a. GHC.Types.Bool -> (a -> a) -> a -> a const :: forall a b. a -> b -> a fix :: forall a. (a -> a) -> a - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c id :: forall a. a -> a on :: forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c @@ -3714,7 +3714,7 @@ module GHC.Base where fetchXorIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) fetchXorWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #) finalizeWeak# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c float2Double# :: Float# -> Double# float2Int# :: Float# -> Int# fmaddDouble# :: Double# -> Double# -> Double# -> Double# @@ -13169,7 +13169,7 @@ module Prelude where errorWithoutStackTrace :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r). [Char] -> a even :: forall a. Integral a => a -> Bool filter :: forall a. (a -> Bool) -> [a] -> [a] - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c fromIntegral :: forall a b. (Integral a, Num b) => a -> b fst :: forall a b. (a, b) -> a gcd :: forall a. Integral a => a -> a -> a ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -1095,7 +1095,7 @@ module Data.Function where applyWhen :: forall a. GHC.Types.Bool -> (a -> a) -> a -> a const :: forall a b. a -> b -> a fix :: forall a. (a -> a) -> a - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c id :: forall a. a -> a on :: forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c @@ -3717,7 +3717,7 @@ module GHC.Base where fetchXorIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) fetchXorWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #) finalizeWeak# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c float2Double# :: Float# -> Double# float2Int# :: Float# -> Int# fmaddDouble# :: Double# -> Double# -> Double# -> Double# @@ -10413,7 +10413,7 @@ module Prelude where errorWithoutStackTrace :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r). [Char] -> a even :: forall a. Integral a => a -> Bool filter :: forall a. (a -> Bool) -> [a] -> [a] - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c fromIntegral :: forall a b. (Integral a, Num b) => a -> b fst :: forall a b. (a, b) -> a gcd :: forall a. Integral a => a -> a -> a ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -1095,7 +1095,7 @@ module Data.Function where applyWhen :: forall a. GHC.Types.Bool -> (a -> a) -> a -> a const :: forall a b. a -> b -> a fix :: forall a. (a -> a) -> a - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c id :: forall a. a -> a on :: forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c @@ -3714,7 +3714,7 @@ module GHC.Base where fetchXorIntArray# :: forall d. MutableByteArray# d -> Int# -> Int# -> State# d -> (# State# d, Int# #) fetchXorWordAddr# :: forall d. Addr# -> Word# -> State# d -> (# State# d, Word# #) finalizeWeak# :: forall {l :: Levity} (a :: TYPE (BoxedRep l)) b. Weak# a -> State# RealWorld -> (# State# RealWorld, Int#, State# RealWorld -> (# State# RealWorld, b #) #) - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c float2Double# :: Float# -> Double# float2Int# :: Float# -> Int# fmaddDouble# :: Double# -> Double# -> Double# -> Double# @@ -10127,7 +10127,7 @@ module Prelude where errorWithoutStackTrace :: forall (r :: GHC.Types.RuntimeRep) (a :: TYPE r). [Char] -> a even :: forall a. Integral a => a -> Bool filter :: forall a. (a -> Bool) -> [a] -> [a] - flip :: forall a b c. (a -> b -> c) -> b -> a -> c + flip :: forall (repc :: GHC.Types.RuntimeRep) a b (c :: TYPE repc). (a -> b -> c) -> b -> a -> c fromIntegral :: forall a b. (Integral a, Num b) => a -> b fst :: forall a b. (a, b) -> a gcd :: forall a. Integral a => a -> a -> a ===================================== testsuite/tests/typecheck/should_compile/abstract_refinement_hole_fits.stderr ===================================== @@ -39,14 +39,14 @@ abstract_refinement_hole_fits.hs:4:5: warning: [GHC-88464] [-Wtyped-holes (in -W where const :: forall a b. a -> b -> a (.) (_ :: b1 -> Integer) (_ :: [Integer] -> b1) where (.) :: forall b c a. (b -> c) -> (a -> b) -> a -> c - flip (_ :: [Integer] -> t0 -> Integer) (_ :: t0) - where flip :: forall a b c. (a -> b -> c) -> b -> a -> c curry (_ :: (t0, [Integer]) -> Integer) (_ :: t0) where curry :: forall a b c. ((a, b) -> c) -> a -> b -> c ($) (_ :: [Integer] -> Integer) where ($) :: forall a b. (a -> b) -> a -> b ($!) (_ :: [Integer] -> Integer) where ($!) :: forall a b. (a -> b) -> a -> b + flip (_ :: [Integer] -> t0 -> Integer) (_ :: t0) + where flip :: forall a b c. (a -> b -> c) -> b -> a -> c id (_ :: t0 -> [Integer] -> Integer) (_ :: t0) where id :: forall a. a -> a head (_ :: [t0 -> [Integer] -> Integer]) (_ :: t0) @@ -160,22 +160,22 @@ abstract_refinement_hole_fits.hs:7:5: warning: [GHC-88464] [-Wtyped-holes (in -W where foldr :: forall (t :: * -> *) a b. Foldable t => (a -> b -> b) -> b -> t a -> b - flip (_ :: [Integer] -> Integer -> Integer) - where flip :: forall a b c. (a -> b -> c) -> b -> a -> c curry (_ :: (Integer, [Integer]) -> Integer) where curry :: forall a b c. ((a, b) -> c) -> a -> b -> c const (_ :: [Integer] -> Integer) where const :: forall a b. a -> b -> a + flip (_ :: [Integer] -> Integer -> Integer) + where flip :: forall a b c. (a -> b -> c) -> b -> a -> c (.) (_ :: b1 -> [Integer] -> Integer) (_ :: Integer -> b1) where (.) :: forall b c a. (b -> c) -> (a -> b) -> a -> c - flip (_ :: Integer -> t0 -> [Integer] -> Integer) (_ :: t0) - where flip :: forall a b c. (a -> b -> c) -> b -> a -> c curry (_ :: (t0, Integer) -> [Integer] -> Integer) (_ :: t0) where curry :: forall a b c. ((a, b) -> c) -> a -> b -> c ($) (_ :: Integer -> [Integer] -> Integer) where ($) :: forall a b. (a -> b) -> a -> b ($!) (_ :: Integer -> [Integer] -> Integer) where ($!) :: forall a b. (a -> b) -> a -> b + flip (_ :: Integer -> t0 -> [Integer] -> Integer) (_ :: t0) + where flip :: forall a b c. (a -> b -> c) -> b -> a -> c id (_ :: t0 -> Integer -> [Integer] -> Integer) (_ :: t0) where id :: forall a. a -> a head (_ :: [t0 -> Integer -> [Integer] -> Integer]) (_ :: t0) ===================================== testsuite/tests/typecheck/should_compile/holes.stderr ===================================== @@ -194,7 +194,6 @@ holes.hs:11:15: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] seq :: forall a b. a -> b -> b ($!) :: forall a b. (a -> b) -> a -> b (.) :: forall b c a. (b -> c) -> (a -> b) -> a -> c - flip :: forall a b c. (a -> b -> c) -> b -> a -> c either :: forall a c b. (a -> c) -> (b -> c) -> Either a b -> c curry :: forall a b c. ((a, b) -> c) -> a -> b -> c uncurry :: forall a b c. (a -> b -> c) -> (a, b) -> c @@ -202,5 +201,6 @@ holes.hs:11:15: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] zip3 :: forall a b c. [a] -> [b] -> [c] -> [(a, b, c)] zipWith :: forall a b c. (a -> b -> c) -> [a] -> [b] -> [c] ($) :: forall a b. (a -> b) -> a -> b + flip :: forall a b c. (a -> b -> c) -> b -> a -> c zipWith3 :: forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] ===================================== testsuite/tests/typecheck/should_compile/holes3.stderr ===================================== @@ -197,7 +197,6 @@ holes3.hs:11:15: error: [GHC-88464] seq :: forall a b. a -> b -> b ($!) :: forall a b. (a -> b) -> a -> b (.) :: forall b c a. (b -> c) -> (a -> b) -> a -> c - flip :: forall a b c. (a -> b -> c) -> b -> a -> c either :: forall a c b. (a -> c) -> (b -> c) -> Either a b -> c curry :: forall a b c. ((a, b) -> c) -> a -> b -> c uncurry :: forall a b c. (a -> b -> c) -> (a, b) -> c @@ -205,5 +204,6 @@ holes3.hs:11:15: error: [GHC-88464] zip3 :: forall a b c. [a] -> [b] -> [c] -> [(a, b, c)] zipWith :: forall a b c. (a -> b -> c) -> [a] -> [b] -> [c] ($) :: forall a b. (a -> b) -> a -> b + flip :: forall a b c. (a -> b -> c) -> b -> a -> c zipWith3 :: forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d] ===================================== testsuite/tests/typecheck/should_compile/refinement_hole_fits.stderr ===================================== @@ -172,11 +172,6 @@ refinement_hole_fits.hs:7:5: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] with foldr @[] @Integer @Integer (imported from ‘Prelude’ at refinement_hole_fits.hs:1:8-30 (and originally defined in ‘GHC.Internal.Data.Foldable’)) - flip (_ :: [Integer] -> Integer -> Integer) - where flip :: forall a b c. (a -> b -> c) -> b -> a -> c - with flip @[Integer] @Integer @Integer - (imported from ‘Prelude’ at refinement_hole_fits.hs:1:8-30 - (and originally defined in ‘GHC.Internal.Base’)) curry (_ :: (Integer, [Integer]) -> Integer) where curry :: forall a b c. ((a, b) -> c) -> a -> b -> c with curry @Integer @[Integer] @Integer @@ -187,6 +182,11 @@ refinement_hole_fits.hs:7:5: warning: [GHC-88464] [-Wtyped-holes (in -Wdefault)] with const @([Integer] -> Integer) @Integer (imported from ‘Prelude’ at refinement_hole_fits.hs:1:8-30 (and originally defined in ‘GHC.Internal.Base’)) + flip (_ :: [Integer] -> Integer -> Integer) + where flip :: forall a b c. (a -> b -> c) -> b -> a -> c + with flip @GHC.Types.LiftedRep @[Integer] @Integer @Integer + (imported from ‘Prelude’ at refinement_hole_fits.hs:1:8-30 + (and originally defined in ‘GHC.Internal.Base’)) ($) (_ :: Integer -> [Integer] -> Integer) where ($) :: forall a b. (a -> b) -> a -> b with ($) @GHC.Types.LiftedRep View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e0099721ce4b2f7f2b5ab21a75160aa212751804 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e0099721ce4b2f7f2b5ab21a75160aa212751804 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 16 21:58:49 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sun, 16 Jun 2024 17:58:49 -0400 Subject: [Git][ghc/ghc][master] EPA: Add location to Match Pats list Message-ID: <666f60199d892_2102e723708506223c@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - 30 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/Language/Haskell/Syntax/Expr.hs - testsuite/tests/ghc-api/exactprint/T22919.stderr The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/118a12921a9ad3049420cdc67deb9c4ea2ccff23 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/118a12921a9ad3049420cdc67deb9c4ea2ccff23 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 16 22:01:06 2024 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Sun, 16 Jun 2024 18:01:06 -0400 Subject: [Git][ghc/ghc][wip/az/T12842-ttg-fixity] TTG: Move SourceText from `Fixity` to `FixitySig` Message-ID: <666f60a296961_2102e72466d9062483@gitlab.mail> Alan Zimmerman pushed to branch wip/az/T12842-ttg-fixity at Glasgow Haskell Compiler / GHC Commits: bdae6b9e by Alan Zimmerman at 2024-06-16T23:00:44+01:00 TTG: Move SourceText from `Fixity` to `FixitySig` It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Supersedes !12842 - - - - - 25 changed files: - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Fixity.hs - testsuite/tests/parser/should_compile/T20846.stderr - utils/check-exact/ExactPrint.hs - utils/genprimopcode/Main.hs - utils/genprimopcode/Parser.y - utils/genprimopcode/Syntax.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Json.hs - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs - utils/haddock/haddock-api/src/Haddock/Types.hs Changes: ===================================== compiler/GHC/Builtin/PrimOps.hs ===================================== @@ -49,7 +49,6 @@ import GHC.Types.Basic import GHC.Types.Fixity ( Fixity(..), FixityDirection(..) ) import GHC.Types.SrcLoc ( wiredInSrcSpan ) import GHC.Types.ForeignCall ( CLabelString ) -import GHC.Types.SourceText ( SourceText(..) ) import GHC.Types.Unique ( Unique ) import GHC.Unit.Types ( Unit ) ===================================== compiler/GHC/Hs/Binds.hs ===================================== @@ -708,7 +708,7 @@ instance OutputableBndrId p => Outputable (IPBind (GhcPass p)) where type instance XTypeSig (GhcPass p) = AnnSig type instance XPatSynSig (GhcPass p) = AnnSig type instance XClassOpSig (GhcPass p) = AnnSig -type instance XFixSig (GhcPass p) = [AddEpAnn] +type instance XFixSig (GhcPass p) = ([AddEpAnn], SourceText) type instance XInlineSig (GhcPass p) = [AddEpAnn] type instance XSpecSig (GhcPass p) = [AddEpAnn] type instance XSpecInstSig (GhcPass p) = ([AddEpAnn], SourceText) ===================================== compiler/GHC/Hs/Dump.hs ===================================== @@ -74,7 +74,6 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0 `extQ` name `extQ` occName `extQ` moduleName `extQ` var `extQ` dataCon `extQ` bagName `extQ` bagRdrName `extQ` bagVar `extQ` nameSet - `extQ` fixity `ext2Q` located `extQ` srcSpanAnnA `extQ` srcSpanAnnL @@ -139,11 +138,12 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0 , generic s ] sourceText :: SourceText -> SDoc - sourceText NoSourceText = parens $ text "NoSourceText" + sourceText NoSourceText = case bs of + BlankSrcSpan -> parens $ text "SourceText" <+> text "blanked" + _ -> parens $ text "NoSourceText" sourceText (SourceText src) = case bs of - NoBlankSrcSpan -> parens $ text "SourceText" <+> ftext src - BlankSrcSpanFile -> parens $ text "SourceText" <+> ftext src - _ -> parens $ text "SourceText" <+> text "blanked" + BlankSrcSpan -> parens $ text "SourceText" <+> text "blanked" + _ -> parens $ text "SourceText" <+> ftext src epaAnchor :: EpaLocation -> SDoc epaAnchor (EpaSpan s) = parens $ text "EpaSpan" <+> srcSpan s @@ -216,11 +216,6 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0 text "NameSet:" $$ (list . nameSetElemsStable $ ns) - fixity :: Fixity -> SDoc - fixity fx = braces $ - text "Fixity:" - <+> ppr fx - located :: (Data a, Data b) => GenLocated a b -> SDoc located (L ss a) = parens (text "L" ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -780,7 +780,7 @@ repLFixD :: LFixitySig GhcRn -> MetaM [(SrcSpan, Core (M TH.Dec))] repLFixD (L loc fix_sig) = rep_fix_d (locA loc) fix_sig rep_fix_d :: SrcSpan -> FixitySig GhcRn -> MetaM [(SrcSpan, Core (M TH.Dec))] -rep_fix_d loc (FixitySig ns_spec names (Fixity _ prec dir)) +rep_fix_d loc (FixitySig ns_spec names (Fixity prec dir)) = do { MkC prec' <- coreIntLit prec ; let rep_fn = case dir of InfixL -> infixLWithSpecDName ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -90,7 +90,6 @@ import GHC.Types.Avail import GHC.Types.Fixity import GHC.Types.Fixity.Env import GHC.Types.SourceError -import GHC.Types.SourceText import GHC.Types.SourceFile import GHC.Types.SafeHaskell import GHC.Types.TypeEnv @@ -1030,7 +1029,7 @@ ghcPrimIface -- The fixity listed here for @`seq`@ should match -- those in primops.txt.pp (from which Haddock docs are generated). - fixities = (getOccName seqId, Fixity NoSourceText 0 InfixR) + fixities = (getOccName seqId, Fixity 0 InfixR) : mapMaybe mkFixity allThePrimOps mkFixity op = (,) (primOpOcc op) <$> primOpFixity op @@ -1235,5 +1234,3 @@ instance Outputable WhereFrom where ppr (ImportByUser NotBoot) = empty ppr ImportBySystem = text "{- SYSTEM -}" ppr ImportByPlugin = text "{- PLUGIN -}" - - ===================================== compiler/GHC/Parser.y ===================================== @@ -2679,8 +2679,8 @@ sigdecl :: { LHsDecl GhcPs } Nothing -> (NoSourceText, maxPrecedence) Just l2 -> (fst $ unLoc l2, snd $ unLoc l2) ; amsA' (sLL $1 $> $ SigD noExtField - (FixSig (mj AnnInfix $1 : maybeToList mbPrecAnn) (FixitySig (unLoc $3) (fromOL $ unLoc $4) - (Fixity fixText fixPrec (unLoc $1))))) + (FixSig (mj AnnInfix $1 : maybeToList mbPrecAnn, fixText) (FixitySig (unLoc $3) (fromOL $ unLoc $4) + (Fixity fixPrec (unLoc $1))))) }} | pattern_synonym_sig { L (getLoc $1) . SigD noExtField . unLoc $ $1 } ===================================== compiler/GHC/Parser/Annotation.hs ===================================== @@ -111,6 +111,7 @@ import GHC.Hs.DocString import GHC.Utils.Outputable hiding ( (<>) ) import GHC.Utils.Panic import qualified GHC.Data.Strict as Strict +import GHC.Types.SourceText (SourceText (NoSourceText)) {- Note [exact print annotations] @@ -1353,6 +1354,9 @@ instance NoAnn (EpToken s) where instance NoAnn (EpUniToken s t) where noAnn = NoEpUniTok +instance NoAnn SourceText where + noAnn = NoSourceText + -- --------------------------------------------------------------------- instance (Outputable a) => Outputable (EpAnn a) where ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -411,7 +411,7 @@ rnExpr (OpApp _ e1 op e2) ; fixity <- case op' of L _ (HsVar _ (L _ n)) -> lookupFixityRn n L _ (HsRecSel _ f) -> lookupFieldFixityRn f - _ -> return (Fixity NoSourceText minPrecedence InfixL) + _ -> return (Fixity minPrecedence InfixL) -- c.f. lookupFixity for unbound ; lexical_negation <- xoptM LangExt.LexicalNegation ===================================== compiler/GHC/Rename/Fixity.hs ===================================== @@ -27,7 +27,6 @@ import GHC.Types.Fixity.Env import GHC.Types.Name import GHC.Types.Name.Env import GHC.Types.Fixity -import GHC.Types.SourceText import GHC.Types.SrcLoc import GHC.Utils.Outputable @@ -147,7 +146,7 @@ lookupFixityRn_help :: Name -> RnM (Bool, Fixity) lookupFixityRn_help name | isUnboundName name - = return (False, Fixity NoSourceText minPrecedence InfixL) + = return (False, Fixity minPrecedence InfixL) -- Minimise errors from unbound names; eg -- a>0 `foo` b>0 -- where 'foo' is not in scope, should not give an error (#7937) ===================================== compiler/GHC/Rename/HsType.hs ===================================== @@ -1557,8 +1557,8 @@ checkPrecMatch op (MG { mg_alts = (L _ ms) }) checkPrec :: Name -> Pat GhcRn -> Bool -> IOEnv (Env TcGblEnv TcLclEnv) () checkPrec op (ConPat NoExtField op1 (InfixCon _ _)) right = do - op_fix@(Fixity _ op_prec op_dir) <- lookupFixityRn op - op1_fix@(Fixity _ op1_prec op1_dir) <- lookupFixityRn (unLoc op1) + op_fix@(Fixity op_prec op_dir) <- lookupFixityRn op + op1_fix@(Fixity op1_prec op1_dir) <- lookupFixityRn (unLoc op1) let inf_ok = op1_prec > op_prec || (op1_prec == op_prec && @@ -1586,8 +1586,8 @@ checkSectionPrec direction section op arg _ -> return () where op_name = get_op op - go_for_it arg_op arg_fix@(Fixity _ arg_prec assoc) = do - op_fix@(Fixity _ op_prec _) <- lookupFixityOp op_name + go_for_it arg_op arg_fix@(Fixity arg_prec assoc) = do + op_fix@(Fixity op_prec _) <- lookupFixityOp op_name unless (op_prec < arg_prec || (op_prec == arg_prec && direction == assoc)) (sectionPrecErr (get_op op, op_fix) ===================================== compiler/GHC/Tc/Deriv/Generate.hs ===================================== @@ -1336,7 +1336,7 @@ appPrecedence = fromIntegral maxPrecedence + 1 getPrecedence :: (Name -> Fixity) -> Name -> Integer getPrecedence get_fixity nm = case get_fixity nm of - Fixity _ x _assoc -> fromIntegral x + Fixity x _assoc -> fromIntegral x -- NB: the Report says that associativity is not taken -- into account for either Read or Show; hence we -- ignore associativity here ===================================== compiler/GHC/Tc/Deriv/Generics.hs ===================================== @@ -654,9 +654,9 @@ tc_mkRepTy gk get_fixity dit@(DerivInstTys{ dit_rep_tc = tycon ctFix c | dataConIsInfix c = case get_fixity (dataConName c) of - Fixity _ n InfixL -> buildFix n pLA - Fixity _ n InfixR -> buildFix n pRA - Fixity _ n InfixN -> buildFix n pNA + Fixity n InfixL -> buildFix n pLA + Fixity n InfixR -> buildFix n pRA + Fixity n InfixN -> buildFix n pNA | otherwise = mkTyConTy pPrefix buildFix n assoc = mkTyConApp pInfix [ mkTyConTy assoc , mkNumLitTy (fromIntegral n)] ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -2814,7 +2814,7 @@ reifyFixity name = do { (found, fix) <- lookupFixityRn_help name ; return (if found then Just (conv_fix fix) else Nothing) } where - conv_fix (Hs.Fixity _ i d) = TH.Fixity i (conv_dir d) + conv_fix (Hs.Fixity i d) = TH.Fixity i (conv_dir d) conv_dir Hs.InfixR = TH.InfixR conv_dir Hs.InfixL = TH.InfixL conv_dir Hs.InfixN = TH.InfixN ===================================== compiler/GHC/ThToHs.hs ===================================== @@ -1984,7 +1984,7 @@ cvtPatSynSigTy ty = cvtSigType ty ----------------------------------------------------------- cvtFixity :: TH.Fixity -> Hs.Fixity -cvtFixity (TH.Fixity prec dir) = Hs.Fixity NoSourceText prec (cvt_dir dir) +cvtFixity (TH.Fixity prec dir) = Hs.Fixity prec (cvt_dir dir) where cvt_dir TH.InfixL = Hs.InfixL cvt_dir TH.InfixR = Hs.InfixR ===================================== compiler/GHC/Types/Fixity.hs ===================================== @@ -16,33 +16,28 @@ where import GHC.Prelude -import GHC.Types.SourceText - import GHC.Utils.Outputable import GHC.Utils.Binary import Data.Data hiding (Fixity, Prefix, Infix) -data Fixity = Fixity SourceText Int FixityDirection - -- Note [Pragma source text] in "GHC.Types.SourceText" +data Fixity = Fixity Int FixityDirection deriving Data instance Outputable Fixity where - ppr (Fixity _ prec dir) = hcat [ppr dir, space, int prec] + ppr (Fixity prec dir) = hcat [ppr dir, space, int prec] instance Eq Fixity where -- Used to determine if two fixities conflict - (Fixity _ p1 dir1) == (Fixity _ p2 dir2) = p1==p2 && dir1 == dir2 + (Fixity p1 dir1) == (Fixity p2 dir2) = p1==p2 && dir1 == dir2 instance Binary Fixity where - put_ bh (Fixity src aa ab) = do - put_ bh src + put_ bh (Fixity aa ab) = do put_ bh aa put_ bh ab get bh = do - src <- get bh aa <- get bh ab <- get bh - return (Fixity src aa ab) + return (Fixity aa ab) ------------------------ data FixityDirection @@ -76,12 +71,12 @@ maxPrecedence = 9 minPrecedence = 0 defaultFixity :: Fixity -defaultFixity = Fixity NoSourceText maxPrecedence InfixL +defaultFixity = Fixity maxPrecedence InfixL negateFixity, funTyFixity :: Fixity -- Wired-in fixities -negateFixity = Fixity NoSourceText 6 InfixL -- Fixity of unary negate -funTyFixity = Fixity NoSourceText (-1) InfixR -- Fixity of '->', see #15235 +negateFixity = Fixity 6 InfixL -- Fixity of unary negate +funTyFixity = Fixity (-1) InfixR -- Fixity of '->', see #15235 {- Consider @@ -96,7 +91,7 @@ whether there's an error. compareFixity :: Fixity -> Fixity -> (Bool, -- Error please Bool) -- Associate to the right: a op1 (b op2 c) -compareFixity (Fixity _ prec1 dir1) (Fixity _ prec2 dir2) +compareFixity (Fixity prec1 dir1) (Fixity prec2 dir2) = case prec1 `compare` prec2 of GT -> left LT -> right ===================================== testsuite/tests/parser/should_compile/T20846.stderr ===================================== @@ -44,7 +44,9 @@ (SigD (NoExtField) (FixSig - [(AddEpAnn AnnInfix (EpaSpan { T20846.hs:3:1-6 }))] + ((,) + [(AddEpAnn AnnInfix (EpaSpan { T20846.hs:3:1-6 }))] + (NoSourceText)) (FixitySig (NoNamespaceSpecifier) [(L @@ -56,7 +58,9 @@ [])) (Unqual {OccName: ++++}))] - {Fixity: infixr 9})))) + (Fixity + (9) + (InfixR)))))) ,(L (EpAnn (EpaSpan { T20846.hs:4:1-18 }) ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -2761,7 +2761,7 @@ instance ExactPrint (Sig GhcPs) where (an0, vars',ty') <- exactVarSig an vars ty return (ClassOpSig an0 is_deflt vars' ty') - exact (FixSig an (FixitySig x names (Fixity src v fdir))) = do + exact (FixSig (an,src) (FixitySig x names (Fixity v fdir))) = do let fixstr = case fdir of InfixL -> "infixl" InfixR -> "infixr" @@ -2769,7 +2769,7 @@ instance ExactPrint (Sig GhcPs) where an0 <- markEpAnnLMS'' an lidl AnnInfix (Just fixstr) an1 <- markEpAnnLMS'' an0 lidl AnnVal (Just (sourceTextToString src (show v))) names' <- markAnnotated names - return (FixSig an1 (FixitySig x names' (Fixity src v fdir))) + return (FixSig (an1,src) (FixitySig x names' (Fixity v fdir))) exact (InlineSig an ln inl) = do an0 <- markAnnOpen an (inl_src inl) "{-# INLINE" ===================================== utils/genprimopcode/Main.hs ===================================== @@ -364,7 +364,7 @@ gen_hs_source (Info defaults entries) = prim_fixity options n = [ pprFixityDir d ++ " " ++ show i ++ " " ++ asInfix n - | OptionFixity (Just (Fixity _ i d)) <- options ] + | OptionFixity (Just (Fixity i d)) <- options ] prim_func n t = [ wrapOp n ++ " :: " ++ pprTy t, wrapOp n ++ " = " ++ funcRhs n ] ===================================== utils/genprimopcode/Parser.y ===================================== @@ -90,9 +90,9 @@ pOption : lowerName '=' false { OptionFalse $1 } | can_fail_warning '=' pPrimOpCanFailWarnFlag { OptionCanFailWarnFlag $3 } pInfix :: { Maybe Fixity } -pInfix : infix integer { Just $ Fixity NoSourceText $2 InfixN } - | infixl integer { Just $ Fixity NoSourceText $2 InfixL } - | infixr integer { Just $ Fixity NoSourceText $2 InfixR } +pInfix : infix integer { Just $ Fixity $2 InfixN } + | infixl integer { Just $ Fixity $2 InfixL } + | infixr integer { Just $ Fixity $2 InfixR } | nothing { Nothing } pEffect :: { PrimOpEffect } ===================================== utils/genprimopcode/Syntax.hs ===================================== @@ -101,16 +101,12 @@ instance Show TyCon where -- The SourceText exists so that it matches the SourceText field in -- BasicTypes.Fixity -data Fixity = Fixity SourceText Int FixityDirection +data Fixity = Fixity Int FixityDirection deriving (Eq, Show) data FixityDirection = InfixN | InfixL | InfixR deriving (Eq, Show) -data SourceText = SourceText String - | NoSourceText - deriving (Eq,Show) - data PrimOpEffect = NoEffect | CanFail ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs ===================================== @@ -372,7 +372,7 @@ ppFixities fs qual = foldr1 (+++) (map ppFix uniq_fs) +++ rightEdge uniq_fs = [ (n, the p, the d') - | (n, Fixity _ p d) <- fs + | (n, Fixity p d) <- fs , let d' = ppDir d , then group by Down (p, d') ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Create.hs ===================================== @@ -57,7 +57,6 @@ import Data.Traversable (for) import Control.Arrow (first, (&&&)) import GHC hiding (lookupName) import GHC.Builtin.Names -import GHC.Builtin.Types import GHC.Builtin.Types.Prim import GHC.Core.ConLike (ConLike (..)) import GHC.Data.FastString (FastString, bytesFS, unpackFS) @@ -65,7 +64,6 @@ import GHC.Driver.Ppr import GHC.HsToCore.Docs hiding (mkMaps) import GHC.Iface.Syntax import GHC.Types.Avail -import GHC.Types.Basic import GHC.Types.Name import GHC.Types.Name.Set import GHC.Types.SafeHaskell ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Json.hs ===================================== @@ -241,7 +241,7 @@ jsonName :: Name -> JsonDoc jsonName = JSString . nameStableString jsonFixity :: Fixity -> JsonDoc -jsonFixity (Fixity _ prec dir) = +jsonFixity (Fixity prec dir) = jsonObject [ ("prec", jsonInt prec) , ("direction", jsonFixityDirection dir) ===================================== utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs ===================================== @@ -56,7 +56,7 @@ import GHC.Types.Unique.FM import GHC.Unit.State import GHC.Utils.Binary -import GHC.Iface.Type (IfaceType, getIfaceType, putIfaceType) +import GHC.Iface.Type (IfaceType, putIfaceType) import Haddock.Options (Visibility (..)) ===================================== utils/haddock/haddock-api/src/Haddock/Types.hs ===================================== @@ -978,8 +978,8 @@ instance NFData FixityDirection where rnf InfixN = () instance NFData Fixity where - rnf (Fixity sourceText n dir) = - sourceText `deepseq` n `deepseq` dir `deepseq` () + rnf (Fixity n dir) = + n `deepseq` dir `deepseq` () instance NFData (EpAnn NameAnn) where rnf (EpAnn en ann cs) = en `deepseq` ann `deepseq` cs `deepseq` () View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bdae6b9e457b43003ce8e645386ab19b6e1b88b2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bdae6b9e457b43003ce8e645386ab19b6e1b88b2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 16 22:14:50 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Sun, 16 Jun 2024 18:14:50 -0400 Subject: [Git][ghc/ghc][wip/T24725] Further improvements to eqType Message-ID: <666f63da529ec_2102e7271e1c8650f@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24725 at Glasgow Haskell Compiler / GHC Commits: 8484934d by Simon Peyton Jones at 2024-06-16T23:14:26+01:00 Further improvements to eqType - - - - - 1 changed file: - compiler/GHC/Core/TyCo/Compare.hs Changes: ===================================== compiler/GHC/Core/TyCo/Compare.hs ===================================== @@ -7,16 +7,17 @@ -- | Type equality and comparison module GHC.Core.TyCo.Compare ( - -- * Type comparison + -- * Type equality eqType, eqTypeIgnoringMultiplicity, eqTypeX, eqTypes, - nonDetCmpType, nonDetCmpTypeX, - nonDetCmpTc, eqVarBndrs, pickyEqType, tcEqType, tcEqKind, tcEqTypeNoKindCheck, tcEqTyConApps, mayLookIdentical, + -- * Type comparison + nonDetCmpType, + -- * Visiblity comparision eqForAllVis, cmpForAllVis @@ -143,50 +144,74 @@ initRnEnv :: Type -> Type -> RnEnv2 initRnEnv ta tb = mkRnEnv2 $ mkInScopeSet $ tyCoVarsOfType ta `unionVarSet` tyCoVarsOfType tb +eqTypeNoKindCheck :: Type -> Type -> Bool +eqTypeNoKindCheck ty1 ty2 = eqTyResBool (eq_type_expand_respect ty1 ty2) + -- | Type equality comparing both visible and invisible arguments, -- expanding synonyms and respecting multiplicities. eqType :: HasCallStack => Type -> Type -> Bool -eqType ta tb = eqTypeX (initRnEnv ta tb) ta tb - -eqTypeNoKindCheck :: Type -> Type -> Bool -eqTypeNoKindCheck ta tb = eq_type_x (initRnEnv ta tb) ta tb +eqType ta tb + = case eq ta tb of + NotEq -> False + IsEq -> True + IsEqCast -> eqTyResBool (eq (typeKind ta) (typeKind tb)) + where + eq = eq_type_expand_respect -- | Compare types with respect to a (presumably) non-empty 'RnEnv2'. eqTypeX :: HasCallStack => RnEnv2 -> Type -> Type -> Bool -eqTypeX env ta tb = eq_type_x env ta tb - && eq_type_x env (typeKind ta) (typeKind tb) - -eq_type_x :: RnEnv2 -> Type -> Type -> Bool -eq_type_x = generic_eq_type ExpandSynonyms RespectMultiplicities +eqTypeX env ta tb + = case eq ta tb of + NotEq -> False + IsEq -> True + IsEqCast -> eqTyResBool (eq (typeKind ta) (typeKind tb)) + where + eq = eq_type_expand_respect_x env eqTypeIgnoringMultiplicity :: Type -> Type -> Bool eqTypeIgnoringMultiplicity ta tb - = eq init_env ta tb - && eq init_env (typeKind ta) (typeKind tb) + = case eq ta tb of + NotEq -> False + IsEq -> True + IsEqCast -> eqTyResBool (eq (typeKind ta) (typeKind tb)) where - eq = generic_eq_type ExpandSynonyms IgnoreMultiplicities - init_env = initRnEnv ta tb + eq = eq_type_expand_ignore -- | Like 'pickyEqTypeVis', but returns a Bool for convenience pickyEqType :: Type -> Type -> Bool -- Check when two types _look_ the same, _including_ synonyms. -- So (pickyEqType String [Char]) returns False -- This ignores kinds and coercions, because this is used only for printing. -pickyEqType ta tb - = generic_eq_type KeepSynonyms RespectMultiplicities (initRnEnv ta tb) ta tb +pickyEqType ta tb = eqTyResBool (eq_type_keep_respect ta tb) -{- Note [Specialising generic_eq_type] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -The type equality predicates in Type are hit pretty hard during typechecking. -Consequently we take pains to ensure that these paths are compiled to -efficient, minimally-allocating code. +{- Note [Specialising type equality] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The type equality predicates in Type are hit pretty hard by GHC. Consequently +we take pains to ensure that these paths are compiled to efficient, +minimally-allocating code. Plan: + +* The main workhorse is `inline_generic_eq_type_x`. It is /non-recursive/ + and is marked INLINE. + +* `inline_generic_eq_type_x` has various parameters that control what it does: + * syn_flag::SynFlag whether type synonyms are expanded or kept. + * mult_flag::MultiplicityFlag whether multiplicities are ignored or respected + * mb_env::Maybe RnEnv2 an optional RnEnv2. + +* `inline_generic_eq_type_x` has a handful of call sites, namely the ones + in `eq_type_expand_respect`, `eq_type_expand_repect_x` etc. It inlines + at all these sites, specialising to the data values passed for the + control parameters. -To this end we place an INLINE on tc_eq_type, ensuring that it is inlined into -its publicly-visible interfaces (e.g. tcEqType). In addition to eliminating -some dynamic branches, this allows the simplifier to eliminate the closure -allocations that would otherwise be necessary to capture the two boolean "mode" -flags. This reduces allocations by a good fraction of a percent when compiling -Cabal. +* All /other/ calls to `inline_generic_eq_type_x` go via + generic_eq_type_x = inline_generic_eq_type_x + {-# NOINLNE generic_eq_type_x #-} + The idea is that all calls to `generic_eq_type_x` are specialised by the + RULES, so this NOINLINE version is seldom, if ever, actually called. + +* For each of specialised copy of `inline_generic_eq_type_x, there is a + corresponding rewrite RULE that rewrites a call to (generic_eq_type_x args) + into the appropriate specialied version. See #19226. -} @@ -194,72 +219,142 @@ See #19226. -- | This flag controls whether we expand synonyms during comparison data SynFlag = ExpandSynonyms | KeepSynonyms +eq_type_expand_respect, eq_type_expand_ignore, eq_type_keep_respect + :: Type -> Type -> EqTyRes +eq_type_expand_respect_x, eq_type_expand_ignore_x, eq_type_keep_respect_x + :: RnEnv2 -> Type -> Type -> EqTyRes + +eq_type_expand_respect = inline_generic_eq_type_x ExpandSynonyms RespectMultiplicities Nothing +eq_type_expand_respect_x env = inline_generic_eq_type_x ExpandSynonyms RespectMultiplicities (Just env) +eq_type_expand_ignore = inline_generic_eq_type_x ExpandSynonyms IgnoreMultiplicities Nothing +eq_type_expand_ignore_x env = inline_generic_eq_type_x ExpandSynonyms IgnoreMultiplicities (Just env) +eq_type_keep_respect = inline_generic_eq_type_x KeepSynonyms RespectMultiplicities Nothing +eq_type_keep_respect_x env = inline_generic_eq_type_x KeepSynonyms RespectMultiplicities (Just env) + +{-# RULES +"eqType1" generic_eq_type_x ExpandSynonyms RespectMultiplicities Nothing + = eq_type_expand_respect +"eqType2" forall env. generic_eq_type_x ExpandSynonyms RespectMultiplicities (Just env) + = eq_type_expand_respect_x env +"eqType3" generic_eq_type_x ExpandSynonyms IgnoreMultiplicities Nothing + = eq_type_expand_ignore +"eqType4" forall env. generic_eq_type_x ExpandSynonyms IgnoreMultiplicities (Just env) + = eq_type_expand_ignore_x env +"eqType5" generic_eq_type_x KeepSynonyms RespectMultiplicities Nothing + = eq_type_keep_respect +"eqType6" forall env. generic_eq_type_x KeepSynonyms RespectMultiplicities (Just env) + = eq_type_keep_respect_x env + #-} + -- --------------------------------------------------------------- -- | Real worker for 'eqType'. No kind check! -- Inline it at the (handful of local) call sites -- The "generic" bit refers to the flag paramerisation -generic_eq_type :: SynFlag -> MultiplicityFlag - -> RnEnv2 -> Type -> Type - -> Bool +-- See Note [Specialising type equality]. +generic_eq_type_x, inline_generic_eq_type_x + :: SynFlag -> MultiplicityFlag -> Maybe RnEnv2 -> Type -> Type -> EqTyRes +{-# NOINLINE generic_eq_type_x #-} +{-# INLINE inline_generic_eq_type_x #-} + +generic_eq_type_x = inline_generic_eq_type_x -- See Note [Computing equality on types] in Type -{-# INLINE generic_eq_type #-} -- See Note [Specialising generic_eq_type]. -generic_eq_type syn_flag mult_flag - = go +inline_generic_eq_type_x syn_flag mult_flag mb_env + = inline_go where - go_with_kc :: RnEnv2 -> Type -> Type -> Bool - go_with_kc env ty1 ty2 - = go env ty1 ty2 && go env (typeKind ty1) (typeKind ty2) + ------------------- + go = generic_eq_type_x syn_flag mult_flag mb_env - go :: RnEnv2 -> Type -> Type -> Bool - -- See Note [Comparing nullary type synonyms] - go _ t1 t2 | 1# <- reallyUnsafePtrEquality# t1 t2 = True + ------------------- + go_with_kc :: Type -> Type -> EqTyRes + {-# INLINE go_with_kc #-} + go_with_kc ty1 ty2 = case go ty1 ty2 of + NotEq -> NotEq + IsEq -> IsEq + IsEqCast -> go (typeKind ty1) (typeKind ty2) - go _ (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = True + ------------------- + inline_go !t1 !t2 | 1# <- reallyUnsafePtrEquality# t1 t2 = IsEq - go env t1 t2 | ExpandSynonyms <- syn_flag, Just t1' <- coreView t1 = go env t1' t2 - go env t1 t2 | ExpandSynonyms <- syn_flag, Just t2' <- coreView t2 = go env t1 t2' + inline_go (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = IsEq + -- Do this first so the function is strict in both args - go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 - go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 - go env (CastTy t1 _) t2 = go env t1 t2 - go env t1 (CastTy t2 _) = go env t1 t2 - go _ (CoercionTy {}) (CoercionTy {}) = True + inline_go t1 t2 | ExpandSynonyms <- syn_flag, Just t1' <- coreView t1 = go t1' t2 + inline_go t1 t2 | ExpandSynonyms <- syn_flag, Just t2' <- coreView t2 = go t1 t2' - go env (ForAllTy (Bndr tv1 vis1) ty1) - (ForAllTy (Bndr tv2 vis2) ty2) - = vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] - && go env (varType tv1) (varType tv2) -- Always do kind-check - && go (rnBndr2 env tv1 tv2) ty1 ty2 + inline_go (TyVarTy tv1) (TyVarTy tv2) + = case mb_env of + Nothing -> boolEqTyRes (tv1 == tv2) + Just env -> boolEqTyRes (rnOccL env tv1 == rnOccR env tv2) + + inline_go (LitTy lit1) (LitTy lit2) = boolEqTyRes (lit1 == lit2) + inline_go (CastTy t1 _) t2 = addEqCast (go t1 t2) + inline_go t1 (CastTy t2 _) = addEqCast (go t1 t2) + inline_go (CoercionTy {}) (CoercionTy {}) = IsEq -- Make sure we handle all FunTy cases since falling through to the -- AppTy case means that tcSplitAppTyNoView_maybe may see an unzonked -- kind variable, which causes things to blow up. -- See Note [Equality on FunTys] in GHC.Core.TyCo.Rep: we must check -- kinds here - go env (FunTy _ w1 arg1 res1) (FunTy _ w2 arg2 res2) - = go_with_kc env arg1 arg2 - && go_with_kc env res1 res2 - && (case mult_flag of - RespectMultiplicities -> go env w1 w2 - IgnoreMultiplicities -> True) + inline_go (FunTy _ w1 arg1 res1) (FunTy _ w2 arg2 res2) + = go_with_kc arg1 arg2 + &=& go_with_kc res1 res2 + &=& (case mult_flag of + RespectMultiplicities -> go w1 w2 + IgnoreMultiplicities -> IsEq) -- See Note [Equality on AppTys] in GHC.Core.Type - go env (AppTy s1 t1) ty2 + inline_go (AppTy s1 t1) ty2 | Just (s2, t2) <- tcSplitAppTyNoView_maybe ty2 - = go env s1 s2 && go env t1 t2 - go env ty1 (AppTy s2 t2) + = go s1 s2 &=& go t1 t2 + inline_go ty1 (AppTy s2 t2) | Just (s1, t1) <- tcSplitAppTyNoView_maybe ty1 - = go env s1 s2 && go env t1 t2 - - go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) - = tc1 == tc2 && gos env ts1 ts2 - - go _ _ _ = False - - gos _ [] [] = True - gos env (t1:ts1) (t2:ts2) = go env t1 t2 && gos env ts1 ts2 - gos _ _ _ = False - + = go s1 s2 &=& go t1 t2 + + inline_go (TyConApp tc1 ts1) (TyConApp tc2 ts2) + | tc1 == tc2 = gos ts1 ts2 + | otherwise = NotEq + where + gos [] [] = IsEq + gos (t1:ts1) (t2:ts2) = go t1 t2 &=& gos ts1 ts2 + gos _ _ = NotEq + + inline_go ty1@(ForAllTy (Bndr tv1 vis1) body1) + ty2@(ForAllTy (Bndr tv2 vis2) body2) + = case mb_env of + Nothing -> generic_eq_type_x syn_flag mult_flag + (Just (initRnEnv ty1 ty2)) ty1 ty2 + Just env + | vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] + -> go (varType tv1) (varType tv2) -- Always do kind-check + &=& generic_eq_type_x syn_flag mult_flag + (Just (rnBndr2 env tv1 tv2)) body1 body2 + | otherwise + -> NotEq + + inline_go _ _ = NotEq + + +data EqTyRes = IsEq | IsEqCast | NotEq + +(&=&) :: EqTyRes -> EqTyRes -> EqTyRes +(&=&) NotEq _ = NotEq +(&=&) _ NotEq = NotEq +(&=&) IsEq x = x +(&=&) IsEqCast _ = IsEqCast + +addEqCast :: EqTyRes -> EqTyRes +addEqCast NotEq = NotEq +addEqCast _ = IsEqCast + +boolEqTyRes :: Bool -> EqTyRes +boolEqTyRes True = IsEq +boolEqTyRes False = NotEq + +eqTyResBool :: EqTyRes -> Bool +eqTyResBool IsEq = True +eqTyResBool IsEqCast = True +eqTyResBool NotEq = False {- ********************************************************************* * * View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8484934d1431615097fbc6ed4fa09f1cddc8eea8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8484934d1431615097fbc6ed4fa09f1cddc8eea8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Sun Jun 16 22:38:01 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Sun, 16 Jun 2024 18:38:01 -0400 Subject: [Git][ghc/ghc][wip/T24725] Wibble Message-ID: <666f69493f5ec_2102e72ac3be86978d@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24725 at Glasgow Haskell Compiler / GHC Commits: 38275e18 by Simon Peyton Jones at 2024-06-16T23:37:39+01:00 Wibble - - - - - 1 changed file: - compiler/GHC/Core/TyCo/Compare.hs Changes: ===================================== compiler/GHC/Core/TyCo/Compare.hs ===================================== @@ -266,11 +266,13 @@ inline_generic_eq_type_x syn_flag mult_flag mb_env ------------------- go_with_kc :: Type -> Type -> EqTyRes + -- Returns a boolean because it does its own kind-check {-# INLINE go_with_kc #-} - go_with_kc ty1 ty2 = case go ty1 ty2 of - NotEq -> NotEq - IsEq -> IsEq - IsEqCast -> go (typeKind ty1) (typeKind ty2) + go_with_kc ty1 ty2 + = case go ty1 ty2 of + NotEq -> NotEq + IsEq -> IsEq + IsEqCast -> go (typeKind ty1) (typeKind ty2) ------------------- inline_go !t1 !t2 | 1# <- reallyUnsafePtrEquality# t1 t2 = IsEq @@ -297,11 +299,12 @@ inline_generic_eq_type_x syn_flag mult_flag mb_env -- See Note [Equality on FunTys] in GHC.Core.TyCo.Rep: we must check -- kinds here inline_go (FunTy _ w1 arg1 res1) (FunTy _ w2 arg2 res2) - = go_with_kc arg1 arg2 - &=& go_with_kc res1 res2 - &=& (case mult_flag of - RespectMultiplicities -> go w1 w2 - IgnoreMultiplicities -> IsEq) + = killEqCast $ -- All kind checking is done explicitly + go_with_kc arg1 arg2 + &=& go_with_kc res1 res2 + &=& (case mult_flag of + RespectMultiplicities -> go w1 w2 + IgnoreMultiplicities -> IsEq) -- See Note [Equality on AppTys] in GHC.Core.Type inline_go (AppTy s1 t1) ty2 @@ -347,6 +350,10 @@ addEqCast :: EqTyRes -> EqTyRes addEqCast NotEq = NotEq addEqCast _ = IsEqCast +killEqCast :: EqTyRes -> EqTyRes +killEqCast IsEqCast = IsEq +killEqCast x = x + boolEqTyRes :: Bool -> EqTyRes boolEqTyRes True = IsEq boolEqTyRes False = NotEq @@ -579,6 +586,7 @@ comparing type variables is nondeterministic, note the call to nonDetCmpVar in nonDetCmpTypeX. See Note [Unique Determinism] for more details. -} + nonDetCmpType :: Type -> Type -> Ordering {-# INLINE nonDetCmpType #-} nonDetCmpType !t1 !t2 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/38275e18011840c72fddbe4811c3f86872e766b5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/38275e18011840c72fddbe4811c3f86872e766b5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 00:00:44 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Sun, 16 Jun 2024 20:00:44 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Make flip representation polymorphic, similar to ($) and (&) Message-ID: <666f7cac8c500_2102e7375163079966@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - c0abe0f5 by Fendor at 2024-06-16T20:00:12-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - fe93a08b by Fendor at 2024-06-16T20:00:12-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The test T16875 fails on i386-linux-debian10 for the same reason. - - - - - 82d86741 by Fabricio de Sousa Nascimento at 2024-06-16T20:00:14-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Gen/Arrow.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5b92a7b68f004935c961995736575380d1c3dd79...82d86741036e55f7a6f668940a7b1dcad1a701cb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5b92a7b68f004935c961995736575380d1c3dd79...82d86741036e55f7a6f668940a7b1dcad1a701cb You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 05:54:47 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Mon, 17 Jun 2024 01:54:47 -0400 Subject: [Git][ghc/ghc][wip/supersven/AArch64-simplify-BL-instruction] 3 commits: Make flip representation polymorphic, similar to ($) and (&) Message-ID: <666fcfa7e2015_3bd4fc11896b479386@gitlab.mail> Sven Tennie pushed to branch wip/supersven/AArch64-simplify-BL-instruction at Glasgow Haskell Compiler / GHC Commits: e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - 6b0e4235 by Sven Tennie at 2024-06-17T05:54:42+00:00 AArch64: Simplify BL instruction The BL constructor carried unused data in its third argument. - - - - - 30 changed files: - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Zonk/Type.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/40f2538cf87655b932f87fc3af07c5147e50dee0...6b0e4235540f4d38da768deb403e6633199cdbd4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/40f2538cf87655b932f87fc3af07c5147e50dee0...6b0e4235540f4d38da768deb403e6633199cdbd4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 06:02:12 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Mon, 17 Jun 2024 02:02:12 -0400 Subject: [Git][ghc/ghc][wip/supersven/AArch64-delete-unused-RegNos] 3 commits: Make flip representation polymorphic, similar to ($) and (&) Message-ID: <666fd164147da_3bd4fc12f730c8086c@gitlab.mail> Sven Tennie pushed to branch wip/supersven/AArch64-delete-unused-RegNos at Glasgow Haskell Compiler / GHC Commits: e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - 5efec6f7 by Sven Tennie at 2024-06-17T06:02:09+00:00 AArch64: Delete unused RegNos This has the additional benefit of getting rid of the -1 encoding (real registers start at 0.) - - - - - 30 changed files: - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/Language/Haskell/Syntax/Expr.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b784d8133ac94eb5ed5eaa3a0c6bed29a74399dc...5efec6f70d146b11ce84abd14cf497812b181c57 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b784d8133ac94eb5ed5eaa3a0c6bed29a74399dc...5efec6f70d146b11ce84abd14cf497812b181c57 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 08:21:47 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 17 Jun 2024 04:21:47 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: Improve sharing of duplicated values in `ModIface`, fixes #24723 Message-ID: <666ff21b342a5_3bd4fc23592549935e@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 185649d7 by Fendor at 2024-06-17T04:21:07-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 02ea1164 by Fendor at 2024-06-17T04:21:07-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The test T16875 fails on i386-linux-debian10 for the same reason. - - - - - c0947669 by Fabricio de Sousa Nascimento at 2024-06-17T04:21:09-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - 3f9ee626 by Dylan Thinnes at 2024-06-17T04:21:15-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - 24 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Gen/Rule.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs - + testsuite/tests/typecheck/T24026/T24026a.hs - + testsuite/tests/typecheck/T24026/T24026a.stderr - + testsuite/tests/typecheck/T24026/T24026b.hs - + testsuite/tests/typecheck/T24026/T24026b.stderr - + testsuite/tests/typecheck/T24026/all.T - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -98,7 +98,35 @@ module GHC ( lookupGlobalName, findGlobalAnns, mkNamePprCtxForModule, - ModIface, ModIface_(..), + ModIface, + ModIface_( + mi_module, + mi_sig_of, + mi_hsc_src, + mi_src_hash, + mi_hi_bytes, + mi_deps, + mi_usages, + mi_exports, + mi_used_th, + mi_fixities, + mi_warns, + mi_anns, + mi_insts, + mi_fam_insts, + mi_rules, + mi_decls, + mi_extra_decls, + mi_top_env, + mi_hpc, + mi_trust, + mi_trust_pkg, + mi_complete_matches, + mi_docs, + mi_final_exts, + mi_ext_fields + ), + pattern ModIface, SafeHaskellMode(..), -- * Printing ===================================== compiler/GHC/Driver/Env.hs ===================================== @@ -86,8 +86,8 @@ import qualified Data.Set as Set import GHC.Unit.Module.Graph runHsc :: HscEnv -> Hsc a -> IO a -runHsc hsc_env (Hsc hsc) = do - (a, w) <- hsc hsc_env emptyMessages +runHsc hsc_env hsc = do + (a, w) <- runHsc' hsc_env hsc let dflags = hsc_dflags hsc_env let !diag_opts = initDiagOpts dflags !print_config = initPrintConfig dflags ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -64,6 +64,7 @@ module GHC.Driver.Main , hscRecompStatus , hscParse , hscTypecheckRename + , hscTypecheckRenameWithDiagnostics , hscTypecheckAndGetWarnings , hscDesugar , makeSimpleDetails @@ -642,7 +643,14 @@ extract_renamed_stuff mod_summary tc_result = do -- | Rename and typecheck a module, additionally returning the renamed syntax hscTypecheckRename :: HscEnv -> ModSummary -> HsParsedModule -> IO (TcGblEnv, RenamedStuff) -hscTypecheckRename hsc_env mod_summary rdr_module = runHsc hsc_env $ +hscTypecheckRename hsc_env mod_summary rdr_module = + fst <$> hscTypecheckRenameWithDiagnostics hsc_env mod_summary rdr_module + +-- | Rename and typecheck a module, additionally returning the renamed syntax +-- and the diagnostics produced. +hscTypecheckRenameWithDiagnostics :: HscEnv -> ModSummary -> HsParsedModule + -> IO ((TcGblEnv, RenamedStuff), Messages GhcMessage) +hscTypecheckRenameWithDiagnostics hsc_env mod_summary rdr_module = runHsc' hsc_env $ hsc_typecheck True mod_summary (Just rdr_module) -- | Do Typechecking without throwing SourceError exception with -Werror ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -1031,9 +1031,12 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs extra_bndrs = scopedSort extra_tvs ++ extra_dicts where extra_tvs = [ v | v <- extra_vars, isTyVar v ] + + -- isEvVar: this includes coercions, matching what + -- happens in `split_lets` (isDictId, isCoVar) extra_dicts = - [ mkLocalId (localiseName (idName d)) ManyTy (idType d) - | d <- extra_vars, isDictId d ] + [ mkLocalIdOrCoVar (localiseName (idName d)) ManyTy (idType d) + | d <- extra_vars, isEvVar d ] extra_vars = [ v | v <- exprsFreeVarsList args ===================================== compiler/GHC/Iface/Binary.hs ===================================== @@ -18,6 +18,8 @@ module GHC.Iface.Binary ( getSymtabName, CheckHiWay(..), TraceBinIFace(..), + getIfaceWithExtFields, + putIfaceWithExtFields, getWithUserData, putWithUserData, @@ -61,6 +63,8 @@ import Data.Map.Strict (Map) import Data.Word import System.IO.Unsafe import Data.Typeable (Typeable) +import qualified GHC.Data.Strict as Strict +import Data.Function ((&)) -- --------------------------------------------------------------------------- @@ -169,17 +173,29 @@ readBinIface readBinIface profile name_cache checkHiWay traceBinIface hi_path = do (src_hash, bh) <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path - extFields_p <- get bh + mod_iface <- getIfaceWithExtFields name_cache bh - mod_iface <- getWithUserData name_cache bh + return $ mod_iface + & addSourceFingerprint src_hash - seekBinReader bh extFields_p - extFields <- get bh - return mod_iface - { mi_ext_fields = extFields - , mi_src_hash = src_hash - } +getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface +getIfaceWithExtFields name_cache bh = do + -- Start offset for the byte array that contains the serialised 'ModIface'. + start <- tellBinReader bh + extFields_p_rel <- getRelBin bh + + mod_iface <- getWithUserData name_cache bh + + seekBinReaderRel bh extFields_p_rel + extFields <- get bh + -- Store the 'ModIface' byte array, so that we can avoid serialisation if + -- the 'ModIface' isn't modified. + -- See Note [Sharing of ModIface] + modIfaceBinData <- freezeBinHandle bh start + pure $ mod_iface + & set_mi_ext_fields extFields + & set_mi_hi_bytes (FullIfaceBinHandle $ Strict.Just modIfaceBinData) -- | This performs a get action after reading the dictionary and symbol -- table. It is necessary to run this before trying to deserialise any @@ -209,7 +225,7 @@ getTables name_cache bh = do -- add it to the 'ReaderUserData' of 'ReadBinHandle'. decodeReaderTable :: Typeable a => ReaderTable a -> ReadBinHandle -> IO ReadBinHandle decodeReaderTable tbl bh0 = do - table <- Binary.forwardGet bh (getTable tbl bh0) + table <- Binary.forwardGetRel bh (getTable tbl bh0) let binaryReader = mkReaderFromTable tbl table pure $ addReaderToUserData binaryReader bh0 @@ -246,19 +262,24 @@ writeBinIface profile traceBinIface compressionLevel hi_path mod_iface = do put_ bh tag put_ bh (mi_src_hash mod_iface) - extFields_p_p <- tellBinWriter bh - put_ bh extFields_p_p - - putWithUserData traceBinIface compressionLevel bh mod_iface - - extFields_p <- tellBinWriter bh - putAt bh extFields_p_p extFields_p - seekBinWriter bh extFields_p - put_ bh (mi_ext_fields mod_iface) + putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface -- And send the result to the file writeBinMem bh hi_path +-- | Puts the 'ModIface' to the 'WriteBinHandle'. +-- +-- This avoids serialisation of the 'ModIface' if the fields 'mi_hi_bytes' contains a +-- 'Just' value. This field is populated by reading the 'ModIface' using +-- 'getIfaceWithExtFields' and not modifying it in any way afterwards. +putIfaceWithExtFields :: TraceBinIFace -> CompressionIFace -> WriteBinHandle -> ModIface -> IO () +putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface = + case mi_hi_bytes mod_iface of + FullIfaceBinHandle Strict.Nothing -> do + forwardPutRel_ bh (\_ -> put_ bh (mi_ext_fields mod_iface)) $ do + putWithUserData traceBinIface compressionLevel bh mod_iface + FullIfaceBinHandle (Strict.Just binData) -> putFullBinData bh binData + -- | Put a piece of data with an initialised `UserData` field. This -- is necessary if you want to serialise Names or FastStrings. -- It also writes a symbol table and the dictionary. @@ -332,7 +353,7 @@ putAllTables _ [] act = do a <- act pure ([], a) putAllTables bh (x : xs) act = do - (r, (res, a)) <- forwardPut bh (const $ putTable x bh) $ do + (r, (res, a)) <- forwardPutRel bh (const $ putTable x bh) $ do putAllTables bh xs act pure (r : res, a) @@ -484,7 +505,7 @@ to the table we need to deserialise first. What deduplication tables exist and the order of serialisation is currently statically specified in 'putWithTables'. 'putWithTables' also takes care of the serialisation of used deduplication tables. The deserialisation of the deduplication tables happens 'getTables', using 'Binary' utility -functions such as 'forwardGet'. +functions such as 'forwardGetRel'. Here, a visualisation of the table structure we currently have (ignoring 'ExtensibleFields'): @@ -585,7 +606,6 @@ initWriteIfaceType compressionLevel = do putGenericSymTab sym_tab bh ty _ -> putIfaceType bh ty - fullIfaceTypeSerialiser sym_tab bh ty = do put_ bh ifaceTypeSharedByte putGenericSymTab sym_tab bh ty ===================================== compiler/GHC/Iface/Ext/Binary.hs ===================================== @@ -228,7 +228,7 @@ readHieFileContents bh0 name_cache = do get bh1 where get_dictionary tbl bin_handle = do - fsTable <- Binary.forwardGet bin_handle (getTable tbl bin_handle) + fsTable <- Binary.forwardGetRel bin_handle (getTable tbl bin_handle) let fsReader = mkReaderFromTable tbl fsTable bhFs = addReaderToUserData fsReader bin_handle ===================================== compiler/GHC/Iface/Ext/Fields.hs ===================================== @@ -41,7 +41,7 @@ instance Binary ExtensibleFields where -- to point to the start of each payload: forM_ header_entries $ \(field_p_p, dat) -> do field_p <- tellBinWriter bh - putAt bh field_p_p field_p + putAtRel bh field_p_p field_p seekBinWriter bh field_p put_ bh dat @@ -50,11 +50,11 @@ instance Binary ExtensibleFields where -- Get the names and field pointers: header_entries <- replicateM n $ - (,) <$> get bh <*> get bh + (,) <$> get bh <*> getRelBin bh -- Seek to and get each field's payload: fields <- forM header_entries $ \(name, field_p) -> do - seekBinReader bh field_p + seekBinReaderRel bh field_p dat <- get bh return (name, dat) ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -117,6 +117,7 @@ import System.FilePath import System.Directory import GHC.Driver.Env.KnotVars import GHC.Iface.Errors.Types +import Data.Function ((&)) {- ************************************************************************ @@ -515,14 +516,12 @@ loadInterface doc_str mod from ; new_eps_anns <- tcIfaceAnnotations (mi_anns iface) ; new_eps_complete_matches <- tcIfaceCompleteMatches (mi_complete_matches iface) - ; let { final_iface = iface { - mi_decls = panic "No mi_decls in PIT", - mi_insts = panic "No mi_insts in PIT", - mi_fam_insts = panic "No mi_fam_insts in PIT", - mi_rules = panic "No mi_rules in PIT", - mi_anns = panic "No mi_anns in PIT" - } - } + ; let final_iface = iface + & set_mi_decls (panic "No mi_decls in PIT") + & set_mi_insts (panic "No mi_insts in PIT") + & set_mi_fam_insts (panic "No mi_fam_insts in PIT") + & set_mi_rules (panic "No mi_rules in PIT") + & set_mi_anns (panic "No mi_anns in PIT") ; let bad_boot = mi_boot iface == IsBoot && isJust (lookupKnotVars (if_rec_types gbl_env) mod) @@ -1018,13 +1017,13 @@ readIface dflags name_cache wanted_mod file_path = do -- See Note [GHC.Prim] in primops.txt.pp. ghcPrimIface :: ModIface ghcPrimIface - = empty_iface { - mi_exports = ghcPrimExports, - mi_decls = [], - mi_fixities = fixities, - mi_final_exts = (mi_final_exts empty_iface){ mi_fix_fn = mkIfaceFixCache fixities }, - mi_docs = Just ghcPrimDeclDocs -- See Note [GHC.Prim Docs] - } + = empty_iface + & set_mi_exports ghcPrimExports + & set_mi_decls [] + & set_mi_fixities fixities + & set_mi_final_exts ((mi_final_exts empty_iface){ mi_fix_fn = mkIfaceFixCache fixities }) + & set_mi_docs (Just ghcPrimDeclDocs) -- See Note [GHC.Prim Docs] + where empty_iface = emptyFullModIface gHC_PRIM @@ -1108,7 +1107,7 @@ pprModIfaceSimple unit_state iface = -- -- The UnitState is used to pretty-print units pprModIface :: UnitState -> ModIface -> SDoc -pprModIface unit_state iface at ModIface{ mi_final_exts = exts } +pprModIface unit_state iface = vcat [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) @@ -1149,6 +1148,7 @@ pprModIface unit_state iface at ModIface{ mi_final_exts = exts } , text "extensible fields:" $$ nest 2 (pprExtensibleFields (mi_ext_fields iface)) ] where + exts = mi_final_exts iface pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" pp_hsc_src HsSrcFile = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -69,10 +69,13 @@ import GHC.Types.HpcInfo import GHC.Types.CompleteMatch import GHC.Types.SourceText import GHC.Types.SrcLoc ( unLoc ) +import GHC.Types.Name.Cache import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Utils.Logger +import GHC.Utils.Binary +import GHC.Iface.Binary import GHC.Data.FastString import GHC.Data.Maybe @@ -142,14 +145,47 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos = do full_iface <- {-# SCC "addFingerprints" #-} - addFingerprints hsc_env partial_iface{ mi_decls = decls } + addFingerprints hsc_env (set_mi_decls decls partial_iface) -- Debug printing let unit_state = hsc_units hsc_env putDumpFileMaybe (hsc_logger hsc_env) Opt_D_dump_hi "FINAL INTERFACE" FormatText (pprModIface unit_state full_iface) + final_iface <- shareIface (hsc_NC hsc_env) (flagsToIfCompression $ hsc_dflags hsc_env) full_iface + return final_iface - return full_iface +-- | Compress an 'ModIface' and share as many values as possible, depending on the 'CompressionIFace' level. +-- See Note [Sharing of ModIface]. +-- +-- We compress the 'ModIface' by serialising the 'ModIface' to an in-memory byte array, and then deserialising it. +-- The deserialisation will deduplicate certain values depending on the 'CompressionIFace' level. +-- See Note [Deduplication during iface binary serialisation] for how we do that. +-- +-- Additionally, we cache the serialised byte array, so if the 'ModIface' is not modified +-- after calling 'shareIface', 'writeBinIface' will reuse that buffer without serialising the 'ModIface' again. +-- Modifying the 'ModIface' forces us to re-serialise it again. +shareIface :: NameCache -> CompressionIFace -> ModIface -> IO ModIface +shareIface _ NormalCompression mi = do + -- In 'NormalCompression', the sharing isn't reducing the memory usage, as 'Name's and 'FastString's are + -- already shared, and at this compression level, we don't compress/share anything else. + -- Thus, for a brief moment we simply double the memory residency for no reason. + -- Therefore, we only try to share expensive values if the compression mode is higher than + -- 'NormalCompression' + pure mi +shareIface nc compressionLevel mi = do + bh <- openBinMem initBinMemSize + start <- tellBinWriter bh + putIfaceWithExtFields QuietBinIFace compressionLevel bh mi + rbh <- shrinkBinBuffer bh + seekBinReader rbh start + res <- getIfaceWithExtFields nc rbh + let resiface = restoreFromOldModIface mi res + forceModIface resiface + return resiface + +-- | Initial ram buffer to allocate for writing interface files. +initBinMemSize :: Int +initBinMemSize = 1024 * 1024 -- 1 MB updateDecl :: [IfaceDecl] -> Maybe StgCgInfos -> Maybe CmmCgInfos -> [IfaceDecl] updateDecl decls Nothing Nothing = decls @@ -304,40 +340,40 @@ mkIface_ hsc_env icomplete_matches = map mkIfaceCompleteMatch complete_matches !rdrs = maybeGlobalRdrEnv rdr_env - ModIface { - mi_module = this_mod, + emptyPartialModIface this_mod -- Need to record this because it depends on the -instantiated-with flag -- which could change - mi_sig_of = if semantic_mod == this_mod - then Nothing - else Just semantic_mod, - mi_hsc_src = hsc_src, - mi_deps = deps, - mi_usages = usages, - mi_exports = mkIfaceExports exports, + & set_mi_sig_of (if semantic_mod == this_mod + then Nothing + else Just semantic_mod) + & set_mi_hsc_src hsc_src + & set_mi_deps deps + & set_mi_usages usages + & set_mi_exports (mkIfaceExports exports) -- Sort these lexicographically, so that -- the result is stable across compilations - mi_insts = sortBy cmp_inst iface_insts, - mi_fam_insts = sortBy cmp_fam_inst iface_fam_insts, - mi_rules = sortBy cmp_rule iface_rules, - - mi_fixities = fixities, - mi_warns = warns, - mi_anns = annotations, - mi_top_env = rdrs, - mi_used_th = used_th, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_hpc = isHpcUsed hpc_info, - mi_trust = trust_info, - mi_trust_pkg = pkg_trust_req, - mi_complete_matches = icomplete_matches, - mi_docs = docs, - mi_final_exts = (), - mi_ext_fields = emptyExtensibleFields, - mi_src_hash = ms_hs_hash mod_summary - } + & set_mi_insts (sortBy cmp_inst iface_insts) + & set_mi_fam_insts (sortBy cmp_fam_inst iface_fam_insts) + & set_mi_rules (sortBy cmp_rule iface_rules) + + & set_mi_fixities fixities + & set_mi_warns warns + & set_mi_anns annotations + & set_mi_top_env rdrs + & set_mi_used_th used_th + & set_mi_decls decls + & set_mi_extra_decls extra_decls + & set_mi_hpc (isHpcUsed hpc_info) + & set_mi_trust trust_info + & set_mi_trust_pkg pkg_trust_req + & set_mi_complete_matches (icomplete_matches) + & set_mi_docs docs + & set_mi_final_exts () + & set_mi_ext_fields emptyExtensibleFields + & set_mi_src_hash (ms_hs_hash mod_summary) + & set_mi_hi_bytes PartialIfaceBinHandle + where cmp_rule = lexicalCompareFS `on` ifRuleName -- Compare these lexicographically by OccName, *not* by unique, @@ -513,3 +549,22 @@ That is, in Y, In the result of mkIfaceExports, the names are grouped by defining module, so we may need to split up a single Avail into multiple ones. -} + +{- +Note [Sharing of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +A 'ModIface' contains many duplicated values such as 'Name', 'FastString' and 'IfaceType'. +'Name's and 'FastString's are already deduplicated by default using the 'NameCache' and +'FastStringTable' respectively. +However, 'IfaceType' can be quite expensive in terms of memory usage. +To improve the sharing of 'IfaceType', we introduced deduplication tables during +serialisation of 'ModIface', see Note [Deduplication during iface binary serialisation]. + +We can improve the sharing of 'ModIface' at run-time as well, by serialising the 'ModIface' to +an in-memory buffer, and then deserialising it again. +This implicitly shares duplicated values. + +To avoid re-serialising the 'ModIface' when writing it to disk, we save the serialised 'ModIface' buffer +in 'mi_hi_bytes_' field of said 'ModIface'. This buffer is written to disk directly in 'putIfaceWithExtFields'. +If we have to modify the 'ModIface' after 'shareIface' is called, the buffer needs to be discarded. +-} ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -1281,7 +1281,8 @@ addFingerprints hsc_env iface0 , mi_fix_fn = fix_fn , mi_hash_fn = lookupOccEnv local_env } - final_iface = iface0 { mi_decls = sorted_decls, mi_extra_decls = sorted_extra_decls, mi_final_exts = final_iface_exts } + final_iface = completePartialModIface iface0 + sorted_decls sorted_extra_decls final_iface_exts -- return final_iface ===================================== compiler/GHC/Iface/Rename.hs ===================================== @@ -44,6 +44,7 @@ import GHC.Utils.Panic import qualified Data.Traversable as T import Data.IORef +import Data.Function ((&)) tcRnMsgMaybe :: IO (Either (Messages TcRnMessage) a) -> TcM a tcRnMsgMaybe do_this = do @@ -108,13 +109,14 @@ rnModIface hsc_env insts nsubst iface = deps <- rnDependencies (mi_deps iface) -- TODO: -- mi_rules - return iface { mi_module = mod - , mi_sig_of = sig_of - , mi_insts = insts - , mi_fam_insts = fams - , mi_exports = exports - , mi_decls = decls - , mi_deps = deps } + return $ iface + & set_mi_module mod + & set_mi_sig_of sig_of + & set_mi_insts insts + & set_mi_fam_insts fams + & set_mi_exports exports + & set_mi_decls decls + & set_mi_deps deps -- | Rename just the exports of a 'ModIface'. Useful when we're doing -- shaping prior to signature merging. ===================================== compiler/GHC/Tc/Errors/Hole.hs ===================================== @@ -76,7 +76,7 @@ import GHC.Tc.Utils.Unify ( tcSubTypeSigma ) import GHC.HsToCore.Docs ( extractDocs ) import GHC.Hs.Doc -import GHC.Unit.Module.ModIface ( ModIface_(..) ) +import GHC.Unit.Module.ModIface ( mi_docs ) import GHC.Iface.Load ( loadInterfaceForName ) import GHC.Builtin.Utils (knownKeyNames) ===================================== compiler/GHC/Tc/Gen/Rule.hs ===================================== @@ -108,11 +108,13 @@ tcRules decls = mapM (wrapLocMA tcRuleDecls) decls tcRuleDecls :: RuleDecls GhcRn -> TcM (RuleDecls GhcTc) tcRuleDecls (HsRules { rds_ext = src , rds_rules = decls }) - = do { tc_decls <- mapM (wrapLocMA tcRule) decls + = do { maybe_tc_decls <- mapM (wrapLocMA tcRule) decls + ; let tc_decls = [L loc rule | (L loc (Just rule)) <- maybe_tc_decls] ; return $ HsRules { rds_ext = src , rds_rules = tc_decls } } -tcRule :: RuleDecl GhcRn -> TcM (RuleDecl GhcTc) + +tcRule :: RuleDecl GhcRn -> TcM (Maybe (RuleDecl GhcTc)) tcRule (HsRule { rd_ext = ext , rd_name = rname@(L _ name) , rd_act = act @@ -181,7 +183,17 @@ tcRule (HsRule { rd_ext = ext ; (rhs_implic, rhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs rhs_wanted ; emitImplications (lhs_implic `unionBags` rhs_implic) - ; return $ HsRule { rd_ext = ext + + -- A type error on the LHS of a rule will be reported earlier while solving for + -- lhs_implic. However, we should also drop the rule entirely for cases where + -- compilation continues regardless of the error. For example with + -- `-fdefer-type-errors`, where this ill-typed LHS rule may cause follow-on errors + -- (#24026). + ; if anyBag insolubleImplic lhs_implic + then + return Nothing -- The RULE LHS does not type-check and will be dropped. + else + return . Just $ HsRule { rd_ext = ext , rd_name = rname , rd_act = act , rd_tyvs = ty_bndrs -- preserved for ppr-ing ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -1562,7 +1562,8 @@ lookupDeclDoc nm = do -- Wasn't in the current module. Try searching other external ones! mIface <- getExternalModIface nm case mIface of - Just ModIface { mi_docs = Just Docs{docs_decls = dmap} } -> + Just iface + | Just Docs{docs_decls = dmap} <- mi_docs iface -> pure $ renderHsDocStrings . map hsDocString <$> lookupUniqMap dmap nm _ -> pure Nothing @@ -1578,7 +1579,8 @@ lookupArgDoc i nm = do Nothing -> do mIface <- getExternalModIface nm case mIface of - Just ModIface { mi_docs = Just Docs{docs_args = amap} } -> + Just iface + | Just Docs{docs_args = amap} <- mi_docs iface-> pure $ renderHsDocString . hsDocString <$> (lookupUniqMap amap nm >>= IntMap.lookup i) _ -> pure Nothing ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -87,6 +87,7 @@ import Control.Monad import Data.List (find) import GHC.Iface.Errors.Types +import Data.Function ((&)) checkHsigDeclM :: ModIface -> TyThing -> TyThing -> TcRn () checkHsigDeclM sig_iface sig_thing real_thing = do @@ -369,8 +370,8 @@ tcRnMergeSignatures hsc_env hpm orig_tcg_env iface = thinModIface :: [AvailInfo] -> ModIface -> ModIface thinModIface avails iface = - iface { - mi_exports = avails, + iface + & set_mi_exports avails -- mi_fixities = ..., -- mi_warns = ..., -- mi_anns = ..., @@ -378,10 +379,9 @@ thinModIface avails iface = -- perhaps there might be two IfaceTopBndr that are the same -- OccName but different Name. Requires better understanding -- of invariants here. - mi_decls = exported_decls ++ non_exported_decls ++ dfun_decls + & set_mi_decls (exported_decls ++ non_exported_decls ++ dfun_decls) -- mi_insts = ..., -- mi_fam_insts = ..., - } where decl_pred occs decl = nameOccName (ifName decl) `elemOccSet` occs filter_decls occs = filter (decl_pred occs . snd) (mi_decls iface) ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -4,10 +4,68 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE PatternSynonyms #-} + module GHC.Unit.Module.ModIface ( ModIface - , ModIface_ (..) + , ModIface_ + ( mi_module + , mi_sig_of + , mi_hsc_src + , mi_deps + , mi_usages + , mi_exports + , mi_used_th + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_extra_decls + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_hpc + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_final_exts + , mi_ext_fields + , mi_src_hash + , mi_hi_bytes + ) + , pattern ModIface + , restoreFromOldModIface + , addSourceFingerprint + , set_mi_module + , set_mi_sig_of + , set_mi_hsc_src + , set_mi_src_hash + , set_mi_hi_bytes + , set_mi_deps + , set_mi_usages + , set_mi_exports + , set_mi_used_th + , set_mi_fixities + , set_mi_warns + , set_mi_anns + , set_mi_insts + , set_mi_fam_insts + , set_mi_rules + , set_mi_decls + , set_mi_extra_decls + , set_mi_top_env + , set_mi_hpc + , set_mi_trust + , set_mi_trust_pkg + , set_mi_complete_matches + , set_mi_docs + , set_mi_final_exts + , set_mi_ext_fields + , completePartialModIface + , IfaceBinHandle(..) , PartialModIface , ModIfaceBackend (..) , IfaceDeclExts @@ -47,6 +105,7 @@ import GHC.Types.Fixity import GHC.Types.Fixity.Env import GHC.Types.HpcInfo import GHC.Types.Name +import GHC.Types.Name.Reader (IfGlobalRdrEnv) import GHC.Types.SafeHaskell import GHC.Types.SourceFile import GHC.Types.Unique.DSet @@ -59,7 +118,7 @@ import GHC.Utils.Binary import Control.DeepSeq import Control.Exception -import GHC.Types.Name.Reader (IfGlobalRdrEnv) +import qualified GHC.Data.Strict as Strict {- Note [Interface file stages] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -141,7 +200,17 @@ type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where IfaceBackendExts 'ModIfaceCore = () IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend - +-- | In-memory byte array representation of a 'ModIface'. +-- +-- See Note [Sharing of ModIface] for why we need this. +data IfaceBinHandle (phase :: ModIfacePhase) where + -- | A partial 'ModIface' cannot be serialised to disk. + PartialIfaceBinHandle :: IfaceBinHandle 'ModIfaceCore + -- | Optional 'FullBinData' that can be serialised to disk directly. + -- + -- See Note [Private fields in ModIface] for when this fields needs to be cleared + -- (e.g., set to 'Nothing'). + FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal -- | A 'ModIface' plus a 'ModDetails' summarises everything we know -- about a compiled module. The 'ModIface' is the stuff *before* linking, @@ -155,62 +224,65 @@ type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where -- -- See Note [Strictness in ModIface] to learn about why some fields are -- strict and others are not. +-- +-- See Note [Private fields in ModIface] to learn why we don't export any of the +-- fields. data ModIface_ (phase :: ModIfacePhase) - = ModIface { - mi_module :: !Module, -- ^ Name of the module we are for - mi_sig_of :: !(Maybe Module), -- ^ Are we a sig of another mod? + = PrivateModIface { + mi_module_ :: !Module, -- ^ Name of the module we are for + mi_sig_of_ :: !(Maybe Module), -- ^ Are we a sig of another mod? - mi_hsc_src :: !HscSource, -- ^ Boot? Signature? + mi_hsc_src_ :: !HscSource, -- ^ Boot? Signature? - mi_deps :: Dependencies, + mi_deps_ :: Dependencies, -- ^ The dependencies of the module. This is -- consulted for directly-imported modules, but not -- for anything else (hence lazy) - mi_usages :: [Usage], + mi_usages_ :: [Usage], -- ^ Usages; kept sorted so that it's easy to decide -- whether to write a new iface file (changing usages -- doesn't affect the hash of this module) -- NOT STRICT! we read this field lazily from the interface file -- It is *only* consulted by the recompilation checker - mi_exports :: ![IfaceExport], + mi_exports_ :: ![IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier -- Records the modules that are the declaration points for things -- exported by this module, and the 'OccName's of those things - mi_used_th :: !Bool, + mi_used_th_ :: !Bool, -- ^ Module required TH splices when it was compiled. -- This disables recompilation avoidance (see #481). - mi_fixities :: [(OccName,Fixity)], + mi_fixities_ :: [(OccName,Fixity)], -- ^ Fixities -- NOT STRICT! we read this field lazily from the interface file - mi_warns :: IfaceWarnings, + mi_warns_ :: IfaceWarnings, -- ^ Warnings -- NOT STRICT! we read this field lazily from the interface file - mi_anns :: [IfaceAnnotation], + mi_anns_ :: [IfaceAnnotation], -- ^ Annotations -- NOT STRICT! we read this field lazily from the interface file - mi_decls :: [IfaceDeclExts phase], + mi_decls_ :: [IfaceDeclExts phase], -- ^ Type, class and variable declarations -- The hash of an Id changes if its fixity or deprecations change -- (as well as its type of course) -- Ditto data constructors, class operations, except that -- the hash of the parent class/tycon changes - mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], + mi_extra_decls_ :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], -- ^ Extra variable definitions which are **NOT** exposed but when -- combined with mi_decls allows us to restart code generation. -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] - mi_top_env :: !(Maybe IfaceTopEnv), + mi_top_env_ :: !(Maybe IfaceTopEnv), -- ^ Just enough information to reconstruct the top level environment in -- the /original source/ code for this module. which -- is NOT the same as mi_exports, nor mi_decls (which @@ -226,36 +298,36 @@ data ModIface_ (phase :: ModIfacePhase) -- 'HomeModInfo', but that leads to more plumbing. -- Instance declarations and rules - mi_insts :: [IfaceClsInst], -- ^ Sorted class instance - mi_fam_insts :: [IfaceFamInst], -- ^ Sorted family instances - mi_rules :: [IfaceRule], -- ^ Sorted rules + mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance + mi_fam_insts_ :: [IfaceFamInst], -- ^ Sorted family instances + mi_rules_ :: [IfaceRule], -- ^ Sorted rules - mi_hpc :: !AnyHpcUsage, + mi_hpc_ :: !AnyHpcUsage, -- ^ True if this program uses Hpc at any point in the program. - mi_trust :: !IfaceTrustInfo, + mi_trust_ :: !IfaceTrustInfo, -- ^ Safe Haskell Trust information for this module. - mi_trust_pkg :: !Bool, + mi_trust_pkg_ :: !Bool, -- ^ Do we require the package this module resides in be trusted -- to trust this module? This is used for the situation where a -- module is Safe (so doesn't require the package be trusted -- itself) but imports some trustworthy modules from its own -- package (which does require its own package be trusted). -- See Note [Trust Own Package] in GHC.Rename.Names - mi_complete_matches :: ![IfaceCompleteMatch], + mi_complete_matches_ :: ![IfaceCompleteMatch], - mi_docs :: !(Maybe Docs), + mi_docs_ :: !(Maybe Docs), -- ^ Docstrings and related data for use by haddock, the ghci -- @:doc@ command, and other tools. -- -- @Just _@ @<=>@ the module was built with @-haddock at . - mi_final_exts :: !(IfaceBackendExts phase), + mi_final_exts_ :: !(IfaceBackendExts phase), -- ^ Either `()` or `ModIfaceBackend` for -- a fully instantiated interface. - mi_ext_fields :: !ExtensibleFields, + mi_ext_fields_ :: !ExtensibleFields, -- ^ Additional optional fields, where the Map key represents -- the field name, resulting in a (size, serialized data) pair. -- Because the data is intended to be serialized through the @@ -264,8 +336,13 @@ data ModIface_ (phase :: ModIfacePhase) -- chosen over `ByteString`s. -- - mi_src_hash :: !Fingerprint + mi_src_hash_ :: !Fingerprint, -- ^ Hash of the .hs source, used for recompilation checking. + mi_hi_bytes_ :: !(IfaceBinHandle phase) + -- ^ A serialised in-memory buffer of this 'ModIface'. + -- If this handle is given, we can avoid serialising the 'ModIface' + -- when writing this 'ModIface' to disk, and write this buffer to disk instead. + -- See Note [Sharing of ModIface]. } -- Enough information to reconstruct the top level environment for a module @@ -354,34 +431,40 @@ renameFreeHoles fhs insts = -- See Note [Strictness in ModIface] about where we use lazyPut vs put instance Binary ModIface where - put_ bh (ModIface { - mi_module = mod, - mi_sig_of = sig_of, - mi_hsc_src = hsc_src, - mi_src_hash = _src_hash, -- Don't `put_` this in the instance + put_ bh (PrivateModIface { + mi_module_ = mod, + mi_sig_of_ = sig_of, + mi_hsc_src_ = hsc_src, + mi_src_hash_ = _src_hash, -- Don't `put_` this in the instance -- because we are going to write it -- out separately in the actual file - mi_deps = deps, - mi_usages = usages, - mi_exports = exports, - mi_used_th = used_th, - mi_fixities = fixities, - mi_warns = warns, - mi_anns = anns, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_insts = insts, - mi_fam_insts = fam_insts, - mi_rules = rules, - mi_hpc = hpc_info, - mi_trust = trust, - mi_trust_pkg = trust_pkg, - mi_complete_matches = complete_matches, - mi_docs = docs, - mi_ext_fields = _ext_fields, -- Don't `put_` this in the instance so we + mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself + -- may contain an in-memory byte array buffer for this + -- 'ModIface'. If we used 'put_' on this 'ModIface', then + -- we likely have a good reason, and do not want to reuse + -- the byte array. + -- See Note [Private fields in ModIface] + mi_deps_ = deps, + mi_usages_ = usages, + mi_exports_ = exports, + mi_used_th_ = used_th, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_anns_ = anns, + mi_decls_ = decls, + mi_extra_decls_ = extra_decls, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_hpc_ = hpc_info, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, + mi_complete_matches_ = complete_matches, + mi_docs_ = docs, + mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file - mi_final_exts = ModIfaceBackend { + mi_final_exts_ = ModIfaceBackend { mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, mi_flag_hash = flag_hash, @@ -455,34 +538,39 @@ instance Binary ModIface where trust_pkg <- get bh complete_matches <- get bh docs <- lazyGetMaybe bh - return (ModIface { - mi_module = mod, - mi_sig_of = sig_of, - mi_hsc_src = hsc_src, - mi_src_hash = fingerprint0, -- placeholder because this is dealt + return (PrivateModIface { + mi_module_ = mod, + mi_sig_of_ = sig_of, + mi_hsc_src_ = hsc_src, + mi_src_hash_ = fingerprint0, -- placeholder because this is dealt -- with specially when the file is read - mi_deps = deps, - mi_usages = usages, - mi_exports = exports, - mi_used_th = used_th, - mi_anns = anns, - mi_fixities = fixities, - mi_warns = warns, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_top_env = Nothing, - mi_insts = insts, - mi_fam_insts = fam_insts, - mi_rules = rules, - mi_hpc = hpc_info, - mi_trust = trust, - mi_trust_pkg = trust_pkg, + mi_hi_bytes_ = + -- We can't populate this field here, as we are + -- missing the 'mi_ext_fields_' field, which is + -- handled in 'getIfaceWithExtFields'. + FullIfaceBinHandle Strict.Nothing, + mi_deps_ = deps, + mi_usages_ = usages, + mi_exports_ = exports, + mi_used_th_ = used_th, + mi_anns_ = anns, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_decls_ = decls, + mi_extra_decls_ = extra_decls, + mi_top_env_ = Nothing, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_hpc_ = hpc_info, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, -- And build the cached values - mi_complete_matches = complete_matches, - mi_docs = docs, - mi_ext_fields = emptyExtensibleFields, -- placeholder because this is dealt + mi_complete_matches_ = complete_matches, + mi_docs_ = docs, + mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read - mi_final_exts = ModIfaceBackend { + mi_final_exts_ = ModIfaceBackend { mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, mi_flag_hash = flag_hash, @@ -499,42 +587,46 @@ instance Binary ModIface where mi_hash_fn = mkIfaceHashCache decls }}) + -- | The original names declared of a certain module that are exported type IfaceExport = AvailInfo emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod - = ModIface { mi_module = mod, - mi_sig_of = Nothing, - mi_hsc_src = HsSrcFile, - mi_src_hash = fingerprint0, - mi_deps = noDependencies, - mi_usages = [], - mi_exports = [], - mi_used_th = False, - mi_fixities = [], - mi_warns = IfWarnSome [] [], - mi_anns = [], - mi_insts = [], - mi_fam_insts = [], - mi_rules = [], - mi_decls = [], - mi_extra_decls = Nothing, - mi_top_env = Nothing, - mi_hpc = False, - mi_trust = noIfaceTrustInfo, - mi_trust_pkg = False, - mi_complete_matches = [], - mi_docs = Nothing, - mi_final_exts = (), - mi_ext_fields = emptyExtensibleFields - } + = PrivateModIface + { mi_module_ = mod, + mi_sig_of_ = Nothing, + mi_hsc_src_ = HsSrcFile, + mi_src_hash_ = fingerprint0, + mi_hi_bytes_ = PartialIfaceBinHandle, + mi_deps_ = noDependencies, + mi_usages_ = [], + mi_exports_ = [], + mi_used_th_ = False, + mi_fixities_ = [], + mi_warns_ = IfWarnSome [] [], + mi_anns_ = [], + mi_insts_ = [], + mi_fam_insts_ = [], + mi_rules_ = [], + mi_decls_ = [], + mi_extra_decls_ = Nothing, + mi_top_env_ = Nothing, + mi_hpc_ = False, + mi_trust_ = noIfaceTrustInfo, + mi_trust_pkg_ = False, + mi_complete_matches_ = [], + mi_docs_ = Nothing, + mi_final_exts_ = (), + mi_ext_fields_ = emptyExtensibleFields + } emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) - { mi_decls = [] - , mi_final_exts = ModIfaceBackend + { mi_decls_ = [] + , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + , mi_final_exts_ = ModIfaceBackend { mi_iface_hash = fingerprint0, mi_mod_hash = fingerprint0, mi_flag_hash = fingerprint0, @@ -569,36 +661,38 @@ emptyIfaceHashCache _occ = Nothing instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (ModIface{ mi_module, mi_sig_of, mi_hsc_src, mi_deps, mi_usages - , mi_exports, mi_used_th, mi_fixities, mi_warns, mi_anns - , mi_decls, mi_extra_decls, mi_top_env, mi_insts - , mi_fam_insts, mi_rules, mi_hpc, mi_trust, mi_trust_pkg - , mi_complete_matches, mi_docs, mi_final_exts - , mi_ext_fields, mi_src_hash }) - = rnf mi_module - `seq` rnf mi_sig_of - `seq` mi_hsc_src - `seq` mi_deps - `seq` mi_usages - `seq` mi_exports - `seq` rnf mi_used_th - `seq` mi_fixities - `seq` rnf mi_warns - `seq` rnf mi_anns - `seq` rnf mi_decls - `seq` rnf mi_extra_decls - `seq` rnf mi_top_env - `seq` rnf mi_insts - `seq` rnf mi_fam_insts - `seq` rnf mi_rules - `seq` rnf mi_hpc - `seq` mi_trust - `seq` rnf mi_trust_pkg - `seq` rnf mi_complete_matches - `seq` rnf mi_docs - `seq` mi_final_exts - `seq` mi_ext_fields - `seq` rnf mi_src_hash + rnf (PrivateModIface + { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_, mi_usages_ + , mi_exports_, mi_used_th_, mi_fixities_, mi_warns_, mi_anns_ + , mi_decls_, mi_extra_decls_, mi_top_env_, mi_insts_ + , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_ + , mi_complete_matches_, mi_docs_, mi_final_exts_ + , mi_ext_fields_, mi_src_hash_ }) + = rnf mi_module_ + `seq` rnf mi_sig_of_ + `seq` mi_hsc_src_ + `seq` mi_hi_bytes_ + `seq` mi_deps_ + `seq` mi_usages_ + `seq` mi_exports_ + `seq` rnf mi_used_th_ + `seq` mi_fixities_ + `seq` rnf mi_warns_ + `seq` rnf mi_anns_ + `seq` rnf mi_decls_ + `seq` rnf mi_extra_decls_ + `seq` rnf mi_top_env_ + `seq` rnf mi_insts_ + `seq` rnf mi_fam_insts_ + `seq` rnf mi_rules_ + `seq` rnf mi_hpc_ + `seq` mi_trust_ + `seq` rnf mi_trust_pkg_ + `seq` rnf mi_complete_matches_ + `seq` rnf mi_docs_ + `seq` mi_final_exts_ + `seq` mi_ext_fields_ + `seq` rnf mi_src_hash_ `seq` () instance NFData (ModIfaceBackend) where @@ -638,5 +732,286 @@ type WhetherHasOrphans = Bool -- | Does this module define family instances? type WhetherHasFamInst = Bool +-- ---------------------------------------------------------------------------- +-- Modify a 'ModIface'. +-- ---------------------------------------------------------------------------- + +{- +Note [Private fields in ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The fields of 'ModIface' are private, e.g., not exported, to make the API +impossible to misuse. A 'ModIface' can be "compressed" in-memory using +'shareIface', which serialises the 'ModIface' to an in-memory buffer. +This has the advantage of reducing memory usage of 'ModIface', reducing the +overall memory usage of GHC. +See Note [Sharing of ModIface]. + +This in-memory buffer can be reused, if and only if the 'ModIface' is not +modified after it has been "compressed"/shared via 'shareIface'. Instead of +serialising 'ModIface', we simply write the in-memory buffer to disk directly. + +However, we can't rely that a 'ModIface' isn't modified after 'shareIface' has +been called. Thus, we make all fields of 'ModIface' private and modification +only happens via exported update functions, such as 'set_mi_decls'. +These functions unconditionally clear any in-memory buffer if used, forcing us +to serialise the 'ModIface' to disk again. +-} + +-- | Given a 'PartialModIface', turn it into a 'ModIface' by completing +-- missing fields. +completePartialModIface :: PartialModIface + -> [(Fingerprint, IfaceDecl)] + -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] + -> ModIfaceBackend + -> ModIface +completePartialModIface partial decls extra_decls final_exts = partial + { mi_decls_ = decls + , mi_extra_decls_ = extra_decls + , mi_final_exts_ = final_exts + , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + } + +-- | Add a source fingerprint to a 'ModIface_' without invalidating the byte array +-- buffer 'mi_hi_bytes'. +-- This is a variant of 'set_mi_src_hash' which does invalidate the buffer. +-- +-- The 'mi_src_hash' is computed outside of 'ModIface_' based on the 'ModSummary'. +addSourceFingerprint :: Fingerprint -> ModIface_ phase -> ModIface_ phase +addSourceFingerprint val iface = iface { mi_src_hash_ = val } + +-- | Copy fields that aren't serialised to disk to the new 'ModIface_'. +-- This includes especially hashes that are usually stored in the interface +-- file header and 'mi_top_env'. +-- +-- We need this function after calling 'shareIface', to make sure the +-- 'ModIface_' doesn't lose any information. This function does not discard +-- the in-memory byte array buffer 'mi_hi_bytes'. +restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase +restoreFromOldModIface old new = new + { mi_top_env_ = mi_top_env_ old + , mi_hsc_src_ = mi_hsc_src_ old + , mi_src_hash_ = mi_src_hash_ old + } + +set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase +set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } + +set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase +set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } + +set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase +set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } + +set_mi_src_hash :: Fingerprint -> ModIface_ phase -> ModIface_ phase +set_mi_src_hash val iface = clear_mi_hi_bytes $ iface { mi_src_hash_ = val } + +set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase +set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } + +set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase +set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } + +set_mi_usages :: [Usage] -> ModIface_ phase -> ModIface_ phase +set_mi_usages val iface = clear_mi_hi_bytes $ iface { mi_usages_ = val } +set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase +set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } + +set_mi_used_th :: Bool -> ModIface_ phase -> ModIface_ phase +set_mi_used_th val iface = clear_mi_hi_bytes $ iface { mi_used_th_ = val } + +set_mi_fixities :: [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase +set_mi_fixities val iface = clear_mi_hi_bytes $ iface { mi_fixities_ = val } + +set_mi_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase +set_mi_warns val iface = clear_mi_hi_bytes $ iface { mi_warns_ = val } + +set_mi_anns :: [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase +set_mi_anns val iface = clear_mi_hi_bytes $ iface { mi_anns_ = val } + +set_mi_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase +set_mi_insts val iface = clear_mi_hi_bytes $ iface { mi_insts_ = val } + +set_mi_fam_insts :: [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase +set_mi_fam_insts val iface = clear_mi_hi_bytes $ iface { mi_fam_insts_ = val } + +set_mi_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase +set_mi_rules val iface = clear_mi_hi_bytes $ iface { mi_rules_ = val } + +set_mi_decls :: [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase +set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls_ = val } + +set_mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase +set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val } + +set_mi_top_env :: Maybe IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } + +set_mi_hpc :: AnyHpcUsage -> ModIface_ phase -> ModIface_ phase +set_mi_hpc val iface = clear_mi_hi_bytes $ iface { mi_hpc_ = val } + +set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase +set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val } + +set_mi_trust_pkg :: Bool -> ModIface_ phase -> ModIface_ phase +set_mi_trust_pkg val iface = clear_mi_hi_bytes $ iface { mi_trust_pkg_ = val } + +set_mi_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase +set_mi_complete_matches val iface = clear_mi_hi_bytes $ iface { mi_complete_matches_ = val } + +set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase +set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } + +set_mi_final_exts :: IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase +set_mi_final_exts val iface = clear_mi_hi_bytes $ iface { mi_final_exts_ = val } + +set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase +set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } + +-- | Invalidate any byte array buffer we might have. +clear_mi_hi_bytes :: ModIface_ phase -> ModIface_ phase +clear_mi_hi_bytes iface = iface + { mi_hi_bytes_ = case mi_hi_bytes iface of + PartialIfaceBinHandle -> PartialIfaceBinHandle + FullIfaceBinHandle _ -> FullIfaceBinHandle Strict.Nothing + } + +-- ---------------------------------------------------------------------------- +-- 'ModIface' pattern synonyms to keep breakage low. +-- ---------------------------------------------------------------------------- + +{- +Note [Inline Pattern synonym of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The introduction of the 'ModIface' pattern synonym originally caused an increase +in allocated bytes in multiple performance tests. +In some benchmarks, it was a 2~3% increase. + +Without {-# INLINE ModIface #-}, the generated core reveals the reason for this increase. +We show the core for the 'mi_module' record selector: + +@ + mi_module + = \ @phase iface -> $w$mModIface iface mi_module1 + + $w$mModIface + = \ @phase iface cont -> + case iface of + { PrivateModIface a b ... z -> + cont + a + b + ... + z + } + + mi_module1 + = \ @phase + a + _ + ... + _ -> + a +@ + +Thus, we can see the '$w$mModIface' is not inlined, leading to an increase in +the allocated bytes. + +However, with the pragma, the correct core is generated: + +@ + mi_module = mi_module_ +@ + +-} +-- See Note [Inline Pattern synonym of ModIface] for why we have all these +-- inline pragmas. +{-# INLINE ModIface #-} +{-# INLINE mi_module #-} +{-# INLINE mi_sig_of #-} +{-# INLINE mi_hsc_src #-} +{-# INLINE mi_deps #-} +{-# INLINE mi_usages #-} +{-# INLINE mi_exports #-} +{-# INLINE mi_used_th #-} +{-# INLINE mi_fixities #-} +{-# INLINE mi_warns #-} +{-# INLINE mi_anns #-} +{-# INLINE mi_decls #-} +{-# INLINE mi_extra_decls #-} +{-# INLINE mi_top_env #-} +{-# INLINE mi_insts #-} +{-# INLINE mi_fam_insts #-} +{-# INLINE mi_rules #-} +{-# INLINE mi_hpc #-} +{-# INLINE mi_trust #-} +{-# INLINE mi_trust_pkg #-} +{-# INLINE mi_complete_matches #-} +{-# INLINE mi_docs #-} +{-# INLINE mi_final_exts #-} +{-# INLINE mi_ext_fields #-} +{-# INLINE mi_src_hash #-} +{-# INLINE mi_hi_bytes #-} + +pattern ModIface :: + Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] -> + [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> + [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> + Maybe IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> + AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> + IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> + ModIface_ phase +pattern ModIface + { mi_module + , mi_sig_of + , mi_hsc_src + , mi_deps + , mi_usages + , mi_exports + , mi_used_th + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_extra_decls + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_hpc + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_final_exts + , mi_ext_fields + , mi_src_hash + , mi_hi_bytes + } <- PrivateModIface + { mi_module_ = mi_module + , mi_sig_of_ = mi_sig_of + , mi_hsc_src_ = mi_hsc_src + , mi_deps_ = mi_deps + , mi_usages_ = mi_usages + , mi_exports_ = mi_exports + , mi_used_th_ = mi_used_th + , mi_fixities_ = mi_fixities + , mi_warns_ = mi_warns + , mi_anns_ = mi_anns + , mi_decls_ = mi_decls + , mi_extra_decls_ = mi_extra_decls + , mi_top_env_ = mi_top_env + , mi_insts_ = mi_insts + , mi_fam_insts_ = mi_fam_insts + , mi_rules_ = mi_rules + , mi_hpc_ = mi_hpc + , mi_trust_ = mi_trust + , mi_trust_pkg_ = mi_trust_pkg + , mi_complete_matches_ = mi_complete_matches + , mi_docs_ = mi_docs + , mi_final_exts_ = mi_final_exts + , mi_ext_fields_ = mi_ext_fields + , mi_src_hash_ = mi_src_hash + , mi_hi_bytes_ = mi_hi_bytes + } ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -19,7 +19,7 @@ -- http://www.cs.york.ac.uk/fp/nhc98/ module GHC.Utils.Binary - ( {-type-} Bin, + ( {-type-} Bin, RelBin(..), getRelBin, {-class-} Binary(..), {-type-} ReadBinHandle, WriteBinHandle, SymbolTable, Dictionary, @@ -32,10 +32,14 @@ module GHC.Utils.Binary seekBinWriter, seekBinReader, + seekBinReaderRel, tellBinReader, tellBinWriter, castBin, withBinBuffer, + freezeWriteHandle, + shrinkBinBuffer, + thawReadHandle, foldGet, foldGet', @@ -44,7 +48,9 @@ module GHC.Utils.Binary readBinMemN, putAt, getAt, + putAtRel, forwardPut, forwardPut_, forwardGet, + forwardPutRel, forwardPutRel_, forwardGetRel, -- * For writing instances putByte, @@ -99,6 +105,8 @@ module GHC.Utils.Binary BindingName(..), simpleBindingNameWriter, simpleBindingNameReader, + FullBinData(..), freezeBinHandle, thawBinHandle, putFullBinData, + BinArray, ) where import GHC.Prelude @@ -107,6 +115,7 @@ import Language.Haskell.Syntax.Module.Name (ModuleName(..)) import {-# SOURCE #-} GHC.Types.Name (Name) import GHC.Data.FastString +import GHC.Data.TrieMap import GHC.Utils.Panic.Plain import GHC.Types.Unique.FM import GHC.Data.FastMutInt @@ -115,7 +124,6 @@ import GHC.Types.SrcLoc import GHC.Types.Unique import qualified GHC.Data.Strict as Strict import GHC.Utils.Outputable( JoinPointHood(..) ) -import GHC.Utils.Misc ( HasCallStack, HasDebugCallStack ) import Control.DeepSeq import Control.Monad ( when, (<$!>), unless, forM_, void ) @@ -123,7 +131,7 @@ import Foreign hiding (shiftL, shiftR, void) import Data.Array import Data.Array.IO import Data.Array.Unsafe -import Data.ByteString (ByteString) +import Data.ByteString (ByteString, copy) import Data.Coerce import qualified Data.ByteString.Internal as BS import qualified Data.ByteString.Unsafe as BS @@ -152,8 +160,6 @@ import GHC.ForeignPtr ( unsafeWithForeignPtr ) import Unsafe.Coerce (unsafeCoerce) -import GHC.Data.TrieMap - type BinArray = ForeignPtr Word8 #if !MIN_VERSION_base(4,15,0) @@ -193,6 +199,62 @@ dataHandle (BinData size bin) = do handleData :: WriteBinHandle -> IO BinData handleData (WriteBinMem _ ixr _ binr) = BinData <$> readFastMutInt ixr <*> readIORef binr +--------------------------------------------------------------- +-- FullBinData +--------------------------------------------------------------- + +-- | 'FullBinData' stores a slice to a 'BinArray'. +-- +-- It requires less memory than 'ReadBinHandle', and can be constructed from +-- a 'ReadBinHandle' via 'freezeBinHandle' and turned back into a +-- 'ReadBinHandle' using 'thawBinHandle'. +-- Additionally, the byte array slice can be put into a 'WriteBinHandle' without extra +-- conversions via 'putFullBinData'. +data FullBinData = FullBinData + { fbd_readerUserData :: ReaderUserData + -- ^ 'ReaderUserData' that can be used to resume reading. + , fbd_off_s :: {-# UNPACK #-} !Int + -- ^ start offset + , fbd_off_e :: {-# UNPACK #-} !Int + -- ^ end offset + , fbd_size :: {-# UNPACK #-} !Int + -- ^ total buffer size + , fbd_buffer :: {-# UNPACK #-} !BinArray + } + +-- Equality and Ord assume that two distinct buffers are different, even if they compare the same things. +instance Eq FullBinData where + (FullBinData _ b c d e) == (FullBinData _ b1 c1 d1 e1) = b == b1 && c == c1 && d == d1 && e == e1 + +instance Ord FullBinData where + compare (FullBinData _ b c d e) (FullBinData _ b1 c1 d1 e1) = + compare b b1 `mappend` compare c c1 `mappend` compare d d1 `mappend` compare e e1 + +-- | Write the 'FullBinData' slice into the 'WriteBinHandle'. +putFullBinData :: WriteBinHandle -> FullBinData -> IO () +putFullBinData bh (FullBinData _ o1 o2 _sz ba) = do + let sz = o2 - o1 + putPrim bh sz $ \dest -> + unsafeWithForeignPtr (ba `plusForeignPtr` o1) $ \orig -> + copyBytes dest orig sz + +-- | Freeze a 'ReadBinHandle' and a start index into a 'FullBinData'. +-- +-- 'FullBinData' stores a slice starting from the 'Bin a' location to the current +-- offset of the 'ReadBinHandle'. +freezeBinHandle :: ReadBinHandle -> Bin a -> IO FullBinData +freezeBinHandle (ReadBinMem user_data ixr sz binr) (BinPtr start) = do + ix <- readFastMutInt ixr + pure (FullBinData user_data start ix sz binr) + +-- | Turn the 'FullBinData' into a 'ReadBinHandle', setting the 'ReadBinHandle' +-- offset to the start of the 'FullBinData' and restore the 'ReaderUserData' that was +-- obtained from 'freezeBinHandle'. +thawBinHandle :: FullBinData -> IO ReadBinHandle +thawBinHandle (FullBinData user_data ix _end sz ba) = do + ixr <- newFastMutInt ix + return $ ReadBinMem user_data ixr sz ba + --------------------------------------------------------------- -- BinHandle --------------------------------------------------------------- @@ -286,9 +348,47 @@ unsafeUnpackBinBuffer (BS.BS arr len) = do newtype Bin a = BinPtr Int deriving (Eq, Ord, Show, Bounded) +-- | Like a 'Bin' but is used to store relative offset pointers. +-- Relative offset pointers store a relative location, but also contain an +-- anchor that allow to obtain the absolute offset. +data RelBin a = RelBin + { relBin_anchor :: {-# UNPACK #-} !(Bin a) + -- ^ Absolute position from where we read 'relBin_offset'. + , relBin_offset :: {-# UNPACK #-} !(RelBinPtr a) + -- ^ Relative offset to 'relBin_anchor'. + -- The absolute position of the 'RelBin' is @relBin_anchor + relBin_offset@ + } + deriving (Eq, Ord, Show, Bounded) + +-- | A 'RelBinPtr' is like a 'Bin', but contains a relative offset pointer +-- instead of an absolute offset. +newtype RelBinPtr a = RelBinPtr (Bin a) + deriving (Eq, Ord, Show, Bounded) + castBin :: Bin a -> Bin b castBin (BinPtr i) = BinPtr i +-- | Read a relative offset location and wrap it in 'RelBin'. +-- +-- The resulting 'RelBin' can be translated into an absolute offset location using +-- 'makeAbsoluteBin' +getRelBin :: ReadBinHandle -> IO (RelBin a) +getRelBin bh = do + start <- tellBinReader bh + off <- get bh + pure $ RelBin start off + +makeAbsoluteBin :: RelBin a -> Bin a +makeAbsoluteBin (RelBin (BinPtr !start) (RelBinPtr (BinPtr !offset))) = + BinPtr $ start + offset + +makeRelativeBin :: RelBin a -> RelBinPtr a +makeRelativeBin (RelBin _ offset) = offset + +toRelBin :: Bin (RelBinPtr a) -> Bin a -> RelBin a +toRelBin (BinPtr !start) (BinPtr !goal) = + RelBin (BinPtr start) (RelBinPtr $ BinPtr $ goal - start) + --------------------------------------------------------------- -- class Binary --------------------------------------------------------------- @@ -309,6 +409,9 @@ class Binary a where putAt :: Binary a => WriteBinHandle -> Bin a -> a -> IO () putAt bh p x = do seekBinWriter bh p; put_ bh x; return () +putAtRel :: WriteBinHandle -> Bin (RelBinPtr a) -> Bin a -> IO () +putAtRel bh from to = putAt bh from (makeRelativeBin $ toRelBin from to) + getAt :: Binary a => ReadBinHandle -> Bin a -> IO a getAt bh p = do seekBinReader bh p; get bh @@ -327,6 +430,44 @@ openBinMem size , wbm_arr_r = arr_r } +-- | Freeze the given 'WriteBinHandle' and turn it into an equivalent 'ReadBinHandle'. +-- +-- The current offset of the 'WriteBinHandle' is maintained in the new 'ReadBinHandle'. +freezeWriteHandle :: WriteBinHandle -> IO ReadBinHandle +freezeWriteHandle wbm = do + rbm_off_r <- newFastMutInt =<< readFastMutInt (wbm_off_r wbm) + rbm_sz_r <- readFastMutInt (wbm_sz_r wbm) + rbm_arr_r <- readIORef (wbm_arr_r wbm) + pure $ ReadBinMem + { rbm_userData = noReaderUserData + , rbm_off_r = rbm_off_r + , rbm_sz_r = rbm_sz_r + , rbm_arr_r = rbm_arr_r + } + +-- | Copy the BinBuffer to a new BinBuffer which is exactly the right size. +-- This performs a copy of the underlying buffer. +-- The buffer may be truncated if the offset is not at the end of the written +-- output. +-- +-- UserData is also discarded during the copy +-- You should just use this when translating a Put handle into a Get handle. +shrinkBinBuffer :: WriteBinHandle -> IO ReadBinHandle +shrinkBinBuffer bh = withBinBuffer bh $ \bs -> do + unsafeUnpackBinBuffer (copy bs) + +thawReadHandle :: ReadBinHandle -> IO WriteBinHandle +thawReadHandle rbm = do + wbm_off_r <- newFastMutInt =<< readFastMutInt (rbm_off_r rbm) + wbm_sz_r <- newFastMutInt (rbm_sz_r rbm) + wbm_arr_r <- newIORef (rbm_arr_r rbm) + pure $ WriteBinMem + { wbm_userData = noWriterUserData + , wbm_off_r = wbm_off_r + , wbm_sz_r = wbm_sz_r + , wbm_arr_r = wbm_arr_r + } + tellBinWriter :: WriteBinHandle -> IO (Bin a) tellBinWriter (WriteBinMem _ r _ _) = do ix <- readFastMutInt r; return (BinPtr ix) @@ -358,6 +499,13 @@ seekBinReader (ReadBinMem _ ix_r sz_r _) (BinPtr !p) = do then panic "seekBinReader: seek out of range" else writeFastMutInt ix_r p +seekBinReaderRel :: ReadBinHandle -> RelBin a -> IO () +seekBinReaderRel (ReadBinMem _ ix_r sz_r _) relBin = do + let (BinPtr !p) = makeAbsoluteBin relBin + if (p > sz_r) + then panic "seekBinReaderRel: seek out of range" + else writeFastMutInt ix_r p + writeBinMem :: WriteBinHandle -> FilePath -> IO () writeBinMem (WriteBinMem _ ix_r _ arr_r) fn = do h <- openBinaryFile fn WriteMode @@ -1078,12 +1226,17 @@ instance Binary (Bin a) where put_ bh (BinPtr i) = putWord32 bh (fromIntegral i :: Word32) get bh = do i <- getWord32 bh; return (BinPtr (fromIntegral (i :: Word32))) +-- Instance uses fixed-width encoding to allow inserting +-- Bin placeholders in the stream. +instance Binary (RelBinPtr a) where + put_ bh (RelBinPtr i) = put_ bh i + get bh = RelBinPtr <$> get bh -- ----------------------------------------------------------------------------- -- Forward reading/writing --- | "forwardPut put_A put_B" outputs A after B but allows A to be read before B --- by using a forward reference +-- | @'forwardPut' put_A put_B@ outputs A after B but allows A to be read before B +-- by using a forward reference. forwardPut :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a,b) forwardPut bh put_A put_B = do -- write placeholder pointer to A @@ -1106,6 +1259,8 @@ forwardPut_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () forwardPut_ bh put_A put_B = void $ forwardPut bh put_A put_B -- | Read a value stored using a forward reference +-- +-- The forward reference is expected to be an absolute offset. forwardGet :: ReadBinHandle -> IO a -> IO a forwardGet bh get_A = do -- read forward reference @@ -1118,6 +1273,48 @@ forwardGet bh get_A = do seekBinReader bh p_a pure r +-- | @'forwardPutRel' put_A put_B@ outputs A after B but allows A to be read before B +-- by using a forward reference. +-- +-- This forward reference is a relative offset that allows us to skip over the +-- result of 'put_A'. +forwardPutRel :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a,b) +forwardPutRel bh put_A put_B = do + -- write placeholder pointer to A + pre_a <- tellBinWriter bh + put_ bh pre_a + + -- write B + r_b <- put_B + + -- update A's pointer + a <- tellBinWriter bh + putAtRel bh pre_a a + seekBinNoExpandWriter bh a + + -- write A + r_a <- put_A r_b + pure (r_a,r_b) + +-- | Like 'forwardGetRel', but discard the result. +forwardPutRel_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () +forwardPutRel_ bh put_A put_B = void $ forwardPutRel bh put_A put_B + +-- | Read a value stored using a forward reference. +-- +-- The forward reference is expected to be a relative offset. +forwardGetRel :: ReadBinHandle -> IO a -> IO a +forwardGetRel bh get_A = do + -- read forward reference + p <- getRelBin bh + -- store current position + p_a <- tellBinReader bh + -- go read the forward value, then seek back + seekBinReader bh $ makeAbsoluteBin p + r <- get_A + seekBinReader bh p_a + pure r + -- ----------------------------------------------------------------------------- -- Lazy reading/writing @@ -1127,19 +1324,19 @@ lazyPut = lazyPut' put_ lazyGet :: Binary a => ReadBinHandle -> IO a lazyGet = lazyGet' get -lazyPut' :: HasDebugCallStack => (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO () +lazyPut' :: (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO () lazyPut' f bh a = do -- output the obj with a ptr to skip over it: pre_a <- tellBinWriter bh put_ bh pre_a -- save a slot for the ptr f bh a -- dump the object q <- tellBinWriter bh -- q = ptr to after object - putAt bh pre_a q -- fill in slot before a with ptr to q + putAtRel bh pre_a q -- fill in slot before a with ptr to q seekBinWriter bh q -- finally carry on writing at q -lazyGet' :: HasDebugCallStack => (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a +lazyGet' :: (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a lazyGet' f bh = do - p <- get bh -- a BinPtr + p <- getRelBin bh -- a BinPtr p_a <- tellBinReader bh a <- unsafeInterleaveIO $ do -- NB: Use a fresh rbm_off_r variable in the child thread, for thread @@ -1148,7 +1345,7 @@ lazyGet' f bh = do let bh' = bh { rbm_off_r = off_r } seekBinReader bh' p_a f bh' - seekBinReader bh p -- skip over the object for now + seekBinReader bh (makeAbsoluteBin p) -- skip over the object for now return a -- | Serialize the constructor strictly but lazily serialize a value inside a @@ -1284,7 +1481,7 @@ mkReader f = BinaryReader -- | Find the 'BinaryReader' for the 'Binary' instance for the type identified by 'Proxy a'. -- -- If no 'BinaryReader' has been configured before, this function will panic. -findUserDataReader :: forall a . (HasCallStack, Refl.Typeable a) => Proxy a -> ReadBinHandle -> BinaryReader a +findUserDataReader :: forall a . Refl.Typeable a => Proxy a -> ReadBinHandle -> BinaryReader a findUserDataReader query bh = case Map.lookup (Refl.someTypeRep query) (ud_reader_data $ getReaderUserData bh) of Nothing -> panic $ "Failed to find BinaryReader for the key: " ++ show (Refl.someTypeRep query) @@ -1306,7 +1503,7 @@ findUserDataReader query bh = -- | Find the 'BinaryWriter' for the 'Binary' instance for the type identified by 'Proxy a'. -- -- If no 'BinaryWriter' has been configured before, this function will panic. -findUserDataWriter :: forall a . (HasCallStack, Refl.Typeable a) => Proxy a -> WriteBinHandle -> BinaryWriter a +findUserDataWriter :: forall a . Refl.Typeable a => Proxy a -> WriteBinHandle -> BinaryWriter a findUserDataWriter query bh = case Map.lookup (Refl.someTypeRep query) (ud_writer_data $ getWriterUserData bh) of Nothing -> panic $ "Failed to find BinaryWriter for the key: " ++ show (Refl.someTypeRep query) @@ -1442,13 +1639,13 @@ putGenericSymbolTable gen_sym_tab serialiser bh = do mapM_ (\n -> serialiser bh n) (reverse todo) loop snd <$> - (forwardPut bh (const $ readFastMutInt symtab_next >>= put_ bh) $ + (forwardPutRel bh (const $ readFastMutInt symtab_next >>= put_ bh) $ loop) -- | Read the elements of a 'GenericSymbolTable' from disk into a 'SymbolTable'. getGenericSymbolTable :: forall a . (ReadBinHandle -> IO a) -> ReadBinHandle -> IO (SymbolTable a) getGenericSymbolTable deserialiser bh = do - sz <- forwardGet bh (get bh) :: IO Int + sz <- forwardGetRel bh (get bh) :: IO Int mut_arr <- newArray_ (0, sz-1) :: IO (IOArray Int a) forM_ [0..(sz-1)] $ \i -> do f <- deserialiser bh ===================================== testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs ===================================== @@ -64,9 +64,10 @@ metaPlugin' _ meta = pprPanic "meta" (showAstData BlankSrcSpan BlankEpAnnotation interfaceLoadPlugin' :: [CommandLineOption] -> ModIface -> IfM lcl ModIface interfaceLoadPlugin' [name, "interface"] iface - = return $ iface { mi_exports = filter (availNotNamedAs name) - (mi_exports iface) - } + = return $ set_mi_exports (filter (availNotNamedAs name) + (mi_exports iface)) + iface + interfaceLoadPlugin' _ iface = return iface availNotNamedAs :: String -> AvailInfo -> Bool ===================================== testsuite/tests/typecheck/T24026/T24026a.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026a where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026a.stderr ===================================== @@ -0,0 +1,9 @@ +T24026a.hs:4:11: warning: [GHC-95396] [-Winline-rule-shadowing (in -Wdefault)] + Rule "f" may never fire because ‘f’ might inline first + Suggested fix: Add an INLINE[n] or NOINLINE[n] pragma for ‘f’ + +T24026a.hs:4:37: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/T24026b.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026b where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026b.stderr ===================================== @@ -0,0 +1,5 @@ +T24026b.hs:4:37: error: [GHC-83865] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/all.T ===================================== @@ -0,0 +1,2 @@ +test('T24026a', normal, compile, ['-dlint -fdefer-type-errors']) +test('T24026b', normal, compile_fail, ['']) \ No newline at end of file ===================================== utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs ===================================== @@ -56,7 +56,7 @@ import GHC.Types.Unique.FM import GHC.Unit.State import GHC.Utils.Binary -import GHC.Iface.Type (IfaceType, getIfaceType, putIfaceType) +import GHC.Iface.Type (IfaceType, putIfaceType) import Haddock.Options (Visibility (..)) @@ -200,7 +200,7 @@ writeInterfaceFile filename iface = do -- write the iface type pointer at the front of the file ifacetype_p <- tellBinWriter bh - putAt bh ifacetype_p_p ifacetype_p + putAtRel bh ifacetype_p_p ifacetype_p seekBinWriter bh ifacetype_p -- write the symbol table itself @@ -208,7 +208,7 @@ writeInterfaceFile filename iface = do -- write the symtab pointer at the front of the file symtab_p <- tellBinWriter bh - putAt bh symtab_p_p symtab_p + putAtRel bh symtab_p_p symtab_p seekBinWriter bh symtab_p -- write the symbol table itself @@ -218,7 +218,7 @@ writeInterfaceFile filename iface = do -- write the dictionary pointer at the fornt of the file dict_p <- tellBinWriter bh - putAt bh dict_p_p dict_p + putAtRel bh dict_p_p dict_p seekBinWriter bh dict_p -- write the dictionary itself View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/82d86741036e55f7a6f668940a7b1dcad1a701cb...3f9ee626cc0cc3423dfaa838186f4f9c49f1c2bd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/82d86741036e55f7a6f668940a7b1dcad1a701cb...3f9ee626cc0cc3423dfaa838186f4f9c49f1c2bd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 08:24:18 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Mon, 17 Jun 2024 04:24:18 -0400 Subject: [Git][ghc/ghc][wip/T14030] 5 commits: Make flip representation polymorphic, similar to ($) and (&) Message-ID: <666ff2b26b3bf_3bd4fc24cac28105317@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - b405e3e4 by Sebastian Graf at 2024-06-17T10:24:07+02:00 Derive previously hand-written `Lift` instances (#14030) This is possible now that #22229 is fixed. - - - - - 1da14215 by Sebastian Graf at 2024-06-17T10:24:07+02:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. - - - - - 5bef3090 by Sebastian Graf at 2024-06-17T10:24:08+02:00 Make fields of GHC.Internal.TH.Syntax.Bytes strict There is no use case where this would not make sense. - - - - - 30 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Match.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/ThToHs.hs - compiler/Language/Haskell/Syntax/Expr.hs - libraries/base/changelog.md The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/223aedd653f6bacdee9bdd13cd0e77f1eb7678e4...5bef3090c743b579f576afa86348e2aa6af493c4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/223aedd653f6bacdee9bdd13cd0e77f1eb7678e4...5bef3090c743b579f576afa86348e2aa6af493c4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 10:51:53 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 17 Jun 2024 06:51:53 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: compiler: Rejects RULES whose LHS immediately fails to type-check Message-ID: <66701548f0bbb_19878d651c10587f1@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 2114f60a by Fabricio de Sousa Nascimento at 2024-06-17T06:51:39-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - d93014c4 by Dylan Thinnes at 2024-06-17T06:51:44-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - 9 changed files: - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/Tc/Gen/Rule.hs - + testsuite/tests/typecheck/T24026/T24026a.hs - + testsuite/tests/typecheck/T24026/T24026a.stderr - + testsuite/tests/typecheck/T24026/T24026b.hs - + testsuite/tests/typecheck/T24026/T24026b.stderr - + testsuite/tests/typecheck/T24026/all.T Changes: ===================================== compiler/GHC/Driver/Env.hs ===================================== @@ -86,8 +86,8 @@ import qualified Data.Set as Set import GHC.Unit.Module.Graph runHsc :: HscEnv -> Hsc a -> IO a -runHsc hsc_env (Hsc hsc) = do - (a, w) <- hsc hsc_env emptyMessages +runHsc hsc_env hsc = do + (a, w) <- runHsc' hsc_env hsc let dflags = hsc_dflags hsc_env let !diag_opts = initDiagOpts dflags !print_config = initPrintConfig dflags ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -64,6 +64,7 @@ module GHC.Driver.Main , hscRecompStatus , hscParse , hscTypecheckRename + , hscTypecheckRenameWithDiagnostics , hscTypecheckAndGetWarnings , hscDesugar , makeSimpleDetails @@ -642,7 +643,14 @@ extract_renamed_stuff mod_summary tc_result = do -- | Rename and typecheck a module, additionally returning the renamed syntax hscTypecheckRename :: HscEnv -> ModSummary -> HsParsedModule -> IO (TcGblEnv, RenamedStuff) -hscTypecheckRename hsc_env mod_summary rdr_module = runHsc hsc_env $ +hscTypecheckRename hsc_env mod_summary rdr_module = + fst <$> hscTypecheckRenameWithDiagnostics hsc_env mod_summary rdr_module + +-- | Rename and typecheck a module, additionally returning the renamed syntax +-- and the diagnostics produced. +hscTypecheckRenameWithDiagnostics :: HscEnv -> ModSummary -> HsParsedModule + -> IO ((TcGblEnv, RenamedStuff), Messages GhcMessage) +hscTypecheckRenameWithDiagnostics hsc_env mod_summary rdr_module = runHsc' hsc_env $ hsc_typecheck True mod_summary (Just rdr_module) -- | Do Typechecking without throwing SourceError exception with -Werror ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -1031,9 +1031,12 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs extra_bndrs = scopedSort extra_tvs ++ extra_dicts where extra_tvs = [ v | v <- extra_vars, isTyVar v ] + + -- isEvVar: this includes coercions, matching what + -- happens in `split_lets` (isDictId, isCoVar) extra_dicts = - [ mkLocalId (localiseName (idName d)) ManyTy (idType d) - | d <- extra_vars, isDictId d ] + [ mkLocalIdOrCoVar (localiseName (idName d)) ManyTy (idType d) + | d <- extra_vars, isEvVar d ] extra_vars = [ v | v <- exprsFreeVarsList args ===================================== compiler/GHC/Tc/Gen/Rule.hs ===================================== @@ -108,11 +108,13 @@ tcRules decls = mapM (wrapLocMA tcRuleDecls) decls tcRuleDecls :: RuleDecls GhcRn -> TcM (RuleDecls GhcTc) tcRuleDecls (HsRules { rds_ext = src , rds_rules = decls }) - = do { tc_decls <- mapM (wrapLocMA tcRule) decls + = do { maybe_tc_decls <- mapM (wrapLocMA tcRule) decls + ; let tc_decls = [L loc rule | (L loc (Just rule)) <- maybe_tc_decls] ; return $ HsRules { rds_ext = src , rds_rules = tc_decls } } -tcRule :: RuleDecl GhcRn -> TcM (RuleDecl GhcTc) + +tcRule :: RuleDecl GhcRn -> TcM (Maybe (RuleDecl GhcTc)) tcRule (HsRule { rd_ext = ext , rd_name = rname@(L _ name) , rd_act = act @@ -181,7 +183,17 @@ tcRule (HsRule { rd_ext = ext ; (rhs_implic, rhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs rhs_wanted ; emitImplications (lhs_implic `unionBags` rhs_implic) - ; return $ HsRule { rd_ext = ext + + -- A type error on the LHS of a rule will be reported earlier while solving for + -- lhs_implic. However, we should also drop the rule entirely for cases where + -- compilation continues regardless of the error. For example with + -- `-fdefer-type-errors`, where this ill-typed LHS rule may cause follow-on errors + -- (#24026). + ; if anyBag insolubleImplic lhs_implic + then + return Nothing -- The RULE LHS does not type-check and will be dropped. + else + return . Just $ HsRule { rd_ext = ext , rd_name = rname , rd_act = act , rd_tyvs = ty_bndrs -- preserved for ppr-ing ===================================== testsuite/tests/typecheck/T24026/T24026a.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026a where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026a.stderr ===================================== @@ -0,0 +1,9 @@ +T24026a.hs:4:11: warning: [GHC-95396] [-Winline-rule-shadowing (in -Wdefault)] + Rule "f" may never fire because ‘f’ might inline first + Suggested fix: Add an INLINE[n] or NOINLINE[n] pragma for ‘f’ + +T24026a.hs:4:37: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/T24026b.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026b where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026b.stderr ===================================== @@ -0,0 +1,5 @@ +T24026b.hs:4:37: error: [GHC-83865] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/all.T ===================================== @@ -0,0 +1,2 @@ +test('T24026a', normal, compile, ['-dlint -fdefer-type-errors']) +test('T24026b', normal, compile_fail, ['']) \ No newline at end of file View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3f9ee626cc0cc3423dfaa838186f4f9c49f1c2bd...d93014c4808da90d68c3b43b97afb2066fc94724 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3f9ee626cc0cc3423dfaa838186f4f9c49f1c2bd...d93014c4808da90d68c3b43b97afb2066fc94724 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 11:09:14 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Mon, 17 Jun 2024 07:09:14 -0400 Subject: [Git][ghc/ghc][wip/T24623] Comments only Message-ID: <6670195ab3347_19878d912fe4656a0@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24623 at Glasgow Haskell Compiler / GHC Commits: 3f0f3915 by Simon Peyton Jones at 2024-06-17T12:08:49+01:00 Comments only - - - - - 2 changed files: - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Types/Demand.hs Changes: ===================================== compiler/GHC/Core/Opt/DmdAnal.hs ===================================== @@ -1106,6 +1106,7 @@ dmdAnalRhsSig top_lvl rec_flag env let_sd id rhs dmd_sig_arity = ww_arity + calledOnceArity body_sd sig = mkDmdSigForArity dmd_sig_arity (DmdType sig_env final_rhs_dmds) + -- See Note [mkDmdSigForArity] opts = ae_opts env final_id = setIdDmdAndBoxSig opts id sig @@ -1287,7 +1288,7 @@ BUT we do /not/ want to worker/wrapper `j` with two arguments. Suppose we have where j2's join-arity is 1, so calls to `j` will all have /one/ argument. Suppose the entire expression is in a called context (like `j` above) and `j2` -gets the demand signature , that is, strict in both arguments. +gets the demand signature <1!P(L)><1!P(L)>, that is, strict in both arguments. we worker/wrapper'd `j2` with two args we'd get join $wj2 x# y# = let x = I# x#; y = I# y# in rhs @@ -1377,6 +1378,27 @@ signatures for different arities (i.e., polyvariance) would be entirely possible, if it weren't for the additional runtime and implementation complexity. +Note [mkDmdSigForArity] +~~~~~~~~~~~~~~~~~~~~~~~ +Consider + f x = case y of { I# y' -> \z -> blah } +We will analyse the body with demand C(1L), reflecting the single visible +argument x. But dmdAnal will return a DmdType looking like + DmdType fvs [x-dmd, z-dmd] +because it has seen two lambdas, \x and \z. Since the length of the argument +demands in a DmdSig gives the "threshold" for applying the signature +(see Note [DmdSig: demand signatures, and demand-sig arity] in GHC.Types.Demand) +we must trim that DmdType to just + DmdSig (DmdTypte fvs [x-dmd]) +when making that DmdType into the DmdSig for f. This trimming is the job of +`mkDmdSigForArity`. + +Alternative. An alternative would be be to ensure that if + (dmd_ty, e') = dmdAnal env subdmd e +then the length dmds in dmd_ty is always less than (or maybe equal to?) the +call-depth of subdmd. To do that we'd need to adjust the Lam case of dmdAnal. +Probably not hard, but a job for another day; see discussion on !12873. + Note [idArity varies independently of dmdTypeDepth] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ In general, an Id `f` has two independently varying attributes: ===================================== compiler/GHC/Types/Demand.hs ===================================== @@ -2136,11 +2136,11 @@ was evaluated. Here's an example: else \z -> z * ... The abstract transformer (let's call it F_e) of the if expression (let's -call it e) would transform an incoming (undersaturated!) head demand 1A into -a demand type like {x-><1L>,y->}. In pictures: +call it e) would transform an incoming (undersaturated!) head sub-demand A +into a demand type like {x-><1L>,y->}. In pictures: - Demand ---F_e---> DmdType - <1A> {x-><1L>,y->} + SubDemand ---F_e---> DmdType + {x-><1L>,y->} Let's assume that the demand transformers we compute for an expression are correct wrt. to some concrete semantics for Core. How do demand signatures fit @@ -2189,10 +2189,10 @@ Here is a table with demand types resulting from different incoming demands we put that expression under. Note the monotonicity; a stronger incoming demand yields a more precise demand type: - incoming demand | demand type + incoming sub-demand | demand type -------------------------------- - 1A | {} - C(1,C(1,L)) | <1P(L)>{} + P(A) | {} + C(1,C(1,P(L))) | <1P(L)>{} C(1,C(1,1P(1P(L),A))) | <1P(A)>{} Note that in the first example, the depth of the demand type was *higher* than View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3f0f3915bf90938a9015805538ceb8cabebc62a2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3f0f3915bf90938a9015805538ceb8cabebc62a2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 12:22:32 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Mon, 17 Jun 2024 08:22:32 -0400 Subject: [Git][ghc/ghc][wip/T14030] Make fields of GHC.Internal.TH.Syntax.Bytes strict Message-ID: <66702a8895770_19878d110e478734f3@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: d525d829 by Sebastian Graf at 2024-06-17T14:22:26+02:00 Make fields of GHC.Internal.TH.Syntax.Bytes strict There is no use case where this would not make sense. - - - - - 2 changed files: - libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs - testsuite/tests/interface-stability/template-haskell-exports.stdout Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Syntax.hs ===================================== @@ -1712,9 +1712,9 @@ data Lit = CharL Char -- ^ @\'c\'@ -- Avoid using Bytes constructor directly as it is likely to change in the -- future. Use helpers such as `mkBytes` in Language.Haskell.TH.Lib instead. data Bytes = Bytes - { bytesPtr :: ForeignPtr Word8 -- ^ Pointer to the data - , bytesOffset :: Word -- ^ Offset from the pointer - , bytesSize :: Word -- ^ Number of bytes + { bytesPtr :: !(ForeignPtr Word8) -- ^ Pointer to the data + , bytesOffset :: {-# UNPACK #-} !Word -- ^ Offset from the pointer + , bytesSize :: {-# UNPACK #-} !Word -- ^ Number of bytes -- Maybe someday: -- , bytesAlignement :: Word -- ^ Alignement constraint ===================================== testsuite/tests/interface-stability/template-haskell-exports.stdout ===================================== @@ -1705,7 +1705,7 @@ module Language.Haskell.TH.Syntax where type Body :: * data Body = GuardedB [(Guard, Exp)] | NormalB Exp type Bytes :: * - data Bytes = Bytes {bytesPtr :: GHC.Internal.ForeignPtr.ForeignPtr GHC.Internal.Word.Word8, bytesOffset :: GHC.Types.Word, bytesSize :: GHC.Types.Word} + data Bytes = Bytes {bytesPtr :: !(GHC.Internal.ForeignPtr.ForeignPtr GHC.Internal.Word.Word8), bytesOffset :: {-# UNPACK #-}GHC.Types.Word, bytesSize :: {-# UNPACK #-}GHC.Types.Word} type Callconv :: * data Callconv = CCall | StdCall | CApi | Prim | JavaScript type CharPos :: * View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d525d829a76b4a6ecf54ef91d06c9e7b24042085 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d525d829a76b4a6ecf54ef91d06c9e7b24042085 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 12:29:36 2024 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Mon, 17 Jun 2024 08:29:36 -0400 Subject: [Git][ghc/ghc][wip/andreask/cast_any] 157 commits: rts: Fix size of StgOrigThunkInfo frames Message-ID: <66702c30a9d65_19878d133af44747e3@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/cast_any at Glasgow Haskell Compiler / GHC Commits: 6d7e6ad8 by Ben Gamari at 2024-05-22T13:40:05-04:00 rts: Fix size of StgOrigThunkInfo frames Previously the entry code of the `stg_orig_thunk` frame failed to account for the size of the profiling header as it hard-coded the frame size. Fix this. Fixes #24809. - - - - - c645fe40 by Fendor at 2024-05-22T13:40:05-04:00 Add regression test T24809 for stg_orig_thunk_info_frame size - - - - - 4181aa40 by Andreas Klebinger at 2024-05-22T13:40:42-04:00 bindists: Check for existence of share folder before trying to copy it. This folder isn't distributed in windows bindists A lack of doing so resulted us copying loads of files twice. - - - - - d216510e by Matthew Pickering at 2024-05-22T13:40:42-04:00 Remove ad-hoc installation of mingw toolchain in relocatable bindists This reverts 616ac30026e8dd7d2ebb98d92dde071eedf5d951 The choice about whether to install mingw is taken in the installation makefile. This is also broken on non-windows systems. The actual issue was the EnableDistroToolchain variable wasn't declared in mk/config.mk and therefore the check to install mingw was failing. - - - - - 7b4c1998 by Cheng Shao at 2024-05-22T21:52:52-04:00 testsuite: fix T17920 for wasm backend T17920 was marked as fragile on wasm before; it can be trivially fixed by avoiding calling variadic printf() in cmm. - - - - - c739383b by Cheng Shao at 2024-05-22T21:53:29-04:00 testsuite: bump T22744 timeout to 5x - - - - - c4c6d714 by Cheng Shao at 2024-05-22T21:54:06-04:00 testsuite: don't attempt to detect host cpu features when testing cross ghc The testsuite driver CPU feature detection logic only detects host CPU and only makes sense when we are not testing a cross GHC. - - - - - 3d9e4ce6 by Simon Peyton Jones at 2024-05-22T21:54:43-04:00 Better skolemisation As #24810 showed, it is (a little) better to skolemise en-bloc, so that Note [Let-bound skolems] fires more often. See Note [Skolemisation en bloc] in GHC.Tc.Utils.Instantiate. - - - - - a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00 Add missing parenthesizePat in cvtp We need to ensure that the output of `cvtp` is parenthesized (at precedence `sigPrec`) so that any pattern signatures with a surrounding pattern signature can parse correctly. Fixes #24837. - - - - - 4bb2a7cc by Hécate Moonlight at 2024-05-22T21:55:59-04:00 [base] Document the memory overhead of ByteArray Add a diagram that shows the constituent parts of a ByteArray and their memory overhead. - - - - - 8b2a016a by Hécate Moonlight at 2024-05-22T21:56:38-04:00 Haddock: Add MR template for Haddock - - - - - ead75532 by Peter Trommler at 2024-05-23T02:28:05-04:00 PPC: Support ELF v2 on powerpc64 big-endian Detect ELF v2 on PowerPC 64-bit systems. Check for `_CALL_ELF` preprocessor macro. Fixes #21191 - - - - - 9d4c10f2 by Hécate Kleidukos at 2024-05-23T02:28:44-04:00 gitlab: Add @Kleidukos to CODEOWNERS for utils/haddock - - - - - 28e64170 by Preetham Gujjula at 2024-05-23T07:20:48-04:00 haddock: Add cabal-fmt to tools for `make style` - - - - - 00126a89 by Andrei Borzenkov at 2024-05-23T07:21:24-04:00 haddock: fix verbosity option parsing - - - - - a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00 base: specify tie-breaking behavior of min, max, and related list/Foldable functions - - - - - bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00 cmm: add word <-> double/float bitcast - closes: #25331 This is the last step in the project plan described in #25331. This commit: - adds bitcast operands for x86_64, LLVM, aarch64 - For PPC and i386 we resort to using the cmm implementations - renames conversion MachOps from Conv to Round|Truncate - - - - - f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor Some functions in StgToByteCode were filtering out void arguments. However, StgToByteCode is called after unarisation: the void arguments should have been removed earlier. Instead of filtering out, we assert that the args are non-void. - - - - - 03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor `layoutNativeCall` was always called with a `primRepCmmType platform` callback. Hence we can put it inside of `layoutNativeCall` rather than repeat it. - - - - - 27c430f3 by David Binder at 2024-05-24T07:52:38-04:00 haddock: Remove compatibility shims for GHC < 8.4 from haddock-library - - - - - 8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00 compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs This patch makes the STG->Cmm backend avoid saving foreign call target to local when there are no caller-save GlobalRegs. Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a foreign call, we unconditionally save the foreign call target to a temporary local first, then rely on cmmSink to clean it up later, which only happens with -fcmm-sink (implied by -O) and not in unoptimized code. And this is troublesome for the wasm backend NCG, which needs to infer a foreign call target symbol's type signature from the Cmm call site. Previously, the NCG has been emitting incorrect type signatures for unoptimized code, which happens to work with `wasm-ld` most of the time, but this is never future-proof against upstream toolchain updates, and it causes horrible breakages when LTO objects are included in linker input. Hence this patch. - - - - - 986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00 testsuite: add callee-no-local regression test - - - - - 52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00 Fix HasCallStack leftovers from !12514 / #24726 - - - - - c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00 user_guide: Fix typo in MultiWayIf chapter Close #24829 - - - - - bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - 1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Fix changelog reference to setBacktraceMechanismState (cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d) - - - - - 43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00 Float/double unboxed literal support for HexFloatLiterals (fix #22155) - - - - - 4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00 Improve test labels for binary interface file size tests Test labels for binary interface file sizes are hard to read and overly verbose at the same time. Extend the name for the metric title, but shorten it in the actual comparison table. - - - - - 14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00 Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present" This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa. - - - - - f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00 Fix default hyperlinked sources pattern Previously this didn't include the `%M` token which manifested as broken links to the hyperlinked sources of reexports of declarations defined in other packages. Fixes haddock#1628. (cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36) - - - - - 42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00 Make DocPaths a proper data type (cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c) - - - - - 53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00 haddock: Bump version to 2.30 (cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602) - - - - - e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00 haddock-api: allow base 4.20 and ghc 9.11 - - - - - e294f7a2 by PHO at 2024-05-24T12:17:55-04:00 Add a flag "threaded" for building haddock with the threaded RTS GHC isn't guaranteed to have a threaded RTS. There should be a way to build it with the vanilla one. (cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d) - - - - - 51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00 Update ticky counter event docs. Add the info about the info table address and json fields. Fixes #23200 - - - - - 98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00 Export extractPromotedList (#24866) This can be useful in plugins. - - - - - 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - a4647ec4 by Andreas Klebinger at 2024-06-17T14:13:46+02:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - 30 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - + .gitlab/merge_request_templates/Haddock.md - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1be6fd0a4f451810be4ea2056f01a88d651a06c0...a4647ec4801be0909ba2ced16eeaeed17acca758 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1be6fd0a4f451810be4ea2056f01a88d651a06c0...a4647ec4801be0909ba2ced16eeaeed17acca758 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 12:30:40 2024 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Mon, 17 Jun 2024 08:30:40 -0400 Subject: [Git][ghc/ghc][wip/andreask/note-lint] 121 commits: template-haskell: Move wired-ins to ghc-internal Message-ID: <66702c70bfbed_19878d141b7ec752b7@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/note-lint at Glasgow Haskell Compiler / GHC Commits: 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - 54c20847 by Andreas Klebinger at 2024-06-17T12:30:28+00:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 30 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Wasm/Asm.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/Wasm/Types.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToC.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5d3cb951a7d80ef1beda12dd8d065739e72b4580...54c20847ed91d1421f705a7017e2d8b0f7f1864e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5d3cb951a7d80ef1beda12dd8d065739e72b4580...54c20847ed91d1421f705a7017e2d8b0f7f1864e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 13:49:58 2024 From: gitlab at gitlab.haskell.org (Zubin (@wz1000)) Date: Mon, 17 Jun 2024 09:49:58 -0400 Subject: [Git][ghc/ghc][wip/fc-hook] 5425 commits: [haddock @ 2002-04-04 16:23:43 by simonmar] Message-ID: <66703f06c3420_124475fa87057571@gitlab.mail> Zubin pushed to branch wip/fc-hook at Glasgow Haskell Compiler / GHC Commits: 2b39cd94 by Simon Marlow at 2002-04-04T16:23:43+00:00 [haddock @ 2002-04-04 16:23:43 by simonmar] This is Haddock, my stab at a Haskell documentation tool. It's not quite ready for release yet, but I'm putting it in the repository so others can take a look. It uses a locally modified version of the hssource parser, extended with support for GHC extensions and documentation annotations. - - - - - 99ede94f by Simon Marlow at 2002-04-04T16:24:10+00:00 [haddock @ 2002-04-04 16:24:10 by simonmar] forgot one file - - - - - 8363294c by Simon Marlow at 2002-04-05T13:58:15+00:00 [haddock @ 2002-04-05 13:58:15 by simonmar] Remap names in the exported declarations to be "closer" to the current module. eg. if an exported declaration mentions a type 'T' which is imported from module A then re-exported from the current module, then links from the type or indeed the documentation will point to the current module rather than module A. This is to support better hiding: module A won't be referred to in the generated output. - - - - - 1570cbc1 by Simon Marlow at 2002-04-05T13:58:23+00:00 [haddock @ 2002-04-05 13:58:23 by simonmar] update the TODO list - - - - - 3a62f96b by Simon Marlow at 2002-04-05T14:11:51+00:00 [haddock @ 2002-04-05 14:11:51 by simonmar] Fix the anchor for a class declaration - - - - - c5d9a471 by Simon Marlow at 2002-04-05T14:18:41+00:00 [haddock @ 2002-04-05 14:18:41 by simonmar] remove underlines on visited links - - - - - 97280525 by Simon Marlow at 2002-04-05T16:11:47+00:00 [haddock @ 2002-04-05 16:11:47 by simonmar] - Update to generate more correct HTML. - Use our own non-overloaded table combinators, as the overloaded versions were giving me a headache. The improved type safety caught several errors in the HTML generation. - - - - - 9acd3a4d by Simon Marlow at 2002-04-05T16:32:19+00:00 [haddock @ 2002-04-05 16:32:19 by simonmar] Add width property to the title, and add TD.children for the module contents page. - - - - - ec9a0847 by Simon Marlow at 2002-04-08T16:39:56+00:00 [haddock @ 2002-04-08 16:39:56 by simonmar] Fix a problem with exports of the form T(..). - - - - - e4627dc8 by Simon Marlow at 2002-04-08T16:41:38+00:00 [haddock @ 2002-04-08 16:41:37 by simonmar] - Add our own versions of Html & BlockTable for the time being. - Add support for generating an index to the HTML backend - - - - - 2d73fd75 by Simon Marlow at 2002-04-09T11:23:24+00:00 [haddock @ 2002-04-09 11:23:24 by simonmar] Add '-- /' as a synonym for '-- |', for compatibility with IDoc. - - - - - 3675464e by Simon Marlow at 2002-04-09T11:33:55+00:00 [haddock @ 2002-04-09 11:33:54 by simonmar] - add the <...> syntax for marking up URLs in documentation - Make the output for data & class declarations more compact when there aren't any documentation annotations on the individual methods or constructors respectively. - - - - - 5077f5b1 by Simon Marlow at 2002-04-09T11:36:04+00:00 [haddock @ 2002-04-09 11:36:04 by simonmar] Update the TODO list - - - - - 9e83c54d by Simon Marlow at 2002-04-10T10:50:06+00:00 [haddock @ 2002-04-10 10:50:06 by simonmar] Use explicit 'px' suffix on pixel sizes; IE seems to prefer them - - - - - 052de51c by Simon Marlow at 2002-04-10T13:23:13+00:00 [haddock @ 2002-04-10 13:23:13 by simonmar] Lex URLs as a single token to avoid having to escape special characters inside the URL string. - - - - - 47187edb by Simon Marlow at 2002-04-10T13:23:55+00:00 [haddock @ 2002-04-10 13:23:55 by simonmar] Not sure why I made the constructor name for a record declaration into a TyCls name, but change it back into a Var name anyhow. - - - - - 3dc6aa81 by Simon Marlow at 2002-04-10T13:26:10+00:00 [haddock @ 2002-04-10 13:26:09 by simonmar] Lots of changes, including: - add index support to the HTML backend - clean up the renamer, put it into a monad - propogate unresolved names to the top level and report them in a nicer way - various bugfixes - - - - - c2a70a72 by Simon Marlow at 2002-04-10T13:32:39+00:00 [haddock @ 2002-04-10 13:32:39 by simonmar] Skeleton documentation - - - - - 50c98d17 by Simon Marlow at 2002-04-10T13:37:23+00:00 [haddock @ 2002-04-10 13:37:23 by simonmar] Update the TODO list, separate into pre-1.0 and post-1.0 items - - - - - f3778be6 by Simon Marlow at 2002-04-10T14:30:58+00:00 [haddock @ 2002-04-10 14:30:58 by simonmar] Add an introduction - - - - - cfbaf9f7 by Simon Marlow at 2002-04-10T14:59:51+00:00 [haddock @ 2002-04-10 14:59:51 by simonmar] Sort the module tree - - - - - 76bd7b34 by Simon Marlow at 2002-04-10T15:50:11+00:00 [haddock @ 2002-04-10 15:50:10 by simonmar] Generate a little table of contents at the top of the module doc (only if the module actually contains some section headings, though). - - - - - bb8560a1 by Simon Marlow at 2002-04-10T16:10:26+00:00 [haddock @ 2002-04-10 16:10:26 by simonmar] Now we understand (or at least don't barf on) type signatures in patterns such as you might find when scoped type variables are in use. - - - - - 86c2a026 by Simon Marlow at 2002-04-10T16:10:49+00:00 [haddock @ 2002-04-10 16:10:49 by simonmar] more updates - - - - - 1c052b0e by Simon Marlow at 2002-04-10T16:28:05+00:00 [haddock @ 2002-04-10 16:28:05 by simonmar] Parse errors in doc strings are now reported as warnings rather that causing the whole thing to fall over. It still needs cleaning up (the warning is emitted with trace) but this will do for the time being. - - - - - ace03e8f by Simon Marlow at 2002-04-10T16:38:03+00:00 [haddock @ 2002-04-10 16:38:03 by simonmar] update again - - - - - 69006c3e by Simon Marlow at 2002-04-11T13:38:02+00:00 [haddock @ 2002-04-11 13:38:02 by simonmar] mention Opera - - - - - fe9b10f8 by Simon Marlow at 2002-04-11T13:40:31+00:00 [haddock @ 2002-04-11 13:40:30 by simonmar] - copy haddock.css into the same place as the generated HTML - new option: --css <file> specifies the style sheet to use - new option: -o <dir> specifies the directory in which to generate the output. - because Haddock now needs to know where to find its default stylesheet, we have to have a wrapper script and do the haddock-inplace thing (Makefile code copied largely from fptools/happy). - - - - - 106adbbe by Simon Marlow at 2002-04-24T15:12:41+00:00 [haddock @ 2002-04-24 15:12:41 by simonmar] Stop slurping comment lines when we see a row of dashes longer than length 2: these are useful as separators. - - - - - 995d3f9e by Simon Marlow at 2002-04-24T15:14:12+00:00 [haddock @ 2002-04-24 15:14:11 by simonmar] Grok the kind of module headers we use in fptools/libraries, and pass the "portability", "stability", and "maintainer" strings through into the generated HTML. If the module header doesn't match the pattern, then we don't include the info in the HTML. - - - - - e14da136 by Simon Marlow at 2002-04-24T15:16:57+00:00 [haddock @ 2002-04-24 15:16:57 by simonmar] Done module headers now. - - - - - 2ca8dfd4 by Simon Marlow at 2002-04-24T15:57:48+00:00 [haddock @ 2002-04-24 15:57:47 by simonmar] Handle gcons in export lists (a common extension). - - - - - 044cea81 by Simon Marlow at 2002-04-25T14:20:12+00:00 [haddock @ 2002-04-25 14:20:12 by simonmar] Add the little lambda icon - - - - - 63955027 by Simon Marlow at 2002-04-25T14:40:05+00:00 [haddock @ 2002-04-25 14:40:05 by simonmar] - Add support for named chunks of documentation which can be referenced from the export list. - Copy the icon from $libdir to the destination in HTML mode. - - - - - 36e3f913 by Simon Marlow at 2002-04-25T16:48:36+00:00 [haddock @ 2002-04-25 16:48:36 by simonmar] More keyboard bashing - - - - - 7ae18dd0 by Simon Marlow at 2002-04-26T08:43:33+00:00 [haddock @ 2002-04-26 08:43:33 by simonmar] Package util reqd. to compile with 4.08.2 - - - - - bbd5fbab by Simon Marlow at 2002-04-26T10:13:00+00:00 [haddock @ 2002-04-26 10:13:00 by simonmar] Include $(GHC_HAPPY_OPTS) when compiling HsParser - - - - - 31c53d79 by Simon Marlow at 2002-04-26T11:18:57+00:00 [haddock @ 2002-04-26 11:18:56 by simonmar] - support for fundeps (partially contributed by Brett Letner - thanks Brett). - make it build with GHC 4.08.2 - - - - - c415ce76 by Simon Marlow at 2002-04-26T13:15:02+00:00 [haddock @ 2002-04-26 13:15:02 by simonmar] Move the explicit formatting of the little table for the stability/portability/maintainer info from the HTML into the CSS, and remove the explicit table size (just right-align it). - - - - - 520ee21a by Simon Marlow at 2002-04-26T16:01:44+00:00 [haddock @ 2002-04-26 16:01:44 by simonmar] Yet more keyboard bashing - this is pretty much complete now. - - - - - 2ae37179 by Simon Marlow at 2002-04-26T16:02:14+00:00 [haddock @ 2002-04-26 16:02:14 by simonmar] Add a couple of things I forgot about - - - - - b7211e04 by Simon Marlow at 2002-04-29T15:28:12+00:00 [haddock @ 2002-04-29 15:28:12 by simonmar] bugfix for declBinders on a NewTypeDecl - - - - - 640c154a by Simon Marlow at 2002-04-29T15:28:54+00:00 [haddock @ 2002-04-29 15:28:54 by simonmar] Allow '-- |' style annotations on constructors and record fields. - - - - - 393f258a by Simon Marlow at 2002-04-29T15:37:32+00:00 [haddock @ 2002-04-29 15:37:32 by simonmar] syntax fix - - - - - 8a2c2549 by Simon Marlow at 2002-04-29T15:37:48+00:00 [haddock @ 2002-04-29 15:37:48 by simonmar] Add an example - - - - - db88f8a2 by Simon Marlow at 2002-04-29T15:55:46+00:00 [haddock @ 2002-04-29 15:55:46 by simonmar] remove a trace - - - - - 2b0248e0 by Simon Marlow at 2002-04-29T15:56:19+00:00 [haddock @ 2002-04-29 15:56:19 by simonmar] Fix for 'make install' - - - - - 120453a0 by Simon Marlow at 2002-04-29T15:56:39+00:00 [haddock @ 2002-04-29 15:56:39 by simonmar] Install the auxilliary bits - - - - - 950e6dbb by Simon Marlow at 2002-04-29T15:57:30+00:00 [haddock @ 2002-04-29 15:57:30 by simonmar] Add BinDist bits - - - - - 154b9d71 by Simon Marlow at 2002-05-01T11:02:52+00:00 [haddock @ 2002-05-01 11:02:52 by simonmar] update - - - - - ba6c39fa by Simon Marlow at 2002-05-01T11:03:26+00:00 [haddock @ 2002-05-01 11:03:26 by simonmar] Add another item - - - - - bacb5e33 by Simon Marlow at 2002-05-03T08:50:00+00:00 [haddock @ 2002-05-03 08:50:00 by simonmar] Fix some typos. - - - - - 54c87895 by Sven Panne at 2002-05-05T19:40:51+00:00 [haddock @ 2002-05-05 19:40:51 by panne] As a temporary hack/workaround for a bug in GHC's simplifier, don't pass Happy the -c option for generating the parsers in this subdir. Furthermore, disable -O for HaddocParse, too. - - - - - e6c08703 by Simon Marlow at 2002-05-06T09:51:10+00:00 [haddock @ 2002-05-06 09:51:10 by simonmar] Add RPM spec file (thanks to Tom Moertel <tom-rpms at moertel.com>) - - - - - 7b8fa8e7 by Simon Marlow at 2002-05-06T12:29:26+00:00 [haddock @ 2002-05-06 12:29:26 by simonmar] Add missing type signature (a different workaround for the bug in GHC's simplifier). - - - - - cd0e300d by Simon Marlow at 2002-05-06T12:30:09+00:00 [haddock @ 2002-05-06 12:30:09 by simonmar] Remove workaround for simplifier bug in previous revision. - - - - - 687e68fa by Simon Marlow at 2002-05-06T12:32:32+00:00 [haddock @ 2002-05-06 12:32:32 by simonmar] Allow empty data declarations (another GHC extension). - - - - - 8f29f696 by Simon Marlow at 2002-05-06T12:49:21+00:00 [haddock @ 2002-05-06 12:49:21 by simonmar] Fix silly bug in named documentation block lookup. - - - - - 8e0059af by Simon Marlow at 2002-05-06T13:02:42+00:00 [haddock @ 2002-05-06 13:02:42 by simonmar] Add another named chunk with a different name - - - - - 68f8a896 by Simon Marlow at 2002-05-06T13:32:32+00:00 [haddock @ 2002-05-06 13:32:32 by simonmar] Be more lenient about extra paragraph breaks - - - - - 65fc31db by Simon Marlow at 2002-05-07T15:36:36+00:00 [haddock @ 2002-05-07 15:36:36 by simonmar] DocEmpty is a right and left-unit of DocAppend (remove it in the smart constructor). - - - - - adc81078 by Simon Marlow at 2002-05-07T15:37:15+00:00 [haddock @ 2002-05-07 15:37:15 by simonmar] Allow code blocks to be denoted with bird-tracks in addition to [...]. - - - - - 1283a3c1 by Simon Marlow at 2002-05-08T11:21:56+00:00 [haddock @ 2002-05-08 11:21:56 by simonmar] Add a facility for specifying options that affect Haddock's treatment of the module. Options are given at the top of the module in a comma-separated list, beginning with '-- #'. eg. -- # prune, hide, ignore-exports Options currently available, with their meanings: prune: ignore declarations which have no documentation annotations ignore-exports: act as if the export list were not specified (i.e. export everything local to the module). hide: do not include this module in the generated documentation, but propagate any exported definitions to modules which re-export them. There's a slight change in the semantics for re-exporting a full module by giving 'module M' in the export list: if module M does not have the 'hide' option, then the documentation will now just contain a reference to module M rather than the full inlined contents of that module. These features, and some other changes in the pipeline, are the result of discussions between myself and Manuel Chakravarty <chak at cse.unsw.edu.au> (author of IDoc) yesterday. Also: some cleanups, use a Writer monad to collect error messages in some places instead of just printing them with trace. - - - - - a2239cf5 by Simon Marlow at 2002-05-08T11:22:30+00:00 [haddock @ 2002-05-08 11:22:30 by simonmar] Update to test new features. - - - - - 6add955f by Simon Marlow at 2002-05-08T13:37:25+00:00 [haddock @ 2002-05-08 13:37:25 by simonmar] Change the markup for typewriter-font from [...] to @... at . The reasoning is that the '@' symbol is much less likely to be needed than square brackets, and we don't want to have to escape square brackets in code fragments. This will be mildly painful in the short term, but it's better to get the change out of the way as early as possible. - - - - - cda06447 by Simon Marlow at 2002-05-08T13:39:56+00:00 [haddock @ 2002-05-08 13:39:56 by simonmar] Allow nested-style comments to be used as documentation annotations too. eg. {-| ... -} is equivalent to -- | ... An extra space can also be left after the comment opener: {- | ... -}. The only version that isn't allowed is {-# ... -}, because this syntax overlaps with Haskell pragmas; use {- # ... -} instead. - - - - - db23f65e by Simon Marlow at 2002-05-08T14:48:41+00:00 [haddock @ 2002-05-08 14:48:39 by simonmar] Add support for existential quantifiers on constructors. - - - - - adce3794 by Simon Marlow at 2002-05-08T15:43:25+00:00 [haddock @ 2002-05-08 15:43:25 by simonmar] update - - - - - 62a1f436 by Simon Marlow at 2002-05-08T15:44:10+00:00 [haddock @ 2002-05-08 15:44:10 by simonmar] Update to version 0.2 - - - - - f6a24ba3 by Simon Marlow at 2002-05-09T08:48:29+00:00 [haddock @ 2002-05-09 08:48:29 by simonmar] typo - - - - - 9f9522a4 by Simon Marlow at 2002-05-09T10:33:14+00:00 [haddock @ 2002-05-09 10:33:14 by simonmar] oops, left out '/' from the special characters in the last change. - - - - - 14abcb39 by Simon Marlow at 2002-05-09T10:34:44+00:00 [haddock @ 2002-05-09 10:34:44 by simonmar] Fix buglet - - - - - b8d878be by Simon Marlow at 2002-05-09T10:35:00+00:00 [haddock @ 2002-05-09 10:35:00 by simonmar] Give a more useful instance of Show for Module. - - - - - f7bfd626 by Simon Marlow at 2002-05-09T10:37:07+00:00 [haddock @ 2002-05-09 10:37:07 by simonmar] The last commit to Main.lhs broke the delicate balance of laziness which was being used to avoid computing the dependency graph of modules. So I finally bit the bullet and did a proper topological sort of the module graph, which turned out to be easy (stealing the Digraph module from GHC - this really ought to be in the libraries somewhere). - - - - - b481c1d0 by Simon Marlow at 2002-05-09T10:37:25+00:00 [haddock @ 2002-05-09 10:37:25 by simonmar] another item done - - - - - 032e2b42 by Simon Marlow at 2002-05-09T10:44:15+00:00 [haddock @ 2002-05-09 10:44:15 by simonmar] Don't consider a module re-export as having documentation, for the purposes of deciding whether we need a Synopsis section or not. - - - - - 5fb45e92 by Simon Marlow at 2002-05-09T11:10:55+00:00 [haddock @ 2002-05-09 11:10:55 by simonmar] Add a special case for list types in ppHsAType - - - - - 1937e428 by Simon Marlow at 2002-05-09T12:43:06+00:00 [haddock @ 2002-05-09 12:43:06 by simonmar] Type synonyms can accept a ctype on the RHS, to match GHC. - - - - - 0f16ce56 by Simon Marlow at 2002-05-09T12:45:19+00:00 [haddock @ 2002-05-09 12:45:19 by simonmar] Add 'stdcall' keyword - - - - - 29b0d7d2 by Simon Marlow at 2002-05-09T13:35:45+00:00 [haddock @ 2002-05-09 13:35:45 by simonmar] Add System Requirements section - - - - - bf14dddd by Simon Marlow at 2002-05-09T13:36:11+00:00 [haddock @ 2002-05-09 13:36:11 by simonmar] Test existential types, amongst other things - - - - - 502f8f6f by Simon Marlow at 2002-05-09T13:37:35+00:00 [haddock @ 2002-05-09 13:37:35 by simonmar] Print the module name in a doc-string parse error - - - - - ca1f8d49 by Simon Marlow at 2002-05-09T13:38:04+00:00 [haddock @ 2002-05-09 13:38:04 by simonmar] Add dependency - - - - - 8d3d91ff by Simon Marlow at 2002-05-09T15:37:57+00:00 [haddock @ 2002-05-09 15:37:57 by simonmar] Add the changelog/release notes - - - - - f3960959 by Simon Marlow at 2002-05-09T15:47:47+00:00 [haddock @ 2002-05-09 15:47:47 by simonmar] mention the backquote-style of markup - - - - - 089fb6e6 by Simon Marlow at 2002-05-09T15:59:45+00:00 [haddock @ 2002-05-09 15:59:45 by simonmar] update - - - - - bdd3be0b by Simon Marlow at 2002-05-09T15:59:56+00:00 [haddock @ 2002-05-09 15:59:56 by simonmar] Document changes since 0.1 - - - - - 00fc4af8 by Simon Marlow at 2002-05-10T08:22:48+00:00 [haddock @ 2002-05-10 08:22:48 by simonmar] oops, update to version 0.2 - - - - - a8a79041 by Simon Marlow at 2002-05-10T16:05:08+00:00 [haddock @ 2002-05-10 16:05:08 by simonmar] Only include a mini-contents if there are 2 or more sections - - - - - 06653319 by Simon Marlow at 2002-05-13T09:13:12+00:00 [haddock @ 2002-05-13 09:13:12 by simonmar] fix typos - - - - - 1402b19b by Simon Marlow at 2002-05-13T10:14:22+00:00 [haddock @ 2002-05-13 10:14:22 by simonmar] Allow backquote as the right-hand quote as well as the left-hand quote, as suggested by Dean Herrington. Clean up the grammar a litte. - - - - - dcd5320d by Simon Marlow at 2002-05-13T10:44:10+00:00 [haddock @ 2002-05-13 10:44:10 by simonmar] a couple more things, prioritise a bit - - - - - a90130c4 by Simon Marlow at 2002-05-13T15:19:03+00:00 [haddock @ 2002-05-13 15:19:03 by simonmar] Cope with datatypes which have documentation on the constructor but not the type itself, and records which have documentation on the fields but not the constructor. (Thanks to Ross Paterson for pointing out the bugs). - - - - - a774d432 by Simon Marlow at 2002-05-13T15:20:54+00:00 [haddock @ 2002-05-13 15:20:54 by simonmar] Fix one of the record examples - - - - - 2d1d5218 by Simon Marlow at 2002-05-15T12:44:35+00:00 [haddock @ 2002-05-15 12:44:35 by simonmar] Preserve the newline before a bird-track, but only within a paragraph. - - - - - 1554c09a by Simon Marlow at 2002-05-15T13:03:02+00:00 [haddock @ 2002-05-15 13:03:01 by simonmar] Reworking of the internals to support documenting function arguments (the Most Wanted new feature by the punters). The old method of keeping parsed documentation in a Name -> Doc mapping wasn't going to cut it for anntations on type components, where there's no name to attach the documentation to, so I've moved to storing all the documentation in the abstract syntax. Previously some of the documentation was left in the abstract syntax by the parser, but was later extracted into the mapping. In order to avoid having to parameterise the abstract syntax over the type of documentation stored in it, we have to parse the documentation at the same time as we parse the Haskell source (well, I suppose we could store 'Either String Doc' in the HsSyn, but that's clunky). One upshot is that documentation is now parsed eagerly, and documentation parse errors are fatal (but have better line numbers in the error message). The new story simplifies matters for the code that processes the source modules, because we don't have to maintain the extra Name->Doc mapping, and it should improve efficiency a little too. New features: - Function arguments and return values can now have doc annotations. - If you refer to a qualified name in a doc string, eg. 'IO.putStr', then Haddock will emit a hyperlink even if the identifier is not in scope, so you don't have to make sure everything referred to from the documentation is imported. - several bugs & minor infelicities fixed. - - - - - 57344dc3 by Simon Marlow at 2002-05-15T13:03:19+00:00 [haddock @ 2002-05-15 13:03:19 by simonmar] Bump to version 0.3 - - - - - b2791812 by Simon Marlow at 2002-05-15T13:03:41+00:00 [haddock @ 2002-05-15 13:03:41 by simonmar] update - - - - - fead183e by Simon Marlow at 2002-05-15T13:10:15+00:00 [haddock @ 2002-05-15 13:10:15 by simonmar] Rename Foo.hs to Test.hs, and add a Makefile - - - - - b0b1f89f by Simon Marlow at 2002-05-15T13:16:07+00:00 [haddock @ 2002-05-15 13:16:07 by simonmar] - Remove the note about function argument docs not being implemented - Note that qualified identifiers can be used to point to entities that aren't in scope. - - - - - 5665f31a by Simon Marlow at 2002-05-15T13:28:46+00:00 [haddock @ 2002-05-15 13:28:46 by simonmar] Patch to add support for GHC-style primitive strings ".."#, from Ross Paterson. - - - - - 0564505d by Simon Marlow at 2002-05-17T10:51:57+00:00 [haddock @ 2002-05-17 10:51:57 by simonmar] Fix bugs in qualified name handling (A.B.f was returned as B.f) - - - - - 10e7311c by Simon Marlow at 2002-05-21T10:24:52+00:00 [haddock @ 2002-05-21 10:24:52 by simonmar] - Use an alternate tabular layout for datatypes, which is more compact - Fix some problems with the function argument documentation - - - - - 2f91c2a6 by Simon Marlow at 2002-05-21T10:27:40+00:00 [haddock @ 2002-05-21 10:27:40 by simonmar] add a few more test cases - - - - - 01c2ddd2 by Simon Marlow at 2002-05-21T10:28:33+00:00 [haddock @ 2002-05-21 10:28:33 by simonmar] Rearrange a bit, and add support for tabular datatype rendering - - - - - a4e4c5f8 by Simon Marlow at 2002-05-27T09:03:52+00:00 [haddock @ 2002-05-27 09:03:51 by simonmar] Lots of changes: - instances of a class are listed with the class, and instances involving a datatype are listed with that type. Derived instances aren't included at the moment: the calculation to find the instance head for a derived instance is non-trivial. - some formatting changes; use rows with specified height rather than cellspacing in some places. - various fixes (source file links were wrong, amongst others) - - - - - 48722e68 by Simon Marlow at 2002-05-27T12:30:38+00:00 [haddock @ 2002-05-27 12:30:37 by simonmar] - Put function arguments *before* the doc for the function, as suggested by Sven Panne. This looks nicer when the function documentation is long. - Switch to using bold for binders at the definition site, and use underline for keywords. This makes the binder stand out more. - - - - - 657204d2 by Simon Marlow at 2002-05-27T13:19:49+00:00 [haddock @ 2002-05-27 13:19:49 by simonmar] Fix bug: we weren't renaming HsDocCommentNamed in renameDecl - - - - - 592aae66 by Simon Marlow at 2002-05-27T14:10:27+00:00 [haddock @ 2002-05-27 14:10:27 by simonmar] Fix some bugs in the rendering of qualified type signatures. - - - - - 69c8f763 by Simon Marlow at 2002-05-27T14:36:45+00:00 [haddock @ 2002-05-27 14:36:45 by simonmar] warning message tweak - - - - - 16e64e21 by Simon Marlow at 2002-05-27T14:53:53+00:00 [haddock @ 2002-05-27 14:53:53 by simonmar] hyperlinked identifiers should be in <tt> - - - - - 8d5e4783 by Simon Marlow at 2002-05-27T15:56:45+00:00 [haddock @ 2002-05-27 15:56:45 by simonmar] Do something sensible for modules which don't export anything (except instances). - - - - - 9d3ef811 by Simon Marlow at 2002-05-28T10:12:50+00:00 [haddock @ 2002-05-28 10:12:50 by simonmar] Rename the module documentation properly (bug reported by Sven Panne). - - - - - ef03a1cc by Simon Marlow at 2002-05-28T10:13:04+00:00 [haddock @ 2002-05-28 10:13:04 by simonmar] Add some more test cases - - - - - 92baa0e8 by Simon Marlow at 2002-05-28T11:17:55+00:00 [haddock @ 2002-05-28 11:17:55 by simonmar] If an identifier doesn't lex, then just replace it by a DocString. - - - - - a3156213 by Simon Marlow at 2002-05-28T16:16:19+00:00 [haddock @ 2002-05-28 16:16:19 by simonmar] Only link to names in the current module which are actually listed in the documentation. A name may be exported but not present in the documentation if it is exported as part of a 'module M' export specifier. - - - - - 31acf941 by Simon Marlow at 2002-05-28T16:17:11+00:00 [haddock @ 2002-05-28 16:17:11 by simonmar] update - - - - - 7e474ebf by Sigbjorn Finne at 2002-05-28T22:42:08+00:00 [haddock @ 2002-05-28 22:42:08 by sof] Handle lone occurrences of '/', e.g., -- | This/that. [did this in the lexer rather than in the parser, as I couldn't see a way not to introduce an S/R conflict that way.] - - - - - 093f7e53 by Simon Marlow at 2002-05-29T09:09:49+00:00 [haddock @ 2002-05-29 09:09:49 by simonmar] Back out previous change until we can find a better way to do this. - - - - - 9234389c by Simon Marlow at 2002-05-29T13:19:06+00:00 [haddock @ 2002-05-29 13:19:06 by simonmar] Make the markup syntax a little more friendly: - single quotes are now interpreted literally unless they surround a valid Haskell identifier. So for example now there's no need to escape a single quote used as an apostrophe. - text to the right of a bird track is now literal (if you want marked-up text in a code block, use @...@). - - - - - b3333526 by Simon Marlow at 2002-05-29T13:38:51+00:00 [haddock @ 2002-05-29 13:38:51 by simonmar] Document recent changes to markup syntax - - - - - f93641d6 by Simon Marlow at 2002-05-29T15:27:18+00:00 [haddock @ 2002-05-29 15:27:18 by simonmar] Include the instances in abstract data types too - - - - - 613f21e3 by Simon Marlow at 2002-06-03T13:05:58+00:00 [haddock @ 2002-06-03 13:05:57 by simonmar] Allow exporting of individual class methods and record selectors. For these we have to invent the correct type signature, which we do in the simplest possible way (i.e. no context reduction nonsense in the class case). - - - - - 14b36807 by Simon Marlow at 2002-06-03T13:20:00+00:00 [haddock @ 2002-06-03 13:20:00 by simonmar] Fix linking to qualified names again (thanks to Sven Panne for pointing out the bug). - - - - - 95b10eac by Simon Marlow at 2002-06-03T13:46:48+00:00 [haddock @ 2002-06-03 13:46:48 by simonmar] Fix for exporting record selectors from a newtype declaration - - - - - 272f932e by Simon Marlow at 2002-06-03T13:56:38+00:00 [haddock @ 2002-06-03 13:56:38 by simonmar] update to version 0.3 - - - - - 1c0a3bed by Simon Marlow at 2002-06-03T14:05:07+00:00 [haddock @ 2002-06-03 14:05:07 by simonmar] Add changes in version 0.3 - - - - - 145b4626 by Simon Marlow at 2002-06-03T14:12:38+00:00 [haddock @ 2002-06-03 14:12:38 by simonmar] Render class names as proper binders - - - - - 052106b3 by Simon Marlow at 2002-06-03T14:15:10+00:00 [haddock @ 2002-06-03 14:15:10 by simonmar] update, and separate into bugs, features, and cosmetic items. - - - - - 854f4914 by Simon Marlow at 2002-06-03T14:16:13+00:00 [haddock @ 2002-06-03 14:16:13 by simonmar] More test cases - - - - - 466922c8 by Simon Marlow at 2002-06-03T14:16:56+00:00 [haddock @ 2002-06-03 14:16:56 by simonmar] Example from the paper - - - - - 9962a045 by Simon Marlow at 2002-06-03T14:17:49+00:00 [haddock @ 2002-06-03 14:17:49 by simonmar] A debugging version of the style-sheet, which gives some tables coloured backgrounds so we can see what's going on. - - - - - f16b79db by Simon Marlow at 2002-06-03T14:19:46+00:00 [haddock @ 2002-06-03 14:19:46 by simonmar] typo - - - - - 620db27b by Simon Marlow at 2002-06-03T14:48:32+00:00 [haddock @ 2002-06-03 14:48:32 by simonmar] oops, fix markup bugs - - - - - 53fd105c by Simon Marlow at 2002-06-05T09:05:07+00:00 [haddock @ 2002-06-05 09:05:07 by simonmar] Keep foreign imports when there is no export list (bug reported by Sven Panne). - - - - - 6d98989c by Simon Marlow at 2002-06-05T09:12:02+00:00 [haddock @ 2002-06-05 09:12:02 by simonmar] Identifiers in single quotes can be symbol names too (bug reported by Hal Daume). - - - - - 001811e5 by Sven Panne at 2002-06-08T14:03:36+00:00 [haddock @ 2002-06-08 14:03:36 by panne] Tiny workaround for the fact that Haddock currently ignores HsImportSpecs: Let the local_orig_env take precedence. This is no real solution at all, but improves things sometimes, e.g. in my GLUT documentation. :-) - - - - - 504d19c9 by Simon Marlow at 2002-06-11T09:23:25+00:00 [haddock @ 2002-06-11 09:23:25 by simonmar] portability nit - - - - - e13b5af4 by Simon Marlow at 2002-06-20T12:38:07+00:00 [haddock @ 2002-06-20 12:38:07 by simonmar] Empty declaration fixes. - - - - - f467a9b6 by Simon Marlow at 2002-06-20T12:39:02+00:00 [haddock @ 2002-06-20 12:39:01 by simonmar] Add support for a "prologue" - a description for the whole library, placed on the contents page before the module list. - - - - - b8dbfe20 by Simon Marlow at 2002-06-21T12:43:06+00:00 [haddock @ 2002-06-21 12:43:06 by simonmar] When we have a single code block paragraph, don't place it in <pre>..</pre>, just use <tt>..</tt> to avoid generating extra vertical white space in some browsers. - - - - - 4831dbbd by Simon Marlow at 2002-06-21T15:50:42+00:00 [haddock @ 2002-06-21 15:50:42 by simonmar] Add support for reading and writing interface files(!) This turned out to be quite easy, and necessary to get decent hyperlinks between the documentation for separate packages in the libraries. The functionality isn't quite complete yet: for a given package of modules, you'd like to say "the HTML for these modules lives in directory <dir>" (currently they are assumed to be all in the same place). Two new flags: --dump-interface=FILE dump an interface file in FILE --read-interface=FILE read interface from FILE an interface file describes *all* the modules being processed. Only the exported names are kept in the interface: if you re-export a name from a module in another interface the signature won't be copied. This is a compromise to keep the size of the interfaces sensible. Also, I added another useful option: --no-implicit-prelude avoids trying to import the Prelude. Previously this was the default, but now importing the Prelude from elsewhere makes sense if you also read in an interface containing the Prelude module, so Haddock imports the Prelude implicitly according to the Haskell spec. - - - - - d3640a19 by Sven Panne at 2002-06-23T14:54:00+00:00 [haddock @ 2002-06-23 14:54:00 by panne] Make it compile with newer GHCs - - - - - 780c506b by Sven Panne at 2002-06-23T15:44:31+00:00 [haddock @ 2002-06-23 15:44:31 by panne] Cleaned up build root handling and added more docs - - - - - 45290d2e by Simon Marlow at 2002-06-24T14:37:43+00:00 [haddock @ 2002-06-24 14:37:42 by simonmar] When reading an interface, allow a file path offset to be specified which represents the path to the HTML files for the modules specified by that interface. The path may be either relative (to the location of the HTML for this package), or absolute. The syntax is --read-interface=PATH,FILE where PATH is the path to the HTML, and FILE is the filename containing the interface. - - - - - 4e2b9ae6 by Simon Marlow at 2002-07-03T16:01:08+00:00 [haddock @ 2002-07-03 16:01:07 by simonmar] Handle import specs properly, include 'hiding'. Haddock now has a complete implementation of the Haskell module system (more or less; I won't claim it's 100% correct). - - - - - 9a9aa1a8 by Simon Marlow at 2002-07-03T16:18:16+00:00 [haddock @ 2002-07-03 16:18:16 by simonmar] Update - - - - - 560c3026 by Simon Marlow at 2002-07-04T14:56:10+00:00 [haddock @ 2002-07-04 14:56:10 by simonmar] Clean up the code that constructs the exported declarations, and fix a couple of bugs along the way. Now if you import a class hiding one of the methods, then re-export the class, the version in the documentation will correctly have the appropriate method removed. - - - - - 2c26e77d by Simon Marlow at 2002-07-04T15:26:13+00:00 [haddock @ 2002-07-04 15:26:13 by simonmar] More bugfixes to the export handling - - - - - 03e0710d by Simon Marlow at 2002-07-09T10:12:10+00:00 [haddock @ 2002-07-09 10:12:10 by simonmar] Don't require that the list type comes from "Prelude" for it to be treated as special syntax (sometimes it comes from Data.List or maybe even GHC.Base). - - - - - 44f3891a by Simon Marlow at 2002-07-09T10:12:51+00:00 [haddock @ 2002-07-09 10:12:51 by simonmar] commented-out debugging code - - - - - 97280873 by Krasimir Angelov at 2002-07-09T16:33:33+00:00 [haddock @ 2002-07-09 16:33:31 by krasimir] 'Microsoft HTML Help' support - - - - - 3dc04655 by Simon Marlow at 2002-07-10T09:40:56+00:00 [haddock @ 2002-07-10 09:40:56 by simonmar] Fix for rendering of the (->) type constructor, from Ross Paterson. - - - - - c9f149c6 by Simon Marlow at 2002-07-10T10:26:11+00:00 [haddock @ 2002-07-10 10:26:11 by simonmar] Tweaks to the MS Help support: the extra files are now only generated if you ask for them (--ms-help). - - - - - e8acc1e6 by Simon Marlow at 2002-07-10T10:57:10+00:00 [haddock @ 2002-07-10 10:57:10 by simonmar] Document all the new options since 0.3 - - - - - 8bb85544 by Simon Marlow at 2002-07-10T10:58:31+00:00 [haddock @ 2002-07-10 10:58:31 by simonmar] Sort the options a bit - - - - - abc0dd59 by Simon Marlow at 2002-07-15T09:19:38+00:00 [haddock @ 2002-07-15 09:19:38 by simonmar] Fix a bug in mkExportItems when processing a module without an explicit export list. We were placing one copy of a declaration for each binder in the declaration, which for a data type would mean one copy of the whole declaration per constructor or record selector. - - - - - dde65bb9 by Simon Marlow at 2002-07-15T09:54:16+00:00 [haddock @ 2002-07-15 09:54:16 by simonmar] merge rev. 1.35 - - - - - bd7eb8c4 by Simon Marlow at 2002-07-15T10:14:31+00:00 [haddock @ 2002-07-15 10:14:30 by simonmar] Be a bit more liberal in the kind of commenting styles we allow, as suggested by Malcolm Wallace. Mostly this consists of allowing doc comments either side of a separator token. In an export list, a section heading is now allowed before the comma, as well as after it. eg. module M where ( T(..) -- * a section heading , f -- * another section heading , g ) In record fields, doc comments are allowed anywhere (previously a doc-next was allowed only after the comma, and a doc-before was allowed only before the comma). eg. data R = C { -- | describes 'f' f :: Int -- | describes 'g' , g :: Int } - - - - - 8f6dfe34 by Simon Marlow at 2002-07-15T10:21:56+00:00 [haddock @ 2002-07-15 10:21:56 by simonmar] Mention alternative commenting styles. - - - - - fc515bb7 by Simon Marlow at 2002-07-15T16:16:50+00:00 [haddock @ 2002-07-15 16:16:50 by simonmar] Allow multiple sections/subsections before and after a comma in the export list. Also at the same time I made the syntax a little stricter (multiple commas now aren't allowed between export specs). - - - - - 80a97e74 by Simon Marlow at 2002-07-19T09:13:10+00:00 [haddock @ 2002-07-19 09:13:10 by simonmar] Allow special id's ([], (), etc.) to be used in an import declaration. - - - - - a69d7378 by Simon Marlow at 2002-07-19T09:59:02+00:00 [haddock @ 2002-07-19 09:59:02 by simonmar] Allow special id's ([], (), etc.) to be used in an import declarations. - - - - - d205fa60 by Simon Marlow at 2002-07-19T10:00:16+00:00 [haddock @ 2002-07-19 10:00:16 by simonmar] Relax the restrictions which require doc comments to be followed by semi colons - in some cases this isn't necessary. Now you can write module M where { -- | some doc class C where {} } without needing to put a semicolon before the class declaration. - - - - - e9301e14 by Simon Marlow at 2002-07-23T08:24:09+00:00 [haddock @ 2002-07-23 08:24:09 by simonmar] A new TODO list item - - - - - e5d77586 by Simon Marlow at 2002-07-23T08:40:56+00:00 [haddock @ 2002-07-23 08:40:56 by simonmar] - update the acknowledgements - remove the paragraph that described how to use explicit layout with doc comments; it isn't relevant any more. - - - - - 78a94137 by Simon Marlow at 2002-07-23T08:43:02+00:00 [haddock @ 2002-07-23 08:43:02 by simonmar] more tests - - - - - 5c320927 by Simon Marlow at 2002-07-23T08:43:26+00:00 [haddock @ 2002-07-23 08:43:26 by simonmar] Updates for version 0.4 - - - - - 488e99ae by Simon Marlow at 2002-07-23T09:10:46+00:00 [haddock @ 2002-07-23 09:10:46 by simonmar] Fix the %changelog (rpm complained that it wasn't in the right order) - - - - - a77bb373 by Simon Marlow at 2002-07-23T09:12:38+00:00 [haddock @ 2002-07-23 09:12:38 by simonmar] Another item for the TODO list - - - - - f1ec1813 by Simon Marlow at 2002-07-23T10:18:46+00:00 [haddock @ 2002-07-23 10:18:46 by simonmar] Add a version banner when invoked with -v - - - - - 1d44cadf by Simon Marlow at 2002-07-24T09:28:19+00:00 [haddock @ 2002-07-24 09:28:19 by simonmar] Remove ^Ms - - - - - 4d8d5e94 by Simon Marlow at 2002-07-24T09:42:18+00:00 [haddock @ 2002-07-24 09:42:17 by simonmar] Patches to quieten ghc -Wall, from those nice folks at Galois. - - - - - d6edc43e by Simon Marlow at 2002-07-25T14:37:29+00:00 [haddock @ 2002-07-25 14:37:28 by simonmar] Patch to allow simple hyperlinking to an arbitrary location in another module's documentation, from Volker Stolz. Now in a doc comment: #foo# creates <a name="foo"></a> And you can use the form "M\#foo" to hyperlink to the label 'foo' in module 'M'. Note that the backslash is necessary for now. - - - - - b34d18fa by Simon Marlow at 2002-08-02T09:08:22+00:00 [haddock @ 2002-08-02 09:08:22 by simonmar] The <TT> and <PRE> environments seem to use a font that is a little too small in IE. Compensate. (suggestion from Daan Leijen). - - - - - 8106b086 by Simon Marlow at 2002-08-02T09:25:23+00:00 [haddock @ 2002-08-02 09:25:20 by simonmar] Remove <P>..</P> from around list items, to reduce excess whitespace between the items of bulleted and ordered lists. (Suggestion from Daan Leijen). - - - - - c1acff8f by Simon Marlow at 2002-08-05T09:03:49+00:00 [haddock @ 2002-08-05 09:03:49 by simonmar] update - - - - - f968661c by Simon Marlow at 2002-11-11T09:32:57+00:00 [haddock @ 2002-11-11 09:32:57 by simonmar] Fix cut-n-pasto - - - - - 12d02619 by Simon Marlow at 2002-11-13T09:49:46+00:00 [haddock @ 2002-11-13 09:49:46 by simonmar] Small bugfix in the --read-interface option parsing from Brett Letner. - - - - - 30e32d5e by Ross Paterson at 2003-01-16T15:07:57+00:00 [haddock @ 2003-01-16 15:07:57 by ross] Adjust for the new exception libraries (as well as the old ones). - - - - - 871f65df by Sven Panne at 2003-02-20T21:31:40+00:00 [haddock @ 2003-02-20 21:31:40 by panne] * Add varsyms and consyms to index * Exclude empty entries from index - - - - - bc42cc87 by Sven Panne at 2003-02-24T21:26:29+00:00 [haddock @ 2003-02-24 21:26:29 by panne] Don't convert a "newtype" to a single-constructor "data" for non-abstractly exported types, they are quite different regarding strictness/pattern matching. Now a "data" without any constructors is only emitted for an abstractly exported type, regardless if it is actually a "newtype" or a "data". - - - - - 0c2a1d99 by Sven Panne at 2003-03-08T19:02:38+00:00 [haddock @ 2003-03-08 19:02:38 by panne] Fixed some broken/redirected/canonicalized links found by a very picky link checker. - - - - - 25459269 by Sven Panne at 2003-03-09T21:13:43+00:00 [haddock @ 2003-03-09 21:13:43 by panne] Don't append a fragment to non-defining index entries, only documents with a defining occurrence have a name anchor. - - - - - 6be4db86 by Sven Panne at 2003-03-10T21:34:25+00:00 [haddock @ 2003-03-10 21:34:24 by panne] Escape fragments. This fixes e.g. links to operators. - - - - - eb12972c by Ross Paterson at 2003-04-25T10:50:06+00:00 [haddock @ 2003-04-25 10:50:05 by ross] An 80% solution to generating derived instances. A complete solution would duplicate the instance inference logic, but if a type variable occurs as a constructor argument, then we can just propagate the derived class to the variable. But we know nothing of the constraints on any type variables that occur elsewhere. For example, the declarations data Either a b = Left a | Right b deriving (Eq, Ord) data Ptr a = Ptr Addr# deriving (Eq, Ord) newtype IORef a = IORef (STRef RealWorld a) deriving Eq yield the instances (Eq a, Eq b) => Eq (Either a b) (Ord a, Ord b) => Ord (Either a b) Eq (Ptr a) Ord (Ptr a) (??? a) => Eq (IORef a) The last example shows the limits of this local analysis. Note that a type variable may be in both categories: then we know a constraint, but there may be more, or a stronger constraint, e.g. data Tree a = Node a [Tree a] deriving Eq yields (Eq a, ??? a) => Eq (Tree a) - - - - - de886f78 by Simon Marlow at 2003-04-25T11:17:55+00:00 [haddock @ 2003-04-25 11:17:55 by simonmar] Some updates, including moving the derived instance item down to the bottom of the list now that Ross has contributed some code that does the job for common cases. - - - - - 1b52cffd by Simon Marlow at 2003-04-30T14:02:32+00:00 [haddock @ 2003-04-30 14:02:32 by simonmar] When installing on Windows, run cygpath over $(HADDOCKLIB) so that haddock (a mingw program, built by GHC) can understand it. You still need to be in a cygwin environment to run Haddock, because of the shell script wrapper. - - - - - d4f638de by Simon Marlow at 2003-05-06T10:04:47+00:00 [haddock @ 2003-05-06 10:04:47 by simonmar] Catch another case of a paragraph containing just a DocMonospaced that should turn into a DocCodeBlock. - - - - - 4162b2b9 by Simon Marlow at 2003-05-06T10:11:44+00:00 [haddock @ 2003-05-06 10:11:44 by simonmar] Add some more code-block tests. - - - - - 4f5802c8 by Simon Marlow at 2003-05-06T10:14:52+00:00 [haddock @ 2003-05-06 10:14:52 by simonmar] Don't turn a single DocCodeBlock into a DocMonospaced, because that tends to remove the line breaks in the code. - - - - - ef8c45f7 by Simon Marlow at 2003-05-21T15:07:21+00:00 [haddock @ 2003-05-21 15:07:21 by simonmar] Only omit the module contents when there are no section headings at all. - - - - - bcee1e75 by Sigbjorn Finne at 2003-05-30T16:50:45+00:00 [haddock @ 2003-05-30 16:50:45 by sof] cygpath: for now, steer clear of --mixed - - - - - 30567af3 by Sigbjorn Finne at 2003-05-30T17:59:28+00:00 [haddock @ 2003-05-30 17:59:28 by sof] oops, drop test defn from prev commit - - - - - b0856e7d by Simon Marlow at 2003-06-03T09:55:26+00:00 [haddock @ 2003-06-03 09:55:26 by simonmar] Two small fixes to make the output valid HTML 4.01 (transitional). Thanks to Malcolm Wallace for pointing out the problems. - - - - - 70e137ea by Simon Marlow at 2003-07-28T13:30:35+00:00 [haddock @ 2003-07-28 13:30:35 by simonmar] Add tests for a couple of bugs. - - - - - 122bd578 by Simon Marlow at 2003-07-28T13:31:25+00:00 [haddock @ 2003-07-28 13:31:25 by simonmar] Add documentation for anchors. - - - - - 0bd27cb2 by Simon Marlow at 2003-07-28T13:31:46+00:00 [haddock @ 2003-07-28 13:31:46 by simonmar] Update - - - - - 08052d42 by Simon Marlow at 2003-07-28T13:32:12+00:00 [haddock @ 2003-07-28 13:32:12 by simonmar] layout tweak. - - - - - 13942749 by Simon Marlow at 2003-07-28T13:33:03+00:00 [haddock @ 2003-07-28 13:33:03 by simonmar] Differentiate links to types/classes from links to variables/constructors with a prefix ("t:" and "v:" respectively). - - - - - d7f493b9 by Simon Marlow at 2003-07-28T13:35:17+00:00 [haddock @ 2003-07-28 13:35:16 by simonmar] When a module A exports another module's contents via 'module B', then modules which import entities from B re-exported by A should link to B.foo rather than A.foo. See examples/Bug2.hs. - - - - - d94cf705 by Simon Marlow at 2003-07-28T13:36:14+00:00 [haddock @ 2003-07-28 13:36:14 by simonmar] Update to version 0.5 - - - - - dbb776cd by Sven Panne at 2003-07-28T14:02:43+00:00 [haddock @ 2003-07-28 14:02:43 by panne] * Updated to version 0.5 * Automagically generate configure if it is not there - - - - - 6cfeee53 by Simon Marlow at 2003-07-28T14:32:43+00:00 [haddock @ 2003-07-28 14:32:42 by simonmar] Update to avoid using hslibs with GHC >= 5.04 - - - - - a1ce838f by Simon Marlow at 2003-07-28T14:33:37+00:00 [haddock @ 2003-07-28 14:33:37 by simonmar] Update for 0.5 - - - - - c0fe6493 by Simon Marlow at 2003-07-28T14:53:22+00:00 [haddock @ 2003-07-28 14:53:22 by simonmar] Markup fix - - - - - 6ea31596 by Sven Panne at 2003-07-28T16:40:45+00:00 [haddock @ 2003-07-28 16:40:45 by panne] Make it compile with GHC >= 6.01 - - - - - afcd30fc by Simon Marlow at 2003-07-30T15:04:52+00:00 [haddock @ 2003-07-30 15:04:52 by simonmar] Pay attention to import specs when building the the import env, as well as the orig env. This may fix some wrong links in documentation when import specs are being used. - - - - - 17c3137f by Simon Marlow at 2003-07-30T16:05:41+00:00 [haddock @ 2003-07-30 16:05:40 by simonmar] Rename instances based on the import_env for the module in which they are to be displayed. This should give, in many cases, better links for the types and classes mentioned in the instance head. This involves keeping around the import_env in the iface until the end, because instances are not collected up until all the modules have been processed. Fortunately it doesn't seem to affect performance much. Instance heads are now attached to ExportDecls, rather than the HTML backend passing around a separate mapping for instances. This is a cleanup. - - - - - 3d3b5c87 by Sven Panne at 2003-08-04T10:18:24+00:00 [haddock @ 2003-08-04 10:18:24 by panne] Don't print parentheses around one-element contexts - - - - - 9e3f3f2d by Simon Marlow at 2003-08-04T12:59:47+00:00 [haddock @ 2003-08-04 12:59:47 by simonmar] A couple of TODOs. - - - - - e9d8085c by Simon Marlow at 2003-08-05T14:10:31+00:00 [haddock @ 2003-08-05 14:10:31 by simonmar] I'm not sure why, but it seems that the index entries for non-defining occurrences of entities did not have an anchor - the link just pointed to the module. This fixes it. - - - - - ff5c7d6d by Simon Marlow at 2003-08-15T14:42:59+00:00 [haddock @ 2003-08-15 14:42:59 by simonmar] Convert the lexer to Alex, and fix a bug in the process. - - - - - 1aa077bf by Simon Marlow at 2003-08-15T15:00:18+00:00 [haddock @ 2003-08-15 15:00:18 by simonmar] Update - - - - - d3de1e38 by Simon Marlow at 2003-08-15T15:01:03+00:00 [haddock @ 2003-08-15 15:01:03 by simonmar] wibbles - - - - - b40ece3b by Simon Marlow at 2003-08-18T10:04:47+00:00 [haddock @ 2003-08-18 10:04:47 by simonmar] Lex the 'mdo' keyword as 'do'. - - - - - 8f9a1146 by Simon Marlow at 2003-08-18T11:48:24+00:00 [haddock @ 2003-08-18 11:48:24 by simonmar] Two bugs from Sven. - - - - - ea54ebc0 by Simon Marlow at 2003-08-18T11:48:46+00:00 [haddock @ 2003-08-18 11:48:46 by simonmar] Fixes to the new lexer. - - - - - d5f6a4b5 by Simon Marlow at 2003-08-19T09:09:03+00:00 [haddock @ 2003-08-19 09:09:03 by simonmar] Further wibbles to the syntax. - - - - - 6bbdadb7 by Sven Panne at 2003-08-26T18:45:35+00:00 [haddock @ 2003-08-26 18:45:35 by panne] Use autoreconf instead of autoconf - - - - - 32e889cb by Sven Panne at 2003-08-26T19:01:19+00:00 [haddock @ 2003-08-26 19:01:18 by panne] Made option handling a bit more consistent with other tools, in particular: Every program in fptools should output * version info on stdout and terminate successfully when -V or --version * usage info on stdout and terminate successfully when -? or --help * usage info on stderr and terminate unsuccessfully when an unknown option is given. - - - - - 5d156a91 by Sven Panne at 2003-08-26T19:20:55+00:00 [haddock @ 2003-08-26 19:20:55 by panne] Make it *very* clear that we terminate when given a -V/--version flag - - - - - e6577265 by Sven Panne at 2003-08-27T07:50:03+00:00 [haddock @ 2003-08-27 07:50:02 by panne] * Made -D a short option for --dump-interface. * Made -m a short option for --ms-help. * Made -n a short option for --no-implicit-prelude. * Made -c a short option for --css. * Removed DocBook options from executable (they didn't do anything), but mark them as reserved in the docs. Note that the short option for DocBook output is now -S (from SGML) instead of -d. The latter is now a short option for --debug. * The order of the Options in the documentation now matches the order printed by Haddock itself. Note: Although changing the names of options is often a bad idea, I'd really like to make the options for the programs in fptools more consistent and compatible to the ones used in common GNU programs. - - - - - d303ff98 by Simon Marlow at 2003-09-10T08:23:48+00:00 [haddock @ 2003-09-10 08:23:48 by simonmar] Add doc subdir. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 9a70e46a by Simon Marlow at 2003-09-10T08:24:32+00:00 [haddock @ 2003-09-10 08:24:32 by simonmar] Install these files in $(datadir), not $(libdir), since they're architecture independent. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - bbb87e7a by Simon Marlow at 2003-09-10T08:25:31+00:00 [haddock @ 2003-09-10 08:25:31 by simonmar] Haddock's supplementary HTML bits now live in $(datadir), not $(libdir). Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 3587c24b by Simon Marlow at 2003-09-22T10:34:38+00:00 [haddock @ 2003-09-22 10:34:38 by simonmar] Allow installing of docs. - - - - - d510b517 by Sven Panne at 2003-10-11T08:10:44+00:00 [haddock @ 2003-10-11 08:10:44 by panne] Include architecture-independent files in file list - - - - - 187d7618 by Sigbjorn Finne at 2003-10-20T17:19:24+00:00 [haddock @ 2003-10-20 17:19:22 by sof] support for i-parameters + zip comprehensions - - - - - b6c7a273 by Simon Marlow at 2003-11-03T14:24:24+00:00 [haddock @ 2003-11-03 14:24:24 by simonmar] Update TODO file. - - - - - 58513e33 by Simon Marlow at 2003-11-05T11:22:04+00:00 [haddock @ 2003-11-05 11:22:04 by simonmar] Remove the last of the uses of 'trace' to emit warnings, and tidy up a couple of places where duplicate warnings were being emitted. - - - - - 33a78846 by Simon Marlow at 2003-11-05T11:30:53+00:00 [haddock @ 2003-11-05 11:30:52 by simonmar] - Suppress warnings about unknown imported modules by default. - Add a -v/--verbose flag to re-enable these warnings. The general idea is to suppress the "Warning: unknown module: Prelude" warnings which most Haddock users will see every time, and which aren't terribly useful. - - - - - a969de7f by Simon Marlow at 2003-11-05T12:30:28+00:00 [haddock @ 2003-11-05 12:30:28 by simonmar] - Remove the emboldening of index entries for defining locations. This isn't useful, and breaks abstractions. - If an entity is re-exported by a module but the module doesn't include documentation for that entity (perhaps because it is re-exported by 'module M'), then don't attempt to hyperlink to the documentation from the index. Instead, just list that module in the index, to indicate that the entity is exported from there. - - - - - f14ea82a by Simon Marlow at 2003-11-05T15:15:59+00:00 [haddock @ 2003-11-05 15:15:59 by simonmar] Index overhaul: - no more separate type/class and variable/function indices - the index now makes a distinction between different entities with the same name. One example is a type constructor with the same name as a data constructor, but another example is simply a function with the same name exported by two different modules. For example, the index entry for 'catch' now looks like this: catch 1 (Function) Control.Exception 2 (Function) GHC.Exception, Prelude, System.IO, System.IO.Error making it clear that there are two different 'catch'es, but one of them is exported by several modules. - Each index page now has the index contents (A B C ...) at the top. Please let me know if you really hate any of this. - - - - - 01a25ca6 by Simon Marlow at 2003-11-05T15:16:38+00:00 [haddock @ 2003-11-05 15:16:38 by simonmar] Update - - - - - 1a7ccb86 by Simon Marlow at 2003-11-05T17:16:05+00:00 [haddock @ 2003-11-05 17:16:04 by simonmar] Support for generating a single unified index for several packages. --use-index=URL turns off normal index generation, causes Index links to point to URL. --gen-index generates an combined index from the specified interfaces. Currently doesn't work exactly right, because the interfaces don't contain the iface_reexported info. I'll need to fix that up. - - - - - a2bca16d by Simon Marlow at 2003-11-06T10:44:52+00:00 [haddock @ 2003-11-06 10:44:52 by simonmar] Include iface_reexported in the .haddock file. This unfortunately bloats the file (40% for base). If this gets to be a problem we can always apply the dictionary trick that GHC uses for squashing .hi files. - - - - - 0a09c293 by Simon Marlow at 2003-11-06T12:39:47+00:00 [haddock @ 2003-11-06 12:39:46 by simonmar] - Add definition lists, marked up like this: -- | This is a definition list: -- -- [@foo@] The description of @foo at . -- -- [@bar@] The description of @bar at . Cunningly, the [] characters are not treated specially unless a [ is found at the beginning of a paragraph, in which case the ] becomes special in the following text. - Add --use-contents and --gen-contents, along the lines of --use-index and --gen-index added yesterday. Now we can generate a combined index and contents for the whole of the hierarchical libraries, and in theory the index/contents on the system could be updated as new packages are added. - - - - - fe1b3460 by Simon Marlow at 2003-11-06T14:47:36+00:00 [haddock @ 2003-11-06 14:47:36 by simonmar] Remove the 'Parent' button - it is of dubious use, and often points into thin air. - - - - - db6d762f by Simon Marlow at 2003-11-06T16:48:14+00:00 [haddock @ 2003-11-06 16:48:11 by simonmar] - Include the OptHide setting in the interface, so we don't include hidden modules in the combined index/contents. - Add a -k/--package flag to set the package name for the current set of modules. The package name for each module is now shown in the right-hand column of the contents, in a combined contents page. - - - - - 7d71718b by Simon Marlow at 2003-11-06T16:50:28+00:00 [haddock @ 2003-11-06 16:50:28 by simonmar] Add -k/--package docs - - - - - ef43949d by Simon Marlow at 2003-11-06T16:51:23+00:00 [haddock @ 2003-11-06 16:51:23 by simonmar] Bump to 0.6 - - - - - 1c419e06 by Simon Marlow at 2003-11-06T16:51:50+00:00 [haddock @ 2003-11-06 16:51:50 by simonmar] update - - - - - 69422327 by Simon Marlow at 2003-11-10T14:41:06+00:00 [haddock @ 2003-11-10 14:41:05 by simonmar] Re-exporting names from a different package is problematic, because we don't have access to the full documentation for the entity. Currently Haddock just ignores entities with no documentation, but this results in bogus-looking empty documentation for many of the modules in the haskell98 package. So: - the documentation will now just list the name, as a link pointing to the location of the actual documentation. - now we don't attempt to link to these re-exported entities if they are referred to by the current module. Additionally: - If there is no documentation in the current module, include just the Synopsis section (rather than just the documentation section, as it was before). This just looks nicer and was on the TODO list. - - - - - 3c3fc433 by Simon Marlow at 2003-11-10T14:51:59+00:00 [haddock @ 2003-11-10 14:51:59 by simonmar] Fix for getReExports: take into account names which are not visible because they are re-exported from a different package. - - - - - 31c8437b by Simon Marlow at 2003-11-10T15:10:53+00:00 [haddock @ 2003-11-10 15:10:53 by simonmar] Version 0.6 changes - - - - - a7c2430b by Simon Marlow at 2003-11-10T15:15:58+00:00 [haddock @ 2003-11-10 15:15:58 by simonmar] getReExports: one error case that isn't - - - - - 00cc459c by Simon Marlow at 2003-11-10T16:15:19+00:00 [haddock @ 2003-11-10 16:15:18 by simonmar] copyright update - - - - - ca62408d by Simon Marlow at 2003-11-11T09:57:25+00:00 [haddock @ 2003-11-11 09:57:25 by simonmar] Version 0.6 - - - - - 3acbf818 by Simon Marlow at 2003-11-11T12:10:44+00:00 [haddock @ 2003-11-11 12:10:44 by simonmar] Go back to producing just the documentation section, rather than just the synopsis section, for a module with no documentation annotations. One reason is that the synopsis section tries to link each entity to its documentation on the same page. Also, the doc section anchors each entity, and it lists instances which the synopsis doesn't. - - - - - 6c90abc2 by Simon Marlow at 2003-11-12T10:03:39+00:00 [haddock @ 2003-11-12 10:03:39 by simonmar] 2002 -> 2003 - - - - - 090bbc4c by Simon Marlow at 2003-11-28T12:08:00+00:00 [haddock @ 2003-11-28 12:08:00 by simonmar] update - - - - - 8096a832 by Simon Marlow at 2003-11-28T12:09:58+00:00 [haddock @ 2003-11-28 12:09:58 by simonmar] Fix some of the problems with Haddock generating pages that are too wide. Now we only specify 'nowrap' when it is necessary to avoid a code box getting squashed up by the text to the right of it. - - - - - 35294929 by Sven Panne at 2003-12-29T17:16:31+00:00 [haddock @ 2003-12-29 17:16:31 by panne] Updated my email address - - - - - cdb697bf by Simon Marlow at 2004-01-08T10:14:24+00:00 [haddock @ 2004-01-08 10:14:24 by simonmar] Add instructions for using GHC to pre-process source for feeding to Haddock. - - - - - 8dfc491f by Simon Marlow at 2004-01-09T12:45:46+00:00 [haddock @ 2004-01-09 12:45:46 by simonmar] Add -optP-P to example ghc command line. - - - - - ac41b820 by Simon Marlow at 2004-02-03T11:02:03+00:00 [haddock @ 2004-02-03 11:02:03 by simonmar] Fix bug in index generation - - - - - f4e7edcb by Simon Marlow at 2004-02-10T11:51:16+00:00 [haddock @ 2004-02-10 11:51:16 by simonmar] Don't throw away whitespace at the beginning of a line (experimental fix). - - - - - 68e212d2 by Simon Marlow at 2004-02-10T12:10:08+00:00 [haddock @ 2004-02-10 12:10:08 by simonmar] Fix for previous commit: I now realise why the whitespace was stripped from the beginning of the line. Work around it. - - - - - e7d7f2df by Sven Panne at 2004-02-10T18:38:45+00:00 [haddock @ 2004-02-10 18:38:45 by panne] Make Haddock link with the latest relocated monad transformer package - - - - - 992d4225 by Simon Marlow at 2004-02-16T10:21:35+00:00 [haddock @ 2004-02-16 10:21:35 by simonmar] Add a TODO - - - - - 1ac55326 by Simon Marlow at 2004-03-12T11:33:39+00:00 [haddock @ 2004-03-12 11:33:39 by simonmar] Add an item. - - - - - 0478e903 by Simon Marlow at 2004-03-15T12:24:05+00:00 [haddock @ 2004-03-15 12:24:05 by simonmar] Add an item. - - - - - 6f26d21a by Simon Marlow at 2004-03-18T14:21:29+00:00 [haddock @ 2004-03-18 14:21:29 by simonmar] Fix URL - - - - - 19b6bb99 by Simon Marlow at 2004-03-22T14:09:03+00:00 [haddock @ 2004-03-22 14:09:03 by simonmar] getReExports was bogus: we should really look in the import_env to find the documentation for an entity which we are re-exporting without documentation. Suggested by: Ross Paterson (patch modified by me). - - - - - 5c756031 by Simon Marlow at 2004-03-24T09:42:11+00:00 [haddock @ 2004-03-24 09:42:10 by simonmar] hiding bug from Ross Paterson (fixed in rev 1.59 of Main.hs) - - - - - 1b692e6c by Simon Marlow at 2004-03-24T10:10:50+00:00 [haddock @ 2004-03-24 10:10:50 by simonmar] mkExportItems fix & simplification: we should be looking at the actual exported names (calculated earlier) to figure out which subordinates of a declaration are exported. This means that if you export a record, and name its fields separately in the export list, the fields will still be visible in the documentation for the constructor. - - - - - 90e5e294 by Simon Marlow at 2004-03-24T10:12:08+00:00 [haddock @ 2004-03-24 10:12:08 by simonmar] Make restrictCons take into account record field names too (removing a ToDo). - - - - - 2600efa4 by Simon Marlow at 2004-03-24T10:16:17+00:00 [haddock @ 2004-03-24 10:16:17 by simonmar] Record export tests. - - - - - 6a8575c7 by Simon Marlow at 2004-03-25T09:35:14+00:00 [haddock @ 2004-03-25 09:35:14 by simonmar] restrictTo: fix for restricting a newtype with a record field. - - - - - dcf55a8d by Simon Marlow at 2004-03-25T10:01:42+00:00 [haddock @ 2004-03-25 10:01:42 by simonmar] Fix duplicate instance bug - - - - - f49aa758 by Simon Marlow at 2004-03-25T10:02:41+00:00 [haddock @ 2004-03-25 10:02:41 by simonmar] Duplicate instance bug. - - - - - 7b87344c by Simon Marlow at 2004-03-25T10:29:56+00:00 [haddock @ 2004-03-25 10:29:56 by simonmar] If a name is imported from two places, one hidden and one not, choose the unhidden one to link to. Also, when there's only a hidden module to link to, don't try linking to it. - - - - - 40f44d7b by Simon Marlow at 2004-03-25T15:17:24+00:00 [haddock @ 2004-03-25 15:17:23 by simonmar] Add support for collaspible parts of the page, with a +/- button and a bit of JavaScript. Make the instances collapsible, and collapse them by default. This makes documentation with long lists of instances (eg. the Prelude) much easier to read. Maybe we should give other documentation sections the same treatment. - - - - - 9b64dc0f by Simon Marlow at 2004-03-25T15:20:55+00:00 [haddock @ 2004-03-25 15:20:55 by simonmar] Update - - - - - c2fff7f2 by Simon Marlow at 2004-03-25T15:45:10+00:00 [haddock @ 2004-03-25 15:45:10 by simonmar] Eliminate some unnecessary spaces in the HTML rendering - - - - - b7948ff0 by Simon Marlow at 2004-03-25T16:00:37+00:00 [haddock @ 2004-03-25 16:00:36 by simonmar] Remove all that indentation in the generated HTML to keep the file sizes down. - - - - - da2bb4ca by Sven Panne at 2004-03-27T09:57:58+00:00 [haddock @ 2004-03-27 09:57:57 by panne] Added the new-born haddock.js to the build process and the documentation. - - - - - b99e6f8c by Sven Panne at 2004-03-27T10:32:20+00:00 [haddock @ 2004-03-27 10:32:20 by panne] "type" is a required attribute of the "script" element - - - - - 562b185a by Sven Panne at 2004-03-27T12:52:34+00:00 [haddock @ 2004-03-27 12:52:34 by panne] Add a doctype for the contents page, too. - - - - - f6a99c2d by Simon Marlow at 2004-04-14T10:03:25+00:00 [haddock @ 2004-04-14 10:03:25 by simonmar] fix for single-line comment syntax - - - - - de366303 by Simon Marlow at 2004-04-20T13:08:04+00:00 [haddock @ 2004-04-20 13:08:04 by simonmar] Allow a 'type' declaration to include documentation comments. These will be ignored by Haddock, but at least one user (Johannes Waldmann) finds this feature useful, and it's easy to add. - - - - - fd78f51e by Simon Marlow at 2004-05-07T15:14:56+00:00 [haddock @ 2004-05-07 15:14:56 by simonmar] - update copyright - add version to abstract - - - - - 59f53e32 by Sven Panne at 2004-05-09T14:39:53+00:00 [haddock @ 2004-05-09 14:39:53 by panne] Fix the fix for single-line comment syntax, ------------------------------------------- is now a valid comment line again. - - - - - 8b18f2fe by Simon Marlow at 2004-05-10T10:11:51+00:00 [haddock @ 2004-05-10 10:11:51 by simonmar] Update - - - - - 225a491d by Ross Paterson at 2004-05-19T13:10:23+00:00 [haddock @ 2004-05-19 13:10:23 by ross] Make the handling of "deriving" slightly smarter, by ignoring data constructor arguments that are identical to the lhs. Now handles things like data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving ... - - - - - 37588686 by Mike Thomas at 2004-05-21T06:38:14+00:00 [haddock @ 2004-05-21 06:38:14 by mthomas] Windows exe extensions (bin remains for Unix). - - - - - cf2b9152 by Simon Marlow at 2004-05-25T09:34:54+00:00 [haddock @ 2004-05-25 09:34:54 by simonmar] Add some TODO items - - - - - 4d29cdfc by Simon Marlow at 2004-05-25T10:41:46+00:00 [haddock @ 2004-05-25 10:41:46 by simonmar] Complain if -h is used with --gen-index or --gen-contents, because it'll overwrite the new index/contents. - - - - - 2e0771e0 by Mike Thomas at 2004-05-28T20:17:55+00:00 [haddock @ 2004-05-28 20:17:55 by mthomas] Windows: search for templates in executable directory. Unix: Haddock tries cwd first rather than error if no -l arg. - - - - - 8d10bde1 by Sven Panne at 2004-06-05T16:53:34+00:00 [haddock @ 2004-06-05 16:53:34 by panne] Misc. rpm spec file cleanup, including: * make BuildRoot handling more consistent * added default file attributes * consistent defines and tags - - - - - 59974349 by Sven Panne at 2004-06-05T18:01:00+00:00 [haddock @ 2004-06-05 18:01:00 by panne] More rpm spec file cleanup, including: * added some BuildRequires * changed packager to me, so people can complain at the right place :-] * consistently refer to haskell.org instead of www.haskell.org - - - - - b94d4903 by Simon Marlow at 2004-07-01T11:08:58+00:00 [haddock @ 2004-07-01 11:08:57 by simonmar] Update to the +/- buttons: use a resized image rather than a <button>. Still seeing some strange effects in Konqueror, so might need to use a fixed-size image instead. - - - - - d5278f67 by Sven Panne at 2004-07-04T15:15:55+00:00 [haddock @ 2004-07-04 15:15:55 by panne] Install pictures for +/- pictures, too (JPEG is a strange format for graphics like this, I would have expected GIF or PNG here.) Things look fine with Konqueror and Netscape on Linux now, the only downside is that the cursor doesn't change when positioned above the "button". - - - - - 46dec6c5 by Sven Panne at 2004-07-13T17:59:28+00:00 [haddock @ 2004-07-13 17:59:28 by panne] A quote is a valid part of a Haskell identifier, but it would interfere with an ECMA script string delimiter, so escape it there. - - - - - 1d7bc432 by Simon Marlow at 2004-07-22T08:54:06+00:00 [haddock @ 2004-07-22 08:54:06 by simonmar] Add single quote to $ident, so you can say eg. 'foldl'' to refer to foldl' (the longest match rule is our friend). Bug reported by Adrian Hey <ahey at iee.org> - - - - - f183618b by Krasimir Angelov at 2004-07-27T22:59:35+00:00 [haddock @ 2004-07-27 22:58:23 by krasimir] Add basic support for Microsoft HTML Help 2.0 - - - - - d515d0c2 by Krasimir Angelov at 2004-07-27T23:02:36+00:00 [haddock @ 2004-07-27 23:02:36 by krasimir] escape names in the index - - - - - a5f1be23 by Krasimir Angelov at 2004-07-27T23:05:21+00:00 [haddock @ 2004-07-27 23:05:21 by krasimir] Add jsFile, plusFile and minusFile to the file list - - - - - c4fb4881 by Krasimir Angelov at 2004-07-28T22:12:10+00:00 [haddock @ 2004-07-28 22:12:09 by krasimir] bugfix. Move contentsHtmlFile, indexHtmlFile and subIndexHtmlFile functions to HaddockUtil.hs module to make them accessible from HaddockHH2.hs - - - - - 64d30b1d by Krasimir Angelov at 2004-07-30T22:15:47+00:00 [haddock @ 2004-07-30 22:15:45 by krasimir] more stuffs - support for separated compilation of packages - the contents page now uses DHTML TreeView - fixed copyFile bug - - - - - 133c8c5c by Krasimir Angelov at 2004-07-31T12:04:38+00:00 [haddock @ 2004-07-31 12:04:37 by krasimir] make the DHtmlTree in contents page more portable. The +/- buttons are replaced with new images which looks more beatiful. - - - - - 79040963 by Krasimir Angelov at 2004-07-31T13:10:20+00:00 [haddock @ 2004-07-31 13:10:20 by krasimir] Make DHtmlTree compatible with Mozila browser - - - - - 1a55dc90 by Krasimir Angelov at 2004-07-31T14:52:55+00:00 [haddock @ 2004-07-31 14:52:55 by krasimir] fix - - - - - 85ce0237 by Krasimir Angelov at 2004-07-31T14:53:28+00:00 [haddock @ 2004-07-31 14:53:28 by krasimir] HtmlHelp 1.x - - - - - 3c0c53ba by Krasimir Angelov at 2004-07-31T20:35:21+00:00 [haddock @ 2004-07-31 20:35:21 by krasimir] Added support for DevHelp - - - - - d42b5af1 by Krasimir Angelov at 2004-07-31T21:17:51+00:00 [haddock @ 2004-07-31 21:17:51 by krasimir] Document new features in HtmlHelp - - - - - 790fe21e by Krasimir Angelov at 2004-08-01T15:14:02+00:00 [haddock @ 2004-08-01 15:14:02 by krasimir] add missing imports - - - - - fd7cc6bc by Krasimir Angelov at 2004-08-01T19:52:08+00:00 [haddock @ 2004-08-01 19:52:06 by krasimir] fix some bugs. Now I have got the entire libraries documentation in HtmlHelp 2.0 format. - - - - - 94ad7ac8 by Krasimir Angelov at 2004-08-01T19:53:50+00:00 [haddock @ 2004-08-01 19:53:50 by krasimir] I forgot to add the new +/- images - - - - - f0c65388 by Krasimir Angelov at 2004-08-02T16:25:53+00:00 [haddock @ 2004-08-02 16:25:53 by krasimir] Add root node to the table of contents. All modules in tree are not children of the root - - - - - f50bd85d by Sven Panne at 2004-08-02T18:17:46+00:00 [haddock @ 2004-08-02 18:17:46 by panne] Mainly DocBook fixes - - - - - 09527ce3 by Sven Panne at 2004-08-02T20:02:29+00:00 [haddock @ 2004-08-02 20:02:29 by panne] Fixed -o/--odir handling. Generating the output, especially the directory handling, is getting a bit convoluted nowadays... - - - - - c8fbacfa by Sven Panne at 2004-08-02T20:31:13+00:00 [haddock @ 2004-08-02 20:31:13 by panne] Warning police - - - - - 37830bff by Sven Panne at 2004-08-02T20:32:29+00:00 [haddock @ 2004-08-02 20:32:28 by panne] Nuked dead code - - - - - 13847171 by Sven Panne at 2004-08-02T21:12:27+00:00 [haddock @ 2004-08-02 21:12:25 by panne] Use pathJoin instead of low-level list-based manipulation for FilePaths - - - - - c711d61e by Sven Panne at 2004-08-02T21:16:02+00:00 [haddock @ 2004-08-02 21:16:02 by panne] Removed WinDoze CRs - - - - - b1f7dc88 by Sven Panne at 2004-08-03T19:35:59+00:00 [haddock @ 2004-08-03 19:35:59 by panne] Fixed spelling of "http-equiv" attribute - - - - - dd5f394e by Sven Panne at 2004-08-03T19:44:03+00:00 [haddock @ 2004-08-03 19:44:03 by panne] Pacify W3C validator: * Added document encoding (currently UTF-8, not sure if this is completely correct) * Fixed syntax of `id' attributes * Added necessary `alt' attribute for +/- images Small layout improvement: * Added space after +/- images (still not perfect, but better than before) - - - - - 919c47c6 by Sigbjorn Finne at 2004-08-03T19:45:11+00:00 [haddock @ 2004-08-03 19:45:11 by sof] make it compile with <= ghc-6.1 - - - - - 4d6f01d8 by Sigbjorn Finne at 2004-08-03T19:45:30+00:00 [haddock @ 2004-08-03 19:45:30 by sof] ffi wibble - - - - - 4770643a by Sven Panne at 2004-08-03T20:47:46+00:00 [haddock @ 2004-08-03 20:47:46 by panne] Fixed CSS for button style. Note that only "0" is a valid measure without a unit! - - - - - 14aaf2e5 by Sven Panne at 2004-08-03T21:07:59+00:00 [haddock @ 2004-08-03 21:07:58 by panne] Improved spacing of dynamic module tree - - - - - 97c3579a by Simon Marlow at 2004-08-09T11:03:04+00:00 [haddock @ 2004-08-09 11:03:04 by simonmar] Add FormatVersion Patch submitted by: George Russell <ger at informatik.uni-bremen.de> - - - - - af7f8c03 by Simon Marlow at 2004-08-09T11:55:07+00:00 [haddock @ 2004-08-09 11:55:05 by simonmar] Add support for a short description for each module, which is included in the contents. The short description should be given in a "Description: " field of the header. Included in this patch are changes that make the format of the header a little more flexible. From the comments: -- all fields in the header are optional and have the form -- -- [spaces1][field name][spaces] ":" -- [text]"\n" ([spaces2][space][text]"\n" | [spaces]"\n")* -- where each [spaces2] should have [spaces1] as a prefix. -- -- Thus for the key "Description", -- -- > Description : this is a -- > rather long -- > -- > description -- > -- > The module comment starts here -- -- the value will be "this is a .. description" and the rest will begin -- at "The module comment". The header fields must be in the following order: Module, Description, Copyright, License, Maintainer, Stability, Portability. Patches submitted by: George Russell <ger at informatik.uni-bremen.de>, with a few small changes be me, mostly to merge with other recent changes. ToDo: document the module header. - - - - - 7b865ad3 by Simon Marlow at 2004-08-10T14:09:57+00:00 [haddock @ 2004-08-10 14:09:57 by simonmar] Fixes for DevHelp/HtmlHelp following introduction of short module description. - - - - - 814766cd by Simon Marlow at 2004-08-10T14:33:46+00:00 [haddock @ 2004-08-10 14:33:45 by simonmar] Fixes to installation under Windows. - - - - - 39cf9ede by Simon Marlow at 2004-08-12T12:08:23+00:00 [haddock @ 2004-08-12 12:08:23 by simonmar] Avoid using string-gap tricks. - - - - - b6d78551 by Simon Marlow at 2004-08-13T10:53:21+00:00 [haddock @ 2004-08-13 10:53:21 by simonmar] Update - - - - - eaae7417 by Simon Marlow at 2004-08-13T10:53:50+00:00 [haddock @ 2004-08-13 10:53:50 by simonmar] Test for primes in quoted links - - - - - 68c34f06 by Sven Panne at 2004-08-16T19:59:38+00:00 [haddock @ 2004-08-16 19:59:36 by panne] XMLification - - - - - 7f45a6f9 by Sven Panne at 2004-08-18T16:42:54+00:00 [haddock @ 2004-08-18 16:42:54 by panne] Re-added indices + minor fixes - - - - - 8a5dd97c by Sigbjorn Finne at 2004-08-25T17:15:42+00:00 [haddock @ 2004-08-25 17:15:42 by sof] backquote HADDOCK_VERSION defn for <= ghc-6.0.x; believe this is only needed under mingw - - - - - 4b1b42ea by Sven Panne at 2004-08-26T20:08:50+00:00 [haddock @ 2004-08-26 20:08:49 by panne] SGML is dead, long live DocBook XML! Note: The BuildRequires tags in the spec files are still incomplete and the documentation about the DocBook tools needs to be updated, too. Stay tuned... - - - - - 8d52cedb by Sven Panne at 2004-08-26T21:03:19+00:00 [haddock @ 2004-08-26 21:03:19 by panne] Updated BuildRequires tags. Alas, there seems to be no real standard here, so your mileage may vary... At least the current specs should work on SuSE Linux. - - - - - e6982912 by Sigbjorn Finne at 2004-08-30T15:44:59+00:00 [haddock @ 2004-08-30 15:44:59 by sof] escape HADDOCK_VERSION double quotes on all platforms when compiling with <=6.0.x - - - - - b3fbc867 by Simon Marlow at 2004-08-31T13:09:42+00:00 [haddock @ 2004-08-31 13:09:42 by simonmar] Avoid GHC/shell versionitis and create Version.hs - - - - - c359e16a by Sven Panne at 2004-09-05T19:12:33+00:00 [haddock @ 2004-09-05 19:12:32 by panne] * HTML documentation for "foo.xml" goes into directory "foo" again, not "foo-html". This is nicer and consistent with the behaviour for building the docs from SGML. * Disabled building PostScript documentation in the spec files for now, there are some strange issues with the FO->PS conversion for some files which have to be clarified first. - - - - - c68b1eba by Sven Panne at 2004-09-24T07:04:38+00:00 [haddock @ 2004-09-24 07:04:38 by panne] Switched the default state for instances and the module hierarchy to non-collapsed. This can be reversed when we finally use cookies from JavaScript to have a more persistent state. Previously going back and forth in the documentation was simply too annoying because everything was collapsed again and therefore the documentation was not easily navigatable. - - - - - dfb32615 by Simon Marlow at 2004-09-30T08:21:29+00:00 [haddock @ 2004-09-30 08:21:29 by simonmar] Add a feature request - - - - - 45ff783c by Sven Panne at 2004-10-23T19:54:00+00:00 [haddock @ 2004-10-23 19:54:00 by panne] Improved the Cygwin/MinGW chaos a little bit. There is still confusion about host platform vs. target platform... - - - - - 5f644714 by Krasimir Angelov at 2004-10-28T16:01:51+00:00 [haddock @ 2004-10-28 16:01:51 by krasimir] update for ghc-6.3+ - - - - - 92d9753e by Sven Panne at 2004-11-01T16:39:01+00:00 [haddock @ 2004-11-01 16:39:01 by panne] Revert previous commit: It's Network.URI which should be changed, not Haddock. - - - - - 05f70f6e by Simon Marlow at 2005-01-04T16:15:51+00:00 [haddock @ 2005-01-04 16:15:51 by simonmar] parser fix: allow qualified specialids. - - - - - 47870837 by Simon Marlow at 2005-01-04T16:16:54+00:00 [haddock @ 2005-01-04 16:16:54 by simonmar] Add a test - - - - - ff11fc2c by Ross Paterson at 2005-01-10T19:18:22+00:00 [haddock @ 2005-01-10 19:18:22 by ross] Render non-ASCII characters using numeric character references, to simplify charset issues. There's a META tag saying the charset is UTF-8, but GHC outputs characters as raw bytes. Ideally we need an encoding on the input side too, primarily in comments, because source files containing non-ASCII characters aren't portable between locales. - - - - - eba2fc4e by Simon Marlow at 2005-01-11T10:44:37+00:00 [haddock @ 2005-01-11 10:44:37 by simonmar] Remove string gap - - - - - b899a381 by Ross Paterson at 2005-01-13T11:41:33+00:00 [haddock @ 2005-01-13 11:41:33 by ross] recognize SGML-style numeric character references &#ddd; or &#xhhhh; and translate them into Chars. - - - - - 106e3cf0 by Ross Paterson at 2005-01-13T14:43:41+00:00 [haddock @ 2005-01-13 14:43:41 by ross] also allow uppercase X in hexadecimal character references (like SGML) - - - - - e8f54f25 by Ross Paterson at 2005-01-13T14:44:24+00:00 [haddock @ 2005-01-13 14:44:24 by ross] Describe numeric character references. - - - - - 914ccdce by Sven Panne at 2005-01-15T18:44:48+00:00 [haddock @ 2005-01-15 18:44:45 by panne] Make Haddock compile again after the recent base package changed. The Map/Set legacy hell has been factored out, so that all modules can simply use the new non-deprecated interfaces. Probably a lot of things can be improved by a little bit of Map/Set/List algebra, this can be done later if needed. Small note: Currently the list of instances in HTML code is reversed. This will hopefully be fixed later. - - - - - 6ab20e84 by Sven Panne at 2005-01-16T12:18:26+00:00 [haddock @ 2005-01-16 12:18:26 by panne] Trim imports - - - - - efb81da9 by Sven Panne at 2005-01-16T12:58:08+00:00 [haddock @ 2005-01-16 12:58:03 by panne] Correctly handle the new order of arguments for the combining function given to fromListWith. - - - - - e27b5834 by Sven Panne at 2005-01-16T14:14:41+00:00 [haddock @ 2005-01-16 14:14:39 by panne] Data.Map.unions is left-biased. - - - - - dae3cc3e by Sven Panne at 2005-01-16T14:22:44+00:00 [haddock @ 2005-01-16 14:22:44 by panne] Added the last missing "flip" to get identical HTML output as previous versions. - - - - - 951d8408 by Sven Panne at 2005-01-16T14:37:10+00:00 [haddock @ 2005-01-16 14:37:10 by panne] Refactored Text.PrettyPrint legacy hell into a separate module. - - - - - f1c4b892 by Sven Panne at 2005-01-16T15:41:25+00:00 [haddock @ 2005-01-16 15:41:21 by panne] Cleaned up imports and dropped support for GHC < 5.03, it never worked, anyway. - - - - - 60824c6e by Simon Marlow at 2005-01-18T10:02:48+00:00 [haddock @ 2005-01-18 10:02:48 by simonmar] Add a TODO - - - - - a8c82f23 by Krasimir Angelov at 2005-01-28T23:19:39+00:00 [haddock @ 2005-01-28 23:19:39 by krasimir] import Foreign/Foreign.C are required for Windows - - - - - d8450a23 by Simon Marlow at 2005-02-02T16:23:04+00:00 [haddock @ 2005-02-02 16:23:00 by simonmar] Revamp the linking strategy in Haddock. Now name resolution is done in two phases: - first resolve everything to original names, like a Haskell compiler would. - then, figure out the "home" location for every entity, and point all the links to there. The home location is the lowest non-hidden module in the import hierarchy that documents the entity. If there are multiple candidates, one is chosen at random. Also: - Haddock should not generate any HTML with dangling links any more. Unlinked references are just rendered as plain text. - Error reporting is better: if we can't find a link destination for an entity reference, we now emit a warning. - - - - - 1cce71d0 by Simon Marlow at 2005-02-03T13:42:19+00:00 [haddock @ 2005-02-03 13:42:19 by simonmar] - add --ignore-all-exports flag, which behaves as if every module has the ignore-exports attribute (requested by Chris Ryder). - add --hide option to hide a module on the command line. - add --use-package option to get Haddock info for a package from ghc-pkg (largely untested). - remove reexports from the .haddock file, they aren't used any more. - - - - - 767123ef by Ross Paterson at 2005-02-03T16:17:37+00:00 [haddock @ 2005-02-03 16:17:37 by ross] fix typo for < 6.3 - - - - - 0c680c04 by Simon Marlow at 2005-02-04T12:03:31+00:00 [haddock @ 2005-02-04 12:03:31 by simonmar] Fix bug in renameExportItems that meant links in instances weren't being renamed properly. - - - - - ff7abe5f by Simon Marlow at 2005-02-04T12:15:53+00:00 [haddock @ 2005-02-04 12:15:52 by simonmar] Add attribute #not-home, to indicate that the current module should not be considered to be a home module for the each entity it exports, unless there is no other module that exports the entity. - - - - - fc2cfd27 by Simon Marlow at 2005-02-04T12:40:02+00:00 [haddock @ 2005-02-04 12:40:02 by simonmar] Update the documentation w.r.t. home modules and the not-home attribute. - - - - - 26b8ddf7 by Ross Paterson at 2005-02-04T13:36:06+00:00 [haddock @ 2005-02-04 13:36:05 by ross] sort lists of instances by - arity of the type constructors (so higher-kinded instances come first) - name of the class - argument types - - - - - 26bfb19c by Simon Marlow at 2005-02-23T15:57:12+00:00 [haddock @ 2005-02-23 15:57:12 by simonmar] Fix documentation regarding the module attributes. - - - - - 9c3afd02 by Simon Marlow at 2005-02-28T16:18:17+00:00 [haddock @ 2005-02-28 16:18:17 by simonmar] version 0.7 - - - - - a95fd63f by Simon Marlow at 2005-02-28T16:22:08+00:00 [haddock @ 2005-02-28 16:22:08 by simonmar] Attempt to fix the layout of the package names in the contents. Having tried just about everything, the only thing I can get to work reliably is to make the package names line up on a fixed offset from the left margin. This obviously isn't ideal, so anyone else that would like to have a go at improving it is welcome. One option is to remove the +/- buttons from the contents list and go back to a plain table. The contents page now uses CSS for layout rather than tables. It seems that most browsers have different interpretations of CSS layout, so only the simplest things lead to consistent results. - - - - - 905d42f7 by Simon Marlow at 2005-03-01T17:16:42+00:00 [haddock @ 2005-03-01 17:16:40 by simonmar] Another attempt at lining up the package names on the contents page. Now, they line up with Konqueror, and almost line up with Firefox & IE (different layout in each case). - - - - - a0e1d178 by Wolfgang Thaller at 2005-03-09T08:28:39+00:00 [haddock @ 2005-03-09 08:28:39 by wolfgang] Hack haddock's lexer to accept the output from Apple's broken version of cpp (Apple's cpp leaves #pragma set_debug_pwd directives in it's output). - - - - - 9e1eb784 by Simon Marlow at 2005-04-22T14:27:15+00:00 [haddock @ 2005-04-22 14:27:15 by simonmar] Add a TODO item - - - - - 23281f78 by Ross Paterson at 2005-05-18T12:41:59+00:00 [haddock @ 2005-05-18 12:41:59 by ross] fix 3 bugs in --use-package, and document it. - - - - - 00074a68 by Sven Panne at 2005-05-21T12:35:29+00:00 [haddock @ 2005-05-21 12:35:29 by panne] Warning/versionitis police - - - - - 341fa822 by Simon Marlow at 2005-06-15T15:43:21+00:00 [haddock @ 2005-06-15 15:43:21 by simonmar] Allow "licence" as an alternate spelling of "license" - - - - - 3b953f8b by Simon Marlow at 2005-06-16T08:14:12+00:00 [haddock @ 2005-06-16 08:14:12 by simonmar] wibble - - - - - abfd9826 by Simon Marlow at 2005-06-27T14:46:40+00:00 [haddock @ 2005-06-27 14:46:40 by simonmar] name hierarchical HTML files as A-B-C.html instead of A.B.C.html. The old way confused Apache because the extensions are sometimes interpreted as having special meanings. - - - - - a01eea00 by Simon Marlow at 2005-08-04T13:59:40+00:00 [haddock @ 2005-08-04 13:59:40 by simonmar] 0.7 changes - - - - - 170ef87e by Simon Marlow at 2005-08-04T15:08:03+00:00 [haddock @ 2005-08-04 15:08:03 by simonmar] spec file from Jens Peterson - - - - - 7621fde4 by Simon Marlow at 2005-08-04T15:59:30+00:00 [haddock @ 2005-08-04 15:59:30 by simonmar] replace mingw tests with $(Windows) - - - - - a20739bb by Sven Panne at 2005-08-05T07:01:12+00:00 [haddock @ 2005-08-05 07:01:12 by panne] Reverted to previous version (but with bumped version number), the last commit broke RPM building on SuSE systems due to differently named dependencies. As a clarification: All .spec files in the repository have to work at least on SuSE, because that's the system I'm using. And as "Mr. Building Police", I reserve me the right to keep them that way... >:-) It might very well be the case that we need different .spec files for different platforms, so packagers which are unhappy with the current .spec files should contact me, stating the actual problems. - - - - - 4afb15cf by Simon Marlow at 2005-10-05T10:51:45+00:00 [haddock @ 2005-10-05 10:51:45 by simonmar] Add a bug - - - - - 60f69f82 by Simon Marlow at 2005-10-05T12:52:03+00:00 [haddock @ 2005-10-05 12:52:03 by simonmar] Document new behaviour of -s option - - - - - f7e520ca by Simon Marlow at 2005-10-10T15:02:55+00:00 [haddock @ 2005-10-10 15:02:55 by simonmar] extractRecSel: ignore non-record constructors (fixes a crash when using datatypes with a mixture of record and non-record style constructors). - - - - - b2edbedb by Simon Marlow at 2005-10-14T09:44:21+00:00 Start CHANGES for 0.8 - - - - - 21c7ac8d by Simon Marlow at 2005-10-14T23:11:19+00:00 First cut of Cabal build system - - - - - 766cecdd by Simon Marlow at 2005-10-29T08:14:43+00:00 Add configure script and Makefile for the docs Add a separate configure script and build system for building the documentation. The configure and Makefile code is stolen from fptools. This is left as a separate build system so that the main Cabal setup doesn't require a Unix build environment or DocBook XML tools. - - - - - aa36c783 by Duncan Coutts at 2006-01-17T19:29:55+00:00 Add a --wiki=URL flag to add a per-module link to a correspondng wiki page. So each html page gets an extra link (placed next to the source code and contents links) to a corresponding wiki page. The idea is to let readers contribute their own notes, examples etc to the documentation. Also slightly tidy up the code for the --source option. - - - - - e06e2da2 by Simon Marlow at 2006-01-18T09:28:15+00:00 TODO: documnet --wiki - - - - - 17adfda9 by Duncan Coutts at 2006-01-19T20:17:59+00:00 Add an optional wiki link for each top level exported name. In each module, for each "top level" exported entity we add a hyper link to a corresponding wiki page. The link url gets the name of the exported entity as a '#'-style anchor, so if there is an anchor in the page with that name then the users browser should jump directly to it. By "top level" we mean functions, classes, class members and data types (data, type, newtype), but not data constructors, class instances or data type class membership. The link is added at the right of the page and in a small font. Hopefully this is the right balance of visibility/distraction. We also include a link to the wiki base url in the contents and index pages. - - - - - f52324bb by Duncan Coutts at 2006-01-19T20:28:27+00:00 Rewrite pathJoin to only add a path separator when necessary. When the path ends in a file seperator there is no need to add another. Now using "--wiki=http://blah.com/foo/" should do the right thing. (Code snippet adapted from Isaac's FilePath package.) - - - - - 43bb89fa by Duncan Coutts at 2006-01-21T17:15:27+00:00 Teach haddock about line pragmas and add accurate source code links Teach haddock about C and Haskell style line pragmas. Extend the lexer/parser's source location tracking to include the file name as well as line/column. This way each AST item that is tagged with a SrcLoc gets the original file name too. Use this original file name to add source links to each exported item, in the same visual style as the wiki links. Note that the per-export source links are to the defining module rather than whichever module haddock pretends it is exported from. This is what we want for source code links. The source code link URL can also contain the name of the export so one could implement jumping to the actual location of the function in the file if it were linked to an html version of the source rather than just plain text. The name can be selected with the %N wild card. So for linking to the raw source code one might use: --source=http://darcs/haskell.org/foo/%F Or for linking to html syntax highlighted code: --source=http://darcs/haskell.org/foo/%M.html#%N - - - - - edd9f229 by Duncan Coutts at 2006-01-22T00:02:00+00:00 Extend URL variable expansion syntax and add source links to the contents page Like the wiki link on the contents and index page, add a source code link too. Extend the wiki & source URL variable expansion syntax. The original syntax was: %F for the source file name (the .hs version only, not the .lhs or .hs.pp one) %M for the module name (with '.' replaced by '/') The new syntax is: %F or %{FILE} for the original source file name %M or %{MODULE} for the module name (no replacements) %N or %{NAME} for the function/type export name %K or %{KIND} for a type/value flag "t" or "v" with these extensions: %{MODULE/./c} to replace the '.' module seperator with any other char c %{VAR|some text with the % char in it} which means if the VAR is not in use in this URL context then "" else replace the given text with the '%' char replaced by the string value of the VAR. This extension allows us to construct URLs wit optional parts, since the module/file name is not available for the URL in the contents/index pages and the value/type name is not available for the URL at the top level of each module. - - - - - eb3c6ada by Duncan Coutts at 2006-01-23T13:42:34+00:00 Remove the complex substitutions and add more command line flags instead. Instead of incomprehensable URL substitutions like ${MODULE/./-|?m=%} we now use three seperate command line flags for the top level, per-module and per-entity source and wiki links. They are: --source-base, --source-module, --source-entity --comments-base, --comments-module, --comments-entity We leave -s, --source as an alias for --source-module which is how that option behaved previously. The long forms of the substitutions are still available, ${FILE} ${MODULE} etc and the only non-trivial substitution is ${MODULE/./c} to replace the '.' characters in the module name with any other character c. eg ${MODULE/./-} Seperating the source and wiki url flags has the added bonus that they can be turned on or off individually. So users can have per-module links for example without having to also have per-entity links.` - - - - - a2f0f2af by Duncan Coutts at 2006-01-23T13:54:52+00:00 Make the --help output fit in 80 columns. This is a purely cosmetic patch, feel free to ignore it. The only trickery going on is that we don't display the deprecated -s, --source flags in the help message, but we do still accept them. - - - - - 2d3a4b0c by Duncan Coutts at 2006-01-23T14:12:16+00:00 Add documentation for the new --source-* and --comments-* command line options - - - - - 1a82a297 by Simon Marlow at 2006-01-23T17:03:27+00:00 fix markup - - - - - 100d464a by Duncan Coutts at 2006-01-23T18:31:13+00:00 remove a couple TODO items that have been done The --wiki, or rather the --comment-* options are now documented. There is probably no need to have haddock invoke unlit or cpp itself since it can now pick up the line pragmas to get the source locations right. Tools like Cabal will arrange for preprocessors to be run so there is less of a need for tools like haddock to do it themselves. - - - - - 3162fa91 by Simon Marlow at 2006-01-24T14:21:56+00:00 add a test I had lying around - - - - - 98947063 by Simon Marlow at 2006-01-31T13:52:54+00:00 add scabal-version field - - - - - c41876e6 by Neil Mitchell at 2006-02-26T17:48:21+00:00 Add Hoogle output option - - - - - f86fb9c0 by Simon Marlow at 2006-03-08T09:15:20+00:00 add haskell.vim Contributed by Brad Bowman <bsb at bereft.net>, thanks! - - - - - 35d3c511 by benjamin.franksen at 2006-03-03T22:39:54+00:00 fixed libdir (/html was missing) - - - - - 4d08fd7d by Simon Marlow at 2006-03-10T11:13:31+00:00 add PatternGuards extension - - - - - 3f095e70 by Simon Marlow at 2006-03-13T11:40:42+00:00 bug fixes from Brad Bowman - - - - - 8610849d by Sven Panne at 2006-03-19T17:02:56+00:00 Fixed Cabal/RPM build - - - - - 34a994d6 by sven.panne at 2006-04-20T12:39:23+00:00 Avoid pattern guards Due to the use of pattern guards in Haddock, GHC was called with -fglasgow-exts. This in turn enables bang patterns, too, which broke the Haddock build. Removing some unnecessary pattern guards seemed to be the better way of fixing this instead of using a pragma to disable pattern guards. - - - - - bb523f51 by Ross Paterson at 2006-04-24T09:03:25+00:00 extend 'deriving' heuristic a little If an argument of a data constructor has a type variable head, it is irreducible and the same type class can be copied into the constraint. (Formerly we just did this for type variable arguments.) - - - - - dab9fe7a by Simon Marlow at 2006-04-26T10:02:31+00:00 record an idea - - - - - 748b7078 by Simon Marlow at 2006-05-08T08:28:53+00:00 add section about deriving - - - - - 11252ea1 by Simon Marlow at 2006-05-24T15:43:10+00:00 replace a fatal error in lexChar with a parseError - - - - - 382c9411 by Simon Marlow at 2006-05-24T15:45:47+00:00 add a bug - - - - - b79272f5 by Simon Marlow at 2006-05-24T15:46:29+00:00 add a bug report - - - - - 912edf65 by David Waern at 2006-07-10T19:09:23+00:00 Initial modifications -- doesn't compile - - - - - a3c7ba99 by David Waern at 2006-07-11T00:54:19+00:00 More porting work -- doesn't compile - - - - - 0a173d19 by David Waern at 2006-07-11T11:30:03+00:00 Make the repos temporarily compile and illustrate a problem - - - - - bad316de by David Waern at 2006-07-11T15:43:47+00:00 Progress on the porting process - - - - - bbf12d02 by David Waern at 2006-07-11T23:07:44+00:00 More progress on the porting -- first pass starting to shape up - - - - - de580ba2 by David Waern at 2006-07-20T17:48:30+00:00 More progress -- still on phase1 - - - - - 75a917a2 by David Waern at 2006-07-23T18:22:43+00:00 More work on pass1 -- mostly done - - - - - 6697b3f7 by David Waern at 2006-07-23T22:17:40+00:00 More work, started working on the renaming phase -- this code will need a cleanup soon :) - - - - - 82a5bcbb by David Waern at 2006-07-29T16:16:43+00:00 Add instances, build renaming environment, start on the renamer - - - - - c3f8f4f1 by David Waern at 2006-07-29T21:37:48+00:00 Complete the renamer - - - - - 7e00d464 by David Waern at 2006-07-30T21:01:57+00:00 Start porting the Html renderer - - - - - f04ce121 by David Waern at 2006-08-09T20:04:56+00:00 More Html rendering progress - - - - - 20c21b53 by David Waern at 2006-08-10T17:37:47+00:00 More progress - - - - - d7097e0d by David Waern at 2006-08-11T20:31:51+00:00 Cleanup - - - - - a7351e86 by David Waern at 2006-08-12T11:44:47+00:00 Render H98 Data declarations - - - - - 3fb2208e by David Waern at 2006-08-12T17:15:34+00:00 Perfect rendering of Test.hs - - - - - 454fd062 by David Waern at 2006-08-13T21:57:08+00:00 Misc fixes and interface load/save - - - - - 7ef7e7be by David Waern at 2006-08-14T00:56:07+00:00 Some refactoring - - - - - a7d3efef by David Waern at 2006-08-19T20:07:55+00:00 Adapt to latest GHC - - - - - 5fc3c0d7 by David Waern at 2006-08-20T21:28:11+00:00 Move interface read/write to its own module + some cleanup - - - - - 037e011c by David Waern at 2006-08-20T21:38:24+00:00 Small cleanup - - - - - da3a1023 by David Waern at 2006-09-03T16:05:22+00:00 Change mode to BatchCompile to avoid GHC API bug - - - - - 3cc9be3b by David Waern at 2006-09-03T16:06:59+00:00 Starting work on GADT rendering - - - - - 94506037 by David Waern at 2006-09-03T20:02:48+00:00 Compensate for change of export list order in GHC - - - - - c2cec4eb by David Waern at 2006-09-04T20:53:01+00:00 Rename a function - - - - - 9a9735ba by David Waern at 2006-09-05T15:51:21+00:00 Change version number to 2.0 - - - - - 3758a714 by David Waern at 2006-09-05T15:51:49+00:00 Align comment properly - - - - - 68478d9e by David Waern at 2006-09-15T18:03:00+00:00 Remove interface reading/writing code and use the GHC api for creating package environments instead - - - - - d2eedd95 by David Waern at 2006-09-15T18:05:29+00:00 Change the executable name to haddock-ghc-nolib - - - - - fcfbcf66 by David Waern at 2006-09-15T18:05:45+00:00 Small source code cleanup - - - - - d08eb017 by David Waern at 2006-09-15T18:06:21+00:00 Remove handling of --package flag - - - - - b8a4cf53 by David Waern at 2006-09-15T18:07:16+00:00 Remove commented-out code - - - - - bef0a684 by David Waern at 2006-09-15T18:37:57+00:00 Don't warn about missing links to () - - - - - e7d25fd7 by David Waern at 2006-09-15T19:50:49+00:00 Remove Interface and Binary2 modules - - - - - 9894f2a1 by David Waern at 2006-09-15T19:53:43+00:00 Remove debug printing from HaddockHtml - - - - - a0e7455d by David Waern at 2006-09-16T00:16:29+00:00 Comments only - - - - - d5b26fa7 by David Waern at 2006-09-16T00:16:57+00:00 Refactor PackageData creation code and start on building the doc env propery (unfinished) - - - - - 06aaa779 by David Waern at 2006-09-16T00:19:25+00:00 Better comments in Main.hs - - - - - 1a52d1b4 by David Waern at 2006-09-18T22:17:11+00:00 Comments and spacing change - - - - - e5a97767 by David Waern at 2006-09-21T17:02:45+00:00 Remove unnecessary fmapM import in Main - - - - - 9d0f9d3a by David Waern at 2006-09-22T18:07:07+00:00 Make import list in HaddockHtml prettier - - - - - 3452f662 by David Waern at 2006-09-22T18:08:47+00:00 Refactor context rendering - - - - - 12d0a6d0 by David Waern at 2006-09-22T18:09:52+00:00 Do proper HsType rendering (inser parentheses correctly) - - - - - 2c20c2f9 by David Waern at 2006-09-22T18:10:45+00:00 Fix a bug in Main.toHsType - - - - - c5396443 by David Waern at 2006-09-22T18:11:16+00:00 Skip external package modules sort for now - - - - - 3fb95547 by David Waern at 2006-09-22T20:35:40+00:00 Take away trailin "2" on all previously clashing type names - - - - - 2174755f by David Waern at 2006-09-22T20:51:43+00:00 Remove unused imports in Main - - - - - 1e9f7a39 by David Waern at 2006-09-22T20:52:11+00:00 Fix a comment in Main - - - - - 32d9e028 by David Waern at 2006-10-05T16:40:11+00:00 Merge with changes to ghc HEAD - - - - - 3058c8f5 by David Waern at 2006-10-05T16:41:02+00:00 Comment fixes - - - - - b9c217ec by David Waern at 2006-10-05T16:49:59+00:00 Filter out more builtin type constructors from warning messages - - - - - 67e7d252 by David Waern at 2006-10-05T19:38:22+00:00 Refactoring -- better structured pass1 - - - - - cd21c0c1 by David Waern at 2006-10-05T19:44:42+00:00 Remove read/dump interface flags - - - - - 313f9e69 by David Waern at 2006-10-05T19:49:26+00:00 Remove unused pretty printing - - - - - 480f09d1 by David Waern at 2006-12-28T13:22:24+00:00 Update to build with latest GHC HEAD - - - - - 63dccfcb by David Waern at 2007-01-05T01:38:45+00:00 Fixed a bug so that --ghc-flag works correctly - - - - - 3117dadc by David Waern at 2006-12-29T18:53:39+00:00 Automatically get the GHC lib dir - - - - - 9dc84a5c by David Waern at 2006-12-29T19:58:53+00:00 Comments - - - - - 0b0237cc by David Waern at 2007-01-05T16:48:30+00:00 Collect docs based on SrcLoc, syncing with removal of DeclEntity from GHC - - - - - a962c256 by David Waern at 2007-01-05T17:02:47+00:00 Add tabs in haddock.cabal - - - - - 0ca30c97 by David Waern at 2007-01-05T17:04:11+00:00 Add GHCUtils.hs - - - - - c0ab9abe by David Waern at 2007-01-10T11:43:08+00:00 Change package name to haddock-ghc, version 0.1 - - - - - 38e18b27 by David Waern at 2007-01-12T12:03:52+00:00 No binder name for foreign exports - - - - - d18587ab by David Waern at 2007-01-12T12:08:15+00:00 Temp record - - - - - ba6251a0 by David Waern at 2007-01-12T18:27:55+00:00 Remove read/dump-interface (again) - - - - - f4ba2b39 by David Waern at 2007-01-12T18:31:36+00:00 Remove DocOption, use the GHC type - - - - - 511be8bd by David Waern at 2007-01-12T18:32:41+00:00 Use exceptions instead of Either when loading package info - - - - - 0f2144d8 by David Waern at 2007-01-12T18:33:23+00:00 Small type change - - - - - 77507eb7 by David Waern at 2007-01-12T18:33:59+00:00 Remove interface file read/write - - - - - 0ea1e14f by David Waern at 2007-01-17T21:40:26+00:00 Add trace_ppr to GHCUtils - - - - - 3878b493 by David Waern at 2007-01-17T21:40:53+00:00 Sort external package modules and build a doc env - - - - - 8dc323fc by David Waern at 2007-01-17T21:42:41+00:00 Remove comment - - - - - f4c5b097 by David Waern at 2007-01-18T23:22:18+00:00 Add haddock-ghc.cabal and remove ghc option pragma in source file - - - - - da242b2c by David Waern at 2007-01-18T23:22:46+00:00 Remove some tabs - - - - - 288ed096 by David Waern at 2007-01-18T23:39:28+00:00 Moved the defaultErrorHandler to scope only over sortAndCheckModules for now - - - - - 4dd150fe by David Waern at 2007-02-03T21:23:56+00:00 Let restrictCons handle infix constructors - - - - - 97893442 by David Waern at 2007-02-04T16:26:00+00:00 Render infix data constructors - - - - - da89db72 by David Waern at 2007-02-04T16:26:33+00:00 CHange project name to Haddock-GHC - - - - - e93d48af by David Waern at 2007-02-04T16:59:08+00:00 Render infix type constructors properly - - - - - 357bc99b by David Waern at 2007-02-04T17:37:08+00:00 Insert spaces around infix function names - - - - - ab6cfc49 by David Waern at 2007-02-04T17:59:54+00:00 Do not list entities without documentation - - - - - 04249c7e by David Waern at 2007-02-04T19:16:25+00:00 Add GADT support (quite untested) - - - - - 2c223f8d by David Waern at 2007-02-04T19:25:10+00:00 Add package file write/save again! - - - - - b07ed218 by David Waern at 2007-02-04T19:33:02+00:00 Comment out minf_iface based stuff - - - - - 953d1fa7 by David Waern at 2007-02-05T00:12:23+00:00 Solve conflicts - - - - - 593247fc by David Waern at 2007-02-06T19:48:48+00:00 Remove -package flag, GHC's can be used instead - - - - - f658ded2 by David Waern at 2007-02-06T20:50:44+00:00 Start for support of ATs - - - - - 97f9e913 by David Waern at 2007-02-06T20:52:27+00:00 Wibble - - - - - 2ce8e4cf by David Waern at 2007-02-16T12:09:49+00:00 Add the DocOptions change - - - - - dee4a9b5 by David Waern at 2007-03-06T01:24:48+00:00 Wibble - - - - - 7cb99d18 by David Waern at 2007-03-06T01:24:58+00:00 Change version to 2.0 and executable name to haddock - - - - - c5aa02bc by David Waern at 2007-03-08T15:59:49+00:00 Go back to -B flag - - - - - 3a349201 by David Waern at 2007-03-09T13:31:59+00:00 Better exception handling and parsing of GHC flags - - - - - 05a69b71 by David Waern at 2007-03-09T17:45:44+00:00 Remove commented-out DocEntity printing - - - - - 755032cb by davve at dtek.chalmers.se at 2007-03-23T23:30:20+00:00 Remove a file that shouldn't be here - - - - - a7077e5f by davve at dtek.chalmers.se at 2007-03-24T03:58:48+00:00 Remove an import - - - - - 6f55aa8b by davve at dtek.chalmers.se at 2007-03-25T00:46:48+00:00 Start work on Haddock API - - - - - f0199480 by davve at dtek.chalmers.se at 2007-03-25T00:56:36+00:00 Prettify some comments - - - - - f952f9d1 by davve at dtek.chalmers.se at 2007-03-25T00:56:53+00:00 Remove ppr in HaddockTypes - - - - - bc594904 by davve at dtek.chalmers.se at 2007-03-25T00:57:53+00:00 Remove commented out doc env inference - - - - - 11ebf08d by davve at dtek.chalmers.se at 2007-03-25T01:23:25+00:00 De-flatten the namespace - - - - - f696b4bc by davve at dtek.chalmers.se at 2007-03-25T03:21:48+00:00 Add missing stuff to API - - - - - 9a2a04c3 by davve at dtek.chalmers.se at 2007-03-25T03:22:02+00:00 Wibble - - - - - 7d04a6d5 by davve at dtek.chalmers.se at 2007-03-25T03:22:08+00:00 Avoid a GHC bug with parseStaticFlags [] - - - - - 4d2820ba by davve at dtek.chalmers.se at 2007-03-26T04:57:01+00:00 Add fall-through case to mkExportItem - - - - - 6ebc8950 by Stefan O'Rear at 2007-03-26T04:14:53+00:00 Add shebang line to Setup.lhs - - - - - 80966ec5 by davve at dtek.chalmers.se at 2007-03-26T05:24:26+00:00 Fix stupid compile error - - - - - 1ea1385d by davve at dtek.chalmers.se at 2007-04-05T17:19:56+00:00 Do save/read of interface files properly - - - - - 0e4f6541 by David Waern at 2007-04-10T21:08:36+00:00 Add version to ghc dependency - - - - - b0499b63 by David Waern at 2007-04-10T21:37:08+00:00 Change package name to haddock - - - - - 9d50d27e by David Waern at 2007-04-24T00:22:14+00:00 Use filepath package instead of FilePath - - - - - 87c7fcdf by David Waern at 2007-07-10T21:03:04+00:00 Add new package dependencies - - - - - 4768709c by David Waern at 2007-07-11T20:37:11+00:00 Follow changes to record constructor representation - - - - - b9a02fee by Simon Marlow at 2007-05-30T14:00:48+00:00 update to compile with the latest GHC & Cabal - - - - - c0ebdc01 by David Waern at 2007-07-11T21:35:45+00:00 Fix conflicts - - - - - 97f7afd4 by David Waern at 2007-07-11T21:52:38+00:00 Follow changes to the GHC API - - - - - a5b7b58f by David Waern at 2007-07-12T20:36:48+00:00 Call parseStaticFlags before newSession - - - - - f7f50dbc by David Waern at 2007-08-01T21:52:58+00:00 Better indentation in haddock.cabal - - - - - d84e52ad by David Waern at 2007-08-02T00:08:18+00:00 Wibble - - - - - a23f494a by David Waern at 2007-08-02T00:08:24+00:00 Be better at trying to load all module dependencies (debugging) - - - - - ee917f13 by David Waern at 2007-08-03T18:48:08+00:00 Load all targets explicitly (checkModule doesn't chase dependencies anymore) - - - - - 5182d631 by David Waern at 2007-08-16T16:48:55+00:00 Finalize support for links to other packages - - - - - dfd1e3da by David Waern at 2007-08-16T16:51:11+00:00 Fix haddock comment errors in Haddock.Types - - - - - 50c0d83e by David Waern at 2007-08-16T16:51:37+00:00 Remove a debug import - - - - - d84b7c2b by David Waern at 2007-08-16T17:06:30+00:00 Rename PackageData to HaddockPackage - - - - - 3b52cb9f by David Waern at 2007-08-16T17:09:42+00:00 Simplify some comments - - - - - 66fa68d9 by David Waern at 2007-08-16T17:11:38+00:00 Comment the HaddockPackage definition - - - - - 8674c761 by David Waern at 2007-08-16T17:25:54+00:00 Improve code layout in Main - - - - - 571a3a0b by David Waern at 2007-08-16T17:32:13+00:00 Remove explict module imports in Main - - - - - d31b3cb0 by David Waern at 2007-08-16T17:36:23+00:00 Correct comments - - - - - 7f8a9f2b by David Waern at 2007-08-16T17:39:50+00:00 Fix layout problems in Haddock.Types - - - - - 9f421d7f by David Waern at 2007-08-17T11:16:48+00:00 Move options out of Main into Haddock.Options - - - - - 80042b63 by David Waern at 2007-08-17T11:26:59+00:00 Small comment/layout fixes - - - - - b141b982 by David Waern at 2007-08-17T11:28:28+00:00 Change project name from Haddock-GHC to Haddock - - - - - dbeb4a81 by David Waern at 2007-08-17T11:41:05+00:00 Add top module comment to all files - - - - - ce99cc9e by David Waern at 2007-08-17T14:53:04+00:00 Factor out typechecking phase into Haddock.Typecheck - - - - - 6bf75d9e by David Waern at 2007-08-17T16:55:35+00:00 Factor out package code to Haddock.Packages - - - - - b396db37 by David Waern at 2007-08-29T22:40:23+00:00 Major refactoring - - - - - 3d4f95ee by David Waern at 2007-08-29T23:26:24+00:00 Rename HaddockModule to Interface and a few more refactorings - - - - - c55326db by David Waern at 2007-08-29T23:48:03+00:00 Some comment cleanup - - - - - 9a84fc46 by David Waern at 2007-08-29T23:49:29+00:00 Add some modules that I forgot to add earlier - - - - - 4536dce2 by David Waern at 2007-08-29T23:55:24+00:00 Wibble - - - - - 9b7f0206 by David Waern at 2007-08-30T16:03:29+00:00 Wibble - - - - - c52c050a by David Waern at 2007-08-30T16:30:37+00:00 Rename HaddockModule to Interface - - - - - eae2995f by David Waern at 2007-08-30T16:42:59+00:00 Simplify createInterfaces - - - - - 53f99caa by David Waern at 2007-09-29T00:04:31+00:00 Add build-type: Simple to the cabal file - - - - - 0d3103a8 by David Waern at 2007-09-29T00:04:58+00:00 Add containers and array dependency - - - - - 6acf5f30 by David Waern at 2007-09-29T00:13:36+00:00 Prettify the cabal file - - - - - 87c1e378 by David Waern at 2007-09-29T13:16:39+00:00 FIX: consym data headers with more than two variables - - - - - b67fc16a by David Waern at 2007-09-29T14:01:32+00:00 FIX: prefix types used as operators should be quoted - - - - - a8f925bc by David Waern at 2007-09-29T14:02:26+00:00 Use isSymOcc from OccName instead of isConSym - - - - - fc330701 by David Waern at 2007-09-29T14:15:37+00:00 Use isLexConSym/isLexVarSym from OccName - - - - - e4f3dbad by David Waern at 2007-09-29T15:01:08+00:00 FIX: do not quote varsym type operators - - - - - 402207d2 by David Waern at 2007-09-29T15:01:50+00:00 Wibble - - - - - f9d89ef0 by David Waern at 2007-09-29T15:17:40+00:00 Take care when pp tyvars - add parens on syms - - - - - 849e2a77 by David Waern at 2007-10-01T21:56:39+00:00 Go back to using a ModuleMap instead of LookupMod - fixes a bug - - - - - 549dbac6 by David Waern at 2007-10-02T01:05:19+00:00 Improve parsing of doc options - - - - - a36021b8 by David Waern at 2007-10-02T23:05:00+00:00 FIX: double arrows in constructor contexts - - - - - d03bf347 by David Waern at 2007-10-09T16:14:05+00:00 Add a simple test suite - - - - - c252c140 by David Waern at 2007-10-17T16:02:28+00:00 Add --optghc=.. style flag passing to GHC - - - - - cce6c1b3 by David Waern at 2007-10-18T22:03:20+00:00 Add support for --read-interface again - - - - - 33d059c0 by David Waern at 2007-10-18T22:30:18+00:00 Refactoring -- get rid of Haddock.Packages - - - - - f9ed0a4c by David Waern at 2007-10-18T22:34:36+00:00 Name changes - - - - - 8a1c816f by David Waern at 2007-10-20T14:24:23+00:00 Add --ghc-version option - - - - - 4925aaa1 by David Waern at 2007-10-21T14:34:26+00:00 Add some Outputable utils - - - - - 69e7e47f by David Waern at 2007-10-21T14:35:49+00:00 FIX: Ord for OrdName was not comparing modules - - - - - 5a4ae535 by David Waern at 2007-10-21T21:18:48+00:00 Wibble - - - - - 03d48e20 by David Waern at 2007-10-24T15:52:56+00:00 Remove Main from "other modules" - - - - - c66f6d82 by David Waern at 2007-10-24T16:37:18+00:00 Make it possible to run haddock on itself - - - - - 21d156d8 by David Waern at 2007-10-25T14:02:14+00:00 Don't set boot modules as targets - - - - - f8bcf91c by David Waern at 2007-10-31T22:11:17+00:00 Add optimisation flags - - - - - 7ac758f2 by David Waern at 2007-11-04T09:48:28+00:00 Go back to loading only targets (seems to work now) - - - - - 4862aae1 by David Waern at 2007-11-05T22:24:57+00:00 Do full compilation of modules -- temporary fix for GHC API problem - - - - - 697e1517 by David Waern at 2007-11-05T22:25:50+00:00 Don't warn about not being able to link to wired/system/builtin-names - - - - - 892186da by David Waern at 2007-11-06T00:49:21+00:00 Filter out instances with TyCons that are not exported - - - - - 9548314c by David Waern at 2007-11-06T09:37:14+00:00 Wibble - - - - - 5cafd627 by David Waern at 2007-11-08T01:43:07+00:00 Filter out all non-vanilla type sigs - - - - - 04621830 by David Waern at 2007-11-08T01:45:13+00:00 Synch loading of names from .haddock files with GHC's name cache - - - - - 88d37f77 by David Waern at 2007-11-08T01:46:21+00:00 Remove commented-out code - - - - - 6409c911 by David Waern at 2007-11-08T01:56:00+00:00 Small bugfix and cleanup in getDeclFromTyCls - - - - - af59d9c2 by David Waern at 2007-11-08T02:08:44+00:00 Remove OrdName stuff - - - - - 3a615e2e by David Waern at 2007-11-08T02:13:41+00:00 Update runtests.hs following changes to haddock - - - - - 01f3314e by David Waern at 2007-11-08T02:33:01+00:00 Complain if we can't link to wired-in names - - - - - fcafb5d1 by David Waern at 2007-11-09T02:40:16+00:00 Don't exit when there are no file arguments - - - - - 194bc332 by David Waern at 2007-11-09T02:55:37+00:00 Wibble - - - - - dbe4cb55 by David Waern at 2007-11-09T02:56:14+00:00 Wibble - - - - - 82869fda by David Waern at 2007-11-10T17:01:43+00:00 Introduce InstalledInterface structure and add more stuff to the .haddock files We introduce InstalledInterface capturing the part of Interface that is stored in the interface files. We change the ppHtmlContents and ppHtmllIndex to take this structure instead of a partial Interface. We add stuff like the doc map and exported names to the .haddock file (via InstalledInterface). - - - - - d6bb57bf by David Waern at 2007-11-10T17:19:48+00:00 FIX: contents and index should include external package modules when --gen-contents/--gen-index - - - - - e8814716 by David Waern at 2007-11-11T00:29:27+00:00 Remove lDocLinkName and its use in Html backend - - - - - 6f9bd702 by David Waern at 2007-11-11T00:50:57+00:00 Do some refactoring in the html backend This also merges an old patch by Augustsson: Wed Jul 12 19:54:36 CEST 2006 lennart.augustsson at credit-suisse.com * Print type definitions like signatures if given arrows. - - - - - 09d0ce24 by Malcolm.Wallace at 2006-07-20T13:13:57+00:00 mention HsColour in the docs, next to option flags for linking to source code - - - - - 24da6c34 by Malcolm.Wallace at 2006-07-20T13:14:50+00:00 change doc references to CVS to give darcs repository location instead - - - - - 74d52cd6 by David Waern at 2007-11-11T00:55:33+00:00 Update copyright - - - - - fcaa3b4f by Duncan Coutts at 2006-09-08T13:41:00+00:00 Eliminate dep on network by doing a little cut'n'paste haddock depending on the network causes a circular dependency at least if you want to build the network lib with haddock docs. - - - - - 10cc9bda by David Waern at 2007-11-11T02:09:41+00:00 Fix conflicts - - - - - 4e3acd39 by David Waern at 2007-11-11T02:21:19+00:00 Manual merge of a patch from Duncan Coutts that removes the dependency on mtl - - - - - fa9070da by Neil Mitchell at 2006-09-29T15:52:03+00:00 Do not generate an empty table if there are no exports, this fixes a <table></table> tag being generated, which is not valid HTML 4.01 - - - - - d7431c85 by David Waern at 2007-11-11T02:28:50+00:00 Fix conflicts - - - - - f87e8f98 by Simon Marlow at 2006-10-10T11:37:16+00:00 changes for 0.8 - - - - - db929565 by Simon Marlow at 2006-10-10T12:07:12+00:00 fix the name of the source file - - - - - 8220aa4b by Simon Marlow at 2006-10-11T14:17:37+00:00 Rename haddock.js to haddock-util.js haddock.js will be run automatically by Windows when you type 'haddock' if it is found on the PATH, so rename to avoid confusion. Spotted by Adrian Hey. - - - - - 6bccdaa1 by sven.panne at 2006-10-12T15:28:23+00:00 Cabal's sdist does not generate "-src.tar.gz" files, but ".tar.gz" ones - - - - - d3f3fc19 by Simon Marlow at 2006-12-06T16:05:07+00:00 add todo item for --maintainer - - - - - 2da7e269 by Simon Marlow at 2006-12-15T15:52:00+00:00 TODO: do something better about re-exported symbols from another package - - - - - 42d85549 by David Waern at 2007-11-11T02:30:59+00:00 Fix conflicts - - - - - 5e7ef6e5 by Neil Mitchell at 2007-01-11T15:41:15+00:00 Never do spliting index files into many - - - - - f3d4aebe by Neil Mitchell at 2007-01-11T17:07:09+00:00 Add searching on the index page - - - - - bad3ab66 by Neil Mitchell at 2007-01-11T18:17:46+00:00 Delete dead code, now there is only one index page - - - - - cd09eedb by Neil Mitchell at 2007-01-11T18:21:19+00:00 Delete more stuff that is no longer required - - - - - e2806646 by David Waern at 2007-11-11T02:41:53+00:00 Fix conflicts - - - - - a872a823 by Neil Mitchell at 2007-01-11T18:51:43+00:00 Make the index be in case-insensitive alphabetic order - - - - - 8bddd9d7 by Neil Mitchell at 2007-02-06T17:49:12+00:00 Do not create empty tables for data declarations which don't have any constructors, instances or comments. Gets better HTML 4.01 compliance - - - - - 036b8120 by David Waern at 2007-11-11T02:56:58+00:00 Fix conflicts - - - - - f50c1639 by Conal Elliott at 2007-02-14T21:54:00+00:00 added substitution %{FILE///c} - - - - - 402e166a by David Waern at 2007-11-11T03:35:46+00:00 Manual merge of old patch: Sat Apr 21 04:36:43 CEST 2007 Roberto Zunino <zunrob at users.sf.net> * URL expansion for %%, %L, %{LINE} - - - - - 2f264fbd by David Waern at 2007-11-11T03:40:33+00:00 Manual merge of an old patch: Thu Apr 19 20:23:40 CEST 2007 Wolfgang Jeltsch <g9ks157k at acme.softbase.org> * bug fix When Haddock was invoked with the --ignore-all-exports flag but the ignore-exports module attribute wasn't used, hyperlinks weren't created for non-exported names. This fix might not be as clean as one would wish (since --ignore-all-exports now results in ignore_all_exports = True *and* an additional OptIgnoreExports option for every module) but at least the bug seems to be resolved now. - - - - - 7d7ae106 by sven.panne at 2007-09-02T12:18:02+00:00 Install LICENSE in the correct place - - - - - 66eaa924 by David Waern at 2007-11-11T19:02:46+00:00 Fix a bug that made haddock loop - - - - - 4ed47b58 by David Waern at 2007-11-11T19:03:09+00:00 Rename java-script file (this wasn't merge correctly) - - - - - d569534a by David Waern at 2007-11-11T19:06:44+00:00 Don't require -B <ghc-libdir> when no argument files Change readInterfaceFile to take a Maybe Session, to avoid having to pass -B <ghc-libdir> to Haddock when there're no source files to process. This is nice when computing contents/index for external packages. - - - - - 373368bc by Neil Mitchell at 2007-01-11T18:22:44+00:00 Change from tabs to spaces in the ppHtmlIndex function - - - - - 6b063a77 by Neil Mitchell at 2007-01-12T12:17:46+00:00 Rewrite much of the index searching code, previously was too slow to execute on the base library with IE, the new version guarantees less than O(log n) operations be performed, where n is the number in the list (before was always O(n)) - - - - - bfad00b7 by David Waern at 2007-11-11T23:33:53+00:00 Fix conflicts - - - - - cd2dcc09 by Neil Mitchell at 2007-01-12T12:25:01+00:00 Make the max number of results 75 instead of 50, to allow map searching in the base library to work - - - - - 3ae74764 by Neil Mitchell at 2007-01-12T12:58:17+00:00 Make the search box in a form so that enter does the default search - - - - - 142103e5 by David Waern at 2007-11-12T00:03:18+00:00 Merge patch from the old branch: Fri Aug 31 13:21:45 CEST 2007 Duncan Coutts <duncan at haskell.org> * Add category: Development to .cabal file Otherwise it appears on the hackage website in the "Unclassified" category. - - - - - 22ec2ddb by David Waern at 2007-11-25T01:55:29+00:00 A a list of small improvements to the TODO file - - - - - eb0129f4 by Wolfgang Jeltsch at 2007-12-03T23:47:55+00:00 addition of type equality support (at least for HTML generation) - - - - - 816a7e22 by David Waern at 2007-12-08T15:46:26+00:00 Handle class operators correctly when rendering predicates - - - - - 68baaad2 by David Waern at 2007-12-08T16:15:54+00:00 Code layout changes - - - - - 09b77fb4 by David Waern at 2007-12-08T16:16:03+00:00 Handle infix operators correctly in the Type -> HsType translation - - - - - 31c36da2 by David Waern at 2007-12-08T16:24:27+00:00 Add ppLParendTypes/ppLParendType - - - - - b17cc818 by David Waern at 2007-12-08T16:26:12+00:00 Use ppParendType when printing types args in predicates - - - - - ffd1f2cf by David Waern at 2007-12-08T16:45:06+00:00 Fix rendering of instance heads to handle infix operators This is also a refactoring to share this code for rendering predicates. - - - - - ff886d45 by David Waern at 2007-12-08T17:27:46+00:00 Fix rendering of class operators - - - - - e2fcbb9e by David Waern at 2007-12-08T17:59:28+00:00 Fix a bug (use ppTyName instead of ppName to print names in type apps) - - - - - 79a1056e by David Waern at 2007-12-08T21:25:18+00:00 Update tests - - - - - 867741ac by David Waern at 2007-12-08T21:25:49+00:00 Give a diff on test failure - - - - - 7e5eb274 by David Waern at 2008-01-05T14:33:45+00:00 Add DrIFT commands - - - - - 3656454d by David Waern at 2008-01-05T20:26:00+00:00 Add "cabal-version: >= 1.2" to the cabal file - - - - - 77974efc by Simon Marlow at 2007-12-20T09:52:44+00:00 add an item - - - - - f6ac1708 by Simon Marlow at 2007-12-06T14:00:10+00:00 Source links must point to the original module, not the referring module - - - - - eda1d5c9 by David Waern at 2008-01-06T14:40:52+00:00 Manual merge of a patch to the 0.8 branch Thu Dec 6 15:00:10 CET 2007 Simon Marlow <simonmar at microsoft.com> * Source links must point to the original module, not the referring module - - - - - 378f4085 by David Waern at 2008-01-06T16:03:45+00:00 Change stability from stable to experimental - - - - - 8bdafe44 by David Waern at 2008-01-06T16:14:22+00:00 Add haskell.vim (it had been removed somehow) - - - - - ea34d02e by David Waern at 2008-01-06T16:36:57+00:00 Change version to 2.0.0.0 - - - - - 34631ac0 by David Waern at 2008-01-06T16:44:57+00:00 Add missing modules to the cabal file - - - - - 9e142935 by David Waern at 2008-01-06T17:25:42+00:00 Depend on ghc >= 6.8.2 && < 6.9 - - - - - 59f9eeaa by Simon Marlow at 2007-12-20T10:43:04+00:00 add build scripts - - - - - 1c29ae30 by Simon Marlow at 2007-12-20T10:47:07+00:00 update version number - - - - - fe16a3e4 by Simon Marlow at 2007-12-20T10:48:03+00:00 update version - - - - - f688530f by Simon Marlow at 2007-12-20T10:48:29+00:00 doc updates - - - - - ce71b611 by David Waern at 2008-01-07T13:46:32+00:00 Change version in docs and spec - - - - - 03ab8d6f by David Waern at 2008-01-07T13:47:38+00:00 Manually merge over changes to CHANGES for 0.9 - - - - - 39f1b042 by David Waern at 2008-01-07T15:17:41+00:00 Remove the -use-package flag, we don't support it anyway - - - - - 7274a544 by David Waern at 2008-01-07T15:33:05+00:00 Update CHANGES for 2.0.0.0 - - - - - 96594f5d by David Waern at 2008-01-07T15:46:49+00:00 Wibble - - - - - f4c5a4c4 by David Waern at 2008-01-07T15:55:36+00:00 Change url to repo in documentation - - - - - 8a4c77f0 by David Waern at 2008-01-07T16:00:54+00:00 Update CHANGES - - - - - cb3a9288 by David Waern at 2008-01-07T16:02:55+00:00 Documentation fix - - - - - d8e45539 by David Waern at 2008-01-07T16:12:00+00:00 Update docs to say that Haddock accets .lhs files and module names - - - - - 4b5ce824 by David Waern at 2008-01-07T16:12:25+00:00 Document -B option - - - - - 47274262 by David Waern at 2008-01-07T16:23:07+00:00 Update CHANGES - - - - - 7ff314a9 by David Waern at 2008-01-07T16:23:20+00:00 Remove --use-package, --package & --no-implicit.. flags from docs - - - - - 6c3819c0 by David Waern at 2008-01-07T16:23:52+00:00 Remove --no-implicit-prelide flag - - - - - 1b14ae40 by David Waern at 2008-01-07T16:32:26+00:00 Update the "Using literate or pre-processed source" section - - - - - 0117f620 by David Waern at 2008-01-07T16:41:55+00:00 Document the --optghc flag - - - - - 087ab1cf by David Waern at 2008-01-07T16:42:10+00:00 Remove the documenation section on derived instances The problem mentioned there doesn't exist in Haddock 2.0.0.0 - - - - - 7253951e by David Waern at 2008-01-07T16:48:40+00:00 Document OPTIONS_HADDOCK - - - - - 3b6bdcf6 by David Waern at 2008-01-07T16:56:54+00:00 Wibble - - - - - 3025adf9 by David Waern at 2008-01-07T17:08:14+00:00 Wibble - - - - - 5f30f1a0 by David Waern at 2008-01-07T17:15:44+00:00 Change synopsis field to description - - - - - 1673f54b by David Waern at 2008-01-07T17:18:21+00:00 Change my email address in the cabal file - - - - - 55aa9808 by David Waern at 2008-01-07T18:18:02+00:00 Add documentation for readInterfaceFile - - - - - eaea417f by David Waern at 2008-01-07T18:21:30+00:00 Export necessary stuff from Distribution.Haddock - - - - - 7ea18759 by David Waern at 2008-01-07T18:31:49+00:00 Remove dep on Cabal - - - - - 7b79c74e by David Waern at 2008-01-07T18:33:49+00:00 Remove dep on process - - - - - ce3054e6 by David Waern at 2008-01-16T23:01:21+00:00 Add feature-requsts from Henning Thielemann to TODO - - - - - 0c08f1ec by David Waern at 2008-01-16T23:03:02+00:00 Record a bug in TODO - - - - - b04605f3 by David Waern at 2008-01-23T16:59:06+00:00 Add a bug reported by Ross to TODO - - - - - 5b17c030 by David Waern at 2008-01-23T18:05:53+00:00 A a bug report to TODO - - - - - 1c993b0d by David Waern at 2008-01-25T16:30:25+00:00 Accept test output - - - - - c22fc0d0 by David Waern at 2008-01-25T16:34:49+00:00 Accept test output - - - - - 4b795811 by David Waern at 2008-01-25T16:38:37+00:00 Change Hidden.hs (test) to use OPTIONS_HADDOCK - - - - - c124dbd9 by David Waern at 2008-01-25T16:39:23+00:00 Accept test output - - - - - ec6f6eea by David Waern at 2008-01-25T16:42:08+00:00 Add Hidden.html.ref to tests - - - - - 1dc9610c by David Waern at 2008-02-02T20:50:51+00:00 Add a comment about UNPACK bug in TODO - - - - - 2d3f7081 by David Waern at 2008-02-09T22:33:24+00:00 Change the representation of DocNames Ross Paterson reported a bug where links would point to the defining module instead of the "best" module for an identifier (e.g Int pointing to GHC.Base instead of Data.Int). This patch fixes this problem by refactoring the way renamed names are represented. Instead of representing them by: > data DocName = Link Name | NoLink Name they are now represented as such: > data DocName = Documented Name Module | Undocumented Name and the the link-env looks like this: > type LinkEnv = Map Name Module There are several reasons for this. First of all, the bug was caused by changing the module part of Names during the renaming process, without changing the Unique field. This caused names to be overwritten during the loading of .haddock files (which caches names using the NameCache of the GHC session). So we might create new Uniques during renaming to fix this (but I'm not sure that would be problem-free). Instead, we just keep the Name and add the Module where the name is best documented, since it can be useful to keep the original Name around (for e.g. source-code location info and for users of the Haddock API). Also, the names Link/NoLink don't really make sense, since wether to use links or not is entirely up to the users of DocName. In the process of following this change into H.Backends.Html I removed the assumption that binder names are Undocumented (which was just an unnecessary assumption, the OccName is the only thing needed to render these). This will probably make it possible to get rid of the renamer and replace it with a traversal from SYB or Uniplate. Since DocName has changed, InterfaceFile has changed so this patch also increments the file-format version. No backwards-compatibility is implemented. - - - - - 0f28c921 by David Waern at 2008-02-09T23:00:36+00:00 H.GHC.Utils: remove unused imports/exports - - - - - 0c44cad5 by David Waern at 2008-02-10T00:28:13+00:00 H.GHC.Utils: add some functions that were removed by mistake - - - - - e3452f49 by David Waern at 2008-02-10T00:28:48+00:00 Fix some trivial warnings in H.InterfaceFile - - - - - a6d74644 by David Waern at 2008-02-10T00:48:06+00:00 Update the version message to fit in small terminals - - - - - 76c9cd3e by David Waern at 2008-02-10T14:47:39+00:00 Remove bugs from TODO that don't apply anymore since the port - - - - - 5e10e090 by David Waern at 2008-02-10T15:22:47+00:00 Remove bugs from TODO that weren't actual bugs - - - - - fef70878 by David Waern at 2008-02-10T15:23:44+00:00 Remove yet another item from TODO that was not an actual bug - - - - - e1af47b8 by David Waern at 2008-02-11T10:25:57+00:00 Bump the version number to 2.1.0 Since the exported datatype DocName has changed, we need to bump the major version number. Let's also drop the fourth version component, it's not that useful. - - - - - e3be7825 by David Waern at 2008-04-11T14:29:04+00:00 Add a bug to TODO - - - - - cb6574be by David Waern at 2008-04-11T16:00:45+00:00 Use the in-place haddock when running tests - - - - - c6d7af0d by David Waern at 2008-04-11T16:09:16+00:00 Turn off GHC warnings when running tests - - - - - 7f61b546 by David Waern at 2008-04-11T17:24:00+00:00 Add a flag for turning off all warnings - - - - - 883b8422 by David Waern at 2008-04-12T14:02:18+00:00 Fix printing of data binders - - - - - 2a0db8fc by David Waern at 2008-04-12T18:52:46+00:00 Fix missing parenthesis in constructor args bug - - - - - 1b3ac3f9 by David Waern at 2008-04-12T18:57:23+00:00 Simplify test suite and add tests I move all tests into one single directory to simplify things, and add a test for the last bug that was fixed. - - - - - 8f178376 by David Waern at 2008-04-12T19:00:15+00:00 Add a script for copying test output to "expected" output - - - - - 193e3a03 by David Waern at 2008-04-12T19:16:37+00:00 Remove two fixed bugs from TODO - - - - - ddc9130c by David Waern at 2008-04-12T19:37:06+00:00 Update test README - - - - - 956069c0 by David Waern at 2008-05-01T12:16:14+00:00 Update version number in spec and docs - - - - - 5478621c by David Waern at 2008-05-01T12:28:12+00:00 Remove claim of backwards compatibility from docs for readInterfaceFile - - - - - 4a16dea9 by David Waern at 2008-05-01T12:33:04+00:00 Update CHANGES - - - - - 804216fb by David Waern at 2008-05-01T12:43:16+00:00 Add a synopsis - - - - - fd0c84d5 by David Waern at 2008-05-01T12:44:44+00:00 Add Haddock.DocName to the cabal file - - - - - 9f4a7439 by David Waern at 2008-05-01T12:45:53+00:00 Remove -fglasgow-exts and -fasm - - - - - aee7c145 by David Waern at 2008-05-01T12:54:01+00:00 Add LANGUAGE pragmas to source files - - - - - 9a58428b by David Waern at 2008-05-01T12:54:19+00:00 Add extensions to cabal file - - - - - 494f1bee by David Waern at 2008-05-01T13:12:09+00:00 Export DocName in the API - - - - - c938196b by David Waern at 2008-05-01T13:12:19+00:00 Add hide options to some source files - - - - - 236e86af by Neil Mitchell at 2008-06-07T20:45:10+00:00 Rewrite the --hoogle flag support - - - - - 6d910950 by Neil Mitchell at 2008-06-14T10:56:50+00:00 Simplify the newtype/data outputting in Hoogle, as haddock does it automatically - - - - - f87a95a8 by Neil Mitchell at 2008-06-14T12:10:18+00:00 Add initial structure for outputting documentation as well, but does not yet output anything - - - - - 7c3bce54 by Neil Mitchell at 2008-06-14T12:27:07+00:00 Remove <document comment> from the Hoogle output - - - - - 9504a325 by Neil Mitchell at 2008-06-16T06:33:21+00:00 Default to "main" if there is no package, otherwise will clobber hoogle's hoogle info - - - - - 4a794a79 by Neil Mitchell at 2008-06-16T06:53:29+00:00 Change packageName to packageStr, as it better reflects the information stored in it - - - - - 7abc9baf by Neil Mitchell at 2008-06-16T07:09:49+00:00 Add modulePkgInfo to Haddock.GHC.Utils, which gives back package name and version info - - - - - 8ca11514 by Neil Mitchell at 2008-06-16T07:13:48+00:00 Change Hoogle to take the package name and package version separately - - - - - a6da452d by Neil Mitchell at 2008-06-18T11:29:46+00:00 In Hoogle do not list things that are not local to this module - - - - - 974b76b7 by David Waern at 2008-06-19T18:40:13+00:00 Be more consistent with GHC API naming in H.GHC.Utils - - - - - 2facb4eb by David Waern at 2008-06-19T19:03:03+00:00 Update test output - - - - - c501de72 by David Waern at 2008-06-26T20:26:49+00:00 Use ghc-paths to get the lib dir The path can still be overridden using the -B flag. It's not longer required to pass the lib dir to the program that runs the test suite. - - - - - ac4c6836 by David Waern at 2008-06-26T20:33:08+00:00 Update CHANGES - - - - - 9d21c60a by David Waern at 2008-06-26T20:34:53+00:00 Update README - - - - - 741448f0 by David Waern at 2008-06-26T21:12:57+00:00 Improve wording in the help message - - - - - b1b42b11 by David Waern at 2008-06-30T10:16:17+00:00 Rename ForeignType - - - - - 6d6c2b34 by David Waern at 2008-06-30T10:25:09+00:00 Rename TyFamily - - - - - 8d1125ed by David Waern at 2008-06-30T10:37:21+00:00 Rename type patterns - - - - - 7610a4cb by David Waern at 2008-06-30T10:45:07+00:00 Rename associated types - - - - - 8eeba14c by David Waern at 2008-06-30T10:47:41+00:00 Remove the TODO file now that we have a trac - - - - - 1af5b25b by David Waern at 2008-07-02T18:19:28+00:00 Render type family declarations (untested) - - - - - ceb99797 by David Waern at 2008-07-02T18:24:06+00:00 Remove redundant check for summary when rendering data types - - - - - b36a58e0 by David Waern at 2008-07-02T22:01:38+00:00 More support for type families and associated types Now we just need to render the instances - - - - - 78784879 by David Waern at 2008-07-07T22:13:58+00:00 Remove filtering of instances We were filtering out all instances for types with unknown names. This was probably an attempt to filter out instances for internal types. I am removing the filtering for the moment, and will try to fix this properly later. - - - - - 3e758dad by David Waern at 2008-06-30T18:50:30+00:00 Run haddock in-place during testing - - - - - d9dab0ce by David Waern at 2008-07-08T21:04:32+00:00 Remove index.html and doc-index.html from output, they should not be versioned - - - - - 3e6c4681 by David Waern at 2008-07-08T21:06:42+00:00 Update test output following change to instance filtering - - - - - e34a3f14 by David Waern at 2008-07-12T16:48:28+00:00 Stop using the map from exported names to declarations During creation of the interface, we were using two maps: one from exported names to declarations, and one from all defined names in the module to declarations. The first contained subordinate names while the second one didn't. The first map was never used to look up names not defined in the associated module, so if we add subordinate names to the second map, we could use it everywhere. That's that this patch does. This simplifies code because we don't have to pass around two maps everywhere. We now store the map from locally defined things in the interface structure instead of the one from exported names. - - - - - 2e1d2766 by David Waern at 2008-07-12T16:55:21+00:00 Get the all locally defined names from GHC API We previously had some code to compute all locally defined names in a module including subordinate names. We don't need it since we can get the names from modInfoTyThings in the GHC API. - - - - - bf637994 by David Waern at 2008-07-13T13:09:16+00:00 Refactoring in H.Interface.Create We were creating a doc map, a declaration map and a list of entities separately by going through the HsGroup. These structures were all used to build the interface of a module. Instead of doing this, we can start by creating a list of declarations from the HsGroup, then collect the docs directly from this list (instead of using the list of entities), creating a documentation map. We no longer need the Entity data type, and we can store a single map from names to declarations and docs in the interface, instead of the declaration map and the doc map. This way, there is only one place where we filter out the declarations that we don't want, and we can remove a lot of code. Another advantage of this is that we can create the exports directly out of the list of declarations when we export the full module contents. (Previously we did a look up for each name to find the declarations). This is faster and removes another point where we depend on names to identify exported declarations, which is good because it eliminates problems with instances (which don't have names). - - - - - 547e410e by David Waern at 2008-07-13T13:34:51+00:00 Remove FastString import and FSLIT macro in H.I.Create -- they were unused - - - - - 693759d1 by David Waern at 2008-07-13T13:36:23+00:00 Remove unused import from H.I.Create - - - - - cde6e7fb by David Waern at 2008-07-13T13:51:54+00:00 Small touches - - - - - 96de8f1d by David Waern at 2008-07-20T11:21:46+00:00 Preparation for rendering instances as separate declarations We want to be able to render instances as separate declarations. So we remove the Name argument of ExportDecl, since instances are nameless. This patch also contains the first steps needed to gather type family instances and display them in the backend, but the implementation is far from complete. Because of this, we don't actually show the instances yet. - - - - - b0f824fb by David Waern at 2008-07-20T15:53:08+00:00 Follow changes to ExportDecl in Hoogle - - - - - 1192eff3 by Neil Mitchell at 2008-06-26T00:28:10+00:00 Change how the Hoogle backend outputs classes, adding the context in - - - - - 7a0d1464 by Neil Mitchell at 2008-06-26T00:28:46+00:00 Remove the indent utility function from Hoogle backend - - - - - 3361241b by Neil Mitchell at 2008-06-26T09:45:09+00:00 Add support for Hoogle writing ForeignImport/ForeignExport properly - - - - - 795ad3bf by Neil Mitchell at 2008-06-26T12:15:25+00:00 Flesh out the Hoogle code to render documentation - - - - - 23277995 by Neil Mitchell at 2008-06-26T14:56:41+00:00 Fix a bug in the Hoogle backend, unordered lists were being written out <ul>...</u> - - - - - db739b27 by Neil Mitchell at 2008-06-26T15:09:54+00:00 Remove any white space around a <li> element - - - - - f2e6bb8c by Neil Mitchell at 2008-07-10T15:30:47+00:00 Remove the TODO in the Hoogle HTML generation, was already done - - - - - 693ec9a3 by Neil Mitchell at 2008-07-10T15:53:00+00:00 Put brackets round operators in more places in the Hoogle output - - - - - 842313aa by Neil Mitchell at 2008-07-10T16:01:25+00:00 Print type signatures with brackets around the name - - - - - cf93deb0 by David Waern at 2008-07-20T17:04:22+00:00 Bump version number to 2.2.0 - - - - - 30e6a8d1 by David Waern at 2008-07-20T17:04:41+00:00 Resolve conflicts in H.B.Hoogle - - - - - 1f0071c9 by David Waern at 2008-07-23T23:05:01+00:00 Add "all" command to runtests.hs that runs all tests despite failures - - - - - f2723023 by David Waern at 2008-07-23T23:08:39+00:00 Update tests/README - - - - - c0304a11 by David Waern at 2008-07-23T23:21:15+00:00 Be compatible with GHC 6.8.3 The cabal file is converted to use the "new" syntax with explicit Library and Executable sections. We define the __GHC_PATCHLEVEL__ symbol using a conditinal cpp-options field in the cabal file. (Ideally, Cabal would define the symbol for us, like it does for __GLASGOW_HASKELL__). We use these symbols to #ifdef around a small difference between 6.8.2 and 6.8.3. Previously, we only supported GHC 6.8.2 officially but the dependencies field said "ghc <= 6.9". This was just for convenience when testing against the (then compatible) HEAD version of GHC, and was left in the release by mistake. Now, we support both GHC 6.8.2 and 6.8.3 and the dependencies field correctly reflects this. - - - - - 88a5fe71 by David Waern at 2008-07-23T23:54:16+00:00 Depend on the currently available ghc-paths versions only - - - - - 8738d97b by David Waern at 2008-07-24T10:50:44+00:00 FIX haskell/haddock#44: Propagate parenthesis level when printing documented types - - - - - 05339119 by David Waern at 2008-07-24T16:06:18+00:00 Drop unnecessary parenthesis in types, put in by the user We were putting in parenthesis were the user did. Let's remove this since it just clutters up the types. The types are readable anyway since we print parens around infix operators and do not rely on fixity levels. When doing this I discovered that we were relying on user parenthesis when printin types like (a `O` b) c. This patchs fixes this problem so that parenthesis are always inserted around an infix op application in case it is applied to further arguments, or if it's an arguments to a type constructor. Tests are updated. - - - - - b3a99828 by David Waern at 2008-07-24T10:19:43+00:00 Print parenthesis around non-atomic banged types Fixes half of haskell/haddock#44 - - - - - ab5238e0 by David Waern at 2008-07-24T22:07:49+00:00 Add a reference file for the TypeFamilies test - - - - - 1941cc11 by David Waern at 2008-07-25T17:15:53+00:00 Simplify definition of pretty and trace_ppr - - - - - e3bfa33c by David Waern at 2008-07-25T17:18:27+00:00 Warning messages Output a warning when filtering out data/type instances and associated types in instances. We don't show these in the documentation yet, and we need to let the user know. - - - - - 9b85fc89 by David Waern at 2008-07-25T17:45:40+00:00 Doc: Mention Hoogle in the Introduction - - - - - afb2dd60 by David Waern at 2008-07-25T17:49:00+00:00 Doc: update -B description - - - - - 584c0c91 by David Waern at 2008-07-25T18:11:38+00:00 Doc: describe -w flag - - - - - 77619c24 by David Waern at 2008-07-28T12:29:07+00:00 Remove TODO from cabal file - - - - - 96717d5f by David Waern at 2008-07-28T12:29:27+00:00 Support type equality predicates - - - - - c2fd2330 by David Waern at 2008-07-29T19:45:14+00:00 Move unL from H.B.Hoogle to H.GHC.Utils I like Neil's shorter unL better than unLoc from the GHC API. - - - - - c4c3bf6a by David Waern at 2008-07-29T19:47:36+00:00 Do not export ATs when not in list of subitems - - - - - bf9a7b85 by David Waern at 2008-08-03T11:42:59+00:00 Filter out ForeignExports - - - - - df59fcb0 by David Waern at 2008-08-03T14:02:51+00:00 Filter out more declarations The previous refactorings in H.I.Create introduced a few bugs. Filtering of some types of declarations that we don't handle was removed. This patch fixes this. - - - - - 2f8a958b by David Waern at 2008-08-03T15:24:07+00:00 Move reL to H.GHC.Utils so we can use it everywhere - - - - - 8ec15efd by David Waern at 2008-08-03T15:25:00+00:00 Use isVanillaLSig from GHC API instead of home brewn function - - - - - 300f93a2 by David Waern at 2008-08-03T15:25:27+00:00 Filter out separately exported ATs This is a quick and dirty hack to get rid of separately exported ATs. We haven't decided how to handle them yet. No warning message is given. - - - - - 8776d1ec by David Waern at 2008-08-03T16:21:21+00:00 Filter out more declarations and keep only vanilla type sigs in classes - - - - - ea07eada by David Waern at 2008-08-03T16:48:00+00:00 Fix layout - - - - - dd5e8199 by David Waern at 2008-08-03T16:50:52+00:00 Move some utility functions from H.I.Create to H.GHC.Utils - - - - - 4a1dbd72 by David Waern at 2008-08-03T17:39:55+00:00 Do not filter out doc declarations - - - - - 0bc8dca4 by David Waern at 2008-08-03T17:47:26+00:00 Filter out separately exported ATs (take two) - - - - - af970fe8 by David Waern at 2008-08-03T22:39:17+00:00 Update CHANGES - - - - - 5436ad24 by David Waern at 2008-08-03T22:40:20+00:00 Bump version number to 2.2.1 - - - - - d66de448 by David Waern at 2008-08-05T19:00:32+00:00 Remove version restriction on ghc-paths - - - - - 534b1364 by David Waern at 2008-08-05T19:04:35+00:00 Bump version to 2.2.2 and update CHANGES - - - - - 549188ff by David Waern at 2008-08-05T19:16:49+00:00 Fix CHANGES - - - - - 0d156bb4 by Luke Plant at 2008-08-11T15:20:59+00:00 invoking haddock clarification and help - - - - - 748295cc by David Waern at 2008-08-11T18:56:37+00:00 Doc: say that the --hoogle option is functional - - - - - 43301db4 by David Waern at 2008-08-05T19:26:08+00:00 Change ghc version dependency to >= 6.8.2 - - - - - 3e5a53b6 by David Waern at 2008-08-10T22:42:05+00:00 Make H.GHC.Utils build with GHC HEAD - - - - - 7568ace0 by David Waern at 2008-08-11T19:41:54+00:00 Import Control.OldException instead of C.Exception when using ghc >= 6.9 We should really test for base version instead, but I don't currently know which version to test for. - - - - - b71ae991 by David Waern at 2008-08-12T22:40:39+00:00 Make our .haddock file version number depend on the GHC version We need to do this, since our .haddock format can potentially change whenever GHC's version changes (even when only the patchlevel changes). - - - - - 6307ce3f by David Waern at 2008-08-12T22:49:57+00:00 Remove matching on NoteTy in AttachInstances, it has been removed - - - - - 2dbcfd5f by David Waern at 2008-08-12T23:02:02+00:00 Comment out H.GHC.loadPackages - it is unused and doesn't build with ghc >= 6.9 - - - - - c74db5c2 by David Waern at 2008-08-12T23:03:58+00:00 Hide <.> from GHC import in Hoogle only for ghc <= 6.8.3 - - - - - 69a44ebb by David Waern at 2008-08-12T23:11:12+00:00 Follow changes to parseDynamic/StaticFlags - - - - - 5881f3f0 by David Waern at 2008-08-13T21:43:58+00:00 Add __GHC_PATCHLEVEL__ symbol also when building the library - - - - - 8574dc11 by David Waern at 2008-08-13T21:44:17+00:00 Follow move of package string functions from PackageConfig to Module - - - - - c9baa77f by David Waern at 2008-08-13T21:45:29+00:00 Follow extensible exceptions changes - - - - - 9092de15 by David Waern at 2008-08-13T21:46:20+00:00 Update test following Haddock version change - - - - - ebe569a4 by David Waern at 2008-08-13T21:46:54+00:00 Follow changes to parseDynamic- parseStaticFlags in GHC - - - - - b8a5ffd3 by David Waern at 2008-08-13T21:47:36+00:00 Follow changes to Binary in GHC 6.9 - - - - - edfda1cc by David Waern at 2008-08-13T21:50:17+00:00 Change ghc version dependency to >= 6.8.2 && <= 6.9 - - - - - d59be1cf by Neil Mitchell at 2008-08-12T16:02:53+00:00 Output all items, even if they are not defined in this module - ensures map comes from Prelude, not just GHC.Base - - - - - dda93b9f by Neil Mitchell at 2008-08-12T21:37:32+00:00 Add support for type synonyms to Hoogle, was accidentally missing before (woops!) - - - - - b6ee795c by Neil Mitchell at 2008-08-13T14:03:24+00:00 Generalise Hoogle.doc and add a docWith - - - - - 415e1bb2 by Neil Mitchell at 2008-08-13T14:03:46+00:00 Make Hoogle add documentation to a package - - - - - 790a1202 by Neil Mitchell at 2008-08-18T12:52:43+00:00 Use the same method to put out signatures as class methods in the Hoogle backend - - - - - ded37eba by Neil Mitchell at 2008-08-18T12:53:04+00:00 Remove Explicit top-level forall's when pretty-printing signatures - - - - - 6468c722 by Neil Mitchell at 2008-08-20T07:59:13+00:00 Simplify the code by removing not-to-important use of <.> in the Hoogle back end - - - - - 788c3a8b by Neil Mitchell at 2008-08-21T18:20:24+00:00 In the hoogle back end, markup definition lists using <i>, not <b> - - - - - 77d4b000 by Ian Lynagh at 2008-08-14T10:49:14+00:00 Add a Makefile for GHC's build system. Still won't work yet, but we're closer - - - - - 920440d7 by Ian Lynagh at 2008-08-27T18:06:46+00:00 Add haddock.wrapper - - - - - bcda925f by Ian Lynagh at 2008-08-27T18:07:02+00:00 Add a manual Cabal flag to control the ghc-paths dependency - - - - - 04d194e2 by Ian Lynagh at 2008-08-27T20:41:27+00:00 Update extensions in Cabal file Use ScopedTypeVariables instead of PatternSignatures - - - - - 12480043 by Ian Lynagh at 2008-08-27T20:41:55+00:00 Increase the upper bound on the GHC version number - - - - - b1f809a5 by Ian Lynagh at 2008-08-27T21:32:22+00:00 Fix some warnings - - - - - aea0453d by Ian Lynagh at 2008-08-28T14:22:29+00:00 Fixes for using haddock in a GHC build tree - - - - - ad23bf86 by Ian Lynagh at 2008-08-28T21:14:27+00:00 Don't use Cabal wrappers on Windows - - - - - 35858e4c by Ian Lynagh at 2008-08-29T00:07:42+00:00 Fix in-tree haddock on Windows - - - - - c2642066 by Ian Lynagh at 2008-09-03T22:35:53+00:00 follow library changes - - - - - 2eb55d50 by Ian Lynagh at 2008-09-07T18:52:51+00:00 bindist fixes - - - - - 3daa5b59 by Ian Lynagh at 2008-09-10T16:58:18+00:00 We need to tell haddock that its datasubdir is . or it can't find package.conf - - - - - 388fd8c2 by Ian Lynagh at 2008-09-10T19:47:44+00:00 Fix haddock inplace on Windows - - - - - 70a641c1 by Ian Lynagh at 2008-09-10T22:15:44+00:00 Fix installed haddock on Windows - - - - - 83c1e997 by Neil Mitchell at 2008-09-11T10:48:55+00:00 Import GHC.Paths if not IN_GHC_TREE, seems to match the use of GHC.Paths functions much better - - - - - b452519b by Ian Lynagh at 2008-09-12T12:58:24+00:00 Add a LANGUAGE ForeignFunctionInterface pragma - - - - - afbd592c by Ian Lynagh at 2008-09-12T12:59:13+00:00 Wibble imports - - - - - 547ac4ad by Ian Lynagh at 2008-09-14T15:34:22+00:00 Add a "#!/bin/sh" to haddock.wrapper - - - - - f207a807 by Ian Lynagh at 2008-09-15T10:02:32+00:00 Use "exec" when calling haddock in the wrapper - - - - - 2ee68509 by Thomas Schilling at 2008-09-15T09:09:16+00:00 Port Haddock.Interface to new GHC API. This required one bigger change: 'readInterfaceFile' used to take an optional 'Session' argument. This was used to optionally update the name cache of an existing GHC session. This does not work with the new GHC API, because an active session requires the function to return a 'GhcMonad' action, but this is not possible if no session is provided. The solution is to use an argument of functions for reading and updating the name cache and to make the function work for any monad that embeds IO, so it's result type can adapt to the calling context. While refactoring, I tried to make the code a little more self-documenting, mostly turning comments into function names. - - - - - 3bb96431 by Thomas Schilling at 2008-09-15T09:09:37+00:00 Reflect GHC API changes. - - - - - 2e60f714 by Thomas Schilling at 2008-09-15T09:10:37+00:00 Port Haddock.GHC.Typecheck to new GHC API. - - - - - 9cfd4cff by Thomas Schilling at 2008-09-15T09:11:00+00:00 Port Haddock.GHC to new GHC API. - - - - - caffa003 by Thomas Schilling at 2008-09-15T09:11:25+00:00 Port Main to new GHC API. - - - - - 069a4608 by Ian Lynagh at 2008-09-21T11:19:00+00:00 Fix paths used on Windows frmo a GHC tree: There is no whare directory - - - - - 7ceee1f7 by Ian Lynagh at 2008-09-21T12:20:16+00:00 Fix the in-tree haddock on Windows - - - - - 0d486514 by Ian Lynagh at 2008-09-23T18:06:58+00:00 Increase the GHC upper bound from 6.11 to 6.13 - - - - - f092c414 by Neil Mitchell at 2008-09-11T14:56:07+00:00 Do not wrap __ in brackets - - - - - 036bdd13 by Ian Lynagh at 2008-09-28T01:42:35+00:00 Fix building haddock when GhcProfiled=YES - - - - - 01434a89 by David Waern at 2008-09-24T20:24:21+00:00 Add PatternSignatures LANGUAGE pragma to Main and Utils - - - - - 1671a750 by David Waern at 2008-10-02T22:57:25+00:00 For source links, get original module from declaration name instead of environment. Getting it from the environment must have been a remnant from the times when we were using unqualified names (versions 0.x). - - - - - a25dde99 by David Waern at 2008-10-02T22:59:57+00:00 Remove ifaceEnv from Interface - it's no longer used - - - - - 610993da by David Waern at 2008-10-02T23:04:58+00:00 Write a comment about source links for type instance declarations - - - - - 5a96b5d5 by Thomas Schilling at 2008-10-03T10:45:08+00:00 Follow GHC API change of parseModule. - - - - - 5a943ae5 by Ian Lynagh at 2008-10-03T15:56:58+00:00 TAG 2008-10-03 - - - - - 76cdd6ae by Thomas Schilling at 2008-10-08T12:29:50+00:00 Only load modules once when typechecking with GHC. This still doesn't fix the memory leak since the typechecked source is retained and then processed separately. To fix the leak, modules must be processed directly after typechecking. - - - - - 7074d251 by David Waern at 2008-10-09T23:53:54+00:00 Interleave typechecking with interface creation At the same time, we fix a bug where the list of interfaces were processed in the wrong order, when building the links and renaming the interfaces. - - - - - 4b9b2b2d by David Waern at 2008-10-09T23:54:49+00:00 Add some strictness annotations in Interface We add some strictness annotations to the fields of Interface, so that less GHC data is hold on to during processing. - - - - - 22035628 by David Waern at 2008-10-10T20:02:31+00:00 Remove typecheckFiles and MonadUtils import from H.GHC.Typeccheck - - - - - be637ad3 by David Waern at 2008-10-10T20:33:38+00:00 Make Haddock build with GHC 6.8.2 - - - - - 523b3404 by David Waern at 2008-10-10T21:08:09+00:00 Fix documentation for createInterfaces - - - - - e1556702 by David Waern at 2008-10-10T21:26:19+00:00 Hide H.Utils in library - - - - - a8e751c3 by David Waern at 2008-10-10T21:34:59+00:00 Add back .haddock file versioning based on GHC version It was accidentally removed in the patch for GHC 6.8.2 compatibility - - - - - 06fb3c01 by David Waern at 2008-10-10T21:47:15+00:00 Bump version number to 2.3.0 - - - - - ff087fce by David Waern at 2008-10-10T22:35:49+00:00 Add support for DocPic The support for DocPic was merged into the GHC source long ago, but the support in Haddock was forgotten. Thanks Peter Gavin for submitting this fix! - - - - - 3af85bf6 by David Waern at 2008-10-10T23:34:05+00:00 Update tests - - - - - 0966873c by Simon Marlow at 2008-10-10T14:43:04+00:00 no need for handleErrMsg now, we don't throw any ErrMsgs - - - - - f1870de3 by Clemens Fruhwirth at 2008-10-10T13:29:36+00:00 Compile with wrapper but remove it for dist-install - - - - - 7b440dc2 by David Waern at 2008-10-11T14:02:25+00:00 Remove interface from LinksInfo It was there to know the documentation home module when creating a wiki link, but we already know this since we have the DocName. - - - - - e5729e6a by David Waern at 2008-10-15T20:49:18+00:00 Wibble - - - - - b2a8e01a by David Waern at 2008-10-15T21:03:36+00:00 Use type synonyms for declarations and docs in H.I.Create - - - - - be71a15b by David Waern at 2008-10-15T21:12:17+00:00 Comment out unused type family stuff completely - - - - - 91aaf075 by David Waern at 2008-10-15T21:49:04+00:00 Wibble - - - - - 42ba4eb4 by David Waern at 2008-10-15T21:53:53+00:00 Move convenient type synonym to H.Types - - - - - db11b723 by David Waern at 2008-10-15T22:14:07+00:00 Add DeclInfo to H.Types - - - - - 193552b6 by David Waern at 2008-10-15T22:15:01+00:00 Add subordinates with docs to the declaration map The only place in the code where we want the subordinates for a declaration is right after having looked up the declaration in the map. And since we include subordinates in the map, we might as well take the opportunity to store those subordinates that belong to a particular declaration together with that declaration. We also store the documentation for each subordinate. - - - - - 31e6eebc by David Waern at 2008-10-16T17:18:47+00:00 Wibble - - - - - 0dcbd79f by David Waern at 2008-10-16T20:58:42+00:00 Fix haskell/haddock#61 We were not getting docs for re-exported class methods. This was because we were looking up the docs in a map made from the declarations in the current module being rendered. Obviously, re-exported class methods come from another module. Class methods and ATs were the only thing we were looking up using the doc map, everything else we found in the ExporItems. So now I've put subordinate docs in the ExportItem's directly, to make things a bit more consistent. To do this, I added subordinates to the the declarations in the declaration map. This was easy since we were computing subordinates anyway, to store stand-alone in the map. I added a new type synonym 'DeclInfo', which is what we call what is now stored in the map. This little refactoring removes duplicate code to retrieve subordinates and documentation from the HsGroup. - - - - - de47f20a by David Waern at 2008-10-16T22:06:35+00:00 Document function and improve its layout - - - - - e74e625a by Thomas Schilling at 2008-10-20T11:12:57+00:00 Force interface more aggressively. For running Haddock on GHC this reduces memory usage by about 50 MB on a 32 bit system. A heap profile shows total memory usage peak at about 100 MB, but actual usage is at around 300 MB even with compacting GC (+RTS -c). - - - - - b63ac9a1 by David Waern at 2008-10-20T20:25:50+00:00 Make renamer consistent Instead of explicitly making some binders Undocumented, treat all names the same way (that is, try to find a Documented name). - - - - - f6de0bb0 by Ian Lynagh at 2008-09-19T00:54:43+00:00 TAG GHC 6.10 fork - - - - - 74599cd0 by David Waern at 2008-10-20T21:13:24+00:00 Do not save hidden modules in the .haddock file We were saving interfaces of all processed modules including those hidden using {-# OPTIONS_HADDOCK hide #-} in the .haddock file. This caused broken links when generating the index for the libraries that come with GHC. This patch excludes modules with hidden documentation when writing .haddock files. It should fix the above problem. - - - - - 7b6742e9 by David Waern at 2008-10-21T19:54:52+00:00 Do not save hidden modules in the .haddock file (also for ghc >= 6.9) When writing the first patch, I forgot to do the fix in both branches of an #if macro. - - - - - b99b1951 by David Waern at 2008-10-22T20:04:18+00:00 Remove subordinate map and its usage It is not needed now that we store subordinate names in the DeclInfo map. - - - - - da97cddc by David Waern at 2008-10-22T20:11:46+00:00 Tidy up code in H.I.Create a little Remove commented out half-done type instance support, and remove DeclWithDoc synonym. - - - - - 6afa76f3 by David Waern at 2008-10-22T21:17:29+00:00 Fix warnings in H.GHC.Utils - - - - - 171ea1e8 by David Waern at 2008-10-22T21:35:04+00:00 Fix warnings in H.Utils - - - - - c8cb3b91 by David Waern at 2008-10-22T21:36:49+00:00 Wibble - - - - - 767fa06a by David Waern at 2008-10-27T19:59:04+00:00 Make named doc comments into ExportDoc instead of ExportDecl Fixes a crash when processing modules without export lists containing named docs. - - - - - e638bbc6 by David Waern at 2008-11-02T22:21:10+00:00 Add HCAR entry - - - - - 92b4ffcf by David Waern at 2008-11-02T22:44:19+00:00 Update CHANGES - - - - - 84d4da6e by David Waern at 2008-11-03T11:25:04+00:00 Add failing test for template haskell crash - - - - - 2a9cd2b1 by David Waern at 2008-11-04T21:13:44+00:00 Add tests/TH.hs - - - - - 8a59348e by David Waern at 2008-11-04T21:30:26+00:00 TAG 2.3.0 - - - - - 54f70d31 by Thomas Schilling at 2008-10-24T17:04:08+00:00 Enable framed view of the HTML documentation. This patch introduces: - A page that displays the documentation in a framed view. The left side will show a full module index. Clicking a module name will show it in the right frame. If Javascript is enabled, the left side is split again to show the modules at the top and a very short synopsis for the module currently displayed on the right. - Code to generate the mini-synopsis for each module and the mini module index ("index-frames.html"). - CSS rules for the mini-synopsis. - A very small amount of javascript to update the mini-synopsis (but only if inside a frame.) Some perhaps controversial things: - Sharing code was very difficult, so there is a small amount of code duplication. - The amount of generated pages has been doubled, since every module now also gets a mini-synopsis. The overhead should not be too much, but I haven't checked. Alternatively, the mini-synopsis could also be generated using Javascript if we properly annotate the actual synopsis. - - - - - 5d7ea5a6 by David Waern at 2008-11-04T23:20:17+00:00 Follow change to ExportDecl in frames code - - - - - 60e16308 by David Waern at 2008-11-04T23:35:26+00:00 Update CHANGES - - - - - d63fd26d by David Waern at 2008-11-04T23:37:43+00:00 Bump version number - - - - - c1660c39 by David Waern at 2008-11-04T23:44:46+00:00 Update CHANGES - - - - - 995ab384 by David Waern at 2008-11-04T23:55:21+00:00 Remove .ref files from tests/output/ - - - - - 1abbbe75 by David Waern at 2008-11-04T23:57:41+00:00 Output version info before running tests - - - - - 649b182f by David Waern at 2008-11-05T22:45:37+00:00 Add ANNOUNCE message - - - - - c36ae0bb by David Waern at 2008-11-05T23:15:35+00:00 Update ANNOUNCE - - - - - 9c4f3d40 by David Waern at 2008-11-05T23:18:30+00:00 Wibble - - - - - 5aac87ce by David Waern at 2008-11-06T21:07:48+00:00 Depend on base 4.* when using GHC >= 6.9, otherwise 3.* - - - - - b9796a74 by David Waern at 2008-11-06T21:13:40+00:00 Bump version to 2.4.1 and update CHANGES - - - - - d4b26baa by David Waern at 2008-11-06T21:26:33+00:00 Depend on base 4.0.* instead of 4.* - - - - - 2cb0903c by David Waern at 2008-11-06T21:46:53+00:00 Fix warnings in H.B.HH and H.B.HH2 - - - - - e568e89a by David Waern at 2008-11-06T21:47:12+00:00 Fix warnings in Haddock.ModuleTree - - - - - 9dc14fbd by David Waern at 2008-11-06T21:47:52+00:00 Fix warnings in Haddock.Version - - - - - 02ac197c by David Waern at 2008-11-06T21:51:31+00:00 Fix warnings in H.InterfaceFile and H.Options - - - - - 63e7439a by David Waern at 2008-11-06T21:59:45+00:00 Fix warnings in H.GHC.Typecheck - - - - - 4bca5b68 by David Waern at 2008-11-08T13:43:42+00:00 Set HscTarget to HscNothing instead of HscAsm There used to be a bug in the GHC API that prevented us from setting this value. - - - - - 07357aec by David Waern at 2008-11-09T22:27:00+00:00 Re-export NameCache and friends from Distribution.Haddock - - - - - ea554b5a by David Waern at 2008-11-09T23:14:10+00:00 Add Haddock.GHC.Utils to other-modules in library - - - - - 74aecfd7 by David Waern at 2008-11-10T01:18:57+00:00 Export DocName in the library - - - - - 241a58b3 by David Waern at 2008-11-10T01:19:18+00:00 Document the functions in H.DocName - - - - - edc2ef1b by David Waern at 2008-11-10T01:20:52+00:00 Export H.DocName in the library - - - - - 4f588d55 by David Waern at 2008-11-10T01:29:14+00:00 Make DocName an instance of NamedThing - - - - - b4647244 by David Waern at 2008-11-15T22:58:18+00:00 Reflect version bump in test suite - - - - - 4bee8ce2 by David Waern at 2008-11-15T22:58:45+00:00 Update tests For unknown reasons, test output for Bug1 and Test has changed for the better. - - - - - 1690e2f9 by David Waern at 2008-11-15T22:59:33+00:00 Store hidden modules in .haddock files We store documentation for an entity in the 'InstalledInterface' of the definition site module, and never in the same structure for a module which re-exports the entity. So when a client of the Haddock library wants to look up some documentation, he/she might need to access a hidden module. But we currently don't store hidden modules in the .haddock files. So we add the hidden modules and the Haddock options to the .haddock files. The options will be used to filter the module list to obtain the visible modules only, which is necessary for generating the contents and index for installed packages. - - - - - 8add6435 by David Waern at 2008-11-16T14:35:50+00:00 Bump major version number due to .haddock file format change - - - - - 48bfcf82 by David Waern at 2008-11-23T14:32:52+00:00 Update tests to account for version number bump - - - - - 0bbd1738 by David Waern at 2008-11-23T14:33:31+00:00 HADDOCK_DATA_DIR changed to haddock_datadir - - - - - 5088b78c by David Waern at 2008-11-23T17:13:21+00:00 FIX haskell/haddock#45: generate two anchors for each name We generate two anchor tags for each name, one where we don't escape the name and one where we URI-encode it. This is for compatibility between IE and Opera. Test output is updated. - - - - - 5ee5ca3b by Neil Mitchell at 2008-11-27T14:38:11+00:00 Drop HsDocTy annotations, they mess up pretty printing and also have a bracketing bug (#2584) - - - - - 51c014e9 by Roman Cheplyaka at 2008-11-27T22:27:36+00:00 Allow referring to a specific section within a module in a module link Fixes haskell/haddock#65 - - - - - 4094bdc5 by David Waern at 2008-11-28T21:13:33+00:00 Update tests following anchor change - - - - - f89552dd by Thomas Schilling at 2008-11-29T16:16:20+00:00 Haddock really shouldn't try to overwrite files. - - - - - 98127499 by David Waern at 2008-12-07T14:09:15+00:00 Solve conflict - - - - - 319356c5 by David Waern at 2008-10-22T21:16:55+00:00 Add -Wall -Werror to ghc-options - - - - - 3c4968c9 by David Waern at 2008-11-04T23:38:56+00:00 TAG 2.4.0 - - - - - 4b21e003 by David Waern at 2008-11-06T21:14:04+00:00 TAG 2.4.1 - - - - - 8e0cad5c by David Waern at 2008-12-07T14:12:54+00:00 Remove -Werror - - - - - 299d6deb by David Waern at 2008-12-07T14:25:18+00:00 Remove -Wall, we'll focus on warnings after 6.10.2 is out - - - - - 5f4216b6 by David Waern at 2008-12-07T20:58:05+00:00 Resolve conflict properly - - - - - 67d774e7 by Neil Mitchell at 2008-12-15T11:44:26+00:00 Make forall's in constructors explicit, i.e. data Foo = Foo {foo :: Eq a => a} - - - - - 61851792 by Neil Mitchell at 2008-12-18T15:39:39+00:00 Try and find a better package name than "main" for Hoogle, goes wrong when working on an executable rather than a library - - - - - 2fab8554 by David Waern at 2008-12-08T23:19:48+00:00 Make visible names from ExportItems Instead of a complicated calculation of visible names out of GHC's export items, we can get them straight out of the already calculated ExportItems. The ExportItems should represent exactly those items that are visible in an interface. If store all the exported sub-names in ExportDecl instead of only those with documentation, the calculation becomes very simple. So we do this change as well (should perhaps have been a separate patch). This should fix the problem with names from ghc-prim not appearing in the link environment. - - - - - 7caadd8c by Ian Lynagh at 2008-12-11T17:01:04+00:00 Wrap the GHC usage with defaultCleanupHandler This fixes a bug where haddock leaves /tmp/ghc* directories uncleaned. - - - - - 7c9fc9a5 by David Waern at 2009-01-02T21:38:27+00:00 Show re-exported names from external packages again This fixes GHC ticket 2746. In order to also link to the exported subordinate names of a declaration, we need to re-introduce the sub map in the .haddock files. - - - - - 119e4e05 by David Waern at 2009-01-06T23:34:17+00:00 Do not process boot modules We should of course not try to produce documentation for boot modules! The reason this has worked in the past is that the output of "real" modules overwrites the output of boot modules later in the process. However, this causes a subtle link environment problem. So let's get rid of this stupid behaviour. We avoid processing boot modules, but we continue to typecheck them. - - - - - c285b9d2 by David Waern at 2009-01-08T18:03:36+00:00 Export modules also when coming from external packages This seems to have regressed since a refactoring that was part of the 2.3.0 release. - - - - - 24031c17 by David Waern at 2009-01-10T15:26:26+00:00 Change version to 2.4.2 - no need to go to 2.5.0 - - - - - 864d1c3f by David Waern at 2009-01-10T15:35:20+00:00 Update tests to account for version number change - - - - - 524ba886 by David Waern at 2009-01-10T18:29:17+00:00 Add test for Template Haskell splicing - - - - - 05e6e003 by David Waern at 2009-01-10T19:35:42+00:00 Fix Trac haskell/haddock#68: Turn on compilation via C for Template Haskell packages We can't use HscNothing if we need to run code coming from modules inside the processed package during typechecking, which is the case for some packages using Template Haskell. This could be improved, to e.g. use HscInterpreted and HscNothing where possible, instead of using HscC for all modules in the package. - - - - - 2b2bafa1 by David Waern at 2009-01-10T20:22:25+00:00 Only use needsTemplateHaskell when compiling with GHC 6.10.2 or above - - - - - bedc3a93 by Ian Lynagh at 2009-01-11T14:58:41+00:00 Fix the location of INPLACE_PKG_CONF; fixes the build Spotted by Conal Elliott - - - - - 943107c8 by David Waern at 2009-01-20T19:27:39+00:00 Document H.I.Create.collectDocs better - - - - - c6252e37 by David Waern at 2009-01-20T19:29:51+00:00 Fix Trac haskell/haddock#59: TH-generated declarations disappearing This patch was contributed by Joachim Breitner (nomeata). - - - - - 3568a6af by David Waern at 2009-01-21T21:41:48+00:00 Do not indicate that a constructor argument is unboxed We only show the strictness annotation for an unboxed constructor argument. The fact that it is unboxed is an implementation detail and should not be part of the module interface. - - - - - 562a4523 by David Waern at 2009-01-22T18:53:49+00:00 Fix Trac haskell/haddock#50: do not attach docs to pragmas or other kinds of non-declarations We now filter out everything that is not a proper Haskell declaration before collecting the docs and attaching them to declarations. - - - - - 6fdf21c2 by David Waern at 2009-01-22T19:48:09+00:00 Add test for quasi quotation. No reference output yet. - - - - - dc4100fd by David Waern at 2009-01-22T19:57:47+00:00 Improve quasi-quotation test and add reference output - - - - - 908b74bb by David Waern at 2009-01-23T23:22:03+00:00 Filter out separately exported associated types in a smarter way - - - - - f6b42ecb by David Waern at 2009-01-24T16:54:39+00:00 Correct spelling mistake in error message - - - - - 24e4245d by David Waern at 2009-01-24T17:48:03+00:00 Correct comment - - - - - b5e8462f by David Waern at 2009-02-07T13:22:29+00:00 Do not show a subordinate at the top level if its parent is also exported See note in the source code for more info. - - - - - 4b09de57 by David Waern at 2009-02-07T13:53:53+00:00 Update test following change to top level subordinates - - - - - 76379896 by David Waern at 2009-02-07T13:58:04+00:00 Remove html files in the tests/output/ directory which have been accidentally added - - - - - 1a6d8b10 by Joachim Breitner at 2009-02-20T10:29:43+00:00 Typo in comment - - - - - fec367d0 by David Waern at 2009-02-24T20:21:17+00:00 Fix small bug The rule is to prefer type constructors to other things when an identifier in a doc string can refer to multiple things. This stopped working with newer GHC versions (due to a tiny change in the GHC renamer). We implement this rule in the HTML backend for now, instead of fixing it in GHC, since we will move renaming of doc strings to Haddock in the future anyway. - - - - - 9b4172eb by David Waern at 2009-02-25T20:04:38+00:00 Fix bad error handling with newer GHCs When support for GHC 6.10 was added, an error handler was installed only around the typechecking phase. This had the effect that errors thrown during dependency chasing were caught in the top-level exception handler and not printed with enough detail. With this patch we wrap the error handler around all our usage of the Ghc monad. - - - - - de2df363 by Simon Peyton Jones at 2009-02-02T16:47:42+00:00 Hide funTyConName, now exported by TypeRep - - - - - 4d40a29f by Ian Lynagh at 2009-02-12T18:57:49+00:00 Don't build the library when building in the GHC tree - - - - - 1cd0abe4 by Ian Lynagh at 2009-02-13T13:58:53+00:00 Add a ghc.mk - - - - - 3d814eeb by Ian Lynagh at 2009-02-13T18:50:28+00:00 do .depend generation for haddock with the stage1 compiler This is a bit of a hack. We mkdepend with stage1 as if .depend depends on the stage2 compiler then make goes wrong: haddock's .depend gets included, which means that make won't reload until it's built, but we can't build it without the stage2 compiler. We therefore build the stage2 compiler before its .depend file is available, and so compilation fails. - - - - - b55036a4 by Ian Lynagh at 2009-02-25T01:38:13+00:00 Give haddock a wrapper on unix in the new GHC build system - - - - - 9eabfe68 by Ian Lynagh at 2009-02-25T19:21:32+00:00 Create inplace/lib/html in the new GHC build system - - - - - 93af30c7 by Ian Lynagh at 2008-11-07T19:18:23+00:00 TAG GHC 6.10.1 release - - - - - 06e6e34a by Thomas Schilling at 2009-02-24T18:11:00+00:00 Define __GHC_PATCHLEVEL__ for recent version of GHC (stable). - - - - - 680e6ed8 by Thomas Schilling at 2009-02-24T18:12:26+00:00 'needsTemplateHaskell' is not defined in current stable GHC. - - - - - 6c5619df by David Waern at 2009-02-25T22:15:23+00:00 Hide fynTyConName only for recent GHC versions - - - - - 6b2344f1 by Ian Lynagh at 2009-02-26T00:49:56+00:00 Add the module to one of haddocks warnings - - - - - e5d11c70 by David Waern at 2009-02-27T21:37:20+00:00 Bug fix We tried to filter out subordinates that were already exported through their parent. This didn't work properly since we were in some cases looking at the grand-parent and not the parent. We now properly compute all the parent-child relations of a declaration, and use this information to get the parent of a subordinate. We also didn't consider record fields with multiple parents. This is now handled correctly. We don't currently support separately exported associated types. But when we do, they should be handled correctly by this process too. Also slightly improved the warning message that we give when filtering out subordinates. - - - - - 10a79a60 by David Waern at 2009-02-27T22:08:08+00:00 Fix error message conflict The module name is already written in the beginning of the message, as seems to be the convention in Haddock. Perhaps not so clear, but we should change it everywhere in that case. Leaving it as it is for now. - - - - - c5055c7f by David Waern at 2009-02-27T22:15:17+00:00 Shorten warning message - - - - - a72fed3a by David Waern at 2009-02-28T00:53:55+00:00 Do not show package name in warning message - - - - - a5daccb2 by Ian Lynagh at 2009-03-01T14:59:35+00:00 Install haddock in the new GHC build system - - - - - dfdb025c by Ian Lynagh at 2009-03-07T23:56:29+00:00 Relax base dependency to < 4.2, not < 4.1 - - - - - 5769c8b4 by David Waern at 2009-03-21T14:58:52+00:00 Bump .haddock file version number (due to change of format) - - - - - f1b8f67b by David Waern at 2009-03-21T14:59:26+00:00 Define __GHC_PATCHLEVEL__=1 when using ghc-6.10.1 - - - - - 23f78831 by David Waern at 2009-03-21T16:40:52+00:00 Update CHANGES - - - - - 7d2735e9 by David Waern at 2009-03-21T16:50:33+00:00 Update ANNOUNCE - - - - - 0771e00a by David Waern at 2009-03-21T16:54:40+00:00 Update ANNOUNCE, again - - - - - 81a6942a by David Waern at 2009-03-21T17:50:06+00:00 Don't be too verbose in CHANGES - - - - - 29861dcf by David Waern at 2009-03-21T18:03:31+00:00 TAG 2.4.2 - - - - - a585f285 by David Waern at 2009-03-21T19:20:29+00:00 Require Cabal >= 1.2.3 - - - - - 7c611662 by David Waern at 2009-03-21T19:21:48+00:00 TAG 2.4.2 with cabal-version >= 1.2.3 - - - - - 23b7deff by Simon Marlow at 2009-03-20T15:43:42+00:00 new GHC build system: use shell-wrappers macro - - - - - 25f8afe7 by Ian Lynagh at 2009-03-21T19:13:53+00:00 Fix (with a hack?) haddock in teh new build system - - - - - 6a29a37e by David Waern at 2009-03-24T22:10:15+00:00 Remove unnecessary LANGUAGE pragma - - - - - 954da57d by David Waern at 2009-03-24T22:21:23+00:00 Fix warnings in H.B.DevHelp - - - - - 1619f1df by David Waern at 2009-03-26T23:20:44+00:00 -Wall police in H.B.Html - - - - - b211e13b by Simon Marlow at 2009-03-24T13:00:56+00:00 install Haddock's html stuff - - - - - 78e0b107 by David Waern at 2008-12-07T19:58:53+00:00 Add verbosity flag and utils, remove "verbose" flag - - - - - 913dae06 by David Waern at 2008-12-07T20:01:05+00:00 Add some basic "verbose" mode logging in H.Interface - - - - - 1cbff3bf by David Waern at 2009-03-27T00:07:26+00:00 Fix conflicts - - - - - 22f82032 by David Waern at 2009-03-27T21:15:11+00:00 Remove H.GHC.Typecheck - - - - - 81557804 by David Waern at 2009-03-27T21:19:22+00:00 Remove docNameOrig and use getName everywhere instead - - - - - d8267213 by David Waern at 2009-03-27T21:21:46+00:00 Use docNameOcc instead of nameOccName . getName - - - - - 5d55deab by David Waern at 2009-03-27T21:33:04+00:00 Remove H.DocName and put DocName in H.Types - - - - - 8ba72611 by David Waern at 2009-03-27T22:06:26+00:00 Document DocName - - - - - 605f8ca5 by David Waern at 2009-03-27T22:45:21+00:00 -Wall police - - - - - e4da93ae by David Waern at 2009-03-27T23:12:53+00:00 -Wall police in H.B.Hoogle - - - - - bb255519 by David Waern at 2009-03-27T23:41:28+00:00 Define Foldable and Traversable instances for Located - - - - - f1195cfe by David Waern at 2009-03-27T23:51:34+00:00 Wibble - - - - - 23818d7c by David Waern at 2009-03-28T00:03:55+00:00 -Wall police in H.I.Rename - - - - - 0f050d67 by David Waern at 2009-03-28T00:15:15+00:00 -Wall police in H.I.AttachInstances - - - - - 0f3fe038 by David Waern at 2009-03-28T21:09:41+00:00 Wibble - - - - - 275d4865 by David Waern at 2009-03-28T21:27:06+00:00 Layout fix - - - - - 54ff0ef8 by David Waern at 2009-03-28T21:59:07+00:00 -Wall police in H.I.Create - - - - - 7f58b117 by David Waern at 2009-03-28T22:10:19+00:00 -Wall police in H.Interface - - - - - f0c03b44 by David Waern at 2009-03-28T22:22:59+00:00 -Wall police in Main - - - - - 29da355c by David Waern at 2009-03-28T22:23:39+00:00 Turn on -Wall -Werror - - - - - 446d3060 by David Waern at 2009-04-01T20:40:30+00:00 hlint police - - - - - 3867c9fc by David Waern at 2009-04-01T20:48:42+00:00 hlint police - - - - - bd1f1600 by David Waern at 2009-04-01T20:58:02+00:00 hlint police - - - - - e0e90866 by David Waern at 2009-04-05T12:42:53+00:00 Move H.GHC.Utils to H.GhcUtils - - - - - 9cbd426b by David Waern at 2009-04-05T12:57:21+00:00 Remove Haddock.GHC and move its (small) contents to Main - - - - - b5c2cbfd by David Waern at 2009-04-05T13:07:04+00:00 Fix whitespace and stylistic issues in Main - - - - - 3c04aa56 by porges at 2008-12-07T08:22:19+00:00 add unicode output - - - - - 607918da by David Waern at 2009-04-26T15:09:43+00:00 Resolve conflict - - - - - 4bec6b6b by Simon Marlow at 2009-05-13T10:00:31+00:00 fix markup - - - - - 436ad6f4 by Simon Marlow at 2009-03-23T11:54:45+00:00 clean up - - - - - bdcd1398 by Simon Marlow at 2009-03-24T10:36:45+00:00 new GHC build system: add $(exeext) - - - - - 9c0972f3 by Simon Marlow at 2009-03-24T11:04:31+00:00 update for new GHC build system layout - - - - - d0f3f83a by Ian Lynagh at 2009-03-29T15:31:43+00:00 GHC new build system fixes - - - - - 5a8245c2 by Ian Lynagh at 2009-04-04T20:44:23+00:00 Tweak new build system - - - - - 9c6f2d7b by Simon Marlow at 2009-05-13T10:01:27+00:00 add build instructions for GHC - - - - - 66d07c76 by Ian Lynagh at 2009-05-31T00:37:53+00:00 Quote program paths in ghc.mk - - - - - bb7de2cd by Ian Lynagh at 2009-06-03T22:57:55+00:00 Use a bang pattern on an unlifted binding - - - - - 3ad283fc by Ian Lynagh at 2009-06-13T16:17:50+00:00 Include haddock in GHC bindists - - - - - ac447ff4 by David Waern at 2009-06-24T21:07:50+00:00 Delete Haddock.Exception and move contents to Haddock.Types Only a few lines of code that mainly declares a type - why not just put it in Haddock.Types. - - - - - 4464fb9b by David Waern at 2009-06-24T22:23:23+00:00 Add Haddock module headers Add a proper Haddock module header to each module, with a more finegrained copyright. If you feel mis-accreditted, please correct any copyright notice! The maintainer field is set to haddock at projects.haskell.org. Next step is to add a brief description to each module. - - - - - 5f4c95dd by David Waern at 2009-06-24T22:39:44+00:00 Fix spelling error - - - - - 6d074cdb by David Waern at 2009-06-25T21:53:56+00:00 Document Interface and InstalledInterface better - - - - - d0cbd183 by David Waern at 2009-06-27T12:46:46+00:00 Remove misplaced whitespace in H.I.Rename - - - - - fa381c49 by David Waern at 2009-06-27T13:26:03+00:00 Fix haskell/haddock#104 - create output directory if missing - - - - - 91fb77ae by Ian Lynagh at 2009-06-25T15:59:50+00:00 TAG 2009-06-25 - - - - - 0d853f40 by Simon Peyton Jones at 2009-07-02T15:35:22+00:00 Follow extra field in ConDecl - - - - - b201735d by Ian Lynagh at 2009-07-05T16:50:35+00:00 Update Makefile for the new GHC build system - - - - - df6c0092 by Ian Lynagh at 2009-07-05T17:01:13+00:00 Resolve conflicts - - - - - 1066870a by Ian Lynagh at 2009-07-05T17:01:48+00:00 Remove the -Wwarn hack in the GHC build system - - - - - 7e856076 by Ian Lynagh at 2009-07-05T17:17:59+00:00 Fix warnings - - - - - 5d4cd958 by Ian Lynagh at 2009-07-05T19:35:40+00:00 Bump version number Cabal needs to distinguish between haddocks having a --verbose and --verbosity flag - - - - - 6ee07c99 by David Waern at 2009-07-06T20:14:57+00:00 Wibble - - - - - 2308b66f by David Waern at 2009-07-06T20:24:20+00:00 Clearer printing of versions by runtests.hs - - - - - d4b5d9ab by David Waern at 2009-07-06T21:22:42+00:00 Fix (invisible) bug introduced by unicode patch - - - - - 2caca8d8 by David Waern at 2009-07-06T21:44:10+00:00 Use HscAsm instead of HscC when using TH - - - - - 18f3b755 by David Waern at 2009-07-06T22:10:22+00:00 Update HCAR entry (by Janis) - - - - - a72ac9db by David Waern at 2009-07-06T23:01:35+00:00 Follow HsRecTy change with an #if __GLASGOW_HASKEL__ >= 611 - - - - - 549135d2 by David Waern at 2009-07-06T23:11:41+00:00 Remove unused functions from Haddock.Utils - - - - - b450134a by Isaac Dupree at 2009-07-11T14:59:00+00:00 revert to split-index for large indices - remove the search-box, because browsers have search-for-text abilities anyway. - pick 150 items in index as the arbitrary time at which to split it - notice the bug that identifiers starting with non-ASCII characters won't be listed in split-index, but don't bother to fix it yet (see ticket haskell/haddock#116, http://trac.haskell.org/haddock/ticket/116 ) - - - - - 78a5661e by Isaac Dupree at 2009-07-20T15:37:18+00:00 Implement GADT records in HTML backend - - - - - 4e163555 by Isaac Dupree at 2009-07-21T22:03:25+00:00 add test for GADT records - - - - - 79aa4d6e by David Waern at 2009-07-23T20:40:37+00:00 Update test suite following version bump - - - - - 5932c011 by David Waern at 2009-08-02T10:25:39+00:00 Fix documentation bug - - - - - a6970fca by David Waern at 2009-08-12T23:08:53+00:00 Remove support for ghc 6.8.* from .cabal file - - - - - c1695902 by Ian Lynagh at 2009-07-07T13:35:45+00:00 Fix unused import warnings - - - - - fb6df7f9 by Ian Lynagh at 2009-07-16T00:20:31+00:00 Use cProjectVersion directly rather than going through compilerInfo Fixes the build after changes in GHC - - - - - 548cdd66 by Simon Marlow at 2009-07-28T14:27:04+00:00 follow changes in GHC's ForeignType - - - - - 9395aaa0 by David Waern at 2009-08-13T22:17:33+00:00 Switch from PatternSignatures to ScopedTypeVariables in Main - - - - - eebf39bd by David Waern at 2009-08-14T17:14:28+00:00 Version .haddock files made with GHC 6.10.3/4 correclty - - - - - 58f3e735 by David Waern at 2009-08-14T17:19:37+00:00 Support GHC 6.10.* and 6.11.* only - - - - - 5f63cecc by David Waern at 2009-08-14T22:03:20+00:00 Do not version .haddock file based on GHC patchlevel version We require that the instances of Binary that we use from GHC will not change between patchlevel versions. - - - - - d519de9f by David Waern at 2009-08-14T23:50:00+00:00 Update CHANGES - - - - - 35dccf5c by David Waern at 2009-08-14T23:51:38+00:00 Update version number everywhere - - - - - 6d363fea by David Waern at 2009-08-15T09:46:49+00:00 Update ANNOUNCE - - - - - c7ee6bc2 by David Waern at 2009-08-15T09:47:13+00:00 Remove -Werror Forgot that Hackage doesn't like it. - - - - - a125c12b by David Waern at 2009-08-15T09:49:50+00:00 Require Cabal >= 1.6 - - - - - adb2f560 by Isaac Dupree at 2009-08-12T03:47:14+00:00 Cross-Package Documentation version 4 - - - - - 3d6dc04d by David Waern at 2009-08-15T23:42:57+00:00 Put all the IN_GHC_TREE stuff inside getGhcLibDir - - - - - 56624097 by David Waern at 2009-08-15T23:52:03+00:00 Add --print-ghc-libdir - - - - - f15d3ccb by David Waern at 2009-08-16T00:37:52+00:00 Read base.haddock when running tests We can now test cross-package docs. - - - - - 283f0fb9 by David Waern at 2009-08-16T00:50:59+00:00 Update test output - we now have more links - - - - - 673d1004 by David Waern at 2009-08-16T01:26:08+00:00 Read process.haddock when running tests - - - - - 0d127f82 by David Waern at 2009-08-16T01:43:04+00:00 Add a test for cross-package documentation - - - - - f94db967 by Ian Lynagh at 2009-08-16T18:42:44+00:00 Follow GHC build system changes - - - - - 5151278a by Isaac Dupree at 2009-08-16T19:58:05+00:00 make cross-package list types look nicer - - - - - c41e8228 by Isaac Dupree at 2009-08-18T01:47:47+00:00 Haddock.Convert: export more functions This lets us remove some code in Haddock.Interface.AttachInstances - - - - - 2e5fa398 by Isaac Dupree at 2009-08-18T02:11:05+00:00 switch AttachInstances to use synify code It changed an instance from showing ((,) a b) to (a, b) because my synify code is more sophisticated; I hope the latter is a good thing rather than a bad thing aesthetically, here. But this definitely reduces code duplication! - - - - - b8b07123 by Isaac Dupree at 2009-08-18T02:23:31+00:00 Find instances using GHC, which is more complete. In particular, it works cross-package. An intermediate patch also moved the instance-finding into createInterface, but that move turned out not to be necessary, so if we want to do that, it'd go in a separate patch. (Is that possible? Or will we need GHC to have loaded all the modules first, before we can go searching for the instances (e.g. if the modules are recursive or something)?) - - - - - 6959b451 by Isaac Dupree at 2009-08-17T00:37:18+00:00 fix preprocessor conditional sense - - - - - 942823af by Isaac Dupree at 2009-08-16T22:46:48+00:00 remove ghc 6.8 conditionals from Haddock.Interface - - - - - 4b3ad888 by Isaac Dupree at 2009-08-18T20:24:38+00:00 Fix GHC 6.11 build in Haddock.Convert - - - - - 0a89c5ab by Isaac Dupree at 2009-08-23T00:08:58+00:00 hacks to make it compile without fnArgDocsn - - - - - 7b3bed43 by Isaac Dupree at 2009-08-23T03:01:28+00:00 less big-Map-based proper extraction of constructor subdocs - - - - - b21c279a by Isaac Dupree at 2009-08-23T03:02:06+00:00 Html: remove unnecessary+troublesome GHC. qualifications - - - - - 96c97115 by Isaac Dupree at 2009-08-23T03:08:03+00:00 Move doc parsing/lexing into Haddock for ghc>=6.11 - - - - - e1cec02d by Isaac Dupree at 2009-08-23T05:08:14+00:00 get rid of unused DocMap parameter in Html - - - - - 66960c59 by Isaac Dupree at 2009-08-23T05:54:20+00:00 fix horrible named-docs-disappearing bug :-) - - - - - a9d7eff3 by Isaac Dupree at 2009-08-23T06:26:36+00:00 re-implement function-argument docs ..on top of the lexParseRn work. This patch doesn't change the InstalledInterface format, and thus, it does not work cross-package, but that will be easy to add subsequently. - - - - - 8bf6852c by Isaac Dupree at 2009-08-23T07:26:05+00:00 cross-package fnArgDocs. WARNING: changes .haddock binary format While breaking the format, I took the opportunity to unrename the DocMap that's saved to disk, because there's really no reason that we want to know what *another* package's favorite place to link a Name to was. (Is that true? Or might we want to know, someday?) Also, I added instance Binary Map in InterfaceFile. It makes the code a little simpler without changing anything of substance. Also it lets us add another Map hidden inside another Map (fnArgsDocs in instDocMap) without having really-convoluted serialization code. Instances are neat! I don't understand why this change to InterfaceFile seemed to subtly break binary compatibility all by itself, but no matter, I'll just roll it into the greater format-changing patch. Done! - - - - - 30115a64 by Isaac Dupree at 2009-08-23T18:22:47+00:00 Improve behavior for unfindable .haddock - - - - - aa364bda by Isaac Dupree at 2009-08-23T18:28:16+00:00 add comment for FnArgsDoc type - - - - - 49b23a99 by Isaac Dupree at 2009-08-23T21:52:48+00:00 bugfix: restore fnArgDocs for type-synonyms - - - - - f65f9467 by Isaac Dupree at 2009-08-23T22:06:55+00:00 Backends.Hoogle: eliminate warnings - - - - - a292d216 by Isaac Dupree at 2009-08-23T22:10:24+00:00 Haddock.Convert: eliminate warnings - - - - - 5546cd20 by Isaac Dupree at 2009-08-23T22:12:31+00:00 Haddock.Interface.Rename: eliminate warnings - - - - - 0a9798b6 by Isaac Dupree at 2009-08-23T22:18:47+00:00 Main.hs: remove ghc<6.9 conditionals - - - - - e8f9867f by Isaac Dupree at 2009-08-23T22:27:46+00:00 Main.hs: eliminate warnings (except for OldException) - - - - - 61c64247 by Isaac Dupree at 2009-08-23T22:41:01+00:00 move get*LibDir code in Main.hs, to +consistent code, -duplication - - - - - 948f1e69 by Isaac Dupree at 2009-08-23T23:14:26+00:00 Main.hs: OldException->Exception: which eliminates warnings - - - - - 3d5d5e03 by Isaac Dupree at 2009-08-23T23:20:11+00:00 GhcUtils: ghc >= 6.10 - - - - - 2771d657 by Isaac Dupree at 2009-08-23T23:21:55+00:00 InterfaceFile: ghc >= 6.10 - - - - - d9f2b9d1 by Isaac Dupree at 2009-08-23T23:22:58+00:00 Types: ghc >= 6.10 - - - - - ca39210e by Isaac Dupree at 2009-08-23T23:23:26+00:00 ModuleTree: ghc >= 6.10 - - - - - 883c4e59 by Isaac Dupree at 2009-08-23T23:24:04+00:00 Backends.DevHelp: ghc >= 6.10 - - - - - 04667df5 by Isaac Dupree at 2009-08-23T23:24:37+00:00 Backends.Html: ghc >= 6.10 - - - - - a9f7f25f by Isaac Dupree at 2009-08-23T23:25:24+00:00 Utils: ghc >= 6.10 - - - - - b7105022 by Isaac Dupree at 2009-08-23T23:37:47+00:00 eliminate haskell98 dependency, following GHC's example It turns out I/we already had, and it was only a matter of deleting it from the cabal file. - - - - - 292e0911 by Isaac Dupree at 2009-08-24T01:22:44+00:00 refactor out subordinatesWithNoDocs dep of inferenced-decls fix - - - - - c2ed46a2 by Isaac Dupree at 2009-08-24T01:24:03+00:00 Eradicate wrong runtime warning for type-inferenced exported-functions see the long comment in the patch for why I did it this way :-) - - - - - 4ac0b57c by David Waern at 2009-09-04T22:56:20+00:00 Clean up tyThingToHsSynSig a little Factor out noLoc and use the case construct. Also rename the function to tyThingToLHsDecl, since it doesn't just create type signatures. - - - - - 28ab9201 by David Waern at 2009-09-04T22:58:50+00:00 Wibble - - - - - 0d9fe6d0 by David Waern at 2009-09-06T18:39:30+00:00 Add more copyright owners to H.I.AttachInstances - - - - - 122441b1 by David Waern at 2009-09-06T18:44:12+00:00 Style police - - - - - 1fa79463 by David Waern at 2009-09-06T18:57:45+00:00 Move toHsInstHead to Haddock.Convert and call it synifyInstHead - - - - - 0d42a8aa by David Waern at 2009-09-06T21:11:38+00:00 Use colordiff to display test results if available - - - - - ea9d8e03 by Simon Marlow at 2009-08-24T08:46:14+00:00 Follow changes in GHC's interface file format Word32 instead of Int for FastString and Name offsets - - - - - 537e051e by Simon Marlow at 2009-07-29T14:16:53+00:00 define unpackPackageId (it was removed from GHC) - - - - - 50c63aa7 by David Waern at 2009-09-09T23:18:03+00:00 Remove commented-out code - - - - - 511631fe by David Waern at 2009-09-09T23:19:05+00:00 Correct copyright in H.I.ParseModuleHeader - - - - - 898ec768 by David Waern at 2009-09-11T11:22:29+00:00 Use Map.fromList/toList intead of fromAscList/toAscList when serializing Maps This fixes the missing docs problem. The Eq and Ord instances for Name uses the unique number in Name. This number is created at deserialization time by GHC's magic Binary instance for Name, and it is random. Thus, fromAscList can't be used at deserialization time, even though toAscList was used at serialization time. - - - - - 37bec0d5 by Simon Peyton Jones at 2009-09-11T08:28:04+00:00 Track change in HsType - - - - - eb3a97c3 by Ian Lynagh at 2009-09-11T16:07:09+00:00 Allow building with base 4.2 - - - - - bb4205ed by Ian Lynagh at 2009-09-22T13:50:02+00:00 Loosen the GHC dependency - - - - - 5c75deb2 by Ian Lynagh at 2009-09-22T14:08:39+00:00 Fix building with GHC >= 6.12 - - - - - fb131481 by David Waern at 2009-09-11T11:24:48+00:00 Update runtests.hs to work with GHC 6.11 - - - - - ac3a419d by David Waern at 2009-09-11T11:25:14+00:00 Update CrossPackageDocs test - - - - - ec65c3c6 by David Waern at 2009-09-11T11:25:40+00:00 Add reference output for CrossPackageDocs - - - - - 520c2758 by Ian Lynagh at 2009-10-25T17:26:40+00:00 Fix installation in the GHC build system - - - - - 28b3d7df by Ian Lynagh at 2009-11-05T15:57:27+00:00 GHC build system: Make *nix installation work in paths containing spaces - - - - - 5c9bb541 by David Waern at 2009-11-14T11:56:39+00:00 Track change in HsType for the right compiler version - - - - - 905097ce by David Waern at 2009-11-14T12:10:47+00:00 hlint police - - - - - 04920630 by Ian Lynagh at 2009-11-20T13:46:30+00:00 Use defaultObjectTarget rather than HscAsm This fixes haddock when we don't have a native code generator - - - - - 966eb079 by David Waern at 2009-11-15T12:32:21+00:00 Remove commented-out code - - - - - 37f00fc4 by David Waern at 2009-11-22T13:58:48+00:00 Make runtests.hs strip links before diffing Generates easier to read diffs when tests fail. The content of the links is not important anyway since it is not taken into account by the tests. - - - - - 3a9bb8ef by David Waern at 2009-11-22T14:05:06+00:00 Follow findProgramOnPath signature change in runtests.hs - - - - - b26b9e5a by David Waern at 2009-11-22T14:08:40+00:00 Follow removal of GHC.MVar from base in CrossPackageDocs - - - - - f4d90ae4 by David Waern at 2009-11-22T14:48:47+00:00 Make copy.hs strip link contents before copying No more updating of reference files when URLs in links changes. - - - - - 4c9c420d by David Waern at 2009-11-22T15:26:41+00:00 Update test reference output * More links (Int, Float etc) * Stripped link contents - - - - - a62b80e3 by David Waern at 2009-11-23T23:19:39+00:00 Update CrossPackageDocs reference output - Remove GHC.MVar import (removed from base) - Strip link contents - - - - - 43491394 by David Waern at 2009-11-23T23:20:00+00:00 Update test reference files with comments on instances - - - - - 0d370a0b by David Waern at 2009-11-23T23:25:16+00:00 Bump version number - - - - - 2293113e by David Waern at 2009-11-24T20:55:49+00:00 Comments on instances Implementing this was a little trickier than I thought, since we need to match up instances from the renamed syntax with instances represented by InstEnv.Instance. This is due to the current design of Haddock, which matches comments with declarations from the renamed syntax, while getting the list of instances of a class/family directly using the GHC API. - Works for class instances only (Haddock has no support for type family instances yet) - The comments are rendered to the right of the instance head in the HTML output - No change to the .haddock file format - Works for normal user-written instances only. No comments are added on derived or TH-generated instances - - - - - bf586f29 by David Waern at 2009-11-27T22:05:15+00:00 Whitespace police - - - - - b8f03afa by David Waern at 2009-11-27T22:11:46+00:00 Remove bad whitespace and commented-out pieces - - - - - 90b8ee90 by David Waern at 2009-11-27T22:15:04+00:00 Whitespace police - - - - - b5ede900 by David Waern at 2009-11-27T22:15:50+00:00 Whitespace police - - - - - e3fddbfe by David Waern at 2009-11-28T13:37:59+00:00 Remove Name from DocInstance It's not used. - - - - - 9502786c by David Waern at 2009-11-28T13:56:54+00:00 Require at least GHC 6.12 While regression testing Haddock, I found a bug that happens with GHC 6.10.3, but not with GHC 6.12-rc2 (haven't tried 6.10.4). I don't have time to track it down. I think we should just always require the latest major GHC version. The time spent on making Haddock work with older versions is too high compared to the time spent on bugfixing, refactoring and features. - - - - - 8fa688d8 by David Waern at 2009-11-28T15:05:03+00:00 Remove cruft due to compatibility with older GHCs - - - - - 46fbbe9d by David Waern at 2009-11-28T15:07:50+00:00 Add a documentation header to Haddock.Convert - - - - - c3d2cc4a by David Waern at 2009-11-28T15:10:14+00:00 Remove unused H.Utils.FastMutInt2 - - - - - 490aba80 by David Waern at 2009-11-28T15:36:36+00:00 Rename Distribution.Haddock into Documentation.Haddock - - - - - 33ee2397 by David Waern at 2009-11-28T15:36:47+00:00 Fix error message - - - - - a5a3b950 by David Waern at 2009-11-28T16:58:39+00:00 Add a test flag that brings in QuickCheck - - - - - fa049e13 by David Waern at 2009-11-28T19:32:18+00:00 Say that we want quickcheck 2 - - - - - f32b0d9b by David Waern at 2009-11-28T19:32:40+00:00 Add an Arbitrary instance for HsDoc - - - - - da9a8bd7 by David Waern at 2009-11-28T20:15:30+00:00 Rename HsDoc back into Doc - - - - - edb60101 by David Waern at 2009-11-28T22:16:16+00:00 Move H.Interface.Parse/Lex to H.Parse/Lex These are not just used to build Interfaces. - - - - - 0656a9b8 by David Waern at 2009-11-28T23:12:14+00:00 Update version number in test suite - - - - - 5e8c6f4a by David Waern at 2009-12-21T14:12:41+00:00 Improve doc of DocName - - - - - 7868e551 by Ian Lynagh at 2009-09-22T10:43:03+00:00 TAG GHC 6.12-branch created - - - - - 0452a3ea by Ian Lynagh at 2009-12-15T12:46:07+00:00 TAG GHC 6.12.1 release - - - - - 65e9be62 by David Waern at 2009-12-21T16:58:58+00:00 Update CHANGES - - - - - 145cee32 by David Waern at 2009-12-21T16:59:09+00:00 TAG 2.6.0 - - - - - 3c552008 by David Waern at 2009-12-22T17:11:14+00:00 Update ANNOUNCE - - - - - 931f9db4 by David Waern at 2010-01-22T19:57:17+00:00 Convert haddock.vim to use unix newlines - - - - - 4e56588f by David Waern at 2010-01-22T22:11:17+00:00 Remove unnecessary (and inexplicable) uses of nub - - - - - 744bb4d1 by David Waern at 2010-01-22T22:12:14+00:00 Follow move of parser and lexer - - - - - e34bab14 by David Waern at 2010-01-22T22:49:13+00:00 Use findProgramLocation instead of findProgramOnPath in runtests.hs - - - - - 8d39891b by Isaac Dupree at 2010-01-14T18:53:18+00:00 fix html arg-doc off-by-one and silliness - - - - - 9401f2e9 by David Waern at 2010-01-22T22:57:03+00:00 Create a test for function argument docs - - - - - 507a82d7 by David Waern at 2010-01-22T23:24:47+00:00 Put parenthesis around type signature arguments of function type - - - - - 8a305c28 by David Waern at 2010-01-23T17:26:59+00:00 Add reference file for the FunArgs test - - - - - 1309d5e1 by David Waern at 2010-01-24T16:05:08+00:00 Improve FunArg test and update Test.html.ref - - - - - 2990f055 by Yitzchak Gale at 2010-02-14T16:03:46+00:00 Do not generate illegal character in HTML ID attribute. - - - - - c5bcab7a by David Waern at 2010-02-22T22:10:30+00:00 Fix Haddock markup error in comment - - - - - c6416a73 by David Waern at 2010-02-24T22:55:08+00:00 Large additions to the Haddock API Also improved and added more doc comments. - - - - - 57d289d7 by David Waern at 2010-02-24T22:58:02+00:00 Remove unused ifaceLocals - - - - - 80528d93 by David Waern at 2010-02-25T21:05:09+00:00 Add HaddockModInfo to the API - - - - - 82806848 by David Waern at 2010-02-25T21:05:27+00:00 Wibble - - - - - 744cad4c by David Waern at 2010-02-25T23:30:59+00:00 Make it possible to run a single test - - - - - 6a806e4c by David Waern at 2010-03-14T14:19:39+00:00 Bump version number - - - - - a5a8e4a7 by David Waern at 2010-03-14T14:36:35+00:00 Update ANNOUNCE - - - - - 6f05435e by Simon Hengel at 2010-03-15T20:52:42+00:00 Add missing dependencies for 'library' in haddock.cabal - - - - - faefe2bd by David Waern at 2010-03-15T22:29:37+00:00 Solve conflicts - - - - - 9808ad52 by David Waern at 2010-03-15T22:51:21+00:00 Bump version number - - - - - eb0bf60b by David Waern at 2010-03-15T22:52:32+00:00 Update CHANGES - - - - - f95cd891 by David Waern at 2010-03-15T23:01:06+00:00 Add Paths_haddock to other-modules of library - - - - - 65997b0a by David Waern at 2010-03-15T23:14:59+00:00 Update CHANGES - - - - - 7e251731 by David Waern at 2010-03-15T23:15:30+00:00 Bump version number - - - - - c9cd0ddc by David Waern at 2010-03-16T00:28:34+00:00 Fix warning - - - - - 1cac2d93 by Simon Peyton Jones at 2010-01-04T15:22:16+00:00 Fix imports for new location of splitKindFunTys - - - - - 474f26f6 by Simon Peyton Jones at 2010-02-10T14:36:06+00:00 Update Haddock for quasiquotes - - - - - 0dcc06c0 by Simon Peyton Jones at 2010-02-10T10:59:45+00:00 Track changes in HsTyVarBndr - - - - - 2d84733a by Simon Peyton Jones at 2010-02-10T14:52:44+00:00 Track HsSyn chnages - - - - - 9e3adb8b by Ian Lynagh at 2010-02-20T17:09:42+00:00 Resolve conflicts - - - - - a3e72ff8 by Simon Peyton Jones at 2010-03-04T13:05:16+00:00 Track change in HsUtils; and use a nicer function not an internal one - - - - - 27994854 by David Waern at 2010-03-18T22:22:27+00:00 Fix build with GHC 6.12.1 - - - - - 11f6e488 by David Waern at 2010-03-18T22:24:09+00:00 Bump version in test reference files - - - - - 0ef2f11b by David Waern at 2010-03-20T00:56:30+00:00 Fix library part of cabal file when in ghc tree - - - - - 3f6146ff by Mark Lentczner at 2010-03-20T22:30:11+00:00 First, experimental XHTML rendering switch to using the xhtml package copied Html.hs to Xhtml.hs and split into sub-modules under Haddock/Backends/Xhtml and detabify moved footer into div, got ready for iface change headers converted to semantic markup contents in semantic markup summary as semantic markup description in semantic markup, info block in header fixed factored out rendering so during debug it can be readable (see renderToString) - - - - - b8ab329b by Mark Lentczner at 2010-03-20T22:54:01+00:00 apply changes to Html.hs to Xhtml/*.hs incorporate changes that were made between the time Html.hs was copied and split into Xhtml.hs and Xhtml/*.hs includes patchs after "Wibble" (!) through "Fix build with GHC 6.12.1" - - - - - 73df2433 by Ian Lynagh at 2010-03-20T21:56:37+00:00 Follow LazyUniqFM->UniqFM in GHC - - - - - db4f602b by David Waern at 2010-03-29T22:00:01+00:00 Fix build with GHC 6.12 - - - - - d8dca088 by Simon Hengel at 2010-04-02T16:39:55+00:00 Add missing dependencies to cabal file - - - - - e2adc437 by Simon Hengel at 2010-04-02T14:08:40+00:00 Add markup support for interactive examples - - - - - e882ac05 by Simon Hengel at 2010-04-02T14:11:53+00:00 Add tests for interactive examples - - - - - 5a07a6d3 by David Waern at 2010-04-07T17:05:20+00:00 Propagate source positions from Lex.x to Parse.y - - - - - 6493b46f by David Waern at 2010-04-07T21:48:57+00:00 Let runtests.hs die when haddock has not been built - - - - - 5e34423e by David Waern at 2010-04-07T22:01:13+00:00 Make runtests.hs slightly more readable - - - - - 321d59b3 by David Waern at 2010-04-07T22:13:27+00:00 Fix haskell/haddock#75 Add colons to the $ident character set. - - - - - 37b08b8d by David Waern at 2010-04-08T00:32:52+00:00 Fix haskell/haddock#118 Avoid being too greedy when lexing URL markup (<..>), in order to allow multiple URLs on the same line. Do the same thing with <<..>> and #..#. - - - - - df8feac9 by David Waern at 2010-04-08T00:57:33+00:00 Make it easier to add new package deps to test suite This is a hack - we should use Cabal to get the package details instead. - - - - - 1ca6f84b by David Waern at 2010-04-08T01:03:06+00:00 Add ghc-prim to test suite deps - - - - - 27371e3a by Simon Hengel at 2010-04-08T19:26:34+00:00 Let parsing fails on paragraphs that are immediately followed by an example This is more consistent with the way we treat code blocks. - - - - - 83096e4a by David Waern at 2010-04-08T21:20:00+00:00 Improve function name - - - - - 439983ce by David Waern at 2010-04-10T10:46:14+00:00 Fix haskell/haddock#112 No link was generated for 'Addr#' in a doc comment. The reason was simply that the identifier didn't parse. We were using parseIdentifier from the GHC API, with a parser state built from 'defaultDynFlags'. If we pass the dynflags of the module instead, the right options are turned on on while parsing the identifer (in this case -XMagicHash), and the parse succeeds. - - - - - 5c0d35d7 by David Waern at 2010-04-10T10:54:06+00:00 Rename startGhc into withGhc - - - - - dca081fa by Simon Hengel at 2010-04-12T19:09:16+00:00 Add documentation for interactive examples - - - - - c7f26bfa by David Waern at 2010-04-13T00:51:51+00:00 Slight fix to the documentation of examples - - - - - 06eb7c4c by David Waern at 2010-04-13T00:57:05+00:00 Rename Interactive Examples into Examples (and simplify explanation) - - - - - 264830cb by David Waern at 2010-05-10T20:07:27+00:00 Update CHANGES with info about 2.6.1 - - - - - 8e5d4514 by Simon Hengel at 2010-04-18T18:16:54+00:00 Add unit tests for parser - - - - - 68297f40 by David Waern at 2010-05-10T21:53:37+00:00 Improve testsuite README - - - - - f04eb6e4 by David Waern at 2010-05-11T19:14:31+00:00 Re-organise the testsuite structure - - - - - a360f710 by David Waern at 2010-05-11T19:18:03+00:00 Shorten function name - - - - - 1d5dd359 by David Waern at 2010-05-11T21:40:02+00:00 Update runtests.hs following testsuite re-organisation - - - - - ffebe217 by David Waern at 2010-05-11T21:40:10+00:00 Update runtests.hs to use base-4.2.0.1 - - - - - 635de402 by David Waern at 2010-05-11T21:41:11+00:00 Update runparsetests.hs following testsuite reorganisation - - - - - 72137910 by Ian Lynagh at 2010-05-06T20:43:06+00:00 Fix build - - - - - 1a80b76e by Ian Lynagh at 2010-05-06T22:25:29+00:00 Remove redundant import - - - - - 1031a80c by Simon Peyton Jones at 2010-05-07T13:21:09+00:00 Minor wibbles to HsBang stuff - - - - - dd8e7fe5 by Ian Lynagh at 2010-05-08T15:22:00+00:00 GHC build system: Follow "rm" variable changes - - - - - 7f5e6748 by David Waern at 2010-05-13T11:53:02+00:00 Fix build with GHC 6.12.2 - - - - - 7953d4d8 by David Waern at 2010-05-13T18:45:01+00:00 Fixes to comments only - - - - - 8ae8eb64 by David Waern at 2010-05-13T18:57:26+00:00 ModuleMap -> IfaceMap - - - - - 1c3eadc6 by David Waern at 2010-05-13T19:03:13+00:00 Fix whitespace style issues - - - - - e96783c0 by David Waern at 2010-05-13T19:08:53+00:00 Fix comment - - - - - c998a78b by David Waern at 2010-05-13T19:39:00+00:00 Position the module header the same way everywhere Silly, but nice with some consistency :-) - - - - - b48a714e by David Waern at 2010-05-13T19:41:32+00:00 Position of module header, this time in the HTML backends - - - - - f9bfb12e by David Waern at 2010-05-13T19:43:05+00:00 Two newlines between declarations in Main - - - - - 071d44c7 by David Waern at 2010-05-13T19:44:21+00:00 Newlines in Convert - - - - - 036346db by David Waern at 2010-05-13T19:46:47+00:00 Fix a few stylistic issues in H.InterfaceFile - - - - - f0b8379e by David Waern at 2010-05-13T19:47:53+00:00 Add newlines to H.ModuleTree - - - - - 27409f8e by David Waern at 2010-05-13T19:51:10+00:00 Fix stylistic issues in H.Utils - - - - - 24774a11 by David Waern at 2010-05-13T20:00:43+00:00 Structure H.Types better - - - - - 7b6f5e40 by David Waern at 2010-05-13T20:01:04+00:00 Remove bad Arbitrary instance - - - - - fac9f1f6 by David Waern at 2010-05-13T20:05:50+00:00 Get rid of H.Utils.pathJoin and use System.FilePath.joinPath instead - - - - - fe6d00c4 by David Waern at 2010-05-13T20:51:55+00:00 Export a couple of more types from the API - - - - - b2e33a5f by David Waern at 2010-05-13T21:27:51+00:00 Improve doc comment for Interface - - - - - c585f2ce by David Waern at 2010-05-13T21:30:14+00:00 Improve documentation of Haddock.Interface - - - - - e6791db2 by David Waern at 2010-05-13T22:07:35+00:00 Remove meaningless comments - - - - - 7801b390 by David Waern at 2010-05-14T17:53:33+00:00 Remove unused modules - - - - - f813e937 by David Waern at 2010-05-14T17:55:17+00:00 Re-direct compilation output to a temporary directory Also add a flag --no-tmp-comp-dir that can be used to get the old behaviour of writing compilation files to GHC's output directory (default "."). - - - - - e56737ec by David Waern at 2010-05-14T18:06:11+00:00 Wibble - - - - - e40b0447 by David Waern at 2010-05-14T19:01:52+00:00 Move flag evaluation code from Main to Haddock.Options Determining the value of "singular" flags (by e.g. taking the last occurrence of the flag) and other flag evaluation should done in Haddock.Options which is the module that is supposed to define the command line interface. This makes Main a bit easier on the eyes as well. - - - - - 27091f57 by David Waern at 2010-05-14T19:05:10+00:00 Wibble - - - - - c658cf61 by David Waern at 2010-05-14T19:06:49+00:00 Re-order things in Haddock.Options a bit - - - - - 8cfdd342 by David Waern at 2010-05-14T19:20:29+00:00 De-tabify Haddock.Options and fix other whitespace issues - - - - - 0df16b62 by David Waern at 2010-05-14T19:25:07+00:00 Improve comments - - - - - 80b38e2b by David Waern at 2010-05-14T19:26:42+00:00 Whitespace police - - - - - fe580255 by David Waern at 2010-05-14T19:31:23+00:00 Wibbles to comments - - - - - a2b43fad by David Waern at 2010-05-14T20:24:32+00:00 Move some more flag functions to Haddock.Options - - - - - 3f895547 by David Waern at 2010-05-14T20:37:12+00:00 Make renderStep a top-level function in Main - - - - - 5cdca11d by David Waern at 2010-05-14T20:39:27+00:00 Spelling in comment - - - - - ad98d14c by David Waern at 2010-05-14T20:40:26+00:00 Comment fixes - - - - - 0bb9218f by David Waern at 2010-05-14T20:49:01+00:00 Whitespace police - - - - - 0f0a533f by David Waern at 2010-05-15T16:42:29+00:00 Improve description of --dump-interface - - - - - 5b2833ac by David Waern at 2010-05-15T17:16:53+00:00 Document --no-tmp-comp-dir - - - - - 8160b170 by David Waern at 2010-05-15T17:18:59+00:00 Wibble - - - - - 570dbe33 by David Waern at 2010-05-18T21:15:38+00:00 HLint police - - - - - 204e425f by David Waern at 2010-05-18T21:16:30+00:00 HLint police - - - - - 6db657ac by David Waern at 2010-05-18T21:16:37+00:00 Wibble - - - - - b942ccd7 by Simon Marlow at 2010-06-02T08:27:30+00:00 Interrupted disappeared in GHC 6.13 (GHC ticket haskell/haddock#4100) - - - - - 3b94a819 by Simon Marlow at 2010-06-02T08:45:08+00:00 Allow base-4.3 - - - - - c5a1fb7c by Simon Marlow at 2010-06-02T09:03:04+00:00 Fix compilation with GHC 6.13 - - - - - 6181296c by David Waern at 2010-06-08T21:09:05+00:00 Display name of prologue file when parsing it fails - - - - - 7cbc6f60 by Ian Lynagh at 2010-06-13T16:20:25+00:00 Remove redundant imports - - - - - 980c804b by Simon Marlow at 2010-06-22T08:41:50+00:00 isLocalAndTypeInferenced: fix for local module names overlapping package modules - - - - - d74d4a12 by Simon Marlow at 2010-06-23T12:03:27+00:00 Unresolved identifiers in Doc get replaced with DocMonospaced rather than plain strings - - - - - d8546783 by Simon Marlow at 2010-06-30T12:45:17+00:00 LaTeX backend (new options: --latex, --latex-style=<style>) - - - - - 437afa9e by David Waern at 2010-07-01T12:02:44+00:00 Fix a few stylistic whitespace issues in LaTeX backend - - - - - 85bc1fae by David Waern at 2010-07-01T15:42:45+00:00 Make runtest.hs work with GHC 6.12.3 (we should really stop hard coding this) - - - - - 7d2eb86f by David Waern at 2010-07-01T15:43:33+00:00 Update test following Simon's patch to render unresolved names in monospaced font - - - - - 08fcbcd2 by David Waern at 2010-07-01T16:12:18+00:00 Warning police - - - - - d04a8d7a by David Waern at 2010-07-04T14:53:39+00:00 Fix a bug in attachInstances We didn't look for instance docs in all the interfaces of the package. This had the effect of instance docs not always showing up under a declaration. I took the opportunity to clean up the code in H.I.AttachInstances a bit as well. More cleanup is needed, however. - - - - - d10344eb by Simon Hengel at 2010-07-10T09:19:04+00:00 Add missing dependencies to cabal file - - - - - 24090531 by Mark Lentczner at 2010-03-21T04:51:16+00:00 add exports to Xhtml modules - - - - - 84f9a333 by Mark Lentczner at 2010-04-03T19:14:22+00:00 clean up Doc formatting code - add CSS for lists - renderToString now uses showHtml since prettyHtml messes up <pre> sections - - - - - bebccf52 by Mark Lentczner at 2010-04-04T04:51:08+00:00 tweak list css - - - - - 0c2aeb5e by Mark Lentczner at 2010-04-04T06:24:14+00:00 all decls now generate Html not HtmlTable - ppDecl return Html, and so now do all of the functions it calls - added some internal tables to some decls, which is wrong, and will have to be fixed - decl "Box" functions became "Elem" functions to make clear they aren't in a table anymore (see Layout.hs) - docBox went away, as only used in one place (and its days are numbered) - cleaned up logic in a number of places, removed dead code - added maybeDocToHtml which simplified a number of places in the code - - - - - dbf73e6e by Mark Lentczner at 2010-04-05T05:02:43+00:00 clean up processExport and place a div around each decl - - - - - e25b7e9f by Mark Lentczner at 2010-04-10T21:23:21+00:00 data decls are now a sequence of paragraphs, not a table - - - - - 89ee0294 by Mark Lentczner at 2010-04-10T21:29:16+00:00 removed commented out code that can't be maintained - - - - - d466f536 by Mark Lentczner at 2010-04-12T04:56:27+00:00 removed declWithDoc and cleaned up data decls in summary - - - - - ed755832 by Mark Lentczner at 2010-04-12T05:07:53+00:00 merge in markupExample changes - - - - - c36f51fd by Mark Lentczner at 2010-04-25T04:56:37+00:00 made record fields be an unordList, not a table - - - - - ed3a28d6 by Mark Lentczner at 2010-04-25T05:23:28+00:00 fixed surround of instance and constructor tables - - - - - 0e35bbc4 by Mark Lentczner at 2010-04-25T05:36:59+00:00 fix class member boxes in summary - - - - - 5041749b by Mark Lentczner at 2010-04-25T05:38:35+00:00 remove unused bodyBox - - - - - e91724db by Mark Lentczner at 2010-04-25T06:26:10+00:00 fixed javascript quoting/escpaing issue - - - - - f4abbb73 by Mark Lentczner at 2010-05-03T23:04:31+00:00 adjust css for current markup - - - - - e75fec4c by Mark Lentczner at 2010-05-04T06:14:34+00:00 added assoicated types and methods back into class decls - - - - - 84169323 by Mark Lentczner at 2010-05-24T13:13:42+00:00 merge in changes from the big-whitespace cleanup - - - - - 3c1c872e by Mark Lentczner at 2010-06-11T21:03:58+00:00 adjust synopsis and bottom bar spacing - - - - - 3c1f9ef7 by Mark Lentczner at 2010-06-11T21:14:44+00:00 fix missing space in "module" lines in synoposis - - - - - 9a137e6d by Mark Lentczner at 2010-06-11T21:34:08+00:00 changed tt elements to code elements - - - - - 50f71ef1 by Mark Lentczner at 2010-06-11T23:27:46+00:00 factored out ppInstances - - - - - 3b9a9de5 by Mark Lentczner at 2010-06-17T17:36:01+00:00 push single constructors (newtype) onto line with decl - - - - - e0f8f2ec by Mark Lentczner at 2010-06-17T22:20:56+00:00 remove <++> connector - - - - - 56c075dd by Mark Lentczner at 2010-07-13T05:26:21+00:00 change to new page structure - - - - - 04be6ca7 by Mark Lentczner at 2010-07-14T04:21:55+00:00 constructors and args as dl lists, built in Layout.hs - - - - - 65aeafc2 by Mark Lentczner at 2010-07-14T05:38:32+00:00 better interface to subDecls - - - - - 72032189 by Mark Lentczner at 2010-07-14T07:04:10+00:00 made subDecl tables looks just so - - - - - b782eca2 by Mark Lentczner at 2010-07-14T16:00:54+00:00 convert args to SubDecl format - - - - - cc75e98f by Mark Lentczner at 2010-07-14T16:28:53+00:00 convert instances to SubDecl - - - - - 34e2aa5a by Mark Lentczner at 2010-07-14T21:07:32+00:00 removing old table cruft from Layout.hs - - - - - d5810d95 by Mark Lentczner at 2010-07-14T21:54:58+00:00 methods and associated types in new layout scheme - - - - - 65ef9579 by Mark Lentczner at 2010-07-14T23:43:42+00:00 clean up synopsis lists - - - - - e523318f by Mark Lentczner at 2010-07-15T05:02:26+00:00 clean up of anchors - - - - - 1215dfc5 by Mark Lentczner at 2010-07-15T23:53:01+00:00 added two new themes and rough css switcher - - - - - 7f0fd36f by Mark Lentczner at 2010-07-16T04:57:38+00:00 fixed package catpion, added style menu - - - - - 0dd4999c by Mark Lentczner at 2010-07-16T20:12:39+00:00 new output for mini_ pages - - - - - 64b2810b by Mark Lentczner at 2010-07-16T20:58:41+00:00 reformat index-frames - - - - - 3173f555 by Mark Lentczner at 2010-07-16T22:41:53+00:00 convert index to new markup - - - - - b0a4b7c9 by Mark Lentczner at 2010-07-17T04:07:22+00:00 convert index.html to new markup, adjust module markup - - - - - 8261ae1e by Mark Lentczner at 2010-07-17T05:07:29+00:00 classing styling of ancillary pages - - - - - 2a4fb025 by Mark Lentczner at 2010-07-17T05:11:45+00:00 clean up Layout.hs: no more vanillaTable - - - - - 87eec685 by Mark Lentczner at 2010-07-17T05:35:16+00:00 clean up Util.hs - - - - - d304e9b0 by Mark Lentczner at 2010-07-17T05:38:50+00:00 qualify import of XHtml as XHtml - - - - - 7dc05807 by Mark Lentczner at 2010-07-17T06:17:53+00:00 factored out head element generation - - - - - 9cdaec9e by Mark Lentczner at 2010-07-17T06:44:54+00:00 refactored out main page body generation - - - - - 8a51019e by Mark Lentczner at 2010-07-17T06:48:20+00:00 moved footer into only place that used it - - - - - efa479da by Mark Lentczner at 2010-07-17T18:48:30+00:00 styling auxillary pages for tibbe and snappy themes - - - - - 81de5509 by Mark Lentczner at 2010-07-18T04:41:38+00:00 fixed alphabet on index page, and styling of it and packages in module lists - - - - - 20718c1a by Mark Lentczner at 2010-07-18T05:34:29+00:00 cleaned up div functions in Layout.hs - - - - - 60d50453 by Mark Lentczner at 2010-07-18T05:48:39+00:00 added content div to main pages - - - - - ed16561c by Mark Lentczner at 2010-07-18T06:12:22+00:00 add .doc class to documentation blocks - - - - - f5c781b0 by Mark Lentczner at 2010-07-19T05:20:53+00:00 refactoring of anchor ID and fragment handling - - - - - a69a93bf by Mark Lentczner at 2010-07-19T05:35:55+00:00 remove an explicit bold tag - replace with .def class - - - - - d76c7225 by Mark Lentczner at 2010-07-19T06:56:15+00:00 rename Haddock.Backends.Xhtml.Util to Utils - - - - - 5a58c0da by David Waern at 2010-07-21T13:30:54+00:00 Remove trailing whitespace in Haddock.Backends.Xhtml - - - - - 0652aa17 by David Waern at 2010-07-21T13:33:21+00:00 Align a few comments - - - - - 785776c3 by David Waern at 2010-07-21T13:39:04+00:00 Remove trailing whitespace in H.B.X.Decl - - - - - 71a30710 by David Waern at 2010-07-21T13:44:27+00:00 Remove more trailing whitespace - - - - - 38750394 by David Waern at 2010-07-21T13:50:43+00:00 Style police - - - - - 3023d940 by David Waern at 2010-07-21T14:01:22+00:00 Style police in H.B.X.Decl - - - - - df16e9e6 by David Waern at 2010-07-21T14:14:45+00:00 Style police in H.B.X.DocMarkup - - - - - 6020e321 by David Waern at 2010-07-21T14:17:32+00:00 More style police - - - - - 86ad8bf5 by David Waern at 2010-07-21T14:21:02+00:00 Style police in H.B.Xhtml - - - - - aea27d03 by David Waern at 2010-07-21T14:42:03+00:00 Fix warnings in LaTeX backend - - - - - 2aff34a9 by David Waern at 2010-07-21T14:50:46+00:00 Style police in LaTeX backend (mainly more newlines) - - - - - e517162d by David Waern at 2010-07-21T15:05:47+00:00 Doc sections in Main - - - - - b971aa0c by David Waern at 2010-07-21T15:06:17+00:00 Trailing whitespace in Documentation.Haddock - - - - - f11628fb by David Waern at 2010-07-21T15:07:06+00:00 Trailing whitespace in Haddock.Convert - - - - - cbaf284c by David Waern at 2010-07-21T15:08:11+00:00 Style police in Haddock.GhcUtils - - - - - 71feb77b by David Waern at 2010-07-21T15:09:06+00:00 Style police in Haddock.InterfaceFile - - - - - 0a9c80e6 by David Waern at 2010-07-21T15:11:33+00:00 Whitespace police - - - - - 6168376c by David Waern at 2010-07-21T15:16:35+00:00 Style police in Haddock.Utils - - - - - 9fe4dd90 by David Waern at 2010-07-21T15:19:31+00:00 Add -fwarn-tabs - - - - - a000d752 by Mark Lentczner at 2010-07-20T17:25:52+00:00 move CSS Theme functions into Themes.hs - - - - - b52b440f by Mark Lentczner at 2010-07-20T17:29:35+00:00 add Thomas Schilling's theme - - - - - e43fa7e8 by Mark Lentczner at 2010-07-21T04:49:34+00:00 correct icon used with Snappy theme - - - - - ba5092d3 by Mark Lentczner at 2010-07-21T04:56:47+00:00 apply Tibbe's updates to his theme - - - - - 7804eef6 by Mark Lentczner at 2010-07-21T05:15:49+00:00 space between "Style" and the downward triangle - - - - - 7131d4c6 by Mark Lentczner at 2010-07-21T17:43:35+00:00 merge with David's source cleanups - - - - - ee65f1cb by David Waern at 2010-07-22T16:50:46+00:00 Fix a bug where we allowed --hoogle, --latex, etc without input files - - - - - e413ff7a by David Waern at 2010-07-22T17:21:58+00:00 Improve function name - - - - - a0fd14f3 by Simon Marlow at 2010-06-30T15:34:32+00:00 fix warnings - - - - - 31f73d2a by David Waern at 2010-07-22T19:29:41+00:00 Solve conflicts - - - - - d563b4a5 by Simon Marlow at 2010-06-30T15:34:37+00:00 fix warning - - - - - 412b6469 by David Waern at 2010-07-22T19:31:28+00:00 Solve conflict - - - - - 35174b94 by Ian Lynagh at 2010-07-06T17:27:16+00:00 Follow mkPState argument order change - - - - - b5c3585c by Simon Marlow at 2010-07-14T08:49:21+00:00 common up code for instance rendering - - - - - d8009560 by Simon Marlow at 2010-07-14T12:37:11+00:00 fix warnings - - - - - a6d88695 by David Waern at 2010-07-24T15:33:33+00:00 Fix build with ghc < 6.13 - - - - - 94cf9de1 by David Waern at 2010-07-24T15:34:37+00:00 Remove conflict left-over - - - - - 313b15c0 by Mark Lentczner at 2010-07-21T22:09:04+00:00 reorganization of nhaddock.css with tibbe - - - - - 9defed80 by Mark Lentczner at 2010-07-21T22:42:14+00:00 further cleanup of nhaddock.css, float TOC, support aux. pages - - - - - 6d944c1b by Mark Lentczner at 2010-07-22T06:22:23+00:00 remove old HTML backend - - - - - b3e8cba5 by Mark Lentczner at 2010-07-22T06:43:32+00:00 remove --html-help support - it was old, out-of-date, and mostly missing - - - - - d2654a08 by Mark Lentczner at 2010-07-22T21:45:34+00:00 tweaks to nhaddock.css - - - - - f73b285c by Mark Lentczner at 2010-07-23T06:19:35+00:00 command like processing for theme selection The bulk of the change is threadnig the selected theme set through functions in Xhtml.hs so that the selected themes can be used when generating the page output. There isn't much going on in most of these changes, just passing it along. The real work is all done in Themes.hs. - - - - - 8bddc90d by Mark Lentczner at 2010-07-23T06:58:31+00:00 drop --themes support, add named theme support decided that --themes was silly - no one would do that, just use multiple --theme arguments made --theme a synonym for --css and -c made those arguments, if no file is found, look up the argument as the name of a built in theme all of this let's haddock be invoked with "--theme=classic" for example. - - - - - 20cafd4f by Mark Lentczner at 2010-07-23T17:44:29+00:00 rename --default-themes to --built-in-themes - - - - - 0fe41307 by Mark Lentczner at 2010-07-23T18:33:02+00:00 tweaks to theme for info table, headings, and tables - - - - - cba4fee0 by Mark Lentczner at 2010-07-23T19:13:59+00:00 tweaks for dl layout, though still not used - - - - - 463fa294 by Mark Lentczner at 2010-07-23T21:07:19+00:00 tweak look of mini pages, keywords, and preblocks - - - - - 5472fc02 by Mark Lentczner at 2010-07-24T05:36:15+00:00 slide out Synopsis drawer - - - - - 9d5d5de5 by Mark Lentczner at 2010-07-24T06:02:42+00:00 extend package header and footer to edges of page - - - - - a47c91a2 by Mark Lentczner at 2010-07-24T06:28:44+00:00 fields are def lists, tweak css for style menu, mini pages, arguments - - - - - ca20f23b by Mark Lentczner at 2010-07-24T16:55:22+00:00 excisting last vestiges of the --xhtml flag - - - - - 71fb012e by Mark Lentczner at 2010-07-25T18:47:49+00:00 change how collapsing sections are done make whole .caption be the target improve javascript for class toggling have plus/minus images come from .css, not img tags - - - - - c168c8d3 by Mark Lentczner at 2010-07-26T00:32:05+00:00 reorganize files in the html lib data dir - - - - - 93324301 by Mark Lentczner at 2010-07-26T01:27:42+00:00 cleaned up Themes.hs - - - - - ad3b5dd4 by Mark Lentczner at 2010-07-26T02:39:15+00:00 make module list use new collapsers - - - - - 1df9bfc6 by Mark Lentczner at 2010-07-27T19:09:25+00:00 remove Tibbe theme - - - - - 8b9b01b3 by Mark Lentczner at 2010-07-27T20:04:03+00:00 move themes into html dir with .theme and .std-theme extensions - - - - - a7beb965 by Mark Lentczner at 2010-07-27T21:06:34+00:00 give a class to empty dd elements so they can be hidden - - - - - a258c117 by Mark Lentczner at 2010-07-27T21:23:58+00:00 remove custom version of copyFile in Xhtml.hs - - - - - b70dba6e by Mark Lentczner at 2010-07-27T22:12:45+00:00 apply margin changes to pre and headings as per group decision, and small cleanups - - - - - e6f722a2 by Mark Lentczner at 2010-07-28T00:03:12+00:00 make info block and package bar links be floatable by placing them first in the dom tree - - - - - c8278867 by Mark Lentczner at 2010-07-28T19:01:18+00:00 styling source links on declarations - - - - - 88fdc399 by Mark Lentczner at 2010-07-29T01:12:46+00:00 styling tweaks don't generate an empty li for absent style menu in links area update css for Classic and Snappy to handle: dl lists links in package header and in declarations floating of links and info block in package and module headers - - - - - 8a75b213 by Ian Lynagh at 2010-07-30T20:21:46+00:00 Fix build in GHC tree - - - - - ce8e18b3 by Simon Hengel at 2010-08-03T18:37:26+00:00 Adapt paths to data files in cabal file - - - - - 9701a455 by Simon Hengel at 2010-08-07T13:20:27+00:00 Add missing dependency to cabal file - - - - - 01b838d1 by Mark Lentczner at 2010-07-30T20:19:40+00:00 improved synopsis drawer: on click, not hover - - - - - 7b6f3e59 by Mark Lentczner at 2010-07-30T23:38:55+00:00 put the synopsis back in the other themes - - - - - 7b2904c9 by Mark Lentczner at 2010-08-11T11:11:26+00:00 close arrows on expanded synopsis drawer - - - - - ea19e177 by Mark Lentczner at 2010-08-12T21:16:45+00:00 width and font changes removed the max width restrictions on the page as a whole and the synopsis made the main font size smaller (nominally 14pt) and then tweaked most font sizes (relative) to be more consistent - - - - - 5ced00c0 by Mark Lentczner at 2010-08-13T15:09:55+00:00 implemented YUI's CSS font approach - - - - - 2799c548 by Mark Lentczner at 2010-08-13T15:11:59+00:00 adjusted margin to 2em, 1 wasn't enough - - - - - 58f06893 by Mark Lentczner at 2010-08-13T15:48:44+00:00 removed underlining on hover for named anchors headings in interface lost thier a element, no need, just put id on heading css for a elements now only applies to those with href attribute - - - - - 7aced4c4 by Mark Lentczner at 2010-08-13T15:50:22+00:00 more space between elements - - - - - 5a3c1cce by Mark Lentczner at 2010-08-13T16:43:43+00:00 adjusted font sizes of auxilary pages per new scheme - - - - - 487539ef by Mark Lentczner at 2010-08-13T21:43:41+00:00 add Frames button and clean up frames.html - - - - - c1a140b6 by Mark Lentczner at 2010-08-13T22:17:48+00:00 move frames button to js - - - - - b0bdb68e by Mark Lentczner at 2010-08-14T03:44:46+00:00 build style menu in javascript moved to javascript, so as to not polute the content with the style menu removed menu building code in Themes.hs removed onclick in Utils.hs changed text of button in header from "Source code" to "Source" more consistent with links in rest of page - - - - - 43ab7120 by Mark Lentczner at 2010-08-16T15:15:37+00:00 font size and margin tweaks - - - - - c0b68652 by Mark Lentczner at 2010-08-17T18:19:52+00:00 clean up collapser logics javascript code for collapasble sections cleaned up rewrote class utilities in javascript to be more robust refactored utilities for generating collapsable sections made toc be same color as synopsis module list has needed clear attribute in CSS - - - - - 5d573427 by Mark Lentczner at 2010-08-17T23:06:02+00:00 don't collapse entries in module list when clicking on links - - - - - 8c307c4a by Mark Lentczner at 2010-08-17T23:21:43+00:00 add missing data file to .cabal - - - - - 414bcfcf by Mark Lentczner at 2010-08-17T23:28:47+00:00 remove synopsis when in frames - - - - - ba0fa98a by Mark Lentczner at 2010-08-18T16:16:11+00:00 layout tweeks - mini page font size, toc color, etc. - - - - - 63c1bed1 by Mark Lentczner at 2010-08-18T19:50:02+00:00 margin fiddling - - - - - c311c094 by Mark Lentczner at 2010-08-20T01:37:55+00:00 better synopsis handling logic - no flashing - - - - - f1fe5fa8 by Mark Lentczner at 2010-08-20T01:41:06+00:00 fix small layout issues mini frames should have same size top heading give info block dts some padding so they don't collide in some browsers - - - - - 0de84d77 by Mark Lentczner at 2010-08-20T02:13:09+00:00 made style changing and cookies storage robust - - - - - 1ef064f9 by Thomas Schilling at 2010-08-04T13:12:22+00:00 Make synopsis frame behave properly in Firefox. In Firefox, pressing the back button first reverted the synopsis frame, and only clicking the back button a second time would update the main frame. - - - - - dd1c9a94 by Mark Lentczner at 2010-08-21T01:46:19+00:00 remove Snappy theme - - - - - 2353a90d by Mark Lentczner at 2010-08-25T05:16:19+00:00 fix occasional v.scroll bars on pre blocks (I think) - - - - - 459b8bf1 by Simon Hengel at 2010-08-08T10:12:45+00:00 Add createInterfaces' (a more high-level alternative to createInterfaces) to Haddock API - - - - - b1b68675 by David Waern at 2010-08-26T20:31:58+00:00 Follow recent API additions with some refactorings Simon Hegel's patch prompted me to do some refactorings in Main, Haddock.Documentation and Haddock.Interface. - - - - - 264d4d67 by David Waern at 2010-08-26T21:40:59+00:00 Get rid of GhcModule and related cruft We can get everything we need directly from TypecheckedModule. - - - - - 0feacec2 by Mark Lentczner at 2010-08-26T23:44:13+00:00 fixed CSS for ordered lists and def lists in doc blocks - - - - - 2997e0c2 by Mark Lentczner at 2010-08-26T23:45:03+00:00 support both kinds of enumerated lists in doc markup The documentation for Haddock says enumerated lists can use either of (1) first item 2. second item The second form wasn't actually supported - - - - - 5d4ddeec by Mark Lentczner at 2010-08-27T21:29:48+00:00 fix broken header link margins - - - - - 614456ba by Mark Lentczner at 2010-08-27T22:16:19+00:00 fix table of contents CSS - - - - - 03f329a2 by David Waern at 2010-08-28T16:36:09+00:00 Update tests following switch to the Xhtml backend - - - - - ca689fa2 by Mark Lentczner at 2010-08-28T18:25:16+00:00 fix def lists - - - - - 18e1d3d2 by Mark Lentczner at 2010-08-28T18:26:18+00:00 push footer to bottom of window - - - - - b0ab8d82 by David Waern at 2010-08-28T22:04:32+00:00 Whitespace police - - - - - 2d217977 by David Waern at 2010-08-29T12:44:45+00:00 Remove Snappy data files - - - - - 01e27d5f by David Waern at 2010-08-29T13:03:28+00:00 Add source entity path to --read-interface You can now use this flag like this: --read-interface=<html path>,<source entity path>,<.haddock file> By "source entity path" I mean the same thing that is specified with the --source-entity flag. The purpose of this is to be able to specify the source entity path per package, to allow source links to work in the presence of cross-package documentation. When given two arguments or less the --read-interface flag behaves as before. - - - - - 20bf4aaa by David Waern at 2010-08-29T13:11:03+00:00 Naming wibbles - - - - - ad22463f by Mark Lentczner at 2010-08-29T15:14:54+00:00 make portability block be a table - solves layout issues - - - - - 97bd1ae6 by Mark Lentczner at 2010-08-29T15:17:42+00:00 update golden test for Test due to portability box change - - - - - d37e139e by Mark Lentczner at 2010-08-29T17:07:17+00:00 move TOC and Info blocks down 0.5em to improve layout issue w/Test.hs - - - - - acf52501 by David Waern at 2010-08-29T17:32:36+00:00 Allow building with ghc < 6.16 - - - - - 1cb34ed8 by Ian Lynagh at 2010-07-24T23:18:49+00:00 Flatten the dynflags before parsing - - - - - b36845b4 by Ian Lynagh at 2010-07-24T23:26:49+00:00 Follow flattenLanguageFlags -> flattenExtensionFlags rename - - - - - 7f7fcc7e by David Waern at 2010-08-29T17:46:23+00:00 Use flattenExtensionFlags with ghc >= 6.13 only - - - - - 13cf9411 by Ian Lynagh at 2010-08-01T18:09:54+00:00 Make the main haddock script versioned, and make plain "haddock" a symlink - - - - - 495cbff2 by Ian Lynagh at 2010-08-18T18:57:24+00:00 Fix installation in the GHC build system Data-files are now in subdirectories, so we need to handle that - - - - - 88ebab0a by Ian Lynagh at 2010-08-18T19:43:53+00:00 GHC build system: Add all the data files to BINDIST_EXTRAS - - - - - 65837172 by David Waern at 2010-08-29T20:12:34+00:00 Update Test - - - - - 094bbaa2 by David Waern at 2010-08-29T20:55:14+00:00 Revert update to Test - - - - - a881cfb3 by David Waern at 2010-08-31T18:24:15+00:00 Bump version number - - - - - 1fc8a3eb by David Waern at 2010-08-31T22:32:27+00:00 Update ANNOUNCE - - - - - ee1df9d0 by David Waern at 2010-08-31T22:33:11+00:00 Update CHANGES - - - - - 394cc854 by David Waern at 2010-08-31T22:33:23+00:00 Update interface file versioning to work with ghc 6.14/15 - - - - - 7d03b79b by David Waern at 2010-08-31T22:36:00+00:00 Update test output following version change - - - - - a48d82d1 by Mark Lentczner at 2010-09-01T04:29:35+00:00 sort options in doc to match --help output removed --html-help option, as it is no longer supported - - - - - 06561aeb by Mark Lentczner at 2010-09-01T05:29:32+00:00 update options documentation rewrote doc for --html added doc for --theme and --built-in-themes added --use-contents and --gen-contents - - - - - 57dea832 by Mark Lentczner at 2010-09-01T05:31:27+00:00 slight wording change about Frames mode - - - - - fa1f6da3 by David Waern at 2010-09-01T10:57:44+00:00 Update doc configure script to find docbook stylesheets on arch linux - - - - - addff770 by David Waern at 2010-09-01T11:02:29+00:00 Wibble - - - - - 8399006d by David Waern at 2010-09-01T11:19:21+00:00 Replace ghci> with >>> in example syntax - - - - - 35074cf8 by David Waern at 2010-09-01T19:03:27+00:00 Improve docs for --no-tmp-comp-dir - - - - - 0f8f8cfd by David Waern at 2010-09-02T11:22:27+00:00 Add a list of contributors to the user guide Break out everyone thanked in the `Acknowledgements` chapter into a separate contributor list and add everyone from `darcs show authors`. We consider everyone who is thanked to be a contributor as a conservative estimation :-) I have added some more contributors that I know about, who were not in the darcs history, but others may be missing. So please add anyone that you think is missing from the list. - - - - - 42ccf099 by David Waern at 2010-09-02T11:29:22+00:00 Update copyright years in license - - - - - 0d560479 by David Waern at 2010-09-02T11:38:52+00:00 Update release instructions - - - - - 72ab7796 by David Waern at 2010-09-02T19:27:08+00:00 Add a note to ANNOUNCE - - - - - bf9d9c5d by David Waern at 2010-09-02T19:27:48+00:00 H.Utils needs FFI on Win+MinGW - - - - - 048ae44a by Mark Lentczner at 2010-09-04T23:19:47+00:00 make TOC group header identifiers validate - - - - - 8c6faf36 by Simon Michael at 2010-09-22T07:12:34+00:00 add hints for cleaner darcs show authors output - - - - - 9909bd17 by Simon Michael at 2010-09-22T17:58:06+00:00 print haddock coverage info on stdout when generating docs A module's haddockable items are its exports and the module itself. The output is lightly formatted so you can align the :'s and sort for readability. - - - - - 6da72171 by David Waern at 2010-10-03T21:31:24+00:00 Style wibble - - - - - 2f8d8e4d by Tobias Brandt at 2010-08-27T07:01:21+00:00 adding the option to fully qualify identifiers - - - - - 833be6c6 by Tobias Brandt at 2010-08-27T15:50:28+00:00 adding support for local and relative name qualification - - - - - df15c4e9 by Tobias Brandt at 2010-08-27T15:56:37+00:00 corrected qualification help message - - - - - 449e9ce1 by David Waern at 2010-10-16T17:34:30+00:00 Solve conflicts - - - - - 3469bda5 by David Waern at 2010-10-16T18:42:40+00:00 Use "qual" as an abbreviation for qualification instead of "quali" for consistency - - - - - 97c2d728 by David Waern at 2010-10-16T18:47:07+00:00 Style police - - - - - ce14fbea by David Waern at 2010-10-16T21:15:25+00:00 Style police - - - - - fdf29e9d by David Waern at 2010-10-17T00:30:44+00:00 Add a pointer to the style guide - - - - - 8e6b44e8 by rrnewton at 2010-10-24T03:19:28+00:00 Change to index pages: include an 'All' option even when subdividing A-Z. - - - - - 755b131c by David Waern at 2010-11-14T19:39:36+00:00 Bump version - - - - - d0345a04 by David Waern at 2010-11-14T19:41:59+00:00 TAG 2.8.1 - - - - - f6221508 by Simon Peyton Jones at 2010-09-13T09:53:00+00:00 Adapt to minor changes in internal GHC functions - - - - - 1290713d by Ian Lynagh at 2010-09-15T10:37:18+00:00 Remove duplicate Outputable instance for Data.Map.Map - - - - - 87f69eef by Ian Lynagh at 2010-09-21T15:01:10+00:00 Bump GHC dep upper bound - - - - - af36e087 by Ian Lynagh at 2010-09-21T15:12:02+00:00 Fix up __GLASGOW_HASKELL__ tests - - - - - ad67716c by Ian Lynagh at 2010-09-21T20:31:35+00:00 Don't build haddock is HADDOCK_DOCS is NO - - - - - 63b3f1f5 by Ian Lynagh at 2010-09-21T21:39:51+00:00 Fixes for when HADDOCK_DOCS=NO - - - - - e92bfa42 by Ian Lynagh at 2010-09-29T21:15:38+00:00 Fix URL creation on Windows: Use / not \ in URLs. Fixes haskell/haddock#4353 - - - - - 66c55e05 by Ian Lynagh at 2010-09-30T17:03:34+00:00 Tidy up haddock symlink installation In particular, it now doesn't get created if we aren't installing haddock. - - - - - 549b5556 by Ian Lynagh at 2010-10-23T21:17:14+00:00 Follow extension-flattening change in GHC - - - - - d7c2f72b by David Waern at 2010-11-14T20:17:55+00:00 Bump version to 2.8.2 - - - - - 6989a3a9 by David Waern at 2010-11-14T20:26:01+00:00 Solve conflict - - - - - 055c6910 by Ian Lynagh at 2010-09-22T15:36:20+00:00 Bump GHC dep - - - - - c96c0763 by Simon Marlow at 2010-10-27T11:09:44+00:00 follow changes in the GHC API - - - - - 45907129 by David Waern at 2010-11-07T14:00:58+00:00 Update the HCAR entry - - - - - 61940b95 by David Waern at 2010-11-07T14:07:34+00:00 Make the HCAR entry smaller - - - - - aa590b7d by David Waern at 2010-11-14T21:30:59+00:00 Update HCAR entry with November 2010 version - - - - - 587f9847 by David Waern at 2010-11-14T23:48:17+00:00 Require ghc >= 7.0 - - - - - ff5c647c by David Waern at 2010-11-14T23:49:09+00:00 TAG 2.8.2 - - - - - 937fcb4f by David Waern at 2010-11-14T23:49:45+00:00 Solve conflict - - - - - 8e5d0c1a by David Waern at 2010-11-15T21:09:50+00:00 Remove code for ghc < 7 - - - - - 3d47b70a by David Waern at 2010-11-15T21:11:06+00:00 Fix bad merge - - - - - 7f4a0d8a by David Waern at 2010-11-15T21:13:57+00:00 Remove more ghc < 7 code - - - - - 9ee34b50 by David Waern at 2010-11-15T21:31:25+00:00 Match all AsyncExceptions in exception handler - - - - - 42849c70 by David Waern at 2010-11-15T21:35:31+00:00 Just say "internal error" instead of "internal Haddock or GHC error" - - - - - c88c809b by David Waern at 2010-11-15T21:44:19+00:00 Remove docNameOcc under the motto "don't name compositions" - - - - - b798fc7c by David Waern at 2010-11-15T23:27:13+00:00 Wibble - - - - - 2228197e by David Waern at 2010-11-15T23:28:24+00:00 Rename the HCAR entry file - - - - - 8a3f9090 by David Waern at 2010-11-16T00:05:29+00:00 Remove Haskell 2010 extensions from .cabal file - - - - - c7a0c597 by David Waern at 2010-11-16T00:10:28+00:00 Style wibbles - - - - - cde707a5 by David Waern at 2010-11-16T00:12:00+00:00 Remove LANGUAGE ForeignFunctionInterface pragmas - - - - - 1dbda8ed by David Waern at 2010-11-16T00:17:21+00:00 Make a little more use of DoAndIfThenElse - - - - - 4c45ff6e by David Waern at 2010-11-16T00:59:41+00:00 hlint police - - - - - d2feaf09 by David Waern at 2010-11-16T01:14:15+00:00 hlint police - - - - - 99876e97 by David Waern at 2010-11-20T19:06:00+00:00 Haddock documentation updates - - - - - 65ce6987 by David Waern at 2010-11-20T19:42:51+00:00 Follow the style guide closer in Haddock.Types and improve docs - - - - - 28ca304a by tob.brandt at 2010-11-20T17:04:40+00:00 add full qualification for undocumented names - - - - - d61341e3 by David Waern at 2010-11-20T20:04:15+00:00 Re-structure qualification code a little - - - - - 0057e4d6 by David Waern at 2010-11-20T20:07:55+00:00 Re-order functions - - - - - d7279afd by David Waern at 2010-11-21T03:39:54+00:00 Add BangPatterns to alex and happy source files - - - - - 629fe60e by tob.brandt at 2010-11-23T23:35:11+00:00 documentation for qualification - - - - - 37031cee by David Waern at 2010-11-23T21:06:44+00:00 Update CHANGES - don't mention 2.8.2, we won't release it - - - - - f2489e19 by David Waern at 2010-12-01T21:57:11+00:00 Update deps of runtests.hs to work with ghc 7.0.1 - - - - - d3657e9a by David Waern at 2010-12-01T22:04:57+00:00 Make tests compile with ghc 7.0.1 - - - - - a2f09d9b by David Waern at 2010-12-01T22:06:59+00:00 Update tests following version bump - - - - - 50883ebb by David Waern at 2010-12-06T14:09:18+00:00 Update tests following recent changes - - - - - fc2fadeb by David Waern at 2010-12-06T14:17:29+00:00 Add a flag --pretty-html for rendering indented html with newlines - - - - - 30832ef2 by David Waern at 2010-12-06T14:17:35+00:00 Use --pretty-html when running the test suite. Makes it easier to compare output - - - - - a0b81b31 by David Waern at 2010-12-06T14:18:27+00:00 Wibble - - - - - 3aaa23fe by David Waern at 2010-12-06T14:19:29+00:00 Haddockify ppHtml comments - - - - - 24bb24f0 by David Waern at 2010-12-06T14:23:15+00:00 Remove --debug. It was't used, and --verbosity should take its place - - - - - 6bc076e5 by David Waern at 2010-12-06T14:25:37+00:00 Rename golden-tests into html-tests. "golden tests" sounds strange - - - - - 53301e55 by David Waern at 2010-12-06T14:26:26+00:00 QUALI -> QUAL in the description --qual for consistency - - - - - 98b6affb by David Waern at 2010-12-06T21:54:02+00:00 Bump version - - - - - 371bf1b3 by David Waern at 2010-12-06T22:08:55+00:00 Update tests following version bump - - - - - 25be762d by David Waern at 2010-12-06T22:21:03+00:00 Update CHANGES - - - - - 7c7dac71 by David Waern at 2010-12-06T22:33:43+00:00 Update ANNOUNCE - - - - - 30d7a5f2 by Simon Peyton Jones at 2010-11-15T08:38:38+00:00 Alex generates BangPatterns, so make Lex.x accept them (It'd be better for Alex to generate this pragma.) - - - - - 605e8018 by Simon Marlow at 2010-11-17T11:37:24+00:00 Add {-# LANGUAGE BangPatterns #-} to mollify GHC - - - - - a46607ba by David Waern at 2010-12-07T14:08:10+00:00 Solve conflicts - - - - - b28cda66 by David Waern at 2010-12-09T20:41:35+00:00 Docs: Mention that \ is a special character in markup - - - - - a435bfdd by Ian Lynagh at 2010-11-17T14:01:19+00:00 TAG GHC 7.0.1 release - - - - - 5a15a05a by David Waern at 2010-12-11T17:51:19+00:00 Fix indentation problem - - - - - 4232289a by Lennart Kolmodin at 2010-12-17T18:32:03+00:00 Revise haddock.cabal given that we now require ghc-7 default-language should be Haskell2010, slight new semantics for extensions. Rewrite into clearer dependencies of base and Cabal. - - - - - a36302dc by David Waern at 2010-12-19T17:12:37+00:00 Update CHANGES - - - - - 7c8b85b3 by David Waern at 2010-12-19T17:14:24+00:00 Bump version - - - - - cff22813 by Ian Lynagh at 2011-01-05T18:24:27+00:00 Write hoogle output in utf8; fixes GHC build on Windows - - - - - c7e762ea by David Waern at 2011-01-22T00:00:35+00:00 Put title outside doc div when HTML:fying title+prologue Avoids indenting the title, and makes more sense since the title is not a doc string anyway. - - - - - 5f639054 by David Waern at 2011-01-22T16:09:44+00:00 Fix spelling error - contributed by Marco Silva - - - - - c11dce78 by Ian Lynagh at 2011-01-07T02:33:11+00:00 Follow GHC build system changes - - - - - 101cfaf5 by David Waern at 2011-01-08T14:06:44+00:00 Bump version - - - - - af62348b by David Waern at 2011-01-08T14:07:07+00:00 TAG 2.9.2 - - - - - 4d1f6461 by Ian Lynagh at 2011-01-07T23:06:57+00:00 Name the haddock script haddock-ghc-7.0.2 instead of haddock-7.0.2; haskell/haddock#4882 "7.0.2" looked like a haddock version number before - - - - - 8ee4d5d3 by Simon Peyton Jones at 2011-01-10T17:31:12+00:00 Update Haddock to reflect change in hs_tyclds field of HsGroup - - - - - 06f3e3db by Ian Lynagh at 2011-03-03T15:02:37+00:00 TAG GHC 7.0.2 release - - - - - 7de0667d by David Waern at 2011-03-10T22:47:13+00:00 Update CHANGES - - - - - 33a9f1c8 by David Waern at 2011-03-10T22:47:31+00:00 Fix build with ghc 7.0.1 - - - - - 4616f861 by David Waern at 2011-03-10T22:47:50+00:00 TAG 2.9.2-actual - - - - - 0dab5e3c by Simon Hengel at 2011-04-08T15:53:01+00:00 Set shell script for unit tests back to work - - - - - 85c54dee by Simon Hengel at 2011-04-08T16:01:24+00:00 Set unit tests back to work Here "ghci>" was still used instead of ">>>". - - - - - 1cea9b78 by Simon Hengel at 2011-04-08T16:25:36+00:00 Update runtests.hs for GHC 7.0.2 - - - - - 8e5b3bbb by Simon Hengel at 2011-04-08T16:28:49+00:00 Update Haddock version in *.html.ref - - - - - 2545e955 by Simon Hengel at 2011-04-08T17:09:28+00:00 Add support for blank lines in the result of examples Result lines that only contain the string "<BLANKLINE>" are treated as a blank line. - - - - - adf64d2e by Simon Hengel at 2011-04-08T17:36:50+00:00 Add documentation for "support for blank lines in the result of examples" - - - - - c51352ca by David Waern at 2011-05-21T23:57:56+00:00 Improve a haddock comment - - - - - 7419cf2c by David Waern at 2011-05-22T15:41:52+00:00 Use cabal's test suite support to run the test suite This gives up proper dependency tracking of the test script. - - - - - 7770070c by David Waern at 2011-05-22T01:45:44+00:00 We don't need to send DocOptions nor a flag to mkExportItems - - - - - 9d95b7b6 by David Waern at 2011-05-22T21:39:03+00:00 Fix a bug - - - - - 1f93699b by David Waern at 2011-05-22T21:40:21+00:00 Break out fullContentsOf, give it a better name and some documentation The documentation describes how we want this function to eventually behave, once we have fixed a few problems with the current implementation. - - - - - 9a86432f by David Waern at 2011-05-22T21:53:52+00:00 Fix some stylistic issues in mkExportItems - - - - - c271ff0c by David Waern at 2011-05-22T22:09:11+00:00 Indentation - - - - - 93e602b1 by David Waern at 2011-06-10T01:35:31+00:00 Add git commits since switchover: darcs format (followed by a conflict resolution): commit 6f92cdd12d1354dfbd80f8323ca333bea700896a Merge: f420cc4 28df3a1 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 19 17:54:34 2011 +0100 Merge remote branch 'origin/master' into ghc-generics commit 28df3a119f770fdfe85c687dd73d5f6712b8e7d0 Author: Max Bolingbroke <batterseapower at hotmail.com> Date: Sat May 14 22:37:02 2011 +0100 Unicode fix for getExecDir on Windows commit 89813e729be8bce26765b95419a171a7826f6d70 Merge: 6df3a04 797ab27 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 9 11:55:17 2011 +0100 Merge branch 'ghc-new-co' commit 6df3a040da3dbddee67c6e30a892f87e6b164383 Author: Ian Lynagh <igloo at earth.li> Date: Sun May 8 17:05:50 2011 +0100 Follow changes in SDoc commit f420cc48b9259f0b1afd2438b12f9a2bde57053d Author: Jose Pedro Magalhaes <jpm at cs.uu.nl> Date: Wed May 4 17:31:52 2011 +0200 Adapt haddock to the removal of HsNumTy and TypePat. commit 797ab27bdccf39c73ccad374fea265f124cb52ea Merge: 1d81436 5a91450 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:05:03 2011 +0100 Merge remote branch 'origin/master' into ghc-new-co commit 1d8143659a81cf9611668348e33fd0775c7ab1d2 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:03:46 2011 +0100 Wibbles for ghc-new-co branch commit 5a91450e2ea5a93c70bd3904b022445c9cc82488 Author: Ian Lynagh <igloo at earth.li> Date: Fri Apr 22 00:51:56 2011 +0100 Follow defaultDynFlags change in GHC - - - - - 498da5ae by David Waern at 2011-06-11T00:33:33+00:00 * Merge in git patch from Michal Terepeta >From 6fc71d067738ef4b7de159327bb6dc3d0596be29 Mon Sep 17 00:00:00 2001 From: Michal Terepeta <michal.terepeta at gmail.com> Date: Sat, 14 May 2011 19:18:22 +0200 Subject: [PATCH] Follow the change of TypeSig in GHC. This follows the change in GHC to make TypeSig take a list of names (instead of just one); GHC ticket haskell/haddock#1595. This should also improve the Haddock output in case the user writes a type signature that refers to many names: -- | Some comment.. foo, bar :: ... will now generate the expected output with one signature for both names. - - - - - 094607fe by Ian Lynagh at 2011-06-17T19:10:29+01:00 Fix build - - - - - 8fa35740 by Ian Lynagh at 2011-06-26T21:06:40+01:00 Bump GHC dep to allow 7.2 - - - - - e4d2ca3c by Ian Lynagh at 2011-07-07T23:06:28+01:00 Relax base dep - - - - - b948fde9 by Ian Lynagh at 2011-07-28T16:39:45+01:00 GHC build system: Don't install the datafiles twice - - - - - f82f6d70 by Simon Marlow at 2011-08-11T12:08:15+01:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - b341cc12 by Max Bolingbroke at 2011-08-22T20:25:27+01:00 Fix compilation with no-pred-ty GHC - - - - - 30494581 by Max Bolingbroke at 2011-08-23T10:20:54+01:00 Remaining fixes for PredTy removal - - - - - 0b197138 by Max Bolingbroke at 2011-08-26T08:27:45+01:00 Rename factKind to constraintKind - - - - - a379bec5 by Max Bolingbroke at 2011-09-04T12:54:47+01:00 Deal with change to IParam handling in GHC - - - - - f94e421b by Max Bolingbroke at 2011-09-06T17:34:31+01:00 Adapt Haddock for the ConstraintKind extension changes - - - - - 8821e5cc by Max Bolingbroke at 2011-09-09T08:24:59+01:00 Ignore associated type defaults (just as we ignore default methods) - - - - - 31a0afd4 by Max Bolingbroke at 2011-09-09T09:06:00+01:00 Merge branch 'no-pred-ty' of ssh://darcs.haskell.org/srv/darcs/haddock into no-pred-ty - - - - - dd3b530a by Max Bolingbroke at 2011-09-09T14:10:25+01:00 Merge branch 'no-pred-ty' Conflicts: src/Haddock/Convert.hs - - - - - 5f25ec96 by Max Bolingbroke at 2011-09-09T14:10:40+01:00 Replace FactTuple with ConstraintTuple - - - - - cd30b9cc by David Waern at 2011-09-26T02:17:55+02:00 Bump to version 2.9.3 - - - - - 4fbfd397 by Max Bolingbroke at 2011-09-27T14:55:21+01:00 Follow changes to BinIface Name serialization - - - - - 92257d90 by David Waern at 2011-09-30T23:45:07+02:00 Fix problem with test files not added to distribution tarball - - - - - 00255bda by David Waern at 2011-09-30T23:48:24+02:00 Merge branch 'development' - - - - - 5421264f by David Waern at 2011-10-01T01:25:39+02:00 Merge in darcs patch from Simon Meier: Wed Jun 1 19:41:16 CEST 2011 iridcode at gmail.com * prettier haddock coverage info The new coverage info rendering uses less horizontal space. This reduces the number of unnecessary line-wrappings. Moreover, the most important information, how much has been documented already, is now put up front. Hopefully, this makes it more likely that a library author is bothered by the low coverage of his modules and fixes that issue ;-) - - - - - 07d318ef by David Waern at 2011-10-01T01:34:10+02:00 Use printException instead of deprecated printExceptionAndWarnings - - - - - 40d52ee4 by David Waern at 2011-10-01T01:41:13+02:00 Merge in darcs pach: Mon Apr 11 18:09:54 JST 2011 Liyang HU <haddock at liyang.hu> * Remember collapsed sections in index.html / haddock-util.js - - - - - 279d6dd4 by David Waern at 2011-10-01T01:55:45+02:00 Merge in darcs patch: Joachim Breitner <mail at joachim-breitner.de>**20110619201645 Ignore-this: f6c51228205b0902ad5bfad5040b989a As reported on http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=578301, generating the global index takes much too long if type-level (with lots of auto-generated types) is installed. The patch avoids a quadratic runtime in the subfunction getIfaceIndex of ppHtmlIndex by using a temporary set. Runtime improvement observed here from 25.36s to 2.86s. - - - - - d1612383 by David Waern at 2011-10-01T01:56:48+02:00 Merge branch 'development' - - - - - 347520c1 by David Waern at 2011-10-01T01:56:54+02:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9a0c95e8 by David Waern at 2011-10-01T02:19:10+02:00 Improve .cabal file - - - - - 6967dc64 by Ian Lynagh at 2011-10-01T01:34:06+01:00 Follow changes to ForeignImport/ForeignExport in GHC - - - - - 565cb26b by Simon Marlow at 2011-10-04T00:15:04+02:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - 8b74f512 by David Waern at 2011-10-04T00:18:17+02:00 Requre ghc >= 7.2 - - - - - 271d360c by David Waern at 2011-10-04T00:22:50+02:00 Bump version to 2.9.4 - - - - - 37f3edb0 by David Waern at 2011-10-06T02:30:21+02:00 Add alex and happy to build-tools. - - - - - 7ac2bb6e by David Terei at 2011-10-12T14:02:55-07:00 Add safe haskell indication to haddock output - - - - - 42c91a47 by David Terei at 2011-10-12T14:06:03-07:00 Fix CSS issue with info table not being contained in module header - - - - - 0eddab6c by David Terei at 2011-10-12T14:06:58-07:00 Add safe haskell indication to haddock output - - - - - 3df058eb by David Terei at 2011-10-12T14:07:07-07:00 Fix CSS issue with info table not being contained in module header - - - - - a40a6c3f by David Waern at 2011-10-22T11:29:06+02:00 Bump .haddock file version since the format has changed recently - - - - - 8a6254be by David Waern at 2011-10-22T11:30:42+02:00 Merge branch 'development' - - - - - 642e3e02 by David Waern at 2011-10-23T21:23:39+02:00 Sort import list - - - - - 36371cf8 by David Waern at 2011-10-23T22:48:18+02:00 Remove NEW_GHC_LAYOUT conditional. - - - - - 5604b499 by David Waern at 2011-10-27T00:15:03+02:00 Add --print-ghc-path. - - - - - 463499fa by David Waern at 2011-10-27T00:16:22+02:00 Make testsuite able to find its dependencies automatically. - - - - - a3506172 by Ryan Newton at 2011-11-05T05:59:58-04:00 Improved declNames internal error. Added a case to handle DocD. - - - - - 001b8baf by David Waern at 2011-11-05T20:37:29+01:00 Rename copy.hs -> accept.hs. - - - - - 55d808d3 by David Waern at 2011-11-05T23:30:02+01:00 Fix build. - - - - - deb5c3be by David Waern at 2011-11-06T00:01:47+01:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9b663554 by David Waern at 2011-11-06T00:03:45+01:00 Merge https://github.com/rrnewton/haddock - - - - - 1abb0ff6 by David Waern at 2011-11-06T01:20:37+01:00 Use getDeclMainBinder instead of declNames. - - - - - 4b005c01 by David Waern at 2011-11-06T19:09:53+01:00 Fix build. - - - - - c2c51bc7 by Ian Lynagh at 2011-11-06T23:01:33+00:00 Remove -DNEW_GHC_LAYOUT in ghc.mk - - - - - f847d703 by Jose Pedro Magalhaes at 2011-11-11T09:07:39+00:00 New kind-polymorphic core This big patch implements a kind-polymorphic core for GHC. The current implementation focuses on making sure that all kind-monomorphic programs still work in the new core; it is not yet guaranteed that kind-polymorphic programs (using the new -XPolyKinds flag) will work. For more information, see http://haskell.org/haskellwiki/GHC/Kinds - - - - - 7d7c3b09 by Jose Pedro Magalhaes at 2011-11-16T21:42:22+01:00 Follow changes to tuple sorts in master - - - - - 8430e03e by Simon Peyton Jones at 2011-11-17T10:20:27+00:00 Remove redundant imports - - - - - d1b06832 by Ian Lynagh at 2011-11-19T01:33:21+00:00 Follow GHC build system change to the way we call rm - - - - - 9e2230ed by David Waern at 2011-11-24T15:00:24+01:00 Fix a bug in test runner and get rid of regex-compat dependency. - - - - - 52039b21 by David Waern at 2011-11-24T23:55:36+01:00 Avoid haskell98 dependency in test - - - - - 92e1220d by David Waern at 2011-11-25T00:03:33+01:00 Avoid depency on regex-compat also in accept.hs. - - - - - ddac6b6f by David Waern at 2011-11-25T02:13:38+01:00 Accept test output. - - - - - 5a720455 by David Waern at 2011-11-25T02:16:20+01:00 Some more changes to test scripts. - - - - - 170a9004 by David Waern at 2011-11-25T02:30:41+01:00 Add flag --interface-version. - - - - - d225576c by David Waern at 2011-11-25T02:39:26+01:00 Remove #ifs for older compiler versions. - - - - - f0d0a4f5 by David Waern at 2011-11-26T04:20:12+01:00 Give preference to type over data constructors for doc comment links at renaming time. Previously this was done in the backends. Also, warn when a doc comment refers to something that is in scope but which we don't have the .haddock file for. These changes mean we can make DocIdentifier [a] into DocIdentifier a. - - - - - eef0e776 by David Waern at 2011-11-26T17:01:06+01:00 Allow doc comments to link to out-of-scope things (#78). (A bug that should have been fixed long ago.) - - - - - 565ad529 by David Waern at 2011-11-26T19:56:21+01:00 Update tests. - - - - - fb3ce7b9 by David Waern at 2011-11-26T21:44:28+01:00 Cleanup. - - - - - d0328126 by David Waern at 2011-11-26T22:10:28+01:00 Fix module reference bug. - - - - - c03765f8 by David Waern at 2011-12-03T05:20:20+01:00 Slightly better behaviour on top-levels without type signatures. - Docs don't get attached to the next top-level with signature by mistake. - If there's an export list and the top-level is part of it, its doc comment shows up in the documentation. - - - - - 48461d31 by David Waern at 2011-12-03T05:38:10+01:00 Add a test for Unicode doc comments. - - - - - 549c4b4e by David Waern at 2011-12-03T19:07:55+01:00 Cleanup. - - - - - 7bfecf91 by David Waern at 2011-12-03T20:13:08+01:00 More cleanup. - - - - - 14fab722 by Ian Lynagh at 2011-12-12T21:21:35+00:00 Update dependencies and binaryInterfaceVersion - - - - - 469e6568 by Ian Lynagh at 2011-12-18T12:56:16+00:00 Fix (untested) building from source tarball without alex/happy haddock's .cabal file was declaring that it needed alex and happy to build, but in the GHC source tarballs it doesn't. - - - - - 895c9a8c by David Waern at 2011-12-27T12:57:43+01:00 Go back to having a doc, sub and decl map instead of one big decl map. This setup makes more sense since when we add value bindings to the processed declarations (for type inference), we will have multiple declarations which should share documentation. Also, we already have a separate doc map for instances which we can now merge into the main doc map. Another benefit is that we don't need the DeclInfo type any longer. - - - - - 736767d9 by David Waern at 2011-12-27T13:33:41+01:00 Merge ../../../haddock Conflicts: src/Haddock/InterfaceFile.hs - - - - - 20016f79 by David Waern at 2011-12-27T13:57:23+01:00 Bump version. - - - - - 31f276fb by David Waern at 2011-12-27T13:57:32+01:00 Merge ../ghc/utils/haddock - - - - - 95b367cd by David Waern at 2011-12-27T14:57:29+01:00 Update tests following version bump. - - - - - fa3c94cd by David Waern at 2011-12-27T14:57:51+01:00 Get rid of quite unnecessary use of different lists. - - - - - 9c4d3c54 by David Waern at 2011-12-27T15:26:42+01:00 Cleanup. - - - - - 2caf9f90 by David Waern at 2011-12-27T16:18:05+01:00 Wibbles. - - - - - 3757d09b by David Waern at 2011-12-27T20:50:26+01:00 Complete support for inferring types for top-level bindings. - - - - - 53418734 by David Waern at 2011-12-28T15:02:13+01:00 Minor fixes and cleanup. - - - - - 0c9d0385 by Ian Lynagh at 2012-01-03T18:31:29+00:00 Follow rename of Instance to ClsInst in GHC - - - - - c9bc969a by Simon Hengel at 2012-01-12T21:28:14+01:00 Make sure that generated xhtml is valid (close haskell/haddock#186) Thanks to Phyx. - - - - - 836a0b9a by David Waern at 2012-02-01T02:30:05+01:00 Fix bug introduced in my recent refactoring. - - - - - c7d733eb by David Waern at 2012-02-01T02:30:26+01:00 Cleanup mkMaps and avoid quadratic behaviour. - - - - - da3cda8f by David Waern at 2012-02-01T02:56:56+01:00 Require ghc >= 7.4. - - - - - 83a3287e by David Waern at 2012-02-01T02:57:36+01:00 Update CHANGES. - - - - - 93408f0b by Simon Hengel at 2012-02-04T00:48:04+01:00 Add reference renderings - - - - - 49d00d2c by Simon Hengel at 2012-02-04T00:48:25+01:00 Set unit tests for parser back to work - - - - - eb450980 by Simon Hengel at 2012-02-04T00:49:07+01:00 Add .gitignore - - - - - a841602c by Simon Hengel at 2012-02-04T00:49:16+01:00 Add .ghci file - - - - - 8861199d by Simon Hengel at 2012-02-04T00:49:29+01:00 tests/html-tests/copy.hs: Use mapM_ instead of mapM So we do net get a list of () on stdout when running with runhaskell. - - - - - b477d9b5 by Simon Hengel at 2012-02-04T00:49:46+01:00 Remove index files from golden tests - - - - - 9dbda34e by Simon Hengel at 2012-02-04T00:49:57+01:00 Add /tests/html-tests/tests/*index*.ref to .gitignore - - - - - a9434817 by Simon Hengel at 2012-02-04T00:50:04+01:00 Add DocWarning to Doc The Xhtml backend has special markup for that, Hoogle and LaTeX reuse what we have for DocEmphasis. - - - - - de2fb6fa by Simon Hengel at 2012-02-04T00:50:13+01:00 Add support for module warnings - - - - - 0640920e by Simon Hengel at 2012-02-04T00:50:21+01:00 Add tests for module warnings - - - - - 30ce0d77 by Simon Hengel at 2012-02-04T00:50:29+01:00 Add support for warnings - - - - - bb367960 by Simon Hengel at 2012-02-04T00:50:37+01:00 Add tests for warnings - - - - - 6af1dc2d by Simon Hengel at 2012-02-04T00:50:50+01:00 Expand type signatures in export list (fixes haskell/haddock#192) - - - - - a06cbf25 by Simon Hengel at 2012-02-04T00:51:04+01:00 Expand type signatures for modules without explicit export list - - - - - 57dda796 by Simon Hengel at 2012-02-04T00:51:15+01:00 Remove obsolete TODO - - - - - 270c3253 by David Waern at 2012-02-04T00:51:24+01:00 Fix issues in support for warnings. * Match against local names only. * Simplify (it's OK to map over the warnings). - - - - - 683634bd by David Waern at 2012-02-04T00:55:11+01:00 Some cleanup and make sure we filter warnings through exports. - - - - - 210cb4ca by David Waern at 2012-02-04T03:01:30+01:00 Merge branch 'fix-for-186' of https://github.com/sol/haddock into ghc-7.4 - - - - - e8db9031 by David Waern at 2012-02-04T03:07:51+01:00 Style police. - - - - - 261f9462 by David Waern at 2012-02-04T03:20:16+01:00 Update tests. - - - - - 823cfc7c by David Waern at 2012-02-04T03:21:12+01:00 Use mapM_ in accept.hs as well. - - - - - 873dd619 by David Waern at 2012-02-04T03:21:33+01:00 Remove copy.hs - use accept.hs instead. - - - - - 0e31a14a by David Waern at 2012-02-04T03:47:33+01:00 Use <> instead of mappend. - - - - - 2ff7544f by David Waern at 2012-02-04T03:48:55+01:00 Remove code for older ghc versions. - - - - - dacf2786 by David Waern at 2012-02-04T15:52:51+01:00 Clean up some code from last SoC project. - - - - - 00cbb117 by David Waern at 2012-02-04T21:43:49+01:00 Mostly hlint-inspired cleanup. - - - - - 7dc86cc2 by Simon Peyton Jones at 2012-02-06T09:14:41+00:00 Track changes in HsDecls - - - - - f91f82fe by Ian Lynagh at 2012-02-16T13:40:11+00:00 Follow changes in GHC caused by the CAPI CTYPE pragma - - - - - a0ea6b0b by Ian Lynagh at 2012-02-22T02:26:12+00:00 Follow changes in GHC - - - - - b23b07d1 by Simon Peyton Jones at 2012-03-02T16:36:41+00:00 Follow changes in data representation from the big PolyKinds commit - - - - - 43406022 by Simon Hengel at 2012-03-05T11:18:34+01:00 Save/restore global state for static flags when running GHC actions This is necessary if we want to run createInterfaces (from Documentation.Haddock) multiple times in the same process. - - - - - 9fba16fe by Paolo Capriotti at 2012-03-06T10:57:33+00:00 Update .gitignore. - - - - - a9325044 by Simon Peyton Jones at 2012-03-14T17:35:42+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - fd48065a by Iavor Diatchki at 2012-03-15T22:43:35-07:00 Add support for type-level literals. - - - - - 2e8206dd by Simon Peyton Jones at 2012-03-16T14:18:22+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - 93e13319 by Simon Peyton Jones at 2012-03-17T01:04:05+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock Conflicts: src/Haddock/Convert.hs - - - - - d253fa71 by Iavor Diatchki at 2012-03-19T20:12:18-07:00 Merge remote-tracking branch 'origin/master' into type-nats - - - - - fc40acc8 by Iavor Diatchki at 2012-03-19T20:31:27-07:00 Add a missing case for type literals. - - - - - fd2ad699 by Iavor Diatchki at 2012-03-24T13:28:29-07:00 Rename variable to avoid shadowing warning. - - - - - 9369dd3c by Simon Peyton Jones at 2012-03-26T09:14:23+01:00 Follow refactoring of TyClDecl/HsTyDefn - - - - - 38825ca5 by Simon Peyton Jones at 2012-03-26T09:14:37+01:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - 4324ac0f by David Waern at 2012-04-01T01:51:19+02:00 Disable unicode test. - - - - - 3165b750 by David Waern at 2012-04-01T01:51:34+02:00 Take reader environment directly from TypecheckedSource. - - - - - 213b644c by David Waern at 2012-04-01T01:55:20+02:00 Cleanup. - - - - - 3118b4ba by David Waern at 2012-04-01T02:16:15+02:00 Don't filter out unexported names from the four maps - fixes a regression. - - - - - d6524e17 by David Waern at 2012-04-01T02:40:34+02:00 Fix crash when using --qual. Naughty GHC API! - - - - - ea3c43d8 by Henning Thielemann at 2012-04-01T13:03:07+02:00 add QualOption type for distinction between qualification argument given by the user and the actual qualification for a concrete module - - - - - 5422ff05 by Henning Thielemann at 2012-04-01T16:25:02+02:00 emit an error message when the --qual option is used incorrectly - - - - - 026e3404 by David Waern at 2012-04-01T18:10:30+02:00 Don't crash on unicode strings in doc comments. - - - - - ce006632 by David Waern at 2012-04-01T20:13:35+02:00 Add test for --ignore-all-exports flag/ignore-exports pragma. - - - - - 6e4dd33c by David Waern at 2012-04-01T20:21:03+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.4 - - - - - 734ae124 by Henning Thielemann at 2012-04-01T20:22:10+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - 622f9ba5 by David Waern at 2012-04-01T21:26:13+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 55ce17cb by Henning Thielemann at 2012-04-01T22:03:25+02:00 'abbreviate' qualification style - basic support Currently we ignore the package a module is imported from. This means that a module import would shadow another one with the same module name from a different package. - - - - - c85314ef by David Waern at 2012-04-01T22:05:12+02:00 Check qualification option before processing modules. - - - - - ae4b626c by Henning Thielemann at 2012-04-02T00:19:36+02:00 abbreviated qualification: use Packages.lookupModuleInAllPackages for finding the package that a module belongs to - - - - - 60bdbcf5 by Henning Thielemann at 2012-04-02T00:25:31+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - df44301d by Henning Thielemann at 2012-04-02T00:29:05+02:00 qualification style 'abbreviated' -> 'aliased' - - - - - f4192a64 by David Waern at 2012-04-02T01:05:47+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 7ba09067 by David Terei at 2012-04-04T15:08:21-07:00 Fix reporting of modules safe haskell mode (#5989) - - - - - d0cc33d0 by David Terei at 2012-04-06T15:50:41+01:00 Fix reporting of modules safe haskell mode (#5989) - - - - - 6e3434c5 by Simon Peyton Jones at 2012-04-20T18:37:46+01:00 Track changes in HsSyn - - - - - 22014ed0 by Simon Peyton Jones at 2012-05-11T22:45:15+01:00 Follow changes to LHsTyVarBndrs - - - - - d9a07b24 by David Waern at 2012-05-15T01:46:35+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - a6c4ebc6 by David Waern at 2012-05-16T02:18:32+02:00 Update CHANGES. - - - - - 8e181d29 by David Waern at 2012-05-16T02:27:56+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - e358210d by David Waern at 2012-05-16T02:35:33+02:00 Mention the new aliased --qual mode in CHANGES. - - - - - efd36a28 by David Waern at 2012-05-16T21:33:13+02:00 Bump version number. - - - - - d6b3af14 by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for deprecated record field - - - - - 927f800e by Simon Hengel at 2012-05-17T19:08:20+02:00 Use >>= instead of fmap and join - - - - - 048b41d5 by Simon Hengel at 2012-05-17T19:08:20+02:00 newtype-wrap Doc nodes for things that may have warnings attached - - - - - e3a89fc3 by Simon Hengel at 2012-05-17T19:08:20+02:00 Attach warnings to `Documentation` type - - - - - 5d4cc43d by Simon Hengel at 2012-05-17T19:08:20+02:00 Simplify lookupWarning - - - - - cf8ae69d by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for haskell/haddock#205 - - - - - cb409b19 by Simon Peyton Jones at 2012-05-25T08:30:11+01:00 Follow changes in LHsTyVarBndrs - - - - - 2d5f4179 by Simon Hengel at 2012-05-26T19:21:29+02:00 Add Applicative instance for (GenRnM a) - - - - - e4373060 by Simon Hengel at 2012-05-26T19:21:33+02:00 Use a map for warnings, as suggested by @waern - - - - - 597a68c7 by Simon Hengel at 2012-05-27T08:48:24+02:00 Add an optional label to URLs - - - - - ef1ac7fe by Simon Hengel at 2012-05-27T08:48:24+02:00 Add support for hyperlink labels to parser - - - - - 41f2adce by Simon Hengel at 2012-05-27T08:48:24+02:00 Add golden test for hyperlinks - - - - - 83d5e764 by Simon Hengel at 2012-05-27T08:50:02+02:00 Use LANGUAGE pragmas instead of default-extensions in cabal file - - - - - ddb755e5 by Simon Hengel at 2012-05-27T08:50:02+02:00 Fix typo in comment - - - - - 110676b4 by Simon Hengel at 2012-05-27T08:50:02+02:00 Add a type signature for a where-binding - - - - - 7d9ba2a0 by Ian Lynagh at 2012-06-12T14:38:01+01:00 Follow changes in GHC - - - - - 47c704f2 by Ian Lynagh at 2012-06-12T18:52:16+01:00 Follow changes in GHC - - - - - e1efe1ab by Simon Peyton Jones at 2012-06-13T17:25:29+01:00 Follow changes for the implementation of implicit parameters - - - - - 69abc81c by Ian Lynagh at 2012-06-19T22:52:58+01:00 Follow changes in base - - - - - 9d074a21 by Paolo Capriotti at 2012-06-22T18:26:47+01:00 Use right docMap to get decl documentation. - - - - - e3292ef6 by Ian Lynagh at 2012-07-15T01:31:19+01:00 Follow changes in GHC - - - - - ceae56b0 by Ian Lynagh at 2012-07-16T21:22:48+01:00 Fix haddock following some GHC changes Passing _|_ as the Settings for defaultDynFlags no longer works well enough - - - - - 9df72735 by Paolo Capriotti at 2012-07-19T16:49:32+01:00 Forward port changes from stable. - - - - - 572f5fcf by Ian Lynagh at 2012-07-19T20:38:26+01:00 Merge branch 'master' of darcs.haskell.org:/srv/darcs//haddock - - - - - 9195aca4 by Paolo Capriotti at 2012-07-20T10:27:28+01:00 Update dependencies. - - - - - 33db3923 by Ian Lynagh at 2012-07-20T17:54:43+01:00 Build with GHC 7.7 - - - - - 925a2cea by David Waern at 2012-07-23T16:50:40+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.6 Conflicts: src/Haddock/InterfaceFile.hs - - - - - d710ef97 by David Waern at 2012-07-23T16:52:07+02:00 Bump version number. - - - - - eb0c2f83 by David Waern at 2012-07-23T16:57:58+02:00 Update CHANGES. - - - - - b3f56943 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Hide "internal" instances This fixes haskell/haddock#37 (http://trac.haskell.org/haddock/ticket/37) Precisely, we show an instance iff its class and all the types are exported by non-hidden modules. - - - - - a70aa412 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Tests for hiding instances (#37) - - - - - c0f4aa58 by Simon Hengel at 2012-07-27T13:00:13+03:00 Add an other test for hiding instances (#37) - - - - - a7ed6268 by Ian Lynagh at 2012-08-07T14:48:13+01:00 Follow changes in GHC - - - - - 0ab30d38 by Ian Lynagh at 2012-08-13T22:12:27+01:00 Improve haddock memory usage - - - - - 0eaa4e30 by Ian Lynagh at 2012-08-13T23:58:46+01:00 Improve haddock memory usage - - - - - 659d26cf by Ian Lynagh at 2012-08-14T13:16:48+01:00 Remove some temporary pragmas I accidentally recorded - - - - - d97fceb6 by Simon Hengel at 2012-08-25T13:19:34+02:00 Add missing dependency to library - - - - - 4c910697 by Simon Hengel at 2012-08-28T07:39:14+02:00 Move .ghci to project root - - - - - fc3c601a by Simon Hengel at 2012-08-28T07:39:14+02:00 accept.hs: Ignore some files - - - - - 1af9b984 by Simon Hengel at 2012-08-28T07:40:04+02:00 Update reference renderings (bump version) - - - - - 980dc253 by Simon Hengel at 2012-08-28T07:40:32+02:00 Update reference renderings (remove links for ()) - - - - - 33651dbf by Simon Hengel at 2012-08-28T07:41:50+02:00 Update documentation of `runInteractiveProcess` in reference rendering - - - - - 7ab25078 by David Waern at 2012-09-07T10:38:50+02:00 Merge branch 'hiddenInstances2' of http://github.com/feuerbach/haddock into ghc-7.6 - - - - - c3de3a4b by David Waern at 2012-09-07T14:29:27+02:00 Follow changes in GHC. - - - - - 298c43ac by David Waern at 2012-09-07T14:59:24+02:00 Update CHANGES. - - - - - e797993a by David Waern at 2012-09-07T15:21:30+02:00 Update ANNOUNCE. - - - - - d0b44790 by David Waern at 2012-09-07T15:22:43+02:00 Merge branch 'hidden-instances' into ghc-7.6 - - - - - 41a4adc8 by Simon Hengel at 2012-09-08T12:08:37+02:00 Update doc/README - - - - - 71ad1040 by Simon Hengel at 2012-09-08T12:17:17+02:00 Add documentation for URL labels - - - - - 9bb41afd by Simon Peyton Jones at 2012-09-20T18:14:26+01:00 Follow data type changes in the tc-untouchables branch Relating entirely to SynTyConRhs - - - - - b8139bfa by Simon Hengel at 2012-09-21T14:24:16+02:00 Disable Unicode test for now - - - - - a5fafdd7 by Simon Hengel at 2012-09-21T14:35:45+02:00 Update TypeOperators test for GHC 7.6.1 Type operators can't be used as type variables anymore! - - - - - 6ccf0025 by Simon Hengel at 2012-09-21T16:02:24+02:00 Remove (Monad (Either e)) instance from ref. rendering of CrossPackageDocs I do not really understand why the behavior changed, so I'll open a ticket, so that we can further investigate. - - - - - b5c6c138 by Ian Lynagh at 2012-09-27T02:00:57+01:00 Follow changes in GHC build system - - - - - b98eded0 by David Waern at 2012-09-27T15:37:02+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 76cc2051 by David Waern at 2012-09-27T15:48:19+02:00 Update hidden instances tests. - - - - - aeaa1c59 by David Waern at 2012-09-28T10:21:32+02:00 Make API buildable with GHC 7.6. - - - - - d76be1b0 by Simon Peyton Jones at 2012-09-28T15:57:05+01:00 Merge remote-tracking branch 'origin/master' into tc-untouchables - - - - - a1922af8 by David Waern at 2012-09-28T19:50:20+02:00 Fix spurious superclass constraints bug. - - - - - bc41bdbb by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove old examples - - - - - bed7d3dd by Simon Hengel at 2012-10-01T11:30:51+02:00 Adapt parsetests for GHC 7.6.1 - - - - - dcdb22bb by Simon Hengel at 2012-10-01T11:30:51+02:00 Add test-suite section for parsetests to cabal file + get rid of HUnit dependency - - - - - 1e5263c9 by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove test flag from cabal file This was not really used. - - - - - 4beee98b by David Waern at 2012-09-28T23:42:28+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 11dd2256 by Ian Lynagh at 2012-10-03T16:17:35+01:00 Follow change in GHC build system - - - - - fbd77962 by Simon Hengel at 2012-10-03T18:49:40+02:00 Remove redundant dependency from cabal file - - - - - 09218989 by Simon Hengel at 2012-10-04T16:03:05+02:00 Fix typo - - - - - 93a2d5f9 by Simon Hengel at 2012-10-04T16:11:41+02:00 Remove trailing whitespace from cabal file - - - - - c8b46cd3 by Simon Hengel at 2012-10-04T16:12:17+02:00 Export Haddock's main entry point from library - - - - - b411e77b by Simon Hengel at 2012-10-04T16:29:46+02:00 Depend on library for executable The main motivation for this is to increase build speed. In GHC's source tree the library is not build, but all modules are now required for the executable, so that GHC's validate will now detect build failures for the library. - - - - - f8f0979f by Simon Hengel at 2012-10-05T00:32:57+02:00 Set executable flag for Setup.lhs - - - - - dd045998 by Simon Hengel at 2012-10-07T16:44:06+02:00 Extend rather than set environment when running HTML tests On some platforms (e.g. ppc64) GHC requires gcc in the path. - - - - - 7b39c3ae by Simon Hengel at 2012-10-07T17:05:45+02:00 cross-package test: re-export IsString instead of Monad There is a monad instance for Q, which is not available on platforms that do not have GHCi support. This caused CrossPackageDocs to fail on those platforms. Re-exporting IsString should test the same thing, but it works on all platforms. - - - - - 0700c605 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Fix some warnings - - - - - f78eca79 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Make -Wall proof - - - - - 6beec041 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Use listToMaybe/fromMaybe instead of safeHead/maybe - - - - - 44b8ce86 by Ian Lynagh at 2012-10-08T21:59:46+01:00 Follow changes in GHC - - - - - 6da5f702 by Simon Hengel at 2012-10-09T11:16:19+02:00 Update .ghci - - - - - 9ac1a1b9 by Kazu Yamamoto at 2012-10-09T12:45:31+02:00 Add markup support for properties - - - - - 1944cb42 by Simon Hengel at 2012-10-09T12:45:31+02:00 Simplify lexing/parsing of properties In contrast to what we do for examples, we do not really need to capture the "prompt" here. - - - - - bffd8e62 by Simon Hengel at 2012-10-09T13:40:14+02:00 Add HTML test for properties - - - - - 2fe9c5cb by Simon Hengel at 2012-10-09T13:40:21+02:00 Add unit tests for properties - - - - - 874e361b by Simon Hengel at 2012-10-09T13:40:33+02:00 Bump interface version - - - - - 2506cc37 by Simon Hengel at 2012-10-09T15:15:04+02:00 Fix parser bug - - - - - 743d2b7d by Simon Hengel at 2012-10-09T15:31:06+02:00 Allow to load interface files with compatible versions - - - - - 981a1660 by Simon Hengel at 2012-10-10T10:32:05+02:00 Export more types from Documentation.Haddock (fixes haskell/haddock#216) - - - - - dff7dc76 by Simon Hengel at 2012-10-10T11:15:19+02:00 Update ANNOUNCE and CHANGES - - - - - edd2bb01 by Simon Hengel at 2012-10-10T11:22:50+02:00 Bump version - - - - - 5039163b by Simon Hengel at 2012-10-10T13:56:04+02:00 Fix typo in documentation - - - - - e4ce34da by Simon Hengel at 2012-10-10T14:28:35+02:00 Add documentation for properties - - - - - 9555ebca by Simon Hengel at 2012-10-11T10:49:04+02:00 Remove redundant if-defs, more source documentation - - - - - 87aa67e1 by Simon Hengel at 2012-10-11T12:32:51+02:00 Adapt cabal file - - - - - c44c1dee by Simon Hengel at 2012-10-11T12:41:58+02:00 Require ghc 7.6 - - - - - 8383bc34 by Simon Hengel at 2012-10-11T12:50:24+02:00 Bump version - - - - - 1030eb38 by Simon Hengel at 2012-10-11T12:55:44+02:00 Update ANNOUNCE and CHANGES - - - - - 74955088 by Simon Hengel at 2012-10-12T09:49:31+02:00 Improve note about `binaryInterfaceVersion` (thanks David) - - - - - ee30f6b7 by Simon Hengel at 2012-10-13T13:40:59+02:00 Update version in html tests, rpm spec file, and user manual - - - - - f2861f18 by Simon Hengel at 2012-10-13T14:40:33+02:00 Remove unused MonadFix constraint - - - - - dfdf1a74 by Simon Hengel at 2012-10-13T15:15:38+02:00 Minor code simplification - - - - - 4ecd1e70 by Simon Hengel at 2012-10-13T15:33:43+02:00 Increase code locality - - - - - f7df5cc9 by Simon Hengel at 2012-10-13T16:03:12+02:00 Minor code simplification - - - - - e737eb6e by Simon Hengel at 2012-10-13T19:03:04+02:00 Handle HsExplicitListTy in renameer (fixes haskell/haddock#213) - - - - - c2dc8f17 by Simon Hengel at 2012-10-13T20:46:31+02:00 Better error messages - - - - - 14d48b4c by Simon Hengel at 2012-10-14T00:21:07+02:00 Simplify RnM type - - - - - 6c2cc547 by Simon Hengel at 2012-10-14T00:23:35+02:00 Simplify lookupRn - - - - - bc77ce85 by Simon Hengel at 2012-10-14T01:51:32+02:00 Organize unite tests hierarchically - - - - - 2306d117 by Simon Hengel at 2012-10-14T10:34:58+02:00 Handle more cases in renameType - - - - - 8a864203 by Simon Hengel at 2012-10-14T11:47:59+02:00 Add mini_HiddenInstances.html.ref and mini_HiddenInstancesB.html.ref - - - - - 3a978eca by Simon Hengel at 2012-10-14T11:49:28+02:00 Add /tests/html-tests/output/ to .gitignore - - - - - db18888a by Simon Hengel at 2012-10-14T13:38:21+02:00 Allow haddock markup in deprecation messages - - - - - e7cfee9f by Simon Hengel at 2012-10-14T14:00:23+02:00 If parsing of deprecation message fails, include it verbatim - - - - - 242a85be by Simon Hengel at 2012-10-14T14:13:24+02:00 Add description for PruneWithWarning test - - - - - 43d33df1 by Simon Hengel at 2012-10-14T15:40:53+02:00 Minor formatting change - - - - - 22768c44 by Simon Hengel at 2012-10-14T16:03:43+02:00 Properly handle deprecation messages for re-exported things (fixes haskell/haddock#220) - - - - - cb4b9111 by Simon Hengel at 2012-10-14T17:30:28+02:00 Add build artifacts for documentation to .gitignore - - - - - 854cd8de by Simon Hengel at 2012-10-14T23:34:51+02:00 unit-tests: Improve readability Add IsString instance for (Doc RdrName) + use <> instead of DocAppend. - - - - - c4446d54 by Simon Hengel at 2012-10-14T23:37:21+02:00 unit-tests: Minor refactoring Rename parse to parseParas. - - - - - 04f2703c by Simon Hengel at 2012-10-15T00:36:42+02:00 Fix typo - - - - - 3d109e44 by Simon Hengel at 2012-10-15T10:30:07+02:00 Add description for DeprecatedReExport test - - - - - 84f0985c by Simon Hengel at 2012-10-15T14:54:19+02:00 Move resources to /resources directory - - - - - a5de7ca6 by Simon Hengel at 2012-10-15T15:46:18+02:00 Move HTML tests to directory /html-test/ - - - - - e21f727d by Simon Hengel at 2012-10-15T19:32:42+02:00 Move HTML reference renderings to /html-test/ref/ - - - - - 3a3c6c75 by Simon Hengel at 2012-10-15T19:32:42+02:00 Copy css, images, etc. on accept - - - - - 40ead6dc by Simon Hengel at 2012-10-15T19:32:42+02:00 Move unit tests to /test directory - - - - - 99a28231 by Simon Hengel at 2012-10-15T19:32:42+02:00 Fix Setup.lhs /usr/bin/runhaskell is not installed on all systems. - - - - - 95faf45e by Simon Hengel at 2012-10-15T19:32:42+02:00 Make test management scripts more robust * They are now independent from the current directory, and hence can be called from everywhere * On UNIX/Linux they can now be run as scripts - - - - - 027aaa2d by Simon Hengel at 2012-10-15T19:53:40+02:00 Add 'dev' flag to cabal file, that builds without -O2 That way --disable-optimization can be used, which decreases build time considerably. - - - - - e0266ede by Simon Hengel at 2012-10-15T20:03:43+02:00 Add test case for "spurious superclass constraints bug" - - - - - 52a2aa92 by Simon Hengel at 2012-10-15T20:28:55+02:00 Adapt accept.lhs, so that it ignores more index files - - - - - 53530781 by Simon Hengel at 2012-10-15T20:49:39+02:00 Rename html-test/runtests.lhs to html-test/run.lhs - - - - - 84518797 by Simon Hengel at 2012-10-15T20:49:39+02:00 Move source files for HTML tests to html-test/src - - - - - a911dc6c by Simon Hengel at 2012-10-15T20:49:39+02:00 Adapt output directory for HTML tests - - - - - d3c15857 by Ian Lynagh at 2012-10-16T16:54:43+01:00 Follow dopt->gopt rename - - - - - 956665a5 by Simon Hengel at 2012-10-18T08:42:48+02:00 Update html-test/README - - - - - 903b1029 by Simon Hengel at 2012-10-18T08:50:26+02:00 Use markdown for html-test/README - - - - - 150b4d63 by Ian Lynagh at 2012-10-18T16:36:00+01:00 Follow changes in GHC: 'flags' has been renamed 'generalFlags' - - - - - 41e04ff9 by Simon Hengel at 2012-11-28T09:54:35+01:00 Export missing types from Documentation.Haddock - - - - - 9be59237 by Ian Lynagh at 2012-11-30T23:20:47+00:00 Update dependencies - - - - - e06842f5 by Simon Hengel at 2012-12-07T20:58:05+01:00 Bump version - - - - - e3dbede0 by Simon Hengel at 2012-12-07T20:58:05+01:00 Add missing test files to cabal file (fixes haskell/haddock#230) - - - - - ee0dcca7 by Simon Hengel at 2012-12-07T20:58:05+01:00 Update CHANGES - - - - - 51601bdb by Simon Peyton Jones at 2012-12-19T17:28:35+00:00 Track changes in UNPACK pragma stuff - - - - - f2573bc1 by Richard Eisenberg at 2012-12-21T20:56:25-05:00 Implement overlapping type family instances. An ordered, overlapping type family instance is introduced by 'type instance where', followed by equations. See the new section in the user manual (7.7.2.2) for details. The canonical example is Boolean equality at the type level: type family Equals (a :: k) (b :: k) :: Bool type instance where Equals a a = True Equals a b = False A branched family instance, such as this one, checks its equations in order and applies only the first the matches. As explained in the note [Instance checking within groups] in FamInstEnv.lhs, we must be careful not to simplify, say, (Equals Int b) to False, because b might later unify with Int. This commit includes all of the commits on the overlapping-tyfams branch. SPJ requested that I combine all my commits over the past several months into one monolithic commit. The following GHC repos are affected: ghc, testsuite, utils/haddock, libraries/template-haskell, and libraries/dph. Here are some details for the interested: - The definition of CoAxiom has been moved from TyCon.lhs to a new file CoAxiom.lhs. I made this decision because of the number of definitions necessary to support BranchList. - BranchList is a GADT whose type tracks whether it is a singleton list or not-necessarily-a-singleton-list. The reason I introduced this type is to increase static checking of places where GHC code assumes that a FamInst or CoAxiom is indeed a singleton. This assumption takes place roughly 10 times throughout the code. I was worried that a future change to GHC would invalidate the assumption, and GHC might subtly fail to do the right thing. By explicitly labeling CoAxioms and FamInsts as being Unbranched (singleton) or Branched (not-necessarily-singleton), we make this assumption explicit and checkable. Furthermore, to enforce the accuracy of this label, the list of branches of a CoAxiom or FamInst is stored using a BranchList, whose constructors constrain its type index appropriately. I think that the decision to use BranchList is probably the most controversial decision I made from a code design point of view. Although I provide conversions to/from ordinary lists, it is more efficient to use the brList... functions provided in CoAxiom than always to convert. The use of these functions does not wander far from the core CoAxiom/FamInst logic. BranchLists are motivated and explained in the note [Branched axioms] in CoAxiom.lhs. - The CoAxiom type has changed significantly. You can see the new type in CoAxiom.lhs. It uses a CoAxBranch type to track branches of the CoAxiom. Correspondingly various functions producing and consuming CoAxioms had to change, including the binary layout of interface files. - To get branched axioms to work correctly, it is important to have a notion of type "apartness": two types are apart if they cannot unify, and no substitution of variables can ever get them to unify, even after type family simplification. (This is different than the normal failure to unify because of the type family bit.) This notion in encoded in tcApartTys, in Unify.lhs. Because apartness is finer-grained than unification, the tcUnifyTys now calls tcApartTys. - CoreLinting axioms has been updated, both to reflect the new form of CoAxiom and to enforce the apartness rules of branch application. The formalization of the new rules is in docs/core-spec/core-spec.pdf. - The FamInst type (in types/FamInstEnv.lhs) has changed significantly, paralleling the changes to CoAxiom. Of course, this forced minor changes in many files. - There are several new Notes in FamInstEnv.lhs, including one discussing confluent overlap and why we're not doing it. - lookupFamInstEnv, lookupFamInstEnvConflicts, and lookup_fam_inst_env' (the function that actually does the work) have all been more-or-less completely rewritten. There is a Note [lookup_fam_inst_env' implementation] describing the implementation. One of the changes that affects other files is to change the type of matches from a pair of (FamInst, [Type]) to a new datatype (which now includes the index of the matching branch). This seemed a better design. - The TySynInstD constructor in Template Haskell was updated to use the new datatype TySynEqn. I also bumped the TH version number, requiring changes to DPH cabal files. (That's why the DPH repo has an overlapping-tyfams branch.) - As SPJ requested, I refactored some of the code in HsDecls: * splitting up TyDecl into SynDecl and DataDecl, correspondingly changing HsTyDefn to HsDataDefn (with only one constructor) * splitting FamInstD into TyFamInstD and DataFamInstD and splitting FamInstDecl into DataFamInstDecl and TyFamInstDecl * making the ClsInstD take a ClsInstDecl, for parallelism with InstDecl's other constructors * changing constructor TyFamily into FamDecl * creating a FamilyDecl type that stores the details for a family declaration; this is useful because FamilyDecls can appear in classes but other decls cannot * restricting the associated types and associated type defaults for a * class to be the new, more restrictive types * splitting cid_fam_insts into cid_tyfam_insts and cid_datafam_insts, according to the new types * perhaps one or two more that I'm overlooking None of these changes has far-reaching implications. - The user manual, section 7.7.2.2, is updated to describe the new type family instances. - - - - - f788d0fb by Simon Peyton Jones at 2012-12-23T15:49:58+00:00 Track changes in HsBang - - - - - ca460a0c by Simon Peyton Jones at 2012-12-23T15:50:28+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - f078fea6 by Simon Peyton Jones at 2013-01-02T08:33:13+00:00 Use InstEnv.instanceSig rather than instanceHead (name change) - - - - - 88e41305 by Simon Peyton Jones at 2013-01-14T17:10:27+00:00 Track change to HsBang type - - - - - e1ad4e19 by Kazu Yamamoto at 2013-02-01T11:59:24+09:00 Merge branch 'ghc-7.6' into ghc-7.6-merge-2 Conflicts: haddock.cabal src/Haddock/Interface/AttachInstances.hs src/Haddock/Interface/Create.hs src/Haddock/Interface/LexParseRn.hs src/Haddock/InterfaceFile.hs src/Haddock/Types.hs Only GHC HEAD can compile this. GHC 7.6.x cannot compile this. Some test fail. - - - - - 62bec012 by Kazu Yamamoto at 2013-02-06T11:12:28+09:00 Using tcSplitSigmaTy in instanceHead' (FIXME is resolved.) - - - - - 013fd2e4 by Kazu Yamamoto at 2013-02-06T17:56:21+09:00 Refactoring instanceHead'. - - - - - 3148ce0e by Kazu Yamamoto at 2013-02-07T17:45:10+09:00 Using new syntax in html-test/src/GADTRecords.hs. - - - - - 626dabe7 by Gabor Greif at 2013-02-15T22:42:01+01:00 Typo - - - - - 1eb667ae by Ian Lynagh at 2013-02-16T17:02:07+00:00 Follow changes in base - - - - - 3ef8253a by Ian Lynagh at 2013-03-01T23:23:57+00:00 Follow changes in GHC's build system - - - - - 1a265a3c by Ian Lynagh at 2013-03-03T23:12:07+00:00 Follow changes in GHC build system - - - - - 69941c79 by Max Bolingbroke at 2013-03-10T09:38:28-07:00 Use Alex 3's Unicode support to properly lex source files as UTF-8 Signed-off-by: David Waern <david.waern at gmail.com> - - - - - ea687dad by Simon Peyton Jones at 2013-03-15T14:16:10+00:00 Adapt to tcRnGetInfo returning family instances too This API change was part of the fix to Trac haskell/haddock#4175. But it offers new information to Haddock: the type-family instances, as well as the class instances, of this type. This patch just drops the new information on the floor, but there's an open opportunity to use it in the information that Haddock displays. - - - - - 971a30b0 by Andreas Voellmy at 2013-05-19T20:47:39+01:00 Fix for haskell/haddock#7879. Changed copy of utils/haddock/html/resources/html to use "cp -RL" rather than "cp -R". This allows users to run validate in a build tree, where the build tree was setup using lndir with a relative path to the source directory. - - - - - 31fb7694 by Ian Lynagh at 2013-05-19T20:47:49+01:00 Use "cp -L" when making $(INPLACE_LIB)/latex too - - - - - e9952233 by Simon Hengel at 2013-06-01T18:06:50+02:00 Add -itest to .ghci - - - - - b06873b3 by Mateusz Kowalczyk at 2013-06-01T18:06:50+02:00 Workaround for a failing build with --enable-tests. - - - - - e7858d16 by Simon Hengel at 2013-06-01T19:29:28+02:00 Fix broken test - - - - - 0690acb1 by Richard Eisenberg at 2013-06-21T14:08:25+01:00 Updates to reflect changes in HsDecls to support closed type families. - - - - - 7fd347ec by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 53ed81b6 by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 931c4f4f by Richard Eisenberg at 2013-07-24T13:15:59+01:00 Remove (error "synifyKind") to use WithinType, to allow haddock to process base. - - - - - 55a9c804 by Richard Eisenberg at 2013-08-02T15:54:55+01:00 Changes to reflect changes in GHC's type HsTyVarBndr - - - - - b6e9226c by Mathieu Boespflug at 2013-08-04T10:39:43-07:00 Output Copright and License keys in Xhtml backend. This information is as relevant in the documentation as it is in the source files themselves. Signed-off-by: David Waern <david.waern at gmail.com> - - - - - 4c66028a by David Waern at 2013-08-04T15:27:36-07:00 Bump interface file version. - - - - - 67340163 by David Waern at 2013-08-09T16:12:51-07:00 Update tests. - - - - - 2087569b by Mateusz Kowalczyk at 2013-08-25T09:24:13+02:00 Add spec tests. This adds tests for all elements we can create during regular parsing. This also adds tests for text with unicode in it. - - - - - 97f36a11 by Mateusz Kowalczyk at 2013-08-27T06:59:12+01:00 Fix ticket haskell/haddock#247. I do the same thing that the XHTML backend does: give these no special treatment and just act as if they are regular functions. - - - - - 60681b4f by Mateusz Kowalczyk at 2013-08-27T21:22:48+02:00 LaTeX tests setup - - - - - fa4c27b2 by Mateusz Kowalczyk at 2013-09-02T23:21:43+01:00 Fixes haskell/haddock#253 - - - - - 1a202490 by Mateusz Kowalczyk at 2013-09-03T01:12:50+01:00 Use Hspec instead of nanospec This is motivated by the fact that Haddock tests are not ran by the GHC's ‘validate’ script so we're pretty liberal on dependencies in that area. Full Hspec gives us some nice features such as Quickcheck integration. - - - - - 8cde3b20 by David Luposchainsky at 2013-09-08T07:27:28-05:00 Fix AMP warnings Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - d10661f2 by Herbert Valerio Riedel at 2013-09-11T15:15:01+02:00 Update Git repo URL in `.cabal` file - - - - - 16a44eb5 by Richard Eisenberg at 2013-09-17T09:34:26-04:00 Revision to reflect new role annotation syntax in GHC. - - - - - 4b9833b9 by Herbert Valerio Riedel at 2013-09-18T10:15:28+02:00 Add missing `traverse` method for `GenLocated` As `Traversable` needs at least one of `traverse` or `sequenceA` to be overridden. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - b71fed5d by Simon Hengel at 2013-09-18T22:43:34+02:00 Add test helper - - - - - 4fc1ea86 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#231 - - - - - 435872f6 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#256 We inject -dynamic-too into flags before we run all our actions in the GHC monad. - - - - - b8b24abb by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Add new field to DynFlags - - - - - 49558795 by Simon Hengel at 2013-09-18T22:43:35+02:00 Fallback to ./resources when Cabal data is not found (so that themes are found during development) - - - - - bf79d05c by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Fixes haskell/haddock#5 - - - - - e1baebc2 by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Print missing documentation. Fixes haskell/haddock#258. - - - - - 02ea74de by Austin Seipp at 2013-10-09T10:52:22-05:00 Don't consider StaticFlags when parsing arguments. Instead, discard any static flags before parsing the command line using GHC's DynFlags parser. See http://ghc.haskell.org/trac/ghc/ticket/8276 Based off a patch from Simon Hengel. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 704fd5bb by Simon Hengel at 2013-11-09T00:15:13+01:00 Update HTML tests - - - - - f9fed49e by Simon Hengel at 2013-11-10T18:43:58+01:00 Bump version - - - - - 97ae1999 by Simon Peyton Jones at 2013-11-25T17:25:14+00:00 Track changes in HsSpliceTy data constructor - - - - - 59ad8268 by Simon Peyton Jones at 2014-01-10T18:17:43+00:00 Adapt to small change in Pretty's exports - - - - - 8b12e6aa by Simon Hengel at 2014-01-12T14:48:35-06:00 Some code simplification by using traverse - - - - - fc5ea9a2 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix warnings in test helper - - - - - 6dbb3ba5 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Add ByteString version of Attoparsec - - - - - 968d7774 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 One pass parser and tests. We remove the HTML test as it is no longer necessary. We cover the test case in spec tests and other HTML tests but keeping this around fails: this is because the new parser has different semantics there. In fact, I suspect the original behaviour was a bug that wasn't caught/fixed but simply included as-is during the testing. - - - - - 37a07c9c by Simon Hengel at 2014-01-12T14:48:35-06:00 Rename Haddock.ParseSpec to Haddock.ParserSpec - - - - - f0f68fe9 by Simon Hengel at 2014-01-12T14:48:35-06:00 Don't append newline to parseString input We also check that we have parsed everything with endOfInput. - - - - - 95d60093 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix totality, unicode, examples, paragraph parsing Also simplify specs and parsers while we're at it. Some parsers were made more generic. This commit is a part of GHC pre-merge squash, email fuuzetsu at fuuzetsu.co.uk if you need the full commit history. - - - - - 7d99108c by Simon Hengel at 2014-01-12T14:48:35-06:00 Update acceptance tests - - - - - d1b59640 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Support for bold. Conflicts: src/Haddock/Backends/Hoogle.hs src/Haddock/Interface/Rename.hs src/Haddock/Parser.hs - - - - - 4b412b39 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Allow for headings inside function documentation. LaTeX will treat the h3-h6 headings the same as we'd have to hack the style file heavily otherwise and it would make the headings tiny anyway. Hoogle upstream said they will put in the functionality on their end. Conflicts: src/Haddock/Interface/Rename.hs src/Haddock/Types.hs test/Haddock/ParserSpec.hs - - - - - fdcca428 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Per-module extension flags and language listing. Any extensions that are not enabled by a used language (Haskell2010 &c) will be shown. Furthermore, any implicitly enabled are also going to be shown. While we could eliminate this either by using the GHC API or a dirty hack, I opted not to: if a user doesn't want the implied flags to show, they are recommended to use enable extensions more carefully or individually. Perhaps this will encourage users to not enable the most powerful flags needlessly. Enabled with show-extensions. Conflicts: src/Haddock/InterfaceFile.hs - - - - - 368942a2 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Bump interface version There were some breaking changes over the last few patches so we bump the interface version. This causes a big problem with testing: 1. To generate cross package docs, we first need to generate docs for the package used. 2. To generate package docs with new interface version, we need to use Haddock which has the version bumped. 3. To get Haddock with the version bump, we first need to test cross package docs 4. GOTO 1 So the problem is the chicken and the egg problem. It seems that the only solution would be to generate some interface files on the fly but it is non-trivial. To run this test, you'll have to: * build Haddock without the test (make sure everything else passes) * rebuild the packages used in the test with your shiny new binary making sure they are visible to Haddock * remove the ‘_hidden’ suffix and re-run the tests Note: because the packages currently used for this test are those provided by GHC, it's probably non-trivial to just re-build them. Preferably something less tedious to rebuild should be used and something that is not subject to change. - - - - - 124ae7a9 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow for nesting of paragraphs under lists. The nesting rules are similar to Markdown's with the exception that we can not simply indent the first line of a hard wrapped indented paragraph and have it treated as if it was fully indented. The reason is differences in markup as some of our constructs care about whitespace while others just swallow everything up so it's just a lot easier to not bother with it rather than making arbitrary rules. Note that we now drop trailing for string entities inside of lists. They weren't needed and it makes the output look uniform whether we use a single or double newline between list elements. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - c7913535 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow escaping in URLs and pictures. Some tests were moved under parseString as they weren't about paragraph level markup. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - 32326680 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update documentation. - - - - - fbef6406 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update maintainer - - - - - b40e82f4 by Mateusz Kowalczyk at 2014-01-13T02:39:25-06:00 Fixes haskell/haddock#271 Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - f4eafbf8 by Gergő Érdi at 2014-01-19T15:35:16-06:00 Support for -XPatternSynonyms Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - a8939591 by Austin Seipp at 2014-01-29T08:09:04-06:00 Update CPP check for __GLASGOW_HASKELL__ Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 30d7e9d5 by Gergő Érdi at 2014-01-31T00:15:01+08:00 <+>: Don't insert a space when concatenating empty nodes - - - - - a25ccd4d by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Fix @ code blocks In cases where we had some horizontal space before the closing ‘@’, the parser would not accept the block as a code block and we'd get ugly output. - - - - - 0f67305a by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Update tests This updates tests due to Haddock Trac haskell/haddock#271 fix and due to removal of TypeHoles as an extension from GHC. - - - - - 157322a7 by Gergő Érdi at 2014-01-31T01:03:17+08:00 Handle infix vs prefix names correctly everywhere, by explicitly specifying the context The basic idea is that "a" and "+" are either pretty-printed as "a" and "(+)" or "`a`" and "+" - - - - - aa6d9685 by Mateusz Kowalczyk at 2014-01-30T17:21:50+00:00 Correct whitespace in ‘hidden’ test for <+> change - - - - - 121872f0 by Mateusz Kowalczyk at 2014-02-09T17:59:12+00:00 Document module header. Fixes Haddock Trac haskell/haddock#270. - - - - - e3253746 by Mateusz Kowalczyk at 2014-02-10T21:37:48+00:00 Insert a space between module link and description Fixes Haddock Trac haskell/haddock#277. - - - - - 771d2384 by Mateusz Kowalczyk at 2014-02-10T23:27:21+00:00 Ensure a space between type signature and ‘Source’ This is briefly related to Haddock Trac haskell/haddock#249 and employs effectively the suggested fix _but_ it doesn't actually fix the reported issue. This commit simply makes copying the full line a bit less of a pain. - - - - - 8cda9eff by nand at 2014-02-11T15:48:30+00:00 Add support for type/data families This adds support for type/data families with their respective instances, as well as closed type families and associated type/data families. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 3f22c510 by nand at 2014-02-11T15:53:50+00:00 Improve display of poly-kinded type operators This now displays them as (==) k a b c ... to mirror GHC's behavior, instead of the old (k == a) b c ... which was just wrong. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - effb2d6b by nand at 2014-02-11T15:56:50+00:00 Add test case for PatternSynonyms This just tests various stuff including poly-kinded patterns and operator patterns to make sure the rendering isn't broken. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - b38faf0d by Niklas Haas at 2014-02-13T21:53:32+00:00 Get rid of re-implementation of sortBy I have no idea what this was doing lying around here, and due to the usage of tuples it's actually slower, too. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - ac1e0413 by Mateusz Kowalczyk at 2014-02-13T23:57:16+00:00 Only warn about missing docs when docs are missing This fixes the ‘Missing documentation for…’ message for modules with 100% coverage. - - - - - cae2e36a by Niklas Haas at 2014-02-15T21:56:18+00:00 Add test case for inter-module type/data family instances These should show up in every place where the class is visible, and indeed they do right now. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 8bea5c3a by Mateusz Kowalczyk at 2014-02-19T05:11:34+00:00 Use a bespoke data type to indicate fixity This deals with what I imagine was an ancient TODO and makes it much clearer what the argument actually does rather than having the user chase down the comment. - - - - - 5b52d57c by Niklas Haas at 2014-02-22T21:31:03+01:00 Strip a single leading space from bird tracks (#201) This makes bird tracks in the form > foo > bar > bat parse as if they had been written as >foo >bar >bat ie. without the leading whitespace in front of every line. Ideally we also want to look into how leading whitespace affects code blocks written using the @ @ syntax, which are currently unaffected by this patch. - - - - - 5a1315a5 by Simon Hengel at 2014-02-22T21:55:35+01:00 Turn a source code comment into specs - - - - - 784cfe58 by Mateusz Kowalczyk at 2014-02-23T05:02:22+00:00 Update test case for lifted GADT type rendering The parsing of these seems to have been fixed by GHC folk and it now renders differently. IMHO it now renders in a better way so I'm updating the test to reflect this. - - - - - c3c88c2f by Mateusz Kowalczyk at 2014-02-23T06:37:14+00:00 Don't shadow ‘strip’. -Wall complains - - - - - 293031d8 by Niklas Haas at 2014-02-23T15:21:52+01:00 Make ImplicitParams render correctly (#260) This introduces a new precedence level for single contexts (because implicit param contexts always need parens around them, but other types of contexts don't necessarily, even when alone) - - - - - 4200842d by Niklas Haas at 2014-02-23T15:37:13+01:00 Lower precedence of equality constraints This drops them to the new precedence pREC_CTX, which makes single eqaulity constraints show up as (a ~ b) => ty, in line with GHC's rendering. Additional tests added to make sure other type operators render as intended. Current behavior matches GHC - - - - - b59e3227 by Niklas Haas at 2014-02-23T16:11:22+01:00 Add RankNTypes test case to ImplicitParams.hs This test actually tests what haskell/haddock#260 originally reported - I omitted the RankNTypes scenario from the original fix because I realized it's not relevant to the underlying issue and indeed, this renders as intended now. Still good to have more tests. - - - - - c373dbf7 by Mateusz Kowalczyk at 2014-02-24T06:09:54+00:00 Fix rendering of Contents when links are present Fixes Haddock Trac haskell/haddock#267. - - - - - 9ecb0e56 by Mateusz Kowalczyk at 2014-02-24T06:26:50+00:00 Fix wording in the docs - - - - - 4f4dcd8e by Mateusz Kowalczyk at 2014-02-27T03:00:33+00:00 Change rendering of duplicate record field docs See Haddock Trac haskell/haddock#195. We now change this behaviour to only rendering the documentation attached to the first instance of a duplicate field. Perhaps we could improve this by rendering the first instance that has documentation attached to it but for now, we'll stick with this. - - - - - ad8aa609 by Niklas Haas at 2014-03-08T09:43:26+01:00 Render fixity information Affects functions, type synonyms, type families, class names, data type names, constructors, data families, associated TFs/DFs, type synonyms, pattern synonyms and everything else I could think of. - - - - - 6a39c917 by Niklas Haas at 2014-03-09T07:43:39+01:00 Reorder topDeclElem to move the source/wiki links to the top They appear in the same position due to the float: right attribute but now they're always at the top of the box instead of at the bottom. - - - - - 2d34b3b4 by Niklas Haas at 2014-03-09T07:53:46+01:00 Use optLast instead of listToMaybe for sourceUrls/wikiUrls This lets you override them using eg. cabal haddock --haddock-options, which can come in handy if you want to use a different layout or URL for your source code links than cabal-install generates. - - - - - 0eff4624 by Niklas Haas at 2014-03-09T07:53:46+01:00 Differentiate between TH splices (line-links) and regular names This adds a new type of source code link, to a specific line rather than a specific declaration/name - this is used to link to the location of a TH splice that defines a certain name. Rather hefty changes throughout and still one unresolved issue (the line URLs aren't parsed from the third form of --read-interface which means they're currently restricted to same-interface links). Not sure if this issue is really worth all the hassle, especially since we could just use line links in general. This commit also contains some cleanup/clarification of the types in Haddock.Backends.Xhtml.Decl and shortens some overlong lines in the process. Notably, the Bool parameter was replaced by a Unicode type synonym to help clarify its presence in type signatures. - - - - - 66d6f77b by Niklas Haas at 2014-03-09T20:02:43+01:00 Group similar fixities together Identical fixities declared for the same line should now render using syntax like: infix 4 <, >=, >, <= - - - - - 6587f9f5 by Mateusz Kowalczyk at 2014-03-10T04:24:18+00:00 Update changelog - - - - - 7387ddad by Niklas Haas at 2014-03-11T10:26:04+01:00 Include fixity information in the Interface file This resolves fixity information not appearing across package borders. The binary file version has been increased accordingly. - - - - - ab46ef44 by Niklas Haas at 2014-03-11T10:26:04+01:00 Update changelog - - - - - 565cab6f by Niklas Haas at 2014-03-11T10:26:04+01:00 Update appearance of fixity annotations This moves them in-line with their corresponding lines, similar to a presentation envision by @hvr and described in #ghc. Redundant operator names are also omitted when no ambiguity is present. - - - - - 5d7afd67 by Niklas Haas at 2014-03-11T10:26:05+01:00 Filter family instances of hidden types Currently, this check does not extend to hidden right hand sides, although it probably should hide them in that case. - - - - - ec291b0c by Niklas Haas at 2014-03-11T10:26:05+01:00 Add documentation for --source-entity-line - - - - - 0922e581 by Niklas Haas at 2014-03-11T10:37:32+01:00 Revert "Reorder topDeclElem to move the source/wiki links to the top" This reverts commit 843c42c4179526a2ad3526e4c7d38cbf4d50001d. This change is no longer needed with the new rendering style, and it messes with copy/pasting lines. - - - - - 30618e8b by Mateusz Kowalczyk at 2014-03-11T09:41:07+00:00 Bump version to 2.15.0 - - - - - adf3f1bb by Mateusz Kowalczyk at 2014-03-11T09:41:09+00:00 Fix up some whitespace - - - - - 8905f57d by Niklas Haas at 2014-03-13T19:18:06+00:00 Hide RHS of TFs with non-exported right hand sides Not sure what to do about data families yet, since technically it would not make a lot of sense to display constructors that cannot be used by the user. - - - - - 5c44d5c2 by Niklas Haas at 2014-03-13T19:18:08+00:00 Add UnicodeSyntax alternatives for * and -> I could not find a cleaner way to do this other than checking for string equality with the given built-in types. But seeing as it's actually equivalent to string rewriting in GHC's implementation of UnicodeSyntax, it's probably fitting. - - - - - b04a63e6 by Niklas Haas at 2014-03-13T19:18:10+00:00 Display minimal complete definitions for type classes This corresponds to the new {-# MINIMAL #-} pragma present in GHC 7.8+. I also cleaned up some of the places in which ExportDecl is used to make adding fields easier in the future. Lots of test cases have been updated since they now render with minimality information. - - - - - a4a20b16 by Niklas Haas at 2014-03-13T19:18:12+00:00 Strip links from recently added html tests These were accidentally left there when the tests were originally added - - - - - d624f315 by Mateusz Kowalczyk at 2014-03-13T19:19:31+00:00 Update changelog - - - - - d27a21ac by Mateusz Kowalczyk at 2014-03-13T21:19:07+00:00 Always read in prologue files as UTF8 (#286). - - - - - 54b2fd78 by Mateusz Kowalczyk at 2014-03-13T21:28:09+00:00 Style only - - - - - fa4fe650 by Simon Hengel at 2014-03-15T09:04:18+01:00 Add Fuuzetsu maintainers field in cabal file - - - - - f83484b7 by Niklas Haas at 2014-03-15T18:20:24+00:00 Hide minimal definition for only-method classes Previously this was not covered by the All xs check since here it is not actually an All, rather a single Var n. This also adds the previously missing html-test/src/Minimal.hs. - - - - - 0099d276 by Niklas Haas at 2014-03-15T18:20:26+00:00 Fix issue haskell/haddock#281 This is a regression from the data family instances change. Data instances are now distinguished from regular lists by usage of the new class "inst", and the style has been updated to only apply to those. I've also updated the appropriate test case to test this a bit better, including GADT instances with GADT-style records. - - - - - 1f9687bd by Mateusz Kowalczyk at 2014-03-21T17:48:37+00:00 Please cabal sdist - - - - - 75542693 by Mateusz Kowalczyk at 2014-03-22T16:36:16+00:00 Drop needless --split-objs which slows us down. Involves tiny cleanup of all the dynflag bindings. Fixes haskell/haddock#292. - - - - - 31214dc3 by Herbert Valerio Riedel at 2014-03-23T18:01:01+01:00 Fix a few typos Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 0b73e638 by Mateusz Kowalczyk at 2014-03-31T05:34:36+01:00 Print kind signatures on GADTs - - - - - 2bab42f3 by Mateusz Kowalczyk at 2014-03-31T16:53:25+01:00 Add default for new PlatformConstraints field - - - - - 42647c5f by Mateusz Kowalczyk at 2014-03-31T18:29:04+01:00 Drop leading whitespace in @-style blocks. Fixes haskell/haddock#201. - - - - - 98208294 by Niklas Haas at 2014-03-31T20:09:58+02:00 Crash when exporting record selectors of data family instances This fixes bug haskell/haddock#294. This also fixes a related but never-before-mentioned bug about the display of GADT record selectors with non-polymorphic type signatures. Note: Associated data type constructors fail to show up if nothing is exported that they could be attached to. Exporting any of the data types in the instance head, or the class + data family itself, causes them to show up, but in the absence of either of these, exporting just the associated data type with the constructor itself will result in it being hidden. The only scenario I can come up that would involve this kind of situation involved OverlappingInstances, and even then it can be mitigated by just exporting the class itself, so I'm not going to solve it since the logic would most likely be very complicated. - - - - - 3832d171 by Mateusz Kowalczyk at 2014-04-01T19:07:33+01:00 Make CHANGES consistent with what's now in 2.14.2 - - - - - c386ae89 by Mateusz Kowalczyk at 2014-04-01T19:18:36+01:00 Actually bundle extra spec tests in sdist - - - - - bd57a6d3 by Mateusz Kowalczyk at 2014-04-03T21:13:48+01:00 Update test cases for GHC bug haskell/haddock#8945, Haddock haskell/haddock#188 The order of signature groups has been corrected upstream. Here we add a test case and update some existing test-cases to reflect this change. We remove grouped signature in test cases that we can (Minimal, BugDeprecated &c) so that the test is as self-contained as possible. - - - - - 708b88b1 by Mateusz Kowalczyk at 2014-04-03T21:16:07+01:00 Enforce strict GHC version in cabal file This stops people with 7.6.3 trying to install 2.15.x which clearly won't work. Unfortunately we shipped 2.14.x without realising this. - - - - - 60334f7c by Mateusz Kowalczyk at 2014-04-03T21:19:24+01:00 Initialise some new PlatformConstants fields - - - - - ea77f668 by Mateusz Kowalczyk at 2014-04-11T16:52:23+01:00 We don't actually want unicode here - - - - - 0b651cae by Mateusz Kowalczyk at 2014-04-11T18:13:30+01:00 Parse identifiers with ^ and ⋆ in them. Fixes haskell/haddock#298. - - - - - e8ad0f5f by Mateusz Kowalczyk at 2014-04-11T18:47:41+01:00 Ignore version string during HTML tests. - - - - - de489089 by Mateusz Kowalczyk at 2014-04-11T18:59:30+01:00 Update CHANGES to follow 2.14.3 - - - - - beb464a9 by Gergő Érdi at 2014-04-13T16:31:10+08:00 remove Origin flag from LHsBindsLR - - - - - cb16f07c by Herbert Valerio Riedel at 2014-04-21T17:16:50+02:00 Replace local `die` by new `System.Exit.die` Starting with GHC 7.10, System.Exit exports the new `die` which is essentially the same as Haddock.Util.die, so this commit changes Haddock.Util.die to be a simple re-export of System.Exit.die. See also https://ghc.haskell.org/trac/ghc/ticket/9016 for more details. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 9b9b23c7 by Mateusz Kowalczyk at 2014-05-03T15:40:11+02:00 Disambiguate ‘die’ in test runners. - - - - - 5d28a2b8 by Mateusz Kowalczyk at 2014-05-05T09:19:49+02:00 Prepare modules for parser split. We have to generalise the Doc (now DocH) slightly to remove the dependency on GHC-supplied type. - - - - - d3967ff3 by Mateusz Kowalczyk at 2014-05-05T11:00:41+02:00 Move parser + parser tests out to own package. We move some types out that are necessary as well and then re-export and specialise them in the core Haddock. Reason for moving out spec tests is that if we're working on the parser, we can simply work on that and we can ignore the rest of Haddock. The downside is that it's a little inconvenient if at the end of the day we want to see that everything passes. - - - - - 522a448d by Mateusz Kowalczyk at 2014-05-05T11:14:47+02:00 Move out Show and Eq instances to Types They are much more useful to the users here. - - - - - 11a6f0f2 by Mateusz Kowalczyk at 2014-05-06T13:50:31+02:00 Remove no longer necessary parser error handling. We can now drop some Maybe tests and even lets us strip an error handling monad away in a few places. - - - - - 6992c924 by Mateusz Kowalczyk at 2014-05-14T02:23:55+02:00 Please the GHC build-system. As I can not figure out how to do this properly, if we're in GHC tree, we treat the library as being the same package. If we're not in the tree, we require that the library be installed separately. - - - - - 7a8ad763 by Mateusz Kowalczyk at 2014-05-14T14:50:25+02:00 Update issue tracker URL - - - - - f616c521 by Mateusz Kowalczyk at 2014-05-14T14:53:32+02:00 Update issue tracker URL for haddock-library - - - - - 66580ded by Gergő Érdi at 2014-05-25T14:24:16+08:00 Accomodate change in PatSyn representation - - - - - 0e43b988 by Mateusz Kowalczyk at 2014-05-29T03:15:29+02:00 Revert "Accomodate change in PatSyn representation" This reverts commit 57aa591362d7c8ba21285fccd6a958629a422091. I am reverting this because I pushed it to master when it was meant to stay on a wip-branch. Sorry Gergo and everyone who had trouble due to this. - - - - - e10d7ec8 by Mateusz Kowalczyk at 2014-05-29T03:24:11+02:00 Revert "Revert "Accomodate change in PatSyn representation"" This reverts commit e110e6e70e40eed06c06676fd2e62578da01d295. Apparently as per GHC commit ac2796e6ddbd54c5762c53e2fcf29f20ea162fd5 this was actually intended. Embarrasing for me. - - - - - 5861aca9 by Mateusz Kowalczyk at 2014-06-05T19:49:27+02:00 Clear up highlighting of identifiers with ‘'’s. - - - - - d7cc420f by Simon Peyton Jones at 2014-06-06T12:41:09+01:00 Follow change in patSynSig - - - - - 938b4fd8 by Mateusz Kowalczyk at 2014-06-12T07:24:29+02:00 Slightly update the readme. Style-sheets are no longer a recent thing, dead links, old maintainers, different formats. - - - - - c7799dea by Mateusz Kowalczyk at 2014-06-18T00:05:56+02:00 Update cabal files Update repository urls, use subdir property for haddock-library and use a separate versioning scheme for haddock-library in preparation for release. - - - - - a2750b6a by Simon Hengel at 2014-06-18T11:01:18+08:00 Compatibility with older versions of base and bytestring - - - - - 009b4b03 by Simon Hengel at 2014-06-18T11:14:01+08:00 Enable travis-ci for haddock-library - - - - - 9b5862eb by Simon Hengel at 2014-06-18T11:14:01+08:00 haddock-library: Do not depend on haddock-library in test suite I think you either add src to hs-source-dirs or the library to build-depends. But doing both does not make sense (AFAICT). - - - - - fb1f3279 by Simon Hengel at 2014-06-18T11:49:05+08:00 haddock-library: Use -Wall for specs - - - - - 649340e1 by Mateusz Kowalczyk at 2014-06-18T06:58:54+02:00 Use Travis with multiple GHC versions When using HEAD, we build haddock-library directly from repository as a dependency (and thanks to --enable-tests, the tests get ran anyway). In all other cases, we manually run the tests on haddock-library only and don't test the main project. - - - - - d7eeeec2 by Mateusz Kowalczyk at 2014-06-18T07:49:04+02:00 Comment improvements + few words in cabal file - - - - - 0f8db914 by Simon Hengel at 2014-06-18T13:52:23+08:00 Use doctest to check examples in documentation - - - - - 2888a8dc by Simon Hengel at 2014-06-18T14:16:48+08:00 Remove doctest dependency (so that we can use haddock-library with doctest) - - - - - 626d5e85 by Mateusz Kowalczyk at 2014-06-18T08:41:25+02:00 Travis tweaks - - - - - 41d4f9cc by Mateusz Kowalczyk at 2014-06-18T08:58:43+02:00 Don't actually forget to install specified GHC. - - - - - c6aa512a by John MacFarlane at 2014-06-18T10:43:57-07:00 Removed reliance on LambdaCase (which breaks build with ghc 7.4). - - - - - b9b93b6f by John MacFarlane at 2014-06-18T10:54:56-07:00 Fixed haddock warnings. - - - - - a41b0ab5 by Mateusz Kowalczyk at 2014-06-19T01:20:10+02:00 Update Travis, bump version - - - - - 864bf62a by Mateusz Kowalczyk at 2014-06-25T10:36:54+02:00 Fix anchors. Closes haskell/haddock#308. - - - - - 53df91bb by Mateusz Kowalczyk at 2014-06-25T15:04:49+02:00 Drop DocParagraph from front of headers I can not remember why they were wrapped in paragraphs to begin with and it seems unnecessary now that I test it. Closes haskell/haddock#307. - - - - - 29b5f2fa by Mateusz Kowalczyk at 2014-06-25T15:17:20+02:00 Don't mangle append order for nested lists. The benefit of this is that the ‘top-level’ element of such lists is properly wrapped in <p> tags so any CSS working with these will be applied properly. It also just makes more sense. Pointed out at jgm/pandoc#1346. - - - - - 05cb6e9c by Mateusz Kowalczyk at 2014-06-25T15:19:45+02:00 Bump haddock-library to 1.1.0 for release - - - - - 70feab15 by Iavor Diatchki at 2014-07-01T03:37:07-07:00 Propagate overloading-mode for instance declarations in haddock (#9242) - - - - - d4ca34a7 by Simon Peyton Jones at 2014-07-14T16:23:15+01:00 Adapt to new definition of HsDecls.TyFamEqn This is a knock-on from the refactoring from Trac haskell/haddock#9063. I'll push the corresponding changes to GHC shortly. - - - - - f91e2276 by Edward Z. Yang at 2014-07-21T08:14:19-07:00 Track GHC PackageId to PackageKey renaming. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - b010f9ef by Edward Z. Yang at 2014-07-25T16:28:46-07:00 Track changes for module reexports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - 8b85f9f9 by Mateusz Kowalczyk at 2014-07-28T13:25:43+02:00 Catch mid-line URLs. Fixes haskell/haddock#314. - - - - - 4c613a78 by Edward Z. Yang at 2014-08-05T03:11:00-07:00 Track type signature change of lookupModuleInAllPackages Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - e80b051c by Edward Z. Yang at 2014-08-05T17:34:26+01:00 If GhcProfiled, also build Haddock profiled. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f9cccd29 by Edward Z. Yang at 2014-08-07T14:23:35+01:00 Ignore TAGS files. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 00b3af52 by Mateusz Kowalczyk at 2014-08-08T04:58:19+02:00 Update to attoparsec-0.12.1.1 There seems to be memory and speed improvement. - - - - - 5457dc71 by Mateusz Kowalczyk at 2014-08-08T18:24:02+02:00 Fix forgotten src - - - - - 3520cb04 by Mateusz Kowalczyk at 2014-08-14T20:19:07+01:00 Bump down the version for master to 2.14.4 - - - - - dc98c21b by Mateusz Kowalczyk at 2014-08-14T20:23:27+01:00 Revert "Track type signature change of lookupModuleInAllPackages" This reverts commit d59fec2c9551b5662a3507c0011e32a09a9c118f. - - - - - 3f2038c0 by Mateusz Kowalczyk at 2014-08-14T20:23:31+01:00 Revert "Track changes for module reexports." This reverts commit b99b57c0df072d12b67816b45eca2a03cb1da96d. - - - - - 56d4e49e by Mateusz Kowalczyk at 2014-08-14T20:23:42+01:00 Revert "Track GHC PackageId to PackageKey renaming." This reverts commit 8ac42d3327473939c013551750425cac191ff0fd. - - - - - 726ea3cb by Mateusz Kowalczyk at 2014-08-14T20:23:47+01:00 Revert "Adapt to new definition of HsDecls.TyFamEqn" This reverts commit cb96b4f1ed0462b4a394b9fda6612c3bea9886bd. - - - - - 61a88ff0 by Mateusz Kowalczyk at 2014-08-14T20:23:52+01:00 Revert "Propagate overloading-mode for instance declarations in haddock (#9242)" This reverts commit 8d20ca8d5a9bee73252ff2035ec45f9c03d0820c. - - - - - a32ba674 by Mateusz Kowalczyk at 2014-08-14T20:26:03+01:00 Revert "Disambiguate ‘die’ in test runners." This reverts commit dba02d6df32534aac5d257f2d28596238d248942. - - - - - f335820f by Mateusz Kowalczyk at 2014-08-14T20:26:09+01:00 Revert "Replace local `die` by new `System.Exit.die`" This reverts commit 08aa509ebac58bfb202ea79c7c41291ec280a1c5. - - - - - 107078e4 by Mateusz Kowalczyk at 2014-08-14T20:27:34+01:00 Merge branch 'reverts' This reverts any changes that were made to have Haddock compile with 7.9. When 7.10 release comes, we can simply re-apply all the patches and any patches that occur on ghc-head branch from now on. This allows us to build master with 7.8.3 - - - - - b44b3871 by Mateusz Kowalczyk at 2014-08-15T02:47:40+01:00 Fix haskell/haddock#313 by doing some list munging. I get rid of the Monoid instance because we weren't satisfying the laws. Convenience of having <> didn't outweigh the shock-factor of having it behave badly. - - - - - e1a62cde by Mateusz Kowalczyk at 2014-08-15T02:52:56+01:00 Stop testing haskell/haddock#188. Because the change is in GHC 7.9 and we now work against 7.8.3, this test no longer makes sense. We revert it until 7.10 becomes the standard version. If anything, there should be a test for this in GHC itself. - - - - - 54e8286d by Mateusz Kowalczyk at 2014-08-15T05:31:57+01:00 Add haskell/haddock#313 to CHANGES - - - - - 9df7ad5d by Simon Hengel at 2014-08-20T11:25:32+08:00 Fix warning - - - - - ee2574d6 by Simon Hengel at 2014-08-20T12:07:01+08:00 Fix travis builds - - - - - 384cf2e6 by Simon Hengel at 2014-08-20T12:14:31+08:00 Require GHC 7.8.3 - - - - - d4779863 by Simon Hengel at 2014-08-22T12:14:16+08:00 Move Haddock API to a separate package - - - - - 80f3e0e1 by Simon Hengel at 2014-08-22T14:57:38+08:00 Bump version to 2.15.0 and add version constraints - - - - - 309a94ce by Simon Hengel at 2014-08-22T15:18:06+08:00 Add deprecated compatibility module - - - - - 4d1e4e3f by Luite Stegeman at 2014-08-22T20:46:45+02:00 export things to allow customizing how the Ghc session is run - - - - - 47884591 by Luite Stegeman at 2014-08-22T20:46:51+02:00 ghc 7.8.2 compatibility - - - - - 5ea94e2c by Luite Stegeman at 2014-08-22T22:08:58+02:00 install dependencies for haddock-api on travis - - - - - 9fb845b2 by Mateusz Kowalczyk at 2014-08-23T10:09:34+01:00 Move sources under haddock-api/src - - - - - 85817dc4 by Mateusz Kowalczyk at 2014-08-23T10:10:48+01:00 Remove compat stuff - - - - - 151c6169 by Niklas Haas at 2014-08-24T08:14:10+02:00 Fix extra whitespace on signatures and update all test cases This was long overdue, now running ./accept.lhs on a clean test from master will not generate a bunch of changes. - - - - - d320e0d2 by Niklas Haas at 2014-08-24T08:14:35+02:00 Omit unnecessary foralls and fix haskell/haddock#315 This also fixes haskell/haddock#86. - - - - - bdafe108 by Mateusz Kowalczyk at 2014-08-24T15:06:46+01:00 Update CHANGES - - - - - fafa6d6e by Mateusz Kowalczyk at 2014-08-24T15:14:23+01:00 Delete few unused/irrelevant/badly-place files. - - - - - 3634923d by Duncan Coutts at 2014-08-27T13:49:31+01:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. - - - - - 539a7e70 by Herbert Valerio Riedel at 2014-08-31T11:36:32+02:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 9e3a0e5b by Mateusz Kowalczyk at 2014-08-31T12:54:43+01:00 Bump version in doc - - - - - 4a177525 by Mateusz Kowalczyk at 2014-08-31T13:01:23+01:00 Bump haddock-library version - - - - - f99c1384 by Mateusz Kowalczyk at 2014-08-31T13:05:25+01:00 Remove references to deleted files - - - - - 5e51a247 by Mateusz Kowalczyk at 2014-08-31T14:18:44+01:00 Make the doc parser not complain - - - - - 2cedb49a by Mateusz Kowalczyk at 2014-09-03T03:33:15+01:00 CONTRIBUTING file for issues - - - - - 88027143 by Mateusz Kowalczyk at 2014-09-04T00:46:59+01:00 Mention --print-missing-docs - - - - - 42f6754f by Alan Zimmerman at 2014-09-05T18:13:24-05:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e712719e by Austin Seipp at 2014-09-09T01:03:27-05:00 Fix import of 'empty' due to AMP. Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 71c29755 by Herbert Valerio Riedel at 2014-09-09T17:35:20+02:00 Bump `base` constraint for AMP - - - - - 0bf9f3ed by Mateusz Kowalczyk at 2014-09-12T19:18:32+01:00 Delete stale ANNOUNCE - - - - - cac89ee6 by Krzysztof Gogolewski at 2014-09-14T17:17:09+02:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 4d683426 by Edward Z. Yang at 2014-09-18T13:38:11-07:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 80697fd5 by Herbert Valerio Riedel at 2014-09-19T00:07:52+02:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. - - - - - c015eb70 by Herbert Valerio Riedel at 2014-09-19T00:10:36+02:00 Revert "Followup changes to addition of -fwarn-context-quantification" This reverts commit 4023817d7c0e46db012ba2eea28022626841ca9b temporarily as the respective feature hasn't landed in GHC HEAD yet, but this commit blocks later commits from being referenced in GHC HEAD. - - - - - 38ded784 by Edward Z. Yang at 2014-09-18T15:32:15-07:00 Revert "Revert "Followup changes to addition of -fwarn-context-quantification"" This reverts commit db14fd8ab4fab43694139bc203808b814eafb2dc. It's in HEAD now. - - - - - f55d59c9 by Herbert Valerio Riedel at 2014-09-26T19:18:28+02:00 Revert "Fix import of 'empty' due to AMP." This reverts commit 0cc5bc85e9fca92ab712b68a2ba2c0dd9d3d79f4 since it turns out we don't need to re-export `empty` from Control.Monad after all. - - - - - 467050f1 by David Feuer at 2014-10-09T20:07:36-04:00 Fix improper lazy IO use Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. - - - - - cc47b699 by Edward Z. Yang at 2014-10-09T21:38:19-07:00 Fix use-after-close lazy IO bug Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. Signed-off-by: David Feuer <David.Feuer at gmail.com> Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 87babcbe by Austin Seipp at 2014-10-20T20:05:27-05:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - ab259516 by Austin Seipp at 2014-10-20T20:07:01-05:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - b918093c by Mateusz Kowalczyk at 2014-10-29T03:59:39+00:00 Experimental support for collapsable headers Closes haskell/haddock#335 - - - - - 849db129 by Mateusz Kowalczyk at 2014-10-29T10:07:26+01:00 Experimental support for collapsable headers (cherry picked from commit e2ed3b9d8dfab09f1b1861dbc8e74f08e137ebcc) - - - - - a4cc4789 by Herbert Valerio Riedel at 2014-10-31T11:08:26+01:00 Collapse user-defined section by default (re haskell/haddock#335) - - - - - 9da1b33e by Yuras Shumovich at 2014-10-31T16:11:04-05:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - c625aefc by Austin Seipp at 2014-10-31T19:34:10-05:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - c7738e5e by Simon Hengel at 2014-11-02T07:25:30+08:00 Remove -fobject-code from .ghci (this slows down reloads on modifications) - - - - - d4a86e95 by Simon Hengel at 2014-11-03T09:26:11+08:00 Get rid of StandaloneDeriving - - - - - a974e311 by Simon Hengel at 2014-11-03T09:26:11+08:00 Derive more instances - - - - - 8aa0c4d7 by Simon Hengel at 2014-11-03T09:27:08+08:00 Remove unused language extensions - - - - - 3052d46a by Simon Hengel at 2014-11-03T09:30:46+08:00 Minor refactoring - - - - - 4281d3cb by Simon Hengel at 2014-11-03T09:30:46+08:00 parser: Try to parse definition lists right before text paragraphs - - - - - 8ba12bf9 by Simon Hengel at 2014-11-03T09:34:19+08:00 Add support for markdown links (closes haskell/haddock#336) - - - - - a2f8d747 by Simon Hengel at 2014-11-03T09:34:19+08:00 Allow markdown links at the beginning of a paragraph - - - - - 53b11207 by Simon Hengel at 2014-11-03T09:34:20+08:00 Update documentation - - - - - 652267c6 by Simon Hengel at 2014-11-03T09:34:20+08:00 Add support for markdown images - - - - - 9d667502 by Simon Hengel at 2014-11-03T09:34:20+08:00 Allow an optional colon after the closing bracket of definition lists This is to disambiguate them from markdown links and will be require with a future release. - - - - - 8167fc32 by Mateusz Kowalczyk at 2014-11-04T01:16:51+00:00 whitespace only - - - - - 3da62981 by Mateusz Kowalczyk at 2014-11-04T01:17:31+00:00 Fix re-exports of built-in type families Fixes haskell/haddock#310 - - - - - edc76b34 by Mateusz Kowalczyk at 2014-11-04T02:54:28+00:00 Turn some uses of error into recoverable warnings This should at the very least not abort when something weird happens. It does feel like we should have a type that carries these errors until the end however as the user might not see them unless they are printed at the end. - - - - - 0a137400 by Mateusz Kowalczyk at 2014-11-04T04:09:44+00:00 Fix warnings - - - - - d068fc21 by Mateusz Kowalczyk at 2014-11-04T21:04:07+00:00 Fix parsing of identifiers written in infix way - - - - - 1a9f2f3d by Simon Hengel at 2014-11-08T11:32:42+08:00 Minor code simplification - - - - - 6475e9b1 by Simon Hengel at 2014-11-08T17:28:33+08:00 newtype-wrap parser monad - - - - - dc1ea105 by Herbert Valerio Riedel at 2014-11-15T11:55:43+01:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - fbb1aca4 by Simon Hengel at 2014-11-16T08:51:38+08:00 State intention rather than implementation details in Haddock comment - - - - - 97851ab2 by Simon Hengel at 2014-11-16T10:20:19+08:00 (wip) Add support for @since (closes haskell/haddock#26) - - - - - 34bcd18e by Gergő Érdi at 2014-11-20T22:35:38+08:00 Update Haddock to new pattern synonym type signature syntax - - - - - 304b7dc3 by Jan Stolarek at 2014-11-20T17:48:43+01:00 Follow changes from haskell/haddock#9812 - - - - - 920f9b03 by Richard Eisenberg at 2014-11-20T16:52:50-05:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 0bfe4e78 by Alan Zimmerman at 2014-11-21T11:23:09-06:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 356ed45a by Thomas Winant at 2014-11-28T16:11:22-06:00 Support for PartialTypeSignatures - - - - - 5dc8f3b1 by Gergő Érdi at 2014-11-29T15:39:09+08:00 For pattern synonyms, render "pattern" as a keyword - - - - - fe704480 by Mateusz Kowalczyk at 2014-12-09T03:38:32+00:00 List new module in cabal file - - - - - b9ad5a29 by Mateusz Kowalczyk at 2014-12-10T00:58:24+00:00 Allow the parser to spit out meta-info Currently we only use it only for ‘since’ annotations but with these patches it should be fairly simple to add new attributes if we wish to. Closes haskell/haddock#26. It seems to work fine but due to 7.10 rush I don't have the chance to do more exhaustive testing right now. The way the meta is output (emphasis at the end of the whole comment) is fairly arbitrary and subject to bikeshedding. Note that this makes test for Bug310 fail due to interface version bump: it can't find the docs for base with this interface version so it fails. There is not much we can do to help this because it tests for ’built-in’ identifier, not something we can provide ourselves. - - - - - 765af0e3 by Mateusz Kowalczyk at 2014-12-10T01:17:19+00:00 Update doctest parts of comments - - - - - 8670272b by jpmoresmau at 2014-12-10T01:35:31+00:00 header could contain several lines Closes haskell/haddock#348 - - - - - 4f9ae4f3 by Mateusz Kowalczyk at 2014-12-12T06:22:31+00:00 Revert "Merge branch 'reverts'" This reverts commit 5c93cc347773c7634321edd5f808d5b55b46301f, reversing changes made to 5b81a9e53894d2ae591ca0c6c96199632d39eb06. Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - e974ac94 by Duncan Coutts at 2014-12-12T06:26:11+00:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. Conflicts: haddock-api/src/Haddock.hs - - - - - 2f3a2365 by Herbert Valerio Riedel at 2014-12-12T06:26:51+00:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 1dbd6390 by Alan Zimmerman at 2014-12-12T06:32:07+00:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - bb6ff1f4 by Mateusz Kowalczyk at 2014-12-12T06:35:07+00:00 Bump ‘base’ constraint Follows the similar commit made on ghc-head branch - - - - - 466fe4ab by Krzysztof Gogolewski at 2014-12-12T06:37:42+00:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 97e080c9 by Edward Z. Yang at 2014-12-12T06:39:35+00:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: haddock-api/src/Haddock/ModuleTree.hs - - - - - 20b2af56 by Herbert Valerio Riedel at 2014-12-12T06:42:50+00:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. Conflicts: haddock-library/src/Documentation/Haddock/Parser.hs - - - - - b3ad269d by Austin Seipp at 2014-12-12T06:44:14+00:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 072df0dd by Austin Seipp at 2014-12-12T06:45:01+00:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - dbb9294a by Herbert Valerio Riedel at 2014-12-12T06:46:17+00:00 Collapse user-defined section by default (re haskell/haddock#335) Conflicts: haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs - - - - - f23ab545 by Yuras Shumovich at 2014-12-12T06:46:41+00:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - 753a4b67 by Austin Seipp at 2014-12-12T06:46:51+00:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8954e8f5 by Herbert Valerio Riedel at 2014-12-12T06:50:53+00:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - d2b06d61 by Gergő Érdi at 2014-12-12T07:07:30+00:00 Update Haddock to new pattern synonym type signature syntax Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 1ff02426 by Jan Stolarek at 2014-12-12T07:13:24+00:00 Follow changes from haskell/haddock#9812 Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - 06ad7600 by Richard Eisenberg at 2014-12-12T07:13:43+00:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 8fd2aa8b by Alan Zimmerman at 2014-12-12T07:22:25+00:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Backends/LaTeX.hs haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 95c3db98 by Thomas Winant at 2014-12-12T07:35:49+00:00 Support for PartialTypeSignatures Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs haddock-api/src/Haddock/Interface/Create.hs - - - - - 45494428 by Gergő Érdi at 2014-12-12T07:36:18+00:00 For pattern synonyms, render "pattern" as a keyword - - - - - a237e3eb by Mateusz Kowalczyk at 2014-12-12T12:27:13+00:00 Various fixups and bumps for next release - - - - - 22918bcd by Herbert Valerio Riedel at 2014-12-14T10:11:47+01:00 Remove redundant wild-card pattern match (this would otherwise cause a build-failure with `-Werror`) - - - - - 1d6ce947 by Herbert Valerio Riedel at 2014-12-14T10:17:06+01:00 Treat GHC 7.10 the same as GHC 7.9 ...since the current GHC 7.9 is going to become GHC 7.10 real-soon-now anyway - - - - - f434ea89 by Herbert Valerio Riedel at 2014-12-14T18:26:50+01:00 Fixup ghc.mk (follow-up to 1739375eb23342) This makes the GHC build-system aware of the data-files to be copied into the bindist (as haddock.cabal doesn't list those anymore) - - - - - 6fb839eb by Mateusz Kowalczyk at 2014-12-17T09:28:59+00:00 Only keep one Version instead of blindly appending - - - - - 40645489 by Mateusz Kowalczyk at 2014-12-18T07:09:44+00:00 Fix dependency version - - - - - 8b3b927b by Mateusz Kowalczyk at 2014-12-18T07:14:23+00:00 Print missing docs by default Adds --no-print-missing-docs - - - - - 59666694 by Mateusz Kowalczyk at 2014-12-18T07:21:37+00:00 update changelog - - - - - aa6d168e by Mateusz Kowalczyk at 2014-12-18T07:30:58+00:00 Update docs for @since - - - - - 2d7043ee by Luite Stegeman at 2014-12-19T18:29:35-06:00 hide projectVersion from DynFlags since it clashes with Haddock.Version.projectVersion - - - - - aaa70fc0 by Luite Stegeman at 2014-12-22T15:58:43+01:00 Add missing import for standalone haddock-api package - - - - - 9ce01269 by Herbert Valerio Riedel at 2014-12-22T17:48:45+01:00 Reset ghc-head with master's tree (this is an overwriting git merge of master into ghc-head) - - - - - fcd6fec1 by Herbert Valerio Riedel at 2014-12-22T17:51:52+01:00 Bump versions for ghc-7.11 - - - - - 525ec900 by Mateusz Kowalczyk at 2014-12-23T13:36:24+00:00 travis-ci: test with HEAD - - - - - cbf494b5 by Simon Peyton Jones at 2014-12-23T15:22:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 50e01c99 by Mateusz Kowalczyk at 2014-12-29T15:28:47+00:00 Make travis use 7.10.x - - - - - 475e60b0 by Njagi Mwaniki at 2014-12-29T15:30:44+00:00 Turn the README into GitHub Markdown format. Closes haskell/haddock#354 - - - - - 8cacf48e by Luite Stegeman at 2015-01-05T16:25:37+01:00 bump haddock-api ghc dependency to allow release candidate and first release - - - - - 6ed6cf1f by Simon Peyton Jones at 2015-01-06T16:37:47+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 8b484f33 by Simon Peyton Jones at 2015-01-08T15:50:22+00:00 Track naming change in DataCon - - - - - 23c5c0b5 by Alan Zimmerman at 2015-01-16T10:15:11-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e7a5532c by JP Moresmau at 2015-01-22T17:19:03+00:00 Ignore warnings, install Cabal 1.22 - - - - - 86942c84 by jpmoresmau at 2015-01-22T17:19:04+00:00 solve dataDir ambiguity - - - - - 5ceb743e by jpmoresmau at 2015-01-22T19:17:32+00:00 support GHC 7.10: no Safe-Inferred, Foldable instance - - - - - 6a3b3fb5 by Mateusz Kowalczyk at 2015-01-22T19:32:10+00:00 Update test files Test: a correct behaviour for fields comma-separating values. I'm surprised we had no bug open for this. Maybe it affects how haskell/haddock#301 renders now but I doubt. Operators: Seems GHC is giving us a new order for operators, something must have changed on their side again. cc @haasn , this makes the fixity to the side not match the order on the LHS which is a bit unpleasant. Maybe the fixity can be made to match the GHC order? Bug335: We expand examples by default now. Bug310: Now inferred safe. - - - - - 708f8b2f by jpmoresmau at 2015-01-22T19:36:59+00:00 Links to source location of class instance definitions - - - - - 5cf8a6da by Vincent Berthoux at 2015-01-22T19:59:58+00:00 Filter '\r' from comments due to Windows problems. On Windows this was causing newline to be rendered twice in code blocks. Closes haskell/haddock#359, fixes haskell/haddock#356. - - - - - 1749e6f0 by Mateusz Kowalczyk at 2015-01-22T20:31:27+00:00 Changelog only - - - - - c8145f90 by Mateusz Kowalczyk at 2015-01-22T23:34:05+00:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. - - - - - 14248254 by Mateusz Kowalczyk at 2015-01-22T23:43:18+00:00 Sort out some module import warnings - - - - - d8a38989 by Simon Peyton Jones at 2015-01-23T07:10:16-06:00 Track naming change in DataCon (cherry picked from commit 04cf63d0195837ed52075ed7d2676e71831e8a0b) - - - - - d3ac6ae4 by Alan Zimmerman at 2015-01-23T07:17:19-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit d61bbc75890e4eb0ad508b9c2a27b91f691213e6) - - - - - 4c1ffeb0 by Simon Peyton Jones at 2015-02-10T12:10:33+00:00 Track changes in HsSyn for quasi-quotes - - - - - 775d20f7 by Mateusz Kowalczyk at 2015-03-15T08:11:48+01:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. (cherry picked from commit 8e06728afb0784128ab2df0be7a5d7a191d30ff4) - - - - - f9245e72 by Phil Ruffwind at 2015-03-16T04:32:01-04:00 Prevent Synopsis from using up too much horizontal space When long type signatures occur in the Synopsis, the element is stretched beyond the width of the window. Scrollbars don't appear, so it's impossible to read anything when this happens. - - - - - cd8fa415 by Mateusz Kowalczyk at 2015-03-17T21:59:39+00:00 Update changelog Closes haskell/haddock#151 due to 71170fc77962f10d7d001e3b8bc8b92bfeda99bc - - - - - b5248b47 by Ben Gamari at 2015-03-25T17:12:17+00:00 Make the error encountered when a package can't be found more user-friendly Closes haskell/haddock#369 - - - - - b756b772 by Mateusz Kowalczyk at 2015-03-26T16:31:40+00:00 Remove now redundant imports - - - - - 5ea5e8dd by Mateusz Kowalczyk at 2015-03-26T16:45:52+00:00 Update test to account for \r filtering - - - - - 6539bfb3 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Test for anchor defaulting I delete the old tests because it turns out that: * test runner would never put them in scope of each other even with imports so just one would suffice * test runner actually needed some hacking to keep links so in the end we would end up with no anchors making them useless - - - - - 1a01d950 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Clearly default to variables in out of scope case - - - - - 7943abe8 by Mateusz Kowalczyk at 2015-03-27T01:14:11+00:00 Fix Hoogle display of constructors Fixes haskell/haddock#361 - - - - - 6d6e587e by Mateusz Kowalczyk at 2015-03-27T01:45:18+00:00 Fully qualify names in Hoogle instances output Closes haskell/haddock#263 - - - - - 52dac365 by Mateusz Kowalczyk at 2015-03-27T01:55:01+00:00 Update changelog - - - - - ca5af9a8 by Mateusz Kowalczyk at 2015-03-27T02:43:55+00:00 Output method documentation in Hoogle backend One thing of note is that we no longer preserve grouping of methods and print each method on its own line. We could preserve it if no documentation is present for any methods in the group if someone asks for it though. Fixes haskell/haddock#259 - - - - - a33f0c10 by Mateusz Kowalczyk at 2015-03-27T03:04:21+00:00 Don't print instance safety information in Hoogle Fixes haskell/haddock#168 - - - - - df6c935a by Mateusz Kowalczyk at 2015-03-28T00:11:47+00:00 Post-release version bumps and changelog - - - - - dde8f7c0 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Loosen bounds on haddock-* - - - - - de93bf89 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Expand response files in arguments Closes haskell/haddock#285 - - - - - 1f0b0856 by Zejun Wu at 2015-04-26T16:35:35-07:00 Do not insert anchor for section headings in contents box - - - - - 860439d7 by Simon Peyton Jones at 2015-05-01T09:36:47+01:00 Track change in API of TyCon - - - - - a32f3e5f by Adam Gundry at 2015-05-04T15:32:59+01:00 Track API changes to support empty closed type familes - - - - - 77e98bee by Ben Gamari at 2015-05-06T20:17:08+01:00 Ignore doc/haddock.{ps,pdf} - - - - - 663d0204 by Murray Campbell at 2015-05-11T04:47:37-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8bb0dcf5 by Murray Campbell at 2015-05-11T06:35:06-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit 2380f07c430c525b205ce2eae6dab23c8388d899) - - - - - bad900ea by Adam Bergmark at 2015-05-11T15:29:39+01:00 haddock-library: require GHC >= 7.4 `Data.Monoid.<>` was added in base-4.5/GHC-7.4 Closes haskell/haddock#394 Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - daceff85 by Simon Peyton Jones at 2015-05-13T12:04:21+01:00 Track the new location of setRdrNameSpace - - - - - 1937d1c4 by Alan Zimmerman at 2015-05-25T21:27:15+02:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - ee0fb6c2 by Łukasz Hanuszczak at 2015-05-27T11:51:31+02:00 Create simple method for indentation parsing. - - - - - 7d6fcad5 by Łukasz Hanuszczak at 2015-05-27T21:36:13+02:00 Make nested lists count indentation according to first item. - - - - - d6819398 by Łukasz Hanuszczak at 2015-05-27T22:46:13+02:00 Add simple test case for arbitrary-depth list nesting. - - - - - 2929c54d by Łukasz Hanuszczak at 2015-06-03T02:11:31+02:00 Add arbitrary-indent spec test for parser. - - - - - 9a0a9bb0 by Mateusz Kowalczyk at 2015-06-03T05:25:29+01:00 Update docs with info on new list nesting rule Fixes haskell/haddock#278 through commits from PR haskell/haddock#401 - - - - - 12efc92c by Mateusz Kowalczyk at 2015-06-03T05:29:26+01:00 Update some meta data at the top of the docs - - - - - 765ee49f by Bartosz Nitka at 2015-06-07T08:40:59-07:00 Add some Hacking docs for getting started - - - - - 19aaf851 by Bartosz Nitka at 2015-06-07T08:44:30-07:00 Fix markdown - - - - - 2a90cb70 by Mateusz Kowalczyk at 2015-06-08T15:08:36+01:00 Refine hacking instructions slightly - - - - - 0894da6e by Thomas Winant at 2015-06-08T23:47:28-05:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 10a9bb76 by Emanuel Borsboom at 2015-06-12T02:46:23+01:00 Build executable with '-threaded' (fixes haskell/haddock#399) - - - - - 7696b94f by Mateusz Kowalczyk at 2015-06-12T02:59:19+01:00 Update changelog for -threaded Closes haskell/haddock#400 - - - - - d3c118ec by Bartosz Nitka at 2015-06-12T03:00:58+01:00 Fix haddock: internal error: spliceURL UnhelpfulSpan (#207) Inferred type signatures don't have SrcSpans, so let's use the one from the declaration. I've tested this manually on the test-case from haskell/haddock#207, but I got stuck at trying to run the test-suite. - - - - - b67e843b by Mateusz Kowalczyk at 2015-06-12T03:01:50+01:00 Changelog for haskell/haddock#207 Fixes haskell/haddock#207, closes haskell/haddock#402 - - - - - 841d785e by jpmoresmau at 2015-06-12T16:03:16+01:00 Attach to instance location the name that has the same location file Fixes haskell/haddock#383 - - - - - 98791cae by Mateusz Kowalczyk at 2015-06-12T16:08:27+01:00 Update changelog Closes haskell/haddock#398 - - - - - 7c0b5a87 by Phil Ruffwind at 2015-06-12T13:07:25-04:00 Fix alignment of Source links in instance table in Firefox Due to a Firefox bug [1], a combination of 'whitespace: nowrap' on the parent element with 'float: right' on the inner element can cause the floated element to be displaced downwards for no apparent reason. To work around this, the left side is wrapped in its own <span> and set to 'float: left'. As a precautionary measure to prevent the parent element from collapsing entirely, we also add the classic "clearfix" hack. The latter is not strictly needed but it helps prevent bugs if the layout is altered again in the future. Fixes haskell/haddock#384. Remark: line 159 of src/Haddock/Backends/Xhtml/Layout.hs was indented to prevent confusion over the operator precedence of (<+>) vs (<<). [1]: https://bugzilla.mozilla.org/show_bug.cgi?id=488725 - - - - - cfe86e73 by Mateusz Kowalczyk at 2015-06-14T10:49:01+01:00 Update tests for the CSS changes - - - - - 2d4983c1 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding for Haskell source parser module. - - - - - 29548785 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement function for tagging parsed chunks with source spans. - - - - - 6a5e4074 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement simple string chunking based on HsColour library. - - - - - 6e52291f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create basic token classification method. - - - - - da971a27 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Adapt source span tagging to work with current whitespace handling. - - - - - 4feb5a22 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add record accessors to exports of hyperlinker parser module. - - - - - a8cc4e39 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Make parser module export all types and associated accessors. - - - - - fb8d468f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple HTML renderer for parsed source file. - - - - - 80747822 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for specifying the CSS file path in HTML source renderer. - - - - - 994dc1f5 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix identifier recognition in Haskell source parser. - - - - - b1bd0430 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix comment recognition in Haskell source parser. - - - - - 11db85ae by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for recognizing compiler pragmas in source parser. - - - - - 736c7bd3 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding of module for associating tokens with AST names. - - - - - 7e149bc2 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement utility method for extracting variable identifiers from AST. - - - - - 32eb640a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple mechanism for associating tokens with AST names. - - - - - d4eba5bc by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add dummy support for hyperlinking named tokens. - - - - - 2b76141f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matcher bug causing wrong items being hyperlinked. - - - - - 2d48002e by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Constrain elements exported by hyperlinker modules. - - - - - 9715eec6 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for type token recognition. - - - - - 8fa401cb by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for binding token recognition. - - - - - d062400b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement go-to-definition mechanism for local bindings. - - - - - f4dc229b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement module export- and import-list item hyperlinking. - - - - - c9a46d58 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matching to allow parenthesized operators hyperlinking. - - - - - 03aad95a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix weird hyperlinking of parenthesized operators. - - - - - b4694a7d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for type declaration anchors. - - - - - 7358d2d2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for top-level function declaration anchors. - - - - - dfc24b24 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix external anchors to contain HTML file extension. - - - - - a045926c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Refactor the way AST names are handled within detailed tokens. - - - - - c76049b4 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement hyperlinking of imported module names. - - - - - 2d2a1572 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix parsing of single line comments with broken up newlines. - - - - - 11afdcf2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix bug with improper newline handling. - - - - - 8137f104 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issues with escaped newlines in comments. - - - - - 34759b19 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for parsing C preprocessor macros. - - - - - 09f0f847 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for parser module of source hyperlinker. - - - - - 709a8389 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for AST module of source hyperlinker. - - - - - 4df5c227 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add command line option for generating hyperlinked source. - - - - - 7a755ea2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Extend module interface with rich source token stream field. - - - - - 494f4ab1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement source tokenization during interface creation process. - - - - - 5f21c953 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create hyperlinker module and plug it into the Haddock pipeline. - - - - - 0cc8a216 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for providing custom CSS files for hyperlinked source. - - - - - a32bbdc1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for fancy highlighting upon hovering over identifier. - - - - - d16d642a by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make source hyperlinker generate output in apropriate directory. - - - - - ae12953d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create module with hyperlinker utility functions. - - - - - 6d4952c5 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make external hyperlinks point to locations specified by source URLs. - - - - - 8417555d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Rewrite source generation to fixed links and directory structure. - - - - - ce9cec01 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add basic support for cross-package hyperlink generation. - - - - - 7eaf025c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Disable generating hyperlinks for module references. - - - - - a50bf92e by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make Haddock generate source for all interfaces (also hidden ones). - - - - - f5ae2838 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Prevent source parser from throwing exception when lexing fails. - - - - - db9ffbe0 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement workaround for Chrome highlighting issues. - - - - - 0b6b453b by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate correct anchors for data constructors. - - - - - c86d38bc by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate anchors for record field declarations. - - - - - 063abf7f by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issue with hyperlink highlight styling in Chrome browser. - - - - - 880fc611 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking constructor names in patters. - - - - - c9e89b95 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record patterns. - - - - - 17a11996 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record expressions. - - - - - 0eef932d by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Make hyperlinker respect pretty-printer flag and add documentation. - - - - - f87c1776 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Unexpose hyperlinker modules in Cabal configuration. - - - - - 4c9e2b06 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Setup HSpec framework for Haddock API package. - - - - - 4b20cb30 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add basic tests related to comment parsing. - - - - - 6842e919 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add tests related to parsing basic language constructs. - - - - - 87bffb35 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add simple tests for do-notation parsing. - - - - - e7af1841 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add very simple QuickCheck properties for source parser spec. - - - - - c84efcf1 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Create simple test runner for hyperlinker tests. - - - - - 76b90447 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for basic identifier hyperlinking. - - - - - 0fbf4df6 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for operator hyperlinking. - - - - - 731aa039 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for constructor hyperlinking. - - - - - 995a78a2 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for record expressions and patterns hyperlinking. - - - - - 3566875a by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for literal syntax highlighting. - - - - - 68469a35 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add hyperlinker test runner to .cabal and .gitignore files. - - - - - aa946c93 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Adapt hyperlinker test runner to have the same interface as HTML one. - - - - - ce34da16 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Fix hyperlinker test runner file paths and add pretty-printing option. - - - - - 0d7dd65e by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add reference files for hyperlinker test cases. - - - - - efa4a1e0 by Łukasz Hanuszczak at 2015-07-01T00:47:32+02:00 Make hyperlinker test runner strip local links from generated source. - - - - - 3e96e584 by Łukasz Hanuszczak at 2015-07-01T01:14:59+02:00 Create simple script for accepting hyperlinker test case references. - - - - - 526fe610 by Łukasz Hanuszczak at 2015-07-01T01:16:41+02:00 Re-accept hyperlinker test cases with local references stripped out. - - - - - 892e2cb3 by Łukasz Hanuszczak at 2015-07-01T01:22:09+02:00 Fix bug with diffing wrong files in hyperlinker test runner. - - - - - 9ff46039 by Łukasz Hanuszczak at 2015-07-01T18:04:46+02:00 Remove unused dependencies in Haddock API spec configuration. - - - - - 47969c07 by Łukasz Hanuszczak at 2015-07-01T18:32:19+02:00 Add support for hyperlinking synonyms in patterns. - - - - - a73449e0 by Łukasz Hanuszczak at 2015-07-01T18:33:44+02:00 Create test case for hyperlinking @-patterns. - - - - - c2077ed8 by Łukasz Hanuszczak at 2015-07-01T19:06:04+02:00 Add support for hyperlinking universally quantified type variables. - - - - - 68017342 by Łukasz Hanuszczak at 2015-07-01T19:28:32+02:00 Create hyperlinker test case with quantified type variables. - - - - - 51c01a78 by Łukasz Hanuszczak at 2015-07-01T19:34:22+02:00 Add scoped type variables test for polymorphism test case. - - - - - 13181ae2 by Łukasz Hanuszczak at 2015-07-01T19:56:27+02:00 Add record wildcards test for records hyperlinking test case. - - - - - 991b81dd by Łukasz Hanuszczak at 2015-07-01T21:01:42+02:00 Document some functions in XHTML utlity module. - - - - - 98c8dfe5 by Łukasz Hanuszczak at 2015-07-01T22:25:21+02:00 Make hyperlinker render qualified names as one entity. - - - - - 75e13b9b by Łukasz Hanuszczak at 2015-07-01T22:27:38+02:00 Add qualified name test for identifiers hyperlinking test case. - - - - - de1e143f by Łukasz Hanuszczak at 2015-07-02T12:32:59+02:00 Fix crash happening when hyperlinking type family declarations. - - - - - 7a8fb175 by Łukasz Hanuszczak at 2015-07-02T12:47:03+02:00 Add support for anchoring data family constructor declarations. - - - - - 3b404e49 by Łukasz Hanuszczak at 2015-07-02T13:31:05+02:00 Improve support for hyperlinking type families. - - - - - 59eb7143 by Łukasz Hanuszczak at 2015-07-02T13:33:34+02:00 Add hyperlinker test case for checking type and type family declarations. - - - - - d1cda0c0 by Łukasz Hanuszczak at 2015-07-02T13:41:38+02:00 Fix issue with operators being recognized as preprocessor directives. - - - - - da206c9d by Łukasz Hanuszczak at 2015-07-02T17:18:12+02:00 Fix broken tests for parsing and hyperlinking hash operators. - - - - - 53750d1b by Łukasz Hanuszczak at 2015-07-02T18:53:28+02:00 Add support for anchoring signatures in type class declarations. - - - - - 1fa5bb10 by Łukasz Hanuszczak at 2015-07-02T19:04:47+02:00 Make hyperlinker generate anchors only to top-level value bindings. - - - - - a542305c by Łukasz Hanuszczak at 2015-07-02T19:05:58+02:00 Create hyperlinker test case for type classes. - - - - - b0dd4581 by Łukasz Hanuszczak at 2015-07-04T16:28:26+02:00 Update docs with information about source hyperlinking. - - - - - 9795302a by Łukasz Hanuszczak at 2015-07-04T16:52:15+02:00 Update docs on using `--read-interface` option. - - - - - 9acdc002 by Łukasz Hanuszczak at 2015-07-04T17:15:26+02:00 Remove potentially dangerous record access in hyperlinker AST module. - - - - - fb3ab7be by Łukasz Hanuszczak at 2015-07-04T17:40:10+02:00 Make Haddock generate warnings about potential misuse of hyperlinker. - - - - - a324c504 by Łukasz Hanuszczak at 2015-07-04T17:43:22+02:00 Fix incorrect specification of source style option in doc file. - - - - - 3f01a8e4 by Łukasz Hanuszczak at 2015-07-05T17:06:36+02:00 Refactor source path mapping to use modules as indices. - - - - - ac70f5b1 by Łukasz Hanuszczak at 2015-07-05T17:47:34+02:00 Fix bug where not all module interfaces were added to source mapping. - - - - - f5e57da9 by Łukasz Hanuszczak at 2015-07-06T16:39:57+02:00 Extract main hyperlinker types to separate module. - - - - - 43974905 by Łukasz Hanuszczak at 2015-07-06T16:52:13+02:00 Move source paths types to hyperlinker types module. - - - - - 3e236055 by Łukasz Hanuszczak at 2015-07-06T17:06:19+02:00 Add support for hyperlinking modules in import lists. - - - - - 58233d9f by Łukasz Hanuszczak at 2015-07-06T17:26:49+02:00 Add short documentation for hyperlinker source map type. - - - - - 14da016d by Łukasz Hanuszczak at 2015-07-06T18:07:20+02:00 Fix bug with module name being hyperlinked to `Prelude`. - - - - - 8f79db52 by Łukasz Hanuszczak at 2015-07-06T18:23:47+02:00 Fix problem with spec build in Haddock API configuration. - - - - - e7cc056c by Adam Sandberg Eriksson at 2015-07-07T23:22:21+01:00 StrictData: print correct strictness marks - - - - - e8253ca8 by Mateusz Kowalczyk at 2015-07-07T23:58:28+01:00 Update changelog - - - - - 0aba676b by Mateusz Kowalczyk at 2015-07-07T23:58:33+01:00 Relax upper bound on GHC a bit - - - - - 7a595381 by Mateusz Kowalczyk at 2015-07-07T23:58:52+01:00 Delete trailing whitespace - - - - - 50976d5e by Adam Sandberg Eriksson at 2015-07-08T15:03:04+02:00 StrictData: changes in HsBang type - - - - - 83b045fa by Mateusz Kowalczyk at 2015-07-11T14:35:18+01:00 Fix expansion icon for user-collapsible sections Closes haskell/haddock#412 - - - - - b2a3b0d1 by Mateusz Kowalczyk at 2015-07-22T22:03:21+01:00 Make some version changes after 2.16.1 release - - - - - a8294423 by Ben Gamari at 2015-07-27T13:16:07+02:00 Merge pull request haskell/haddock#422 from adamse/adamse-D1033 Merge for GHC D1033 - - - - - c0173f17 by randen at 2015-07-30T14:49:08-07:00 Break the response file by line termination rather than spaces, since spaces may be within the parameters. This simple approach avoids having the need for any quoting and/or escaping (although a newline char will not be possible in a parameter and has no escape mechanism to allow it). - - - - - 47c0ca14 by Alan Zimmerman at 2015-07-31T10:41:52+02:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - 45a9d770 by Mateusz Kowalczyk at 2015-07-31T09:47:43+01:00 Update changelog - - - - - 347a20a3 by Phil Ruffwind at 2015-08-02T23:15:26+01:00 Avoid JavaScript error during page load in non-frame mode In non-frame mode, parent.window.synopsis refers to the synopsis div rather than the nonexistent frame. Unfortunately, the script wrongly assumes that if it exists it must be a frame, leading to an error where it tries to access the nonexistent attribute 'replace' of an undefined value (synopsis.location). Closes haskell/haddock#406 - - - - - 54ebd519 by Phil Ruffwind at 2015-08-02T23:27:10+01:00 Link to the definitions to themselves Currently, the definitions already have an anchor tag that allows URLs with fragment identifiers to locate them, but it is rather inconvenient to obtain such a URL (so-called "permalink") as it would require finding the a link to the corresponding item in the Synopsis or elsewhere. This commit adds hyperlinks to the definitions themselves, allowing users to obtain links to them easily. To preserve the original aesthetics of the definitions, we alter the color of the link so as to be identical to what it was, except it now has a hover effect indicating that it is clickable. Additionally, the anchor now uses the 'id' attribute instead of the (obsolete) 'name' attribute. Closes haskell/haddock#407 - - - - - 02cc8bb7 by Phil Ruffwind at 2015-08-02T23:28:02+01:00 Fix typo in Haddock.Backends.Xhtml.Layout: divSynposis -> divSynopsis Closes haskell/haddock#408 - - - - - 2eb0a458 by Phil Ruffwind at 2015-08-02T23:30:07+01:00 Fix record field alignment when name is too long Change <dl> to <ul> and use display:table rather than floats to layout the record fields. This avoids bug haskell/haddock#301 that occurs whenever the field name gets too long. Slight aesthetic change: the entire cell of the field's source code is now shaded gray rather than just the area where text exists. Fixes haskell/haddock#301. Closes haskell/haddock#421 - - - - - 7abb3402 by Łukasz Hanuszczak at 2015-08-02T23:32:14+01:00 Add some utility definitions for generating line anchors. - - - - - e0b1d79b by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Make hyperlinked source renderer generate line anchors. - - - - - 24dd4c9f by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Re-accept test cases after adding line anchors for each of them. - - - - - 0372cfcb by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Override source line flags when source hyperlinker is enabled. - - - - - a81bcd07 by Mateusz Kowalczyk at 2015-08-02T23:58:25+01:00 Update tests to follow HTML changes - - - - - d2d7426f by Łukasz Hanuszczak at 2015-08-06T20:54:59+02:00 Fix quote syntax for promoted types. - - - - - 668cf029 by Łukasz Hanuszczak at 2015-08-06T21:12:00+02:00 Apply promoted type quoting to type-level consing. - - - - - 89f8e7c6 by Łukasz Hanuszczak at 2015-08-06T21:17:10+02:00 Extend advanced types test case with other examples. - - - - - 86494bca by Łukasz Hanuszczak at 2015-08-06T21:22:06+02:00 Rename advanced types test case and accept new output. - - - - - dbb7c7c0 by Adam Sandberg Eriksson at 2015-08-09T23:01:05+02:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 2a7704fa by Ben Gamari at 2015-08-10T13:18:05+02:00 Merge pull request haskell/haddock#433 from adamse/split-hsbang HsBang is split into HsSrcBang and HsImplBang - - - - - 891954bc by Thomas Miedema at 2015-08-15T14:51:18+02:00 Follow changes in GHC build system - - - - - b55d32ab by Mateusz Kowalczyk at 2015-08-21T18:06:09+01:00 Make Travis use 7.10.2 - - - - - 97348b51 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Move SYB utilities to standalone module. - - - - - 748ec081 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement `everywhere` transformation in SYB module. - - - - - 011cc543 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement generic transformation constructor. - - - - - b9510db2 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Create simple utility module for type specialization. - - - - - 43229fa6 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Make type of type specialization function more general. - - - - - fd844e90 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Add basic HTML test case for checking instance specialization. - - - - - 6ea0ad04 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Make HTML class instance printer take optional signature argument. - - - - - 65aa41b6 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Refactor instance head type to record instead of a meaningless tuple. - - - - - 3fc3bede by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add expandable method section for each class instance declaration. - - - - - 99ceb107 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Move dummy post-family instances for `DocName` to `Types` module. - - - - - e98f4708 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create convenience functions for type specialization module. - - - - - b947552f by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Hook type specialization logic with HTML pretty-printer. - - - - - dcaa8030 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create stub functions for sugaring specialized types. - - - - - fa84bc65 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement list syntax sugaring logic for specialized types. - - - - - e8b05b07 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement tuple syntax sugaring logic for specialized types. - - - - - 68a2e5bc by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Get rid of code duplication in type specialization module. - - - - - 4721c336 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create scaffolding of a framework for renaming specialized types. - - - - - 271b488d by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in missing cases in specialized type renaming function. - - - - - bfa5f2a4 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Remove code duplication in specialized type renamer. - - - - - ea6bd0e8 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Change state of the type renaming monad. - - - - - 77c5496e by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement simple mechanism for generating new type names. - - - - - 91bfb48b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in stub behaviour with actual environment renaming. - - - - - d244517b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix logic behind binder type renaming. - - - - - f3c5e360 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add SYB-like utility function for performing stateful queries. - - - - - eb3f9154 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create function for retrieving free variables from given type. - - - - - a94561d3 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix compilation error caused by incorrect type signature. - - - - - 8bb707cf by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Move `SetName` class definition to types module. - - - - - 5800b13b by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Hook type renamer with instance method HTML pretty-printer. - - - - - 6a480164 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some test cases for type renamer. - - - - - 839842f7 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized signatures refer to original signature declaration. - - - - - 4880f7c9 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized methods be nicely formatted again. - - - - - ab5a6a2e by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Attach source locations to the specialized class methods. - - - - - 43f8a559 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Extend instances test case to also test multi-name type signatures. - - - - - 59bc751c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix tab-based indentation in instances test case. - - - - - c2126815 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Improve placement of instance methods expander button. - - - - - 0a32e287 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add new data type declaration to instance specialization test case. - - - - - 5281af1f by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make type renamer first try single-letter names as alternatives. - - - - - 7d509475 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix type renamer bug with incorrect names being generated. - - - - - 0f35bf7c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some documentation and refactor type specialization module. - - - - - da1d0803 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix another bug where type renamer was generating incorrect names. - - - - - cd39b5cb by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Refactor type renamer to rebinding and pure renaming phases. - - - - - 850251f4 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix unwitting compilation bug. - - - - - e5e9fc01 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Integrate instance specification type into class instance definition. - - - - - 825b0ea0 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer neccessary instance specification type. - - - - - cdba44eb by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix declaration converter to use more appropriate mode for methods. - - - - - bc45c309 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug with types not being specialized at all. - - - - - 5d8e5d89 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug where instance expander was opening wrong section. - - - - - 6001ee41 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix another type renamer bug where not all names were rebound. - - - - - 5f58ce2a by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix yet another renamer bug where some names were not unique. - - - - - 8265e521 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split instance subsection layout method to top-level declarations. - - - - - e5e66298 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Rearrange layout of instance methods in generated documentation. - - - - - a50b4eea by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer used layout method. - - - - - 2ff36ec2 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach section title to the instance methods block. - - - - - 7ac15300 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Add basic tests for associated types in instances test case. - - - - - db0ea2f9 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach associated types information to instance header. - - - - - 71cad4d5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details section contain associated types information. - - - - - deee2809 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Improve look of rendered associated families in instance details. - - - - - 839d13a5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Introduce alternative type for family declarations. - - - - - d397f03f by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details record use new type for family declarations. - - - - - 2b23fe97 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split printer of type family header to separate functions. - - - - - c3498cdc by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Implement HTML renderer for pseudo-family declarations. - - - - - c12bbb04 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Apply type specializer to associated type family declarations. - - - - - 2fd69ff2 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Create helper method for specializing type signatures. - - - - - 475826e7 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Refactor specializer module to be independent from XHTML backend. - - - - - f00b431c by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add some documentation for instance head specializer. - - - - - a9fef2dc by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix bug with missing space in documentation for associated types. - - - - - 50e29056 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with incorrect instance details sections being expanded. - - - - - e6dfdd03 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by adding instance details section. - - - - - 75565b2a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make section identifier of instance details more GHC-independent. - - - - - add0c23e by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Re-accept tests after applying deterministic section identifiers. - - - - - 878f2534 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make identifier generation also architecture-independent. - - - - - 48be69f8 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with instance expander hijacking type hyperlink click. - - - - - 47830c1f by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Get rid of dreadful hashing function for generating identifiers. - - - - - 956cd5af by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Move `InstOrigin` type declaration to more appropriate module. - - - - - bf672ed3 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by changes related to instance expander. - - - - - 8f2a949a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add examples with type operators to the instances test case. - - - - - 64600a84 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add basic support for sugaring infix type operators. - - - - - 747d71b8 by Łukasz Hanuszczak at 2015-08-21T18:22:34+01:00 Add support for sugaring built-in function syntax. - - - - - d4696ffb by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Remove default methods from Hoogle class output. - - - - - bf0e09d7 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add fixity declarations in Hoogle backend output. - - - - - 90e91a51 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix bug with incorrect fixities being generated in Hoogle backend. - - - - - 48f11d35 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve class type family declarations output in Hoogle backend. - - - - - 661e8e8f by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add missing default family equations in Hoogle output. - - - - - e2d64103 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve formatting of class details output in Hoogle backend. - - - - - 490fc377 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix weird-looking Hoogle output for familyless classes. - - - - - ea115b64 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create script file for new HTML test runner. - - - - - 609913d3 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Set default behaviour if no arguments given. - - - - - dc115f67 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for providing optional arguments for test runner. - - - - - d93ec867 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve output of test runner error messages. - - - - - 0be9fe12 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for executing Haddock process in test runner. - - - - - 4e4d00d9 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add GHC path to test runner configuration. - - - - - d67a2086 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make GHC path a test runner command-line argument. - - - - - c810079a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Extend test runner configuration with Haddock arguments. - - - - - fee18845 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor test runner and create stub functions. - - - - - ff7c161f by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make test runner actually run Haddock executable. - - - - - 391f73e6 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with test runner not producing any output files. - - - - - 81a74e2d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Setup skeleton of framework for running tests. - - - - - f8a79ec4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with modules not being found in global search mode. - - - - - 7e700b4d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make Haddock standard output redirection be more configurable. - - - - - 53b4c17a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Incorporate old, ugly functions for comparing output files. - - - - - 8277c8aa by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor architecture of test runner output checking functions. - - - - - 587bb414 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement actual diffing mechanism. - - - - - 9ed2b5e4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve code style to match popular guidelines. - - - - - 14bffaf8 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make it possible to choose alternative diff tool. - - - - - 5cdfb005 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create stub methods for processing test output as XML documents. - - - - - 7ef8e12e by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement link-stripping logic as simple SYB transformation. - - - - - 8a1fcd4f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Incorporate link stripping to output diffing mechanism. - - - - - 37dba2bc by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement footer-stripping logic. - - - - - 9cd52120 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Add missing dependencies in Cabal configuration file. - - - - - e0f83c6e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix issue with output being printed in incorrect order. - - - - - 0a94fbb0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to run tests without generating diff. - - - - - 76a58c6f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor HTML test suite boilerplate to external package. - - - - - af41e6b0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utilities for storing directory configuration. - - - - - d8f0698f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move IO-dependent config of HTML test suite to test package. - - - - - 17369fa0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Enable all compiler warnings in Haddock test package configuration. - - - - - 9d03b47a by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move Haddock runner of HTML test suite to Haddock test package. - - - - - 4b3483c5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 03754194 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience wrappers to simplify in test entry points. - - - - - 27476ab7 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adjust module visibility and items they export. - - - - - c40002ba by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Remove no longer useful test option. - - - - - 55ab2541 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Change extension of test files used for diffing. - - - - - 136bf4e4 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor and simplify XHTML helper module of test package. - - - - - 69f7e3df by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix typo in link stripper of HTML test suite runner. - - - - - 0c3c1c6b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience script for running specific HTML tests. - - - - - 489e1b05 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement utility functions for conditional link stripping. - - - - - 0f985dc3 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt `hypsrc-test` module to work with new testing framework. - - - - - 927406f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement output accepting mechanism in test package. - - - - - 8545715e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utility function for recursive obtaining directory contents. - - - - - cb70381f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 019599b5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix path handling in test runner. - - - - - 399b985b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to specify ignored files for test output. - - - - - 41b3d93d by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt HTML test runner to use new ignoring functionality. - - - - - e2091c8b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix bug with not all test output files being checked. - - - - - b22134f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Specify ignored files for hyperlinker source test runner. - - - - - 3301dfa1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Copy test runner script for hyperlinked source case. - - - - - d39a6dfa by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner invoking Haddock in incorrect mode. - - - - - f32c8ff3 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix path handling in test module loader. - - - - - 10f94ee9 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make test runner ignore test packages with no modules. - - - - - 5dc4239c by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create test runner entry points for LaTeX test suite. - - - - - 58d1f7cf by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with unnecessary checking old test output. - - - - - c7ce76e1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Re-implement test acceptance functionality. - - - - - 13bbabe8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix warning about no longer needed definition. - - - - - 958a99b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Adapt Cabal configuration to execute LaTeX suite with new runner. - - - - - 550ff663 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Setup test suite for Hoogle backend. - - - - - 3aa969c4 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make Hoogle backend create output directory if needed. - - - - - eb085b02 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Add appropriate .gitignore entry and configure Hoogle test suite. - - - - - a50bf915 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner failing when run on multiple test packages. - - - - - bf5368b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create simple test cases for Hoogle backend. - - - - - 6121ba4b by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create helper function for conversion between XML and XHTML. - - - - - cb516061 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Refactor existing code to use XHTML printer instead of XML one. - - - - - e2de8c82 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Improve portability of test runner scripts. - - - - - 9563e774 by Łukasz Hanuszczak at 2015-08-22T23:43:16+02:00 Remove redundant import statement. - - - - - 55353df1 by Łukasz Hanuszczak at 2015-08-24T23:09:20+02:00 Fix bug with accepting to non-existing directory. - - - - - 00a334ca by Łukasz Hanuszczak at 2015-08-24T23:09:47+02:00 Accept output for Hoogle and LaTeX backends. - - - - - 29191d8b by Łukasz Hanuszczak at 2015-08-24T23:14:18+02:00 Get rid of obsolete testing utilities. - - - - - bbb25db3 by Łukasz Hanuszczak at 2015-08-24T23:18:50+02:00 Update sandbox setup guide to work with Haddock test package. - - - - - cfd45248 by Łukasz Hanuszczak at 2015-08-24T23:51:30+02:00 Make Travis aware of Haddock test package. - - - - - 74185b7a by Łukasz Hanuszczak at 2015-08-25T17:41:59+02:00 Fix test suite failure when used with Stack. - - - - - 18769697 by Łukasz Hanuszczak at 2015-08-25T18:02:09+02:00 Add sample Stack setup to the hacking guide. - - - - - 22715eeb by Łukasz Hanuszczak at 2015-08-25T18:04:47+02:00 Fix Markdown formatting of README file. - - - - - b49ec386 by Łukasz Hanuszczak at 2015-08-25T18:13:36+02:00 Setup Haddock executable path in Travis configuration. - - - - - 5d29eb03 by Eric Seidel at 2015-08-30T09:55:58-07:00 account for changes to ipClass - - - - - f111740a by Ben Gamari at 2015-09-02T13:20:37+02:00 Merge pull request haskell/haddock#443 from bgamari/ghc-head account for changes to ipClass - - - - - a2654bf6 by Jan Stolarek at 2015-09-03T01:32:57+02:00 Follow changes from haskell/haddock#6018 - - - - - 2678bafe by Richard Eisenberg at 2015-09-21T12:00:47-04:00 React to refactoring CoAxiom branch lists. - - - - - ebc56e24 by Edward Z. Yang at 2015-09-21T11:53:46-07:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4a8c4198 by Tamar Christina at 2015-09-27T13:59:08+02:00 Create Process: removed PhaseFailed - - - - - 7e99b790 by Oleg Grenrus at 2015-09-27T20:52:10+03:00 Generate docs for orphan instances - - - - - 32e932e2 by Oleg Grenrus at 2015-09-28T07:21:11+03:00 Have source links for orphan instances - - - - - c2eb9f4f by Oleg Grenrus at 2015-09-28T07:24:58+03:00 Print orphan instances header only if required - - - - - ff96f978 by Oleg Grenrus at 2015-09-28T07:40:54+03:00 Add orphan instances link to contents box - - - - - d72490a6 by Oleg Grenrus at 2015-09-28T16:37:44+03:00 Fix orphan instance collapsing - - - - - 25d3dfe5 by Ben Gamari at 2015-10-03T12:38:09+02:00 Merge pull request haskell/haddock#448 from Mistuke/fix-silent-death-of-runInteractive Remove PhaseFailed - - - - - 1e45e43b by Edward Z. Yang at 2015-10-11T13:10:10-07:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b1370ac1 by Adam Gundry at 2015-10-16T16:26:42+01:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 60bef421 by Simon Peyton Jones at 2015-10-26T12:52:36+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 4c1898ca by Simon Peyton Jones at 2015-10-27T14:24:56+00:00 Track change to PatSyn.patSynSig - - - - - 25108e85 by Simon Peyton Jones at 2015-10-27T17:34:18+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - 693643ac by Ben Gamari at 2015-10-28T14:33:06+01:00 Account for Typeable changes The treatment of type families changed. - - - - - cd7c2221 by Simon Peyton Jones at 2015-10-30T13:03:51+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - 712032cb by Herbert Valerio Riedel at 2015-10-31T11:01:45+01:00 Relax upper bound on `base` to allow base-4.9 - - - - - 0bfa0475 by Simon Peyton Jones at 2015-10-31T19:08:13+00:00 More adaption to wildcard-refactor - - - - - 0a3c0cb7 by Simon Peyton Jones at 2015-10-31T22:14:43+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - c4fd4ec9 by Alan Zimmerman at 2015-11-01T11:16:34+01:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 42cdd882 by Matthew Pickering at 2015-11-06T20:02:16+00:00 Change for IEThingWith - - - - - f368b7be by Ben Gamari at 2015-11-11T11:35:51+01:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - e32965b8 by Simon Peyton Jones at 2015-11-13T12:18:17+00:00 Merge with origin/head - - - - - ebcf795a by Edward Z. Yang at 2015-11-13T21:56:27-08:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4e23989f by Simon Peyton Jones at 2015-11-18T11:32:54+00:00 Wibbles to Haddock - - - - - 2289cd4a by Simon Peyton Jones at 2015-11-20T23:12:49+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor - - - - - 695975a6 by Alan Zimmerman at 2015-11-21T21:16:12+02:00 Update to match GHC wip/T11019 - - - - - bbba21e7 by Simon Peyton Jones at 2015-11-23T13:54:31+00:00 merge with origin/ghc-head - - - - - 3d664258 by Simon Peyton Jones at 2015-11-23T17:17:18+00:00 Wibble - - - - - e64cf586 by Herbert Valerio Riedel at 2015-12-05T00:29:55+01:00 Canonicalise Monad instances - - - - - a2de15a7 by Alan Zimmerman at 2015-12-05T17:33:52+02:00 Matching changes for haskell/haddock#11028 - - - - - cc29a3e4 by Alan Zimmerman at 2015-12-05T19:45:33+02:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 95dd15d1 by Richard Eisenberg at 2015-12-11T17:33:39-06:00 Update for type=kinds - - - - - cb5fd9ed by Herbert Valerio Riedel at 2015-12-14T15:07:30+00:00 Bump versions for ghc-7.11 - - - - - 4f286d96 by Simon Peyton Jones at 2015-12-14T15:10:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 13ea2733 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 098df8b8 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track changes in HsSyn for quasi-quotes - - - - - 716a64de by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track change in API of TyCon - - - - - 77a66bca by Adam Gundry at 2015-12-14T15:10:58+00:00 Track API changes to support empty closed type familes - - - - - f2808305 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track the new location of setRdrNameSpace - - - - - ba8b08a4 by Alan Zimmerman at 2015-12-14T15:10:59+00:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - a4ded87e by Thomas Winant at 2015-12-14T15:14:05+00:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 25c78107 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: print correct strictness marks - - - - - 6cbc41c4 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: changes in HsBang type - - - - - ad46821a by Alan Zimmerman at 2015-12-14T15:14:06+00:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - abc0ae5b by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 3308d06c by Thomas Miedema at 2015-12-14T15:14:07+00:00 Follow changes in GHC build system - - - - - 6c763deb by Eric Seidel at 2015-12-14T15:14:07+00:00 account for changes to ipClass - - - - - ae5b4eac by Jan Stolarek at 2015-12-14T15:17:00+00:00 Follow changes from haskell/haddock#6018 - - - - - ffbc40e0 by Richard Eisenberg at 2015-12-14T15:17:02+00:00 React to refactoring CoAxiom branch lists. - - - - - d1f531e9 by Edward Z. Yang at 2015-12-14T15:17:02+00:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 79f73754 by Tamar Christina at 2015-12-14T15:17:02+00:00 Create Process: removed PhaseFailed - - - - - 3d37bebb by Edward Z. Yang at 2015-12-14T15:20:46+00:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 5f8a9e44 by Adam Gundry at 2015-12-14T15:20:48+00:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 79dda70f by Simon Peyton Jones at 2015-12-14T15:26:02+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 959930fb by Simon Peyton Jones at 2015-12-14T15:37:50+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - e18a8df5 by Simon Peyton Jones at 2015-12-14T15:37:52+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - aa35ab52 by Simon Peyton Jones at 2015-12-14T15:40:18+00:00 More adaption to wildcard-refactor - - - - - 8ceef94b by Simon Peyton Jones at 2015-12-14T15:46:04+00:00 Track change to PatSyn.patSynSig - - - - - cd81e83d by Ben Gamari at 2015-12-14T15:46:06+00:00 Account for Typeable changes The treatment of type families changed. - - - - - 63c9117c by Herbert Valerio Riedel at 2015-12-14T15:46:34+00:00 Relax upper bound on `base` to allow base-4.9 - - - - - a484c613 by Alan Zimmerman at 2015-12-14T15:47:46+00:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 2c26fa51 by Matthew Pickering at 2015-12-14T15:47:47+00:00 Change for IEThingWith - - - - - 593baa0f by Ben Gamari at 2015-12-14T15:49:21+00:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - b6b5ca78 by Edward Z. Yang at 2015-12-14T15:49:54+00:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b5b0e072 by Alan Zimmerman at 2015-12-14T15:54:20+00:00 Update to match GHC wip/T11019 - - - - - 14ddeb68 by Simon Peyton Jones at 2015-12-14T15:54:22+00:00 Wibble - - - - - 10a90ad8 by Herbert Valerio Riedel at 2015-12-14T15:54:22+00:00 Canonicalise Monad instances - - - - - ed68ac50 by Alan Zimmerman at 2015-12-14T15:55:48+00:00 Matching changes for haskell/haddock#11028 - - - - - 3f7e5a2d by Alan Zimmerman at 2015-12-14T15:55:49+00:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 6543a73f by Richard Eisenberg at 2015-12-14T15:59:55+00:00 Update for type=kinds - - - - - 193a5c48 by Matthew Pickering at 2015-12-14T18:17:00+00:00 Changes to compile with 8.0 - - - - - add669ec by Matthew Pickering at 2015-12-14T18:47:12+00:00 Warnings - - - - - 223f3fb4 by Ben Gamari at 2015-12-15T23:45:05+01:00 Update for D1200 - - - - - d058388f by Ben Gamari at 2015-12-16T05:40:17-05:00 Types: Add Outputable[Bndr] DocName instances - - - - - 62ecd7fb by Ben Gamari at 2015-12-16T09:23:09-05:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ddbc187a by Ben Gamari at 2015-12-16T17:54:55+01:00 Update for D1200 - - - - - cec83b52 by Ben Gamari at 2015-12-16T17:54:55+01:00 Types: Add Outputable[Bndr] DocName instances - - - - - d12ecc98 by Ben Gamari at 2015-12-16T17:54:55+01:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ada1616f by Ben Gamari at 2015-12-16T17:54:58+01:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a4f0383d by Ben Gamari at 2015-12-16T23:32:38+01:00 Fix Hyperlinker GHC.con_names is now GHC.getConNames - - - - - a10e6849 by Ben Gamari at 2015-12-20T00:54:11+01:00 Merge remote-tracking branch 'mrhania/testing-framework-improvements' into ghc-head - - - - - f078b4fd by Ben Gamari at 2015-12-20T00:59:51+01:00 test: Compatibility with Cabal 1.23 - - - - - 88a511a9 by Ben Gamari at 2015-12-20T01:14:35+01:00 Merge remote-tracking branch 'phadej/orphans' into ghc-head - - - - - 4e250f36 by Ben Gamari at 2015-12-20T01:14:52+01:00 Add html-test for orphan instances output - - - - - 87fffbad by Alan Zimmerman at 2015-12-20T09:50:42+02:00 Update for GHC trac#11258 Adding locations to RdrName in FieldOcc and AmbiguousFieldOcc - - - - - 6b7e51c9 by idontgetoutmuch at 2015-12-20T21:01:47+00:00 Merge pull request haskell/haddock#1 from haskell/ghc-head Ghc head - - - - - 229c1fb5 by Dominic Steinitz at 2015-12-21T07:19:16+00:00 Handle inline math with mathjax. - - - - - 57902d66 by Dominic Steinitz at 2015-12-21T08:07:11+00:00 Fix the documentation for haddock itself. Change notation and add support for inline math. Allow newlines in display math. Add a command line option for the mathjax url (you might want to use a locally installed version). Rebase tests because of extra url and version change. Respond to (some of the) comments. Fix warnings in InterfaceFile.hs - - - - - 0e69f236 by Herbert Valerio Riedel at 2015-12-21T18:30:43+01:00 Fix-up left-over assumptions of GHC 7.12 into GHC 8.0 - - - - - c67f8444 by Simon Peyton Jones at 2015-12-22T16:26:56+00:00 Follow removal of NamedWildCard from HsType - - - - - da40327a by Ben Gamari at 2015-12-23T14:15:28+01:00 html-test/Operators: Clear up ambiguous types For reasons that aren't entirely clear a class with ambiguous types was accepted by GHC <8.0. I've added a functional dependency to clear up this ambiguity. - - - - - 541b7fa4 by Ben Gamari at 2015-12-23T14:18:51+01:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 0febc947 by Ben Gamari at 2015-12-24T00:30:20+01:00 hoogle-test/AssocTypes: Allow AmbiguousTypes GHC 8.0 complains otherwise - - - - - 25810841 by Ben Gamari at 2015-12-24T00:33:18+01:00 OrphanInstances: Accept test output - - - - - 841987f3 by Ben Gamari at 2015-12-25T11:03:11+01:00 Merge remote-tracking branch 'idontgetoutmuch/ghc-head' into ghc-head - - - - - 358391f0 by Ben Gamari at 2015-12-26T10:44:50+01:00 Add missing import - - - - - a8896885 by Ben Gamari at 2015-12-26T10:45:27+01:00 travis: Use Travis containers - - - - - 85e82134 by Herbert Valerio Riedel at 2015-12-30T17:25:39+01:00 tweak version bounds for GHC-8.1 - - - - - 672a5f75 by randen at 2016-01-01T23:45:25-08:00 The Haddock part for fully gcc-like response files " driver/Main.hs * Moved the response file handling into ResponseFile.hs, updating import section as appropriate. * driver/ResponseFile.hs * New file. In anticipation that maybe some day this could be provided by another library, and to make it possible to unit test, this functionality is pulled out of the Main.hs module, and expanded to support the style/format of response files which gcc uses. * The specification for the format of response files which gcc generates and consumes, seems to be best derived from the gcc code itself (libiberty/argv.c), so that is what has been done here. * This is intended to fix haskell/haddock#379 * driver-test/Main.hs * New file for testing code in the driver source tree * driver-test/ResponseFileSpec.hs * Tests, adapted/adopted from the same gcc code where the escaping/unescaping is from, in the hspec style of unit tests * haddock.cabal * Add the driver-test test-suite. Introduces a new library dependency (upon hspec) for the haddock driver target in the haddock.cabal file, but practically, this should not be a problem as the haddock-api tests already depend on hspec. - - - - - 498781df by Ben Gamari at 2016-01-06T13:41:04+01:00 Version bumps and changelog - - - - - 8451e46a by Ben Gamari at 2016-01-06T13:47:17+01:00 Merge remote-tracking branch 'randen/bug468' - - - - - fb2d9181 by Ben Gamari at 2016-01-06T08:14:42-05:00 Add ResponseFile to OtherModules - - - - - 2cb2d2e3 by Ben Gamari at 2016-01-06T14:35:00+01:00 Merge branch 'master' into ghc-head - - - - - 913477d4 by Eric Seidel at 2016-01-11T14:57:57-08:00 deal with un-wiring of IP class - - - - - c557a4b3 by Alan Zimmerman at 2016-01-15T11:14:35+02:00 Update to match wip/T11430 in GHC - - - - - 3e135093 by Alan Zimmerman at 2016-01-16T18:21:59+01:00 Update to match wip/T11430 in GHC - - - - - c48ef2f9 by Ben Gamari at 2016-01-18T09:50:06+01:00 Merge remote-tracking branch 'gridaphobe/ghc-head' into ghc-head - - - - - 9138a1b0 by Eric Seidel at 2016-01-18T12:50:15+01:00 deal with un-wiring of IP class (cherry picked from commit 17388b0f0029d969d79353be7737eb01c7b8dc5f) - - - - - b48c172e by Joachim Breitner at 2016-01-19T00:11:38+01:00 Make sure --mathjax affects all written HTML files This fixes haskell/haddock#475. - - - - - af61fe63 by Ryan Scott at 2016-02-07T23:25:57+01:00 Render */# instead of TYPE 'Lifted/TYPE 'Unlifted (fixes haskell/haddock#473) - - - - - b6458693 by Ben Gamari at 2016-02-07T23:29:27+01:00 Merge pull request haskell/haddock#477 from haskell/issue-475 Make sure --mathjax affects all written HTML files - - - - - adcc0071 by Ben Gamari at 2016-02-07T23:34:52+01:00 Merge branch 'master' into ghc-head - - - - - d0404e61 by Ben Gamari at 2016-02-08T12:46:49+01:00 doc: Switch to Sphinx - - - - - acb153b3 by Ben Gamari at 2016-02-08T12:46:56+01:00 Document --use-unicode flag - - - - - c20bdf1d by Ben Gamari at 2016-02-08T13:41:24+01:00 Fix GHC and haddock-library dependency bounds - - - - - 8d946801 by Ben Gamari at 2016-02-08T14:54:56+01:00 testsuite: Rework handling of output sanitization Previously un-cleaned artifacts were kept as reference output, making it difficult to tell what has changed and causing spurious changes in the version control history. Here we rework this, cleaning the output during acceptance. To accomplish this it was necessary to move to strict I/O to ensure the reference handle was closed before accept attempts to open the reference file. - - - - - c465705d by Ben Gamari at 2016-02-08T15:36:05+01:00 test: Compare on dump For reasons I don't understand the Xml representations differ despite their textual representations being identical. - - - - - 1ec0227a by Ben Gamari at 2016-02-08T15:36:05+01:00 html-test: Accept test output - - - - - eefbd63a by Ben Gamari at 2016-02-08T15:36:08+01:00 hypsrc-test: Accept test output And fix impredicative Polymorphism testcase. - - - - - d1df4372 by Ben Gamari at 2016-02-08T15:40:44+01:00 Merge branch 'fix-up-testsuite' - - - - - 206a3859 by Phil Ruffwind at 2016-02-08T17:51:21+01:00 Move the permalinks to "#" on the right side Since pull request haskell/haddock#407, the identifiers have been permalinked to themselves, but this makes it difficult to copy the identifier by double-clicking. To work around this usability problem, the permalinks are now placed on the far right adjacent to "Source", indicated by "#". Also, 'namedAnchor' now uses 'id' instead of 'name' (which is obsolete). - - - - - 6c89fa03 by Phil Ruffwind at 2016-02-08T17:54:44+01:00 Update tests for previous commit - - - - - effaa832 by Ben Gamari at 2016-02-08T17:56:17+01:00 Merge branch 'anchors-redux' - - - - - 9a2bec90 by Ben Gamari at 2016-02-08T17:58:40+01:00 Use -fprint-unicode-syntax when --use-unicode is enabled This allows GHC to render `*` as its Unicode representation, among other things. - - - - - 28ecac5b by Ben Gamari at 2016-02-11T18:53:03+01:00 Merge pull request haskell/haddock#480 from bgamari/sphinx Move documentation to ReStructuredText - - - - - 222e5920 by Ryan Scott at 2016-02-11T15:42:42-05:00 Collapse type/data family instances by default - - - - - a80ac03b by Ryan Scott at 2016-02-11T20:17:09-05:00 Ensure expanded family instances render correctly - - - - - 7f985231 by Ben Gamari at 2016-02-12T10:04:22+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - d4eda086 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Various cleanups - - - - - 79bee48d by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show kind signatures for type family variables Addresses GHC haskell/haddock#11588. - - - - - b2981d98 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show 'where ...' after closed type family Seems like we should ideally show the actual equations as well but that seems like it would be a fair amount of work - - - - - cfc0e621 by Ben Gamari at 2016-02-18T22:48:12+01:00 Merge pull request haskell/haddock#483 from bgamari/T11588 Fix GHC haskell/haddock#11588 This fixes GHC haskell/haddock#11588: * Show where ... after closed type families * Show kind signatures on type family type variables - - - - - 256e8a0d by Ben Gamari at 2016-02-18T23:15:39+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 32402036 by Richard Eisenberg at 2016-02-24T13:21:44-05:00 Follow-on changes to support RuntimeRep - - - - - 2b1c572d by Matthew Pickering at 2016-03-04T21:04:02+00:00 Remove unused functions - - - - - eb906f50 by Richard Eisenberg at 2016-03-13T21:17:20+01:00 Follow-on changes to support RuntimeRep (cherry picked from commit ab954263a793d8ced734459d6194a5d89214b66c) - - - - - 8c34ef34 by Richard Eisenberg at 2016-03-14T23:47:23-04:00 Changes due to fix for GHC#11648. - - - - - 0e022014 by Richard Eisenberg at 2016-03-15T14:06:45+01:00 Changes due to fix for GHC#11648. (cherry picked from commit bb994de1ab0c76d1aaf1e39c54158db2526d31f1) - - - - - ed3f78ab by Rik Steenkamp at 2016-04-02T22:20:36+01:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 - - - - - d3210042 by Rik Steenkamp at 2016-04-04T15:43:32+02:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 (cherry picked from commit 3ddcbd6b8e6884bd95028381176eb33bee6896fb) - - - - - 236eec90 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 692ee7e0 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. - - - - - 79619f57 by Ben Gamari at 2016-04-10T23:46:22+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. (cherry picked from commit c6d6a18d85e5e2d9bb5904e6919e8a8d7e31c4c5) - - - - - 3358ccb4 by Ben Gamari at 2016-04-10T23:47:27+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 264949b1 by Ben Gamari at 2016-04-16T17:50:23+02:00 Merge pull request haskell/haddock#482 from RyanGlScott/ghc-head Collapse type/data family instances by default - - - - - 478c483a by Ben Gamari at 2016-04-16T17:51:09+02:00 Merge pull request haskell/haddock#489 from mpickering/unused-functions Remove some unused functions - - - - - c94e55f0 by Ryan Scott at 2016-04-16T17:57:54+02:00 Collapse type/data family instances by default (cherry picked from commit 2da130a8db8f995c119b544fad807533236cf088) - - - - - 31e633d3 by Ryan Scott at 2016-04-16T17:58:06+02:00 Ensure expanded family instances render correctly (cherry picked from commit 1338b5d7c32939de6bbc31af0049477e4f847103) - - - - - 03e4d197 by Matthew Pickering at 2016-04-16T17:58:21+02:00 Remove unused functions (cherry picked from commit b89d1c2456bdb2d4208d94ded56155f7088a37d0) - - - - - ed4116f6 by Ben Gamari at 2016-04-20T10:46:57+02:00 ghc: Install files for needed --hyperlinked-source - - - - - 0be999c4 by Ben Gamari at 2016-04-20T11:37:54+02:00 ghc: Install files for needed --hyperlinked-source (cherry picked from commit 5c82c9fc2d21ddaae4a2470f1c375426968f19c6) - - - - - 4d17544c by Simon Peyton Jones at 2016-04-20T12:42:28+01:00 Track change to HsGroup This relates to a big GHC patch for Trac haskell/haddock#11348 - - - - - 1700a50d by Ben Gamari at 2016-05-01T13:19:27+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. - - - - - 0b7c8125 by Ben Gamari at 2016-05-01T13:21:43+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. (cherry picked from commit 609018dd09c4ffe27f9248b2d8b50f6196cd42b9) - - - - - af115ce0 by Ryan Scott at 2016-05-04T22:15:50-04:00 Render Haddocks for derived instances Currently, one can document top-level instance declarations, but derived instances (both those in `deriving` clauses and standalone `deriving` instances) do not enjoy the same privilege. This makes the necessary changes to the Haddock API to enable rendering Haddock comments for derived instances. This is part of a fix for Trac haskell/haddock#11768. - - - - - 76fa1edc by Ben Gamari at 2016-05-10T18:13:25+02:00 haddock-test: A bit of refactoring for debuggability - - - - - 7d4c4b20 by Ben Gamari at 2016-05-10T18:13:25+02:00 Create: Mark a comment as TODO - - - - - 2a6d0c90 by Ben Gamari at 2016-05-10T18:13:25+02:00 html-test: Update reference output - - - - - bd60913d by Ben Gamari at 2016-05-10T18:13:25+02:00 hypsrc-test: Fix reference file path in cabal file It appears the haddock insists on prefixing --hyperlinked-sourcer output with directory which the source appeared in. - - - - - c1548057 by Ben Gamari at 2016-05-10T18:22:12+02:00 doc: Update extra-source-files in Cabal file - - - - - 41d5bae3 by Ben Gamari at 2016-05-10T18:29:21+02:00 Bump versions - - - - - ca75b779 by Ben Gamari at 2016-05-11T16:03:44+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 4e3cfd62 by Ben Gamari at 2016-05-11T16:06:45+02:00 Merge remote-tracking branch 'RyanGlScott/ghc-head' into ghc-head - - - - - a2379970 by Ben Gamari at 2016-05-11T23:15:11+02:00 doc: Add clean targets - - - - - f275212e by Ben Gamari at 2016-05-11T23:15:14+02:00 doc: Add html as an all-target for ghc Otherwise the html documentation won't be installed for binary-dist. - - - - - 388fc0af by Ben Gamari at 2016-05-12T09:49:12+02:00 Update CHANGES - - - - - bad81ad5 by Ben Gamari at 2016-05-12T09:49:38+02:00 Version bump - - - - - c01688a7 by Ben Gamari at 2016-05-12T10:04:58+02:00 Revert "Version bump" This bump was a bit premature. This reverts commit 7b238d9c5be9b07aa2d10df323b5c7b8d1634dc8. - - - - - 7ed05724 by Ben Gamari at 2016-05-12T10:05:33+02:00 doc: Fix GHC clean rule Apparently GHC's build system doesn't permit wildcards in clean paths. - - - - - 5d9611f4 by Ben Gamari at 2016-05-12T17:43:50+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 653566b2 by Ben Gamari at 2016-05-14T09:57:31+02:00 Version bump to 2.17.2 - - - - - b355c439 by Ben Gamari at 2016-05-14T09:57:51+02:00 doc: Use `$(MAKE)` instead of `make` This is necessary to ensure we use gmake. - - - - - 8a18537d by Ben Gamari at 2016-05-14T10:15:45+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - b3290ef1 by Sebastian Meric de Bellefon at 2016-05-14T11:29:47-04:00 Fix haskell/haddock#303. Hide footer when printing The "Produced by Haddock" footer was overlapping the page's body when printing. This patch hides the footer with a css media rule. - - - - - b4a76f89 by Sebastian Meric de Bellefon at 2016-05-15T02:12:46-04:00 Fix haskell/haddock#280. Parsing of module header The initial newlines were counted as indentation spaces, thus disturbing the parsing of next lines - - - - - ba797c9e by Ben Gamari at 2016-05-16T14:53:46+02:00 doc: Vendorize alabaster Sphinx theme Alabaster is now the default sphinx theme and is a significant improvement over the previous default that it's worthproviding it when unavailable (e.g. Sphinx <1.3). - - - - - c9283e44 by Ben Gamari at 2016-05-16T14:55:17+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 1c9ea198 by Sebastian Méric de Bellefon at 2016-05-16T12:30:40-04:00 Merge pull request haskell/haddock#502 from Helkafen/master Fix haskell/haddock#303. Hide footer when printing - - - - - 33631016 by Ben Gamari at 2016-05-16T19:56:11+02:00 Revert "doc: Vendorize alabaster Sphinx theme" This ended up causes far too many issues to be worthwhile. We'll just have to live with inconsistent haddock documentation. This reverts commit cec21957001143794e71bcd9420283df18e7de40. - - - - - 93317d26 by Ben Gamari at 2016-05-16T19:56:11+02:00 cabal: Fix README path - - - - - c8695b22 by Ben Gamari at 2016-05-16T19:58:51+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 0b50eaaa by Ben Gamari at 2016-05-16T21:02:08+02:00 doc: Use whichever theme sphinx deems appropriate - - - - - 857c1c9c by Ben Gamari at 2016-05-16T21:07:08+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 15fc5637 by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Remove redundant imports - - - - - 132ddc6a by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Better debug output For tracking down haskell/haddock#505 - - - - - 2252a149 by Ben Gamari at 2016-05-22T12:43:59+02:00 Don't consider default class ops when looking for decls When we are looking for an operation within a class we don't care about `default`-type declarations. This was the cause of haskell/haddock#505. - - - - - 4886b2ec by Oleg Grenrus at 2016-05-24T16:19:48+03:00 UnfelpfulSpan line number omitted Kind of resolves https://github.com/haskell/haddock/issues/508 - - - - - a4befd36 by Oleg Grenrus at 2016-05-24T16:53:35+03:00 Change Hyperlinked lexer to know about DataKinds ticks - - - - - f45cb52e by David Feuer at 2016-05-24T18:48:53-04:00 Make parser state a newtype Previously, it was `data` wrapping a `Maybe`, which seems a bit silly. Obviously, this can be changed back if anyone wants to add more fields some day. - - - - - 05013dd7 by Sebastian Meric de Bellefon at 2016-05-24T22:03:55-04:00 remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) Frames are a bit broken, ignored by Hackage, and considered obsolete in general. This patch disables frames generation. The mini_*.html files are still used in the synopsis. - - - - - b8163a88 by Ben Gamari at 2016-05-25T14:44:15+02:00 Merge pull request haskell/haddock#507 from bgamari/T505 Fix haskell/haddock#505 - - - - - ea1b30c6 by Sebastian Meric de Bellefon at 2016-05-25T14:17:00-04:00 Update CHANGES - - - - - eddfc258 by Sebastian Méric de Bellefon at 2016-05-25T15:17:40-04:00 Merge pull request haskell/haddock#514 from Helkafen/frames remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) - - - - - 0e506818 by Alex Biehl at 2016-05-26T12:43:09+02:00 Remove misplaced haddock comment - - - - - a07d28c0 by Ben Gamari at 2016-05-27T11:34:59+02:00 Merge pull request haskell/haddock#515 from alexbiehl/master Remove misplaced haddock comment - - - - - 9001d267 by Ben Gamari at 2016-05-27T11:35:46+02:00 Merge pull request haskell/haddock#513 from treeowl/newtype-since Make parser state a newtype - - - - - 74e1a018 by Sebastian Méric de Bellefon at 2016-05-28T17:28:15-04:00 Merge pull request haskell/haddock#504 from Helkafen/issue-280 Fix haskell/haddock#280. Parsing of module header - - - - - 37557f4f by Alan Zimmerman at 2016-05-29T23:36:50+02:00 Matching changes for haskell/haddock#12105 - - - - - 7d09e5d6 by Sebastian Meric de Bellefon at 2016-06-03T18:07:48-04:00 Version bumps (2.17.3, 1.4.2) - - - - - 85b4bc15 by Sebastian Méric de Bellefon at 2016-06-06T18:35:13-04:00 Merge pull request haskell/haddock#521 from Helkafen/master Version bumps (2.17.3, 1.4.2) - - - - - e95f0dee by Sebastian Meric de Bellefon at 2016-06-06T19:11:35-04:00 publish haddock-test library - - - - - 4de40586 by Sebastian Méric de Bellefon at 2016-06-06T20:26:30-04:00 Merge pull request haskell/haddock#512 from phadej/oleg-fixes Fixes for haskell/haddock#508 and haskell/haddock#510 - - - - - ddfd0789 by Dominic Steinitz at 2016-06-09T09:27:28+01:00 Documentation for LaTeX markup. - - - - - 697a503a by Dominic Steinitz at 2016-06-09T09:33:59+01:00 Fix spelling mistake. - - - - - 246f6fff by Dominic Steinitz at 2016-06-09T09:37:15+01:00 Camel case MathJax. - - - - - 4684bd23 by Dominic Steinitz at 2016-06-09T09:44:53+01:00 Fix math typo and add link. - - - - - f20c037c by Simon Peyton Jones at 2016-06-13T18:26:03+01:00 Follow changes to LHsSigWcType - - - - - 0c58996d by Simon Peyton Jones at 2016-06-15T12:56:01+01:00 Follow GHC re-adding FunTy - - - - - 401b5ca7 by Sebastian Méric de Bellefon at 2016-06-15T12:16:47-04:00 Merge pull request haskell/haddock#525 from idontgetoutmuch/master Documentation for LaTeX markup. - - - - - 92d263b7 by Sebastian Méric de Bellefon at 2016-06-15T12:17:29-04:00 Merge pull request haskell/haddock#522 from Helkafen/master publish haddock-test library - - - - - 0953a2ca by Sebastian Meric de Bellefon at 2016-06-16T00:46:46-04:00 Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 65453e14 by Ben Gamari at 2016-06-16T11:16:32+02:00 ocean: Ensure that synopsis fully covers other content Previously MathJax content was being rendered on top of the synopsis due to ambiguous z-ordering. Here we explicitly give the synopsis block a higher z-index to ensure it is rendered on top. Fixes haskell/haddock#531. - - - - - 68e411a1 by Sebastian Méric de Bellefon at 2016-06-16T23:34:39-04:00 Merge pull request haskell/haddock#534 from bgamari/T531 ocean: Ensure that synopsis fully covers other content - - - - - fad6491b by Sebastian Méric de Bellefon at 2016-06-18T23:57:20-04:00 Merge pull request haskell/haddock#533 from Helkafen/master Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 6108e21b by Sebastian Meric de Bellefon at 2016-06-22T23:08:28-04:00 do not create empty src directory Fix haskell/haddock#536. - - - - - 1ef23823 by Sebastian Méric de Bellefon at 2016-06-24T00:04:48-04:00 Merge pull request haskell/haddock#537 from Helkafen/master do not create empty src directory - - - - - 966baa96 by Omari Norman at 2016-06-29T21:59:34-04:00 Add $ as a special character If this character is not escaped, documentation built with Haddock 2.17.2 will fail. This was not an issue with 2.16 series, which causes builds to fail and there is nothing in the docs or error message giving a clue about why builds that used to succeed now don't. - - - - - 324adb60 by Ben Gamari at 2016-07-01T12:18:51+02:00 GhcUtils: Changes for multi-pattern signatures - - - - - d7571675 by Ömer Sinan Ağacan at 2016-07-21T13:30:47+02:00 Add support for unboxed sums - - - - - 29d0907b by Simon Marlow at 2016-07-22T13:55:48+01:00 Disable NFData instances for GHC types when GHC >= 8.2 - - - - - 702d95f3 by Simon Marlow at 2016-08-02T15:57:30+02:00 Disable NFData instances for GHC types when GHC >= 8.0.2 (cherry picked from commit a3309e797c42dae9bccdeb17ce52fcababbaff8a) - - - - - f4fa79c3 by Ben Gamari at 2016-08-07T13:51:18+02:00 ghc.mk: Don't attempt to install html/frames.html The frames business has been removed. - - - - - 9cd63daf by Ben Gamari at 2016-08-07T13:51:40+02:00 Haddock.Types: More precise version guard This allows haddock to be built with GHC 8.0.2 pre-releases. - - - - - f3d7e03f by Mateusz Kowalczyk at 2016-08-29T20:47:45+01:00 Merge pull request haskell/haddock#538 from massysett/master Add $ as a special character - - - - - 16dbf7fd by Bartosz Nitka at 2016-09-20T19:44:04+01:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 - - - - - 7c31c1ff by Bartosz Nitka at 2016-09-27T17:32:22-04:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 (cherry picked from commit 073d899a8f94ddec698f617a38d3420160a7fd0b) - - - - - 33a90dce by Ryan Scott at 2016-09-30T20:53:41-04:00 Haddock changes for T10598 See https://ghc.haskell.org/trac/ghc/ticket/10598 - - - - - 1f32f7cb by Ben Gamari at 2016-10-13T20:01:26-04:00 Update for refactoring of NameCache - - - - - 1678ff2e by Ben Gamari at 2016-11-15T17:42:48-05:00 Bump upper bound on base - - - - - 9262a7c5 by Alan Zimmerman at 2016-12-07T21:14:28+02:00 Match changes in GHC wip/T3384 branch - - - - - ac0eaf1a by Ben Gamari at 2016-12-09T09:48:41-05:00 haddock-api: Don't use stdcall calling convention on 64-bit Windows See GHC haskell/haddock#12890. - - - - - 04afe4f7 by Alan Zimmerman at 2016-12-12T20:07:21+02:00 Matching changes for GHC wip/T12942 - - - - - e1d1701d by Ben Gamari at 2016-12-13T16:50:41-05:00 Bump base upper bound - - - - - 3d3eacd1 by Alan Zimmerman at 2017-01-10T16:59:38+02:00 HsIParamTy now has a Located name - - - - - 7dbceefd by Kyrill Briantsev at 2017-01-12T13:23:50+03:00 Prevent GHC API from doing optimization passes. - - - - - d48d1e33 by Richard Eisenberg at 2017-01-19T08:41:41-05:00 Upstream changes re levity polymorphism - - - - - 40c25ed6 by Alan Zimmerman at 2017-01-26T15:16:18+02:00 Changes to match haskell/haddock#13163 in GHC - - - - - 504f586d by Ben Gamari at 2017-02-02T17:19:37-05:00 Kill remaining static flags - - - - - 49147ea0 by Justus Adam at 2017-03-02T15:33:34+01:00 Adding MDoc to exports of Documentation.Haddock - - - - - 1cfba9b4 by Justus Adam at 2017-03-09T11:41:44+01:00 Also exposing toInstalledIface - - - - - 53f0c0dd by Ben Gamari at 2017-03-09T13:10:08-05:00 Bump for GHC 8.3 - - - - - c7902d2e by Ben Gamari at 2017-03-09T23:46:02-05:00 Bump for GHC 8.2 - - - - - 4f3a74f8 by Ben Gamari at 2017-03-10T10:21:55-05:00 Merge branch 'ghc-head' - - - - - e273b72f by Richard Eisenberg at 2017-03-14T13:34:04-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - 6ec3d436 by Richard Eisenberg at 2017-03-14T15:15:52-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - eee3cda1 by Ben Gamari at 2017-03-15T15:19:59-04:00 Adapt to EnumSet - - - - - 017cf58e by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 736d6773 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 475f84a0 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 13240b53 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - cd16d529 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 3bea97ae by Edward Z. Yang at 2017-03-15T22:50:46-07:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b2b051ce by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 0f082795 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 20ef63c9 by Edward Z. Yang at 2017-03-22T13:48:12-07:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 45692dcb by Edward Z. Yang at 2017-03-22T14:11:25-07:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4eae8caf by Ben Gamari at 2017-03-23T09:25:33-04:00 Merge commit '240bc38b94ed2d0af27333b23392d03eeb615e82' into HEAD - - - - - 0bbe03f5 by Ben Gamari at 2017-03-23T09:27:28-04:00 haddock-api: Bump bound on GHC - - - - - 65f3ac9d by Alex Biehl at 2017-03-23T17:36:11+01:00 Merge pull request haskell/haddock#581 from JustusAdam/master Adding more exports to Documentation.Haddock - - - - - 37d49a47 by Alex Biehl at 2017-03-23T17:39:14+01:00 Merge pull request haskell/haddock#568 from awson/ghc-head Prevent GHC API from doing optimization passes. - - - - - 1ed047e4 by Brian Huffman at 2017-03-23T17:45:58+01:00 Print any user-supplied kind signatures on type parameters. This applies to type parameters on data, newtype, type, and class declarations, and also to forall-bound type vars in type signatures. - - - - - 1b78ca5c by Brian Huffman at 2017-03-23T17:45:58+01:00 Update test suite to expect kind annotations on type parameters. - - - - - a856b162 by Alex Biehl at 2017-03-23T17:49:32+01:00 Include travis build indication badge - - - - - 8e2e2c56 by Ben Gamari at 2017-03-23T17:20:08-04:00 haddock-api: Bump bound on GHC - - - - - 4d2d9995 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 26d6c150b31bc4580ab17cfd07b6e7f9afe10737) - - - - - a650e20f by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 930cfbe58e2e87f5a4d431d89a3c204934e6e858) - - - - - caa282c2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 2067a2d0afa9cef381d26fb7140b67c62f433fc0) - - - - - 49684884 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 0671abfe7e8ceae2269467a30b77ed9d9656e2cc) - - - - - 4dcfeb1a by Edward Z. Yang at 2017-03-23T17:20:08-04:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 3d77b373dd5807d5d956719dd7c849a11534fa6a) - - - - - 74dd19d2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 94610e9b446324f4231fa6ad4c6ac51e4eba8c0e) - - - - - a9b19a23 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 6cc832dfb1de6088a4abcaae62b25a7e944d55c3) - - - - - d3631064 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit bf3c4d72a0fda38561376eac7eda216158783267) - - - - - ef2148fc by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 07b88c5d4e79b87a319fbb08f8ea01dbb41063c1) - - - - - 2f29518b by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 4eb765ca4205c79539d60b7afa9b7e261a4a49fe) - - - - - 37de047d by Phil Ruffwind at 2017-04-03T11:57:14+02:00 Update MathJax URL MathJax is shutting down their CDN: https://www.mathjax.org/cdn-shutting-down/ They recommend migrating to cdnjs. - - - - - e9d24ba8 by David C. Turner at 2017-04-03T14:58:01+02:00 Add highlight for :target to ocean.css - - - - - 4819a202 by Alex Biehl at 2017-04-11T19:36:48+02:00 Allow base-4.10 for haddock-test - - - - - 44cec69c by Alex Biehl at 2017-04-11T19:39:22+02:00 cabal.project for haddock-api, haddock-library and haddock-test - - - - - 935d0f6a by Alex Biehl at 2017-04-11T19:46:29+02:00 Move dist scripts to scripts/ - - - - - 128e150c by Alex Biehl at 2017-04-11T20:34:46+02:00 Add haddock to cabal.project - - - - - cc8e08ea by Alex Biehl at 2017-04-11T20:35:08+02:00 Read files for hyperlinker eagerly This also exposes Documentation.Haddock.Utf8 - - - - - 152dda78 by Alex Biehl at 2017-04-11T20:37:06+02:00 Explicit import list ofr Control.DeepSeq in Haddock.Interface.Create - - - - - 501b33c4 by Kyrill Briantsev at 2017-04-11T21:01:42+02:00 Prevent GHC API from doing optimization passes. - - - - - c9f3f5ff by Alexander Biehl at 2017-04-12T16:36:53+02:00 Add @alexbiehl as maintaner - - - - - 76f214cc by Alex Biehl at 2017-04-13T07:27:18+02:00 Disable doctest with ghc-8.3 Currently doctest doesn't support ghc-head - - - - - 46b4f5fc by Edward Z. Yang at 2017-04-22T20:38:26-07:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f0555235 by Alex Biehl at 2017-04-25T10:08:48+02:00 Travis: Use ghc-8.2.1 on master - - - - - 966ea348 by Alex Biehl at 2017-04-25T10:32:01+02:00 Travis: Verbose cabal output cf. https://travis-ci.org/haskell/haddock/jobs/225512194#L377 - - - - - 36972bcd by Alex Biehl at 2017-04-25T10:40:43+02:00 Use travis_retry for cabal invocations - - - - - b3a09d2c by Alex Biehl at 2017-04-25T17:02:20+02:00 Use new MathJax URL in html-test 18ed871afb82560d5433b2f53e31b4db9353a74e switched to a new MathJax URL but didn't update the tests. - - - - - ae331e5f by Alexander Biehl at 2017-04-25T17:02:20+02:00 Expand signatures for class declarations - - - - - e573c65a by Alexander Biehl at 2017-04-25T17:02:20+02:00 Hoogle: Correctly print classes with associated data types - - - - - 3fc6be9b by Edward Z. Yang at 2017-04-25T17:02:20+02:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit a0c4790e15a2d3fab8d830eee8fcd639fe6d39c9) - - - - - 6725c060 by Herbert Valerio Riedel at 2017-04-25T17:02:20+02:00 `html-test --accept` deltas to reference samples - - - - - 7d444d61 by Alex Biehl at 2017-04-26T07:13:50+02:00 Remove anything related to obsolete frames mode - - - - - b888972c by Alex Biehl at 2017-04-26T07:49:10+02:00 Cherry-picked remaining commits from haddock-2.17.4-release (#603) * Release haddock/haddock-api 2.17.4 and haddock-library 1.4.3 * Set version bounds for haddock-library NB: This allows GHC 8.2.1's base * Set version bounds for haddock & haddock-api The version bounds support GHC 8.2 * Merge (temporary) v2.17.3 branch into v2.17 This allows us to delete the v2.17.3 branch * Fixup changelog * Pin down haddock-api to a single version as otherwise `haddock`'s package version has no proper meaning * fix source-repo spec for haddock-api - - - - - 4161099b by Alex Biehl at 2017-04-26T11:11:20+02:00 Update changelog to reflect news in HEAD - - - - - eed72cb8 by Alex Biehl at 2017-04-26T11:11:20+02:00 Markdownify changelog - - - - - 5815cea1 by Alex Biehl at 2017-04-26T11:32:33+02:00 Bump to 2.18.0 (#605) - - - - - a551d558 by Alex Biehl at 2017-04-29T22:00:25+02:00 Update attoparsec-0.12.1.1 to attoparsec-0.13.1.0 - - - - - ea164a8d by Sergey Vinokurov at 2017-04-29T22:42:36+02:00 Improve error message - - - - - 2e10122f by Alex Biehl at 2017-04-30T10:07:46+02:00 Correctly remember collapsed sections (#608) Now the "collapsed" cookie stores which sections have changed state instead of which are collapsed. - - - - - f9b24d99 by Alex Biehl at 2017-05-01T17:40:36+02:00 Lazily decode docMap and argMap (#610) These are only used in case of a doc reexport so most of the time decoding these is wasted work. - - - - - 2372af62 by Alex Biehl at 2017-05-01T21:59:23+02:00 Fix Binary instance for InstalledInterface (#611) (#610) introduced lazy decoding for docs from InstalledInterface but forgot to remove the original calls to get and put_ - - - - - 6c633c13 by Nathan Collins at 2017-05-11T11:47:55+02:00 Improve documenation of Haddock markup (#614) * Improve documentation of Haddock markup. - document that Haddock supports inferring types top-level functions with without type signatures, but also explain why using this feature is discouraged. Looks like this feature has been around since version 2.0.0.0 in 2008! - rework the "Module description" section: - move the general discussion of field formatting to the section intro and add examples illustrating the prose for multiline fields. - mention that newlines are preserved in some multiline fields, but not in others (I also noticed that commas in the `Copyright` field are not preserved; I'll look into this bug later). - add a subsection for the module description fields documentation, and put the field keywords in code formatting (double back ticks) instead of double quotes, to be consistent with the typesetting of keywords in other parts of the documentation. - mention that "Named chunks" are not supported in the long-form "Module description" documentation. - fix formatting of keywords in the "Module attributes" section. Perhaps these errors were left over from an automatic translation to ReST from some other format as part of the transition to using Sphinx for Haddock documentation? Also, add a missing reference here; it just said "See ?"! - update footnote about special treatment for re-exporting partially imported modules not being implemented. In my tests it's not implemented at all -- I tried re-exporting both `import B hiding (f)` and `import B (a, b)` style partial imports, and in both cases got the same result as with full imports `import B`: I only get a module reference. * Rework the `Controlling the documentation structure` section. My main goal was to better explain how to use Haddock without an export list, since that's my most common use case, but I hope I improved the section overall: - remove the incomplete `Omitting the export list` section and fold it into the other sections. In particular, summarize the differences between using and not using an export list -- i.e. control over what and in what order is documented -- in the section lead. - add "realistic" examples that use the structure markup, both with and without an export list. I wanted a realistic example here to capture how it can be useful to explain the relationship between a group of functions in a section, in addition to documenting their individual APIs. - make it clear that you can associate documentation chunks with documentation sections when you aren't using an export list, and that doing it in the most obvious way -- i.e. with `-- |`, as you can in the export list -- doesn't work without an export list. It took me a while to figure this out the first time, since the docs didn't explain it at all before. - add a "no export list" example to the section header section. - add more cross references. * Add examples of gotchas for markup in `@...@`. I'm not sure this will help anyone, since I think most people first learn about `@...@` by reading other people's Haddocks, but I've documented the mistakes which I've made and then gotten confused by. * Use consistent Capitalization of Titles. Some titles were in usual title caps, and others only had the first word capitalized. I chose making them all use title caps because that seems to make the cross references look better. - - - - - d4734f45 by Ben Gamari at 2017-05-12T20:36:08+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 93883f37 by Alex Biehl at 2017-05-12T21:02:33+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 5b8f179c by Alex Biehl at 2017-05-13T12:48:10+02:00 Consequently use inClass and notInClass in haddock-library (#617) These allow attoparsec to do some clever lookup optimization - - - - - 77984b82 by Doug Wilson at 2017-05-27T17:37:38+02:00 Don't enable compilation for template haskell (#624) This is no longer necessary after ghc commit 53c78be0aab76a3107c4dacbb1d177afacdd37fa - - - - - 5a3de2b4 by Doug Wilson at 2017-05-27T19:54:53+02:00 Improve Syb code (#621) Specialize.hs and Ast.hs are modified to have their Syb code not recurse into Name or Id in HsSyn types. Specialize.hs is refactored to have fewer calls to Syb functions. Syb.hs has some foldl calls replaced with foldl' calls. There is still a lot of performance on the floor of Ast.hs. The RenamedSource is traversed many times, and lookupBySpan is very inefficient. everywhereBut and lookupBySpan dominate the runtime whenever --hyperlinked-source is passed. - - - - - 3d35a949 by Alex Biehl at 2017-05-30T19:01:37+02:00 Clear fixme comment (#625) - - - - - 2a44bd0c by Alex Biehl at 2017-05-30T19:02:12+02:00 Make haddock-library and haddock-api warning free (#626) - - - - - bd1a0e42 by Alex Biehl at 2017-06-01T10:40:33+02:00 Include `driver-test/*.hs` sdist (#630) This lead to haskell/haddock#629. - - - - - 184a3ab6 by Doug Wilson at 2017-06-03T12:02:08+02:00 Disable pattern match warnings (#628) This disables the pattern match checker which can be very expensive in some cases. The disabled warnings include: * Opt_WarnIncompletePatterns * Opt_WarnIncompleteUniPatterns * Opt_WarnIncompletePatternsRecUpd * Opt_WarnOverlappingPatterns - - - - - 0cf68004 by Alex Biehl at 2017-06-03T20:37:28+02:00 Allow user defined signatures for pattern synonyms (#631) - - - - - 7f51a58a by Alex Biehl at 2017-06-04T11:56:38+02:00 Use NameSet for isExported check (#632) - - - - - d8f044a9 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Match new AST as per GHC wip/new-tree-one-param See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow - - - - - da1254e3 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Rename extension index tags - - - - - 538c7514 by Christiaan Baaij at 2017-06-09T08:26:43+02:00 Haddock support for bundled pattern synonyms (#627) * Haddock support for bundled pattern synonyms * Add fixities to bundled pattern synonyms * Add bundled pattern synonyms to the synopsis * Store bundled pattern fixities in expItemFixities * Add test for bundled pattern synonyms * Stop threading fixities * Include bundled pattern synonyms for re-exported data types Sadly, fixity information isn't found for re-exported data types * Support for pattern synonyms * Modify tests after haskell/haddock#631 * Test some reexport variations * Also lookup bundled pattern synonyms from `InstalledInterface`s * Check isExported for bundled pattern synonyms * Pattern synonym is exported check * Always look for pattern synonyms in the current module Another overlooked cornercase * Account for types named twice in export lists Also introduce a fast function for nubbing on a `Name` and use it throughout the code base. * correct fixities for reexported pattern synonyms * Fuse concatMap and map * Remove obsolete import * Add pattern synonyms to visible exports * Fix test * Remove corner case - - - - - a050bffd by Doug Wilson at 2017-06-21T09:27:33+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#636) There is some performance improvement. GHC compiler: | version | bytes allocated | cpu_seconds --------------------------------- | before | 56057108648 | 41.0 | after | 51592019560 | 35.1 base: | version | bytes allocated | cpu_seconds --------------------------------- | before | 25174011784 | 14.6 | after | 23712637272 | 13.1 Cabal: | version | bytes allocated | cpu_seconds --------------------------------- | before | 18754966920 | 12.6 | after | 18198208864 | 11.6 - - - - - 5d06b871 by Doug Wilson at 2017-06-22T20:23:29+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#639) * Use new function getNameToInstancesIndex instead of tcRnGetInfo There is some significant performance improvement in the ghc testsuite. haddock.base: -23.3% haddock.Cabal: -16.7% haddock.compiler: -19.8% * Remove unused imports - - - - - b11bb73a by Alex Biehl at 2017-06-23T14:44:41+02:00 Lookup fixities for reexports without subordinates (#642) So we agree that reexported declarations which do not have subordinates (for example top-level functions) shouldn't have gotten fixities reexported according to the current logic. I wondered why for example Prelude.($) which is obviously reexported from GHC.Base has fixities attached (c.f. http://hackage.haskell.org/package/base-4.9.1.0/docs/Prelude.html#v:-36-). The reason is this: In mkMaps we lookup all the subordinates of top-level declarations, of course top-level functions don't have subordinates so for them the resulting list is empty. In haskell/haddock#644 I established the invariant that there won't be any empty lists in the subordinate map. Without the patch from haskell/haddock#642 top-level functions now started to fail reexporting their fixities. - - - - - d2a6dad6 by Alex Biehl at 2017-06-23T18:30:45+02:00 Don't include names with empty subordinates in maps (#644) These are unecessary anyway and just blow up interface size - - - - - 69c2aac4 by Alex Biehl at 2017-06-29T19:54:49+02:00 Make per-argument docs for class methods work again (#648) * Make per-argument docs for class methods work again * Test case - - - - - c9448d54 by Bartosz Nitka at 2017-07-02T12:12:01+02:00 Fix haddock: internal error: links: UnhelpfulSpan (#561) * Fix haddock: internal error: links: UnhelpfulSpan This fixes haskell/haddock#554 for me. I believe this is another fall out of `wildcard-refactor`, like haskell/haddock#549. * Comment to clarify why we take the methods name location - - - - - d4f29eb7 by Alex Biehl at 2017-07-03T19:43:04+02:00 Document record fields when DuplicateRecordFields is enabled (#649) - - - - - 9d6e3423 by Yuji Yamamoto at 2017-07-03T22:37:58+02:00 Fix test failures on Windows (#564) * Ignore .stack-work * Fix for windows: use nul instead of /dev/null * Fix for windows: canonicalize line separator * Also normalize osx line endings - - - - - 7d81e8b3 by Yuji Yamamoto at 2017-07-04T16:13:12+02:00 Avoid errors on non UTF-8 Windows (#566) * Avoid errors on non UTF-8 Windows Problem ==== haddock exits with errors like below: `(1)` ``` haddock: internal error: <stderr>: hPutChar: invalid argument (invalid character) ``` `(2)` ``` haddock: internal error: Language\Haskell\HsColour\Anchors.hs: hGetContents: invalid argument (invalid byte sequence) ``` `(1)` is caused by printing [the "bullet" character](http://www.fileformat.info/info/unicode/char/2022/index.htm) onto stderr. For example, this warning contains it: ``` Language\Haskell\HsColour\ANSI.hs:62:10: warning: [-Wmissing-methods] • No explicit implementation for ‘toEnum’ • In the instance declaration for ‘Enum Highlight’ ``` `(2)` is caused when the input file of `readFile` contains some Unicode characters. In the case above, '⇒' is the cause. Environment ---- OS: Windows 10 haddock: 2.17.3 GHC: 8.0.1 Solution ==== Add `hSetEncoding handle utf8` to avoid the errors. Note ==== - I found the detailed causes by these changes for debugging: - https://github.com/haskell/haddock/commit/8f29edb6b02691c1cf4c479f6c6f3f922b35a55b - https://github.com/haskell/haddock/commit/1dd23bf2065a1e1f2c14d0f4abd847c906b4ecb4 - These errors happen even after executing `chcp 65001` on the console. According to the debug code, `hGetEncoding stderr` returns `CP932` regardless of the console encoding. * Avoid 'internal error: <stderr>: hPutChar: invalid argument (invalid character)' non UTF-8 Windows Better solution for 59411754a6db41d17820733c076e6a72bcdbd82b's (1) - - - - - eded67d2 by Alex Biehl at 2017-07-07T19:17:15+02:00 Remove redudant import warning (#651) - - - - - 05114757 by Alex Biehl at 2017-07-08T00:33:12+02:00 Avoid missing home module warning (#652) * Avoid missing home module warning * Update haddock-library.cabal - - - - - e9cfc902 by Bryn Edwards at 2017-07-17T07:51:20+02:00 Fix haskell/haddock#249 (#655) - - - - - eb02792b by Herbert Valerio Riedel at 2017-07-20T09:09:15+02:00 Fix compilation of lib:haddock-library w/ GHC < 8 - - - - - 9200bfbc by Alex Biehl at 2017-07-20T09:20:38+02:00 Prepare 2.18.1 release (#657) - - - - - 46ddd22c by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Tweak haddock-api.cabal for pending release - - - - - 85e33d29 by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Avoid trivial use of LambdaCase otherwise we can't test w/ e.g. GHC 7.4.2 - - - - - 3afb4bfe by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Refactor .cabal to use sub-lib for vendored lib A practical benefit is that we can control the build-depends and also avoid some recompilation between library and test-suite. - - - - - e56a552e by Herbert Valerio Riedel at 2017-07-20T10:17:48+02:00 haddock-api: add changelog pointing to haddock's changelog This addresses https://github.com/haskell/haddock/issues/638#issuecomment-309283297 - - - - - 2222ff0d by Herbert Valerio Riedel at 2017-07-20T10:19:56+02:00 Drop obsolete/misleading `stability: experimental` This .cabal property has long been considered obsolete - - - - - 9b882905 by Alex Biehl at 2017-07-20T11:25:54+02:00 Beef up haddock description (#658) * Beef up haddock description * Handle empty lines - - - - - bb60e95c by Herbert Valerio Riedel at 2017-07-20T12:08:53+02:00 Import @aisamanra's Haddock cheatsheet from https://github.com/aisamanra/haddock-cheatsheet - - - - - 0761e456 by Herbert Valerio Riedel at 2017-07-20T12:12:55+02:00 Add cheatsheet to haddock.cabal - - - - - 2ece0f0f by Herbert Valerio Riedel at 2017-07-20T12:18:38+02:00 Mention new-build in README - - - - - 947b7865 by Herbert Valerio Riedel at 2017-07-20T12:32:16+02:00 Update README Also improves markup and removes/fixes redundant/obsolete parts [skip ci] - - - - - 785e09ad by Alex Biehl at 2017-07-27T07:28:57+02:00 Bump haddock to 2.18.2, haddock-library to 1.4.5 - - - - - e3ff1ca3 by Alex Biehl at 2017-07-31T20:15:32+02:00 Move `DocMarkup` from haddock-api to haddock-library (#659) * Move `DocMarkup` from haddock-api to haddock-library * Move more markup related functions * Markup module * CHANGELOG - - - - - cda7c20c by Alex Biehl at 2017-07-31T20:35:49+02:00 Fixup haddock - - - - - 583b6812 by Alex Biehl at 2017-07-31T21:20:45+02:00 Changelog for haddock-library - - - - - bac6a0eb by Alex Biehl at 2017-07-31T21:50:24+02:00 Prepare haddock-library-1.4.5 release - - - - - 58ce6877 by Moritz Drexl at 2017-08-05T16:44:40+02:00 Fix renaming after instance signature specializing (#660) * rework rename * Add regression test for Bug 613 * update tests * update changelog - - - - - b8137ec8 by Tim Baumann at 2017-08-06T11:33:38+02:00 Fix: Generate pattern signatures for constructors exported as patterns (#663) * Fix pretty-printing of pattern signatures Pattern synonyms can have up to two contexts, both having a different semantic meaning: The first holds the constraints required to perform the matching, the second contains the constraints provided by a successful pattern match. When the first context is empty but the second is not it is necessary to render the first, empty context. * Generate pattern synonym signatures for ctors exported as patterns This fixes haskell/haddock#653. * Simplify extractPatternSyn It is not necessary to generate the simplest type signature since it will be simplified when pretty-printed. * Add changelog entries for PR haskell/haddock#663 * Fix extractPatternSyn error message - - - - - d037086b by Alex Biehl at 2017-08-06T12:43:25+02:00 Bump haddock-library - - - - - 99d7e792 by Alex Biehl at 2017-08-06T12:44:07+02:00 Bump haddock-library in haddock-api - - - - - 94802a5b by Alex Biehl at 2017-08-06T13:18:02+02:00 Provide --show-interface option to dump interfaces (#645) * WIP: Provide --show-interface option to dump interfaces Like ghcs own --show-iface this flag dumps a binary interface file to stdout in a human (and machine) readable fashion. Currently it uses json as output format. * Fill all the jsonNull stubs * Rework Bifunctor instance of DocH, update changelog and documentation * replace changelog, bring DocMarkupH doc back * Update CHANGES.md * Update CHANGES.md * Move Control.Arrow up It would result in unused import if the Bifunctor instance is not generated. - - - - - c662e476 by Ryan Scott at 2017-08-14T21:00:21-04:00 Adapt to haskell/haddock#14060 - - - - - b891eb73 by Alex Biehl at 2017-08-16T08:24:48+02:00 Bifoldable and Bitraversable for DocH and MetaDoc - - - - - 021bb56c by Alex Biehl at 2017-08-16T09:06:40+02:00 Refactoring: Make doc renaming monadic This allows us to later throw warnings if can't find an identifier - - - - - 39fbf022 by Alex Biehl at 2017-08-19T20:35:27+02:00 Hyperlinker: Avoid linear lookup in enrichToken (#669) * Make Span strict in Position * Hyperlinker: Use a proper map to enrich tokens - - - - - e13baedd by Alex Biehl at 2017-08-21T20:05:42+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 27dd6e87 by Alex Biehl at 2017-08-21T22:06:35+02:00 Drop Avails from export list - - - - - 86b247e2 by Alex Biehl at 2017-08-22T08:44:22+02:00 Bump ghc version for haddock-api tests - - - - - d4607ca0 by Alex Biehl at 2017-08-22T08:45:17+02:00 Revert "Drop Avails from export list" This reverts commit a850ba86d88a4fb9c0bd175453a2580e544e3def. - - - - - c9c54c30 by Alex Biehl at 2017-08-22T09:26:01+02:00 IntefaceFile version - - - - - a85b7c02 by Ben Gamari at 2017-08-22T09:29:52-04:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 34e976f5 by Ben Gamari at 2017-08-22T17:40:06+02:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 577abf06 by Ryan Scott at 2017-08-23T14:47:29-04:00 Update for haskell/haddock#14131 - - - - - da68fc55 by Florian Eggenhofer at 2017-08-27T18:21:56+02:00 Generate an index for package content search (#662) Generate an index for package content search - - - - - 39e62302 by Alex Biehl at 2017-08-27T18:50:16+02:00 Content search for haddock html doc - - - - - 91fd6fb2 by Alex Biehl at 2017-08-28T18:39:58+02:00 Fix tests for content search - - - - - b4a3798a by Alex Biehl at 2017-08-28T18:44:08+02:00 Add search button to #page-menu - - - - - 25a7ca65 by Alex Biehl at 2017-08-28T18:47:43+02:00 Load javascript below the fold - - - - - 8d323c1a by Alex Biehl at 2017-08-28T18:49:22+02:00 Accept tests - - - - - c5dac557 by Alex Biehl at 2017-08-28T19:14:55+02:00 Content search css - - - - - 89a5af57 by Paolo Veronelli at 2017-08-29T07:42:13+02:00 Removed `nowrap` for interface method sigs (#674) with nowrap the interfaces method sigs would expand at libitum - - - - - a505f6f7 by Alex Biehl at 2017-08-29T08:05:33+02:00 Include subordinates in content index - - - - - 4bb698c4 by Alexander Biehl at 2017-08-29T11:40:19+02:00 QuickNav: Make docbase configurable - - - - - c783bf44 by Alexander Biehl at 2017-08-29T11:48:36+02:00 QuickNav: Also use baseUrl for doc-index.json request - - - - - 47017510 by Alex Biehl at 2017-08-29T17:56:47+02:00 Fix test fallout (again) - - - - - 924fc318 by Alex Biehl at 2017-08-30T09:24:56+02:00 Write meta.json when generating html output (#676) - - - - - 717dea52 by Alex Biehl at 2017-09-01T09:20:34+02:00 Use relative URL when no docBaseUrl given - - - - - e5d85f3b by Alex Biehl at 2017-09-01T09:35:19+02:00 Add missing js files to data-files (#677) - - - - - 95b9231a by Alex Biehl at 2017-09-01T11:01:36+02:00 Rename "Search" tab to "Quick Jump" - - - - - da0ead0b by Alex Biehl at 2017-09-01T13:03:49+02:00 Make trigger link configurable (#678) QuickNav: Configurable show/hide trigger - - - - - de7da594 by Ben Gamari at 2017-09-05T06:49:55-04:00 Account for "Remember the AvailInfo for each IE" As of GHC commit f609374a55bdcf3b79f3a299104767aae2ffbf21 GHC retains the AvailInfo associated with each IE. @alexbiehl has a patch making proper use of this change, but this is just to keep things building. - - - - - b05cd3b3 by Ben Gamari at 2017-09-14T07:55:07-04:00 Bump upper bound on base - - - - - 79db899e by Herbert Valerio Riedel at 2017-09-21T23:27:52+02:00 Make compatible with Prelude.<> export in GHC 8.4/base-4.11 - - - - - 3405dd52 by Tim Baumann at 2017-09-23T22:02:01+02:00 Add compile step that bundles and compresses JS files (#684) * Add compile step that bundles and compresses JS files Also, manage dependencies on third-party JS libraries using NPM. * Compile JS from TypeScript * Enable 'noImplicitAny' in TypeScript * QuickJump: use JSX syntax * Generate source maps from TypeScript for easier debugging * TypeScript: more accurate type * Separate quick jump css file from ocean theme - - - - - df0b5742 by Alex Biehl at 2017-09-29T21:15:40+02:00 Bump base for haddock-library and haddock-test - - - - - 62b12ea0 by Merijn Verstraaten at 2017-10-04T16:03:13+02:00 Inhibit output of coverage information for hidden modules. (#687) * Inhibit output of coverage information for hidden modules. * Add changelog entry. - - - - - 8daf8bc1 by Alexander Biehl at 2017-10-05T11:27:05+02:00 Don't use subMap in attachInstances - - - - - ad75114e by Alexander Biehl at 2017-10-05T11:27:58+02:00 Revert "Don't use subMap in attachInstances" This reverts commit 3adf5bcb1a6c5326ab33dc77b4aa229a91d91ce9. - - - - - 7d4aa02f by Alex Biehl at 2017-10-08T15:32:28+02:00 Precise Haddock: Use Avails for export resolution (#688) * Use Avails for export resolution * Support reexported modules * Factor out availExportItem * Use avails for fullModuleExports * Don't use subMap in attachInstances * lookupDocs without subMap * Completely remove subMap * Only calculate unqualified modules when explicit export list is given * Refactor * Refine comment * return * Fix * Refactoring * Split avail if declaration is not exported itself * Move avail splitting - - - - - b9b4faa8 by Alex Biehl at 2017-10-08T19:38:21+02:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 43325295 by Alex Biehl at 2017-10-08T20:18:46+02:00 Fix merge fallout - - - - - c6423cc0 by Alex Biehl at 2017-10-08T20:36:12+02:00 Copy QuickJump files over - - - - - 1db587c3 by Tim Baumann at 2017-10-09T18:33:09+02:00 Use <details> element for collapsibles (#690) * Remove unnecessary call to 'collapseSection' The call is unnecessary since there is no corresponding toggle for hiding the section of orphan instances. * Use <details> for collapsibles This makes them work even when JS is disabled. Closes haskell/haddock#560. - - - - - 1b54c64b by Tim Baumann at 2017-10-10T09:50:59+02:00 Quick Jump: Show error when loading 'doc-index.json' failed (#691) - - - - - 910f716d by Veronika Romashkina at 2017-10-24T07:36:20+02:00 Fix tiny typo in docs (#693) - - - - - b21de7e5 by Ryan Scott at 2017-10-24T13:07:15+02:00 Overhaul Haddock's rendering of kind signatures (#681) * Overhaul Haddock's rendering of kind signatures * Strip off kind signatures when specializing As an added bonus, this lets us remove an ugly hack specifically for `(->)`. Yay! * Update due to 0390e4a0f61e37bd1dcc24a36d499e92f2561b67 * @alexbiehl's suggestions * Import injectiveVarsOfBinder from GHC - - - - - 6704405c by Ryan Scott at 2017-10-28T07:10:27+02:00 Fix Haddock rendering of kind-indexed data family instances (#694) - - - - - 470f6b9c by Alex Biehl at 2017-10-30T08:45:51+01:00 Add QuickJump version to meta.json (#696) - - - - - b89eccdf by Alex Biehl at 2017-10-30T10:15:49+01:00 Put Quickjump behind --quickjump flag (#697) - - - - - 3095fb58 by Alex Biehl at 2017-10-30T19:09:06+01:00 Add build command to package.json - - - - - f223fda9 by Alex Biehl at 2017-10-30T19:10:39+01:00 Decrease threshold for fuzzy matching - - - - - 80245dda by Edward Z. Yang at 2017-10-31T20:35:05+01:00 Supported reexported-modules via --reexport flag. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 7e389742 by Alex Biehl at 2017-10-31T20:37:56+01:00 Correct missing title in changelog - - - - - 1a2a1c03 by Alex Biehl at 2017-10-31T20:59:07+01:00 Copy quickjump.css for nicer error messages - - - - - db234bb9 by Alex Biehl at 2017-10-31T21:31:18+01:00 Reexported modules: Report warnings if argument cannot be parsed or ... module cannot be found - - - - - eea8a205 by Carlo Hamalainen at 2017-10-31T21:43:14+01:00 More general type for nameCacheFromGhc. (#539) - - - - - 580eb42a by Alex Biehl at 2017-10-31T21:46:52+01:00 Remote tab - - - - - 0e599498 by Alex Biehl at 2017-10-31T21:48:55+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 7b8539bb by Alex Biehl at 2017-10-31T22:28:34+01:00 fullModuleContents traverses exports in declaration order - - - - - 0c91fbf2 by Alex Biehl at 2017-10-31T22:32:31+01:00 Remove excessive use of list comprehensions - - - - - f7356e02 by Alex Biehl at 2017-11-01T19:11:03+01:00 Make better use of AvailInfo - - - - - f3e512d5 by Alex Biehl at 2017-11-02T12:16:22+01:00 Always return documentation for exported subordinates ... event if they have no documentation (e.g. noDocForDecl) By using the information in the AvailInfo we don't need additional export checks. - - - - - 7cf58898 by Alan Zimmerman at 2017-11-07T08:28:03+02:00 Match changes for Trees that Grow in GHC - - - - - e5105a41 by Alan Zimmerman at 2017-11-08T17:21:58+02:00 Match Trees That Grow - - - - - 55178266 by Alan Zimmerman at 2017-11-11T22:20:31+02:00 Match Trees that Grow in GHC for HsExpr - - - - - 2082ab02 by Ryan Scott at 2017-11-14T15:27:03+01:00 Actually render infix type operators as infix (#703) * Actually render infix type operators as infix * Account for things like `(f :*: g) p`, too - - - - - c52ab7d0 by Alan Zimmerman at 2017-11-14T23:14:26+02:00 Clean up use of PlaceHolder, to match TTG - - - - - 81cc9851 by Moritz Angermann at 2017-11-20T07:52:49+01:00 Declare use of `Paths_haddock` module in other-modules (#705) This was detected by `-Wmissing-home-modules` - - - - - f9d27598 by Moritz Angermann at 2017-11-20T12:47:34+01:00 Drop Paths_haddock from ghc.mk (#707) With haskell/haddock#705 and haskell/haddock#706, the custom addition should not be necessary any more. # Conflicts: # ghc.mk - - - - - f34818dc by Moritz Angermann at 2017-11-20T12:47:59+01:00 Add autogen-modules (#706) > Packages using 'cabal-version: >= 1.25' and the autogenerated module Paths_* must include it also on the 'autogen-modules' field besides 'exposed-modules' and 'other-modules'. This specifies that the module does not come with the package and is generated on setup. Modules built with a custom Setup.hs script also go here to ensure that commands like sdist don't fail. # Conflicts: # haddock.cabal - - - - - bb43a0aa by Ben Gamari at 2017-11-21T15:50:12-05:00 Revert "Clean up use of PlaceHolder, to match TTG" This reverts commit 134a7bb054ea730b13c8629a76232d73e3ace049. - - - - - af9ebb2b by Ben Gamari at 2017-11-21T15:50:14-05:00 Revert "Match Trees that Grow in GHC for HsExpr" This reverts commit 9f054dc365379c66668de6719840918190ae6e44. - - - - - 5d35c3af by Ben Gamari at 2017-11-21T15:50:15-05:00 Revert "Match Trees That Grow" This reverts commit 73a26af844ac50b8bec39de11d64452a6286b00c. - - - - - 99a8e43b by Ben Gamari at 2017-11-21T16:36:06-05:00 Revert "Match changes for Trees that Grow in GHC" This reverts commit 01eeeb048acd2dd05ff6471ae148a97cf0720547. - - - - - c4d650c2 by Ben Gamari at 2017-12-04T15:06:07-05:00 Bump GHC version - - - - - 027b2274 by Ben Gamari at 2017-12-04T17:06:31-05:00 Bump GHC bound to 8.4.* - - - - - 58eaf755 by Alex Biehl at 2017-12-06T15:44:24+01:00 Update changelog - - - - - d68f5584 by Simon Peyton Jones at 2017-12-07T14:39:56+00:00 Track changes to follow Trac haskell/haddock#14529 This tracks the refactoring of HsDecl.ConDecl. - - - - - dc519d6b by Alec Theriault at 2018-01-06T08:20:43-08:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - 8285118c by Alec Theriault at 2018-01-13T12:12:37+01:00 Constructor and pattern synonym argument docs (#709) * Support Haddocks on constructor arguments This is in conjunction with https://phabricator.haskell.org/D4094. Adds support for rendering Haddock's on (non-record) constructor arguments, both for regular and GADT constructors. * Support haddocks on pattern synonym arguments It appears that GHC already parsed these - we just weren't using them. In the process of doing this, I tried to deduplicate some code around handling patterns. * Update the markup guide Add some information about the new support for commenting constructor arguments, and mention pattern synonyms and GADT-style constructors. * Overhaul LaTeX support for data/pattern decls This includes at least * fixing several bugs that resulted in invalid LaTeX * fixing GADT data declaration headers * overhaul handling of record fields * overhaul handling of GADT constructors * overhaul handling of bundled patterns * add support for constructor argument docs * Support GADT record constructors This means changes what existing HTML docs look like. As for LaTeX, looks like GADT records were never even supported. Now they are. * Clean up code/comments Made code/comments consistent between the LaTeX and XHTML backend when possible. * Update changelog * Patch post-rebase regressions * Another post-rebase change We want return values to be documentable on record GADT constructors. - - - - - ca4fabb4 by Alec Theriault at 2018-01-15T17:12:18-08:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 4c472fea by Ryan Scott at 2018-01-19T10:44:02+01:00 Fix haskell/haddock#732 (#733) - - - - - bff14dbd by Alex Biehl at 2018-01-19T15:33:30+01:00 extractDecl: Extract associated types correctly (#736) - - - - - a2a94a73 by Alex Biehl at 2018-01-19T15:34:40+01:00 extractDecl: Extract associated types correctly (#736) - - - - - 26df93dc by Alex Biehl at 2018-01-20T10:18:22+01:00 haddock-api: bump ghc to ^>= 8.4 - - - - - f65aeb1d by Alex Biehl at 2018-01-20T19:18:20+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - 0e721b97 by Alex Biehl at 2018-01-20T19:20:19+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - cb6234f6 by Ben Gamari at 2018-01-26T13:40:55-05:00 Merge remote-tracking branch 'harpocrates/fix/missing-orphan-instances' into ghc-head - - - - - 0fc28554 by Alec Theriault at 2018-02-01T14:58:18+01:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - b9123772 by Alec Theriault at 2018-02-01T14:58:18+01:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 0c12e274 by Ryan Scott at 2018-02-01T14:58:18+01:00 Fix haskell/haddock#548 by rendering datatype kinds more carefully (#702) - - - - - 8876d20b by Alec Theriault at 2018-02-01T14:58:18+01:00 Use the GHC lexer for the Hyperlinker backend (#714) * Start changing to use GHC lexer * better cpp * Change SrcSpan to RealSrcSpan * Remove error * Try to stop too many open files * wip * wip * Revert "wip" This reverts commit b605510a195f26315e3d8ca90e6d95a6737553e1. Conflicts: haddock-api/haddock-api.cabal haddock-api/src/Haddock/Interface.hs * Remove pointless 'caching' * Use dlist rather than lists when finding vars * Use a map rather than list * Delete bogus comment * Rebase followup Things now run using the GHC lexer. There are still - stray debug statements - unnecessary changes w.r.t. master * Cleaned up differences w.r.t. current Haddock HEAD Things are looking good. quasiquotes in particular look beautiful: the TH ones (with Haskell source inside) colour/link their contents too! Haven't yet begun to check for possible performance problems. * Support CPP and top-level pragmas The support for these is hackier - but no more hacky than the existing support. * Tests pass, CPP is better recognized The tests were in some cases altered: I consider the new output to be more correct than the old one.... * Fix shrinking of source without tabs in test * Replace 'Position'/'Span' with GHC counterparts Replaces 'Position' -> 'GHC.RealSrcLoc' and 'Span' -> 'GHC.RealSrcSpan'. * Nits * Forgot entry in .cabal * Update changelog - - - - - 95c6a771 by Alec Theriault at 2018-02-01T14:58:18+01:00 Clickable anchors for headings (#716) See haskell/haddock#579. This just adds an <a> tag around the heading, pointing to the heading itself. - - - - - 21463d28 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump: Matches on function names weight more than matches in ... module names. - - - - - 8023af39 by Alex Biehl at 2018-02-01T14:58:18+01:00 Treat escaped \] better in definition lists (#717) This fixes haskell/haddock#546. - - - - - e4866dc1 by Alex Biehl at 2018-02-01T14:58:18+01:00 Remove scanner, takeWhile1_ already takes care of escaping - - - - - 9bcaa49d by Alex Biehl at 2018-02-01T14:58:18+01:00 Take until line feed - - - - - 01d2af93 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Add simple framework for running parser fixtures (#668) * Add simple framework for running parser fixtures * Compatible with tree-diff-0.0.0.1 * Use parseParas to parse fixtures This allows to test all syntactic constructs available in haddock markup. - - - - - 31128417 by Alec Theriault at 2018-02-01T14:58:18+01:00 Patch flaky parser test (#720) * Patch flaky parser test This test was a great idea, but it doesn't port over too well to using the GHC lexer. GHC rewrites its input a bit - nothing surprising, but we need to guard against those cases for the test. * Change instance head * Change use site - - - - - 9704f214 by Herbert Valerio Riedel at 2018-02-01T14:58:18+01:00 Include secondary LICENSE file in source dist - - - - - 51f25074 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Grid Tables (#718) * Add table examples * Add table types and adopt simple parser Simple parser is done by Giovanni Cappellotto (@potomak) in https://github.com/haskell/haddock/pull/577 It seems to support single fine full tables, so far from full RST-grid tables, but it's good start. Table type support row- and colspans, but obviously parser is lacking. Still TODO: - Latex backend. Should we use multirow package https://ctan.org/pkg/multirow?lang=en? - Hoogle backend: ? * Implement grid-tables * Refactor table parser * Add two ill-examples * Update CHANGES.md * Basic documentation for tables * Fix documentation example - - - - - 670d6200 by Alex Biehl at 2018-02-01T14:58:18+01:00 Add grid table example to cheatsheet (pdf and svg need to be regenerated thought) - - - - - 4262dec9 by Alec Theriault at 2018-02-01T14:58:18+01:00 Fix infinite loop when specializing instance heads (#723) * Fix infinite loop when specializing instance heads The bug can only be triggered from TH, hence why it went un-noticed for so long. * Add test for haskell/haddock#679 and haskell/haddock#710 - - - - - 67ecd803 by Alec Theriault at 2018-02-01T14:58:18+01:00 Filter RTS arguments from 'ghc-options' arguments (#725) This fixes haskell/haddock#666. - - - - - 7db26992 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump Scrollable overlay - - - - - da9ff634 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Hyperlinker: Adjust parser to new PFailed constructor - - - - - 7b7cf8cb by Alexander Biehl at 2018-02-01T14:58:18+01:00 Specialize: Add missing IdP annotations - - - - - 78cd7231 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Convert: Correct pass type - - - - - a2d0f590 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Warning free compilation - - - - - cd861cf3 by Alexander Biehl at 2018-02-01T14:58:18+01:00 hadock-2.19.0 / haddock-api-2.19.0 / haddock-library-1.5.0 - - - - - c6651b72 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Adjust changelogs - - - - - 1e93da0b by Alexander Biehl at 2018-02-01T14:58:18+01:00 haddock-library: Info about breaking changes - - - - - f9b11db8 by Alec Theriault at 2018-02-02T12:36:02+01:00 Properly color pragma contents in hyperlinker The hyperlinker backend now classifies the content of pragmas as 'TkPragma'. That means that in something like '{-# INLINE foo #-}', 'foo' still gets classified as a pragma token. - - - - - c40b0043 by Alec Theriault at 2018-02-02T12:36:02+01:00 Support the new 'ITcolumn_prag' token - - - - - 4a2a4d39 by Alex Biehl at 2018-02-03T12:11:55+01:00 QuickJump: Mitigate encoding problems on Windows - - - - - bb34503a by Alex Biehl at 2018-02-04T18:39:31+01:00 Use withBinaryFile - - - - - 637605bf by Herbert Valerio Riedel at 2018-02-05T09:48:32+01:00 Try GHC 8.4.1 for Travis CI job - - - - - 7abb67e4 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 try harder to build w/ GHC 8.4.1 - - - - - 8255cc98 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 Add `SPDX-License-Identifier` as alised for "license" module header tokens C.f. SPDX 2.1 - Appendix V https://spdx.org/spdx-specification-21-web-version#h.twlc0ztnng3b The tag should appear on its own line in the source file, generally as part of a comment. SPDX-License-Identifier: <SPDX License Expression> Cherry-picked from haskell/haddock#743 - - - - - 267cd23d by Herbert Valerio Riedel at 2018-02-05T10:24:34+01:00 Make test-suite SMP compatible - - - - - 95d4bf40 by Alec Theriault at 2018-02-05T22:01:04+01:00 Hyperlink pattern synonyms and 'module' imports (#744) Links to pattern synonyms are now generated, as well as links from modules in import lists. Fixes haskell/haddock#731. - - - - - 67838dcd by Alec Theriault at 2018-02-06T08:23:36+01:00 Don't warn about missing '~' (#746) This manually filters out '~' from the list of things to warn about. It truly makes no sense to warn on this since '~' has nothing it could link to - it is magical. This fixes haskell/haddock#532. - - - - - ab6c3f9f by Alec Theriault at 2018-02-06T08:24:47+01:00 Don't barf on 'HsSpliceTy' (#745) This handles 'HsSpliceTy's by replacing them with what they expand to. IIUC everything that is happening, 'renameHsSpliceTy' should not be able to fail for the inputs we feed it from GHC. This fixes haskell/haddock#574. - - - - - 92bf95ad by Alex Biehl at 2018-02-06T08:28:23+01:00 Rename: renameHsSpliceTy ttg - - - - - 3130b1e1 by Alex Biehl at 2018-02-06T09:02:14+01:00 Expand SigDs - - - - - c72adae5 by Alex Biehl at 2018-02-06T09:20:51+01:00 fullModuleContents: support named docs - - - - - de2e4dbf by Alex Biehl at 2018-02-06T13:56:17+01:00 Hyperlinker: Also link pattern synonym arguments - - - - - b7c98237 by Alex Biehl at 2018-02-09T18:44:23+01:00 Expand SigD in a better place In https://github.com/haskell/haddock/issues/287 we found that haddock-2.19.0 would miss documentation on class methods with multiples names. This patch uses expandSigDecls in a more sensible place. - - - - - 8f598b27 by Alec Theriault at 2018-02-11T12:29:56+01:00 Add module tooltips to linked identifiers (#753) No more clicking to figure out whether your bytestring is strict or lazy! - - - - - d812e65d by Alec Theriault at 2018-02-11T12:31:44+01:00 Add 'show' option to complement 'hide' (#752) * Add 'show' option to complement 'hide' The behaviour is for flags passed in the command line to override flags in file headers. In the command line, later flags override earlier ones. Fixes haskell/haddock#751 and haskell/haddock#266. * Add a '--show-all' option - - - - - 6676cecb by Alex Biehl at 2018-02-18T11:07:15-05:00 QuickJump: Mitigate encoding problems on Windows (cherry picked from commit 86292c54bfee2343aee84559ec01f1fc68f52231) - - - - - e753dd88 by Alex Biehl at 2018-02-18T17:59:54+01:00 Use withBinaryFile - - - - - 724dc881 by Tamar Christina at 2018-02-19T05:34:49+01:00 Haddock: support splitted include paths. (#689) - - - - - 9b6d6f50 by Alex Biehl at 2018-02-19T05:57:02+01:00 Teach the HTML backend how to render methods with multiple names - - - - - a74aa754 by Alexander Biehl at 2018-02-19T10:04:34+01:00 Hoogle/Latex: Remove use of partial function - - - - - 66d8bb0e by Alec Theriault at 2018-02-25T16:04:01+01:00 Fix file handle leak (#763) (#764) Brought back some mistakenly deleted code for handling encoding and eager reading of files from e0ada1743cb722d2f82498a95b201f3ffb303137. - - - - - bb92d03d by Alex Biehl at 2018-03-02T14:21:23+01:00 Enable running test suite with stock haddock and ghc using ``` $ cabal new-run -- html-test --haddock-path=$(which haddock) --ghc-path=$(which ghc) ``` - - - - - dddb3cb2 by Alex Biehl at 2018-03-02T15:43:21+01:00 Make testsuite work with haddock-1.19.0 release (#766) - - - - - f38636ed by Alec Theriault at 2018-03-02T15:48:36+01:00 Support unicode operators, proper modules Unicode operators are a pretty big thing in Haskell, so supporting linking them seems like it outweighs the cost of the extra machinery to force Attoparsec to look for unicode. Fixes haskell/haddock#458. - - - - - 09d89f7c by Alec Theriault at 2018-03-02T15:48:43+01:00 Remove bang pattern - - - - - d150a687 by Alex Biehl at 2018-03-02T15:48:48+01:00 fix test - - - - - d6fd71a5 by Alex Biehl at 2018-03-02T16:22:38+01:00 haddock-test: Be more explicit which packages to pass We now pass `-hide-all-packages` to haddock when invoking the testsuite. This ensures we don't accidentally pick up any dependencies up through ghc.env files. - - - - - 0932c78c by Alex Biehl at 2018-03-02T17:50:38+01:00 Revert "fix test" This reverts commit 1ac2f9569242f6cb074ba6e577285a4c33ae1197. - - - - - 52516029 by Alex Biehl at 2018-03-02T18:16:50+01:00 Fix Bug548 for real - - - - - 89df9eb5 by Alex Biehl at 2018-03-05T18:28:19+01:00 Hyperlinker: Links for TyOps, class methods and associated types - - - - - d019a4cb by Ryan Scott at 2018-03-06T13:43:56-05:00 Updates for haskell/haddock#13324 - - - - - 6d5a42ce by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump haddock-2.19.0.1, haddock-api-2.19.0.1, haddock-library-1.5.0.1 - - - - - c0e6f380 by Alex Biehl at 2018-03-10T18:25:57+01:00 Update changelogs for haddock-2.19.0.1 and haddock-library-1.5.0.1 - - - - - 500da489 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Update to QC 2.11 - - - - - ce8362e9 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Restore backward-compat with base-4.5 through base-4.8 - - - - - baae4435 by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump lower bound for haddock-library - - - - - 10b7a73e by Alex Biehl at 2018-03-10T18:25:57+01:00 Haddock: Straighten out base bound - - - - - a6096f7b by Alex Biehl at 2018-03-13T08:45:06+01:00 extractDecl: Extract constructor patterns from data family instances (#776) * extractDecl: Allow extraction of data family instance constructors * extractDecl: extract data family instance constructors - - - - - ba4a0744 by Simon Jakobi at 2018-03-14T08:26:42+01:00 Readme: Update GHC version (#778) - - - - - 8de157d4 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for definition lists - - - - - 425b46f9 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for links - - - - - d53945d8 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for inline links - - - - - f1dc7c99 by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Slightly unmangle output - - - - - 0879d31c by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Prevent stdout buffering - - - - - 1f9e5f1b by Simon Jakobi at 2018-03-14T20:39:29+01:00 haddock-library.cabal: Clean up GHC options - - - - - 066b891a by Simon Jakobi at 2018-03-14T20:39:29+01:00 Make a proper definition for the <link> parser - - - - - 573d6ba7 by Alec Theriault at 2018-03-21T09:16:57+01:00 Show where instances are defined (#748) * Indicate source module of instances Above instance, we now also display a link to the module where the instance was defined. This is sometimes helpful in figuring out what to import. * Source module for type/data families too * Remove parens * Accept tests - - - - - 99b5d28b by Alex Biehl at 2018-03-21T09:20:36+01:00 Prepare changelog for next release - - - - - 482d3a93 by Alex Biehl at 2018-03-23T15:57:36+01:00 Useful cost centres, timers and allocation counters (#785) * Add some useful cost-centres for profiling * Add withTiming for each haddock phase Invoking haddock with `--optghc=-ddump-timings` now shows the amount of time spent and the number of allocated bytes for each phase. - - - - - 773b41bb by Alec Theriault at 2018-03-27T08:35:59+02:00 @since includes package name (#749) * Metadoc stores a package name This means that '@since' annotations can be package aware. * Get the package name the right way This should extract the package name for `@since` annotations the right way. I had to move `modulePackageInfo` around to do this and, in the process, I took the liberty to update it. Since it appears that finding the package name is something that can fail, I added a warning for this case. * Silence warnings * Hide package for local 'since' annotations As discussed, this is still the usual case (and we should avoid being noisy for it). Although this commit is large, it is basically only about threading a 'Maybe Package' from 'Haddock.render' all the way to 'Haddock.Backends.Xhtml.DocMarkup.renderMeta'. * Bump binary interface version * Add a '--since-qual' option This controls when to qualify since annotations with the package they come from. The default is always, but I've left an 'external' variant where only those annotations coming from outside of the current package are qualified. * Make ParserSpec work * Make Fixtures work * Use package name even if package version is not available The @since stuff needs only the package name passed in, so it makes sense to not be forced to pass in a version too. - - - - - e42c57bc by Alex Biehl at 2018-03-27T08:42:50+02:00 haddock-2.19.1, haddock-api-2.19.1, haddock-library-1.6.0 - - - - - 8373a529 by Alex Biehl at 2018-03-28T10:17:11+02:00 Bump haddock and haddock-api to 2.20.0 - - - - - 5038eddd by Jack Henahan at 2018-04-03T13:28:12+02:00 Clear search string on hide for haskell/haddock#781 (#789) - - - - - 920ca1eb by Alex Biehl at 2018-04-03T16:35:50+02:00 Travis: Build with ghc-8.4.2 (#793) - - - - - a232f0eb by Alan Zimmerman at 2018-04-07T14:14:32+02:00 Match changes in GHC for D4199 Removing HasSourceText and SourceTextX classes. - - - - - ab85060b by Alan Zimmerman at 2018-04-09T21:20:24+02:00 Match GHC changes for TTG - - - - - 739302b6 by Alan Zimmerman at 2018-04-13T13:31:44+02:00 Match GHC for TTG implemented on HsBinds, D4581 - - - - - 2f56d3cb by Ryan Scott at 2018-04-19T11:42:58-04:00 Bump upper bound on base to < 4.13 See https://ghc.haskell.org/trac/ghc/ticket/15018. - - - - - a49df92a by Alex Biehl at 2018-04-20T07:31:44+02:00 Don't treat fixity signatures like declarations - - - - - d02c103b by Ryan Scott at 2018-04-24T11:20:11-04:00 Add regression test for haskell/haddock#413 Fixes haskell/haddock#413. - - - - - c7577f52 by Ryan Scott at 2018-04-24T13:51:06-07:00 Improve the Hoogle backend's treatment of type families (#808) Fixes parts 1 and 2 of haskell/haddock#806. - - - - - d88f85b1 by Alec Theriault at 2018-04-25T11:24:07-07:00 Replace 'attoparsec' with 'parsec' (#799) * Remove attoparsec with parsec and start fixing failed parses * Make tests pass * Fix encoding issues The Haddock parser no longer needs to worry about bytestrings. All the internal parsing work in haddock-library happens over 'Text'. * Remove attoparsec vendor * Fix stuff broken in 'attoparsec' -> 'parsec' * hyperlinks * codeblocks * examples Pretty much all issues are due to attoparsec's backtracking failure behaviour vs. parsec's non-backtracking failure behaviour. * Fix small TODOs * Missing quote + Haddocks * Better handle spaces before/after paragraphs * Address review comments - - - - - fc25e2fe by Alan Zimmerman at 2018-04-27T15:36:53+02:00 Match changes in GHC for TTG - - - - - 06175f91 by Herbert Valerio Riedel at 2018-05-01T18:11:09+02:00 Merge branch 'ghc-head' with 'ghc-8.4' - - - - - 879caaa8 by Alec Theriault at 2018-05-07T18:53:15-07:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 3e0120cb by Simon Jakobi at 2018-05-07T19:00:18-07:00 Add docs for some DocH constructors (#814) - - - - - 0a32c6db by Alec Theriault at 2018-05-08T02:15:45-07:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 8816e783 by Simon Jakobi at 2018-05-08T10:48:11-07:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - ad60366f by Ryan Scott at 2018-05-10T11:19:47-04:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - 03b7cc3b by Ryan Scott at 2018-05-10T11:24:38-04:00 Wibbles - - - - - b03dd563 by Chaitanya Koparkar at 2018-05-10T11:44:58-04:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 9f298a40 by Ben Gamari at 2018-05-13T17:36:04-04:00 Account for refactoring of LitString - - - - - ea3dabe7 by Ryan Scott at 2018-05-16T09:21:43-04:00 Merge pull request haskell/haddock#826 from haskell/T825 Remove Hoogle backend hack that butchers infix datatype names - - - - - 0d234f7c by Alec Theriault at 2018-05-23T11:29:05+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 15fc9712 by Simon Jakobi at 2018-05-31T04:17:47+02:00 Adjust to new HsDocString internals - - - - - 6f1e19a8 by Ben Gamari at 2018-06-02T16:18:58-04:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 0d0355d9 by Ryan Scott at 2018-06-04T21:26:59-04:00 DerivingVia changes - - - - - 0d93475a by Simon Jakobi at 2018-06-05T19:47:05+02:00 Bump a few dependency bounds (#845) - - - - - 5cbef804 by Alec Theriault at 2018-06-05T19:47:16+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 9094c56f by Alec Theriault at 2018-06-05T22:53:25+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 70188719 by Simon Jakobi at 2018-06-08T22:20:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - 495cd1fc by Chaitanya Koparkar at 2018-06-13T23:01:34+02:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 81088732 by Ben Gamari at 2018-06-13T23:01:34+02:00 Account for refactoring of LitString - - - - - 7baf6587 by Simon Jakobi at 2018-06-13T23:05:08+02:00 Adjust to new HsDocString internals - - - - - bb61464d by Ben Gamari at 2018-06-13T23:05:22+02:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 5d8cb87f by Ryan Scott at 2018-06-13T23:39:30+02:00 DerivingVia changes - - - - - 73d373a3 by Alec Theriault at 2018-06-13T23:39:30+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 4865e254 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Remove `ITtildehsh` token - - - - - b867db54 by Alec Theriault at 2018-06-13T23:39:30+02:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 9598e392 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Add docs for some DocH constructors (#814) - - - - - 8a59035b by Alec Theriault at 2018-06-13T23:39:30+02:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 29350fc8 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - 2590bbd9 by Ryan Scott at 2018-06-13T23:39:30+02:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - a9939fdc by Ryan Scott at 2018-06-13T23:39:30+02:00 Wibbles - - - - - a22f7df4 by Alec Theriault at 2018-06-13T23:39:30+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 8741015d by Simon Jakobi at 2018-06-13T23:39:30+02:00 Bump a few dependency bounds (#845) - - - - - 4791e1cc by Alec Theriault at 2018-06-13T23:39:30+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 311d3216 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - d0577817 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Complete FixitySig and FamilyDecl pattern matches - - - - - 055b3aa7 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Fix redundant import warnings - - - - - f9ce19b1 by Simon Jakobi at 2018-06-13T23:49:52+02:00 html-test: Accept output - - - - - 04604ea7 by Simon Jakobi at 2018-06-13T23:54:37+02:00 Bump bounds on Cabal - - - - - 0713b692 by Simon Jakobi at 2018-06-14T00:00:12+02:00 Merge branch 'ghc-head' into ghc-head-update-3 - - - - - c6a56bfd by Simon Jakobi at 2018-06-14T02:33:27+02:00 Bump ghc bound for haddock-api spec test-suite - - - - - 119d04b2 by Simon Jakobi at 2018-06-14T12:37:48+02:00 Travis: `--allow-newer` for all packages - - - - - 0e876e2c by Alex Biehl at 2018-06-14T15:28:52+02:00 Merge pull request haskell/haddock#857 from sjakobi/ghc-head-update-3 Update ghc-head - - - - - 5be46454 by Alec Theriault at 2018-06-14T21:42:45+02:00 Improved handling of interfaces in 'haddock-test' (#851) This should now work with an inplace GHC where (for instance) HTML directories may not be properly recorded in the package DB. - - - - - 96ab1387 by Vladislav Zavialov at 2018-06-14T17:06:21-04:00 Handle -XStarIsType - - - - - e518f8c4 by Ben Gamari at 2018-06-14T17:48:00-04:00 Revert unintentional reversion of fix of haskell/haddock#548 - - - - - 01b9f96d by Alan Zimmerman at 2018-06-19T11:52:22+02:00 Match changes in GHC for haskell/haddock#14259 - - - - - 7f8c8298 by Ben Gamari at 2018-06-19T18:14:27-04:00 Bump GHC version to 8.6 - - - - - 11c6b5d2 by Ryan Scott at 2018-06-19T23:17:31-04:00 Remove HsEqTy and XEqTy - - - - - b33347c2 by Herbert Valerio Riedel at 2018-06-20T23:14:52+02:00 Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. - - - - - f0d2460e by Herbert Valerio Riedel at 2018-06-20T23:28:46+02:00 Update Travis CI job - - - - - ef239223 by Herbert Valerio Riedel at 2018-06-20T23:32:41+02:00 Drop GHC HEAD from CI and update GHC to 8.4.3 It's a waste of resource to even try to build this branch w/ ghc-head; so let's not do that... - - - - - 41c4a9fa by Ben Gamari at 2018-06-20T18:26:20-04:00 Bump GHC version to 8.7 - - - - - 8be593dc by Herbert Valerio Riedel at 2018-06-21T22:32:15+02:00 Update CI job to use GHC 8.7.* - - - - - b91d334a by Simon Jakobi at 2018-06-30T13:41:38+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section - - - - - f707d848 by Alec Theriault at 2018-07-05T10:43:35-04:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. - - - - - a6d2b8dc by Alec Theriault at 2018-07-06T10:06:32-04:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case - - - - - 13819f71 by Alan Zimmerman at 2018-07-15T19:33:51+02:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 - - - - - c346aa78 by Simon Jakobi at 2018-07-19T12:29:32+02:00 haddock-library: Bump bounds for containers - - - - - 722e733c by Simon Jakobi at 2018-07-19T13:36:45+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] - - - - - f0bd83fd by Alec Theriault at 2018-07-19T14:39:57+02:00 Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. - - - - - 394053a8 by Simon Jakobi at 2018-07-19T14:58:07+02:00 haddock-library: Bump bounds for containers - - - - - 1bda11a2 by Alec Theriault at 2018-07-20T09:04:03+02:00 Add HEAD.hackage overlay (#887) * Add HEAD.hackage overlay * Add HCPKG variable - - - - - c7b4ab45 by Alec Theriault at 2018-07-20T12:01:16+02:00 Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test - - - - - c05d32ad by Alec Theriault at 2018-07-20T12:01:49+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output - - - - - 24b39ee4 by Alec Theriault at 2018-07-20T12:02:16+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. - - - - - cb9d2099 by Simon Jakobi at 2018-07-20T13:39:29+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) - - - - - 133f24f5 by Alec Theriault at 2018-07-20T13:39:29+02:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) - - - - - 11024149 by Alec Theriault at 2018-07-20T13:39:29+02:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) - - - - - de0c139e by Simon Jakobi at 2018-07-20T13:39:29+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) - - - - - 6435e952 by Alec Theriault at 2018-07-20T13:39:29+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) - - - - - 1461af39 by Alec Theriault at 2018-07-20T13:39:29+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) - - - - - 69d3bde1 by Alec Theriault at 2018-07-20T13:49:47+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) - - - - - 6a5c73c7 by Alec Theriault at 2018-07-20T13:50:00+02:00 Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests - - - - - 92ca94c6 by Alec Theriault at 2018-07-20T13:55:36+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) - - - - - 981bc7fa by Simon Jakobi at 2018-07-20T15:06:06+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers - - - - - 27e7c0c5 by Simon Jakobi at 2018-07-20T15:09:05+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 49e1a415 by Simon Jakobi at 2018-07-20T16:02:02+02:00 Update the ghc-8.6 branch (#889) * Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. * README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) * Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) * Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) * tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) * Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. * Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test * Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) * Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) * Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) * Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests * Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 5ca14bed by Simon Jakobi at 2018-07-20T16:05:47+02:00 Revert "Revert "Bump GHC version to 8.6"" That commit didn't belong onto the ghc-8.6 branch. This reverts commit acbaef3b9daf1d2dea10017964bf886e77a8e967. - - - - - 2dd600dd by Simon Jakobi at 2018-07-20T16:18:21+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. - - - - - fceb2422 by Simon Jakobi at 2018-07-20T16:18:21+02:00 outOfScope: Recommend qualifying the identifier - - - - - acea5d23 by Simon Jakobi at 2018-07-20T16:19:35+02:00 outOfScope: Recommend qualifying the identifier (cherry picked from commit 73707ed58d879cc04cb644c5dab88c39ca1465b7) - - - - - 1a83ca55 by Simon Jakobi at 2018-07-20T16:19:35+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. (cherry picked from commit d504a2864a4e1982e142cf88c023e7caeea3b76f) - - - - - 48374451 by Masahiro Sakai at 2018-07-20T17:06:42+02:00 Add # as a special character (#884) '#' has special meaning used for anchors and can be escaped using backslash. Therefore it would be nice to be listed as special characters. - - - - - 5e1a5275 by Alec Theriault at 2018-07-20T23:37:24+02:00 Let `haddock-test` bypass interface version check (#890) This means `haddock-test` might * crash during deserialization * deserialize incorrectly Still - it means things _might_ work where they were previously sure not to. - - - - - 27286754 by Yuji Yamamoto at 2018-07-23T08:16:01+02:00 Avoid "invalid argument (invalid character)" on non-unicode Windows (#892) Steps to reproduce and the error message ==== ``` > stack haddock basement ... snip ... Warning: 'A' is out of scope. Warning: 'haddock: internal error: <stdout>: commitBuffer: invalid argument (invalid character) ``` Environment ==== OS: Windows 10 ver. 1709 haddock: [HEAD of ghc-8.4 when I reproduce the error](https://github.com/haskell/haddock/commit/532b209d127e4cecdbf7e9e3dcf4f653a5605b5a). (I had to use this version to avoid another probrem already fixed in HEAD) GHC: 8.4.3 stack: Version 1.7.1, Git revision 681c800873816c022739ca7ed14755e85a579565 (5807 commits) x86_64 hpack-0.28.2 Related pull request ==== https://github.com/haskell/haddock/pull/566 - - - - - 6729d361 by Alec Theriault at 2018-07-23T13:52:56-07:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). - - - - - 8cf4e6b5 by Ryan Scott at 2018-07-27T11:28:03-04:00 eqTyCon_RDR now lives in TysWiredIn After GHC commit http://git.haskell.org/ghc.git/commit/f265008fb6f70830e7e92ce563f6d83833cef071 - - - - - 1ad251a6 by Alan Zimmerman at 2018-07-30T13:28:09-04:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 (cherry picked from commit e3926b50ab8a7269fd6904b06e881745f08bc5d6) - - - - - 8aea2492 by Richard Eisenberg at 2018-08-02T10:54:17-04:00 Update against new HsImplicitBndrs - - - - - e42cada9 by Alec Theriault at 2018-08-04T17:51:30+02:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 0e852512 by Alex Biehl at 2018-08-06T13:04:02+02:00 Make --package-version optional for --hoogle generation (#899) * Make --package-version optional for --hoogle generation * Import mkVersion * It's makeVersion not mkVersion - - - - - d2abd684 by Noel Bourke at 2018-08-21T09:34:18+02:00 Remove unnecessary backslashes from docs (#908) On https://haskell-haddock.readthedocs.io/en/latest/markup.html#special-characters the backslash and backtick special characters showed up with an extra backslash before them – I think the escaping is not (or no longer) needed for those characters in rst. - - - - - 7a578a9e by Matthew Pickering at 2018-08-21T09:34:50+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - aa3d4db3 by Matthew Pickering at 2018-08-21T09:37:34+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - ede91744 by Alec Theriault at 2018-08-21T09:42:52+02:00 Better test output when Haddock crashes on a test (#902) In particular: we report the tests that crashed seperately from the tests that produced incorrect output. In order for tests to pass (and exit 0), they must not crash and must produce the right output. - - - - - 4a872b84 by Guillaume Bouchard at 2018-08-21T09:45:57+02:00 Fix a typo (#878) - - - - - 4dbf7595 by Ben Sklaroff at 2018-08-21T12:04:09-04:00 Add ITcomment_line_prag token to Hyperlinker Parser This token is necessary for parsing #line pragmas inside nested comments. Reviewers: bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D4935 - - - - - 9170b2a9 by Ben Gamari at 2018-08-21T17:55:15-04:00 Merge pull request haskell/haddock#893 from harpocrates/get-name-to-instances Accumulate explicitly which modules to load for 'attachInstances' - - - - - d57b57cc by Ben Gamari at 2018-08-21T17:59:13-04:00 Merge branch 'ghc-head' of github.com:haskell/haddock into ghc-head - - - - - 14601ca2 by Alec Theriault at 2018-08-21T19:09:37-04:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). (cherry picked from commit 5c7c596c51d69b92164e9ba920157b36ce2b2ec1) - - - - - 438c645e by Matthew Pickering at 2018-08-21T19:12:39-04:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 (cherry picked from commit e6aa8fb47b9477cc5ef5e46097524fe83e080f6d) - - - - - a80c5161 by Alec Theriault at 2018-08-21T22:06:40-07:00 Better rendering of unboxed sums/tuples * adds space after/before the '#' marks * properly reify 'HsSumTy' in 'synifyType' - - - - - 88456cc1 by Alec Theriault at 2018-08-21T22:06:40-07:00 Handle promoted tuples in 'synifyType' When we have a fully applied promoted tuple, we can expand it out properly. - - - - - fd1c1094 by Alec Theriault at 2018-08-21T22:19:34-07:00 Accept test cases - - - - - 6e80d9e0 by Alec Theriault at 2018-08-21T22:24:03-07:00 Merge pull request haskell/haddock#914 from harpocrates/feature/unboxed-stuff Better rendering of unboxed sums, unboxed tuples, promoted tuples. - - - - - 181a23f1 by Ben Gamari at 2018-08-23T15:53:48-04:00 Merge remote-tracking branch 'origin/ghc-8.6' into ghc-8.6 - - - - - 3a18c1d8 by Alec Theriault at 2018-08-27T14:15:25-07:00 Properly synify promoted list types We reconstruct promoted list literals whenever possible. That means that 'synifyType' produces '[Int, Bool, ()] instead of (Int ': (() ': (Bool ': ([] :: [Type])))) - - - - - b4794946 by Alec Theriault at 2018-09-03T07:19:55-07:00 Only look at visible types when synifying a 'HsListTy' The other types are still looked at when considering whether to make a kind signature or not. - - - - - a231fce2 by Alec Theriault at 2018-09-03T07:38:10-07:00 Merge pull request haskell/haddock#922 from harpocrates/promoted-lists Properly synify promoted list types - - - - - 0fdf044e by Ningning Xie at 2018-09-15T10:25:58-04:00 Update according to GHC Core changes - - - - - 7379b115 by Ningning Xie at 2018-09-15T15:40:18-04:00 update dataFullSig to work with Co Quantification This should have been in the previous patch, but wasn't. - - - - - cf84a046 by Alec Theriault at 2018-09-17T20:12:18-07:00 Fix/add to various docs * Add documentation for a bunch of previously undocumented options (fixes haskell/haddock#870) * Extend the documentation of `--hoogle` considerably (see haskell/haddock#807) * Describe how to add docs to `deriving` clauses (fixes haskell/haddock#912) * Fix inaccurate docs about hyperlinking infix identifiers (fixes haskell/haddock#780) - - - - - ae017935 by Alec Theriault at 2018-09-22T08:32:16-07:00 Update Travis - - - - - d95ae753 by Alec Theriault at 2018-09-22T09:34:10-07:00 Accept failing tests Also silence orphan warnings. - - - - - f3e67024 by Alec Theriault at 2018-09-22T09:41:23-07:00 Bump haddock-api-2.21.0, haddock-library-1.7.0 * Update CHANGELOGS * Update new versions in Cabal files * Purge references to ghc-8.4/master branches in README - - - - - 3f136d4a by Alec Theriault at 2018-09-22T10:53:31-07:00 Turn haddock-library into a minor release Fix some version bounds in haddock-library too. - - - - - b9def006 by Alec Theriault at 2018-09-22T13:07:35-07:00 keep cabal.project file - - - - - 4909aca7 by Alec Theriault at 2018-10-16T09:36:30-07:00 Build on 7.4 and 7.8 - - - - - 99d20a28 by Herbert Valerio Riedel at 2018-10-16T18:45:52+02:00 Minor tweak to package description - - - - - a8059618 by Herbert Valerio Riedel at 2018-10-16T18:47:24+02:00 Merge pull request haskell/haddock#945 haddock-api 2.21.0 and haddock-library 1.6.1 release - - - - - 2d9bdfc1 by Alec Theriault at 2018-10-16T10:54:21-07:00 Bump haddock-library to 1.7.0 The 1.6.1 release should've been a major bump, since types in the `Documentation.Haddock.Parser.Monad` module changed. This version makes that module internal (as it morally should be). - - - - - ed340cef by Alec Theriault at 2018-10-16T14:59:13-07:00 Merge branch 'ghc-8.4' into ghc-8.6 - - - - - 2821a8df by Alec Theriault at 2018-10-16T15:14:48-07:00 Merge branch 'ghc-8.6' into ghc-head - - - - - a722dc84 by Alec Theriault at 2018-10-16T16:28:55-07:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 63377496 by Alec Theriault at 2018-10-16T16:39:07-07:00 Update changelog - - - - - 099a0110 by Alec Theriault at 2018-10-16T16:49:28-07:00 Merge pull request haskell/haddock#942 from harpocrates/update-docs Fix & add to documentation - - - - - 0927416f by Alec Theriault at 2018-10-16T16:50:14-07:00 Set UTF-8 encoding before writing files (#934) This should fix haskell/haddock#929, as well as guard against future problems of this sort in other places. Basically replaces 'writeFile' (which selects the users default locale) with 'writeUtf8File' (which always uses utf8). - - - - - 83b7b017 by Alec Theriault at 2018-10-16T17:42:05-07:00 Output pattern synonyms in Hoogle backend (#947) * Output pattern synonyms in Hoogle backend We were previously weren't outputting _any_ pattern synonyms, bundled or not. Now, we output both. Fixes haskell/haddock#946. * Update changelog - - - - - 81e5033d by Alec Theriault at 2018-10-16T18:04:40-07:00 Release `haddock{,-api}-2.22.0` This version will accompany ghc-8.6.2 - - - - - 9661744e by Alex Biehl at 2018-10-18T08:14:32-07:00 Add NewOcean theme And make it the default theme. - - - - - 7ae6d722 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Improve appearance and readability These changes include: - use latest Haskell's logo colors - decrease #content width to improve readability - use nicer font - improve sizes and distances - - - - - 37f8703d by NunoAlexandre at 2018-10-18T08:14:32-07:00 Include custom font in the html head - - - - - 1d5e1d79 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Update html test reference files - - - - - 53b7651f by NunoAlexandre at 2018-10-18T08:14:32-07:00 Make it responsive - It makes small screens taking more space than larger ones - fixes a few issues present in small screens currently - make it look good across different screen sizes. - - - - - 6aa1aeb1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make the style consistent with hackage Several things are addressed here: - better responsive behaviour on the header - better space usage - consistent colors overall - other nit PR comments - - - - - 3a250c5c by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Place the package name before the menu links This supports the expected responsive menu design, where the package name appears above the menu links. - - - - - cae699b3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update html-test reference files The package name element in the package-header is now a div instead of a paragraph, and it is now above the menu ul.links instead of below. - - - - - 2ec7fd2d by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve synopsis style and code - Use CSS3 instead of loading pictures to show "+" and "-" symbols - Drop redundant code - - - - - 0c874c01 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Decrease space between code blocks There was too much space between code blocks as pointed out by reviewers. - - - - - 85568ce2 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Add an initial-scale property to all haddock pages This solves an issue reported about the content looking incredibly small on mobile devices. - - - - - c1538926 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Address several PR comments - Darken text color like done for hackage - Move synopsis to left side - Make table of contents stick to the left on wide screens - Wrap links to avoid page overflow - Improve expand/collapse buttons - Fix issue with content size on mobile devices - Fix issue with font-size on landscape mode - Increase width of the content - Change colors of table of contents and synopsis - Etc - - - - - e6639e5f by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make synopsis scrollable on wide screens When the synopsis is longer than the screen, you can’t see its end and you can't scroll down either, making the content unreachable. - - - - - 1f0591ff by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve information density - Reduce font size - Improve space between and within code blocks - Improve alignments - Improve spacing within sub-blocks - - - - - bf083097 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Minor adjustments Bring in some adjustments made to hackage: - link colors - page header show everything when package title is too long - - - - - 10375fc7 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix responsive triggers overlap issue The min and max width triggers have the same values, which caused the style resolution to take an intersection of both style declarations when the screen resolution had the size of the limts (say 1280px), causing an odd behaviour and look. - - - - - 95ff2f95 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix issue with menu alignment on firefox Reported and described here: https://github.com/haskell/haddock/pull/721#issuecomment-374668869 - - - - - dc86587e by Alex Biehl at 2018-10-18T08:14:32-07:00 Changelog entry for NewOcean - - - - - 27195e47 by Herbert Valerio Riedel at 2018-10-18T08:14:32-07:00 html-test --accept - - - - - 83f4f9c0 by Alex Biehl at 2018-10-18T08:14:32-07:00 Avoid name shadowing - - - - - 231487f1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font to PT Sans Also migrate some general text related changes from hackage. - - - - - 313db81a by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Use 'flex' to fix header alignment - - - - - 5087367b by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Misc of tweaks - Update link colors to hackage scheme - Tune spacing between content elements - Update footer style - Fix and improve code blocks identation - - - - - b08020df by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font in Xhtml.hs to PT Sans - - - - - 78ce06e3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve code blocks styling - Fix and improve spacing - Improve colors and borders - - - - - 81262d20 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make package-header caption backward-compatible The current html generator of this branch wraps the package-header caption as a div, which does not work (without style adjustments) with the old themes. Changing it from div to span does the trick, without needing to adjust the old stylesheets. - - - - - dc4475cb by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update test-suite reference html pages - - - - - 393d35d8 by Alec Theriault at 2018-10-18T08:25:36-07:00 Accept tests - - - - - a94484ba by Alec Theriault at 2018-10-21T10:29:29-07:00 Fix CHANGELOG - - - - - 8797eca3 by Alec Theriault at 2018-10-21T10:36:19-07:00 Update 'data-files' to include NewOcean stuff - - - - - 1ae51e4a by Simon Jakobi at 2018-10-23T11:29:14+02:00 Fix typo in a warning - - - - - 009ad8e8 by Alec Theriault at 2018-10-24T12:47:47-07:00 Update JS dependencies This was done via `npm audit fix`. I think this fixes haskell/haddock#903 along with some more serious vulnerabilities that nobody seems to have noticed. - - - - - 051994db by Alec Theriault at 2018-10-24T17:31:09-07:00 Resurrect the style-switcher This fixes haskell/haddock#810. Looks like things were broken during the quickjump refactor of the JS. For the (git) record: I do not think the style switcher is a good idea. I'm fixing it for the same reason @mzero added it; as an answer to "rumblings from some that they didn't want their pixels changed on bit" - - - - - 2a1d620f by Alec Theriault at 2018-10-24T17:38:07-07:00 Fix copy-pasta error in data-files - - - - - ed5bfb7f by Alec Theriault at 2018-10-24T20:42:14-07:00 Fix the synopsis button Here's these changes are supposed to do: * put the synopsis back on the right side * properly have it on the edge of the screen on wide screens * adjust the background of the synopsis to match the button (otherwise the grey blends in with what is underneath) * get rid of the dotted purple line * the synopsis contents are now scrollable even when in wide screens (this has been a long-standing bug) - - - - - 883fd74b by Alec Theriault at 2018-10-25T20:16:46-07:00 Avoid more conflicts in generated ids (#954) This fixes haskell/haddock#953 by passing more names into the generated ids. - - - - - ea54e331 by Alec Theriault at 2018-10-25T21:07:12-07:00 Don't hide bullets in method docs I think thst CSS was meant only to deal with fields and the effect on bullets was accidental. Fixes haskell/haddock#926. - - - - - 9a14ef4a by Alec Theriault at 2018-10-25T22:02:07-07:00 Indent more things + slightly smaller font - - - - - b9f17e29 by Alec Theriault at 2018-10-25T22:10:01-07:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 096a3cfa by Alec Theriault at 2018-10-25T22:24:38-07:00 Accept HTML output - - - - - 2669517d by Alec Theriault at 2018-10-26T09:02:35-07:00 User manual + stuff for building GHC docs - - - - - 46b27687 by Alec Theriault at 2018-10-26T09:10:59-07:00 Make 'Contents' in NewOcean scrollable This only happens if the contents block on the left is so big that it doesn't fit (vertically) on the page. If that happens, we want it to be scrollable. - - - - - 3443dd94 by Alec Theriault at 2018-10-26T09:36:46-07:00 Revert "Make 'Contents' in NewOcean scrollable" This reverts commit f909ffd8353d6463fd5dd184998a32aa98d5c922. I missed the fact this also forces the 'Contents' to always go down to the bottom of the page. - - - - - ed081424 by Alec Theriault at 2018-10-26T14:22:23-07:00 Avoid some partiality AFAICT this wasn't causing any crashes, but that's mostly because we happen not to be forcing `pkgStr` when it would diverge. We come dangerously close to doing that in `ppHtmlIndex`. Fixes haskell/haddock#569. - - - - - 6a5bec41 by Alec Theriault at 2018-10-27T10:05:04-07:00 Fix documentation in `haddock-api` (#957) * Fix misplaced Haddocks in Haddock itself Haddock should be able to generate documentation for 'haddock-api' again. * Make CI check that documentation can be built. * Add back a doc that is OK - - - - - 5100450a by Matthew Yacavone at 2018-10-27T14:51:38-04:00 More explicit foralls (GHC Proposal 0007) - - - - - 8771a6b0 by Alec Theriault at 2018-11-05T13:58:11-08:00 Only run MathJax on entities with "mathjax" class (#960) Correspondingly, we wrap all inline/diplay math in <span class="mathjax"> ... the math .... </span> This fixes haskell/haddock#959. - - - - - bd7ff5c5 by Alec Theriault at 2018-11-05T15:54:22-08:00 Deduplicate some work in 'AttachInstances' Perf only change: * avoid needlessly union-ing maps * avoid synify-ing instances twice Took this opportunity to add some docs too - - - - - cf99fd8f by Alec Theriault at 2018-11-05T15:54:22-08:00 Specialize some SYB functions Perf only change: * Add a 'SPECIALIZE' pragma to help GHC optimize a 'Data a =>' constraint * Manually specialize the needlessly general type of 'specializeTyVarBndrs' - - - - - 4f91c473 by Alec Theriault at 2018-11-05T15:54:22-08:00 Improve perf of renaming Perf only change: * don't look up type variable names (they're never in the environment) * use a difference list for accumulating missing names * more efficient 'Functor'/'Applicative' instances for 'RnM' - - - - - 4bbab0d4 by Alec Theriault at 2018-11-05T15:54:22-08:00 Faster 'Text' driven parser combinators Perf only change: * use 'getParserState'/'setParserState' to make 'Text'-optimized parser combinators * minimize uses of 'Data.Text.{pack,unpack,cons,snoc}' - - - - - fa430c02 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support hyperlink labels with inline markup The parser for pictures hasn't been properly adjusted yet. - - - - - c1431035 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support (and flatten) inline markup in image links Inline markup is supported in image links but, as per the [commonmark recommendation][0], it is stripped back to a plain text representation. [0]: https://spec.commonmark.org/0.28/#example-547 - - - - - d4ee1ba5 by Alec Theriault at 2018-11-06T12:03:24-08:00 Accept test case - - - - - 8088aeb1 by Alec Theriault at 2018-11-06T12:03:24-08:00 Fix/add to haddock-library test suite - - - - - e78f644d by Alec Theriault at 2018-11-06T13:26:31-08:00 Bump version bounds - - - - - 644335eb by Alec Theriault at 2018-11-06T13:53:30-08:00 Merge pull request haskell/haddock#875 from harpocrates/feature/markup-in-hyperlinks Inline markup in markdown-style links and images - - - - - e173ed0d by Alec Theriault at 2018-11-07T12:37:18-08:00 Fix issues around plus/minus * swap the minimize unicode to something more intuitive * use new unicode expander/collapser for instance lists * address some alignment issues in the "index" page - - - - - b2d92df7 by Alec Theriault at 2018-11-07T13:41:57-08:00 Allow "Contents" summary to scroll in a fixed div In the unfortunate event that the "Contents" summary doesn't fit vertically (like in the "Prelude"), it will be scrollable. - - - - - ca704c23 by Alec Theriault at 2018-11-07T13:45:15-08:00 Accept HTML output changes - - - - - 82c0ec6d by Alec Theriault at 2018-11-07T18:12:54-08:00 overflow-y 'scroll' -> 'auto' - - - - - 571d7657 by Alec Theriault at 2018-11-08T19:44:12-08:00 Clicking on "Contents" navigates to top of page - - - - - 8065a012 by Alec Theriault at 2018-11-08T19:44:17-08:00 Space out functions more Also, functions and data decls now have the same space before and after them. - - - - - cc650ede by Alec Theriault at 2018-11-09T08:13:35-08:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 65f8c17f by Alec Theriault at 2018-11-10T14:04:06-08:00 Update changelog - - - - - 20473847 by Alec Theriault at 2018-11-10T14:21:40-08:00 Replace oplus/ominus expander/collapser icons with triangles - - - - - 16592957 by Alec Theriault at 2018-11-10T14:35:10-08:00 Merge pull request haskell/haddock#949 from haskell/wip/new-ocean Introduce NewOcean theme. - - - - - 357cefe1 by Alec Theriault at 2018-11-10T16:02:13-08:00 Merge branch 'ghc-8.6' into ghc-head - - - - - de612267 by Alec Theriault at 2018-11-11T20:01:21-08:00 Rename 'NewOcean' theme to 'Linuwial' - - - - - 954b5baa by Alec Theriault at 2018-11-12T08:33:18-08:00 Add blockquote styling Matches b71da1feabf33efbbc517ac376bb690b5a604c2f from hackage-server. Fixes haskell/haddock#967. - - - - - d32c0b0b by Fangyi Zhou at 2018-11-12T10:24:13-08:00 Fix some broken links (#15733) Summary: For links in subpackages as well. https://phabricator.haskell.org/D5257 Test Plan: Manually verify links Reviewers: mpickering, bgamari, osa1 Reviewed By: osa1 GHC Trac Issues: haskell/haddock#15733 Differential Revision: https://phabricator.haskell.org/D5262 - - - - - 41098b1f by Alp Mestanogullari at 2018-11-15T22:40:09+01:00 Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change It got introduced in ghc/ghc at ae2c9b40f5b6bf272251d1f4107c60003f541b62. - - - - - c5c1c7e0 by Alec Theriault at 2018-11-15T13:48:13-08:00 Merge pull request haskell/haddock#970 from alpmestan/alp/fix-promotionflag Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change - - - - - 6473d3a4 by Shayan-Najd at 2018-11-23T01:38:49+01:00 [TTG: Handling Source Locations] Foundation and Pat Trac Issues haskell/haddock#15495 This patch removes the ping-pong style from HsPat (only, for now), using the plan laid out at https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/HandlingSourceLocations (solution A). - the class `HasSrcSpan`, and its functions (e.g., `cL` and `dL`), are introduced - some instances of `HasSrcSpan` are introduced - some constructors `L` are replaced with `cL` - some patterns `L` are replaced with `dL->L` view pattern - some type annotation are necessarily updated (e.g., `Pat p` --> `Pat (GhcPass p)`) - - - - - 7a088dfe by Alec Theriault at 2018-11-26T11:11:28-08:00 More uniform handling of `forall`'s in HTML/LaTeX * don't forget to print explicit `forall`'s when there are arg docs * when printing an explicit `forall`, print all tyvars Fixes haskell/haddock#973 - - - - - d735e570 by Alec Theriault at 2018-12-12T08:42:09-08:00 Fix warnings, accept output * remove redundant imports (only brought to light due to recent work for improving redundant import detection) * fix a bug that was casuing exports to appear in reverse order * fix something in haddock-library that prevented compilation on old GHC's - - - - - a3852f8a by Zejun Wu at 2018-12-14T09:37:47-05:00 Output better debug infromation on internal error in extractDecl This will make investigation of haskell/haddock#979 easier - - - - - 2eccb5b9 by Alec Theriault at 2018-12-17T09:25:10-05:00 Refactor names + unused functions (#982) This commit should not introduce any change in functionality! * consistently use `getOccString` to convert `Name`s to strings * compare names directly when possible (instead of comparing strings) * get rid of unused utility functions - - - - - e82e4df8 by Alec Theriault at 2018-12-20T16:16:30-05:00 Load plugins when compiling each module (#983) * WIP: Load (typechecker) plugins from language pragmas * Revert "Load plugins when starting a GHC session (#905)" This reverts commit 72d82e52f2a6225686d9668790ac33c1d1743193. * Simplify plugin initialization code - - - - - 96e86f38 by Alec Theriault at 2018-12-23T10:23:20-05:00 Properly synify and render promoted type variables (#985) * Synify and render properly promoted type variables Fixes haskell/haddock#923. * Accept output - - - - - 23343345 by Alec Theriault at 2018-12-27T16:39:38-05:00 Remove `haddock-test`'s dep. on `syb` (#987) The functionality is easily inlined into one short function: `gmapEverywhere`. This doesn't warrant pulling in another package. - - - - - d0734f21 by Alec Theriault at 2018-12-27T16:39:52-05:00 Address deprecation warnings in `haddock-test` (#988) Fixes haskell/haddock#885. - - - - - 4d9f144e by mynguyen at 2018-12-30T23:42:26-05:00 Visible kind application haddock update - - - - - ffe0e9ed by Alec Theriault at 2019-01-07T13:55:22-08:00 Print kinded tyvars in constructors for Hoogle (#993) Fixes haskell/haddock#992 - - - - - 2e18b55d by Alec Theriault at 2019-01-10T16:42:45-08:00 Accept new output `GHC.Maybe` -> `Data.Maybe` (#996) Since 53874834b779ad0dfbcde6650069c37926da1b79 in GHC, "GHC.Maybe" is marked as `not-home`. That changes around some test output. - - - - - 055da666 by Gabor Greif at 2019-01-22T14:41:51+01:00 Lone typofix - - - - - 01bb71c9 by Alec Theriault at 2019-01-23T11:46:46-08:00 Keep forall on H98 existential data constructors (#1003) The information about whether or not there is a source-level `forall` is already available on a `ConDecl` (as `con_forall`), so we should use it instead of always assuming `False`! Fixes haskell/haddock#1002. - - - - - f9b9bc0e by Ryan Scott at 2019-01-27T09:28:12-08:00 Fix haskell/haddock#1004 with a pinch of dropForAlls - - - - - 5cfcdd0a by Alec Theriault at 2019-01-28T16:49:57-08:00 Loosen 'QuickCheck' and 'hspec' bounds It looks like the new versions don't cause any breakage and loosening the bounds helps deps fit in one stack resolver. - - - - - 3545d3dd by Alec Theriault at 2019-01-31T01:37:25-08:00 Use `.hie` files for the Hyperlinker backend (#977) # Summary This is a large architectural change to the Hyperlinker. * extract link (and now also type) information from `.hie` instead of doing ad-hoc SYB traversals of the `RenamedSource`. Also adds a superb type-on-hover feature (#715). * re-engineer the lexer to avoid needless string conversions. By going directly through GHC's `P` monad and taking bytestring slices, we avoid a ton of allocation and have better handling of position pragmas and CPP. In terms of performance, the Haddock side of things has gotten _much_ more efficient. Unfortunately, much of this is cancelled out by the increased GHC workload for generating `.hie` files. For the full set of boot libs (including `ghc`-the-library) * the sum of total time went down by 9-10% overall * the sum of total allocations went down by 6-7% # Motivation Haddock is moving towards working entirely over `.hi` and `.hie` files. This change means we no longer need the `RenamedSource` from `TypecheckedModule` (something which is _not_ in `.hi` files). # Details Along the way a bunch of things were fixed: * Cross package (and other) links are now more reliable (#496) * The lexer tries to recover from errors on every line (instead of at CPP boundaries) * `LINE`/`COLUMN` pragmas are taken into account * filter out zero length tokens before rendering * avoid recomputing the `ModuleName`-based `SrcMap` * remove the last use of `Documentation.Haddock.Utf8` (see haskell/haddock#998) * restructure temporary folder logic for `.hi`/`.hie` model - - - - - 2ded3359 by Herbert Valerio Riedel at 2019-02-02T12:06:12+01:00 Update/modernise haddock-library.cabal file - - - - - 62b93451 by Herbert Valerio Riedel at 2019-02-02T12:19:31+01:00 Tentatively declare support for unreleased base-4.13/ghc-8.8 - - - - - 6041e767 by Herbert Valerio Riedel at 2019-02-02T16:04:32+01:00 Normalise LICENSE text w/ cabal's BSD2 template Also, correct the `.cabal` files to advertise `BSD2` instead of the incorrect `BSD3` license. - - - - - 0b459d7f by Alec Theriault at 2019-02-02T18:06:12-08:00 CI: fetch GHC from validate artifact Should help make CI be less broken - - - - - 6b5c07cf by Alec Theriault at 2019-02-02T18:06:12-08:00 Fix some Hyperlinker test suite fallout * Amend `ParserSpec` to match new Hyperlinker API - pass in compiler info - strip out null tokens * Make `hypsrc-test` pass reliably - strip out `local-*` ids - strip out `line-*` ids from the `ClangCppBug` test - re-accept output - - - - - ded34791 by Nathan Collins at 2019-02-02T18:31:23-08:00 Update README instructions for Stack No need to `stack install` Haddock to test it. Indeed, `stack install` changes the `haddock` on user's `PATH` if `~/.local/bin` is on user's `PATH` which may not be desirable when hacking on Haddock. - - - - - 723298c9 by Alec Theriault at 2019-02-03T09:11:05-08:00 Remove `Documentation.Haddock.Utf8` The circumstances under which this module appeared are completely gone. The Hyperlinker backend no longer needs this module (it uses the more efficient `Encoding` module from `ghc`). Why no deprecation? Because this module really shouldn't exist! - It isn't used in `haddock-library`/`haddock-api` anymore - It was copy pasted directly from `utf8-string` - Folks seeking a boot-lib only solution can use `ghc`'s `Encoding` - - - - - 51050006 by Alec Theriault at 2019-02-03T22:58:58-08:00 Miscellaneous improvements to `Convert` (#1020) Now that Haddock is moving towards working entirely over `.hi` and `.hie` files, all declarations and types are going to be synthesized via the `Convert` module. In preparation for this change, here are a bunch of fixes to this module: * Add kind annotations to type variables in `forall`'s whose kind is not `Type`, unless the kind can be inferred from some later use of the variable. See `implicitForAll` and `noKindTyVars` in particular if you wish to dive into this. * Properly detect `HsQualTy` in `synifyType`. This is done by following suit with what GHC's `toIfaceTypeX` does and checking the first argument of `FunTy{} :: Type` to see if it classified as a given/wanted in the typechecker (see `isPredTy`). * Beef up the logic around figuring out when an explicit `forall` is needed. This includes: observing if any of the type variables will need kind signatures, if the inferred type variable order _without_ a forall will still match the one GHC claims, and some other small things. * Add some (not yet used) functionality for default levity polymorphic type signatures. This functionality similar to `fprint-explicit-runtime-reps`. Couple other smaller fixes only worth mentioning: * Show the family result signature only when it isn't `Type` * Fix rendering of implicit parameters in the LaTeX and Hoogle backends * Better handling of the return kind of polykinded H98 data declarations * Class decls produced by `tyThingToLHsDecl` now contain associated type defaults and default method signatures when appropriate * Filter out more `forall`'s in pattern synonyms - - - - - 841980c4 by Oleg Grenrus at 2019-02-04T08:44:25-08:00 Make a fixture of weird parsing of lists (#997) The second example is interesting. If there's a list directly after the header, and that list has deeper structure, the parser is confused: It finds two lists: - One with the first nested element, - everything after it I'm not trying to fix this, as I'm not even sure this is a bug, and not a feature. - - - - - 7315c0c8 by Ryan Scott at 2019-02-04T12:17:56-08:00 Fix haskell/haddock#1015 with dataConUserTyVars (#1022) The central trick in this patch is to use `dataConUserTyVars` instead of `univ_tvs ++ ex_tvs`, which displays the foralls in a GADT constructor in a way that's more faithful to how the user originally wrote it. Fixes haskell/haddock#1015. - - - - - ee0b49a3 by Ryan Scott at 2019-02-04T15:25:17-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. - - - - - 1c850dc8 by Alan Zimmerman at 2019-02-05T21:54:18+02:00 Matching changes in GHC for haskell/haddock#16236 - - - - - ab03c38e by Simon Marlow at 2019-02-06T08:07:33+00:00 Merge pull request haskell/haddock#1014 from hvr/pr/bsd2-normalise Normalise LICENSE text w/ cabal's BSD2 template - - - - - 5a92ccae by Alec Theriault at 2019-02-10T06:21:55-05:00 Merge remote-tracking branch 'gitlab/wip/T16236-2' into ghc-head - - - - - c0485a1d by Alec Theriault at 2019-02-10T03:32:52-08:00 Removes `haddock-test`s dependency on `xml`/`xhtml` (#1027) This means that `html-test`, `latex-test`, `hoogle-test`, and `hypsrc-test` now only depend on GHC boot libs. So we should now be able to build and run these as part of GHC's testsuite. \o/ The reference output has changed very slightly, in three ways: * we don't convert quotes back into `&quot;` as the `xml` lib did * we don't add extra `&nbsp;` as the `xml` lib did * we now remove the entire footer `div` (instead of just emptying it) - - - - - 65a448e3 by Alec Theriault at 2019-02-11T12:27:41-05:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - 360ca937 by Alec Theriault at 2019-02-13T11:36:11-05:00 Clean up logic for guessing `-B` and `--lib` (#1026) Haddock built with the `in-ghc-tree` flag tries harder to find the GHC lib folder and its own resources. This should make it possible to use `in-ghc-tree`-built Haddock without having to specify the `-B` and `--lib` options (just how you can use in-tree GHC without always specifying the `-B` option). The logic to do this relies on `getExecutablePath`, so we only get this auto-detection on platforms where this function works. - - - - - d583e364 by Alec Theriault at 2019-02-16T10:41:22-05:00 Fix tests broken by GHC Changes in 19626218566ea709b5f6f287d3c296b0c4021de2 affected some of the hyperlinker output. Accepted the new output (hovering over a `..` now shows you what that wildcard binds). Also fixed some stray deprecation warnings. - - - - - da0c42cc by Vladislav Zavialov at 2019-02-17T11:39:19+03:00 Parser changes to match !380 - - - - - ab96bed7 by Ryan Scott at 2019-02-18T04:44:08-05:00 Bump ghc version to 8.9 - - - - - 44b7c714 by Alec Theriault at 2019-02-22T05:49:43-08:00 Match GHC changes for T16185 `FunTy` now has an `AnonArgFlag` that indicates whether the arrow is a `t1 => t2` or `t1 -> t2`. This commit shouldn't change any functionality in Haddock. - - - - - 2ee653b1 by Alec Theriault at 2019-02-24T18:53:33-08:00 Update .travis.yml Points to the new GHC CI artifact. - - - - - 90939d71 by Alec Theriault at 2019-02-25T00:42:41-08:00 Support value/type namespaces on identifier links Identifier links can be prefixed with a 'v' or 't' to indicate the value or type namespace of the desired identifier. For example: -- | Some link to a value: v'Data.Functor.Identity' -- -- Some link to a type: t'Data.Functor.Identity' The default is still the type (with a warning about the ambiguity) - - - - - d6ed496c by Alec Theriault at 2019-02-25T00:42:46-08:00 Better identifier parsing * '(<|>)' and '`elem`' now get parsed and rendered properly as links * 'DbModule'/'DbUnitId' now properly get split apart into two links * tuple names now get parsed properly * some more small niceties... The identifier parsing code is more precise and more efficient (although to be fair: it is also longer and in its own module). On the rendering side, we need to pipe through information about backticks/parens/neither all the way through from renaming to the backends. In terms of impact: a total of 35 modules in the entirety of the bootlib + ghc lib docs change. The only "regression" is things like '\0'. These should be changed to @\\0@ (the path by which this previously worked seems accidental). - - - - - 3c3b404c by Alec Theriault at 2019-02-25T22:12:11-08:00 Fix standalone deriving docs Docs on standalone deriving decls for classes with associated types should be associated with the class instance, not the associated type instance. Fixes haskell/haddock#1033 - - - - - d51ef69e by Alec Theriault at 2019-02-26T19:14:59-08:00 Fix bogus identifier defaulting This avoids a situation in which an identifier would get defaulted to a completely different identifier. Prior to this commit, the 'Bug1035' test case would hyperlink 'Foo' into 'Bar'! Fixes haskell/haddock#1035. - - - - - 88cbbdc7 by Ryan Scott at 2019-02-27T10:14:03-05:00 Visible dependent quantification (#16326) changes - - - - - 0dcf6cee by Xia Li-yao at 2019-02-27T21:53:27-05:00 Menu item controlling which instances are expanded/collapsed (#1007) Adds a menu item (like "Quick Jump") for options related to displaying instances. This provides functionality for: * expanding/collapsing all instances on the currently opened page * controlling whether instances are expanded/collapsed by default * controlling whether the state of instances should be "remembered" This new functionality is implemented in Typescript in `details-helper`. The built-in-themes style switcher also got a revamp so that all three of QuickJump, the style switcher, and instance preferences now have the same style and implementation structure. See also: https://mail.haskell.org/pipermail/haskell-cafe/2019-January/130495.html Fixes haskell/haddock#698. Co-authored-by: Lysxia <lysxia at gmail.com> Co-authored-by: Nathan Collins <conathan at galois.com> - - - - - 3828c0fb by Alec Theriault at 2019-02-28T12:42:49-05:00 `--show-interface` should output to stdout. (#1040) Fixes haskell/haddock#864. - - - - - a50f4cda by gbaz at 2019-03-01T07:43:16-08:00 Increase contrast of Linuwal theme (#1037) This is to address the concern that, on less nice and older screens, some of the shades of grey blend in too easily with the white background. * darken the font slightly * darken slightly the grey behind type signatures and such * add a border and round the corners on code blocks * knock the font down by one point - - - - - ab4d41de by Alec Theriault at 2019-03-03T09:23:26-08:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 12f509eb by Ben Gamari at 2019-03-04T22:13:20-05:00 Remove reference to Opt_SplitObjs flag Split-objects has been removed. - - - - - 5b3e4c9a by Ryan Scott at 2019-03-06T19:16:24-05:00 Update html-test output to reflect haskell/haddock#16391 changes - - - - - fc228af1 by Alec Theriault at 2019-03-09T08:29:23-08:00 Match changes for "Stop inferring over-polymorphic kinds" The `hsq_ext` field of `HsQTvs` is now just the implicit variables (instead of also including information about which of these variables are dependent). This commit shouldn't change any functionality in Haddock. - - - - - 6ac109eb by Alec Theriault at 2019-03-09T11:22:55-08:00 Add .hi, .dyn_hi, etc files to .gitignore Fixes haskell/haddock#1030. - - - - - b55f0c05 by Alec Theriault at 2019-03-09T11:22:55-08:00 Better support for default methods in classes * default methods now get rendered differently * default associated types get rendered * fix a forgotten `s/TypeSig/ClassOpSig/` refactor in LaTeX backend * LaTeX backend now renders default method signatures NB: there is still no way to document default class members and the NB: LaTeX backend still crashes on associated types - - - - - 10aea0cf by Alec Theriault at 2019-03-09T11:22:55-08:00 Avoid multi-line `emph` in LaTeX backend `markupWarning` often processes inputs which span across paragraphs. Unfortunately, LaTeX's `emph` is not made to handle this (and will crash). Fixes haskell/haddock#936. - - - - - d22dc2c9 by Alec Theriault at 2019-03-09T11:22:55-08:00 Many LaTeX backend fixes After this commit, we can run with `--latex` on all boot libraries without crashing (although the generated LaTeX still fails to compile in a handful of larger packages like `ghc` and `base`). * Add newlines after all block elements in LaTeX. This is important to prevent the final output from being more an more indented. See the `latext-test/src/Example` test case for a sample of this. * Support associated types in class declarations (but not yet defaults) * Several small issues for producing compiling LaTeX; - avoid empy `\haddockbeginargs` lists (ex: `type family Any`) - properly escape identifiers depending on context (ex: `Int#`) - add `vbox` around `itemize`/`enumerate` (so they can be in tables) * Several spacing fixes: - limit the width of `Pretty`-arranged monospaced code - cut out extra space characters in export lists - only escape spaces if there are _multiple_ spaces - allow type signatures to be multiline (even without docs) * Remove uninteresting and repetitive `main.tex`/`haddock.sty` files from `latex-test` test reference output. Fixes haskell/haddock#935, haskell/haddock#929 (LaTeX docs for `text` build & compile) Fixes haskell/haddock#727, haskell/haddock#930 (I think both are really about type families...) - - - - - 0e6cee00 by Alec Theriault at 2019-03-29T12:11:56-07:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - ce05434d by Alan Zimmerman at 2019-03-29T12:12:11-07:00 Matching changes in GHC for haskell/haddock#16236 (cherry picked from commit 3ee6526d4ae7bf4deb7cd1caf24b3d7355573576) - - - - - d85766b2 by Ben Gamari at 2019-03-29T12:14:04-07:00 Bump GHC to 8.8 - - - - - 5a82cbaf by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Redo ParseModuleHeader - - - - - b9033348 by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - bb55c8f4 by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove outdated `.ghci` files and `scripts` The `.ghci` files are actively annoying when trying to `cabal v2-repl`. As for the `scripts`, the distribution workflow is completely different. - - - - - 5ee244dc by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove obsolete arcanist files + STYLE Now that GHC is hosted on Gitlab, the arcanist files don't make sense anymore. The STYLE file contains nothing more than a dead link too. - - - - - d07c1928 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Redo ParseModuleHeader - - - - - 492762d2 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - af2ac773 by Ryan Scott at 2019-05-14T17:22:13-04:00 Changes for haskell/haddock#16110/#16356 - - - - - 6820ed0d by Alec Theriault at 2019-05-17T08:51:27-07:00 Unbreak haskell/haddock#1004 test case `fail` is no longer part of `Monad`. - - - - - 6bf7be98 by Alec Theriault at 2019-05-17T08:51:27-07:00 Fix haskell/haddock#1063 with better parenthesization logic for contexts The only other change in html/hoogle/hyperlinker output for the boot libraries that this caused is a fix to some Hoogle output for implicit params. ``` $ diff -r _build/docs/ old_docs diff -r _build/docs/html/libraries/base/base.txt old_docs/html/libraries/base/base.txt 13296c13296 < assertError :: (?callStack :: CallStack) => Bool -> a -> a --- > assertError :: ?callStack :: CallStack => Bool -> a -> a ``` - - - - - b5716b61 by Ryan Scott at 2019-05-22T17:24:32-04:00 Match changes with haskell/haddock#14332 - - - - - c115abf6 by Alec Theriault at 2019-05-26T16:01:58-04:00 Remove Haddock's dependency on `Cabal` At this point, Haddock depended on Cabal-the-library solely for a verbosity parser (which misleadingly accepts all sorts of verbosity options that Haddock never uses). Now, the only dependency on Cabal is for `haddock-test` (which uses Cabal to locate the Haddock interface files of a couple boot libraries). - - - - - e5b2d4a3 by Alec Theriault at 2019-05-26T16:16:25-04:00 Regression test: promoted lists in associated types When possible, associated types with promoted lists should use the promoted list literal syntax (instead of repeated applications of ': and '[]). This was fixed in 2122de5473fd5b434af690ff9ccb1a2e58491f8c. Closes haskell/haddock#466, - - - - - cc5ad5d3 by Alec Theriault at 2019-05-26T17:55:54-04:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 4b3301a6 by Alec Theriault at 2019-05-26T17:57:52-04:00 Release haddock-2.23, haddock-library-1.8.0 Tentatively adjust bounds and changelogs for the release to be bundled with GHC 8.8.1. - - - - - 69c7cfce by Matthew Pickering at 2019-05-30T10:54:27+01:00 Update hyperlinker tests for new types in .hie files - - - - - 29b7e738 by Zubin Duggal at 2019-05-30T10:57:51+01:00 update for new way to store hiefile headers - - - - - aeca5d5f by Zubin Duggal at 2019-06-04T18:57:42-04:00 update for new way to store hiefile headers - - - - - ba2ca518 by Ben Gamari at 2019-06-07T23:11:14+00:00 Update test output for introduction of Safe-Inferred - - - - - 3a975a6c by Ryan Scott at 2019-07-03T12:06:27-04:00 Changes for haskell/haddock#15247 - - - - - 0df46555 by Zubin Duggal at 2019-07-22T10:52:50+01:00 Fix haddockHypsrcTest - - - - - 2688686b by Sylvain Henry at 2019-09-12T23:19:39+02:00 Fix for GHC module renaming - - - - - 9ec0f3fc by Alec Theriault at 2019-09-20T03:21:00-04:00 Fix Travis CI, loosen .cabal bounds (#1089) Tentatively for the 2.23 release: * updated Travis CI to work again * tweaked bounds in the `.cabal` files * adjusted `extra-source-files` to properly identify test files - - - - - ca559beb by Matthías Páll Gissurarson at 2019-09-28T12:14:40-04:00 Small change in to facilitate extended typed-holes (#1090) This change has no functional effect on haddock itself, it just changes one pattern to use `_ (` rather than `_(`, so that we may use `_(` as a token for extended typed-holes later. - - - - - 02e28976 by Vladislav Zavialov at 2019-09-28T12:17:45-04:00 Remove spaces around @-patterns (#1093) This is needed to compile `haddock` when [GHC Proposal haskell/haddock#229](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0229-whitespace-bang-patterns.rst) is implemented. - - - - - 83cbbf55 by Alexis King at 2019-09-30T21:12:42-04:00 Fix the ignore-exports option (#1082) The `ignore-exports` option has been broken since haskell/haddock#688, as mentioned in https://github.com/haskell/haddock/pull/766#issue-172505043. This PR fixes it. - - - - - e127e0ab by Ben Gamari at 2019-10-06T15:12:06-04:00 Fix a few haddock issues - - - - - 3a0f5c89 by Zubin Duggal at 2019-10-07T17:56:13-04:00 Fix crash when there are no srcspans in the file due to CPP - - - - - 339c5ff8 by Alec Theriault at 2019-10-07T17:56:13-04:00 Prefer un-hyperlinked sources to no sources It is possible to fail to extract an HIE ast. This is however not a reason to produce _no_ output - we should still make a colorized HTML page. - - - - - d47ef478 by Alec Theriault at 2019-10-07T17:56:13-04:00 Add a regression test for haskell/haddock#1091 Previously, this input would crash Haddock. - - - - - ed7c8b0f by Alec Theriault at 2019-10-07T20:56:48-04:00 Add Hyperlinker test cases for TH-related stuff Hopefully this will guard against regressions around quasiquotes, TH quotes, and TH splices. - - - - - d00436ab by Andreas Klebinger at 2019-10-21T15:53:03+02:00 Refactor for withTiming changes. - - - - - 4230e712 by Ben Gamari at 2019-10-22T09:36:37-04:00 Merge pull request haskell/haddock#1101 from AndreasPK/withTimingRefactor Refactor for withTiming changes. - - - - - d155c5f4 by Ryan Scott at 2019-10-23T10:37:17-04:00 Reify oversaturated data family instances correctly (#1103) This fixes haskell/haddock#1103 by adapting the corresponding patch for GHC (see https://gitlab.haskell.org/ghc/ghc/issues/17296 and https://gitlab.haskell.org/ghc/ghc/merge_requests/1877). - - - - - 331a5adf by Sebastian Graf at 2019-10-25T17:14:40+02:00 Refactor for OutputableBndrId changes - - - - - 48a490e0 by Ben Gamari at 2019-10-27T10:16:16-04:00 Merge pull request haskell/haddock#1105 from sgraf812/wip/flexible-outputable Refactor for OutputableBndrId changes - - - - - f62a7dfc by Sebastian Graf at 2019-11-01T11:54:16+00:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - d9b242ed by Ryan Scott at 2019-11-03T13:20:03-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. (cherry picked from commit cfd682c5fd03b099a3d78c44f9279faf56a0ac70) - - - - - dfd42406 by Sebastian Graf at 2019-11-04T07:02:14-05:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - 0b15be7c by Ben Gamari at 2019-11-09T13:21:33-05:00 Import isRuntimeRepVar from Type rather than TyCoRep isRuntimeRepVar is not longer exported from TyCoRep due to ghc#17441. - - - - - 091f7283 by Ben Gamari at 2019-11-10T12:47:06-05:00 Bump to GHC 8.10 - - - - - e88c71f2 by Ben Gamari at 2019-11-14T00:22:24-05:00 Merge pull request haskell/haddock#1110 from haskell/wip/T17441 Import isRuntimeRepVar from Type rather than TyCoRep - - - - - 4e0bbc17 by Ben Gamari at 2019-11-14T00:22:45-05:00 Version bumps for GHC 8.11 - - - - - 0e85ceb4 by Ben Gamari at 2019-11-15T11:59:45-05:00 Bump to GHC 8.10 - - - - - 00d6d68b by Ben Gamari at 2019-11-16T18:35:58-05:00 Bump ghc version to 8.11 - - - - - dde1fc3f by Ben Gamari at 2019-11-16T20:40:37-05:00 Drop support for base 4.13 - - - - - f52e331d by Vladislav Zavialov at 2019-11-24T13:02:28+03:00 Update Hyperlinker.Parser.classify to use ITdollar - - - - - 1ad96198 by Vladislav Zavialov at 2019-11-28T16:12:33+03:00 Remove HasSrcSpan (#17494) - - - - - 651afd70 by Herbert Valerio Riedel at 2019-12-08T12:08:16+01:00 Document error-prone conditional definition of instances This can easily trip up people if one isn't aware of it. Usually it's better to avoid this kind of conditionality especially for typeclasses for which there's an compat-package as conditional instances like these tend to fragment the ecosystem into those packages that go the extra mile to provide backward compat via those compat-packages and those that fail to do so. - - - - - b521af56 by Herbert Valerio Riedel at 2019-12-08T12:09:54+01:00 Fix build-failure regression for base < 4.7 The `$>` operator definition is available only since base-4.7 which unfortunately wasn't caught before release to Hackage (but has been fixed up by a metadata-revision) This commit introduces a `CompatPrelude` module which allows to reduce the amount of CPP by ousting it to a central location, i.e. the new `CompatPrelude` module. This pattern also tends to reduce the tricks needed to silence unused import warnings. Addresses haskell/haddock#1119 - - - - - 556c375d by Sylvain Henry at 2020-01-02T19:01:55+01:00 Fix after Iface modules renaming - - - - - bd6c53e5 by Sylvain Henry at 2020-01-07T00:48:48+01:00 hsyl20-modules-renamer - - - - - fb23713b by Ryan Scott at 2020-01-08T07:41:13-05:00 Changes for GHC#17608 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2372 - - - - - 4a4dd382 by Ryan Scott at 2020-01-25T08:08:26-05:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - e782a44d by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename PackageConfig into UnitInfo - - - - - ba3c9f05 by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename lookupPackage - - - - - ab37f9b3 by Ben Gamari at 2020-01-29T13:00:44-05:00 Merge pull request haskell/haddock#1125 from haskell/wip/T17566-take-two Changes for GHC#17566 - - - - - 3ebd5ae0 by Ryan Scott at 2020-01-31T05:56:50-05:00 Merge branch 'wip-hsyl20-package-refactor' into ghc-head - - - - - 602a747e by Richard Eisenberg at 2020-02-04T09:05:43+00:00 Echo GHC's removal of PlaceHolder module This goes with GHC's !2083. - - - - - ccfe5679 by Sylvain Henry at 2020-02-10T10:13:56+01:00 Module hierarchy: runtime (cf haskell/haddock#13009) - - - - - 554914ce by Cale Gibbard at 2020-02-10T16:10:39-05:00 Fix build of haddock in stage1 We have to use the correct version of the GHC API, but the version of the compiler itself doesn't matter. - - - - - 5b6fa2a7 by John Ericson at 2020-02-10T16:18:07-05:00 Noramlize `tested-with` fields in cabal files - - - - - e6eb3ebe by Vladislav Zavialov at 2020-02-16T13:25:26+03:00 No MonadFail/Alternative for P - - - - - 90e181f7 by Ben Gamari at 2020-02-18T14:13:47-05:00 Merge pull request haskell/haddock#1129 from obsidiansystems/wip/fix-stage1-build Fix build of haddock in stage1 - - - - - 93b64636 by Sylvain Henry at 2020-02-19T11:20:27+01:00 Modules: Driver (#13009) - - - - - da4f6c7b by Vladislav Zavialov at 2020-02-22T15:33:02+03:00 Use RealSrcSpan in InstMap - - - - - 479b1b50 by Ben Gamari at 2020-02-23T10:28:13-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 55ecacf0 by Sylvain Henry at 2020-02-25T15:18:27+01:00 Modules: Core (#13009) - - - - - 60867b3b by Vladislav Zavialov at 2020-02-28T15:53:52+03:00 Ignore the BufLoc/BufSpan added in GHC's !2516 - - - - - 1e5506d3 by Sylvain Henry at 2020-03-02T12:32:43+01:00 Modules: Core (#13009) - - - - - 6fb53177 by Richard Eisenberg at 2020-03-09T14:49:40+00:00 Changes in GHC's !1913. - - - - - 30b792ea by Ben Gamari at 2020-03-16T12:45:02-04:00 Merge pull request haskell/haddock#1130 from hsyl20/wip/hsyl20-modules-core2 Modules: Core (#13009) - - - - - cd761ffa by Sylvain Henry at 2020-03-18T15:24:00+01:00 Modules: Types - - - - - b6646486 by Ben Gamari at 2020-03-18T14:42:43-04:00 Merge pull request haskell/haddock#1133 from hsyl20/wip/hsyl20/modules/types Modules: Types - - - - - 9325d734 by Kleidukos at 2020-03-19T12:38:31-04:00 Replace the 'caption' class so that the collapsible sections are shown - - - - - 5e2bb555 by Kleidukos at 2020-03-19T12:38:31-04:00 Force ghc-8.8.3 - - - - - c6fcd0aa by Kleidukos at 2020-03-19T12:38:31-04:00 Update test fixtures - - - - - 5c849cb1 by Sylvain Henry at 2020-03-20T09:34:39+01:00 Modules: Types - - - - - 7f439155 by Alec Theriault at 2020-03-20T20:17:01-04:00 Merge branch 'ghc-8.8' into ghc-8.10 - - - - - b7904e5c by Alina Banerjee at 2020-03-20T20:24:17-04:00 Update parsing to strip whitespace from table cells (#1074) * Update parsing to strip leading & trailing whitespace from table cells * Update fixture data to disallow whitespaces at both ends in table cells * Add test case for whitespaces stripped from both ends of table cells * Update table reference test data for html tests - - - - - b9d60a59 by Alec Theriault at 2020-03-22T11:46:42-04:00 Clean up warnings * unused imports * imports of `Data.List` without import lists * missing `CompatPrelude` file in `.cabal` - - - - - 0c317dbe by Alec Theriault at 2020-03-22T18:46:54-04:00 Fix NPM security warnings This was done by calling `npm audit fix`. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. - - - - - 6e306242 by Alec Theriault at 2020-03-22T20:10:52-04:00 Tentative 2.24 release Adjusted changelogs and versions in `.cabal` files in preparation for the upcoming release bundled with GHC 8.10. - - - - - 1bfb4645 by Ben Gamari at 2020-03-23T16:40:54-04:00 Merge commit '3c2944c037263b426c4fe60a3424c27b852ea71c' into HEAD More changes from the GHC types module refactoring. - - - - - be8c6f3d by Alec Theriault at 2020-03-26T20:10:53-04:00 Update `.travis.yml` to work with GHC 8.10.1 * Regenerated the Travis file with `haskell-ci` * Beef up `.cabal` files with more `tested-with` information - - - - - b025a9c6 by Alec Theriault at 2020-03-26T20:10:53-04:00 Update README Removed some out of date links/info, added some more useful links. * badge to Hackage * update old trac link * `ghc-head` => `ghc-8.10` * `cabal new-*` is now `cabal v2-*` and it should Just Work * `--test-option='--accept'` is the way to accept testsuite output - - - - - 564d889a by Alec Theriault at 2020-03-27T20:34:33-04:00 Fix crash in `haddock-library` on unicode space Our quickcheck tests for `haddock-library` stumbled across an edge case input that was causing Haddock to crash: it was a unicode space character. The root cause of the crash is that we were implicitly assuming that if a space character was not " \t\f\v\r", it would have to be "\n". We fix this by instead defining horizontal space as: any space character that is not '\n'. Fixes haskell/haddock#1142 - - - - - 2d360ba1 by Alec Theriault at 2020-03-27T21:57:32-04:00 Disallow qualified uses of reserved identifiers This a GHC bug (https://gitlab.haskell.org/ghc/ghc/issues/14109) too, but it is a relatively easy fix in Haddock. Note that the fix must live in `haddock-api` instead of `haddock-library` because we can only really decide if an identifier is a reserved one by asking the GHC lexer. Fixes haskell/haddock#952 - - - - - 47ae22ed by Alec Theriault at 2020-03-28T13:36:25-04:00 Remove unused `Haddock.Utils` functions * removed functions in `Haddock.Utils` that were not used anywhere (or exported from the `haddock-api` package) * moved GHC-specific utils from `Haddock.Utils` to `Haddock.GhcUtils` - - - - - c0291245 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use TTG empty extensions to remove some `error`'s None of these error cases should ever have been reachable, so this is just a matter of leveraging the type system to assert this. * Use the `NoExtCon` and `noExtCon` to handle case matches for no extension constructors, instead of throwing an `error`. * Use the extension field of `HsSpliceTy` to ensure that this variant of `HsType` cannot exist in an `HsType DocNameI`. - - - - - 0aff8dc4 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use `unLoc`/`noLoc` from GHC instead of `unL`/`reL` * `unL` is already defined by GHC as `unLoc` * `reL` is already defined by GHC as `noLoc` (in a safer way too!) * Condense `setOutputDir` and add a about exporting from GHC Fixes haskell/haddock#978 - - - - - bf6f2fb7 by Alec Theriault at 2020-03-28T13:36:25-04:00 Cleanup up GHC flags in `.cabal` files * enable more useful warning flags in `haddock-api`, handle the new warnings generated * remove `-fwarn-tabs` (now we'd use `-Wtabs`, but this has been in `-Wall` for a while now) - - - - - c576fbf1 by Alec Theriault at 2020-03-28T13:36:25-04:00 `haddock-library` document header level Document the fact the header level is going to always be between 1 and 6 inclusive. Along the way, I also optimized the parsing code a bit. - - - - - 71bce0ee by Alec Theriault at 2020-03-28T14:26:27-04:00 Disallow links in section headers This is quite straightforward to implement, since we already had a function `docToHtmlNoAnchors` (which we used to generate the link in the sidebar "Contents"). This breaks test `Bug387`, but that test case has aged badly: we now automatically generate anchors for all headings, so manually adding an anchor in a section makes no sense. Nested anchors are, as pointed out in haskell/haddock#1054, disallowed by the HTML standard. Fixes haskell/haddock#1054 - - - - - b461b0ed by Sylvain Henry at 2020-03-30T10:34:23+02:00 Modules: type checker - - - - - cd8cd1ee by Ben Gamari at 2020-03-31T12:45:02-04:00 Merge pull request haskell/haddock#1152 from hsyl20/wip/hsyl20/modules/tc Module renaming - - - - - 5e8f8ea7 by Felix Yan at 2020-04-01T17:58:06-07:00 Allow QuickCheck 2.14 Builds fine and all tests pass. - - - - - dc6b1633 by Sylvain Henry at 2020-04-05T16:43:44+02:00 Module renaming: amend previous patch - - - - - eee2f4ae by Ryan Scott at 2020-04-05T09:04:43-07:00 Fix haskell/haddock#1050 by filtering out invisible AppTy arguments This makes the `synifyType` case for `AppTy` more intelligent by taking into consideration the visibilities of each `AppTy` argument and filtering out any invisible arguments, as they aren't intended to be displayed in the source code. (See haskell/haddock#1050 for an example of what can happen if you fail to filter these out.) Along the way, I noticed that a special `synifyType` case for `AppTy t1 (CoercionTy {})` could be consolidated with the case below it, so I took the opportunity to tidy this up. - - - - - 23eb99e8 by Ben Gamari at 2020-04-07T11:19:58-04:00 Merge pull request haskell/haddock#1154 from hsyl20/wip/hsyl20/modules/tc Module renaming: amend previous patch - - - - - 072d994d by Ryan Scott at 2020-04-07T19:32:47-04:00 Make NoExtCon fields strict These changes are a part of a fix for [GHC#17992](https://gitlab.haskell.org/ghc/ghc/issues/17992). - - - - - d8ebf6c8 by Ignat Insarov at 2020-04-09T21:15:01-04:00 Recode Doc to Json. (#1159) * Recode Doc to Json. * More descriptive field labels. - - - - - 52df4b4e by Sylvain Henry at 2020-04-10T12:39:18+02:00 Module renaming - - - - - d9ab8ec8 by Cale Gibbard at 2020-04-14T11:43:34-04:00 Add instance of XCollectPat for DocNameI - - - - - 323d221d by Cale Gibbard at 2020-04-14T11:43:34-04:00 Rename XCollectPat -> CollectPass - - - - - 2df80867 by Alec Theriault at 2020-04-15T07:30:51-07:00 Prune docstrings that are never rendered When first creating a Haddock interface, trim `ifaceDocMap` and `ifaceArgMap` to not include docstrings that can never appear in the final output. Besides checking with GHC which names are exported, we also need to keep all the docs attached to instance declarations (it is much tougher to detect when an instance is fully private). This change means: * slightly smaller interface files (7% reduction on boot libs) * slightly less work to do processing docstrings that aren't used * no warnings in Haddock's output about private docstrings (see haskell/haddock#1070) I've tested manually that this does not affect any of the boot library generated docs (the only change in output was some small re-ordering in a handful of instance lists). This should mean no docstrings have been incorrectly dropped. - - - - - f49c90cc by Alec Theriault at 2020-04-15T07:30:51-07:00 Don't warn about missing links in miminal sigs When renaming the Haddock interface, never emit warnings when renaming a minimal signature. Also added some documention around `renameInterface`. Minimal signatures intentionally include references to potentially un-exported methods (see the discussion in haskell/haddock#330), so it is expected that they will not always have a link destination. On the principle that warnings should always be resolvable, this shouldn't produce a warning. See haskell/haddock#1070. - - - - - a9eda64d by Ben Gamari at 2020-04-17T09:27:35-04:00 Merge pull request haskell/haddock#1160 from hsyl20/wip/hsyl20/modules/systools Module renaming - - - - - f40d7879 by Cale Gibbard at 2020-04-20T11:30:38-04:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ttg-con-pat - - - - - a50e7753 by Ben Gamari at 2020-04-20T11:36:10-04:00 Merge pull request haskell/haddock#1165 from obsidiansystems/wip/ttg-con-pat Trees that Grow refactor (GHC !2553) - - - - - 6a24795c by Alec Theriault at 2020-04-21T08:06:45-07:00 Fallback to `hiDecl` when `extractDecl` fails Sometimes, the declaration being exported is a subdecl (for instance, a record accessor getting exported at the top-level). For these cases, Haddock has to find a way to produce some synthetic sensible top-level declaration. This is done with `extractDecl`. As is shown by haskell/haddock#1067, this is sometimes impossible to do just at a syntactic level (for instance when the subdecl is re-exported). In these cases, the only sensible thing to do is to try to reify a declaration based on a GHC `TyThing` via `hiDecl`. - - - - - eee1a8b7 by Sylvain Henry at 2020-04-24T15:46:05+02:00 Module structure - - - - - 50b9259c by Iñaki at 2020-04-25T18:38:11-04:00 Add support for custom section anchors (#1179) This allows to have stable anchors for groups, even if the set of groups in the documentation is altered. The syntax for setting the anchor of a group is -- * Group name #desiredAnchor# Which will produce an html anchor of the form '#g:desiredAnchor' Co-authored-by: Iñaki García Etxebarria <git at inaki.blueleaf.cc> - - - - - 4003c97a by Ben Gamari at 2020-04-26T09:35:15-04:00 Merge pull request haskell/haddock#1166 from hsyl20/wip/hsyl20/modules/utils Module structure - - - - - 5206ab60 by Sylvain Henry at 2020-04-27T16:47:39+02:00 Renamed UnitInfo fields - - - - - c32c333b by Sylvain Henry at 2020-04-27T17:32:58+02:00 UnitId has been renamed into Unit - - - - - 3e87db64 by Sylvain Henry at 2020-04-27T17:36:00+02:00 Fix for GHC.Unit.* modules - - - - - ae3323a7 by Ben Gamari at 2020-04-29T12:36:37-04:00 Merge pull request haskell/haddock#1183 from hsyl20/wip/hsyl20/unitid Refactoring of Unit code - - - - - b105564a by Artem Pelenitsyn at 2020-05-03T08:14:10+01:00 add dependency on exceptions because GHC.Exception was boiled down (ghc haskell/haddock#18075) - - - - - 9857eff3 by Zubin Duggal at 2020-05-04T18:48:25+01:00 Atomic update of NameCache in readHieFile - - - - - 86bbb226 by Sylvain Henry at 2020-05-14T16:36:27+02:00 Fix after Config module renaming - - - - - a4bbdbc2 by Gert-Jan Bottu at 2020-05-15T22:09:44+02:00 Explicit Specificity Support for Haddock - - - - - 46199daf by Ben Gamari at 2020-05-19T09:59:56-04:00 Merge pull request haskell/haddock#1192 from hsyl20/hsyl20/modules-config Fix after Config module renaming - - - - - f9a9d2ba by Gert-Jan Bottu at 2020-05-20T16:48:38-04:00 Explicit Specificity Support for Haddock - - - - - 55c5b7ea by Ben Gamari at 2020-05-21T00:32:02-04:00 Merge commit 'a8d7e66da4dcc3b242103271875261604be42d6e' into ghc-head - - - - - a566557f by Cale Gibbard at 2020-05-21T16:02:06-04:00 isBootSummary now produces a result of type IsBootInterface - - - - - ea52f905 by Zubin Duggal at 2020-05-24T17:55:48+01:00 update for hiefile-typeclass-info - - - - - 49ba7a67 by Willem Van Onsem at 2020-05-25T12:23:01-04:00 Use floor over round to calculate the percentage (#1195) If we compile documentation where only a small fraction is undocumented, it is misleading to see 100% coverage - 99% is more intuitive. Fixes haskell/haddock#1194 - - - - - c025ebf1 by Ben Gamari at 2020-05-29T14:32:42-04:00 Merge pull request haskell/haddock#1185 from obsidiansystems/boot-disambig isBootSummary now produces a result of type IsBootInterface - - - - - 74ab9415 by Ben Gamari at 2020-05-29T20:23:39-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - b40be944 by Ben Gamari at 2020-06-03T17:02:31-04:00 testsuite: Update expected output for simplified subsumption - - - - - 624be71c by Ryan Scott at 2020-06-05T12:43:23-04:00 Changes for GHC#18191 See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3337. - - - - - fbd8f7ce by Sylvain Henry at 2020-06-08T15:31:47+02:00 Fix after unit refactoring - - - - - 743fda4d by Ben Gamari at 2020-06-09T12:09:58-04:00 Merge pull request haskell/haddock#1202 from hsyl20/wip/hsyl20/unitid-ii Fix after unit refactoring - - - - - d07a06a9 by Ryan Scott at 2020-06-13T07:16:55-04:00 Use HsForAllTelescope (GHC#18235) - - - - - 389bb60d by Ben Gamari at 2020-06-13T15:30:52-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - 7a377f5f by Ben Gamari at 2020-06-17T14:53:16-04:00 Merge pull request haskell/haddock#1199 from bgamari/wip/ghc-8.12 haddock: Bounds bumps for GHC 8.12 - - - - - 9fd9e586 by Krzysztof Gogolewski at 2020-06-17T16:09:07-04:00 Adapt Haddock to LinearTypes See ghc/ghc!852. - - - - - 46fe7636 by Ben Gamari at 2020-06-18T14:20:02-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 35a3c9e2 by Zubin Duggal at 2020-06-21T21:19:18+05:30 Use functions exported from HsToCore - - - - - 8abe3928 by Ben Gamari at 2020-06-24T13:53:39-04:00 Merge pull request haskell/haddock#1204 from wz1000/wip/haddock-hstocore Use functions exported from GHC.HsToCore.Docs - - - - - 22f2c937 by Matthías Páll Gissurarson at 2020-06-26T19:07:03+02:00 Adapt Haddock for QualifiedDo - - - - - 3f6208d7 by Vladislav Zavialov at 2020-06-28T14:28:16+03:00 Handle LexicalNegation's ITprefixminus - - - - - 03a19f41 by Sylvain Henry at 2020-07-02T09:37:38+02:00 Rename hsctarget into backend - - - - - ea17ff23 by Andreas Klebinger at 2020-07-02T17:44:18+02:00 Update for UniqFM changes. - - - - - 9872f2f3 by Ben Gamari at 2020-07-09T10:39:19-04:00 Merge pull request haskell/haddock#1209 from AndreasPK/wip/typed_uniqfm Update for UniqFM changes. - - - - - 68f7b668 by Krzysztof Gogolewski at 2020-07-12T18:16:57+02:00 Sync with GHC removing {-# CORE #-} pragma See ghc ticket haskell/haddock#18048 - - - - - eb372681 by Sylvain Henry at 2020-07-20T11:41:30+02:00 Rename hscTarget into backend - - - - - fb7f78bf by Ben Gamari at 2020-07-21T12:15:25-04:00 Merge pull request haskell/haddock#1214 from hsyl20/wip/hsyl20/hadrian/ncg Rename hscTarget into backend - - - - - 1e8f5b56 by Ben Gamari at 2020-07-23T09:11:50-04:00 Merge commit '904dce0cafe0a241dd3ef355775db47fc12f434d' into ghc-head - - - - - d8fd1775 by Zubin Duggal at 2020-07-23T18:46:40+05:30 Update for modular ping pong - - - - - 8416f872 by Ben Gamari at 2020-07-23T09:35:03-04:00 Merge pull request haskell/haddock#1200 from wz1000/wip/wz1000-modular-ping-pong Modular ping pong - - - - - a24a8577 by Ben Gamari at 2020-07-28T15:23:36-04:00 Bump GHC version to 9.0 - - - - - 6a51c9dd by Sylvain Henry at 2020-08-05T18:47:05+02:00 Fix after Outputable refactoring - - - - - c05e1c99 by Ben Gamari at 2020-08-10T14:41:41-04:00 Merge pull request haskell/haddock#1223 from hsyl20/wip/hsyl20/dynflags/exception Fix after Outputable refactoring - - - - - d964f15b by Sylvain Henry at 2020-08-12T11:58:49+02:00 Fix after HomeUnit - - - - - 8e6d5b23 by Ben Gamari at 2020-08-12T14:25:30-04:00 Merge pull request haskell/haddock#1225 from hsyl20/wip/hsyl20/plugins/homeunit Fix after HomeUnit - - - - - 8c7880fe by Sylvain Henry at 2020-08-17T14:13:29+02:00 Remove Ord FastString instance - - - - - 8ea410db by Alex Biehl at 2020-08-19T10:56:32+02:00 Another round of `npm audit fix` (#1228) This should shut down the warnings on Github. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. Last NPM dependency audit happend in d576b2327e2bc117f912fe0a9d595e9ae62614e0 Co-authored-by: Alex Biehl <alex.biehl at target.com> - - - - - 7af6e2a8 by Ben Gamari at 2020-08-31T13:59:34-04:00 Merge pull request haskell/haddock#1226 from hsyl20/wip/hsyl20/fs_ord Remove Ord FastString instance - - - - - ffbc8702 by Alan Zimmerman at 2020-09-07T21:47:41+01:00 Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - a93f1268 by Alan Zimmerman at 2020-09-07T23:11:38+01:00 Merge pull request haskell/haddock#1232 from haskell/wip/T18639-remove-generated-pragma, Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - 1f605d50 by Ben Gamari at 2020-09-14T18:30:01-04:00 Bump GHC version to 9.1 - - - - - 6599df62 by Vladislav Zavialov at 2020-09-18T14:05:15+03:00 Bump base upper bound to 4.16 - - - - - a01b3c43 by Ben Gamari at 2020-09-22T15:41:48-04:00 Update hypsrc-test for QuickLook This appears to be a spurious change. - - - - - e9cc6cac by Vladislav Zavialov at 2020-09-26T21:00:12+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 30e3ca7c by Sylvain Henry at 2020-09-29T11:18:32-04:00 Update for parser (#1234) - - - - - b172f3e3 by Vladislav Zavialov at 2020-09-30T01:01:30+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 0b9c08d3 by Sylvain Henry at 2020-09-30T11:02:33+02:00 Adapt to GHC parser changes - - - - - b9540b7a by Sylvain Henry at 2020-10-12T09:13:38-04:00 Don't pass the HomeUnitId (#1239) - - - - - 34762e80 by HaskellMouse at 2020-10-13T12:58:04+03:00 Changed tests due to unification of `Nat` and `Natural` in the follwing merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3583 - - - - - 256f86b6 by Vladislav Zavialov at 2020-10-15T10:48:03+03:00 Add whitespace in: map ($ v) - - - - - 4a3f711b by Alan Zimmerman at 2020-10-19T08:57:27+01:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled - - - - - 072cdd21 by Alan Zimmerman at 2020-10-21T14:48:28-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 9e09a445 by Alan Zimmerman at 2020-10-21T23:53:34-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 636d7de3 by Sylvain Henry at 2020-10-26T14:31:54-04:00 GHC.Driver.Types refactoring (#1242) - - - - - a597f000 by Ryan Scott at 2020-10-29T04:18:05-04:00 Adapt to the removal of Hs{Boxed,Constraint}Tuple See ghc/ghc!4097 and GHC#18723. - - - - - b96660fb by Ryan Scott at 2020-10-30T04:53:05-04:00 Adapt to HsConDecl{H98,GADT}Details split Needed for GHC#18844. - - - - - c287d82c by Ryan Scott at 2020-10-30T19:35:59-04:00 Adapt to HsOuterTyVarBndrs These changes accompany ghc/ghc!4107, which aims to be a fix for haskell/haddock#16762. - - - - - a34c31a1 by Ryan Scott at 2020-11-13T13:38:34-05:00 Adapt to splitPiTysInvisible being renamed to splitInvisPiTys This is a part of !4434, a fix for GHC#18939. - - - - - 66ea459d by Sylvain Henry at 2020-11-16T10:59:30+01:00 Fix after Plugins moved into HscEnv - - - - - 508556d8 by Ben Gamari at 2020-11-18T15:47:40-05:00 Merge pull request haskell/haddock#1253 from hsyl20/wip/hsyl20/plugins/hscenv Fix after Plugins moved into HscEnv - - - - - 620fec1a by Andreas Klebinger at 2020-11-24T20:51:59+01:00 Update for changes in GHC's Pretty - - - - - 01cc13ab by Richard Eisenberg at 2020-11-25T23:18:35-05:00 Avoid GHC#18932. - - - - - 8d29ba21 by Cale Gibbard at 2020-11-25T23:18:35-05:00 Add type arguments to PrefixCon - - - - - 414d5f87 by Sylvain Henry at 2020-11-30T17:06:04+01:00 DynFlags's unit fields moved to HscEnv - - - - - e356668c by Ben Gamari at 2020-11-30T11:11:37-05:00 Merge pull request haskell/haddock#1258 from hsyl20/wip/hsyl20/hscenv/unitstate Unit fields moved from DynFlags to HscEnv - - - - - 7cf552f1 by Ben Gamari at 2020-12-03T10:31:27-05:00 Merge pull request haskell/haddock#1257 from AndreasPK/wip/andreask/opt_dumps Update for changes in GHC's Pretty - - - - - fc0871c3 by Veronika Romashkina at 2020-12-08T16:35:33+01:00 Fix docs links from Darcs to GitHub in intro (#1262) - - - - - 7059e808 by Veronika Romashkina at 2020-12-08T16:36:16+01:00 Use gender neutral word in docs (#1260) - - - - - 1b16e5ee by Maximilian Tagher at 2020-12-08T16:40:03+01:00 Allow scrolling search results (#1235) Closes https://github.com/haskell/haddock/issues/1231 - - - - - 8a118c01 by dependabot[bot] at 2020-12-08T16:40:25+01:00 Bump bl from 1.2.2 to 1.2.3 in /haddock-api/resources/html (#1255) Bumps [bl](https://github.com/rvagg/bl) from 1.2.2 to 1.2.3. - [Release notes](https://github.com/rvagg/bl/releases) - [Commits](https://github.com/rvagg/bl/compare/v1.2.2...v1.2.3) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - c89ff587 by Xia Li-yao at 2020-12-08T16:42:17+01:00 Allow more characters in anchor following module reference (#1220) - - - - - 14af7d64 by Xia Li-yao at 2020-12-08T16:43:05+01:00 Add dangling changes from branches ghc-8.6 and ghc-8.8 (#1243) * Fix multiple typos and inconsistencies in doc/markup.rst Note: I noticed some overlap with haskell/haddock#1112 from @wygulmage and haskell/haddock#1081 from @parsonsmatt after creating these proposed changes - mea culpa for not looking at the open PRs sooner. * Fix haskell/haddock#1113 If no Signatures, no section of index.html * Change the formatting of missing link destinations The current formatting of the missing link destination does not really help user to understand the reasons of the missing link. To address this, I've changed the formatting in two ways: - the missing link symbol name is now fully qualified. This way you immediately know which haskell module cannot be linked. It is then easier to understand why this module does not have documentation (hidden module or broken documentation). - one line per missing link, that's more readable now that symbol name can be longer due to qualification. For example, before haddock was listing missing symbol such as: ``` could not find link destinations for: Word8 Word16 mapMaybe ``` Now it is listed as: ``` could not find link destinations for: - Data.Word.Word8 - Data.Word.Word16 - Data.Maybe.mapMaybe ``` * Add `--ignore-link-symbol` command line argument This argument can be used multiples time. A missing link to a symbol listed by `--ignore-link-symbol` won't trigger "missing link" warning. * Forbid spaces in anchors (#1148) * Improve error messages with context information (#1060) Co-authored-by: Matt Audesse <matt at mattaudesse.com> Co-authored-by: Mike Pilgrem <mpilgrem at users.noreply.github.com> Co-authored-by: Guillaume Bouchard <guillaume.bouchard at tweag.io> Co-authored-by: Pepe Iborra <pepeiborra at gmail.com> - - - - - 89e3af13 by tomjaguarpaw at 2020-12-08T18:00:04+01:00 Enable two warnings (#1245) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - c3320f8d by Willem Van Onsem at 2020-12-08T18:26:55+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 685df308 by Alex Biehl at 2020-12-08T20:06:26+01:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - be3ec3c0 by Alex Biehl at 2020-12-08T20:06:26+01:00 Import intercalate - - - - - 32c33912 by Matthías Páll Gissurarson at 2020-12-08T21:15:30+01:00 Adapt Haddock for QualifiedDo - - - - - 31696088 by Alex Biehl at 2020-12-08T22:06:02+01:00 Fix haddock-library tests - - - - - fbc0998a by Alex Biehl at 2020-12-08T23:08:23+01:00 Move to GitHub CI (#1266) * Initial version of ci.yml This is a straight copy from Dmitrii Kovanikov's blog post at https://kodimensional.dev/github-actions. Will adapt to haddock in successive commits. * Delete .travis.yml * Modify to only test on ghc-8.10.{1,2} * Use actions/setup-haskell at v1.1.4 * Relax QuickCheck bound on haddock-api * Remove stack matrix for now * Nail down to ghc-8.10 branch for now * Pin index state to 2020-12-08T20:13:44Z for now * Disable macOS and Windows tests for now for speed up - - - - - 5b946b9a by tomjaguarpaw at 2020-12-10T19:01:41+01:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - bc5a408f by dependabot[bot] at 2020-12-10T19:02:16+01:00 Bump ini from 1.3.5 to 1.3.7 in /haddock-api/resources/html (#1269) Bumps [ini](https://github.com/isaacs/ini) from 1.3.5 to 1.3.7. - [Release notes](https://github.com/isaacs/ini/releases) - [Commits](https://github.com/isaacs/ini/compare/v1.3.5...v1.3.7) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - d02995f1 by Andrew Martin at 2020-12-14T16:48:40-05:00 Update for boxed rep - - - - - a381aeff by Ben Gamari at 2020-12-15T15:13:30-05:00 Revert "Enable two warnings (#1245) (#1268)" As this does not build on GHC `master`. This reverts commit 7936692badfe38f23ae95b51fb7bd7c2ff7e9bce. - - - - - a63c0a9e by Ben Gamari at 2020-12-15T15:17:59-05:00 Revert "Update for boxed rep" This reverts commit 4ffb30d8b637ccebecc81ce610f0af451ac8088d. - - - - - 53bfbb29 by Ben Gamari at 2020-12-15T15:37:24-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - bae76a30 by Ben Gamari at 2020-12-16T02:44:42+00:00 Update output for nullary TyConApp optimisation (ghc/ghc!2952) - - - - - 4b733b57 by Krzysztof Gogolewski at 2020-12-16T20:03:14+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. - - - - - ee463bd3 by Ryan Scott at 2020-12-16T16:55:23-05:00 Adapt to HsCoreTy (formerly NewHsTypeX) becoming a type synonym Needed for !4417, the fix for GHC#15706 and GHC#18914. - - - - - ed0b02f8 by tomjaguarpaw at 2020-12-19T10:17:19+00:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - d80bf8f5 by Sylvain Henry at 2020-12-21T10:09:25+01:00 Fix after binder collect changes - - - - - bf4c9d32 by Adam Gundry at 2020-12-23T21:35:01+00:00 Adapt to changes to GlobalRdrElt and AvailInfo Needed for ghc/ghc!4467 - - - - - 37736c4c by John Ericson at 2020-12-28T12:27:02-05:00 Support a new ghc --make node type for parallel backpack upsweep - - - - - 717bdeac by Vladislav Zavialov at 2020-12-29T10:50:02+03:00 Inline and fix getGADTConTypeG The getGADTConTypeG used HsRecTy, which is at odds with GHC issue haskell/haddock#18782. I noticed that getGADTConTypeG was only used in the Hoogle backend. Interestingly, when handling H98 constructors, Hoogle converts RecCon to PrefixCon (see Haddock.Backends.Hoogle.ppCtor). So I changed getGADTConTypeG to handle RecConGADT in the same manner as PrefixConGADT, and after this simplification moved it into the 'where' clause of ppCtor, to the only place where it is used. The practical effect of this change is as follows. Consider this example: data TestH98 = T98 { bar::Int } data TestGADT where TG :: { foo :: Int } -> TestGADT Before this patch, haddock --hoogle used to produce: T98 :: Int -> TestH98 [TG] :: {foo :: Int} -> TestGADT Notice how the record syntax was discarded in T98 but not TG. With this patch, we always produce signatures without record syntax: T98 :: Int -> TestH98 [TG] :: Int -> TestGADT I suspect this might also be a bugfix, as currently Hoogle doesn't seem to render GADT record constructors properly. - - - - - cb1b8c56 by Andreas Abel at 2020-12-30T21:12:37+01:00 Build instructions: haddock-library and -api first! - - - - - b947f6ad by Ben Gamari at 2020-12-31T13:04:19-05:00 Merge pull request haskell/haddock#1281 from obsidiansystems/wip/backpack-j Changes to support -j with backpack - - - - - 120e1cfd by Hécate Moonlight at 2021-01-04T19:54:58+01:00 Merge pull request haskell/haddock#1282 from andreasabel/master Build instructions: haddock-library and -api first! - - - - - fd45e41a by Ben Gamari at 2021-01-05T16:14:31-05:00 Merge remote-tracking branch 'origin/ghc-8.10' into ghc-9.0 - - - - - b471bdec by Ben Gamari at 2021-01-05T16:23:02-05:00 Merge commit '1e56f63c3197e7ca1c1e506e083c2bad25d08793' into ghc-9.0 - - - - - 81cdbc41 by Alex Biehl at 2021-01-09T12:14:41+01:00 Prepare Haddock for being a GHC Plugin - - - - - b646d952 by Alex Biehl at 2021-01-09T12:14:41+01:00 Make Haddock a GHC Plugin - - - - - cc044674 by Alex Biehl at 2021-01-09T12:14:41+01:00 Add -j[n] CLI param to Haddock executable It translates to `--ghcopt=-j[n]` - - - - - 84a04073 by Alex Biehl at 2021-01-09T12:14:41+01:00 Abstract Monad for interface creation I found that when running as a plugin the lookupName function (which runs in Ghc monad) does not work correctly from the typeCheckResultAction hook. Instead, we abstracted the monad used when creating interfaces, so that access to GHC session specific parts is explicit and so that the TcM can provide their (correct) implementation of lookupName. - - - - - 5be2c4f7 by Alex Biehl at 2021-01-09T12:14:41+01:00 Accept tests - - - - - 8cefee9d by Alex Biehl at 2021-01-09T16:10:47+01:00 Add missing dependency for mtl - - - - - 3681f919 by Ben Gamari at 2021-01-13T18:39:25-05:00 Merge remote-tracking branch 'origin/ghc-9.0' into ghc-head - - - - - 33c6b152 by Hécate Moonlight at 2021-01-14T16:04:20+01:00 Merge pull request haskell/haddock#1273 from hsyl20/wip/hsyl20/arrows Fix after binder collect changes - - - - - 70d13e8e by Joachim Breitner at 2021-01-22T19:03:45+01:00 Make haddock more robust to changes to the `Language` data type With the introduction of GHC2021, the `Languages` data type in GHC will grow. In preparation of that (and to avoid changing haddock with each new language), this change makes the code handle extensions to that data type gracefully. (cherry picked from commit c341dd7c9c3fc5ebc83a2d577c5a726f3eb152a5) - - - - - 7d6dd57a by John Ericson at 2021-01-22T22:02:02+00:00 Add `NoGhcTc` instance now that it's not closed - - - - - e5fdaf0a by Alan Zimmerman at 2021-01-23T22:57:44+00:00 Merge pull request haskell/haddock#1293 from obsidiansystems/wip/fix-18936 Add `NoGhcTc` instance now that it's not closed - - - - - 989a1e05 by Oleg Grenrus at 2021-01-24T16:11:46+03:00 Add import list to Data.List - - - - - 368e144a by Ben Gamari at 2021-01-28T22:15:48+01:00 Adapt to "Make PatSyn immutable" - - - - - abe66c21 by Alfredo Di Napoli at 2021-02-01T08:05:35+01:00 Rename pprLogErrMsg to new name - - - - - e600e75c by Hécate Moonlight at 2021-02-05T14:53:00+01:00 Move CI to ghc-9.0 - - - - - dd492961 by Vladislav Zavialov at 2021-02-05T14:53:00+01:00 Update cabal.project and README build instructions - - - - - 31bd292a by Hécate Moonlight at 2021-02-05T15:03:56+01:00 Merge pull request haskell/haddock#1296 from Kleidukos/ghc-9.0 Merge the late additions to ghc-8.10 into ghc-9.0 - - - - - 6388989e by Vladislav Zavialov at 2021-02-05T17:41:57+03:00 Cleanup: fix build warnings - - - - - f99407ef by Daniel Rogozin at 2021-02-05T18:11:48+03:00 type level characters support for haddock (required for haskell/haddock#11342) - - - - - d8c6b26f by Hécate Moonlight at 2021-02-05T17:44:50+01:00 Add a CONTRIBUTING.md file - - - - - 6a01ad98 by Hécate Moonlight at 2021-02-05T17:58:16+01:00 Merge pull request haskell/haddock#1312 from Kleidukos/proper-branch-etiquette Add a CONTRIBUTING.md file - - - - - 955eecc4 by Vladislav Zavialov at 2021-02-05T20:29:00+03:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into ghc-head - - - - - 47b3d6ab by Hécate Moonlight at 2021-02-05T19:09:38+01:00 Amend the CONTRIBUTING.md file - - - - - 23de6137 by Hécate Moonlight at 2021-02-05T19:16:49+01:00 Merge pull request haskell/haddock#1313 from Kleidukos/amend-contributing Amend the CONTRIBUTING.md file - - - - - 69026b59 by Krzysztof Gogolewski at 2021-02-05T23:05:56+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. (cherry picked from commit b4b4d896d2d68d6c48e7db7bfe95c185ca0709cb) - - - - - ea026b78 by Oleg Grenrus at 2021-02-06T17:14:45+01:00 Add import list to Data.List - - - - - 5204326f by Hécate Moonlight at 2021-02-06T17:15:44+01:00 Merge pull request haskell/haddock#1316 from Kleidukos/explicit-imports-to-data-list Add import list to Data.List - - - - - 1f4d2136 by Ben Gamari at 2021-02-06T11:53:31-05:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ghc-head-merge - - - - - 13f0d09a by Ben Gamari at 2021-02-06T11:53:45-05:00 Fix partial record selector warning - - - - - 5c115f7e by Ben Gamari at 2021-02-06T11:55:52-05:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into wip/ghc-head-merge - - - - - b6fd8b75 by Ben Gamari at 2021-02-06T12:01:31-05:00 Merge commit '41964cb2fd54b5a10f8c0f28147015b7d5ad2c02' into wip/ghc-head-merge - - - - - a967194c by Ben Gamari at 2021-02-06T18:30:35-05:00 Merge branch 'wip/ghc-head-merge' into ghc-head - - - - - 1f4c3a91 by MorrowM at 2021-02-07T01:52:33+02:00 Fix search div not scrolling - - - - - 684b1287 by Iñaki García Etxebarria at 2021-02-07T16:13:04+01:00 Add support for labeled module references Support a markdown-style way of annotating module references. For instance -- | [label]("Module.Name#anchor") will create a link that points to the same place as the module reference "Module.Name#anchor" but the text displayed on the link will be "label". - - - - - bdb55a5d by Hécate Moonlight at 2021-02-07T16:18:10+01:00 Merge pull request haskell/haddock#1319 from alexbiehl/alex/compat Backward compat: Add support for labeled module references - - - - - 6ca70991 by Hécate Moonlight at 2021-02-07T16:21:29+01:00 Merge pull request haskell/haddock#1314 from tweag/show-linear-backport Backport haskell/haddock#1238 (linear types) to ghc-9.0 - - - - - d9d73298 by Alex Biehl at 2021-02-07T17:46:25+01:00 Remove dubious parseModLink Instead construct the ModLink value directly when parsing. - - - - - 33b4d020 by Hécate Moonlight at 2021-02-07T17:52:05+01:00 Merge pull request haskell/haddock#1320 from haskell/alex/fix Remove dubious parseModLink - - - - - 54211316 by Hécate Moonlight at 2021-02-07T18:12:07+01:00 Merge pull request haskell/haddock#1318 from MorrowM/ghc-9.0 Fix search div not scrolling - - - - - 19db679e by alexbiehl-gc at 2021-02-07T18:14:46+01:00 Merge pull request haskell/haddock#1317 from bgamari/wip/ghc-head-merge Merge ghc-8.10 into ghc-head - - - - - 6bc1e9e4 by Willem Van Onsem at 2021-02-07T18:25:30+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - c8537cf8 by alexbiehl-gc at 2021-02-07T18:30:40+01:00 Merge pull request haskell/haddock#1322 from haskell/alex/forward-port simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 2d47ae4e by alexbiehl-gc at 2021-02-07T18:39:59+01:00 Merge branch 'ghc-head' into ghc-9.0 - - - - - 849e4733 by Hécate Moonlight at 2021-02-07T18:43:19+01:00 Merge pull request haskell/haddock#1321 from Kleidukos/ghc-9.0 Merge ghc-9.0 into ghc-head - - - - - ee6095d7 by Sylvain Henry at 2021-02-08T11:36:38+01:00 Update for Logger - - - - - 4ad688c9 by Alex Biehl at 2021-02-08T18:11:24+01:00 Merge pull request haskell/haddock#1310 from hsyl20/wip/hsyl20/logger2 Logger refactoring - - - - - 922a9e0e by Ben Gamari at 2021-02-08T12:54:33-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - 991649d2 by Sylvain Henry at 2021-02-09T10:55:17+01:00 Fix to build with HEAD - - - - - a8348dc2 by Hécate Moonlight at 2021-02-09T10:58:51+01:00 Merge pull request haskell/haddock#1327 from hsyl20/wip/hsyl20/logger2 Fix to build with HEAD - - - - - 0abdbca6 by Fendor at 2021-02-09T20:06:15+01:00 Add UnitId to Target record - - - - - d5790a0e by Alex Biehl at 2021-02-11T10:32:32+01:00 Stable sort for (data/newtype) instances - - - - - 8e6036f5 by Alex Biehl at 2021-02-11T10:32:32+01:00 Also make TyLit deterministic - - - - - f76d2945 by Hécate Moonlight at 2021-02-11T11:00:31+01:00 Merge pull request haskell/haddock#1329 from hsyl20/hsyl20/stabe_iface Stable sort for instances - - - - - 5e0469ea by Oleg Grenrus at 2021-02-14T15:28:15+02:00 Add import list to Data.List in Haddock.Interface.Create - - - - - fa57cd24 by Hécate Moonlight at 2021-02-14T17:19:27+01:00 Merge pull request haskell/haddock#1331 from phadej/more-explicit-data-list-imports Add import list to Data.List in Haddock.Interface.Create - - - - - f0cd629c by Hécate Moonlight at 2021-02-21T00:22:01+01:00 Merge pull request haskell/haddock#1311 from fendor/wip/add-targetUnitId-to-target Add UnitId to Target record - - - - - 674ef723 by Joachim Breitner at 2021-02-22T10:39:18+01:00 html-test: Always set language from ghc-9.2 on, the “default” langauge of GHC is expected to change more wildly. To prepare for that (and unblock https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4853), this sets the language for all the test files to `Haskell2010`. This should insolate this test suite against changes to the default. Cherry-picked from https://github.com/haskell/haddock/pull/1341 - - - - - f072d623 by Hécate Moonlight at 2021-02-22T10:56:51+01:00 Merge pull request haskell/haddock#1342 from nomeata/joachim/haskell2010-in-tests-ghc-head html-test: Always set language - - - - - caebbfca by Hécate Moonlight at 2021-02-22T11:53:07+01:00 Clean-up of Interface and Interface.Create's imports and pragmata - - - - - f6caa89d by Hécate Moonlight at 2021-02-22T11:54:58+01:00 Merge pull request haskell/haddock#1345 from Kleidukos/head/fix-interface-imports [ghc-head] Clean-up of Interface and Interface.Create's imports and pragmata - - - - - 7395c9cb by Hécate Moonlight at 2021-02-22T18:44:57+01:00 Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 6e9fb5d5 by Hécate Moonlight at 2021-02-22T18:45:28+01:00 Merge pull request haskell/haddock#1348 from Kleidukos/head/explicit-imports-interface Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 9198b118 by Alan Zimmerman at 2021-02-22T20:04:24+00:00 Context becomes a Maybe in the GHC AST This prevents noLoc's appearing in the ParsedSource. Match the change in GHC. - - - - - 0af20f64 by Hécate Moonlight at 2021-02-23T12:36:12+01:00 Fix the call-site of guessTarget in Interface.hs Explicit the imports from GHC.HsToCore.Docs - - - - - b7886885 by Hécate Moonlight at 2021-02-23T12:37:54+01:00 Merge pull request haskell/haddock#1349 from Kleidukos/fix-interface-guesstarget-call Fix the call-site of guessTarget in Interface.hs - - - - - 9cf041ba by Sylvain Henry at 2021-02-24T11:08:20+01:00 Fix haddockHypsrcTest output in ghc-head - - - - - b194182a by Hécate Moonlight at 2021-02-24T11:12:36+01:00 Merge pull request haskell/haddock#1351 from hsyl20/wip/hsyl20/fix-head Fix haddockHypsrcTest output in ghc-head - - - - - 3ce8b375 by Shayne Fletcher at 2021-03-06T09:55:03-05:00 Add ITproj to parser - - - - - d2abf762 by Ben Gamari at 2021-03-06T19:26:49-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a0f6047d by Andrew Martin at 2021-03-07T11:25:23-05:00 Update for boxed rep - - - - - 6f63c99e by Ben Gamari at 2021-03-10T13:20:21-05:00 Update for "FastString: Use FastMutInt instead of IORef Int" - - - - - e13f01df by Luke Lau at 2021-03-10T15:38:40-05:00 Implement template-haskell's putDoc This catches up to GHC using the new extractTHDocs function, which returns documentation added via the putDoc function (provided it was compiled with Opt_Haddock). Since it's already a map from names -> docs, there's no need to do traversal etc. It also matches the change from the argument map being made an IntMap rather than a Map Int - - - - - 89263d94 by Alan Zimmerman at 2021-03-15T17:15:26+00:00 Match changes in GHC AST for in-tree API Annotations As landed via https://gitlab.haskell.org/ghc/ghc/-/merge_requests/2418 - - - - - 28db1934 by Alan Zimmerman at 2021-03-15T20:40:09+00:00 Change some type family test results. It is not clear to me whether the original was printing incorrectly (since we did not have the TopLevel flag before now), or if this behaviour is expected. For the time being I am assuming the former. - - - - - 7c11c989 by Sylvain Henry at 2021-03-22T10:05:19+01:00 Fix after NameCache changes - - - - - addbde15 by Sylvain Henry at 2021-03-22T10:05:19+01:00 NameCache doesn't store a UniqSupply anymore - - - - - 15ec6cec by Ben Gamari at 2021-03-22T17:53:44-04:00 Bump GHC version to 9.2 - - - - - dbd6aa63 by Hécate Moonlight at 2021-03-24T14:28:36+01:00 Merge pull request haskell/haddock#1365 from hsyl20/wip/hsyl20/iface1 NameCache refactoring - - - - - 2d32da7e by Oleg Grenrus at 2021-03-27T01:12:00+02:00 Specialization of Data.List - - - - - 32b84fa6 by Fendor at 2021-03-27T10:50:17+01:00 Add UnitId to Target record This way we always know to which home-unit a given target belongs to. So far, there only exists a single home-unit at a time, but it enables having multiple home-units at the same time. - - - - - 54bf9f0e by Hécate Moonlight at 2021-03-28T14:08:35+02:00 Merge pull request haskell/haddock#1368 from fendor/target-unit-id-revert Add UnitId to Target record - - - - - 7dea168a by Alan Zimmerman at 2021-03-29T08:45:52+01:00 EPA : Rename ApiAnn to EpAnn - - - - - 72967f65 by Alfredo Di Napoli at 2021-03-29T09:47:01+02:00 pprError changed name in GHC - - - - - 4bc61035 by Alan Zimmerman at 2021-03-29T16:16:27-04:00 EPA : Rename ApiAnn to EpAnn - - - - - 108d031d by Ben Gamari at 2021-03-29T18:49:36-04:00 Merge commit '36418c4f70d7d2b179a77925b3ad5caedb08c9b5' into HEAD - - - - - 1444f700 by Ben Gamari at 2021-03-31T09:18:39-04:00 Merge pull request haskell/haddock#1370 from adinapoli/wip/adinapoli-diag-reason-severity Rename pprError to mkParserErr - - - - - d3087b79 by Ben Gamari at 2021-03-31T11:34:17-04:00 Merge commit 'd8d8024ad6796549a8d3b5512dabf3288d14e30f' into ghc-head - - - - - 170b79e9 by Ben Gamari at 2021-03-31T12:24:56-04:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - db0d6bae by Ben Gamari at 2021-04-10T09:34:35-04:00 Bump GHC version to 9.3 - - - - - a9f2c421 by Alan Zimmerman at 2021-04-19T18:26:46-04:00 Update for EPA changes in GHC (cherry picked from commit cafb48118f7c111020663776845897e225607b41) - - - - - 1ee4b7c7 by Sylvain Henry at 2021-05-11T10:00:06+02:00 Removal of HsVersions.h (#1388) * Update for EPA changes in GHC * Account for HsVersions.h removal Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 79e819e9 by Hécate Moonlight at 2021-05-11T10:14:47+02:00 Revert "Removal of HsVersions.h (#1388)" This reverts commit 72118896464f94d81f10c52f5d9261efcacc57a6. - - - - - 3dbd3f8b by Alan Zimmerman at 2021-05-11T10:15:17+02:00 Update for EPA changes in GHC - - - - - 2ce80c17 by Sylvain Henry at 2021-05-11T10:15:19+02:00 Account for HsVersions.h removal - - - - - 00e4c918 by Christiaan Baaij at 2021-05-13T08:21:56+02:00 Add Haddock support for the OPAQUE pragma (#1380) - - - - - 8f9049b2 by Hécate Moonlight at 2021-05-13T08:40:22+02:00 fixup! Use GHC 9.2 in CI runner - - - - - 27ddec38 by Alan Zimmerman at 2021-05-13T22:51:20+01:00 EPA: match changes from GHC T19834 - - - - - f8a1d714 by Felix Yan at 2021-05-14T17:10:04+02:00 Allow hspec 2.8 (#1389) All tests are passing. - - - - - df44453b by Divam Narula at 2021-05-20T15:42:42+02:00 Update ref, the variables got renamed. (#1391) This is due to ghc/ghc!5555 which caused a change in ModDetails in case of NoBackend. Now the initModDetails is used to recreate the ModDetails from interface and in-memory ModDetails is not used. - - - - - e46bfc87 by Alan Zimmerman at 2021-05-20T19:05:09+01:00 Remove Maybe from HsQualTy Match changes in GHC for haskell/haddock#19845 - - - - - 79bd7b62 by Shayne Fletcher at 2021-05-22T08:20:39+10:00 FieldOcc: rename extFieldOcc to foExt - - - - - 6ed68c74 by Ben Gamari at 2021-05-21T22:29:30-04:00 Merge commit '3b6a8774bdb543dad59b2618458b07feab8a55e9' into ghc-head - - - - - f9a02d34 by Alfredo Di Napoli at 2021-05-24T13:53:00+02:00 New Parser diagnostics interface - - - - - 392807d0 by Ben Gamari at 2021-05-24T09:57:40-04:00 Merge pull request haskell/haddock#1394 from adinapoli/wip/adinapoli-align-ps-messages Align Haddock to use the new Parser diagnostics interface - - - - - 33023cd8 by Ben Gamari at 2021-05-24T11:19:16-04:00 Revert "Add Haddock support for the OPAQUE pragma (#1380)" This reverts commit a1337c599ef7720b0482a25c55f11794112496dc. The GHC patch associated with this change is not yet ready to be merged. - - - - - 8c005af7 by Ben Simms at 2021-05-28T07:56:20+02:00 CI configuration for ghc-head (#1395) - - - - - 1e947612 by Hécate Moonlight at 2021-05-28T12:27:35+02:00 Use GHC 9.2 in CI runner (#1378) - - - - - e6fa10ab by CGenie at 2021-05-31T09:02:13+02:00 Add page about common errors (#1396) * Update index.rst Common errors page * Create common-errors.rst * Update common-errors.rst * Use GHC 9.2 in CI runner (#1378) * [haddock-api] remove .hspec-failures Co-authored-by: Hécate Moonlight <Kleidukos at users.noreply.github.com> - - - - - abc72a8d by Sylvain Henry at 2021-06-01T10:02:06+02:00 Adapt Haddock to Logger and Parser changes (#1399) - - - - - 91373656 by Zubin Duggal at 2021-06-01T20:45:10+02:00 Update haddockHypSrc tests since we now compute slighly more type info (#1397) - - - - - ed712822 by Marcin Szamotulski at 2021-06-02T08:54:33+02:00 Added myself to contributors - - - - - 49fdbcb7 by Marcin Szamotulski at 2021-06-02T08:57:24+02:00 Document multi component support - - - - - 9ddc8d7d by Hécate Moonlight at 2021-06-02T09:35:55+02:00 Merge pull request haskell/haddock#1379 from coot/coot/document-multi-component-support Document multi component support - - - - - 585b5c5e by Ben Simms at 2021-06-02T19:46:54+02:00 Update CONTRIBUTING.md (#1402) - - - - - 1df4a605 by Ben Simms at 2021-06-02T19:47:14+02:00 Update CONTRIBUTING.md (#1403) - - - - - 58ea43d2 by sheaf at 2021-06-02T22:09:06+02:00 Update Haddock Bug873 to account for renaming - - - - - c5d0ab23 by Vladislav Zavialov at 2021-06-10T13:35:42+03:00 HsToken in FunTy, RecConGADT - - - - - 1ae2f40c by Hécate Moonlight at 2021-06-11T11:19:09+02:00 Update the CI badges - - - - - 6fdc4de2 by Sylvain Henry at 2021-06-28T19:21:17+02:00 Fix mkParserOpts (#1411) - - - - - 18201670 by Alfredo Di Napoli at 2021-07-05T07:55:12+02:00 Rename getErrorMessages Lexer import This commit renames the Lexer import in `Hyperlinker.Parser` from `getErrorMessages` to `getPsErrorMessages` to eliminate the ambiguity with the `getErrorMessages` function defined in `GHC.Types.Error`. - - - - - 23173ca3 by Ben Gamari at 2021-07-07T11:31:44-04:00 Merge pull request haskell/haddock#1413 from adinapoli/wip/adinapoli-issue-19920 Rename getErrorMessages Lexer import - - - - - b3dc4ed8 by Alan Zimmerman at 2021-07-28T22:30:59+01:00 EPA: match changes from GHC T19834 (cherry picked from commit 2fec1b44e0ee7e263286709aa528b4ecb99ac6c2) - - - - - 5f177278 by Ben Gamari at 2021-08-06T01:17:37-04:00 Merge commit '2a966c8ca37' into HEAD - - - - - cdd81d08 by Marcin Szamotulski at 2021-08-08T17:19:06+02:00 coot/multiple packages (ghc-9.2) (#1418) - - - - - be0d71f1 by Marcin Szamotulski at 2021-08-16T08:46:03+02:00 coot/multiple package (ghc-head) (#1419) * FromJSON class Aeson style FromJSON class with Parsec based json parser. * doc-index.json file for multiple packages When creating haddock summary page for multiple packages render doc-index.json file using contents of all found 'doc-index.json' files. * Render doc-index.json When rendering html, render doc-index.json file independently of maybe_index_url option. doc-index.json file is useful now even if maybe_index_url is not `Nothing`. * base url option New `Flag_BaseURL` which configures from where static files are loaded (--base-url). If given and not equal "." static files are not coppied, as this indicates that they are not read from the the directory where we'd copy them. The default value is ".". - - - - - 3b09dbdf by Hécate Moonlight at 2021-10-07T23:26:03+02:00 Update GHC 9.2 to latest pre-release in CI - - - - - 7ac55417 by Zubin Duggal at 2021-10-11T12:10:19+02:00 Enable Haddock tests in GHC windows CI (#1428) * testsuite: strip windows line endings for haddock * hyperlinker: Work around double escaping (#19236) * deterministic SCC - - - - - 1cb81f25 by Andrew Lelechenko at 2021-10-12T15:23:19+02:00 haddock-library does not depend on bytestring or transformers (#1426) - - - - - a890b9aa by sheaf at 2021-10-15T22:19:42+02:00 update haddockHypsrcTest for GHC MR !6705 (#1430) - - - - - 42a55c6c by Sylvain Henry at 2021-10-15T22:20:10+02:00 Fix after PkgQual refactoring (#1429) - - - - - 91659238 by Alan Zimmerman at 2021-10-28T18:57:10+01:00 Update for changes in GHC for branch wip/az/no-srcspan-anno-instances - - - - - acf23e60 by Vladislav Zavialov at 2021-11-05T02:09:47+03:00 Do not use forall as an identifier See GHC ticket haskell/haddock#20609 - - - - - c565db0e by Krzysztof Gogolewski at 2021-11-27T02:42:35+01:00 Update after NoExtCon -> DataConCantHappen rename - - - - - b5f55590 by Artem Pelenitsyn at 2021-11-27T11:14:17+01:00 fix CI for 9.2 (#1436) - - - - - 25cd621e by Matthew Pickering at 2021-12-02T11:46:54+00:00 Update html-test for Data.List revert - - - - - 1d5ff85f by malteneuss at 2021-12-15T07:56:55+01:00 Add hint about inline link issue (#1444) - - - - - 791fde81 by Sylvain Henry at 2021-12-16T09:29:51+01:00 Bump ghc-head (#1445) * Update after NoExtCon -> DataConCantHappen rename * Update html-test for Data.List revert * Fix for new Plugins datatype Co-authored-by: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 44236317 by Sylvain Henry at 2021-12-17T09:39:00+01:00 Fix for new Plugins datatype - - - - - 80ada0fa by Hécate Moonlight at 2021-12-17T17:28:48+01:00 Remove ghc-head workflow (#1446) Contributions of GHC glue code are now done on the GHC gitlab, not in the GitHub repo anymore. - - - - - 49e171cd by Matthew Pickering at 2021-12-28T09:47:09+00:00 Remove use of ExtendedModSummary - - - - - 0e91b5ea by askeblad at 2022-01-04T09:18:35+01:00 update URLs - - - - - 9f13c212 by Hécate Moonlight at 2022-02-25T10:19:46+01:00 Fix solver for GHC 9.2 - - - - - 386751a1 by Meng Weng Wong at 2022-02-25T19:19:11+01:00 IDoc link has bitrotted; replaced with web.archive.org cache. (#1454) - - - - - d877cbe6 by Hécate Moonlight at 2022-02-25T19:21:58+01:00 Fix haddock user guide (#1456) - - - - - cc47f036 by Andrew Lelechenko at 2022-03-04T17:29:36+01:00 Allow text-2.0 in haddock-library (#1459) - - - - - 7b3685a3 by malteneuss at 2022-03-07T19:27:24+01:00 Add multi-line style hint to style section (#1460) - - - - - c51088b8 by John Ericson at 2022-03-11T16:46:26+01:00 Fix CollectPass instance to match TTG refactor Companion to GHC !7614 (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7614) - - - - - b882195b by Vladislav Zavialov at 2022-03-14T20:32:30+01:00 Link to (~) - - - - - 877349b8 by Christiaan Baaij at 2022-03-16T09:20:43+01:00 Add Haddock support for the OPAQUE pragma - - - - - 0ea22721 by askeblad at 2022-03-16T09:44:27+01:00 typos (#1464) - - - - - a6d13da1 by Matthew Pickering at 2022-03-22T13:41:17+00:00 Minimum changes needed for compilation with hi-haddock With hi-haddock, of course there is a much large refactoring of haddock which could be achieved but that is left for a future patch which can implemented at any time independently of GHC. - - - - - e7ac9129 by Matthew Pickering at 2022-03-22T21:17:50+00:00 Update test output - - - - - 6d916214 by Matthew Pickering at 2022-03-24T15:06:26+00:00 Merge branch 'wip/opaque_pragma' into 'ghc-head' Add Haddock support for the OPAQUE pragma See merge request ghc/haddock!2 - - - - - 42208183 by Steve Hart at 2022-03-25T20:43:50+01:00 Fix CI (#1467) * CI: Reinstall GHC with docs CI tests were failing because the GHC preinstalled to the CI environment does not include documentation, which is required for running the Haddock tests. This commit causes the CI workflow to reinstall GHC with docs so that tests can succeed. - - - - - 9676fd79 by Steve Hart at 2022-03-25T21:33:34+01:00 Make links in Synopsis functional again (#1458) Commit e41c1cbe9f0476997eac7b4a3f17cbc6b2262faf added a call to e.preventDefault() when handling click events that reach a toggle element. This prevents the browser from following hyperlinks within the Synopsis section when they are clicked by a user. This commit restores functioning hyperlinks within the Synopsis section by removing the call to e.preventDefault(), as it does not appear to be necessary, and removing it increases the flexibility of the details-helper code. - - - - - d1edd637 by sheaf at 2022-04-01T12:02:02+02:00 Keep track of promotion ticks in HsOpTy Keeping track of promotion ticks in HsOpTy allows us to properly pretty-print promoted constructors such as lists. - - - - - 9dcb2dfc by Jakob Brünker at 2022-04-01T15:46:22+00:00 Add support for \cases See merge request ghc/ghc!7873 - - - - - b0412ee5 by askeblad at 2022-04-06T17:47:57+02:00 spelling errors (#1471) - - - - - 6b18829b by Vladislav Zavialov at 2022-04-06T18:53:58+02:00 Rename [] to List - - - - - 2d046691 by Vladislav Zavialov at 2022-04-07T20:25:54+03:00 HsToken ConDeclGADT con_dcolon - - - - - 90b43da4 by Steve Hart at 2022-04-12T13:29:46+02:00 Parse Markdown links at beginning of line within a paragraph (#1470) * Catch Markdown links at beginning of line within paragraph Per Issue haskell/haddock#774, Markdown links were being parsed as ordinary text when they occurred at the beginning of a line other than the first line of the paragraph. This occurred because the parser was not interpreting a left square bracket as a special character that could delimit special markup. A space character was considered a special character, so, if a space occurred at the beginning of the new line, then the parser would interpret the space by itself and then continue parsing, thereby catching the Markdown link. '\n' was not treated as a special character, so the parser did not catch a Markdown link that may have followed. Note that this will allow for Markdown links that are not surrounded by spaces. For example, the following text includes a Markdown link that will be parsed: Hello, world[label](url) This is consistent with how the parser handles other types of markup. * Remove obsolete documentation hint Commit 6b9aeafddf20efc65d3725c16e3fc43a20aac343 should eliminate the need for the workaround suggested in the documentation. - - - - - 5b08312d by Hécate Moonlight at 2022-04-12T13:36:38+02:00 Force ghc-9.2 in the cabal.project - - - - - 0d0ea349 by dependabot[bot] at 2022-04-12T13:57:41+02:00 Bump path-parse from 1.0.5 to 1.0.7 in /haddock-api/resources/html (#1469) Bumps [path-parse](https://github.com/jbgutierrez/path-parse) from 1.0.5 to 1.0.7. - [Release notes](https://github.com/jbgutierrez/path-parse/releases) - [Commits](https://github.com/jbgutierrez/path-parse/commits/v1.0.7) --- updated-dependencies: - dependency-name: path-parse dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 2b9fc65e by dependabot[bot] at 2022-04-12T13:57:54+02:00 Bump copy-props from 2.0.4 to 2.0.5 in /haddock-api/resources/html (#1468) Bumps [copy-props](https://github.com/gulpjs/copy-props) from 2.0.4 to 2.0.5. - [Release notes](https://github.com/gulpjs/copy-props/releases) - [Changelog](https://github.com/gulpjs/copy-props/blob/master/CHANGELOG.md) - [Commits](https://github.com/gulpjs/copy-props/compare/2.0.4...2.0.5) --- updated-dependencies: - dependency-name: copy-props dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - ea98a6fb by Ben Gamari at 2022-04-23T22:54:37-04:00 Update for GHC 9.4 - - - - - 9e11864f by Ben Gamari at 2022-04-25T16:24:31-04:00 Merge remote-tracking branch 'upstream/ghc-9.2' into ghc-head - - - - - f83cc506 by Ben Gamari at 2022-04-25T17:00:25-04:00 Bump ghc version to 9.5 - - - - - e01c2e7d by Ben Gamari at 2022-04-28T16:19:04-04:00 Revert "Bump ghc-head (#1445)" This reverts commit b29a78ef6926101338f62e84f456dac8659dc9d2. This should not have been merged. - - - - - a2b5ee8c by Ben Gamari at 2022-04-28T16:19:24-04:00 Merge commit '2627a86c' into ghc-head - - - - - 0c6fe4f9 by Ben Gamari at 2022-04-29T10:05:54-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-9.4 - - - - - b6e5cb0a by Ben Gamari at 2022-04-29T11:46:06-04:00 Revert "HsToken ConDeclGADT con_dcolon" This reverts commit 24208496649a02d5f87373052c430ea4a97842c5. - - - - - 15a62888 by Ben Gamari at 2022-04-29T15:12:55-04:00 Bump base upper bound - - - - - 165b9031 by Ben Gamari at 2022-04-29T23:58:38-04:00 Update test output - - - - - e0c3e5da by Phil de Joux at 2022-05-02T14:46:38+02:00 Add hlint action .hlint.yaml with ignores & CPP. (#1475) - - - - - ead1158d by Raphael Das Gupta at 2022-05-02T14:46:48+02:00 fix grammar in docs: "can the" → "can be" (#1477) - - - - - cff97944 by Ben Gamari at 2022-05-02T18:38:56-04:00 Allow base-4.17 - - - - - e4ecb201 by Phil de Joux at 2022-05-03T13:14:55+02:00 Remove unused imports that GHC warned about. (#1480) - - - - - 222890b1 by Phil de Joux at 2022-05-03T13:15:46+02:00 Follow hlint suggestion to remove redundant bang. (#1479) - - - - - 058b671f by Phil de Joux at 2022-05-03T13:34:04+02:00 Follow hlint, remove language pragmas in libs. (#1478) - - - - - 0a645049 by Ben Simms at 2022-05-03T14:19:24+02:00 Keep track of ordered list indexes and render them (#1407) * Keep track of ordered list indexes and render them * Rename some identifiers to clarify - - - - - f0433304 by Norman Ramsey at 2022-05-04T15:13:34-04:00 update for changes in GHC API - - - - - 3740cf71 by Emily Martins at 2022-05-06T18:23:48+02:00 Add link to the readthedocs in cabal description to show on hackage. (cherry picked from commit 52e2d40d47295c02d3181aac0c53028e730f1e3b) - - - - - 5d754f1e by Hécate Moonlight at 2022-05-06T18:44:57+02:00 remove Bug873 - - - - - 968fc267 by Hécate Moonlight at 2022-05-06T18:48:28+02:00 Ignore "Use second" HLint suggestion. It increases laziness. - - - - - 02d14e97 by Jade Lovelace at 2022-05-07T17:42:08+02:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` - - - - - b22b87ed by Artem Pelenitsyn at 2022-05-08T16:19:47+02:00 fix parsing trailing quotes in backticked identifiers (#1408) (#1483) - - - - - 80ae107b by Alex Biehl at 2022-05-08T16:37:16+02:00 Fix "Defined by not used" error (cherry picked from commit 6e02a620a26c3a44f98675dd1b93b08070c36c0a) - - - - - 4c838e84 by Hécate Moonlight at 2022-05-08T16:37:16+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - fc9827b4 by Hécate Moonlight at 2022-05-08T16:40:40+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - b153b555 by Xia Li-yao at 2022-05-20T17:52:42+02:00 Hide synopsis from search when hidden (#1486) Fix haskell/haddock#1451 - - - - - f3e38b85 by Marcin Szamotulski at 2022-05-21T23:32:31+02:00 Allow to hide interfaces when rendering multiple components (#1487) This is useful when one wishes to `--gen-contents` when rendering multiple components, but one does not want to render all modules. This is in particular useful when adding base package. - - - - - f942863b by Marcin Szamotulski at 2022-05-24T08:29:59+02:00 Check if doc-index.json exists before reading it (#1488) - - - - - 31e92982 by Marcin Szamotulski at 2022-05-25T16:22:13+02:00 Version bump 2.26.1 (#1489) * Version bump 2.26.1 We extended format accepted by `--read-interface` option, which requires updating the minor version. * Update documentation of --read-interface option - - - - - 7cc873e0 by sheaf at 2022-05-25T16:42:31+02:00 Updated HaddockHypsrcTest output for record update changes (MR !7981) - - - - - cd196942 by Marcin Szamotulski at 2022-05-25T20:28:47+02:00 Use visibility to decide which interfaces are included in quickjump (#1490) This is also consistent with how html index is build. See haskell/cabal#7669 for rationale behind this decision. - - - - - 00c713c5 by Hécate Moonlight at 2022-05-26T17:09:15+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 2f3039f1 by Hécate Moonlight at 2022-05-26T17:10:59+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 63a5650c by romes at 2022-05-31T12:43:22+01:00 TTG: Match new GHC AST - - - - - dd7d1617 by romes at 2022-06-02T16:11:00+01:00 Update for IE changes in !8228 - - - - - c23aaab7 by cydparser at 2022-06-06T08:48:14+02:00 Fix and improve CI (#1495) * Pin GHC version before creating the freeze file * Use newest action versions * Improve caching * Avoid unnecessarily reinstalling GHC * Use GHC 9.2.2 for CI Co-authored-by: Cyd Wise <cwise at tripshot.com> - - - - - c156fa77 by Hécate Moonlight at 2022-06-06T11:59:35+02:00 Add Mergify configuration (#1496) - - - - - 2dba4188 by Hécate Moonlight at 2022-06-06T16:12:50+02:00 Bump haddock's version in cabal file to 2.26.1 (#1497) - - - - - d7d4b8b9 by Marcin Szamotulski at 2022-06-07T06:09:40+00:00 Render module tree per package in the content page (#1492) * Render module tree per package in the content page When rendering content page for multiple packages it is useful to split the module tree per package. Package names in this patch are inferred from haddock's interface file names. * Write PackageInfo into interface file To keep interface file format backward compatible, instead of using `Binary` instance for `InterfaceFile` we introduce functions to serialise and deserialise, which depends on the interface file version. - - - - - 77765665 by Mike Pilgrem at 2022-06-12T21:57:19+01:00 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - b0e079b0 by mergify[bot] at 2022-06-13T11:49:37+00:00 Merge pull request haskell/haddock#1108 from mpilgrem/fix783 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - 6c0292b1 by Hécate Moonlight at 2022-06-21T17:21:08+02:00 Update the contribution guide - - - - - e413b9fa by dependabot[bot] at 2022-06-21T23:38:19+02:00 Bump shell-quote from 1.6.1 to 1.7.3 in /haddock-api/resources/html (#1500) Bumps [shell-quote](https://github.com/substack/node-shell-quote) from 1.6.1 to 1.7.3. - [Release notes](https://github.com/substack/node-shell-quote/releases) - [Changelog](https://github.com/substack/node-shell-quote/blob/master/CHANGELOG.md) - [Commits](https://github.com/substack/node-shell-quote/compare/1.6.1...1.7.3) --- updated-dependencies: - dependency-name: shell-quote dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 29d0ef70 by romes at 2022-07-06T11:29:39+02:00 TTG: AST Updates for !8308 - - - - - 1bae7c87 by Alan Zimmerman at 2022-07-06T22:50:43+01:00 Match GHC changes for T21805 This brings in a newtype for FieldLabelString - - - - - 6fe8b988 by Phil de Joux at 2022-07-16T20:54:26+00:00 Bump hlint version to 3.4.1, the version with counts. (#1503) Redo the counts available with the --default option. - - - - - 48fb43af by Phil de Joux at 2022-07-19T09:32:55+02:00 Follow hlint suggestion: unused LANGUAGE pragma. (#1504) * Follow hlint suggestion: unused LANGUAGE pragma. * Ignore within modules to pass linting and pass tests. - - - - - c1cf1fa7 by Phil de Joux at 2022-07-24T13:45:59+02:00 Follow hlint suggestion: redundant $. (#1505) * Follow hlint suggestion: redundant $. * Remove $ and surplus blank lines in Operators. - - - - - 74777eb2 by Jade Lovelace at 2022-07-29T11:02:41+01:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` (cherry picked from commit ab53ccf089ea703b767581ac14be0f6c78a7678a) - - - - - faa4cfcf by Hécate Moonlight at 2022-07-29T20:31:20+02:00 Merge pull request haskell/haddock#1516 from duog/9-4-backport-fix-hyperlinks Backport 9-4: Fix hyperlinks to external items and modules (#1482) - - - - - 5d2450f3 by Ben Gamari at 2022-08-05T17:41:15-04:00 Merge remote-tracking branch 'origin/ghc-9.4' - - - - - 63954f73 by Ben Gamari at 2022-08-05T19:08:36-04:00 Clean up build and testsuite for GHC 9.4 - - - - - d4568cb8 by Hécate Moonlight at 2022-08-05T19:10:49-04:00 Bump the versions - - - - - 505583a4 by Ben Gamari at 2022-08-06T13:58:27-04:00 Merge pull request haskell/haddock#1518 from bgamari/wip/ghc-9.4-merge Merge GHC 9.4 into `main` - - - - - 5706f6a4 by Ben Gamari at 2022-08-06T22:57:21-04:00 html-test: Testsuite changes for GHC 9.4.1 - - - - - 5f2a45a2 by Ben Gamari at 2022-08-15T14:33:05-04:00 doc: Fix a few minor ReST issues Sphinx was complaining about too-short title underlines. - - - - - 220e6410 by Ben Gamari at 2022-08-15T14:41:24-04:00 Merge branch 'main' into ghc-head - - - - - fbeb1b02 by Ben Gamari at 2022-08-15T14:45:16-04:00 Updates for GHC 9.5 - - - - - eee562eb by Vladislav Zavialov at 2022-08-15T14:46:13-04:00 HsToken ConDeclGADT con_dcolon - - - - - c5f073db by Ben Gamari at 2022-08-15T16:55:35-04:00 Updates for GHC 9.5 - - - - - 3f7ab242 by Vladislav Zavialov at 2022-08-15T16:55:35-04:00 HsToken ConDeclGADT con_dcolon - - - - - a18e473d by Ben Gamari at 2022-08-16T08:35:19-04:00 Merge branch 'wip/ghc-head-bump' into ghc-head - - - - - af0ff3a4 by M Farkas-Dyck at 2022-09-15T21:16:05+00:00 Disuse `mapLoc`. - - - - - a748fc38 by Matthew Farkas-Dyck at 2022-09-17T10:44:18+00:00 Scrub partiality about `NewOrData`. - - - - - 2758fb6c by John Ericson at 2022-09-18T03:27:37+02:00 Test output changed because of change to `base` Spooky, but I guess that is intended? - - - - - a7eec128 by Torsten Schmits at 2022-09-21T11:06:55+02:00 update tests for the move of tuples to GHC.Tuple.Prim - - - - - 461e7b9d by Ross Paterson at 2022-09-24T22:01:25+00:00 match implementation of GHC proposal haskell/haddock#106 (Define Kinds Without Promotion) - - - - - f7fd77ef by sheaf at 2022-10-17T14:53:01+02:00 Update Haddock for GHC MR !8563 (configuration of diagnostics) - - - - - 3d3e85ab by Vladislav Zavialov at 2022-10-22T23:04:06+03:00 Class layout info - - - - - cbde4cb0 by Simon Peyton Jones at 2022-10-25T23:19:18+01:00 Adapt to Constraint-vs-Type See haskell/haddock#21623 and !8750 - - - - - 7108ba96 by Tom Smeding at 2022-11-01T22:33:23+01:00 Remove outdated footnote about module re-exports The footnote is invalid with GHC 9.2.4 (and possibly earlier): the described behaviour in the main text works fine. - - - - - 206c6bc7 by Hécate Moonlight at 2022-11-01T23:00:46+01:00 Merge pull request haskell/haddock#1534 from tomsmeding/patch-1 - - - - - a57b4c4b by Andrew Lelechenko at 2022-11-21T00:39:52+00:00 Support mtl-2.3 - - - - - e9d62453 by Simon Peyton Jones at 2022-11-25T13:49:12+01:00 Track small API change in TyCon.hs - - - - - eb1c73f7 by Ben Gamari at 2022-12-07T08:46:21-05:00 Update for GhC 9.6 - - - - - 063268dd by Ben Gamari at 2022-12-07T11:26:32-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 4ca722fe by Ben Gamari at 2022-12-08T14:43:26-05:00 Bump bounds to accomodate base-4.18 - - - - - 340b7511 by Vladislav Zavialov at 2022-12-10T12:31:28+00:00 HsToken in HsAppKindTy - - - - - 946226ec by Ben Gamari at 2022-12-13T20:12:56-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - fd8faa66 by Ben Gamari at 2022-12-22T13:44:28-05:00 Bump GHC version to 9.7 - - - - - 2958aa9c by Ben Gamari at 2022-12-22T14:49:16-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 9e0fefd8 by Andrei Borzenkov at 2023-01-30T14:02:04+04:00 Rename () to Unit, Rename (,,...,,) to Tuple<n> - - - - - eb3968b5 by Ben Gamari at 2023-03-10T02:32:43-05:00 Bump versions for ghc-9.6 release - - - - - 4aeead36 by Adam Gundry at 2023-03-23T13:53:47+01:00 Adapt to warning categories changes - - - - - 642d8d60 by sheaf at 2023-03-29T13:35:56+02:00 Adapt to record field refactor This commit adapts to the changes in GHC MR !8686, which overhauls the treatment of record fields in the renamer, adding separate record field namespaces and entirely removing the GreName datatype. - - - - - ac8d4333 by doyougnu at 2023-03-29T11:11:44-04:00 Update UniqMap API - - - - - 7866fc86 by Ben Orchard at 2023-04-20T11:29:33+02:00 update classify with new tokens - - - - - ffcdd683 by Finley McIlwaine at 2023-04-24T09:36:18-06:00 Remove index-state - - - - - 05b70982 by Finley McIlwaine at 2023-04-26T08:16:31-06:00 `renameInterface` space leak fixes - Change logic for accumulation of names for which link warnings will be generated - Change handling of `--ignore-link-symbol` to allow qualified and unqualified names. Added to CHANGES.md - Some formatting changes and comments here and there - - - - - e5697d7c by Finley McIlwaine at 2023-04-27T18:46:36-06:00 Messy things - ghc-debug dependency and instrumentation - cabal.project custom with-compiler - hie.yaml files - traces and such - - - - - 0b8ef80b by Finley McIlwaine at 2023-05-02T18:08:52-06:00 Stop retaining GRE closures GRE closures should never be necessary to Haddock, so we never want to keep them on the heap. Despite that, they are retained by a lot of the data structures that Haddock makes use of. - Attempt to fix that situation by adding strictness to various computations and pruning the `ifaceInstances` field of `Interface` to a much thinner data type. - Removes the `ifaceFamInstances` field, as it was never used. - Move some of the attach instances types (e.g. `SimpleType`) to the types module - - - - - 8bda991b by Finley McIlwaine at 2023-05-08T16:07:51-06:00 Memory usage fixes - Refactor `ifaceDeclMap` to drastically reduce memory footprint. We no longer store all declarations associated with a given name, since we only cared to determine if the only declaration associated with a name was a value declaration. Change the `DeclMap` type to better reflect this. - Drop pre-renaming export items after the renaming step. Since the Hoogle backend used the pre-renamed export items, this isn't trivial. We now generate Hoogle output for exported declarations during the renaming step (if Hoogle output /should/ be generated), and store that with the renamed export item. - Slightly refactor Hoogle backend to handle the above change and allow for early generation of Hoogle output. - Remove the `ifaceRnDocMap` and `ifaceRnArgMap` fields of the `Interface` type, as they were never used. - Remove some unnecessary strictness - Remove a lot of dead code from `Syb` module - - - - - 1611ac0c by Finley McIlwaine at 2023-05-09T11:51:57-06:00 Unify ErrMsgM and IfM - Delete ErrMsgM, stop accumulating warnings in a writer - Make IfM a state monad, print warnings directly to stdout, move IfM type into types module - Drop ErrMsg = String synonym - Unset IORefs from plugin after they are read, preventing unnecessary retention of interfaces - - - - - 42d696ab by Finley McIlwaine at 2023-05-11T15:52:07-06:00 Thunk leak fixes The strictness introduced in this commit was motivated by observing thunk leaks in the eventlog2html output. - Refactor attach instances list comprehension to avoid large intermediate thunks - Refactor some HTML backend list comprehensions to avoid large intermediate thunks - Avoid thunks accumulating in documentation types or documentation parser - A lot of orphan NFData instances to allow us to force documentation values - - - - - 68561cf6 by Finley McIlwaine at 2023-05-11T17:02:10-06:00 Remove GHC debug dep - - - - - 10519e3d by Finley McIlwaine at 2023-05-15T12:40:48-06:00 Force HIE file path Removes a potential retainer of `ModSummary`s - - - - - 1e4a6ec6 by Finley McIlwaine at 2023-05-15T14:20:34-06:00 Re-add index-state, with-compiler, delete hie.yamls - - - - - a2363fe9 by Hécate Moonlight at 2023-05-15T22:45:16+02:00 Merge pull request haskell/haddock#1594 from FinleyMcIlwaine/finley/ghc-9.6-mem-fixes Reduce memory usage - - - - - e8a78383 by Finley McIlwaine at 2023-05-17T12:19:16-06:00 Merge branch ghc-9.6 into ghc-head - - - - - 22e25581 by Finley McIlwaine at 2023-05-17T12:20:23-06:00 Merge branch 'ghc-head' of gitlab.haskell.org:ghc/haddock into ghc-head - - - - - 41bbf0df by Bartłomiej Cieślar at 2023-05-24T08:57:58+02:00 changes to the WarningTxt cases Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - c686ba9b by Hécate Moonlight at 2023-06-01T14:03:02-06:00 Port the remains of Hi-Haddock - - - - - 9d8a85fd by Hécate Moonlight at 2023-06-01T14:03:06-06:00 Stdout for tests - - - - - 36331d07 by Finley McIlwaine at 2023-06-01T14:06:02-06:00 Formatting, organize imports - - - - - a06059b1 by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix empty context confusion in Convert module - - - - - 379346ae by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix associated type families in Hoogle output - - - - - fc6ea7ed by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix test refs Accept several changes in Hoogle tests: Pretty printing logic no longer prints the `(Proxy (Proxy (...))` chain in Bug806 with parentheses. Since this test was only meant to verify that line breaks do not occur, accept the change. `tyThingToLHsDecl` is called for class and data declarations, which ends up "synifying" the type variables and giving unlifted types kind signatures. As a result, type variables of kind `Type -> Type` are now printed with kind signatures in Hoogle output. This could be changed by manually drop kind signatures from class variables in the Hoogle backend if the behavior is deemed unacceptable. Sometimes subordinate declarations are exported separate from their parent declarations (e.g. record selectors). In this case, a type signature is cobbled together for the export item in `extractDecl`. Since this type signature is very manually constructed, it may lack kind signatures of decls constructed from `tyThingToLHsDecl`. An example of this is the `type-sigs` Hoogle test. Change `*` to `Type` in Hoogle test refs. I don't think this will break Hoogle behavior, since it appears to not consider type signatures in search. I have not fully verified this. - - - - - e14b7e58 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix LaTeX backend test refs Changes to GHC pretty printing code have resulted in some differences to Haddock's LaTeX output. - Type variables are printed explicitly quantified in the LinearTypes test - Wildcard types in type family equations are now printed numbered, e.g. _1 _2, in the TypeFamilies3 test - Combined signatures in DefaultSignatures test are now documented as separate signatures - - - - - 41b5b296 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and test source updates - Stop using kind `*` in html test sources - Add TypeOperators where necessary to avoid warnings and future errors - Rename some test modules to match their module names - - - - - c640e2a2 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix missing deprecation warnings on record fields `lookupOccEnv` was used to resolve `OccNames` with warnings attached, but it doesn't look in the record field namespace. Thus, if a record field had a warning attached, it would not resolve and the warning map would not include it. This commit fixes by using `lookupOccEnv_WithFields` instead. - - - - - fad0c462 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and some comments - - - - - 751fd023 by Finley McIlwaine at 2023-06-01T14:11:41-06:00 Accept HTML test diffs All diffs now boil down to the expected differences resulting from declarations being reified from TyThings in hi-haddock. Surface syntax now has much less control over the syntax used in the documentation. - - - - - d835c845 by Finley McIlwaine at 2023-06-01T14:11:45-06:00 Adapt to new load' type - - - - - dcf776c4 by Finley McIlwaine at 2023-06-01T14:13:13-06:00 Update mkWarningMap and moduleWarning - - - - - 8e8432fd by Finley McIlwaine at 2023-06-01T14:28:54-06:00 Revert load' changes - - - - - aeb2982c by Finley McIlwaine at 2023-06-01T14:40:24-06:00 Accept change to Instances test in html-test Link to Data.Tuple instead of GHC.Tuple.Prim - - - - - 8adfdbac by Finley McIlwaine at 2023-06-01T15:53:17-06:00 Reset ghc dep to ^>= 9.6 - - - - - 2b1ce93d by Finley McIlwaine at 2023-06-06T07:50:04-06:00 Update CHANGES.md, user guide, recomp avoidance * Add --trace-args flag for tracing arguments received to standard output * Avoid recompiling due to changes in optimization flags * Update users guide and changes.md - - - - - f3da6676 by Finley McIlwaine at 2023-06-06T14:12:56-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - bf36c467 by Matthew Pickering at 2023-06-07T10:16:09+01:00 Revert back to e16e20d592a6f5d9ed1af17b77fafd6495242345 Neither of these MRs are ready to land yet which causes issues with other MRs which are ready to land and need haddock changes. - - - - - 421510a9 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 atSign has no unicode variant Prior to this change, atSign was defined as follows: atSign unicode = text (if unicode then "@" else "@") Yes, this is the same symbol '\64' and not your font playing tricks on you. Now we define: atSign = char '@' Both the LaTeX and the Xhtml backend are updated accordingly. - - - - - 3785c276 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 LaTeX: fix printing of type variable bindings Consider this type signature: kindOf :: forall {k} (a :: k). Proxy a -> Proxy k Prior to this fix, the LaTeX backend rendered it like this: kindOf :: forall k a. Proxy a -> Proxy k Now we preserve explicit specificity and kind annotations. - - - - - 0febf3a8 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 Add support for invisible binders in type declarations - - - - - 13e33bb3 by Finley McIlwaine at 2023-06-08T07:51:59-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - 3e5340ce by Finley McIlwaine at 2023-06-08T07:54:27-06:00 Add note about stubdir to recompilation docs - - - - - db7e84dc by Finley at 2023-06-08T08:11:03-06:00 Merge pull request haskell/haddock#1597 from haskell/finley/hi-haddock-9.6 hi-haddock for ghc 9.6 - - - - - 4e085d17 by Finley McIlwaine at 2023-06-14T13:41:06-06:00 Replace SYB traversals - - - - - 7b39aec5 by Finley McIlwaine at 2023-06-14T14:20:17-06:00 Test ref accepts, remove unused HaddockClsInst - - - - - df9c2090 by Finley McIlwaine at 2023-06-15T08:02:51-06:00 Use batchMsg for progress reporting during load With hi-haddock as is, there is an awkward silence during the load operation. This commit makes haddock use the default `batchMsg` Messager for progress reporting, and makes the default GHC verbosity level 1, so the user can see what GHC is doing. - - - - - f23679a8 by Hécate Moonlight at 2023-06-15T20:31:53+02:00 Merge pull request haskell/haddock#1600 from haskell/finley/hi-haddock-optim - - - - - a7982192 by Finley McIlwaine at 2023-06-15T15:02:16-06:00 hi-haddock squashed - - - - - c34f0c8d by Finley McIlwaine at 2023-06-15T16:22:03-06:00 Merge remote-tracking branch 'origin/ghc-9.6' into finley/hi-haddock-squashed - - - - - 40452797 by Bartłomiej Cieślar at 2023-06-16T12:26:04+02:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - e58673bf by Ben Gamari at 2023-06-16T09:33:35-04:00 Bump GHC version to 9.8 - - - - - 74bdf972 by Ben Gamari at 2023-06-16T09:36:18-04:00 Merge commit 'fcaaad06770a26d35d4aafd65772dedadf17669c' into ghc-head - - - - - 418ee3dc by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Remove NFData SourceText, IfaceWarnings updates The NFData SourceText instance is now available in GHC Handle mod_iface mi_warns now being IfaceWarnings - - - - - 62f31380 by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Accept Instances.hs test output Due to ghc!10469. - - - - - a8f2fc0e by Ben Gamari at 2023-06-20T15:48:08-04:00 Test fixes for "Fix associated data family doc structure items" Associated data families were being given their own export DocStructureItems, which resulted in them being documented separately from their classes in haddocks. This commit fixes it. - - - - - cb1ac33e by Bartłomiej Cieślar at 2023-06-21T12:56:02-04:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - 9933e10b by Ben Gamari at 2023-06-21T12:56:02-04:00 Bump GHC version to 9.8 - - - - - fe8c18b6 by Ben Gamari at 2023-06-21T15:36:29-04:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - c61a0d5b by Ben Gamari at 2023-06-21T16:10:51-04:00 Bump GHC version to 9.9 - - - - - 0c2a756e by sheaf at 2023-07-07T13:45:12+02:00 Avoid incomplete record update in Haddock Hoogle This commit avoids running into an incomplete record update warning in the Hoogle backend of Haddock. This was only noticed now, because incomplete record updates were broken in GHC 9.6. Now that they are fixed, we have to avoid running into them! - - - - - dd38aca9 by Andreas Schwab at 2023-07-11T13:55:56+00:00 Hadrian: enable GHCi support on riscv64 - - - - - 09a5c6cc by Josh Meredith at 2023-07-12T11:25:13-04:00 JavaScript: support unicode code points > 2^16 in toJSString using String.fromCodePoint (#23628) - - - - - 29fbbd4e by Matthew Pickering at 2023-07-12T11:25:49-04:00 Remove references to make build system in mk/build.mk Fixes #23636 - - - - - 630e3026 by sheaf at 2023-07-12T11:26:43-04:00 Valid hole fits: don't panic on a Given The function GHC.Tc.Errors.validHoleFits would end up panicking when encountering a Given constraint. To fix this, it suffices to filter out the Givens before continuing. Fixes #22684 - - - - - c39f279b by Matthew Pickering at 2023-07-12T23:18:38-04:00 Use deb10 for i386 bindists deb9 is now EOL so it's time to upgrade the i386 bindist to use deb10 Fixes #23585 - - - - - bf9b9de0 by Krzysztof Gogolewski at 2023-07-12T23:19:15-04:00 Fix #23567, a specializer bug Found by Simon in https://gitlab.haskell.org/ghc/ghc/-/issues/23567#note_507834 The testcase isn't ideal because it doesn't detect the bug in master, unless doNotUnbox is removed as in https://gitlab.haskell.org/ghc/ghc/-/issues/23567#note_507692. But I have confirmed that with that modification, it fails before and passes afterwards. - - - - - 84c1a4a2 by Bartłomiej Cieślar at 2023-07-12T23:20:08-04:00 Comments - - - - - b2846cb5 by Bartłomiej Cieślar at 2023-07-12T23:20:08-04:00 updates to comments - - - - - 2af23f0e by Bartłomiej Cieślar at 2023-07-12T23:20:08-04:00 changes - - - - - 6143838a by sheaf at 2023-07-13T08:02:17-04:00 Fix deprecation of record fields Commit 3f374399 inadvertently broke the deprecation/warning mechanism for record fields due to its introduction of record field namespaces. This patch ensures that, when a top-level deprecation is applied to an identifier, it applies to all the record fields as well. This is achieved by refactoring GHC.Rename.Env.lookupLocalTcNames, and GHC.Rename.Env.lookupBindGroupOcc, to not look up a fixed number of NameSpaces but to look up all NameSpaces and filter out the irrelevant ones. - - - - - 6fd8f566 by sheaf at 2023-07-13T08:02:17-04:00 Introduce greInfo, greParent These are simple helper functions that wrap the internal field names gre_info, gre_par. - - - - - 7f0a86ed by sheaf at 2023-07-13T08:02:17-04:00 Refactor lookupGRE_... functions This commit consolidates all the logic for looking up something in the Global Reader Environment into the single function lookupGRE. This allows us to declaratively specify all the different modes of looking up in the GlobalRdrEnv, and avoids manually passing around filtering functions as was the case in e.g. the function GHC.Rename.Env.lookupSubBndrOcc_helper. ------------------------- Metric Decrease: T8095 ------------------------- ------------------------- Metric Increase: T8095 ------------------------- - - - - - 5e951395 by Rodrigo Mesquita at 2023-07-13T08:02:54-04:00 configure: Drop DllWrap command We used to configure into settings a DllWrap command for windows builds and distributions, however, we no longer do, and dllwrap is effectively unused. This simplification is motivated in part by the larger toolchain-selection project (#19877, !9263) - - - - - e10556b6 by Teo Camarasu at 2023-07-14T16:28:46-04:00 base: fix haddock syntax in GHC.Profiling - - - - - 0f3fda81 by Matthew Pickering at 2023-07-14T16:29:23-04:00 Revert "CI: add JS release and debug builds, regen CI jobs" This reverts commit 59c5fe1d4b624423b1c37891710f2757bb58d6af. This commit added two duplicate jobs on all validate pipelines, so we are reverting for now whilst we work out what the best way forward is. Ticket #23618 - - - - - 54bca324 by Alan Zimmerman at 2023-07-15T03:23:26-04:00 EPA: Simplify GHC/Parser.y sLL Follow up to !10743 - - - - - c8863828 by sheaf at 2023-07-15T03:24:06-04:00 Configure: canonicalise PythonCmd on Windows This change makes PythonCmd resolve to a canonical absolute path on Windows, which prevents HLS getting confused (now that we have a build-time dependency on python). fixes #23652 - - - - - ca1e636a by Rodrigo Mesquita at 2023-07-15T03:24:42-04:00 Improve Note [Binder-swap during float-out] - - - - - cf86f3ec by Matthew Craven at 2023-07-16T01:42:09+02:00 Equality of forall-types is visibility aware This patch finally (I hope) nails the question of whether (forall a. ty) and (forall a -> ty) are `eqType`: they aren't! There is a long discussion in #22762, plus useful Notes: * Note [ForAllTy and type equality] in GHC.Core.TyCo.Compare * Note [Comparing visiblities] in GHC.Core.TyCo.Compare * Note [ForAllCo] in GHC.Core.TyCo.Rep It also establishes a helpful new invariant for ForAllCo, and ForAllTy, when the bound variable is a CoVar:in that case the visibility must be coreTyLamForAllTyFlag. All this is well documented in revised Notes. - - - - - 7f13acbf by Vladislav Zavialov at 2023-07-16T01:56:27-04:00 List and Tuple<n>: update documentation Add the missing changelog.md entries and @since-annotations. - - - - - 2afbddb0 by Andrei Borzenkov at 2023-07-16T10:21:24+04:00 Type patterns (#22478, #18986) Improved name resolution and type checking of type patterns in constructors: 1. HsTyPat: a new dedicated data type that represents type patterns in HsConPatDetails instead of reusing HsPatSigType 2. rnHsTyPat: a new function that renames a type pattern and collects its binders into three groups: - explicitly bound type variables, excluding locally bound variables - implicitly bound type variables from kind signatures (only if ScopedTypeVariables are enabled) - named wildcards (only from kind signatures) 2a. rnHsPatSigTypeBindingVars: removed in favour of rnHsTyPat 2b. rnImplcitTvBndrs: removed because no longer needed 3. collect_pat: updated to collect type variable binders from type patterns (this means that types and terms use the same infrastructure to detect conflicting bindings, unused variables and name shadowing) 3a. CollVarTyVarBinders: a new CollectFlag constructor that enables collection of type variables 4. tcHsTyPat: a new function that typechecks type patterns, capable of handling polymorphic kinds. See Note [Type patterns: binders and unifiers] Examples of code that is now accepted: f = \(P @a) -> \(P @a) -> ... -- triggers -Wname-shadowing g :: forall a. Proxy a -> ... g (P @a) = ... -- also triggers -Wname-shadowing h (P @($(TH.varT (TH.mkName "t")))) = ... -- t is bound at splice time j (P @(a :: (x,x))) = ... -- (x,x) is no longer rejected data T where MkT :: forall (f :: forall k. k -> Type). f Int -> f Maybe -> T k :: T -> () k (MkT @f (x :: f Int) (y :: f Maybe)) = () -- f :: forall k. k -> Type Examples of code that is rejected with better error messages: f (Left @a @a _) = ... -- new message: -- • Conflicting definitions for ‘a’ -- Bound at: Test.hs:1:11 -- Test.hs:1:14 Examples of code that is now rejected: {-# OPTIONS_GHC -Werror=unused-matches #-} f (P @a) = () -- Defined but not used: type variable ‘a’ - - - - - eb1a6ab1 by sheaf at 2023-07-16T09:20:45-04:00 Don't use substTyUnchecked in newMetaTyVar There were some comments that explained that we needed to use an unchecked substitution function because of issue #12931, but that has since been fixed, so we should be able to use substTy instead now. - - - - - c7bbad9a by sheaf at 2023-07-17T02:48:19-04:00 rnImports: var shouldn't import NoFldSelectors In an import declaration such as import M ( var ) the import of the variable "var" should **not** bring into scope record fields named "var" which are defined with NoFieldSelectors. Doing so can cause spurious "unused import" warnings, as reported in ticket #23557. Fixes #23557 - - - - - 1af2e773 by sheaf at 2023-07-17T02:48:19-04:00 Suggest similar names in imports This commit adds similar name suggestions when importing. For example module A where { spelling = 'o' } module B where { import B ( speling ) } will give rise to the error message: Module ‘A’ does not export ‘speling’. Suggested fix: Perhaps use ‘spelling’ This also provides hints when users try to import record fields defined with NoFieldSelectors. - - - - - 654fdb98 by Alan Zimmerman at 2023-07-17T02:48:55-04:00 EPA: Store leading AnnSemi for decllist in al_rest This simplifies the markAnnListA implementation in ExactPrint - - - - - 22565506 by sheaf at 2023-07-17T21:12:59-04:00 base: add COMPLETE pragma to BufferCodec PatSyn This implements CLC proposal #178, rectifying an oversight in the implementation of CLC proposal #134 which could lead to spurious pattern match warnings. https://github.com/haskell/core-libraries-committee/issues/178 https://github.com/haskell/core-libraries-committee/issues/134 - - - - - 860f6269 by sheaf at 2023-07-17T21:13:00-04:00 exactprint: silence incomplete record update warnings - - - - - df706de3 by sheaf at 2023-07-17T21:13:00-04:00 Re-instate -Wincomplete-record-updates Commit e74fc066 refactored the handling of record updates to use the HsExpanded mechanism. This meant that the pattern matching inherent to a record update was considered to be "generated code", and thus we stopped emitting "incomplete record update" warnings entirely. This commit changes the "data Origin = Source | Generated" datatype, adding a field to the Generated constructor to indicate whether we still want to perform pattern-match checking. We also have to do a bit of plumbing with HsCase, to record that the HsCase arose from an HsExpansion of a RecUpd, so that the error message continues to mention record updates as opposed to a generic "incomplete pattern matches in case" error. Finally, this patch also changes the way we handle inaccessible code warnings. Commit e74fc066 was also a regression in this regard, as we were emitting "inaccessible code" warnings for case statements spuriously generated when desugaring a record update (remember: the desugaring mechanism happens before typechecking; it thus can't take into account e.g. GADT information in order to decide which constructors to include in the RHS of the desugaring of the record update). We fix this by changing the mechanism through which we disable inaccessible code warnings: we now check whether we are in generated code in GHC.Tc.Utils.TcMType.newImplication in order to determine whether to emit inaccessible code warnings. Fixes #23520 Updates haddock submodule, to avoid incomplete record update warnings - - - - - 1d05971e by sheaf at 2023-07-17T21:13:00-04:00 Propagate long-distance information in do-notation The preceding commit re-enabled pattern-match checking inside record updates. This revealed that #21360 was in fact NOT fixed by e74fc066. This commit makes sure we correctly propagate long-distance information in do blocks, e.g. in ```haskell data T = A { fld :: Int } | B f :: T -> Maybe T f r = do a at A{} <- Just r Just $ case a of { A _ -> A 9 } ``` we need to propagate the fact that "a" is headed by the constructor "A" to see that the case expression "case a of { A _ -> A 9 }" cannot fail. Fixes #21360 - - - - - bea0e323 by sheaf at 2023-07-17T21:13:00-04:00 Skip PMC for boring patterns Some patterns introduce no new information to the pattern-match checker (such as plain variable or wildcard patterns). We can thus skip doing any pattern-match checking on them when the sole purpose for doing so was introducing new long-distance information. See Note [Boring patterns] in GHC.Hs.Pat. Doing this avoids regressing in performance now that we do additional pattern-match checking inside do notation. - - - - - ddcdd88c by Rodrigo Mesquita at 2023-07-17T21:13:36-04:00 Split GHC.Platform.ArchOS from ghc-boot into ghc-platform Split off the `GHC.Platform.ArchOS` module from the `ghc-boot` package into this reinstallable standalone package which abides by the PVP, in part motivated by the ongoing work on `ghc-toolchain` towards runtime retargetability. - - - - - b55a8ea7 by Sylvain Henry at 2023-07-17T21:14:27-04:00 JS: better implementation for plusWord64 (#23597) - - - - - 889c2bbb by sheaf at 2023-07-18T06:37:32-04:00 Do primop rep-poly checks when instantiating This patch changes how we perform representation-polymorphism checking for primops (and other wired-in Ids such as coerce). When instantiating the primop, we check whether each type variable is required to instantiated to a concrete type, and if so we create a new concrete metavariable (a ConcreteTv) instead of a simple MetaTv. (A little subtlety is the need to apply the substitution obtained from instantiating to the ConcreteTvOrigins, see Note [substConcreteTvOrigin] in GHC.Tc.Utils.TcMType.) This allows us to prevent representation-polymorphism in non-argument position, as that is required for some of these primops. We can also remove the logic in tcRemainingValArgs, except for the part concerning representation-polymorphic unlifted newtypes. The function has been renamed rejectRepPolyNewtypes; all it does now is reject unsaturated occurrences of representation-polymorphic newtype constructors when the representation of its argument isn't a concrete RuntimeRep (i.e. still a PHASE 1 FixedRuntimeRep check). The Note [Eta-expanding rep-poly unlifted newtypes] in GHC.Tc.Gen.Head gives more explanation about a possible path to PHASE 2, which would be in line with the treatment for primops taken in this patch. We also update the Core Lint check to handle this new framework. This means Core Lint now checks representation-polymorphism in continuation position like needed for catch#. Fixes #21906 ------------------------- Metric Increase: LargeRecord ------------------------- - - - - - 00648e5d by Krzysztof Gogolewski at 2023-07-18T06:38:10-04:00 Core Lint: distinguish let and letrec in locations Lint messages were saying "in the body of letrec" even for non-recursive let. I've also renamed BodyOfLetRec to BodyOfLet in stg, since there's no separate letrec. - - - - - 787bae96 by Krzysztof Gogolewski at 2023-07-18T06:38:50-04:00 Use extended literals when deriving Show This implements GHC proposal https://github.com/ghc-proposals/ghc-proposals/pull/596 Also add support for Int64# and Word64#; see testcase ShowPrim. - - - - - 257f1567 by Jaro Reinders at 2023-07-18T06:39:29-04:00 Add StgFromCore and StgCodeGen linting - - - - - 34d08a20 by Ben Gamari at 2023-07-19T03:33:22-04:00 Reg.Liveness: Strictness - - - - - c5deaa27 by Ben Gamari at 2023-07-19T03:33:22-04:00 Reg.Liveness: Don't repeatedly construct UniqSets - - - - - b947250b by Ben Gamari at 2023-07-19T03:33:22-04:00 compiler/Types: Ensure that fromList-type operations can fuse In #20740 I noticed that mkUniqSet does not fuse. In practice, allowing it to do so makes a considerable difference in allocations due to the backend. Metric Decrease: T12707 T13379 T3294 T4801 T5321FD T5321Fun T783 - - - - - 6c88c2ba by Sven Tennie at 2023-07-19T03:33:59-04:00 x86 Codegen: Implement MO_S_MulMayOflo for W16 - - - - - 5f1154e0 by Sven Tennie at 2023-07-19T03:33:59-04:00 x86 CodeGen: MO_S_MulMayOflo better error message for rep > W64 It's useful to see which value made the pattern match fail. (If it ever occurs.) - - - - - e8c9a95f by Sven Tennie at 2023-07-19T03:33:59-04:00 x86 CodeGen: Implement MO_S_MulMayOflo for W8 This case wasn't handled before. But, the test-primops test suite showed that it actually might appear. - - - - - a36f9dc9 by Sven Tennie at 2023-07-19T03:33:59-04:00 Add test for %mulmayoflo primop The test expects a perfect implementation with no false positives. - - - - - 38a36248 by Matthew Pickering at 2023-07-19T03:34:36-04:00 lint-ci-config: Generate jobs-metadata.json We also now save the jobs-metadata.json and jobs.yaml file as artifacts as: * It might be useful for someone who is modifying CI to copy jobs.yaml if they are having trouble regenerating locally. * jobs-metadata.json is very useful for downstream pipelines to work out the right job to download. Fixes #23654 - - - - - 1535a671 by Vladislav Zavialov at 2023-07-19T03:35:12-04:00 Initialize 9.10.1-notes.rst Create new release notes for the next GHC release (GHC 9.10) - - - - - 3bd4d5b5 by sheaf at 2023-07-19T03:35:53-04:00 Prioritise Parent when looking up class sub-binder When we look up children GlobalRdrElts of a given Parent, we sometimes would rather prioritise those GlobalRdrElts which have the right Parent, and sometimes prioritise those that have the right NameSpace: - in export lists, we should prioritise NameSpace - for class/instance binders, we should prioritise Parent See Note [childGREPriority] in GHC.Types.Name.Reader. fixes #23664 - - - - - 9c8fdda3 by Alan Zimmerman at 2023-07-19T03:36:29-04:00 EPA: Improve annotation management in getMonoBind Ensure the LHsDecl for a FunBind has the correct leading comments and trailing annotations. See the added note for details. - - - - - ff884b77 by Matthew Pickering at 2023-07-19T11:42:02+01:00 Remove unused files in .gitlab These were left over after 6078b429 - - - - - 29ef590c by Matthew Pickering at 2023-07-19T11:42:52+01:00 gen_ci: Add hie.yaml file This allows you to load `gen_ci.hs` into HLS, and now it is a huge module, that is quite useful. - - - - - 808b55cf by Matthew Pickering at 2023-07-19T12:24:41+01:00 ci: Make "fast-ci" the default validate configuration We are trying out a lighter weight validation pipeline where by default we just test on 5 platforms: * x86_64-deb10-slow-validate * windows * x86_64-fedora33-release * aarch64-darwin * aarch64-linux-deb10 In order to enable the "full" validation pipeline you can apply the `full-ci` label which will enable all the validation pipelines. All the validation jobs are still run on a marge batch. The goal is to reduce the overall CI capacity so that pipelines start faster for MRs and marge bot batches are faster. Fixes #23694 - - - - - 0b23db03 by Alan Zimmerman at 2023-07-20T05:28:47-04:00 EPA: Simplify GHC/Parser.y sL1 This is the next patch in a series simplifying location management in GHC/Parser.y This one simplifies sL1, to use the HasLoc instances introduced in !10743 (closed) - - - - - 3ece9856 by Ben Gamari at 2023-07-21T07:30:45-04:00 nativeGen: Explicitly set flags of text sections on Windows The binutils documentation (for COFF) claims, > If no flags are specified, the default flags depend upon the section > name. If the section name is not recognized, the default will be for the > section to be loaded and writable. We previously assumed that this would do the right thing for split sections (e.g. a section named `.text$foo` would be correctly inferred to be a text section). However, we have observed that this is not the case (at least under the clang toolchain used on Windows): when split-sections is enabled, text sections are treated by the assembler as data (matching the "default" behavior specified by the documentation). Avoid this by setting section flags explicitly. This should fix split sections on Windows. Fixes #22834. - - - - - db7f7240 by Ben Gamari at 2023-07-21T07:30:45-04:00 nativeGen: Set explicit section types on all platforms - - - - - b444c16f by Finley McIlwaine at 2023-07-21T07:31:28-04:00 Insert documentation into parsed signature modules Causes haddock comments in signature modules to be properly inserted into the AST (just as they are for regular modules) if the `-haddock` flag is given. Also adds a test that compares `-ddump-parsed-ast` output for a signature module to prevent further regressions. Fixes #23315 - - - - - f9b952a7 by Ben Gamari at 2023-07-21T11:58:05-04:00 Bump base bound to <4.20 For GHC 9.8. - - - - - c30cea53 by Ben Gamari at 2023-07-21T23:23:49-04:00 primops: Introduce unsafeThawByteArray# This addresses an odd asymmetry in the ByteArray# primops, which previously provided unsafeFreezeByteArray# but no corresponding thaw operation. Closes #22710 - - - - - 87f9bd47 by Ben Gamari at 2023-07-21T23:23:49-04:00 testsuite: Elaborate in interface stability README This discussion didn't make it into the original MR. - - - - - e4350b41 by Matthew Pickering at 2023-07-21T23:24:25-04:00 Allow users to override non-essential haddock options in a Flavour We now supply the non-essential options to haddock using the `extraArgs` field, which can be specified in a Flavour so that if an advanced user wants to change how documentation is generated then they can use something other than the `defaultHaddockExtraArgs`. This does have the potential to regress some packaging if a user has overridden `extraArgs` themselves, because now they also need to add the haddock options to extraArgs. This can easily be done by appending `defaultHaddockExtraArgs` to their extraArgs invocation but someone might not notice this behaviour has changed. In any case, I think passing the non-essential options in this manner is the right thing to do and matches what we do for the "ghc" builder, which by default doesn't pass any optmisation levels, and would likewise be very bad if someone didn't pass suitable `-O` levels for builds. Fixes #23625 - - - - - fc186b0c by Ilias Tsitsimpis at 2023-07-21T23:25:03-04:00 ghc-prim: Link against libatomic Commit b4d39adbb58 made 'hs_cmpxchg64()' available to all architectures. Unfortunately this made GHC to fail to build on armel, since armel needs libatomic to support atomic operations on 64-bit word sizes. Configure libraries/ghc-prim/ghc-prim.cabal to link against libatomic, the same way as we do in rts/rts.cabal. - - - - - 4f5538a8 by Matthew Pickering at 2023-07-21T23:25:39-04:00 simplifier: Correct InScopeSet in rule matching The in-scope set passedto the `exprIsLambda_maybe` call lacked all the in-scope binders. @simonpj suggests this fix where we augment the in-scope set with the free variables of expression which fixes this failure mode in quite a direct way. Fixes #23630 - - - - - 5ad8d597 by Krzysztof Gogolewski at 2023-07-21T23:26:17-04:00 Add a test for #23413 It was fixed by commit e1590ddc661d6: Add the SolverStage monad. - - - - - 7e05f6df by sheaf at 2023-07-21T23:26:56-04:00 Finish migration of diagnostics in GHC.Tc.Validity This patch finishes migrating the error messages in GHC.Tc.Validity to use the new diagnostic infrastructure. It also refactors the error message datatypes for class and family instances, to common them up under a single datatype as much as possible. - - - - - 4876fddc by Matthew Pickering at 2023-07-21T23:27:33-04:00 ci: Enable some more jobs to run in a marge batch In !10907 I made the majority of jobs not run on a validate pipeline but then forgot to renable a select few jobs on the marge batch MR. - - - - - 026991d7 by Jens Petersen at 2023-07-21T23:28:13-04:00 user_guide/flags.py: python-3.12 no longer includes distutils packaging.version seems able to handle this fine - - - - - b91bbc2b by Matthew Pickering at 2023-07-21T23:28:50-04:00 ci: Mention ~full-ci label in MR template We mention that if you need a full validation pipeline then you can apply the ~full-ci label to your MR in order to test against the full validation pipeline (like we do for marge). - - - - - 42b05e9b by sheaf at 2023-07-22T12:36:00-04:00 RTS: declare setKeepCAFs symbol Commit 08ba8720 failed to declare the dependency of keepCAFsForGHCi on the symbol setKeepCAFs in the RTS, which led to undefined symbol errors on Windows, as exhibited by the testcase frontend001. Thanks to Moritz Angermann and Ryan Scott for the diagnosis and fix. Fixes #22961 - - - - - a72015d6 by sheaf at 2023-07-22T12:36:01-04:00 Mark plugins-external as broken on Windows This test is broken on Windows, so we explicitly mark it as such now that we stop skipping plugin tests on Windows. - - - - - cb9c93d7 by sheaf at 2023-07-22T12:36:01-04:00 Stop marking plugin tests as fragile on Windows Now that b2bb3e62 has landed we are in a better situation with regards to plugins on Windows, allowing us to unmark many plugin tests as fragile. Fixes #16405 - - - - - a7349217 by Krzysztof Gogolewski at 2023-07-22T12:36:37-04:00 Misc cleanup - Remove unused RDR names - Fix typos in comments - Deriving: simplify boxConTbl and remove unused litConTbl - chmod -x GHC/Exts.hs, this seems accidental - - - - - 33b6850a by Vladislav Zavialov at 2023-07-23T10:27:37-04:00 Visible forall in types of terms: Part 1 (#22326) This patch implements part 1 of GHC Proposal #281, introducing explicit `type` patterns and `type` arguments. Summary of the changes: 1. New extension flag: RequiredTypeArguments 2. New user-facing syntax: `type p` patterns (represented by EmbTyPat) `type e` expressions (represented by HsEmbTy) 3. Functions with required type arguments (visible forall) can now be defined and applied: idv :: forall a -> a -> a -- signature (relevant change: checkVdqOK in GHC/Tc/Validity.hs) idv (type a) (x :: a) = x -- definition (relevant change: tcPats in GHC/Tc/Gen/Pat.hs) x = idv (type Int) 42 -- usage (relevant change: tcInstFun in GHC/Tc/Gen/App.hs) 4. template-haskell support: TH.TypeE corresponds to HsEmbTy TH.TypeP corresponds to EmbTyPat 5. Test cases and a new User's Guide section Changes *not* included here are the t2t (term-to-type) transformation and term variable capture; those belong to part 2. - - - - - 73b5c7ce by sheaf at 2023-07-23T10:28:18-04:00 Add test for #22424 This is a simple Template Haskell test in which we refer to record selectors by their exact Names, in two different ways. Fixes #22424 - - - - - 83cbc672 by Ben Gamari at 2023-07-24T07:40:49+00:00 ghc-toolchain: Initial commit - - - - - 31dcd26c by Rodrigo Mesquita at 2023-07-24T07:40:49+00:00 ghc-toolchain: Toolchain Selection This commit integrates ghc-toolchain, the brand new way of configuring toolchains for GHC, with the Hadrian build system, with configure, and extends and improves the first iteration of ghc-toolchain. The general overview is * We introduce a program invoked `ghc-toolchain --triple=...` which, when run, produces a file with a `Target`. A `GHC.Toolchain.Target.Target` describes the properties of a target and the toolchain (executables and configured flags) to produce code for that target * Hadrian was modified to read Target files, and will both * Invoke the toolchain configured in the Target file as needed * Produce a `settings` file for GHC based on the Target file for that stage * `./configure` will invoke ghc-toolchain to generate target files, but it will also generate target files based on the flags configure itself configured (through `.in` files that are substituted) * By default, the Targets generated by configure are still (for now) the ones used by Hadrian * But we additionally validate the Target files generated by ghc-toolchain against the ones generated by configure, to get a head start on catching configuration bugs before we transition completely. * When we make that transition, we will want to drop a lot of the toolchain configuration logic from configure, but keep it otherwise. * For each compiler stage we should have 1 target file (up to a stage compiler we can't run in our machine) * We just have a HOST target file, which we use as the target for stage0 * And a TARGET target file, which we use for stage1 (and later stages, if not cross compiling) * Note there is no BUILD target file, because we only support cross compilation where BUILD=HOST * (for more details on cross-compilation see discussion on !9263) See also * Note [How we configure the bundled windows toolchain] * Note [ghc-toolchain consistency checking] * Note [ghc-toolchain overview] Ticket: #19877 MR: !9263 - - - - - a732b6d3 by Rodrigo Mesquita at 2023-07-24T07:40:49+00:00 Add flag to enable/disable ghc-toolchain based configurations This flag is disabled by default, and we'll use the configure-generated-toolchains by default until we remove the toolchain configuration logic from configure. - - - - - 61eea240 by Rodrigo Mesquita at 2023-07-24T07:40:49+00:00 Split ghc-toolchain executable to new packge In light of #23690, we split the ghc-toolchain executable out of the library package to be able to ship it in the bindist using Hadrian. Ideally, we eventually revert this commit. - - - - - 38e795ff by Rodrigo Mesquita at 2023-07-24T07:40:49+00:00 Ship ghc-toolchain in the bindist Add the ghc-toolchain binary to the binary distribution we ship to users, and teach the bindist configure to use the existing ghc-toolchain. - - - - - 32cae784 by Matthew Craven at 2023-07-24T16:48:24-04:00 Kill off gen_bytearray_addr_access_ops.py The relevant primop descriptions are now generated directly by genprimopcode. This makes progress toward fixing #23490, but it is not a complete fix since there is more than one way in which cabal-reinstall (hadrian/build build-cabal) is broken. - - - - - 02e6a6ce by Matthew Pickering at 2023-07-24T16:49:00-04:00 compiler: Remove unused `containers.h` include Fixes #23712 - - - - - 822ef66b by Matthew Pickering at 2023-07-25T08:44:50-04:00 Fix pretty printing of WARNING pragmas There is still something quite unsavoury going on with WARNING pragma printing because the printing relies on the fact that for decl deprecations the SourceText of WarningTxt is empty. However, I let that lion sleep and just fixed things directly. Fixes #23465 - - - - - e7b38ede by Matthew Pickering at 2023-07-25T08:45:28-04:00 ci-images: Bump to commit which has 9.6 image The test-bootstrap job has been failing for 9.6 because we accidentally used a non-master commit. - - - - - bb408936 by Matthew Pickering at 2023-07-25T08:45:28-04:00 Update bootstrap plans for 9.6.2 and 9.4.5 - - - - - 355e1792 by Alan Zimmerman at 2023-07-26T10:17:32-04:00 EPA: Simplify GHC/Parser.y comb4/comb5 Use the HasLoc instance from Ast.hs to allow comb4/comb5 to work with anything with a SrcSpan Also get rid of some more now unnecessary reLoc calls. - - - - - 9393df83 by Gavin Zhao at 2023-07-26T10:18:16-04:00 compiler: make -ddump-asm work with wasm backend NCG Fixes #23503. Now the `-ddump-asm` flag is respected in the wasm backend NCG, so developers can directly view the generated ASM instead of needing to pass `-S` or `-keep-tmp-files` and manually find & open the assembly file. Ideally, we should be able to output the assembly files in smaller chunks like in other NCG backends. This would also make dumping assembly stats easier. However, this would require a large refactoring, so for short-term debugging purposes I think the current approach works fine. Signed-off-by: Gavin Zhao <git at gzgz.dev> - - - - - 79463036 by Krzysztof Gogolewski at 2023-07-26T10:18:54-04:00 llvm: Restore accidentally deleted code in 0fc5cb97 Fixes #23711 - - - - - 20db7e26 by Rodrigo Mesquita at 2023-07-26T10:19:33-04:00 configure: Default missing options to False when preparing ghc-toolchain Targets This commit fixes building ghc with 9.2 as the boostrap compiler. The ghc-toolchain patch assumed all _STAGE0 options were available, and forgot to account for this missing information in 9.2. Ghc 9.2 does not have in settings whether ar supports -l, hence can't report it with --info (unliked 9.4 upwards). The fix is to default the missing information (we default "ar supports -l" and other missing options to False) - - - - - fac9e84e by Naïm Favier at 2023-07-26T10:20:16-04:00 docs: Fix typo - - - - - 503fd647 by Bartłomiej Cieślar at 2023-07-26T17:23:10-04:00 This MR is an implementation of the proposal #516. It adds a warning -Wincomplete-record-selectors for usages of a record field access function (either a record selector or getField @"rec"), while trying to silence the warning whenever it can be sure that a constructor without the record field would not be invoked (which would otherwise cause the program to fail). For example: data T = T1 | T2 {x :: Bool} f a = x a -- this would throw an error g T1 = True g a = x a -- this would not throw an error h :: HasField "x" r Bool => r -> Bool h = getField @"x" j :: T -> Bool j = h -- this would throw an error because of the `HasField` -- constraint being solved See the tests DsIncompleteRecSel* and TcIncompleteRecSel for more examples of the warning. See Note [Detecting incomplete record selectors] in GHC.HsToCore.Expr for implementation details - - - - - af6fdf42 by Arnaud Spiwack at 2023-07-26T17:23:52-04:00 Fix user-facing label in MR template - - - - - 5d45b92a by Matthew Pickering at 2023-07-27T05:46:46-04:00 ci: Test bootstrapping configurations with full-ci and on marge batches There have been two incidents recently where bootstrapping has been broken by removing support for building with 9.2.*. The process for bumping the minimum required version starts with bumping the configure version and then other CI jobs such as the bootstrap jobs have to be updated. We must not silently bump the minimum required version. Now we are running a slimmed down validate pipeline it seems worthwile to test these bootstrap configurations in the full-ci pipeline. - - - - - 25d4fee7 by Matthew Pickering at 2023-07-27T05:46:46-04:00 bootstrap: Remove ghc-9_2_* plans We are anticipating shortly making it necessary to use ghc-9.4 to boot the compiler. - - - - - 2f66da16 by Matthew Pickering at 2023-07-27T05:46:46-04:00 Update bootstrap plans for ghc-platform and ghc-toolchain dependencies Fixes #23735 - - - - - c8c6eab1 by Matthew Pickering at 2023-07-27T05:46:46-04:00 bootstrap: Disable -selftest flag from bootstrap plans This saves on building one dependency (QuickCheck) which is unecessary for bootstrapping. - - - - - a80ca086 by Andrew Lelechenko at 2023-07-27T05:47:26-04:00 Link reference paper and package from System.Mem.{StableName,Weak} - - - - - a5319358 by David Knothe at 2023-07-28T13:13:10-04:00 Update Match Datatype EquationInfo currently contains a list of the equation's patterns together with a CoreExpr that is to be evaluated after a successful match on this equation. All the match-functions only operate on the first pattern of an equation - after successfully matching it, match is called recursively on the tail of the pattern list. We can express this more clearly and make the code a little more elegant by updating the datatype of EquationInfo as follows: data EquationInfo = EqnMatch { eqn_pat = Pat GhcTc, eqn_rest = EquationInfo } | EqnDone { eqn_rhs = MatchResult CoreExpr } An EquationInfo now explicitly exposes its first pattern which most functions operate on, and exposes the equation that remains after processing the first pattern. An EqnDone signifies an empty equation where the CoreExpr can now be evaluated. - - - - - 86ad1af9 by David Binder at 2023-07-28T13:13:53-04:00 Improve documentation for Data.Fixed - - - - - f8fa1d08 by Ben Gamari at 2023-07-28T13:14:31-04:00 ghc-prim: Use C11 atomics Previously `ghc-prim`'s atomic wrappers used the legacy `__sync_*` family of C builtins. Here we refactor these to rather use the appropriate C11 atomic equivalents, allowing us to be more explicit about the expected ordering semantics. - - - - - 0bfc8908 by Finley McIlwaine at 2023-07-28T18:46:26-04:00 Include -haddock in DynFlags fingerprint The -haddock flag determines whether or not the resulting .hi files contain haddock documentation strings. If the existing .hi files do not contain haddock documentation strings and the user requests them, we should recompile. - - - - - 40425c50 by Andreas Klebinger at 2023-07-28T18:47:02-04:00 Aarch64 NCG: Use encoded immediates for literals. Try to generate instr x2, <imm> instead of mov x1, lit instr x2, x1 When possible. This get's rid if quite a few redundant mov instructions. I believe this causes a metric decrease for LargeRecords as we reduce register pressure. ------------------------- Metric Decrease: LargeRecord ------------------------- - - - - - e9a0fa3f by Andrew Lelechenko at 2023-07-28T18:47:42-04:00 Bump filepath submodule to 1.4.100.4 Resolves #23741 Metric Decrease: MultiComponentModules MultiComponentModulesRecomp MultiLayerModules MultiLayerModulesRecomp T10421 T12234 T12425 T13035 T13701 T13719 T16875 T18304 T18698a T18698b T21839c T9198 TcPlugin_RewritePerf hard_hole_fits Metric decrease on Windows can be probably attributed to https://github.com/haskell/filepath/pull/183 - - - - - ee93edfd by Andrew Lelechenko at 2023-07-28T18:48:21-04:00 Add since pragmas to GHC.IO.Handle.FD - - - - - d0369802 by Simon Peyton Jones at 2023-07-30T09:24:48+01:00 Make the occurrence analyser smarter about join points This MR addresses #22404. There is a big Note Note [Occurrence analysis for join points] that explains it all. Significant changes * New field occ_join_points in OccEnv * The NonRec case of occAnalBind splits into two cases: one for existing join points (which does the special magic for Note [Occurrence analysis for join points], and one for other bindings. * mkOneOcc adds in info from occ_join_points. * All "bring into scope" activity is centralised in the new function `addInScope`. * I made a local data type LocalOcc for use inside the occurrence analyser It is like OccInfo, but lacks IAmDead and IAmALoopBreaker, which in turn makes computationns over it simpler and more efficient. * I found quite a bit of allocation in GHC.Core.Rules.getRules so I optimised it a bit. More minor changes * I found I was using (Maybe Arity) a lot, so I defined a new data type JoinPointHood and used it everwhere. This touches a lot of non-occ-anal files, but it makes everything more perspicuous. * Renamed data constructor WithUsageDetails to WUD, and WithTailUsageDetails to WTUD This also fixes #21128, on the way. --------- Compiler perf ----------- I spent quite a time on performance tuning, so even though it does more than before, the occurrence analyser runs slightly faster on average. Here are the compile-time allocation changes over 0.5% CoOpt_Read(normal) ghc/alloc 766,025,520 754,561,992 -1.5% CoOpt_Singletons(normal) ghc/alloc 759,436,840 762,925,512 +0.5% LargeRecord(normal) ghc/alloc 1,814,482,440 1,799,530,456 -0.8% PmSeriesT(normal) ghc/alloc 68,159,272 67,519,720 -0.9% T10858(normal) ghc/alloc 120,805,224 118,746,968 -1.7% T11374(normal) ghc/alloc 164,901,104 164,070,624 -0.5% T11545(normal) ghc/alloc 79,851,808 78,964,704 -1.1% T12150(optasm) ghc/alloc 73,903,664 71,237,544 -3.6% GOOD T12227(normal) ghc/alloc 333,663,200 331,625,864 -0.6% T12234(optasm) ghc/alloc 52,583,224 52,340,344 -0.5% T12425(optasm) ghc/alloc 81,943,216 81,566,720 -0.5% T13056(optasm) ghc/alloc 294,517,928 289,642,512 -1.7% T13253-spj(normal) ghc/alloc 118,271,264 59,859,040 -49.4% GOOD T15164(normal) ghc/alloc 1,102,630,352 1,091,841,296 -1.0% T15304(normal) ghc/alloc 1,196,084,000 1,166,733,000 -2.5% T15630(normal) ghc/alloc 148,729,632 147,261,064 -1.0% T15703(normal) ghc/alloc 379,366,664 377,600,008 -0.5% T16875(normal) ghc/alloc 32,907,120 32,670,976 -0.7% T17516(normal) ghc/alloc 1,658,001,888 1,627,863,848 -1.8% T17836(normal) ghc/alloc 395,329,400 393,080,248 -0.6% T18140(normal) ghc/alloc 71,968,824 73,243,040 +1.8% T18223(normal) ghc/alloc 456,852,568 453,059,088 -0.8% T18282(normal) ghc/alloc 129,105,576 131,397,064 +1.8% T18304(normal) ghc/alloc 71,311,712 70,722,720 -0.8% T18698a(normal) ghc/alloc 208,795,112 210,102,904 +0.6% T18698b(normal) ghc/alloc 230,320,736 232,697,976 +1.0% BAD T19695(normal) ghc/alloc 1,483,648,128 1,504,702,976 +1.4% T20049(normal) ghc/alloc 85,612,024 85,114,376 -0.6% T21839c(normal) ghc/alloc 415,080,992 410,906,216 -1.0% GOOD T4801(normal) ghc/alloc 247,590,920 250,726,272 +1.3% T6048(optasm) ghc/alloc 95,699,416 95,080,680 -0.6% T783(normal) ghc/alloc 335,323,384 332,988,120 -0.7% T9233(normal) ghc/alloc 709,641,224 685,947,008 -3.3% GOOD T9630(normal) ghc/alloc 965,635,712 948,356,120 -1.8% T9675(optasm) ghc/alloc 444,604,152 428,987,216 -3.5% GOOD T9961(normal) ghc/alloc 303,064,592 308,798,800 +1.9% BAD WWRec(normal) ghc/alloc 503,728,832 498,102,272 -1.1% geo. mean -1.0% minimum -49.4% maximum +1.9% In fact these figures seem to vary between platforms; generally worse on i386 for some reason. The Windows numbers vary by 1% espec in benchmarks where the total allocation is low. But the geom mean stays solidly negative, which is good. The "increase/decrease" list below covers all platforms. The big win on T13253-spj comes because it has a big nest of join points, each occurring twice in the next one. The new occ-anal takes only one iteration of the simplifier to do the inlining; the old one took four. Moreover, we get much smaller code with the new one: New: Result size of Tidy Core = {terms: 429, types: 84, coercions: 0, joins: 14/14} Old: Result size of Tidy Core = {terms: 2,437, types: 304, coercions: 0, joins: 10/10} --------- Runtime perf ----------- No significant changes in nofib results, except a 1% reduction in compiler allocation. Metric Decrease: CoOpt_Read T13253-spj T9233 T9630 T9675 T12150 T21839c LargeRecord MultiComponentModulesRecomp T10421 T13701 T10421 T13701 T12425 Metric Increase: T18140 T9961 T18282 T18698a T18698b T19695 - - - - - 42aa7fbd by Julian Ospald at 2023-07-30T17:22:01-04:00 Improve documentation around IOException and ioe_filename See: * https://github.com/haskell/core-libraries-committee/issues/189 * https://github.com/haskell/unix/pull/279 * https://github.com/haskell/unix/pull/289 - - - - - 33598ecb by Sylvain Henry at 2023-08-01T14:45:54-04:00 JS: implement getMonotonicTime (fix #23687) - - - - - d2bedffd by Bartłomiej Cieślar at 2023-08-01T14:46:40-04:00 Implementation of the Deprecated Instances proposal #575 This commit implements the ability to deprecate certain instances, which causes the compiler to emit the desired deprecation message whenever they are instantiated. For example: module A where class C t where instance {-# DEPRECATED "dont use" #-} C Int where module B where import A f :: C t => t f = undefined g :: Int g = f -- "dont use" emitted here The implementation is as follows: - In the parser, we parse deprecations/warnings attached to instances: instance {-# DEPRECATED "msg" #-} Show X deriving instance {-# WARNING "msg2" #-} Eq Y (Note that non-standalone deriving instance declarations do not support this mechanism.) - We store the resulting warning message in `ClsInstDecl` (respectively, `DerivDecl`). In `GHC.Tc.TyCl.Instance.tcClsInstDecl` (respectively, `GHC.Tc.Deriv.Utils.newDerivClsInst`), we pass on that information to `ClsInst` (and eventually store it in `IfaceClsInst` too). - Finally, when we solve a constraint using such an instance, in `GHC.Tc.Instance.Class.matchInstEnv`, we emit the appropriate warning that was stored in `ClsInst`. Note that we only emit a warning when the instance is used in a different module than it is defined, which keeps the behaviour in line with the deprecation of top-level identifiers. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - d5a65af6 by Ben Gamari at 2023-08-01T14:47:18-04:00 compiler: Style fixes - - - - - 7218c80a by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Fix implicit cast This ensures that Task.h can be built with a C++ compiler. - - - - - d6d5aafc by Ben Gamari at 2023-08-01T14:47:19-04:00 testsuite: Fix warning in hs_try_putmvar001 - - - - - d9eddf7a by Ben Gamari at 2023-08-01T14:47:19-04:00 testsuite: Add AtomicModifyIORef test - - - - - f9eea4ba by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Introduce NO_WARN macro This allows fine-grained ignoring of warnings. - - - - - 497b24ec by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Simplify atomicModifyMutVar2# implementation Previously we would perform a redundant load in the non-threaded RTS in atomicModifyMutVar2# implementation for the benefit of the non-moving GC's write barrier. Eliminate this. - - - - - 52ee082b by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Introduce more principled fence operations - - - - - cd3c0377 by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Introduce SET_INFO_RELAXED - - - - - 6df2352a by Ben Gamari at 2023-08-01T14:47:19-04:00 rts: Style fixes - - - - - 4ef6f319 by Ben Gamari at 2023-08-01T14:47:19-04:00 codeGen/tsan: Rework handling of spilling - - - - - f9ca7e27 by Ben Gamari at 2023-08-01T14:47:19-04:00 hadrian: More debug information - - - - - df4153ac by Ben Gamari at 2023-08-01T14:47:19-04:00 Improve TSAN documentation - - - - - fecae988 by Ben Gamari at 2023-08-01T14:47:19-04:00 hadrian: More selective TSAN instrumentation - - - - - 465a9a0b by Alan Zimmerman at 2023-08-01T14:47:56-04:00 EPA: Provide correct annotation span for ImportDecl Use the whole declaration, rather than just the span of the 'import' keyword. Metric Decrease: T9961 T5205 Metric Increase: T13035 - - - - - ae63d0fa by Bartłomiej Cieślar at 2023-08-01T14:48:40-04:00 Add cases to T23279: HasField for deprecated record fields This commit adds additional tests from ticket #23279 to ensure that we don't regress on reporting deprecated record fields in conjunction with HasField, either when using overloaded record dot syntax or directly through `getField`. Fixes #23279 - - - - - 00fb6e6b by Andreas Klebinger at 2023-08-01T14:49:17-04:00 AArch NCG: Pure refactor Combine some alternatives. Add some line breaks for overly long lines - - - - - 8f3b3b78 by Andreas Klebinger at 2023-08-01T14:49:54-04:00 Aarch ncg: Optimize immediate use for address calculations When the offset doesn't fit into the immediate we now just reuse the general getRegister' code path which is well optimized to compute the offset into a register instead of a special case for CmmRegOff. This means we generate a lot less code under certain conditions which is why performance metrics for these improve. ------------------------- Metric Decrease: T4801 T5321FD T5321Fun ------------------------- - - - - - 74a882dc by MorrowM at 2023-08-02T06:00:03-04:00 Add a RULE to make lookup fuse See https://github.com/haskell/core-libraries-committee/issues/175 Metric Increase: T18282 - - - - - cca74dab by Ben Gamari at 2023-08-02T06:00:39-04:00 hadrian: Ensure that way-flags are passed to CC Previously the way-specific compilation flags (e.g. `-DDEBUG`, `-DTHREADED_RTS`) would not be passed to the CC invocations. This meant that C dependency files would not correctly reflect dependencies predicated on the way, resulting in the rather painful #23554. Closes #23554. - - - - - 622b483c by Jaro Reinders at 2023-08-02T06:01:20-04:00 Native 32-bit Enum Int64/Word64 instances This commits adds more performant Enum Int64 and Enum Word64 instances for 32-bit platforms, replacing the Integer-based implementation. These instances are a copy of the Enum Int and Enum Word instances with minimal changes to manipulate Int64 and Word64 instead. On i386 this yields a 1.5x performance increase and for the JavaScript back end it even yields a 5.6x speedup. Metric Decrease: T18964 - - - - - c8bd7fa4 by Sylvain Henry at 2023-08-02T06:02:03-04:00 JS: fix typos in constants (#23650) - - - - - b9d5bfe9 by Josh Meredith at 2023-08-02T06:02:40-04:00 JavaScript: update MK_TUP macros to use current tuple constructors (#23659) - - - - - 28211215 by Matthew Pickering at 2023-08-02T06:03:19-04:00 ci: Pass -Werror when building hadrian in hadrian-ghc-in-ghci job Warnings when building Hadrian can end up cluttering the output of HLS, and we've had bug reports in the past about these warnings when building Hadrian. It would be nice to turn on -Werror on at least one build of Hadrian in CI to avoid a patch introducing warnings when building Hadrian. Fixes #23638 - - - - - aca20a5d by Ben Gamari at 2023-08-02T06:03:55-04:00 codeGen: Ensure that TSAN is aware of writeArray# write barriers By using a proper release store instead of a fence. - - - - - 453c0531 by Ben Gamari at 2023-08-02T06:03:55-04:00 codeGen: Ensure that array reads have necessary barriers This was the cause of #23541. - - - - - 93a0d089 by Arnaud Spiwack at 2023-08-02T06:04:37-04:00 Add test for #23550 - - - - - 6a2f4a20 by Arnaud Spiwack at 2023-08-02T06:04:37-04:00 Desugar non-recursive lets to non-recursive lets (take 2) This reverts commit 522bd584f71ddeda21efdf0917606ce3d81ec6cc. And takes care of the case that I missed in my previous attempt. Namely the case of an AbsBinds with no type variables and no dictionary variable. Ironically, the comment explaining why non-recursive lets were desugared to recursive lets were pointing specifically at this case as the reason. I just failed to understand that it was until Simon PJ pointed it out to me. See #23550 for more discussion. - - - - - ff81d53f by jade at 2023-08-02T06:05:20-04:00 Expand documentation of List & Data.List This commit aims to improve the documentation and examples of symbols exported from Data.List - - - - - fa4e5913 by Jade at 2023-08-02T06:06:03-04:00 Improve documentation of Semigroup & Monoid This commit aims to improve the documentation of various symbols exported from Data.Semigroup and Data.Monoid - - - - - 1b27e151 by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Check for puns (see ghc#23368) - - - - - 457341fd by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Remove fake exports for (~), List, and Tuple<n> The old reasoning no longer applies, nowadays those names can be mentioned in export lists. - - - - - bf3dcddf by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Fix pretty-printing of Solo and MkSolo - - - - - e2c91bff by Gergő Érdi at 2023-08-03T02:55:46+01:00 Desugar bindings in the context of their evidence Closes #23172 - - - - - 481f4a46 by Gergő Érdi at 2023-08-03T07:48:43+01:00 Add flag to `-f{no-}specialise-incoherents` to enable/disable specialisation of incoherent instances Fixes #23287 - - - - - d751c583 by Profpatsch at 2023-08-04T12:24:26-04:00 base: Improve String & IsString documentation - - - - - 01db1117 by Ben Gamari at 2023-08-04T12:25:02-04:00 rts/win32: Ensure reliability of IO manager shutdown When the Win32 threaded IO manager shuts down, `ioManagerDie` sends an `IO_MANAGER_DIE` event to the IO manager thread using the `io_manager_event` event object. Finally, it will closes the event object, and invalidate `io_manager_event`. Previously, `readIOManagerEvent` would see that `io_manager_event` is invalid and return `0`, suggesting that everything is right with the world. This meant that if `ioManagerDie` invalidated the handle before the event manager was blocked on the event we would end up in a situation where the event manager would never realize it was asked to shut down. Fix this by ensuring that `readIOManagerEvent` instead returns `IO_MANAGER_DIE` when we detect that the event object has been invalidated by `ioManagerDie`. Fixes #23691. - - - - - fdef003a by Ryan Scott at 2023-08-04T12:25:39-04:00 Look through TH splices in splitHsApps This modifies `splitHsApps` (a key function used in typechecking function applications) to look through untyped TH splices and quasiquotes. Not doing so was the cause of #21077. This builds on !7821 by making `splitHsApps` match on `HsUntypedSpliceTop`, which contains the `ThModFinalizers` that must be run as part of invoking the TH splice. See the new `Note [Looking through Template Haskell splices in splitHsApps]` in `GHC.Tc.Gen.Head`. Along the way, I needed to make the type of `splitHsApps.set` slightly more general to accommodate the fact that the location attached to a quasiquote is a `SrcAnn NoEpAnns` rather than a `SrcSpanAnnA`. Fixes #21077. - - - - - e77a0b41 by Ben Gamari at 2023-08-04T12:26:15-04:00 Bump deepseq submodule to 1.5. And bump bounds (cherry picked from commit 1228d3a4a08d30eaf0138a52d1be25b38339ef0b) - - - - - cebb5819 by Ben Gamari at 2023-08-04T12:26:15-04:00 configure: Bump minimal boot GHC version to 9.4 (cherry picked from commit d3ffdaf9137705894d15ccc3feff569d64163e8e) - - - - - 83766dbf by Ben Gamari at 2023-08-04T12:26:15-04:00 template-haskell: Bump version to 2.21.0.0 Bumps exceptions submodule. (cherry picked from commit bf57fc9aea1196f97f5adb72c8b56434ca4b87cb) - - - - - 1211112a by Ben Gamari at 2023-08-04T12:26:15-04:00 base: Bump version to 4.19 Updates all boot library submodules. (cherry picked from commit 433d99a3c24a55b14ec09099395e9b9641430143) - - - - - 3ab5efd9 by Ben Gamari at 2023-08-04T12:26:15-04:00 testsuite: Normalise versions more aggressively In backpack hashes can contain `+` characters. (cherry picked from commit 024861af51aee807d800e01e122897166a65ea93) - - - - - d52be957 by Ben Gamari at 2023-08-04T12:26:15-04:00 testsuite: Declare bkpcabal08 as fragile Due to spurious output changes described in #23648. (cherry picked from commit c046a2382420f2be2c4a657c56f8d95f914ea47b) - - - - - e75a58d1 by Ben Gamari at 2023-08-04T12:26:15-04:00 gitlab-ci: Only mark linker_unload_native as broken in static jobs This test passes on dynamically-linked Alpine. (cherry picked from commit f356a7e8ec8ec3d6b2b30fd175598b9b80065d87) - - - - - 8b176514 by Ben Gamari at 2023-08-04T12:26:15-04:00 testsuite: Update base-exports - - - - - 4b647936 by Ben Gamari at 2023-08-04T12:26:15-04:00 testsuite/interface-stability: normalise versions This eliminates spurious changes from version bumps. - - - - - 0eb54c05 by Ben Gamari at 2023-08-04T12:26:51-04:00 linker/PEi386: Don't sign-extend symbol section number Previously we incorrectly interpreted PE section numbers as signed values. However, this isn't the case; rather, it's an unsigned 16-bit number with a few special bit-patterns (0xffff and 0xfffe). This resulted in #22941 as the linker would conclude that the sections were invalid. Fixing this required quite a bit of refactoring. Closes #22941. - - - - - fd7ce39c by Ben Gamari at 2023-08-04T12:27:28-04:00 testsuite: Mark MulMayOflo_full as broken rather than skipping To ensure that we don't accidentally fix it. See #23742. - - - - - 824092f2 by Ben Gamari at 2023-08-04T12:27:28-04:00 nativeGen/AArch64: Fix sign extension in MulMayOflo Previously the 32-bit implementations of MulMayOflo would use the a non-sensical sign-extension mode. Rewrite these to reflect what gcc 11 produces. Also similarly rework the 16- and 8-bit cases. This now passes the MulMayOflo tests in ghc/test-primops> in all four widths, including the precision tests. Fixes #23721. - - - - - 1b15dbc4 by Jan Hrček at 2023-08-04T12:28:08-04:00 Fix haddock markup in code example for coerce - - - - - 46fd8ced by Vladislav Zavialov at 2023-08-04T12:28:44-04:00 Fix (~) and (@) infix operators in TH splices (#23748) 8168b42a "Whitespace-sensitive bang patterns" allows GHC to accept the following infix operators: a ~ b = () a @ b = () But not if TH is used to generate those declarations: $([d| a ~ b = () a @ b = () |]) -- Test.hs:5:2: error: [GHC-55017] -- Illegal variable name: ‘~’ -- When splicing a TH declaration: (~_0) a_1 b_2 = GHC.Tuple.Prim.() This is easily fixed by modifying `reservedOps` in GHC.Utils.Lexeme - - - - - a1899d8f by Aaron Allen at 2023-08-04T12:29:24-04:00 [#23663] Show Flag Suggestions in GHCi Makes suggestions when using `:set` in GHCi with a misspelled flag. This mirrors how invalid flags are handled when passed to GHC directly. Logic for producing flag suggestions was moved to GHC.Driver.Sesssion so it can be shared. resolves #23663 - - - - - 03f2debd by Rodrigo Mesquita at 2023-08-04T12:30:00-04:00 Improve ghc-toolchain validation configure warning Fixes the layout of the ghc-toolchain validation warning produced by configure. - - - - - de25487d by Alan Zimmerman at 2023-08-04T12:30:36-04:00 EPA make getLocA a synonym for getHasLoc This is basically a no-op change, but allows us to make future changes that can rely on the HasLoc instances And I presume this means we can use more precise functions based on class resolution, so the Windows CI build reports Metric Decrease: T12234 T13035 - - - - - 3ac423b9 by Ben Gamari at 2023-08-04T12:31:13-04:00 ghc-platform: Add upper bound on base Hackage upload requires this. - - - - - 8ba20b21 by Matthew Craven at 2023-08-04T17:22:59-04:00 Adjust and clarify handling of primop effects Fixes #17900; fixes #20195. The existing "can_fail" and "has_side_effects" primop attributes that previously governed this were used in inconsistent and confusingly-documented ways, especially with regard to raising exceptions. This patch replaces them with a single "effect" attribute, which has four possible values: NoEffect, CanFail, ThrowsException, and ReadWriteEffect. These are described in Note [Classifying primop effects]. A substantial amount of related documentation has been re-drafted for clarity and accuracy. In the process of making this attribute format change for literally every primop, several existing mis-classifications were detected and corrected. One of these mis-classifications was tagToEnum#, which is now considered CanFail; this particular fix is known to cause a regression in performance for derived Enum instances. (See #23782.) Fixing this is left as future work. New primop attributes "cheap" and "work_free" were also added, and used in the corresponding parts of GHC.Core.Utils. In view of their actual meaning and uses, `primOpOkForSideEffects` and `exprOkForSideEffects` have been renamed to `primOpOkToDiscard` and `exprOkToDiscard`, respectively. Metric Increase: T21839c - - - - - 41bf2c09 by sheaf at 2023-08-04T17:23:42-04:00 Update inert_solved_dicts for ImplicitParams When adding an implicit parameter dictionary to the inert set, we must make sure that it replaces any previous implicit parameter dictionaries that overlap, in order to get the appropriate shadowing behaviour, as in let ?x = 1 in let ?x = 2 in ?x We were already doing this for inert_cans, but we weren't doing the same thing for inert_solved_dicts, which lead to the bug reported in #23761. The fix is thus to make sure that, when handling an implicit parameter dictionary in updInertDicts, we update **both** inert_cans and inert_solved_dicts to ensure a new implicit parameter dictionary correctly shadows old ones. Fixes #23761 - - - - - 43578d60 by Matthew Craven at 2023-08-05T01:05:36-04:00 Bump bytestring submodule to 0.11.5.1 - - - - - 91353622 by Ben Gamari at 2023-08-05T01:06:13-04:00 Initial commit of Note [Thunks, blackholes, and indirections] This Note attempts to summarize the treatment of thunks, thunk update, and indirections. This fell out of work on #23185. - - - - - 8d686854 by sheaf at 2023-08-05T01:06:54-04:00 Remove zonk in tcVTA This removes the zonk in GHC.Tc.Gen.App.tc_inst_forall_arg and its accompanying Note [Visible type application zonk]. Indeed, this zonk is no longer necessary, as we no longer maintain the invariant that types are well-kinded without zonking; only that typeKind does not crash; see Note [The Purely Kinded Type Invariant (PKTI)]. This commit removes this zonking step (as well as a secondary zonk), and replaces the aforementioned Note with the explanatory Note [Type application substitution], which justifies why the substitution performed in tc_inst_forall_arg remains valid without this zonking step. Fixes #23661 - - - - - 19dea673 by Ben Gamari at 2023-08-05T01:07:30-04:00 Bump nofib submodule Ensuring that nofib can be build using the same range of bootstrap compilers as GHC itself. - - - - - aa07402e by Luite Stegeman at 2023-08-05T23:15:55+09:00 JS: Improve compatibility with recent emsdk The JavaScript code in libraries/base/jsbits/base.js had some hardcoded offsets for fields in structs, because we expected the layout of the data structures to remain unchanged. Emsdk 3.1.42 changed the layout of the stat struct, breaking this assumption, and causing code in .hsc files accessing the stat struct to fail. This patch improves compatibility with recent emsdk by removing the assumption that data layouts stay unchanged: 1. offsets of fields in structs used by JavaScript code are now computed by the configure script, so both the .js and .hsc files will automatically use the new layout if anything changes. 2. the distrib/configure script checks that the emsdk version on a user's system is the same version that a bindist was booted with, to avoid data layout inconsistencies See #23641 - - - - - b938950d by Luite Stegeman at 2023-08-07T06:27:51-04:00 JS: Fix missing local variable declarations This fixes some missing local variable declarations that were found by running the testsuite in strict mode. Fixes #23775 - - - - - 6c0e2247 by sheaf at 2023-08-07T13:31:21-04:00 Update Haddock submodule to fix #23368 This submodule update adds the following three commits: bbf1c8ae - Check for puns 0550694e - Remove fake exports for (~), List, and Tuple<n> 5877bceb - Fix pretty-printing of Solo and MkSolo These commits fix the issues with Haddock HTML rendering reported in ticket #23368. Fixes #23368 - - - - - 5b5be3ea by Matthew Pickering at 2023-08-07T13:32:00-04:00 Revert "Bump bytestring submodule to 0.11.5.1" This reverts commit 43578d60bfc478e7277dcd892463cec305400025. Fixes #23789 - - - - - 01961be3 by Ben Gamari at 2023-08-08T02:47:14-04:00 configure: Derive library version from ghc-prim.cabal.in Since ghc-prim.cabal is now generated by Hadrian, we cannot depend upon it. Closes #23726. - - - - - 3b373838 by Ryan Scott at 2023-08-08T02:47:49-04:00 tcExpr: Push expected types for untyped TH splices inwards In !10911, I deleted a `tcExpr` case for `HsUntypedSplice` in favor of a much simpler case that simply delegates to `tcApp`. Although this passed the test suite at the time, this was actually an error, as the previous `tcExpr` case was critically pushing the expected type inwards. This actually matters for programs like the one in #23796, which GHC would not accept with type inference alone—we need full-blown type _checking_ to accept these. I have added back the previous `tcExpr` case for `HsUntypedSplice` and now explain why we have two different `HsUntypedSplice` cases (one in `tcExpr` and another in `splitHsApps`) in `Note [Looking through Template Haskell splices in splitHsApps]` in `GHC.Tc.Gen.Head`. Fixes #23796. - - - - - 0ef1d8ae by sheaf at 2023-08-08T21:26:51-04:00 Compute all emitted diagnostic codes This commit introduces in GHC.Types.Error.Codes the function constructorCodes :: forall diag. (...) => Map DiagnosticCode String which computes a collection of all the diagnostic codes that correspond to a particular type. In particular, we can compute the collection of all diagnostic codes emitted by GHC using the invocation constructorCodes @GhcMessage We then make use of this functionality in the new "codes" test which checks consistency and coverage of GHC diagnostic codes. It performs three checks: - check 1: all non-outdated GhcDiagnosticCode equations are statically used. - check 2: all outdated GhcDiagnosticCode equations are statically unused. - check 3: all statically used diagnostic codes are covered by the testsuite (modulo accepted exceptions). - - - - - 4bc7b1e5 by Fraser Tweedale at 2023-08-08T21:27:32-04:00 numberToRangedRational: fix edge cases for exp ≈ (maxBound :: Int) Currently a negative exponent less than `minBound :: Int` results in Infinity, which is very surprising and obviously wrong. ``` λ> read "1e-9223372036854775808" :: Double 0.0 λ> read "1e-9223372036854775809" :: Double Infinity ``` There is a further edge case where the exponent can overflow when increased by the number of tens places in the integer part, or underflow when decreased by the number of leading zeros in the fractional part if the integer part is zero: ``` λ> read "10e9223372036854775807" :: Double 0.0 λ> read "0.01e-9223372036854775808" :: Double Infinity ``` To resolve both of these issues, perform all arithmetic and comparisons involving the exponent in type `Integer`. This approach also eliminates the need to explicitly check the exponent against `maxBound :: Int` and `minBound :: Int`, because the allowed range of the exponent (i.e. the result of `floatRange` for the target floating point type) is certainly within those bounds. This change implements CLC proposal 192: https://github.com/haskell/core-libraries-committee/issues/192 - - - - - 6eab07b2 by Alan Zimmerman at 2023-08-08T21:28:10-04:00 EPA: Remove Location from WarningTxt source This is not needed. - - - - - 1a98d673 by Sebastian Graf at 2023-08-09T16:24:29-04:00 Cleanup a TODO introduced in 1f94e0f7 The change must have slipped through review of !4412 - - - - - 2274abc8 by Sebastian Graf at 2023-08-09T16:24:29-04:00 More explicit strictness in GHC.Real - - - - - ce8aa54c by Sebastian Graf at 2023-08-09T16:24:30-04:00 exprIsTrivial: Factor out shared implementation The duplication between `exprIsTrivial` and `getIdFromTrivialExpr_maybe` has been bugging me for a long time. This patch introduces an inlinable worker function `trivial_expr_fold` acting as the single, shared decision procedure of triviality. It "returns" a Church-encoded `Maybe (Maybe Id)`, so when it is inlined, it fuses to similar code as before. (Better code, even, in the case of `getIdFromTrivialExpr` which presently allocates a `Just` constructor that cancels away after this patch.) - - - - - d004a36d by Sebastian Graf at 2023-08-09T16:24:30-04:00 Simplify: Simplification of arguments in a single function The Simplifier had a function `simplArg` that wasn't called in `rebuildCall`, which seems to be the main way to simplify args. Hence I consolidated the code path to call `simplArg`, too, renaming to `simplLazyArg`. - - - - - 8c73505e by Sebastian Graf at 2023-08-09T16:24:30-04:00 Core.Ppr: Omit case binder for empty case alternatives A minor improvement to pretty-printing - - - - - d8d993f1 by Sebastian Graf at 2023-08-09T16:24:30-04:00 Disable tests RepPolyWrappedVar2 and RepPolyUnsafeCoerce1 in JS backend ... because those coerce between incompatible/unknown PrimReps. - - - - - f06e87e4 by Sebastian Graf at 2023-08-09T16:24:30-04:00 Inlining literals into boring contexts is OK - - - - - 4a6b7c87 by Sebastian Graf at 2023-08-09T16:24:30-04:00 Clarify floating of unsafeEqualityProofs (#23754) - - - - - b0f4752e by Sebastian Graf at 2023-08-09T16:24:30-04:00 Kill SetLevel.notWorthFloating.is_triv (#23270) We have had it since b84ba676034, when it operated on annotated expressions. Nowadays it operates on vanilla `CoreExpr` though, so we should just call `exprIsTrivial`; thus handling empty cases and string literals correctly. - - - - - 7e0c8b3b by Sebastian Graf at 2023-08-09T16:24:30-04:00 ANFise string literal arguments (#23270) This instates the invariant that a trivial CoreExpr translates to an atomic StgExpr. Nice. Annoyingly, in -O0 we sometimes generate ``` foo = case "blah"# of sat { __DEFAULT -> unpackCString# sat } ``` which makes it a bit harder to spot that we can emit a standard `stg_unpack_cstring` thunk. Fixes #23270. - - - - - 357f2738 by Sebastian Graf at 2023-08-09T16:24:30-04:00 Deactivate -fcatch-nonexhaustive-cases in ghc-bignum (#23345) - - - - - 59202c80 by Sebastian Graf at 2023-08-09T16:24:30-04:00 CorePrep: Eliminate EmptyCase and unsafeEqualityProof in CoreToStg instead We eliminate EmptyCase by way of `coreToStg (Case e _ _ []) = coreToStg e` now. The main reason is that it plays far better in conjunction with eta expansion (as we aim to do for arguments in CorePrep, #23083), because we can discard any arguments, `(case e of {}) eta == case e of {}`, whereas in `(e |> co) eta` it's impossible to discard the argument. We do also give the same treatment to unsafeCoerce proofs and treat them as trivial iff their RHS is trivial. It is also both much simpler to describe than the previous mechanism of emitting an unsafe coercion and simpler to implement, removing quite a bit of commentary and `CorePrepProv`. In the ghc/alloc perf test `LargeRecord`, we introduce an additional Simplifier iteration due to #17910. E.g., FloatOut produces a binding ``` lvl_s6uK [Occ=Once1] :: GHC.Types.Int [LclId] lvl_s6uK = GHC.Types.I# 2# lvl_s6uL [Occ=Once1] :: GHC.Types.Any [LclId] lvl_s6uL = case Unsafe.Coerce.unsafeEqualityProof ... of { Unsafe.Coerce.UnsafeRefl v2_i6tr -> lvl_s6uK `cast` (... v2_i6tr ...) } ``` That occurs once and hence is pre-inlined unconditionally in the next Simplifier pass. It's non-trivial to find a way around that, but not really harmful otherwise. Hence we accept a 1.2% increase on some architectures. Metric Increase: LargeRecord - - - - - 00d31188 by Sebastian Graf at 2023-08-09T16:24:30-04:00 CorePrep: Eta expand arguments (#23083) Previously, we'd only eta expand let bindings and lambdas, now we'll also eta expand arguments such as in T23083: ```hs g f h = f (h `seq` (h $)) ``` Unless `-fpedantic-bottoms` is set, we'll now transform to ```hs g f h = f (\eta -> h eta) ``` in CorePrep. See the new `Note [Eta expansion of arguments in CorePrep]` for the details. We only do this optimisation with -O2 because we saw 2-3% ghc/alloc regressions in T4801 and T5321FD. Fixes #23083. - - - - - bf885d7a by Matthew Craven at 2023-08-09T16:25:07-04:00 Bump bytestring submodule to 0.11.5, again Fixes #23789. The bytestring commit used here is unreleased; a release can be made when necessary. - - - - - 7acbf0fd by Sven Tennie at 2023-08-10T19:17:11-04:00 Serialize CmmRetInfo in .rodata The handling of case was missing. - - - - - 0c3136f2 by Sven Tennie at 2023-08-10T19:17:11-04:00 Reference StgRetFun payload by its struct field address This is easier to grasp than relative pointer offsets. - - - - - f68ff313 by Sven Tennie at 2023-08-10T19:17:11-04:00 Better variable name: u -> frame The 'u' was likely introduced by copy'n'paste. - - - - - 0131bb7f by Sven Tennie at 2023-08-10T19:17:11-04:00 Make checkSTACK() public Such that it can also be used in tests. - - - - - 7b6e1e53 by Sven Tennie at 2023-08-10T19:17:11-04:00 Publish stack related fields in DerivedConstants.h These will be used in ghc-heap to decode these parts of the stack. - - - - - 907ed054 by Sven Tennie at 2023-08-10T19:17:11-04:00 ghc-heap: Decode StgStack and its stack frames Previously, ghc-heap could only decode heap closures. The approach is explained in detail in note [Decoding the stack]. - - - - - 6beb6ac2 by Sven Tennie at 2023-08-10T19:17:11-04:00 Remove RetFunType from RetFun stack frame representation It's a technical detail. The single usage is replaced by a predicate. - - - - - 006bb4f3 by Sven Tennie at 2023-08-10T19:17:11-04:00 Better parameter name The call-site uses the term "offset", too. - - - - - d4c2c1af by Sven Tennie at 2023-08-10T19:17:11-04:00 Make closure boxing pure There seems to be no need to do something complicated. However, the strictness of the closure pointer matters, otherwise a thunk gets decoded. - - - - - 8d8426c9 by Sven Tennie at 2023-08-10T19:17:11-04:00 Document entertainGC in test It wasn't obvious why it's there and what its role is. Also, increase the "entertainment level" a bit. I checked in STG and Cmm dumps that this really generates closures (and is not e.g. constant folded away.) - - - - - cc52c358 by Finley McIlwaine at 2023-08-10T19:17:47-04:00 Add -dipe-stats flag This is useful for seeing which info tables have information. - - - - - 261c4acb by Finley McIlwaine at 2023-08-10T19:17:47-04:00 Add -finfo-table-map-with-fallback -finfo-table-map-with-stack The -fno-info-table-map-with-stack flag omits STACK info tables from the info table map, and the -fno-info-table-map-with-fallback flag omits info tables with defaulted source locations from the map. In a test on the Agda codebase the build results were about 7% smaller when both of those types of tables were omitted. Adds a test that verifies that passing each combination of these flags results in the correct output for -dipe-stats, which is disabled for the js backend since profiling is not implemented. This commit also refactors a lot of the logic around extracting info tables from the Cmm results and building the info table map. This commit also fixes some issues in the users guide rst source to fix warnings that were noticed while debugging the documentation for these flags. Fixes #23702 - - - - - d7047e0d by Jaro Reinders at 2023-08-14T04:41:42-04:00 Add changelog entry for specialised Enum Int64/Word64 instances - - - - - 52f5e8fb by cydparser at 2023-08-14T04:42:20-04:00 Fix -ddump-to-file and -ddump-timings interaction (#20316) - - - - - 1274c5d6 by cydparser at 2023-08-14T04:42:20-04:00 Update release notes (#20316) - - - - - 8e699b23 by Matthew Pickering at 2023-08-14T10:44:47-04:00 base: Add changelog entry for CLC #188 This proposal modified the implementations of copyBytes, moveBytes and fillBytes (as detailed in the proposal) https://github.com/haskell/core-libraries-committee/issues/188 - - - - - 026f040a by Matthew Pickering at 2023-08-14T10:45:23-04:00 packaging: Build manpage in separate directory to other documentation We were installing two copies of the manpage: * One useless one in the `share/doc` folder, because we copy the doc/ folder into share/ * The one we deliberately installed into `share/man` etc The solution is to build the manpage into the `manpage` directory when building the bindist, and then just install it separately. Fixes #23707 - - - - - 524c60c8 by Bartłomiej Cieślar at 2023-08-14T13:46:33-04:00 Report deprecated fields bound by record wildcards when used This commit ensures that we emit the appropriate warnings when a deprecated record field bound by a record wildcard is used. For example: module A where data Foo = Foo {x :: Int, y :: Bool, z :: Char} {-# DEPRECATED x "Don't use x" #-} {-# WARNING y "Don't use y" #-} module B where import A foo (Foo {..}) = x This will cause us to emit a "Don't use x" warning, with location the location of the record wildcard. Note that we don't warn about `y`, because it is unused in the RHS of `foo`. Fixes #23382 - - - - - d6130065 by Matthew Pickering at 2023-08-14T13:47:11-04:00 Add zstd suffix to jobs which rely on zstd This was causing some confusion as the job was named simply "x86_64-linux-deb10-validate", which implies a standard configuration rather than any dependency on libzstd. - - - - - e24e44fc by Matthew Pickering at 2023-08-14T13:47:11-04:00 ci: Always run project-version job This is needed for the downstream test-primops pipeline to workout what the version of a bindist produced by a pipeline is. - - - - - f17b9d62 by Matthew Pickering at 2023-08-14T13:47:11-04:00 gen_ci: Rework how jobs-metadata.json is generated * We now represent a job group a triple of Maybes, which makes it easier to work out when jobs are enabled/disabled on certain pipelines. ``` data JobGroup a = StandardTriple { v :: Maybe (NamedJob a) , n :: Maybe (NamedJob a) , r :: Maybe (NamedJob a) } ``` * `jobs-metadata.json` generation is reworked using the following algorithm. - For each pipeline type, find all the platforms we are doing builds for. - Select one build per platform - Zip together the results This way we can choose different pipelines for validate/nightly/release which makes the metadata also useful for validate pipelines. This feature is used by the test-primops downstream CI in order to select the right bindist for testing validate pipelines. This makes it easier to inspect which jobs are going to be enabled on a particular pipeline. - - - - - f9a5563d by Matthew Pickering at 2023-08-14T13:47:11-04:00 gen_ci: Rules rework In particular we now distinguish between whether we are dealing with a Nightly/Release pipeline (which labels don't matter for) and a validate pipeline where labels do matter. The overall goal here is to allow a disjunction of labels for validate pipelines, for example, > Run a job if we have the full-ci label or test-primops label Therefore the "ValidateOnly" rules are treated as a set of disjunctions rather than conjunctions like before. What this means in particular is that if we want to ONLY run a job if a label is set, for example, "FreeBSD" label then we have to override the whole label set. Fixes #23772 - - - - - d54b0c1d by Matthew Pickering at 2023-08-14T13:47:11-04:00 ci: set -e for lint-ci-config scripts - - - - - 994a9b35 by Matthew Pickering at 2023-08-14T13:47:11-04:00 ci: Fix job metadata generation - - - - - e194ed2b by Ben Gamari at 2023-08-15T00:58:09-04:00 users-guide: Note that GHC2021 doesn't include ExplicitNamespaces As noted in #23801. - - - - - d814bda9 by Ben Gamari at 2023-08-15T05:43:53-04:00 users-guide: Support both distutils and packaging As noted in #23818, some old distributions (e.g. Debian 9) only include `distutils` while newer distributions only include `packaging`. Fixes #23818. - - - - - 1726db3f by Ben Gamari at 2023-08-15T05:43:53-04:00 users-guide: Ensure extlinks is compatible with Sphinx <4 The semantics of the `extlinks` attribute annoyingly changed in Sphinx 4. Reflect this in our configuration. See #22690. Fixes #23807. - - - - - 173338cf by Matthew Pickering at 2023-08-15T22:00:24-04:00 ci: Run full-ci on master and release branches Fixes #23737 - - - - - bdab6898 by Andrew Lelechenko at 2023-08-15T22:01:03-04:00 Add @since pragmas for Data.Ord.clamp and GHC.Float.clamp - - - - - 662d351b by Matthew Pickering at 2023-08-16T09:35:04-04:00 ghc-toolchain: Match CPP args with configure script At the moment we need ghc-toolchain to precisely match the output as provided by the normal configure script. The normal configure script (FP_HSCPP_CMD_WITH_ARGS) branches on whether we are using clang or gcc so we match that logic exactly in ghc-toolchain. The old implementation (which checks if certain flags are supported) is better but for now we have to match to catch any potential errors in the configuration. Ticket: #23720 - - - - - 09c6759e by Matthew Pickering at 2023-08-16T09:35:04-04:00 configure: Fix `-Wl,--no-as-needed` check The check was failing because the args supplied by $$1 were quoted which failed because then the C compiler thought they were an input file. Fixes #23720 - - - - - 2129678b by Matthew Pickering at 2023-08-16T09:35:04-04:00 configure: Add flag which turns ghc-toolchain check into error We want to catch these errors in CI, but first we need to a flag which turns this check into an error. - - - - - 6e2aa8e0 by Matthew Pickering at 2023-08-16T09:35:04-04:00 ci: Enable --enable-strict-ghc-toolchain-check for all CI jobs This will cause any CI job to fail if we have a mismatch between what ghc-toolchain reports and what ./configure natively reports. Fixing these kinds of issues is highest priority for 9.10 release. - - - - - 12d39e24 by Rodrigo Mesquita at 2023-08-16T09:35:04-04:00 Pass user-specified options to ghc-toolchain The current user interface to configuring target toolchains is `./configure`. In !9263 we added a new tool to configure target toolchains called `ghc-toolchain`, but the blessed way of creating these toolchains is still through configure. However, we were not passing the user-specified options given with the `./configure` invocation to the ghc-toolchain tool. This commit remedies that by storing the user options and environment variables in USER_* variables, which then get passed to GHC-toolchain. The exception to the rule is the windows bundled toolchain, which overrides the USER_* variables with whatever flags the windows bundled toolchain requires to work. We consider the bundled toolchain to be effectively the user specifying options, since the actual user delegated that configuration work. Closes #23678 - - - - - f7b3c3a0 by Rodrigo Mesquita at 2023-08-16T09:35:04-04:00 ghc-toolchain: Parse javascript and ghcjs as a Arch and OS - - - - - 8a0ae4ee by Rodrigo Mesquita at 2023-08-16T09:35:04-04:00 ghc-toolchain: Fix ranlib option - - - - - 31e9ec96 by Rodrigo Mesquita at 2023-08-16T09:35:04-04:00 Check Link Works with -Werror - - - - - bc1998b3 by Matthew Pickering at 2023-08-16T09:35:04-04:00 Only check for no_compact_unwind support on darwin While writing ghc-toolchain we noticed that the FP_PROG_LD_NO_COMPACT_UNWIND check is subtly wrong. Specifically, we pass -Wl,-no_compact_unwind to cc. However, ld.gold interprets this as -n o_compact_unwind, which is a valid argument. Fixes #23676 - - - - - 0283f36e by Matthew Pickering at 2023-08-16T09:35:04-04:00 Add some javascript special cases to ghc-toolchain On javascript there isn't a choice of toolchain but some of the configure checks were not accurately providing the correct answer. 1. The linker was reported as gnu LD because the --version output mentioned gnu LD. 2. The --target flag makes no sense on javascript but it was just ignored by the linker, so we add a special case to stop ghc-toolchain thinking that emcc supports --target when used as a linker. - - - - - a48ec5f8 by Matthew Pickering at 2023-08-16T09:35:04-04:00 check for emcc in gnu_LD check - - - - - 50df2e69 by Matthew Pickering at 2023-08-16T09:35:04-04:00 Add ldOverrideWhitelist to only default to ldOverride on windows/linux On some platforms - ie darwin, javascript etc we really do not want to allow the user to use any linker other than the default one as this leads to all kinds of bugs. Therefore it is a bit more prudant to add a whitelist which specifies on which platforms it might be possible to use a different linker. - - - - - a669a39c by Matthew Pickering at 2023-08-16T09:35:04-04:00 Fix plaform glob in FPTOOLS_SET_C_LD_FLAGS A normal triple may look like x86_64-unknown-linux but when cross-compiling you get $target set to a quad such as.. aarch64-unknown-linux-gnu Which should also match this check. - - - - - c52b6769 by Matthew Pickering at 2023-08-16T09:35:04-04:00 ghc-toolchain: Pass ld-override onto ghc-toolchain - - - - - 039b484f by Matthew Pickering at 2023-08-16T09:35:04-04:00 ld override: Make whitelist override user given option - - - - - d2b63cbc by Matthew Pickering at 2023-08-16T09:35:05-04:00 ghc-toolchain: Add format mode to normalise differences before diffing. The "format" mode takes an "--input" and "--ouput" target file and formats it. This is intended to be useful on windows where the configure/ghc-toolchain target files can't be diffed very easily because the path separators are different. - - - - - f2b39e4a by Matthew Pickering at 2023-08-16T09:35:05-04:00 ghc-toolchain: Bump ci-images commit to get new ghc-wasm-meta We needed to remove -Wno-unused-command-line-argument from the arguments passed in order for the configure check to report correctly. See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/10976#note_516335 - - - - - 92103830 by Matthew Pickering at 2023-08-16T09:35:05-04:00 configure: MergeObjsCmd - distinguish between empty string and unset variable If `MergeObjsCmd` is explicitly set to the empty string then we should assume that MergeObjs is just not supported. This is especially important for windows where we set MergeObjsCmd to "" in m4/fp_setup_windows_toolchain.m4. - - - - - 3500bb2c by Matthew Pickering at 2023-08-16T09:35:05-04:00 configure: Add proper check to see if object merging works - - - - - 08c9a014 by Matthew Pickering at 2023-08-16T09:35:05-04:00 ghc-toolchain: If MergeObjsCmd is not set, replace setting with Nothing If the user explicitly chooses to not set a MergeObjsCmd then it is correct to use Nothing for tgtMergeObjs field in the Target file. - - - - - c9071d94 by Matthew Pickering at 2023-08-16T09:35:05-04:00 HsCppArgs: Augment the HsCppOptions This is important when we pass -I when setting up the windows toolchain. - - - - - 294a6d80 by Matthew Pickering at 2023-08-16T09:35:05-04:00 Set USER_CPP_ARGS when setting up windows toolchain - - - - - bde4b5d4 by Rodrigo Mesquita at 2023-08-16T09:35:05-04:00 Improve handling of Cc as a fallback - - - - - f4c1c3a3 by Rodrigo Mesquita at 2023-08-16T09:35:05-04:00 ghc-toolchain: Configure Cpp and HsCpp correctly when user specifies flags In ghc-toolchain, we were only /not/ configuring required flags when the user specified any flags at all for the of the HsCpp and Cpp tools. Otherwise, the linker takes into consideration the user specified flags to determine whether to search for a better linker implementation, but already configured the remaining GHC and platform-specific flags regardless of the user options. Other Tools consider the user options as a baseline for further configuration (see `findProgram`), so #23689 is not applicable. Closes #23689 - - - - - bfe4ffac by Matthew Pickering at 2023-08-16T09:35:05-04:00 CPP_ARGS: Put new options after user specified options This matches up with the behaviour of ghc-toolchain, so that the output of both matches. - - - - - a6828173 by Gergő Érdi at 2023-08-16T09:35:41-04:00 If a defaulting plugin made progress, re-zonk wanteds before built-in defaulting Fixes #23821. - - - - - e2b38115 by Sylvain Henry at 2023-08-17T07:54:06-04:00 JS: implement openat(AT_FDCWD...) (#23697) Use `openSync` to implement `openat(AT_FDCWD...)`. - - - - - a975c663 by sheaf at 2023-08-17T07:54:47-04:00 Use unsatisfiable for missing methods w/ defaults When a class instance has an Unsatisfiable constraint in its context and the user has not explicitly provided an implementation of a method, we now always provide a RHS of the form `unsatisfiable @msg`, even if the method has a default definition available. This ensures that, when deferring type errors, users get the appropriate error message instead of a possible runtime loop, if class default methods were defined recursively. Fixes #23816 - - - - - 45ca51e5 by Ben Gamari at 2023-08-17T15:16:41-04:00 ghc-internal: Initial commit of the skeleton - - - - - 88bbf8c5 by Ben Gamari at 2023-08-17T15:16:41-04:00 ghc-experimental: Initial commit - - - - - 664468c0 by Ben Gamari at 2023-08-17T15:17:17-04:00 testsuite/cloneStackLib: Fix incorrect format specifiers - - - - - eaa835bb by Ben Gamari at 2023-08-17T15:17:17-04:00 rts/ipe: Fix const-correctness of IpeBufferListNode Both info tables and the string table should be `const` - - - - - 78f6f6fd by Ben Gamari at 2023-08-17T15:17:17-04:00 nonmoving: Drop dead debugging utilities These are largely superceded by support in the ghc-utils GDB extension. - - - - - 3f6e8f42 by Ben Gamari at 2023-08-17T15:17:17-04:00 nonmoving: Refactor management of mark thread Here we refactor that treatment of the worker thread used by the nonmoving GC for concurrent marking, avoiding creating a new thread with every major GC cycle. As well, the new scheme is considerably easier to reason about, consolidating all state in one place, accessed via a small set of accessors with clear semantics. - - - - - 88c32b7d by Ben Gamari at 2023-08-17T15:17:17-04:00 testsuite: Skip T23221 in nonmoving GC ways This test is very dependent upon GC behavior. - - - - - 381cfaed by Ben Gamari at 2023-08-17T15:17:17-04:00 ghc-heap: Don't expose stack dirty and marking fields These are GC metadata and are not relevant to the end-user. Moreover, they are unstable which makes ghc-heap harder to test than necessary. - - - - - 16828ca5 by Luite Stegeman at 2023-08-21T18:42:53-04:00 bump process submodule to include macOS fix and JS support - - - - - b4d5f6ed by Matthew Pickering at 2023-08-21T18:43:29-04:00 ci: Add support for triggering test-primops pipelines This commit adds 4 ways to trigger testing with test-primops. 1. Applying the ~test-primops label to a validate pipeline. 2. A manually triggered job on a validate pipeline 3. A nightly pipeline job 4. A release pipeline job Fixes #23695 - - - - - 32c50daa by Matthew Pickering at 2023-08-21T18:43:29-04:00 Add test-primops label support The test-primops CI job requires some additional builds in the validation pipeline, so we make sure to enable these jobs when test-primops label is set. - - - - - 73ca8340 by Matthew Pickering at 2023-08-21T18:43:29-04:00 Revert "Aarch ncg: Optimize immediate use for address calculations" This reverts commit 8f3b3b78a8cce3bd463ed175ee933c2aabffc631. See #23793 - - - - - 5546ad9e by Matthew Pickering at 2023-08-21T18:43:29-04:00 Revert "AArch NCG: Pure refactor" This reverts commit 00fb6e6b06598752414a0b9a92840fb6ca61338d. See #23793 - - - - - 02dfcdc2 by Matthew Pickering at 2023-08-21T18:43:29-04:00 Revert "Aarch64 NCG: Use encoded immediates for literals." This reverts commit 40425c5021a9d8eb5e1c1046e2d5fa0a2918f96c. See #23793 ------------------------- Metric Increase: T4801 T5321FD T5321Fun ------------------------- - - - - - 7be4a272 by Matthew Pickering at 2023-08-22T08:55:20+01:00 ci: Remove manually triggered test-ci job This doesn't work on slimmed down pipelines as the needed jobs don't exist. If you want to run test-primops then apply the label. - - - - - 76a4d11b by Jaro Reinders at 2023-08-22T08:08:13-04:00 Remove Ptr example from roles docs - - - - - 069729d3 by Bryan Richter at 2023-08-22T08:08:49-04:00 Guard against duplicate pipelines in forks - - - - - f861423b by Rune K. Svendsen at 2023-08-22T08:09:35-04:00 dump-decls: fix "Ambiguous module name"-error Fixes errors of the following kind, which happen when dump-decls is run on a package that contains a module name that clashes with that of another package. ``` dump-decls: <no location info>: error: Ambiguous module name `System.Console.ANSI.Types': it was found in multiple packages: ansi-terminal-0.11.4 ansi-terminal-types-0.11.5 ``` - - - - - edd8bc43 by Krzysztof Gogolewski at 2023-08-22T12:31:20-04:00 Fix MultiWayIf linearity checking (#23814) Co-authored-by: Thomas BAGREL <thomas.bagrel at tweag.io> - - - - - 4ba088d1 by konsumlamm at 2023-08-22T12:32:02-04:00 Update `Control.Concurrent.*` documentation - - - - - 015886ec by ARATA Mizuki at 2023-08-22T15:13:13-04:00 Support 128-bit SIMD on AArch64 via LLVM backend - - - - - 52a6d868 by Krzysztof Gogolewski at 2023-08-22T15:13:51-04:00 Testsuite cleanup - Remove misleading help text in perf_notes, ways are not metrics - Remove no_print_summary - this was used for Phabricator - In linters tests, run 'git ls-files' just once. Previously, it was called on each has_ls_files() - Add ghc-prim.cabal to gitignore, noticed in #23726 - Remove ghc-prim.cabal, it was accidentally committed in 524c60c8cd - - - - - ab40aa52 by Alan Zimmerman at 2023-08-22T15:14:28-04:00 EPA: Use Introduce [DeclTag] in AnnSortKey The AnnSortKey is used to keep track of the order of declarations for printing when the container has split them apart. This applies to HsValBinds and ClassDecl, ClsInstDecl. When making modifications to the list of declarations, the new order must be captured for when it must be printed. For each list of declarations (binds and sigs for a HsValBind) we can just store the list in order. To recreate the list when printing, we must merge them, and this is what the AnnSortKey records. It used to be indexed by SrcSpan, we now simply index by a marker as to which list to take the next item from. - - - - - e7db36c1 by sheaf at 2023-08-23T08:41:28-04:00 Don't attempt pattern synonym error recovery This commit gets rid of the pattern synonym error recovery mechanism (recoverPSB). The rationale is that the fake pattern synonym binding that the recovery mechanism introduced could lead to undesirable knock-on errors, and it isn't really feasible to conjure up a satisfactory binding as pattern synonyms can be used both in expressions and patterns. See Note [Pattern synonym error recovery] in GHC.Tc.TyCl.PatSyn. It isn't such a big deal to eagerly fail compilation on a pattern synonym that doesn't typecheck anyway. Fixes #23467 - - - - - 6ccd9d65 by Ben Gamari at 2023-08-23T08:42:05-04:00 base: Don't use Data.ByteString.Internals.memcpy This function is now deprecated from `bytestring`. Use `Foreign.Marshal.Utils.copyBytes` instead. Fixes #23880. - - - - - 0bfa0031 by Matthew Pickering at 2023-08-23T13:43:48-04:00 hadrian: Uniformly pass buildOptions to all builders in runBuilder In Builder.hs, runBuilderWith mostly ignores the buildOptions in BuildInfo. This leads to hard to diagnose bugs as any build options you pass with runBuilderWithCmdOptions are ignored for many builders. Solution: Uniformly pass buildOptions to the invocation of cmd. Fixes #23845 - - - - - 9cac8f11 by Matthew Pickering at 2023-08-23T13:43:48-04:00 Abstract windows toolchain setup This commit splits up the windows toolchain setup logic into two functions. * FP_INSTALL_WINDOWS_TOOLCHAIN - deals with downloading the toolchain if it isn't already downloaded * FP_SETUP_WINDOWS_TOOLCHAIN - sets the environment variables to point to the correct place FP_SETUP_WINDOWS_TOOLCHAIN is abstracted from the location of the mingw toolchain and also the eventual location where we will install the toolchain in the installed bindist. This is the first step towards #23608 - - - - - 6c043187 by Matthew Pickering at 2023-08-23T13:43:48-04:00 Generate build.mk for bindists The config.mk.in script was relying on some variables which were supposed to be set by build.mk but therefore never were when used to install a bindist. Specifically * BUILD_PROF_LIBS to determine whether we had profiled libraries or not * DYNAMIC_GHC_PROGRAMS to determine whether we had shared libraries or not Not only were these never set but also not really accurate because you could have shared libaries but still statically linked ghc executable. In addition variables like GhcLibWays were just never used, so those have been deleted from the script. Now instead we generate a build.mk file which just directly specifies which RtsWays we have supplied in the bindist and whether we have DYNAMIC_GHC_PROGRAMS. - - - - - fe23629b by Matthew Pickering at 2023-08-23T13:43:48-04:00 hadrian: Add reloc-binary-dist-* targets This adds a command line option to build a "relocatable" bindist. The bindist is created by first creating a normal bindist and then installing it using the `RelocatableBuild=YES` option. This creates a bindist without any wrapper scripts pointing to the libdir. The motivation for this feature is that we want to ship relocatable bindists on windows and this method is more uniform than the ad-hoc method which lead to bugs such as #23608 and #23476 The relocatable bindist can be built with the "reloc-binary-dist" target and supports the same suffixes as the normal "binary-dist" command to specify the compression style. - - - - - 41cbaf44 by Matthew Pickering at 2023-08-23T13:43:48-04:00 packaging: Fix installation scripts on windows/RelocatableBuild case This includes quite a lot of small fixes which fix the installation makefile to work on windows properly. This also required fixing the RelocatableBuild variable which seemed to have been broken for a long while. Sam helped me a lot writing this patch by providing a windows machine to test the changes. Without him it would have taken ages to tweak everything. Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 03474456 by Matthew Pickering at 2023-08-23T13:43:48-04:00 ci: Build relocatable bindist on windows We now build the relocatable bindist target on windows, which means we test and distribute the new method of creating a relocatable bindist. - - - - - d0b48113 by Matthew Pickering at 2023-08-23T13:43:48-04:00 hadrian: Add error when trying to build binary-dist target on windows The binary dist produced by `binary-dist` target doesn't work on windows because of the wrapper script the makefile installs. In order to not surprise any packagers we just give an error if someone tries to build the old binary-dist target rather than the reloc-binary-dist target. - - - - - 7cbf9361 by Matthew Pickering at 2023-08-23T13:43:48-04:00 hadrian: Remove query' logic to use tooldir - - - - - 03fad42e by Matthew Pickering at 2023-08-23T13:43:48-04:00 configure: Set WindresCmd directly and removed unused variables For some reason there was an indirection via the Windres variable before setting WindresCmd. That indirection led to #23855. I then also noticed that these other variables were just not used anywhere when trying to work out what the correct condition was for this bit of the configure script. - - - - - c82770f5 by sheaf at 2023-08-23T13:43:48-04:00 Apply shellcheck suggestion to SUBST_TOOLDIR - - - - - 896e35e5 by sheaf at 2023-08-23T13:44:34-04:00 Compute hints from TcSolverReportMsg This commit changes how hints are handled in conjunction with constraint solver report messages. Instead of storing `[GhcHint]` in the TcRnSolverReport error constructor, we compute the hints depending on the underlying TcSolverReportMsg. This disentangles the logic and makes it easier to add new hints for certain errors. - - - - - a05cdaf0 by Alexander Esgen at 2023-08-23T13:45:16-04:00 users-guide: remove note about fatal Haddock parse failures - - - - - 4908d798 by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Introduce Data.Enum - - - - - f59707c7 by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Num.Integer - - - - - b1054053 by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Num - - - - - 6baa481d by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Num.Natural - - - - - 2ac15233 by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Float - - - - - f3c489de by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add export list to GHC.Real - - - - - 94f59eaa by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Eliminate module reexport in GHC.Exception The metric increase here isn't strictly due to this commit but it's a rather small, incidental change. Metric Increase: T8095 T13386 Metric Decrease: T8095 T13386 T18304 - - - - - be1fc7df by Ben Gamari at 2023-08-23T17:36:41-04:00 base: Add disclaimers in internal modules To warn users that these modules are internal and their interfaces may change with little warning. As proposed in Core Libraries Committee #146 [CLC146]. [CLC146]: https://github.com/haskell/core-libraries-committee/issues/146 - - - - - 0326f3f4 by sheaf at 2023-08-23T17:37:29-04:00 Bump Cabal submodule We need to bump the Cabal submodule to include commit ec75950 which fixes an issue with a dodgy import Rep(..) which relied on GHC bug #23570 - - - - - 0504cd08 by Facundo Domínguez at 2023-08-23T17:38:11-04:00 Fix typos in the documentation of Data.OldList.permutations - - - - - 1420b8cb by Antoine Leblanc at 2023-08-24T16:18:17-04:00 Be more eager in TyCon boot validity checking This commit performs boot-file consistency checking for TyCons into checkValidTyCl. This ensures that we eagerly catch any mismatches, which prevents the compiler from seeing these inconsistencies and panicking as a result. See Note [TyCon boot consistency checking] in GHC.Tc.TyCl. Fixes #16127 - - - - - d99c816f by Finley McIlwaine at 2023-08-24T16:18:55-04:00 Refactor estimation of stack info table provenance This commit greatly refactors the way we compute estimated provenance for stack info tables. Previously, this process was done using an entirely separate traversal of the whole Cmm code stream to build the map from info tables to source locations. The separate traversal is now fused with the Cmm code generation pipeline in GHC.Driver.Main. This results in very significant code generation speed ups when -finfo-table-map is enabled. In testing, this patch reduces code generation times by almost 30% with -finfo-table-map and -O0, and 60% with -finfo-table-map and -O1 or -O2 . Fixes #23103 - - - - - d3e0124c by Finley McIlwaine at 2023-08-24T16:18:55-04:00 Add a test checking overhead of -finfo-table-map We want to make sure we don't end up with poor codegen performance resulting from -finfo-table-map again as in #23103. This test adds a performance test tracking total allocations while compiling ExactPrint with -finfo-table-map. - - - - - fcfc1777 by Ben Gamari at 2023-08-25T10:58:16-04:00 llvmGen: Add export list to GHC.Llvm.MetaData - - - - - 5880fff6 by Ben Gamari at 2023-08-25T10:58:16-04:00 llvmGen: Allow LlvmLits in MetaExprs This omission appears to be an oversight. - - - - - 86ce92a2 by Ben Gamari at 2023-08-25T10:58:16-04:00 compiler: Move platform feature predicates to GHC.Driver.DynFlags These are useful in `GHC.Driver.Config.*`. - - - - - a6a38742 by Ben Gamari at 2023-08-25T10:58:16-04:00 llvmGen: Introduce infrastructure for module flag metadata - - - - - e9af2cf3 by Ben Gamari at 2023-08-25T10:58:16-04:00 llvmGen: Don't pass stack alignment via command line As of https://reviews.llvm.org/D103048 LLVM no longer supports the `-stack-alignment=...` flag. Instead this information is passed via a module flag metadata node. This requires dropping support for LLVM 11 and 12. Fixes #23870 - - - - - a936f244 by Alan Zimmerman at 2023-08-25T10:58:56-04:00 EPA: Keep track of "in" token for WarningTxt category A warning can now be written with a category, e.g. {-# WARNInG in "x-c" e "d" #-} Keep track of the location of the 'in' keyword and string, as well as the original SourceText of the label, in case it uses character escapes. - - - - - 3df8a653 by Matthew Pickering at 2023-08-25T17:42:18-04:00 Remove redundant import in InfoTableProv The copyBytes function is provided by the import of Foreign. Fixes #23889 - - - - - d6f807ec by Ben Gamari at 2023-08-25T17:42:54-04:00 gitlab/issue-template: Mention report-a-bug - - - - - 50b9f75d by Artin Ghasivand at 2023-08-26T20:02:50+03:30 Added StandaloneKindSignature examples to replace CUSKs ones - - - - - 2f6309a4 by Vladislav Zavialov at 2023-08-27T03:47:37-04:00 Remove outdated CPP in compiler/* and template-haskell/* The boot compiler was bumped to 9.4 in cebb5819b43. There is no point supporting older GHC versions with CPP. - - - - - 5248fdf7 by Zubin Duggal at 2023-08-28T15:01:09+05:30 testsuite: Add regression test for #23861 Simon says this was fixed by commit 8d68685468d0b6e922332a3ee8c7541efbe46137 Author: sheaf <sam.derbyshire at gmail.com> Date: Fri Aug 4 15:28:45 2023 +0200 Remove zonk in tcVTA - - - - - b6903f4d by Zubin Duggal at 2023-08-28T12:33:58-04:00 testsuite: Add regression test for #23864 Simon says this was fixed by commit 59202c800f2c97c16906120ab2561f6e1556e4af Author: Sebastian Graf <sebastian.graf at kit.edu> Date: Fri Mar 31 17:35:22 2023 +0200 CorePrep: Eliminate EmptyCase and unsafeEqualityProof in CoreToStg instead We eliminate EmptyCase by way of `coreToStg (Case e _ _ []) = coreToStg e` now. The main reason is that it plays far better in conjunction with eta expansion (as we aim to do for arguments in CorePrep, #23083), because we can discard any arguments, `(case e of {}) eta == case e of {}`, whereas in `(e |> co) eta` it's impossible to discard the argument. - - - - - 9eecdf33 by sheaf at 2023-08-28T18:54:06+00:00 Remove ScopedTypeVariables => TypeAbstractions This commit implements [amendment 604](https://github.com/ghc-proposals/ghc-proposals/pull/604/) to [GHC proposal 448](https://github.com/ghc-proposals/ghc-proposals/pull/448) by removing the implication of language extensions ScopedTypeVariables => TypeAbstractions To limit breakage, we now allow type arguments in constructor patterns when both ScopedTypeVariables and TypeApplications are enabled, but we emit a warning notifying the user that this is deprecated behaviour that will go away starting in GHC 9.12. Fixes #23776 - - - - - fadd5b4d by sheaf at 2023-08-28T18:54:06+00:00 .stderr: ScopedTypeVariables =/> TypeAbstractions This commit accepts testsuite changes for the changes in the previous commit, which mean that TypeAbstractions is no longer implied by ScopedTypeVariables. - - - - - 4f5fb500 by Greg Steuck at 2023-08-29T07:55:13-04:00 Repair `codes` test on OpenBSD by explicitly requesting extended RE - - - - - 6bbde581 by Vasily Sterekhov at 2023-08-29T12:06:58-04:00 Add test for #23540 `T23540.hs` makes use of `explainEv` from `HieQueries.hs`, so `explainEv` has been moved to `TestUtils.hs`. - - - - - 257bb3bd by Vasily Sterekhov at 2023-08-29T12:06:58-04:00 Add test for #23120 - - - - - 4f192947 by Vasily Sterekhov at 2023-08-29T12:06:58-04:00 Make some evidence uses reachable by toHie Resolves #23540, #23120 This adds spans to certain expressions in the typechecker and renamer, and lets 'toHie' make use of those spans. Therefore the relevant evidence uses for the following syntax will now show up under the expected nodes in 'HieAst's: - Overloaded literals ('IsString', 'Num', 'Fractional') - Natural patterns and N+k patterns ('Eq', 'Ord', and instances from the overloaded literals being matched on) - Arithmetic sequences ('Enum') - Monadic bind statements ('Monad') - Monadic body statements ('Monad', 'Alternative') - ApplicativeDo ('Applicative', 'Functor') - Overloaded lists ('IsList') Also see Note [Source locations for implicit function calls] In the process of handling overloaded lists I added an extra 'SrcSpan' field to 'VAExpansion' - this allows us to more accurately reconstruct the locations from the renamer in 'rebuildHsApps'. This also happens to fix #23120. See the additions to Note [Looking through HsExpanded] - - - - - fe9fcf9d by Sylvain Henry at 2023-08-29T12:07:50-04:00 ghc-heap: rename C file (fix #23898) - - - - - b60d6576 by Krzysztof Gogolewski at 2023-08-29T12:08:29-04:00 Misc cleanup - Builtin.PrimOps: ReturnsAlg was used only for unboxed tuples. Rename to ReturnsTuple. - Builtin.Utils: use SDoc for a panic message. The comment about <<details unavailable>> was obsoleted by e8d356773b56. - TagCheck: fix wrong logic. It was zipping a list 'args' with its version 'args_cmm' after filtering. - Core.Type: remove an outdated 1999 comment about unlifted polymorphic types - hadrian: remove leftover debugging print - - - - - 3054fd6d by Krzysztof Gogolewski at 2023-08-29T12:09:08-04:00 Add a regression test for #23903 The bug has been fixed by commit bad2f8b8aa8424. - - - - - 21584b12 by Ben Gamari at 2023-08-29T19:52:02-04:00 README: Refer to ghc-hq repository for contributor and governance information - - - - - e542d590 by sheaf at 2023-08-29T19:52:40-04:00 Export setInertSet from GHC.Tc.Solver.Monad We used to export getTcSInerts and setTcSInerts from GHC.Tc.Solver.Monad. These got renamed to getInertSet/setInertSet in e1590ddc. That commit also removed the export of setInertSet, but that function is useful for the GHC API. - - - - - 694ec5b1 by sheaf at 2023-08-30T10:18:32-04:00 Don't bundle children for non-parent Avails We used to bundle all children of the parent Avail with things that aren't the parent, e.g. with class C a where type T a meth :: .. we would bundle the whole Avail (C, T, meth) with all of C, T and meth, instead of only with C. Avoiding this fixes #23570 - - - - - d926380d by Krzysztof Gogolewski at 2023-08-30T10:19:08-04:00 Fix typos - - - - - d07080d2 by Josh Meredith at 2023-08-30T19:42:32-04:00 JS: Implement missing C functions `rename`, `realpath`, and `getcwd` (#23806) - - - - - e2940272 by David Binder at 2023-08-30T19:43:08-04:00 Bump submodules of hpc and hpc-bin to version 0.7.0.0 hpc 0.7.0.0 dropped SafeHaskell safety guarantees in order to simplify compatibility with newer versions of the directory package which dropped all SafeHaskell guarantees. - - - - - 5d56d05c by David Binder at 2023-08-30T19:43:08-04:00 Bump hpc bound in ghc.cabal.in - - - - - 99fff496 by Dominik Schrempf at 2023-08-31T00:04:46-04:00 ghc classes documentation: rm redundant comment - - - - - fe021bab by Dominik Schrempf at 2023-08-31T00:04:46-04:00 prelude documentation: various nits - - - - - 48c84547 by Dominik Schrempf at 2023-08-31T00:04:46-04:00 integer documentation: minor corrections - - - - - 20cd12f4 by Dominik Schrempf at 2023-08-31T00:04:46-04:00 real documentation: nits - - - - - dd39bdc0 by sheaf at 2023-08-31T00:05:27-04:00 Add a test for #21765 This issue (of reporting a constraint as being redundant even though removing it causes typechecking to fail) was fixed in aed1974e. This commit simply adds a regression test. Fixes #21765 - - - - - f1ec3628 by Andrew Lelechenko at 2023-08-31T23:53:30-04:00 Export foldl' from Prelude and bump submodules See https://github.com/haskell/core-libraries-committee/issues/167 for discussion Metric Decrease: T8095 T13386 Metric Increase: T13386 T8095 T8095 ghc/alloc decreased on x86_64, but increased on aarch64. T13386 ghc/alloc decreased on x86_64-windows, but increased on other platforms. Neither has anything to do with `foldl'`, so I conclude that both are flaky. - - - - - 3181b97d by Gergő Érdi at 2023-08-31T23:54:06-04:00 Allow cross-tyvar defaulting proposals from plugins Fixes #23832. - - - - - 495b2241 by Matthew Pickering at 2023-09-01T13:02:07+02:00 Fix issue with duplicate reexported definitions (T23616) When a class method was reexported, it's default methods were also showing up in the generated html page. The simplest and most non-invasive fix is to not look for the default method if we are just exporting the class method.. because the backends are just showing default methods when the whole class is exported. In general it would be worthwhile to rewrite this bit of code I think as the logic and what gets included is split over `lookupDocs` and `availExportDecl` it would be clearer to combine the two. The result of lookupDocs is always just passed to availExportDecl so it seems simpler and more obvious to just write the function directly. - - - - - e4af506e by Sebastian Graf at 2023-09-01T14:29:12-04:00 Clarify Note [GlobalId/LocalId] after CorePrep (#23797) Fixes #23797. - - - - - ac29787c by Sylvain Henry at 2023-09-01T14:30:02-04:00 Fix warning with UNPACK on sum type (#23921) - - - - - 9765ac7b by Zubin Duggal at 2023-09-05T00:37:45-04:00 hadrian: track python dependencies in doc rules - - - - - 1578215f by sheaf at 2023-09-05T00:38:26-04:00 Bump Haddock to fix #23616 This commit updates the Haddock submodule to include the fix to #23616. Fixes #23616 - - - - - 5a2fe35a by David Binder at 2023-09-05T00:39:07-04:00 Fix example in GHC user guide in SafeHaskell section The example given in the SafeHaskell section uses an implementation of Monad which no longer works. This MR removes the non-canonical return instance and adds the necessary instances of Functor and Applicative. - - - - - 291d81ae by Matthew Pickering at 2023-09-05T14:03:10-04:00 driver: Check transitive closure of haskell package dependencies when deciding whether to relink We were previously just checking whether direct package dependencies had been modified. This caused issues when compiling without optimisations as we wouldn't relink the direct dependency if one of its dependenices changed. Fixes #23724 - - - - - 35da0775 by Krzysztof Gogolewski at 2023-09-05T14:03:47-04:00 Re-export GHC.Utils.Panic.Plain from GHC.Utils.Panic Fixes #23930 - - - - - 6551824d by Finley McIlwaine at 2023-09-05T13:06:57-07:00 Remove fake export of `FUN` from Prelude This prevents `data FUN` from being shown at the top of the Prelude docs. Fixes \#23920 on GHC. - - - - - 3930d793 by Jaro Reinders at 2023-09-06T18:42:55-04:00 Make STG rewriter produce updatable closures - - - - - 0104221a by Krzysztof Gogolewski at 2023-09-06T18:43:32-04:00 configure: update message to use hadrian (#22616) - - - - - b34f8586 by Alan Zimmerman at 2023-09-07T10:58:38-04:00 EPA: Incorrect locations for UserTyVar with '@' In T13343.hs, the location for the @ is not within the span of the surrounding UserTyVar. type Bad @v = (forall (v1 :: RuntimeRep) (a1 :: TYPE v). a1) :: TYPE v Widen it so it is captured. Closes #23887 - - - - - 8046f020 by Finley McIlwaine at 2023-09-07T10:59:15-04:00 Bump haddock submodule to fix #23920 Removes the fake export of `FUN` from Prelude. Fixes #23920. Bumps haddock submodule. - - - - - e0aa8c6e by Krzysztof Gogolewski at 2023-09-07T11:00:03-04:00 Fix wrong role in mkSelCo_maybe In the Lint failure in #23938, we start with a coercion Refl :: T a ~R T a, and call mkSelCo (SelTyCon 1 nominal) Refl. The function incorrectly returned Refl :: a ~R a. The returned role should be nominal, according to the SelCo rule: co : (T s1..sn) ~r0 (T t1..tn) r = tyConRole tc r0 i ---------------------------------- SelCo (SelTyCon i r) : si ~r ti In this test case, r is nominal while r0 is representational. - - - - - 1d92f2df by Gergő Érdi at 2023-09-08T04:04:30-04:00 If we have multiple defaulting plugins, then we should zonk in between them after any defaulting has taken place, to avoid a defaulting plugin seeing a metavariable that has already been filled. Fixes #23821. - - - - - eaee4d29 by Gergő Érdi at 2023-09-08T04:04:30-04:00 Improvements to the documentation of defaulting plugins Based on @simonpj's draft and comments in !11117 - - - - - ede3df27 by Alan Zimmerman at 2023-09-08T04:05:06-04:00 EPA: Incorrect span for LWarnDec GhcPs The code (from T23465.hs) {-# WARNInG in "x-c" e "d" #-} e = e gives an incorrect span for the LWarnDecl GhcPs Closes #23892 It also fixes the Test23465/Test23464 mixup - - - - - a0ccef7a by Krzysztof Gogolewski at 2023-09-08T04:05:42-04:00 Valid hole fits: don't suggest unsafeCoerce (#17940) - - - - - 9ab5a448 by Alan Zimmerman at 2023-09-08T18:26:53+01:00 Match changes in wip/az/T23885-unicode-funtycon - - - - - 88b942c4 by Oleg Grenrus at 2023-09-08T19:58:42-04:00 Add warning for badly staged types. Resolves #23829. The stage violation results in out-of-bound names in splices. Technically this is an error, but someone might rely on this!? Internal changes: - we now track stages for TyVars. - thLevel (RunSplice _) = 0, instead of panic, as reifyInstances does in fact rename its argument type, and it can contain variables. - - - - - 9861f787 by Ben Gamari at 2023-09-08T19:59:19-04:00 rts: Fix invalid symbol type I suspect this code is dead since we haven't observed this failing despite the obviously incorrect macro name. - - - - - 03ed6a9a by Ben Gamari at 2023-09-08T19:59:19-04:00 testsuite: Add simple test exercising C11 atomics in GHCi See #22012. - - - - - 1aa5733a by Ben Gamari at 2023-09-08T19:59:19-04:00 rts/RtsSymbols: Add AArch64 outline atomic operations Fixes #22012 by adding the symbols described in https://github.com/llvm/llvm-project/blob/main/llvm/docs/Atomics.rst#libcalls-atomic. Ultimately this would be better addressed by #22011, but this is a first step in the right direction and fixes the immediate symptom. Note that we dropped the `__arch64_cas16` operations as these provided by all platforms's compilers. Also, we don't link directly against the libgcc/compiler-rt definitions but rather provide our own wrappers to work around broken toolchains (e.g. https://bugs.gentoo.org/868018). Generated via https://gitlab.haskell.org/ghc/ghc/-/snippets/5733. - - - - - 8f7d3041 by Matthew Pickering at 2023-09-08T19:59:55-04:00 ci: Build debian12 and fedora38 bindists This adds builds for the latest releases for fedora and debian We build these bindists in nightly and release pipelines. - - - - - a1f0d55c by Felix Leitz at 2023-09-08T20:00:37-04:00 Fix documentation around extension implication for MultiParamTypeClasses/ConstrainedClassMethods. - - - - - 98166389 by Teo Camarasu at 2023-09-12T04:30:54-04:00 docs: move -xn flag beside --nonmoving-gc It makes sense to have these beside each other as they are aliases. - - - - - f367835c by Teo Camarasu at 2023-09-12T04:30:55-04:00 nonmoving: introduce a family of dense allocators Supplement the existing power 2 sized nonmoving allocators with a family of dense allocators up to a configurable threshold. This should reduce waste from rounding up block sizes while keeping the amount of allocator sizes manageable. This patch: - Adds a new configuration option `--nonmoving-dense-allocator-count` to control the amount of these new dense allocators. - Adds some constants to `NonmovingAllocator` in order to keep marking fast with the new allocators. Resolves #23340 - - - - - 2b07bf2e by Teo Camarasu at 2023-09-12T04:30:55-04:00 Add changelog entry for #23340 - - - - - f96fe681 by sheaf at 2023-09-12T04:31:44-04:00 Use printGhciException in run{Stmt, Decls} When evaluating statements in GHCi, we need to use printGhciException instead of the printException function that GHC provides in order to get the appropriate error messages that are customised for ghci use. - - - - - d09b932b by psilospore at 2023-09-12T04:31:44-04:00 T23686: Suggest how to enable Language Extension when in ghci Fixes #23686 - - - - - da30f0be by Matthew Craven at 2023-09-12T04:32:24-04:00 Unarise: Split Rubbish literals in function args Fixes #23914. Also adds a check to STG lint that these args are properly unary or nullary after unarisation - - - - - 261b6747 by Matthew Pickering at 2023-09-12T04:33:04-04:00 darwin: Bump MAXOSX_DEPLOYMENT_TARGET to 10.13 This bumps the minumum supported version to 10.13 (High Sierra) which is 6 years old at this point. Fixes #22938 - - - - - f418f919 by Mario Blažević at 2023-09-12T04:33:45-04:00 Fix TH pretty-printing of nested GADTs, issue #23937 This commit fixes `Language.Haskell.TH.Ppr.pprint` so that it correctly pretty-prints GADTs declarations contained within data family instances. Fixes #23937 - - - - - d7a64753 by John Ericson at 2023-09-12T04:34:20-04:00 Put hadrian non-bootstrap plans through `jq` This makes it possible to review changes with conventional diffing tools. This is picking up where ad8cfed4195b1bbfc15b841f010e75e71f63157d left off. - - - - - ff0a709a by Sylvain Henry at 2023-09-12T08:46:28-04:00 JS: fix some tests - Tests using Setup programs need to pass --with-hc-pkg - Several other fixes See https://gitlab.haskell.org/ghc/ghc/-/wikis/javascript-backend/bug_triage for the current status - - - - - fc86f0e7 by Krzysztof Gogolewski at 2023-09-12T08:47:04-04:00 Fix in-scope set assertion failure (#23918) Patch by Simon - - - - - 21a906c2 by Matthew Pickering at 2023-09-12T17:21:04+02:00 Add -Winconsistent-flags warning The warning fires when inconsistent command line flags are passed. For example: * -dynamic-too and -dynamic * -dynamic-too on windows * -O and --interactive * etc This is on by default and allows users to control whether the warning is displayed and whether it should be an error or not. Fixes #22572 - - - - - dfc4f426 by Krzysztof Gogolewski at 2023-09-12T20:31:35-04:00 Avoid serializing BCOs with the internal interpreter Refs #23919 - - - - - 9217950b by Finley McIlwaine at 2023-09-13T08:06:03-04:00 Fix numa auto configure - - - - - 98e7c1cf by Simon Peyton Jones at 2023-09-13T08:06:40-04:00 Add -fno-cse to T15426 and T18964 This -fno-cse change is to avoid these performance tests depending on flukey CSE stuff. Each contains several independent tests, and we don't want them to interact. See #23925. By killing CSE we expect a 400% increase in T15426, and 100% in T18964. Metric Increase: T15426 T18964 - - - - - 236a134e by Simon Peyton Jones at 2023-09-13T08:06:40-04:00 Tiny refactor canEtaReduceToArity was only called internally, and always with two arguments equal to zero. This patch just specialises the function, and renames it to cantEtaReduceFun. No change in behaviour. - - - - - 56b403c9 by Ben Gamari at 2023-09-13T19:21:36-04:00 spec-constr: Lift argument limit for SPEC-marked functions When the user adds a SPEC argument to a function, they are informing us that they expect the function to be specialised. However, previously this instruction could be preempted by the specialised-argument limit (sc_max_args). Fix this. This fixes #14003. - - - - - 6840012e by Simon Peyton Jones at 2023-09-13T19:22:13-04:00 Fix eta reduction Issue #23922 showed that GHC was bogusly eta-reducing a join point. We should never eta-reduce (\x -> j x) to j, if j is a join point. It is extremly difficult to trigger this bug. It took me 45 mins of trying to make a small tests case, here immortalised as T23922a. - - - - - e5c00092 by Andreas Klebinger at 2023-09-14T08:57:43-04:00 Profiling: Properly escape characters when using `-pj`. There are some ways in which unusual characters like quotes or others can make it into cost centre names. So properly escape these. Fixes #23924 - - - - - ec490578 by Ellie Hermaszewska at 2023-09-14T08:58:24-04:00 Use clearer example variable names for bool eliminator - - - - - 5126a2fe by Sylvain Henry at 2023-09-15T11:18:02-04:00 Add missing int64/word64-to-double/float rules (#23907) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/203 - - - - - 566ef411 by Mario Blažević at 2023-09-15T11:18:43-04:00 Fix and test TH pretty-printing of type operator role declarations This commit fixes and tests `Language.Haskell.TH.Ppr.pprint` so that it correctly pretty-prints `type role` declarations for operator names. Fixes #23954 - - - - - 8e05c54a by Simon Peyton Jones at 2023-09-16T01:42:33-04:00 Use correct FunTyFlag in adjustJoinPointType As the Lint error in #23952 showed, the function adjustJoinPointType was failing to adjust the FunTyFlag when adjusting the type. I don't think this caused the seg-fault reported in the ticket, but it is definitely. This patch fixes it. It is tricky to come up a small test case; Krzysztof came up with this one, but it only triggers a failure in GHC 9.6. - - - - - 778c84b6 by Pierre Le Marre at 2023-09-16T01:43:15-04:00 Update to Unicode 15.1.0 See: https://www.unicode.org/versions/Unicode15.1.0/ - - - - - f9d79a6c by Alan Zimmerman at 2023-09-18T00:00:14-04:00 EPA: track unicode version for unrestrictedFunTyCon Closes #23885 Updates haddock submodule - - - - - 9374f116 by Andrew Lelechenko at 2023-09-18T00:00:54-04:00 Bump parsec submodule to allow text-2.1 and bytestring-0.12 - - - - - 7ca0240e by Ben Gamari at 2023-09-18T15:16:48-04:00 base: Advertise linear time of readFloat As noted in #23538, `readFloat` has runtime that scales nonlinearly in the size of its input. Consequently, its use on untrusted input can be exploited as a denial-of-service vector. Point this out and suggest use of `read` instead. See #23538. - - - - - f3f58f13 by Simon Peyton Jones at 2023-09-18T15:17:24-04:00 Remove dead code GHC.CoreToStg.Prep.canFloat This function never fires, so we can delete it: #23965. - - - - - ccab5b15 by Ben Gamari at 2023-09-18T15:18:02-04:00 base/changelog: Move fix for #23907 to 9.8.1 section Since the fix was backported to 9.8.1 - - - - - 51b57d65 by Matthew Pickering at 2023-09-19T08:44:31-04:00 Add aarch64 alpine bindist This is dynamically linked and makes creating statically linked executables more straightforward. Fixes #23482 - - - - - 02c87213 by Matthew Pickering at 2023-09-19T08:44:31-04:00 Add aarch64-deb11 bindist This adds a debian 11 release job for aarch64. Fixes #22005 - - - - - 8b61dfd6 by Alexis King at 2023-09-19T08:45:13-04:00 Don’t store the async exception masking state in CATCH frames - - - - - 86d2971e by doyougnu at 2023-09-19T19:08:19-04:00 compiler,ghci: error codes link to HF error index closes: #23259 - adds -fprint-error-index-links={auto|always|never} flag - - - - - 5f826c18 by sheaf at 2023-09-19T19:09:03-04:00 Pass quantified tyvars in tcDefaultAssocDecl This commit passes the correct set of quantified type variables written by the user in associated type default declarations for validity checking. This ensures that validity checking of associated type defaults mirrors that of standalone type family instances. Fixes #23768 (see testcase T23734 in subsequent commit) - - - - - aba18424 by sheaf at 2023-09-19T19:09:03-04:00 Avoid panic in mkGADTVars This commit avoids panicking in mkGADTVars when we encounter a type variable as in #23784 that is bound by a user-written forall but not actually used. Fixes #23784 - - - - - a525a92a by sheaf at 2023-09-19T19:09:03-04:00 Adjust reporting of unused tyvars in data FamInsts This commit adjusts the validity checking of data family instances to improve the reporting of unused type variables. See Note [Out of scope tvs in data family instances] in GHC.Tc.Validity. The problem was that, in a situation such as data family D :: Type data instance forall (d :: Type). D = MkD the RHS passed to 'checkFamPatBinders' would be the TyCon app R:D d which mentions the type variable 'd' quantified in the user-written forall. Thus, when computing the set of unused type variables in the RHS of the data family instance, we would find that 'd' is used, and report a strange error message that would say that 'd' is not bound on the LHS. To fix this, we special-case the data-family instance case, manually extracting all the type variables that appear in the arguments of all the data constructores of the data family instance. Fixes #23778 - - - - - 28dd52ee by sheaf at 2023-09-19T19:09:03-04:00 Unused tyvars in FamInst: only report user tyvars This commit changes how we perform some validity checking for coercion axioms to mirror how we handle default declarations for associated type families. This allows us to keep track of whether type variables in type and data family instances were user-written or not, in order to only report the user-written ones in "unused type variable" error messages. Consider for example: {-# LANGUAGE PolyKinds #-} type family F type instance forall a. F = () In this case, we get two quantified type variables, (k :: Type) and (a :: k); the second being user-written, but the first is introduced by the typechecker. We should only report 'a' as being unused, as the user has no idea what 'k' is. Fixes #23734 - - - - - 1eed645c by sheaf at 2023-09-19T19:09:03-04:00 Validity: refactor treatment of data families This commit refactors the reporting of unused type variables in type and data family instances to be more principled. This avoids ad-hoc logic in the treatment of data family instances. - - - - - 35bc506b by John Ericson at 2023-09-19T19:09:40-04:00 Remove `ghc-cabal` It is dead code since the Make build system was removed. I tried to go over every match of `git grep -i ghc-cabal` to find other stray bits. Some of those might be workarounds that can be further removed. - - - - - 665ca116 by John Paul Adrian Glaubitz at 2023-09-19T19:10:39-04:00 Re-add unregisterised build support for sparc and sparc64 Closes #23959 - - - - - 142f8740 by Matthew Pickering at 2023-09-19T19:11:16-04:00 Bump ci-images to use updated version of Alex Fixes #23977 - - - - - fa977034 by John Ericson at 2023-09-21T12:55:25-04:00 Use Cabal 3.10 for Hadrian We need the newer version for `CABAL_FLAG_*` env vars for #17191. - - - - - a5d22cab by John Ericson at 2023-09-21T12:55:25-04:00 hadrian: `need` any `configure` script we will call When the script is changed, we should reconfigure. - - - - - db882b57 by John Ericson at 2023-09-21T12:55:25-04:00 hadrian: Make it easier to debug Cabal configure Right now, output is squashed. This make per-package configure scripts extremely hard to maintain, because we get vague "library is missing" errors when the actually probably is usually completely unrelated except for also involving the C/C++ toolchain. (I can always pass `-VVV` to Hadrian locally, but these errors are subtle and I often cannot reproduce them locally!) `--disable-option-checking` was added back in 75c6e0684dda585c37b4ac254cd7a13537a59a91 but seems to be a bit overkill; if other flags are passed that are not recognized behind the two from Cabal mentioned in the former comment, we *do* want to know about it. - - - - - 7ed65f5a by John Ericson at 2023-09-21T12:55:25-04:00 hadrian: Increase verbosity of certain cabal commands This is a hack to get around the cabal function we're calling *decreasing* the verbosity it passes to another function, which is the stuff we often actually care about. Sigh. Keeping this a separate commit so if this makes things too verbose it is easy to revert. - - - - - a4fde569 by John Ericson at 2023-09-21T12:55:25-04:00 rts: Move most external symbols logic to the configure script This is much more terse because we are programmatically handling the leading underscore. `findPtr` however is still handled in the Cabal file because we need a newer Cabal to pass flags to the configure script automatically. Co-Authored-By: Ben Gamari <ben at well-typed.com> - - - - - 56cc85fb by Andrew Lelechenko at 2023-09-21T12:56:21-04:00 Bump Cabal submodule to allow text-2.1 and bytestring-0.12 - - - - - 0cd6148c by Matthew Pickering at 2023-09-21T12:56:21-04:00 hadrian: Generate Distribution/Fields/Lexer.x before creating a source-dist - - - - - b10ba6a3 by Andrew Lelechenko at 2023-09-21T12:56:21-04:00 Bump hadrian's index-state to upgrade alex at least to 3.2.7.3 - - - - - 11ecc37b by Luite Stegeman at 2023-09-21T12:57:03-04:00 JS: correct file size and times Programs produced by the JavaScript backend were returning incorrect file sizes and modification times, causing cabal related tests to fail. This fixes the problem and adds an additional test that verifies basic file information operations. fixes #23980 - - - - - b35fd2cd by Ben Gamari at 2023-09-21T12:57:39-04:00 gitlab-ci: Drop libiserv from upload_ghc_libs libiserv has been merged into the ghci package. - - - - - 37ad04e8 by Ben Gamari at 2023-09-21T12:58:15-04:00 testsuite: Fix Windows line endings - - - - - 5795b365 by Ben Gamari at 2023-09-21T12:58:15-04:00 testsuite: Use makefile_test - - - - - 15118740 by Ben Gamari at 2023-09-21T12:58:55-04:00 system-cxx-std-lib: Add license and description - - - - - 0208f1d5 by Ben Gamari at 2023-09-21T12:59:33-04:00 gitlab/issue-templates: Rename bug.md -> default.md So that it is visible by default. - - - - - 23cc3f21 by Andrew Lelechenko at 2023-09-21T20:18:11+01:00 Bump submodule text to 2.1 - - - - - b8e4fe23 by Andrew Lelechenko at 2023-09-22T20:05:05-04:00 Bump submodule unix to 2.8.2.1 - - - - - 54b2016e by John Ericson at 2023-09-23T11:40:41-04:00 Move lib{numa,dw} defines to RTS configure Clean up the m4 to handle the auto case always and be more consistent. Also simplify the CPP --- we should always have both headers if we are using libnuma. "side effects" (AC_DEFINE, and AC_SUBST) are removed from the macros to better separate searching from actions taken based on search results. This might seem overkill now, but will make shuffling logic between configure scripts easier later. The macro comments are converted from `dnl` to `#` following the recomendation in https://www.gnu.org/software/autoconf/manual/autoconf-2.71/html_node/Macro-Definitions.html - - - - - d51b601b by John Ericson at 2023-09-23T11:40:50-04:00 Shuffle libzstd configuring between scripts Like the prior commit for libdw and libnuma, `AC_DEFINE` to RTS configure, `AC_SUBST` goes to the top-level configure script, and the documentation of the m4 macro is improved. - - - - - d1425af0 by John Ericson at 2023-09-23T11:41:03-04:00 Move `FP_ARM_OUTLINE_ATOMICS` to RTS configure It is just `AC_DEFINE` it belongs there instead. - - - - - 18de37e4 by John Ericson at 2023-09-23T11:41:03-04:00 Move mmap in the runtime linker check to the RTS configure `AC_DEFINE` should go there instead. - - - - - 74132c2b by Andrew Lelechenko at 2023-09-25T21:56:54-04:00 Elaborate comment on GHC_NO_UNICODE - - - - - de142aa2 by Ben Gamari at 2023-09-26T15:25:03-04:00 gitlab-ci: Mark T22012 as broken on CentOS 7 Due to #23979. - - - - - 6a896ce8 by Teo Camarasu at 2023-09-26T15:25:39-04:00 hadrian: better error for failing to find file's dependencies Resolves #24004 - - - - - d697a6c2 by Stefan Holdermans at 2023-09-26T20:58:37+00:00 Refactor uses of `partitionEithers . map` This patch changes occurences of the idiom `partitionEithers (map f xs)` by the simpler form `partitionWith f xs` where `partitionWith` is the utility function defined in `GHC.Utils.Misc`. Resolves: #23953 - - - - - 8a2968b7 by Stefan Holdermans at 2023-09-26T20:58:37+00:00 Refactor uses of `partitionEithers <$> mapM f xs` This patch changes occurences of the idiom `partitionEithers <$> mapM f xs` by the simpler form `partitionWithM f xs` where `partitionWithM` is a utility function newly added to `GHC.Utils.Misc`. - - - - - 6a27eb97 by Stefan Holdermans at 2023-09-26T20:58:37+00:00 Mark `GHC.Utils.Misc.partitionWithM` as inlineable This patch adds an `INLINEABLE` pragma for `partitionWithM` to ensure that the right-hand side of the definition of this function remains available for specialisation at call sites. - - - - - f1e5245a by David Binder at 2023-09-27T01:19:00-04:00 Add RTS option to supress tix file - - - - - 1f43124f by David Binder at 2023-09-27T01:19:00-04:00 Add expected output to testsuite in test interface-stability/base-exports - - - - - b9d2c354 by David Binder at 2023-09-27T01:19:00-04:00 Expose HpcFlags and getHpcFlags from GHC.RTS.Flags - - - - - 345675c6 by David Binder at 2023-09-27T01:19:00-04:00 Fix expected output of interface-stability test - - - - - 146e1c39 by David Binder at 2023-09-27T01:19:00-04:00 Implement getHpcFlags - - - - - 61ba8e20 by David Binder at 2023-09-27T01:19:00-04:00 Add section in user guide - - - - - ea05f890 by David Binder at 2023-09-27T01:19:01-04:00 Rename --emit-tix-file to --write-tix-file - - - - - cabce2ce by David Binder at 2023-09-27T01:19:01-04:00 Update the golden files for interface stability - - - - - 1dbdb9d0 by Krzysztof Gogolewski at 2023-09-27T01:19:37-04:00 Refactor: introduce stgArgRep The function 'stgArgType' returns the type in STG. But this violates the abstraction: in STG we're supposed to operate on PrimReps. This introduces stgArgRep ty = typePrimRep (stgArgType ty) stgArgRep1 ty = typePrimRep1 (stgArgType ty) stgArgRep_maybe ty = typePrimRep_maybe (stgArgType ty) stgArgType is still directly used for unboxed tuples (should be fixable), FFI and in ticky. - - - - - b02f8042 by Mario Blažević at 2023-09-27T17:33:28-04:00 Fix TH pretty-printer's parenthesization This PR Fixes `Language.Haskell.TH.Ppr.pprint` so it correctly emits parentheses where needed. Fixes #23962, #23968, #23971, and #23986 - - - - - 79104334 by Krzysztof Gogolewski at 2023-09-27T17:34:04-04:00 Add a testcase for #17564 The code in the ticket relied on the behaviour of Derived constraints. Derived constraints were removed in GHC 9.4 and now the code works as expected. - - - - - d7a80143 by sheaf at 2023-09-28T03:25:53-04:00 lint-codes: add new modes of operation This commit adds two new modes of operation to the lint-codes utility: list - list all statically used diagnostic codes outdated - list all outdated diagnostic codes The previous behaviour is now: test - test consistency and coverage of diagnostic codes - - - - - 477d223c by sheaf at 2023-09-28T03:25:53-04:00 lint codes: avoid using git-grep We manually traverse through the filesystem to find the diagnostic codes embedded in .stdout and .stderr files, to avoid any issues with old versions of grep. Fixes #23843 - - - - - a38ae69a by sheaf at 2023-09-28T03:25:53-04:00 lint-codes: add Hadrian targets This commit adds new Hadrian targets: codes, codes:used - list all used diagnostic codes codes:outdated - list outdated diagnostic codes This allows users to easily query GHC for used and outdated diagnostic codes, e.g. hadrian/build -j --flavour=<..> codes will list all used diagnostic codes in the command line by running the lint-codes utility in the "list codes" mode of operation. The diagnostic code consistency and coverage test is still run as usual, through the testsuite: hadrian/build test --only="codes" - - - - - 9cdd629b by Ben Gamari at 2023-09-28T03:26:29-04:00 hadrian: Install LICENSE files in bindists Fixes #23548. - - - - - b8ebf876 by Matthew Craven at 2023-09-28T03:27:05-04:00 Fix visibility when eta-reducing a type lambda Fixes #24014. - - - - - d3874407 by Torsten Schmits at 2023-09-30T16:08:10-04:00 Fix several mistakes around free variables in iface breakpoints Fixes #23612 , #23607, #23998 and #23666. MR: !11026 The fingerprinting logic in `Iface.Recomp` failed lookups when processing decls containing breakpoints for two reasons: * IfaceBreakpoint created binders for free variables instead of expressions * When collecting free names for the dependency analysis for fingerprinting, breakpoint FVs were skipped - - - - - ef5342cd by Simon Peyton Jones at 2023-09-30T16:08:48-04:00 Refactor to combine HsLam and HsLamCase This MR is pure refactoring (#23916): * Combine `HsLam` and `HsLamCase` * Combine `HsCmdLam` and `HsCmdLamCase` This just arranges to treat uniformly \x -> e \case pi -> ei \cases pis -> ie In the exising code base the first is treated differently to the latter two. No change in behaviour. More specifics: * Combine `HsLam` and `HsLamCase` (constructors of `Language.Haskell.Syntax.Expr.HsExpr`) into one data construtor covering * Lambda * `\case` * `\cases` * The new `HsLam` has an argument of type `HsLamVariant` to distinguish the three cases. * Similarly, combine `HsCmdLam` and `HsCmdLamCase` (constructors of `Language.Haskell.Syntax.Expr.HsCmd` ) into one. * Similarly, combine `mkHsLamPV` and `mkHsLamCasePV` (methods of class `DisambECP`) into one. (Thank you Alan Zimmerman.) * Similarly, combine `LambdaExpr` and `LamCaseAlt` (constructors of `Language.Haskell.Syntax.Expr.HsMatchContext`) into one: `LamAlt` with a `HsLamVariant` argument. * Similarly, combine `KappaExpr` and `ArrowLamCaseAlt` (constructors of `Language.Haskell.Syntax.Expr.HsArrowMatchContext`) into one: `ArrowLamAlt` with a `HsLamVariant` argument. * Similarly, combine `PsErrLambdaInPat` and `PsErrLambdaCaseInPat` (constructors of `GHC.Parser.Errors.Ppr.PsError`) into one. * Similarly, combine `PsErrLambdaInPat` and `PsErrLambdaCaseInPat` (constructors of `GHC.Parser.Errors.Ppr.PsError`) into one. * In the same `PsError` data type, combine `PsErrLambdaCmdInFunAppCmd` and `PsErrLambdaCaseCmdInFunAppCmd` into one. * In the same `PsError` data tpye, combine `PsErrLambdaInFunAppExpr` and `PsErrLambdaCaseInFunAppExpr` into one. p* Smilarly combine `ExpectedFunTyLam` and `ExpectedFunTyLamCase` (constructors of `GHC.Tc.Types.Origin.ExpectedFunTyOrigin`) into one. Phew! - - - - - b048bea0 by Andreas Klebinger at 2023-09-30T16:09:24-04:00 Arm: Make ppr methods easier to use by not requiring NCGConfig - - - - - 2adc0508 by Andreas Klebinger at 2023-09-30T16:09:24-04:00 AArch64: Fix broken conditional jumps for offsets >= 1MB Rewrite conditional jump instructions with offsets >= 1MB to use unconditional jumps to avoid overflowing the immediate. Fixes #23746 - - - - - 1424f790 by Alan Zimmerman at 2023-09-30T16:10:00-04:00 EPA: Replace Monoid with NoAnn We currently use the Monoid class as a constraint on Exact Print Annotation functions, so we can use mempty. But this leads to requiring Semigroup instances too, which do not always make sense. Instead, introduce a class NoAnn, with a function noAnn analogous to mempty. Closes #20372 Updates haddock submodule - - - - - c1a3ecde by Ben Gamari at 2023-09-30T16:10:36-04:00 users-guide: Refactor handling of :base-ref: et al. - - - - - bc204783 by Richard Eisenberg at 2023-10-02T14:50:52+02:00 Simplify and correct nasty case in coercion opt This fixes #21062. No test case, because triggering this code seems challenging. - - - - - 9c9ca67e by Andrew Lelechenko at 2023-10-04T05:42:28-04:00 Bump bytestring submodule to 0.12.0.2 - - - - - 4e46dc2b by Andrew Lelechenko at 2023-10-04T05:42:28-04:00 Inline bucket_match - - - - - f6b2751f by Ben Gamari at 2023-10-04T05:43:05-04:00 configure: Fix #21712 again This is a bit of a shot in the dark to fix #24033, which appears to be another instance of #21712. For some reason the ld-override logic *still* appears to be active on Darwin targets (or at least one). Consequently, on misconfigured systems we may choose a non-`ld64` linker. It's a bit unclear exactly what happened in #24033 but ultimately the check added for #21712 was not quite right, checking for the `ghc_host_os` (the value of which depends upon the bootstrap compiler) instead of the target platform. Fix this. Fixes #24033. - - - - - 2f0a101d by Krzysztof Gogolewski at 2023-10-04T05:43:42-04:00 Add a regression test for #24029 - - - - - 8cee3fd7 by sheaf at 2023-10-04T05:44:22-04:00 Fix non-symbolic children lookup of fixity decl The fix for #23664 did not correctly account for non-symbolic names when looking up children of a given parent. This one-line fix changes that. Fixes #24037 - - - - - a4785b33 by Cheng Shao at 2023-10-04T05:44:59-04:00 rts: fix incorrect ticket reference - - - - - e037f459 by Ben Gamari at 2023-10-04T05:45:35-04:00 users-guide: Fix discussion of -Wpartial-fields * fix a few typos * add a new example showing when the warning fires * clarify the existing example * point out -Wincomplete-record-selects Fixes #24049. - - - - - 8ff3134e by Matthew Pickering at 2023-10-05T05:34:58-04:00 Revert "Pass preprocessor options to C compiler when building foreign C files (#16737)" This reverts commit 1c18d3b41f897f34a93669edaebe6069f319f9e2. `-optP` should pass options to the preprocessor, that might be a very different program to the C compiler, so passing the options to the C compiler is likely to result in `-optP` being useless. Fixes #17185 and #21291 - - - - - 8f6010b9 by Ben Gamari at 2023-10-05T05:35:36-04:00 rts/nonmoving: Fix on LLP64 platforms Previously `NONMOVING_SEGMENT_MASK` and friends were defined with the `UL` size suffix. However, this is wrong on LLP64 platforms like Windows, where `long` is 32-bits. Fixes #23003. Fixes #24042. - - - - - f20d02f8 by Andreas Klebinger at 2023-10-05T05:36:14-04:00 Fix isAArch64Bitmask for 32bit immediates. Fixes #23802 - - - - - 63afb701 by Bryan Richter at 2023-10-05T05:36:49-04:00 Work around perf note fetch failure Addresses #24055. - - - - - 242102f4 by Krzysztof Gogolewski at 2023-10-05T05:37:26-04:00 Add a test for #21348 - - - - - 7d390bce by Rewbert at 2023-10-05T05:38:08-04:00 Fixes #24046 - - - - - 69abb171 by Finley McIlwaine at 2023-10-06T14:06:28-07:00 Ensure unconstrained instance dictionaries get IPE info In the `StgRhsCon` case of `GHC.Stg.Debug.collectStgRhs`, we were not coming up with an initial source span based on the span of the binder, which was causing instance dictionaries without dynamic superclass constraints to not have source locations in their IPE info. Now they do. Resolves #24005 - - - - - 390443b7 by Andreas Klebinger at 2023-10-07T10:00:20-04:00 rts: Split up rts/include/stg/MachRegs.h by arch - - - - - 3685942f by Bryan Richter at 2023-10-07T10:00:56-04:00 Actually set hackage index state Or at least, use a version of the cabal command that *claims* to set the index state. Time will tell. - - - - - 46a0e5be by Bryan Richter at 2023-10-07T10:00:56-04:00 Update hackage index state - - - - - d4b037de by Bryan Richter at 2023-10-07T10:00:56-04:00 Ensure hadrian uses CI's hackage index state - - - - - e206be64 by Andrew Lelechenko at 2023-10-08T15:06:14-04:00 Do not use O_NONBLOCK on regular files or block devices CLC proposal https://github.com/haskell/core-libraries-committee/issues/166 - - - - - a06197c4 by David Binder at 2023-10-08T15:06:55-04:00 Update hpc-bin submodule to 0.69 - - - - - ed6785b6 by David Binder at 2023-10-08T15:06:55-04:00 Update Hadrian with correct path to happy file for hpc-bin - - - - - 94066d58 by Alan Zimmerman at 2023-10-09T21:35:53-04:00 EPA: Introduce HasAnnotation class The class is defined as class HasAnnotation e where noAnnSrcSpan :: SrcSpan -> e This generalises noAnnSrcSpan, and allows noLocA :: (HasAnnotation e) => a -> GenLocated e a noLocA = L (noAnnSrcSpan noSrcSpan) - - - - - 8792a1bc by Ben Gamari at 2023-10-09T21:36:29-04:00 Bump unix submodule to v2.8.3.0 - - - - - e96c51cb by Andreas Klebinger at 2023-10-10T16:44:27+01:00 Add a flag -fkeep-auto-rules to optionally keep auto-generated rules around. The motivation for the flag is given in #21917. - - - - - 3ed58cef by Matthew Pickering at 2023-10-10T19:01:22-04:00 hadrian: Add ghcToolchain to tool args list This allows you to load ghc-toolchain and ghc-toolchain-bin into HLS. - - - - - 476c02d4 by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Normalise triple via config.sub We were not normalising the target triple anymore like we did with the old make build system. Fixes #23856 - - - - - 303dd237 by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Add missing vendor normalisation This is copied from m4/ghc_convert_vendor.m4 Towards #23868 - - - - - 838026c9 by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Add loongarch64 to parseArch Towards #23868 - - - - - 1a5bc0b5 by Matthew Pickering at 2023-10-10T19:01:22-04:00 Add same LD hack to ghc-toolchain In the ./configure script, if you pass the `LD` variable then this has the effect of stopping use searching for a linker and hence passing `-fuse-ld=...`. We want to emulate this logic in ghc-toolchain, if a use explicilty specifies `LD` variable then don't add `-fuse-ld=..` with the goal of making ./configure and ghc-toolchain agree on which flags to use when using the C compiler as a linker. This is quite unsavoury as we don't bake the choice of LD into the configuration anywhere but what's important for now is making ghc-toolchain and ./configure agree as much as possible. See #23857 for more discussion - - - - - 42d50b5a by Ben Gamari at 2023-10-10T19:01:22-04:00 ghc-toolchain: Check for C99 support with -std=c99 Previously we failed to try enabling C99 support with `-std=c99`, as `autoconf` attempts. This broke on older compilers (e.g. CentOS 7) which don't enable C99 by default. Fixes #23879. - - - - - da2961af by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Add endianess check using __BYTE_ORDER__ macro In very old toolchains the BYTE_ORDER macro is not set but thankfully the __BYTE_ORDER__ macro can be used instead. - - - - - d8da73cd by Matthew Pickering at 2023-10-10T19:01:22-04:00 configure: AC_PATH_TARGET_TOOL for LD We want to make sure that LD is set to an absolute path in order to be consistent with the `LD=$(command -v ld)` call. The AC_PATH_TARGET_TOOL macro uses the absolute path rather than AC_CHECK_TARGET_TOOL which might use a relative path. - - - - - 171f93cc by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Check whether we need -std=gnu99 for CPP as well In ./configure the C99 flag is passed to the C compiler when used as a C preprocessor. So we also check the same thing in ghc-toolchain. - - - - - 89a0918d by Matthew Pickering at 2023-10-10T19:01:22-04:00 Check for --target linker flag separately to C compiler There are situations where the C compiler doesn't accept `--target` but when used as a linker it does (but doesn't do anything most likely) In particular with old gcc toolchains, the C compiler doesn't support --target but when used as a linker it does. - - - - - 37218329 by Matthew Pickering at 2023-10-10T19:01:22-04:00 Use Cc to compile test file in nopie check We were attempting to use the C compiler, as a linker, to compile a file in the nopie check, but that won't work in general as the flags we pass to the linker might not be compatible with the ones we pass when using the C compiler. - - - - - 9b2dfd21 by Matthew Pickering at 2023-10-10T19:01:22-04:00 configure: Error when ghc-toolchain fails to compile This is a small QOL change as if you are working on ghc-toolchain and it fails to compile then configure will continue and can give you outdated results. - - - - - 1f0de49a by Matthew Pickering at 2023-10-10T19:01:22-04:00 configure: Check whether -no-pie works when the C compiler is used as a linker `-no-pie` is a flag we pass when using the C compiler as a linker (see pieCCLDOpts in GHC.Driver.Session) so we should test whether the C compiler used as a linker supports the flag, rather than just the C compiler. - - - - - 62cd2579 by Matthew Pickering at 2023-10-10T19:01:22-04:00 ghc-toolchain: Remove javascript special case for --target detection emcc when used as a linker seems to ignore the --target flag, and for consistency with configure which now tests for --target, we remove this special case. - - - - - 0720fde7 by Ben Gamari at 2023-10-10T19:01:22-04:00 toolchain: Don't pass --target to emscripten toolchain As noted in `Note [Don't pass --target to emscripten toolchain]`, emscripten's `emcc` is rather inconsistent with respect to its treatment of the `--target` flag. Avoid this by special-casing this toolchain in the `configure` script and `ghc-toolchain`. Fixes on aspect of #23744. - - - - - 6354e1da by Matthew Pickering at 2023-10-10T19:01:22-04:00 hadrian: Don't pass `--gcc-options` as a --configure-arg to cabal configure Stop passing -gcc-options which mixed together linker flags and non-linker flags. There's no guarantee the C compiler will accept both of these in each mode. - - - - - c00a4bd6 by Ben Gamari at 2023-10-10T19:01:22-04:00 configure: Probe stage0 link flags For consistency with later stages and CC. - - - - - 1f11e7c4 by Sebastian Graf at 2023-10-10T19:01:58-04:00 Stricter Binary.get in GHC.Types.Unit (#23964) I noticed some thunking while looking at Core. This change has very modest, but throughout positive ghc/alloc effect: ``` hard_hole_fits(normal) ghc/alloc 283,057,664 281,620,872 -0.5% geo. mean -0.1% minimum -0.5% maximum +0.0% ``` Fixes #23964. - - - - - a4f1a181 by Bryan Richter at 2023-10-10T19:02:37-04:00 rel_eng/upload.sh cleanups - - - - - 80705335 by doyougnu at 2023-10-10T19:03:18-04:00 ci: add javascript label rule This adds a rule which triggers the javascript job when the "javascript" label is assigned to an MR. - - - - - a2c0fff6 by Matthew Craven at 2023-10-10T19:03:54-04:00 Make 'wWarningFlagsDeps' include every WarningFlag Fixes #24071. - - - - - d055f099 by Jan Hrček at 2023-10-10T19:04:33-04:00 Fix pretty printing of overlap pragmas in TH splices (fixes #24074) - - - - - 0746b868 by Andreas Klebinger at 2023-10-10T19:05:09-04:00 Aarch64 NCG: Use encoded immediates for literals. Try to generate instr x2, <imm> instead of mov x1, lit instr x2, x1 When possible. This get's rid if quite a few redundant mov instructions. I believe this causes a metric decrease for LargeRecords as we reduce register pressure. ------------------------- Metric Decrease: LargeRecord ------------------------- - - - - - 739f4e6f by Andreas Klebinger at 2023-10-10T19:05:09-04:00 AArch NCG: Refactor getRegister' Remove some special cases which can be handled just as well by the generic case. This increases code re-use while also fixing #23749. Since some of the special case wasn't upholding Note [Signed arithmetic on AArch64]. - - - - - 1b213d33 by Andreas Klebinger at 2023-10-10T19:05:09-04:00 Aarch ncg: Optimize immediate use for address calculations When the offset doesn't fit into the immediate we now just reuse the general getRegister' code path which is well optimized to compute the offset into a register instead of a special case for CmmRegOff. This means we generate a lot less code under certain conditions which is why performance metrics for these improve. ------------------------- Metric Decrease: T4801 T5321FD T5321Fun ------------------------- - - - - - b7df0732 by John Ericson at 2023-10-11T16:02:11-04:00 RTS configure: Move over mem management checks These are for heap allocation, a strictly RTS concern. All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. The RTS configure one has a new ``` AC_CHECK_SIZEOF([void *]) ``` that the top-level configure version didn't have, so that `ac_cv_sizeof_void_p` is defined. Once more code is moved over in latter commits, that can go away. Progress towards #17191 - - - - - 41130a65 by John Ericson at 2023-10-11T16:02:11-04:00 RTS configure: Move over `__thread` check This used by (@bgamari thinks) the `GCThread` abstraction in the RTS. All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. Progress towards #17191 - - - - - cc5ec2bd by John Ericson at 2023-10-11T16:02:11-04:00 RTS configure: Move over misc function checks These are for general use in the RTS. All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. Progress towards #17191 - - - - - 809e7c2d by John Ericson at 2023-10-11T16:02:11-04:00 RTS configure: Move over `eventfd` check This check is for the RTS part of the event manager and has a corresponding part in `base`. All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. Progress towards #17191 - - - - - 58f3babf by John Ericson at 2023-10-11T16:02:48-04:00 Split `FP_CHECK_PTHREADS` and move part to RTS configure `NEED_PTHREAD_LIB` is unused since 3609340743c1b25fdfd0e18b1670dac54c8d8623 (part of the make build system), and so is no longer defined. Progress towards #17191 - - - - - e99cf237 by Moritz Angermann at 2023-10-11T16:03:24-04:00 nativeGen: section flags for .text$foo only Commit 3ece9856d157c85511d59f9f862ab351bbd9b38b, was supposed to fix #22834 in !9810. It does however add "xr" indiscriminatly to .text sections even if splitSections is disabled. This leads to the assembler saying: ghc_1.s:7849:0: error: Warning: Ignoring changed section attributes for .text | 7849 | .section .text,"xr" | ^ - - - - - f383a242 by Sylvain Henry at 2023-10-11T16:04:04-04:00 Modularity: pass TempDir instead of DynFlags (#17957) - - - - - 34fc28b0 by John Ericson at 2023-10-12T06:48:28-04:00 Test that functions from `mingwex` are available Ryan wrote these two minimizations, but they never got added to the test suite. See #23309, #23378 Co-Authored-By: Ben Gamari <bgamari.foss at gmail.com> Co-Authored-By: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - bdb54a0e by John Ericson at 2023-10-12T06:48:28-04:00 Do not check for the `mingwex` library in `/configure` See the recent discussion in !10360 --- Cabal will itself check for the library for the packages that need it, and while the autoconf check additionally does some other things like define a `HAS_LIBMINGWEX` C Preprocessor macro, those other things are also unused and unneeded. Progress towards #17191, which aims to get rid of `/configure` entirely. - - - - - 43e814e1 by Ben Gamari at 2023-10-12T06:49:40-04:00 base: Introduce move modules into src The only non-move changes here are whitespace changes to pass the `whitespace` test and a few testsuite adaptations. - - - - - df81536f by Moritz Angermann at 2023-10-12T06:50:16-04:00 [PEi386 linker] Bounds check and null-deref guard We should resonably be able to expect that we won't exceed the number of sections if we assume to be dealing with legal object files. We can however not guarantee that we get some negative values, and while we try to special case most, we should exclude negative indexing into the sections array. We also need to ensure that we do not try to derefences targetSection, if it is NULL, due to the switch statement. - - - - - c74c4f00 by John Ericson at 2023-10-12T10:31:13-04:00 Move apple compat check to RTS configure - - - - - c80778ea by John Ericson at 2023-10-12T10:31:13-04:00 Move clock/timer fun checks to RTS configure Actual library check (which will set the Cabal flag) is left in the top-level configure for now. Progress towards #17191 - - - - - 7f9f2686 by John Ericson at 2023-10-12T10:31:13-04:00 Move visibility and "musttail" annotation checks to the RTS configure All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. Progress towards #17191 - - - - - ffb3efe6 by John Ericson at 2023-10-12T10:31:13-04:00 Move leading underscore checks to RTS configure `CabalLeadingUnderscore` is done via Hadrian already, so we can stop `AC_SUBST`ing it completely. - - - - - 25fa4b02 by John Ericson at 2023-10-12T10:31:13-04:00 Move alloca, fork, const, and big endian checks to RTS configure All of this should boil down to `AC_DEFINE` not `AC_SUBST`, so it belongs in the RTS configure and should be safe to move without modification. - - - - - 5170f42a by John Ericson at 2023-10-12T10:31:13-04:00 Move libdl check to RTS configure - - - - - ea7a1447 by John Ericson at 2023-10-12T10:31:13-04:00 Adjust `FP_FIND_LIBFFI` Just set vars, and `AC_SUBST` in top-level configure. Don't define `HAVE_SYSTEM_LIBFFI` because nothing is using it. It hasn't be in used since 3609340743c1b25fdfd0e18b1670dac54c8d8623 (part of the make build system). - - - - - f399812c by John Ericson at 2023-10-12T10:31:13-04:00 Split BFD support to RTS configure The flag is still in the top-level configure, but the other checks (which define various macros --- important) are in the RTS configure. - - - - - f64f44e9 by John Ericson at 2023-10-12T10:31:13-04:00 Split libm check between top level and RTS - - - - - dafc4709 by Moritz Angermann at 2023-10-12T10:31:49-04:00 CgUtils.fixStgRegStmt respect register width This change ensure that the reg + offset computation is always of the same size. Before this we could end up with a 64bit register, and then add a 32bit offset (on 32bit platforms). This not only would fail type sanity checking, but also incorrectly truncate 64bit values into 32bit values silently on 32bit architectures. - - - - - 9e6ef7ba by Matthew Pickering at 2023-10-12T20:35:00-04:00 hadrian: Decrease verbosity of cabal commands In Normal, most tools do not produce output to stdout unless there are error conditions. Reverts 7ed65f5a1bc8e040e318ccff395f53a9bbfd8217 - - - - - 08fc27af by John Ericson at 2023-10-12T20:35:36-04:00 Do not substitute `@...@` for stage-specific values in cabal files `rts` and `ghc-prim` now no longer have a `*.cabal.in` to set Cabal flag defaults; instead manual choices are passed to configure in the usual way. The old way was fundamentally broken, because it meant we were baking these Cabal files for a specific stage. Now we only do stage-agnostic @...@ substitution in cabal files (the GHC version), and so all stage-specific configuration is properly confined to `_build` and the right stage dir. Also `include-ghc-prim` is a flag that no longer exists for `ghc-prim` (it was removed in 835d8ddbbfb11796ea8a03d1806b7cee38ba17a6) so I got rid of it. Co-Authored-By: Matthew Pickering <matthewtpickering at gmail.com> - - - - - a0ac8785 by Sebastian Graf at 2023-10-14T19:17:12-04:00 Fix restarts in .ghcid Using the whole of `hadrian/` restarted in a loop for me. - - - - - fea9ecdb by Sebastian Graf at 2023-10-14T19:17:12-04:00 CorePrep: Refactor FloatingBind (#23442) A drastically improved architecture for local floating in CorePrep that decouples the decision of whether a float is going to be let- or case-bound from how far it can float (out of strict contexts, out of lazy contexts, to top-level). There are a couple of new Notes describing the effort: * `Note [Floating in CorePrep]` for the overview * `Note [BindInfo and FloatInfo]` for the new classification of floats * `Note [Floats and FloatDecision]` for how FloatInfo is used to inform floating decisions This is necessary ground work for proper treatment of Strict fields and unlifted values at top-level. Fixes #23442. NoFib results (omitted = 0.0%): ``` -------------------------------------------------------------------------------- Program Allocs Instrs -------------------------------------------------------------------------------- pretty 0.0% -1.6% scc 0.0% -1.7% -------------------------------------------------------------------------------- Min 0.0% -1.7% Max 0.0% -0.0% Geometric Mean -0.0% -0.0% ``` - - - - - 32523713 by Matthew Pickering at 2023-10-14T19:17:49-04:00 hadrian: Move ghcBinDeps into ghcLibDeps This completes a5227080b57cb51ac34d4c9de1accdf6360b818b, the `ghc-usage.txt` and `ghci-usage.txt` file are also used by the `ghc` library so need to make sure they are present in the libdir even if we are not going to build `ghc-bin`. This also fixes things for cross compilers because the stage2 cross-compiler requires the ghc-usage.txt file, but we are using the stage2 lib folder but not building stage3:exe:ghc-bin so ghc-usage.txt was not being generated. - - - - - ec3c4488 by sheaf at 2023-10-14T19:18:29-04:00 Combine GREs when combining in mkImportOccEnv In `GHC.Rename.Names.mkImportOccEnv`, we sometimes discard one import item in favour of another, as explained in Note [Dealing with imports] in `GHC.Rename.Names`. However, this can cause us to lose track of important parent information. Consider for example #24084: module M1 where { class C a where { type T a } } module M2 ( module M1 ) where { import M1 } module M3 where { import M2 ( C, T ); instance C () where T () = () } When processing the import list of `M3`, we start off (for reasons that are not relevant right now) with two `Avail`s attached to `T`, namely `C(C, T)` and `T(T)`. We combine them in the `combine` function of `mkImportOccEnv`; as described in Note [Dealing with imports] we discard `C(C, T)` in favour of `T(T)`. However, in doing so, we **must not** discard the information want that `C` is the parent of `T`. Indeed, losing track of this information can cause errors when importing, as we could get an error of the form ‘T’ is not a (visible) associated type of class ‘C’ We fix this by combining the two GREs for `T` using `plusGRE`. Fixes #24084 - - - - - 257c2807 by Ilias Tsitsimpis at 2023-10-14T19:19:07-04:00 hadrian: Pass -DNOSMP to C compiler when needed Hadrian passes the -DNOSMP flag to GHC when the target doesn't support SMP, but doesn't pass it to CC as well, leading to the following compilation error on mips64el: | Run Cc (FindCDependencies CDep) Stage1: rts/sm/NonMovingScav.c => _build/stage1/rts/build/c/sm/NonMovingScav.o.d Command line: /usr/bin/mips64el-linux-gnuabi64-gcc -E -MM -MG -MF _build/stage1/rts/build/c/hooks/FlagDefaults.thr_debug_p_o.d -MT _build/stage1/rts/build/c/hooks/FlagDefaults.o -Irts/include -I_build/stage1/rts/build -I_build/stage1/rts/build/include -Irts/include -x c rts/hooks/FlagDefaults.c -Wall -Wextra -Wstrict-prototypes -Wmissing-prototypes -Wmissing-declarations -Winline -Wpointer-arith -Wmissing-noreturn -Wnested-externs -Wredundant-decls -Wundef -fno-strict-aliasing -DTHREADED_RTS -DDEBUG -fomit-frame-pointer -O2 -g -Irts -I_build/stage1/rts/build -DDEBUG -fno-omit-frame-pointer -g3 -O0 ===> Command failed with error code: 1 In file included from rts/include/Stg.h:348, from rts/include/Rts.h:38, from rts/hooks/FlagDefaults.c:8: rts/include/stg/SMP.h:416:2: error: #error memory barriers unimplemented on this architecture 416 | #error memory barriers unimplemented on this architecture | ^~~~~ rts/include/stg/SMP.h:440:2: error: #error memory barriers unimplemented on this architecture 440 | #error memory barriers unimplemented on this architecture | ^~~~~ rts/include/stg/SMP.h:464:2: error: #error memory barriers unimplemented on this architecture 464 | #error memory barriers unimplemented on this architecture | ^~~~~ The old make system correctly passed this flag to both GHC and CC [1]. Fix this error by passing -DNOSMP to CC as well. [1] https://gitlab.haskell.org/ghc/ghc/-/blob/00920f176b0235d5bb52a8e054d89a664f8938fe/rts/ghc.mk#L407 Closes #24082 - - - - - 13d3c613 by John Ericson at 2023-10-14T19:19:42-04:00 Users Guide: Drop dead code for Haddock refs to `parallel` I noticed while working on !11451 that `@LIBRARY_parallel_UNIT_ID@` was not substituted. It is dead code -- there is no `parallel-ref` usages and it doesn't look like there ever was (going back to 3e5d0f188d6c8633e55e9ba6c8941c07e459fa4b), so let's delete it. - - - - - fe067577 by Sylvain Henry at 2023-10-18T19:40:25-04:00 Avoid out-of-bound array access in bigNatIsPowerOf2 (fix #24066) bigNatIndex# in the `where` clause wasn't guarded by "bigNatIsZero a". - - - - - cc1625b1 by Sylvain Henry at 2023-10-18T19:40:25-04:00 Bignum: fix right shift of negative BigNat with native backend - - - - - cbe4400d by Sylvain Henry at 2023-10-18T19:40:25-04:00 Rts: expose rtsOutOfBoundsAccess symbol - - - - - 72c7380c by Sylvain Henry at 2023-10-18T19:40:25-04:00 Hadrian: enable `-fcheck-prim-bounds` in validate flavour This allows T24066 to fail when the bug is present. Otherwise the out-of-bound access isn't detected as it happens in ghc-bignum which wasn't compiled with the bounds check. - - - - - f9436990 by John Ericson at 2023-10-18T19:41:01-04:00 Make Hadrian solely responsible for substituting `docs/users_guide/ghc_config.py.in` Fixes #24091 Progress on #23966 Issue #24091 reports that `@ProjectVersion@` is no longer being substituted in the GHC user's guide. I assume this is a recent issue, but I am not sure how it's worked since c1a3ecde720b3bddc2c8616daaa06ee324e602ab; it looks like both Hadrian and configure are trying to substitute the same `.in` file! Now only Hadrian does. That is better anyways; already something that issue #23966 requested. It seems like we were missing some dependencies in Hadrian. (I really, really hate that this is possible!) Hopefully it is fixed now. - - - - - b12df0bb by John Ericson at 2023-10-18T19:41:37-04:00 `ghcversion.h`: No need to cope with undefined `ProjectPatchLevel*` Since 4e6c80197f1cc46dfdef0300de46847c7cfbdcb0, these are guaranteed to be defined. (Guaranteed including a test in the testsuite.) - - - - - 0295375a by John Ericson at 2023-10-18T19:41:37-04:00 Generate `ghcversion.h` from a `.in` file Now that there are no conditional sections (see the previous commit), we can just a do simple substitution rather than pasting it together line by line. Progress on #23966 - - - - - 740a1b85 by Krzysztof Gogolewski at 2023-10-19T11:37:20-04:00 Add a regression test for #24064 - - - - - 921fbf2f by Hécate Moonlight at 2023-10-19T11:37:59-04:00 CLC Proposal #182: Export List from Data.List Proposal link: https://github.com/haskell/core-libraries-committee/issues/182 - - - - - 4f02d3c1 by Sylvain Henry at 2023-10-20T04:01:32-04:00 rts: fix small argument passing on big-endian arch (fix #23387) - - - - - b86243b4 by Sylvain Henry at 2023-10-20T04:02:13-04:00 Interpreter: fix literal alignment on big-endian architectures (fix #19261) Literals weren't correctly aligned on big-endian, despite what the comment said. - - - - - a4b2ec47 by Sylvain Henry at 2023-10-20T04:02:54-04:00 Testsuite: recomp011 and recomp015 are fixed on powerpc These tests have been fixed but not tested and re-enabled on big-endian powerpc (see comments in #11260 and #11323) - - - - - fded7dd4 by Sebastian Graf at 2023-10-20T04:03:30-04:00 CorePrep: Allow floating dictionary applications in -O0 into a Rec (#24102) - - - - - 02efc181 by John Ericson at 2023-10-22T02:48:55-04:00 Move function checks to RTS configure Some of these functions are used in `base` too, but we can copy the checks over to its configure if that's an issue. - - - - - 5f4bccab by John Ericson at 2023-10-22T02:48:55-04:00 Move over a number of C-style checks to RTS configure - - - - - 5cf04f58 by John Ericson at 2023-10-22T02:48:55-04:00 Move/Copy more `AC_DEFINE` to RTS config Only exception is the LLVM version macros, which are used for GHC itself. - - - - - b8ce5dfe by John Ericson at 2023-10-22T02:48:55-04:00 Define `TABLES_NEXT_TO_CODE` in the RTS configure We create a new cabal flag to facilitate this. - - - - - 4a40271e by John Ericson at 2023-10-22T02:48:55-04:00 Configure scripts: `checkOS`: Make a bit more robust `mingw64` and `mingw32` are now both accepted for `OSMinGW32`. This allows us to cope with configs/triples that we haven't normalized extra being what GNU `config.sub` does. - - - - - 16bec0a0 by John Ericson at 2023-10-22T02:48:55-04:00 Generate `ghcplatform.h` from RTS configure We create a new cabal flag to facilitate this. - - - - - 7dfcab2f by John Ericson at 2023-10-22T02:48:55-04:00 Get rid of all mention of `mk/config.h` The RTS configure script is now solely responsible for managing its headers; the top level configure script does not help. - - - - - c1e3719c by Cheng Shao at 2023-10-22T02:49:33-04:00 rts: drop stale mentions of MIN_UPD_SIZE We used to have MIN_UPD_SIZE macro that describes the minimum reserved size for thunks, so that the thunk can be overwritten in place as indirections or blackholes. However, this macro has not been actually defined or used anywhere since a long time ago; StgThunkHeader already reserves a padding word for this purpose. Hence this patch which drops stale mentions of MIN_UPD_SIZE. - - - - - d24b0d85 by Andrew Lelechenko at 2023-10-22T02:50:11-04:00 base changelog: move non-backported entries from 4.19 section to 4.20 Neither !10933 (check https://hackage.haskell.org/package/base-4.19.0.0/docs/src/Text.Read.Lex.html#numberToRangedRational) nor !10189 (check https://hackage.haskell.org/package/base-4.19.0.0/docs/src/Data.List.NonEmpty.html#unzip) were backported to `base-4.19.0.0`. Moving them to `base-4.20.0.0` section. Also minor stylistic changes to other entries, bringing them to a uniform form. - - - - - de78b32a by Alan Zimmerman at 2023-10-23T09:09:41-04:00 EPA Some tweaks to annotations - Fix span for GRHS - Move TrailingAnns from last match to FunBind - Fix GADT 'where' clause span - Capture full range for a CaseAlt Match - - - - - d5a8780d by Simon Hengel at 2023-10-23T09:10:23-04:00 Update primitives.rst - - - - - 4d075924 by Josh Meredith at 2023-10-24T23:04:12+11:00 JS/userguide: add explanation of writing jsbits - - - - - 07ab5cc1 by Cheng Shao at 2023-10-24T15:40:32-04:00 testsuite: increase timeout of ghc-api tests for wasm32 ghc-api tests for wasm32 are more likely to timeout due to the large wasm module sizes, especially when testing with wasm native tail calls, given wasmtime's handling of tail call opcodes are suboptimal at the moment. It makes sense to increase timeout specifically for these tests on wasm32. This doesn't affect other targets, and for wasm32 we don't increase timeout for all tests, so not to risk letting major performance regressions slip through the testsuite. - - - - - 0d6acca5 by Greg Steuck at 2023-10-26T08:44:23-04:00 Explicitly require RLIMIT_AS before use in OSMem.c This is done elsewhere in the source tree. It also suddenly is required on OpenBSD. - - - - - 9408b086 by Sylvain Henry at 2023-10-26T08:45:03-04:00 Modularity: modularize external linker Decouple runLink from DynFlags to allow calling runLink more easily. This is preliminary work for calling Emscripten's linker (emcc) from our JavaScript linker. - - - - - e0f35030 by doyougnu at 2023-10-27T08:41:12-04:00 js: add JStg IR, remove unsaturated constructor - Major step towards #22736 and adding the optimizer in #22261 - - - - - 35587eba by Simon Peyton Jones at 2023-10-27T08:41:48-04:00 Fix a bug in tail calls with ticks See #24078 for the diagnosis. The change affects only the Tick case of occurrence analysis. It's a bit hard to test, so no regression test (yet anyway). - - - - - 9bc5cb92 by Matthew Craven at 2023-10-28T07:06:17-04:00 Teach tag-inference about SeqOp/seq# Fixes the STG/tag-inference analogue of #15226. Co-Authored-By: Simon Peyton Jones <simon.peytonjones at gmail.com> - - - - - 34f06334 by Moritz Angermann at 2023-10-28T07:06:53-04:00 [PEi386] Mask SYM_TYPE_DUP_DISCARD in makeSymbolExtra 48e391952c17ff7eab10b0b1456e3f2a2af28a9b introduced `SYM_TYPE_DUP_DISCARD` to the bitfield. The linker however, failed to mask the `SYM_TYPE_DUP_DISCARD` value. Thus `== SYM_TYPE_CODE` comparisons easily failed. This lead to us relocating DATA lookups (GOT) into E8 (call) and E9 (jump) instructions. - - - - - 5b51b2a2 by Mario Blažević at 2023-10-28T07:07:33-04:00 Fix and test for issue #24111, TH.Ppr output of pattern synonyms - - - - - 723bc352 by Alan Zimmerman at 2023-10-30T20:36:41-04:00 EPA: print doc comments as normal comments And ignore the ones allocated in haddock processing. It does not guarantee that every original haddock-like comment appears in the output, as it discards ones that have no legal attachment point. closes #23459 - - - - - 21b76843 by Simon Peyton Jones at 2023-10-30T20:37:17-04:00 Fix non-termination bug in equality solver constraint left-to-right then right to left, forever. Easily fixed. - - - - - 270867ac by Sebastian Graf at 2023-10-30T20:37:52-04:00 ghc-toolchain: build with `-package-env=-` (#24131) Otherwise globally installed libraries (via `cabal install --lib`) break the build. Fixes #24131. - - - - - 4d08364e by Alan Zimmerman at 2023-10-31T19:46:45+00:00 EPA: match changes in GHC - EPA: Comments in AnchorOperation - EPA: Remove EpaEofComment - - - - - 7a90020f by Krzysztof Gogolewski at 2023-10-31T20:03:37-04:00 docs: fix ScopedTypeVariables example (#24101) The previous example didn't compile. Furthermore, it wasn't demonstrating the point properly. I have changed it to an example which shows that 'a' in the signature must be the same 'a' as in the instance head. - - - - - 49f69f50 by Krzysztof Gogolewski at 2023-10-31T20:04:13-04:00 Fix pretty-printing of type family dependencies "where" should be after the injectivity annotation. - - - - - 73c191c0 by Ben Gamari at 2023-10-31T20:04:49-04:00 gitlab-ci: Bump LLVM bootstrap jobs to Debian 12 As the Debian 10 images have too old an LLVM. Addresses #24056. - - - - - 5b0392e0 by Matthew Pickering at 2023-10-31T20:04:49-04:00 ci: Run aarch64 llvm backend job with "LLVM backend" label This brings it into line with the x86 LLVM backend job. - - - - - 9f9c9227 by Ryan Scott at 2023-11-01T09:19:12-04:00 More robust checking for DataKinds As observed in #22141, GHC was not doing its due diligence in catching code that should require `DataKinds` in order to use. Most notably, it was allowing the use of arbitrary data types in kind contexts without `DataKinds`, e.g., ```hs data Vector :: Nat -> Type -> Type where ``` This patch revamps how GHC tracks `DataKinds`. The full specification is written out in the `DataKinds` section of the GHC User's Guide, and the implementation thereof is described in `Note [Checking for DataKinds]` in `GHC.Tc.Validity`. In brief: * We catch _type_-level `DataKinds` violations in the renamer. See `checkDataKinds` in `GHC.Rename.HsType` and `check_data_kinds` in `GHC.Rename.Pat`. * We catch _kind_-level `DataKinds` violations in the typechecker, as this allows us to catch things that appear beneath type synonyms. (We do *not* want to do this in type-level contexts, as it is perfectly fine for a type synonym to mention something that requires DataKinds while still using the type synonym in a module that doesn't enable DataKinds.) See `checkValidType` in `GHC.Tc.Validity`. * There is now a single `TcRnDataKindsError` that classifies all manner of `DataKinds` violations, both in the renamer and the typechecker. The `NoDataKindsDC` error has been removed, as it has been subsumed by `TcRnDataKindsError`. * I have added `CONSTRAINT` is `isKindTyCon`, which is what checks for illicit uses of data types at the kind level without `DataKinds`. Previously, `isKindTyCon` checked for `Constraint` but not `CONSTRAINT`. This is inconsistent, given that both `Type` and `TYPE` were checked by `isKindTyCon`. Moreover, it thwarted the implementation of the `DataKinds` check in `checkValidType`, since we would expand `Constraint` (which was OK without `DataKinds`) to `CONSTRAINT` (which was _not_ OK without `DataKinds`) and reject it. Now both are allowed. * I have added a flurry of additional test cases that test various corners of `DataKinds` checking. Fixes #22141. - - - - - 575d7690 by Sylvain Henry at 2023-11-01T09:19:53-04:00 JS: fix FFI "wrapper" and "dynamic" Fix codegen and helper functions for "wrapper" and "dynamic" foreign imports. Fix tests: - ffi006 - ffi011 - T2469 - T4038 Related to #22363 - - - - - 81fb8885 by Alan Zimmerman at 2023-11-01T22:23:56-04:00 EPA: Use full range for Anchor This change requires a series of related changes, which must all land at the same time, otherwise all the EPA tests break. * Use the current Anchor end as prior end Use the original anchor location end as the source of truth for calculating print deltas. This allows original spacing to apply in most cases, only changed AST items need initial delta positions. * Add DArrow to TrailingAnn * EPA Introduce HasTrailing in ExactPrint Use [TrailingAnn] in enterAnn and remove it from ExactPrint (LocatedN RdrName) * In HsDo, put TrailingAnns at top of LastStmt * EPA: do not convert comments to deltas when balancing. * EPA: deal with fallout from getMonoBind * EPA fix captureLineSpacing * EPA print any comments in the span before exiting it * EPA: Add comments to AnchorOperation * EPA: remove AnnEofComment, it is no longer used Updates Haddock submodule - - - - - 03e82511 by Rodrigo Mesquita at 2023-11-01T22:24:32-04:00 Fix in docs regarding SSymbol, SNat, SChar (#24119) - - - - - 362cc693 by Matthew Pickering at 2023-11-01T22:25:08-04:00 hadrian: Update bootstrap plans (9.4.6, 9.4.7, 9.6.2, 9.6.3, 9.8.1) Updating the bootstrap plans with more recent GHC versions. - - - - - 00b9b8d3 by Matthew Pickering at 2023-11-01T22:25:08-04:00 ci: Add 9.8.1 bootstrap testing job - - - - - ef3d20f8 by Matthew Pickering at 2023-11-01T22:25:08-04:00 Compatibility with 9.8.1 as boot compiler This fixes several compatability issues when using 9.8.1 as the boot compiler. * An incorrect version guard on the stack decoding logic in ghc-heap * Some ghc-prim bounds need relaxing * ghc is no longer wired in, so we have to remove the -this-unit-id ghc call. Fixes #24077 - - - - - 6755d833 by Jaro Reinders at 2023-11-03T10:54:42+01:00 Add NCG support for common 64bit operations to the x86 backend. These used to be implemented via C calls which was obviously quite bad for performance for operations like simple addition. Co-authored-by: Andreas Klebinger - - - - - 0dfb1fa7 by Vladislav Zavialov at 2023-11-03T14:08:41-04:00 T2T in Expressions (#23738) This patch implements the T2T (term-to-type) transformation in expressions. Given a function with a required type argument vfun :: forall a -> ... the user can now call it as vfun (Maybe Int) instead of vfun (type (Maybe Int)) The Maybe Int argument is parsed and renamed as a term (HsExpr), but then undergoes a conversion to a type (HsType). See the new function expr_to_type in compiler/GHC/Tc/Gen/App.hs and Note [RequiredTypeArguments and the T2T mapping] Left as future work: checking for puns. - - - - - cc1c7c54 by Duncan Coutts at 2023-11-05T00:23:44-04:00 Add a test for I/O managers It tries to cover the cases of multiple threads waiting on the same fd for reading and multiple threads waiting for writing, including wait cancellation by async exceptions. It should work for any I/O manager, in-RTS or in-Haskell. Unfortunately it will not currently work for Windows because it relies on anonymous unix sockets. It could in principle be ported to use Windows named pipes. - - - - - 2e448f98 by Cheng Shao at 2023-11-05T00:23:44-04:00 Skip the IOManager test on wasm32 arch. The test relies on the sockets API which are not (yet) available. - - - - - fe50eb35 by Cheng Shao at 2023-11-05T00:24:20-04:00 compiler: fix eager blackhole symbol in wasm32 NCG - - - - - af771148 by Cheng Shao at 2023-11-05T00:24:20-04:00 testsuite: fix optasm tests for wasm32 - - - - - 1b90735c by Matthew Pickering at 2023-11-05T00:24:20-04:00 testsuite: Add wasm32 to testsuite arches with NCG The compiler --info reports that wasm32 compilers have a NCG, so we should agree with that here. - - - - - db9a6496 by Alan Zimmerman at 2023-11-05T00:24:55-04:00 EPA: make locA a function, not a field name And use it to generalise reLoc The following for the windows pipeline one. 5.5% Metric Increase: T5205 - - - - - 833e250c by Simon Peyton Jones at 2023-11-05T00:25:31-04:00 Update the unification count in wrapUnifierX Omitting this caused type inference to fail in #24146. This was an accidental omision in my refactoring of the equality solver. - - - - - e451139f by Andreas Klebinger at 2023-11-05T00:26:07-04:00 Remove an accidental git conflict marker from a comment. - - - - - e7da0d25 by Alan Zimmerman at 2023-11-05T11:20:31+00:00 EPA: match changes in GHC, l2l cleanup - - - - - 30baac7a by Tobias Haslop at 2023-11-06T10:50:32+00:00 Add laws relating between Foldable/Traversable with their Bi- superclasses See https://github.com/haskell/core-libraries-committee/issues/205 for discussion. This commit also documents that the tuple instances only satisfy the laws up to lazyness, similar to the documentation added in !9512. - - - - - df626f00 by Tobias Haslop at 2023-11-07T02:20:37-05:00 Elaborate on the quantified superclass of Bifunctor This was requested in the comment https://github.com/haskell/core-libraries-committee/issues/93#issuecomment-1597271700 for when Traversable becomes a superclass of Bitraversable, but similarly applies to Functor/Bifunctor, which already are in a superclass relationship. - - - - - 8217acb8 by Alan Zimmerman at 2023-11-07T02:21:12-05:00 EPA: get rid of l2l and friends Replace them with l2l to convert the location la2la to convert a GenLocated thing Updates haddock submodule - - - - - dd88a260 by Luite Stegeman at 2023-11-07T02:21:53-05:00 JS: remove broken newIdents from JStg Monad GHC.JS.JStg.Monad.newIdents was broken, resulting in duplicate identifiers being generated in h$c1, h$c2, ... . This change removes the broken newIdents. - - - - - 455524a2 by Matthew Craven at 2023-11-09T08:41:59-05:00 Create specially-solved DataToTag class Closes #20532. This implements CLC proposal 104: https://github.com/haskell/core-libraries-committee/issues/104 The design is explained in Note [DataToTag overview] in GHC.Tc.Instance.Class. This replaces the existing `dataToTag#` primop. These metric changes are not "real"; they represent Unique-related flukes triggering on a different set of jobs than they did previously. See also #19414. Metric Decrease: T13386 T8095 Metric Increase: T13386 T8095 Co-authored-by: Simon Peyton Jones <simon.peytonjones at gmail.com> - - - - - a05f4554 by Alan Zimmerman at 2023-11-09T08:42:35-05:00 EPA: get rid of glRR and friends in GHC/Parser.y With the HasLoc and HasAnnotation classes, we can replace a number of type-specific helper functions in the parser with polymorphic ones instead Metric Decrease: MultiLayerModulesTH_Make - - - - - 18498538 by Cheng Shao at 2023-11-09T16:58:12+00:00 ci: bump ci-images for wasi-sdk upgrade - - - - - 52c0fc69 by PHO at 2023-11-09T19:16:22-05:00 Don't assume the current locale is *.UTF-8, set the encoding explicitly primops.txt contains Unicode characters: > LC_ALL=C ./genprimopcode --data-decl < ./primops.txt > genprimopcode: <stdin>: hGetContents: invalid argument (cannot decode byte sequence starting from 226) Hadrian must also avoid using readFile' to read primops.txt because it tries to decode the file with a locale-specific encoding. - - - - - 7233b3b1 by PHO at 2023-11-09T19:17:01-05:00 Use '[' instead of '[[' because the latter is a Bash-ism It doesn't work on platforms where /bin/sh is something other than Bash. - - - - - 6dbab180 by Simon Peyton Jones at 2023-11-09T19:17:36-05:00 Add an extra check in kcCheckDeclHeader_sig Fix #24083 by checking for a implicitly-scoped type variable that is not actually bound. See Note [Disconnected type variables] in GHC.Tc.Gen.HsType For some reason, on aarch64-darwin we saw a 2.8% decrease in compiler allocations for MultiLayerModulesTH_Make; but 0.0% on other architectures. Metric Decrease: MultiLayerModulesTH_Make - - - - - 22551364 by Sven Tennie at 2023-11-11T06:35:22-05:00 AArch64: Delete unused LDATA pseudo-instruction Though there were consuming functions for LDATA, there were no producers. Thus, the removed code was "dead". - - - - - 2a0ec8eb by Alan Zimmerman at 2023-11-11T06:35:59-05:00 EPA: harmonise acsa and acsA in GHC/Parser.y With the HasLoc class, we can remove the acsa helper function, using acsA instead. - - - - - 4ceac14d by Alan Zimmerman at 2023-11-11T15:16:41+00:00 EPA: Replace Anchor with EpaLocation Match GHC - - - - - 7ae517a0 by Teo Camarasu at 2023-11-12T08:04:12-05:00 nofib: bump submodule This includes changes that: - fix building a benchmark with HEAD - remove a Makefile-ism that causes errors in bash scripts Resolves #24178 - - - - - 3f0036ec by Alan Zimmerman at 2023-11-12T08:04:47-05:00 EPA: Replace Anchor with EpaLocation An Anchor has a location and an operation, which is either that it is unchanged or that it has moved with a DeltaPos data Anchor = Anchor { anchor :: RealSrcSpan , anchor_op :: AnchorOperation } An EpaLocation also has either a location or a DeltaPos data EpaLocation = EpaSpan !RealSrcSpan !(Strict.Maybe BufSpan) | EpaDelta !DeltaPos ![LEpaComment] Now that we do not care about always having a location in the anchor, we remove Anchor and replace it with EpaLocation We do this with a type alias initially, to ease the transition. The alias will be removed in time. We also have helpers to reconstruct the AnchorOperation from an EpaLocation. This is also temporary. Updates Haddock submodule - - - - - a7492048 by Alan Zimmerman at 2023-11-12T13:43:07+00:00 EPA: get rid of AnchorOperation Now that the Anchor type is an alias for EpaLocation, remove AnchorOperation. Updates haddock submodule - - - - - 0745c34d by Andrew Lelechenko at 2023-11-13T16:25:07-05:00 Add since annotation for showHFloat - - - - - e98051a5 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 Suppress duplicate librares linker warning of new macOS linker Fixes #24167 XCode 15 introduced a new linker which warns on duplicate libraries being linked. To disable this warning, we pass -Wl,-no_warn_duplicate_libraries as suggested by Brad King in CMake issue #25297. This flag isn't necessarily available to other linkers on darwin, so we must only configure it into the CC linker arguments if valid. - - - - - c411c431 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 testsuite: Encoding test witnesses recent iconv bug is fragile A regression in the new iconv() distributed with XCode 15 and MacOS Sonoma causes the test 'encoding004' to fail in the CP936 roundrip. We mark this test as fragile until this is fixed upstream (rather than broken, since previous versions of iconv pass the test) See #24161 - - - - - ce7fe5a9 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 testsuite: Update to LC_ALL=C no longer being ignored in darwin MacOS seems to have fixed an issue where it used to ignore the variable `LC_ALL` in program invocations and default to using Unicode. Since the behaviour seems to be fixed to account for the locale variable, we mark tests that were previously broken in spite of it as fragile (since they now pass in recent macOS distributions) See #24161 - - - - - e6c803f7 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 darwin: Fix single_module is obsolete warning In XCode 15's linker, -single_module is the default and otherwise passing it as a flag results in a warning being raised: ld: warning: -single_module is obsolete This patch fixes this warning by, at configure time, determining whether the linker supports -single_module (which is likely false for all non-darwin linkers, and true for darwin linkers in previous versions of macOS), and using that information at runtime to decide to pass or not the flag in the invocation. Fixes #24168 - - - - - 929ba2f9 by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 testsuite: Skip MultiLayerModulesTH_Make on darwin The recent toolchain upgrade on darwin machines resulted in the MultiLayerModulesTH_Make test metrics varying too much from the baseline, ultimately blocking the CI pipelines. This commit skips the test on darwin to temporarily avoid failures due to the environment change in the runners. However, the metrics divergence is being investigated still (tracked in #24177) - - - - - af261ccd by Rodrigo Mesquita at 2023-11-15T13:18:58-05:00 configure: check target (not build) understands -no_compact_unwind Previously, we were branching on whether the build system was darwin to shortcut this check, but we really want to branch on whether the target system (which is what we are configuring ld_prog for) is darwin. - - - - - 2125c176 by Luite Stegeman at 2023-11-15T13:19:38-05:00 JS: Fix missing variable declarations The JStg IR update was missing some local variable declarations that were present earlier, causing global variables to be used implicitly (or an error in JavaScript strict mode). This adds the local variable declarations again. - - - - - 99ced73b by Krzysztof Gogolewski at 2023-11-15T13:20:14-05:00 Remove loopy superclass solve mechanism Programs with a -Wloopy-superclass-solve warning will now fail with an error. Fixes #23017 - - - - - 2aff2361 by Zubin Duggal at 2023-11-15T13:20:50-05:00 users-guide: Fix links to libraries from the users-guide. The unit-ids generated in c1a3ecde720b3bddc2c8616daaa06ee324e602ab include the package name, so we don't need to explicitly add it to the links. Fixes #24151 - - - - - 27981fac by Alan Zimmerman at 2023-11-15T13:21:25-05:00 EPA: splitLHsForAllTyInvis does not return ann We did not use the annotations returned from splitLHsForAllTyInvis, so do not return them. - - - - - a6467834 by Krzysztof Gogolewski at 2023-11-15T22:22:59-05:00 Document defaulting of RuntimeReps Fixes #24099 - - - - - 2776920e by Simon Peyton Jones at 2023-11-15T22:23:35-05:00 Second fix to #24083 My earlier fix turns out to be too aggressive for data/type families See wrinkle (DTV1) in Note [Disconnected type variables] - - - - - cee81370 by Sylvain Henry at 2023-11-16T09:57:46-05:00 Fix unusable units and module reexport interaction (#21097) This commit fixes an issue with ModUnusable introduced in df0f148feae. In mkUnusableModuleNameProvidersMap we traverse the list of unusable units and generate ModUnusable origin for all the modules they contain: exposed modules, hidden modules, and also re-exported modules. To do this we have a two-level map: ModuleName -> Unit:ModuleName (aka Module) -> ModuleOrigin So for each module name "M" in broken unit "u" we have: "M" -> u:M -> ModUnusable reason However in the case of module reexports we were using the *target* module as a key. E.g. if "u:M" is a reexport for "X" from unit "o": "M" -> o:X -> ModUnusable reason Case 1: suppose a reexport without module renaming (u:M -> o:M) from unusable unit u: "M" -> o:M -> ModUnusable reason Here it's claiming that the import of M is unusable because a reexport from u is unusable. But if unit o isn't unusable we could also have in the map: "M" -> o:M -> ModOrigin ... Issue: the Semigroup instance of ModuleOrigin doesn't handle the case (ModUnusable <> ModOrigin) Case 2: similarly we could have 2 unusable units reexporting the same module without renaming, say (u:M -> o:M) and (v:M -> o:M) with u and v unusable. It gives: "M" -> o:M -> ModUnusable ... (for u) "M" -> o:M -> ModUnusable ... (for v) Issue: the Semigroup instance of ModuleOrigin doesn't handle the case (ModUnusable <> ModUnusable). This led to #21097, #16996, #11050. To fix this, in this commit we make ModUnusable track whether the module used as key is a reexport or not (for better error messages) and we use the re-export module as key. E.g. if "u:M" is a reexport for "o:X" and u is unusable, we now record: "M" -> u:M -> ModUnusable reason reexported=True So now, we have two cases for a reexport u:M -> o:X: - u unusable: "M" -> u:M -> ModUnusable ... reexported=True - u usable: "M" -> o:X -> ModOrigin ... reexportedFrom=u:M The second case is indexed with o:X because in this case the Semigroup instance of ModOrigin is used to combine valid expositions of a module (directly or via reexports). Note that module lookup functions select usable modules first (those who have a ModOrigin value), so it doesn't matter if we add new ModUnusable entries in the map like this: "M" -> { u:M -> ModUnusable ... reexported=True o:M -> ModOrigin ... } The ModOrigin one will be used. Only if there is no ModOrigin or ModHidden entry will the ModUnusable error be printed. See T21097 for an example printing several reasons why an import is unusable. - - - - - 3e606230 by Krzysztof Gogolewski at 2023-11-16T09:58:22-05:00 Fix IPE test A helper function was defined in a different module than used. To reproduce: ./hadrian/build test --test-root-dirs=testsuite/tests/rts/ipe - - - - - 49f5264b by Andreas Klebinger at 2023-11-16T20:52:11-05:00 Properly compute unpacked sizes for -funpack-small-strict-fields. Use rep size rather than rep count to compute the size. Fixes #22309 - - - - - b4f84e4b by James Henri Haydon at 2023-11-16T20:52:53-05:00 Explicit methods for Alternative Compose Explicitly define some and many in Alternative instance for Data.Functor.Compose Implementation of https://github.com/haskell/core-libraries-committee/issues/181 - - - - - 9bc0dd1f by Ignat Insarov at 2023-11-16T20:53:34-05:00 Add permutations for non-empty lists. Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/68#issuecomment-1221409837 - - - - - 5643ecf9 by Andrew Lelechenko at 2023-11-16T20:53:34-05:00 Update changelog and since annotations for Data.List.NonEmpty.permutations Approved by CLC in https://github.com/haskell/core-libraries-committee/issues/68#issuecomment-1221409837 - - - - - 94ff2134 by Oleg Alexander at 2023-11-16T20:54:15-05:00 Update doc string for traceShow Updated doc string for traceShow. - - - - - faff671a by Luite Stegeman at 2023-11-17T14:12:51+01:00 JS: clean up some foreign imports - - - - - 856e0a4e by Sven Tennie at 2023-11-18T06:54:11-05:00 AArch64: Remove unused instructions As these aren't ever emitted, we don't even know if they work or will ever be used. If one of them is needed in future, we may easily re-add it. Deleted instructions are: - CMN - ANDS - BIC - BICS - EON - ORN - ROR - TST - STP - LDP - DMBSY - - - - - 615441ef by Alan Zimmerman at 2023-11-18T06:54:46-05:00 EPA: Replace Monoid with NoAnn Remove the final Monoid instances in the exact print infrastructure. For Windows CI Metric Decrease: T5205 - - - - - 5a6c49d4 by David Feuer at 2023-11-20T18:53:18-05:00 Speed up stimes in instance Semigroup Endo As discussed at https://github.com/haskell/core-libraries-committee/issues/4 - - - - - cf9da4b3 by Andrew Lelechenko at 2023-11-20T18:53:18-05:00 base: reflect latest changes in the changelog - - - - - 48bf364e by Alan Zimmerman at 2023-11-20T18:53:54-05:00 EPA: Use SrcSpan in EpaSpan This is more natural, since we already need to deal with invalid RealSrcSpans, and that is exactly what SrcSpan.UnhelpfulSpan is for. Updates haddock submodule. - - - - - 97ec37cc by Sebastian Graf at 2023-11-20T18:54:31-05:00 Add regression test for #6070 Fixes #6070. - - - - - e9d5ae41 by Owen Shepherd at 2023-11-21T18:32:23-05:00 chore: Correct typo in the gitlab MR template [skip ci] - - - - - f158a8d0 by Rodrigo Mesquita at 2023-11-21T18:32:59-05:00 Improve error message when reading invalid `.target` files A `.target` file generated by ghc-toolchain or by configure can become invalid if the target representation (`Toolchain.Target`) is changed while the files are not re-generated by calling `./configure` or `ghc-toolchain` again. There is also the issue of hadrian caching the dependencies on `.target` files, which makes parsing fail when reading reading the cached value if the representation has been updated. This patch provides a better error message in both situations, moving away from a terrible `Prelude.read: no parse` error that you would get otherwise. Fixes #24199 - - - - - 955520c6 by Ben Gamari at 2023-11-21T18:33:34-05:00 users guide: Note that QuantifiedConstraints implies ExplicitForAll Fixes #24025. - - - - - 17ec3e97 by Owen Shepherd at 2023-11-22T09:37:28+01:00 fix: Change type signatures in NonEmpty export comments to reflect reality This fixes several typos in the comments of Data.List.NonEmpty export list items. - - - - - 2fd78f9f by Samuel Thibault at 2023-11-22T11:49:13-05:00 Fix the platform string for GNU/Hurd As commited in Cargo https://github.com/haskell/cabal/pull/9434 there is confusion between "gnu" and "hurd". This got fixed in Cargo, we need the converse in Hadrian. Fixes #24180 - - - - - a79960fe by Alan Zimmerman at 2023-11-22T11:49:48-05:00 EPA: Tuple Present no longer has annotation The Present constructor for a Tuple argument will never have an exact print annotation. So make this impossible. - - - - - 121c9ab7 by David Binder at 2023-11-22T21:12:29-05:00 Unify the hpc testsuites The hpc testsuite was split between testsuite/tests/hpc and the submodule libraries/hpc/test. This commit unifies the two testsuites in the GHC repository in the directory testsuite/tests/hpc. - - - - - d2733a05 by Alan Zimmerman at 2023-11-22T21:13:05-05:00 EPA: empty tup_tail has noAnn In Parser.y, the tup_tail rule had the following option | {- empty -} %shift { return [Left noAnn] } Once this works through PostProcess.hs, it means we add an extra Missing constructor if the last item was a comma. Change the annotation type to a Bool to indicate this, and use the EpAnn Anchor for the print location for the others. - - - - - fa576eb8 by Andreas Klebinger at 2023-11-24T08:29:13-05:00 Fix FMA primops generating broken assembly on x86. `genFMA3Code` assumed that we had to take extra precations to avoid overwriting the result of `getNonClobberedReg`. One of these special cases caused a bug resulting in broken assembly. I believe we don't need to hadle these cases specially at all, which means this MR simply deletes the special cases to fix the bug. Fixes #24160 - - - - - 34d86315 by Alan Zimmerman at 2023-11-24T08:29:49-05:00 EPA: Remove parenthesizeHsType This is called from PostProcess.hs, and adds spurious parens. With the looser version of exact printing we had before we could tolerate this, as they would be swallowed by the original at the same place. But with the next change (remove EpAnnNotUsed) they result in duplicates in the output. For Darwin build: Metric Increase: MultiLayerModulesTH_OneShot - - - - - 3ede659d by Vladislav Zavialov at 2023-11-26T06:43:32-05:00 Add name for -Wdeprecated-type-abstractions (#24154) This warning had no name or flag and was triggered unconditionally. Now it is part of -Wcompat. - - - - - 7902ebf8 by Alan Zimmerman at 2023-11-26T06:44:08-05:00 EPA: Remove EpAnnNotUsed We no longer need the EpAnnNotUsed constructor for EpAnn, as we can represent an unused annotation with an anchor having a EpaDelta of zero, and empty comments and annotations. This simplifies code handling annotations considerably. Updates haddock submodule Metric Increase: parsing001 - - - - - 471b2672 by Mario Blažević at 2023-11-26T06:44:48-05:00 Bumped the upper bound of text to <2.2 - - - - - d1bf25c7 by Vladislav Zavialov at 2023-11-26T11:45:49-05:00 Term variable capture (#23740) This patch changes type variable lookup rules (lookupTypeOccRn) and implicit quantification rules (filterInScope) so that variables bound in the term namespace can be captured at the type level {-# LANGUAGE RequiredTypeArguments #-} f1 x = g1 @x -- `x` used in a type application f2 x = g2 (undefined :: x) -- `x` used in a type annotation f3 x = g3 (type x) -- `x` used in an embedded type f4 x = ... where g4 :: x -> x -- `x` used in a type signature g4 = ... This change alone does not allow us to accept examples shown above, but at least it gets them past the renamer. - - - - - da863d15 by Vladislav Zavialov at 2023-11-26T11:46:26-05:00 Update Note [hsScopedTvs and visible foralls] The Note was written before GHC gained support for visible forall in types of terms. Rewrite a few sentences and use a better example. - - - - - b5213542 by Matthew Pickering at 2023-11-27T12:53:59-05:00 testsuite: Add mechanism to collect generic metrics * Generalise the metric logic by adding an additional field which allows you to specify how to query for the actual value. Previously the method of querying the baseline value was abstracted (but always set to the same thing). * This requires rejigging how the stat collection works slightly but now it's more uniform and hopefully simpler. * Introduce some new "generic" helper functions for writing generic stats tests. - collect_size ( deviation, path ) Record the size of the file as a metric - stat_from_file ( metric, deviation, path ) Read a value from the given path, and store that as a metric - collect_generic_stat ( metric, deviation, get_stat) Provide your own `get_stat` function, `lambda way: <Int>`, which can be used to establish the current value of the metric. - collect_generic_stats ( metric_info ): Like collect_generic_stat but provide the whole dictionary of metric definitions. { metric: { deviation: <Int> current: lambda way: <Int> } } * Introduce two new "size" metrics for keeping track of build products. - `size_hello_obj` - The size of `hello.o` from compiling hello.hs - `libdir` - The total size of the `libdir` folder. * Track the number of modules in the AST tests - CountDepsAst - CountDepsParser This lays the infrastructure for #24191 #22256 #17129 - - - - - 7d9a2e44 by ARATA Mizuki at 2023-11-27T12:54:39-05:00 x86: Don't require -mavx2 when using 256-bit floating-point SIMD primitives Fixes #24222 - - - - - 4e5ff6a4 by Alan Zimmerman at 2023-11-27T12:55:15-05:00 EPA: Remove SrcSpanAnn Now that we only have a single constructor for EpAnn, And it uses a SrcSpan for its location, we can do away with SrcSpanAnn completely. It only existed to wrap the original SrcSpan in a location, and provide a place for the exact print annotation. For darwin only: Metric Increase: MultiLayerModulesTH_OneShot Updates haddock submodule - - - - - e05bca39 by Krzysztof Gogolewski at 2023-11-28T08:00:55-05:00 testsuite: don't initialize testdir to '.' The test directory is removed during cleanup, if there's an interrupt that could remove the entire repository. Fixes #24219 - - - - - af881674 by Alan Zimmerman at 2023-11-28T08:01:30-05:00 EPA: Clean up mkScope in Ast.hs Now that we have HasLoc we can get rid of all the custom variants of mkScope For deb10-numa Metric Increase: libdir - - - - - 292983c8 by Ben Gamari at 2023-11-28T22:44:28-05:00 distrib: Rediscover otool and install_name_tool on Darwin In the bindist configure script we must rediscover the `otool` and `install_name_tool`s since they may be different from the build environment. Fixes #24211. - - - - - dfe1c354 by Stefan Schulze Frielinghaus at 2023-11-28T22:45:04-05:00 llvmGen: Align objects in the data section Objects in the data section may be referenced via tagged pointers. Thus, align those objects to a 4- or 8-byte boundary for 32- or 64-bit platforms, respectively. Note, this may need to be reconsidered if objects with a greater natural alignment requirement are emitted as e.g. 128-bit atomics. Fixes #24163. - - - - - f6c486c3 by Matthew Pickering at 2023-11-29T11:08:13-05:00 metrics: Widen libdir and size_hello_obj acceptance window af8816740d9b8759be1a22af8adcb5f13edeb61d shows that the libdir size can fluctuate quite significantly even when the change is quite small. Therefore we widen the acceptance window to 10%. - - - - - 99a6a49c by Alan Zimmerman at 2023-11-29T11:08:49-05:00 EPA: Clean up TC Monad Utils We no longer need the alternative variant of addLocM (addLocMA) nor wrapLocAM, wrapLocSndMA. aarch64-darwin Metric Increase: MultiLayerModulesTH_OneShot deb10-numa-slow Metric Decrease: libdir - - - - - 94fb8d47 by Alan Zimmerman at 2023-11-29T18:10:26+00:00 Match GHC, No comments in EpaDelta for comments - - - - - cbc03fa0 by Sebastian Graf at 2023-11-30T12:37:21-05:00 perf tests: Move comments into new `Note [Sensitivity to unique increment]` (#19414) And additionally to T12545, link from T8095, T13386 to this new Note. - - - - - c7623b22 by Alan Zimmerman at 2023-11-30T12:37:56-05:00 EPA: EpaDelta for comment has no comments EpaLocation is used to position things. It has two constructors, EpaSpan holding a SrcSpan, and EpaDelta with a delta position and a possible list of comments. The comment list is needed because the location in EpaDelta has no absolute information to decide which comments should be emitted before them when printing. But it is also used for specifying the position of a comment. To prevent the absurdity of a comment position having a list of comments in it, we make EpaLocation parameterisable, using comments for the normal case and a constant for within comments. Updates haddock submodule. aarch64-darwin Metric Decrease: MultiLayerModulesTH_OneShot - - - - - bd8acc0c by Krzysztof Gogolewski at 2023-11-30T12:38:32-05:00 Kind-check body of a required forall We now require that in 'forall a -> ty', ty has kind TYPE r for some r. Fixes #24176 - - - - - 010fb784 by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Remove incorrect haddock link quotes in code block - - - - - cda9c12d by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Remove cycle from group haddock example - - - - - 495265b9 by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Use repl haddock syntax in group docs - - - - - d134d1de by Owen Shepherd at 2023-12-03T00:10:09-05:00 docs(NonEmpty/group): Use list [] notation in group haddock - - - - - dfcf629c by Owen Shepherd at 2023-12-03T00:10:10-05:00 docs(NonEmpty/group): Specify final property of group function in haddock - - - - - cad3b734 by Owen Shepherd at 2023-12-03T00:10:10-05:00 fix: Add missing property of List.group - - - - - bad37656 by Matthew Pickering at 2023-12-03T00:10:46-05:00 testsuite: Fix T21097b test with make 4.1 (deb9) cee81370cd6ef256f66035e3116878d4cb82e28b recently added a test which failed on deb9 because the version of make was emitting the recipe failure to stdout rather than stderr. One way to fix this is to be more precise in the test about which part of the output we care about inspecting. - - - - - 5efdf421 by Matthew Pickering at 2023-12-03T00:11:21-05:00 testsuite: Track size of libdir in bytes For consistency it's better if we track all size metrics in bytes. Metric Increase: libdir - - - - - f5eb0f29 by Matthew Pickering at 2023-12-03T00:11:22-05:00 testsuite: Remove rogue trace in testsuite I accidentally left a trace in the generics metric patch. - - - - - d5610737 by Claudio Bley at 2023-12-06T16:13:33-05:00 Only exit ghci in -e mode when :add command fails Previously, when running `ghci -e ':add Sample.hs'` the process would exit with exit code 1 if the file exists and could be loaded. Fixes #24115 - - - - - 0f0c53a5 by Vladislav Zavialov at 2023-12-06T16:14:09-05:00 T2T in Patterns (#23739) This patch implements the T2T (term-to-type) transformation in patterns. Patterns that are checked against a visible forall can now be written without the `type` keyword: \(type t) (x :: t) -> ... -- old \t (x :: t) -> ... -- new The `t` binder is parsed and renamed as a term pattern (Pat), but then undergoes a conversion to a type pattern (HsTyPat). See the new function pat_to_type_pat in compiler/GHC/Tc/Gen/Pat.hs - - - - - 10a1a6c6 by Sebastian Graf at 2023-12-06T16:14:45-05:00 Pmc: Fix SrcLoc and warning for incomplete irrefutable pats (#24234) Before, the source location would point at the surrounding function definition, causing the confusion in #24234. I also took the opportunity to introduce a new `LazyPatCtx :: HsMatchContext _` to make the warning message say "irrefutable pattern" instead of "pattern binding". - - - - - 36b9a38c by Matthew Pickering at 2023-12-06T16:15:21-05:00 libraries: Bump filepath to 1.4.200.1 and unix to 2.8.4.0 Updates filepath submodule Updates unix submodule Fixes #24240 - - - - - 91ff0971 by Matthew Pickering at 2023-12-06T16:15:21-05:00 Submodule linter: Allow references to tags We modify the submodule linter so that if the bumped commit is a specific tag then the commit is accepted. Fixes #24241 - - - - - 86f652dc by Zubin Duggal at 2023-12-06T16:15:21-05:00 hadrian: set -Wno-deprecations for directory and Win32 The filepath bump to 1.4.200.1 introduces a deprecation warning. See https://gitlab.haskell.org/ghc/ghc/-/issues/24240 https://github.com/haskell/filepath/pull/206 - - - - - 7ac6006e by Sylvain Henry at 2023-12-06T16:16:02-05:00 Zap OccInfo on case binders during StgCse #14895 #24233 StgCse can revive dead binders: case foo of dead { Foo x y -> Foo x y; ... } ===> case foo of dead { Foo x y -> dead; ... } -- dead is no longer dead So we must zap occurrence information on case binders. Fix #14895 and #24233 - - - - - 57c391c4 by Sebastian Graf at 2023-12-06T16:16:37-05:00 Cpr: Turn an assertion into a check to deal with some dead code (#23862) See the new `Note [Dead code may contain type confusions]`. Fixes #23862. - - - - - c1c8abf8 by Zubin Duggal at 2023-12-08T02:25:07-05:00 testsuite: add test for #23944 - - - - - 6329d308 by Zubin Duggal at 2023-12-08T02:25:07-05:00 driver: Only run a dynamic-too pipeline if object files are going to be generated Otherwise we run into a panic in hscMaybeWriteIface: "Unexpected DT_Dyn state when writing simple interface" when dynamic-too is enabled We could remove the panic and just write the interface even if the state is `DT_Dyn`, but it seems pointless to run the pipeline twice when `hscMaybeWriteIface` is already designed to write both `hi` and `dyn_hi` files if dynamic-too is enabled. Fixes #23944. - - - - - 28811f88 by Simon Peyton Jones at 2023-12-08T05:47:18-05:00 Improve duplicate elimination in SpecConstr This partially fixes #24229. See the new Note [Pattern duplicate elimination] in SpecConstr - - - - - fec7894f by Simon Peyton Jones at 2023-12-08T05:47:18-05:00 Make SpecConstr deal with casts better This patch does two things, to fix #23209: * It improves SpecConstr so that it no longer quantifies over coercion variables. See Note [SpecConstr and casts] * It improves the rule matcher to deal nicely with the case where the rule does not quantify over coercion variables, but the the template has a cast in it. See Note [Casts in the template] - - - - - 8db8d2fd by Zubin Duggal at 2023-12-08T05:47:54-05:00 driver: Don't lose track of nodes when we fail to resolve cycles The nodes that take part in a cycle should include both hs-boot and hs files, but when we fail to resolve a cycle, we were only counting the nodes from the graph without boot files. Fixes #24196 - - - - - c5b4efd3 by Zubin Duggal at 2023-12-08T05:48:30-05:00 testsuite: Skip MultiLayerModulesTH_OneShot on darwin See #24177 - - - - - fae472a9 by Wendao Lee at 2023-12-08T05:49:12-05:00 docs(Data.Char):Add more detailed descriptions for some functions Related changed function's docs: -GHC.Unicode.isAlpha -GHC.Unicode.isPrint -GHC.Unicode.isAlphaNum Add more details for what the function will return. Co-authored-by: Bodigrim <andrew.lelechenko at gmail.com> - - - - - ca7510e4 by Malik Ammar Faisal at 2023-12-08T05:49:55-05:00 Fix float parsing in GHC Cmm Lexer Add test case for bug #24224 - - - - - d8baa1bd by Simon Peyton Jones at 2023-12-08T15:40:37+00:00 Take care when simplifying unfoldings This MR fixes a very subtle bug exposed by #24242. See Note [Environment for simplLetUnfolding]. I also updated a bunch of Notes on shadowing - - - - - 03ca551d by Simon Peyton Jones at 2023-12-08T15:54:50-05:00 Comments only in FloatIn Relevant to #3458 - - - - - 50c78779 by Simon Peyton Jones at 2023-12-08T15:54:50-05:00 Comments only in SpecConstr - - - - - 9431e195 by Simon Peyton Jones at 2023-12-08T15:54:50-05:00 Add test for #22238 - - - - - d9e4c597 by Vladislav Zavialov at 2023-12-11T04:19:34-05:00 Make forall a keyword (#23719) Before this change, GHC used to accept `forall` as a term-level identifier: -- from constraints-0.13 forall :: forall p. (forall a. Dict (p a)) -> Dict (Forall p) forall d = ... Now it is a parse error. The -Wforall-identifier warning has served its purpose and is now a deprecated no-op. - - - - - 58d56644 by Zubin Duggal at 2023-12-11T04:20:10-05:00 driver: Ensure we actually clear the interactive context before reloading Previously we called discardIC, but immediately after set the session back to an old HscEnv that still contained the IC Partially addresses #24107 Fixes #23405 - - - - - 8e5745a0 by Zubin Duggal at 2023-12-11T04:20:10-05:00 driver: Ensure we force the lookup of old build artifacts before returning the build plan This prevents us from retaining all previous build artifacts in memory until a recompile finishes, instead only retaining the exact artifacts we need. Fixes #24118 - - - - - 105c370c by Zubin Duggal at 2023-12-11T04:20:10-05:00 testsuite: add test for #24118 and #24107 MultiLayerModulesDefsGhci was not able to catch the leak because it uses :l which discards the previous environment. Using :r catches both of these leaks - - - - - e822ff88 by Zubin Duggal at 2023-12-11T04:20:10-05:00 compiler: Add some strictness annotations to ImportSpec and related constructors This prevents us from retaining entire HscEnvs. Force these ImportSpecs when forcing the GlobalRdrEltX Adds an NFData instance for Bag Fixes #24107 - - - - - 522c12a4 by Zubin Duggal at 2023-12-11T04:20:10-05:00 compiler: Force IfGlobalRdrEnv in NFData instance. - - - - - 188b280d by Arnaud Spiwack at 2023-12-11T15:33:31+01:00 LinearTypes => MonoLocalBinds - - - - - 8e0446df by Arnaud Spiwack at 2023-12-11T15:44:28+01:00 Linear let and where bindings For expediency, the initial implementation of linear types in GHC made it so that let and where binders would always be considered unrestricted. This was rather unpleasant, and probably a big obstacle to adoption. At any rate, this was not how the proposal was designed. This patch fixes this infelicity. It was surprisingly difficult to build, which explains, in part, why it took so long to materialise. As of this patch, let or where bindings marked with %1 will be linear (respectively %p for an arbitrary multiplicity p). Unmarked let will infer their multiplicity. Here is a prototypical example of program that used to be rejected and is accepted with this patch: ```haskell f :: A %1 -> B g :: B %1 -> C h :: A %1 -> C h x = g y where y = f x ``` Exceptions: - Recursive let are unrestricted, as there isn't a clear semantics of what a linear recursive binding would be. - Destructive lets with lazy bindings are unrestricted, as their desugaring isn't linear (see also #23461). - (Strict) destructive lets with inferred polymorphic type are unrestricted. Because the desugaring isn't linear (See #18461 down-thread). Closes #18461 and #18739 Co-authored-by: @jackohughes - - - - - effa7e2d by Matthew Craven at 2023-12-12T04:37:20-05:00 Introduce `dataToTagSmall#` primop (closes #21710) ...and use it to generate slightly better code when dataToTag# is used at a "small data type" where there is no need to mess with "is_too_big_tag" or potentially look at an info table. Metric Decrease: T18304 - - - - - 35c7aef6 by Matthew Craven at 2023-12-12T04:37:20-05:00 Fix formatting of Note [alg-alt heap check] - - - - - 7397c784 by Oleg Grenrus at 2023-12-12T04:37:56-05:00 Allow untyped brackets in typed splices and vice versa. Resolves #24190 Apparently the check was essentially always (as far as I can trace back: d0d47ba76f8f0501cf3c4966bc83966ab38cac27), and while it does catch some mismatches, the type-checker will catch them too. OTOH, it prevents writing completely reasonable programs. - - - - - 32d208e1 by Vladislav Zavialov at 2023-12-12T20:41:36+03:00 EPA: Match changes to LHsToken removal - - - - - a3ee3b99 by Moritz Angermann at 2023-12-12T19:50:58-05:00 Drop hard Xcode dependency XCODE_VERSION calls out to `xcodebuild`, which is only available when having `Xcode` installed. The CommandLineTools are not sufficient. To install Xcode, you must have an apple id to download the Xcode.xip from apple. We do not use xcodebuild anywhere in our build explicilty. At best it appears to be a proxy for checking the linker or the compiler. These should rather be done with ``` xcrun ld -version ``` or similar, and not by proxy through Xcode. The CLR should be sufficient for building software on macOS. - - - - - 1c9496e0 by Vladislav Zavialov at 2023-12-12T19:51:34-05:00 docs: update information on RequiredTypeArguments Update the User's Guide and Release Notes to account for the recent progress in the implementation of RequiredTypeArguments. - - - - - d0b17576 by Ben Gamari at 2023-12-13T06:33:37-05:00 rts/eventlog: Fix off-by-one in assertion Previously we failed to account for the NULL terminator `postString` asserted that there is enough room in the buffer for the string. - - - - - a10f9b9b by Ben Gamari at 2023-12-13T06:33:37-05:00 rts/eventlog: Honor result of ensureRoomForVariableEvent is Previously we would keep plugging along, even if isn't enough room for the event. - - - - - 0e0f41c0 by Ben Gamari at 2023-12-13T06:33:37-05:00 rts/eventlog: Avoid truncating event sizes Previously ensureRoomForVariableEvent would truncate the desired size to 16-bits, resulting in #24197. Fixes #24197. - - - - - 64e724c8 by Artin Ghasivand at 2023-12-13T06:34:20-05:00 Remove the "Derived Constraint" argument of TcPluginSolver, docs - - - - - fe6d97dd by Vladislav Zavialov at 2023-12-13T06:34:56-05:00 EPA: Move tokens into GhcPs extension fields (#23447) Summary of changes * Remove Language.Haskell.Syntax.Concrete * Move all tokens into GhcPs extension fields (LHsToken -> EpToken) * Create new TTG extension fields as needed * Drop the MultAnn wrapper Updates the haddock submodule. Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 8106e695 by Zubin Duggal at 2023-12-13T06:35:34-05:00 testsuite: use copy_files in T23405 This prevents the tree from being dirtied when the file is modified. - - - - - ed0e4099 by Bryan Richter at 2023-12-14T04:30:53-05:00 Document ghc package's PVP-noncompliance This changes nothing, it just makes the status quo explicit. - - - - - 8bef8d9f by Luite Stegeman at 2023-12-14T04:31:33-05:00 JS: Mark spurious CI failures js_fragile(24259) This marks the spurious test failures on the JS platform as js_fragile(24259), so we don't hold up merge requests while fixing the underlying issues. See #24259 - - - - - 1c79526a by Finley McIlwaine at 2023-12-15T12:24:40-08:00 Late plugins - - - - - 000c3302 by Finley McIlwaine at 2023-12-15T12:24:40-08:00 withTiming on LateCCs and late plugins - - - - - be4551ac by Finley McIlwaine at 2023-12-15T12:24:40-08:00 add test for late plugins - - - - - 7c29da9f by Finley McIlwaine at 2023-12-15T12:24:40-08:00 Document late plugins - - - - - 9a52ae46 by Ben Gamari at 2023-12-20T07:07:26-05:00 Fix thunk update ordering Previously we attempted to ensure soundness of concurrent thunk update by synchronizing on the access of the thunk's info table pointer field. This was believed to be sufficient since the indirectee (which may expose a closure allocated by another core) would not be examined until the info table pointer update is complete. However, it turns out that this can result in data races in the presence of multiple threads racing a update a single thunk. For instance, consider this interleaving under the old scheme: Thread A Thread B --------- --------- t=0 Enter t 1 Push update frame 2 Begin evaluation 4 Pause thread 5 t.indirectee=tso 6 Release t.info=BLACKHOLE 7 ... (e.g. GC) 8 Resume thread 9 Finish evaluation 10 Relaxed t.indirectee=x 11 Load t.info 12 Acquire fence 13 Inspect t.indirectee 14 Release t.info=BLACKHOLE Here Thread A enters thunk `t` but is soon paused, resulting in `t` being lazily blackholed at t=6. Then, at t=10 Thread A finishes evaluation and updates `t.indirectee` with a relaxed store. Meanwhile, Thread B enters the blackhole. Under the old scheme this would introduce an acquire-fence but this would only synchronize with Thread A at t=6. Consequently, the result of the evaluation, `x`, is not visible to Thread B, introducing a data race. We fix this by treating the `indirectee` field as we do all other mutable fields. This means we must always access this field with acquire-loads and release-stores. See #23185. - - - - - f4b53538 by Vladislav Zavialov at 2023-12-20T07:08:02-05:00 docs: Fix link to 051-ghc-base-libraries.rst The proposal is no longer available at the previous URL. - - - - - f7e21fab by Matthew Pickering at 2023-12-21T14:57:40+00:00 hadrian: Build all executables in bin/ folder In the end the bindist creation logic copies them all into the bin folder. There is no benefit to building a specific few binaries in the lib/bin folder anymore. This also removes the ad-hoc logic to copy the touchy and unlit executables from stage0 into stage1. It takes <1s to build so we might as well just build it. - - - - - 0038d052 by Zubin Duggal at 2023-12-22T23:28:00-05:00 testsuite: mark jspace as fragile on i386. This test has been flaky for some time and has been failing consistently on i386-linux since 8e0446df landed. See #24261 - - - - - dfd670a0 by Ben Bellick at 2023-12-24T10:10:31-05:00 Deprecate -ddump-json and introduce -fdiagnostics-as-json Addresses #19278 This commit deprecates the underspecified -ddump-json flag and introduces a newer, well-specified flag -fdiagnostics-as-json. Also included is a JSON schema as part of the documentation. The -ddump-json flag will be slated for removal shortly after this merge. - - - - - 609e6225 by Ben Bellick at 2023-12-24T10:10:31-05:00 Deprecate -ddump-json and introduce -fdiagnostics-as-json Addresses #19278 This commit deprecates the underspecified -ddump-json flag and introduces a newer, well-specified flag -fdiagnostics-as-json. Also included is a JSON schema as part of the documentation. The -ddump-json flag will be slated for removal shortly after this merge. - - - - - 865513b2 by Ömer Sinan Ağacan at 2023-12-24T10:11:13-05:00 Fix BNF in user manual 6.6.8.2: formal syntax for instance declarations - - - - - c247b6be by Zubin Duggal at 2023-12-25T16:01:23-05:00 docs: document permissibility of -XOverloadedLabels (#24249) Document the permissibility introduced by https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0170-unrestricted-overloadedlabels.rst - - - - - e5b7eb59 by Ömer Sinan Ağacan at 2023-12-25T16:02:03-05:00 Fix a code block syntax in user manual sec. 6.8.8.6 - - - - - 2db11c08 by Ben Gamari at 2023-12-29T15:35:48-05:00 genSym: Reimplement via CAS on 32-bit platforms Previously the remaining use of the C implementation on 32-bit platforms resulted in a subtle bug, #24261. This was due to the C object (which used the RTS's `atomic_inc64` macro) being compiled without `-threaded` yet later being used in a threaded compiler. Side-step this issue by using the pure Haskell `genSym` implementation on all platforms. This required implementing `fetchAddWord64Addr#` in terms of CAS on 64-bit platforms. - - - - - 19328a8c by Xiaoyan Ren at 2023-12-29T15:36:30-05:00 Do not color the diagnostic code in error messages (#24172) - - - - - 685b467c by Krzysztof Gogolewski at 2023-12-29T15:37:06-05:00 Enforce that bindings of implicit parameters are lifted Fixes #24298 - - - - - bc4d67b7 by Matthew Craven at 2023-12-31T06:15:42-05:00 StgToCmm: Detect some no-op case-continuations ...and generate no code for them. Fixes #24264. - - - - - 5b603139 by Krzysztof Gogolewski at 2023-12-31T06:16:18-05:00 Revert "testsuite: mark jspace as fragile on i386." This reverts commit 0038d052c8c80b4b430bb2aa1c66d5280be1aa95. The atomicity bug should be fixed by !11802. - - - - - d55216ad by Krzysztof Gogolewski at 2024-01-01T12:05:49-05:00 Refactor: store [[PrimRep]] rather than [Type] in STG StgConApp stored a list of types. This list was used exclusively during unarisation of unboxed sums (mkUbxSum). However, this is at a wrong level of abstraction: STG shouldn't be concerned with Haskell types, only PrimReps. Update the code to store a [[PrimRep]]. Also, there's no point in storing this list when we're not dealing with an unboxed sum. - - - - - 8b340bc7 by Ömer Sinan Ağacan at 2024-01-01T12:06:29-05:00 Kind signatures docs: mention that they're allowed in newtypes - - - - - 989bf8e5 by Zubin Duggal at 2024-01-03T20:08:47-05:00 ci: Ensure we use the correct bindist name for the test artifact when generating release ghcup metadata Fixes #24268 - - - - - 89299a89 by Krzysztof Gogolewski at 2024-01-03T20:09:23-05:00 Refactor: remove calls to typePrimRepArgs The function typePrimRepArgs is just a thin wrapper around typePrimRep, adding a VoidRep if the list is empty. However, in StgToByteCode, we were discarding that VoidRep anyway, so there's no point in calling it. - - - - - c7be0c68 by mmzk1526 at 2024-01-03T20:10:07-05:00 Use "-V" for alex version check for better backward compatibility Fixes #24302. In recent versions of alex, "-v" is used for "--verbose" instead of "-version". - - - - - 67dbcc0a by Krzysztof Gogolewski at 2024-01-05T02:07:18-05:00 Fix VoidRep handling in ghci debugger 'go' inside extractSubTerms was giving a bad result given a VoidRep, attempting to round towards the next multiple of 0. I don't understand much about the debugger but the code should be better than it was. Fixes #24306 - - - - - 90ea574e by Krzysztof Gogolewski at 2024-01-05T02:07:54-05:00 VoidRep-related refactor * In GHC.StgToByteCode, replace bcIdPrimId with idPrimRep, bcIdArgRep with idArgRep, atomPrimRep with stgArgRep1. All of them were duplicates. * In GHC.Stg.Unarise, we were converting a PrimRep to a Type and back to PrimRep. Remove the calls to primRepToType and typePrimRep1 which cancel out. * In GHC.STG.Lint, GHC.StgToCmm, GHC.Types.RepType we were filtering out VoidRep from the result of typePrimRep. But typePrimRep never returns VoidRep - remove the filtering. - - - - - eaf72479 by brian at 2024-01-06T23:03:09-05:00 Add unaligned Addr# primops Implements CLC proposal #154: https://github.com/haskell/core-libraries-committee/issues/154 * add unaligned addr primops * add tests * accept tests * add documentation * fix js primops * uncomment in access ops * use Word64 in tests * apply suggestions * remove extra file * move docs * remove random options * use setByteArray# primop * better naming * update base-exports test * add base-exports for other architectures - - - - - d471d445 by Krzysztof Gogolewski at 2024-01-06T23:03:47-05:00 Remove VoidRep from PrimRep, introduce PrimOrVoidRep This introduces data PrimOrVoidRep = VoidRep | NVRep PrimRep changes typePrimRep1 to return PrimOrVoidRep, and adds a new function typePrimRepU to be used when the argument is definitely non-void. Details in Note [VoidRep] in GHC.Types.RepType. Fixes #19520 - - - - - 48720a07 by Matthew Craven at 2024-01-08T18:57:36-05:00 Apply Note [Sensitivity to unique increment] to LargeRecord - - - - - 9e2e180f by Sebastian Graf at 2024-01-08T18:58:13-05:00 Debugging: Add diffUFM for convenient diffing between UniqFMs - - - - - 948f3e35 by Sebastian Graf at 2024-01-08T18:58:13-05:00 Rename Opt_D_dump_stranal to Opt_D_dump_dmdanal ... and Opt_D_dump_str_signatures to Opt_D_dump_dmd_signatures - - - - - 4e217e3e by Sebastian Graf at 2024-01-08T18:58:13-05:00 Deprecate -ddump-stranal and -ddump-str-signatures ... and suggest -ddump-dmdanal and -ddump-dmd-signatures instead - - - - - 6c613c90 by Sebastian Graf at 2024-01-08T18:58:13-05:00 Move testsuite/tests/stranal to testsuite/tests/dmdanal A separate commit so that the rename is obvious to Git(Lab) - - - - - c929f02b by Sebastian Graf at 2024-01-08T18:58:13-05:00 CoreSubst: Stricten `substBndr` and `cloneBndr` Doing so reduced allocations of `cloneBndr` by about 25%. ``` T9233(normal) ghc/alloc 672,488,656 663,083,216 -1.4% GOOD T9675(optasm) ghc/alloc 423,029,256 415,812,200 -1.7% geo. mean -0.1% minimum -1.7% maximum +0.1% ``` Metric Decrease: T9233 - - - - - e3ca78f3 by Krzysztof Gogolewski at 2024-01-10T17:35:59-05:00 Deprecate -Wsemigroup This warning was used to prepare for Semigroup becoming a superclass of Monoid, and for (<>) being exported from Prelude. This happened in GHC 8.4 in 8ae263ceb3566 and feac0a3bc69fd3. The leftover logic for (<>) has been removed in GHC 9.8, 4d29ecdfcc79. Now the warning does nothing at all and can be deprecated. - - - - - 08d14925 by amesgen at 2024-01-10T17:36:42-05:00 WASM metadata: use correct GHC version - - - - - 7a808419 by Xiaoyan Ren at 2024-01-10T17:37:24-05:00 Allow SCC declarations in TH (#24081) - - - - - 28827c51 by Xiaoyan Ren at 2024-01-10T17:37:24-05:00 Fix prettyprinting of SCC pragmas - - - - - ae9cc1a8 by Matthew Craven at 2024-01-10T17:38:01-05:00 Fix loopification in the presence of void arguments This also removes Note [Void arguments in self-recursive tail calls], which was just misleading. It's important to count void args both in the function's arity and at the call site. Fixes #24295. - - - - - b718b145 by Zubin Duggal at 2024-01-10T17:38:36-05:00 testsuite: Teach testsuite driver about c++ sources - - - - - 09cb57ad by Zubin Duggal at 2024-01-10T17:38:36-05:00 driver: Set -DPROFILING when compiling C++ sources with profiling Earlier, we used to pass all preprocessor flags to the c++ compiler. This meant that -DPROFILING was passed to the c++ compiler because it was a part of C++ flags However, this was incorrect and the behaviour was changed in 8ff3134ed4aa323b0199ad683f72165e51a59ab6. See #21291. But that commit exposed this bug where -DPROFILING was no longer being passed when compiling c++ sources. The fix is to explicitly include -DPROFILING in `opt_cxx` when profiling is enabled to ensure we pass the correct options for the way to both C and C++ compilers Fixes #24286 - - - - - 2cf9dd96 by Zubin Duggal at 2024-01-10T17:38:36-05:00 testsuite: rename objcpp -> objcxx To avoid confusion with C Pre Processsor - - - - - af6932d6 by Simon Peyton Jones at 2024-01-10T17:39:12-05:00 Make TYPE and CONSTRAINT not-apart Issue #24279 showed up a bug in the logic in GHC.Core.Unify.unify_ty which is supposed to make TYPE and CONSTRAINT be not-apart. Easily fixed. - - - - - 4a39b5ff by Zubin Duggal at 2024-01-10T17:39:48-05:00 ci: Fix typo in mk_ghcup_metadata.py There was a missing colon in the fix to #24268 in 989bf8e53c08eb22de716901b914b3607bc8dd08 - - - - - 13503451 by Zubin Duggal at 2024-01-10T17:40:24-05:00 release-ci: remove release-x86_64-linux-deb11-release+boot_nonmoving_gc job There is no reason to have this release build or distribute this variation. This configuration is for testing purposes only. - - - - - afca46a4 by Sebastian Graf at 2024-01-10T17:41:00-05:00 Parser: Add a Note detailing why we need happy's `error` to implement layout - - - - - eaf8a06d by Krzysztof Gogolewski at 2024-01-11T00:43:17+01:00 Turn -Wtype-equality-out-of-scope on by default Also remove -Wnoncanonical-{monoid,monad}-instances from -Wcompat, since they are enabled by default. Refresh wcompat-warnings/ test with new -Wcompat warnings. Part of #24267 Co-authored-by: sheaf <sam.derbyshire at gmail.com> - - - - - 42bee5aa by Sebastian Graf at 2024-01-12T21:16:21-05:00 Arity: Require called *exactly once* for eta exp with -fpedantic-bottoms (#24296) In #24296, we had a program in which we eta expanded away an error despite the presence of `-fpedantic-bottoms`. This was caused by turning called *at least once* lambdas into one-shot lambdas, while with `-fpedantic-bottoms` it is only sound to eta expand over lambdas that are called *exactly* once. An example can be found in `Note [Combining arity type with demand info]`. Fixes #24296. - - - - - 7e95f738 by Andreas Klebinger at 2024-01-12T21:16:57-05:00 Aarch64: Enable -mfma by default. Fixes #24311 - - - - - e43788d0 by Jason Shipman at 2024-01-14T12:47:38-05:00 Add more instances for Compose: Fractional, RealFrac, Floating, RealFloat CLC proposal #226 https://github.com/haskell/core-libraries-committee/issues/226 - - - - - ae6d8cd2 by Sebastian Graf at 2024-01-14T12:48:15-05:00 Pmc: COMPLETE pragmas associated with Family TyCons should apply to representation TyCons as well (#24326) Fixes #24326. - - - - - c5fc7304 by sheaf at 2024-01-15T14:15:29-05:00 Use lookupOccRn_maybe in TH.lookupName When looking up a value, we want to be able to find both variables and record fields. So we should not use the lookupSameOccRn_maybe function, as we can't know ahead of time which record field namespace a record field with the given textual name will belong to. Fixes #24293 - - - - - da908790 by Krzysztof Gogolewski at 2024-01-15T14:16:05-05:00 Make the build more strict on documentation errors * Detect undefined labels. This can be tested by adding :ref:`nonexistent` to a documentation rst file; attempting to build docs will fail. Fixed the undefined label in `9.8.1-notes.rst`. * Detect errors. While we have plenty of warnings, we can at least enforce that Sphinx does not report errors. Fixed the error in `required_type_arguments.rst`. Unrelated change: I have documented that the `-dlint` enables `-fcatch-nonexhaustive-cases`, as can be verified by checking `enableDLint`. - - - - - 5077416e by Javier Sagredo at 2024-01-16T15:40:06-05:00 Profiling: Adds an option to not start time profiling at startup Using the functionality provided by d89deeba47ce04a5198a71fa4cbc203fe2c90794, this patch creates a new rts flag `--no-automatic-time-samples` which disables the time profiling when starting a program. It is then expected that the user starts it whenever it is needed. Fixes #24337 - - - - - 5776008c by Matthew Pickering at 2024-01-16T15:40:42-05:00 eventlog: Fix off-by-one error in postIPE We were missing the extra_comma from the calculation of the size of the payload of postIPE. This was causing assertion failures when the event would overflow the buffer by one byte, as ensureRoomForVariable event would report there was enough space for `n` bytes but then we would write `n + 1` bytes into the buffer. Fixes #24287 - - - - - 66dc09b1 by Simon Peyton Jones at 2024-01-16T15:41:18-05:00 Improve SpecConstr (esp nofib/spectral/ansi) This MR makes three improvements to SpecConstr: see #24282 * It fixes an outright (and recently-introduced) bug in `betterPat`, which was wrongly forgetting to compare the lengths of the argument lists. * It enhances ConVal to inclue a boolean for work-free-ness, so that the envt can contain non-work-free constructor applications, so that we can do more: see Note [ConVal work-free-ness] * It rejigs `subsumePats` so that it doesn't reverse the list. This can make a difference because, when patterns overlap, we arbitrarily pick the first. There is no "right" way, but this retains the old pre-subsumePats behaviour, thereby "fixing" the regression in #24282. Nofib results +======================================== | spectral/ansi -21.14% | spectral/hartel/comp_lab_zift -0.12% | spectral/hartel/parstof +0.09% | spectral/last-piece -2.32% | spectral/multiplier +6.03% | spectral/para +0.60% | spectral/simple -0.26% +======================================== | geom mean -0.18% +---------------------------------------- The regression in `multiplier` is sad, but it simply replicates GHC's previous behaviour (e.g. GHC 9.6). - - - - - 65da79b3 by Matthew Pickering at 2024-01-16T15:41:54-05:00 hadrian: Reduce Cabal verbosity The comment claims that `simpleUserHooks` decrease verbosity, and it does, but only for the `postConf` phase. The other phases are too verbose with `-V`. At the moment > 5000 lines of the build log are devoted to output from `cabal copy`. So I take the simple approach and just decrease the verbosity level again. If the output of `postConf` is essential then it would be better to implement our own `UserHooks` which doesn't decrease the verbosity for `postConf`. Fixes #24338 - - - - - 16414d7d by Matthew Pickering at 2024-01-17T10:54:59-05:00 Stop retaining old ModGuts throughout subsequent simplifier phases Each phase of the simplifier typically rewrites the majority of ModGuts, so we want to be able to release the old ModGuts as soon as possible. `name_ppr_ctxt` lives throught the whole optimiser phase and it was retaining a reference to `ModGuts`, so we were failing to release the old `ModGuts` until the end of the phase (potentially doubling peak memory usage for that particular phase). This was discovered using eras profiling (#24332) Fixes #24328 - - - - - 7f0879e1 by Matthew Pickering at 2024-01-17T10:55:35-05:00 Update nofib submodule - - - - - 320454d3 by Cheng Shao at 2024-01-17T23:02:40+00:00 ci: bump ci-images for updated wasm image - - - - - 2eca52b4 by Cheng Shao at 2024-01-17T23:06:44+00:00 base: treat all FDs as "nonblocking" on wasm On posix platforms, when performing read/write on FDs, we check the nonblocking flag first. For FDs without this flag (e.g. stdout), we call fdReady() first, which in turn calls poll() to wait for I/O to be available on that FD. This is problematic for wasm32-wasi: although select()/poll() is supported via the poll_oneoff() wasi syscall, that syscall is rather heavyweight and runtime behavior differs in different wasi implementations. The issue is even worse when targeting browsers, given there's no satisfactory way to implement async I/O as a synchronous syscall, so existing JS polyfills for wasi often give up and simply return ENOSYS. Before we have a proper I/O manager that avoids poll_oneoff() for async I/O on wasm, this patch improves the status quo a lot by merely pretending all FDs are "nonblocking". Read/write on FDs will directly invoke read()/write(), which are much more reliably handled in existing wasi implementations, especially those in browsers. Fixes #23275 and the following test cases: T7773 isEOF001 openFile009 T4808 cgrun025 Approved by CLC proposal #234: https://github.com/haskell/core-libraries-committee/issues/234 - - - - - 83c6c710 by Andrew Lelechenko at 2024-01-18T05:21:49-05:00 base: clarify how to disable warnings about partiality of Data.List.{head,tail} - - - - - c4078f2f by Simon Peyton Jones at 2024-01-18T05:22:25-05:00 Fix four bug in handling of (forall cv. body_ty) These bugs are all described in #24335 It's not easy to provoke the bug, hence no test case. - - - - - 119586ea by Alexis King at 2024-01-19T00:08:00-05:00 Always refresh profiling CCSes after running pending initializers Fixes #24171. - - - - - 9718d970 by Oleg Grenrus at 2024-01-19T00:08:36-05:00 Set default-language: GHC2021 in ghc library Go through compiler/ sources, and remove all BangPatterns (and other GHC2021 enabled extensions in these files). - - - - - 3ef71669 by Matthew Pickering at 2024-01-19T21:55:16-05:00 testsuite: Remove unused have_library function Also remove the hence unused testsuite option `--test-package-db`. Fixes #24342 - - - - - 5b7fa20c by Jade at 2024-01-19T21:55:53-05:00 Fix Spelling in the compiler Tracking: #16591 - - - - - 09875f48 by Matthew Pickering at 2024-01-20T12:20:44-05:00 testsuite: Implement `isInTreeCompiler` in a more robust way Just a small refactoring to avoid redundantly specifying the same strings in two different places. - - - - - 0d12b987 by Jade at 2024-01-20T12:21:20-05:00 Change maintainer email from cvs-ghc at haskell.org to ghc-devs at haskell.org. Fixes #22142 - - - - - eebdd316 by Apoorv Ingle at 2024-01-23T13:49:12+00:00 Changes for haskell/haddock#18324 - - - - - 1fa1c00c by Jade at 2024-01-23T19:17:03-05:00 Enhance Documentation of functions exported by Data.Function This patch aims to improve the documentation of functions exported in Data.Function Tracking: #17929 Fixes: #10065 - - - - - ab47a43d by Jade at 2024-01-23T19:17:39-05:00 Improve documentation of hGetLine. - Add explanation for whether a newline is returned - Add examples Fixes #14804 - - - - - dd4af0e5 by Cheng Shao at 2024-01-23T19:18:17-05:00 Fix genapply for cross-compilation by nuking fragile CPP logic This commit fixes incorrectly built genapply when cross compiling (#24347) by nuking all fragile CPP logic in it from the orbit. All target-specific info are now read from DerivedConstants.h at runtime, see added note for details. Also removes a legacy Makefile and adds haskell language server support for genapply. - - - - - 0cda2b8b by Cheng Shao at 2024-01-23T19:18:17-05:00 rts: enable wasm32 register mapping The wasm backend didn't properly make use of all Cmm global registers due to #24347. Now that it is fixed, this patch re-enables full register mapping for wasm32, and we can now generate smaller & faster wasm modules that doesn't always spill arguments onto the stack. Fixes #22460 #24152. - - - - - 0325a6e5 by Greg Steuck at 2024-01-24T01:29:44-05:00 Avoid utf8 in primops.txt.pp comments They don't make it through readFile' without explicitly setting the encoding. See https://gitlab.haskell.org/ghc/ghc/-/issues/17755 - - - - - 1aaf0bd8 by David Binder at 2024-01-24T01:30:20-05:00 Bump hpc and hpc-bin submodule Bump hpc to 0.7.0.1 Bump hpc-bin to commit d1780eb2 - - - - - e693a4e8 by Ben Gamari at 2024-01-24T01:30:56-05:00 testsuite: Ignore stderr in T8089 Otherwise spurious "Killed: 9" messages to stderr may cause the test to fail. Fixes #24361. - - - - - a40f4ab2 by sheaf at 2024-01-24T14:04:33-05:00 Fix FMA instruction on LLVM We were emitting the wrong instructions for fused multiply-add operations on LLVM: - the instruction name is "llvm.fma.f32" or "llvm.fma.f64", not "fmadd" - LLVM does not support other instructions such as "fmsub"; instead we implement these by flipping signs of some arguments - the instruction is an LLVM intrinsic, which requires handling it like a normal function call instead of a machine instruction Fixes #24223 - - - - - 69abc786 by Andrei Borzenkov at 2024-01-24T14:05:09-05:00 Add changelog entry for renaming tuples from (,,...,,) to Tuple<n> (24291) - - - - - 0ac8f385 by Cheng Shao at 2024-01-25T00:27:48-05:00 compiler: remove unused GHC.Linker module The GHC.Linker module is empty and unused, other than as a hack for the make build system. We can remove it now that make is long gone; the note is moved to GHC.Linker.Loader instead. - - - - - 699da01b by Hécate Moonlight at 2024-01-25T00:28:27-05:00 Clarification for newtype constructors when using `coerce` - - - - - b2d8cd85 by Matt Walker at 2024-01-26T09:50:08-05:00 Fix #24308 Add tests for semicolon separated where clauses - - - - - 0da490a1 by Ben Gamari at 2024-01-26T17:34:41-05:00 hsc2hs: Bump submodule - - - - - 3f442fd2 by Ben Gamari at 2024-01-26T17:34:41-05:00 Bump containers submodule to 0.7 - - - - - 82a1c656 by Sebastian Nagel at 2024-01-29T02:32:40-05:00 base: with{Binary}File{Blocking} only annotates own exceptions Fixes #20886 This ensures that inner, unrelated exceptions are not misleadingly annotated with the opened file. - - - - - 9294a086 by Andreas Klebinger at 2024-01-29T02:33:15-05:00 Fix fma warning when using llvm on aarch64. On aarch64 fma is always on so the +fma flag doesn't exist for that target. Hence no need to try and pass +fma to llvm. Fixes #24379 - - - - - ced2e731 by sheaf at 2024-01-29T17:27:12-05:00 No shadowing warnings for NoFieldSelector fields This commit ensures we don't emit shadowing warnings when a user shadows a field defined with NoFieldSelectors. Fixes #24381 - - - - - 8eeadfad by Patrick at 2024-01-29T17:27:51-05:00 Fix bug wrong span of nested_doc_comment #24378 close #24378 1. Update the start position of span in `nested_doc_comment` correctly. and hence the spans of identifiers of haddoc can be computed correctly. 2. add test `HaddockSpanIssueT24378`. - - - - - a557580f by Alexey Radkov at 2024-01-30T19:41:52-05:00 Fix irrelevant dodgy-foreign-imports warning on import f-pointers by value A test *сс018* is attached (not sure about the naming convention though). Note that without the fix, the test fails with the *dodgy-foreign-imports* warning passed to stderr. The warning disappears after the fix. GHC shouldn't warn on imports of natural function pointers from C by value (which is feasible with CApiFFI), such as ```haskell foreign import capi "cc018.h value f" f :: FunPtr (Int -> IO ()) ``` where ```c void (*f)(int); ``` See a related real-world use-case [here](https://gitlab.com/daniel-casanueva/pcre-light/-/merge_requests/17). There, GHC warns on import of C function pointer `pcre_free`. - - - - - ca99efaf by Alexey Radkov at 2024-01-30T19:41:53-05:00 Rename test cc018 -> T24034 - - - - - 88c38dd5 by Ben Gamari at 2024-01-30T19:42:28-05:00 rts/TraverseHeap.c: Ensure that PosixSource.h is included first - - - - - ca2e919e by Simon Peyton Jones at 2024-01-31T09:29:45+00:00 Make decomposeRuleLhs a bit more clever This fixes #24370 by making decomposeRuleLhs undertand dictionary /functions/ as well as plain /dictionaries/ - - - - - 94ce031d by Teo Camarasu at 2024-02-01T05:49:49-05:00 doc: Add -Dn flag to user guide Resolves #24394 - - - - - 31553b11 by Ben Gamari at 2024-02-01T12:21:29-05:00 cmm: Introduce MO_RelaxedRead In hand-written Cmm it can sometimes be necessary to atomically load from memory deep within an expression (e.g. see the `CHECK_GC` macro). This MachOp provides a convenient way to do so without breaking the expression into multiple statements. - - - - - 0785cf81 by Ben Gamari at 2024-02-01T12:21:29-05:00 codeGen: Use relaxed accesses in ticky bumping - - - - - be423dda by Ben Gamari at 2024-02-01T12:21:29-05:00 base: use atomic write when updating timer manager - - - - - 8a310e35 by Ben Gamari at 2024-02-01T12:21:29-05:00 Use relaxed atomics to manipulate TSO status fields - - - - - d6809ee4 by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Add necessary barriers when manipulating TSO owner - - - - - 39e3ac5d by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Use `switch` to branch on why_blocked This is a semantics-preserving refactoring. - - - - - 515eb33d by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix synchronization on thread blocking state We now use a release barrier whenever we update a thread's blocking state. This required widening StgTSO.why_blocked as AArch64 does not support atomic writes on 16-bit values. - - - - - eb38812e by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix data race in threadPaused This only affects an assertion in the debug RTS and only needs relaxed ordering. - - - - - 26c48dd6 by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix data race in threadStatus# - - - - - 6af43ab4 by Ben Gamari at 2024-02-01T12:21:29-05:00 rts: Fix data race in Interpreter's preemption check - - - - - 9502ad3c by Ben Gamari at 2024-02-01T12:21:29-05:00 rts/Messages: Fix data race - - - - - 60802db5 by Ben Gamari at 2024-02-01T12:21:30-05:00 rts/Prof: Fix data race - - - - - ef8ccef5 by Ben Gamari at 2024-02-01T12:21:30-05:00 rts: Use relaxed ordering on dirty/clean info tables updates When changing the dirty/clean state of a mutable object we needn't have any particular ordering. - - - - - 76fe2b75 by Ben Gamari at 2024-02-01T12:21:30-05:00 codeGen: Use relaxed-read in closureInfoPtr - - - - - a6316eb4 by Ben Gamari at 2024-02-01T12:21:30-05:00 STM: Use acquire loads when possible Full sequential consistency is not needed here. - - - - - 6bddfd3d by Ben Gamari at 2024-02-01T12:21:30-05:00 rts: Use fence rather than redundant load Previously we would use an atomic load to ensure acquire ordering. However, we now have `ACQUIRE_FENCE_ON`, which allows us to express this more directly. - - - - - 55c65dbc by Ben Gamari at 2024-02-01T12:21:30-05:00 rts: Fix data races in profiling timer - - - - - 856b5e75 by Ben Gamari at 2024-02-01T12:21:30-05:00 Add Note [C11 memory model] - - - - - 6534da24 by Cheng Shao at 2024-02-01T12:22:07-05:00 compiler: move generic cmm optimization logic in NCG to a standalone module This commit moves GHC.CmmToAsm.cmmToCmm to a standalone module, GHC.Cmm.GenericOpt. The main motivation is enabling this logic to be run in the wasm backend NCG code, which is defined in other modules that's imported by GHC.CmmToAsm, causing a cyclic dependency issue. - - - - - 87e34888 by Cheng Shao at 2024-02-01T12:22:07-05:00 compiler: explicitly disable PIC in wasm32 NCG This commit explicitly disables the ncgPIC flag for the wasm32 target. The wasm backend doesn't support PIC for the time being. - - - - - c6ce242e by Cheng Shao at 2024-02-01T12:22:07-05:00 compiler: enable generic cmm optimizations in wasm backend NCG This commit enables the generic cmm optimizations in other NCGs to be run in the wasm backend as well, followed by a late cmm control-flow optimization pass. The added optimizations do catch some corner cases not handled by the pre-NCG cmm pipeline and are useful in generating smaller CFGs. - - - - - 151dda4e by Andrei Borzenkov at 2024-02-01T12:22:43-05:00 Namespacing for WARNING/DEPRECATED pragmas (#24396) New syntax for WARNING and DEPRECATED pragmas was added, namely namespace specifierss: namespace_spec ::= 'type' | 'data' | {- empty -} warning ::= warning_category namespace_spec namelist strings deprecation ::= namespace_spec namelist strings A new data type was introduced to represent these namespace specifiers: data NamespaceSpecifier = NoSpecifier | TypeNamespaceSpecifier (EpToken "type") | DataNamespaceSpecifier (EpToken "data") Extension field XWarning now contains this NamespaceSpecifier. lookupBindGroupOcc function was changed: it now takes NamespaceSpecifier and checks that the namespace of the found names matches the passed flag. With this change {-# WARNING data D "..." #-} pragma will only affect value namespace and {-# WARNING type D "..." #-} will only affect type namespace. The same logic is applicable to DEPRECATED pragmas. Finding duplicated warnings inside rnSrcWarnDecls now takes into consideration NamespaceSpecifier flag to allow warnings with the same names that refer to different namespaces. - - - - - 38c3afb6 by Bryan Richter at 2024-02-01T12:23:19-05:00 CI: Disable the test-cabal-reinstall job Fixes #24363 - - - - - 27020458 by Matthew Craven at 2024-02-03T01:53:26-05:00 Bump bytestring submodule to something closer to 0.12.1 ...mostly so that 16d6b7e835ffdcf9b894e79f933dd52348dedd0c (which reworks unaligned writes in Builder) and the stuff in https://github.com/haskell/bytestring/pull/631 can see wider testing. The less-terrible code for unaligned writes used in Builder on hosts not known to be ulaigned-friendly also takes less effort for GHC to compile, resulting in a metric decrease for T21839c on some platforms. The metric increase on T21839r is caused by the unrelated commit 750dac33465e7b59100698a330b44de7049a345c. It perhaps warrants further analysis and discussion (see #23822) but is not critical. Metric Decrease: T21839c Metric Increase: T21839r - - - - - cdddeb0f by Rodrigo Mesquita at 2024-02-03T01:54:02-05:00 Work around autotools setting C11 standard in CC/CXX In autoconf >=2.70, C11 is set by default for $CC and $CXX via the -std=...11 flag. In this patch, we split the "-std" flag out of the $CC and $CXX variables, which we traditionally assume to be just the executable name/path, and move it to $CFLAGS/$CXXFLAGS instead. Fixes #24324 - - - - - 5ff7cc26 by Apoorv Ingle at 2024-02-03T13:14:46-06:00 Expand `do` blocks right before typechecking using the `HsExpansion` philosophy. - Fixes #18324 #20020 #23147 #22788 #15598 #22086 #21206 - The change is detailed in - Note [Expanding HsDo with HsExpansion] in `GHC.Tc.Gen.Do` - Note [Doing HsExpansion in the Renamer vs Typechecker] in `GHC.Rename.Expr` expains the rational of doing expansions in type checker as opposed to in the renamer - Adds new datatypes: - `GHC.Hs.Expr.XXExprGhcRn`: new datatype makes this expansion work easier 1. Expansion bits for Expressions, Statements and Patterns in (`ExpandedThingRn`) 2. `PopErrCtxt` a special GhcRn Phase only artifcat to pop the previous error message in the error context stack - `GHC.Basic.Origin` now tracks the reason for expansion in case of Generated This is useful for type checking cf. `GHC.Tc.Gen.Expr.tcExpr` case for `HsLam` - Kills `HsExpansion` and `HsExpanded` as we have inlined them in `XXExprGhcRn` and `XXExprGhcTc` - Ensures warnings such as 1. Pattern match checks 2. Failable patterns 3. non-() return in body statements are preserved - Kill `HsMatchCtxt` in favor of `TcMatchAltChecker` - Testcases: * T18324 T20020 T23147 T22788 T15598 T22086 * T23147b (error message check), * DoubleMatch (match inside a match for pmc check) * pattern-fails (check pattern match with non-refutable pattern, eg. newtype) * Simple-rec (rec statements inside do statment) * T22788 (code snippet from #22788) * DoExpanion1 (Error messages for body statments) * DoExpansion2 (Error messages for bind statements) * DoExpansion3 (Error messages for let statements) Also repoint haddock to the right submodule so that the test (haddockHypsrcTest) pass Metric Increase 'compile_time/bytes allocated': T9020 The testcase is a pathalogical example of a `do`-block with many statements that do nothing. Given that we are expanding the statements into function binds, we will have to bear a (small) 2% cost upfront in the compiler to unroll the statements. - - - - - 0df8ce27 by Vladislav Zavialov at 2024-02-04T03:55:14-05:00 Reduce parser allocations in allocateCommentsP In the most common case, the comment queue is empty, so we can skip the work of processing it. This reduces allocations by about 10% in the parsing001 test. Metric Decrease: MultiLayerModulesRecomp parsing001 - - - - - ae856a82 by Matthew Pickering at 2024-02-05T12:22:39+00:00 ghc-internals fallout - - - - - cfd68290 by Simon Peyton Jones at 2024-02-05T17:58:33-05:00 Stop dropping a case whose binder is demanded This MR fixes #24251. See Note [Case-to-let for strictly-used binders] in GHC.Core.Opt.Simplify.Iteration, plus #24251, for lots of discussion. Final Nofib changes over 0.1%: +----------------------------------------- | imaginary/digits-of-e2 -2.16% | imaginary/rfib -0.15% | real/fluid -0.10% | real/gamteb -1.47% | real/gg -0.20% | real/maillist +0.19% | real/pic -0.23% | real/scs -0.43% | shootout/n-body -0.41% | shootout/spectral-norm -0.12% +======================================== | geom mean -0.05% Pleasingly, overall executable size is down by just over 1%. Compile times (in perf/compiler) wobble around a bit +/- 0.5%, but the geometric mean is -0.1% which seems good. - - - - - e4d137bb by Simon Peyton Jones at 2024-02-05T17:58:33-05:00 Add Note [Bangs in Integer functions] ...to document the bangs in the functions in GHC.Num.Integer - - - - - ce90f12f by Andrei Borzenkov at 2024-02-05T17:59:09-05:00 Hide WARNING/DEPRECATED namespacing under -XExplicitNamespaces (#24396) - - - - - e2ea933f by Simon Peyton Jones at 2024-02-06T10:12:04-05:00 Refactoring in preparation for lazy skolemisation * Make HsMatchContext and HsStmtContext be parameterised over the function name itself, rather than over the pass. See [mc_fun field of FunRhs] in Language.Haskell.Syntax.Expr - Replace types HsMatchContext GhcPs --> HsMatchContextPs HsMatchContext GhcRn --> HsMatchContextRn HsMatchContext GhcTc --> HsMatchContextRn (sic! not Tc) HsStmtContext GhcRn --> HsStmtContextRn - Kill off convertHsMatchCtxt * Split GHC.Tc.Type.BasicTypes.TcSigInfo so that TcCompleteSig (describing a complete user-supplied signature) is its own data type. - Split TcIdSigInfo(CompleteSig, PartialSig) into TcCompleteSig(CSig) TcPartialSig(PSig) - Use TcCompleteSig in tcPolyCheck, CheckGen - Rename types and data constructors: TcIdSigInfo --> TcIdSig TcPatSynInfo(TPSI) --> TcPatSynSig(PatSig) - Shuffle around helper functions: tcSigInfoName (moved to GHC.Tc.Types.BasicTypes) completeSigPolyId_maybe (moved to GHC.Tc.Types.BasicTypes) tcIdSigName (inlined and removed) tcIdSigLoc (introduced) - Rearrange the pattern match in chooseInferredQuantifiers * Rename functions and types: tcMatchesCase --> tcCaseMatches tcMatchesFun --> tcFunBindMatches tcMatchLambda --> tcLambdaMatches tcPats --> tcMatchPats matchActualFunTysRho --> matchActualFunTys matchActualFunTySigma --> matchActualFunTy * Add HasDebugCallStack constraints to: mkBigCoreVarTupTy, mkBigCoreTupTy, boxTy, mkPiTy, mkPiTys, splitAppTys, splitTyConAppNoView_maybe * Use `penv` from the outer context in the inner loop of GHC.Tc.Gen.Pat.tcMultiple * Move tcMkVisFunTy, tcMkInvisFunTy, tcMkScaledFunTys down the file, factor out and export tcMkScaledFunTy. * Move isPatSigCtxt down the file. * Formatting and comments Co-authored-by: Vladislav Zavialov <vlad.z.4096 at gmail.com> - - - - - f5d3e03c by Andrei Borzenkov at 2024-02-06T10:12:04-05:00 Lazy skolemisation for @a-binders (#17594) This patch is a preparation for @a-binders implementation. The main changes are: * Skolemisation is now prepared to deal with @binders. See Note [Skolemisation overview] in GHC.Tc.Utils.Unify. Most of the action is in - Utils.Unify.matchExpectedFunTys - Gen.Pat.tcMatchPats - Gen.Expr.tcPolyExprCheck - Gen.Binds.tcPolyCheck Some accompanying refactoring: * I found that funTyConAppTy_maybe was doing a lot of allocation, and rejigged userTypeError_maybe to avoid calling it. - - - - - 532993c8 by Zubin Duggal at 2024-02-06T10:12:41-05:00 driver: Really don't lose track of nodes when we fail to resolve cycles This fixes a bug in 8db8d2fd1c881032b1b360c032b6d9d072c11723, where we could lose track of acyclic components at the start of an unresolved cycle. We now ensure we never loose track of any of these components. As T24275 demonstrates, a "cyclic" SCC might not really be a true SCC: When viewed without boot files, we have a single SCC ``` [REC main:T24275B [main:T24275B {-# SOURCE #-}, main:T24275A {-# SOURCE #-}] main:T24275A [main:T24275A {-# SOURCE #-}]] ``` But with boot files this turns into ``` [NONREC main:T24275B {-# SOURCE #-} [], REC main:T24275B [main:T24275B {-# SOURCE #-}, main:T24275A {-# SOURCE #-}] main:T24275A {-# SOURCE #-} [main:T24275B], NONREC main:T24275A [main:T24275A {-# SOURCE #-}]] ``` Note that this is truly not an SCC, as no nodes are reachable from T24275B.hs-boot. However, we treat this entire group as a single "SCC" because it seems so when we analyse the graph without taking boot files into account. Indeed, we must return a single ResolvedCycle element in the BuildPlan for this as described in Note [Upsweep]. However, since after resolving this is not a true SCC anymore, `findCycle` fails to find a cycle and we have a sub-optimal error message as a result. To handle this, I extended `findCycle` to not assume its input is an SCC, and to try harder to find cycles in its input. Fixes #24275 - - - - - b35dd613 by Zubin Duggal at 2024-02-06T10:13:17-05:00 GHCi: Lookup breakpoint CCs in the correct module We need to look up breakpoint CCs in the module that the breakpoint points to, and not the current module. Fixes #24327 - - - - - b09e6958 by Zubin Duggal at 2024-02-06T10:13:17-05:00 testsuite: Add test for #24327 - - - - - 569b4c10 by doyougnu at 2024-02-07T03:06:26-05:00 ts: add compile_artifact, ignore_extension flag In b521354216f2821e00d75f088d74081d8b236810 the testsuite gained the capability to collect generic metrics. But this assumed that the test was not linking and producing artifacts and we only wanted to track object files, interface files, or build artifacts from the compiler build. However, some backends, such as the JS backend, produce artifacts when compiling, such as the jsexe directory which we want to track. This patch: - tweaks the testsuite to collect generic metrics on any build artifact in the test directory. - expands the exe_extension function to consider windows and adds the ignore_extension flag. - Modifies certain tests to add the ignore_extension flag. Tests such as heaprof002 expect a .ps file, but on windows without ignore_extensions the testsuite will look for foo.exe.ps. Hence the flag. - adds the size_hello_artifact test - - - - - 75a31379 by doyougnu at 2024-02-07T03:06:26-05:00 ts: add wasm_arch, heapprof002 wasm extension - - - - - c9731d6d by Rodrigo Mesquita at 2024-02-07T03:07:03-05:00 Synchronize bindist configure for #24324 In cdddeb0f1280b40cc194028bbaef36e127175c4c, we set up a workaround for #24324 in the in-tree configure script, but forgot to update the bindist configure script accordingly. This updates it. - - - - - d309f4e7 by Matthew Pickering at 2024-02-07T03:07:38-05:00 distrib/configure: Fix typo in CONF_GCC_LINKER_OPTS_STAGE2 variable Instead we were setting CONF_GCC_LINK_OPTS_STAGE2 which meant that we were missing passing `--target` when invoking the linker. Fixes #24414 - - - - - 77db84ab by Ben Gamari at 2024-02-08T00:35:22-05:00 llvmGen: Adapt to allow use of new pass manager. We now must use `-passes` in place of `-O<n>` due to #21936. Closes #21936. - - - - - 3c9ddf97 by Matthew Pickering at 2024-02-08T00:35:59-05:00 testsuite: Mark length001 as fragile on javascript Modifying the timeout multiplier is not a robust way to get this test to reliably fail. Therefore we mark it as fragile until/if javascript ever supports the stack limit. - - - - - 20b702b5 by Matthew Pickering at 2024-02-08T00:35:59-05:00 Javascript: Don't filter out rtsDeps list This logic appears to be incorrect as it would drop any dependency which was not in a direct dependency of the package being linked. In the ghc-internals split this started to cause errors because `ghc-internal` is not a direct dependency of most packages, and hence important symbols to keep which are hard coded into the js runtime were getting dropped. - - - - - 2df96366 by Ben Gamari at 2024-02-08T00:35:59-05:00 base: Cleanup whitespace in cbits - - - - - 44f6557a by Ben Gamari at 2024-02-08T00:35:59-05:00 Move `base` to `ghc-internal` Here we move a good deal of the implementation of `base` into a new package, `ghc-internal` such that it can be evolved independently from the user-visible interfaces of `base`. While we want to isolate implementation from interfaces, naturally, we would like to avoid turning `base` into a mere set of module re-exports. However, this is a non-trivial undertaking for a variety of reasons: * `base` contains numerous known-key and wired-in things, requiring corresponding changes in the compiler * `base` contains a significant amount of C code and corresponding autoconf logic, which is very fragile and difficult to break apart * `base` has numerous import cycles, which are currently dealt with via carefully balanced `hs-boot` files * We must not break existing users To accomplish this migration, I tried the following approaches: * [Split-GHC.Base]: Break apart the GHC.Base knot to allow incremental migration of modules into ghc-internal: this knot is simply too intertwined to be easily pulled apart, especially given the rather tricky import cycles that it contains) * [Move-Core]: Moving the "core" connected component of base (roughly 150 modules) into ghc-internal. While the Haskell side of this seems tractable, the C dependencies are very subtle to break apart. * [Move-Incrementally]: 1. Move all of base into ghc-internal 2. Examine the module structure and begin moving obvious modules (e.g. leaves of the import graph) back into base 3. Examine the modules remaining in ghc-internal, refactor as necessary to facilitate further moves 4. Go to (2) iterate until the cost/benefit of further moves is insufficient to justify continuing 5. Rename the modules moved into ghc-internal to ensure that they don't overlap with those in base 6. For each module moved into ghc-internal, add a shim module to base with the declarations which should be exposed and any requisite Haddocks (thus guaranteeing that base will be insulated from changes in the export lists of modules in ghc-internal Here I am using the [Move-Incrementally] approach, which is empirically the least painful of the unpleasant options above Bumps haddock submodule. Metric Decrease: haddock.Cabal haddock.base Metric Increase: MultiComponentModulesRecomp T16875 size_hello_artifact - - - - - e8fb2451 by Vladislav Zavialov at 2024-02-08T00:36:36-05:00 Haddock comments on infix constructors (#24221) Rewrite the `HasHaddock` instance for `ConDecl GhcPs` to account for infix constructors. This change fixes a Haddock regression (introduced in 19e80b9af252) that affected leading comments on infix data constructor declarations: -- | Docs for infix constructor | Int :* Bool The comment should be associated with the data constructor (:*), not with its left-hand side Int. - - - - - 9060d55b by Ben Gamari at 2024-02-08T00:37:13-05:00 Add os-string as a boot package Introduces `os-string` submodule. This will be necessary for `filepath-1.5`. - - - - - 9d65235a by Ben Gamari at 2024-02-08T00:37:13-05:00 gitignore: Ignore .hadrian_ghci_multi/ - - - - - d7ee12ea by Ben Gamari at 2024-02-08T00:37:13-05:00 hadrian: Set -this-package-name When constructing the GHC flags for a package Hadrian must take care to set `-this-package-name` in addition to `-this-unit-id`. This hasn't broken until now as we have not had any uses of qualified package imports. However, this will change with `filepath-1.5` and the corresponding `unix` bump, breaking `hadrian/multi-ghci`. - - - - - f2dffd2e by Ben Gamari at 2024-02-08T00:37:13-05:00 Bump filepath to 1.5.0.0 Required bumps of the following submodules: * `directory` * `filepath` * `haskeline` * `process` * `unix` * `hsc2hs` * `Win32` * `semaphore-compat` and the addition of `os-string` as a boot package. - - - - - ab533e71 by Matthew Pickering at 2024-02-08T00:37:50-05:00 Use specific clang assembler when compiling with -fllvm There are situations where LLVM will produce assembly which older gcc toolchains can't handle. For example on Deb10, it seems that LLVM >= 13 produces assembly which the default gcc doesn't support. A more robust solution in the long term is to require a specific LLVM compatible assembler when using -fllvm. Fixes #16354 - - - - - c32b6426 by Matthew Pickering at 2024-02-08T00:37:50-05:00 Update CI images with LLVM 15, ghc-9.6.4 and cabal-install-3.10.2.0 - - - - - 5fcd58be by Matthew Pickering at 2024-02-08T00:37:50-05:00 Update bootstrap plans for 9.4.8 and 9.6.4 - - - - - 707a32f5 by Matthew Pickering at 2024-02-08T00:37:50-05:00 Add alpine 3_18 release job This is mainly experimental and future proofing to enable a smooth transition to newer alpine releases once 3_12 is too old. - - - - - c37931b3 by John Ericson at 2024-02-08T06:39:05-05:00 Generate LLVM min/max bound policy via Hadrian Per #23966, I want the top-level configure to only generate configuration data for Hadrian, not do any "real" tasks on its own. This is part of that effort --- one less file generated by it. (It is still done with a `.in` file, so in a future world non-Hadrian also can easily create this file.) Split modules: - GHC.CmmToLlvm.Config - GHC.CmmToLlvm.Version - GHC.CmmToLlvm.Version.Bounds - GHC.CmmToLlvm.Version.Type This also means we can get rid of the silly `unused.h` introduced in !6803 / 7dfcab2f4bcb7206174ea48857df1883d05e97a2 as temporary kludge. Part of #23966 - - - - - 9f987235 by Apoorv Ingle at 2024-02-08T06:39:42-05:00 Enable mdo statements to use HsExpansions Fixes: #24411 Added test T24411 for regression - - - - - f8429266 by Jade at 2024-02-08T14:56:50+01:00 Adjust test for ghc MR !10993 - - - - - 762b2120 by Jade at 2024-02-08T15:17:15+00:00 Improve Monad, Functor & Applicative docs This patch aims to improve the documentation of Functor, Applicative, Monad and related symbols. The main goal is to make it more consistent and make accessible. See also: !10979 (closed) and !10985 (closed) Ticket #17929 Updates haddock submodule - - - - - 151770ca by Josh Meredith at 2024-02-10T14:28:15-05:00 JavaScript codegen: Use GHC's tag inference where JS backend-specific evaluation inference was previously used (#24309) - - - - - 2e880635 by Zubin Duggal at 2024-02-10T14:28:51-05:00 ci: Allow release-hackage-lint to fail Otherwise it blocks the ghcup metadata pipeline from running. - - - - - b0293f78 by Matthew Pickering at 2024-02-10T14:29:28-05:00 rts: eras profiling mode The eras profiling mode is useful for tracking the life-time of closures. When a closure is written, the current era is recorded in the profiling header. This records the era in which the closure was created. * Enable with -he * User mode: Use functions ghc-experimental module GHC.Profiling.Eras to modify the era * Automatically: --automatic-era-increment, increases the user era on major collections * The first era is era 1 * -he<era> can be used with other profiling modes to select a specific era If you just want to record the era but not to perform heap profiling you can use `-he --no-automatic-heap-samples`. https://well-typed.com/blog/2024/01/ghc-eras-profiling/ Fixes #24332 - - - - - be674a2c by Jade at 2024-02-10T14:30:04-05:00 Adjust error message for trailing whitespace in as-pattern. Fixes #22524 - - - - - 53ef83f9 by doyougnu at 2024-02-10T14:30:47-05:00 gitlab: js: add codeowners Fixes: - #24409 Follow on from: - #21078 and MR !9133 - When we added the JS backend this was forgotten. This patch adds the rightful codeowners. - - - - - 8bbe12f2 by Matthew Pickering at 2024-02-10T14:31:23-05:00 Bump CI images so that alpine3_18 image includes clang15 The only changes here are that clang15 is now installed on the alpine-3_18 image. - - - - - df9fd9f7 by Sylvain Henry at 2024-02-12T12:18:42-05:00 JS: handle stored null StablePtr Some Haskell codes unsafely cast StablePtr into ptr to compare against NULL. E.g. in direct-sqlite: if castStablePtrToPtr aggStPtr /= nullPtr then where `aggStPtr` is read (`peek`) from zeroed memory initially. We fix this by giving these StablePtr the same representation as other null pointers. It's safe because StablePtr at offset 0 is unused (for this exact reason). - - - - - 55346ede by Sylvain Henry at 2024-02-12T12:18:42-05:00 JS: disable MergeObjsMode test This isn't implemented for JS backend objects. - - - - - aef587f6 by Sylvain Henry at 2024-02-12T12:18:42-05:00 JS: add support for linking C sources Support linking C sources with JS output of the JavaScript backend. See the added documentation in the users guide. The implementation simply extends the JS linker to use the objects (.o) that were already produced by the emcc compiler and which were filtered out previously. I've also added some options to control the link with C functions (see the documentation about pragmas). With this change I've successfully compiled the direct-sqlite package which embeds the sqlite.c database code. Some wrappers are still required (see the documentation about wrappers) but everything generic enough to be reused for other libraries have been integrated into rts/js/mem.js. - - - - - b71b392f by Sylvain Henry at 2024-02-12T12:18:42-05:00 JS: avoid EMCC logging spurious failure emcc would sometime output messages like: cache:INFO: generating system asset: symbol_lists/424b44514e43d789148e69e4e7d1c7fdc0350b79.json... (this will be cached in "/emsdk/upstream/emscripten/cache/symbol_lists/424b44514e43d789148e69e4e7d1c7fdc0350b79.json" for subsequent builds) cache:INFO: - ok Cf https://github.com/emscripten-core/emscripten/issues/18607 This breaks our tests matching the stderr output. We avoid this by setting EMCC_LOGGING=0 - - - - - ff2c0cc9 by Simon Peyton Jones at 2024-02-12T12:19:17-05:00 Remove a dead comment Just remove an out of date block of commented-out code, and tidy up the relevant Notes. See #8317. - - - - - bedb4f0d by Teo Camarasu at 2024-02-12T18:50:33-05:00 nonmoving: Add support for heap profiling Add support for heap profiling while using the nonmoving collector. We greatly simply the implementation by disabling concurrent collection for GCs when heap profiling is enabled. This entails that the marked objects on the nonmoving heap are exactly the live objects. Note that we match the behaviour for live bytes accounting by taking the size of objects on the nonmoving heap to be that of the segment's block rather than the object itself. Resolves #22221 - - - - - d0d5acb5 by Teo Camarasu at 2024-02-12T18:51:09-05:00 doc: Add requires prof annotation to options that require it Resolves #24421 - - - - - 6d1e2386 by Alan Zimmerman at 2024-02-13T22:00:28+03:00 EPA: Match changes to HsParTy and HsFunTy - - - - - 57bb8c92 by Cheng Shao at 2024-02-13T14:07:49-05:00 deriveConstants: add needed constants for wasm backend This commit adds needed constants to deriveConstants. They are used by RTS code in the wasm backend to support the JSFFI logic. - - - - - 615eb855 by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: make genSym use C-based atomic increment on non-JS 32-bit platforms The pure Haskell implementation causes i386 regression in unrelated work that can be fixed by using C-based atomic increment, see added comment for details. - - - - - a9918891 by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: allow JSFFI for wasm32 This commit allows the javascript calling convention to be used when the target platform is wasm32. - - - - - 8771a53b by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: allow boxed JSVal as a foreign type This commit allows the boxed JSVal type to be used as a foreign argument/result type. - - - - - 053c92b3 by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: ensure ctors have the right priority on wasm32 This commit fixes the priorities of ctors generated by GHC codegen on wasm32, see the referred note for details. - - - - - b7942e0a by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: add JSFFI desugar logic for wasm32 This commit adds JSFFI desugar logic for the wasm backend. - - - - - 2c1dca76 by Cheng Shao at 2024-02-13T14:07:49-05:00 compiler: add JavaScriptFFI to supported extension list on wasm32 This commit adds JavaScriptFFI as a supported extension when the target platform is wasm32. - - - - - 9ad0e2b4 by Cheng Shao at 2024-02-13T14:07:49-05:00 rts/ghc-internal: add JSFFI support logic for wasm32 This commit adds rts/ghc-internal logic to support the wasm backend's JSFFI functionality. - - - - - e9ebea66 by Cheng Shao at 2024-02-13T14:07:49-05:00 ghc-internal: fix threadDelay for wasm in browsers This commit fixes broken threadDelay for wasm when it runs in browsers, see added note for detailed explanation. - - - - - f85f3fdb by Cheng Shao at 2024-02-13T14:07:49-05:00 utils: add JSFFI utility code This commit adds JavaScript util code to utils to support the wasm backend's JSFFI functionality: - jsffi/post-link.mjs, a post-linker to process the linked wasm module and emit a small complement JavaScript ESM module to be used with it at runtime - jsffi/prelude.js, a tiny bit of prelude code as the JavaScript side of runtime logic - jsffi/test-runner.mjs, run the jsffi test cases Co-authored-by: amesgen <amesgen at amesgen.de> - - - - - 77e91500 by Cheng Shao at 2024-02-13T14:07:49-05:00 hadrian: distribute jsbits needed for wasm backend's JSFFI support The post-linker.mjs/prelude.js files are now distributed in the bindist libdir, so when using the wasm backend's JSFFI feature, the user wouldn't need to fetch them from a ghc checkout manually. - - - - - c47ba1c3 by Cheng Shao at 2024-02-13T14:07:49-05:00 testsuite: add opts.target_wrapper This commit adds opts.target_wrapper which allows overriding the target wrapper on a per test case basis when testing a cross target. This is used when testing the wasm backend's JSFFI functionality; the rest of the cases are tested using wasmtime, though the jsffi cases are tested using the node.js based test runner. - - - - - 8e048675 by Cheng Shao at 2024-02-13T14:07:49-05:00 testsuite: T22774 should work for wasm JSFFI T22774 works since the wasm backend now supports the JSFFI feature. - - - - - 1d07f9a6 by Cheng Shao at 2024-02-13T14:07:49-05:00 testsuite: add JSFFI test cases for wasm backend This commit adds a few test cases for the wasm backend's JSFFI functionality, as well as a simple README to instruct future contributors to add new test cases. - - - - - b8997080 by Cheng Shao at 2024-02-13T14:07:49-05:00 docs: add documentation for wasm backend JSFFI This commit adds changelog and user facing documentation for the wasm backend's JSFFI feature. - - - - - ffeb000d by David Binder at 2024-02-13T14:08:30-05:00 Add tests from libraries/process/tests and libraries/Win32/tests to GHC These tests were previously part of the libraries, which themselves are submodules of the GHC repository. This commit moves the tests directly to the GHC repository. - - - - - 5a932cf2 by David Binder at 2024-02-13T14:08:30-05:00 Do not execute win32 tests on non-windows runners - - - - - 500d8cb8 by Jade at 2024-02-13T14:09:07-05:00 prevent GHCi (and runghc) from suggesting other symbols when not finding main Fixes: #23996 - - - - - b19ec331 by Cheng Shao at 2024-02-13T14:09:46-05:00 rts: update xxHash to v0.8.2 - - - - - 4a97bdb8 by Cheng Shao at 2024-02-13T14:09:46-05:00 rts: use XXH3_64bits hash on all 64-bit platforms This commit enables XXH3_64bits hash to be used on all 64-bit platforms. Previously it was only enabled on x86_64, so platforms like aarch64 silently falls back to using XXH32 which degrades the hashing function quality. - - - - - ee01de7d by Cheng Shao at 2024-02-13T14:09:46-05:00 rts: define XXH_INLINE_ALL This commit cleans up how we include the xxhash.h header and only define XXH_INLINE_ALL, which is sufficient to inline the xxHash functions without symbol collision. - - - - - 0e01e1db by Alan Zimmerman at 2024-02-14T02:13:22-05:00 EPA: Move EpAnn out of extension points Leaving a few that are too tricky, maybe some other time. Also - remove some unneeded helpers from Parser.y - reduce allocations with strictness annotations Updates haddock submodule Metric Decrease: parsing001 - - - - - de589554 by Andreas Klebinger at 2024-02-14T02:13:59-05:00 Fix ffi callbacks with >6 args and non-64bit args. Check for ptr/int arguments rather than 64-bit width arguments when counting integer register arguments. The old approach broke when we stopped using exclusively W64-sized types to represent sub-word sized integers. Fixes #24314 - - - - - 9c588f19 by Fendor at 2024-02-14T11:05:36+01:00 Adapt to GHC giving better Name's for linking - - - - - 325b7613 by Ben Gamari at 2024-02-14T14:27:45-05:00 rts/EventLog: Place eliminate duplicate strlens Previously many of the `post*` implementations would first compute the length of the event's strings in order to determine the event length. Later we would then end up computing the length yet again in `postString`. Now we instead pass the string length to `postStringLen`, avoiding the repeated work. - - - - - 8aafa51c by Ben Gamari at 2024-02-14T14:27:46-05:00 rts/eventlog: Place upper bound on IPE string field lengths The strings in IPE events may be of unbounded length. Limit the lengths of these fields to 64k characters to ensure that we don't exceed the maximum event length. - - - - - 0e60d52c by Zubin Duggal at 2024-02-14T14:27:46-05:00 rts: drop unused postString function - - - - - d8d1333a by Cheng Shao at 2024-02-14T14:28:23-05:00 compiler/rts: fix wasm unreg regression This commit fixes two wasm unreg regressions caught by a nightly pipeline: - Unknown stg_scheduler_loopzh symbol when compiling scheduler.cmm - Invalid _hs_constructor(101) function name when handling ctor - - - - - 264a4fa9 by Owen Shepherd at 2024-02-15T09:41:06-05:00 feat: Add sortOn to Data.List.NonEmpty Adds `sortOn` to `Data.List.NonEmpty`, and adds comments describing when to use it, compared to `sortWith` or `sortBy . comparing`. The aim is to smooth out the API between `Data.List`, and `Data.List.NonEmpty`. This change has been discussed in the [clc issue](https://github.com/haskell/core-libraries-committee/issues/227). - - - - - b57200de by Fendor at 2024-02-15T09:41:47-05:00 Prefer RdrName over OccName for looking up locations in doc renaming step Looking up by OccName only does not take into account when functions are only imported in a qualified way. Fixes issue #24294 Bump haddock submodule to include regression test - - - - - 8ad02724 by Luite Stegeman at 2024-02-15T17:33:32-05:00 JS: add simple optimizer The simple optimizer reduces the size of the code generated by the JavaScript backend without the complexity and performance penalty of the optimizer in GHCJS. Also see #22736 Metric Decrease: libdir size_hello_artifact - - - - - 20769b36 by Matthew Pickering at 2024-02-15T17:34:07-05:00 base: Expose `--no-automatic-time-samples` in `GHC.RTS.Flags` API This patch builds on 5077416e12cf480fb2048928aa51fa4c8fc22cf1 and modifies the base API to reflect the new RTS flag. CLC proposal #243 - https://github.com/haskell/core-libraries-committee/issues/243 Fixes #24337 - - - - - 778e1db3 by Andrei Borzenkov at 2024-02-16T16:12:07+03:00 Namespace specifiers for fixity signatures - - - - - 08031ada by Teo Camarasu at 2024-02-16T13:37:00-05:00 base: export System.Mem.performBlockingMajorGC The corresponding C function was introduced in ba73a807edbb444c49e0cf21ab2ce89226a77f2e. As part of #22264. Resolves #24228 The CLC proposal was disccused at: https://github.com/haskell/core-libraries-committee/issues/230 Co-authored-by: Ben Gamari <bgamari.foss at gmail.com> - - - - - 1f534c2e by Florian Weimer at 2024-02-16T13:37:42-05:00 Fix C output for modern C initiative GCC 14 on aarch64 rejects the C code written by GHC with this kind of error: error: assignment to ‘ffi_arg’ {aka ‘long unsigned int’} from ‘HsPtr’ {aka ‘void *’} makes integer from pointer without a cast [-Wint-conversion] 68 | *(ffi_arg*)resp = cret; | ^ Add the correct cast. For more information on this see: https://fedoraproject.org/wiki/Changes/PortingToModernC Tested-by: Richard W.M. Jones <rjones at redhat.com> - - - - - 5d3f7862 by Matthew Craven at 2024-02-16T13:38:18-05:00 Bump bytestring submodule to 0.12.1.0 - - - - - 902ebcc2 by Ian-Woo Kim at 2024-02-17T06:01:01-05:00 Add missing BCO handling in scavenge_one. - - - - - 97d26206 by Sylvain Henry at 2024-02-17T06:01:44-05:00 Make cast between words and floats real primops (#24331) First step towards fixing #24331. Replace foreign prim imports with real primops. - - - - - a40e4781 by Sylvain Henry at 2024-02-17T06:01:44-05:00 Perf: add constant folding for bitcast between float and word (#24331) - - - - - 5fd2c00f by Sylvain Henry at 2024-02-17T06:01:44-05:00 Perf: replace stack checks with assertions in casting primops There are RESERVED_STACK_WORDS free words (currently 21) on the stack, so omit the checks. Suggested by Cheng Shao. - - - - - 401dfe7b by Sylvain Henry at 2024-02-17T06:01:44-05:00 Reexport primops from GHC.Float + add deprecation - - - - - 4ab48edb by Ben Gamari at 2024-02-17T06:02:21-05:00 rts/Hash: Don't iterate over chunks if we don't need to free data When freeing a `HashTable` there is no reason to walk over the hash list before freeing it if the user has not given us a `dataFreeFun`. Noticed while looking at #24410. - - - - - bd5a1f91 by Cheng Shao at 2024-02-17T06:03:00-05:00 compiler: add SEQ_CST fence support In addition to existing Acquire/Release fences, this commit adds SEQ_CST fence support to GHC, allowing Cmm code to explicitly emit a fence that enforces total memory ordering. The following logic is added: - The MO_SeqCstFence callish MachOp - The %prim fence_seq_cst() Cmm syntax and the SEQ_CST_FENCE macro in Cmm.h - MO_SeqCstFence lowering logic in every single GHC codegen backend - - - - - 2ce2a493 by Cheng Shao at 2024-02-17T06:03:38-05:00 testsuite: fix hs_try_putmvar002 for targets without pthread.h hs_try_putmvar002 includes pthread.h and doesn't work on targets without this header (e.g. wasm32). It doesn't need to include this header at all. This was previously unnoticed by wasm CI, though recent toolchain upgrade brought in upstream changes that completely removes pthread.h in the single-threaded wasm32-wasi sysroot, therefore we need to handle that change. - - - - - 1fb3974e by Cheng Shao at 2024-02-17T06:03:38-05:00 ci: bump ci-images to use updated wasm image This commit bumps our ci-images revision to use updated wasm image. - - - - - 56e3f097 by Andrew Lelechenko at 2024-02-17T06:04:13-05:00 Bump submodule text to 2.1.1 T17123 allocates less because of improvements to Data.Text.concat in 1a6a06a. Metric Decrease: T17123 - - - - - a7569495 by Cheng Shao at 2024-02-17T06:04:51-05:00 rts: remove redundant rCCCS initialization This commit removes the redundant logic of initializing each Capability's rCCCS to CCS_SYSTEM in initProfiling(). Before initProfiling() is called during RTS startup, each Capability's rCCCS has already been assigned CCS_SYSTEM when they're first initialized. - - - - - 7a0293cc by Ben Gamari at 2024-02-19T07:11:00-05:00 Drop dependence on `touch` This drops GHC's dependence on the `touch` program, instead implementing it within GHC. This eliminates an external dependency and means that we have one fewer program to keep track of in the `configure` script - - - - - 0dbd729e by Andrei Borzenkov at 2024-02-19T07:11:37-05:00 Parser, renamer, type checker for @a-binders (#17594) GHC Proposal 448 introduces binders for invisible type arguments (@a-binders) in various contexts. This patch implements @-binders in lambda patterns and function equations: {-# LANGUAGE TypeAbstractions #-} id1 :: a -> a id1 @t x = x :: t -- @t-binder on the LHS of a function equation higherRank :: (forall a. (Num a, Bounded a) => a -> a) -> (Int8, Int16) higherRank f = (f 42, f 42) ex :: (Int8, Int16) ex = higherRank (\ @a x -> maxBound @a - x ) -- @a-binder in a lambda pattern in an argument -- to a higher-order function Syntax ------ To represent those @-binders in the AST, the list of patterns in Match now uses ArgPat instead of Pat: data Match p body = Match { ... - m_pats :: [LPat p], + m_pats :: [LArgPat p], ... } + data ArgPat pass + = VisPat (XVisPat pass) (LPat pass) + | InvisPat (XInvisPat pass) (HsTyPat (NoGhcTc pass)) + | XArgPat !(XXArgPat pass) The VisPat constructor represents patterns for visible arguments, which include ordinary value-level arguments and required type arguments (neither is prefixed with a @), while InvisPat represents invisible type arguments (prefixed with a @). Parser ------ In the grammar (Parser.y), the lambda and lambda-cases productions of aexp non-terminal were updated to accept argpats instead of apats: aexp : ... - | '\\' apats '->' exp + | '\\' argpats '->' exp ... - | '\\' 'lcases' altslist(apats) + | '\\' 'lcases' altslist(argpats) ... + argpat : apat + | PREFIX_AT atype Function left-hand sides did not require any changes to the grammar, as they were already parsed with productions capable of parsing @-binders. Those binders were being rejected in post-processing (isFunLhs), and now we accept them. In Parser.PostProcess, patterns are constructed with the help of PatBuilder, which is used as an intermediate data structure when disambiguating between FunBind and PatBind. In this patch we define ArgPatBuilder to accompany PatBuilder. ArgPatBuilder is a short-lived data structure produced in isFunLhs and consumed in checkFunBind. Renamer ------- Renaming of @-binders builds upon prior work on type patterns, implemented in 2afbddb0f24, which guarantees proper scoping and shadowing behavior of bound type variables. This patch merely defines rnLArgPatsAndThen to process a mix of visible and invisible patterns: + rnLArgPatsAndThen :: NameMaker -> [LArgPat GhcPs] -> CpsRn [LArgPat GhcRn] + rnLArgPatsAndThen mk = mapM (wrapSrcSpanCps rnArgPatAndThen) where + rnArgPatAndThen (VisPat x p) = ... rnLPatAndThen ... + rnArgPatAndThen (InvisPat _ tp) = ... rnHsTyPat ... Common logic between rnArgPats and rnPats is factored out into the rn_pats_general helper. Type checker ------------ Type-checking of @-binders builds upon prior work on lazy skolemisation, implemented in f5d3e03c56f. This patch extends tcMatchPats to handle @-binders. Now it takes and returns a list of LArgPat rather than LPat: tcMatchPats :: ... - -> [LPat GhcRn] + -> [LArgPat GhcRn] ... - -> TcM ([LPat GhcTc], a) + -> TcM ([LArgPat GhcTc], a) Invisible binders in the Match are matched up with invisible (Specified) foralls in the type. This is done with a new clause in the `loop` worker of tcMatchPats: loop :: [LArgPat GhcRn] -> [ExpPatType] -> TcM ([LArgPat GhcTc], a) loop (L l apat : pats) (ExpForAllPatTy (Bndr tv vis) : pat_tys) ... -- NEW CLAUSE: | InvisPat _ tp <- apat, isSpecifiedForAllTyFlag vis = ... In addition to that, tcMatchPats no longer discards type patterns. This is done by filterOutErasedPats in the desugarer instead. x86_64-linux-deb10-validate+debug_info Metric Increase: MultiLayerModulesTH_OneShot - - - - - 486979b0 by Jade at 2024-02-19T07:12:13-05:00 Add specialized sconcat implementation for Data.Monoid.First and Data.Semigroup.First Approved CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/246 Fixes: #24346 - - - - - 17e309d2 by John Ericson at 2024-02-19T07:12:49-05:00 Fix reST in users guide It appears that aef587f65de642142c1dcba0335a301711aab951 wasn't valid syntax. - - - - - 35b0ad90 by Brandon Chinn at 2024-02-19T07:13:25-05:00 Fix searching for errors in sphinx build - - - - - 4696b966 by Cheng Shao at 2024-02-19T07:14:02-05:00 hadrian: fix wasm backend post linker script permissions The post-link.mjs script was incorrectly copied and installed as a regular data file without executable permission, this commit fixes it. - - - - - a6142e0c by Cheng Shao at 2024-02-19T07:14:40-05:00 testsuite: mark T23540 as fragile on i386 See #24449 for details. - - - - - 249caf0d by Matthew Craven at 2024-02-19T20:36:09-05:00 Add @since annotation to Data.Data.mkConstrTag - - - - - cdd939e7 by Jade at 2024-02-19T20:36:46-05:00 Enhance documentation of Data.Complex - - - - - d04f384f by Ben Gamari at 2024-02-21T04:59:23-05:00 hadrian/bindist: Ensure that phony rules are marked as such Otherwise make may not run the rule if file with the same name as the rule happens to exist. - - - - - efcbad2d by Ben Gamari at 2024-02-21T04:59:23-05:00 hadrian: Generate HSC2HS_EXTRAS variable in bindist installation We must generate the hsc2hs wrapper at bindist installation time since it must contain `--lflag` and `--cflag` arguments which depend upon the installation path. The solution here is to substitute these variables in the configure script (see mk/hsc2hs.in). This is then copied over a dummy wrapper in the install rules. Fixes #24050. - - - - - c540559c by Matthew Pickering at 2024-02-21T04:59:23-05:00 ci: Show --info for installed compiler - - - - - ab9281a2 by Matthew Pickering at 2024-02-21T04:59:23-05:00 configure: Correctly set --target flag for linker opts Previously we were trying to use the FP_CC_SUPPORTS_TARGET with 4 arguments, when it only takes 3 arguments. Instead we need to use the `FP_PROG_CC_LINKER_TARGET` function in order to set the linker flags. Actually fixes #24414 - - - - - 9460d504 by Rodrigo Mesquita at 2024-02-21T04:59:59-05:00 configure: Do not override existing linker flags in FP_LD_NO_FIXUP_CHAINS - - - - - 77629e76 by Andrei Borzenkov at 2024-02-21T05:00:35-05:00 Namespacing for fixity signatures (#14032) Namespace specifiers were added to syntax of fixity signatures: - sigdecl ::= infix prec ops | ... + sigdecl ::= infix prec namespace_spec ops | ... To preserve namespace during renaming MiniFixityEnv type now has separate FastStringEnv fields for names that should be on the term level and for name that should be on the type level. makeMiniFixityEnv function was changed to fill MiniFixityEnv in the right way: - signatures without namespace specifiers fill both fields - signatures with 'data' specifier fill data field only - signatures with 'type' specifier fill type field only Was added helper function lookupMiniFixityEnv that takes care about looking for a name in an appropriate namespace. Updates haddock submodule. Metric Decrease: MultiLayerModulesTH_OneShot - - - - - 84357d11 by Teo Camarasu at 2024-02-21T05:01:11-05:00 rts: only collect live words in nonmoving census when non-concurrent This avoids segfaults when the mutator modifies closures as we examine them. Resolves #24393 - - - - - 9ca56dd3 by Ian-Woo Kim at 2024-02-21T05:01:53-05:00 mutex wrap in refreshProfilingCCSs - - - - - 1387966a by Cheng Shao at 2024-02-21T05:02:32-05:00 rts: remove unused HAVE_C11_ATOMICS macro This commit removes the unused HAVE_C11_ATOMICS macro. We used to have a few places that have fallback paths when HAVE_C11_ATOMICS is not defined, but that is completely redundant, since the FP_CC_SUPPORTS__ATOMICS configure check will fail when the C compiler doesn't support C11 style atomics. There are also many places (e.g. in unreg backend, SMP.h, library cbits, etc) where we unconditionally use C11 style atomics anyway which work in even CentOS 7 (gcc 4.8), the oldest distro we test in our CI, so there's no value in keeping HAVE_C11_ATOMICS. - - - - - 0f40d68f by Andreas Klebinger at 2024-02-21T05:03:09-05:00 RTS: -Ds - make sure incall is non-zero before dereferencing it. Fixes #24445 - - - - - e5886de5 by Ben Gamari at 2024-02-21T05:03:44-05:00 rts/AdjustorPool: Use ExecPage abstraction This is just a minor cleanup I found while reviewing the implementation. - - - - - 826c5b47 by Torsten Schmits at 2024-02-21T13:17:05+01:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 09941666 by Adam Gundry at 2024-02-21T13:53:12+00:00 Define GHC2024 language edition (#24320) See https://github.com/ghc-proposals/ghc-proposals/pull/613. Also fixes #24343 and improves the documentation of language editions. Co-authored-by: Joachim Breitner <mail at joachim-breitner.de> - - - - - 2cff14d5 by Ben Gamari at 2024-02-22T09:35:56-05:00 Bump bounds - - - - - f49376b3 by Ben Gamari at 2024-02-22T09:35:56-05:00 Allow `@since` annotations in export lists Here we extend Haddock to admit `@since` annotations in export lists. These can be attached to most export list items (although not subordinate lists). These annotations supercede the declaration's `@since` annotation in produced Haddocks. - - - - - b5aa93df by Ben Gamari at 2024-02-22T12:09:06-05:00 Allow package-qualified @since declarations - - - - - 8f5957f2 by Ben Gamari at 2024-02-22T13:55:19-05:00 Documentation changes from ghc-internal restructuring Previously many declarations (e.g. `Int`) were declared to have a "home" in `Prelude`. However, now Haddock instead chooses to put these in more specific homes (e.g. `Data.Int`). Given that the "home" decision is driven by heuristics and in general these changes seem quite reasonable I am accepting them: * `Int` moved from `Prelude` to `Data.Int` * `(~)` moved from `Prelude` to `Data.Type.Equality` * `Type` moved from `GHC.Types` to `Data.Kind` * `Maybe` moved from `Prelude` to `Data.Maybe` * `Bool` moved from `Prelude` to `Data.Bool` * `Ordering` moved from `Prelude` to `Data.Ord` As well, more identifiers are now hyperlinked; it's not immediately clear *why*, but it is an improvement nevertheless. - - - - - ec33fec3 by Ben Gamari at 2024-02-22T20:36:24-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 5121a4ed by Ben Gamari at 2024-02-23T06:40:55-05:00 Allow docstrings after exports Here we extend the parser and AST to preserve docstrings following export items. We then extend Haddock to parse `@since` annotations in such docstrings, allowing changes in export structure to be properly documented. Bumps haddock submodule. - - - - - 30cfd251 by Torsten Schmits at 2024-02-24T13:00:42-05:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 0eb2265d by Hécate Moonlight at 2024-02-24T16:02:16-05:00 Improve the synopsis and description of base - - - - - 2e36f5d2 by Jade at 2024-02-24T16:02:51-05:00 Error Messages: Properly align cyclic module error Fixes: #24476 - - - - - bbfb051c by Ben Gamari at 2024-02-24T19:10:23-05:00 Allow docstrings after exports Here we extend the parser and AST to preserve docstrings following export items. We then extend Haddock to parse `@since` annotations in such docstrings, allowing changes in export structure to be properly documented. - - - - - d8d6ad8c by Ben Gamari at 2024-02-24T19:10:23-05:00 ghc-internal: Move modules into GHC.Internal.* namespace Bumps haddock submodule due to testsuite output changes. - - - - - a82af7cd by Ben Gamari at 2024-02-24T19:10:23-05:00 ghc-internal: Rewrite `@since ` to `@since base-` These will be incrementally moved to the export sites in `base` where possible. - - - - - ca3836e1 by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Migrate Haddock `not-home` pragmas from `ghc-internal` This ensures that we do not use `base` stub modules as declarations' homes when not appropriate. - - - - - c8cf3e26 by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Partially freeze exports of GHC.Base Sadly there are still a few module reexports. However, at least we have decoupled from the exports of `GHC.Internal.Base`. - - - - - 272573c6 by Ben Gamari at 2024-02-24T19:10:23-05:00 Move Haddock named chunks - - - - - 2d8a881d by Ben Gamari at 2024-02-24T19:10:23-05:00 Drop GHC.Internal.Data.Int - - - - - 55c4c385 by Ben Gamari at 2024-02-24T19:10:23-05:00 compiler: Fix mention to `GHC....` modules in wasm desugaring Really, these references should be via known-key names anyways. I have fixed the proximate issue here but have opened #24472 to track the additional needed refactoring. - - - - - 64150911 by Ben Gamari at 2024-02-24T19:10:23-05:00 Accept performance shifts from ghc-internal restructure As expected, Haddock now does more work. Less expected is that some other testcases actually get faster, presumably due to less interface file loading. As well, the size_hello_artifact test regressed a bit when debug information is enabled due to debug information for the new stub symbols. Metric Decrease: T12227 T13056 Metric Increase: haddock.Cabal haddock.base MultiLayerModulesTH_OneShot size_hello_artifact - - - - - 317a915b by Ben Gamari at 2024-02-24T19:10:23-05:00 Expose GHC.Wasm.Prim from ghc-experimental Previously this was only exposed from `ghc-internal` which violates our agreement that users shall not rely on things exposed from that package. Fixes #24479. - - - - - 3bbd2bf2 by Ben Gamari at 2024-02-24T19:10:23-05:00 compiler/tc: Small optimisation of evCallStack Don't lookupIds unless we actually need them. - - - - - 3e5c9e3c by Ben Gamari at 2024-02-24T19:10:23-05:00 compiler/tc: Use toException instead of SomeException - - - - - 125714a6 by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Factor out errorBelch This was useful when debugging - - - - - 3d6aae7c by Ben Gamari at 2024-02-24T19:10:23-05:00 base: Clean up imports of GHC.Stack.CloneStack - - - - - 6900306e by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Move PrimMVar to GHC.Internal.MVar - - - - - 28f8a148 by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Move prettyCallStack to GHC.Internal.Stack - - - - - 4892de47 by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Explicit dependency to workaround #24436 Currently `ghc -M` fails to account for `.hs-boot` files correctly, leading to issues with cross-package one-shot builds failing. This currently manifests in `GHC.Exception` due to the boot file for `GHC.Internal.Stack`. Work around this by adding an explicit `import`, ensuring that `GHC.Internal.Stack` is built before `GHC.Exception`. See #24436. - - - - - 294c93a5 by Ben Gamari at 2024-02-24T19:10:24-05:00 base: Use displayException in top-level exception handler Happily this also allows us to eliminate a special case for Deadlock exceptions. Implements [CLC #198](https://github.com/haskell/core-libraries-committee/issues/198). - - - - - 732db81d by Ben Gamari at 2024-02-24T19:12:18-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - cf756a25 by Ben Gamari at 2024-02-24T22:11:53-05:00 rts: Fix symbol references in Wasm RTS - - - - - 4e4d47a0 by Jade at 2024-02-26T15:17:20-05:00 GHCi: Improve response to unloading, loading and reloading modules Fixes #13869 - - - - - f3de8a3c by Zubin Duggal at 2024-02-26T15:17:57-05:00 rel-eng/fetch-gitlab.py: Fix name of aarch64 alpine 3_18 release job - - - - - c71bfdff by Cheng Shao at 2024-02-26T15:18:35-05:00 hadrian/hie-bios: pass -j to hadrian This commit passes -j to hadrian in the hadrian/hie-bios scripts. When the user starts HLS in a fresh clone that has just been configured, it takes quite a while for hie-bios to pick up the ghc flags and start actual indexing, due to the fact that the hadrian build step defaulted to -j1, so -j speeds things up and improve HLS user experience in GHC. Also add -j flag to .ghcid to speed up ghcid, and sets the Windows build root to .hie-bios which also works and unifies with other platforms, the previous build root _hie-bios was missing from .gitignore anyway. - - - - - 50bfdb46 by Cheng Shao at 2024-02-26T15:18:35-05:00 ci: enable parallelism in hadrian/ghci scripts This commit enables parallelism when the hadrian/ghci scripts are called in CI. The time bottleneck is in the hadrian build step, but previously the build step wasn't parallelized. - - - - - 61a78231 by Felix Yan at 2024-02-26T15:19:14-05:00 m4: Correctly detect GCC version When calling as `cc`, GCC does not outputs lowercased "gcc" at least in 13.2.1 version here. ``` $ cc --version cc (GCC) 13.2.1 20230801 ... ``` This fails the check and outputs the confusing message: `configure: $CC is not gcc; assuming it's a reasonably new C compiler` This patch makes it check for upper-cased "GCC" too so that it works correctly: ``` checking version of gcc... 13.2.1 ``` - - - - - 001aa539 by Teo Camarasu at 2024-02-27T13:26:46-05:00 Fix formatting in whereFrom docstring Previously it used markdown syntax rather than Haddock syntax for code quotes - - - - - e8034d15 by Teo Camarasu at 2024-02-27T13:26:46-05:00 Move ClosureType type to ghc-internal - Use ClosureType for InfoProv.ipDesc. - Use ClosureType for CloneStack.closureType. - Now ghc-heap re-exports this type from ghc-internal. See the accompanying CLC proposal: https://github.com/haskell/core-libraries-committee/issues/210 Resolves #22600 - - - - - 3da0a551 by Matthew Craven at 2024-02-27T13:27:22-05:00 StgToJS: Simplify ExprInline constructor of ExprResult Its payload was used only for a small optimization in genAlts, avoiding a few assignments for programs of this form: case NormalDataCon arg1 arg2 of x { NormalDataCon x1 x2 -> ... ; } But when compiling with optimizations, this sort of code is generally eliminated by case-of-known-constructor in Core-to-Core. So it doesn't seem worth tracking and cleaning up again in StgToJS. - - - - - 61bc92cc by Cheng Shao at 2024-02-27T16:58:42-05:00 rts: add missing ccs_mutex guard to internal_dlopen See added comment for details. Closes #24423. - - - - - dd29d3b2 by doyougnu at 2024-02-27T16:59:23-05:00 cg: Remove GHC.Cmm.DataFlow.Collections In pursuit of #15560 and #17957 and generally removing redundancy. - - - - - d3a050d2 by Cheng Shao at 2024-02-27T17:00:00-05:00 utils: remove unused lndir from tree Ever since the removal of the make build system, the in tree lndir hasn't been actually built, so this patch removes it. - - - - - 86bf7010 by Ben Gamari at 2024-02-27T19:28:10-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 74b24a9b by Teo Camarasu at 2024-02-28T16:32:58+00:00 rts: avoid checking bdescr of value outside of Haskell heap In nonmovingTidyWeaks we want to check if the key of a weak pointer lives in the non-moving heap. We do this by checking the flags of the block the key lives in. But we need to be careful with values that live outside the Haskell heap, since they will lack a block descriptor and looking for one may lead to a segfault. In this case we should just accept that it isn't on the non-moving heap. Resolves #24492 - - - - - b4cae4ec by Simon Peyton Jones at 2024-02-29T02:10:08-05:00 In mkDataConRep, ensure the in-scope set is right A small change that fixes #24489 - - - - - 3836a110 by Cheng Shao at 2024-02-29T21:25:45-05:00 testsuite: fix T23540 fragility on 32-bit platforms T23540 is fragile on 32-bit platforms. The root cause is usage of `getEvidenceTreesAtPoint`, which internally relies on `Name`'s `Ord` instance, which is indeterministic. The solution is adding a deterministic `Ord` instance for `EvidenceInfo` and sorting the evidence trees before pretty printing. Fixes #24449. - - - - - 960c8d47 by Teo Camarasu at 2024-02-29T21:26:20-05:00 Reduce AtomicModifyIORef increment count This test leads to a lot of contention when N>2 and becomes very slow. Let's reduce the amount of work we do to compensate. Resolves #24490 - - - - - 2e46c8ad by Matthew Pickering at 2024-03-01T05:48:06-05:00 hadrian: Improve parallelism in binary-dist-dir rule I noticed that the "docs" target was needed after the libraries and executables were built. We can improve the parallelism by needing everything at once so that documentation can be built immediately after a library is built for example. - - - - - cb6c11fe by Matthew Pickering at 2024-03-01T05:48:07-05:00 ci: Bump windows and freebsd boot compilers to 9.6.4 We have previously bumped the docker images to use 9.6.4, but neglected to bump the windows images until now. - - - - - 30f06996 by Matthew Pickering at 2024-03-01T05:48:07-05:00 ci: darwin: Update to 9.6.2 for boot compiler 9.6.4 is currently broken due to #24050 Also update to use LLVM-15 rather than LLVM-11, which is out of date. - - - - - d9d69e12 by Matthew Pickering at 2024-03-01T05:48:07-05:00 Bump minimum bootstrap version to 9.6 - - - - - 67ace1c5 by Matthew Pickering at 2024-03-01T05:48:07-05:00 ci: Enable more documentation building Here we enable documentation building on 1. Darwin: The sphinx toolchain was already installed so we enable html and manpages. 2. Rocky8: Full documentation (toolchain already installed) 3. Alpine: Full documetnation (toolchain already installed) 4. Windows: HTML and manpages (toolchain already installed) Fixes #24465 - - - - - 39583c39 by Matthew Pickering at 2024-03-01T05:48:42-05:00 ci: Bump ci-images to allow updated aarch64-alpine image with llvm15 and clang15 - - - - - d91d00fc by Torsten Schmits at 2024-03-01T15:01:50-05:00 Introduce ListTuplePuns extension This implements Proposal 0475, introducing the `ListTuplePuns` extension which is enabled by default. Disabling this extension makes it invalid to refer to list, tuple and sum type constructors by using built-in syntax like `[Int]`, `(Int, Int)`, `(# Int#, Int# #)` or `(# Int | Int #)`. Instead, this syntax exclusively denotes data constructors for use with `DataKinds`. The conventional way of referring to these data constructors by prefixing them with a single quote (`'(Int, Int)`) is now a parser error. Tuple declarations have been moved to `GHC.Tuple.Prim` and the `Solo` data constructor has been renamed to `MkSolo` (in a previous commit). Unboxed tuples and sums now have real source declarations in `GHC.Types`. Unit and solo types for tuples are now called `Unit`, `Unit#`, `Solo` and `Solo#`. Constraint tuples now have the unambiguous type constructors `CTuple<n>` as well as `CUnit` and `CSolo`, defined in `GHC.Classes` like before. A new parser construct has been added for the unboxed sum data constructor declarations. The type families `Tuple`, `Sum#` etc. that were intended to provide nicer syntax have been omitted from this change set due to inference problems, to be implemented at a later time. See the MR discussion for more info. Updates the submodule utils/haddock. Updates the cabal submodule due to new language extension. Metric Increase: haddock.base Metric Decrease: MultiLayerModulesTH_OneShot size_hello_artifact Proposal document: https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0475-tuple-syntax.rst Merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/8820 Tracking ticket: https://gitlab.haskell.org/ghc/ghc/-/issues/21294 - - - - - bbdb6286 by Sylvain Henry at 2024-03-01T15:01:50-05:00 JS linker: filter unboxed tuples - - - - - dec6d8d3 by Arnaud Spiwack at 2024-03-01T15:02:30-05:00 Improve error messages coming from non-linear patterns This enriched the `CtOrigin` for non-linear patterns to include data of the pattern that created the constraint (which can be quite useful if it occurs nested in a pattern) as well as an explanation why the pattern is non-restricted in (at least in some cases). - - - - - 6612388e by Arnaud Spiwack at 2024-03-01T15:02:30-05:00 Adjust documentation of linear lets according to committee decision - - - - - 1c064ef1 by Cheng Shao at 2024-03-02T17:11:19-05:00 compiler: start deprecating cmmToRawCmmHook cmmToRawCmmHook was added 4 years ago in d561c8f6244f8280a2483e8753c38e39d34c1f01. Its only user is the Asterius project, which has been archived and deprecated in favor of the ghc wasm backend. This patch starts deprecating cmmToRawCmmHook by placing a DEPRECATED pragma, and actual removal shall happen in a future GHC major release if no issue to oppose the deprecation has been raised in the meantime. - - - - - 9b74845f by Andrew Lelechenko at 2024-03-02T17:11:55-05:00 Data.List.NonEmpty.unzip: use WARNING with category instead of DEPRECATED CLC proposal: https://github.com/haskell/core-libraries-committee/issues/258 - - - - - 61bb5ff6 by Finley McIlwaine at 2024-03-04T09:01:40-08:00 add -fprof-late-overloaded and -fprof-late-overloaded-calls * Refactor late cost centre insertion for extensibility * Add two more late cost centre insertion methods that add SCCs to overloaded top level bindings and call sites with dictionary arguments. * Some tests for the basic functionality of the new insertion methods Resolves: #24500 - - - - - 82ccb801 by Andreas Klebinger at 2024-03-04T19:59:14-05:00 x86-ncg: Fix fma codegen when arguments are globals Fix a bug in the x86 ncg where results would be wrong when the desired output register and one of the input registers were the same global. Also adds a tiny optimization to make use of the memory addressing support when convenient. Fixes #24496 - - - - - 18ad1077 by Matthew Pickering at 2024-03-05T14:22:31-05:00 rel_eng: Update hackage docs upload scripts This adds the upload of ghc-internal and ghc-experimental to our scripts which upload packages to hackage. - - - - - bf47c9ba by Matthew Pickering at 2024-03-05T14:22:31-05:00 docs: Remove stray module comment from GHC.Profiling.Eras - - - - - 37d9b340 by Matthew Pickering at 2024-03-05T14:22:31-05:00 Fix ghc-internal cabal file The file mentioned some artifacts relating to the base library. I have renamed these to the new ghc-internal variants. - - - - - 23f2a478 by Matthew Pickering at 2024-03-05T14:22:31-05:00 Fix haddock source links and hyperlinked source There were a few issues with the hackage links: 1. We were using the package id rather than the package name for the package links. This is fixed by now allowing the template to mention %pkg% or %pkgid% and substituing both appropiatly. 2. The `--haddock-base-url` flag is renamed to `--haddock-for-hackage` as the new base link works on a local or remote hackage server. 3. The "src" path including too much stuff, so cross-package source links were broken as the template was getting double expanded. Fixes #24086 - - - - - 2fa336a9 by Ben Gamari at 2024-03-05T14:23:07-05:00 filepath: Bump submodule to 1.5.2.0 - - - - - 31217944 by Ben Gamari at 2024-03-05T14:23:07-05:00 os-string: Bump submodule to 2.0.2 - - - - - 4074a3f2 by Matthew Pickering at 2024-03-05T21:44:35-05:00 base: Reflect new era profiling RTS flags in GHC.RTS.Flags * -he profiling mode * -he profiling selector * --automatic-era-increment CLC proposal #254 - https://github.com/haskell/core-libraries-committee/issues/254 - - - - - a8c0e31b by Sylvain Henry at 2024-03-05T21:45:14-05:00 JS: faster implementation for some numeric primitives (#23597) Use faster implementations for the following primitives in the JS backend by not using JavaScript's BigInt: - plusInt64 - minusInt64 - minusWord64 - timesWord64 - timesInt64 Co-authored-by: Josh Meredith <joshmeredith2008 at gmail.com> - - - - - 21e3f325 by Cheng Shao at 2024-03-05T21:45:52-05:00 rts: add -xr option to control two step allocator reserved space size This patch adds a -xr RTS option to control the size of virtual memory address space reserved by the two step allocator on a 64-bit platform, see added documentation for explanation. Closes #24498. - - - - - dedcf102 by Cheng Shao at 2024-03-06T13:39:04-05:00 rts: expose HeapAlloc.h as public header This commit exposes HeapAlloc.h as a public header. The intention is to expose HEAP_ALLOCED/HEAP_ALLOCED_GC, so they can be used in assertions in other public headers, and they may also be useful for user code. - - - - - d19441d7 by Cheng Shao at 2024-03-06T13:39:04-05:00 rts: assert pointer is indeed heap allocated in Bdescr() This commit adds an assertion to Bdescr() to assert the pointer is indeed heap allocated. This is useful to rule out RTS bugs that attempt to access non-existent block descriptor of a static closure, #24492 being one such example. - - - - - 9a656a04 by Ben Gamari at 2024-03-06T13:39:39-05:00 ghc-experimental: Add dummy dependencies to work around #23942 This is a temporary measure to improve CI reliability until a proper solution is developed. Works around #23942. - - - - - 1e84b924 by Simon Peyton Jones at 2024-03-06T13:39:39-05:00 Three compile perf improvements with deep nesting These were changes are all triggered by #24471. 1. Make GHC.Core.Opt.SetLevels.lvlMFE behave better when there are many free variables. See Note [Large free-variable sets]. 2. Make GHC.Core.Opt.Arity.floatIn a bit lazier in its Cost argument. This benefits the common case where the ArityType turns out to be nullary. See Note [Care with nested expressions] 3. Make GHC.CoreToStg.Prep.cpeArg behave for deeply-nested expressions. See Note [Eta expansion of arguments in CorePrep] wrinkle (EA2). Compile times go down by up to 4.5%, and much more in artificial cases. (Geo mean of compiler/perf changes is -0.4%.) Metric Decrease: CoOpt_Read T10421 T12425 - - - - - c4b13113 by Hécate Moonlight at 2024-03-06T13:40:17-05:00 Use "module" instead of "library" when applicable in base haddocks - - - - - 9cd9efb4 by Vladislav Zavialov at 2024-03-07T13:01:54+03:00 Rephrase error message to say "visible arguments" (#24318) * Main change: make the error message generated by mkFunTysMsg more accurate by changing "value arguments" to "visible arguments". * Refactor: define a new type synonym VisArity and use it instead of Arity in a few places. It might be the case that there other places in the compiler that should talk about visible arguments rather than value arguments, but I haven't tried to find them all, focusing only on the error message reported in the ticket. - - - - - 4b6e76b5 by Patrick at 2024-03-07T22:09:30+08:00 fix haskell/haddock#24493, with module name introduced in hieAst The accompanies haddoc PR with GHC PR https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12153 Two things have been done: 1. Link is introduced to every `X` in `module X where`, since we introduce the module name to HieAst, 2. `{-# LINE 4 "hypsrc-test/src/PositionPragmas.hs" #-}` is added before the `module PositionPragmas where` in ` hypsrc-test/ref/src/PositionPragmas.html `.It ensures only a single hieAst for file `hypsrc-test/src/PositionPragmas.hs` is generated. - - - - - d523a6a7 by Ben Gamari at 2024-03-07T19:40:45-05:00 Bump array submodule - - - - - 7e55003c by Ben Gamari at 2024-03-07T19:40:45-05:00 Bump stm submodule - - - - - 32d337ef by Ben Gamari at 2024-03-07T19:40:45-05:00 Introduce exception context Here we introduce the `ExceptionContext` type and `ExceptionAnnotation` class, allowing dynamically-typed user-defined annotations to be attached to exceptions. CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/199 GHC Proposal: https://github.com/ghc-proposals/ghc-proposals/pull/330 - - - - - 39f3d922 by Ben Gamari at 2024-03-07T19:40:46-05:00 testsuite/interface-stability: Update documentation - - - - - fdea7ada by Ben Gamari at 2024-03-07T19:40:46-05:00 ghc-internal: comment formatting - - - - - 4fba42ef by Ben Gamari at 2024-03-07T19:40:46-05:00 compiler: Default and warn ExceptionContext constraints - - - - - 3886a205 by Ben Gamari at 2024-03-07T19:40:46-05:00 base: Introduce exception backtraces Here we introduce the `Backtraces` type and associated machinery for attaching these via `ExceptionContext`. These has a few compile-time regressions (`T15703` and `T9872d`) due to the additional dependencies in the exception machinery. As well, there is a surprisingly large regression in the `size_hello_artifact` test. This appears to be due to various `Integer` and `Read` bits now being reachable at link-time. I believe it should be possible to avoid this but I have accepted the change for now to get the feature merged. CLC Proposal: https://github.com/haskell/core-libraries-committee/issues/199 GHC Proposal: https://github.com/ghc-proposals/ghc-proposals/pull/330 Metric Increase: T15703 T9872d size_hello_artifact - - - - - 18c5409f by Ben Gamari at 2024-03-07T19:40:46-05:00 users guide: Release notes for exception backtrace work - - - - - f849c5fc by Ben Gamari at 2024-03-07T19:40:46-05:00 compiler: Don't show ExceptionContext of GhcExceptions Most GhcExceptions are user-facing errors and therefore the ExceptionContext has little value. Ideally we would enable it in the DEBUG compiler but I am leaving this for future work. - - - - - dc646e6f by Sylvain Henry at 2024-03-07T19:40:46-05:00 Disable T9930fail for the JS target (cf #19174) - - - - - bfc09760 by Alan Zimmerman at 2024-03-07T19:41:22-05:00 Update showAstData to honour blanking of AnnParen Also tweak rendering of SrcSpan to remove extra blank line. - - - - - 50454a29 by Ben Gamari at 2024-03-08T03:32:42-05:00 ghc-internal: Eliminate GHC.Internal.Data.Kind This was simply reexporting things from `ghc-prim`. Instead reexport these directly from `Data.Kind`. Also add build ordering dependency to work around #23942. - - - - - 38a4b6ab by Ben Gamari at 2024-03-08T03:33:18-05:00 rts: Fix SET_HDR initialization of retainer set This fixes a regression in retainer set profiling introduced by b0293f78cb6acf2540389e22bdda420d0ab874da. Prior to that commit the heap traversal word would be initialized by `SET_HDR` using `LDV_RECORD_CREATE`. However, the commit added a `doingLDVProfiling` check in `LDV_RECORD_CREATE`, meaning that this initialization no longer happened. Given that this initialization was awkwardly indirectly anyways, I have fixed this by explicitly initializating the heap traversal word to `NULL` in `SET_PROF_HDR`. This is equivalent to the previous behavior, but much more direct. Fixes #24513. - - - - - 635abccc by Ben Gamari at 2024-03-08T17:09:06-05:00 Bump ghc version to 9.10 - - - - - 2859a637 by Ben Gamari at 2024-03-08T18:26:47-05:00 base: Use strerror_r instead of strerror As noted by #24344, `strerror` is not necessarily thread-safe. Thankfully, POSIX.1-2001 has long offered `strerror_r`, which is safe to use. Fixes #24344. CLC discussion: https://github.com/haskell/core-libraries-committee/issues/249 - - - - - 5b934048 by Ben Gamari at 2024-03-08T18:50:12-05:00 Bump base upper bound - - - - - b30d134e by Ben Gamari at 2024-03-08T18:50:44-05:00 Testsuite output update - - - - - edb9bf77 by Jade at 2024-03-09T03:39:38-05:00 Error messages: Improve Error messages for Data constructors in type signatures. This patch improves the error messages from invalid type signatures by trying to guess what the user did and suggesting an appropriate fix. Partially fixes: #17879 - - - - - cfb197e3 by Patrick at 2024-03-09T03:40:15-05:00 HieAst: add module name #24493 The main purpose of this is to tuck the module name `xxx` in `module xxx where` into the hieAst. It should fix #24493. The following have been done: 1. Renamed and update the `tcg_doc_hdr :: Maybe (LHsDoc GhcRn)` to `tcg_hdr_info :: (Maybe (LHsDoc GhcRn), Maybe (XRec GhcRn ModuleName))` To store the located module name information. 2. update the `RenamedSource` and `RenamedStuff` with extra `Maybe (XRec GhcRn ModuleName)` located module name information. 3. add test `testsuite/tests/hiefile/should_compile/T24493.hs` to ensure the module name is added and update several relevent tests. 4. accompanied submodule haddoc test update MR in https://gitlab.haskell.org/ghc/haddock/-/merge_requests/53 - - - - - 2341d81e by Vaibhav Sagar at 2024-03-09T03:40:54-05:00 GHC.Utils.Binary: fix a couple of typos - - - - - 5580e1bd by Ben Gamari at 2024-03-09T03:41:30-05:00 rts: Drop .wasm suffix from .prof file names This replicates the behavior on Windows, where `Hi.exe` will produce profiling output named `Hi.prof` instead of `Hi.exe.prof`. While in the area I also fixed the extension-stripping logic, which incorrectly rewrote `Hi.exefoo` to `Hi.foo`. Closes #24515. - - - - - 259495ee by Cheng Shao at 2024-03-09T03:41:30-05:00 testsuite: drop exe extension from .hp & .prof filenames See #24515 for details. - - - - - c477a8d2 by Ben Gamari at 2024-03-09T03:42:05-05:00 rts/linker: Enable GOT support on all platforms There is nothing platform-dependent about our GOT implementation and GOT support is needed by `T24171` on i386. - - - - - 2e592857 by Vladislav Zavialov at 2024-03-09T03:42:41-05:00 Drop outdated comment on TcRnIllformedTypePattern This should have been done in 0f0c53a501b but I missed it. - - - - - c554b4da by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/CloneStack: Bounds check array write - - - - - 15c590a5 by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/CloneStack: Don't expose helper functions in header - - - - - e831ce31 by Ben Gamari at 2024-03-09T09:39:20-05:00 base: Move internals of GHC.InfoProv into GHC.InfoProv.Types Such that we can add new helpers into GHC.InfoProv.Types without breakage. - - - - - 6948e24d by Ben Gamari at 2024-03-09T09:39:20-05:00 rts: Lazily decode IPE tables Previously we would eagerly allocate `InfoTableEnt`s for each info table registered in the info table provenance map. However, this costs considerable memory and initialization time. Instead we now lazily decode these tables. This allows us to use one-third the memory *and* opens the door to taking advantage of sharing opportunities within a module. This required considerable reworking since lookupIPE now must be passed its result buffer. - - - - - 9204a04e by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/IPE: Don't expose helper in header - - - - - 308926ff by Ben Gamari at 2024-03-09T09:39:20-05:00 rts/IPE: Share module_name within a Node This allows us to shave a 64-bit word off of the packed IPE entry size. - - - - - bebdea05 by Ben Gamari at 2024-03-09T09:39:20-05:00 IPE: Expose unit ID in InfoTableProv Here we add the unit ID to the info table provenance structure. - - - - - 6519c9ad by Ben Gamari at 2024-03-09T09:39:35-05:00 rts: Refactor GHC.Stack.CloneStack.decode Don't allocate a Ptr constructor per frame. - - - - - ed0b69dc by Ben Gamari at 2024-03-09T09:39:35-05:00 base: Do not expose whereFrom# from GHC.Exts - - - - - 2b1faea9 by Vladislav Zavialov at 2024-03-09T17:38:21-05:00 docs: Update info on TypeAbstractions * Mention TypeAbstractions in 9.10.1-notes.rst * Set the status to "Experimental". * Add a "Since: GHC 9.x" comment to each section. - - - - - f8b88918 by Ben Gamari at 2024-03-09T21:21:46-05:00 ci-images: Bump Alpine image to bootstrap with 9.8.2 - - - - - 705e6927 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Mark T24171 as fragile due to #24512 I will fix this but not in time for 9.10.1-alpha1 - - - - - c74196e1 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Mark linker_unload_native as fragile In particular this fails on platforms without `dlinfo`. I plan to address this but not before 9.10.1-alpha1. - - - - - f4d87f7a by Ben Gamari at 2024-03-09T21:21:46-05:00 configure: Bump version to 9.10 - - - - - 88df9a5f by Ben Gamari at 2024-03-09T21:21:46-05:00 Bump transformers submodule to 0.6.1.1 - - - - - 8176d5e8 by Ben Gamari at 2024-03-09T21:21:46-05:00 testsuite: Increase ulimit for T18623 1 MByte was just too tight and failed intermittently on some platforms (e.g. CentOS 7). Bumping the limit to 8 MByte should provide sufficient headroom. Fixes #23139. - - - - - c74b38a3 by Ben Gamari at 2024-03-09T21:21:46-05:00 base: Bump version to 4.20.0.0 - - - - - b2937fc3 by Ben Gamari at 2024-03-09T21:21:46-05:00 ghc-internal: Set initial version at 9.1001.0 This provides PVP compliance while maintaining a clear correspondence between GHC releases and `ghc-internal` versions. - - - - - 4ae7d868 by Ben Gamari at 2024-03-09T21:21:46-05:00 ghc-prim: Bump version to 0.11.0 - - - - - 50798dc6 by Ben Gamari at 2024-03-09T21:21:46-05:00 template-haskell: Bump version to 2.22.0.0 - - - - - 8564f976 by Ben Gamari at 2024-03-09T21:21:46-05:00 base-exports: Accommodate spurious whitespace changes in 32-bit output It appears that this was - - - - - 9d4f0e98 by Ben Gamari at 2024-03-09T21:21:46-05:00 users-guide: Move exception backtrace relnotes to 9.10 This was previously mistakenly added to the GHC 9.8 release notes. - - - - - 145eae60 by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/rel_eng: Fix name of Rocky8 artifact - - - - - 39c2a630 by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/rel_eng: Fix path of generate_jobs_metadata - - - - - aed034de by Ben Gamari at 2024-03-09T21:21:46-05:00 gitlab/upload: Rework recompression The old `combine` approach was quite fragile due to use of filename globbing. Moreover, it didn't parallelize well. This refactoring makes the goal more obvious, parallelizes better, and is more robust. - - - - - 9bdf3586 by Ben Gamari at 2024-03-09T21:37:44-05:00 Merge branch 'ghc-9.10' into ghc-head - - - - - cec76981 by Ben Gamari at 2024-03-09T21:54:00-05:00 Bump GHC version to 9.11 - - - - - 4c59feb7 by Ben Gamari at 2024-03-09T22:15:01-05:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - dc207d06 by Ben Gamari at 2024-03-10T08:56:08-04:00 configure: Bump GHC version to 9.11 Bumps haddock submodule. - - - - - 8b2513e8 by Ben Gamari at 2024-03-11T01:20:03-04:00 rts/linker: Don't unload code when profiling is enabled The heap census may contain references (e.g. `Counter.identity`) to static data which must be available when the census is reported at the end of execution. Fixes #24512. - - - - - 7810b4c3 by Ben Gamari at 2024-03-11T01:20:03-04:00 rts/linker: Don't unload native objects when dlinfo isn't available To do so is unsafe as we have no way of identifying references to symbols provided by the object. Fixes #24513. Fixes #23993. - - - - - 0590764c by Ben Gamari at 2024-03-11T01:20:39-04:00 rel_eng/upload: Purge both $rel_name/ and $ver/ This is necessary for prereleases, where GHCup accesses the release via `$ver/` - - - - - b85a4631 by Brandon Chinn at 2024-03-12T19:25:56-04:00 Remove duplicate code normalising slashes - - - - - c91946f9 by Brandon Chinn at 2024-03-12T19:25:56-04:00 Simplify regexes with raw strings - - - - - 1a5f53c6 by Brandon Chinn at 2024-03-12T19:25:57-04:00 Don't normalize backslashes in characters - - - - - 7ea971d3 by Andrei Borzenkov at 2024-03-12T19:26:32-04:00 Fix compiler crash caused by implicit RHS quantification in type synonyms (#24470) - - - - - 39f3ac3e by Cheng Shao at 2024-03-12T19:27:11-04:00 Revert "compiler: make genSym use C-based atomic increment on non-JS 32-bit platforms" This reverts commit 615eb855416ce536e02ed935ecc5a6f25519ae16. It was originally intended to fix #24449, but it was merely sweeping the bug under the rug. 3836a110577b5c9343915fd96c1b2c64217e0082 has properly fixed the fragile test, and we no longer need the C version of genSym. Furthermore, the C implementation causes trouble when compiling with clang that targets i386 due to alignment warning and libatomic linking issue, so it makes sense to revert it. - - - - - e6bfb85c by Cheng Shao at 2024-03-12T19:27:11-04:00 compiler: fix out-of-bound memory access of genSym on 32-bit This commit fixes an unnoticed out-of-bound memory access of genSym on 32-bit. ghc_unique_inc is 32-bit sized/aligned on 32-bit platforms, but we mistakenly treat it as a Word64 pointer in genSym, and therefore will accidentally load 2 garbage higher bytes, or with a small but non-zero chance, overwrite something else in the data section depends on how the linker places the data segments. This regression was introduced in !11802 and fixed here. - - - - - 77171cd1 by Ben Orchard at 2024-03-14T09:00:40-04:00 Note mutability of array and address access primops Without an understanding of immutable vs. mutable memory, the index primop family have a potentially non-intuitive type signature: indexOffAddr :: Addr# -> Int# -> a readOffAddr :: Addr# -> Int# -> State# d -> (# State# d, a #) indexOffAddr# might seem like a free generality improvement, which it certainly is not! This change adds a brief note on mutability expectations for most index/read/write access primops. - - - - - 7da7f8f6 by Alan Zimmerman at 2024-03-14T09:01:15-04:00 EPA: Fix regression discarding comments in contexts Closes #24533 - - - - - 73be65ab by Fendor at 2024-03-19T01:42:53-04:00 Fix sharing of 'IfaceTyConInfo' during core to iface type translation During heap analysis, we noticed that during generation of 'mi_extra_decls' we have lots of duplicates for the instances: * `IfaceTyConInfo NotPromoted IfaceNormalTyCon` * `IfaceTyConInfo IsPromoted IfaceNormalTyCon` which should be shared instead of duplicated. This duplication increased the number of live bytes by around 200MB while loading the agda codebase into GHCi. These instances are created during `CoreToIface` translation, in particular `toIfaceTyCon`. The generated core looks like: toIfaceTyCon = \ tc_sjJw -> case $wtoIfaceTyCon tc_sjJw of { (# ww_sjJz, ww1_sjNL, ww2_sjNM #) -> IfaceTyCon ww_sjJz (IfaceTyConInfo ww1_sjNL ww2_sjNM) } whichs removes causes the sharing to work propery. Adding explicit sharing, with NOINLINE annotations, changes the core to: toIfaceTyCon = \ tc_sjJq -> case $wtoIfaceTyCon tc_sjJq of { (# ww_sjNB, ww1_sjNC #) -> IfaceTyCon ww_sjNB ww1_sjNC } which looks much more like sharing is happening. We confirmed via ghc-debug that all duplications were eliminated and the number of live bytes are noticeably reduced. - - - - - bd8209eb by Alan Zimmerman at 2024-03-19T01:43:28-04:00 EPA: Address more 9.10.1-alpha1 regressions from recent changes Closes #24533 Hopefully for good this time - - - - - 31bf85ee by Fendor at 2024-03-19T14:48:08-04:00 Escape multiple arguments in the settings file Uses responseFile syntax. The issue arises when GHC is installed on windows into a location that has a space, for example the user name is 'Fake User'. The $topdir will also contain a space, consequentially. When we resolve the top dir in the string `-I$topdir/mingw/include`, then `words` will turn this single argument into `-I/C/Users/Fake` and `User/.../mingw/include` which trips up the flag argument parser of various tools such as gcc or clang. We avoid this by escaping the $topdir before replacing it in `initSettngs`. Additionally, we allow to escape spaces and quotation marks for arguments in `settings` file. Add regression test case to count the number of options after variable expansion and argument escaping took place. Additionally, we check that escaped spaces and double quotation marks are correctly parsed. - - - - - f45f700e by Matthew Pickering at 2024-03-19T14:48:44-04:00 Read global package database from settings file Before this patch, the global package database was always assumed to be in libdir </> package.conf.d. This causes issues in GHC's build system because there are sometimes situations where the package database you need to use is not located in the same place as the settings file. * The stage1 compiler needs to use stage1 libraries, so we should set "Global Package DB" for the stage1 compiler to the stage1 package database. * Stage 2 cross compilers need to use stage2 libraries, so likewise, we should set the package database path to `_build/stage2/lib/` * The normal situation is where the stage2 compiler uses stage1 libraries. Then everything lines up. * When installing we have rearranged everything so that the settings file and package database line up properly, so then everything should continue to work as before. In this case we set the relative package db path to `package.conf.d`, so it resolves the same as before. * ghc-pkg needs to be modified as well to look in the settings file fo the package database rather than assuming the global package database location relative to the lib folder. * Cabal/cabal-install will work correctly because they query the global package database using `--print-global-package-db`. A reasonable question is why not generate the "right" settings files in the right places in GHC's build system. In order to do this you would need to engineer wrappers for all executables to point to a specific libdir. There are also situations where the same package db is used by two different compilers with two different settings files (think stage2 cross compiler and stage3 compiler). In short, this 10 line patch allows for some reasonable simplifications in Hadrian at very little cost to anything else. Fixes #24502 - - - - - 4c8f1794 by Matthew Pickering at 2024-03-19T14:48:44-04:00 hadrian: Remove stage1 testsuite wrappers logic Now instead of producing wrappers which pass the global package database argument to ghc and ghc-pkg, we write the location of the correct package database into the settings file so you can just use the intree compiler directly. - - - - - da0d8ba5 by Matthew Craven at 2024-03-19T14:49:20-04:00 Remove unused ghc-internal module "GHC.Internal.Constants" - - - - - b56d2761 by Matthew Craven at 2024-03-19T14:49:20-04:00 CorePrep: Rework lowering of BigNat# literals Don't use bigNatFromWord#, because that's terrible: * We shouldn't have to traverse a linked list at run-time to build a BigNat# literal. That's just silly! * The static List object we have to create is much larger than the actual BigNat#'s contents, bloating code size. * We have to read the corresponding interface file, which causes un-tracked implicit dependencies. (#23942) Instead, encode them into the appropriate platform-dependent sequence of bytes, and generate code that copies these bytes at run-time from an Addr# literal into a new ByteArray#. A ByteArray# literal would be the correct thing to generate, but these are not yet supported; see also #17747. Somewhat surprisingly, this change results in a slight reduction in compiler allocations, averaging around 0.5% on ghc's compiler performance tests, including when compiling programs that contain no bignum literals to begin with. The specific cause of this has not been investigated. Since this lowering no longer reads the interface file for GHC.Num.BigNat, the reasoning in Note [Depend on GHC.Num.Integer] is obsoleted. But the story of un-tracked built-in dependencies remains complex, and Note [Tracking dependencies on primitives] now exists to explain this complexity. Additionally, many empty imports have been modified to refer to this new note and comply with its guidance. Several empty imports necessary for other reasons have also been given brief explanations. Metric Decrease: MultiLayerModulesTH_OneShot - - - - - 349ea330 by Fendor at 2024-03-19T14:50:00-04:00 Eliminate thunk in 'IfaceTyCon' Heap analysis showed that `IfaceTyCon` retains a thunk to `IfaceTyConInfo`, defeating the sharing of the most common instances of `IfaceTyConInfo`. We make sure the indirection is removed by adding bang patterns to `IfaceTyCon`. Experimental results on the agda code base, where the `mi_extra_decls` were read from disk: Before this change, we observe around 8654045 instances of: `IfaceTyCon[Name,THUNK_1_0]` But these thunks almost exclusively point to a shared value! Forcing the thunk a little bit more, leads to `ghc-debug` reporting: `IfaceTyCon[Name:Name,IfaceTyConInfo]` and a noticeable reduction of live bytes (on agda ~10%). - - - - - 594bee0b by Krzysztof Gogolewski at 2024-03-19T14:50:36-04:00 Minor misc cleanups - GHC.HsToCore.Foreign.JavaScript: remove dropRuntimeRepArgs; boxed tuples don't take RuntimeRep args - GHC.HsToCore.Foreign.Call: avoid partial pattern matching - GHC.Stg.Unarise: strengthen the assertion; we can assert that non-rubbish literals are unary rather than just non-void - GHC.Tc.Gen.HsType: make sure the fsLit "literal" rule fires - users_guide/using-warnings.rst: remove -Wforall-identifier, now deprecated and does nothing - users_guide/using.rst: fix formatting - andy_cherry/test.T: remove expect_broken_for(23272...), 23272 is fixed The rest are simple cleanups. - - - - - cf55a54b by Ben Gamari at 2024-03-19T14:51:12-04:00 mk/relpath: Fix quoting Previously there were two instances in this script which lacked proper quoting. This resulted in `relpath` invocations in the binary distribution Makefile producing incorrect results on Windows, leading to confusing failures from `sed` and the production of empty package registrations. Fixes #24538. - - - - - 5ff88389 by Bryan Richter at 2024-03-19T14:51:48-04:00 testsuite: Disable T21336a on wasm - - - - - 60023351 by Ben Gamari at 2024-03-19T22:33:10-04:00 hadrian/bindist: Eliminate extraneous `dirname` invocation Previously we would call `dirname` twice per installed library file. We now instead reuse this result. This helps appreciably on Windows, where processes are quite expensive. - - - - - 616ac300 by Ben Gamari at 2024-03-19T22:33:10-04:00 hadrian: Package mingw toolchain in expected location This fixes #24525, a regression due to 41cbaf44a6ab5eb9fa676d65d32df8377898dc89. Specifically, GHC expects to find the mingw32 toolchain in the binary distribution root. However, after this patch it was packaged in the `lib/` directory. - - - - - de9daade by Ben Gamari at 2024-03-19T22:33:11-04:00 gitlab/rel_eng: More upload.sh tweaks - - - - - 1dfe12db by Ben Gamari at 2024-03-19T22:33:11-04:00 rel_eng: Drop dead prepare_docs codepath - - - - - dd2d748b by Ben Gamari at 2024-03-19T22:33:11-04:00 rel_env/recompress_all: unxz before recompressing Previously we would rather compress the xz *again*, before in addition compressing it with the desired scheme. Fixes #24545. - - - - - 9d936c57 by Ben Gamari at 2024-03-19T22:33:11-04:00 mk-ghcup-metadata: Fix directory of testsuite tarball As reported in #24546, the `dlTest` artifact should be extracted into the `testsuite` directory. - - - - - 6d398066 by Ben Gamari at 2024-03-19T22:33:11-04:00 ghcup-metadata: Don't populate dlOutput unless necessary ghcup can apparently infer the output name of an artifact from its URL. Consequently, we should only include the `dlOutput` field when it would differ from the filename of `dlUri`. Fixes #24547. - - - - - 576f8b7e by Zubin Duggal at 2024-03-19T22:33:46-04:00 Revert "Apply shellcheck suggestion to SUBST_TOOLDIR" This reverts commit c82770f57977a2b5add6e1378f234f8dd6153392. The shellcheck suggestion is spurious and results in SUBST_TOOLDIR being a no-op. `set` sets positional arguments for bash, but we want to set the variable given as the first autoconf argument. Fixes #24542 Metric decreases because the paths in the settings file are now shorter, so we allocate less when we read the settings file. ------------------------- Metric Decrease: T12425 T13035 T9198 ------------------------- - - - - - cdfe6e01 by Fendor at 2024-03-19T22:34:22-04:00 Compact serialisation of IfaceAppArgs In #24563, we identified that IfaceAppArgs serialisation tags each cons cell element with a discriminator byte. These bytes add up quickly, blowing up interface files considerably when '-fwrite-if-simplified-core' is enabled. We compact the serialisation by writing out the length of 'IfaceAppArgs', followed by serialising the elements directly without any discriminator byte. This improvement can decrease the size of some interface files by up to 35%. - - - - - 97a2bb1c by Simon Peyton Jones at 2024-03-20T17:11:29+00:00 Expand untyped splices in tcPolyExprCheck Fixes #24559 - - - - - 5f275176 by Alan Zimmerman at 2024-03-20T22:44:12-04:00 EPA: Clean up Exactprint helper functions a bit - Introduce a helper lens to compose on `EpAnn a` vs `a` versions - Rename some prime versions of functions back to non-prime They were renamed during the rework - - - - - da2a10ce by Vladislav Zavialov at 2024-03-20T22:44:48-04:00 Type operators in promoteOccName (#24570) Type operators differ from term operators in that they are lexically classified as (type) constructors, not as (type) variables. Prior to this change, promoteOccName did not account for this difference, causing a scoping issue that affected RequiredTypeArguments. type (!@#) = Bool f = idee (!@#) -- Not in scope: ‘!@#’ (BUG) Now we have a special case in promoteOccName to account for this. - - - - - 247fc0fa by Preetham Gujjula at 2024-03-21T10:19:18-04:00 docs: Remove mention of non-existent Ord instance for Complex The documentation for Data.Complex says that the Ord instance for Complex Float is deficient, but there is no Ord instance for Complex a. The Eq instance for Complex Float is similarly deficient, so we use that as an example instead. - - - - - 6fafc51e by Andrei Borzenkov at 2024-03-21T10:19:54-04:00 Fix TH handling in `pat_to_type_pat` function (#24571) There was missing case for `SplicePat` in `pat_to_type_at` function, hence patterns with splicing that checked against `forall->` doesn't work properly because they fall into the "illegal pattern" case. Code example that is now accepted: g :: forall a -> () g $([p| a |]) = () - - - - - 52072f8e by Sylvain Henry at 2024-03-21T21:01:59-04:00 Type-check default declarations before deriving clauses (#24566) See added Note and #24566. Default declarations must be type-checked before deriving clauses. - - - - - 7dfdf3d9 by Sylvain Henry at 2024-03-21T21:02:40-04:00 Lexer: small perf changes - Use unsafeChr because we know our values to be valid - Remove some unnecessary use of `ord` (return Word8 values directly) - - - - - 864922ef by Sylvain Henry at 2024-03-21T21:02:40-04:00 JS: fix some comments - - - - - 3e0b2b1f by Sebastian Graf at 2024-03-21T21:03:16-04:00 Simplifier: Re-do dependency analysis in abstractFloats (#24551) In #24551, we abstracted a string literal binding over a type variable, triggering a CoreLint error when that binding floated to top-level. The solution implemented in this patch fixes this by re-doing dependency analysis on a simplified recursive let binding that is about to be type abstracted, in order to find the minimal set of type variables to abstract over. See wrinkle (AB5) of Note [Floating and type abstraction] for more details. Fixes #24551 - - - - - 8a8ac65a by Matthew Craven at 2024-03-23T00:20:52-04:00 Improve toInteger @Word32 on 64-bit platforms On 64-bit platforms, every Word32 fits in an Int, so we can convert to Int# without having to perform the overflow check integerFromWord# uses internally. - - - - - 0c48f2b9 by Apoorv Ingle at 2024-03-23T00:21:28-04:00 Fix for #24552 (see testcase T24552) Fixes for a bug in desugaring pattern synonyms matches, introduced while working on on expanding `do`-blocks in #18324 The `matchWrapper` unecessarily (and incorrectly) filtered out the default wild patterns in a match. Now the wild pattern alternative is simply ignored by the pm check as its origin is `Generated`. The current code now matches the expected semantics according to the language spec. - - - - - b72705e9 by Simon Peyton Jones at 2024-03-23T00:22:04-04:00 Print more info about kinds in error messages This fixes #24553, where GHC unhelpfully said error: [GHC-83865] • Expected kind ‘* -> * -> *’, but ‘Foo’ has kind ‘* -> * -> *’ See Note [Showing invisible bits of types in error messages] - - - - - 8f7cfc7e by Tristan Cacqueray at 2024-03-23T00:22:44-04:00 docs: remove the don't use float hint This hint is outdated, ``Complex Float`` are now specialised, and the heap space suggestion needs more nuance so it should be explained in the unboxed/storable array documentation. - - - - - 5bd8ed53 by Andreas Klebinger at 2024-03-23T16:18:33-04:00 NCG: Fix a bug in jump shortcutting. When checking if a jump has more than one destination account for the possibility of some jumps not being representable by a BlockId. We do so by having isJumpishInstr return a `Maybe BlockId` where Nothing represents non-BlockId jump destinations. Fixes #24507 - - - - - 8d67f247 by Ben Gamari at 2024-03-23T16:19:09-04:00 docs: Drop old release notes, add for 9.12.1 - - - - - 7db8c992 by Cheng Shao at 2024-03-25T13:45:46-04:00 rts: fix clang compilation on aarch64 This patch fixes function prototypes in ARMOutlineAtomicsSymbols.h which causes "error: address argument to atomic operation must be a pointer to _Atomic type" when compiling with clang on aarch64. - - - - - 237194ce by Sylvain Henry at 2024-03-25T13:46:27-04:00 Lexer: fix imports for Alex 3.5.1 (#24583) - - - - - 810660b7 by Cheng Shao at 2024-03-25T22:19:16-04:00 libffi-tarballs: bump libffi-tarballs submodule to libffi 3.4.6 This commit bumps the libffi-tarballs submodule to libffi 3.4.6, which includes numerous upstream libffi fixes, especially https://github.com/libffi/libffi/issues/760. - - - - - d2ba41e8 by Alan Zimmerman at 2024-03-25T22:19:51-04:00 EPA: do not duplicate comments in signature RHS - - - - - 32a8103f by Rodrigo Mesquita at 2024-03-26T21:16:12-04:00 configure: Use LDFLAGS when trying linkers A user may configure `LDFLAGS` but not `LD`. When choosing a linker, we will prefer `ldd`, then `ld.gold`, then `ld.bfd` -- however, we have to check for a working linker. If either of these fail, we try the next in line. However, we were not considering the `$LDFLAGS` when checking if these linkers worked. So we would pick a linker that does not support the current $LDFLAGS and fail further down the line when we used that linker with those flags. Fixes #24565, where `LDFLAGS=-Wl,-z,pack-relative-relocs` is not supported by `ld.gold` but that was being picked still. - - - - - bf65a7c3 by Rodrigo Mesquita at 2024-03-26T21:16:48-04:00 bindist: Clean xattrs of bin and lib at configure time For issue #21506, we started cleaning the extended attributes of binaries and libraries from the bindist *after* they were installed to workaround notarisation (#17418), as part of `make install`. However, the `ghc-toolchain` binary that is now shipped with the bindist must be run at `./configure` time. Since we only cleaned the xattributes of the binaries and libs after they were installed, in some situations users would be unable to run `ghc-toolchain` from the bindist, failing at configure time (#24554). In this commit we move the xattr cleaning logic to the configure script. Fixes #24554 - - - - - cfeb70d3 by Rodrigo Mesquita at 2024-03-26T21:17:24-04:00 Revert "NCG: Fix a bug in jump shortcutting." This reverts commit 5bd8ed53dcefe10b72acb5729789e19ceb22df66. Fixes #24586 - - - - - 13223f6d by Serge S. Gulin at 2024-03-27T07:28:51-04:00 JS: `h$rts_isProfiled` is removed from `profiling` and left its version at `rts/js/config.js` - - - - - 0acfe391 by Alan Zimmerman at 2024-03-27T07:29:27-04:00 EPA: Do not extend declaration range for trailine zero len semi The lexer inserts virtual semicolons having zero width. Do not use them to extend the list span of items in a list. - - - - - cd0fb82f by Alan Zimmerman at 2024-03-27T19:33:08+00:00 EPA: Fix FamDecl range The span was incorrect if opt_datafam_kind_sig was empty - - - - - f8f384a8 by Ben Gamari at 2024-03-29T01:23:03-04:00 Fix type of _get_osfhandle foreign import Fixes #24601. - - - - - 00d3ecf0 by Alan Zimmerman at 2024-03-29T12:19:10+00:00 EPA: Extend StringLiteral range to include trailing commas This goes slightly against the exact printing philosophy where trailing decorations should be in an annotation, but the practicalities of adding it to the WarningTxt environment, and the problems caused by deviating do not make a more principles approach worthwhile. - - - - - efab3649 by brandon s allbery kf8nh at 2024-03-31T20:04:01-04:00 clarify Note [Preproccesing invocations] - - - - - c8a4c050 by Ben Gamari at 2024-04-02T12:50:35-04:00 rts: Fix TSAN_ENABLED CPP guard This should be `#if defined(TSAN_ENABLED)`, not `#if TSAN_ENABLED`, lest we suffer warnings. - - - - - e91dad93 by Cheng Shao at 2024-04-02T12:50:35-04:00 rts: fix errors when compiling with TSAN This commit fixes rts compilation errors when compiling with TSAN: - xxx_FENCE macros are redefined and trigger CPP warnings. - Use SIZEOF_W. WORD_SIZE_IN_BITS is provided by MachDeps.h which Cmm.h doesn't include by default. - - - - - a9ab9455 by Cheng Shao at 2024-04-02T12:50:35-04:00 rts: fix clang-specific errors when compiling with TSAN This commit fixes clang-specific rts compilation errors when compiling with TSAN: - clang doesn't have -Wtsan flag - Fix prototype of ghc_tsan_* helper functions - __tsan_atomic_* functions aren't clang built-ins and sanitizer/tsan_interface_atomic.h needs to be included - On macOS, TSAN runtime library is libclang_rt.tsan_osx_dynamic.dylib, not libtsan. -fsanitize-thread as a link-time flag will take care of linking the TSAN runtime library anyway so remove tsan as an rts extra library - - - - - 865bd717 by Cheng Shao at 2024-04-02T12:50:35-04:00 compiler: fix github link to __tsan_memory_order in a comment - - - - - 07cb627c by Cheng Shao at 2024-04-02T12:50:35-04:00 ci: improve TSAN CI jobs - Run TSAN jobs with +thread_sanitizer_cmm which enables Cmm instrumentation as well. - Run TSAN jobs in deb12 which ships gcc-12, a reasonably recent gcc that @bgamari confirms he's using in #GHC:matrix.org. Ideally we should be using latest clang release for latest improvements in sanitizers, though that's left as future work. - Mark TSAN jobs as manual+allow_failure in validate pipelines. The purpose is to demonstrate that we have indeed at least fixed building of TSAN mode in CI without blocking the patch to land, and once merged other people can begin playing with TSAN using their own dev setups and feature branches. - - - - - a1c18c7b by Andrei Borzenkov at 2024-04-02T12:51:11-04:00 Merge tc_infer_hs_type and tc_hs_type into one function using ExpType philosophy (#24299, #23639) This patch implements refactoring which is a prerequisite to updating kind checking of type patterns. This is a huge simplification of the main worker that checks kind of HsType. It also fixes the issues caused by previous code duplication, e.g. that we didn't add module finalizers from splices in inference mode. - - - - - 817e8936 by Rodrigo Mesquita at 2024-04-02T20:13:05-04:00 th: Hide the Language.Haskell.TH.Lib.Internal module from haddock Fixes #24562 - - - - - b36ee57b by Sylvain Henry at 2024-04-02T20:13:46-04:00 JS: reenable h$appendToHsString optimization (#24495) The optimization introducing h$appendToHsString wasn't kicking in anymore (while it did in 9.8.1) because of the changes introduced in #23270 (7e0c8b3bab30). This patch reenables the optimization by matching on case-expression, as done in Cmm for unpackCString# standard thunks. The test is also T24495 added in the next commits (two commits for ease of backporting to 9.8). - - - - - 527616e9 by Sylvain Henry at 2024-04-02T20:13:46-04:00 JS: fix h$appendToHsString implementation (#24495) h$appendToHsString needs to wrap its argument in an updatable thunk to behave like unpackAppendCString#. Otherwise if a SingleEntry thunk is passed, it is stored as-is in a CONS cell, making the resulting list impossible to deepseq (forcing the thunk doesn't update the contents of the CONS cell)! The added test checks that the optimization kicks in and that h$appendToHsString works as intended. Fix #24495 - - - - - faa30b41 by Simon Peyton Jones at 2024-04-02T20:14:22-04:00 Deal with duplicate tyvars in type declarations GHC was outright crashing before this fix: #24604 - - - - - e0b0c717 by Simon Peyton Jones at 2024-04-02T20:14:58-04:00 Try using MCoercion in exprIsConApp_maybe This is just a simple refactor that makes exprIsConApp_maybe a little bit more direct, simple, and efficient. Metrics: compile_time/bytes allocated geo. mean -0.1% minimum -2.0% maximum -0.0% Not a big gain, but worthwhile given that the code is, if anything, easier to grok. - - - - - 15f4d867 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Initial ./configure support for selecting I/O managers In this patch we just define new CPP vars, but don't yet use them or replace the existing approach. That will follow. The intention here is that every I/O manager can be enabled/disabled at GHC build time (subject to some constraints). More than one I/O manager can be enabled to be built. At least one I/O manager supporting the non-threaded RTS must be enabled as well as at least one supporting the non-threaded RTS. The I/O managers enabled here will become the choices available at runtime at RTS startup (in later patches). The choice can be made with RTS flags. There are separate sets of choices for the threaded and non-threaded RTS ways, because most I/O managers are specific to these ways. Furthermore we must establish a default I/O manager for the threaded and non-threaded RTS. Most I/O managers are platform-specific so there are checks to ensure each one can be enabled on the platform. Such checks are also where (in future) any system dependencies (e.g. libraries) can be checked. The output is a set of CPP flags (in the mk/config.h file), with one flag per named I/O manager: * IOMGR_BUILD_<name> : which ones should be built (some) * IOMGR_DEFAULT_NON_THREADED_<name> : which one is default (exactly one) * IOMGR_DEFAULT_THREADED_<name> : which one is default (exactly one) and a set of derived flags in IOManager.h * IOMGR_ENABLED_<name> : enabled for the current RTS way Note that IOMGR_BUILD_<name> just says that an I/O manager will be built for _some_ RTS way (i.e. threaded or non-threaded). The derived flags IOMGR_ENABLED_<name> in IOManager.h say if each I/O manager is enabled in the "current" RTS way. These are the ones that can be used for conditional compilation of the I/O manager code. Co-authored-by: Pi Delport <pi at well-typed.com> - - - - - 85b0f87a by Duncan Coutts at 2024-04-03T01:27:17-04:00 Change the handling of the RTS flag --io-manager= Now instead of it being just used on Windows to select between the WinIO vs the MIO or Win32-legacy I/O managers, it is now used on all platforms for selecting the I/O manager to use. Right now it remains the case that there is only an actual choice on Windows, but that will change later. Document the --io-manager flag in the user guide. This change is also reflected in the RTS flags types in the base library. Deprecate the export of IoSubSystem from GHC.RTS.Flags with a message to import it from GHC.IO.Subsystem. The way the 'IoSubSystem' is detected also changes. Instead of looking at the RTS flag, there is now a C bool global var in the RTS which gets set on startup when the I/O manager is selected. This bool var says whether the selected I/O manager classifies as "native" on Windows, which in practice means the WinIO I/O manager has been selected. Similarly, the is_io_mng_native_p RTS helper function is re-implemented in terms of the selected I/O manager, rather than based on the RTS flags. We do however remove the ./configure --native-io-manager flag because we're bringing the WinIO/MIO/Win32-legacy choice under the new general scheme for selecting I/O managers, and that new scheme involves no ./configure time user choices, just runtime RTS flag choices. - - - - - 1a8f020f by Duncan Coutts at 2024-04-03T01:27:17-04:00 Convert {init,stop,exit}IOManager to switch style Rather than ad-hoc cpp conitionals on THREADED_RTS and mingw32_HOST_OS, we use a style where we switch on the I/O manager impl, with cases for each I/O manager impl. - - - - - a5bad3d2 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Split up the CapIOManager content by I/O manager Using the new IOMGR_ENABLED_<name> CPP defines. - - - - - 1d36e609 by Duncan Coutts at 2024-04-03T01:27:17-04:00 Convert initIOManagerAfterFork and wakeupIOManager to switch style - - - - - c2f26f36 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move most of waitRead#/Write# from cmm to C Moves it into the IOManager.c where we can follow the new pattern of switching on the selected I/O manager. - - - - - 457705a8 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move most of the delay# impl from cmm to C Moves it into the IOManager.c where we can follow the new pattern of switching on the selected I/O manager. Uses a new IOManager API: syncDelay, following the naming convention of sync* for thread-synchronous I/O & timer/delay operations. As part of porting from cmm to C, we maintain the rule that the why_blocked gets accessed using load acquire and store release atomic memory operations. There was one exception to this rule: in the delay# primop cmm code on posix (not win32), the why_blocked was being updated using a store relaxed, not a store release. I've no idea why. In this convesion I'm playing it safe here and using store release consistently. - - - - - e93058e0 by Duncan Coutts at 2024-04-03T01:27:18-04:00 insertIntoSleepingQueue is no longer public No longer defined in IOManager.h, just a private function in IOManager.c. Since it is no longer called from cmm code, just from syncDelay. It ought to get moved further into the select() I/O manager impl, rather than living in IOManager.c. On the other hand appendToIOBlockedQueue is still called from cmm code in the win32-legacy I/O manager primops async{Read,Write}#, and it is also used by the select() I/O manager. Update the CPP and comments to reflect this. - - - - - 60ce9910 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move anyPendingTimeoutsOrIO impl from .h to .c The implementation is eventually going to need to use more private things, which will drag in unwanted includes into IOManager.h, so it's better to move the impl out of the header file and into the .c file, at the slight cost of it no longer being inline. At the same time, change to the "switch (iomgr_type)" style. - - - - - f70b8108 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Take a simpler approach to gcc warnings in IOManager.c We have lots of functions with conditional implementations for different I/O managers. Some functions, for some I/O managers, naturally have implementations that do nothing or barf. When only one such I/O manager is enabled then the whole function implementation will have an implementation that does nothing or barfs. This then results in warnings from gcc that parameters are unused, or that the function should be marked with attribute noreturn (since barf does not return). The USED_IF_THREADS trick for fine-grained warning supression is fine for just two cases, but an equivalent here would need USED_IF_THE_ONLY_ENABLED_IOMGR_IS_X_OR_Y which would have combinitorial blowup. So we take a coarse grained approach and simply disable these two warnings for the whole file. So we use a GCC pragma, with its handy push/pop support: #pragma GCC diagnostic push #pragma GCC diagnostic ignored "-Wsuggest-attribute=noreturn" #pragma GCC diagnostic ignored "-Wunused-parameter" ... #pragma GCC diagnostic pop - - - - - b48805b9 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add a new trace class for the iomanager It makes sense now for it to be separate from the scheduler class of tracers. Enabled with +RTS -Do. Document the -Do debug flag in the user guide. - - - - - f0c1f862 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Have the throwTo impl go via (new) IOManager APIs rather than directly operating on the IO manager's data structures. Specifically, when thowing an async exception to a thread that is blocked waiting for I/O or waiting for a timer, then we want to cancel that I/O waiting or cancel the timer. Currently this is done directly in removeFromQueues() in RaiseAsync.c. We want it to go via proper APIs both for modularity but also to let us support multiple I/O managers. So add sync{IO,Delay}Cancel, which is the cancellation for the corresponding sync{IO,Delay}. The implementations of these use the usual "switch (iomgr_type)" style. - - - - - 4f9e9c4e by Duncan Coutts at 2024-04-03T01:27:18-04:00 Move awaitEvent into a proper IOManager API and have the scheduler use it. Previously the scheduler calls awaitEvent directly, and awaitEvent is implemented directly in the RTS I/O managers (select, win32). This relies on the old scheme where there's a single active I/O manager for each platform and RTS way. We want to move that to go via an API in IOManager.{h,c} which can then call out to the active I/O manager. Also take the opportunity to split awaitEvent into two. The existing awaitEvent has a bool wait parameter, to say if the call should be blocking or non-blocking. We split this into two separate functions: pollCompletedTimeoutsOrIO and awaitCompletedTimeoutsOrIO. We split them for a few reasons: they have different post-conditions (specifically the await version is supposed to guarantee that there are threads runnable when it completes). Secondly, it is also anticipated that in future I/O managers the implementations of the two cases will be simpler if they are separated. - - - - - 5ad4b30f by Duncan Coutts at 2024-04-03T01:27:18-04:00 Rename awaitEvent in select and win32 I/O managers These are now just called from IOManager.c and are the per-I/O manager backend impls (whereas previously awaitEvent was the entry point). Follow the new naming convention in the IOManager.{h,c} of awaitCompletedTimeoutsOrIO, with the I/O manager's name as a suffix: so awaitCompletedTimeoutsOrIO{Select,Win32}. - - - - - d30c6bc6 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Tidy up a couple things in Select.{h,c} Use the standard #include {Begin,End}Private.h style rather than RTS_PRIVATE on individual decls. And conditionally build the code for the select I/O manager based on the new CPP IOMGR_ENABLED_SELECT rather than on THREADED_RTS. - - - - - 4161f516 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add an IOManager API for scavenging TSO blocked_info When the GC scavenges a TSO it needs to scavenge the tso->blocked_info but the blocked_info is a big union and what lives there depends on the two->why_blocked, which for I/O-related reasons is something that in principle is the responsibility of the I/O manager and not the GC. So the right thing to do is for the GC to ask the I/O manager to sscavenge the blocked_info if it encounters any I/O-related why_blocked reasons. So we add scavengeTSOIOManager in IOManager.{h,c} with the usual style. Now as it happens, right now, there is no special scavenging to do, so the implementation of scavengeTSOIOManager is a fancy no-op. That's because the select I/O manager uses only the fd and target members, which are not GC pointers, and the win32-legacy I/O manager _ought_ to be using GC-managed heap objects for the StgAsyncIOResult but it is actually usingthe C heap, so again no GC pointers. If the win32-legacy were doing this more sensibly, then scavengeTSOIOManager would be the right place to do the GC magic. Future I/O managers will need GC heap objects in the tso->blocked_info and will make use of this functionality. - - - - - 94a87d21 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add I/O manager API notifyIOManagerCapabilitiesChanged Used in setNumCapabilities. It only does anything for MIO on Posix. Previously it always invoked Haskell code, but that code only did anything on non-Windows (and non-JS), and only threaded. That currently effectively means the MIO I/O manager on Posix. So now it only invokes it for the MIO Posix case. - - - - - 3be6d591 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Select an I/O manager early in RTS startup We need to select the I/O manager to use during startup before the per-cap I/O manager initialisation. - - - - - aaa294d0 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Make struct CapIOManager be fully opaque Provide an opaque (forward) definition in Capability.h (since the cap contains a *CapIOManager) and then only provide a full definition in a new file IOManagerInternals.h. This new file is only supposed to be included by the IOManager implementation, not by its users. So that means IOManager.c and individual I/O manager implementations. The posix/Signals.c still needs direct access, but that should be eliminated. Anything that needs direct access either needs to be clearly part of an I/O manager (e.g. the sleect() one) or go via a proper API. - - - - - 877a2a80 by Duncan Coutts at 2024-04-03T01:27:18-04:00 The select() I/O manager does have some global initialisation It's just to make sure an exception CAF is a GC root. - - - - - 9c51473b by Duncan Coutts at 2024-04-03T01:27:18-04:00 Add tracing for the main I/O manager actions Using the new tracer class. Note: The unconditional definition of showIOManager should be compatible with the debugTrace change in 7c7d1f6. Co-authored-by: Pi Delport <pi at well-typed.com> - - - - - c7d3e3a3 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Include the default I/O manager in the +RTS --info output Document the extra +RTS --info output in the user guide - - - - - 8023bad4 by Duncan Coutts at 2024-04-03T01:27:18-04:00 waitRead# / waitWrite# do not work for win32-legacy I/O manager Previously it was unclear that they did not work because the code path was shared with other I/O managers (in particular select()). Following the code carefully shows that what actually happens is that the calling thread would block forever: the thread will be put into the blocked queue, but no other action is scheduled that will ever result in it getting unblocked. It's better to just fail loudly in case anyone accidentally calls it, also it's less confusing code. - - - - - 83a74d20 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Conditionally ignore some GCC warnings Some GCC versions don't know about some warnings, and they complain that we're ignoring unknown warnings. So we try to ignore the warning based on the GCC version. - - - - - 1adc6fa4 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Accept changes to base-exports All the changes are in fact not changes at all. Previously, the IoSubSystem data type was defined in GHC.RTS.Flags and exported from both GHC.RTS.Flags and GHC.IO.SubSystem. Now, the data type is defined in GHC.IO.SubSystem and still exported from both modules. Therefore, the same exports and same instances are still available from both modules. But the base-exports records only the defining module, and so it looks like a change when it is fully compatible. Related: we do add a deprecation to the export of the type via GHC.RTS.Flags, telling people to use the export from GHC.IO.SubSystem. Also the sort order for some unrelated Show instances changed. No idea why. The same changes apply in the other versions, with a few more changes due to sort order weirdness. - - - - - 8d950968 by Duncan Coutts at 2024-04-03T01:27:18-04:00 Accept metric decrease in T12227 I can't think of any good reason that anything in this MR should have changed the number of allocations, up or down. (Yes this is an empty commit.) Metric Decrease: T12227 - - - - - e869605e by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Several improvements to the handling of coercions * Make `mkSymCo` and `mkInstCo` smarter Fixes #23642 * Fix return role of `SelCo` in the coercion optimiser. Fixes #23617 * Make the coercion optimiser `opt_trans_rule` work better for newtypes Fixes #23619 - - - - - 1efd0714 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 FloatOut: improve floating for join point See the new Note [Floating join point bindings]. * Completely get rid of the complicated join_ceiling nonsense, which I have never understood. * Do not float join points at all, except perhaps to top level. * Some refactoring around wantToFloat, to treat Rec and NonRec more uniformly - - - - - 9c00154d by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Improve eta-expansion through call stacks See Note [Eta expanding through CallStacks] in GHC.Core.Opt.Arity This is a one-line change, that fixes an inconsistency - || isCallStackPredTy ty + || isCallStackPredTy ty || isCallStackTy ty - - - - - 95a9a172 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Spelling, layout, pretty-printing only - - - - - bdf1660f by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Improve exprIsConApp_maybe a little Eliminate a redundant case at birth. This sometimes reduces Simplifier iterations. See Note [Case elim in exprIsConApp_maybe]. - - - - - 609cd32c by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Inline GHC.HsToCore.Pmc.Solver.Types.trvVarInfo When exploring compile-time regressions after meddling with the Simplifier, I discovered that GHC.HsToCore.Pmc.Solver.Types.trvVarInfo was very delicately balanced. It's a small, heavily used, overloaded function and it's important that it inlines. By a fluke it was before, but at various times in my journey it stopped doing so. So I just added an INLINE pragma to it; no sense in depending on a delicately-balanced fluke. - - - - - ae24c9bc by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Slight improvement in WorkWrap Ensure that WorkWrap preserves lambda binders, in case of join points. Sadly I have forgotten why I made this change (it was while I was doing a lot of meddling in the Simplifier, but * it does no harm, * it is slightly more efficient, and * presumably it made something better! Anyway I have kept it in a separate commit. - - - - - e9297181 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Use named record fields for the CastIt { ... } data constructor This is a pure refactor - - - - - b4581e23 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Remove a long-commented-out line Pure refactoring - - - - - e026bdf2 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Simplifier improvements This MR started as: allow the simplifer to do more in one pass, arising from places I could see the simplifier taking two iterations where one would do. But it turned into a larger project, because these changes unexpectedly made inlining blow up, especially join points in deeply-nested cases. The main changes are below. There are also many new or rewritten Notes. Avoiding simplifying repeatedly ~~~~~~~~~~~~~~~ See Note [Avoiding simplifying repeatedly] * The SimplEnv now has a seInlineDepth field, which says how deep in unfoldings we are. See Note [Inline depth] in Simplify.Env. Currently used only for the next point: avoiding repeatedly simplifying coercions. * Avoid repeatedly simplifying coercions. see Note [Avoid re-simplifying coercions] in Simplify.Iteration As you'll see from the Note, this makes use of the seInlineDepth. * Allow Simplify.Iteration.simplAuxBind to inline used-once things. This is another part of Note [Post-inline for single-use things], and is really good for reducing simplifier iterations in situations like case K e of { K x -> blah } wher x is used once in blah. * Make GHC.Core.SimpleOpt.exprIsConApp_maybe do some simple case elimination. Note [Case elim in exprIsConApp_maybe] * Improve the case-merge transformation: - Move the main code to `GHC.Core.Utils.mergeCaseAlts`, to join `filterAlts` and friends. See Note [Merge Nested Cases] in GHC.Core.Utils. - Add a new case for `tagToEnum#`; see wrinkle (MC3). - Add a new case to look through join points: see wrinkle (MC4) postInlineUnconditionally ~~~~~~~~~~~~~~~~~~~~~~~~~ * Allow Simplify.Utils.postInlineUnconditionally to inline variables that are used exactly once. See Note [Post-inline for single-use things]. * Do not postInlineUnconditionally join point, ever. Doing so does not reduce allocation, which is the main point, and with join points that are used a lot it can bloat code. See point (1) of Note [Duplicating join points] in GHC.Core.Opt.Simplify.Iteration. * Do not postInlineUnconditionally a strict (demanded) binding. It will not allocate a thunk (it'll turn into a case instead) so again the main point of inlining it doesn't hold. Better to check per-call-site. * Improve occurrence analyis for bottoming function calls, to help postInlineUnconditionally. See Note [Bottoming function calls] in GHC.Core.Opt.OccurAnal Inlining generally ~~~~~~~~~~~~~~~~~~ * In GHC.Core.Opt.Simplify.Utils.interestingCallContext, use RhsCtxt NonRecursive (not BoringCtxt) for a plain-seq case. See Note [Seq is boring] Also, wrinkle (SB1), inline in that `seq` context only for INLINE functions (UnfWhen guidance). * In GHC.Core.Opt.Simplify.Utils.interestingArg, - return ValueArg for OtherCon [c1,c2, ...], but - return NonTrivArg for OtherCon [] This makes a function a little less likely to inline if all we know is that the argument is evaluated, but nothing else. * isConLikeUnfolding is no longer true for OtherCon {}. This propagates to exprIsConLike. Con-like-ness has /positive/ information. Join points ~~~~~~~~~~~ * Be very careful about inlining join points. See these two long Notes Note [Duplicating join points] in GHC.Core.Opt.Simplify.Iteration Note [Inlining join points] in GHC.Core.Opt.Simplify.Inline * When making join points, don't do so if the join point is so small it will immediately be inlined; check uncondInlineJoin. * In GHC.Core.Opt.Simplify.Inline.tryUnfolding, improve the inlining heuristics for join points. In general we /do not/ want to inline join points /even if they are small/. See Note [Duplicating join points] GHC.Core.Opt.Simplify.Iteration. But sometimes we do: see Note [Inlining join points] in GHC.Core.Opt.Simplify.Inline; and the new `isBetterUnfoldingThan` function. * Do not add an unfolding to a join point at birth. This is a tricky one and has a long Note [Do not add unfoldings to join points at birth] It shows up in two places - In `mkDupableAlt` do not add an inlining - (trickier) In `simplLetUnfolding` don't add an unfolding for a fresh join point I am not fully satisifed with this, but it works and is well documented. * In GHC.Core.Unfold.sizeExpr, make jumps small, so that we don't penalise having a non-inlined join point. Performance changes ~~~~~~~~~~~~~~~~~~~ * Binary sizes fall by around 2.6%, according to nofib. * Compile times improve slightly. Here are the figures over 1%. I investiate the biggest differnce in T18304. It's a very small module, just a few hundred nodes. The large percentage difffence is due to a single function that didn't quite inline before, and does now, making code size a bit bigger. I decided gains outweighed the losses. Metrics: compile_time/bytes allocated (changes over +/- 1%) ------------------------------------------------ CoOpt_Singletons(normal) -9.2% GOOD LargeRecord(normal) -23.5% GOOD MultiComponentModulesRecomp(normal) +1.2% MultiLayerModulesTH_OneShot(normal) +4.1% BAD PmSeriesS(normal) -3.8% PmSeriesV(normal) -1.5% T11195(normal) -1.3% T12227(normal) -20.4% GOOD T12545(normal) -3.2% T12707(normal) -2.1% GOOD T13253(normal) -1.2% T13253-spj(normal) +8.1% BAD T13386(normal) -3.1% GOOD T14766(normal) -2.6% GOOD T15164(normal) -1.4% T15304(normal) +1.2% T15630(normal) -8.2% T15630a(normal) NEW T15703(normal) -14.7% GOOD T16577(normal) -2.3% GOOD T17516(normal) -39.7% GOOD T18140(normal) +1.2% T18223(normal) -17.1% GOOD T18282(normal) -5.0% GOOD T18304(normal) +10.8% BAD T18923(normal) -2.9% GOOD T1969(normal) +1.0% T19695(normal) -1.5% T20049(normal) -12.7% GOOD T21839c(normal) -4.1% GOOD T3064(normal) -1.5% T3294(normal) +1.2% BAD T4801(normal) +1.2% T5030(normal) -15.2% GOOD T5321Fun(normal) -2.2% GOOD T6048(optasm) -16.8% GOOD T783(normal) -1.2% T8095(normal) -6.0% GOOD T9630(normal) -4.7% GOOD T9961(normal) +1.9% BAD WWRec(normal) -1.4% info_table_map_perf(normal) -1.3% parsing001(normal) +1.5% geo. mean -2.0% minimum -39.7% maximum +10.8% * Runtimes generally improve. In the testsuite perf/should_run gives: Metrics: runtime/bytes allocated ------------------------------------------ Conversions(normal) -0.3% T13536a(optasm) -41.7% GOOD T4830(normal) -0.1% haddock.Cabal(normal) -0.1% haddock.base(normal) -0.1% haddock.compiler(normal) -0.1% geo. mean -0.8% minimum -41.7% maximum +0.0% * For runtime, nofib is a better test. The news is mostly good. Here are the number more than +/- 0.1%: # bytes allocated ==========================++========== imaginary/digits-of-e1 || -14.40% imaginary/digits-of-e2 || -4.41% imaginary/paraffins || -0.17% imaginary/rfib || -0.15% imaginary/wheel-sieve2 || -0.10% real/compress || -0.47% real/fluid || -0.10% real/fulsom || +0.14% real/gamteb || -1.47% real/gg || -0.20% real/infer || +0.24% real/pic || -0.23% real/prolog || -0.36% real/scs || -0.46% real/smallpt || +4.03% shootout/k-nucleotide || -20.23% shootout/n-body || -0.42% shootout/spectral-norm || -0.13% spectral/boyer2 || -3.80% spectral/constraints || -0.27% spectral/hartel/ida || -0.82% spectral/mate || -20.34% spectral/para || +0.46% spectral/rewrite || +1.30% spectral/sphere || -0.14% ==========================++========== geom mean || -0.59% real/smallpt has a huge nest of local definitions, and I could not pin down a reason for a regression. But there are three big wins! Metric Decrease: CoOpt_Singletons LargeRecord T12227 T12707 T13386 T13536a T14766 T15703 T16577 T17516 T18223 T18282 T18923 T21839c T20049 T5321Fun T5030 T6048 T8095 T9630 T783 Metric Increase: MultiLayerModulesTH_OneShot T13253-spj T18304 T18698a T9961 T3294 - - - - - 27db3c5e by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Testsuite message changes from simplifier improvements - - - - - 271a7812 by Simon Peyton Jones at 2024-04-03T01:27:55-04:00 Account for bottoming functions in OccurAnal This fixes #24582, a small but long-standing bug - - - - - 0fde229f by Ben Gamari at 2024-04-04T07:04:58-04:00 testsuite: Introduce template-haskell-exports test - - - - - 0c4a9686 by Luite Stegeman at 2024-04-04T07:05:39-04:00 Update correct counter in bumpTickyAllocd - - - - - 5f085d3a by Fendor at 2024-04-04T14:47:33-04:00 Replace `SizedSeq` with `FlatBag` for flattened structure LinkedLists are notoriously memory ineffiecient when all we do is traversing a structure. As 'UnlinkedBCO' has been identified as a data structure that impacts the overall memory usage of GHCi sessions, we avoid linked lists and prefer flattened structure for storing. We introduce a new memory efficient representation of sequential elements that has special support for the cases: * Empty * Singleton * Tuple Elements This improves sharing in the 'Empty' case and avoids the overhead of 'Array' until its constant overhead is justified. - - - - - 82cfe10c by Fendor at 2024-04-04T14:47:33-04:00 Compact FlatBag array representation `Array` contains three additional `Word`'s we do not need in `FlatBag`. Move `FlatBag` to `SmallArray`. Expand the API of SmallArray by `sizeofSmallArray` and add common traversal functions, such as `mapSmallArray` and `foldMapSmallArray`. Additionally, allow users to force the elements of a `SmallArray` via `rnfSmallArray`. - - - - - 36a75b80 by Andrei Borzenkov at 2024-04-04T14:48:10-04:00 Change how invisible patterns represented in haskell syntax and TH AST (#24557) Before this patch: data ArgPat p = InvisPat (LHsType p) | VisPat (LPat p) With this patch: data Pat p = ... | InvisPat (LHsType p) ... And the same transformation in the TH land. The rest of the changes is just updating code to handle new AST and writing tests to check if it is possible to create invalid states using TH. Metric Increase: MultiLayerModulesTH_OneShot - - - - - 28009fbc by Matthew Pickering at 2024-04-04T14:48:46-04:00 Fix off by one error in seekBinNoExpand and seekBin - - - - - 9b9e031b by Ben Gamari at 2024-04-04T21:30:08-04:00 compiler: Allow more types in GHCForeignImportPrim For many, many years `GHCForeignImportPrim` has suffered from the rather restrictive limitation of not allowing any non-trivial types in arguments or results. This limitation was justified by the code generator allegely barfing in the presence of such types. However, this restriction appears to originate well before the NCG rewrite and the new NCG does not appear to have any trouble with such types (see the added `T24598` test). Lift this restriction. Fixes #24598. - - - - - 1324b862 by Alan Zimmerman at 2024-04-04T21:30:44-04:00 EPA: Use EpaLocation not SrcSpan in ForeignDecls This allows us to update them for makeDeltaAst in ghc-exactprint - - - - - 19883a23 by Alan Zimmerman at 2024-04-05T16:58:17-04:00 EPA: Use EpaLocation for RecFieldsDotDot So we can update it to a delta position in makeDeltaAst if needed. - - - - - e8724327 by Matthew Pickering at 2024-04-05T16:58:53-04:00 Remove accidentally committed test.hs - - - - - 88cb3e10 by Fendor at 2024-04-08T09:03:34-04:00 Avoid UArray when indexing is not required `UnlinkedBCO`'s can occur many times in the heap. Each `UnlinkedBCO` references two `UArray`'s but never indexes them. They are only needed to encode the elements into a `ByteArray#`. The three words for the lower bound, upper bound and number of elements are essentially unused, thus we replace `UArray` with a wrapper around `ByteArray#`. This saves us up to three words for each `UnlinkedBCO`. Further, to avoid re-allocating these words for `ResolvedBCO`, we repeat the procedure for `ResolvedBCO` and add custom `Binary` and `Show` instances. For example, agda's repl session has around 360_000 UnlinkedBCO's, so avoiding these three words is already saving us around 8MB residency. - - - - - f2cc1107 by Fendor at 2024-04-08T09:04:11-04:00 Never UNPACK `FastMutInt` for counting z-encoded `FastString`s In `FastStringTable`, we count the number of z-encoded FastStrings that exist in a GHC session. We used to UNPACK the counters to not waste memory, but live retainer analysis showed that we allocate a lot of `FastMutInt`s, retained by `mkFastZString`. We lazily compute the `FastZString`, only incrementing the counter when the `FastZString` is forced. The function `mkFastStringWith` calls `mkZFastString` and boxes the `FastMutInt`, leading to the following core: mkFastStringWith = \ mk_fs _ -> = case stringTable of { FastStringTable _ n_zencs segments# _ -> ... case ((mk_fs (I# ...) (FastMutInt n_zencs)) `cast` <Co:2> :: ...) ... Marking this field as `NOUNPACK` avoids this reboxing, eliminating the allocation of a fresh `FastMutInt` on every `FastString` allocation. - - - - - c6def949 by Matthew Pickering at 2024-04-08T16:06:51-04:00 Force in_multi to avoid retaining entire hsc_env - - - - - fbb91a63 by Fendor at 2024-04-08T16:06:51-04:00 Eliminate name thunk in declaration fingerprinting Thunk analysis showed that we have about 100_000 thunks (in agda and `-fwrite-simplified-core`) pointing to the name of the name decl. Forcing this thunk fixes this issue. The thunk created here is retained by the thunk created by forkM, it is better to eagerly force this because the result (a `Name`) is already retained indirectly via the `IfaceDecl`. - - - - - 3b7b0c1c by Alan Zimmerman at 2024-04-08T16:07:27-04:00 EPA: Use EpaLocation in WarningTxt This allows us to use an EpDelta if needed when using makeDeltaAst. - - - - - 12b997df by Alan Zimmerman at 2024-04-08T16:07:27-04:00 EPA: Move DeltaPos and EpaLocation' into GHC.Types.SrcLoc This allows us to use a NoCommentsLocation for the possibly trailing comma location in a StringLiteral. This in turn allows us to correctly roundtrip via makeDeltaAst. - - - - - 868c8a78 by Fendor at 2024-04-09T08:51:50-04:00 Prefer packed representation for CompiledByteCode As there are many 'CompiledByteCode' objects alive during a GHCi session, representing its element in a more packed manner improves space behaviour at a minimal cost. When running GHCi on the agda codebase, we find around 380 live 'CompiledByteCode' objects. Packing their respective 'UnlinkedByteCode' can save quite some pointers. - - - - - be3bddde by Alan Zimmerman at 2024-04-09T08:52:26-04:00 EPA: Capture all comments in a ClassDecl Hopefully the final fix needed for #24533 - - - - - 3d0806fc by Jade at 2024-04-10T05:39:53-04:00 Validate -main-is flag using parseIdentifier Fixes #24368 - - - - - dd530bb7 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 rts: free error message before returning Fixes a memory leak in rts/linker/PEi386.c - - - - - e008a19a by Alexis King at 2024-04-10T05:40:29-04:00 linker: Avoid linear search when looking up Haskell symbols via dlsym See the primary Note [Looking up symbols in the relevant objects] for a more in-depth explanation. When dynamically loading a Haskell symbol (typical when running a splice or GHCi expression), before this commit we would search for the symbol in all dynamic libraries that were loaded. However, this could be very inefficient when too many packages are loaded (which can happen if there are many package dependencies) because the time to lookup the would be linear in the number of packages loaded. This commit drastically improves symbol loading performance by introducing a mapping from units to the handles of corresponding loaded dlls. These handles are returned by dlopen when we load a dll, and can then be used to look up in a specific dynamic library. Looking up a given Name is now much more precise because we can get lookup its unit in the mapping and lookup the symbol solely in the handles of the dynamic libraries loaded for that unit. In one measurement, the wait time before the expression was executed went from +-38 seconds down to +-2s. This commit also includes Note [Symbols may not be found in pkgs_loaded], explaining the fallback to the old behaviour in case no dll can be found in the unit mapping for a given Name. Fixes #23415 Co-authored-by: Rodrigo Mesquita (@alt-romes) - - - - - dcfaa190 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 rts: Make addDLL a wrapper around loadNativeObj Rewrite the implementation of `addDLL` as a wrapper around the more principled `loadNativeObj` rts linker function. The latter should be preferred while the former is preserved for backwards compatibility. `loadNativeObj` was previously only available on ELF platforms, so this commit further refactors the rts linker to transform loadNativeObj_ELF into loadNativeObj_POSIX, which is available in ELF and MachO platforms. The refactor made it possible to remove the `dl_mutex` mutex in favour of always using `linker_mutex` (rather than a combination of both). Lastly, we implement `loadNativeObj` for Windows too. - - - - - 12931698 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 Use symbol cache in internal interpreter too This commit makes the symbol cache that was used by the external interpreter available for the internal interpreter too. This follows from the analysis in #23415 that suggests the internal interpreter could benefit from this cache too, and that there is no good reason not to have the cache for it too. It also makes it a bit more uniform to have the symbol cache range over both the internal and external interpreter. This commit also refactors the cache into a function which is used by both `lookupSymbol` and also by `lookupSymbolInDLL`, extending the caching logic to `lookupSymbolInDLL` too. - - - - - dccd3ea1 by Ben Gamari at 2024-04-10T05:40:29-04:00 testsuite: Add test for lookupSymbolInNativeObj - - - - - 1b1a92bd by Alan Zimmerman at 2024-04-10T05:41:05-04:00 EPA: Remove unnecessary XRec in CompleteMatchSig The XRec for [LIdP pass] is not needed for exact printing, remove it. - - - - - 6e18ce2b by Ben Gamari at 2024-04-12T08:16:09-04:00 users-guide: Clarify language extension documentation Over the years the users guide's language extension documentation has gone through quite a few refactorings. In the process some of the descriptions have been rendered non-sensical. For instance, the description of `NoImplicitPrelude` actually describes the semantics of `ImplicitPrelude`. To fix this we: * ensure that all extensions are named in their "positive" sense (e.g. `ImplicitPrelude` rather than `NoImplicitPrelude`). * rework the documentation to avoid flag-oriented wording like "enable" and "disable" * ensure that the polarity of the documentation is consistent with reality. Fixes #23895. - - - - - a933aff3 by Zubin Duggal at 2024-04-12T08:16:45-04:00 driver: Make `checkHomeUnitsClosed` faster The implementation of `checkHomeUnitsClosed` was traversing every single path in the unit dependency graph - this grows exponentially and quickly grows to be infeasible on larger unit dependency graphs. Instead we replace this with a faster implementation which follows from the specificiation of the closure property - there is a closure error if there are units which are both are both (transitively) depended upon by home units and (transitively) depend on home units, but are not themselves home units. To compute the set of units required for closure, we first compute the closure of the unit dependency graph, then the transpose of this closure, and find all units that are reachable from the home units in the transpose of the closure. - - - - - 23c3e624 by Andreas Klebinger at 2024-04-12T08:17:21-04:00 RTS: Emit warning when -M < -H Fixes #24487 - - - - - d23afb8c by Ben Gamari at 2024-04-12T08:17:56-04:00 testsuite: Add broken test for CApiFFI with -fprefer-bytecode See #24634. - - - - - a4bb3a51 by Ben Gamari at 2024-04-12T08:18:32-04:00 base: Deprecate GHC.Pack As proposed in #21461. Closes #21540. - - - - - 55eb8c98 by Ben Gamari at 2024-04-12T08:19:08-04:00 ghc-internal: Fix mentions of ghc-internal in deprecation warnings Closes #24609. - - - - - b0fbd181 by Ben Gamari at 2024-04-12T08:19:44-04:00 rts: Implement set_initial_registers for AArch64 Fixes #23680. - - - - - 14c9ec62 by Ben Gamari at 2024-04-12T08:20:20-04:00 ghcup-metadata: Use Debian 9 binaries on Ubuntu 16, 17 Closes #24646. - - - - - 35a1621e by Ben Gamari at 2024-04-12T08:20:55-04:00 Bump unix submodule to 2.8.5.1 Closes #24640. - - - - - a1c24df0 by Finley McIlwaine at 2024-04-12T08:21:31-04:00 Correct default -funfolding-use-threshold in docs - - - - - 0255d03c by Oleg Grenrus at 2024-04-12T08:22:07-04:00 FastString is a __Modified__ UTF-8 - - - - - c3489547 by Matthew Pickering at 2024-04-12T13:13:44-04:00 rts: Improve tracing message when nursery is resized It is sometimes more useful to know how much bigger or smaller the nursery got when it is resized. In particular I am trying to investigate situations where we end up with fragmentation due to the nursery (#24577) - - - - - 5e4f4ba8 by Simon Peyton Jones at 2024-04-12T13:14:20-04:00 Don't generate wrappers for `type data` constructors with StrictData Previously, the logic for checking if a data constructor needs a wrapper or not would take into account whether the constructor's fields have explicit strictness (e.g., `data T = MkT !Int`), but the logic would _not_ take into account whether `StrictData` was enabled. This meant that something like `type data T = MkT Int` would incorrectly generate a wrapper for `MkT` if `StrictData` was enabled, leading to the horrible errors seen in #24620. To fix this, we disable generating wrappers for `type data` constructors altogether. Fixes #24620. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - dbdf1995 by Alex Mason at 2024-04-15T15:28:26+10:00 Implements MO_S_Mul2 and MO_U_Mul2 using the UMULH, UMULL and SMULH instructions for AArch64 Also adds a test for MO_S_Mul2 - - - - - 42bd0407 by Teo Camarasu at 2024-04-16T20:06:39-04:00 Make template-haskell a stage1 package Promoting template-haskell from a stage0 to a stage1 package means that we can much more easily refactor template-haskell. We implement this by duplicating the in-tree `template-haskell`. A new `template-haskell-next` library is autogenerated to mirror `template-haskell` `stage1:ghc` to depend on the new interface of the library including the `Binary` instances without adding an explicit dependency on `template-haskell`. This is controlled by the `bootstrap-th` cabal flag When building `template-haskell` modules as part of this vendoring we do not have access to quote syntax, so we cannot use variable quote notation (`'Just`). So we either replace these with hand-written `Name`s or hide the code behind CPP. We can remove the `th_hack` from hadrian, which was required when building stage0 packages using the in-tree `template-haskell` library. For more details see Note [Bootstrapping Template Haskell]. Resolves #23536 Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> Co-Authored-By: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org> - - - - - 3d973e47 by Ben Gamari at 2024-04-16T20:07:15-04:00 Bump parsec submodule to 3.1.17.0 - - - - - 9d38bfa0 by Simon Peyton Jones at 2024-04-16T20:07:51-04:00 Clone CoVars in CorePrep This MR addresses #24463. It's all explained in the new Note [Cloning CoVars and TyVars] - - - - - 0fe2b410 by Andreas Klebinger at 2024-04-16T20:08:27-04:00 NCG: Fix a bug where we errounously removed a required jump instruction. Add a new method to the Instruction class to check if we can eliminate a jump in favour of fallthrough control flow. Fixes #24507 - - - - - 9f99126a by Teo Camarasu at 2024-04-16T20:09:04-04:00 Fix documentation preview from doc-tarball job - Include all the .html files and assets in the job artefacts - Include all the .pdf files in the job artefacts - Mark the artefact as an "exposed" artefact meaning it turns up in the UI. Resolves #24651 - - - - - 3a0642ea by Ben Gamari at 2024-04-16T20:09:39-04:00 rts: Ignore EINTR while polling in timerfd itimer implementation While the RTS does attempt to mask signals, it may be that a foreign library unmasks them. This previously caused benign warnings which we now ignore. See #24610. - - - - - 9a53cd3f by Alan Zimmerman at 2024-04-16T20:10:15-04:00 EPA: Add additional comments field to AnnsModule This is used in exact printing to store comments coming after the `where` keyword but before any comments allocated to imports or decls. It is used in ghc-exactprint, see https://github.com/alanz/ghc-exactprint/commit/44bbed311fd8f0d053053fef195bf47c17d34fa7 - - - - - e5c43259 by Bryan Richter at 2024-04-16T20:10:51-04:00 Remove unrunnable FreeBSD CI jobs FreeBSD runner supply is inelastic. Currently there is only one, and it's unavailable because of a hardware issue. - - - - - 914eb49a by Ben Gamari at 2024-04-16T20:11:27-04:00 rel-eng: Fix mktemp usage in recompress-all We need a temporary directory, not a file. - - - - - f30e4984 by Teo Camarasu at 2024-04-16T20:12:03-04:00 Fix ghc API link in docs/index.html This was missing part of the unit ID meaning it would 404. Resolves #24674 - - - - - d7a3d6b5 by Ben Gamari at 2024-04-16T20:12:39-04:00 template-haskell: Declare TH.Lib.Internal as not-home Rather than `hide`. Closes #24659. - - - - - 5eaa46e7 by Matthew Pickering at 2024-04-19T02:14:55-04:00 testsuite: Rename isCross() predicate to needsTargetWrapper() isCross() was a misnamed because it assumed that all cross targets would provide a target wrapper, but the two most common cross targets (javascript, wasm) don't need a target wrapper. Therefore we rename this predicate to `needsTargetWrapper()` so situations in the testsuite where we can check whether running executables requires a target wrapper or not. - - - - - 55a9d699 by Simon Peyton Jones at 2024-04-19T02:15:32-04:00 Do not float HNFs out of lambdas This MR adjusts SetLevels so that it is less eager to float a HNF (lambda or constructor application) out of a lambda, unless it gets to top level. Data suggests that this change is a small net win: * nofib bytes-allocated falls by -0.09% (but a couple go up) * perf/should_compile bytes-allocated falls by -0.5% * perf/should_run bytes-allocated falls by -0.1% See !12410 for more detail. When fiddling elsewhere, I also found that this patch had a huge positive effect on the (very delicate) test perf/should_run/T21839r But that improvement doesn't show up in this MR by itself. Metric Decrease: MultiLayerModulesRecomp T15703 parsing001 - - - - - f0701585 by Alan Zimmerman at 2024-04-19T02:16:08-04:00 EPA: Fix comments in mkListSyntaxTy0 Also extend the test to confirm. Addresses #24669, 1 of 4 - - - - - b01c01d4 by Serge S. Gulin at 2024-04-19T02:16:51-04:00 JS: set image `x86_64-linux-deb11-emsdk-closure` for build - - - - - c90c6039 by Alan Zimmerman at 2024-04-19T02:17:27-04:00 EPA: Provide correct span for PatBind And remove unused parameter in checkPatBind Contributes to #24669 - - - - - bee54c24 by Krzysztof Gogolewski at 2024-04-19T11:13:00+02:00 Update quantification order following GHC haskell/haddock#23764 - - - - - 2814eb89 by Ben Gamari at 2024-04-19T18:57:05+02:00 hypsrc-test: Fix output of PositionPragmas.html - - - - - 26036f96 by Alan Zimmerman at 2024-04-19T13:11:08-04:00 EPA: Fix span for PatBuilderAppType Include the location of the prefix @ in the span for InVisPat. Also removes unnecessary annotations from HsTP. Contributes to #24669 - - - - - dba03aab by Matthew Craven at 2024-04-19T13:11:44-04:00 testsuite: Give the pre_cmd for mhu-perf more time - - - - - d31fbf6c by Krzysztof Gogolewski at 2024-04-19T21:04:09-04:00 Fix quantification order for a `op` b and a %m -> b Fixes #23764 Implements https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0640-tyop-quantification-order.rst Updates haddock submodule. - - - - - 385cd1c4 by Sebastian Graf at 2024-04-19T21:04:45-04:00 Make `seq#` a magic Id and inline it in CorePrep (#24124) We can save much code and explanation in Tag Inference and StgToCmm by making `seq#` a known-key Magic Id in `GHC.Internal.IO` and inline this definition in CorePrep. See the updated `Note [seq# magic]`. I also implemented a new `Note [Flatten case-bind]` to get better code for otherwise nested case scrutinees. I renamed the contructors of `ArgInfo` to use an `AI` prefix in order to resolve the clash between `type CpeApp = CoreExpr` and the data constructor of `ArgInfo`, as well as fixed typos in `Note [CorePrep invariants]`. Fixes #24252 and #24124. - - - - - 275e41a9 by Jade at 2024-04-20T11:10:40-04:00 Put the newline after errors instead of before them This mainly has consequences for GHCi but also slightly alters how the output of GHC on the commandline looks. Fixes: #22499 - - - - - dd339c7a by Teo Camarasu at 2024-04-20T11:11:16-04:00 Remove unecessary stage0 packages Historically quite a few packages had to be stage0 as they depended on `template-haskell` and that was stage0. In #23536 we made it so that was no longer the case. This allows us to remove a bunch of packages from this list. A few still remain. A new version of `Win32` is required by `semaphore-compat`. Including `Win32` in the stage0 set requires also including `filepath` because otherwise Hadrian's dependency logic gets confused. Once our boot compiler has a newer version of `Win32` all of these will be able to be dropped. Resolves #24652 - - - - - 2f8e3a25 by Alan Zimmerman at 2024-04-20T11:11:52-04:00 EPA: Avoid duplicated comments in splice decls Contributes to #24669 - - - - - c70b9ddb by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: fix typos and namings (fixes #24602) You may noted that I've also changed term of ``` , global "h$vt_double" ||= toJExpr IntV ``` See "IntV" and ``` WaitReadOp -> \[] [fd] -> pure $ PRPrimCall $ returnS (app "h$waidRead" [fd]) ``` See "h$waidRead" - - - - - 3db54f9b by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: trivial checks for variable presence (fixes #24602) - - - - - 777f108f by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: fs module imported twice (by emscripten and by ghc-internal). ghc-internal import wrapped in a closure to prevent conflict with emscripten (fixes #24602) Better solution is to use some JavaScript module system like AMD, CommonJS or even UMD. It will be investigated at other issues. At first glance we should try UMD (See https://github.com/umdjs/umd) - - - - - a45a5712 by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: thread.js requires h$fds and h$fdReady to be declared for static code analysis, minimal code copied from GHCJS (fixes #24602) I've just copied some old pieces of GHCJS from publicly available sources (See https://github.com/Taneb/shims/blob/a6dd0202dcdb86ad63201495b8b5d9763483eb35/src/io.js#L607). Also I didn't put details to h$fds. I took minimal and left only its object initialization: `var h$fds = {};` - - - - - ad90bf12 by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: heap and stack overflows reporting defined as js hard failure (fixes #24602) These errors were treated as a hard failure for browser application. The fix is trivial: just throw error. - - - - - 5962fa52 by Serge S. Gulin at 2024-04-21T16:33:44+03:00 JS: Stubs for code without actual implementation detected by Google Closure Compiler (fixes #24602) These errors were fixed just by introducing stubbed functions with throw for further implementation. - - - - - a0694298 by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Add externs to linker (fixes #24602) After enabling jsdoc and built-in google closure compiler types I was needed to deal with the following: 1. Define NodeJS-environment types. I've just copied minimal set of externs from semi-official repo (see https://github.com/externs/nodejs/blob/6c6882c73efcdceecf42e7ba11f1e3e5c9c041f0/v8/nodejs.js#L8). 2. Define Emscripten-environment types: `HEAP8`. Emscripten already provides some externs in our code but it supposed to be run in some module system. And its definitions do not work well in plain bundle. 3. We have some functions which purpose is to add to functions some contextual information via function properties. These functions should be marked as `modifies` to let google closure compiler remove calls if these functions are not used actually by call graph. Such functions are: `h$o`, `h$sti`, `h$init_closure`, `h$setObjInfo`. 4. STG primitives such as registries and stuff from `GHC.StgToJS`. `dXX` properties were already present at externs generator function but they are started from `7`, not from `1`. This message is related: `// fixme does closure compiler bite us here?` - - - - - e58bb29f by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: added both tests: for size and for correctness (fixes #24602) By some reason MacOS builds add to stderr messages like: Ignoring unexpected archive entry: __.SYMDEF ... However I left stderr to `/dev/null` for compatibility with linux CI builds. - - - - - 909f3a9c by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Disable js linker warning for empty symbol table to make js tests running consistent across environments - - - - - 83eb10da by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Add special preprocessor for js files due of needing to keep jsdoc comments (fixes #24602) Our js files have defined google closure compiler types at jsdoc entries but these jsdoc entries are removed by cpp preprocessor. I considered that reusing them in javascript-backend would be a nice thing. Right now haskell processor uses `-traditional` option to deal with comments and `//` operators. But now there are following compiler options: `-C` and `-CC`. You can read about them at GCC (see https://gcc.gnu.org/onlinedocs/gcc/Preprocessor-Options.html#index-CC) and CLang (see https://clang.llvm.org/docs/ClangCommandLineReference.html#cmdoption-clang-CC). It seems that `-CC` works better for javascript jsdoc than `-traditional`. At least it leaves `/* ... */` comments w/o changes. - - - - - e1cf8dc2 by brandon s allbery kf8nh at 2024-04-22T03:48:26-04:00 fix link in CODEOWNERS It seems that our local Gitlab no longer has documentation for the `CODEOWNERS` file, but the master documentation still does. Use that instead. - - - - - a27c6a49 by Fendor at 2024-04-22T10:13:03+02:00 Adapt to UserData split - - - - - 1efc5a7a by Fendor at 2024-04-22T10:13:03+02:00 Adapt to BinHandle split - - - - - 593f4e04 by Fendor at 2024-04-23T10:19:14-04:00 Add performance regression test for '-fwrite-simplified-core' - - - - - 1ba39b05 by Fendor at 2024-04-23T10:19:14-04:00 Typecheck corebindings lazily during bytecode generation This delays typechecking the corebindings until the bytecode generation happens. We also avoid allocating a thunk that is retained by `unsafeInterleaveIO`. In general, we shouldn't retain values of the hydrated `Type`, as not evaluating the bytecode object keeps it alive. It is better if we retain the unhydrated `IfaceType`. See Note [Hydrating Modules] - - - - - e916fc92 by Alan Zimmerman at 2024-04-23T10:19:50-04:00 EPA: Keep comments in a CaseAlt match The comments now live in the surrounding location, not inside the Match. Make sure we keep them. Closes #24707 - - - - - d2b17f32 by Cheng Shao at 2024-04-23T15:01:22-04:00 driver: force merge objects when building dynamic objects This patch forces the driver to always merge objects when building dynamic objects even when ar -L is supported. It is an oversight of !8887: original rationale of that patch is favoring the relatively cheap ar -L operation over object merging when ar -L is supported, which makes sense but only if we are building static objects! Omitting check for whether we are building dynamic objects will result in broken .so files with undefined reference errors at executable link time when building GHC with llvm-ar. Fixes #22210. - - - - - 209d09f5 by Julian Ospald at 2024-04-23T15:02:03-04:00 Allow non-absolute values for bootstrap GHC variable Fixes #24682 - - - - - 3fff0977 by Matthew Pickering at 2024-04-23T15:02:38-04:00 Don't depend on registerPackage function in Cabal More recent versions of Cabal modify the behaviour of libAbiHash which breaks our usage of registerPackage. It is simpler to inline the part of registerPackage that we need and avoid any additional dependency and complication using the higher-level function introduces. - - - - - c62dc317 by Cheng Shao at 2024-04-25T01:32:02-04:00 ghc-bignum: remove obsolete ln script This commit removes an obsolete ln script in ghc-bignum/gmp. See 060251c24ad160264ae8553efecbb8bed2f06360 for its original intention, but it's been obsolete for a long time, especially since the removal of the make build system. Hence the house cleaning. - - - - - 6399d52b by Cheng Shao at 2024-04-25T01:32:02-04:00 ghc-bignum: update gmp to 6.3.0 This patch bumps the gmp-tarballs submodule and updates gmp to 6.3.0. The tarball format is now xz, and gmpsrc.patch has been patched into the tarball so hadrian no longer needs to deal with patching logic when building in-tree GMP. - - - - - 65b4b92f by Cheng Shao at 2024-04-25T01:32:02-04:00 hadrian: remove obsolete Patch logic This commit removes obsolete Patch logic from hadrian, given we no longer need to patch the gmp tarball when building in-tree GMP. - - - - - 71f28958 by Cheng Shao at 2024-04-25T01:32:02-04:00 autoconf: remove obsolete patch detection This commit removes obsolete deletection logic of the patch command from autoconf scripts, given we no longer need to patch anything in the GHC build process. - - - - - daeda834 by Sylvain Henry at 2024-04-25T01:32:43-04:00 JS: correctly handle RUBBISH literals (#24664) - - - - - 8a06ddf6 by Matthew Pickering at 2024-04-25T11:16:16-04:00 Linearise ghc-internal and base build This is achieved by requesting the final package database for ghc-internal, which mandates it is fully built as a dependency of configuring the `base` package. This is at the expense of cross-package parrallelism between ghc-internal and the base package. Fixes #24436 - - - - - 94da9365 by Andrei Borzenkov at 2024-04-25T11:16:54-04:00 Fix tuple puns renaming (24702) Move tuple renaming short cutter from `isBuiltInOcc_maybe` to `isPunOcc_maybe`, so we consider incoming module. I also fixed some hidden bugs that raised after the change was done. - - - - - fa03b1fb by Fendor at 2024-04-26T18:03:13-04:00 Refactor the Binary serialisation interface The goal is simplifiy adding deduplication tables to `ModIface` interface serialisation. We identify two main points of interest that make this difficult: 1. UserData hardcodes what `Binary` instances can have deduplication tables. Moreover, it heavily uses partial functions. 2. GHC.Iface.Binary hardcodes the deduplication tables for 'Name' and 'FastString', making it difficult to add more deduplication. Instead of having a single `UserData` record with fields for all the types that can have deduplication tables, we allow to provide custom serialisers for any `Typeable`. These are wrapped in existentials and stored in a `Map` indexed by their respective `TypeRep`. The `Binary` instance of the type to deduplicate still needs to explicitly look up the decoder via `findUserDataReader` and `findUserDataWriter`, which is no worse than the status-quo. `Map` was chosen as microbenchmarks indicate it is the fastest for a small number of keys (< 10). To generalise the deduplication table serialisation mechanism, we introduce the types `ReaderTable` and `WriterTable` which provide a simple interface that is sufficient to implement a general purpose deduplication mechanism for `writeBinIface` and `readBinIface`. This allows us to provide a list of deduplication tables for serialisation that can be extended more easily, for example for `IfaceTyCon`, see the issue https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for more motivation. In addition to this refactoring, we split `UserData` into `ReaderUserData` and `WriterUserData`, to avoid partial functions and reduce overall memory usage, as we need fewer mutable variables. Bump haddock submodule to accomodate for `UserData` split. ------------------------- Metric Increase: MultiLayerModulesTH_Make MultiLayerModulesRecomp T21839c ------------------------- - - - - - bac57298 by Fendor at 2024-04-26T18:03:13-04:00 Split `BinHandle` into `ReadBinHandle` and `WriteBinHandle` A `BinHandle` contains too much information for reading data. For example, it needs to keep a `FastMutInt` and a `IORef BinData`, when the non-mutable variants would suffice. Additionally, this change has the benefit that anyone can immediately tell whether the `BinHandle` is used for reading or writing. Bump haddock submodule BinHandle split. - - - - - 4d6394dd by Simon Peyton Jones at 2024-04-26T18:03:49-04:00 Fix missing escaping-kind check in tcPatSynSig Note [Escaping kind in type signatures] explains how we deal with escaping kinds in type signatures, e.g. f :: forall r (a :: TYPE r). a where the kind of the body is (TYPE r), but `r` is not in scope outside the forall-type. I had missed this subtlety in tcPatSynSig, leading to #24686. This MR fixes it; and a similar bug in tc_top_lhs_type. (The latter is tested by T24686a.) - - - - - 981c2c2c by Alan Zimmerman at 2024-04-26T18:04:25-04:00 EPA: check-exact: check that the roundtrip reproduces the source Closes #24670 - - - - - a8616747 by Andrew Lelechenko at 2024-04-26T18:05:01-04:00 Document that setEnv is not thread-safe - - - - - 1e41de83 by Bryan Richter at 2024-04-26T18:05:37-04:00 CI: Work around frequent Signal 9 errors - - - - - a6d5f9da by Naïm Favier at 2024-04-27T17:52:40-04:00 ghc-internal: add MonadFix instance for (,) Closes https://gitlab.haskell.org/ghc/ghc/-/issues/24288, implements CLC proposal https://github.com/haskell/core-libraries-committee/issues/238. Adds a MonadFix instance for tuples, permitting value recursion in the "native" writer monad and bringing consistency with the existing instance for transformers's WriterT (and, to a lesser extent, for Solo). - - - - - 64feadcd by Rodrigo Mesquita at 2024-04-27T17:53:16-04:00 bindist: Fix xattr cleaning The original fix (725343aa) was incorrect because it used the shell bracket syntax which is the quoting syntax in autoconf, making the test for existence be incorrect and therefore `xattr` was never run. Fixes #24554 - - - - - e2094df3 by damhiya at 2024-04-28T23:52:00+09:00 Make read accepts binary integer formats CLC proposal : https://github.com/haskell/core-libraries-committee/issues/177 - - - - - c62239b7 by Sylvain Henry at 2024-04-29T10:35:00+02:00 Fix tests for T22229 - - - - - 1c2fd963 by Alan Zimmerman at 2024-04-29T23:17:00-04:00 EPA: Preserve comments in Match Pats Closes #24708 Closes #24715 Closes #24734 - - - - - 4189d17e by Sylvain Henry at 2024-04-29T23:17:42-04:00 LLVM: better unreachable default destination in Switch (#24717) See added note. Co-authored-by: Siddharth Bhat <siddu.druid at gmail.com> - - - - - a3725c88 by Cheng Shao at 2024-04-29T23:18:20-04:00 ci: enable wasm jobs for MRs with wasm label This patch enables wasm jobs for MRs with wasm label. Previously the wasm label didn't actually have any effect on the CI pipeline, and full-ci needed to be applied to run wasm jobs which was a waste of runners when working on the wasm backend, hence the fix here. - - - - - 702f7964 by Matthew Pickering at 2024-04-29T23:18:56-04:00 Make interface files and object files depend on inplace .conf file A potential fix for #24737 - - - - - 728af21e by Cheng Shao at 2024-04-30T05:30:23-04:00 utils: remove obsolete vagrant scripts Vagrantfile has long been removed in !5288. This commit further removes the obsolete vagrant scripts in the tree. - - - - - 36f2c342 by Cheng Shao at 2024-04-30T05:31:00-04:00 Update autoconf scripts Scripts taken from autoconf 948ae97ca5703224bd3eada06b7a69f40dd15a02 - - - - - ecbf22a6 by Ben Gamari at 2024-04-30T05:31:36-04:00 ghcup-metadata: Drop output_name field This is entirely redundant to the filename of the URL. There is no compelling reason to name the downloaded file differently from its source. - - - - - c56d728e by Zubin Duggal at 2024-04-30T22:45:09-04:00 testsuite: Handle exceptions in framework_fail when testdir is not initialised When `framework_fail` is called before initialising testdir, it would fail with an exception reporting the testdir not being initialised instead of the actual failure. Ensure we report the actual reason for the failure instead of failing in this way. One way this can manifest is when trying to run a test that doesn't exist using `--only` - - - - - d5bea4d6 by Alan Zimmerman at 2024-04-30T22:45:45-04:00 EPA: Fix range for GADT decl with sig only Closes #24714 - - - - - 4d78c53c by Sylvain Henry at 2024-05-01T17:23:06-04:00 Fix TH dependencies (#22229) Add a dependency between Syntax and Internal (via module reexport). - - - - - 37e38db4 by Sylvain Henry at 2024-05-01T17:23:06-04:00 Bump haddock submodule - - - - - ca13075c by Sylvain Henry at 2024-05-01T17:23:47-04:00 JS: cleanup to prepare for #24743 - - - - - 40026ac3 by Alan Zimmerman at 2024-05-01T22:45:07-04:00 EPA: Preserve comments for PrefixCon Preserve comments in fun (Con {- c1 -} a b) = undefined Closes #24736 - - - - - 92134789 by Hécate Moonlight at 2024-05-01T22:45:42-04:00 Correct `@since` metadata in HpcFlags It was introduced in base-4.20, not 4.22. Fix #24721 - - - - - a580722e by Cheng Shao at 2024-05-02T08:18:45-04:00 testsuite: fix req_target_smp predicate - - - - - ac9c5f84 by Andreas Klebinger at 2024-05-02T08:18:45-04:00 STM: Remove (unused)coarse grained locking. The STM code had a coarse grained locking mode guarded by #defines that was unused. This commit removes the code. - - - - - 917ef81b by Andreas Klebinger at 2024-05-02T08:18:45-04:00 STM: Be more optimistic when validating in-flight transactions. * Don't lock tvars when performing non-committal validation. * If we encounter a locked tvar don't consider it a failure. This means in-flight validation will only fail if committing at the moment of validation is *guaranteed* to fail. This prevents in-flight validation from failing spuriously if it happens in parallel on multiple threads or parallel to thread comitting. - - - - - 167a56a0 by Alan Zimmerman at 2024-05-02T08:19:22-04:00 EPA: fix span for empty \case(s) In instance SDecide Nat where SZero %~ (SSucc _) = Disproved (\case) Ensure the span for the HsLam covers the full construct. Closes #24748 - - - - - 9bae34d8 by doyougnu at 2024-05-02T15:41:08-04:00 testsuite: expand size testing infrastructure - closes #24191 - adds windows_skip, wasm_skip, wasm_arch, find_so, _find_so - path_from_ghcPkg, collect_size_ghc_pkg, collect_object_size, find_non_inplace functions to testsuite - adds on_windows and req_dynamic_ghc predicate to testsuite The design is to not make the testsuite too smart and simply offload to ghc-pkg for locations of object files and directories. - - - - - b85b1199 by Sylvain Henry at 2024-05-02T15:41:49-04:00 GHCi: support inlining breakpoints (#24712) When a breakpoint is inlined, its context may change (e.g. tyvars in scope). We must take this into account and not used the breakpoint tick index as its sole identifier. Each instance of a breakpoint (even with the same tick index) now gets a different "info" index. We also need to distinguish modules: - tick module: module with the break array (tick counters, status, etc.) - info module: module having the CgBreakInfo (info at occurrence site) - - - - - 649c24b9 by Oleg Grenrus at 2024-05-03T20:45:42-04:00 Expose constructors of SNat, SChar and SSymbol in ghc-internal - - - - - d603f199 by Mikolaj Konarski at 2024-05-03T20:46:19-04:00 Add DCoVarSet to PluginProv (!12037) - - - - - ba480026 by Serge S. Gulin at 2024-05-03T20:47:01-04:00 JS: Enable more efficient packing of string data (fixes #24706) - - - - - be1e60ee by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Track in-scope variables in ruleCheckProgram This small patch fixes #24726, by tracking in-scope variables properly in -drule-check. Not hard to do! - - - - - 58408c77 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Add a couple more HasCallStack constraints in SimpleOpt Just for debugging, no effect on normal code - - - - - 70e245e8 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Add comments to Prep.hs This documentation patch fixes a TODO left over from !12364 - - - - - e5687186 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Use HasDebugCallStack, rather than HasCallStack - - - - - 631cefec by Cheng Shao at 2024-05-03T20:48:17-04:00 driver: always merge objects when possible This patch makes the driver always merge objects with `ld -r` when possible, and only fall back to calling `ar -L` when merge objects command is unavailable. This completely reverts !8887 and !12313, given more fixes in Cabal seems to be needed to avoid breaking certain configurations and the maintainence cost is exceeding the behefits in this case :/ - - - - - 1dacb506 by Ben Gamari at 2024-05-03T20:48:53-04:00 Bump time submodule to 1.14 As requested in #24528. ------------------------- Metric Decrease: ghc_bignum_so rts_so Metric Increase: cabal_syntax_dir rts_so time_dir time_so ------------------------- - - - - - 4941b90e by Ben Gamari at 2024-05-03T20:48:53-04:00 Bump terminfo submodule to current master - - - - - 43d48b44 by Cheng Shao at 2024-05-03T20:49:30-04:00 wasm: use scheduler.postTask() for context switch when available This patch makes use of scheduler.postTask() for JSFFI context switch when it's available. It's a more principled approach than our MessageChannel based setImmediate() implementation, and it's available in latest version of Chromium based browsers. - - - - - 08207501 by Cheng Shao at 2024-05-03T20:50:08-04:00 testsuite: give pre_cmd for mhu-perf 5x time - - - - - bf3d4db0 by Alan Zimmerman at 2024-05-03T20:50:43-04:00 EPA: Preserve comments for pattern synonym sig Closes #24749 - - - - - c49493f2 by Matthew Pickering at 2024-05-04T06:02:57-04:00 tests: Widen acceptance window for dir and so size tests These are testing things which are sometimes out the control of a GHC developer. Therefore we shouldn't fail CI if something about these dependencies change because we can't do anything about it. It is still useful to have these statistics for visualisation in grafana though. Ticket #24759 - - - - - 9562808d by Matthew Pickering at 2024-05-04T06:02:57-04:00 Disable rts_so test It has already manifested large fluctuations and destabilising CI Fixes #24762 - - - - - fc24c5cf by Ryan Scott at 2024-05-04T06:03:33-04:00 unboxedSum{Type,Data}Name: Use GHC.Types as the module Unboxed sum constructors are now defined in the `GHC.Types` module, so if you manually quote an unboxed sum (e.g., `''Sum2#`), you will get a `Name` like: ```hs GHC.Types.Sum2# ``` The `unboxedSumTypeName` function in `template-haskell`, however, mistakenly believes that unboxed sum constructors are defined in `GHC.Prim`, so `unboxedSumTypeName 2` would return an entirely different `Name`: ```hs GHC.Prim.(#|#) ``` This is a problem for Template Haskell users, as it means that they can't be sure which `Name` is the correct one. (Similarly for `unboxedSumDataName`.) This patch fixes the implementations of `unboxedSum{Type,Data}Name` to use `GHC.Types` as the module. For consistency with `unboxedTupleTypeName`, the `unboxedSumTypeName` function now uses the non-punned syntax for unboxed sums (`Sum<N>#`) as the `OccName`. Fixes #24750. - - - - - 7eab4e01 by Alan Zimmerman at 2024-05-04T16:14:55+01:00 EPA: Widen stmtslist to include last semicolon Closes #24754 - - - - - 06f7db40 by Teo Camarasu at 2024-05-05T00:19:38-04:00 doc: Fix type error in hs_try_putmvar example - - - - - af000532 by Moritz Schuler at 2024-05-05T06:30:58-04:00 Fix parsing of module names in CLI arguments closes issue #24732 - - - - - da74e9c9 by Ben Gamari at 2024-05-05T06:31:34-04:00 ghc-platform: Add Setup.hs The Hadrian bootstrapping script relies upon `Setup.hs` to drive its build. Addresses #24761. - - - - - 35d34fde by Alan Zimmerman at 2024-05-05T12:52:40-04:00 EPA: preserve comments in class and data decls Fix checkTyClHdr which was discarding comments. Closes #24755 - - - - - 03c5dfbf by Simon Peyton Jones at 2024-05-05T12:53:15-04:00 Fix a float-out error Ticket #24768 showed that the Simplifier was accidentally destroying a join point. It turned out to be that we were sending a bottoming join point to the top, accidentally abstracting over /other/ join points. Easily fixed. - - - - - adba68e7 by John Ericson at 2024-05-05T19:35:56-04:00 Substitute bindist files with Hadrian not configure The `ghc-toolchain` overhaul will eventually replace all this stuff with something much more cleaned up, but I think it is still worth making this sort of cleanup in the meantime so other untanglings and dead code cleaning can procede. I was able to delete a fair amount of dead code doing this too. `LLVMTarget_CPP` is renamed to / merged with `LLVMTarget` because it wasn't actually turned into a valid CPP identifier. (Original to 1345c7cc42c45e63ab1726a8fd24a7e4d4222467, actually.) Progress on #23966 Co-Authored-By: Sylvain Henry <hsyl20 at gmail.com> - - - - - 18f4ff84 by Alan Zimmerman at 2024-05-05T19:36:32-04:00 EPA: fix mkHsOpTyPV duplicating comments Closes #24753 - - - - - a19201d4 by Matthew Craven at 2024-05-06T19:54:29-04:00 Add test cases for #24664 ...since none are present in the original MR !12463 fixing this issue. - - - - - 46328a49 by Alan Zimmerman at 2024-05-06T19:55:05-04:00 EPA: preserve comments in data decls Closes #24771 - - - - - 3b51995c by Andrei Borzenkov at 2024-05-07T14:39:40-04:00 Rename Solo# data constructor to MkSolo# (#24673) - data Solo# a = (# a #) + data Solo# a = MkSolo# a And `(# foo #)` syntax now becomes just a syntactic sugar for `MkSolo# a`. - - - - - 4d59abf2 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Add the cmm_cpp_is_gcc predicate to the testsuite A future C-- test called T24474-cmm-override-g0 relies on the GCC-specific behaviour of -g3 implying -dD, which, in turn, leads to it emitting #defines past the preprocessing stage. Clang, at least, does not do this, so the test would fail if ran on Clang. As the behaviour here being tested is ``-optCmmP-g3'' undoing effects of the workaround we apply as a fix for bug #24474, and the workaround was for GCC-specific behaviour, the test needs to be marked as fragile on other compilers. - - - - - 25b0b404 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Split out the C-- preprocessor, and make it pass -g0 Previously, C-- was processed with the C preprocessor program. This means that it inherited flags passed via -optc. A flag that is somewhat often passed through -optc is -g. At certain -g levels (>=2), GCC starts emitting defines *after* preprocessing, for the purposes of debug info generation. This is not useful for the C-- compiler, and, in fact, causes lexer errors. We can suppress this effect (safely, if supported) via -g0. As a workaround, in older versions of GCC (<=10), GCC only emitted defines if a certain set of -g*3 flags was passed. Newer versions check the debug level. For the former, we filter out those -g*3 flags and, for the latter, we specify -g0 on top of that. As a compatible and effective solution, this change adds a C-- preprocessor distinct from the C compiler and preprocessor, but that keeps its flags. The command line produced for C-- preprocessing now looks like: $pgmCmmP $optCs_without_g3 $g0_if_supported $optCmmP Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/24474 - - - - - 9b4129a5 by Andreas Klebinger at 2024-05-08T13:24:20-04:00 -fprof-late: Only insert cost centres on functions/non-workfree cafs. They are usually useless and doing so for data values comes with a large compile time/code size overhead. Fixes #24103 - - - - - 259b63d3 by Sebastian Graf at 2024-05-08T13:24:57-04:00 Simplifier: Preserve OccInfo on DataAlt fields when case binder is dead (#24770) See the adjusted `Note [DataAlt occ info]`. This change also has a positive repercussion on `Note [Combine case alts: awkward corner]`. Fixes #24770. We now try not to call `dataConRepStrictness` in `adjustFieldsIdInfo` when all fields are lazy anyway, leading to a 2% ghc/alloc decrease in T9675. Metric Decrease: T9675 - - - - - 31b28cdb by Sebastian Graf at 2024-05-08T13:24:57-04:00 Kill seqRule, discard dead seq# in Prep (#24334) Discarding seq#s in Core land via `seqRule` was problematic; see #24334. So instead we discard certain dead, discardable seq#s in Prep now. See the updated `Note [seq# magic]`. This fixes the symptoms of #24334. - - - - - b2682534 by Rodrigo Mesquita at 2024-05-10T01:47:51-04:00 Document NcgImpl methods Fixes #19914 - - - - - 4d3acbcf by Zejun Wu at 2024-05-10T01:48:28-04:00 Make renamer to be more flexible with parens in the LHS of the rules We used to reject LHS like `(f a) b` in RULES and requires it to be written as `f a b`. It will be handy to allow both as the expression may be more readable with extra parens in some cases when infix operator is involved. Espceially when TemplateHaskell is used, extra parens may be added out of user's control and result in "valid" rules being rejected and there are not always ways to workaround it. Fixes #24621 - - - - - ab840ce6 by Ben Gamari at 2024-05-10T01:49:04-04:00 IPE: Eliminate dependency on Read Instead of encoding the closure type as decimal string we now simply represent it as an integer, eliminating the need for `Read` in `GHC.Internal.InfoProv.Types.peekInfoProv`. Closes #24504. ------------------------- Metric Decrease: T24602_perf_size size_hello_artifact ------------------------- - - - - - a9979f55 by Cheng Shao at 2024-05-10T01:49:43-04:00 testsuite: fix testwsdeque with recent clang This patch fixes compilation of testwsdeque.c with recent versions of clang, which will fail with the error below: ``` testwsdeque.c:95:33: error: warning: format specifies type 'long' but the argument has type 'void *' [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~~ ^ testwsdeque.c:95:39: error: warning: format specifies type 'int' but the argument has type 'StgWord' (aka 'unsigned long') [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~ ^~~ | %lu testwsdeque.c:133:42: error: error: incompatible function pointer types passing 'void (void *)' to parameter of type 'OSThreadProc *' (aka 'void *(*)(void *)') [-Wincompatible-function-pointer-types] 133 | createOSThread(&ids[n], "thief", thief, (void*)(StgWord)n); | ^~~~~ /workspace/ghc/_build/stage1/lib/../lib/x86_64-linux-ghc-9.11.20240502/rts-1.0.2/include/rts/OSThreads.h:193:51: error: note: passing argument to parameter 'startProc' here 193 | OSThreadProc *startProc, void *param); | ^ 2 warnings and 1 error generated. ``` - - - - - c2b33fc9 by Rodrigo Mesquita at 2024-05-10T01:50:20-04:00 Rename pre-processor invocation args Small clean up. Uses proper names for the various groups of arguments that make up the pre-processor invocation. - - - - - 2b1af08b by Cheng Shao at 2024-05-10T01:50:55-04:00 ghc-heap: fix typo in ghc-heap cbits - - - - - fc2d6de1 by Jade at 2024-05-10T21:07:16-04:00 Improve performance of Data.List.sort(By) This patch improves the algorithm to sort lists in base. It does so using two strategies: 1) Use a four-way-merge instead of the 'default' two-way-merge. This is able to save comparisons and allocations. 2) Use `(>) a b` over `compare a b == GT` and allow inlining and specialization. This mainly benefits types with a fast (>). Note that this *may* break instances with a *malformed* Ord instance where `a > b` is *not* equal to `compare a b == GT`. CLC proposal: https://github.com/haskell/core-libraries-committee/issues/236 Fixes #24280 ------------------------- Metric Decrease: MultiLayerModulesTH_Make T10421 T13719 T15164 T18698a T18698b T1969 T9872a T9961 T18730 WWRec T12425 T15703 ------------------------- - - - - - 1012e8aa by Matthew Pickering at 2024-05-10T21:07:52-04:00 Revert "ghcup-metadata: Drop output_name field" This reverts commit ecbf22a6ac397a791204590f94c0afa82e29e79f. This breaks the ghcup metadata generation on the nightly jobs. - - - - - daff1e30 by Jannis at 2024-05-12T13:38:35-04:00 Division by constants optimization - - - - - 413217ba by Andreas Klebinger at 2024-05-12T13:39:11-04:00 Tidy: Add flag to expose unfoldings if they take dictionary arguments. Add the flag `-fexpose-overloaded-unfoldings` to be able to control this behaviour. For ghc's boot libraries file size grew by less than 1% when it was enabled. However I refrained from enabling it by default for now. I've also added a section on specialization more broadly to the users guide. ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot Metric Increase: T12425 T13386 hard_hole_fits ------------------------- - - - - - c5d89412 by Zubin Duggal at 2024-05-13T22:19:53-04:00 Don't store a GlobalRdrEnv in `mi_globals` for GHCi. GHCi only needs the `mi_globals` field for modules imported with :module +*SomeModule. It uses this field to make the top level environment in `SomeModule` available to the repl. By default, only the first target in the command line parameters is "star" loaded into GHCi. Other modules have to be manually "star" loaded into the repl. Storing the top level GlobalRdrEnv for each module is very wasteful, especially given that we will most likely never need most of these environments. Instead we store only the information needed to reconstruct the top level environment in a module, which is the `IfaceTopEnv` data structure, consisting of all import statements as well as all top level symbols defined in the module (not taking export lists into account) When a particular module is "star-loaded" into GHCi (as the first commandline target, or via an explicit `:module +*SomeModule`, we reconstruct the top level environment on demand using the `IfaceTopEnv`. - - - - - d65bf4a2 by Fendor at 2024-05-13T22:20:30-04:00 Add perf regression test for `-fwrite-if-simplified-core` - - - - - 2c0f8ddb by Andrei Borzenkov at 2024-05-13T22:21:07-04:00 Improve pattern to type pattern transformation (23739) `pat_to_type_pat` function now can handle more patterns: - TuplePat - ListPat - LitPat - NPat - ConPat Allowing these new constructors in type patterns significantly increases possible shapes of type patterns without `type` keyword. This patch also changes how lookups in `lookupOccRnConstr` are performed, because we need to fall back into types when we didn't find a constructor on data level to perform `ConPat` to type transformation properly. - - - - - be514bb4 by Cheng Shao at 2024-05-13T22:21:43-04:00 hadrian: fix hadrian building with ghc-9.10.1 - - - - - ad38e954 by Cheng Shao at 2024-05-13T22:21:43-04:00 linters: fix lint-whitespace compilation with ghc-9.10.1 - - - - - a593f284 by Andreas Klebinger at 2024-05-15T07:32:10-04:00 Expand the `inline` rule to look through casts/ticks. Fixes #24808 - - - - - b1e0c313 by Cheng Shao at 2024-05-15T07:32:46-04:00 testsuite: bump PartialDownSweep timeout to 5x on wasm32 - - - - - b2227487 by Fendor at 2024-05-15T17:14:06-04:00 Add Eq and Ord instance to `IfaceType` We add an `Ord` instance so that we can store `IfaceType` in a `Data.Map` container. This is required to deduplicate `IfaceType` while writing `.hi` files to disk. Deduplication has many beneficial consequences to both file size and memory usage, as the deduplication enables implicit sharing of values. See issue #24540 for more motivation. The `Ord` instance would be unnecessary if we used a `TrieMap` instead of `Data.Map` for the deduplication process. While in theory this is clerarly the better option, experiments on the agda code base showed that a `TrieMap` implementation has worse run-time performance characteristics. To the change itself, we mostly derive `Eq` and `Ord`. This requires us to change occurrences of `FastString` with `LexicalFastString`, since `FastString` has no `Ord` instance. We change the definition of `IfLclName` to a newtype of `LexicalFastString`, to make such changes in the future easier. Bump haddock submodule for IfLclName changes - - - - - d368f9a6 by Fendor at 2024-05-15T17:14:06-04:00 Move out LiteralMap to avoid cyclic module dependencies - - - - - 2fcc09fd by Fendor at 2024-05-15T17:14:06-04:00 Add deduplication table for `IfaceType` The type `IfaceType` is a highly redundant, tree-like data structure. While benchmarking, we realised that the high redundancy of `IfaceType` causes high memory consumption in GHCi sessions when byte code is embedded into the `.hi` file via `-fwrite-if-simplified-core` or `-fbyte-code-and-object-code`. Loading such `.hi` files from disk introduces many duplicates of memory expensive values in `IfaceType`, such as `IfaceTyCon`, `IfaceTyConApp`, `IA_Arg` and many more. We improve the memory behaviour of GHCi by adding an additional deduplication table for `IfaceType` to the serialisation of `ModIface`, similar to how we deduplicate `Name`s and `FastString`s. When reading the interface file back, the table allows us to automatically share identical values of `IfaceType`. To provide some numbers, we evaluated this patch on the agda code base. We loaded the full library from the `.hi` files, which contained the embedded core expressions (`-fwrite-if-simplified-core`). Before this patch: * Load time: 11.7 s, 2.5 GB maximum residency. After this patch: * Load time: 7.3 s, 1.7 GB maximum residency. This deduplication has the beneficial side effect to additionally reduce the size of the on-disk interface files tremendously. For example, on agda, we reduce the size of `.hi` files (with `-fwrite-if-simplified-core`): * Before: 101 MB on disk * Now: 24 MB on disk This has even a beneficial side effect on the cabal store. We reduce the size of the store on disk: * Before: 341 MB on disk * Now: 310 MB on disk Note, none of the dependencies have been compiled with `-fwrite-if-simplified-core`, but `IfaceType` occurs in multiple locations in a `ModIface`. We also add IfaceType deduplication table to .hie serialisation and refactor .hie file serialisation to use the same infrastrucutre as `putWithTables`. Bump haddock submodule to accomodate for changes to the deduplication table layout and binary interface. - - - - - 36aa7cf1 by Fendor at 2024-05-15T17:14:06-04:00 Add run-time configurability of `.hi` file compression Introduce the flag `-fwrite-if-compression=<n>` which allows to configure the compression level of writing .hi files. The motivation is that some deduplication operations are too expensive for the average use case. Hence, we introduce multiple compression levels with variable impact on performance, but still reduce the memory residency and `.hi` file size on disk considerably. We introduce three compression levels: * `1`: `Normal` mode. This is the least amount of compression. It deduplicates only `Name` and `FastString`s, and is naturally the fastest compression mode. * `2`: `Safe` mode. It has a noticeable impact on .hi file size and is marginally slower than `Normal` mode. In general, it should be safe to always use `Safe` mode. * `3`: `Full` deduplication mode. Deduplicate as much as we can, resulting in minimal .hi files, but at the cost of additional compilation time. Reading .hi files doesn't need to know the initial compression level, and can always deserialise a `ModIface`, as we write out a byte that indicates the next value has been deduplicated. This allows users to experiment with different compression levels for packages, without recompilation of dependencies. Note, the deduplication also has an additional side effect of reduced memory consumption to implicit sharing of deduplicated elements. See https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for example where that matters. ------------------------- Metric Decrease: MultiLayerModulesDefsGhciWithCore T16875 T21839c T24471 hard_hole_fits libdir ------------------------- - - - - - 1e63a6fb by Matthew Pickering at 2024-05-15T17:14:07-04:00 Introduce regression tests for `.hi` file sizes Add regression tests to track how `-fwrite-if-compression` levels affect the size of `.hi` files. - - - - - 639d742b by M Farkas-Dyck at 2024-05-15T17:14:49-04:00 TTG: ApplicativeStatement exist only in Rn and Tc Co-Authored-By: romes <rodrigo.m.mesquita at gmail.com> - - - - - aa7b336b by Jade at 2024-05-15T23:06:17-04:00 Documentation: Improve documentation for symbols exported from System.IO - - - - - c561de8f by Jade at 2024-05-15T23:06:54-04:00 Improve suggestions for language extensions - When suggesting Language extensions, also suggest Extensions which imply them - Suggest ExplicitForAll and GADTSyntax instead of more specific extensions - Rephrase suggestion to include the term 'Extension' - Also moves some flag specific definitions out of Session.hs into Flags.hs (#24478) Fixes: #24477 Fixes: #24448 Fixes: #10893 - - - - - 4c7ae2a1 by Andreas Klebinger at 2024-05-15T23:07:30-04:00 Testsuite: Check if llvm assembler is available for have_llvm - - - - - bc672166 by Torsten Schmits at 2024-05-15T23:08:06-04:00 refactor quadratic search in warnMissingHomeModules - - - - - 7875e8cb by Torsten Schmits at 2024-05-15T23:08:06-04:00 add test that runs MakeDepend on thousands of modules - - - - - b84b91f5 by Adam Gundry at 2024-05-16T15:32:06-04:00 Representation-polymorphic HasField (fixes #22156) This generalises the HasField class to support representation polymorphism, so that instead of type HasField :: forall {k} . k -> Type -> Type -> Constraint we have type HasField :: forall {k} {r_rep} {a_rep} . k -> TYPE r_rep -> TYPE a_rep -> Constraint - - - - - 05285090 by Matthew Pickering at 2024-05-16T15:32:43-04:00 Bump os-string submodule to 2.0.2.2 Closes #24786 - - - - - 886ab43a by Cheng Shao at 2024-05-17T01:34:50-04:00 rts: do not prefetch mark_closure bdescr in non-moving gc when ASSERTS_ENABLED This commit fixes a small an oversight in !12148: the prefetch logic in non-moving GC may trap in debug RTS because it calls Bdescr() for mark_closure which may be a static one. It's fine in non-debug RTS because even invalid bdescr addresses are prefetched, they will not cause segfaults, so this commit implements the most straightforward fix: don't prefetch mark_closure bdescr when assertions are enabled. - - - - - b38dcf39 by Teo Camarasu at 2024-05-17T01:34:50-04:00 rts: Allocate non-moving segments with megablocks Non-moving segments are 8 blocks long and need to be aligned. Previously we serviced allocations by grabbing 15 blocks, finding an aligned 8 block group in it and returning the rest. This proved to lead to high levels of fragmentation as a de-allocating a segment caused an 8 block gap to form, and this could not be reused for allocation. This patch introduces a segment allocator based around using entire megablocks to service segment allocations in bulk. When there are no free segments, we grab an entire megablock and fill it with aligned segments. As the megablock is free, we can easily guarantee alignment. Any unused segments are placed on a free list. It only makes sense to free segments in bulk when all of the segments in a megablock are freeable. After sweeping, we grab the free list, sort it, and find all groups of segments where they cover the megablock and free them. This introduces a period of time when free segments are not available to the mutator, but the risk that this would lead to excessive allocation is low. Right after sweep, we should have an abundance of partially full segments, and this pruning step is relatively quick. In implementing this we drop the logic that kept NONMOVING_MAX_FREE segments on the free list. We also introduce an eventlog event to log the amount of pruned/retained free segments. See Note [Segment allocation strategy] Resolves #24150 ------------------------- Metric Decrease: T13253 T19695 ------------------------- - - - - - 710665bd by Cheng Shao at 2024-05-17T01:35:30-04:00 rts: fix I/O manager compilation errors for win32 target This patch fixes I/O manager compilation errors for win32 target discovered when cross-compiling to win32 using recent clang: ``` rts/win32/ThrIOManager.c:117:7: error: error: call to undeclared function 'is_io_mng_native_p'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 117 | if (is_io_mng_native_p ()) { | ^ | 117 | if (is_io_mng_native_p ()) { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/fs.c:143:28: error: error: a function declaration without a prototype is deprecated in all versions of C [-Werror,-Wstrict-prototypes] 143 | int setErrNoFromWin32Error () { | ^ | void | 143 | int setErrNoFromWin32Error () { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:227:9: error: error: call to undeclared function 'interruptIOManagerEvent'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 227 | interruptIOManagerEvent (); | ^ | 227 | interruptIOManagerEvent (); | ^ rts/win32/ConsoleHandler.c:227:9: error: note: did you mean 'getIOManagerEvent'? | 227 | interruptIOManagerEvent (); | ^ rts/include/rts/IOInterface.h:27:10: error: note: 'getIOManagerEvent' declared here 27 | void * getIOManagerEvent (void); | ^ | 27 | void * getIOManagerEvent (void); | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:196:9: error: error: call to undeclared function 'setThreadLabel'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/win32/ConsoleHandler.c:196:9: error: note: did you mean 'postThreadLabel'? | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/eventlog/EventLog.h:118:6: error: note: 'postThreadLabel' declared here 118 | void postThreadLabel(Capability *cap, | ^ | 118 | void postThreadLabel(Capability *cap, | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) ``` - - - - - 28b9cee0 by Rodrigo Mesquita at 2024-05-17T01:36:05-04:00 configure: Check C99-compat for Cmm preprocessor Fixes #24815 - - - - - 8927e0c3 by Andreas Klebinger at 2024-05-17T01:36:41-04:00 Ensure `tcHasFixedRuntimeRep (# #)` returns True. - - - - - 04179044 by doyougnu at 2024-05-17T09:00:32-04:00 testsuite: make find_so regex less general Closes #24759 Background. In MR !12372 we began tracking shared object files and directories sizes for dependencies. However, this broke release builds because release builds alter the filenames swapping "in-place" for a hash. This was not considered in the MR and thus broke release pipelines. Furthermore, the rts_so test was found to be wildly varying and was therefore disabled in !12561. This commit fixes both of these issues: - fix the rts_so test by making the regex less general, now the rts_so test and all other foo.so tests must match "libHS<some-lib>-<version>-<hash|'in-place>-<ghc>". This prevents the rts_so test from accidentally matching different rts variants such as rts_threaded, which was the cause of the wild swings after !12372. - add logic to match either a hash or the string in-place. This should make the find_so function build agnostic. - - - - - 0962b50d by Andreas Klebinger at 2024-05-17T09:01:08-04:00 TagAnalysis: Treat all bottom ids as tagged during analysis. Ticket #24806 showed that we also need to treat dead end thunks as tagged during the analysis. - - - - - 7eb9f184 by Ben Gamari at 2024-05-17T11:23:37-04:00 Remove haddock submodule In preparation for merge into the GHC, as proposed in #23178. - - - - - 47b14dcc by Fendor at 2024-05-17T11:28:17-04:00 Adapt to `IfLclName` newtype changes (cherry picked from commit a711607e29b925f3d69e27c5fde4ba655c711ff1) - - - - - 6cc6681d by Fendor at 2024-05-17T11:28:17-04:00 Add IfaceType deduplication table to interface file serialisation Although we do not really need it in the interface file serialisation, as the deserialisation uses `getWithUserData`, we need to mirror the structure `getWithUserData` expects. Thus, we write essentially an empty `IfaceType` table at the end of the file, as the interface file doesn't reference `IfaceType`. (cherry picked from commit c9bc29c6a708483d2abc3d8ec9262510ce87ca61) - - - - - b9721206 by Ben Gamari at 2024-05-17T11:30:22-04:00 ghc-tags.yaml: Initial commit - - - - - 074e7d8f by Ben Gamari at 2024-05-17T11:31:29-04:00 fourmolu: Add configuration - - - - - 151b1736 by Ben Gamari at 2024-05-17T11:32:52-04:00 Makefile: Rework for use by haddock developers Previously the Makefile was present only for GHC's old make-based build system. Now since the make-based build system is gone we can use it for more useful ends. - - - - - a7dcf13b by Ben Gamari at 2024-05-17T11:36:14-04:00 Reformat with fourmolu Using previously-added configuration and `fourmolu -i .` Note that we exclude the test-cases (`./{hoogle,html-hypsrc,latex}-test`) as they are sensitive to formatting. - - - - - 0ea6017b by Ben Gamari at 2024-05-17T11:40:04-04:00 Add 'utils/haddock/' from commit 'a7dcf13bfbb97b20e75cc8ce650e2bb628db4660' git-subtree-dir: utils/haddock git-subtree-mainline: 7eb9f1849b1c72a1c61dee88462b4244550406f3 git-subtree-split: a7dcf13bfbb97b20e75cc8ce650e2bb628db4660 - - - - - aba1d304 by Hécate Moonlight at 2024-05-17T11:40:48-04:00 Add exceptions to the dangling notes list - - - - - 527bfbfb by Hécate Moonlight at 2024-05-17T11:40:52-04:00 Add haddock to the whitespace lint ignore list - - - - - 43274677 by Ben Gamari at 2024-05-17T11:41:20-04:00 git-blame-ignore-revs: Ignore haddock reformatting - - - - - 0e679e37 by Fendor at 2024-05-18T00:27:24-04:00 Pass cpp options to the CC builder in hadrian - - - - - bb40244e by Sylvain Henry at 2024-05-18T00:28:06-04:00 JS: fix allocation constant (fix #24746) - - - - - 646d30ab by Jade at 2024-05-18T19:23:31+02:00 Add highlighting for inline-code snippets in haddock - - - - - 64459a3e by Hécate Moonlight at 2024-05-19T08:42:27-04:00 haddock: Add a .readthedocs.yml file for online documentation - - - - - 7d3d9bbf by Serge S. Gulin at 2024-05-19T18:47:05+00:00 Unicode: General Category size test (related #24789) Added trivial size performance test which involves unicode general category usage via `read`. The `read` itself uses general category to detect spaces. The purpose for this test is to measure outcome of applying improvements at General Category representation in code discussed at #24789. - - - - - 8e04efcf by Alan Zimmerman at 2024-05-19T21:29:34-04:00 EPA: Remove redundant code Remove unused epAnnAnns function various cases for showAstData that no longer exist - - - - - 071d7a1e by Rodrigo Mesquita at 2024-05-20T10:55:16-04:00 Improve docs on closed type families in hs-boots Fixes #24776 - - - - - d9e2c119 by Torsten Schmits at 2024-05-20T10:55:52-04:00 Use default deviation for large-project test This new performance test has the purpose of detecting regressions in complexity in relation to the number of modules in a project, so 1% deviation is way too small to avoid false positives. - - - - - 20b0136a by Ben Gamari at 2024-05-22T00:31:39-04:00 ghcup-metadata: Various fixes from 9.10.1 Use Debian 12/x86-64, Debian 10/aarch64, and Debian 11/aarch64 bindists where possible. - - - - - 6838a7c3 by Sylvain Henry at 2024-05-22T00:32:23-04:00 Reverse arguments to stgCallocBytes (fix #24828) - - - - - f50f46c3 by Fendor at 2024-05-22T00:32:59-04:00 Add log messages for Iface serialisation compression level Fix the label of the number of 'IfaceType' entries in the log message. Add log message for the compression level that is used to serialise a an interface file. Adds `Outputable` instance for 'CompressionIFace'. - - - - - 3bad5d55 by Hécate Moonlight at 2024-05-22T00:33:40-04:00 base: Update doctests outputs ghc-internal: Update doctests outputs - - - - - 9317c6fb by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix the testsuites of the haddock-library - Apply all the metadata revisions from Hackage to the cabal file. - Fix the `ParserSpec.hs` file in the `spec` testsuite of haddock-library. - Make `CHANGES.md` an extra-doc-file instead of an extra-source-file. - - - - - 54073b02 by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix parser of @since pragma The testsuite contained tests for annotations of the form `@since foo-bar-0.5.0`, but the parser was written incorrectly. - - - - - ede6ede3 by Matthew Pickering at 2024-05-22T00:34:57-04:00 Fix nightly pages job It seems likely broken by 9f99126a which moved `index.html` from the root folder into `docs/` folder. Fixes #24840 - - - - - b7bcf729 by Cheng Shao at 2024-05-22T00:35:32-04:00 autoconf: remove unused context diff check This patch removes redundant autoconf check for the context diff program given it isn't actually been used anywhere, especially since make removal. - - - - - ea2fe66e by Hécate Moonlight at 2024-05-22T00:36:13-04:00 haddock: Rework the contributing guide - - - - - 0f302a94 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 haddock: Add module relationships diagrams of haddock-api and haddock-library - - - - - d1a9f34f by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add instructions - - - - - b880ee80 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add SVG outputs - - - - - 6d7e6ad8 by Ben Gamari at 2024-05-22T13:40:05-04:00 rts: Fix size of StgOrigThunkInfo frames Previously the entry code of the `stg_orig_thunk` frame failed to account for the size of the profiling header as it hard-coded the frame size. Fix this. Fixes #24809. - - - - - c645fe40 by Fendor at 2024-05-22T13:40:05-04:00 Add regression test T24809 for stg_orig_thunk_info_frame size - - - - - 4181aa40 by Andreas Klebinger at 2024-05-22T13:40:42-04:00 bindists: Check for existence of share folder before trying to copy it. This folder isn't distributed in windows bindists A lack of doing so resulted us copying loads of files twice. - - - - - d216510e by Matthew Pickering at 2024-05-22T13:40:42-04:00 Remove ad-hoc installation of mingw toolchain in relocatable bindists This reverts 616ac30026e8dd7d2ebb98d92dde071eedf5d951 The choice about whether to install mingw is taken in the installation makefile. This is also broken on non-windows systems. The actual issue was the EnableDistroToolchain variable wasn't declared in mk/config.mk and therefore the check to install mingw was failing. - - - - - 7b4c1998 by Cheng Shao at 2024-05-22T21:52:52-04:00 testsuite: fix T17920 for wasm backend T17920 was marked as fragile on wasm before; it can be trivially fixed by avoiding calling variadic printf() in cmm. - - - - - c739383b by Cheng Shao at 2024-05-22T21:53:29-04:00 testsuite: bump T22744 timeout to 5x - - - - - c4c6d714 by Cheng Shao at 2024-05-22T21:54:06-04:00 testsuite: don't attempt to detect host cpu features when testing cross ghc The testsuite driver CPU feature detection logic only detects host CPU and only makes sense when we are not testing a cross GHC. - - - - - 3d9e4ce6 by Simon Peyton Jones at 2024-05-22T21:54:43-04:00 Better skolemisation As #24810 showed, it is (a little) better to skolemise en-bloc, so that Note [Let-bound skolems] fires more often. See Note [Skolemisation en bloc] in GHC.Tc.Utils.Instantiate. - - - - - a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00 Add missing parenthesizePat in cvtp We need to ensure that the output of `cvtp` is parenthesized (at precedence `sigPrec`) so that any pattern signatures with a surrounding pattern signature can parse correctly. Fixes #24837. - - - - - 4bb2a7cc by Hécate Moonlight at 2024-05-22T21:55:59-04:00 [base] Document the memory overhead of ByteArray Add a diagram that shows the constituent parts of a ByteArray and their memory overhead. - - - - - 8b2a016a by Hécate Moonlight at 2024-05-22T21:56:38-04:00 Haddock: Add MR template for Haddock - - - - - ead75532 by Peter Trommler at 2024-05-23T02:28:05-04:00 PPC: Support ELF v2 on powerpc64 big-endian Detect ELF v2 on PowerPC 64-bit systems. Check for `_CALL_ELF` preprocessor macro. Fixes #21191 - - - - - 9d4c10f2 by Hécate Kleidukos at 2024-05-23T02:28:44-04:00 gitlab: Add @Kleidukos to CODEOWNERS for utils/haddock - - - - - 28e64170 by Preetham Gujjula at 2024-05-23T07:20:48-04:00 haddock: Add cabal-fmt to tools for `make style` - - - - - 00126a89 by Andrei Borzenkov at 2024-05-23T07:21:24-04:00 haddock: fix verbosity option parsing - - - - - a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00 base: specify tie-breaking behavior of min, max, and related list/Foldable functions - - - - - bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00 cmm: add word <-> double/float bitcast - closes: #25331 This is the last step in the project plan described in #25331. This commit: - adds bitcast operands for x86_64, LLVM, aarch64 - For PPC and i386 we resort to using the cmm implementations - renames conversion MachOps from Conv to Round|Truncate - - - - - f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor Some functions in StgToByteCode were filtering out void arguments. However, StgToByteCode is called after unarisation: the void arguments should have been removed earlier. Instead of filtering out, we assert that the args are non-void. - - - - - 03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor `layoutNativeCall` was always called with a `primRepCmmType platform` callback. Hence we can put it inside of `layoutNativeCall` rather than repeat it. - - - - - 27c430f3 by David Binder at 2024-05-24T07:52:38-04:00 haddock: Remove compatibility shims for GHC < 8.4 from haddock-library - - - - - 8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00 compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs This patch makes the STG->Cmm backend avoid saving foreign call target to local when there are no caller-save GlobalRegs. Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a foreign call, we unconditionally save the foreign call target to a temporary local first, then rely on cmmSink to clean it up later, which only happens with -fcmm-sink (implied by -O) and not in unoptimized code. And this is troublesome for the wasm backend NCG, which needs to infer a foreign call target symbol's type signature from the Cmm call site. Previously, the NCG has been emitting incorrect type signatures for unoptimized code, which happens to work with `wasm-ld` most of the time, but this is never future-proof against upstream toolchain updates, and it causes horrible breakages when LTO objects are included in linker input. Hence this patch. - - - - - 986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00 testsuite: add callee-no-local regression test - - - - - 52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00 Fix HasCallStack leftovers from !12514 / #24726 - - - - - c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00 user_guide: Fix typo in MultiWayIf chapter Close #24829 - - - - - bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - 1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Fix changelog reference to setBacktraceMechanismState (cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d) - - - - - 43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00 Float/double unboxed literal support for HexFloatLiterals (fix #22155) - - - - - 4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00 Improve test labels for binary interface file size tests Test labels for binary interface file sizes are hard to read and overly verbose at the same time. Extend the name for the metric title, but shorten it in the actual comparison table. - - - - - 14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00 Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present" This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa. - - - - - f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00 Fix default hyperlinked sources pattern Previously this didn't include the `%M` token which manifested as broken links to the hyperlinked sources of reexports of declarations defined in other packages. Fixes haddock#1628. (cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36) - - - - - 42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00 Make DocPaths a proper data type (cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c) - - - - - 53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00 haddock: Bump version to 2.30 (cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602) - - - - - e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00 haddock-api: allow base 4.20 and ghc 9.11 - - - - - e294f7a2 by PHO at 2024-05-24T12:17:55-04:00 Add a flag "threaded" for building haddock with the threaded RTS GHC isn't guaranteed to have a threaded RTS. There should be a way to build it with the vanilla one. (cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d) - - - - - 51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00 Update ticky counter event docs. Add the info about the info table address and json fields. Fixes #23200 - - - - - 98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00 Export extractPromotedList (#24866) This can be useful in plugins. - - - - - 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - 31e52eb6 by Zubin Duggal at 2024-06-17T13:49:24+00:00 compiler: Turn `FinderCache` into a record of operations so that GHC API clients can have full control over how its state is managed by overriding `hsc_FC`. Also removes the `uncacheModule` function as this wasn't being used by anything since 1893ba12fe1fa2ade35a62c336594afcd569736e Fixes #23604 - - - - - 13 changed files: - .ghcid - + .git-blame-ignore-revs - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/darwin/nix/sources.json - .gitlab/darwin/toolchain.nix - − .gitlab/gen-ci.cabal - .gitlab/generate-ci/gen_ci.hs - .gitlab/generate-ci/generate-job-metadata - .gitlab/generate-ci/generate-jobs - .gitlab/hie.yaml → .gitlab/generate-ci/hie.yaml - .gitlab/issue_templates/bug.md → .gitlab/issue_templates/default.md The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/94ab8c9683b58711c1abe981091b5bec8f27cadd...31e52eb60f8cb14ede49154db82e8662550b264b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/94ab8c9683b58711c1abe981091b5bec8f27cadd...31e52eb60f8cb14ede49154db82e8662550b264b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 14:02:27 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 17 Jun 2024 10:02:27 -0400 Subject: [Git][ghc/ghc][master] compiler: Rejects RULES whose LHS immediately fails to type-check Message-ID: <667041f385c1f_12447a7d1046508a@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - 7 changed files: - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/Tc/Gen/Rule.hs - + testsuite/tests/typecheck/T24026/T24026a.hs - + testsuite/tests/typecheck/T24026/T24026a.stderr - + testsuite/tests/typecheck/T24026/T24026b.hs - + testsuite/tests/typecheck/T24026/T24026b.stderr - + testsuite/tests/typecheck/T24026/all.T Changes: ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -1031,9 +1031,12 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs extra_bndrs = scopedSort extra_tvs ++ extra_dicts where extra_tvs = [ v | v <- extra_vars, isTyVar v ] + + -- isEvVar: this includes coercions, matching what + -- happens in `split_lets` (isDictId, isCoVar) extra_dicts = - [ mkLocalId (localiseName (idName d)) ManyTy (idType d) - | d <- extra_vars, isDictId d ] + [ mkLocalIdOrCoVar (localiseName (idName d)) ManyTy (idType d) + | d <- extra_vars, isEvVar d ] extra_vars = [ v | v <- exprsFreeVarsList args ===================================== compiler/GHC/Tc/Gen/Rule.hs ===================================== @@ -108,11 +108,13 @@ tcRules decls = mapM (wrapLocMA tcRuleDecls) decls tcRuleDecls :: RuleDecls GhcRn -> TcM (RuleDecls GhcTc) tcRuleDecls (HsRules { rds_ext = src , rds_rules = decls }) - = do { tc_decls <- mapM (wrapLocMA tcRule) decls + = do { maybe_tc_decls <- mapM (wrapLocMA tcRule) decls + ; let tc_decls = [L loc rule | (L loc (Just rule)) <- maybe_tc_decls] ; return $ HsRules { rds_ext = src , rds_rules = tc_decls } } -tcRule :: RuleDecl GhcRn -> TcM (RuleDecl GhcTc) + +tcRule :: RuleDecl GhcRn -> TcM (Maybe (RuleDecl GhcTc)) tcRule (HsRule { rd_ext = ext , rd_name = rname@(L _ name) , rd_act = act @@ -181,7 +183,17 @@ tcRule (HsRule { rd_ext = ext ; (rhs_implic, rhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs rhs_wanted ; emitImplications (lhs_implic `unionBags` rhs_implic) - ; return $ HsRule { rd_ext = ext + + -- A type error on the LHS of a rule will be reported earlier while solving for + -- lhs_implic. However, we should also drop the rule entirely for cases where + -- compilation continues regardless of the error. For example with + -- `-fdefer-type-errors`, where this ill-typed LHS rule may cause follow-on errors + -- (#24026). + ; if anyBag insolubleImplic lhs_implic + then + return Nothing -- The RULE LHS does not type-check and will be dropped. + else + return . Just $ HsRule { rd_ext = ext , rd_name = rname , rd_act = act , rd_tyvs = ty_bndrs -- preserved for ppr-ing ===================================== testsuite/tests/typecheck/T24026/T24026a.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026a where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026a.stderr ===================================== @@ -0,0 +1,9 @@ +T24026a.hs:4:11: warning: [GHC-95396] [-Winline-rule-shadowing (in -Wdefault)] + Rule "f" may never fire because ‘f’ might inline first + Suggested fix: Add an INLINE[n] or NOINLINE[n] pragma for ‘f’ + +T24026a.hs:4:37: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/T24026b.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026b where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026b.stderr ===================================== @@ -0,0 +1,5 @@ +T24026b.hs:4:37: error: [GHC-83865] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/all.T ===================================== @@ -0,0 +1,2 @@ +test('T24026a', normal, compile, ['-dlint -fdefer-type-errors']) +test('T24026b', normal, compile_fail, ['']) \ No newline at end of file View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/db3433247fd62af09727379355381543b288b63d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/db3433247fd62af09727379355381543b288b63d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 14:03:04 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 17 Jun 2024 10:03:04 -0400 Subject: [Git][ghc/ghc][master] Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Message-ID: <66704218d8bff_12447c3d7a06832@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - 2 changed files: - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs Changes: ===================================== compiler/GHC/Driver/Env.hs ===================================== @@ -86,8 +86,8 @@ import qualified Data.Set as Set import GHC.Unit.Module.Graph runHsc :: HscEnv -> Hsc a -> IO a -runHsc hsc_env (Hsc hsc) = do - (a, w) <- hsc hsc_env emptyMessages +runHsc hsc_env hsc = do + (a, w) <- runHsc' hsc_env hsc let dflags = hsc_dflags hsc_env let !diag_opts = initDiagOpts dflags !print_config = initPrintConfig dflags ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -64,6 +64,7 @@ module GHC.Driver.Main , hscRecompStatus , hscParse , hscTypecheckRename + , hscTypecheckRenameWithDiagnostics , hscTypecheckAndGetWarnings , hscDesugar , makeSimpleDetails @@ -642,7 +643,14 @@ extract_renamed_stuff mod_summary tc_result = do -- | Rename and typecheck a module, additionally returning the renamed syntax hscTypecheckRename :: HscEnv -> ModSummary -> HsParsedModule -> IO (TcGblEnv, RenamedStuff) -hscTypecheckRename hsc_env mod_summary rdr_module = runHsc hsc_env $ +hscTypecheckRename hsc_env mod_summary rdr_module = + fst <$> hscTypecheckRenameWithDiagnostics hsc_env mod_summary rdr_module + +-- | Rename and typecheck a module, additionally returning the renamed syntax +-- and the diagnostics produced. +hscTypecheckRenameWithDiagnostics :: HscEnv -> ModSummary -> HsParsedModule + -> IO ((TcGblEnv, RenamedStuff), Messages GhcMessage) +hscTypecheckRenameWithDiagnostics hsc_env mod_summary rdr_module = runHsc' hsc_env $ hsc_typecheck True mod_summary (Just rdr_module) -- | Do Typechecking without throwing SourceError exception with -Werror View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e7a956623b7d71e50fa86fee83459d2611c423b8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e7a956623b7d71e50fa86fee83459d2611c423b8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 14:29:35 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Mon, 17 Jun 2024 10:29:35 -0400 Subject: [Git][ghc/ghc][wip/T14030] Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) Message-ID: <6670484f4dafb_1244713c444c867a0@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: 4e1b3ea5 by Sebastian Graf at 2024-06-17T16:29:25+02:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. - - - - - 8 changed files: - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - testsuite/tests/ghci/scripts/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/th/TH_Lift.hs - + testsuite/tests/th/TH_Lift.stderr - testsuite/tests/th/all.T Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs ===================================== @@ -42,7 +42,7 @@ module GHC.Internal.TH.Lift where import GHC.Internal.TH.Syntax -import GHC.Internal.TH.Lib () -- See wrinkle (W4) of Note [Tracking dependencies on primitives] +import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives] import GHC.Internal.Lexeme ( startsVarSym, startsVarId ) import GHC.Internal.Data.Either @@ -54,8 +54,9 @@ import GHC.Internal.Integer import GHC.Internal.Real import GHC.Internal.Word import GHC.Internal.Int -import GHC.Internal.Data.Data +import GHC.Internal.Data.Data hiding (Fixity) import GHC.Internal.Natural +import GHC.Internal.ForeignPtr -- | A 'Lift' instance can have any of its values turned into a Template -- Haskell expression. This is needed when a value used within a Template @@ -305,6 +306,141 @@ rightName = 'Right nonemptyName :: Name nonemptyName = '(:|) +----------------------------------------------------- +-- +-- Lifting the TH AST +-- +----------------------------------------------------- + +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Loc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DocLoc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ModName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift GHC.Internal.TH.Syntax.Module +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameSpace +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NamespaceSpecifier +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PkgName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameFlavour +-- | @since template-haskell-2.22.1.0 +deriving instance Lift OccName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Name +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameIs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Specificity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift BndrVis +-- | @since template-haskell-2.22.1.0 +deriving instance Lift a => Lift (TyVarBndr a) +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TyLit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Type +-- | @since template-haskell-2.22.1.0 +instance Lift Bytes where + liftTyped x = unsafeCodeCoerce (lift x) + lift bytes at Bytes{} = -- See Note [Why FinalPtr] + [| Bytes + { bytesPtr = ForeignPtr $(Lib.litE (BytesPrimL bytes)) FinalPtr + , bytesOffset = 0 + , bytesSize = $(lift (bytesSize bytes)) + } + |] +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Lit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pat +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Clause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivClause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivStrategy +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Overlap +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FunDep +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Safety +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Callconv +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Foreign +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ForeignSrcLang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FixityDirection +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Fixity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Inline +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleMatch +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Phases +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleBndr +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnTarget +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pragma +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceUnpackedness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DecidedStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Bang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Con +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TySynEqn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FamilyResultSig +-- | @since template-haskell-2.22.1.0 +deriving instance Lift InjectivityAnn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TypeFamilyHead +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Role +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynArgs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynDir +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Dec +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Range +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Exp +-- | @since template-haskell-2.22.1.0 +instance Lift (TExp a) where + lift (TExp e) = [| TExp $(lift e) |] + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Match +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Guard +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Stmt +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Body +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Info +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnLookup +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Extension + ----------------------------------------------------- -- -- Generic Lift implementations ===================================== libraries/template-haskell/changelog.md ===================================== @@ -1,5 +1,9 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) +## 2.22.1.0 + + * `Lift` instances were added for the `template-haskell` AST. + ## 2.22.0.0 * The kind of `Code` was changed from `forall r. (Type -> Type) -> TYPE r -> Type` ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -3,7 +3,7 @@ -- template-haskell.cabal. name: template-haskell -version: 2.22.0.0 +version: 2.22.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE ===================================== testsuite/tests/ghci/scripts/all.T ===================================== @@ -369,8 +369,8 @@ test('T20909', normal, ghci_script, ['T20909.script']) test('T20150', normal, ghci_script, ['T20150.script']) test('T20974', normal, ghci_script, ['T20974.script']) test('T21088', normal, ghci_script, ['T21088.script']) -test('T21110', [extra_files(['T21110A.hs'])], ghci_script, - ['T21110.script']) +test('T21110', [extra_files(['T21110A.hs']), normalise_version('template-haskell')], + ghci_script, ['T21110.script']) test('T17830', [filter_stdout_lines(r'======.*')], ghci_script, ['T17830.script']) test('T21294a', normal, ghci_script, ['T21294a.script']) test('T21507', normal, ghci_script, ['T21507.script']) ===================================== testsuite/tests/interface-stability/template-haskell-exports.stdout ===================================== @@ -2420,11 +2420,37 @@ instance GHC.Internal.Show.Show GHC.Internal.LanguageExtensions.Extension -- Def instance GHC.Internal.Show.Show GHC.Internal.TH.Ppr.ForallVisFlag -- Defined in ‘GHC.Internal.TH.Ppr’ instance [safe] GHC.Internal.Show.Show GHC.Internal.TH.PprLib.Doc -- Defined in ‘GHC.Internal.TH.PprLib’ instance GHC.Internal.Show.Show GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.ForeignSrcLang’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnLookup -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnTarget -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.BndrVis -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Body -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Bool -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bytes -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Callconv -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Char -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Clause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Con -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Dec -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DecidedStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivClause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivStrategy -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DocLoc -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Double -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (GHC.Internal.Data.Either.Either a b) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Exp -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.LanguageExtensions.Extension -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FamilyResultSig -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Fixity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FixityDirection -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Float -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Foreign -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FunDep -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Guard -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Info -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.InjectivityAnn -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Inline -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Int -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int16 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int32 -- Defined in ‘GHC.Internal.TH.Lift’ @@ -2432,16 +2458,49 @@ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int64 -- Defined in ‘GHC.I instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int8 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Integer.Integer -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift [a] -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Lit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Loc -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Match -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Maybe.Maybe a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.ModName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Module -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Name -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameFlavour -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameIs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameSpace -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NamespaceSpecifier -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Natural.Natural -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.OccName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Overlap -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pat -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynArgs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynDir -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Phases -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PkgName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pragma -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Range -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.Real.Integral a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Real.Ratio a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Role -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleBndr -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleMatch -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Safety -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceUnpackedness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Specificity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Stmt -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TExp a) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (a, b) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c) => GHC.Internal.TH.Lift.Lift (a, b, c) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d) => GHC.Internal.TH.Lift.Lift (a, b, c, d) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f g. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f, GHC.Internal.TH.Lift.Lift g) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f, g) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TyLit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TySynEqn -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TyVarBndr a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Type -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TypeFamilyHead -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift () -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Word -- Defined in ‘GHC.Internal.TH.Lift’ ===================================== testsuite/tests/th/TH_Lift.hs ===================================== @@ -1,6 +1,7 @@ -- test Lifting instances {-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE MagicHash #-} module TH_Lift where @@ -10,6 +11,8 @@ import Data.Word import Data.Int import Numeric.Natural import Data.List.NonEmpty +import qualified Data.ByteString as B +import qualified Data.ByteString.Internal as B a :: Integer a = $( (\x -> [| x |]) (5 :: Integer) ) @@ -80,3 +83,17 @@ o = $( (\x -> [| x |]) (True, 'x', 4 :: Int) ) p :: NonEmpty Char p = $( (\x -> [| x |]) ('a' :| "bcde") ) +exp :: Exp +exp = $( [| 3 + 4 |] >>= lift ) + +texp :: TExp Int +texp = $$( examineCode [|| 3 + 4 ||] `bindCode` liftTyped ) + +bytes :: Bytes +bytes = $(do + let (fp, offset, size) = B.toForeignPtr (B.pack [72, 101, 108, 108, 111]) -- "hello"# + let bytes = Bytes { bytesPtr = fp + , bytesOffset = fromIntegral offset + , bytesSize = fromIntegral size + } + lift bytes) ===================================== testsuite/tests/th/TH_Lift.stderr ===================================== @@ -0,0 +1,197 @@ +TH_Lift.hs:18:6-39: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Integer) + ======> + 5 +TH_Lift.hs:21:6-35: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int) + ======> + 5 +TH_Lift.hs:24:7-37: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int8) + ======> + 5 +TH_Lift.hs:27:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int16) + ======> + 5 +TH_Lift.hs:30:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int32) + ======> + 5 +TH_Lift.hs:33:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int64) + ======> + 5 +TH_Lift.hs:36:6-36: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word) + ======> + 5 +TH_Lift.hs:39:6-37: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word8) + ======> + 5 +TH_Lift.hs:42:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word16) + ======> + 5 +TH_Lift.hs:45:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word32) + ======> + 5 +TH_Lift.hs:48:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word64) + ======> + 5 +TH_Lift.hs:51:7-40: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Natural) + ======> + 5 +TH_Lift.hs:54:6-44: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 % 3 :: Rational) + ======> + 1.6666666666666667 +TH_Lift.hs:57:7-39: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (pi :: Float) + ======> + 3.1415927410125732 +TH_Lift.hs:60:7-40: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (pi :: Double) + ======> + 3.141592653589793 +TH_Lift.hs:63:6-28: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + 'x' + ======> + 'x' +TH_Lift.hs:66:6-29: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + True + ======> + True +TH_Lift.hs:69:6-35: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (Just 'x') + ======> + Just 'x' +TH_Lift.hs:72:6-58: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (Right False :: Either Char Bool) + ======> + Right False +TH_Lift.hs:75:6-29: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + "hi!" + ======> + "hi!" +TH_Lift.hs:78:6-27: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + () + ======> + () +TH_Lift.hs:81:6-46: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (True, 'x', 4 :: Int) + ======> + (,,) True 'x' 4 +TH_Lift.hs:84:6-41: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + ('a' :| "bcde") + ======> + (:|) 'a' "bcde" +TH_Lift.hs:87:8-31: Splicing expression + [| 3 + 4 |] >>= lift + ======> + InfixE + (Just (LitE (IntegerL 3))) + (VarE + (Name + (OccName "+") + (NameG + VarName (PkgName "ghc-internal") (ModName "GHC.Internal.Num")))) + (Just (LitE (IntegerL 4))) +TH_Lift.hs:(93,10)-(99,13): Splicing expression + do let (fp, offset, size) + = B.toForeignPtr (B.pack [72, 101, 108, 108, 111]) + let bytes + = Bytes + {bytesPtr = fp, bytesOffset = fromIntegral offset, + bytesSize = fromIntegral size} + lift bytes + ======> + Bytes + {bytesPtr = GHC.Internal.ForeignPtr.ForeignPtr + "Hello"# GHC.Internal.ForeignPtr.FinalPtr, + bytesOffset = 0, bytesSize = 5} +TH_Lift.hs:90:10-59: Splicing expression + examineCode [|| 3 + 4 ||] `bindCode` liftTyped + ======> + TExp + (InfixE + (Just (LitE (IntegerL 3))) + (VarE + (Name + (OccName "+") + (NameG + VarName (PkgName "ghc-internal") (ModName "GHC.Internal.Num")))) + (Just (LitE (IntegerL 4)))) ===================================== testsuite/tests/th/all.T ===================================== @@ -318,7 +318,7 @@ test('T1476', normal, compile, ['-v0']) test('T1476b', normal, compile, ['-v0']) test('T8031', normal, compile, ['-v0']) test('T8624', only_ways(['normal']), makefile_test, ['T8624']) -test('TH_Lift', normal, compile, ['-v0']) +test('TH_Lift', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques']) test('T10047', only_ways(['ghci']), ghci_script, ['T10047.script']) test('T10019', only_ways(['ghci']), ghci_script, ['T10019.script']) test('T10267', [], multimod_compile_fail, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4e1b3ea5a403151c75c7ece23db8c96a8fa469f8 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4e1b3ea5a403151c75c7ece23db8c96a8fa469f8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 14:32:35 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Mon, 17 Jun 2024 10:32:35 -0400 Subject: [Git][ghc/ghc][wip/romes/12935] 2 commits: Local test script tweaks Message-ID: <66704903454ae_1244715b2eac960fe@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/12935 at Glasgow Haskell Compiler / GHC Commits: b52063dd by Rodrigo Mesquita at 2024-05-28T11:00:06+01:00 Local test script tweaks - - - - - db38b635 by Rodrigo Mesquita at 2024-06-17T15:32:27+01:00 Do uniq renaming before SRTs - - - - - 6 changed files: - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/UniqueRenamer.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/GenerateCgIPEStub.hs - compiler/GHC/Driver/Main.hs - testsuite/tests/determinism/object/check.sh Changes: ===================================== compiler/GHC/Cmm/Pipeline.hs ===================================== @@ -19,6 +19,7 @@ import GHC.Cmm.ProcPoint import GHC.Cmm.Sink import GHC.Cmm.Switch.Implement import GHC.Cmm.ThreadSanitizer +import GHC.Cmm.UniqueRenamer import GHC.Types.Unique.Supply @@ -42,18 +43,27 @@ cmmPipeline :: Logger -> CmmConfig -> ModuleSRTInfo -- Info about SRTs generated so far + -> DetUniqFM -> CmmGroup -- Input C-- with Procedures - -> IO (ModuleSRTInfo, CmmGroupSRTs) -- Output CPS transformed C-- + -> IO (ModuleSRTInfo, (DetUniqFM, CmmGroupSRTs)) -- Output CPS transformed C-- -cmmPipeline logger cmm_config srtInfo prog = do +cmmPipeline logger cmm_config srtInfo detRnEnv prog = do let forceRes (info, group) = info `seq` foldr seq () group let platform = cmmPlatform cmm_config withTimingSilent logger (text "Cmm pipeline") forceRes $ do - (procs, data_) <- {-# SCC "tops" #-} partitionWithM (cpsTop logger platform cmm_config) prog + + -- To produce deterministic object code, we alpha-rename all Uniques to deterministic uniques before Cmm linting. + -- From here on out, the backend code generation can't use (non-deterministic) Uniques, or risk producing non-deterministic code. + -- For example, the fix-up action in the ASM NCG should use determinist names for potential new blocks it has to create. + -- Therefore, in the ASM NCG `NatM` Monad we use a deterministic `UniqSuply` (which won't be shared about multiple threads) + -- TODO: Put these all into notes carefully organized + let (rn_mapping, renamed_prog) = detRenameUniques detRnEnv prog -- TODO: if gopt Opt_DeterministicObjects dflags + + (procs, data_) <- {-# SCC "tops" #-} partitionWithM (cpsTop logger platform cmm_config) renamed_prog (srtInfo, cmms) <- {-# SCC "doSRTs" #-} doSRTs cmm_config srtInfo procs data_ dumpWith logger Opt_D_dump_cmm_cps "Post CPS Cmm" FormatCMM (pdoc platform cmms) - return (srtInfo, cmms) + return (srtInfo, (rn_mapping, cmms)) -- | The Cmm pipeline for a single 'CmmDecl'. Returns: ===================================== compiler/GHC/Cmm/UniqueRenamer.hs ===================================== @@ -76,7 +76,7 @@ renameDetUniq uq = do return det_uniq -- Rename local symbols deterministically (in order of appearance) -detRenameUniques :: DetUniqFM -> RawCmmGroup -> (DetUniqFM, RawCmmGroup) +detRenameUniques :: DetUniqFM -> CmmGroup -> (DetUniqFM, CmmGroup) detRenameUniques dufm group = swap $ runState (mapM uniqRename group) dufm -- The most important function here, which does the actual renaming. @@ -112,12 +112,33 @@ instance UniqRenamable CmmTickScope where -- * Traversals from here on out +-- ROMES:TODO: Delete RawCmmStatics instanceS? instance UniqRenamable (GenCmmDecl RawCmmStatics (LabelMap RawCmmStatics) CmmGraph) where uniqRename (CmmProc h lbl regs g) = CmmProc <$> uniqRename h <*> uniqRename lbl <*> mapM uniqRename regs <*> uniqRename g uniqRename (CmmData sec d) = CmmData <$> uniqRename sec <*> uniqRename d +instance UniqRenamable (GenCmmDecl CmmStatics CmmTopInfo CmmGraph) where + uniqRename (CmmProc h lbl regs g) + = CmmProc <$> uniqRename h <*> uniqRename lbl <*> mapM uniqRename regs <*> uniqRename g + uniqRename (CmmData sec d) + = CmmData <$> uniqRename sec <*> uniqRename d + +instance UniqRenamable CmmTopInfo where + uniqRename TopInfo{info_tbls, stack_info} + = TopInfo <$> uniqRename info_tbls <*> pure stack_info + +instance UniqRenamable CmmStatics where + uniqRename (CmmStatics clbl info ccs lits1 lits2) + = CmmStatics <$> uniqRename clbl <*> uniqRename info <*> pure ccs <*> mapM uniqRename lits1 <*> mapM uniqRename lits2 + uniqRename (CmmStaticsRaw lbl sts) + = CmmStaticsRaw <$> uniqRename lbl <*> mapM uniqRename sts + +instance UniqRenamable CmmInfoTable where + uniqRename CmmInfoTable{cit_lbl, cit_rep, cit_prof, cit_srt, cit_clo} + = CmmInfoTable <$> uniqRename cit_lbl <*> pure cit_rep <*> pure cit_prof <*> uniqRename cit_srt <*> pure cit_clo + instance UniqRenamable Section where uniqRename (Section ty lbl) = Section ty <$> uniqRename lbl ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -95,23 +95,12 @@ codeOutput logger tmpfs llvm_config dflags unit_state this_mod filenm location g cmm_stream = do { - -- To produce deterministic object code, we alpha-rename all Uniques to deterministic uniques before Cmm linting. - -- From here on out, the backend code generation can't use (non-deterministic) Uniques, or risk producing non-deterministic code. - -- For example, the fix-up action in the ASM NCG should use determinist names for potential new blocks it has to create. - -- Therefore, in the ASM NCG `NatM` Monad we use a deterministic `UniqSuply` (which won't be shared about multiple threads) - -- TODO: Put these all into notes carefully organized - ; let renamed_cmm_stream = do - -- if gopt Opt_DeterministicObjects dflags - - (rn_mapping, stream) <- Stream.mapAccumL_ (fmap pure . detRenameUniques) emptyDetUFM cmm_stream - Stream.liftIO $ debugTraceMsg logger 3 (text "DetRnM mapping:" <+> ppr rn_mapping) - return stream -- Lint each CmmGroup as it goes past ; let linted_cmm_stream = if gopt Opt_DoCmmLinting dflags - then Stream.mapM do_lint renamed_cmm_stream - else renamed_cmm_stream + then Stream.mapM do_lint cmm_stream + else cmm_stream do_lint cmm = withTimingSilent logger (text "CmmLint"<+>brackets (ppr this_mod)) ===================================== compiler/GHC/Driver/GenerateCgIPEStub.hs ===================================== @@ -35,6 +35,7 @@ import GHC.Unit.Types (Module, moduleName) import GHC.Unit.Module (moduleNameString) import qualified GHC.Utils.Logger as Logger import GHC.Utils.Outputable (ppr) +import GHC.Cmm.UniqueRenamer (emptyDetUFM) {- Note [Stacktraces from Info Table Provenance Entries (IPE based stack unwinding)] @@ -211,7 +212,7 @@ generateCgIPEStub hsc_env this_mod denv (nonCaffySet, moduleLFInfos, infoTablesW let denv' = denv {provInfoTables = Map.mapKeys cit_lbl infoTablesWithTickishes} ((mIpeStub, ipeCmmGroup), _) = runC (initStgToCmmConfig dflags this_mod) fstate cgState $ getCmm (initInfoTableProv initStats (Map.keys infoTablesWithTickishes) denv') - (_, ipeCmmGroupSRTs) <- liftIO $ cmmPipeline logger cmm_cfg (emptySRT this_mod) ipeCmmGroup + (_, (_, ipeCmmGroupSRTs)) <- liftIO $ cmmPipeline logger cmm_cfg (emptySRT this_mod) emptyDetUFM ipeCmmGroup Stream.yield ipeCmmGroupSRTs ipeStub <- ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -298,6 +298,8 @@ import GHC.StgToCmm.Utils (IPEStats) import GHC.Types.Unique.FM import GHC.Types.Unique.DFM import GHC.Cmm.Config (CmmConfig) +import GHC.Cmm.UniqueRenamer +import Data.Bifunctor {- ********************************************************************** @@ -2076,6 +2078,7 @@ hscCompileCmmFile hsc_env original_filename filename output_filename = runHsc hs $ parseCmmFile cmmpConfig cmm_mod home_unit filename let msgs = warns `unionMessages` errs return (GhcPsMessage <$> msgs, cmm) + liftIO $ do putDumpFileMaybe logger Opt_D_dump_cmm_verbose_by_proc "Parsed Cmm" FormatCMM (pdoc platform cmm) @@ -2085,8 +2088,10 @@ hscCompileCmmFile hsc_env original_filename filename output_filename = runHsc hs -- Re-ordering here causes breakage when booting with C backend because -- in C we must declare before use, but SRT algorithm is free to -- re-order [A, B] (B refers to A) when A is not CAFFY and return [B, A] - cmmgroup <- - concatMapM (\cmm -> snd <$> cmmPipeline logger cmm_config (emptySRT cmm_mod) [cmm]) cmm + (rn_mapping, cmmgroup) <- + second concat <$> mapAccumLM (\rn_mapping cmm -> snd <$> cmmPipeline logger cmm_config (emptySRT cmm_mod) rn_mapping [cmm]) emptyDetUFM cmm + + debugTraceMsg logger 3 (text "DetRnM mapping:" <+> ppr rn_mapping) unless (null cmmgroup) $ putDumpFileMaybe logger Opt_D_dump_cmm "Output Cmm" @@ -2178,9 +2183,10 @@ doCodeGen hsc_env this_mod denv data_tycons pipeline_stream :: Stream IO CmmGroupSRTs CmmCgInfos pipeline_stream = do - ((mod_srt_info, ipes, ipe_stats), lf_infos) <- + ((mod_srt_info, ipes, ipe_stats, rn_mapping), lf_infos) <- {-# SCC "cmmPipeline" #-} - Stream.mapAccumL_ (pipeline_action logger cmm_config) (emptySRT this_mod, M.empty, mempty) ppr_stream1 + Stream.mapAccumL_ (pipeline_action logger cmm_config) (emptySRT this_mod, M.empty, mempty, emptyDetUFM) ppr_stream1 + liftIO $ debugTraceMsg logger 3 (text "DetRnM mapping:" <+> ppr rn_mapping) let nonCaffySet = srtMapNonCAFs (moduleSRTMap mod_srt_info) cmmCgInfos <- generateCgIPEStub hsc_env this_mod denv (nonCaffySet, lf_infos, ipes, ipe_stats) return cmmCgInfos @@ -2188,11 +2194,11 @@ doCodeGen hsc_env this_mod denv data_tycons pipeline_action :: Logger -> CmmConfig - -> (ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats) + -> (ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats, DetUniqFM) -> CmmGroup - -> IO ((ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats), CmmGroupSRTs) - pipeline_action logger cmm_config (mod_srt_info, ipes, stats) cmm_group = do - (mod_srt_info', cmm_srts) <- cmmPipeline logger cmm_config mod_srt_info cmm_group + -> IO ((ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats, DetUniqFM), CmmGroupSRTs) + pipeline_action logger cmm_config (mod_srt_info, ipes, stats, detRnEnv) cmm_group = do + (mod_srt_info', (rn_mapping, cmm_srts)) <- cmmPipeline logger cmm_config mod_srt_info detRnEnv cmm_group -- If -finfo-table-map is enabled, we precompute a map from info -- tables to source locations. See Note [Mapping Info Tables to Source @@ -2203,7 +2209,7 @@ doCodeGen hsc_env this_mod denv data_tycons else return (ipes, stats) - return ((mod_srt_info', ipes', stats'), cmm_srts) + return ((mod_srt_info', ipes', stats', rn_mapping), cmm_srts) dump2 a = do unless (null a) $ ===================================== testsuite/tests/determinism/object/check.sh ===================================== @@ -1,6 +1,6 @@ #!/bin/sh -set -e +# set -e if test -z "$1" then @@ -34,7 +34,7 @@ compareObjs() { # Compare the object dumps except for the first line which prints the file path $OBJDUMP $2 Cabal-3.12.0.0/out1/$o | tail -n+2 > dump1 $OBJDUMP $2 Cabal-3.12.0.0/out2/$o | tail -n+2 > dump2 - diff dump1 dump2 + diff dump1 dump2 && echo "OK" echo "--------------------------------------------------------------------------------" done } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dd74409aa3889dc7a4353b8e1687721448d72116...db38b635d626106e40b3ab18091e0a24046c30c5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dd74409aa3889dc7a4353b8e1687721448d72116...db38b635d626106e40b3ab18091e0a24046c30c5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 14:37:31 2024 From: gitlab at gitlab.haskell.org (Apoorv Ingle (@ani)) Date: Mon, 17 Jun 2024 10:37:31 -0400 Subject: [Git][ghc/ghc][wip/expansions-appdo] 40 commits: Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw Message-ID: <66704a2b32d4f_12447178755c9967e@gitlab.mail> Apoorv Ingle pushed to branch wip/expansions-appdo at Glasgow Haskell Compiler / GHC Commits: edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - 0a862888 by Apoorv Ingle at 2024-06-17T08:55:17-05:00 Make ApplicativeDo work with HsExpansions testcase added: T24406 Issues Fixed: #24406, #16135 Code Changes: - Remove `XStmtLR GhcTc` as `XStmtLR GhcRn` is now compiled to `HsExpr GhcTc` - The expanded statements are guided by `GHC.Hs.Expr.TcFunInfo` which is used to decide if the `XExpr GhcRn` is to be typechecked using `tcApp` or `tcExpr` Note [Expanding HsDo with XXExprGhcRn] explains the change in more detail - - - - - 30 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - CODEOWNERS - compiler/GHC/Builtin/Names.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/GuardedRHSs.hs - compiler/GHC/HsToCore/ListComp.hs - compiler/GHC/HsToCore/Match.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57d640c5ed21e7f2c84a87ebb50d9f1ad0ca7752...0a86288800ecf18f91bbbeb924c8d7d897d33c54 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57d640c5ed21e7f2c84a87ebb50d9f1ad0ca7752...0a86288800ecf18f91bbbeb924c8d7d897d33c54 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 15:04:13 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Mon, 17 Jun 2024 11:04:13 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: compiler: Rejects RULES whose LHS immediately fails to type-check Message-ID: <6670506deb9b4_124471bd2f08111637@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - 70ef2878 by David Binder at 2024-06-17T11:03:55-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - 460e65ed by Andreas Klebinger at 2024-06-17T11:03:56-04:00 GHCi interpreter: Tag constructor closures when possible. When evaluating PUSH_G try to tag the reference we are pushing if it's a constructor or function. This is potentially helpful for performance and required to fix #24870. - - - - - 28 changed files: - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/Tc/Gen/Rule.hs - docs/users_guide/9.12.1-notes.rst - docs/users_guide/profiling.rst - docs/users_guide/runtime_control.rst - libraries/base/changelog.md - libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc - rts/Hpc.c - rts/Interpreter.c - rts/RtsFlags.c - rts/include/rts/Flags.h - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - + testsuite/tests/th/should_compile/T24870/Def.hs - + testsuite/tests/th/should_compile/T24870/T24870.stderr - + testsuite/tests/th/should_compile/T24870/T24870.stderr-mingw32 - + testsuite/tests/th/should_compile/T24870/Use.hs - + testsuite/tests/th/should_compile/T24870/all.T - + testsuite/tests/typecheck/T24026/T24026a.hs - + testsuite/tests/typecheck/T24026/T24026a.stderr - + testsuite/tests/typecheck/T24026/T24026b.hs - + testsuite/tests/typecheck/T24026/T24026b.stderr - + testsuite/tests/typecheck/T24026/all.T Changes: ===================================== compiler/GHC/ByteCode/Instr.hs ===================================== @@ -83,7 +83,7 @@ data BCInstr | PUSH16_W !ByteOff | PUSH32_W !ByteOff - -- Push a ptr (these all map to PUSH_G really) + -- Push a (heap) ptr (these all map to PUSH_G really) | PUSH_G Name | PUSH_PRIMOP PrimOp | PUSH_BCO (ProtoBCO Name) ===================================== compiler/GHC/Driver/Env.hs ===================================== @@ -86,8 +86,8 @@ import qualified Data.Set as Set import GHC.Unit.Module.Graph runHsc :: HscEnv -> Hsc a -> IO a -runHsc hsc_env (Hsc hsc) = do - (a, w) <- hsc hsc_env emptyMessages +runHsc hsc_env hsc = do + (a, w) <- runHsc' hsc_env hsc let dflags = hsc_dflags hsc_env let !diag_opts = initDiagOpts dflags !print_config = initPrintConfig dflags ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -64,6 +64,7 @@ module GHC.Driver.Main , hscRecompStatus , hscParse , hscTypecheckRename + , hscTypecheckRenameWithDiagnostics , hscTypecheckAndGetWarnings , hscDesugar , makeSimpleDetails @@ -642,7 +643,14 @@ extract_renamed_stuff mod_summary tc_result = do -- | Rename and typecheck a module, additionally returning the renamed syntax hscTypecheckRename :: HscEnv -> ModSummary -> HsParsedModule -> IO (TcGblEnv, RenamedStuff) -hscTypecheckRename hsc_env mod_summary rdr_module = runHsc hsc_env $ +hscTypecheckRename hsc_env mod_summary rdr_module = + fst <$> hscTypecheckRenameWithDiagnostics hsc_env mod_summary rdr_module + +-- | Rename and typecheck a module, additionally returning the renamed syntax +-- and the diagnostics produced. +hscTypecheckRenameWithDiagnostics :: HscEnv -> ModSummary -> HsParsedModule + -> IO ((TcGblEnv, RenamedStuff), Messages GhcMessage) +hscTypecheckRenameWithDiagnostics hsc_env mod_summary rdr_module = runHsc' hsc_env $ hsc_typecheck True mod_summary (Just rdr_module) -- | Do Typechecking without throwing SourceError exception with -Werror ===================================== compiler/GHC/HsToCore/Binds.hs ===================================== @@ -1031,9 +1031,12 @@ decomposeRuleLhs dflags orig_bndrs orig_lhs rhs_fvs extra_bndrs = scopedSort extra_tvs ++ extra_dicts where extra_tvs = [ v | v <- extra_vars, isTyVar v ] + + -- isEvVar: this includes coercions, matching what + -- happens in `split_lets` (isDictId, isCoVar) extra_dicts = - [ mkLocalId (localiseName (idName d)) ManyTy (idType d) - | d <- extra_vars, isDictId d ] + [ mkLocalIdOrCoVar (localiseName (idName d)) ManyTy (idType d) + | d <- extra_vars, isEvVar d ] extra_vars = [ v | v <- exprsFreeVarsList args ===================================== compiler/GHC/Tc/Gen/Rule.hs ===================================== @@ -108,11 +108,13 @@ tcRules decls = mapM (wrapLocMA tcRuleDecls) decls tcRuleDecls :: RuleDecls GhcRn -> TcM (RuleDecls GhcTc) tcRuleDecls (HsRules { rds_ext = src , rds_rules = decls }) - = do { tc_decls <- mapM (wrapLocMA tcRule) decls + = do { maybe_tc_decls <- mapM (wrapLocMA tcRule) decls + ; let tc_decls = [L loc rule | (L loc (Just rule)) <- maybe_tc_decls] ; return $ HsRules { rds_ext = src , rds_rules = tc_decls } } -tcRule :: RuleDecl GhcRn -> TcM (RuleDecl GhcTc) + +tcRule :: RuleDecl GhcRn -> TcM (Maybe (RuleDecl GhcTc)) tcRule (HsRule { rd_ext = ext , rd_name = rname@(L _ name) , rd_act = act @@ -181,7 +183,17 @@ tcRule (HsRule { rd_ext = ext ; (rhs_implic, rhs_binds) <- buildImplicationFor tc_lvl (getSkolemInfo skol_info) qtkvs lhs_evs rhs_wanted ; emitImplications (lhs_implic `unionBags` rhs_implic) - ; return $ HsRule { rd_ext = ext + + -- A type error on the LHS of a rule will be reported earlier while solving for + -- lhs_implic. However, we should also drop the rule entirely for cases where + -- compilation continues regardless of the error. For example with + -- `-fdefer-type-errors`, where this ill-typed LHS rule may cause follow-on errors + -- (#24026). + ; if anyBag insolubleImplic lhs_implic + then + return Nothing -- The RULE LHS does not type-check and will be dropped. + else + return . Just $ HsRule { rd_ext = ext , rd_name = rname , rd_act = act , rd_tyvs = ty_bndrs -- preserved for ppr-ing ===================================== docs/users_guide/9.12.1-notes.rst ===================================== @@ -91,6 +91,11 @@ Runtime system - Reduce fragmentation incurred by the nonmoving GC's segment allocator. In one application this reduced resident set size by 26%. See :ghc-ticket:`24150`. +- The new runtime flag :rts-flag:`--read-tix-file=\` allows to modify whether a preexisting .tix file is read in at the beginning of a program run. + The default is currently ``--read-tix-file=yes`` but will change to ``--read-tix-file=no`` in a future version of GHC. + For this reason, a warning is emitted if a .tix file is read in implicitly. You can silence this warning by explicitly passing ``--read-tix-file=yes``. + Details can be found in `GHC proposal 612 `__. + ``base`` library ~~~~~~~~~~~~~~~~ ===================================== docs/users_guide/profiling.rst ===================================== @@ -1502,9 +1502,9 @@ Running the program generates a file with the ``.tix`` suffix, in this case :file:`Recip.tix`, which contains the coverage data for this run of the program. The program may be run multiple times (e.g. with different test data), and the coverage data from the separate runs is accumulated in -the ``.tix`` file. To reset the coverage data and start again, just -remove the ``.tix`` file. You can control where the ``.tix`` file -is generated using the environment variable :envvar:`HPCTIXFILE`. +the ``.tix`` file. This behaviour can be controlled with the :rts-flag:`--read-tix-file=\` +You can control where the ``.tix`` file is generated using the +environment variable :envvar:`HPCTIXFILE`. .. envvar:: HPCTIXFILE ===================================== docs/users_guide/runtime_control.rst ===================================== @@ -1373,7 +1373,22 @@ and can be controlled by the following flags. .. index:: single: RTS options, hpc -.. rts-flag:: --write-tix-file +.. rts-flag:: --read-tix-file= + + :default: enabled + :since: 9.12 + + The RTS can be instructed to read a ``.tix`` file during the startup + phase. The datastructures which accumulate the coverage information during + program execution are then initialized with the information from this file. + This option is useful for aggregating coverage information over multiple runs + of an executable. + + The default for this flag is currently ``--read-tix-file=yes`` but will change + to ``-read-tix-file=no`` in a future version of GHC according to the accepted + `GHC proposal 612 `__. + +.. rts-flag:: --write-tix-file= :default: enabled :since: 9.10 ===================================== libraries/base/changelog.md ===================================== @@ -1,6 +1,7 @@ # Changelog for [`base` package](http://hackage.haskell.org/package/base) ## 4.21.0.0 *TBA* + * Add a `readTixFile` field to the `HpcFlags` record in `GHC.RTS.Flags` ([CLC proposal #276](https://github.com/haskell/core-libraries-committee/issues/276)) * Add the `MonadFix` instance for `(,) a`, similar to the one for `Writer a` ([CLC proposal #238](https://github.com/haskell/core-libraries-committee/issues/238)) * Improve `toInteger :: Word32 -> Integer` on 64-bit platforms ([CLC proposal #259](https://github.com/haskell/core-libraries-committee/issues/259)) * Make `flip` representation polymorphic ([CLC proposal #245](https://github.com/haskell/core-libraries-committee/issues/245)) ===================================== libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc ===================================== @@ -382,7 +382,11 @@ data ParFlags = ParFlags -- -- @since base-4.20.0.0 data HpcFlags = HpcFlags - { writeTixFile :: Bool + { readTixFile :: Bool + -- ^ Controls whether a @.tix@ file is read at + -- the start of execution to initialize the RTS internal + -- HPC datastructures. + , writeTixFile :: Bool -- ^ Controls whether the @.tix@ file should be -- written after the execution of the program. } @@ -498,6 +502,8 @@ getHpcFlags = do let ptr = (#ptr RTS_FLAGS, HpcFlags) rtsFlagsPtr HpcFlags <$> (toBool <$> + (#{peek HPC_FLAGS, readTixFile} ptr :: IO CBool)) + <*> (toBool <$> (#{peek HPC_FLAGS, writeTixFile} ptr :: IO CBool)) getConcFlags :: IO ConcFlags ===================================== rts/Hpc.c ===================================== @@ -236,7 +236,14 @@ startupHpc(void) sprintf(tixFilename, "%s.tix", prog_name); } - if (init_open(__rts_fopen(tixFilename,"r"))) { + if ((RtsFlags.HpcFlags.readTixFile == HPC_YES_IMPLICIT) && init_open(__rts_fopen(tixFilename,"r"))) { + fprintf(stderr,"Deprecation warning:\n" + "I am reading in the existing tix file, and will add hpc info from this run to the existing data in that file.\n" + "GHC 9.14 will cease looking for an existing tix file by default.\n" + "If you positively want to add hpc info to the current tix file, use the RTS option --read-tix-file=yes.\n" + "More information can be found in the accepted GHC proposal 612.\n"); + readTix(); + } else if ((RtsFlags.HpcFlags.readTixFile == HPC_YES_EXPLICIT) && init_open(__rts_fopen(tixFilename,"r"))) { readTix(); } } ===================================== rts/Interpreter.c ===================================== @@ -4,6 +4,30 @@ * Copyright (c) The GHC Team, 1994-2002. * ---------------------------------------------------------------------------*/ +/* +Note [CBV Functions and the interpreter] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +When the byte code interpreter loads a reference to a value it often +ends up as a non-tagged pointers *especially* if we already know a value +is a certain constructor and therefore don't perform an eval on the reference. +This causes friction with CBV functions which assume +their value arguments are properly tagged by the caller. + +In order to ensure CBV functions still get passed tagged functions we have +three options: +a) Special case the interpreter behaviour into the tag inference analysis. + If we assume the interpreter can't properly tag value references the STG passes + would then wrap such calls in appropriate evals which are executed at runtime. + This would ensure tags by doing additional evals at runtime. +b) When the interpreter pushes references for known constructors instead of + pushing the objects address add the tag to the value pushed. This is what + the NCG backends do. +c) When the interpreter pushes a reference inspect the closure of the object + and apply the appropriate tag at runtime. + +For now we use approach c). Mostly because it's easiest to implement. We also don't +tag functions as tag inference currently doesn't rely on those being properly tagged. +*/ #include "rts/PosixSource.h" #include "Rts.h" @@ -290,6 +314,18 @@ STATIC_INLINE StgClosure *tagConstr(StgClosure *con) { return TAG_CLOSURE(stg_min(TAG_MASK, 1 + GET_TAG(con)), con); } +// Compute the pointer tag for the function and tag the pointer; +STATIC_INLINE StgClosure *tagFun(StgClosure *fun) { + StgHalfWord tag = GET_TAG(fun); + if(tag > TAG_MASK) { return fun; } + else { + return TAG_CLOSURE(tag, fun); + } + + +} + + static StgWord app_ptrs_itbl[] = { (W_)&stg_ap_p_info, (W_)&stg_ap_pp_info, @@ -1304,7 +1340,52 @@ run_BCO: case bci_PUSH_G: { W_ o1 = BCO_GET_LARGE_ARG; - SpW(-1) = BCO_PTR(o1); + StgClosure *tagged_obj = (StgClosure*) BCO_PTR(o1); + + tag_push_g: + ASSERT(LOOKS_LIKE_CLOSURE_PTR((StgClosure*) tagged_obj)); + // Here we make sure references we push are tagged. + // See Note [CBV Functions and the interpreter] in Info.hs + + //Safe some memory reads if we already have a tag. + if(GET_CLOSURE_TAG(tagged_obj) == 0) { + StgClosure *obj = UNTAG_CLOSURE(tagged_obj); + switch ( get_itbl(obj)->type ) { + case IND: + case IND_STATIC: + { + tagged_obj = ACQUIRE_LOAD(&((StgInd*)obj)->indirectee); + goto tag_push_g; + } + case CONSTR: + case CONSTR_1_0: + case CONSTR_0_1: + case CONSTR_2_0: + case CONSTR_1_1: + case CONSTR_0_2: + case CONSTR_NOCAF: + // The value is already evaluated, so we can just return it. However, + // before we do, we MUST ensure that the pointer is tagged, because we + // might return to a native `case` expression, which assumes the returned + // pointer is tagged so it can use the tag to select an alternative. + tagged_obj = tagConstr(obj); + break; + case FUN: + case FUN_1_0: + case FUN_0_1: + case FUN_2_0: + case FUN_1_1: + case FUN_0_2: + case FUN_STATIC: + // Purely for performance since we already hit memory anyway. + tagged_obj = tagFun(obj); + break; + default: + break; + } + } + + SpW(-1) = (W_) tagged_obj; Sp_subW(1); goto nextInsn; } ===================================== rts/RtsFlags.c ===================================== @@ -297,6 +297,7 @@ void initRtsFlagsDefaults(void) RtsFlags.TickyFlags.showTickyStats = false; RtsFlags.TickyFlags.tickyFile = NULL; #endif + RtsFlags.HpcFlags.readTixFile = HPC_YES_IMPLICIT; RtsFlags.HpcFlags.writeTixFile = true; } @@ -565,6 +566,10 @@ usage_text[] = { " HeapOverflow exception before the exception is thrown again, if", " the program is still exceeding the heap limit.", "", +" --read-tix-file=", +" Whether to initialize HPC datastructures from .tix " +" at the start of execution. (default: yes)", +"", " --write-tix-file=", " Whether to write .tix at the end of execution.", " (default: yes)", @@ -1068,6 +1073,16 @@ error = true; RtsFlags.GcFlags.nonmovingDenseAllocatorCount = threshold; } } + else if (strequal("read-tix-file=yes", + &rts_argv[arg][2])) { + OPTION_UNSAFE; + RtsFlags.HpcFlags.readTixFile = HPC_YES_EXPLICIT; + } + else if (strequal("read-tix-file=no", + &rts_argv[arg][2])) { + OPTION_UNSAFE; + RtsFlags.HpcFlags.readTixFile = HPC_NO_EXPLICIT; + } else if (strequal("write-tix-file=yes", &rts_argv[arg][2])) { OPTION_UNSAFE; ===================================== rts/include/rts/Flags.h ===================================== @@ -302,10 +302,26 @@ typedef struct _PAR_FLAGS { bool setAffinity; /* force thread affinity with CPUs */ } PAR_FLAGS; +/* Corresponds to the RTS flag `--read-tix-file=`. + * The accepted GHC proposal 612 introduced a one-release warning period + * during which we emit a warning if we read a .tix file and the flag + * isn't explicitly set. In order to distinguish between whether the flag + * was explicitly set or defaulted we need to use a tri-state variable. + */ +typedef enum _HPC_READ_FILE { + HPC_NO_EXPLICIT = 0, /* The user has specified --read-tix-file=no */ + HPC_YES_IMPLICIT = 1, /* The user hasn't specified an option and we emit + * a warning when we read a tix file. + */ + HPC_YES_EXPLICIT = 2 /* The user has specified --read-tix-file=yes */ + } HPC_READ_FILE; + /* See Note [Synchronization of flags and base APIs] */ typedef struct _HPC_FLAGS { bool writeTixFile; /* Whether the RTS should write a tix file at the end of execution */ + HPC_READ_FILE readTixFile; /* Whether the RTS should read a tix + file at the beginning of execution */ } HPC_FLAGS; /* See Note [Synchronization of flags and base APIs] */ ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -9105,7 +9105,7 @@ module GHC.RTS.Flags where type GiveGCStats :: * data GiveGCStats = NoGCStats | CollectGCStats | OneLineGCStats | SummaryGCStats | VerboseGCStats type HpcFlags :: * - data HpcFlags = HpcFlags {writeTixFile :: GHC.Types.Bool} + data HpcFlags = HpcFlags {readTixFile :: GHC.Types.Bool, writeTixFile :: GHC.Types.Bool} type IoManagerFlag :: * data IoManagerFlag = IoManagerFlagAuto | IoManagerFlagSelect | IoManagerFlagMIO | IoManagerFlagWinIO | IoManagerFlagWin32Legacy type IoSubSystem :: * ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -12147,7 +12147,7 @@ module GHC.RTS.Flags where type GiveGCStats :: * data GiveGCStats = NoGCStats | CollectGCStats | OneLineGCStats | SummaryGCStats | VerboseGCStats type HpcFlags :: * - data HpcFlags = HpcFlags {writeTixFile :: GHC.Types.Bool} + data HpcFlags = HpcFlags {readTixFile :: GHC.Types.Bool, writeTixFile :: GHC.Types.Bool} type IoManagerFlag :: * data IoManagerFlag = IoManagerFlagAuto | IoManagerFlagSelect | IoManagerFlagMIO | IoManagerFlagWinIO | IoManagerFlagWin32Legacy type IoSubSystem :: * ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -9329,7 +9329,7 @@ module GHC.RTS.Flags where type GiveGCStats :: * data GiveGCStats = NoGCStats | CollectGCStats | OneLineGCStats | SummaryGCStats | VerboseGCStats type HpcFlags :: * - data HpcFlags = HpcFlags {writeTixFile :: GHC.Types.Bool} + data HpcFlags = HpcFlags {readTixFile :: GHC.Types.Bool, writeTixFile :: GHC.Types.Bool} type IoManagerFlag :: * data IoManagerFlag = IoManagerFlagAuto | IoManagerFlagSelect | IoManagerFlagMIO | IoManagerFlagWinIO | IoManagerFlagWin32Legacy type IoSubSystem :: * ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -9105,7 +9105,7 @@ module GHC.RTS.Flags where type GiveGCStats :: * data GiveGCStats = NoGCStats | CollectGCStats | OneLineGCStats | SummaryGCStats | VerboseGCStats type HpcFlags :: * - data HpcFlags = HpcFlags {writeTixFile :: GHC.Types.Bool} + data HpcFlags = HpcFlags {readTixFile :: GHC.Types.Bool, writeTixFile :: GHC.Types.Bool} type IoManagerFlag :: * data IoManagerFlag = IoManagerFlagAuto | IoManagerFlagSelect | IoManagerFlagMIO | IoManagerFlagWinIO | IoManagerFlagWin32Legacy type IoSubSystem :: * ===================================== testsuite/tests/th/should_compile/T24870/Def.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE TemplateHaskell #-} + +module SDef where + +{-# NOINLINE aValue #-} +aValue = True + +{-# NOINLINE aStrictFunction #-} +aStrictFunction !x = [| x |] ===================================== testsuite/tests/th/should_compile/T24870/T24870.stderr ===================================== @@ -0,0 +1,2 @@ +[1 of 2] Compiling SDef ( Def.hs, Def.o, Def.dyn_o ) +[2 of 2] Compiling SUse ( Use.hs, Use.o ) ===================================== testsuite/tests/th/should_compile/T24870/T24870.stderr-mingw32 ===================================== @@ -0,0 +1,2 @@ +[1 of 2] Compiling SDef ( Def.hs, Def.o ) +[2 of 2] Compiling SUse ( Use.hs, Use.o ) ===================================== testsuite/tests/th/should_compile/T24870/Use.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE TemplateHaskell #-} + +module SUse where + +import qualified Language.Haskell.TH.Syntax as TH +import SDef +import GHC.Exts + +bar = $( inline aStrictFunction aValue ) ===================================== testsuite/tests/th/should_compile/T24870/all.T ===================================== @@ -0,0 +1,6 @@ +# The interpreter must uphold tagging invariants, and failed to do so in #24870 +# We test this here by having the interpreter calls a strict worker function +# with a reference to a value it constructed. +# See also Note [CBV Functions and the interpreter] +test('T24870', [extra_files(['Def.hs', 'Use.hs']), req_th], + multimod_compile, ['Def Use', '-dtag-inference-checks']) ===================================== testsuite/tests/typecheck/T24026/T24026a.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026a where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026a.stderr ===================================== @@ -0,0 +1,9 @@ +T24026a.hs:4:11: warning: [GHC-95396] [-Winline-rule-shadowing (in -Wdefault)] + Rule "f" may never fire because ‘f’ might inline first + Suggested fix: Add an INLINE[n] or NOINLINE[n] pragma for ‘f’ + +T24026a.hs:4:37: warning: [GHC-83865] [-Wdeferred-type-errors (in -Wdefault)] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/T24026b.hs ===================================== @@ -0,0 +1,7 @@ +-- This rule has a type error on the LHS +module T24026b where + +{-# RULES "f" forall (x :: Bool). f x = 0 #-} + +f :: Int -> Int +f x = 0 ===================================== testsuite/tests/typecheck/T24026/T24026b.stderr ===================================== @@ -0,0 +1,5 @@ +T24026b.hs:4:37: error: [GHC-83865] + • Couldn't match expected type ‘Int’ with actual type ‘Bool’ + • In the first argument of ‘f’, namely ‘x’ + In the expression: f x + When checking the rewrite rule "f" \ No newline at end of file ===================================== testsuite/tests/typecheck/T24026/all.T ===================================== @@ -0,0 +1,2 @@ +test('T24026a', normal, compile, ['-dlint -fdefer-type-errors']) +test('T24026b', normal, compile_fail, ['']) \ No newline at end of file View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d93014c4808da90d68c3b43b97afb2066fc94724...460e65edf5851696f15c250390c057f2e55fe59e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d93014c4808da90d68c3b43b97afb2066fc94724...460e65edf5851696f15c250390c057f2e55fe59e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 15:32:30 2024 From: gitlab at gitlab.haskell.org (Hannes Siebenhandl (@fendor)) Date: Mon, 17 Jun 2024 11:32:30 -0400 Subject: [Git][ghc/ghc][wip/fendor/ghc-iface-sharing-avoid-reserialisation] 6 commits: Make flip representation polymorphic, similar to ($) and (&) Message-ID: <6670570e437a7_1244720968a0133292@gitlab.mail> Hannes Siebenhandl pushed to branch wip/fendor/ghc-iface-sharing-avoid-reserialisation at Glasgow Haskell Compiler / GHC Commits: e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - 13320ff2 by Fendor at 2024-06-17T17:31:34+02:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 52e2537a by Fendor at 2024-06-17T17:31:37+02:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18698b T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The tests T16875 and T18698b fail on i386-linux for the same reason. - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/146d298ecaa3b343b35b2a56713d1b022ce77728...52e2537a0c24ff3a75a808403a63313c809c355d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/146d298ecaa3b343b35b2a56713d1b022ce77728...52e2537a0c24ff3a75a808403a63313c809c355d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 16:36:01 2024 From: gitlab at gitlab.haskell.org (Jacco Krijnen (@jacco)) Date: Mon, 17 Jun 2024 12:36:01 -0400 Subject: [Git][ghc/ghc][wip/jacco/haddock/codeblock-highlighting] Haddock highlighted codeblocks: optional language. Message-ID: <667065f17af3d_124472b698901557f8@gitlab.mail> Jacco Krijnen pushed to branch wip/jacco/haddock/codeblock-highlighting at Glasgow Haskell Compiler / GHC Commits: 1521cf9b by Jacco Krijnen at 2024-06-17T18:33:15+02:00 Haddock highlighted codeblocks: optional language. The triple backtick notation should not require a language to be used for highlighting. - - - - - 4 changed files: - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs - utils/haddock/haddock-api/src/Haddock/Interface/Json.hs - utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs - utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs Changes: ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs ===================================== @@ -70,8 +70,9 @@ parHtmlMarkup qual insertAnchors ppId = , markupOrderedList = makeOrdList , markupDefList = defList , markupCodeBlock = pre - , markupCodeBlockHighlight = \(Highlight l cont) -> - pre ! [theclass ("language-" ++ l)] << toHtml cont + , markupCodeBlockHighlight = \(Highlight mLang cont) -> + let attrs = maybe [] (\name -> [theclass ("language-" ++ name)]) mLang + in pre ! attrs << toHtml cont , markupHyperlink = \(Hyperlink url mLabel) -> if insertAnchors then ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Json.hs ===================================== @@ -155,7 +155,7 @@ jsonDoc (DocCodeBlockHighlight hl) = jsonObject ] where jsonHighlight Highlight{..} = jsonObject - [ ("highlightLanguage", jsonString highlightLanguage) + [ ("highlightLanguage", jsonMaybe jsonString highlightLanguage) , ("highlightContent", jsonString highlightContent) ] ===================================== utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs ===================================== @@ -910,10 +910,10 @@ codeblockHighlight indent = DocCodeBlockHighlight <$> pHighlight <*> pLang <*> (intercalate "\n" <$> Parsec.manyTill pCodeLine pBlockEnd) - pLang :: Parser String + pLang :: Parser (Maybe String) pLang = skipHorizontalSpace - *> Parsec.many1 Parsec.alphaNum + *> optional (Parsec.many1 Parsec.alphaNum) <* skipHorizontalSpace <* Parsec.newline ===================================== utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs ===================================== @@ -110,7 +110,7 @@ data Table id = Table deriving (Eq, Show, Functor, Foldable, Traversable) data Highlight = Highlight - { highlightLanguage :: String + { highlightLanguage :: Maybe String , highlightContent :: String } deriving (Eq, Show) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1521cf9b08943f3e23c9ae532b5f979d0be93d8c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1521cf9b08943f3e23c9ae532b5f979d0be93d8c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 17:11:34 2024 From: gitlab at gitlab.haskell.org (Jacco Krijnen (@jacco)) Date: Mon, 17 Jun 2024 13:11:34 -0400 Subject: [Git][ghc/ghc][wip/jacco/haddock/codeblock-highlighting] Add golden test for codeblocks with highlighting Message-ID: <66706e4623b7e_1244731ef27817083f@gitlab.mail> Jacco Krijnen pushed to branch wip/jacco/haddock/codeblock-highlighting at Glasgow Haskell Compiler / GHC Commits: b9abfee5 by Jacco Krijnen at 2024-06-17T19:11:22+02:00 Add golden test for codeblocks with highlighting - - - - - 2 changed files: - + utils/haddock/html-test/ref/CodeblockHighlight.html - + utils/haddock/html-test/src/CodeblockHighlight.hs Changes: ===================================== utils/haddock/html-test/ref/CodeblockHighlight.html ===================================== @@ -0,0 +1,115 @@ +CodeblockHighlight
Safe HaskellNone

CodeblockHighlight

Synopsis

Documentation

add :: Int -> Int -> Int #

A simple function that adds two integers.

Its implementation is straightforward:

add :: Int -> Int -> Int
+add x y = x + y

main :: IO () #

Run this program as follows:

runghc CodeBlockHighlight.hs
===================================== utils/haddock/html-test/src/CodeblockHighlight.hs ===================================== @@ -0,0 +1,20 @@ +module CodeblockHighlight where + +-- | A simple function that adds two integers. +-- +-- Its implementation is straightforward: +-- +-- ```haskell +-- add :: Int -> Int -> Int +-- add x y = x + y +-- ``` +add :: Int -> Int -> Int +add x y = x + y + +-- | Run this program as follows: +-- +-- ```bash +-- runghc CodeBlockHighlight.hs +-- ``` +main :: IO () +main = putStrLn "Hello, Haskell!" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b9abfee529ec0301910560e11b9d4e57b7beecc3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b9abfee529ec0301910560e11b9d4e57b7beecc3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 17:32:23 2024 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Mon, 17 Jun 2024 13:32:23 -0400 Subject: [Git][ghc/ghc][wip/az/T12842-ttg-fixity] 5 commits: Make flip representation polymorphic, similar to ($) and (&) Message-ID: <66707327bdb85_2fe09915a51895087@gitlab.mail> Alan Zimmerman pushed to branch wip/az/T12842-ttg-fixity at Glasgow Haskell Compiler / GHC Commits: e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - 5915b8d8 by Alan Zimmerman at 2024-06-17T18:31:52+01:00 TTG: Move SourceText from `Fixity` to `FixitySig` It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Precedes !12842, to simplify it - - - - - 30 changed files: - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Utils.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Gen/Expr.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bdae6b9e457b43003ce8e645386ab19b6e1b88b2...5915b8d828a8885f7ec6cd6a1a2dc2446fc7240b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/bdae6b9e457b43003ce8e645386ab19b6e1b88b2...5915b8d828a8885f7ec6cd6a1a2dc2446fc7240b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 17:57:45 2024 From: gitlab at gitlab.haskell.org (Jacco Krijnen (@jacco)) Date: Mon, 17 Jun 2024 13:57:45 -0400 Subject: [Git][ghc/ghc][wip/jacco/haddock/codeblock-highlighting] Add haddock tests for codeblock with highlighting Message-ID: <6670791929ee1_2fe099527bc81003dc@gitlab.mail> Jacco Krijnen pushed to branch wip/jacco/haddock/codeblock-highlighting at Glasgow Haskell Compiler / GHC Commits: 6da12dd9 by Jacco Krijnen at 2024-06-17T19:56:53+02:00 Add haddock tests for codeblock with highlighting - - - - - 2 changed files: - + utils/haddock/html-test/ref/CodeblockHighlight2.html - + utils/haddock/html-test/src/CodeblockHighlight2.hs Changes: ===================================== utils/haddock/html-test/ref/CodeblockHighlight2.html ===================================== @@ -0,0 +1,120 @@ +CodeblockHighlight2
Safe HaskellNone

CodeblockHighlight2

Synopsis

Documentation

add :: Int -> Int -> Int #

The following codeblocks start at different indentation in the source, but + that should not be visible in the rendered html:

add :: Int -> Int -> Int
+add x y = x + y
mul :: Int -> Int -> Int
+mul x y = x * y
pow :: Int -> Int -> Int
+pow x y = x + y

main :: IO () #

The triple backtick notation can also be used without mentioning a language

runghc CodeBlockHighlight2.hs
===================================== utils/haddock/html-test/src/CodeblockHighlight2.hs ===================================== @@ -0,0 +1,29 @@ +module CodeblockHighlight2 where + +-- | The following codeblocks start at different indentation in the source, but +-- that should not be visible in the rendered html: +-- +-- ```haskell +-- add :: Int -> Int -> Int +-- add x y = x + y +-- ``` +-- +-- ```haskell +-- mul :: Int -> Int -> Int +-- mul x y = x * y +-- ``` +-- +--```haskell +--pow :: Int -> Int -> Int +--pow x y = x + y +--``` +add :: Int -> Int -> Int +add x y = x + y + +-- | The triple backtick notation can also be used without mentioning a language +-- +-- ``` +-- runghc CodeBlockHighlight2.hs +-- ``` +main :: IO () +main = putStrLn "Hello, Haskell!" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6da12dd97a97e4143f3b02d670b92f7a6f7fd8a6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6da12dd97a97e4143f3b02d670b92f7a6f7fd8a6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 18:10:22 2024 From: gitlab at gitlab.haskell.org (Jacco Krijnen (@jacco)) Date: Mon, 17 Jun 2024 14:10:22 -0400 Subject: [Git][ghc/ghc][wip/jacco/haddock/codeblock-highlighting] Add haddock tests for codeblock with highlighting Message-ID: <66707c0eb86e7_2fe0997d48a810439e@gitlab.mail> Jacco Krijnen pushed to branch wip/jacco/haddock/codeblock-highlighting at Glasgow Haskell Compiler / GHC Commits: bd520bee by Jacco Krijnen at 2024-06-17T20:10:05+02:00 Add haddock tests for codeblock with highlighting - - - - - 2 changed files: - + utils/haddock/html-test/ref/CodeblockHighlight2.html - + utils/haddock/html-test/src/CodeblockHighlight2.hs Changes: ===================================== utils/haddock/html-test/ref/CodeblockHighlight2.html ===================================== @@ -0,0 +1,120 @@ +CodeblockHighlight2
Safe HaskellNone

CodeblockHighlight2

Synopsis

Documentation

add :: Int -> Int -> Int #

The following codeblocks start at different indentation in the source, but + that should not be visible in the rendered html:

add :: Int -> Int -> Int
+add x y = x + y
mul :: Int -> Int -> Int
+mul x y = x * y
pow :: Int -> Int -> Int
+pow x y = x ^ y

main :: IO () #

The triple backtick notation can also be used without mentioning a language

runghc CodeBlockHighlight2.hs
===================================== utils/haddock/html-test/src/CodeblockHighlight2.hs ===================================== @@ -0,0 +1,29 @@ +module CodeblockHighlight2 where + +-- | The following codeblocks start at different indentation in the source, but +-- that should not be visible in the rendered html: +-- +-- ```haskell +-- add :: Int -> Int -> Int +-- add x y = x + y +-- ``` +-- +-- ```haskell +-- mul :: Int -> Int -> Int +-- mul x y = x * y +-- ``` +-- +--```haskell +--pow :: Int -> Int -> Int +--pow x y = x ^ y +--``` +add :: Int -> Int -> Int +add x y = x + y + +-- | The triple backtick notation can also be used without mentioning a language +-- +-- ``` +-- runghc CodeBlockHighlight2.hs +-- ``` +main :: IO () +main = putStrLn "Hello, Haskell!" View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bd520beea77ca0f0dd95d01eab79c846f1fc2be5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bd520beea77ca0f0dd95d01eab79c846f1fc2be5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 18:21:54 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Mon, 17 Jun 2024 14:21:54 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/bump-T17572 Message-ID: <66707ec2d04f1_2fe0999be6f010664c@gitlab.mail> Cheng Shao pushed new branch wip/bump-T17572 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/bump-T17572 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 19:57:48 2024 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Mon, 17 Jun 2024 15:57:48 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ttg-zurich] 14 commits: Add hack for #24623 Message-ID: <6670953c8357b_2fe09915064e011665f@gitlab.mail> Alan Zimmerman pushed to branch wip/kirchner/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - 5915b8d8 by Alan Zimmerman at 2024-06-17T18:31:52+01:00 TTG: Move SourceText from `Fixity` to `FixitySig` It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Precedes !12842, to simplify it - - - - - 0b90fd6c by romes at 2024-06-17T20:56:48+01:00 Split TTG orphans from internal `Fixity` data type Filling in missing instances and creating a separate "semantic" datatype are two different layers of abstraction, and so we should create two different modules for them. Fixed arrow desugaring bug. (This was dead code before.) Co-authored-by: Fabian Kirchner <kirchner at posteo.de> - - - - - fbf4dbaf by Alan Zimmerman at 2024-06-17T20:57:21+01:00 Fix failing test T20846 failed for printing prefix, not infix. ppr for HsCmdArrForm uses lexical fixity for the GhcPs case - - - - - 30 changed files: - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - + compiler/GHC/Hs/Basic.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Tidy/StaticPtrTable.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/PostProcess.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b2035eecfdcaa8b122113523e4e8fe76f58d7341...fbf4dbafb82e64613e40f10f4ef16bed28588163 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b2035eecfdcaa8b122113523e4e8fe76f58d7341...fbf4dbafb82e64613e40f10f4ef16bed28588163 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 20:07:45 2024 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Mon, 17 Jun 2024 16:07:45 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ttg-zurich] Fix failing test Message-ID: <66709791b8b77_2fe09917751e01251f1@gitlab.mail> Alan Zimmerman pushed to branch wip/kirchner/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: 9e065ec3 by Alan Zimmerman at 2024-06-17T21:07:32+01:00 Fix failing test T20846 failed for printing prefix, not infix. ppr for HsCmdArrForm uses lexical fixity for the GhcPs case - - - - - 1 changed file: - compiler/GHC/Hs/Expr.hs Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -1428,7 +1428,7 @@ ppr_cmd (HsCmdArrForm rn_fix (L _ op) ps_fix args) ppr_cmd_infix v | [arg1, arg2] <- args , case ghcPass @p of - GhcPs -> False + GhcPs -> ps_fix == Infix GhcRn -> isJust rn_fix || ps_fix == Infix GhcTc -> isJust rn_fix || ps_fix == Infix = hang (pprCmdArg (unLoc arg1)) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9e065ec30357bece8c22126b061688736fee2bee -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9e065ec30357bece8c22126b061688736fee2bee You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 20:12:21 2024 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Mon, 17 Jun 2024 16:12:21 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ttg-zurich] Fix failing test Message-ID: <667098a547eb7_2fe09918a2248128499@gitlab.mail> Alan Zimmerman pushed to branch wip/kirchner/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: e212f755 by Alan Zimmerman at 2024-06-17T21:12:10+01:00 Fix failing test T20846 failed for printing prefix, not infix. ppr for HsCmdArrForm uses lexical fixity for the GhcPs case - - - - - 2 changed files: - compiler/GHC/Hs/Expr.hs - compiler/GHC/Types/Fixity.hs Changes: ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -1428,7 +1428,7 @@ ppr_cmd (HsCmdArrForm rn_fix (L _ op) ps_fix args) ppr_cmd_infix v | [arg1, arg2] <- args , case ghcPass @p of - GhcPs -> False + GhcPs -> ps_fix == Infix GhcRn -> isJust rn_fix || ps_fix == Infix GhcTc -> isJust rn_fix || ps_fix == Infix = hang (pprCmdArg (unLoc arg1)) ===================================== compiler/GHC/Types/Fixity.hs ===================================== @@ -32,9 +32,6 @@ import Data.Data hiding (Fixity(..)) import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Basic (FixityDirection(..), LexicalFixity(..)) --- type instance XFixity (GhcPass _) = NoExtField --- type instance XXFixity (GhcPass _) = DataConCantHappen - -- | Fixity used internally in GHC, so that we don't have to take `GhcPass p` -- everywhere. -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e212f755a344474b23ea8d17cc2665cf937fed5a -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e212f755a344474b23ea8d17cc2665cf937fed5a You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 21:22:47 2024 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Mon, 17 Jun 2024 17:22:47 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ttg-zurich] TTG HsCmdArrForm: use GHC Fixity via extension point Message-ID: <6670a927ab62a_384d7b5af5b45605f@gitlab.mail> Alan Zimmerman pushed to branch wip/kirchner/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: 80083341 by Alan Zimmerman at 2024-06-17T22:21:21+01:00 TTG HsCmdArrForm: use GHC Fixity via extension point And simplify, stripping Fixity out of the Hs Syntax zone - - - - - 19 changed files: - compiler/GHC/Hs/Basic.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Parser.y - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Fixity.hs - compiler/GHC/Types/Fixity/Env.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Binds.hs - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - testsuite/tests/parser/should_compile/T20846.stderr - utils/check-exact/ExactPrint.hs - utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs - utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs - utils/haddock/haddock-api/src/Haddock/Types.hs Changes: ===================================== compiler/GHC/Hs/Basic.hs ===================================== @@ -8,52 +8,12 @@ module GHC.Hs.Basic ( module Language.Haskell.Syntax.Basic ) where -import GHC.Prelude - -import GHC.Hs.Extension - import GHC.Utils.Outputable -import GHC.Utils.Binary import Data.Data () -import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Basic -type instance XFixity (GhcPass _) = NoExtField -type instance XXFixity (GhcPass _) = DataConCantHappen - -instance Outputable FixityDirection where - ppr InfixL = text "infixl" - ppr InfixR = text "infixr" - ppr InfixN = text "infix" - -instance Binary FixityDirection where - put_ bh InfixL = - putByte bh 0 - put_ bh InfixR = - putByte bh 1 - put_ bh InfixN = - putByte bh 2 - get bh = do - h <- getByte bh - case h of - 0 -> return InfixL - 1 -> return InfixR - _ -> return InfixN - instance Outputable LexicalFixity where ppr Prefix = text "Prefix" ppr Infix = text "Infix" - -instance Outputable (Fixity (GhcPass p)) where - ppr (Fixity _ prec dir) = hcat [ppr dir, space, int prec] - -instance Binary (Fixity (GhcPass p)) where - put_ bh (Fixity _src aa ab) = do - put_ bh aa - put_ bh ab - get bh = do - aa <- get bh - ab <- get bh - return (Fixity noExtField aa ab) ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -32,6 +32,7 @@ import Language.Haskell.Syntax.Expr -- friends: import GHC.Prelude +import GHC.Hs.Basic() -- import instances import GHC.Hs.Decls() -- import instances import GHC.Hs.Pat import GHC.Hs.Lit ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -33,7 +33,6 @@ import GHC.Hs.Type import GHC.Hs.Pat import GHC.Hs.ImpExp import GHC.Parser.Annotation -import Language.Haskell.Syntax.Basic (Fixity(..)) -- --------------------------------------------------------------------- -- Data derivations from GHC.Hs----------------------------------------- @@ -574,12 +573,6 @@ deriving instance Data XXExprGhcRn -- --------------------------------------------------------------------- -deriving instance Data (Fixity GhcPs) -deriving instance Data (Fixity GhcRn) -deriving instance Data (Fixity GhcTc) - --- --------------------------------------------------------------------- - deriving instance Data XXExprGhcTc deriving instance Data XXPatGhcTc ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -90,7 +90,6 @@ import Data.Kind (Constraint) import qualified GHC.LanguageExtensions as LangExt import Language.Haskell.Syntax.Basic (FieldLabelString(..)) -import qualified Language.Haskell.Syntax.Basic as H import Data.ByteString ( unpack ) import Control.Monad @@ -781,7 +780,7 @@ repLFixD :: LFixitySig GhcRn -> MetaM [(SrcSpan, Core (M TH.Dec))] repLFixD (L loc fix_sig) = rep_fix_d (locA loc) fix_sig rep_fix_d :: SrcSpan -> FixitySig GhcRn -> MetaM [(SrcSpan, Core (M TH.Dec))] -rep_fix_d loc (FixitySig ns_spec names (H.Fixity _ prec dir)) +rep_fix_d loc (FixitySig ns_spec names (Fixity prec dir)) = do { MkC prec' <- coreIntLit prec ; let rep_fn = case dir of InfixL -> infixLWithSpecDName ===================================== compiler/GHC/Parser.y ===================================== @@ -71,7 +71,7 @@ import GHC.Types.Name.Occurrence ( varName, dataName, tcClsName, tvName, occName import GHC.Types.SrcLoc import GHC.Types.Basic import GHC.Types.Error ( GhcHint(..) ) -import GHC.Types.Fixity hiding (Fixity(..)) +import GHC.Types.Fixity import GHC.Types.ForeignCall import GHC.Types.SourceFile import GHC.Types.SourceText @@ -98,8 +98,6 @@ import GHC.Builtin.Types ( unitTyCon, unitDataCon, sumTyCon, import Language.Haskell.Syntax.Basic (FieldLabelString(..)) import qualified Data.Semigroup as Semi - -import Language.Haskell.Syntax.Basic (Fixity(..)) } %expect 0 -- shift/reduce conflicts @@ -2682,7 +2680,7 @@ sigdecl :: { LHsDecl GhcPs } Just l2 -> (fst $ unLoc l2, snd $ unLoc l2) ; amsA' (sLL $1 $> $ SigD noExtField (FixSig (mj AnnInfix $1 : maybeToList mbPrecAnn, fixText) (FixitySig (unLoc $3) (fromOL $ unLoc $4) - (Fixity noExtField fixPrec (unLoc $1))))) + (Fixity fixPrec (unLoc $1))))) }} | pattern_synonym_sig { L (getLoc $1) . SigD noExtField . unLoc $ $1 } ===================================== compiler/GHC/Rename/Bind.hs ===================================== @@ -52,7 +52,6 @@ import GHC.Driver.DynFlags import GHC.Unit.Module import GHC.Types.Error import GHC.Types.FieldLabel -import GHC.Types.Fixity import GHC.Types.Name import GHC.Types.Name.Env import GHC.Types.Name.Set @@ -72,7 +71,6 @@ import GHC.Data.OrdList import qualified GHC.LanguageExtensions as LangExt import Language.Haskell.Syntax.Basic (FieldLabelString(..)) -import qualified Language.Haskell.Syntax.Basic as H import Control.Monad import Data.List ( partition ) @@ -695,7 +693,7 @@ makeMiniFixityEnv decls = foldlM add_one_sig emptyMiniFixityEnv decls where add_one_sig :: MiniFixityEnv -> LFixitySig GhcPs -> RnM MiniFixityEnv add_one_sig env (L loc (FixitySig ns_spec names fixity)) = - foldlM add_one env [ (locA loc, locA name_loc, name, fixityFromSyntax fixity, ns_spec) + foldlM add_one env [ (locA loc,locA name_loc,name,fixity, ns_spec) | L name_loc name <- names ] add_one env (loc, name_loc, name, fixity, ns_spec) = do @@ -1403,12 +1401,12 @@ rnSrcFixityDecl sig_ctxt = rn_decl -- for con-like things; hence returning a list -- If neither are in scope, report an error; otherwise -- return a fixity sig for each (slightly odd) - rn_decl sig@(FixitySig ns_spec fnames (H.Fixity x a b)) + rn_decl sig@(FixitySig ns_spec fnames fixity) = do unlessXOptM LangExt.ExplicitNamespaces $ when (ns_spec /= NoNamespaceSpecifier) $ addErr (TcRnNamespacedFixitySigWithoutFlag sig) names <- concatMapM (lookup_one ns_spec) fnames - return (FixitySig ns_spec names $ H.Fixity x a b) + return (FixitySig ns_spec names fixity) lookup_one :: NamespaceSpecifier -> LocatedN RdrName -> RnM [LocatedN Name] lookup_one ns_spec (L name_loc rdr_name) ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -77,10 +77,10 @@ import qualified GHC.LanguageExtensions as LangExt import Language.Haskell.Syntax.Basic (FieldLabelString(..)) -import Control.Arrow (first) import Control.Monad import Data.List (unzip4, minimumBy) import Data.List.NonEmpty ( NonEmpty(..), nonEmpty ) +import Control.Arrow (first) import Data.Ord import Data.Array import qualified Data.List.NonEmpty as NE ===================================== compiler/GHC/ThToHs.hs ===================================== @@ -64,7 +64,6 @@ import Foreign.ForeignPtr import Foreign.Ptr import System.IO.Unsafe -import qualified Language.Haskell.Syntax.Basic as HSyn (Fixity(..)) ------------------------------------------------------------------- -- The external interface @@ -1984,8 +1983,8 @@ cvtPatSynSigTy (ForallT univs reqs (ForallT exis provs ty)) cvtPatSynSigTy ty = cvtSigType ty ----------------------------------------------------------- -cvtFixity :: TH.Fixity -> HSyn.Fixity (GhcPass p) -cvtFixity (TH.Fixity prec dir) = HSyn.Fixity noExtField prec (cvt_dir dir) +cvtFixity :: TH.Fixity -> Hs.Fixity +cvtFixity (TH.Fixity prec dir) = Hs.Fixity prec (cvt_dir dir) where cvt_dir TH.InfixL = Hs.InfixL cvt_dir TH.InfixR = Hs.InfixR ===================================== compiler/GHC/Types/Fixity.hs ===================================== @@ -1,6 +1,3 @@ -{-# OPTIONS_GHC -Wno-orphans #-} -- Outputable, Binary, Eq -{-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DeriveDataTypeable #-} -- | Fixity @@ -14,36 +11,26 @@ module GHC.Types.Fixity , negateFixity , funTyFixity , compareFixity - , fixityFromSyntax - , fixityToSyntax ) where import GHC.Prelude -import GHC.Hs.Extension -import qualified GHC.Hs.Basic as H - import GHC.Utils.Outputable import GHC.Utils.Binary -import Data.Data hiding (Fixity(..)) - -import Language.Haskell.Syntax.Extension -import Language.Haskell.Syntax.Basic (FixityDirection(..), LexicalFixity(..)) +import Data.Data hiding (Fixity, Prefix, Infix) +import Language.Haskell.Syntax.Basic (LexicalFixity(..)) --- | Fixity used internally in GHC, so that we don't have to take `GhcPass p` --- everywhere. --- --- The Fixity defined in the AST is converted to this Fixity --- --- See `fixityFromSyntax` data Fixity = Fixity Int FixityDirection - deriving (Eq, Data) + deriving Data instance Outputable Fixity where ppr (Fixity prec dir) = hcat [ppr dir, space, int prec] +instance Eq Fixity where -- Used to determine if two fixities conflict + (Fixity p1 dir1) == (Fixity p2 dir2) = p1==p2 && dir1 == dir2 + instance Binary Fixity where put_ bh (Fixity aa ab) = do put_ bh aa @@ -53,6 +40,32 @@ instance Binary Fixity where ab <- get bh return (Fixity aa ab) +------------------------ +data FixityDirection + = InfixL + | InfixR + | InfixN + deriving (Eq, Data) + +instance Outputable FixityDirection where + ppr InfixL = text "infixl" + ppr InfixR = text "infixr" + ppr InfixN = text "infix" + +instance Binary FixityDirection where + put_ bh InfixL = + putByte bh 0 + put_ bh InfixR = + putByte bh 1 + put_ bh InfixN = + putByte bh 2 + get bh = do + h <- getByte bh + case h of + 0 -> return InfixL + 1 -> return InfixR + _ -> return InfixN + ------------------------ maxPrecedence, minPrecedence :: Int maxPrecedence = 9 @@ -91,9 +104,3 @@ compareFixity (Fixity prec1 dir1) (Fixity prec2 dir2) right = (False, True) left = (False, False) error_please = (True, False) - -fixityFromSyntax :: H.Fixity (GhcPass p) -> Fixity -fixityFromSyntax (H.Fixity _ i d) = Fixity i d - -fixityToSyntax :: Fixity -> H.Fixity (GhcPass p) -fixityToSyntax (Fixity i d) = H.Fixity noExtField i d ===================================== compiler/GHC/Types/Fixity/Env.hs ===================================== @@ -1,5 +1,3 @@ -{-# LANGUAGE ExistentialQuantification #-} -{-# LANGUAGE FlexibleInstances #-} module GHC.Types.Fixity.Env ( FixityEnv , FixItem (..) @@ -33,7 +31,7 @@ emptyFixityEnv = emptyNameEnv lookupFixity :: FixityEnv -> Name -> Fixity lookupFixity env n = case lookupNameEnv env n of - Just (FixItem _ (Fixity a b)) -> Fixity a b + Just (FixItem _ fix) -> fix Nothing -> defaultFixity -- | Creates cached lookup for the 'mi_fix_fn' field of 'ModIface' @@ -45,4 +43,3 @@ mkIfaceFixCache pairs emptyIfaceFixCache :: OccName -> Maybe Fixity emptyIfaceFixCache _ = Nothing - ===================================== compiler/Language/Haskell/Syntax/Basic.hs ===================================== @@ -2,8 +2,6 @@ {-# LANGUAGE GeneralisedNewtypeDeriving #-} module Language.Haskell.Syntax.Basic where -import Language.Haskell.Syntax.Extension - import Data.Data import Data.Eq import Data.Ord @@ -99,23 +97,6 @@ data SrcUnpackedness = SrcUnpack -- ^ {-# UNPACK #-} specified | NoSrcUnpack -- ^ no unpack pragma deriving (Eq, Data) -{- -************************************************************************ -* * -Fixity -* * -************************************************************************ --} - -data Fixity pass = Fixity (XFixity pass) Int FixityDirection - | XFixity !(XXFixity pass) - -data FixityDirection - = InfixL - | InfixR - | InfixN - deriving (Eq, Data) - -- | Captures the fixity of declarations as they are parsed. This is not -- necessarily the same as the fixity declaration, as the normal fixity may be -- overridden using parens or backticks. ===================================== compiler/Language/Haskell/Syntax/Binds.hs ===================================== @@ -30,9 +30,9 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Pat ( LPat ) import Language.Haskell.Syntax.Extension -import Language.Haskell.Syntax.Basic (Fixity) import Language.Haskell.Syntax.Type +import GHC.Types.Fixity (Fixity) import GHC.Data.Bag (Bag) import GHC.Types.Basic (InlinePragma) @@ -495,7 +495,7 @@ data Sig pass type LFixitySig pass = XRec pass (FixitySig pass) -- | Fixity Signature -data FixitySig pass = FixitySig (XFixitySig pass) [LIdP pass] (Fixity pass) +data FixitySig pass = FixitySig (XFixitySig pass) [LIdP pass] Fixity | XFixitySig !(XXFixitySig pass) isFixityLSig :: forall p. UnXRec p => LSig p -> Bool ===================================== compiler/Language/Haskell/Syntax/Decls.hs ===================================== @@ -97,11 +97,12 @@ import {-# SOURCE #-} Language.Haskell.Syntax.Expr import Language.Haskell.Syntax.Binds import Language.Haskell.Syntax.Extension import Language.Haskell.Syntax.Type -import Language.Haskell.Syntax.Basic (Role, LexicalFixity) +import Language.Haskell.Syntax.Basic (Role) import GHC.Types.Basic (TopLevelFlag, OverlapMode, RuleName, Activation ,TyConFlavour(..), TypeOrData(..)) import GHC.Types.ForeignCall (CType, CCallConv, Safety, Header, CLabelString, CCallTarget, CExportSpec) +import GHC.Types.Fixity (LexicalFixity) import GHC.Core.Type (Specificity) import GHC.Unit.Module.Warnings (WarningTxt) ===================================== compiler/Language/Haskell/Syntax/Extension.hs ===================================== @@ -722,12 +722,6 @@ type family XXIEWrappedName p --- ===================================================================== --- Type families for the type families in L.H.S.Basic - -type family XFixity x -type family XXFixity x - -- ===================================================================== -- Misc ===================================== testsuite/tests/parser/should_compile/T20846.stderr ===================================== @@ -59,7 +59,6 @@ (Unqual {OccName: ++++}))] (Fixity - (NoExtField) (9) (InfixR)))))) ,(L ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -39,6 +39,7 @@ import qualified GHC.Data.BooleanFormula as BF import GHC.Data.FastString import GHC.TypeLits import GHC.Types.Basic hiding (EP) +import GHC.Types.Fixity import GHC.Types.ForeignCall import GHC.Types.Name.Reader import GHC.Types.PkgQual @@ -49,7 +50,7 @@ import GHC.Unit.Module.Warnings import GHC.Utils.Misc import GHC.Utils.Panic -import Language.Haskell.Syntax.Basic (FieldLabelString(..), Fixity(..)) +import Language.Haskell.Syntax.Basic (FieldLabelString(..)) import Control.Monad (forM, when, unless) import Control.Monad.Identity (Identity(..)) @@ -2760,7 +2761,7 @@ instance ExactPrint (Sig GhcPs) where (an0, vars',ty') <- exactVarSig an vars ty return (ClassOpSig an0 is_deflt vars' ty') - exact (FixSig (an,src) (FixitySig x names (Fixity xf v fdir))) = do + exact (FixSig (an,src) (FixitySig x names (Fixity v fdir))) = do let fixstr = case fdir of InfixL -> "infixl" InfixR -> "infixr" @@ -2768,7 +2769,7 @@ instance ExactPrint (Sig GhcPs) where an0 <- markEpAnnLMS'' an lidl AnnInfix (Just fixstr) an1 <- markEpAnnLMS'' an0 lidl AnnVal (Just (sourceTextToString src (show v))) names' <- markAnnotated names - return (FixSig (an1,src) (FixitySig x names' (Fixity xf v fdir))) + return (FixSig (an1,src) (FixitySig x names' (Fixity v fdir))) exact (InlineSig an ln inl) = do an0 <- markAnnOpen an (inl_src inl) "{-# INLINE" ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Hoogle.hs ===================================== @@ -33,7 +33,6 @@ import GHC import GHC.Core.InstEnv import GHC.Driver.Ppr import GHC.Plugins (TopLevelFlag (..)) -import GHC.Types.Fixity (fixityToSyntax) import GHC.Types.SourceText import GHC.Unit.State import GHC.Utils.Outputable as Outputable @@ -360,7 +359,7 @@ ppCtor mkFunTy a b = noLocA (HsFunTy noExtField (HsUnrestrictedArrow noExtField) a b) ppFixity :: DynFlags -> (Name, Fixity) -> [String] -ppFixity dflags (name, fixity) = [out dflags ((FixitySig NoNamespaceSpecifier [noLocA name] (fixityToSyntax fixity)) :: FixitySig GhcRn)] +ppFixity dflags (name, fixity) = [out dflags ((FixitySig NoNamespaceSpecifier [noLocA name] fixity) :: FixitySig GhcRn)] --------------------------------------------------------------------- -- DOCUMENTATION ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Rename.hs ===================================== @@ -23,14 +23,13 @@ import Data.Traversable (mapM) import Haddock.Backends.Hoogle (ppExportD) import Haddock.GhcUtils -import Haddock.Types hiding (Fixity) +import Haddock.Types -import GHC hiding (Fixity, NoLink) +import GHC hiding (NoLink) import GHC.Builtin.Types (eqTyCon_RDR, tupleDataConName, tupleTyConName) import GHC.Data.Bag (emptyBag) import GHC.Types.Name import GHC.Types.Name.Reader (RdrName (Exact)) -import Language.Haskell.Syntax.Basic (Fixity(..)) import Control.Applicative import Control.DeepSeq (force) @@ -764,9 +763,9 @@ renameSig sig = case sig of lnames' <- mapM renameNameL lnames sig_ty' <- renameLSigType sig_ty return $ PatSynSig noExtField lnames' sig_ty' - FixSig _ (FixitySig _ lnames (Fixity _ i d)) -> do + FixSig _ (FixitySig _ lnames fixity) -> do lnames' <- mapM renameNameL lnames - return $ FixSig noExtField (FixitySig noExtField lnames' (Fixity noExtField i d)) + return $ FixSig noExtField (FixitySig noExtField lnames' fixity) MinimalSig _ (L l s) -> do s' <- traverse (traverse lookupRn) s return $ MinimalSig noExtField (L l s') ===================================== utils/haddock/haddock-api/src/Haddock/Types.hs ===================================== @@ -880,14 +880,12 @@ type instance XXTyVarBndr DocNameI = DataConCantHappen type instance XCFieldOcc DocNameI = DocName type instance XXFieldOcc DocNameI = NoExtField -type instance XFixity DocNameI = NoExtField type instance XFixitySig DocNameI = NoExtField type instance XFixSig DocNameI = NoExtField type instance XPatSynSig DocNameI = NoExtField type instance XClassOpSig DocNameI = NoExtField type instance XTypeSig DocNameI = NoExtField type instance XMinimalSig DocNameI = NoExtField -type instance XXFixity DocNameI = DataConCantHappen type instance XForeignExport DocNameI = NoExtField type instance XForeignImport DocNameI = NoExtField View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8008334174728e39b4aacf21158a6dd7bf8f524e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8008334174728e39b4aacf21158a6dd7bf8f524e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Mon Jun 17 22:49:54 2024 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Mon, 17 Jun 2024 18:49:54 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/andreask/bound_cmm_folding Message-ID: <6670bd9266865_384d7b1010eb863297@gitlab.mail> Andreas Klebinger pushed new branch wip/andreask/bound_cmm_folding at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/andreask/bound_cmm_folding You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 04:15:45 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 18 Jun 2024 00:15:45 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: Clarify -XGADTs enables existential quantification Message-ID: <667109f1bfd24_55913165497853122@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 6bad0de7 by sheaf at 2024-06-18T00:15:09-04:00 Clarify -XGADTs enables existential quantification Even though -XGADTs does not turn on -XExistentialQuantification, it does allow the user of existential quantification syntax, without needing to use GADT-style syntax. Fixes #20865 - - - - - 1f005635 by David Binder at 2024-06-18T00:15:13-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - 5a3c2dca by Andreas Klebinger at 2024-06-18T00:15:13-04:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - d4ffd058 by Jakob Bruenker at 2024-06-18T00:15:15-04:00 Update user guide to indicate support for 64-tuples - - - - - 754d4d2c by Andreas Klebinger at 2024-06-18T00:15:15-04:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 379ed573 by Andreas Klebinger at 2024-06-18T00:15:17-04:00 GHCi interpreter: Tag constructor closures when possible. When evaluating PUSH_G try to tag the reference we are pushing if it's a constructor or function. This is potentially helpful for performance and required to fix #24870. - - - - - 3c350a5c by Jakob Bruenker at 2024-06-18T00:15:18-04:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 35de8a60 by Sjoerd Visscher at 2024-06-18T00:15:24-04:00 Bump stm submodule to current master - - - - - 28 changed files: - compiler/GHC/Builtin/Types.hs - compiler/GHC/ByteCode/Instr.hs - docs/users_guide/9.12.1-notes.rst - docs/users_guide/bugs.rst - docs/users_guide/exts/gadt.rst - docs/users_guide/exts/representation_polymorphism.rst - docs/users_guide/profiling.rst - docs/users_guide/runtime_control.rst - libraries/base/changelog.md - libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc - libraries/ghc-internal/src/GHC/Internal/Unsafe/Coerce.hs - libraries/ghc-prim/GHC/Types.hs - libraries/stm - linters/lint-notes/Main.hs - rts/Hpc.c - rts/Interpreter.c - rts/RtsFlags.c - rts/include/rts/Flags.h - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - testsuite/tests/linters/notes.stdout - + testsuite/tests/th/should_compile/T24870/Def.hs - + testsuite/tests/th/should_compile/T24870/T24870.stderr - + testsuite/tests/th/should_compile/T24870/T24870.stderr-mingw32 - + testsuite/tests/th/should_compile/T24870/Use.hs - + testsuite/tests/th/should_compile/T24870/all.T Changes: ===================================== compiler/GHC/Builtin/Types.hs ===================================== @@ -445,7 +445,15 @@ It has these properties: * When instantiated at a lifted type it is inhabited by at least one value, namely bottom - * You can safely coerce any /lifted/ type to Any, and back with unsafeCoerce. + * You can safely coerce any /lifted/ type to Any and back with unsafeCoerce. + You can safely coerce any /unlifted/ type to Any and back with unsafeCoerceUnlifted. + You can coerce /any/ type to Any and back with unsafeCoerce#, but it's only safe when + the kinds of both the type and Any match. + + For lifted/unlifted types unsafeCoerce[Unlifted] should be preferred over unsafeCoerce# + as they prevent accidentally coercing between types with kinds that don't match. + + See examples in ghc-prim:GHC.Types * It does not claim to be a *data* type, and that's important for the code generator, because the code gen may *enter* a data value ===================================== compiler/GHC/ByteCode/Instr.hs ===================================== @@ -83,7 +83,7 @@ data BCInstr | PUSH16_W !ByteOff | PUSH32_W !ByteOff - -- Push a ptr (these all map to PUSH_G really) + -- Push a (heap) ptr (these all map to PUSH_G really) | PUSH_G Name | PUSH_PRIMOP PrimOp | PUSH_BCO (ProtoBCO Name) ===================================== docs/users_guide/9.12.1-notes.rst ===================================== @@ -91,6 +91,11 @@ Runtime system - Reduce fragmentation incurred by the nonmoving GC's segment allocator. In one application this reduced resident set size by 26%. See :ghc-ticket:`24150`. +- The new runtime flag :rts-flag:`--read-tix-file=\` allows to modify whether a preexisting .tix file is read in at the beginning of a program run. + The default is currently ``--read-tix-file=yes`` but will change to ``--read-tix-file=no`` in a future version of GHC. + For this reason, a warning is emitted if a .tix file is read in implicitly. You can silence this warning by explicitly passing ``--read-tix-file=yes``. + Details can be found in `GHC proposal 612 `__. + ``base`` library ~~~~~~~~~~~~~~~~ ===================================== docs/users_guide/bugs.rst ===================================== @@ -553,7 +553,7 @@ Unchecked floating-point arithmetic Large tuple support The Haskell Report only requires implementations to provide tuple types and their accompanying standard instances up to size 15. GHC - limits the size of tuple types to 62 and provides instances of + limits the size of tuple types to 64 and provides instances of ``Eq``, ``Ord``, ``Bounded``, ``Read``, ``Show``, and ``Ix`` for tuples up to size 15. ===================================== docs/users_guide/exts/gadt.rst ===================================== @@ -93,6 +93,12 @@ also sets :extension:`GADTSyntax` and :extension:`MonoLocalBinds`. -- essentially the same as: -- MkG :: Int -> Int -> G Int + Note that, even though :extension:`GADTs` technically does not imply + :extension:`ExistentialQuantification`, enabling :extension:`GADTs` + does also enable the syntax for existential quantification: :: + + data SomeShow = forall a. Show a => SomeShow a + - It is permitted to declare an ordinary algebraic data type using GADT-style syntax. What makes a GADT into a GADT is not the syntax, but rather the presence of data constructors whose result type is not ===================================== docs/users_guide/exts/representation_polymorphism.rst ===================================== @@ -79,14 +79,26 @@ representation-polymorphic type. However, not all is lost. We can still do this: :: - ($) :: forall r (a :: Type) (b :: TYPE r). + good :: forall r (a :: Type) (b :: TYPE r). (a -> b) -> a -> b - f $ x = f x + good f x = f x Here, only ``b`` is representation-polymorphic. There are no variables with a representation-polymorphic type. And the code generator has no -trouble with this. Indeed, this is the true type of GHC's ``$`` operator, -slightly more general than the Haskell 98 version. +trouble with this. Nonetheless, there is a way to write a definition with +``bad``'s type: :: + + + ($) :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) + (a :: TYPE r1) (b :: TYPE r2). + (a -> b) -> a -> b + ($) f = f + +By eta-reducing, we got rid of ``x``, and thus have no variable with a +representation-polymorphic type. Indeed, this is the true type of GHC's ``$`` +operator, slightly more general than the Haskell 98 version. However, its +strictness properties are different: ``(good undefined) `seq` ()`` is equivalent +to ``()``, whereas ``(($) undefined) `seq` ()`` diverges. Because the code generator must store and move arguments as well as variables, the logic above applies equally well to function arguments, ===================================== docs/users_guide/profiling.rst ===================================== @@ -1502,9 +1502,9 @@ Running the program generates a file with the ``.tix`` suffix, in this case :file:`Recip.tix`, which contains the coverage data for this run of the program. The program may be run multiple times (e.g. with different test data), and the coverage data from the separate runs is accumulated in -the ``.tix`` file. To reset the coverage data and start again, just -remove the ``.tix`` file. You can control where the ``.tix`` file -is generated using the environment variable :envvar:`HPCTIXFILE`. +the ``.tix`` file. This behaviour can be controlled with the :rts-flag:`--read-tix-file=\` +You can control where the ``.tix`` file is generated using the +environment variable :envvar:`HPCTIXFILE`. .. envvar:: HPCTIXFILE ===================================== docs/users_guide/runtime_control.rst ===================================== @@ -1373,7 +1373,22 @@ and can be controlled by the following flags. .. index:: single: RTS options, hpc -.. rts-flag:: --write-tix-file +.. rts-flag:: --read-tix-file= + + :default: enabled + :since: 9.12 + + The RTS can be instructed to read a ``.tix`` file during the startup + phase. The datastructures which accumulate the coverage information during + program execution are then initialized with the information from this file. + This option is useful for aggregating coverage information over multiple runs + of an executable. + + The default for this flag is currently ``--read-tix-file=yes`` but will change + to ``-read-tix-file=no`` in a future version of GHC according to the accepted + `GHC proposal 612 `__. + +.. rts-flag:: --write-tix-file= :default: enabled :since: 9.10 ===================================== libraries/base/changelog.md ===================================== @@ -1,6 +1,7 @@ # Changelog for [`base` package](http://hackage.haskell.org/package/base) ## 4.21.0.0 *TBA* + * Add a `readTixFile` field to the `HpcFlags` record in `GHC.RTS.Flags` ([CLC proposal #276](https://github.com/haskell/core-libraries-committee/issues/276)) * Add the `MonadFix` instance for `(,) a`, similar to the one for `Writer a` ([CLC proposal #238](https://github.com/haskell/core-libraries-committee/issues/238)) * Improve `toInteger :: Word32 -> Integer` on 64-bit platforms ([CLC proposal #259](https://github.com/haskell/core-libraries-committee/issues/259)) * Make `flip` representation polymorphic ([CLC proposal #245](https://github.com/haskell/core-libraries-committee/issues/245)) ===================================== libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc ===================================== @@ -382,7 +382,11 @@ data ParFlags = ParFlags -- -- @since base-4.20.0.0 data HpcFlags = HpcFlags - { writeTixFile :: Bool + { readTixFile :: Bool + -- ^ Controls whether a @.tix@ file is read at + -- the start of execution to initialize the RTS internal + -- HPC datastructures. + , writeTixFile :: Bool -- ^ Controls whether the @.tix@ file should be -- written after the execution of the program. } @@ -498,6 +502,8 @@ getHpcFlags = do let ptr = (#ptr RTS_FLAGS, HpcFlags) rtsFlagsPtr HpcFlags <$> (toBool <$> + (#{peek HPC_FLAGS, readTixFile} ptr :: IO CBool)) + <*> (toBool <$> (#{peek HPC_FLAGS, writeTixFile} ptr :: IO CBool)) getConcFlags :: IO ConcFlags ===================================== libraries/ghc-internal/src/GHC/Internal/Unsafe/Coerce.hs ===================================== @@ -336,6 +336,10 @@ unsafeCoerceAddr x = case unsafeEqualityProof @a @b of UnsafeRefl -> x -- to another. Misuse of this function can invite the garbage collector -- to trounce upon your data and then laugh in your face. You don't want -- this function. Really. +-- +-- This becomes more obvious when looking at its actual type: +-- @forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) (a :: TYPE r1) (b :: TYPE r2). a -> b@ +-- Which often get's rendered as @a -> b@ in haddock for technical reasons. unsafeCoerce# :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) (a :: TYPE r1) (b :: TYPE r2). a -> b ===================================== libraries/ghc-prim/GHC/Types.hs ===================================== @@ -283,11 +283,43 @@ data Symbol * * ********************************************************************* -} --- | The type constructor 'Any' is type to which you can unsafely coerce any --- lifted type, and back. More concretely, for a lifted type @t@ and --- value @x :: t@, @unsafeCoerce (unsafeCoerce x :: Any) :: t@ is equivalent --- to @x at . +-- | The type constructor @Any :: forall k. k@ is a type to which you can unsafely coerce any type, and back. -- +-- For @unsafeCoerce@ this means for all lifted types @t@ that +-- @unsafeCoerce (unsafeCoerce x :: Any) :: t@ is equivalent to @x@ and safe. +-- +-- The same is true for *all* types when using +-- @ +-- unsafeCoerce# :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) +-- (a :: TYPE r1) (b :: TYPE r2). +-- a -> b +-- @ +-- but /only/ if you instantiate @r1@ and @r2@ to the /same/ runtime representation. +-- For example using @(unsafeCoerce# :: forall (a :: TYPE IntRep) (b :: TYPE IntRep). a -> b) x@ +-- is fine, but @(unsafeCoerce# :: forall (a :: TYPE IntRep) (b :: TYPE FloatRep). a -> b)@ +-- will likely cause seg-faults or worse. +-- For this resason, users should always prefer unsafeCoerce over unsafeCoerce# when possible. +-- +-- Here are some more examples: +-- @ +-- bad_a1 :: Any @(TYPE 'IntRep) +-- bad_a1 = unsafeCoerce# True +-- +-- bad_a2 :: Any @(TYPE ('BoxedRep 'UnliftedRep)) +-- bad_a2 = unsafeCoerce# True +-- @ +-- Here @bad_a1@ is bad because we started with @True :: (Bool :: Type)@, represented by a boxed heap pointer, +-- and coerced it to @a1 :: Any @(TYPE 'IntRep)@, whose representation is a non-pointer integer. +-- That's why we had to use `unsafeCoerce#`; it is really unsafe because it can change representations. +-- Similarly @bad_a2@ is bad because although both @True@ and @bad_a2@ are represented by a heap pointer, +-- @True@ is lifted but @bad_a2@ is not; bugs here may be rather subtle. +-- +-- If you must use unsafeCoerce# to cast to `Any`, type annotations are recommended +-- to make sure that @Any@ has the correct kind. As casting between different runtimereps is +-- unsound. For example to cast a @ByteArray#@ to @Any@ you might use: +-- @ +-- unsafeCoerce# b :: (Any :: TYPE ('BoxedRep 'Unlifted)) +-- @ type family Any :: k where { } -- See Note [Any types] in GHC.Builtin.Types. Also, for a bit of history on Any see -- #10886. Note that this must be a *closed* type family: we need to ensure ===================================== libraries/stm ===================================== @@ -1 +1 @@ -Subproject commit 4e7aa7885b3f9724b19e68d12cbd2774b11b9bd0 +Subproject commit 8de008f1928e029e54b822d85a16f1804d7e99a6 ===================================== linters/lint-notes/Main.hs ===================================== @@ -37,7 +37,9 @@ main = do parseMode "unreferenced" = Just $ printNoteDefs . S.toList . unreferencedNotes parseMode "defs" = Just $ printNoteDefs . allNoteDefs parseMode "refs" = Just $ printNoteRefs . allNoteRefs - parseMode "broken-refs" = Just $ printNoteRefs . map fst . brokenNoteRefs + parseMode "broken-refs" = Just $ \notedb -> do + putStrLn "Broken note references (target note not found!):" + printNoteRefs . map fst . brokenNoteRefs $ notedb parseMode "broken-refs-suggest" = Just $ mapM_ printNoteRefsSugg . brokenNoteRefs parseMode _ = Nothing ===================================== rts/Hpc.c ===================================== @@ -236,7 +236,14 @@ startupHpc(void) sprintf(tixFilename, "%s.tix", prog_name); } - if (init_open(__rts_fopen(tixFilename,"r"))) { + if ((RtsFlags.HpcFlags.readTixFile == HPC_YES_IMPLICIT) && init_open(__rts_fopen(tixFilename,"r"))) { + fprintf(stderr,"Deprecation warning:\n" + "I am reading in the existing tix file, and will add hpc info from this run to the existing data in that file.\n" + "GHC 9.14 will cease looking for an existing tix file by default.\n" + "If you positively want to add hpc info to the current tix file, use the RTS option --read-tix-file=yes.\n" + "More information can be found in the accepted GHC proposal 612.\n"); + readTix(); + } else if ((RtsFlags.HpcFlags.readTixFile == HPC_YES_EXPLICIT) && init_open(__rts_fopen(tixFilename,"r"))) { readTix(); } } ===================================== rts/Interpreter.c ===================================== @@ -4,6 +4,30 @@ * Copyright (c) The GHC Team, 1994-2002. * ---------------------------------------------------------------------------*/ +/* +Note [CBV Functions and the interpreter] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +When the byte code interpreter loads a reference to a value it often +ends up as a non-tagged pointers *especially* if we already know a value +is a certain constructor and therefore don't perform an eval on the reference. +This causes friction with CBV functions which assume +their value arguments are properly tagged by the caller. + +In order to ensure CBV functions still get passed tagged functions we have +three options: +a) Special case the interpreter behaviour into the tag inference analysis. + If we assume the interpreter can't properly tag value references the STG passes + would then wrap such calls in appropriate evals which are executed at runtime. + This would ensure tags by doing additional evals at runtime. +b) When the interpreter pushes references for known constructors instead of + pushing the objects address add the tag to the value pushed. This is what + the NCG backends do. +c) When the interpreter pushes a reference inspect the closure of the object + and apply the appropriate tag at runtime. + +For now we use approach c). Mostly because it's easiest to implement. We also don't +tag functions as tag inference currently doesn't rely on those being properly tagged. +*/ #include "rts/PosixSource.h" #include "Rts.h" @@ -290,6 +314,18 @@ STATIC_INLINE StgClosure *tagConstr(StgClosure *con) { return TAG_CLOSURE(stg_min(TAG_MASK, 1 + GET_TAG(con)), con); } +// Compute the pointer tag for the function and tag the pointer; +STATIC_INLINE StgClosure *tagFun(StgClosure *fun) { + StgHalfWord tag = GET_TAG(fun); + if(tag > TAG_MASK) { return fun; } + else { + return TAG_CLOSURE(tag, fun); + } + + +} + + static StgWord app_ptrs_itbl[] = { (W_)&stg_ap_p_info, (W_)&stg_ap_pp_info, @@ -1304,7 +1340,52 @@ run_BCO: case bci_PUSH_G: { W_ o1 = BCO_GET_LARGE_ARG; - SpW(-1) = BCO_PTR(o1); + StgClosure *tagged_obj = (StgClosure*) BCO_PTR(o1); + + tag_push_g: + ASSERT(LOOKS_LIKE_CLOSURE_PTR((StgClosure*) tagged_obj)); + // Here we make sure references we push are tagged. + // See Note [CBV Functions and the interpreter] in Info.hs + + //Safe some memory reads if we already have a tag. + if(GET_CLOSURE_TAG(tagged_obj) == 0) { + StgClosure *obj = UNTAG_CLOSURE(tagged_obj); + switch ( get_itbl(obj)->type ) { + case IND: + case IND_STATIC: + { + tagged_obj = ACQUIRE_LOAD(&((StgInd*)obj)->indirectee); + goto tag_push_g; + } + case CONSTR: + case CONSTR_1_0: + case CONSTR_0_1: + case CONSTR_2_0: + case CONSTR_1_1: + case CONSTR_0_2: + case CONSTR_NOCAF: + // The value is already evaluated, so we can just return it. However, + // before we do, we MUST ensure that the pointer is tagged, because we + // might return to a native `case` expression, which assumes the returned + // pointer is tagged so it can use the tag to select an alternative. + tagged_obj = tagConstr(obj); + break; + case FUN: + case FUN_1_0: + case FUN_0_1: + case FUN_2_0: + case FUN_1_1: + case FUN_0_2: + case FUN_STATIC: + // Purely for performance since we already hit memory anyway. + tagged_obj = tagFun(obj); + break; + default: + break; + } + } + + SpW(-1) = (W_) tagged_obj; Sp_subW(1); goto nextInsn; } ===================================== rts/RtsFlags.c ===================================== @@ -297,6 +297,7 @@ void initRtsFlagsDefaults(void) RtsFlags.TickyFlags.showTickyStats = false; RtsFlags.TickyFlags.tickyFile = NULL; #endif + RtsFlags.HpcFlags.readTixFile = HPC_YES_IMPLICIT; RtsFlags.HpcFlags.writeTixFile = true; } @@ -565,6 +566,10 @@ usage_text[] = { " HeapOverflow exception before the exception is thrown again, if", " the program is still exceeding the heap limit.", "", +" --read-tix-file=", +" Whether to initialize HPC datastructures from .tix " +" at the start of execution. (default: yes)", +"", " --write-tix-file=", " Whether to write .tix at the end of execution.", " (default: yes)", @@ -1068,6 +1073,16 @@ error = true; RtsFlags.GcFlags.nonmovingDenseAllocatorCount = threshold; } } + else if (strequal("read-tix-file=yes", + &rts_argv[arg][2])) { + OPTION_UNSAFE; + RtsFlags.HpcFlags.readTixFile = HPC_YES_EXPLICIT; + } + else if (strequal("read-tix-file=no", + &rts_argv[arg][2])) { + OPTION_UNSAFE; + RtsFlags.HpcFlags.readTixFile = HPC_NO_EXPLICIT; + } else if (strequal("write-tix-file=yes", &rts_argv[arg][2])) { OPTION_UNSAFE; ===================================== rts/include/rts/Flags.h ===================================== @@ -302,10 +302,26 @@ typedef struct _PAR_FLAGS { bool setAffinity; /* force thread affinity with CPUs */ } PAR_FLAGS; +/* Corresponds to the RTS flag `--read-tix-file=`. + * The accepted GHC proposal 612 introduced a one-release warning period + * during which we emit a warning if we read a .tix file and the flag + * isn't explicitly set. In order to distinguish between whether the flag + * was explicitly set or defaulted we need to use a tri-state variable. + */ +typedef enum _HPC_READ_FILE { + HPC_NO_EXPLICIT = 0, /* The user has specified --read-tix-file=no */ + HPC_YES_IMPLICIT = 1, /* The user hasn't specified an option and we emit + * a warning when we read a tix file. + */ + HPC_YES_EXPLICIT = 2 /* The user has specified --read-tix-file=yes */ + } HPC_READ_FILE; + /* See Note [Synchronization of flags and base APIs] */ typedef struct _HPC_FLAGS { bool writeTixFile; /* Whether the RTS should write a tix file at the end of execution */ + HPC_READ_FILE readTixFile; /* Whether the RTS should read a tix + file at the beginning of execution */ } HPC_FLAGS; /* See Note [Synchronization of flags and base APIs] */ ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -9105,7 +9105,7 @@ module GHC.RTS.Flags where type GiveGCStats :: * data GiveGCStats = NoGCStats | CollectGCStats | OneLineGCStats | SummaryGCStats | VerboseGCStats type HpcFlags :: * - data HpcFlags = HpcFlags {writeTixFile :: GHC.Types.Bool} + data HpcFlags = HpcFlags {readTixFile :: GHC.Types.Bool, writeTixFile :: GHC.Types.Bool} type IoManagerFlag :: * data IoManagerFlag = IoManagerFlagAuto | IoManagerFlagSelect | IoManagerFlagMIO | IoManagerFlagWinIO | IoManagerFlagWin32Legacy type IoSubSystem :: * ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -12147,7 +12147,7 @@ module GHC.RTS.Flags where type GiveGCStats :: * data GiveGCStats = NoGCStats | CollectGCStats | OneLineGCStats | SummaryGCStats | VerboseGCStats type HpcFlags :: * - data HpcFlags = HpcFlags {writeTixFile :: GHC.Types.Bool} + data HpcFlags = HpcFlags {readTixFile :: GHC.Types.Bool, writeTixFile :: GHC.Types.Bool} type IoManagerFlag :: * data IoManagerFlag = IoManagerFlagAuto | IoManagerFlagSelect | IoManagerFlagMIO | IoManagerFlagWinIO | IoManagerFlagWin32Legacy type IoSubSystem :: * ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -9329,7 +9329,7 @@ module GHC.RTS.Flags where type GiveGCStats :: * data GiveGCStats = NoGCStats | CollectGCStats | OneLineGCStats | SummaryGCStats | VerboseGCStats type HpcFlags :: * - data HpcFlags = HpcFlags {writeTixFile :: GHC.Types.Bool} + data HpcFlags = HpcFlags {readTixFile :: GHC.Types.Bool, writeTixFile :: GHC.Types.Bool} type IoManagerFlag :: * data IoManagerFlag = IoManagerFlagAuto | IoManagerFlagSelect | IoManagerFlagMIO | IoManagerFlagWinIO | IoManagerFlagWin32Legacy type IoSubSystem :: * ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -9105,7 +9105,7 @@ module GHC.RTS.Flags where type GiveGCStats :: * data GiveGCStats = NoGCStats | CollectGCStats | OneLineGCStats | SummaryGCStats | VerboseGCStats type HpcFlags :: * - data HpcFlags = HpcFlags {writeTixFile :: GHC.Types.Bool} + data HpcFlags = HpcFlags {readTixFile :: GHC.Types.Bool, writeTixFile :: GHC.Types.Bool} type IoManagerFlag :: * data IoManagerFlag = IoManagerFlagAuto | IoManagerFlagSelect | IoManagerFlagMIO | IoManagerFlagWinIO | IoManagerFlagWin32Legacy type IoSubSystem :: * ===================================== testsuite/tests/linters/notes.stdout ===================================== @@ -1,39 +1,40 @@ +Broken note references (target note not found!): ref compiler/GHC/Core/Coercion/Axiom.hs:472:2: Note [RoughMap and rm_empty] ref compiler/GHC/Core/Opt/OccurAnal.hs:1157:7: Note [Loop breaking] -ref compiler/GHC/Core/Opt/SetLevels.hs:1586:30: Note [Top level scope] -ref compiler/GHC/Core/Opt/Simplify/Iteration.hs:2832:13: Note [Case binder next] -ref compiler/GHC/Core/Opt/Simplify/Iteration.hs:4023:8: Note [Lambda-bound unfoldings] -ref compiler/GHC/Core/Opt/Simplify/Utils.hs:1342:37: Note [Gentle mode] +ref compiler/GHC/Core/Opt/SetLevels.hs:1688:30: Note [Top level scope] +ref compiler/GHC/Core/Opt/Simplify/Iteration.hs:2937:13: Note [Case binder next] +ref compiler/GHC/Core/Opt/Simplify/Iteration.hs:4253:8: Note [Lambda-bound unfoldings] +ref compiler/GHC/Core/Opt/Simplify/Utils.hs:1406:37: Note [Gentle mode] ref compiler/GHC/Core/Opt/Specialise.hs:1763:29: Note [Arity decrease] -ref compiler/GHC/Core/TyCo/Rep.hs:1652:31: Note [What prevents a constraint from floating] -ref compiler/GHC/Driver/DynFlags.hs:1251:52: Note [Eta-reduction in -O0] -ref compiler/GHC/Driver/Main.hs:1749:34: Note [simpleTidyPgm - mkBootModDetailsTc] -ref compiler/GHC/Hs/Expr.hs:191:63: Note [Pending Splices] -ref compiler/GHC/Hs/Expr.hs:1727:87: Note [Lifecycle of a splice] -ref compiler/GHC/Hs/Expr.hs:1763:7: Note [Pending Splices] -ref compiler/GHC/Hs/Extension.hs:147:5: Note [Strict argument type constraints] -ref compiler/GHC/Hs/Pat.hs:141:74: Note [Lifecycle of a splice] +ref compiler/GHC/Core/TyCo/Rep.hs:1677:31: Note [What prevents a constraint from floating] +ref compiler/GHC/Driver/DynFlags.hs:1254:52: Note [Eta-reduction in -O0] +ref compiler/GHC/Driver/Main.hs:1750:34: Note [simpleTidyPgm - mkBootModDetailsTc] +ref compiler/GHC/Hs/Expr.hs:192:63: Note [Pending Splices] +ref compiler/GHC/Hs/Expr.hs:1955:87: Note [Lifecycle of a splice] +ref compiler/GHC/Hs/Expr.hs:1991:7: Note [Pending Splices] +ref compiler/GHC/Hs/Extension.hs:144:5: Note [Strict argument type constraints] +ref compiler/GHC/Hs/Pat.hs:146:74: Note [Lifecycle of a splice] ref compiler/GHC/HsToCore/Pmc/Solver.hs:856:20: Note [COMPLETE sets on data families] -ref compiler/GHC/HsToCore/Quote.hs:1487:7: Note [How brackets and nested splices are handled] -ref compiler/GHC/Stg/Unarise.hs:438:32: Note [Renaming during unarisation] -ref compiler/GHC/Tc/Gen/HsType.hs:556:56: Note [Skolem escape prevention] -ref compiler/GHC/Tc/Gen/HsType.hs:2676:7: Note [Matching a kind signature with a declaration] -ref compiler/GHC/Tc/Gen/Pat.hs:174:20: Note [Typing patterns in pattern bindings] -ref compiler/GHC/Tc/Gen/Pat.hs:1163:7: Note [Matching polytyped patterns] -ref compiler/GHC/Tc/Gen/Sig.hs:80:10: Note [Overview of type signatures] +ref compiler/GHC/HsToCore/Quote.hs:1505:7: Note [How brackets and nested splices are handled] +ref compiler/GHC/Stg/Unarise.hs:451:32: Note [Renaming during unarisation] +ref compiler/GHC/Tc/Gen/HsType.hs:561:56: Note [Skolem escape prevention] +ref compiler/GHC/Tc/Gen/HsType.hs:2707:7: Note [Matching a kind signature with a declaration] +ref compiler/GHC/Tc/Gen/Pat.hs:286:20: Note [Typing patterns in pattern bindings] +ref compiler/GHC/Tc/Gen/Pat.hs:1385:7: Note [Matching polytyped patterns] +ref compiler/GHC/Tc/Gen/Sig.hs:77:10: Note [Overview of type signatures] ref compiler/GHC/Tc/Gen/Splice.hs:358:16: Note [How brackets and nested splices are handled] ref compiler/GHC/Tc/Gen/Splice.hs:533:35: Note [PendingRnSplice] -ref compiler/GHC/Tc/Gen/Splice.hs:657:7: Note [How brackets and nested splices are handled] -ref compiler/GHC/Tc/Gen/Splice.hs:891:11: Note [How brackets and nested splices are handled] +ref compiler/GHC/Tc/Gen/Splice.hs:660:7: Note [How brackets and nested splices are handled] +ref compiler/GHC/Tc/Gen/Splice.hs:904:11: Note [How brackets and nested splices are handled] ref compiler/GHC/Tc/Instance/Family.hs:406:35: Note [Constrained family instances] -ref compiler/GHC/Tc/Solver/Rewrite.hs:1010:7: Note [Stability of rewriting] +ref compiler/GHC/Tc/Solver/Rewrite.hs:1006:7: Note [Stability of rewriting] ref compiler/GHC/Tc/TyCl.hs:1316:6: Note [Unification variables need fresh Names] ref compiler/GHC/Tc/Types/Constraint.hs:206:38: Note [NonCanonical Semantics] -ref compiler/GHC/Types/Demand.hs:301:25: Note [Preserving Boxity of results is rarely a win] +ref compiler/GHC/Types/Demand.hs:303:25: Note [Preserving Boxity of results is rarely a win] ref compiler/GHC/Unit/Module/Deps.hs:83:13: Note [Structure of dep_boot_mods] ref compiler/GHC/Utils/Monad.hs:410:34: Note [multiShotIO] -ref compiler/Language/Haskell/Syntax/Binds.hs:200:31: Note [fun_id in Match] -ref configure.ac:203:10: Note [Linking ghc-bin against threaded stage0 RTS] +ref compiler/Language/Haskell/Syntax/Binds.hs:220:31: Note [fun_id in Match] +ref configure.ac:191:10: Note [Linking ghc-bin against threaded stage0 RTS] ref docs/core-spec/core-spec.mng:177:6: Note [TyBinders] ref hadrian/src/Expression.hs:145:30: Note [Linking ghc-bin against threaded stage0 RTS] ref linters/lint-notes/Notes.hs:32:29: Note [" <> T.unpack x <> "] @@ -51,18 +52,18 @@ ref testsuite/tests/typecheck/should_compile/tc228.hs:9:7: Note [Inferenc ref testsuite/tests/typecheck/should_compile/tc231.hs:12:16: Note [Important subtlety in oclose] ref testsuite/tests/typecheck/should_fail/UnliftedNewtypesMultiFieldGadt.hs:11:28: Note [Kind-checking the field type] ref testsuite/tests/typecheck/should_fail/tcfail093.hs:13:7: Note [Important subtlety in oclose] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Eta reduction for data family axioms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:: Note [Exporting built-in items] -ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:: Note [Exporting built-in items] -ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:: Note [Exporting built-in items] -ref utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs:: Note [The DocModule story] -ref utils/haddock/haddock-api/src/Haddock/Types.hs:: Note [Pass sensitive types] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1068:13: Note [Eta reduction for data family axioms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1085:0: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1101:7: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1108:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1117:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1131:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1145:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1147:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1156:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:120:11: Note [Exporting built-in items] +ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:185:9: Note [Exporting built-in items] +ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:255:7: Note [Exporting built-in items] +ref utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs:118:3: Note [The DocModule story] +ref utils/haddock/haddock-api/src/Haddock/Types.hs:17:3: Note [Pass sensitive types] ===================================== testsuite/tests/th/should_compile/T24870/Def.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE TemplateHaskell #-} + +module SDef where + +{-# NOINLINE aValue #-} +aValue = True + +{-# NOINLINE aStrictFunction #-} +aStrictFunction !x = [| x |] ===================================== testsuite/tests/th/should_compile/T24870/T24870.stderr ===================================== @@ -0,0 +1,2 @@ +[1 of 2] Compiling SDef ( Def.hs, Def.o, Def.dyn_o ) +[2 of 2] Compiling SUse ( Use.hs, Use.o ) ===================================== testsuite/tests/th/should_compile/T24870/T24870.stderr-mingw32 ===================================== @@ -0,0 +1,2 @@ +[1 of 2] Compiling SDef ( Def.hs, Def.o ) +[2 of 2] Compiling SUse ( Use.hs, Use.o ) ===================================== testsuite/tests/th/should_compile/T24870/Use.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE TemplateHaskell #-} + +module SUse where + +import qualified Language.Haskell.TH.Syntax as TH +import SDef +import GHC.Exts + +bar = $( inline aStrictFunction aValue ) ===================================== testsuite/tests/th/should_compile/T24870/all.T ===================================== @@ -0,0 +1,6 @@ +# The interpreter must uphold tagging invariants, and failed to do so in #24870 +# We test this here by having the interpreter calls a strict worker function +# with a reference to a value it constructed. +# See also Note [CBV Functions and the interpreter] +test('T24870', [extra_files(['Def.hs', 'Use.hs']), req_th], + multimod_compile, ['Def Use', '-dtag-inference-checks']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/460e65edf5851696f15c250390c057f2e55fe59e...35de8a60fdf5fcd285de56ebaa290e3f87bad4fd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/460e65edf5851696f15c250390c057f2e55fe59e...35de8a60fdf5fcd285de56ebaa290e3f87bad4fd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 06:21:03 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Tue, 18 Jun 2024 02:21:03 -0400 Subject: [Git][ghc/ghc][wip/supersven/ghc-9.10-riscv-ncg] Rework the far branches algorithm according to AArch64 Message-ID: <6671274f611e0_559132447c247087d@gitlab.mail> Sven Tennie pushed to branch wip/supersven/ghc-9.10-riscv-ncg at Glasgow Haskell Compiler / GHC Commits: cb66c228 by Sven Tennie at 2024-06-18T06:19:32+00:00 Rework the far branches algorithm according to AArch64 - - - - - 4 changed files: - compiler/GHC/CmmToAsm/RV64/CodeGen.hs - compiler/GHC/CmmToAsm/RV64/Cond.hs - compiler/GHC/CmmToAsm/RV64/Instr.hs - compiler/GHC/CmmToAsm/RV64/Ppr.hs Changes: ===================================== compiler/GHC/CmmToAsm/RV64/CodeGen.hs ===================================== @@ -6,11 +6,11 @@ module GHC.CmmToAsm.RV64.CodeGen ( cmmTopCodeGen , generateJumpTableForInstr + , makeFarBranches ) where -import Control.Monad (mapAndUnzipM) import Data.Maybe import Data.Word import GHC.Cmm @@ -55,6 +55,9 @@ import GHC.Utils.Constants (debugIsOn) import GHC.Utils.Misc import GHC.Utils.Outputable import GHC.Utils.Panic +import GHC.Cmm.Dataflow.Label +import GHC.Types.Unique.Supply +import GHC.Utils.Monad -- For an overview of an NCG's structure, see Note [General layout of an NCG] @@ -125,14 +128,17 @@ basicBlockCodeGen block = do let (top,other_blocks,statics) = foldrOL mkBlocks ([],[],[]) instrs - mkBlocks (NEWBLOCK id) (instrs,blocks,statics) - = ([], BasicBlock id instrs : blocks, statics) - mkBlocks (LDATA sec dat) (instrs,blocks,statics) - = (instrs, blocks, CmmData sec dat:statics) - mkBlocks instr (instrs,blocks,statics) - = (instr:instrs, blocks, statics) return (BasicBlock id top : other_blocks, statics) +mkBlocks :: Instr + -> ([Instr], [GenBasicBlock Instr], [GenCmmDecl RawCmmStatics h g]) + -> ([Instr], [GenBasicBlock Instr], [GenCmmDecl RawCmmStatics h g]) +mkBlocks (NEWBLOCK id) (instrs,blocks,statics) + = ([], BasicBlock id instrs : blocks, statics) +mkBlocks (LDATA sec dat) (instrs,blocks,statics) + = (instrs, blocks, CmmData sec dat:statics) +mkBlocks instr (instrs,blocks,statics) + = (instr:instrs, blocks, statics) -- ----------------------------------------------------------------------------- -- | Utilities @@ -1495,7 +1501,7 @@ genCCall target dest_regs arg_regs bid = do then 8 * (stackSpace' `div` 8 + 1) else stackSpace' - (returnRegs, readResultsCode) <- readResults allGpArgRegs allFpArgRegs dest_regs [] nilOL + readResultsCode <- readResults allGpArgRegs allFpArgRegs dest_regs [] nilOL let moveStackDown 0 = toOL [ PUSH_STACK_FRAME , DELTA (-16) ] @@ -1513,7 +1519,7 @@ genCCall target dest_regs arg_regs bid = do let code = call_target_code -- compute the label (possibly into a register) `appOL` moveStackDown (stackSpace `div` 8) `appOL` passArgumentsCode -- put the arguments into x0, ... - `snocOL` BL call_target passRegs returnRegs -- branch and link. + `snocOL` BL call_target passRegs -- branch and link. `appOL` readResultsCode -- parse the results into registers `appOL` moveStackUp (stackSpace `div` 8) return (code, Nothing) @@ -1801,8 +1807,8 @@ genCCall target dest_regs arg_regs bid = do passArguments _ _ _ _ _ _ = pprPanic "passArguments" (text "invalid state") - readResults :: [Reg] -> [Reg] -> [LocalReg] -> [Reg]-> InstrBlock -> NatM ([Reg], InstrBlock) - readResults _ _ [] accumRegs accumCode = return (accumRegs, accumCode) + readResults :: [Reg] -> [Reg] -> [LocalReg] -> [Reg]-> InstrBlock -> NatM InstrBlock + readResults _ _ [] _ accumCode = return accumCode readResults [] _ _ _ _ = do platform <- getPlatform pprPanic "genCCall, out of gp registers when reading results" (pdoc platform target) @@ -1830,3 +1836,220 @@ genCCall target dest_regs arg_regs bid = do let dst = getRegisterReg platform (CmmLocal dest_reg) let code = code_fx `appOL` op (OpReg w dst) (OpReg w reg_fx) return (code, Nothing) + +{- Note [RISCV64 far jumps] +~~~~~~~~~~~~~~~~~~~~~~~~~~~ + +RISCV64 conditional jump instructions can only encode an offset of +/-4KiB +(12bits) which is usually enough but can be exceeded in edge cases. In these +cases we will replace: + + b.cond foo + +with the sequence: + + b.cond + b + : + la reg foo + b reg + : + +Compared to AArch64 the target label is loaded to a register, because +unconditional jump instructions can only address +/-1MiB. The LA +pseudo-instruction will be replaced by up to two real instructions, ensuring +correct addressing. + +RISCV has many pseudo-instructions which emit more than one real instructions. +Thus, our counting algorithm is approximative. (This could be optimized by +either only using real instructions or accounting pseudo-instructions by their +real size.) + +We make some simplifications in the name of performance which can result in overestimating +jump <-> label offsets: + +* To avoid having to recalculate the label offsets once we replaced a jump we simply + assume all jumps will be expanded to a three instruction far jump sequence. +* For labels associated with a info table we assume the info table is 64byte large. + Most info tables are smaller than that but it means we don't have to distinguish + between multiple types of info tables. + +In terms of implementation we walk the instruction stream at least once calculating +label offsets, and if we determine during this that the functions body is big enough +to potentially contain out of range jumps we walk the instructions a second time, replacing +out of range jumps with the sequence of instructions described above. + +-} + +-- | A conditional jump to a far target +-- +-- By loading the far target into a register for the jump, we can address the +-- whole memory range. +genCondFarJump :: (MonadUnique m) => Cond -> Operand -> Operand -> BlockId -> m InstrBlock +genCondFarJump cond op1 op2 far_target = do + skip_lbl_id <- newBlockId + jmp_lbl_id <- newBlockId + + -- TODO: We can improve this by inverting the condition + -- but it's not quite trivial since we don't know if we + -- need to consider float orderings. + -- So we take the hit of the additional jump in the false + -- case for now. + return + $ toOL + [ ann (text "Conditional far jump to: " <> ppr far_target) + $ BCOND cond op1 op2 (TBlock jmp_lbl_id), + B (TBlock skip_lbl_id), + NEWBLOCK jmp_lbl_id, + LDR II64 (OpReg W64 ipReg) (OpImm (ImmCLbl (blockLbl far_target))), + B (TReg ipReg), + NEWBLOCK skip_lbl_id + ] + +-- | An unconditional jump to a far target +-- +-- By loading the far target into a register for the jump, we can address the +-- whole memory range. +genFarJump :: (MonadUnique m) => BlockId -> m InstrBlock +genFarJump far_target = + return + $ toOL + [ ann (text "Unconditional far jump to: " <> ppr far_target) + $ LDR II64 (OpReg W64 ipReg) (OpImm (ImmCLbl (blockLbl far_target))), + B (TReg ipReg) + ] + +-- | An unconditional jump to a far target +-- +-- By loading the far target into a register for the jump, we can address the +-- whole memory range. +genFarBranchAndLink :: (MonadUnique m) => BlockId -> [Reg] -> m InstrBlock +genFarBranchAndLink far_target ps = + return + $ toOL + [ ann (text "Unconditional branch and link to: " <> ppr far_target) + $ LDR II64 (OpReg W64 ipReg) (OpImm (ImmCLbl (blockLbl far_target))), + BL (TReg ipReg) ps + ] + +-- See Note [RISCV64 far jumps] +data BlockInRange = InRange | NotInRange BlockId + +-- See Note [RISCV64 far jumps] +makeFarBranches :: Platform -> LabelMap RawCmmStatics -> [NatBasicBlock Instr] + -> UniqSM [NatBasicBlock Instr] +makeFarBranches {- only used when debugging -} _platform statics basic_blocks = do + -- All offsets/positions are counted in multiples of 4 bytes (the size of RISCV64 instructions) + -- That is an offset of 1 represents a 4-byte/one instruction offset. + let (func_size, lblMap) = foldl' calc_lbl_positions (0, mapEmpty) basic_blocks + if func_size < max_jump_dist + then pure basic_blocks + else do + (_,blocks) <- mapAccumLM (replace_blk lblMap) 0 basic_blocks + pure $ concat blocks + -- pprTrace "lblMap" (ppr lblMap) $ basic_blocks + + where + -- 2^11, 12 bit immediate with one bit is reserved for the sign + max_jump_dist = 2^(11::Int) - 1 :: Int + -- Currently all inline info tables fit into 64 bytes. + max_info_size = 16 :: Int + long_bc_jump_size = 5 :: Int + long_b_jump_size = 2 :: Int + + -- Replace out of range conditional jumps with unconditional jumps. + replace_blk :: LabelMap Int -> Int -> GenBasicBlock Instr -> UniqSM (Int, [GenBasicBlock Instr]) + replace_blk !m !pos (BasicBlock lbl instrs) = do + -- Account for a potential info table before the label. + let !block_pos = pos + infoTblSize_maybe lbl + (!pos', instrs') <- mapAccumLM (replace_jump m) block_pos instrs + let instrs'' = concat instrs' + -- We might have introduced new labels, so split the instructions into basic blocks again if neccesary. + let (top, split_blocks, no_data) = foldr mkBlocks ([],[],[]) instrs'' + -- There should be no data in the instruction stream at this point + massert (null no_data) + + let final_blocks = BasicBlock lbl top : split_blocks + pure (pos', final_blocks) + + replace_jump :: LabelMap Int -> Int -> Instr -> UniqSM (Int, [Instr]) + replace_jump !m !pos instr = do + case instr of + ANN ann instr -> do + (idx,instr':instrs') <- replace_jump m pos instr + pure (idx, ANN ann instr':instrs') + BCOND cond op1 op2 t + -> case target_in_range m t pos of + InRange -> pure (pos+long_bc_jump_size,[instr]) + NotInRange far_target -> do + jmp_code <- genCondFarJump cond op1 op2 far_target + pure (pos+long_bc_jump_size, fromOL jmp_code) + B t + -> case target_in_range m t pos of + InRange -> pure (pos+long_b_jump_size,[instr]) + NotInRange far_target -> do + jmp_code <- genFarJump far_target + pure (pos+long_b_jump_size, fromOL jmp_code) + J t + -> case target_in_range m t pos of + InRange -> pure (pos+long_b_jump_size,[instr]) + NotInRange far_target -> do + jmp_code <- genFarJump far_target + pure (pos+long_b_jump_size, fromOL jmp_code) + BL t ps + -> case target_in_range m t pos of + InRange -> pure (pos+long_b_jump_size,[instr]) + NotInRange far_target -> do + jmp_code <- genFarBranchAndLink far_target ps + pure (pos+long_b_jump_size, fromOL jmp_code) + instr + | isMetaInstr instr -> pure (pos,[instr]) + | otherwise -> pure (pos+1, [instr]) + + target_in_range :: LabelMap Int -> Target -> Int -> BlockInRange + target_in_range m target src = + case target of + (TReg{}) -> InRange + (TBlock bid) -> block_in_range m src bid + + block_in_range :: LabelMap Int -> Int -> BlockId -> BlockInRange + block_in_range m src_pos dest_lbl = + case mapLookup dest_lbl m of + Nothing -> + pprTrace "not in range" (ppr dest_lbl) $ + NotInRange dest_lbl + Just dest_pos -> if abs (dest_pos - src_pos) < max_jump_dist + then InRange + else NotInRange dest_lbl + + calc_lbl_positions :: (Int, LabelMap Int) -> GenBasicBlock Instr -> (Int, LabelMap Int) + calc_lbl_positions (pos, m) (BasicBlock lbl instrs) + = let !pos' = pos + infoTblSize_maybe lbl + in foldl' instr_pos (pos',mapInsert lbl pos' m) instrs + + instr_pos :: (Int, LabelMap Int) -> Instr -> (Int, LabelMap Int) + instr_pos (pos, m) instr = + case instr of + ANN _ann instr -> instr_pos (pos, m) instr + NEWBLOCK _bid -> panic "mkFarBranched - unexpected NEWBLOCK" -- At this point there should be no NEWBLOCK + -- in the instruction stream + -- (pos, mapInsert bid pos m) + COMMENT{} -> (pos, m) + instr + | Just jump_size <- is_expandable_jump instr -> (pos+jump_size, m) + | otherwise -> (pos+1, m) + + infoTblSize_maybe bid = + case mapLookup bid statics of + Nothing -> 0 :: Int + Just _info_static -> max_info_size + + -- These jumps have a 12bit immediate as offset which is quite + -- limiting so we potentially have to expand them into + -- multiple instructions. + is_expandable_jump i = case i of + BCOND{} -> Just long_bc_jump_size + J (TBlock _) -> Just long_b_jump_size + B (TBlock _) -> Just long_b_jump_size + BL (TBlock _) _ -> Just long_b_jump_size + _ -> Nothing ===================================== compiler/GHC/CmmToAsm/RV64/Cond.hs ===================================== @@ -1,4 +1,7 @@ -module GHC.CmmToAsm.RV64.Cond where +module GHC.CmmToAsm.RV64.Cond + ( Cond (..), + ) +where import GHC.Prelude hiding (EQ) @@ -37,22 +40,3 @@ data Cond | -- | floating point instruction @fgt@ FGT deriving (Eq, Show) - --- | Negate a condition. --- --- This is useful to e.g. construct far branches from usual branches. -negateCond :: Cond -> Cond -negateCond EQ = NE -negateCond NE = EQ -negateCond SLT = SGE -negateCond SLE = SGT -negateCond SGE = SLT -negateCond SGT = SLE -negateCond ULT = UGE -negateCond ULE = UGT -negateCond UGE = ULT -negateCond UGT = ULE -negateCond FLT = FGE -negateCond FLE = FGT -negateCond FGE = FLT -negateCond FGT = FLE ===================================== compiler/GHC/CmmToAsm/RV64/Instr.hs ===================================== @@ -28,10 +28,6 @@ import GHC.Utils.Panic import Data.Maybe import GHC.Stack -import qualified Data.List.NonEmpty as NE -import Data.Foldable -import GHC.Cmm.Info (maxRetInfoTableSizeW) -import GHC.Types.Unique.FM (listToUFM, lookupUFM) import GHC.Data.FastString (LexicalFastString) -- | Stack frame header size in bytes. @@ -109,10 +105,8 @@ regUsageOfInstr platform instr = case instr of J t -> usage (regTarget t, []) J_TBL _ _ t -> usage ([t], []) B t -> usage (regTarget t, []) - B_FAR _t -> usage ([], []) BCOND _ l r t -> usage (regTarget t ++ regOp l ++ regOp r, []) - BCOND_FAR _ l r _ t -> usage (regTarget t ++ regOp l ++ regOp r, []) - BL t ps _rs -> usage (regTarget t ++ ps, callerSavedRegisters) + BL t ps -> usage (regTarget t ++ ps, callerSavedRegisters) -- 5. Atomic Instructions ---------------------------------------------------- -- 6. Conditional Instructions ----------------------------------------------- @@ -209,10 +203,8 @@ patchRegsOfInstr instr env = case instr of J t -> J (patchTarget t) J_TBL ids mbLbl t -> J_TBL ids mbLbl (env t) B t -> B (patchTarget t) - B_FAR t -> B_FAR t - BL t rs ts -> BL (patchTarget t) rs ts + BL t ps -> BL (patchTarget t) ps BCOND c o1 o2 t -> BCOND c (patchOp o1) (patchOp o2) (patchTarget t) - BCOND_FAR c o1 o2 b t -> BCOND_FAR c (patchOp o1) (patchOp o2) (patchTarget b) (patchTarget t) -- 5. Atomic Instructions -------------------------------------------------- -- 6. Conditional Instructions --------------------------------------------- @@ -257,10 +249,8 @@ isJumpishInstr instr = case instr of J {} -> True J_TBL {} -> True B {} -> True - B_FAR {} -> True BL {} -> True BCOND {} -> True - BCOND_FAR {} -> True _ -> False -- | Get the `BlockId`s of the jump destinations (if any) @@ -269,10 +259,8 @@ jumpDestsOfInstr (ANN _ i) = jumpDestsOfInstr i jumpDestsOfInstr (J t) = [id | TBlock id <- [t]] jumpDestsOfInstr (J_TBL ids _mbLbl _r) = catMaybes ids jumpDestsOfInstr (B t) = [id | TBlock id <- [t]] -jumpDestsOfInstr (B_FAR t) = [t] -jumpDestsOfInstr (BL t _ _) = [id | TBlock id <- [t]] +jumpDestsOfInstr (BL t _) = [id | TBlock id <- [t]] jumpDestsOfInstr (BCOND _ _ _ t) = [id | TBlock id <- [t]] -jumpDestsOfInstr (BCOND_FAR _ _ _ _ t) = [id | TBlock id <- [t]] jumpDestsOfInstr _ = [] -- | Change the destination of this (potential) jump instruction. @@ -286,10 +274,8 @@ patchJumpInstr instr patchF = J (TBlock bid) -> J (TBlock (patchF bid)) J_TBL ids mbLbl r -> J_TBL (map (fmap patchF) ids) mbLbl r B (TBlock bid) -> B (TBlock (patchF bid)) - B_FAR bid -> B_FAR (patchF bid) - BL (TBlock bid) ps rs -> BL (TBlock (patchF bid)) ps rs + BL (TBlock bid) ps -> BL (TBlock (patchF bid)) ps BCOND c o1 o2 (TBlock bid) -> BCOND c o1 o2 (TBlock (patchF bid)) - BCOND_FAR c o1 o2 b (TBlock bid) -> BCOND_FAR c o1 o2 b (TBlock (patchF bid)) _ -> panic $ "patchJumpInstr: " ++ instrCon instr -- ----------------------------------------------------------------------------- @@ -596,12 +582,9 @@ data Instr -- | A `J` instruction with data for switch jump tables | J_TBL [Maybe BlockId] (Maybe CLabel) Reg | B Target -- unconditional branching b/br. (To a blockid, label or register) - -- | pseudo-op for far branch targets - | B_FAR BlockId - | BL Target [Reg] [Reg] -- branch and link (e.g. set x30 to next pc, and branch) + | BL Target [Reg] -- branch and link (e.g. set x30 to next pc, and branch) | BCOND Cond Operand Operand Target -- branch with condition. b. -- | pseudo-op for far branch targets - | BCOND_FAR Cond Operand Operand Target Target -- 8. Synchronization Instructions ----------------------------------------- | DMBSY DmbType DmbType @@ -661,10 +644,8 @@ instrCon i = J{} -> "J" J_TBL{} -> "J_TBL" B{} -> "B" - B_FAR{} -> "B_FAR" BL{} -> "BL" BCOND{} -> "BCOND" - BCOND_FAR{} -> "BCOND_FAR" DMBSY{} -> "DMBSY" FCVT{} -> "FCVT" SCVTF{} -> "SCVTF" @@ -809,75 +790,3 @@ isFloatReg (RegReal (RealRegSingle i)) | i > 31 = True isFloatReg (RegVirtual (VirtualRegF _)) = True isFloatReg (RegVirtual (VirtualRegD _)) = True isFloatReg _ = False - - --- | Making far branches - --- Conditional branch instructions can target labels in a range of +/- 4 KiB. --- The assembler can transform this into a J instruction targeting +/- 1MiB. --- There are rare cases where this is not enough (e.g. the Happy-generated --- @Parser.hs at .) We need to manually transform these into register based jumps --- using @ip@ (register reserved for calculations.) The trick is to invert the --- condition, do a far jump in the fall-through case or a short jump when the --- (inverted) condition is true. -makeFarBranches :: - Platform -> - LabelMap RawCmmStatics -> - [NatBasicBlock Instr] -> - UniqSM [NatBasicBlock Instr] -makeFarBranches _platform info_env blocks - | NE.last blockAddresses < nearLimit = pure blocks - | otherwise = pure $ zipWith handleBlock blockAddressList blocks - where - blockAddresses = NE.scanl (+) 0 $ map blockLen blocks - blockAddressList = toList blockAddresses - blockLen (BasicBlock _ instrs) = length instrs - - handleBlock addr (BasicBlock id instrs) = - BasicBlock id (zipWith (makeFar id) [addr ..] instrs) - - -- TODO: Use UniqSM to generate unique block ids. - makeFar :: BlockId -> Int -> Instr -> Instr - makeFar bid addr orig@(BCOND cond op1 op2 tgt@(TBlock tgtBid)) - | abs (addr - targetAddr) >= nearLimit = - annotate addr targetAddr $ - BCOND_FAR cond op1 op2 (TBlock bid) tgt - | otherwise = - annotate addr targetAddr orig - where - targetAddr = fromJust $ lookupUFM blockAddressMap tgtBid - makeFar _bid addr orig@(B (TBlock tgtBid)) - | abs (addr - targetAddr) >= nearLimit = - annotate addr targetAddr $ - B_FAR tgtBid - | otherwise = - annotate addr targetAddr orig - where - targetAddr = fromJust $ lookupUFM blockAddressMap tgtBid - makeFar bid addr (ANN desc other) = ANN desc $ makeFar bid addr other - makeFar _bid _ other = other - - -- 262144 (2^20 / 4) instructions are allowed; let's keep some distance, as - -- we have pseudo-insns that are pretty-printed as multiple instructions, - -- and it's just not worth the effort to calculate things exactly as linker - -- relaxations are applied later (optimizing away our flaws.) The educated - -- guess here is that every instruction does not emit more than two in the - -- mean. - nearLimit = 131072 - mapSize info_env * maxRetInfoTableSizeW - - blockAddressMap = listToUFM $ zip (map blockId blocks) blockAddressList - - -- We may want to optimize the limit in future. So, annotate the most - -- important values of the decision. - annotate :: Int -> Int -> Instr -> Instr - annotate addr targetAddr instr = - ANN - ( text (instrCon instr) - <+> text "targetAddr" <> colon - <+> int targetAddr <> comma - <+> text "offset" <> colon - <+> int (addr - targetAddr) <> comma - <+> text "nearLimit" <> colon - <+> int nearLimit - ) - instr ===================================== compiler/GHC/CmmToAsm/RV64/Ppr.hs ===================================== @@ -512,30 +512,14 @@ pprInstr platform instr = case instr of B l | isLabel l -> line $ text "\tjal" <+> pprOp platform x0 <> comma <+> getLabel platform l B (TReg r) -> line $ text "\tjalr" <+> text "x0" <> comma <+> pprReg W64 r <> comma <+> text "0" - B_FAR bid -> lines_ [ text "\tla" <+> pprOp platform ip <> comma <+> pprBlockId platform bid - , text "\tjalr" <+> text "x0" <> comma <+> pprOp platform ip <> comma <+> text "0" ] - - BL l _ _ | isLabel l-> line $ text "\tcall" <+> getLabel platform l - BL (TReg r) _ _ -> line $ text "\tjalr" <+> text "x1" <> comma <+> pprReg W64 r <> comma <+> text "0" + BL l _ | isLabel l-> line $ text "\tcall" <+> getLabel platform l + BL (TReg r) _ -> line $ text "\tjalr" <+> text "x1" <> comma <+> pprReg W64 r <> comma <+> text "0" BCOND c l r t | isLabel t -> line $ text "\t" <> pprBcond c <+> pprOp platform l <> comma <+> pprOp platform r <> comma <+> getLabel platform t BCOND _ _ _ (TReg _) -> panic "RV64.ppr: No conditional branching to registers!" - -- This is the far branches trick: Negate the condition and either do a - -- register based jump (ignoring the link result in register zero) or just - -- branch to the end of the block, jumping over the far jump instructions. - BCOND_FAR c l r b t | isLabel t -> - lines_ [ text "\t" <> pprBcond (negateCond c) <+> pprOp platform l <> comma <+> pprOp platform r <> comma <+> getLabel platform b <> text "far_branch_end" - , text "\tla" <+> pprOp platform ip <> comma <+> getLabel platform t - , text "\tjalr" <+> text "x0" <> comma <+> pprOp platform ip <> comma <+> text "0" - , text "\t" <> getLabel platform b <> text "far_branch_end" <> colon - ] - - BCOND_FAR _ _ _ _ (TReg _) -> panic "RV64.ppr: No conditional branching to registers!" - - -- 5. Atomic Instructions ---------------------------------------------------- -- 6. Conditional Instructions ----------------------------------------------- CSET o l r c -> case c of View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cb66c228cd836270da6e26a160f71785acd47940 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cb66c228cd836270da6e26a160f71785acd47940 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 09:24:41 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Tue, 18 Jun 2024 05:24:41 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] 2 commits: Revert "SIMD: refactor Format datatype" Message-ID: <667152591c859_24605acb375c249b2@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 7abec336 by sheaf at 2024-06-18T10:57:17+02:00 Revert "SIMD: refactor Format datatype" This reverts commit 84c46f16be09760b64a8b926f1f92ceb853b2da8. - - - - - 9f603670 by sheaf at 2024-06-18T11:24:19+02:00 SIMD cleanups, remove virtual Float reg - - - - - 14 changed files: - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/AArch64/Regs.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/PPC.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/PPC/Regs.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToAsm/X86/Regs.hs - compiler/GHC/Platform/Reg.hs Changes: ===================================== compiler/GHC/CmmToAsm/AArch64/Ppr.hs ===================================== @@ -306,7 +306,6 @@ pprReg w r = case r of RegReal (RealRegSingle i) -> ppr_reg_no w i -- virtual regs should not show up, but this is helpful for debugging. RegVirtual (VirtualRegI u) -> text "%vI_" <> pprUniqueAlways u - RegVirtual (VirtualRegF u) -> text "%vF_" <> pprUniqueAlways u RegVirtual (VirtualRegD u) -> text "%vD_" <> pprUniqueAlways u _ -> pprPanic "AArch64.pprReg" (text $ show r) @@ -336,8 +335,8 @@ pprReg w r = case r of isFloatOp :: Operand -> Bool isFloatOp (OpReg _ (RegReal (RealRegSingle i))) | i > 31 = True -isFloatOp (OpReg _ (RegVirtual (VirtualRegF _))) = True isFloatOp (OpReg _ (RegVirtual (VirtualRegD _))) = True +-- SIMD NCG TODO: what about VirtualVecV128? Could be floating-point or not? isFloatOp _ = False pprInstr :: IsDoc doc => Platform -> Instr -> doc ===================================== compiler/GHC/CmmToAsm/AArch64/Regs.hs ===================================== @@ -111,7 +111,7 @@ virtualRegSqueeze cls vr RcFloatOrVector -> case vr of VirtualRegD{} -> 1 - VirtualRegF{} -> 0 + VirtualRegV128{} -> 1 _other -> 0 {-# INLINE realRegSqueeze #-} ===================================== compiler/GHC/CmmToAsm/Format.hs ===================================== @@ -1,13 +1,7 @@ -{-# LANGUAGE DataKinds #-} {-# LANGUAGE LambdaCase #-} -{-# LANGUAGE MagicHash #-} {-# LANGUAGE PatternSynonyms #-} -{-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE ViewPatterns #-} -{-# OPTIONS_GHC -Wno-duplicate-exports #-} - -- Allow bundling II8, II16... with both Format and ScalarFormat - -- | Formats on this architecture -- A Format is a combination of width and class -- @@ -19,19 +13,18 @@ -- properly. eg SPARC doesn't care about FF80. -- module GHC.CmmToAsm.Format ( - Format(Format, VecFormat, II8, II16, II32, II64, FF32, FF64, ..), + Format(..), ScalarFormat(..), intFormat, floatFormat, isIntFormat, - isIntScalarFormat, isFloatFormat, - isFloatScalarFormat, vecFormat, isVecFormat, cmmTypeFormat, formatToWidth, formatInBytes, + isIntScalarFormat, RegFormat(..), takeVirtualRegs, takeRealRegs, @@ -49,9 +42,6 @@ import GHC.Types.Unique.Set import GHC.Utils.Outputable import GHC.Utils.Panic -import Data.Coerce -import Data.Word (Word8) - {- Note [GHC's data format representations] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ GHC has severals types that represent various aspects of data format. @@ -87,57 +77,41 @@ These include: -- here. I've removed them from the x86 version, we'll see what happens --SDM -- ToDo: quite a few occurrences of Format could usefully be replaced by Width -newtype Format = MkFormat { formatBits :: Word8 } - deriving (Eq, Ord) -newtype ScalarFormat = ScalarFormat { scalarFormatBits :: Word8 } - deriving (Eq, Ord) - -pattern II8, II16, II32, II64, FF32, FF64 :: Coercible a Word8 => a -pattern II8 <- ( coerce -> ( 0b0_000 :: Word8 ) ) where { II8 = coerce (0b0_000 :: Word8) } -pattern II16 <- ( coerce -> ( 0b0_001 :: Word8 ) ) where { II16 = coerce (0b0_001 :: Word8) } -pattern II32 <- ( coerce -> ( 0b0_010 :: Word8 ) ) where { II32 = coerce (0b0_010 :: Word8) } -pattern II64 <- ( coerce -> ( 0b0_011 :: Word8 ) ) where { II64 = coerce (0b0_011 :: Word8) } -pattern FF32 <- ( coerce -> ( 0b1_010 :: Word8 ) ) where { FF32 = coerce (0b1_010 :: Word8) } -pattern FF64 <- ( coerce -> ( 0b1_011 :: Word8 ) ) where { FF64 = coerce (0b1_011 :: Word8) } - -pattern Format :: Length -> ScalarFormat -> Format -pattern Format lg b <- ( getFormat -> (# _, lg, b #) ) - where - Format lg b = MkFormat $ scalarFormatBits b .|. ( fromIntegral ( finiteBitSize lg - 1 - countLeadingZeros lg ) `shiftL` 4 ) -pattern VecFormat :: Length -> ScalarFormat -> Format -pattern VecFormat lg b <- ( getFormat -> (# True, lg, b #) ) - where - VecFormat lg b = Format lg b - -{-# COMPLETE Format :: Format #-} -{-# COMPLETE II8, II16, II32, II64, FF32, FF64, VecFormat :: Format #-} -{-# COMPLETE II8, II16, II32, II64, FF32, FF64 :: ScalarFormat #-} -getFormat :: Format -> (# Bool, Length, ScalarFormat #) -getFormat ( MkFormat b ) = (# lg > 1, lg, ScalarFormat (b .&. 0b0000_1111) #) - where - lg = bit ( fromIntegral b `shiftR` 4 ) - -instance Show ScalarFormat where - show = \case - II8 -> "II8" - II16 -> "II16" - II32 -> "II32" - II64 -> "II64" - FF32 -> "FF32" - FF64 -> "FF64" -instance Show Format where - show (Format l f) - | l == 1 - = show f - | otherwise - = "V" ++ show l ++ show f + +data Format + = II8 + | II16 + | II32 + | II64 + | FF32 + | FF64 + | VecFormat !Length -- ^ number of elements + !ScalarFormat -- ^ format of each element + deriving (Show, Eq, Ord) + instance Outputable Format where ppr fmt = text (show fmt) +data ScalarFormat + = FmtInt8 + | FmtInt16 + | FmtInt32 + | FmtInt64 + | FmtFloat + | FmtDouble + deriving (Show, Eq, Ord) + +isIntScalarFormat :: ScalarFormat -> Bool +isIntScalarFormat FmtInt8 = True +isIntScalarFormat FmtInt16 = True +isIntScalarFormat FmtInt32 = True +isIntScalarFormat FmtInt64 = True +isIntScalarFormat _ = False + -- | Get the integer format of this width. intFormat :: Width -> Format intFormat width - = case width of + = case width of W8 -> II8 W16 -> II16 W32 -> II32 @@ -149,37 +123,36 @@ intFormat width -- | Check if a format represents a vector isVecFormat :: Format -> Bool isVecFormat (VecFormat {}) = True -isVecFormat _ = False +isVecFormat _ = False -- | Get the float format of this width. floatFormat :: Width -> Format floatFormat width = case width of - W32 -> FF32 - W64 -> FF64 - other -> pprPanic "Format.floatFormat" (ppr other) + W32 -> FF32 + W64 -> FF64 + + other -> pprPanic "Format.floatFormat" (ppr other) --- | Check if a format represents a scalar integer value. +-- | Check if a format represent an integer value. isIntFormat :: Format -> Bool -isIntFormat(Format l f) - = l == 1 && isIntScalarFormat f -isIntScalarFormat :: ScalarFormat -> Bool -isIntScalarFormat = not . isFloatScalarFormat +isIntFormat = not . isFloatFormat --- | Check if a format represents a scalar floating point value. +-- | Check if a format represents a floating point value. isFloatFormat :: Format -> Bool -isFloatFormat (Format l f) - = l == 1 && isFloatScalarFormat f +isFloatFormat format + = case format of + FF32 -> True + FF64 -> True + _ -> False -isFloatScalarFormat :: ScalarFormat -> Bool -isFloatScalarFormat (ScalarFormat b) = testBit b 3 -- | Convert a Cmm type to a Format. cmmTypeFormat :: CmmType -> Format cmmTypeFormat ty - | isFloatType ty = floatFormat (typeWidth ty) - | isVecType ty = vecFormat ty - | otherwise = intFormat (typeWidth ty) + | isFloatType ty = floatFormat (typeWidth ty) + | isVecType ty = vecFormat ty + | otherwise = intFormat (typeWidth ty) vecFormat :: CmmType -> Format vecFormat ty = @@ -187,31 +160,37 @@ vecFormat ty = elemTy = vecElemType ty in if isFloatType elemTy then case typeWidth elemTy of - W32 -> Format l FF32 - W64 -> Format l FF64 + W32 -> VecFormat l FmtFloat + W64 -> VecFormat l FmtDouble _ -> pprPanic "Incorrect vector element width" (ppr elemTy) else case typeWidth elemTy of - W8 -> Format l II8 - W16 -> Format l II16 - W32 -> Format l II32 - W64 -> Format l II64 + W8 -> VecFormat l FmtInt8 + W16 -> VecFormat l FmtInt16 + W32 -> VecFormat l FmtInt32 + W64 -> VecFormat l FmtInt64 _ -> pprPanic "Incorrect vector element width" (ppr elemTy) -- | Get the Width of a Format. formatToWidth :: Format -> Width -formatToWidth (Format l f) - | l == 1 - = go f - | otherwise - = widthFromBytes (l * widthInBytes (go f)) - where - go = \case - II8 -> W8 - II16 -> W16 - II32 -> W32 - II64 -> W64 - FF32 -> W32 - FF64 -> W64 +formatToWidth format + = case format of + II8 -> W8 + II16 -> W16 + II32 -> W32 + II64 -> W64 + FF32 -> W32 + FF64 -> W64 + VecFormat l s -> + widthFromBytes (l * widthInBytes (scalarWidth s)) + +scalarWidth :: ScalarFormat -> Width +scalarWidth = \case + FmtInt8 -> W8 + FmtInt16 -> W16 + FmtInt32 -> W32 + FmtInt64 -> W64 + FmtFloat -> W32 + FmtDouble -> W64 formatInBytes :: Format -> Int formatInBytes = widthInBytes . formatToWidth @@ -248,4 +227,4 @@ takeRealRegs = mapMaybeUniqSet_sameUnique $ -- See Note [Unique Determinism and code generation] mapRegFormatSet :: (Reg -> Reg) -> UniqSet RegFormat -> UniqSet RegFormat -mapRegFormatSet f = mapUniqSet ( \ ( RegFormat r fmt ) -> RegFormat ( f r ) fmt ) +mapRegFormatSet f = mapUniqSet (\ ( RegFormat r fmt ) -> RegFormat ( f r ) fmt) ===================================== compiler/GHC/CmmToAsm/PPC.hs ===================================== @@ -48,8 +48,8 @@ instance Instruction PPC.Instr where jumpDestsOfInstr = PPC.jumpDestsOfInstr canFallthroughTo = PPC.canFallthroughTo patchJumpInstr = PPC.patchJumpInstr - mkSpillInstr = PPC.mkSpillInstr - mkLoadInstr = PPC.mkLoadInstr + mkSpillInstr cfg reg _ i j = PPC.mkSpillInstr cfg reg i j + mkLoadInstr cfg reg _ i j = PPC.mkLoadInstr cfg reg i j takeDeltaInstr = PPC.takeDeltaInstr isMetaInstr = PPC.isMetaInstr mkRegRegMoveInstr _ = PPC.mkRegRegMoveInstr ===================================== compiler/GHC/CmmToAsm/PPC/Instr.hs ===================================== @@ -41,7 +41,9 @@ import GHC.CmmToAsm.PPC.Cond import GHC.CmmToAsm.Types import GHC.CmmToAsm.Instr (RegUsage(..), noUsage) import GHC.CmmToAsm.Format +import GHC.CmmToAsm.Reg.Target import GHC.CmmToAsm.Config +import GHC.Platform.Reg.Class import GHC.Platform.Reg import GHC.Platform.Regs @@ -66,8 +68,8 @@ import Data.Maybe (fromMaybe) -- archWordFormat :: Bool -> Format archWordFormat is32Bit - | is32Bit = II32 - | otherwise = II64 + | is32Bit = II32 + | otherwise = II64 mkStackAllocInstr :: Platform -> Int -> [Instr] @@ -549,16 +551,21 @@ patchJumpInstr insn patchF mkSpillInstr :: NCGConfig -> Reg -- register to spill - -> Format -> Int -- current stack delta -> Int -- spill slot to use -> [Instr] -mkSpillInstr config reg fmt delta slot +mkSpillInstr config reg delta slot = let platform = ncgPlatform config off = spillSlotToOffset platform slot + arch = platformArch platform in - let instr = case makeImmediate W32 True (off-delta) of + let fmt = case targetClassOfReg platform reg of + RcInteger -> case arch of + ArchPPC -> II32 + _ -> II64 + RcFloatOrVector -> FF64 + instr = case makeImmediate W32 True (off-delta) of Just _ -> ST Nothing -> STFAR -- pseudo instruction: 32 bit offsets @@ -568,16 +575,21 @@ mkSpillInstr config reg fmt delta slot mkLoadInstr :: NCGConfig -> Reg -- register to load - -> Format -> Int -- current stack delta -> Int -- spill slot to use -> [Instr] -mkLoadInstr config reg fmt delta slot +mkLoadInstr config reg delta slot = let platform = ncgPlatform config off = spillSlotToOffset platform slot + arch = platformArch platform in - let instr = case makeImmediate W32 True (off-delta) of + let fmt = case targetClassOfReg platform reg of + RcInteger -> case arch of + ArchPPC -> II32 + _ -> II64 + RcFloatOrVector -> FF64 + instr = case makeImmediate W32 True (off-delta) of Just _ -> LD Nothing -> LDFAR -- pseudo instruction: 32 bit offsets ===================================== compiler/GHC/CmmToAsm/PPC/Ppr.hs ===================================== @@ -199,7 +199,6 @@ pprReg r RegReal (RealRegSingle i) -> ppr_reg_no i RegVirtual (VirtualRegI u) -> text "%vI_" <> pprUniqueAlways u RegVirtual (VirtualRegHi u) -> text "%vHi_" <> pprUniqueAlways u - RegVirtual (VirtualRegF u) -> text "%vF_" <> pprUniqueAlways u RegVirtual (VirtualRegD u) -> text "%vD_" <> pprUniqueAlways u RegVirtual (VirtualRegV128 u) -> text "%vV128_" <> pprUniqueAlways u ===================================== compiler/GHC/CmmToAsm/PPC/Regs.hs ===================================== @@ -86,7 +86,7 @@ virtualRegSqueeze cls vr RcFloatOrVector -> case vr of VirtualRegD{} -> 1 - VirtualRegF{} -> 0 + VirtualRegV128{} -> 1 _other -> 0 {-# INLINE realRegSqueeze #-} @@ -108,14 +108,13 @@ realRegSqueeze cls rr mkVirtualReg :: Unique -> Format -> VirtualReg -mkVirtualReg u fmt = - case fmt of - VecFormat {} -> panic "mkVirtualReg: vector register" - _ | not (isFloatFormat fmt) - -> VirtualRegI u - FF32 -> VirtualRegD u - FF64 -> VirtualRegD u - _ -> panic "mkVirtualReg" +mkVirtualReg u format + | not (isFloatFormat format) = VirtualRegI u + | otherwise + = case format of + FF32 -> VirtualRegD u + FF64 -> VirtualRegD u + _ -> panic "mkVirtualReg" regDotColor :: RealReg -> SDoc regDotColor reg ===================================== compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs ===================================== @@ -239,8 +239,8 @@ allocatableRegsInteger = length $ filter (\r -> regClass r == RcInteger) $ map RealReg allocatableRegs -allocatableRegsFloat :: Int -allocatableRegsFloat - = length $ filter (\r -> regClass r == RcFloatOrVector +allocatableRegsDouble :: Int +allocatableRegsDouble + = length $ filter (\r -> regClass r == RcFloatOrVector) $ map RealReg allocatableRegs -} ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -873,7 +873,7 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc let regclass = classOfVirtualReg r freeRegs_thisClass = frGetFreeRegs platform regclass freeRegs :: [RealReg] vr_fmt = case r of - VirtualRegV128 {} -> VecFormat 2 FF64 + VirtualRegV128 {} -> VecFormat 2 FmtDouble -- It doesn't really matter whether we use e.g. v2f64 or v4f32 -- or v4i32 etc here. This is perhaps a sign that 'Format' -- is not the right type to use here, but that is a battle ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1220,12 +1220,12 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps vector_float_negate_avx :: Length -> Width -> CmmExpr -> NatM Register vector_float_negate_avx l w expr = do - tmp <- getNewRegNat (VecFormat l FF32) + tmp <- getNewRegNat (VecFormat l FmtFloat) (reg, exp) <- getSomeReg expr Amode addr addr_code <- memConstant (mkAlignment $ widthInBytes W32) (CmmFloat 0.0 W32) let format = case w of - W32 -> VecFormat l FF32 - W64 -> VecFormat l FF64 + W32 -> VecFormat l FmtFloat + W64 -> VecFormat l FmtDouble _ -> pprPanic "Cannot negate vector of width" (ppr w) code dst = case w of W32 -> exp `appOL` addr_code `snocOL` @@ -1240,11 +1240,11 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps vector_float_negate_sse :: Length -> Width -> CmmExpr -> NatM Register vector_float_negate_sse l w expr = do - tmp <- getNewRegNat (VecFormat l FF32) + tmp <- getNewRegNat (VecFormat l FmtFloat) (reg, exp) <- getSomeReg expr let format = case w of - W32 -> VecFormat l FF32 - W64 -> VecFormat l FF64 + W32 -> VecFormat l FmtFloat + W64 -> VecFormat l FmtDouble _ -> pprPanic "Cannot negate vector of width" (ppr w) code dst = exp `snocOL` (XOR format (OpReg tmp) (OpReg tmp)) `snocOL` @@ -1260,7 +1260,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps vector_float_broadcast_avx len W32 expr = do (reg, exp) <- getSomeReg expr - let f = VecFormat len FF32 + let f = VecFormat len FmtFloat addr = spRel platform 0 in return $ Any f (\dst -> exp `snocOL` (MOVU f (OpReg reg) (OpAddr addr)) `snocOL` @@ -1268,7 +1268,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps vector_float_broadcast_avx len W64 expr = do (reg, exp) <- getSomeReg expr - let f = VecFormat len FF64 + let f = VecFormat len FmtDouble addr = spRel platform 0 in return $ Any f (\dst -> exp `snocOL` (MOVU f (OpReg reg) (OpAddr addr)) `snocOL` @@ -1284,7 +1284,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps vector_float_broadcast_sse len W32 expr = do (reg, exp) <- getSomeReg expr - let f = VecFormat len FF32 + let f = VecFormat len FmtFloat addr = spRel platform 0 code dst = exp `snocOL` (MOVU f (OpReg reg) (OpAddr addr)) `snocOL` @@ -1307,7 +1307,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps vector_int_broadcast len W64 expr = do (reg, exp) <- getSomeReg expr - let fmt = VecFormat len II64 + let fmt = VecFormat len FmtInt64 return $ Any fmt (\dst -> exp `snocOL` (MOV II64 (OpReg reg) (OpReg dst)) `snocOL` (PUNPCKLQDQ fmt (OpReg dst) dst) `snocOL` @@ -1652,8 +1652,8 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps (reg1, exp1) <- getSomeReg expr1 (reg2, exp2) <- getSomeReg expr2 let format = case w of - W32 -> VecFormat l FF32 - W64 -> VecFormat l FF64 + W32 -> VecFormat l FmtFloat + W64 -> VecFormat l FmtDouble _ -> pprPanic "Operation not supported for width " (ppr w) code dst = case op of VA_Add -> arithInstr VADD @@ -1676,8 +1676,8 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps (reg1, exp1) <- getSomeReg expr1 (reg2, exp2) <- getSomeReg expr2 let format = case w of - W32 -> VecFormat l FF32 - W64 -> VecFormat l FF64 + W32 -> VecFormat l FmtFloat + W64 -> VecFormat l FmtDouble _ -> pprPanic "Operation not supported for width " (ppr w) code dst = case op of VA_Add -> arithInstr ADD @@ -1700,22 +1700,22 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps vector_float_unpack l W32 expr (CmmLit lit) = do (r, exp) <- getSomeReg expr - let format = VecFormat l FF32 + let format = VecFormat l FmtFloat imm = litToImm lit code dst = case lit of - CmmInt 0 _ -> exp `snocOL` (MOVSD FF32 (OpReg r) (OpReg dst)) + CmmInt 0 _ -> exp `snocOL` (MOV FF32 (OpReg r) (OpReg dst)) CmmInt _ _ -> exp `snocOL` (VPSHUFD format imm (OpReg r) dst) _ -> panic "Error in offset while unpacking" return (Any format code) vector_float_unpack l W64 expr (CmmLit lit) = do (r, exp) <- getSomeReg expr - let format = VecFormat l FF64 + let format = VecFormat l FmtDouble code dst = case lit of CmmInt 0 _ -> exp `snocOL` - (MOVSD FF64 (OpReg r) (OpReg dst)) + (MOV FF64 (OpReg r) (OpReg dst)) CmmInt 1 _ -> exp `snocOL` (MOVHLPS format (OpReg r) dst) _ -> panic "Error in offset while unpacking" @@ -1732,7 +1732,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps vector_float_unpack_sse l W32 expr (CmmLit lit) = do (r,exp) <- getSomeReg expr - let format = VecFormat l FF32 + let format = VecFormat l FmtFloat imm = litToImm lit code dst = case lit of @@ -1752,7 +1752,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps vector_int_unpack_sse l at 2 W64 expr (CmmLit lit) = do (r, exp) <- getSomeReg expr - let fmt = VecFormat l II64 + let fmt = VecFormat l FmtInt64 tmp <- getNewRegNat fmt let code dst = case lit of @@ -1770,7 +1770,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps vector_shuffle_float l w v1 v2 is = do (r1, exp1) <- getSomeReg v1 (r2, exp2) <- getSomeReg v2 - let fmt = VecFormat l (if w == W32 then FF32 else FF64) + let fmt = VecFormat l (if w == W32 then FmtFloat else FmtDouble) code dst = exp1 `appOL` (exp2 `appOL` shuffleInstructions fmt r1 r2 is dst) return (Any fmt code) @@ -1778,7 +1778,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps shuffleInstructions :: Format -> Reg -> Reg -> [Int] -> Reg -> OrdList Instr shuffleInstructions fmt v1 v2 is dst = case fmt of - VecFormat 2 FF64 -> + VecFormat 2 FmtDouble -> case is of [i1, i2] -> case (i1, i2) of (0,0) -> unitOL (VSHUFPD fmt (ImmInt 0b00) (OpReg v1) v1 dst) @@ -1799,7 +1799,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps (3,1) -> unitOL (VSHUFPD fmt (ImmInt 0b11) (OpReg v1) v2 dst) _ -> pprPanic "vector shuffle: indices out of bounds 0 <= i <= 3" (ppr is) _ -> pprPanic "vector shuffle: wrong number of indices (expected 2)" (ppr is) - VecFormat 4 FF32 + VecFormat 4 FmtFloat -- indices 0 <= i <= 7 | all ( (>= 0) <&&> (<= 7) ) is -> case is of @@ -1885,7 +1885,7 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps = do fn <- getAnyReg vecExpr (r, exp) <- getSomeReg valExpr - let fmt = VecFormat len FF32 + let fmt = VecFormat len FmtFloat imm = litToImm (CmmInt (offset `shiftL` 4) W32) code dst = exp `appOL` (fn dst) `snocOL` @@ -1896,16 +1896,16 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps = do (valReg, valExp) <- getSomeReg valExpr (vecReg, vecExp) <- getSomeReg vecExpr - let fmt = VecFormat len FF64 + let fmt = VecFormat len FmtDouble code dst = case offset of CmmInt 0 _ -> valExp `appOL` vecExp `snocOL` - (MOVSD FF64 (OpReg valReg) (OpReg dst)) `snocOL` + (MOV FF64 (OpReg valReg) (OpReg dst)) `snocOL` (SHUFPD fmt (ImmInt 0b00) (OpReg vecReg) dst) CmmInt 1 _ -> valExp `appOL` vecExp `snocOL` - (MOVSD FF64 (OpReg vecReg) (OpReg dst)) `snocOL` + (MOV FF64 (OpReg vecReg) (OpReg dst)) `snocOL` (SHUFPD fmt (ImmInt 0b00) (OpReg valReg) dst) _ -> pprPanic "MO_VF_Insert DoubleX2: unsupported offset" (ppr offset) in return $ Any fmt code @@ -1934,7 +1934,7 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps pprTraceM "vecExpr:" (pdoc platform vecExpr) (valReg, valExp) <- getSomeReg valExpr (vecReg, vecExp) <- getSomeReg vecExpr - let fmt = VecFormat len II64 + let fmt = VecFormat len FmtInt64 tmp <- getNewRegNat fmt pprTraceM "tmp:" (ppr tmp) let code dst @@ -2382,7 +2382,7 @@ addAlignmentCheck align reg = where check :: Format -> Reg -> InstrBlock check fmt reg = - assert (isIntFormat fmt) $ + assert (not $ isFloatFormat fmt) $ toOL [ TEST fmt (OpImm $ ImmInt $ align-1) (OpReg reg) , JXX_GBL NE $ ImmCLbl mkBadAlignmentLabel ] ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -373,7 +373,6 @@ data Instr | MOVA Format Operand Operand | MOVDQU Format Operand Operand | VMOVDQU Format Operand Operand - | MOVSD Format Operand Operand -- logic operations | VPXOR Format Reg Reg Reg @@ -530,7 +529,6 @@ regUsageOfInstr platform instr MOVH fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) MOVDQU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) VMOVDQU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) - MOVSD fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) VPXOR fmt s1 s2 dst -> mkRU fmt [s1,s2] [dst] @@ -746,7 +744,6 @@ patchRegsOfInstr instr env MOVH fmt src dst -> MOVH fmt (patchOp src) (patchOp dst) MOVDQU fmt src dst -> MOVDQU fmt (patchOp src) (patchOp dst) VMOVDQU fmt src dst -> VMOVDQU fmt (patchOp src) (patchOp dst) - MOVSD fmt src dst -> MOVSD fmt (patchOp src) (patchOp dst) VPXOR fmt s1 s2 dst -> VPXOR fmt (env s1) (env s2) (env dst) @@ -968,9 +965,6 @@ mkRegRegMoveInstr _platform fmt@(VecFormat _ s) src dst then MOVU fmt (OpReg src) (OpReg dst) else VMOVU fmt (OpReg src) (OpReg dst) mkRegRegMoveInstr _platform fmt src dst - | isFloatFormat fmt - = MOVSD fmt (OpReg src) (OpReg dst) - | otherwise = MOV fmt (OpReg src) (OpReg dst) -- | Check whether an instruction represents a reg-reg move. @@ -991,7 +985,7 @@ takeRegRegMoveInstr platform (MOV fmt (OpReg r1) (OpReg r2)) -- some instructions only support XMM registers. , targetClassOfReg platform r1 == targetClassOfReg platform r2 = Just (r1,r2) -takeRegRegMoveInstr _ (MOVSD fmt (OpReg r1) (OpReg r2)) +takeRegRegMoveInstr _ (MOV fmt (OpReg r1) (OpReg r2)) | not (isVecFormat fmt) = Just (r1,r2) takeRegRegMoveInstr _ (MOVA _ (OpReg r1) (OpReg r2)) ===================================== compiler/GHC/CmmToAsm/X86/Ppr.hs ===================================== @@ -293,7 +293,6 @@ pprReg platform f r else ppr64_reg_no f i RegVirtual (VirtualRegI u) -> text "%vI_" <> pprUniqueAlways u RegVirtual (VirtualRegHi u) -> text "%vHi_" <> pprUniqueAlways u - RegVirtual (VirtualRegF u) -> text "%vF_" <> pprUniqueAlways u RegVirtual (VirtualRegD u) -> text "%vD_" <> pprUniqueAlways u RegVirtual (VirtualRegV128 u) -> text "%vVec_" <> pprUniqueAlways u @@ -431,13 +430,13 @@ pprFormat x = case x of II64 -> text "q" FF32 -> text "ss" -- "scalar single-precision float" (SSE2) FF64 -> text "sd" -- "scalar double-precision float" (SSE2) - VecFormat _ FF32 -> text "ps" - VecFormat _ FF64 -> text "pd" + VecFormat _ FmtFloat -> text "ps" + VecFormat _ FmtDouble -> text "pd" -- TODO: this is shady because it only works for certain instructions - VecFormat _ II8 -> text "b" - VecFormat _ II16 -> text "w" - VecFormat _ II32 -> text "l" - VecFormat _ II64 -> text "q" + VecFormat _ FmtInt8 -> text "b" + VecFormat _ FmtInt16 -> text "w" + VecFormat _ FmtInt32 -> text "l" + VecFormat _ FmtInt64 -> text "q" pprFormat_x87 :: IsLine doc => Format -> doc pprFormat_x87 x = case x of @@ -781,9 +780,9 @@ pprInstr platform i = case i of BT format imm src -> pprFormatImmOp (text "bt") format imm src - CMP fmt@(Format _ s) src dst - | isFloatScalarFormat s -> pprFormatOpOp (text "ucomi") fmt src dst -- SSE2 - | otherwise -> pprFormatOpOp (text "cmp") fmt src dst + CMP format src dst + | isFloatFormat format -> pprFormatOpOp (text "ucomi") format src dst -- SSE2 + | otherwise -> pprFormatOpOp (text "cmp") format src dst TEST format src dst -> pprFormatOpOp (text "test") format' src dst @@ -973,8 +972,6 @@ pprInstr platform i = case i of -> pprOpOp (text "movdqu") format from to VMOVDQU format from to -> pprOpOp (text "vmovdqu") format from to - MOVSD format from to - -> pprOpOp (text "movsd") format from to VPXOR format s1 s2 dst -> pprXor (text "vpxor") format s1 s2 dst @@ -1051,13 +1048,14 @@ pprInstr platform i = case i of char '\t' <> name <> pprBroadcastFormat format <> space pprBroadcastFormat :: Format -> Line doc - pprBroadcastFormat (VecFormat _ f) = case f of - FF32 -> text "ss" - FF64 -> text "sd" - II8 -> text "b" - II16 -> text "w" - II32 -> text "d" - II64 -> text "q" + pprBroadcastFormat (VecFormat _ f) + = case f of + FmtFloat -> text "ss" + FmtDouble -> text "sd" + FmtInt8 -> text "b" + FmtInt16 -> text "w" + FmtInt32 -> text "d" + FmtInt64 -> text "q" pprBroadcastFormat _ = panic "Scalar Format invading vector operation" pprFormatImmOp :: Line doc -> Format -> Imm -> Operand -> doc ===================================== compiler/GHC/CmmToAsm/X86/Regs.hs ===================================== @@ -80,8 +80,7 @@ virtualRegSqueeze cls vr RcFloatOrVector -> case vr of VirtualRegD{} -> 1 - VirtualRegF{} -> 0 - VirtualRegV128{} -> 1 + VirtualRegV128{} -> 1 _other -> 0 ===================================== compiler/GHC/Platform/Reg.hs ===================================== @@ -60,8 +60,6 @@ data VirtualReg = VirtualRegI { virtualRegUnique :: {-# UNPACK #-} !Unique } -- | High part of 2-word virtual register | VirtualRegHi { virtualRegUnique :: {-# UNPACK #-} !Unique } - -- | Float virtual register - | VirtualRegF { virtualRegUnique :: {-# UNPACK #-} !Unique } -- | Double virtual register | VirtualRegD { virtualRegUnique :: {-# UNPACK #-} !Unique } -- | 128-bit wide vector virtual register @@ -87,7 +85,6 @@ instance Outputable VirtualReg where = case reg of VirtualRegI u -> text "%vI_" <> pprUniqueAlways u VirtualRegHi u -> text "%vHi_" <> pprUniqueAlways u - VirtualRegF u -> text "%vFloat_" <> pprUniqueAlways u VirtualRegD u -> text "%vDouble_" <> pprUniqueAlways u VirtualRegV128 u -> text "%vV128_" <> pprUniqueAlways u @@ -100,7 +97,6 @@ classOfVirtualReg vr = case vr of VirtualRegI{} -> RcInteger VirtualRegHi{} -> RcInteger - VirtualRegF{} -> RcFloatOrVector VirtualRegD{} -> RcFloatOrVector VirtualRegV128{} -> RcFloatOrVector View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/62168cfcccf795af856a9a096af78c599502477c...9f6036704c0dcf4ac93c701a3d281976d62085eb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/62168cfcccf795af856a9a096af78c599502477c...9f6036704c0dcf4ac93c701a3d281976d62085eb You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 09:32:12 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Tue, 18 Jun 2024 05:32:12 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] SIMD cleanups, remove virtual Float reg Message-ID: <6671541c63ea9_24605ae2f10825693@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 9ffe722e by sheaf at 2024-06-18T11:31:55+02:00 SIMD cleanups, remove virtual Float reg - - - - - 10 changed files: - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/AArch64/Regs.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/PPC/Regs.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Ppr.hs - compiler/GHC/CmmToAsm/X86/Regs.hs - compiler/GHC/Platform/Reg.hs Changes: ===================================== compiler/GHC/CmmToAsm/AArch64/Ppr.hs ===================================== @@ -306,7 +306,6 @@ pprReg w r = case r of RegReal (RealRegSingle i) -> ppr_reg_no w i -- virtual regs should not show up, but this is helpful for debugging. RegVirtual (VirtualRegI u) -> text "%vI_" <> pprUniqueAlways u - RegVirtual (VirtualRegF u) -> text "%vF_" <> pprUniqueAlways u RegVirtual (VirtualRegD u) -> text "%vD_" <> pprUniqueAlways u _ -> pprPanic "AArch64.pprReg" (text $ show r) @@ -336,8 +335,8 @@ pprReg w r = case r of isFloatOp :: Operand -> Bool isFloatOp (OpReg _ (RegReal (RealRegSingle i))) | i > 31 = True -isFloatOp (OpReg _ (RegVirtual (VirtualRegF _))) = True isFloatOp (OpReg _ (RegVirtual (VirtualRegD _))) = True +-- SIMD NCG TODO: what about VirtualVecV128? Could be floating-point or not? isFloatOp _ = False pprInstr :: IsDoc doc => Platform -> Instr -> doc ===================================== compiler/GHC/CmmToAsm/AArch64/Regs.hs ===================================== @@ -111,7 +111,7 @@ virtualRegSqueeze cls vr RcFloatOrVector -> case vr of VirtualRegD{} -> 1 - VirtualRegF{} -> 0 + VirtualRegV128{} -> 1 _other -> 0 {-# INLINE realRegSqueeze #-} ===================================== compiler/GHC/CmmToAsm/PPC/Ppr.hs ===================================== @@ -199,7 +199,6 @@ pprReg r RegReal (RealRegSingle i) -> ppr_reg_no i RegVirtual (VirtualRegI u) -> text "%vI_" <> pprUniqueAlways u RegVirtual (VirtualRegHi u) -> text "%vHi_" <> pprUniqueAlways u - RegVirtual (VirtualRegF u) -> text "%vF_" <> pprUniqueAlways u RegVirtual (VirtualRegD u) -> text "%vD_" <> pprUniqueAlways u RegVirtual (VirtualRegV128 u) -> text "%vV128_" <> pprUniqueAlways u ===================================== compiler/GHC/CmmToAsm/PPC/Regs.hs ===================================== @@ -86,7 +86,7 @@ virtualRegSqueeze cls vr RcFloatOrVector -> case vr of VirtualRegD{} -> 1 - VirtualRegF{} -> 0 + VirtualRegV128{} -> 1 _other -> 0 {-# INLINE realRegSqueeze #-} ===================================== compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs ===================================== @@ -239,8 +239,8 @@ allocatableRegsInteger = length $ filter (\r -> regClass r == RcInteger) $ map RealReg allocatableRegs -allocatableRegsFloat :: Int -allocatableRegsFloat - = length $ filter (\r -> regClass r == RcFloatOrVector +allocatableRegsDouble :: Int +allocatableRegsDouble + = length $ filter (\r -> regClass r == RcFloatOrVector) $ map RealReg allocatableRegs -} ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -1704,7 +1704,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps imm = litToImm lit code dst = case lit of - CmmInt 0 _ -> exp `snocOL` (MOVSD FF32 (OpReg r) (OpReg dst)) + CmmInt 0 _ -> exp `snocOL` (MOV FF32 (OpReg r) (OpReg dst)) CmmInt _ _ -> exp `snocOL` (VPSHUFD format imm (OpReg r) dst) _ -> panic "Error in offset while unpacking" return (Any format code) @@ -1715,7 +1715,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps code dst = case lit of CmmInt 0 _ -> exp `snocOL` - (MOVSD FF64 (OpReg r) (OpReg dst)) + (MOV FF64 (OpReg r) (OpReg dst)) CmmInt 1 _ -> exp `snocOL` (MOVHLPS format (OpReg r) dst) _ -> panic "Error in offset while unpacking" @@ -1901,11 +1901,11 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps = case offset of CmmInt 0 _ -> valExp `appOL` vecExp `snocOL` - (MOVSD FF64 (OpReg valReg) (OpReg dst)) `snocOL` + (MOV FF64 (OpReg valReg) (OpReg dst)) `snocOL` (SHUFPD fmt (ImmInt 0b00) (OpReg vecReg) dst) CmmInt 1 _ -> valExp `appOL` vecExp `snocOL` - (MOVSD FF64 (OpReg vecReg) (OpReg dst)) `snocOL` + (MOV FF64 (OpReg vecReg) (OpReg dst)) `snocOL` (SHUFPD fmt (ImmInt 0b00) (OpReg valReg) dst) _ -> pprPanic "MO_VF_Insert DoubleX2: unsupported offset" (ppr offset) in return $ Any fmt code ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -1,3 +1,4 @@ +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE TypeFamilies #-} ----------------------------------------------------------------------------- @@ -373,7 +374,6 @@ data Instr | MOVA Format Operand Operand | MOVDQU Format Operand Operand | VMOVDQU Format Operand Operand - | MOVSD Format Operand Operand -- logic operations | VPXOR Format Reg Reg Reg @@ -530,7 +530,6 @@ regUsageOfInstr platform instr MOVH fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) MOVDQU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) VMOVDQU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) - MOVSD fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) VPXOR fmt s1 s2 dst -> mkRU fmt [s1,s2] [dst] @@ -746,7 +745,6 @@ patchRegsOfInstr instr env MOVH fmt src dst -> MOVH fmt (patchOp src) (patchOp dst) MOVDQU fmt src dst -> MOVDQU fmt (patchOp src) (patchOp dst) VMOVDQU fmt src dst -> VMOVDQU fmt (patchOp src) (patchOp dst) - MOVSD fmt src dst -> MOVSD fmt (patchOp src) (patchOp dst) VPXOR fmt s1 s2 dst -> VPXOR fmt (env s1) (env s2) (env dst) @@ -968,9 +966,6 @@ mkRegRegMoveInstr _platform fmt@(VecFormat _ s) src dst then MOVU fmt (OpReg src) (OpReg dst) else VMOVU fmt (OpReg src) (OpReg dst) mkRegRegMoveInstr _platform fmt src dst - | isFloatFormat fmt - = MOVSD fmt (OpReg src) (OpReg dst) - | otherwise = MOV fmt (OpReg src) (OpReg dst) -- | Check whether an instruction represents a reg-reg move. @@ -982,31 +977,32 @@ takeRegRegMoveInstr -> Instr -> Maybe (Reg,Reg) -takeRegRegMoveInstr platform (MOV fmt (OpReg r1) (OpReg r2)) - -- MOV zeroes the upper part of vector registers, - -- so it is not a real "move" in that case. - | not (isVecFormat fmt) - -- Don't eliminate a move between e.g. RAX and XMM: - -- even though we might be using XMM to store a scalar integer value, - -- some instructions only support XMM registers. - , targetClassOfReg platform r1 == targetClassOfReg platform r2 - = Just (r1,r2) -takeRegRegMoveInstr _ (MOVSD fmt (OpReg r1) (OpReg r2)) - | not (isVecFormat fmt) - = Just (r1,r2) -takeRegRegMoveInstr _ (MOVA _ (OpReg r1) (OpReg r2)) - = Just (r1, r2) -takeRegRegMoveInstr _ (MOVU _ (OpReg r1) (OpReg r2)) - = Just (r1, r2) -takeRegRegMoveInstr _ (VMOVU _ (OpReg r1) (OpReg r2)) - = Just (r1, r2) -takeRegRegMoveInstr _ (MOVDQU _ (OpReg r1) (OpReg r2)) - = Just (r1, r2) -takeRegRegMoveInstr _ (VMOVDQU _ (OpReg r1) (OpReg r2)) - = Just (r1, r2) - -takeRegRegMoveInstr _ _ = Nothing - +takeRegRegMoveInstr platform = \case + MOV fmt (OpReg r1) (OpReg r2) + -- MOV zeroes the upper part of vector registers, + -- so it is not a real "move" in that case. + | not (isVecFormat fmt) + -> go r1 r2 + MOVA _ (OpReg r1) (OpReg r2) + -> go r1 r2 + MOVU _ (OpReg r1) (OpReg r2) + -> go r1 r2 + VMOVU _ (OpReg r1) (OpReg r2) + -> go r1 r2 + MOVDQU _ (OpReg r1) (OpReg r2) + -> go r1 r2 + VMOVDQU _ (OpReg r1) (OpReg r2) + -> go r1 r2 + _ -> Nothing + where + go r1 r2 + -- Don't eliminate a move between e.g. RAX and XMM: + -- even though we might be using XMM to store a scalar integer value, + -- some instructions only support XMM registers. + | targetClassOfReg platform r1 == targetClassOfReg platform r2 + = Just (r1, r2) + | otherwise + = Nothing -- | Make an unconditional branch instruction. mkJumpInstr ===================================== compiler/GHC/CmmToAsm/X86/Ppr.hs ===================================== @@ -293,7 +293,6 @@ pprReg platform f r else ppr64_reg_no f i RegVirtual (VirtualRegI u) -> text "%vI_" <> pprUniqueAlways u RegVirtual (VirtualRegHi u) -> text "%vHi_" <> pprUniqueAlways u - RegVirtual (VirtualRegF u) -> text "%vF_" <> pprUniqueAlways u RegVirtual (VirtualRegD u) -> text "%vD_" <> pprUniqueAlways u RegVirtual (VirtualRegV128 u) -> text "%vVec_" <> pprUniqueAlways u @@ -973,8 +972,6 @@ pprInstr platform i = case i of -> pprOpOp (text "movdqu") format from to VMOVDQU format from to -> pprOpOp (text "vmovdqu") format from to - MOVSD format from to - -> pprOpOp (text "movsd") format from to VPXOR format s1 s2 dst -> pprXor (text "vpxor") format s1 s2 dst ===================================== compiler/GHC/CmmToAsm/X86/Regs.hs ===================================== @@ -80,8 +80,7 @@ virtualRegSqueeze cls vr RcFloatOrVector -> case vr of VirtualRegD{} -> 1 - VirtualRegF{} -> 0 - VirtualRegV128{} -> 1 + VirtualRegV128{} -> 1 _other -> 0 ===================================== compiler/GHC/Platform/Reg.hs ===================================== @@ -60,8 +60,6 @@ data VirtualReg = VirtualRegI { virtualRegUnique :: {-# UNPACK #-} !Unique } -- | High part of 2-word virtual register | VirtualRegHi { virtualRegUnique :: {-# UNPACK #-} !Unique } - -- | Float virtual register - | VirtualRegF { virtualRegUnique :: {-# UNPACK #-} !Unique } -- | Double virtual register | VirtualRegD { virtualRegUnique :: {-# UNPACK #-} !Unique } -- | 128-bit wide vector virtual register @@ -87,7 +85,6 @@ instance Outputable VirtualReg where = case reg of VirtualRegI u -> text "%vI_" <> pprUniqueAlways u VirtualRegHi u -> text "%vHi_" <> pprUniqueAlways u - VirtualRegF u -> text "%vFloat_" <> pprUniqueAlways u VirtualRegD u -> text "%vDouble_" <> pprUniqueAlways u VirtualRegV128 u -> text "%vV128_" <> pprUniqueAlways u @@ -100,7 +97,6 @@ classOfVirtualReg vr = case vr of VirtualRegI{} -> RcInteger VirtualRegHi{} -> RcInteger - VirtualRegF{} -> RcFloatOrVector VirtualRegD{} -> RcFloatOrVector VirtualRegV128{} -> RcFloatOrVector View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9ffe722ed4bbbc77b9a4409dff8dcdc4822975ac -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9ffe722ed4bbbc77b9a4409dff8dcdc4822975ac You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 09:37:14 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Tue, 18 Jun 2024 05:37:14 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] add simd012 test Message-ID: <6671554aad344_24605aff6a2c35813@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 4d98b2de by sheaf at 2024-06-18T11:37:06+02:00 add simd012 test - - - - - 3 changed files: - testsuite/tests/simd/should_run/all.T - + testsuite/tests/simd/should_run/simd012.hs - + testsuite/tests/simd/should_run/simd012.stdout Changes: ===================================== testsuite/tests/simd/should_run/all.T ===================================== @@ -16,3 +16,4 @@ test('simd008', [], compile_and_run, ['']) test('simd009', [req_th, extra_files(['Simd009b.hs', 'Simd009c.hs'])], multimod_compile_and_run, ['simd009', '']) test('simd010', [], compile_and_run, ['']) test('simd011', [when(have_cpu_feature('fma'), extra_hc_opts('-mfma'))], compile_and_run, ['']) +test('simd012', [], compile_and_run, ['']) ===================================== testsuite/tests/simd/should_run/simd012.hs ===================================== @@ -0,0 +1,72 @@ +{-# LANGUAGE UnboxedTuples, MagicHash #-} + +module Main where + +import GHC.Exts +import GHC.Word + +main :: IO () +main = + print $ + tuple4b_a tuple4b + 3000 3001 3002 3003 + 3004 3005 3006 3007 + 3008 3009 3010 3011 + 3012 3013 3014 3015 + 3016 3017 3018 3019 + +type T4b = Float -> Double -> Float -> Double + -> Float -> Double -> Float -> Double + -> Float -> Double -> Float -> Double + -> Float -> Double -> Float -> Double + -> Float -> Double -> Float -> Double + -> (# Float#, Double#, Float#, Double# + , Float#, Double#, Float#, Double# + , Float#, Double#, Float#, Double# + , Float#, Double#, Float#, Double# + , Float#, Double#, Float#, Double# #) +tuple4b :: T4b +tuple4b (F# f1) (D# d1) (F# f2) (D# d2) + (F# f3) (D# d3) (F# f4) (D# d4) + (F# f5) (D# d5) (F# f6) (D# d6) + (F# f7) (D# d7) (F# f8) (D# d8) + (F# f9) (D# d9) (F# f10) (D# d10) = + (# f1, d1, f2, d2 + , f3, d3, f4, d4 + , f5, d5, f6, d6 + , f7, d7, f8, d8 + , f9, d9, f10, d10 + #) + +tuple4b_a :: T4b + -> Float -> Double -> Float -> Double + -> Float -> Double -> Float -> Double + -> Float -> Double -> Float -> Double + -> Float -> Double -> Float -> Double + -> Float -> Double -> Float -> Double + -> ( (Float, Double, Float, Double) + , (Float, Double, Float, Double) + , (Float, Double, Float, Double) + , (Float, Double, Float, Double) + , (Float, Double, Float, Double) + ) +tuple4b_a h f1 d1 f2 d2 + f3 d3 f4 d4 + f5 d5 f6 d6 + f7 d7 f8 d8 + f9 d9 f10 d10 = + case h f1 d1 f2 d2 + f3 d3 f4 d4 + f5 d5 f6 d6 + f7 d7 f8 d8 + f9 d9 f10 d10 of + (# g1, e1, g2, e2 + , g3, e3, g4, e4 + , g5, e5, g6, e6 + , g7, e7, g8, e8 + , g9, e9, g10, e10 #) -> + ( (F# g1, D# e1, F# g2, D# e2) + , (F# g3, D# e3, F# g4, D# e4) + , (F# g5, D# e5, F# g6, D# e6) + , (F# g7, D# e7, F# g8, D# e8) + , (F# g9, D# e9, F# g10, D# e10) ) ===================================== testsuite/tests/simd/should_run/simd012.stdout ===================================== @@ -0,0 +1 @@ +((3000.0,3001.0,3002.0,3003.0),(3004.0,3005.0,3006.0,3007.0),(3008.0,3009.0,3010.0,3011.0),(3012.0,3013.0,3014.0,3015.0),(3016.0,3017.0,3018.0,3019.0)) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4d98b2de41ba28d5f6403c42250fb97ad168cf80 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4d98b2de41ba28d5f6403c42250fb97ad168cf80 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 10:20:37 2024 From: gitlab at gitlab.haskell.org (Sven Tennie (@supersven)) Date: Tue, 18 Jun 2024 06:20:37 -0400 Subject: [Git][ghc/ghc][wip/supersven/ghc-9.10-riscv-ncg] More precise mkFarBranches Message-ID: <66715f7551cc8_24605a182a270460d@gitlab.mail> Sven Tennie pushed to branch wip/supersven/ghc-9.10-riscv-ncg at Glasgow Haskell Compiler / GHC Commits: bb677e56 by Sven Tennie at 2024-06-18T10:19:17+00:00 More precise mkFarBranches - - - - - 1 changed file: - compiler/GHC/CmmToAsm/RV64/CodeGen.hs Changes: ===================================== compiler/GHC/CmmToAsm/RV64/CodeGen.hs ===================================== @@ -1855,21 +1855,32 @@ with the sequence: b reg : +and + + b foo + +with the sequence: + + la reg foo + b reg + Compared to AArch64 the target label is loaded to a register, because unconditional jump instructions can only address +/-1MiB. The LA pseudo-instruction will be replaced by up to two real instructions, ensuring correct addressing. +One could surely find more efficient replacements, taking PC-relative addressing +into account. This could be a future improvement. (As far branches are pretty +rare, one might question and measure the value of such improvement.) + RISCV has many pseudo-instructions which emit more than one real instructions. -Thus, our counting algorithm is approximative. (This could be optimized by -either only using real instructions or accounting pseudo-instructions by their -real size.) +Thus, we count the real instructions after the Assembler has seen them. -We make some simplifications in the name of performance which can result in overestimating -jump <-> label offsets: +We make some simplifications in the name of performance which can result in +overestimating jump <-> label offsets: * To avoid having to recalculate the label offsets once we replaced a jump we simply - assume all jumps will be expanded to a three instruction far jump sequence. + assume all label jumps will be expanded to a three instruction far jump sequence. * For labels associated with a info table we assume the info table is 64byte large. Most info tables are smaller than that but it means we don't have to distinguish between multiple types of info tables. @@ -1936,8 +1947,11 @@ genFarBranchAndLink far_target ps = data BlockInRange = InRange | NotInRange BlockId -- See Note [RISCV64 far jumps] -makeFarBranches :: Platform -> LabelMap RawCmmStatics -> [NatBasicBlock Instr] - -> UniqSM [NatBasicBlock Instr] +makeFarBranches :: + Platform -> + LabelMap RawCmmStatics -> + [NatBasicBlock Instr] -> + UniqSM [NatBasicBlock Instr] makeFarBranches {- only used when debugging -} _platform statics basic_blocks = do -- All offsets/positions are counted in multiples of 4 bytes (the size of RISCV64 instructions) -- That is an offset of 1 represents a 4-byte/one instruction offset. @@ -1945,16 +1959,16 @@ makeFarBranches {- only used when debugging -} _platform statics basic_blocks = if func_size < max_jump_dist then pure basic_blocks else do - (_,blocks) <- mapAccumLM (replace_blk lblMap) 0 basic_blocks + (_, blocks) <- mapAccumLM (replace_blk lblMap) 0 basic_blocks pure $ concat blocks - -- pprTrace "lblMap" (ppr lblMap) $ basic_blocks - where + -- pprTrace "lblMap" (ppr lblMap) $ basic_blocks + -- 2^11, 12 bit immediate with one bit is reserved for the sign - max_jump_dist = 2^(11::Int) - 1 :: Int + max_jump_dist = 2 ^ (11 :: Int) - 1 :: Int -- Currently all inline info tables fit into 64 bytes. - max_info_size = 16 :: Int - long_bc_jump_size = 5 :: Int + max_info_size = 16 :: Int + long_bc_jump_size = 5 :: Int long_b_jump_size = 2 :: Int -- Replace out of range conditional jumps with unconditional jumps. @@ -1965,7 +1979,7 @@ makeFarBranches {- only used when debugging -} _platform statics basic_blocks = (!pos', instrs') <- mapAccumLM (replace_jump m) block_pos instrs let instrs'' = concat instrs' -- We might have introduced new labels, so split the instructions into basic blocks again if neccesary. - let (top, split_blocks, no_data) = foldr mkBlocks ([],[],[]) instrs'' + let (top, split_blocks, no_data) = foldr mkBlocks ([], [], []) instrs'' -- There should be no data in the instruction stream at this point massert (null no_data) @@ -1976,80 +1990,111 @@ makeFarBranches {- only used when debugging -} _platform statics basic_blocks = replace_jump !m !pos instr = do case instr of ANN ann instr -> do - (idx,instr':instrs') <- replace_jump m pos instr - pure (idx, ANN ann instr':instrs') - BCOND cond op1 op2 t - -> case target_in_range m t pos of - InRange -> pure (pos+long_bc_jump_size,[instr]) - NotInRange far_target -> do - jmp_code <- genCondFarJump cond op1 op2 far_target - pure (pos+long_bc_jump_size, fromOL jmp_code) - B t - -> case target_in_range m t pos of - InRange -> pure (pos+long_b_jump_size,[instr]) - NotInRange far_target -> do - jmp_code <- genFarJump far_target - pure (pos+long_b_jump_size, fromOL jmp_code) - J t - -> case target_in_range m t pos of - InRange -> pure (pos+long_b_jump_size,[instr]) - NotInRange far_target -> do - jmp_code <- genFarJump far_target - pure (pos+long_b_jump_size, fromOL jmp_code) - BL t ps - -> case target_in_range m t pos of - InRange -> pure (pos+long_b_jump_size,[instr]) - NotInRange far_target -> do - jmp_code <- genFarBranchAndLink far_target ps - pure (pos+long_b_jump_size, fromOL jmp_code) - instr - | isMetaInstr instr -> pure (pos,[instr]) - | otherwise -> pure (pos+1, [instr]) + (idx, instr' : instrs') <- replace_jump m pos instr + pure (idx, ANN ann instr' : instrs') + BCOND cond op1 op2 t -> + case target_in_range m t pos of + InRange -> pure (pos + instr_size instr, [instr]) + NotInRange far_target -> do + jmp_code <- genCondFarJump cond op1 op2 far_target + pure (pos + instr_size instr, fromOL jmp_code) + B t -> + case target_in_range m t pos of + InRange -> pure (pos + instr_size instr, [instr]) + NotInRange far_target -> do + jmp_code <- genFarJump far_target + pure (pos + instr_size instr, fromOL jmp_code) + J t -> + case target_in_range m t pos of + InRange -> pure (pos + instr_size instr, [instr]) + NotInRange far_target -> do + jmp_code <- genFarJump far_target + pure (pos + instr_size instr, fromOL jmp_code) + BL t ps -> + case target_in_range m t pos of + InRange -> pure (pos + instr_size instr, [instr]) + NotInRange far_target -> do + jmp_code <- genFarBranchAndLink far_target ps + pure (pos + instr_size instr, fromOL jmp_code) + _ -> pure (pos + instr_size instr, [instr]) target_in_range :: LabelMap Int -> Target -> Int -> BlockInRange target_in_range m target src = case target of - (TReg{}) -> InRange + (TReg {}) -> InRange (TBlock bid) -> block_in_range m src bid block_in_range :: LabelMap Int -> Int -> BlockId -> BlockInRange block_in_range m src_pos dest_lbl = case mapLookup dest_lbl m of - Nothing -> - pprTrace "not in range" (ppr dest_lbl) $ - NotInRange dest_lbl - Just dest_pos -> if abs (dest_pos - src_pos) < max_jump_dist - then InRange - else NotInRange dest_lbl + Nothing -> + pprTrace "not in range" (ppr dest_lbl) + $ NotInRange dest_lbl + Just dest_pos -> + if abs (dest_pos - src_pos) < max_jump_dist + then InRange + else NotInRange dest_lbl calc_lbl_positions :: (Int, LabelMap Int) -> GenBasicBlock Instr -> (Int, LabelMap Int) - calc_lbl_positions (pos, m) (BasicBlock lbl instrs) - = let !pos' = pos + infoTblSize_maybe lbl - in foldl' instr_pos (pos',mapInsert lbl pos' m) instrs + calc_lbl_positions (pos, m) (BasicBlock lbl instrs) = + let !pos' = pos + infoTblSize_maybe lbl + in foldl' instr_pos (pos', mapInsert lbl pos' m) instrs instr_pos :: (Int, LabelMap Int) -> Instr -> (Int, LabelMap Int) - instr_pos (pos, m) instr = - case instr of - ANN _ann instr -> instr_pos (pos, m) instr - NEWBLOCK _bid -> panic "mkFarBranched - unexpected NEWBLOCK" -- At this point there should be no NEWBLOCK - -- in the instruction stream - -- (pos, mapInsert bid pos m) - COMMENT{} -> (pos, m) - instr - | Just jump_size <- is_expandable_jump instr -> (pos+jump_size, m) - | otherwise -> (pos+1, m) + instr_pos (pos, m) instr = (pos + instr_size instr, m) infoTblSize_maybe bid = case mapLookup bid statics of - Nothing -> 0 :: Int + Nothing -> 0 :: Int Just _info_static -> max_info_size - -- These jumps have a 12bit immediate as offset which is quite - -- limiting so we potentially have to expand them into - -- multiple instructions. - is_expandable_jump i = case i of - BCOND{} -> Just long_bc_jump_size - J (TBlock _) -> Just long_b_jump_size - B (TBlock _) -> Just long_b_jump_size - BL (TBlock _) _ -> Just long_b_jump_size - _ -> Nothing + instr_size :: Instr -> Int + instr_size i = case i of + COMMENT {} -> 0 + MULTILINE_COMMENT {} -> 0 + ANN _ instr -> instr_size instr + LOCATION {} -> 0 + DELTA {} -> 0 + -- At this point there should be no NEWBLOCK in the instruction stream (pos, mapInsert bid pos m) + NEWBLOCK {} -> panic "mkFarBranched - Unexpected" + LDATA {} -> panic "mkFarBranched - Unexpected" + PUSH_STACK_FRAME -> 4 + POP_STACK_FRAME -> 4 + ADD {} -> 1 + MUL {} -> 1 + SMULH {} -> 1 + NEG {} -> 1 + DIV {} -> 1 + REM {} -> 1 + REMU {} -> 1 + SUB {} -> 1 + DIVU {} -> 1 + AND {} -> 1 + OR {} -> 1 + ASR {} -> 1 + XOR {} -> 1 + LSL {} -> 1 + LSR {} -> 1 + MOV {} -> 2 + ORI {} -> 1 + XORI {} -> 1 + CSET {} -> 2 + STR {} -> 1 + LDR {} -> 3 + LDRU {} -> 1 + DMBSY {} -> 1 + FCVT {} -> 1 + SCVTF {} -> 1 + FCVTZS {} -> 1 + FABS {} -> 1 + FMA {} -> 1 + -- estimate the subsituted size for jumps to lables + -- jumps to registers have size 1 + BCOND {} -> long_bc_jump_size + J (TBlock _) -> long_b_jump_size + J (TReg _) -> 1 + B (TBlock _) -> long_b_jump_size + B (TReg _) -> 1 + BL (TBlock _) _ -> long_b_jump_size + BL (TReg _) _ -> 1 + J_TBL {} -> 1 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bb677e56ce808b8fc3ca8b03e48ad0e535d6050f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bb677e56ce808b8fc3ca8b03e48ad0e535d6050f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 10:45:51 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Tue, 18 Jun 2024 06:45:51 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] fix getStackSlotFor FF32 Message-ID: <6671655f9fbfa_24605a1c64138602f@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 8d32ceb9 by sheaf at 2024-06-18T12:45:42+02:00 fix getStackSlotFor FF32 - - - - - 2 changed files: - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs Changes: ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -878,7 +878,10 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc -- or v4i32 etc here. This is perhaps a sign that 'Format' -- is not the right type to use here, but that is a battle -- for another day. - _ -> II64 + VirtualRegD {} -> FF64 + VirtualRegI {} -> II64 + VirtualRegHi {} -> II64 + -- Can we put the variable into a register it already was? pref_reg <- findPrefRealReg r ===================================== compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs ===================================== @@ -55,7 +55,7 @@ getStackSlotFor fs@(StackMap _ reserved) _fmt regUnique getStackSlotFor (StackMap freeSlot reserved) fmt regUnique = let - nbSlots = formatInBytes fmt `div` 8 + nbSlots = max 1 (formatInBytes fmt `div` 8) in (StackMap (freeSlot+nbSlots) (addToUFM reserved regUnique freeSlot), freeSlot) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8d32ceb97496ca9e7644dd758270bb198f490a13 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8d32ceb97496ca9e7644dd758270bb198f490a13 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 11:18:27 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Tue, 18 Jun 2024 07:18:27 -0400 Subject: [Git][ghc/ghc][wip/fix-small-addr-space] 49 commits: Improve haddocks of Language.Haskell.Syntax.Pat.Pat Message-ID: <66716d03baa68_24605a22cd9d4702a1@gitlab.mail> Cheng Shao pushed to branch wip/fix-small-addr-space at Glasgow Haskell Compiler / GHC Commits: 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - cdad0da3 by Cheng Shao at 2024-06-18T11:18:17+00:00 testsuite: remove obsolete stderr files for outofmem - - - - - d954b77a by Cheng Shao at 2024-06-18T11:18:17+00:00 hadrian/testsuite: support have_large_address_space This patch adds the `have_large_address_space` predicate to the testsuite. This information comes from ghcautoconf.h which is read by hadrian, both in-tree/out-of-tree cases are handled. - - - - - 8afaa331 by Cheng Shao at 2024-06-18T11:18:17+00:00 testsuite: skip test cases that doesn't work with --disable-large-address-space - - - - - 30 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - CODEOWNERS - compiler/GHC/Builtin/Names.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Driver/Config/StgToCmm.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Binds.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dc5a1bc399215121bec3a15c0b023629842585f3...8afaa33164baa095180dae67b801efe5045e60c6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dc5a1bc399215121bec3a15c0b023629842585f3...8afaa33164baa095180dae67b801efe5045e60c6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 11:27:36 2024 From: gitlab at gitlab.haskell.org (Cheng Shao (@TerrorJack)) Date: Tue, 18 Jun 2024 07:27:36 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/ghcid-multi-repl Message-ID: <66716f28b3227_24605a2526dac70984@gitlab.mail> Cheng Shao pushed new branch wip/ghcid-multi-repl at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/ghcid-multi-repl You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 11:32:09 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 18 Jun 2024 07:32:09 -0400 Subject: [Git][ghc/ghc][wip/romes/12935] 3 commits: Revert "Do uniq renaming before SRTs" Message-ID: <66717039beeaf_24605a25f9734712b7@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/12935 at Glasgow Haskell Compiler / GHC Commits: 882530a0 by Rodrigo Mesquita at 2024-06-17T16:33:36+01:00 Revert "Do uniq renaming before SRTs" This reverts commit db38b635d626106e40b3ab18091e0a24046c30c5. - - - - - d8aea116 by Rodrigo Mesquita at 2024-06-18T12:07:18+01:00 Do on CmmGroup - - - - - 4a375647 by Rodrigo Mesquita at 2024-06-18T12:31:52+01:00 Do uniq-renaming pass right at `codeGen` - - - - - 5 changed files: - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Data/Stream.hs - compiler/GHC/Driver/GenerateCgIPEStub.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/StgToCmm.hs Changes: ===================================== compiler/GHC/Cmm/Pipeline.hs ===================================== @@ -19,7 +19,6 @@ import GHC.Cmm.ProcPoint import GHC.Cmm.Sink import GHC.Cmm.Switch.Implement import GHC.Cmm.ThreadSanitizer -import GHC.Cmm.UniqueRenamer import GHC.Types.Unique.Supply @@ -43,27 +42,18 @@ cmmPipeline :: Logger -> CmmConfig -> ModuleSRTInfo -- Info about SRTs generated so far - -> DetUniqFM -> CmmGroup -- Input C-- with Procedures - -> IO (ModuleSRTInfo, (DetUniqFM, CmmGroupSRTs)) -- Output CPS transformed C-- + -> IO (ModuleSRTInfo, CmmGroupSRTs) -- Output CPS transformed C-- -cmmPipeline logger cmm_config srtInfo detRnEnv prog = do +cmmPipeline logger cmm_config srtInfo prog = do let forceRes (info, group) = info `seq` foldr seq () group let platform = cmmPlatform cmm_config withTimingSilent logger (text "Cmm pipeline") forceRes $ do - - -- To produce deterministic object code, we alpha-rename all Uniques to deterministic uniques before Cmm linting. - -- From here on out, the backend code generation can't use (non-deterministic) Uniques, or risk producing non-deterministic code. - -- For example, the fix-up action in the ASM NCG should use determinist names for potential new blocks it has to create. - -- Therefore, in the ASM NCG `NatM` Monad we use a deterministic `UniqSuply` (which won't be shared about multiple threads) - -- TODO: Put these all into notes carefully organized - let (rn_mapping, renamed_prog) = detRenameUniques detRnEnv prog -- TODO: if gopt Opt_DeterministicObjects dflags - - (procs, data_) <- {-# SCC "tops" #-} partitionWithM (cpsTop logger platform cmm_config) renamed_prog + (procs, data_) <- {-# SCC "tops" #-} partitionWithM (cpsTop logger platform cmm_config) prog (srtInfo, cmms) <- {-# SCC "doSRTs" #-} doSRTs cmm_config srtInfo procs data_ dumpWith logger Opt_D_dump_cmm_cps "Post CPS Cmm" FormatCMM (pdoc platform cmms) - return (srtInfo, (rn_mapping, cmms)) + return (srtInfo, cmms) -- | The Cmm pipeline for a single 'CmmDecl'. Returns: ===================================== compiler/GHC/Data/Stream.hs ===================================== @@ -60,6 +60,7 @@ newtype Stream m a b = (a -> m r') -- For fusing calls to `map` and `mapM` -> (b -> StreamS m r' r) -- For fusing `>>=` -> StreamS m r' r } +-- romes:TODO: I suppose this lends itself well to parallelism? Perhaps we could make Stream be as parallel as possible? runStream :: Applicative m => Stream m r' r -> StreamS m r' r runStream st = runStreamInternal st pure Done ===================================== compiler/GHC/Driver/GenerateCgIPEStub.hs ===================================== @@ -35,7 +35,6 @@ import GHC.Unit.Types (Module, moduleName) import GHC.Unit.Module (moduleNameString) import qualified GHC.Utils.Logger as Logger import GHC.Utils.Outputable (ppr) -import GHC.Cmm.UniqueRenamer (emptyDetUFM) {- Note [Stacktraces from Info Table Provenance Entries (IPE based stack unwinding)] @@ -212,7 +211,7 @@ generateCgIPEStub hsc_env this_mod denv (nonCaffySet, moduleLFInfos, infoTablesW let denv' = denv {provInfoTables = Map.mapKeys cit_lbl infoTablesWithTickishes} ((mIpeStub, ipeCmmGroup), _) = runC (initStgToCmmConfig dflags this_mod) fstate cgState $ getCmm (initInfoTableProv initStats (Map.keys infoTablesWithTickishes) denv') - (_, (_, ipeCmmGroupSRTs)) <- liftIO $ cmmPipeline logger cmm_cfg (emptySRT this_mod) emptyDetUFM ipeCmmGroup + (_, ipeCmmGroupSRTs) <- liftIO $ cmmPipeline logger cmm_cfg (emptySRT this_mod) ipeCmmGroup Stream.yield ipeCmmGroupSRTs ipeStub <- ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -298,8 +298,6 @@ import GHC.StgToCmm.Utils (IPEStats) import GHC.Types.Unique.FM import GHC.Types.Unique.DFM import GHC.Cmm.Config (CmmConfig) -import GHC.Cmm.UniqueRenamer -import Data.Bifunctor {- ********************************************************************** @@ -2078,7 +2076,6 @@ hscCompileCmmFile hsc_env original_filename filename output_filename = runHsc hs $ parseCmmFile cmmpConfig cmm_mod home_unit filename let msgs = warns `unionMessages` errs return (GhcPsMessage <$> msgs, cmm) - liftIO $ do putDumpFileMaybe logger Opt_D_dump_cmm_verbose_by_proc "Parsed Cmm" FormatCMM (pdoc platform cmm) @@ -2088,10 +2085,8 @@ hscCompileCmmFile hsc_env original_filename filename output_filename = runHsc hs -- Re-ordering here causes breakage when booting with C backend because -- in C we must declare before use, but SRT algorithm is free to -- re-order [A, B] (B refers to A) when A is not CAFFY and return [B, A] - (rn_mapping, cmmgroup) <- - second concat <$> mapAccumLM (\rn_mapping cmm -> snd <$> cmmPipeline logger cmm_config (emptySRT cmm_mod) rn_mapping [cmm]) emptyDetUFM cmm - - debugTraceMsg logger 3 (text "DetRnM mapping:" <+> ppr rn_mapping) + cmmgroup <- + concatMapM (\cmm -> snd <$> cmmPipeline logger cmm_config (emptySRT cmm_mod) [cmm]) cmm unless (null cmmgroup) $ putDumpFileMaybe logger Opt_D_dump_cmm "Output Cmm" @@ -2183,10 +2178,9 @@ doCodeGen hsc_env this_mod denv data_tycons pipeline_stream :: Stream IO CmmGroupSRTs CmmCgInfos pipeline_stream = do - ((mod_srt_info, ipes, ipe_stats, rn_mapping), lf_infos) <- + ((mod_srt_info, ipes, ipe_stats), lf_infos) <- {-# SCC "cmmPipeline" #-} - Stream.mapAccumL_ (pipeline_action logger cmm_config) (emptySRT this_mod, M.empty, mempty, emptyDetUFM) ppr_stream1 - liftIO $ debugTraceMsg logger 3 (text "DetRnM mapping:" <+> ppr rn_mapping) + Stream.mapAccumL_ (pipeline_action logger cmm_config) (emptySRT this_mod, M.empty, mempty) ppr_stream1 let nonCaffySet = srtMapNonCAFs (moduleSRTMap mod_srt_info) cmmCgInfos <- generateCgIPEStub hsc_env this_mod denv (nonCaffySet, lf_infos, ipes, ipe_stats) return cmmCgInfos @@ -2194,11 +2188,11 @@ doCodeGen hsc_env this_mod denv data_tycons pipeline_action :: Logger -> CmmConfig - -> (ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats, DetUniqFM) + -> (ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats) -> CmmGroup - -> IO ((ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats, DetUniqFM), CmmGroupSRTs) - pipeline_action logger cmm_config (mod_srt_info, ipes, stats, detRnEnv) cmm_group = do - (mod_srt_info', (rn_mapping, cmm_srts)) <- cmmPipeline logger cmm_config mod_srt_info detRnEnv cmm_group + -> IO ((ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats), CmmGroupSRTs) + pipeline_action logger cmm_config (mod_srt_info, ipes, stats) cmm_group = do + (mod_srt_info', cmm_srts) <- cmmPipeline logger cmm_config mod_srt_info cmm_group -- If -finfo-table-map is enabled, we precompute a map from info -- tables to source locations. See Note [Mapping Info Tables to Source @@ -2209,7 +2203,7 @@ doCodeGen hsc_env this_mod denv data_tycons else return (ipes, stats) - return ((mod_srt_info', ipes', stats', rn_mapping), cmm_srts) + return ((mod_srt_info', ipes', stats'), cmm_srts) dump2 a = do unless (null a) $ ===================================== compiler/GHC/StgToCmm.hs ===================================== @@ -67,6 +67,7 @@ import System.IO.Unsafe import qualified Data.ByteString as BS import Data.IORef import GHC.Utils.Panic +import GHC.Cmm.UniqueRenamer codeGen :: Logger -> TmpFs @@ -79,6 +80,7 @@ codeGen :: Logger -> Stream IO CmmGroup ModuleLFInfos -- Output as a stream, so codegen can -- be interleaved with output +-- romes:TODO: it looks like we could do a lot of this in parallel... codeGen logger tmpfs cfg (InfoTableProvMap (UniqMap denv) _ _) data_tycons cost_centre_info stg_binds hpc_info = do { -- cg: run the code generator, and yield the resulting CmmGroup @@ -86,18 +88,29 @@ codeGen logger tmpfs cfg (InfoTableProvMap (UniqMap denv) _ _) data_tycons -- we would need to add a state monad layer which regresses -- allocations by 0.5-2%. ; cgref <- liftIO $ initC >>= \s -> newIORef s + ; uniqRnRef <- liftIO $ newIORef emptyDetUFM ; let cg :: FCode a -> Stream IO CmmGroup a cg fcode = do (a, cmm) <- liftIO . withTimingSilent logger (text "STG -> Cmm") (`seq` ()) $ do st <- readIORef cgref let fstate = initFCodeState $ stgToCmmPlatform cfg - let (a,st') = runC cfg fstate st (getCmm fcode) + let ((a, cmm),st') = runC cfg fstate st (getCmm fcode) -- NB. stub-out cgs_tops and cgs_stmts. This fixes -- a big space leak. DO NOT REMOVE! -- This is observed by the #3294 test writeIORef cgref $! (st'{ cgs_tops = nilOL, cgs_stmts = mkNop }) - return a + + -- To produce deterministic object code, we alpha-rename all Uniques to deterministic uniques before Cmm linting. + -- From here on out, the backend code generation can't use (non-deterministic) Uniques, or risk producing non-deterministic code. + -- For example, the fix-up action in the ASM NCG should use determinist names for potential new blocks it has to create. + -- Therefore, in the ASM NCG `NatM` Monad we use a deterministic `UniqSuply` (which won't be shared about multiple threads) + -- TODO: Put these all into notes carefully organized + rn_mapping <- liftIO $ readIORef uniqRnRef + let (rn_mapping', renamed_cmm) = detRenameUniques rn_mapping cmm -- todo: if gopt Opt_DeterministicObjects dflags + writeIORef uniqRnRef $! rn_mapping' + + return (a, renamed_cmm) yield cmm return a @@ -138,6 +151,8 @@ codeGen logger tmpfs cfg (InfoTableProvMap (UniqMap denv) _ _) data_tycons | otherwise = mkNameEnv (Prelude.map extractInfo (nonDetEltsUFM cg_id_infos)) + ; rn_mapping <- liftIO $ readIORef uniqRnRef + ; liftIO $ debugTraceMsg logger 3 (text "DetRnM mapping:" <+> ppr rn_mapping) ; return generatedInfo } View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/db38b635d626106e40b3ab18091e0a24046c30c5...4a3756478fb791071c75c5d6b9393aa4353fcaa1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/db38b635d626106e40b3ab18091e0a24046c30c5...4a3756478fb791071c75c5d6b9393aa4353fcaa1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 13:34:52 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Tue, 18 Jun 2024 09:34:52 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] X86 NCG: use FF64 format for Float MOV instructions Message-ID: <66718cfcf0f3f_25c8b01d0e5c668f2@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 95d3ef7b by sheaf at 2024-06-18T15:34:41+02:00 X86 NCG: use FF64 format for Float MOV instructions - - - - - 1 changed file: - compiler/GHC/CmmToAsm/X86/Instr.hs Changes: ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -875,7 +875,7 @@ mkSpillInstr config reg fmt delta slot -> [MOVU fmt (OpReg reg) (OpAddr (spRel platform off))] -- NB: not using MOVA, because we have no guarantees about the stack -- being sufficiently aligned, including even numbered stack slots. - _ -> [MOV fmt (OpReg reg) (OpAddr (spRel platform off))] + _ -> [MOV (scalarMoveFormat platform fmt) (OpReg reg) (OpAddr (spRel platform off))] where platform = ncgPlatform config -- | Make a spill reload instruction. @@ -897,8 +897,7 @@ mkLoadInstr config reg fmt delta slot -> [MOVU fmt (OpAddr (spRel platform off)) (OpReg reg)] -- NB: not using MOVA, because we have no guarantees about the stack -- being sufficiently aligned, including even numbered stack slots. - _ -> [MOV fmt (OpAddr (spRel platform off)) (OpReg reg)] - + _ -> [MOV (scalarMoveFormat platform fmt) (OpAddr (spRel platform off)) (OpReg reg)] where platform = ncgPlatform config spillSlotSize :: Platform -> Int @@ -965,8 +964,19 @@ mkRegRegMoveInstr _platform fmt@(VecFormat _ s) src dst = if widthInBytes (formatToWidth fmt) <= 128 then MOVU fmt (OpReg src) (OpReg dst) else VMOVU fmt (OpReg src) (OpReg dst) -mkRegRegMoveInstr _platform fmt src dst - = MOV fmt (OpReg src) (OpReg dst) +mkRegRegMoveInstr platform fmt src dst + = MOV (scalarMoveFormat platform fmt) (OpReg src) (OpReg dst) + +scalarMoveFormat :: Platform -> Format -> Format +scalarMoveFormat platform fmt + | isFloatFormat fmt + = FF64 + | II64 <- fmt + = II64 + | PW4 <- platformWordSize platform + = II32 + | otherwise + = II64 -- | Check whether an instruction represents a reg-reg move. -- The register allocator attempts to eliminate reg->reg moves whenever it can, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/95d3ef7b4fc000185338aae2757bf8752e3cec92 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/95d3ef7b4fc000185338aae2757bf8752e3cec92 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 13:37:38 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 18 Jun 2024 09:37:38 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 12 commits: Clarify -XGADTs enables existential quantification Message-ID: <66718da1ec0f0_25c8b039bc8c78670@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 2cf22b7e by sheaf at 2024-06-18T09:36:40-04:00 Clarify -XGADTs enables existential quantification Even though -XGADTs does not turn on -XExistentialQuantification, it does allow the user of existential quantification syntax, without needing to use GADT-style syntax. Fixes #20865 - - - - - 77c04b4f by David Binder at 2024-06-18T09:36:44-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - 2516d7ae by Fendor at 2024-06-18T09:36:44-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - bfd23255 by Fendor at 2024-06-18T09:36:44-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18698b T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The tests T16875 and T18698b fail on i386-linux for the same reason. - - - - - 5dd66072 by Andreas Klebinger at 2024-06-18T09:36:45-04:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - 8ec19242 by Jakob Bruenker at 2024-06-18T09:36:46-04:00 Update user guide to indicate support for 64-tuples - - - - - b98668d9 by Andreas Klebinger at 2024-06-18T09:36:47-04:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 3adb1384 by Jakob Bruenker at 2024-06-18T09:36:48-04:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - dd2a0226 by Jan Hrček at 2024-06-18T09:36:55-04:00 Remove duplicate Anno instances - - - - - 416c59e4 by Sven Tennie at 2024-06-18T09:36:55-04:00 AArch64: Delete unused RegNos This has the additional benefit of getting rid of the -1 encoding (real registers start at 0.) - - - - - daf7b443 by Sjoerd Visscher at 2024-06-18T09:36:58-04:00 Bump stm submodule to current master - - - - - 7a0f02bc by Cheng Shao at 2024-06-18T09:36:59-04:00 testsuite: bump T17572 timeout on wasm32 - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/Hs.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - docs/users_guide/9.12.1-notes.rst - docs/users_guide/bugs.rst - docs/users_guide/exts/gadt.rst - docs/users_guide/exts/representation_polymorphism.rst - docs/users_guide/profiling.rst - docs/users_guide/runtime_control.rst - libraries/base/changelog.md - libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc - libraries/ghc-internal/src/GHC/Internal/Unsafe/Coerce.hs - libraries/ghc-prim/GHC/Types.hs - libraries/stm - linters/lint-notes/Main.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/35de8a60fdf5fcd285de56ebaa290e3f87bad4fd...7a0f02bc7a2884986dd6cb5231255f94348addf7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/35de8a60fdf5fcd285de56ebaa290e3f87bad4fd...7a0f02bc7a2884986dd6cb5231255f94348addf7 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 14:35:58 2024 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Tue, 18 Jun 2024 10:35:58 -0400 Subject: [Git][ghc/ghc][wip/andreask/bytecode_tagging] GHCi interpreter: Tag constructor closures when possible. Message-ID: <66719b4e3bdbf_1d931d5281b8112699@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/bytecode_tagging at Glasgow Haskell Compiler / GHC Commits: fa968687 by Andreas Klebinger at 2024-06-18T16:20:39+02:00 GHCi interpreter: Tag constructor closures when possible. When evaluating PUSH_G try to tag the reference we are pushing if it's a constructor or function. This is potentially helpful for performance and required to fix #24870. - - - - - 5 changed files: - compiler/GHC/ByteCode/Instr.hs - rts/Interpreter.c - + testsuite/tests/th/should_compile/T24870/Def.hs - + testsuite/tests/th/should_compile/T24870/Use.hs - + testsuite/tests/th/should_compile/T24870/all.T Changes: ===================================== compiler/GHC/ByteCode/Instr.hs ===================================== @@ -83,7 +83,7 @@ data BCInstr | PUSH16_W !ByteOff | PUSH32_W !ByteOff - -- Push a ptr (these all map to PUSH_G really) + -- Push a (heap) ptr (these all map to PUSH_G really) | PUSH_G Name | PUSH_PRIMOP PrimOp | PUSH_BCO (ProtoBCO Name) ===================================== rts/Interpreter.c ===================================== @@ -4,6 +4,30 @@ * Copyright (c) The GHC Team, 1994-2002. * ---------------------------------------------------------------------------*/ +/* +Note [CBV Functions and the interpreter] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +When the byte code interpreter loads a reference to a value it often +ends up as a non-tagged pointers *especially* if we already know a value +is a certain constructor and therefore don't perform an eval on the reference. +This causes friction with CBV functions which assume +their value arguments are properly tagged by the caller. + +In order to ensure CBV functions still get passed tagged functions we have +three options: +a) Special case the interpreter behaviour into the tag inference analysis. + If we assume the interpreter can't properly tag value references the STG passes + would then wrap such calls in appropriate evals which are executed at runtime. + This would ensure tags by doing additional evals at runtime. +b) When the interpreter pushes references for known constructors instead of + pushing the objects address add the tag to the value pushed. This is what + the NCG backends do. +c) When the interpreter pushes a reference inspect the closure of the object + and apply the appropriate tag at runtime. + +For now we use approach c). Mostly because it's easiest to implement. We also don't +tag functions as tag inference currently doesn't rely on those being properly tagged. +*/ #include "rts/PosixSource.h" #include "Rts.h" @@ -292,6 +316,18 @@ STATIC_INLINE StgClosure *tagConstr(StgClosure *con) { return TAG_CLOSURE(stg_min(TAG_MASK, 1 + GET_TAG(con)), con); } +// Compute the pointer tag for the function and tag the pointer; +STATIC_INLINE StgClosure *tagFun(StgClosure *fun) { + StgHalfWord tag = GET_TAG(fun); + if(tag > TAG_MASK) { return fun; } + else { + return TAG_CLOSURE(tag, fun); + } + + +} + + static StgWord app_ptrs_itbl[] = { (W_)&stg_ap_p_info, (W_)&stg_ap_pp_info, @@ -1306,7 +1342,52 @@ run_BCO: case bci_PUSH_G: { W_ o1 = BCO_GET_LARGE_ARG; - SpW(-1) = BCO_PTR(o1); + StgClosure *tagged_obj = (StgClosure*) BCO_PTR(o1); + + tag_push_g: + ASSERT(LOOKS_LIKE_CLOSURE_PTR((StgClosure*) tagged_obj)); + // Here we make sure references we push are tagged. + // See Note [CBV Functions and the interpreter] in Info.hs + + //Safe some memory reads if we already have a tag. + if(GET_CLOSURE_TAG(tagged_obj) == 0) { + StgClosure *obj = UNTAG_CLOSURE(tagged_obj); + switch ( get_itbl(obj)->type ) { + case IND: + case IND_STATIC: + { + tagged_obj = ACQUIRE_LOAD(&((StgInd*)obj)->indirectee); + goto tag_push_g; + } + case CONSTR: + case CONSTR_1_0: + case CONSTR_0_1: + case CONSTR_2_0: + case CONSTR_1_1: + case CONSTR_0_2: + case CONSTR_NOCAF: + // The value is already evaluated, so we can just return it. However, + // before we do, we MUST ensure that the pointer is tagged, because we + // might return to a native `case` expression, which assumes the returned + // pointer is tagged so it can use the tag to select an alternative. + tagged_obj = tagConstr(obj); + break; + case FUN: + case FUN_1_0: + case FUN_0_1: + case FUN_2_0: + case FUN_1_1: + case FUN_0_2: + case FUN_STATIC: + // Purely for performance since we already hit memory anyway. + tagged_obj = tagFun(obj); + break; + default: + break; + } + } + + SpW(-1) = (W_) tagged_obj; Sp_subW(1); goto nextInsn; } ===================================== testsuite/tests/th/should_compile/T24870/Def.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE TemplateHaskell #-} + +module SDef where + +{-# NOINLINE aValue #-} +aValue = True + +{-# NOINLINE aStrictFunction #-} +aStrictFunction !x = [| x |] ===================================== testsuite/tests/th/should_compile/T24870/Use.hs ===================================== @@ -0,0 +1,9 @@ +{-# LANGUAGE TemplateHaskell #-} + +module SUse where + +import qualified Language.Haskell.TH.Syntax as TH +import SDef +import GHC.Exts + +bar = $( inline aStrictFunction aValue ) ===================================== testsuite/tests/th/should_compile/T24870/all.T ===================================== @@ -0,0 +1,6 @@ +# The interpreter must uphold tagging invariants, and failed to do so in #24870 +# We test this here by having the interpreter calls a strict worker function +# with a reference to a value it constructed. +# See also Note [CBV Functions and the interpreter] +test('T24870', [extra_files(['Def.hs', 'Use.hs']), req_th], + multimod_compile, ['Def Use', '-dtag-inference-checks -v0']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fa968687de81df65db846b15651ecd4e18eea3c6 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fa968687de81df65db846b15651ecd4e18eea3c6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 15:08:54 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 18 Jun 2024 11:08:54 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/romes/25002 Message-ID: <6671a3061fafb_1d931da26b741405f8@gitlab.mail> Rodrigo Mesquita pushed new branch wip/romes/25002 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/25002 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 15:16:37 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 18 Jun 2024 11:16:37 -0400 Subject: [Git][ghc/ghc][wip/romes/25002] cmm: Don't parse MO_BSwap for W8 Message-ID: <6671a4d570822_1d931dc47c281590d3@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/25002 at Glasgow Haskell Compiler / GHC Commits: 9c12ebe0 by Rodrigo Mesquita at 2024-06-18T16:16:25+01:00 cmm: Don't parse MO_BSwap for W8 Don't support parsing bswap8, since bswap8 is not really an operation and would have to be implemented as a no-op (and currently is not implemented at all). Fixes #25002 - - - - - 1 changed file: - compiler/GHC/Cmm/Parser.y Changes: ===================================== compiler/GHC/Cmm/Parser.y ===================================== @@ -1146,12 +1146,15 @@ callishMachOps platform = listToUFM $ ( "prefetch0", (MO_Prefetch_Data 0,)), ( "prefetch1", (MO_Prefetch_Data 1,)), ( "prefetch2", (MO_Prefetch_Data 2,)), - ( "prefetch3", (MO_Prefetch_Data 3,)) + ( "prefetch3", (MO_Prefetch_Data 3,)), + + ( "bswap16", (MO_BSwap W16,) ), + ( "bswap32", (MO_BSwap W32,) ), + ( "bswap64", (MO_BSwap W64,) ) ] ++ concat [ allWidths "popcnt" MO_PopCnt , allWidths "pdep" MO_Pdep , allWidths "pext" MO_Pext - , allWidths "bswap" MO_BSwap , allWidths "cmpxchg" MO_Cmpxchg , allWidths "xchg" MO_Xchg , allWidths "load_relaxed" (\w -> MO_AtomicRead w MemOrderAcquire) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9c12ebe08cee135cc7951efd4bcc1d5a1f9a3e1e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9c12ebe08cee135cc7951efd4bcc1d5a1f9a3e1e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 15:59:38 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 18 Jun 2024 11:59:38 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/romes/24998 Message-ID: <6671aeea2f411_1fcbb52ce5c0110211@gitlab.mail> Rodrigo Mesquita pushed new branch wip/romes/24998 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/romes/24998 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 16:08:57 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 18 Jun 2024 12:08:57 -0400 Subject: [Git][ghc/ghc][wip/romes/24998] base: Deprecate some .Internal modules Message-ID: <6671b119cae14_1fcbb54bc35012249d@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/24998 at Glasgow Haskell Compiler / GHC Commits: 2bb6bfc5 by Rodrigo Mesquita at 2024-06-18T17:08:44+01:00 base: Deprecate some .Internal modules Deprecates the following modules according to clc-proposal #217: https://github.com/haskell/core-libraries-committee/issues/217 * GHC.TypeNats.Internal * GHC.TypeLits.Internal * GHC.ExecutionStack.Internal Closes #24998 - - - - - 3 changed files: - libraries/base/src/GHC/ExecutionStack/Internal.hs - libraries/base/src/GHC/TypeLits/Internal.hs - libraries/base/src/GHC/TypeNats/Internal.hs Changes: ===================================== libraries/base/src/GHC/ExecutionStack/Internal.hs ===================================== @@ -16,7 +16,7 @@ -- -- @since 4.9.0.0 -module GHC.ExecutionStack.Internal ( +module GHC.ExecutionStack.Internal {-# DEPRECATED "This module will be removed from base in the next version (v4.22)" #-} ( -- * Internal Location (..) , SrcLoc (..) ===================================== libraries/base/src/GHC/TypeLits/Internal.hs ===================================== @@ -26,7 +26,7 @@ -- -- @since 4.16.0.0 -module GHC.TypeLits.Internal +module GHC.TypeLits.Internal {-# DEPRECATED "This module will be removed from base in the next version (v4.22)" #-} (Symbol, CmpSymbol, CmpChar ===================================== libraries/base/src/GHC/TypeNats/Internal.hs ===================================== @@ -1,7 +1,7 @@ {-# LANGUAGE Safe #-} {-# OPTIONS_HADDOCK not-home #-} -module GHC.TypeNats.Internal +module GHC.TypeNats.Internal {-# DEPRECATED "This module will be removed from base in the next version (v4.22)" #-} (Natural, CmpNat ) where View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2bb6bfc56a055e0a9575b06ff6480cbb5fe67119 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2bb6bfc56a055e0a9575b06ff6480cbb5fe67119 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 16:48:30 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Tue, 18 Jun 2024 12:48:30 -0400 Subject: [Git][ghc/ghc][wip/romes/24792] 2 commits: dist: Don't forget to configure JavascriptCPP Message-ID: <6671ba5ec2391_1fcbb5aaa4601335a0@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/24792 at Glasgow Haskell Compiler / GHC Commits: 5eb84580 by Rodrigo Mesquita at 2024-06-18T17:40:11+01:00 dist: Don't forget to configure JavascriptCPP We introduced a configuration step for the javascript preprocessor, but only did so for the in-tree configure script. This commit makes it so that we also configure the javascript preprocessor in the configure shipped in the compiler bindist. - - - - - bd998183 by Rodrigo Mesquita at 2024-06-18T17:46:59+01:00 distrib: LlvmTarget in distrib/configure LlvmTarget was being set and substituted in the in-tree configure, but not in the configure shipped in the bindist. We want to set the LlvmTarget to the canonical LLVM name of the platform that GHC is targetting. Currently, that is going to be the boostrapped llvm target (hence the code which sets LlvmTarget=bootstrap_llvm_target). - - - - - 1 changed file: - distrib/configure.ac.in Changes: ===================================== distrib/configure.ac.in ===================================== @@ -151,6 +151,11 @@ FP_HSCPP_CMD_WITH_ARGS(HaskellCPPCmd, HaskellCPPArgs) AC_SUBST([HaskellCPPCmd]) AC_SUBST([HaskellCPPArgs]) +# --with-js-cpp/--with-js-cpp-flags +FP_JSCPP_CMD_WITH_ARGS(JavaScriptCPPCmd, JavaScriptCPPArgs) +AC_SUBST([JavaScriptCPPCmd]) +AC_SUBST([JavaScriptCPPArgs]) + # --with-cmm-cpp/--with-cmm-cpp-flags FP_CMM_CPP_CMD_WITH_ARGS([$CC], [CmmCPPCmd], [CmmCPPArgs], [CmmCPPSupportsG0]) AC_SUBST([CmmCPPCmd]) @@ -288,6 +293,9 @@ AC_SUBST(TargetHasIdentDirective) GHC_GNU_NONEXEC_STACK AC_SUBST(TargetHasGnuNonexecStack) +GHC_LLVM_TARGET_SET_VAR +AC_SUBST(LlvmTarget) + dnl ** See whether cc supports --target= and set dnl CONF_CC_OPTS_STAGE[12] accordingly. FP_CC_SUPPORTS_TARGET([$CC], [CONF_CC_OPTS_STAGE1], [CONF_CXX_OPTS_STAGE1]) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d0ac40dd004dce1ea413bcddfbfc2de82eecdd64...bd9981839bc79f2a72cb8ebfa995361e7e43d2dd -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d0ac40dd004dce1ea413bcddfbfc2de82eecdd64...bd9981839bc79f2a72cb8ebfa995361e7e43d2dd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 16:51:03 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 18 Jun 2024 12:51:03 -0400 Subject: [Git][ghc/ghc][wip/T24978] Onward with AxiomRule Message-ID: <6671baf7abbc6_1fcbb5c289e013548b@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24978 at Glasgow Haskell Compiler / GHC Commits: a5a19e03 by Simon Peyton Jones at 2024-06-18T17:50:35+01:00 Onward with AxiomRule ..won't compile - - - - - 3 changed files: - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Tc/Instance/FunDeps.hs Changes: ===================================== compiler/GHC/Builtin/Types/Literals.hs ===================================== @@ -33,7 +33,7 @@ import GHC.Core.TyCon ( TyCon, FamTyConFlav(..), mkFamilyTyCon , Injectivity(..) ) import GHC.Core.Coercion ( Role(..) ) import GHC.Tc.Types.Constraint ( Xi ) -import GHC.Core.Coercion.Axiom ( CoAxiomRule(..), BuiltInSynFamily(..), TypeEqn ) +import GHC.Core.Coercion.Axiom import GHC.Core.TyCo.Compare ( tcEqType ) import GHC.Types.Name ( Name, BuiltInSyntax(..) ) import GHC.Types.Unique.FM @@ -179,8 +179,10 @@ typeNatSubTyCon :: TyCon typeNatSubTyCon = mkTypeNatFunTyCon2 name BuiltInSynFamily { sfMatchFam = matchFamSub - , sfInteractTop = interactTopSub - , sfInteractInert = interactInertSub + , sfInteractTop = sfInteractTopNone + , sfInteractInert = sfInteractInertNone +-- , sfInteractTop = \_ -> [] interactTopSub +-- , sfInteractInert = interactInertSub } where name = mkWiredInTyConName UserSyntax gHC_INTERNAL_TYPENATS (fsLit "-") @@ -190,8 +192,10 @@ typeNatMulTyCon :: TyCon typeNatMulTyCon = mkTypeNatFunTyCon2 name BuiltInSynFamily { sfMatchFam = matchFamMul - , sfInteractTop = interactTopMul - , sfInteractInert = interactInertMul + , sfInteractTop = sfInteractTopNone + , sfInteractInert = sfInteractInertNone +-- , sfInteractTop = interactTopMul +-- , sfInteractInert = interactInertMul } where name = mkWiredInTyConName UserSyntax gHC_INTERNAL_TYPENATS (fsLit "*") @@ -201,8 +205,10 @@ typeNatDivTyCon :: TyCon typeNatDivTyCon = mkTypeNatFunTyCon2 name BuiltInSynFamily { sfMatchFam = matchFamDiv - , sfInteractTop = interactTopDiv - , sfInteractInert = interactInertDiv + , sfInteractTop = sfInteractTopNone + , sfInteractInert = sfInteractInertNone +-- , sfInteractTop = interactTopDiv +-- , sfInteractInert = interactInertDiv } where name = mkWiredInTyConName UserSyntax gHC_INTERNAL_TYPENATS (fsLit "Div") @@ -212,8 +218,10 @@ typeNatModTyCon :: TyCon typeNatModTyCon = mkTypeNatFunTyCon2 name BuiltInSynFamily { sfMatchFam = matchFamMod - , sfInteractTop = interactTopMod - , sfInteractInert = interactInertMod + , sfInteractTop = sfInteractTopNone + , sfInteractInert = sfInteractInertNone +-- , sfInteractTop = interactTopMod +-- , sfInteractInert = interactInertMod } where name = mkWiredInTyConName UserSyntax gHC_INTERNAL_TYPENATS (fsLit "Mod") @@ -223,8 +231,10 @@ typeNatExpTyCon :: TyCon typeNatExpTyCon = mkTypeNatFunTyCon2 name BuiltInSynFamily { sfMatchFam = matchFamExp - , sfInteractTop = interactTopExp - , sfInteractInert = interactInertExp + , sfInteractTop = sfInteractTopNone + , sfInteractInert = sfInteractInertNone +-- , sfInteractTop = interactTopExp +-- , sfInteractInert = interactInertExp } where name = mkWiredInTyConName UserSyntax gHC_INTERNAL_TYPENATS (fsLit "^") @@ -234,15 +244,15 @@ typeNatLogTyCon :: TyCon typeNatLogTyCon = mkTypeNatFunTyCon1 name BuiltInSynFamily { sfMatchFam = matchFamLog - , sfInteractTop = interactTopLog - , sfInteractInert = interactInertLog + , sfInteractTop = sfInteractTopNone + , sfInteractInert = sfInteractInertNone +-- , sfInteractTop = interactTopLog +-- , sfInteractInert = interactInertLog } where name = mkWiredInTyConName UserSyntax gHC_INTERNAL_TYPENATS (fsLit "Log2") typeNatLogTyFamNameKey typeNatLogTyCon - - typeNatCmpTyCon :: TyCon typeNatCmpTyCon = mkFamilyTyCon name @@ -277,16 +287,20 @@ typeSymbolCmpTyCon = typeSymbolCmpTyFamNameKey typeSymbolCmpTyCon ops = BuiltInSynFamily { sfMatchFam = matchFamCmpSymbol - , sfInteractTop = interactTopCmpSymbol - , sfInteractInert = \_ _ _ _ -> [] + , sfInteractTop = sfInteractTopNone + , sfInteractInert = sfInteractInertNone +-- , sfInteractTop = interactTopCmpSymbol +-- , sfInteractInert = sfInteractInertNone } typeSymbolAppendTyCon :: TyCon typeSymbolAppendTyCon = mkTypeSymbolFunTyCon2 name BuiltInSynFamily { sfMatchFam = matchFamAppendSymbol - , sfInteractTop = interactTopAppendSymbol - , sfInteractInert = interactInertAppendSymbol + , sfInteractTop = sfInteractTopNone + , sfInteractInert = sfInteractInertNone +-- , sfInteractTop = interactTopAppendSymbol +-- , sfInteractInert = interactInertAppendSymbol } where name = mkWiredInTyConName UserSyntax gHC_INTERNAL_TYPELITS (fsLit "AppendSymbol") @@ -306,8 +320,10 @@ typeConsSymbolTyCon = typeConsSymbolTyFamNameKey typeConsSymbolTyCon ops = BuiltInSynFamily { sfMatchFam = matchFamConsSymbol - , sfInteractTop = interactTopConsSymbol - , sfInteractInert = interactInertConsSymbol + , sfInteractTop = sfInteractTopNone + , sfInteractInert = sfInteractInertNone +-- , sfInteractTop = interactTopConsSymbol +-- , sfInteractInert = interactInertConsSymbol } typeUnconsSymbolTyCon :: TyCon @@ -324,8 +340,10 @@ typeUnconsSymbolTyCon = typeUnconsSymbolTyFamNameKey typeUnconsSymbolTyCon ops = BuiltInSynFamily { sfMatchFam = matchFamUnconsSymbol - , sfInteractTop = interactTopUnconsSymbol - , sfInteractInert = interactInertUnconsSymbol + , sfInteractTop = sfInteractTopNone + , sfInteractInert = sfInteractInertNone +-- , sfInteractTop = interactTopUnconsSymbol +-- , sfInteractInert = interactInertUnconsSymbol } typeCharToNatTyCon :: TyCon @@ -342,8 +360,10 @@ typeCharToNatTyCon = typeCharToNatTyFamNameKey typeCharToNatTyCon ops = BuiltInSynFamily { sfMatchFam = matchFamCharToNat - , sfInteractTop = interactTopCharToNat - , sfInteractInert = \_ _ _ _ -> [] + , sfInteractTop = sfInteractTopNone + , sfInteractInert = sfInteractInertNone +-- , sfInteractTop = interactTopCharToNat +-- , sfInteractInert = sfInteractInertNone } @@ -361,8 +381,10 @@ typeNatToCharTyCon = typeNatToCharTyFamNameKey typeNatToCharTyCon ops = BuiltInSynFamily { sfMatchFam = matchFamNatToChar - , sfInteractTop = interactTopNatToChar - , sfInteractInert = \_ _ _ _ -> [] + , sfInteractTop = sfInteractTopNone + , sfInteractInert = sfInteractInertNone +-- , sfInteractTop = interactTopNatToChar +-- , sfInteractInert = sfInteractInertNone } -- Make a unary built-in constructor of kind: Nat -> Nat @@ -415,8 +437,8 @@ axAddDef , axUnconsSymbolDef , axCharToNatDef , axNatToCharDef - , axAdd0L - , axAdd0R +-- , axAdd0L +-- , axAdd0R , axMul0L , axMul0R , axMul1L @@ -504,8 +526,8 @@ axLogDef = mkUnAxiom "LogDef" typeNatLogTyCon isNumLitTy $ \x -> do (a,_) <- genLog x 2 return (num a) -axAdd0L = mkAxiom1 "Add0L" $ \(Pair s t) -> (num 0 .+. s) === t -axAdd0R = mkAxiom1 "Add0R" $ \(Pair s t) -> (s .+. num 0) === t +--axAdd0L = mkAxiom1 "Add0L" $ \(Pair s t) -> (num 0 .+. s) === t +--axAdd0R = mkAxiom1 "Add0R" $ \(Pair s t) -> (s .+. num 0) === t axSub0R = mkAxiom1 "Sub0R" $ \(Pair s t) -> (s .-. num 0) === t axMul0L = mkAxiom1 "Mul0L" $ \(Pair s _) -> (num 0 .*. s) === num 0 axMul0R = mkAxiom1 "Mul0R" $ \(Pair s _) -> (s .*. num 0) === num 0 @@ -823,21 +845,83 @@ integerToChar _ = Nothing Interact with axioms -------------------------------------------------------------------------------} -interactTopAdd :: [Xi] -> Xi -> [Pair Type] +interactTopAdd :: [Xi] -> Xi -> [(CoAxiomRule, TypeEqn)] interactTopAdd [s,t] r - | Just 0 <- mbZ = [ s === num 0, t === num 0 ] -- (s + t ~ 0) => (s ~ 0, t ~ 0) - | Just x <- mbX, Just z <- mbZ, Just y <- minus z x = [t === num y] -- (5 + t ~ 8) => (t ~ 3) - | Just y <- mbY, Just z <- mbZ, Just x <- minus z y = [s === num x] -- (s + 5 ~ 8) => (s ~ 3) + = [(ar, eqn) | ar <- [axAdd0L, axAdd0R, axAddKKL, axAddKKR] + , [Just eqn] <- [coaxrProves [Pair fam_app r]] ] where - mbX = isNumLitTy s - mbY = isNumLitTy t - mbZ = isNumLitTy r -interactTopAdd _ _ = [] + fam_app = mkTyConApp typeNatAddTyCon [s,t] + +interactInertAdd :: [Xi] -> Xi + -> [Xi] -> Xi + -> [(CoAxiomRule, TypeEqn)] +interactInertAdd [x1,y1] z1 [x2,y2] z2 + = [(ar, eqn) | ar <- [axAddInteract11,axAddInteract12,axAddInteract21,axAddInteract22] + , [Just eqn] <- [coaxrProves [eq1,eq2]] ] + where + eq1 = Pair (mkTyConApp typeNatAddTyCon [x1,y1]) z1 + eq2 = Pair (mkTyConApp typeNatAddTyCon [x2,y2]) z2 + +axAdd0L, axAdd0R, axAddKKR, axAddKKL :: CoAxiomRule +axAdd0L -- (s + t ~ 0) => (s ~ 0) + = mkTopBinFamDeduction1 "Add-0L" typeNatAddTyCon $ \ a _b rhs -> + do { 0 <- isNumLitTy rhs; return (Pair a (num 0)) } +axAdd0R -- (s + t ~ 0) => (t ~ 0) + = mkTopBinFamDeduction1 "Add-0R" typeNatAddTyCon $ \ _a b rhs -> + do { 0 <- isNumLitTy rhs; return (Pair b (num 0)) } +axAddKKL -- (5 + t ~ 8) => (t ~ 3) + = mkTopBinFamDeduction1 "Add-KKL" typeNatAddTyCon $ \ a b rhs -> + do { na <- isNumLitTy a; nr <- isNumLitTy r; return (Pair b (num (nr-na))) } +axAddKKR -- (s + 5 ~ 8) => (s ~ 3) + = mkTopBinFamDeduction1 "Add-KKR" typeNatAddTyCon $ \ a b rhs -> + do { nb <- isNumLitTy b; nr <- isNumLitTy r; return (Pair a (num (nr-nb))) } + +axAddInteract11 -- (x+y1~z, x+y2~z) => (y1 ~ y2) + = mkInteractBinFamDeduction "AddI-11" typeNatAddTyCon $ \ q1 y1 z1 q2 y2 z2 -> + do { guard (z1 `tcEqType` z2); guard (q1 `tcEqType` q2); return (Pair y1 y2) } +axAddInteract12 -- (x+y1~z, y2+x~z) => (y1 ~ y2) + = mkInteractBinFamDeduction "AddI-12" typeNatAddTyCon $ \ q1 y1 z1 y2 q2 z2 -> + do { guard (z1 `tcEqType` z2); guard (q1 `tcEqType` q2); return (Pair y1 y2) } +axAddInteract21 -- (y1+x~z, x+y2~z) => (y1 ~ y2) + = mkInteractBinFamDeduction "AddI-21" typeNatAddTyCon $ \ y1 q1 z1 q2 y2 z2 -> + do { guard (z1 `tcEqType` z2); guard (q1 `tcEqType` q2); return (Pair y1 y2) } +axAddInteract22 -- (y1+x~z, y2+x~z) => (y1 ~ y2) + = mkInteractBinFamDeduction "AddI-22" typeNatAddTyCon $ \ y1 q1 z1 y2 q2 z2 -> + do { guard (z1 `tcEqType` z2); guard (q1 `tcEqType` q2); return (Pair y1 y2) } + +mkTopBinFamDeduction :: String -> TyCon + -> (Type -> Type -> Type -> Maybe TypeEqn) + -> CoAxiomRule +mkTopBinFamDeduction str fam_tc f + = CoAxiomRule + { coaxrName = fsLit str + , coaxrAsmpRoles = [Nominal] + , coaxrRole = Nominal + , coaxrProves = \cs -> do { [Pair lhs rhs] <- cs + ; Just (tc, [a,b]) <- splitTyConApp_maybe lhs + ; guard (tc == fam_c) + ; f a b rhs } } + +mkInteractBinFamDeduction :: String -> TyCon + -> (Type -> Type -> Type -> -- F x1 y1 ~ r1 + Type -> Type -> Type -> -- F x2 y2 ~ r2 + Maybe TypeEqn) + -> CoAxiomRule +mkInteractBinFamDeduction str fam_tc f + = CoAxiomRule + { coaxrName = fsLit str + , coaxrAsmpRoles = [Nominal] + , coaxrRole = Nominal + , coaxrProves = \cs -> do { [Pair lhs1 rhs1, Pair lhs2 rhs2] <- cs + ; Just (tc1, [x1,y1]) <- splitTyConApp_maybe lhs1 + ; Just (tc2, [x2,y2]) <- splitTyConApp_maybe lhs2 + ; guard (tc1 == fam_c) + ; guard (tc2 == fam_c) + ; f x1 y1 rhs1 x2 y2 rhs2 } } {- Note [Weakened interaction rule for subtraction] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ - A simpler interaction here might be: `s - t ~ r` --> `t + r ~ s` @@ -865,6 +949,7 @@ So, for the time being, we only add an improvement when the RHS is a constant, which happens to work OK for the moment, although clearly we need to do something more general. -} +{- interactTopSub :: [Xi] -> Xi -> [Pair Type] interactTopSub [s,t] r | Just z <- mbZ = [ s === (num z .+. t) ] -- (s - t ~ 5) => (5 + t ~ s) @@ -1119,6 +1204,7 @@ genLog x base = Just (exactLoop 0 x) | otherwise = let s1 = s + 1 in s1 `seq` underLoop s1 (div i base) ----------------------------------------------------------------------------- +-} typeCharCmpTyCon :: TyCon typeCharCmpTyCon = @@ -1134,10 +1220,13 @@ typeCharCmpTyCon = typeCharCmpTyFamNameKey typeCharCmpTyCon ops = BuiltInSynFamily { sfMatchFam = matchFamCmpChar - , sfInteractTop = interactTopCmpChar - , sfInteractInert = \_ _ _ _ -> [] + , sfInteractTop = sfInteractTopNone + , sfInteractInert = sfInteractInertNone +-- , sfInteractTop = interactTopCmpChar +-- , sfInteractInert = sfInteractInertNone } +{- interactTopCmpChar :: [Xi] -> Xi -> [Pair Type] interactTopCmpChar [s,t] r | Just EQ <- isOrderingLitTy r = [ s === t ] @@ -1161,3 +1250,4 @@ matchFamCmpChar [s,t] where mbX = isCharLitTy s mbY = isCharLitTy t matchFamCmpChar _ = Nothing +-} ===================================== compiler/GHC/Core/Coercion/Axiom.hs ===================================== @@ -31,7 +31,8 @@ module GHC.Core.Coercion.Axiom ( Role(..), fsFromRole, CoAxiomRule(..), TypeEqn, - BuiltInSynFamily(..), trivialBuiltInFamily + BuiltInSynFamily(..), trivialBuiltInFamily, + sfMatchNone, sfInteractTopNone, sfInteractInertNone ) where import GHC.Prelude @@ -608,12 +609,15 @@ data BuiltInSynFamily = BuiltInSynFamily -- where the r in the output is coaxrRole of the rule. It is up to the -- caller to ensure that this role is appropriate. - , sfInteractTop :: [Type] -> Type -> [TypeEqn] + , sfInteractTop :: [Type] -> Type -> [(CoAxiomRule, TypeEqn)] -- If given these type arguments and RHS, returns the equalities that - -- are guaranteed to hold. + -- are guaranteed to hold. That is, if + -- (ar, Pair s1 s2) is an element ofo (sfInteractTop tys ty) + -- then AxiomRule ar [co :: F tys ~ ty] :: s1~s2 , sfInteractInert :: [Type] -> Type -> - [Type] -> Type -> [TypeEqn] + [Type] -> Type + -> [(CoAxiomRule,TypeEqn)] -- If given one set of arguments and result, and another set of arguments -- and result, returns the equalities that are guaranteed to hold. } @@ -621,7 +625,16 @@ data BuiltInSynFamily = BuiltInSynFamily -- Provides default implementations that do nothing. trivialBuiltInFamily :: BuiltInSynFamily trivialBuiltInFamily = BuiltInSynFamily - { sfMatchFam = \_ -> Nothing - , sfInteractTop = \_ _ -> [] - , sfInteractInert = \_ _ _ _ -> [] + { sfMatchFam = sfMatchNone + , sfInteractTop = sfInteractTopNone + , sfInteractInert = sfInteractInertNone } + +sfMatchNone :: a -> Maybe b +sfMatchNone _ = Nothing + +sfInteractTopNone :: a -> b -> [c] +sfInteractTopNone _ _ = [] + +sfInteractInertNone :: a -> b -> c -> d -> [e] +sfInteractInertNone _ _ _ _ = [] ===================================== compiler/GHC/Tc/Instance/FunDeps.hs ===================================== @@ -115,8 +115,7 @@ Wrinkles: FDEqn { fd_qtvs = [x], fd_eqs = [Pair (Maybe x) ty] } Note that the fd_qtvs can be free in the /first/ component of the Pair, - - but not in the seconde (which comes from the [W] constraint. + but not in the second (which comes from the [W] constraint). (2) Multi-range fundeps. When these meta_tvs are involved, there is a subtle difference between the fundep (a -> b c) and the two fundeps (a->b, a->c). View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a5a19e03323f542cd3be64691285de7540337986 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a5a19e03323f542cd3be64691285de7540337986 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 22:28:38 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Tue, 18 Jun 2024 18:28:38 -0400 Subject: [Git][ghc/ghc][wip/T24978] Progress Message-ID: <66720a16b52df_296a1b21472f4120564@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24978 at Glasgow Haskell Compiler / GHC Commits: e92e84c6 by Simon Peyton Jones at 2024-06-18T23:28:22+01:00 Progress - - - - - 3 changed files: - compiler/GHC/Builtin/Types/Literals.hs - compiler/GHC/Core/Coercion/Axiom.hs - compiler/GHC/Tc/Solver/Equality.hs Changes: ===================================== compiler/GHC/Builtin/Types/Literals.hs ===================================== @@ -1,7 +1,9 @@ {-# LANGUAGE LambdaCase #-} module GHC.Builtin.Types.Literals - ( typeNatTyCons + ( tryInteractInertFam, tryInteractTopFam + + , typeNatTyCons , typeNatCoAxiomRules , BuiltInSynFamily(..) @@ -61,6 +63,9 @@ import GHC.Builtin.Names , typeNatToCharTyFamNameKey ) import GHC.Data.FastString +import GHC.Utils.Panic +import GHC.Utils.Outputable + import Control.Monad ( guard ) import Data.List ( isPrefixOf, isSuffixOf ) import qualified Data.Char as Char @@ -138,9 +143,35 @@ There are a few steps to adding a built-in type family: built-in type family deals with Nats or Symbols, respectively. -} -{------------------------------------------------------------------------------- -Built-in type constructors for functions on type-level nats --} +------------------------------------------------------------------------------- +-- Key utility functions +------------------------------------------------------------------------------- + +tryInteractTopFam :: BuiltInSynFamily -> TyCon -> [Type] -> Type + -> [(CoAxiomRule, TypeEqn)] +tryInteractTopFam fam fam_tc tys r + = [(ax_rule, eqn) | ax_rule <- sfInteractTop fam + , Just eqn <- [coaxrProves ax_rule [eqn]] ] + where + eqn :: TypeEqn + eqn = Pair (mkTyConApp fam_tc tys) r + +tryInteractInertFam :: BuiltInSynFamily -> TyCon + -> [Type] -> Type -- F tys1 ~ ty1 + -> [Type] -> Type -- F tys2 ~ ty2 + -> [(CoAxiomRule, TypeEqn)] +tryInteractInertFam fam fam_tc tys1 ty1 tys2 ty2 + = [(ax_rule, eqn) | ax_rule <- sfInteractInert fam + , Just eqn <- [coaxrProves ax_rule [eqn1,eqn2]] ] + where + eqn1 = Pair (mkTyConApp fam_tc tys1) ty1 + eqn2 = Pair (mkTyConApp fam_tc tys2) ty2 + + + +------------------------------------------------------------------------------- +-- Built-in type constructors for functions on type-level nats +------------------------------------------------------------------------------- -- The list of built-in type family TyCons that GHC uses. -- If you define a built-in type family, make sure to add it to this list. @@ -168,21 +199,19 @@ typeNatAddTyCon :: TyCon typeNatAddTyCon = mkTypeNatFunTyCon2 name BuiltInSynFamily { sfMatchFam = matchFamAdd - , sfInteractTop = interactTopAdd - , sfInteractInert = interactInertAdd + , sfInteractTop = [axAddTop0L, axAddTop0R, axAddTopKKL, axAddTopKKR] + , sfInteractInert = [axAddInteract11, axAddInteract12, axAddInteract21, axAddInteract22] } where - name = mkWiredInTyConName UserSyntax gHC_INTERNAL_TYPENATS (fsLit "+") - typeNatAddTyFamNameKey typeNatAddTyCon + name = mkWiredInTyConName UserSyntax gHC_INTERNAL_TYPENATS (fsLit "+") + typeNatAddTyFamNameKey typeNatAddTyCon typeNatSubTyCon :: TyCon typeNatSubTyCon = mkTypeNatFunTyCon2 name BuiltInSynFamily { sfMatchFam = matchFamSub - , sfInteractTop = sfInteractTopNone - , sfInteractInert = sfInteractInertNone --- , sfInteractTop = \_ -> [] interactTopSub --- , sfInteractInert = interactInertSub + , sfInteractTop = [axSubTop] + , sfInteractInert = [axSubInteract1, axSubInteract2] } where name = mkWiredInTyConName UserSyntax gHC_INTERNAL_TYPENATS (fsLit "-") @@ -192,10 +221,8 @@ typeNatMulTyCon :: TyCon typeNatMulTyCon = mkTypeNatFunTyCon2 name BuiltInSynFamily { sfMatchFam = matchFamMul - , sfInteractTop = sfInteractTopNone - , sfInteractInert = sfInteractInertNone --- , sfInteractTop = interactTopMul --- , sfInteractInert = interactInertMul + , sfInteractTop = [axMulTop1, axMulTop2, axMulTop3, axMulTop4] + , sfInteractInert = [axMulInteract1, axMulInteract2] } where name = mkWiredInTyConName UserSyntax gHC_INTERNAL_TYPENATS (fsLit "*") @@ -205,10 +232,8 @@ typeNatDivTyCon :: TyCon typeNatDivTyCon = mkTypeNatFunTyCon2 name BuiltInSynFamily { sfMatchFam = matchFamDiv - , sfInteractTop = sfInteractTopNone - , sfInteractInert = sfInteractInertNone --- , sfInteractTop = interactTopDiv --- , sfInteractInert = interactInertDiv + , sfInteractTop = [] + , sfInteractInert = [] } where name = mkWiredInTyConName UserSyntax gHC_INTERNAL_TYPENATS (fsLit "Div") @@ -218,10 +243,8 @@ typeNatModTyCon :: TyCon typeNatModTyCon = mkTypeNatFunTyCon2 name BuiltInSynFamily { sfMatchFam = matchFamMod - , sfInteractTop = sfInteractTopNone - , sfInteractInert = sfInteractInertNone --- , sfInteractTop = interactTopMod --- , sfInteractInert = interactInertMod + , sfInteractTop = [] + , sfInteractInert = [] } where name = mkWiredInTyConName UserSyntax gHC_INTERNAL_TYPENATS (fsLit "Mod") @@ -244,10 +267,8 @@ typeNatLogTyCon :: TyCon typeNatLogTyCon = mkTypeNatFunTyCon1 name BuiltInSynFamily { sfMatchFam = matchFamLog - , sfInteractTop = sfInteractTopNone - , sfInteractInert = sfInteractInertNone --- , sfInteractTop = interactTopLog --- , sfInteractInert = interactInertLog + , sfInteractTop = [] + , sfInteractInert = [] } where name = mkWiredInTyConName UserSyntax gHC_INTERNAL_TYPENATS (fsLit "Log2") @@ -268,8 +289,10 @@ typeNatCmpTyCon = typeNatCmpTyFamNameKey typeNatCmpTyCon ops = BuiltInSynFamily { sfMatchFam = matchFamCmpNat - , sfInteractTop = interactTopCmpNat - , sfInteractInert = \_ _ _ _ -> [] + , sfInteractTop = sfInteractTopNone + , sfInteractInert = sfInteractInertNone +-- , sfInteractTop = interactTopCmpNat +-- , sfInteractInert = sfInteractInertNone } typeSymbolCmpTyCon :: TyCon @@ -437,8 +460,8 @@ axAddDef , axUnconsSymbolDef , axCharToNatDef , axNatToCharDef --- , axAdd0L --- , axAdd0R + , axAdd0L + , axAdd0R , axMul0L , axMul0R , axMul1L @@ -459,75 +482,50 @@ axAddDef , axLogDef :: CoAxiomRule -axAddDef = mkBinAxiom "AddDef" typeNatAddTyCon isNumLitTy isNumLitTy $ +axAddDef = mkBinAxiom "AddDef" typeNatAddTyCon isNumLitTy isNumLitTy $ \x y -> Just $ num (x + y) -axMulDef = mkBinAxiom "MulDef" typeNatMulTyCon isNumLitTy isNumLitTy $ +axMulDef = mkBinAxiom "MulDef" typeNatMulTyCon isNumLitTy isNumLitTy $ \x y -> Just $ num (x * y) -axExpDef = mkBinAxiom "ExpDef" typeNatExpTyCon isNumLitTy isNumLitTy $ +axExpDef = mkBinAxiom "ExpDef" typeNatExpTyCon isNumLitTy isNumLitTy $ \x y -> Just $ num (x ^ y) -axCmpNatDef = mkBinAxiom "CmpNatDef" typeNatCmpTyCon isNumLitTy isNumLitTy - $ \x y -> Just $ ordering (compare x y) +axCmpNatDef = mkBinAxiom "CmpNatDef" typeNatCmpTyCon isNumLitTy isNumLitTy $ + \x y -> Just $ ordering (compare x y) -axCmpSymbolDef = - CoAxiomRule - { coaxrName = fsLit "CmpSymbolDef" - , coaxrAsmpRoles = [Nominal, Nominal] - , coaxrRole = Nominal - , coaxrProves = \cs -> - do [Pair s1 s2, Pair t1 t2] <- return cs - s2' <- isStrLitTy s2 - t2' <- isStrLitTy t2 - return (mkTyConApp typeSymbolCmpTyCon [s1,t1] === - ordering (lexicalCompareFS s2' t2')) } +axCmpSymbolDef = mkBinAxiom "CmpSymbolDef" typeSymbolCmpTyCon isStrLitTy isStrLitTy $ + \s2' t2' -> Just (ordering (lexicalCompareFS s2' t2')) -axAppendSymbolDef = CoAxiomRule - { coaxrName = fsLit "AppendSymbolDef" - , coaxrAsmpRoles = [Nominal, Nominal] - , coaxrRole = Nominal - , coaxrProves = \cs -> - do [Pair s1 s2, Pair t1 t2] <- return cs - s2' <- isStrLitTy s2 - t2' <- isStrLitTy t2 - let z = mkStrLitTy (appendFS s2' t2') - return (mkTyConApp typeSymbolAppendTyCon [s1, t1] === z) - } +axAppendSymbolDef = mkBinAxiom "AppendSymbolDef" typeSymbolAppendTyCon isStrLitTy isStrLitTy $ + \s2' t2' -> Just (mkStrLitTy (appendFS s2' t2')) -axConsSymbolDef = - mkBinAxiom "ConsSymbolDef" typeConsSymbolTyCon isCharLitTy isStrLitTy $ - \c str -> Just $ mkStrLitTy (consFS c str) +axConsSymbolDef = mkBinAxiom "ConsSymbolDef" typeConsSymbolTyCon isCharLitTy isStrLitTy $ + \c str -> Just $ mkStrLitTy (consFS c str) -axUnconsSymbolDef = - mkUnAxiom "UnconsSymbolDef" typeUnconsSymbolTyCon isStrLitTy $ - \str -> Just $ computeUncons str +axUnconsSymbolDef = mkUnAxiom "UnconsSymbolDef" typeUnconsSymbolTyCon isStrLitTy $ + \str -> Just $ computeUncons str -axCharToNatDef = - mkUnAxiom "CharToNatDef" typeCharToNatTyCon isCharLitTy $ - \c -> Just $ num (charToInteger c) +axCharToNatDef = mkUnAxiom "CharToNatDef" typeCharToNatTyCon isCharLitTy $ + \c -> Just $ num (charToInteger c) -axNatToCharDef = - mkUnAxiom "NatToCharDef" typeNatToCharTyCon isNumLitTy $ - \n -> fmap mkCharLitTy (integerToChar n) +axNatToCharDef = mkUnAxiom "NatToCharDef" typeNatToCharTyCon isNumLitTy $ + \n -> fmap mkCharLitTy (integerToChar n) axSubDef = mkBinAxiom "SubDef" typeNatSubTyCon isNumLitTy isNumLitTy $ \x y -> fmap num (minus x y) axDivDef = mkBinAxiom "DivDef" typeNatDivTyCon isNumLitTy isNumLitTy $ - \x y -> do guard (y /= 0) - return (num (div x y)) + \x y -> do { guard (y /= 0); return (num (div x y)) } axModDef = mkBinAxiom "ModDef" typeNatModTyCon isNumLitTy isNumLitTy $ - \x y -> do guard (y /= 0) - return (num (mod x y)) + \x y -> do { guard (y /= 0); return (num (mod x y)) } axLogDef = mkUnAxiom "LogDef" typeNatLogTyCon isNumLitTy $ - \x -> do (a,_) <- genLog x 2 - return (num a) + \x -> do { (a,_) <- genLog x 2; return (num a) } ---axAdd0L = mkAxiom1 "Add0L" $ \(Pair s t) -> (num 0 .+. s) === t ---axAdd0R = mkAxiom1 "Add0R" $ \(Pair s t) -> (s .+. num 0) === t +axAdd0L = mkAxiom1 "Add0L" $ \(Pair s t) -> (num 0 .+. s) === t +axAdd0R = mkAxiom1 "Add0R" $ \(Pair s t) -> (s .+. num 0) === t axSub0R = mkAxiom1 "Sub0R" $ \(Pair s t) -> (s .-. num 0) === t axMul0L = mkAxiom1 "Mul0L" $ \(Pair s _) -> (num 0 .*. s) === num 0 axMul0R = mkAxiom1 "Mul0R" $ \(Pair s _) -> (s .*. num 0) === num 0 @@ -540,13 +538,13 @@ axExp1L = mkAxiom1 "Exp1L" $ \(Pair s _) -> (num 1 .^. s) === num 1 axExp0R = mkAxiom1 "Exp0R" $ \(Pair s _) -> (s .^. num 0) === num 1 axExp1R = mkAxiom1 "Exp1R" $ \(Pair s t) -> (s .^. num 1) === t axCmpNatRefl = mkAxiom1 "CmpNatRefl" - $ \(Pair s _) -> (cmpNat s s) === ordering EQ + $ \(Pair s _) -> (cmpNat s s) === ordering EQ axCmpSymbolRefl = mkAxiom1 "CmpSymbolRefl" - $ \(Pair s _) -> (cmpSymbol s s) === ordering EQ + $ \(Pair s _) -> (cmpSymbol s s) === ordering EQ axAppendSymbol0R = mkAxiom1 "Concat0R" - $ \(Pair s t) -> (mkStrLitTy nilFS `appendSymbol` s) === t + $ \(Pair s t) -> (mkStrLitTy nilFS `appendSymbol` s) === t axAppendSymbol0L = mkAxiom1 "Concat0L" - $ \(Pair s t) -> (s `appendSymbol` mkStrLitTy nilFS) === t + $ \(Pair s t) -> (s `appendSymbol` mkStrLitTy nilFS) === t -- The list of built-in type family axioms that GHC uses. -- If you define new axioms, make sure to include them in this list. @@ -575,7 +573,7 @@ typeNatCoAxiomRules = listToUFM $ map (\x -> (coaxrName x, x)) , axExp1R , axCmpNatRefl , axCmpSymbolRefl - , axCmpCharRefl +-- , axCmpCharRefl , axSubDef , axSub0R , axAppendSymbol0R @@ -698,9 +696,43 @@ mkAxiom1 str f = } -{------------------------------------------------------------------------------- -Evaluation --------------------------------------------------------------------------------} +natInjCheck :: Type -> Type -> Type -> Type -> Type -> Type -> Maybe TypeEqn +natInjCheck x1 y1 z1 x2 y2 z2 + = do { guard (z1 `tcEqType` z2); guard (x1 `tcEqType` x2); return (Pair y1 y2) } + +mkTopBinFamDeduction :: String -> TyCon + -> (Type -> Type -> Type -> Maybe TypeEqn) + -> CoAxiomRule +mkTopBinFamDeduction str fam_tc f + = CoAxiomRule + { coaxrName = fsLit str + , coaxrAsmpRoles = [Nominal] + , coaxrRole = Nominal + , coaxrProves = \cs -> do { [Pair lhs rhs] <- return cs + ; (tc, [a,b]) <- splitTyConApp_maybe lhs + ; massertPpr (tc == fam_tc) (ppr tc $$ ppr fam_tc) + ; f a b rhs } } + +mkInteractBinFamDeduction :: String -> TyCon + -> (Type -> Type -> Type -> -- F x1 y1 ~ r1 + Type -> Type -> Type -> -- F x2 y2 ~ r2 + Maybe TypeEqn) + -> CoAxiomRule +mkInteractBinFamDeduction str fam_tc f + = CoAxiomRule + { coaxrName = fsLit str + , coaxrAsmpRoles = [Nominal] + , coaxrRole = Nominal + , coaxrProves = \cs -> do { [Pair lhs1 rhs1, Pair lhs2 rhs2] <- return cs + ; (tc1, [x1,y1]) <- splitTyConApp_maybe lhs1 + ; (tc2, [x2,y2]) <- splitTyConApp_maybe lhs2 + ; massertPpr (tc1 == fam_tc) (ppr tc1 $$ ppr fam_tc) + ; massertPpr (tc2 == fam_tc) (ppr tc2 $$ ppr fam_tc) + ; f x1 y1 rhs1 x2 y2 rhs2 } } + +------------------------------------------------------------------------------- +-- Evaluation: matchFamAdd and friends +------------------------------------------------------------------------------- matchFamAdd :: [Type] -> Maybe (CoAxiomRule, [Type], Type) matchFamAdd [s,t] @@ -841,83 +873,38 @@ integerToChar n | inBounds = Just (Char.chr (fromInteger n)) n <= charToInteger maxBound integerToChar _ = Nothing -{------------------------------------------------------------------------------- -Interact with axioms --------------------------------------------------------------------------------} - -interactTopAdd :: [Xi] -> Xi -> [(CoAxiomRule, TypeEqn)] -interactTopAdd [s,t] r - = [(ar, eqn) | ar <- [axAdd0L, axAdd0R, axAddKKL, axAddKKR] - , [Just eqn] <- [coaxrProves [Pair fam_app r]] ] - where - fam_app = mkTyConApp typeNatAddTyCon [s,t] - -interactInertAdd :: [Xi] -> Xi - -> [Xi] -> Xi - -> [(CoAxiomRule, TypeEqn)] -interactInertAdd [x1,y1] z1 [x2,y2] z2 - = [(ar, eqn) | ar <- [axAddInteract11,axAddInteract12,axAddInteract21,axAddInteract22] - , [Just eqn] <- [coaxrProves [eq1,eq2]] ] - where - eq1 = Pair (mkTyConApp typeNatAddTyCon [x1,y1]) z1 - eq2 = Pair (mkTyConApp typeNatAddTyCon [x2,y2]) z2 - -axAdd0L, axAdd0R, axAddKKR, axAddKKL :: CoAxiomRule -axAdd0L -- (s + t ~ 0) => (s ~ 0) - = mkTopBinFamDeduction1 "Add-0L" typeNatAddTyCon $ \ a _b rhs -> - do { 0 <- isNumLitTy rhs; return (Pair a (num 0)) } -axAdd0R -- (s + t ~ 0) => (t ~ 0) - = mkTopBinFamDeduction1 "Add-0R" typeNatAddTyCon $ \ _a b rhs -> - do { 0 <- isNumLitTy rhs; return (Pair b (num 0)) } -axAddKKL -- (5 + t ~ 8) => (t ~ 3) - = mkTopBinFamDeduction1 "Add-KKL" typeNatAddTyCon $ \ a b rhs -> +------------------------------------------------------------------------------- +-- Interact with axioms +------------------------------------------------------------------------------- + +axAddTop0L, axAddTop0R, axAddTopKKR, axAddTopKKL :: CoAxiomRule +axAddTop0L -- (s + t ~ 0) => (s ~ 0) + = mkTopBinFamDeduction "AddT-0L" typeNatAddTyCon $ \ a _b r -> + do { 0 <- isNumLitTy r; return (Pair a (num 0)) } +axAddTop0R -- (s + t ~ 0) => (t ~ 0) + = mkTopBinFamDeduction "AddT-0R" typeNatAddTyCon $ \ _a b r -> + do { 0 <- isNumLitTy r; return (Pair b (num 0)) } +axAddTopKKL -- (5 + t ~ 8) => (t ~ 3) + = mkTopBinFamDeduction "AddT-KKL" typeNatAddTyCon $ \ a b r -> do { na <- isNumLitTy a; nr <- isNumLitTy r; return (Pair b (num (nr-na))) } -axAddKKR -- (s + 5 ~ 8) => (s ~ 3) - = mkTopBinFamDeduction1 "Add-KKR" typeNatAddTyCon $ \ a b rhs -> +axAddTopKKR -- (s + 5 ~ 8) => (s ~ 3) + = mkTopBinFamDeduction "AddT-KKR" typeNatAddTyCon $ \ a b r -> do { nb <- isNumLitTy b; nr <- isNumLitTy r; return (Pair a (num (nr-nb))) } +axAddInteract11, axAddInteract12, axAddInteract21, axAddInteract22 :: CoAxiomRule axAddInteract11 -- (x+y1~z, x+y2~z) => (y1 ~ y2) - = mkInteractBinFamDeduction "AddI-11" typeNatAddTyCon $ \ q1 y1 z1 q2 y2 z2 -> - do { guard (z1 `tcEqType` z2); guard (q1 `tcEqType` q2); return (Pair y1 y2) } + = mkInteractBinFamDeduction "AddI-11" typeNatAddTyCon $ \ x1 y1 z1 x2 y2 z2 -> + natInjCheck x1 y1 z1 x2 y2 z2 axAddInteract12 -- (x+y1~z, y2+x~z) => (y1 ~ y2) - = mkInteractBinFamDeduction "AddI-12" typeNatAddTyCon $ \ q1 y1 z1 y2 q2 z2 -> - do { guard (z1 `tcEqType` z2); guard (q1 `tcEqType` q2); return (Pair y1 y2) } + = mkInteractBinFamDeduction "AddI-12" typeNatAddTyCon $ \ x1 y1 z1 x2 y2 z2 -> + natInjCheck y1 x1 z1 x2 y2 z2 axAddInteract21 -- (y1+x~z, x+y2~z) => (y1 ~ y2) - = mkInteractBinFamDeduction "AddI-21" typeNatAddTyCon $ \ y1 q1 z1 q2 y2 z2 -> - do { guard (z1 `tcEqType` z2); guard (q1 `tcEqType` q2); return (Pair y1 y2) } + = mkInteractBinFamDeduction "AddI-21" typeNatAddTyCon $ \ x1 y1 z1 x2 y2 z2 -> + natInjCheck x1 y1 z1 y2 x2 z2 axAddInteract22 -- (y1+x~z, y2+x~z) => (y1 ~ y2) - = mkInteractBinFamDeduction "AddI-22" typeNatAddTyCon $ \ y1 q1 z1 y2 q2 z2 -> - do { guard (z1 `tcEqType` z2); guard (q1 `tcEqType` q2); return (Pair y1 y2) } - -mkTopBinFamDeduction :: String -> TyCon - -> (Type -> Type -> Type -> Maybe TypeEqn) - -> CoAxiomRule -mkTopBinFamDeduction str fam_tc f - = CoAxiomRule - { coaxrName = fsLit str - , coaxrAsmpRoles = [Nominal] - , coaxrRole = Nominal - , coaxrProves = \cs -> do { [Pair lhs rhs] <- cs - ; Just (tc, [a,b]) <- splitTyConApp_maybe lhs - ; guard (tc == fam_c) - ; f a b rhs } } + = mkInteractBinFamDeduction "AddI-22" typeNatAddTyCon $ \ x1 y1 z1 x2 y2 z2 -> + natInjCheck y1 x1 z1 y2 x2 z2 -mkInteractBinFamDeduction :: String -> TyCon - -> (Type -> Type -> Type -> -- F x1 y1 ~ r1 - Type -> Type -> Type -> -- F x2 y2 ~ r2 - Maybe TypeEqn) - -> CoAxiomRule -mkInteractBinFamDeduction str fam_tc f - = CoAxiomRule - { coaxrName = fsLit str - , coaxrAsmpRoles = [Nominal] - , coaxrRole = Nominal - , coaxrProves = \cs -> do { [Pair lhs1 rhs1, Pair lhs2 rhs2] <- cs - ; Just (tc1, [x1,y1]) <- splitTyConApp_maybe lhs1 - ; Just (tc2, [x2,y2]) <- splitTyConApp_maybe lhs2 - ; guard (tc1 == fam_c) - ; guard (tc2 == fam_c) - ; f x1 y1 rhs1 x2 y2 rhs2 } } {- Note [Weakened interaction rule for subtraction] @@ -949,35 +936,46 @@ So, for the time being, we only add an improvement when the RHS is a constant, which happens to work OK for the moment, although clearly we need to do something more general. -} -{- -interactTopSub :: [Xi] -> Xi -> [Pair Type] -interactTopSub [s,t] r - | Just z <- mbZ = [ s === (num z .+. t) ] -- (s - t ~ 5) => (5 + t ~ s) - where - mbZ = isNumLitTy r -interactTopSub _ _ = [] - +axSubTop :: CoAxiomRule +axSubTop -- (a - b ~ 5) => (5 + b ~ a) + = mkTopBinFamDeduction "SubT" typeNatSubTyCon $ \ a b r -> + do { _ <- isNumLitTy r; return (Pair (r .+. b) a) } + +axSubInteract1, axSubInteract2 :: CoAxiomRule +axSubInteract1 -- (x-y1 ~ z, x-y2 ~ z) => (y1 ~ y2) + = mkInteractBinFamDeduction "SubI-2" typeNatSubTyCon $ \ x1 y1 z1 x2 y2 z2 -> + natInjCheck x1 y1 z1 x2 y2 z2 +axSubInteract2 -- (x1-y ~ z, x2-y ~ z) => (x1 ~ x2) + = mkInteractBinFamDeduction "SubI-2" typeNatSubTyCon $ \ x1 y1 z1 x2 y2 z2 -> + natInjCheck y1 x1 z1 y2 x2 z2 + + +axMulTop1, axMulTop2, axMulTop3, axMulTop4 :: CoAxiomRule +axMulTop1 -- (s * t ~ 1) => (s ~ 1) + = mkTopBinFamDeduction "MulT1" typeNatMulTyCon $ \ s _t r -> + do { 1 <- isNumLitTy r; return (Pair s r) } +axMulTop2 -- (s * t ~ 1) => (t ~ 1) + = mkTopBinFamDeduction "MulT2" typeNatMulTyCon $ \ _s t r -> + do { 1 <- isNumLitTy r; return (Pair t r) } +axMulTop3 -- (3 * t ~ 15) => (t ~ 5) + = mkTopBinFamDeduction "MulT3" typeNatMulTyCon $ \ s t r -> + do { ns <- isNumLitTy s; nr <- isNumLitTy r; y <- divide nr ns; return (Pair t (num y)) } +axMulTop4 -- (s * 3 ~ 15) => (s ~ 5) + = mkTopBinFamDeduction "MulT4" typeNatMulTyCon $ \ s t r -> + do { nt <- isNumLitTy t; nr <- isNumLitTy r; y <- divide nr nt; return (Pair s (num y)) } + +axMulInteract1, axMulInteract2 :: CoAxiomRule +axMulInteract1 -- (x*y1 ~ z, x*y2 ~ z) => (y1~y2) if x/=0 + = mkInteractBinFamDeduction "MulI1" typeNatMulTyCon $ \ x1 y1 z1 x2 y2 z2 -> + do { nx1 <- isNumLitTy x1; guard (nx1 /= 0); guard (z1 `tcEqType` z2) + ; guard (x1 `tcEqType` x2); return (Pair y1 y2) } +axMulInteract2 -- (x1*y ~ z, x2*y ~ z) => (x1~x2) if y/0 + = mkInteractBinFamDeduction "MulI2" typeNatMulTyCon $ \ x1 y1 z1 x2 y2 z2 -> + do { ny1 <- isNumLitTy y1; guard (ny1 /= 0); guard (z1 `tcEqType` z2) + ; guard (y1 `tcEqType` y2); return (Pair x1 x2) } - - -interactTopMul :: [Xi] -> Xi -> [Pair Type] -interactTopMul [s,t] r - | Just 1 <- mbZ = [ s === num 1, t === num 1 ] -- (s * t ~ 1) => (s ~ 1, t ~ 1) - | Just x <- mbX, Just z <- mbZ, Just y <- divide z x = [t === num y] -- (3 * t ~ 15) => (t ~ 5) - | Just y <- mbY, Just z <- mbZ, Just x <- divide z y = [s === num x] -- (s * 3 ~ 15) => (s ~ 5) - where - mbX = isNumLitTy s - mbY = isNumLitTy t - mbZ = isNumLitTy r -interactTopMul _ _ = [] - -interactTopDiv :: [Xi] -> Xi -> [Pair Type] -interactTopDiv _ _ = [] -- I can't think of anything... - -interactTopMod :: [Xi] -> Xi -> [Pair Type] -interactTopMod _ _ = [] -- I can't think of anything... - +{- interactTopExp :: [Xi] -> Xi -> [Pair Type] interactTopExp [s,t] r | Just 0 <- mbZ = [ s === num 0 ] -- (s ^ t ~ 0) => (s ~ 0) @@ -989,11 +987,6 @@ interactTopExp [s,t] r mbZ = isNumLitTy r interactTopExp _ _ = [] -interactTopLog :: [Xi] -> Xi -> [Pair Type] -interactTopLog _ _ = [] -- I can't think of anything... - - - interactTopCmpNat :: [Xi] -> Xi -> [Pair Type] interactTopCmpNat [s,t] r | Just EQ <- isOrderingLitTy r = [ s === t ] @@ -1077,27 +1070,6 @@ interactInertAdd [x1,y1] z1 [x2,y2] z2 where sameZ = tcEqType z1 z2 interactInertAdd _ _ _ _ = [] -interactInertSub :: [Xi] -> Xi -> [Xi] -> Xi -> [Pair Type] -interactInertSub [x1,y1] z1 [x2,y2] z2 - | sameZ && tcEqType x1 x2 = [ y1 === y2 ] - | sameZ && tcEqType y1 y2 = [ x1 === x2 ] - where sameZ = tcEqType z1 z2 -interactInertSub _ _ _ _ = [] - -interactInertMul :: [Xi] -> Xi -> [Xi] -> Xi -> [Pair Type] -interactInertMul [x1,y1] z1 [x2,y2] z2 - | sameZ && known (/= 0) x1 && tcEqType x1 x2 = [ y1 === y2 ] - | sameZ && known (/= 0) y1 && tcEqType y1 y2 = [ x1 === x2 ] - where sameZ = tcEqType z1 z2 - -interactInertMul _ _ _ _ = [] - -interactInertDiv :: [Xi] -> Xi -> [Xi] -> Xi -> [Pair Type] -interactInertDiv _ _ _ _ = [] - -interactInertMod :: [Xi] -> Xi -> [Xi] -> Xi -> [Pair Type] -interactInertMod _ _ _ _ = [] - interactInertExp :: [Xi] -> Xi -> [Xi] -> Xi -> [Pair Type] interactInertExp [x1,y1] z1 [x2,y2] z2 | sameZ && known (> 1) x1 && tcEqType x1 x2 = [ y1 === y2 ] @@ -1106,9 +1078,6 @@ interactInertExp [x1,y1] z1 [x2,y2] z2 interactInertExp _ _ _ _ = [] -interactInertLog :: [Xi] -> Xi -> [Xi] -> Xi -> [Pair Type] -interactInertLog _ _ _ _ = [] - interactInertAppendSymbol :: [Xi] -> Xi -> [Xi] -> Xi -> [Pair Type] interactInertAppendSymbol [x1,y1] z1 [x2,y2] z2 @@ -1128,7 +1097,7 @@ interactInertUnconsSymbol :: [Xi] -> Xi -> [Xi] -> Xi -> [Pair Type] interactInertUnconsSymbol [x1] z1 [x2] z2 | tcEqType z1 z2 = [ x1 === x2 ] interactInertUnconsSymbol _ _ _ _ = [] - +-} {- ----------------------------------------------------------------------------- These inverse functions are used for simplifying propositions using @@ -1204,7 +1173,6 @@ genLog x base = Just (exactLoop 0 x) | otherwise = let s1 = s + 1 in s1 `seq` underLoop s1 (div i base) ----------------------------------------------------------------------------- --} typeCharCmpTyCon :: TyCon typeCharCmpTyCon = @@ -1220,28 +1188,10 @@ typeCharCmpTyCon = typeCharCmpTyFamNameKey typeCharCmpTyCon ops = BuiltInSynFamily { sfMatchFam = matchFamCmpChar - , sfInteractTop = sfInteractTopNone - , sfInteractInert = sfInteractInertNone --- , sfInteractTop = interactTopCmpChar --- , sfInteractInert = sfInteractInertNone + , sfInteractTop = [axCmpCharTop] + , sfInteractInert = [] } -{- -interactTopCmpChar :: [Xi] -> Xi -> [Pair Type] -interactTopCmpChar [s,t] r - | Just EQ <- isOrderingLitTy r = [ s === t ] -interactTopCmpChar _ _ = [] - -cmpChar :: Type -> Type -> Type -cmpChar s t = mkTyConApp typeCharCmpTyCon [s,t] - -axCmpCharDef, axCmpCharRefl :: CoAxiomRule -axCmpCharDef = - mkBinAxiom "CmpCharDef" typeCharCmpTyCon isCharLitTy isCharLitTy $ - \chr1 chr2 -> Just $ ordering $ compare chr1 chr2 -axCmpCharRefl = mkAxiom1 "CmpCharRefl" - $ \(Pair s _) -> (cmpChar s s) === ordering EQ - matchFamCmpChar :: [Type] -> Maybe (CoAxiomRule, [Type], Type) matchFamCmpChar [s,t] | Just x <- mbX, Just y <- mbY = @@ -1250,4 +1200,20 @@ matchFamCmpChar [s,t] where mbX = isCharLitTy s mbY = isCharLitTy t matchFamCmpChar _ = Nothing --} + +cmpChar :: Type -> Type -> Type +cmpChar s t = mkTyConApp typeCharCmpTyCon [s,t] + +axCmpCharDef, axCmpCharRefl :: CoAxiomRule +axCmpCharDef = mkBinAxiom "CmpCharDef" typeCharCmpTyCon isCharLitTy isCharLitTy $ + \chr1 chr2 -> Just $ ordering $ compare chr1 chr2 +axCmpCharRefl = mkAxiom1 "CmpCharRefl" $ + \(Pair s _) -> (cmpChar s s) === ordering EQ + +axCmpCharTop :: CoAxiomRule +axCmpCharTop -- (CmpChar s t ~ EQ) => s ~ t + = mkTopBinFamDeduction "CmpCharT" typeCharCmpTyCon $ \ s t r -> + do { EQ <- isOrderingLitTy r; return (Pair s t) } + + + ===================================== compiler/GHC/Core/Coercion/Axiom.hs ===================================== @@ -609,15 +609,13 @@ data BuiltInSynFamily = BuiltInSynFamily -- where the r in the output is coaxrRole of the rule. It is up to the -- caller to ensure that this role is appropriate. - , sfInteractTop :: [Type] -> Type -> [(CoAxiomRule, TypeEqn)] + , sfInteractTop :: [CoAxiomRule] -- If given these type arguments and RHS, returns the equalities that -- are guaranteed to hold. That is, if -- (ar, Pair s1 s2) is an element ofo (sfInteractTop tys ty) -- then AxiomRule ar [co :: F tys ~ ty] :: s1~s2 - , sfInteractInert :: [Type] -> Type -> - [Type] -> Type - -> [(CoAxiomRule,TypeEqn)] + , sfInteractInert :: [CoAxiomRule] -- If given one set of arguments and result, and another set of arguments -- and result, returns the equalities that are guaranteed to hold. } @@ -626,15 +624,13 @@ data BuiltInSynFamily = BuiltInSynFamily trivialBuiltInFamily :: BuiltInSynFamily trivialBuiltInFamily = BuiltInSynFamily { sfMatchFam = sfMatchNone - , sfInteractTop = sfInteractTopNone - , sfInteractInert = sfInteractInertNone + , sfInteractTop = [] + , sfInteractInert = [] } sfMatchNone :: a -> Maybe b sfMatchNone _ = Nothing -sfInteractTopNone :: a -> b -> [c] -sfInteractTopNone _ _ = [] - -sfInteractInertNone :: a -> b -> c -> d -> [e] -sfInteractInertNone _ _ _ _ = [] +sfInteractTopNone, sfInteractInertNone :: [CoAxiomRule] +sfInteractTopNone = [] +sfInteractInertNone = [] ===================================== compiler/GHC/Tc/Solver/Equality.hs ===================================== @@ -44,6 +44,7 @@ import GHC.Types.Name.Reader import GHC.Types.Basic import GHC.Builtin.Types ( anyTypeOfKind ) +import GHC.Builtin.Types.Literals ( tryInteractTopFam, tryInteractInertFam ) import GHC.Utils.Outputable import GHC.Utils.Panic @@ -2964,7 +2965,8 @@ tryFamFamInjectivity ev eq_rel fun_tc1 fun_args1 fun_tc2 fun_args2 mco fake_rhs2 = anyTypeOfKind ki2 eqs :: [TypeEqn] - eqs = sfInteractInert ops fun_args1 fake_rhs1 fun_args2 fake_rhs2 + eqs = map snd $ tryInteractInertFam ops fun_tc1 + fun_args1 fake_rhs1 fun_args2 fake_rhs2 in unifyFunDeps ev Nominal $ \uenv -> uPairsTcM uenv eqs @@ -3001,8 +3003,8 @@ improveGivenTopFunEqs fam_tc args ev rhs_ty | Just ops <- isBuiltInSynFamTyCon_maybe fam_tc = do { emitNewGivens (ctEvLoc ev) $ [ (Nominal, s, t, new_co) - | Pair s t <- sfInteractTop ops args rhs_ty - , let new_co = mkUnivCo BuiltinProv [given_co] Nominal s t ] + | (ax, Pair s t) <- tryInteractTopFam ops fam_tc args rhs_ty + , let new_co = mkAxiomRuleCo ax [given_co] ] ; return False } | otherwise = return False -- See Note [No Given/Given fundeps] @@ -3030,7 +3032,7 @@ improve_top_fun_eqs :: FamInstEnvs -> TcS [TypeEqn] improve_top_fun_eqs fam_envs fam_tc args rhs_ty | Just ops <- isBuiltInSynFamTyCon_maybe fam_tc - = return (sfInteractTop ops args rhs_ty) + = return (map snd $ tryInteractTopFam ops fam_tc args rhs_ty) -- see Note [Type inference for type families with injectivity] | isOpenTypeFamilyTyCon fam_tc @@ -3144,11 +3146,10 @@ improveLocalFunEqs inerts fam_tc args (EqCt { eq_ev = work_ev, eq_rhs = rhs }) -------------------- do_one_built_in ops rhs (EqCt { eq_lhs = TyFamLHS _ iargs, eq_rhs = irhs, eq_ev = inert_ev }) - | not (isGiven inert_ev && isGiven work_ev) -- See Note [No Given/Given fundeps] - = mk_fd_eqns inert_ev (sfInteractInert ops args rhs iargs irhs) - + | isGiven inert_ev && isGiven work_ev + = [] -- ToDo: fill in | otherwise - = [] + = mk_fd_eqns inert_ev (map snd $ tryInteractInertFam ops fam_tc args rhs iargs irhs) do_one_built_in _ _ _ = pprPanic "interactFunEq 1" (ppr fam_tc) -- TyVarLHS View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e92e84c63781a5224299d455c77f2110ea94bdec -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e92e84c63781a5224299d455c77f2110ea94bdec You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 22:47:50 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 18 Jun 2024 18:47:50 -0400 Subject: [Git][ghc/ghc][master] Clarify -XGADTs enables existential quantification Message-ID: <66720e9618fa1_296a1b251e198126956@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: d70abb49 by sheaf at 2024-06-18T18:47:20-04:00 Clarify -XGADTs enables existential quantification Even though -XGADTs does not turn on -XExistentialQuantification, it does allow the user of existential quantification syntax, without needing to use GADT-style syntax. Fixes #20865 - - - - - 1 changed file: - docs/users_guide/exts/gadt.rst Changes: ===================================== docs/users_guide/exts/gadt.rst ===================================== @@ -93,6 +93,12 @@ also sets :extension:`GADTSyntax` and :extension:`MonoLocalBinds`. -- essentially the same as: -- MkG :: Int -> Int -> G Int + Note that, even though :extension:`GADTs` technically does not imply + :extension:`ExistentialQuantification`, enabling :extension:`GADTs` + does also enable the syntax for existential quantification: :: + + data SomeShow = forall a. Show a => SomeShow a + - It is permitted to declare an ordinary algebraic data type using GADT-style syntax. What makes a GADT into a GADT is not the syntax, but rather the presence of data constructors whose result type is not View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d70abb49cdcbcd0cabc977d6804c6e083bc9f31d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d70abb49cdcbcd0cabc977d6804c6e083bc9f31d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 22:48:35 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 18 Jun 2024 18:48:35 -0400 Subject: [Git][ghc/ghc][master] Add RTS flag --read-tix-file (GHC Proposal 612) Message-ID: <66720ec31df87_296a1b26f0d2c130638@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 13fdf788 by David Binder at 2024-06-18T18:48:02-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - 12 changed files: - docs/users_guide/9.12.1-notes.rst - docs/users_guide/profiling.rst - docs/users_guide/runtime_control.rst - libraries/base/changelog.md - libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc - rts/Hpc.c - rts/RtsFlags.c - rts/include/rts/Flags.h - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 Changes: ===================================== docs/users_guide/9.12.1-notes.rst ===================================== @@ -91,6 +91,11 @@ Runtime system - Reduce fragmentation incurred by the nonmoving GC's segment allocator. In one application this reduced resident set size by 26%. See :ghc-ticket:`24150`. +- The new runtime flag :rts-flag:`--read-tix-file=\` allows to modify whether a preexisting .tix file is read in at the beginning of a program run. + The default is currently ``--read-tix-file=yes`` but will change to ``--read-tix-file=no`` in a future version of GHC. + For this reason, a warning is emitted if a .tix file is read in implicitly. You can silence this warning by explicitly passing ``--read-tix-file=yes``. + Details can be found in `GHC proposal 612 `__. + ``base`` library ~~~~~~~~~~~~~~~~ ===================================== docs/users_guide/profiling.rst ===================================== @@ -1502,9 +1502,9 @@ Running the program generates a file with the ``.tix`` suffix, in this case :file:`Recip.tix`, which contains the coverage data for this run of the program. The program may be run multiple times (e.g. with different test data), and the coverage data from the separate runs is accumulated in -the ``.tix`` file. To reset the coverage data and start again, just -remove the ``.tix`` file. You can control where the ``.tix`` file -is generated using the environment variable :envvar:`HPCTIXFILE`. +the ``.tix`` file. This behaviour can be controlled with the :rts-flag:`--read-tix-file=\` +You can control where the ``.tix`` file is generated using the +environment variable :envvar:`HPCTIXFILE`. .. envvar:: HPCTIXFILE ===================================== docs/users_guide/runtime_control.rst ===================================== @@ -1373,7 +1373,22 @@ and can be controlled by the following flags. .. index:: single: RTS options, hpc -.. rts-flag:: --write-tix-file +.. rts-flag:: --read-tix-file= + + :default: enabled + :since: 9.12 + + The RTS can be instructed to read a ``.tix`` file during the startup + phase. The datastructures which accumulate the coverage information during + program execution are then initialized with the information from this file. + This option is useful for aggregating coverage information over multiple runs + of an executable. + + The default for this flag is currently ``--read-tix-file=yes`` but will change + to ``-read-tix-file=no`` in a future version of GHC according to the accepted + `GHC proposal 612 `__. + +.. rts-flag:: --write-tix-file= :default: enabled :since: 9.10 ===================================== libraries/base/changelog.md ===================================== @@ -1,6 +1,7 @@ # Changelog for [`base` package](http://hackage.haskell.org/package/base) ## 4.21.0.0 *TBA* + * Add a `readTixFile` field to the `HpcFlags` record in `GHC.RTS.Flags` ([CLC proposal #276](https://github.com/haskell/core-libraries-committee/issues/276)) * Add the `MonadFix` instance for `(,) a`, similar to the one for `Writer a` ([CLC proposal #238](https://github.com/haskell/core-libraries-committee/issues/238)) * Improve `toInteger :: Word32 -> Integer` on 64-bit platforms ([CLC proposal #259](https://github.com/haskell/core-libraries-committee/issues/259)) * Make `flip` representation polymorphic ([CLC proposal #245](https://github.com/haskell/core-libraries-committee/issues/245)) ===================================== libraries/ghc-internal/src/GHC/Internal/RTS/Flags.hsc ===================================== @@ -382,7 +382,11 @@ data ParFlags = ParFlags -- -- @since base-4.20.0.0 data HpcFlags = HpcFlags - { writeTixFile :: Bool + { readTixFile :: Bool + -- ^ Controls whether a @.tix@ file is read at + -- the start of execution to initialize the RTS internal + -- HPC datastructures. + , writeTixFile :: Bool -- ^ Controls whether the @.tix@ file should be -- written after the execution of the program. } @@ -498,6 +502,8 @@ getHpcFlags = do let ptr = (#ptr RTS_FLAGS, HpcFlags) rtsFlagsPtr HpcFlags <$> (toBool <$> + (#{peek HPC_FLAGS, readTixFile} ptr :: IO CBool)) + <*> (toBool <$> (#{peek HPC_FLAGS, writeTixFile} ptr :: IO CBool)) getConcFlags :: IO ConcFlags ===================================== rts/Hpc.c ===================================== @@ -236,7 +236,14 @@ startupHpc(void) sprintf(tixFilename, "%s.tix", prog_name); } - if (init_open(__rts_fopen(tixFilename,"r"))) { + if ((RtsFlags.HpcFlags.readTixFile == HPC_YES_IMPLICIT) && init_open(__rts_fopen(tixFilename,"r"))) { + fprintf(stderr,"Deprecation warning:\n" + "I am reading in the existing tix file, and will add hpc info from this run to the existing data in that file.\n" + "GHC 9.14 will cease looking for an existing tix file by default.\n" + "If you positively want to add hpc info to the current tix file, use the RTS option --read-tix-file=yes.\n" + "More information can be found in the accepted GHC proposal 612.\n"); + readTix(); + } else if ((RtsFlags.HpcFlags.readTixFile == HPC_YES_EXPLICIT) && init_open(__rts_fopen(tixFilename,"r"))) { readTix(); } } ===================================== rts/RtsFlags.c ===================================== @@ -297,6 +297,7 @@ void initRtsFlagsDefaults(void) RtsFlags.TickyFlags.showTickyStats = false; RtsFlags.TickyFlags.tickyFile = NULL; #endif + RtsFlags.HpcFlags.readTixFile = HPC_YES_IMPLICIT; RtsFlags.HpcFlags.writeTixFile = true; } @@ -565,6 +566,10 @@ usage_text[] = { " HeapOverflow exception before the exception is thrown again, if", " the program is still exceeding the heap limit.", "", +" --read-tix-file=", +" Whether to initialize HPC datastructures from .tix " +" at the start of execution. (default: yes)", +"", " --write-tix-file=", " Whether to write .tix at the end of execution.", " (default: yes)", @@ -1068,6 +1073,16 @@ error = true; RtsFlags.GcFlags.nonmovingDenseAllocatorCount = threshold; } } + else if (strequal("read-tix-file=yes", + &rts_argv[arg][2])) { + OPTION_UNSAFE; + RtsFlags.HpcFlags.readTixFile = HPC_YES_EXPLICIT; + } + else if (strequal("read-tix-file=no", + &rts_argv[arg][2])) { + OPTION_UNSAFE; + RtsFlags.HpcFlags.readTixFile = HPC_NO_EXPLICIT; + } else if (strequal("write-tix-file=yes", &rts_argv[arg][2])) { OPTION_UNSAFE; ===================================== rts/include/rts/Flags.h ===================================== @@ -302,10 +302,26 @@ typedef struct _PAR_FLAGS { bool setAffinity; /* force thread affinity with CPUs */ } PAR_FLAGS; +/* Corresponds to the RTS flag `--read-tix-file=`. + * The accepted GHC proposal 612 introduced a one-release warning period + * during which we emit a warning if we read a .tix file and the flag + * isn't explicitly set. In order to distinguish between whether the flag + * was explicitly set or defaulted we need to use a tri-state variable. + */ +typedef enum _HPC_READ_FILE { + HPC_NO_EXPLICIT = 0, /* The user has specified --read-tix-file=no */ + HPC_YES_IMPLICIT = 1, /* The user hasn't specified an option and we emit + * a warning when we read a tix file. + */ + HPC_YES_EXPLICIT = 2 /* The user has specified --read-tix-file=yes */ + } HPC_READ_FILE; + /* See Note [Synchronization of flags and base APIs] */ typedef struct _HPC_FLAGS { bool writeTixFile; /* Whether the RTS should write a tix file at the end of execution */ + HPC_READ_FILE readTixFile; /* Whether the RTS should read a tix + file at the beginning of execution */ } HPC_FLAGS; /* See Note [Synchronization of flags and base APIs] */ ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -9105,7 +9105,7 @@ module GHC.RTS.Flags where type GiveGCStats :: * data GiveGCStats = NoGCStats | CollectGCStats | OneLineGCStats | SummaryGCStats | VerboseGCStats type HpcFlags :: * - data HpcFlags = HpcFlags {writeTixFile :: GHC.Types.Bool} + data HpcFlags = HpcFlags {readTixFile :: GHC.Types.Bool, writeTixFile :: GHC.Types.Bool} type IoManagerFlag :: * data IoManagerFlag = IoManagerFlagAuto | IoManagerFlagSelect | IoManagerFlagMIO | IoManagerFlagWinIO | IoManagerFlagWin32Legacy type IoSubSystem :: * ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -12147,7 +12147,7 @@ module GHC.RTS.Flags where type GiveGCStats :: * data GiveGCStats = NoGCStats | CollectGCStats | OneLineGCStats | SummaryGCStats | VerboseGCStats type HpcFlags :: * - data HpcFlags = HpcFlags {writeTixFile :: GHC.Types.Bool} + data HpcFlags = HpcFlags {readTixFile :: GHC.Types.Bool, writeTixFile :: GHC.Types.Bool} type IoManagerFlag :: * data IoManagerFlag = IoManagerFlagAuto | IoManagerFlagSelect | IoManagerFlagMIO | IoManagerFlagWinIO | IoManagerFlagWin32Legacy type IoSubSystem :: * ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -9329,7 +9329,7 @@ module GHC.RTS.Flags where type GiveGCStats :: * data GiveGCStats = NoGCStats | CollectGCStats | OneLineGCStats | SummaryGCStats | VerboseGCStats type HpcFlags :: * - data HpcFlags = HpcFlags {writeTixFile :: GHC.Types.Bool} + data HpcFlags = HpcFlags {readTixFile :: GHC.Types.Bool, writeTixFile :: GHC.Types.Bool} type IoManagerFlag :: * data IoManagerFlag = IoManagerFlagAuto | IoManagerFlagSelect | IoManagerFlagMIO | IoManagerFlagWinIO | IoManagerFlagWin32Legacy type IoSubSystem :: * ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -9105,7 +9105,7 @@ module GHC.RTS.Flags where type GiveGCStats :: * data GiveGCStats = NoGCStats | CollectGCStats | OneLineGCStats | SummaryGCStats | VerboseGCStats type HpcFlags :: * - data HpcFlags = HpcFlags {writeTixFile :: GHC.Types.Bool} + data HpcFlags = HpcFlags {readTixFile :: GHC.Types.Bool, writeTixFile :: GHC.Types.Bool} type IoManagerFlag :: * data IoManagerFlag = IoManagerFlagAuto | IoManagerFlagSelect | IoManagerFlagMIO | IoManagerFlagWinIO | IoManagerFlagWin32Legacy type IoSubSystem :: * View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/13fdf78861b18678087b70abc4c435facbc28e35 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/13fdf78861b18678087b70abc4c435facbc28e35 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 22:49:32 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 18 Jun 2024 18:49:32 -0400 Subject: [Git][ghc/ghc][master] 2 commits: Improve sharing of duplicated values in `ModIface`, fixes #24723 Message-ID: <66720efca8148_296a1b28e84681354e4@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 1bab7dde by Fendor at 2024-06-18T18:48:38-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18698b T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The tests T16875 and T18698b fail on i386-linux for the same reason. - - - - - 15 changed files: - compiler/GHC.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/Unit/Module/ModIface.hs - compiler/GHC/Utils/Binary.hs - testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs - utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs Changes: ===================================== compiler/GHC.hs ===================================== @@ -98,7 +98,35 @@ module GHC ( lookupGlobalName, findGlobalAnns, mkNamePprCtxForModule, - ModIface, ModIface_(..), + ModIface, + ModIface_( + mi_module, + mi_sig_of, + mi_hsc_src, + mi_src_hash, + mi_hi_bytes, + mi_deps, + mi_usages, + mi_exports, + mi_used_th, + mi_fixities, + mi_warns, + mi_anns, + mi_insts, + mi_fam_insts, + mi_rules, + mi_decls, + mi_extra_decls, + mi_top_env, + mi_hpc, + mi_trust, + mi_trust_pkg, + mi_complete_matches, + mi_docs, + mi_final_exts, + mi_ext_fields + ), + pattern ModIface, SafeHaskellMode(..), -- * Printing ===================================== compiler/GHC/Iface/Binary.hs ===================================== @@ -18,6 +18,8 @@ module GHC.Iface.Binary ( getSymtabName, CheckHiWay(..), TraceBinIFace(..), + getIfaceWithExtFields, + putIfaceWithExtFields, getWithUserData, putWithUserData, @@ -61,6 +63,8 @@ import Data.Map.Strict (Map) import Data.Word import System.IO.Unsafe import Data.Typeable (Typeable) +import qualified GHC.Data.Strict as Strict +import Data.Function ((&)) -- --------------------------------------------------------------------------- @@ -169,17 +173,29 @@ readBinIface readBinIface profile name_cache checkHiWay traceBinIface hi_path = do (src_hash, bh) <- readBinIfaceHeader profile name_cache checkHiWay traceBinIface hi_path - extFields_p <- get bh + mod_iface <- getIfaceWithExtFields name_cache bh - mod_iface <- getWithUserData name_cache bh + return $ mod_iface + & addSourceFingerprint src_hash - seekBinReader bh extFields_p - extFields <- get bh - return mod_iface - { mi_ext_fields = extFields - , mi_src_hash = src_hash - } +getIfaceWithExtFields :: NameCache -> ReadBinHandle -> IO ModIface +getIfaceWithExtFields name_cache bh = do + -- Start offset for the byte array that contains the serialised 'ModIface'. + start <- tellBinReader bh + extFields_p_rel <- getRelBin bh + + mod_iface <- getWithUserData name_cache bh + + seekBinReaderRel bh extFields_p_rel + extFields <- get bh + -- Store the 'ModIface' byte array, so that we can avoid serialisation if + -- the 'ModIface' isn't modified. + -- See Note [Sharing of ModIface] + modIfaceBinData <- freezeBinHandle bh start + pure $ mod_iface + & set_mi_ext_fields extFields + & set_mi_hi_bytes (FullIfaceBinHandle $ Strict.Just modIfaceBinData) -- | This performs a get action after reading the dictionary and symbol -- table. It is necessary to run this before trying to deserialise any @@ -209,7 +225,7 @@ getTables name_cache bh = do -- add it to the 'ReaderUserData' of 'ReadBinHandle'. decodeReaderTable :: Typeable a => ReaderTable a -> ReadBinHandle -> IO ReadBinHandle decodeReaderTable tbl bh0 = do - table <- Binary.forwardGet bh (getTable tbl bh0) + table <- Binary.forwardGetRel bh (getTable tbl bh0) let binaryReader = mkReaderFromTable tbl table pure $ addReaderToUserData binaryReader bh0 @@ -246,19 +262,24 @@ writeBinIface profile traceBinIface compressionLevel hi_path mod_iface = do put_ bh tag put_ bh (mi_src_hash mod_iface) - extFields_p_p <- tellBinWriter bh - put_ bh extFields_p_p - - putWithUserData traceBinIface compressionLevel bh mod_iface - - extFields_p <- tellBinWriter bh - putAt bh extFields_p_p extFields_p - seekBinWriter bh extFields_p - put_ bh (mi_ext_fields mod_iface) + putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface -- And send the result to the file writeBinMem bh hi_path +-- | Puts the 'ModIface' to the 'WriteBinHandle'. +-- +-- This avoids serialisation of the 'ModIface' if the fields 'mi_hi_bytes' contains a +-- 'Just' value. This field is populated by reading the 'ModIface' using +-- 'getIfaceWithExtFields' and not modifying it in any way afterwards. +putIfaceWithExtFields :: TraceBinIFace -> CompressionIFace -> WriteBinHandle -> ModIface -> IO () +putIfaceWithExtFields traceBinIface compressionLevel bh mod_iface = + case mi_hi_bytes mod_iface of + FullIfaceBinHandle Strict.Nothing -> do + forwardPutRel_ bh (\_ -> put_ bh (mi_ext_fields mod_iface)) $ do + putWithUserData traceBinIface compressionLevel bh mod_iface + FullIfaceBinHandle (Strict.Just binData) -> putFullBinData bh binData + -- | Put a piece of data with an initialised `UserData` field. This -- is necessary if you want to serialise Names or FastStrings. -- It also writes a symbol table and the dictionary. @@ -332,7 +353,7 @@ putAllTables _ [] act = do a <- act pure ([], a) putAllTables bh (x : xs) act = do - (r, (res, a)) <- forwardPut bh (const $ putTable x bh) $ do + (r, (res, a)) <- forwardPutRel bh (const $ putTable x bh) $ do putAllTables bh xs act pure (r : res, a) @@ -484,7 +505,7 @@ to the table we need to deserialise first. What deduplication tables exist and the order of serialisation is currently statically specified in 'putWithTables'. 'putWithTables' also takes care of the serialisation of used deduplication tables. The deserialisation of the deduplication tables happens 'getTables', using 'Binary' utility -functions such as 'forwardGet'. +functions such as 'forwardGetRel'. Here, a visualisation of the table structure we currently have (ignoring 'ExtensibleFields'): @@ -585,7 +606,6 @@ initWriteIfaceType compressionLevel = do putGenericSymTab sym_tab bh ty _ -> putIfaceType bh ty - fullIfaceTypeSerialiser sym_tab bh ty = do put_ bh ifaceTypeSharedByte putGenericSymTab sym_tab bh ty ===================================== compiler/GHC/Iface/Ext/Binary.hs ===================================== @@ -228,7 +228,7 @@ readHieFileContents bh0 name_cache = do get bh1 where get_dictionary tbl bin_handle = do - fsTable <- Binary.forwardGet bin_handle (getTable tbl bin_handle) + fsTable <- Binary.forwardGetRel bin_handle (getTable tbl bin_handle) let fsReader = mkReaderFromTable tbl fsTable bhFs = addReaderToUserData fsReader bin_handle ===================================== compiler/GHC/Iface/Ext/Fields.hs ===================================== @@ -41,7 +41,7 @@ instance Binary ExtensibleFields where -- to point to the start of each payload: forM_ header_entries $ \(field_p_p, dat) -> do field_p <- tellBinWriter bh - putAt bh field_p_p field_p + putAtRel bh field_p_p field_p seekBinWriter bh field_p put_ bh dat @@ -50,11 +50,11 @@ instance Binary ExtensibleFields where -- Get the names and field pointers: header_entries <- replicateM n $ - (,) <$> get bh <*> get bh + (,) <$> get bh <*> getRelBin bh -- Seek to and get each field's payload: fields <- forM header_entries $ \(name, field_p) -> do - seekBinReader bh field_p + seekBinReaderRel bh field_p dat <- get bh return (name, dat) ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -117,6 +117,7 @@ import System.FilePath import System.Directory import GHC.Driver.Env.KnotVars import GHC.Iface.Errors.Types +import Data.Function ((&)) {- ************************************************************************ @@ -515,14 +516,12 @@ loadInterface doc_str mod from ; new_eps_anns <- tcIfaceAnnotations (mi_anns iface) ; new_eps_complete_matches <- tcIfaceCompleteMatches (mi_complete_matches iface) - ; let { final_iface = iface { - mi_decls = panic "No mi_decls in PIT", - mi_insts = panic "No mi_insts in PIT", - mi_fam_insts = panic "No mi_fam_insts in PIT", - mi_rules = panic "No mi_rules in PIT", - mi_anns = panic "No mi_anns in PIT" - } - } + ; let final_iface = iface + & set_mi_decls (panic "No mi_decls in PIT") + & set_mi_insts (panic "No mi_insts in PIT") + & set_mi_fam_insts (panic "No mi_fam_insts in PIT") + & set_mi_rules (panic "No mi_rules in PIT") + & set_mi_anns (panic "No mi_anns in PIT") ; let bad_boot = mi_boot iface == IsBoot && isJust (lookupKnotVars (if_rec_types gbl_env) mod) @@ -1018,13 +1017,13 @@ readIface dflags name_cache wanted_mod file_path = do -- See Note [GHC.Prim] in primops.txt.pp. ghcPrimIface :: ModIface ghcPrimIface - = empty_iface { - mi_exports = ghcPrimExports, - mi_decls = [], - mi_fixities = fixities, - mi_final_exts = (mi_final_exts empty_iface){ mi_fix_fn = mkIfaceFixCache fixities }, - mi_docs = Just ghcPrimDeclDocs -- See Note [GHC.Prim Docs] - } + = empty_iface + & set_mi_exports ghcPrimExports + & set_mi_decls [] + & set_mi_fixities fixities + & set_mi_final_exts ((mi_final_exts empty_iface){ mi_fix_fn = mkIfaceFixCache fixities }) + & set_mi_docs (Just ghcPrimDeclDocs) -- See Note [GHC.Prim Docs] + where empty_iface = emptyFullModIface gHC_PRIM @@ -1108,7 +1107,7 @@ pprModIfaceSimple unit_state iface = -- -- The UnitState is used to pretty-print units pprModIface :: UnitState -> ModIface -> SDoc -pprModIface unit_state iface at ModIface{ mi_final_exts = exts } +pprModIface unit_state iface = vcat [ text "interface" <+> ppr (mi_module iface) <+> pp_hsc_src (mi_hsc_src iface) <+> (if mi_orphan exts then text "[orphan module]" else Outputable.empty) @@ -1149,6 +1148,7 @@ pprModIface unit_state iface at ModIface{ mi_final_exts = exts } , text "extensible fields:" $$ nest 2 (pprExtensibleFields (mi_ext_fields iface)) ] where + exts = mi_final_exts iface pp_hsc_src HsBootFile = text "[boot]" pp_hsc_src HsigFile = text "[hsig]" pp_hsc_src HsSrcFile = Outputable.empty ===================================== compiler/GHC/Iface/Make.hs ===================================== @@ -69,10 +69,13 @@ import GHC.Types.HpcInfo import GHC.Types.CompleteMatch import GHC.Types.SourceText import GHC.Types.SrcLoc ( unLoc ) +import GHC.Types.Name.Cache import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Utils.Logger +import GHC.Utils.Binary +import GHC.Iface.Binary import GHC.Data.FastString import GHC.Data.Maybe @@ -142,14 +145,47 @@ mkFullIface hsc_env partial_iface mb_stg_infos mb_cmm_infos = do full_iface <- {-# SCC "addFingerprints" #-} - addFingerprints hsc_env partial_iface{ mi_decls = decls } + addFingerprints hsc_env (set_mi_decls decls partial_iface) -- Debug printing let unit_state = hsc_units hsc_env putDumpFileMaybe (hsc_logger hsc_env) Opt_D_dump_hi "FINAL INTERFACE" FormatText (pprModIface unit_state full_iface) + final_iface <- shareIface (hsc_NC hsc_env) (flagsToIfCompression $ hsc_dflags hsc_env) full_iface + return final_iface - return full_iface +-- | Compress an 'ModIface' and share as many values as possible, depending on the 'CompressionIFace' level. +-- See Note [Sharing of ModIface]. +-- +-- We compress the 'ModIface' by serialising the 'ModIface' to an in-memory byte array, and then deserialising it. +-- The deserialisation will deduplicate certain values depending on the 'CompressionIFace' level. +-- See Note [Deduplication during iface binary serialisation] for how we do that. +-- +-- Additionally, we cache the serialised byte array, so if the 'ModIface' is not modified +-- after calling 'shareIface', 'writeBinIface' will reuse that buffer without serialising the 'ModIface' again. +-- Modifying the 'ModIface' forces us to re-serialise it again. +shareIface :: NameCache -> CompressionIFace -> ModIface -> IO ModIface +shareIface _ NormalCompression mi = do + -- In 'NormalCompression', the sharing isn't reducing the memory usage, as 'Name's and 'FastString's are + -- already shared, and at this compression level, we don't compress/share anything else. + -- Thus, for a brief moment we simply double the memory residency for no reason. + -- Therefore, we only try to share expensive values if the compression mode is higher than + -- 'NormalCompression' + pure mi +shareIface nc compressionLevel mi = do + bh <- openBinMem initBinMemSize + start <- tellBinWriter bh + putIfaceWithExtFields QuietBinIFace compressionLevel bh mi + rbh <- shrinkBinBuffer bh + seekBinReader rbh start + res <- getIfaceWithExtFields nc rbh + let resiface = restoreFromOldModIface mi res + forceModIface resiface + return resiface + +-- | Initial ram buffer to allocate for writing interface files. +initBinMemSize :: Int +initBinMemSize = 1024 * 1024 -- 1 MB updateDecl :: [IfaceDecl] -> Maybe StgCgInfos -> Maybe CmmCgInfos -> [IfaceDecl] updateDecl decls Nothing Nothing = decls @@ -304,40 +340,40 @@ mkIface_ hsc_env icomplete_matches = map mkIfaceCompleteMatch complete_matches !rdrs = maybeGlobalRdrEnv rdr_env - ModIface { - mi_module = this_mod, + emptyPartialModIface this_mod -- Need to record this because it depends on the -instantiated-with flag -- which could change - mi_sig_of = if semantic_mod == this_mod - then Nothing - else Just semantic_mod, - mi_hsc_src = hsc_src, - mi_deps = deps, - mi_usages = usages, - mi_exports = mkIfaceExports exports, + & set_mi_sig_of (if semantic_mod == this_mod + then Nothing + else Just semantic_mod) + & set_mi_hsc_src hsc_src + & set_mi_deps deps + & set_mi_usages usages + & set_mi_exports (mkIfaceExports exports) -- Sort these lexicographically, so that -- the result is stable across compilations - mi_insts = sortBy cmp_inst iface_insts, - mi_fam_insts = sortBy cmp_fam_inst iface_fam_insts, - mi_rules = sortBy cmp_rule iface_rules, - - mi_fixities = fixities, - mi_warns = warns, - mi_anns = annotations, - mi_top_env = rdrs, - mi_used_th = used_th, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_hpc = isHpcUsed hpc_info, - mi_trust = trust_info, - mi_trust_pkg = pkg_trust_req, - mi_complete_matches = icomplete_matches, - mi_docs = docs, - mi_final_exts = (), - mi_ext_fields = emptyExtensibleFields, - mi_src_hash = ms_hs_hash mod_summary - } + & set_mi_insts (sortBy cmp_inst iface_insts) + & set_mi_fam_insts (sortBy cmp_fam_inst iface_fam_insts) + & set_mi_rules (sortBy cmp_rule iface_rules) + + & set_mi_fixities fixities + & set_mi_warns warns + & set_mi_anns annotations + & set_mi_top_env rdrs + & set_mi_used_th used_th + & set_mi_decls decls + & set_mi_extra_decls extra_decls + & set_mi_hpc (isHpcUsed hpc_info) + & set_mi_trust trust_info + & set_mi_trust_pkg pkg_trust_req + & set_mi_complete_matches (icomplete_matches) + & set_mi_docs docs + & set_mi_final_exts () + & set_mi_ext_fields emptyExtensibleFields + & set_mi_src_hash (ms_hs_hash mod_summary) + & set_mi_hi_bytes PartialIfaceBinHandle + where cmp_rule = lexicalCompareFS `on` ifRuleName -- Compare these lexicographically by OccName, *not* by unique, @@ -513,3 +549,22 @@ That is, in Y, In the result of mkIfaceExports, the names are grouped by defining module, so we may need to split up a single Avail into multiple ones. -} + +{- +Note [Sharing of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~ +A 'ModIface' contains many duplicated values such as 'Name', 'FastString' and 'IfaceType'. +'Name's and 'FastString's are already deduplicated by default using the 'NameCache' and +'FastStringTable' respectively. +However, 'IfaceType' can be quite expensive in terms of memory usage. +To improve the sharing of 'IfaceType', we introduced deduplication tables during +serialisation of 'ModIface', see Note [Deduplication during iface binary serialisation]. + +We can improve the sharing of 'ModIface' at run-time as well, by serialising the 'ModIface' to +an in-memory buffer, and then deserialising it again. +This implicitly shares duplicated values. + +To avoid re-serialising the 'ModIface' when writing it to disk, we save the serialised 'ModIface' buffer +in 'mi_hi_bytes_' field of said 'ModIface'. This buffer is written to disk directly in 'putIfaceWithExtFields'. +If we have to modify the 'ModIface' after 'shareIface' is called, the buffer needs to be discarded. +-} ===================================== compiler/GHC/Iface/Recomp.hs ===================================== @@ -1281,7 +1281,8 @@ addFingerprints hsc_env iface0 , mi_fix_fn = fix_fn , mi_hash_fn = lookupOccEnv local_env } - final_iface = iface0 { mi_decls = sorted_decls, mi_extra_decls = sorted_extra_decls, mi_final_exts = final_iface_exts } + final_iface = completePartialModIface iface0 + sorted_decls sorted_extra_decls final_iface_exts -- return final_iface ===================================== compiler/GHC/Iface/Rename.hs ===================================== @@ -44,6 +44,7 @@ import GHC.Utils.Panic import qualified Data.Traversable as T import Data.IORef +import Data.Function ((&)) tcRnMsgMaybe :: IO (Either (Messages TcRnMessage) a) -> TcM a tcRnMsgMaybe do_this = do @@ -108,13 +109,14 @@ rnModIface hsc_env insts nsubst iface = deps <- rnDependencies (mi_deps iface) -- TODO: -- mi_rules - return iface { mi_module = mod - , mi_sig_of = sig_of - , mi_insts = insts - , mi_fam_insts = fams - , mi_exports = exports - , mi_decls = decls - , mi_deps = deps } + return $ iface + & set_mi_module mod + & set_mi_sig_of sig_of + & set_mi_insts insts + & set_mi_fam_insts fams + & set_mi_exports exports + & set_mi_decls decls + & set_mi_deps deps -- | Rename just the exports of a 'ModIface'. Useful when we're doing -- shaping prior to signature merging. ===================================== compiler/GHC/Tc/Errors/Hole.hs ===================================== @@ -76,7 +76,7 @@ import GHC.Tc.Utils.Unify ( tcSubTypeSigma ) import GHC.HsToCore.Docs ( extractDocs ) import GHC.Hs.Doc -import GHC.Unit.Module.ModIface ( ModIface_(..) ) +import GHC.Unit.Module.ModIface ( mi_docs ) import GHC.Iface.Load ( loadInterfaceForName ) import GHC.Builtin.Utils (knownKeyNames) ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -1562,7 +1562,8 @@ lookupDeclDoc nm = do -- Wasn't in the current module. Try searching other external ones! mIface <- getExternalModIface nm case mIface of - Just ModIface { mi_docs = Just Docs{docs_decls = dmap} } -> + Just iface + | Just Docs{docs_decls = dmap} <- mi_docs iface -> pure $ renderHsDocStrings . map hsDocString <$> lookupUniqMap dmap nm _ -> pure Nothing @@ -1578,7 +1579,8 @@ lookupArgDoc i nm = do Nothing -> do mIface <- getExternalModIface nm case mIface of - Just ModIface { mi_docs = Just Docs{docs_args = amap} } -> + Just iface + | Just Docs{docs_args = amap} <- mi_docs iface-> pure $ renderHsDocString . hsDocString <$> (lookupUniqMap amap nm >>= IntMap.lookup i) _ -> pure Nothing ===================================== compiler/GHC/Tc/Utils/Backpack.hs ===================================== @@ -87,6 +87,7 @@ import Control.Monad import Data.List (find) import GHC.Iface.Errors.Types +import Data.Function ((&)) checkHsigDeclM :: ModIface -> TyThing -> TyThing -> TcRn () checkHsigDeclM sig_iface sig_thing real_thing = do @@ -369,8 +370,8 @@ tcRnMergeSignatures hsc_env hpm orig_tcg_env iface = thinModIface :: [AvailInfo] -> ModIface -> ModIface thinModIface avails iface = - iface { - mi_exports = avails, + iface + & set_mi_exports avails -- mi_fixities = ..., -- mi_warns = ..., -- mi_anns = ..., @@ -378,10 +379,9 @@ thinModIface avails iface = -- perhaps there might be two IfaceTopBndr that are the same -- OccName but different Name. Requires better understanding -- of invariants here. - mi_decls = exported_decls ++ non_exported_decls ++ dfun_decls + & set_mi_decls (exported_decls ++ non_exported_decls ++ dfun_decls) -- mi_insts = ..., -- mi_fam_insts = ..., - } where decl_pred occs decl = nameOccName (ifName decl) `elemOccSet` occs filter_decls occs = filter (decl_pred occs . snd) (mi_decls iface) ===================================== compiler/GHC/Unit/Module/ModIface.hs ===================================== @@ -4,10 +4,68 @@ {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE NamedFieldPuns #-} +{-# LANGUAGE PatternSynonyms #-} + module GHC.Unit.Module.ModIface ( ModIface - , ModIface_ (..) + , ModIface_ + ( mi_module + , mi_sig_of + , mi_hsc_src + , mi_deps + , mi_usages + , mi_exports + , mi_used_th + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_extra_decls + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_hpc + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_final_exts + , mi_ext_fields + , mi_src_hash + , mi_hi_bytes + ) + , pattern ModIface + , restoreFromOldModIface + , addSourceFingerprint + , set_mi_module + , set_mi_sig_of + , set_mi_hsc_src + , set_mi_src_hash + , set_mi_hi_bytes + , set_mi_deps + , set_mi_usages + , set_mi_exports + , set_mi_used_th + , set_mi_fixities + , set_mi_warns + , set_mi_anns + , set_mi_insts + , set_mi_fam_insts + , set_mi_rules + , set_mi_decls + , set_mi_extra_decls + , set_mi_top_env + , set_mi_hpc + , set_mi_trust + , set_mi_trust_pkg + , set_mi_complete_matches + , set_mi_docs + , set_mi_final_exts + , set_mi_ext_fields + , completePartialModIface + , IfaceBinHandle(..) , PartialModIface , ModIfaceBackend (..) , IfaceDeclExts @@ -47,6 +105,7 @@ import GHC.Types.Fixity import GHC.Types.Fixity.Env import GHC.Types.HpcInfo import GHC.Types.Name +import GHC.Types.Name.Reader (IfGlobalRdrEnv) import GHC.Types.SafeHaskell import GHC.Types.SourceFile import GHC.Types.Unique.DSet @@ -59,7 +118,7 @@ import GHC.Utils.Binary import Control.DeepSeq import Control.Exception -import GHC.Types.Name.Reader (IfGlobalRdrEnv) +import qualified GHC.Data.Strict as Strict {- Note [Interface file stages] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -141,7 +200,17 @@ type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where IfaceBackendExts 'ModIfaceCore = () IfaceBackendExts 'ModIfaceFinal = ModIfaceBackend - +-- | In-memory byte array representation of a 'ModIface'. +-- +-- See Note [Sharing of ModIface] for why we need this. +data IfaceBinHandle (phase :: ModIfacePhase) where + -- | A partial 'ModIface' cannot be serialised to disk. + PartialIfaceBinHandle :: IfaceBinHandle 'ModIfaceCore + -- | Optional 'FullBinData' that can be serialised to disk directly. + -- + -- See Note [Private fields in ModIface] for when this fields needs to be cleared + -- (e.g., set to 'Nothing'). + FullIfaceBinHandle :: !(Strict.Maybe FullBinData) -> IfaceBinHandle 'ModIfaceFinal -- | A 'ModIface' plus a 'ModDetails' summarises everything we know -- about a compiled module. The 'ModIface' is the stuff *before* linking, @@ -155,62 +224,65 @@ type family IfaceBackendExts (phase :: ModIfacePhase) = bk | bk -> phase where -- -- See Note [Strictness in ModIface] to learn about why some fields are -- strict and others are not. +-- +-- See Note [Private fields in ModIface] to learn why we don't export any of the +-- fields. data ModIface_ (phase :: ModIfacePhase) - = ModIface { - mi_module :: !Module, -- ^ Name of the module we are for - mi_sig_of :: !(Maybe Module), -- ^ Are we a sig of another mod? + = PrivateModIface { + mi_module_ :: !Module, -- ^ Name of the module we are for + mi_sig_of_ :: !(Maybe Module), -- ^ Are we a sig of another mod? - mi_hsc_src :: !HscSource, -- ^ Boot? Signature? + mi_hsc_src_ :: !HscSource, -- ^ Boot? Signature? - mi_deps :: Dependencies, + mi_deps_ :: Dependencies, -- ^ The dependencies of the module. This is -- consulted for directly-imported modules, but not -- for anything else (hence lazy) - mi_usages :: [Usage], + mi_usages_ :: [Usage], -- ^ Usages; kept sorted so that it's easy to decide -- whether to write a new iface file (changing usages -- doesn't affect the hash of this module) -- NOT STRICT! we read this field lazily from the interface file -- It is *only* consulted by the recompilation checker - mi_exports :: ![IfaceExport], + mi_exports_ :: ![IfaceExport], -- ^ Exports -- Kept sorted by (mod,occ), to make version comparisons easier -- Records the modules that are the declaration points for things -- exported by this module, and the 'OccName's of those things - mi_used_th :: !Bool, + mi_used_th_ :: !Bool, -- ^ Module required TH splices when it was compiled. -- This disables recompilation avoidance (see #481). - mi_fixities :: [(OccName,Fixity)], + mi_fixities_ :: [(OccName,Fixity)], -- ^ Fixities -- NOT STRICT! we read this field lazily from the interface file - mi_warns :: IfaceWarnings, + mi_warns_ :: IfaceWarnings, -- ^ Warnings -- NOT STRICT! we read this field lazily from the interface file - mi_anns :: [IfaceAnnotation], + mi_anns_ :: [IfaceAnnotation], -- ^ Annotations -- NOT STRICT! we read this field lazily from the interface file - mi_decls :: [IfaceDeclExts phase], + mi_decls_ :: [IfaceDeclExts phase], -- ^ Type, class and variable declarations -- The hash of an Id changes if its fixity or deprecations change -- (as well as its type of course) -- Ditto data constructors, class operations, except that -- the hash of the parent class/tycon changes - mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], + mi_extra_decls_ :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo], -- ^ Extra variable definitions which are **NOT** exposed but when -- combined with mi_decls allows us to restart code generation. -- See Note [Interface Files with Core Definitions] and Note [Interface File with Core: Sharing RHSs] - mi_top_env :: !(Maybe IfaceTopEnv), + mi_top_env_ :: !(Maybe IfaceTopEnv), -- ^ Just enough information to reconstruct the top level environment in -- the /original source/ code for this module. which -- is NOT the same as mi_exports, nor mi_decls (which @@ -226,36 +298,36 @@ data ModIface_ (phase :: ModIfacePhase) -- 'HomeModInfo', but that leads to more plumbing. -- Instance declarations and rules - mi_insts :: [IfaceClsInst], -- ^ Sorted class instance - mi_fam_insts :: [IfaceFamInst], -- ^ Sorted family instances - mi_rules :: [IfaceRule], -- ^ Sorted rules + mi_insts_ :: [IfaceClsInst], -- ^ Sorted class instance + mi_fam_insts_ :: [IfaceFamInst], -- ^ Sorted family instances + mi_rules_ :: [IfaceRule], -- ^ Sorted rules - mi_hpc :: !AnyHpcUsage, + mi_hpc_ :: !AnyHpcUsage, -- ^ True if this program uses Hpc at any point in the program. - mi_trust :: !IfaceTrustInfo, + mi_trust_ :: !IfaceTrustInfo, -- ^ Safe Haskell Trust information for this module. - mi_trust_pkg :: !Bool, + mi_trust_pkg_ :: !Bool, -- ^ Do we require the package this module resides in be trusted -- to trust this module? This is used for the situation where a -- module is Safe (so doesn't require the package be trusted -- itself) but imports some trustworthy modules from its own -- package (which does require its own package be trusted). -- See Note [Trust Own Package] in GHC.Rename.Names - mi_complete_matches :: ![IfaceCompleteMatch], + mi_complete_matches_ :: ![IfaceCompleteMatch], - mi_docs :: !(Maybe Docs), + mi_docs_ :: !(Maybe Docs), -- ^ Docstrings and related data for use by haddock, the ghci -- @:doc@ command, and other tools. -- -- @Just _@ @<=>@ the module was built with @-haddock at . - mi_final_exts :: !(IfaceBackendExts phase), + mi_final_exts_ :: !(IfaceBackendExts phase), -- ^ Either `()` or `ModIfaceBackend` for -- a fully instantiated interface. - mi_ext_fields :: !ExtensibleFields, + mi_ext_fields_ :: !ExtensibleFields, -- ^ Additional optional fields, where the Map key represents -- the field name, resulting in a (size, serialized data) pair. -- Because the data is intended to be serialized through the @@ -264,8 +336,13 @@ data ModIface_ (phase :: ModIfacePhase) -- chosen over `ByteString`s. -- - mi_src_hash :: !Fingerprint + mi_src_hash_ :: !Fingerprint, -- ^ Hash of the .hs source, used for recompilation checking. + mi_hi_bytes_ :: !(IfaceBinHandle phase) + -- ^ A serialised in-memory buffer of this 'ModIface'. + -- If this handle is given, we can avoid serialising the 'ModIface' + -- when writing this 'ModIface' to disk, and write this buffer to disk instead. + -- See Note [Sharing of ModIface]. } -- Enough information to reconstruct the top level environment for a module @@ -354,34 +431,40 @@ renameFreeHoles fhs insts = -- See Note [Strictness in ModIface] about where we use lazyPut vs put instance Binary ModIface where - put_ bh (ModIface { - mi_module = mod, - mi_sig_of = sig_of, - mi_hsc_src = hsc_src, - mi_src_hash = _src_hash, -- Don't `put_` this in the instance + put_ bh (PrivateModIface { + mi_module_ = mod, + mi_sig_of_ = sig_of, + mi_hsc_src_ = hsc_src, + mi_src_hash_ = _src_hash, -- Don't `put_` this in the instance -- because we are going to write it -- out separately in the actual file - mi_deps = deps, - mi_usages = usages, - mi_exports = exports, - mi_used_th = used_th, - mi_fixities = fixities, - mi_warns = warns, - mi_anns = anns, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_insts = insts, - mi_fam_insts = fam_insts, - mi_rules = rules, - mi_hpc = hpc_info, - mi_trust = trust, - mi_trust_pkg = trust_pkg, - mi_complete_matches = complete_matches, - mi_docs = docs, - mi_ext_fields = _ext_fields, -- Don't `put_` this in the instance so we + mi_hi_bytes_ = _hi_bytes, -- We don't serialise the 'mi_hi_bytes_', as it itself + -- may contain an in-memory byte array buffer for this + -- 'ModIface'. If we used 'put_' on this 'ModIface', then + -- we likely have a good reason, and do not want to reuse + -- the byte array. + -- See Note [Private fields in ModIface] + mi_deps_ = deps, + mi_usages_ = usages, + mi_exports_ = exports, + mi_used_th_ = used_th, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_anns_ = anns, + mi_decls_ = decls, + mi_extra_decls_ = extra_decls, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_hpc_ = hpc_info, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, + mi_complete_matches_ = complete_matches, + mi_docs_ = docs, + mi_ext_fields_ = _ext_fields, -- Don't `put_` this in the instance so we -- can deal with it's pointer in the header -- when we write the actual file - mi_final_exts = ModIfaceBackend { + mi_final_exts_ = ModIfaceBackend { mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, mi_flag_hash = flag_hash, @@ -455,34 +538,39 @@ instance Binary ModIface where trust_pkg <- get bh complete_matches <- get bh docs <- lazyGetMaybe bh - return (ModIface { - mi_module = mod, - mi_sig_of = sig_of, - mi_hsc_src = hsc_src, - mi_src_hash = fingerprint0, -- placeholder because this is dealt + return (PrivateModIface { + mi_module_ = mod, + mi_sig_of_ = sig_of, + mi_hsc_src_ = hsc_src, + mi_src_hash_ = fingerprint0, -- placeholder because this is dealt -- with specially when the file is read - mi_deps = deps, - mi_usages = usages, - mi_exports = exports, - mi_used_th = used_th, - mi_anns = anns, - mi_fixities = fixities, - mi_warns = warns, - mi_decls = decls, - mi_extra_decls = extra_decls, - mi_top_env = Nothing, - mi_insts = insts, - mi_fam_insts = fam_insts, - mi_rules = rules, - mi_hpc = hpc_info, - mi_trust = trust, - mi_trust_pkg = trust_pkg, + mi_hi_bytes_ = + -- We can't populate this field here, as we are + -- missing the 'mi_ext_fields_' field, which is + -- handled in 'getIfaceWithExtFields'. + FullIfaceBinHandle Strict.Nothing, + mi_deps_ = deps, + mi_usages_ = usages, + mi_exports_ = exports, + mi_used_th_ = used_th, + mi_anns_ = anns, + mi_fixities_ = fixities, + mi_warns_ = warns, + mi_decls_ = decls, + mi_extra_decls_ = extra_decls, + mi_top_env_ = Nothing, + mi_insts_ = insts, + mi_fam_insts_ = fam_insts, + mi_rules_ = rules, + mi_hpc_ = hpc_info, + mi_trust_ = trust, + mi_trust_pkg_ = trust_pkg, -- And build the cached values - mi_complete_matches = complete_matches, - mi_docs = docs, - mi_ext_fields = emptyExtensibleFields, -- placeholder because this is dealt + mi_complete_matches_ = complete_matches, + mi_docs_ = docs, + mi_ext_fields_ = emptyExtensibleFields, -- placeholder because this is dealt -- with specially when the file is read - mi_final_exts = ModIfaceBackend { + mi_final_exts_ = ModIfaceBackend { mi_iface_hash = iface_hash, mi_mod_hash = mod_hash, mi_flag_hash = flag_hash, @@ -499,42 +587,46 @@ instance Binary ModIface where mi_hash_fn = mkIfaceHashCache decls }}) + -- | The original names declared of a certain module that are exported type IfaceExport = AvailInfo emptyPartialModIface :: Module -> PartialModIface emptyPartialModIface mod - = ModIface { mi_module = mod, - mi_sig_of = Nothing, - mi_hsc_src = HsSrcFile, - mi_src_hash = fingerprint0, - mi_deps = noDependencies, - mi_usages = [], - mi_exports = [], - mi_used_th = False, - mi_fixities = [], - mi_warns = IfWarnSome [] [], - mi_anns = [], - mi_insts = [], - mi_fam_insts = [], - mi_rules = [], - mi_decls = [], - mi_extra_decls = Nothing, - mi_top_env = Nothing, - mi_hpc = False, - mi_trust = noIfaceTrustInfo, - mi_trust_pkg = False, - mi_complete_matches = [], - mi_docs = Nothing, - mi_final_exts = (), - mi_ext_fields = emptyExtensibleFields - } + = PrivateModIface + { mi_module_ = mod, + mi_sig_of_ = Nothing, + mi_hsc_src_ = HsSrcFile, + mi_src_hash_ = fingerprint0, + mi_hi_bytes_ = PartialIfaceBinHandle, + mi_deps_ = noDependencies, + mi_usages_ = [], + mi_exports_ = [], + mi_used_th_ = False, + mi_fixities_ = [], + mi_warns_ = IfWarnSome [] [], + mi_anns_ = [], + mi_insts_ = [], + mi_fam_insts_ = [], + mi_rules_ = [], + mi_decls_ = [], + mi_extra_decls_ = Nothing, + mi_top_env_ = Nothing, + mi_hpc_ = False, + mi_trust_ = noIfaceTrustInfo, + mi_trust_pkg_ = False, + mi_complete_matches_ = [], + mi_docs_ = Nothing, + mi_final_exts_ = (), + mi_ext_fields_ = emptyExtensibleFields + } emptyFullModIface :: Module -> ModIface emptyFullModIface mod = (emptyPartialModIface mod) - { mi_decls = [] - , mi_final_exts = ModIfaceBackend + { mi_decls_ = [] + , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + , mi_final_exts_ = ModIfaceBackend { mi_iface_hash = fingerprint0, mi_mod_hash = fingerprint0, mi_flag_hash = fingerprint0, @@ -569,36 +661,38 @@ emptyIfaceHashCache _occ = Nothing instance ( NFData (IfaceBackendExts (phase :: ModIfacePhase)) , NFData (IfaceDeclExts (phase :: ModIfacePhase)) ) => NFData (ModIface_ phase) where - rnf (ModIface{ mi_module, mi_sig_of, mi_hsc_src, mi_deps, mi_usages - , mi_exports, mi_used_th, mi_fixities, mi_warns, mi_anns - , mi_decls, mi_extra_decls, mi_top_env, mi_insts - , mi_fam_insts, mi_rules, mi_hpc, mi_trust, mi_trust_pkg - , mi_complete_matches, mi_docs, mi_final_exts - , mi_ext_fields, mi_src_hash }) - = rnf mi_module - `seq` rnf mi_sig_of - `seq` mi_hsc_src - `seq` mi_deps - `seq` mi_usages - `seq` mi_exports - `seq` rnf mi_used_th - `seq` mi_fixities - `seq` rnf mi_warns - `seq` rnf mi_anns - `seq` rnf mi_decls - `seq` rnf mi_extra_decls - `seq` rnf mi_top_env - `seq` rnf mi_insts - `seq` rnf mi_fam_insts - `seq` rnf mi_rules - `seq` rnf mi_hpc - `seq` mi_trust - `seq` rnf mi_trust_pkg - `seq` rnf mi_complete_matches - `seq` rnf mi_docs - `seq` mi_final_exts - `seq` mi_ext_fields - `seq` rnf mi_src_hash + rnf (PrivateModIface + { mi_module_, mi_sig_of_, mi_hsc_src_, mi_hi_bytes_, mi_deps_, mi_usages_ + , mi_exports_, mi_used_th_, mi_fixities_, mi_warns_, mi_anns_ + , mi_decls_, mi_extra_decls_, mi_top_env_, mi_insts_ + , mi_fam_insts_, mi_rules_, mi_hpc_, mi_trust_, mi_trust_pkg_ + , mi_complete_matches_, mi_docs_, mi_final_exts_ + , mi_ext_fields_, mi_src_hash_ }) + = rnf mi_module_ + `seq` rnf mi_sig_of_ + `seq` mi_hsc_src_ + `seq` mi_hi_bytes_ + `seq` mi_deps_ + `seq` mi_usages_ + `seq` mi_exports_ + `seq` rnf mi_used_th_ + `seq` mi_fixities_ + `seq` rnf mi_warns_ + `seq` rnf mi_anns_ + `seq` rnf mi_decls_ + `seq` rnf mi_extra_decls_ + `seq` rnf mi_top_env_ + `seq` rnf mi_insts_ + `seq` rnf mi_fam_insts_ + `seq` rnf mi_rules_ + `seq` rnf mi_hpc_ + `seq` mi_trust_ + `seq` rnf mi_trust_pkg_ + `seq` rnf mi_complete_matches_ + `seq` rnf mi_docs_ + `seq` mi_final_exts_ + `seq` mi_ext_fields_ + `seq` rnf mi_src_hash_ `seq` () instance NFData (ModIfaceBackend) where @@ -638,5 +732,286 @@ type WhetherHasOrphans = Bool -- | Does this module define family instances? type WhetherHasFamInst = Bool +-- ---------------------------------------------------------------------------- +-- Modify a 'ModIface'. +-- ---------------------------------------------------------------------------- + +{- +Note [Private fields in ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The fields of 'ModIface' are private, e.g., not exported, to make the API +impossible to misuse. A 'ModIface' can be "compressed" in-memory using +'shareIface', which serialises the 'ModIface' to an in-memory buffer. +This has the advantage of reducing memory usage of 'ModIface', reducing the +overall memory usage of GHC. +See Note [Sharing of ModIface]. + +This in-memory buffer can be reused, if and only if the 'ModIface' is not +modified after it has been "compressed"/shared via 'shareIface'. Instead of +serialising 'ModIface', we simply write the in-memory buffer to disk directly. + +However, we can't rely that a 'ModIface' isn't modified after 'shareIface' has +been called. Thus, we make all fields of 'ModIface' private and modification +only happens via exported update functions, such as 'set_mi_decls'. +These functions unconditionally clear any in-memory buffer if used, forcing us +to serialise the 'ModIface' to disk again. +-} + +-- | Given a 'PartialModIface', turn it into a 'ModIface' by completing +-- missing fields. +completePartialModIface :: PartialModIface + -> [(Fingerprint, IfaceDecl)] + -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] + -> ModIfaceBackend + -> ModIface +completePartialModIface partial decls extra_decls final_exts = partial + { mi_decls_ = decls + , mi_extra_decls_ = extra_decls + , mi_final_exts_ = final_exts + , mi_hi_bytes_ = FullIfaceBinHandle Strict.Nothing + } + +-- | Add a source fingerprint to a 'ModIface_' without invalidating the byte array +-- buffer 'mi_hi_bytes'. +-- This is a variant of 'set_mi_src_hash' which does invalidate the buffer. +-- +-- The 'mi_src_hash' is computed outside of 'ModIface_' based on the 'ModSummary'. +addSourceFingerprint :: Fingerprint -> ModIface_ phase -> ModIface_ phase +addSourceFingerprint val iface = iface { mi_src_hash_ = val } + +-- | Copy fields that aren't serialised to disk to the new 'ModIface_'. +-- This includes especially hashes that are usually stored in the interface +-- file header and 'mi_top_env'. +-- +-- We need this function after calling 'shareIface', to make sure the +-- 'ModIface_' doesn't lose any information. This function does not discard +-- the in-memory byte array buffer 'mi_hi_bytes'. +restoreFromOldModIface :: ModIface_ phase -> ModIface_ phase -> ModIface_ phase +restoreFromOldModIface old new = new + { mi_top_env_ = mi_top_env_ old + , mi_hsc_src_ = mi_hsc_src_ old + , mi_src_hash_ = mi_src_hash_ old + } + +set_mi_module :: Module -> ModIface_ phase -> ModIface_ phase +set_mi_module val iface = clear_mi_hi_bytes $ iface { mi_module_ = val } + +set_mi_sig_of :: Maybe Module -> ModIface_ phase -> ModIface_ phase +set_mi_sig_of val iface = clear_mi_hi_bytes $ iface { mi_sig_of_ = val } + +set_mi_hsc_src :: HscSource -> ModIface_ phase -> ModIface_ phase +set_mi_hsc_src val iface = clear_mi_hi_bytes $ iface { mi_hsc_src_ = val } + +set_mi_src_hash :: Fingerprint -> ModIface_ phase -> ModIface_ phase +set_mi_src_hash val iface = clear_mi_hi_bytes $ iface { mi_src_hash_ = val } + +set_mi_hi_bytes :: IfaceBinHandle phase -> ModIface_ phase -> ModIface_ phase +set_mi_hi_bytes val iface = iface { mi_hi_bytes_ = val } + +set_mi_deps :: Dependencies -> ModIface_ phase -> ModIface_ phase +set_mi_deps val iface = clear_mi_hi_bytes $ iface { mi_deps_ = val } + +set_mi_usages :: [Usage] -> ModIface_ phase -> ModIface_ phase +set_mi_usages val iface = clear_mi_hi_bytes $ iface { mi_usages_ = val } +set_mi_exports :: [IfaceExport] -> ModIface_ phase -> ModIface_ phase +set_mi_exports val iface = clear_mi_hi_bytes $ iface { mi_exports_ = val } + +set_mi_used_th :: Bool -> ModIface_ phase -> ModIface_ phase +set_mi_used_th val iface = clear_mi_hi_bytes $ iface { mi_used_th_ = val } + +set_mi_fixities :: [(OccName, Fixity)] -> ModIface_ phase -> ModIface_ phase +set_mi_fixities val iface = clear_mi_hi_bytes $ iface { mi_fixities_ = val } + +set_mi_warns :: IfaceWarnings -> ModIface_ phase -> ModIface_ phase +set_mi_warns val iface = clear_mi_hi_bytes $ iface { mi_warns_ = val } + +set_mi_anns :: [IfaceAnnotation] -> ModIface_ phase -> ModIface_ phase +set_mi_anns val iface = clear_mi_hi_bytes $ iface { mi_anns_ = val } + +set_mi_insts :: [IfaceClsInst] -> ModIface_ phase -> ModIface_ phase +set_mi_insts val iface = clear_mi_hi_bytes $ iface { mi_insts_ = val } + +set_mi_fam_insts :: [IfaceFamInst] -> ModIface_ phase -> ModIface_ phase +set_mi_fam_insts val iface = clear_mi_hi_bytes $ iface { mi_fam_insts_ = val } + +set_mi_rules :: [IfaceRule] -> ModIface_ phase -> ModIface_ phase +set_mi_rules val iface = clear_mi_hi_bytes $ iface { mi_rules_ = val } + +set_mi_decls :: [IfaceDeclExts phase] -> ModIface_ phase -> ModIface_ phase +set_mi_decls val iface = clear_mi_hi_bytes $ iface { mi_decls_ = val } + +set_mi_extra_decls :: Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> ModIface_ phase -> ModIface_ phase +set_mi_extra_decls val iface = clear_mi_hi_bytes $ iface { mi_extra_decls_ = val } + +set_mi_top_env :: Maybe IfaceTopEnv -> ModIface_ phase -> ModIface_ phase +set_mi_top_env val iface = clear_mi_hi_bytes $ iface { mi_top_env_ = val } + +set_mi_hpc :: AnyHpcUsage -> ModIface_ phase -> ModIface_ phase +set_mi_hpc val iface = clear_mi_hi_bytes $ iface { mi_hpc_ = val } + +set_mi_trust :: IfaceTrustInfo -> ModIface_ phase -> ModIface_ phase +set_mi_trust val iface = clear_mi_hi_bytes $ iface { mi_trust_ = val } + +set_mi_trust_pkg :: Bool -> ModIface_ phase -> ModIface_ phase +set_mi_trust_pkg val iface = clear_mi_hi_bytes $ iface { mi_trust_pkg_ = val } + +set_mi_complete_matches :: [IfaceCompleteMatch] -> ModIface_ phase -> ModIface_ phase +set_mi_complete_matches val iface = clear_mi_hi_bytes $ iface { mi_complete_matches_ = val } + +set_mi_docs :: Maybe Docs -> ModIface_ phase -> ModIface_ phase +set_mi_docs val iface = clear_mi_hi_bytes $ iface { mi_docs_ = val } + +set_mi_final_exts :: IfaceBackendExts phase -> ModIface_ phase -> ModIface_ phase +set_mi_final_exts val iface = clear_mi_hi_bytes $ iface { mi_final_exts_ = val } + +set_mi_ext_fields :: ExtensibleFields -> ModIface_ phase -> ModIface_ phase +set_mi_ext_fields val iface = clear_mi_hi_bytes $ iface { mi_ext_fields_ = val } + +-- | Invalidate any byte array buffer we might have. +clear_mi_hi_bytes :: ModIface_ phase -> ModIface_ phase +clear_mi_hi_bytes iface = iface + { mi_hi_bytes_ = case mi_hi_bytes iface of + PartialIfaceBinHandle -> PartialIfaceBinHandle + FullIfaceBinHandle _ -> FullIfaceBinHandle Strict.Nothing + } + +-- ---------------------------------------------------------------------------- +-- 'ModIface' pattern synonyms to keep breakage low. +-- ---------------------------------------------------------------------------- + +{- +Note [Inline Pattern synonym of ModIface] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The introduction of the 'ModIface' pattern synonym originally caused an increase +in allocated bytes in multiple performance tests. +In some benchmarks, it was a 2~3% increase. + +Without {-# INLINE ModIface #-}, the generated core reveals the reason for this increase. +We show the core for the 'mi_module' record selector: + +@ + mi_module + = \ @phase iface -> $w$mModIface iface mi_module1 + + $w$mModIface + = \ @phase iface cont -> + case iface of + { PrivateModIface a b ... z -> + cont + a + b + ... + z + } + + mi_module1 + = \ @phase + a + _ + ... + _ -> + a +@ + +Thus, we can see the '$w$mModIface' is not inlined, leading to an increase in +the allocated bytes. + +However, with the pragma, the correct core is generated: + +@ + mi_module = mi_module_ +@ + +-} +-- See Note [Inline Pattern synonym of ModIface] for why we have all these +-- inline pragmas. +{-# INLINE ModIface #-} +{-# INLINE mi_module #-} +{-# INLINE mi_sig_of #-} +{-# INLINE mi_hsc_src #-} +{-# INLINE mi_deps #-} +{-# INLINE mi_usages #-} +{-# INLINE mi_exports #-} +{-# INLINE mi_used_th #-} +{-# INLINE mi_fixities #-} +{-# INLINE mi_warns #-} +{-# INLINE mi_anns #-} +{-# INLINE mi_decls #-} +{-# INLINE mi_extra_decls #-} +{-# INLINE mi_top_env #-} +{-# INLINE mi_insts #-} +{-# INLINE mi_fam_insts #-} +{-# INLINE mi_rules #-} +{-# INLINE mi_hpc #-} +{-# INLINE mi_trust #-} +{-# INLINE mi_trust_pkg #-} +{-# INLINE mi_complete_matches #-} +{-# INLINE mi_docs #-} +{-# INLINE mi_final_exts #-} +{-# INLINE mi_ext_fields #-} +{-# INLINE mi_src_hash #-} +{-# INLINE mi_hi_bytes #-} + +pattern ModIface :: + Module -> Maybe Module -> HscSource -> Dependencies -> [Usage] -> + [IfaceExport] -> Bool -> [(OccName, Fixity)] -> IfaceWarnings -> + [IfaceAnnotation] -> [IfaceDeclExts phase] -> Maybe [IfaceBindingX IfaceMaybeRhs IfaceTopBndrInfo] -> + Maybe IfaceTopEnv -> [IfaceClsInst] -> [IfaceFamInst] -> [IfaceRule] -> + AnyHpcUsage -> IfaceTrustInfo -> Bool -> [IfaceCompleteMatch] -> Maybe Docs -> + IfaceBackendExts phase -> ExtensibleFields -> Fingerprint -> IfaceBinHandle phase -> + ModIface_ phase +pattern ModIface + { mi_module + , mi_sig_of + , mi_hsc_src + , mi_deps + , mi_usages + , mi_exports + , mi_used_th + , mi_fixities + , mi_warns + , mi_anns + , mi_decls + , mi_extra_decls + , mi_top_env + , mi_insts + , mi_fam_insts + , mi_rules + , mi_hpc + , mi_trust + , mi_trust_pkg + , mi_complete_matches + , mi_docs + , mi_final_exts + , mi_ext_fields + , mi_src_hash + , mi_hi_bytes + } <- PrivateModIface + { mi_module_ = mi_module + , mi_sig_of_ = mi_sig_of + , mi_hsc_src_ = mi_hsc_src + , mi_deps_ = mi_deps + , mi_usages_ = mi_usages + , mi_exports_ = mi_exports + , mi_used_th_ = mi_used_th + , mi_fixities_ = mi_fixities + , mi_warns_ = mi_warns + , mi_anns_ = mi_anns + , mi_decls_ = mi_decls + , mi_extra_decls_ = mi_extra_decls + , mi_top_env_ = mi_top_env + , mi_insts_ = mi_insts + , mi_fam_insts_ = mi_fam_insts + , mi_rules_ = mi_rules + , mi_hpc_ = mi_hpc + , mi_trust_ = mi_trust + , mi_trust_pkg_ = mi_trust_pkg + , mi_complete_matches_ = mi_complete_matches + , mi_docs_ = mi_docs + , mi_final_exts_ = mi_final_exts + , mi_ext_fields_ = mi_ext_fields + , mi_src_hash_ = mi_src_hash + , mi_hi_bytes_ = mi_hi_bytes + } ===================================== compiler/GHC/Utils/Binary.hs ===================================== @@ -19,7 +19,7 @@ -- http://www.cs.york.ac.uk/fp/nhc98/ module GHC.Utils.Binary - ( {-type-} Bin, + ( {-type-} Bin, RelBin(..), getRelBin, {-class-} Binary(..), {-type-} ReadBinHandle, WriteBinHandle, SymbolTable, Dictionary, @@ -32,10 +32,14 @@ module GHC.Utils.Binary seekBinWriter, seekBinReader, + seekBinReaderRel, tellBinReader, tellBinWriter, castBin, withBinBuffer, + freezeWriteHandle, + shrinkBinBuffer, + thawReadHandle, foldGet, foldGet', @@ -44,7 +48,9 @@ module GHC.Utils.Binary readBinMemN, putAt, getAt, + putAtRel, forwardPut, forwardPut_, forwardGet, + forwardPutRel, forwardPutRel_, forwardGetRel, -- * For writing instances putByte, @@ -99,6 +105,8 @@ module GHC.Utils.Binary BindingName(..), simpleBindingNameWriter, simpleBindingNameReader, + FullBinData(..), freezeBinHandle, thawBinHandle, putFullBinData, + BinArray, ) where import GHC.Prelude @@ -107,6 +115,7 @@ import Language.Haskell.Syntax.Module.Name (ModuleName(..)) import {-# SOURCE #-} GHC.Types.Name (Name) import GHC.Data.FastString +import GHC.Data.TrieMap import GHC.Utils.Panic.Plain import GHC.Types.Unique.FM import GHC.Data.FastMutInt @@ -115,7 +124,6 @@ import GHC.Types.SrcLoc import GHC.Types.Unique import qualified GHC.Data.Strict as Strict import GHC.Utils.Outputable( JoinPointHood(..) ) -import GHC.Utils.Misc ( HasCallStack, HasDebugCallStack ) import Control.DeepSeq import Control.Monad ( when, (<$!>), unless, forM_, void ) @@ -123,7 +131,7 @@ import Foreign hiding (shiftL, shiftR, void) import Data.Array import Data.Array.IO import Data.Array.Unsafe -import Data.ByteString (ByteString) +import Data.ByteString (ByteString, copy) import Data.Coerce import qualified Data.ByteString.Internal as BS import qualified Data.ByteString.Unsafe as BS @@ -152,8 +160,6 @@ import GHC.ForeignPtr ( unsafeWithForeignPtr ) import Unsafe.Coerce (unsafeCoerce) -import GHC.Data.TrieMap - type BinArray = ForeignPtr Word8 #if !MIN_VERSION_base(4,15,0) @@ -193,6 +199,62 @@ dataHandle (BinData size bin) = do handleData :: WriteBinHandle -> IO BinData handleData (WriteBinMem _ ixr _ binr) = BinData <$> readFastMutInt ixr <*> readIORef binr +--------------------------------------------------------------- +-- FullBinData +--------------------------------------------------------------- + +-- | 'FullBinData' stores a slice to a 'BinArray'. +-- +-- It requires less memory than 'ReadBinHandle', and can be constructed from +-- a 'ReadBinHandle' via 'freezeBinHandle' and turned back into a +-- 'ReadBinHandle' using 'thawBinHandle'. +-- Additionally, the byte array slice can be put into a 'WriteBinHandle' without extra +-- conversions via 'putFullBinData'. +data FullBinData = FullBinData + { fbd_readerUserData :: ReaderUserData + -- ^ 'ReaderUserData' that can be used to resume reading. + , fbd_off_s :: {-# UNPACK #-} !Int + -- ^ start offset + , fbd_off_e :: {-# UNPACK #-} !Int + -- ^ end offset + , fbd_size :: {-# UNPACK #-} !Int + -- ^ total buffer size + , fbd_buffer :: {-# UNPACK #-} !BinArray + } + +-- Equality and Ord assume that two distinct buffers are different, even if they compare the same things. +instance Eq FullBinData where + (FullBinData _ b c d e) == (FullBinData _ b1 c1 d1 e1) = b == b1 && c == c1 && d == d1 && e == e1 + +instance Ord FullBinData where + compare (FullBinData _ b c d e) (FullBinData _ b1 c1 d1 e1) = + compare b b1 `mappend` compare c c1 `mappend` compare d d1 `mappend` compare e e1 + +-- | Write the 'FullBinData' slice into the 'WriteBinHandle'. +putFullBinData :: WriteBinHandle -> FullBinData -> IO () +putFullBinData bh (FullBinData _ o1 o2 _sz ba) = do + let sz = o2 - o1 + putPrim bh sz $ \dest -> + unsafeWithForeignPtr (ba `plusForeignPtr` o1) $ \orig -> + copyBytes dest orig sz + +-- | Freeze a 'ReadBinHandle' and a start index into a 'FullBinData'. +-- +-- 'FullBinData' stores a slice starting from the 'Bin a' location to the current +-- offset of the 'ReadBinHandle'. +freezeBinHandle :: ReadBinHandle -> Bin a -> IO FullBinData +freezeBinHandle (ReadBinMem user_data ixr sz binr) (BinPtr start) = do + ix <- readFastMutInt ixr + pure (FullBinData user_data start ix sz binr) + +-- | Turn the 'FullBinData' into a 'ReadBinHandle', setting the 'ReadBinHandle' +-- offset to the start of the 'FullBinData' and restore the 'ReaderUserData' that was +-- obtained from 'freezeBinHandle'. +thawBinHandle :: FullBinData -> IO ReadBinHandle +thawBinHandle (FullBinData user_data ix _end sz ba) = do + ixr <- newFastMutInt ix + return $ ReadBinMem user_data ixr sz ba + --------------------------------------------------------------- -- BinHandle --------------------------------------------------------------- @@ -286,9 +348,47 @@ unsafeUnpackBinBuffer (BS.BS arr len) = do newtype Bin a = BinPtr Int deriving (Eq, Ord, Show, Bounded) +-- | Like a 'Bin' but is used to store relative offset pointers. +-- Relative offset pointers store a relative location, but also contain an +-- anchor that allow to obtain the absolute offset. +data RelBin a = RelBin + { relBin_anchor :: {-# UNPACK #-} !(Bin a) + -- ^ Absolute position from where we read 'relBin_offset'. + , relBin_offset :: {-# UNPACK #-} !(RelBinPtr a) + -- ^ Relative offset to 'relBin_anchor'. + -- The absolute position of the 'RelBin' is @relBin_anchor + relBin_offset@ + } + deriving (Eq, Ord, Show, Bounded) + +-- | A 'RelBinPtr' is like a 'Bin', but contains a relative offset pointer +-- instead of an absolute offset. +newtype RelBinPtr a = RelBinPtr (Bin a) + deriving (Eq, Ord, Show, Bounded) + castBin :: Bin a -> Bin b castBin (BinPtr i) = BinPtr i +-- | Read a relative offset location and wrap it in 'RelBin'. +-- +-- The resulting 'RelBin' can be translated into an absolute offset location using +-- 'makeAbsoluteBin' +getRelBin :: ReadBinHandle -> IO (RelBin a) +getRelBin bh = do + start <- tellBinReader bh + off <- get bh + pure $ RelBin start off + +makeAbsoluteBin :: RelBin a -> Bin a +makeAbsoluteBin (RelBin (BinPtr !start) (RelBinPtr (BinPtr !offset))) = + BinPtr $ start + offset + +makeRelativeBin :: RelBin a -> RelBinPtr a +makeRelativeBin (RelBin _ offset) = offset + +toRelBin :: Bin (RelBinPtr a) -> Bin a -> RelBin a +toRelBin (BinPtr !start) (BinPtr !goal) = + RelBin (BinPtr start) (RelBinPtr $ BinPtr $ goal - start) + --------------------------------------------------------------- -- class Binary --------------------------------------------------------------- @@ -309,6 +409,9 @@ class Binary a where putAt :: Binary a => WriteBinHandle -> Bin a -> a -> IO () putAt bh p x = do seekBinWriter bh p; put_ bh x; return () +putAtRel :: WriteBinHandle -> Bin (RelBinPtr a) -> Bin a -> IO () +putAtRel bh from to = putAt bh from (makeRelativeBin $ toRelBin from to) + getAt :: Binary a => ReadBinHandle -> Bin a -> IO a getAt bh p = do seekBinReader bh p; get bh @@ -327,6 +430,44 @@ openBinMem size , wbm_arr_r = arr_r } +-- | Freeze the given 'WriteBinHandle' and turn it into an equivalent 'ReadBinHandle'. +-- +-- The current offset of the 'WriteBinHandle' is maintained in the new 'ReadBinHandle'. +freezeWriteHandle :: WriteBinHandle -> IO ReadBinHandle +freezeWriteHandle wbm = do + rbm_off_r <- newFastMutInt =<< readFastMutInt (wbm_off_r wbm) + rbm_sz_r <- readFastMutInt (wbm_sz_r wbm) + rbm_arr_r <- readIORef (wbm_arr_r wbm) + pure $ ReadBinMem + { rbm_userData = noReaderUserData + , rbm_off_r = rbm_off_r + , rbm_sz_r = rbm_sz_r + , rbm_arr_r = rbm_arr_r + } + +-- | Copy the BinBuffer to a new BinBuffer which is exactly the right size. +-- This performs a copy of the underlying buffer. +-- The buffer may be truncated if the offset is not at the end of the written +-- output. +-- +-- UserData is also discarded during the copy +-- You should just use this when translating a Put handle into a Get handle. +shrinkBinBuffer :: WriteBinHandle -> IO ReadBinHandle +shrinkBinBuffer bh = withBinBuffer bh $ \bs -> do + unsafeUnpackBinBuffer (copy bs) + +thawReadHandle :: ReadBinHandle -> IO WriteBinHandle +thawReadHandle rbm = do + wbm_off_r <- newFastMutInt =<< readFastMutInt (rbm_off_r rbm) + wbm_sz_r <- newFastMutInt (rbm_sz_r rbm) + wbm_arr_r <- newIORef (rbm_arr_r rbm) + pure $ WriteBinMem + { wbm_userData = noWriterUserData + , wbm_off_r = wbm_off_r + , wbm_sz_r = wbm_sz_r + , wbm_arr_r = wbm_arr_r + } + tellBinWriter :: WriteBinHandle -> IO (Bin a) tellBinWriter (WriteBinMem _ r _ _) = do ix <- readFastMutInt r; return (BinPtr ix) @@ -358,6 +499,13 @@ seekBinReader (ReadBinMem _ ix_r sz_r _) (BinPtr !p) = do then panic "seekBinReader: seek out of range" else writeFastMutInt ix_r p +seekBinReaderRel :: ReadBinHandle -> RelBin a -> IO () +seekBinReaderRel (ReadBinMem _ ix_r sz_r _) relBin = do + let (BinPtr !p) = makeAbsoluteBin relBin + if (p > sz_r) + then panic "seekBinReaderRel: seek out of range" + else writeFastMutInt ix_r p + writeBinMem :: WriteBinHandle -> FilePath -> IO () writeBinMem (WriteBinMem _ ix_r _ arr_r) fn = do h <- openBinaryFile fn WriteMode @@ -1078,12 +1226,17 @@ instance Binary (Bin a) where put_ bh (BinPtr i) = putWord32 bh (fromIntegral i :: Word32) get bh = do i <- getWord32 bh; return (BinPtr (fromIntegral (i :: Word32))) +-- Instance uses fixed-width encoding to allow inserting +-- Bin placeholders in the stream. +instance Binary (RelBinPtr a) where + put_ bh (RelBinPtr i) = put_ bh i + get bh = RelBinPtr <$> get bh -- ----------------------------------------------------------------------------- -- Forward reading/writing --- | "forwardPut put_A put_B" outputs A after B but allows A to be read before B --- by using a forward reference +-- | @'forwardPut' put_A put_B@ outputs A after B but allows A to be read before B +-- by using a forward reference. forwardPut :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a,b) forwardPut bh put_A put_B = do -- write placeholder pointer to A @@ -1106,6 +1259,8 @@ forwardPut_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () forwardPut_ bh put_A put_B = void $ forwardPut bh put_A put_B -- | Read a value stored using a forward reference +-- +-- The forward reference is expected to be an absolute offset. forwardGet :: ReadBinHandle -> IO a -> IO a forwardGet bh get_A = do -- read forward reference @@ -1118,6 +1273,48 @@ forwardGet bh get_A = do seekBinReader bh p_a pure r +-- | @'forwardPutRel' put_A put_B@ outputs A after B but allows A to be read before B +-- by using a forward reference. +-- +-- This forward reference is a relative offset that allows us to skip over the +-- result of 'put_A'. +forwardPutRel :: WriteBinHandle -> (b -> IO a) -> IO b -> IO (a,b) +forwardPutRel bh put_A put_B = do + -- write placeholder pointer to A + pre_a <- tellBinWriter bh + put_ bh pre_a + + -- write B + r_b <- put_B + + -- update A's pointer + a <- tellBinWriter bh + putAtRel bh pre_a a + seekBinNoExpandWriter bh a + + -- write A + r_a <- put_A r_b + pure (r_a,r_b) + +-- | Like 'forwardGetRel', but discard the result. +forwardPutRel_ :: WriteBinHandle -> (b -> IO a) -> IO b -> IO () +forwardPutRel_ bh put_A put_B = void $ forwardPutRel bh put_A put_B + +-- | Read a value stored using a forward reference. +-- +-- The forward reference is expected to be a relative offset. +forwardGetRel :: ReadBinHandle -> IO a -> IO a +forwardGetRel bh get_A = do + -- read forward reference + p <- getRelBin bh + -- store current position + p_a <- tellBinReader bh + -- go read the forward value, then seek back + seekBinReader bh $ makeAbsoluteBin p + r <- get_A + seekBinReader bh p_a + pure r + -- ----------------------------------------------------------------------------- -- Lazy reading/writing @@ -1127,19 +1324,19 @@ lazyPut = lazyPut' put_ lazyGet :: Binary a => ReadBinHandle -> IO a lazyGet = lazyGet' get -lazyPut' :: HasDebugCallStack => (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO () +lazyPut' :: (WriteBinHandle -> a -> IO ()) -> WriteBinHandle -> a -> IO () lazyPut' f bh a = do -- output the obj with a ptr to skip over it: pre_a <- tellBinWriter bh put_ bh pre_a -- save a slot for the ptr f bh a -- dump the object q <- tellBinWriter bh -- q = ptr to after object - putAt bh pre_a q -- fill in slot before a with ptr to q + putAtRel bh pre_a q -- fill in slot before a with ptr to q seekBinWriter bh q -- finally carry on writing at q -lazyGet' :: HasDebugCallStack => (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a +lazyGet' :: (ReadBinHandle -> IO a) -> ReadBinHandle -> IO a lazyGet' f bh = do - p <- get bh -- a BinPtr + p <- getRelBin bh -- a BinPtr p_a <- tellBinReader bh a <- unsafeInterleaveIO $ do -- NB: Use a fresh rbm_off_r variable in the child thread, for thread @@ -1148,7 +1345,7 @@ lazyGet' f bh = do let bh' = bh { rbm_off_r = off_r } seekBinReader bh' p_a f bh' - seekBinReader bh p -- skip over the object for now + seekBinReader bh (makeAbsoluteBin p) -- skip over the object for now return a -- | Serialize the constructor strictly but lazily serialize a value inside a @@ -1284,7 +1481,7 @@ mkReader f = BinaryReader -- | Find the 'BinaryReader' for the 'Binary' instance for the type identified by 'Proxy a'. -- -- If no 'BinaryReader' has been configured before, this function will panic. -findUserDataReader :: forall a . (HasCallStack, Refl.Typeable a) => Proxy a -> ReadBinHandle -> BinaryReader a +findUserDataReader :: forall a . Refl.Typeable a => Proxy a -> ReadBinHandle -> BinaryReader a findUserDataReader query bh = case Map.lookup (Refl.someTypeRep query) (ud_reader_data $ getReaderUserData bh) of Nothing -> panic $ "Failed to find BinaryReader for the key: " ++ show (Refl.someTypeRep query) @@ -1306,7 +1503,7 @@ findUserDataReader query bh = -- | Find the 'BinaryWriter' for the 'Binary' instance for the type identified by 'Proxy a'. -- -- If no 'BinaryWriter' has been configured before, this function will panic. -findUserDataWriter :: forall a . (HasCallStack, Refl.Typeable a) => Proxy a -> WriteBinHandle -> BinaryWriter a +findUserDataWriter :: forall a . Refl.Typeable a => Proxy a -> WriteBinHandle -> BinaryWriter a findUserDataWriter query bh = case Map.lookup (Refl.someTypeRep query) (ud_writer_data $ getWriterUserData bh) of Nothing -> panic $ "Failed to find BinaryWriter for the key: " ++ show (Refl.someTypeRep query) @@ -1442,13 +1639,13 @@ putGenericSymbolTable gen_sym_tab serialiser bh = do mapM_ (\n -> serialiser bh n) (reverse todo) loop snd <$> - (forwardPut bh (const $ readFastMutInt symtab_next >>= put_ bh) $ + (forwardPutRel bh (const $ readFastMutInt symtab_next >>= put_ bh) $ loop) -- | Read the elements of a 'GenericSymbolTable' from disk into a 'SymbolTable'. getGenericSymbolTable :: forall a . (ReadBinHandle -> IO a) -> ReadBinHandle -> IO (SymbolTable a) getGenericSymbolTable deserialiser bh = do - sz <- forwardGet bh (get bh) :: IO Int + sz <- forwardGetRel bh (get bh) :: IO Int mut_arr <- newArray_ (0, sz-1) :: IO (IOArray Int a) forM_ [0..(sz-1)] $ \i -> do f <- deserialiser bh ===================================== testsuite/tests/plugins/simple-plugin/Simple/RemovePlugin.hs ===================================== @@ -64,9 +64,10 @@ metaPlugin' _ meta = pprPanic "meta" (showAstData BlankSrcSpan BlankEpAnnotation interfaceLoadPlugin' :: [CommandLineOption] -> ModIface -> IfM lcl ModIface interfaceLoadPlugin' [name, "interface"] iface - = return $ iface { mi_exports = filter (availNotNamedAs name) - (mi_exports iface) - } + = return $ set_mi_exports (filter (availNotNamedAs name) + (mi_exports iface)) + iface + interfaceLoadPlugin' _ iface = return iface availNotNamedAs :: String -> AvailInfo -> Bool ===================================== utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs ===================================== @@ -56,7 +56,7 @@ import GHC.Types.Unique.FM import GHC.Unit.State import GHC.Utils.Binary -import GHC.Iface.Type (IfaceType, getIfaceType, putIfaceType) +import GHC.Iface.Type (IfaceType, putIfaceType) import Haddock.Options (Visibility (..)) @@ -200,7 +200,7 @@ writeInterfaceFile filename iface = do -- write the iface type pointer at the front of the file ifacetype_p <- tellBinWriter bh - putAt bh ifacetype_p_p ifacetype_p + putAtRel bh ifacetype_p_p ifacetype_p seekBinWriter bh ifacetype_p -- write the symbol table itself @@ -208,7 +208,7 @@ writeInterfaceFile filename iface = do -- write the symtab pointer at the front of the file symtab_p <- tellBinWriter bh - putAt bh symtab_p_p symtab_p + putAtRel bh symtab_p_p symtab_p seekBinWriter bh symtab_p -- write the symbol table itself @@ -218,7 +218,7 @@ writeInterfaceFile filename iface = do -- write the dictionary pointer at the fornt of the file dict_p <- tellBinWriter bh - putAt bh dict_p_p dict_p + putAtRel bh dict_p_p dict_p seekBinWriter bh dict_p -- write the dictionary itself View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/13fdf78861b18678087b70abc4c435facbc28e35...1bab7dde7e3600f24476cbb2a5b43864ccde1faa -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/13fdf78861b18678087b70abc4c435facbc28e35...1bab7dde7e3600f24476cbb2a5b43864ccde1faa You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 22:50:47 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 18 Jun 2024 18:50:47 -0400 Subject: [Git][ghc/ghc][master] Improve documentation of @Any@ type. Message-ID: <66720f4729913_296a1b2b46da4142036@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - 3 changed files: - compiler/GHC/Builtin/Types.hs - libraries/ghc-internal/src/GHC/Internal/Unsafe/Coerce.hs - libraries/ghc-prim/GHC/Types.hs Changes: ===================================== compiler/GHC/Builtin/Types.hs ===================================== @@ -445,7 +445,15 @@ It has these properties: * When instantiated at a lifted type it is inhabited by at least one value, namely bottom - * You can safely coerce any /lifted/ type to Any, and back with unsafeCoerce. + * You can safely coerce any /lifted/ type to Any and back with unsafeCoerce. + You can safely coerce any /unlifted/ type to Any and back with unsafeCoerceUnlifted. + You can coerce /any/ type to Any and back with unsafeCoerce#, but it's only safe when + the kinds of both the type and Any match. + + For lifted/unlifted types unsafeCoerce[Unlifted] should be preferred over unsafeCoerce# + as they prevent accidentally coercing between types with kinds that don't match. + + See examples in ghc-prim:GHC.Types * It does not claim to be a *data* type, and that's important for the code generator, because the code gen may *enter* a data value ===================================== libraries/ghc-internal/src/GHC/Internal/Unsafe/Coerce.hs ===================================== @@ -336,6 +336,10 @@ unsafeCoerceAddr x = case unsafeEqualityProof @a @b of UnsafeRefl -> x -- to another. Misuse of this function can invite the garbage collector -- to trounce upon your data and then laugh in your face. You don't want -- this function. Really. +-- +-- This becomes more obvious when looking at its actual type: +-- @forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) (a :: TYPE r1) (b :: TYPE r2). a -> b@ +-- Which often get's rendered as @a -> b@ in haddock for technical reasons. unsafeCoerce# :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) (a :: TYPE r1) (b :: TYPE r2). a -> b ===================================== libraries/ghc-prim/GHC/Types.hs ===================================== @@ -283,11 +283,43 @@ data Symbol * * ********************************************************************* -} --- | The type constructor 'Any' is type to which you can unsafely coerce any --- lifted type, and back. More concretely, for a lifted type @t@ and --- value @x :: t@, @unsafeCoerce (unsafeCoerce x :: Any) :: t@ is equivalent --- to @x at . +-- | The type constructor @Any :: forall k. k@ is a type to which you can unsafely coerce any type, and back. -- +-- For @unsafeCoerce@ this means for all lifted types @t@ that +-- @unsafeCoerce (unsafeCoerce x :: Any) :: t@ is equivalent to @x@ and safe. +-- +-- The same is true for *all* types when using +-- @ +-- unsafeCoerce# :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) +-- (a :: TYPE r1) (b :: TYPE r2). +-- a -> b +-- @ +-- but /only/ if you instantiate @r1@ and @r2@ to the /same/ runtime representation. +-- For example using @(unsafeCoerce# :: forall (a :: TYPE IntRep) (b :: TYPE IntRep). a -> b) x@ +-- is fine, but @(unsafeCoerce# :: forall (a :: TYPE IntRep) (b :: TYPE FloatRep). a -> b)@ +-- will likely cause seg-faults or worse. +-- For this resason, users should always prefer unsafeCoerce over unsafeCoerce# when possible. +-- +-- Here are some more examples: +-- @ +-- bad_a1 :: Any @(TYPE 'IntRep) +-- bad_a1 = unsafeCoerce# True +-- +-- bad_a2 :: Any @(TYPE ('BoxedRep 'UnliftedRep)) +-- bad_a2 = unsafeCoerce# True +-- @ +-- Here @bad_a1@ is bad because we started with @True :: (Bool :: Type)@, represented by a boxed heap pointer, +-- and coerced it to @a1 :: Any @(TYPE 'IntRep)@, whose representation is a non-pointer integer. +-- That's why we had to use `unsafeCoerce#`; it is really unsafe because it can change representations. +-- Similarly @bad_a2@ is bad because although both @True@ and @bad_a2@ are represented by a heap pointer, +-- @True@ is lifted but @bad_a2@ is not; bugs here may be rather subtle. +-- +-- If you must use unsafeCoerce# to cast to `Any`, type annotations are recommended +-- to make sure that @Any@ has the correct kind. As casting between different runtimereps is +-- unsound. For example to cast a @ByteArray#@ to @Any@ you might use: +-- @ +-- unsafeCoerce# b :: (Any :: TYPE ('BoxedRep 'Unlifted)) +-- @ type family Any :: k where { } -- See Note [Any types] in GHC.Builtin.Types. Also, for a bit of history on Any see -- #10886. Note that this must be a *closed* type family: we need to ensure View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/099992df3b8028f5e324c5bda994e589507b11f7 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/099992df3b8028f5e324c5bda994e589507b11f7 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 22:51:22 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 18 Jun 2024 18:51:22 -0400 Subject: [Git][ghc/ghc][master] Update user guide to indicate support for 64-tuples Message-ID: <66720f6a1239b_296a1b288657414687d@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00 Update user guide to indicate support for 64-tuples - - - - - 1 changed file: - docs/users_guide/bugs.rst Changes: ===================================== docs/users_guide/bugs.rst ===================================== @@ -553,7 +553,7 @@ Unchecked floating-point arithmetic Large tuple support The Haskell Report only requires implementations to provide tuple types and their accompanying standard instances up to size 15. GHC - limits the size of tuple types to 62 and provides instances of + limits the size of tuple types to 64 and provides instances of ``Eq``, ``Ord``, ``Bounded``, ``Read``, ``Show``, and ``Ix`` for tuples up to size 15. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5e75412bb8061fae8837fa249d5bdc614ce2e461 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5e75412bb8061fae8837fa249d5bdc614ce2e461 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 22:52:03 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 18 Jun 2024 18:52:03 -0400 Subject: [Git][ghc/ghc][master] lint notes: Add more info to notes.stdout Message-ID: <66720f9365d49_296a1b2fa09cc1501b0@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 2 changed files: - linters/lint-notes/Main.hs - testsuite/tests/linters/notes.stdout Changes: ===================================== linters/lint-notes/Main.hs ===================================== @@ -37,7 +37,9 @@ main = do parseMode "unreferenced" = Just $ printNoteDefs . S.toList . unreferencedNotes parseMode "defs" = Just $ printNoteDefs . allNoteDefs parseMode "refs" = Just $ printNoteRefs . allNoteRefs - parseMode "broken-refs" = Just $ printNoteRefs . map fst . brokenNoteRefs + parseMode "broken-refs" = Just $ \notedb -> do + putStrLn "Broken note references (target note not found!):" + printNoteRefs . map fst . brokenNoteRefs $ notedb parseMode "broken-refs-suggest" = Just $ mapM_ printNoteRefsSugg . brokenNoteRefs parseMode _ = Nothing ===================================== testsuite/tests/linters/notes.stdout ===================================== @@ -1,39 +1,40 @@ +Broken note references (target note not found!): ref compiler/GHC/Core/Coercion/Axiom.hs:472:2: Note [RoughMap and rm_empty] ref compiler/GHC/Core/Opt/OccurAnal.hs:1157:7: Note [Loop breaking] -ref compiler/GHC/Core/Opt/SetLevels.hs:1586:30: Note [Top level scope] -ref compiler/GHC/Core/Opt/Simplify/Iteration.hs:2832:13: Note [Case binder next] -ref compiler/GHC/Core/Opt/Simplify/Iteration.hs:4023:8: Note [Lambda-bound unfoldings] -ref compiler/GHC/Core/Opt/Simplify/Utils.hs:1342:37: Note [Gentle mode] +ref compiler/GHC/Core/Opt/SetLevels.hs:1688:30: Note [Top level scope] +ref compiler/GHC/Core/Opt/Simplify/Iteration.hs:2937:13: Note [Case binder next] +ref compiler/GHC/Core/Opt/Simplify/Iteration.hs:4253:8: Note [Lambda-bound unfoldings] +ref compiler/GHC/Core/Opt/Simplify/Utils.hs:1406:37: Note [Gentle mode] ref compiler/GHC/Core/Opt/Specialise.hs:1763:29: Note [Arity decrease] -ref compiler/GHC/Core/TyCo/Rep.hs:1652:31: Note [What prevents a constraint from floating] -ref compiler/GHC/Driver/DynFlags.hs:1251:52: Note [Eta-reduction in -O0] -ref compiler/GHC/Driver/Main.hs:1749:34: Note [simpleTidyPgm - mkBootModDetailsTc] -ref compiler/GHC/Hs/Expr.hs:191:63: Note [Pending Splices] -ref compiler/GHC/Hs/Expr.hs:1727:87: Note [Lifecycle of a splice] -ref compiler/GHC/Hs/Expr.hs:1763:7: Note [Pending Splices] -ref compiler/GHC/Hs/Extension.hs:147:5: Note [Strict argument type constraints] -ref compiler/GHC/Hs/Pat.hs:141:74: Note [Lifecycle of a splice] +ref compiler/GHC/Core/TyCo/Rep.hs:1677:31: Note [What prevents a constraint from floating] +ref compiler/GHC/Driver/DynFlags.hs:1254:52: Note [Eta-reduction in -O0] +ref compiler/GHC/Driver/Main.hs:1750:34: Note [simpleTidyPgm - mkBootModDetailsTc] +ref compiler/GHC/Hs/Expr.hs:192:63: Note [Pending Splices] +ref compiler/GHC/Hs/Expr.hs:1955:87: Note [Lifecycle of a splice] +ref compiler/GHC/Hs/Expr.hs:1991:7: Note [Pending Splices] +ref compiler/GHC/Hs/Extension.hs:144:5: Note [Strict argument type constraints] +ref compiler/GHC/Hs/Pat.hs:146:74: Note [Lifecycle of a splice] ref compiler/GHC/HsToCore/Pmc/Solver.hs:856:20: Note [COMPLETE sets on data families] -ref compiler/GHC/HsToCore/Quote.hs:1487:7: Note [How brackets and nested splices are handled] -ref compiler/GHC/Stg/Unarise.hs:438:32: Note [Renaming during unarisation] -ref compiler/GHC/Tc/Gen/HsType.hs:556:56: Note [Skolem escape prevention] -ref compiler/GHC/Tc/Gen/HsType.hs:2676:7: Note [Matching a kind signature with a declaration] -ref compiler/GHC/Tc/Gen/Pat.hs:174:20: Note [Typing patterns in pattern bindings] -ref compiler/GHC/Tc/Gen/Pat.hs:1163:7: Note [Matching polytyped patterns] -ref compiler/GHC/Tc/Gen/Sig.hs:80:10: Note [Overview of type signatures] +ref compiler/GHC/HsToCore/Quote.hs:1505:7: Note [How brackets and nested splices are handled] +ref compiler/GHC/Stg/Unarise.hs:451:32: Note [Renaming during unarisation] +ref compiler/GHC/Tc/Gen/HsType.hs:561:56: Note [Skolem escape prevention] +ref compiler/GHC/Tc/Gen/HsType.hs:2707:7: Note [Matching a kind signature with a declaration] +ref compiler/GHC/Tc/Gen/Pat.hs:286:20: Note [Typing patterns in pattern bindings] +ref compiler/GHC/Tc/Gen/Pat.hs:1385:7: Note [Matching polytyped patterns] +ref compiler/GHC/Tc/Gen/Sig.hs:77:10: Note [Overview of type signatures] ref compiler/GHC/Tc/Gen/Splice.hs:358:16: Note [How brackets and nested splices are handled] ref compiler/GHC/Tc/Gen/Splice.hs:533:35: Note [PendingRnSplice] -ref compiler/GHC/Tc/Gen/Splice.hs:657:7: Note [How brackets and nested splices are handled] -ref compiler/GHC/Tc/Gen/Splice.hs:891:11: Note [How brackets and nested splices are handled] +ref compiler/GHC/Tc/Gen/Splice.hs:660:7: Note [How brackets and nested splices are handled] +ref compiler/GHC/Tc/Gen/Splice.hs:904:11: Note [How brackets and nested splices are handled] ref compiler/GHC/Tc/Instance/Family.hs:406:35: Note [Constrained family instances] -ref compiler/GHC/Tc/Solver/Rewrite.hs:1010:7: Note [Stability of rewriting] +ref compiler/GHC/Tc/Solver/Rewrite.hs:1006:7: Note [Stability of rewriting] ref compiler/GHC/Tc/TyCl.hs:1316:6: Note [Unification variables need fresh Names] ref compiler/GHC/Tc/Types/Constraint.hs:206:38: Note [NonCanonical Semantics] -ref compiler/GHC/Types/Demand.hs:301:25: Note [Preserving Boxity of results is rarely a win] +ref compiler/GHC/Types/Demand.hs:303:25: Note [Preserving Boxity of results is rarely a win] ref compiler/GHC/Unit/Module/Deps.hs:83:13: Note [Structure of dep_boot_mods] ref compiler/GHC/Utils/Monad.hs:410:34: Note [multiShotIO] -ref compiler/Language/Haskell/Syntax/Binds.hs:200:31: Note [fun_id in Match] -ref configure.ac:203:10: Note [Linking ghc-bin against threaded stage0 RTS] +ref compiler/Language/Haskell/Syntax/Binds.hs:220:31: Note [fun_id in Match] +ref configure.ac:191:10: Note [Linking ghc-bin against threaded stage0 RTS] ref docs/core-spec/core-spec.mng:177:6: Note [TyBinders] ref hadrian/src/Expression.hs:145:30: Note [Linking ghc-bin against threaded stage0 RTS] ref linters/lint-notes/Notes.hs:32:29: Note [" <> T.unpack x <> "] @@ -51,18 +52,18 @@ ref testsuite/tests/typecheck/should_compile/tc228.hs:9:7: Note [Inferenc ref testsuite/tests/typecheck/should_compile/tc231.hs:12:16: Note [Important subtlety in oclose] ref testsuite/tests/typecheck/should_fail/UnliftedNewtypesMultiFieldGadt.hs:11:28: Note [Kind-checking the field type] ref testsuite/tests/typecheck/should_fail/tcfail093.hs:13:7: Note [Important subtlety in oclose] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Eta reduction for data family axioms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Convert.hs:: Note [Invariant: Never expand type synonyms] -ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:: Note [Exporting built-in items] -ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:: Note [Exporting built-in items] -ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:: Note [Exporting built-in items] -ref utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs:: Note [The DocModule story] -ref utils/haddock/haddock-api/src/Haddock/Types.hs:: Note [Pass sensitive types] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1068:13: Note [Eta reduction for data family axioms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1085:0: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1101:7: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1108:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1117:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1131:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1145:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1147:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Convert.hs:1156:9: Note [Invariant: Never expand type synonyms] +ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:120:11: Note [Exporting built-in items] +ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:185:9: Note [Exporting built-in items] +ref utils/haddock/haddock-api/src/Haddock/Interface/Create.hs:255:7: Note [Exporting built-in items] +ref utils/haddock/haddock-api/src/Haddock/InterfaceFile.hs:118:3: Note [The DocModule story] +ref utils/haddock/haddock-api/src/Haddock/Types.hs:17:3: Note [Pass sensitive types] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4f5da5953830e99ea0e8fcd2294f0c379faa028d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/4f5da5953830e99ea0e8fcd2294f0c379faa028d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 22:52:40 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 18 Jun 2024 18:52:40 -0400 Subject: [Git][ghc/ghc][master] docs: Update mention of ($) type in user guide Message-ID: <66720fb8cca9d_296a1b3170a1815556a@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 1 changed file: - docs/users_guide/exts/representation_polymorphism.rst Changes: ===================================== docs/users_guide/exts/representation_polymorphism.rst ===================================== @@ -79,14 +79,26 @@ representation-polymorphic type. However, not all is lost. We can still do this: :: - ($) :: forall r (a :: Type) (b :: TYPE r). + good :: forall r (a :: Type) (b :: TYPE r). (a -> b) -> a -> b - f $ x = f x + good f x = f x Here, only ``b`` is representation-polymorphic. There are no variables with a representation-polymorphic type. And the code generator has no -trouble with this. Indeed, this is the true type of GHC's ``$`` operator, -slightly more general than the Haskell 98 version. +trouble with this. Nonetheless, there is a way to write a definition with +``bad``'s type: :: + + + ($) :: forall (r1 :: RuntimeRep) (r2 :: RuntimeRep) + (a :: TYPE r1) (b :: TYPE r2). + (a -> b) -> a -> b + ($) f = f + +By eta-reducing, we got rid of ``x``, and thus have no variable with a +representation-polymorphic type. Indeed, this is the true type of GHC's ``$`` +operator, slightly more general than the Haskell 98 version. However, its +strictness properties are different: ``(good undefined) `seq` ()`` is equivalent +to ``()``, whereas ``(($) undefined) `seq` ()`` diverges. Because the code generator must store and move arguments as well as variables, the logic above applies equally well to function arguments, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1eb15c61652ac70829b2130526e729e8177bbeb5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1eb15c61652ac70829b2130526e729e8177bbeb5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 22:53:22 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 18 Jun 2024 18:53:22 -0400 Subject: [Git][ghc/ghc][master] Remove duplicate Anno instances Message-ID: <66720fe21b9ed_296a1b2dada981601fb@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00 Remove duplicate Anno instances - - - - - 3 changed files: - compiler/GHC/Hs.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs Changes: ===================================== compiler/GHC/Hs.hs ===================================== @@ -94,8 +94,6 @@ type instance XCModule GhcRn = DataConCantHappen type instance XCModule GhcTc = DataConCantHappen type instance XXModule p = DataConCantHappen -type instance Anno ModuleName = SrcSpanAnnA - deriving instance Data (HsModule GhcPs) data AnnsModule ===================================== compiler/GHC/Hs/Decls.hs ===================================== @@ -810,8 +810,6 @@ ppr_con_names = pprWithCommas (pprPrefixOcc . unLoc) type instance XCFamEqn (GhcPass _) r = [AddEpAnn] type instance XXFamEqn (GhcPass _) r = DataConCantHappen -type instance Anno (FamEqn (GhcPass p) _) = SrcSpanAnnA - ----------------- Class instances ------------- type instance XCClsInstDecl GhcPs = ( Maybe (LWarningTxt GhcPs) @@ -1025,8 +1023,6 @@ derivDeprecation = fmap unLoc . decl_deprecation (ghcPass @p) = depr decl_deprecation _ _ = Nothing -type instance Anno OverlapMode = SrcSpanAnnP - instance OutputableBndrId p => Outputable (DerivDecl (GhcPass p)) where ppr (deriv at DerivDecl { deriv_type = ty @@ -1342,8 +1338,6 @@ type instance XCRoleAnnotDecl GhcTc = NoExtField type instance XXRoleAnnotDecl (GhcPass _) = DataConCantHappen -type instance Anno (Maybe Role) = EpAnnCO - instance OutputableBndr (IdP (GhcPass p)) => Outputable (RoleAnnotDecl (GhcPass p)) where ppr (RoleAnnotDecl _ ltycon roles) ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -1279,9 +1279,6 @@ type instance XXCmd GhcPs = DataConCantHappen type instance XXCmd GhcRn = DataConCantHappen type instance XXCmd GhcTc = HsWrap HsCmd -type instance Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] - = SrcSpanAnnL - -- If cmd :: arg1 --> res -- wrap :: arg1 "->" arg2 -- Then (XCmd (HsWrap wrap cmd)) :: arg2 --> res View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1d66c9e3dd3bd92da97be7ebc7bb06eb3d406289 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1d66c9e3dd3bd92da97be7ebc7bb06eb3d406289 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 22:54:03 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 18 Jun 2024 18:54:03 -0400 Subject: [Git][ghc/ghc][master] AArch64: Delete unused RegNos Message-ID: <6672100b43dfd_296a1b350b04c1633fc@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00 AArch64: Delete unused RegNos This has the additional benefit of getting rid of the -1 encoding (real registers start at 0.) - - - - - 1 changed file: - compiler/GHC/CmmToAsm/AArch64/Instr.hs Changes: ===================================== compiler/GHC/CmmToAsm/AArch64/Instr.hs ===================================== @@ -171,7 +171,6 @@ regUsageOfInstr platform instr = case instr of -- Is this register interesting for the register allocator? interesting :: Platform -> Reg -> Bool interesting _ (RegVirtual _) = True - interesting _ (RegReal (RealRegSingle (-1))) = False interesting platform (RegReal (RealRegSingle i)) = freeReg platform i -- Save caller save registers @@ -758,15 +757,10 @@ data Operand opReg :: Width -> Reg -> Operand opReg = OpReg -xzr, wzr, sp, ip0 :: Operand -xzr = OpReg W64 (RegReal (RealRegSingle (-1))) -wzr = OpReg W32 (RegReal (RealRegSingle (-1))) +sp, ip0 :: Operand sp = OpReg W64 (RegReal (RealRegSingle 31)) ip0 = OpReg W64 (RegReal (RealRegSingle 16)) -reg_zero :: Reg -reg_zero = RegReal (RealRegSingle (-1)) - _x :: Int -> Operand _x i = OpReg W64 (RegReal (RealRegSingle i)) x0, x1, x2, x3, x4, x5, x6, x7 :: Operand View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8ea0ba95e9b3a092429f8999ac44dc60e46fcdca -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8ea0ba95e9b3a092429f8999ac44dc60e46fcdca You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 22:54:41 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 18 Jun 2024 18:54:41 -0400 Subject: [Git][ghc/ghc][master] Bump stm submodule to current master Message-ID: <667210312fd6e_296a1b36b83a4166443@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00 Bump stm submodule to current master - - - - - 1 changed file: - libraries/stm Changes: ===================================== libraries/stm ===================================== @@ -1 +1 @@ -Subproject commit 4e7aa7885b3f9724b19e68d12cbd2774b11b9bd0 +Subproject commit 8de008f1928e029e54b822d85a16f1804d7e99a6 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/325422e02fdf8ba004545e89571d6edf3a3aa12c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/325422e02fdf8ba004545e89571d6edf3a3aa12c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 22:55:00 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 18 Jun 2024 18:55:00 -0400 Subject: [Git][ghc/ghc][master] testsuite: bump T17572 timeout on wasm32 Message-ID: <6672104418e80_296a1b37584e4166642@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00 testsuite: bump T17572 timeout on wasm32 - - - - - 1 changed file: - testsuite/tests/profiling/should_run/all.T Changes: ===================================== testsuite/tests/profiling/should_run/all.T ===================================== @@ -186,7 +186,7 @@ test('T15897', fragile(15467)], makefile_test, ['T15897']) -test('T17572', [], compile_and_run, ['']) +test('T17572', [when(arch('wasm32'), run_timeout_multiplier(5))], compile_and_run, ['']) test('TraverseHeapTest', [only_ways(['prof'])], compile_and_run, ['-debug']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/64fba310c2d23a41c88514aed0a482fbe5a3b184 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/64fba310c2d23a41c88514aed0a482fbe5a3b184 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Tue Jun 18 23:25:20 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Tue, 18 Jun 2024 19:25:20 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 14 commits: Clarify -XGADTs enables existential quantification Message-ID: <66721760c77c7_bf78e2a8ac85935@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: d70abb49 by sheaf at 2024-06-18T18:47:20-04:00 Clarify -XGADTs enables existential quantification Even though -XGADTs does not turn on -XExistentialQuantification, it does allow the user of existential quantification syntax, without needing to use GADT-style syntax. Fixes #20865 - - - - - 13fdf788 by David Binder at 2024-06-18T18:48:02-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 1bab7dde by Fendor at 2024-06-18T18:48:38-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18698b T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The tests T16875 and T18698b fail on i386-linux for the same reason. - - - - - 099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - 5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00 Update user guide to indicate support for 64-tuples - - - - - 4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00 Remove duplicate Anno instances - - - - - 8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00 AArch64: Delete unused RegNos This has the additional benefit of getting rid of the -1 encoding (real registers start at 0.) - - - - - 325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00 Bump stm submodule to current master - - - - - 64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00 testsuite: bump T17572 timeout on wasm32 - - - - - ca8ea694 by Sven Tennie at 2024-06-18T19:24:54-04:00 AArch64: Simplify BL instruction The BL constructor carried unused data in its third argument. - - - - - 8efafc06 by Alan Zimmerman at 2024-06-18T19:24:55-04:00 TTG: Move SourceText from `Fixity` to `FixitySig` It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Precedes !12842, to simplify it - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/Hs.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Hole.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Utils/Backpack.hs - compiler/GHC/ThToHs.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7a0f02bc7a2884986dd6cb5231255f94348addf7...8efafc068066e1dbbd95b6443bd08e0543f0c77b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7a0f02bc7a2884986dd6cb5231255f94348addf7...8efafc068066e1dbbd95b6443bd08e0543f0c77b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 07:36:13 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 19 Jun 2024 03:36:13 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 3 commits: AArch64: Simplify BL instruction Message-ID: <66728a6de157f_2c0b1c28b8f9c8219@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 04a5170f by Sven Tennie at 2024-06-19T03:35:51-04:00 AArch64: Simplify BL instruction The BL constructor carried unused data in its third argument. - - - - - cae6052d by Alan Zimmerman at 2024-06-19T03:35:52-04:00 TTG: Move SourceText from `Fixity` to `FixitySig` It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Precedes !12842, to simplify it - - - - - 72bacf3f by Rodrigo Mesquita at 2024-06-19T03:35:53-04:00 base: Deprecate some .Internal modules Deprecates the following modules according to clc-proposal #217: https://github.com/haskell/core-libraries-committee/issues/217 * GHC.TypeNats.Internal * GHC.TypeLits.Internal * GHC.ExecutionStack.Internal Closes #24998 - - - - - 30 changed files: - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Fixity.hs - libraries/base/src/GHC/ExecutionStack/Internal.hs - libraries/base/src/GHC/TypeLits/Internal.hs - libraries/base/src/GHC/TypeNats/Internal.hs - testsuite/tests/parser/should_compile/T20846.stderr - utils/check-exact/ExactPrint.hs - utils/genprimopcode/Main.hs - utils/genprimopcode/Parser.y - utils/genprimopcode/Syntax.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Json.hs - utils/haddock/haddock-api/src/Haddock/Types.hs Changes: ===================================== compiler/GHC/Builtin/PrimOps.hs ===================================== @@ -49,7 +49,6 @@ import GHC.Types.Basic import GHC.Types.Fixity ( Fixity(..), FixityDirection(..) ) import GHC.Types.SrcLoc ( wiredInSrcSpan ) import GHC.Types.ForeignCall ( CLabelString ) -import GHC.Types.SourceText ( SourceText(..) ) import GHC.Types.Unique ( Unique ) import GHC.Unit.Types ( Unit ) ===================================== compiler/GHC/CmmToAsm/AArch64/CodeGen.hs ===================================== @@ -1596,7 +1596,7 @@ genCCall target dest_regs arg_regs bid = do then 8 * (stackSpace' `div` 8 + 1) else stackSpace' - (returnRegs, readResultsCode) <- readResults allGpArgRegs allFpArgRegs dest_regs [] nilOL + readResultsCode <- readResults allGpArgRegs allFpArgRegs dest_regs [] nilOL let moveStackDown 0 = toOL [ PUSH_STACK_FRAME , DELTA (-16) ] @@ -1614,7 +1614,7 @@ genCCall target dest_regs arg_regs bid = do let code = call_target_code -- compute the label (possibly into a register) `appOL` moveStackDown (stackSpace `div` 8) `appOL` passArgumentsCode -- put the arguments into x0, ... - `appOL` (unitOL $ BL call_target passRegs returnRegs) -- branch and link. + `appOL` (unitOL $ BL call_target passRegs) -- branch and link. `appOL` readResultsCode -- parse the results into registers `appOL` moveStackUp (stackSpace `div` 8) return (code, Nothing) @@ -2203,8 +2203,8 @@ genCCall target dest_regs arg_regs bid = do passArguments _ _ _ _ _ _ _ = pprPanic "passArguments" (text "invalid state") - readResults :: [Reg] -> [Reg] -> [LocalReg] -> [Reg]-> InstrBlock -> NatM ([Reg], InstrBlock) - readResults _ _ [] accumRegs accumCode = return (accumRegs, accumCode) + readResults :: [Reg] -> [Reg] -> [LocalReg] -> [Reg]-> InstrBlock -> NatM (InstrBlock) + readResults _ _ [] _ accumCode = return accumCode readResults [] _ _ _ _ = do platform <- getPlatform pprPanic "genCCall, out of gp registers when reading results" (pdoc platform target) ===================================== compiler/GHC/CmmToAsm/AArch64/Instr.hs ===================================== @@ -117,7 +117,7 @@ regUsageOfInstr platform instr = case instr of J t -> usage (regTarget t, []) B t -> usage (regTarget t, []) BCOND _ t -> usage (regTarget t, []) - BL t ps _rs -> usage (regTarget t ++ ps, callerSavedRegisters) + BL t ps -> usage (regTarget t ++ ps, callerSavedRegisters) -- 5. Atomic Instructions ---------------------------------------------------- -- 6. Conditional Instructions ----------------------------------------------- @@ -254,7 +254,7 @@ patchRegsOfInstr instr env = case instr of -- 4. Branch Instructions -------------------------------------------------- J t -> J (patchTarget t) B t -> B (patchTarget t) - BL t rs ts -> BL (patchTarget t) rs ts + BL t rs -> BL (patchTarget t) rs BCOND c t -> BCOND c (patchTarget t) -- 5. Atomic Instructions -------------------------------------------------- @@ -320,7 +320,7 @@ jumpDestsOfInstr (CBZ _ t) = [ id | TBlock id <- [t]] jumpDestsOfInstr (CBNZ _ t) = [ id | TBlock id <- [t]] jumpDestsOfInstr (J t) = [id | TBlock id <- [t]] jumpDestsOfInstr (B t) = [id | TBlock id <- [t]] -jumpDestsOfInstr (BL t _ _) = [ id | TBlock id <- [t]] +jumpDestsOfInstr (BL t _) = [ id | TBlock id <- [t]] jumpDestsOfInstr (BCOND _ t) = [ id | TBlock id <- [t]] jumpDestsOfInstr _ = [] @@ -341,7 +341,7 @@ patchJumpInstr instr patchF CBNZ r (TBlock bid) -> CBNZ r (TBlock (patchF bid)) J (TBlock bid) -> J (TBlock (patchF bid)) B (TBlock bid) -> B (TBlock (patchF bid)) - BL (TBlock bid) ps rs -> BL (TBlock (patchF bid)) ps rs + BL (TBlock bid) ps -> BL (TBlock (patchF bid)) ps BCOND c (TBlock bid) -> BCOND c (TBlock (patchF bid)) _ -> panic $ "patchJumpInstr: " ++ instrCon instr @@ -626,7 +626,7 @@ data Instr -- Branching. | J Target -- like B, but only generated from genJump. Used to distinguish genJumps from others. | B Target -- unconditional branching b/br. (To a blockid, label or register) - | BL Target [Reg] [Reg] -- branch and link (e.g. set x30 to next pc, and branch) + | BL Target [Reg] -- branch and link (e.g. set x30 to next pc, and branch) | BCOND Cond Target -- branch with condition. b. -- 8. Synchronization Instructions ----------------------------------------- ===================================== compiler/GHC/CmmToAsm/AArch64/Ppr.hs ===================================== @@ -426,9 +426,9 @@ pprInstr platform instr = case instr of B (TLabel lbl) -> line $ text "\tb" <+> pprAsmLabel platform lbl B (TReg r) -> line $ text "\tbr" <+> pprReg W64 r - BL (TBlock bid) _ _ -> line $ text "\tbl" <+> pprAsmLabel platform (mkLocalBlockLabel (getUnique bid)) - BL (TLabel lbl) _ _ -> line $ text "\tbl" <+> pprAsmLabel platform lbl - BL (TReg r) _ _ -> line $ text "\tblr" <+> pprReg W64 r + BL (TBlock bid) _ -> line $ text "\tbl" <+> pprAsmLabel platform (mkLocalBlockLabel (getUnique bid)) + BL (TLabel lbl) _ -> line $ text "\tbl" <+> pprAsmLabel platform lbl + BL (TReg r) _ -> line $ text "\tblr" <+> pprReg W64 r BCOND c (TBlock bid) -> line $ text "\t" <> pprBcond c <+> pprAsmLabel platform (mkLocalBlockLabel (getUnique bid)) BCOND c (TLabel lbl) -> line $ text "\t" <> pprBcond c <+> pprAsmLabel platform lbl ===================================== compiler/GHC/Hs/Binds.hs ===================================== @@ -708,7 +708,7 @@ instance OutputableBndrId p => Outputable (IPBind (GhcPass p)) where type instance XTypeSig (GhcPass p) = AnnSig type instance XPatSynSig (GhcPass p) = AnnSig type instance XClassOpSig (GhcPass p) = AnnSig -type instance XFixSig (GhcPass p) = [AddEpAnn] +type instance XFixSig (GhcPass p) = ([AddEpAnn], SourceText) type instance XInlineSig (GhcPass p) = [AddEpAnn] type instance XSpecSig (GhcPass p) = [AddEpAnn] type instance XSpecInstSig (GhcPass p) = ([AddEpAnn], SourceText) ===================================== compiler/GHC/Hs/Dump.hs ===================================== @@ -74,7 +74,6 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0 `extQ` name `extQ` occName `extQ` moduleName `extQ` var `extQ` dataCon `extQ` bagName `extQ` bagRdrName `extQ` bagVar `extQ` nameSet - `extQ` fixity `ext2Q` located `extQ` srcSpanAnnA `extQ` srcSpanAnnL @@ -139,11 +138,12 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0 , generic s ] sourceText :: SourceText -> SDoc - sourceText NoSourceText = parens $ text "NoSourceText" + sourceText NoSourceText = case bs of + BlankSrcSpan -> parens $ text "SourceText" <+> text "blanked" + _ -> parens $ text "NoSourceText" sourceText (SourceText src) = case bs of - NoBlankSrcSpan -> parens $ text "SourceText" <+> ftext src - BlankSrcSpanFile -> parens $ text "SourceText" <+> ftext src - _ -> parens $ text "SourceText" <+> text "blanked" + BlankSrcSpan -> parens $ text "SourceText" <+> text "blanked" + _ -> parens $ text "SourceText" <+> ftext src epaAnchor :: EpaLocation -> SDoc epaAnchor (EpaSpan s) = parens $ text "EpaSpan" <+> srcSpan s @@ -216,11 +216,6 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0 text "NameSet:" $$ (list . nameSetElemsStable $ ns) - fixity :: Fixity -> SDoc - fixity fx = braces $ - text "Fixity:" - <+> ppr fx - located :: (Data a, Data b) => GenLocated a b -> SDoc located (L ss a) = parens (text "L" ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -780,7 +780,7 @@ repLFixD :: LFixitySig GhcRn -> MetaM [(SrcSpan, Core (M TH.Dec))] repLFixD (L loc fix_sig) = rep_fix_d (locA loc) fix_sig rep_fix_d :: SrcSpan -> FixitySig GhcRn -> MetaM [(SrcSpan, Core (M TH.Dec))] -rep_fix_d loc (FixitySig ns_spec names (Fixity _ prec dir)) +rep_fix_d loc (FixitySig ns_spec names (Fixity prec dir)) = do { MkC prec' <- coreIntLit prec ; let rep_fn = case dir of InfixL -> infixLWithSpecDName ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -90,7 +90,6 @@ import GHC.Types.Avail import GHC.Types.Fixity import GHC.Types.Fixity.Env import GHC.Types.SourceError -import GHC.Types.SourceText import GHC.Types.SourceFile import GHC.Types.SafeHaskell import GHC.Types.TypeEnv @@ -1029,7 +1028,7 @@ ghcPrimIface -- The fixity listed here for @`seq`@ should match -- those in primops.txt.pp (from which Haddock docs are generated). - fixities = (getOccName seqId, Fixity NoSourceText 0 InfixR) + fixities = (getOccName seqId, Fixity 0 InfixR) : mapMaybe mkFixity allThePrimOps mkFixity op = (,) (primOpOcc op) <$> primOpFixity op @@ -1235,5 +1234,3 @@ instance Outputable WhereFrom where ppr (ImportByUser NotBoot) = empty ppr ImportBySystem = text "{- SYSTEM -}" ppr ImportByPlugin = text "{- PLUGIN -}" - - ===================================== compiler/GHC/Parser.y ===================================== @@ -2679,8 +2679,8 @@ sigdecl :: { LHsDecl GhcPs } Nothing -> (NoSourceText, maxPrecedence) Just l2 -> (fst $ unLoc l2, snd $ unLoc l2) ; amsA' (sLL $1 $> $ SigD noExtField - (FixSig (mj AnnInfix $1 : maybeToList mbPrecAnn) (FixitySig (unLoc $3) (fromOL $ unLoc $4) - (Fixity fixText fixPrec (unLoc $1))))) + (FixSig (mj AnnInfix $1 : maybeToList mbPrecAnn, fixText) (FixitySig (unLoc $3) (fromOL $ unLoc $4) + (Fixity fixPrec (unLoc $1))))) }} | pattern_synonym_sig { L (getLoc $1) . SigD noExtField . unLoc $ $1 } ===================================== compiler/GHC/Parser/Annotation.hs ===================================== @@ -112,6 +112,7 @@ import GHC.Hs.DocString import GHC.Utils.Outputable hiding ( (<>) ) import GHC.Utils.Panic import qualified GHC.Data.Strict as Strict +import GHC.Types.SourceText (SourceText (NoSourceText)) {- Note [exact print annotations] @@ -1363,6 +1364,9 @@ instance NoAnn (EpToken s) where instance NoAnn (EpUniToken s t) where noAnn = NoEpUniTok +instance NoAnn SourceText where + noAnn = NoSourceText + -- --------------------------------------------------------------------- instance (Outputable a) => Outputable (EpAnn a) where ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -411,7 +411,7 @@ rnExpr (OpApp _ e1 op e2) ; fixity <- case op' of L _ (HsVar _ (L _ n)) -> lookupFixityRn n L _ (HsRecSel _ f) -> lookupFieldFixityRn f - _ -> return (Fixity NoSourceText minPrecedence InfixL) + _ -> return (Fixity minPrecedence InfixL) -- c.f. lookupFixity for unbound ; lexical_negation <- xoptM LangExt.LexicalNegation ===================================== compiler/GHC/Rename/Fixity.hs ===================================== @@ -27,7 +27,6 @@ import GHC.Types.Fixity.Env import GHC.Types.Name import GHC.Types.Name.Env import GHC.Types.Fixity -import GHC.Types.SourceText import GHC.Types.SrcLoc import GHC.Utils.Outputable @@ -147,7 +146,7 @@ lookupFixityRn_help :: Name -> RnM (Bool, Fixity) lookupFixityRn_help name | isUnboundName name - = return (False, Fixity NoSourceText minPrecedence InfixL) + = return (False, Fixity minPrecedence InfixL) -- Minimise errors from unbound names; eg -- a>0 `foo` b>0 -- where 'foo' is not in scope, should not give an error (#7937) ===================================== compiler/GHC/Rename/HsType.hs ===================================== @@ -1557,8 +1557,8 @@ checkPrecMatch op (MG { mg_alts = (L _ ms) }) checkPrec :: Name -> Pat GhcRn -> Bool -> IOEnv (Env TcGblEnv TcLclEnv) () checkPrec op (ConPat NoExtField op1 (InfixCon _ _)) right = do - op_fix@(Fixity _ op_prec op_dir) <- lookupFixityRn op - op1_fix@(Fixity _ op1_prec op1_dir) <- lookupFixityRn (unLoc op1) + op_fix@(Fixity op_prec op_dir) <- lookupFixityRn op + op1_fix@(Fixity op1_prec op1_dir) <- lookupFixityRn (unLoc op1) let inf_ok = op1_prec > op_prec || (op1_prec == op_prec && @@ -1586,8 +1586,8 @@ checkSectionPrec direction section op arg _ -> return () where op_name = get_op op - go_for_it arg_op arg_fix@(Fixity _ arg_prec assoc) = do - op_fix@(Fixity _ op_prec _) <- lookupFixityOp op_name + go_for_it arg_op arg_fix@(Fixity arg_prec assoc) = do + op_fix@(Fixity op_prec _) <- lookupFixityOp op_name unless (op_prec < arg_prec || (op_prec == arg_prec && direction == assoc)) (sectionPrecErr (get_op op, op_fix) ===================================== compiler/GHC/Tc/Deriv/Generate.hs ===================================== @@ -1336,7 +1336,7 @@ appPrecedence = fromIntegral maxPrecedence + 1 getPrecedence :: (Name -> Fixity) -> Name -> Integer getPrecedence get_fixity nm = case get_fixity nm of - Fixity _ x _assoc -> fromIntegral x + Fixity x _assoc -> fromIntegral x -- NB: the Report says that associativity is not taken -- into account for either Read or Show; hence we -- ignore associativity here ===================================== compiler/GHC/Tc/Deriv/Generics.hs ===================================== @@ -654,9 +654,9 @@ tc_mkRepTy gk get_fixity dit@(DerivInstTys{ dit_rep_tc = tycon ctFix c | dataConIsInfix c = case get_fixity (dataConName c) of - Fixity _ n InfixL -> buildFix n pLA - Fixity _ n InfixR -> buildFix n pRA - Fixity _ n InfixN -> buildFix n pNA + Fixity n InfixL -> buildFix n pLA + Fixity n InfixR -> buildFix n pRA + Fixity n InfixN -> buildFix n pNA | otherwise = mkTyConTy pPrefix buildFix n assoc = mkTyConApp pInfix [ mkTyConTy assoc , mkNumLitTy (fromIntegral n)] ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -2816,7 +2816,7 @@ reifyFixity name = do { (found, fix) <- lookupFixityRn_help name ; return (if found then Just (conv_fix fix) else Nothing) } where - conv_fix (Hs.Fixity _ i d) = TH.Fixity i (conv_dir d) + conv_fix (Hs.Fixity i d) = TH.Fixity i (conv_dir d) conv_dir Hs.InfixR = TH.InfixR conv_dir Hs.InfixL = TH.InfixL conv_dir Hs.InfixN = TH.InfixN ===================================== compiler/GHC/ThToHs.hs ===================================== @@ -1984,7 +1984,7 @@ cvtPatSynSigTy ty = cvtSigType ty ----------------------------------------------------------- cvtFixity :: TH.Fixity -> Hs.Fixity -cvtFixity (TH.Fixity prec dir) = Hs.Fixity NoSourceText prec (cvt_dir dir) +cvtFixity (TH.Fixity prec dir) = Hs.Fixity prec (cvt_dir dir) where cvt_dir TH.InfixL = Hs.InfixL cvt_dir TH.InfixR = Hs.InfixR ===================================== compiler/GHC/Types/Fixity.hs ===================================== @@ -16,33 +16,28 @@ where import GHC.Prelude -import GHC.Types.SourceText - import GHC.Utils.Outputable import GHC.Utils.Binary import Data.Data hiding (Fixity, Prefix, Infix) -data Fixity = Fixity SourceText Int FixityDirection - -- Note [Pragma source text] in "GHC.Types.SourceText" +data Fixity = Fixity Int FixityDirection deriving Data instance Outputable Fixity where - ppr (Fixity _ prec dir) = hcat [ppr dir, space, int prec] + ppr (Fixity prec dir) = hcat [ppr dir, space, int prec] instance Eq Fixity where -- Used to determine if two fixities conflict - (Fixity _ p1 dir1) == (Fixity _ p2 dir2) = p1==p2 && dir1 == dir2 + (Fixity p1 dir1) == (Fixity p2 dir2) = p1==p2 && dir1 == dir2 instance Binary Fixity where - put_ bh (Fixity src aa ab) = do - put_ bh src + put_ bh (Fixity aa ab) = do put_ bh aa put_ bh ab get bh = do - src <- get bh aa <- get bh ab <- get bh - return (Fixity src aa ab) + return (Fixity aa ab) ------------------------ data FixityDirection @@ -76,12 +71,12 @@ maxPrecedence = 9 minPrecedence = 0 defaultFixity :: Fixity -defaultFixity = Fixity NoSourceText maxPrecedence InfixL +defaultFixity = Fixity maxPrecedence InfixL negateFixity, funTyFixity :: Fixity -- Wired-in fixities -negateFixity = Fixity NoSourceText 6 InfixL -- Fixity of unary negate -funTyFixity = Fixity NoSourceText (-1) InfixR -- Fixity of '->', see #15235 +negateFixity = Fixity 6 InfixL -- Fixity of unary negate +funTyFixity = Fixity (-1) InfixR -- Fixity of '->', see #15235 {- Consider @@ -96,7 +91,7 @@ whether there's an error. compareFixity :: Fixity -> Fixity -> (Bool, -- Error please Bool) -- Associate to the right: a op1 (b op2 c) -compareFixity (Fixity _ prec1 dir1) (Fixity _ prec2 dir2) +compareFixity (Fixity prec1 dir1) (Fixity prec2 dir2) = case prec1 `compare` prec2 of GT -> left LT -> right ===================================== libraries/base/src/GHC/ExecutionStack/Internal.hs ===================================== @@ -16,7 +16,7 @@ -- -- @since 4.9.0.0 -module GHC.ExecutionStack.Internal ( +module GHC.ExecutionStack.Internal {-# DEPRECATED "This module will be removed from base in the next version (v4.22)" #-} ( -- * Internal Location (..) , SrcLoc (..) ===================================== libraries/base/src/GHC/TypeLits/Internal.hs ===================================== @@ -26,7 +26,7 @@ -- -- @since 4.16.0.0 -module GHC.TypeLits.Internal +module GHC.TypeLits.Internal {-# DEPRECATED "This module will be removed from base in the next version (v4.22)" #-} (Symbol, CmpSymbol, CmpChar ===================================== libraries/base/src/GHC/TypeNats/Internal.hs ===================================== @@ -1,7 +1,7 @@ {-# LANGUAGE Safe #-} {-# OPTIONS_HADDOCK not-home #-} -module GHC.TypeNats.Internal +module GHC.TypeNats.Internal {-# DEPRECATED "This module will be removed from base in the next version (v4.22)" #-} (Natural, CmpNat ) where ===================================== testsuite/tests/parser/should_compile/T20846.stderr ===================================== @@ -44,7 +44,9 @@ (SigD (NoExtField) (FixSig - [(AddEpAnn AnnInfix (EpaSpan { T20846.hs:3:1-6 }))] + ((,) + [(AddEpAnn AnnInfix (EpaSpan { T20846.hs:3:1-6 }))] + (NoSourceText)) (FixitySig (NoNamespaceSpecifier) [(L @@ -56,7 +58,9 @@ [])) (Unqual {OccName: ++++}))] - {Fixity: infixr 9})))) + (Fixity + (9) + (InfixR)))))) ,(L (EpAnn (EpaSpan { T20846.hs:4:1-18 }) ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -2761,7 +2761,7 @@ instance ExactPrint (Sig GhcPs) where (an0, vars',ty') <- exactVarSig an vars ty return (ClassOpSig an0 is_deflt vars' ty') - exact (FixSig an (FixitySig x names (Fixity src v fdir))) = do + exact (FixSig (an,src) (FixitySig x names (Fixity v fdir))) = do let fixstr = case fdir of InfixL -> "infixl" InfixR -> "infixr" @@ -2769,7 +2769,7 @@ instance ExactPrint (Sig GhcPs) where an0 <- markEpAnnLMS'' an lidl AnnInfix (Just fixstr) an1 <- markEpAnnLMS'' an0 lidl AnnVal (Just (sourceTextToString src (show v))) names' <- markAnnotated names - return (FixSig an1 (FixitySig x names' (Fixity src v fdir))) + return (FixSig (an1,src) (FixitySig x names' (Fixity v fdir))) exact (InlineSig an ln inl) = do an0 <- markAnnOpen an (inl_src inl) "{-# INLINE" ===================================== utils/genprimopcode/Main.hs ===================================== @@ -364,7 +364,7 @@ gen_hs_source (Info defaults entries) = prim_fixity options n = [ pprFixityDir d ++ " " ++ show i ++ " " ++ asInfix n - | OptionFixity (Just (Fixity _ i d)) <- options ] + | OptionFixity (Just (Fixity i d)) <- options ] prim_func n t = [ wrapOp n ++ " :: " ++ pprTy t, wrapOp n ++ " = " ++ funcRhs n ] ===================================== utils/genprimopcode/Parser.y ===================================== @@ -90,9 +90,9 @@ pOption : lowerName '=' false { OptionFalse $1 } | can_fail_warning '=' pPrimOpCanFailWarnFlag { OptionCanFailWarnFlag $3 } pInfix :: { Maybe Fixity } -pInfix : infix integer { Just $ Fixity NoSourceText $2 InfixN } - | infixl integer { Just $ Fixity NoSourceText $2 InfixL } - | infixr integer { Just $ Fixity NoSourceText $2 InfixR } +pInfix : infix integer { Just $ Fixity $2 InfixN } + | infixl integer { Just $ Fixity $2 InfixL } + | infixr integer { Just $ Fixity $2 InfixR } | nothing { Nothing } pEffect :: { PrimOpEffect } ===================================== utils/genprimopcode/Syntax.hs ===================================== @@ -101,16 +101,12 @@ instance Show TyCon where -- The SourceText exists so that it matches the SourceText field in -- BasicTypes.Fixity -data Fixity = Fixity SourceText Int FixityDirection +data Fixity = Fixity Int FixityDirection deriving (Eq, Show) data FixityDirection = InfixN | InfixL | InfixR deriving (Eq, Show) -data SourceText = SourceText String - | NoSourceText - deriving (Eq,Show) - data PrimOpEffect = NoEffect | CanFail ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs ===================================== @@ -372,7 +372,7 @@ ppFixities fs qual = foldr1 (+++) (map ppFix uniq_fs) +++ rightEdge uniq_fs = [ (n, the p, the d') - | (n, Fixity _ p d) <- fs + | (n, Fixity p d) <- fs , let d' = ppDir d , then group by Down (p, d') ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Create.hs ===================================== @@ -57,7 +57,6 @@ import Data.Traversable (for) import Control.Arrow (first, (&&&)) import GHC hiding (lookupName) import GHC.Builtin.Names -import GHC.Builtin.Types import GHC.Builtin.Types.Prim import GHC.Core.ConLike (ConLike (..)) import GHC.Data.FastString (FastString, bytesFS, unpackFS) @@ -65,7 +64,6 @@ import GHC.Driver.Ppr import GHC.HsToCore.Docs hiding (mkMaps) import GHC.Iface.Syntax import GHC.Types.Avail -import GHC.Types.Basic import GHC.Types.Name import GHC.Types.Name.Set import GHC.Types.SafeHaskell ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Json.hs ===================================== @@ -241,7 +241,7 @@ jsonName :: Name -> JsonDoc jsonName = JSString . nameStableString jsonFixity :: Fixity -> JsonDoc -jsonFixity (Fixity _ prec dir) = +jsonFixity (Fixity prec dir) = jsonObject [ ("prec", jsonInt prec) , ("direction", jsonFixityDirection dir) ===================================== utils/haddock/haddock-api/src/Haddock/Types.hs ===================================== @@ -978,8 +978,8 @@ instance NFData FixityDirection where rnf InfixN = () instance NFData Fixity where - rnf (Fixity sourceText n dir) = - sourceText `deepseq` n `deepseq` dir `deepseq` () + rnf (Fixity n dir) = + n `deepseq` dir `deepseq` () instance NFData (EpAnn NameAnn) where rnf (EpAnn en ann cs) = en `deepseq` ann `deepseq` cs `deepseq` () View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8efafc068066e1dbbd95b6443bd08e0543f0c77b...72bacf3f58473d1956e2524be82864f34406b076 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8efafc068066e1dbbd95b6443bd08e0543f0c77b...72bacf3f58473d1956e2524be82864f34406b076 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 08:37:42 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Wed, 19 Jun 2024 04:37:42 -0400 Subject: [Git][ghc/ghc][wip/sgraf-T12457] WIP Message-ID: <667298d6bc73d_2d7c4e588464425ac@gitlab.mail> Sebastian Graf pushed to branch wip/sgraf-T12457 at Glasgow Haskell Compiler / GHC Commits: 82aea77e by Sebastian Graf at 2024-06-19T10:37:16+02:00 WIP - - - - - 23 changed files: - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Rename/Module.hs - compiler/GHC/Rename/Splice.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Infer.hs - compiler/GHC/Tc/Deriv/Utils.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/HsType.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/Tc/Gen/Splice.hs-boot - compiler/GHC/Tc/Module.hs-boot - compiler/Language/Haskell/Syntax/Decls.hs - compiler/Language/Haskell/Syntax/Extension.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs Changes: ===================================== compiler/GHC/Builtin/Names/TH.hs ===================================== @@ -32,8 +32,7 @@ templateHaskellNames :: [Name] templateHaskellNames = [ returnQName, bindQName, sequenceQName, newNameName, liftName, liftTypedName, mkNameName, mkNameG_vName, mkNameG_dName, mkNameG_tcName, mkNameG_fldName, - mkNameLName, - mkNameSName, mkNameQName, + mkNameUName, mkNameLName, mkNameSName, mkNameQName, mkModNameName, liftStringName, unTypeName, unTypeCodeName, @@ -177,7 +176,11 @@ templateHaskellNames = [ modNameTyConName, -- Quasiquoting - quoteDecName, quoteTypeName, quoteExpName, quotePatName] + quoteDecName, quoteTypeName, quoteExpName, quotePatName, + + -- DeriveTH + deriveTHClassName, deriveTHName + ] thSyn, thLib, qqLib, liftLib :: Module thSyn = mkTHModule (fsLit "GHC.Internal.TH.Syntax") @@ -210,6 +213,9 @@ liftClassName = mk_known_key_name clsName liftLib (fsLit "Lift") liftClassKey quoteClassName :: Name quoteClassName = thCls (fsLit "Quote") quoteClassKey +deriveTHClassName :: Name +deriveTHClassName = mk_known_key_name clsName thLib (fsLit "DeriveTH") deriveTHClassKey + qTyConName, nameTyConName, fieldExpTyConName, patTyConName, fieldPatTyConName, expTyConName, decTyConName, typeTyConName, matchTyConName, clauseTyConName, funDepTyConName, predTyConName, @@ -236,7 +242,8 @@ modNameTyConName = thTc (fsLit "ModName") modNameTyConKey returnQName, bindQName, sequenceQName, newNameName, liftName, mkNameName, mkNameG_vName, mkNameG_fldName, mkNameG_dName, mkNameG_tcName, mkNameLName, mkNameSName, liftStringName, unTypeName, unTypeCodeName, - unsafeCodeCoerceName, liftTypedName, mkModNameName, mkNameQName :: Name + unsafeCodeCoerceName, liftTypedName, mkModNameName, mkNameQName, + deriveTHName :: Name returnQName = thFun (fsLit "returnQ") returnQIdKey bindQName = thFun (fsLit "bindQ") bindQIdKey sequenceQName = thFun (fsLit "sequenceQ") sequenceQIdKey @@ -246,6 +253,7 @@ mkNameG_vName = thFun (fsLit "mkNameG_v") mkNameG_vIdKey mkNameG_dName = thFun (fsLit "mkNameG_d") mkNameG_dIdKey mkNameG_tcName = thFun (fsLit "mkNameG_tc") mkNameG_tcIdKey mkNameG_fldName= thFun (fsLit "mkNameG_fld") mkNameG_fldIdKey +mkNameUName = thFun (fsLit "mkNameU") mkNameUIdKey mkNameLName = thFun (fsLit "mkNameL") mkNameLIdKey mkNameQName = thFun (fsLit "mkNameQ") mkNameQIdKey mkNameSName = thFun (fsLit "mkNameS") mkNameSIdKey @@ -256,6 +264,7 @@ unsafeCodeCoerceName = thFun (fsLit "unsafeCodeCoerce") unsafeCodeCoerceIdKey liftName = liftFun (fsLit "lift") liftIdKey liftStringName = liftFun (fsLit "liftString") liftStringIdKey liftTypedName = liftFun (fsLit "liftTyped") liftTypedIdKey +deriveTHName = libFun (fsLit "deriveTHEntry") deriveTHIdKey -------------------- TH.Lib ----------------------- @@ -689,6 +698,9 @@ liftClassKey = mkPreludeClassUnique 200 quoteClassKey :: Unique quoteClassKey = mkPreludeClassUnique 201 +deriveTHClassKey :: Unique +deriveTHClassKey = mkPreludeClassUnique 202 + {- ********************************************************************* * * TyCon keys @@ -799,8 +811,9 @@ dataNamespaceSpecifierDataConKey = mkPreludeDataConUnique 215 returnQIdKey, bindQIdKey, sequenceQIdKey, liftIdKey, newNameIdKey, mkNameIdKey, mkNameG_vIdKey, mkNameG_fldIdKey, mkNameG_dIdKey, mkNameG_tcIdKey, - mkNameLIdKey, mkNameSIdKey, unTypeIdKey, unTypeCodeIdKey, - unsafeCodeCoerceIdKey, liftTypedIdKey, mkModNameIdKey, mkNameQIdKey :: Unique + mkNameUIdKey, mkNameLIdKey, mkNameSIdKey, unTypeIdKey, unTypeCodeIdKey, + unsafeCodeCoerceIdKey, liftTypedIdKey, mkModNameIdKey, mkNameQIdKey, + deriveTHIdKey :: Unique returnQIdKey = mkPreludeMiscIdUnique 200 bindQIdKey = mkPreludeMiscIdUnique 201 sequenceQIdKey = mkPreludeMiscIdUnique 202 @@ -819,6 +832,7 @@ mkModNameIdKey = mkPreludeMiscIdUnique 215 unsafeCodeCoerceIdKey = mkPreludeMiscIdUnique 216 mkNameQIdKey = mkPreludeMiscIdUnique 217 mkNameG_fldIdKey = mkPreludeMiscIdUnique 218 +deriveTHIdKey = mkPreludeMiscIdUnique 219 -- data Lit = ... @@ -874,6 +888,7 @@ matchIdKey = mkPreludeMiscIdUnique 261 clauseIdKey :: Unique clauseIdKey = mkPreludeMiscIdUnique 262 +mkNameUIdKey = mkPreludeMiscIdUnique 269 -- data Exp = ... varEIdKey, conEIdKey, litEIdKey, appEIdKey, appTypeEIdKey, infixEIdKey, ===================================== compiler/GHC/Hs/Decls.hs ===================================== @@ -647,6 +647,7 @@ derivStrategyName = text . go go AnyclassStrategy {} = "anyclass" go NewtypeStrategy {} = "newtype" go ViaStrategy {} = "via" + go THStrategy {} = "template-haskell" type instance XDctSingle (GhcPass _) = NoExtField type instance XDctMulti (GhcPass _) = NoExtField @@ -1063,6 +1064,10 @@ type instance XViaStrategy GhcPs = XViaStrategyPs type instance XViaStrategy GhcRn = LHsSigType GhcRn type instance XViaStrategy GhcTc = Type +type instance XTHStrategy GhcPs = [AddEpAnn] +type instance XTHStrategy GhcRn = NoExtField +type instance XTHStrategy GhcTc = NoExtField + data XViaStrategyPs = XViaStrategyPs [AddEpAnn] (LHsSigType GhcPs) instance OutputableBndrId p @@ -1074,6 +1079,7 @@ instance OutputableBndrId p GhcPs -> ppr ty GhcRn -> ppr ty GhcTc -> ppr ty + ppr (THStrategy _) = text "template-haskell" instance Outputable XViaStrategyPs where ppr (XViaStrategyPs _ t) = ppr t @@ -1085,7 +1091,8 @@ foldDerivStrategy :: (p ~ GhcPass pass) foldDerivStrategy other _ (StockStrategy _) = other foldDerivStrategy other _ (AnyclassStrategy _) = other foldDerivStrategy other _ (NewtypeStrategy _) = other -foldDerivStrategy _ via (ViaStrategy t) = via t +foldDerivStrategy other _ (THStrategy _) = other +foldDerivStrategy _ via (ViaStrategy t) = via t -- | Map over the @via@ type if dealing with 'ViaStrategy'. Otherwise, -- return the 'DerivStrategy' unchanged. ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -66,7 +66,8 @@ import GHC.Tc.Utils.TcType (TcType, TcTyVar) import {-# SOURCE #-} GHC.Tc.Types.LclEnv (TcLclEnv) import GHCi.RemoteTypes ( ForeignRef ) -import qualified GHC.Internal.TH.Syntax as TH (Q) +import qualified GHC.Internal.TH.Syntax as TH +import qualified GHC.Internal.TH.Ppr as TH -- libraries: import Data.Data hiding (Fixity(..)) @@ -2039,6 +2040,8 @@ ppr_splice herald mn e Just splice_name -> whenPprDebug (brackets (ppr splice_name))) <> ppr e +data THQuote + = THTypBr TH.Type type instance XExpBr GhcPs = NoExtField type instance XPatBr GhcPs = NoExtField @@ -2054,7 +2057,7 @@ type instance XDecBrL GhcRn = NoExtField type instance XDecBrG GhcRn = NoExtField type instance XTypBr GhcRn = NoExtField type instance XVarBr GhcRn = NoExtField -type instance XXQuote GhcRn = DataConCantHappen +type instance XXQuote GhcRn = THQuote -- See Note [The life cycle of a TH quotation] type instance XExpBr GhcTc = DataConCantHappen @@ -2065,6 +2068,9 @@ type instance XTypBr GhcTc = DataConCantHappen type instance XVarBr GhcTc = DataConCantHappen type instance XXQuote GhcTc = NoExtField +instance Outputable THQuote where + ppr (THTypBr ty) = thBrackets (text "TH.Type") (text (TH.pprint ty)) + instance OutputableBndrId p => Outputable (HsQuote (GhcPass p)) where ppr = pprHsQuote @@ -2081,6 +2087,7 @@ instance OutputableBndrId p pprHsQuote (VarBr _ False n) = text "''" <> pprPrefixOcc (unLoc n) pprHsQuote (XQuote b) = case ghcPass @p of + GhcRn -> ppr b GhcTc -> pprPanic "pprHsQuote: `HsQuote GhcTc` shouldn't exist" (ppr b) -- See Note [The life cycle of a TH quotation] ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -405,6 +405,8 @@ deriving instance Data (HsUntypedSplice GhcTc) deriving instance Data a => Data (HsUntypedSpliceResult a) +deriving instance Data THQuote + -- deriving instance (DataIdLR p p) => Data (HsQuote p) deriving instance Data (HsQuote GhcPs) deriving instance Data (HsQuote GhcRn) ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -175,6 +175,7 @@ dsBracket (HsBracketTc { hsb_wrap = mb_wrap, hsb_splices = splices, hsb_quote = TypBr _ t -> runOverloaded $ do { MkC t1 <- repLTy t ; return t1 } DecBrG _ gp -> runOverloaded $ do { MkC ds1 <- repTopDs gp ; return ds1 } DecBrL {} -> panic "dsUntypedBracket: unexpected DecBrL" + XQuote (THTypBr t) -> runOverloaded $ do { MkC t1 <- repThTy t ; return t1 } where Just wrap = mb_wrap -- Not used in VarBr case -- In the overloaded case we have to get given a wrapper, it is just @@ -1184,15 +1185,26 @@ instance RepTV () () where repKindedTV (MkC nm) () (MkC ki) = rep2 kindedTVName [nm, ki] instance RepTV Specificity TH.Specificity where + tyVarBndrName = tyVarBndrSpecTyConName + repPlainTV (MkC nm) spec = do { (MkC spec') <- rep_flag (spec2spec spec) + ; rep2 plainInvisTVName [nm, spec'] } + repKindedTV (MkC nm) spec (MkC ki) = do { (MkC spec') <- rep_flag (spec2spec spec) + ; rep2 kindedInvisTVName [nm, spec', ki] } + +instance RepTV TH.Specificity TH.Specificity where tyVarBndrName = tyVarBndrSpecTyConName repPlainTV (MkC nm) spec = do { (MkC spec') <- rep_flag spec ; rep2 plainInvisTVName [nm, spec'] } repKindedTV (MkC nm) spec (MkC ki) = do { (MkC spec') <- rep_flag spec ; rep2 kindedInvisTVName [nm, spec', ki] } -rep_flag :: Specificity -> MetaM (Core TH.Specificity) -rep_flag SpecifiedSpec = rep2_nw specifiedSpecName [] -rep_flag InferredSpec = rep2_nw inferredSpecName [] +spec2spec :: Specificity -> TH.Specificity +spec2spec SpecifiedSpec = TH.SpecifiedSpec +spec2spec InferredSpec = TH.InferredSpec + +rep_flag :: TH.Specificity -> MetaM (Core TH.Specificity) +rep_flag TH.SpecifiedSpec = rep2_nw specifiedSpecName [] +rep_flag TH.InferredSpec = rep2_nw inferredSpecName [] instance RepTV (HsBndrVis GhcRn) TH.BndrVis where tyVarBndrName = tyVarBndrVisTyConName @@ -1497,6 +1509,101 @@ repRole (L _ (Just Representational)) = rep2_nw representationalRName [] repRole (L _ (Just Phantom)) = rep2_nw phantomRName [] repRole (L _ Nothing) = rep2_nw inferRName [] +repThName :: TH.Name -> MetaM (Core (TH.Name)) +repThName (TH.Name (TH.OccName s) flv) = coreString s >>= \nm -> case flv of + TH.NameS -> repNameS nm + TH.NameQ (TH.ModName mod) -> repNameQ nm =<< coreString mod + TH.NameU u -> repNameU nm =<< coreIntegerLit u + TH.NameL u -> repNameL nm =<< coreIntegerLit u + TH.NameG ns (TH.PkgName pkg) (TH.ModName mod) -> do + mod <- coreString mod + pkg <- coreString pkg + repNameG ns mod pkg nm + +-- | Represent a TH type variable binder +repThTyVarBndr :: RepTV flag flag' => TH.TyVarBndr flag -> MetaM (Core (M (TH.TyVarBndr flag'))) +repThTyVarBndr (TH.PlainTV nm fl) = do { nm <- repThName nm; repPlainTV nm fl } +repThTyVarBndr (TH.KindedTV nm fl ki) = do { nm <- repThName nm; ki <- repThTy ki; repKindedTV nm fl ki } + +repThTyLit :: TH.TyLit -> MetaM (Core (M TH.TyLit)) +repThTyLit (TH.NumTyLit n) = repTnumTyLit =<< coreIntegerLit n +repThTyLit (TH.StrTyLit s) = repTstrTyLit =<< coreString s +repThTyLit (TH.CharTyLit c) = repTcharTyLit =<< coreChar c + +repTnumTyLit :: Core Integer -> MetaM (Core (M TH.TyLit)) +repTnumTyLit (MkC n) = rep2 numTyLitName [n] + +repTstrTyLit :: Core String -> MetaM (Core (M TH.TyLit)) +repTstrTyLit (MkC s) = rep2 strTyLitName [s] + +repTcharTyLit :: Core Char -> MetaM (Core (M TH.TyLit)) +repTcharTyLit (MkC c) = rep2 charTyLitName [c] + +repThCxt :: TH.Cxt -> MetaM (Core (M TH.Cxt)) +repThCxt cxt = repListM typeTyConName repThTy cxt >>= repCtxt + +repThTy :: TH.Type -> MetaM (Core (M TH.Type)) +-- A bit like `lift @TH.Type`, but in `MetaM . Core . M` instead of `Q` +repThTy (TH.ForallT bndrs cxt ty) = do + bndrs <- repListM tyVarBndrSpecTyConName repThTyVarBndr bndrs + cxt <- repThCxt cxt + ty <- repThTy ty + repTForall bndrs cxt ty +repThTy (TH.ForallVisT bndrs ty) = do + bndrs <- repListM tyVarBndrSpecTyConName repThTyVarBndr bndrs + ty <- repThTy ty + repTForallVis bndrs ty +repThTy (TH.AppT f a) = do + f <- repThTy f + a <- repThTy a + repTapp f a +repThTy (TH.AppKindT f k) = do + f <- repThTy f + k <- repThTy k + repTappKind f k +repThTy (TH.SigT t k) = do + t <- repThTy t + k <- repThTy k + repTSig t k +repThTy (TH.VarT n) = do + n <- repThName n + repTvar n +repThTy (TH.ConT n) = do + n <- repThName n + repNamedTyCon n +repThTy (TH.PromotedT n) = do + n <- repThName n + repPromotedDataCon n +repThTy (TH.InfixT a n b) = do + a <- repThTy a + n <- repThName n + b <- repThTy b + repTInfix a n b +repThTy (TH.TupleT n) = repTupleTyCon n +repThTy (TH.UnboxedTupleT n) = repUnboxedTupleTyCon n +repThTy (TH.UnboxedSumT n) = repUnboxedSumTyCon n +repThTy TH.ArrowT = repArrowTyCon +repThTy TH.MulArrowT = repMulArrowTyCon +repThTy TH.EqualityT = repTequality +repThTy TH.ListT = repListTyCon +repThTy (TH.PromotedTupleT n) = repPromotedTupleTyCon n +repThTy TH.PromotedNilT = repPromotedNilTyCon +repThTy TH.PromotedConsT = repPromotedConsTyCon +repThTy TH.StarT = repTStar +repThTy TH.ConstraintT = repTConstraint +repThTy TH.WildCardT = repTWildCard +repThTy (TH.ImplicitParamT s t) = do + s <- coreString s + t <- repThTy t + repTImplicitParam s t +repThTy (TH.LitT lit) = do + lit <- repThTyLit lit + repTLit lit +repThTy TH.ParensT{} = panic "ParensT impossible" +repThTy TH.PromotedInfixT{} = panic "PromotedInfixT impossible" +repThTy TH.UInfixT{} = panic "UInfixT impossible" +repThTy TH.PromotedUInfixT{} = panic "PromotedUInfixT impossible" + ----------------------------------------------------------------------------- -- Splices ----------------------------------------------------------------------------- @@ -3038,6 +3145,20 @@ repNameS (MkC name) = rep2_nw mkNameSName [name] repNameQ :: Core String -> Core String -> MetaM (Core TH.Name) repNameQ (MkC mn) (MkC name) = rep2_nw mkNameQName [mn, name] +repNameU :: Core String -> Core Integer -> MetaM (Core TH.Name) +repNameU (MkC mn) (MkC uniq) = rep2_nw mkNameUName [mn, uniq] + +repNameL :: Core String -> Core Integer -> MetaM (Core TH.Name) +repNameL (MkC mn) (MkC uniq) = rep2_nw mkNameLName [mn, uniq] + +repNameG :: TH.NameSpace -> Core String -> Core String -> Core String -> MetaM (Core TH.Name) +repNameG TH.DataName (MkC mod) (MkC pkg) (MkC nm) = rep2_nw mkNameG_dName [pkg,mod,nm] +repNameG TH.VarName (MkC mod) (MkC pkg) (MkC nm) = rep2_nw mkNameG_vName [pkg,mod,nm] +repNameG TH.TcClsName (MkC mod) (MkC pkg) (MkC nm) = rep2_nw mkNameG_tcName [pkg,mod,nm] +repNameG (TH.FldName fld) (MkC mod) (MkC pkg) (MkC nm) = do + MkC fld <- coreString fld + rep2_nw mkNameG_fldName [pkg,mod,nm,fld] + --------------- Miscellaneous ------------------- repGensym :: Core String -> MetaM (Core (M TH.Name)) @@ -3131,6 +3252,12 @@ nonEmptyCoreList' xs@(MkC x:|_) = MkC (mkListExpr (exprType x) (toList $ fmap un coreStringLit :: MonadThings m => FastString -> m (Core String) coreStringLit s = do { z <- mkStringExprFS s; return (MkC z) } +coreString :: MonadThings m => String -> m (Core String) +coreString s = do { z <- mkStringExpr s; return (MkC z) } + +coreChar :: MonadThings m => Char -> m (Core Char) +coreChar c = return (MkC (mkCharExpr c)) + ------------------- Maybe ------------------ repMaybe :: Name -> (a -> MetaM (Core b)) @@ -3187,6 +3314,10 @@ coreIntLit :: Int -> MetaM (Core Int) coreIntLit i = do platform <- getPlatform return (MkC (mkIntExprInt platform i)) +coreIntegerLit :: Integer -> MetaM (Core Integer) +coreIntegerLit i = do platform <- getPlatform + return (MkC (mkIntegerExpr platform i)) + coreVar :: Id -> Core TH.Name -- The Id has type Name coreVar id = MkC (Var id) ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1699,6 +1699,7 @@ instance ToHie (RScoped (LocatedAn NoEpAnns (DerivStrategy GhcRn))) where AnyclassStrategy _ -> [] NewtypeStrategy _ -> [] ViaStrategy s -> [ toHie (TS (ResolvedScopes [sc]) s) ] + THStrategy _ -> [] instance ToHie (LocatedP OverlapMode) where toHie (L span _) = locOnly (locA span) ===================================== compiler/GHC/Parser.y ===================================== @@ -635,9 +635,10 @@ are the most common patterns, rewritten as regular expressions for clarity: 'using' { L _ ITusing } -- for list transform extension 'pattern' { L _ ITpattern } -- for pattern synonyms 'static' { L _ ITstatic } -- for static pointers extension - 'stock' { L _ ITstock } -- for DerivingStrategies extension - 'anyclass' { L _ ITanyclass } -- for DerivingStrategies extension - 'via' { L _ ITvia } -- for DerivingStrategies extension + 'stock' { L _ ITstock } -- for DerivingStrategies extension + 'anyclass' { L _ ITanyclass } -- for DerivingStrategies extension + 'via' { L _ ITvia } -- for DerivingStrategies extension + 'template-haskell' { L _ ITtemplatehaskell } -- for DerivingStrategies extension 'unit' { L _ ITunit } 'signature' { L _ ITsignature } @@ -1415,6 +1416,7 @@ deriv_strategy_no_via :: { LDerivStrategy GhcPs } : 'stock' {% amsA' (sL1 $1 (StockStrategy [mj AnnStock $1])) } | 'anyclass' {% amsA' (sL1 $1 (AnyclassStrategy [mj AnnAnyclass $1])) } | 'newtype' {% amsA' (sL1 $1 (NewtypeStrategy [mj AnnNewtype $1])) } + | 'template-haskell' {% amsA' (sL1 $1 (THStrategy [mj AnnTH $1])) } deriv_strategy_via :: { LDerivStrategy GhcPs } : 'via' sigktype {% amsA' (sLL $1 $> (ViaStrategy (XViaStrategyPs [mj AnnVia $1] $2))) } ===================================== compiler/GHC/Parser/Annotation.hs ===================================== @@ -311,6 +311,7 @@ data AnnKeywordId | AnnValStr -- ^ String value, will need quotes when output | AnnVbar -- ^ '|' | AnnVia -- ^ 'via' + | AnnTH -- ^ 'template-haskell' (as deriving strategy) | AnnWhere | Annlarrowtail -- ^ '-<' | AnnlarrowtailU -- ^ '-<', unicode variant ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -856,6 +856,7 @@ data Token | ITstock | ITanyclass | ITvia + | ITtemplatehaskell -- Backpack tokens | ITunit @@ -1104,6 +1105,7 @@ reservedWordsFM = listToUFM $ ( "stock", ITstock, 0 ), ( "anyclass", ITanyclass, 0 ), ( "via", ITvia, 0 ), + ( "th", ITtemplatehaskell, 0 ), ( "group", ITgroup, xbit TransformComprehensionsBit), ( "by", ITby, xbit TransformComprehensionsBit), ( "using", ITusing, xbit TransformComprehensionsBit), ===================================== compiler/GHC/Rename/Module.hs ===================================== @@ -2176,7 +2176,7 @@ rnLDerivStrategy doc mds thing_inside let extNeeded :: LangExt.Extension extNeeded | ViaStrategy{} <- ds - = LangExt.DerivingVia + = LangExt.DerivingVia -- TODO: TH | otherwise = LangExt.DerivingStrategies @@ -2187,6 +2187,7 @@ rnLDerivStrategy doc mds thing_inside StockStrategy _ -> boring_case (StockStrategy noExtField) AnyclassStrategy _ -> boring_case (AnyclassStrategy noExtField) NewtypeStrategy _ -> boring_case (NewtypeStrategy noExtField) + THStrategy _ -> boring_case (THStrategy noExtField) ViaStrategy (XViaStrategyPs _ via_ty) -> do checkInferredVars doc via_ty (via_ty', fvs1) <- rnHsSigType doc TypeLevel via_ty ===================================== compiler/GHC/Rename/Splice.hs ===================================== @@ -9,6 +9,7 @@ module GHC.Rename.Splice ( rnTypedSplice, -- Untyped splices rnSpliceType, rnUntypedSpliceExpr, rnSplicePat, rnSpliceTyPat, rnSpliceDecl, + runRnSplice, -- Brackets rnTypedBracket, rnUntypedBracket, @@ -361,6 +362,7 @@ runRnSplice :: UntypedSpliceFlavour -> TcRn (res, [ForeignRef (TH.Q ())]) runRnSplice flavour run_meta ppr_res splice = do { hooks <- hsc_hooks <$> getTopEnv + ; pprTraceM "run0" empty ; splice' <- case runRnSpliceHook hooks of Nothing -> return splice Just h -> h splice @@ -371,19 +373,26 @@ runRnSplice flavour run_meta ppr_res splice -- Typecheck the expression ; meta_exp_ty <- tcMetaTy meta_ty_name + ; pprTraceM "run01" (ppr meta_exp_ty $$ ppr the_expr) + ; blah <- tcTopSpliceExpr Untyped + (tcCheckPolyExpr the_expr meta_exp_ty) + ; pprTraceM "run02" (ppr meta_exp_ty $$ ppr the_expr $$ ppr blah) ; zonked_q_expr <- zonkTopLExpr =<< tcTopSpliceExpr Untyped (tcCheckPolyExpr the_expr meta_exp_ty) + ; pprTraceM "run1" empty -- Run the expression ; mod_finalizers_ref <- newTcRef [] ; result <- setStage (RunSplice mod_finalizers_ref) $ run_meta zonked_q_expr + ; pprTraceM "run2" empty ; mod_finalizers <- readTcRef mod_finalizers_ref ; traceSplice (SpliceInfo { spliceDescription = what , spliceIsDecl = is_decl , spliceSource = Just the_expr , spliceGenerated = ppr_res result }) + ; pprTraceM "run3" empty ; return (result, mod_finalizers) } ===================================== compiler/GHC/Tc/Deriv.hs ===================================== @@ -39,7 +39,7 @@ import GHC.Unit.Module.Warnings import GHC.Rename.Bind import GHC.Rename.Env -import GHC.Rename.Module ( addTcgDUs ) +import GHC.Rename.Module ( addTcgDUs, findSplice ) import GHC.Rename.Utils import GHC.Core.Unify( tcUnifyTy ) @@ -71,6 +71,13 @@ import Control.Monad import Control.Monad.Trans.Class import Control.Monad.Trans.Reader import Data.List (partition, find) +import {-# SOURCE #-} GHC.Tc.Gen.Splice (reifyType, runMetaD) +import {-# SOURCE #-} GHC.Tc.Module (rnTopSrcDecls, tcTopSrcDecls) +import GHC.Types.Basic +import GHC.ThToHs (convertToHsType) +import GHC.Builtin.Names.TH (deriveTHName) +import GHC.Rename.Splice (runRnSplice) +import GHC.Tc.Solver (captureTopConstraints) {- ************************************************************************ @@ -266,9 +273,9 @@ pprRepTy fi@(FamInst { fi_tys = lhs }) where rhs = famInstRHS fi renameDeriv :: [InstInfo GhcPs] - -> Bag (LHsBind GhcPs, LSig GhcPs) + -> (LHsBinds GhcPs, [LSig GhcPs]) -> TcM (Bag (InstInfo GhcRn), HsValBinds GhcRn, DefUses) -renameDeriv inst_infos bagBinds +renameDeriv inst_infos (aux_binds, aux_sigs) = discardWarnings $ -- Discard warnings about unused bindings etc setXOptM LangExt.EmptyCase $ @@ -289,8 +296,7 @@ renameDeriv inst_infos bagBinds -- Bring the extra deriving stuff into scope -- before renaming the instances themselves ; traceTc "rnd" (vcat (map (\i -> pprInstInfoDetails i $$ text "") inst_infos)) - ; let (aux_binds, aux_sigs) = unzipBag bagBinds - aux_val_binds = ValBinds NoAnnSortKey aux_binds (bagToList aux_sigs) + ; let aux_val_binds = ValBinds NoAnnSortKey aux_binds aux_sigs -- Importantly, we use rnLocalValBindsLHS, not rnTopBindsLHS, to rename -- auxiliary bindings as if they were defined locally. -- See Note [Auxiliary binders] in GHC.Tc.Deriv.Generate. @@ -1208,6 +1214,11 @@ mkEqnHelp overlap_mode tvs cls cls_args deriv_ctxt deriv_strat warn = do derivingThingFailWith NoGeneralizedNewtypeDeriving DerivErrGNDUsedOnData mkNewTypeEqn True dit + Just (THStrategy _) -> do + (cls_tys, inst_ty) <- expectNonNullaryClsArgs cls_args + dit <- expectAlgTyConApp cls_tys inst_ty + mk_eqn_th cls_tys inst_ty dit + Nothing -> mk_eqn_no_strategy -- @expectNonNullaryClsArgs inst_tys@ checks if @inst_tys@ is non-empty. @@ -1425,6 +1436,75 @@ mk_eqn_via cls_tys inst_ty via_ty = , dsm_via_inst_ty = inst_ty , dsm_via_ty = via_ty } +mk_eqn_th :: [Type] -- All arguments to the class besides the last + -> Type -- The last argument to the class + -> DerivInstTys -- Information about the arguments to the class + -> DerivM EarlyDerivSpec +mk_eqn_th cls_tys inst_ty dit = do + -- dflags <- getDynFlags + -- TODO + -- let isDeriveAnyClassEnabled = + -- deriveAnyClassEnabled (xopt LangExt.DeriveAnyClass dflags) + cls <- asks denv_cls + th_ty <- lift $ reifyType (mkTyConApp (dit_tc dit) (dit_tc_args dit)) + let hs_ty = case convertToHsType (Generated OtherExpansion SkipPmc) noSrcSpan th_ty of + Left _ -> Nothing + Right hs_ty -> Just hs_ty + let br = noLocA $ HsUntypedBracket [] $ XQuote (THTypBr th_ty) :: LHsExpr GhcRn + let head = nlHsVar deriveTHName :: LHsExpr GhcRn + let tc = classTyCon cls + let inst_ty = nlHsTyVar NotPromoted (tyConName tc) :: LHsType GhcRn + let app_ty = mkHsAppType head (HsWC [] inst_ty) :: LHsExpr GhcRn + let app = nlHsApp app_ty br :: LHsExpr GhcRn + let spl = HsUntypedSpliceExpr [] app :: HsUntypedSplice GhcRn + let ppr_decls :: [LHsDecl GhcPs] -> SDoc + ppr_decls ds = vcat (map ppr ds) + pprTraceM "here1" empty + (decls, mod_finalizers) <- lift $ checkNoErrs $ + runRnSplice UntypedDeclSplice runMetaD ppr_decls spl + inst_decl <- case decls of + [L _ (InstD _ (ClsInstD _ inst_decl))] -> pure inst_decl + _ -> panic "not a class inst" + --(grp, mb_rest) <- lift $ findSplice decls + --case mb_rest of + --Just _ -> panic "urgh" + --Nothing -> return () + --pprTraceM "here2" empty + --(tcg_env, rn_decls) <- lift $ rnTopSrcDecls grp + -- Get TH-generated top-level declarations and make sure they don't + -- contain any splices since we don't handle that at the moment + -- + -- The plumbing here is a bit odd: see #10853 + th_topdecls_var <- fmap tcg_th_topdecls (lift getGblEnv) + th_ds <- readTcRef th_topdecls_var + writeTcRef th_topdecls_var [] + let (aux_binds, _, _, _, _, _) = partitionBindsAndSigs th_ds -- TODO check rest empty + -- Rename TH-generated top-level declarations + -- (th_grp, mb_rest) <- lift $ findSplice th_ds + -- case mb_rest of + -- Just _ -> panic "urgh" + -- Nothing -> return () + -- (tcg_env, th_rn_decls) <- lift $ setGblEnv tcg_env $ rnTopSrcDecls th_grp + -- let grp = appendGroups rn_decls th_rn_decls + + -- Type check all declarations + -- NB: set the env **before** captureTopConstraints so that error messages + -- get reported w.r.t. the right GlobalRdrEnv. It is for this reason that + -- the captureTopConstraints must go here, not in tcRnSrcDecls. +-- ((tcg_env, _tcl_env), _lie1) <- lift $ +-- setGblEnv tcg_env $ +-- captureTopConstraints $ +-- tcTopSrcDecls grp +-- pprTraceM "here3" empty + + -- add_mod_finalizers_now mod_finalizers + -- TODO: top-level decls + pprTraceM "blah" (ppr hs_ty $$ ppr br $$ ppr inst_decl $$ ppr aux_binds) + mk_eqn_from_mechanism (DerivSpecTH + { dsm_th_dit = dit + , dsm_th_inst_decl = inst_decl + , dsm_th_aux_binds = aux_binds}) + -- Derive an instance without a user-requested deriving strategy. This uses -- heuristics to determine which deriving strategy to use. -- See Note [Deriving strategies]. @@ -1921,6 +2001,9 @@ genInstBinds spec@(DS { ds_tvs = tyvars, ds_mechanism = mechanism DerivSpecVia{dsm_via_ty = via_ty} -> gen_newtype_or_via via_ty + DerivSpecTH{dsm_th_aux_binds = aux_binds} + -> pure (emptyBag, [], mapBag DerivTH aux_binds, []) + gen_newtype_or_via ty = do let (binds, sigs) = gen_Newtype_binds loc clas tyvars inst_tys ty return (binds, sigs, emptyBag, []) @@ -1958,6 +2041,9 @@ genFamInsts spec@(DS { ds_tvs = tyvars, ds_mechanism = mechanism -- Try DerivingVia DerivSpecVia{dsm_via_ty = via_ty} -> gen_newtype_or_via via_ty + + DerivSpecTH{} -> do + pure $ undefined where gen_newtype_or_via ty = gen_Newtype_fam_insts loc clas tyvars inst_tys ty @@ -1990,6 +2076,8 @@ doDerivInstErrorChecks1 mechanism = -> pure () DerivSpecVia{} -> atf_coerce_based_error_checks + DerivSpecTH{} + -> pure () where -- When processing a standalone deriving declaration, check that all of the -- constructors for the data type are in scope. For instance: ===================================== compiler/GHC/Tc/Deriv/Generate.hs ===================================== @@ -136,6 +136,8 @@ data AuxBindSpec -- data type. This is only used on the RHS of the -- to-be-generated $c binding. + | DerivTH (LHsBind GhcPs) -- just the thing; should be System name already (see ThToHs.thRdrName) + -- | Retrieve the 'RdrName' of the binding that the supplied 'AuxBindSpec' -- describes. auxBindSpecRdrName :: AuxBindSpec -> RdrName @@ -143,6 +145,7 @@ auxBindSpecRdrName (DerivTag2Con _ tag2con_RDR) = tag2con_RDR auxBindSpecRdrName (DerivMaxTag _ maxtag_RDR) = maxtag_RDR auxBindSpecRdrName (DerivDataDataType _ dataT_RDR _) = dataT_RDR auxBindSpecRdrName (DerivDataConstr _ dataC_RDR _) = dataC_RDR +auxBindSpecRdrName DerivTH{} = panic "not here; see gen_aux_bind_spec" {- ************************************************************************ @@ -2203,6 +2206,8 @@ genAuxBindSpecOriginal loc spec fixity | is_infix = infix_RDR | otherwise = prefix_RDR + gen_bind DerivTH{} = panic "not here; see gen_aux_bind_spec" + -- | Generate the code for an auxiliary binding that is a duplicate of another -- auxiliary binding. -- See @Note [Auxiliary binders] (Wrinkle: Reducing code duplication)@. @@ -2231,6 +2236,8 @@ genAuxBindSpecSig loc spec = case spec of -> mk_sig (nlHsTyVar NotPromoted dataType_RDR) DerivDataConstr _ _ _ -> mk_sig (nlHsTyVar NotPromoted constr_RDR) + DerivTH{} + -> panic "not here; see gen_aux_bind_spec" where mk_sig = mkHsWildCardBndrs . L (noAnnSrcSpan loc) . mkHsImplicitSigType @@ -2238,8 +2245,8 @@ genAuxBindSpecSig loc spec = case spec of -- bindings based on the declarative descriptions in the supplied -- 'AuxBindSpec's. See @Note [Auxiliary binders]@. genAuxBinds :: SrcSpan -> Bag AuxBindSpec - -> Bag (LHsBind GhcPs, LSig GhcPs) -genAuxBinds loc = snd . foldr gen_aux_bind_spec (emptyOccEnv, emptyBag) + -> (LHsBinds GhcPs, [LSig GhcPs]) +genAuxBinds loc = snd . foldr gen_aux_bind_spec (emptyOccEnv, (emptyBag, [])) where -- Perform a CSE-like pass over the generated auxiliary bindings to avoid -- code duplication, as described in @@ -2247,19 +2254,21 @@ genAuxBinds loc = snd . foldr gen_aux_bind_spec (emptyOccEnv, emptyBag) -- The OccEnv remembers the first occurrence of each sort of auxiliary -- binding and maps it to the unique RdrName for that binding. gen_aux_bind_spec :: AuxBindSpec - -> (OccEnv RdrName, Bag (LHsBind GhcPs, LSig GhcPs)) - -> (OccEnv RdrName, Bag (LHsBind GhcPs, LSig GhcPs)) + -> (OccEnv RdrName, (LHsBinds GhcPs, [LSig GhcPs])) + -> (OccEnv RdrName, (LHsBinds GhcPs, [LSig GhcPs])) + gen_aux_bind_spec (DerivTH bind) (env, (binds, sigs)) = (env, (bind `consBag` binds, sigs)) -- TODO sigs gen_aux_bind_spec spec (original_rdr_name_env, spec_bag) = case lookupOccEnv original_rdr_name_env spec_occ of Nothing -> ( extendOccEnv original_rdr_name_env spec_occ spec_rdr_name - , genAuxBindSpecOriginal loc spec `consBag` spec_bag ) + , genAuxBindSpecOriginal loc spec `cons_bind_sig` spec_bag ) Just original_rdr_name -> ( original_rdr_name_env - , genAuxBindSpecDup loc original_rdr_name spec `consBag` spec_bag ) + , genAuxBindSpecDup loc original_rdr_name spec `cons_bind_sig` spec_bag ) where spec_rdr_name = auxBindSpecRdrName spec spec_occ = rdrNameOcc spec_rdr_name + cons_bind_sig (bind, sig) (binds, sigs) = (bind `consBag` binds, sig : sigs) mkParentType :: TyCon -> Type -- Turn the representation tycon of a family into ===================================== compiler/GHC/Tc/Deriv/Infer.hs ===================================== @@ -6,6 +6,7 @@ {-# LANGUAGE MultiWayIf #-} +{-# LANGUAGE OverloadedRecordDot #-} -- | Functions for inferring (and simplifying) the context for derived instances. module GHC.Tc.Deriv.Infer @@ -62,6 +63,11 @@ import Data.Function (on) import Data.Functor.Classes (liftEq) import Data.List (sortBy) import Data.Maybe +import GHC.Types.Id (idName, idType) +import GHC.Rename.HsType (rnHsSigType) +import GHC.Tc.Errors.Types (HsDocContext(..)) +import GHC.Tc.Gen.HsType (tcHsClsInstType) +import GHC.Hs.Decls (ClsInstDecl(..)) ---------------------- @@ -96,6 +102,8 @@ inferConstraints mechanism , mechanism{dsm_stock_dit = dit'} ) DerivSpecAnyClass -> infer_constraints_simple inferConstraintsAnyclass + DerivSpecTH{} + -> infer_constraints_simple (inferConstraintsTH mechanism) DerivSpecNewtype { dsm_newtype_dit = DerivInstTys{dit_cls_tys = cls_tys} , dsm_newtype_rep_ty = rep_ty } @@ -394,6 +402,49 @@ inferConstraintsAnyclass ; pure $ map meth_pred gen_dms } +-- | Like 'inferConstraintsAnyclass', but used only in the case of @DeriveTH@, +-- where constraints are gathered based on the type signatures generated for +-- class methods. +-- +-- See Note [Gathering and simplifying constraints for DeriveTH] +-- for an explanation of how these constraints are used to determine the +-- derived instance context. +inferConstraintsTH :: DerivSpecMechanism -> DerivM ThetaSpec +inferConstraintsTH mechanism at DerivSpecTH{dsm_th_inst_decl=inst_decl} + = do { DerivEnv { denv_cls = cls + , denv_inst_tys = inst_tys } <- ask + ; wildcard <- isStandaloneWildcardDeriv + ; let ctx = GenericCtx $ text "a derived instance declaration" + ; (inst_ty, inst_fvs) <- lift $ rnHsSigType ctx TypeLevel inst_decl.cid_poly_ty + ; inst_ty <- lift $ tcHsClsInstType (InstDeclCtxt False {-TODO-}) inst_ty + ; let (tyvars, theta, clas, inst_tys2) = tcSplitDFunTy inst_ty -- TODO verify that inst_tys matches (is equal to?) inst_tys2 +-- ; let gen_dms = [ idName sel_id +-- | (sel_id, _) <- classOpItems cls ] + ; pprTraceM "infer" (ppr inst_ty $$ ppr inst_tys $$ ppr inst_tys2 $$ ppr theta) + ; let blah pred = SimplePredSpec pred (mkDerivOrigin wildcard) TypeLevel {- TODO -} + ; return (map blah theta) } + +-- ; let meth_pred :: (Id, Type) -> PredSpec +-- -- (Id,Type) are the selector Id and the generic default method type +-- -- NB: the latter is /not/ quantified over the class variables +-- -- See Note [Gathering and simplifying constraints for DeriveAnyClass] +-- meth_pred (sel_id, gen_dm_ty) +-- = let (sel_tvs, _cls_pred, meth_ty) = tcSplitMethodTy (varType sel_id) +-- meth_ty' = substTyWith sel_tvs inst_tys meth_ty +-- gen_dm_ty' = substTyWith sel_tvs inst_tys gen_dm_ty in +-- -- This is the only place where a SubTypePredSpec is +-- -- constructed instead of a SimplePredSpec. See +-- -- Note [Gathering and simplifying constraints for DeriveAnyClass] +-- -- for a more in-depth explanation. +-- SubTypePredSpec { stps_ty_actual = gen_dm_ty' +-- , stps_ty_expected = meth_ty' +-- , stps_origin = mkDerivOrigin wildcard +-- } +-- +-- ; pure $ map meth_pred gen_dms } +inferConstraintsTH _ + = panic "not called with DerivTH" + -- Like 'inferConstraints', but used only for @GeneralizedNewtypeDeriving@ and -- @DerivingVia at . Since both strategies generate code involving 'coerce', the -- inferred constraints set up the scaffolding needed to typecheck those uses ===================================== compiler/GHC/Tc/Deriv/Utils.hs ===================================== @@ -12,7 +12,7 @@ module GHC.Tc.Deriv.Utils ( DerivM, DerivEnv(..), DerivSpec(..), pprDerivSpec, setDerivSpecTheta, zonkDerivSpec, DerivSpecMechanism(..), derivSpecMechanismToStrategy, isDerivSpecStock, - isDerivSpecNewtype, isDerivSpecAnyClass, + isDerivSpecNewtype, isDerivSpecAnyClass, isDerivSpecTH, isDerivSpecVia, zonkDerivSpecMechanism, DerivContext(..), OriginativeDerivStatus(..), StockGenFns(..), isStandaloneDeriv, isStandaloneWildcardDeriv, @@ -291,15 +291,26 @@ data DerivSpecMechanism -- ^ The @via@ type } + -- | @DeriveAnyClass@ + | DerivSpecTH + { dsm_th_dit :: DerivInstTys + -- ^ Information about the arguments to the class in the derived + -- instance, including what type constructor the last argument is + -- headed by. See @Note [DerivEnv and DerivSpecMechanism]@. + , dsm_th_inst_decl :: ClsInstDecl GhcPs + , dsm_th_aux_binds :: LHsBinds GhcPs + } + -- | Convert a 'DerivSpecMechanism' to its corresponding 'DerivStrategy'. derivSpecMechanismToStrategy :: DerivSpecMechanism -> DerivStrategy GhcTc -derivSpecMechanismToStrategy DerivSpecStock{} = StockStrategy noExtField -derivSpecMechanismToStrategy DerivSpecNewtype{} = NewtypeStrategy noExtField -derivSpecMechanismToStrategy DerivSpecAnyClass = AnyclassStrategy noExtField +derivSpecMechanismToStrategy DerivSpecStock{} = StockStrategy noExtField +derivSpecMechanismToStrategy DerivSpecNewtype{} = NewtypeStrategy noExtField +derivSpecMechanismToStrategy DerivSpecAnyClass = AnyclassStrategy noExtField +derivSpecMechanismToStrategy DerivSpecTH{} = THStrategy noExtField derivSpecMechanismToStrategy (DerivSpecVia{dsm_via_ty = t}) = ViaStrategy t -isDerivSpecStock, isDerivSpecNewtype, isDerivSpecAnyClass, isDerivSpecVia - :: DerivSpecMechanism -> Bool +isDerivSpecStock, isDerivSpecNewtype, isDerivSpecAnyClass, isDerivSpecVia, + isDerivSpecTH :: DerivSpecMechanism -> Bool isDerivSpecStock (DerivSpecStock{}) = True isDerivSpecStock _ = False @@ -312,6 +323,9 @@ isDerivSpecAnyClass _ = False isDerivSpecVia (DerivSpecVia{}) = True isDerivSpecVia _ = False +isDerivSpecTH (DerivSpecTH{}) = True +isDerivSpecTH _ = False + -- | Zonk the 'TcTyVar's in a 'DerivSpecMechanism' to 'TyVar's. -- See @Note [What is zonking?]@ in "GHC.Tc.Zonk.Type". -- @@ -349,6 +363,10 @@ zonkDerivSpecMechanism mechanism = , dsm_via_inst_ty = inst_ty' , dsm_via_ty = via_ty' } + DerivSpecTH { dsm_th_dit = dit + } -> do + dit' <- zonkDerivInstTys dit + pure $ mechanism { dsm_th_dit = dit' } instance Outputable DerivSpecMechanism where ppr (DerivSpecStock{dsm_stock_dit = dit}) @@ -365,6 +383,9 @@ instance Outputable DerivSpecMechanism where 2 (vcat [ text "dsm_via_cls_tys" <+> ppr cls_tys , text "dsm_via_inst_ty" <+> ppr inst_ty , text "dsm_via_ty" <+> ppr via_ty ]) + ppr (DerivSpecTH{dsm_th_dit = dit}) + = hang (text "DerivSpecTH") + 2 (vcat [ text "dsm_th_dit" <+> ppr dit ]) {- Note [DerivEnv and DerivSpecMechanism] ===================================== compiler/GHC/Tc/Gen/Bind.hs ===================================== @@ -15,6 +15,7 @@ module GHC.Tc.Gen.Bind ( tcLocalBinds , tcTopBinds , tcValBinds + , tcTySigs , tcHsBootSigs , tcPolyCheck , chooseInferredQuantifiers ===================================== compiler/GHC/Tc/Gen/HsType.hs ===================================== @@ -676,6 +676,7 @@ tcDerivStrategy mb_lds tc_deriv_strategy (StockStrategy _) = boring_case (StockStrategy noExtField) tc_deriv_strategy (AnyclassStrategy _) = boring_case (AnyclassStrategy noExtField) tc_deriv_strategy (NewtypeStrategy _) = boring_case (NewtypeStrategy noExtField) + tc_deriv_strategy (THStrategy _) = boring_case (THStrategy noExtField) tc_deriv_strategy (ViaStrategy hs_sig) = do { ty <- tcTopLHsType DerivClauseCtxt hs_sig -- rec {..}: see Note [Keeping SkolemInfo inside a SkolemTv] ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -21,7 +21,7 @@ -- | Template Haskell splices module GHC.Tc.Gen.Splice( tcTypedSplice, tcTypedBracket, tcUntypedBracket, - runAnnotation, getUntypedSpliceBody, + reifyType, runAnnotation, getUntypedSpliceBody, runMetaE, runMetaP, runMetaT, runMetaD, runQuasi, tcTopSpliceExpr, lookupThName_maybe, @@ -762,13 +762,14 @@ brackTy b = return (Just wrapper, final_ty) in case b of - (VarBr {}) -> (Nothing,) <$> tcMetaTy nameTyConName + (VarBr {}) -> (Nothing,) <$> tcMetaTy nameTyConName -- Result type is Var (not Quote-monadic) - (ExpBr {}) -> mkTy expTyConName -- Result type is m Exp - (TypBr {}) -> mkTy typeTyConName -- Result type is m Type - (DecBrG {}) -> mkTy decsTyConName -- Result type is m [Dec] - (PatBr {}) -> mkTy patTyConName -- Result type is m Pat - (DecBrL {}) -> panic "tcBrackTy: Unexpected DecBrL" + (ExpBr {}) -> mkTy expTyConName -- Result type is m Exp + (TypBr {}) -> mkTy typeTyConName -- Result type is m Type + (DecBrG {}) -> mkTy decsTyConName -- Result type is m [Dec] + (PatBr {}) -> mkTy patTyConName -- Result type is m Pat + (DecBrL {}) -> panic "tcBrackTy: Unexpected DecBrL" + (XQuote (THTypBr{})) -> mkTy typeTyConName -- Result type is m Type --------------- -- | Typechecking a pending splice from a untyped bracket ===================================== compiler/GHC/Tc/Gen/Splice.hs-boot ===================================== @@ -9,6 +9,7 @@ import GHC.Tc.Types( TcM , SpliceType ) import GHC.Tc.Utils.TcType ( ExpRhoType ) import GHC.Types.Annotations ( Annotation, CoreAnnTarget ) import GHC.Hs.Extension ( GhcRn, GhcPs, GhcTc ) +import qualified GHC.Core.TyCo.Rep as TyCoRep import GHC.Hs ( HsQuote, HsExpr, LHsExpr, LHsType, LPat, LHsDecl, ThModFinalizers, HsUntypedSpliceResult ) import qualified GHC.Internal.TH.Syntax as TH @@ -28,6 +29,8 @@ tcUntypedBracket :: HsExpr GhcRn -> ExpRhoType -> TcM (HsExpr GhcTc) +reifyType :: TyCoRep.Type -> TcM TH.Type + runTopSplice :: DelayedSplice -> TcM (HsExpr GhcTc) runAnnotation :: CoreAnnTarget -> LHsExpr GhcRn -> TcM Annotation ===================================== compiler/GHC/Tc/Module.hs-boot ===================================== @@ -2,6 +2,10 @@ module GHC.Tc.Module where import GHC.Types.SourceFile(HsBootOrSig) import GHC.Types.TyThing(TyThing) -import GHC.Tc.Types (TcM) +import GHC.Tc.Types (TcM, TcGblEnv, TcLclEnv) +import GHC.Hs.Extension (GhcPs, GhcRn) +import GHC.Hs.Decls (HsGroup) checkBootDeclM :: HsBootOrSig -> TyThing -> TyThing -> TcM () +rnTopSrcDecls :: HsGroup GhcPs -> TcM (TcGblEnv, HsGroup GhcRn) +tcTopSrcDecls :: HsGroup GhcRn -> TcM (TcGblEnv, TcLclEnv) ===================================== compiler/Language/Haskell/Syntax/Decls.hs ===================================== @@ -1497,6 +1497,8 @@ data DerivStrategy pass | NewtypeStrategy (XNewtypeStrategy pass) -- ^ @-XGeneralizedNewtypeDeriving@ | ViaStrategy (XViaStrategy pass) -- ^ @-XDerivingVia@ + | THStrategy (XTHStrategy pass) + -- ^ @-XDerivingTemplateHaskell@ {- ===================================== compiler/Language/Haskell/Syntax/Extension.hs ===================================== @@ -340,6 +340,7 @@ type family XStockStrategy x type family XAnyClassStrategy x type family XNewtypeStrategy x type family XViaStrategy x +type family XTHStrategy x -- ------------------------------------- -- DefaultDecl type families ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Lib.hs ===================================== @@ -1,6 +1,8 @@ {-# OPTIONS_HADDOCK not-home #-} {-# LANGUAGE CPP #-} {-# LANGUAGE PolyKinds #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE StandaloneKindSignatures #-} {-# LANGUAGE Trustworthy #-} @@ -27,13 +29,15 @@ import Control.Applicative(liftA, Applicative(..)) import qualified Data.Kind as Kind (Type) import Data.Word( Word8 ) import Data.List.NonEmpty ( NonEmpty(..) ) -import GHC.Exts (TYPE) +import GHC.Exts (TYPE, Constraint) import Prelude hiding (Applicative(..)) +import Data.Proxy #else import GHC.Internal.Base hiding (Type, Module, inline) import GHC.Internal.Data.Foldable import GHC.Internal.Data.Functor import GHC.Internal.Data.Maybe +import GHC.Internal.Data.Proxy import GHC.Internal.Data.Traversable (traverse, sequenceA) import GHC.Internal.Integer import GHC.Internal.List (zip) @@ -1252,3 +1256,14 @@ docCons (c, md, arg_docs) = do | nm <- get_cons_names c' , (i, Just arg_doc) <- zip [0..] arg_docs ] + +class DeriveTH (c :: k) where + deriveTH :: Proxy c -> Type -> Q [Dec] + +deriveTHEntry :: forall c. DeriveTH c => Q Type -> Q [Dec] +-- TODO: Use RequiredTypeArguments instead? +deriveTHEntry head = do + head <- head + -- Nothing :: Maybe Overlap; will be overwritten by the type-checker with the + -- proper overlap pragma + deriveTH (Proxy :: Proxy c) head View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/82aea77ed908fe36bed829c9c4a01ea9b30a0181 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/82aea77ed908fe36bed829c9c4a01ea9b30a0181 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 09:01:54 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 19 Jun 2024 05:01:54 -0400 Subject: [Git][ghc/ghc][wip/T24623] Add strictCallArity Message-ID: <66729e8298909_2d7c4e8f0660485b7@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24623 at Glasgow Haskell Compiler / GHC Commits: 85f84982 by Simon Peyton Jones at 2024-06-19T10:01:19+01:00 Add strictCallArity - - - - - 2 changed files: - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Types/Demand.hs Changes: ===================================== compiler/GHC/Core/Opt/DmdAnal.hs ===================================== @@ -1104,8 +1104,9 @@ dmdAnalRhsSig top_lvl rec_flag env let_sd id rhs (final_rhs_dmds, final_rhs) = finaliseArgBoxities env id ww_arity rhs_dmds (de_div rhs_env) rhs' - dmd_sig_arity = ww_arity + calledOnceArity body_sd + dmd_sig_arity = ww_arity + strictCallArity body_sd sig = mkDmdSigForArity dmd_sig_arity (DmdType sig_env final_rhs_dmds) + -- strictCallArity is > 0 only for join points -- See Note [mkDmdSigForArity] opts = ae_opts env ===================================== compiler/GHC/Types/Demand.hs ===================================== @@ -39,7 +39,7 @@ module GHC.Types.Demand ( lazyApply1Dmd, lazyApply2Dmd, strictOnceApply1Dmd, strictManyApply1Dmd, -- ** Other @Demand@ operations oneifyCard, oneifyDmd, strictifyDmd, strictifyDictDmd, lazifyDmd, - peelCallDmd, peelManyCalls, mkCalledOnceDmd, mkCalledOnceDmds, calledOnceArity, + peelCallDmd, peelManyCalls, mkCalledOnceDmd, mkCalledOnceDmds, strictCallArity, mkWorkerDemand, subDemandIfEvaluated, -- ** Extracting one-shot information callCards, argOneShots, argsOneShots, saturatedByOneShots, @@ -1038,11 +1038,11 @@ peelManyCalls k sd = go k C_11 sd go _ _ _ = (topCard, topSubDmd) {-# INLINE peelManyCalls #-} -- so that the pair cancels away in a `fst _` context -calledOnceArity :: SubDemand -> Arity -calledOnceArity sd = go 0 sd +strictCallArity :: SubDemand -> Arity +strictCallArity sd = go 0 sd where - go n (viewCall -> Just (C_11, sd)) = go (n+1) sd - go n _ = n + go n (Call card sd) | isStrict card = go (n+1) sd + go n _ = n -- | Extract the 'SubDemand' of a 'Demand'. -- PRECONDITION: The SubDemand must be used in a context where the expression View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/85f849826f1fe370f4ec9243f437f52701269c34 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/85f849826f1fe370f4ec9243f437f52701269c34 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 09:17:35 2024 From: gitlab at gitlab.haskell.org (Andrei Borzenkov (@sand-witch)) Date: Wed, 19 Jun 2024 05:17:35 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/sand-witch/types-in-terms Message-ID: <6672a22f30c6e_17fcd5140cd01018@gitlab.mail> Andrei Borzenkov pushed new branch wip/sand-witch/types-in-terms at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/sand-witch/types-in-terms You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 09:20:04 2024 From: gitlab at gitlab.haskell.org (Andrei Borzenkov (@sand-witch)) Date: Wed, 19 Jun 2024 05:20:04 -0400 Subject: [Git][ghc/ghc][wip/sand-witch/types-in-terms] 59 commits: StgToCmm: refactor opTranslate and friends Message-ID: <6672a2c4e8281_17fcd51eff00125c2@gitlab.mail> Andrei Borzenkov pushed to branch wip/sand-witch/types-in-terms at Glasgow Haskell Compiler / GHC Commits: 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - d70abb49 by sheaf at 2024-06-18T18:47:20-04:00 Clarify -XGADTs enables existential quantification Even though -XGADTs does not turn on -XExistentialQuantification, it does allow the user of existential quantification syntax, without needing to use GADT-style syntax. Fixes #20865 - - - - - 13fdf788 by David Binder at 2024-06-18T18:48:02-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 1bab7dde by Fendor at 2024-06-18T18:48:38-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18698b T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The tests T16875 and T18698b fail on i386-linux for the same reason. - - - - - 099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - 5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00 Update user guide to indicate support for 64-tuples - - - - - 4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00 Remove duplicate Anno instances - - - - - 8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00 AArch64: Delete unused RegNos This has the additional benefit of getting rid of the -1 encoding (real registers start at 0.) - - - - - 325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00 Bump stm submodule to current master - - - - - 64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00 testsuite: bump T17572 timeout on wasm32 - - - - - ad68f4ad by Vladislav Zavialov at 2024-06-19T13:18:12+04:00 WIP: Types in terms - - - - - 05a3cd45 by Vladislav Zavialov at 2024-06-19T13:18:12+04:00 WIP: -Wview-pattern-signatures - - - - - 17a0e35d by Andrei Borzenkov at 2024-06-19T13:19:34+04:00 Implement type syntax in the expressions (24159, 24572) - - - - - 30 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Driver/Config/StgToCmm.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Flags.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57405173ab12221b9e1c2aad851360483a0f585c...17a0e35d9b44778cdd44d731bf7cd5655f4506b2 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/57405173ab12221b9e1c2aad851360483a0f585c...17a0e35d9b44778cdd44d731bf7cd5655f4506b2 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 10:22:57 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Wed, 19 Jun 2024 06:22:57 -0400 Subject: [Git][ghc/ghc][wip/romes/12935] 157 commits: base: specify tie-breaking behavior of min, max, and related list/Foldable functions Message-ID: <6672b1817ba53_17fcd594d6082967d@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/12935 at Glasgow Haskell Compiler / GHC Commits: a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00 base: specify tie-breaking behavior of min, max, and related list/Foldable functions - - - - - bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00 cmm: add word <-> double/float bitcast - closes: #25331 This is the last step in the project plan described in #25331. This commit: - adds bitcast operands for x86_64, LLVM, aarch64 - For PPC and i386 we resort to using the cmm implementations - renames conversion MachOps from Conv to Round|Truncate - - - - - f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor Some functions in StgToByteCode were filtering out void arguments. However, StgToByteCode is called after unarisation: the void arguments should have been removed earlier. Instead of filtering out, we assert that the args are non-void. - - - - - 03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor `layoutNativeCall` was always called with a `primRepCmmType platform` callback. Hence we can put it inside of `layoutNativeCall` rather than repeat it. - - - - - 27c430f3 by David Binder at 2024-05-24T07:52:38-04:00 haddock: Remove compatibility shims for GHC < 8.4 from haddock-library - - - - - 8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00 compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs This patch makes the STG->Cmm backend avoid saving foreign call target to local when there are no caller-save GlobalRegs. Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a foreign call, we unconditionally save the foreign call target to a temporary local first, then rely on cmmSink to clean it up later, which only happens with -fcmm-sink (implied by -O) and not in unoptimized code. And this is troublesome for the wasm backend NCG, which needs to infer a foreign call target symbol's type signature from the Cmm call site. Previously, the NCG has been emitting incorrect type signatures for unoptimized code, which happens to work with `wasm-ld` most of the time, but this is never future-proof against upstream toolchain updates, and it causes horrible breakages when LTO objects are included in linker input. Hence this patch. - - - - - 986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00 testsuite: add callee-no-local regression test - - - - - 52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00 Fix HasCallStack leftovers from !12514 / #24726 - - - - - c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00 user_guide: Fix typo in MultiWayIf chapter Close #24829 - - - - - bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - 1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Fix changelog reference to setBacktraceMechanismState (cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d) - - - - - 43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00 Float/double unboxed literal support for HexFloatLiterals (fix #22155) - - - - - 4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00 Improve test labels for binary interface file size tests Test labels for binary interface file sizes are hard to read and overly verbose at the same time. Extend the name for the metric title, but shorten it in the actual comparison table. - - - - - 14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00 Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present" This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa. - - - - - f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00 Fix default hyperlinked sources pattern Previously this didn't include the `%M` token which manifested as broken links to the hyperlinked sources of reexports of declarations defined in other packages. Fixes haddock#1628. (cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36) - - - - - 42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00 Make DocPaths a proper data type (cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c) - - - - - 53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00 haddock: Bump version to 2.30 (cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602) - - - - - e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00 haddock-api: allow base 4.20 and ghc 9.11 - - - - - e294f7a2 by PHO at 2024-05-24T12:17:55-04:00 Add a flag "threaded" for building haddock with the threaded RTS GHC isn't guaranteed to have a threaded RTS. There should be a way to build it with the vanilla one. (cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d) - - - - - 51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00 Update ticky counter event docs. Add the info about the info table address and json fields. Fixes #23200 - - - - - 98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00 Export extractPromotedList (#24866) This can be useful in plugins. - - - - - 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - d9357f66 by Rodrigo Mesquita at 2024-06-19T11:22:14+01:00 Write a test for object determinism - - - - - 3672b390 by Rodrigo Mesquita at 2024-06-19T11:22:15+01:00 Extend abi_test with object determinism check - - - - - 269c004d by Rodrigo Mesquita at 2024-06-19T11:22:15+01:00 Standalone run abi test - - - - - 8a8df7b5 by Matthew Pickering at 2024-06-19T11:22:15+01:00 Run on test-abi label - - - - - 4bfe7885 by Rodrigo Mesquita at 2024-06-19T11:22:15+01:00 Disable local test on CI - - - - - 9184c59d by Rodrigo Mesquita at 2024-06-19T11:22:43+01:00 WIP - - - - - 41623dd9 by Rodrigo Mesquita at 2024-06-19T11:22:45+01:00 Progress - - - - - f3e1daee by Rodrigo Mesquita at 2024-06-19T11:22:45+01:00 Work around LLVM assembler bug! In a really stupid way) - - - - - 9abb834b by Rodrigo Mesquita at 2024-06-19T11:22:45+01:00 Fix ordering of CLabels for IdLabels - - - - - e4b31346 by Rodrigo Mesquita at 2024-06-19T11:22:45+01:00 Local test script tweaks - - - - - 8892f27b by Rodrigo Mesquita at 2024-06-19T11:22:45+01:00 Do uniq renaming before SRTs - - - - - 682f8973 by Rodrigo Mesquita at 2024-06-19T11:22:45+01:00 Revert "Do uniq renaming before SRTs" This reverts commit db38b635d626106e40b3ab18091e0a24046c30c5. - - - - - 429f3e6d by Rodrigo Mesquita at 2024-06-19T11:22:45+01:00 Do on CmmGroup - - - - - 51fd4fe4 by Rodrigo Mesquita at 2024-06-19T11:22:45+01:00 Do uniq-renaming pass right at `codeGen` - - - - - 30 changed files: - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/BlockId.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Dataflow/Label.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/Switch.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - + compiler/GHC/Cmm/UniqueRenamer.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4a3756478fb791071c75c5d6b9393aa4353fcaa1...51fd4fe4b24520251cbfc2787e244a83b497730e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4a3756478fb791071c75c5d6b9393aa4353fcaa1...51fd4fe4b24520251cbfc2787e244a83b497730e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 10:31:05 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 19 Jun 2024 06:31:05 -0400 Subject: [Git][ghc/ghc][wip/T24623] 29 commits: ucd2haskell: remove Streamly dependency + misc Message-ID: <6672b369343f6_17fcd5b2e008315f9@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24623 at Glasgow Haskell Compiler / GHC Commits: 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - d70abb49 by sheaf at 2024-06-18T18:47:20-04:00 Clarify -XGADTs enables existential quantification Even though -XGADTs does not turn on -XExistentialQuantification, it does allow the user of existential quantification syntax, without needing to use GADT-style syntax. Fixes #20865 - - - - - 13fdf788 by David Binder at 2024-06-18T18:48:02-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 1bab7dde by Fendor at 2024-06-18T18:48:38-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18698b T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The tests T16875 and T18698b fail on i386-linux for the same reason. - - - - - 099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - 5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00 Update user guide to indicate support for 64-tuples - - - - - 4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00 Remove duplicate Anno instances - - - - - 8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00 AArch64: Delete unused RegNos This has the additional benefit of getting rid of the -1 encoding (real registers start at 0.) - - - - - 325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00 Bump stm submodule to current master - - - - - 64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00 testsuite: bump T17572 timeout on wasm32 - - - - - a96cc423 by Simon Peyton Jones at 2024-06-19T11:30:51+01:00 Fix demand signatures for join points This MR tackles #24623 and #23113 The main change is to give a clearer notion of "worker/wrapper arity", esp for join points. See GHC.Core.Opt.DmdAnal Note [Worker/wrapper arity and join points] This Note is a good summary of what this MR does: (1) The "worker/wrapper arity" of an Id is * For non-join-points: idArity * The join points: the join arity (Id part only of course) This is the number of args we will use in worker/wrapper. See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`. (2) A join point's demand-signature arity may exceed the Id's worker/wrapper arity. See the `arity_ok` assertion in `mkWwBodies`. (3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond the worker/wrapper arity. (4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper arity (re)-computed by workWrapArity. - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Opt/WorkWrap.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Hs.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Ast.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/85f849826f1fe370f4ec9243f437f52701269c34...a96cc423914575d14d4c182badef3eba8b9ea2a0 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/85f849826f1fe370f4ec9243f437f52701269c34...a96cc423914575d14d4c182badef3eba8b9ea2a0 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 10:47:10 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 19 Jun 2024 06:47:10 -0400 Subject: [Git][ghc/ghc][master] AArch64: Simplify BL instruction Message-ID: <6672b72e5c106_17fcd5103e840630be@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00 AArch64: Simplify BL instruction The BL constructor carried unused data in its third argument. - - - - - 3 changed files: - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs Changes: ===================================== compiler/GHC/CmmToAsm/AArch64/CodeGen.hs ===================================== @@ -1596,7 +1596,7 @@ genCCall target dest_regs arg_regs bid = do then 8 * (stackSpace' `div` 8 + 1) else stackSpace' - (returnRegs, readResultsCode) <- readResults allGpArgRegs allFpArgRegs dest_regs [] nilOL + readResultsCode <- readResults allGpArgRegs allFpArgRegs dest_regs [] nilOL let moveStackDown 0 = toOL [ PUSH_STACK_FRAME , DELTA (-16) ] @@ -1614,7 +1614,7 @@ genCCall target dest_regs arg_regs bid = do let code = call_target_code -- compute the label (possibly into a register) `appOL` moveStackDown (stackSpace `div` 8) `appOL` passArgumentsCode -- put the arguments into x0, ... - `appOL` (unitOL $ BL call_target passRegs returnRegs) -- branch and link. + `appOL` (unitOL $ BL call_target passRegs) -- branch and link. `appOL` readResultsCode -- parse the results into registers `appOL` moveStackUp (stackSpace `div` 8) return (code, Nothing) @@ -2203,8 +2203,8 @@ genCCall target dest_regs arg_regs bid = do passArguments _ _ _ _ _ _ _ = pprPanic "passArguments" (text "invalid state") - readResults :: [Reg] -> [Reg] -> [LocalReg] -> [Reg]-> InstrBlock -> NatM ([Reg], InstrBlock) - readResults _ _ [] accumRegs accumCode = return (accumRegs, accumCode) + readResults :: [Reg] -> [Reg] -> [LocalReg] -> [Reg]-> InstrBlock -> NatM (InstrBlock) + readResults _ _ [] _ accumCode = return accumCode readResults [] _ _ _ _ = do platform <- getPlatform pprPanic "genCCall, out of gp registers when reading results" (pdoc platform target) ===================================== compiler/GHC/CmmToAsm/AArch64/Instr.hs ===================================== @@ -117,7 +117,7 @@ regUsageOfInstr platform instr = case instr of J t -> usage (regTarget t, []) B t -> usage (regTarget t, []) BCOND _ t -> usage (regTarget t, []) - BL t ps _rs -> usage (regTarget t ++ ps, callerSavedRegisters) + BL t ps -> usage (regTarget t ++ ps, callerSavedRegisters) -- 5. Atomic Instructions ---------------------------------------------------- -- 6. Conditional Instructions ----------------------------------------------- @@ -254,7 +254,7 @@ patchRegsOfInstr instr env = case instr of -- 4. Branch Instructions -------------------------------------------------- J t -> J (patchTarget t) B t -> B (patchTarget t) - BL t rs ts -> BL (patchTarget t) rs ts + BL t rs -> BL (patchTarget t) rs BCOND c t -> BCOND c (patchTarget t) -- 5. Atomic Instructions -------------------------------------------------- @@ -320,7 +320,7 @@ jumpDestsOfInstr (CBZ _ t) = [ id | TBlock id <- [t]] jumpDestsOfInstr (CBNZ _ t) = [ id | TBlock id <- [t]] jumpDestsOfInstr (J t) = [id | TBlock id <- [t]] jumpDestsOfInstr (B t) = [id | TBlock id <- [t]] -jumpDestsOfInstr (BL t _ _) = [ id | TBlock id <- [t]] +jumpDestsOfInstr (BL t _) = [ id | TBlock id <- [t]] jumpDestsOfInstr (BCOND _ t) = [ id | TBlock id <- [t]] jumpDestsOfInstr _ = [] @@ -341,7 +341,7 @@ patchJumpInstr instr patchF CBNZ r (TBlock bid) -> CBNZ r (TBlock (patchF bid)) J (TBlock bid) -> J (TBlock (patchF bid)) B (TBlock bid) -> B (TBlock (patchF bid)) - BL (TBlock bid) ps rs -> BL (TBlock (patchF bid)) ps rs + BL (TBlock bid) ps -> BL (TBlock (patchF bid)) ps BCOND c (TBlock bid) -> BCOND c (TBlock (patchF bid)) _ -> panic $ "patchJumpInstr: " ++ instrCon instr @@ -626,7 +626,7 @@ data Instr -- Branching. | J Target -- like B, but only generated from genJump. Used to distinguish genJumps from others. | B Target -- unconditional branching b/br. (To a blockid, label or register) - | BL Target [Reg] [Reg] -- branch and link (e.g. set x30 to next pc, and branch) + | BL Target [Reg] -- branch and link (e.g. set x30 to next pc, and branch) | BCOND Cond Target -- branch with condition. b. -- 8. Synchronization Instructions ----------------------------------------- ===================================== compiler/GHC/CmmToAsm/AArch64/Ppr.hs ===================================== @@ -426,9 +426,9 @@ pprInstr platform instr = case instr of B (TLabel lbl) -> line $ text "\tb" <+> pprAsmLabel platform lbl B (TReg r) -> line $ text "\tbr" <+> pprReg W64 r - BL (TBlock bid) _ _ -> line $ text "\tbl" <+> pprAsmLabel platform (mkLocalBlockLabel (getUnique bid)) - BL (TLabel lbl) _ _ -> line $ text "\tbl" <+> pprAsmLabel platform lbl - BL (TReg r) _ _ -> line $ text "\tblr" <+> pprReg W64 r + BL (TBlock bid) _ -> line $ text "\tbl" <+> pprAsmLabel platform (mkLocalBlockLabel (getUnique bid)) + BL (TLabel lbl) _ -> line $ text "\tbl" <+> pprAsmLabel platform lbl + BL (TReg r) _ -> line $ text "\tblr" <+> pprReg W64 r BCOND c (TBlock bid) -> line $ text "\t" <> pprBcond c <+> pprAsmLabel platform (mkLocalBlockLabel (getUnique bid)) BCOND c (TLabel lbl) -> line $ text "\t" <> pprBcond c <+> pprAsmLabel platform lbl View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eb612fbc8e94d50c9895c02f3d6ee076f61b7773 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eb612fbc8e94d50c9895c02f3d6ee076f61b7773 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 10:48:11 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 19 Jun 2024 06:48:11 -0400 Subject: [Git][ghc/ghc][master] TTG: Move SourceText from `Fixity` to `FixitySig` Message-ID: <6672b76b3a657_17fcd512014c066344@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00 TTG: Move SourceText from `Fixity` to `FixitySig` It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Precedes !12842, to simplify it - - - - - 24 changed files: - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Fixity.hs - testsuite/tests/parser/should_compile/T20846.stderr - utils/check-exact/ExactPrint.hs - utils/genprimopcode/Main.hs - utils/genprimopcode/Parser.y - utils/genprimopcode/Syntax.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Interface/Json.hs - utils/haddock/haddock-api/src/Haddock/Types.hs Changes: ===================================== compiler/GHC/Builtin/PrimOps.hs ===================================== @@ -49,7 +49,6 @@ import GHC.Types.Basic import GHC.Types.Fixity ( Fixity(..), FixityDirection(..) ) import GHC.Types.SrcLoc ( wiredInSrcSpan ) import GHC.Types.ForeignCall ( CLabelString ) -import GHC.Types.SourceText ( SourceText(..) ) import GHC.Types.Unique ( Unique ) import GHC.Unit.Types ( Unit ) ===================================== compiler/GHC/Hs/Binds.hs ===================================== @@ -708,7 +708,7 @@ instance OutputableBndrId p => Outputable (IPBind (GhcPass p)) where type instance XTypeSig (GhcPass p) = AnnSig type instance XPatSynSig (GhcPass p) = AnnSig type instance XClassOpSig (GhcPass p) = AnnSig -type instance XFixSig (GhcPass p) = [AddEpAnn] +type instance XFixSig (GhcPass p) = ([AddEpAnn], SourceText) type instance XInlineSig (GhcPass p) = [AddEpAnn] type instance XSpecSig (GhcPass p) = [AddEpAnn] type instance XSpecInstSig (GhcPass p) = ([AddEpAnn], SourceText) ===================================== compiler/GHC/Hs/Dump.hs ===================================== @@ -74,7 +74,6 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0 `extQ` name `extQ` occName `extQ` moduleName `extQ` var `extQ` dataCon `extQ` bagName `extQ` bagRdrName `extQ` bagVar `extQ` nameSet - `extQ` fixity `ext2Q` located `extQ` srcSpanAnnA `extQ` srcSpanAnnL @@ -139,11 +138,12 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0 , generic s ] sourceText :: SourceText -> SDoc - sourceText NoSourceText = parens $ text "NoSourceText" + sourceText NoSourceText = case bs of + BlankSrcSpan -> parens $ text "SourceText" <+> text "blanked" + _ -> parens $ text "NoSourceText" sourceText (SourceText src) = case bs of - NoBlankSrcSpan -> parens $ text "SourceText" <+> ftext src - BlankSrcSpanFile -> parens $ text "SourceText" <+> ftext src - _ -> parens $ text "SourceText" <+> text "blanked" + BlankSrcSpan -> parens $ text "SourceText" <+> text "blanked" + _ -> parens $ text "SourceText" <+> ftext src epaAnchor :: EpaLocation -> SDoc epaAnchor (EpaSpan s) = parens $ text "EpaSpan" <+> srcSpan s @@ -216,11 +216,6 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0 text "NameSet:" $$ (list . nameSetElemsStable $ ns) - fixity :: Fixity -> SDoc - fixity fx = braces $ - text "Fixity:" - <+> ppr fx - located :: (Data a, Data b) => GenLocated a b -> SDoc located (L ss a) = parens (text "L" ===================================== compiler/GHC/HsToCore/Quote.hs ===================================== @@ -780,7 +780,7 @@ repLFixD :: LFixitySig GhcRn -> MetaM [(SrcSpan, Core (M TH.Dec))] repLFixD (L loc fix_sig) = rep_fix_d (locA loc) fix_sig rep_fix_d :: SrcSpan -> FixitySig GhcRn -> MetaM [(SrcSpan, Core (M TH.Dec))] -rep_fix_d loc (FixitySig ns_spec names (Fixity _ prec dir)) +rep_fix_d loc (FixitySig ns_spec names (Fixity prec dir)) = do { MkC prec' <- coreIntLit prec ; let rep_fn = case dir of InfixL -> infixLWithSpecDName ===================================== compiler/GHC/Iface/Load.hs ===================================== @@ -90,7 +90,6 @@ import GHC.Types.Avail import GHC.Types.Fixity import GHC.Types.Fixity.Env import GHC.Types.SourceError -import GHC.Types.SourceText import GHC.Types.SourceFile import GHC.Types.SafeHaskell import GHC.Types.TypeEnv @@ -1029,7 +1028,7 @@ ghcPrimIface -- The fixity listed here for @`seq`@ should match -- those in primops.txt.pp (from which Haddock docs are generated). - fixities = (getOccName seqId, Fixity NoSourceText 0 InfixR) + fixities = (getOccName seqId, Fixity 0 InfixR) : mapMaybe mkFixity allThePrimOps mkFixity op = (,) (primOpOcc op) <$> primOpFixity op @@ -1235,5 +1234,3 @@ instance Outputable WhereFrom where ppr (ImportByUser NotBoot) = empty ppr ImportBySystem = text "{- SYSTEM -}" ppr ImportByPlugin = text "{- PLUGIN -}" - - ===================================== compiler/GHC/Parser.y ===================================== @@ -2679,8 +2679,8 @@ sigdecl :: { LHsDecl GhcPs } Nothing -> (NoSourceText, maxPrecedence) Just l2 -> (fst $ unLoc l2, snd $ unLoc l2) ; amsA' (sLL $1 $> $ SigD noExtField - (FixSig (mj AnnInfix $1 : maybeToList mbPrecAnn) (FixitySig (unLoc $3) (fromOL $ unLoc $4) - (Fixity fixText fixPrec (unLoc $1))))) + (FixSig (mj AnnInfix $1 : maybeToList mbPrecAnn, fixText) (FixitySig (unLoc $3) (fromOL $ unLoc $4) + (Fixity fixPrec (unLoc $1))))) }} | pattern_synonym_sig { L (getLoc $1) . SigD noExtField . unLoc $ $1 } ===================================== compiler/GHC/Parser/Annotation.hs ===================================== @@ -112,6 +112,7 @@ import GHC.Hs.DocString import GHC.Utils.Outputable hiding ( (<>) ) import GHC.Utils.Panic import qualified GHC.Data.Strict as Strict +import GHC.Types.SourceText (SourceText (NoSourceText)) {- Note [exact print annotations] @@ -1363,6 +1364,9 @@ instance NoAnn (EpToken s) where instance NoAnn (EpUniToken s t) where noAnn = NoEpUniTok +instance NoAnn SourceText where + noAnn = NoSourceText + -- --------------------------------------------------------------------- instance (Outputable a) => Outputable (EpAnn a) where ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -411,7 +411,7 @@ rnExpr (OpApp _ e1 op e2) ; fixity <- case op' of L _ (HsVar _ (L _ n)) -> lookupFixityRn n L _ (HsRecSel _ f) -> lookupFieldFixityRn f - _ -> return (Fixity NoSourceText minPrecedence InfixL) + _ -> return (Fixity minPrecedence InfixL) -- c.f. lookupFixity for unbound ; lexical_negation <- xoptM LangExt.LexicalNegation ===================================== compiler/GHC/Rename/Fixity.hs ===================================== @@ -27,7 +27,6 @@ import GHC.Types.Fixity.Env import GHC.Types.Name import GHC.Types.Name.Env import GHC.Types.Fixity -import GHC.Types.SourceText import GHC.Types.SrcLoc import GHC.Utils.Outputable @@ -147,7 +146,7 @@ lookupFixityRn_help :: Name -> RnM (Bool, Fixity) lookupFixityRn_help name | isUnboundName name - = return (False, Fixity NoSourceText minPrecedence InfixL) + = return (False, Fixity minPrecedence InfixL) -- Minimise errors from unbound names; eg -- a>0 `foo` b>0 -- where 'foo' is not in scope, should not give an error (#7937) ===================================== compiler/GHC/Rename/HsType.hs ===================================== @@ -1557,8 +1557,8 @@ checkPrecMatch op (MG { mg_alts = (L _ ms) }) checkPrec :: Name -> Pat GhcRn -> Bool -> IOEnv (Env TcGblEnv TcLclEnv) () checkPrec op (ConPat NoExtField op1 (InfixCon _ _)) right = do - op_fix@(Fixity _ op_prec op_dir) <- lookupFixityRn op - op1_fix@(Fixity _ op1_prec op1_dir) <- lookupFixityRn (unLoc op1) + op_fix@(Fixity op_prec op_dir) <- lookupFixityRn op + op1_fix@(Fixity op1_prec op1_dir) <- lookupFixityRn (unLoc op1) let inf_ok = op1_prec > op_prec || (op1_prec == op_prec && @@ -1586,8 +1586,8 @@ checkSectionPrec direction section op arg _ -> return () where op_name = get_op op - go_for_it arg_op arg_fix@(Fixity _ arg_prec assoc) = do - op_fix@(Fixity _ op_prec _) <- lookupFixityOp op_name + go_for_it arg_op arg_fix@(Fixity arg_prec assoc) = do + op_fix@(Fixity op_prec _) <- lookupFixityOp op_name unless (op_prec < arg_prec || (op_prec == arg_prec && direction == assoc)) (sectionPrecErr (get_op op, op_fix) ===================================== compiler/GHC/Tc/Deriv/Generate.hs ===================================== @@ -1336,7 +1336,7 @@ appPrecedence = fromIntegral maxPrecedence + 1 getPrecedence :: (Name -> Fixity) -> Name -> Integer getPrecedence get_fixity nm = case get_fixity nm of - Fixity _ x _assoc -> fromIntegral x + Fixity x _assoc -> fromIntegral x -- NB: the Report says that associativity is not taken -- into account for either Read or Show; hence we -- ignore associativity here ===================================== compiler/GHC/Tc/Deriv/Generics.hs ===================================== @@ -654,9 +654,9 @@ tc_mkRepTy gk get_fixity dit@(DerivInstTys{ dit_rep_tc = tycon ctFix c | dataConIsInfix c = case get_fixity (dataConName c) of - Fixity _ n InfixL -> buildFix n pLA - Fixity _ n InfixR -> buildFix n pRA - Fixity _ n InfixN -> buildFix n pNA + Fixity n InfixL -> buildFix n pLA + Fixity n InfixR -> buildFix n pRA + Fixity n InfixN -> buildFix n pNA | otherwise = mkTyConTy pPrefix buildFix n assoc = mkTyConApp pInfix [ mkTyConTy assoc , mkNumLitTy (fromIntegral n)] ===================================== compiler/GHC/Tc/Gen/Splice.hs ===================================== @@ -2816,7 +2816,7 @@ reifyFixity name = do { (found, fix) <- lookupFixityRn_help name ; return (if found then Just (conv_fix fix) else Nothing) } where - conv_fix (Hs.Fixity _ i d) = TH.Fixity i (conv_dir d) + conv_fix (Hs.Fixity i d) = TH.Fixity i (conv_dir d) conv_dir Hs.InfixR = TH.InfixR conv_dir Hs.InfixL = TH.InfixL conv_dir Hs.InfixN = TH.InfixN ===================================== compiler/GHC/ThToHs.hs ===================================== @@ -1984,7 +1984,7 @@ cvtPatSynSigTy ty = cvtSigType ty ----------------------------------------------------------- cvtFixity :: TH.Fixity -> Hs.Fixity -cvtFixity (TH.Fixity prec dir) = Hs.Fixity NoSourceText prec (cvt_dir dir) +cvtFixity (TH.Fixity prec dir) = Hs.Fixity prec (cvt_dir dir) where cvt_dir TH.InfixL = Hs.InfixL cvt_dir TH.InfixR = Hs.InfixR ===================================== compiler/GHC/Types/Fixity.hs ===================================== @@ -16,33 +16,28 @@ where import GHC.Prelude -import GHC.Types.SourceText - import GHC.Utils.Outputable import GHC.Utils.Binary import Data.Data hiding (Fixity, Prefix, Infix) -data Fixity = Fixity SourceText Int FixityDirection - -- Note [Pragma source text] in "GHC.Types.SourceText" +data Fixity = Fixity Int FixityDirection deriving Data instance Outputable Fixity where - ppr (Fixity _ prec dir) = hcat [ppr dir, space, int prec] + ppr (Fixity prec dir) = hcat [ppr dir, space, int prec] instance Eq Fixity where -- Used to determine if two fixities conflict - (Fixity _ p1 dir1) == (Fixity _ p2 dir2) = p1==p2 && dir1 == dir2 + (Fixity p1 dir1) == (Fixity p2 dir2) = p1==p2 && dir1 == dir2 instance Binary Fixity where - put_ bh (Fixity src aa ab) = do - put_ bh src + put_ bh (Fixity aa ab) = do put_ bh aa put_ bh ab get bh = do - src <- get bh aa <- get bh ab <- get bh - return (Fixity src aa ab) + return (Fixity aa ab) ------------------------ data FixityDirection @@ -76,12 +71,12 @@ maxPrecedence = 9 minPrecedence = 0 defaultFixity :: Fixity -defaultFixity = Fixity NoSourceText maxPrecedence InfixL +defaultFixity = Fixity maxPrecedence InfixL negateFixity, funTyFixity :: Fixity -- Wired-in fixities -negateFixity = Fixity NoSourceText 6 InfixL -- Fixity of unary negate -funTyFixity = Fixity NoSourceText (-1) InfixR -- Fixity of '->', see #15235 +negateFixity = Fixity 6 InfixL -- Fixity of unary negate +funTyFixity = Fixity (-1) InfixR -- Fixity of '->', see #15235 {- Consider @@ -96,7 +91,7 @@ whether there's an error. compareFixity :: Fixity -> Fixity -> (Bool, -- Error please Bool) -- Associate to the right: a op1 (b op2 c) -compareFixity (Fixity _ prec1 dir1) (Fixity _ prec2 dir2) +compareFixity (Fixity prec1 dir1) (Fixity prec2 dir2) = case prec1 `compare` prec2 of GT -> left LT -> right ===================================== testsuite/tests/parser/should_compile/T20846.stderr ===================================== @@ -44,7 +44,9 @@ (SigD (NoExtField) (FixSig - [(AddEpAnn AnnInfix (EpaSpan { T20846.hs:3:1-6 }))] + ((,) + [(AddEpAnn AnnInfix (EpaSpan { T20846.hs:3:1-6 }))] + (NoSourceText)) (FixitySig (NoNamespaceSpecifier) [(L @@ -56,7 +58,9 @@ [])) (Unqual {OccName: ++++}))] - {Fixity: infixr 9})))) + (Fixity + (9) + (InfixR)))))) ,(L (EpAnn (EpaSpan { T20846.hs:4:1-18 }) ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -2761,7 +2761,7 @@ instance ExactPrint (Sig GhcPs) where (an0, vars',ty') <- exactVarSig an vars ty return (ClassOpSig an0 is_deflt vars' ty') - exact (FixSig an (FixitySig x names (Fixity src v fdir))) = do + exact (FixSig (an,src) (FixitySig x names (Fixity v fdir))) = do let fixstr = case fdir of InfixL -> "infixl" InfixR -> "infixr" @@ -2769,7 +2769,7 @@ instance ExactPrint (Sig GhcPs) where an0 <- markEpAnnLMS'' an lidl AnnInfix (Just fixstr) an1 <- markEpAnnLMS'' an0 lidl AnnVal (Just (sourceTextToString src (show v))) names' <- markAnnotated names - return (FixSig an1 (FixitySig x names' (Fixity src v fdir))) + return (FixSig (an1,src) (FixitySig x names' (Fixity v fdir))) exact (InlineSig an ln inl) = do an0 <- markAnnOpen an (inl_src inl) "{-# INLINE" ===================================== utils/genprimopcode/Main.hs ===================================== @@ -364,7 +364,7 @@ gen_hs_source (Info defaults entries) = prim_fixity options n = [ pprFixityDir d ++ " " ++ show i ++ " " ++ asInfix n - | OptionFixity (Just (Fixity _ i d)) <- options ] + | OptionFixity (Just (Fixity i d)) <- options ] prim_func n t = [ wrapOp n ++ " :: " ++ pprTy t, wrapOp n ++ " = " ++ funcRhs n ] ===================================== utils/genprimopcode/Parser.y ===================================== @@ -90,9 +90,9 @@ pOption : lowerName '=' false { OptionFalse $1 } | can_fail_warning '=' pPrimOpCanFailWarnFlag { OptionCanFailWarnFlag $3 } pInfix :: { Maybe Fixity } -pInfix : infix integer { Just $ Fixity NoSourceText $2 InfixN } - | infixl integer { Just $ Fixity NoSourceText $2 InfixL } - | infixr integer { Just $ Fixity NoSourceText $2 InfixR } +pInfix : infix integer { Just $ Fixity $2 InfixN } + | infixl integer { Just $ Fixity $2 InfixL } + | infixr integer { Just $ Fixity $2 InfixR } | nothing { Nothing } pEffect :: { PrimOpEffect } ===================================== utils/genprimopcode/Syntax.hs ===================================== @@ -101,16 +101,12 @@ instance Show TyCon where -- The SourceText exists so that it matches the SourceText field in -- BasicTypes.Fixity -data Fixity = Fixity SourceText Int FixityDirection +data Fixity = Fixity Int FixityDirection deriving (Eq, Show) data FixityDirection = InfixN | InfixL | InfixR deriving (Eq, Show) -data SourceText = SourceText String - | NoSourceText - deriving (Eq,Show) - data PrimOpEffect = NoEffect | CanFail ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Decl.hs ===================================== @@ -372,7 +372,7 @@ ppFixities fs qual = foldr1 (+++) (map ppFix uniq_fs) +++ rightEdge uniq_fs = [ (n, the p, the d') - | (n, Fixity _ p d) <- fs + | (n, Fixity p d) <- fs , let d' = ppDir d , then group by Down (p, d') ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Create.hs ===================================== @@ -57,7 +57,6 @@ import Data.Traversable (for) import Control.Arrow (first, (&&&)) import GHC hiding (lookupName) import GHC.Builtin.Names -import GHC.Builtin.Types import GHC.Builtin.Types.Prim import GHC.Core.ConLike (ConLike (..)) import GHC.Data.FastString (FastString, bytesFS, unpackFS) @@ -65,7 +64,6 @@ import GHC.Driver.Ppr import GHC.HsToCore.Docs hiding (mkMaps) import GHC.Iface.Syntax import GHC.Types.Avail -import GHC.Types.Basic import GHC.Types.Name import GHC.Types.Name.Set import GHC.Types.SafeHaskell ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Json.hs ===================================== @@ -241,7 +241,7 @@ jsonName :: Name -> JsonDoc jsonName = JSString . nameStableString jsonFixity :: Fixity -> JsonDoc -jsonFixity (Fixity _ prec dir) = +jsonFixity (Fixity prec dir) = jsonObject [ ("prec", jsonInt prec) , ("direction", jsonFixityDirection dir) ===================================== utils/haddock/haddock-api/src/Haddock/Types.hs ===================================== @@ -978,8 +978,8 @@ instance NFData FixityDirection where rnf InfixN = () instance NFData Fixity where - rnf (Fixity sourceText n dir) = - sourceText `deepseq` n `deepseq` dir `deepseq` () + rnf (Fixity n dir) = + n `deepseq` dir `deepseq` () instance NFData (EpAnn NameAnn) where rnf (EpAnn en ann cs) = en `deepseq` ann `deepseq` cs `deepseq` () View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b0300503806331e6a4d48733222c71a52da884cf -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b0300503806331e6a4d48733222c71a52da884cf You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 10:49:14 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 19 Jun 2024 06:49:14 -0400 Subject: [Git][ghc/ghc][master] base: Deprecate some .Internal modules Message-ID: <6672b7aa32317_17fcd51255ad46815c@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00 base: Deprecate some .Internal modules Deprecates the following modules according to clc-proposal #217: https://github.com/haskell/core-libraries-committee/issues/217 * GHC.TypeNats.Internal * GHC.TypeLits.Internal * GHC.ExecutionStack.Internal Closes #24998 - - - - - 3 changed files: - libraries/base/src/GHC/ExecutionStack/Internal.hs - libraries/base/src/GHC/TypeLits/Internal.hs - libraries/base/src/GHC/TypeNats/Internal.hs Changes: ===================================== libraries/base/src/GHC/ExecutionStack/Internal.hs ===================================== @@ -16,7 +16,7 @@ -- -- @since 4.9.0.0 -module GHC.ExecutionStack.Internal ( +module GHC.ExecutionStack.Internal {-# DEPRECATED "This module will be removed from base in the next version (v4.22)" #-} ( -- * Internal Location (..) , SrcLoc (..) ===================================== libraries/base/src/GHC/TypeLits/Internal.hs ===================================== @@ -26,7 +26,7 @@ -- -- @since 4.16.0.0 -module GHC.TypeLits.Internal +module GHC.TypeLits.Internal {-# DEPRECATED "This module will be removed from base in the next version (v4.22)" #-} (Symbol, CmpSymbol, CmpChar ===================================== libraries/base/src/GHC/TypeNats/Internal.hs ===================================== @@ -1,7 +1,7 @@ {-# LANGUAGE Safe #-} {-# OPTIONS_HADDOCK not-home #-} -module GHC.TypeNats.Internal +module GHC.TypeNats.Internal {-# DEPRECATED "This module will be removed from base in the next version (v4.22)" #-} (Natural, CmpNat ) where View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/842e119b559931859556f42ed4b9a7c453a34cbe -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/842e119b559931859556f42ed4b9a7c453a34cbe You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 10:51:27 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 19 Jun 2024 06:51:27 -0400 Subject: [Git][ghc/ghc][wip/T24725] 4130 commits: [haddock @ 2002-04-04 16:23:43 by simonmar] Message-ID: <6672b82feb717_17fcd51470a307002e@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24725 at Glasgow Haskell Compiler / GHC Commits: 2b39cd94 by Simon Marlow at 2002-04-04T16:23:43+00:00 [haddock @ 2002-04-04 16:23:43 by simonmar] This is Haddock, my stab at a Haskell documentation tool. It's not quite ready for release yet, but I'm putting it in the repository so others can take a look. It uses a locally modified version of the hssource parser, extended with support for GHC extensions and documentation annotations. - - - - - 99ede94f by Simon Marlow at 2002-04-04T16:24:10+00:00 [haddock @ 2002-04-04 16:24:10 by simonmar] forgot one file - - - - - 8363294c by Simon Marlow at 2002-04-05T13:58:15+00:00 [haddock @ 2002-04-05 13:58:15 by simonmar] Remap names in the exported declarations to be "closer" to the current module. eg. if an exported declaration mentions a type 'T' which is imported from module A then re-exported from the current module, then links from the type or indeed the documentation will point to the current module rather than module A. This is to support better hiding: module A won't be referred to in the generated output. - - - - - 1570cbc1 by Simon Marlow at 2002-04-05T13:58:23+00:00 [haddock @ 2002-04-05 13:58:23 by simonmar] update the TODO list - - - - - 3a62f96b by Simon Marlow at 2002-04-05T14:11:51+00:00 [haddock @ 2002-04-05 14:11:51 by simonmar] Fix the anchor for a class declaration - - - - - c5d9a471 by Simon Marlow at 2002-04-05T14:18:41+00:00 [haddock @ 2002-04-05 14:18:41 by simonmar] remove underlines on visited links - - - - - 97280525 by Simon Marlow at 2002-04-05T16:11:47+00:00 [haddock @ 2002-04-05 16:11:47 by simonmar] - Update to generate more correct HTML. - Use our own non-overloaded table combinators, as the overloaded versions were giving me a headache. The improved type safety caught several errors in the HTML generation. - - - - - 9acd3a4d by Simon Marlow at 2002-04-05T16:32:19+00:00 [haddock @ 2002-04-05 16:32:19 by simonmar] Add width property to the title, and add TD.children for the module contents page. - - - - - ec9a0847 by Simon Marlow at 2002-04-08T16:39:56+00:00 [haddock @ 2002-04-08 16:39:56 by simonmar] Fix a problem with exports of the form T(..). - - - - - e4627dc8 by Simon Marlow at 2002-04-08T16:41:38+00:00 [haddock @ 2002-04-08 16:41:37 by simonmar] - Add our own versions of Html & BlockTable for the time being. - Add support for generating an index to the HTML backend - - - - - 2d73fd75 by Simon Marlow at 2002-04-09T11:23:24+00:00 [haddock @ 2002-04-09 11:23:24 by simonmar] Add '-- /' as a synonym for '-- |', for compatibility with IDoc. - - - - - 3675464e by Simon Marlow at 2002-04-09T11:33:55+00:00 [haddock @ 2002-04-09 11:33:54 by simonmar] - add the <...> syntax for marking up URLs in documentation - Make the output for data & class declarations more compact when there aren't any documentation annotations on the individual methods or constructors respectively. - - - - - 5077f5b1 by Simon Marlow at 2002-04-09T11:36:04+00:00 [haddock @ 2002-04-09 11:36:04 by simonmar] Update the TODO list - - - - - 9e83c54d by Simon Marlow at 2002-04-10T10:50:06+00:00 [haddock @ 2002-04-10 10:50:06 by simonmar] Use explicit 'px' suffix on pixel sizes; IE seems to prefer them - - - - - 052de51c by Simon Marlow at 2002-04-10T13:23:13+00:00 [haddock @ 2002-04-10 13:23:13 by simonmar] Lex URLs as a single token to avoid having to escape special characters inside the URL string. - - - - - 47187edb by Simon Marlow at 2002-04-10T13:23:55+00:00 [haddock @ 2002-04-10 13:23:55 by simonmar] Not sure why I made the constructor name for a record declaration into a TyCls name, but change it back into a Var name anyhow. - - - - - 3dc6aa81 by Simon Marlow at 2002-04-10T13:26:10+00:00 [haddock @ 2002-04-10 13:26:09 by simonmar] Lots of changes, including: - add index support to the HTML backend - clean up the renamer, put it into a monad - propogate unresolved names to the top level and report them in a nicer way - various bugfixes - - - - - c2a70a72 by Simon Marlow at 2002-04-10T13:32:39+00:00 [haddock @ 2002-04-10 13:32:39 by simonmar] Skeleton documentation - - - - - 50c98d17 by Simon Marlow at 2002-04-10T13:37:23+00:00 [haddock @ 2002-04-10 13:37:23 by simonmar] Update the TODO list, separate into pre-1.0 and post-1.0 items - - - - - f3778be6 by Simon Marlow at 2002-04-10T14:30:58+00:00 [haddock @ 2002-04-10 14:30:58 by simonmar] Add an introduction - - - - - cfbaf9f7 by Simon Marlow at 2002-04-10T14:59:51+00:00 [haddock @ 2002-04-10 14:59:51 by simonmar] Sort the module tree - - - - - 76bd7b34 by Simon Marlow at 2002-04-10T15:50:11+00:00 [haddock @ 2002-04-10 15:50:10 by simonmar] Generate a little table of contents at the top of the module doc (only if the module actually contains some section headings, though). - - - - - bb8560a1 by Simon Marlow at 2002-04-10T16:10:26+00:00 [haddock @ 2002-04-10 16:10:26 by simonmar] Now we understand (or at least don't barf on) type signatures in patterns such as you might find when scoped type variables are in use. - - - - - 86c2a026 by Simon Marlow at 2002-04-10T16:10:49+00:00 [haddock @ 2002-04-10 16:10:49 by simonmar] more updates - - - - - 1c052b0e by Simon Marlow at 2002-04-10T16:28:05+00:00 [haddock @ 2002-04-10 16:28:05 by simonmar] Parse errors in doc strings are now reported as warnings rather that causing the whole thing to fall over. It still needs cleaning up (the warning is emitted with trace) but this will do for the time being. - - - - - ace03e8f by Simon Marlow at 2002-04-10T16:38:03+00:00 [haddock @ 2002-04-10 16:38:03 by simonmar] update again - - - - - 69006c3e by Simon Marlow at 2002-04-11T13:38:02+00:00 [haddock @ 2002-04-11 13:38:02 by simonmar] mention Opera - - - - - fe9b10f8 by Simon Marlow at 2002-04-11T13:40:31+00:00 [haddock @ 2002-04-11 13:40:30 by simonmar] - copy haddock.css into the same place as the generated HTML - new option: --css <file> specifies the style sheet to use - new option: -o <dir> specifies the directory in which to generate the output. - because Haddock now needs to know where to find its default stylesheet, we have to have a wrapper script and do the haddock-inplace thing (Makefile code copied largely from fptools/happy). - - - - - 106adbbe by Simon Marlow at 2002-04-24T15:12:41+00:00 [haddock @ 2002-04-24 15:12:41 by simonmar] Stop slurping comment lines when we see a row of dashes longer than length 2: these are useful as separators. - - - - - 995d3f9e by Simon Marlow at 2002-04-24T15:14:12+00:00 [haddock @ 2002-04-24 15:14:11 by simonmar] Grok the kind of module headers we use in fptools/libraries, and pass the "portability", "stability", and "maintainer" strings through into the generated HTML. If the module header doesn't match the pattern, then we don't include the info in the HTML. - - - - - e14da136 by Simon Marlow at 2002-04-24T15:16:57+00:00 [haddock @ 2002-04-24 15:16:57 by simonmar] Done module headers now. - - - - - 2ca8dfd4 by Simon Marlow at 2002-04-24T15:57:48+00:00 [haddock @ 2002-04-24 15:57:47 by simonmar] Handle gcons in export lists (a common extension). - - - - - 044cea81 by Simon Marlow at 2002-04-25T14:20:12+00:00 [haddock @ 2002-04-25 14:20:12 by simonmar] Add the little lambda icon - - - - - 63955027 by Simon Marlow at 2002-04-25T14:40:05+00:00 [haddock @ 2002-04-25 14:40:05 by simonmar] - Add support for named chunks of documentation which can be referenced from the export list. - Copy the icon from $libdir to the destination in HTML mode. - - - - - 36e3f913 by Simon Marlow at 2002-04-25T16:48:36+00:00 [haddock @ 2002-04-25 16:48:36 by simonmar] More keyboard bashing - - - - - 7ae18dd0 by Simon Marlow at 2002-04-26T08:43:33+00:00 [haddock @ 2002-04-26 08:43:33 by simonmar] Package util reqd. to compile with 4.08.2 - - - - - bbd5fbab by Simon Marlow at 2002-04-26T10:13:00+00:00 [haddock @ 2002-04-26 10:13:00 by simonmar] Include $(GHC_HAPPY_OPTS) when compiling HsParser - - - - - 31c53d79 by Simon Marlow at 2002-04-26T11:18:57+00:00 [haddock @ 2002-04-26 11:18:56 by simonmar] - support for fundeps (partially contributed by Brett Letner - thanks Brett). - make it build with GHC 4.08.2 - - - - - c415ce76 by Simon Marlow at 2002-04-26T13:15:02+00:00 [haddock @ 2002-04-26 13:15:02 by simonmar] Move the explicit formatting of the little table for the stability/portability/maintainer info from the HTML into the CSS, and remove the explicit table size (just right-align it). - - - - - 520ee21a by Simon Marlow at 2002-04-26T16:01:44+00:00 [haddock @ 2002-04-26 16:01:44 by simonmar] Yet more keyboard bashing - this is pretty much complete now. - - - - - 2ae37179 by Simon Marlow at 2002-04-26T16:02:14+00:00 [haddock @ 2002-04-26 16:02:14 by simonmar] Add a couple of things I forgot about - - - - - b7211e04 by Simon Marlow at 2002-04-29T15:28:12+00:00 [haddock @ 2002-04-29 15:28:12 by simonmar] bugfix for declBinders on a NewTypeDecl - - - - - 640c154a by Simon Marlow at 2002-04-29T15:28:54+00:00 [haddock @ 2002-04-29 15:28:54 by simonmar] Allow '-- |' style annotations on constructors and record fields. - - - - - 393f258a by Simon Marlow at 2002-04-29T15:37:32+00:00 [haddock @ 2002-04-29 15:37:32 by simonmar] syntax fix - - - - - 8a2c2549 by Simon Marlow at 2002-04-29T15:37:48+00:00 [haddock @ 2002-04-29 15:37:48 by simonmar] Add an example - - - - - db88f8a2 by Simon Marlow at 2002-04-29T15:55:46+00:00 [haddock @ 2002-04-29 15:55:46 by simonmar] remove a trace - - - - - 2b0248e0 by Simon Marlow at 2002-04-29T15:56:19+00:00 [haddock @ 2002-04-29 15:56:19 by simonmar] Fix for 'make install' - - - - - 120453a0 by Simon Marlow at 2002-04-29T15:56:39+00:00 [haddock @ 2002-04-29 15:56:39 by simonmar] Install the auxilliary bits - - - - - 950e6dbb by Simon Marlow at 2002-04-29T15:57:30+00:00 [haddock @ 2002-04-29 15:57:30 by simonmar] Add BinDist bits - - - - - 154b9d71 by Simon Marlow at 2002-05-01T11:02:52+00:00 [haddock @ 2002-05-01 11:02:52 by simonmar] update - - - - - ba6c39fa by Simon Marlow at 2002-05-01T11:03:26+00:00 [haddock @ 2002-05-01 11:03:26 by simonmar] Add another item - - - - - bacb5e33 by Simon Marlow at 2002-05-03T08:50:00+00:00 [haddock @ 2002-05-03 08:50:00 by simonmar] Fix some typos. - - - - - 54c87895 by Sven Panne at 2002-05-05T19:40:51+00:00 [haddock @ 2002-05-05 19:40:51 by panne] As a temporary hack/workaround for a bug in GHC's simplifier, don't pass Happy the -c option for generating the parsers in this subdir. Furthermore, disable -O for HaddocParse, too. - - - - - e6c08703 by Simon Marlow at 2002-05-06T09:51:10+00:00 [haddock @ 2002-05-06 09:51:10 by simonmar] Add RPM spec file (thanks to Tom Moertel <tom-rpms at moertel.com>) - - - - - 7b8fa8e7 by Simon Marlow at 2002-05-06T12:29:26+00:00 [haddock @ 2002-05-06 12:29:26 by simonmar] Add missing type signature (a different workaround for the bug in GHC's simplifier). - - - - - cd0e300d by Simon Marlow at 2002-05-06T12:30:09+00:00 [haddock @ 2002-05-06 12:30:09 by simonmar] Remove workaround for simplifier bug in previous revision. - - - - - 687e68fa by Simon Marlow at 2002-05-06T12:32:32+00:00 [haddock @ 2002-05-06 12:32:32 by simonmar] Allow empty data declarations (another GHC extension). - - - - - 8f29f696 by Simon Marlow at 2002-05-06T12:49:21+00:00 [haddock @ 2002-05-06 12:49:21 by simonmar] Fix silly bug in named documentation block lookup. - - - - - 8e0059af by Simon Marlow at 2002-05-06T13:02:42+00:00 [haddock @ 2002-05-06 13:02:42 by simonmar] Add another named chunk with a different name - - - - - 68f8a896 by Simon Marlow at 2002-05-06T13:32:32+00:00 [haddock @ 2002-05-06 13:32:32 by simonmar] Be more lenient about extra paragraph breaks - - - - - 65fc31db by Simon Marlow at 2002-05-07T15:36:36+00:00 [haddock @ 2002-05-07 15:36:36 by simonmar] DocEmpty is a right and left-unit of DocAppend (remove it in the smart constructor). - - - - - adc81078 by Simon Marlow at 2002-05-07T15:37:15+00:00 [haddock @ 2002-05-07 15:37:15 by simonmar] Allow code blocks to be denoted with bird-tracks in addition to [...]. - - - - - 1283a3c1 by Simon Marlow at 2002-05-08T11:21:56+00:00 [haddock @ 2002-05-08 11:21:56 by simonmar] Add a facility for specifying options that affect Haddock's treatment of the module. Options are given at the top of the module in a comma-separated list, beginning with '-- #'. eg. -- # prune, hide, ignore-exports Options currently available, with their meanings: prune: ignore declarations which have no documentation annotations ignore-exports: act as if the export list were not specified (i.e. export everything local to the module). hide: do not include this module in the generated documentation, but propagate any exported definitions to modules which re-export them. There's a slight change in the semantics for re-exporting a full module by giving 'module M' in the export list: if module M does not have the 'hide' option, then the documentation will now just contain a reference to module M rather than the full inlined contents of that module. These features, and some other changes in the pipeline, are the result of discussions between myself and Manuel Chakravarty <chak at cse.unsw.edu.au> (author of IDoc) yesterday. Also: some cleanups, use a Writer monad to collect error messages in some places instead of just printing them with trace. - - - - - a2239cf5 by Simon Marlow at 2002-05-08T11:22:30+00:00 [haddock @ 2002-05-08 11:22:30 by simonmar] Update to test new features. - - - - - 6add955f by Simon Marlow at 2002-05-08T13:37:25+00:00 [haddock @ 2002-05-08 13:37:25 by simonmar] Change the markup for typewriter-font from [...] to @... at . The reasoning is that the '@' symbol is much less likely to be needed than square brackets, and we don't want to have to escape square brackets in code fragments. This will be mildly painful in the short term, but it's better to get the change out of the way as early as possible. - - - - - cda06447 by Simon Marlow at 2002-05-08T13:39:56+00:00 [haddock @ 2002-05-08 13:39:56 by simonmar] Allow nested-style comments to be used as documentation annotations too. eg. {-| ... -} is equivalent to -- | ... An extra space can also be left after the comment opener: {- | ... -}. The only version that isn't allowed is {-# ... -}, because this syntax overlaps with Haskell pragmas; use {- # ... -} instead. - - - - - db23f65e by Simon Marlow at 2002-05-08T14:48:41+00:00 [haddock @ 2002-05-08 14:48:39 by simonmar] Add support for existential quantifiers on constructors. - - - - - adce3794 by Simon Marlow at 2002-05-08T15:43:25+00:00 [haddock @ 2002-05-08 15:43:25 by simonmar] update - - - - - 62a1f436 by Simon Marlow at 2002-05-08T15:44:10+00:00 [haddock @ 2002-05-08 15:44:10 by simonmar] Update to version 0.2 - - - - - f6a24ba3 by Simon Marlow at 2002-05-09T08:48:29+00:00 [haddock @ 2002-05-09 08:48:29 by simonmar] typo - - - - - 9f9522a4 by Simon Marlow at 2002-05-09T10:33:14+00:00 [haddock @ 2002-05-09 10:33:14 by simonmar] oops, left out '/' from the special characters in the last change. - - - - - 14abcb39 by Simon Marlow at 2002-05-09T10:34:44+00:00 [haddock @ 2002-05-09 10:34:44 by simonmar] Fix buglet - - - - - b8d878be by Simon Marlow at 2002-05-09T10:35:00+00:00 [haddock @ 2002-05-09 10:35:00 by simonmar] Give a more useful instance of Show for Module. - - - - - f7bfd626 by Simon Marlow at 2002-05-09T10:37:07+00:00 [haddock @ 2002-05-09 10:37:07 by simonmar] The last commit to Main.lhs broke the delicate balance of laziness which was being used to avoid computing the dependency graph of modules. So I finally bit the bullet and did a proper topological sort of the module graph, which turned out to be easy (stealing the Digraph module from GHC - this really ought to be in the libraries somewhere). - - - - - b481c1d0 by Simon Marlow at 2002-05-09T10:37:25+00:00 [haddock @ 2002-05-09 10:37:25 by simonmar] another item done - - - - - 032e2b42 by Simon Marlow at 2002-05-09T10:44:15+00:00 [haddock @ 2002-05-09 10:44:15 by simonmar] Don't consider a module re-export as having documentation, for the purposes of deciding whether we need a Synopsis section or not. - - - - - 5fb45e92 by Simon Marlow at 2002-05-09T11:10:55+00:00 [haddock @ 2002-05-09 11:10:55 by simonmar] Add a special case for list types in ppHsAType - - - - - 1937e428 by Simon Marlow at 2002-05-09T12:43:06+00:00 [haddock @ 2002-05-09 12:43:06 by simonmar] Type synonyms can accept a ctype on the RHS, to match GHC. - - - - - 0f16ce56 by Simon Marlow at 2002-05-09T12:45:19+00:00 [haddock @ 2002-05-09 12:45:19 by simonmar] Add 'stdcall' keyword - - - - - 29b0d7d2 by Simon Marlow at 2002-05-09T13:35:45+00:00 [haddock @ 2002-05-09 13:35:45 by simonmar] Add System Requirements section - - - - - bf14dddd by Simon Marlow at 2002-05-09T13:36:11+00:00 [haddock @ 2002-05-09 13:36:11 by simonmar] Test existential types, amongst other things - - - - - 502f8f6f by Simon Marlow at 2002-05-09T13:37:35+00:00 [haddock @ 2002-05-09 13:37:35 by simonmar] Print the module name in a doc-string parse error - - - - - ca1f8d49 by Simon Marlow at 2002-05-09T13:38:04+00:00 [haddock @ 2002-05-09 13:38:04 by simonmar] Add dependency - - - - - 8d3d91ff by Simon Marlow at 2002-05-09T15:37:57+00:00 [haddock @ 2002-05-09 15:37:57 by simonmar] Add the changelog/release notes - - - - - f3960959 by Simon Marlow at 2002-05-09T15:47:47+00:00 [haddock @ 2002-05-09 15:47:47 by simonmar] mention the backquote-style of markup - - - - - 089fb6e6 by Simon Marlow at 2002-05-09T15:59:45+00:00 [haddock @ 2002-05-09 15:59:45 by simonmar] update - - - - - bdd3be0b by Simon Marlow at 2002-05-09T15:59:56+00:00 [haddock @ 2002-05-09 15:59:56 by simonmar] Document changes since 0.1 - - - - - 00fc4af8 by Simon Marlow at 2002-05-10T08:22:48+00:00 [haddock @ 2002-05-10 08:22:48 by simonmar] oops, update to version 0.2 - - - - - a8a79041 by Simon Marlow at 2002-05-10T16:05:08+00:00 [haddock @ 2002-05-10 16:05:08 by simonmar] Only include a mini-contents if there are 2 or more sections - - - - - 06653319 by Simon Marlow at 2002-05-13T09:13:12+00:00 [haddock @ 2002-05-13 09:13:12 by simonmar] fix typos - - - - - 1402b19b by Simon Marlow at 2002-05-13T10:14:22+00:00 [haddock @ 2002-05-13 10:14:22 by simonmar] Allow backquote as the right-hand quote as well as the left-hand quote, as suggested by Dean Herrington. Clean up the grammar a litte. - - - - - dcd5320d by Simon Marlow at 2002-05-13T10:44:10+00:00 [haddock @ 2002-05-13 10:44:10 by simonmar] a couple more things, prioritise a bit - - - - - a90130c4 by Simon Marlow at 2002-05-13T15:19:03+00:00 [haddock @ 2002-05-13 15:19:03 by simonmar] Cope with datatypes which have documentation on the constructor but not the type itself, and records which have documentation on the fields but not the constructor. (Thanks to Ross Paterson for pointing out the bugs). - - - - - a774d432 by Simon Marlow at 2002-05-13T15:20:54+00:00 [haddock @ 2002-05-13 15:20:54 by simonmar] Fix one of the record examples - - - - - 2d1d5218 by Simon Marlow at 2002-05-15T12:44:35+00:00 [haddock @ 2002-05-15 12:44:35 by simonmar] Preserve the newline before a bird-track, but only within a paragraph. - - - - - 1554c09a by Simon Marlow at 2002-05-15T13:03:02+00:00 [haddock @ 2002-05-15 13:03:01 by simonmar] Reworking of the internals to support documenting function arguments (the Most Wanted new feature by the punters). The old method of keeping parsed documentation in a Name -> Doc mapping wasn't going to cut it for anntations on type components, where there's no name to attach the documentation to, so I've moved to storing all the documentation in the abstract syntax. Previously some of the documentation was left in the abstract syntax by the parser, but was later extracted into the mapping. In order to avoid having to parameterise the abstract syntax over the type of documentation stored in it, we have to parse the documentation at the same time as we parse the Haskell source (well, I suppose we could store 'Either String Doc' in the HsSyn, but that's clunky). One upshot is that documentation is now parsed eagerly, and documentation parse errors are fatal (but have better line numbers in the error message). The new story simplifies matters for the code that processes the source modules, because we don't have to maintain the extra Name->Doc mapping, and it should improve efficiency a little too. New features: - Function arguments and return values can now have doc annotations. - If you refer to a qualified name in a doc string, eg. 'IO.putStr', then Haddock will emit a hyperlink even if the identifier is not in scope, so you don't have to make sure everything referred to from the documentation is imported. - several bugs & minor infelicities fixed. - - - - - 57344dc3 by Simon Marlow at 2002-05-15T13:03:19+00:00 [haddock @ 2002-05-15 13:03:19 by simonmar] Bump to version 0.3 - - - - - b2791812 by Simon Marlow at 2002-05-15T13:03:41+00:00 [haddock @ 2002-05-15 13:03:41 by simonmar] update - - - - - fead183e by Simon Marlow at 2002-05-15T13:10:15+00:00 [haddock @ 2002-05-15 13:10:15 by simonmar] Rename Foo.hs to Test.hs, and add a Makefile - - - - - b0b1f89f by Simon Marlow at 2002-05-15T13:16:07+00:00 [haddock @ 2002-05-15 13:16:07 by simonmar] - Remove the note about function argument docs not being implemented - Note that qualified identifiers can be used to point to entities that aren't in scope. - - - - - 5665f31a by Simon Marlow at 2002-05-15T13:28:46+00:00 [haddock @ 2002-05-15 13:28:46 by simonmar] Patch to add support for GHC-style primitive strings ".."#, from Ross Paterson. - - - - - 0564505d by Simon Marlow at 2002-05-17T10:51:57+00:00 [haddock @ 2002-05-17 10:51:57 by simonmar] Fix bugs in qualified name handling (A.B.f was returned as B.f) - - - - - 10e7311c by Simon Marlow at 2002-05-21T10:24:52+00:00 [haddock @ 2002-05-21 10:24:52 by simonmar] - Use an alternate tabular layout for datatypes, which is more compact - Fix some problems with the function argument documentation - - - - - 2f91c2a6 by Simon Marlow at 2002-05-21T10:27:40+00:00 [haddock @ 2002-05-21 10:27:40 by simonmar] add a few more test cases - - - - - 01c2ddd2 by Simon Marlow at 2002-05-21T10:28:33+00:00 [haddock @ 2002-05-21 10:28:33 by simonmar] Rearrange a bit, and add support for tabular datatype rendering - - - - - a4e4c5f8 by Simon Marlow at 2002-05-27T09:03:52+00:00 [haddock @ 2002-05-27 09:03:51 by simonmar] Lots of changes: - instances of a class are listed with the class, and instances involving a datatype are listed with that type. Derived instances aren't included at the moment: the calculation to find the instance head for a derived instance is non-trivial. - some formatting changes; use rows with specified height rather than cellspacing in some places. - various fixes (source file links were wrong, amongst others) - - - - - 48722e68 by Simon Marlow at 2002-05-27T12:30:38+00:00 [haddock @ 2002-05-27 12:30:37 by simonmar] - Put function arguments *before* the doc for the function, as suggested by Sven Panne. This looks nicer when the function documentation is long. - Switch to using bold for binders at the definition site, and use underline for keywords. This makes the binder stand out more. - - - - - 657204d2 by Simon Marlow at 2002-05-27T13:19:49+00:00 [haddock @ 2002-05-27 13:19:49 by simonmar] Fix bug: we weren't renaming HsDocCommentNamed in renameDecl - - - - - 592aae66 by Simon Marlow at 2002-05-27T14:10:27+00:00 [haddock @ 2002-05-27 14:10:27 by simonmar] Fix some bugs in the rendering of qualified type signatures. - - - - - 69c8f763 by Simon Marlow at 2002-05-27T14:36:45+00:00 [haddock @ 2002-05-27 14:36:45 by simonmar] warning message tweak - - - - - 16e64e21 by Simon Marlow at 2002-05-27T14:53:53+00:00 [haddock @ 2002-05-27 14:53:53 by simonmar] hyperlinked identifiers should be in <tt> - - - - - 8d5e4783 by Simon Marlow at 2002-05-27T15:56:45+00:00 [haddock @ 2002-05-27 15:56:45 by simonmar] Do something sensible for modules which don't export anything (except instances). - - - - - 9d3ef811 by Simon Marlow at 2002-05-28T10:12:50+00:00 [haddock @ 2002-05-28 10:12:50 by simonmar] Rename the module documentation properly (bug reported by Sven Panne). - - - - - ef03a1cc by Simon Marlow at 2002-05-28T10:13:04+00:00 [haddock @ 2002-05-28 10:13:04 by simonmar] Add some more test cases - - - - - 92baa0e8 by Simon Marlow at 2002-05-28T11:17:55+00:00 [haddock @ 2002-05-28 11:17:55 by simonmar] If an identifier doesn't lex, then just replace it by a DocString. - - - - - a3156213 by Simon Marlow at 2002-05-28T16:16:19+00:00 [haddock @ 2002-05-28 16:16:19 by simonmar] Only link to names in the current module which are actually listed in the documentation. A name may be exported but not present in the documentation if it is exported as part of a 'module M' export specifier. - - - - - 31acf941 by Simon Marlow at 2002-05-28T16:17:11+00:00 [haddock @ 2002-05-28 16:17:11 by simonmar] update - - - - - 7e474ebf by Sigbjorn Finne at 2002-05-28T22:42:08+00:00 [haddock @ 2002-05-28 22:42:08 by sof] Handle lone occurrences of '/', e.g., -- | This/that. [did this in the lexer rather than in the parser, as I couldn't see a way not to introduce an S/R conflict that way.] - - - - - 093f7e53 by Simon Marlow at 2002-05-29T09:09:49+00:00 [haddock @ 2002-05-29 09:09:49 by simonmar] Back out previous change until we can find a better way to do this. - - - - - 9234389c by Simon Marlow at 2002-05-29T13:19:06+00:00 [haddock @ 2002-05-29 13:19:06 by simonmar] Make the markup syntax a little more friendly: - single quotes are now interpreted literally unless they surround a valid Haskell identifier. So for example now there's no need to escape a single quote used as an apostrophe. - text to the right of a bird track is now literal (if you want marked-up text in a code block, use @...@). - - - - - b3333526 by Simon Marlow at 2002-05-29T13:38:51+00:00 [haddock @ 2002-05-29 13:38:51 by simonmar] Document recent changes to markup syntax - - - - - f93641d6 by Simon Marlow at 2002-05-29T15:27:18+00:00 [haddock @ 2002-05-29 15:27:18 by simonmar] Include the instances in abstract data types too - - - - - 613f21e3 by Simon Marlow at 2002-06-03T13:05:58+00:00 [haddock @ 2002-06-03 13:05:57 by simonmar] Allow exporting of individual class methods and record selectors. For these we have to invent the correct type signature, which we do in the simplest possible way (i.e. no context reduction nonsense in the class case). - - - - - 14b36807 by Simon Marlow at 2002-06-03T13:20:00+00:00 [haddock @ 2002-06-03 13:20:00 by simonmar] Fix linking to qualified names again (thanks to Sven Panne for pointing out the bug). - - - - - 95b10eac by Simon Marlow at 2002-06-03T13:46:48+00:00 [haddock @ 2002-06-03 13:46:48 by simonmar] Fix for exporting record selectors from a newtype declaration - - - - - 272f932e by Simon Marlow at 2002-06-03T13:56:38+00:00 [haddock @ 2002-06-03 13:56:38 by simonmar] update to version 0.3 - - - - - 1c0a3bed by Simon Marlow at 2002-06-03T14:05:07+00:00 [haddock @ 2002-06-03 14:05:07 by simonmar] Add changes in version 0.3 - - - - - 145b4626 by Simon Marlow at 2002-06-03T14:12:38+00:00 [haddock @ 2002-06-03 14:12:38 by simonmar] Render class names as proper binders - - - - - 052106b3 by Simon Marlow at 2002-06-03T14:15:10+00:00 [haddock @ 2002-06-03 14:15:10 by simonmar] update, and separate into bugs, features, and cosmetic items. - - - - - 854f4914 by Simon Marlow at 2002-06-03T14:16:13+00:00 [haddock @ 2002-06-03 14:16:13 by simonmar] More test cases - - - - - 466922c8 by Simon Marlow at 2002-06-03T14:16:56+00:00 [haddock @ 2002-06-03 14:16:56 by simonmar] Example from the paper - - - - - 9962a045 by Simon Marlow at 2002-06-03T14:17:49+00:00 [haddock @ 2002-06-03 14:17:49 by simonmar] A debugging version of the style-sheet, which gives some tables coloured backgrounds so we can see what's going on. - - - - - f16b79db by Simon Marlow at 2002-06-03T14:19:46+00:00 [haddock @ 2002-06-03 14:19:46 by simonmar] typo - - - - - 620db27b by Simon Marlow at 2002-06-03T14:48:32+00:00 [haddock @ 2002-06-03 14:48:32 by simonmar] oops, fix markup bugs - - - - - 53fd105c by Simon Marlow at 2002-06-05T09:05:07+00:00 [haddock @ 2002-06-05 09:05:07 by simonmar] Keep foreign imports when there is no export list (bug reported by Sven Panne). - - - - - 6d98989c by Simon Marlow at 2002-06-05T09:12:02+00:00 [haddock @ 2002-06-05 09:12:02 by simonmar] Identifiers in single quotes can be symbol names too (bug reported by Hal Daume). - - - - - 001811e5 by Sven Panne at 2002-06-08T14:03:36+00:00 [haddock @ 2002-06-08 14:03:36 by panne] Tiny workaround for the fact that Haddock currently ignores HsImportSpecs: Let the local_orig_env take precedence. This is no real solution at all, but improves things sometimes, e.g. in my GLUT documentation. :-) - - - - - 504d19c9 by Simon Marlow at 2002-06-11T09:23:25+00:00 [haddock @ 2002-06-11 09:23:25 by simonmar] portability nit - - - - - e13b5af4 by Simon Marlow at 2002-06-20T12:38:07+00:00 [haddock @ 2002-06-20 12:38:07 by simonmar] Empty declaration fixes. - - - - - f467a9b6 by Simon Marlow at 2002-06-20T12:39:02+00:00 [haddock @ 2002-06-20 12:39:01 by simonmar] Add support for a "prologue" - a description for the whole library, placed on the contents page before the module list. - - - - - b8dbfe20 by Simon Marlow at 2002-06-21T12:43:06+00:00 [haddock @ 2002-06-21 12:43:06 by simonmar] When we have a single code block paragraph, don't place it in <pre>..</pre>, just use <tt>..</tt> to avoid generating extra vertical white space in some browsers. - - - - - 4831dbbd by Simon Marlow at 2002-06-21T15:50:42+00:00 [haddock @ 2002-06-21 15:50:42 by simonmar] Add support for reading and writing interface files(!) This turned out to be quite easy, and necessary to get decent hyperlinks between the documentation for separate packages in the libraries. The functionality isn't quite complete yet: for a given package of modules, you'd like to say "the HTML for these modules lives in directory <dir>" (currently they are assumed to be all in the same place). Two new flags: --dump-interface=FILE dump an interface file in FILE --read-interface=FILE read interface from FILE an interface file describes *all* the modules being processed. Only the exported names are kept in the interface: if you re-export a name from a module in another interface the signature won't be copied. This is a compromise to keep the size of the interfaces sensible. Also, I added another useful option: --no-implicit-prelude avoids trying to import the Prelude. Previously this was the default, but now importing the Prelude from elsewhere makes sense if you also read in an interface containing the Prelude module, so Haddock imports the Prelude implicitly according to the Haskell spec. - - - - - d3640a19 by Sven Panne at 2002-06-23T14:54:00+00:00 [haddock @ 2002-06-23 14:54:00 by panne] Make it compile with newer GHCs - - - - - 780c506b by Sven Panne at 2002-06-23T15:44:31+00:00 [haddock @ 2002-06-23 15:44:31 by panne] Cleaned up build root handling and added more docs - - - - - 45290d2e by Simon Marlow at 2002-06-24T14:37:43+00:00 [haddock @ 2002-06-24 14:37:42 by simonmar] When reading an interface, allow a file path offset to be specified which represents the path to the HTML files for the modules specified by that interface. The path may be either relative (to the location of the HTML for this package), or absolute. The syntax is --read-interface=PATH,FILE where PATH is the path to the HTML, and FILE is the filename containing the interface. - - - - - 4e2b9ae6 by Simon Marlow at 2002-07-03T16:01:08+00:00 [haddock @ 2002-07-03 16:01:07 by simonmar] Handle import specs properly, include 'hiding'. Haddock now has a complete implementation of the Haskell module system (more or less; I won't claim it's 100% correct). - - - - - 9a9aa1a8 by Simon Marlow at 2002-07-03T16:18:16+00:00 [haddock @ 2002-07-03 16:18:16 by simonmar] Update - - - - - 560c3026 by Simon Marlow at 2002-07-04T14:56:10+00:00 [haddock @ 2002-07-04 14:56:10 by simonmar] Clean up the code that constructs the exported declarations, and fix a couple of bugs along the way. Now if you import a class hiding one of the methods, then re-export the class, the version in the documentation will correctly have the appropriate method removed. - - - - - 2c26e77d by Simon Marlow at 2002-07-04T15:26:13+00:00 [haddock @ 2002-07-04 15:26:13 by simonmar] More bugfixes to the export handling - - - - - 03e0710d by Simon Marlow at 2002-07-09T10:12:10+00:00 [haddock @ 2002-07-09 10:12:10 by simonmar] Don't require that the list type comes from "Prelude" for it to be treated as special syntax (sometimes it comes from Data.List or maybe even GHC.Base). - - - - - 44f3891a by Simon Marlow at 2002-07-09T10:12:51+00:00 [haddock @ 2002-07-09 10:12:51 by simonmar] commented-out debugging code - - - - - 97280873 by Krasimir Angelov at 2002-07-09T16:33:33+00:00 [haddock @ 2002-07-09 16:33:31 by krasimir] 'Microsoft HTML Help' support - - - - - 3dc04655 by Simon Marlow at 2002-07-10T09:40:56+00:00 [haddock @ 2002-07-10 09:40:56 by simonmar] Fix for rendering of the (->) type constructor, from Ross Paterson. - - - - - c9f149c6 by Simon Marlow at 2002-07-10T10:26:11+00:00 [haddock @ 2002-07-10 10:26:11 by simonmar] Tweaks to the MS Help support: the extra files are now only generated if you ask for them (--ms-help). - - - - - e8acc1e6 by Simon Marlow at 2002-07-10T10:57:10+00:00 [haddock @ 2002-07-10 10:57:10 by simonmar] Document all the new options since 0.3 - - - - - 8bb85544 by Simon Marlow at 2002-07-10T10:58:31+00:00 [haddock @ 2002-07-10 10:58:31 by simonmar] Sort the options a bit - - - - - abc0dd59 by Simon Marlow at 2002-07-15T09:19:38+00:00 [haddock @ 2002-07-15 09:19:38 by simonmar] Fix a bug in mkExportItems when processing a module without an explicit export list. We were placing one copy of a declaration for each binder in the declaration, which for a data type would mean one copy of the whole declaration per constructor or record selector. - - - - - dde65bb9 by Simon Marlow at 2002-07-15T09:54:16+00:00 [haddock @ 2002-07-15 09:54:16 by simonmar] merge rev. 1.35 - - - - - bd7eb8c4 by Simon Marlow at 2002-07-15T10:14:31+00:00 [haddock @ 2002-07-15 10:14:30 by simonmar] Be a bit more liberal in the kind of commenting styles we allow, as suggested by Malcolm Wallace. Mostly this consists of allowing doc comments either side of a separator token. In an export list, a section heading is now allowed before the comma, as well as after it. eg. module M where ( T(..) -- * a section heading , f -- * another section heading , g ) In record fields, doc comments are allowed anywhere (previously a doc-next was allowed only after the comma, and a doc-before was allowed only before the comma). eg. data R = C { -- | describes 'f' f :: Int -- | describes 'g' , g :: Int } - - - - - 8f6dfe34 by Simon Marlow at 2002-07-15T10:21:56+00:00 [haddock @ 2002-07-15 10:21:56 by simonmar] Mention alternative commenting styles. - - - - - fc515bb7 by Simon Marlow at 2002-07-15T16:16:50+00:00 [haddock @ 2002-07-15 16:16:50 by simonmar] Allow multiple sections/subsections before and after a comma in the export list. Also at the same time I made the syntax a little stricter (multiple commas now aren't allowed between export specs). - - - - - 80a97e74 by Simon Marlow at 2002-07-19T09:13:10+00:00 [haddock @ 2002-07-19 09:13:10 by simonmar] Allow special id's ([], (), etc.) to be used in an import declaration. - - - - - a69d7378 by Simon Marlow at 2002-07-19T09:59:02+00:00 [haddock @ 2002-07-19 09:59:02 by simonmar] Allow special id's ([], (), etc.) to be used in an import declarations. - - - - - d205fa60 by Simon Marlow at 2002-07-19T10:00:16+00:00 [haddock @ 2002-07-19 10:00:16 by simonmar] Relax the restrictions which require doc comments to be followed by semi colons - in some cases this isn't necessary. Now you can write module M where { -- | some doc class C where {} } without needing to put a semicolon before the class declaration. - - - - - e9301e14 by Simon Marlow at 2002-07-23T08:24:09+00:00 [haddock @ 2002-07-23 08:24:09 by simonmar] A new TODO list item - - - - - e5d77586 by Simon Marlow at 2002-07-23T08:40:56+00:00 [haddock @ 2002-07-23 08:40:56 by simonmar] - update the acknowledgements - remove the paragraph that described how to use explicit layout with doc comments; it isn't relevant any more. - - - - - 78a94137 by Simon Marlow at 2002-07-23T08:43:02+00:00 [haddock @ 2002-07-23 08:43:02 by simonmar] more tests - - - - - 5c320927 by Simon Marlow at 2002-07-23T08:43:26+00:00 [haddock @ 2002-07-23 08:43:26 by simonmar] Updates for version 0.4 - - - - - 488e99ae by Simon Marlow at 2002-07-23T09:10:46+00:00 [haddock @ 2002-07-23 09:10:46 by simonmar] Fix the %changelog (rpm complained that it wasn't in the right order) - - - - - a77bb373 by Simon Marlow at 2002-07-23T09:12:38+00:00 [haddock @ 2002-07-23 09:12:38 by simonmar] Another item for the TODO list - - - - - f1ec1813 by Simon Marlow at 2002-07-23T10:18:46+00:00 [haddock @ 2002-07-23 10:18:46 by simonmar] Add a version banner when invoked with -v - - - - - 1d44cadf by Simon Marlow at 2002-07-24T09:28:19+00:00 [haddock @ 2002-07-24 09:28:19 by simonmar] Remove ^Ms - - - - - 4d8d5e94 by Simon Marlow at 2002-07-24T09:42:18+00:00 [haddock @ 2002-07-24 09:42:17 by simonmar] Patches to quieten ghc -Wall, from those nice folks at Galois. - - - - - d6edc43e by Simon Marlow at 2002-07-25T14:37:29+00:00 [haddock @ 2002-07-25 14:37:28 by simonmar] Patch to allow simple hyperlinking to an arbitrary location in another module's documentation, from Volker Stolz. Now in a doc comment: #foo# creates <a name="foo"></a> And you can use the form "M\#foo" to hyperlink to the label 'foo' in module 'M'. Note that the backslash is necessary for now. - - - - - b34d18fa by Simon Marlow at 2002-08-02T09:08:22+00:00 [haddock @ 2002-08-02 09:08:22 by simonmar] The <TT> and <PRE> environments seem to use a font that is a little too small in IE. Compensate. (suggestion from Daan Leijen). - - - - - 8106b086 by Simon Marlow at 2002-08-02T09:25:23+00:00 [haddock @ 2002-08-02 09:25:20 by simonmar] Remove <P>..</P> from around list items, to reduce excess whitespace between the items of bulleted and ordered lists. (Suggestion from Daan Leijen). - - - - - c1acff8f by Simon Marlow at 2002-08-05T09:03:49+00:00 [haddock @ 2002-08-05 09:03:49 by simonmar] update - - - - - f968661c by Simon Marlow at 2002-11-11T09:32:57+00:00 [haddock @ 2002-11-11 09:32:57 by simonmar] Fix cut-n-pasto - - - - - 12d02619 by Simon Marlow at 2002-11-13T09:49:46+00:00 [haddock @ 2002-11-13 09:49:46 by simonmar] Small bugfix in the --read-interface option parsing from Brett Letner. - - - - - 30e32d5e by Ross Paterson at 2003-01-16T15:07:57+00:00 [haddock @ 2003-01-16 15:07:57 by ross] Adjust for the new exception libraries (as well as the old ones). - - - - - 871f65df by Sven Panne at 2003-02-20T21:31:40+00:00 [haddock @ 2003-02-20 21:31:40 by panne] * Add varsyms and consyms to index * Exclude empty entries from index - - - - - bc42cc87 by Sven Panne at 2003-02-24T21:26:29+00:00 [haddock @ 2003-02-24 21:26:29 by panne] Don't convert a "newtype" to a single-constructor "data" for non-abstractly exported types, they are quite different regarding strictness/pattern matching. Now a "data" without any constructors is only emitted for an abstractly exported type, regardless if it is actually a "newtype" or a "data". - - - - - 0c2a1d99 by Sven Panne at 2003-03-08T19:02:38+00:00 [haddock @ 2003-03-08 19:02:38 by panne] Fixed some broken/redirected/canonicalized links found by a very picky link checker. - - - - - 25459269 by Sven Panne at 2003-03-09T21:13:43+00:00 [haddock @ 2003-03-09 21:13:43 by panne] Don't append a fragment to non-defining index entries, only documents with a defining occurrence have a name anchor. - - - - - 6be4db86 by Sven Panne at 2003-03-10T21:34:25+00:00 [haddock @ 2003-03-10 21:34:24 by panne] Escape fragments. This fixes e.g. links to operators. - - - - - eb12972c by Ross Paterson at 2003-04-25T10:50:06+00:00 [haddock @ 2003-04-25 10:50:05 by ross] An 80% solution to generating derived instances. A complete solution would duplicate the instance inference logic, but if a type variable occurs as a constructor argument, then we can just propagate the derived class to the variable. But we know nothing of the constraints on any type variables that occur elsewhere. For example, the declarations data Either a b = Left a | Right b deriving (Eq, Ord) data Ptr a = Ptr Addr# deriving (Eq, Ord) newtype IORef a = IORef (STRef RealWorld a) deriving Eq yield the instances (Eq a, Eq b) => Eq (Either a b) (Ord a, Ord b) => Ord (Either a b) Eq (Ptr a) Ord (Ptr a) (??? a) => Eq (IORef a) The last example shows the limits of this local analysis. Note that a type variable may be in both categories: then we know a constraint, but there may be more, or a stronger constraint, e.g. data Tree a = Node a [Tree a] deriving Eq yields (Eq a, ??? a) => Eq (Tree a) - - - - - de886f78 by Simon Marlow at 2003-04-25T11:17:55+00:00 [haddock @ 2003-04-25 11:17:55 by simonmar] Some updates, including moving the derived instance item down to the bottom of the list now that Ross has contributed some code that does the job for common cases. - - - - - 1b52cffd by Simon Marlow at 2003-04-30T14:02:32+00:00 [haddock @ 2003-04-30 14:02:32 by simonmar] When installing on Windows, run cygpath over $(HADDOCKLIB) so that haddock (a mingw program, built by GHC) can understand it. You still need to be in a cygwin environment to run Haddock, because of the shell script wrapper. - - - - - d4f638de by Simon Marlow at 2003-05-06T10:04:47+00:00 [haddock @ 2003-05-06 10:04:47 by simonmar] Catch another case of a paragraph containing just a DocMonospaced that should turn into a DocCodeBlock. - - - - - 4162b2b9 by Simon Marlow at 2003-05-06T10:11:44+00:00 [haddock @ 2003-05-06 10:11:44 by simonmar] Add some more code-block tests. - - - - - 4f5802c8 by Simon Marlow at 2003-05-06T10:14:52+00:00 [haddock @ 2003-05-06 10:14:52 by simonmar] Don't turn a single DocCodeBlock into a DocMonospaced, because that tends to remove the line breaks in the code. - - - - - ef8c45f7 by Simon Marlow at 2003-05-21T15:07:21+00:00 [haddock @ 2003-05-21 15:07:21 by simonmar] Only omit the module contents when there are no section headings at all. - - - - - bcee1e75 by Sigbjorn Finne at 2003-05-30T16:50:45+00:00 [haddock @ 2003-05-30 16:50:45 by sof] cygpath: for now, steer clear of --mixed - - - - - 30567af3 by Sigbjorn Finne at 2003-05-30T17:59:28+00:00 [haddock @ 2003-05-30 17:59:28 by sof] oops, drop test defn from prev commit - - - - - b0856e7d by Simon Marlow at 2003-06-03T09:55:26+00:00 [haddock @ 2003-06-03 09:55:26 by simonmar] Two small fixes to make the output valid HTML 4.01 (transitional). Thanks to Malcolm Wallace for pointing out the problems. - - - - - 70e137ea by Simon Marlow at 2003-07-28T13:30:35+00:00 [haddock @ 2003-07-28 13:30:35 by simonmar] Add tests for a couple of bugs. - - - - - 122bd578 by Simon Marlow at 2003-07-28T13:31:25+00:00 [haddock @ 2003-07-28 13:31:25 by simonmar] Add documentation for anchors. - - - - - 0bd27cb2 by Simon Marlow at 2003-07-28T13:31:46+00:00 [haddock @ 2003-07-28 13:31:46 by simonmar] Update - - - - - 08052d42 by Simon Marlow at 2003-07-28T13:32:12+00:00 [haddock @ 2003-07-28 13:32:12 by simonmar] layout tweak. - - - - - 13942749 by Simon Marlow at 2003-07-28T13:33:03+00:00 [haddock @ 2003-07-28 13:33:03 by simonmar] Differentiate links to types/classes from links to variables/constructors with a prefix ("t:" and "v:" respectively). - - - - - d7f493b9 by Simon Marlow at 2003-07-28T13:35:17+00:00 [haddock @ 2003-07-28 13:35:16 by simonmar] When a module A exports another module's contents via 'module B', then modules which import entities from B re-exported by A should link to B.foo rather than A.foo. See examples/Bug2.hs. - - - - - d94cf705 by Simon Marlow at 2003-07-28T13:36:14+00:00 [haddock @ 2003-07-28 13:36:14 by simonmar] Update to version 0.5 - - - - - dbb776cd by Sven Panne at 2003-07-28T14:02:43+00:00 [haddock @ 2003-07-28 14:02:43 by panne] * Updated to version 0.5 * Automagically generate configure if it is not there - - - - - 6cfeee53 by Simon Marlow at 2003-07-28T14:32:43+00:00 [haddock @ 2003-07-28 14:32:42 by simonmar] Update to avoid using hslibs with GHC >= 5.04 - - - - - a1ce838f by Simon Marlow at 2003-07-28T14:33:37+00:00 [haddock @ 2003-07-28 14:33:37 by simonmar] Update for 0.5 - - - - - c0fe6493 by Simon Marlow at 2003-07-28T14:53:22+00:00 [haddock @ 2003-07-28 14:53:22 by simonmar] Markup fix - - - - - 6ea31596 by Sven Panne at 2003-07-28T16:40:45+00:00 [haddock @ 2003-07-28 16:40:45 by panne] Make it compile with GHC >= 6.01 - - - - - afcd30fc by Simon Marlow at 2003-07-30T15:04:52+00:00 [haddock @ 2003-07-30 15:04:52 by simonmar] Pay attention to import specs when building the the import env, as well as the orig env. This may fix some wrong links in documentation when import specs are being used. - - - - - 17c3137f by Simon Marlow at 2003-07-30T16:05:41+00:00 [haddock @ 2003-07-30 16:05:40 by simonmar] Rename instances based on the import_env for the module in which they are to be displayed. This should give, in many cases, better links for the types and classes mentioned in the instance head. This involves keeping around the import_env in the iface until the end, because instances are not collected up until all the modules have been processed. Fortunately it doesn't seem to affect performance much. Instance heads are now attached to ExportDecls, rather than the HTML backend passing around a separate mapping for instances. This is a cleanup. - - - - - 3d3b5c87 by Sven Panne at 2003-08-04T10:18:24+00:00 [haddock @ 2003-08-04 10:18:24 by panne] Don't print parentheses around one-element contexts - - - - - 9e3f3f2d by Simon Marlow at 2003-08-04T12:59:47+00:00 [haddock @ 2003-08-04 12:59:47 by simonmar] A couple of TODOs. - - - - - e9d8085c by Simon Marlow at 2003-08-05T14:10:31+00:00 [haddock @ 2003-08-05 14:10:31 by simonmar] I'm not sure why, but it seems that the index entries for non-defining occurrences of entities did not have an anchor - the link just pointed to the module. This fixes it. - - - - - ff5c7d6d by Simon Marlow at 2003-08-15T14:42:59+00:00 [haddock @ 2003-08-15 14:42:59 by simonmar] Convert the lexer to Alex, and fix a bug in the process. - - - - - 1aa077bf by Simon Marlow at 2003-08-15T15:00:18+00:00 [haddock @ 2003-08-15 15:00:18 by simonmar] Update - - - - - d3de1e38 by Simon Marlow at 2003-08-15T15:01:03+00:00 [haddock @ 2003-08-15 15:01:03 by simonmar] wibbles - - - - - b40ece3b by Simon Marlow at 2003-08-18T10:04:47+00:00 [haddock @ 2003-08-18 10:04:47 by simonmar] Lex the 'mdo' keyword as 'do'. - - - - - 8f9a1146 by Simon Marlow at 2003-08-18T11:48:24+00:00 [haddock @ 2003-08-18 11:48:24 by simonmar] Two bugs from Sven. - - - - - ea54ebc0 by Simon Marlow at 2003-08-18T11:48:46+00:00 [haddock @ 2003-08-18 11:48:46 by simonmar] Fixes to the new lexer. - - - - - d5f6a4b5 by Simon Marlow at 2003-08-19T09:09:03+00:00 [haddock @ 2003-08-19 09:09:03 by simonmar] Further wibbles to the syntax. - - - - - 6bbdadb7 by Sven Panne at 2003-08-26T18:45:35+00:00 [haddock @ 2003-08-26 18:45:35 by panne] Use autoreconf instead of autoconf - - - - - 32e889cb by Sven Panne at 2003-08-26T19:01:19+00:00 [haddock @ 2003-08-26 19:01:18 by panne] Made option handling a bit more consistent with other tools, in particular: Every program in fptools should output * version info on stdout and terminate successfully when -V or --version * usage info on stdout and terminate successfully when -? or --help * usage info on stderr and terminate unsuccessfully when an unknown option is given. - - - - - 5d156a91 by Sven Panne at 2003-08-26T19:20:55+00:00 [haddock @ 2003-08-26 19:20:55 by panne] Make it *very* clear that we terminate when given a -V/--version flag - - - - - e6577265 by Sven Panne at 2003-08-27T07:50:03+00:00 [haddock @ 2003-08-27 07:50:02 by panne] * Made -D a short option for --dump-interface. * Made -m a short option for --ms-help. * Made -n a short option for --no-implicit-prelude. * Made -c a short option for --css. * Removed DocBook options from executable (they didn't do anything), but mark them as reserved in the docs. Note that the short option for DocBook output is now -S (from SGML) instead of -d. The latter is now a short option for --debug. * The order of the Options in the documentation now matches the order printed by Haddock itself. Note: Although changing the names of options is often a bad idea, I'd really like to make the options for the programs in fptools more consistent and compatible to the ones used in common GNU programs. - - - - - d303ff98 by Simon Marlow at 2003-09-10T08:23:48+00:00 [haddock @ 2003-09-10 08:23:48 by simonmar] Add doc subdir. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 9a70e46a by Simon Marlow at 2003-09-10T08:24:32+00:00 [haddock @ 2003-09-10 08:24:32 by simonmar] Install these files in $(datadir), not $(libdir), since they're architecture independent. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - bbb87e7a by Simon Marlow at 2003-09-10T08:25:31+00:00 [haddock @ 2003-09-10 08:25:31 by simonmar] Haddock's supplementary HTML bits now live in $(datadir), not $(libdir). Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 3587c24b by Simon Marlow at 2003-09-22T10:34:38+00:00 [haddock @ 2003-09-22 10:34:38 by simonmar] Allow installing of docs. - - - - - d510b517 by Sven Panne at 2003-10-11T08:10:44+00:00 [haddock @ 2003-10-11 08:10:44 by panne] Include architecture-independent files in file list - - - - - 187d7618 by Sigbjorn Finne at 2003-10-20T17:19:24+00:00 [haddock @ 2003-10-20 17:19:22 by sof] support for i-parameters + zip comprehensions - - - - - b6c7a273 by Simon Marlow at 2003-11-03T14:24:24+00:00 [haddock @ 2003-11-03 14:24:24 by simonmar] Update TODO file. - - - - - 58513e33 by Simon Marlow at 2003-11-05T11:22:04+00:00 [haddock @ 2003-11-05 11:22:04 by simonmar] Remove the last of the uses of 'trace' to emit warnings, and tidy up a couple of places where duplicate warnings were being emitted. - - - - - 33a78846 by Simon Marlow at 2003-11-05T11:30:53+00:00 [haddock @ 2003-11-05 11:30:52 by simonmar] - Suppress warnings about unknown imported modules by default. - Add a -v/--verbose flag to re-enable these warnings. The general idea is to suppress the "Warning: unknown module: Prelude" warnings which most Haddock users will see every time, and which aren't terribly useful. - - - - - a969de7f by Simon Marlow at 2003-11-05T12:30:28+00:00 [haddock @ 2003-11-05 12:30:28 by simonmar] - Remove the emboldening of index entries for defining locations. This isn't useful, and breaks abstractions. - If an entity is re-exported by a module but the module doesn't include documentation for that entity (perhaps because it is re-exported by 'module M'), then don't attempt to hyperlink to the documentation from the index. Instead, just list that module in the index, to indicate that the entity is exported from there. - - - - - f14ea82a by Simon Marlow at 2003-11-05T15:15:59+00:00 [haddock @ 2003-11-05 15:15:59 by simonmar] Index overhaul: - no more separate type/class and variable/function indices - the index now makes a distinction between different entities with the same name. One example is a type constructor with the same name as a data constructor, but another example is simply a function with the same name exported by two different modules. For example, the index entry for 'catch' now looks like this: catch 1 (Function) Control.Exception 2 (Function) GHC.Exception, Prelude, System.IO, System.IO.Error making it clear that there are two different 'catch'es, but one of them is exported by several modules. - Each index page now has the index contents (A B C ...) at the top. Please let me know if you really hate any of this. - - - - - 01a25ca6 by Simon Marlow at 2003-11-05T15:16:38+00:00 [haddock @ 2003-11-05 15:16:38 by simonmar] Update - - - - - 1a7ccb86 by Simon Marlow at 2003-11-05T17:16:05+00:00 [haddock @ 2003-11-05 17:16:04 by simonmar] Support for generating a single unified index for several packages. --use-index=URL turns off normal index generation, causes Index links to point to URL. --gen-index generates an combined index from the specified interfaces. Currently doesn't work exactly right, because the interfaces don't contain the iface_reexported info. I'll need to fix that up. - - - - - a2bca16d by Simon Marlow at 2003-11-06T10:44:52+00:00 [haddock @ 2003-11-06 10:44:52 by simonmar] Include iface_reexported in the .haddock file. This unfortunately bloats the file (40% for base). If this gets to be a problem we can always apply the dictionary trick that GHC uses for squashing .hi files. - - - - - 0a09c293 by Simon Marlow at 2003-11-06T12:39:47+00:00 [haddock @ 2003-11-06 12:39:46 by simonmar] - Add definition lists, marked up like this: -- | This is a definition list: -- -- [@foo@] The description of @foo at . -- -- [@bar@] The description of @bar at . Cunningly, the [] characters are not treated specially unless a [ is found at the beginning of a paragraph, in which case the ] becomes special in the following text. - Add --use-contents and --gen-contents, along the lines of --use-index and --gen-index added yesterday. Now we can generate a combined index and contents for the whole of the hierarchical libraries, and in theory the index/contents on the system could be updated as new packages are added. - - - - - fe1b3460 by Simon Marlow at 2003-11-06T14:47:36+00:00 [haddock @ 2003-11-06 14:47:36 by simonmar] Remove the 'Parent' button - it is of dubious use, and often points into thin air. - - - - - db6d762f by Simon Marlow at 2003-11-06T16:48:14+00:00 [haddock @ 2003-11-06 16:48:11 by simonmar] - Include the OptHide setting in the interface, so we don't include hidden modules in the combined index/contents. - Add a -k/--package flag to set the package name for the current set of modules. The package name for each module is now shown in the right-hand column of the contents, in a combined contents page. - - - - - 7d71718b by Simon Marlow at 2003-11-06T16:50:28+00:00 [haddock @ 2003-11-06 16:50:28 by simonmar] Add -k/--package docs - - - - - ef43949d by Simon Marlow at 2003-11-06T16:51:23+00:00 [haddock @ 2003-11-06 16:51:23 by simonmar] Bump to 0.6 - - - - - 1c419e06 by Simon Marlow at 2003-11-06T16:51:50+00:00 [haddock @ 2003-11-06 16:51:50 by simonmar] update - - - - - 69422327 by Simon Marlow at 2003-11-10T14:41:06+00:00 [haddock @ 2003-11-10 14:41:05 by simonmar] Re-exporting names from a different package is problematic, because we don't have access to the full documentation for the entity. Currently Haddock just ignores entities with no documentation, but this results in bogus-looking empty documentation for many of the modules in the haskell98 package. So: - the documentation will now just list the name, as a link pointing to the location of the actual documentation. - now we don't attempt to link to these re-exported entities if they are referred to by the current module. Additionally: - If there is no documentation in the current module, include just the Synopsis section (rather than just the documentation section, as it was before). This just looks nicer and was on the TODO list. - - - - - 3c3fc433 by Simon Marlow at 2003-11-10T14:51:59+00:00 [haddock @ 2003-11-10 14:51:59 by simonmar] Fix for getReExports: take into account names which are not visible because they are re-exported from a different package. - - - - - 31c8437b by Simon Marlow at 2003-11-10T15:10:53+00:00 [haddock @ 2003-11-10 15:10:53 by simonmar] Version 0.6 changes - - - - - a7c2430b by Simon Marlow at 2003-11-10T15:15:58+00:00 [haddock @ 2003-11-10 15:15:58 by simonmar] getReExports: one error case that isn't - - - - - 00cc459c by Simon Marlow at 2003-11-10T16:15:19+00:00 [haddock @ 2003-11-10 16:15:18 by simonmar] copyright update - - - - - ca62408d by Simon Marlow at 2003-11-11T09:57:25+00:00 [haddock @ 2003-11-11 09:57:25 by simonmar] Version 0.6 - - - - - 3acbf818 by Simon Marlow at 2003-11-11T12:10:44+00:00 [haddock @ 2003-11-11 12:10:44 by simonmar] Go back to producing just the documentation section, rather than just the synopsis section, for a module with no documentation annotations. One reason is that the synopsis section tries to link each entity to its documentation on the same page. Also, the doc section anchors each entity, and it lists instances which the synopsis doesn't. - - - - - 6c90abc2 by Simon Marlow at 2003-11-12T10:03:39+00:00 [haddock @ 2003-11-12 10:03:39 by simonmar] 2002 -> 2003 - - - - - 090bbc4c by Simon Marlow at 2003-11-28T12:08:00+00:00 [haddock @ 2003-11-28 12:08:00 by simonmar] update - - - - - 8096a832 by Simon Marlow at 2003-11-28T12:09:58+00:00 [haddock @ 2003-11-28 12:09:58 by simonmar] Fix some of the problems with Haddock generating pages that are too wide. Now we only specify 'nowrap' when it is necessary to avoid a code box getting squashed up by the text to the right of it. - - - - - 35294929 by Sven Panne at 2003-12-29T17:16:31+00:00 [haddock @ 2003-12-29 17:16:31 by panne] Updated my email address - - - - - cdb697bf by Simon Marlow at 2004-01-08T10:14:24+00:00 [haddock @ 2004-01-08 10:14:24 by simonmar] Add instructions for using GHC to pre-process source for feeding to Haddock. - - - - - 8dfc491f by Simon Marlow at 2004-01-09T12:45:46+00:00 [haddock @ 2004-01-09 12:45:46 by simonmar] Add -optP-P to example ghc command line. - - - - - ac41b820 by Simon Marlow at 2004-02-03T11:02:03+00:00 [haddock @ 2004-02-03 11:02:03 by simonmar] Fix bug in index generation - - - - - f4e7edcb by Simon Marlow at 2004-02-10T11:51:16+00:00 [haddock @ 2004-02-10 11:51:16 by simonmar] Don't throw away whitespace at the beginning of a line (experimental fix). - - - - - 68e212d2 by Simon Marlow at 2004-02-10T12:10:08+00:00 [haddock @ 2004-02-10 12:10:08 by simonmar] Fix for previous commit: I now realise why the whitespace was stripped from the beginning of the line. Work around it. - - - - - e7d7f2df by Sven Panne at 2004-02-10T18:38:45+00:00 [haddock @ 2004-02-10 18:38:45 by panne] Make Haddock link with the latest relocated monad transformer package - - - - - 992d4225 by Simon Marlow at 2004-02-16T10:21:35+00:00 [haddock @ 2004-02-16 10:21:35 by simonmar] Add a TODO - - - - - 1ac55326 by Simon Marlow at 2004-03-12T11:33:39+00:00 [haddock @ 2004-03-12 11:33:39 by simonmar] Add an item. - - - - - 0478e903 by Simon Marlow at 2004-03-15T12:24:05+00:00 [haddock @ 2004-03-15 12:24:05 by simonmar] Add an item. - - - - - 6f26d21a by Simon Marlow at 2004-03-18T14:21:29+00:00 [haddock @ 2004-03-18 14:21:29 by simonmar] Fix URL - - - - - 19b6bb99 by Simon Marlow at 2004-03-22T14:09:03+00:00 [haddock @ 2004-03-22 14:09:03 by simonmar] getReExports was bogus: we should really look in the import_env to find the documentation for an entity which we are re-exporting without documentation. Suggested by: Ross Paterson (patch modified by me). - - - - - 5c756031 by Simon Marlow at 2004-03-24T09:42:11+00:00 [haddock @ 2004-03-24 09:42:10 by simonmar] hiding bug from Ross Paterson (fixed in rev 1.59 of Main.hs) - - - - - 1b692e6c by Simon Marlow at 2004-03-24T10:10:50+00:00 [haddock @ 2004-03-24 10:10:50 by simonmar] mkExportItems fix & simplification: we should be looking at the actual exported names (calculated earlier) to figure out which subordinates of a declaration are exported. This means that if you export a record, and name its fields separately in the export list, the fields will still be visible in the documentation for the constructor. - - - - - 90e5e294 by Simon Marlow at 2004-03-24T10:12:08+00:00 [haddock @ 2004-03-24 10:12:08 by simonmar] Make restrictCons take into account record field names too (removing a ToDo). - - - - - 2600efa4 by Simon Marlow at 2004-03-24T10:16:17+00:00 [haddock @ 2004-03-24 10:16:17 by simonmar] Record export tests. - - - - - 6a8575c7 by Simon Marlow at 2004-03-25T09:35:14+00:00 [haddock @ 2004-03-25 09:35:14 by simonmar] restrictTo: fix for restricting a newtype with a record field. - - - - - dcf55a8d by Simon Marlow at 2004-03-25T10:01:42+00:00 [haddock @ 2004-03-25 10:01:42 by simonmar] Fix duplicate instance bug - - - - - f49aa758 by Simon Marlow at 2004-03-25T10:02:41+00:00 [haddock @ 2004-03-25 10:02:41 by simonmar] Duplicate instance bug. - - - - - 7b87344c by Simon Marlow at 2004-03-25T10:29:56+00:00 [haddock @ 2004-03-25 10:29:56 by simonmar] If a name is imported from two places, one hidden and one not, choose the unhidden one to link to. Also, when there's only a hidden module to link to, don't try linking to it. - - - - - 40f44d7b by Simon Marlow at 2004-03-25T15:17:24+00:00 [haddock @ 2004-03-25 15:17:23 by simonmar] Add support for collaspible parts of the page, with a +/- button and a bit of JavaScript. Make the instances collapsible, and collapse them by default. This makes documentation with long lists of instances (eg. the Prelude) much easier to read. Maybe we should give other documentation sections the same treatment. - - - - - 9b64dc0f by Simon Marlow at 2004-03-25T15:20:55+00:00 [haddock @ 2004-03-25 15:20:55 by simonmar] Update - - - - - c2fff7f2 by Simon Marlow at 2004-03-25T15:45:10+00:00 [haddock @ 2004-03-25 15:45:10 by simonmar] Eliminate some unnecessary spaces in the HTML rendering - - - - - b7948ff0 by Simon Marlow at 2004-03-25T16:00:37+00:00 [haddock @ 2004-03-25 16:00:36 by simonmar] Remove all that indentation in the generated HTML to keep the file sizes down. - - - - - da2bb4ca by Sven Panne at 2004-03-27T09:57:58+00:00 [haddock @ 2004-03-27 09:57:57 by panne] Added the new-born haddock.js to the build process and the documentation. - - - - - b99e6f8c by Sven Panne at 2004-03-27T10:32:20+00:00 [haddock @ 2004-03-27 10:32:20 by panne] "type" is a required attribute of the "script" element - - - - - 562b185a by Sven Panne at 2004-03-27T12:52:34+00:00 [haddock @ 2004-03-27 12:52:34 by panne] Add a doctype for the contents page, too. - - - - - f6a99c2d by Simon Marlow at 2004-04-14T10:03:25+00:00 [haddock @ 2004-04-14 10:03:25 by simonmar] fix for single-line comment syntax - - - - - de366303 by Simon Marlow at 2004-04-20T13:08:04+00:00 [haddock @ 2004-04-20 13:08:04 by simonmar] Allow a 'type' declaration to include documentation comments. These will be ignored by Haddock, but at least one user (Johannes Waldmann) finds this feature useful, and it's easy to add. - - - - - fd78f51e by Simon Marlow at 2004-05-07T15:14:56+00:00 [haddock @ 2004-05-07 15:14:56 by simonmar] - update copyright - add version to abstract - - - - - 59f53e32 by Sven Panne at 2004-05-09T14:39:53+00:00 [haddock @ 2004-05-09 14:39:53 by panne] Fix the fix for single-line comment syntax, ------------------------------------------- is now a valid comment line again. - - - - - 8b18f2fe by Simon Marlow at 2004-05-10T10:11:51+00:00 [haddock @ 2004-05-10 10:11:51 by simonmar] Update - - - - - 225a491d by Ross Paterson at 2004-05-19T13:10:23+00:00 [haddock @ 2004-05-19 13:10:23 by ross] Make the handling of "deriving" slightly smarter, by ignoring data constructor arguments that are identical to the lhs. Now handles things like data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving ... - - - - - 37588686 by Mike Thomas at 2004-05-21T06:38:14+00:00 [haddock @ 2004-05-21 06:38:14 by mthomas] Windows exe extensions (bin remains for Unix). - - - - - cf2b9152 by Simon Marlow at 2004-05-25T09:34:54+00:00 [haddock @ 2004-05-25 09:34:54 by simonmar] Add some TODO items - - - - - 4d29cdfc by Simon Marlow at 2004-05-25T10:41:46+00:00 [haddock @ 2004-05-25 10:41:46 by simonmar] Complain if -h is used with --gen-index or --gen-contents, because it'll overwrite the new index/contents. - - - - - 2e0771e0 by Mike Thomas at 2004-05-28T20:17:55+00:00 [haddock @ 2004-05-28 20:17:55 by mthomas] Windows: search for templates in executable directory. Unix: Haddock tries cwd first rather than error if no -l arg. - - - - - 8d10bde1 by Sven Panne at 2004-06-05T16:53:34+00:00 [haddock @ 2004-06-05 16:53:34 by panne] Misc. rpm spec file cleanup, including: * make BuildRoot handling more consistent * added default file attributes * consistent defines and tags - - - - - 59974349 by Sven Panne at 2004-06-05T18:01:00+00:00 [haddock @ 2004-06-05 18:01:00 by panne] More rpm spec file cleanup, including: * added some BuildRequires * changed packager to me, so people can complain at the right place :-] * consistently refer to haskell.org instead of www.haskell.org - - - - - b94d4903 by Simon Marlow at 2004-07-01T11:08:58+00:00 [haddock @ 2004-07-01 11:08:57 by simonmar] Update to the +/- buttons: use a resized image rather than a <button>. Still seeing some strange effects in Konqueror, so might need to use a fixed-size image instead. - - - - - d5278f67 by Sven Panne at 2004-07-04T15:15:55+00:00 [haddock @ 2004-07-04 15:15:55 by panne] Install pictures for +/- pictures, too (JPEG is a strange format for graphics like this, I would have expected GIF or PNG here.) Things look fine with Konqueror and Netscape on Linux now, the only downside is that the cursor doesn't change when positioned above the "button". - - - - - 46dec6c5 by Sven Panne at 2004-07-13T17:59:28+00:00 [haddock @ 2004-07-13 17:59:28 by panne] A quote is a valid part of a Haskell identifier, but it would interfere with an ECMA script string delimiter, so escape it there. - - - - - 1d7bc432 by Simon Marlow at 2004-07-22T08:54:06+00:00 [haddock @ 2004-07-22 08:54:06 by simonmar] Add single quote to $ident, so you can say eg. 'foldl'' to refer to foldl' (the longest match rule is our friend). Bug reported by Adrian Hey <ahey at iee.org> - - - - - f183618b by Krasimir Angelov at 2004-07-27T22:59:35+00:00 [haddock @ 2004-07-27 22:58:23 by krasimir] Add basic support for Microsoft HTML Help 2.0 - - - - - d515d0c2 by Krasimir Angelov at 2004-07-27T23:02:36+00:00 [haddock @ 2004-07-27 23:02:36 by krasimir] escape names in the index - - - - - a5f1be23 by Krasimir Angelov at 2004-07-27T23:05:21+00:00 [haddock @ 2004-07-27 23:05:21 by krasimir] Add jsFile, plusFile and minusFile to the file list - - - - - c4fb4881 by Krasimir Angelov at 2004-07-28T22:12:10+00:00 [haddock @ 2004-07-28 22:12:09 by krasimir] bugfix. Move contentsHtmlFile, indexHtmlFile and subIndexHtmlFile functions to HaddockUtil.hs module to make them accessible from HaddockHH2.hs - - - - - 64d30b1d by Krasimir Angelov at 2004-07-30T22:15:47+00:00 [haddock @ 2004-07-30 22:15:45 by krasimir] more stuffs - support for separated compilation of packages - the contents page now uses DHTML TreeView - fixed copyFile bug - - - - - 133c8c5c by Krasimir Angelov at 2004-07-31T12:04:38+00:00 [haddock @ 2004-07-31 12:04:37 by krasimir] make the DHtmlTree in contents page more portable. The +/- buttons are replaced with new images which looks more beatiful. - - - - - 79040963 by Krasimir Angelov at 2004-07-31T13:10:20+00:00 [haddock @ 2004-07-31 13:10:20 by krasimir] Make DHtmlTree compatible with Mozila browser - - - - - 1a55dc90 by Krasimir Angelov at 2004-07-31T14:52:55+00:00 [haddock @ 2004-07-31 14:52:55 by krasimir] fix - - - - - 85ce0237 by Krasimir Angelov at 2004-07-31T14:53:28+00:00 [haddock @ 2004-07-31 14:53:28 by krasimir] HtmlHelp 1.x - - - - - 3c0c53ba by Krasimir Angelov at 2004-07-31T20:35:21+00:00 [haddock @ 2004-07-31 20:35:21 by krasimir] Added support for DevHelp - - - - - d42b5af1 by Krasimir Angelov at 2004-07-31T21:17:51+00:00 [haddock @ 2004-07-31 21:17:51 by krasimir] Document new features in HtmlHelp - - - - - 790fe21e by Krasimir Angelov at 2004-08-01T15:14:02+00:00 [haddock @ 2004-08-01 15:14:02 by krasimir] add missing imports - - - - - fd7cc6bc by Krasimir Angelov at 2004-08-01T19:52:08+00:00 [haddock @ 2004-08-01 19:52:06 by krasimir] fix some bugs. Now I have got the entire libraries documentation in HtmlHelp 2.0 format. - - - - - 94ad7ac8 by Krasimir Angelov at 2004-08-01T19:53:50+00:00 [haddock @ 2004-08-01 19:53:50 by krasimir] I forgot to add the new +/- images - - - - - f0c65388 by Krasimir Angelov at 2004-08-02T16:25:53+00:00 [haddock @ 2004-08-02 16:25:53 by krasimir] Add root node to the table of contents. All modules in tree are not children of the root - - - - - f50bd85d by Sven Panne at 2004-08-02T18:17:46+00:00 [haddock @ 2004-08-02 18:17:46 by panne] Mainly DocBook fixes - - - - - 09527ce3 by Sven Panne at 2004-08-02T20:02:29+00:00 [haddock @ 2004-08-02 20:02:29 by panne] Fixed -o/--odir handling. Generating the output, especially the directory handling, is getting a bit convoluted nowadays... - - - - - c8fbacfa by Sven Panne at 2004-08-02T20:31:13+00:00 [haddock @ 2004-08-02 20:31:13 by panne] Warning police - - - - - 37830bff by Sven Panne at 2004-08-02T20:32:29+00:00 [haddock @ 2004-08-02 20:32:28 by panne] Nuked dead code - - - - - 13847171 by Sven Panne at 2004-08-02T21:12:27+00:00 [haddock @ 2004-08-02 21:12:25 by panne] Use pathJoin instead of low-level list-based manipulation for FilePaths - - - - - c711d61e by Sven Panne at 2004-08-02T21:16:02+00:00 [haddock @ 2004-08-02 21:16:02 by panne] Removed WinDoze CRs - - - - - b1f7dc88 by Sven Panne at 2004-08-03T19:35:59+00:00 [haddock @ 2004-08-03 19:35:59 by panne] Fixed spelling of "http-equiv" attribute - - - - - dd5f394e by Sven Panne at 2004-08-03T19:44:03+00:00 [haddock @ 2004-08-03 19:44:03 by panne] Pacify W3C validator: * Added document encoding (currently UTF-8, not sure if this is completely correct) * Fixed syntax of `id' attributes * Added necessary `alt' attribute for +/- images Small layout improvement: * Added space after +/- images (still not perfect, but better than before) - - - - - 919c47c6 by Sigbjorn Finne at 2004-08-03T19:45:11+00:00 [haddock @ 2004-08-03 19:45:11 by sof] make it compile with <= ghc-6.1 - - - - - 4d6f01d8 by Sigbjorn Finne at 2004-08-03T19:45:30+00:00 [haddock @ 2004-08-03 19:45:30 by sof] ffi wibble - - - - - 4770643a by Sven Panne at 2004-08-03T20:47:46+00:00 [haddock @ 2004-08-03 20:47:46 by panne] Fixed CSS for button style. Note that only "0" is a valid measure without a unit! - - - - - 14aaf2e5 by Sven Panne at 2004-08-03T21:07:59+00:00 [haddock @ 2004-08-03 21:07:58 by panne] Improved spacing of dynamic module tree - - - - - 97c3579a by Simon Marlow at 2004-08-09T11:03:04+00:00 [haddock @ 2004-08-09 11:03:04 by simonmar] Add FormatVersion Patch submitted by: George Russell <ger at informatik.uni-bremen.de> - - - - - af7f8c03 by Simon Marlow at 2004-08-09T11:55:07+00:00 [haddock @ 2004-08-09 11:55:05 by simonmar] Add support for a short description for each module, which is included in the contents. The short description should be given in a "Description: " field of the header. Included in this patch are changes that make the format of the header a little more flexible. From the comments: -- all fields in the header are optional and have the form -- -- [spaces1][field name][spaces] ":" -- [text]"\n" ([spaces2][space][text]"\n" | [spaces]"\n")* -- where each [spaces2] should have [spaces1] as a prefix. -- -- Thus for the key "Description", -- -- > Description : this is a -- > rather long -- > -- > description -- > -- > The module comment starts here -- -- the value will be "this is a .. description" and the rest will begin -- at "The module comment". The header fields must be in the following order: Module, Description, Copyright, License, Maintainer, Stability, Portability. Patches submitted by: George Russell <ger at informatik.uni-bremen.de>, with a few small changes be me, mostly to merge with other recent changes. ToDo: document the module header. - - - - - 7b865ad3 by Simon Marlow at 2004-08-10T14:09:57+00:00 [haddock @ 2004-08-10 14:09:57 by simonmar] Fixes for DevHelp/HtmlHelp following introduction of short module description. - - - - - 814766cd by Simon Marlow at 2004-08-10T14:33:46+00:00 [haddock @ 2004-08-10 14:33:45 by simonmar] Fixes to installation under Windows. - - - - - 39cf9ede by Simon Marlow at 2004-08-12T12:08:23+00:00 [haddock @ 2004-08-12 12:08:23 by simonmar] Avoid using string-gap tricks. - - - - - b6d78551 by Simon Marlow at 2004-08-13T10:53:21+00:00 [haddock @ 2004-08-13 10:53:21 by simonmar] Update - - - - - eaae7417 by Simon Marlow at 2004-08-13T10:53:50+00:00 [haddock @ 2004-08-13 10:53:50 by simonmar] Test for primes in quoted links - - - - - 68c34f06 by Sven Panne at 2004-08-16T19:59:38+00:00 [haddock @ 2004-08-16 19:59:36 by panne] XMLification - - - - - 7f45a6f9 by Sven Panne at 2004-08-18T16:42:54+00:00 [haddock @ 2004-08-18 16:42:54 by panne] Re-added indices + minor fixes - - - - - 8a5dd97c by Sigbjorn Finne at 2004-08-25T17:15:42+00:00 [haddock @ 2004-08-25 17:15:42 by sof] backquote HADDOCK_VERSION defn for <= ghc-6.0.x; believe this is only needed under mingw - - - - - 4b1b42ea by Sven Panne at 2004-08-26T20:08:50+00:00 [haddock @ 2004-08-26 20:08:49 by panne] SGML is dead, long live DocBook XML! Note: The BuildRequires tags in the spec files are still incomplete and the documentation about the DocBook tools needs to be updated, too. Stay tuned... - - - - - 8d52cedb by Sven Panne at 2004-08-26T21:03:19+00:00 [haddock @ 2004-08-26 21:03:19 by panne] Updated BuildRequires tags. Alas, there seems to be no real standard here, so your mileage may vary... At least the current specs should work on SuSE Linux. - - - - - e6982912 by Sigbjorn Finne at 2004-08-30T15:44:59+00:00 [haddock @ 2004-08-30 15:44:59 by sof] escape HADDOCK_VERSION double quotes on all platforms when compiling with <=6.0.x - - - - - b3fbc867 by Simon Marlow at 2004-08-31T13:09:42+00:00 [haddock @ 2004-08-31 13:09:42 by simonmar] Avoid GHC/shell versionitis and create Version.hs - - - - - c359e16a by Sven Panne at 2004-09-05T19:12:33+00:00 [haddock @ 2004-09-05 19:12:32 by panne] * HTML documentation for "foo.xml" goes into directory "foo" again, not "foo-html". This is nicer and consistent with the behaviour for building the docs from SGML. * Disabled building PostScript documentation in the spec files for now, there are some strange issues with the FO->PS conversion for some files which have to be clarified first. - - - - - c68b1eba by Sven Panne at 2004-09-24T07:04:38+00:00 [haddock @ 2004-09-24 07:04:38 by panne] Switched the default state for instances and the module hierarchy to non-collapsed. This can be reversed when we finally use cookies from JavaScript to have a more persistent state. Previously going back and forth in the documentation was simply too annoying because everything was collapsed again and therefore the documentation was not easily navigatable. - - - - - dfb32615 by Simon Marlow at 2004-09-30T08:21:29+00:00 [haddock @ 2004-09-30 08:21:29 by simonmar] Add a feature request - - - - - 45ff783c by Sven Panne at 2004-10-23T19:54:00+00:00 [haddock @ 2004-10-23 19:54:00 by panne] Improved the Cygwin/MinGW chaos a little bit. There is still confusion about host platform vs. target platform... - - - - - 5f644714 by Krasimir Angelov at 2004-10-28T16:01:51+00:00 [haddock @ 2004-10-28 16:01:51 by krasimir] update for ghc-6.3+ - - - - - 92d9753e by Sven Panne at 2004-11-01T16:39:01+00:00 [haddock @ 2004-11-01 16:39:01 by panne] Revert previous commit: It's Network.URI which should be changed, not Haddock. - - - - - 05f70f6e by Simon Marlow at 2005-01-04T16:15:51+00:00 [haddock @ 2005-01-04 16:15:51 by simonmar] parser fix: allow qualified specialids. - - - - - 47870837 by Simon Marlow at 2005-01-04T16:16:54+00:00 [haddock @ 2005-01-04 16:16:54 by simonmar] Add a test - - - - - ff11fc2c by Ross Paterson at 2005-01-10T19:18:22+00:00 [haddock @ 2005-01-10 19:18:22 by ross] Render non-ASCII characters using numeric character references, to simplify charset issues. There's a META tag saying the charset is UTF-8, but GHC outputs characters as raw bytes. Ideally we need an encoding on the input side too, primarily in comments, because source files containing non-ASCII characters aren't portable between locales. - - - - - eba2fc4e by Simon Marlow at 2005-01-11T10:44:37+00:00 [haddock @ 2005-01-11 10:44:37 by simonmar] Remove string gap - - - - - b899a381 by Ross Paterson at 2005-01-13T11:41:33+00:00 [haddock @ 2005-01-13 11:41:33 by ross] recognize SGML-style numeric character references &#ddd; or &#xhhhh; and translate them into Chars. - - - - - 106e3cf0 by Ross Paterson at 2005-01-13T14:43:41+00:00 [haddock @ 2005-01-13 14:43:41 by ross] also allow uppercase X in hexadecimal character references (like SGML) - - - - - e8f54f25 by Ross Paterson at 2005-01-13T14:44:24+00:00 [haddock @ 2005-01-13 14:44:24 by ross] Describe numeric character references. - - - - - 914ccdce by Sven Panne at 2005-01-15T18:44:48+00:00 [haddock @ 2005-01-15 18:44:45 by panne] Make Haddock compile again after the recent base package changed. The Map/Set legacy hell has been factored out, so that all modules can simply use the new non-deprecated interfaces. Probably a lot of things can be improved by a little bit of Map/Set/List algebra, this can be done later if needed. Small note: Currently the list of instances in HTML code is reversed. This will hopefully be fixed later. - - - - - 6ab20e84 by Sven Panne at 2005-01-16T12:18:26+00:00 [haddock @ 2005-01-16 12:18:26 by panne] Trim imports - - - - - efb81da9 by Sven Panne at 2005-01-16T12:58:08+00:00 [haddock @ 2005-01-16 12:58:03 by panne] Correctly handle the new order of arguments for the combining function given to fromListWith. - - - - - e27b5834 by Sven Panne at 2005-01-16T14:14:41+00:00 [haddock @ 2005-01-16 14:14:39 by panne] Data.Map.unions is left-biased. - - - - - dae3cc3e by Sven Panne at 2005-01-16T14:22:44+00:00 [haddock @ 2005-01-16 14:22:44 by panne] Added the last missing "flip" to get identical HTML output as previous versions. - - - - - 951d8408 by Sven Panne at 2005-01-16T14:37:10+00:00 [haddock @ 2005-01-16 14:37:10 by panne] Refactored Text.PrettyPrint legacy hell into a separate module. - - - - - f1c4b892 by Sven Panne at 2005-01-16T15:41:25+00:00 [haddock @ 2005-01-16 15:41:21 by panne] Cleaned up imports and dropped support for GHC < 5.03, it never worked, anyway. - - - - - 60824c6e by Simon Marlow at 2005-01-18T10:02:48+00:00 [haddock @ 2005-01-18 10:02:48 by simonmar] Add a TODO - - - - - a8c82f23 by Krasimir Angelov at 2005-01-28T23:19:39+00:00 [haddock @ 2005-01-28 23:19:39 by krasimir] import Foreign/Foreign.C are required for Windows - - - - - d8450a23 by Simon Marlow at 2005-02-02T16:23:04+00:00 [haddock @ 2005-02-02 16:23:00 by simonmar] Revamp the linking strategy in Haddock. Now name resolution is done in two phases: - first resolve everything to original names, like a Haskell compiler would. - then, figure out the "home" location for every entity, and point all the links to there. The home location is the lowest non-hidden module in the import hierarchy that documents the entity. If there are multiple candidates, one is chosen at random. Also: - Haddock should not generate any HTML with dangling links any more. Unlinked references are just rendered as plain text. - Error reporting is better: if we can't find a link destination for an entity reference, we now emit a warning. - - - - - 1cce71d0 by Simon Marlow at 2005-02-03T13:42:19+00:00 [haddock @ 2005-02-03 13:42:19 by simonmar] - add --ignore-all-exports flag, which behaves as if every module has the ignore-exports attribute (requested by Chris Ryder). - add --hide option to hide a module on the command line. - add --use-package option to get Haddock info for a package from ghc-pkg (largely untested). - remove reexports from the .haddock file, they aren't used any more. - - - - - 767123ef by Ross Paterson at 2005-02-03T16:17:37+00:00 [haddock @ 2005-02-03 16:17:37 by ross] fix typo for < 6.3 - - - - - 0c680c04 by Simon Marlow at 2005-02-04T12:03:31+00:00 [haddock @ 2005-02-04 12:03:31 by simonmar] Fix bug in renameExportItems that meant links in instances weren't being renamed properly. - - - - - ff7abe5f by Simon Marlow at 2005-02-04T12:15:53+00:00 [haddock @ 2005-02-04 12:15:52 by simonmar] Add attribute #not-home, to indicate that the current module should not be considered to be a home module for the each entity it exports, unless there is no other module that exports the entity. - - - - - fc2cfd27 by Simon Marlow at 2005-02-04T12:40:02+00:00 [haddock @ 2005-02-04 12:40:02 by simonmar] Update the documentation w.r.t. home modules and the not-home attribute. - - - - - 26b8ddf7 by Ross Paterson at 2005-02-04T13:36:06+00:00 [haddock @ 2005-02-04 13:36:05 by ross] sort lists of instances by - arity of the type constructors (so higher-kinded instances come first) - name of the class - argument types - - - - - 26bfb19c by Simon Marlow at 2005-02-23T15:57:12+00:00 [haddock @ 2005-02-23 15:57:12 by simonmar] Fix documentation regarding the module attributes. - - - - - 9c3afd02 by Simon Marlow at 2005-02-28T16:18:17+00:00 [haddock @ 2005-02-28 16:18:17 by simonmar] version 0.7 - - - - - a95fd63f by Simon Marlow at 2005-02-28T16:22:08+00:00 [haddock @ 2005-02-28 16:22:08 by simonmar] Attempt to fix the layout of the package names in the contents. Having tried just about everything, the only thing I can get to work reliably is to make the package names line up on a fixed offset from the left margin. This obviously isn't ideal, so anyone else that would like to have a go at improving it is welcome. One option is to remove the +/- buttons from the contents list and go back to a plain table. The contents page now uses CSS for layout rather than tables. It seems that most browsers have different interpretations of CSS layout, so only the simplest things lead to consistent results. - - - - - 905d42f7 by Simon Marlow at 2005-03-01T17:16:42+00:00 [haddock @ 2005-03-01 17:16:40 by simonmar] Another attempt at lining up the package names on the contents page. Now, they line up with Konqueror, and almost line up with Firefox & IE (different layout in each case). - - - - - a0e1d178 by Wolfgang Thaller at 2005-03-09T08:28:39+00:00 [haddock @ 2005-03-09 08:28:39 by wolfgang] Hack haddock's lexer to accept the output from Apple's broken version of cpp (Apple's cpp leaves #pragma set_debug_pwd directives in it's output). - - - - - 9e1eb784 by Simon Marlow at 2005-04-22T14:27:15+00:00 [haddock @ 2005-04-22 14:27:15 by simonmar] Add a TODO item - - - - - 23281f78 by Ross Paterson at 2005-05-18T12:41:59+00:00 [haddock @ 2005-05-18 12:41:59 by ross] fix 3 bugs in --use-package, and document it. - - - - - 00074a68 by Sven Panne at 2005-05-21T12:35:29+00:00 [haddock @ 2005-05-21 12:35:29 by panne] Warning/versionitis police - - - - - 341fa822 by Simon Marlow at 2005-06-15T15:43:21+00:00 [haddock @ 2005-06-15 15:43:21 by simonmar] Allow "licence" as an alternate spelling of "license" - - - - - 3b953f8b by Simon Marlow at 2005-06-16T08:14:12+00:00 [haddock @ 2005-06-16 08:14:12 by simonmar] wibble - - - - - abfd9826 by Simon Marlow at 2005-06-27T14:46:40+00:00 [haddock @ 2005-06-27 14:46:40 by simonmar] name hierarchical HTML files as A-B-C.html instead of A.B.C.html. The old way confused Apache because the extensions are sometimes interpreted as having special meanings. - - - - - a01eea00 by Simon Marlow at 2005-08-04T13:59:40+00:00 [haddock @ 2005-08-04 13:59:40 by simonmar] 0.7 changes - - - - - 170ef87e by Simon Marlow at 2005-08-04T15:08:03+00:00 [haddock @ 2005-08-04 15:08:03 by simonmar] spec file from Jens Peterson - - - - - 7621fde4 by Simon Marlow at 2005-08-04T15:59:30+00:00 [haddock @ 2005-08-04 15:59:30 by simonmar] replace mingw tests with $(Windows) - - - - - a20739bb by Sven Panne at 2005-08-05T07:01:12+00:00 [haddock @ 2005-08-05 07:01:12 by panne] Reverted to previous version (but with bumped version number), the last commit broke RPM building on SuSE systems due to differently named dependencies. As a clarification: All .spec files in the repository have to work at least on SuSE, because that's the system I'm using. And as "Mr. Building Police", I reserve me the right to keep them that way... >:-) It might very well be the case that we need different .spec files for different platforms, so packagers which are unhappy with the current .spec files should contact me, stating the actual problems. - - - - - 4afb15cf by Simon Marlow at 2005-10-05T10:51:45+00:00 [haddock @ 2005-10-05 10:51:45 by simonmar] Add a bug - - - - - 60f69f82 by Simon Marlow at 2005-10-05T12:52:03+00:00 [haddock @ 2005-10-05 12:52:03 by simonmar] Document new behaviour of -s option - - - - - f7e520ca by Simon Marlow at 2005-10-10T15:02:55+00:00 [haddock @ 2005-10-10 15:02:55 by simonmar] extractRecSel: ignore non-record constructors (fixes a crash when using datatypes with a mixture of record and non-record style constructors). - - - - - b2edbedb by Simon Marlow at 2005-10-14T09:44:21+00:00 Start CHANGES for 0.8 - - - - - 21c7ac8d by Simon Marlow at 2005-10-14T23:11:19+00:00 First cut of Cabal build system - - - - - 766cecdd by Simon Marlow at 2005-10-29T08:14:43+00:00 Add configure script and Makefile for the docs Add a separate configure script and build system for building the documentation. The configure and Makefile code is stolen from fptools. This is left as a separate build system so that the main Cabal setup doesn't require a Unix build environment or DocBook XML tools. - - - - - aa36c783 by Duncan Coutts at 2006-01-17T19:29:55+00:00 Add a --wiki=URL flag to add a per-module link to a correspondng wiki page. So each html page gets an extra link (placed next to the source code and contents links) to a corresponding wiki page. The idea is to let readers contribute their own notes, examples etc to the documentation. Also slightly tidy up the code for the --source option. - - - - - e06e2da2 by Simon Marlow at 2006-01-18T09:28:15+00:00 TODO: documnet --wiki - - - - - 17adfda9 by Duncan Coutts at 2006-01-19T20:17:59+00:00 Add an optional wiki link for each top level exported name. In each module, for each "top level" exported entity we add a hyper link to a corresponding wiki page. The link url gets the name of the exported entity as a '#'-style anchor, so if there is an anchor in the page with that name then the users browser should jump directly to it. By "top level" we mean functions, classes, class members and data types (data, type, newtype), but not data constructors, class instances or data type class membership. The link is added at the right of the page and in a small font. Hopefully this is the right balance of visibility/distraction. We also include a link to the wiki base url in the contents and index pages. - - - - - f52324bb by Duncan Coutts at 2006-01-19T20:28:27+00:00 Rewrite pathJoin to only add a path separator when necessary. When the path ends in a file seperator there is no need to add another. Now using "--wiki=http://blah.com/foo/" should do the right thing. (Code snippet adapted from Isaac's FilePath package.) - - - - - 43bb89fa by Duncan Coutts at 2006-01-21T17:15:27+00:00 Teach haddock about line pragmas and add accurate source code links Teach haddock about C and Haskell style line pragmas. Extend the lexer/parser's source location tracking to include the file name as well as line/column. This way each AST item that is tagged with a SrcLoc gets the original file name too. Use this original file name to add source links to each exported item, in the same visual style as the wiki links. Note that the per-export source links are to the defining module rather than whichever module haddock pretends it is exported from. This is what we want for source code links. The source code link URL can also contain the name of the export so one could implement jumping to the actual location of the function in the file if it were linked to an html version of the source rather than just plain text. The name can be selected with the %N wild card. So for linking to the raw source code one might use: --source=http://darcs/haskell.org/foo/%F Or for linking to html syntax highlighted code: --source=http://darcs/haskell.org/foo/%M.html#%N - - - - - edd9f229 by Duncan Coutts at 2006-01-22T00:02:00+00:00 Extend URL variable expansion syntax and add source links to the contents page Like the wiki link on the contents and index page, add a source code link too. Extend the wiki & source URL variable expansion syntax. The original syntax was: %F for the source file name (the .hs version only, not the .lhs or .hs.pp one) %M for the module name (with '.' replaced by '/') The new syntax is: %F or %{FILE} for the original source file name %M or %{MODULE} for the module name (no replacements) %N or %{NAME} for the function/type export name %K or %{KIND} for a type/value flag "t" or "v" with these extensions: %{MODULE/./c} to replace the '.' module seperator with any other char c %{VAR|some text with the % char in it} which means if the VAR is not in use in this URL context then "" else replace the given text with the '%' char replaced by the string value of the VAR. This extension allows us to construct URLs wit optional parts, since the module/file name is not available for the URL in the contents/index pages and the value/type name is not available for the URL at the top level of each module. - - - - - eb3c6ada by Duncan Coutts at 2006-01-23T13:42:34+00:00 Remove the complex substitutions and add more command line flags instead. Instead of incomprehensable URL substitutions like ${MODULE/./-|?m=%} we now use three seperate command line flags for the top level, per-module and per-entity source and wiki links. They are: --source-base, --source-module, --source-entity --comments-base, --comments-module, --comments-entity We leave -s, --source as an alias for --source-module which is how that option behaved previously. The long forms of the substitutions are still available, ${FILE} ${MODULE} etc and the only non-trivial substitution is ${MODULE/./c} to replace the '.' characters in the module name with any other character c. eg ${MODULE/./-} Seperating the source and wiki url flags has the added bonus that they can be turned on or off individually. So users can have per-module links for example without having to also have per-entity links.` - - - - - a2f0f2af by Duncan Coutts at 2006-01-23T13:54:52+00:00 Make the --help output fit in 80 columns. This is a purely cosmetic patch, feel free to ignore it. The only trickery going on is that we don't display the deprecated -s, --source flags in the help message, but we do still accept them. - - - - - 2d3a4b0c by Duncan Coutts at 2006-01-23T14:12:16+00:00 Add documentation for the new --source-* and --comments-* command line options - - - - - 1a82a297 by Simon Marlow at 2006-01-23T17:03:27+00:00 fix markup - - - - - 100d464a by Duncan Coutts at 2006-01-23T18:31:13+00:00 remove a couple TODO items that have been done The --wiki, or rather the --comment-* options are now documented. There is probably no need to have haddock invoke unlit or cpp itself since it can now pick up the line pragmas to get the source locations right. Tools like Cabal will arrange for preprocessors to be run so there is less of a need for tools like haddock to do it themselves. - - - - - 3162fa91 by Simon Marlow at 2006-01-24T14:21:56+00:00 add a test I had lying around - - - - - 98947063 by Simon Marlow at 2006-01-31T13:52:54+00:00 add scabal-version field - - - - - c41876e6 by Neil Mitchell at 2006-02-26T17:48:21+00:00 Add Hoogle output option - - - - - f86fb9c0 by Simon Marlow at 2006-03-08T09:15:20+00:00 add haskell.vim Contributed by Brad Bowman <bsb at bereft.net>, thanks! - - - - - 35d3c511 by benjamin.franksen at 2006-03-03T22:39:54+00:00 fixed libdir (/html was missing) - - - - - 4d08fd7d by Simon Marlow at 2006-03-10T11:13:31+00:00 add PatternGuards extension - - - - - 3f095e70 by Simon Marlow at 2006-03-13T11:40:42+00:00 bug fixes from Brad Bowman - - - - - 8610849d by Sven Panne at 2006-03-19T17:02:56+00:00 Fixed Cabal/RPM build - - - - - 34a994d6 by sven.panne at 2006-04-20T12:39:23+00:00 Avoid pattern guards Due to the use of pattern guards in Haddock, GHC was called with -fglasgow-exts. This in turn enables bang patterns, too, which broke the Haddock build. Removing some unnecessary pattern guards seemed to be the better way of fixing this instead of using a pragma to disable pattern guards. - - - - - bb523f51 by Ross Paterson at 2006-04-24T09:03:25+00:00 extend 'deriving' heuristic a little If an argument of a data constructor has a type variable head, it is irreducible and the same type class can be copied into the constraint. (Formerly we just did this for type variable arguments.) - - - - - dab9fe7a by Simon Marlow at 2006-04-26T10:02:31+00:00 record an idea - - - - - 748b7078 by Simon Marlow at 2006-05-08T08:28:53+00:00 add section about deriving - - - - - 11252ea1 by Simon Marlow at 2006-05-24T15:43:10+00:00 replace a fatal error in lexChar with a parseError - - - - - 382c9411 by Simon Marlow at 2006-05-24T15:45:47+00:00 add a bug - - - - - b79272f5 by Simon Marlow at 2006-05-24T15:46:29+00:00 add a bug report - - - - - 912edf65 by David Waern at 2006-07-10T19:09:23+00:00 Initial modifications -- doesn't compile - - - - - a3c7ba99 by David Waern at 2006-07-11T00:54:19+00:00 More porting work -- doesn't compile - - - - - 0a173d19 by David Waern at 2006-07-11T11:30:03+00:00 Make the repos temporarily compile and illustrate a problem - - - - - bad316de by David Waern at 2006-07-11T15:43:47+00:00 Progress on the porting process - - - - - bbf12d02 by David Waern at 2006-07-11T23:07:44+00:00 More progress on the porting -- first pass starting to shape up - - - - - de580ba2 by David Waern at 2006-07-20T17:48:30+00:00 More progress -- still on phase1 - - - - - 75a917a2 by David Waern at 2006-07-23T18:22:43+00:00 More work on pass1 -- mostly done - - - - - 6697b3f7 by David Waern at 2006-07-23T22:17:40+00:00 More work, started working on the renaming phase -- this code will need a cleanup soon :) - - - - - 82a5bcbb by David Waern at 2006-07-29T16:16:43+00:00 Add instances, build renaming environment, start on the renamer - - - - - c3f8f4f1 by David Waern at 2006-07-29T21:37:48+00:00 Complete the renamer - - - - - 7e00d464 by David Waern at 2006-07-30T21:01:57+00:00 Start porting the Html renderer - - - - - f04ce121 by David Waern at 2006-08-09T20:04:56+00:00 More Html rendering progress - - - - - 20c21b53 by David Waern at 2006-08-10T17:37:47+00:00 More progress - - - - - d7097e0d by David Waern at 2006-08-11T20:31:51+00:00 Cleanup - - - - - a7351e86 by David Waern at 2006-08-12T11:44:47+00:00 Render H98 Data declarations - - - - - 3fb2208e by David Waern at 2006-08-12T17:15:34+00:00 Perfect rendering of Test.hs - - - - - 454fd062 by David Waern at 2006-08-13T21:57:08+00:00 Misc fixes and interface load/save - - - - - 7ef7e7be by David Waern at 2006-08-14T00:56:07+00:00 Some refactoring - - - - - a7d3efef by David Waern at 2006-08-19T20:07:55+00:00 Adapt to latest GHC - - - - - 5fc3c0d7 by David Waern at 2006-08-20T21:28:11+00:00 Move interface read/write to its own module + some cleanup - - - - - 037e011c by David Waern at 2006-08-20T21:38:24+00:00 Small cleanup - - - - - da3a1023 by David Waern at 2006-09-03T16:05:22+00:00 Change mode to BatchCompile to avoid GHC API bug - - - - - 3cc9be3b by David Waern at 2006-09-03T16:06:59+00:00 Starting work on GADT rendering - - - - - 94506037 by David Waern at 2006-09-03T20:02:48+00:00 Compensate for change of export list order in GHC - - - - - c2cec4eb by David Waern at 2006-09-04T20:53:01+00:00 Rename a function - - - - - 9a9735ba by David Waern at 2006-09-05T15:51:21+00:00 Change version number to 2.0 - - - - - 3758a714 by David Waern at 2006-09-05T15:51:49+00:00 Align comment properly - - - - - 68478d9e by David Waern at 2006-09-15T18:03:00+00:00 Remove interface reading/writing code and use the GHC api for creating package environments instead - - - - - d2eedd95 by David Waern at 2006-09-15T18:05:29+00:00 Change the executable name to haddock-ghc-nolib - - - - - fcfbcf66 by David Waern at 2006-09-15T18:05:45+00:00 Small source code cleanup - - - - - d08eb017 by David Waern at 2006-09-15T18:06:21+00:00 Remove handling of --package flag - - - - - b8a4cf53 by David Waern at 2006-09-15T18:07:16+00:00 Remove commented-out code - - - - - bef0a684 by David Waern at 2006-09-15T18:37:57+00:00 Don't warn about missing links to () - - - - - e7d25fd7 by David Waern at 2006-09-15T19:50:49+00:00 Remove Interface and Binary2 modules - - - - - 9894f2a1 by David Waern at 2006-09-15T19:53:43+00:00 Remove debug printing from HaddockHtml - - - - - a0e7455d by David Waern at 2006-09-16T00:16:29+00:00 Comments only - - - - - d5b26fa7 by David Waern at 2006-09-16T00:16:57+00:00 Refactor PackageData creation code and start on building the doc env propery (unfinished) - - - - - 06aaa779 by David Waern at 2006-09-16T00:19:25+00:00 Better comments in Main.hs - - - - - 1a52d1b4 by David Waern at 2006-09-18T22:17:11+00:00 Comments and spacing change - - - - - e5a97767 by David Waern at 2006-09-21T17:02:45+00:00 Remove unnecessary fmapM import in Main - - - - - 9d0f9d3a by David Waern at 2006-09-22T18:07:07+00:00 Make import list in HaddockHtml prettier - - - - - 3452f662 by David Waern at 2006-09-22T18:08:47+00:00 Refactor context rendering - - - - - 12d0a6d0 by David Waern at 2006-09-22T18:09:52+00:00 Do proper HsType rendering (inser parentheses correctly) - - - - - 2c20c2f9 by David Waern at 2006-09-22T18:10:45+00:00 Fix a bug in Main.toHsType - - - - - c5396443 by David Waern at 2006-09-22T18:11:16+00:00 Skip external package modules sort for now - - - - - 3fb95547 by David Waern at 2006-09-22T20:35:40+00:00 Take away trailin "2" on all previously clashing type names - - - - - 2174755f by David Waern at 2006-09-22T20:51:43+00:00 Remove unused imports in Main - - - - - 1e9f7a39 by David Waern at 2006-09-22T20:52:11+00:00 Fix a comment in Main - - - - - 32d9e028 by David Waern at 2006-10-05T16:40:11+00:00 Merge with changes to ghc HEAD - - - - - 3058c8f5 by David Waern at 2006-10-05T16:41:02+00:00 Comment fixes - - - - - b9c217ec by David Waern at 2006-10-05T16:49:59+00:00 Filter out more builtin type constructors from warning messages - - - - - 67e7d252 by David Waern at 2006-10-05T19:38:22+00:00 Refactoring -- better structured pass1 - - - - - cd21c0c1 by David Waern at 2006-10-05T19:44:42+00:00 Remove read/dump interface flags - - - - - 313f9e69 by David Waern at 2006-10-05T19:49:26+00:00 Remove unused pretty printing - - - - - 480f09d1 by David Waern at 2006-12-28T13:22:24+00:00 Update to build with latest GHC HEAD - - - - - 63dccfcb by David Waern at 2007-01-05T01:38:45+00:00 Fixed a bug so that --ghc-flag works correctly - - - - - 3117dadc by David Waern at 2006-12-29T18:53:39+00:00 Automatically get the GHC lib dir - - - - - 9dc84a5c by David Waern at 2006-12-29T19:58:53+00:00 Comments - - - - - 0b0237cc by David Waern at 2007-01-05T16:48:30+00:00 Collect docs based on SrcLoc, syncing with removal of DeclEntity from GHC - - - - - a962c256 by David Waern at 2007-01-05T17:02:47+00:00 Add tabs in haddock.cabal - - - - - 0ca30c97 by David Waern at 2007-01-05T17:04:11+00:00 Add GHCUtils.hs - - - - - c0ab9abe by David Waern at 2007-01-10T11:43:08+00:00 Change package name to haddock-ghc, version 0.1 - - - - - 38e18b27 by David Waern at 2007-01-12T12:03:52+00:00 No binder name for foreign exports - - - - - d18587ab by David Waern at 2007-01-12T12:08:15+00:00 Temp record - - - - - ba6251a0 by David Waern at 2007-01-12T18:27:55+00:00 Remove read/dump-interface (again) - - - - - f4ba2b39 by David Waern at 2007-01-12T18:31:36+00:00 Remove DocOption, use the GHC type - - - - - 511be8bd by David Waern at 2007-01-12T18:32:41+00:00 Use exceptions instead of Either when loading package info - - - - - 0f2144d8 by David Waern at 2007-01-12T18:33:23+00:00 Small type change - - - - - 77507eb7 by David Waern at 2007-01-12T18:33:59+00:00 Remove interface file read/write - - - - - 0ea1e14f by David Waern at 2007-01-17T21:40:26+00:00 Add trace_ppr to GHCUtils - - - - - 3878b493 by David Waern at 2007-01-17T21:40:53+00:00 Sort external package modules and build a doc env - - - - - 8dc323fc by David Waern at 2007-01-17T21:42:41+00:00 Remove comment - - - - - f4c5b097 by David Waern at 2007-01-18T23:22:18+00:00 Add haddock-ghc.cabal and remove ghc option pragma in source file - - - - - da242b2c by David Waern at 2007-01-18T23:22:46+00:00 Remove some tabs - - - - - 288ed096 by David Waern at 2007-01-18T23:39:28+00:00 Moved the defaultErrorHandler to scope only over sortAndCheckModules for now - - - - - 4dd150fe by David Waern at 2007-02-03T21:23:56+00:00 Let restrictCons handle infix constructors - - - - - 97893442 by David Waern at 2007-02-04T16:26:00+00:00 Render infix data constructors - - - - - da89db72 by David Waern at 2007-02-04T16:26:33+00:00 CHange project name to Haddock-GHC - - - - - e93d48af by David Waern at 2007-02-04T16:59:08+00:00 Render infix type constructors properly - - - - - 357bc99b by David Waern at 2007-02-04T17:37:08+00:00 Insert spaces around infix function names - - - - - ab6cfc49 by David Waern at 2007-02-04T17:59:54+00:00 Do not list entities without documentation - - - - - 04249c7e by David Waern at 2007-02-04T19:16:25+00:00 Add GADT support (quite untested) - - - - - 2c223f8d by David Waern at 2007-02-04T19:25:10+00:00 Add package file write/save again! - - - - - b07ed218 by David Waern at 2007-02-04T19:33:02+00:00 Comment out minf_iface based stuff - - - - - 953d1fa7 by David Waern at 2007-02-05T00:12:23+00:00 Solve conflicts - - - - - 593247fc by David Waern at 2007-02-06T19:48:48+00:00 Remove -package flag, GHC's can be used instead - - - - - f658ded2 by David Waern at 2007-02-06T20:50:44+00:00 Start for support of ATs - - - - - 97f9e913 by David Waern at 2007-02-06T20:52:27+00:00 Wibble - - - - - 2ce8e4cf by David Waern at 2007-02-16T12:09:49+00:00 Add the DocOptions change - - - - - dee4a9b5 by David Waern at 2007-03-06T01:24:48+00:00 Wibble - - - - - 7cb99d18 by David Waern at 2007-03-06T01:24:58+00:00 Change version to 2.0 and executable name to haddock - - - - - c5aa02bc by David Waern at 2007-03-08T15:59:49+00:00 Go back to -B flag - - - - - 3a349201 by David Waern at 2007-03-09T13:31:59+00:00 Better exception handling and parsing of GHC flags - - - - - 05a69b71 by David Waern at 2007-03-09T17:45:44+00:00 Remove commented-out DocEntity printing - - - - - 755032cb by davve at dtek.chalmers.se at 2007-03-23T23:30:20+00:00 Remove a file that shouldn't be here - - - - - a7077e5f by davve at dtek.chalmers.se at 2007-03-24T03:58:48+00:00 Remove an import - - - - - 6f55aa8b by davve at dtek.chalmers.se at 2007-03-25T00:46:48+00:00 Start work on Haddock API - - - - - f0199480 by davve at dtek.chalmers.se at 2007-03-25T00:56:36+00:00 Prettify some comments - - - - - f952f9d1 by davve at dtek.chalmers.se at 2007-03-25T00:56:53+00:00 Remove ppr in HaddockTypes - - - - - bc594904 by davve at dtek.chalmers.se at 2007-03-25T00:57:53+00:00 Remove commented out doc env inference - - - - - 11ebf08d by davve at dtek.chalmers.se at 2007-03-25T01:23:25+00:00 De-flatten the namespace - - - - - f696b4bc by davve at dtek.chalmers.se at 2007-03-25T03:21:48+00:00 Add missing stuff to API - - - - - 9a2a04c3 by davve at dtek.chalmers.se at 2007-03-25T03:22:02+00:00 Wibble - - - - - 7d04a6d5 by davve at dtek.chalmers.se at 2007-03-25T03:22:08+00:00 Avoid a GHC bug with parseStaticFlags [] - - - - - 4d2820ba by davve at dtek.chalmers.se at 2007-03-26T04:57:01+00:00 Add fall-through case to mkExportItem - - - - - 6ebc8950 by Stefan O'Rear at 2007-03-26T04:14:53+00:00 Add shebang line to Setup.lhs - - - - - 80966ec5 by davve at dtek.chalmers.se at 2007-03-26T05:24:26+00:00 Fix stupid compile error - - - - - 1ea1385d by davve at dtek.chalmers.se at 2007-04-05T17:19:56+00:00 Do save/read of interface files properly - - - - - 0e4f6541 by David Waern at 2007-04-10T21:08:36+00:00 Add version to ghc dependency - - - - - b0499b63 by David Waern at 2007-04-10T21:37:08+00:00 Change package name to haddock - - - - - 9d50d27e by David Waern at 2007-04-24T00:22:14+00:00 Use filepath package instead of FilePath - - - - - 87c7fcdf by David Waern at 2007-07-10T21:03:04+00:00 Add new package dependencies - - - - - 4768709c by David Waern at 2007-07-11T20:37:11+00:00 Follow changes to record constructor representation - - - - - b9a02fee by Simon Marlow at 2007-05-30T14:00:48+00:00 update to compile with the latest GHC & Cabal - - - - - c0ebdc01 by David Waern at 2007-07-11T21:35:45+00:00 Fix conflicts - - - - - 97f7afd4 by David Waern at 2007-07-11T21:52:38+00:00 Follow changes to the GHC API - - - - - a5b7b58f by David Waern at 2007-07-12T20:36:48+00:00 Call parseStaticFlags before newSession - - - - - f7f50dbc by David Waern at 2007-08-01T21:52:58+00:00 Better indentation in haddock.cabal - - - - - d84e52ad by David Waern at 2007-08-02T00:08:18+00:00 Wibble - - - - - a23f494a by David Waern at 2007-08-02T00:08:24+00:00 Be better at trying to load all module dependencies (debugging) - - - - - ee917f13 by David Waern at 2007-08-03T18:48:08+00:00 Load all targets explicitly (checkModule doesn't chase dependencies anymore) - - - - - 5182d631 by David Waern at 2007-08-16T16:48:55+00:00 Finalize support for links to other packages - - - - - dfd1e3da by David Waern at 2007-08-16T16:51:11+00:00 Fix haddock comment errors in Haddock.Types - - - - - 50c0d83e by David Waern at 2007-08-16T16:51:37+00:00 Remove a debug import - - - - - d84b7c2b by David Waern at 2007-08-16T17:06:30+00:00 Rename PackageData to HaddockPackage - - - - - 3b52cb9f by David Waern at 2007-08-16T17:09:42+00:00 Simplify some comments - - - - - 66fa68d9 by David Waern at 2007-08-16T17:11:38+00:00 Comment the HaddockPackage definition - - - - - 8674c761 by David Waern at 2007-08-16T17:25:54+00:00 Improve code layout in Main - - - - - 571a3a0b by David Waern at 2007-08-16T17:32:13+00:00 Remove explict module imports in Main - - - - - d31b3cb0 by David Waern at 2007-08-16T17:36:23+00:00 Correct comments - - - - - 7f8a9f2b by David Waern at 2007-08-16T17:39:50+00:00 Fix layout problems in Haddock.Types - - - - - 9f421d7f by David Waern at 2007-08-17T11:16:48+00:00 Move options out of Main into Haddock.Options - - - - - 80042b63 by David Waern at 2007-08-17T11:26:59+00:00 Small comment/layout fixes - - - - - b141b982 by David Waern at 2007-08-17T11:28:28+00:00 Change project name from Haddock-GHC to Haddock - - - - - dbeb4a81 by David Waern at 2007-08-17T11:41:05+00:00 Add top module comment to all files - - - - - ce99cc9e by David Waern at 2007-08-17T14:53:04+00:00 Factor out typechecking phase into Haddock.Typecheck - - - - - 6bf75d9e by David Waern at 2007-08-17T16:55:35+00:00 Factor out package code to Haddock.Packages - - - - - b396db37 by David Waern at 2007-08-29T22:40:23+00:00 Major refactoring - - - - - 3d4f95ee by David Waern at 2007-08-29T23:26:24+00:00 Rename HaddockModule to Interface and a few more refactorings - - - - - c55326db by David Waern at 2007-08-29T23:48:03+00:00 Some comment cleanup - - - - - 9a84fc46 by David Waern at 2007-08-29T23:49:29+00:00 Add some modules that I forgot to add earlier - - - - - 4536dce2 by David Waern at 2007-08-29T23:55:24+00:00 Wibble - - - - - 9b7f0206 by David Waern at 2007-08-30T16:03:29+00:00 Wibble - - - - - c52c050a by David Waern at 2007-08-30T16:30:37+00:00 Rename HaddockModule to Interface - - - - - eae2995f by David Waern at 2007-08-30T16:42:59+00:00 Simplify createInterfaces - - - - - 53f99caa by David Waern at 2007-09-29T00:04:31+00:00 Add build-type: Simple to the cabal file - - - - - 0d3103a8 by David Waern at 2007-09-29T00:04:58+00:00 Add containers and array dependency - - - - - 6acf5f30 by David Waern at 2007-09-29T00:13:36+00:00 Prettify the cabal file - - - - - 87c1e378 by David Waern at 2007-09-29T13:16:39+00:00 FIX: consym data headers with more than two variables - - - - - b67fc16a by David Waern at 2007-09-29T14:01:32+00:00 FIX: prefix types used as operators should be quoted - - - - - a8f925bc by David Waern at 2007-09-29T14:02:26+00:00 Use isSymOcc from OccName instead of isConSym - - - - - fc330701 by David Waern at 2007-09-29T14:15:37+00:00 Use isLexConSym/isLexVarSym from OccName - - - - - e4f3dbad by David Waern at 2007-09-29T15:01:08+00:00 FIX: do not quote varsym type operators - - - - - 402207d2 by David Waern at 2007-09-29T15:01:50+00:00 Wibble - - - - - f9d89ef0 by David Waern at 2007-09-29T15:17:40+00:00 Take care when pp tyvars - add parens on syms - - - - - 849e2a77 by David Waern at 2007-10-01T21:56:39+00:00 Go back to using a ModuleMap instead of LookupMod - fixes a bug - - - - - 549dbac6 by David Waern at 2007-10-02T01:05:19+00:00 Improve parsing of doc options - - - - - a36021b8 by David Waern at 2007-10-02T23:05:00+00:00 FIX: double arrows in constructor contexts - - - - - d03bf347 by David Waern at 2007-10-09T16:14:05+00:00 Add a simple test suite - - - - - c252c140 by David Waern at 2007-10-17T16:02:28+00:00 Add --optghc=.. style flag passing to GHC - - - - - cce6c1b3 by David Waern at 2007-10-18T22:03:20+00:00 Add support for --read-interface again - - - - - 33d059c0 by David Waern at 2007-10-18T22:30:18+00:00 Refactoring -- get rid of Haddock.Packages - - - - - f9ed0a4c by David Waern at 2007-10-18T22:34:36+00:00 Name changes - - - - - 8a1c816f by David Waern at 2007-10-20T14:24:23+00:00 Add --ghc-version option - - - - - 4925aaa1 by David Waern at 2007-10-21T14:34:26+00:00 Add some Outputable utils - - - - - 69e7e47f by David Waern at 2007-10-21T14:35:49+00:00 FIX: Ord for OrdName was not comparing modules - - - - - 5a4ae535 by David Waern at 2007-10-21T21:18:48+00:00 Wibble - - - - - 03d48e20 by David Waern at 2007-10-24T15:52:56+00:00 Remove Main from "other modules" - - - - - c66f6d82 by David Waern at 2007-10-24T16:37:18+00:00 Make it possible to run haddock on itself - - - - - 21d156d8 by David Waern at 2007-10-25T14:02:14+00:00 Don't set boot modules as targets - - - - - f8bcf91c by David Waern at 2007-10-31T22:11:17+00:00 Add optimisation flags - - - - - 7ac758f2 by David Waern at 2007-11-04T09:48:28+00:00 Go back to loading only targets (seems to work now) - - - - - 4862aae1 by David Waern at 2007-11-05T22:24:57+00:00 Do full compilation of modules -- temporary fix for GHC API problem - - - - - 697e1517 by David Waern at 2007-11-05T22:25:50+00:00 Don't warn about not being able to link to wired/system/builtin-names - - - - - 892186da by David Waern at 2007-11-06T00:49:21+00:00 Filter out instances with TyCons that are not exported - - - - - 9548314c by David Waern at 2007-11-06T09:37:14+00:00 Wibble - - - - - 5cafd627 by David Waern at 2007-11-08T01:43:07+00:00 Filter out all non-vanilla type sigs - - - - - 04621830 by David Waern at 2007-11-08T01:45:13+00:00 Synch loading of names from .haddock files with GHC's name cache - - - - - 88d37f77 by David Waern at 2007-11-08T01:46:21+00:00 Remove commented-out code - - - - - 6409c911 by David Waern at 2007-11-08T01:56:00+00:00 Small bugfix and cleanup in getDeclFromTyCls - - - - - af59d9c2 by David Waern at 2007-11-08T02:08:44+00:00 Remove OrdName stuff - - - - - 3a615e2e by David Waern at 2007-11-08T02:13:41+00:00 Update runtests.hs following changes to haddock - - - - - 01f3314e by David Waern at 2007-11-08T02:33:01+00:00 Complain if we can't link to wired-in names - - - - - fcafb5d1 by David Waern at 2007-11-09T02:40:16+00:00 Don't exit when there are no file arguments - - - - - 194bc332 by David Waern at 2007-11-09T02:55:37+00:00 Wibble - - - - - dbe4cb55 by David Waern at 2007-11-09T02:56:14+00:00 Wibble - - - - - 82869fda by David Waern at 2007-11-10T17:01:43+00:00 Introduce InstalledInterface structure and add more stuff to the .haddock files We introduce InstalledInterface capturing the part of Interface that is stored in the interface files. We change the ppHtmlContents and ppHtmllIndex to take this structure instead of a partial Interface. We add stuff like the doc map and exported names to the .haddock file (via InstalledInterface). - - - - - d6bb57bf by David Waern at 2007-11-10T17:19:48+00:00 FIX: contents and index should include external package modules when --gen-contents/--gen-index - - - - - e8814716 by David Waern at 2007-11-11T00:29:27+00:00 Remove lDocLinkName and its use in Html backend - - - - - 6f9bd702 by David Waern at 2007-11-11T00:50:57+00:00 Do some refactoring in the html backend This also merges an old patch by Augustsson: Wed Jul 12 19:54:36 CEST 2006 lennart.augustsson at credit-suisse.com * Print type definitions like signatures if given arrows. - - - - - 09d0ce24 by Malcolm.Wallace at 2006-07-20T13:13:57+00:00 mention HsColour in the docs, next to option flags for linking to source code - - - - - 24da6c34 by Malcolm.Wallace at 2006-07-20T13:14:50+00:00 change doc references to CVS to give darcs repository location instead - - - - - 74d52cd6 by David Waern at 2007-11-11T00:55:33+00:00 Update copyright - - - - - fcaa3b4f by Duncan Coutts at 2006-09-08T13:41:00+00:00 Eliminate dep on network by doing a little cut'n'paste haddock depending on the network causes a circular dependency at least if you want to build the network lib with haddock docs. - - - - - 10cc9bda by David Waern at 2007-11-11T02:09:41+00:00 Fix conflicts - - - - - 4e3acd39 by David Waern at 2007-11-11T02:21:19+00:00 Manual merge of a patch from Duncan Coutts that removes the dependency on mtl - - - - - fa9070da by Neil Mitchell at 2006-09-29T15:52:03+00:00 Do not generate an empty table if there are no exports, this fixes a <table></table> tag being generated, which is not valid HTML 4.01 - - - - - d7431c85 by David Waern at 2007-11-11T02:28:50+00:00 Fix conflicts - - - - - f87e8f98 by Simon Marlow at 2006-10-10T11:37:16+00:00 changes for 0.8 - - - - - db929565 by Simon Marlow at 2006-10-10T12:07:12+00:00 fix the name of the source file - - - - - 8220aa4b by Simon Marlow at 2006-10-11T14:17:37+00:00 Rename haddock.js to haddock-util.js haddock.js will be run automatically by Windows when you type 'haddock' if it is found on the PATH, so rename to avoid confusion. Spotted by Adrian Hey. - - - - - 6bccdaa1 by sven.panne at 2006-10-12T15:28:23+00:00 Cabal's sdist does not generate "-src.tar.gz" files, but ".tar.gz" ones - - - - - d3f3fc19 by Simon Marlow at 2006-12-06T16:05:07+00:00 add todo item for --maintainer - - - - - 2da7e269 by Simon Marlow at 2006-12-15T15:52:00+00:00 TODO: do something better about re-exported symbols from another package - - - - - 42d85549 by David Waern at 2007-11-11T02:30:59+00:00 Fix conflicts - - - - - 5e7ef6e5 by Neil Mitchell at 2007-01-11T15:41:15+00:00 Never do spliting index files into many - - - - - f3d4aebe by Neil Mitchell at 2007-01-11T17:07:09+00:00 Add searching on the index page - - - - - bad3ab66 by Neil Mitchell at 2007-01-11T18:17:46+00:00 Delete dead code, now there is only one index page - - - - - cd09eedb by Neil Mitchell at 2007-01-11T18:21:19+00:00 Delete more stuff that is no longer required - - - - - e2806646 by David Waern at 2007-11-11T02:41:53+00:00 Fix conflicts - - - - - a872a823 by Neil Mitchell at 2007-01-11T18:51:43+00:00 Make the index be in case-insensitive alphabetic order - - - - - 8bddd9d7 by Neil Mitchell at 2007-02-06T17:49:12+00:00 Do not create empty tables for data declarations which don't have any constructors, instances or comments. Gets better HTML 4.01 compliance - - - - - 036b8120 by David Waern at 2007-11-11T02:56:58+00:00 Fix conflicts - - - - - f50c1639 by Conal Elliott at 2007-02-14T21:54:00+00:00 added substitution %{FILE///c} - - - - - 402e166a by David Waern at 2007-11-11T03:35:46+00:00 Manual merge of old patch: Sat Apr 21 04:36:43 CEST 2007 Roberto Zunino <zunrob at users.sf.net> * URL expansion for %%, %L, %{LINE} - - - - - 2f264fbd by David Waern at 2007-11-11T03:40:33+00:00 Manual merge of an old patch: Thu Apr 19 20:23:40 CEST 2007 Wolfgang Jeltsch <g9ks157k at acme.softbase.org> * bug fix When Haddock was invoked with the --ignore-all-exports flag but the ignore-exports module attribute wasn't used, hyperlinks weren't created for non-exported names. This fix might not be as clean as one would wish (since --ignore-all-exports now results in ignore_all_exports = True *and* an additional OptIgnoreExports option for every module) but at least the bug seems to be resolved now. - - - - - 7d7ae106 by sven.panne at 2007-09-02T12:18:02+00:00 Install LICENSE in the correct place - - - - - 66eaa924 by David Waern at 2007-11-11T19:02:46+00:00 Fix a bug that made haddock loop - - - - - 4ed47b58 by David Waern at 2007-11-11T19:03:09+00:00 Rename java-script file (this wasn't merge correctly) - - - - - d569534a by David Waern at 2007-11-11T19:06:44+00:00 Don't require -B <ghc-libdir> when no argument files Change readInterfaceFile to take a Maybe Session, to avoid having to pass -B <ghc-libdir> to Haddock when there're no source files to process. This is nice when computing contents/index for external packages. - - - - - 373368bc by Neil Mitchell at 2007-01-11T18:22:44+00:00 Change from tabs to spaces in the ppHtmlIndex function - - - - - 6b063a77 by Neil Mitchell at 2007-01-12T12:17:46+00:00 Rewrite much of the index searching code, previously was too slow to execute on the base library with IE, the new version guarantees less than O(log n) operations be performed, where n is the number in the list (before was always O(n)) - - - - - bfad00b7 by David Waern at 2007-11-11T23:33:53+00:00 Fix conflicts - - - - - cd2dcc09 by Neil Mitchell at 2007-01-12T12:25:01+00:00 Make the max number of results 75 instead of 50, to allow map searching in the base library to work - - - - - 3ae74764 by Neil Mitchell at 2007-01-12T12:58:17+00:00 Make the search box in a form so that enter does the default search - - - - - 142103e5 by David Waern at 2007-11-12T00:03:18+00:00 Merge patch from the old branch: Fri Aug 31 13:21:45 CEST 2007 Duncan Coutts <duncan at haskell.org> * Add category: Development to .cabal file Otherwise it appears on the hackage website in the "Unclassified" category. - - - - - 22ec2ddb by David Waern at 2007-11-25T01:55:29+00:00 A a list of small improvements to the TODO file - - - - - eb0129f4 by Wolfgang Jeltsch at 2007-12-03T23:47:55+00:00 addition of type equality support (at least for HTML generation) - - - - - 816a7e22 by David Waern at 2007-12-08T15:46:26+00:00 Handle class operators correctly when rendering predicates - - - - - 68baaad2 by David Waern at 2007-12-08T16:15:54+00:00 Code layout changes - - - - - 09b77fb4 by David Waern at 2007-12-08T16:16:03+00:00 Handle infix operators correctly in the Type -> HsType translation - - - - - 31c36da2 by David Waern at 2007-12-08T16:24:27+00:00 Add ppLParendTypes/ppLParendType - - - - - b17cc818 by David Waern at 2007-12-08T16:26:12+00:00 Use ppParendType when printing types args in predicates - - - - - ffd1f2cf by David Waern at 2007-12-08T16:45:06+00:00 Fix rendering of instance heads to handle infix operators This is also a refactoring to share this code for rendering predicates. - - - - - ff886d45 by David Waern at 2007-12-08T17:27:46+00:00 Fix rendering of class operators - - - - - e2fcbb9e by David Waern at 2007-12-08T17:59:28+00:00 Fix a bug (use ppTyName instead of ppName to print names in type apps) - - - - - 79a1056e by David Waern at 2007-12-08T21:25:18+00:00 Update tests - - - - - 867741ac by David Waern at 2007-12-08T21:25:49+00:00 Give a diff on test failure - - - - - 7e5eb274 by David Waern at 2008-01-05T14:33:45+00:00 Add DrIFT commands - - - - - 3656454d by David Waern at 2008-01-05T20:26:00+00:00 Add "cabal-version: >= 1.2" to the cabal file - - - - - 77974efc by Simon Marlow at 2007-12-20T09:52:44+00:00 add an item - - - - - f6ac1708 by Simon Marlow at 2007-12-06T14:00:10+00:00 Source links must point to the original module, not the referring module - - - - - eda1d5c9 by David Waern at 2008-01-06T14:40:52+00:00 Manual merge of a patch to the 0.8 branch Thu Dec 6 15:00:10 CET 2007 Simon Marlow <simonmar at microsoft.com> * Source links must point to the original module, not the referring module - - - - - 378f4085 by David Waern at 2008-01-06T16:03:45+00:00 Change stability from stable to experimental - - - - - 8bdafe44 by David Waern at 2008-01-06T16:14:22+00:00 Add haskell.vim (it had been removed somehow) - - - - - ea34d02e by David Waern at 2008-01-06T16:36:57+00:00 Change version to 2.0.0.0 - - - - - 34631ac0 by David Waern at 2008-01-06T16:44:57+00:00 Add missing modules to the cabal file - - - - - 9e142935 by David Waern at 2008-01-06T17:25:42+00:00 Depend on ghc >= 6.8.2 && < 6.9 - - - - - 59f9eeaa by Simon Marlow at 2007-12-20T10:43:04+00:00 add build scripts - - - - - 1c29ae30 by Simon Marlow at 2007-12-20T10:47:07+00:00 update version number - - - - - fe16a3e4 by Simon Marlow at 2007-12-20T10:48:03+00:00 update version - - - - - f688530f by Simon Marlow at 2007-12-20T10:48:29+00:00 doc updates - - - - - ce71b611 by David Waern at 2008-01-07T13:46:32+00:00 Change version in docs and spec - - - - - 03ab8d6f by David Waern at 2008-01-07T13:47:38+00:00 Manually merge over changes to CHANGES for 0.9 - - - - - 39f1b042 by David Waern at 2008-01-07T15:17:41+00:00 Remove the -use-package flag, we don't support it anyway - - - - - 7274a544 by David Waern at 2008-01-07T15:33:05+00:00 Update CHANGES for 2.0.0.0 - - - - - 96594f5d by David Waern at 2008-01-07T15:46:49+00:00 Wibble - - - - - f4c5a4c4 by David Waern at 2008-01-07T15:55:36+00:00 Change url to repo in documentation - - - - - 8a4c77f0 by David Waern at 2008-01-07T16:00:54+00:00 Update CHANGES - - - - - cb3a9288 by David Waern at 2008-01-07T16:02:55+00:00 Documentation fix - - - - - d8e45539 by David Waern at 2008-01-07T16:12:00+00:00 Update docs to say that Haddock accets .lhs files and module names - - - - - 4b5ce824 by David Waern at 2008-01-07T16:12:25+00:00 Document -B option - - - - - 47274262 by David Waern at 2008-01-07T16:23:07+00:00 Update CHANGES - - - - - 7ff314a9 by David Waern at 2008-01-07T16:23:20+00:00 Remove --use-package, --package & --no-implicit.. flags from docs - - - - - 6c3819c0 by David Waern at 2008-01-07T16:23:52+00:00 Remove --no-implicit-prelide flag - - - - - 1b14ae40 by David Waern at 2008-01-07T16:32:26+00:00 Update the "Using literate or pre-processed source" section - - - - - 0117f620 by David Waern at 2008-01-07T16:41:55+00:00 Document the --optghc flag - - - - - 087ab1cf by David Waern at 2008-01-07T16:42:10+00:00 Remove the documenation section on derived instances The problem mentioned there doesn't exist in Haddock 2.0.0.0 - - - - - 7253951e by David Waern at 2008-01-07T16:48:40+00:00 Document OPTIONS_HADDOCK - - - - - 3b6bdcf6 by David Waern at 2008-01-07T16:56:54+00:00 Wibble - - - - - 3025adf9 by David Waern at 2008-01-07T17:08:14+00:00 Wibble - - - - - 5f30f1a0 by David Waern at 2008-01-07T17:15:44+00:00 Change synopsis field to description - - - - - 1673f54b by David Waern at 2008-01-07T17:18:21+00:00 Change my email address in the cabal file - - - - - 55aa9808 by David Waern at 2008-01-07T18:18:02+00:00 Add documentation for readInterfaceFile - - - - - eaea417f by David Waern at 2008-01-07T18:21:30+00:00 Export necessary stuff from Distribution.Haddock - - - - - 7ea18759 by David Waern at 2008-01-07T18:31:49+00:00 Remove dep on Cabal - - - - - 7b79c74e by David Waern at 2008-01-07T18:33:49+00:00 Remove dep on process - - - - - ce3054e6 by David Waern at 2008-01-16T23:01:21+00:00 Add feature-requsts from Henning Thielemann to TODO - - - - - 0c08f1ec by David Waern at 2008-01-16T23:03:02+00:00 Record a bug in TODO - - - - - b04605f3 by David Waern at 2008-01-23T16:59:06+00:00 Add a bug reported by Ross to TODO - - - - - 5b17c030 by David Waern at 2008-01-23T18:05:53+00:00 A a bug report to TODO - - - - - 1c993b0d by David Waern at 2008-01-25T16:30:25+00:00 Accept test output - - - - - c22fc0d0 by David Waern at 2008-01-25T16:34:49+00:00 Accept test output - - - - - 4b795811 by David Waern at 2008-01-25T16:38:37+00:00 Change Hidden.hs (test) to use OPTIONS_HADDOCK - - - - - c124dbd9 by David Waern at 2008-01-25T16:39:23+00:00 Accept test output - - - - - ec6f6eea by David Waern at 2008-01-25T16:42:08+00:00 Add Hidden.html.ref to tests - - - - - 1dc9610c by David Waern at 2008-02-02T20:50:51+00:00 Add a comment about UNPACK bug in TODO - - - - - 2d3f7081 by David Waern at 2008-02-09T22:33:24+00:00 Change the representation of DocNames Ross Paterson reported a bug where links would point to the defining module instead of the "best" module for an identifier (e.g Int pointing to GHC.Base instead of Data.Int). This patch fixes this problem by refactoring the way renamed names are represented. Instead of representing them by: > data DocName = Link Name | NoLink Name they are now represented as such: > data DocName = Documented Name Module | Undocumented Name and the the link-env looks like this: > type LinkEnv = Map Name Module There are several reasons for this. First of all, the bug was caused by changing the module part of Names during the renaming process, without changing the Unique field. This caused names to be overwritten during the loading of .haddock files (which caches names using the NameCache of the GHC session). So we might create new Uniques during renaming to fix this (but I'm not sure that would be problem-free). Instead, we just keep the Name and add the Module where the name is best documented, since it can be useful to keep the original Name around (for e.g. source-code location info and for users of the Haddock API). Also, the names Link/NoLink don't really make sense, since wether to use links or not is entirely up to the users of DocName. In the process of following this change into H.Backends.Html I removed the assumption that binder names are Undocumented (which was just an unnecessary assumption, the OccName is the only thing needed to render these). This will probably make it possible to get rid of the renamer and replace it with a traversal from SYB or Uniplate. Since DocName has changed, InterfaceFile has changed so this patch also increments the file-format version. No backwards-compatibility is implemented. - - - - - 0f28c921 by David Waern at 2008-02-09T23:00:36+00:00 H.GHC.Utils: remove unused imports/exports - - - - - 0c44cad5 by David Waern at 2008-02-10T00:28:13+00:00 H.GHC.Utils: add some functions that were removed by mistake - - - - - e3452f49 by David Waern at 2008-02-10T00:28:48+00:00 Fix some trivial warnings in H.InterfaceFile - - - - - a6d74644 by David Waern at 2008-02-10T00:48:06+00:00 Update the version message to fit in small terminals - - - - - 76c9cd3e by David Waern at 2008-02-10T14:47:39+00:00 Remove bugs from TODO that don't apply anymore since the port - - - - - 5e10e090 by David Waern at 2008-02-10T15:22:47+00:00 Remove bugs from TODO that weren't actual bugs - - - - - fef70878 by David Waern at 2008-02-10T15:23:44+00:00 Remove yet another item from TODO that was not an actual bug - - - - - e1af47b8 by David Waern at 2008-02-11T10:25:57+00:00 Bump the version number to 2.1.0 Since the exported datatype DocName has changed, we need to bump the major version number. Let's also drop the fourth version component, it's not that useful. - - - - - e3be7825 by David Waern at 2008-04-11T14:29:04+00:00 Add a bug to TODO - - - - - cb6574be by David Waern at 2008-04-11T16:00:45+00:00 Use the in-place haddock when running tests - - - - - c6d7af0d by David Waern at 2008-04-11T16:09:16+00:00 Turn off GHC warnings when running tests - - - - - 7f61b546 by David Waern at 2008-04-11T17:24:00+00:00 Add a flag for turning off all warnings - - - - - 883b8422 by David Waern at 2008-04-12T14:02:18+00:00 Fix printing of data binders - - - - - 2a0db8fc by David Waern at 2008-04-12T18:52:46+00:00 Fix missing parenthesis in constructor args bug - - - - - 1b3ac3f9 by David Waern at 2008-04-12T18:57:23+00:00 Simplify test suite and add tests I move all tests into one single directory to simplify things, and add a test for the last bug that was fixed. - - - - - 8f178376 by David Waern at 2008-04-12T19:00:15+00:00 Add a script for copying test output to "expected" output - - - - - 193e3a03 by David Waern at 2008-04-12T19:16:37+00:00 Remove two fixed bugs from TODO - - - - - ddc9130c by David Waern at 2008-04-12T19:37:06+00:00 Update test README - - - - - 956069c0 by David Waern at 2008-05-01T12:16:14+00:00 Update version number in spec and docs - - - - - 5478621c by David Waern at 2008-05-01T12:28:12+00:00 Remove claim of backwards compatibility from docs for readInterfaceFile - - - - - 4a16dea9 by David Waern at 2008-05-01T12:33:04+00:00 Update CHANGES - - - - - 804216fb by David Waern at 2008-05-01T12:43:16+00:00 Add a synopsis - - - - - fd0c84d5 by David Waern at 2008-05-01T12:44:44+00:00 Add Haddock.DocName to the cabal file - - - - - 9f4a7439 by David Waern at 2008-05-01T12:45:53+00:00 Remove -fglasgow-exts and -fasm - - - - - aee7c145 by David Waern at 2008-05-01T12:54:01+00:00 Add LANGUAGE pragmas to source files - - - - - 9a58428b by David Waern at 2008-05-01T12:54:19+00:00 Add extensions to cabal file - - - - - 494f1bee by David Waern at 2008-05-01T13:12:09+00:00 Export DocName in the API - - - - - c938196b by David Waern at 2008-05-01T13:12:19+00:00 Add hide options to some source files - - - - - 236e86af by Neil Mitchell at 2008-06-07T20:45:10+00:00 Rewrite the --hoogle flag support - - - - - 6d910950 by Neil Mitchell at 2008-06-14T10:56:50+00:00 Simplify the newtype/data outputting in Hoogle, as haddock does it automatically - - - - - f87a95a8 by Neil Mitchell at 2008-06-14T12:10:18+00:00 Add initial structure for outputting documentation as well, but does not yet output anything - - - - - 7c3bce54 by Neil Mitchell at 2008-06-14T12:27:07+00:00 Remove <document comment> from the Hoogle output - - - - - 9504a325 by Neil Mitchell at 2008-06-16T06:33:21+00:00 Default to "main" if there is no package, otherwise will clobber hoogle's hoogle info - - - - - 4a794a79 by Neil Mitchell at 2008-06-16T06:53:29+00:00 Change packageName to packageStr, as it better reflects the information stored in it - - - - - 7abc9baf by Neil Mitchell at 2008-06-16T07:09:49+00:00 Add modulePkgInfo to Haddock.GHC.Utils, which gives back package name and version info - - - - - 8ca11514 by Neil Mitchell at 2008-06-16T07:13:48+00:00 Change Hoogle to take the package name and package version separately - - - - - a6da452d by Neil Mitchell at 2008-06-18T11:29:46+00:00 In Hoogle do not list things that are not local to this module - - - - - 974b76b7 by David Waern at 2008-06-19T18:40:13+00:00 Be more consistent with GHC API naming in H.GHC.Utils - - - - - 2facb4eb by David Waern at 2008-06-19T19:03:03+00:00 Update test output - - - - - c501de72 by David Waern at 2008-06-26T20:26:49+00:00 Use ghc-paths to get the lib dir The path can still be overridden using the -B flag. It's not longer required to pass the lib dir to the program that runs the test suite. - - - - - ac4c6836 by David Waern at 2008-06-26T20:33:08+00:00 Update CHANGES - - - - - 9d21c60a by David Waern at 2008-06-26T20:34:53+00:00 Update README - - - - - 741448f0 by David Waern at 2008-06-26T21:12:57+00:00 Improve wording in the help message - - - - - b1b42b11 by David Waern at 2008-06-30T10:16:17+00:00 Rename ForeignType - - - - - 6d6c2b34 by David Waern at 2008-06-30T10:25:09+00:00 Rename TyFamily - - - - - 8d1125ed by David Waern at 2008-06-30T10:37:21+00:00 Rename type patterns - - - - - 7610a4cb by David Waern at 2008-06-30T10:45:07+00:00 Rename associated types - - - - - 8eeba14c by David Waern at 2008-06-30T10:47:41+00:00 Remove the TODO file now that we have a trac - - - - - 1af5b25b by David Waern at 2008-07-02T18:19:28+00:00 Render type family declarations (untested) - - - - - ceb99797 by David Waern at 2008-07-02T18:24:06+00:00 Remove redundant check for summary when rendering data types - - - - - b36a58e0 by David Waern at 2008-07-02T22:01:38+00:00 More support for type families and associated types Now we just need to render the instances - - - - - 78784879 by David Waern at 2008-07-07T22:13:58+00:00 Remove filtering of instances We were filtering out all instances for types with unknown names. This was probably an attempt to filter out instances for internal types. I am removing the filtering for the moment, and will try to fix this properly later. - - - - - 3e758dad by David Waern at 2008-06-30T18:50:30+00:00 Run haddock in-place during testing - - - - - d9dab0ce by David Waern at 2008-07-08T21:04:32+00:00 Remove index.html and doc-index.html from output, they should not be versioned - - - - - 3e6c4681 by David Waern at 2008-07-08T21:06:42+00:00 Update test output following change to instance filtering - - - - - e34a3f14 by David Waern at 2008-07-12T16:48:28+00:00 Stop using the map from exported names to declarations During creation of the interface, we were using two maps: one from exported names to declarations, and one from all defined names in the module to declarations. The first contained subordinate names while the second one didn't. The first map was never used to look up names not defined in the associated module, so if we add subordinate names to the second map, we could use it everywhere. That's that this patch does. This simplifies code because we don't have to pass around two maps everywhere. We now store the map from locally defined things in the interface structure instead of the one from exported names. - - - - - 2e1d2766 by David Waern at 2008-07-12T16:55:21+00:00 Get the all locally defined names from GHC API We previously had some code to compute all locally defined names in a module including subordinate names. We don't need it since we can get the names from modInfoTyThings in the GHC API. - - - - - bf637994 by David Waern at 2008-07-13T13:09:16+00:00 Refactoring in H.Interface.Create We were creating a doc map, a declaration map and a list of entities separately by going through the HsGroup. These structures were all used to build the interface of a module. Instead of doing this, we can start by creating a list of declarations from the HsGroup, then collect the docs directly from this list (instead of using the list of entities), creating a documentation map. We no longer need the Entity data type, and we can store a single map from names to declarations and docs in the interface, instead of the declaration map and the doc map. This way, there is only one place where we filter out the declarations that we don't want, and we can remove a lot of code. Another advantage of this is that we can create the exports directly out of the list of declarations when we export the full module contents. (Previously we did a look up for each name to find the declarations). This is faster and removes another point where we depend on names to identify exported declarations, which is good because it eliminates problems with instances (which don't have names). - - - - - 547e410e by David Waern at 2008-07-13T13:34:51+00:00 Remove FastString import and FSLIT macro in H.I.Create -- they were unused - - - - - 693759d1 by David Waern at 2008-07-13T13:36:23+00:00 Remove unused import from H.I.Create - - - - - cde6e7fb by David Waern at 2008-07-13T13:51:54+00:00 Small touches - - - - - 96de8f1d by David Waern at 2008-07-20T11:21:46+00:00 Preparation for rendering instances as separate declarations We want to be able to render instances as separate declarations. So we remove the Name argument of ExportDecl, since instances are nameless. This patch also contains the first steps needed to gather type family instances and display them in the backend, but the implementation is far from complete. Because of this, we don't actually show the instances yet. - - - - - b0f824fb by David Waern at 2008-07-20T15:53:08+00:00 Follow changes to ExportDecl in Hoogle - - - - - 1192eff3 by Neil Mitchell at 2008-06-26T00:28:10+00:00 Change how the Hoogle backend outputs classes, adding the context in - - - - - 7a0d1464 by Neil Mitchell at 2008-06-26T00:28:46+00:00 Remove the indent utility function from Hoogle backend - - - - - 3361241b by Neil Mitchell at 2008-06-26T09:45:09+00:00 Add support for Hoogle writing ForeignImport/ForeignExport properly - - - - - 795ad3bf by Neil Mitchell at 2008-06-26T12:15:25+00:00 Flesh out the Hoogle code to render documentation - - - - - 23277995 by Neil Mitchell at 2008-06-26T14:56:41+00:00 Fix a bug in the Hoogle backend, unordered lists were being written out <ul>...</u> - - - - - db739b27 by Neil Mitchell at 2008-06-26T15:09:54+00:00 Remove any white space around a <li> element - - - - - f2e6bb8c by Neil Mitchell at 2008-07-10T15:30:47+00:00 Remove the TODO in the Hoogle HTML generation, was already done - - - - - 693ec9a3 by Neil Mitchell at 2008-07-10T15:53:00+00:00 Put brackets round operators in more places in the Hoogle output - - - - - 842313aa by Neil Mitchell at 2008-07-10T16:01:25+00:00 Print type signatures with brackets around the name - - - - - cf93deb0 by David Waern at 2008-07-20T17:04:22+00:00 Bump version number to 2.2.0 - - - - - 30e6a8d1 by David Waern at 2008-07-20T17:04:41+00:00 Resolve conflicts in H.B.Hoogle - - - - - 1f0071c9 by David Waern at 2008-07-23T23:05:01+00:00 Add "all" command to runtests.hs that runs all tests despite failures - - - - - f2723023 by David Waern at 2008-07-23T23:08:39+00:00 Update tests/README - - - - - c0304a11 by David Waern at 2008-07-23T23:21:15+00:00 Be compatible with GHC 6.8.3 The cabal file is converted to use the "new" syntax with explicit Library and Executable sections. We define the __GHC_PATCHLEVEL__ symbol using a conditinal cpp-options field in the cabal file. (Ideally, Cabal would define the symbol for us, like it does for __GLASGOW_HASKELL__). We use these symbols to #ifdef around a small difference between 6.8.2 and 6.8.3. Previously, we only supported GHC 6.8.2 officially but the dependencies field said "ghc <= 6.9". This was just for convenience when testing against the (then compatible) HEAD version of GHC, and was left in the release by mistake. Now, we support both GHC 6.8.2 and 6.8.3 and the dependencies field correctly reflects this. - - - - - 88a5fe71 by David Waern at 2008-07-23T23:54:16+00:00 Depend on the currently available ghc-paths versions only - - - - - 8738d97b by David Waern at 2008-07-24T10:50:44+00:00 FIX haskell/haddock#44: Propagate parenthesis level when printing documented types - - - - - 05339119 by David Waern at 2008-07-24T16:06:18+00:00 Drop unnecessary parenthesis in types, put in by the user We were putting in parenthesis were the user did. Let's remove this since it just clutters up the types. The types are readable anyway since we print parens around infix operators and do not rely on fixity levels. When doing this I discovered that we were relying on user parenthesis when printin types like (a `O` b) c. This patchs fixes this problem so that parenthesis are always inserted around an infix op application in case it is applied to further arguments, or if it's an arguments to a type constructor. Tests are updated. - - - - - b3a99828 by David Waern at 2008-07-24T10:19:43+00:00 Print parenthesis around non-atomic banged types Fixes half of haskell/haddock#44 - - - - - ab5238e0 by David Waern at 2008-07-24T22:07:49+00:00 Add a reference file for the TypeFamilies test - - - - - 1941cc11 by David Waern at 2008-07-25T17:15:53+00:00 Simplify definition of pretty and trace_ppr - - - - - e3bfa33c by David Waern at 2008-07-25T17:18:27+00:00 Warning messages Output a warning when filtering out data/type instances and associated types in instances. We don't show these in the documentation yet, and we need to let the user know. - - - - - 9b85fc89 by David Waern at 2008-07-25T17:45:40+00:00 Doc: Mention Hoogle in the Introduction - - - - - afb2dd60 by David Waern at 2008-07-25T17:49:00+00:00 Doc: update -B description - - - - - 584c0c91 by David Waern at 2008-07-25T18:11:38+00:00 Doc: describe -w flag - - - - - 77619c24 by David Waern at 2008-07-28T12:29:07+00:00 Remove TODO from cabal file - - - - - 96717d5f by David Waern at 2008-07-28T12:29:27+00:00 Support type equality predicates - - - - - c2fd2330 by David Waern at 2008-07-29T19:45:14+00:00 Move unL from H.B.Hoogle to H.GHC.Utils I like Neil's shorter unL better than unLoc from the GHC API. - - - - - c4c3bf6a by David Waern at 2008-07-29T19:47:36+00:00 Do not export ATs when not in list of subitems - - - - - bf9a7b85 by David Waern at 2008-08-03T11:42:59+00:00 Filter out ForeignExports - - - - - df59fcb0 by David Waern at 2008-08-03T14:02:51+00:00 Filter out more declarations The previous refactorings in H.I.Create introduced a few bugs. Filtering of some types of declarations that we don't handle was removed. This patch fixes this. - - - - - 2f8a958b by David Waern at 2008-08-03T15:24:07+00:00 Move reL to H.GHC.Utils so we can use it everywhere - - - - - 8ec15efd by David Waern at 2008-08-03T15:25:00+00:00 Use isVanillaLSig from GHC API instead of home brewn function - - - - - 300f93a2 by David Waern at 2008-08-03T15:25:27+00:00 Filter out separately exported ATs This is a quick and dirty hack to get rid of separately exported ATs. We haven't decided how to handle them yet. No warning message is given. - - - - - 8776d1ec by David Waern at 2008-08-03T16:21:21+00:00 Filter out more declarations and keep only vanilla type sigs in classes - - - - - ea07eada by David Waern at 2008-08-03T16:48:00+00:00 Fix layout - - - - - dd5e8199 by David Waern at 2008-08-03T16:50:52+00:00 Move some utility functions from H.I.Create to H.GHC.Utils - - - - - 4a1dbd72 by David Waern at 2008-08-03T17:39:55+00:00 Do not filter out doc declarations - - - - - 0bc8dca4 by David Waern at 2008-08-03T17:47:26+00:00 Filter out separately exported ATs (take two) - - - - - af970fe8 by David Waern at 2008-08-03T22:39:17+00:00 Update CHANGES - - - - - 5436ad24 by David Waern at 2008-08-03T22:40:20+00:00 Bump version number to 2.2.1 - - - - - d66de448 by David Waern at 2008-08-05T19:00:32+00:00 Remove version restriction on ghc-paths - - - - - 534b1364 by David Waern at 2008-08-05T19:04:35+00:00 Bump version to 2.2.2 and update CHANGES - - - - - 549188ff by David Waern at 2008-08-05T19:16:49+00:00 Fix CHANGES - - - - - 0d156bb4 by Luke Plant at 2008-08-11T15:20:59+00:00 invoking haddock clarification and help - - - - - 748295cc by David Waern at 2008-08-11T18:56:37+00:00 Doc: say that the --hoogle option is functional - - - - - 43301db4 by David Waern at 2008-08-05T19:26:08+00:00 Change ghc version dependency to >= 6.8.2 - - - - - 3e5a53b6 by David Waern at 2008-08-10T22:42:05+00:00 Make H.GHC.Utils build with GHC HEAD - - - - - 7568ace0 by David Waern at 2008-08-11T19:41:54+00:00 Import Control.OldException instead of C.Exception when using ghc >= 6.9 We should really test for base version instead, but I don't currently know which version to test for. - - - - - b71ae991 by David Waern at 2008-08-12T22:40:39+00:00 Make our .haddock file version number depend on the GHC version We need to do this, since our .haddock format can potentially change whenever GHC's version changes (even when only the patchlevel changes). - - - - - 6307ce3f by David Waern at 2008-08-12T22:49:57+00:00 Remove matching on NoteTy in AttachInstances, it has been removed - - - - - 2dbcfd5f by David Waern at 2008-08-12T23:02:02+00:00 Comment out H.GHC.loadPackages - it is unused and doesn't build with ghc >= 6.9 - - - - - c74db5c2 by David Waern at 2008-08-12T23:03:58+00:00 Hide <.> from GHC import in Hoogle only for ghc <= 6.8.3 - - - - - 69a44ebb by David Waern at 2008-08-12T23:11:12+00:00 Follow changes to parseDynamic/StaticFlags - - - - - 5881f3f0 by David Waern at 2008-08-13T21:43:58+00:00 Add __GHC_PATCHLEVEL__ symbol also when building the library - - - - - 8574dc11 by David Waern at 2008-08-13T21:44:17+00:00 Follow move of package string functions from PackageConfig to Module - - - - - c9baa77f by David Waern at 2008-08-13T21:45:29+00:00 Follow extensible exceptions changes - - - - - 9092de15 by David Waern at 2008-08-13T21:46:20+00:00 Update test following Haddock version change - - - - - ebe569a4 by David Waern at 2008-08-13T21:46:54+00:00 Follow changes to parseDynamic- parseStaticFlags in GHC - - - - - b8a5ffd3 by David Waern at 2008-08-13T21:47:36+00:00 Follow changes to Binary in GHC 6.9 - - - - - edfda1cc by David Waern at 2008-08-13T21:50:17+00:00 Change ghc version dependency to >= 6.8.2 && <= 6.9 - - - - - d59be1cf by Neil Mitchell at 2008-08-12T16:02:53+00:00 Output all items, even if they are not defined in this module - ensures map comes from Prelude, not just GHC.Base - - - - - dda93b9f by Neil Mitchell at 2008-08-12T21:37:32+00:00 Add support for type synonyms to Hoogle, was accidentally missing before (woops!) - - - - - b6ee795c by Neil Mitchell at 2008-08-13T14:03:24+00:00 Generalise Hoogle.doc and add a docWith - - - - - 415e1bb2 by Neil Mitchell at 2008-08-13T14:03:46+00:00 Make Hoogle add documentation to a package - - - - - 790a1202 by Neil Mitchell at 2008-08-18T12:52:43+00:00 Use the same method to put out signatures as class methods in the Hoogle backend - - - - - ded37eba by Neil Mitchell at 2008-08-18T12:53:04+00:00 Remove Explicit top-level forall's when pretty-printing signatures - - - - - 6468c722 by Neil Mitchell at 2008-08-20T07:59:13+00:00 Simplify the code by removing not-to-important use of <.> in the Hoogle back end - - - - - 788c3a8b by Neil Mitchell at 2008-08-21T18:20:24+00:00 In the hoogle back end, markup definition lists using <i>, not <b> - - - - - 77d4b000 by Ian Lynagh at 2008-08-14T10:49:14+00:00 Add a Makefile for GHC's build system. Still won't work yet, but we're closer - - - - - 920440d7 by Ian Lynagh at 2008-08-27T18:06:46+00:00 Add haddock.wrapper - - - - - bcda925f by Ian Lynagh at 2008-08-27T18:07:02+00:00 Add a manual Cabal flag to control the ghc-paths dependency - - - - - 04d194e2 by Ian Lynagh at 2008-08-27T20:41:27+00:00 Update extensions in Cabal file Use ScopedTypeVariables instead of PatternSignatures - - - - - 12480043 by Ian Lynagh at 2008-08-27T20:41:55+00:00 Increase the upper bound on the GHC version number - - - - - b1f809a5 by Ian Lynagh at 2008-08-27T21:32:22+00:00 Fix some warnings - - - - - aea0453d by Ian Lynagh at 2008-08-28T14:22:29+00:00 Fixes for using haddock in a GHC build tree - - - - - ad23bf86 by Ian Lynagh at 2008-08-28T21:14:27+00:00 Don't use Cabal wrappers on Windows - - - - - 35858e4c by Ian Lynagh at 2008-08-29T00:07:42+00:00 Fix in-tree haddock on Windows - - - - - c2642066 by Ian Lynagh at 2008-09-03T22:35:53+00:00 follow library changes - - - - - 2eb55d50 by Ian Lynagh at 2008-09-07T18:52:51+00:00 bindist fixes - - - - - 3daa5b59 by Ian Lynagh at 2008-09-10T16:58:18+00:00 We need to tell haddock that its datasubdir is . or it can't find package.conf - - - - - 388fd8c2 by Ian Lynagh at 2008-09-10T19:47:44+00:00 Fix haddock inplace on Windows - - - - - 70a641c1 by Ian Lynagh at 2008-09-10T22:15:44+00:00 Fix installed haddock on Windows - - - - - 83c1e997 by Neil Mitchell at 2008-09-11T10:48:55+00:00 Import GHC.Paths if not IN_GHC_TREE, seems to match the use of GHC.Paths functions much better - - - - - b452519b by Ian Lynagh at 2008-09-12T12:58:24+00:00 Add a LANGUAGE ForeignFunctionInterface pragma - - - - - afbd592c by Ian Lynagh at 2008-09-12T12:59:13+00:00 Wibble imports - - - - - 547ac4ad by Ian Lynagh at 2008-09-14T15:34:22+00:00 Add a "#!/bin/sh" to haddock.wrapper - - - - - f207a807 by Ian Lynagh at 2008-09-15T10:02:32+00:00 Use "exec" when calling haddock in the wrapper - - - - - 2ee68509 by Thomas Schilling at 2008-09-15T09:09:16+00:00 Port Haddock.Interface to new GHC API. This required one bigger change: 'readInterfaceFile' used to take an optional 'Session' argument. This was used to optionally update the name cache of an existing GHC session. This does not work with the new GHC API, because an active session requires the function to return a 'GhcMonad' action, but this is not possible if no session is provided. The solution is to use an argument of functions for reading and updating the name cache and to make the function work for any monad that embeds IO, so it's result type can adapt to the calling context. While refactoring, I tried to make the code a little more self-documenting, mostly turning comments into function names. - - - - - 3bb96431 by Thomas Schilling at 2008-09-15T09:09:37+00:00 Reflect GHC API changes. - - - - - 2e60f714 by Thomas Schilling at 2008-09-15T09:10:37+00:00 Port Haddock.GHC.Typecheck to new GHC API. - - - - - 9cfd4cff by Thomas Schilling at 2008-09-15T09:11:00+00:00 Port Haddock.GHC to new GHC API. - - - - - caffa003 by Thomas Schilling at 2008-09-15T09:11:25+00:00 Port Main to new GHC API. - - - - - 069a4608 by Ian Lynagh at 2008-09-21T11:19:00+00:00 Fix paths used on Windows frmo a GHC tree: There is no whare directory - - - - - 7ceee1f7 by Ian Lynagh at 2008-09-21T12:20:16+00:00 Fix the in-tree haddock on Windows - - - - - 0d486514 by Ian Lynagh at 2008-09-23T18:06:58+00:00 Increase the GHC upper bound from 6.11 to 6.13 - - - - - f092c414 by Neil Mitchell at 2008-09-11T14:56:07+00:00 Do not wrap __ in brackets - - - - - 036bdd13 by Ian Lynagh at 2008-09-28T01:42:35+00:00 Fix building haddock when GhcProfiled=YES - - - - - 01434a89 by David Waern at 2008-09-24T20:24:21+00:00 Add PatternSignatures LANGUAGE pragma to Main and Utils - - - - - 1671a750 by David Waern at 2008-10-02T22:57:25+00:00 For source links, get original module from declaration name instead of environment. Getting it from the environment must have been a remnant from the times when we were using unqualified names (versions 0.x). - - - - - a25dde99 by David Waern at 2008-10-02T22:59:57+00:00 Remove ifaceEnv from Interface - it's no longer used - - - - - 610993da by David Waern at 2008-10-02T23:04:58+00:00 Write a comment about source links for type instance declarations - - - - - 5a96b5d5 by Thomas Schilling at 2008-10-03T10:45:08+00:00 Follow GHC API change of parseModule. - - - - - 5a943ae5 by Ian Lynagh at 2008-10-03T15:56:58+00:00 TAG 2008-10-03 - - - - - 76cdd6ae by Thomas Schilling at 2008-10-08T12:29:50+00:00 Only load modules once when typechecking with GHC. This still doesn't fix the memory leak since the typechecked source is retained and then processed separately. To fix the leak, modules must be processed directly after typechecking. - - - - - 7074d251 by David Waern at 2008-10-09T23:53:54+00:00 Interleave typechecking with interface creation At the same time, we fix a bug where the list of interfaces were processed in the wrong order, when building the links and renaming the interfaces. - - - - - 4b9b2b2d by David Waern at 2008-10-09T23:54:49+00:00 Add some strictness annotations in Interface We add some strictness annotations to the fields of Interface, so that less GHC data is hold on to during processing. - - - - - 22035628 by David Waern at 2008-10-10T20:02:31+00:00 Remove typecheckFiles and MonadUtils import from H.GHC.Typeccheck - - - - - be637ad3 by David Waern at 2008-10-10T20:33:38+00:00 Make Haddock build with GHC 6.8.2 - - - - - 523b3404 by David Waern at 2008-10-10T21:08:09+00:00 Fix documentation for createInterfaces - - - - - e1556702 by David Waern at 2008-10-10T21:26:19+00:00 Hide H.Utils in library - - - - - a8e751c3 by David Waern at 2008-10-10T21:34:59+00:00 Add back .haddock file versioning based on GHC version It was accidentally removed in the patch for GHC 6.8.2 compatibility - - - - - 06fb3c01 by David Waern at 2008-10-10T21:47:15+00:00 Bump version number to 2.3.0 - - - - - ff087fce by David Waern at 2008-10-10T22:35:49+00:00 Add support for DocPic The support for DocPic was merged into the GHC source long ago, but the support in Haddock was forgotten. Thanks Peter Gavin for submitting this fix! - - - - - 3af85bf6 by David Waern at 2008-10-10T23:34:05+00:00 Update tests - - - - - 0966873c by Simon Marlow at 2008-10-10T14:43:04+00:00 no need for handleErrMsg now, we don't throw any ErrMsgs - - - - - f1870de3 by Clemens Fruhwirth at 2008-10-10T13:29:36+00:00 Compile with wrapper but remove it for dist-install - - - - - 7b440dc2 by David Waern at 2008-10-11T14:02:25+00:00 Remove interface from LinksInfo It was there to know the documentation home module when creating a wiki link, but we already know this since we have the DocName. - - - - - e5729e6a by David Waern at 2008-10-15T20:49:18+00:00 Wibble - - - - - b2a8e01a by David Waern at 2008-10-15T21:03:36+00:00 Use type synonyms for declarations and docs in H.I.Create - - - - - be71a15b by David Waern at 2008-10-15T21:12:17+00:00 Comment out unused type family stuff completely - - - - - 91aaf075 by David Waern at 2008-10-15T21:49:04+00:00 Wibble - - - - - 42ba4eb4 by David Waern at 2008-10-15T21:53:53+00:00 Move convenient type synonym to H.Types - - - - - db11b723 by David Waern at 2008-10-15T22:14:07+00:00 Add DeclInfo to H.Types - - - - - 193552b6 by David Waern at 2008-10-15T22:15:01+00:00 Add subordinates with docs to the declaration map The only place in the code where we want the subordinates for a declaration is right after having looked up the declaration in the map. And since we include subordinates in the map, we might as well take the opportunity to store those subordinates that belong to a particular declaration together with that declaration. We also store the documentation for each subordinate. - - - - - 31e6eebc by David Waern at 2008-10-16T17:18:47+00:00 Wibble - - - - - 0dcbd79f by David Waern at 2008-10-16T20:58:42+00:00 Fix haskell/haddock#61 We were not getting docs for re-exported class methods. This was because we were looking up the docs in a map made from the declarations in the current module being rendered. Obviously, re-exported class methods come from another module. Class methods and ATs were the only thing we were looking up using the doc map, everything else we found in the ExporItems. So now I've put subordinate docs in the ExportItem's directly, to make things a bit more consistent. To do this, I added subordinates to the the declarations in the declaration map. This was easy since we were computing subordinates anyway, to store stand-alone in the map. I added a new type synonym 'DeclInfo', which is what we call what is now stored in the map. This little refactoring removes duplicate code to retrieve subordinates and documentation from the HsGroup. - - - - - de47f20a by David Waern at 2008-10-16T22:06:35+00:00 Document function and improve its layout - - - - - e74e625a by Thomas Schilling at 2008-10-20T11:12:57+00:00 Force interface more aggressively. For running Haddock on GHC this reduces memory usage by about 50 MB on a 32 bit system. A heap profile shows total memory usage peak at about 100 MB, but actual usage is at around 300 MB even with compacting GC (+RTS -c). - - - - - b63ac9a1 by David Waern at 2008-10-20T20:25:50+00:00 Make renamer consistent Instead of explicitly making some binders Undocumented, treat all names the same way (that is, try to find a Documented name). - - - - - f6de0bb0 by Ian Lynagh at 2008-09-19T00:54:43+00:00 TAG GHC 6.10 fork - - - - - 74599cd0 by David Waern at 2008-10-20T21:13:24+00:00 Do not save hidden modules in the .haddock file We were saving interfaces of all processed modules including those hidden using {-# OPTIONS_HADDOCK hide #-} in the .haddock file. This caused broken links when generating the index for the libraries that come with GHC. This patch excludes modules with hidden documentation when writing .haddock files. It should fix the above problem. - - - - - 7b6742e9 by David Waern at 2008-10-21T19:54:52+00:00 Do not save hidden modules in the .haddock file (also for ghc >= 6.9) When writing the first patch, I forgot to do the fix in both branches of an #if macro. - - - - - b99b1951 by David Waern at 2008-10-22T20:04:18+00:00 Remove subordinate map and its usage It is not needed now that we store subordinate names in the DeclInfo map. - - - - - da97cddc by David Waern at 2008-10-22T20:11:46+00:00 Tidy up code in H.I.Create a little Remove commented out half-done type instance support, and remove DeclWithDoc synonym. - - - - - 6afa76f3 by David Waern at 2008-10-22T21:17:29+00:00 Fix warnings in H.GHC.Utils - - - - - 171ea1e8 by David Waern at 2008-10-22T21:35:04+00:00 Fix warnings in H.Utils - - - - - c8cb3b91 by David Waern at 2008-10-22T21:36:49+00:00 Wibble - - - - - 767fa06a by David Waern at 2008-10-27T19:59:04+00:00 Make named doc comments into ExportDoc instead of ExportDecl Fixes a crash when processing modules without export lists containing named docs. - - - - - e638bbc6 by David Waern at 2008-11-02T22:21:10+00:00 Add HCAR entry - - - - - 92b4ffcf by David Waern at 2008-11-02T22:44:19+00:00 Update CHANGES - - - - - 84d4da6e by David Waern at 2008-11-03T11:25:04+00:00 Add failing test for template haskell crash - - - - - 2a9cd2b1 by David Waern at 2008-11-04T21:13:44+00:00 Add tests/TH.hs - - - - - 8a59348e by David Waern at 2008-11-04T21:30:26+00:00 TAG 2.3.0 - - - - - 54f70d31 by Thomas Schilling at 2008-10-24T17:04:08+00:00 Enable framed view of the HTML documentation. This patch introduces: - A page that displays the documentation in a framed view. The left side will show a full module index. Clicking a module name will show it in the right frame. If Javascript is enabled, the left side is split again to show the modules at the top and a very short synopsis for the module currently displayed on the right. - Code to generate the mini-synopsis for each module and the mini module index ("index-frames.html"). - CSS rules for the mini-synopsis. - A very small amount of javascript to update the mini-synopsis (but only if inside a frame.) Some perhaps controversial things: - Sharing code was very difficult, so there is a small amount of code duplication. - The amount of generated pages has been doubled, since every module now also gets a mini-synopsis. The overhead should not be too much, but I haven't checked. Alternatively, the mini-synopsis could also be generated using Javascript if we properly annotate the actual synopsis. - - - - - 5d7ea5a6 by David Waern at 2008-11-04T23:20:17+00:00 Follow change to ExportDecl in frames code - - - - - 60e16308 by David Waern at 2008-11-04T23:35:26+00:00 Update CHANGES - - - - - d63fd26d by David Waern at 2008-11-04T23:37:43+00:00 Bump version number - - - - - c1660c39 by David Waern at 2008-11-04T23:44:46+00:00 Update CHANGES - - - - - 995ab384 by David Waern at 2008-11-04T23:55:21+00:00 Remove .ref files from tests/output/ - - - - - 1abbbe75 by David Waern at 2008-11-04T23:57:41+00:00 Output version info before running tests - - - - - 649b182f by David Waern at 2008-11-05T22:45:37+00:00 Add ANNOUNCE message - - - - - c36ae0bb by David Waern at 2008-11-05T23:15:35+00:00 Update ANNOUNCE - - - - - 9c4f3d40 by David Waern at 2008-11-05T23:18:30+00:00 Wibble - - - - - 5aac87ce by David Waern at 2008-11-06T21:07:48+00:00 Depend on base 4.* when using GHC >= 6.9, otherwise 3.* - - - - - b9796a74 by David Waern at 2008-11-06T21:13:40+00:00 Bump version to 2.4.1 and update CHANGES - - - - - d4b26baa by David Waern at 2008-11-06T21:26:33+00:00 Depend on base 4.0.* instead of 4.* - - - - - 2cb0903c by David Waern at 2008-11-06T21:46:53+00:00 Fix warnings in H.B.HH and H.B.HH2 - - - - - e568e89a by David Waern at 2008-11-06T21:47:12+00:00 Fix warnings in Haddock.ModuleTree - - - - - 9dc14fbd by David Waern at 2008-11-06T21:47:52+00:00 Fix warnings in Haddock.Version - - - - - 02ac197c by David Waern at 2008-11-06T21:51:31+00:00 Fix warnings in H.InterfaceFile and H.Options - - - - - 63e7439a by David Waern at 2008-11-06T21:59:45+00:00 Fix warnings in H.GHC.Typecheck - - - - - 4bca5b68 by David Waern at 2008-11-08T13:43:42+00:00 Set HscTarget to HscNothing instead of HscAsm There used to be a bug in the GHC API that prevented us from setting this value. - - - - - 07357aec by David Waern at 2008-11-09T22:27:00+00:00 Re-export NameCache and friends from Distribution.Haddock - - - - - ea554b5a by David Waern at 2008-11-09T23:14:10+00:00 Add Haddock.GHC.Utils to other-modules in library - - - - - 74aecfd7 by David Waern at 2008-11-10T01:18:57+00:00 Export DocName in the library - - - - - 241a58b3 by David Waern at 2008-11-10T01:19:18+00:00 Document the functions in H.DocName - - - - - edc2ef1b by David Waern at 2008-11-10T01:20:52+00:00 Export H.DocName in the library - - - - - 4f588d55 by David Waern at 2008-11-10T01:29:14+00:00 Make DocName an instance of NamedThing - - - - - b4647244 by David Waern at 2008-11-15T22:58:18+00:00 Reflect version bump in test suite - - - - - 4bee8ce2 by David Waern at 2008-11-15T22:58:45+00:00 Update tests For unknown reasons, test output for Bug1 and Test has changed for the better. - - - - - 1690e2f9 by David Waern at 2008-11-15T22:59:33+00:00 Store hidden modules in .haddock files We store documentation for an entity in the 'InstalledInterface' of the definition site module, and never in the same structure for a module which re-exports the entity. So when a client of the Haddock library wants to look up some documentation, he/she might need to access a hidden module. But we currently don't store hidden modules in the .haddock files. So we add the hidden modules and the Haddock options to the .haddock files. The options will be used to filter the module list to obtain the visible modules only, which is necessary for generating the contents and index for installed packages. - - - - - 8add6435 by David Waern at 2008-11-16T14:35:50+00:00 Bump major version number due to .haddock file format change - - - - - 48bfcf82 by David Waern at 2008-11-23T14:32:52+00:00 Update tests to account for version number bump - - - - - 0bbd1738 by David Waern at 2008-11-23T14:33:31+00:00 HADDOCK_DATA_DIR changed to haddock_datadir - - - - - 5088b78c by David Waern at 2008-11-23T17:13:21+00:00 FIX haskell/haddock#45: generate two anchors for each name We generate two anchor tags for each name, one where we don't escape the name and one where we URI-encode it. This is for compatibility between IE and Opera. Test output is updated. - - - - - 5ee5ca3b by Neil Mitchell at 2008-11-27T14:38:11+00:00 Drop HsDocTy annotations, they mess up pretty printing and also have a bracketing bug (#2584) - - - - - 51c014e9 by Roman Cheplyaka at 2008-11-27T22:27:36+00:00 Allow referring to a specific section within a module in a module link Fixes haskell/haddock#65 - - - - - 4094bdc5 by David Waern at 2008-11-28T21:13:33+00:00 Update tests following anchor change - - - - - f89552dd by Thomas Schilling at 2008-11-29T16:16:20+00:00 Haddock really shouldn't try to overwrite files. - - - - - 98127499 by David Waern at 2008-12-07T14:09:15+00:00 Solve conflict - - - - - 319356c5 by David Waern at 2008-10-22T21:16:55+00:00 Add -Wall -Werror to ghc-options - - - - - 3c4968c9 by David Waern at 2008-11-04T23:38:56+00:00 TAG 2.4.0 - - - - - 4b21e003 by David Waern at 2008-11-06T21:14:04+00:00 TAG 2.4.1 - - - - - 8e0cad5c by David Waern at 2008-12-07T14:12:54+00:00 Remove -Werror - - - - - 299d6deb by David Waern at 2008-12-07T14:25:18+00:00 Remove -Wall, we'll focus on warnings after 6.10.2 is out - - - - - 5f4216b6 by David Waern at 2008-12-07T20:58:05+00:00 Resolve conflict properly - - - - - 67d774e7 by Neil Mitchell at 2008-12-15T11:44:26+00:00 Make forall's in constructors explicit, i.e. data Foo = Foo {foo :: Eq a => a} - - - - - 61851792 by Neil Mitchell at 2008-12-18T15:39:39+00:00 Try and find a better package name than "main" for Hoogle, goes wrong when working on an executable rather than a library - - - - - 2fab8554 by David Waern at 2008-12-08T23:19:48+00:00 Make visible names from ExportItems Instead of a complicated calculation of visible names out of GHC's export items, we can get them straight out of the already calculated ExportItems. The ExportItems should represent exactly those items that are visible in an interface. If store all the exported sub-names in ExportDecl instead of only those with documentation, the calculation becomes very simple. So we do this change as well (should perhaps have been a separate patch). This should fix the problem with names from ghc-prim not appearing in the link environment. - - - - - 7caadd8c by Ian Lynagh at 2008-12-11T17:01:04+00:00 Wrap the GHC usage with defaultCleanupHandler This fixes a bug where haddock leaves /tmp/ghc* directories uncleaned. - - - - - 7c9fc9a5 by David Waern at 2009-01-02T21:38:27+00:00 Show re-exported names from external packages again This fixes GHC ticket 2746. In order to also link to the exported subordinate names of a declaration, we need to re-introduce the sub map in the .haddock files. - - - - - 119e4e05 by David Waern at 2009-01-06T23:34:17+00:00 Do not process boot modules We should of course not try to produce documentation for boot modules! The reason this has worked in the past is that the output of "real" modules overwrites the output of boot modules later in the process. However, this causes a subtle link environment problem. So let's get rid of this stupid behaviour. We avoid processing boot modules, but we continue to typecheck them. - - - - - c285b9d2 by David Waern at 2009-01-08T18:03:36+00:00 Export modules also when coming from external packages This seems to have regressed since a refactoring that was part of the 2.3.0 release. - - - - - 24031c17 by David Waern at 2009-01-10T15:26:26+00:00 Change version to 2.4.2 - no need to go to 2.5.0 - - - - - 864d1c3f by David Waern at 2009-01-10T15:35:20+00:00 Update tests to account for version number change - - - - - 524ba886 by David Waern at 2009-01-10T18:29:17+00:00 Add test for Template Haskell splicing - - - - - 05e6e003 by David Waern at 2009-01-10T19:35:42+00:00 Fix Trac haskell/haddock#68: Turn on compilation via C for Template Haskell packages We can't use HscNothing if we need to run code coming from modules inside the processed package during typechecking, which is the case for some packages using Template Haskell. This could be improved, to e.g. use HscInterpreted and HscNothing where possible, instead of using HscC for all modules in the package. - - - - - 2b2bafa1 by David Waern at 2009-01-10T20:22:25+00:00 Only use needsTemplateHaskell when compiling with GHC 6.10.2 or above - - - - - bedc3a93 by Ian Lynagh at 2009-01-11T14:58:41+00:00 Fix the location of INPLACE_PKG_CONF; fixes the build Spotted by Conal Elliott - - - - - 943107c8 by David Waern at 2009-01-20T19:27:39+00:00 Document H.I.Create.collectDocs better - - - - - c6252e37 by David Waern at 2009-01-20T19:29:51+00:00 Fix Trac haskell/haddock#59: TH-generated declarations disappearing This patch was contributed by Joachim Breitner (nomeata). - - - - - 3568a6af by David Waern at 2009-01-21T21:41:48+00:00 Do not indicate that a constructor argument is unboxed We only show the strictness annotation for an unboxed constructor argument. The fact that it is unboxed is an implementation detail and should not be part of the module interface. - - - - - 562a4523 by David Waern at 2009-01-22T18:53:49+00:00 Fix Trac haskell/haddock#50: do not attach docs to pragmas or other kinds of non-declarations We now filter out everything that is not a proper Haskell declaration before collecting the docs and attaching them to declarations. - - - - - 6fdf21c2 by David Waern at 2009-01-22T19:48:09+00:00 Add test for quasi quotation. No reference output yet. - - - - - dc4100fd by David Waern at 2009-01-22T19:57:47+00:00 Improve quasi-quotation test and add reference output - - - - - 908b74bb by David Waern at 2009-01-23T23:22:03+00:00 Filter out separately exported associated types in a smarter way - - - - - f6b42ecb by David Waern at 2009-01-24T16:54:39+00:00 Correct spelling mistake in error message - - - - - 24e4245d by David Waern at 2009-01-24T17:48:03+00:00 Correct comment - - - - - b5e8462f by David Waern at 2009-02-07T13:22:29+00:00 Do not show a subordinate at the top level if its parent is also exported See note in the source code for more info. - - - - - 4b09de57 by David Waern at 2009-02-07T13:53:53+00:00 Update test following change to top level subordinates - - - - - 76379896 by David Waern at 2009-02-07T13:58:04+00:00 Remove html files in the tests/output/ directory which have been accidentally added - - - - - 1a6d8b10 by Joachim Breitner at 2009-02-20T10:29:43+00:00 Typo in comment - - - - - fec367d0 by David Waern at 2009-02-24T20:21:17+00:00 Fix small bug The rule is to prefer type constructors to other things when an identifier in a doc string can refer to multiple things. This stopped working with newer GHC versions (due to a tiny change in the GHC renamer). We implement this rule in the HTML backend for now, instead of fixing it in GHC, since we will move renaming of doc strings to Haddock in the future anyway. - - - - - 9b4172eb by David Waern at 2009-02-25T20:04:38+00:00 Fix bad error handling with newer GHCs When support for GHC 6.10 was added, an error handler was installed only around the typechecking phase. This had the effect that errors thrown during dependency chasing were caught in the top-level exception handler and not printed with enough detail. With this patch we wrap the error handler around all our usage of the Ghc monad. - - - - - de2df363 by Simon Peyton Jones at 2009-02-02T16:47:42+00:00 Hide funTyConName, now exported by TypeRep - - - - - 4d40a29f by Ian Lynagh at 2009-02-12T18:57:49+00:00 Don't build the library when building in the GHC tree - - - - - 1cd0abe4 by Ian Lynagh at 2009-02-13T13:58:53+00:00 Add a ghc.mk - - - - - 3d814eeb by Ian Lynagh at 2009-02-13T18:50:28+00:00 do .depend generation for haddock with the stage1 compiler This is a bit of a hack. We mkdepend with stage1 as if .depend depends on the stage2 compiler then make goes wrong: haddock's .depend gets included, which means that make won't reload until it's built, but we can't build it without the stage2 compiler. We therefore build the stage2 compiler before its .depend file is available, and so compilation fails. - - - - - b55036a4 by Ian Lynagh at 2009-02-25T01:38:13+00:00 Give haddock a wrapper on unix in the new GHC build system - - - - - 9eabfe68 by Ian Lynagh at 2009-02-25T19:21:32+00:00 Create inplace/lib/html in the new GHC build system - - - - - 93af30c7 by Ian Lynagh at 2008-11-07T19:18:23+00:00 TAG GHC 6.10.1 release - - - - - 06e6e34a by Thomas Schilling at 2009-02-24T18:11:00+00:00 Define __GHC_PATCHLEVEL__ for recent version of GHC (stable). - - - - - 680e6ed8 by Thomas Schilling at 2009-02-24T18:12:26+00:00 'needsTemplateHaskell' is not defined in current stable GHC. - - - - - 6c5619df by David Waern at 2009-02-25T22:15:23+00:00 Hide fynTyConName only for recent GHC versions - - - - - 6b2344f1 by Ian Lynagh at 2009-02-26T00:49:56+00:00 Add the module to one of haddocks warnings - - - - - e5d11c70 by David Waern at 2009-02-27T21:37:20+00:00 Bug fix We tried to filter out subordinates that were already exported through their parent. This didn't work properly since we were in some cases looking at the grand-parent and not the parent. We now properly compute all the parent-child relations of a declaration, and use this information to get the parent of a subordinate. We also didn't consider record fields with multiple parents. This is now handled correctly. We don't currently support separately exported associated types. But when we do, they should be handled correctly by this process too. Also slightly improved the warning message that we give when filtering out subordinates. - - - - - 10a79a60 by David Waern at 2009-02-27T22:08:08+00:00 Fix error message conflict The module name is already written in the beginning of the message, as seems to be the convention in Haddock. Perhaps not so clear, but we should change it everywhere in that case. Leaving it as it is for now. - - - - - c5055c7f by David Waern at 2009-02-27T22:15:17+00:00 Shorten warning message - - - - - a72fed3a by David Waern at 2009-02-28T00:53:55+00:00 Do not show package name in warning message - - - - - a5daccb2 by Ian Lynagh at 2009-03-01T14:59:35+00:00 Install haddock in the new GHC build system - - - - - dfdb025c by Ian Lynagh at 2009-03-07T23:56:29+00:00 Relax base dependency to < 4.2, not < 4.1 - - - - - 5769c8b4 by David Waern at 2009-03-21T14:58:52+00:00 Bump .haddock file version number (due to change of format) - - - - - f1b8f67b by David Waern at 2009-03-21T14:59:26+00:00 Define __GHC_PATCHLEVEL__=1 when using ghc-6.10.1 - - - - - 23f78831 by David Waern at 2009-03-21T16:40:52+00:00 Update CHANGES - - - - - 7d2735e9 by David Waern at 2009-03-21T16:50:33+00:00 Update ANNOUNCE - - - - - 0771e00a by David Waern at 2009-03-21T16:54:40+00:00 Update ANNOUNCE, again - - - - - 81a6942a by David Waern at 2009-03-21T17:50:06+00:00 Don't be too verbose in CHANGES - - - - - 29861dcf by David Waern at 2009-03-21T18:03:31+00:00 TAG 2.4.2 - - - - - a585f285 by David Waern at 2009-03-21T19:20:29+00:00 Require Cabal >= 1.2.3 - - - - - 7c611662 by David Waern at 2009-03-21T19:21:48+00:00 TAG 2.4.2 with cabal-version >= 1.2.3 - - - - - 23b7deff by Simon Marlow at 2009-03-20T15:43:42+00:00 new GHC build system: use shell-wrappers macro - - - - - 25f8afe7 by Ian Lynagh at 2009-03-21T19:13:53+00:00 Fix (with a hack?) haddock in teh new build system - - - - - 6a29a37e by David Waern at 2009-03-24T22:10:15+00:00 Remove unnecessary LANGUAGE pragma - - - - - 954da57d by David Waern at 2009-03-24T22:21:23+00:00 Fix warnings in H.B.DevHelp - - - - - 1619f1df by David Waern at 2009-03-26T23:20:44+00:00 -Wall police in H.B.Html - - - - - b211e13b by Simon Marlow at 2009-03-24T13:00:56+00:00 install Haddock's html stuff - - - - - 78e0b107 by David Waern at 2008-12-07T19:58:53+00:00 Add verbosity flag and utils, remove "verbose" flag - - - - - 913dae06 by David Waern at 2008-12-07T20:01:05+00:00 Add some basic "verbose" mode logging in H.Interface - - - - - 1cbff3bf by David Waern at 2009-03-27T00:07:26+00:00 Fix conflicts - - - - - 22f82032 by David Waern at 2009-03-27T21:15:11+00:00 Remove H.GHC.Typecheck - - - - - 81557804 by David Waern at 2009-03-27T21:19:22+00:00 Remove docNameOrig and use getName everywhere instead - - - - - d8267213 by David Waern at 2009-03-27T21:21:46+00:00 Use docNameOcc instead of nameOccName . getName - - - - - 5d55deab by David Waern at 2009-03-27T21:33:04+00:00 Remove H.DocName and put DocName in H.Types - - - - - 8ba72611 by David Waern at 2009-03-27T22:06:26+00:00 Document DocName - - - - - 605f8ca5 by David Waern at 2009-03-27T22:45:21+00:00 -Wall police - - - - - e4da93ae by David Waern at 2009-03-27T23:12:53+00:00 -Wall police in H.B.Hoogle - - - - - bb255519 by David Waern at 2009-03-27T23:41:28+00:00 Define Foldable and Traversable instances for Located - - - - - f1195cfe by David Waern at 2009-03-27T23:51:34+00:00 Wibble - - - - - 23818d7c by David Waern at 2009-03-28T00:03:55+00:00 -Wall police in H.I.Rename - - - - - 0f050d67 by David Waern at 2009-03-28T00:15:15+00:00 -Wall police in H.I.AttachInstances - - - - - 0f3fe038 by David Waern at 2009-03-28T21:09:41+00:00 Wibble - - - - - 275d4865 by David Waern at 2009-03-28T21:27:06+00:00 Layout fix - - - - - 54ff0ef8 by David Waern at 2009-03-28T21:59:07+00:00 -Wall police in H.I.Create - - - - - 7f58b117 by David Waern at 2009-03-28T22:10:19+00:00 -Wall police in H.Interface - - - - - f0c03b44 by David Waern at 2009-03-28T22:22:59+00:00 -Wall police in Main - - - - - 29da355c by David Waern at 2009-03-28T22:23:39+00:00 Turn on -Wall -Werror - - - - - 446d3060 by David Waern at 2009-04-01T20:40:30+00:00 hlint police - - - - - 3867c9fc by David Waern at 2009-04-01T20:48:42+00:00 hlint police - - - - - bd1f1600 by David Waern at 2009-04-01T20:58:02+00:00 hlint police - - - - - e0e90866 by David Waern at 2009-04-05T12:42:53+00:00 Move H.GHC.Utils to H.GhcUtils - - - - - 9cbd426b by David Waern at 2009-04-05T12:57:21+00:00 Remove Haddock.GHC and move its (small) contents to Main - - - - - b5c2cbfd by David Waern at 2009-04-05T13:07:04+00:00 Fix whitespace and stylistic issues in Main - - - - - 3c04aa56 by porges at 2008-12-07T08:22:19+00:00 add unicode output - - - - - 607918da by David Waern at 2009-04-26T15:09:43+00:00 Resolve conflict - - - - - 4bec6b6b by Simon Marlow at 2009-05-13T10:00:31+00:00 fix markup - - - - - 436ad6f4 by Simon Marlow at 2009-03-23T11:54:45+00:00 clean up - - - - - bdcd1398 by Simon Marlow at 2009-03-24T10:36:45+00:00 new GHC build system: add $(exeext) - - - - - 9c0972f3 by Simon Marlow at 2009-03-24T11:04:31+00:00 update for new GHC build system layout - - - - - d0f3f83a by Ian Lynagh at 2009-03-29T15:31:43+00:00 GHC new build system fixes - - - - - 5a8245c2 by Ian Lynagh at 2009-04-04T20:44:23+00:00 Tweak new build system - - - - - 9c6f2d7b by Simon Marlow at 2009-05-13T10:01:27+00:00 add build instructions for GHC - - - - - 66d07c76 by Ian Lynagh at 2009-05-31T00:37:53+00:00 Quote program paths in ghc.mk - - - - - bb7de2cd by Ian Lynagh at 2009-06-03T22:57:55+00:00 Use a bang pattern on an unlifted binding - - - - - 3ad283fc by Ian Lynagh at 2009-06-13T16:17:50+00:00 Include haddock in GHC bindists - - - - - ac447ff4 by David Waern at 2009-06-24T21:07:50+00:00 Delete Haddock.Exception and move contents to Haddock.Types Only a few lines of code that mainly declares a type - why not just put it in Haddock.Types. - - - - - 4464fb9b by David Waern at 2009-06-24T22:23:23+00:00 Add Haddock module headers Add a proper Haddock module header to each module, with a more finegrained copyright. If you feel mis-accreditted, please correct any copyright notice! The maintainer field is set to haddock at projects.haskell.org. Next step is to add a brief description to each module. - - - - - 5f4c95dd by David Waern at 2009-06-24T22:39:44+00:00 Fix spelling error - - - - - 6d074cdb by David Waern at 2009-06-25T21:53:56+00:00 Document Interface and InstalledInterface better - - - - - d0cbd183 by David Waern at 2009-06-27T12:46:46+00:00 Remove misplaced whitespace in H.I.Rename - - - - - fa381c49 by David Waern at 2009-06-27T13:26:03+00:00 Fix haskell/haddock#104 - create output directory if missing - - - - - 91fb77ae by Ian Lynagh at 2009-06-25T15:59:50+00:00 TAG 2009-06-25 - - - - - 0d853f40 by Simon Peyton Jones at 2009-07-02T15:35:22+00:00 Follow extra field in ConDecl - - - - - b201735d by Ian Lynagh at 2009-07-05T16:50:35+00:00 Update Makefile for the new GHC build system - - - - - df6c0092 by Ian Lynagh at 2009-07-05T17:01:13+00:00 Resolve conflicts - - - - - 1066870a by Ian Lynagh at 2009-07-05T17:01:48+00:00 Remove the -Wwarn hack in the GHC build system - - - - - 7e856076 by Ian Lynagh at 2009-07-05T17:17:59+00:00 Fix warnings - - - - - 5d4cd958 by Ian Lynagh at 2009-07-05T19:35:40+00:00 Bump version number Cabal needs to distinguish between haddocks having a --verbose and --verbosity flag - - - - - 6ee07c99 by David Waern at 2009-07-06T20:14:57+00:00 Wibble - - - - - 2308b66f by David Waern at 2009-07-06T20:24:20+00:00 Clearer printing of versions by runtests.hs - - - - - d4b5d9ab by David Waern at 2009-07-06T21:22:42+00:00 Fix (invisible) bug introduced by unicode patch - - - - - 2caca8d8 by David Waern at 2009-07-06T21:44:10+00:00 Use HscAsm instead of HscC when using TH - - - - - 18f3b755 by David Waern at 2009-07-06T22:10:22+00:00 Update HCAR entry (by Janis) - - - - - a72ac9db by David Waern at 2009-07-06T23:01:35+00:00 Follow HsRecTy change with an #if __GLASGOW_HASKEL__ >= 611 - - - - - 549135d2 by David Waern at 2009-07-06T23:11:41+00:00 Remove unused functions from Haddock.Utils - - - - - b450134a by Isaac Dupree at 2009-07-11T14:59:00+00:00 revert to split-index for large indices - remove the search-box, because browsers have search-for-text abilities anyway. - pick 150 items in index as the arbitrary time at which to split it - notice the bug that identifiers starting with non-ASCII characters won't be listed in split-index, but don't bother to fix it yet (see ticket haskell/haddock#116, http://trac.haskell.org/haddock/ticket/116 ) - - - - - 78a5661e by Isaac Dupree at 2009-07-20T15:37:18+00:00 Implement GADT records in HTML backend - - - - - 4e163555 by Isaac Dupree at 2009-07-21T22:03:25+00:00 add test for GADT records - - - - - 79aa4d6e by David Waern at 2009-07-23T20:40:37+00:00 Update test suite following version bump - - - - - 5932c011 by David Waern at 2009-08-02T10:25:39+00:00 Fix documentation bug - - - - - a6970fca by David Waern at 2009-08-12T23:08:53+00:00 Remove support for ghc 6.8.* from .cabal file - - - - - c1695902 by Ian Lynagh at 2009-07-07T13:35:45+00:00 Fix unused import warnings - - - - - fb6df7f9 by Ian Lynagh at 2009-07-16T00:20:31+00:00 Use cProjectVersion directly rather than going through compilerInfo Fixes the build after changes in GHC - - - - - 548cdd66 by Simon Marlow at 2009-07-28T14:27:04+00:00 follow changes in GHC's ForeignType - - - - - 9395aaa0 by David Waern at 2009-08-13T22:17:33+00:00 Switch from PatternSignatures to ScopedTypeVariables in Main - - - - - eebf39bd by David Waern at 2009-08-14T17:14:28+00:00 Version .haddock files made with GHC 6.10.3/4 correclty - - - - - 58f3e735 by David Waern at 2009-08-14T17:19:37+00:00 Support GHC 6.10.* and 6.11.* only - - - - - 5f63cecc by David Waern at 2009-08-14T22:03:20+00:00 Do not version .haddock file based on GHC patchlevel version We require that the instances of Binary that we use from GHC will not change between patchlevel versions. - - - - - d519de9f by David Waern at 2009-08-14T23:50:00+00:00 Update CHANGES - - - - - 35dccf5c by David Waern at 2009-08-14T23:51:38+00:00 Update version number everywhere - - - - - 6d363fea by David Waern at 2009-08-15T09:46:49+00:00 Update ANNOUNCE - - - - - c7ee6bc2 by David Waern at 2009-08-15T09:47:13+00:00 Remove -Werror Forgot that Hackage doesn't like it. - - - - - a125c12b by David Waern at 2009-08-15T09:49:50+00:00 Require Cabal >= 1.6 - - - - - adb2f560 by Isaac Dupree at 2009-08-12T03:47:14+00:00 Cross-Package Documentation version 4 - - - - - 3d6dc04d by David Waern at 2009-08-15T23:42:57+00:00 Put all the IN_GHC_TREE stuff inside getGhcLibDir - - - - - 56624097 by David Waern at 2009-08-15T23:52:03+00:00 Add --print-ghc-libdir - - - - - f15d3ccb by David Waern at 2009-08-16T00:37:52+00:00 Read base.haddock when running tests We can now test cross-package docs. - - - - - 283f0fb9 by David Waern at 2009-08-16T00:50:59+00:00 Update test output - we now have more links - - - - - 673d1004 by David Waern at 2009-08-16T01:26:08+00:00 Read process.haddock when running tests - - - - - 0d127f82 by David Waern at 2009-08-16T01:43:04+00:00 Add a test for cross-package documentation - - - - - f94db967 by Ian Lynagh at 2009-08-16T18:42:44+00:00 Follow GHC build system changes - - - - - 5151278a by Isaac Dupree at 2009-08-16T19:58:05+00:00 make cross-package list types look nicer - - - - - c41e8228 by Isaac Dupree at 2009-08-18T01:47:47+00:00 Haddock.Convert: export more functions This lets us remove some code in Haddock.Interface.AttachInstances - - - - - 2e5fa398 by Isaac Dupree at 2009-08-18T02:11:05+00:00 switch AttachInstances to use synify code It changed an instance from showing ((,) a b) to (a, b) because my synify code is more sophisticated; I hope the latter is a good thing rather than a bad thing aesthetically, here. But this definitely reduces code duplication! - - - - - b8b07123 by Isaac Dupree at 2009-08-18T02:23:31+00:00 Find instances using GHC, which is more complete. In particular, it works cross-package. An intermediate patch also moved the instance-finding into createInterface, but that move turned out not to be necessary, so if we want to do that, it'd go in a separate patch. (Is that possible? Or will we need GHC to have loaded all the modules first, before we can go searching for the instances (e.g. if the modules are recursive or something)?) - - - - - 6959b451 by Isaac Dupree at 2009-08-17T00:37:18+00:00 fix preprocessor conditional sense - - - - - 942823af by Isaac Dupree at 2009-08-16T22:46:48+00:00 remove ghc 6.8 conditionals from Haddock.Interface - - - - - 4b3ad888 by Isaac Dupree at 2009-08-18T20:24:38+00:00 Fix GHC 6.11 build in Haddock.Convert - - - - - 0a89c5ab by Isaac Dupree at 2009-08-23T00:08:58+00:00 hacks to make it compile without fnArgDocsn - - - - - 7b3bed43 by Isaac Dupree at 2009-08-23T03:01:28+00:00 less big-Map-based proper extraction of constructor subdocs - - - - - b21c279a by Isaac Dupree at 2009-08-23T03:02:06+00:00 Html: remove unnecessary+troublesome GHC. qualifications - - - - - 96c97115 by Isaac Dupree at 2009-08-23T03:08:03+00:00 Move doc parsing/lexing into Haddock for ghc>=6.11 - - - - - e1cec02d by Isaac Dupree at 2009-08-23T05:08:14+00:00 get rid of unused DocMap parameter in Html - - - - - 66960c59 by Isaac Dupree at 2009-08-23T05:54:20+00:00 fix horrible named-docs-disappearing bug :-) - - - - - a9d7eff3 by Isaac Dupree at 2009-08-23T06:26:36+00:00 re-implement function-argument docs ..on top of the lexParseRn work. This patch doesn't change the InstalledInterface format, and thus, it does not work cross-package, but that will be easy to add subsequently. - - - - - 8bf6852c by Isaac Dupree at 2009-08-23T07:26:05+00:00 cross-package fnArgDocs. WARNING: changes .haddock binary format While breaking the format, I took the opportunity to unrename the DocMap that's saved to disk, because there's really no reason that we want to know what *another* package's favorite place to link a Name to was. (Is that true? Or might we want to know, someday?) Also, I added instance Binary Map in InterfaceFile. It makes the code a little simpler without changing anything of substance. Also it lets us add another Map hidden inside another Map (fnArgsDocs in instDocMap) without having really-convoluted serialization code. Instances are neat! I don't understand why this change to InterfaceFile seemed to subtly break binary compatibility all by itself, but no matter, I'll just roll it into the greater format-changing patch. Done! - - - - - 30115a64 by Isaac Dupree at 2009-08-23T18:22:47+00:00 Improve behavior for unfindable .haddock - - - - - aa364bda by Isaac Dupree at 2009-08-23T18:28:16+00:00 add comment for FnArgsDoc type - - - - - 49b23a99 by Isaac Dupree at 2009-08-23T21:52:48+00:00 bugfix: restore fnArgDocs for type-synonyms - - - - - f65f9467 by Isaac Dupree at 2009-08-23T22:06:55+00:00 Backends.Hoogle: eliminate warnings - - - - - a292d216 by Isaac Dupree at 2009-08-23T22:10:24+00:00 Haddock.Convert: eliminate warnings - - - - - 5546cd20 by Isaac Dupree at 2009-08-23T22:12:31+00:00 Haddock.Interface.Rename: eliminate warnings - - - - - 0a9798b6 by Isaac Dupree at 2009-08-23T22:18:47+00:00 Main.hs: remove ghc<6.9 conditionals - - - - - e8f9867f by Isaac Dupree at 2009-08-23T22:27:46+00:00 Main.hs: eliminate warnings (except for OldException) - - - - - 61c64247 by Isaac Dupree at 2009-08-23T22:41:01+00:00 move get*LibDir code in Main.hs, to +consistent code, -duplication - - - - - 948f1e69 by Isaac Dupree at 2009-08-23T23:14:26+00:00 Main.hs: OldException->Exception: which eliminates warnings - - - - - 3d5d5e03 by Isaac Dupree at 2009-08-23T23:20:11+00:00 GhcUtils: ghc >= 6.10 - - - - - 2771d657 by Isaac Dupree at 2009-08-23T23:21:55+00:00 InterfaceFile: ghc >= 6.10 - - - - - d9f2b9d1 by Isaac Dupree at 2009-08-23T23:22:58+00:00 Types: ghc >= 6.10 - - - - - ca39210e by Isaac Dupree at 2009-08-23T23:23:26+00:00 ModuleTree: ghc >= 6.10 - - - - - 883c4e59 by Isaac Dupree at 2009-08-23T23:24:04+00:00 Backends.DevHelp: ghc >= 6.10 - - - - - 04667df5 by Isaac Dupree at 2009-08-23T23:24:37+00:00 Backends.Html: ghc >= 6.10 - - - - - a9f7f25f by Isaac Dupree at 2009-08-23T23:25:24+00:00 Utils: ghc >= 6.10 - - - - - b7105022 by Isaac Dupree at 2009-08-23T23:37:47+00:00 eliminate haskell98 dependency, following GHC's example It turns out I/we already had, and it was only a matter of deleting it from the cabal file. - - - - - 292e0911 by Isaac Dupree at 2009-08-24T01:22:44+00:00 refactor out subordinatesWithNoDocs dep of inferenced-decls fix - - - - - c2ed46a2 by Isaac Dupree at 2009-08-24T01:24:03+00:00 Eradicate wrong runtime warning for type-inferenced exported-functions see the long comment in the patch for why I did it this way :-) - - - - - 4ac0b57c by David Waern at 2009-09-04T22:56:20+00:00 Clean up tyThingToHsSynSig a little Factor out noLoc and use the case construct. Also rename the function to tyThingToLHsDecl, since it doesn't just create type signatures. - - - - - 28ab9201 by David Waern at 2009-09-04T22:58:50+00:00 Wibble - - - - - 0d9fe6d0 by David Waern at 2009-09-06T18:39:30+00:00 Add more copyright owners to H.I.AttachInstances - - - - - 122441b1 by David Waern at 2009-09-06T18:44:12+00:00 Style police - - - - - 1fa79463 by David Waern at 2009-09-06T18:57:45+00:00 Move toHsInstHead to Haddock.Convert and call it synifyInstHead - - - - - 0d42a8aa by David Waern at 2009-09-06T21:11:38+00:00 Use colordiff to display test results if available - - - - - ea9d8e03 by Simon Marlow at 2009-08-24T08:46:14+00:00 Follow changes in GHC's interface file format Word32 instead of Int for FastString and Name offsets - - - - - 537e051e by Simon Marlow at 2009-07-29T14:16:53+00:00 define unpackPackageId (it was removed from GHC) - - - - - 50c63aa7 by David Waern at 2009-09-09T23:18:03+00:00 Remove commented-out code - - - - - 511631fe by David Waern at 2009-09-09T23:19:05+00:00 Correct copyright in H.I.ParseModuleHeader - - - - - 898ec768 by David Waern at 2009-09-11T11:22:29+00:00 Use Map.fromList/toList intead of fromAscList/toAscList when serializing Maps This fixes the missing docs problem. The Eq and Ord instances for Name uses the unique number in Name. This number is created at deserialization time by GHC's magic Binary instance for Name, and it is random. Thus, fromAscList can't be used at deserialization time, even though toAscList was used at serialization time. - - - - - 37bec0d5 by Simon Peyton Jones at 2009-09-11T08:28:04+00:00 Track change in HsType - - - - - eb3a97c3 by Ian Lynagh at 2009-09-11T16:07:09+00:00 Allow building with base 4.2 - - - - - bb4205ed by Ian Lynagh at 2009-09-22T13:50:02+00:00 Loosen the GHC dependency - - - - - 5c75deb2 by Ian Lynagh at 2009-09-22T14:08:39+00:00 Fix building with GHC >= 6.12 - - - - - fb131481 by David Waern at 2009-09-11T11:24:48+00:00 Update runtests.hs to work with GHC 6.11 - - - - - ac3a419d by David Waern at 2009-09-11T11:25:14+00:00 Update CrossPackageDocs test - - - - - ec65c3c6 by David Waern at 2009-09-11T11:25:40+00:00 Add reference output for CrossPackageDocs - - - - - 520c2758 by Ian Lynagh at 2009-10-25T17:26:40+00:00 Fix installation in the GHC build system - - - - - 28b3d7df by Ian Lynagh at 2009-11-05T15:57:27+00:00 GHC build system: Make *nix installation work in paths containing spaces - - - - - 5c9bb541 by David Waern at 2009-11-14T11:56:39+00:00 Track change in HsType for the right compiler version - - - - - 905097ce by David Waern at 2009-11-14T12:10:47+00:00 hlint police - - - - - 04920630 by Ian Lynagh at 2009-11-20T13:46:30+00:00 Use defaultObjectTarget rather than HscAsm This fixes haddock when we don't have a native code generator - - - - - 966eb079 by David Waern at 2009-11-15T12:32:21+00:00 Remove commented-out code - - - - - 37f00fc4 by David Waern at 2009-11-22T13:58:48+00:00 Make runtests.hs strip links before diffing Generates easier to read diffs when tests fail. The content of the links is not important anyway since it is not taken into account by the tests. - - - - - 3a9bb8ef by David Waern at 2009-11-22T14:05:06+00:00 Follow findProgramOnPath signature change in runtests.hs - - - - - b26b9e5a by David Waern at 2009-11-22T14:08:40+00:00 Follow removal of GHC.MVar from base in CrossPackageDocs - - - - - f4d90ae4 by David Waern at 2009-11-22T14:48:47+00:00 Make copy.hs strip link contents before copying No more updating of reference files when URLs in links changes. - - - - - 4c9c420d by David Waern at 2009-11-22T15:26:41+00:00 Update test reference output * More links (Int, Float etc) * Stripped link contents - - - - - a62b80e3 by David Waern at 2009-11-23T23:19:39+00:00 Update CrossPackageDocs reference output - Remove GHC.MVar import (removed from base) - Strip link contents - - - - - 43491394 by David Waern at 2009-11-23T23:20:00+00:00 Update test reference files with comments on instances - - - - - 0d370a0b by David Waern at 2009-11-23T23:25:16+00:00 Bump version number - - - - - 2293113e by David Waern at 2009-11-24T20:55:49+00:00 Comments on instances Implementing this was a little trickier than I thought, since we need to match up instances from the renamed syntax with instances represented by InstEnv.Instance. This is due to the current design of Haddock, which matches comments with declarations from the renamed syntax, while getting the list of instances of a class/family directly using the GHC API. - Works for class instances only (Haddock has no support for type family instances yet) - The comments are rendered to the right of the instance head in the HTML output - No change to the .haddock file format - Works for normal user-written instances only. No comments are added on derived or TH-generated instances - - - - - bf586f29 by David Waern at 2009-11-27T22:05:15+00:00 Whitespace police - - - - - b8f03afa by David Waern at 2009-11-27T22:11:46+00:00 Remove bad whitespace and commented-out pieces - - - - - 90b8ee90 by David Waern at 2009-11-27T22:15:04+00:00 Whitespace police - - - - - b5ede900 by David Waern at 2009-11-27T22:15:50+00:00 Whitespace police - - - - - e3fddbfe by David Waern at 2009-11-28T13:37:59+00:00 Remove Name from DocInstance It's not used. - - - - - 9502786c by David Waern at 2009-11-28T13:56:54+00:00 Require at least GHC 6.12 While regression testing Haddock, I found a bug that happens with GHC 6.10.3, but not with GHC 6.12-rc2 (haven't tried 6.10.4). I don't have time to track it down. I think we should just always require the latest major GHC version. The time spent on making Haddock work with older versions is too high compared to the time spent on bugfixing, refactoring and features. - - - - - 8fa688d8 by David Waern at 2009-11-28T15:05:03+00:00 Remove cruft due to compatibility with older GHCs - - - - - 46fbbe9d by David Waern at 2009-11-28T15:07:50+00:00 Add a documentation header to Haddock.Convert - - - - - c3d2cc4a by David Waern at 2009-11-28T15:10:14+00:00 Remove unused H.Utils.FastMutInt2 - - - - - 490aba80 by David Waern at 2009-11-28T15:36:36+00:00 Rename Distribution.Haddock into Documentation.Haddock - - - - - 33ee2397 by David Waern at 2009-11-28T15:36:47+00:00 Fix error message - - - - - a5a3b950 by David Waern at 2009-11-28T16:58:39+00:00 Add a test flag that brings in QuickCheck - - - - - fa049e13 by David Waern at 2009-11-28T19:32:18+00:00 Say that we want quickcheck 2 - - - - - f32b0d9b by David Waern at 2009-11-28T19:32:40+00:00 Add an Arbitrary instance for HsDoc - - - - - da9a8bd7 by David Waern at 2009-11-28T20:15:30+00:00 Rename HsDoc back into Doc - - - - - edb60101 by David Waern at 2009-11-28T22:16:16+00:00 Move H.Interface.Parse/Lex to H.Parse/Lex These are not just used to build Interfaces. - - - - - 0656a9b8 by David Waern at 2009-11-28T23:12:14+00:00 Update version number in test suite - - - - - 5e8c6f4a by David Waern at 2009-12-21T14:12:41+00:00 Improve doc of DocName - - - - - 7868e551 by Ian Lynagh at 2009-09-22T10:43:03+00:00 TAG GHC 6.12-branch created - - - - - 0452a3ea by Ian Lynagh at 2009-12-15T12:46:07+00:00 TAG GHC 6.12.1 release - - - - - 65e9be62 by David Waern at 2009-12-21T16:58:58+00:00 Update CHANGES - - - - - 145cee32 by David Waern at 2009-12-21T16:59:09+00:00 TAG 2.6.0 - - - - - 3c552008 by David Waern at 2009-12-22T17:11:14+00:00 Update ANNOUNCE - - - - - 931f9db4 by David Waern at 2010-01-22T19:57:17+00:00 Convert haddock.vim to use unix newlines - - - - - 4e56588f by David Waern at 2010-01-22T22:11:17+00:00 Remove unnecessary (and inexplicable) uses of nub - - - - - 744bb4d1 by David Waern at 2010-01-22T22:12:14+00:00 Follow move of parser and lexer - - - - - e34bab14 by David Waern at 2010-01-22T22:49:13+00:00 Use findProgramLocation instead of findProgramOnPath in runtests.hs - - - - - 8d39891b by Isaac Dupree at 2010-01-14T18:53:18+00:00 fix html arg-doc off-by-one and silliness - - - - - 9401f2e9 by David Waern at 2010-01-22T22:57:03+00:00 Create a test for function argument docs - - - - - 507a82d7 by David Waern at 2010-01-22T23:24:47+00:00 Put parenthesis around type signature arguments of function type - - - - - 8a305c28 by David Waern at 2010-01-23T17:26:59+00:00 Add reference file for the FunArgs test - - - - - 1309d5e1 by David Waern at 2010-01-24T16:05:08+00:00 Improve FunArg test and update Test.html.ref - - - - - 2990f055 by Yitzchak Gale at 2010-02-14T16:03:46+00:00 Do not generate illegal character in HTML ID attribute. - - - - - c5bcab7a by David Waern at 2010-02-22T22:10:30+00:00 Fix Haddock markup error in comment - - - - - c6416a73 by David Waern at 2010-02-24T22:55:08+00:00 Large additions to the Haddock API Also improved and added more doc comments. - - - - - 57d289d7 by David Waern at 2010-02-24T22:58:02+00:00 Remove unused ifaceLocals - - - - - 80528d93 by David Waern at 2010-02-25T21:05:09+00:00 Add HaddockModInfo to the API - - - - - 82806848 by David Waern at 2010-02-25T21:05:27+00:00 Wibble - - - - - 744cad4c by David Waern at 2010-02-25T23:30:59+00:00 Make it possible to run a single test - - - - - 6a806e4c by David Waern at 2010-03-14T14:19:39+00:00 Bump version number - - - - - a5a8e4a7 by David Waern at 2010-03-14T14:36:35+00:00 Update ANNOUNCE - - - - - 6f05435e by Simon Hengel at 2010-03-15T20:52:42+00:00 Add missing dependencies for 'library' in haddock.cabal - - - - - faefe2bd by David Waern at 2010-03-15T22:29:37+00:00 Solve conflicts - - - - - 9808ad52 by David Waern at 2010-03-15T22:51:21+00:00 Bump version number - - - - - eb0bf60b by David Waern at 2010-03-15T22:52:32+00:00 Update CHANGES - - - - - f95cd891 by David Waern at 2010-03-15T23:01:06+00:00 Add Paths_haddock to other-modules of library - - - - - 65997b0a by David Waern at 2010-03-15T23:14:59+00:00 Update CHANGES - - - - - 7e251731 by David Waern at 2010-03-15T23:15:30+00:00 Bump version number - - - - - c9cd0ddc by David Waern at 2010-03-16T00:28:34+00:00 Fix warning - - - - - 1cac2d93 by Simon Peyton Jones at 2010-01-04T15:22:16+00:00 Fix imports for new location of splitKindFunTys - - - - - 474f26f6 by Simon Peyton Jones at 2010-02-10T14:36:06+00:00 Update Haddock for quasiquotes - - - - - 0dcc06c0 by Simon Peyton Jones at 2010-02-10T10:59:45+00:00 Track changes in HsTyVarBndr - - - - - 2d84733a by Simon Peyton Jones at 2010-02-10T14:52:44+00:00 Track HsSyn chnages - - - - - 9e3adb8b by Ian Lynagh at 2010-02-20T17:09:42+00:00 Resolve conflicts - - - - - a3e72ff8 by Simon Peyton Jones at 2010-03-04T13:05:16+00:00 Track change in HsUtils; and use a nicer function not an internal one - - - - - 27994854 by David Waern at 2010-03-18T22:22:27+00:00 Fix build with GHC 6.12.1 - - - - - 11f6e488 by David Waern at 2010-03-18T22:24:09+00:00 Bump version in test reference files - - - - - 0ef2f11b by David Waern at 2010-03-20T00:56:30+00:00 Fix library part of cabal file when in ghc tree - - - - - 3f6146ff by Mark Lentczner at 2010-03-20T22:30:11+00:00 First, experimental XHTML rendering switch to using the xhtml package copied Html.hs to Xhtml.hs and split into sub-modules under Haddock/Backends/Xhtml and detabify moved footer into div, got ready for iface change headers converted to semantic markup contents in semantic markup summary as semantic markup description in semantic markup, info block in header fixed factored out rendering so during debug it can be readable (see renderToString) - - - - - b8ab329b by Mark Lentczner at 2010-03-20T22:54:01+00:00 apply changes to Html.hs to Xhtml/*.hs incorporate changes that were made between the time Html.hs was copied and split into Xhtml.hs and Xhtml/*.hs includes patchs after "Wibble" (!) through "Fix build with GHC 6.12.1" - - - - - 73df2433 by Ian Lynagh at 2010-03-20T21:56:37+00:00 Follow LazyUniqFM->UniqFM in GHC - - - - - db4f602b by David Waern at 2010-03-29T22:00:01+00:00 Fix build with GHC 6.12 - - - - - d8dca088 by Simon Hengel at 2010-04-02T16:39:55+00:00 Add missing dependencies to cabal file - - - - - e2adc437 by Simon Hengel at 2010-04-02T14:08:40+00:00 Add markup support for interactive examples - - - - - e882ac05 by Simon Hengel at 2010-04-02T14:11:53+00:00 Add tests for interactive examples - - - - - 5a07a6d3 by David Waern at 2010-04-07T17:05:20+00:00 Propagate source positions from Lex.x to Parse.y - - - - - 6493b46f by David Waern at 2010-04-07T21:48:57+00:00 Let runtests.hs die when haddock has not been built - - - - - 5e34423e by David Waern at 2010-04-07T22:01:13+00:00 Make runtests.hs slightly more readable - - - - - 321d59b3 by David Waern at 2010-04-07T22:13:27+00:00 Fix haskell/haddock#75 Add colons to the $ident character set. - - - - - 37b08b8d by David Waern at 2010-04-08T00:32:52+00:00 Fix haskell/haddock#118 Avoid being too greedy when lexing URL markup (<..>), in order to allow multiple URLs on the same line. Do the same thing with <<..>> and #..#. - - - - - df8feac9 by David Waern at 2010-04-08T00:57:33+00:00 Make it easier to add new package deps to test suite This is a hack - we should use Cabal to get the package details instead. - - - - - 1ca6f84b by David Waern at 2010-04-08T01:03:06+00:00 Add ghc-prim to test suite deps - - - - - 27371e3a by Simon Hengel at 2010-04-08T19:26:34+00:00 Let parsing fails on paragraphs that are immediately followed by an example This is more consistent with the way we treat code blocks. - - - - - 83096e4a by David Waern at 2010-04-08T21:20:00+00:00 Improve function name - - - - - 439983ce by David Waern at 2010-04-10T10:46:14+00:00 Fix haskell/haddock#112 No link was generated for 'Addr#' in a doc comment. The reason was simply that the identifier didn't parse. We were using parseIdentifier from the GHC API, with a parser state built from 'defaultDynFlags'. If we pass the dynflags of the module instead, the right options are turned on on while parsing the identifer (in this case -XMagicHash), and the parse succeeds. - - - - - 5c0d35d7 by David Waern at 2010-04-10T10:54:06+00:00 Rename startGhc into withGhc - - - - - dca081fa by Simon Hengel at 2010-04-12T19:09:16+00:00 Add documentation for interactive examples - - - - - c7f26bfa by David Waern at 2010-04-13T00:51:51+00:00 Slight fix to the documentation of examples - - - - - 06eb7c4c by David Waern at 2010-04-13T00:57:05+00:00 Rename Interactive Examples into Examples (and simplify explanation) - - - - - 264830cb by David Waern at 2010-05-10T20:07:27+00:00 Update CHANGES with info about 2.6.1 - - - - - 8e5d4514 by Simon Hengel at 2010-04-18T18:16:54+00:00 Add unit tests for parser - - - - - 68297f40 by David Waern at 2010-05-10T21:53:37+00:00 Improve testsuite README - - - - - f04eb6e4 by David Waern at 2010-05-11T19:14:31+00:00 Re-organise the testsuite structure - - - - - a360f710 by David Waern at 2010-05-11T19:18:03+00:00 Shorten function name - - - - - 1d5dd359 by David Waern at 2010-05-11T21:40:02+00:00 Update runtests.hs following testsuite re-organisation - - - - - ffebe217 by David Waern at 2010-05-11T21:40:10+00:00 Update runtests.hs to use base-4.2.0.1 - - - - - 635de402 by David Waern at 2010-05-11T21:41:11+00:00 Update runparsetests.hs following testsuite reorganisation - - - - - 72137910 by Ian Lynagh at 2010-05-06T20:43:06+00:00 Fix build - - - - - 1a80b76e by Ian Lynagh at 2010-05-06T22:25:29+00:00 Remove redundant import - - - - - 1031a80c by Simon Peyton Jones at 2010-05-07T13:21:09+00:00 Minor wibbles to HsBang stuff - - - - - dd8e7fe5 by Ian Lynagh at 2010-05-08T15:22:00+00:00 GHC build system: Follow "rm" variable changes - - - - - 7f5e6748 by David Waern at 2010-05-13T11:53:02+00:00 Fix build with GHC 6.12.2 - - - - - 7953d4d8 by David Waern at 2010-05-13T18:45:01+00:00 Fixes to comments only - - - - - 8ae8eb64 by David Waern at 2010-05-13T18:57:26+00:00 ModuleMap -> IfaceMap - - - - - 1c3eadc6 by David Waern at 2010-05-13T19:03:13+00:00 Fix whitespace style issues - - - - - e96783c0 by David Waern at 2010-05-13T19:08:53+00:00 Fix comment - - - - - c998a78b by David Waern at 2010-05-13T19:39:00+00:00 Position the module header the same way everywhere Silly, but nice with some consistency :-) - - - - - b48a714e by David Waern at 2010-05-13T19:41:32+00:00 Position of module header, this time in the HTML backends - - - - - f9bfb12e by David Waern at 2010-05-13T19:43:05+00:00 Two newlines between declarations in Main - - - - - 071d44c7 by David Waern at 2010-05-13T19:44:21+00:00 Newlines in Convert - - - - - 036346db by David Waern at 2010-05-13T19:46:47+00:00 Fix a few stylistic issues in H.InterfaceFile - - - - - f0b8379e by David Waern at 2010-05-13T19:47:53+00:00 Add newlines to H.ModuleTree - - - - - 27409f8e by David Waern at 2010-05-13T19:51:10+00:00 Fix stylistic issues in H.Utils - - - - - 24774a11 by David Waern at 2010-05-13T20:00:43+00:00 Structure H.Types better - - - - - 7b6f5e40 by David Waern at 2010-05-13T20:01:04+00:00 Remove bad Arbitrary instance - - - - - fac9f1f6 by David Waern at 2010-05-13T20:05:50+00:00 Get rid of H.Utils.pathJoin and use System.FilePath.joinPath instead - - - - - fe6d00c4 by David Waern at 2010-05-13T20:51:55+00:00 Export a couple of more types from the API - - - - - b2e33a5f by David Waern at 2010-05-13T21:27:51+00:00 Improve doc comment for Interface - - - - - c585f2ce by David Waern at 2010-05-13T21:30:14+00:00 Improve documentation of Haddock.Interface - - - - - e6791db2 by David Waern at 2010-05-13T22:07:35+00:00 Remove meaningless comments - - - - - 7801b390 by David Waern at 2010-05-14T17:53:33+00:00 Remove unused modules - - - - - f813e937 by David Waern at 2010-05-14T17:55:17+00:00 Re-direct compilation output to a temporary directory Also add a flag --no-tmp-comp-dir that can be used to get the old behaviour of writing compilation files to GHC's output directory (default "."). - - - - - e56737ec by David Waern at 2010-05-14T18:06:11+00:00 Wibble - - - - - e40b0447 by David Waern at 2010-05-14T19:01:52+00:00 Move flag evaluation code from Main to Haddock.Options Determining the value of "singular" flags (by e.g. taking the last occurrence of the flag) and other flag evaluation should done in Haddock.Options which is the module that is supposed to define the command line interface. This makes Main a bit easier on the eyes as well. - - - - - 27091f57 by David Waern at 2010-05-14T19:05:10+00:00 Wibble - - - - - c658cf61 by David Waern at 2010-05-14T19:06:49+00:00 Re-order things in Haddock.Options a bit - - - - - 8cfdd342 by David Waern at 2010-05-14T19:20:29+00:00 De-tabify Haddock.Options and fix other whitespace issues - - - - - 0df16b62 by David Waern at 2010-05-14T19:25:07+00:00 Improve comments - - - - - 80b38e2b by David Waern at 2010-05-14T19:26:42+00:00 Whitespace police - - - - - fe580255 by David Waern at 2010-05-14T19:31:23+00:00 Wibbles to comments - - - - - a2b43fad by David Waern at 2010-05-14T20:24:32+00:00 Move some more flag functions to Haddock.Options - - - - - 3f895547 by David Waern at 2010-05-14T20:37:12+00:00 Make renderStep a top-level function in Main - - - - - 5cdca11d by David Waern at 2010-05-14T20:39:27+00:00 Spelling in comment - - - - - ad98d14c by David Waern at 2010-05-14T20:40:26+00:00 Comment fixes - - - - - 0bb9218f by David Waern at 2010-05-14T20:49:01+00:00 Whitespace police - - - - - 0f0a533f by David Waern at 2010-05-15T16:42:29+00:00 Improve description of --dump-interface - - - - - 5b2833ac by David Waern at 2010-05-15T17:16:53+00:00 Document --no-tmp-comp-dir - - - - - 8160b170 by David Waern at 2010-05-15T17:18:59+00:00 Wibble - - - - - 570dbe33 by David Waern at 2010-05-18T21:15:38+00:00 HLint police - - - - - 204e425f by David Waern at 2010-05-18T21:16:30+00:00 HLint police - - - - - 6db657ac by David Waern at 2010-05-18T21:16:37+00:00 Wibble - - - - - b942ccd7 by Simon Marlow at 2010-06-02T08:27:30+00:00 Interrupted disappeared in GHC 6.13 (GHC ticket haskell/haddock#4100) - - - - - 3b94a819 by Simon Marlow at 2010-06-02T08:45:08+00:00 Allow base-4.3 - - - - - c5a1fb7c by Simon Marlow at 2010-06-02T09:03:04+00:00 Fix compilation with GHC 6.13 - - - - - 6181296c by David Waern at 2010-06-08T21:09:05+00:00 Display name of prologue file when parsing it fails - - - - - 7cbc6f60 by Ian Lynagh at 2010-06-13T16:20:25+00:00 Remove redundant imports - - - - - 980c804b by Simon Marlow at 2010-06-22T08:41:50+00:00 isLocalAndTypeInferenced: fix for local module names overlapping package modules - - - - - d74d4a12 by Simon Marlow at 2010-06-23T12:03:27+00:00 Unresolved identifiers in Doc get replaced with DocMonospaced rather than plain strings - - - - - d8546783 by Simon Marlow at 2010-06-30T12:45:17+00:00 LaTeX backend (new options: --latex, --latex-style=<style>) - - - - - 437afa9e by David Waern at 2010-07-01T12:02:44+00:00 Fix a few stylistic whitespace issues in LaTeX backend - - - - - 85bc1fae by David Waern at 2010-07-01T15:42:45+00:00 Make runtest.hs work with GHC 6.12.3 (we should really stop hard coding this) - - - - - 7d2eb86f by David Waern at 2010-07-01T15:43:33+00:00 Update test following Simon's patch to render unresolved names in monospaced font - - - - - 08fcbcd2 by David Waern at 2010-07-01T16:12:18+00:00 Warning police - - - - - d04a8d7a by David Waern at 2010-07-04T14:53:39+00:00 Fix a bug in attachInstances We didn't look for instance docs in all the interfaces of the package. This had the effect of instance docs not always showing up under a declaration. I took the opportunity to clean up the code in H.I.AttachInstances a bit as well. More cleanup is needed, however. - - - - - d10344eb by Simon Hengel at 2010-07-10T09:19:04+00:00 Add missing dependencies to cabal file - - - - - 24090531 by Mark Lentczner at 2010-03-21T04:51:16+00:00 add exports to Xhtml modules - - - - - 84f9a333 by Mark Lentczner at 2010-04-03T19:14:22+00:00 clean up Doc formatting code - add CSS for lists - renderToString now uses showHtml since prettyHtml messes up <pre> sections - - - - - bebccf52 by Mark Lentczner at 2010-04-04T04:51:08+00:00 tweak list css - - - - - 0c2aeb5e by Mark Lentczner at 2010-04-04T06:24:14+00:00 all decls now generate Html not HtmlTable - ppDecl return Html, and so now do all of the functions it calls - added some internal tables to some decls, which is wrong, and will have to be fixed - decl "Box" functions became "Elem" functions to make clear they aren't in a table anymore (see Layout.hs) - docBox went away, as only used in one place (and its days are numbered) - cleaned up logic in a number of places, removed dead code - added maybeDocToHtml which simplified a number of places in the code - - - - - dbf73e6e by Mark Lentczner at 2010-04-05T05:02:43+00:00 clean up processExport and place a div around each decl - - - - - e25b7e9f by Mark Lentczner at 2010-04-10T21:23:21+00:00 data decls are now a sequence of paragraphs, not a table - - - - - 89ee0294 by Mark Lentczner at 2010-04-10T21:29:16+00:00 removed commented out code that can't be maintained - - - - - d466f536 by Mark Lentczner at 2010-04-12T04:56:27+00:00 removed declWithDoc and cleaned up data decls in summary - - - - - ed755832 by Mark Lentczner at 2010-04-12T05:07:53+00:00 merge in markupExample changes - - - - - c36f51fd by Mark Lentczner at 2010-04-25T04:56:37+00:00 made record fields be an unordList, not a table - - - - - ed3a28d6 by Mark Lentczner at 2010-04-25T05:23:28+00:00 fixed surround of instance and constructor tables - - - - - 0e35bbc4 by Mark Lentczner at 2010-04-25T05:36:59+00:00 fix class member boxes in summary - - - - - 5041749b by Mark Lentczner at 2010-04-25T05:38:35+00:00 remove unused bodyBox - - - - - e91724db by Mark Lentczner at 2010-04-25T06:26:10+00:00 fixed javascript quoting/escpaing issue - - - - - f4abbb73 by Mark Lentczner at 2010-05-03T23:04:31+00:00 adjust css for current markup - - - - - e75fec4c by Mark Lentczner at 2010-05-04T06:14:34+00:00 added assoicated types and methods back into class decls - - - - - 84169323 by Mark Lentczner at 2010-05-24T13:13:42+00:00 merge in changes from the big-whitespace cleanup - - - - - 3c1c872e by Mark Lentczner at 2010-06-11T21:03:58+00:00 adjust synopsis and bottom bar spacing - - - - - 3c1f9ef7 by Mark Lentczner at 2010-06-11T21:14:44+00:00 fix missing space in "module" lines in synoposis - - - - - 9a137e6d by Mark Lentczner at 2010-06-11T21:34:08+00:00 changed tt elements to code elements - - - - - 50f71ef1 by Mark Lentczner at 2010-06-11T23:27:46+00:00 factored out ppInstances - - - - - 3b9a9de5 by Mark Lentczner at 2010-06-17T17:36:01+00:00 push single constructors (newtype) onto line with decl - - - - - e0f8f2ec by Mark Lentczner at 2010-06-17T22:20:56+00:00 remove <++> connector - - - - - 56c075dd by Mark Lentczner at 2010-07-13T05:26:21+00:00 change to new page structure - - - - - 04be6ca7 by Mark Lentczner at 2010-07-14T04:21:55+00:00 constructors and args as dl lists, built in Layout.hs - - - - - 65aeafc2 by Mark Lentczner at 2010-07-14T05:38:32+00:00 better interface to subDecls - - - - - 72032189 by Mark Lentczner at 2010-07-14T07:04:10+00:00 made subDecl tables looks just so - - - - - b782eca2 by Mark Lentczner at 2010-07-14T16:00:54+00:00 convert args to SubDecl format - - - - - cc75e98f by Mark Lentczner at 2010-07-14T16:28:53+00:00 convert instances to SubDecl - - - - - 34e2aa5a by Mark Lentczner at 2010-07-14T21:07:32+00:00 removing old table cruft from Layout.hs - - - - - d5810d95 by Mark Lentczner at 2010-07-14T21:54:58+00:00 methods and associated types in new layout scheme - - - - - 65ef9579 by Mark Lentczner at 2010-07-14T23:43:42+00:00 clean up synopsis lists - - - - - e523318f by Mark Lentczner at 2010-07-15T05:02:26+00:00 clean up of anchors - - - - - 1215dfc5 by Mark Lentczner at 2010-07-15T23:53:01+00:00 added two new themes and rough css switcher - - - - - 7f0fd36f by Mark Lentczner at 2010-07-16T04:57:38+00:00 fixed package catpion, added style menu - - - - - 0dd4999c by Mark Lentczner at 2010-07-16T20:12:39+00:00 new output for mini_ pages - - - - - 64b2810b by Mark Lentczner at 2010-07-16T20:58:41+00:00 reformat index-frames - - - - - 3173f555 by Mark Lentczner at 2010-07-16T22:41:53+00:00 convert index to new markup - - - - - b0a4b7c9 by Mark Lentczner at 2010-07-17T04:07:22+00:00 convert index.html to new markup, adjust module markup - - - - - 8261ae1e by Mark Lentczner at 2010-07-17T05:07:29+00:00 classing styling of ancillary pages - - - - - 2a4fb025 by Mark Lentczner at 2010-07-17T05:11:45+00:00 clean up Layout.hs: no more vanillaTable - - - - - 87eec685 by Mark Lentczner at 2010-07-17T05:35:16+00:00 clean up Util.hs - - - - - d304e9b0 by Mark Lentczner at 2010-07-17T05:38:50+00:00 qualify import of XHtml as XHtml - - - - - 7dc05807 by Mark Lentczner at 2010-07-17T06:17:53+00:00 factored out head element generation - - - - - 9cdaec9e by Mark Lentczner at 2010-07-17T06:44:54+00:00 refactored out main page body generation - - - - - 8a51019e by Mark Lentczner at 2010-07-17T06:48:20+00:00 moved footer into only place that used it - - - - - efa479da by Mark Lentczner at 2010-07-17T18:48:30+00:00 styling auxillary pages for tibbe and snappy themes - - - - - 81de5509 by Mark Lentczner at 2010-07-18T04:41:38+00:00 fixed alphabet on index page, and styling of it and packages in module lists - - - - - 20718c1a by Mark Lentczner at 2010-07-18T05:34:29+00:00 cleaned up div functions in Layout.hs - - - - - 60d50453 by Mark Lentczner at 2010-07-18T05:48:39+00:00 added content div to main pages - - - - - ed16561c by Mark Lentczner at 2010-07-18T06:12:22+00:00 add .doc class to documentation blocks - - - - - f5c781b0 by Mark Lentczner at 2010-07-19T05:20:53+00:00 refactoring of anchor ID and fragment handling - - - - - a69a93bf by Mark Lentczner at 2010-07-19T05:35:55+00:00 remove an explicit bold tag - replace with .def class - - - - - d76c7225 by Mark Lentczner at 2010-07-19T06:56:15+00:00 rename Haddock.Backends.Xhtml.Util to Utils - - - - - 5a58c0da by David Waern at 2010-07-21T13:30:54+00:00 Remove trailing whitespace in Haddock.Backends.Xhtml - - - - - 0652aa17 by David Waern at 2010-07-21T13:33:21+00:00 Align a few comments - - - - - 785776c3 by David Waern at 2010-07-21T13:39:04+00:00 Remove trailing whitespace in H.B.X.Decl - - - - - 71a30710 by David Waern at 2010-07-21T13:44:27+00:00 Remove more trailing whitespace - - - - - 38750394 by David Waern at 2010-07-21T13:50:43+00:00 Style police - - - - - 3023d940 by David Waern at 2010-07-21T14:01:22+00:00 Style police in H.B.X.Decl - - - - - df16e9e6 by David Waern at 2010-07-21T14:14:45+00:00 Style police in H.B.X.DocMarkup - - - - - 6020e321 by David Waern at 2010-07-21T14:17:32+00:00 More style police - - - - - 86ad8bf5 by David Waern at 2010-07-21T14:21:02+00:00 Style police in H.B.Xhtml - - - - - aea27d03 by David Waern at 2010-07-21T14:42:03+00:00 Fix warnings in LaTeX backend - - - - - 2aff34a9 by David Waern at 2010-07-21T14:50:46+00:00 Style police in LaTeX backend (mainly more newlines) - - - - - e517162d by David Waern at 2010-07-21T15:05:47+00:00 Doc sections in Main - - - - - b971aa0c by David Waern at 2010-07-21T15:06:17+00:00 Trailing whitespace in Documentation.Haddock - - - - - f11628fb by David Waern at 2010-07-21T15:07:06+00:00 Trailing whitespace in Haddock.Convert - - - - - cbaf284c by David Waern at 2010-07-21T15:08:11+00:00 Style police in Haddock.GhcUtils - - - - - 71feb77b by David Waern at 2010-07-21T15:09:06+00:00 Style police in Haddock.InterfaceFile - - - - - 0a9c80e6 by David Waern at 2010-07-21T15:11:33+00:00 Whitespace police - - - - - 6168376c by David Waern at 2010-07-21T15:16:35+00:00 Style police in Haddock.Utils - - - - - 9fe4dd90 by David Waern at 2010-07-21T15:19:31+00:00 Add -fwarn-tabs - - - - - a000d752 by Mark Lentczner at 2010-07-20T17:25:52+00:00 move CSS Theme functions into Themes.hs - - - - - b52b440f by Mark Lentczner at 2010-07-20T17:29:35+00:00 add Thomas Schilling's theme - - - - - e43fa7e8 by Mark Lentczner at 2010-07-21T04:49:34+00:00 correct icon used with Snappy theme - - - - - ba5092d3 by Mark Lentczner at 2010-07-21T04:56:47+00:00 apply Tibbe's updates to his theme - - - - - 7804eef6 by Mark Lentczner at 2010-07-21T05:15:49+00:00 space between "Style" and the downward triangle - - - - - 7131d4c6 by Mark Lentczner at 2010-07-21T17:43:35+00:00 merge with David's source cleanups - - - - - ee65f1cb by David Waern at 2010-07-22T16:50:46+00:00 Fix a bug where we allowed --hoogle, --latex, etc without input files - - - - - e413ff7a by David Waern at 2010-07-22T17:21:58+00:00 Improve function name - - - - - a0fd14f3 by Simon Marlow at 2010-06-30T15:34:32+00:00 fix warnings - - - - - 31f73d2a by David Waern at 2010-07-22T19:29:41+00:00 Solve conflicts - - - - - d563b4a5 by Simon Marlow at 2010-06-30T15:34:37+00:00 fix warning - - - - - 412b6469 by David Waern at 2010-07-22T19:31:28+00:00 Solve conflict - - - - - 35174b94 by Ian Lynagh at 2010-07-06T17:27:16+00:00 Follow mkPState argument order change - - - - - b5c3585c by Simon Marlow at 2010-07-14T08:49:21+00:00 common up code for instance rendering - - - - - d8009560 by Simon Marlow at 2010-07-14T12:37:11+00:00 fix warnings - - - - - a6d88695 by David Waern at 2010-07-24T15:33:33+00:00 Fix build with ghc < 6.13 - - - - - 94cf9de1 by David Waern at 2010-07-24T15:34:37+00:00 Remove conflict left-over - - - - - 313b15c0 by Mark Lentczner at 2010-07-21T22:09:04+00:00 reorganization of nhaddock.css with tibbe - - - - - 9defed80 by Mark Lentczner at 2010-07-21T22:42:14+00:00 further cleanup of nhaddock.css, float TOC, support aux. pages - - - - - 6d944c1b by Mark Lentczner at 2010-07-22T06:22:23+00:00 remove old HTML backend - - - - - b3e8cba5 by Mark Lentczner at 2010-07-22T06:43:32+00:00 remove --html-help support - it was old, out-of-date, and mostly missing - - - - - d2654a08 by Mark Lentczner at 2010-07-22T21:45:34+00:00 tweaks to nhaddock.css - - - - - f73b285c by Mark Lentczner at 2010-07-23T06:19:35+00:00 command like processing for theme selection The bulk of the change is threadnig the selected theme set through functions in Xhtml.hs so that the selected themes can be used when generating the page output. There isn't much going on in most of these changes, just passing it along. The real work is all done in Themes.hs. - - - - - 8bddc90d by Mark Lentczner at 2010-07-23T06:58:31+00:00 drop --themes support, add named theme support decided that --themes was silly - no one would do that, just use multiple --theme arguments made --theme a synonym for --css and -c made those arguments, if no file is found, look up the argument as the name of a built in theme all of this let's haddock be invoked with "--theme=classic" for example. - - - - - 20cafd4f by Mark Lentczner at 2010-07-23T17:44:29+00:00 rename --default-themes to --built-in-themes - - - - - 0fe41307 by Mark Lentczner at 2010-07-23T18:33:02+00:00 tweaks to theme for info table, headings, and tables - - - - - cba4fee0 by Mark Lentczner at 2010-07-23T19:13:59+00:00 tweaks for dl layout, though still not used - - - - - 463fa294 by Mark Lentczner at 2010-07-23T21:07:19+00:00 tweak look of mini pages, keywords, and preblocks - - - - - 5472fc02 by Mark Lentczner at 2010-07-24T05:36:15+00:00 slide out Synopsis drawer - - - - - 9d5d5de5 by Mark Lentczner at 2010-07-24T06:02:42+00:00 extend package header and footer to edges of page - - - - - a47c91a2 by Mark Lentczner at 2010-07-24T06:28:44+00:00 fields are def lists, tweak css for style menu, mini pages, arguments - - - - - ca20f23b by Mark Lentczner at 2010-07-24T16:55:22+00:00 excisting last vestiges of the --xhtml flag - - - - - 71fb012e by Mark Lentczner at 2010-07-25T18:47:49+00:00 change how collapsing sections are done make whole .caption be the target improve javascript for class toggling have plus/minus images come from .css, not img tags - - - - - c168c8d3 by Mark Lentczner at 2010-07-26T00:32:05+00:00 reorganize files in the html lib data dir - - - - - 93324301 by Mark Lentczner at 2010-07-26T01:27:42+00:00 cleaned up Themes.hs - - - - - ad3b5dd4 by Mark Lentczner at 2010-07-26T02:39:15+00:00 make module list use new collapsers - - - - - 1df9bfc6 by Mark Lentczner at 2010-07-27T19:09:25+00:00 remove Tibbe theme - - - - - 8b9b01b3 by Mark Lentczner at 2010-07-27T20:04:03+00:00 move themes into html dir with .theme and .std-theme extensions - - - - - a7beb965 by Mark Lentczner at 2010-07-27T21:06:34+00:00 give a class to empty dd elements so they can be hidden - - - - - a258c117 by Mark Lentczner at 2010-07-27T21:23:58+00:00 remove custom version of copyFile in Xhtml.hs - - - - - b70dba6e by Mark Lentczner at 2010-07-27T22:12:45+00:00 apply margin changes to pre and headings as per group decision, and small cleanups - - - - - e6f722a2 by Mark Lentczner at 2010-07-28T00:03:12+00:00 make info block and package bar links be floatable by placing them first in the dom tree - - - - - c8278867 by Mark Lentczner at 2010-07-28T19:01:18+00:00 styling source links on declarations - - - - - 88fdc399 by Mark Lentczner at 2010-07-29T01:12:46+00:00 styling tweaks don't generate an empty li for absent style menu in links area update css for Classic and Snappy to handle: dl lists links in package header and in declarations floating of links and info block in package and module headers - - - - - 8a75b213 by Ian Lynagh at 2010-07-30T20:21:46+00:00 Fix build in GHC tree - - - - - ce8e18b3 by Simon Hengel at 2010-08-03T18:37:26+00:00 Adapt paths to data files in cabal file - - - - - 9701a455 by Simon Hengel at 2010-08-07T13:20:27+00:00 Add missing dependency to cabal file - - - - - 01b838d1 by Mark Lentczner at 2010-07-30T20:19:40+00:00 improved synopsis drawer: on click, not hover - - - - - 7b6f3e59 by Mark Lentczner at 2010-07-30T23:38:55+00:00 put the synopsis back in the other themes - - - - - 7b2904c9 by Mark Lentczner at 2010-08-11T11:11:26+00:00 close arrows on expanded synopsis drawer - - - - - ea19e177 by Mark Lentczner at 2010-08-12T21:16:45+00:00 width and font changes removed the max width restrictions on the page as a whole and the synopsis made the main font size smaller (nominally 14pt) and then tweaked most font sizes (relative) to be more consistent - - - - - 5ced00c0 by Mark Lentczner at 2010-08-13T15:09:55+00:00 implemented YUI's CSS font approach - - - - - 2799c548 by Mark Lentczner at 2010-08-13T15:11:59+00:00 adjusted margin to 2em, 1 wasn't enough - - - - - 58f06893 by Mark Lentczner at 2010-08-13T15:48:44+00:00 removed underlining on hover for named anchors headings in interface lost thier a element, no need, just put id on heading css for a elements now only applies to those with href attribute - - - - - 7aced4c4 by Mark Lentczner at 2010-08-13T15:50:22+00:00 more space between elements - - - - - 5a3c1cce by Mark Lentczner at 2010-08-13T16:43:43+00:00 adjusted font sizes of auxilary pages per new scheme - - - - - 487539ef by Mark Lentczner at 2010-08-13T21:43:41+00:00 add Frames button and clean up frames.html - - - - - c1a140b6 by Mark Lentczner at 2010-08-13T22:17:48+00:00 move frames button to js - - - - - b0bdb68e by Mark Lentczner at 2010-08-14T03:44:46+00:00 build style menu in javascript moved to javascript, so as to not polute the content with the style menu removed menu building code in Themes.hs removed onclick in Utils.hs changed text of button in header from "Source code" to "Source" more consistent with links in rest of page - - - - - 43ab7120 by Mark Lentczner at 2010-08-16T15:15:37+00:00 font size and margin tweaks - - - - - c0b68652 by Mark Lentczner at 2010-08-17T18:19:52+00:00 clean up collapser logics javascript code for collapasble sections cleaned up rewrote class utilities in javascript to be more robust refactored utilities for generating collapsable sections made toc be same color as synopsis module list has needed clear attribute in CSS - - - - - 5d573427 by Mark Lentczner at 2010-08-17T23:06:02+00:00 don't collapse entries in module list when clicking on links - - - - - 8c307c4a by Mark Lentczner at 2010-08-17T23:21:43+00:00 add missing data file to .cabal - - - - - 414bcfcf by Mark Lentczner at 2010-08-17T23:28:47+00:00 remove synopsis when in frames - - - - - ba0fa98a by Mark Lentczner at 2010-08-18T16:16:11+00:00 layout tweeks - mini page font size, toc color, etc. - - - - - 63c1bed1 by Mark Lentczner at 2010-08-18T19:50:02+00:00 margin fiddling - - - - - c311c094 by Mark Lentczner at 2010-08-20T01:37:55+00:00 better synopsis handling logic - no flashing - - - - - f1fe5fa8 by Mark Lentczner at 2010-08-20T01:41:06+00:00 fix small layout issues mini frames should have same size top heading give info block dts some padding so they don't collide in some browsers - - - - - 0de84d77 by Mark Lentczner at 2010-08-20T02:13:09+00:00 made style changing and cookies storage robust - - - - - 1ef064f9 by Thomas Schilling at 2010-08-04T13:12:22+00:00 Make synopsis frame behave properly in Firefox. In Firefox, pressing the back button first reverted the synopsis frame, and only clicking the back button a second time would update the main frame. - - - - - dd1c9a94 by Mark Lentczner at 2010-08-21T01:46:19+00:00 remove Snappy theme - - - - - 2353a90d by Mark Lentczner at 2010-08-25T05:16:19+00:00 fix occasional v.scroll bars on pre blocks (I think) - - - - - 459b8bf1 by Simon Hengel at 2010-08-08T10:12:45+00:00 Add createInterfaces' (a more high-level alternative to createInterfaces) to Haddock API - - - - - b1b68675 by David Waern at 2010-08-26T20:31:58+00:00 Follow recent API additions with some refactorings Simon Hegel's patch prompted me to do some refactorings in Main, Haddock.Documentation and Haddock.Interface. - - - - - 264d4d67 by David Waern at 2010-08-26T21:40:59+00:00 Get rid of GhcModule and related cruft We can get everything we need directly from TypecheckedModule. - - - - - 0feacec2 by Mark Lentczner at 2010-08-26T23:44:13+00:00 fixed CSS for ordered lists and def lists in doc blocks - - - - - 2997e0c2 by Mark Lentczner at 2010-08-26T23:45:03+00:00 support both kinds of enumerated lists in doc markup The documentation for Haddock says enumerated lists can use either of (1) first item 2. second item The second form wasn't actually supported - - - - - 5d4ddeec by Mark Lentczner at 2010-08-27T21:29:48+00:00 fix broken header link margins - - - - - 614456ba by Mark Lentczner at 2010-08-27T22:16:19+00:00 fix table of contents CSS - - - - - 03f329a2 by David Waern at 2010-08-28T16:36:09+00:00 Update tests following switch to the Xhtml backend - - - - - ca689fa2 by Mark Lentczner at 2010-08-28T18:25:16+00:00 fix def lists - - - - - 18e1d3d2 by Mark Lentczner at 2010-08-28T18:26:18+00:00 push footer to bottom of window - - - - - b0ab8d82 by David Waern at 2010-08-28T22:04:32+00:00 Whitespace police - - - - - 2d217977 by David Waern at 2010-08-29T12:44:45+00:00 Remove Snappy data files - - - - - 01e27d5f by David Waern at 2010-08-29T13:03:28+00:00 Add source entity path to --read-interface You can now use this flag like this: --read-interface=<html path>,<source entity path>,<.haddock file> By "source entity path" I mean the same thing that is specified with the --source-entity flag. The purpose of this is to be able to specify the source entity path per package, to allow source links to work in the presence of cross-package documentation. When given two arguments or less the --read-interface flag behaves as before. - - - - - 20bf4aaa by David Waern at 2010-08-29T13:11:03+00:00 Naming wibbles - - - - - ad22463f by Mark Lentczner at 2010-08-29T15:14:54+00:00 make portability block be a table - solves layout issues - - - - - 97bd1ae6 by Mark Lentczner at 2010-08-29T15:17:42+00:00 update golden test for Test due to portability box change - - - - - d37e139e by Mark Lentczner at 2010-08-29T17:07:17+00:00 move TOC and Info blocks down 0.5em to improve layout issue w/Test.hs - - - - - acf52501 by David Waern at 2010-08-29T17:32:36+00:00 Allow building with ghc < 6.16 - - - - - 1cb34ed8 by Ian Lynagh at 2010-07-24T23:18:49+00:00 Flatten the dynflags before parsing - - - - - b36845b4 by Ian Lynagh at 2010-07-24T23:26:49+00:00 Follow flattenLanguageFlags -> flattenExtensionFlags rename - - - - - 7f7fcc7e by David Waern at 2010-08-29T17:46:23+00:00 Use flattenExtensionFlags with ghc >= 6.13 only - - - - - 13cf9411 by Ian Lynagh at 2010-08-01T18:09:54+00:00 Make the main haddock script versioned, and make plain "haddock" a symlink - - - - - 495cbff2 by Ian Lynagh at 2010-08-18T18:57:24+00:00 Fix installation in the GHC build system Data-files are now in subdirectories, so we need to handle that - - - - - 88ebab0a by Ian Lynagh at 2010-08-18T19:43:53+00:00 GHC build system: Add all the data files to BINDIST_EXTRAS - - - - - 65837172 by David Waern at 2010-08-29T20:12:34+00:00 Update Test - - - - - 094bbaa2 by David Waern at 2010-08-29T20:55:14+00:00 Revert update to Test - - - - - a881cfb3 by David Waern at 2010-08-31T18:24:15+00:00 Bump version number - - - - - 1fc8a3eb by David Waern at 2010-08-31T22:32:27+00:00 Update ANNOUNCE - - - - - ee1df9d0 by David Waern at 2010-08-31T22:33:11+00:00 Update CHANGES - - - - - 394cc854 by David Waern at 2010-08-31T22:33:23+00:00 Update interface file versioning to work with ghc 6.14/15 - - - - - 7d03b79b by David Waern at 2010-08-31T22:36:00+00:00 Update test output following version change - - - - - a48d82d1 by Mark Lentczner at 2010-09-01T04:29:35+00:00 sort options in doc to match --help output removed --html-help option, as it is no longer supported - - - - - 06561aeb by Mark Lentczner at 2010-09-01T05:29:32+00:00 update options documentation rewrote doc for --html added doc for --theme and --built-in-themes added --use-contents and --gen-contents - - - - - 57dea832 by Mark Lentczner at 2010-09-01T05:31:27+00:00 slight wording change about Frames mode - - - - - fa1f6da3 by David Waern at 2010-09-01T10:57:44+00:00 Update doc configure script to find docbook stylesheets on arch linux - - - - - addff770 by David Waern at 2010-09-01T11:02:29+00:00 Wibble - - - - - 8399006d by David Waern at 2010-09-01T11:19:21+00:00 Replace ghci> with >>> in example syntax - - - - - 35074cf8 by David Waern at 2010-09-01T19:03:27+00:00 Improve docs for --no-tmp-comp-dir - - - - - 0f8f8cfd by David Waern at 2010-09-02T11:22:27+00:00 Add a list of contributors to the user guide Break out everyone thanked in the `Acknowledgements` chapter into a separate contributor list and add everyone from `darcs show authors`. We consider everyone who is thanked to be a contributor as a conservative estimation :-) I have added some more contributors that I know about, who were not in the darcs history, but others may be missing. So please add anyone that you think is missing from the list. - - - - - 42ccf099 by David Waern at 2010-09-02T11:29:22+00:00 Update copyright years in license - - - - - 0d560479 by David Waern at 2010-09-02T11:38:52+00:00 Update release instructions - - - - - 72ab7796 by David Waern at 2010-09-02T19:27:08+00:00 Add a note to ANNOUNCE - - - - - bf9d9c5d by David Waern at 2010-09-02T19:27:48+00:00 H.Utils needs FFI on Win+MinGW - - - - - 048ae44a by Mark Lentczner at 2010-09-04T23:19:47+00:00 make TOC group header identifiers validate - - - - - 8c6faf36 by Simon Michael at 2010-09-22T07:12:34+00:00 add hints for cleaner darcs show authors output - - - - - 9909bd17 by Simon Michael at 2010-09-22T17:58:06+00:00 print haddock coverage info on stdout when generating docs A module's haddockable items are its exports and the module itself. The output is lightly formatted so you can align the :'s and sort for readability. - - - - - 6da72171 by David Waern at 2010-10-03T21:31:24+00:00 Style wibble - - - - - 2f8d8e4d by Tobias Brandt at 2010-08-27T07:01:21+00:00 adding the option to fully qualify identifiers - - - - - 833be6c6 by Tobias Brandt at 2010-08-27T15:50:28+00:00 adding support for local and relative name qualification - - - - - df15c4e9 by Tobias Brandt at 2010-08-27T15:56:37+00:00 corrected qualification help message - - - - - 449e9ce1 by David Waern at 2010-10-16T17:34:30+00:00 Solve conflicts - - - - - 3469bda5 by David Waern at 2010-10-16T18:42:40+00:00 Use "qual" as an abbreviation for qualification instead of "quali" for consistency - - - - - 97c2d728 by David Waern at 2010-10-16T18:47:07+00:00 Style police - - - - - ce14fbea by David Waern at 2010-10-16T21:15:25+00:00 Style police - - - - - fdf29e9d by David Waern at 2010-10-17T00:30:44+00:00 Add a pointer to the style guide - - - - - 8e6b44e8 by rrnewton at 2010-10-24T03:19:28+00:00 Change to index pages: include an 'All' option even when subdividing A-Z. - - - - - 755b131c by David Waern at 2010-11-14T19:39:36+00:00 Bump version - - - - - d0345a04 by David Waern at 2010-11-14T19:41:59+00:00 TAG 2.8.1 - - - - - f6221508 by Simon Peyton Jones at 2010-09-13T09:53:00+00:00 Adapt to minor changes in internal GHC functions - - - - - 1290713d by Ian Lynagh at 2010-09-15T10:37:18+00:00 Remove duplicate Outputable instance for Data.Map.Map - - - - - 87f69eef by Ian Lynagh at 2010-09-21T15:01:10+00:00 Bump GHC dep upper bound - - - - - af36e087 by Ian Lynagh at 2010-09-21T15:12:02+00:00 Fix up __GLASGOW_HASKELL__ tests - - - - - ad67716c by Ian Lynagh at 2010-09-21T20:31:35+00:00 Don't build haddock is HADDOCK_DOCS is NO - - - - - 63b3f1f5 by Ian Lynagh at 2010-09-21T21:39:51+00:00 Fixes for when HADDOCK_DOCS=NO - - - - - e92bfa42 by Ian Lynagh at 2010-09-29T21:15:38+00:00 Fix URL creation on Windows: Use / not \ in URLs. Fixes haskell/haddock#4353 - - - - - 66c55e05 by Ian Lynagh at 2010-09-30T17:03:34+00:00 Tidy up haddock symlink installation In particular, it now doesn't get created if we aren't installing haddock. - - - - - 549b5556 by Ian Lynagh at 2010-10-23T21:17:14+00:00 Follow extension-flattening change in GHC - - - - - d7c2f72b by David Waern at 2010-11-14T20:17:55+00:00 Bump version to 2.8.2 - - - - - 6989a3a9 by David Waern at 2010-11-14T20:26:01+00:00 Solve conflict - - - - - 055c6910 by Ian Lynagh at 2010-09-22T15:36:20+00:00 Bump GHC dep - - - - - c96c0763 by Simon Marlow at 2010-10-27T11:09:44+00:00 follow changes in the GHC API - - - - - 45907129 by David Waern at 2010-11-07T14:00:58+00:00 Update the HCAR entry - - - - - 61940b95 by David Waern at 2010-11-07T14:07:34+00:00 Make the HCAR entry smaller - - - - - aa590b7d by David Waern at 2010-11-14T21:30:59+00:00 Update HCAR entry with November 2010 version - - - - - 587f9847 by David Waern at 2010-11-14T23:48:17+00:00 Require ghc >= 7.0 - - - - - ff5c647c by David Waern at 2010-11-14T23:49:09+00:00 TAG 2.8.2 - - - - - 937fcb4f by David Waern at 2010-11-14T23:49:45+00:00 Solve conflict - - - - - 8e5d0c1a by David Waern at 2010-11-15T21:09:50+00:00 Remove code for ghc < 7 - - - - - 3d47b70a by David Waern at 2010-11-15T21:11:06+00:00 Fix bad merge - - - - - 7f4a0d8a by David Waern at 2010-11-15T21:13:57+00:00 Remove more ghc < 7 code - - - - - 9ee34b50 by David Waern at 2010-11-15T21:31:25+00:00 Match all AsyncExceptions in exception handler - - - - - 42849c70 by David Waern at 2010-11-15T21:35:31+00:00 Just say "internal error" instead of "internal Haddock or GHC error" - - - - - c88c809b by David Waern at 2010-11-15T21:44:19+00:00 Remove docNameOcc under the motto "don't name compositions" - - - - - b798fc7c by David Waern at 2010-11-15T23:27:13+00:00 Wibble - - - - - 2228197e by David Waern at 2010-11-15T23:28:24+00:00 Rename the HCAR entry file - - - - - 8a3f9090 by David Waern at 2010-11-16T00:05:29+00:00 Remove Haskell 2010 extensions from .cabal file - - - - - c7a0c597 by David Waern at 2010-11-16T00:10:28+00:00 Style wibbles - - - - - cde707a5 by David Waern at 2010-11-16T00:12:00+00:00 Remove LANGUAGE ForeignFunctionInterface pragmas - - - - - 1dbda8ed by David Waern at 2010-11-16T00:17:21+00:00 Make a little more use of DoAndIfThenElse - - - - - 4c45ff6e by David Waern at 2010-11-16T00:59:41+00:00 hlint police - - - - - d2feaf09 by David Waern at 2010-11-16T01:14:15+00:00 hlint police - - - - - 99876e97 by David Waern at 2010-11-20T19:06:00+00:00 Haddock documentation updates - - - - - 65ce6987 by David Waern at 2010-11-20T19:42:51+00:00 Follow the style guide closer in Haddock.Types and improve docs - - - - - 28ca304a by tob.brandt at 2010-11-20T17:04:40+00:00 add full qualification for undocumented names - - - - - d61341e3 by David Waern at 2010-11-20T20:04:15+00:00 Re-structure qualification code a little - - - - - 0057e4d6 by David Waern at 2010-11-20T20:07:55+00:00 Re-order functions - - - - - d7279afd by David Waern at 2010-11-21T03:39:54+00:00 Add BangPatterns to alex and happy source files - - - - - 629fe60e by tob.brandt at 2010-11-23T23:35:11+00:00 documentation for qualification - - - - - 37031cee by David Waern at 2010-11-23T21:06:44+00:00 Update CHANGES - don't mention 2.8.2, we won't release it - - - - - f2489e19 by David Waern at 2010-12-01T21:57:11+00:00 Update deps of runtests.hs to work with ghc 7.0.1 - - - - - d3657e9a by David Waern at 2010-12-01T22:04:57+00:00 Make tests compile with ghc 7.0.1 - - - - - a2f09d9b by David Waern at 2010-12-01T22:06:59+00:00 Update tests following version bump - - - - - 50883ebb by David Waern at 2010-12-06T14:09:18+00:00 Update tests following recent changes - - - - - fc2fadeb by David Waern at 2010-12-06T14:17:29+00:00 Add a flag --pretty-html for rendering indented html with newlines - - - - - 30832ef2 by David Waern at 2010-12-06T14:17:35+00:00 Use --pretty-html when running the test suite. Makes it easier to compare output - - - - - a0b81b31 by David Waern at 2010-12-06T14:18:27+00:00 Wibble - - - - - 3aaa23fe by David Waern at 2010-12-06T14:19:29+00:00 Haddockify ppHtml comments - - - - - 24bb24f0 by David Waern at 2010-12-06T14:23:15+00:00 Remove --debug. It was't used, and --verbosity should take its place - - - - - 6bc076e5 by David Waern at 2010-12-06T14:25:37+00:00 Rename golden-tests into html-tests. "golden tests" sounds strange - - - - - 53301e55 by David Waern at 2010-12-06T14:26:26+00:00 QUALI -> QUAL in the description --qual for consistency - - - - - 98b6affb by David Waern at 2010-12-06T21:54:02+00:00 Bump version - - - - - 371bf1b3 by David Waern at 2010-12-06T22:08:55+00:00 Update tests following version bump - - - - - 25be762d by David Waern at 2010-12-06T22:21:03+00:00 Update CHANGES - - - - - 7c7dac71 by David Waern at 2010-12-06T22:33:43+00:00 Update ANNOUNCE - - - - - 30d7a5f2 by Simon Peyton Jones at 2010-11-15T08:38:38+00:00 Alex generates BangPatterns, so make Lex.x accept them (It'd be better for Alex to generate this pragma.) - - - - - 605e8018 by Simon Marlow at 2010-11-17T11:37:24+00:00 Add {-# LANGUAGE BangPatterns #-} to mollify GHC - - - - - a46607ba by David Waern at 2010-12-07T14:08:10+00:00 Solve conflicts - - - - - b28cda66 by David Waern at 2010-12-09T20:41:35+00:00 Docs: Mention that \ is a special character in markup - - - - - a435bfdd by Ian Lynagh at 2010-11-17T14:01:19+00:00 TAG GHC 7.0.1 release - - - - - 5a15a05a by David Waern at 2010-12-11T17:51:19+00:00 Fix indentation problem - - - - - 4232289a by Lennart Kolmodin at 2010-12-17T18:32:03+00:00 Revise haddock.cabal given that we now require ghc-7 default-language should be Haskell2010, slight new semantics for extensions. Rewrite into clearer dependencies of base and Cabal. - - - - - a36302dc by David Waern at 2010-12-19T17:12:37+00:00 Update CHANGES - - - - - 7c8b85b3 by David Waern at 2010-12-19T17:14:24+00:00 Bump version - - - - - cff22813 by Ian Lynagh at 2011-01-05T18:24:27+00:00 Write hoogle output in utf8; fixes GHC build on Windows - - - - - c7e762ea by David Waern at 2011-01-22T00:00:35+00:00 Put title outside doc div when HTML:fying title+prologue Avoids indenting the title, and makes more sense since the title is not a doc string anyway. - - - - - 5f639054 by David Waern at 2011-01-22T16:09:44+00:00 Fix spelling error - contributed by Marco Silva - - - - - c11dce78 by Ian Lynagh at 2011-01-07T02:33:11+00:00 Follow GHC build system changes - - - - - 101cfaf5 by David Waern at 2011-01-08T14:06:44+00:00 Bump version - - - - - af62348b by David Waern at 2011-01-08T14:07:07+00:00 TAG 2.9.2 - - - - - 4d1f6461 by Ian Lynagh at 2011-01-07T23:06:57+00:00 Name the haddock script haddock-ghc-7.0.2 instead of haddock-7.0.2; haskell/haddock#4882 "7.0.2" looked like a haddock version number before - - - - - 8ee4d5d3 by Simon Peyton Jones at 2011-01-10T17:31:12+00:00 Update Haddock to reflect change in hs_tyclds field of HsGroup - - - - - 06f3e3db by Ian Lynagh at 2011-03-03T15:02:37+00:00 TAG GHC 7.0.2 release - - - - - 7de0667d by David Waern at 2011-03-10T22:47:13+00:00 Update CHANGES - - - - - 33a9f1c8 by David Waern at 2011-03-10T22:47:31+00:00 Fix build with ghc 7.0.1 - - - - - 4616f861 by David Waern at 2011-03-10T22:47:50+00:00 TAG 2.9.2-actual - - - - - 0dab5e3c by Simon Hengel at 2011-04-08T15:53:01+00:00 Set shell script for unit tests back to work - - - - - 85c54dee by Simon Hengel at 2011-04-08T16:01:24+00:00 Set unit tests back to work Here "ghci>" was still used instead of ">>>". - - - - - 1cea9b78 by Simon Hengel at 2011-04-08T16:25:36+00:00 Update runtests.hs for GHC 7.0.2 - - - - - 8e5b3bbb by Simon Hengel at 2011-04-08T16:28:49+00:00 Update Haddock version in *.html.ref - - - - - 2545e955 by Simon Hengel at 2011-04-08T17:09:28+00:00 Add support for blank lines in the result of examples Result lines that only contain the string "<BLANKLINE>" are treated as a blank line. - - - - - adf64d2e by Simon Hengel at 2011-04-08T17:36:50+00:00 Add documentation for "support for blank lines in the result of examples" - - - - - c51352ca by David Waern at 2011-05-21T23:57:56+00:00 Improve a haddock comment - - - - - 7419cf2c by David Waern at 2011-05-22T15:41:52+00:00 Use cabal's test suite support to run the test suite This gives up proper dependency tracking of the test script. - - - - - 7770070c by David Waern at 2011-05-22T01:45:44+00:00 We don't need to send DocOptions nor a flag to mkExportItems - - - - - 9d95b7b6 by David Waern at 2011-05-22T21:39:03+00:00 Fix a bug - - - - - 1f93699b by David Waern at 2011-05-22T21:40:21+00:00 Break out fullContentsOf, give it a better name and some documentation The documentation describes how we want this function to eventually behave, once we have fixed a few problems with the current implementation. - - - - - 9a86432f by David Waern at 2011-05-22T21:53:52+00:00 Fix some stylistic issues in mkExportItems - - - - - c271ff0c by David Waern at 2011-05-22T22:09:11+00:00 Indentation - - - - - 93e602b1 by David Waern at 2011-06-10T01:35:31+00:00 Add git commits since switchover: darcs format (followed by a conflict resolution): commit 6f92cdd12d1354dfbd80f8323ca333bea700896a Merge: f420cc4 28df3a1 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 19 17:54:34 2011 +0100 Merge remote branch 'origin/master' into ghc-generics commit 28df3a119f770fdfe85c687dd73d5f6712b8e7d0 Author: Max Bolingbroke <batterseapower at hotmail.com> Date: Sat May 14 22:37:02 2011 +0100 Unicode fix for getExecDir on Windows commit 89813e729be8bce26765b95419a171a7826f6d70 Merge: 6df3a04 797ab27 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 9 11:55:17 2011 +0100 Merge branch 'ghc-new-co' commit 6df3a040da3dbddee67c6e30a892f87e6b164383 Author: Ian Lynagh <igloo at earth.li> Date: Sun May 8 17:05:50 2011 +0100 Follow changes in SDoc commit f420cc48b9259f0b1afd2438b12f9a2bde57053d Author: Jose Pedro Magalhaes <jpm at cs.uu.nl> Date: Wed May 4 17:31:52 2011 +0200 Adapt haddock to the removal of HsNumTy and TypePat. commit 797ab27bdccf39c73ccad374fea265f124cb52ea Merge: 1d81436 5a91450 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:05:03 2011 +0100 Merge remote branch 'origin/master' into ghc-new-co commit 1d8143659a81cf9611668348e33fd0775c7ab1d2 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:03:46 2011 +0100 Wibbles for ghc-new-co branch commit 5a91450e2ea5a93c70bd3904b022445c9cc82488 Author: Ian Lynagh <igloo at earth.li> Date: Fri Apr 22 00:51:56 2011 +0100 Follow defaultDynFlags change in GHC - - - - - 498da5ae by David Waern at 2011-06-11T00:33:33+00:00 * Merge in git patch from Michal Terepeta >From 6fc71d067738ef4b7de159327bb6dc3d0596be29 Mon Sep 17 00:00:00 2001 From: Michal Terepeta <michal.terepeta at gmail.com> Date: Sat, 14 May 2011 19:18:22 +0200 Subject: [PATCH] Follow the change of TypeSig in GHC. This follows the change in GHC to make TypeSig take a list of names (instead of just one); GHC ticket haskell/haddock#1595. This should also improve the Haddock output in case the user writes a type signature that refers to many names: -- | Some comment.. foo, bar :: ... will now generate the expected output with one signature for both names. - - - - - 094607fe by Ian Lynagh at 2011-06-17T19:10:29+01:00 Fix build - - - - - 8fa35740 by Ian Lynagh at 2011-06-26T21:06:40+01:00 Bump GHC dep to allow 7.2 - - - - - e4d2ca3c by Ian Lynagh at 2011-07-07T23:06:28+01:00 Relax base dep - - - - - b948fde9 by Ian Lynagh at 2011-07-28T16:39:45+01:00 GHC build system: Don't install the datafiles twice - - - - - f82f6d70 by Simon Marlow at 2011-08-11T12:08:15+01:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - b341cc12 by Max Bolingbroke at 2011-08-22T20:25:27+01:00 Fix compilation with no-pred-ty GHC - - - - - 30494581 by Max Bolingbroke at 2011-08-23T10:20:54+01:00 Remaining fixes for PredTy removal - - - - - 0b197138 by Max Bolingbroke at 2011-08-26T08:27:45+01:00 Rename factKind to constraintKind - - - - - a379bec5 by Max Bolingbroke at 2011-09-04T12:54:47+01:00 Deal with change to IParam handling in GHC - - - - - f94e421b by Max Bolingbroke at 2011-09-06T17:34:31+01:00 Adapt Haddock for the ConstraintKind extension changes - - - - - 8821e5cc by Max Bolingbroke at 2011-09-09T08:24:59+01:00 Ignore associated type defaults (just as we ignore default methods) - - - - - 31a0afd4 by Max Bolingbroke at 2011-09-09T09:06:00+01:00 Merge branch 'no-pred-ty' of ssh://darcs.haskell.org/srv/darcs/haddock into no-pred-ty - - - - - dd3b530a by Max Bolingbroke at 2011-09-09T14:10:25+01:00 Merge branch 'no-pred-ty' Conflicts: src/Haddock/Convert.hs - - - - - 5f25ec96 by Max Bolingbroke at 2011-09-09T14:10:40+01:00 Replace FactTuple with ConstraintTuple - - - - - cd30b9cc by David Waern at 2011-09-26T02:17:55+02:00 Bump to version 2.9.3 - - - - - 4fbfd397 by Max Bolingbroke at 2011-09-27T14:55:21+01:00 Follow changes to BinIface Name serialization - - - - - 92257d90 by David Waern at 2011-09-30T23:45:07+02:00 Fix problem with test files not added to distribution tarball - - - - - 00255bda by David Waern at 2011-09-30T23:48:24+02:00 Merge branch 'development' - - - - - 5421264f by David Waern at 2011-10-01T01:25:39+02:00 Merge in darcs patch from Simon Meier: Wed Jun 1 19:41:16 CEST 2011 iridcode at gmail.com * prettier haddock coverage info The new coverage info rendering uses less horizontal space. This reduces the number of unnecessary line-wrappings. Moreover, the most important information, how much has been documented already, is now put up front. Hopefully, this makes it more likely that a library author is bothered by the low coverage of his modules and fixes that issue ;-) - - - - - 07d318ef by David Waern at 2011-10-01T01:34:10+02:00 Use printException instead of deprecated printExceptionAndWarnings - - - - - 40d52ee4 by David Waern at 2011-10-01T01:41:13+02:00 Merge in darcs pach: Mon Apr 11 18:09:54 JST 2011 Liyang HU <haddock at liyang.hu> * Remember collapsed sections in index.html / haddock-util.js - - - - - 279d6dd4 by David Waern at 2011-10-01T01:55:45+02:00 Merge in darcs patch: Joachim Breitner <mail at joachim-breitner.de>**20110619201645 Ignore-this: f6c51228205b0902ad5bfad5040b989a As reported on http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=578301, generating the global index takes much too long if type-level (with lots of auto-generated types) is installed. The patch avoids a quadratic runtime in the subfunction getIfaceIndex of ppHtmlIndex by using a temporary set. Runtime improvement observed here from 25.36s to 2.86s. - - - - - d1612383 by David Waern at 2011-10-01T01:56:48+02:00 Merge branch 'development' - - - - - 347520c1 by David Waern at 2011-10-01T01:56:54+02:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9a0c95e8 by David Waern at 2011-10-01T02:19:10+02:00 Improve .cabal file - - - - - 6967dc64 by Ian Lynagh at 2011-10-01T01:34:06+01:00 Follow changes to ForeignImport/ForeignExport in GHC - - - - - 565cb26b by Simon Marlow at 2011-10-04T00:15:04+02:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - 8b74f512 by David Waern at 2011-10-04T00:18:17+02:00 Requre ghc >= 7.2 - - - - - 271d360c by David Waern at 2011-10-04T00:22:50+02:00 Bump version to 2.9.4 - - - - - 37f3edb0 by David Waern at 2011-10-06T02:30:21+02:00 Add alex and happy to build-tools. - - - - - 7ac2bb6e by David Terei at 2011-10-12T14:02:55-07:00 Add safe haskell indication to haddock output - - - - - 42c91a47 by David Terei at 2011-10-12T14:06:03-07:00 Fix CSS issue with info table not being contained in module header - - - - - 0eddab6c by David Terei at 2011-10-12T14:06:58-07:00 Add safe haskell indication to haddock output - - - - - 3df058eb by David Terei at 2011-10-12T14:07:07-07:00 Fix CSS issue with info table not being contained in module header - - - - - a40a6c3f by David Waern at 2011-10-22T11:29:06+02:00 Bump .haddock file version since the format has changed recently - - - - - 8a6254be by David Waern at 2011-10-22T11:30:42+02:00 Merge branch 'development' - - - - - 642e3e02 by David Waern at 2011-10-23T21:23:39+02:00 Sort import list - - - - - 36371cf8 by David Waern at 2011-10-23T22:48:18+02:00 Remove NEW_GHC_LAYOUT conditional. - - - - - 5604b499 by David Waern at 2011-10-27T00:15:03+02:00 Add --print-ghc-path. - - - - - 463499fa by David Waern at 2011-10-27T00:16:22+02:00 Make testsuite able to find its dependencies automatically. - - - - - a3506172 by Ryan Newton at 2011-11-05T05:59:58-04:00 Improved declNames internal error. Added a case to handle DocD. - - - - - 001b8baf by David Waern at 2011-11-05T20:37:29+01:00 Rename copy.hs -> accept.hs. - - - - - 55d808d3 by David Waern at 2011-11-05T23:30:02+01:00 Fix build. - - - - - deb5c3be by David Waern at 2011-11-06T00:01:47+01:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9b663554 by David Waern at 2011-11-06T00:03:45+01:00 Merge https://github.com/rrnewton/haddock - - - - - 1abb0ff6 by David Waern at 2011-11-06T01:20:37+01:00 Use getDeclMainBinder instead of declNames. - - - - - 4b005c01 by David Waern at 2011-11-06T19:09:53+01:00 Fix build. - - - - - c2c51bc7 by Ian Lynagh at 2011-11-06T23:01:33+00:00 Remove -DNEW_GHC_LAYOUT in ghc.mk - - - - - f847d703 by Jose Pedro Magalhaes at 2011-11-11T09:07:39+00:00 New kind-polymorphic core This big patch implements a kind-polymorphic core for GHC. The current implementation focuses on making sure that all kind-monomorphic programs still work in the new core; it is not yet guaranteed that kind-polymorphic programs (using the new -XPolyKinds flag) will work. For more information, see http://haskell.org/haskellwiki/GHC/Kinds - - - - - 7d7c3b09 by Jose Pedro Magalhaes at 2011-11-16T21:42:22+01:00 Follow changes to tuple sorts in master - - - - - 8430e03e by Simon Peyton Jones at 2011-11-17T10:20:27+00:00 Remove redundant imports - - - - - d1b06832 by Ian Lynagh at 2011-11-19T01:33:21+00:00 Follow GHC build system change to the way we call rm - - - - - 9e2230ed by David Waern at 2011-11-24T15:00:24+01:00 Fix a bug in test runner and get rid of regex-compat dependency. - - - - - 52039b21 by David Waern at 2011-11-24T23:55:36+01:00 Avoid haskell98 dependency in test - - - - - 92e1220d by David Waern at 2011-11-25T00:03:33+01:00 Avoid depency on regex-compat also in accept.hs. - - - - - ddac6b6f by David Waern at 2011-11-25T02:13:38+01:00 Accept test output. - - - - - 5a720455 by David Waern at 2011-11-25T02:16:20+01:00 Some more changes to test scripts. - - - - - 170a9004 by David Waern at 2011-11-25T02:30:41+01:00 Add flag --interface-version. - - - - - d225576c by David Waern at 2011-11-25T02:39:26+01:00 Remove #ifs for older compiler versions. - - - - - f0d0a4f5 by David Waern at 2011-11-26T04:20:12+01:00 Give preference to type over data constructors for doc comment links at renaming time. Previously this was done in the backends. Also, warn when a doc comment refers to something that is in scope but which we don't have the .haddock file for. These changes mean we can make DocIdentifier [a] into DocIdentifier a. - - - - - eef0e776 by David Waern at 2011-11-26T17:01:06+01:00 Allow doc comments to link to out-of-scope things (#78). (A bug that should have been fixed long ago.) - - - - - 565ad529 by David Waern at 2011-11-26T19:56:21+01:00 Update tests. - - - - - fb3ce7b9 by David Waern at 2011-11-26T21:44:28+01:00 Cleanup. - - - - - d0328126 by David Waern at 2011-11-26T22:10:28+01:00 Fix module reference bug. - - - - - c03765f8 by David Waern at 2011-12-03T05:20:20+01:00 Slightly better behaviour on top-levels without type signatures. - Docs don't get attached to the next top-level with signature by mistake. - If there's an export list and the top-level is part of it, its doc comment shows up in the documentation. - - - - - 48461d31 by David Waern at 2011-12-03T05:38:10+01:00 Add a test for Unicode doc comments. - - - - - 549c4b4e by David Waern at 2011-12-03T19:07:55+01:00 Cleanup. - - - - - 7bfecf91 by David Waern at 2011-12-03T20:13:08+01:00 More cleanup. - - - - - 14fab722 by Ian Lynagh at 2011-12-12T21:21:35+00:00 Update dependencies and binaryInterfaceVersion - - - - - 469e6568 by Ian Lynagh at 2011-12-18T12:56:16+00:00 Fix (untested) building from source tarball without alex/happy haddock's .cabal file was declaring that it needed alex and happy to build, but in the GHC source tarballs it doesn't. - - - - - 895c9a8c by David Waern at 2011-12-27T12:57:43+01:00 Go back to having a doc, sub and decl map instead of one big decl map. This setup makes more sense since when we add value bindings to the processed declarations (for type inference), we will have multiple declarations which should share documentation. Also, we already have a separate doc map for instances which we can now merge into the main doc map. Another benefit is that we don't need the DeclInfo type any longer. - - - - - 736767d9 by David Waern at 2011-12-27T13:33:41+01:00 Merge ../../../haddock Conflicts: src/Haddock/InterfaceFile.hs - - - - - 20016f79 by David Waern at 2011-12-27T13:57:23+01:00 Bump version. - - - - - 31f276fb by David Waern at 2011-12-27T13:57:32+01:00 Merge ../ghc/utils/haddock - - - - - 95b367cd by David Waern at 2011-12-27T14:57:29+01:00 Update tests following version bump. - - - - - fa3c94cd by David Waern at 2011-12-27T14:57:51+01:00 Get rid of quite unnecessary use of different lists. - - - - - 9c4d3c54 by David Waern at 2011-12-27T15:26:42+01:00 Cleanup. - - - - - 2caf9f90 by David Waern at 2011-12-27T16:18:05+01:00 Wibbles. - - - - - 3757d09b by David Waern at 2011-12-27T20:50:26+01:00 Complete support for inferring types for top-level bindings. - - - - - 53418734 by David Waern at 2011-12-28T15:02:13+01:00 Minor fixes and cleanup. - - - - - 0c9d0385 by Ian Lynagh at 2012-01-03T18:31:29+00:00 Follow rename of Instance to ClsInst in GHC - - - - - c9bc969a by Simon Hengel at 2012-01-12T21:28:14+01:00 Make sure that generated xhtml is valid (close haskell/haddock#186) Thanks to Phyx. - - - - - 836a0b9a by David Waern at 2012-02-01T02:30:05+01:00 Fix bug introduced in my recent refactoring. - - - - - c7d733eb by David Waern at 2012-02-01T02:30:26+01:00 Cleanup mkMaps and avoid quadratic behaviour. - - - - - da3cda8f by David Waern at 2012-02-01T02:56:56+01:00 Require ghc >= 7.4. - - - - - 83a3287e by David Waern at 2012-02-01T02:57:36+01:00 Update CHANGES. - - - - - 93408f0b by Simon Hengel at 2012-02-04T00:48:04+01:00 Add reference renderings - - - - - 49d00d2c by Simon Hengel at 2012-02-04T00:48:25+01:00 Set unit tests for parser back to work - - - - - eb450980 by Simon Hengel at 2012-02-04T00:49:07+01:00 Add .gitignore - - - - - a841602c by Simon Hengel at 2012-02-04T00:49:16+01:00 Add .ghci file - - - - - 8861199d by Simon Hengel at 2012-02-04T00:49:29+01:00 tests/html-tests/copy.hs: Use mapM_ instead of mapM So we do net get a list of () on stdout when running with runhaskell. - - - - - b477d9b5 by Simon Hengel at 2012-02-04T00:49:46+01:00 Remove index files from golden tests - - - - - 9dbda34e by Simon Hengel at 2012-02-04T00:49:57+01:00 Add /tests/html-tests/tests/*index*.ref to .gitignore - - - - - a9434817 by Simon Hengel at 2012-02-04T00:50:04+01:00 Add DocWarning to Doc The Xhtml backend has special markup for that, Hoogle and LaTeX reuse what we have for DocEmphasis. - - - - - de2fb6fa by Simon Hengel at 2012-02-04T00:50:13+01:00 Add support for module warnings - - - - - 0640920e by Simon Hengel at 2012-02-04T00:50:21+01:00 Add tests for module warnings - - - - - 30ce0d77 by Simon Hengel at 2012-02-04T00:50:29+01:00 Add support for warnings - - - - - bb367960 by Simon Hengel at 2012-02-04T00:50:37+01:00 Add tests for warnings - - - - - 6af1dc2d by Simon Hengel at 2012-02-04T00:50:50+01:00 Expand type signatures in export list (fixes haskell/haddock#192) - - - - - a06cbf25 by Simon Hengel at 2012-02-04T00:51:04+01:00 Expand type signatures for modules without explicit export list - - - - - 57dda796 by Simon Hengel at 2012-02-04T00:51:15+01:00 Remove obsolete TODO - - - - - 270c3253 by David Waern at 2012-02-04T00:51:24+01:00 Fix issues in support for warnings. * Match against local names only. * Simplify (it's OK to map over the warnings). - - - - - 683634bd by David Waern at 2012-02-04T00:55:11+01:00 Some cleanup and make sure we filter warnings through exports. - - - - - 210cb4ca by David Waern at 2012-02-04T03:01:30+01:00 Merge branch 'fix-for-186' of https://github.com/sol/haddock into ghc-7.4 - - - - - e8db9031 by David Waern at 2012-02-04T03:07:51+01:00 Style police. - - - - - 261f9462 by David Waern at 2012-02-04T03:20:16+01:00 Update tests. - - - - - 823cfc7c by David Waern at 2012-02-04T03:21:12+01:00 Use mapM_ in accept.hs as well. - - - - - 873dd619 by David Waern at 2012-02-04T03:21:33+01:00 Remove copy.hs - use accept.hs instead. - - - - - 0e31a14a by David Waern at 2012-02-04T03:47:33+01:00 Use <> instead of mappend. - - - - - 2ff7544f by David Waern at 2012-02-04T03:48:55+01:00 Remove code for older ghc versions. - - - - - dacf2786 by David Waern at 2012-02-04T15:52:51+01:00 Clean up some code from last SoC project. - - - - - 00cbb117 by David Waern at 2012-02-04T21:43:49+01:00 Mostly hlint-inspired cleanup. - - - - - 7dc86cc2 by Simon Peyton Jones at 2012-02-06T09:14:41+00:00 Track changes in HsDecls - - - - - f91f82fe by Ian Lynagh at 2012-02-16T13:40:11+00:00 Follow changes in GHC caused by the CAPI CTYPE pragma - - - - - a0ea6b0b by Ian Lynagh at 2012-02-22T02:26:12+00:00 Follow changes in GHC - - - - - b23b07d1 by Simon Peyton Jones at 2012-03-02T16:36:41+00:00 Follow changes in data representation from the big PolyKinds commit - - - - - 43406022 by Simon Hengel at 2012-03-05T11:18:34+01:00 Save/restore global state for static flags when running GHC actions This is necessary if we want to run createInterfaces (from Documentation.Haddock) multiple times in the same process. - - - - - 9fba16fe by Paolo Capriotti at 2012-03-06T10:57:33+00:00 Update .gitignore. - - - - - a9325044 by Simon Peyton Jones at 2012-03-14T17:35:42+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - fd48065a by Iavor Diatchki at 2012-03-15T22:43:35-07:00 Add support for type-level literals. - - - - - 2e8206dd by Simon Peyton Jones at 2012-03-16T14:18:22+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - 93e13319 by Simon Peyton Jones at 2012-03-17T01:04:05+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock Conflicts: src/Haddock/Convert.hs - - - - - d253fa71 by Iavor Diatchki at 2012-03-19T20:12:18-07:00 Merge remote-tracking branch 'origin/master' into type-nats - - - - - fc40acc8 by Iavor Diatchki at 2012-03-19T20:31:27-07:00 Add a missing case for type literals. - - - - - fd2ad699 by Iavor Diatchki at 2012-03-24T13:28:29-07:00 Rename variable to avoid shadowing warning. - - - - - 9369dd3c by Simon Peyton Jones at 2012-03-26T09:14:23+01:00 Follow refactoring of TyClDecl/HsTyDefn - - - - - 38825ca5 by Simon Peyton Jones at 2012-03-26T09:14:37+01:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - 4324ac0f by David Waern at 2012-04-01T01:51:19+02:00 Disable unicode test. - - - - - 3165b750 by David Waern at 2012-04-01T01:51:34+02:00 Take reader environment directly from TypecheckedSource. - - - - - 213b644c by David Waern at 2012-04-01T01:55:20+02:00 Cleanup. - - - - - 3118b4ba by David Waern at 2012-04-01T02:16:15+02:00 Don't filter out unexported names from the four maps - fixes a regression. - - - - - d6524e17 by David Waern at 2012-04-01T02:40:34+02:00 Fix crash when using --qual. Naughty GHC API! - - - - - ea3c43d8 by Henning Thielemann at 2012-04-01T13:03:07+02:00 add QualOption type for distinction between qualification argument given by the user and the actual qualification for a concrete module - - - - - 5422ff05 by Henning Thielemann at 2012-04-01T16:25:02+02:00 emit an error message when the --qual option is used incorrectly - - - - - 026e3404 by David Waern at 2012-04-01T18:10:30+02:00 Don't crash on unicode strings in doc comments. - - - - - ce006632 by David Waern at 2012-04-01T20:13:35+02:00 Add test for --ignore-all-exports flag/ignore-exports pragma. - - - - - 6e4dd33c by David Waern at 2012-04-01T20:21:03+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.4 - - - - - 734ae124 by Henning Thielemann at 2012-04-01T20:22:10+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - 622f9ba5 by David Waern at 2012-04-01T21:26:13+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 55ce17cb by Henning Thielemann at 2012-04-01T22:03:25+02:00 'abbreviate' qualification style - basic support Currently we ignore the package a module is imported from. This means that a module import would shadow another one with the same module name from a different package. - - - - - c85314ef by David Waern at 2012-04-01T22:05:12+02:00 Check qualification option before processing modules. - - - - - ae4b626c by Henning Thielemann at 2012-04-02T00:19:36+02:00 abbreviated qualification: use Packages.lookupModuleInAllPackages for finding the package that a module belongs to - - - - - 60bdbcf5 by Henning Thielemann at 2012-04-02T00:25:31+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - df44301d by Henning Thielemann at 2012-04-02T00:29:05+02:00 qualification style 'abbreviated' -> 'aliased' - - - - - f4192a64 by David Waern at 2012-04-02T01:05:47+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 7ba09067 by David Terei at 2012-04-04T15:08:21-07:00 Fix reporting of modules safe haskell mode (#5989) - - - - - d0cc33d0 by David Terei at 2012-04-06T15:50:41+01:00 Fix reporting of modules safe haskell mode (#5989) - - - - - 6e3434c5 by Simon Peyton Jones at 2012-04-20T18:37:46+01:00 Track changes in HsSyn - - - - - 22014ed0 by Simon Peyton Jones at 2012-05-11T22:45:15+01:00 Follow changes to LHsTyVarBndrs - - - - - d9a07b24 by David Waern at 2012-05-15T01:46:35+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - a6c4ebc6 by David Waern at 2012-05-16T02:18:32+02:00 Update CHANGES. - - - - - 8e181d29 by David Waern at 2012-05-16T02:27:56+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - e358210d by David Waern at 2012-05-16T02:35:33+02:00 Mention the new aliased --qual mode in CHANGES. - - - - - efd36a28 by David Waern at 2012-05-16T21:33:13+02:00 Bump version number. - - - - - d6b3af14 by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for deprecated record field - - - - - 927f800e by Simon Hengel at 2012-05-17T19:08:20+02:00 Use >>= instead of fmap and join - - - - - 048b41d5 by Simon Hengel at 2012-05-17T19:08:20+02:00 newtype-wrap Doc nodes for things that may have warnings attached - - - - - e3a89fc3 by Simon Hengel at 2012-05-17T19:08:20+02:00 Attach warnings to `Documentation` type - - - - - 5d4cc43d by Simon Hengel at 2012-05-17T19:08:20+02:00 Simplify lookupWarning - - - - - cf8ae69d by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for haskell/haddock#205 - - - - - cb409b19 by Simon Peyton Jones at 2012-05-25T08:30:11+01:00 Follow changes in LHsTyVarBndrs - - - - - 2d5f4179 by Simon Hengel at 2012-05-26T19:21:29+02:00 Add Applicative instance for (GenRnM a) - - - - - e4373060 by Simon Hengel at 2012-05-26T19:21:33+02:00 Use a map for warnings, as suggested by @waern - - - - - 597a68c7 by Simon Hengel at 2012-05-27T08:48:24+02:00 Add an optional label to URLs - - - - - ef1ac7fe by Simon Hengel at 2012-05-27T08:48:24+02:00 Add support for hyperlink labels to parser - - - - - 41f2adce by Simon Hengel at 2012-05-27T08:48:24+02:00 Add golden test for hyperlinks - - - - - 83d5e764 by Simon Hengel at 2012-05-27T08:50:02+02:00 Use LANGUAGE pragmas instead of default-extensions in cabal file - - - - - ddb755e5 by Simon Hengel at 2012-05-27T08:50:02+02:00 Fix typo in comment - - - - - 110676b4 by Simon Hengel at 2012-05-27T08:50:02+02:00 Add a type signature for a where-binding - - - - - 7d9ba2a0 by Ian Lynagh at 2012-06-12T14:38:01+01:00 Follow changes in GHC - - - - - 47c704f2 by Ian Lynagh at 2012-06-12T18:52:16+01:00 Follow changes in GHC - - - - - e1efe1ab by Simon Peyton Jones at 2012-06-13T17:25:29+01:00 Follow changes for the implementation of implicit parameters - - - - - 69abc81c by Ian Lynagh at 2012-06-19T22:52:58+01:00 Follow changes in base - - - - - 9d074a21 by Paolo Capriotti at 2012-06-22T18:26:47+01:00 Use right docMap to get decl documentation. - - - - - e3292ef6 by Ian Lynagh at 2012-07-15T01:31:19+01:00 Follow changes in GHC - - - - - ceae56b0 by Ian Lynagh at 2012-07-16T21:22:48+01:00 Fix haddock following some GHC changes Passing _|_ as the Settings for defaultDynFlags no longer works well enough - - - - - 9df72735 by Paolo Capriotti at 2012-07-19T16:49:32+01:00 Forward port changes from stable. - - - - - 572f5fcf by Ian Lynagh at 2012-07-19T20:38:26+01:00 Merge branch 'master' of darcs.haskell.org:/srv/darcs//haddock - - - - - 9195aca4 by Paolo Capriotti at 2012-07-20T10:27:28+01:00 Update dependencies. - - - - - 33db3923 by Ian Lynagh at 2012-07-20T17:54:43+01:00 Build with GHC 7.7 - - - - - 925a2cea by David Waern at 2012-07-23T16:50:40+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.6 Conflicts: src/Haddock/InterfaceFile.hs - - - - - d710ef97 by David Waern at 2012-07-23T16:52:07+02:00 Bump version number. - - - - - eb0c2f83 by David Waern at 2012-07-23T16:57:58+02:00 Update CHANGES. - - - - - b3f56943 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Hide "internal" instances This fixes haskell/haddock#37 (http://trac.haskell.org/haddock/ticket/37) Precisely, we show an instance iff its class and all the types are exported by non-hidden modules. - - - - - a70aa412 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Tests for hiding instances (#37) - - - - - c0f4aa58 by Simon Hengel at 2012-07-27T13:00:13+03:00 Add an other test for hiding instances (#37) - - - - - a7ed6268 by Ian Lynagh at 2012-08-07T14:48:13+01:00 Follow changes in GHC - - - - - 0ab30d38 by Ian Lynagh at 2012-08-13T22:12:27+01:00 Improve haddock memory usage - - - - - 0eaa4e30 by Ian Lynagh at 2012-08-13T23:58:46+01:00 Improve haddock memory usage - - - - - 659d26cf by Ian Lynagh at 2012-08-14T13:16:48+01:00 Remove some temporary pragmas I accidentally recorded - - - - - d97fceb6 by Simon Hengel at 2012-08-25T13:19:34+02:00 Add missing dependency to library - - - - - 4c910697 by Simon Hengel at 2012-08-28T07:39:14+02:00 Move .ghci to project root - - - - - fc3c601a by Simon Hengel at 2012-08-28T07:39:14+02:00 accept.hs: Ignore some files - - - - - 1af9b984 by Simon Hengel at 2012-08-28T07:40:04+02:00 Update reference renderings (bump version) - - - - - 980dc253 by Simon Hengel at 2012-08-28T07:40:32+02:00 Update reference renderings (remove links for ()) - - - - - 33651dbf by Simon Hengel at 2012-08-28T07:41:50+02:00 Update documentation of `runInteractiveProcess` in reference rendering - - - - - 7ab25078 by David Waern at 2012-09-07T10:38:50+02:00 Merge branch 'hiddenInstances2' of http://github.com/feuerbach/haddock into ghc-7.6 - - - - - c3de3a4b by David Waern at 2012-09-07T14:29:27+02:00 Follow changes in GHC. - - - - - 298c43ac by David Waern at 2012-09-07T14:59:24+02:00 Update CHANGES. - - - - - e797993a by David Waern at 2012-09-07T15:21:30+02:00 Update ANNOUNCE. - - - - - d0b44790 by David Waern at 2012-09-07T15:22:43+02:00 Merge branch 'hidden-instances' into ghc-7.6 - - - - - 41a4adc8 by Simon Hengel at 2012-09-08T12:08:37+02:00 Update doc/README - - - - - 71ad1040 by Simon Hengel at 2012-09-08T12:17:17+02:00 Add documentation for URL labels - - - - - 9bb41afd by Simon Peyton Jones at 2012-09-20T18:14:26+01:00 Follow data type changes in the tc-untouchables branch Relating entirely to SynTyConRhs - - - - - b8139bfa by Simon Hengel at 2012-09-21T14:24:16+02:00 Disable Unicode test for now - - - - - a5fafdd7 by Simon Hengel at 2012-09-21T14:35:45+02:00 Update TypeOperators test for GHC 7.6.1 Type operators can't be used as type variables anymore! - - - - - 6ccf0025 by Simon Hengel at 2012-09-21T16:02:24+02:00 Remove (Monad (Either e)) instance from ref. rendering of CrossPackageDocs I do not really understand why the behavior changed, so I'll open a ticket, so that we can further investigate. - - - - - b5c6c138 by Ian Lynagh at 2012-09-27T02:00:57+01:00 Follow changes in GHC build system - - - - - b98eded0 by David Waern at 2012-09-27T15:37:02+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 76cc2051 by David Waern at 2012-09-27T15:48:19+02:00 Update hidden instances tests. - - - - - aeaa1c59 by David Waern at 2012-09-28T10:21:32+02:00 Make API buildable with GHC 7.6. - - - - - d76be1b0 by Simon Peyton Jones at 2012-09-28T15:57:05+01:00 Merge remote-tracking branch 'origin/master' into tc-untouchables - - - - - a1922af8 by David Waern at 2012-09-28T19:50:20+02:00 Fix spurious superclass constraints bug. - - - - - bc41bdbb by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove old examples - - - - - bed7d3dd by Simon Hengel at 2012-10-01T11:30:51+02:00 Adapt parsetests for GHC 7.6.1 - - - - - dcdb22bb by Simon Hengel at 2012-10-01T11:30:51+02:00 Add test-suite section for parsetests to cabal file + get rid of HUnit dependency - - - - - 1e5263c9 by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove test flag from cabal file This was not really used. - - - - - 4beee98b by David Waern at 2012-09-28T23:42:28+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 11dd2256 by Ian Lynagh at 2012-10-03T16:17:35+01:00 Follow change in GHC build system - - - - - fbd77962 by Simon Hengel at 2012-10-03T18:49:40+02:00 Remove redundant dependency from cabal file - - - - - 09218989 by Simon Hengel at 2012-10-04T16:03:05+02:00 Fix typo - - - - - 93a2d5f9 by Simon Hengel at 2012-10-04T16:11:41+02:00 Remove trailing whitespace from cabal file - - - - - c8b46cd3 by Simon Hengel at 2012-10-04T16:12:17+02:00 Export Haddock's main entry point from library - - - - - b411e77b by Simon Hengel at 2012-10-04T16:29:46+02:00 Depend on library for executable The main motivation for this is to increase build speed. In GHC's source tree the library is not build, but all modules are now required for the executable, so that GHC's validate will now detect build failures for the library. - - - - - f8f0979f by Simon Hengel at 2012-10-05T00:32:57+02:00 Set executable flag for Setup.lhs - - - - - dd045998 by Simon Hengel at 2012-10-07T16:44:06+02:00 Extend rather than set environment when running HTML tests On some platforms (e.g. ppc64) GHC requires gcc in the path. - - - - - 7b39c3ae by Simon Hengel at 2012-10-07T17:05:45+02:00 cross-package test: re-export IsString instead of Monad There is a monad instance for Q, which is not available on platforms that do not have GHCi support. This caused CrossPackageDocs to fail on those platforms. Re-exporting IsString should test the same thing, but it works on all platforms. - - - - - 0700c605 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Fix some warnings - - - - - f78eca79 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Make -Wall proof - - - - - 6beec041 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Use listToMaybe/fromMaybe instead of safeHead/maybe - - - - - 44b8ce86 by Ian Lynagh at 2012-10-08T21:59:46+01:00 Follow changes in GHC - - - - - 6da5f702 by Simon Hengel at 2012-10-09T11:16:19+02:00 Update .ghci - - - - - 9ac1a1b9 by Kazu Yamamoto at 2012-10-09T12:45:31+02:00 Add markup support for properties - - - - - 1944cb42 by Simon Hengel at 2012-10-09T12:45:31+02:00 Simplify lexing/parsing of properties In contrast to what we do for examples, we do not really need to capture the "prompt" here. - - - - - bffd8e62 by Simon Hengel at 2012-10-09T13:40:14+02:00 Add HTML test for properties - - - - - 2fe9c5cb by Simon Hengel at 2012-10-09T13:40:21+02:00 Add unit tests for properties - - - - - 874e361b by Simon Hengel at 2012-10-09T13:40:33+02:00 Bump interface version - - - - - 2506cc37 by Simon Hengel at 2012-10-09T15:15:04+02:00 Fix parser bug - - - - - 743d2b7d by Simon Hengel at 2012-10-09T15:31:06+02:00 Allow to load interface files with compatible versions - - - - - 981a1660 by Simon Hengel at 2012-10-10T10:32:05+02:00 Export more types from Documentation.Haddock (fixes haskell/haddock#216) - - - - - dff7dc76 by Simon Hengel at 2012-10-10T11:15:19+02:00 Update ANNOUNCE and CHANGES - - - - - edd2bb01 by Simon Hengel at 2012-10-10T11:22:50+02:00 Bump version - - - - - 5039163b by Simon Hengel at 2012-10-10T13:56:04+02:00 Fix typo in documentation - - - - - e4ce34da by Simon Hengel at 2012-10-10T14:28:35+02:00 Add documentation for properties - - - - - 9555ebca by Simon Hengel at 2012-10-11T10:49:04+02:00 Remove redundant if-defs, more source documentation - - - - - 87aa67e1 by Simon Hengel at 2012-10-11T12:32:51+02:00 Adapt cabal file - - - - - c44c1dee by Simon Hengel at 2012-10-11T12:41:58+02:00 Require ghc 7.6 - - - - - 8383bc34 by Simon Hengel at 2012-10-11T12:50:24+02:00 Bump version - - - - - 1030eb38 by Simon Hengel at 2012-10-11T12:55:44+02:00 Update ANNOUNCE and CHANGES - - - - - 74955088 by Simon Hengel at 2012-10-12T09:49:31+02:00 Improve note about `binaryInterfaceVersion` (thanks David) - - - - - ee30f6b7 by Simon Hengel at 2012-10-13T13:40:59+02:00 Update version in html tests, rpm spec file, and user manual - - - - - f2861f18 by Simon Hengel at 2012-10-13T14:40:33+02:00 Remove unused MonadFix constraint - - - - - dfdf1a74 by Simon Hengel at 2012-10-13T15:15:38+02:00 Minor code simplification - - - - - 4ecd1e70 by Simon Hengel at 2012-10-13T15:33:43+02:00 Increase code locality - - - - - f7df5cc9 by Simon Hengel at 2012-10-13T16:03:12+02:00 Minor code simplification - - - - - e737eb6e by Simon Hengel at 2012-10-13T19:03:04+02:00 Handle HsExplicitListTy in renameer (fixes haskell/haddock#213) - - - - - c2dc8f17 by Simon Hengel at 2012-10-13T20:46:31+02:00 Better error messages - - - - - 14d48b4c by Simon Hengel at 2012-10-14T00:21:07+02:00 Simplify RnM type - - - - - 6c2cc547 by Simon Hengel at 2012-10-14T00:23:35+02:00 Simplify lookupRn - - - - - bc77ce85 by Simon Hengel at 2012-10-14T01:51:32+02:00 Organize unite tests hierarchically - - - - - 2306d117 by Simon Hengel at 2012-10-14T10:34:58+02:00 Handle more cases in renameType - - - - - 8a864203 by Simon Hengel at 2012-10-14T11:47:59+02:00 Add mini_HiddenInstances.html.ref and mini_HiddenInstancesB.html.ref - - - - - 3a978eca by Simon Hengel at 2012-10-14T11:49:28+02:00 Add /tests/html-tests/output/ to .gitignore - - - - - db18888a by Simon Hengel at 2012-10-14T13:38:21+02:00 Allow haddock markup in deprecation messages - - - - - e7cfee9f by Simon Hengel at 2012-10-14T14:00:23+02:00 If parsing of deprecation message fails, include it verbatim - - - - - 242a85be by Simon Hengel at 2012-10-14T14:13:24+02:00 Add description for PruneWithWarning test - - - - - 43d33df1 by Simon Hengel at 2012-10-14T15:40:53+02:00 Minor formatting change - - - - - 22768c44 by Simon Hengel at 2012-10-14T16:03:43+02:00 Properly handle deprecation messages for re-exported things (fixes haskell/haddock#220) - - - - - cb4b9111 by Simon Hengel at 2012-10-14T17:30:28+02:00 Add build artifacts for documentation to .gitignore - - - - - 854cd8de by Simon Hengel at 2012-10-14T23:34:51+02:00 unit-tests: Improve readability Add IsString instance for (Doc RdrName) + use <> instead of DocAppend. - - - - - c4446d54 by Simon Hengel at 2012-10-14T23:37:21+02:00 unit-tests: Minor refactoring Rename parse to parseParas. - - - - - 04f2703c by Simon Hengel at 2012-10-15T00:36:42+02:00 Fix typo - - - - - 3d109e44 by Simon Hengel at 2012-10-15T10:30:07+02:00 Add description for DeprecatedReExport test - - - - - 84f0985c by Simon Hengel at 2012-10-15T14:54:19+02:00 Move resources to /resources directory - - - - - a5de7ca6 by Simon Hengel at 2012-10-15T15:46:18+02:00 Move HTML tests to directory /html-test/ - - - - - e21f727d by Simon Hengel at 2012-10-15T19:32:42+02:00 Move HTML reference renderings to /html-test/ref/ - - - - - 3a3c6c75 by Simon Hengel at 2012-10-15T19:32:42+02:00 Copy css, images, etc. on accept - - - - - 40ead6dc by Simon Hengel at 2012-10-15T19:32:42+02:00 Move unit tests to /test directory - - - - - 99a28231 by Simon Hengel at 2012-10-15T19:32:42+02:00 Fix Setup.lhs /usr/bin/runhaskell is not installed on all systems. - - - - - 95faf45e by Simon Hengel at 2012-10-15T19:32:42+02:00 Make test management scripts more robust * They are now independent from the current directory, and hence can be called from everywhere * On UNIX/Linux they can now be run as scripts - - - - - 027aaa2d by Simon Hengel at 2012-10-15T19:53:40+02:00 Add 'dev' flag to cabal file, that builds without -O2 That way --disable-optimization can be used, which decreases build time considerably. - - - - - e0266ede by Simon Hengel at 2012-10-15T20:03:43+02:00 Add test case for "spurious superclass constraints bug" - - - - - 52a2aa92 by Simon Hengel at 2012-10-15T20:28:55+02:00 Adapt accept.lhs, so that it ignores more index files - - - - - 53530781 by Simon Hengel at 2012-10-15T20:49:39+02:00 Rename html-test/runtests.lhs to html-test/run.lhs - - - - - 84518797 by Simon Hengel at 2012-10-15T20:49:39+02:00 Move source files for HTML tests to html-test/src - - - - - a911dc6c by Simon Hengel at 2012-10-15T20:49:39+02:00 Adapt output directory for HTML tests - - - - - d3c15857 by Ian Lynagh at 2012-10-16T16:54:43+01:00 Follow dopt->gopt rename - - - - - 956665a5 by Simon Hengel at 2012-10-18T08:42:48+02:00 Update html-test/README - - - - - 903b1029 by Simon Hengel at 2012-10-18T08:50:26+02:00 Use markdown for html-test/README - - - - - 150b4d63 by Ian Lynagh at 2012-10-18T16:36:00+01:00 Follow changes in GHC: 'flags' has been renamed 'generalFlags' - - - - - 41e04ff9 by Simon Hengel at 2012-11-28T09:54:35+01:00 Export missing types from Documentation.Haddock - - - - - 9be59237 by Ian Lynagh at 2012-11-30T23:20:47+00:00 Update dependencies - - - - - e06842f5 by Simon Hengel at 2012-12-07T20:58:05+01:00 Bump version - - - - - e3dbede0 by Simon Hengel at 2012-12-07T20:58:05+01:00 Add missing test files to cabal file (fixes haskell/haddock#230) - - - - - ee0dcca7 by Simon Hengel at 2012-12-07T20:58:05+01:00 Update CHANGES - - - - - 51601bdb by Simon Peyton Jones at 2012-12-19T17:28:35+00:00 Track changes in UNPACK pragma stuff - - - - - f2573bc1 by Richard Eisenberg at 2012-12-21T20:56:25-05:00 Implement overlapping type family instances. An ordered, overlapping type family instance is introduced by 'type instance where', followed by equations. See the new section in the user manual (7.7.2.2) for details. The canonical example is Boolean equality at the type level: type family Equals (a :: k) (b :: k) :: Bool type instance where Equals a a = True Equals a b = False A branched family instance, such as this one, checks its equations in order and applies only the first the matches. As explained in the note [Instance checking within groups] in FamInstEnv.lhs, we must be careful not to simplify, say, (Equals Int b) to False, because b might later unify with Int. This commit includes all of the commits on the overlapping-tyfams branch. SPJ requested that I combine all my commits over the past several months into one monolithic commit. The following GHC repos are affected: ghc, testsuite, utils/haddock, libraries/template-haskell, and libraries/dph. Here are some details for the interested: - The definition of CoAxiom has been moved from TyCon.lhs to a new file CoAxiom.lhs. I made this decision because of the number of definitions necessary to support BranchList. - BranchList is a GADT whose type tracks whether it is a singleton list or not-necessarily-a-singleton-list. The reason I introduced this type is to increase static checking of places where GHC code assumes that a FamInst or CoAxiom is indeed a singleton. This assumption takes place roughly 10 times throughout the code. I was worried that a future change to GHC would invalidate the assumption, and GHC might subtly fail to do the right thing. By explicitly labeling CoAxioms and FamInsts as being Unbranched (singleton) or Branched (not-necessarily-singleton), we make this assumption explicit and checkable. Furthermore, to enforce the accuracy of this label, the list of branches of a CoAxiom or FamInst is stored using a BranchList, whose constructors constrain its type index appropriately. I think that the decision to use BranchList is probably the most controversial decision I made from a code design point of view. Although I provide conversions to/from ordinary lists, it is more efficient to use the brList... functions provided in CoAxiom than always to convert. The use of these functions does not wander far from the core CoAxiom/FamInst logic. BranchLists are motivated and explained in the note [Branched axioms] in CoAxiom.lhs. - The CoAxiom type has changed significantly. You can see the new type in CoAxiom.lhs. It uses a CoAxBranch type to track branches of the CoAxiom. Correspondingly various functions producing and consuming CoAxioms had to change, including the binary layout of interface files. - To get branched axioms to work correctly, it is important to have a notion of type "apartness": two types are apart if they cannot unify, and no substitution of variables can ever get them to unify, even after type family simplification. (This is different than the normal failure to unify because of the type family bit.) This notion in encoded in tcApartTys, in Unify.lhs. Because apartness is finer-grained than unification, the tcUnifyTys now calls tcApartTys. - CoreLinting axioms has been updated, both to reflect the new form of CoAxiom and to enforce the apartness rules of branch application. The formalization of the new rules is in docs/core-spec/core-spec.pdf. - The FamInst type (in types/FamInstEnv.lhs) has changed significantly, paralleling the changes to CoAxiom. Of course, this forced minor changes in many files. - There are several new Notes in FamInstEnv.lhs, including one discussing confluent overlap and why we're not doing it. - lookupFamInstEnv, lookupFamInstEnvConflicts, and lookup_fam_inst_env' (the function that actually does the work) have all been more-or-less completely rewritten. There is a Note [lookup_fam_inst_env' implementation] describing the implementation. One of the changes that affects other files is to change the type of matches from a pair of (FamInst, [Type]) to a new datatype (which now includes the index of the matching branch). This seemed a better design. - The TySynInstD constructor in Template Haskell was updated to use the new datatype TySynEqn. I also bumped the TH version number, requiring changes to DPH cabal files. (That's why the DPH repo has an overlapping-tyfams branch.) - As SPJ requested, I refactored some of the code in HsDecls: * splitting up TyDecl into SynDecl and DataDecl, correspondingly changing HsTyDefn to HsDataDefn (with only one constructor) * splitting FamInstD into TyFamInstD and DataFamInstD and splitting FamInstDecl into DataFamInstDecl and TyFamInstDecl * making the ClsInstD take a ClsInstDecl, for parallelism with InstDecl's other constructors * changing constructor TyFamily into FamDecl * creating a FamilyDecl type that stores the details for a family declaration; this is useful because FamilyDecls can appear in classes but other decls cannot * restricting the associated types and associated type defaults for a * class to be the new, more restrictive types * splitting cid_fam_insts into cid_tyfam_insts and cid_datafam_insts, according to the new types * perhaps one or two more that I'm overlooking None of these changes has far-reaching implications. - The user manual, section 7.7.2.2, is updated to describe the new type family instances. - - - - - f788d0fb by Simon Peyton Jones at 2012-12-23T15:49:58+00:00 Track changes in HsBang - - - - - ca460a0c by Simon Peyton Jones at 2012-12-23T15:50:28+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - f078fea6 by Simon Peyton Jones at 2013-01-02T08:33:13+00:00 Use InstEnv.instanceSig rather than instanceHead (name change) - - - - - 88e41305 by Simon Peyton Jones at 2013-01-14T17:10:27+00:00 Track change to HsBang type - - - - - e1ad4e19 by Kazu Yamamoto at 2013-02-01T11:59:24+09:00 Merge branch 'ghc-7.6' into ghc-7.6-merge-2 Conflicts: haddock.cabal src/Haddock/Interface/AttachInstances.hs src/Haddock/Interface/Create.hs src/Haddock/Interface/LexParseRn.hs src/Haddock/InterfaceFile.hs src/Haddock/Types.hs Only GHC HEAD can compile this. GHC 7.6.x cannot compile this. Some test fail. - - - - - 62bec012 by Kazu Yamamoto at 2013-02-06T11:12:28+09:00 Using tcSplitSigmaTy in instanceHead' (FIXME is resolved.) - - - - - 013fd2e4 by Kazu Yamamoto at 2013-02-06T17:56:21+09:00 Refactoring instanceHead'. - - - - - 3148ce0e by Kazu Yamamoto at 2013-02-07T17:45:10+09:00 Using new syntax in html-test/src/GADTRecords.hs. - - - - - 626dabe7 by Gabor Greif at 2013-02-15T22:42:01+01:00 Typo - - - - - 1eb667ae by Ian Lynagh at 2013-02-16T17:02:07+00:00 Follow changes in base - - - - - 3ef8253a by Ian Lynagh at 2013-03-01T23:23:57+00:00 Follow changes in GHC's build system - - - - - 1a265a3c by Ian Lynagh at 2013-03-03T23:12:07+00:00 Follow changes in GHC build system - - - - - 69941c79 by Max Bolingbroke at 2013-03-10T09:38:28-07:00 Use Alex 3's Unicode support to properly lex source files as UTF-8 Signed-off-by: David Waern <david.waern at gmail.com> - - - - - ea687dad by Simon Peyton Jones at 2013-03-15T14:16:10+00:00 Adapt to tcRnGetInfo returning family instances too This API change was part of the fix to Trac haskell/haddock#4175. But it offers new information to Haddock: the type-family instances, as well as the class instances, of this type. This patch just drops the new information on the floor, but there's an open opportunity to use it in the information that Haddock displays. - - - - - 971a30b0 by Andreas Voellmy at 2013-05-19T20:47:39+01:00 Fix for haskell/haddock#7879. Changed copy of utils/haddock/html/resources/html to use "cp -RL" rather than "cp -R". This allows users to run validate in a build tree, where the build tree was setup using lndir with a relative path to the source directory. - - - - - 31fb7694 by Ian Lynagh at 2013-05-19T20:47:49+01:00 Use "cp -L" when making $(INPLACE_LIB)/latex too - - - - - e9952233 by Simon Hengel at 2013-06-01T18:06:50+02:00 Add -itest to .ghci - - - - - b06873b3 by Mateusz Kowalczyk at 2013-06-01T18:06:50+02:00 Workaround for a failing build with --enable-tests. - - - - - e7858d16 by Simon Hengel at 2013-06-01T19:29:28+02:00 Fix broken test - - - - - 0690acb1 by Richard Eisenberg at 2013-06-21T14:08:25+01:00 Updates to reflect changes in HsDecls to support closed type families. - - - - - 7fd347ec by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 53ed81b6 by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 931c4f4f by Richard Eisenberg at 2013-07-24T13:15:59+01:00 Remove (error "synifyKind") to use WithinType, to allow haddock to process base. - - - - - 55a9c804 by Richard Eisenberg at 2013-08-02T15:54:55+01:00 Changes to reflect changes in GHC's type HsTyVarBndr - - - - - b6e9226c by Mathieu Boespflug at 2013-08-04T10:39:43-07:00 Output Copright and License keys in Xhtml backend. This information is as relevant in the documentation as it is in the source files themselves. Signed-off-by: David Waern <david.waern at gmail.com> - - - - - 4c66028a by David Waern at 2013-08-04T15:27:36-07:00 Bump interface file version. - - - - - 67340163 by David Waern at 2013-08-09T16:12:51-07:00 Update tests. - - - - - 2087569b by Mateusz Kowalczyk at 2013-08-25T09:24:13+02:00 Add spec tests. This adds tests for all elements we can create during regular parsing. This also adds tests for text with unicode in it. - - - - - 97f36a11 by Mateusz Kowalczyk at 2013-08-27T06:59:12+01:00 Fix ticket haskell/haddock#247. I do the same thing that the XHTML backend does: give these no special treatment and just act as if they are regular functions. - - - - - 60681b4f by Mateusz Kowalczyk at 2013-08-27T21:22:48+02:00 LaTeX tests setup - - - - - fa4c27b2 by Mateusz Kowalczyk at 2013-09-02T23:21:43+01:00 Fixes haskell/haddock#253 - - - - - 1a202490 by Mateusz Kowalczyk at 2013-09-03T01:12:50+01:00 Use Hspec instead of nanospec This is motivated by the fact that Haddock tests are not ran by the GHC's ‘validate’ script so we're pretty liberal on dependencies in that area. Full Hspec gives us some nice features such as Quickcheck integration. - - - - - 8cde3b20 by David Luposchainsky at 2013-09-08T07:27:28-05:00 Fix AMP warnings Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - d10661f2 by Herbert Valerio Riedel at 2013-09-11T15:15:01+02:00 Update Git repo URL in `.cabal` file - - - - - 16a44eb5 by Richard Eisenberg at 2013-09-17T09:34:26-04:00 Revision to reflect new role annotation syntax in GHC. - - - - - 4b9833b9 by Herbert Valerio Riedel at 2013-09-18T10:15:28+02:00 Add missing `traverse` method for `GenLocated` As `Traversable` needs at least one of `traverse` or `sequenceA` to be overridden. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - b71fed5d by Simon Hengel at 2013-09-18T22:43:34+02:00 Add test helper - - - - - 4fc1ea86 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#231 - - - - - 435872f6 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#256 We inject -dynamic-too into flags before we run all our actions in the GHC monad. - - - - - b8b24abb by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Add new field to DynFlags - - - - - 49558795 by Simon Hengel at 2013-09-18T22:43:35+02:00 Fallback to ./resources when Cabal data is not found (so that themes are found during development) - - - - - bf79d05c by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Fixes haskell/haddock#5 - - - - - e1baebc2 by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Print missing documentation. Fixes haskell/haddock#258. - - - - - 02ea74de by Austin Seipp at 2013-10-09T10:52:22-05:00 Don't consider StaticFlags when parsing arguments. Instead, discard any static flags before parsing the command line using GHC's DynFlags parser. See http://ghc.haskell.org/trac/ghc/ticket/8276 Based off a patch from Simon Hengel. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 704fd5bb by Simon Hengel at 2013-11-09T00:15:13+01:00 Update HTML tests - - - - - f9fed49e by Simon Hengel at 2013-11-10T18:43:58+01:00 Bump version - - - - - 97ae1999 by Simon Peyton Jones at 2013-11-25T17:25:14+00:00 Track changes in HsSpliceTy data constructor - - - - - 59ad8268 by Simon Peyton Jones at 2014-01-10T18:17:43+00:00 Adapt to small change in Pretty's exports - - - - - 8b12e6aa by Simon Hengel at 2014-01-12T14:48:35-06:00 Some code simplification by using traverse - - - - - fc5ea9a2 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix warnings in test helper - - - - - 6dbb3ba5 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Add ByteString version of Attoparsec - - - - - 968d7774 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 One pass parser and tests. We remove the HTML test as it is no longer necessary. We cover the test case in spec tests and other HTML tests but keeping this around fails: this is because the new parser has different semantics there. In fact, I suspect the original behaviour was a bug that wasn't caught/fixed but simply included as-is during the testing. - - - - - 37a07c9c by Simon Hengel at 2014-01-12T14:48:35-06:00 Rename Haddock.ParseSpec to Haddock.ParserSpec - - - - - f0f68fe9 by Simon Hengel at 2014-01-12T14:48:35-06:00 Don't append newline to parseString input We also check that we have parsed everything with endOfInput. - - - - - 95d60093 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix totality, unicode, examples, paragraph parsing Also simplify specs and parsers while we're at it. Some parsers were made more generic. This commit is a part of GHC pre-merge squash, email fuuzetsu at fuuzetsu.co.uk if you need the full commit history. - - - - - 7d99108c by Simon Hengel at 2014-01-12T14:48:35-06:00 Update acceptance tests - - - - - d1b59640 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Support for bold. Conflicts: src/Haddock/Backends/Hoogle.hs src/Haddock/Interface/Rename.hs src/Haddock/Parser.hs - - - - - 4b412b39 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Allow for headings inside function documentation. LaTeX will treat the h3-h6 headings the same as we'd have to hack the style file heavily otherwise and it would make the headings tiny anyway. Hoogle upstream said they will put in the functionality on their end. Conflicts: src/Haddock/Interface/Rename.hs src/Haddock/Types.hs test/Haddock/ParserSpec.hs - - - - - fdcca428 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Per-module extension flags and language listing. Any extensions that are not enabled by a used language (Haskell2010 &c) will be shown. Furthermore, any implicitly enabled are also going to be shown. While we could eliminate this either by using the GHC API or a dirty hack, I opted not to: if a user doesn't want the implied flags to show, they are recommended to use enable extensions more carefully or individually. Perhaps this will encourage users to not enable the most powerful flags needlessly. Enabled with show-extensions. Conflicts: src/Haddock/InterfaceFile.hs - - - - - 368942a2 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Bump interface version There were some breaking changes over the last few patches so we bump the interface version. This causes a big problem with testing: 1. To generate cross package docs, we first need to generate docs for the package used. 2. To generate package docs with new interface version, we need to use Haddock which has the version bumped. 3. To get Haddock with the version bump, we first need to test cross package docs 4. GOTO 1 So the problem is the chicken and the egg problem. It seems that the only solution would be to generate some interface files on the fly but it is non-trivial. To run this test, you'll have to: * build Haddock without the test (make sure everything else passes) * rebuild the packages used in the test with your shiny new binary making sure they are visible to Haddock * remove the ‘_hidden’ suffix and re-run the tests Note: because the packages currently used for this test are those provided by GHC, it's probably non-trivial to just re-build them. Preferably something less tedious to rebuild should be used and something that is not subject to change. - - - - - 124ae7a9 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow for nesting of paragraphs under lists. The nesting rules are similar to Markdown's with the exception that we can not simply indent the first line of a hard wrapped indented paragraph and have it treated as if it was fully indented. The reason is differences in markup as some of our constructs care about whitespace while others just swallow everything up so it's just a lot easier to not bother with it rather than making arbitrary rules. Note that we now drop trailing for string entities inside of lists. They weren't needed and it makes the output look uniform whether we use a single or double newline between list elements. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - c7913535 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow escaping in URLs and pictures. Some tests were moved under parseString as they weren't about paragraph level markup. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - 32326680 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update documentation. - - - - - fbef6406 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update maintainer - - - - - b40e82f4 by Mateusz Kowalczyk at 2014-01-13T02:39:25-06:00 Fixes haskell/haddock#271 Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - f4eafbf8 by Gergő Érdi at 2014-01-19T15:35:16-06:00 Support for -XPatternSynonyms Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - a8939591 by Austin Seipp at 2014-01-29T08:09:04-06:00 Update CPP check for __GLASGOW_HASKELL__ Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 30d7e9d5 by Gergő Érdi at 2014-01-31T00:15:01+08:00 <+>: Don't insert a space when concatenating empty nodes - - - - - a25ccd4d by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Fix @ code blocks In cases where we had some horizontal space before the closing ‘@’, the parser would not accept the block as a code block and we'd get ugly output. - - - - - 0f67305a by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Update tests This updates tests due to Haddock Trac haskell/haddock#271 fix and due to removal of TypeHoles as an extension from GHC. - - - - - 157322a7 by Gergő Érdi at 2014-01-31T01:03:17+08:00 Handle infix vs prefix names correctly everywhere, by explicitly specifying the context The basic idea is that "a" and "+" are either pretty-printed as "a" and "(+)" or "`a`" and "+" - - - - - aa6d9685 by Mateusz Kowalczyk at 2014-01-30T17:21:50+00:00 Correct whitespace in ‘hidden’ test for <+> change - - - - - 121872f0 by Mateusz Kowalczyk at 2014-02-09T17:59:12+00:00 Document module header. Fixes Haddock Trac haskell/haddock#270. - - - - - e3253746 by Mateusz Kowalczyk at 2014-02-10T21:37:48+00:00 Insert a space between module link and description Fixes Haddock Trac haskell/haddock#277. - - - - - 771d2384 by Mateusz Kowalczyk at 2014-02-10T23:27:21+00:00 Ensure a space between type signature and ‘Source’ This is briefly related to Haddock Trac haskell/haddock#249 and employs effectively the suggested fix _but_ it doesn't actually fix the reported issue. This commit simply makes copying the full line a bit less of a pain. - - - - - 8cda9eff by nand at 2014-02-11T15:48:30+00:00 Add support for type/data families This adds support for type/data families with their respective instances, as well as closed type families and associated type/data families. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 3f22c510 by nand at 2014-02-11T15:53:50+00:00 Improve display of poly-kinded type operators This now displays them as (==) k a b c ... to mirror GHC's behavior, instead of the old (k == a) b c ... which was just wrong. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - effb2d6b by nand at 2014-02-11T15:56:50+00:00 Add test case for PatternSynonyms This just tests various stuff including poly-kinded patterns and operator patterns to make sure the rendering isn't broken. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - b38faf0d by Niklas Haas at 2014-02-13T21:53:32+00:00 Get rid of re-implementation of sortBy I have no idea what this was doing lying around here, and due to the usage of tuples it's actually slower, too. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - ac1e0413 by Mateusz Kowalczyk at 2014-02-13T23:57:16+00:00 Only warn about missing docs when docs are missing This fixes the ‘Missing documentation for…’ message for modules with 100% coverage. - - - - - cae2e36a by Niklas Haas at 2014-02-15T21:56:18+00:00 Add test case for inter-module type/data family instances These should show up in every place where the class is visible, and indeed they do right now. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 8bea5c3a by Mateusz Kowalczyk at 2014-02-19T05:11:34+00:00 Use a bespoke data type to indicate fixity This deals with what I imagine was an ancient TODO and makes it much clearer what the argument actually does rather than having the user chase down the comment. - - - - - 5b52d57c by Niklas Haas at 2014-02-22T21:31:03+01:00 Strip a single leading space from bird tracks (#201) This makes bird tracks in the form > foo > bar > bat parse as if they had been written as >foo >bar >bat ie. without the leading whitespace in front of every line. Ideally we also want to look into how leading whitespace affects code blocks written using the @ @ syntax, which are currently unaffected by this patch. - - - - - 5a1315a5 by Simon Hengel at 2014-02-22T21:55:35+01:00 Turn a source code comment into specs - - - - - 784cfe58 by Mateusz Kowalczyk at 2014-02-23T05:02:22+00:00 Update test case for lifted GADT type rendering The parsing of these seems to have been fixed by GHC folk and it now renders differently. IMHO it now renders in a better way so I'm updating the test to reflect this. - - - - - c3c88c2f by Mateusz Kowalczyk at 2014-02-23T06:37:14+00:00 Don't shadow ‘strip’. -Wall complains - - - - - 293031d8 by Niklas Haas at 2014-02-23T15:21:52+01:00 Make ImplicitParams render correctly (#260) This introduces a new precedence level for single contexts (because implicit param contexts always need parens around them, but other types of contexts don't necessarily, even when alone) - - - - - 4200842d by Niklas Haas at 2014-02-23T15:37:13+01:00 Lower precedence of equality constraints This drops them to the new precedence pREC_CTX, which makes single eqaulity constraints show up as (a ~ b) => ty, in line with GHC's rendering. Additional tests added to make sure other type operators render as intended. Current behavior matches GHC - - - - - b59e3227 by Niklas Haas at 2014-02-23T16:11:22+01:00 Add RankNTypes test case to ImplicitParams.hs This test actually tests what haskell/haddock#260 originally reported - I omitted the RankNTypes scenario from the original fix because I realized it's not relevant to the underlying issue and indeed, this renders as intended now. Still good to have more tests. - - - - - c373dbf7 by Mateusz Kowalczyk at 2014-02-24T06:09:54+00:00 Fix rendering of Contents when links are present Fixes Haddock Trac haskell/haddock#267. - - - - - 9ecb0e56 by Mateusz Kowalczyk at 2014-02-24T06:26:50+00:00 Fix wording in the docs - - - - - 4f4dcd8e by Mateusz Kowalczyk at 2014-02-27T03:00:33+00:00 Change rendering of duplicate record field docs See Haddock Trac haskell/haddock#195. We now change this behaviour to only rendering the documentation attached to the first instance of a duplicate field. Perhaps we could improve this by rendering the first instance that has documentation attached to it but for now, we'll stick with this. - - - - - ad8aa609 by Niklas Haas at 2014-03-08T09:43:26+01:00 Render fixity information Affects functions, type synonyms, type families, class names, data type names, constructors, data families, associated TFs/DFs, type synonyms, pattern synonyms and everything else I could think of. - - - - - 6a39c917 by Niklas Haas at 2014-03-09T07:43:39+01:00 Reorder topDeclElem to move the source/wiki links to the top They appear in the same position due to the float: right attribute but now they're always at the top of the box instead of at the bottom. - - - - - 2d34b3b4 by Niklas Haas at 2014-03-09T07:53:46+01:00 Use optLast instead of listToMaybe for sourceUrls/wikiUrls This lets you override them using eg. cabal haddock --haddock-options, which can come in handy if you want to use a different layout or URL for your source code links than cabal-install generates. - - - - - 0eff4624 by Niklas Haas at 2014-03-09T07:53:46+01:00 Differentiate between TH splices (line-links) and regular names This adds a new type of source code link, to a specific line rather than a specific declaration/name - this is used to link to the location of a TH splice that defines a certain name. Rather hefty changes throughout and still one unresolved issue (the line URLs aren't parsed from the third form of --read-interface which means they're currently restricted to same-interface links). Not sure if this issue is really worth all the hassle, especially since we could just use line links in general. This commit also contains some cleanup/clarification of the types in Haddock.Backends.Xhtml.Decl and shortens some overlong lines in the process. Notably, the Bool parameter was replaced by a Unicode type synonym to help clarify its presence in type signatures. - - - - - 66d6f77b by Niklas Haas at 2014-03-09T20:02:43+01:00 Group similar fixities together Identical fixities declared for the same line should now render using syntax like: infix 4 <, >=, >, <= - - - - - 6587f9f5 by Mateusz Kowalczyk at 2014-03-10T04:24:18+00:00 Update changelog - - - - - 7387ddad by Niklas Haas at 2014-03-11T10:26:04+01:00 Include fixity information in the Interface file This resolves fixity information not appearing across package borders. The binary file version has been increased accordingly. - - - - - ab46ef44 by Niklas Haas at 2014-03-11T10:26:04+01:00 Update changelog - - - - - 565cab6f by Niklas Haas at 2014-03-11T10:26:04+01:00 Update appearance of fixity annotations This moves them in-line with their corresponding lines, similar to a presentation envision by @hvr and described in #ghc. Redundant operator names are also omitted when no ambiguity is present. - - - - - 5d7afd67 by Niklas Haas at 2014-03-11T10:26:05+01:00 Filter family instances of hidden types Currently, this check does not extend to hidden right hand sides, although it probably should hide them in that case. - - - - - ec291b0c by Niklas Haas at 2014-03-11T10:26:05+01:00 Add documentation for --source-entity-line - - - - - 0922e581 by Niklas Haas at 2014-03-11T10:37:32+01:00 Revert "Reorder topDeclElem to move the source/wiki links to the top" This reverts commit 843c42c4179526a2ad3526e4c7d38cbf4d50001d. This change is no longer needed with the new rendering style, and it messes with copy/pasting lines. - - - - - 30618e8b by Mateusz Kowalczyk at 2014-03-11T09:41:07+00:00 Bump version to 2.15.0 - - - - - adf3f1bb by Mateusz Kowalczyk at 2014-03-11T09:41:09+00:00 Fix up some whitespace - - - - - 8905f57d by Niklas Haas at 2014-03-13T19:18:06+00:00 Hide RHS of TFs with non-exported right hand sides Not sure what to do about data families yet, since technically it would not make a lot of sense to display constructors that cannot be used by the user. - - - - - 5c44d5c2 by Niklas Haas at 2014-03-13T19:18:08+00:00 Add UnicodeSyntax alternatives for * and -> I could not find a cleaner way to do this other than checking for string equality with the given built-in types. But seeing as it's actually equivalent to string rewriting in GHC's implementation of UnicodeSyntax, it's probably fitting. - - - - - b04a63e6 by Niklas Haas at 2014-03-13T19:18:10+00:00 Display minimal complete definitions for type classes This corresponds to the new {-# MINIMAL #-} pragma present in GHC 7.8+. I also cleaned up some of the places in which ExportDecl is used to make adding fields easier in the future. Lots of test cases have been updated since they now render with minimality information. - - - - - a4a20b16 by Niklas Haas at 2014-03-13T19:18:12+00:00 Strip links from recently added html tests These were accidentally left there when the tests were originally added - - - - - d624f315 by Mateusz Kowalczyk at 2014-03-13T19:19:31+00:00 Update changelog - - - - - d27a21ac by Mateusz Kowalczyk at 2014-03-13T21:19:07+00:00 Always read in prologue files as UTF8 (#286). - - - - - 54b2fd78 by Mateusz Kowalczyk at 2014-03-13T21:28:09+00:00 Style only - - - - - fa4fe650 by Simon Hengel at 2014-03-15T09:04:18+01:00 Add Fuuzetsu maintainers field in cabal file - - - - - f83484b7 by Niklas Haas at 2014-03-15T18:20:24+00:00 Hide minimal definition for only-method classes Previously this was not covered by the All xs check since here it is not actually an All, rather a single Var n. This also adds the previously missing html-test/src/Minimal.hs. - - - - - 0099d276 by Niklas Haas at 2014-03-15T18:20:26+00:00 Fix issue haskell/haddock#281 This is a regression from the data family instances change. Data instances are now distinguished from regular lists by usage of the new class "inst", and the style has been updated to only apply to those. I've also updated the appropriate test case to test this a bit better, including GADT instances with GADT-style records. - - - - - 1f9687bd by Mateusz Kowalczyk at 2014-03-21T17:48:37+00:00 Please cabal sdist - - - - - 75542693 by Mateusz Kowalczyk at 2014-03-22T16:36:16+00:00 Drop needless --split-objs which slows us down. Involves tiny cleanup of all the dynflag bindings. Fixes haskell/haddock#292. - - - - - 31214dc3 by Herbert Valerio Riedel at 2014-03-23T18:01:01+01:00 Fix a few typos Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 0b73e638 by Mateusz Kowalczyk at 2014-03-31T05:34:36+01:00 Print kind signatures on GADTs - - - - - 2bab42f3 by Mateusz Kowalczyk at 2014-03-31T16:53:25+01:00 Add default for new PlatformConstraints field - - - - - 42647c5f by Mateusz Kowalczyk at 2014-03-31T18:29:04+01:00 Drop leading whitespace in @-style blocks. Fixes haskell/haddock#201. - - - - - 98208294 by Niklas Haas at 2014-03-31T20:09:58+02:00 Crash when exporting record selectors of data family instances This fixes bug haskell/haddock#294. This also fixes a related but never-before-mentioned bug about the display of GADT record selectors with non-polymorphic type signatures. Note: Associated data type constructors fail to show up if nothing is exported that they could be attached to. Exporting any of the data types in the instance head, or the class + data family itself, causes them to show up, but in the absence of either of these, exporting just the associated data type with the constructor itself will result in it being hidden. The only scenario I can come up that would involve this kind of situation involved OverlappingInstances, and even then it can be mitigated by just exporting the class itself, so I'm not going to solve it since the logic would most likely be very complicated. - - - - - 3832d171 by Mateusz Kowalczyk at 2014-04-01T19:07:33+01:00 Make CHANGES consistent with what's now in 2.14.2 - - - - - c386ae89 by Mateusz Kowalczyk at 2014-04-01T19:18:36+01:00 Actually bundle extra spec tests in sdist - - - - - bd57a6d3 by Mateusz Kowalczyk at 2014-04-03T21:13:48+01:00 Update test cases for GHC bug haskell/haddock#8945, Haddock haskell/haddock#188 The order of signature groups has been corrected upstream. Here we add a test case and update some existing test-cases to reflect this change. We remove grouped signature in test cases that we can (Minimal, BugDeprecated &c) so that the test is as self-contained as possible. - - - - - 708b88b1 by Mateusz Kowalczyk at 2014-04-03T21:16:07+01:00 Enforce strict GHC version in cabal file This stops people with 7.6.3 trying to install 2.15.x which clearly won't work. Unfortunately we shipped 2.14.x without realising this. - - - - - 60334f7c by Mateusz Kowalczyk at 2014-04-03T21:19:24+01:00 Initialise some new PlatformConstants fields - - - - - ea77f668 by Mateusz Kowalczyk at 2014-04-11T16:52:23+01:00 We don't actually want unicode here - - - - - 0b651cae by Mateusz Kowalczyk at 2014-04-11T18:13:30+01:00 Parse identifiers with ^ and ⋆ in them. Fixes haskell/haddock#298. - - - - - e8ad0f5f by Mateusz Kowalczyk at 2014-04-11T18:47:41+01:00 Ignore version string during HTML tests. - - - - - de489089 by Mateusz Kowalczyk at 2014-04-11T18:59:30+01:00 Update CHANGES to follow 2.14.3 - - - - - beb464a9 by Gergő Érdi at 2014-04-13T16:31:10+08:00 remove Origin flag from LHsBindsLR - - - - - cb16f07c by Herbert Valerio Riedel at 2014-04-21T17:16:50+02:00 Replace local `die` by new `System.Exit.die` Starting with GHC 7.10, System.Exit exports the new `die` which is essentially the same as Haddock.Util.die, so this commit changes Haddock.Util.die to be a simple re-export of System.Exit.die. See also https://ghc.haskell.org/trac/ghc/ticket/9016 for more details. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 9b9b23c7 by Mateusz Kowalczyk at 2014-05-03T15:40:11+02:00 Disambiguate ‘die’ in test runners. - - - - - 5d28a2b8 by Mateusz Kowalczyk at 2014-05-05T09:19:49+02:00 Prepare modules for parser split. We have to generalise the Doc (now DocH) slightly to remove the dependency on GHC-supplied type. - - - - - d3967ff3 by Mateusz Kowalczyk at 2014-05-05T11:00:41+02:00 Move parser + parser tests out to own package. We move some types out that are necessary as well and then re-export and specialise them in the core Haddock. Reason for moving out spec tests is that if we're working on the parser, we can simply work on that and we can ignore the rest of Haddock. The downside is that it's a little inconvenient if at the end of the day we want to see that everything passes. - - - - - 522a448d by Mateusz Kowalczyk at 2014-05-05T11:14:47+02:00 Move out Show and Eq instances to Types They are much more useful to the users here. - - - - - 11a6f0f2 by Mateusz Kowalczyk at 2014-05-06T13:50:31+02:00 Remove no longer necessary parser error handling. We can now drop some Maybe tests and even lets us strip an error handling monad away in a few places. - - - - - 6992c924 by Mateusz Kowalczyk at 2014-05-14T02:23:55+02:00 Please the GHC build-system. As I can not figure out how to do this properly, if we're in GHC tree, we treat the library as being the same package. If we're not in the tree, we require that the library be installed separately. - - - - - 7a8ad763 by Mateusz Kowalczyk at 2014-05-14T14:50:25+02:00 Update issue tracker URL - - - - - f616c521 by Mateusz Kowalczyk at 2014-05-14T14:53:32+02:00 Update issue tracker URL for haddock-library - - - - - 66580ded by Gergő Érdi at 2014-05-25T14:24:16+08:00 Accomodate change in PatSyn representation - - - - - 0e43b988 by Mateusz Kowalczyk at 2014-05-29T03:15:29+02:00 Revert "Accomodate change in PatSyn representation" This reverts commit 57aa591362d7c8ba21285fccd6a958629a422091. I am reverting this because I pushed it to master when it was meant to stay on a wip-branch. Sorry Gergo and everyone who had trouble due to this. - - - - - e10d7ec8 by Mateusz Kowalczyk at 2014-05-29T03:24:11+02:00 Revert "Revert "Accomodate change in PatSyn representation"" This reverts commit e110e6e70e40eed06c06676fd2e62578da01d295. Apparently as per GHC commit ac2796e6ddbd54c5762c53e2fcf29f20ea162fd5 this was actually intended. Embarrasing for me. - - - - - 5861aca9 by Mateusz Kowalczyk at 2014-06-05T19:49:27+02:00 Clear up highlighting of identifiers with ‘'’s. - - - - - d7cc420f by Simon Peyton Jones at 2014-06-06T12:41:09+01:00 Follow change in patSynSig - - - - - 938b4fd8 by Mateusz Kowalczyk at 2014-06-12T07:24:29+02:00 Slightly update the readme. Style-sheets are no longer a recent thing, dead links, old maintainers, different formats. - - - - - c7799dea by Mateusz Kowalczyk at 2014-06-18T00:05:56+02:00 Update cabal files Update repository urls, use subdir property for haddock-library and use a separate versioning scheme for haddock-library in preparation for release. - - - - - a2750b6a by Simon Hengel at 2014-06-18T11:01:18+08:00 Compatibility with older versions of base and bytestring - - - - - 009b4b03 by Simon Hengel at 2014-06-18T11:14:01+08:00 Enable travis-ci for haddock-library - - - - - 9b5862eb by Simon Hengel at 2014-06-18T11:14:01+08:00 haddock-library: Do not depend on haddock-library in test suite I think you either add src to hs-source-dirs or the library to build-depends. But doing both does not make sense (AFAICT). - - - - - fb1f3279 by Simon Hengel at 2014-06-18T11:49:05+08:00 haddock-library: Use -Wall for specs - - - - - 649340e1 by Mateusz Kowalczyk at 2014-06-18T06:58:54+02:00 Use Travis with multiple GHC versions When using HEAD, we build haddock-library directly from repository as a dependency (and thanks to --enable-tests, the tests get ran anyway). In all other cases, we manually run the tests on haddock-library only and don't test the main project. - - - - - d7eeeec2 by Mateusz Kowalczyk at 2014-06-18T07:49:04+02:00 Comment improvements + few words in cabal file - - - - - 0f8db914 by Simon Hengel at 2014-06-18T13:52:23+08:00 Use doctest to check examples in documentation - - - - - 2888a8dc by Simon Hengel at 2014-06-18T14:16:48+08:00 Remove doctest dependency (so that we can use haddock-library with doctest) - - - - - 626d5e85 by Mateusz Kowalczyk at 2014-06-18T08:41:25+02:00 Travis tweaks - - - - - 41d4f9cc by Mateusz Kowalczyk at 2014-06-18T08:58:43+02:00 Don't actually forget to install specified GHC. - - - - - c6aa512a by John MacFarlane at 2014-06-18T10:43:57-07:00 Removed reliance on LambdaCase (which breaks build with ghc 7.4). - - - - - b9b93b6f by John MacFarlane at 2014-06-18T10:54:56-07:00 Fixed haddock warnings. - - - - - a41b0ab5 by Mateusz Kowalczyk at 2014-06-19T01:20:10+02:00 Update Travis, bump version - - - - - 864bf62a by Mateusz Kowalczyk at 2014-06-25T10:36:54+02:00 Fix anchors. Closes haskell/haddock#308. - - - - - 53df91bb by Mateusz Kowalczyk at 2014-06-25T15:04:49+02:00 Drop DocParagraph from front of headers I can not remember why they were wrapped in paragraphs to begin with and it seems unnecessary now that I test it. Closes haskell/haddock#307. - - - - - 29b5f2fa by Mateusz Kowalczyk at 2014-06-25T15:17:20+02:00 Don't mangle append order for nested lists. The benefit of this is that the ‘top-level’ element of such lists is properly wrapped in <p> tags so any CSS working with these will be applied properly. It also just makes more sense. Pointed out at jgm/pandoc#1346. - - - - - 05cb6e9c by Mateusz Kowalczyk at 2014-06-25T15:19:45+02:00 Bump haddock-library to 1.1.0 for release - - - - - 70feab15 by Iavor Diatchki at 2014-07-01T03:37:07-07:00 Propagate overloading-mode for instance declarations in haddock (#9242) - - - - - d4ca34a7 by Simon Peyton Jones at 2014-07-14T16:23:15+01:00 Adapt to new definition of HsDecls.TyFamEqn This is a knock-on from the refactoring from Trac haskell/haddock#9063. I'll push the corresponding changes to GHC shortly. - - - - - f91e2276 by Edward Z. Yang at 2014-07-21T08:14:19-07:00 Track GHC PackageId to PackageKey renaming. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - b010f9ef by Edward Z. Yang at 2014-07-25T16:28:46-07:00 Track changes for module reexports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - 8b85f9f9 by Mateusz Kowalczyk at 2014-07-28T13:25:43+02:00 Catch mid-line URLs. Fixes haskell/haddock#314. - - - - - 4c613a78 by Edward Z. Yang at 2014-08-05T03:11:00-07:00 Track type signature change of lookupModuleInAllPackages Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - e80b051c by Edward Z. Yang at 2014-08-05T17:34:26+01:00 If GhcProfiled, also build Haddock profiled. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f9cccd29 by Edward Z. Yang at 2014-08-07T14:23:35+01:00 Ignore TAGS files. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 00b3af52 by Mateusz Kowalczyk at 2014-08-08T04:58:19+02:00 Update to attoparsec-0.12.1.1 There seems to be memory and speed improvement. - - - - - 5457dc71 by Mateusz Kowalczyk at 2014-08-08T18:24:02+02:00 Fix forgotten src - - - - - 3520cb04 by Mateusz Kowalczyk at 2014-08-14T20:19:07+01:00 Bump down the version for master to 2.14.4 - - - - - dc98c21b by Mateusz Kowalczyk at 2014-08-14T20:23:27+01:00 Revert "Track type signature change of lookupModuleInAllPackages" This reverts commit d59fec2c9551b5662a3507c0011e32a09a9c118f. - - - - - 3f2038c0 by Mateusz Kowalczyk at 2014-08-14T20:23:31+01:00 Revert "Track changes for module reexports." This reverts commit b99b57c0df072d12b67816b45eca2a03cb1da96d. - - - - - 56d4e49e by Mateusz Kowalczyk at 2014-08-14T20:23:42+01:00 Revert "Track GHC PackageId to PackageKey renaming." This reverts commit 8ac42d3327473939c013551750425cac191ff0fd. - - - - - 726ea3cb by Mateusz Kowalczyk at 2014-08-14T20:23:47+01:00 Revert "Adapt to new definition of HsDecls.TyFamEqn" This reverts commit cb96b4f1ed0462b4a394b9fda6612c3bea9886bd. - - - - - 61a88ff0 by Mateusz Kowalczyk at 2014-08-14T20:23:52+01:00 Revert "Propagate overloading-mode for instance declarations in haddock (#9242)" This reverts commit 8d20ca8d5a9bee73252ff2035ec45f9c03d0820c. - - - - - a32ba674 by Mateusz Kowalczyk at 2014-08-14T20:26:03+01:00 Revert "Disambiguate ‘die’ in test runners." This reverts commit dba02d6df32534aac5d257f2d28596238d248942. - - - - - f335820f by Mateusz Kowalczyk at 2014-08-14T20:26:09+01:00 Revert "Replace local `die` by new `System.Exit.die`" This reverts commit 08aa509ebac58bfb202ea79c7c41291ec280a1c5. - - - - - 107078e4 by Mateusz Kowalczyk at 2014-08-14T20:27:34+01:00 Merge branch 'reverts' This reverts any changes that were made to have Haddock compile with 7.9. When 7.10 release comes, we can simply re-apply all the patches and any patches that occur on ghc-head branch from now on. This allows us to build master with 7.8.3 - - - - - b44b3871 by Mateusz Kowalczyk at 2014-08-15T02:47:40+01:00 Fix haskell/haddock#313 by doing some list munging. I get rid of the Monoid instance because we weren't satisfying the laws. Convenience of having <> didn't outweigh the shock-factor of having it behave badly. - - - - - e1a62cde by Mateusz Kowalczyk at 2014-08-15T02:52:56+01:00 Stop testing haskell/haddock#188. Because the change is in GHC 7.9 and we now work against 7.8.3, this test no longer makes sense. We revert it until 7.10 becomes the standard version. If anything, there should be a test for this in GHC itself. - - - - - 54e8286d by Mateusz Kowalczyk at 2014-08-15T05:31:57+01:00 Add haskell/haddock#313 to CHANGES - - - - - 9df7ad5d by Simon Hengel at 2014-08-20T11:25:32+08:00 Fix warning - - - - - ee2574d6 by Simon Hengel at 2014-08-20T12:07:01+08:00 Fix travis builds - - - - - 384cf2e6 by Simon Hengel at 2014-08-20T12:14:31+08:00 Require GHC 7.8.3 - - - - - d4779863 by Simon Hengel at 2014-08-22T12:14:16+08:00 Move Haddock API to a separate package - - - - - 80f3e0e1 by Simon Hengel at 2014-08-22T14:57:38+08:00 Bump version to 2.15.0 and add version constraints - - - - - 309a94ce by Simon Hengel at 2014-08-22T15:18:06+08:00 Add deprecated compatibility module - - - - - 4d1e4e3f by Luite Stegeman at 2014-08-22T20:46:45+02:00 export things to allow customizing how the Ghc session is run - - - - - 47884591 by Luite Stegeman at 2014-08-22T20:46:51+02:00 ghc 7.8.2 compatibility - - - - - 5ea94e2c by Luite Stegeman at 2014-08-22T22:08:58+02:00 install dependencies for haddock-api on travis - - - - - 9fb845b2 by Mateusz Kowalczyk at 2014-08-23T10:09:34+01:00 Move sources under haddock-api/src - - - - - 85817dc4 by Mateusz Kowalczyk at 2014-08-23T10:10:48+01:00 Remove compat stuff - - - - - 151c6169 by Niklas Haas at 2014-08-24T08:14:10+02:00 Fix extra whitespace on signatures and update all test cases This was long overdue, now running ./accept.lhs on a clean test from master will not generate a bunch of changes. - - - - - d320e0d2 by Niklas Haas at 2014-08-24T08:14:35+02:00 Omit unnecessary foralls and fix haskell/haddock#315 This also fixes haskell/haddock#86. - - - - - bdafe108 by Mateusz Kowalczyk at 2014-08-24T15:06:46+01:00 Update CHANGES - - - - - fafa6d6e by Mateusz Kowalczyk at 2014-08-24T15:14:23+01:00 Delete few unused/irrelevant/badly-place files. - - - - - 3634923d by Duncan Coutts at 2014-08-27T13:49:31+01:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. - - - - - 539a7e70 by Herbert Valerio Riedel at 2014-08-31T11:36:32+02:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 9e3a0e5b by Mateusz Kowalczyk at 2014-08-31T12:54:43+01:00 Bump version in doc - - - - - 4a177525 by Mateusz Kowalczyk at 2014-08-31T13:01:23+01:00 Bump haddock-library version - - - - - f99c1384 by Mateusz Kowalczyk at 2014-08-31T13:05:25+01:00 Remove references to deleted files - - - - - 5e51a247 by Mateusz Kowalczyk at 2014-08-31T14:18:44+01:00 Make the doc parser not complain - - - - - 2cedb49a by Mateusz Kowalczyk at 2014-09-03T03:33:15+01:00 CONTRIBUTING file for issues - - - - - 88027143 by Mateusz Kowalczyk at 2014-09-04T00:46:59+01:00 Mention --print-missing-docs - - - - - 42f6754f by Alan Zimmerman at 2014-09-05T18:13:24-05:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e712719e by Austin Seipp at 2014-09-09T01:03:27-05:00 Fix import of 'empty' due to AMP. Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 71c29755 by Herbert Valerio Riedel at 2014-09-09T17:35:20+02:00 Bump `base` constraint for AMP - - - - - 0bf9f3ed by Mateusz Kowalczyk at 2014-09-12T19:18:32+01:00 Delete stale ANNOUNCE - - - - - cac89ee6 by Krzysztof Gogolewski at 2014-09-14T17:17:09+02:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 4d683426 by Edward Z. Yang at 2014-09-18T13:38:11-07:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 80697fd5 by Herbert Valerio Riedel at 2014-09-19T00:07:52+02:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. - - - - - c015eb70 by Herbert Valerio Riedel at 2014-09-19T00:10:36+02:00 Revert "Followup changes to addition of -fwarn-context-quantification" This reverts commit 4023817d7c0e46db012ba2eea28022626841ca9b temporarily as the respective feature hasn't landed in GHC HEAD yet, but this commit blocks later commits from being referenced in GHC HEAD. - - - - - 38ded784 by Edward Z. Yang at 2014-09-18T15:32:15-07:00 Revert "Revert "Followup changes to addition of -fwarn-context-quantification"" This reverts commit db14fd8ab4fab43694139bc203808b814eafb2dc. It's in HEAD now. - - - - - f55d59c9 by Herbert Valerio Riedel at 2014-09-26T19:18:28+02:00 Revert "Fix import of 'empty' due to AMP." This reverts commit 0cc5bc85e9fca92ab712b68a2ba2c0dd9d3d79f4 since it turns out we don't need to re-export `empty` from Control.Monad after all. - - - - - 467050f1 by David Feuer at 2014-10-09T20:07:36-04:00 Fix improper lazy IO use Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. - - - - - cc47b699 by Edward Z. Yang at 2014-10-09T21:38:19-07:00 Fix use-after-close lazy IO bug Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. Signed-off-by: David Feuer <David.Feuer at gmail.com> Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 87babcbe by Austin Seipp at 2014-10-20T20:05:27-05:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - ab259516 by Austin Seipp at 2014-10-20T20:07:01-05:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - b918093c by Mateusz Kowalczyk at 2014-10-29T03:59:39+00:00 Experimental support for collapsable headers Closes haskell/haddock#335 - - - - - 849db129 by Mateusz Kowalczyk at 2014-10-29T10:07:26+01:00 Experimental support for collapsable headers (cherry picked from commit e2ed3b9d8dfab09f1b1861dbc8e74f08e137ebcc) - - - - - a4cc4789 by Herbert Valerio Riedel at 2014-10-31T11:08:26+01:00 Collapse user-defined section by default (re haskell/haddock#335) - - - - - 9da1b33e by Yuras Shumovich at 2014-10-31T16:11:04-05:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - c625aefc by Austin Seipp at 2014-10-31T19:34:10-05:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - c7738e5e by Simon Hengel at 2014-11-02T07:25:30+08:00 Remove -fobject-code from .ghci (this slows down reloads on modifications) - - - - - d4a86e95 by Simon Hengel at 2014-11-03T09:26:11+08:00 Get rid of StandaloneDeriving - - - - - a974e311 by Simon Hengel at 2014-11-03T09:26:11+08:00 Derive more instances - - - - - 8aa0c4d7 by Simon Hengel at 2014-11-03T09:27:08+08:00 Remove unused language extensions - - - - - 3052d46a by Simon Hengel at 2014-11-03T09:30:46+08:00 Minor refactoring - - - - - 4281d3cb by Simon Hengel at 2014-11-03T09:30:46+08:00 parser: Try to parse definition lists right before text paragraphs - - - - - 8ba12bf9 by Simon Hengel at 2014-11-03T09:34:19+08:00 Add support for markdown links (closes haskell/haddock#336) - - - - - a2f8d747 by Simon Hengel at 2014-11-03T09:34:19+08:00 Allow markdown links at the beginning of a paragraph - - - - - 53b11207 by Simon Hengel at 2014-11-03T09:34:20+08:00 Update documentation - - - - - 652267c6 by Simon Hengel at 2014-11-03T09:34:20+08:00 Add support for markdown images - - - - - 9d667502 by Simon Hengel at 2014-11-03T09:34:20+08:00 Allow an optional colon after the closing bracket of definition lists This is to disambiguate them from markdown links and will be require with a future release. - - - - - 8167fc32 by Mateusz Kowalczyk at 2014-11-04T01:16:51+00:00 whitespace only - - - - - 3da62981 by Mateusz Kowalczyk at 2014-11-04T01:17:31+00:00 Fix re-exports of built-in type families Fixes haskell/haddock#310 - - - - - edc76b34 by Mateusz Kowalczyk at 2014-11-04T02:54:28+00:00 Turn some uses of error into recoverable warnings This should at the very least not abort when something weird happens. It does feel like we should have a type that carries these errors until the end however as the user might not see them unless they are printed at the end. - - - - - 0a137400 by Mateusz Kowalczyk at 2014-11-04T04:09:44+00:00 Fix warnings - - - - - d068fc21 by Mateusz Kowalczyk at 2014-11-04T21:04:07+00:00 Fix parsing of identifiers written in infix way - - - - - 1a9f2f3d by Simon Hengel at 2014-11-08T11:32:42+08:00 Minor code simplification - - - - - 6475e9b1 by Simon Hengel at 2014-11-08T17:28:33+08:00 newtype-wrap parser monad - - - - - dc1ea105 by Herbert Valerio Riedel at 2014-11-15T11:55:43+01:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - fbb1aca4 by Simon Hengel at 2014-11-16T08:51:38+08:00 State intention rather than implementation details in Haddock comment - - - - - 97851ab2 by Simon Hengel at 2014-11-16T10:20:19+08:00 (wip) Add support for @since (closes haskell/haddock#26) - - - - - 34bcd18e by Gergő Érdi at 2014-11-20T22:35:38+08:00 Update Haddock to new pattern synonym type signature syntax - - - - - 304b7dc3 by Jan Stolarek at 2014-11-20T17:48:43+01:00 Follow changes from haskell/haddock#9812 - - - - - 920f9b03 by Richard Eisenberg at 2014-11-20T16:52:50-05:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 0bfe4e78 by Alan Zimmerman at 2014-11-21T11:23:09-06:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 356ed45a by Thomas Winant at 2014-11-28T16:11:22-06:00 Support for PartialTypeSignatures - - - - - 5dc8f3b1 by Gergő Érdi at 2014-11-29T15:39:09+08:00 For pattern synonyms, render "pattern" as a keyword - - - - - fe704480 by Mateusz Kowalczyk at 2014-12-09T03:38:32+00:00 List new module in cabal file - - - - - b9ad5a29 by Mateusz Kowalczyk at 2014-12-10T00:58:24+00:00 Allow the parser to spit out meta-info Currently we only use it only for ‘since’ annotations but with these patches it should be fairly simple to add new attributes if we wish to. Closes haskell/haddock#26. It seems to work fine but due to 7.10 rush I don't have the chance to do more exhaustive testing right now. The way the meta is output (emphasis at the end of the whole comment) is fairly arbitrary and subject to bikeshedding. Note that this makes test for Bug310 fail due to interface version bump: it can't find the docs for base with this interface version so it fails. There is not much we can do to help this because it tests for ’built-in’ identifier, not something we can provide ourselves. - - - - - 765af0e3 by Mateusz Kowalczyk at 2014-12-10T01:17:19+00:00 Update doctest parts of comments - - - - - 8670272b by jpmoresmau at 2014-12-10T01:35:31+00:00 header could contain several lines Closes haskell/haddock#348 - - - - - 4f9ae4f3 by Mateusz Kowalczyk at 2014-12-12T06:22:31+00:00 Revert "Merge branch 'reverts'" This reverts commit 5c93cc347773c7634321edd5f808d5b55b46301f, reversing changes made to 5b81a9e53894d2ae591ca0c6c96199632d39eb06. Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - e974ac94 by Duncan Coutts at 2014-12-12T06:26:11+00:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. Conflicts: haddock-api/src/Haddock.hs - - - - - 2f3a2365 by Herbert Valerio Riedel at 2014-12-12T06:26:51+00:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 1dbd6390 by Alan Zimmerman at 2014-12-12T06:32:07+00:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - bb6ff1f4 by Mateusz Kowalczyk at 2014-12-12T06:35:07+00:00 Bump ‘base’ constraint Follows the similar commit made on ghc-head branch - - - - - 466fe4ab by Krzysztof Gogolewski at 2014-12-12T06:37:42+00:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 97e080c9 by Edward Z. Yang at 2014-12-12T06:39:35+00:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: haddock-api/src/Haddock/ModuleTree.hs - - - - - 20b2af56 by Herbert Valerio Riedel at 2014-12-12T06:42:50+00:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. Conflicts: haddock-library/src/Documentation/Haddock/Parser.hs - - - - - b3ad269d by Austin Seipp at 2014-12-12T06:44:14+00:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 072df0dd by Austin Seipp at 2014-12-12T06:45:01+00:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - dbb9294a by Herbert Valerio Riedel at 2014-12-12T06:46:17+00:00 Collapse user-defined section by default (re haskell/haddock#335) Conflicts: haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs - - - - - f23ab545 by Yuras Shumovich at 2014-12-12T06:46:41+00:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - 753a4b67 by Austin Seipp at 2014-12-12T06:46:51+00:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8954e8f5 by Herbert Valerio Riedel at 2014-12-12T06:50:53+00:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - d2b06d61 by Gergő Érdi at 2014-12-12T07:07:30+00:00 Update Haddock to new pattern synonym type signature syntax Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 1ff02426 by Jan Stolarek at 2014-12-12T07:13:24+00:00 Follow changes from haskell/haddock#9812 Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - 06ad7600 by Richard Eisenberg at 2014-12-12T07:13:43+00:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 8fd2aa8b by Alan Zimmerman at 2014-12-12T07:22:25+00:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Backends/LaTeX.hs haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 95c3db98 by Thomas Winant at 2014-12-12T07:35:49+00:00 Support for PartialTypeSignatures Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs haddock-api/src/Haddock/Interface/Create.hs - - - - - 45494428 by Gergő Érdi at 2014-12-12T07:36:18+00:00 For pattern synonyms, render "pattern" as a keyword - - - - - a237e3eb by Mateusz Kowalczyk at 2014-12-12T12:27:13+00:00 Various fixups and bumps for next release - - - - - 22918bcd by Herbert Valerio Riedel at 2014-12-14T10:11:47+01:00 Remove redundant wild-card pattern match (this would otherwise cause a build-failure with `-Werror`) - - - - - 1d6ce947 by Herbert Valerio Riedel at 2014-12-14T10:17:06+01:00 Treat GHC 7.10 the same as GHC 7.9 ...since the current GHC 7.9 is going to become GHC 7.10 real-soon-now anyway - - - - - f434ea89 by Herbert Valerio Riedel at 2014-12-14T18:26:50+01:00 Fixup ghc.mk (follow-up to 1739375eb23342) This makes the GHC build-system aware of the data-files to be copied into the bindist (as haddock.cabal doesn't list those anymore) - - - - - 6fb839eb by Mateusz Kowalczyk at 2014-12-17T09:28:59+00:00 Only keep one Version instead of blindly appending - - - - - 40645489 by Mateusz Kowalczyk at 2014-12-18T07:09:44+00:00 Fix dependency version - - - - - 8b3b927b by Mateusz Kowalczyk at 2014-12-18T07:14:23+00:00 Print missing docs by default Adds --no-print-missing-docs - - - - - 59666694 by Mateusz Kowalczyk at 2014-12-18T07:21:37+00:00 update changelog - - - - - aa6d168e by Mateusz Kowalczyk at 2014-12-18T07:30:58+00:00 Update docs for @since - - - - - 2d7043ee by Luite Stegeman at 2014-12-19T18:29:35-06:00 hide projectVersion from DynFlags since it clashes with Haddock.Version.projectVersion - - - - - aaa70fc0 by Luite Stegeman at 2014-12-22T15:58:43+01:00 Add missing import for standalone haddock-api package - - - - - 9ce01269 by Herbert Valerio Riedel at 2014-12-22T17:48:45+01:00 Reset ghc-head with master's tree (this is an overwriting git merge of master into ghc-head) - - - - - fcd6fec1 by Herbert Valerio Riedel at 2014-12-22T17:51:52+01:00 Bump versions for ghc-7.11 - - - - - 525ec900 by Mateusz Kowalczyk at 2014-12-23T13:36:24+00:00 travis-ci: test with HEAD - - - - - cbf494b5 by Simon Peyton Jones at 2014-12-23T15:22:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 50e01c99 by Mateusz Kowalczyk at 2014-12-29T15:28:47+00:00 Make travis use 7.10.x - - - - - 475e60b0 by Njagi Mwaniki at 2014-12-29T15:30:44+00:00 Turn the README into GitHub Markdown format. Closes haskell/haddock#354 - - - - - 8cacf48e by Luite Stegeman at 2015-01-05T16:25:37+01:00 bump haddock-api ghc dependency to allow release candidate and first release - - - - - 6ed6cf1f by Simon Peyton Jones at 2015-01-06T16:37:47+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 8b484f33 by Simon Peyton Jones at 2015-01-08T15:50:22+00:00 Track naming change in DataCon - - - - - 23c5c0b5 by Alan Zimmerman at 2015-01-16T10:15:11-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e7a5532c by JP Moresmau at 2015-01-22T17:19:03+00:00 Ignore warnings, install Cabal 1.22 - - - - - 86942c84 by jpmoresmau at 2015-01-22T17:19:04+00:00 solve dataDir ambiguity - - - - - 5ceb743e by jpmoresmau at 2015-01-22T19:17:32+00:00 support GHC 7.10: no Safe-Inferred, Foldable instance - - - - - 6a3b3fb5 by Mateusz Kowalczyk at 2015-01-22T19:32:10+00:00 Update test files Test: a correct behaviour for fields comma-separating values. I'm surprised we had no bug open for this. Maybe it affects how haskell/haddock#301 renders now but I doubt. Operators: Seems GHC is giving us a new order for operators, something must have changed on their side again. cc @haasn , this makes the fixity to the side not match the order on the LHS which is a bit unpleasant. Maybe the fixity can be made to match the GHC order? Bug335: We expand examples by default now. Bug310: Now inferred safe. - - - - - 708f8b2f by jpmoresmau at 2015-01-22T19:36:59+00:00 Links to source location of class instance definitions - - - - - 5cf8a6da by Vincent Berthoux at 2015-01-22T19:59:58+00:00 Filter '\r' from comments due to Windows problems. On Windows this was causing newline to be rendered twice in code blocks. Closes haskell/haddock#359, fixes haskell/haddock#356. - - - - - 1749e6f0 by Mateusz Kowalczyk at 2015-01-22T20:31:27+00:00 Changelog only - - - - - c8145f90 by Mateusz Kowalczyk at 2015-01-22T23:34:05+00:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. - - - - - 14248254 by Mateusz Kowalczyk at 2015-01-22T23:43:18+00:00 Sort out some module import warnings - - - - - d8a38989 by Simon Peyton Jones at 2015-01-23T07:10:16-06:00 Track naming change in DataCon (cherry picked from commit 04cf63d0195837ed52075ed7d2676e71831e8a0b) - - - - - d3ac6ae4 by Alan Zimmerman at 2015-01-23T07:17:19-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit d61bbc75890e4eb0ad508b9c2a27b91f691213e6) - - - - - 4c1ffeb0 by Simon Peyton Jones at 2015-02-10T12:10:33+00:00 Track changes in HsSyn for quasi-quotes - - - - - 775d20f7 by Mateusz Kowalczyk at 2015-03-15T08:11:48+01:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. (cherry picked from commit 8e06728afb0784128ab2df0be7a5d7a191d30ff4) - - - - - f9245e72 by Phil Ruffwind at 2015-03-16T04:32:01-04:00 Prevent Synopsis from using up too much horizontal space When long type signatures occur in the Synopsis, the element is stretched beyond the width of the window. Scrollbars don't appear, so it's impossible to read anything when this happens. - - - - - cd8fa415 by Mateusz Kowalczyk at 2015-03-17T21:59:39+00:00 Update changelog Closes haskell/haddock#151 due to 71170fc77962f10d7d001e3b8bc8b92bfeda99bc - - - - - b5248b47 by Ben Gamari at 2015-03-25T17:12:17+00:00 Make the error encountered when a package can't be found more user-friendly Closes haskell/haddock#369 - - - - - b756b772 by Mateusz Kowalczyk at 2015-03-26T16:31:40+00:00 Remove now redundant imports - - - - - 5ea5e8dd by Mateusz Kowalczyk at 2015-03-26T16:45:52+00:00 Update test to account for \r filtering - - - - - 6539bfb3 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Test for anchor defaulting I delete the old tests because it turns out that: * test runner would never put them in scope of each other even with imports so just one would suffice * test runner actually needed some hacking to keep links so in the end we would end up with no anchors making them useless - - - - - 1a01d950 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Clearly default to variables in out of scope case - - - - - 7943abe8 by Mateusz Kowalczyk at 2015-03-27T01:14:11+00:00 Fix Hoogle display of constructors Fixes haskell/haddock#361 - - - - - 6d6e587e by Mateusz Kowalczyk at 2015-03-27T01:45:18+00:00 Fully qualify names in Hoogle instances output Closes haskell/haddock#263 - - - - - 52dac365 by Mateusz Kowalczyk at 2015-03-27T01:55:01+00:00 Update changelog - - - - - ca5af9a8 by Mateusz Kowalczyk at 2015-03-27T02:43:55+00:00 Output method documentation in Hoogle backend One thing of note is that we no longer preserve grouping of methods and print each method on its own line. We could preserve it if no documentation is present for any methods in the group if someone asks for it though. Fixes haskell/haddock#259 - - - - - a33f0c10 by Mateusz Kowalczyk at 2015-03-27T03:04:21+00:00 Don't print instance safety information in Hoogle Fixes haskell/haddock#168 - - - - - df6c935a by Mateusz Kowalczyk at 2015-03-28T00:11:47+00:00 Post-release version bumps and changelog - - - - - dde8f7c0 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Loosen bounds on haddock-* - - - - - de93bf89 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Expand response files in arguments Closes haskell/haddock#285 - - - - - 1f0b0856 by Zejun Wu at 2015-04-26T16:35:35-07:00 Do not insert anchor for section headings in contents box - - - - - 860439d7 by Simon Peyton Jones at 2015-05-01T09:36:47+01:00 Track change in API of TyCon - - - - - a32f3e5f by Adam Gundry at 2015-05-04T15:32:59+01:00 Track API changes to support empty closed type familes - - - - - 77e98bee by Ben Gamari at 2015-05-06T20:17:08+01:00 Ignore doc/haddock.{ps,pdf} - - - - - 663d0204 by Murray Campbell at 2015-05-11T04:47:37-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8bb0dcf5 by Murray Campbell at 2015-05-11T06:35:06-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit 2380f07c430c525b205ce2eae6dab23c8388d899) - - - - - bad900ea by Adam Bergmark at 2015-05-11T15:29:39+01:00 haddock-library: require GHC >= 7.4 `Data.Monoid.<>` was added in base-4.5/GHC-7.4 Closes haskell/haddock#394 Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - daceff85 by Simon Peyton Jones at 2015-05-13T12:04:21+01:00 Track the new location of setRdrNameSpace - - - - - 1937d1c4 by Alan Zimmerman at 2015-05-25T21:27:15+02:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - ee0fb6c2 by Łukasz Hanuszczak at 2015-05-27T11:51:31+02:00 Create simple method for indentation parsing. - - - - - 7d6fcad5 by Łukasz Hanuszczak at 2015-05-27T21:36:13+02:00 Make nested lists count indentation according to first item. - - - - - d6819398 by Łukasz Hanuszczak at 2015-05-27T22:46:13+02:00 Add simple test case for arbitrary-depth list nesting. - - - - - 2929c54d by Łukasz Hanuszczak at 2015-06-03T02:11:31+02:00 Add arbitrary-indent spec test for parser. - - - - - 9a0a9bb0 by Mateusz Kowalczyk at 2015-06-03T05:25:29+01:00 Update docs with info on new list nesting rule Fixes haskell/haddock#278 through commits from PR haskell/haddock#401 - - - - - 12efc92c by Mateusz Kowalczyk at 2015-06-03T05:29:26+01:00 Update some meta data at the top of the docs - - - - - 765ee49f by Bartosz Nitka at 2015-06-07T08:40:59-07:00 Add some Hacking docs for getting started - - - - - 19aaf851 by Bartosz Nitka at 2015-06-07T08:44:30-07:00 Fix markdown - - - - - 2a90cb70 by Mateusz Kowalczyk at 2015-06-08T15:08:36+01:00 Refine hacking instructions slightly - - - - - 0894da6e by Thomas Winant at 2015-06-08T23:47:28-05:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 10a9bb76 by Emanuel Borsboom at 2015-06-12T02:46:23+01:00 Build executable with '-threaded' (fixes haskell/haddock#399) - - - - - 7696b94f by Mateusz Kowalczyk at 2015-06-12T02:59:19+01:00 Update changelog for -threaded Closes haskell/haddock#400 - - - - - d3c118ec by Bartosz Nitka at 2015-06-12T03:00:58+01:00 Fix haddock: internal error: spliceURL UnhelpfulSpan (#207) Inferred type signatures don't have SrcSpans, so let's use the one from the declaration. I've tested this manually on the test-case from haskell/haddock#207, but I got stuck at trying to run the test-suite. - - - - - b67e843b by Mateusz Kowalczyk at 2015-06-12T03:01:50+01:00 Changelog for haskell/haddock#207 Fixes haskell/haddock#207, closes haskell/haddock#402 - - - - - 841d785e by jpmoresmau at 2015-06-12T16:03:16+01:00 Attach to instance location the name that has the same location file Fixes haskell/haddock#383 - - - - - 98791cae by Mateusz Kowalczyk at 2015-06-12T16:08:27+01:00 Update changelog Closes haskell/haddock#398 - - - - - 7c0b5a87 by Phil Ruffwind at 2015-06-12T13:07:25-04:00 Fix alignment of Source links in instance table in Firefox Due to a Firefox bug [1], a combination of 'whitespace: nowrap' on the parent element with 'float: right' on the inner element can cause the floated element to be displaced downwards for no apparent reason. To work around this, the left side is wrapped in its own <span> and set to 'float: left'. As a precautionary measure to prevent the parent element from collapsing entirely, we also add the classic "clearfix" hack. The latter is not strictly needed but it helps prevent bugs if the layout is altered again in the future. Fixes haskell/haddock#384. Remark: line 159 of src/Haddock/Backends/Xhtml/Layout.hs was indented to prevent confusion over the operator precedence of (<+>) vs (<<). [1]: https://bugzilla.mozilla.org/show_bug.cgi?id=488725 - - - - - cfe86e73 by Mateusz Kowalczyk at 2015-06-14T10:49:01+01:00 Update tests for the CSS changes - - - - - 2d4983c1 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding for Haskell source parser module. - - - - - 29548785 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement function for tagging parsed chunks with source spans. - - - - - 6a5e4074 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement simple string chunking based on HsColour library. - - - - - 6e52291f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create basic token classification method. - - - - - da971a27 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Adapt source span tagging to work with current whitespace handling. - - - - - 4feb5a22 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add record accessors to exports of hyperlinker parser module. - - - - - a8cc4e39 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Make parser module export all types and associated accessors. - - - - - fb8d468f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple HTML renderer for parsed source file. - - - - - 80747822 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for specifying the CSS file path in HTML source renderer. - - - - - 994dc1f5 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix identifier recognition in Haskell source parser. - - - - - b1bd0430 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix comment recognition in Haskell source parser. - - - - - 11db85ae by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for recognizing compiler pragmas in source parser. - - - - - 736c7bd3 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding of module for associating tokens with AST names. - - - - - 7e149bc2 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement utility method for extracting variable identifiers from AST. - - - - - 32eb640a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple mechanism for associating tokens with AST names. - - - - - d4eba5bc by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add dummy support for hyperlinking named tokens. - - - - - 2b76141f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matcher bug causing wrong items being hyperlinked. - - - - - 2d48002e by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Constrain elements exported by hyperlinker modules. - - - - - 9715eec6 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for type token recognition. - - - - - 8fa401cb by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for binding token recognition. - - - - - d062400b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement go-to-definition mechanism for local bindings. - - - - - f4dc229b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement module export- and import-list item hyperlinking. - - - - - c9a46d58 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matching to allow parenthesized operators hyperlinking. - - - - - 03aad95a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix weird hyperlinking of parenthesized operators. - - - - - b4694a7d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for type declaration anchors. - - - - - 7358d2d2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for top-level function declaration anchors. - - - - - dfc24b24 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix external anchors to contain HTML file extension. - - - - - a045926c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Refactor the way AST names are handled within detailed tokens. - - - - - c76049b4 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement hyperlinking of imported module names. - - - - - 2d2a1572 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix parsing of single line comments with broken up newlines. - - - - - 11afdcf2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix bug with improper newline handling. - - - - - 8137f104 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issues with escaped newlines in comments. - - - - - 34759b19 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for parsing C preprocessor macros. - - - - - 09f0f847 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for parser module of source hyperlinker. - - - - - 709a8389 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for AST module of source hyperlinker. - - - - - 4df5c227 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add command line option for generating hyperlinked source. - - - - - 7a755ea2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Extend module interface with rich source token stream field. - - - - - 494f4ab1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement source tokenization during interface creation process. - - - - - 5f21c953 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create hyperlinker module and plug it into the Haddock pipeline. - - - - - 0cc8a216 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for providing custom CSS files for hyperlinked source. - - - - - a32bbdc1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for fancy highlighting upon hovering over identifier. - - - - - d16d642a by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make source hyperlinker generate output in apropriate directory. - - - - - ae12953d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create module with hyperlinker utility functions. - - - - - 6d4952c5 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make external hyperlinks point to locations specified by source URLs. - - - - - 8417555d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Rewrite source generation to fixed links and directory structure. - - - - - ce9cec01 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add basic support for cross-package hyperlink generation. - - - - - 7eaf025c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Disable generating hyperlinks for module references. - - - - - a50bf92e by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make Haddock generate source for all interfaces (also hidden ones). - - - - - f5ae2838 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Prevent source parser from throwing exception when lexing fails. - - - - - db9ffbe0 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement workaround for Chrome highlighting issues. - - - - - 0b6b453b by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate correct anchors for data constructors. - - - - - c86d38bc by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate anchors for record field declarations. - - - - - 063abf7f by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issue with hyperlink highlight styling in Chrome browser. - - - - - 880fc611 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking constructor names in patters. - - - - - c9e89b95 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record patterns. - - - - - 17a11996 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record expressions. - - - - - 0eef932d by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Make hyperlinker respect pretty-printer flag and add documentation. - - - - - f87c1776 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Unexpose hyperlinker modules in Cabal configuration. - - - - - 4c9e2b06 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Setup HSpec framework for Haddock API package. - - - - - 4b20cb30 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add basic tests related to comment parsing. - - - - - 6842e919 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add tests related to parsing basic language constructs. - - - - - 87bffb35 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add simple tests for do-notation parsing. - - - - - e7af1841 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add very simple QuickCheck properties for source parser spec. - - - - - c84efcf1 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Create simple test runner for hyperlinker tests. - - - - - 76b90447 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for basic identifier hyperlinking. - - - - - 0fbf4df6 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for operator hyperlinking. - - - - - 731aa039 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for constructor hyperlinking. - - - - - 995a78a2 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for record expressions and patterns hyperlinking. - - - - - 3566875a by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for literal syntax highlighting. - - - - - 68469a35 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add hyperlinker test runner to .cabal and .gitignore files. - - - - - aa946c93 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Adapt hyperlinker test runner to have the same interface as HTML one. - - - - - ce34da16 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Fix hyperlinker test runner file paths and add pretty-printing option. - - - - - 0d7dd65e by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add reference files for hyperlinker test cases. - - - - - efa4a1e0 by Łukasz Hanuszczak at 2015-07-01T00:47:32+02:00 Make hyperlinker test runner strip local links from generated source. - - - - - 3e96e584 by Łukasz Hanuszczak at 2015-07-01T01:14:59+02:00 Create simple script for accepting hyperlinker test case references. - - - - - 526fe610 by Łukasz Hanuszczak at 2015-07-01T01:16:41+02:00 Re-accept hyperlinker test cases with local references stripped out. - - - - - 892e2cb3 by Łukasz Hanuszczak at 2015-07-01T01:22:09+02:00 Fix bug with diffing wrong files in hyperlinker test runner. - - - - - 9ff46039 by Łukasz Hanuszczak at 2015-07-01T18:04:46+02:00 Remove unused dependencies in Haddock API spec configuration. - - - - - 47969c07 by Łukasz Hanuszczak at 2015-07-01T18:32:19+02:00 Add support for hyperlinking synonyms in patterns. - - - - - a73449e0 by Łukasz Hanuszczak at 2015-07-01T18:33:44+02:00 Create test case for hyperlinking @-patterns. - - - - - c2077ed8 by Łukasz Hanuszczak at 2015-07-01T19:06:04+02:00 Add support for hyperlinking universally quantified type variables. - - - - - 68017342 by Łukasz Hanuszczak at 2015-07-01T19:28:32+02:00 Create hyperlinker test case with quantified type variables. - - - - - 51c01a78 by Łukasz Hanuszczak at 2015-07-01T19:34:22+02:00 Add scoped type variables test for polymorphism test case. - - - - - 13181ae2 by Łukasz Hanuszczak at 2015-07-01T19:56:27+02:00 Add record wildcards test for records hyperlinking test case. - - - - - 991b81dd by Łukasz Hanuszczak at 2015-07-01T21:01:42+02:00 Document some functions in XHTML utlity module. - - - - - 98c8dfe5 by Łukasz Hanuszczak at 2015-07-01T22:25:21+02:00 Make hyperlinker render qualified names as one entity. - - - - - 75e13b9b by Łukasz Hanuszczak at 2015-07-01T22:27:38+02:00 Add qualified name test for identifiers hyperlinking test case. - - - - - de1e143f by Łukasz Hanuszczak at 2015-07-02T12:32:59+02:00 Fix crash happening when hyperlinking type family declarations. - - - - - 7a8fb175 by Łukasz Hanuszczak at 2015-07-02T12:47:03+02:00 Add support for anchoring data family constructor declarations. - - - - - 3b404e49 by Łukasz Hanuszczak at 2015-07-02T13:31:05+02:00 Improve support for hyperlinking type families. - - - - - 59eb7143 by Łukasz Hanuszczak at 2015-07-02T13:33:34+02:00 Add hyperlinker test case for checking type and type family declarations. - - - - - d1cda0c0 by Łukasz Hanuszczak at 2015-07-02T13:41:38+02:00 Fix issue with operators being recognized as preprocessor directives. - - - - - da206c9d by Łukasz Hanuszczak at 2015-07-02T17:18:12+02:00 Fix broken tests for parsing and hyperlinking hash operators. - - - - - 53750d1b by Łukasz Hanuszczak at 2015-07-02T18:53:28+02:00 Add support for anchoring signatures in type class declarations. - - - - - 1fa5bb10 by Łukasz Hanuszczak at 2015-07-02T19:04:47+02:00 Make hyperlinker generate anchors only to top-level value bindings. - - - - - a542305c by Łukasz Hanuszczak at 2015-07-02T19:05:58+02:00 Create hyperlinker test case for type classes. - - - - - b0dd4581 by Łukasz Hanuszczak at 2015-07-04T16:28:26+02:00 Update docs with information about source hyperlinking. - - - - - 9795302a by Łukasz Hanuszczak at 2015-07-04T16:52:15+02:00 Update docs on using `--read-interface` option. - - - - - 9acdc002 by Łukasz Hanuszczak at 2015-07-04T17:15:26+02:00 Remove potentially dangerous record access in hyperlinker AST module. - - - - - fb3ab7be by Łukasz Hanuszczak at 2015-07-04T17:40:10+02:00 Make Haddock generate warnings about potential misuse of hyperlinker. - - - - - a324c504 by Łukasz Hanuszczak at 2015-07-04T17:43:22+02:00 Fix incorrect specification of source style option in doc file. - - - - - 3f01a8e4 by Łukasz Hanuszczak at 2015-07-05T17:06:36+02:00 Refactor source path mapping to use modules as indices. - - - - - ac70f5b1 by Łukasz Hanuszczak at 2015-07-05T17:47:34+02:00 Fix bug where not all module interfaces were added to source mapping. - - - - - f5e57da9 by Łukasz Hanuszczak at 2015-07-06T16:39:57+02:00 Extract main hyperlinker types to separate module. - - - - - 43974905 by Łukasz Hanuszczak at 2015-07-06T16:52:13+02:00 Move source paths types to hyperlinker types module. - - - - - 3e236055 by Łukasz Hanuszczak at 2015-07-06T17:06:19+02:00 Add support for hyperlinking modules in import lists. - - - - - 58233d9f by Łukasz Hanuszczak at 2015-07-06T17:26:49+02:00 Add short documentation for hyperlinker source map type. - - - - - 14da016d by Łukasz Hanuszczak at 2015-07-06T18:07:20+02:00 Fix bug with module name being hyperlinked to `Prelude`. - - - - - 8f79db52 by Łukasz Hanuszczak at 2015-07-06T18:23:47+02:00 Fix problem with spec build in Haddock API configuration. - - - - - e7cc056c by Adam Sandberg Eriksson at 2015-07-07T23:22:21+01:00 StrictData: print correct strictness marks - - - - - e8253ca8 by Mateusz Kowalczyk at 2015-07-07T23:58:28+01:00 Update changelog - - - - - 0aba676b by Mateusz Kowalczyk at 2015-07-07T23:58:33+01:00 Relax upper bound on GHC a bit - - - - - 7a595381 by Mateusz Kowalczyk at 2015-07-07T23:58:52+01:00 Delete trailing whitespace - - - - - 50976d5e by Adam Sandberg Eriksson at 2015-07-08T15:03:04+02:00 StrictData: changes in HsBang type - - - - - 83b045fa by Mateusz Kowalczyk at 2015-07-11T14:35:18+01:00 Fix expansion icon for user-collapsible sections Closes haskell/haddock#412 - - - - - b2a3b0d1 by Mateusz Kowalczyk at 2015-07-22T22:03:21+01:00 Make some version changes after 2.16.1 release - - - - - a8294423 by Ben Gamari at 2015-07-27T13:16:07+02:00 Merge pull request haskell/haddock#422 from adamse/adamse-D1033 Merge for GHC D1033 - - - - - c0173f17 by randen at 2015-07-30T14:49:08-07:00 Break the response file by line termination rather than spaces, since spaces may be within the parameters. This simple approach avoids having the need for any quoting and/or escaping (although a newline char will not be possible in a parameter and has no escape mechanism to allow it). - - - - - 47c0ca14 by Alan Zimmerman at 2015-07-31T10:41:52+02:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - 45a9d770 by Mateusz Kowalczyk at 2015-07-31T09:47:43+01:00 Update changelog - - - - - 347a20a3 by Phil Ruffwind at 2015-08-02T23:15:26+01:00 Avoid JavaScript error during page load in non-frame mode In non-frame mode, parent.window.synopsis refers to the synopsis div rather than the nonexistent frame. Unfortunately, the script wrongly assumes that if it exists it must be a frame, leading to an error where it tries to access the nonexistent attribute 'replace' of an undefined value (synopsis.location). Closes haskell/haddock#406 - - - - - 54ebd519 by Phil Ruffwind at 2015-08-02T23:27:10+01:00 Link to the definitions to themselves Currently, the definitions already have an anchor tag that allows URLs with fragment identifiers to locate them, but it is rather inconvenient to obtain such a URL (so-called "permalink") as it would require finding the a link to the corresponding item in the Synopsis or elsewhere. This commit adds hyperlinks to the definitions themselves, allowing users to obtain links to them easily. To preserve the original aesthetics of the definitions, we alter the color of the link so as to be identical to what it was, except it now has a hover effect indicating that it is clickable. Additionally, the anchor now uses the 'id' attribute instead of the (obsolete) 'name' attribute. Closes haskell/haddock#407 - - - - - 02cc8bb7 by Phil Ruffwind at 2015-08-02T23:28:02+01:00 Fix typo in Haddock.Backends.Xhtml.Layout: divSynposis -> divSynopsis Closes haskell/haddock#408 - - - - - 2eb0a458 by Phil Ruffwind at 2015-08-02T23:30:07+01:00 Fix record field alignment when name is too long Change <dl> to <ul> and use display:table rather than floats to layout the record fields. This avoids bug haskell/haddock#301 that occurs whenever the field name gets too long. Slight aesthetic change: the entire cell of the field's source code is now shaded gray rather than just the area where text exists. Fixes haskell/haddock#301. Closes haskell/haddock#421 - - - - - 7abb3402 by Łukasz Hanuszczak at 2015-08-02T23:32:14+01:00 Add some utility definitions for generating line anchors. - - - - - e0b1d79b by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Make hyperlinked source renderer generate line anchors. - - - - - 24dd4c9f by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Re-accept test cases after adding line anchors for each of them. - - - - - 0372cfcb by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Override source line flags when source hyperlinker is enabled. - - - - - a81bcd07 by Mateusz Kowalczyk at 2015-08-02T23:58:25+01:00 Update tests to follow HTML changes - - - - - d2d7426f by Łukasz Hanuszczak at 2015-08-06T20:54:59+02:00 Fix quote syntax for promoted types. - - - - - 668cf029 by Łukasz Hanuszczak at 2015-08-06T21:12:00+02:00 Apply promoted type quoting to type-level consing. - - - - - 89f8e7c6 by Łukasz Hanuszczak at 2015-08-06T21:17:10+02:00 Extend advanced types test case with other examples. - - - - - 86494bca by Łukasz Hanuszczak at 2015-08-06T21:22:06+02:00 Rename advanced types test case and accept new output. - - - - - dbb7c7c0 by Adam Sandberg Eriksson at 2015-08-09T23:01:05+02:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 2a7704fa by Ben Gamari at 2015-08-10T13:18:05+02:00 Merge pull request haskell/haddock#433 from adamse/split-hsbang HsBang is split into HsSrcBang and HsImplBang - - - - - 891954bc by Thomas Miedema at 2015-08-15T14:51:18+02:00 Follow changes in GHC build system - - - - - b55d32ab by Mateusz Kowalczyk at 2015-08-21T18:06:09+01:00 Make Travis use 7.10.2 - - - - - 97348b51 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Move SYB utilities to standalone module. - - - - - 748ec081 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement `everywhere` transformation in SYB module. - - - - - 011cc543 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement generic transformation constructor. - - - - - b9510db2 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Create simple utility module for type specialization. - - - - - 43229fa6 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Make type of type specialization function more general. - - - - - fd844e90 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Add basic HTML test case for checking instance specialization. - - - - - 6ea0ad04 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Make HTML class instance printer take optional signature argument. - - - - - 65aa41b6 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Refactor instance head type to record instead of a meaningless tuple. - - - - - 3fc3bede by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add expandable method section for each class instance declaration. - - - - - 99ceb107 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Move dummy post-family instances for `DocName` to `Types` module. - - - - - e98f4708 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create convenience functions for type specialization module. - - - - - b947552f by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Hook type specialization logic with HTML pretty-printer. - - - - - dcaa8030 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create stub functions for sugaring specialized types. - - - - - fa84bc65 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement list syntax sugaring logic for specialized types. - - - - - e8b05b07 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement tuple syntax sugaring logic for specialized types. - - - - - 68a2e5bc by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Get rid of code duplication in type specialization module. - - - - - 4721c336 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create scaffolding of a framework for renaming specialized types. - - - - - 271b488d by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in missing cases in specialized type renaming function. - - - - - bfa5f2a4 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Remove code duplication in specialized type renamer. - - - - - ea6bd0e8 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Change state of the type renaming monad. - - - - - 77c5496e by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement simple mechanism for generating new type names. - - - - - 91bfb48b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in stub behaviour with actual environment renaming. - - - - - d244517b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix logic behind binder type renaming. - - - - - f3c5e360 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add SYB-like utility function for performing stateful queries. - - - - - eb3f9154 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create function for retrieving free variables from given type. - - - - - a94561d3 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix compilation error caused by incorrect type signature. - - - - - 8bb707cf by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Move `SetName` class definition to types module. - - - - - 5800b13b by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Hook type renamer with instance method HTML pretty-printer. - - - - - 6a480164 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some test cases for type renamer. - - - - - 839842f7 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized signatures refer to original signature declaration. - - - - - 4880f7c9 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized methods be nicely formatted again. - - - - - ab5a6a2e by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Attach source locations to the specialized class methods. - - - - - 43f8a559 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Extend instances test case to also test multi-name type signatures. - - - - - 59bc751c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix tab-based indentation in instances test case. - - - - - c2126815 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Improve placement of instance methods expander button. - - - - - 0a32e287 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add new data type declaration to instance specialization test case. - - - - - 5281af1f by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make type renamer first try single-letter names as alternatives. - - - - - 7d509475 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix type renamer bug with incorrect names being generated. - - - - - 0f35bf7c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some documentation and refactor type specialization module. - - - - - da1d0803 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix another bug where type renamer was generating incorrect names. - - - - - cd39b5cb by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Refactor type renamer to rebinding and pure renaming phases. - - - - - 850251f4 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix unwitting compilation bug. - - - - - e5e9fc01 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Integrate instance specification type into class instance definition. - - - - - 825b0ea0 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer neccessary instance specification type. - - - - - cdba44eb by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix declaration converter to use more appropriate mode for methods. - - - - - bc45c309 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug with types not being specialized at all. - - - - - 5d8e5d89 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug where instance expander was opening wrong section. - - - - - 6001ee41 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix another type renamer bug where not all names were rebound. - - - - - 5f58ce2a by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix yet another renamer bug where some names were not unique. - - - - - 8265e521 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split instance subsection layout method to top-level declarations. - - - - - e5e66298 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Rearrange layout of instance methods in generated documentation. - - - - - a50b4eea by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer used layout method. - - - - - 2ff36ec2 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach section title to the instance methods block. - - - - - 7ac15300 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Add basic tests for associated types in instances test case. - - - - - db0ea2f9 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach associated types information to instance header. - - - - - 71cad4d5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details section contain associated types information. - - - - - deee2809 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Improve look of rendered associated families in instance details. - - - - - 839d13a5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Introduce alternative type for family declarations. - - - - - d397f03f by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details record use new type for family declarations. - - - - - 2b23fe97 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split printer of type family header to separate functions. - - - - - c3498cdc by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Implement HTML renderer for pseudo-family declarations. - - - - - c12bbb04 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Apply type specializer to associated type family declarations. - - - - - 2fd69ff2 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Create helper method for specializing type signatures. - - - - - 475826e7 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Refactor specializer module to be independent from XHTML backend. - - - - - f00b431c by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add some documentation for instance head specializer. - - - - - a9fef2dc by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix bug with missing space in documentation for associated types. - - - - - 50e29056 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with incorrect instance details sections being expanded. - - - - - e6dfdd03 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by adding instance details section. - - - - - 75565b2a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make section identifier of instance details more GHC-independent. - - - - - add0c23e by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Re-accept tests after applying deterministic section identifiers. - - - - - 878f2534 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make identifier generation also architecture-independent. - - - - - 48be69f8 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with instance expander hijacking type hyperlink click. - - - - - 47830c1f by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Get rid of dreadful hashing function for generating identifiers. - - - - - 956cd5af by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Move `InstOrigin` type declaration to more appropriate module. - - - - - bf672ed3 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by changes related to instance expander. - - - - - 8f2a949a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add examples with type operators to the instances test case. - - - - - 64600a84 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add basic support for sugaring infix type operators. - - - - - 747d71b8 by Łukasz Hanuszczak at 2015-08-21T18:22:34+01:00 Add support for sugaring built-in function syntax. - - - - - d4696ffb by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Remove default methods from Hoogle class output. - - - - - bf0e09d7 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add fixity declarations in Hoogle backend output. - - - - - 90e91a51 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix bug with incorrect fixities being generated in Hoogle backend. - - - - - 48f11d35 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve class type family declarations output in Hoogle backend. - - - - - 661e8e8f by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add missing default family equations in Hoogle output. - - - - - e2d64103 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve formatting of class details output in Hoogle backend. - - - - - 490fc377 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix weird-looking Hoogle output for familyless classes. - - - - - ea115b64 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create script file for new HTML test runner. - - - - - 609913d3 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Set default behaviour if no arguments given. - - - - - dc115f67 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for providing optional arguments for test runner. - - - - - d93ec867 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve output of test runner error messages. - - - - - 0be9fe12 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for executing Haddock process in test runner. - - - - - 4e4d00d9 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add GHC path to test runner configuration. - - - - - d67a2086 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make GHC path a test runner command-line argument. - - - - - c810079a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Extend test runner configuration with Haddock arguments. - - - - - fee18845 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor test runner and create stub functions. - - - - - ff7c161f by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make test runner actually run Haddock executable. - - - - - 391f73e6 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with test runner not producing any output files. - - - - - 81a74e2d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Setup skeleton of framework for running tests. - - - - - f8a79ec4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with modules not being found in global search mode. - - - - - 7e700b4d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make Haddock standard output redirection be more configurable. - - - - - 53b4c17a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Incorporate old, ugly functions for comparing output files. - - - - - 8277c8aa by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor architecture of test runner output checking functions. - - - - - 587bb414 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement actual diffing mechanism. - - - - - 9ed2b5e4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve code style to match popular guidelines. - - - - - 14bffaf8 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make it possible to choose alternative diff tool. - - - - - 5cdfb005 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create stub methods for processing test output as XML documents. - - - - - 7ef8e12e by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement link-stripping logic as simple SYB transformation. - - - - - 8a1fcd4f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Incorporate link stripping to output diffing mechanism. - - - - - 37dba2bc by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement footer-stripping logic. - - - - - 9cd52120 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Add missing dependencies in Cabal configuration file. - - - - - e0f83c6e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix issue with output being printed in incorrect order. - - - - - 0a94fbb0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to run tests without generating diff. - - - - - 76a58c6f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor HTML test suite boilerplate to external package. - - - - - af41e6b0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utilities for storing directory configuration. - - - - - d8f0698f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move IO-dependent config of HTML test suite to test package. - - - - - 17369fa0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Enable all compiler warnings in Haddock test package configuration. - - - - - 9d03b47a by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move Haddock runner of HTML test suite to Haddock test package. - - - - - 4b3483c5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 03754194 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience wrappers to simplify in test entry points. - - - - - 27476ab7 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adjust module visibility and items they export. - - - - - c40002ba by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Remove no longer useful test option. - - - - - 55ab2541 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Change extension of test files used for diffing. - - - - - 136bf4e4 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor and simplify XHTML helper module of test package. - - - - - 69f7e3df by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix typo in link stripper of HTML test suite runner. - - - - - 0c3c1c6b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience script for running specific HTML tests. - - - - - 489e1b05 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement utility functions for conditional link stripping. - - - - - 0f985dc3 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt `hypsrc-test` module to work with new testing framework. - - - - - 927406f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement output accepting mechanism in test package. - - - - - 8545715e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utility function for recursive obtaining directory contents. - - - - - cb70381f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 019599b5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix path handling in test runner. - - - - - 399b985b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to specify ignored files for test output. - - - - - 41b3d93d by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt HTML test runner to use new ignoring functionality. - - - - - e2091c8b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix bug with not all test output files being checked. - - - - - b22134f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Specify ignored files for hyperlinker source test runner. - - - - - 3301dfa1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Copy test runner script for hyperlinked source case. - - - - - d39a6dfa by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner invoking Haddock in incorrect mode. - - - - - f32c8ff3 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix path handling in test module loader. - - - - - 10f94ee9 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make test runner ignore test packages with no modules. - - - - - 5dc4239c by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create test runner entry points for LaTeX test suite. - - - - - 58d1f7cf by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with unnecessary checking old test output. - - - - - c7ce76e1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Re-implement test acceptance functionality. - - - - - 13bbabe8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix warning about no longer needed definition. - - - - - 958a99b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Adapt Cabal configuration to execute LaTeX suite with new runner. - - - - - 550ff663 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Setup test suite for Hoogle backend. - - - - - 3aa969c4 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make Hoogle backend create output directory if needed. - - - - - eb085b02 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Add appropriate .gitignore entry and configure Hoogle test suite. - - - - - a50bf915 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner failing when run on multiple test packages. - - - - - bf5368b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create simple test cases for Hoogle backend. - - - - - 6121ba4b by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create helper function for conversion between XML and XHTML. - - - - - cb516061 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Refactor existing code to use XHTML printer instead of XML one. - - - - - e2de8c82 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Improve portability of test runner scripts. - - - - - 9563e774 by Łukasz Hanuszczak at 2015-08-22T23:43:16+02:00 Remove redundant import statement. - - - - - 55353df1 by Łukasz Hanuszczak at 2015-08-24T23:09:20+02:00 Fix bug with accepting to non-existing directory. - - - - - 00a334ca by Łukasz Hanuszczak at 2015-08-24T23:09:47+02:00 Accept output for Hoogle and LaTeX backends. - - - - - 29191d8b by Łukasz Hanuszczak at 2015-08-24T23:14:18+02:00 Get rid of obsolete testing utilities. - - - - - bbb25db3 by Łukasz Hanuszczak at 2015-08-24T23:18:50+02:00 Update sandbox setup guide to work with Haddock test package. - - - - - cfd45248 by Łukasz Hanuszczak at 2015-08-24T23:51:30+02:00 Make Travis aware of Haddock test package. - - - - - 74185b7a by Łukasz Hanuszczak at 2015-08-25T17:41:59+02:00 Fix test suite failure when used with Stack. - - - - - 18769697 by Łukasz Hanuszczak at 2015-08-25T18:02:09+02:00 Add sample Stack setup to the hacking guide. - - - - - 22715eeb by Łukasz Hanuszczak at 2015-08-25T18:04:47+02:00 Fix Markdown formatting of README file. - - - - - b49ec386 by Łukasz Hanuszczak at 2015-08-25T18:13:36+02:00 Setup Haddock executable path in Travis configuration. - - - - - 5d29eb03 by Eric Seidel at 2015-08-30T09:55:58-07:00 account for changes to ipClass - - - - - f111740a by Ben Gamari at 2015-09-02T13:20:37+02:00 Merge pull request haskell/haddock#443 from bgamari/ghc-head account for changes to ipClass - - - - - a2654bf6 by Jan Stolarek at 2015-09-03T01:32:57+02:00 Follow changes from haskell/haddock#6018 - - - - - 2678bafe by Richard Eisenberg at 2015-09-21T12:00:47-04:00 React to refactoring CoAxiom branch lists. - - - - - ebc56e24 by Edward Z. Yang at 2015-09-21T11:53:46-07:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4a8c4198 by Tamar Christina at 2015-09-27T13:59:08+02:00 Create Process: removed PhaseFailed - - - - - 7e99b790 by Oleg Grenrus at 2015-09-27T20:52:10+03:00 Generate docs for orphan instances - - - - - 32e932e2 by Oleg Grenrus at 2015-09-28T07:21:11+03:00 Have source links for orphan instances - - - - - c2eb9f4f by Oleg Grenrus at 2015-09-28T07:24:58+03:00 Print orphan instances header only if required - - - - - ff96f978 by Oleg Grenrus at 2015-09-28T07:40:54+03:00 Add orphan instances link to contents box - - - - - d72490a6 by Oleg Grenrus at 2015-09-28T16:37:44+03:00 Fix orphan instance collapsing - - - - - 25d3dfe5 by Ben Gamari at 2015-10-03T12:38:09+02:00 Merge pull request haskell/haddock#448 from Mistuke/fix-silent-death-of-runInteractive Remove PhaseFailed - - - - - 1e45e43b by Edward Z. Yang at 2015-10-11T13:10:10-07:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b1370ac1 by Adam Gundry at 2015-10-16T16:26:42+01:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 60bef421 by Simon Peyton Jones at 2015-10-26T12:52:36+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 4c1898ca by Simon Peyton Jones at 2015-10-27T14:24:56+00:00 Track change to PatSyn.patSynSig - - - - - 25108e85 by Simon Peyton Jones at 2015-10-27T17:34:18+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - 693643ac by Ben Gamari at 2015-10-28T14:33:06+01:00 Account for Typeable changes The treatment of type families changed. - - - - - cd7c2221 by Simon Peyton Jones at 2015-10-30T13:03:51+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - 712032cb by Herbert Valerio Riedel at 2015-10-31T11:01:45+01:00 Relax upper bound on `base` to allow base-4.9 - - - - - 0bfa0475 by Simon Peyton Jones at 2015-10-31T19:08:13+00:00 More adaption to wildcard-refactor - - - - - 0a3c0cb7 by Simon Peyton Jones at 2015-10-31T22:14:43+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - c4fd4ec9 by Alan Zimmerman at 2015-11-01T11:16:34+01:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 42cdd882 by Matthew Pickering at 2015-11-06T20:02:16+00:00 Change for IEThingWith - - - - - f368b7be by Ben Gamari at 2015-11-11T11:35:51+01:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - e32965b8 by Simon Peyton Jones at 2015-11-13T12:18:17+00:00 Merge with origin/head - - - - - ebcf795a by Edward Z. Yang at 2015-11-13T21:56:27-08:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4e23989f by Simon Peyton Jones at 2015-11-18T11:32:54+00:00 Wibbles to Haddock - - - - - 2289cd4a by Simon Peyton Jones at 2015-11-20T23:12:49+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor - - - - - 695975a6 by Alan Zimmerman at 2015-11-21T21:16:12+02:00 Update to match GHC wip/T11019 - - - - - bbba21e7 by Simon Peyton Jones at 2015-11-23T13:54:31+00:00 merge with origin/ghc-head - - - - - 3d664258 by Simon Peyton Jones at 2015-11-23T17:17:18+00:00 Wibble - - - - - e64cf586 by Herbert Valerio Riedel at 2015-12-05T00:29:55+01:00 Canonicalise Monad instances - - - - - a2de15a7 by Alan Zimmerman at 2015-12-05T17:33:52+02:00 Matching changes for haskell/haddock#11028 - - - - - cc29a3e4 by Alan Zimmerman at 2015-12-05T19:45:33+02:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 95dd15d1 by Richard Eisenberg at 2015-12-11T17:33:39-06:00 Update for type=kinds - - - - - cb5fd9ed by Herbert Valerio Riedel at 2015-12-14T15:07:30+00:00 Bump versions for ghc-7.11 - - - - - 4f286d96 by Simon Peyton Jones at 2015-12-14T15:10:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 13ea2733 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 098df8b8 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track changes in HsSyn for quasi-quotes - - - - - 716a64de by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track change in API of TyCon - - - - - 77a66bca by Adam Gundry at 2015-12-14T15:10:58+00:00 Track API changes to support empty closed type familes - - - - - f2808305 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track the new location of setRdrNameSpace - - - - - ba8b08a4 by Alan Zimmerman at 2015-12-14T15:10:59+00:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - a4ded87e by Thomas Winant at 2015-12-14T15:14:05+00:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 25c78107 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: print correct strictness marks - - - - - 6cbc41c4 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: changes in HsBang type - - - - - ad46821a by Alan Zimmerman at 2015-12-14T15:14:06+00:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - abc0ae5b by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 3308d06c by Thomas Miedema at 2015-12-14T15:14:07+00:00 Follow changes in GHC build system - - - - - 6c763deb by Eric Seidel at 2015-12-14T15:14:07+00:00 account for changes to ipClass - - - - - ae5b4eac by Jan Stolarek at 2015-12-14T15:17:00+00:00 Follow changes from haskell/haddock#6018 - - - - - ffbc40e0 by Richard Eisenberg at 2015-12-14T15:17:02+00:00 React to refactoring CoAxiom branch lists. - - - - - d1f531e9 by Edward Z. Yang at 2015-12-14T15:17:02+00:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 79f73754 by Tamar Christina at 2015-12-14T15:17:02+00:00 Create Process: removed PhaseFailed - - - - - 3d37bebb by Edward Z. Yang at 2015-12-14T15:20:46+00:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 5f8a9e44 by Adam Gundry at 2015-12-14T15:20:48+00:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 79dda70f by Simon Peyton Jones at 2015-12-14T15:26:02+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 959930fb by Simon Peyton Jones at 2015-12-14T15:37:50+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - e18a8df5 by Simon Peyton Jones at 2015-12-14T15:37:52+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - aa35ab52 by Simon Peyton Jones at 2015-12-14T15:40:18+00:00 More adaption to wildcard-refactor - - - - - 8ceef94b by Simon Peyton Jones at 2015-12-14T15:46:04+00:00 Track change to PatSyn.patSynSig - - - - - cd81e83d by Ben Gamari at 2015-12-14T15:46:06+00:00 Account for Typeable changes The treatment of type families changed. - - - - - 63c9117c by Herbert Valerio Riedel at 2015-12-14T15:46:34+00:00 Relax upper bound on `base` to allow base-4.9 - - - - - a484c613 by Alan Zimmerman at 2015-12-14T15:47:46+00:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 2c26fa51 by Matthew Pickering at 2015-12-14T15:47:47+00:00 Change for IEThingWith - - - - - 593baa0f by Ben Gamari at 2015-12-14T15:49:21+00:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - b6b5ca78 by Edward Z. Yang at 2015-12-14T15:49:54+00:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b5b0e072 by Alan Zimmerman at 2015-12-14T15:54:20+00:00 Update to match GHC wip/T11019 - - - - - 14ddeb68 by Simon Peyton Jones at 2015-12-14T15:54:22+00:00 Wibble - - - - - 10a90ad8 by Herbert Valerio Riedel at 2015-12-14T15:54:22+00:00 Canonicalise Monad instances - - - - - ed68ac50 by Alan Zimmerman at 2015-12-14T15:55:48+00:00 Matching changes for haskell/haddock#11028 - - - - - 3f7e5a2d by Alan Zimmerman at 2015-12-14T15:55:49+00:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 6543a73f by Richard Eisenberg at 2015-12-14T15:59:55+00:00 Update for type=kinds - - - - - 193a5c48 by Matthew Pickering at 2015-12-14T18:17:00+00:00 Changes to compile with 8.0 - - - - - add669ec by Matthew Pickering at 2015-12-14T18:47:12+00:00 Warnings - - - - - 223f3fb4 by Ben Gamari at 2015-12-15T23:45:05+01:00 Update for D1200 - - - - - d058388f by Ben Gamari at 2015-12-16T05:40:17-05:00 Types: Add Outputable[Bndr] DocName instances - - - - - 62ecd7fb by Ben Gamari at 2015-12-16T09:23:09-05:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ddbc187a by Ben Gamari at 2015-12-16T17:54:55+01:00 Update for D1200 - - - - - cec83b52 by Ben Gamari at 2015-12-16T17:54:55+01:00 Types: Add Outputable[Bndr] DocName instances - - - - - d12ecc98 by Ben Gamari at 2015-12-16T17:54:55+01:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ada1616f by Ben Gamari at 2015-12-16T17:54:58+01:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a4f0383d by Ben Gamari at 2015-12-16T23:32:38+01:00 Fix Hyperlinker GHC.con_names is now GHC.getConNames - - - - - a10e6849 by Ben Gamari at 2015-12-20T00:54:11+01:00 Merge remote-tracking branch 'mrhania/testing-framework-improvements' into ghc-head - - - - - f078b4fd by Ben Gamari at 2015-12-20T00:59:51+01:00 test: Compatibility with Cabal 1.23 - - - - - 88a511a9 by Ben Gamari at 2015-12-20T01:14:35+01:00 Merge remote-tracking branch 'phadej/orphans' into ghc-head - - - - - 4e250f36 by Ben Gamari at 2015-12-20T01:14:52+01:00 Add html-test for orphan instances output - - - - - 87fffbad by Alan Zimmerman at 2015-12-20T09:50:42+02:00 Update for GHC trac#11258 Adding locations to RdrName in FieldOcc and AmbiguousFieldOcc - - - - - 6b7e51c9 by idontgetoutmuch at 2015-12-20T21:01:47+00:00 Merge pull request haskell/haddock#1 from haskell/ghc-head Ghc head - - - - - 229c1fb5 by Dominic Steinitz at 2015-12-21T07:19:16+00:00 Handle inline math with mathjax. - - - - - 57902d66 by Dominic Steinitz at 2015-12-21T08:07:11+00:00 Fix the documentation for haddock itself. Change notation and add support for inline math. Allow newlines in display math. Add a command line option for the mathjax url (you might want to use a locally installed version). Rebase tests because of extra url and version change. Respond to (some of the) comments. Fix warnings in InterfaceFile.hs - - - - - 0e69f236 by Herbert Valerio Riedel at 2015-12-21T18:30:43+01:00 Fix-up left-over assumptions of GHC 7.12 into GHC 8.0 - - - - - c67f8444 by Simon Peyton Jones at 2015-12-22T16:26:56+00:00 Follow removal of NamedWildCard from HsType - - - - - da40327a by Ben Gamari at 2015-12-23T14:15:28+01:00 html-test/Operators: Clear up ambiguous types For reasons that aren't entirely clear a class with ambiguous types was accepted by GHC <8.0. I've added a functional dependency to clear up this ambiguity. - - - - - 541b7fa4 by Ben Gamari at 2015-12-23T14:18:51+01:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 0febc947 by Ben Gamari at 2015-12-24T00:30:20+01:00 hoogle-test/AssocTypes: Allow AmbiguousTypes GHC 8.0 complains otherwise - - - - - 25810841 by Ben Gamari at 2015-12-24T00:33:18+01:00 OrphanInstances: Accept test output - - - - - 841987f3 by Ben Gamari at 2015-12-25T11:03:11+01:00 Merge remote-tracking branch 'idontgetoutmuch/ghc-head' into ghc-head - - - - - 358391f0 by Ben Gamari at 2015-12-26T10:44:50+01:00 Add missing import - - - - - a8896885 by Ben Gamari at 2015-12-26T10:45:27+01:00 travis: Use Travis containers - - - - - 85e82134 by Herbert Valerio Riedel at 2015-12-30T17:25:39+01:00 tweak version bounds for GHC-8.1 - - - - - 672a5f75 by randen at 2016-01-01T23:45:25-08:00 The Haddock part for fully gcc-like response files " driver/Main.hs * Moved the response file handling into ResponseFile.hs, updating import section as appropriate. * driver/ResponseFile.hs * New file. In anticipation that maybe some day this could be provided by another library, and to make it possible to unit test, this functionality is pulled out of the Main.hs module, and expanded to support the style/format of response files which gcc uses. * The specification for the format of response files which gcc generates and consumes, seems to be best derived from the gcc code itself (libiberty/argv.c), so that is what has been done here. * This is intended to fix haskell/haddock#379 * driver-test/Main.hs * New file for testing code in the driver source tree * driver-test/ResponseFileSpec.hs * Tests, adapted/adopted from the same gcc code where the escaping/unescaping is from, in the hspec style of unit tests * haddock.cabal * Add the driver-test test-suite. Introduces a new library dependency (upon hspec) for the haddock driver target in the haddock.cabal file, but practically, this should not be a problem as the haddock-api tests already depend on hspec. - - - - - 498781df by Ben Gamari at 2016-01-06T13:41:04+01:00 Version bumps and changelog - - - - - 8451e46a by Ben Gamari at 2016-01-06T13:47:17+01:00 Merge remote-tracking branch 'randen/bug468' - - - - - fb2d9181 by Ben Gamari at 2016-01-06T08:14:42-05:00 Add ResponseFile to OtherModules - - - - - 2cb2d2e3 by Ben Gamari at 2016-01-06T14:35:00+01:00 Merge branch 'master' into ghc-head - - - - - 913477d4 by Eric Seidel at 2016-01-11T14:57:57-08:00 deal with un-wiring of IP class - - - - - c557a4b3 by Alan Zimmerman at 2016-01-15T11:14:35+02:00 Update to match wip/T11430 in GHC - - - - - 3e135093 by Alan Zimmerman at 2016-01-16T18:21:59+01:00 Update to match wip/T11430 in GHC - - - - - c48ef2f9 by Ben Gamari at 2016-01-18T09:50:06+01:00 Merge remote-tracking branch 'gridaphobe/ghc-head' into ghc-head - - - - - 9138a1b0 by Eric Seidel at 2016-01-18T12:50:15+01:00 deal with un-wiring of IP class (cherry picked from commit 17388b0f0029d969d79353be7737eb01c7b8dc5f) - - - - - b48c172e by Joachim Breitner at 2016-01-19T00:11:38+01:00 Make sure --mathjax affects all written HTML files This fixes haskell/haddock#475. - - - - - af61fe63 by Ryan Scott at 2016-02-07T23:25:57+01:00 Render */# instead of TYPE 'Lifted/TYPE 'Unlifted (fixes haskell/haddock#473) - - - - - b6458693 by Ben Gamari at 2016-02-07T23:29:27+01:00 Merge pull request haskell/haddock#477 from haskell/issue-475 Make sure --mathjax affects all written HTML files - - - - - adcc0071 by Ben Gamari at 2016-02-07T23:34:52+01:00 Merge branch 'master' into ghc-head - - - - - d0404e61 by Ben Gamari at 2016-02-08T12:46:49+01:00 doc: Switch to Sphinx - - - - - acb153b3 by Ben Gamari at 2016-02-08T12:46:56+01:00 Document --use-unicode flag - - - - - c20bdf1d by Ben Gamari at 2016-02-08T13:41:24+01:00 Fix GHC and haddock-library dependency bounds - - - - - 8d946801 by Ben Gamari at 2016-02-08T14:54:56+01:00 testsuite: Rework handling of output sanitization Previously un-cleaned artifacts were kept as reference output, making it difficult to tell what has changed and causing spurious changes in the version control history. Here we rework this, cleaning the output during acceptance. To accomplish this it was necessary to move to strict I/O to ensure the reference handle was closed before accept attempts to open the reference file. - - - - - c465705d by Ben Gamari at 2016-02-08T15:36:05+01:00 test: Compare on dump For reasons I don't understand the Xml representations differ despite their textual representations being identical. - - - - - 1ec0227a by Ben Gamari at 2016-02-08T15:36:05+01:00 html-test: Accept test output - - - - - eefbd63a by Ben Gamari at 2016-02-08T15:36:08+01:00 hypsrc-test: Accept test output And fix impredicative Polymorphism testcase. - - - - - d1df4372 by Ben Gamari at 2016-02-08T15:40:44+01:00 Merge branch 'fix-up-testsuite' - - - - - 206a3859 by Phil Ruffwind at 2016-02-08T17:51:21+01:00 Move the permalinks to "#" on the right side Since pull request haskell/haddock#407, the identifiers have been permalinked to themselves, but this makes it difficult to copy the identifier by double-clicking. To work around this usability problem, the permalinks are now placed on the far right adjacent to "Source", indicated by "#". Also, 'namedAnchor' now uses 'id' instead of 'name' (which is obsolete). - - - - - 6c89fa03 by Phil Ruffwind at 2016-02-08T17:54:44+01:00 Update tests for previous commit - - - - - effaa832 by Ben Gamari at 2016-02-08T17:56:17+01:00 Merge branch 'anchors-redux' - - - - - 9a2bec90 by Ben Gamari at 2016-02-08T17:58:40+01:00 Use -fprint-unicode-syntax when --use-unicode is enabled This allows GHC to render `*` as its Unicode representation, among other things. - - - - - 28ecac5b by Ben Gamari at 2016-02-11T18:53:03+01:00 Merge pull request haskell/haddock#480 from bgamari/sphinx Move documentation to ReStructuredText - - - - - 222e5920 by Ryan Scott at 2016-02-11T15:42:42-05:00 Collapse type/data family instances by default - - - - - a80ac03b by Ryan Scott at 2016-02-11T20:17:09-05:00 Ensure expanded family instances render correctly - - - - - 7f985231 by Ben Gamari at 2016-02-12T10:04:22+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - d4eda086 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Various cleanups - - - - - 79bee48d by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show kind signatures for type family variables Addresses GHC haskell/haddock#11588. - - - - - b2981d98 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show 'where ...' after closed type family Seems like we should ideally show the actual equations as well but that seems like it would be a fair amount of work - - - - - cfc0e621 by Ben Gamari at 2016-02-18T22:48:12+01:00 Merge pull request haskell/haddock#483 from bgamari/T11588 Fix GHC haskell/haddock#11588 This fixes GHC haskell/haddock#11588: * Show where ... after closed type families * Show kind signatures on type family type variables - - - - - 256e8a0d by Ben Gamari at 2016-02-18T23:15:39+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 32402036 by Richard Eisenberg at 2016-02-24T13:21:44-05:00 Follow-on changes to support RuntimeRep - - - - - 2b1c572d by Matthew Pickering at 2016-03-04T21:04:02+00:00 Remove unused functions - - - - - eb906f50 by Richard Eisenberg at 2016-03-13T21:17:20+01:00 Follow-on changes to support RuntimeRep (cherry picked from commit ab954263a793d8ced734459d6194a5d89214b66c) - - - - - 8c34ef34 by Richard Eisenberg at 2016-03-14T23:47:23-04:00 Changes due to fix for GHC#11648. - - - - - 0e022014 by Richard Eisenberg at 2016-03-15T14:06:45+01:00 Changes due to fix for GHC#11648. (cherry picked from commit bb994de1ab0c76d1aaf1e39c54158db2526d31f1) - - - - - ed3f78ab by Rik Steenkamp at 2016-04-02T22:20:36+01:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 - - - - - d3210042 by Rik Steenkamp at 2016-04-04T15:43:32+02:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 (cherry picked from commit 3ddcbd6b8e6884bd95028381176eb33bee6896fb) - - - - - 236eec90 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 692ee7e0 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. - - - - - 79619f57 by Ben Gamari at 2016-04-10T23:46:22+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. (cherry picked from commit c6d6a18d85e5e2d9bb5904e6919e8a8d7e31c4c5) - - - - - 3358ccb4 by Ben Gamari at 2016-04-10T23:47:27+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 264949b1 by Ben Gamari at 2016-04-16T17:50:23+02:00 Merge pull request haskell/haddock#482 from RyanGlScott/ghc-head Collapse type/data family instances by default - - - - - 478c483a by Ben Gamari at 2016-04-16T17:51:09+02:00 Merge pull request haskell/haddock#489 from mpickering/unused-functions Remove some unused functions - - - - - c94e55f0 by Ryan Scott at 2016-04-16T17:57:54+02:00 Collapse type/data family instances by default (cherry picked from commit 2da130a8db8f995c119b544fad807533236cf088) - - - - - 31e633d3 by Ryan Scott at 2016-04-16T17:58:06+02:00 Ensure expanded family instances render correctly (cherry picked from commit 1338b5d7c32939de6bbc31af0049477e4f847103) - - - - - 03e4d197 by Matthew Pickering at 2016-04-16T17:58:21+02:00 Remove unused functions (cherry picked from commit b89d1c2456bdb2d4208d94ded56155f7088a37d0) - - - - - ed4116f6 by Ben Gamari at 2016-04-20T10:46:57+02:00 ghc: Install files for needed --hyperlinked-source - - - - - 0be999c4 by Ben Gamari at 2016-04-20T11:37:54+02:00 ghc: Install files for needed --hyperlinked-source (cherry picked from commit 5c82c9fc2d21ddaae4a2470f1c375426968f19c6) - - - - - 4d17544c by Simon Peyton Jones at 2016-04-20T12:42:28+01:00 Track change to HsGroup This relates to a big GHC patch for Trac haskell/haddock#11348 - - - - - 1700a50d by Ben Gamari at 2016-05-01T13:19:27+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. - - - - - 0b7c8125 by Ben Gamari at 2016-05-01T13:21:43+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. (cherry picked from commit 609018dd09c4ffe27f9248b2d8b50f6196cd42b9) - - - - - af115ce0 by Ryan Scott at 2016-05-04T22:15:50-04:00 Render Haddocks for derived instances Currently, one can document top-level instance declarations, but derived instances (both those in `deriving` clauses and standalone `deriving` instances) do not enjoy the same privilege. This makes the necessary changes to the Haddock API to enable rendering Haddock comments for derived instances. This is part of a fix for Trac haskell/haddock#11768. - - - - - 76fa1edc by Ben Gamari at 2016-05-10T18:13:25+02:00 haddock-test: A bit of refactoring for debuggability - - - - - 7d4c4b20 by Ben Gamari at 2016-05-10T18:13:25+02:00 Create: Mark a comment as TODO - - - - - 2a6d0c90 by Ben Gamari at 2016-05-10T18:13:25+02:00 html-test: Update reference output - - - - - bd60913d by Ben Gamari at 2016-05-10T18:13:25+02:00 hypsrc-test: Fix reference file path in cabal file It appears the haddock insists on prefixing --hyperlinked-sourcer output with directory which the source appeared in. - - - - - c1548057 by Ben Gamari at 2016-05-10T18:22:12+02:00 doc: Update extra-source-files in Cabal file - - - - - 41d5bae3 by Ben Gamari at 2016-05-10T18:29:21+02:00 Bump versions - - - - - ca75b779 by Ben Gamari at 2016-05-11T16:03:44+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 4e3cfd62 by Ben Gamari at 2016-05-11T16:06:45+02:00 Merge remote-tracking branch 'RyanGlScott/ghc-head' into ghc-head - - - - - a2379970 by Ben Gamari at 2016-05-11T23:15:11+02:00 doc: Add clean targets - - - - - f275212e by Ben Gamari at 2016-05-11T23:15:14+02:00 doc: Add html as an all-target for ghc Otherwise the html documentation won't be installed for binary-dist. - - - - - 388fc0af by Ben Gamari at 2016-05-12T09:49:12+02:00 Update CHANGES - - - - - bad81ad5 by Ben Gamari at 2016-05-12T09:49:38+02:00 Version bump - - - - - c01688a7 by Ben Gamari at 2016-05-12T10:04:58+02:00 Revert "Version bump" This bump was a bit premature. This reverts commit 7b238d9c5be9b07aa2d10df323b5c7b8d1634dc8. - - - - - 7ed05724 by Ben Gamari at 2016-05-12T10:05:33+02:00 doc: Fix GHC clean rule Apparently GHC's build system doesn't permit wildcards in clean paths. - - - - - 5d9611f4 by Ben Gamari at 2016-05-12T17:43:50+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 653566b2 by Ben Gamari at 2016-05-14T09:57:31+02:00 Version bump to 2.17.2 - - - - - b355c439 by Ben Gamari at 2016-05-14T09:57:51+02:00 doc: Use `$(MAKE)` instead of `make` This is necessary to ensure we use gmake. - - - - - 8a18537d by Ben Gamari at 2016-05-14T10:15:45+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - b3290ef1 by Sebastian Meric de Bellefon at 2016-05-14T11:29:47-04:00 Fix haskell/haddock#303. Hide footer when printing The "Produced by Haddock" footer was overlapping the page's body when printing. This patch hides the footer with a css media rule. - - - - - b4a76f89 by Sebastian Meric de Bellefon at 2016-05-15T02:12:46-04:00 Fix haskell/haddock#280. Parsing of module header The initial newlines were counted as indentation spaces, thus disturbing the parsing of next lines - - - - - ba797c9e by Ben Gamari at 2016-05-16T14:53:46+02:00 doc: Vendorize alabaster Sphinx theme Alabaster is now the default sphinx theme and is a significant improvement over the previous default that it's worthproviding it when unavailable (e.g. Sphinx <1.3). - - - - - c9283e44 by Ben Gamari at 2016-05-16T14:55:17+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 1c9ea198 by Sebastian Méric de Bellefon at 2016-05-16T12:30:40-04:00 Merge pull request haskell/haddock#502 from Helkafen/master Fix haskell/haddock#303. Hide footer when printing - - - - - 33631016 by Ben Gamari at 2016-05-16T19:56:11+02:00 Revert "doc: Vendorize alabaster Sphinx theme" This ended up causes far too many issues to be worthwhile. We'll just have to live with inconsistent haddock documentation. This reverts commit cec21957001143794e71bcd9420283df18e7de40. - - - - - 93317d26 by Ben Gamari at 2016-05-16T19:56:11+02:00 cabal: Fix README path - - - - - c8695b22 by Ben Gamari at 2016-05-16T19:58:51+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 0b50eaaa by Ben Gamari at 2016-05-16T21:02:08+02:00 doc: Use whichever theme sphinx deems appropriate - - - - - 857c1c9c by Ben Gamari at 2016-05-16T21:07:08+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 15fc5637 by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Remove redundant imports - - - - - 132ddc6a by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Better debug output For tracking down haskell/haddock#505 - - - - - 2252a149 by Ben Gamari at 2016-05-22T12:43:59+02:00 Don't consider default class ops when looking for decls When we are looking for an operation within a class we don't care about `default`-type declarations. This was the cause of haskell/haddock#505. - - - - - 4886b2ec by Oleg Grenrus at 2016-05-24T16:19:48+03:00 UnfelpfulSpan line number omitted Kind of resolves https://github.com/haskell/haddock/issues/508 - - - - - a4befd36 by Oleg Grenrus at 2016-05-24T16:53:35+03:00 Change Hyperlinked lexer to know about DataKinds ticks - - - - - f45cb52e by David Feuer at 2016-05-24T18:48:53-04:00 Make parser state a newtype Previously, it was `data` wrapping a `Maybe`, which seems a bit silly. Obviously, this can be changed back if anyone wants to add more fields some day. - - - - - 05013dd7 by Sebastian Meric de Bellefon at 2016-05-24T22:03:55-04:00 remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) Frames are a bit broken, ignored by Hackage, and considered obsolete in general. This patch disables frames generation. The mini_*.html files are still used in the synopsis. - - - - - b8163a88 by Ben Gamari at 2016-05-25T14:44:15+02:00 Merge pull request haskell/haddock#507 from bgamari/T505 Fix haskell/haddock#505 - - - - - ea1b30c6 by Sebastian Meric de Bellefon at 2016-05-25T14:17:00-04:00 Update CHANGES - - - - - eddfc258 by Sebastian Méric de Bellefon at 2016-05-25T15:17:40-04:00 Merge pull request haskell/haddock#514 from Helkafen/frames remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) - - - - - 0e506818 by Alex Biehl at 2016-05-26T12:43:09+02:00 Remove misplaced haddock comment - - - - - a07d28c0 by Ben Gamari at 2016-05-27T11:34:59+02:00 Merge pull request haskell/haddock#515 from alexbiehl/master Remove misplaced haddock comment - - - - - 9001d267 by Ben Gamari at 2016-05-27T11:35:46+02:00 Merge pull request haskell/haddock#513 from treeowl/newtype-since Make parser state a newtype - - - - - 74e1a018 by Sebastian Méric de Bellefon at 2016-05-28T17:28:15-04:00 Merge pull request haskell/haddock#504 from Helkafen/issue-280 Fix haskell/haddock#280. Parsing of module header - - - - - 37557f4f by Alan Zimmerman at 2016-05-29T23:36:50+02:00 Matching changes for haskell/haddock#12105 - - - - - 7d09e5d6 by Sebastian Meric de Bellefon at 2016-06-03T18:07:48-04:00 Version bumps (2.17.3, 1.4.2) - - - - - 85b4bc15 by Sebastian Méric de Bellefon at 2016-06-06T18:35:13-04:00 Merge pull request haskell/haddock#521 from Helkafen/master Version bumps (2.17.3, 1.4.2) - - - - - e95f0dee by Sebastian Meric de Bellefon at 2016-06-06T19:11:35-04:00 publish haddock-test library - - - - - 4de40586 by Sebastian Méric de Bellefon at 2016-06-06T20:26:30-04:00 Merge pull request haskell/haddock#512 from phadej/oleg-fixes Fixes for haskell/haddock#508 and haskell/haddock#510 - - - - - ddfd0789 by Dominic Steinitz at 2016-06-09T09:27:28+01:00 Documentation for LaTeX markup. - - - - - 697a503a by Dominic Steinitz at 2016-06-09T09:33:59+01:00 Fix spelling mistake. - - - - - 246f6fff by Dominic Steinitz at 2016-06-09T09:37:15+01:00 Camel case MathJax. - - - - - 4684bd23 by Dominic Steinitz at 2016-06-09T09:44:53+01:00 Fix math typo and add link. - - - - - f20c037c by Simon Peyton Jones at 2016-06-13T18:26:03+01:00 Follow changes to LHsSigWcType - - - - - 0c58996d by Simon Peyton Jones at 2016-06-15T12:56:01+01:00 Follow GHC re-adding FunTy - - - - - 401b5ca7 by Sebastian Méric de Bellefon at 2016-06-15T12:16:47-04:00 Merge pull request haskell/haddock#525 from idontgetoutmuch/master Documentation for LaTeX markup. - - - - - 92d263b7 by Sebastian Méric de Bellefon at 2016-06-15T12:17:29-04:00 Merge pull request haskell/haddock#522 from Helkafen/master publish haddock-test library - - - - - 0953a2ca by Sebastian Meric de Bellefon at 2016-06-16T00:46:46-04:00 Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 65453e14 by Ben Gamari at 2016-06-16T11:16:32+02:00 ocean: Ensure that synopsis fully covers other content Previously MathJax content was being rendered on top of the synopsis due to ambiguous z-ordering. Here we explicitly give the synopsis block a higher z-index to ensure it is rendered on top. Fixes haskell/haddock#531. - - - - - 68e411a1 by Sebastian Méric de Bellefon at 2016-06-16T23:34:39-04:00 Merge pull request haskell/haddock#534 from bgamari/T531 ocean: Ensure that synopsis fully covers other content - - - - - fad6491b by Sebastian Méric de Bellefon at 2016-06-18T23:57:20-04:00 Merge pull request haskell/haddock#533 from Helkafen/master Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 6108e21b by Sebastian Meric de Bellefon at 2016-06-22T23:08:28-04:00 do not create empty src directory Fix haskell/haddock#536. - - - - - 1ef23823 by Sebastian Méric de Bellefon at 2016-06-24T00:04:48-04:00 Merge pull request haskell/haddock#537 from Helkafen/master do not create empty src directory - - - - - 966baa96 by Omari Norman at 2016-06-29T21:59:34-04:00 Add $ as a special character If this character is not escaped, documentation built with Haddock 2.17.2 will fail. This was not an issue with 2.16 series, which causes builds to fail and there is nothing in the docs or error message giving a clue about why builds that used to succeed now don't. - - - - - 324adb60 by Ben Gamari at 2016-07-01T12:18:51+02:00 GhcUtils: Changes for multi-pattern signatures - - - - - d7571675 by Ömer Sinan Ağacan at 2016-07-21T13:30:47+02:00 Add support for unboxed sums - - - - - 29d0907b by Simon Marlow at 2016-07-22T13:55:48+01:00 Disable NFData instances for GHC types when GHC >= 8.2 - - - - - 702d95f3 by Simon Marlow at 2016-08-02T15:57:30+02:00 Disable NFData instances for GHC types when GHC >= 8.0.2 (cherry picked from commit a3309e797c42dae9bccdeb17ce52fcababbaff8a) - - - - - f4fa79c3 by Ben Gamari at 2016-08-07T13:51:18+02:00 ghc.mk: Don't attempt to install html/frames.html The frames business has been removed. - - - - - 9cd63daf by Ben Gamari at 2016-08-07T13:51:40+02:00 Haddock.Types: More precise version guard This allows haddock to be built with GHC 8.0.2 pre-releases. - - - - - f3d7e03f by Mateusz Kowalczyk at 2016-08-29T20:47:45+01:00 Merge pull request haskell/haddock#538 from massysett/master Add $ as a special character - - - - - 16dbf7fd by Bartosz Nitka at 2016-09-20T19:44:04+01:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 - - - - - 7c31c1ff by Bartosz Nitka at 2016-09-27T17:32:22-04:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 (cherry picked from commit 073d899a8f94ddec698f617a38d3420160a7fd0b) - - - - - 33a90dce by Ryan Scott at 2016-09-30T20:53:41-04:00 Haddock changes for T10598 See https://ghc.haskell.org/trac/ghc/ticket/10598 - - - - - 1f32f7cb by Ben Gamari at 2016-10-13T20:01:26-04:00 Update for refactoring of NameCache - - - - - 1678ff2e by Ben Gamari at 2016-11-15T17:42:48-05:00 Bump upper bound on base - - - - - 9262a7c5 by Alan Zimmerman at 2016-12-07T21:14:28+02:00 Match changes in GHC wip/T3384 branch - - - - - ac0eaf1a by Ben Gamari at 2016-12-09T09:48:41-05:00 haddock-api: Don't use stdcall calling convention on 64-bit Windows See GHC haskell/haddock#12890. - - - - - 04afe4f7 by Alan Zimmerman at 2016-12-12T20:07:21+02:00 Matching changes for GHC wip/T12942 - - - - - e1d1701d by Ben Gamari at 2016-12-13T16:50:41-05:00 Bump base upper bound - - - - - 3d3eacd1 by Alan Zimmerman at 2017-01-10T16:59:38+02:00 HsIParamTy now has a Located name - - - - - 7dbceefd by Kyrill Briantsev at 2017-01-12T13:23:50+03:00 Prevent GHC API from doing optimization passes. - - - - - d48d1e33 by Richard Eisenberg at 2017-01-19T08:41:41-05:00 Upstream changes re levity polymorphism - - - - - 40c25ed6 by Alan Zimmerman at 2017-01-26T15:16:18+02:00 Changes to match haskell/haddock#13163 in GHC - - - - - 504f586d by Ben Gamari at 2017-02-02T17:19:37-05:00 Kill remaining static flags - - - - - 49147ea0 by Justus Adam at 2017-03-02T15:33:34+01:00 Adding MDoc to exports of Documentation.Haddock - - - - - 1cfba9b4 by Justus Adam at 2017-03-09T11:41:44+01:00 Also exposing toInstalledIface - - - - - 53f0c0dd by Ben Gamari at 2017-03-09T13:10:08-05:00 Bump for GHC 8.3 - - - - - c7902d2e by Ben Gamari at 2017-03-09T23:46:02-05:00 Bump for GHC 8.2 - - - - - 4f3a74f8 by Ben Gamari at 2017-03-10T10:21:55-05:00 Merge branch 'ghc-head' - - - - - e273b72f by Richard Eisenberg at 2017-03-14T13:34:04-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - 6ec3d436 by Richard Eisenberg at 2017-03-14T15:15:52-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - eee3cda1 by Ben Gamari at 2017-03-15T15:19:59-04:00 Adapt to EnumSet - - - - - 017cf58e by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 736d6773 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 475f84a0 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 13240b53 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - cd16d529 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 3bea97ae by Edward Z. Yang at 2017-03-15T22:50:46-07:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b2b051ce by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 0f082795 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 20ef63c9 by Edward Z. Yang at 2017-03-22T13:48:12-07:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 45692dcb by Edward Z. Yang at 2017-03-22T14:11:25-07:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4eae8caf by Ben Gamari at 2017-03-23T09:25:33-04:00 Merge commit '240bc38b94ed2d0af27333b23392d03eeb615e82' into HEAD - - - - - 0bbe03f5 by Ben Gamari at 2017-03-23T09:27:28-04:00 haddock-api: Bump bound on GHC - - - - - 65f3ac9d by Alex Biehl at 2017-03-23T17:36:11+01:00 Merge pull request haskell/haddock#581 from JustusAdam/master Adding more exports to Documentation.Haddock - - - - - 37d49a47 by Alex Biehl at 2017-03-23T17:39:14+01:00 Merge pull request haskell/haddock#568 from awson/ghc-head Prevent GHC API from doing optimization passes. - - - - - 1ed047e4 by Brian Huffman at 2017-03-23T17:45:58+01:00 Print any user-supplied kind signatures on type parameters. This applies to type parameters on data, newtype, type, and class declarations, and also to forall-bound type vars in type signatures. - - - - - 1b78ca5c by Brian Huffman at 2017-03-23T17:45:58+01:00 Update test suite to expect kind annotations on type parameters. - - - - - a856b162 by Alex Biehl at 2017-03-23T17:49:32+01:00 Include travis build indication badge - - - - - 8e2e2c56 by Ben Gamari at 2017-03-23T17:20:08-04:00 haddock-api: Bump bound on GHC - - - - - 4d2d9995 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 26d6c150b31bc4580ab17cfd07b6e7f9afe10737) - - - - - a650e20f by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 930cfbe58e2e87f5a4d431d89a3c204934e6e858) - - - - - caa282c2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 2067a2d0afa9cef381d26fb7140b67c62f433fc0) - - - - - 49684884 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 0671abfe7e8ceae2269467a30b77ed9d9656e2cc) - - - - - 4dcfeb1a by Edward Z. Yang at 2017-03-23T17:20:08-04:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 3d77b373dd5807d5d956719dd7c849a11534fa6a) - - - - - 74dd19d2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 94610e9b446324f4231fa6ad4c6ac51e4eba8c0e) - - - - - a9b19a23 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 6cc832dfb1de6088a4abcaae62b25a7e944d55c3) - - - - - d3631064 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit bf3c4d72a0fda38561376eac7eda216158783267) - - - - - ef2148fc by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 07b88c5d4e79b87a319fbb08f8ea01dbb41063c1) - - - - - 2f29518b by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 4eb765ca4205c79539d60b7afa9b7e261a4a49fe) - - - - - 37de047d by Phil Ruffwind at 2017-04-03T11:57:14+02:00 Update MathJax URL MathJax is shutting down their CDN: https://www.mathjax.org/cdn-shutting-down/ They recommend migrating to cdnjs. - - - - - e9d24ba8 by David C. Turner at 2017-04-03T14:58:01+02:00 Add highlight for :target to ocean.css - - - - - 4819a202 by Alex Biehl at 2017-04-11T19:36:48+02:00 Allow base-4.10 for haddock-test - - - - - 44cec69c by Alex Biehl at 2017-04-11T19:39:22+02:00 cabal.project for haddock-api, haddock-library and haddock-test - - - - - 935d0f6a by Alex Biehl at 2017-04-11T19:46:29+02:00 Move dist scripts to scripts/ - - - - - 128e150c by Alex Biehl at 2017-04-11T20:34:46+02:00 Add haddock to cabal.project - - - - - cc8e08ea by Alex Biehl at 2017-04-11T20:35:08+02:00 Read files for hyperlinker eagerly This also exposes Documentation.Haddock.Utf8 - - - - - 152dda78 by Alex Biehl at 2017-04-11T20:37:06+02:00 Explicit import list ofr Control.DeepSeq in Haddock.Interface.Create - - - - - 501b33c4 by Kyrill Briantsev at 2017-04-11T21:01:42+02:00 Prevent GHC API from doing optimization passes. - - - - - c9f3f5ff by Alexander Biehl at 2017-04-12T16:36:53+02:00 Add @alexbiehl as maintaner - - - - - 76f214cc by Alex Biehl at 2017-04-13T07:27:18+02:00 Disable doctest with ghc-8.3 Currently doctest doesn't support ghc-head - - - - - 46b4f5fc by Edward Z. Yang at 2017-04-22T20:38:26-07:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f0555235 by Alex Biehl at 2017-04-25T10:08:48+02:00 Travis: Use ghc-8.2.1 on master - - - - - 966ea348 by Alex Biehl at 2017-04-25T10:32:01+02:00 Travis: Verbose cabal output cf. https://travis-ci.org/haskell/haddock/jobs/225512194#L377 - - - - - 36972bcd by Alex Biehl at 2017-04-25T10:40:43+02:00 Use travis_retry for cabal invocations - - - - - b3a09d2c by Alex Biehl at 2017-04-25T17:02:20+02:00 Use new MathJax URL in html-test 18ed871afb82560d5433b2f53e31b4db9353a74e switched to a new MathJax URL but didn't update the tests. - - - - - ae331e5f by Alexander Biehl at 2017-04-25T17:02:20+02:00 Expand signatures for class declarations - - - - - e573c65a by Alexander Biehl at 2017-04-25T17:02:20+02:00 Hoogle: Correctly print classes with associated data types - - - - - 3fc6be9b by Edward Z. Yang at 2017-04-25T17:02:20+02:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit a0c4790e15a2d3fab8d830eee8fcd639fe6d39c9) - - - - - 6725c060 by Herbert Valerio Riedel at 2017-04-25T17:02:20+02:00 `html-test --accept` deltas to reference samples - - - - - 7d444d61 by Alex Biehl at 2017-04-26T07:13:50+02:00 Remove anything related to obsolete frames mode - - - - - b888972c by Alex Biehl at 2017-04-26T07:49:10+02:00 Cherry-picked remaining commits from haddock-2.17.4-release (#603) * Release haddock/haddock-api 2.17.4 and haddock-library 1.4.3 * Set version bounds for haddock-library NB: This allows GHC 8.2.1's base * Set version bounds for haddock & haddock-api The version bounds support GHC 8.2 * Merge (temporary) v2.17.3 branch into v2.17 This allows us to delete the v2.17.3 branch * Fixup changelog * Pin down haddock-api to a single version as otherwise `haddock`'s package version has no proper meaning * fix source-repo spec for haddock-api - - - - - 4161099b by Alex Biehl at 2017-04-26T11:11:20+02:00 Update changelog to reflect news in HEAD - - - - - eed72cb8 by Alex Biehl at 2017-04-26T11:11:20+02:00 Markdownify changelog - - - - - 5815cea1 by Alex Biehl at 2017-04-26T11:32:33+02:00 Bump to 2.18.0 (#605) - - - - - a551d558 by Alex Biehl at 2017-04-29T22:00:25+02:00 Update attoparsec-0.12.1.1 to attoparsec-0.13.1.0 - - - - - ea164a8d by Sergey Vinokurov at 2017-04-29T22:42:36+02:00 Improve error message - - - - - 2e10122f by Alex Biehl at 2017-04-30T10:07:46+02:00 Correctly remember collapsed sections (#608) Now the "collapsed" cookie stores which sections have changed state instead of which are collapsed. - - - - - f9b24d99 by Alex Biehl at 2017-05-01T17:40:36+02:00 Lazily decode docMap and argMap (#610) These are only used in case of a doc reexport so most of the time decoding these is wasted work. - - - - - 2372af62 by Alex Biehl at 2017-05-01T21:59:23+02:00 Fix Binary instance for InstalledInterface (#611) (#610) introduced lazy decoding for docs from InstalledInterface but forgot to remove the original calls to get and put_ - - - - - 6c633c13 by Nathan Collins at 2017-05-11T11:47:55+02:00 Improve documenation of Haddock markup (#614) * Improve documentation of Haddock markup. - document that Haddock supports inferring types top-level functions with without type signatures, but also explain why using this feature is discouraged. Looks like this feature has been around since version 2.0.0.0 in 2008! - rework the "Module description" section: - move the general discussion of field formatting to the section intro and add examples illustrating the prose for multiline fields. - mention that newlines are preserved in some multiline fields, but not in others (I also noticed that commas in the `Copyright` field are not preserved; I'll look into this bug later). - add a subsection for the module description fields documentation, and put the field keywords in code formatting (double back ticks) instead of double quotes, to be consistent with the typesetting of keywords in other parts of the documentation. - mention that "Named chunks" are not supported in the long-form "Module description" documentation. - fix formatting of keywords in the "Module attributes" section. Perhaps these errors were left over from an automatic translation to ReST from some other format as part of the transition to using Sphinx for Haddock documentation? Also, add a missing reference here; it just said "See ?"! - update footnote about special treatment for re-exporting partially imported modules not being implemented. In my tests it's not implemented at all -- I tried re-exporting both `import B hiding (f)` and `import B (a, b)` style partial imports, and in both cases got the same result as with full imports `import B`: I only get a module reference. * Rework the `Controlling the documentation structure` section. My main goal was to better explain how to use Haddock without an export list, since that's my most common use case, but I hope I improved the section overall: - remove the incomplete `Omitting the export list` section and fold it into the other sections. In particular, summarize the differences between using and not using an export list -- i.e. control over what and in what order is documented -- in the section lead. - add "realistic" examples that use the structure markup, both with and without an export list. I wanted a realistic example here to capture how it can be useful to explain the relationship between a group of functions in a section, in addition to documenting their individual APIs. - make it clear that you can associate documentation chunks with documentation sections when you aren't using an export list, and that doing it in the most obvious way -- i.e. with `-- |`, as you can in the export list -- doesn't work without an export list. It took me a while to figure this out the first time, since the docs didn't explain it at all before. - add a "no export list" example to the section header section. - add more cross references. * Add examples of gotchas for markup in `@...@`. I'm not sure this will help anyone, since I think most people first learn about `@...@` by reading other people's Haddocks, but I've documented the mistakes which I've made and then gotten confused by. * Use consistent Capitalization of Titles. Some titles were in usual title caps, and others only had the first word capitalized. I chose making them all use title caps because that seems to make the cross references look better. - - - - - d4734f45 by Ben Gamari at 2017-05-12T20:36:08+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 93883f37 by Alex Biehl at 2017-05-12T21:02:33+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 5b8f179c by Alex Biehl at 2017-05-13T12:48:10+02:00 Consequently use inClass and notInClass in haddock-library (#617) These allow attoparsec to do some clever lookup optimization - - - - - 77984b82 by Doug Wilson at 2017-05-27T17:37:38+02:00 Don't enable compilation for template haskell (#624) This is no longer necessary after ghc commit 53c78be0aab76a3107c4dacbb1d177afacdd37fa - - - - - 5a3de2b4 by Doug Wilson at 2017-05-27T19:54:53+02:00 Improve Syb code (#621) Specialize.hs and Ast.hs are modified to have their Syb code not recurse into Name or Id in HsSyn types. Specialize.hs is refactored to have fewer calls to Syb functions. Syb.hs has some foldl calls replaced with foldl' calls. There is still a lot of performance on the floor of Ast.hs. The RenamedSource is traversed many times, and lookupBySpan is very inefficient. everywhereBut and lookupBySpan dominate the runtime whenever --hyperlinked-source is passed. - - - - - 3d35a949 by Alex Biehl at 2017-05-30T19:01:37+02:00 Clear fixme comment (#625) - - - - - 2a44bd0c by Alex Biehl at 2017-05-30T19:02:12+02:00 Make haddock-library and haddock-api warning free (#626) - - - - - bd1a0e42 by Alex Biehl at 2017-06-01T10:40:33+02:00 Include `driver-test/*.hs` sdist (#630) This lead to haskell/haddock#629. - - - - - 184a3ab6 by Doug Wilson at 2017-06-03T12:02:08+02:00 Disable pattern match warnings (#628) This disables the pattern match checker which can be very expensive in some cases. The disabled warnings include: * Opt_WarnIncompletePatterns * Opt_WarnIncompleteUniPatterns * Opt_WarnIncompletePatternsRecUpd * Opt_WarnOverlappingPatterns - - - - - 0cf68004 by Alex Biehl at 2017-06-03T20:37:28+02:00 Allow user defined signatures for pattern synonyms (#631) - - - - - 7f51a58a by Alex Biehl at 2017-06-04T11:56:38+02:00 Use NameSet for isExported check (#632) - - - - - d8f044a9 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Match new AST as per GHC wip/new-tree-one-param See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow - - - - - da1254e3 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Rename extension index tags - - - - - 538c7514 by Christiaan Baaij at 2017-06-09T08:26:43+02:00 Haddock support for bundled pattern synonyms (#627) * Haddock support for bundled pattern synonyms * Add fixities to bundled pattern synonyms * Add bundled pattern synonyms to the synopsis * Store bundled pattern fixities in expItemFixities * Add test for bundled pattern synonyms * Stop threading fixities * Include bundled pattern synonyms for re-exported data types Sadly, fixity information isn't found for re-exported data types * Support for pattern synonyms * Modify tests after haskell/haddock#631 * Test some reexport variations * Also lookup bundled pattern synonyms from `InstalledInterface`s * Check isExported for bundled pattern synonyms * Pattern synonym is exported check * Always look for pattern synonyms in the current module Another overlooked cornercase * Account for types named twice in export lists Also introduce a fast function for nubbing on a `Name` and use it throughout the code base. * correct fixities for reexported pattern synonyms * Fuse concatMap and map * Remove obsolete import * Add pattern synonyms to visible exports * Fix test * Remove corner case - - - - - a050bffd by Doug Wilson at 2017-06-21T09:27:33+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#636) There is some performance improvement. GHC compiler: | version | bytes allocated | cpu_seconds --------------------------------- | before | 56057108648 | 41.0 | after | 51592019560 | 35.1 base: | version | bytes allocated | cpu_seconds --------------------------------- | before | 25174011784 | 14.6 | after | 23712637272 | 13.1 Cabal: | version | bytes allocated | cpu_seconds --------------------------------- | before | 18754966920 | 12.6 | after | 18198208864 | 11.6 - - - - - 5d06b871 by Doug Wilson at 2017-06-22T20:23:29+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#639) * Use new function getNameToInstancesIndex instead of tcRnGetInfo There is some significant performance improvement in the ghc testsuite. haddock.base: -23.3% haddock.Cabal: -16.7% haddock.compiler: -19.8% * Remove unused imports - - - - - b11bb73a by Alex Biehl at 2017-06-23T14:44:41+02:00 Lookup fixities for reexports without subordinates (#642) So we agree that reexported declarations which do not have subordinates (for example top-level functions) shouldn't have gotten fixities reexported according to the current logic. I wondered why for example Prelude.($) which is obviously reexported from GHC.Base has fixities attached (c.f. http://hackage.haskell.org/package/base-4.9.1.0/docs/Prelude.html#v:-36-). The reason is this: In mkMaps we lookup all the subordinates of top-level declarations, of course top-level functions don't have subordinates so for them the resulting list is empty. In haskell/haddock#644 I established the invariant that there won't be any empty lists in the subordinate map. Without the patch from haskell/haddock#642 top-level functions now started to fail reexporting their fixities. - - - - - d2a6dad6 by Alex Biehl at 2017-06-23T18:30:45+02:00 Don't include names with empty subordinates in maps (#644) These are unecessary anyway and just blow up interface size - - - - - 69c2aac4 by Alex Biehl at 2017-06-29T19:54:49+02:00 Make per-argument docs for class methods work again (#648) * Make per-argument docs for class methods work again * Test case - - - - - c9448d54 by Bartosz Nitka at 2017-07-02T12:12:01+02:00 Fix haddock: internal error: links: UnhelpfulSpan (#561) * Fix haddock: internal error: links: UnhelpfulSpan This fixes haskell/haddock#554 for me. I believe this is another fall out of `wildcard-refactor`, like haskell/haddock#549. * Comment to clarify why we take the methods name location - - - - - d4f29eb7 by Alex Biehl at 2017-07-03T19:43:04+02:00 Document record fields when DuplicateRecordFields is enabled (#649) - - - - - 9d6e3423 by Yuji Yamamoto at 2017-07-03T22:37:58+02:00 Fix test failures on Windows (#564) * Ignore .stack-work * Fix for windows: use nul instead of /dev/null * Fix for windows: canonicalize line separator * Also normalize osx line endings - - - - - 7d81e8b3 by Yuji Yamamoto at 2017-07-04T16:13:12+02:00 Avoid errors on non UTF-8 Windows (#566) * Avoid errors on non UTF-8 Windows Problem ==== haddock exits with errors like below: `(1)` ``` haddock: internal error: <stderr>: hPutChar: invalid argument (invalid character) ``` `(2)` ``` haddock: internal error: Language\Haskell\HsColour\Anchors.hs: hGetContents: invalid argument (invalid byte sequence) ``` `(1)` is caused by printing [the "bullet" character](http://www.fileformat.info/info/unicode/char/2022/index.htm) onto stderr. For example, this warning contains it: ``` Language\Haskell\HsColour\ANSI.hs:62:10: warning: [-Wmissing-methods] • No explicit implementation for ‘toEnum’ • In the instance declaration for ‘Enum Highlight’ ``` `(2)` is caused when the input file of `readFile` contains some Unicode characters. In the case above, '⇒' is the cause. Environment ---- OS: Windows 10 haddock: 2.17.3 GHC: 8.0.1 Solution ==== Add `hSetEncoding handle utf8` to avoid the errors. Note ==== - I found the detailed causes by these changes for debugging: - https://github.com/haskell/haddock/commit/8f29edb6b02691c1cf4c479f6c6f3f922b35a55b - https://github.com/haskell/haddock/commit/1dd23bf2065a1e1f2c14d0f4abd847c906b4ecb4 - These errors happen even after executing `chcp 65001` on the console. According to the debug code, `hGetEncoding stderr` returns `CP932` regardless of the console encoding. * Avoid 'internal error: <stderr>: hPutChar: invalid argument (invalid character)' non UTF-8 Windows Better solution for 59411754a6db41d17820733c076e6a72bcdbd82b's (1) - - - - - eded67d2 by Alex Biehl at 2017-07-07T19:17:15+02:00 Remove redudant import warning (#651) - - - - - 05114757 by Alex Biehl at 2017-07-08T00:33:12+02:00 Avoid missing home module warning (#652) * Avoid missing home module warning * Update haddock-library.cabal - - - - - e9cfc902 by Bryn Edwards at 2017-07-17T07:51:20+02:00 Fix haskell/haddock#249 (#655) - - - - - eb02792b by Herbert Valerio Riedel at 2017-07-20T09:09:15+02:00 Fix compilation of lib:haddock-library w/ GHC < 8 - - - - - 9200bfbc by Alex Biehl at 2017-07-20T09:20:38+02:00 Prepare 2.18.1 release (#657) - - - - - 46ddd22c by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Tweak haddock-api.cabal for pending release - - - - - 85e33d29 by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Avoid trivial use of LambdaCase otherwise we can't test w/ e.g. GHC 7.4.2 - - - - - 3afb4bfe by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Refactor .cabal to use sub-lib for vendored lib A practical benefit is that we can control the build-depends and also avoid some recompilation between library and test-suite. - - - - - e56a552e by Herbert Valerio Riedel at 2017-07-20T10:17:48+02:00 haddock-api: add changelog pointing to haddock's changelog This addresses https://github.com/haskell/haddock/issues/638#issuecomment-309283297 - - - - - 2222ff0d by Herbert Valerio Riedel at 2017-07-20T10:19:56+02:00 Drop obsolete/misleading `stability: experimental` This .cabal property has long been considered obsolete - - - - - 9b882905 by Alex Biehl at 2017-07-20T11:25:54+02:00 Beef up haddock description (#658) * Beef up haddock description * Handle empty lines - - - - - bb60e95c by Herbert Valerio Riedel at 2017-07-20T12:08:53+02:00 Import @aisamanra's Haddock cheatsheet from https://github.com/aisamanra/haddock-cheatsheet - - - - - 0761e456 by Herbert Valerio Riedel at 2017-07-20T12:12:55+02:00 Add cheatsheet to haddock.cabal - - - - - 2ece0f0f by Herbert Valerio Riedel at 2017-07-20T12:18:38+02:00 Mention new-build in README - - - - - 947b7865 by Herbert Valerio Riedel at 2017-07-20T12:32:16+02:00 Update README Also improves markup and removes/fixes redundant/obsolete parts [skip ci] - - - - - 785e09ad by Alex Biehl at 2017-07-27T07:28:57+02:00 Bump haddock to 2.18.2, haddock-library to 1.4.5 - - - - - e3ff1ca3 by Alex Biehl at 2017-07-31T20:15:32+02:00 Move `DocMarkup` from haddock-api to haddock-library (#659) * Move `DocMarkup` from haddock-api to haddock-library * Move more markup related functions * Markup module * CHANGELOG - - - - - cda7c20c by Alex Biehl at 2017-07-31T20:35:49+02:00 Fixup haddock - - - - - 583b6812 by Alex Biehl at 2017-07-31T21:20:45+02:00 Changelog for haddock-library - - - - - bac6a0eb by Alex Biehl at 2017-07-31T21:50:24+02:00 Prepare haddock-library-1.4.5 release - - - - - 58ce6877 by Moritz Drexl at 2017-08-05T16:44:40+02:00 Fix renaming after instance signature specializing (#660) * rework rename * Add regression test for Bug 613 * update tests * update changelog - - - - - b8137ec8 by Tim Baumann at 2017-08-06T11:33:38+02:00 Fix: Generate pattern signatures for constructors exported as patterns (#663) * Fix pretty-printing of pattern signatures Pattern synonyms can have up to two contexts, both having a different semantic meaning: The first holds the constraints required to perform the matching, the second contains the constraints provided by a successful pattern match. When the first context is empty but the second is not it is necessary to render the first, empty context. * Generate pattern synonym signatures for ctors exported as patterns This fixes haskell/haddock#653. * Simplify extractPatternSyn It is not necessary to generate the simplest type signature since it will be simplified when pretty-printed. * Add changelog entries for PR haskell/haddock#663 * Fix extractPatternSyn error message - - - - - d037086b by Alex Biehl at 2017-08-06T12:43:25+02:00 Bump haddock-library - - - - - 99d7e792 by Alex Biehl at 2017-08-06T12:44:07+02:00 Bump haddock-library in haddock-api - - - - - 94802a5b by Alex Biehl at 2017-08-06T13:18:02+02:00 Provide --show-interface option to dump interfaces (#645) * WIP: Provide --show-interface option to dump interfaces Like ghcs own --show-iface this flag dumps a binary interface file to stdout in a human (and machine) readable fashion. Currently it uses json as output format. * Fill all the jsonNull stubs * Rework Bifunctor instance of DocH, update changelog and documentation * replace changelog, bring DocMarkupH doc back * Update CHANGES.md * Update CHANGES.md * Move Control.Arrow up It would result in unused import if the Bifunctor instance is not generated. - - - - - c662e476 by Ryan Scott at 2017-08-14T21:00:21-04:00 Adapt to haskell/haddock#14060 - - - - - b891eb73 by Alex Biehl at 2017-08-16T08:24:48+02:00 Bifoldable and Bitraversable for DocH and MetaDoc - - - - - 021bb56c by Alex Biehl at 2017-08-16T09:06:40+02:00 Refactoring: Make doc renaming monadic This allows us to later throw warnings if can't find an identifier - - - - - 39fbf022 by Alex Biehl at 2017-08-19T20:35:27+02:00 Hyperlinker: Avoid linear lookup in enrichToken (#669) * Make Span strict in Position * Hyperlinker: Use a proper map to enrich tokens - - - - - e13baedd by Alex Biehl at 2017-08-21T20:05:42+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 27dd6e87 by Alex Biehl at 2017-08-21T22:06:35+02:00 Drop Avails from export list - - - - - 86b247e2 by Alex Biehl at 2017-08-22T08:44:22+02:00 Bump ghc version for haddock-api tests - - - - - d4607ca0 by Alex Biehl at 2017-08-22T08:45:17+02:00 Revert "Drop Avails from export list" This reverts commit a850ba86d88a4fb9c0bd175453a2580e544e3def. - - - - - c9c54c30 by Alex Biehl at 2017-08-22T09:26:01+02:00 IntefaceFile version - - - - - a85b7c02 by Ben Gamari at 2017-08-22T09:29:52-04:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 34e976f5 by Ben Gamari at 2017-08-22T17:40:06+02:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 577abf06 by Ryan Scott at 2017-08-23T14:47:29-04:00 Update for haskell/haddock#14131 - - - - - da68fc55 by Florian Eggenhofer at 2017-08-27T18:21:56+02:00 Generate an index for package content search (#662) Generate an index for package content search - - - - - 39e62302 by Alex Biehl at 2017-08-27T18:50:16+02:00 Content search for haddock html doc - - - - - 91fd6fb2 by Alex Biehl at 2017-08-28T18:39:58+02:00 Fix tests for content search - - - - - b4a3798a by Alex Biehl at 2017-08-28T18:44:08+02:00 Add search button to #page-menu - - - - - 25a7ca65 by Alex Biehl at 2017-08-28T18:47:43+02:00 Load javascript below the fold - - - - - 8d323c1a by Alex Biehl at 2017-08-28T18:49:22+02:00 Accept tests - - - - - c5dac557 by Alex Biehl at 2017-08-28T19:14:55+02:00 Content search css - - - - - 89a5af57 by Paolo Veronelli at 2017-08-29T07:42:13+02:00 Removed `nowrap` for interface method sigs (#674) with nowrap the interfaces method sigs would expand at libitum - - - - - a505f6f7 by Alex Biehl at 2017-08-29T08:05:33+02:00 Include subordinates in content index - - - - - 4bb698c4 by Alexander Biehl at 2017-08-29T11:40:19+02:00 QuickNav: Make docbase configurable - - - - - c783bf44 by Alexander Biehl at 2017-08-29T11:48:36+02:00 QuickNav: Also use baseUrl for doc-index.json request - - - - - 47017510 by Alex Biehl at 2017-08-29T17:56:47+02:00 Fix test fallout (again) - - - - - 924fc318 by Alex Biehl at 2017-08-30T09:24:56+02:00 Write meta.json when generating html output (#676) - - - - - 717dea52 by Alex Biehl at 2017-09-01T09:20:34+02:00 Use relative URL when no docBaseUrl given - - - - - e5d85f3b by Alex Biehl at 2017-09-01T09:35:19+02:00 Add missing js files to data-files (#677) - - - - - 95b9231a by Alex Biehl at 2017-09-01T11:01:36+02:00 Rename "Search" tab to "Quick Jump" - - - - - da0ead0b by Alex Biehl at 2017-09-01T13:03:49+02:00 Make trigger link configurable (#678) QuickNav: Configurable show/hide trigger - - - - - de7da594 by Ben Gamari at 2017-09-05T06:49:55-04:00 Account for "Remember the AvailInfo for each IE" As of GHC commit f609374a55bdcf3b79f3a299104767aae2ffbf21 GHC retains the AvailInfo associated with each IE. @alexbiehl has a patch making proper use of this change, but this is just to keep things building. - - - - - b05cd3b3 by Ben Gamari at 2017-09-14T07:55:07-04:00 Bump upper bound on base - - - - - 79db899e by Herbert Valerio Riedel at 2017-09-21T23:27:52+02:00 Make compatible with Prelude.<> export in GHC 8.4/base-4.11 - - - - - 3405dd52 by Tim Baumann at 2017-09-23T22:02:01+02:00 Add compile step that bundles and compresses JS files (#684) * Add compile step that bundles and compresses JS files Also, manage dependencies on third-party JS libraries using NPM. * Compile JS from TypeScript * Enable 'noImplicitAny' in TypeScript * QuickJump: use JSX syntax * Generate source maps from TypeScript for easier debugging * TypeScript: more accurate type * Separate quick jump css file from ocean theme - - - - - df0b5742 by Alex Biehl at 2017-09-29T21:15:40+02:00 Bump base for haddock-library and haddock-test - - - - - 62b12ea0 by Merijn Verstraaten at 2017-10-04T16:03:13+02:00 Inhibit output of coverage information for hidden modules. (#687) * Inhibit output of coverage information for hidden modules. * Add changelog entry. - - - - - 8daf8bc1 by Alexander Biehl at 2017-10-05T11:27:05+02:00 Don't use subMap in attachInstances - - - - - ad75114e by Alexander Biehl at 2017-10-05T11:27:58+02:00 Revert "Don't use subMap in attachInstances" This reverts commit 3adf5bcb1a6c5326ab33dc77b4aa229a91d91ce9. - - - - - 7d4aa02f by Alex Biehl at 2017-10-08T15:32:28+02:00 Precise Haddock: Use Avails for export resolution (#688) * Use Avails for export resolution * Support reexported modules * Factor out availExportItem * Use avails for fullModuleExports * Don't use subMap in attachInstances * lookupDocs without subMap * Completely remove subMap * Only calculate unqualified modules when explicit export list is given * Refactor * Refine comment * return * Fix * Refactoring * Split avail if declaration is not exported itself * Move avail splitting - - - - - b9b4faa8 by Alex Biehl at 2017-10-08T19:38:21+02:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 43325295 by Alex Biehl at 2017-10-08T20:18:46+02:00 Fix merge fallout - - - - - c6423cc0 by Alex Biehl at 2017-10-08T20:36:12+02:00 Copy QuickJump files over - - - - - 1db587c3 by Tim Baumann at 2017-10-09T18:33:09+02:00 Use <details> element for collapsibles (#690) * Remove unnecessary call to 'collapseSection' The call is unnecessary since there is no corresponding toggle for hiding the section of orphan instances. * Use <details> for collapsibles This makes them work even when JS is disabled. Closes haskell/haddock#560. - - - - - 1b54c64b by Tim Baumann at 2017-10-10T09:50:59+02:00 Quick Jump: Show error when loading 'doc-index.json' failed (#691) - - - - - 910f716d by Veronika Romashkina at 2017-10-24T07:36:20+02:00 Fix tiny typo in docs (#693) - - - - - b21de7e5 by Ryan Scott at 2017-10-24T13:07:15+02:00 Overhaul Haddock's rendering of kind signatures (#681) * Overhaul Haddock's rendering of kind signatures * Strip off kind signatures when specializing As an added bonus, this lets us remove an ugly hack specifically for `(->)`. Yay! * Update due to 0390e4a0f61e37bd1dcc24a36d499e92f2561b67 * @alexbiehl's suggestions * Import injectiveVarsOfBinder from GHC - - - - - 6704405c by Ryan Scott at 2017-10-28T07:10:27+02:00 Fix Haddock rendering of kind-indexed data family instances (#694) - - - - - 470f6b9c by Alex Biehl at 2017-10-30T08:45:51+01:00 Add QuickJump version to meta.json (#696) - - - - - b89eccdf by Alex Biehl at 2017-10-30T10:15:49+01:00 Put Quickjump behind --quickjump flag (#697) - - - - - 3095fb58 by Alex Biehl at 2017-10-30T19:09:06+01:00 Add build command to package.json - - - - - f223fda9 by Alex Biehl at 2017-10-30T19:10:39+01:00 Decrease threshold for fuzzy matching - - - - - 80245dda by Edward Z. Yang at 2017-10-31T20:35:05+01:00 Supported reexported-modules via --reexport flag. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 7e389742 by Alex Biehl at 2017-10-31T20:37:56+01:00 Correct missing title in changelog - - - - - 1a2a1c03 by Alex Biehl at 2017-10-31T20:59:07+01:00 Copy quickjump.css for nicer error messages - - - - - db234bb9 by Alex Biehl at 2017-10-31T21:31:18+01:00 Reexported modules: Report warnings if argument cannot be parsed or ... module cannot be found - - - - - eea8a205 by Carlo Hamalainen at 2017-10-31T21:43:14+01:00 More general type for nameCacheFromGhc. (#539) - - - - - 580eb42a by Alex Biehl at 2017-10-31T21:46:52+01:00 Remote tab - - - - - 0e599498 by Alex Biehl at 2017-10-31T21:48:55+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 7b8539bb by Alex Biehl at 2017-10-31T22:28:34+01:00 fullModuleContents traverses exports in declaration order - - - - - 0c91fbf2 by Alex Biehl at 2017-10-31T22:32:31+01:00 Remove excessive use of list comprehensions - - - - - f7356e02 by Alex Biehl at 2017-11-01T19:11:03+01:00 Make better use of AvailInfo - - - - - f3e512d5 by Alex Biehl at 2017-11-02T12:16:22+01:00 Always return documentation for exported subordinates ... event if they have no documentation (e.g. noDocForDecl) By using the information in the AvailInfo we don't need additional export checks. - - - - - 7cf58898 by Alan Zimmerman at 2017-11-07T08:28:03+02:00 Match changes for Trees that Grow in GHC - - - - - e5105a41 by Alan Zimmerman at 2017-11-08T17:21:58+02:00 Match Trees That Grow - - - - - 55178266 by Alan Zimmerman at 2017-11-11T22:20:31+02:00 Match Trees that Grow in GHC for HsExpr - - - - - 2082ab02 by Ryan Scott at 2017-11-14T15:27:03+01:00 Actually render infix type operators as infix (#703) * Actually render infix type operators as infix * Account for things like `(f :*: g) p`, too - - - - - c52ab7d0 by Alan Zimmerman at 2017-11-14T23:14:26+02:00 Clean up use of PlaceHolder, to match TTG - - - - - 81cc9851 by Moritz Angermann at 2017-11-20T07:52:49+01:00 Declare use of `Paths_haddock` module in other-modules (#705) This was detected by `-Wmissing-home-modules` - - - - - f9d27598 by Moritz Angermann at 2017-11-20T12:47:34+01:00 Drop Paths_haddock from ghc.mk (#707) With haskell/haddock#705 and haskell/haddock#706, the custom addition should not be necessary any more. # Conflicts: # ghc.mk - - - - - f34818dc by Moritz Angermann at 2017-11-20T12:47:59+01:00 Add autogen-modules (#706) > Packages using 'cabal-version: >= 1.25' and the autogenerated module Paths_* must include it also on the 'autogen-modules' field besides 'exposed-modules' and 'other-modules'. This specifies that the module does not come with the package and is generated on setup. Modules built with a custom Setup.hs script also go here to ensure that commands like sdist don't fail. # Conflicts: # haddock.cabal - - - - - bb43a0aa by Ben Gamari at 2017-11-21T15:50:12-05:00 Revert "Clean up use of PlaceHolder, to match TTG" This reverts commit 134a7bb054ea730b13c8629a76232d73e3ace049. - - - - - af9ebb2b by Ben Gamari at 2017-11-21T15:50:14-05:00 Revert "Match Trees that Grow in GHC for HsExpr" This reverts commit 9f054dc365379c66668de6719840918190ae6e44. - - - - - 5d35c3af by Ben Gamari at 2017-11-21T15:50:15-05:00 Revert "Match Trees That Grow" This reverts commit 73a26af844ac50b8bec39de11d64452a6286b00c. - - - - - 99a8e43b by Ben Gamari at 2017-11-21T16:36:06-05:00 Revert "Match changes for Trees that Grow in GHC" This reverts commit 01eeeb048acd2dd05ff6471ae148a97cf0720547. - - - - - c4d650c2 by Ben Gamari at 2017-12-04T15:06:07-05:00 Bump GHC version - - - - - 027b2274 by Ben Gamari at 2017-12-04T17:06:31-05:00 Bump GHC bound to 8.4.* - - - - - 58eaf755 by Alex Biehl at 2017-12-06T15:44:24+01:00 Update changelog - - - - - d68f5584 by Simon Peyton Jones at 2017-12-07T14:39:56+00:00 Track changes to follow Trac haskell/haddock#14529 This tracks the refactoring of HsDecl.ConDecl. - - - - - dc519d6b by Alec Theriault at 2018-01-06T08:20:43-08:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - 8285118c by Alec Theriault at 2018-01-13T12:12:37+01:00 Constructor and pattern synonym argument docs (#709) * Support Haddocks on constructor arguments This is in conjunction with https://phabricator.haskell.org/D4094. Adds support for rendering Haddock's on (non-record) constructor arguments, both for regular and GADT constructors. * Support haddocks on pattern synonym arguments It appears that GHC already parsed these - we just weren't using them. In the process of doing this, I tried to deduplicate some code around handling patterns. * Update the markup guide Add some information about the new support for commenting constructor arguments, and mention pattern synonyms and GADT-style constructors. * Overhaul LaTeX support for data/pattern decls This includes at least * fixing several bugs that resulted in invalid LaTeX * fixing GADT data declaration headers * overhaul handling of record fields * overhaul handling of GADT constructors * overhaul handling of bundled patterns * add support for constructor argument docs * Support GADT record constructors This means changes what existing HTML docs look like. As for LaTeX, looks like GADT records were never even supported. Now they are. * Clean up code/comments Made code/comments consistent between the LaTeX and XHTML backend when possible. * Update changelog * Patch post-rebase regressions * Another post-rebase change We want return values to be documentable on record GADT constructors. - - - - - ca4fabb4 by Alec Theriault at 2018-01-15T17:12:18-08:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 4c472fea by Ryan Scott at 2018-01-19T10:44:02+01:00 Fix haskell/haddock#732 (#733) - - - - - bff14dbd by Alex Biehl at 2018-01-19T15:33:30+01:00 extractDecl: Extract associated types correctly (#736) - - - - - a2a94a73 by Alex Biehl at 2018-01-19T15:34:40+01:00 extractDecl: Extract associated types correctly (#736) - - - - - 26df93dc by Alex Biehl at 2018-01-20T10:18:22+01:00 haddock-api: bump ghc to ^>= 8.4 - - - - - f65aeb1d by Alex Biehl at 2018-01-20T19:18:20+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - 0e721b97 by Alex Biehl at 2018-01-20T19:20:19+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - cb6234f6 by Ben Gamari at 2018-01-26T13:40:55-05:00 Merge remote-tracking branch 'harpocrates/fix/missing-orphan-instances' into ghc-head - - - - - 0fc28554 by Alec Theriault at 2018-02-01T14:58:18+01:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - b9123772 by Alec Theriault at 2018-02-01T14:58:18+01:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 0c12e274 by Ryan Scott at 2018-02-01T14:58:18+01:00 Fix haskell/haddock#548 by rendering datatype kinds more carefully (#702) - - - - - 8876d20b by Alec Theriault at 2018-02-01T14:58:18+01:00 Use the GHC lexer for the Hyperlinker backend (#714) * Start changing to use GHC lexer * better cpp * Change SrcSpan to RealSrcSpan * Remove error * Try to stop too many open files * wip * wip * Revert "wip" This reverts commit b605510a195f26315e3d8ca90e6d95a6737553e1. Conflicts: haddock-api/haddock-api.cabal haddock-api/src/Haddock/Interface.hs * Remove pointless 'caching' * Use dlist rather than lists when finding vars * Use a map rather than list * Delete bogus comment * Rebase followup Things now run using the GHC lexer. There are still - stray debug statements - unnecessary changes w.r.t. master * Cleaned up differences w.r.t. current Haddock HEAD Things are looking good. quasiquotes in particular look beautiful: the TH ones (with Haskell source inside) colour/link their contents too! Haven't yet begun to check for possible performance problems. * Support CPP and top-level pragmas The support for these is hackier - but no more hacky than the existing support. * Tests pass, CPP is better recognized The tests were in some cases altered: I consider the new output to be more correct than the old one.... * Fix shrinking of source without tabs in test * Replace 'Position'/'Span' with GHC counterparts Replaces 'Position' -> 'GHC.RealSrcLoc' and 'Span' -> 'GHC.RealSrcSpan'. * Nits * Forgot entry in .cabal * Update changelog - - - - - 95c6a771 by Alec Theriault at 2018-02-01T14:58:18+01:00 Clickable anchors for headings (#716) See haskell/haddock#579. This just adds an <a> tag around the heading, pointing to the heading itself. - - - - - 21463d28 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump: Matches on function names weight more than matches in ... module names. - - - - - 8023af39 by Alex Biehl at 2018-02-01T14:58:18+01:00 Treat escaped \] better in definition lists (#717) This fixes haskell/haddock#546. - - - - - e4866dc1 by Alex Biehl at 2018-02-01T14:58:18+01:00 Remove scanner, takeWhile1_ already takes care of escaping - - - - - 9bcaa49d by Alex Biehl at 2018-02-01T14:58:18+01:00 Take until line feed - - - - - 01d2af93 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Add simple framework for running parser fixtures (#668) * Add simple framework for running parser fixtures * Compatible with tree-diff-0.0.0.1 * Use parseParas to parse fixtures This allows to test all syntactic constructs available in haddock markup. - - - - - 31128417 by Alec Theriault at 2018-02-01T14:58:18+01:00 Patch flaky parser test (#720) * Patch flaky parser test This test was a great idea, but it doesn't port over too well to using the GHC lexer. GHC rewrites its input a bit - nothing surprising, but we need to guard against those cases for the test. * Change instance head * Change use site - - - - - 9704f214 by Herbert Valerio Riedel at 2018-02-01T14:58:18+01:00 Include secondary LICENSE file in source dist - - - - - 51f25074 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Grid Tables (#718) * Add table examples * Add table types and adopt simple parser Simple parser is done by Giovanni Cappellotto (@potomak) in https://github.com/haskell/haddock/pull/577 It seems to support single fine full tables, so far from full RST-grid tables, but it's good start. Table type support row- and colspans, but obviously parser is lacking. Still TODO: - Latex backend. Should we use multirow package https://ctan.org/pkg/multirow?lang=en? - Hoogle backend: ? * Implement grid-tables * Refactor table parser * Add two ill-examples * Update CHANGES.md * Basic documentation for tables * Fix documentation example - - - - - 670d6200 by Alex Biehl at 2018-02-01T14:58:18+01:00 Add grid table example to cheatsheet (pdf and svg need to be regenerated thought) - - - - - 4262dec9 by Alec Theriault at 2018-02-01T14:58:18+01:00 Fix infinite loop when specializing instance heads (#723) * Fix infinite loop when specializing instance heads The bug can only be triggered from TH, hence why it went un-noticed for so long. * Add test for haskell/haddock#679 and haskell/haddock#710 - - - - - 67ecd803 by Alec Theriault at 2018-02-01T14:58:18+01:00 Filter RTS arguments from 'ghc-options' arguments (#725) This fixes haskell/haddock#666. - - - - - 7db26992 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump Scrollable overlay - - - - - da9ff634 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Hyperlinker: Adjust parser to new PFailed constructor - - - - - 7b7cf8cb by Alexander Biehl at 2018-02-01T14:58:18+01:00 Specialize: Add missing IdP annotations - - - - - 78cd7231 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Convert: Correct pass type - - - - - a2d0f590 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Warning free compilation - - - - - cd861cf3 by Alexander Biehl at 2018-02-01T14:58:18+01:00 hadock-2.19.0 / haddock-api-2.19.0 / haddock-library-1.5.0 - - - - - c6651b72 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Adjust changelogs - - - - - 1e93da0b by Alexander Biehl at 2018-02-01T14:58:18+01:00 haddock-library: Info about breaking changes - - - - - f9b11db8 by Alec Theriault at 2018-02-02T12:36:02+01:00 Properly color pragma contents in hyperlinker The hyperlinker backend now classifies the content of pragmas as 'TkPragma'. That means that in something like '{-# INLINE foo #-}', 'foo' still gets classified as a pragma token. - - - - - c40b0043 by Alec Theriault at 2018-02-02T12:36:02+01:00 Support the new 'ITcolumn_prag' token - - - - - 4a2a4d39 by Alex Biehl at 2018-02-03T12:11:55+01:00 QuickJump: Mitigate encoding problems on Windows - - - - - bb34503a by Alex Biehl at 2018-02-04T18:39:31+01:00 Use withBinaryFile - - - - - 637605bf by Herbert Valerio Riedel at 2018-02-05T09:48:32+01:00 Try GHC 8.4.1 for Travis CI job - - - - - 7abb67e4 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 try harder to build w/ GHC 8.4.1 - - - - - 8255cc98 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 Add `SPDX-License-Identifier` as alised for "license" module header tokens C.f. SPDX 2.1 - Appendix V https://spdx.org/spdx-specification-21-web-version#h.twlc0ztnng3b The tag should appear on its own line in the source file, generally as part of a comment. SPDX-License-Identifier: <SPDX License Expression> Cherry-picked from haskell/haddock#743 - - - - - 267cd23d by Herbert Valerio Riedel at 2018-02-05T10:24:34+01:00 Make test-suite SMP compatible - - - - - 95d4bf40 by Alec Theriault at 2018-02-05T22:01:04+01:00 Hyperlink pattern synonyms and 'module' imports (#744) Links to pattern synonyms are now generated, as well as links from modules in import lists. Fixes haskell/haddock#731. - - - - - 67838dcd by Alec Theriault at 2018-02-06T08:23:36+01:00 Don't warn about missing '~' (#746) This manually filters out '~' from the list of things to warn about. It truly makes no sense to warn on this since '~' has nothing it could link to - it is magical. This fixes haskell/haddock#532. - - - - - ab6c3f9f by Alec Theriault at 2018-02-06T08:24:47+01:00 Don't barf on 'HsSpliceTy' (#745) This handles 'HsSpliceTy's by replacing them with what they expand to. IIUC everything that is happening, 'renameHsSpliceTy' should not be able to fail for the inputs we feed it from GHC. This fixes haskell/haddock#574. - - - - - 92bf95ad by Alex Biehl at 2018-02-06T08:28:23+01:00 Rename: renameHsSpliceTy ttg - - - - - 3130b1e1 by Alex Biehl at 2018-02-06T09:02:14+01:00 Expand SigDs - - - - - c72adae5 by Alex Biehl at 2018-02-06T09:20:51+01:00 fullModuleContents: support named docs - - - - - de2e4dbf by Alex Biehl at 2018-02-06T13:56:17+01:00 Hyperlinker: Also link pattern synonym arguments - - - - - b7c98237 by Alex Biehl at 2018-02-09T18:44:23+01:00 Expand SigD in a better place In https://github.com/haskell/haddock/issues/287 we found that haddock-2.19.0 would miss documentation on class methods with multiples names. This patch uses expandSigDecls in a more sensible place. - - - - - 8f598b27 by Alec Theriault at 2018-02-11T12:29:56+01:00 Add module tooltips to linked identifiers (#753) No more clicking to figure out whether your bytestring is strict or lazy! - - - - - d812e65d by Alec Theriault at 2018-02-11T12:31:44+01:00 Add 'show' option to complement 'hide' (#752) * Add 'show' option to complement 'hide' The behaviour is for flags passed in the command line to override flags in file headers. In the command line, later flags override earlier ones. Fixes haskell/haddock#751 and haskell/haddock#266. * Add a '--show-all' option - - - - - 6676cecb by Alex Biehl at 2018-02-18T11:07:15-05:00 QuickJump: Mitigate encoding problems on Windows (cherry picked from commit 86292c54bfee2343aee84559ec01f1fc68f52231) - - - - - e753dd88 by Alex Biehl at 2018-02-18T17:59:54+01:00 Use withBinaryFile - - - - - 724dc881 by Tamar Christina at 2018-02-19T05:34:49+01:00 Haddock: support splitted include paths. (#689) - - - - - 9b6d6f50 by Alex Biehl at 2018-02-19T05:57:02+01:00 Teach the HTML backend how to render methods with multiple names - - - - - a74aa754 by Alexander Biehl at 2018-02-19T10:04:34+01:00 Hoogle/Latex: Remove use of partial function - - - - - 66d8bb0e by Alec Theriault at 2018-02-25T16:04:01+01:00 Fix file handle leak (#763) (#764) Brought back some mistakenly deleted code for handling encoding and eager reading of files from e0ada1743cb722d2f82498a95b201f3ffb303137. - - - - - bb92d03d by Alex Biehl at 2018-03-02T14:21:23+01:00 Enable running test suite with stock haddock and ghc using ``` $ cabal new-run -- html-test --haddock-path=$(which haddock) --ghc-path=$(which ghc) ``` - - - - - dddb3cb2 by Alex Biehl at 2018-03-02T15:43:21+01:00 Make testsuite work with haddock-1.19.0 release (#766) - - - - - f38636ed by Alec Theriault at 2018-03-02T15:48:36+01:00 Support unicode operators, proper modules Unicode operators are a pretty big thing in Haskell, so supporting linking them seems like it outweighs the cost of the extra machinery to force Attoparsec to look for unicode. Fixes haskell/haddock#458. - - - - - 09d89f7c by Alec Theriault at 2018-03-02T15:48:43+01:00 Remove bang pattern - - - - - d150a687 by Alex Biehl at 2018-03-02T15:48:48+01:00 fix test - - - - - d6fd71a5 by Alex Biehl at 2018-03-02T16:22:38+01:00 haddock-test: Be more explicit which packages to pass We now pass `-hide-all-packages` to haddock when invoking the testsuite. This ensures we don't accidentally pick up any dependencies up through ghc.env files. - - - - - 0932c78c by Alex Biehl at 2018-03-02T17:50:38+01:00 Revert "fix test" This reverts commit 1ac2f9569242f6cb074ba6e577285a4c33ae1197. - - - - - 52516029 by Alex Biehl at 2018-03-02T18:16:50+01:00 Fix Bug548 for real - - - - - 89df9eb5 by Alex Biehl at 2018-03-05T18:28:19+01:00 Hyperlinker: Links for TyOps, class methods and associated types - - - - - d019a4cb by Ryan Scott at 2018-03-06T13:43:56-05:00 Updates for haskell/haddock#13324 - - - - - 6d5a42ce by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump haddock-2.19.0.1, haddock-api-2.19.0.1, haddock-library-1.5.0.1 - - - - - c0e6f380 by Alex Biehl at 2018-03-10T18:25:57+01:00 Update changelogs for haddock-2.19.0.1 and haddock-library-1.5.0.1 - - - - - 500da489 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Update to QC 2.11 - - - - - ce8362e9 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Restore backward-compat with base-4.5 through base-4.8 - - - - - baae4435 by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump lower bound for haddock-library - - - - - 10b7a73e by Alex Biehl at 2018-03-10T18:25:57+01:00 Haddock: Straighten out base bound - - - - - a6096f7b by Alex Biehl at 2018-03-13T08:45:06+01:00 extractDecl: Extract constructor patterns from data family instances (#776) * extractDecl: Allow extraction of data family instance constructors * extractDecl: extract data family instance constructors - - - - - ba4a0744 by Simon Jakobi at 2018-03-14T08:26:42+01:00 Readme: Update GHC version (#778) - - - - - 8de157d4 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for definition lists - - - - - 425b46f9 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for links - - - - - d53945d8 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for inline links - - - - - f1dc7c99 by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Slightly unmangle output - - - - - 0879d31c by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Prevent stdout buffering - - - - - 1f9e5f1b by Simon Jakobi at 2018-03-14T20:39:29+01:00 haddock-library.cabal: Clean up GHC options - - - - - 066b891a by Simon Jakobi at 2018-03-14T20:39:29+01:00 Make a proper definition for the <link> parser - - - - - 573d6ba7 by Alec Theriault at 2018-03-21T09:16:57+01:00 Show where instances are defined (#748) * Indicate source module of instances Above instance, we now also display a link to the module where the instance was defined. This is sometimes helpful in figuring out what to import. * Source module for type/data families too * Remove parens * Accept tests - - - - - 99b5d28b by Alex Biehl at 2018-03-21T09:20:36+01:00 Prepare changelog for next release - - - - - 482d3a93 by Alex Biehl at 2018-03-23T15:57:36+01:00 Useful cost centres, timers and allocation counters (#785) * Add some useful cost-centres for profiling * Add withTiming for each haddock phase Invoking haddock with `--optghc=-ddump-timings` now shows the amount of time spent and the number of allocated bytes for each phase. - - - - - 773b41bb by Alec Theriault at 2018-03-27T08:35:59+02:00 @since includes package name (#749) * Metadoc stores a package name This means that '@since' annotations can be package aware. * Get the package name the right way This should extract the package name for `@since` annotations the right way. I had to move `modulePackageInfo` around to do this and, in the process, I took the liberty to update it. Since it appears that finding the package name is something that can fail, I added a warning for this case. * Silence warnings * Hide package for local 'since' annotations As discussed, this is still the usual case (and we should avoid being noisy for it). Although this commit is large, it is basically only about threading a 'Maybe Package' from 'Haddock.render' all the way to 'Haddock.Backends.Xhtml.DocMarkup.renderMeta'. * Bump binary interface version * Add a '--since-qual' option This controls when to qualify since annotations with the package they come from. The default is always, but I've left an 'external' variant where only those annotations coming from outside of the current package are qualified. * Make ParserSpec work * Make Fixtures work * Use package name even if package version is not available The @since stuff needs only the package name passed in, so it makes sense to not be forced to pass in a version too. - - - - - e42c57bc by Alex Biehl at 2018-03-27T08:42:50+02:00 haddock-2.19.1, haddock-api-2.19.1, haddock-library-1.6.0 - - - - - 8373a529 by Alex Biehl at 2018-03-28T10:17:11+02:00 Bump haddock and haddock-api to 2.20.0 - - - - - 5038eddd by Jack Henahan at 2018-04-03T13:28:12+02:00 Clear search string on hide for haskell/haddock#781 (#789) - - - - - 920ca1eb by Alex Biehl at 2018-04-03T16:35:50+02:00 Travis: Build with ghc-8.4.2 (#793) - - - - - a232f0eb by Alan Zimmerman at 2018-04-07T14:14:32+02:00 Match changes in GHC for D4199 Removing HasSourceText and SourceTextX classes. - - - - - ab85060b by Alan Zimmerman at 2018-04-09T21:20:24+02:00 Match GHC changes for TTG - - - - - 739302b6 by Alan Zimmerman at 2018-04-13T13:31:44+02:00 Match GHC for TTG implemented on HsBinds, D4581 - - - - - 2f56d3cb by Ryan Scott at 2018-04-19T11:42:58-04:00 Bump upper bound on base to < 4.13 See https://ghc.haskell.org/trac/ghc/ticket/15018. - - - - - a49df92a by Alex Biehl at 2018-04-20T07:31:44+02:00 Don't treat fixity signatures like declarations - - - - - d02c103b by Ryan Scott at 2018-04-24T11:20:11-04:00 Add regression test for haskell/haddock#413 Fixes haskell/haddock#413. - - - - - c7577f52 by Ryan Scott at 2018-04-24T13:51:06-07:00 Improve the Hoogle backend's treatment of type families (#808) Fixes parts 1 and 2 of haskell/haddock#806. - - - - - d88f85b1 by Alec Theriault at 2018-04-25T11:24:07-07:00 Replace 'attoparsec' with 'parsec' (#799) * Remove attoparsec with parsec and start fixing failed parses * Make tests pass * Fix encoding issues The Haddock parser no longer needs to worry about bytestrings. All the internal parsing work in haddock-library happens over 'Text'. * Remove attoparsec vendor * Fix stuff broken in 'attoparsec' -> 'parsec' * hyperlinks * codeblocks * examples Pretty much all issues are due to attoparsec's backtracking failure behaviour vs. parsec's non-backtracking failure behaviour. * Fix small TODOs * Missing quote + Haddocks * Better handle spaces before/after paragraphs * Address review comments - - - - - fc25e2fe by Alan Zimmerman at 2018-04-27T15:36:53+02:00 Match changes in GHC for TTG - - - - - 06175f91 by Herbert Valerio Riedel at 2018-05-01T18:11:09+02:00 Merge branch 'ghc-head' with 'ghc-8.4' - - - - - 879caaa8 by Alec Theriault at 2018-05-07T18:53:15-07:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 3e0120cb by Simon Jakobi at 2018-05-07T19:00:18-07:00 Add docs for some DocH constructors (#814) - - - - - 0a32c6db by Alec Theriault at 2018-05-08T02:15:45-07:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 8816e783 by Simon Jakobi at 2018-05-08T10:48:11-07:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - ad60366f by Ryan Scott at 2018-05-10T11:19:47-04:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - 03b7cc3b by Ryan Scott at 2018-05-10T11:24:38-04:00 Wibbles - - - - - b03dd563 by Chaitanya Koparkar at 2018-05-10T11:44:58-04:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 9f298a40 by Ben Gamari at 2018-05-13T17:36:04-04:00 Account for refactoring of LitString - - - - - ea3dabe7 by Ryan Scott at 2018-05-16T09:21:43-04:00 Merge pull request haskell/haddock#826 from haskell/T825 Remove Hoogle backend hack that butchers infix datatype names - - - - - 0d234f7c by Alec Theriault at 2018-05-23T11:29:05+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 15fc9712 by Simon Jakobi at 2018-05-31T04:17:47+02:00 Adjust to new HsDocString internals - - - - - 6f1e19a8 by Ben Gamari at 2018-06-02T16:18:58-04:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 0d0355d9 by Ryan Scott at 2018-06-04T21:26:59-04:00 DerivingVia changes - - - - - 0d93475a by Simon Jakobi at 2018-06-05T19:47:05+02:00 Bump a few dependency bounds (#845) - - - - - 5cbef804 by Alec Theriault at 2018-06-05T19:47:16+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 9094c56f by Alec Theriault at 2018-06-05T22:53:25+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 70188719 by Simon Jakobi at 2018-06-08T22:20:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - 495cd1fc by Chaitanya Koparkar at 2018-06-13T23:01:34+02:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 81088732 by Ben Gamari at 2018-06-13T23:01:34+02:00 Account for refactoring of LitString - - - - - 7baf6587 by Simon Jakobi at 2018-06-13T23:05:08+02:00 Adjust to new HsDocString internals - - - - - bb61464d by Ben Gamari at 2018-06-13T23:05:22+02:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 5d8cb87f by Ryan Scott at 2018-06-13T23:39:30+02:00 DerivingVia changes - - - - - 73d373a3 by Alec Theriault at 2018-06-13T23:39:30+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 4865e254 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Remove `ITtildehsh` token - - - - - b867db54 by Alec Theriault at 2018-06-13T23:39:30+02:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 9598e392 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Add docs for some DocH constructors (#814) - - - - - 8a59035b by Alec Theriault at 2018-06-13T23:39:30+02:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 29350fc8 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - 2590bbd9 by Ryan Scott at 2018-06-13T23:39:30+02:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - a9939fdc by Ryan Scott at 2018-06-13T23:39:30+02:00 Wibbles - - - - - a22f7df4 by Alec Theriault at 2018-06-13T23:39:30+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 8741015d by Simon Jakobi at 2018-06-13T23:39:30+02:00 Bump a few dependency bounds (#845) - - - - - 4791e1cc by Alec Theriault at 2018-06-13T23:39:30+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 311d3216 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - d0577817 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Complete FixitySig and FamilyDecl pattern matches - - - - - 055b3aa7 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Fix redundant import warnings - - - - - f9ce19b1 by Simon Jakobi at 2018-06-13T23:49:52+02:00 html-test: Accept output - - - - - 04604ea7 by Simon Jakobi at 2018-06-13T23:54:37+02:00 Bump bounds on Cabal - - - - - 0713b692 by Simon Jakobi at 2018-06-14T00:00:12+02:00 Merge branch 'ghc-head' into ghc-head-update-3 - - - - - c6a56bfd by Simon Jakobi at 2018-06-14T02:33:27+02:00 Bump ghc bound for haddock-api spec test-suite - - - - - 119d04b2 by Simon Jakobi at 2018-06-14T12:37:48+02:00 Travis: `--allow-newer` for all packages - - - - - 0e876e2c by Alex Biehl at 2018-06-14T15:28:52+02:00 Merge pull request haskell/haddock#857 from sjakobi/ghc-head-update-3 Update ghc-head - - - - - 5be46454 by Alec Theriault at 2018-06-14T21:42:45+02:00 Improved handling of interfaces in 'haddock-test' (#851) This should now work with an inplace GHC where (for instance) HTML directories may not be properly recorded in the package DB. - - - - - 96ab1387 by Vladislav Zavialov at 2018-06-14T17:06:21-04:00 Handle -XStarIsType - - - - - e518f8c4 by Ben Gamari at 2018-06-14T17:48:00-04:00 Revert unintentional reversion of fix of haskell/haddock#548 - - - - - 01b9f96d by Alan Zimmerman at 2018-06-19T11:52:22+02:00 Match changes in GHC for haskell/haddock#14259 - - - - - 7f8c8298 by Ben Gamari at 2018-06-19T18:14:27-04:00 Bump GHC version to 8.6 - - - - - 11c6b5d2 by Ryan Scott at 2018-06-19T23:17:31-04:00 Remove HsEqTy and XEqTy - - - - - b33347c2 by Herbert Valerio Riedel at 2018-06-20T23:14:52+02:00 Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. - - - - - f0d2460e by Herbert Valerio Riedel at 2018-06-20T23:28:46+02:00 Update Travis CI job - - - - - ef239223 by Herbert Valerio Riedel at 2018-06-20T23:32:41+02:00 Drop GHC HEAD from CI and update GHC to 8.4.3 It's a waste of resource to even try to build this branch w/ ghc-head; so let's not do that... - - - - - 41c4a9fa by Ben Gamari at 2018-06-20T18:26:20-04:00 Bump GHC version to 8.7 - - - - - 8be593dc by Herbert Valerio Riedel at 2018-06-21T22:32:15+02:00 Update CI job to use GHC 8.7.* - - - - - b91d334a by Simon Jakobi at 2018-06-30T13:41:38+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section - - - - - f707d848 by Alec Theriault at 2018-07-05T10:43:35-04:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. - - - - - a6d2b8dc by Alec Theriault at 2018-07-06T10:06:32-04:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case - - - - - 13819f71 by Alan Zimmerman at 2018-07-15T19:33:51+02:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 - - - - - c346aa78 by Simon Jakobi at 2018-07-19T12:29:32+02:00 haddock-library: Bump bounds for containers - - - - - 722e733c by Simon Jakobi at 2018-07-19T13:36:45+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] - - - - - f0bd83fd by Alec Theriault at 2018-07-19T14:39:57+02:00 Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. - - - - - 394053a8 by Simon Jakobi at 2018-07-19T14:58:07+02:00 haddock-library: Bump bounds for containers - - - - - 1bda11a2 by Alec Theriault at 2018-07-20T09:04:03+02:00 Add HEAD.hackage overlay (#887) * Add HEAD.hackage overlay * Add HCPKG variable - - - - - c7b4ab45 by Alec Theriault at 2018-07-20T12:01:16+02:00 Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test - - - - - c05d32ad by Alec Theriault at 2018-07-20T12:01:49+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output - - - - - 24b39ee4 by Alec Theriault at 2018-07-20T12:02:16+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. - - - - - cb9d2099 by Simon Jakobi at 2018-07-20T13:39:29+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) - - - - - 133f24f5 by Alec Theriault at 2018-07-20T13:39:29+02:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) - - - - - 11024149 by Alec Theriault at 2018-07-20T13:39:29+02:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) - - - - - de0c139e by Simon Jakobi at 2018-07-20T13:39:29+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) - - - - - 6435e952 by Alec Theriault at 2018-07-20T13:39:29+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) - - - - - 1461af39 by Alec Theriault at 2018-07-20T13:39:29+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) - - - - - 69d3bde1 by Alec Theriault at 2018-07-20T13:49:47+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) - - - - - 6a5c73c7 by Alec Theriault at 2018-07-20T13:50:00+02:00 Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests - - - - - 92ca94c6 by Alec Theriault at 2018-07-20T13:55:36+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) - - - - - 981bc7fa by Simon Jakobi at 2018-07-20T15:06:06+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers - - - - - 27e7c0c5 by Simon Jakobi at 2018-07-20T15:09:05+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 49e1a415 by Simon Jakobi at 2018-07-20T16:02:02+02:00 Update the ghc-8.6 branch (#889) * Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. * README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) * Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) * Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) * tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) * Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. * Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test * Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) * Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) * Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) * Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests * Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 5ca14bed by Simon Jakobi at 2018-07-20T16:05:47+02:00 Revert "Revert "Bump GHC version to 8.6"" That commit didn't belong onto the ghc-8.6 branch. This reverts commit acbaef3b9daf1d2dea10017964bf886e77a8e967. - - - - - 2dd600dd by Simon Jakobi at 2018-07-20T16:18:21+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. - - - - - fceb2422 by Simon Jakobi at 2018-07-20T16:18:21+02:00 outOfScope: Recommend qualifying the identifier - - - - - acea5d23 by Simon Jakobi at 2018-07-20T16:19:35+02:00 outOfScope: Recommend qualifying the identifier (cherry picked from commit 73707ed58d879cc04cb644c5dab88c39ca1465b7) - - - - - 1a83ca55 by Simon Jakobi at 2018-07-20T16:19:35+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. (cherry picked from commit d504a2864a4e1982e142cf88c023e7caeea3b76f) - - - - - 48374451 by Masahiro Sakai at 2018-07-20T17:06:42+02:00 Add # as a special character (#884) '#' has special meaning used for anchors and can be escaped using backslash. Therefore it would be nice to be listed as special characters. - - - - - 5e1a5275 by Alec Theriault at 2018-07-20T23:37:24+02:00 Let `haddock-test` bypass interface version check (#890) This means `haddock-test` might * crash during deserialization * deserialize incorrectly Still - it means things _might_ work where they were previously sure not to. - - - - - 27286754 by Yuji Yamamoto at 2018-07-23T08:16:01+02:00 Avoid "invalid argument (invalid character)" on non-unicode Windows (#892) Steps to reproduce and the error message ==== ``` > stack haddock basement ... snip ... Warning: 'A' is out of scope. Warning: 'haddock: internal error: <stdout>: commitBuffer: invalid argument (invalid character) ``` Environment ==== OS: Windows 10 ver. 1709 haddock: [HEAD of ghc-8.4 when I reproduce the error](https://github.com/haskell/haddock/commit/532b209d127e4cecdbf7e9e3dcf4f653a5605b5a). (I had to use this version to avoid another probrem already fixed in HEAD) GHC: 8.4.3 stack: Version 1.7.1, Git revision 681c800873816c022739ca7ed14755e85a579565 (5807 commits) x86_64 hpack-0.28.2 Related pull request ==== https://github.com/haskell/haddock/pull/566 - - - - - 6729d361 by Alec Theriault at 2018-07-23T13:52:56-07:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). - - - - - 8cf4e6b5 by Ryan Scott at 2018-07-27T11:28:03-04:00 eqTyCon_RDR now lives in TysWiredIn After GHC commit http://git.haskell.org/ghc.git/commit/f265008fb6f70830e7e92ce563f6d83833cef071 - - - - - 1ad251a6 by Alan Zimmerman at 2018-07-30T13:28:09-04:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 (cherry picked from commit e3926b50ab8a7269fd6904b06e881745f08bc5d6) - - - - - 8aea2492 by Richard Eisenberg at 2018-08-02T10:54:17-04:00 Update against new HsImplicitBndrs - - - - - e42cada9 by Alec Theriault at 2018-08-04T17:51:30+02:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 0e852512 by Alex Biehl at 2018-08-06T13:04:02+02:00 Make --package-version optional for --hoogle generation (#899) * Make --package-version optional for --hoogle generation * Import mkVersion * It's makeVersion not mkVersion - - - - - d2abd684 by Noel Bourke at 2018-08-21T09:34:18+02:00 Remove unnecessary backslashes from docs (#908) On https://haskell-haddock.readthedocs.io/en/latest/markup.html#special-characters the backslash and backtick special characters showed up with an extra backslash before them – I think the escaping is not (or no longer) needed for those characters in rst. - - - - - 7a578a9e by Matthew Pickering at 2018-08-21T09:34:50+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - aa3d4db3 by Matthew Pickering at 2018-08-21T09:37:34+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - ede91744 by Alec Theriault at 2018-08-21T09:42:52+02:00 Better test output when Haddock crashes on a test (#902) In particular: we report the tests that crashed seperately from the tests that produced incorrect output. In order for tests to pass (and exit 0), they must not crash and must produce the right output. - - - - - 4a872b84 by Guillaume Bouchard at 2018-08-21T09:45:57+02:00 Fix a typo (#878) - - - - - 4dbf7595 by Ben Sklaroff at 2018-08-21T12:04:09-04:00 Add ITcomment_line_prag token to Hyperlinker Parser This token is necessary for parsing #line pragmas inside nested comments. Reviewers: bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D4935 - - - - - 9170b2a9 by Ben Gamari at 2018-08-21T17:55:15-04:00 Merge pull request haskell/haddock#893 from harpocrates/get-name-to-instances Accumulate explicitly which modules to load for 'attachInstances' - - - - - d57b57cc by Ben Gamari at 2018-08-21T17:59:13-04:00 Merge branch 'ghc-head' of github.com:haskell/haddock into ghc-head - - - - - 14601ca2 by Alec Theriault at 2018-08-21T19:09:37-04:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). (cherry picked from commit 5c7c596c51d69b92164e9ba920157b36ce2b2ec1) - - - - - 438c645e by Matthew Pickering at 2018-08-21T19:12:39-04:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 (cherry picked from commit e6aa8fb47b9477cc5ef5e46097524fe83e080f6d) - - - - - a80c5161 by Alec Theriault at 2018-08-21T22:06:40-07:00 Better rendering of unboxed sums/tuples * adds space after/before the '#' marks * properly reify 'HsSumTy' in 'synifyType' - - - - - 88456cc1 by Alec Theriault at 2018-08-21T22:06:40-07:00 Handle promoted tuples in 'synifyType' When we have a fully applied promoted tuple, we can expand it out properly. - - - - - fd1c1094 by Alec Theriault at 2018-08-21T22:19:34-07:00 Accept test cases - - - - - 6e80d9e0 by Alec Theriault at 2018-08-21T22:24:03-07:00 Merge pull request haskell/haddock#914 from harpocrates/feature/unboxed-stuff Better rendering of unboxed sums, unboxed tuples, promoted tuples. - - - - - 181a23f1 by Ben Gamari at 2018-08-23T15:53:48-04:00 Merge remote-tracking branch 'origin/ghc-8.6' into ghc-8.6 - - - - - 3a18c1d8 by Alec Theriault at 2018-08-27T14:15:25-07:00 Properly synify promoted list types We reconstruct promoted list literals whenever possible. That means that 'synifyType' produces '[Int, Bool, ()] instead of (Int ': (() ': (Bool ': ([] :: [Type])))) - - - - - b4794946 by Alec Theriault at 2018-09-03T07:19:55-07:00 Only look at visible types when synifying a 'HsListTy' The other types are still looked at when considering whether to make a kind signature or not. - - - - - a231fce2 by Alec Theriault at 2018-09-03T07:38:10-07:00 Merge pull request haskell/haddock#922 from harpocrates/promoted-lists Properly synify promoted list types - - - - - 0fdf044e by Ningning Xie at 2018-09-15T10:25:58-04:00 Update according to GHC Core changes - - - - - 7379b115 by Ningning Xie at 2018-09-15T15:40:18-04:00 update dataFullSig to work with Co Quantification This should have been in the previous patch, but wasn't. - - - - - cf84a046 by Alec Theriault at 2018-09-17T20:12:18-07:00 Fix/add to various docs * Add documentation for a bunch of previously undocumented options (fixes haskell/haddock#870) * Extend the documentation of `--hoogle` considerably (see haskell/haddock#807) * Describe how to add docs to `deriving` clauses (fixes haskell/haddock#912) * Fix inaccurate docs about hyperlinking infix identifiers (fixes haskell/haddock#780) - - - - - ae017935 by Alec Theriault at 2018-09-22T08:32:16-07:00 Update Travis - - - - - d95ae753 by Alec Theriault at 2018-09-22T09:34:10-07:00 Accept failing tests Also silence orphan warnings. - - - - - f3e67024 by Alec Theriault at 2018-09-22T09:41:23-07:00 Bump haddock-api-2.21.0, haddock-library-1.7.0 * Update CHANGELOGS * Update new versions in Cabal files * Purge references to ghc-8.4/master branches in README - - - - - 3f136d4a by Alec Theriault at 2018-09-22T10:53:31-07:00 Turn haddock-library into a minor release Fix some version bounds in haddock-library too. - - - - - b9def006 by Alec Theriault at 2018-09-22T13:07:35-07:00 keep cabal.project file - - - - - 4909aca7 by Alec Theriault at 2018-10-16T09:36:30-07:00 Build on 7.4 and 7.8 - - - - - 99d20a28 by Herbert Valerio Riedel at 2018-10-16T18:45:52+02:00 Minor tweak to package description - - - - - a8059618 by Herbert Valerio Riedel at 2018-10-16T18:47:24+02:00 Merge pull request haskell/haddock#945 haddock-api 2.21.0 and haddock-library 1.6.1 release - - - - - 2d9bdfc1 by Alec Theriault at 2018-10-16T10:54:21-07:00 Bump haddock-library to 1.7.0 The 1.6.1 release should've been a major bump, since types in the `Documentation.Haddock.Parser.Monad` module changed. This version makes that module internal (as it morally should be). - - - - - ed340cef by Alec Theriault at 2018-10-16T14:59:13-07:00 Merge branch 'ghc-8.4' into ghc-8.6 - - - - - 2821a8df by Alec Theriault at 2018-10-16T15:14:48-07:00 Merge branch 'ghc-8.6' into ghc-head - - - - - a722dc84 by Alec Theriault at 2018-10-16T16:28:55-07:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 63377496 by Alec Theriault at 2018-10-16T16:39:07-07:00 Update changelog - - - - - 099a0110 by Alec Theriault at 2018-10-16T16:49:28-07:00 Merge pull request haskell/haddock#942 from harpocrates/update-docs Fix & add to documentation - - - - - 0927416f by Alec Theriault at 2018-10-16T16:50:14-07:00 Set UTF-8 encoding before writing files (#934) This should fix haskell/haddock#929, as well as guard against future problems of this sort in other places. Basically replaces 'writeFile' (which selects the users default locale) with 'writeUtf8File' (which always uses utf8). - - - - - 83b7b017 by Alec Theriault at 2018-10-16T17:42:05-07:00 Output pattern synonyms in Hoogle backend (#947) * Output pattern synonyms in Hoogle backend We were previously weren't outputting _any_ pattern synonyms, bundled or not. Now, we output both. Fixes haskell/haddock#946. * Update changelog - - - - - 81e5033d by Alec Theriault at 2018-10-16T18:04:40-07:00 Release `haddock{,-api}-2.22.0` This version will accompany ghc-8.6.2 - - - - - 9661744e by Alex Biehl at 2018-10-18T08:14:32-07:00 Add NewOcean theme And make it the default theme. - - - - - 7ae6d722 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Improve appearance and readability These changes include: - use latest Haskell's logo colors - decrease #content width to improve readability - use nicer font - improve sizes and distances - - - - - 37f8703d by NunoAlexandre at 2018-10-18T08:14:32-07:00 Include custom font in the html head - - - - - 1d5e1d79 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Update html test reference files - - - - - 53b7651f by NunoAlexandre at 2018-10-18T08:14:32-07:00 Make it responsive - It makes small screens taking more space than larger ones - fixes a few issues present in small screens currently - make it look good across different screen sizes. - - - - - 6aa1aeb1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make the style consistent with hackage Several things are addressed here: - better responsive behaviour on the header - better space usage - consistent colors overall - other nit PR comments - - - - - 3a250c5c by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Place the package name before the menu links This supports the expected responsive menu design, where the package name appears above the menu links. - - - - - cae699b3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update html-test reference files The package name element in the package-header is now a div instead of a paragraph, and it is now above the menu ul.links instead of below. - - - - - 2ec7fd2d by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve synopsis style and code - Use CSS3 instead of loading pictures to show "+" and "-" symbols - Drop redundant code - - - - - 0c874c01 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Decrease space between code blocks There was too much space between code blocks as pointed out by reviewers. - - - - - 85568ce2 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Add an initial-scale property to all haddock pages This solves an issue reported about the content looking incredibly small on mobile devices. - - - - - c1538926 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Address several PR comments - Darken text color like done for hackage - Move synopsis to left side - Make table of contents stick to the left on wide screens - Wrap links to avoid page overflow - Improve expand/collapse buttons - Fix issue with content size on mobile devices - Fix issue with font-size on landscape mode - Increase width of the content - Change colors of table of contents and synopsis - Etc - - - - - e6639e5f by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make synopsis scrollable on wide screens When the synopsis is longer than the screen, you can’t see its end and you can't scroll down either, making the content unreachable. - - - - - 1f0591ff by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve information density - Reduce font size - Improve space between and within code blocks - Improve alignments - Improve spacing within sub-blocks - - - - - bf083097 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Minor adjustments Bring in some adjustments made to hackage: - link colors - page header show everything when package title is too long - - - - - 10375fc7 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix responsive triggers overlap issue The min and max width triggers have the same values, which caused the style resolution to take an intersection of both style declarations when the screen resolution had the size of the limts (say 1280px), causing an odd behaviour and look. - - - - - 95ff2f95 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix issue with menu alignment on firefox Reported and described here: https://github.com/haskell/haddock/pull/721#issuecomment-374668869 - - - - - dc86587e by Alex Biehl at 2018-10-18T08:14:32-07:00 Changelog entry for NewOcean - - - - - 27195e47 by Herbert Valerio Riedel at 2018-10-18T08:14:32-07:00 html-test --accept - - - - - 83f4f9c0 by Alex Biehl at 2018-10-18T08:14:32-07:00 Avoid name shadowing - - - - - 231487f1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font to PT Sans Also migrate some general text related changes from hackage. - - - - - 313db81a by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Use 'flex' to fix header alignment - - - - - 5087367b by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Misc of tweaks - Update link colors to hackage scheme - Tune spacing between content elements - Update footer style - Fix and improve code blocks identation - - - - - b08020df by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font in Xhtml.hs to PT Sans - - - - - 78ce06e3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve code blocks styling - Fix and improve spacing - Improve colors and borders - - - - - 81262d20 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make package-header caption backward-compatible The current html generator of this branch wraps the package-header caption as a div, which does not work (without style adjustments) with the old themes. Changing it from div to span does the trick, without needing to adjust the old stylesheets. - - - - - dc4475cb by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update test-suite reference html pages - - - - - 393d35d8 by Alec Theriault at 2018-10-18T08:25:36-07:00 Accept tests - - - - - a94484ba by Alec Theriault at 2018-10-21T10:29:29-07:00 Fix CHANGELOG - - - - - 8797eca3 by Alec Theriault at 2018-10-21T10:36:19-07:00 Update 'data-files' to include NewOcean stuff - - - - - 1ae51e4a by Simon Jakobi at 2018-10-23T11:29:14+02:00 Fix typo in a warning - - - - - 009ad8e8 by Alec Theriault at 2018-10-24T12:47:47-07:00 Update JS dependencies This was done via `npm audit fix`. I think this fixes haskell/haddock#903 along with some more serious vulnerabilities that nobody seems to have noticed. - - - - - 051994db by Alec Theriault at 2018-10-24T17:31:09-07:00 Resurrect the style-switcher This fixes haskell/haddock#810. Looks like things were broken during the quickjump refactor of the JS. For the (git) record: I do not think the style switcher is a good idea. I'm fixing it for the same reason @mzero added it; as an answer to "rumblings from some that they didn't want their pixels changed on bit" - - - - - 2a1d620f by Alec Theriault at 2018-10-24T17:38:07-07:00 Fix copy-pasta error in data-files - - - - - ed5bfb7f by Alec Theriault at 2018-10-24T20:42:14-07:00 Fix the synopsis button Here's these changes are supposed to do: * put the synopsis back on the right side * properly have it on the edge of the screen on wide screens * adjust the background of the synopsis to match the button (otherwise the grey blends in with what is underneath) * get rid of the dotted purple line * the synopsis contents are now scrollable even when in wide screens (this has been a long-standing bug) - - - - - 883fd74b by Alec Theriault at 2018-10-25T20:16:46-07:00 Avoid more conflicts in generated ids (#954) This fixes haskell/haddock#953 by passing more names into the generated ids. - - - - - ea54e331 by Alec Theriault at 2018-10-25T21:07:12-07:00 Don't hide bullets in method docs I think thst CSS was meant only to deal with fields and the effect on bullets was accidental. Fixes haskell/haddock#926. - - - - - 9a14ef4a by Alec Theriault at 2018-10-25T22:02:07-07:00 Indent more things + slightly smaller font - - - - - b9f17e29 by Alec Theriault at 2018-10-25T22:10:01-07:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 096a3cfa by Alec Theriault at 2018-10-25T22:24:38-07:00 Accept HTML output - - - - - 2669517d by Alec Theriault at 2018-10-26T09:02:35-07:00 User manual + stuff for building GHC docs - - - - - 46b27687 by Alec Theriault at 2018-10-26T09:10:59-07:00 Make 'Contents' in NewOcean scrollable This only happens if the contents block on the left is so big that it doesn't fit (vertically) on the page. If that happens, we want it to be scrollable. - - - - - 3443dd94 by Alec Theriault at 2018-10-26T09:36:46-07:00 Revert "Make 'Contents' in NewOcean scrollable" This reverts commit f909ffd8353d6463fd5dd184998a32aa98d5c922. I missed the fact this also forces the 'Contents' to always go down to the bottom of the page. - - - - - ed081424 by Alec Theriault at 2018-10-26T14:22:23-07:00 Avoid some partiality AFAICT this wasn't causing any crashes, but that's mostly because we happen not to be forcing `pkgStr` when it would diverge. We come dangerously close to doing that in `ppHtmlIndex`. Fixes haskell/haddock#569. - - - - - 6a5bec41 by Alec Theriault at 2018-10-27T10:05:04-07:00 Fix documentation in `haddock-api` (#957) * Fix misplaced Haddocks in Haddock itself Haddock should be able to generate documentation for 'haddock-api' again. * Make CI check that documentation can be built. * Add back a doc that is OK - - - - - 5100450a by Matthew Yacavone at 2018-10-27T14:51:38-04:00 More explicit foralls (GHC Proposal 0007) - - - - - 8771a6b0 by Alec Theriault at 2018-11-05T13:58:11-08:00 Only run MathJax on entities with "mathjax" class (#960) Correspondingly, we wrap all inline/diplay math in <span class="mathjax"> ... the math .... </span> This fixes haskell/haddock#959. - - - - - bd7ff5c5 by Alec Theriault at 2018-11-05T15:54:22-08:00 Deduplicate some work in 'AttachInstances' Perf only change: * avoid needlessly union-ing maps * avoid synify-ing instances twice Took this opportunity to add some docs too - - - - - cf99fd8f by Alec Theriault at 2018-11-05T15:54:22-08:00 Specialize some SYB functions Perf only change: * Add a 'SPECIALIZE' pragma to help GHC optimize a 'Data a =>' constraint * Manually specialize the needlessly general type of 'specializeTyVarBndrs' - - - - - 4f91c473 by Alec Theriault at 2018-11-05T15:54:22-08:00 Improve perf of renaming Perf only change: * don't look up type variable names (they're never in the environment) * use a difference list for accumulating missing names * more efficient 'Functor'/'Applicative' instances for 'RnM' - - - - - 4bbab0d4 by Alec Theriault at 2018-11-05T15:54:22-08:00 Faster 'Text' driven parser combinators Perf only change: * use 'getParserState'/'setParserState' to make 'Text'-optimized parser combinators * minimize uses of 'Data.Text.{pack,unpack,cons,snoc}' - - - - - fa430c02 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support hyperlink labels with inline markup The parser for pictures hasn't been properly adjusted yet. - - - - - c1431035 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support (and flatten) inline markup in image links Inline markup is supported in image links but, as per the [commonmark recommendation][0], it is stripped back to a plain text representation. [0]: https://spec.commonmark.org/0.28/#example-547 - - - - - d4ee1ba5 by Alec Theriault at 2018-11-06T12:03:24-08:00 Accept test case - - - - - 8088aeb1 by Alec Theriault at 2018-11-06T12:03:24-08:00 Fix/add to haddock-library test suite - - - - - e78f644d by Alec Theriault at 2018-11-06T13:26:31-08:00 Bump version bounds - - - - - 644335eb by Alec Theriault at 2018-11-06T13:53:30-08:00 Merge pull request haskell/haddock#875 from harpocrates/feature/markup-in-hyperlinks Inline markup in markdown-style links and images - - - - - e173ed0d by Alec Theriault at 2018-11-07T12:37:18-08:00 Fix issues around plus/minus * swap the minimize unicode to something more intuitive * use new unicode expander/collapser for instance lists * address some alignment issues in the "index" page - - - - - b2d92df7 by Alec Theriault at 2018-11-07T13:41:57-08:00 Allow "Contents" summary to scroll in a fixed div In the unfortunate event that the "Contents" summary doesn't fit vertically (like in the "Prelude"), it will be scrollable. - - - - - ca704c23 by Alec Theriault at 2018-11-07T13:45:15-08:00 Accept HTML output changes - - - - - 82c0ec6d by Alec Theriault at 2018-11-07T18:12:54-08:00 overflow-y 'scroll' -> 'auto' - - - - - 571d7657 by Alec Theriault at 2018-11-08T19:44:12-08:00 Clicking on "Contents" navigates to top of page - - - - - 8065a012 by Alec Theriault at 2018-11-08T19:44:17-08:00 Space out functions more Also, functions and data decls now have the same space before and after them. - - - - - cc650ede by Alec Theriault at 2018-11-09T08:13:35-08:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 65f8c17f by Alec Theriault at 2018-11-10T14:04:06-08:00 Update changelog - - - - - 20473847 by Alec Theriault at 2018-11-10T14:21:40-08:00 Replace oplus/ominus expander/collapser icons with triangles - - - - - 16592957 by Alec Theriault at 2018-11-10T14:35:10-08:00 Merge pull request haskell/haddock#949 from haskell/wip/new-ocean Introduce NewOcean theme. - - - - - 357cefe1 by Alec Theriault at 2018-11-10T16:02:13-08:00 Merge branch 'ghc-8.6' into ghc-head - - - - - de612267 by Alec Theriault at 2018-11-11T20:01:21-08:00 Rename 'NewOcean' theme to 'Linuwial' - - - - - 954b5baa by Alec Theriault at 2018-11-12T08:33:18-08:00 Add blockquote styling Matches b71da1feabf33efbbc517ac376bb690b5a604c2f from hackage-server. Fixes haskell/haddock#967. - - - - - d32c0b0b by Fangyi Zhou at 2018-11-12T10:24:13-08:00 Fix some broken links (#15733) Summary: For links in subpackages as well. https://phabricator.haskell.org/D5257 Test Plan: Manually verify links Reviewers: mpickering, bgamari, osa1 Reviewed By: osa1 GHC Trac Issues: haskell/haddock#15733 Differential Revision: https://phabricator.haskell.org/D5262 - - - - - 41098b1f by Alp Mestanogullari at 2018-11-15T22:40:09+01:00 Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change It got introduced in ghc/ghc at ae2c9b40f5b6bf272251d1f4107c60003f541b62. - - - - - c5c1c7e0 by Alec Theriault at 2018-11-15T13:48:13-08:00 Merge pull request haskell/haddock#970 from alpmestan/alp/fix-promotionflag Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change - - - - - 6473d3a4 by Shayan-Najd at 2018-11-23T01:38:49+01:00 [TTG: Handling Source Locations] Foundation and Pat Trac Issues haskell/haddock#15495 This patch removes the ping-pong style from HsPat (only, for now), using the plan laid out at https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/HandlingSourceLocations (solution A). - the class `HasSrcSpan`, and its functions (e.g., `cL` and `dL`), are introduced - some instances of `HasSrcSpan` are introduced - some constructors `L` are replaced with `cL` - some patterns `L` are replaced with `dL->L` view pattern - some type annotation are necessarily updated (e.g., `Pat p` --> `Pat (GhcPass p)`) - - - - - 7a088dfe by Alec Theriault at 2018-11-26T11:11:28-08:00 More uniform handling of `forall`'s in HTML/LaTeX * don't forget to print explicit `forall`'s when there are arg docs * when printing an explicit `forall`, print all tyvars Fixes haskell/haddock#973 - - - - - d735e570 by Alec Theriault at 2018-12-12T08:42:09-08:00 Fix warnings, accept output * remove redundant imports (only brought to light due to recent work for improving redundant import detection) * fix a bug that was casuing exports to appear in reverse order * fix something in haddock-library that prevented compilation on old GHC's - - - - - a3852f8a by Zejun Wu at 2018-12-14T09:37:47-05:00 Output better debug infromation on internal error in extractDecl This will make investigation of haskell/haddock#979 easier - - - - - 2eccb5b9 by Alec Theriault at 2018-12-17T09:25:10-05:00 Refactor names + unused functions (#982) This commit should not introduce any change in functionality! * consistently use `getOccString` to convert `Name`s to strings * compare names directly when possible (instead of comparing strings) * get rid of unused utility functions - - - - - e82e4df8 by Alec Theriault at 2018-12-20T16:16:30-05:00 Load plugins when compiling each module (#983) * WIP: Load (typechecker) plugins from language pragmas * Revert "Load plugins when starting a GHC session (#905)" This reverts commit 72d82e52f2a6225686d9668790ac33c1d1743193. * Simplify plugin initialization code - - - - - 96e86f38 by Alec Theriault at 2018-12-23T10:23:20-05:00 Properly synify and render promoted type variables (#985) * Synify and render properly promoted type variables Fixes haskell/haddock#923. * Accept output - - - - - 23343345 by Alec Theriault at 2018-12-27T16:39:38-05:00 Remove `haddock-test`'s dep. on `syb` (#987) The functionality is easily inlined into one short function: `gmapEverywhere`. This doesn't warrant pulling in another package. - - - - - d0734f21 by Alec Theriault at 2018-12-27T16:39:52-05:00 Address deprecation warnings in `haddock-test` (#988) Fixes haskell/haddock#885. - - - - - 4d9f144e by mynguyen at 2018-12-30T23:42:26-05:00 Visible kind application haddock update - - - - - ffe0e9ed by Alec Theriault at 2019-01-07T13:55:22-08:00 Print kinded tyvars in constructors for Hoogle (#993) Fixes haskell/haddock#992 - - - - - 2e18b55d by Alec Theriault at 2019-01-10T16:42:45-08:00 Accept new output `GHC.Maybe` -> `Data.Maybe` (#996) Since 53874834b779ad0dfbcde6650069c37926da1b79 in GHC, "GHC.Maybe" is marked as `not-home`. That changes around some test output. - - - - - 055da666 by Gabor Greif at 2019-01-22T14:41:51+01:00 Lone typofix - - - - - 01bb71c9 by Alec Theriault at 2019-01-23T11:46:46-08:00 Keep forall on H98 existential data constructors (#1003) The information about whether or not there is a source-level `forall` is already available on a `ConDecl` (as `con_forall`), so we should use it instead of always assuming `False`! Fixes haskell/haddock#1002. - - - - - f9b9bc0e by Ryan Scott at 2019-01-27T09:28:12-08:00 Fix haskell/haddock#1004 with a pinch of dropForAlls - - - - - 5cfcdd0a by Alec Theriault at 2019-01-28T16:49:57-08:00 Loosen 'QuickCheck' and 'hspec' bounds It looks like the new versions don't cause any breakage and loosening the bounds helps deps fit in one stack resolver. - - - - - 3545d3dd by Alec Theriault at 2019-01-31T01:37:25-08:00 Use `.hie` files for the Hyperlinker backend (#977) # Summary This is a large architectural change to the Hyperlinker. * extract link (and now also type) information from `.hie` instead of doing ad-hoc SYB traversals of the `RenamedSource`. Also adds a superb type-on-hover feature (#715). * re-engineer the lexer to avoid needless string conversions. By going directly through GHC's `P` monad and taking bytestring slices, we avoid a ton of allocation and have better handling of position pragmas and CPP. In terms of performance, the Haddock side of things has gotten _much_ more efficient. Unfortunately, much of this is cancelled out by the increased GHC workload for generating `.hie` files. For the full set of boot libs (including `ghc`-the-library) * the sum of total time went down by 9-10% overall * the sum of total allocations went down by 6-7% # Motivation Haddock is moving towards working entirely over `.hi` and `.hie` files. This change means we no longer need the `RenamedSource` from `TypecheckedModule` (something which is _not_ in `.hi` files). # Details Along the way a bunch of things were fixed: * Cross package (and other) links are now more reliable (#496) * The lexer tries to recover from errors on every line (instead of at CPP boundaries) * `LINE`/`COLUMN` pragmas are taken into account * filter out zero length tokens before rendering * avoid recomputing the `ModuleName`-based `SrcMap` * remove the last use of `Documentation.Haddock.Utf8` (see haskell/haddock#998) * restructure temporary folder logic for `.hi`/`.hie` model - - - - - 2ded3359 by Herbert Valerio Riedel at 2019-02-02T12:06:12+01:00 Update/modernise haddock-library.cabal file - - - - - 62b93451 by Herbert Valerio Riedel at 2019-02-02T12:19:31+01:00 Tentatively declare support for unreleased base-4.13/ghc-8.8 - - - - - 6041e767 by Herbert Valerio Riedel at 2019-02-02T16:04:32+01:00 Normalise LICENSE text w/ cabal's BSD2 template Also, correct the `.cabal` files to advertise `BSD2` instead of the incorrect `BSD3` license. - - - - - 0b459d7f by Alec Theriault at 2019-02-02T18:06:12-08:00 CI: fetch GHC from validate artifact Should help make CI be less broken - - - - - 6b5c07cf by Alec Theriault at 2019-02-02T18:06:12-08:00 Fix some Hyperlinker test suite fallout * Amend `ParserSpec` to match new Hyperlinker API - pass in compiler info - strip out null tokens * Make `hypsrc-test` pass reliably - strip out `local-*` ids - strip out `line-*` ids from the `ClangCppBug` test - re-accept output - - - - - ded34791 by Nathan Collins at 2019-02-02T18:31:23-08:00 Update README instructions for Stack No need to `stack install` Haddock to test it. Indeed, `stack install` changes the `haddock` on user's `PATH` if `~/.local/bin` is on user's `PATH` which may not be desirable when hacking on Haddock. - - - - - 723298c9 by Alec Theriault at 2019-02-03T09:11:05-08:00 Remove `Documentation.Haddock.Utf8` The circumstances under which this module appeared are completely gone. The Hyperlinker backend no longer needs this module (it uses the more efficient `Encoding` module from `ghc`). Why no deprecation? Because this module really shouldn't exist! - It isn't used in `haddock-library`/`haddock-api` anymore - It was copy pasted directly from `utf8-string` - Folks seeking a boot-lib only solution can use `ghc`'s `Encoding` - - - - - 51050006 by Alec Theriault at 2019-02-03T22:58:58-08:00 Miscellaneous improvements to `Convert` (#1020) Now that Haddock is moving towards working entirely over `.hi` and `.hie` files, all declarations and types are going to be synthesized via the `Convert` module. In preparation for this change, here are a bunch of fixes to this module: * Add kind annotations to type variables in `forall`'s whose kind is not `Type`, unless the kind can be inferred from some later use of the variable. See `implicitForAll` and `noKindTyVars` in particular if you wish to dive into this. * Properly detect `HsQualTy` in `synifyType`. This is done by following suit with what GHC's `toIfaceTypeX` does and checking the first argument of `FunTy{} :: Type` to see if it classified as a given/wanted in the typechecker (see `isPredTy`). * Beef up the logic around figuring out when an explicit `forall` is needed. This includes: observing if any of the type variables will need kind signatures, if the inferred type variable order _without_ a forall will still match the one GHC claims, and some other small things. * Add some (not yet used) functionality for default levity polymorphic type signatures. This functionality similar to `fprint-explicit-runtime-reps`. Couple other smaller fixes only worth mentioning: * Show the family result signature only when it isn't `Type` * Fix rendering of implicit parameters in the LaTeX and Hoogle backends * Better handling of the return kind of polykinded H98 data declarations * Class decls produced by `tyThingToLHsDecl` now contain associated type defaults and default method signatures when appropriate * Filter out more `forall`'s in pattern synonyms - - - - - 841980c4 by Oleg Grenrus at 2019-02-04T08:44:25-08:00 Make a fixture of weird parsing of lists (#997) The second example is interesting. If there's a list directly after the header, and that list has deeper structure, the parser is confused: It finds two lists: - One with the first nested element, - everything after it I'm not trying to fix this, as I'm not even sure this is a bug, and not a feature. - - - - - 7315c0c8 by Ryan Scott at 2019-02-04T12:17:56-08:00 Fix haskell/haddock#1015 with dataConUserTyVars (#1022) The central trick in this patch is to use `dataConUserTyVars` instead of `univ_tvs ++ ex_tvs`, which displays the foralls in a GADT constructor in a way that's more faithful to how the user originally wrote it. Fixes haskell/haddock#1015. - - - - - ee0b49a3 by Ryan Scott at 2019-02-04T15:25:17-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. - - - - - 1c850dc8 by Alan Zimmerman at 2019-02-05T21:54:18+02:00 Matching changes in GHC for haskell/haddock#16236 - - - - - ab03c38e by Simon Marlow at 2019-02-06T08:07:33+00:00 Merge pull request haskell/haddock#1014 from hvr/pr/bsd2-normalise Normalise LICENSE text w/ cabal's BSD2 template - - - - - 5a92ccae by Alec Theriault at 2019-02-10T06:21:55-05:00 Merge remote-tracking branch 'gitlab/wip/T16236-2' into ghc-head - - - - - c0485a1d by Alec Theriault at 2019-02-10T03:32:52-08:00 Removes `haddock-test`s dependency on `xml`/`xhtml` (#1027) This means that `html-test`, `latex-test`, `hoogle-test`, and `hypsrc-test` now only depend on GHC boot libs. So we should now be able to build and run these as part of GHC's testsuite. \o/ The reference output has changed very slightly, in three ways: * we don't convert quotes back into `&quot;` as the `xml` lib did * we don't add extra `&nbsp;` as the `xml` lib did * we now remove the entire footer `div` (instead of just emptying it) - - - - - 65a448e3 by Alec Theriault at 2019-02-11T12:27:41-05:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - 360ca937 by Alec Theriault at 2019-02-13T11:36:11-05:00 Clean up logic for guessing `-B` and `--lib` (#1026) Haddock built with the `in-ghc-tree` flag tries harder to find the GHC lib folder and its own resources. This should make it possible to use `in-ghc-tree`-built Haddock without having to specify the `-B` and `--lib` options (just how you can use in-tree GHC without always specifying the `-B` option). The logic to do this relies on `getExecutablePath`, so we only get this auto-detection on platforms where this function works. - - - - - d583e364 by Alec Theriault at 2019-02-16T10:41:22-05:00 Fix tests broken by GHC Changes in 19626218566ea709b5f6f287d3c296b0c4021de2 affected some of the hyperlinker output. Accepted the new output (hovering over a `..` now shows you what that wildcard binds). Also fixed some stray deprecation warnings. - - - - - da0c42cc by Vladislav Zavialov at 2019-02-17T11:39:19+03:00 Parser changes to match !380 - - - - - ab96bed7 by Ryan Scott at 2019-02-18T04:44:08-05:00 Bump ghc version to 8.9 - - - - - 44b7c714 by Alec Theriault at 2019-02-22T05:49:43-08:00 Match GHC changes for T16185 `FunTy` now has an `AnonArgFlag` that indicates whether the arrow is a `t1 => t2` or `t1 -> t2`. This commit shouldn't change any functionality in Haddock. - - - - - 2ee653b1 by Alec Theriault at 2019-02-24T18:53:33-08:00 Update .travis.yml Points to the new GHC CI artifact. - - - - - 90939d71 by Alec Theriault at 2019-02-25T00:42:41-08:00 Support value/type namespaces on identifier links Identifier links can be prefixed with a 'v' or 't' to indicate the value or type namespace of the desired identifier. For example: -- | Some link to a value: v'Data.Functor.Identity' -- -- Some link to a type: t'Data.Functor.Identity' The default is still the type (with a warning about the ambiguity) - - - - - d6ed496c by Alec Theriault at 2019-02-25T00:42:46-08:00 Better identifier parsing * '(<|>)' and '`elem`' now get parsed and rendered properly as links * 'DbModule'/'DbUnitId' now properly get split apart into two links * tuple names now get parsed properly * some more small niceties... The identifier parsing code is more precise and more efficient (although to be fair: it is also longer and in its own module). On the rendering side, we need to pipe through information about backticks/parens/neither all the way through from renaming to the backends. In terms of impact: a total of 35 modules in the entirety of the bootlib + ghc lib docs change. The only "regression" is things like '\0'. These should be changed to @\\0@ (the path by which this previously worked seems accidental). - - - - - 3c3b404c by Alec Theriault at 2019-02-25T22:12:11-08:00 Fix standalone deriving docs Docs on standalone deriving decls for classes with associated types should be associated with the class instance, not the associated type instance. Fixes haskell/haddock#1033 - - - - - d51ef69e by Alec Theriault at 2019-02-26T19:14:59-08:00 Fix bogus identifier defaulting This avoids a situation in which an identifier would get defaulted to a completely different identifier. Prior to this commit, the 'Bug1035' test case would hyperlink 'Foo' into 'Bar'! Fixes haskell/haddock#1035. - - - - - 88cbbdc7 by Ryan Scott at 2019-02-27T10:14:03-05:00 Visible dependent quantification (#16326) changes - - - - - 0dcf6cee by Xia Li-yao at 2019-02-27T21:53:27-05:00 Menu item controlling which instances are expanded/collapsed (#1007) Adds a menu item (like "Quick Jump") for options related to displaying instances. This provides functionality for: * expanding/collapsing all instances on the currently opened page * controlling whether instances are expanded/collapsed by default * controlling whether the state of instances should be "remembered" This new functionality is implemented in Typescript in `details-helper`. The built-in-themes style switcher also got a revamp so that all three of QuickJump, the style switcher, and instance preferences now have the same style and implementation structure. See also: https://mail.haskell.org/pipermail/haskell-cafe/2019-January/130495.html Fixes haskell/haddock#698. Co-authored-by: Lysxia <lysxia at gmail.com> Co-authored-by: Nathan Collins <conathan at galois.com> - - - - - 3828c0fb by Alec Theriault at 2019-02-28T12:42:49-05:00 `--show-interface` should output to stdout. (#1040) Fixes haskell/haddock#864. - - - - - a50f4cda by gbaz at 2019-03-01T07:43:16-08:00 Increase contrast of Linuwal theme (#1037) This is to address the concern that, on less nice and older screens, some of the shades of grey blend in too easily with the white background. * darken the font slightly * darken slightly the grey behind type signatures and such * add a border and round the corners on code blocks * knock the font down by one point - - - - - ab4d41de by Alec Theriault at 2019-03-03T09:23:26-08:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 12f509eb by Ben Gamari at 2019-03-04T22:13:20-05:00 Remove reference to Opt_SplitObjs flag Split-objects has been removed. - - - - - 5b3e4c9a by Ryan Scott at 2019-03-06T19:16:24-05:00 Update html-test output to reflect haskell/haddock#16391 changes - - - - - fc228af1 by Alec Theriault at 2019-03-09T08:29:23-08:00 Match changes for "Stop inferring over-polymorphic kinds" The `hsq_ext` field of `HsQTvs` is now just the implicit variables (instead of also including information about which of these variables are dependent). This commit shouldn't change any functionality in Haddock. - - - - - 6ac109eb by Alec Theriault at 2019-03-09T11:22:55-08:00 Add .hi, .dyn_hi, etc files to .gitignore Fixes haskell/haddock#1030. - - - - - b55f0c05 by Alec Theriault at 2019-03-09T11:22:55-08:00 Better support for default methods in classes * default methods now get rendered differently * default associated types get rendered * fix a forgotten `s/TypeSig/ClassOpSig/` refactor in LaTeX backend * LaTeX backend now renders default method signatures NB: there is still no way to document default class members and the NB: LaTeX backend still crashes on associated types - - - - - 10aea0cf by Alec Theriault at 2019-03-09T11:22:55-08:00 Avoid multi-line `emph` in LaTeX backend `markupWarning` often processes inputs which span across paragraphs. Unfortunately, LaTeX's `emph` is not made to handle this (and will crash). Fixes haskell/haddock#936. - - - - - d22dc2c9 by Alec Theriault at 2019-03-09T11:22:55-08:00 Many LaTeX backend fixes After this commit, we can run with `--latex` on all boot libraries without crashing (although the generated LaTeX still fails to compile in a handful of larger packages like `ghc` and `base`). * Add newlines after all block elements in LaTeX. This is important to prevent the final output from being more an more indented. See the `latext-test/src/Example` test case for a sample of this. * Support associated types in class declarations (but not yet defaults) * Several small issues for producing compiling LaTeX; - avoid empy `\haddockbeginargs` lists (ex: `type family Any`) - properly escape identifiers depending on context (ex: `Int#`) - add `vbox` around `itemize`/`enumerate` (so they can be in tables) * Several spacing fixes: - limit the width of `Pretty`-arranged monospaced code - cut out extra space characters in export lists - only escape spaces if there are _multiple_ spaces - allow type signatures to be multiline (even without docs) * Remove uninteresting and repetitive `main.tex`/`haddock.sty` files from `latex-test` test reference output. Fixes haskell/haddock#935, haskell/haddock#929 (LaTeX docs for `text` build & compile) Fixes haskell/haddock#727, haskell/haddock#930 (I think both are really about type families...) - - - - - 0e6cee00 by Alec Theriault at 2019-03-29T12:11:56-07:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - ce05434d by Alan Zimmerman at 2019-03-29T12:12:11-07:00 Matching changes in GHC for haskell/haddock#16236 (cherry picked from commit 3ee6526d4ae7bf4deb7cd1caf24b3d7355573576) - - - - - d85766b2 by Ben Gamari at 2019-03-29T12:14:04-07:00 Bump GHC to 8.8 - - - - - 5a82cbaf by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Redo ParseModuleHeader - - - - - b9033348 by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - bb55c8f4 by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove outdated `.ghci` files and `scripts` The `.ghci` files are actively annoying when trying to `cabal v2-repl`. As for the `scripts`, the distribution workflow is completely different. - - - - - 5ee244dc by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove obsolete arcanist files + STYLE Now that GHC is hosted on Gitlab, the arcanist files don't make sense anymore. The STYLE file contains nothing more than a dead link too. - - - - - d07c1928 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Redo ParseModuleHeader - - - - - 492762d2 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - af2ac773 by Ryan Scott at 2019-05-14T17:22:13-04:00 Changes for haskell/haddock#16110/#16356 - - - - - 6820ed0d by Alec Theriault at 2019-05-17T08:51:27-07:00 Unbreak haskell/haddock#1004 test case `fail` is no longer part of `Monad`. - - - - - 6bf7be98 by Alec Theriault at 2019-05-17T08:51:27-07:00 Fix haskell/haddock#1063 with better parenthesization logic for contexts The only other change in html/hoogle/hyperlinker output for the boot libraries that this caused is a fix to some Hoogle output for implicit params. ``` $ diff -r _build/docs/ old_docs diff -r _build/docs/html/libraries/base/base.txt old_docs/html/libraries/base/base.txt 13296c13296 < assertError :: (?callStack :: CallStack) => Bool -> a -> a --- > assertError :: ?callStack :: CallStack => Bool -> a -> a ``` - - - - - b5716b61 by Ryan Scott at 2019-05-22T17:24:32-04:00 Match changes with haskell/haddock#14332 - - - - - c115abf6 by Alec Theriault at 2019-05-26T16:01:58-04:00 Remove Haddock's dependency on `Cabal` At this point, Haddock depended on Cabal-the-library solely for a verbosity parser (which misleadingly accepts all sorts of verbosity options that Haddock never uses). Now, the only dependency on Cabal is for `haddock-test` (which uses Cabal to locate the Haddock interface files of a couple boot libraries). - - - - - e5b2d4a3 by Alec Theriault at 2019-05-26T16:16:25-04:00 Regression test: promoted lists in associated types When possible, associated types with promoted lists should use the promoted list literal syntax (instead of repeated applications of ': and '[]). This was fixed in 2122de5473fd5b434af690ff9ccb1a2e58491f8c. Closes haskell/haddock#466, - - - - - cc5ad5d3 by Alec Theriault at 2019-05-26T17:55:54-04:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 4b3301a6 by Alec Theriault at 2019-05-26T17:57:52-04:00 Release haddock-2.23, haddock-library-1.8.0 Tentatively adjust bounds and changelogs for the release to be bundled with GHC 8.8.1. - - - - - 69c7cfce by Matthew Pickering at 2019-05-30T10:54:27+01:00 Update hyperlinker tests for new types in .hie files - - - - - 29b7e738 by Zubin Duggal at 2019-05-30T10:57:51+01:00 update for new way to store hiefile headers - - - - - aeca5d5f by Zubin Duggal at 2019-06-04T18:57:42-04:00 update for new way to store hiefile headers - - - - - ba2ca518 by Ben Gamari at 2019-06-07T23:11:14+00:00 Update test output for introduction of Safe-Inferred - - - - - 3a975a6c by Ryan Scott at 2019-07-03T12:06:27-04:00 Changes for haskell/haddock#15247 - - - - - 0df46555 by Zubin Duggal at 2019-07-22T10:52:50+01:00 Fix haddockHypsrcTest - - - - - 2688686b by Sylvain Henry at 2019-09-12T23:19:39+02:00 Fix for GHC module renaming - - - - - 9ec0f3fc by Alec Theriault at 2019-09-20T03:21:00-04:00 Fix Travis CI, loosen .cabal bounds (#1089) Tentatively for the 2.23 release: * updated Travis CI to work again * tweaked bounds in the `.cabal` files * adjusted `extra-source-files` to properly identify test files - - - - - ca559beb by Matthías Páll Gissurarson at 2019-09-28T12:14:40-04:00 Small change in to facilitate extended typed-holes (#1090) This change has no functional effect on haddock itself, it just changes one pattern to use `_ (` rather than `_(`, so that we may use `_(` as a token for extended typed-holes later. - - - - - 02e28976 by Vladislav Zavialov at 2019-09-28T12:17:45-04:00 Remove spaces around @-patterns (#1093) This is needed to compile `haddock` when [GHC Proposal haskell/haddock#229](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0229-whitespace-bang-patterns.rst) is implemented. - - - - - 83cbbf55 by Alexis King at 2019-09-30T21:12:42-04:00 Fix the ignore-exports option (#1082) The `ignore-exports` option has been broken since haskell/haddock#688, as mentioned in https://github.com/haskell/haddock/pull/766#issue-172505043. This PR fixes it. - - - - - e127e0ab by Ben Gamari at 2019-10-06T15:12:06-04:00 Fix a few haddock issues - - - - - 3a0f5c89 by Zubin Duggal at 2019-10-07T17:56:13-04:00 Fix crash when there are no srcspans in the file due to CPP - - - - - 339c5ff8 by Alec Theriault at 2019-10-07T17:56:13-04:00 Prefer un-hyperlinked sources to no sources It is possible to fail to extract an HIE ast. This is however not a reason to produce _no_ output - we should still make a colorized HTML page. - - - - - d47ef478 by Alec Theriault at 2019-10-07T17:56:13-04:00 Add a regression test for haskell/haddock#1091 Previously, this input would crash Haddock. - - - - - ed7c8b0f by Alec Theriault at 2019-10-07T20:56:48-04:00 Add Hyperlinker test cases for TH-related stuff Hopefully this will guard against regressions around quasiquotes, TH quotes, and TH splices. - - - - - d00436ab by Andreas Klebinger at 2019-10-21T15:53:03+02:00 Refactor for withTiming changes. - - - - - 4230e712 by Ben Gamari at 2019-10-22T09:36:37-04:00 Merge pull request haskell/haddock#1101 from AndreasPK/withTimingRefactor Refactor for withTiming changes. - - - - - d155c5f4 by Ryan Scott at 2019-10-23T10:37:17-04:00 Reify oversaturated data family instances correctly (#1103) This fixes haskell/haddock#1103 by adapting the corresponding patch for GHC (see https://gitlab.haskell.org/ghc/ghc/issues/17296 and https://gitlab.haskell.org/ghc/ghc/merge_requests/1877). - - - - - 331a5adf by Sebastian Graf at 2019-10-25T17:14:40+02:00 Refactor for OutputableBndrId changes - - - - - 48a490e0 by Ben Gamari at 2019-10-27T10:16:16-04:00 Merge pull request haskell/haddock#1105 from sgraf812/wip/flexible-outputable Refactor for OutputableBndrId changes - - - - - f62a7dfc by Sebastian Graf at 2019-11-01T11:54:16+00:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - d9b242ed by Ryan Scott at 2019-11-03T13:20:03-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. (cherry picked from commit cfd682c5fd03b099a3d78c44f9279faf56a0ac70) - - - - - dfd42406 by Sebastian Graf at 2019-11-04T07:02:14-05:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - 0b15be7c by Ben Gamari at 2019-11-09T13:21:33-05:00 Import isRuntimeRepVar from Type rather than TyCoRep isRuntimeRepVar is not longer exported from TyCoRep due to ghc#17441. - - - - - 091f7283 by Ben Gamari at 2019-11-10T12:47:06-05:00 Bump to GHC 8.10 - - - - - e88c71f2 by Ben Gamari at 2019-11-14T00:22:24-05:00 Merge pull request haskell/haddock#1110 from haskell/wip/T17441 Import isRuntimeRepVar from Type rather than TyCoRep - - - - - 4e0bbc17 by Ben Gamari at 2019-11-14T00:22:45-05:00 Version bumps for GHC 8.11 - - - - - 0e85ceb4 by Ben Gamari at 2019-11-15T11:59:45-05:00 Bump to GHC 8.10 - - - - - 00d6d68b by Ben Gamari at 2019-11-16T18:35:58-05:00 Bump ghc version to 8.11 - - - - - dde1fc3f by Ben Gamari at 2019-11-16T20:40:37-05:00 Drop support for base 4.13 - - - - - f52e331d by Vladislav Zavialov at 2019-11-24T13:02:28+03:00 Update Hyperlinker.Parser.classify to use ITdollar - - - - - 1ad96198 by Vladislav Zavialov at 2019-11-28T16:12:33+03:00 Remove HasSrcSpan (#17494) - - - - - 651afd70 by Herbert Valerio Riedel at 2019-12-08T12:08:16+01:00 Document error-prone conditional definition of instances This can easily trip up people if one isn't aware of it. Usually it's better to avoid this kind of conditionality especially for typeclasses for which there's an compat-package as conditional instances like these tend to fragment the ecosystem into those packages that go the extra mile to provide backward compat via those compat-packages and those that fail to do so. - - - - - b521af56 by Herbert Valerio Riedel at 2019-12-08T12:09:54+01:00 Fix build-failure regression for base < 4.7 The `$>` operator definition is available only since base-4.7 which unfortunately wasn't caught before release to Hackage (but has been fixed up by a metadata-revision) This commit introduces a `CompatPrelude` module which allows to reduce the amount of CPP by ousting it to a central location, i.e. the new `CompatPrelude` module. This pattern also tends to reduce the tricks needed to silence unused import warnings. Addresses haskell/haddock#1119 - - - - - 556c375d by Sylvain Henry at 2020-01-02T19:01:55+01:00 Fix after Iface modules renaming - - - - - bd6c53e5 by Sylvain Henry at 2020-01-07T00:48:48+01:00 hsyl20-modules-renamer - - - - - fb23713b by Ryan Scott at 2020-01-08T07:41:13-05:00 Changes for GHC#17608 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2372 - - - - - 4a4dd382 by Ryan Scott at 2020-01-25T08:08:26-05:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - e782a44d by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename PackageConfig into UnitInfo - - - - - ba3c9f05 by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename lookupPackage - - - - - ab37f9b3 by Ben Gamari at 2020-01-29T13:00:44-05:00 Merge pull request haskell/haddock#1125 from haskell/wip/T17566-take-two Changes for GHC#17566 - - - - - 3ebd5ae0 by Ryan Scott at 2020-01-31T05:56:50-05:00 Merge branch 'wip-hsyl20-package-refactor' into ghc-head - - - - - 602a747e by Richard Eisenberg at 2020-02-04T09:05:43+00:00 Echo GHC's removal of PlaceHolder module This goes with GHC's !2083. - - - - - ccfe5679 by Sylvain Henry at 2020-02-10T10:13:56+01:00 Module hierarchy: runtime (cf haskell/haddock#13009) - - - - - 554914ce by Cale Gibbard at 2020-02-10T16:10:39-05:00 Fix build of haddock in stage1 We have to use the correct version of the GHC API, but the version of the compiler itself doesn't matter. - - - - - 5b6fa2a7 by John Ericson at 2020-02-10T16:18:07-05:00 Noramlize `tested-with` fields in cabal files - - - - - e6eb3ebe by Vladislav Zavialov at 2020-02-16T13:25:26+03:00 No MonadFail/Alternative for P - - - - - 90e181f7 by Ben Gamari at 2020-02-18T14:13:47-05:00 Merge pull request haskell/haddock#1129 from obsidiansystems/wip/fix-stage1-build Fix build of haddock in stage1 - - - - - 93b64636 by Sylvain Henry at 2020-02-19T11:20:27+01:00 Modules: Driver (#13009) - - - - - da4f6c7b by Vladislav Zavialov at 2020-02-22T15:33:02+03:00 Use RealSrcSpan in InstMap - - - - - 479b1b50 by Ben Gamari at 2020-02-23T10:28:13-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 55ecacf0 by Sylvain Henry at 2020-02-25T15:18:27+01:00 Modules: Core (#13009) - - - - - 60867b3b by Vladislav Zavialov at 2020-02-28T15:53:52+03:00 Ignore the BufLoc/BufSpan added in GHC's !2516 - - - - - 1e5506d3 by Sylvain Henry at 2020-03-02T12:32:43+01:00 Modules: Core (#13009) - - - - - 6fb53177 by Richard Eisenberg at 2020-03-09T14:49:40+00:00 Changes in GHC's !1913. - - - - - 30b792ea by Ben Gamari at 2020-03-16T12:45:02-04:00 Merge pull request haskell/haddock#1130 from hsyl20/wip/hsyl20-modules-core2 Modules: Core (#13009) - - - - - cd761ffa by Sylvain Henry at 2020-03-18T15:24:00+01:00 Modules: Types - - - - - b6646486 by Ben Gamari at 2020-03-18T14:42:43-04:00 Merge pull request haskell/haddock#1133 from hsyl20/wip/hsyl20/modules/types Modules: Types - - - - - 9325d734 by Kleidukos at 2020-03-19T12:38:31-04:00 Replace the 'caption' class so that the collapsible sections are shown - - - - - 5e2bb555 by Kleidukos at 2020-03-19T12:38:31-04:00 Force ghc-8.8.3 - - - - - c6fcd0aa by Kleidukos at 2020-03-19T12:38:31-04:00 Update test fixtures - - - - - 5c849cb1 by Sylvain Henry at 2020-03-20T09:34:39+01:00 Modules: Types - - - - - 7f439155 by Alec Theriault at 2020-03-20T20:17:01-04:00 Merge branch 'ghc-8.8' into ghc-8.10 - - - - - b7904e5c by Alina Banerjee at 2020-03-20T20:24:17-04:00 Update parsing to strip whitespace from table cells (#1074) * Update parsing to strip leading & trailing whitespace from table cells * Update fixture data to disallow whitespaces at both ends in table cells * Add test case for whitespaces stripped from both ends of table cells * Update table reference test data for html tests - - - - - b9d60a59 by Alec Theriault at 2020-03-22T11:46:42-04:00 Clean up warnings * unused imports * imports of `Data.List` without import lists * missing `CompatPrelude` file in `.cabal` - - - - - 0c317dbe by Alec Theriault at 2020-03-22T18:46:54-04:00 Fix NPM security warnings This was done by calling `npm audit fix`. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. - - - - - 6e306242 by Alec Theriault at 2020-03-22T20:10:52-04:00 Tentative 2.24 release Adjusted changelogs and versions in `.cabal` files in preparation for the upcoming release bundled with GHC 8.10. - - - - - 1bfb4645 by Ben Gamari at 2020-03-23T16:40:54-04:00 Merge commit '3c2944c037263b426c4fe60a3424c27b852ea71c' into HEAD More changes from the GHC types module refactoring. - - - - - be8c6f3d by Alec Theriault at 2020-03-26T20:10:53-04:00 Update `.travis.yml` to work with GHC 8.10.1 * Regenerated the Travis file with `haskell-ci` * Beef up `.cabal` files with more `tested-with` information - - - - - b025a9c6 by Alec Theriault at 2020-03-26T20:10:53-04:00 Update README Removed some out of date links/info, added some more useful links. * badge to Hackage * update old trac link * `ghc-head` => `ghc-8.10` * `cabal new-*` is now `cabal v2-*` and it should Just Work * `--test-option='--accept'` is the way to accept testsuite output - - - - - 564d889a by Alec Theriault at 2020-03-27T20:34:33-04:00 Fix crash in `haddock-library` on unicode space Our quickcheck tests for `haddock-library` stumbled across an edge case input that was causing Haddock to crash: it was a unicode space character. The root cause of the crash is that we were implicitly assuming that if a space character was not " \t\f\v\r", it would have to be "\n". We fix this by instead defining horizontal space as: any space character that is not '\n'. Fixes haskell/haddock#1142 - - - - - 2d360ba1 by Alec Theriault at 2020-03-27T21:57:32-04:00 Disallow qualified uses of reserved identifiers This a GHC bug (https://gitlab.haskell.org/ghc/ghc/issues/14109) too, but it is a relatively easy fix in Haddock. Note that the fix must live in `haddock-api` instead of `haddock-library` because we can only really decide if an identifier is a reserved one by asking the GHC lexer. Fixes haskell/haddock#952 - - - - - 47ae22ed by Alec Theriault at 2020-03-28T13:36:25-04:00 Remove unused `Haddock.Utils` functions * removed functions in `Haddock.Utils` that were not used anywhere (or exported from the `haddock-api` package) * moved GHC-specific utils from `Haddock.Utils` to `Haddock.GhcUtils` - - - - - c0291245 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use TTG empty extensions to remove some `error`'s None of these error cases should ever have been reachable, so this is just a matter of leveraging the type system to assert this. * Use the `NoExtCon` and `noExtCon` to handle case matches for no extension constructors, instead of throwing an `error`. * Use the extension field of `HsSpliceTy` to ensure that this variant of `HsType` cannot exist in an `HsType DocNameI`. - - - - - 0aff8dc4 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use `unLoc`/`noLoc` from GHC instead of `unL`/`reL` * `unL` is already defined by GHC as `unLoc` * `reL` is already defined by GHC as `noLoc` (in a safer way too!) * Condense `setOutputDir` and add a about exporting from GHC Fixes haskell/haddock#978 - - - - - bf6f2fb7 by Alec Theriault at 2020-03-28T13:36:25-04:00 Cleanup up GHC flags in `.cabal` files * enable more useful warning flags in `haddock-api`, handle the new warnings generated * remove `-fwarn-tabs` (now we'd use `-Wtabs`, but this has been in `-Wall` for a while now) - - - - - c576fbf1 by Alec Theriault at 2020-03-28T13:36:25-04:00 `haddock-library` document header level Document the fact the header level is going to always be between 1 and 6 inclusive. Along the way, I also optimized the parsing code a bit. - - - - - 71bce0ee by Alec Theriault at 2020-03-28T14:26:27-04:00 Disallow links in section headers This is quite straightforward to implement, since we already had a function `docToHtmlNoAnchors` (which we used to generate the link in the sidebar "Contents"). This breaks test `Bug387`, but that test case has aged badly: we now automatically generate anchors for all headings, so manually adding an anchor in a section makes no sense. Nested anchors are, as pointed out in haskell/haddock#1054, disallowed by the HTML standard. Fixes haskell/haddock#1054 - - - - - b461b0ed by Sylvain Henry at 2020-03-30T10:34:23+02:00 Modules: type checker - - - - - cd8cd1ee by Ben Gamari at 2020-03-31T12:45:02-04:00 Merge pull request haskell/haddock#1152 from hsyl20/wip/hsyl20/modules/tc Module renaming - - - - - 5e8f8ea7 by Felix Yan at 2020-04-01T17:58:06-07:00 Allow QuickCheck 2.14 Builds fine and all tests pass. - - - - - dc6b1633 by Sylvain Henry at 2020-04-05T16:43:44+02:00 Module renaming: amend previous patch - - - - - eee2f4ae by Ryan Scott at 2020-04-05T09:04:43-07:00 Fix haskell/haddock#1050 by filtering out invisible AppTy arguments This makes the `synifyType` case for `AppTy` more intelligent by taking into consideration the visibilities of each `AppTy` argument and filtering out any invisible arguments, as they aren't intended to be displayed in the source code. (See haskell/haddock#1050 for an example of what can happen if you fail to filter these out.) Along the way, I noticed that a special `synifyType` case for `AppTy t1 (CoercionTy {})` could be consolidated with the case below it, so I took the opportunity to tidy this up. - - - - - 23eb99e8 by Ben Gamari at 2020-04-07T11:19:58-04:00 Merge pull request haskell/haddock#1154 from hsyl20/wip/hsyl20/modules/tc Module renaming: amend previous patch - - - - - 072d994d by Ryan Scott at 2020-04-07T19:32:47-04:00 Make NoExtCon fields strict These changes are a part of a fix for [GHC#17992](https://gitlab.haskell.org/ghc/ghc/issues/17992). - - - - - d8ebf6c8 by Ignat Insarov at 2020-04-09T21:15:01-04:00 Recode Doc to Json. (#1159) * Recode Doc to Json. * More descriptive field labels. - - - - - 52df4b4e by Sylvain Henry at 2020-04-10T12:39:18+02:00 Module renaming - - - - - d9ab8ec8 by Cale Gibbard at 2020-04-14T11:43:34-04:00 Add instance of XCollectPat for DocNameI - - - - - 323d221d by Cale Gibbard at 2020-04-14T11:43:34-04:00 Rename XCollectPat -> CollectPass - - - - - 2df80867 by Alec Theriault at 2020-04-15T07:30:51-07:00 Prune docstrings that are never rendered When first creating a Haddock interface, trim `ifaceDocMap` and `ifaceArgMap` to not include docstrings that can never appear in the final output. Besides checking with GHC which names are exported, we also need to keep all the docs attached to instance declarations (it is much tougher to detect when an instance is fully private). This change means: * slightly smaller interface files (7% reduction on boot libs) * slightly less work to do processing docstrings that aren't used * no warnings in Haddock's output about private docstrings (see haskell/haddock#1070) I've tested manually that this does not affect any of the boot library generated docs (the only change in output was some small re-ordering in a handful of instance lists). This should mean no docstrings have been incorrectly dropped. - - - - - f49c90cc by Alec Theriault at 2020-04-15T07:30:51-07:00 Don't warn about missing links in miminal sigs When renaming the Haddock interface, never emit warnings when renaming a minimal signature. Also added some documention around `renameInterface`. Minimal signatures intentionally include references to potentially un-exported methods (see the discussion in haskell/haddock#330), so it is expected that they will not always have a link destination. On the principle that warnings should always be resolvable, this shouldn't produce a warning. See haskell/haddock#1070. - - - - - a9eda64d by Ben Gamari at 2020-04-17T09:27:35-04:00 Merge pull request haskell/haddock#1160 from hsyl20/wip/hsyl20/modules/systools Module renaming - - - - - f40d7879 by Cale Gibbard at 2020-04-20T11:30:38-04:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ttg-con-pat - - - - - a50e7753 by Ben Gamari at 2020-04-20T11:36:10-04:00 Merge pull request haskell/haddock#1165 from obsidiansystems/wip/ttg-con-pat Trees that Grow refactor (GHC !2553) - - - - - 6a24795c by Alec Theriault at 2020-04-21T08:06:45-07:00 Fallback to `hiDecl` when `extractDecl` fails Sometimes, the declaration being exported is a subdecl (for instance, a record accessor getting exported at the top-level). For these cases, Haddock has to find a way to produce some synthetic sensible top-level declaration. This is done with `extractDecl`. As is shown by haskell/haddock#1067, this is sometimes impossible to do just at a syntactic level (for instance when the subdecl is re-exported). In these cases, the only sensible thing to do is to try to reify a declaration based on a GHC `TyThing` via `hiDecl`. - - - - - eee1a8b7 by Sylvain Henry at 2020-04-24T15:46:05+02:00 Module structure - - - - - 50b9259c by Iñaki at 2020-04-25T18:38:11-04:00 Add support for custom section anchors (#1179) This allows to have stable anchors for groups, even if the set of groups in the documentation is altered. The syntax for setting the anchor of a group is -- * Group name #desiredAnchor# Which will produce an html anchor of the form '#g:desiredAnchor' Co-authored-by: Iñaki García Etxebarria <git at inaki.blueleaf.cc> - - - - - 4003c97a by Ben Gamari at 2020-04-26T09:35:15-04:00 Merge pull request haskell/haddock#1166 from hsyl20/wip/hsyl20/modules/utils Module structure - - - - - 5206ab60 by Sylvain Henry at 2020-04-27T16:47:39+02:00 Renamed UnitInfo fields - - - - - c32c333b by Sylvain Henry at 2020-04-27T17:32:58+02:00 UnitId has been renamed into Unit - - - - - 3e87db64 by Sylvain Henry at 2020-04-27T17:36:00+02:00 Fix for GHC.Unit.* modules - - - - - ae3323a7 by Ben Gamari at 2020-04-29T12:36:37-04:00 Merge pull request haskell/haddock#1183 from hsyl20/wip/hsyl20/unitid Refactoring of Unit code - - - - - b105564a by Artem Pelenitsyn at 2020-05-03T08:14:10+01:00 add dependency on exceptions because GHC.Exception was boiled down (ghc haskell/haddock#18075) - - - - - 9857eff3 by Zubin Duggal at 2020-05-04T18:48:25+01:00 Atomic update of NameCache in readHieFile - - - - - 86bbb226 by Sylvain Henry at 2020-05-14T16:36:27+02:00 Fix after Config module renaming - - - - - a4bbdbc2 by Gert-Jan Bottu at 2020-05-15T22:09:44+02:00 Explicit Specificity Support for Haddock - - - - - 46199daf by Ben Gamari at 2020-05-19T09:59:56-04:00 Merge pull request haskell/haddock#1192 from hsyl20/hsyl20/modules-config Fix after Config module renaming - - - - - f9a9d2ba by Gert-Jan Bottu at 2020-05-20T16:48:38-04:00 Explicit Specificity Support for Haddock - - - - - 55c5b7ea by Ben Gamari at 2020-05-21T00:32:02-04:00 Merge commit 'a8d7e66da4dcc3b242103271875261604be42d6e' into ghc-head - - - - - a566557f by Cale Gibbard at 2020-05-21T16:02:06-04:00 isBootSummary now produces a result of type IsBootInterface - - - - - ea52f905 by Zubin Duggal at 2020-05-24T17:55:48+01:00 update for hiefile-typeclass-info - - - - - 49ba7a67 by Willem Van Onsem at 2020-05-25T12:23:01-04:00 Use floor over round to calculate the percentage (#1195) If we compile documentation where only a small fraction is undocumented, it is misleading to see 100% coverage - 99% is more intuitive. Fixes haskell/haddock#1194 - - - - - c025ebf1 by Ben Gamari at 2020-05-29T14:32:42-04:00 Merge pull request haskell/haddock#1185 from obsidiansystems/boot-disambig isBootSummary now produces a result of type IsBootInterface - - - - - 74ab9415 by Ben Gamari at 2020-05-29T20:23:39-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - b40be944 by Ben Gamari at 2020-06-03T17:02:31-04:00 testsuite: Update expected output for simplified subsumption - - - - - 624be71c by Ryan Scott at 2020-06-05T12:43:23-04:00 Changes for GHC#18191 See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3337. - - - - - fbd8f7ce by Sylvain Henry at 2020-06-08T15:31:47+02:00 Fix after unit refactoring - - - - - 743fda4d by Ben Gamari at 2020-06-09T12:09:58-04:00 Merge pull request haskell/haddock#1202 from hsyl20/wip/hsyl20/unitid-ii Fix after unit refactoring - - - - - d07a06a9 by Ryan Scott at 2020-06-13T07:16:55-04:00 Use HsForAllTelescope (GHC#18235) - - - - - 389bb60d by Ben Gamari at 2020-06-13T15:30:52-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - 7a377f5f by Ben Gamari at 2020-06-17T14:53:16-04:00 Merge pull request haskell/haddock#1199 from bgamari/wip/ghc-8.12 haddock: Bounds bumps for GHC 8.12 - - - - - 9fd9e586 by Krzysztof Gogolewski at 2020-06-17T16:09:07-04:00 Adapt Haddock to LinearTypes See ghc/ghc!852. - - - - - 46fe7636 by Ben Gamari at 2020-06-18T14:20:02-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 35a3c9e2 by Zubin Duggal at 2020-06-21T21:19:18+05:30 Use functions exported from HsToCore - - - - - 8abe3928 by Ben Gamari at 2020-06-24T13:53:39-04:00 Merge pull request haskell/haddock#1204 from wz1000/wip/haddock-hstocore Use functions exported from GHC.HsToCore.Docs - - - - - 22f2c937 by Matthías Páll Gissurarson at 2020-06-26T19:07:03+02:00 Adapt Haddock for QualifiedDo - - - - - 3f6208d7 by Vladislav Zavialov at 2020-06-28T14:28:16+03:00 Handle LexicalNegation's ITprefixminus - - - - - 03a19f41 by Sylvain Henry at 2020-07-02T09:37:38+02:00 Rename hsctarget into backend - - - - - ea17ff23 by Andreas Klebinger at 2020-07-02T17:44:18+02:00 Update for UniqFM changes. - - - - - 9872f2f3 by Ben Gamari at 2020-07-09T10:39:19-04:00 Merge pull request haskell/haddock#1209 from AndreasPK/wip/typed_uniqfm Update for UniqFM changes. - - - - - 68f7b668 by Krzysztof Gogolewski at 2020-07-12T18:16:57+02:00 Sync with GHC removing {-# CORE #-} pragma See ghc ticket haskell/haddock#18048 - - - - - eb372681 by Sylvain Henry at 2020-07-20T11:41:30+02:00 Rename hscTarget into backend - - - - - fb7f78bf by Ben Gamari at 2020-07-21T12:15:25-04:00 Merge pull request haskell/haddock#1214 from hsyl20/wip/hsyl20/hadrian/ncg Rename hscTarget into backend - - - - - 1e8f5b56 by Ben Gamari at 2020-07-23T09:11:50-04:00 Merge commit '904dce0cafe0a241dd3ef355775db47fc12f434d' into ghc-head - - - - - d8fd1775 by Zubin Duggal at 2020-07-23T18:46:40+05:30 Update for modular ping pong - - - - - 8416f872 by Ben Gamari at 2020-07-23T09:35:03-04:00 Merge pull request haskell/haddock#1200 from wz1000/wip/wz1000-modular-ping-pong Modular ping pong - - - - - a24a8577 by Ben Gamari at 2020-07-28T15:23:36-04:00 Bump GHC version to 9.0 - - - - - 6a51c9dd by Sylvain Henry at 2020-08-05T18:47:05+02:00 Fix after Outputable refactoring - - - - - c05e1c99 by Ben Gamari at 2020-08-10T14:41:41-04:00 Merge pull request haskell/haddock#1223 from hsyl20/wip/hsyl20/dynflags/exception Fix after Outputable refactoring - - - - - d964f15b by Sylvain Henry at 2020-08-12T11:58:49+02:00 Fix after HomeUnit - - - - - 8e6d5b23 by Ben Gamari at 2020-08-12T14:25:30-04:00 Merge pull request haskell/haddock#1225 from hsyl20/wip/hsyl20/plugins/homeunit Fix after HomeUnit - - - - - 8c7880fe by Sylvain Henry at 2020-08-17T14:13:29+02:00 Remove Ord FastString instance - - - - - 8ea410db by Alex Biehl at 2020-08-19T10:56:32+02:00 Another round of `npm audit fix` (#1228) This should shut down the warnings on Github. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. Last NPM dependency audit happend in d576b2327e2bc117f912fe0a9d595e9ae62614e0 Co-authored-by: Alex Biehl <alex.biehl at target.com> - - - - - 7af6e2a8 by Ben Gamari at 2020-08-31T13:59:34-04:00 Merge pull request haskell/haddock#1226 from hsyl20/wip/hsyl20/fs_ord Remove Ord FastString instance - - - - - ffbc8702 by Alan Zimmerman at 2020-09-07T21:47:41+01:00 Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - a93f1268 by Alan Zimmerman at 2020-09-07T23:11:38+01:00 Merge pull request haskell/haddock#1232 from haskell/wip/T18639-remove-generated-pragma, Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - 1f605d50 by Ben Gamari at 2020-09-14T18:30:01-04:00 Bump GHC version to 9.1 - - - - - 6599df62 by Vladislav Zavialov at 2020-09-18T14:05:15+03:00 Bump base upper bound to 4.16 - - - - - a01b3c43 by Ben Gamari at 2020-09-22T15:41:48-04:00 Update hypsrc-test for QuickLook This appears to be a spurious change. - - - - - e9cc6cac by Vladislav Zavialov at 2020-09-26T21:00:12+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 30e3ca7c by Sylvain Henry at 2020-09-29T11:18:32-04:00 Update for parser (#1234) - - - - - b172f3e3 by Vladislav Zavialov at 2020-09-30T01:01:30+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 0b9c08d3 by Sylvain Henry at 2020-09-30T11:02:33+02:00 Adapt to GHC parser changes - - - - - b9540b7a by Sylvain Henry at 2020-10-12T09:13:38-04:00 Don't pass the HomeUnitId (#1239) - - - - - 34762e80 by HaskellMouse at 2020-10-13T12:58:04+03:00 Changed tests due to unification of `Nat` and `Natural` in the follwing merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3583 - - - - - 256f86b6 by Vladislav Zavialov at 2020-10-15T10:48:03+03:00 Add whitespace in: map ($ v) - - - - - 4a3f711b by Alan Zimmerman at 2020-10-19T08:57:27+01:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled - - - - - 072cdd21 by Alan Zimmerman at 2020-10-21T14:48:28-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 9e09a445 by Alan Zimmerman at 2020-10-21T23:53:34-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 636d7de3 by Sylvain Henry at 2020-10-26T14:31:54-04:00 GHC.Driver.Types refactoring (#1242) - - - - - a597f000 by Ryan Scott at 2020-10-29T04:18:05-04:00 Adapt to the removal of Hs{Boxed,Constraint}Tuple See ghc/ghc!4097 and GHC#18723. - - - - - b96660fb by Ryan Scott at 2020-10-30T04:53:05-04:00 Adapt to HsConDecl{H98,GADT}Details split Needed for GHC#18844. - - - - - c287d82c by Ryan Scott at 2020-10-30T19:35:59-04:00 Adapt to HsOuterTyVarBndrs These changes accompany ghc/ghc!4107, which aims to be a fix for haskell/haddock#16762. - - - - - a34c31a1 by Ryan Scott at 2020-11-13T13:38:34-05:00 Adapt to splitPiTysInvisible being renamed to splitInvisPiTys This is a part of !4434, a fix for GHC#18939. - - - - - 66ea459d by Sylvain Henry at 2020-11-16T10:59:30+01:00 Fix after Plugins moved into HscEnv - - - - - 508556d8 by Ben Gamari at 2020-11-18T15:47:40-05:00 Merge pull request haskell/haddock#1253 from hsyl20/wip/hsyl20/plugins/hscenv Fix after Plugins moved into HscEnv - - - - - 620fec1a by Andreas Klebinger at 2020-11-24T20:51:59+01:00 Update for changes in GHC's Pretty - - - - - 01cc13ab by Richard Eisenberg at 2020-11-25T23:18:35-05:00 Avoid GHC#18932. - - - - - 8d29ba21 by Cale Gibbard at 2020-11-25T23:18:35-05:00 Add type arguments to PrefixCon - - - - - 414d5f87 by Sylvain Henry at 2020-11-30T17:06:04+01:00 DynFlags's unit fields moved to HscEnv - - - - - e356668c by Ben Gamari at 2020-11-30T11:11:37-05:00 Merge pull request haskell/haddock#1258 from hsyl20/wip/hsyl20/hscenv/unitstate Unit fields moved from DynFlags to HscEnv - - - - - 7cf552f1 by Ben Gamari at 2020-12-03T10:31:27-05:00 Merge pull request haskell/haddock#1257 from AndreasPK/wip/andreask/opt_dumps Update for changes in GHC's Pretty - - - - - fc0871c3 by Veronika Romashkina at 2020-12-08T16:35:33+01:00 Fix docs links from Darcs to GitHub in intro (#1262) - - - - - 7059e808 by Veronika Romashkina at 2020-12-08T16:36:16+01:00 Use gender neutral word in docs (#1260) - - - - - 1b16e5ee by Maximilian Tagher at 2020-12-08T16:40:03+01:00 Allow scrolling search results (#1235) Closes https://github.com/haskell/haddock/issues/1231 - - - - - 8a118c01 by dependabot[bot] at 2020-12-08T16:40:25+01:00 Bump bl from 1.2.2 to 1.2.3 in /haddock-api/resources/html (#1255) Bumps [bl](https://github.com/rvagg/bl) from 1.2.2 to 1.2.3. - [Release notes](https://github.com/rvagg/bl/releases) - [Commits](https://github.com/rvagg/bl/compare/v1.2.2...v1.2.3) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - c89ff587 by Xia Li-yao at 2020-12-08T16:42:17+01:00 Allow more characters in anchor following module reference (#1220) - - - - - 14af7d64 by Xia Li-yao at 2020-12-08T16:43:05+01:00 Add dangling changes from branches ghc-8.6 and ghc-8.8 (#1243) * Fix multiple typos and inconsistencies in doc/markup.rst Note: I noticed some overlap with haskell/haddock#1112 from @wygulmage and haskell/haddock#1081 from @parsonsmatt after creating these proposed changes - mea culpa for not looking at the open PRs sooner. * Fix haskell/haddock#1113 If no Signatures, no section of index.html * Change the formatting of missing link destinations The current formatting of the missing link destination does not really help user to understand the reasons of the missing link. To address this, I've changed the formatting in two ways: - the missing link symbol name is now fully qualified. This way you immediately know which haskell module cannot be linked. It is then easier to understand why this module does not have documentation (hidden module or broken documentation). - one line per missing link, that's more readable now that symbol name can be longer due to qualification. For example, before haddock was listing missing symbol such as: ``` could not find link destinations for: Word8 Word16 mapMaybe ``` Now it is listed as: ``` could not find link destinations for: - Data.Word.Word8 - Data.Word.Word16 - Data.Maybe.mapMaybe ``` * Add `--ignore-link-symbol` command line argument This argument can be used multiples time. A missing link to a symbol listed by `--ignore-link-symbol` won't trigger "missing link" warning. * Forbid spaces in anchors (#1148) * Improve error messages with context information (#1060) Co-authored-by: Matt Audesse <matt at mattaudesse.com> Co-authored-by: Mike Pilgrem <mpilgrem at users.noreply.github.com> Co-authored-by: Guillaume Bouchard <guillaume.bouchard at tweag.io> Co-authored-by: Pepe Iborra <pepeiborra at gmail.com> - - - - - 89e3af13 by tomjaguarpaw at 2020-12-08T18:00:04+01:00 Enable two warnings (#1245) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - c3320f8d by Willem Van Onsem at 2020-12-08T18:26:55+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 685df308 by Alex Biehl at 2020-12-08T20:06:26+01:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - be3ec3c0 by Alex Biehl at 2020-12-08T20:06:26+01:00 Import intercalate - - - - - 32c33912 by Matthías Páll Gissurarson at 2020-12-08T21:15:30+01:00 Adapt Haddock for QualifiedDo - - - - - 31696088 by Alex Biehl at 2020-12-08T22:06:02+01:00 Fix haddock-library tests - - - - - fbc0998a by Alex Biehl at 2020-12-08T23:08:23+01:00 Move to GitHub CI (#1266) * Initial version of ci.yml This is a straight copy from Dmitrii Kovanikov's blog post at https://kodimensional.dev/github-actions. Will adapt to haddock in successive commits. * Delete .travis.yml * Modify to only test on ghc-8.10.{1,2} * Use actions/setup-haskell at v1.1.4 * Relax QuickCheck bound on haddock-api * Remove stack matrix for now * Nail down to ghc-8.10 branch for now * Pin index state to 2020-12-08T20:13:44Z for now * Disable macOS and Windows tests for now for speed up - - - - - 5b946b9a by tomjaguarpaw at 2020-12-10T19:01:41+01:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - bc5a408f by dependabot[bot] at 2020-12-10T19:02:16+01:00 Bump ini from 1.3.5 to 1.3.7 in /haddock-api/resources/html (#1269) Bumps [ini](https://github.com/isaacs/ini) from 1.3.5 to 1.3.7. - [Release notes](https://github.com/isaacs/ini/releases) - [Commits](https://github.com/isaacs/ini/compare/v1.3.5...v1.3.7) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - d02995f1 by Andrew Martin at 2020-12-14T16:48:40-05:00 Update for boxed rep - - - - - a381aeff by Ben Gamari at 2020-12-15T15:13:30-05:00 Revert "Enable two warnings (#1245) (#1268)" As this does not build on GHC `master`. This reverts commit 7936692badfe38f23ae95b51fb7bd7c2ff7e9bce. - - - - - a63c0a9e by Ben Gamari at 2020-12-15T15:17:59-05:00 Revert "Update for boxed rep" This reverts commit 4ffb30d8b637ccebecc81ce610f0af451ac8088d. - - - - - 53bfbb29 by Ben Gamari at 2020-12-15T15:37:24-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - bae76a30 by Ben Gamari at 2020-12-16T02:44:42+00:00 Update output for nullary TyConApp optimisation (ghc/ghc!2952) - - - - - 4b733b57 by Krzysztof Gogolewski at 2020-12-16T20:03:14+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. - - - - - ee463bd3 by Ryan Scott at 2020-12-16T16:55:23-05:00 Adapt to HsCoreTy (formerly NewHsTypeX) becoming a type synonym Needed for !4417, the fix for GHC#15706 and GHC#18914. - - - - - ed0b02f8 by tomjaguarpaw at 2020-12-19T10:17:19+00:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - d80bf8f5 by Sylvain Henry at 2020-12-21T10:09:25+01:00 Fix after binder collect changes - - - - - bf4c9d32 by Adam Gundry at 2020-12-23T21:35:01+00:00 Adapt to changes to GlobalRdrElt and AvailInfo Needed for ghc/ghc!4467 - - - - - 37736c4c by John Ericson at 2020-12-28T12:27:02-05:00 Support a new ghc --make node type for parallel backpack upsweep - - - - - 717bdeac by Vladislav Zavialov at 2020-12-29T10:50:02+03:00 Inline and fix getGADTConTypeG The getGADTConTypeG used HsRecTy, which is at odds with GHC issue haskell/haddock#18782. I noticed that getGADTConTypeG was only used in the Hoogle backend. Interestingly, when handling H98 constructors, Hoogle converts RecCon to PrefixCon (see Haddock.Backends.Hoogle.ppCtor). So I changed getGADTConTypeG to handle RecConGADT in the same manner as PrefixConGADT, and after this simplification moved it into the 'where' clause of ppCtor, to the only place where it is used. The practical effect of this change is as follows. Consider this example: data TestH98 = T98 { bar::Int } data TestGADT where TG :: { foo :: Int } -> TestGADT Before this patch, haddock --hoogle used to produce: T98 :: Int -> TestH98 [TG] :: {foo :: Int} -> TestGADT Notice how the record syntax was discarded in T98 but not TG. With this patch, we always produce signatures without record syntax: T98 :: Int -> TestH98 [TG] :: Int -> TestGADT I suspect this might also be a bugfix, as currently Hoogle doesn't seem to render GADT record constructors properly. - - - - - cb1b8c56 by Andreas Abel at 2020-12-30T21:12:37+01:00 Build instructions: haddock-library and -api first! - - - - - b947f6ad by Ben Gamari at 2020-12-31T13:04:19-05:00 Merge pull request haskell/haddock#1281 from obsidiansystems/wip/backpack-j Changes to support -j with backpack - - - - - 120e1cfd by Hécate Moonlight at 2021-01-04T19:54:58+01:00 Merge pull request haskell/haddock#1282 from andreasabel/master Build instructions: haddock-library and -api first! - - - - - fd45e41a by Ben Gamari at 2021-01-05T16:14:31-05:00 Merge remote-tracking branch 'origin/ghc-8.10' into ghc-9.0 - - - - - b471bdec by Ben Gamari at 2021-01-05T16:23:02-05:00 Merge commit '1e56f63c3197e7ca1c1e506e083c2bad25d08793' into ghc-9.0 - - - - - 81cdbc41 by Alex Biehl at 2021-01-09T12:14:41+01:00 Prepare Haddock for being a GHC Plugin - - - - - b646d952 by Alex Biehl at 2021-01-09T12:14:41+01:00 Make Haddock a GHC Plugin - - - - - cc044674 by Alex Biehl at 2021-01-09T12:14:41+01:00 Add -j[n] CLI param to Haddock executable It translates to `--ghcopt=-j[n]` - - - - - 84a04073 by Alex Biehl at 2021-01-09T12:14:41+01:00 Abstract Monad for interface creation I found that when running as a plugin the lookupName function (which runs in Ghc monad) does not work correctly from the typeCheckResultAction hook. Instead, we abstracted the monad used when creating interfaces, so that access to GHC session specific parts is explicit and so that the TcM can provide their (correct) implementation of lookupName. - - - - - 5be2c4f7 by Alex Biehl at 2021-01-09T12:14:41+01:00 Accept tests - - - - - 8cefee9d by Alex Biehl at 2021-01-09T16:10:47+01:00 Add missing dependency for mtl - - - - - 3681f919 by Ben Gamari at 2021-01-13T18:39:25-05:00 Merge remote-tracking branch 'origin/ghc-9.0' into ghc-head - - - - - 33c6b152 by Hécate Moonlight at 2021-01-14T16:04:20+01:00 Merge pull request haskell/haddock#1273 from hsyl20/wip/hsyl20/arrows Fix after binder collect changes - - - - - 70d13e8e by Joachim Breitner at 2021-01-22T19:03:45+01:00 Make haddock more robust to changes to the `Language` data type With the introduction of GHC2021, the `Languages` data type in GHC will grow. In preparation of that (and to avoid changing haddock with each new language), this change makes the code handle extensions to that data type gracefully. (cherry picked from commit c341dd7c9c3fc5ebc83a2d577c5a726f3eb152a5) - - - - - 7d6dd57a by John Ericson at 2021-01-22T22:02:02+00:00 Add `NoGhcTc` instance now that it's not closed - - - - - e5fdaf0a by Alan Zimmerman at 2021-01-23T22:57:44+00:00 Merge pull request haskell/haddock#1293 from obsidiansystems/wip/fix-18936 Add `NoGhcTc` instance now that it's not closed - - - - - 989a1e05 by Oleg Grenrus at 2021-01-24T16:11:46+03:00 Add import list to Data.List - - - - - 368e144a by Ben Gamari at 2021-01-28T22:15:48+01:00 Adapt to "Make PatSyn immutable" - - - - - abe66c21 by Alfredo Di Napoli at 2021-02-01T08:05:35+01:00 Rename pprLogErrMsg to new name - - - - - e600e75c by Hécate Moonlight at 2021-02-05T14:53:00+01:00 Move CI to ghc-9.0 - - - - - dd492961 by Vladislav Zavialov at 2021-02-05T14:53:00+01:00 Update cabal.project and README build instructions - - - - - 31bd292a by Hécate Moonlight at 2021-02-05T15:03:56+01:00 Merge pull request haskell/haddock#1296 from Kleidukos/ghc-9.0 Merge the late additions to ghc-8.10 into ghc-9.0 - - - - - 6388989e by Vladislav Zavialov at 2021-02-05T17:41:57+03:00 Cleanup: fix build warnings - - - - - f99407ef by Daniel Rogozin at 2021-02-05T18:11:48+03:00 type level characters support for haddock (required for haskell/haddock#11342) - - - - - d8c6b26f by Hécate Moonlight at 2021-02-05T17:44:50+01:00 Add a CONTRIBUTING.md file - - - - - 6a01ad98 by Hécate Moonlight at 2021-02-05T17:58:16+01:00 Merge pull request haskell/haddock#1312 from Kleidukos/proper-branch-etiquette Add a CONTRIBUTING.md file - - - - - 955eecc4 by Vladislav Zavialov at 2021-02-05T20:29:00+03:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into ghc-head - - - - - 47b3d6ab by Hécate Moonlight at 2021-02-05T19:09:38+01:00 Amend the CONTRIBUTING.md file - - - - - 23de6137 by Hécate Moonlight at 2021-02-05T19:16:49+01:00 Merge pull request haskell/haddock#1313 from Kleidukos/amend-contributing Amend the CONTRIBUTING.md file - - - - - 69026b59 by Krzysztof Gogolewski at 2021-02-05T23:05:56+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. (cherry picked from commit b4b4d896d2d68d6c48e7db7bfe95c185ca0709cb) - - - - - ea026b78 by Oleg Grenrus at 2021-02-06T17:14:45+01:00 Add import list to Data.List - - - - - 5204326f by Hécate Moonlight at 2021-02-06T17:15:44+01:00 Merge pull request haskell/haddock#1316 from Kleidukos/explicit-imports-to-data-list Add import list to Data.List - - - - - 1f4d2136 by Ben Gamari at 2021-02-06T11:53:31-05:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ghc-head-merge - - - - - 13f0d09a by Ben Gamari at 2021-02-06T11:53:45-05:00 Fix partial record selector warning - - - - - 5c115f7e by Ben Gamari at 2021-02-06T11:55:52-05:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into wip/ghc-head-merge - - - - - b6fd8b75 by Ben Gamari at 2021-02-06T12:01:31-05:00 Merge commit '41964cb2fd54b5a10f8c0f28147015b7d5ad2c02' into wip/ghc-head-merge - - - - - a967194c by Ben Gamari at 2021-02-06T18:30:35-05:00 Merge branch 'wip/ghc-head-merge' into ghc-head - - - - - 1f4c3a91 by MorrowM at 2021-02-07T01:52:33+02:00 Fix search div not scrolling - - - - - 684b1287 by Iñaki García Etxebarria at 2021-02-07T16:13:04+01:00 Add support for labeled module references Support a markdown-style way of annotating module references. For instance -- | [label]("Module.Name#anchor") will create a link that points to the same place as the module reference "Module.Name#anchor" but the text displayed on the link will be "label". - - - - - bdb55a5d by Hécate Moonlight at 2021-02-07T16:18:10+01:00 Merge pull request haskell/haddock#1319 from alexbiehl/alex/compat Backward compat: Add support for labeled module references - - - - - 6ca70991 by Hécate Moonlight at 2021-02-07T16:21:29+01:00 Merge pull request haskell/haddock#1314 from tweag/show-linear-backport Backport haskell/haddock#1238 (linear types) to ghc-9.0 - - - - - d9d73298 by Alex Biehl at 2021-02-07T17:46:25+01:00 Remove dubious parseModLink Instead construct the ModLink value directly when parsing. - - - - - 33b4d020 by Hécate Moonlight at 2021-02-07T17:52:05+01:00 Merge pull request haskell/haddock#1320 from haskell/alex/fix Remove dubious parseModLink - - - - - 54211316 by Hécate Moonlight at 2021-02-07T18:12:07+01:00 Merge pull request haskell/haddock#1318 from MorrowM/ghc-9.0 Fix search div not scrolling - - - - - 19db679e by alexbiehl-gc at 2021-02-07T18:14:46+01:00 Merge pull request haskell/haddock#1317 from bgamari/wip/ghc-head-merge Merge ghc-8.10 into ghc-head - - - - - 6bc1e9e4 by Willem Van Onsem at 2021-02-07T18:25:30+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - c8537cf8 by alexbiehl-gc at 2021-02-07T18:30:40+01:00 Merge pull request haskell/haddock#1322 from haskell/alex/forward-port simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 2d47ae4e by alexbiehl-gc at 2021-02-07T18:39:59+01:00 Merge branch 'ghc-head' into ghc-9.0 - - - - - 849e4733 by Hécate Moonlight at 2021-02-07T18:43:19+01:00 Merge pull request haskell/haddock#1321 from Kleidukos/ghc-9.0 Merge ghc-9.0 into ghc-head - - - - - ee6095d7 by Sylvain Henry at 2021-02-08T11:36:38+01:00 Update for Logger - - - - - 4ad688c9 by Alex Biehl at 2021-02-08T18:11:24+01:00 Merge pull request haskell/haddock#1310 from hsyl20/wip/hsyl20/logger2 Logger refactoring - - - - - 922a9e0e by Ben Gamari at 2021-02-08T12:54:33-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - 991649d2 by Sylvain Henry at 2021-02-09T10:55:17+01:00 Fix to build with HEAD - - - - - a8348dc2 by Hécate Moonlight at 2021-02-09T10:58:51+01:00 Merge pull request haskell/haddock#1327 from hsyl20/wip/hsyl20/logger2 Fix to build with HEAD - - - - - 0abdbca6 by Fendor at 2021-02-09T20:06:15+01:00 Add UnitId to Target record - - - - - d5790a0e by Alex Biehl at 2021-02-11T10:32:32+01:00 Stable sort for (data/newtype) instances - - - - - 8e6036f5 by Alex Biehl at 2021-02-11T10:32:32+01:00 Also make TyLit deterministic - - - - - f76d2945 by Hécate Moonlight at 2021-02-11T11:00:31+01:00 Merge pull request haskell/haddock#1329 from hsyl20/hsyl20/stabe_iface Stable sort for instances - - - - - 5e0469ea by Oleg Grenrus at 2021-02-14T15:28:15+02:00 Add import list to Data.List in Haddock.Interface.Create - - - - - fa57cd24 by Hécate Moonlight at 2021-02-14T17:19:27+01:00 Merge pull request haskell/haddock#1331 from phadej/more-explicit-data-list-imports Add import list to Data.List in Haddock.Interface.Create - - - - - f0cd629c by Hécate Moonlight at 2021-02-21T00:22:01+01:00 Merge pull request haskell/haddock#1311 from fendor/wip/add-targetUnitId-to-target Add UnitId to Target record - - - - - 674ef723 by Joachim Breitner at 2021-02-22T10:39:18+01:00 html-test: Always set language from ghc-9.2 on, the “default” langauge of GHC is expected to change more wildly. To prepare for that (and unblock https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4853), this sets the language for all the test files to `Haskell2010`. This should insolate this test suite against changes to the default. Cherry-picked from https://github.com/haskell/haddock/pull/1341 - - - - - f072d623 by Hécate Moonlight at 2021-02-22T10:56:51+01:00 Merge pull request haskell/haddock#1342 from nomeata/joachim/haskell2010-in-tests-ghc-head html-test: Always set language - - - - - caebbfca by Hécate Moonlight at 2021-02-22T11:53:07+01:00 Clean-up of Interface and Interface.Create's imports and pragmata - - - - - f6caa89d by Hécate Moonlight at 2021-02-22T11:54:58+01:00 Merge pull request haskell/haddock#1345 from Kleidukos/head/fix-interface-imports [ghc-head] Clean-up of Interface and Interface.Create's imports and pragmata - - - - - 7395c9cb by Hécate Moonlight at 2021-02-22T18:44:57+01:00 Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 6e9fb5d5 by Hécate Moonlight at 2021-02-22T18:45:28+01:00 Merge pull request haskell/haddock#1348 from Kleidukos/head/explicit-imports-interface Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 9198b118 by Alan Zimmerman at 2021-02-22T20:04:24+00:00 Context becomes a Maybe in the GHC AST This prevents noLoc's appearing in the ParsedSource. Match the change in GHC. - - - - - 0af20f64 by Hécate Moonlight at 2021-02-23T12:36:12+01:00 Fix the call-site of guessTarget in Interface.hs Explicit the imports from GHC.HsToCore.Docs - - - - - b7886885 by Hécate Moonlight at 2021-02-23T12:37:54+01:00 Merge pull request haskell/haddock#1349 from Kleidukos/fix-interface-guesstarget-call Fix the call-site of guessTarget in Interface.hs - - - - - 9cf041ba by Sylvain Henry at 2021-02-24T11:08:20+01:00 Fix haddockHypsrcTest output in ghc-head - - - - - b194182a by Hécate Moonlight at 2021-02-24T11:12:36+01:00 Merge pull request haskell/haddock#1351 from hsyl20/wip/hsyl20/fix-head Fix haddockHypsrcTest output in ghc-head - - - - - 3ce8b375 by Shayne Fletcher at 2021-03-06T09:55:03-05:00 Add ITproj to parser - - - - - d2abf762 by Ben Gamari at 2021-03-06T19:26:49-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a0f6047d by Andrew Martin at 2021-03-07T11:25:23-05:00 Update for boxed rep - - - - - 6f63c99e by Ben Gamari at 2021-03-10T13:20:21-05:00 Update for "FastString: Use FastMutInt instead of IORef Int" - - - - - e13f01df by Luke Lau at 2021-03-10T15:38:40-05:00 Implement template-haskell's putDoc This catches up to GHC using the new extractTHDocs function, which returns documentation added via the putDoc function (provided it was compiled with Opt_Haddock). Since it's already a map from names -> docs, there's no need to do traversal etc. It also matches the change from the argument map being made an IntMap rather than a Map Int - - - - - 89263d94 by Alan Zimmerman at 2021-03-15T17:15:26+00:00 Match changes in GHC AST for in-tree API Annotations As landed via https://gitlab.haskell.org/ghc/ghc/-/merge_requests/2418 - - - - - 28db1934 by Alan Zimmerman at 2021-03-15T20:40:09+00:00 Change some type family test results. It is not clear to me whether the original was printing incorrectly (since we did not have the TopLevel flag before now), or if this behaviour is expected. For the time being I am assuming the former. - - - - - 7c11c989 by Sylvain Henry at 2021-03-22T10:05:19+01:00 Fix after NameCache changes - - - - - addbde15 by Sylvain Henry at 2021-03-22T10:05:19+01:00 NameCache doesn't store a UniqSupply anymore - - - - - 15ec6cec by Ben Gamari at 2021-03-22T17:53:44-04:00 Bump GHC version to 9.2 - - - - - dbd6aa63 by Hécate Moonlight at 2021-03-24T14:28:36+01:00 Merge pull request haskell/haddock#1365 from hsyl20/wip/hsyl20/iface1 NameCache refactoring - - - - - 2d32da7e by Oleg Grenrus at 2021-03-27T01:12:00+02:00 Specialization of Data.List - - - - - 32b84fa6 by Fendor at 2021-03-27T10:50:17+01:00 Add UnitId to Target record This way we always know to which home-unit a given target belongs to. So far, there only exists a single home-unit at a time, but it enables having multiple home-units at the same time. - - - - - 54bf9f0e by Hécate Moonlight at 2021-03-28T14:08:35+02:00 Merge pull request haskell/haddock#1368 from fendor/target-unit-id-revert Add UnitId to Target record - - - - - 7dea168a by Alan Zimmerman at 2021-03-29T08:45:52+01:00 EPA : Rename ApiAnn to EpAnn - - - - - 72967f65 by Alfredo Di Napoli at 2021-03-29T09:47:01+02:00 pprError changed name in GHC - - - - - 4bc61035 by Alan Zimmerman at 2021-03-29T16:16:27-04:00 EPA : Rename ApiAnn to EpAnn - - - - - 108d031d by Ben Gamari at 2021-03-29T18:49:36-04:00 Merge commit '36418c4f70d7d2b179a77925b3ad5caedb08c9b5' into HEAD - - - - - 1444f700 by Ben Gamari at 2021-03-31T09:18:39-04:00 Merge pull request haskell/haddock#1370 from adinapoli/wip/adinapoli-diag-reason-severity Rename pprError to mkParserErr - - - - - d3087b79 by Ben Gamari at 2021-03-31T11:34:17-04:00 Merge commit 'd8d8024ad6796549a8d3b5512dabf3288d14e30f' into ghc-head - - - - - 170b79e9 by Ben Gamari at 2021-03-31T12:24:56-04:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - db0d6bae by Ben Gamari at 2021-04-10T09:34:35-04:00 Bump GHC version to 9.3 - - - - - a9f2c421 by Alan Zimmerman at 2021-04-19T18:26:46-04:00 Update for EPA changes in GHC (cherry picked from commit cafb48118f7c111020663776845897e225607b41) - - - - - 1ee4b7c7 by Sylvain Henry at 2021-05-11T10:00:06+02:00 Removal of HsVersions.h (#1388) * Update for EPA changes in GHC * Account for HsVersions.h removal Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 79e819e9 by Hécate Moonlight at 2021-05-11T10:14:47+02:00 Revert "Removal of HsVersions.h (#1388)" This reverts commit 72118896464f94d81f10c52f5d9261efcacc57a6. - - - - - 3dbd3f8b by Alan Zimmerman at 2021-05-11T10:15:17+02:00 Update for EPA changes in GHC - - - - - 2ce80c17 by Sylvain Henry at 2021-05-11T10:15:19+02:00 Account for HsVersions.h removal - - - - - 00e4c918 by Christiaan Baaij at 2021-05-13T08:21:56+02:00 Add Haddock support for the OPAQUE pragma (#1380) - - - - - 8f9049b2 by Hécate Moonlight at 2021-05-13T08:40:22+02:00 fixup! Use GHC 9.2 in CI runner - - - - - 27ddec38 by Alan Zimmerman at 2021-05-13T22:51:20+01:00 EPA: match changes from GHC T19834 - - - - - f8a1d714 by Felix Yan at 2021-05-14T17:10:04+02:00 Allow hspec 2.8 (#1389) All tests are passing. - - - - - df44453b by Divam Narula at 2021-05-20T15:42:42+02:00 Update ref, the variables got renamed. (#1391) This is due to ghc/ghc!5555 which caused a change in ModDetails in case of NoBackend. Now the initModDetails is used to recreate the ModDetails from interface and in-memory ModDetails is not used. - - - - - e46bfc87 by Alan Zimmerman at 2021-05-20T19:05:09+01:00 Remove Maybe from HsQualTy Match changes in GHC for haskell/haddock#19845 - - - - - 79bd7b62 by Shayne Fletcher at 2021-05-22T08:20:39+10:00 FieldOcc: rename extFieldOcc to foExt - - - - - 6ed68c74 by Ben Gamari at 2021-05-21T22:29:30-04:00 Merge commit '3b6a8774bdb543dad59b2618458b07feab8a55e9' into ghc-head - - - - - f9a02d34 by Alfredo Di Napoli at 2021-05-24T13:53:00+02:00 New Parser diagnostics interface - - - - - 392807d0 by Ben Gamari at 2021-05-24T09:57:40-04:00 Merge pull request haskell/haddock#1394 from adinapoli/wip/adinapoli-align-ps-messages Align Haddock to use the new Parser diagnostics interface - - - - - 33023cd8 by Ben Gamari at 2021-05-24T11:19:16-04:00 Revert "Add Haddock support for the OPAQUE pragma (#1380)" This reverts commit a1337c599ef7720b0482a25c55f11794112496dc. The GHC patch associated with this change is not yet ready to be merged. - - - - - 8c005af7 by Ben Simms at 2021-05-28T07:56:20+02:00 CI configuration for ghc-head (#1395) - - - - - 1e947612 by Hécate Moonlight at 2021-05-28T12:27:35+02:00 Use GHC 9.2 in CI runner (#1378) - - - - - e6fa10ab by CGenie at 2021-05-31T09:02:13+02:00 Add page about common errors (#1396) * Update index.rst Common errors page * Create common-errors.rst * Update common-errors.rst * Use GHC 9.2 in CI runner (#1378) * [haddock-api] remove .hspec-failures Co-authored-by: Hécate Moonlight <Kleidukos at users.noreply.github.com> - - - - - abc72a8d by Sylvain Henry at 2021-06-01T10:02:06+02:00 Adapt Haddock to Logger and Parser changes (#1399) - - - - - 91373656 by Zubin Duggal at 2021-06-01T20:45:10+02:00 Update haddockHypSrc tests since we now compute slighly more type info (#1397) - - - - - ed712822 by Marcin Szamotulski at 2021-06-02T08:54:33+02:00 Added myself to contributors - - - - - 49fdbcb7 by Marcin Szamotulski at 2021-06-02T08:57:24+02:00 Document multi component support - - - - - 9ddc8d7d by Hécate Moonlight at 2021-06-02T09:35:55+02:00 Merge pull request haskell/haddock#1379 from coot/coot/document-multi-component-support Document multi component support - - - - - 585b5c5e by Ben Simms at 2021-06-02T19:46:54+02:00 Update CONTRIBUTING.md (#1402) - - - - - 1df4a605 by Ben Simms at 2021-06-02T19:47:14+02:00 Update CONTRIBUTING.md (#1403) - - - - - 58ea43d2 by sheaf at 2021-06-02T22:09:06+02:00 Update Haddock Bug873 to account for renaming - - - - - c5d0ab23 by Vladislav Zavialov at 2021-06-10T13:35:42+03:00 HsToken in FunTy, RecConGADT - - - - - 1ae2f40c by Hécate Moonlight at 2021-06-11T11:19:09+02:00 Update the CI badges - - - - - 6fdc4de2 by Sylvain Henry at 2021-06-28T19:21:17+02:00 Fix mkParserOpts (#1411) - - - - - 18201670 by Alfredo Di Napoli at 2021-07-05T07:55:12+02:00 Rename getErrorMessages Lexer import This commit renames the Lexer import in `Hyperlinker.Parser` from `getErrorMessages` to `getPsErrorMessages` to eliminate the ambiguity with the `getErrorMessages` function defined in `GHC.Types.Error`. - - - - - 23173ca3 by Ben Gamari at 2021-07-07T11:31:44-04:00 Merge pull request haskell/haddock#1413 from adinapoli/wip/adinapoli-issue-19920 Rename getErrorMessages Lexer import - - - - - b3dc4ed8 by Alan Zimmerman at 2021-07-28T22:30:59+01:00 EPA: match changes from GHC T19834 (cherry picked from commit 2fec1b44e0ee7e263286709aa528b4ecb99ac6c2) - - - - - 5f177278 by Ben Gamari at 2021-08-06T01:17:37-04:00 Merge commit '2a966c8ca37' into HEAD - - - - - cdd81d08 by Marcin Szamotulski at 2021-08-08T17:19:06+02:00 coot/multiple packages (ghc-9.2) (#1418) - - - - - be0d71f1 by Marcin Szamotulski at 2021-08-16T08:46:03+02:00 coot/multiple package (ghc-head) (#1419) * FromJSON class Aeson style FromJSON class with Parsec based json parser. * doc-index.json file for multiple packages When creating haddock summary page for multiple packages render doc-index.json file using contents of all found 'doc-index.json' files. * Render doc-index.json When rendering html, render doc-index.json file independently of maybe_index_url option. doc-index.json file is useful now even if maybe_index_url is not `Nothing`. * base url option New `Flag_BaseURL` which configures from where static files are loaded (--base-url). If given and not equal "." static files are not coppied, as this indicates that they are not read from the the directory where we'd copy them. The default value is ".". - - - - - 3b09dbdf by Hécate Moonlight at 2021-10-07T23:26:03+02:00 Update GHC 9.2 to latest pre-release in CI - - - - - 7ac55417 by Zubin Duggal at 2021-10-11T12:10:19+02:00 Enable Haddock tests in GHC windows CI (#1428) * testsuite: strip windows line endings for haddock * hyperlinker: Work around double escaping (#19236) * deterministic SCC - - - - - 1cb81f25 by Andrew Lelechenko at 2021-10-12T15:23:19+02:00 haddock-library does not depend on bytestring or transformers (#1426) - - - - - a890b9aa by sheaf at 2021-10-15T22:19:42+02:00 update haddockHypsrcTest for GHC MR !6705 (#1430) - - - - - 42a55c6c by Sylvain Henry at 2021-10-15T22:20:10+02:00 Fix after PkgQual refactoring (#1429) - - - - - 91659238 by Alan Zimmerman at 2021-10-28T18:57:10+01:00 Update for changes in GHC for branch wip/az/no-srcspan-anno-instances - - - - - acf23e60 by Vladislav Zavialov at 2021-11-05T02:09:47+03:00 Do not use forall as an identifier See GHC ticket haskell/haddock#20609 - - - - - c565db0e by Krzysztof Gogolewski at 2021-11-27T02:42:35+01:00 Update after NoExtCon -> DataConCantHappen rename - - - - - b5f55590 by Artem Pelenitsyn at 2021-11-27T11:14:17+01:00 fix CI for 9.2 (#1436) - - - - - 25cd621e by Matthew Pickering at 2021-12-02T11:46:54+00:00 Update html-test for Data.List revert - - - - - 1d5ff85f by malteneuss at 2021-12-15T07:56:55+01:00 Add hint about inline link issue (#1444) - - - - - 791fde81 by Sylvain Henry at 2021-12-16T09:29:51+01:00 Bump ghc-head (#1445) * Update after NoExtCon -> DataConCantHappen rename * Update html-test for Data.List revert * Fix for new Plugins datatype Co-authored-by: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 44236317 by Sylvain Henry at 2021-12-17T09:39:00+01:00 Fix for new Plugins datatype - - - - - 80ada0fa by Hécate Moonlight at 2021-12-17T17:28:48+01:00 Remove ghc-head workflow (#1446) Contributions of GHC glue code are now done on the GHC gitlab, not in the GitHub repo anymore. - - - - - 49e171cd by Matthew Pickering at 2021-12-28T09:47:09+00:00 Remove use of ExtendedModSummary - - - - - 0e91b5ea by askeblad at 2022-01-04T09:18:35+01:00 update URLs - - - - - 9f13c212 by Hécate Moonlight at 2022-02-25T10:19:46+01:00 Fix solver for GHC 9.2 - - - - - 386751a1 by Meng Weng Wong at 2022-02-25T19:19:11+01:00 IDoc link has bitrotted; replaced with web.archive.org cache. (#1454) - - - - - d877cbe6 by Hécate Moonlight at 2022-02-25T19:21:58+01:00 Fix haddock user guide (#1456) - - - - - cc47f036 by Andrew Lelechenko at 2022-03-04T17:29:36+01:00 Allow text-2.0 in haddock-library (#1459) - - - - - 7b3685a3 by malteneuss at 2022-03-07T19:27:24+01:00 Add multi-line style hint to style section (#1460) - - - - - c51088b8 by John Ericson at 2022-03-11T16:46:26+01:00 Fix CollectPass instance to match TTG refactor Companion to GHC !7614 (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7614) - - - - - b882195b by Vladislav Zavialov at 2022-03-14T20:32:30+01:00 Link to (~) - - - - - 877349b8 by Christiaan Baaij at 2022-03-16T09:20:43+01:00 Add Haddock support for the OPAQUE pragma - - - - - 0ea22721 by askeblad at 2022-03-16T09:44:27+01:00 typos (#1464) - - - - - a6d13da1 by Matthew Pickering at 2022-03-22T13:41:17+00:00 Minimum changes needed for compilation with hi-haddock With hi-haddock, of course there is a much large refactoring of haddock which could be achieved but that is left for a future patch which can implemented at any time independently of GHC. - - - - - e7ac9129 by Matthew Pickering at 2022-03-22T21:17:50+00:00 Update test output - - - - - 6d916214 by Matthew Pickering at 2022-03-24T15:06:26+00:00 Merge branch 'wip/opaque_pragma' into 'ghc-head' Add Haddock support for the OPAQUE pragma See merge request ghc/haddock!2 - - - - - 42208183 by Steve Hart at 2022-03-25T20:43:50+01:00 Fix CI (#1467) * CI: Reinstall GHC with docs CI tests were failing because the GHC preinstalled to the CI environment does not include documentation, which is required for running the Haddock tests. This commit causes the CI workflow to reinstall GHC with docs so that tests can succeed. - - - - - 9676fd79 by Steve Hart at 2022-03-25T21:33:34+01:00 Make links in Synopsis functional again (#1458) Commit e41c1cbe9f0476997eac7b4a3f17cbc6b2262faf added a call to e.preventDefault() when handling click events that reach a toggle element. This prevents the browser from following hyperlinks within the Synopsis section when they are clicked by a user. This commit restores functioning hyperlinks within the Synopsis section by removing the call to e.preventDefault(), as it does not appear to be necessary, and removing it increases the flexibility of the details-helper code. - - - - - d1edd637 by sheaf at 2022-04-01T12:02:02+02:00 Keep track of promotion ticks in HsOpTy Keeping track of promotion ticks in HsOpTy allows us to properly pretty-print promoted constructors such as lists. - - - - - 9dcb2dfc by Jakob Brünker at 2022-04-01T15:46:22+00:00 Add support for \cases See merge request ghc/ghc!7873 - - - - - b0412ee5 by askeblad at 2022-04-06T17:47:57+02:00 spelling errors (#1471) - - - - - 6b18829b by Vladislav Zavialov at 2022-04-06T18:53:58+02:00 Rename [] to List - - - - - 2d046691 by Vladislav Zavialov at 2022-04-07T20:25:54+03:00 HsToken ConDeclGADT con_dcolon - - - - - 90b43da4 by Steve Hart at 2022-04-12T13:29:46+02:00 Parse Markdown links at beginning of line within a paragraph (#1470) * Catch Markdown links at beginning of line within paragraph Per Issue haskell/haddock#774, Markdown links were being parsed as ordinary text when they occurred at the beginning of a line other than the first line of the paragraph. This occurred because the parser was not interpreting a left square bracket as a special character that could delimit special markup. A space character was considered a special character, so, if a space occurred at the beginning of the new line, then the parser would interpret the space by itself and then continue parsing, thereby catching the Markdown link. '\n' was not treated as a special character, so the parser did not catch a Markdown link that may have followed. Note that this will allow for Markdown links that are not surrounded by spaces. For example, the following text includes a Markdown link that will be parsed: Hello, world[label](url) This is consistent with how the parser handles other types of markup. * Remove obsolete documentation hint Commit 6b9aeafddf20efc65d3725c16e3fc43a20aac343 should eliminate the need for the workaround suggested in the documentation. - - - - - 5b08312d by Hécate Moonlight at 2022-04-12T13:36:38+02:00 Force ghc-9.2 in the cabal.project - - - - - 0d0ea349 by dependabot[bot] at 2022-04-12T13:57:41+02:00 Bump path-parse from 1.0.5 to 1.0.7 in /haddock-api/resources/html (#1469) Bumps [path-parse](https://github.com/jbgutierrez/path-parse) from 1.0.5 to 1.0.7. - [Release notes](https://github.com/jbgutierrez/path-parse/releases) - [Commits](https://github.com/jbgutierrez/path-parse/commits/v1.0.7) --- updated-dependencies: - dependency-name: path-parse dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 2b9fc65e by dependabot[bot] at 2022-04-12T13:57:54+02:00 Bump copy-props from 2.0.4 to 2.0.5 in /haddock-api/resources/html (#1468) Bumps [copy-props](https://github.com/gulpjs/copy-props) from 2.0.4 to 2.0.5. - [Release notes](https://github.com/gulpjs/copy-props/releases) - [Changelog](https://github.com/gulpjs/copy-props/blob/master/CHANGELOG.md) - [Commits](https://github.com/gulpjs/copy-props/compare/2.0.4...2.0.5) --- updated-dependencies: - dependency-name: copy-props dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - ea98a6fb by Ben Gamari at 2022-04-23T22:54:37-04:00 Update for GHC 9.4 - - - - - 9e11864f by Ben Gamari at 2022-04-25T16:24:31-04:00 Merge remote-tracking branch 'upstream/ghc-9.2' into ghc-head - - - - - f83cc506 by Ben Gamari at 2022-04-25T17:00:25-04:00 Bump ghc version to 9.5 - - - - - e01c2e7d by Ben Gamari at 2022-04-28T16:19:04-04:00 Revert "Bump ghc-head (#1445)" This reverts commit b29a78ef6926101338f62e84f456dac8659dc9d2. This should not have been merged. - - - - - a2b5ee8c by Ben Gamari at 2022-04-28T16:19:24-04:00 Merge commit '2627a86c' into ghc-head - - - - - 0c6fe4f9 by Ben Gamari at 2022-04-29T10:05:54-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-9.4 - - - - - b6e5cb0a by Ben Gamari at 2022-04-29T11:46:06-04:00 Revert "HsToken ConDeclGADT con_dcolon" This reverts commit 24208496649a02d5f87373052c430ea4a97842c5. - - - - - 15a62888 by Ben Gamari at 2022-04-29T15:12:55-04:00 Bump base upper bound - - - - - 165b9031 by Ben Gamari at 2022-04-29T23:58:38-04:00 Update test output - - - - - e0c3e5da by Phil de Joux at 2022-05-02T14:46:38+02:00 Add hlint action .hlint.yaml with ignores & CPP. (#1475) - - - - - ead1158d by Raphael Das Gupta at 2022-05-02T14:46:48+02:00 fix grammar in docs: "can the" → "can be" (#1477) - - - - - cff97944 by Ben Gamari at 2022-05-02T18:38:56-04:00 Allow base-4.17 - - - - - e4ecb201 by Phil de Joux at 2022-05-03T13:14:55+02:00 Remove unused imports that GHC warned about. (#1480) - - - - - 222890b1 by Phil de Joux at 2022-05-03T13:15:46+02:00 Follow hlint suggestion to remove redundant bang. (#1479) - - - - - 058b671f by Phil de Joux at 2022-05-03T13:34:04+02:00 Follow hlint, remove language pragmas in libs. (#1478) - - - - - 0a645049 by Ben Simms at 2022-05-03T14:19:24+02:00 Keep track of ordered list indexes and render them (#1407) * Keep track of ordered list indexes and render them * Rename some identifiers to clarify - - - - - f0433304 by Norman Ramsey at 2022-05-04T15:13:34-04:00 update for changes in GHC API - - - - - 3740cf71 by Emily Martins at 2022-05-06T18:23:48+02:00 Add link to the readthedocs in cabal description to show on hackage. (cherry picked from commit 52e2d40d47295c02d3181aac0c53028e730f1e3b) - - - - - 5d754f1e by Hécate Moonlight at 2022-05-06T18:44:57+02:00 remove Bug873 - - - - - 968fc267 by Hécate Moonlight at 2022-05-06T18:48:28+02:00 Ignore "Use second" HLint suggestion. It increases laziness. - - - - - 02d14e97 by Jade Lovelace at 2022-05-07T17:42:08+02:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` - - - - - b22b87ed by Artem Pelenitsyn at 2022-05-08T16:19:47+02:00 fix parsing trailing quotes in backticked identifiers (#1408) (#1483) - - - - - 80ae107b by Alex Biehl at 2022-05-08T16:37:16+02:00 Fix "Defined by not used" error (cherry picked from commit 6e02a620a26c3a44f98675dd1b93b08070c36c0a) - - - - - 4c838e84 by Hécate Moonlight at 2022-05-08T16:37:16+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - fc9827b4 by Hécate Moonlight at 2022-05-08T16:40:40+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - b153b555 by Xia Li-yao at 2022-05-20T17:52:42+02:00 Hide synopsis from search when hidden (#1486) Fix haskell/haddock#1451 - - - - - f3e38b85 by Marcin Szamotulski at 2022-05-21T23:32:31+02:00 Allow to hide interfaces when rendering multiple components (#1487) This is useful when one wishes to `--gen-contents` when rendering multiple components, but one does not want to render all modules. This is in particular useful when adding base package. - - - - - f942863b by Marcin Szamotulski at 2022-05-24T08:29:59+02:00 Check if doc-index.json exists before reading it (#1488) - - - - - 31e92982 by Marcin Szamotulski at 2022-05-25T16:22:13+02:00 Version bump 2.26.1 (#1489) * Version bump 2.26.1 We extended format accepted by `--read-interface` option, which requires updating the minor version. * Update documentation of --read-interface option - - - - - 7cc873e0 by sheaf at 2022-05-25T16:42:31+02:00 Updated HaddockHypsrcTest output for record update changes (MR !7981) - - - - - cd196942 by Marcin Szamotulski at 2022-05-25T20:28:47+02:00 Use visibility to decide which interfaces are included in quickjump (#1490) This is also consistent with how html index is build. See haskell/cabal#7669 for rationale behind this decision. - - - - - 00c713c5 by Hécate Moonlight at 2022-05-26T17:09:15+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 2f3039f1 by Hécate Moonlight at 2022-05-26T17:10:59+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 63a5650c by romes at 2022-05-31T12:43:22+01:00 TTG: Match new GHC AST - - - - - dd7d1617 by romes at 2022-06-02T16:11:00+01:00 Update for IE changes in !8228 - - - - - c23aaab7 by cydparser at 2022-06-06T08:48:14+02:00 Fix and improve CI (#1495) * Pin GHC version before creating the freeze file * Use newest action versions * Improve caching * Avoid unnecessarily reinstalling GHC * Use GHC 9.2.2 for CI Co-authored-by: Cyd Wise <cwise at tripshot.com> - - - - - c156fa77 by Hécate Moonlight at 2022-06-06T11:59:35+02:00 Add Mergify configuration (#1496) - - - - - 2dba4188 by Hécate Moonlight at 2022-06-06T16:12:50+02:00 Bump haddock's version in cabal file to 2.26.1 (#1497) - - - - - d7d4b8b9 by Marcin Szamotulski at 2022-06-07T06:09:40+00:00 Render module tree per package in the content page (#1492) * Render module tree per package in the content page When rendering content page for multiple packages it is useful to split the module tree per package. Package names in this patch are inferred from haddock's interface file names. * Write PackageInfo into interface file To keep interface file format backward compatible, instead of using `Binary` instance for `InterfaceFile` we introduce functions to serialise and deserialise, which depends on the interface file version. - - - - - 77765665 by Mike Pilgrem at 2022-06-12T21:57:19+01:00 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - b0e079b0 by mergify[bot] at 2022-06-13T11:49:37+00:00 Merge pull request haskell/haddock#1108 from mpilgrem/fix783 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - 6c0292b1 by Hécate Moonlight at 2022-06-21T17:21:08+02:00 Update the contribution guide - - - - - e413b9fa by dependabot[bot] at 2022-06-21T23:38:19+02:00 Bump shell-quote from 1.6.1 to 1.7.3 in /haddock-api/resources/html (#1500) Bumps [shell-quote](https://github.com/substack/node-shell-quote) from 1.6.1 to 1.7.3. - [Release notes](https://github.com/substack/node-shell-quote/releases) - [Changelog](https://github.com/substack/node-shell-quote/blob/master/CHANGELOG.md) - [Commits](https://github.com/substack/node-shell-quote/compare/1.6.1...1.7.3) --- updated-dependencies: - dependency-name: shell-quote dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 29d0ef70 by romes at 2022-07-06T11:29:39+02:00 TTG: AST Updates for !8308 - - - - - 1bae7c87 by Alan Zimmerman at 2022-07-06T22:50:43+01:00 Match GHC changes for T21805 This brings in a newtype for FieldLabelString - - - - - 6fe8b988 by Phil de Joux at 2022-07-16T20:54:26+00:00 Bump hlint version to 3.4.1, the version with counts. (#1503) Redo the counts available with the --default option. - - - - - 48fb43af by Phil de Joux at 2022-07-19T09:32:55+02:00 Follow hlint suggestion: unused LANGUAGE pragma. (#1504) * Follow hlint suggestion: unused LANGUAGE pragma. * Ignore within modules to pass linting and pass tests. - - - - - c1cf1fa7 by Phil de Joux at 2022-07-24T13:45:59+02:00 Follow hlint suggestion: redundant $. (#1505) * Follow hlint suggestion: redundant $. * Remove $ and surplus blank lines in Operators. - - - - - 74777eb2 by Jade Lovelace at 2022-07-29T11:02:41+01:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` (cherry picked from commit ab53ccf089ea703b767581ac14be0f6c78a7678a) - - - - - faa4cfcf by Hécate Moonlight at 2022-07-29T20:31:20+02:00 Merge pull request haskell/haddock#1516 from duog/9-4-backport-fix-hyperlinks Backport 9-4: Fix hyperlinks to external items and modules (#1482) - - - - - 5d2450f3 by Ben Gamari at 2022-08-05T17:41:15-04:00 Merge remote-tracking branch 'origin/ghc-9.4' - - - - - 63954f73 by Ben Gamari at 2022-08-05T19:08:36-04:00 Clean up build and testsuite for GHC 9.4 - - - - - d4568cb8 by Hécate Moonlight at 2022-08-05T19:10:49-04:00 Bump the versions - - - - - 505583a4 by Ben Gamari at 2022-08-06T13:58:27-04:00 Merge pull request haskell/haddock#1518 from bgamari/wip/ghc-9.4-merge Merge GHC 9.4 into `main` - - - - - 5706f6a4 by Ben Gamari at 2022-08-06T22:57:21-04:00 html-test: Testsuite changes for GHC 9.4.1 - - - - - 5f2a45a2 by Ben Gamari at 2022-08-15T14:33:05-04:00 doc: Fix a few minor ReST issues Sphinx was complaining about too-short title underlines. - - - - - 220e6410 by Ben Gamari at 2022-08-15T14:41:24-04:00 Merge branch 'main' into ghc-head - - - - - fbeb1b02 by Ben Gamari at 2022-08-15T14:45:16-04:00 Updates for GHC 9.5 - - - - - eee562eb by Vladislav Zavialov at 2022-08-15T14:46:13-04:00 HsToken ConDeclGADT con_dcolon - - - - - c5f073db by Ben Gamari at 2022-08-15T16:55:35-04:00 Updates for GHC 9.5 - - - - - 3f7ab242 by Vladislav Zavialov at 2022-08-15T16:55:35-04:00 HsToken ConDeclGADT con_dcolon - - - - - a18e473d by Ben Gamari at 2022-08-16T08:35:19-04:00 Merge branch 'wip/ghc-head-bump' into ghc-head - - - - - af0ff3a4 by M Farkas-Dyck at 2022-09-15T21:16:05+00:00 Disuse `mapLoc`. - - - - - a748fc38 by Matthew Farkas-Dyck at 2022-09-17T10:44:18+00:00 Scrub partiality about `NewOrData`. - - - - - 2758fb6c by John Ericson at 2022-09-18T03:27:37+02:00 Test output changed because of change to `base` Spooky, but I guess that is intended? - - - - - a7eec128 by Torsten Schmits at 2022-09-21T11:06:55+02:00 update tests for the move of tuples to GHC.Tuple.Prim - - - - - 461e7b9d by Ross Paterson at 2022-09-24T22:01:25+00:00 match implementation of GHC proposal haskell/haddock#106 (Define Kinds Without Promotion) - - - - - f7fd77ef by sheaf at 2022-10-17T14:53:01+02:00 Update Haddock for GHC MR !8563 (configuration of diagnostics) - - - - - 3d3e85ab by Vladislav Zavialov at 2022-10-22T23:04:06+03:00 Class layout info - - - - - cbde4cb0 by Simon Peyton Jones at 2022-10-25T23:19:18+01:00 Adapt to Constraint-vs-Type See haskell/haddock#21623 and !8750 - - - - - 7108ba96 by Tom Smeding at 2022-11-01T22:33:23+01:00 Remove outdated footnote about module re-exports The footnote is invalid with GHC 9.2.4 (and possibly earlier): the described behaviour in the main text works fine. - - - - - 206c6bc7 by Hécate Moonlight at 2022-11-01T23:00:46+01:00 Merge pull request haskell/haddock#1534 from tomsmeding/patch-1 - - - - - a57b4c4b by Andrew Lelechenko at 2022-11-21T00:39:52+00:00 Support mtl-2.3 - - - - - e9d62453 by Simon Peyton Jones at 2022-11-25T13:49:12+01:00 Track small API change in TyCon.hs - - - - - eb1c73f7 by Ben Gamari at 2022-12-07T08:46:21-05:00 Update for GhC 9.6 - - - - - 063268dd by Ben Gamari at 2022-12-07T11:26:32-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 4ca722fe by Ben Gamari at 2022-12-08T14:43:26-05:00 Bump bounds to accomodate base-4.18 - - - - - 340b7511 by Vladislav Zavialov at 2022-12-10T12:31:28+00:00 HsToken in HsAppKindTy - - - - - 946226ec by Ben Gamari at 2022-12-13T20:12:56-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - fd8faa66 by Ben Gamari at 2022-12-22T13:44:28-05:00 Bump GHC version to 9.7 - - - - - 2958aa9c by Ben Gamari at 2022-12-22T14:49:16-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 9e0fefd8 by Andrei Borzenkov at 2023-01-30T14:02:04+04:00 Rename () to Unit, Rename (,,...,,) to Tuple<n> - - - - - eb3968b5 by Ben Gamari at 2023-03-10T02:32:43-05:00 Bump versions for ghc-9.6 release - - - - - 4aeead36 by Adam Gundry at 2023-03-23T13:53:47+01:00 Adapt to warning categories changes - - - - - 642d8d60 by sheaf at 2023-03-29T13:35:56+02:00 Adapt to record field refactor This commit adapts to the changes in GHC MR !8686, which overhauls the treatment of record fields in the renamer, adding separate record field namespaces and entirely removing the GreName datatype. - - - - - ac8d4333 by doyougnu at 2023-03-29T11:11:44-04:00 Update UniqMap API - - - - - 7866fc86 by Ben Orchard at 2023-04-20T11:29:33+02:00 update classify with new tokens - - - - - ffcdd683 by Finley McIlwaine at 2023-04-24T09:36:18-06:00 Remove index-state - - - - - 05b70982 by Finley McIlwaine at 2023-04-26T08:16:31-06:00 `renameInterface` space leak fixes - Change logic for accumulation of names for which link warnings will be generated - Change handling of `--ignore-link-symbol` to allow qualified and unqualified names. Added to CHANGES.md - Some formatting changes and comments here and there - - - - - e5697d7c by Finley McIlwaine at 2023-04-27T18:46:36-06:00 Messy things - ghc-debug dependency and instrumentation - cabal.project custom with-compiler - hie.yaml files - traces and such - - - - - 0b8ef80b by Finley McIlwaine at 2023-05-02T18:08:52-06:00 Stop retaining GRE closures GRE closures should never be necessary to Haddock, so we never want to keep them on the heap. Despite that, they are retained by a lot of the data structures that Haddock makes use of. - Attempt to fix that situation by adding strictness to various computations and pruning the `ifaceInstances` field of `Interface` to a much thinner data type. - Removes the `ifaceFamInstances` field, as it was never used. - Move some of the attach instances types (e.g. `SimpleType`) to the types module - - - - - 8bda991b by Finley McIlwaine at 2023-05-08T16:07:51-06:00 Memory usage fixes - Refactor `ifaceDeclMap` to drastically reduce memory footprint. We no longer store all declarations associated with a given name, since we only cared to determine if the only declaration associated with a name was a value declaration. Change the `DeclMap` type to better reflect this. - Drop pre-renaming export items after the renaming step. Since the Hoogle backend used the pre-renamed export items, this isn't trivial. We now generate Hoogle output for exported declarations during the renaming step (if Hoogle output /should/ be generated), and store that with the renamed export item. - Slightly refactor Hoogle backend to handle the above change and allow for early generation of Hoogle output. - Remove the `ifaceRnDocMap` and `ifaceRnArgMap` fields of the `Interface` type, as they were never used. - Remove some unnecessary strictness - Remove a lot of dead code from `Syb` module - - - - - 1611ac0c by Finley McIlwaine at 2023-05-09T11:51:57-06:00 Unify ErrMsgM and IfM - Delete ErrMsgM, stop accumulating warnings in a writer - Make IfM a state monad, print warnings directly to stdout, move IfM type into types module - Drop ErrMsg = String synonym - Unset IORefs from plugin after they are read, preventing unnecessary retention of interfaces - - - - - 42d696ab by Finley McIlwaine at 2023-05-11T15:52:07-06:00 Thunk leak fixes The strictness introduced in this commit was motivated by observing thunk leaks in the eventlog2html output. - Refactor attach instances list comprehension to avoid large intermediate thunks - Refactor some HTML backend list comprehensions to avoid large intermediate thunks - Avoid thunks accumulating in documentation types or documentation parser - A lot of orphan NFData instances to allow us to force documentation values - - - - - 68561cf6 by Finley McIlwaine at 2023-05-11T17:02:10-06:00 Remove GHC debug dep - - - - - 10519e3d by Finley McIlwaine at 2023-05-15T12:40:48-06:00 Force HIE file path Removes a potential retainer of `ModSummary`s - - - - - 1e4a6ec6 by Finley McIlwaine at 2023-05-15T14:20:34-06:00 Re-add index-state, with-compiler, delete hie.yamls - - - - - a2363fe9 by Hécate Moonlight at 2023-05-15T22:45:16+02:00 Merge pull request haskell/haddock#1594 from FinleyMcIlwaine/finley/ghc-9.6-mem-fixes Reduce memory usage - - - - - e8a78383 by Finley McIlwaine at 2023-05-17T12:19:16-06:00 Merge branch ghc-9.6 into ghc-head - - - - - 22e25581 by Finley McIlwaine at 2023-05-17T12:20:23-06:00 Merge branch 'ghc-head' of gitlab.haskell.org:ghc/haddock into ghc-head - - - - - 41bbf0df by Bartłomiej Cieślar at 2023-05-24T08:57:58+02:00 changes to the WarningTxt cases Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - c686ba9b by Hécate Moonlight at 2023-06-01T14:03:02-06:00 Port the remains of Hi-Haddock - - - - - 9d8a85fd by Hécate Moonlight at 2023-06-01T14:03:06-06:00 Stdout for tests - - - - - 36331d07 by Finley McIlwaine at 2023-06-01T14:06:02-06:00 Formatting, organize imports - - - - - a06059b1 by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix empty context confusion in Convert module - - - - - 379346ae by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix associated type families in Hoogle output - - - - - fc6ea7ed by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix test refs Accept several changes in Hoogle tests: Pretty printing logic no longer prints the `(Proxy (Proxy (...))` chain in Bug806 with parentheses. Since this test was only meant to verify that line breaks do not occur, accept the change. `tyThingToLHsDecl` is called for class and data declarations, which ends up "synifying" the type variables and giving unlifted types kind signatures. As a result, type variables of kind `Type -> Type` are now printed with kind signatures in Hoogle output. This could be changed by manually drop kind signatures from class variables in the Hoogle backend if the behavior is deemed unacceptable. Sometimes subordinate declarations are exported separate from their parent declarations (e.g. record selectors). In this case, a type signature is cobbled together for the export item in `extractDecl`. Since this type signature is very manually constructed, it may lack kind signatures of decls constructed from `tyThingToLHsDecl`. An example of this is the `type-sigs` Hoogle test. Change `*` to `Type` in Hoogle test refs. I don't think this will break Hoogle behavior, since it appears to not consider type signatures in search. I have not fully verified this. - - - - - e14b7e58 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix LaTeX backend test refs Changes to GHC pretty printing code have resulted in some differences to Haddock's LaTeX output. - Type variables are printed explicitly quantified in the LinearTypes test - Wildcard types in type family equations are now printed numbered, e.g. _1 _2, in the TypeFamilies3 test - Combined signatures in DefaultSignatures test are now documented as separate signatures - - - - - 41b5b296 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and test source updates - Stop using kind `*` in html test sources - Add TypeOperators where necessary to avoid warnings and future errors - Rename some test modules to match their module names - - - - - c640e2a2 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix missing deprecation warnings on record fields `lookupOccEnv` was used to resolve `OccNames` with warnings attached, but it doesn't look in the record field namespace. Thus, if a record field had a warning attached, it would not resolve and the warning map would not include it. This commit fixes by using `lookupOccEnv_WithFields` instead. - - - - - fad0c462 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and some comments - - - - - 751fd023 by Finley McIlwaine at 2023-06-01T14:11:41-06:00 Accept HTML test diffs All diffs now boil down to the expected differences resulting from declarations being reified from TyThings in hi-haddock. Surface syntax now has much less control over the syntax used in the documentation. - - - - - d835c845 by Finley McIlwaine at 2023-06-01T14:11:45-06:00 Adapt to new load' type - - - - - dcf776c4 by Finley McIlwaine at 2023-06-01T14:13:13-06:00 Update mkWarningMap and moduleWarning - - - - - 8e8432fd by Finley McIlwaine at 2023-06-01T14:28:54-06:00 Revert load' changes - - - - - aeb2982c by Finley McIlwaine at 2023-06-01T14:40:24-06:00 Accept change to Instances test in html-test Link to Data.Tuple instead of GHC.Tuple.Prim - - - - - 8adfdbac by Finley McIlwaine at 2023-06-01T15:53:17-06:00 Reset ghc dep to ^>= 9.6 - - - - - 2b1ce93d by Finley McIlwaine at 2023-06-06T07:50:04-06:00 Update CHANGES.md, user guide, recomp avoidance * Add --trace-args flag for tracing arguments received to standard output * Avoid recompiling due to changes in optimization flags * Update users guide and changes.md - - - - - f3da6676 by Finley McIlwaine at 2023-06-06T14:12:56-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - bf36c467 by Matthew Pickering at 2023-06-07T10:16:09+01:00 Revert back to e16e20d592a6f5d9ed1af17b77fafd6495242345 Neither of these MRs are ready to land yet which causes issues with other MRs which are ready to land and need haddock changes. - - - - - 421510a9 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 atSign has no unicode variant Prior to this change, atSign was defined as follows: atSign unicode = text (if unicode then "@" else "@") Yes, this is the same symbol '\64' and not your font playing tricks on you. Now we define: atSign = char '@' Both the LaTeX and the Xhtml backend are updated accordingly. - - - - - 3785c276 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 LaTeX: fix printing of type variable bindings Consider this type signature: kindOf :: forall {k} (a :: k). Proxy a -> Proxy k Prior to this fix, the LaTeX backend rendered it like this: kindOf :: forall k a. Proxy a -> Proxy k Now we preserve explicit specificity and kind annotations. - - - - - 0febf3a8 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 Add support for invisible binders in type declarations - - - - - 13e33bb3 by Finley McIlwaine at 2023-06-08T07:51:59-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - 3e5340ce by Finley McIlwaine at 2023-06-08T07:54:27-06:00 Add note about stubdir to recompilation docs - - - - - db7e84dc by Finley at 2023-06-08T08:11:03-06:00 Merge pull request haskell/haddock#1597 from haskell/finley/hi-haddock-9.6 hi-haddock for ghc 9.6 - - - - - 4e085d17 by Finley McIlwaine at 2023-06-14T13:41:06-06:00 Replace SYB traversals - - - - - 7b39aec5 by Finley McIlwaine at 2023-06-14T14:20:17-06:00 Test ref accepts, remove unused HaddockClsInst - - - - - df9c2090 by Finley McIlwaine at 2023-06-15T08:02:51-06:00 Use batchMsg for progress reporting during load With hi-haddock as is, there is an awkward silence during the load operation. This commit makes haddock use the default `batchMsg` Messager for progress reporting, and makes the default GHC verbosity level 1, so the user can see what GHC is doing. - - - - - f23679a8 by Hécate Moonlight at 2023-06-15T20:31:53+02:00 Merge pull request haskell/haddock#1600 from haskell/finley/hi-haddock-optim - - - - - a7982192 by Finley McIlwaine at 2023-06-15T15:02:16-06:00 hi-haddock squashed - - - - - c34f0c8d by Finley McIlwaine at 2023-06-15T16:22:03-06:00 Merge remote-tracking branch 'origin/ghc-9.6' into finley/hi-haddock-squashed - - - - - 40452797 by Bartłomiej Cieślar at 2023-06-16T12:26:04+02:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - e58673bf by Ben Gamari at 2023-06-16T09:33:35-04:00 Bump GHC version to 9.8 - - - - - 74bdf972 by Ben Gamari at 2023-06-16T09:36:18-04:00 Merge commit 'fcaaad06770a26d35d4aafd65772dedadf17669c' into ghc-head - - - - - 418ee3dc by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Remove NFData SourceText, IfaceWarnings updates The NFData SourceText instance is now available in GHC Handle mod_iface mi_warns now being IfaceWarnings - - - - - 62f31380 by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Accept Instances.hs test output Due to ghc!10469. - - - - - a8f2fc0e by Ben Gamari at 2023-06-20T15:48:08-04:00 Test fixes for "Fix associated data family doc structure items" Associated data families were being given their own export DocStructureItems, which resulted in them being documented separately from their classes in haddocks. This commit fixes it. - - - - - cb1ac33e by Bartłomiej Cieślar at 2023-06-21T12:56:02-04:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - 9933e10b by Ben Gamari at 2023-06-21T12:56:02-04:00 Bump GHC version to 9.8 - - - - - fe8c18b6 by Ben Gamari at 2023-06-21T15:36:29-04:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - c61a0d5b by Ben Gamari at 2023-06-21T16:10:51-04:00 Bump GHC version to 9.9 - - - - - 0c2a756e by sheaf at 2023-07-07T13:45:12+02:00 Avoid incomplete record update in Haddock Hoogle This commit avoids running into an incomplete record update warning in the Hoogle backend of Haddock. This was only noticed now, because incomplete record updates were broken in GHC 9.6. Now that they are fixed, we have to avoid running into them! - - - - - f9b952a7 by Ben Gamari at 2023-07-21T11:58:05-04:00 Bump base bound to <4.20 For GHC 9.8. - - - - - 1b27e151 by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Check for puns (see ghc#23368) - - - - - 457341fd by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Remove fake exports for (~), List, and Tuple<n> The old reasoning no longer applies, nowadays those names can be mentioned in export lists. - - - - - bf3dcddf by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Fix pretty-printing of Solo and MkSolo - - - - - 495b2241 by Matthew Pickering at 2023-09-01T13:02:07+02:00 Fix issue with duplicate reexported definitions (T23616) When a class method was reexported, it's default methods were also showing up in the generated html page. The simplest and most non-invasive fix is to not look for the default method if we are just exporting the class method.. because the backends are just showing default methods when the whole class is exported. In general it would be worthwhile to rewrite this bit of code I think as the logic and what gets included is split over `lookupDocs` and `availExportDecl` it would be clearer to combine the two. The result of lookupDocs is always just passed to availExportDecl so it seems simpler and more obvious to just write the function directly. - - - - - 6551824d by Finley McIlwaine at 2023-09-05T13:06:57-07:00 Remove fake export of `FUN` from Prelude This prevents `data FUN` from being shown at the top of the Prelude docs. Fixes \#23920 on GHC. - - - - - 9ab5a448 by Alan Zimmerman at 2023-09-08T18:26:53+01:00 Match changes in wip/az/T23885-unicode-funtycon - - - - - 4d08364e by Alan Zimmerman at 2023-10-31T19:46:45+00:00 EPA: match changes in GHC - EPA: Comments in AnchorOperation - EPA: Remove EpaEofComment - - - - - e7da0d25 by Alan Zimmerman at 2023-11-05T11:20:31+00:00 EPA: match changes in GHC, l2l cleanup - - - - - 4ceac14d by Alan Zimmerman at 2023-11-11T15:16:41+00:00 EPA: Replace Anchor with EpaLocation Match GHC - - - - - 94fb8d47 by Alan Zimmerman at 2023-11-29T18:10:26+00:00 Match GHC, No comments in EpaDelta for comments - - - - - 32d208e1 by Vladislav Zavialov at 2023-12-12T20:41:36+03:00 EPA: Match changes to LHsToken removal - - - - - eebdd316 by Apoorv Ingle at 2024-01-23T13:49:12+00:00 Changes for haskell/haddock#18324 - - - - - ae856a82 by Matthew Pickering at 2024-02-05T12:22:39+00:00 ghc-internals fallout - - - - - f8429266 by Jade at 2024-02-08T14:56:50+01:00 Adjust test for ghc MR !10993 - - - - - 6d1e2386 by Alan Zimmerman at 2024-02-13T22:00:28+03:00 EPA: Match changes to HsParTy and HsFunTy - - - - - 9c588f19 by Fendor at 2024-02-14T11:05:36+01:00 Adapt to GHC giving better Name's for linking - - - - - 778e1db3 by Andrei Borzenkov at 2024-02-16T16:12:07+03:00 Namespace specifiers for fixity signatures - - - - - 826c5b47 by Torsten Schmits at 2024-02-21T13:17:05+01:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 2cff14d5 by Ben Gamari at 2024-02-22T09:35:56-05:00 Bump bounds - - - - - f49376b3 by Ben Gamari at 2024-02-22T09:35:56-05:00 Allow `@since` annotations in export lists Here we extend Haddock to admit `@since` annotations in export lists. These can be attached to most export list items (although not subordinate lists). These annotations supercede the declaration's `@since` annotation in produced Haddocks. - - - - - b5aa93df by Ben Gamari at 2024-02-22T12:09:06-05:00 Allow package-qualified @since declarations - - - - - 8f5957f2 by Ben Gamari at 2024-02-22T13:55:19-05:00 Documentation changes from ghc-internal restructuring Previously many declarations (e.g. `Int`) were declared to have a "home" in `Prelude`. However, now Haddock instead chooses to put these in more specific homes (e.g. `Data.Int`). Given that the "home" decision is driven by heuristics and in general these changes seem quite reasonable I am accepting them: * `Int` moved from `Prelude` to `Data.Int` * `(~)` moved from `Prelude` to `Data.Type.Equality` * `Type` moved from `GHC.Types` to `Data.Kind` * `Maybe` moved from `Prelude` to `Data.Maybe` * `Bool` moved from `Prelude` to `Data.Bool` * `Ordering` moved from `Prelude` to `Data.Ord` As well, more identifiers are now hyperlinked; it's not immediately clear *why*, but it is an improvement nevertheless. - - - - - ec33fec3 by Ben Gamari at 2024-02-22T20:36:24-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 30cfd251 by Torsten Schmits at 2024-02-24T13:00:42-05:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 732db81d by Ben Gamari at 2024-02-24T19:12:18-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 86bf7010 by Ben Gamari at 2024-02-27T19:28:10-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 4b6e76b5 by Patrick at 2024-03-07T22:09:30+08:00 fix haskell/haddock#24493, with module name introduced in hieAst The accompanies haddoc PR with GHC PR https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12153 Two things have been done: 1. Link is introduced to every `X` in `module X where`, since we introduce the module name to HieAst, 2. `{-# LINE 4 "hypsrc-test/src/PositionPragmas.hs" #-}` is added before the `module PositionPragmas where` in ` hypsrc-test/ref/src/PositionPragmas.html `.It ensures only a single hieAst for file `hypsrc-test/src/PositionPragmas.hs` is generated. - - - - - 635abccc by Ben Gamari at 2024-03-08T17:09:06-05:00 Bump ghc version to 9.10 - - - - - 5b934048 by Ben Gamari at 2024-03-08T18:50:12-05:00 Bump base upper bound - - - - - b30d134e by Ben Gamari at 2024-03-08T18:50:44-05:00 Testsuite output update - - - - - 9bdf3586 by Ben Gamari at 2024-03-09T21:37:44-05:00 Merge branch 'ghc-9.10' into ghc-head - - - - - cec76981 by Ben Gamari at 2024-03-09T21:54:00-05:00 Bump GHC version to 9.11 - - - - - 4c59feb7 by Ben Gamari at 2024-03-09T22:15:01-05:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - bee54c24 by Krzysztof Gogolewski at 2024-04-19T11:13:00+02:00 Update quantification order following GHC haskell/haddock#23764 - - - - - 2814eb89 by Ben Gamari at 2024-04-19T18:57:05+02:00 hypsrc-test: Fix output of PositionPragmas.html - - - - - a27c6a49 by Fendor at 2024-04-22T10:13:03+02:00 Adapt to UserData split - - - - - 1efc5a7a by Fendor at 2024-04-22T10:13:03+02:00 Adapt to BinHandle split - - - - - c62239b7 by Sylvain Henry at 2024-04-29T10:35:00+02:00 Fix tests for T22229 - - - - - b84b91f5 by Adam Gundry at 2024-05-16T15:32:06-04:00 Representation-polymorphic HasField (fixes #22156) This generalises the HasField class to support representation polymorphism, so that instead of type HasField :: forall {k} . k -> Type -> Type -> Constraint we have type HasField :: forall {k} {r_rep} {a_rep} . k -> TYPE r_rep -> TYPE a_rep -> Constraint - - - - - 05285090 by Matthew Pickering at 2024-05-16T15:32:43-04:00 Bump os-string submodule to 2.0.2.2 Closes #24786 - - - - - 886ab43a by Cheng Shao at 2024-05-17T01:34:50-04:00 rts: do not prefetch mark_closure bdescr in non-moving gc when ASSERTS_ENABLED This commit fixes a small an oversight in !12148: the prefetch logic in non-moving GC may trap in debug RTS because it calls Bdescr() for mark_closure which may be a static one. It's fine in non-debug RTS because even invalid bdescr addresses are prefetched, they will not cause segfaults, so this commit implements the most straightforward fix: don't prefetch mark_closure bdescr when assertions are enabled. - - - - - b38dcf39 by Teo Camarasu at 2024-05-17T01:34:50-04:00 rts: Allocate non-moving segments with megablocks Non-moving segments are 8 blocks long and need to be aligned. Previously we serviced allocations by grabbing 15 blocks, finding an aligned 8 block group in it and returning the rest. This proved to lead to high levels of fragmentation as a de-allocating a segment caused an 8 block gap to form, and this could not be reused for allocation. This patch introduces a segment allocator based around using entire megablocks to service segment allocations in bulk. When there are no free segments, we grab an entire megablock and fill it with aligned segments. As the megablock is free, we can easily guarantee alignment. Any unused segments are placed on a free list. It only makes sense to free segments in bulk when all of the segments in a megablock are freeable. After sweeping, we grab the free list, sort it, and find all groups of segments where they cover the megablock and free them. This introduces a period of time when free segments are not available to the mutator, but the risk that this would lead to excessive allocation is low. Right after sweep, we should have an abundance of partially full segments, and this pruning step is relatively quick. In implementing this we drop the logic that kept NONMOVING_MAX_FREE segments on the free list. We also introduce an eventlog event to log the amount of pruned/retained free segments. See Note [Segment allocation strategy] Resolves #24150 ------------------------- Metric Decrease: T13253 T19695 ------------------------- - - - - - 710665bd by Cheng Shao at 2024-05-17T01:35:30-04:00 rts: fix I/O manager compilation errors for win32 target This patch fixes I/O manager compilation errors for win32 target discovered when cross-compiling to win32 using recent clang: ``` rts/win32/ThrIOManager.c:117:7: error: error: call to undeclared function 'is_io_mng_native_p'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 117 | if (is_io_mng_native_p ()) { | ^ | 117 | if (is_io_mng_native_p ()) { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/fs.c:143:28: error: error: a function declaration without a prototype is deprecated in all versions of C [-Werror,-Wstrict-prototypes] 143 | int setErrNoFromWin32Error () { | ^ | void | 143 | int setErrNoFromWin32Error () { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:227:9: error: error: call to undeclared function 'interruptIOManagerEvent'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 227 | interruptIOManagerEvent (); | ^ | 227 | interruptIOManagerEvent (); | ^ rts/win32/ConsoleHandler.c:227:9: error: note: did you mean 'getIOManagerEvent'? | 227 | interruptIOManagerEvent (); | ^ rts/include/rts/IOInterface.h:27:10: error: note: 'getIOManagerEvent' declared here 27 | void * getIOManagerEvent (void); | ^ | 27 | void * getIOManagerEvent (void); | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:196:9: error: error: call to undeclared function 'setThreadLabel'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/win32/ConsoleHandler.c:196:9: error: note: did you mean 'postThreadLabel'? | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/eventlog/EventLog.h:118:6: error: note: 'postThreadLabel' declared here 118 | void postThreadLabel(Capability *cap, | ^ | 118 | void postThreadLabel(Capability *cap, | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) ``` - - - - - 28b9cee0 by Rodrigo Mesquita at 2024-05-17T01:36:05-04:00 configure: Check C99-compat for Cmm preprocessor Fixes #24815 - - - - - 8927e0c3 by Andreas Klebinger at 2024-05-17T01:36:41-04:00 Ensure `tcHasFixedRuntimeRep (# #)` returns True. - - - - - 04179044 by doyougnu at 2024-05-17T09:00:32-04:00 testsuite: make find_so regex less general Closes #24759 Background. In MR !12372 we began tracking shared object files and directories sizes for dependencies. However, this broke release builds because release builds alter the filenames swapping "in-place" for a hash. This was not considered in the MR and thus broke release pipelines. Furthermore, the rts_so test was found to be wildly varying and was therefore disabled in !12561. This commit fixes both of these issues: - fix the rts_so test by making the regex less general, now the rts_so test and all other foo.so tests must match "libHS<some-lib>-<version>-<hash|'in-place>-<ghc>". This prevents the rts_so test from accidentally matching different rts variants such as rts_threaded, which was the cause of the wild swings after !12372. - add logic to match either a hash or the string in-place. This should make the find_so function build agnostic. - - - - - 0962b50d by Andreas Klebinger at 2024-05-17T09:01:08-04:00 TagAnalysis: Treat all bottom ids as tagged during analysis. Ticket #24806 showed that we also need to treat dead end thunks as tagged during the analysis. - - - - - 7eb9f184 by Ben Gamari at 2024-05-17T11:23:37-04:00 Remove haddock submodule In preparation for merge into the GHC, as proposed in #23178. - - - - - 47b14dcc by Fendor at 2024-05-17T11:28:17-04:00 Adapt to `IfLclName` newtype changes (cherry picked from commit a711607e29b925f3d69e27c5fde4ba655c711ff1) - - - - - 6cc6681d by Fendor at 2024-05-17T11:28:17-04:00 Add IfaceType deduplication table to interface file serialisation Although we do not really need it in the interface file serialisation, as the deserialisation uses `getWithUserData`, we need to mirror the structure `getWithUserData` expects. Thus, we write essentially an empty `IfaceType` table at the end of the file, as the interface file doesn't reference `IfaceType`. (cherry picked from commit c9bc29c6a708483d2abc3d8ec9262510ce87ca61) - - - - - b9721206 by Ben Gamari at 2024-05-17T11:30:22-04:00 ghc-tags.yaml: Initial commit - - - - - 074e7d8f by Ben Gamari at 2024-05-17T11:31:29-04:00 fourmolu: Add configuration - - - - - 151b1736 by Ben Gamari at 2024-05-17T11:32:52-04:00 Makefile: Rework for use by haddock developers Previously the Makefile was present only for GHC's old make-based build system. Now since the make-based build system is gone we can use it for more useful ends. - - - - - a7dcf13b by Ben Gamari at 2024-05-17T11:36:14-04:00 Reformat with fourmolu Using previously-added configuration and `fourmolu -i .` Note that we exclude the test-cases (`./{hoogle,html-hypsrc,latex}-test`) as they are sensitive to formatting. - - - - - 0ea6017b by Ben Gamari at 2024-05-17T11:40:04-04:00 Add 'utils/haddock/' from commit 'a7dcf13bfbb97b20e75cc8ce650e2bb628db4660' git-subtree-dir: utils/haddock git-subtree-mainline: 7eb9f1849b1c72a1c61dee88462b4244550406f3 git-subtree-split: a7dcf13bfbb97b20e75cc8ce650e2bb628db4660 - - - - - aba1d304 by Hécate Moonlight at 2024-05-17T11:40:48-04:00 Add exceptions to the dangling notes list - - - - - 527bfbfb by Hécate Moonlight at 2024-05-17T11:40:52-04:00 Add haddock to the whitespace lint ignore list - - - - - 43274677 by Ben Gamari at 2024-05-17T11:41:20-04:00 git-blame-ignore-revs: Ignore haddock reformatting - - - - - 0e679e37 by Fendor at 2024-05-18T00:27:24-04:00 Pass cpp options to the CC builder in hadrian - - - - - bb40244e by Sylvain Henry at 2024-05-18T00:28:06-04:00 JS: fix allocation constant (fix #24746) - - - - - 646d30ab by Jade at 2024-05-18T19:23:31+02:00 Add highlighting for inline-code snippets in haddock - - - - - 64459a3e by Hécate Moonlight at 2024-05-19T08:42:27-04:00 haddock: Add a .readthedocs.yml file for online documentation - - - - - 7d3d9bbf by Serge S. Gulin at 2024-05-19T18:47:05+00:00 Unicode: General Category size test (related #24789) Added trivial size performance test which involves unicode general category usage via `read`. The `read` itself uses general category to detect spaces. The purpose for this test is to measure outcome of applying improvements at General Category representation in code discussed at #24789. - - - - - 8e04efcf by Alan Zimmerman at 2024-05-19T21:29:34-04:00 EPA: Remove redundant code Remove unused epAnnAnns function various cases for showAstData that no longer exist - - - - - 071d7a1e by Rodrigo Mesquita at 2024-05-20T10:55:16-04:00 Improve docs on closed type families in hs-boots Fixes #24776 - - - - - d9e2c119 by Torsten Schmits at 2024-05-20T10:55:52-04:00 Use default deviation for large-project test This new performance test has the purpose of detecting regressions in complexity in relation to the number of modules in a project, so 1% deviation is way too small to avoid false positives. - - - - - 20b0136a by Ben Gamari at 2024-05-22T00:31:39-04:00 ghcup-metadata: Various fixes from 9.10.1 Use Debian 12/x86-64, Debian 10/aarch64, and Debian 11/aarch64 bindists where possible. - - - - - 6838a7c3 by Sylvain Henry at 2024-05-22T00:32:23-04:00 Reverse arguments to stgCallocBytes (fix #24828) - - - - - f50f46c3 by Fendor at 2024-05-22T00:32:59-04:00 Add log messages for Iface serialisation compression level Fix the label of the number of 'IfaceType' entries in the log message. Add log message for the compression level that is used to serialise a an interface file. Adds `Outputable` instance for 'CompressionIFace'. - - - - - 3bad5d55 by Hécate Moonlight at 2024-05-22T00:33:40-04:00 base: Update doctests outputs ghc-internal: Update doctests outputs - - - - - 9317c6fb by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix the testsuites of the haddock-library - Apply all the metadata revisions from Hackage to the cabal file. - Fix the `ParserSpec.hs` file in the `spec` testsuite of haddock-library. - Make `CHANGES.md` an extra-doc-file instead of an extra-source-file. - - - - - 54073b02 by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix parser of @since pragma The testsuite contained tests for annotations of the form `@since foo-bar-0.5.0`, but the parser was written incorrectly. - - - - - ede6ede3 by Matthew Pickering at 2024-05-22T00:34:57-04:00 Fix nightly pages job It seems likely broken by 9f99126a which moved `index.html` from the root folder into `docs/` folder. Fixes #24840 - - - - - b7bcf729 by Cheng Shao at 2024-05-22T00:35:32-04:00 autoconf: remove unused context diff check This patch removes redundant autoconf check for the context diff program given it isn't actually been used anywhere, especially since make removal. - - - - - ea2fe66e by Hécate Moonlight at 2024-05-22T00:36:13-04:00 haddock: Rework the contributing guide - - - - - 0f302a94 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 haddock: Add module relationships diagrams of haddock-api and haddock-library - - - - - d1a9f34f by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add instructions - - - - - b880ee80 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add SVG outputs - - - - - 6d7e6ad8 by Ben Gamari at 2024-05-22T13:40:05-04:00 rts: Fix size of StgOrigThunkInfo frames Previously the entry code of the `stg_orig_thunk` frame failed to account for the size of the profiling header as it hard-coded the frame size. Fix this. Fixes #24809. - - - - - c645fe40 by Fendor at 2024-05-22T13:40:05-04:00 Add regression test T24809 for stg_orig_thunk_info_frame size - - - - - 4181aa40 by Andreas Klebinger at 2024-05-22T13:40:42-04:00 bindists: Check for existence of share folder before trying to copy it. This folder isn't distributed in windows bindists A lack of doing so resulted us copying loads of files twice. - - - - - d216510e by Matthew Pickering at 2024-05-22T13:40:42-04:00 Remove ad-hoc installation of mingw toolchain in relocatable bindists This reverts 616ac30026e8dd7d2ebb98d92dde071eedf5d951 The choice about whether to install mingw is taken in the installation makefile. This is also broken on non-windows systems. The actual issue was the EnableDistroToolchain variable wasn't declared in mk/config.mk and therefore the check to install mingw was failing. - - - - - 7b4c1998 by Cheng Shao at 2024-05-22T21:52:52-04:00 testsuite: fix T17920 for wasm backend T17920 was marked as fragile on wasm before; it can be trivially fixed by avoiding calling variadic printf() in cmm. - - - - - c739383b by Cheng Shao at 2024-05-22T21:53:29-04:00 testsuite: bump T22744 timeout to 5x - - - - - c4c6d714 by Cheng Shao at 2024-05-22T21:54:06-04:00 testsuite: don't attempt to detect host cpu features when testing cross ghc The testsuite driver CPU feature detection logic only detects host CPU and only makes sense when we are not testing a cross GHC. - - - - - 3d9e4ce6 by Simon Peyton Jones at 2024-05-22T21:54:43-04:00 Better skolemisation As #24810 showed, it is (a little) better to skolemise en-bloc, so that Note [Let-bound skolems] fires more often. See Note [Skolemisation en bloc] in GHC.Tc.Utils.Instantiate. - - - - - a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00 Add missing parenthesizePat in cvtp We need to ensure that the output of `cvtp` is parenthesized (at precedence `sigPrec`) so that any pattern signatures with a surrounding pattern signature can parse correctly. Fixes #24837. - - - - - 4bb2a7cc by Hécate Moonlight at 2024-05-22T21:55:59-04:00 [base] Document the memory overhead of ByteArray Add a diagram that shows the constituent parts of a ByteArray and their memory overhead. - - - - - 8b2a016a by Hécate Moonlight at 2024-05-22T21:56:38-04:00 Haddock: Add MR template for Haddock - - - - - ead75532 by Peter Trommler at 2024-05-23T02:28:05-04:00 PPC: Support ELF v2 on powerpc64 big-endian Detect ELF v2 on PowerPC 64-bit systems. Check for `_CALL_ELF` preprocessor macro. Fixes #21191 - - - - - 9d4c10f2 by Hécate Kleidukos at 2024-05-23T02:28:44-04:00 gitlab: Add @Kleidukos to CODEOWNERS for utils/haddock - - - - - 28e64170 by Preetham Gujjula at 2024-05-23T07:20:48-04:00 haddock: Add cabal-fmt to tools for `make style` - - - - - 00126a89 by Andrei Borzenkov at 2024-05-23T07:21:24-04:00 haddock: fix verbosity option parsing - - - - - a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00 base: specify tie-breaking behavior of min, max, and related list/Foldable functions - - - - - bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00 cmm: add word <-> double/float bitcast - closes: #25331 This is the last step in the project plan described in #25331. This commit: - adds bitcast operands for x86_64, LLVM, aarch64 - For PPC and i386 we resort to using the cmm implementations - renames conversion MachOps from Conv to Round|Truncate - - - - - f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor Some functions in StgToByteCode were filtering out void arguments. However, StgToByteCode is called after unarisation: the void arguments should have been removed earlier. Instead of filtering out, we assert that the args are non-void. - - - - - 03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor `layoutNativeCall` was always called with a `primRepCmmType platform` callback. Hence we can put it inside of `layoutNativeCall` rather than repeat it. - - - - - 27c430f3 by David Binder at 2024-05-24T07:52:38-04:00 haddock: Remove compatibility shims for GHC < 8.4 from haddock-library - - - - - 8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00 compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs This patch makes the STG->Cmm backend avoid saving foreign call target to local when there are no caller-save GlobalRegs. Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a foreign call, we unconditionally save the foreign call target to a temporary local first, then rely on cmmSink to clean it up later, which only happens with -fcmm-sink (implied by -O) and not in unoptimized code. And this is troublesome for the wasm backend NCG, which needs to infer a foreign call target symbol's type signature from the Cmm call site. Previously, the NCG has been emitting incorrect type signatures for unoptimized code, which happens to work with `wasm-ld` most of the time, but this is never future-proof against upstream toolchain updates, and it causes horrible breakages when LTO objects are included in linker input. Hence this patch. - - - - - 986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00 testsuite: add callee-no-local regression test - - - - - 52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00 Fix HasCallStack leftovers from !12514 / #24726 - - - - - c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00 user_guide: Fix typo in MultiWayIf chapter Close #24829 - - - - - bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - 1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Fix changelog reference to setBacktraceMechanismState (cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d) - - - - - 43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00 Float/double unboxed literal support for HexFloatLiterals (fix #22155) - - - - - 4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00 Improve test labels for binary interface file size tests Test labels for binary interface file sizes are hard to read and overly verbose at the same time. Extend the name for the metric title, but shorten it in the actual comparison table. - - - - - 14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00 Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present" This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa. - - - - - f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00 Fix default hyperlinked sources pattern Previously this didn't include the `%M` token which manifested as broken links to the hyperlinked sources of reexports of declarations defined in other packages. Fixes haddock#1628. (cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36) - - - - - 42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00 Make DocPaths a proper data type (cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c) - - - - - 53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00 haddock: Bump version to 2.30 (cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602) - - - - - e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00 haddock-api: allow base 4.20 and ghc 9.11 - - - - - e294f7a2 by PHO at 2024-05-24T12:17:55-04:00 Add a flag "threaded" for building haddock with the threaded RTS GHC isn't guaranteed to have a threaded RTS. There should be a way to build it with the vanilla one. (cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d) - - - - - 51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00 Update ticky counter event docs. Add the info about the info table address and json fields. Fixes #23200 - - - - - 98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00 Export extractPromotedList (#24866) This can be useful in plugins. - - - - - 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - d70abb49 by sheaf at 2024-06-18T18:47:20-04:00 Clarify -XGADTs enables existential quantification Even though -XGADTs does not turn on -XExistentialQuantification, it does allow the user of existential quantification syntax, without needing to use GADT-style syntax. Fixes #20865 - - - - - 13fdf788 by David Binder at 2024-06-18T18:48:02-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 1bab7dde by Fendor at 2024-06-18T18:48:38-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18698b T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The tests T16875 and T18698b fail on i386-linux for the same reason. - - - - - 099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - 5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00 Update user guide to indicate support for 64-tuples - - - - - 4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00 Remove duplicate Anno instances - - - - - 8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00 AArch64: Delete unused RegNos This has the additional benefit of getting rid of the -1 encoding (real registers start at 0.) - - - - - 325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00 Bump stm submodule to current master - - - - - 64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00 testsuite: bump T17572 timeout on wasm32 - - - - - eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00 AArch64: Simplify BL instruction The BL constructor carried unused data in its third argument. - - - - - b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00 TTG: Move SourceText from `Fixity` to `FixitySig` It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Precedes !12842, to simplify it - - - - - 842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00 base: Deprecate some .Internal modules Deprecates the following modules according to clc-proposal #217: https://github.com/haskell/core-libraries-committee/issues/217 * GHC.TypeNats.Internal * GHC.TypeLits.Internal * GHC.ExecutionStack.Internal Closes #24998 - - - - - dfaed326 by Arnaud Spiwack at 2024-06-19T11:49:19+01:00 Add test case for #23586 - - - - - df15eca9 by Arnaud Spiwack at 2024-06-19T11:49:19+01:00 When matching functions in rewrite rules: ignore multiplicity When matching a template variable to an expression, we check that it has the same type as the matched expression. But if the variable `f` has type `A -> B` while the expression `e` has type `A %1 -> B`, the match was previously rejected. A principled solution would have `f` substituted by `\(%Many x) -> e x` or some other appropriate coercion. But since linearity is not properly checked in Core, we can be cheeky and simply ignore multiplicity while matching. Much easier. This has forced a change in the linter which, when `-dlinear-core-lint` is off, must consider that `a -> b` and `a %1 -> b` are equal. This is achieved by adding an argument to configure the behaviour of `nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour which ignores multiplicities when comparing two `FunTy`. Fixes #24725. - - - - - 42ee5684 by Simon Peyton Jones at 2024-06-19T11:49:43+01:00 Faster type equality This MR speeds up type equality, triggered by perf regressions that showed up when fixing #24725 by parameterising type equality over whether to ignore multiplicity. The changes are: * Do not use `nonDetCmpType` for type /equality/. Instead use a specialised type-equality function, which we have always had! `nonDetCmpType` remains, but I did not invest effort in refactoring or optimising it. * Type equality is parameterised by - whether to expand synonyms - whether to respect multiplicities - whether it has a RnEnv2 environment In this MR I systematically specialise it for static values of these parameters. Much more direct and predictable than before. See Note [Specialising type equality] * We want to avoid comparing kinds if possible. I refactored how this happens, at least for `eqType`. See Note [Casts and coercions in type comparison] * To make Lint fast, we want to avoid allocating a thunk for <msg> in ensureEqTypes ty1 ty2 <msg> because the test almost always succeeds, and <msg> isn't needed. See Note [INLINE ensureEqTys] - - - - - 30 changed files: - + .git-blame-ignore-revs - .gitignore - .gitlab-ci.yml - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - + .gitlab/merge_request_templates/Haddock.md - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitmodules - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Sink.hs - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/38275e18011840c72fddbe4811c3f86872e766b5...42ee56840611222cccb36c86440d80f6a1397272 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/38275e18011840c72fddbe4811c3f86872e766b5...42ee56840611222cccb36c86440d80f6a1397272 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 10:52:02 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 19 Jun 2024 06:52:02 -0400 Subject: [Git][ghc/ghc][wip/T24725] Faster type equality Message-ID: <6672b8526830a_17fcd51584ee4704e8@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24725 at Glasgow Haskell Compiler / GHC Commits: 0eb7cf7e by Simon Peyton Jones at 2024-06-19T11:50:41+01:00 Faster type equality This MR speeds up type equality, triggered by perf regressions that showed up when fixing #24725 by parameterising type equality over whether to ignore multiplicity. The changes are: * Do not use `nonDetCmpType` for type /equality/. Instead use a specialised type-equality function, which we have always had! `nonDetCmpType` remains, but I did not invest effort in refactoring or optimising it. * Type equality is parameterised by - whether to expand synonyms - whether to respect multiplicities - whether it has a RnEnv2 environment In this MR I systematically specialise it for static values of these parameters. Much more direct and predictable than before. See Note [Specialising type equality] * We want to avoid comparing kinds if possible. I refactored how this happens, at least for `eqType`. See Note [Casts and coercions in type comparison] * To make Lint fast, we want to avoid allocating a thunk for <msg> in ensureEqTypes ty1 ty2 <msg> because the test almost always succeeds, and <msg> isn't needed. See Note [INLINE ensureEqTys] Metric Decrease: T13386 T5030 - - - - - 5 changed files: - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Multiplicity.hs - compiler/GHC/Core/TyCo/Compare.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Tc/Utils/TcType.hs Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -53,7 +53,7 @@ import GHC.Core.Predicate( isCoVarType ) import GHC.Core.Multiplicity import GHC.Core.UsageEnv import GHC.Core.TyCo.Rep -- checks validity of types/coercions -import GHC.Core.TyCo.Compare ( eqType, eqTypeOpt, defaultCmpTypeOpt, CmpTypeOpt (..), eqForAllVis ) +import GHC.Core.TyCo.Compare ( eqType, eqTypes, eqTypeIgnoringMultiplicity, eqForAllVis ) import GHC.Core.TyCo.Subst import GHC.Core.TyCo.FVs import GHC.Core.TyCo.Ppr @@ -2807,7 +2807,7 @@ lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches extra_checks | isNewTyCon tc - = do { CoAxBranch { cab_tvs = tvs + = do { CoAxBranch { cab_tvs = ax_tvs , cab_eta_tvs = eta_tvs , cab_cvs = cvs , cab_roles = roles @@ -2815,14 +2815,10 @@ lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches <- case branch_list of [branch] -> return branch _ -> failWithL (text "multi-branch axiom with newtype") - ; let ax_lhs = mkInfForAllTys tvs $ - mkTyConApp tc lhs_tys - nt_tvs = takeList tvs (tyConTyVars tc) - -- axiom may be eta-reduced: Note [Newtype eta] in GHC.Core.TyCon - nt_lhs = mkInfForAllTys nt_tvs $ - mkTyConApp tc (mkTyVarTys nt_tvs) - -- See Note [Newtype eta] in GHC.Core.TyCon - ; lintL (ax_lhs `eqType` nt_lhs) + + -- The LHS of the axiom is (N lhs_tys) + -- We expect it to be (N ax_tvs) + ; lintL (mkTyVarTys ax_tvs `eqTypes` lhs_tys) (text "Newtype axiom LHS does not match newtype definition") ; lintL (null cvs) (text "Newtype axiom binds coercion variables") @@ -2831,7 +2827,7 @@ lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches (text "Newtype axiom has eta-tvs") ; lintL (ax_role == Representational) (text "Newtype axiom role not representational") - ; lintL (roles `equalLength` tvs) + ; lintL (roles `equalLength` ax_tvs) (text "Newtype axiom roles list is the wrong length." $$ text "roles:" <+> sep (map ppr roles)) ; lintL (roles == takeList roles (tyConRoles tc)) @@ -3101,17 +3097,14 @@ Note [Linting linearity] Lint ignores linearity unless `-dlinear-core-lint` is set. For why, see below. But first, "ignore linearity" specifically means two things. When ignoring linearity: -* In `ensureEqTypes`, use `eqTypeOpt` with instructions to ignore multiplicities in FunTy. +* In `ensureEqTypes`, use `eqTypeIgnoringMultiplicity` * In `ensureSubMult`, do nothing -The behaviour of functions such as eqTypeOpt which may or may not ignore -linearity is governed by a flag of type GHC.Core.Multiplicity.MultiplicityFlag. - -But why make `-dcore-lint` ignore linearity? Because -optimisation passes are not (yet) guaranteed to maintain linearity. They should -do so semantically (GHC is careful not to duplicate computation) but it is much -harder to ensure that the statically-checkable constraints of Linear Core are -maintained. The current Linear Core is described in the wiki at: +But why make `-dcore-lint` ignore linearity? Because optimisation passes are +not (yet) guaranteed to maintain linearity. They should do so semantically (GHC +is careful not to duplicate computation) but it is much harder to ensure that +the statically-checkable constraints of Linear Core are maintained. The current +Linear Core is described in the wiki at: https://gitlab.haskell.org/ghc/ghc/-/wikis/linear-types/implementation. Here are some examples of how the optimiser can break linearity checking. Other @@ -3495,17 +3488,25 @@ ensureEqTys :: LintedType -> LintedType -> SDoc -> LintM () -- check ty2 is subtype of ty1 (ie, has same structure but usage -- annotations need only be consistent, not equal) -- Assumes ty1,ty2 are have already had the substitution applied -ensureEqTys ty1 ty2 msg = do - flags <- getLintFlags - -- When `-dlinear-core-lint` is off, then consider `a -> b` and `a %1 -> b` to - -- be equal. See Note [Linting linearity]. - lintL (eqTypeOpt (opt flags) ty1 ty2) msg - where - opt flags = - if lf_check_linearity flags then - defaultCmpTypeOpt { cmp_multiplicity_in_funty = RespectMultiplicities } - else - defaultCmpTypeOpt { cmp_multiplicity_in_funty = IgnoreMultiplicities } +{-# INLINE ensureEqTys #-} -- See Note [INLINE ensureEqTys] +ensureEqTys ty1 ty2 msg + = do { flags <- getLintFlags + ; lintL (eq_type flags ty1 ty2) msg } + +eq_type :: LintFlags -> Type -> Type -> Bool +-- When `-dlinear-core-lint` is off, then consider `a -> b` and `a %1 -> b` to +-- be equal. See Note [Linting linearity]. +eq_type flags ty1 ty2 | lf_check_linearity flags = eqType ty1 ty2 + | otherwise = eqTypeIgnoringMultiplicity ty1 ty2 + +{- Note [INLNE ensureEqTys] +~~~~~~~~~~~~~~~~~~~~~~~~~~~ +To make Lint fast, we want to avoid allocating a thunk for in + ensureEqTypes ty1 ty2 +because the test almost always succeeds, and isn't needed. +So we INLINE `ensureEqTys`. This actually make a difference of +1-2% when compiling programs with -dcore-lint. +-} ensureSubUsage :: Usage -> Mult -> SDoc -> LintM () ensureSubUsage Bottom _ _ = return () ===================================== compiler/GHC/Core/Multiplicity.hs ===================================== @@ -31,7 +31,8 @@ module GHC.Core.Multiplicity , submult , mapScaledType , pprArrowWithMultiplicity - , MultiplicityFlag(..)) where + , MultiplicityFlag(..) + ) where import GHC.Prelude ===================================== compiler/GHC/Core/TyCo/Compare.hs ===================================== @@ -7,16 +7,17 @@ -- | Type equality and comparison module GHC.Core.TyCo.Compare ( - -- * Type comparison - eqType, eqTypeOpt, eqTypeX, eqTypes, nonDetCmpType, nonDetCmpTypes, nonDetCmpTypeX, - nonDetCmpTypesX, nonDetCmpTc, + -- * Type equality + eqType, eqTypeIgnoringMultiplicity, eqTypeX, eqTypes, eqVarBndrs, - CmpTypeOpt (..), defaultCmpTypeOpt, pickyEqType, tcEqType, tcEqKind, tcEqTypeNoKindCheck, tcEqTyConApps, mayLookIdentical, + -- * Type comparison + nonDetCmpType, + -- * Visiblity comparision eqForAllVis, cmpForAllVis @@ -30,10 +31,12 @@ import GHC.Core.Type( typeKind, coreView, tcSplitAppTyNoView_maybe, splitAppTyNo import GHC.Core.TyCo.Rep import GHC.Core.TyCo.FVs import GHC.Core.TyCon +import GHC.Core.Multiplicity( MultiplicityFlag(..) ) import GHC.Types.Var import GHC.Types.Unique import GHC.Types.Var.Env +import GHC.Types.Var.Set import GHC.Utils.Outputable import GHC.Utils.Misc @@ -42,7 +45,6 @@ import GHC.Utils.Panic import GHC.Base (reallyUnsafePtrEquality#) import qualified Data.Semigroup as S -import GHC.Core.Multiplicity {- GHC.Core.TyCo.Compare overview ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -54,7 +56,8 @@ so it currently sits "on top of" GHC.Core.Type. {- ********************************************************************* * * - Type equality + Type equality + We don't use (==) from class Eq, that we know where it happens * * ********************************************************************* -} @@ -74,6 +77,75 @@ that needs to be updated. * See Historical Note [Typechecker equality vs definitional equality] below +Note [Casts and coercions in type comparision] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +As (EQTYPE) in Note [Non-trivial definitional equality] says, our +general plan, implemented by `fullEq`, is: + (1) ignore both casts and coercions when comparing types, + (2) instead, compare the /kinds/ of the two types, + as well as the types themselves + +If possible we want to avoid step (2), comparing the kinds; doing so involved +calling `typeKind` and doing another comparision. + +When can we avoid doing so? Answer: we can certainly avoid doing so if the +types we are comparing have no casts or coercions. But we can do better. +Consider + eqType (TyConApp T [s1, ..., sn]) (TyConApp T [t1, .., tn]) +We are going to call (eqType s1 t1), (eqType s2 t2) etc. + +Now the kind of `s1` and `s2` must be equal; and hence the kind of `s2` and `t2` +must be equal (the kind of T could be (forall k. k -> ...), but `k` will be +instantiate with `s1` and `t1` resp, which are equal. And so on. + +Conclusion: + +* casts and coercions under a TyConApp don't matter -- even including type synonyms + +* In step (2), use `hasCasts` to tell if there are any casts to worry about. It + does not look very deep, because TyConApps and FunTys are so common, and it + doesn't allocate. The only recursive cases are AppTy and ForAllTy. + +Note [Equality on AppTys] +~~~~~~~~~~~~~~~~~~~~~~~~~ +In our cast-ignoring equality, we want to say that the following two +are equal: + + (Maybe |> co) (Int |> co') ~? Maybe Int + +But the left is an AppTy while the right is a TyConApp. The solution is +to use splitAppTyNoView_maybe to break up the TyConApp into its pieces and +then continue. Easy to do, but also easy to forget to do. + +Note [Comparing nullary type synonyms] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider the task of testing equality between two 'Type's of the form + + TyConApp tc [] + +where @tc@ is a type synonym. A naive way to perform this comparison these +would first expand the synonym and then compare the resulting expansions. + +However, this is obviously wasteful and the RHS of @tc@ may be large; it is +much better to rather compare the TyCons directly. Consequently, before +expanding type synonyms in type comparisons we first look for a nullary +TyConApp and simply compare the TyCons if we find one. Of course, if we find +that the TyCons are *not* equal then we still need to perform the expansion as +their RHSs may still be equal. + +We perform this optimisation in a number of places: + + * GHC.Core.Types.eqType + * GHC.Core.Types.nonDetCmpType + * GHC.Core.Unify.unify_ty + * GHC.Tc.Solver.Equality.can_eq_nc' + * TcUnify.uType + +This optimisation is especially helpful for the ubiquitous GHC.Types.Type, +since GHC prefers to use the type synonym over @TYPE 'LiftedRep@ applications +whenever possible. See Note [Using synonyms to compress types] in +GHC.Core.Type for details. + Note [Type comparisons using object pointer comparisons] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Quite often we substitute the type from a definition site into @@ -83,6 +155,19 @@ The type of every `x` will often be represented by a single object in the heap. We can take advantage of this by shortcutting the equality check if two types are represented by the same pointer under the hood. In some cases this reduces compiler allocations by ~2%. + +Note [Respecting multiplicity when comparing types] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Generally speaking, we respect multiplicities (i.e. the linear part of the type +system) when comparing types. Doing so is of course crucial during typechecking. + +But for reasons described in Note [Linting linearity] in GHC.Core.Lint, it is hard +to ensure that Core is always type-correct when it comes to linearity. So +* `eqTypeIgnoringMultiplicity` provides a way to compare types that /ignores/ multiplicities +* We use this multiplicity-blind comparison very occasionally, notably + - in Core Lint: see Note [Linting linearity] in GHC.Core.Lint + - in rule matching: see Note [Rewrite rules ignore multiplicities in FunTy] + in GHC.Core.Unify -} @@ -90,21 +175,12 @@ tcEqKind :: HasDebugCallStack => Kind -> Kind -> Bool tcEqKind = tcEqType tcEqType :: HasDebugCallStack => Type -> Type -> Bool --- ^ tcEqType implements typechecker equality --- It behaves just like eqType, but is implemented --- differently (for now) -tcEqType ty1 ty2 - = tcEqTypeNoSyns ki1 ki2 - && tcEqTypeNoSyns ty1 ty2 - where - ki1 = typeKind ty1 - ki2 = typeKind ty2 +tcEqType = eqType -- | Just like 'tcEqType', but will return True for types of different kinds -- as long as their non-coercion structure is identical. tcEqTypeNoKindCheck :: Type -> Type -> Bool -tcEqTypeNoKindCheck ty1 ty2 - = tcEqTypeNoSyns ty1 ty2 +tcEqTypeNoKindCheck = eqTypeNoKindCheck -- | Check whether two TyConApps are the same; if the number of arguments -- are different, just checks the common prefix of arguments. @@ -116,175 +192,221 @@ tcEqTyConApps tc1 args1 tc2 args2 -- any difference in the kinds of later arguments would show up -- as differences in earlier (dependent) arguments -{- -Note [Specialising tc_eq_type] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -The type equality predicates in Type are hit pretty hard during typechecking. -Consequently we take pains to ensure that these paths are compiled to -efficient, minimally-allocating code. -To this end we place an INLINE on tc_eq_type, ensuring that it is inlined into -its publicly-visible interfaces (e.g. tcEqType). In addition to eliminating -some dynamic branches, this allows the simplifier to eliminate the closure -allocations that would otherwise be necessary to capture the two boolean "mode" -flags. This reduces allocations by a good fraction of a percent when compiling -Cabal. - -See #19226. --} - -mayLookIdentical :: Type -> Type -> Bool --- | Returns True if the /visible/ part of the types --- might look equal, even if they are really unequal (in the invisible bits) --- --- This function is very similar to tc_eq_type but it is much more --- heuristic. Notably, it is always safe to return True, even with types --- that might (in truth) be unequal -- this affects error messages only --- (Originally there were one function with an extra flag, but the result --- was hard to understand.) -mayLookIdentical orig_ty1 orig_ty2 - = go orig_env orig_ty1 orig_ty2 - where - orig_env = mkRnEnv2 $ mkInScopeSet $ tyCoVarsOfTypes [orig_ty1, orig_ty2] +-- | Type equality on lists of types, looking through type synonyms +eqTypes :: [Type] -> [Type] -> Bool +eqTypes [] [] = True +eqTypes (t1:ts1) (t2:ts2) = eqType t1 t2 && eqTypes ts1 ts2 +eqTypes _ _ = False - go :: RnEnv2 -> Type -> Type -> Bool - -- See Note [Comparing nullary type synonyms] - go _ (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = True +eqVarBndrs :: HasCallStack => RnEnv2 -> [Var] -> [Var] -> Maybe RnEnv2 +-- Check that the var lists are the same length +-- and have matching kinds; if so, extend the RnEnv2 +-- Returns Nothing if they don't match +eqVarBndrs env [] [] + = Just env +eqVarBndrs env (tv1:tvs1) (tv2:tvs2) + | eqTypeX env (varType tv1) (varType tv2) + = eqVarBndrs (rnBndr2 env tv1 tv2) tvs1 tvs2 +eqVarBndrs _ _ _= Nothing - go env t1 t2 | Just t1' <- coreView t1 = go env t1' t2 - go env t1 t2 | Just t2' <- coreView t2 = go env t1 t2' +initRnEnv :: Type -> Type -> RnEnv2 +initRnEnv ta tb = mkRnEnv2 $ mkInScopeSet $ + tyCoVarsOfType ta `unionVarSet` tyCoVarsOfType tb - go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 - go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 - go env (CastTy t1 _) t2 = go env t1 t2 - go env t1 (CastTy t2 _) = go env t1 t2 - go _ (CoercionTy {}) (CoercionTy {}) = True +eqTypeNoKindCheck :: Type -> Type -> Bool +eqTypeNoKindCheck ty1 ty2 = eq_type_expand_respect ty1 ty2 - go env (ForAllTy (Bndr tv1 vis1) ty1) - (ForAllTy (Bndr tv2 vis2) ty2) - = vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] - && go (rnBndr2 env tv1 tv2) ty1 ty2 - -- Visible stuff only: ignore kinds of binders +-- | Type equality comparing both visible and invisible arguments, +-- expanding synonyms and respecting multiplicities. +eqType :: HasCallStack => Type -> Type -> Bool +eqType ta tb = fullEq eq_type_expand_respect ta tb - -- If we have (forall (r::RunTimeRep). ty1 ~ blah) then respond - -- with True. Reason: the type pretty-printer defaults RuntimeRep - -- foralls (see Ghc.Iface.Type.hideNonStandardTypes). That can make, - -- say (forall r. TYPE r -> Type) into (Type -> Type), so it looks the - -- same as a very different type (#24553). By responding True, we - -- tell GHC (see calls of mayLookIdentical) to display without defaulting. - -- See Note [Showing invisible bits of types in error messages] - -- in GHC.Tc.Errors.Ppr - go _ (ForAllTy b _) _ | isDefaultableBndr b = True - go _ _ (ForAllTy b _) | isDefaultableBndr b = True +-- | Compare types with respect to a (presumably) non-empty 'RnEnv2'. +eqTypeX :: HasCallStack => RnEnv2 -> Type -> Type -> Bool +eqTypeX env ta tb = fullEq (eq_type_expand_respect_x env) ta tb - go env (FunTy _ w1 arg1 res1) (FunTy _ w2 arg2 res2) - = go env arg1 arg2 && go env res1 res2 && go env w1 w2 - -- Visible stuff only: ignore agg kinds +eqTypeIgnoringMultiplicity :: Type -> Type -> Bool +-- See Note [Respecting multiplicity when comparing types] +eqTypeIgnoringMultiplicity ta tb = fullEq eq_type_expand_ignore ta tb - -- See Note [Equality on AppTys] in GHC.Core.Type - go env (AppTy s1 t1) ty2 - | Just (s2, t2) <- tcSplitAppTyNoView_maybe ty2 - = go env s1 s2 && go env t1 t2 - go env ty1 (AppTy s2 t2) - | Just (s1, t1) <- tcSplitAppTyNoView_maybe ty1 - = go env s1 s2 && go env t1 t2 +-- | Like 'pickyEqTypeVis', but returns a Bool for convenience +pickyEqType :: Type -> Type -> Bool +-- Check when two types _look_ the same, _including_ synonyms. +-- So (pickyEqType String [Char]) returns False +-- This ignores kinds and coercions, because this is used only for printing. +pickyEqType ta tb = eq_type_keep_respect ta tb - go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) - = tc1 == tc2 && gos env (tyConBinders tc1) ts1 ts2 +{- Note [Specialising type equality] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The type equality predicates in Type are hit pretty hard by GHC. Consequently +we take pains to ensure that these paths are compiled to efficient, +minimally-allocating code. Plan: - go _ _ _ = False +* The main workhorse is `inline_generic_eq_type_x`. It is /non-recursive/ + and is marked INLINE. - gos :: RnEnv2 -> [TyConBinder] -> [Type] -> [Type] -> Bool - gos _ _ [] [] = True - gos env bs (t1:ts1) (t2:ts2) - | (invisible, bs') <- case bs of - [] -> (False, []) - (b:bs) -> (isInvisibleTyConBinder b, bs) - = (invisible || go env t1 t2) && gos env bs' ts1 ts2 +* `inline_generic_eq_type_x` has various parameters that control what it does: + * syn_flag::SynFlag whether type synonyms are expanded or kept. + * mult_flag::MultiplicityFlag whether multiplicities are ignored or respected + * mb_env::Maybe RnEnv2 an optional RnEnv2. - gos _ _ _ _ = False +* `inline_generic_eq_type_x` has a handful of call sites, namely the ones + in `eq_type_expand_respect`, `eq_type_expand_repect_x` etc. It inlines + at all these sites, specialising to the data values passed for the + control parameters. +* All /other/ calls to `inline_generic_eq_type_x` go via + generic_eq_type_x = inline_generic_eq_type_x + {-# NOINLNE generic_eq_type_x #-} + The idea is that all calls to `generic_eq_type_x` are specialised by the + RULES, so this NOINLINE version is seldom, if ever, actually called. --- | Type equality comparing both visible and invisible arguments and expanding --- type synonyms. -tcEqTypeNoSyns :: Type -> Type -> Bool -tcEqTypeNoSyns ta tb = tc_eq_type False ta tb +* For each of specialised copy of `inline_generic_eq_type_x, there is a + corresponding rewrite RULE that rewrites a call to (generic_eq_type_x args) + into the appropriate specialied version. --- | Like 'pickyEqTypeVis', but returns a Bool for convenience -pickyEqType :: Type -> Type -> Bool --- Check when two types _look_ the same, _including_ synonyms. --- So (pickyEqType String [Char]) returns False --- This ignores kinds and coercions, because this is used only for printing. -pickyEqType ty1 ty2 = tc_eq_type True ty1 ty2 +See #19226. +-} --- | Real worker for 'tcEqType'. No kind check! -tc_eq_type :: Bool -- ^ True <=> do not expand type synonyms - -> Type -> Type - -> Bool --- Flags False, False is the usual setting for tc_eq_type +-- | This flag controls whether we expand synonyms during comparison +data SynFlag = ExpandSynonyms | KeepSynonyms + +eq_type_expand_respect, eq_type_expand_ignore, eq_type_keep_respect + :: Type -> Type -> Bool +eq_type_expand_respect_x, eq_type_expand_ignore_x, eq_type_keep_respect_x + :: RnEnv2 -> Type -> Type -> Bool + +eq_type_expand_respect = inline_generic_eq_type_x ExpandSynonyms RespectMultiplicities Nothing +eq_type_expand_respect_x env = inline_generic_eq_type_x ExpandSynonyms RespectMultiplicities (Just env) +eq_type_expand_ignore = inline_generic_eq_type_x ExpandSynonyms IgnoreMultiplicities Nothing +eq_type_expand_ignore_x env = inline_generic_eq_type_x ExpandSynonyms IgnoreMultiplicities (Just env) +eq_type_keep_respect = inline_generic_eq_type_x KeepSynonyms RespectMultiplicities Nothing +eq_type_keep_respect_x env = inline_generic_eq_type_x KeepSynonyms RespectMultiplicities (Just env) + +{-# RULES +"eqType1" generic_eq_type_x ExpandSynonyms RespectMultiplicities Nothing + = eq_type_expand_respect +"eqType2" forall env. generic_eq_type_x ExpandSynonyms RespectMultiplicities (Just env) + = eq_type_expand_respect_x env +"eqType3" generic_eq_type_x ExpandSynonyms IgnoreMultiplicities Nothing + = eq_type_expand_ignore +"eqType4" forall env. generic_eq_type_x ExpandSynonyms IgnoreMultiplicities (Just env) + = eq_type_expand_ignore_x env +"eqType5" generic_eq_type_x KeepSynonyms RespectMultiplicities Nothing + = eq_type_keep_respect +"eqType6" forall env. generic_eq_type_x KeepSynonyms RespectMultiplicities (Just env) + = eq_type_keep_respect_x env + #-} + +-- --------------------------------------------------------------- +-- | Real worker for 'eqType'. No kind check! +-- Inline it at the (handful of local) call sites +-- The "generic" bit refers to the flag paramerisation +-- See Note [Specialising type equality]. +generic_eq_type_x, inline_generic_eq_type_x + :: SynFlag -> MultiplicityFlag -> Maybe RnEnv2 -> Type -> Type -> Bool + +{-# NOINLINE generic_eq_type_x #-} +generic_eq_type_x = inline_generic_eq_type_x -- See Note [Computing equality on types] in Type -{-# INLINE tc_eq_type #-} -- See Note [Specialising tc_eq_type]. -tc_eq_type keep_syns orig_ty1 orig_ty2 - = go orig_env orig_ty1 orig_ty2 + +{-# INLINE inline_generic_eq_type_x #-} +inline_generic_eq_type_x syn_flag mult_flag mb_env + = inline_go -- This is the only call of inline_go where - orig_env = mkRnEnv2 $ mkInScopeSet $ tyCoVarsOfTypes [orig_ty1, orig_ty2] + ------------------- + go = generic_eq_type_x syn_flag mult_flag mb_env - go :: RnEnv2 -> Type -> Type -> Bool - -- See Note [Comparing nullary type synonyms] - go _ (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = True + ------------------- + inline_go !t1 !t2 | 1# <- reallyUnsafePtrEquality# t1 t2 = True + -- See Note [Type comparisons using object pointer comparisons] - go env t1 t2 | not keep_syns, Just t1' <- coreView t1 = go env t1' t2 - go env t1 t2 | not keep_syns, Just t2' <- coreView t2 = go env t1 t2' + inline_go (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = True + -- See Note [Comparing nullary type synonyms] - go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 - go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 - go env (CastTy t1 _) t2 = go env t1 t2 - go env t1 (CastTy t2 _) = go env t1 t2 - go _ (CoercionTy {}) (CoercionTy {}) = True + inline_go t1 t2 | ExpandSynonyms <- syn_flag, Just t1' <- coreView t1 = go t1' t2 + inline_go t1 t2 | ExpandSynonyms <- syn_flag, Just t2' <- coreView t2 = go t1 t2' - go env (ForAllTy (Bndr tv1 vis1) ty1) - (ForAllTy (Bndr tv2 vis2) ty2) - = vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] - && go env (varType tv1) (varType tv2) - && go (rnBndr2 env tv1 tv2) ty1 ty2 + inline_go (TyVarTy tv1) (TyVarTy tv2) + = case mb_env of + Nothing -> tv1 == tv2 + Just env -> rnOccL env tv1 == rnOccR env tv2 + + inline_go (LitTy lit1) (LitTy lit2) = lit1 == lit2 + inline_go (CastTy t1 _) t2 = go t1 t2 -- Ignore casts + inline_go t1 (CastTy t2 _) = go t1 t2 -- Ignore casts + inline_go (CoercionTy {}) (CoercionTy {}) = True -- Ignore coercions -- Make sure we handle all FunTy cases since falling through to the -- AppTy case means that tcSplitAppTyNoView_maybe may see an unzonked -- kind variable, which causes things to blow up. -- See Note [Equality on FunTys] in GHC.Core.TyCo.Rep: we must check -- kinds here - go env (FunTy _ w1 arg1 res1) (FunTy _ w2 arg2 res2) - = go env (typeKind arg1) (typeKind arg2) && - go env (typeKind res1) (typeKind res2) && - go env arg1 arg2 && go env res1 res2 && go env w1 w2 + inline_go (FunTy _ w1 arg1 res1) (FunTy _ w2 arg2 res2) + = fullEq go arg1 arg2 + && fullEq go res1 res2 + && (case mult_flag of + RespectMultiplicities -> go w1 w2 + IgnoreMultiplicities -> True) -- See Note [Equality on AppTys] in GHC.Core.Type - go env (AppTy s1 t1) ty2 + inline_go (AppTy s1 t1) ty2 | Just (s2, t2) <- tcSplitAppTyNoView_maybe ty2 - = go env s1 s2 && go env t1 t2 - go env ty1 (AppTy s2 t2) + = go s1 s2 && go t1 t2 + inline_go ty1 (AppTy s2 t2) | Just (s1, t1) <- tcSplitAppTyNoView_maybe ty1 - = go env s1 s2 && go env t1 t2 - - go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) - = tc1 == tc2 && gos env ts1 ts2 - - go _ _ _ = False - - gos _ [] [] = True - gos env (t1:ts1) (t2:ts2) = go env t1 t2 && gos env ts1 ts2 - gos _ _ _ = False + = go s1 s2 && go t1 t2 + + inline_go (TyConApp tc1 ts1) (TyConApp tc2 ts2) + | tc1 == tc2 = gos ts1 ts2 + | otherwise = False + where + gos [] [] = True + gos (t1:ts1) (t2:ts2) = go t1 t2 && gos ts1 ts2 + gos _ _ = False + + inline_go ty1@(ForAllTy (Bndr tv1 vis1) body1) + ty2@(ForAllTy (Bndr tv2 vis2) body2) + = case mb_env of + Nothing -> generic_eq_type_x syn_flag mult_flag + (Just (initRnEnv ty1 ty2)) ty1 ty2 + Just env + | vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] + -> go (varType tv1) (varType tv2) -- Always do kind-check + && generic_eq_type_x syn_flag mult_flag + (Just (rnBndr2 env tv1 tv2)) body1 body2 + | otherwise + -> False + + inline_go _ _ = False + +fullEq :: (Type -> Type -> Bool) -> Type -> Type -> Bool +-- Do "full equality" including the kind check +-- See Note [Casts and coercions in type comparision] +{-# INLINE fullEq #-} +fullEq eq ty1 ty2 + = case eq ty1 ty2 of + False -> False + True | hasCasts ty1 || hasCasts ty2 + -> eq (typeKind ty1) (typeKind ty2) + | otherwise + -> True + +hasCasts :: Type -> Bool +-- Fast, does not look deep, does not allocate +hasCasts (CastTy {}) = True +hasCasts (CoercionTy {}) = True +hasCasts (AppTy t1 t2) = hasCasts t1 || hasCasts t2 +hasCasts (ForAllTy _ ty) = hasCasts ty +hasCasts _ = False -- TyVarTy, TyConApp, FunTy, LitTy -isDefaultableBndr :: ForAllTyBinder -> Bool --- This function should line up with the defaulting done --- by GHC.Iface.Type.defaultIfaceTyVarsOfKind --- See Note [Showing invisible bits of types in error messages] --- in GHC.Tc.Errors.Ppr -isDefaultableBndr (Bndr tv vis) - = isInvisibleForAllTyFlag vis && is_defaultable (tyVarKind tv) - where - is_defaultable ki = isLevityTy ki || isRuntimeRepTy ki || isMultiplicityTy ki +{- ********************************************************************* +* * + Comparing ForAllTyFlags +* * +********************************************************************* -} -- | Do these denote the same level of visibility? 'Required' -- arguments are visible, others are not. So this function @@ -444,94 +566,13 @@ is more finer-grained than definitional equality in two places: ************************************************************************ * * Comparison for types - (We don't use instances so that we know where it happens) + + Not so heavily used, less carefully optimised * * ************************************************************************ -Note [Equality on AppTys] -~~~~~~~~~~~~~~~~~~~~~~~~~ -In our cast-ignoring equality, we want to say that the following two -are equal: - - (Maybe |> co) (Int |> co') ~? Maybe Int - -But the left is an AppTy while the right is a TyConApp. The solution is -to use splitAppTyNoView_maybe to break up the TyConApp into its pieces and -then continue. Easy to do, but also easy to forget to do. - -Note [Comparing nullary type synonyms] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Consider the task of testing equality between two 'Type's of the form - - TyConApp tc [] - -where @tc@ is a type synonym. A naive way to perform this comparison these -would first expand the synonym and then compare the resulting expansions. - -However, this is obviously wasteful and the RHS of @tc@ may be large; it is -much better to rather compare the TyCons directly. Consequently, before -expanding type synonyms in type comparisons we first look for a nullary -TyConApp and simply compare the TyCons if we find one. Of course, if we find -that the TyCons are *not* equal then we still need to perform the expansion as -their RHSs may still be equal. - -We perform this optimisation in a number of places: - - * GHC.Core.Types.eqType - * GHC.Core.Types.nonDetCmpType - * GHC.Core.Unify.unify_ty - * GHC.Tc.Solver.Equality.can_eq_nc' - * TcUnify.uType - -This optimisation is especially helpful for the ubiquitous GHC.Types.Type, -since GHC prefers to use the type synonym over @TYPE 'LiftedRep@ applications -whenever possible. See Note [Using synonyms to compress types] in -GHC.Core.Type for details. - --} - -eqType :: Type -> Type -> Bool --- ^ Type equality on source types. Does not look through @newtypes@, --- 'PredType's or type families, but it does look through type synonyms. --- This first checks that the kinds of the types are equal and then --- checks whether the types are equal, ignoring casts and coercions. --- (The kind check is a recursive call, but since all kinds have type --- @Type@, there is no need to check the types of kinds.) --- See also Note [Non-trivial definitional equality] in "GHC.Core.TyCo.Rep". -eqType t1 t2 = isEqual $ nonDetCmpType t1 t2 - -- It's OK to use nonDetCmpType here and eqType is deterministic, - -- nonDetCmpType does equality deterministically - -eqTypeOpt :: CmpTypeOpt -> Type -> Type -> Bool -eqTypeOpt opt t1 t2 = isEqual $ nonDetCmpTypeOpt opt t1 t2 - --- | Compare types with respect to a (presumably) non-empty 'RnEnv2'. -eqTypeX :: RnEnv2 -> Type -> Type -> Bool -eqTypeX env t1 t2 = isEqual $ nonDetCmpTypeX defaultCmpTypeOpt env t1 t2 - -- It's OK to use nonDetCmpType here and eqTypeX is deterministic, - -- nonDetCmpTypeX does equality deterministically - --- | Type equality on lists of types, looking through type synonyms --- but not newtypes. -eqTypes :: [Type] -> [Type] -> Bool -eqTypes tys1 tys2 = isEqual $ nonDetCmpTypes tys1 tys2 - -- It's OK to use nonDetCmpType here and eqTypes is deterministic, - -- nonDetCmpTypes does equality deterministically - -eqVarBndrs :: RnEnv2 -> [Var] -> [Var] -> Maybe RnEnv2 --- Check that the var lists are the same length --- and have matching kinds; if so, extend the RnEnv2 --- Returns Nothing if they don't match -eqVarBndrs env [] [] - = Just env -eqVarBndrs env (tv1:tvs1) (tv2:tvs2) - | eqTypeX env (varType tv1) (varType tv2) - = eqVarBndrs (rnBndr2 env tv1 tv2) tvs1 tvs2 -eqVarBndrs _ _ _= Nothing - -- Now here comes the real worker -{- Note [nonDetCmpType nondeterminism] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ nonDetCmpType is implemented in terms of nonDetCmpTypeX. nonDetCmpTypeX @@ -541,27 +582,20 @@ comparing type variables is nondeterministic, note the call to nonDetCmpVar in nonDetCmpTypeX. See Note [Unique Determinism] for more details. -} -nonDetCmpType :: Type -> Type -> Ordering -nonDetCmpType = nonDetCmpTypeOpt defaultCmpTypeOpt -nonDetCmpTypeOpt :: CmpTypeOpt -> Type -> Type -> Ordering -nonDetCmpTypeOpt _ !t1 !t2 +nonDetCmpType :: Type -> Type -> Ordering +{-# INLINE nonDetCmpType #-} +nonDetCmpType !t1 !t2 -- See Note [Type comparisons using object pointer comparisons] | 1# <- reallyUnsafePtrEquality# t1 t2 = EQ -nonDetCmpTypeOpt _ (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 +nonDetCmpType (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = EQ -nonDetCmpTypeOpt opt t1 t2 +nonDetCmpType t1 t2 -- we know k1 and k2 have the same kind, because they both have kind *. - = nonDetCmpTypeX opt rn_env t1 t2 + = nonDetCmpTypeX rn_env t1 t2 where rn_env = mkRnEnv2 (mkInScopeSet (tyCoVarsOfTypes [t1, t2])) -{-# INLINE nonDetCmpType #-} - -nonDetCmpTypes :: [Type] -> [Type] -> Ordering -nonDetCmpTypes ts1 ts2 = nonDetCmpTypesX rn_env ts1 ts2 - where - rn_env = mkRnEnv2 (mkInScopeSet (tyCoVarsOfTypes (ts1 ++ ts2))) -- | An ordering relation between two 'Type's (known below as @t1 :: k1@ -- and @t2 :: k2@) @@ -573,10 +607,11 @@ data TypeOrdering = TLT -- ^ @t1 < t2@ | TGT -- ^ @t1 > t2@ deriving (Eq, Ord, Enum, Bounded) -nonDetCmpTypeX :: CmpTypeOpt -> RnEnv2 -> Type -> Type -> Ordering -- Main workhorse +nonDetCmpTypeX :: RnEnv2 -> Type -> Type -> Ordering -- Main workhorse -- See Note [Non-trivial definitional equality] in GHC.Core.TyCo.Rep -- See Note [Computing equality on types] -nonDetCmpTypeX opt env orig_t1 orig_t2 = + -- Always respects multiplicities, unlike eqType +nonDetCmpTypeX env orig_t1 orig_t2 = case go env orig_t1 orig_t2 of -- If there are casts then we also need to do a comparison of -- the kinds of the types being compared @@ -635,13 +670,9 @@ nonDetCmpTypeX opt env orig_t1 orig_t2 = go env (FunTy _ w1 s1 t1) (FunTy _ w2 s2 t2) -- NB: nonDepCmpTypeX does the kind check requested by -- Note [Equality on FunTys] in GHC.Core.TyCo.Rep - = liftOrdering (nonDetCmpTypeX opt env s1 s2 S.<> nonDetCmpTypeX opt env t1 t2) - `thenCmpTy` cmp_mults + = liftOrdering (nonDetCmpTypeX env s1 s2 S.<> nonDetCmpTypeX env t1 t2) + `thenCmpTy` go env w1 w2 -- Comparing multiplicities last because the test is usually true - where - cmp_mults = case cmp_multiplicity_in_funty opt of - RespectMultiplicities -> go env w1 w2 - IgnoreMultiplicities -> TEQ go env (TyConApp tc1 tys1) (TyConApp tc2 tys2) = liftOrdering (tc1 `nonDetCmpTc` tc2) `thenCmpTy` gos env tys1 tys2 @@ -672,36 +703,6 @@ nonDetCmpTypeX opt env orig_t1 orig_t2 = gos _ _ [] = TGT gos env (ty1:tys1) (ty2:tys2) = go env ty1 ty2 `thenCmpTy` gos env tys1 tys2 -{- Note [Respecting multiplicity when comparing types] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Generally speaking, we respect multiplicities (i.e. the linear part of the type -system) when comparing types. Doing so is of course crucial during typechecking. - -But for reasons described in Note [Linting linearity] in GHC.Core.Lint, it is hard -to ensure that Core is always type-correct when it comes to linearity. So -* `CmpTypeOpt` provides a way to compare types that /ignores/ multiplicities -* We use this multiplicity-blind comparison very occasionally, notably - - in Core Lint: see Note [Linting linearity] in GHC.Core.Lint - - in rule matching: see Note [Rewrite rules ignore multiplicities in FunTy] - in GHC.Core.Unify --} -data CmpTypeOpt = CmpTypeOpt - { -- Whether to consider `a -> b` and `a %1 -> b` distinct or equal. Default: - -- RespectMultiplicities. See Note [Respecting multiplicity when comparing types]. - cmp_multiplicity_in_funty :: MultiplicityFlag - } - -defaultCmpTypeOpt :: CmpTypeOpt -defaultCmpTypeOpt = CmpTypeOpt - { cmp_multiplicity_in_funty = RespectMultiplicities } - -------------- -nonDetCmpTypesX :: RnEnv2 -> [Type] -> [Type] -> Ordering -nonDetCmpTypesX _ [] [] = EQ -nonDetCmpTypesX env (t1:tys1) (t2:tys2) = nonDetCmpTypeX defaultCmpTypeOpt env t1 t2 S.<> - nonDetCmpTypesX env tys1 tys2 -nonDetCmpTypesX _ [] _ = LT -nonDetCmpTypesX _ _ [] = GT ------------- -- | Compare two 'TyCon's. @@ -714,4 +715,91 @@ nonDetCmpTc tc1 tc2 u2 = tyConUnique tc2 +{- ********************************************************************* +* * + mayLookIdentical +* * +********************************************************************* -} + +mayLookIdentical :: Type -> Type -> Bool +-- | Returns True if the /visible/ part of the types +-- might look equal, even if they are really unequal (in the invisible bits) +-- +-- This function is very similar to tc_eq_type but it is much more +-- heuristic. Notably, it is always safe to return True, even with types +-- that might (in truth) be unequal -- this affects error messages only +-- (Originally there were one function with an extra flag, but the result +-- was hard to understand.) +mayLookIdentical orig_ty1 orig_ty2 + = go orig_env orig_ty1 orig_ty2 + where + orig_env = mkRnEnv2 $ mkInScopeSet $ tyCoVarsOfTypes [orig_ty1, orig_ty2] + + go :: RnEnv2 -> Type -> Type -> Bool + -- See Note [Comparing nullary type synonyms] + go _ (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = True + + go env t1 t2 | Just t1' <- coreView t1 = go env t1' t2 + go env t1 t2 | Just t2' <- coreView t2 = go env t1 t2' + + go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 + go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 + go env (CastTy t1 _) t2 = go env t1 t2 + go env t1 (CastTy t2 _) = go env t1 t2 + go _ (CoercionTy {}) (CoercionTy {}) = True + + go env (ForAllTy (Bndr tv1 vis1) ty1) + (ForAllTy (Bndr tv2 vis2) ty2) + = vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] + && go (rnBndr2 env tv1 tv2) ty1 ty2 + -- Visible stuff only: ignore kinds of binders + + -- If we have (forall (r::RunTimeRep). ty1 ~ blah) then respond + -- with True. Reason: the type pretty-printer defaults RuntimeRep + -- foralls (see Ghc.Iface.Type.hideNonStandardTypes). That can make, + -- say (forall r. TYPE r -> Type) into (Type -> Type), so it looks the + -- same as a very different type (#24553). By responding True, we + -- tell GHC (see calls of mayLookIdentical) to display without defaulting. + -- See Note [Showing invisible bits of types in error messages] + -- in GHC.Tc.Errors.Ppr + go _ (ForAllTy b _) _ | isDefaultableBndr b = True + go _ _ (ForAllTy b _) | isDefaultableBndr b = True + + go env (FunTy _ w1 arg1 res1) (FunTy _ w2 arg2 res2) + = go env arg1 arg2 && go env res1 res2 && go env w1 w2 + -- Visible stuff only: ignore agg kinds + + -- See Note [Equality on AppTys] in GHC.Core.Type + go env (AppTy s1 t1) ty2 + | Just (s2, t2) <- tcSplitAppTyNoView_maybe ty2 + = go env s1 s2 && go env t1 t2 + go env ty1 (AppTy s2 t2) + | Just (s1, t1) <- tcSplitAppTyNoView_maybe ty1 + = go env s1 s2 && go env t1 t2 + + go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) + = tc1 == tc2 && gos env (tyConBinders tc1) ts1 ts2 + + go _ _ _ = False + + gos :: RnEnv2 -> [TyConBinder] -> [Type] -> [Type] -> Bool + gos _ _ [] [] = True + gos env bs (t1:ts1) (t2:ts2) + | (invisible, bs') <- case bs of + [] -> (False, []) + (b:bs) -> (isInvisibleTyConBinder b, bs) + = (invisible || go env t1 t2) && gos env bs' ts1 ts2 + + gos _ _ _ _ = False + + +isDefaultableBndr :: ForAllTyBinder -> Bool +-- This function should line up with the defaulting done +-- by GHC.Iface.Type.defaultIfaceTyVarsOfKind +-- See Note [Showing invisible bits of types in error messages] +-- in GHC.Tc.Errors.Ppr +isDefaultableBndr (Bndr tv vis) + = isInvisibleForAllTyFlag vis && is_defaultable (tyVarKind tv) + where + is_defaultable ki = isLevityTy ki || isRuntimeRepTy ki || isMultiplicityTy ki ===================================== compiler/GHC/Core/TyCo/Rep.hs ===================================== @@ -350,14 +350,24 @@ This kind instantiation only happens in TyConApp currently. Note [Non-trivial definitional equality] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Is Int |> <*> the same as Int? YES! In order to reduce headaches, -we decide that any reflexive casts in types are just ignored. -(Indeed they must be. See Note [Respecting definitional equality].) -More generally, the `eqType` function, which defines Core's type equality -relation, ignores casts and coercion arguments, as long as the -two types have the same kind. This allows us to be a little sloppier -in keeping track of coercions, which is a good thing. It also means -that eqType does not depend on eqCoercion, which is also a good thing. +Is ((Monad |> co1) Int |> co2) equal to (Monad Int)? +Assume + co1 :: (Type->Type) ~ (Type->Wombat) + co2 :: Wombat ~ Type +Well, yes. The casts are just getting in the way. +See also Note [Respecting definitional equality]. + +So we do this: + +(EQTYPE) + The `eqType` function, which defines Core's type equality relation, + - /ignores/ casts, and + - /ignores/ coercion arguments + - /provided/ two types have the same kind + +This allows us to be a little sloppier in keeping track of coercions, which is a +good thing. It also means that eqType does not depend on eqCoercion, which is +also a good thing. Why is this sensible? That is, why is something different than α-equivalence appropriate for the implementation of eqType? ===================================== compiler/GHC/Tc/Utils/TcType.hs ===================================== @@ -96,7 +96,7 @@ module GHC.Tc.Utils.TcType ( -- Re-exported from GHC.Core.TyCo.Compare -- mainly just for back-compat reasons - eqType, eqTypes, nonDetCmpType, nonDetCmpTypes, eqTypeX, + eqType, eqTypes, nonDetCmpType, eqTypeX, pickyEqType, tcEqType, tcEqKind, tcEqTypeNoKindCheck, mayLookIdentical, tcEqTyConApps, eqForAllVis, eqVarBndrs, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0eb7cf7eee1dc2159b8d5d8ce3108a076d548c4b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/0eb7cf7eee1dc2159b8d5d8ce3108a076d548c4b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 11:15:01 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Wed, 19 Jun 2024 07:15:01 -0400 Subject: [Git][ghc/ghc][wip/jacco/ast] 36 commits: JS: establish single source of truth for symbols Message-ID: <6672bdb51dfe6_3910c817552014440@gitlab.mail> Rodrigo Mesquita pushed to branch wip/jacco/ast at Glasgow Haskell Compiler / GHC Commits: 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - 97f792f5 by Jacco Krijnen at 2024-06-19T12:14:47+01:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 30 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Builtin/Names.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Binds.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/64cde5147671f8aa7c63986bd0b1adc1bed091f2...97f792f56b4fbda3606c4508b84710907fa3b124 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/64cde5147671f8aa7c63986bd0b1adc1bed091f2...97f792f56b4fbda3606c4508b84710907fa3b124 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 11:38:45 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Wed, 19 Jun 2024 07:38:45 -0400 Subject: [Git][ghc/ghc][wip/fabu/T24452-confusing-error] wip Message-ID: <6672c345d1198_3910c86ddb20210e1@gitlab.mail> Fabricio Nascimento pushed to branch wip/fabu/T24452-confusing-error at Glasgow Haskell Compiler / GHC Commits: 01eed4f4 by Fabricio de Sousa Nascimento at 2024-06-19T20:38:09+09:00 wip - - - - - 9 changed files: - compiler/GHC/Rename/Env.hs - + testsuite/tests/rename/T24452/T24452a.hs - + testsuite/tests/rename/T24452/T24452b.hs - + testsuite/tests/rename/T24452/T24452b.stderr - + testsuite/tests/rename/T24452/T24452c.hs - + testsuite/tests/rename/T24452/T24452c.stderr - + testsuite/tests/rename/T24452/T24452d.hs - + testsuite/tests/rename/T24452/T24452d.stderr - + testsuite/tests/rename/T24452/all.T Changes: ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -3,6 +3,8 @@ {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TupleSections #-} +{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} +{-# HLINT ignore "Use camelCase" #-} {- (c) The GRASP/AQUA Project, Glasgow University, 1992-2006 @@ -709,7 +711,9 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name how_lkup DisambiguatedOccurrence g -> checkFld g AmbiguousOccurrence gres -> - mkNameClashErr gres + if must_have_parent + then noMatchingParentErr original_gres + else mkNameClashErr gres where checkFld :: GlobalRdrElt -> RnM ChildLookupResult checkFld g = do @@ -721,21 +725,25 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name how_lkup -- 1. There were none to begin with. -- 2. None of the matching ones were the parent but -- a. They were from an overloaded record field so we can report - -- a better error + -- a better error, or we were looking for references that must + -- have the correct parent. For example instance member names + -- that need to match the class they come from. Reporting those + -- as clashing errors, gives the user a confusing message + -- as in (#24452). -- b. The original lookup was actually ambiguous. -- For example, the case where overloading is off and two -- record fields are in scope from different record -- constructors, neither of which is the parent. noMatchingParentErr :: [GlobalRdrElt] -> RnM ChildLookupResult noMatchingParentErr original_gres = do - traceRn "npe" (ppr original_gres) + traceRn "noMatchingParentErr" (ppr original_gres) dup_fields_ok <- xoptM LangExt.DuplicateRecordFields case original_gres of [] -> return NameNotFound [g] -> return $ IncorrectParent parent g [p | ParentIs p <- [greParent g]] gss@(g:gss'@(_:_)) -> - if all isRecFldGRE gss && dup_fields_ok + if must_have_parent || all isRecFldGRE gss && dup_fields_ok then return $ IncorrectParent parent g [p | x <- gss, ParentIs p <- [greParent x]] @@ -838,6 +846,7 @@ lookupSubBndrOcc warn_if_deprec the_parent doc rdr_name = lookupExactOrOrig rdr_name (Right . greName) $ -- This happens for built-in classes, see mod052 for example do { child <- lookupSubBndrOcc_helper True warn_if_deprec the_parent rdr_name what_lkup + ; traceTc "Here we go" (vcat [ppr child]) ; return $ case child of FoundChild g -> Right (greName g) NameNotFound -> Left (UnknownSubordinate doc) ===================================== testsuite/tests/rename/T24452/T24452a.hs ===================================== @@ -0,0 +1,11 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative (empty, (<|>))) + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined + p <|> q = undefined ===================================== testsuite/tests/rename/T24452/T24452b.hs ===================================== @@ -0,0 +1,10 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452b.stderr ===================================== @@ -0,0 +1,2 @@ +T24452b.hs:10:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452c.hs ===================================== @@ -0,0 +1,11 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) +import qualified Data.Map as Map + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452c.stderr ===================================== @@ -0,0 +1,2 @@ +T24452c.hs:11:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452d.hs ===================================== @@ -0,0 +1,12 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) +import qualified Data.Map as Map +import qualified Data.Set as Set + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452d.stderr ===================================== @@ -0,0 +1,2 @@ +T24452d.hs:12:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/all.T ===================================== @@ -0,0 +1,4 @@ +test('T24452a', normal, compile, ['']) +test('T24452b', normal, compile_fail, ['']) +test('T24452c', normal, compile_fail, ['']) +test('T24452d', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/01eed4f4a0d541b4fb365e8a4e3b39f91a4a561b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/01eed4f4a0d541b4fb365e8a4e3b39f91a4a561b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 11:45:59 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Wed, 19 Jun 2024 07:45:59 -0400 Subject: [Git][ghc/ghc][wip/fabu/T24452-confusing-error] wip Message-ID: <6672c4f7406ab_3910c882a12c2486a@gitlab.mail> Fabricio Nascimento pushed to branch wip/fabu/T24452-confusing-error at Glasgow Haskell Compiler / GHC Commits: 5eee25be by Fabricio de Sousa Nascimento at 2024-06-19T20:45:46+09:00 wip - - - - - 9 changed files: - compiler/GHC/Rename/Env.hs - + testsuite/tests/rename/T24452/T24452a.hs - + testsuite/tests/rename/T24452/T24452b.hs - + testsuite/tests/rename/T24452/T24452b.stderr - + testsuite/tests/rename/T24452/T24452c.hs - + testsuite/tests/rename/T24452/T24452c.stderr - + testsuite/tests/rename/T24452/T24452d.hs - + testsuite/tests/rename/T24452/T24452d.stderr - + testsuite/tests/rename/T24452/all.T Changes: ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -3,6 +3,8 @@ {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TupleSections #-} +{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-} +{-# HLINT ignore "Use camelCase" #-} {- (c) The GRASP/AQUA Project, Glasgow University, 1992-2006 @@ -709,7 +711,9 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name how_lkup DisambiguatedOccurrence g -> checkFld g AmbiguousOccurrence gres -> - mkNameClashErr gres + if must_have_parent + then noMatchingParentErr original_gres + else mkNameClashErr gres where checkFld :: GlobalRdrElt -> RnM ChildLookupResult checkFld g = do @@ -721,21 +725,25 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name how_lkup -- 1. There were none to begin with. -- 2. None of the matching ones were the parent but -- a. They were from an overloaded record field so we can report - -- a better error + -- a better error, or we were looking for references that must + -- have the correct parent. For example instance member names + -- that need to match the class they come from. Reporting those + -- as clashing errors, gives the user a confusing message + -- as in (#24452). -- b. The original lookup was actually ambiguous. -- For example, the case where overloading is off and two -- record fields are in scope from different record -- constructors, neither of which is the parent. noMatchingParentErr :: [GlobalRdrElt] -> RnM ChildLookupResult noMatchingParentErr original_gres = do - traceRn "npe" (ppr original_gres) + traceRn "noMatchingParentErr" (ppr original_gres) dup_fields_ok <- xoptM LangExt.DuplicateRecordFields case original_gres of [] -> return NameNotFound [g] -> return $ IncorrectParent parent g [p | ParentIs p <- [greParent g]] gss@(g:gss'@(_:_)) -> - if all isRecFldGRE gss && dup_fields_ok + if must_have_parent || all isRecFldGRE gss && dup_fields_ok then return $ IncorrectParent parent g [p | x <- gss, ParentIs p <- [greParent x]] @@ -838,6 +846,7 @@ lookupSubBndrOcc warn_if_deprec the_parent doc rdr_name = lookupExactOrOrig rdr_name (Right . greName) $ -- This happens for built-in classes, see mod052 for example do { child <- lookupSubBndrOcc_helper True warn_if_deprec the_parent rdr_name what_lkup + ; traceTc "Here we go" (vcat [ppr child]) ; return $ case child of FoundChild g -> Right (greName g) NameNotFound -> Left (UnknownSubordinate doc) ===================================== testsuite/tests/rename/T24452/T24452a.hs ===================================== @@ -0,0 +1,11 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative (empty, (<|>))) + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined + p <|> q = undefined ===================================== testsuite/tests/rename/T24452/T24452b.hs ===================================== @@ -0,0 +1,10 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452b.stderr ===================================== @@ -0,0 +1,2 @@ +T24452b.hs:10:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452c.hs ===================================== @@ -0,0 +1,11 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) +import qualified Data.Map as Map + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452c.stderr ===================================== @@ -0,0 +1,2 @@ +T24452c.hs:11:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452d.hs ===================================== @@ -0,0 +1,12 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) +import qualified Data.Map as Map +import qualified Data.Set as Set + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452d.stderr ===================================== @@ -0,0 +1,2 @@ +T24452d.hs:12:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/all.T ===================================== @@ -0,0 +1,4 @@ +test('T24452a', normal, compile, ['']) +test('T24452b', normal, compile_fail, ['']) +test('T24452c', normal, compile_fail, ['']) +test('T24452d', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5eee25be5d437cbd01aa8ac2314c49f7b894dbef -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5eee25be5d437cbd01aa8ac2314c49f7b894dbef You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 11:47:01 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Wed, 19 Jun 2024 07:47:01 -0400 Subject: [Git][ghc/ghc][wip/fabu/T24452-confusing-error] wip Message-ID: <6672c535143c2_3910c88f72942565c@gitlab.mail> Fabricio Nascimento pushed to branch wip/fabu/T24452-confusing-error at Glasgow Haskell Compiler / GHC Commits: 3850605a by Fabricio de Sousa Nascimento at 2024-06-19T20:46:51+09:00 wip - - - - - 9 changed files: - compiler/GHC/Rename/Env.hs - + testsuite/tests/rename/T24452/T24452a.hs - + testsuite/tests/rename/T24452/T24452b.hs - + testsuite/tests/rename/T24452/T24452b.stderr - + testsuite/tests/rename/T24452/T24452c.hs - + testsuite/tests/rename/T24452/T24452c.stderr - + testsuite/tests/rename/T24452/T24452d.hs - + testsuite/tests/rename/T24452/T24452d.stderr - + testsuite/tests/rename/T24452/all.T Changes: ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -1,4 +1,5 @@ {-# LANGUAGE FlexibleContexts #-} + {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE TypeApplications #-} @@ -709,7 +710,9 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name how_lkup DisambiguatedOccurrence g -> checkFld g AmbiguousOccurrence gres -> - mkNameClashErr gres + if must_have_parent + then noMatchingParentErr original_gres + else mkNameClashErr gres where checkFld :: GlobalRdrElt -> RnM ChildLookupResult checkFld g = do @@ -721,21 +724,25 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name how_lkup -- 1. There were none to begin with. -- 2. None of the matching ones were the parent but -- a. They were from an overloaded record field so we can report - -- a better error + -- a better error, or we were looking for references that must + -- have the correct parent. For example instance member names + -- that need to match the class they come from. Reporting those + -- as clashing errors, gives the user a confusing message + -- as in (#24452). -- b. The original lookup was actually ambiguous. -- For example, the case where overloading is off and two -- record fields are in scope from different record -- constructors, neither of which is the parent. noMatchingParentErr :: [GlobalRdrElt] -> RnM ChildLookupResult noMatchingParentErr original_gres = do - traceRn "npe" (ppr original_gres) + traceRn "noMatchingParentErr" (ppr original_gres) dup_fields_ok <- xoptM LangExt.DuplicateRecordFields case original_gres of [] -> return NameNotFound [g] -> return $ IncorrectParent parent g [p | ParentIs p <- [greParent g]] gss@(g:gss'@(_:_)) -> - if all isRecFldGRE gss && dup_fields_ok + if must_have_parent || all isRecFldGRE gss && dup_fields_ok then return $ IncorrectParent parent g [p | x <- gss, ParentIs p <- [greParent x]] @@ -838,6 +845,7 @@ lookupSubBndrOcc warn_if_deprec the_parent doc rdr_name = lookupExactOrOrig rdr_name (Right . greName) $ -- This happens for built-in classes, see mod052 for example do { child <- lookupSubBndrOcc_helper True warn_if_deprec the_parent rdr_name what_lkup + ; traceTc "Here we go" (vcat [ppr child]) ; return $ case child of FoundChild g -> Right (greName g) NameNotFound -> Left (UnknownSubordinate doc) ===================================== testsuite/tests/rename/T24452/T24452a.hs ===================================== @@ -0,0 +1,11 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative (empty, (<|>))) + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined + p <|> q = undefined ===================================== testsuite/tests/rename/T24452/T24452b.hs ===================================== @@ -0,0 +1,10 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452b.stderr ===================================== @@ -0,0 +1,2 @@ +T24452b.hs:10:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452c.hs ===================================== @@ -0,0 +1,11 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) +import qualified Data.Map as Map + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452c.stderr ===================================== @@ -0,0 +1,2 @@ +T24452c.hs:11:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452d.hs ===================================== @@ -0,0 +1,12 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) +import qualified Data.Map as Map +import qualified Data.Set as Set + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452d.stderr ===================================== @@ -0,0 +1,2 @@ +T24452d.hs:12:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/all.T ===================================== @@ -0,0 +1,4 @@ +test('T24452a', normal, compile, ['']) +test('T24452b', normal, compile_fail, ['']) +test('T24452c', normal, compile_fail, ['']) +test('T24452d', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3850605a1151a999aa0ad37ef7e72031b15ecbb1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/3850605a1151a999aa0ad37ef7e72031b15ecbb1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 11:47:42 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Wed, 19 Jun 2024 07:47:42 -0400 Subject: [Git][ghc/ghc][wip/fabu/T24452-confusing-error] wip Message-ID: <6672c55ed7185_3910c89e5fac26480@gitlab.mail> Fabricio Nascimento pushed to branch wip/fabu/T24452-confusing-error at Glasgow Haskell Compiler / GHC Commits: 400d22fd by Fabricio de Sousa Nascimento at 2024-06-19T20:47:31+09:00 wip - - - - - 9 changed files: - compiler/GHC/Rename/Env.hs - + testsuite/tests/rename/T24452/T24452a.hs - + testsuite/tests/rename/T24452/T24452b.hs - + testsuite/tests/rename/T24452/T24452b.stderr - + testsuite/tests/rename/T24452/T24452c.hs - + testsuite/tests/rename/T24452/T24452c.stderr - + testsuite/tests/rename/T24452/T24452d.hs - + testsuite/tests/rename/T24452/T24452d.stderr - + testsuite/tests/rename/T24452/all.T Changes: ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -1,4 +1,5 @@ {-# LANGUAGE FlexibleContexts #-} + {-# LANGUAGE GADTs #-} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE TypeApplications #-} @@ -709,7 +710,9 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name how_lkup DisambiguatedOccurrence g -> checkFld g AmbiguousOccurrence gres -> - mkNameClashErr gres + if must_have_parent + then noMatchingParentErr original_gres + else mkNameClashErr gres where checkFld :: GlobalRdrElt -> RnM ChildLookupResult checkFld g = do @@ -721,21 +724,25 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name how_lkup -- 1. There were none to begin with. -- 2. None of the matching ones were the parent but -- a. They were from an overloaded record field so we can report - -- a better error + -- a better error, or we were looking for references that must + -- have the correct parent. For example instance member names + -- that need to match the class they come from. Reporting those + -- as clashing errors, gives the user a confusing message + -- as in (#24452). -- b. The original lookup was actually ambiguous. -- For example, the case where overloading is off and two -- record fields are in scope from different record -- constructors, neither of which is the parent. noMatchingParentErr :: [GlobalRdrElt] -> RnM ChildLookupResult noMatchingParentErr original_gres = do - traceRn "npe" (ppr original_gres) + traceRn "noMatchingParentErr" (ppr original_gres) dup_fields_ok <- xoptM LangExt.DuplicateRecordFields case original_gres of [] -> return NameNotFound [g] -> return $ IncorrectParent parent g [p | ParentIs p <- [greParent g]] gss@(g:gss'@(_:_)) -> - if all isRecFldGRE gss && dup_fields_ok + if must_have_parent || all isRecFldGRE gss && dup_fields_ok then return $ IncorrectParent parent g [p | x <- gss, ParentIs p <- [greParent x]] @@ -838,6 +845,7 @@ lookupSubBndrOcc warn_if_deprec the_parent doc rdr_name = lookupExactOrOrig rdr_name (Right . greName) $ -- This happens for built-in classes, see mod052 for example do { child <- lookupSubBndrOcc_helper True warn_if_deprec the_parent rdr_name what_lkup + ; traceTc "Here we go" (vcat [ppr child]) ; return $ case child of FoundChild g -> Right (greName g) NameNotFound -> Left (UnknownSubordinate doc) ===================================== testsuite/tests/rename/T24452/T24452a.hs ===================================== @@ -0,0 +1,11 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative (empty, (<|>))) + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined + p <|> q = undefined ===================================== testsuite/tests/rename/T24452/T24452b.hs ===================================== @@ -0,0 +1,10 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452b.stderr ===================================== @@ -0,0 +1,2 @@ +T24452b.hs:10:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452c.hs ===================================== @@ -0,0 +1,11 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) +import qualified Data.Map as Map + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452c.stderr ===================================== @@ -0,0 +1,2 @@ +T24452c.hs:11:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452d.hs ===================================== @@ -0,0 +1,12 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) +import qualified Data.Map as Map +import qualified Data.Set as Set + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452d.stderr ===================================== @@ -0,0 +1,2 @@ +T24452d.hs:12:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/all.T ===================================== @@ -0,0 +1,4 @@ +test('T24452a', normal, compile, ['']) +test('T24452b', normal, compile_fail, ['']) +test('T24452c', normal, compile_fail, ['']) +test('T24452d', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/400d22fd14a74e75099b161725be6e1f14fd1e94 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/400d22fd14a74e75099b161725be6e1f14fd1e94 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 11:48:20 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Wed, 19 Jun 2024 07:48:20 -0400 Subject: [Git][ghc/ghc][wip/fabu/T24452-confusing-error] wip Message-ID: <6672c5845d356_3910c8a91a6427210@gitlab.mail> Fabricio Nascimento pushed to branch wip/fabu/T24452-confusing-error at Glasgow Haskell Compiler / GHC Commits: f06bc46e by Fabricio de Sousa Nascimento at 2024-06-19T20:48:08+09:00 wip - - - - - 9 changed files: - compiler/GHC/Rename/Env.hs - + testsuite/tests/rename/T24452/T24452a.hs - + testsuite/tests/rename/T24452/T24452b.hs - + testsuite/tests/rename/T24452/T24452b.stderr - + testsuite/tests/rename/T24452/T24452c.hs - + testsuite/tests/rename/T24452/T24452c.stderr - + testsuite/tests/rename/T24452/T24452d.hs - + testsuite/tests/rename/T24452/T24452d.stderr - + testsuite/tests/rename/T24452/all.T Changes: ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -709,7 +709,9 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name how_lkup DisambiguatedOccurrence g -> checkFld g AmbiguousOccurrence gres -> - mkNameClashErr gres + if must_have_parent + then noMatchingParentErr original_gres + else mkNameClashErr gres where checkFld :: GlobalRdrElt -> RnM ChildLookupResult checkFld g = do @@ -721,21 +723,25 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name how_lkup -- 1. There were none to begin with. -- 2. None of the matching ones were the parent but -- a. They were from an overloaded record field so we can report - -- a better error + -- a better error, or we were looking for references that must + -- have the correct parent. For example instance member names + -- that need to match the class they come from. Reporting those + -- as clashing errors, gives the user a confusing message + -- as in (#24452). -- b. The original lookup was actually ambiguous. -- For example, the case where overloading is off and two -- record fields are in scope from different record -- constructors, neither of which is the parent. noMatchingParentErr :: [GlobalRdrElt] -> RnM ChildLookupResult noMatchingParentErr original_gres = do - traceRn "npe" (ppr original_gres) + traceRn "noMatchingParentErr" (ppr original_gres) dup_fields_ok <- xoptM LangExt.DuplicateRecordFields case original_gres of [] -> return NameNotFound [g] -> return $ IncorrectParent parent g [p | ParentIs p <- [greParent g]] gss@(g:gss'@(_:_)) -> - if all isRecFldGRE gss && dup_fields_ok + if must_have_parent || all isRecFldGRE gss && dup_fields_ok then return $ IncorrectParent parent g [p | x <- gss, ParentIs p <- [greParent x]] @@ -838,6 +844,7 @@ lookupSubBndrOcc warn_if_deprec the_parent doc rdr_name = lookupExactOrOrig rdr_name (Right . greName) $ -- This happens for built-in classes, see mod052 for example do { child <- lookupSubBndrOcc_helper True warn_if_deprec the_parent rdr_name what_lkup + ; traceTc "Here we go" (vcat [ppr child]) ; return $ case child of FoundChild g -> Right (greName g) NameNotFound -> Left (UnknownSubordinate doc) ===================================== testsuite/tests/rename/T24452/T24452a.hs ===================================== @@ -0,0 +1,11 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative (empty, (<|>))) + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined + p <|> q = undefined ===================================== testsuite/tests/rename/T24452/T24452b.hs ===================================== @@ -0,0 +1,10 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452b.stderr ===================================== @@ -0,0 +1,2 @@ +T24452b.hs:10:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452c.hs ===================================== @@ -0,0 +1,11 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) +import qualified Data.Map as Map + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452c.stderr ===================================== @@ -0,0 +1,2 @@ +T24452c.hs:11:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452d.hs ===================================== @@ -0,0 +1,12 @@ +-- Note +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) +import qualified Data.Map as Map +import qualified Data.Set as Set + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452d.stderr ===================================== @@ -0,0 +1,2 @@ +T24452d.hs:12:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/all.T ===================================== @@ -0,0 +1,4 @@ +test('T24452a', normal, compile, ['']) +test('T24452b', normal, compile_fail, ['']) +test('T24452c', normal, compile_fail, ['']) +test('T24452d', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f06bc46ec7a7edefd125b9a24ed865bdca1afdbb -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f06bc46ec7a7edefd125b9a24ed865bdca1afdbb You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 12:42:25 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Wed, 19 Jun 2024 08:42:25 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T24223-fixup Message-ID: <6672d231e13aa_3910c8117d6343969a@gitlab.mail> sheaf pushed new branch wip/T24223-fixup at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T24223-fixup You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 13:19:08 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 19 Jun 2024 09:19:08 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: AArch64: Simplify BL instruction Message-ID: <6672daccb2134_3910c81779e705734d@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00 AArch64: Simplify BL instruction The BL constructor carried unused data in its third argument. - - - - - b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00 TTG: Move SourceText from `Fixity` to `FixitySig` It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Precedes !12842, to simplify it - - - - - 842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00 base: Deprecate some .Internal modules Deprecates the following modules according to clc-proposal #217: https://github.com/haskell/core-libraries-committee/issues/217 * GHC.TypeNats.Internal * GHC.TypeLits.Internal * GHC.ExecutionStack.Internal Closes #24998 - - - - - 8380ccf6 by Andreas Klebinger at 2024-06-19T09:18:56-04:00 GHCi interpreter: Tag constructor closures when possible. When evaluating PUSH_G try to tag the reference we are pushing if it's a constructor or function. This is potentially helpful for performance and required to fix #24870. - - - - - 87282fee by Simon Peyton Jones at 2024-06-19T09:18:59-04:00 Fix demand signatures for join points This MR tackles #24623 and #23113 The main change is to give a clearer notion of "worker/wrapper arity", esp for join points. See GHC.Core.Opt.DmdAnal Note [Worker/wrapper arity and join points] This Note is a good summary of what this MR does: (1) The "worker/wrapper arity" of an Id is * For non-join-points: idArity * The join points: the join arity (Id part only of course) This is the number of args we will use in worker/wrapper. See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`. (2) A join point's demand-signature arity may exceed the Id's worker/wrapper arity. See the `arity_ok` assertion in `mkWwBodies`. (3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond the worker/wrapper arity. (4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper arity (re)-computed by workWrapArity. - - - - - d2462c9c by Rodrigo Mesquita at 2024-06-19T09:18:59-04:00 cmm: Don't parse MO_BSwap for W8 Don't support parsing bswap8, since bswap8 is not really an operation and would have to be implemented as a no-op (and currently is not implemented at all). Fixes #25002 - - - - - 30 changed files: - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/WorkWrap.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Gen/Splice.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Demand.hs - compiler/GHC/Types/Fixity.hs - libraries/base/src/GHC/ExecutionStack/Internal.hs - libraries/base/src/GHC/TypeLits/Internal.hs - libraries/base/src/GHC/TypeNats/Internal.hs - rts/Interpreter.c - + testsuite/tests/dmdanal/should_compile/T24623.hs - testsuite/tests/dmdanal/should_compile/all.T The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/72bacf3f58473d1956e2524be82864f34406b076...d2462c9c1f627029178ec2300e9131b01ccda34c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/72bacf3f58473d1956e2524be82864f34406b076...d2462c9c1f627029178ec2300e9131b01ccda34c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 15:10:37 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Wed, 19 Jun 2024 11:10:37 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] 45 commits: JS: establish single source of truth for symbols Message-ID: <6672f4eda1825_1334dab8af103782a@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - daa3bd77 by Adriaan Leijnse at 2024-06-19T16:07:52+01:00 ttg: Remove SourceText from OverloadedLabel Progress towards #21592 - - - - - 510becd2 by Alexander Foremny at 2024-06-19T16:07:53+01:00 AST: GHC.Prelude -> Prelude Refactor occurrences to GHC.Prelude with Prelude within Language/Haskell. Progress towards #21592 - - - - - 71b82620 by Alexander Foremny at 2024-06-19T16:07:53+01:00 AST: remove occurrences of GHC.Unit.Module.ModuleName `GHC.Unit.Module` re-exports `ModuleName` from `Language.Haskell.Syntax.Module.Name`. Progress towards #21592 - - - - - 4afd2edd by Fabian Kirchner at 2024-06-19T16:07:53+01:00 AST: move Data instance definition for ModuleName to GHC.Unit.Types To remove the dependency on GHC.Utils.Misc inside Language.Haskell.Syntax.Module.Name, the instance definition is moved from there into GHC.Unit.Types. Progress towards #21592 - - - - - d8bac257 by Fabian Kirchner at 2024-06-19T16:07:53+01:00 AST: move negateOverLitVal into GHC.Hs.Lit The function negateOverLitVal is not used within Language.Haskell and therefore can be moved to the respective module inside GHC.Hs. Progress towards #21592 - - - - - c38620c3 by Fabian Kirchner at 2024-06-19T16:07:53+01:00 AST: move conDetailsArity into GHC.Rename.Module The function conDetailsArity is only used inside GHC.Rename.Module. We therefore move it there from Language.Haskell.Syntax.Lit. Progress towards #21592 - - - - - 381ba1cd by Mauricio at 2024-06-19T16:07:53+01:00 AST: Remove GHC.Utils.Assert from GHC Simple cleanup. Progress towards #21592 - - - - - 44104dae by Fabian Kirchner at 2024-06-19T16:07:53+01:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - c6a9f667 by Adowrath at 2024-06-19T16:10:19+01:00 ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type Progress towards #21592 This splits HsSrcBang up, creating the new HsBang within `Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness and strictness information, while `HsSrcBang` only adds the SourceText for usage within the compiler directly. Inside the AST, to preserve the SourceText, it is hidden behind the pre-existing extension point `XBindTy`. All other occurrences of `HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when interacting with the `BindTy` constructor, the hidden `SourceText` is extracted/inserted into the `XBindTy` extension point. `GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for convenience. A constructor function `mkHsSrcBang` that takes all individual components has been added. Two exceptions has been made though: - The `Outputable HsSrcBang` instance is replaced by `Outputable HsBang`. While being only GHC-internal, the only place it's used is in outputting `HsBangTy` constructors -- which already have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just to ignore the `SourceText` anyway. - The error `TcRnUnexpectedAnnotation` did not use the `SourceText`, so it too now only holds a `HsBang`. - - - - - 1ca7365d by Mauricio at 2024-06-19T16:10:19+01:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - 30 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Opt/Simplify.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/Predicate.hs - compiler/GHC/Core/Rules.hs - compiler/GHC/Core/SimpleOpt.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Utils.hs - compiler/GHC/CoreToIface.hs - compiler/GHC/Driver/Config/Core/Lint.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Lit.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/Hs/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b6c6b315ecd0df35c87cb6d1a64edbcbfca55002...1ca7365dae33407ddc3f3b68008d876823d4011e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/b6c6b315ecd0df35c87cb6d1a64edbcbfca55002...1ca7365dae33407ddc3f3b68008d876823d4011e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 15:46:54 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Wed, 19 Jun 2024 11:46:54 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/remove-pragma Message-ID: <6672fd6ec622a_1334da141b3b4453a3@gitlab.mail> Matthew Pickering pushed new branch wip/remove-pragma at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/remove-pragma You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 16:25:38 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 19 Jun 2024 12:25:38 -0400 Subject: [Git][ghc/ghc][wip/T24938] 36 commits: compiler: Make ghc-experimental not wired in Message-ID: <66730682123d0_1334da1912fc056154@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24938 at Glasgow Haskell Compiler / GHC Commits: b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - d70abb49 by sheaf at 2024-06-18T18:47:20-04:00 Clarify -XGADTs enables existential quantification Even though -XGADTs does not turn on -XExistentialQuantification, it does allow the user of existential quantification syntax, without needing to use GADT-style syntax. Fixes #20865 - - - - - 13fdf788 by David Binder at 2024-06-18T18:48:02-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 1bab7dde by Fendor at 2024-06-18T18:48:38-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18698b T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The tests T16875 and T18698b fail on i386-linux for the same reason. - - - - - 099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - 5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00 Update user guide to indicate support for 64-tuples - - - - - 4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00 Remove duplicate Anno instances - - - - - 8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00 AArch64: Delete unused RegNos This has the additional benefit of getting rid of the -1 encoding (real registers start at 0.) - - - - - 325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00 Bump stm submodule to current master - - - - - 64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00 testsuite: bump T17572 timeout on wasm32 - - - - - eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00 AArch64: Simplify BL instruction The BL constructor carried unused data in its third argument. - - - - - b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00 TTG: Move SourceText from `Fixity` to `FixitySig` It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Precedes !12842, to simplify it - - - - - 842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00 base: Deprecate some .Internal modules Deprecates the following modules according to clc-proposal #217: https://github.com/haskell/core-libraries-committee/issues/217 * GHC.TypeNats.Internal * GHC.TypeLits.Internal * GHC.ExecutionStack.Internal Closes #24998 - - - - - 9cecd5ad by Simon Peyton Jones at 2024-06-19T17:22:36+01:00 Fix untouchability test Addresses #24938 more documentation to come - - - - - 5bac4438 by Simon Peyton Jones at 2024-06-19T17:24:12+01:00 Wibbles - - - - - 30 changed files: - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Opt/SpecConstr.hs - compiler/GHC/Core/TyCo/FVs.hs - compiler/GHC/Core/TyCo/Ppr.hs - compiler/GHC/Core/TyCo/Tidy.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Hs.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Match.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/046e255d023c2954d475d14d19c784a9a76341a7...5bac4438d07035d1266023502566648ba21bfddf -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/046e255d023c2954d475d14d19c784a9a76341a7...5bac4438d07035d1266023502566648ba21bfddf You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 19:26:10 2024 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Wed, 19 Jun 2024 15:26:10 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ttg-zurich] 16 commits: Clarify -XGADTs enables existential quantification Message-ID: <667330d281708_1334da2f65c78773bc@gitlab.mail> Alan Zimmerman pushed to branch wip/kirchner/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: d70abb49 by sheaf at 2024-06-18T18:47:20-04:00 Clarify -XGADTs enables existential quantification Even though -XGADTs does not turn on -XExistentialQuantification, it does allow the user of existential quantification syntax, without needing to use GADT-style syntax. Fixes #20865 - - - - - 13fdf788 by David Binder at 2024-06-18T18:48:02-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 1bab7dde by Fendor at 2024-06-18T18:48:38-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18698b T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The tests T16875 and T18698b fail on i386-linux for the same reason. - - - - - 099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - 5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00 Update user guide to indicate support for 64-tuples - - - - - 4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00 Remove duplicate Anno instances - - - - - 8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00 AArch64: Delete unused RegNos This has the additional benefit of getting rid of the -1 encoding (real registers start at 0.) - - - - - 325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00 Bump stm submodule to current master - - - - - 64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00 testsuite: bump T17572 timeout on wasm32 - - - - - eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00 AArch64: Simplify BL instruction The BL constructor carried unused data in its third argument. - - - - - b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00 TTG: Move SourceText from `Fixity` to `FixitySig` It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Precedes !12842, to simplify it - - - - - 842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00 base: Deprecate some .Internal modules Deprecates the following modules according to clc-proposal #217: https://github.com/haskell/core-libraries-committee/issues/217 * GHC.TypeNats.Internal * GHC.TypeLits.Internal * GHC.ExecutionStack.Internal Closes #24998 - - - - - 87553a50 by romes at 2024-06-19T20:22:21+01:00 TTG HsCmdArrForm: use Fixity via extension point Also migrate Fixity from GHC.Hs to Language.Haskell.Syntax since it no longer uses any GHC-specific data types. Fixed arrow desugaring bug. (This was dead code before.) Co-authored-by: Fabian Kirchner <kirchner at posteo.de> Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/Hs.hs - + compiler/GHC/Hs/Basic.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/Fixity.hs - compiler/GHC/Rename/HsType.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8008334174728e39b4aacf21158a6dd7bf8f524e...87553a50fa428b28fa655911ec46f195b862776c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/8008334174728e39b4aacf21158a6dd7bf8f524e...87553a50fa428b28fa655911ec46f195b862776c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 19:44:07 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 19 Jun 2024 15:44:07 -0400 Subject: [Git][ghc/ghc][wip/T24938] Fix untouchability test Message-ID: <667335079a16f_1334da32739b0797f1@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24938 at Glasgow Haskell Compiler / GHC Commits: df2fde33 by Simon Peyton Jones at 2024-06-19T20:43:50+01:00 Fix untouchability test This MR fixes #24938. The underlying problem was tha the test for "does this implication bring in scope any equalities" was plain wrong. See Note [Tracking Given equalities] and Note [Let-bound skolems] both in GHC.Tc.Solver.InertSet. Then * Test LocalGivenEqs succeeds for a different reason than before; see (LBS2) in Note [Let-bound skolems] * New test T24938a succeeds because of (LBS2), whereas it failed before. * Test LocalGivenEqs2 now fails, as it should. * Test T224938, the repro from the ticket, fails, as it should. - - - - - 13 changed files: - compiler/GHC/Tc/Solver/InertSet.hs - testsuite/tests/indexed-types/should_fail/T13784.stderr - testsuite/tests/linters/notes.stdout - testsuite/tests/patsyn/should_fail/T11010.stderr - testsuite/tests/typecheck/should_compile/LocalGivenEqs.hs - testsuite/tests/typecheck/should_compile/LocalGivenEqs2.hs - + testsuite/tests/typecheck/should_compile/LocalGivenEqs2.stderr - + testsuite/tests/typecheck/should_compile/T24938a.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T22645.stderr - + testsuite/tests/typecheck/should_fail/T24938.hs - + testsuite/tests/typecheck/should_fail/T24938.stderr - testsuite/tests/typecheck/should_fail/all.T Changes: ===================================== compiler/GHC/Tc/Solver/InertSet.hs ===================================== @@ -647,11 +647,16 @@ enclosing Given equality. Exactly which constraints should trigger (UNTOUCHABLE), and hence should update inert_given_eq_lvl? -* We do /not/ need to worry about let-bound skolems, such ast +(TGE1) We do /not/ need to worry about let-bound skolems, such as forall[2] a. a ~ [b] => blah - See Note [Let-bound skolems] + See Note [Let-bound skolems] and the isOuterTyVar tests in `updGivenEqs` -* Consider an implication +(TGE2) However, solely to support better error messages (see Note [HasGivenEqs] in + GHC.Tc.Types.Constraint) we also track these "local" equalities in the + boolean inert_given_eqs field. This field is used only subsequntly (see + `getHasGivenEqs`), to set the ic_given_eqs field to LocalGivenEqs. + +(TGE3) Consider an implication forall[2]. beta[1] => alpha[1] ~ Int where beta is a unification variable that has already been unified to () in an outer scope. Then alpha[1] is perfectly touchable and @@ -659,64 +664,66 @@ should update inert_given_eq_lvl? an equality, we should canonicalise first, rather than just looking at the /original/ givens (#8644). - * However, we must take account of *potential* equalities. Consider the +(TGE4) However, we must take account of *potential* equalities. Consider the same example again, but this time we have /not/ yet unified beta: forall[2] beta[1] => ...blah... Because beta might turn into an equality, updGivenEqs conservatively treats it as a potential equality, and updates inert_give_eq_lvl - * What about something like forall[2] a b. a ~ F b => [W] alpha[1] ~ X y z? - - That Given cannot affect the Wanted, because the Given is entirely - *local*: it mentions only skolems bound in the very same - implication. Such equalities need not make alpha untouchable. (Test - case typecheck/should_compile/LocalGivenEqs has a real-life - motivating example, with some detailed commentary.) - Hence the 'mentionsOuterVar' test in updGivenEqs. - - However, solely to support better error messages - (see Note [HasGivenEqs] in GHC.Tc.Types.Constraint) we also track - these "local" equalities in the boolean inert_given_eqs field. - This field is used only to set the ic_given_eqs field to LocalGivenEqs; - see the function getHasGivenEqs. - - Here is a simpler case that triggers this behaviour: - - data T where - MkT :: F a ~ G b => a -> b -> T - - f (MkT _ _) = True - - Because of this behaviour around local equality givens, we can infer the - type of f. This is typecheck/should_compile/LocalGivenEqs2. - - * We need not look at the equality relation involved (nominal vs +(TGE5) We should not look at the equality relation involved (nominal vs representational), because representational equalities can still imply nominal ones. For example, if (G a ~R G b) and G's argument's role is nominal, then we can deduce a ~N b. +Historical note: prior to #24938 we also ignored Given equalities that +did not mention an "outer" type variable. But that is wrong, as #24938 +showed. Another example is immortalised in test LocalGivenEqs2 + data T where + MkT :: F a ~ G b => a -> b -> T + f (MkT _ _) = True +We should not infer the type for `f`; let-bound-skolems does not apply. + Note [Let-bound skolems] ~~~~~~~~~~~~~~~~~~~~~~~~ If * the inert set contains a canonical Given CEqCan (a ~ ty) and * 'a' is a skolem bound in this very implication, then: -a) The Given is pretty much a let-binding, like - f :: (a ~ b->c) => a -> a - Here the equality constraint is like saying - let a = b->c in ... - It is not adding any new, local equality information, - and hence can be ignored by has_given_eqs + a) The Given is pretty much a let-binding, like + f :: (a ~ b->c) => a -> a + Here the equality constraint is like saying + let a = b->c in ... + It is not adding any new, local equality information, + and hence can be ignored by has_given_eqs -b) 'a' will have been completely substituted out in the inert set, - so we can safely discard it. + b) 'a' will have been completely substituted out in the inert set, + so we can safely discard it. For an example, see #9211. -See also GHC.Tc.Utils.Unify Note [Deeper level on the left] for how we ensure -that the right variable is on the left of the equality when both are -tyvars. +The actual test is in `isLetBoundSkolemCt` + +Wrinkles: + +(LBS1) See GHC.Tc.Utils.Unify Note [Deeper level on the left] for how we ensure + that the correct variable is on the left of the equality when both are + tyvars. + +(LBS2) We also want this to work for + forall a. [G] F b ~ a (CEqCt with TyFamLHS) + Here the Given will have a TyFamLHS, with the skolem-bound tyvar on the RHS. + See tests T24938a, and LocalGivenEqs. + +(LBS3) Happily (LBS2) also makes cycle-breakers work. Suppose we have + forall a. [G] (F a) Int ~ a + where F has arity 1, and `a` is the locally-bound skolem. Then, as + Note [Type equality cycles] explains, we split into + [G] F a ~ cbv, [G] cbv Int ~ a + where `cbv` is the cycle breaker variable. But cbv has the same level + as `a`, so `isOuterTyVar` (called in `isLetBoundSkolemCt`) will return False. + + This actually matters occasionally: see test LocalGivenEqs. You might wonder whether the skolem really needs to be bound "in the very same implication" as the equality constraint. @@ -741,6 +748,18 @@ body of the lambda we'll get Now, unify alpha := a. Now we are stuck with an unsolved alpha~Int! So we must treat alpha as untouchable under the forall[2] implication. +Possible future improvements. The current test just looks to see whether one +side of an equality is a locally-bound skolem. But actually we could, in +theory, do better: if one side (or both sides, actually) of an equality +ineluctably mentions a local skolem, then the equality cannot possibly impact +types outside of the implication (because doing to would cause those types to be +ill-scoped). The problem is the "ineluctably": this means that no expansion, +other solving, etc., could possibly get rid of the variable. This is hard, +perhaps impossible, to know for sure, especially when we think about type family +interactions. (And it's a user-visible property so we don't want it to be hard +to predict.) So we keep the existing check, looking for one lone variable, +because we're sure that variable isn't going anywhere. + Note [Detailed InertCans Invariants] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The InertCans represents a collection of constraints with the following properties: @@ -1467,27 +1486,28 @@ updGivenEqs :: TcLevel -> Ct -> InertCans -> InertCans -- if the constraint is a given equality that should prevent -- filling in an outer unification variable. -- See Note [Tracking Given equalities] -updGivenEqs tclvl ct inerts@(IC { inert_given_eq_lvl = ge_lvl }) +-- +-- Precondition: Ct is either CEqCan or CIrredCan +updGivenEqs tclvl ct inerts | not (isGivenCt ct) = inerts - | not_equality ct = inerts -- See Note [Let-bound skolems] - | otherwise = inerts { inert_given_eq_lvl = ge_lvl' - , inert_given_eqs = True } - where - ge_lvl' | mentionsOuterVar tclvl (ctEvidence ct) - -- Includes things like (c a), which *might* be an equality - = tclvl - | otherwise - = ge_lvl - - not_equality :: Ct -> Bool - -- True <=> definitely not an equality of any kind - -- except for a let-bound skolem, which doesn't count - -- See Note [Let-bound skolems] - -- NB: no need to spot the boxed CDictCan (a ~ b) because its - -- superclass (a ~# b) will be a CEqCan - not_equality (CEqCan (EqCt { eq_lhs = TyVarLHS tv })) = not (isOuterTyVar tclvl tv) - not_equality (CDictCan {}) = True - not_equality _ = False + + -- See Note [Let-bound skolems] + | isLetBoundSkolemCt tclvl ct = inerts { inert_given_eqs = True } + + -- At this point we are left with a constraint that either + -- is an equality (F a ~ ty), or /might/ be, like (c a) + | otherwise = inerts { inert_given_eq_lvl = tclvl + , inert_given_eqs = True } + +isLetBoundSkolemCt :: TcLevel -> Ct -> Bool +-- See Note [Let-bound skolems] +isLetBoundSkolemCt tclvl (CEqCan (EqCt { eq_lhs = lhs, eq_rhs = rhs })) + = case lhs of + TyVarLHS tv -> not (isOuterTyVar tclvl tv) + TyFamLHS {} -> case getTyVar_maybe rhs of + Just tv -> not (isOuterTyVar tclvl tv) + Nothing -> False +isLetBoundSkolemCt _ _ = False data KickOutSpec -- See Note [KickOutSpec] = KOAfterUnify TcTyVarSet -- We have unified these tyvars @@ -1732,11 +1752,6 @@ Hence: * * ********************************************************************* -} -mentionsOuterVar :: TcLevel -> CtEvidence -> Bool -mentionsOuterVar tclvl ev - = anyFreeVarsOfType (isOuterTyVar tclvl) $ - ctEvPred ev - isOuterTyVar :: TcLevel -> TyCoVar -> Bool -- True of a type variable that comes from a -- shallower level than the ambient level (tclvl) ===================================== testsuite/tests/indexed-types/should_fail/T13784.stderr ===================================== @@ -1,6 +1,10 @@ - T13784.hs:29:28: error: [GHC-25897] - • Couldn't match type ‘as’ with ‘a : Divide a as’ + • Could not deduce ‘as ~ (a : Divide a as)’ + from the context: (a : as) ~ (a1 : as1) + bound by a pattern with constructor: + :* :: forall a (as :: [*]). a -> Product as -> Product (a : as), + in an equation for ‘divide’ + at T13784.hs:29:13-19 Expected: Product (Divide a (a : as)) Actual: Product as1 ‘as’ is a rigid type variable bound by @@ -36,3 +40,4 @@ T13784.hs:33:29: error: [GHC-83865] • Relevant bindings include divide :: Product (a : as) -> (b, Product (Divide b (a : as))) (bound at T13784.hs:33:5) + ===================================== testsuite/tests/linters/notes.stdout ===================================== @@ -44,8 +44,6 @@ ref testsuite/tests/perf/should_run/all.T:8:6: Note [Solving from instanc ref testsuite/tests/polykinds/CuskFam.hs:16:11: Note [Unifying implicit CUSK variables] ref testsuite/tests/simplCore/should_compile/T5776.hs:16:7: Note [Simplifying RULE lhs constraints] ref testsuite/tests/simplCore/should_compile/simpl018.hs:3:7: Note [Float coercions] -ref testsuite/tests/typecheck/should_compile/LocalGivenEqs.hs:7:7: Note [When does an implication have given equalities?] -ref testsuite/tests/typecheck/should_compile/LocalGivenEqs2.hs:4:6: Note [When does an implication have given equalities?] ref testsuite/tests/typecheck/should_compile/T9117.hs:3:12: Note [Order of Coercible Instances] ref testsuite/tests/typecheck/should_compile/tc200.hs:5:7: Note [Multiple instantiation] ref testsuite/tests/typecheck/should_compile/tc228.hs:9:7: Note [Inference and implication constraints] ===================================== testsuite/tests/patsyn/should_fail/T11010.stderr ===================================== @@ -1,6 +1,8 @@ - T11010.hs:9:34: error: [GHC-25897] - • Couldn't match type ‘a1’ with ‘Int’ + • Could not deduce ‘a1 ~ Int’ + from the context: a ~ Int + bound by the signature for pattern synonym ‘IntFun’ + at T11010.hs:9:1-36 Expected: a -> b Actual: a1 -> b ‘a1’ is a rigid type variable bound by @@ -15,3 +17,4 @@ T11010.hs:9:34: error: [GHC-25897] | 9 | pattern IntFun str f x = Fun str f x | ^ + ===================================== testsuite/tests/typecheck/should_compile/LocalGivenEqs.hs ===================================== @@ -4,7 +4,7 @@ module LocalGivenEqs where --- See Note [When does an implication have given equalities?] in GHC.Tc.Solver.Monad; +-- See Note [Tracking Given equalities] in GHC.Tc.Solver.InertSet; -- this tests custom treatment for LocalGivenEqs {- ===================================== testsuite/tests/typecheck/should_compile/LocalGivenEqs2.hs ===================================== @@ -1,9 +1,7 @@ {-# LANGUAGE TypeFamilies, GADTSyntax, ExistentialQuantification #-} --- This is a simple case that exercises the LocalGivenEqs bullet --- of Note [When does an implication have given equalities?] in GHC.Tc.Solver.Monad --- If a future change rejects this, that's not the end of the world, but it's nice --- to be able to infer `f`. +-- This one should be rejected. +-- See Note [Tracking Given equalities] in GHC.Tc.Solver.InertSet module LocalGivenEqs2 where ===================================== testsuite/tests/typecheck/should_compile/LocalGivenEqs2.stderr ===================================== @@ -0,0 +1,16 @@ +LocalGivenEqs2.hs:14:15: error: [GHC-25897] + • Could not deduce ‘p ~ Bool’ + from the context: F a ~ G b + bound by a pattern with constructor: + MkT :: forall a b. (F a ~ G b) => a -> b -> T, + in an equation for ‘f’ + at LocalGivenEqs2.hs:14:4-10 + ‘p’ is a rigid type variable bound by + the inferred type of f :: T -> p + at LocalGivenEqs2.hs:14:1-18 + • In the expression: True + In an equation for ‘f’: f (MkT _ _) = True + • Relevant bindings include + f :: T -> p (bound at LocalGivenEqs2.hs:14:1) + Suggested fix: Consider giving ‘f’ a type signature + ===================================== testsuite/tests/typecheck/should_compile/T24938a.hs ===================================== @@ -0,0 +1,11 @@ +{-# LANGUAGE TypeFamilies, GADTs #-} + +module T24938a where + +type family F a + +data T b where + MkT :: forall a b. F b ~ a => a -> T b + -- This equality is a let-bound skolem + +f (MkT x) = True ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -762,7 +762,7 @@ test('InstanceGivenOverlap2', expect_broken(20076), compile_fail, ['']) test('T19044', normal, compile, ['']) test('T19052', normal, compile, ['']) test('LocalGivenEqs', normal, compile, ['']) -test('LocalGivenEqs2', normal, compile, ['']) +test('LocalGivenEqs2', normal, compile_fail, ['']) test('T18891', normal, compile, ['']) test('TyAppPat_Existential', normal, compile, ['']) @@ -918,3 +918,5 @@ test('T23764', normal, compile, ['']) test('T23739a', normal, compile, ['']) test('T24810', normal, compile, ['']) test('T24887', normal, compile, ['']) +test('T24938a', normal, compile, ['']) + ===================================== testsuite/tests/typecheck/should_fail/T22645.stderr ===================================== @@ -1,6 +1,9 @@ - T22645.hs:9:5: error: [GHC-25897] - • Couldn't match type ‘a’ with ‘b’ arising from a use of ‘coerce’ + • Could not deduce ‘a ~ b’ arising from a use of ‘coerce’ + from the context: Coercible a b + bound by the type signature for: + p :: forall a b. Coercible a b => T Maybe a -> T Maybe b + at T22645.hs:8:1-44 ‘a’ is a rigid type variable bound by the type signature for: p :: forall a b. Coercible a b => T Maybe a -> T Maybe b @@ -13,3 +16,4 @@ T22645.hs:9:5: error: [GHC-25897] In an equation for ‘p’: p = coerce • Relevant bindings include p :: T Maybe a -> T Maybe b (bound at T22645.hs:9:1) + ===================================== testsuite/tests/typecheck/should_fail/T24938.hs ===================================== @@ -0,0 +1,33 @@ +{-# LANGUAGE TypeFamilyDependencies, PartialTypeSignatures #-} + +module T24938 where + +import Prelude (Int, String, undefined) + +data Eq a b where + Refl :: Eq a a + +type family Mt a = r | r -> a + +anyM :: Mt a +anyM = undefined + +useIntAndRaise :: Mt Int -> a +useIntAndRaise = undefined + +type family Nt a = r | r -> a + +use :: Nt a -> a +use = undefined + +anyN :: Nt a +anyN = undefined + +foo p (e :: Eq (Mt Int) (Nt String)) = + (case e of + Refl -> + let bar x = + if p then useIntAndRaise x + else use x + in + bar) anyM ===================================== testsuite/tests/typecheck/should_fail/T24938.stderr ===================================== @@ -0,0 +1,19 @@ +T24938.hs:30:16: error: [GHC-25897] + • Could not deduce ‘p ~ GHC.Types.Bool’ + from the context: Nt String ~ Mt Int + bound by a pattern with constructor: + Refl :: forall {k} (a :: k). Eq a a, + in a case alternative + at T24938.hs:28:5-8 + ‘p’ is a rigid type variable bound by + the inferred type of foo :: p -> Eq (Mt Int) (Nt String) -> t + at T24938.hs:(26,1)-(33,17) + • In the expression: p + In the expression: if p then useIntAndRaise x else use x + In an equation for ‘bar’: + bar x = if p then useIntAndRaise x else use x + • Relevant bindings include + p :: p (bound at T24938.hs:26:5) + foo :: p -> Eq (Mt Int) (Nt String) -> t (bound at T24938.hs:26:1) + Suggested fix: Consider giving ‘foo’ a type signature + ===================================== testsuite/tests/typecheck/should_fail/all.T ===================================== @@ -728,3 +728,4 @@ test('T24470a', normal, compile_fail, ['']) test('T24553', normal, compile_fail, ['']) test('T23739b', normal, compile_fail, ['']) test('T24868', normal, compile_fail, ['']) +test('T24938', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/df2fde33d54b02afdcc99bc860cc11f952d0d240 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/df2fde33d54b02afdcc99bc860cc11f952d0d240 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 21:21:52 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 19 Jun 2024 17:21:52 -0400 Subject: [Git][ghc/ghc][wip/T24725] Faster type equality Message-ID: <66734bf08c80c_1334da3e6afe8902fa@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24725 at Glasgow Haskell Compiler / GHC Commits: 56f6962b by Simon Peyton Jones at 2024-06-19T22:21:17+01:00 Faster type equality This MR speeds up type equality, triggered by perf regressions that showed up when fixing #24725 by parameterising type equality over whether to ignore multiplicity. The changes are: * Do not use `nonDetCmpType` for type /equality/. Instead use a specialised type-equality function, which we have always had! `nonDetCmpType` remains, but I did not invest effort in refactoring or optimising it. * Type equality is parameterised by - whether to expand synonyms - whether to respect multiplicities - whether it has a RnEnv2 environment In this MR I systematically specialise it for static values of these parameters. Much more direct and predictable than before. See Note [Specialising type equality] * We want to avoid comparing kinds if possible. I refactored how this happens, at least for `eqType`. See Note [Casts and coercions in type comparison] * To make Lint fast, we want to avoid allocating a thunk for <msg> in ensureEqTypes ty1 ty2 <msg> because the test almost always succeeds, and <msg> isn't needed. See Note [INLINE ensureEqTys] Metric Decrease: T13386 T5030 - - - - - 6 changed files: - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Multiplicity.hs - compiler/GHC/Core/TyCo/Compare.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Utils/TcType.hs Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -53,7 +53,7 @@ import GHC.Core.Predicate( isCoVarType ) import GHC.Core.Multiplicity import GHC.Core.UsageEnv import GHC.Core.TyCo.Rep -- checks validity of types/coercions -import GHC.Core.TyCo.Compare ( eqType, eqTypeOpt, defaultCmpTypeOpt, CmpTypeOpt (..), eqForAllVis ) +import GHC.Core.TyCo.Compare ( eqType, eqTypes, eqTypeIgnoringMultiplicity, eqForAllVis ) import GHC.Core.TyCo.Subst import GHC.Core.TyCo.FVs import GHC.Core.TyCo.Ppr @@ -2807,7 +2807,7 @@ lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches extra_checks | isNewTyCon tc - = do { CoAxBranch { cab_tvs = tvs + = do { CoAxBranch { cab_tvs = ax_tvs , cab_eta_tvs = eta_tvs , cab_cvs = cvs , cab_roles = roles @@ -2815,14 +2815,10 @@ lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches <- case branch_list of [branch] -> return branch _ -> failWithL (text "multi-branch axiom with newtype") - ; let ax_lhs = mkInfForAllTys tvs $ - mkTyConApp tc lhs_tys - nt_tvs = takeList tvs (tyConTyVars tc) - -- axiom may be eta-reduced: Note [Newtype eta] in GHC.Core.TyCon - nt_lhs = mkInfForAllTys nt_tvs $ - mkTyConApp tc (mkTyVarTys nt_tvs) - -- See Note [Newtype eta] in GHC.Core.TyCon - ; lintL (ax_lhs `eqType` nt_lhs) + + -- The LHS of the axiom is (N lhs_tys) + -- We expect it to be (N ax_tvs) + ; lintL (mkTyVarTys ax_tvs `eqTypes` lhs_tys) (text "Newtype axiom LHS does not match newtype definition") ; lintL (null cvs) (text "Newtype axiom binds coercion variables") @@ -2831,7 +2827,7 @@ lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches (text "Newtype axiom has eta-tvs") ; lintL (ax_role == Representational) (text "Newtype axiom role not representational") - ; lintL (roles `equalLength` tvs) + ; lintL (roles `equalLength` ax_tvs) (text "Newtype axiom roles list is the wrong length." $$ text "roles:" <+> sep (map ppr roles)) ; lintL (roles == takeList roles (tyConRoles tc)) @@ -3101,17 +3097,14 @@ Note [Linting linearity] Lint ignores linearity unless `-dlinear-core-lint` is set. For why, see below. But first, "ignore linearity" specifically means two things. When ignoring linearity: -* In `ensureEqTypes`, use `eqTypeOpt` with instructions to ignore multiplicities in FunTy. +* In `ensureEqTypes`, use `eqTypeIgnoringMultiplicity` * In `ensureSubMult`, do nothing -The behaviour of functions such as eqTypeOpt which may or may not ignore -linearity is governed by a flag of type GHC.Core.Multiplicity.MultiplicityFlag. - -But why make `-dcore-lint` ignore linearity? Because -optimisation passes are not (yet) guaranteed to maintain linearity. They should -do so semantically (GHC is careful not to duplicate computation) but it is much -harder to ensure that the statically-checkable constraints of Linear Core are -maintained. The current Linear Core is described in the wiki at: +But why make `-dcore-lint` ignore linearity? Because optimisation passes are +not (yet) guaranteed to maintain linearity. They should do so semantically (GHC +is careful not to duplicate computation) but it is much harder to ensure that +the statically-checkable constraints of Linear Core are maintained. The current +Linear Core is described in the wiki at: https://gitlab.haskell.org/ghc/ghc/-/wikis/linear-types/implementation. Here are some examples of how the optimiser can break linearity checking. Other @@ -3495,17 +3488,25 @@ ensureEqTys :: LintedType -> LintedType -> SDoc -> LintM () -- check ty2 is subtype of ty1 (ie, has same structure but usage -- annotations need only be consistent, not equal) -- Assumes ty1,ty2 are have already had the substitution applied -ensureEqTys ty1 ty2 msg = do - flags <- getLintFlags - -- When `-dlinear-core-lint` is off, then consider `a -> b` and `a %1 -> b` to - -- be equal. See Note [Linting linearity]. - lintL (eqTypeOpt (opt flags) ty1 ty2) msg - where - opt flags = - if lf_check_linearity flags then - defaultCmpTypeOpt { cmp_multiplicity_in_funty = RespectMultiplicities } - else - defaultCmpTypeOpt { cmp_multiplicity_in_funty = IgnoreMultiplicities } +{-# INLINE ensureEqTys #-} -- See Note [INLINE ensureEqTys] +ensureEqTys ty1 ty2 msg + = do { flags <- getLintFlags + ; lintL (eq_type flags ty1 ty2) msg } + +eq_type :: LintFlags -> Type -> Type -> Bool +-- When `-dlinear-core-lint` is off, then consider `a -> b` and `a %1 -> b` to +-- be equal. See Note [Linting linearity]. +eq_type flags ty1 ty2 | lf_check_linearity flags = eqType ty1 ty2 + | otherwise = eqTypeIgnoringMultiplicity ty1 ty2 + +{- Note [INLINE ensureEqTys] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +To make Lint fast, we want to avoid allocating a thunk for in + ensureEqTypes ty1 ty2 +because the test almost always succeeds, and isn't needed. +So we INLINE `ensureEqTys`. This actually make a difference of +1-2% when compiling programs with -dcore-lint. +-} ensureSubUsage :: Usage -> Mult -> SDoc -> LintM () ensureSubUsage Bottom _ _ = return () ===================================== compiler/GHC/Core/Multiplicity.hs ===================================== @@ -31,7 +31,8 @@ module GHC.Core.Multiplicity , submult , mapScaledType , pprArrowWithMultiplicity - , MultiplicityFlag(..)) where + , MultiplicityFlag(..) + ) where import GHC.Prelude ===================================== compiler/GHC/Core/TyCo/Compare.hs ===================================== @@ -7,16 +7,17 @@ -- | Type equality and comparison module GHC.Core.TyCo.Compare ( - -- * Type comparison - eqType, eqTypeOpt, eqTypeX, eqTypes, nonDetCmpType, nonDetCmpTypes, nonDetCmpTypeX, - nonDetCmpTypesX, nonDetCmpTc, + -- * Type equality + eqType, eqTypeIgnoringMultiplicity, eqTypeX, eqTypes, eqVarBndrs, - CmpTypeOpt (..), defaultCmpTypeOpt, pickyEqType, tcEqType, tcEqKind, tcEqTypeNoKindCheck, tcEqTyConApps, mayLookIdentical, + -- * Type comparison + nonDetCmpType, + -- * Visiblity comparision eqForAllVis, cmpForAllVis @@ -30,10 +31,12 @@ import GHC.Core.Type( typeKind, coreView, tcSplitAppTyNoView_maybe, splitAppTyNo import GHC.Core.TyCo.Rep import GHC.Core.TyCo.FVs import GHC.Core.TyCon +import GHC.Core.Multiplicity( MultiplicityFlag(..) ) import GHC.Types.Var import GHC.Types.Unique import GHC.Types.Var.Env +import GHC.Types.Var.Set import GHC.Utils.Outputable import GHC.Utils.Misc @@ -42,7 +45,6 @@ import GHC.Utils.Panic import GHC.Base (reallyUnsafePtrEquality#) import qualified Data.Semigroup as S -import GHC.Core.Multiplicity {- GHC.Core.TyCo.Compare overview ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -54,7 +56,11 @@ so it currently sits "on top of" GHC.Core.Type. {- ********************************************************************* * * - Type equality + Type equality + + We don't use (==) from class Eq, partly so that we know where + type equality is called, and partly because there are multiple + variants. * * ********************************************************************* -} @@ -74,6 +80,93 @@ that needs to be updated. * See Historical Note [Typechecker equality vs definitional equality] below +Note [Casts and coercions in type comparision] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +As (EQTYPE) in Note [Non-trivial definitional equality] says, our +general plan, implemented by `fullEq`, is: + (1) ignore both casts and coercions when comparing types, + (2) instead, compare the /kinds/ of the two types, + as well as the types themselves + +If possible we want to avoid step (2), comparing the kinds; doing so involves +calling `typeKind` and doing another comparision. + +When can we avoid doing so? Answer: we can certainly avoid doing so if the +types we are comparing have no casts or coercions. But we can do better. +Consider + eqType (TyConApp T [s1, ..., sn]) (TyConApp T [t1, .., tn]) +We are going to call (eqType s1 t1), (eqType s2 t2) etc. + +The kinds of `s1` and `t1` must be equal, because these TyConApps are well-kinded, +and both TyConApps are headed by the same T. So the first recursive call to `eqType` +certainly doesn't need to check kinds. If that call returns False, we stop. Otherwise, +we know that `s1` and `t1` are themselves equal (not just their kinds). This +makes the kinds of `s2` and `t2` to be equal, because those kinds come from the +kind of T instantiated with `s1` and `t1` -- which are the same. Thus we do not +need to check the kinds of `s2` and `t2`. By induction, we don't need to check +the kinds of *any* of the types in a TyConApp, and we also do not need to check +the kinds of the TyConApps themselves. + +Conclusion: + +* casts and coercions under a TyConApp don't matter -- even including type synonyms + +* In step (2), use `hasCasts` to tell if there are any casts to worry about. It + does not look very deep, because TyConApps and FunTys are so common, and it + doesn't allocate. The only recursive cases are AppTy and ForAllTy. + +Alternative implementation. Instead of `hasCasts`, we could make the +generic_eq_type function return + data EqResult = NotEq | EqWithNoCasts | EqWithCasts +Practically free; but stylistically I prefer useing `hasCasts`: + * `generic_eq_type` can just uses familiar booleans + * There is a lot more branching with the three-value variant. + * It separates concerns. No need to think about cast-tracking when doing the + equality comparison. + * Indeed sometimes we omit the kind check unconditionally, so tracking it is just wasted + work. +I did try both; there was no perceptible perf difference so I chose `hasCasts` version. + +Note [Equality on AppTys] +~~~~~~~~~~~~~~~~~~~~~~~~~ +In our cast-ignoring equality, we want to say that the following two +are equal: + + (Maybe |> co) (Int |> co') ~? Maybe Int + +But the left is an AppTy while the right is a TyConApp. The solution is +to use splitAppTyNoView_maybe to break up the TyConApp into its pieces and +then continue. Easy to do, but also easy to forget to do. + +Note [Comparing nullary type synonyms] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider the task of testing equality between two 'Type's of the form + + TyConApp tc [] + +where @tc@ is a type synonym. A naive way to perform this comparison these +would first expand the synonym and then compare the resulting expansions. + +However, this is obviously wasteful and the RHS of @tc@ may be large; it is +much better to rather compare the TyCons directly. Consequently, before +expanding type synonyms in type comparisons we first look for a nullary +TyConApp and simply compare the TyCons if we find one. Of course, if we find +that the TyCons are *not* equal then we still need to perform the expansion as +their RHSs may still be equal. + +We perform this optimisation in a number of places: + + * GHC.Core.Types.eqType + * GHC.Core.Types.nonDetCmpType + * GHC.Core.Unify.unify_ty + * GHC.Tc.Solver.Equality.can_eq_nc' + * TcUnify.uType + +This optimisation is especially helpful for the ubiquitous GHC.Types.Type, +since GHC prefers to use the type synonym over @TYPE 'LiftedRep@ applications +whenever possible. See Note [Using synonyms to compress types] in +GHC.Core.Type for details. + Note [Type comparisons using object pointer comparisons] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Quite often we substitute the type from a definition site into @@ -83,6 +176,21 @@ The type of every `x` will often be represented by a single object in the heap. We can take advantage of this by shortcutting the equality check if two types are represented by the same pointer under the hood. In some cases this reduces compiler allocations by ~2%. + +See Note [Pointer comparison operations] in GHC.Builtin.primops.txt.pp + +Note [Respecting multiplicity when comparing types] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Generally speaking, we respect multiplicities (i.e. the linear part of the type +system) when comparing types. Doing so is of course crucial during typechecking. + +But for reasons described in Note [Linting linearity] in GHC.Core.Lint, it is hard +to ensure that Core is always type-correct when it comes to linearity. So +* `eqTypeIgnoringMultiplicity` provides a way to compare types that /ignores/ multiplicities +* We use this multiplicity-blind comparison very occasionally, notably + - in Core Lint: see Note [Linting linearity] in GHC.Core.Lint + - in rule matching: see Note [Rewrite rules ignore multiplicities in FunTy] + in GHC.Core.Unify -} @@ -90,21 +198,12 @@ tcEqKind :: HasDebugCallStack => Kind -> Kind -> Bool tcEqKind = tcEqType tcEqType :: HasDebugCallStack => Type -> Type -> Bool --- ^ tcEqType implements typechecker equality --- It behaves just like eqType, but is implemented --- differently (for now) -tcEqType ty1 ty2 - = tcEqTypeNoSyns ki1 ki2 - && tcEqTypeNoSyns ty1 ty2 - where - ki1 = typeKind ty1 - ki2 = typeKind ty2 +tcEqType = eqType -- | Just like 'tcEqType', but will return True for types of different kinds -- as long as their non-coercion structure is identical. tcEqTypeNoKindCheck :: Type -> Type -> Bool -tcEqTypeNoKindCheck ty1 ty2 - = tcEqTypeNoSyns ty1 ty2 +tcEqTypeNoKindCheck = eqTypeNoKindCheck -- | Check whether two TyConApps are the same; if the number of arguments -- are different, just checks the common prefix of arguments. @@ -116,175 +215,220 @@ tcEqTyConApps tc1 args1 tc2 args2 -- any difference in the kinds of later arguments would show up -- as differences in earlier (dependent) arguments -{- -Note [Specialising tc_eq_type] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -The type equality predicates in Type are hit pretty hard during typechecking. -Consequently we take pains to ensure that these paths are compiled to -efficient, minimally-allocating code. - -To this end we place an INLINE on tc_eq_type, ensuring that it is inlined into -its publicly-visible interfaces (e.g. tcEqType). In addition to eliminating -some dynamic branches, this allows the simplifier to eliminate the closure -allocations that would otherwise be necessary to capture the two boolean "mode" -flags. This reduces allocations by a good fraction of a percent when compiling -Cabal. - -See #19226. --} - -mayLookIdentical :: Type -> Type -> Bool --- | Returns True if the /visible/ part of the types --- might look equal, even if they are really unequal (in the invisible bits) --- --- This function is very similar to tc_eq_type but it is much more --- heuristic. Notably, it is always safe to return True, even with types --- that might (in truth) be unequal -- this affects error messages only --- (Originally there were one function with an extra flag, but the result --- was hard to understand.) -mayLookIdentical orig_ty1 orig_ty2 - = go orig_env orig_ty1 orig_ty2 - where - orig_env = mkRnEnv2 $ mkInScopeSet $ tyCoVarsOfTypes [orig_ty1, orig_ty2] - - go :: RnEnv2 -> Type -> Type -> Bool - -- See Note [Comparing nullary type synonyms] - go _ (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = True - - go env t1 t2 | Just t1' <- coreView t1 = go env t1' t2 - go env t1 t2 | Just t2' <- coreView t2 = go env t1 t2' - go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 - go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 - go env (CastTy t1 _) t2 = go env t1 t2 - go env t1 (CastTy t2 _) = go env t1 t2 - go _ (CoercionTy {}) (CoercionTy {}) = True - - go env (ForAllTy (Bndr tv1 vis1) ty1) - (ForAllTy (Bndr tv2 vis2) ty2) - = vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] - && go (rnBndr2 env tv1 tv2) ty1 ty2 - -- Visible stuff only: ignore kinds of binders - - -- If we have (forall (r::RunTimeRep). ty1 ~ blah) then respond - -- with True. Reason: the type pretty-printer defaults RuntimeRep - -- foralls (see Ghc.Iface.Type.hideNonStandardTypes). That can make, - -- say (forall r. TYPE r -> Type) into (Type -> Type), so it looks the - -- same as a very different type (#24553). By responding True, we - -- tell GHC (see calls of mayLookIdentical) to display without defaulting. - -- See Note [Showing invisible bits of types in error messages] - -- in GHC.Tc.Errors.Ppr - go _ (ForAllTy b _) _ | isDefaultableBndr b = True - go _ _ (ForAllTy b _) | isDefaultableBndr b = True +-- | Type equality on lists of types, looking through type synonyms +eqTypes :: [Type] -> [Type] -> Bool +eqTypes [] [] = True +eqTypes (t1:ts1) (t2:ts2) = eqType t1 t2 && eqTypes ts1 ts2 +eqTypes _ _ = False - go env (FunTy _ w1 arg1 res1) (FunTy _ w2 arg2 res2) - = go env arg1 arg2 && go env res1 res2 && go env w1 w2 - -- Visible stuff only: ignore agg kinds +eqVarBndrs :: HasCallStack => RnEnv2 -> [Var] -> [Var] -> Maybe RnEnv2 +-- Check that the var lists are the same length +-- and have matching kinds; if so, extend the RnEnv2 +-- Returns Nothing if they don't match +eqVarBndrs env [] [] + = Just env +eqVarBndrs env (tv1:tvs1) (tv2:tvs2) + | eqTypeX env (varType tv1) (varType tv2) + = eqVarBndrs (rnBndr2 env tv1 tv2) tvs1 tvs2 +eqVarBndrs _ _ _= Nothing - -- See Note [Equality on AppTys] in GHC.Core.Type - go env (AppTy s1 t1) ty2 - | Just (s2, t2) <- tcSplitAppTyNoView_maybe ty2 - = go env s1 s2 && go env t1 t2 - go env ty1 (AppTy s2 t2) - | Just (s1, t1) <- tcSplitAppTyNoView_maybe ty1 - = go env s1 s2 && go env t1 t2 +initRnEnv :: Type -> Type -> RnEnv2 +initRnEnv ta tb = mkRnEnv2 $ mkInScopeSet $ + tyCoVarsOfType ta `unionVarSet` tyCoVarsOfType tb - go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) - = tc1 == tc2 && gos env (tyConBinders tc1) ts1 ts2 +eqTypeNoKindCheck :: Type -> Type -> Bool +eqTypeNoKindCheck ty1 ty2 = eq_type_expand_respect ty1 ty2 - go _ _ _ = False - - gos :: RnEnv2 -> [TyConBinder] -> [Type] -> [Type] -> Bool - gos _ _ [] [] = True - gos env bs (t1:ts1) (t2:ts2) - | (invisible, bs') <- case bs of - [] -> (False, []) - (b:bs) -> (isInvisibleTyConBinder b, bs) - = (invisible || go env t1 t2) && gos env bs' ts1 ts2 - - gos _ _ _ _ = False +-- | Type equality comparing both visible and invisible arguments, +-- expanding synonyms and respecting multiplicities. +eqType :: HasCallStack => Type -> Type -> Bool +eqType ta tb = fullEq eq_type_expand_respect ta tb +-- | Compare types with respect to a (presumably) non-empty 'RnEnv2'. +eqTypeX :: HasCallStack => RnEnv2 -> Type -> Type -> Bool +eqTypeX env ta tb = fullEq (eq_type_expand_respect_x env) ta tb --- | Type equality comparing both visible and invisible arguments and expanding --- type synonyms. -tcEqTypeNoSyns :: Type -> Type -> Bool -tcEqTypeNoSyns ta tb = tc_eq_type False ta tb +eqTypeIgnoringMultiplicity :: Type -> Type -> Bool +-- See Note [Respecting multiplicity when comparing types] +eqTypeIgnoringMultiplicity ta tb = fullEq eq_type_expand_ignore ta tb -- | Like 'pickyEqTypeVis', but returns a Bool for convenience pickyEqType :: Type -> Type -> Bool -- Check when two types _look_ the same, _including_ synonyms. -- So (pickyEqType String [Char]) returns False -- This ignores kinds and coercions, because this is used only for printing. -pickyEqType ty1 ty2 = tc_eq_type True ty1 ty2 +pickyEqType ta tb = eq_type_keep_respect ta tb --- | Real worker for 'tcEqType'. No kind check! -tc_eq_type :: Bool -- ^ True <=> do not expand type synonyms - -> Type -> Type - -> Bool --- Flags False, False is the usual setting for tc_eq_type --- See Note [Computing equality on types] in Type -{-# INLINE tc_eq_type #-} -- See Note [Specialising tc_eq_type]. -tc_eq_type keep_syns orig_ty1 orig_ty2 - = go orig_env orig_ty1 orig_ty2 - where - orig_env = mkRnEnv2 $ mkInScopeSet $ tyCoVarsOfTypes [orig_ty1, orig_ty2] +{- Note [Specialising type equality] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The type equality predicates in Type are hit pretty hard by GHC. Consequently +we take pains to ensure that these paths are compiled to efficient, +minimally-allocating code. Plan: - go :: RnEnv2 -> Type -> Type -> Bool - -- See Note [Comparing nullary type synonyms] - go _ (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = True +* The main workhorse is `inline_generic_eq_type_x`. It is /non-recursive/ + and is marked INLINE. - go env t1 t2 | not keep_syns, Just t1' <- coreView t1 = go env t1' t2 - go env t1 t2 | not keep_syns, Just t2' <- coreView t2 = go env t1 t2' +* `inline_generic_eq_type_x` has various parameters that control what it does: + * syn_flag::SynFlag whether type synonyms are expanded or kept. + * mult_flag::MultiplicityFlag whether multiplicities are ignored or respected + * mb_env::Maybe RnEnv2 an optional RnEnv2. - go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 - go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 - go env (CastTy t1 _) t2 = go env t1 t2 - go env t1 (CastTy t2 _) = go env t1 t2 - go _ (CoercionTy {}) (CoercionTy {}) = True +* `inline_generic_eq_type_x` has a handful of call sites, namely the ones + in `eq_type_expand_respect`, `eq_type_expand_repect_x` etc. It inlines + at all these sites, specialising to the data values passed for the + control parameters. - go env (ForAllTy (Bndr tv1 vis1) ty1) - (ForAllTy (Bndr tv2 vis2) ty2) - = vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] - && go env (varType tv1) (varType tv2) - && go (rnBndr2 env tv1 tv2) ty1 ty2 +* All /other/ calls to `inline_generic_eq_type_x` go via + generic_eq_type_x = inline_generic_eq_type_x + {-# NOINLNE generic_eq_type_x #-} + The idea is that all calls to `generic_eq_type_x` are specialised by the + RULES, so this NOINLINE version is seldom, if ever, actually called. + +* For each of specialised copy of `inline_generic_eq_type_x, there is a + corresponding rewrite RULE that rewrites a call to (generic_eq_type_x args) + into the appropriate specialied version. + +See #19226. +-} + +-- | This flag controls whether we expand synonyms during comparison +data SynFlag = ExpandSynonyms | KeepSynonyms + +eq_type_expand_respect, eq_type_expand_ignore, eq_type_keep_respect + :: Type -> Type -> Bool +eq_type_expand_respect_x, eq_type_expand_ignore_x, eq_type_keep_respect_x + :: RnEnv2 -> Type -> Type -> Bool + +eq_type_expand_respect = inline_generic_eq_type_x ExpandSynonyms RespectMultiplicities Nothing +eq_type_expand_respect_x env = inline_generic_eq_type_x ExpandSynonyms RespectMultiplicities (Just env) +eq_type_expand_ignore = inline_generic_eq_type_x ExpandSynonyms IgnoreMultiplicities Nothing +eq_type_expand_ignore_x env = inline_generic_eq_type_x ExpandSynonyms IgnoreMultiplicities (Just env) +eq_type_keep_respect = inline_generic_eq_type_x KeepSynonyms RespectMultiplicities Nothing +eq_type_keep_respect_x env = inline_generic_eq_type_x KeepSynonyms RespectMultiplicities (Just env) + +{-# RULES +"eqType1" generic_eq_type_x ExpandSynonyms RespectMultiplicities Nothing + = eq_type_expand_respect +"eqType2" forall env. generic_eq_type_x ExpandSynonyms RespectMultiplicities (Just env) + = eq_type_expand_respect_x env +"eqType3" generic_eq_type_x ExpandSynonyms IgnoreMultiplicities Nothing + = eq_type_expand_ignore +"eqType4" forall env. generic_eq_type_x ExpandSynonyms IgnoreMultiplicities (Just env) + = eq_type_expand_ignore_x env +"eqType5" generic_eq_type_x KeepSynonyms RespectMultiplicities Nothing + = eq_type_keep_respect +"eqType6" forall env. generic_eq_type_x KeepSynonyms RespectMultiplicities (Just env) + = eq_type_keep_respect_x env + #-} + +-- --------------------------------------------------------------- +-- | Real worker for 'eqType'. No kind check! +-- Inline it at the (handful of local) call sites +-- The "generic" bit refers to the flag paramerisation +-- See Note [Specialising type equality]. +generic_eq_type_x, inline_generic_eq_type_x + :: SynFlag -> MultiplicityFlag -> Maybe RnEnv2 -> Type -> Type -> Bool + +{-# NOINLINE generic_eq_type_x #-} +generic_eq_type_x = inline_generic_eq_type_x +-- See Note [Computing equality on types] in Type + +{-# INLINE inline_generic_eq_type_x #-} +-- This non-recursive function can inline at its (few) call sites. The +-- recursion goes via generic_eq_type_x, which is the loop-breaker. +inline_generic_eq_type_x syn_flag mult_flag mb_env + = \ t1 t2 -> t1 `seq` t2 `seq` + let go = generic_eq_type_x syn_flag mult_flag mb_env + -- Abbreviation for recursive calls + in case (t1,t2) of + _ | 1# <- reallyUnsafePtrEquality# t1 t2 -> True + -- See Note [Type comparisons using object pointer comparisons] + + (TyConApp tc1 [], TyConApp tc2 []) | tc1 == tc2 -> True + -- See Note [Comparing nullary type synonyms] + + _ | ExpandSynonyms <- syn_flag, Just t1' <- coreView t1 -> go t1' t2 + | ExpandSynonyms <- syn_flag, Just t2' <- coreView t2 -> go t1 t2' + + (TyVarTy tv1, TyVarTy tv2) + -> case mb_env of + Nothing -> tv1 == tv2 + Just env -> rnOccL env tv1 == rnOccR env tv2 + + (LitTy lit1, LitTy lit2) -> lit1 == lit2 + (CastTy t1' _, _) -> go t1' t2 -- Ignore casts + (_, CastTy t2' _) -> go t1 t2' -- Ignore casts + (CoercionTy {}, CoercionTy {}) -> True -- Ignore coercions -- Make sure we handle all FunTy cases since falling through to the -- AppTy case means that tcSplitAppTyNoView_maybe may see an unzonked -- kind variable, which causes things to blow up. -- See Note [Equality on FunTys] in GHC.Core.TyCo.Rep: we must check -- kinds here - go env (FunTy _ w1 arg1 res1) (FunTy _ w2 arg2 res2) - = go env (typeKind arg1) (typeKind arg2) && - go env (typeKind res1) (typeKind res2) && - go env arg1 arg2 && go env res1 res2 && go env w1 w2 + (FunTy _ w1 arg1 res1, FunTy _ w2 arg2 res2) + -> fullEq go arg1 arg2 + && fullEq go res1 res2 + && (case mult_flag of + RespectMultiplicities -> go w1 w2 + IgnoreMultiplicities -> True) -- See Note [Equality on AppTys] in GHC.Core.Type - go env (AppTy s1 t1) ty2 - | Just (s2, t2) <- tcSplitAppTyNoView_maybe ty2 - = go env s1 s2 && go env t1 t2 - go env ty1 (AppTy s2 t2) - | Just (s1, t1) <- tcSplitAppTyNoView_maybe ty1 - = go env s1 s2 && go env t1 t2 - - go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) - = tc1 == tc2 && gos env ts1 ts2 - - go _ _ _ = False - - gos _ [] [] = True - gos env (t1:ts1) (t2:ts2) = go env t1 t2 && gos env ts1 ts2 - gos _ _ _ = False + (AppTy s1 t1', _) + | Just (s2, t2') <- tcSplitAppTyNoView_maybe t2 + -> go s1 s2 && go t1' t2' + (_, AppTy s2 t2') + | Just (s1, t1') <- tcSplitAppTyNoView_maybe t1 + -> go s1 s2 && go t1' t2' + + (TyConApp tc1 ts1, TyConApp tc2 ts2) + | tc1 == tc2 -> gos ts1 ts2 + | otherwise -> False + where + gos [] [] = True + gos (t1:ts1) (t2:ts2) = go t1 t2 && gos ts1 ts2 + gos _ _ = False + + (ForAllTy (Bndr tv1 vis1) body1, ForAllTy (Bndr tv2 vis2) body2) + -> case mb_env of + Nothing -> generic_eq_type_x syn_flag mult_flag + (Just (initRnEnv t1 t2)) t1 t2 + Just env + | vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] + -> go (varType tv1) (varType tv2) -- Always do kind-check + && generic_eq_type_x syn_flag mult_flag + (Just (rnBndr2 env tv1 tv2)) body1 body2 + | otherwise + -> False + + _ -> False + +fullEq :: (Type -> Type -> Bool) -> Type -> Type -> Bool +-- Do "full equality" including the kind check +-- See Note [Casts and coercions in type comparision] +{-# INLINE fullEq #-} +fullEq eq ty1 ty2 + = case eq ty1 ty2 of + False -> False + True | hasCasts ty1 || hasCasts ty2 + -> eq (typeKind ty1) (typeKind ty2) + | otherwise + -> True + +hasCasts :: Type -> Bool +-- Fast, does not look deep, does not allocate +hasCasts (CastTy {}) = True +hasCasts (CoercionTy {}) = True +hasCasts (AppTy t1 t2) = hasCasts t1 || hasCasts t2 +hasCasts (ForAllTy _ ty) = hasCasts ty +hasCasts _ = False -- TyVarTy, TyConApp, FunTy, LitTy -isDefaultableBndr :: ForAllTyBinder -> Bool --- This function should line up with the defaulting done --- by GHC.Iface.Type.defaultIfaceTyVarsOfKind --- See Note [Showing invisible bits of types in error messages] --- in GHC.Tc.Errors.Ppr -isDefaultableBndr (Bndr tv vis) - = isInvisibleForAllTyFlag vis && is_defaultable (tyVarKind tv) - where - is_defaultable ki = isLevityTy ki || isRuntimeRepTy ki || isMultiplicityTy ki +{- ********************************************************************* +* * + Comparing ForAllTyFlags +* * +********************************************************************* -} -- | Do these denote the same level of visibility? 'Required' -- arguments are visible, others are not. So this function @@ -444,94 +588,13 @@ is more finer-grained than definitional equality in two places: ************************************************************************ * * Comparison for types - (We don't use instances so that we know where it happens) + + Not so heavily used, less carefully optimised * * ************************************************************************ -Note [Equality on AppTys] -~~~~~~~~~~~~~~~~~~~~~~~~~ -In our cast-ignoring equality, we want to say that the following two -are equal: - - (Maybe |> co) (Int |> co') ~? Maybe Int - -But the left is an AppTy while the right is a TyConApp. The solution is -to use splitAppTyNoView_maybe to break up the TyConApp into its pieces and -then continue. Easy to do, but also easy to forget to do. - -Note [Comparing nullary type synonyms] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Consider the task of testing equality between two 'Type's of the form - - TyConApp tc [] - -where @tc@ is a type synonym. A naive way to perform this comparison these -would first expand the synonym and then compare the resulting expansions. - -However, this is obviously wasteful and the RHS of @tc@ may be large; it is -much better to rather compare the TyCons directly. Consequently, before -expanding type synonyms in type comparisons we first look for a nullary -TyConApp and simply compare the TyCons if we find one. Of course, if we find -that the TyCons are *not* equal then we still need to perform the expansion as -their RHSs may still be equal. - -We perform this optimisation in a number of places: - - * GHC.Core.Types.eqType - * GHC.Core.Types.nonDetCmpType - * GHC.Core.Unify.unify_ty - * GHC.Tc.Solver.Equality.can_eq_nc' - * TcUnify.uType - -This optimisation is especially helpful for the ubiquitous GHC.Types.Type, -since GHC prefers to use the type synonym over @TYPE 'LiftedRep@ applications -whenever possible. See Note [Using synonyms to compress types] in -GHC.Core.Type for details. - --} - -eqType :: Type -> Type -> Bool --- ^ Type equality on source types. Does not look through @newtypes@, --- 'PredType's or type families, but it does look through type synonyms. --- This first checks that the kinds of the types are equal and then --- checks whether the types are equal, ignoring casts and coercions. --- (The kind check is a recursive call, but since all kinds have type --- @Type@, there is no need to check the types of kinds.) --- See also Note [Non-trivial definitional equality] in "GHC.Core.TyCo.Rep". -eqType t1 t2 = isEqual $ nonDetCmpType t1 t2 - -- It's OK to use nonDetCmpType here and eqType is deterministic, - -- nonDetCmpType does equality deterministically - -eqTypeOpt :: CmpTypeOpt -> Type -> Type -> Bool -eqTypeOpt opt t1 t2 = isEqual $ nonDetCmpTypeOpt opt t1 t2 - --- | Compare types with respect to a (presumably) non-empty 'RnEnv2'. -eqTypeX :: RnEnv2 -> Type -> Type -> Bool -eqTypeX env t1 t2 = isEqual $ nonDetCmpTypeX defaultCmpTypeOpt env t1 t2 - -- It's OK to use nonDetCmpType here and eqTypeX is deterministic, - -- nonDetCmpTypeX does equality deterministically - --- | Type equality on lists of types, looking through type synonyms --- but not newtypes. -eqTypes :: [Type] -> [Type] -> Bool -eqTypes tys1 tys2 = isEqual $ nonDetCmpTypes tys1 tys2 - -- It's OK to use nonDetCmpType here and eqTypes is deterministic, - -- nonDetCmpTypes does equality deterministically - -eqVarBndrs :: RnEnv2 -> [Var] -> [Var] -> Maybe RnEnv2 --- Check that the var lists are the same length --- and have matching kinds; if so, extend the RnEnv2 --- Returns Nothing if they don't match -eqVarBndrs env [] [] - = Just env -eqVarBndrs env (tv1:tvs1) (tv2:tvs2) - | eqTypeX env (varType tv1) (varType tv2) - = eqVarBndrs (rnBndr2 env tv1 tv2) tvs1 tvs2 -eqVarBndrs _ _ _= Nothing - -- Now here comes the real worker -{- Note [nonDetCmpType nondeterminism] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ nonDetCmpType is implemented in terms of nonDetCmpTypeX. nonDetCmpTypeX @@ -541,27 +604,20 @@ comparing type variables is nondeterministic, note the call to nonDetCmpVar in nonDetCmpTypeX. See Note [Unique Determinism] for more details. -} -nonDetCmpType :: Type -> Type -> Ordering -nonDetCmpType = nonDetCmpTypeOpt defaultCmpTypeOpt -nonDetCmpTypeOpt :: CmpTypeOpt -> Type -> Type -> Ordering -nonDetCmpTypeOpt _ !t1 !t2 +nonDetCmpType :: Type -> Type -> Ordering +{-# INLINE nonDetCmpType #-} +nonDetCmpType !t1 !t2 -- See Note [Type comparisons using object pointer comparisons] | 1# <- reallyUnsafePtrEquality# t1 t2 = EQ -nonDetCmpTypeOpt _ (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 +nonDetCmpType (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = EQ -nonDetCmpTypeOpt opt t1 t2 +nonDetCmpType t1 t2 -- we know k1 and k2 have the same kind, because they both have kind *. - = nonDetCmpTypeX opt rn_env t1 t2 + = nonDetCmpTypeX rn_env t1 t2 where rn_env = mkRnEnv2 (mkInScopeSet (tyCoVarsOfTypes [t1, t2])) -{-# INLINE nonDetCmpType #-} - -nonDetCmpTypes :: [Type] -> [Type] -> Ordering -nonDetCmpTypes ts1 ts2 = nonDetCmpTypesX rn_env ts1 ts2 - where - rn_env = mkRnEnv2 (mkInScopeSet (tyCoVarsOfTypes (ts1 ++ ts2))) -- | An ordering relation between two 'Type's (known below as @t1 :: k1@ -- and @t2 :: k2@) @@ -573,10 +629,11 @@ data TypeOrdering = TLT -- ^ @t1 < t2@ | TGT -- ^ @t1 > t2@ deriving (Eq, Ord, Enum, Bounded) -nonDetCmpTypeX :: CmpTypeOpt -> RnEnv2 -> Type -> Type -> Ordering -- Main workhorse +nonDetCmpTypeX :: RnEnv2 -> Type -> Type -> Ordering -- Main workhorse -- See Note [Non-trivial definitional equality] in GHC.Core.TyCo.Rep -- See Note [Computing equality on types] -nonDetCmpTypeX opt env orig_t1 orig_t2 = + -- Always respects multiplicities, unlike eqType +nonDetCmpTypeX env orig_t1 orig_t2 = case go env orig_t1 orig_t2 of -- If there are casts then we also need to do a comparison of -- the kinds of the types being compared @@ -635,13 +692,9 @@ nonDetCmpTypeX opt env orig_t1 orig_t2 = go env (FunTy _ w1 s1 t1) (FunTy _ w2 s2 t2) -- NB: nonDepCmpTypeX does the kind check requested by -- Note [Equality on FunTys] in GHC.Core.TyCo.Rep - = liftOrdering (nonDetCmpTypeX opt env s1 s2 S.<> nonDetCmpTypeX opt env t1 t2) - `thenCmpTy` cmp_mults + = liftOrdering (nonDetCmpTypeX env s1 s2 S.<> nonDetCmpTypeX env t1 t2) + `thenCmpTy` go env w1 w2 -- Comparing multiplicities last because the test is usually true - where - cmp_mults = case cmp_multiplicity_in_funty opt of - RespectMultiplicities -> go env w1 w2 - IgnoreMultiplicities -> TEQ go env (TyConApp tc1 tys1) (TyConApp tc2 tys2) = liftOrdering (tc1 `nonDetCmpTc` tc2) `thenCmpTy` gos env tys1 tys2 @@ -672,36 +725,6 @@ nonDetCmpTypeX opt env orig_t1 orig_t2 = gos _ _ [] = TGT gos env (ty1:tys1) (ty2:tys2) = go env ty1 ty2 `thenCmpTy` gos env tys1 tys2 -{- Note [Respecting multiplicity when comparing types] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Generally speaking, we respect multiplicities (i.e. the linear part of the type -system) when comparing types. Doing so is of course crucial during typechecking. - -But for reasons described in Note [Linting linearity] in GHC.Core.Lint, it is hard -to ensure that Core is always type-correct when it comes to linearity. So -* `CmpTypeOpt` provides a way to compare types that /ignores/ multiplicities -* We use this multiplicity-blind comparison very occasionally, notably - - in Core Lint: see Note [Linting linearity] in GHC.Core.Lint - - in rule matching: see Note [Rewrite rules ignore multiplicities in FunTy] - in GHC.Core.Unify --} -data CmpTypeOpt = CmpTypeOpt - { -- Whether to consider `a -> b` and `a %1 -> b` distinct or equal. Default: - -- RespectMultiplicities. See Note [Respecting multiplicity when comparing types]. - cmp_multiplicity_in_funty :: MultiplicityFlag - } - -defaultCmpTypeOpt :: CmpTypeOpt -defaultCmpTypeOpt = CmpTypeOpt - { cmp_multiplicity_in_funty = RespectMultiplicities } - -------------- -nonDetCmpTypesX :: RnEnv2 -> [Type] -> [Type] -> Ordering -nonDetCmpTypesX _ [] [] = EQ -nonDetCmpTypesX env (t1:tys1) (t2:tys2) = nonDetCmpTypeX defaultCmpTypeOpt env t1 t2 S.<> - nonDetCmpTypesX env tys1 tys2 -nonDetCmpTypesX _ [] _ = LT -nonDetCmpTypesX _ _ [] = GT ------------- -- | Compare two 'TyCon's. @@ -714,4 +737,91 @@ nonDetCmpTc tc1 tc2 u2 = tyConUnique tc2 +{- ********************************************************************* +* * + mayLookIdentical +* * +********************************************************************* -} + +mayLookIdentical :: Type -> Type -> Bool +-- | Returns True if the /visible/ part of the types +-- might look equal, even if they are really unequal (in the invisible bits) +-- +-- This function is very similar to tc_eq_type but it is much more +-- heuristic. Notably, it is always safe to return True, even with types +-- that might (in truth) be unequal -- this affects error messages only +-- (Originally this test was done by eqType with an extra flag, but the result +-- was hard to understand.) +mayLookIdentical orig_ty1 orig_ty2 + = go orig_env orig_ty1 orig_ty2 + where + orig_env = mkRnEnv2 $ mkInScopeSet $ tyCoVarsOfTypes [orig_ty1, orig_ty2] + + go :: RnEnv2 -> Type -> Type -> Bool + -- See Note [Comparing nullary type synonyms] + go _ (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = True + + go env t1 t2 | Just t1' <- coreView t1 = go env t1' t2 + go env t1 t2 | Just t2' <- coreView t2 = go env t1 t2' + + go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 + go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 + go env (CastTy t1 _) t2 = go env t1 t2 + go env t1 (CastTy t2 _) = go env t1 t2 + go _ (CoercionTy {}) (CoercionTy {}) = True + + go env (ForAllTy (Bndr tv1 vis1) ty1) + (ForAllTy (Bndr tv2 vis2) ty2) + = vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] + && go (rnBndr2 env tv1 tv2) ty1 ty2 + -- Visible stuff only: ignore kinds of binders + + -- If we have (forall (r::RunTimeRep). ty1 ~ blah) then respond + -- with True. Reason: the type pretty-printer defaults RuntimeRep + -- foralls (see Ghc.Iface.Type.hideNonStandardTypes). That can make, + -- say (forall r. TYPE r -> Type) into (Type -> Type), so it looks the + -- same as a very different type (#24553). By responding True, we + -- tell GHC (see calls of mayLookIdentical) to display without defaulting. + -- See Note [Showing invisible bits of types in error messages] + -- in GHC.Tc.Errors.Ppr + go _ (ForAllTy b _) _ | isDefaultableBndr b = True + go _ _ (ForAllTy b _) | isDefaultableBndr b = True + + go env (FunTy _ w1 arg1 res1) (FunTy _ w2 arg2 res2) + = go env arg1 arg2 && go env res1 res2 && go env w1 w2 + -- Visible stuff only: ignore agg kinds + + -- See Note [Equality on AppTys] in GHC.Core.Type + go env (AppTy s1 t1) ty2 + | Just (s2, t2) <- tcSplitAppTyNoView_maybe ty2 + = go env s1 s2 && go env t1 t2 + go env ty1 (AppTy s2 t2) + | Just (s1, t1) <- tcSplitAppTyNoView_maybe ty1 + = go env s1 s2 && go env t1 t2 + + go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) + = tc1 == tc2 && gos env (tyConBinders tc1) ts1 ts2 + + go _ _ _ = False + + gos :: RnEnv2 -> [TyConBinder] -> [Type] -> [Type] -> Bool + gos _ _ [] [] = True + gos env bs (t1:ts1) (t2:ts2) + | (invisible, bs') <- case bs of + [] -> (False, []) + (b:bs) -> (isInvisibleTyConBinder b, bs) + = (invisible || go env t1 t2) && gos env bs' ts1 ts2 + + gos _ _ _ _ = False + + +isDefaultableBndr :: ForAllTyBinder -> Bool +-- This function should line up with the defaulting done +-- by GHC.Iface.Type.defaultIfaceTyVarsOfKind +-- See Note [Showing invisible bits of types in error messages] +-- in GHC.Tc.Errors.Ppr +isDefaultableBndr (Bndr tv vis) + = isInvisibleForAllTyFlag vis && is_defaultable (tyVarKind tv) + where + is_defaultable ki = isLevityTy ki || isRuntimeRepTy ki || isMultiplicityTy ki ===================================== compiler/GHC/Core/TyCo/Rep.hs ===================================== @@ -350,14 +350,24 @@ This kind instantiation only happens in TyConApp currently. Note [Non-trivial definitional equality] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Is Int |> <*> the same as Int? YES! In order to reduce headaches, -we decide that any reflexive casts in types are just ignored. -(Indeed they must be. See Note [Respecting definitional equality].) -More generally, the `eqType` function, which defines Core's type equality -relation, ignores casts and coercion arguments, as long as the -two types have the same kind. This allows us to be a little sloppier -in keeping track of coercions, which is a good thing. It also means -that eqType does not depend on eqCoercion, which is also a good thing. +Is ((IO |> co1) Int |> co2) equal to (IO Int)? +Assume + co1 :: (Type->Type) ~ (Type->Wombat) + co2 :: Wombat ~ Type +Well, yes. The casts are just getting in the way. +See also Note [Respecting definitional equality]. + +So we do this: + +(EQTYPE) + The `eqType` function, which defines Core's type equality relation, + - /ignores/ casts, and + - /ignores/ coercion arguments + - /provided/ two types have the same kind + +This allows us to be a little sloppier in keeping track of coercions, which is a +good thing. It also means that eqType does not depend on eqCoercion, which is +also a good thing. Why is this sensible? That is, why is something different than α-equivalence appropriate for the implementation of eqType? ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -233,6 +233,7 @@ ruleMatchTyKiX tmpl_tvs rn_env tenv tmpl target = case tc_unify_tys (matchBindFun tmpl_tvs) False False True -- <-- this means to match the kinds IgnoreMultiplicities + -- See Note [Rewrite rules ignore multiplicities in FunTy] rn_env tenv emptyCvSubstEnv [tmpl] [target] of Unifiable (tenv', _) -> Just tenv' _ -> Nothing @@ -418,10 +419,16 @@ their types unify (see Note [Matching variable types] in GHC.Core.Rules). So when unifying types for the sake of rule-matching, the unification algorithm must be able to ignore multiplicities altogether. -The way we implement this deserves a comment. In unify_ty, `FunTy` is handled as -if it was a regular type constructor. In this case, and when the types being -unified are *function* arrows, but not constraint arrows, then the first -argument is a multiplicity. +How is this done? + (1) The `um_arr_mult` field of `UMEnv` recordsw when we are doing rule-matching, + and hence want to ignore multiplicities. + (2) The field is set to True in by `ruleMatchTyKiX`. + (3) It is consulted when matching `FunTy` in `unify_ty`. + +Wrinkle in (3). In `unify_tc_app`, in `unify_ty`, `FunTy` is handled as if it +was a regular type constructor. In this case, and when the types being unified +are *function* arrows, but not constraint arrows, then the first argument is a +multiplicity. We select this situation by comparing the type constructor with fUNTyCon. In this case, and this case only, we can safely drop the first argument (using the @@ -1208,21 +1215,22 @@ unify_ty env ty1 ty2 _kco where mb_tc_app1 = splitTyConApp_maybe ty1 mb_tc_app2 = splitTyConApp_maybe ty2 + unify_tc_app tc tys1 tys2 | tc == fUNTyCon , IgnoreMultiplicities <- um_arr_mult env - , (_ : no_mult_tys1) <- tys1 - , (_ : no_mult_tys2) <- tys2 + , (_mult1 : no_mult_tys1) <- tys1 + , (_mult2 : no_mult_tys2) <- tys2 = -- We're comparing function arrow types here (not constraint arrow -- types!), and they have at least one argument, which is the arrow's -- multiplicity annotation. The flag `um_arr_mult` instructs us to -- ignore multiplicities in this very case. This is a little tricky: see - -- Note [Rewrite rules ignore multiplicities in FunTy]. + -- point (3) in Note [Rewrite rules ignore multiplicities in FunTy]. unify_tys env no_mult_tys1 no_mult_tys2 + | otherwise = unify_tys env tys1 tys2 - -- Applications need a bit of care! -- They can match FunTy and TyConApp, so use splitAppTy_maybe -- NB: we've already dealt with type variables, ===================================== compiler/GHC/Tc/Utils/TcType.hs ===================================== @@ -96,7 +96,7 @@ module GHC.Tc.Utils.TcType ( -- Re-exported from GHC.Core.TyCo.Compare -- mainly just for back-compat reasons - eqType, eqTypes, nonDetCmpType, nonDetCmpTypes, eqTypeX, + eqType, eqTypes, nonDetCmpType, eqTypeX, pickyEqType, tcEqType, tcEqKind, tcEqTypeNoKindCheck, mayLookIdentical, tcEqTyConApps, eqForAllVis, eqVarBndrs, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/56f6962b9aa84b5a08b238cc44ed36cfa7b20f68 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/56f6962b9aa84b5a08b238cc44ed36cfa7b20f68 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 21:33:58 2024 From: gitlab at gitlab.haskell.org (Andreas Klebinger (@AndreasK)) Date: Wed, 19 Jun 2024 17:33:58 -0400 Subject: [Git][ghc/ghc][wip/andreask/profile_safe_ffi] 4189 commits: [haddock @ 2002-04-04 16:23:43 by simonmar] Message-ID: <66734ec659378_1334da4127fb094375@gitlab.mail> Andreas Klebinger pushed to branch wip/andreask/profile_safe_ffi at Glasgow Haskell Compiler / GHC Commits: 2b39cd94 by Simon Marlow at 2002-04-04T16:23:43+00:00 [haddock @ 2002-04-04 16:23:43 by simonmar] This is Haddock, my stab at a Haskell documentation tool. It's not quite ready for release yet, but I'm putting it in the repository so others can take a look. It uses a locally modified version of the hssource parser, extended with support for GHC extensions and documentation annotations. - - - - - 99ede94f by Simon Marlow at 2002-04-04T16:24:10+00:00 [haddock @ 2002-04-04 16:24:10 by simonmar] forgot one file - - - - - 8363294c by Simon Marlow at 2002-04-05T13:58:15+00:00 [haddock @ 2002-04-05 13:58:15 by simonmar] Remap names in the exported declarations to be "closer" to the current module. eg. if an exported declaration mentions a type 'T' which is imported from module A then re-exported from the current module, then links from the type or indeed the documentation will point to the current module rather than module A. This is to support better hiding: module A won't be referred to in the generated output. - - - - - 1570cbc1 by Simon Marlow at 2002-04-05T13:58:23+00:00 [haddock @ 2002-04-05 13:58:23 by simonmar] update the TODO list - - - - - 3a62f96b by Simon Marlow at 2002-04-05T14:11:51+00:00 [haddock @ 2002-04-05 14:11:51 by simonmar] Fix the anchor for a class declaration - - - - - c5d9a471 by Simon Marlow at 2002-04-05T14:18:41+00:00 [haddock @ 2002-04-05 14:18:41 by simonmar] remove underlines on visited links - - - - - 97280525 by Simon Marlow at 2002-04-05T16:11:47+00:00 [haddock @ 2002-04-05 16:11:47 by simonmar] - Update to generate more correct HTML. - Use our own non-overloaded table combinators, as the overloaded versions were giving me a headache. The improved type safety caught several errors in the HTML generation. - - - - - 9acd3a4d by Simon Marlow at 2002-04-05T16:32:19+00:00 [haddock @ 2002-04-05 16:32:19 by simonmar] Add width property to the title, and add TD.children for the module contents page. - - - - - ec9a0847 by Simon Marlow at 2002-04-08T16:39:56+00:00 [haddock @ 2002-04-08 16:39:56 by simonmar] Fix a problem with exports of the form T(..). - - - - - e4627dc8 by Simon Marlow at 2002-04-08T16:41:38+00:00 [haddock @ 2002-04-08 16:41:37 by simonmar] - Add our own versions of Html & BlockTable for the time being. - Add support for generating an index to the HTML backend - - - - - 2d73fd75 by Simon Marlow at 2002-04-09T11:23:24+00:00 [haddock @ 2002-04-09 11:23:24 by simonmar] Add '-- /' as a synonym for '-- |', for compatibility with IDoc. - - - - - 3675464e by Simon Marlow at 2002-04-09T11:33:55+00:00 [haddock @ 2002-04-09 11:33:54 by simonmar] - add the <...> syntax for marking up URLs in documentation - Make the output for data & class declarations more compact when there aren't any documentation annotations on the individual methods or constructors respectively. - - - - - 5077f5b1 by Simon Marlow at 2002-04-09T11:36:04+00:00 [haddock @ 2002-04-09 11:36:04 by simonmar] Update the TODO list - - - - - 9e83c54d by Simon Marlow at 2002-04-10T10:50:06+00:00 [haddock @ 2002-04-10 10:50:06 by simonmar] Use explicit 'px' suffix on pixel sizes; IE seems to prefer them - - - - - 052de51c by Simon Marlow at 2002-04-10T13:23:13+00:00 [haddock @ 2002-04-10 13:23:13 by simonmar] Lex URLs as a single token to avoid having to escape special characters inside the URL string. - - - - - 47187edb by Simon Marlow at 2002-04-10T13:23:55+00:00 [haddock @ 2002-04-10 13:23:55 by simonmar] Not sure why I made the constructor name for a record declaration into a TyCls name, but change it back into a Var name anyhow. - - - - - 3dc6aa81 by Simon Marlow at 2002-04-10T13:26:10+00:00 [haddock @ 2002-04-10 13:26:09 by simonmar] Lots of changes, including: - add index support to the HTML backend - clean up the renamer, put it into a monad - propogate unresolved names to the top level and report them in a nicer way - various bugfixes - - - - - c2a70a72 by Simon Marlow at 2002-04-10T13:32:39+00:00 [haddock @ 2002-04-10 13:32:39 by simonmar] Skeleton documentation - - - - - 50c98d17 by Simon Marlow at 2002-04-10T13:37:23+00:00 [haddock @ 2002-04-10 13:37:23 by simonmar] Update the TODO list, separate into pre-1.0 and post-1.0 items - - - - - f3778be6 by Simon Marlow at 2002-04-10T14:30:58+00:00 [haddock @ 2002-04-10 14:30:58 by simonmar] Add an introduction - - - - - cfbaf9f7 by Simon Marlow at 2002-04-10T14:59:51+00:00 [haddock @ 2002-04-10 14:59:51 by simonmar] Sort the module tree - - - - - 76bd7b34 by Simon Marlow at 2002-04-10T15:50:11+00:00 [haddock @ 2002-04-10 15:50:10 by simonmar] Generate a little table of contents at the top of the module doc (only if the module actually contains some section headings, though). - - - - - bb8560a1 by Simon Marlow at 2002-04-10T16:10:26+00:00 [haddock @ 2002-04-10 16:10:26 by simonmar] Now we understand (or at least don't barf on) type signatures in patterns such as you might find when scoped type variables are in use. - - - - - 86c2a026 by Simon Marlow at 2002-04-10T16:10:49+00:00 [haddock @ 2002-04-10 16:10:49 by simonmar] more updates - - - - - 1c052b0e by Simon Marlow at 2002-04-10T16:28:05+00:00 [haddock @ 2002-04-10 16:28:05 by simonmar] Parse errors in doc strings are now reported as warnings rather that causing the whole thing to fall over. It still needs cleaning up (the warning is emitted with trace) but this will do for the time being. - - - - - ace03e8f by Simon Marlow at 2002-04-10T16:38:03+00:00 [haddock @ 2002-04-10 16:38:03 by simonmar] update again - - - - - 69006c3e by Simon Marlow at 2002-04-11T13:38:02+00:00 [haddock @ 2002-04-11 13:38:02 by simonmar] mention Opera - - - - - fe9b10f8 by Simon Marlow at 2002-04-11T13:40:31+00:00 [haddock @ 2002-04-11 13:40:30 by simonmar] - copy haddock.css into the same place as the generated HTML - new option: --css <file> specifies the style sheet to use - new option: -o <dir> specifies the directory in which to generate the output. - because Haddock now needs to know where to find its default stylesheet, we have to have a wrapper script and do the haddock-inplace thing (Makefile code copied largely from fptools/happy). - - - - - 106adbbe by Simon Marlow at 2002-04-24T15:12:41+00:00 [haddock @ 2002-04-24 15:12:41 by simonmar] Stop slurping comment lines when we see a row of dashes longer than length 2: these are useful as separators. - - - - - 995d3f9e by Simon Marlow at 2002-04-24T15:14:12+00:00 [haddock @ 2002-04-24 15:14:11 by simonmar] Grok the kind of module headers we use in fptools/libraries, and pass the "portability", "stability", and "maintainer" strings through into the generated HTML. If the module header doesn't match the pattern, then we don't include the info in the HTML. - - - - - e14da136 by Simon Marlow at 2002-04-24T15:16:57+00:00 [haddock @ 2002-04-24 15:16:57 by simonmar] Done module headers now. - - - - - 2ca8dfd4 by Simon Marlow at 2002-04-24T15:57:48+00:00 [haddock @ 2002-04-24 15:57:47 by simonmar] Handle gcons in export lists (a common extension). - - - - - 044cea81 by Simon Marlow at 2002-04-25T14:20:12+00:00 [haddock @ 2002-04-25 14:20:12 by simonmar] Add the little lambda icon - - - - - 63955027 by Simon Marlow at 2002-04-25T14:40:05+00:00 [haddock @ 2002-04-25 14:40:05 by simonmar] - Add support for named chunks of documentation which can be referenced from the export list. - Copy the icon from $libdir to the destination in HTML mode. - - - - - 36e3f913 by Simon Marlow at 2002-04-25T16:48:36+00:00 [haddock @ 2002-04-25 16:48:36 by simonmar] More keyboard bashing - - - - - 7ae18dd0 by Simon Marlow at 2002-04-26T08:43:33+00:00 [haddock @ 2002-04-26 08:43:33 by simonmar] Package util reqd. to compile with 4.08.2 - - - - - bbd5fbab by Simon Marlow at 2002-04-26T10:13:00+00:00 [haddock @ 2002-04-26 10:13:00 by simonmar] Include $(GHC_HAPPY_OPTS) when compiling HsParser - - - - - 31c53d79 by Simon Marlow at 2002-04-26T11:18:57+00:00 [haddock @ 2002-04-26 11:18:56 by simonmar] - support for fundeps (partially contributed by Brett Letner - thanks Brett). - make it build with GHC 4.08.2 - - - - - c415ce76 by Simon Marlow at 2002-04-26T13:15:02+00:00 [haddock @ 2002-04-26 13:15:02 by simonmar] Move the explicit formatting of the little table for the stability/portability/maintainer info from the HTML into the CSS, and remove the explicit table size (just right-align it). - - - - - 520ee21a by Simon Marlow at 2002-04-26T16:01:44+00:00 [haddock @ 2002-04-26 16:01:44 by simonmar] Yet more keyboard bashing - this is pretty much complete now. - - - - - 2ae37179 by Simon Marlow at 2002-04-26T16:02:14+00:00 [haddock @ 2002-04-26 16:02:14 by simonmar] Add a couple of things I forgot about - - - - - b7211e04 by Simon Marlow at 2002-04-29T15:28:12+00:00 [haddock @ 2002-04-29 15:28:12 by simonmar] bugfix for declBinders on a NewTypeDecl - - - - - 640c154a by Simon Marlow at 2002-04-29T15:28:54+00:00 [haddock @ 2002-04-29 15:28:54 by simonmar] Allow '-- |' style annotations on constructors and record fields. - - - - - 393f258a by Simon Marlow at 2002-04-29T15:37:32+00:00 [haddock @ 2002-04-29 15:37:32 by simonmar] syntax fix - - - - - 8a2c2549 by Simon Marlow at 2002-04-29T15:37:48+00:00 [haddock @ 2002-04-29 15:37:48 by simonmar] Add an example - - - - - db88f8a2 by Simon Marlow at 2002-04-29T15:55:46+00:00 [haddock @ 2002-04-29 15:55:46 by simonmar] remove a trace - - - - - 2b0248e0 by Simon Marlow at 2002-04-29T15:56:19+00:00 [haddock @ 2002-04-29 15:56:19 by simonmar] Fix for 'make install' - - - - - 120453a0 by Simon Marlow at 2002-04-29T15:56:39+00:00 [haddock @ 2002-04-29 15:56:39 by simonmar] Install the auxilliary bits - - - - - 950e6dbb by Simon Marlow at 2002-04-29T15:57:30+00:00 [haddock @ 2002-04-29 15:57:30 by simonmar] Add BinDist bits - - - - - 154b9d71 by Simon Marlow at 2002-05-01T11:02:52+00:00 [haddock @ 2002-05-01 11:02:52 by simonmar] update - - - - - ba6c39fa by Simon Marlow at 2002-05-01T11:03:26+00:00 [haddock @ 2002-05-01 11:03:26 by simonmar] Add another item - - - - - bacb5e33 by Simon Marlow at 2002-05-03T08:50:00+00:00 [haddock @ 2002-05-03 08:50:00 by simonmar] Fix some typos. - - - - - 54c87895 by Sven Panne at 2002-05-05T19:40:51+00:00 [haddock @ 2002-05-05 19:40:51 by panne] As a temporary hack/workaround for a bug in GHC's simplifier, don't pass Happy the -c option for generating the parsers in this subdir. Furthermore, disable -O for HaddocParse, too. - - - - - e6c08703 by Simon Marlow at 2002-05-06T09:51:10+00:00 [haddock @ 2002-05-06 09:51:10 by simonmar] Add RPM spec file (thanks to Tom Moertel <tom-rpms at moertel.com>) - - - - - 7b8fa8e7 by Simon Marlow at 2002-05-06T12:29:26+00:00 [haddock @ 2002-05-06 12:29:26 by simonmar] Add missing type signature (a different workaround for the bug in GHC's simplifier). - - - - - cd0e300d by Simon Marlow at 2002-05-06T12:30:09+00:00 [haddock @ 2002-05-06 12:30:09 by simonmar] Remove workaround for simplifier bug in previous revision. - - - - - 687e68fa by Simon Marlow at 2002-05-06T12:32:32+00:00 [haddock @ 2002-05-06 12:32:32 by simonmar] Allow empty data declarations (another GHC extension). - - - - - 8f29f696 by Simon Marlow at 2002-05-06T12:49:21+00:00 [haddock @ 2002-05-06 12:49:21 by simonmar] Fix silly bug in named documentation block lookup. - - - - - 8e0059af by Simon Marlow at 2002-05-06T13:02:42+00:00 [haddock @ 2002-05-06 13:02:42 by simonmar] Add another named chunk with a different name - - - - - 68f8a896 by Simon Marlow at 2002-05-06T13:32:32+00:00 [haddock @ 2002-05-06 13:32:32 by simonmar] Be more lenient about extra paragraph breaks - - - - - 65fc31db by Simon Marlow at 2002-05-07T15:36:36+00:00 [haddock @ 2002-05-07 15:36:36 by simonmar] DocEmpty is a right and left-unit of DocAppend (remove it in the smart constructor). - - - - - adc81078 by Simon Marlow at 2002-05-07T15:37:15+00:00 [haddock @ 2002-05-07 15:37:15 by simonmar] Allow code blocks to be denoted with bird-tracks in addition to [...]. - - - - - 1283a3c1 by Simon Marlow at 2002-05-08T11:21:56+00:00 [haddock @ 2002-05-08 11:21:56 by simonmar] Add a facility for specifying options that affect Haddock's treatment of the module. Options are given at the top of the module in a comma-separated list, beginning with '-- #'. eg. -- # prune, hide, ignore-exports Options currently available, with their meanings: prune: ignore declarations which have no documentation annotations ignore-exports: act as if the export list were not specified (i.e. export everything local to the module). hide: do not include this module in the generated documentation, but propagate any exported definitions to modules which re-export them. There's a slight change in the semantics for re-exporting a full module by giving 'module M' in the export list: if module M does not have the 'hide' option, then the documentation will now just contain a reference to module M rather than the full inlined contents of that module. These features, and some other changes in the pipeline, are the result of discussions between myself and Manuel Chakravarty <chak at cse.unsw.edu.au> (author of IDoc) yesterday. Also: some cleanups, use a Writer monad to collect error messages in some places instead of just printing them with trace. - - - - - a2239cf5 by Simon Marlow at 2002-05-08T11:22:30+00:00 [haddock @ 2002-05-08 11:22:30 by simonmar] Update to test new features. - - - - - 6add955f by Simon Marlow at 2002-05-08T13:37:25+00:00 [haddock @ 2002-05-08 13:37:25 by simonmar] Change the markup for typewriter-font from [...] to @... at . The reasoning is that the '@' symbol is much less likely to be needed than square brackets, and we don't want to have to escape square brackets in code fragments. This will be mildly painful in the short term, but it's better to get the change out of the way as early as possible. - - - - - cda06447 by Simon Marlow at 2002-05-08T13:39:56+00:00 [haddock @ 2002-05-08 13:39:56 by simonmar] Allow nested-style comments to be used as documentation annotations too. eg. {-| ... -} is equivalent to -- | ... An extra space can also be left after the comment opener: {- | ... -}. The only version that isn't allowed is {-# ... -}, because this syntax overlaps with Haskell pragmas; use {- # ... -} instead. - - - - - db23f65e by Simon Marlow at 2002-05-08T14:48:41+00:00 [haddock @ 2002-05-08 14:48:39 by simonmar] Add support for existential quantifiers on constructors. - - - - - adce3794 by Simon Marlow at 2002-05-08T15:43:25+00:00 [haddock @ 2002-05-08 15:43:25 by simonmar] update - - - - - 62a1f436 by Simon Marlow at 2002-05-08T15:44:10+00:00 [haddock @ 2002-05-08 15:44:10 by simonmar] Update to version 0.2 - - - - - f6a24ba3 by Simon Marlow at 2002-05-09T08:48:29+00:00 [haddock @ 2002-05-09 08:48:29 by simonmar] typo - - - - - 9f9522a4 by Simon Marlow at 2002-05-09T10:33:14+00:00 [haddock @ 2002-05-09 10:33:14 by simonmar] oops, left out '/' from the special characters in the last change. - - - - - 14abcb39 by Simon Marlow at 2002-05-09T10:34:44+00:00 [haddock @ 2002-05-09 10:34:44 by simonmar] Fix buglet - - - - - b8d878be by Simon Marlow at 2002-05-09T10:35:00+00:00 [haddock @ 2002-05-09 10:35:00 by simonmar] Give a more useful instance of Show for Module. - - - - - f7bfd626 by Simon Marlow at 2002-05-09T10:37:07+00:00 [haddock @ 2002-05-09 10:37:07 by simonmar] The last commit to Main.lhs broke the delicate balance of laziness which was being used to avoid computing the dependency graph of modules. So I finally bit the bullet and did a proper topological sort of the module graph, which turned out to be easy (stealing the Digraph module from GHC - this really ought to be in the libraries somewhere). - - - - - b481c1d0 by Simon Marlow at 2002-05-09T10:37:25+00:00 [haddock @ 2002-05-09 10:37:25 by simonmar] another item done - - - - - 032e2b42 by Simon Marlow at 2002-05-09T10:44:15+00:00 [haddock @ 2002-05-09 10:44:15 by simonmar] Don't consider a module re-export as having documentation, for the purposes of deciding whether we need a Synopsis section or not. - - - - - 5fb45e92 by Simon Marlow at 2002-05-09T11:10:55+00:00 [haddock @ 2002-05-09 11:10:55 by simonmar] Add a special case for list types in ppHsAType - - - - - 1937e428 by Simon Marlow at 2002-05-09T12:43:06+00:00 [haddock @ 2002-05-09 12:43:06 by simonmar] Type synonyms can accept a ctype on the RHS, to match GHC. - - - - - 0f16ce56 by Simon Marlow at 2002-05-09T12:45:19+00:00 [haddock @ 2002-05-09 12:45:19 by simonmar] Add 'stdcall' keyword - - - - - 29b0d7d2 by Simon Marlow at 2002-05-09T13:35:45+00:00 [haddock @ 2002-05-09 13:35:45 by simonmar] Add System Requirements section - - - - - bf14dddd by Simon Marlow at 2002-05-09T13:36:11+00:00 [haddock @ 2002-05-09 13:36:11 by simonmar] Test existential types, amongst other things - - - - - 502f8f6f by Simon Marlow at 2002-05-09T13:37:35+00:00 [haddock @ 2002-05-09 13:37:35 by simonmar] Print the module name in a doc-string parse error - - - - - ca1f8d49 by Simon Marlow at 2002-05-09T13:38:04+00:00 [haddock @ 2002-05-09 13:38:04 by simonmar] Add dependency - - - - - 8d3d91ff by Simon Marlow at 2002-05-09T15:37:57+00:00 [haddock @ 2002-05-09 15:37:57 by simonmar] Add the changelog/release notes - - - - - f3960959 by Simon Marlow at 2002-05-09T15:47:47+00:00 [haddock @ 2002-05-09 15:47:47 by simonmar] mention the backquote-style of markup - - - - - 089fb6e6 by Simon Marlow at 2002-05-09T15:59:45+00:00 [haddock @ 2002-05-09 15:59:45 by simonmar] update - - - - - bdd3be0b by Simon Marlow at 2002-05-09T15:59:56+00:00 [haddock @ 2002-05-09 15:59:56 by simonmar] Document changes since 0.1 - - - - - 00fc4af8 by Simon Marlow at 2002-05-10T08:22:48+00:00 [haddock @ 2002-05-10 08:22:48 by simonmar] oops, update to version 0.2 - - - - - a8a79041 by Simon Marlow at 2002-05-10T16:05:08+00:00 [haddock @ 2002-05-10 16:05:08 by simonmar] Only include a mini-contents if there are 2 or more sections - - - - - 06653319 by Simon Marlow at 2002-05-13T09:13:12+00:00 [haddock @ 2002-05-13 09:13:12 by simonmar] fix typos - - - - - 1402b19b by Simon Marlow at 2002-05-13T10:14:22+00:00 [haddock @ 2002-05-13 10:14:22 by simonmar] Allow backquote as the right-hand quote as well as the left-hand quote, as suggested by Dean Herrington. Clean up the grammar a litte. - - - - - dcd5320d by Simon Marlow at 2002-05-13T10:44:10+00:00 [haddock @ 2002-05-13 10:44:10 by simonmar] a couple more things, prioritise a bit - - - - - a90130c4 by Simon Marlow at 2002-05-13T15:19:03+00:00 [haddock @ 2002-05-13 15:19:03 by simonmar] Cope with datatypes which have documentation on the constructor but not the type itself, and records which have documentation on the fields but not the constructor. (Thanks to Ross Paterson for pointing out the bugs). - - - - - a774d432 by Simon Marlow at 2002-05-13T15:20:54+00:00 [haddock @ 2002-05-13 15:20:54 by simonmar] Fix one of the record examples - - - - - 2d1d5218 by Simon Marlow at 2002-05-15T12:44:35+00:00 [haddock @ 2002-05-15 12:44:35 by simonmar] Preserve the newline before a bird-track, but only within a paragraph. - - - - - 1554c09a by Simon Marlow at 2002-05-15T13:03:02+00:00 [haddock @ 2002-05-15 13:03:01 by simonmar] Reworking of the internals to support documenting function arguments (the Most Wanted new feature by the punters). The old method of keeping parsed documentation in a Name -> Doc mapping wasn't going to cut it for anntations on type components, where there's no name to attach the documentation to, so I've moved to storing all the documentation in the abstract syntax. Previously some of the documentation was left in the abstract syntax by the parser, but was later extracted into the mapping. In order to avoid having to parameterise the abstract syntax over the type of documentation stored in it, we have to parse the documentation at the same time as we parse the Haskell source (well, I suppose we could store 'Either String Doc' in the HsSyn, but that's clunky). One upshot is that documentation is now parsed eagerly, and documentation parse errors are fatal (but have better line numbers in the error message). The new story simplifies matters for the code that processes the source modules, because we don't have to maintain the extra Name->Doc mapping, and it should improve efficiency a little too. New features: - Function arguments and return values can now have doc annotations. - If you refer to a qualified name in a doc string, eg. 'IO.putStr', then Haddock will emit a hyperlink even if the identifier is not in scope, so you don't have to make sure everything referred to from the documentation is imported. - several bugs & minor infelicities fixed. - - - - - 57344dc3 by Simon Marlow at 2002-05-15T13:03:19+00:00 [haddock @ 2002-05-15 13:03:19 by simonmar] Bump to version 0.3 - - - - - b2791812 by Simon Marlow at 2002-05-15T13:03:41+00:00 [haddock @ 2002-05-15 13:03:41 by simonmar] update - - - - - fead183e by Simon Marlow at 2002-05-15T13:10:15+00:00 [haddock @ 2002-05-15 13:10:15 by simonmar] Rename Foo.hs to Test.hs, and add a Makefile - - - - - b0b1f89f by Simon Marlow at 2002-05-15T13:16:07+00:00 [haddock @ 2002-05-15 13:16:07 by simonmar] - Remove the note about function argument docs not being implemented - Note that qualified identifiers can be used to point to entities that aren't in scope. - - - - - 5665f31a by Simon Marlow at 2002-05-15T13:28:46+00:00 [haddock @ 2002-05-15 13:28:46 by simonmar] Patch to add support for GHC-style primitive strings ".."#, from Ross Paterson. - - - - - 0564505d by Simon Marlow at 2002-05-17T10:51:57+00:00 [haddock @ 2002-05-17 10:51:57 by simonmar] Fix bugs in qualified name handling (A.B.f was returned as B.f) - - - - - 10e7311c by Simon Marlow at 2002-05-21T10:24:52+00:00 [haddock @ 2002-05-21 10:24:52 by simonmar] - Use an alternate tabular layout for datatypes, which is more compact - Fix some problems with the function argument documentation - - - - - 2f91c2a6 by Simon Marlow at 2002-05-21T10:27:40+00:00 [haddock @ 2002-05-21 10:27:40 by simonmar] add a few more test cases - - - - - 01c2ddd2 by Simon Marlow at 2002-05-21T10:28:33+00:00 [haddock @ 2002-05-21 10:28:33 by simonmar] Rearrange a bit, and add support for tabular datatype rendering - - - - - a4e4c5f8 by Simon Marlow at 2002-05-27T09:03:52+00:00 [haddock @ 2002-05-27 09:03:51 by simonmar] Lots of changes: - instances of a class are listed with the class, and instances involving a datatype are listed with that type. Derived instances aren't included at the moment: the calculation to find the instance head for a derived instance is non-trivial. - some formatting changes; use rows with specified height rather than cellspacing in some places. - various fixes (source file links were wrong, amongst others) - - - - - 48722e68 by Simon Marlow at 2002-05-27T12:30:38+00:00 [haddock @ 2002-05-27 12:30:37 by simonmar] - Put function arguments *before* the doc for the function, as suggested by Sven Panne. This looks nicer when the function documentation is long. - Switch to using bold for binders at the definition site, and use underline for keywords. This makes the binder stand out more. - - - - - 657204d2 by Simon Marlow at 2002-05-27T13:19:49+00:00 [haddock @ 2002-05-27 13:19:49 by simonmar] Fix bug: we weren't renaming HsDocCommentNamed in renameDecl - - - - - 592aae66 by Simon Marlow at 2002-05-27T14:10:27+00:00 [haddock @ 2002-05-27 14:10:27 by simonmar] Fix some bugs in the rendering of qualified type signatures. - - - - - 69c8f763 by Simon Marlow at 2002-05-27T14:36:45+00:00 [haddock @ 2002-05-27 14:36:45 by simonmar] warning message tweak - - - - - 16e64e21 by Simon Marlow at 2002-05-27T14:53:53+00:00 [haddock @ 2002-05-27 14:53:53 by simonmar] hyperlinked identifiers should be in <tt> - - - - - 8d5e4783 by Simon Marlow at 2002-05-27T15:56:45+00:00 [haddock @ 2002-05-27 15:56:45 by simonmar] Do something sensible for modules which don't export anything (except instances). - - - - - 9d3ef811 by Simon Marlow at 2002-05-28T10:12:50+00:00 [haddock @ 2002-05-28 10:12:50 by simonmar] Rename the module documentation properly (bug reported by Sven Panne). - - - - - ef03a1cc by Simon Marlow at 2002-05-28T10:13:04+00:00 [haddock @ 2002-05-28 10:13:04 by simonmar] Add some more test cases - - - - - 92baa0e8 by Simon Marlow at 2002-05-28T11:17:55+00:00 [haddock @ 2002-05-28 11:17:55 by simonmar] If an identifier doesn't lex, then just replace it by a DocString. - - - - - a3156213 by Simon Marlow at 2002-05-28T16:16:19+00:00 [haddock @ 2002-05-28 16:16:19 by simonmar] Only link to names in the current module which are actually listed in the documentation. A name may be exported but not present in the documentation if it is exported as part of a 'module M' export specifier. - - - - - 31acf941 by Simon Marlow at 2002-05-28T16:17:11+00:00 [haddock @ 2002-05-28 16:17:11 by simonmar] update - - - - - 7e474ebf by Sigbjorn Finne at 2002-05-28T22:42:08+00:00 [haddock @ 2002-05-28 22:42:08 by sof] Handle lone occurrences of '/', e.g., -- | This/that. [did this in the lexer rather than in the parser, as I couldn't see a way not to introduce an S/R conflict that way.] - - - - - 093f7e53 by Simon Marlow at 2002-05-29T09:09:49+00:00 [haddock @ 2002-05-29 09:09:49 by simonmar] Back out previous change until we can find a better way to do this. - - - - - 9234389c by Simon Marlow at 2002-05-29T13:19:06+00:00 [haddock @ 2002-05-29 13:19:06 by simonmar] Make the markup syntax a little more friendly: - single quotes are now interpreted literally unless they surround a valid Haskell identifier. So for example now there's no need to escape a single quote used as an apostrophe. - text to the right of a bird track is now literal (if you want marked-up text in a code block, use @...@). - - - - - b3333526 by Simon Marlow at 2002-05-29T13:38:51+00:00 [haddock @ 2002-05-29 13:38:51 by simonmar] Document recent changes to markup syntax - - - - - f93641d6 by Simon Marlow at 2002-05-29T15:27:18+00:00 [haddock @ 2002-05-29 15:27:18 by simonmar] Include the instances in abstract data types too - - - - - 613f21e3 by Simon Marlow at 2002-06-03T13:05:58+00:00 [haddock @ 2002-06-03 13:05:57 by simonmar] Allow exporting of individual class methods and record selectors. For these we have to invent the correct type signature, which we do in the simplest possible way (i.e. no context reduction nonsense in the class case). - - - - - 14b36807 by Simon Marlow at 2002-06-03T13:20:00+00:00 [haddock @ 2002-06-03 13:20:00 by simonmar] Fix linking to qualified names again (thanks to Sven Panne for pointing out the bug). - - - - - 95b10eac by Simon Marlow at 2002-06-03T13:46:48+00:00 [haddock @ 2002-06-03 13:46:48 by simonmar] Fix for exporting record selectors from a newtype declaration - - - - - 272f932e by Simon Marlow at 2002-06-03T13:56:38+00:00 [haddock @ 2002-06-03 13:56:38 by simonmar] update to version 0.3 - - - - - 1c0a3bed by Simon Marlow at 2002-06-03T14:05:07+00:00 [haddock @ 2002-06-03 14:05:07 by simonmar] Add changes in version 0.3 - - - - - 145b4626 by Simon Marlow at 2002-06-03T14:12:38+00:00 [haddock @ 2002-06-03 14:12:38 by simonmar] Render class names as proper binders - - - - - 052106b3 by Simon Marlow at 2002-06-03T14:15:10+00:00 [haddock @ 2002-06-03 14:15:10 by simonmar] update, and separate into bugs, features, and cosmetic items. - - - - - 854f4914 by Simon Marlow at 2002-06-03T14:16:13+00:00 [haddock @ 2002-06-03 14:16:13 by simonmar] More test cases - - - - - 466922c8 by Simon Marlow at 2002-06-03T14:16:56+00:00 [haddock @ 2002-06-03 14:16:56 by simonmar] Example from the paper - - - - - 9962a045 by Simon Marlow at 2002-06-03T14:17:49+00:00 [haddock @ 2002-06-03 14:17:49 by simonmar] A debugging version of the style-sheet, which gives some tables coloured backgrounds so we can see what's going on. - - - - - f16b79db by Simon Marlow at 2002-06-03T14:19:46+00:00 [haddock @ 2002-06-03 14:19:46 by simonmar] typo - - - - - 620db27b by Simon Marlow at 2002-06-03T14:48:32+00:00 [haddock @ 2002-06-03 14:48:32 by simonmar] oops, fix markup bugs - - - - - 53fd105c by Simon Marlow at 2002-06-05T09:05:07+00:00 [haddock @ 2002-06-05 09:05:07 by simonmar] Keep foreign imports when there is no export list (bug reported by Sven Panne). - - - - - 6d98989c by Simon Marlow at 2002-06-05T09:12:02+00:00 [haddock @ 2002-06-05 09:12:02 by simonmar] Identifiers in single quotes can be symbol names too (bug reported by Hal Daume). - - - - - 001811e5 by Sven Panne at 2002-06-08T14:03:36+00:00 [haddock @ 2002-06-08 14:03:36 by panne] Tiny workaround for the fact that Haddock currently ignores HsImportSpecs: Let the local_orig_env take precedence. This is no real solution at all, but improves things sometimes, e.g. in my GLUT documentation. :-) - - - - - 504d19c9 by Simon Marlow at 2002-06-11T09:23:25+00:00 [haddock @ 2002-06-11 09:23:25 by simonmar] portability nit - - - - - e13b5af4 by Simon Marlow at 2002-06-20T12:38:07+00:00 [haddock @ 2002-06-20 12:38:07 by simonmar] Empty declaration fixes. - - - - - f467a9b6 by Simon Marlow at 2002-06-20T12:39:02+00:00 [haddock @ 2002-06-20 12:39:01 by simonmar] Add support for a "prologue" - a description for the whole library, placed on the contents page before the module list. - - - - - b8dbfe20 by Simon Marlow at 2002-06-21T12:43:06+00:00 [haddock @ 2002-06-21 12:43:06 by simonmar] When we have a single code block paragraph, don't place it in <pre>..</pre>, just use <tt>..</tt> to avoid generating extra vertical white space in some browsers. - - - - - 4831dbbd by Simon Marlow at 2002-06-21T15:50:42+00:00 [haddock @ 2002-06-21 15:50:42 by simonmar] Add support for reading and writing interface files(!) This turned out to be quite easy, and necessary to get decent hyperlinks between the documentation for separate packages in the libraries. The functionality isn't quite complete yet: for a given package of modules, you'd like to say "the HTML for these modules lives in directory <dir>" (currently they are assumed to be all in the same place). Two new flags: --dump-interface=FILE dump an interface file in FILE --read-interface=FILE read interface from FILE an interface file describes *all* the modules being processed. Only the exported names are kept in the interface: if you re-export a name from a module in another interface the signature won't be copied. This is a compromise to keep the size of the interfaces sensible. Also, I added another useful option: --no-implicit-prelude avoids trying to import the Prelude. Previously this was the default, but now importing the Prelude from elsewhere makes sense if you also read in an interface containing the Prelude module, so Haddock imports the Prelude implicitly according to the Haskell spec. - - - - - d3640a19 by Sven Panne at 2002-06-23T14:54:00+00:00 [haddock @ 2002-06-23 14:54:00 by panne] Make it compile with newer GHCs - - - - - 780c506b by Sven Panne at 2002-06-23T15:44:31+00:00 [haddock @ 2002-06-23 15:44:31 by panne] Cleaned up build root handling and added more docs - - - - - 45290d2e by Simon Marlow at 2002-06-24T14:37:43+00:00 [haddock @ 2002-06-24 14:37:42 by simonmar] When reading an interface, allow a file path offset to be specified which represents the path to the HTML files for the modules specified by that interface. The path may be either relative (to the location of the HTML for this package), or absolute. The syntax is --read-interface=PATH,FILE where PATH is the path to the HTML, and FILE is the filename containing the interface. - - - - - 4e2b9ae6 by Simon Marlow at 2002-07-03T16:01:08+00:00 [haddock @ 2002-07-03 16:01:07 by simonmar] Handle import specs properly, include 'hiding'. Haddock now has a complete implementation of the Haskell module system (more or less; I won't claim it's 100% correct). - - - - - 9a9aa1a8 by Simon Marlow at 2002-07-03T16:18:16+00:00 [haddock @ 2002-07-03 16:18:16 by simonmar] Update - - - - - 560c3026 by Simon Marlow at 2002-07-04T14:56:10+00:00 [haddock @ 2002-07-04 14:56:10 by simonmar] Clean up the code that constructs the exported declarations, and fix a couple of bugs along the way. Now if you import a class hiding one of the methods, then re-export the class, the version in the documentation will correctly have the appropriate method removed. - - - - - 2c26e77d by Simon Marlow at 2002-07-04T15:26:13+00:00 [haddock @ 2002-07-04 15:26:13 by simonmar] More bugfixes to the export handling - - - - - 03e0710d by Simon Marlow at 2002-07-09T10:12:10+00:00 [haddock @ 2002-07-09 10:12:10 by simonmar] Don't require that the list type comes from "Prelude" for it to be treated as special syntax (sometimes it comes from Data.List or maybe even GHC.Base). - - - - - 44f3891a by Simon Marlow at 2002-07-09T10:12:51+00:00 [haddock @ 2002-07-09 10:12:51 by simonmar] commented-out debugging code - - - - - 97280873 by Krasimir Angelov at 2002-07-09T16:33:33+00:00 [haddock @ 2002-07-09 16:33:31 by krasimir] 'Microsoft HTML Help' support - - - - - 3dc04655 by Simon Marlow at 2002-07-10T09:40:56+00:00 [haddock @ 2002-07-10 09:40:56 by simonmar] Fix for rendering of the (->) type constructor, from Ross Paterson. - - - - - c9f149c6 by Simon Marlow at 2002-07-10T10:26:11+00:00 [haddock @ 2002-07-10 10:26:11 by simonmar] Tweaks to the MS Help support: the extra files are now only generated if you ask for them (--ms-help). - - - - - e8acc1e6 by Simon Marlow at 2002-07-10T10:57:10+00:00 [haddock @ 2002-07-10 10:57:10 by simonmar] Document all the new options since 0.3 - - - - - 8bb85544 by Simon Marlow at 2002-07-10T10:58:31+00:00 [haddock @ 2002-07-10 10:58:31 by simonmar] Sort the options a bit - - - - - abc0dd59 by Simon Marlow at 2002-07-15T09:19:38+00:00 [haddock @ 2002-07-15 09:19:38 by simonmar] Fix a bug in mkExportItems when processing a module without an explicit export list. We were placing one copy of a declaration for each binder in the declaration, which for a data type would mean one copy of the whole declaration per constructor or record selector. - - - - - dde65bb9 by Simon Marlow at 2002-07-15T09:54:16+00:00 [haddock @ 2002-07-15 09:54:16 by simonmar] merge rev. 1.35 - - - - - bd7eb8c4 by Simon Marlow at 2002-07-15T10:14:31+00:00 [haddock @ 2002-07-15 10:14:30 by simonmar] Be a bit more liberal in the kind of commenting styles we allow, as suggested by Malcolm Wallace. Mostly this consists of allowing doc comments either side of a separator token. In an export list, a section heading is now allowed before the comma, as well as after it. eg. module M where ( T(..) -- * a section heading , f -- * another section heading , g ) In record fields, doc comments are allowed anywhere (previously a doc-next was allowed only after the comma, and a doc-before was allowed only before the comma). eg. data R = C { -- | describes 'f' f :: Int -- | describes 'g' , g :: Int } - - - - - 8f6dfe34 by Simon Marlow at 2002-07-15T10:21:56+00:00 [haddock @ 2002-07-15 10:21:56 by simonmar] Mention alternative commenting styles. - - - - - fc515bb7 by Simon Marlow at 2002-07-15T16:16:50+00:00 [haddock @ 2002-07-15 16:16:50 by simonmar] Allow multiple sections/subsections before and after a comma in the export list. Also at the same time I made the syntax a little stricter (multiple commas now aren't allowed between export specs). - - - - - 80a97e74 by Simon Marlow at 2002-07-19T09:13:10+00:00 [haddock @ 2002-07-19 09:13:10 by simonmar] Allow special id's ([], (), etc.) to be used in an import declaration. - - - - - a69d7378 by Simon Marlow at 2002-07-19T09:59:02+00:00 [haddock @ 2002-07-19 09:59:02 by simonmar] Allow special id's ([], (), etc.) to be used in an import declarations. - - - - - d205fa60 by Simon Marlow at 2002-07-19T10:00:16+00:00 [haddock @ 2002-07-19 10:00:16 by simonmar] Relax the restrictions which require doc comments to be followed by semi colons - in some cases this isn't necessary. Now you can write module M where { -- | some doc class C where {} } without needing to put a semicolon before the class declaration. - - - - - e9301e14 by Simon Marlow at 2002-07-23T08:24:09+00:00 [haddock @ 2002-07-23 08:24:09 by simonmar] A new TODO list item - - - - - e5d77586 by Simon Marlow at 2002-07-23T08:40:56+00:00 [haddock @ 2002-07-23 08:40:56 by simonmar] - update the acknowledgements - remove the paragraph that described how to use explicit layout with doc comments; it isn't relevant any more. - - - - - 78a94137 by Simon Marlow at 2002-07-23T08:43:02+00:00 [haddock @ 2002-07-23 08:43:02 by simonmar] more tests - - - - - 5c320927 by Simon Marlow at 2002-07-23T08:43:26+00:00 [haddock @ 2002-07-23 08:43:26 by simonmar] Updates for version 0.4 - - - - - 488e99ae by Simon Marlow at 2002-07-23T09:10:46+00:00 [haddock @ 2002-07-23 09:10:46 by simonmar] Fix the %changelog (rpm complained that it wasn't in the right order) - - - - - a77bb373 by Simon Marlow at 2002-07-23T09:12:38+00:00 [haddock @ 2002-07-23 09:12:38 by simonmar] Another item for the TODO list - - - - - f1ec1813 by Simon Marlow at 2002-07-23T10:18:46+00:00 [haddock @ 2002-07-23 10:18:46 by simonmar] Add a version banner when invoked with -v - - - - - 1d44cadf by Simon Marlow at 2002-07-24T09:28:19+00:00 [haddock @ 2002-07-24 09:28:19 by simonmar] Remove ^Ms - - - - - 4d8d5e94 by Simon Marlow at 2002-07-24T09:42:18+00:00 [haddock @ 2002-07-24 09:42:17 by simonmar] Patches to quieten ghc -Wall, from those nice folks at Galois. - - - - - d6edc43e by Simon Marlow at 2002-07-25T14:37:29+00:00 [haddock @ 2002-07-25 14:37:28 by simonmar] Patch to allow simple hyperlinking to an arbitrary location in another module's documentation, from Volker Stolz. Now in a doc comment: #foo# creates <a name="foo"></a> And you can use the form "M\#foo" to hyperlink to the label 'foo' in module 'M'. Note that the backslash is necessary for now. - - - - - b34d18fa by Simon Marlow at 2002-08-02T09:08:22+00:00 [haddock @ 2002-08-02 09:08:22 by simonmar] The <TT> and <PRE> environments seem to use a font that is a little too small in IE. Compensate. (suggestion from Daan Leijen). - - - - - 8106b086 by Simon Marlow at 2002-08-02T09:25:23+00:00 [haddock @ 2002-08-02 09:25:20 by simonmar] Remove <P>..</P> from around list items, to reduce excess whitespace between the items of bulleted and ordered lists. (Suggestion from Daan Leijen). - - - - - c1acff8f by Simon Marlow at 2002-08-05T09:03:49+00:00 [haddock @ 2002-08-05 09:03:49 by simonmar] update - - - - - f968661c by Simon Marlow at 2002-11-11T09:32:57+00:00 [haddock @ 2002-11-11 09:32:57 by simonmar] Fix cut-n-pasto - - - - - 12d02619 by Simon Marlow at 2002-11-13T09:49:46+00:00 [haddock @ 2002-11-13 09:49:46 by simonmar] Small bugfix in the --read-interface option parsing from Brett Letner. - - - - - 30e32d5e by Ross Paterson at 2003-01-16T15:07:57+00:00 [haddock @ 2003-01-16 15:07:57 by ross] Adjust for the new exception libraries (as well as the old ones). - - - - - 871f65df by Sven Panne at 2003-02-20T21:31:40+00:00 [haddock @ 2003-02-20 21:31:40 by panne] * Add varsyms and consyms to index * Exclude empty entries from index - - - - - bc42cc87 by Sven Panne at 2003-02-24T21:26:29+00:00 [haddock @ 2003-02-24 21:26:29 by panne] Don't convert a "newtype" to a single-constructor "data" for non-abstractly exported types, they are quite different regarding strictness/pattern matching. Now a "data" without any constructors is only emitted for an abstractly exported type, regardless if it is actually a "newtype" or a "data". - - - - - 0c2a1d99 by Sven Panne at 2003-03-08T19:02:38+00:00 [haddock @ 2003-03-08 19:02:38 by panne] Fixed some broken/redirected/canonicalized links found by a very picky link checker. - - - - - 25459269 by Sven Panne at 2003-03-09T21:13:43+00:00 [haddock @ 2003-03-09 21:13:43 by panne] Don't append a fragment to non-defining index entries, only documents with a defining occurrence have a name anchor. - - - - - 6be4db86 by Sven Panne at 2003-03-10T21:34:25+00:00 [haddock @ 2003-03-10 21:34:24 by panne] Escape fragments. This fixes e.g. links to operators. - - - - - eb12972c by Ross Paterson at 2003-04-25T10:50:06+00:00 [haddock @ 2003-04-25 10:50:05 by ross] An 80% solution to generating derived instances. A complete solution would duplicate the instance inference logic, but if a type variable occurs as a constructor argument, then we can just propagate the derived class to the variable. But we know nothing of the constraints on any type variables that occur elsewhere. For example, the declarations data Either a b = Left a | Right b deriving (Eq, Ord) data Ptr a = Ptr Addr# deriving (Eq, Ord) newtype IORef a = IORef (STRef RealWorld a) deriving Eq yield the instances (Eq a, Eq b) => Eq (Either a b) (Ord a, Ord b) => Ord (Either a b) Eq (Ptr a) Ord (Ptr a) (??? a) => Eq (IORef a) The last example shows the limits of this local analysis. Note that a type variable may be in both categories: then we know a constraint, but there may be more, or a stronger constraint, e.g. data Tree a = Node a [Tree a] deriving Eq yields (Eq a, ??? a) => Eq (Tree a) - - - - - de886f78 by Simon Marlow at 2003-04-25T11:17:55+00:00 [haddock @ 2003-04-25 11:17:55 by simonmar] Some updates, including moving the derived instance item down to the bottom of the list now that Ross has contributed some code that does the job for common cases. - - - - - 1b52cffd by Simon Marlow at 2003-04-30T14:02:32+00:00 [haddock @ 2003-04-30 14:02:32 by simonmar] When installing on Windows, run cygpath over $(HADDOCKLIB) so that haddock (a mingw program, built by GHC) can understand it. You still need to be in a cygwin environment to run Haddock, because of the shell script wrapper. - - - - - d4f638de by Simon Marlow at 2003-05-06T10:04:47+00:00 [haddock @ 2003-05-06 10:04:47 by simonmar] Catch another case of a paragraph containing just a DocMonospaced that should turn into a DocCodeBlock. - - - - - 4162b2b9 by Simon Marlow at 2003-05-06T10:11:44+00:00 [haddock @ 2003-05-06 10:11:44 by simonmar] Add some more code-block tests. - - - - - 4f5802c8 by Simon Marlow at 2003-05-06T10:14:52+00:00 [haddock @ 2003-05-06 10:14:52 by simonmar] Don't turn a single DocCodeBlock into a DocMonospaced, because that tends to remove the line breaks in the code. - - - - - ef8c45f7 by Simon Marlow at 2003-05-21T15:07:21+00:00 [haddock @ 2003-05-21 15:07:21 by simonmar] Only omit the module contents when there are no section headings at all. - - - - - bcee1e75 by Sigbjorn Finne at 2003-05-30T16:50:45+00:00 [haddock @ 2003-05-30 16:50:45 by sof] cygpath: for now, steer clear of --mixed - - - - - 30567af3 by Sigbjorn Finne at 2003-05-30T17:59:28+00:00 [haddock @ 2003-05-30 17:59:28 by sof] oops, drop test defn from prev commit - - - - - b0856e7d by Simon Marlow at 2003-06-03T09:55:26+00:00 [haddock @ 2003-06-03 09:55:26 by simonmar] Two small fixes to make the output valid HTML 4.01 (transitional). Thanks to Malcolm Wallace for pointing out the problems. - - - - - 70e137ea by Simon Marlow at 2003-07-28T13:30:35+00:00 [haddock @ 2003-07-28 13:30:35 by simonmar] Add tests for a couple of bugs. - - - - - 122bd578 by Simon Marlow at 2003-07-28T13:31:25+00:00 [haddock @ 2003-07-28 13:31:25 by simonmar] Add documentation for anchors. - - - - - 0bd27cb2 by Simon Marlow at 2003-07-28T13:31:46+00:00 [haddock @ 2003-07-28 13:31:46 by simonmar] Update - - - - - 08052d42 by Simon Marlow at 2003-07-28T13:32:12+00:00 [haddock @ 2003-07-28 13:32:12 by simonmar] layout tweak. - - - - - 13942749 by Simon Marlow at 2003-07-28T13:33:03+00:00 [haddock @ 2003-07-28 13:33:03 by simonmar] Differentiate links to types/classes from links to variables/constructors with a prefix ("t:" and "v:" respectively). - - - - - d7f493b9 by Simon Marlow at 2003-07-28T13:35:17+00:00 [haddock @ 2003-07-28 13:35:16 by simonmar] When a module A exports another module's contents via 'module B', then modules which import entities from B re-exported by A should link to B.foo rather than A.foo. See examples/Bug2.hs. - - - - - d94cf705 by Simon Marlow at 2003-07-28T13:36:14+00:00 [haddock @ 2003-07-28 13:36:14 by simonmar] Update to version 0.5 - - - - - dbb776cd by Sven Panne at 2003-07-28T14:02:43+00:00 [haddock @ 2003-07-28 14:02:43 by panne] * Updated to version 0.5 * Automagically generate configure if it is not there - - - - - 6cfeee53 by Simon Marlow at 2003-07-28T14:32:43+00:00 [haddock @ 2003-07-28 14:32:42 by simonmar] Update to avoid using hslibs with GHC >= 5.04 - - - - - a1ce838f by Simon Marlow at 2003-07-28T14:33:37+00:00 [haddock @ 2003-07-28 14:33:37 by simonmar] Update for 0.5 - - - - - c0fe6493 by Simon Marlow at 2003-07-28T14:53:22+00:00 [haddock @ 2003-07-28 14:53:22 by simonmar] Markup fix - - - - - 6ea31596 by Sven Panne at 2003-07-28T16:40:45+00:00 [haddock @ 2003-07-28 16:40:45 by panne] Make it compile with GHC >= 6.01 - - - - - afcd30fc by Simon Marlow at 2003-07-30T15:04:52+00:00 [haddock @ 2003-07-30 15:04:52 by simonmar] Pay attention to import specs when building the the import env, as well as the orig env. This may fix some wrong links in documentation when import specs are being used. - - - - - 17c3137f by Simon Marlow at 2003-07-30T16:05:41+00:00 [haddock @ 2003-07-30 16:05:40 by simonmar] Rename instances based on the import_env for the module in which they are to be displayed. This should give, in many cases, better links for the types and classes mentioned in the instance head. This involves keeping around the import_env in the iface until the end, because instances are not collected up until all the modules have been processed. Fortunately it doesn't seem to affect performance much. Instance heads are now attached to ExportDecls, rather than the HTML backend passing around a separate mapping for instances. This is a cleanup. - - - - - 3d3b5c87 by Sven Panne at 2003-08-04T10:18:24+00:00 [haddock @ 2003-08-04 10:18:24 by panne] Don't print parentheses around one-element contexts - - - - - 9e3f3f2d by Simon Marlow at 2003-08-04T12:59:47+00:00 [haddock @ 2003-08-04 12:59:47 by simonmar] A couple of TODOs. - - - - - e9d8085c by Simon Marlow at 2003-08-05T14:10:31+00:00 [haddock @ 2003-08-05 14:10:31 by simonmar] I'm not sure why, but it seems that the index entries for non-defining occurrences of entities did not have an anchor - the link just pointed to the module. This fixes it. - - - - - ff5c7d6d by Simon Marlow at 2003-08-15T14:42:59+00:00 [haddock @ 2003-08-15 14:42:59 by simonmar] Convert the lexer to Alex, and fix a bug in the process. - - - - - 1aa077bf by Simon Marlow at 2003-08-15T15:00:18+00:00 [haddock @ 2003-08-15 15:00:18 by simonmar] Update - - - - - d3de1e38 by Simon Marlow at 2003-08-15T15:01:03+00:00 [haddock @ 2003-08-15 15:01:03 by simonmar] wibbles - - - - - b40ece3b by Simon Marlow at 2003-08-18T10:04:47+00:00 [haddock @ 2003-08-18 10:04:47 by simonmar] Lex the 'mdo' keyword as 'do'. - - - - - 8f9a1146 by Simon Marlow at 2003-08-18T11:48:24+00:00 [haddock @ 2003-08-18 11:48:24 by simonmar] Two bugs from Sven. - - - - - ea54ebc0 by Simon Marlow at 2003-08-18T11:48:46+00:00 [haddock @ 2003-08-18 11:48:46 by simonmar] Fixes to the new lexer. - - - - - d5f6a4b5 by Simon Marlow at 2003-08-19T09:09:03+00:00 [haddock @ 2003-08-19 09:09:03 by simonmar] Further wibbles to the syntax. - - - - - 6bbdadb7 by Sven Panne at 2003-08-26T18:45:35+00:00 [haddock @ 2003-08-26 18:45:35 by panne] Use autoreconf instead of autoconf - - - - - 32e889cb by Sven Panne at 2003-08-26T19:01:19+00:00 [haddock @ 2003-08-26 19:01:18 by panne] Made option handling a bit more consistent with other tools, in particular: Every program in fptools should output * version info on stdout and terminate successfully when -V or --version * usage info on stdout and terminate successfully when -? or --help * usage info on stderr and terminate unsuccessfully when an unknown option is given. - - - - - 5d156a91 by Sven Panne at 2003-08-26T19:20:55+00:00 [haddock @ 2003-08-26 19:20:55 by panne] Make it *very* clear that we terminate when given a -V/--version flag - - - - - e6577265 by Sven Panne at 2003-08-27T07:50:03+00:00 [haddock @ 2003-08-27 07:50:02 by panne] * Made -D a short option for --dump-interface. * Made -m a short option for --ms-help. * Made -n a short option for --no-implicit-prelude. * Made -c a short option for --css. * Removed DocBook options from executable (they didn't do anything), but mark them as reserved in the docs. Note that the short option for DocBook output is now -S (from SGML) instead of -d. The latter is now a short option for --debug. * The order of the Options in the documentation now matches the order printed by Haddock itself. Note: Although changing the names of options is often a bad idea, I'd really like to make the options for the programs in fptools more consistent and compatible to the ones used in common GNU programs. - - - - - d303ff98 by Simon Marlow at 2003-09-10T08:23:48+00:00 [haddock @ 2003-09-10 08:23:48 by simonmar] Add doc subdir. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 9a70e46a by Simon Marlow at 2003-09-10T08:24:32+00:00 [haddock @ 2003-09-10 08:24:32 by simonmar] Install these files in $(datadir), not $(libdir), since they're architecture independent. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - bbb87e7a by Simon Marlow at 2003-09-10T08:25:31+00:00 [haddock @ 2003-09-10 08:25:31 by simonmar] Haddock's supplementary HTML bits now live in $(datadir), not $(libdir). Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 3587c24b by Simon Marlow at 2003-09-22T10:34:38+00:00 [haddock @ 2003-09-22 10:34:38 by simonmar] Allow installing of docs. - - - - - d510b517 by Sven Panne at 2003-10-11T08:10:44+00:00 [haddock @ 2003-10-11 08:10:44 by panne] Include architecture-independent files in file list - - - - - 187d7618 by Sigbjorn Finne at 2003-10-20T17:19:24+00:00 [haddock @ 2003-10-20 17:19:22 by sof] support for i-parameters + zip comprehensions - - - - - b6c7a273 by Simon Marlow at 2003-11-03T14:24:24+00:00 [haddock @ 2003-11-03 14:24:24 by simonmar] Update TODO file. - - - - - 58513e33 by Simon Marlow at 2003-11-05T11:22:04+00:00 [haddock @ 2003-11-05 11:22:04 by simonmar] Remove the last of the uses of 'trace' to emit warnings, and tidy up a couple of places where duplicate warnings were being emitted. - - - - - 33a78846 by Simon Marlow at 2003-11-05T11:30:53+00:00 [haddock @ 2003-11-05 11:30:52 by simonmar] - Suppress warnings about unknown imported modules by default. - Add a -v/--verbose flag to re-enable these warnings. The general idea is to suppress the "Warning: unknown module: Prelude" warnings which most Haddock users will see every time, and which aren't terribly useful. - - - - - a969de7f by Simon Marlow at 2003-11-05T12:30:28+00:00 [haddock @ 2003-11-05 12:30:28 by simonmar] - Remove the emboldening of index entries for defining locations. This isn't useful, and breaks abstractions. - If an entity is re-exported by a module but the module doesn't include documentation for that entity (perhaps because it is re-exported by 'module M'), then don't attempt to hyperlink to the documentation from the index. Instead, just list that module in the index, to indicate that the entity is exported from there. - - - - - f14ea82a by Simon Marlow at 2003-11-05T15:15:59+00:00 [haddock @ 2003-11-05 15:15:59 by simonmar] Index overhaul: - no more separate type/class and variable/function indices - the index now makes a distinction between different entities with the same name. One example is a type constructor with the same name as a data constructor, but another example is simply a function with the same name exported by two different modules. For example, the index entry for 'catch' now looks like this: catch 1 (Function) Control.Exception 2 (Function) GHC.Exception, Prelude, System.IO, System.IO.Error making it clear that there are two different 'catch'es, but one of them is exported by several modules. - Each index page now has the index contents (A B C ...) at the top. Please let me know if you really hate any of this. - - - - - 01a25ca6 by Simon Marlow at 2003-11-05T15:16:38+00:00 [haddock @ 2003-11-05 15:16:38 by simonmar] Update - - - - - 1a7ccb86 by Simon Marlow at 2003-11-05T17:16:05+00:00 [haddock @ 2003-11-05 17:16:04 by simonmar] Support for generating a single unified index for several packages. --use-index=URL turns off normal index generation, causes Index links to point to URL. --gen-index generates an combined index from the specified interfaces. Currently doesn't work exactly right, because the interfaces don't contain the iface_reexported info. I'll need to fix that up. - - - - - a2bca16d by Simon Marlow at 2003-11-06T10:44:52+00:00 [haddock @ 2003-11-06 10:44:52 by simonmar] Include iface_reexported in the .haddock file. This unfortunately bloats the file (40% for base). If this gets to be a problem we can always apply the dictionary trick that GHC uses for squashing .hi files. - - - - - 0a09c293 by Simon Marlow at 2003-11-06T12:39:47+00:00 [haddock @ 2003-11-06 12:39:46 by simonmar] - Add definition lists, marked up like this: -- | This is a definition list: -- -- [@foo@] The description of @foo at . -- -- [@bar@] The description of @bar at . Cunningly, the [] characters are not treated specially unless a [ is found at the beginning of a paragraph, in which case the ] becomes special in the following text. - Add --use-contents and --gen-contents, along the lines of --use-index and --gen-index added yesterday. Now we can generate a combined index and contents for the whole of the hierarchical libraries, and in theory the index/contents on the system could be updated as new packages are added. - - - - - fe1b3460 by Simon Marlow at 2003-11-06T14:47:36+00:00 [haddock @ 2003-11-06 14:47:36 by simonmar] Remove the 'Parent' button - it is of dubious use, and often points into thin air. - - - - - db6d762f by Simon Marlow at 2003-11-06T16:48:14+00:00 [haddock @ 2003-11-06 16:48:11 by simonmar] - Include the OptHide setting in the interface, so we don't include hidden modules in the combined index/contents. - Add a -k/--package flag to set the package name for the current set of modules. The package name for each module is now shown in the right-hand column of the contents, in a combined contents page. - - - - - 7d71718b by Simon Marlow at 2003-11-06T16:50:28+00:00 [haddock @ 2003-11-06 16:50:28 by simonmar] Add -k/--package docs - - - - - ef43949d by Simon Marlow at 2003-11-06T16:51:23+00:00 [haddock @ 2003-11-06 16:51:23 by simonmar] Bump to 0.6 - - - - - 1c419e06 by Simon Marlow at 2003-11-06T16:51:50+00:00 [haddock @ 2003-11-06 16:51:50 by simonmar] update - - - - - 69422327 by Simon Marlow at 2003-11-10T14:41:06+00:00 [haddock @ 2003-11-10 14:41:05 by simonmar] Re-exporting names from a different package is problematic, because we don't have access to the full documentation for the entity. Currently Haddock just ignores entities with no documentation, but this results in bogus-looking empty documentation for many of the modules in the haskell98 package. So: - the documentation will now just list the name, as a link pointing to the location of the actual documentation. - now we don't attempt to link to these re-exported entities if they are referred to by the current module. Additionally: - If there is no documentation in the current module, include just the Synopsis section (rather than just the documentation section, as it was before). This just looks nicer and was on the TODO list. - - - - - 3c3fc433 by Simon Marlow at 2003-11-10T14:51:59+00:00 [haddock @ 2003-11-10 14:51:59 by simonmar] Fix for getReExports: take into account names which are not visible because they are re-exported from a different package. - - - - - 31c8437b by Simon Marlow at 2003-11-10T15:10:53+00:00 [haddock @ 2003-11-10 15:10:53 by simonmar] Version 0.6 changes - - - - - a7c2430b by Simon Marlow at 2003-11-10T15:15:58+00:00 [haddock @ 2003-11-10 15:15:58 by simonmar] getReExports: one error case that isn't - - - - - 00cc459c by Simon Marlow at 2003-11-10T16:15:19+00:00 [haddock @ 2003-11-10 16:15:18 by simonmar] copyright update - - - - - ca62408d by Simon Marlow at 2003-11-11T09:57:25+00:00 [haddock @ 2003-11-11 09:57:25 by simonmar] Version 0.6 - - - - - 3acbf818 by Simon Marlow at 2003-11-11T12:10:44+00:00 [haddock @ 2003-11-11 12:10:44 by simonmar] Go back to producing just the documentation section, rather than just the synopsis section, for a module with no documentation annotations. One reason is that the synopsis section tries to link each entity to its documentation on the same page. Also, the doc section anchors each entity, and it lists instances which the synopsis doesn't. - - - - - 6c90abc2 by Simon Marlow at 2003-11-12T10:03:39+00:00 [haddock @ 2003-11-12 10:03:39 by simonmar] 2002 -> 2003 - - - - - 090bbc4c by Simon Marlow at 2003-11-28T12:08:00+00:00 [haddock @ 2003-11-28 12:08:00 by simonmar] update - - - - - 8096a832 by Simon Marlow at 2003-11-28T12:09:58+00:00 [haddock @ 2003-11-28 12:09:58 by simonmar] Fix some of the problems with Haddock generating pages that are too wide. Now we only specify 'nowrap' when it is necessary to avoid a code box getting squashed up by the text to the right of it. - - - - - 35294929 by Sven Panne at 2003-12-29T17:16:31+00:00 [haddock @ 2003-12-29 17:16:31 by panne] Updated my email address - - - - - cdb697bf by Simon Marlow at 2004-01-08T10:14:24+00:00 [haddock @ 2004-01-08 10:14:24 by simonmar] Add instructions for using GHC to pre-process source for feeding to Haddock. - - - - - 8dfc491f by Simon Marlow at 2004-01-09T12:45:46+00:00 [haddock @ 2004-01-09 12:45:46 by simonmar] Add -optP-P to example ghc command line. - - - - - ac41b820 by Simon Marlow at 2004-02-03T11:02:03+00:00 [haddock @ 2004-02-03 11:02:03 by simonmar] Fix bug in index generation - - - - - f4e7edcb by Simon Marlow at 2004-02-10T11:51:16+00:00 [haddock @ 2004-02-10 11:51:16 by simonmar] Don't throw away whitespace at the beginning of a line (experimental fix). - - - - - 68e212d2 by Simon Marlow at 2004-02-10T12:10:08+00:00 [haddock @ 2004-02-10 12:10:08 by simonmar] Fix for previous commit: I now realise why the whitespace was stripped from the beginning of the line. Work around it. - - - - - e7d7f2df by Sven Panne at 2004-02-10T18:38:45+00:00 [haddock @ 2004-02-10 18:38:45 by panne] Make Haddock link with the latest relocated monad transformer package - - - - - 992d4225 by Simon Marlow at 2004-02-16T10:21:35+00:00 [haddock @ 2004-02-16 10:21:35 by simonmar] Add a TODO - - - - - 1ac55326 by Simon Marlow at 2004-03-12T11:33:39+00:00 [haddock @ 2004-03-12 11:33:39 by simonmar] Add an item. - - - - - 0478e903 by Simon Marlow at 2004-03-15T12:24:05+00:00 [haddock @ 2004-03-15 12:24:05 by simonmar] Add an item. - - - - - 6f26d21a by Simon Marlow at 2004-03-18T14:21:29+00:00 [haddock @ 2004-03-18 14:21:29 by simonmar] Fix URL - - - - - 19b6bb99 by Simon Marlow at 2004-03-22T14:09:03+00:00 [haddock @ 2004-03-22 14:09:03 by simonmar] getReExports was bogus: we should really look in the import_env to find the documentation for an entity which we are re-exporting without documentation. Suggested by: Ross Paterson (patch modified by me). - - - - - 5c756031 by Simon Marlow at 2004-03-24T09:42:11+00:00 [haddock @ 2004-03-24 09:42:10 by simonmar] hiding bug from Ross Paterson (fixed in rev 1.59 of Main.hs) - - - - - 1b692e6c by Simon Marlow at 2004-03-24T10:10:50+00:00 [haddock @ 2004-03-24 10:10:50 by simonmar] mkExportItems fix & simplification: we should be looking at the actual exported names (calculated earlier) to figure out which subordinates of a declaration are exported. This means that if you export a record, and name its fields separately in the export list, the fields will still be visible in the documentation for the constructor. - - - - - 90e5e294 by Simon Marlow at 2004-03-24T10:12:08+00:00 [haddock @ 2004-03-24 10:12:08 by simonmar] Make restrictCons take into account record field names too (removing a ToDo). - - - - - 2600efa4 by Simon Marlow at 2004-03-24T10:16:17+00:00 [haddock @ 2004-03-24 10:16:17 by simonmar] Record export tests. - - - - - 6a8575c7 by Simon Marlow at 2004-03-25T09:35:14+00:00 [haddock @ 2004-03-25 09:35:14 by simonmar] restrictTo: fix for restricting a newtype with a record field. - - - - - dcf55a8d by Simon Marlow at 2004-03-25T10:01:42+00:00 [haddock @ 2004-03-25 10:01:42 by simonmar] Fix duplicate instance bug - - - - - f49aa758 by Simon Marlow at 2004-03-25T10:02:41+00:00 [haddock @ 2004-03-25 10:02:41 by simonmar] Duplicate instance bug. - - - - - 7b87344c by Simon Marlow at 2004-03-25T10:29:56+00:00 [haddock @ 2004-03-25 10:29:56 by simonmar] If a name is imported from two places, one hidden and one not, choose the unhidden one to link to. Also, when there's only a hidden module to link to, don't try linking to it. - - - - - 40f44d7b by Simon Marlow at 2004-03-25T15:17:24+00:00 [haddock @ 2004-03-25 15:17:23 by simonmar] Add support for collaspible parts of the page, with a +/- button and a bit of JavaScript. Make the instances collapsible, and collapse them by default. This makes documentation with long lists of instances (eg. the Prelude) much easier to read. Maybe we should give other documentation sections the same treatment. - - - - - 9b64dc0f by Simon Marlow at 2004-03-25T15:20:55+00:00 [haddock @ 2004-03-25 15:20:55 by simonmar] Update - - - - - c2fff7f2 by Simon Marlow at 2004-03-25T15:45:10+00:00 [haddock @ 2004-03-25 15:45:10 by simonmar] Eliminate some unnecessary spaces in the HTML rendering - - - - - b7948ff0 by Simon Marlow at 2004-03-25T16:00:37+00:00 [haddock @ 2004-03-25 16:00:36 by simonmar] Remove all that indentation in the generated HTML to keep the file sizes down. - - - - - da2bb4ca by Sven Panne at 2004-03-27T09:57:58+00:00 [haddock @ 2004-03-27 09:57:57 by panne] Added the new-born haddock.js to the build process and the documentation. - - - - - b99e6f8c by Sven Panne at 2004-03-27T10:32:20+00:00 [haddock @ 2004-03-27 10:32:20 by panne] "type" is a required attribute of the "script" element - - - - - 562b185a by Sven Panne at 2004-03-27T12:52:34+00:00 [haddock @ 2004-03-27 12:52:34 by panne] Add a doctype for the contents page, too. - - - - - f6a99c2d by Simon Marlow at 2004-04-14T10:03:25+00:00 [haddock @ 2004-04-14 10:03:25 by simonmar] fix for single-line comment syntax - - - - - de366303 by Simon Marlow at 2004-04-20T13:08:04+00:00 [haddock @ 2004-04-20 13:08:04 by simonmar] Allow a 'type' declaration to include documentation comments. These will be ignored by Haddock, but at least one user (Johannes Waldmann) finds this feature useful, and it's easy to add. - - - - - fd78f51e by Simon Marlow at 2004-05-07T15:14:56+00:00 [haddock @ 2004-05-07 15:14:56 by simonmar] - update copyright - add version to abstract - - - - - 59f53e32 by Sven Panne at 2004-05-09T14:39:53+00:00 [haddock @ 2004-05-09 14:39:53 by panne] Fix the fix for single-line comment syntax, ------------------------------------------- is now a valid comment line again. - - - - - 8b18f2fe by Simon Marlow at 2004-05-10T10:11:51+00:00 [haddock @ 2004-05-10 10:11:51 by simonmar] Update - - - - - 225a491d by Ross Paterson at 2004-05-19T13:10:23+00:00 [haddock @ 2004-05-19 13:10:23 by ross] Make the handling of "deriving" slightly smarter, by ignoring data constructor arguments that are identical to the lhs. Now handles things like data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving ... - - - - - 37588686 by Mike Thomas at 2004-05-21T06:38:14+00:00 [haddock @ 2004-05-21 06:38:14 by mthomas] Windows exe extensions (bin remains for Unix). - - - - - cf2b9152 by Simon Marlow at 2004-05-25T09:34:54+00:00 [haddock @ 2004-05-25 09:34:54 by simonmar] Add some TODO items - - - - - 4d29cdfc by Simon Marlow at 2004-05-25T10:41:46+00:00 [haddock @ 2004-05-25 10:41:46 by simonmar] Complain if -h is used with --gen-index or --gen-contents, because it'll overwrite the new index/contents. - - - - - 2e0771e0 by Mike Thomas at 2004-05-28T20:17:55+00:00 [haddock @ 2004-05-28 20:17:55 by mthomas] Windows: search for templates in executable directory. Unix: Haddock tries cwd first rather than error if no -l arg. - - - - - 8d10bde1 by Sven Panne at 2004-06-05T16:53:34+00:00 [haddock @ 2004-06-05 16:53:34 by panne] Misc. rpm spec file cleanup, including: * make BuildRoot handling more consistent * added default file attributes * consistent defines and tags - - - - - 59974349 by Sven Panne at 2004-06-05T18:01:00+00:00 [haddock @ 2004-06-05 18:01:00 by panne] More rpm spec file cleanup, including: * added some BuildRequires * changed packager to me, so people can complain at the right place :-] * consistently refer to haskell.org instead of www.haskell.org - - - - - b94d4903 by Simon Marlow at 2004-07-01T11:08:58+00:00 [haddock @ 2004-07-01 11:08:57 by simonmar] Update to the +/- buttons: use a resized image rather than a <button>. Still seeing some strange effects in Konqueror, so might need to use a fixed-size image instead. - - - - - d5278f67 by Sven Panne at 2004-07-04T15:15:55+00:00 [haddock @ 2004-07-04 15:15:55 by panne] Install pictures for +/- pictures, too (JPEG is a strange format for graphics like this, I would have expected GIF or PNG here.) Things look fine with Konqueror and Netscape on Linux now, the only downside is that the cursor doesn't change when positioned above the "button". - - - - - 46dec6c5 by Sven Panne at 2004-07-13T17:59:28+00:00 [haddock @ 2004-07-13 17:59:28 by panne] A quote is a valid part of a Haskell identifier, but it would interfere with an ECMA script string delimiter, so escape it there. - - - - - 1d7bc432 by Simon Marlow at 2004-07-22T08:54:06+00:00 [haddock @ 2004-07-22 08:54:06 by simonmar] Add single quote to $ident, so you can say eg. 'foldl'' to refer to foldl' (the longest match rule is our friend). Bug reported by Adrian Hey <ahey at iee.org> - - - - - f183618b by Krasimir Angelov at 2004-07-27T22:59:35+00:00 [haddock @ 2004-07-27 22:58:23 by krasimir] Add basic support for Microsoft HTML Help 2.0 - - - - - d515d0c2 by Krasimir Angelov at 2004-07-27T23:02:36+00:00 [haddock @ 2004-07-27 23:02:36 by krasimir] escape names in the index - - - - - a5f1be23 by Krasimir Angelov at 2004-07-27T23:05:21+00:00 [haddock @ 2004-07-27 23:05:21 by krasimir] Add jsFile, plusFile and minusFile to the file list - - - - - c4fb4881 by Krasimir Angelov at 2004-07-28T22:12:10+00:00 [haddock @ 2004-07-28 22:12:09 by krasimir] bugfix. Move contentsHtmlFile, indexHtmlFile and subIndexHtmlFile functions to HaddockUtil.hs module to make them accessible from HaddockHH2.hs - - - - - 64d30b1d by Krasimir Angelov at 2004-07-30T22:15:47+00:00 [haddock @ 2004-07-30 22:15:45 by krasimir] more stuffs - support for separated compilation of packages - the contents page now uses DHTML TreeView - fixed copyFile bug - - - - - 133c8c5c by Krasimir Angelov at 2004-07-31T12:04:38+00:00 [haddock @ 2004-07-31 12:04:37 by krasimir] make the DHtmlTree in contents page more portable. The +/- buttons are replaced with new images which looks more beatiful. - - - - - 79040963 by Krasimir Angelov at 2004-07-31T13:10:20+00:00 [haddock @ 2004-07-31 13:10:20 by krasimir] Make DHtmlTree compatible with Mozila browser - - - - - 1a55dc90 by Krasimir Angelov at 2004-07-31T14:52:55+00:00 [haddock @ 2004-07-31 14:52:55 by krasimir] fix - - - - - 85ce0237 by Krasimir Angelov at 2004-07-31T14:53:28+00:00 [haddock @ 2004-07-31 14:53:28 by krasimir] HtmlHelp 1.x - - - - - 3c0c53ba by Krasimir Angelov at 2004-07-31T20:35:21+00:00 [haddock @ 2004-07-31 20:35:21 by krasimir] Added support for DevHelp - - - - - d42b5af1 by Krasimir Angelov at 2004-07-31T21:17:51+00:00 [haddock @ 2004-07-31 21:17:51 by krasimir] Document new features in HtmlHelp - - - - - 790fe21e by Krasimir Angelov at 2004-08-01T15:14:02+00:00 [haddock @ 2004-08-01 15:14:02 by krasimir] add missing imports - - - - - fd7cc6bc by Krasimir Angelov at 2004-08-01T19:52:08+00:00 [haddock @ 2004-08-01 19:52:06 by krasimir] fix some bugs. Now I have got the entire libraries documentation in HtmlHelp 2.0 format. - - - - - 94ad7ac8 by Krasimir Angelov at 2004-08-01T19:53:50+00:00 [haddock @ 2004-08-01 19:53:50 by krasimir] I forgot to add the new +/- images - - - - - f0c65388 by Krasimir Angelov at 2004-08-02T16:25:53+00:00 [haddock @ 2004-08-02 16:25:53 by krasimir] Add root node to the table of contents. All modules in tree are not children of the root - - - - - f50bd85d by Sven Panne at 2004-08-02T18:17:46+00:00 [haddock @ 2004-08-02 18:17:46 by panne] Mainly DocBook fixes - - - - - 09527ce3 by Sven Panne at 2004-08-02T20:02:29+00:00 [haddock @ 2004-08-02 20:02:29 by panne] Fixed -o/--odir handling. Generating the output, especially the directory handling, is getting a bit convoluted nowadays... - - - - - c8fbacfa by Sven Panne at 2004-08-02T20:31:13+00:00 [haddock @ 2004-08-02 20:31:13 by panne] Warning police - - - - - 37830bff by Sven Panne at 2004-08-02T20:32:29+00:00 [haddock @ 2004-08-02 20:32:28 by panne] Nuked dead code - - - - - 13847171 by Sven Panne at 2004-08-02T21:12:27+00:00 [haddock @ 2004-08-02 21:12:25 by panne] Use pathJoin instead of low-level list-based manipulation for FilePaths - - - - - c711d61e by Sven Panne at 2004-08-02T21:16:02+00:00 [haddock @ 2004-08-02 21:16:02 by panne] Removed WinDoze CRs - - - - - b1f7dc88 by Sven Panne at 2004-08-03T19:35:59+00:00 [haddock @ 2004-08-03 19:35:59 by panne] Fixed spelling of "http-equiv" attribute - - - - - dd5f394e by Sven Panne at 2004-08-03T19:44:03+00:00 [haddock @ 2004-08-03 19:44:03 by panne] Pacify W3C validator: * Added document encoding (currently UTF-8, not sure if this is completely correct) * Fixed syntax of `id' attributes * Added necessary `alt' attribute for +/- images Small layout improvement: * Added space after +/- images (still not perfect, but better than before) - - - - - 919c47c6 by Sigbjorn Finne at 2004-08-03T19:45:11+00:00 [haddock @ 2004-08-03 19:45:11 by sof] make it compile with <= ghc-6.1 - - - - - 4d6f01d8 by Sigbjorn Finne at 2004-08-03T19:45:30+00:00 [haddock @ 2004-08-03 19:45:30 by sof] ffi wibble - - - - - 4770643a by Sven Panne at 2004-08-03T20:47:46+00:00 [haddock @ 2004-08-03 20:47:46 by panne] Fixed CSS for button style. Note that only "0" is a valid measure without a unit! - - - - - 14aaf2e5 by Sven Panne at 2004-08-03T21:07:59+00:00 [haddock @ 2004-08-03 21:07:58 by panne] Improved spacing of dynamic module tree - - - - - 97c3579a by Simon Marlow at 2004-08-09T11:03:04+00:00 [haddock @ 2004-08-09 11:03:04 by simonmar] Add FormatVersion Patch submitted by: George Russell <ger at informatik.uni-bremen.de> - - - - - af7f8c03 by Simon Marlow at 2004-08-09T11:55:07+00:00 [haddock @ 2004-08-09 11:55:05 by simonmar] Add support for a short description for each module, which is included in the contents. The short description should be given in a "Description: " field of the header. Included in this patch are changes that make the format of the header a little more flexible. From the comments: -- all fields in the header are optional and have the form -- -- [spaces1][field name][spaces] ":" -- [text]"\n" ([spaces2][space][text]"\n" | [spaces]"\n")* -- where each [spaces2] should have [spaces1] as a prefix. -- -- Thus for the key "Description", -- -- > Description : this is a -- > rather long -- > -- > description -- > -- > The module comment starts here -- -- the value will be "this is a .. description" and the rest will begin -- at "The module comment". The header fields must be in the following order: Module, Description, Copyright, License, Maintainer, Stability, Portability. Patches submitted by: George Russell <ger at informatik.uni-bremen.de>, with a few small changes be me, mostly to merge with other recent changes. ToDo: document the module header. - - - - - 7b865ad3 by Simon Marlow at 2004-08-10T14:09:57+00:00 [haddock @ 2004-08-10 14:09:57 by simonmar] Fixes for DevHelp/HtmlHelp following introduction of short module description. - - - - - 814766cd by Simon Marlow at 2004-08-10T14:33:46+00:00 [haddock @ 2004-08-10 14:33:45 by simonmar] Fixes to installation under Windows. - - - - - 39cf9ede by Simon Marlow at 2004-08-12T12:08:23+00:00 [haddock @ 2004-08-12 12:08:23 by simonmar] Avoid using string-gap tricks. - - - - - b6d78551 by Simon Marlow at 2004-08-13T10:53:21+00:00 [haddock @ 2004-08-13 10:53:21 by simonmar] Update - - - - - eaae7417 by Simon Marlow at 2004-08-13T10:53:50+00:00 [haddock @ 2004-08-13 10:53:50 by simonmar] Test for primes in quoted links - - - - - 68c34f06 by Sven Panne at 2004-08-16T19:59:38+00:00 [haddock @ 2004-08-16 19:59:36 by panne] XMLification - - - - - 7f45a6f9 by Sven Panne at 2004-08-18T16:42:54+00:00 [haddock @ 2004-08-18 16:42:54 by panne] Re-added indices + minor fixes - - - - - 8a5dd97c by Sigbjorn Finne at 2004-08-25T17:15:42+00:00 [haddock @ 2004-08-25 17:15:42 by sof] backquote HADDOCK_VERSION defn for <= ghc-6.0.x; believe this is only needed under mingw - - - - - 4b1b42ea by Sven Panne at 2004-08-26T20:08:50+00:00 [haddock @ 2004-08-26 20:08:49 by panne] SGML is dead, long live DocBook XML! Note: The BuildRequires tags in the spec files are still incomplete and the documentation about the DocBook tools needs to be updated, too. Stay tuned... - - - - - 8d52cedb by Sven Panne at 2004-08-26T21:03:19+00:00 [haddock @ 2004-08-26 21:03:19 by panne] Updated BuildRequires tags. Alas, there seems to be no real standard here, so your mileage may vary... At least the current specs should work on SuSE Linux. - - - - - e6982912 by Sigbjorn Finne at 2004-08-30T15:44:59+00:00 [haddock @ 2004-08-30 15:44:59 by sof] escape HADDOCK_VERSION double quotes on all platforms when compiling with <=6.0.x - - - - - b3fbc867 by Simon Marlow at 2004-08-31T13:09:42+00:00 [haddock @ 2004-08-31 13:09:42 by simonmar] Avoid GHC/shell versionitis and create Version.hs - - - - - c359e16a by Sven Panne at 2004-09-05T19:12:33+00:00 [haddock @ 2004-09-05 19:12:32 by panne] * HTML documentation for "foo.xml" goes into directory "foo" again, not "foo-html". This is nicer and consistent with the behaviour for building the docs from SGML. * Disabled building PostScript documentation in the spec files for now, there are some strange issues with the FO->PS conversion for some files which have to be clarified first. - - - - - c68b1eba by Sven Panne at 2004-09-24T07:04:38+00:00 [haddock @ 2004-09-24 07:04:38 by panne] Switched the default state for instances and the module hierarchy to non-collapsed. This can be reversed when we finally use cookies from JavaScript to have a more persistent state. Previously going back and forth in the documentation was simply too annoying because everything was collapsed again and therefore the documentation was not easily navigatable. - - - - - dfb32615 by Simon Marlow at 2004-09-30T08:21:29+00:00 [haddock @ 2004-09-30 08:21:29 by simonmar] Add a feature request - - - - - 45ff783c by Sven Panne at 2004-10-23T19:54:00+00:00 [haddock @ 2004-10-23 19:54:00 by panne] Improved the Cygwin/MinGW chaos a little bit. There is still confusion about host platform vs. target platform... - - - - - 5f644714 by Krasimir Angelov at 2004-10-28T16:01:51+00:00 [haddock @ 2004-10-28 16:01:51 by krasimir] update for ghc-6.3+ - - - - - 92d9753e by Sven Panne at 2004-11-01T16:39:01+00:00 [haddock @ 2004-11-01 16:39:01 by panne] Revert previous commit: It's Network.URI which should be changed, not Haddock. - - - - - 05f70f6e by Simon Marlow at 2005-01-04T16:15:51+00:00 [haddock @ 2005-01-04 16:15:51 by simonmar] parser fix: allow qualified specialids. - - - - - 47870837 by Simon Marlow at 2005-01-04T16:16:54+00:00 [haddock @ 2005-01-04 16:16:54 by simonmar] Add a test - - - - - ff11fc2c by Ross Paterson at 2005-01-10T19:18:22+00:00 [haddock @ 2005-01-10 19:18:22 by ross] Render non-ASCII characters using numeric character references, to simplify charset issues. There's a META tag saying the charset is UTF-8, but GHC outputs characters as raw bytes. Ideally we need an encoding on the input side too, primarily in comments, because source files containing non-ASCII characters aren't portable between locales. - - - - - eba2fc4e by Simon Marlow at 2005-01-11T10:44:37+00:00 [haddock @ 2005-01-11 10:44:37 by simonmar] Remove string gap - - - - - b899a381 by Ross Paterson at 2005-01-13T11:41:33+00:00 [haddock @ 2005-01-13 11:41:33 by ross] recognize SGML-style numeric character references &#ddd; or &#xhhhh; and translate them into Chars. - - - - - 106e3cf0 by Ross Paterson at 2005-01-13T14:43:41+00:00 [haddock @ 2005-01-13 14:43:41 by ross] also allow uppercase X in hexadecimal character references (like SGML) - - - - - e8f54f25 by Ross Paterson at 2005-01-13T14:44:24+00:00 [haddock @ 2005-01-13 14:44:24 by ross] Describe numeric character references. - - - - - 914ccdce by Sven Panne at 2005-01-15T18:44:48+00:00 [haddock @ 2005-01-15 18:44:45 by panne] Make Haddock compile again after the recent base package changed. The Map/Set legacy hell has been factored out, so that all modules can simply use the new non-deprecated interfaces. Probably a lot of things can be improved by a little bit of Map/Set/List algebra, this can be done later if needed. Small note: Currently the list of instances in HTML code is reversed. This will hopefully be fixed later. - - - - - 6ab20e84 by Sven Panne at 2005-01-16T12:18:26+00:00 [haddock @ 2005-01-16 12:18:26 by panne] Trim imports - - - - - efb81da9 by Sven Panne at 2005-01-16T12:58:08+00:00 [haddock @ 2005-01-16 12:58:03 by panne] Correctly handle the new order of arguments for the combining function given to fromListWith. - - - - - e27b5834 by Sven Panne at 2005-01-16T14:14:41+00:00 [haddock @ 2005-01-16 14:14:39 by panne] Data.Map.unions is left-biased. - - - - - dae3cc3e by Sven Panne at 2005-01-16T14:22:44+00:00 [haddock @ 2005-01-16 14:22:44 by panne] Added the last missing "flip" to get identical HTML output as previous versions. - - - - - 951d8408 by Sven Panne at 2005-01-16T14:37:10+00:00 [haddock @ 2005-01-16 14:37:10 by panne] Refactored Text.PrettyPrint legacy hell into a separate module. - - - - - f1c4b892 by Sven Panne at 2005-01-16T15:41:25+00:00 [haddock @ 2005-01-16 15:41:21 by panne] Cleaned up imports and dropped support for GHC < 5.03, it never worked, anyway. - - - - - 60824c6e by Simon Marlow at 2005-01-18T10:02:48+00:00 [haddock @ 2005-01-18 10:02:48 by simonmar] Add a TODO - - - - - a8c82f23 by Krasimir Angelov at 2005-01-28T23:19:39+00:00 [haddock @ 2005-01-28 23:19:39 by krasimir] import Foreign/Foreign.C are required for Windows - - - - - d8450a23 by Simon Marlow at 2005-02-02T16:23:04+00:00 [haddock @ 2005-02-02 16:23:00 by simonmar] Revamp the linking strategy in Haddock. Now name resolution is done in two phases: - first resolve everything to original names, like a Haskell compiler would. - then, figure out the "home" location for every entity, and point all the links to there. The home location is the lowest non-hidden module in the import hierarchy that documents the entity. If there are multiple candidates, one is chosen at random. Also: - Haddock should not generate any HTML with dangling links any more. Unlinked references are just rendered as plain text. - Error reporting is better: if we can't find a link destination for an entity reference, we now emit a warning. - - - - - 1cce71d0 by Simon Marlow at 2005-02-03T13:42:19+00:00 [haddock @ 2005-02-03 13:42:19 by simonmar] - add --ignore-all-exports flag, which behaves as if every module has the ignore-exports attribute (requested by Chris Ryder). - add --hide option to hide a module on the command line. - add --use-package option to get Haddock info for a package from ghc-pkg (largely untested). - remove reexports from the .haddock file, they aren't used any more. - - - - - 767123ef by Ross Paterson at 2005-02-03T16:17:37+00:00 [haddock @ 2005-02-03 16:17:37 by ross] fix typo for < 6.3 - - - - - 0c680c04 by Simon Marlow at 2005-02-04T12:03:31+00:00 [haddock @ 2005-02-04 12:03:31 by simonmar] Fix bug in renameExportItems that meant links in instances weren't being renamed properly. - - - - - ff7abe5f by Simon Marlow at 2005-02-04T12:15:53+00:00 [haddock @ 2005-02-04 12:15:52 by simonmar] Add attribute #not-home, to indicate that the current module should not be considered to be a home module for the each entity it exports, unless there is no other module that exports the entity. - - - - - fc2cfd27 by Simon Marlow at 2005-02-04T12:40:02+00:00 [haddock @ 2005-02-04 12:40:02 by simonmar] Update the documentation w.r.t. home modules and the not-home attribute. - - - - - 26b8ddf7 by Ross Paterson at 2005-02-04T13:36:06+00:00 [haddock @ 2005-02-04 13:36:05 by ross] sort lists of instances by - arity of the type constructors (so higher-kinded instances come first) - name of the class - argument types - - - - - 26bfb19c by Simon Marlow at 2005-02-23T15:57:12+00:00 [haddock @ 2005-02-23 15:57:12 by simonmar] Fix documentation regarding the module attributes. - - - - - 9c3afd02 by Simon Marlow at 2005-02-28T16:18:17+00:00 [haddock @ 2005-02-28 16:18:17 by simonmar] version 0.7 - - - - - a95fd63f by Simon Marlow at 2005-02-28T16:22:08+00:00 [haddock @ 2005-02-28 16:22:08 by simonmar] Attempt to fix the layout of the package names in the contents. Having tried just about everything, the only thing I can get to work reliably is to make the package names line up on a fixed offset from the left margin. This obviously isn't ideal, so anyone else that would like to have a go at improving it is welcome. One option is to remove the +/- buttons from the contents list and go back to a plain table. The contents page now uses CSS for layout rather than tables. It seems that most browsers have different interpretations of CSS layout, so only the simplest things lead to consistent results. - - - - - 905d42f7 by Simon Marlow at 2005-03-01T17:16:42+00:00 [haddock @ 2005-03-01 17:16:40 by simonmar] Another attempt at lining up the package names on the contents page. Now, they line up with Konqueror, and almost line up with Firefox & IE (different layout in each case). - - - - - a0e1d178 by Wolfgang Thaller at 2005-03-09T08:28:39+00:00 [haddock @ 2005-03-09 08:28:39 by wolfgang] Hack haddock's lexer to accept the output from Apple's broken version of cpp (Apple's cpp leaves #pragma set_debug_pwd directives in it's output). - - - - - 9e1eb784 by Simon Marlow at 2005-04-22T14:27:15+00:00 [haddock @ 2005-04-22 14:27:15 by simonmar] Add a TODO item - - - - - 23281f78 by Ross Paterson at 2005-05-18T12:41:59+00:00 [haddock @ 2005-05-18 12:41:59 by ross] fix 3 bugs in --use-package, and document it. - - - - - 00074a68 by Sven Panne at 2005-05-21T12:35:29+00:00 [haddock @ 2005-05-21 12:35:29 by panne] Warning/versionitis police - - - - - 341fa822 by Simon Marlow at 2005-06-15T15:43:21+00:00 [haddock @ 2005-06-15 15:43:21 by simonmar] Allow "licence" as an alternate spelling of "license" - - - - - 3b953f8b by Simon Marlow at 2005-06-16T08:14:12+00:00 [haddock @ 2005-06-16 08:14:12 by simonmar] wibble - - - - - abfd9826 by Simon Marlow at 2005-06-27T14:46:40+00:00 [haddock @ 2005-06-27 14:46:40 by simonmar] name hierarchical HTML files as A-B-C.html instead of A.B.C.html. The old way confused Apache because the extensions are sometimes interpreted as having special meanings. - - - - - a01eea00 by Simon Marlow at 2005-08-04T13:59:40+00:00 [haddock @ 2005-08-04 13:59:40 by simonmar] 0.7 changes - - - - - 170ef87e by Simon Marlow at 2005-08-04T15:08:03+00:00 [haddock @ 2005-08-04 15:08:03 by simonmar] spec file from Jens Peterson - - - - - 7621fde4 by Simon Marlow at 2005-08-04T15:59:30+00:00 [haddock @ 2005-08-04 15:59:30 by simonmar] replace mingw tests with $(Windows) - - - - - a20739bb by Sven Panne at 2005-08-05T07:01:12+00:00 [haddock @ 2005-08-05 07:01:12 by panne] Reverted to previous version (but with bumped version number), the last commit broke RPM building on SuSE systems due to differently named dependencies. As a clarification: All .spec files in the repository have to work at least on SuSE, because that's the system I'm using. And as "Mr. Building Police", I reserve me the right to keep them that way... >:-) It might very well be the case that we need different .spec files for different platforms, so packagers which are unhappy with the current .spec files should contact me, stating the actual problems. - - - - - 4afb15cf by Simon Marlow at 2005-10-05T10:51:45+00:00 [haddock @ 2005-10-05 10:51:45 by simonmar] Add a bug - - - - - 60f69f82 by Simon Marlow at 2005-10-05T12:52:03+00:00 [haddock @ 2005-10-05 12:52:03 by simonmar] Document new behaviour of -s option - - - - - f7e520ca by Simon Marlow at 2005-10-10T15:02:55+00:00 [haddock @ 2005-10-10 15:02:55 by simonmar] extractRecSel: ignore non-record constructors (fixes a crash when using datatypes with a mixture of record and non-record style constructors). - - - - - b2edbedb by Simon Marlow at 2005-10-14T09:44:21+00:00 Start CHANGES for 0.8 - - - - - 21c7ac8d by Simon Marlow at 2005-10-14T23:11:19+00:00 First cut of Cabal build system - - - - - 766cecdd by Simon Marlow at 2005-10-29T08:14:43+00:00 Add configure script and Makefile for the docs Add a separate configure script and build system for building the documentation. The configure and Makefile code is stolen from fptools. This is left as a separate build system so that the main Cabal setup doesn't require a Unix build environment or DocBook XML tools. - - - - - aa36c783 by Duncan Coutts at 2006-01-17T19:29:55+00:00 Add a --wiki=URL flag to add a per-module link to a correspondng wiki page. So each html page gets an extra link (placed next to the source code and contents links) to a corresponding wiki page. The idea is to let readers contribute their own notes, examples etc to the documentation. Also slightly tidy up the code for the --source option. - - - - - e06e2da2 by Simon Marlow at 2006-01-18T09:28:15+00:00 TODO: documnet --wiki - - - - - 17adfda9 by Duncan Coutts at 2006-01-19T20:17:59+00:00 Add an optional wiki link for each top level exported name. In each module, for each "top level" exported entity we add a hyper link to a corresponding wiki page. The link url gets the name of the exported entity as a '#'-style anchor, so if there is an anchor in the page with that name then the users browser should jump directly to it. By "top level" we mean functions, classes, class members and data types (data, type, newtype), but not data constructors, class instances or data type class membership. The link is added at the right of the page and in a small font. Hopefully this is the right balance of visibility/distraction. We also include a link to the wiki base url in the contents and index pages. - - - - - f52324bb by Duncan Coutts at 2006-01-19T20:28:27+00:00 Rewrite pathJoin to only add a path separator when necessary. When the path ends in a file seperator there is no need to add another. Now using "--wiki=http://blah.com/foo/" should do the right thing. (Code snippet adapted from Isaac's FilePath package.) - - - - - 43bb89fa by Duncan Coutts at 2006-01-21T17:15:27+00:00 Teach haddock about line pragmas and add accurate source code links Teach haddock about C and Haskell style line pragmas. Extend the lexer/parser's source location tracking to include the file name as well as line/column. This way each AST item that is tagged with a SrcLoc gets the original file name too. Use this original file name to add source links to each exported item, in the same visual style as the wiki links. Note that the per-export source links are to the defining module rather than whichever module haddock pretends it is exported from. This is what we want for source code links. The source code link URL can also contain the name of the export so one could implement jumping to the actual location of the function in the file if it were linked to an html version of the source rather than just plain text. The name can be selected with the %N wild card. So for linking to the raw source code one might use: --source=http://darcs/haskell.org/foo/%F Or for linking to html syntax highlighted code: --source=http://darcs/haskell.org/foo/%M.html#%N - - - - - edd9f229 by Duncan Coutts at 2006-01-22T00:02:00+00:00 Extend URL variable expansion syntax and add source links to the contents page Like the wiki link on the contents and index page, add a source code link too. Extend the wiki & source URL variable expansion syntax. The original syntax was: %F for the source file name (the .hs version only, not the .lhs or .hs.pp one) %M for the module name (with '.' replaced by '/') The new syntax is: %F or %{FILE} for the original source file name %M or %{MODULE} for the module name (no replacements) %N or %{NAME} for the function/type export name %K or %{KIND} for a type/value flag "t" or "v" with these extensions: %{MODULE/./c} to replace the '.' module seperator with any other char c %{VAR|some text with the % char in it} which means if the VAR is not in use in this URL context then "" else replace the given text with the '%' char replaced by the string value of the VAR. This extension allows us to construct URLs wit optional parts, since the module/file name is not available for the URL in the contents/index pages and the value/type name is not available for the URL at the top level of each module. - - - - - eb3c6ada by Duncan Coutts at 2006-01-23T13:42:34+00:00 Remove the complex substitutions and add more command line flags instead. Instead of incomprehensable URL substitutions like ${MODULE/./-|?m=%} we now use three seperate command line flags for the top level, per-module and per-entity source and wiki links. They are: --source-base, --source-module, --source-entity --comments-base, --comments-module, --comments-entity We leave -s, --source as an alias for --source-module which is how that option behaved previously. The long forms of the substitutions are still available, ${FILE} ${MODULE} etc and the only non-trivial substitution is ${MODULE/./c} to replace the '.' characters in the module name with any other character c. eg ${MODULE/./-} Seperating the source and wiki url flags has the added bonus that they can be turned on or off individually. So users can have per-module links for example without having to also have per-entity links.` - - - - - a2f0f2af by Duncan Coutts at 2006-01-23T13:54:52+00:00 Make the --help output fit in 80 columns. This is a purely cosmetic patch, feel free to ignore it. The only trickery going on is that we don't display the deprecated -s, --source flags in the help message, but we do still accept them. - - - - - 2d3a4b0c by Duncan Coutts at 2006-01-23T14:12:16+00:00 Add documentation for the new --source-* and --comments-* command line options - - - - - 1a82a297 by Simon Marlow at 2006-01-23T17:03:27+00:00 fix markup - - - - - 100d464a by Duncan Coutts at 2006-01-23T18:31:13+00:00 remove a couple TODO items that have been done The --wiki, or rather the --comment-* options are now documented. There is probably no need to have haddock invoke unlit or cpp itself since it can now pick up the line pragmas to get the source locations right. Tools like Cabal will arrange for preprocessors to be run so there is less of a need for tools like haddock to do it themselves. - - - - - 3162fa91 by Simon Marlow at 2006-01-24T14:21:56+00:00 add a test I had lying around - - - - - 98947063 by Simon Marlow at 2006-01-31T13:52:54+00:00 add scabal-version field - - - - - c41876e6 by Neil Mitchell at 2006-02-26T17:48:21+00:00 Add Hoogle output option - - - - - f86fb9c0 by Simon Marlow at 2006-03-08T09:15:20+00:00 add haskell.vim Contributed by Brad Bowman <bsb at bereft.net>, thanks! - - - - - 35d3c511 by benjamin.franksen at 2006-03-03T22:39:54+00:00 fixed libdir (/html was missing) - - - - - 4d08fd7d by Simon Marlow at 2006-03-10T11:13:31+00:00 add PatternGuards extension - - - - - 3f095e70 by Simon Marlow at 2006-03-13T11:40:42+00:00 bug fixes from Brad Bowman - - - - - 8610849d by Sven Panne at 2006-03-19T17:02:56+00:00 Fixed Cabal/RPM build - - - - - 34a994d6 by sven.panne at 2006-04-20T12:39:23+00:00 Avoid pattern guards Due to the use of pattern guards in Haddock, GHC was called with -fglasgow-exts. This in turn enables bang patterns, too, which broke the Haddock build. Removing some unnecessary pattern guards seemed to be the better way of fixing this instead of using a pragma to disable pattern guards. - - - - - bb523f51 by Ross Paterson at 2006-04-24T09:03:25+00:00 extend 'deriving' heuristic a little If an argument of a data constructor has a type variable head, it is irreducible and the same type class can be copied into the constraint. (Formerly we just did this for type variable arguments.) - - - - - dab9fe7a by Simon Marlow at 2006-04-26T10:02:31+00:00 record an idea - - - - - 748b7078 by Simon Marlow at 2006-05-08T08:28:53+00:00 add section about deriving - - - - - 11252ea1 by Simon Marlow at 2006-05-24T15:43:10+00:00 replace a fatal error in lexChar with a parseError - - - - - 382c9411 by Simon Marlow at 2006-05-24T15:45:47+00:00 add a bug - - - - - b79272f5 by Simon Marlow at 2006-05-24T15:46:29+00:00 add a bug report - - - - - 912edf65 by David Waern at 2006-07-10T19:09:23+00:00 Initial modifications -- doesn't compile - - - - - a3c7ba99 by David Waern at 2006-07-11T00:54:19+00:00 More porting work -- doesn't compile - - - - - 0a173d19 by David Waern at 2006-07-11T11:30:03+00:00 Make the repos temporarily compile and illustrate a problem - - - - - bad316de by David Waern at 2006-07-11T15:43:47+00:00 Progress on the porting process - - - - - bbf12d02 by David Waern at 2006-07-11T23:07:44+00:00 More progress on the porting -- first pass starting to shape up - - - - - de580ba2 by David Waern at 2006-07-20T17:48:30+00:00 More progress -- still on phase1 - - - - - 75a917a2 by David Waern at 2006-07-23T18:22:43+00:00 More work on pass1 -- mostly done - - - - - 6697b3f7 by David Waern at 2006-07-23T22:17:40+00:00 More work, started working on the renaming phase -- this code will need a cleanup soon :) - - - - - 82a5bcbb by David Waern at 2006-07-29T16:16:43+00:00 Add instances, build renaming environment, start on the renamer - - - - - c3f8f4f1 by David Waern at 2006-07-29T21:37:48+00:00 Complete the renamer - - - - - 7e00d464 by David Waern at 2006-07-30T21:01:57+00:00 Start porting the Html renderer - - - - - f04ce121 by David Waern at 2006-08-09T20:04:56+00:00 More Html rendering progress - - - - - 20c21b53 by David Waern at 2006-08-10T17:37:47+00:00 More progress - - - - - d7097e0d by David Waern at 2006-08-11T20:31:51+00:00 Cleanup - - - - - a7351e86 by David Waern at 2006-08-12T11:44:47+00:00 Render H98 Data declarations - - - - - 3fb2208e by David Waern at 2006-08-12T17:15:34+00:00 Perfect rendering of Test.hs - - - - - 454fd062 by David Waern at 2006-08-13T21:57:08+00:00 Misc fixes and interface load/save - - - - - 7ef7e7be by David Waern at 2006-08-14T00:56:07+00:00 Some refactoring - - - - - a7d3efef by David Waern at 2006-08-19T20:07:55+00:00 Adapt to latest GHC - - - - - 5fc3c0d7 by David Waern at 2006-08-20T21:28:11+00:00 Move interface read/write to its own module + some cleanup - - - - - 037e011c by David Waern at 2006-08-20T21:38:24+00:00 Small cleanup - - - - - da3a1023 by David Waern at 2006-09-03T16:05:22+00:00 Change mode to BatchCompile to avoid GHC API bug - - - - - 3cc9be3b by David Waern at 2006-09-03T16:06:59+00:00 Starting work on GADT rendering - - - - - 94506037 by David Waern at 2006-09-03T20:02:48+00:00 Compensate for change of export list order in GHC - - - - - c2cec4eb by David Waern at 2006-09-04T20:53:01+00:00 Rename a function - - - - - 9a9735ba by David Waern at 2006-09-05T15:51:21+00:00 Change version number to 2.0 - - - - - 3758a714 by David Waern at 2006-09-05T15:51:49+00:00 Align comment properly - - - - - 68478d9e by David Waern at 2006-09-15T18:03:00+00:00 Remove interface reading/writing code and use the GHC api for creating package environments instead - - - - - d2eedd95 by David Waern at 2006-09-15T18:05:29+00:00 Change the executable name to haddock-ghc-nolib - - - - - fcfbcf66 by David Waern at 2006-09-15T18:05:45+00:00 Small source code cleanup - - - - - d08eb017 by David Waern at 2006-09-15T18:06:21+00:00 Remove handling of --package flag - - - - - b8a4cf53 by David Waern at 2006-09-15T18:07:16+00:00 Remove commented-out code - - - - - bef0a684 by David Waern at 2006-09-15T18:37:57+00:00 Don't warn about missing links to () - - - - - e7d25fd7 by David Waern at 2006-09-15T19:50:49+00:00 Remove Interface and Binary2 modules - - - - - 9894f2a1 by David Waern at 2006-09-15T19:53:43+00:00 Remove debug printing from HaddockHtml - - - - - a0e7455d by David Waern at 2006-09-16T00:16:29+00:00 Comments only - - - - - d5b26fa7 by David Waern at 2006-09-16T00:16:57+00:00 Refactor PackageData creation code and start on building the doc env propery (unfinished) - - - - - 06aaa779 by David Waern at 2006-09-16T00:19:25+00:00 Better comments in Main.hs - - - - - 1a52d1b4 by David Waern at 2006-09-18T22:17:11+00:00 Comments and spacing change - - - - - e5a97767 by David Waern at 2006-09-21T17:02:45+00:00 Remove unnecessary fmapM import in Main - - - - - 9d0f9d3a by David Waern at 2006-09-22T18:07:07+00:00 Make import list in HaddockHtml prettier - - - - - 3452f662 by David Waern at 2006-09-22T18:08:47+00:00 Refactor context rendering - - - - - 12d0a6d0 by David Waern at 2006-09-22T18:09:52+00:00 Do proper HsType rendering (inser parentheses correctly) - - - - - 2c20c2f9 by David Waern at 2006-09-22T18:10:45+00:00 Fix a bug in Main.toHsType - - - - - c5396443 by David Waern at 2006-09-22T18:11:16+00:00 Skip external package modules sort for now - - - - - 3fb95547 by David Waern at 2006-09-22T20:35:40+00:00 Take away trailin "2" on all previously clashing type names - - - - - 2174755f by David Waern at 2006-09-22T20:51:43+00:00 Remove unused imports in Main - - - - - 1e9f7a39 by David Waern at 2006-09-22T20:52:11+00:00 Fix a comment in Main - - - - - 32d9e028 by David Waern at 2006-10-05T16:40:11+00:00 Merge with changes to ghc HEAD - - - - - 3058c8f5 by David Waern at 2006-10-05T16:41:02+00:00 Comment fixes - - - - - b9c217ec by David Waern at 2006-10-05T16:49:59+00:00 Filter out more builtin type constructors from warning messages - - - - - 67e7d252 by David Waern at 2006-10-05T19:38:22+00:00 Refactoring -- better structured pass1 - - - - - cd21c0c1 by David Waern at 2006-10-05T19:44:42+00:00 Remove read/dump interface flags - - - - - 313f9e69 by David Waern at 2006-10-05T19:49:26+00:00 Remove unused pretty printing - - - - - 480f09d1 by David Waern at 2006-12-28T13:22:24+00:00 Update to build with latest GHC HEAD - - - - - 63dccfcb by David Waern at 2007-01-05T01:38:45+00:00 Fixed a bug so that --ghc-flag works correctly - - - - - 3117dadc by David Waern at 2006-12-29T18:53:39+00:00 Automatically get the GHC lib dir - - - - - 9dc84a5c by David Waern at 2006-12-29T19:58:53+00:00 Comments - - - - - 0b0237cc by David Waern at 2007-01-05T16:48:30+00:00 Collect docs based on SrcLoc, syncing with removal of DeclEntity from GHC - - - - - a962c256 by David Waern at 2007-01-05T17:02:47+00:00 Add tabs in haddock.cabal - - - - - 0ca30c97 by David Waern at 2007-01-05T17:04:11+00:00 Add GHCUtils.hs - - - - - c0ab9abe by David Waern at 2007-01-10T11:43:08+00:00 Change package name to haddock-ghc, version 0.1 - - - - - 38e18b27 by David Waern at 2007-01-12T12:03:52+00:00 No binder name for foreign exports - - - - - d18587ab by David Waern at 2007-01-12T12:08:15+00:00 Temp record - - - - - ba6251a0 by David Waern at 2007-01-12T18:27:55+00:00 Remove read/dump-interface (again) - - - - - f4ba2b39 by David Waern at 2007-01-12T18:31:36+00:00 Remove DocOption, use the GHC type - - - - - 511be8bd by David Waern at 2007-01-12T18:32:41+00:00 Use exceptions instead of Either when loading package info - - - - - 0f2144d8 by David Waern at 2007-01-12T18:33:23+00:00 Small type change - - - - - 77507eb7 by David Waern at 2007-01-12T18:33:59+00:00 Remove interface file read/write - - - - - 0ea1e14f by David Waern at 2007-01-17T21:40:26+00:00 Add trace_ppr to GHCUtils - - - - - 3878b493 by David Waern at 2007-01-17T21:40:53+00:00 Sort external package modules and build a doc env - - - - - 8dc323fc by David Waern at 2007-01-17T21:42:41+00:00 Remove comment - - - - - f4c5b097 by David Waern at 2007-01-18T23:22:18+00:00 Add haddock-ghc.cabal and remove ghc option pragma in source file - - - - - da242b2c by David Waern at 2007-01-18T23:22:46+00:00 Remove some tabs - - - - - 288ed096 by David Waern at 2007-01-18T23:39:28+00:00 Moved the defaultErrorHandler to scope only over sortAndCheckModules for now - - - - - 4dd150fe by David Waern at 2007-02-03T21:23:56+00:00 Let restrictCons handle infix constructors - - - - - 97893442 by David Waern at 2007-02-04T16:26:00+00:00 Render infix data constructors - - - - - da89db72 by David Waern at 2007-02-04T16:26:33+00:00 CHange project name to Haddock-GHC - - - - - e93d48af by David Waern at 2007-02-04T16:59:08+00:00 Render infix type constructors properly - - - - - 357bc99b by David Waern at 2007-02-04T17:37:08+00:00 Insert spaces around infix function names - - - - - ab6cfc49 by David Waern at 2007-02-04T17:59:54+00:00 Do not list entities without documentation - - - - - 04249c7e by David Waern at 2007-02-04T19:16:25+00:00 Add GADT support (quite untested) - - - - - 2c223f8d by David Waern at 2007-02-04T19:25:10+00:00 Add package file write/save again! - - - - - b07ed218 by David Waern at 2007-02-04T19:33:02+00:00 Comment out minf_iface based stuff - - - - - 953d1fa7 by David Waern at 2007-02-05T00:12:23+00:00 Solve conflicts - - - - - 593247fc by David Waern at 2007-02-06T19:48:48+00:00 Remove -package flag, GHC's can be used instead - - - - - f658ded2 by David Waern at 2007-02-06T20:50:44+00:00 Start for support of ATs - - - - - 97f9e913 by David Waern at 2007-02-06T20:52:27+00:00 Wibble - - - - - 2ce8e4cf by David Waern at 2007-02-16T12:09:49+00:00 Add the DocOptions change - - - - - dee4a9b5 by David Waern at 2007-03-06T01:24:48+00:00 Wibble - - - - - 7cb99d18 by David Waern at 2007-03-06T01:24:58+00:00 Change version to 2.0 and executable name to haddock - - - - - c5aa02bc by David Waern at 2007-03-08T15:59:49+00:00 Go back to -B flag - - - - - 3a349201 by David Waern at 2007-03-09T13:31:59+00:00 Better exception handling and parsing of GHC flags - - - - - 05a69b71 by David Waern at 2007-03-09T17:45:44+00:00 Remove commented-out DocEntity printing - - - - - 755032cb by davve at dtek.chalmers.se at 2007-03-23T23:30:20+00:00 Remove a file that shouldn't be here - - - - - a7077e5f by davve at dtek.chalmers.se at 2007-03-24T03:58:48+00:00 Remove an import - - - - - 6f55aa8b by davve at dtek.chalmers.se at 2007-03-25T00:46:48+00:00 Start work on Haddock API - - - - - f0199480 by davve at dtek.chalmers.se at 2007-03-25T00:56:36+00:00 Prettify some comments - - - - - f952f9d1 by davve at dtek.chalmers.se at 2007-03-25T00:56:53+00:00 Remove ppr in HaddockTypes - - - - - bc594904 by davve at dtek.chalmers.se at 2007-03-25T00:57:53+00:00 Remove commented out doc env inference - - - - - 11ebf08d by davve at dtek.chalmers.se at 2007-03-25T01:23:25+00:00 De-flatten the namespace - - - - - f696b4bc by davve at dtek.chalmers.se at 2007-03-25T03:21:48+00:00 Add missing stuff to API - - - - - 9a2a04c3 by davve at dtek.chalmers.se at 2007-03-25T03:22:02+00:00 Wibble - - - - - 7d04a6d5 by davve at dtek.chalmers.se at 2007-03-25T03:22:08+00:00 Avoid a GHC bug with parseStaticFlags [] - - - - - 4d2820ba by davve at dtek.chalmers.se at 2007-03-26T04:57:01+00:00 Add fall-through case to mkExportItem - - - - - 6ebc8950 by Stefan O'Rear at 2007-03-26T04:14:53+00:00 Add shebang line to Setup.lhs - - - - - 80966ec5 by davve at dtek.chalmers.se at 2007-03-26T05:24:26+00:00 Fix stupid compile error - - - - - 1ea1385d by davve at dtek.chalmers.se at 2007-04-05T17:19:56+00:00 Do save/read of interface files properly - - - - - 0e4f6541 by David Waern at 2007-04-10T21:08:36+00:00 Add version to ghc dependency - - - - - b0499b63 by David Waern at 2007-04-10T21:37:08+00:00 Change package name to haddock - - - - - 9d50d27e by David Waern at 2007-04-24T00:22:14+00:00 Use filepath package instead of FilePath - - - - - 87c7fcdf by David Waern at 2007-07-10T21:03:04+00:00 Add new package dependencies - - - - - 4768709c by David Waern at 2007-07-11T20:37:11+00:00 Follow changes to record constructor representation - - - - - b9a02fee by Simon Marlow at 2007-05-30T14:00:48+00:00 update to compile with the latest GHC & Cabal - - - - - c0ebdc01 by David Waern at 2007-07-11T21:35:45+00:00 Fix conflicts - - - - - 97f7afd4 by David Waern at 2007-07-11T21:52:38+00:00 Follow changes to the GHC API - - - - - a5b7b58f by David Waern at 2007-07-12T20:36:48+00:00 Call parseStaticFlags before newSession - - - - - f7f50dbc by David Waern at 2007-08-01T21:52:58+00:00 Better indentation in haddock.cabal - - - - - d84e52ad by David Waern at 2007-08-02T00:08:18+00:00 Wibble - - - - - a23f494a by David Waern at 2007-08-02T00:08:24+00:00 Be better at trying to load all module dependencies (debugging) - - - - - ee917f13 by David Waern at 2007-08-03T18:48:08+00:00 Load all targets explicitly (checkModule doesn't chase dependencies anymore) - - - - - 5182d631 by David Waern at 2007-08-16T16:48:55+00:00 Finalize support for links to other packages - - - - - dfd1e3da by David Waern at 2007-08-16T16:51:11+00:00 Fix haddock comment errors in Haddock.Types - - - - - 50c0d83e by David Waern at 2007-08-16T16:51:37+00:00 Remove a debug import - - - - - d84b7c2b by David Waern at 2007-08-16T17:06:30+00:00 Rename PackageData to HaddockPackage - - - - - 3b52cb9f by David Waern at 2007-08-16T17:09:42+00:00 Simplify some comments - - - - - 66fa68d9 by David Waern at 2007-08-16T17:11:38+00:00 Comment the HaddockPackage definition - - - - - 8674c761 by David Waern at 2007-08-16T17:25:54+00:00 Improve code layout in Main - - - - - 571a3a0b by David Waern at 2007-08-16T17:32:13+00:00 Remove explict module imports in Main - - - - - d31b3cb0 by David Waern at 2007-08-16T17:36:23+00:00 Correct comments - - - - - 7f8a9f2b by David Waern at 2007-08-16T17:39:50+00:00 Fix layout problems in Haddock.Types - - - - - 9f421d7f by David Waern at 2007-08-17T11:16:48+00:00 Move options out of Main into Haddock.Options - - - - - 80042b63 by David Waern at 2007-08-17T11:26:59+00:00 Small comment/layout fixes - - - - - b141b982 by David Waern at 2007-08-17T11:28:28+00:00 Change project name from Haddock-GHC to Haddock - - - - - dbeb4a81 by David Waern at 2007-08-17T11:41:05+00:00 Add top module comment to all files - - - - - ce99cc9e by David Waern at 2007-08-17T14:53:04+00:00 Factor out typechecking phase into Haddock.Typecheck - - - - - 6bf75d9e by David Waern at 2007-08-17T16:55:35+00:00 Factor out package code to Haddock.Packages - - - - - b396db37 by David Waern at 2007-08-29T22:40:23+00:00 Major refactoring - - - - - 3d4f95ee by David Waern at 2007-08-29T23:26:24+00:00 Rename HaddockModule to Interface and a few more refactorings - - - - - c55326db by David Waern at 2007-08-29T23:48:03+00:00 Some comment cleanup - - - - - 9a84fc46 by David Waern at 2007-08-29T23:49:29+00:00 Add some modules that I forgot to add earlier - - - - - 4536dce2 by David Waern at 2007-08-29T23:55:24+00:00 Wibble - - - - - 9b7f0206 by David Waern at 2007-08-30T16:03:29+00:00 Wibble - - - - - c52c050a by David Waern at 2007-08-30T16:30:37+00:00 Rename HaddockModule to Interface - - - - - eae2995f by David Waern at 2007-08-30T16:42:59+00:00 Simplify createInterfaces - - - - - 53f99caa by David Waern at 2007-09-29T00:04:31+00:00 Add build-type: Simple to the cabal file - - - - - 0d3103a8 by David Waern at 2007-09-29T00:04:58+00:00 Add containers and array dependency - - - - - 6acf5f30 by David Waern at 2007-09-29T00:13:36+00:00 Prettify the cabal file - - - - - 87c1e378 by David Waern at 2007-09-29T13:16:39+00:00 FIX: consym data headers with more than two variables - - - - - b67fc16a by David Waern at 2007-09-29T14:01:32+00:00 FIX: prefix types used as operators should be quoted - - - - - a8f925bc by David Waern at 2007-09-29T14:02:26+00:00 Use isSymOcc from OccName instead of isConSym - - - - - fc330701 by David Waern at 2007-09-29T14:15:37+00:00 Use isLexConSym/isLexVarSym from OccName - - - - - e4f3dbad by David Waern at 2007-09-29T15:01:08+00:00 FIX: do not quote varsym type operators - - - - - 402207d2 by David Waern at 2007-09-29T15:01:50+00:00 Wibble - - - - - f9d89ef0 by David Waern at 2007-09-29T15:17:40+00:00 Take care when pp tyvars - add parens on syms - - - - - 849e2a77 by David Waern at 2007-10-01T21:56:39+00:00 Go back to using a ModuleMap instead of LookupMod - fixes a bug - - - - - 549dbac6 by David Waern at 2007-10-02T01:05:19+00:00 Improve parsing of doc options - - - - - a36021b8 by David Waern at 2007-10-02T23:05:00+00:00 FIX: double arrows in constructor contexts - - - - - d03bf347 by David Waern at 2007-10-09T16:14:05+00:00 Add a simple test suite - - - - - c252c140 by David Waern at 2007-10-17T16:02:28+00:00 Add --optghc=.. style flag passing to GHC - - - - - cce6c1b3 by David Waern at 2007-10-18T22:03:20+00:00 Add support for --read-interface again - - - - - 33d059c0 by David Waern at 2007-10-18T22:30:18+00:00 Refactoring -- get rid of Haddock.Packages - - - - - f9ed0a4c by David Waern at 2007-10-18T22:34:36+00:00 Name changes - - - - - 8a1c816f by David Waern at 2007-10-20T14:24:23+00:00 Add --ghc-version option - - - - - 4925aaa1 by David Waern at 2007-10-21T14:34:26+00:00 Add some Outputable utils - - - - - 69e7e47f by David Waern at 2007-10-21T14:35:49+00:00 FIX: Ord for OrdName was not comparing modules - - - - - 5a4ae535 by David Waern at 2007-10-21T21:18:48+00:00 Wibble - - - - - 03d48e20 by David Waern at 2007-10-24T15:52:56+00:00 Remove Main from "other modules" - - - - - c66f6d82 by David Waern at 2007-10-24T16:37:18+00:00 Make it possible to run haddock on itself - - - - - 21d156d8 by David Waern at 2007-10-25T14:02:14+00:00 Don't set boot modules as targets - - - - - f8bcf91c by David Waern at 2007-10-31T22:11:17+00:00 Add optimisation flags - - - - - 7ac758f2 by David Waern at 2007-11-04T09:48:28+00:00 Go back to loading only targets (seems to work now) - - - - - 4862aae1 by David Waern at 2007-11-05T22:24:57+00:00 Do full compilation of modules -- temporary fix for GHC API problem - - - - - 697e1517 by David Waern at 2007-11-05T22:25:50+00:00 Don't warn about not being able to link to wired/system/builtin-names - - - - - 892186da by David Waern at 2007-11-06T00:49:21+00:00 Filter out instances with TyCons that are not exported - - - - - 9548314c by David Waern at 2007-11-06T09:37:14+00:00 Wibble - - - - - 5cafd627 by David Waern at 2007-11-08T01:43:07+00:00 Filter out all non-vanilla type sigs - - - - - 04621830 by David Waern at 2007-11-08T01:45:13+00:00 Synch loading of names from .haddock files with GHC's name cache - - - - - 88d37f77 by David Waern at 2007-11-08T01:46:21+00:00 Remove commented-out code - - - - - 6409c911 by David Waern at 2007-11-08T01:56:00+00:00 Small bugfix and cleanup in getDeclFromTyCls - - - - - af59d9c2 by David Waern at 2007-11-08T02:08:44+00:00 Remove OrdName stuff - - - - - 3a615e2e by David Waern at 2007-11-08T02:13:41+00:00 Update runtests.hs following changes to haddock - - - - - 01f3314e by David Waern at 2007-11-08T02:33:01+00:00 Complain if we can't link to wired-in names - - - - - fcafb5d1 by David Waern at 2007-11-09T02:40:16+00:00 Don't exit when there are no file arguments - - - - - 194bc332 by David Waern at 2007-11-09T02:55:37+00:00 Wibble - - - - - dbe4cb55 by David Waern at 2007-11-09T02:56:14+00:00 Wibble - - - - - 82869fda by David Waern at 2007-11-10T17:01:43+00:00 Introduce InstalledInterface structure and add more stuff to the .haddock files We introduce InstalledInterface capturing the part of Interface that is stored in the interface files. We change the ppHtmlContents and ppHtmllIndex to take this structure instead of a partial Interface. We add stuff like the doc map and exported names to the .haddock file (via InstalledInterface). - - - - - d6bb57bf by David Waern at 2007-11-10T17:19:48+00:00 FIX: contents and index should include external package modules when --gen-contents/--gen-index - - - - - e8814716 by David Waern at 2007-11-11T00:29:27+00:00 Remove lDocLinkName and its use in Html backend - - - - - 6f9bd702 by David Waern at 2007-11-11T00:50:57+00:00 Do some refactoring in the html backend This also merges an old patch by Augustsson: Wed Jul 12 19:54:36 CEST 2006 lennart.augustsson at credit-suisse.com * Print type definitions like signatures if given arrows. - - - - - 09d0ce24 by Malcolm.Wallace at 2006-07-20T13:13:57+00:00 mention HsColour in the docs, next to option flags for linking to source code - - - - - 24da6c34 by Malcolm.Wallace at 2006-07-20T13:14:50+00:00 change doc references to CVS to give darcs repository location instead - - - - - 74d52cd6 by David Waern at 2007-11-11T00:55:33+00:00 Update copyright - - - - - fcaa3b4f by Duncan Coutts at 2006-09-08T13:41:00+00:00 Eliminate dep on network by doing a little cut'n'paste haddock depending on the network causes a circular dependency at least if you want to build the network lib with haddock docs. - - - - - 10cc9bda by David Waern at 2007-11-11T02:09:41+00:00 Fix conflicts - - - - - 4e3acd39 by David Waern at 2007-11-11T02:21:19+00:00 Manual merge of a patch from Duncan Coutts that removes the dependency on mtl - - - - - fa9070da by Neil Mitchell at 2006-09-29T15:52:03+00:00 Do not generate an empty table if there are no exports, this fixes a <table></table> tag being generated, which is not valid HTML 4.01 - - - - - d7431c85 by David Waern at 2007-11-11T02:28:50+00:00 Fix conflicts - - - - - f87e8f98 by Simon Marlow at 2006-10-10T11:37:16+00:00 changes for 0.8 - - - - - db929565 by Simon Marlow at 2006-10-10T12:07:12+00:00 fix the name of the source file - - - - - 8220aa4b by Simon Marlow at 2006-10-11T14:17:37+00:00 Rename haddock.js to haddock-util.js haddock.js will be run automatically by Windows when you type 'haddock' if it is found on the PATH, so rename to avoid confusion. Spotted by Adrian Hey. - - - - - 6bccdaa1 by sven.panne at 2006-10-12T15:28:23+00:00 Cabal's sdist does not generate "-src.tar.gz" files, but ".tar.gz" ones - - - - - d3f3fc19 by Simon Marlow at 2006-12-06T16:05:07+00:00 add todo item for --maintainer - - - - - 2da7e269 by Simon Marlow at 2006-12-15T15:52:00+00:00 TODO: do something better about re-exported symbols from another package - - - - - 42d85549 by David Waern at 2007-11-11T02:30:59+00:00 Fix conflicts - - - - - 5e7ef6e5 by Neil Mitchell at 2007-01-11T15:41:15+00:00 Never do spliting index files into many - - - - - f3d4aebe by Neil Mitchell at 2007-01-11T17:07:09+00:00 Add searching on the index page - - - - - bad3ab66 by Neil Mitchell at 2007-01-11T18:17:46+00:00 Delete dead code, now there is only one index page - - - - - cd09eedb by Neil Mitchell at 2007-01-11T18:21:19+00:00 Delete more stuff that is no longer required - - - - - e2806646 by David Waern at 2007-11-11T02:41:53+00:00 Fix conflicts - - - - - a872a823 by Neil Mitchell at 2007-01-11T18:51:43+00:00 Make the index be in case-insensitive alphabetic order - - - - - 8bddd9d7 by Neil Mitchell at 2007-02-06T17:49:12+00:00 Do not create empty tables for data declarations which don't have any constructors, instances or comments. Gets better HTML 4.01 compliance - - - - - 036b8120 by David Waern at 2007-11-11T02:56:58+00:00 Fix conflicts - - - - - f50c1639 by Conal Elliott at 2007-02-14T21:54:00+00:00 added substitution %{FILE///c} - - - - - 402e166a by David Waern at 2007-11-11T03:35:46+00:00 Manual merge of old patch: Sat Apr 21 04:36:43 CEST 2007 Roberto Zunino <zunrob at users.sf.net> * URL expansion for %%, %L, %{LINE} - - - - - 2f264fbd by David Waern at 2007-11-11T03:40:33+00:00 Manual merge of an old patch: Thu Apr 19 20:23:40 CEST 2007 Wolfgang Jeltsch <g9ks157k at acme.softbase.org> * bug fix When Haddock was invoked with the --ignore-all-exports flag but the ignore-exports module attribute wasn't used, hyperlinks weren't created for non-exported names. This fix might not be as clean as one would wish (since --ignore-all-exports now results in ignore_all_exports = True *and* an additional OptIgnoreExports option for every module) but at least the bug seems to be resolved now. - - - - - 7d7ae106 by sven.panne at 2007-09-02T12:18:02+00:00 Install LICENSE in the correct place - - - - - 66eaa924 by David Waern at 2007-11-11T19:02:46+00:00 Fix a bug that made haddock loop - - - - - 4ed47b58 by David Waern at 2007-11-11T19:03:09+00:00 Rename java-script file (this wasn't merge correctly) - - - - - d569534a by David Waern at 2007-11-11T19:06:44+00:00 Don't require -B <ghc-libdir> when no argument files Change readInterfaceFile to take a Maybe Session, to avoid having to pass -B <ghc-libdir> to Haddock when there're no source files to process. This is nice when computing contents/index for external packages. - - - - - 373368bc by Neil Mitchell at 2007-01-11T18:22:44+00:00 Change from tabs to spaces in the ppHtmlIndex function - - - - - 6b063a77 by Neil Mitchell at 2007-01-12T12:17:46+00:00 Rewrite much of the index searching code, previously was too slow to execute on the base library with IE, the new version guarantees less than O(log n) operations be performed, where n is the number in the list (before was always O(n)) - - - - - bfad00b7 by David Waern at 2007-11-11T23:33:53+00:00 Fix conflicts - - - - - cd2dcc09 by Neil Mitchell at 2007-01-12T12:25:01+00:00 Make the max number of results 75 instead of 50, to allow map searching in the base library to work - - - - - 3ae74764 by Neil Mitchell at 2007-01-12T12:58:17+00:00 Make the search box in a form so that enter does the default search - - - - - 142103e5 by David Waern at 2007-11-12T00:03:18+00:00 Merge patch from the old branch: Fri Aug 31 13:21:45 CEST 2007 Duncan Coutts <duncan at haskell.org> * Add category: Development to .cabal file Otherwise it appears on the hackage website in the "Unclassified" category. - - - - - 22ec2ddb by David Waern at 2007-11-25T01:55:29+00:00 A a list of small improvements to the TODO file - - - - - eb0129f4 by Wolfgang Jeltsch at 2007-12-03T23:47:55+00:00 addition of type equality support (at least for HTML generation) - - - - - 816a7e22 by David Waern at 2007-12-08T15:46:26+00:00 Handle class operators correctly when rendering predicates - - - - - 68baaad2 by David Waern at 2007-12-08T16:15:54+00:00 Code layout changes - - - - - 09b77fb4 by David Waern at 2007-12-08T16:16:03+00:00 Handle infix operators correctly in the Type -> HsType translation - - - - - 31c36da2 by David Waern at 2007-12-08T16:24:27+00:00 Add ppLParendTypes/ppLParendType - - - - - b17cc818 by David Waern at 2007-12-08T16:26:12+00:00 Use ppParendType when printing types args in predicates - - - - - ffd1f2cf by David Waern at 2007-12-08T16:45:06+00:00 Fix rendering of instance heads to handle infix operators This is also a refactoring to share this code for rendering predicates. - - - - - ff886d45 by David Waern at 2007-12-08T17:27:46+00:00 Fix rendering of class operators - - - - - e2fcbb9e by David Waern at 2007-12-08T17:59:28+00:00 Fix a bug (use ppTyName instead of ppName to print names in type apps) - - - - - 79a1056e by David Waern at 2007-12-08T21:25:18+00:00 Update tests - - - - - 867741ac by David Waern at 2007-12-08T21:25:49+00:00 Give a diff on test failure - - - - - 7e5eb274 by David Waern at 2008-01-05T14:33:45+00:00 Add DrIFT commands - - - - - 3656454d by David Waern at 2008-01-05T20:26:00+00:00 Add "cabal-version: >= 1.2" to the cabal file - - - - - 77974efc by Simon Marlow at 2007-12-20T09:52:44+00:00 add an item - - - - - f6ac1708 by Simon Marlow at 2007-12-06T14:00:10+00:00 Source links must point to the original module, not the referring module - - - - - eda1d5c9 by David Waern at 2008-01-06T14:40:52+00:00 Manual merge of a patch to the 0.8 branch Thu Dec 6 15:00:10 CET 2007 Simon Marlow <simonmar at microsoft.com> * Source links must point to the original module, not the referring module - - - - - 378f4085 by David Waern at 2008-01-06T16:03:45+00:00 Change stability from stable to experimental - - - - - 8bdafe44 by David Waern at 2008-01-06T16:14:22+00:00 Add haskell.vim (it had been removed somehow) - - - - - ea34d02e by David Waern at 2008-01-06T16:36:57+00:00 Change version to 2.0.0.0 - - - - - 34631ac0 by David Waern at 2008-01-06T16:44:57+00:00 Add missing modules to the cabal file - - - - - 9e142935 by David Waern at 2008-01-06T17:25:42+00:00 Depend on ghc >= 6.8.2 && < 6.9 - - - - - 59f9eeaa by Simon Marlow at 2007-12-20T10:43:04+00:00 add build scripts - - - - - 1c29ae30 by Simon Marlow at 2007-12-20T10:47:07+00:00 update version number - - - - - fe16a3e4 by Simon Marlow at 2007-12-20T10:48:03+00:00 update version - - - - - f688530f by Simon Marlow at 2007-12-20T10:48:29+00:00 doc updates - - - - - ce71b611 by David Waern at 2008-01-07T13:46:32+00:00 Change version in docs and spec - - - - - 03ab8d6f by David Waern at 2008-01-07T13:47:38+00:00 Manually merge over changes to CHANGES for 0.9 - - - - - 39f1b042 by David Waern at 2008-01-07T15:17:41+00:00 Remove the -use-package flag, we don't support it anyway - - - - - 7274a544 by David Waern at 2008-01-07T15:33:05+00:00 Update CHANGES for 2.0.0.0 - - - - - 96594f5d by David Waern at 2008-01-07T15:46:49+00:00 Wibble - - - - - f4c5a4c4 by David Waern at 2008-01-07T15:55:36+00:00 Change url to repo in documentation - - - - - 8a4c77f0 by David Waern at 2008-01-07T16:00:54+00:00 Update CHANGES - - - - - cb3a9288 by David Waern at 2008-01-07T16:02:55+00:00 Documentation fix - - - - - d8e45539 by David Waern at 2008-01-07T16:12:00+00:00 Update docs to say that Haddock accets .lhs files and module names - - - - - 4b5ce824 by David Waern at 2008-01-07T16:12:25+00:00 Document -B option - - - - - 47274262 by David Waern at 2008-01-07T16:23:07+00:00 Update CHANGES - - - - - 7ff314a9 by David Waern at 2008-01-07T16:23:20+00:00 Remove --use-package, --package & --no-implicit.. flags from docs - - - - - 6c3819c0 by David Waern at 2008-01-07T16:23:52+00:00 Remove --no-implicit-prelide flag - - - - - 1b14ae40 by David Waern at 2008-01-07T16:32:26+00:00 Update the "Using literate or pre-processed source" section - - - - - 0117f620 by David Waern at 2008-01-07T16:41:55+00:00 Document the --optghc flag - - - - - 087ab1cf by David Waern at 2008-01-07T16:42:10+00:00 Remove the documenation section on derived instances The problem mentioned there doesn't exist in Haddock 2.0.0.0 - - - - - 7253951e by David Waern at 2008-01-07T16:48:40+00:00 Document OPTIONS_HADDOCK - - - - - 3b6bdcf6 by David Waern at 2008-01-07T16:56:54+00:00 Wibble - - - - - 3025adf9 by David Waern at 2008-01-07T17:08:14+00:00 Wibble - - - - - 5f30f1a0 by David Waern at 2008-01-07T17:15:44+00:00 Change synopsis field to description - - - - - 1673f54b by David Waern at 2008-01-07T17:18:21+00:00 Change my email address in the cabal file - - - - - 55aa9808 by David Waern at 2008-01-07T18:18:02+00:00 Add documentation for readInterfaceFile - - - - - eaea417f by David Waern at 2008-01-07T18:21:30+00:00 Export necessary stuff from Distribution.Haddock - - - - - 7ea18759 by David Waern at 2008-01-07T18:31:49+00:00 Remove dep on Cabal - - - - - 7b79c74e by David Waern at 2008-01-07T18:33:49+00:00 Remove dep on process - - - - - ce3054e6 by David Waern at 2008-01-16T23:01:21+00:00 Add feature-requsts from Henning Thielemann to TODO - - - - - 0c08f1ec by David Waern at 2008-01-16T23:03:02+00:00 Record a bug in TODO - - - - - b04605f3 by David Waern at 2008-01-23T16:59:06+00:00 Add a bug reported by Ross to TODO - - - - - 5b17c030 by David Waern at 2008-01-23T18:05:53+00:00 A a bug report to TODO - - - - - 1c993b0d by David Waern at 2008-01-25T16:30:25+00:00 Accept test output - - - - - c22fc0d0 by David Waern at 2008-01-25T16:34:49+00:00 Accept test output - - - - - 4b795811 by David Waern at 2008-01-25T16:38:37+00:00 Change Hidden.hs (test) to use OPTIONS_HADDOCK - - - - - c124dbd9 by David Waern at 2008-01-25T16:39:23+00:00 Accept test output - - - - - ec6f6eea by David Waern at 2008-01-25T16:42:08+00:00 Add Hidden.html.ref to tests - - - - - 1dc9610c by David Waern at 2008-02-02T20:50:51+00:00 Add a comment about UNPACK bug in TODO - - - - - 2d3f7081 by David Waern at 2008-02-09T22:33:24+00:00 Change the representation of DocNames Ross Paterson reported a bug where links would point to the defining module instead of the "best" module for an identifier (e.g Int pointing to GHC.Base instead of Data.Int). This patch fixes this problem by refactoring the way renamed names are represented. Instead of representing them by: > data DocName = Link Name | NoLink Name they are now represented as such: > data DocName = Documented Name Module | Undocumented Name and the the link-env looks like this: > type LinkEnv = Map Name Module There are several reasons for this. First of all, the bug was caused by changing the module part of Names during the renaming process, without changing the Unique field. This caused names to be overwritten during the loading of .haddock files (which caches names using the NameCache of the GHC session). So we might create new Uniques during renaming to fix this (but I'm not sure that would be problem-free). Instead, we just keep the Name and add the Module where the name is best documented, since it can be useful to keep the original Name around (for e.g. source-code location info and for users of the Haddock API). Also, the names Link/NoLink don't really make sense, since wether to use links or not is entirely up to the users of DocName. In the process of following this change into H.Backends.Html I removed the assumption that binder names are Undocumented (which was just an unnecessary assumption, the OccName is the only thing needed to render these). This will probably make it possible to get rid of the renamer and replace it with a traversal from SYB or Uniplate. Since DocName has changed, InterfaceFile has changed so this patch also increments the file-format version. No backwards-compatibility is implemented. - - - - - 0f28c921 by David Waern at 2008-02-09T23:00:36+00:00 H.GHC.Utils: remove unused imports/exports - - - - - 0c44cad5 by David Waern at 2008-02-10T00:28:13+00:00 H.GHC.Utils: add some functions that were removed by mistake - - - - - e3452f49 by David Waern at 2008-02-10T00:28:48+00:00 Fix some trivial warnings in H.InterfaceFile - - - - - a6d74644 by David Waern at 2008-02-10T00:48:06+00:00 Update the version message to fit in small terminals - - - - - 76c9cd3e by David Waern at 2008-02-10T14:47:39+00:00 Remove bugs from TODO that don't apply anymore since the port - - - - - 5e10e090 by David Waern at 2008-02-10T15:22:47+00:00 Remove bugs from TODO that weren't actual bugs - - - - - fef70878 by David Waern at 2008-02-10T15:23:44+00:00 Remove yet another item from TODO that was not an actual bug - - - - - e1af47b8 by David Waern at 2008-02-11T10:25:57+00:00 Bump the version number to 2.1.0 Since the exported datatype DocName has changed, we need to bump the major version number. Let's also drop the fourth version component, it's not that useful. - - - - - e3be7825 by David Waern at 2008-04-11T14:29:04+00:00 Add a bug to TODO - - - - - cb6574be by David Waern at 2008-04-11T16:00:45+00:00 Use the in-place haddock when running tests - - - - - c6d7af0d by David Waern at 2008-04-11T16:09:16+00:00 Turn off GHC warnings when running tests - - - - - 7f61b546 by David Waern at 2008-04-11T17:24:00+00:00 Add a flag for turning off all warnings - - - - - 883b8422 by David Waern at 2008-04-12T14:02:18+00:00 Fix printing of data binders - - - - - 2a0db8fc by David Waern at 2008-04-12T18:52:46+00:00 Fix missing parenthesis in constructor args bug - - - - - 1b3ac3f9 by David Waern at 2008-04-12T18:57:23+00:00 Simplify test suite and add tests I move all tests into one single directory to simplify things, and add a test for the last bug that was fixed. - - - - - 8f178376 by David Waern at 2008-04-12T19:00:15+00:00 Add a script for copying test output to "expected" output - - - - - 193e3a03 by David Waern at 2008-04-12T19:16:37+00:00 Remove two fixed bugs from TODO - - - - - ddc9130c by David Waern at 2008-04-12T19:37:06+00:00 Update test README - - - - - 956069c0 by David Waern at 2008-05-01T12:16:14+00:00 Update version number in spec and docs - - - - - 5478621c by David Waern at 2008-05-01T12:28:12+00:00 Remove claim of backwards compatibility from docs for readInterfaceFile - - - - - 4a16dea9 by David Waern at 2008-05-01T12:33:04+00:00 Update CHANGES - - - - - 804216fb by David Waern at 2008-05-01T12:43:16+00:00 Add a synopsis - - - - - fd0c84d5 by David Waern at 2008-05-01T12:44:44+00:00 Add Haddock.DocName to the cabal file - - - - - 9f4a7439 by David Waern at 2008-05-01T12:45:53+00:00 Remove -fglasgow-exts and -fasm - - - - - aee7c145 by David Waern at 2008-05-01T12:54:01+00:00 Add LANGUAGE pragmas to source files - - - - - 9a58428b by David Waern at 2008-05-01T12:54:19+00:00 Add extensions to cabal file - - - - - 494f1bee by David Waern at 2008-05-01T13:12:09+00:00 Export DocName in the API - - - - - c938196b by David Waern at 2008-05-01T13:12:19+00:00 Add hide options to some source files - - - - - 236e86af by Neil Mitchell at 2008-06-07T20:45:10+00:00 Rewrite the --hoogle flag support - - - - - 6d910950 by Neil Mitchell at 2008-06-14T10:56:50+00:00 Simplify the newtype/data outputting in Hoogle, as haddock does it automatically - - - - - f87a95a8 by Neil Mitchell at 2008-06-14T12:10:18+00:00 Add initial structure for outputting documentation as well, but does not yet output anything - - - - - 7c3bce54 by Neil Mitchell at 2008-06-14T12:27:07+00:00 Remove <document comment> from the Hoogle output - - - - - 9504a325 by Neil Mitchell at 2008-06-16T06:33:21+00:00 Default to "main" if there is no package, otherwise will clobber hoogle's hoogle info - - - - - 4a794a79 by Neil Mitchell at 2008-06-16T06:53:29+00:00 Change packageName to packageStr, as it better reflects the information stored in it - - - - - 7abc9baf by Neil Mitchell at 2008-06-16T07:09:49+00:00 Add modulePkgInfo to Haddock.GHC.Utils, which gives back package name and version info - - - - - 8ca11514 by Neil Mitchell at 2008-06-16T07:13:48+00:00 Change Hoogle to take the package name and package version separately - - - - - a6da452d by Neil Mitchell at 2008-06-18T11:29:46+00:00 In Hoogle do not list things that are not local to this module - - - - - 974b76b7 by David Waern at 2008-06-19T18:40:13+00:00 Be more consistent with GHC API naming in H.GHC.Utils - - - - - 2facb4eb by David Waern at 2008-06-19T19:03:03+00:00 Update test output - - - - - c501de72 by David Waern at 2008-06-26T20:26:49+00:00 Use ghc-paths to get the lib dir The path can still be overridden using the -B flag. It's not longer required to pass the lib dir to the program that runs the test suite. - - - - - ac4c6836 by David Waern at 2008-06-26T20:33:08+00:00 Update CHANGES - - - - - 9d21c60a by David Waern at 2008-06-26T20:34:53+00:00 Update README - - - - - 741448f0 by David Waern at 2008-06-26T21:12:57+00:00 Improve wording in the help message - - - - - b1b42b11 by David Waern at 2008-06-30T10:16:17+00:00 Rename ForeignType - - - - - 6d6c2b34 by David Waern at 2008-06-30T10:25:09+00:00 Rename TyFamily - - - - - 8d1125ed by David Waern at 2008-06-30T10:37:21+00:00 Rename type patterns - - - - - 7610a4cb by David Waern at 2008-06-30T10:45:07+00:00 Rename associated types - - - - - 8eeba14c by David Waern at 2008-06-30T10:47:41+00:00 Remove the TODO file now that we have a trac - - - - - 1af5b25b by David Waern at 2008-07-02T18:19:28+00:00 Render type family declarations (untested) - - - - - ceb99797 by David Waern at 2008-07-02T18:24:06+00:00 Remove redundant check for summary when rendering data types - - - - - b36a58e0 by David Waern at 2008-07-02T22:01:38+00:00 More support for type families and associated types Now we just need to render the instances - - - - - 78784879 by David Waern at 2008-07-07T22:13:58+00:00 Remove filtering of instances We were filtering out all instances for types with unknown names. This was probably an attempt to filter out instances for internal types. I am removing the filtering for the moment, and will try to fix this properly later. - - - - - 3e758dad by David Waern at 2008-06-30T18:50:30+00:00 Run haddock in-place during testing - - - - - d9dab0ce by David Waern at 2008-07-08T21:04:32+00:00 Remove index.html and doc-index.html from output, they should not be versioned - - - - - 3e6c4681 by David Waern at 2008-07-08T21:06:42+00:00 Update test output following change to instance filtering - - - - - e34a3f14 by David Waern at 2008-07-12T16:48:28+00:00 Stop using the map from exported names to declarations During creation of the interface, we were using two maps: one from exported names to declarations, and one from all defined names in the module to declarations. The first contained subordinate names while the second one didn't. The first map was never used to look up names not defined in the associated module, so if we add subordinate names to the second map, we could use it everywhere. That's that this patch does. This simplifies code because we don't have to pass around two maps everywhere. We now store the map from locally defined things in the interface structure instead of the one from exported names. - - - - - 2e1d2766 by David Waern at 2008-07-12T16:55:21+00:00 Get the all locally defined names from GHC API We previously had some code to compute all locally defined names in a module including subordinate names. We don't need it since we can get the names from modInfoTyThings in the GHC API. - - - - - bf637994 by David Waern at 2008-07-13T13:09:16+00:00 Refactoring in H.Interface.Create We were creating a doc map, a declaration map and a list of entities separately by going through the HsGroup. These structures were all used to build the interface of a module. Instead of doing this, we can start by creating a list of declarations from the HsGroup, then collect the docs directly from this list (instead of using the list of entities), creating a documentation map. We no longer need the Entity data type, and we can store a single map from names to declarations and docs in the interface, instead of the declaration map and the doc map. This way, there is only one place where we filter out the declarations that we don't want, and we can remove a lot of code. Another advantage of this is that we can create the exports directly out of the list of declarations when we export the full module contents. (Previously we did a look up for each name to find the declarations). This is faster and removes another point where we depend on names to identify exported declarations, which is good because it eliminates problems with instances (which don't have names). - - - - - 547e410e by David Waern at 2008-07-13T13:34:51+00:00 Remove FastString import and FSLIT macro in H.I.Create -- they were unused - - - - - 693759d1 by David Waern at 2008-07-13T13:36:23+00:00 Remove unused import from H.I.Create - - - - - cde6e7fb by David Waern at 2008-07-13T13:51:54+00:00 Small touches - - - - - 96de8f1d by David Waern at 2008-07-20T11:21:46+00:00 Preparation for rendering instances as separate declarations We want to be able to render instances as separate declarations. So we remove the Name argument of ExportDecl, since instances are nameless. This patch also contains the first steps needed to gather type family instances and display them in the backend, but the implementation is far from complete. Because of this, we don't actually show the instances yet. - - - - - b0f824fb by David Waern at 2008-07-20T15:53:08+00:00 Follow changes to ExportDecl in Hoogle - - - - - 1192eff3 by Neil Mitchell at 2008-06-26T00:28:10+00:00 Change how the Hoogle backend outputs classes, adding the context in - - - - - 7a0d1464 by Neil Mitchell at 2008-06-26T00:28:46+00:00 Remove the indent utility function from Hoogle backend - - - - - 3361241b by Neil Mitchell at 2008-06-26T09:45:09+00:00 Add support for Hoogle writing ForeignImport/ForeignExport properly - - - - - 795ad3bf by Neil Mitchell at 2008-06-26T12:15:25+00:00 Flesh out the Hoogle code to render documentation - - - - - 23277995 by Neil Mitchell at 2008-06-26T14:56:41+00:00 Fix a bug in the Hoogle backend, unordered lists were being written out <ul>...</u> - - - - - db739b27 by Neil Mitchell at 2008-06-26T15:09:54+00:00 Remove any white space around a <li> element - - - - - f2e6bb8c by Neil Mitchell at 2008-07-10T15:30:47+00:00 Remove the TODO in the Hoogle HTML generation, was already done - - - - - 693ec9a3 by Neil Mitchell at 2008-07-10T15:53:00+00:00 Put brackets round operators in more places in the Hoogle output - - - - - 842313aa by Neil Mitchell at 2008-07-10T16:01:25+00:00 Print type signatures with brackets around the name - - - - - cf93deb0 by David Waern at 2008-07-20T17:04:22+00:00 Bump version number to 2.2.0 - - - - - 30e6a8d1 by David Waern at 2008-07-20T17:04:41+00:00 Resolve conflicts in H.B.Hoogle - - - - - 1f0071c9 by David Waern at 2008-07-23T23:05:01+00:00 Add "all" command to runtests.hs that runs all tests despite failures - - - - - f2723023 by David Waern at 2008-07-23T23:08:39+00:00 Update tests/README - - - - - c0304a11 by David Waern at 2008-07-23T23:21:15+00:00 Be compatible with GHC 6.8.3 The cabal file is converted to use the "new" syntax with explicit Library and Executable sections. We define the __GHC_PATCHLEVEL__ symbol using a conditinal cpp-options field in the cabal file. (Ideally, Cabal would define the symbol for us, like it does for __GLASGOW_HASKELL__). We use these symbols to #ifdef around a small difference between 6.8.2 and 6.8.3. Previously, we only supported GHC 6.8.2 officially but the dependencies field said "ghc <= 6.9". This was just for convenience when testing against the (then compatible) HEAD version of GHC, and was left in the release by mistake. Now, we support both GHC 6.8.2 and 6.8.3 and the dependencies field correctly reflects this. - - - - - 88a5fe71 by David Waern at 2008-07-23T23:54:16+00:00 Depend on the currently available ghc-paths versions only - - - - - 8738d97b by David Waern at 2008-07-24T10:50:44+00:00 FIX haskell/haddock#44: Propagate parenthesis level when printing documented types - - - - - 05339119 by David Waern at 2008-07-24T16:06:18+00:00 Drop unnecessary parenthesis in types, put in by the user We were putting in parenthesis were the user did. Let's remove this since it just clutters up the types. The types are readable anyway since we print parens around infix operators and do not rely on fixity levels. When doing this I discovered that we were relying on user parenthesis when printin types like (a `O` b) c. This patchs fixes this problem so that parenthesis are always inserted around an infix op application in case it is applied to further arguments, or if it's an arguments to a type constructor. Tests are updated. - - - - - b3a99828 by David Waern at 2008-07-24T10:19:43+00:00 Print parenthesis around non-atomic banged types Fixes half of haskell/haddock#44 - - - - - ab5238e0 by David Waern at 2008-07-24T22:07:49+00:00 Add a reference file for the TypeFamilies test - - - - - 1941cc11 by David Waern at 2008-07-25T17:15:53+00:00 Simplify definition of pretty and trace_ppr - - - - - e3bfa33c by David Waern at 2008-07-25T17:18:27+00:00 Warning messages Output a warning when filtering out data/type instances and associated types in instances. We don't show these in the documentation yet, and we need to let the user know. - - - - - 9b85fc89 by David Waern at 2008-07-25T17:45:40+00:00 Doc: Mention Hoogle in the Introduction - - - - - afb2dd60 by David Waern at 2008-07-25T17:49:00+00:00 Doc: update -B description - - - - - 584c0c91 by David Waern at 2008-07-25T18:11:38+00:00 Doc: describe -w flag - - - - - 77619c24 by David Waern at 2008-07-28T12:29:07+00:00 Remove TODO from cabal file - - - - - 96717d5f by David Waern at 2008-07-28T12:29:27+00:00 Support type equality predicates - - - - - c2fd2330 by David Waern at 2008-07-29T19:45:14+00:00 Move unL from H.B.Hoogle to H.GHC.Utils I like Neil's shorter unL better than unLoc from the GHC API. - - - - - c4c3bf6a by David Waern at 2008-07-29T19:47:36+00:00 Do not export ATs when not in list of subitems - - - - - bf9a7b85 by David Waern at 2008-08-03T11:42:59+00:00 Filter out ForeignExports - - - - - df59fcb0 by David Waern at 2008-08-03T14:02:51+00:00 Filter out more declarations The previous refactorings in H.I.Create introduced a few bugs. Filtering of some types of declarations that we don't handle was removed. This patch fixes this. - - - - - 2f8a958b by David Waern at 2008-08-03T15:24:07+00:00 Move reL to H.GHC.Utils so we can use it everywhere - - - - - 8ec15efd by David Waern at 2008-08-03T15:25:00+00:00 Use isVanillaLSig from GHC API instead of home brewn function - - - - - 300f93a2 by David Waern at 2008-08-03T15:25:27+00:00 Filter out separately exported ATs This is a quick and dirty hack to get rid of separately exported ATs. We haven't decided how to handle them yet. No warning message is given. - - - - - 8776d1ec by David Waern at 2008-08-03T16:21:21+00:00 Filter out more declarations and keep only vanilla type sigs in classes - - - - - ea07eada by David Waern at 2008-08-03T16:48:00+00:00 Fix layout - - - - - dd5e8199 by David Waern at 2008-08-03T16:50:52+00:00 Move some utility functions from H.I.Create to H.GHC.Utils - - - - - 4a1dbd72 by David Waern at 2008-08-03T17:39:55+00:00 Do not filter out doc declarations - - - - - 0bc8dca4 by David Waern at 2008-08-03T17:47:26+00:00 Filter out separately exported ATs (take two) - - - - - af970fe8 by David Waern at 2008-08-03T22:39:17+00:00 Update CHANGES - - - - - 5436ad24 by David Waern at 2008-08-03T22:40:20+00:00 Bump version number to 2.2.1 - - - - - d66de448 by David Waern at 2008-08-05T19:00:32+00:00 Remove version restriction on ghc-paths - - - - - 534b1364 by David Waern at 2008-08-05T19:04:35+00:00 Bump version to 2.2.2 and update CHANGES - - - - - 549188ff by David Waern at 2008-08-05T19:16:49+00:00 Fix CHANGES - - - - - 0d156bb4 by Luke Plant at 2008-08-11T15:20:59+00:00 invoking haddock clarification and help - - - - - 748295cc by David Waern at 2008-08-11T18:56:37+00:00 Doc: say that the --hoogle option is functional - - - - - 43301db4 by David Waern at 2008-08-05T19:26:08+00:00 Change ghc version dependency to >= 6.8.2 - - - - - 3e5a53b6 by David Waern at 2008-08-10T22:42:05+00:00 Make H.GHC.Utils build with GHC HEAD - - - - - 7568ace0 by David Waern at 2008-08-11T19:41:54+00:00 Import Control.OldException instead of C.Exception when using ghc >= 6.9 We should really test for base version instead, but I don't currently know which version to test for. - - - - - b71ae991 by David Waern at 2008-08-12T22:40:39+00:00 Make our .haddock file version number depend on the GHC version We need to do this, since our .haddock format can potentially change whenever GHC's version changes (even when only the patchlevel changes). - - - - - 6307ce3f by David Waern at 2008-08-12T22:49:57+00:00 Remove matching on NoteTy in AttachInstances, it has been removed - - - - - 2dbcfd5f by David Waern at 2008-08-12T23:02:02+00:00 Comment out H.GHC.loadPackages - it is unused and doesn't build with ghc >= 6.9 - - - - - c74db5c2 by David Waern at 2008-08-12T23:03:58+00:00 Hide <.> from GHC import in Hoogle only for ghc <= 6.8.3 - - - - - 69a44ebb by David Waern at 2008-08-12T23:11:12+00:00 Follow changes to parseDynamic/StaticFlags - - - - - 5881f3f0 by David Waern at 2008-08-13T21:43:58+00:00 Add __GHC_PATCHLEVEL__ symbol also when building the library - - - - - 8574dc11 by David Waern at 2008-08-13T21:44:17+00:00 Follow move of package string functions from PackageConfig to Module - - - - - c9baa77f by David Waern at 2008-08-13T21:45:29+00:00 Follow extensible exceptions changes - - - - - 9092de15 by David Waern at 2008-08-13T21:46:20+00:00 Update test following Haddock version change - - - - - ebe569a4 by David Waern at 2008-08-13T21:46:54+00:00 Follow changes to parseDynamic- parseStaticFlags in GHC - - - - - b8a5ffd3 by David Waern at 2008-08-13T21:47:36+00:00 Follow changes to Binary in GHC 6.9 - - - - - edfda1cc by David Waern at 2008-08-13T21:50:17+00:00 Change ghc version dependency to >= 6.8.2 && <= 6.9 - - - - - d59be1cf by Neil Mitchell at 2008-08-12T16:02:53+00:00 Output all items, even if they are not defined in this module - ensures map comes from Prelude, not just GHC.Base - - - - - dda93b9f by Neil Mitchell at 2008-08-12T21:37:32+00:00 Add support for type synonyms to Hoogle, was accidentally missing before (woops!) - - - - - b6ee795c by Neil Mitchell at 2008-08-13T14:03:24+00:00 Generalise Hoogle.doc and add a docWith - - - - - 415e1bb2 by Neil Mitchell at 2008-08-13T14:03:46+00:00 Make Hoogle add documentation to a package - - - - - 790a1202 by Neil Mitchell at 2008-08-18T12:52:43+00:00 Use the same method to put out signatures as class methods in the Hoogle backend - - - - - ded37eba by Neil Mitchell at 2008-08-18T12:53:04+00:00 Remove Explicit top-level forall's when pretty-printing signatures - - - - - 6468c722 by Neil Mitchell at 2008-08-20T07:59:13+00:00 Simplify the code by removing not-to-important use of <.> in the Hoogle back end - - - - - 788c3a8b by Neil Mitchell at 2008-08-21T18:20:24+00:00 In the hoogle back end, markup definition lists using <i>, not <b> - - - - - 77d4b000 by Ian Lynagh at 2008-08-14T10:49:14+00:00 Add a Makefile for GHC's build system. Still won't work yet, but we're closer - - - - - 920440d7 by Ian Lynagh at 2008-08-27T18:06:46+00:00 Add haddock.wrapper - - - - - bcda925f by Ian Lynagh at 2008-08-27T18:07:02+00:00 Add a manual Cabal flag to control the ghc-paths dependency - - - - - 04d194e2 by Ian Lynagh at 2008-08-27T20:41:27+00:00 Update extensions in Cabal file Use ScopedTypeVariables instead of PatternSignatures - - - - - 12480043 by Ian Lynagh at 2008-08-27T20:41:55+00:00 Increase the upper bound on the GHC version number - - - - - b1f809a5 by Ian Lynagh at 2008-08-27T21:32:22+00:00 Fix some warnings - - - - - aea0453d by Ian Lynagh at 2008-08-28T14:22:29+00:00 Fixes for using haddock in a GHC build tree - - - - - ad23bf86 by Ian Lynagh at 2008-08-28T21:14:27+00:00 Don't use Cabal wrappers on Windows - - - - - 35858e4c by Ian Lynagh at 2008-08-29T00:07:42+00:00 Fix in-tree haddock on Windows - - - - - c2642066 by Ian Lynagh at 2008-09-03T22:35:53+00:00 follow library changes - - - - - 2eb55d50 by Ian Lynagh at 2008-09-07T18:52:51+00:00 bindist fixes - - - - - 3daa5b59 by Ian Lynagh at 2008-09-10T16:58:18+00:00 We need to tell haddock that its datasubdir is . or it can't find package.conf - - - - - 388fd8c2 by Ian Lynagh at 2008-09-10T19:47:44+00:00 Fix haddock inplace on Windows - - - - - 70a641c1 by Ian Lynagh at 2008-09-10T22:15:44+00:00 Fix installed haddock on Windows - - - - - 83c1e997 by Neil Mitchell at 2008-09-11T10:48:55+00:00 Import GHC.Paths if not IN_GHC_TREE, seems to match the use of GHC.Paths functions much better - - - - - b452519b by Ian Lynagh at 2008-09-12T12:58:24+00:00 Add a LANGUAGE ForeignFunctionInterface pragma - - - - - afbd592c by Ian Lynagh at 2008-09-12T12:59:13+00:00 Wibble imports - - - - - 547ac4ad by Ian Lynagh at 2008-09-14T15:34:22+00:00 Add a "#!/bin/sh" to haddock.wrapper - - - - - f207a807 by Ian Lynagh at 2008-09-15T10:02:32+00:00 Use "exec" when calling haddock in the wrapper - - - - - 2ee68509 by Thomas Schilling at 2008-09-15T09:09:16+00:00 Port Haddock.Interface to new GHC API. This required one bigger change: 'readInterfaceFile' used to take an optional 'Session' argument. This was used to optionally update the name cache of an existing GHC session. This does not work with the new GHC API, because an active session requires the function to return a 'GhcMonad' action, but this is not possible if no session is provided. The solution is to use an argument of functions for reading and updating the name cache and to make the function work for any monad that embeds IO, so it's result type can adapt to the calling context. While refactoring, I tried to make the code a little more self-documenting, mostly turning comments into function names. - - - - - 3bb96431 by Thomas Schilling at 2008-09-15T09:09:37+00:00 Reflect GHC API changes. - - - - - 2e60f714 by Thomas Schilling at 2008-09-15T09:10:37+00:00 Port Haddock.GHC.Typecheck to new GHC API. - - - - - 9cfd4cff by Thomas Schilling at 2008-09-15T09:11:00+00:00 Port Haddock.GHC to new GHC API. - - - - - caffa003 by Thomas Schilling at 2008-09-15T09:11:25+00:00 Port Main to new GHC API. - - - - - 069a4608 by Ian Lynagh at 2008-09-21T11:19:00+00:00 Fix paths used on Windows frmo a GHC tree: There is no whare directory - - - - - 7ceee1f7 by Ian Lynagh at 2008-09-21T12:20:16+00:00 Fix the in-tree haddock on Windows - - - - - 0d486514 by Ian Lynagh at 2008-09-23T18:06:58+00:00 Increase the GHC upper bound from 6.11 to 6.13 - - - - - f092c414 by Neil Mitchell at 2008-09-11T14:56:07+00:00 Do not wrap __ in brackets - - - - - 036bdd13 by Ian Lynagh at 2008-09-28T01:42:35+00:00 Fix building haddock when GhcProfiled=YES - - - - - 01434a89 by David Waern at 2008-09-24T20:24:21+00:00 Add PatternSignatures LANGUAGE pragma to Main and Utils - - - - - 1671a750 by David Waern at 2008-10-02T22:57:25+00:00 For source links, get original module from declaration name instead of environment. Getting it from the environment must have been a remnant from the times when we were using unqualified names (versions 0.x). - - - - - a25dde99 by David Waern at 2008-10-02T22:59:57+00:00 Remove ifaceEnv from Interface - it's no longer used - - - - - 610993da by David Waern at 2008-10-02T23:04:58+00:00 Write a comment about source links for type instance declarations - - - - - 5a96b5d5 by Thomas Schilling at 2008-10-03T10:45:08+00:00 Follow GHC API change of parseModule. - - - - - 5a943ae5 by Ian Lynagh at 2008-10-03T15:56:58+00:00 TAG 2008-10-03 - - - - - 76cdd6ae by Thomas Schilling at 2008-10-08T12:29:50+00:00 Only load modules once when typechecking with GHC. This still doesn't fix the memory leak since the typechecked source is retained and then processed separately. To fix the leak, modules must be processed directly after typechecking. - - - - - 7074d251 by David Waern at 2008-10-09T23:53:54+00:00 Interleave typechecking with interface creation At the same time, we fix a bug where the list of interfaces were processed in the wrong order, when building the links and renaming the interfaces. - - - - - 4b9b2b2d by David Waern at 2008-10-09T23:54:49+00:00 Add some strictness annotations in Interface We add some strictness annotations to the fields of Interface, so that less GHC data is hold on to during processing. - - - - - 22035628 by David Waern at 2008-10-10T20:02:31+00:00 Remove typecheckFiles and MonadUtils import from H.GHC.Typeccheck - - - - - be637ad3 by David Waern at 2008-10-10T20:33:38+00:00 Make Haddock build with GHC 6.8.2 - - - - - 523b3404 by David Waern at 2008-10-10T21:08:09+00:00 Fix documentation for createInterfaces - - - - - e1556702 by David Waern at 2008-10-10T21:26:19+00:00 Hide H.Utils in library - - - - - a8e751c3 by David Waern at 2008-10-10T21:34:59+00:00 Add back .haddock file versioning based on GHC version It was accidentally removed in the patch for GHC 6.8.2 compatibility - - - - - 06fb3c01 by David Waern at 2008-10-10T21:47:15+00:00 Bump version number to 2.3.0 - - - - - ff087fce by David Waern at 2008-10-10T22:35:49+00:00 Add support for DocPic The support for DocPic was merged into the GHC source long ago, but the support in Haddock was forgotten. Thanks Peter Gavin for submitting this fix! - - - - - 3af85bf6 by David Waern at 2008-10-10T23:34:05+00:00 Update tests - - - - - 0966873c by Simon Marlow at 2008-10-10T14:43:04+00:00 no need for handleErrMsg now, we don't throw any ErrMsgs - - - - - f1870de3 by Clemens Fruhwirth at 2008-10-10T13:29:36+00:00 Compile with wrapper but remove it for dist-install - - - - - 7b440dc2 by David Waern at 2008-10-11T14:02:25+00:00 Remove interface from LinksInfo It was there to know the documentation home module when creating a wiki link, but we already know this since we have the DocName. - - - - - e5729e6a by David Waern at 2008-10-15T20:49:18+00:00 Wibble - - - - - b2a8e01a by David Waern at 2008-10-15T21:03:36+00:00 Use type synonyms for declarations and docs in H.I.Create - - - - - be71a15b by David Waern at 2008-10-15T21:12:17+00:00 Comment out unused type family stuff completely - - - - - 91aaf075 by David Waern at 2008-10-15T21:49:04+00:00 Wibble - - - - - 42ba4eb4 by David Waern at 2008-10-15T21:53:53+00:00 Move convenient type synonym to H.Types - - - - - db11b723 by David Waern at 2008-10-15T22:14:07+00:00 Add DeclInfo to H.Types - - - - - 193552b6 by David Waern at 2008-10-15T22:15:01+00:00 Add subordinates with docs to the declaration map The only place in the code where we want the subordinates for a declaration is right after having looked up the declaration in the map. And since we include subordinates in the map, we might as well take the opportunity to store those subordinates that belong to a particular declaration together with that declaration. We also store the documentation for each subordinate. - - - - - 31e6eebc by David Waern at 2008-10-16T17:18:47+00:00 Wibble - - - - - 0dcbd79f by David Waern at 2008-10-16T20:58:42+00:00 Fix haskell/haddock#61 We were not getting docs for re-exported class methods. This was because we were looking up the docs in a map made from the declarations in the current module being rendered. Obviously, re-exported class methods come from another module. Class methods and ATs were the only thing we were looking up using the doc map, everything else we found in the ExporItems. So now I've put subordinate docs in the ExportItem's directly, to make things a bit more consistent. To do this, I added subordinates to the the declarations in the declaration map. This was easy since we were computing subordinates anyway, to store stand-alone in the map. I added a new type synonym 'DeclInfo', which is what we call what is now stored in the map. This little refactoring removes duplicate code to retrieve subordinates and documentation from the HsGroup. - - - - - de47f20a by David Waern at 2008-10-16T22:06:35+00:00 Document function and improve its layout - - - - - e74e625a by Thomas Schilling at 2008-10-20T11:12:57+00:00 Force interface more aggressively. For running Haddock on GHC this reduces memory usage by about 50 MB on a 32 bit system. A heap profile shows total memory usage peak at about 100 MB, but actual usage is at around 300 MB even with compacting GC (+RTS -c). - - - - - b63ac9a1 by David Waern at 2008-10-20T20:25:50+00:00 Make renamer consistent Instead of explicitly making some binders Undocumented, treat all names the same way (that is, try to find a Documented name). - - - - - f6de0bb0 by Ian Lynagh at 2008-09-19T00:54:43+00:00 TAG GHC 6.10 fork - - - - - 74599cd0 by David Waern at 2008-10-20T21:13:24+00:00 Do not save hidden modules in the .haddock file We were saving interfaces of all processed modules including those hidden using {-# OPTIONS_HADDOCK hide #-} in the .haddock file. This caused broken links when generating the index for the libraries that come with GHC. This patch excludes modules with hidden documentation when writing .haddock files. It should fix the above problem. - - - - - 7b6742e9 by David Waern at 2008-10-21T19:54:52+00:00 Do not save hidden modules in the .haddock file (also for ghc >= 6.9) When writing the first patch, I forgot to do the fix in both branches of an #if macro. - - - - - b99b1951 by David Waern at 2008-10-22T20:04:18+00:00 Remove subordinate map and its usage It is not needed now that we store subordinate names in the DeclInfo map. - - - - - da97cddc by David Waern at 2008-10-22T20:11:46+00:00 Tidy up code in H.I.Create a little Remove commented out half-done type instance support, and remove DeclWithDoc synonym. - - - - - 6afa76f3 by David Waern at 2008-10-22T21:17:29+00:00 Fix warnings in H.GHC.Utils - - - - - 171ea1e8 by David Waern at 2008-10-22T21:35:04+00:00 Fix warnings in H.Utils - - - - - c8cb3b91 by David Waern at 2008-10-22T21:36:49+00:00 Wibble - - - - - 767fa06a by David Waern at 2008-10-27T19:59:04+00:00 Make named doc comments into ExportDoc instead of ExportDecl Fixes a crash when processing modules without export lists containing named docs. - - - - - e638bbc6 by David Waern at 2008-11-02T22:21:10+00:00 Add HCAR entry - - - - - 92b4ffcf by David Waern at 2008-11-02T22:44:19+00:00 Update CHANGES - - - - - 84d4da6e by David Waern at 2008-11-03T11:25:04+00:00 Add failing test for template haskell crash - - - - - 2a9cd2b1 by David Waern at 2008-11-04T21:13:44+00:00 Add tests/TH.hs - - - - - 8a59348e by David Waern at 2008-11-04T21:30:26+00:00 TAG 2.3.0 - - - - - 54f70d31 by Thomas Schilling at 2008-10-24T17:04:08+00:00 Enable framed view of the HTML documentation. This patch introduces: - A page that displays the documentation in a framed view. The left side will show a full module index. Clicking a module name will show it in the right frame. If Javascript is enabled, the left side is split again to show the modules at the top and a very short synopsis for the module currently displayed on the right. - Code to generate the mini-synopsis for each module and the mini module index ("index-frames.html"). - CSS rules for the mini-synopsis. - A very small amount of javascript to update the mini-synopsis (but only if inside a frame.) Some perhaps controversial things: - Sharing code was very difficult, so there is a small amount of code duplication. - The amount of generated pages has been doubled, since every module now also gets a mini-synopsis. The overhead should not be too much, but I haven't checked. Alternatively, the mini-synopsis could also be generated using Javascript if we properly annotate the actual synopsis. - - - - - 5d7ea5a6 by David Waern at 2008-11-04T23:20:17+00:00 Follow change to ExportDecl in frames code - - - - - 60e16308 by David Waern at 2008-11-04T23:35:26+00:00 Update CHANGES - - - - - d63fd26d by David Waern at 2008-11-04T23:37:43+00:00 Bump version number - - - - - c1660c39 by David Waern at 2008-11-04T23:44:46+00:00 Update CHANGES - - - - - 995ab384 by David Waern at 2008-11-04T23:55:21+00:00 Remove .ref files from tests/output/ - - - - - 1abbbe75 by David Waern at 2008-11-04T23:57:41+00:00 Output version info before running tests - - - - - 649b182f by David Waern at 2008-11-05T22:45:37+00:00 Add ANNOUNCE message - - - - - c36ae0bb by David Waern at 2008-11-05T23:15:35+00:00 Update ANNOUNCE - - - - - 9c4f3d40 by David Waern at 2008-11-05T23:18:30+00:00 Wibble - - - - - 5aac87ce by David Waern at 2008-11-06T21:07:48+00:00 Depend on base 4.* when using GHC >= 6.9, otherwise 3.* - - - - - b9796a74 by David Waern at 2008-11-06T21:13:40+00:00 Bump version to 2.4.1 and update CHANGES - - - - - d4b26baa by David Waern at 2008-11-06T21:26:33+00:00 Depend on base 4.0.* instead of 4.* - - - - - 2cb0903c by David Waern at 2008-11-06T21:46:53+00:00 Fix warnings in H.B.HH and H.B.HH2 - - - - - e568e89a by David Waern at 2008-11-06T21:47:12+00:00 Fix warnings in Haddock.ModuleTree - - - - - 9dc14fbd by David Waern at 2008-11-06T21:47:52+00:00 Fix warnings in Haddock.Version - - - - - 02ac197c by David Waern at 2008-11-06T21:51:31+00:00 Fix warnings in H.InterfaceFile and H.Options - - - - - 63e7439a by David Waern at 2008-11-06T21:59:45+00:00 Fix warnings in H.GHC.Typecheck - - - - - 4bca5b68 by David Waern at 2008-11-08T13:43:42+00:00 Set HscTarget to HscNothing instead of HscAsm There used to be a bug in the GHC API that prevented us from setting this value. - - - - - 07357aec by David Waern at 2008-11-09T22:27:00+00:00 Re-export NameCache and friends from Distribution.Haddock - - - - - ea554b5a by David Waern at 2008-11-09T23:14:10+00:00 Add Haddock.GHC.Utils to other-modules in library - - - - - 74aecfd7 by David Waern at 2008-11-10T01:18:57+00:00 Export DocName in the library - - - - - 241a58b3 by David Waern at 2008-11-10T01:19:18+00:00 Document the functions in H.DocName - - - - - edc2ef1b by David Waern at 2008-11-10T01:20:52+00:00 Export H.DocName in the library - - - - - 4f588d55 by David Waern at 2008-11-10T01:29:14+00:00 Make DocName an instance of NamedThing - - - - - b4647244 by David Waern at 2008-11-15T22:58:18+00:00 Reflect version bump in test suite - - - - - 4bee8ce2 by David Waern at 2008-11-15T22:58:45+00:00 Update tests For unknown reasons, test output for Bug1 and Test has changed for the better. - - - - - 1690e2f9 by David Waern at 2008-11-15T22:59:33+00:00 Store hidden modules in .haddock files We store documentation for an entity in the 'InstalledInterface' of the definition site module, and never in the same structure for a module which re-exports the entity. So when a client of the Haddock library wants to look up some documentation, he/she might need to access a hidden module. But we currently don't store hidden modules in the .haddock files. So we add the hidden modules and the Haddock options to the .haddock files. The options will be used to filter the module list to obtain the visible modules only, which is necessary for generating the contents and index for installed packages. - - - - - 8add6435 by David Waern at 2008-11-16T14:35:50+00:00 Bump major version number due to .haddock file format change - - - - - 48bfcf82 by David Waern at 2008-11-23T14:32:52+00:00 Update tests to account for version number bump - - - - - 0bbd1738 by David Waern at 2008-11-23T14:33:31+00:00 HADDOCK_DATA_DIR changed to haddock_datadir - - - - - 5088b78c by David Waern at 2008-11-23T17:13:21+00:00 FIX haskell/haddock#45: generate two anchors for each name We generate two anchor tags for each name, one where we don't escape the name and one where we URI-encode it. This is for compatibility between IE and Opera. Test output is updated. - - - - - 5ee5ca3b by Neil Mitchell at 2008-11-27T14:38:11+00:00 Drop HsDocTy annotations, they mess up pretty printing and also have a bracketing bug (#2584) - - - - - 51c014e9 by Roman Cheplyaka at 2008-11-27T22:27:36+00:00 Allow referring to a specific section within a module in a module link Fixes haskell/haddock#65 - - - - - 4094bdc5 by David Waern at 2008-11-28T21:13:33+00:00 Update tests following anchor change - - - - - f89552dd by Thomas Schilling at 2008-11-29T16:16:20+00:00 Haddock really shouldn't try to overwrite files. - - - - - 98127499 by David Waern at 2008-12-07T14:09:15+00:00 Solve conflict - - - - - 319356c5 by David Waern at 2008-10-22T21:16:55+00:00 Add -Wall -Werror to ghc-options - - - - - 3c4968c9 by David Waern at 2008-11-04T23:38:56+00:00 TAG 2.4.0 - - - - - 4b21e003 by David Waern at 2008-11-06T21:14:04+00:00 TAG 2.4.1 - - - - - 8e0cad5c by David Waern at 2008-12-07T14:12:54+00:00 Remove -Werror - - - - - 299d6deb by David Waern at 2008-12-07T14:25:18+00:00 Remove -Wall, we'll focus on warnings after 6.10.2 is out - - - - - 5f4216b6 by David Waern at 2008-12-07T20:58:05+00:00 Resolve conflict properly - - - - - 67d774e7 by Neil Mitchell at 2008-12-15T11:44:26+00:00 Make forall's in constructors explicit, i.e. data Foo = Foo {foo :: Eq a => a} - - - - - 61851792 by Neil Mitchell at 2008-12-18T15:39:39+00:00 Try and find a better package name than "main" for Hoogle, goes wrong when working on an executable rather than a library - - - - - 2fab8554 by David Waern at 2008-12-08T23:19:48+00:00 Make visible names from ExportItems Instead of a complicated calculation of visible names out of GHC's export items, we can get them straight out of the already calculated ExportItems. The ExportItems should represent exactly those items that are visible in an interface. If store all the exported sub-names in ExportDecl instead of only those with documentation, the calculation becomes very simple. So we do this change as well (should perhaps have been a separate patch). This should fix the problem with names from ghc-prim not appearing in the link environment. - - - - - 7caadd8c by Ian Lynagh at 2008-12-11T17:01:04+00:00 Wrap the GHC usage with defaultCleanupHandler This fixes a bug where haddock leaves /tmp/ghc* directories uncleaned. - - - - - 7c9fc9a5 by David Waern at 2009-01-02T21:38:27+00:00 Show re-exported names from external packages again This fixes GHC ticket 2746. In order to also link to the exported subordinate names of a declaration, we need to re-introduce the sub map in the .haddock files. - - - - - 119e4e05 by David Waern at 2009-01-06T23:34:17+00:00 Do not process boot modules We should of course not try to produce documentation for boot modules! The reason this has worked in the past is that the output of "real" modules overwrites the output of boot modules later in the process. However, this causes a subtle link environment problem. So let's get rid of this stupid behaviour. We avoid processing boot modules, but we continue to typecheck them. - - - - - c285b9d2 by David Waern at 2009-01-08T18:03:36+00:00 Export modules also when coming from external packages This seems to have regressed since a refactoring that was part of the 2.3.0 release. - - - - - 24031c17 by David Waern at 2009-01-10T15:26:26+00:00 Change version to 2.4.2 - no need to go to 2.5.0 - - - - - 864d1c3f by David Waern at 2009-01-10T15:35:20+00:00 Update tests to account for version number change - - - - - 524ba886 by David Waern at 2009-01-10T18:29:17+00:00 Add test for Template Haskell splicing - - - - - 05e6e003 by David Waern at 2009-01-10T19:35:42+00:00 Fix Trac haskell/haddock#68: Turn on compilation via C for Template Haskell packages We can't use HscNothing if we need to run code coming from modules inside the processed package during typechecking, which is the case for some packages using Template Haskell. This could be improved, to e.g. use HscInterpreted and HscNothing where possible, instead of using HscC for all modules in the package. - - - - - 2b2bafa1 by David Waern at 2009-01-10T20:22:25+00:00 Only use needsTemplateHaskell when compiling with GHC 6.10.2 or above - - - - - bedc3a93 by Ian Lynagh at 2009-01-11T14:58:41+00:00 Fix the location of INPLACE_PKG_CONF; fixes the build Spotted by Conal Elliott - - - - - 943107c8 by David Waern at 2009-01-20T19:27:39+00:00 Document H.I.Create.collectDocs better - - - - - c6252e37 by David Waern at 2009-01-20T19:29:51+00:00 Fix Trac haskell/haddock#59: TH-generated declarations disappearing This patch was contributed by Joachim Breitner (nomeata). - - - - - 3568a6af by David Waern at 2009-01-21T21:41:48+00:00 Do not indicate that a constructor argument is unboxed We only show the strictness annotation for an unboxed constructor argument. The fact that it is unboxed is an implementation detail and should not be part of the module interface. - - - - - 562a4523 by David Waern at 2009-01-22T18:53:49+00:00 Fix Trac haskell/haddock#50: do not attach docs to pragmas or other kinds of non-declarations We now filter out everything that is not a proper Haskell declaration before collecting the docs and attaching them to declarations. - - - - - 6fdf21c2 by David Waern at 2009-01-22T19:48:09+00:00 Add test for quasi quotation. No reference output yet. - - - - - dc4100fd by David Waern at 2009-01-22T19:57:47+00:00 Improve quasi-quotation test and add reference output - - - - - 908b74bb by David Waern at 2009-01-23T23:22:03+00:00 Filter out separately exported associated types in a smarter way - - - - - f6b42ecb by David Waern at 2009-01-24T16:54:39+00:00 Correct spelling mistake in error message - - - - - 24e4245d by David Waern at 2009-01-24T17:48:03+00:00 Correct comment - - - - - b5e8462f by David Waern at 2009-02-07T13:22:29+00:00 Do not show a subordinate at the top level if its parent is also exported See note in the source code for more info. - - - - - 4b09de57 by David Waern at 2009-02-07T13:53:53+00:00 Update test following change to top level subordinates - - - - - 76379896 by David Waern at 2009-02-07T13:58:04+00:00 Remove html files in the tests/output/ directory which have been accidentally added - - - - - 1a6d8b10 by Joachim Breitner at 2009-02-20T10:29:43+00:00 Typo in comment - - - - - fec367d0 by David Waern at 2009-02-24T20:21:17+00:00 Fix small bug The rule is to prefer type constructors to other things when an identifier in a doc string can refer to multiple things. This stopped working with newer GHC versions (due to a tiny change in the GHC renamer). We implement this rule in the HTML backend for now, instead of fixing it in GHC, since we will move renaming of doc strings to Haddock in the future anyway. - - - - - 9b4172eb by David Waern at 2009-02-25T20:04:38+00:00 Fix bad error handling with newer GHCs When support for GHC 6.10 was added, an error handler was installed only around the typechecking phase. This had the effect that errors thrown during dependency chasing were caught in the top-level exception handler and not printed with enough detail. With this patch we wrap the error handler around all our usage of the Ghc monad. - - - - - de2df363 by Simon Peyton Jones at 2009-02-02T16:47:42+00:00 Hide funTyConName, now exported by TypeRep - - - - - 4d40a29f by Ian Lynagh at 2009-02-12T18:57:49+00:00 Don't build the library when building in the GHC tree - - - - - 1cd0abe4 by Ian Lynagh at 2009-02-13T13:58:53+00:00 Add a ghc.mk - - - - - 3d814eeb by Ian Lynagh at 2009-02-13T18:50:28+00:00 do .depend generation for haddock with the stage1 compiler This is a bit of a hack. We mkdepend with stage1 as if .depend depends on the stage2 compiler then make goes wrong: haddock's .depend gets included, which means that make won't reload until it's built, but we can't build it without the stage2 compiler. We therefore build the stage2 compiler before its .depend file is available, and so compilation fails. - - - - - b55036a4 by Ian Lynagh at 2009-02-25T01:38:13+00:00 Give haddock a wrapper on unix in the new GHC build system - - - - - 9eabfe68 by Ian Lynagh at 2009-02-25T19:21:32+00:00 Create inplace/lib/html in the new GHC build system - - - - - 93af30c7 by Ian Lynagh at 2008-11-07T19:18:23+00:00 TAG GHC 6.10.1 release - - - - - 06e6e34a by Thomas Schilling at 2009-02-24T18:11:00+00:00 Define __GHC_PATCHLEVEL__ for recent version of GHC (stable). - - - - - 680e6ed8 by Thomas Schilling at 2009-02-24T18:12:26+00:00 'needsTemplateHaskell' is not defined in current stable GHC. - - - - - 6c5619df by David Waern at 2009-02-25T22:15:23+00:00 Hide fynTyConName only for recent GHC versions - - - - - 6b2344f1 by Ian Lynagh at 2009-02-26T00:49:56+00:00 Add the module to one of haddocks warnings - - - - - e5d11c70 by David Waern at 2009-02-27T21:37:20+00:00 Bug fix We tried to filter out subordinates that were already exported through their parent. This didn't work properly since we were in some cases looking at the grand-parent and not the parent. We now properly compute all the parent-child relations of a declaration, and use this information to get the parent of a subordinate. We also didn't consider record fields with multiple parents. This is now handled correctly. We don't currently support separately exported associated types. But when we do, they should be handled correctly by this process too. Also slightly improved the warning message that we give when filtering out subordinates. - - - - - 10a79a60 by David Waern at 2009-02-27T22:08:08+00:00 Fix error message conflict The module name is already written in the beginning of the message, as seems to be the convention in Haddock. Perhaps not so clear, but we should change it everywhere in that case. Leaving it as it is for now. - - - - - c5055c7f by David Waern at 2009-02-27T22:15:17+00:00 Shorten warning message - - - - - a72fed3a by David Waern at 2009-02-28T00:53:55+00:00 Do not show package name in warning message - - - - - a5daccb2 by Ian Lynagh at 2009-03-01T14:59:35+00:00 Install haddock in the new GHC build system - - - - - dfdb025c by Ian Lynagh at 2009-03-07T23:56:29+00:00 Relax base dependency to < 4.2, not < 4.1 - - - - - 5769c8b4 by David Waern at 2009-03-21T14:58:52+00:00 Bump .haddock file version number (due to change of format) - - - - - f1b8f67b by David Waern at 2009-03-21T14:59:26+00:00 Define __GHC_PATCHLEVEL__=1 when using ghc-6.10.1 - - - - - 23f78831 by David Waern at 2009-03-21T16:40:52+00:00 Update CHANGES - - - - - 7d2735e9 by David Waern at 2009-03-21T16:50:33+00:00 Update ANNOUNCE - - - - - 0771e00a by David Waern at 2009-03-21T16:54:40+00:00 Update ANNOUNCE, again - - - - - 81a6942a by David Waern at 2009-03-21T17:50:06+00:00 Don't be too verbose in CHANGES - - - - - 29861dcf by David Waern at 2009-03-21T18:03:31+00:00 TAG 2.4.2 - - - - - a585f285 by David Waern at 2009-03-21T19:20:29+00:00 Require Cabal >= 1.2.3 - - - - - 7c611662 by David Waern at 2009-03-21T19:21:48+00:00 TAG 2.4.2 with cabal-version >= 1.2.3 - - - - - 23b7deff by Simon Marlow at 2009-03-20T15:43:42+00:00 new GHC build system: use shell-wrappers macro - - - - - 25f8afe7 by Ian Lynagh at 2009-03-21T19:13:53+00:00 Fix (with a hack?) haddock in teh new build system - - - - - 6a29a37e by David Waern at 2009-03-24T22:10:15+00:00 Remove unnecessary LANGUAGE pragma - - - - - 954da57d by David Waern at 2009-03-24T22:21:23+00:00 Fix warnings in H.B.DevHelp - - - - - 1619f1df by David Waern at 2009-03-26T23:20:44+00:00 -Wall police in H.B.Html - - - - - b211e13b by Simon Marlow at 2009-03-24T13:00:56+00:00 install Haddock's html stuff - - - - - 78e0b107 by David Waern at 2008-12-07T19:58:53+00:00 Add verbosity flag and utils, remove "verbose" flag - - - - - 913dae06 by David Waern at 2008-12-07T20:01:05+00:00 Add some basic "verbose" mode logging in H.Interface - - - - - 1cbff3bf by David Waern at 2009-03-27T00:07:26+00:00 Fix conflicts - - - - - 22f82032 by David Waern at 2009-03-27T21:15:11+00:00 Remove H.GHC.Typecheck - - - - - 81557804 by David Waern at 2009-03-27T21:19:22+00:00 Remove docNameOrig and use getName everywhere instead - - - - - d8267213 by David Waern at 2009-03-27T21:21:46+00:00 Use docNameOcc instead of nameOccName . getName - - - - - 5d55deab by David Waern at 2009-03-27T21:33:04+00:00 Remove H.DocName and put DocName in H.Types - - - - - 8ba72611 by David Waern at 2009-03-27T22:06:26+00:00 Document DocName - - - - - 605f8ca5 by David Waern at 2009-03-27T22:45:21+00:00 -Wall police - - - - - e4da93ae by David Waern at 2009-03-27T23:12:53+00:00 -Wall police in H.B.Hoogle - - - - - bb255519 by David Waern at 2009-03-27T23:41:28+00:00 Define Foldable and Traversable instances for Located - - - - - f1195cfe by David Waern at 2009-03-27T23:51:34+00:00 Wibble - - - - - 23818d7c by David Waern at 2009-03-28T00:03:55+00:00 -Wall police in H.I.Rename - - - - - 0f050d67 by David Waern at 2009-03-28T00:15:15+00:00 -Wall police in H.I.AttachInstances - - - - - 0f3fe038 by David Waern at 2009-03-28T21:09:41+00:00 Wibble - - - - - 275d4865 by David Waern at 2009-03-28T21:27:06+00:00 Layout fix - - - - - 54ff0ef8 by David Waern at 2009-03-28T21:59:07+00:00 -Wall police in H.I.Create - - - - - 7f58b117 by David Waern at 2009-03-28T22:10:19+00:00 -Wall police in H.Interface - - - - - f0c03b44 by David Waern at 2009-03-28T22:22:59+00:00 -Wall police in Main - - - - - 29da355c by David Waern at 2009-03-28T22:23:39+00:00 Turn on -Wall -Werror - - - - - 446d3060 by David Waern at 2009-04-01T20:40:30+00:00 hlint police - - - - - 3867c9fc by David Waern at 2009-04-01T20:48:42+00:00 hlint police - - - - - bd1f1600 by David Waern at 2009-04-01T20:58:02+00:00 hlint police - - - - - e0e90866 by David Waern at 2009-04-05T12:42:53+00:00 Move H.GHC.Utils to H.GhcUtils - - - - - 9cbd426b by David Waern at 2009-04-05T12:57:21+00:00 Remove Haddock.GHC and move its (small) contents to Main - - - - - b5c2cbfd by David Waern at 2009-04-05T13:07:04+00:00 Fix whitespace and stylistic issues in Main - - - - - 3c04aa56 by porges at 2008-12-07T08:22:19+00:00 add unicode output - - - - - 607918da by David Waern at 2009-04-26T15:09:43+00:00 Resolve conflict - - - - - 4bec6b6b by Simon Marlow at 2009-05-13T10:00:31+00:00 fix markup - - - - - 436ad6f4 by Simon Marlow at 2009-03-23T11:54:45+00:00 clean up - - - - - bdcd1398 by Simon Marlow at 2009-03-24T10:36:45+00:00 new GHC build system: add $(exeext) - - - - - 9c0972f3 by Simon Marlow at 2009-03-24T11:04:31+00:00 update for new GHC build system layout - - - - - d0f3f83a by Ian Lynagh at 2009-03-29T15:31:43+00:00 GHC new build system fixes - - - - - 5a8245c2 by Ian Lynagh at 2009-04-04T20:44:23+00:00 Tweak new build system - - - - - 9c6f2d7b by Simon Marlow at 2009-05-13T10:01:27+00:00 add build instructions for GHC - - - - - 66d07c76 by Ian Lynagh at 2009-05-31T00:37:53+00:00 Quote program paths in ghc.mk - - - - - bb7de2cd by Ian Lynagh at 2009-06-03T22:57:55+00:00 Use a bang pattern on an unlifted binding - - - - - 3ad283fc by Ian Lynagh at 2009-06-13T16:17:50+00:00 Include haddock in GHC bindists - - - - - ac447ff4 by David Waern at 2009-06-24T21:07:50+00:00 Delete Haddock.Exception and move contents to Haddock.Types Only a few lines of code that mainly declares a type - why not just put it in Haddock.Types. - - - - - 4464fb9b by David Waern at 2009-06-24T22:23:23+00:00 Add Haddock module headers Add a proper Haddock module header to each module, with a more finegrained copyright. If you feel mis-accreditted, please correct any copyright notice! The maintainer field is set to haddock at projects.haskell.org. Next step is to add a brief description to each module. - - - - - 5f4c95dd by David Waern at 2009-06-24T22:39:44+00:00 Fix spelling error - - - - - 6d074cdb by David Waern at 2009-06-25T21:53:56+00:00 Document Interface and InstalledInterface better - - - - - d0cbd183 by David Waern at 2009-06-27T12:46:46+00:00 Remove misplaced whitespace in H.I.Rename - - - - - fa381c49 by David Waern at 2009-06-27T13:26:03+00:00 Fix haskell/haddock#104 - create output directory if missing - - - - - 91fb77ae by Ian Lynagh at 2009-06-25T15:59:50+00:00 TAG 2009-06-25 - - - - - 0d853f40 by Simon Peyton Jones at 2009-07-02T15:35:22+00:00 Follow extra field in ConDecl - - - - - b201735d by Ian Lynagh at 2009-07-05T16:50:35+00:00 Update Makefile for the new GHC build system - - - - - df6c0092 by Ian Lynagh at 2009-07-05T17:01:13+00:00 Resolve conflicts - - - - - 1066870a by Ian Lynagh at 2009-07-05T17:01:48+00:00 Remove the -Wwarn hack in the GHC build system - - - - - 7e856076 by Ian Lynagh at 2009-07-05T17:17:59+00:00 Fix warnings - - - - - 5d4cd958 by Ian Lynagh at 2009-07-05T19:35:40+00:00 Bump version number Cabal needs to distinguish between haddocks having a --verbose and --verbosity flag - - - - - 6ee07c99 by David Waern at 2009-07-06T20:14:57+00:00 Wibble - - - - - 2308b66f by David Waern at 2009-07-06T20:24:20+00:00 Clearer printing of versions by runtests.hs - - - - - d4b5d9ab by David Waern at 2009-07-06T21:22:42+00:00 Fix (invisible) bug introduced by unicode patch - - - - - 2caca8d8 by David Waern at 2009-07-06T21:44:10+00:00 Use HscAsm instead of HscC when using TH - - - - - 18f3b755 by David Waern at 2009-07-06T22:10:22+00:00 Update HCAR entry (by Janis) - - - - - a72ac9db by David Waern at 2009-07-06T23:01:35+00:00 Follow HsRecTy change with an #if __GLASGOW_HASKEL__ >= 611 - - - - - 549135d2 by David Waern at 2009-07-06T23:11:41+00:00 Remove unused functions from Haddock.Utils - - - - - b450134a by Isaac Dupree at 2009-07-11T14:59:00+00:00 revert to split-index for large indices - remove the search-box, because browsers have search-for-text abilities anyway. - pick 150 items in index as the arbitrary time at which to split it - notice the bug that identifiers starting with non-ASCII characters won't be listed in split-index, but don't bother to fix it yet (see ticket haskell/haddock#116, http://trac.haskell.org/haddock/ticket/116 ) - - - - - 78a5661e by Isaac Dupree at 2009-07-20T15:37:18+00:00 Implement GADT records in HTML backend - - - - - 4e163555 by Isaac Dupree at 2009-07-21T22:03:25+00:00 add test for GADT records - - - - - 79aa4d6e by David Waern at 2009-07-23T20:40:37+00:00 Update test suite following version bump - - - - - 5932c011 by David Waern at 2009-08-02T10:25:39+00:00 Fix documentation bug - - - - - a6970fca by David Waern at 2009-08-12T23:08:53+00:00 Remove support for ghc 6.8.* from .cabal file - - - - - c1695902 by Ian Lynagh at 2009-07-07T13:35:45+00:00 Fix unused import warnings - - - - - fb6df7f9 by Ian Lynagh at 2009-07-16T00:20:31+00:00 Use cProjectVersion directly rather than going through compilerInfo Fixes the build after changes in GHC - - - - - 548cdd66 by Simon Marlow at 2009-07-28T14:27:04+00:00 follow changes in GHC's ForeignType - - - - - 9395aaa0 by David Waern at 2009-08-13T22:17:33+00:00 Switch from PatternSignatures to ScopedTypeVariables in Main - - - - - eebf39bd by David Waern at 2009-08-14T17:14:28+00:00 Version .haddock files made with GHC 6.10.3/4 correclty - - - - - 58f3e735 by David Waern at 2009-08-14T17:19:37+00:00 Support GHC 6.10.* and 6.11.* only - - - - - 5f63cecc by David Waern at 2009-08-14T22:03:20+00:00 Do not version .haddock file based on GHC patchlevel version We require that the instances of Binary that we use from GHC will not change between patchlevel versions. - - - - - d519de9f by David Waern at 2009-08-14T23:50:00+00:00 Update CHANGES - - - - - 35dccf5c by David Waern at 2009-08-14T23:51:38+00:00 Update version number everywhere - - - - - 6d363fea by David Waern at 2009-08-15T09:46:49+00:00 Update ANNOUNCE - - - - - c7ee6bc2 by David Waern at 2009-08-15T09:47:13+00:00 Remove -Werror Forgot that Hackage doesn't like it. - - - - - a125c12b by David Waern at 2009-08-15T09:49:50+00:00 Require Cabal >= 1.6 - - - - - adb2f560 by Isaac Dupree at 2009-08-12T03:47:14+00:00 Cross-Package Documentation version 4 - - - - - 3d6dc04d by David Waern at 2009-08-15T23:42:57+00:00 Put all the IN_GHC_TREE stuff inside getGhcLibDir - - - - - 56624097 by David Waern at 2009-08-15T23:52:03+00:00 Add --print-ghc-libdir - - - - - f15d3ccb by David Waern at 2009-08-16T00:37:52+00:00 Read base.haddock when running tests We can now test cross-package docs. - - - - - 283f0fb9 by David Waern at 2009-08-16T00:50:59+00:00 Update test output - we now have more links - - - - - 673d1004 by David Waern at 2009-08-16T01:26:08+00:00 Read process.haddock when running tests - - - - - 0d127f82 by David Waern at 2009-08-16T01:43:04+00:00 Add a test for cross-package documentation - - - - - f94db967 by Ian Lynagh at 2009-08-16T18:42:44+00:00 Follow GHC build system changes - - - - - 5151278a by Isaac Dupree at 2009-08-16T19:58:05+00:00 make cross-package list types look nicer - - - - - c41e8228 by Isaac Dupree at 2009-08-18T01:47:47+00:00 Haddock.Convert: export more functions This lets us remove some code in Haddock.Interface.AttachInstances - - - - - 2e5fa398 by Isaac Dupree at 2009-08-18T02:11:05+00:00 switch AttachInstances to use synify code It changed an instance from showing ((,) a b) to (a, b) because my synify code is more sophisticated; I hope the latter is a good thing rather than a bad thing aesthetically, here. But this definitely reduces code duplication! - - - - - b8b07123 by Isaac Dupree at 2009-08-18T02:23:31+00:00 Find instances using GHC, which is more complete. In particular, it works cross-package. An intermediate patch also moved the instance-finding into createInterface, but that move turned out not to be necessary, so if we want to do that, it'd go in a separate patch. (Is that possible? Or will we need GHC to have loaded all the modules first, before we can go searching for the instances (e.g. if the modules are recursive or something)?) - - - - - 6959b451 by Isaac Dupree at 2009-08-17T00:37:18+00:00 fix preprocessor conditional sense - - - - - 942823af by Isaac Dupree at 2009-08-16T22:46:48+00:00 remove ghc 6.8 conditionals from Haddock.Interface - - - - - 4b3ad888 by Isaac Dupree at 2009-08-18T20:24:38+00:00 Fix GHC 6.11 build in Haddock.Convert - - - - - 0a89c5ab by Isaac Dupree at 2009-08-23T00:08:58+00:00 hacks to make it compile without fnArgDocsn - - - - - 7b3bed43 by Isaac Dupree at 2009-08-23T03:01:28+00:00 less big-Map-based proper extraction of constructor subdocs - - - - - b21c279a by Isaac Dupree at 2009-08-23T03:02:06+00:00 Html: remove unnecessary+troublesome GHC. qualifications - - - - - 96c97115 by Isaac Dupree at 2009-08-23T03:08:03+00:00 Move doc parsing/lexing into Haddock for ghc>=6.11 - - - - - e1cec02d by Isaac Dupree at 2009-08-23T05:08:14+00:00 get rid of unused DocMap parameter in Html - - - - - 66960c59 by Isaac Dupree at 2009-08-23T05:54:20+00:00 fix horrible named-docs-disappearing bug :-) - - - - - a9d7eff3 by Isaac Dupree at 2009-08-23T06:26:36+00:00 re-implement function-argument docs ..on top of the lexParseRn work. This patch doesn't change the InstalledInterface format, and thus, it does not work cross-package, but that will be easy to add subsequently. - - - - - 8bf6852c by Isaac Dupree at 2009-08-23T07:26:05+00:00 cross-package fnArgDocs. WARNING: changes .haddock binary format While breaking the format, I took the opportunity to unrename the DocMap that's saved to disk, because there's really no reason that we want to know what *another* package's favorite place to link a Name to was. (Is that true? Or might we want to know, someday?) Also, I added instance Binary Map in InterfaceFile. It makes the code a little simpler without changing anything of substance. Also it lets us add another Map hidden inside another Map (fnArgsDocs in instDocMap) without having really-convoluted serialization code. Instances are neat! I don't understand why this change to InterfaceFile seemed to subtly break binary compatibility all by itself, but no matter, I'll just roll it into the greater format-changing patch. Done! - - - - - 30115a64 by Isaac Dupree at 2009-08-23T18:22:47+00:00 Improve behavior for unfindable .haddock - - - - - aa364bda by Isaac Dupree at 2009-08-23T18:28:16+00:00 add comment for FnArgsDoc type - - - - - 49b23a99 by Isaac Dupree at 2009-08-23T21:52:48+00:00 bugfix: restore fnArgDocs for type-synonyms - - - - - f65f9467 by Isaac Dupree at 2009-08-23T22:06:55+00:00 Backends.Hoogle: eliminate warnings - - - - - a292d216 by Isaac Dupree at 2009-08-23T22:10:24+00:00 Haddock.Convert: eliminate warnings - - - - - 5546cd20 by Isaac Dupree at 2009-08-23T22:12:31+00:00 Haddock.Interface.Rename: eliminate warnings - - - - - 0a9798b6 by Isaac Dupree at 2009-08-23T22:18:47+00:00 Main.hs: remove ghc<6.9 conditionals - - - - - e8f9867f by Isaac Dupree at 2009-08-23T22:27:46+00:00 Main.hs: eliminate warnings (except for OldException) - - - - - 61c64247 by Isaac Dupree at 2009-08-23T22:41:01+00:00 move get*LibDir code in Main.hs, to +consistent code, -duplication - - - - - 948f1e69 by Isaac Dupree at 2009-08-23T23:14:26+00:00 Main.hs: OldException->Exception: which eliminates warnings - - - - - 3d5d5e03 by Isaac Dupree at 2009-08-23T23:20:11+00:00 GhcUtils: ghc >= 6.10 - - - - - 2771d657 by Isaac Dupree at 2009-08-23T23:21:55+00:00 InterfaceFile: ghc >= 6.10 - - - - - d9f2b9d1 by Isaac Dupree at 2009-08-23T23:22:58+00:00 Types: ghc >= 6.10 - - - - - ca39210e by Isaac Dupree at 2009-08-23T23:23:26+00:00 ModuleTree: ghc >= 6.10 - - - - - 883c4e59 by Isaac Dupree at 2009-08-23T23:24:04+00:00 Backends.DevHelp: ghc >= 6.10 - - - - - 04667df5 by Isaac Dupree at 2009-08-23T23:24:37+00:00 Backends.Html: ghc >= 6.10 - - - - - a9f7f25f by Isaac Dupree at 2009-08-23T23:25:24+00:00 Utils: ghc >= 6.10 - - - - - b7105022 by Isaac Dupree at 2009-08-23T23:37:47+00:00 eliminate haskell98 dependency, following GHC's example It turns out I/we already had, and it was only a matter of deleting it from the cabal file. - - - - - 292e0911 by Isaac Dupree at 2009-08-24T01:22:44+00:00 refactor out subordinatesWithNoDocs dep of inferenced-decls fix - - - - - c2ed46a2 by Isaac Dupree at 2009-08-24T01:24:03+00:00 Eradicate wrong runtime warning for type-inferenced exported-functions see the long comment in the patch for why I did it this way :-) - - - - - 4ac0b57c by David Waern at 2009-09-04T22:56:20+00:00 Clean up tyThingToHsSynSig a little Factor out noLoc and use the case construct. Also rename the function to tyThingToLHsDecl, since it doesn't just create type signatures. - - - - - 28ab9201 by David Waern at 2009-09-04T22:58:50+00:00 Wibble - - - - - 0d9fe6d0 by David Waern at 2009-09-06T18:39:30+00:00 Add more copyright owners to H.I.AttachInstances - - - - - 122441b1 by David Waern at 2009-09-06T18:44:12+00:00 Style police - - - - - 1fa79463 by David Waern at 2009-09-06T18:57:45+00:00 Move toHsInstHead to Haddock.Convert and call it synifyInstHead - - - - - 0d42a8aa by David Waern at 2009-09-06T21:11:38+00:00 Use colordiff to display test results if available - - - - - ea9d8e03 by Simon Marlow at 2009-08-24T08:46:14+00:00 Follow changes in GHC's interface file format Word32 instead of Int for FastString and Name offsets - - - - - 537e051e by Simon Marlow at 2009-07-29T14:16:53+00:00 define unpackPackageId (it was removed from GHC) - - - - - 50c63aa7 by David Waern at 2009-09-09T23:18:03+00:00 Remove commented-out code - - - - - 511631fe by David Waern at 2009-09-09T23:19:05+00:00 Correct copyright in H.I.ParseModuleHeader - - - - - 898ec768 by David Waern at 2009-09-11T11:22:29+00:00 Use Map.fromList/toList intead of fromAscList/toAscList when serializing Maps This fixes the missing docs problem. The Eq and Ord instances for Name uses the unique number in Name. This number is created at deserialization time by GHC's magic Binary instance for Name, and it is random. Thus, fromAscList can't be used at deserialization time, even though toAscList was used at serialization time. - - - - - 37bec0d5 by Simon Peyton Jones at 2009-09-11T08:28:04+00:00 Track change in HsType - - - - - eb3a97c3 by Ian Lynagh at 2009-09-11T16:07:09+00:00 Allow building with base 4.2 - - - - - bb4205ed by Ian Lynagh at 2009-09-22T13:50:02+00:00 Loosen the GHC dependency - - - - - 5c75deb2 by Ian Lynagh at 2009-09-22T14:08:39+00:00 Fix building with GHC >= 6.12 - - - - - fb131481 by David Waern at 2009-09-11T11:24:48+00:00 Update runtests.hs to work with GHC 6.11 - - - - - ac3a419d by David Waern at 2009-09-11T11:25:14+00:00 Update CrossPackageDocs test - - - - - ec65c3c6 by David Waern at 2009-09-11T11:25:40+00:00 Add reference output for CrossPackageDocs - - - - - 520c2758 by Ian Lynagh at 2009-10-25T17:26:40+00:00 Fix installation in the GHC build system - - - - - 28b3d7df by Ian Lynagh at 2009-11-05T15:57:27+00:00 GHC build system: Make *nix installation work in paths containing spaces - - - - - 5c9bb541 by David Waern at 2009-11-14T11:56:39+00:00 Track change in HsType for the right compiler version - - - - - 905097ce by David Waern at 2009-11-14T12:10:47+00:00 hlint police - - - - - 04920630 by Ian Lynagh at 2009-11-20T13:46:30+00:00 Use defaultObjectTarget rather than HscAsm This fixes haddock when we don't have a native code generator - - - - - 966eb079 by David Waern at 2009-11-15T12:32:21+00:00 Remove commented-out code - - - - - 37f00fc4 by David Waern at 2009-11-22T13:58:48+00:00 Make runtests.hs strip links before diffing Generates easier to read diffs when tests fail. The content of the links is not important anyway since it is not taken into account by the tests. - - - - - 3a9bb8ef by David Waern at 2009-11-22T14:05:06+00:00 Follow findProgramOnPath signature change in runtests.hs - - - - - b26b9e5a by David Waern at 2009-11-22T14:08:40+00:00 Follow removal of GHC.MVar from base in CrossPackageDocs - - - - - f4d90ae4 by David Waern at 2009-11-22T14:48:47+00:00 Make copy.hs strip link contents before copying No more updating of reference files when URLs in links changes. - - - - - 4c9c420d by David Waern at 2009-11-22T15:26:41+00:00 Update test reference output * More links (Int, Float etc) * Stripped link contents - - - - - a62b80e3 by David Waern at 2009-11-23T23:19:39+00:00 Update CrossPackageDocs reference output - Remove GHC.MVar import (removed from base) - Strip link contents - - - - - 43491394 by David Waern at 2009-11-23T23:20:00+00:00 Update test reference files with comments on instances - - - - - 0d370a0b by David Waern at 2009-11-23T23:25:16+00:00 Bump version number - - - - - 2293113e by David Waern at 2009-11-24T20:55:49+00:00 Comments on instances Implementing this was a little trickier than I thought, since we need to match up instances from the renamed syntax with instances represented by InstEnv.Instance. This is due to the current design of Haddock, which matches comments with declarations from the renamed syntax, while getting the list of instances of a class/family directly using the GHC API. - Works for class instances only (Haddock has no support for type family instances yet) - The comments are rendered to the right of the instance head in the HTML output - No change to the .haddock file format - Works for normal user-written instances only. No comments are added on derived or TH-generated instances - - - - - bf586f29 by David Waern at 2009-11-27T22:05:15+00:00 Whitespace police - - - - - b8f03afa by David Waern at 2009-11-27T22:11:46+00:00 Remove bad whitespace and commented-out pieces - - - - - 90b8ee90 by David Waern at 2009-11-27T22:15:04+00:00 Whitespace police - - - - - b5ede900 by David Waern at 2009-11-27T22:15:50+00:00 Whitespace police - - - - - e3fddbfe by David Waern at 2009-11-28T13:37:59+00:00 Remove Name from DocInstance It's not used. - - - - - 9502786c by David Waern at 2009-11-28T13:56:54+00:00 Require at least GHC 6.12 While regression testing Haddock, I found a bug that happens with GHC 6.10.3, but not with GHC 6.12-rc2 (haven't tried 6.10.4). I don't have time to track it down. I think we should just always require the latest major GHC version. The time spent on making Haddock work with older versions is too high compared to the time spent on bugfixing, refactoring and features. - - - - - 8fa688d8 by David Waern at 2009-11-28T15:05:03+00:00 Remove cruft due to compatibility with older GHCs - - - - - 46fbbe9d by David Waern at 2009-11-28T15:07:50+00:00 Add a documentation header to Haddock.Convert - - - - - c3d2cc4a by David Waern at 2009-11-28T15:10:14+00:00 Remove unused H.Utils.FastMutInt2 - - - - - 490aba80 by David Waern at 2009-11-28T15:36:36+00:00 Rename Distribution.Haddock into Documentation.Haddock - - - - - 33ee2397 by David Waern at 2009-11-28T15:36:47+00:00 Fix error message - - - - - a5a3b950 by David Waern at 2009-11-28T16:58:39+00:00 Add a test flag that brings in QuickCheck - - - - - fa049e13 by David Waern at 2009-11-28T19:32:18+00:00 Say that we want quickcheck 2 - - - - - f32b0d9b by David Waern at 2009-11-28T19:32:40+00:00 Add an Arbitrary instance for HsDoc - - - - - da9a8bd7 by David Waern at 2009-11-28T20:15:30+00:00 Rename HsDoc back into Doc - - - - - edb60101 by David Waern at 2009-11-28T22:16:16+00:00 Move H.Interface.Parse/Lex to H.Parse/Lex These are not just used to build Interfaces. - - - - - 0656a9b8 by David Waern at 2009-11-28T23:12:14+00:00 Update version number in test suite - - - - - 5e8c6f4a by David Waern at 2009-12-21T14:12:41+00:00 Improve doc of DocName - - - - - 7868e551 by Ian Lynagh at 2009-09-22T10:43:03+00:00 TAG GHC 6.12-branch created - - - - - 0452a3ea by Ian Lynagh at 2009-12-15T12:46:07+00:00 TAG GHC 6.12.1 release - - - - - 65e9be62 by David Waern at 2009-12-21T16:58:58+00:00 Update CHANGES - - - - - 145cee32 by David Waern at 2009-12-21T16:59:09+00:00 TAG 2.6.0 - - - - - 3c552008 by David Waern at 2009-12-22T17:11:14+00:00 Update ANNOUNCE - - - - - 931f9db4 by David Waern at 2010-01-22T19:57:17+00:00 Convert haddock.vim to use unix newlines - - - - - 4e56588f by David Waern at 2010-01-22T22:11:17+00:00 Remove unnecessary (and inexplicable) uses of nub - - - - - 744bb4d1 by David Waern at 2010-01-22T22:12:14+00:00 Follow move of parser and lexer - - - - - e34bab14 by David Waern at 2010-01-22T22:49:13+00:00 Use findProgramLocation instead of findProgramOnPath in runtests.hs - - - - - 8d39891b by Isaac Dupree at 2010-01-14T18:53:18+00:00 fix html arg-doc off-by-one and silliness - - - - - 9401f2e9 by David Waern at 2010-01-22T22:57:03+00:00 Create a test for function argument docs - - - - - 507a82d7 by David Waern at 2010-01-22T23:24:47+00:00 Put parenthesis around type signature arguments of function type - - - - - 8a305c28 by David Waern at 2010-01-23T17:26:59+00:00 Add reference file for the FunArgs test - - - - - 1309d5e1 by David Waern at 2010-01-24T16:05:08+00:00 Improve FunArg test and update Test.html.ref - - - - - 2990f055 by Yitzchak Gale at 2010-02-14T16:03:46+00:00 Do not generate illegal character in HTML ID attribute. - - - - - c5bcab7a by David Waern at 2010-02-22T22:10:30+00:00 Fix Haddock markup error in comment - - - - - c6416a73 by David Waern at 2010-02-24T22:55:08+00:00 Large additions to the Haddock API Also improved and added more doc comments. - - - - - 57d289d7 by David Waern at 2010-02-24T22:58:02+00:00 Remove unused ifaceLocals - - - - - 80528d93 by David Waern at 2010-02-25T21:05:09+00:00 Add HaddockModInfo to the API - - - - - 82806848 by David Waern at 2010-02-25T21:05:27+00:00 Wibble - - - - - 744cad4c by David Waern at 2010-02-25T23:30:59+00:00 Make it possible to run a single test - - - - - 6a806e4c by David Waern at 2010-03-14T14:19:39+00:00 Bump version number - - - - - a5a8e4a7 by David Waern at 2010-03-14T14:36:35+00:00 Update ANNOUNCE - - - - - 6f05435e by Simon Hengel at 2010-03-15T20:52:42+00:00 Add missing dependencies for 'library' in haddock.cabal - - - - - faefe2bd by David Waern at 2010-03-15T22:29:37+00:00 Solve conflicts - - - - - 9808ad52 by David Waern at 2010-03-15T22:51:21+00:00 Bump version number - - - - - eb0bf60b by David Waern at 2010-03-15T22:52:32+00:00 Update CHANGES - - - - - f95cd891 by David Waern at 2010-03-15T23:01:06+00:00 Add Paths_haddock to other-modules of library - - - - - 65997b0a by David Waern at 2010-03-15T23:14:59+00:00 Update CHANGES - - - - - 7e251731 by David Waern at 2010-03-15T23:15:30+00:00 Bump version number - - - - - c9cd0ddc by David Waern at 2010-03-16T00:28:34+00:00 Fix warning - - - - - 1cac2d93 by Simon Peyton Jones at 2010-01-04T15:22:16+00:00 Fix imports for new location of splitKindFunTys - - - - - 474f26f6 by Simon Peyton Jones at 2010-02-10T14:36:06+00:00 Update Haddock for quasiquotes - - - - - 0dcc06c0 by Simon Peyton Jones at 2010-02-10T10:59:45+00:00 Track changes in HsTyVarBndr - - - - - 2d84733a by Simon Peyton Jones at 2010-02-10T14:52:44+00:00 Track HsSyn chnages - - - - - 9e3adb8b by Ian Lynagh at 2010-02-20T17:09:42+00:00 Resolve conflicts - - - - - a3e72ff8 by Simon Peyton Jones at 2010-03-04T13:05:16+00:00 Track change in HsUtils; and use a nicer function not an internal one - - - - - 27994854 by David Waern at 2010-03-18T22:22:27+00:00 Fix build with GHC 6.12.1 - - - - - 11f6e488 by David Waern at 2010-03-18T22:24:09+00:00 Bump version in test reference files - - - - - 0ef2f11b by David Waern at 2010-03-20T00:56:30+00:00 Fix library part of cabal file when in ghc tree - - - - - 3f6146ff by Mark Lentczner at 2010-03-20T22:30:11+00:00 First, experimental XHTML rendering switch to using the xhtml package copied Html.hs to Xhtml.hs and split into sub-modules under Haddock/Backends/Xhtml and detabify moved footer into div, got ready for iface change headers converted to semantic markup contents in semantic markup summary as semantic markup description in semantic markup, info block in header fixed factored out rendering so during debug it can be readable (see renderToString) - - - - - b8ab329b by Mark Lentczner at 2010-03-20T22:54:01+00:00 apply changes to Html.hs to Xhtml/*.hs incorporate changes that were made between the time Html.hs was copied and split into Xhtml.hs and Xhtml/*.hs includes patchs after "Wibble" (!) through "Fix build with GHC 6.12.1" - - - - - 73df2433 by Ian Lynagh at 2010-03-20T21:56:37+00:00 Follow LazyUniqFM->UniqFM in GHC - - - - - db4f602b by David Waern at 2010-03-29T22:00:01+00:00 Fix build with GHC 6.12 - - - - - d8dca088 by Simon Hengel at 2010-04-02T16:39:55+00:00 Add missing dependencies to cabal file - - - - - e2adc437 by Simon Hengel at 2010-04-02T14:08:40+00:00 Add markup support for interactive examples - - - - - e882ac05 by Simon Hengel at 2010-04-02T14:11:53+00:00 Add tests for interactive examples - - - - - 5a07a6d3 by David Waern at 2010-04-07T17:05:20+00:00 Propagate source positions from Lex.x to Parse.y - - - - - 6493b46f by David Waern at 2010-04-07T21:48:57+00:00 Let runtests.hs die when haddock has not been built - - - - - 5e34423e by David Waern at 2010-04-07T22:01:13+00:00 Make runtests.hs slightly more readable - - - - - 321d59b3 by David Waern at 2010-04-07T22:13:27+00:00 Fix haskell/haddock#75 Add colons to the $ident character set. - - - - - 37b08b8d by David Waern at 2010-04-08T00:32:52+00:00 Fix haskell/haddock#118 Avoid being too greedy when lexing URL markup (<..>), in order to allow multiple URLs on the same line. Do the same thing with <<..>> and #..#. - - - - - df8feac9 by David Waern at 2010-04-08T00:57:33+00:00 Make it easier to add new package deps to test suite This is a hack - we should use Cabal to get the package details instead. - - - - - 1ca6f84b by David Waern at 2010-04-08T01:03:06+00:00 Add ghc-prim to test suite deps - - - - - 27371e3a by Simon Hengel at 2010-04-08T19:26:34+00:00 Let parsing fails on paragraphs that are immediately followed by an example This is more consistent with the way we treat code blocks. - - - - - 83096e4a by David Waern at 2010-04-08T21:20:00+00:00 Improve function name - - - - - 439983ce by David Waern at 2010-04-10T10:46:14+00:00 Fix haskell/haddock#112 No link was generated for 'Addr#' in a doc comment. The reason was simply that the identifier didn't parse. We were using parseIdentifier from the GHC API, with a parser state built from 'defaultDynFlags'. If we pass the dynflags of the module instead, the right options are turned on on while parsing the identifer (in this case -XMagicHash), and the parse succeeds. - - - - - 5c0d35d7 by David Waern at 2010-04-10T10:54:06+00:00 Rename startGhc into withGhc - - - - - dca081fa by Simon Hengel at 2010-04-12T19:09:16+00:00 Add documentation for interactive examples - - - - - c7f26bfa by David Waern at 2010-04-13T00:51:51+00:00 Slight fix to the documentation of examples - - - - - 06eb7c4c by David Waern at 2010-04-13T00:57:05+00:00 Rename Interactive Examples into Examples (and simplify explanation) - - - - - 264830cb by David Waern at 2010-05-10T20:07:27+00:00 Update CHANGES with info about 2.6.1 - - - - - 8e5d4514 by Simon Hengel at 2010-04-18T18:16:54+00:00 Add unit tests for parser - - - - - 68297f40 by David Waern at 2010-05-10T21:53:37+00:00 Improve testsuite README - - - - - f04eb6e4 by David Waern at 2010-05-11T19:14:31+00:00 Re-organise the testsuite structure - - - - - a360f710 by David Waern at 2010-05-11T19:18:03+00:00 Shorten function name - - - - - 1d5dd359 by David Waern at 2010-05-11T21:40:02+00:00 Update runtests.hs following testsuite re-organisation - - - - - ffebe217 by David Waern at 2010-05-11T21:40:10+00:00 Update runtests.hs to use base-4.2.0.1 - - - - - 635de402 by David Waern at 2010-05-11T21:41:11+00:00 Update runparsetests.hs following testsuite reorganisation - - - - - 72137910 by Ian Lynagh at 2010-05-06T20:43:06+00:00 Fix build - - - - - 1a80b76e by Ian Lynagh at 2010-05-06T22:25:29+00:00 Remove redundant import - - - - - 1031a80c by Simon Peyton Jones at 2010-05-07T13:21:09+00:00 Minor wibbles to HsBang stuff - - - - - dd8e7fe5 by Ian Lynagh at 2010-05-08T15:22:00+00:00 GHC build system: Follow "rm" variable changes - - - - - 7f5e6748 by David Waern at 2010-05-13T11:53:02+00:00 Fix build with GHC 6.12.2 - - - - - 7953d4d8 by David Waern at 2010-05-13T18:45:01+00:00 Fixes to comments only - - - - - 8ae8eb64 by David Waern at 2010-05-13T18:57:26+00:00 ModuleMap -> IfaceMap - - - - - 1c3eadc6 by David Waern at 2010-05-13T19:03:13+00:00 Fix whitespace style issues - - - - - e96783c0 by David Waern at 2010-05-13T19:08:53+00:00 Fix comment - - - - - c998a78b by David Waern at 2010-05-13T19:39:00+00:00 Position the module header the same way everywhere Silly, but nice with some consistency :-) - - - - - b48a714e by David Waern at 2010-05-13T19:41:32+00:00 Position of module header, this time in the HTML backends - - - - - f9bfb12e by David Waern at 2010-05-13T19:43:05+00:00 Two newlines between declarations in Main - - - - - 071d44c7 by David Waern at 2010-05-13T19:44:21+00:00 Newlines in Convert - - - - - 036346db by David Waern at 2010-05-13T19:46:47+00:00 Fix a few stylistic issues in H.InterfaceFile - - - - - f0b8379e by David Waern at 2010-05-13T19:47:53+00:00 Add newlines to H.ModuleTree - - - - - 27409f8e by David Waern at 2010-05-13T19:51:10+00:00 Fix stylistic issues in H.Utils - - - - - 24774a11 by David Waern at 2010-05-13T20:00:43+00:00 Structure H.Types better - - - - - 7b6f5e40 by David Waern at 2010-05-13T20:01:04+00:00 Remove bad Arbitrary instance - - - - - fac9f1f6 by David Waern at 2010-05-13T20:05:50+00:00 Get rid of H.Utils.pathJoin and use System.FilePath.joinPath instead - - - - - fe6d00c4 by David Waern at 2010-05-13T20:51:55+00:00 Export a couple of more types from the API - - - - - b2e33a5f by David Waern at 2010-05-13T21:27:51+00:00 Improve doc comment for Interface - - - - - c585f2ce by David Waern at 2010-05-13T21:30:14+00:00 Improve documentation of Haddock.Interface - - - - - e6791db2 by David Waern at 2010-05-13T22:07:35+00:00 Remove meaningless comments - - - - - 7801b390 by David Waern at 2010-05-14T17:53:33+00:00 Remove unused modules - - - - - f813e937 by David Waern at 2010-05-14T17:55:17+00:00 Re-direct compilation output to a temporary directory Also add a flag --no-tmp-comp-dir that can be used to get the old behaviour of writing compilation files to GHC's output directory (default "."). - - - - - e56737ec by David Waern at 2010-05-14T18:06:11+00:00 Wibble - - - - - e40b0447 by David Waern at 2010-05-14T19:01:52+00:00 Move flag evaluation code from Main to Haddock.Options Determining the value of "singular" flags (by e.g. taking the last occurrence of the flag) and other flag evaluation should done in Haddock.Options which is the module that is supposed to define the command line interface. This makes Main a bit easier on the eyes as well. - - - - - 27091f57 by David Waern at 2010-05-14T19:05:10+00:00 Wibble - - - - - c658cf61 by David Waern at 2010-05-14T19:06:49+00:00 Re-order things in Haddock.Options a bit - - - - - 8cfdd342 by David Waern at 2010-05-14T19:20:29+00:00 De-tabify Haddock.Options and fix other whitespace issues - - - - - 0df16b62 by David Waern at 2010-05-14T19:25:07+00:00 Improve comments - - - - - 80b38e2b by David Waern at 2010-05-14T19:26:42+00:00 Whitespace police - - - - - fe580255 by David Waern at 2010-05-14T19:31:23+00:00 Wibbles to comments - - - - - a2b43fad by David Waern at 2010-05-14T20:24:32+00:00 Move some more flag functions to Haddock.Options - - - - - 3f895547 by David Waern at 2010-05-14T20:37:12+00:00 Make renderStep a top-level function in Main - - - - - 5cdca11d by David Waern at 2010-05-14T20:39:27+00:00 Spelling in comment - - - - - ad98d14c by David Waern at 2010-05-14T20:40:26+00:00 Comment fixes - - - - - 0bb9218f by David Waern at 2010-05-14T20:49:01+00:00 Whitespace police - - - - - 0f0a533f by David Waern at 2010-05-15T16:42:29+00:00 Improve description of --dump-interface - - - - - 5b2833ac by David Waern at 2010-05-15T17:16:53+00:00 Document --no-tmp-comp-dir - - - - - 8160b170 by David Waern at 2010-05-15T17:18:59+00:00 Wibble - - - - - 570dbe33 by David Waern at 2010-05-18T21:15:38+00:00 HLint police - - - - - 204e425f by David Waern at 2010-05-18T21:16:30+00:00 HLint police - - - - - 6db657ac by David Waern at 2010-05-18T21:16:37+00:00 Wibble - - - - - b942ccd7 by Simon Marlow at 2010-06-02T08:27:30+00:00 Interrupted disappeared in GHC 6.13 (GHC ticket haskell/haddock#4100) - - - - - 3b94a819 by Simon Marlow at 2010-06-02T08:45:08+00:00 Allow base-4.3 - - - - - c5a1fb7c by Simon Marlow at 2010-06-02T09:03:04+00:00 Fix compilation with GHC 6.13 - - - - - 6181296c by David Waern at 2010-06-08T21:09:05+00:00 Display name of prologue file when parsing it fails - - - - - 7cbc6f60 by Ian Lynagh at 2010-06-13T16:20:25+00:00 Remove redundant imports - - - - - 980c804b by Simon Marlow at 2010-06-22T08:41:50+00:00 isLocalAndTypeInferenced: fix for local module names overlapping package modules - - - - - d74d4a12 by Simon Marlow at 2010-06-23T12:03:27+00:00 Unresolved identifiers in Doc get replaced with DocMonospaced rather than plain strings - - - - - d8546783 by Simon Marlow at 2010-06-30T12:45:17+00:00 LaTeX backend (new options: --latex, --latex-style=<style>) - - - - - 437afa9e by David Waern at 2010-07-01T12:02:44+00:00 Fix a few stylistic whitespace issues in LaTeX backend - - - - - 85bc1fae by David Waern at 2010-07-01T15:42:45+00:00 Make runtest.hs work with GHC 6.12.3 (we should really stop hard coding this) - - - - - 7d2eb86f by David Waern at 2010-07-01T15:43:33+00:00 Update test following Simon's patch to render unresolved names in monospaced font - - - - - 08fcbcd2 by David Waern at 2010-07-01T16:12:18+00:00 Warning police - - - - - d04a8d7a by David Waern at 2010-07-04T14:53:39+00:00 Fix a bug in attachInstances We didn't look for instance docs in all the interfaces of the package. This had the effect of instance docs not always showing up under a declaration. I took the opportunity to clean up the code in H.I.AttachInstances a bit as well. More cleanup is needed, however. - - - - - d10344eb by Simon Hengel at 2010-07-10T09:19:04+00:00 Add missing dependencies to cabal file - - - - - 24090531 by Mark Lentczner at 2010-03-21T04:51:16+00:00 add exports to Xhtml modules - - - - - 84f9a333 by Mark Lentczner at 2010-04-03T19:14:22+00:00 clean up Doc formatting code - add CSS for lists - renderToString now uses showHtml since prettyHtml messes up <pre> sections - - - - - bebccf52 by Mark Lentczner at 2010-04-04T04:51:08+00:00 tweak list css - - - - - 0c2aeb5e by Mark Lentczner at 2010-04-04T06:24:14+00:00 all decls now generate Html not HtmlTable - ppDecl return Html, and so now do all of the functions it calls - added some internal tables to some decls, which is wrong, and will have to be fixed - decl "Box" functions became "Elem" functions to make clear they aren't in a table anymore (see Layout.hs) - docBox went away, as only used in one place (and its days are numbered) - cleaned up logic in a number of places, removed dead code - added maybeDocToHtml which simplified a number of places in the code - - - - - dbf73e6e by Mark Lentczner at 2010-04-05T05:02:43+00:00 clean up processExport and place a div around each decl - - - - - e25b7e9f by Mark Lentczner at 2010-04-10T21:23:21+00:00 data decls are now a sequence of paragraphs, not a table - - - - - 89ee0294 by Mark Lentczner at 2010-04-10T21:29:16+00:00 removed commented out code that can't be maintained - - - - - d466f536 by Mark Lentczner at 2010-04-12T04:56:27+00:00 removed declWithDoc and cleaned up data decls in summary - - - - - ed755832 by Mark Lentczner at 2010-04-12T05:07:53+00:00 merge in markupExample changes - - - - - c36f51fd by Mark Lentczner at 2010-04-25T04:56:37+00:00 made record fields be an unordList, not a table - - - - - ed3a28d6 by Mark Lentczner at 2010-04-25T05:23:28+00:00 fixed surround of instance and constructor tables - - - - - 0e35bbc4 by Mark Lentczner at 2010-04-25T05:36:59+00:00 fix class member boxes in summary - - - - - 5041749b by Mark Lentczner at 2010-04-25T05:38:35+00:00 remove unused bodyBox - - - - - e91724db by Mark Lentczner at 2010-04-25T06:26:10+00:00 fixed javascript quoting/escpaing issue - - - - - f4abbb73 by Mark Lentczner at 2010-05-03T23:04:31+00:00 adjust css for current markup - - - - - e75fec4c by Mark Lentczner at 2010-05-04T06:14:34+00:00 added assoicated types and methods back into class decls - - - - - 84169323 by Mark Lentczner at 2010-05-24T13:13:42+00:00 merge in changes from the big-whitespace cleanup - - - - - 3c1c872e by Mark Lentczner at 2010-06-11T21:03:58+00:00 adjust synopsis and bottom bar spacing - - - - - 3c1f9ef7 by Mark Lentczner at 2010-06-11T21:14:44+00:00 fix missing space in "module" lines in synoposis - - - - - 9a137e6d by Mark Lentczner at 2010-06-11T21:34:08+00:00 changed tt elements to code elements - - - - - 50f71ef1 by Mark Lentczner at 2010-06-11T23:27:46+00:00 factored out ppInstances - - - - - 3b9a9de5 by Mark Lentczner at 2010-06-17T17:36:01+00:00 push single constructors (newtype) onto line with decl - - - - - e0f8f2ec by Mark Lentczner at 2010-06-17T22:20:56+00:00 remove <++> connector - - - - - 56c075dd by Mark Lentczner at 2010-07-13T05:26:21+00:00 change to new page structure - - - - - 04be6ca7 by Mark Lentczner at 2010-07-14T04:21:55+00:00 constructors and args as dl lists, built in Layout.hs - - - - - 65aeafc2 by Mark Lentczner at 2010-07-14T05:38:32+00:00 better interface to subDecls - - - - - 72032189 by Mark Lentczner at 2010-07-14T07:04:10+00:00 made subDecl tables looks just so - - - - - b782eca2 by Mark Lentczner at 2010-07-14T16:00:54+00:00 convert args to SubDecl format - - - - - cc75e98f by Mark Lentczner at 2010-07-14T16:28:53+00:00 convert instances to SubDecl - - - - - 34e2aa5a by Mark Lentczner at 2010-07-14T21:07:32+00:00 removing old table cruft from Layout.hs - - - - - d5810d95 by Mark Lentczner at 2010-07-14T21:54:58+00:00 methods and associated types in new layout scheme - - - - - 65ef9579 by Mark Lentczner at 2010-07-14T23:43:42+00:00 clean up synopsis lists - - - - - e523318f by Mark Lentczner at 2010-07-15T05:02:26+00:00 clean up of anchors - - - - - 1215dfc5 by Mark Lentczner at 2010-07-15T23:53:01+00:00 added two new themes and rough css switcher - - - - - 7f0fd36f by Mark Lentczner at 2010-07-16T04:57:38+00:00 fixed package catpion, added style menu - - - - - 0dd4999c by Mark Lentczner at 2010-07-16T20:12:39+00:00 new output for mini_ pages - - - - - 64b2810b by Mark Lentczner at 2010-07-16T20:58:41+00:00 reformat index-frames - - - - - 3173f555 by Mark Lentczner at 2010-07-16T22:41:53+00:00 convert index to new markup - - - - - b0a4b7c9 by Mark Lentczner at 2010-07-17T04:07:22+00:00 convert index.html to new markup, adjust module markup - - - - - 8261ae1e by Mark Lentczner at 2010-07-17T05:07:29+00:00 classing styling of ancillary pages - - - - - 2a4fb025 by Mark Lentczner at 2010-07-17T05:11:45+00:00 clean up Layout.hs: no more vanillaTable - - - - - 87eec685 by Mark Lentczner at 2010-07-17T05:35:16+00:00 clean up Util.hs - - - - - d304e9b0 by Mark Lentczner at 2010-07-17T05:38:50+00:00 qualify import of XHtml as XHtml - - - - - 7dc05807 by Mark Lentczner at 2010-07-17T06:17:53+00:00 factored out head element generation - - - - - 9cdaec9e by Mark Lentczner at 2010-07-17T06:44:54+00:00 refactored out main page body generation - - - - - 8a51019e by Mark Lentczner at 2010-07-17T06:48:20+00:00 moved footer into only place that used it - - - - - efa479da by Mark Lentczner at 2010-07-17T18:48:30+00:00 styling auxillary pages for tibbe and snappy themes - - - - - 81de5509 by Mark Lentczner at 2010-07-18T04:41:38+00:00 fixed alphabet on index page, and styling of it and packages in module lists - - - - - 20718c1a by Mark Lentczner at 2010-07-18T05:34:29+00:00 cleaned up div functions in Layout.hs - - - - - 60d50453 by Mark Lentczner at 2010-07-18T05:48:39+00:00 added content div to main pages - - - - - ed16561c by Mark Lentczner at 2010-07-18T06:12:22+00:00 add .doc class to documentation blocks - - - - - f5c781b0 by Mark Lentczner at 2010-07-19T05:20:53+00:00 refactoring of anchor ID and fragment handling - - - - - a69a93bf by Mark Lentczner at 2010-07-19T05:35:55+00:00 remove an explicit bold tag - replace with .def class - - - - - d76c7225 by Mark Lentczner at 2010-07-19T06:56:15+00:00 rename Haddock.Backends.Xhtml.Util to Utils - - - - - 5a58c0da by David Waern at 2010-07-21T13:30:54+00:00 Remove trailing whitespace in Haddock.Backends.Xhtml - - - - - 0652aa17 by David Waern at 2010-07-21T13:33:21+00:00 Align a few comments - - - - - 785776c3 by David Waern at 2010-07-21T13:39:04+00:00 Remove trailing whitespace in H.B.X.Decl - - - - - 71a30710 by David Waern at 2010-07-21T13:44:27+00:00 Remove more trailing whitespace - - - - - 38750394 by David Waern at 2010-07-21T13:50:43+00:00 Style police - - - - - 3023d940 by David Waern at 2010-07-21T14:01:22+00:00 Style police in H.B.X.Decl - - - - - df16e9e6 by David Waern at 2010-07-21T14:14:45+00:00 Style police in H.B.X.DocMarkup - - - - - 6020e321 by David Waern at 2010-07-21T14:17:32+00:00 More style police - - - - - 86ad8bf5 by David Waern at 2010-07-21T14:21:02+00:00 Style police in H.B.Xhtml - - - - - aea27d03 by David Waern at 2010-07-21T14:42:03+00:00 Fix warnings in LaTeX backend - - - - - 2aff34a9 by David Waern at 2010-07-21T14:50:46+00:00 Style police in LaTeX backend (mainly more newlines) - - - - - e517162d by David Waern at 2010-07-21T15:05:47+00:00 Doc sections in Main - - - - - b971aa0c by David Waern at 2010-07-21T15:06:17+00:00 Trailing whitespace in Documentation.Haddock - - - - - f11628fb by David Waern at 2010-07-21T15:07:06+00:00 Trailing whitespace in Haddock.Convert - - - - - cbaf284c by David Waern at 2010-07-21T15:08:11+00:00 Style police in Haddock.GhcUtils - - - - - 71feb77b by David Waern at 2010-07-21T15:09:06+00:00 Style police in Haddock.InterfaceFile - - - - - 0a9c80e6 by David Waern at 2010-07-21T15:11:33+00:00 Whitespace police - - - - - 6168376c by David Waern at 2010-07-21T15:16:35+00:00 Style police in Haddock.Utils - - - - - 9fe4dd90 by David Waern at 2010-07-21T15:19:31+00:00 Add -fwarn-tabs - - - - - a000d752 by Mark Lentczner at 2010-07-20T17:25:52+00:00 move CSS Theme functions into Themes.hs - - - - - b52b440f by Mark Lentczner at 2010-07-20T17:29:35+00:00 add Thomas Schilling's theme - - - - - e43fa7e8 by Mark Lentczner at 2010-07-21T04:49:34+00:00 correct icon used with Snappy theme - - - - - ba5092d3 by Mark Lentczner at 2010-07-21T04:56:47+00:00 apply Tibbe's updates to his theme - - - - - 7804eef6 by Mark Lentczner at 2010-07-21T05:15:49+00:00 space between "Style" and the downward triangle - - - - - 7131d4c6 by Mark Lentczner at 2010-07-21T17:43:35+00:00 merge with David's source cleanups - - - - - ee65f1cb by David Waern at 2010-07-22T16:50:46+00:00 Fix a bug where we allowed --hoogle, --latex, etc without input files - - - - - e413ff7a by David Waern at 2010-07-22T17:21:58+00:00 Improve function name - - - - - a0fd14f3 by Simon Marlow at 2010-06-30T15:34:32+00:00 fix warnings - - - - - 31f73d2a by David Waern at 2010-07-22T19:29:41+00:00 Solve conflicts - - - - - d563b4a5 by Simon Marlow at 2010-06-30T15:34:37+00:00 fix warning - - - - - 412b6469 by David Waern at 2010-07-22T19:31:28+00:00 Solve conflict - - - - - 35174b94 by Ian Lynagh at 2010-07-06T17:27:16+00:00 Follow mkPState argument order change - - - - - b5c3585c by Simon Marlow at 2010-07-14T08:49:21+00:00 common up code for instance rendering - - - - - d8009560 by Simon Marlow at 2010-07-14T12:37:11+00:00 fix warnings - - - - - a6d88695 by David Waern at 2010-07-24T15:33:33+00:00 Fix build with ghc < 6.13 - - - - - 94cf9de1 by David Waern at 2010-07-24T15:34:37+00:00 Remove conflict left-over - - - - - 313b15c0 by Mark Lentczner at 2010-07-21T22:09:04+00:00 reorganization of nhaddock.css with tibbe - - - - - 9defed80 by Mark Lentczner at 2010-07-21T22:42:14+00:00 further cleanup of nhaddock.css, float TOC, support aux. pages - - - - - 6d944c1b by Mark Lentczner at 2010-07-22T06:22:23+00:00 remove old HTML backend - - - - - b3e8cba5 by Mark Lentczner at 2010-07-22T06:43:32+00:00 remove --html-help support - it was old, out-of-date, and mostly missing - - - - - d2654a08 by Mark Lentczner at 2010-07-22T21:45:34+00:00 tweaks to nhaddock.css - - - - - f73b285c by Mark Lentczner at 2010-07-23T06:19:35+00:00 command like processing for theme selection The bulk of the change is threadnig the selected theme set through functions in Xhtml.hs so that the selected themes can be used when generating the page output. There isn't much going on in most of these changes, just passing it along. The real work is all done in Themes.hs. - - - - - 8bddc90d by Mark Lentczner at 2010-07-23T06:58:31+00:00 drop --themes support, add named theme support decided that --themes was silly - no one would do that, just use multiple --theme arguments made --theme a synonym for --css and -c made those arguments, if no file is found, look up the argument as the name of a built in theme all of this let's haddock be invoked with "--theme=classic" for example. - - - - - 20cafd4f by Mark Lentczner at 2010-07-23T17:44:29+00:00 rename --default-themes to --built-in-themes - - - - - 0fe41307 by Mark Lentczner at 2010-07-23T18:33:02+00:00 tweaks to theme for info table, headings, and tables - - - - - cba4fee0 by Mark Lentczner at 2010-07-23T19:13:59+00:00 tweaks for dl layout, though still not used - - - - - 463fa294 by Mark Lentczner at 2010-07-23T21:07:19+00:00 tweak look of mini pages, keywords, and preblocks - - - - - 5472fc02 by Mark Lentczner at 2010-07-24T05:36:15+00:00 slide out Synopsis drawer - - - - - 9d5d5de5 by Mark Lentczner at 2010-07-24T06:02:42+00:00 extend package header and footer to edges of page - - - - - a47c91a2 by Mark Lentczner at 2010-07-24T06:28:44+00:00 fields are def lists, tweak css for style menu, mini pages, arguments - - - - - ca20f23b by Mark Lentczner at 2010-07-24T16:55:22+00:00 excisting last vestiges of the --xhtml flag - - - - - 71fb012e by Mark Lentczner at 2010-07-25T18:47:49+00:00 change how collapsing sections are done make whole .caption be the target improve javascript for class toggling have plus/minus images come from .css, not img tags - - - - - c168c8d3 by Mark Lentczner at 2010-07-26T00:32:05+00:00 reorganize files in the html lib data dir - - - - - 93324301 by Mark Lentczner at 2010-07-26T01:27:42+00:00 cleaned up Themes.hs - - - - - ad3b5dd4 by Mark Lentczner at 2010-07-26T02:39:15+00:00 make module list use new collapsers - - - - - 1df9bfc6 by Mark Lentczner at 2010-07-27T19:09:25+00:00 remove Tibbe theme - - - - - 8b9b01b3 by Mark Lentczner at 2010-07-27T20:04:03+00:00 move themes into html dir with .theme and .std-theme extensions - - - - - a7beb965 by Mark Lentczner at 2010-07-27T21:06:34+00:00 give a class to empty dd elements so they can be hidden - - - - - a258c117 by Mark Lentczner at 2010-07-27T21:23:58+00:00 remove custom version of copyFile in Xhtml.hs - - - - - b70dba6e by Mark Lentczner at 2010-07-27T22:12:45+00:00 apply margin changes to pre and headings as per group decision, and small cleanups - - - - - e6f722a2 by Mark Lentczner at 2010-07-28T00:03:12+00:00 make info block and package bar links be floatable by placing them first in the dom tree - - - - - c8278867 by Mark Lentczner at 2010-07-28T19:01:18+00:00 styling source links on declarations - - - - - 88fdc399 by Mark Lentczner at 2010-07-29T01:12:46+00:00 styling tweaks don't generate an empty li for absent style menu in links area update css for Classic and Snappy to handle: dl lists links in package header and in declarations floating of links and info block in package and module headers - - - - - 8a75b213 by Ian Lynagh at 2010-07-30T20:21:46+00:00 Fix build in GHC tree - - - - - ce8e18b3 by Simon Hengel at 2010-08-03T18:37:26+00:00 Adapt paths to data files in cabal file - - - - - 9701a455 by Simon Hengel at 2010-08-07T13:20:27+00:00 Add missing dependency to cabal file - - - - - 01b838d1 by Mark Lentczner at 2010-07-30T20:19:40+00:00 improved synopsis drawer: on click, not hover - - - - - 7b6f3e59 by Mark Lentczner at 2010-07-30T23:38:55+00:00 put the synopsis back in the other themes - - - - - 7b2904c9 by Mark Lentczner at 2010-08-11T11:11:26+00:00 close arrows on expanded synopsis drawer - - - - - ea19e177 by Mark Lentczner at 2010-08-12T21:16:45+00:00 width and font changes removed the max width restrictions on the page as a whole and the synopsis made the main font size smaller (nominally 14pt) and then tweaked most font sizes (relative) to be more consistent - - - - - 5ced00c0 by Mark Lentczner at 2010-08-13T15:09:55+00:00 implemented YUI's CSS font approach - - - - - 2799c548 by Mark Lentczner at 2010-08-13T15:11:59+00:00 adjusted margin to 2em, 1 wasn't enough - - - - - 58f06893 by Mark Lentczner at 2010-08-13T15:48:44+00:00 removed underlining on hover for named anchors headings in interface lost thier a element, no need, just put id on heading css for a elements now only applies to those with href attribute - - - - - 7aced4c4 by Mark Lentczner at 2010-08-13T15:50:22+00:00 more space between elements - - - - - 5a3c1cce by Mark Lentczner at 2010-08-13T16:43:43+00:00 adjusted font sizes of auxilary pages per new scheme - - - - - 487539ef by Mark Lentczner at 2010-08-13T21:43:41+00:00 add Frames button and clean up frames.html - - - - - c1a140b6 by Mark Lentczner at 2010-08-13T22:17:48+00:00 move frames button to js - - - - - b0bdb68e by Mark Lentczner at 2010-08-14T03:44:46+00:00 build style menu in javascript moved to javascript, so as to not polute the content with the style menu removed menu building code in Themes.hs removed onclick in Utils.hs changed text of button in header from "Source code" to "Source" more consistent with links in rest of page - - - - - 43ab7120 by Mark Lentczner at 2010-08-16T15:15:37+00:00 font size and margin tweaks - - - - - c0b68652 by Mark Lentczner at 2010-08-17T18:19:52+00:00 clean up collapser logics javascript code for collapasble sections cleaned up rewrote class utilities in javascript to be more robust refactored utilities for generating collapsable sections made toc be same color as synopsis module list has needed clear attribute in CSS - - - - - 5d573427 by Mark Lentczner at 2010-08-17T23:06:02+00:00 don't collapse entries in module list when clicking on links - - - - - 8c307c4a by Mark Lentczner at 2010-08-17T23:21:43+00:00 add missing data file to .cabal - - - - - 414bcfcf by Mark Lentczner at 2010-08-17T23:28:47+00:00 remove synopsis when in frames - - - - - ba0fa98a by Mark Lentczner at 2010-08-18T16:16:11+00:00 layout tweeks - mini page font size, toc color, etc. - - - - - 63c1bed1 by Mark Lentczner at 2010-08-18T19:50:02+00:00 margin fiddling - - - - - c311c094 by Mark Lentczner at 2010-08-20T01:37:55+00:00 better synopsis handling logic - no flashing - - - - - f1fe5fa8 by Mark Lentczner at 2010-08-20T01:41:06+00:00 fix small layout issues mini frames should have same size top heading give info block dts some padding so they don't collide in some browsers - - - - - 0de84d77 by Mark Lentczner at 2010-08-20T02:13:09+00:00 made style changing and cookies storage robust - - - - - 1ef064f9 by Thomas Schilling at 2010-08-04T13:12:22+00:00 Make synopsis frame behave properly in Firefox. In Firefox, pressing the back button first reverted the synopsis frame, and only clicking the back button a second time would update the main frame. - - - - - dd1c9a94 by Mark Lentczner at 2010-08-21T01:46:19+00:00 remove Snappy theme - - - - - 2353a90d by Mark Lentczner at 2010-08-25T05:16:19+00:00 fix occasional v.scroll bars on pre blocks (I think) - - - - - 459b8bf1 by Simon Hengel at 2010-08-08T10:12:45+00:00 Add createInterfaces' (a more high-level alternative to createInterfaces) to Haddock API - - - - - b1b68675 by David Waern at 2010-08-26T20:31:58+00:00 Follow recent API additions with some refactorings Simon Hegel's patch prompted me to do some refactorings in Main, Haddock.Documentation and Haddock.Interface. - - - - - 264d4d67 by David Waern at 2010-08-26T21:40:59+00:00 Get rid of GhcModule and related cruft We can get everything we need directly from TypecheckedModule. - - - - - 0feacec2 by Mark Lentczner at 2010-08-26T23:44:13+00:00 fixed CSS for ordered lists and def lists in doc blocks - - - - - 2997e0c2 by Mark Lentczner at 2010-08-26T23:45:03+00:00 support both kinds of enumerated lists in doc markup The documentation for Haddock says enumerated lists can use either of (1) first item 2. second item The second form wasn't actually supported - - - - - 5d4ddeec by Mark Lentczner at 2010-08-27T21:29:48+00:00 fix broken header link margins - - - - - 614456ba by Mark Lentczner at 2010-08-27T22:16:19+00:00 fix table of contents CSS - - - - - 03f329a2 by David Waern at 2010-08-28T16:36:09+00:00 Update tests following switch to the Xhtml backend - - - - - ca689fa2 by Mark Lentczner at 2010-08-28T18:25:16+00:00 fix def lists - - - - - 18e1d3d2 by Mark Lentczner at 2010-08-28T18:26:18+00:00 push footer to bottom of window - - - - - b0ab8d82 by David Waern at 2010-08-28T22:04:32+00:00 Whitespace police - - - - - 2d217977 by David Waern at 2010-08-29T12:44:45+00:00 Remove Snappy data files - - - - - 01e27d5f by David Waern at 2010-08-29T13:03:28+00:00 Add source entity path to --read-interface You can now use this flag like this: --read-interface=<html path>,<source entity path>,<.haddock file> By "source entity path" I mean the same thing that is specified with the --source-entity flag. The purpose of this is to be able to specify the source entity path per package, to allow source links to work in the presence of cross-package documentation. When given two arguments or less the --read-interface flag behaves as before. - - - - - 20bf4aaa by David Waern at 2010-08-29T13:11:03+00:00 Naming wibbles - - - - - ad22463f by Mark Lentczner at 2010-08-29T15:14:54+00:00 make portability block be a table - solves layout issues - - - - - 97bd1ae6 by Mark Lentczner at 2010-08-29T15:17:42+00:00 update golden test for Test due to portability box change - - - - - d37e139e by Mark Lentczner at 2010-08-29T17:07:17+00:00 move TOC and Info blocks down 0.5em to improve layout issue w/Test.hs - - - - - acf52501 by David Waern at 2010-08-29T17:32:36+00:00 Allow building with ghc < 6.16 - - - - - 1cb34ed8 by Ian Lynagh at 2010-07-24T23:18:49+00:00 Flatten the dynflags before parsing - - - - - b36845b4 by Ian Lynagh at 2010-07-24T23:26:49+00:00 Follow flattenLanguageFlags -> flattenExtensionFlags rename - - - - - 7f7fcc7e by David Waern at 2010-08-29T17:46:23+00:00 Use flattenExtensionFlags with ghc >= 6.13 only - - - - - 13cf9411 by Ian Lynagh at 2010-08-01T18:09:54+00:00 Make the main haddock script versioned, and make plain "haddock" a symlink - - - - - 495cbff2 by Ian Lynagh at 2010-08-18T18:57:24+00:00 Fix installation in the GHC build system Data-files are now in subdirectories, so we need to handle that - - - - - 88ebab0a by Ian Lynagh at 2010-08-18T19:43:53+00:00 GHC build system: Add all the data files to BINDIST_EXTRAS - - - - - 65837172 by David Waern at 2010-08-29T20:12:34+00:00 Update Test - - - - - 094bbaa2 by David Waern at 2010-08-29T20:55:14+00:00 Revert update to Test - - - - - a881cfb3 by David Waern at 2010-08-31T18:24:15+00:00 Bump version number - - - - - 1fc8a3eb by David Waern at 2010-08-31T22:32:27+00:00 Update ANNOUNCE - - - - - ee1df9d0 by David Waern at 2010-08-31T22:33:11+00:00 Update CHANGES - - - - - 394cc854 by David Waern at 2010-08-31T22:33:23+00:00 Update interface file versioning to work with ghc 6.14/15 - - - - - 7d03b79b by David Waern at 2010-08-31T22:36:00+00:00 Update test output following version change - - - - - a48d82d1 by Mark Lentczner at 2010-09-01T04:29:35+00:00 sort options in doc to match --help output removed --html-help option, as it is no longer supported - - - - - 06561aeb by Mark Lentczner at 2010-09-01T05:29:32+00:00 update options documentation rewrote doc for --html added doc for --theme and --built-in-themes added --use-contents and --gen-contents - - - - - 57dea832 by Mark Lentczner at 2010-09-01T05:31:27+00:00 slight wording change about Frames mode - - - - - fa1f6da3 by David Waern at 2010-09-01T10:57:44+00:00 Update doc configure script to find docbook stylesheets on arch linux - - - - - addff770 by David Waern at 2010-09-01T11:02:29+00:00 Wibble - - - - - 8399006d by David Waern at 2010-09-01T11:19:21+00:00 Replace ghci> with >>> in example syntax - - - - - 35074cf8 by David Waern at 2010-09-01T19:03:27+00:00 Improve docs for --no-tmp-comp-dir - - - - - 0f8f8cfd by David Waern at 2010-09-02T11:22:27+00:00 Add a list of contributors to the user guide Break out everyone thanked in the `Acknowledgements` chapter into a separate contributor list and add everyone from `darcs show authors`. We consider everyone who is thanked to be a contributor as a conservative estimation :-) I have added some more contributors that I know about, who were not in the darcs history, but others may be missing. So please add anyone that you think is missing from the list. - - - - - 42ccf099 by David Waern at 2010-09-02T11:29:22+00:00 Update copyright years in license - - - - - 0d560479 by David Waern at 2010-09-02T11:38:52+00:00 Update release instructions - - - - - 72ab7796 by David Waern at 2010-09-02T19:27:08+00:00 Add a note to ANNOUNCE - - - - - bf9d9c5d by David Waern at 2010-09-02T19:27:48+00:00 H.Utils needs FFI on Win+MinGW - - - - - 048ae44a by Mark Lentczner at 2010-09-04T23:19:47+00:00 make TOC group header identifiers validate - - - - - 8c6faf36 by Simon Michael at 2010-09-22T07:12:34+00:00 add hints for cleaner darcs show authors output - - - - - 9909bd17 by Simon Michael at 2010-09-22T17:58:06+00:00 print haddock coverage info on stdout when generating docs A module's haddockable items are its exports and the module itself. The output is lightly formatted so you can align the :'s and sort for readability. - - - - - 6da72171 by David Waern at 2010-10-03T21:31:24+00:00 Style wibble - - - - - 2f8d8e4d by Tobias Brandt at 2010-08-27T07:01:21+00:00 adding the option to fully qualify identifiers - - - - - 833be6c6 by Tobias Brandt at 2010-08-27T15:50:28+00:00 adding support for local and relative name qualification - - - - - df15c4e9 by Tobias Brandt at 2010-08-27T15:56:37+00:00 corrected qualification help message - - - - - 449e9ce1 by David Waern at 2010-10-16T17:34:30+00:00 Solve conflicts - - - - - 3469bda5 by David Waern at 2010-10-16T18:42:40+00:00 Use "qual" as an abbreviation for qualification instead of "quali" for consistency - - - - - 97c2d728 by David Waern at 2010-10-16T18:47:07+00:00 Style police - - - - - ce14fbea by David Waern at 2010-10-16T21:15:25+00:00 Style police - - - - - fdf29e9d by David Waern at 2010-10-17T00:30:44+00:00 Add a pointer to the style guide - - - - - 8e6b44e8 by rrnewton at 2010-10-24T03:19:28+00:00 Change to index pages: include an 'All' option even when subdividing A-Z. - - - - - 755b131c by David Waern at 2010-11-14T19:39:36+00:00 Bump version - - - - - d0345a04 by David Waern at 2010-11-14T19:41:59+00:00 TAG 2.8.1 - - - - - f6221508 by Simon Peyton Jones at 2010-09-13T09:53:00+00:00 Adapt to minor changes in internal GHC functions - - - - - 1290713d by Ian Lynagh at 2010-09-15T10:37:18+00:00 Remove duplicate Outputable instance for Data.Map.Map - - - - - 87f69eef by Ian Lynagh at 2010-09-21T15:01:10+00:00 Bump GHC dep upper bound - - - - - af36e087 by Ian Lynagh at 2010-09-21T15:12:02+00:00 Fix up __GLASGOW_HASKELL__ tests - - - - - ad67716c by Ian Lynagh at 2010-09-21T20:31:35+00:00 Don't build haddock is HADDOCK_DOCS is NO - - - - - 63b3f1f5 by Ian Lynagh at 2010-09-21T21:39:51+00:00 Fixes for when HADDOCK_DOCS=NO - - - - - e92bfa42 by Ian Lynagh at 2010-09-29T21:15:38+00:00 Fix URL creation on Windows: Use / not \ in URLs. Fixes haskell/haddock#4353 - - - - - 66c55e05 by Ian Lynagh at 2010-09-30T17:03:34+00:00 Tidy up haddock symlink installation In particular, it now doesn't get created if we aren't installing haddock. - - - - - 549b5556 by Ian Lynagh at 2010-10-23T21:17:14+00:00 Follow extension-flattening change in GHC - - - - - d7c2f72b by David Waern at 2010-11-14T20:17:55+00:00 Bump version to 2.8.2 - - - - - 6989a3a9 by David Waern at 2010-11-14T20:26:01+00:00 Solve conflict - - - - - 055c6910 by Ian Lynagh at 2010-09-22T15:36:20+00:00 Bump GHC dep - - - - - c96c0763 by Simon Marlow at 2010-10-27T11:09:44+00:00 follow changes in the GHC API - - - - - 45907129 by David Waern at 2010-11-07T14:00:58+00:00 Update the HCAR entry - - - - - 61940b95 by David Waern at 2010-11-07T14:07:34+00:00 Make the HCAR entry smaller - - - - - aa590b7d by David Waern at 2010-11-14T21:30:59+00:00 Update HCAR entry with November 2010 version - - - - - 587f9847 by David Waern at 2010-11-14T23:48:17+00:00 Require ghc >= 7.0 - - - - - ff5c647c by David Waern at 2010-11-14T23:49:09+00:00 TAG 2.8.2 - - - - - 937fcb4f by David Waern at 2010-11-14T23:49:45+00:00 Solve conflict - - - - - 8e5d0c1a by David Waern at 2010-11-15T21:09:50+00:00 Remove code for ghc < 7 - - - - - 3d47b70a by David Waern at 2010-11-15T21:11:06+00:00 Fix bad merge - - - - - 7f4a0d8a by David Waern at 2010-11-15T21:13:57+00:00 Remove more ghc < 7 code - - - - - 9ee34b50 by David Waern at 2010-11-15T21:31:25+00:00 Match all AsyncExceptions in exception handler - - - - - 42849c70 by David Waern at 2010-11-15T21:35:31+00:00 Just say "internal error" instead of "internal Haddock or GHC error" - - - - - c88c809b by David Waern at 2010-11-15T21:44:19+00:00 Remove docNameOcc under the motto "don't name compositions" - - - - - b798fc7c by David Waern at 2010-11-15T23:27:13+00:00 Wibble - - - - - 2228197e by David Waern at 2010-11-15T23:28:24+00:00 Rename the HCAR entry file - - - - - 8a3f9090 by David Waern at 2010-11-16T00:05:29+00:00 Remove Haskell 2010 extensions from .cabal file - - - - - c7a0c597 by David Waern at 2010-11-16T00:10:28+00:00 Style wibbles - - - - - cde707a5 by David Waern at 2010-11-16T00:12:00+00:00 Remove LANGUAGE ForeignFunctionInterface pragmas - - - - - 1dbda8ed by David Waern at 2010-11-16T00:17:21+00:00 Make a little more use of DoAndIfThenElse - - - - - 4c45ff6e by David Waern at 2010-11-16T00:59:41+00:00 hlint police - - - - - d2feaf09 by David Waern at 2010-11-16T01:14:15+00:00 hlint police - - - - - 99876e97 by David Waern at 2010-11-20T19:06:00+00:00 Haddock documentation updates - - - - - 65ce6987 by David Waern at 2010-11-20T19:42:51+00:00 Follow the style guide closer in Haddock.Types and improve docs - - - - - 28ca304a by tob.brandt at 2010-11-20T17:04:40+00:00 add full qualification for undocumented names - - - - - d61341e3 by David Waern at 2010-11-20T20:04:15+00:00 Re-structure qualification code a little - - - - - 0057e4d6 by David Waern at 2010-11-20T20:07:55+00:00 Re-order functions - - - - - d7279afd by David Waern at 2010-11-21T03:39:54+00:00 Add BangPatterns to alex and happy source files - - - - - 629fe60e by tob.brandt at 2010-11-23T23:35:11+00:00 documentation for qualification - - - - - 37031cee by David Waern at 2010-11-23T21:06:44+00:00 Update CHANGES - don't mention 2.8.2, we won't release it - - - - - f2489e19 by David Waern at 2010-12-01T21:57:11+00:00 Update deps of runtests.hs to work with ghc 7.0.1 - - - - - d3657e9a by David Waern at 2010-12-01T22:04:57+00:00 Make tests compile with ghc 7.0.1 - - - - - a2f09d9b by David Waern at 2010-12-01T22:06:59+00:00 Update tests following version bump - - - - - 50883ebb by David Waern at 2010-12-06T14:09:18+00:00 Update tests following recent changes - - - - - fc2fadeb by David Waern at 2010-12-06T14:17:29+00:00 Add a flag --pretty-html for rendering indented html with newlines - - - - - 30832ef2 by David Waern at 2010-12-06T14:17:35+00:00 Use --pretty-html when running the test suite. Makes it easier to compare output - - - - - a0b81b31 by David Waern at 2010-12-06T14:18:27+00:00 Wibble - - - - - 3aaa23fe by David Waern at 2010-12-06T14:19:29+00:00 Haddockify ppHtml comments - - - - - 24bb24f0 by David Waern at 2010-12-06T14:23:15+00:00 Remove --debug. It was't used, and --verbosity should take its place - - - - - 6bc076e5 by David Waern at 2010-12-06T14:25:37+00:00 Rename golden-tests into html-tests. "golden tests" sounds strange - - - - - 53301e55 by David Waern at 2010-12-06T14:26:26+00:00 QUALI -> QUAL in the description --qual for consistency - - - - - 98b6affb by David Waern at 2010-12-06T21:54:02+00:00 Bump version - - - - - 371bf1b3 by David Waern at 2010-12-06T22:08:55+00:00 Update tests following version bump - - - - - 25be762d by David Waern at 2010-12-06T22:21:03+00:00 Update CHANGES - - - - - 7c7dac71 by David Waern at 2010-12-06T22:33:43+00:00 Update ANNOUNCE - - - - - 30d7a5f2 by Simon Peyton Jones at 2010-11-15T08:38:38+00:00 Alex generates BangPatterns, so make Lex.x accept them (It'd be better for Alex to generate this pragma.) - - - - - 605e8018 by Simon Marlow at 2010-11-17T11:37:24+00:00 Add {-# LANGUAGE BangPatterns #-} to mollify GHC - - - - - a46607ba by David Waern at 2010-12-07T14:08:10+00:00 Solve conflicts - - - - - b28cda66 by David Waern at 2010-12-09T20:41:35+00:00 Docs: Mention that \ is a special character in markup - - - - - a435bfdd by Ian Lynagh at 2010-11-17T14:01:19+00:00 TAG GHC 7.0.1 release - - - - - 5a15a05a by David Waern at 2010-12-11T17:51:19+00:00 Fix indentation problem - - - - - 4232289a by Lennart Kolmodin at 2010-12-17T18:32:03+00:00 Revise haddock.cabal given that we now require ghc-7 default-language should be Haskell2010, slight new semantics for extensions. Rewrite into clearer dependencies of base and Cabal. - - - - - a36302dc by David Waern at 2010-12-19T17:12:37+00:00 Update CHANGES - - - - - 7c8b85b3 by David Waern at 2010-12-19T17:14:24+00:00 Bump version - - - - - cff22813 by Ian Lynagh at 2011-01-05T18:24:27+00:00 Write hoogle output in utf8; fixes GHC build on Windows - - - - - c7e762ea by David Waern at 2011-01-22T00:00:35+00:00 Put title outside doc div when HTML:fying title+prologue Avoids indenting the title, and makes more sense since the title is not a doc string anyway. - - - - - 5f639054 by David Waern at 2011-01-22T16:09:44+00:00 Fix spelling error - contributed by Marco Silva - - - - - c11dce78 by Ian Lynagh at 2011-01-07T02:33:11+00:00 Follow GHC build system changes - - - - - 101cfaf5 by David Waern at 2011-01-08T14:06:44+00:00 Bump version - - - - - af62348b by David Waern at 2011-01-08T14:07:07+00:00 TAG 2.9.2 - - - - - 4d1f6461 by Ian Lynagh at 2011-01-07T23:06:57+00:00 Name the haddock script haddock-ghc-7.0.2 instead of haddock-7.0.2; haskell/haddock#4882 "7.0.2" looked like a haddock version number before - - - - - 8ee4d5d3 by Simon Peyton Jones at 2011-01-10T17:31:12+00:00 Update Haddock to reflect change in hs_tyclds field of HsGroup - - - - - 06f3e3db by Ian Lynagh at 2011-03-03T15:02:37+00:00 TAG GHC 7.0.2 release - - - - - 7de0667d by David Waern at 2011-03-10T22:47:13+00:00 Update CHANGES - - - - - 33a9f1c8 by David Waern at 2011-03-10T22:47:31+00:00 Fix build with ghc 7.0.1 - - - - - 4616f861 by David Waern at 2011-03-10T22:47:50+00:00 TAG 2.9.2-actual - - - - - 0dab5e3c by Simon Hengel at 2011-04-08T15:53:01+00:00 Set shell script for unit tests back to work - - - - - 85c54dee by Simon Hengel at 2011-04-08T16:01:24+00:00 Set unit tests back to work Here "ghci>" was still used instead of ">>>". - - - - - 1cea9b78 by Simon Hengel at 2011-04-08T16:25:36+00:00 Update runtests.hs for GHC 7.0.2 - - - - - 8e5b3bbb by Simon Hengel at 2011-04-08T16:28:49+00:00 Update Haddock version in *.html.ref - - - - - 2545e955 by Simon Hengel at 2011-04-08T17:09:28+00:00 Add support for blank lines in the result of examples Result lines that only contain the string "<BLANKLINE>" are treated as a blank line. - - - - - adf64d2e by Simon Hengel at 2011-04-08T17:36:50+00:00 Add documentation for "support for blank lines in the result of examples" - - - - - c51352ca by David Waern at 2011-05-21T23:57:56+00:00 Improve a haddock comment - - - - - 7419cf2c by David Waern at 2011-05-22T15:41:52+00:00 Use cabal's test suite support to run the test suite This gives up proper dependency tracking of the test script. - - - - - 7770070c by David Waern at 2011-05-22T01:45:44+00:00 We don't need to send DocOptions nor a flag to mkExportItems - - - - - 9d95b7b6 by David Waern at 2011-05-22T21:39:03+00:00 Fix a bug - - - - - 1f93699b by David Waern at 2011-05-22T21:40:21+00:00 Break out fullContentsOf, give it a better name and some documentation The documentation describes how we want this function to eventually behave, once we have fixed a few problems with the current implementation. - - - - - 9a86432f by David Waern at 2011-05-22T21:53:52+00:00 Fix some stylistic issues in mkExportItems - - - - - c271ff0c by David Waern at 2011-05-22T22:09:11+00:00 Indentation - - - - - 93e602b1 by David Waern at 2011-06-10T01:35:31+00:00 Add git commits since switchover: darcs format (followed by a conflict resolution): commit 6f92cdd12d1354dfbd80f8323ca333bea700896a Merge: f420cc4 28df3a1 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 19 17:54:34 2011 +0100 Merge remote branch 'origin/master' into ghc-generics commit 28df3a119f770fdfe85c687dd73d5f6712b8e7d0 Author: Max Bolingbroke <batterseapower at hotmail.com> Date: Sat May 14 22:37:02 2011 +0100 Unicode fix for getExecDir on Windows commit 89813e729be8bce26765b95419a171a7826f6d70 Merge: 6df3a04 797ab27 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 9 11:55:17 2011 +0100 Merge branch 'ghc-new-co' commit 6df3a040da3dbddee67c6e30a892f87e6b164383 Author: Ian Lynagh <igloo at earth.li> Date: Sun May 8 17:05:50 2011 +0100 Follow changes in SDoc commit f420cc48b9259f0b1afd2438b12f9a2bde57053d Author: Jose Pedro Magalhaes <jpm at cs.uu.nl> Date: Wed May 4 17:31:52 2011 +0200 Adapt haddock to the removal of HsNumTy and TypePat. commit 797ab27bdccf39c73ccad374fea265f124cb52ea Merge: 1d81436 5a91450 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:05:03 2011 +0100 Merge remote branch 'origin/master' into ghc-new-co commit 1d8143659a81cf9611668348e33fd0775c7ab1d2 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:03:46 2011 +0100 Wibbles for ghc-new-co branch commit 5a91450e2ea5a93c70bd3904b022445c9cc82488 Author: Ian Lynagh <igloo at earth.li> Date: Fri Apr 22 00:51:56 2011 +0100 Follow defaultDynFlags change in GHC - - - - - 498da5ae by David Waern at 2011-06-11T00:33:33+00:00 * Merge in git patch from Michal Terepeta >From 6fc71d067738ef4b7de159327bb6dc3d0596be29 Mon Sep 17 00:00:00 2001 From: Michal Terepeta <michal.terepeta at gmail.com> Date: Sat, 14 May 2011 19:18:22 +0200 Subject: [PATCH] Follow the change of TypeSig in GHC. This follows the change in GHC to make TypeSig take a list of names (instead of just one); GHC ticket haskell/haddock#1595. This should also improve the Haddock output in case the user writes a type signature that refers to many names: -- | Some comment.. foo, bar :: ... will now generate the expected output with one signature for both names. - - - - - 094607fe by Ian Lynagh at 2011-06-17T19:10:29+01:00 Fix build - - - - - 8fa35740 by Ian Lynagh at 2011-06-26T21:06:40+01:00 Bump GHC dep to allow 7.2 - - - - - e4d2ca3c by Ian Lynagh at 2011-07-07T23:06:28+01:00 Relax base dep - - - - - b948fde9 by Ian Lynagh at 2011-07-28T16:39:45+01:00 GHC build system: Don't install the datafiles twice - - - - - f82f6d70 by Simon Marlow at 2011-08-11T12:08:15+01:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - b341cc12 by Max Bolingbroke at 2011-08-22T20:25:27+01:00 Fix compilation with no-pred-ty GHC - - - - - 30494581 by Max Bolingbroke at 2011-08-23T10:20:54+01:00 Remaining fixes for PredTy removal - - - - - 0b197138 by Max Bolingbroke at 2011-08-26T08:27:45+01:00 Rename factKind to constraintKind - - - - - a379bec5 by Max Bolingbroke at 2011-09-04T12:54:47+01:00 Deal with change to IParam handling in GHC - - - - - f94e421b by Max Bolingbroke at 2011-09-06T17:34:31+01:00 Adapt Haddock for the ConstraintKind extension changes - - - - - 8821e5cc by Max Bolingbroke at 2011-09-09T08:24:59+01:00 Ignore associated type defaults (just as we ignore default methods) - - - - - 31a0afd4 by Max Bolingbroke at 2011-09-09T09:06:00+01:00 Merge branch 'no-pred-ty' of ssh://darcs.haskell.org/srv/darcs/haddock into no-pred-ty - - - - - dd3b530a by Max Bolingbroke at 2011-09-09T14:10:25+01:00 Merge branch 'no-pred-ty' Conflicts: src/Haddock/Convert.hs - - - - - 5f25ec96 by Max Bolingbroke at 2011-09-09T14:10:40+01:00 Replace FactTuple with ConstraintTuple - - - - - cd30b9cc by David Waern at 2011-09-26T02:17:55+02:00 Bump to version 2.9.3 - - - - - 4fbfd397 by Max Bolingbroke at 2011-09-27T14:55:21+01:00 Follow changes to BinIface Name serialization - - - - - 92257d90 by David Waern at 2011-09-30T23:45:07+02:00 Fix problem with test files not added to distribution tarball - - - - - 00255bda by David Waern at 2011-09-30T23:48:24+02:00 Merge branch 'development' - - - - - 5421264f by David Waern at 2011-10-01T01:25:39+02:00 Merge in darcs patch from Simon Meier: Wed Jun 1 19:41:16 CEST 2011 iridcode at gmail.com * prettier haddock coverage info The new coverage info rendering uses less horizontal space. This reduces the number of unnecessary line-wrappings. Moreover, the most important information, how much has been documented already, is now put up front. Hopefully, this makes it more likely that a library author is bothered by the low coverage of his modules and fixes that issue ;-) - - - - - 07d318ef by David Waern at 2011-10-01T01:34:10+02:00 Use printException instead of deprecated printExceptionAndWarnings - - - - - 40d52ee4 by David Waern at 2011-10-01T01:41:13+02:00 Merge in darcs pach: Mon Apr 11 18:09:54 JST 2011 Liyang HU <haddock at liyang.hu> * Remember collapsed sections in index.html / haddock-util.js - - - - - 279d6dd4 by David Waern at 2011-10-01T01:55:45+02:00 Merge in darcs patch: Joachim Breitner <mail at joachim-breitner.de>**20110619201645 Ignore-this: f6c51228205b0902ad5bfad5040b989a As reported on http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=578301, generating the global index takes much too long if type-level (with lots of auto-generated types) is installed. The patch avoids a quadratic runtime in the subfunction getIfaceIndex of ppHtmlIndex by using a temporary set. Runtime improvement observed here from 25.36s to 2.86s. - - - - - d1612383 by David Waern at 2011-10-01T01:56:48+02:00 Merge branch 'development' - - - - - 347520c1 by David Waern at 2011-10-01T01:56:54+02:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9a0c95e8 by David Waern at 2011-10-01T02:19:10+02:00 Improve .cabal file - - - - - 6967dc64 by Ian Lynagh at 2011-10-01T01:34:06+01:00 Follow changes to ForeignImport/ForeignExport in GHC - - - - - 565cb26b by Simon Marlow at 2011-10-04T00:15:04+02:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - 8b74f512 by David Waern at 2011-10-04T00:18:17+02:00 Requre ghc >= 7.2 - - - - - 271d360c by David Waern at 2011-10-04T00:22:50+02:00 Bump version to 2.9.4 - - - - - 37f3edb0 by David Waern at 2011-10-06T02:30:21+02:00 Add alex and happy to build-tools. - - - - - 7ac2bb6e by David Terei at 2011-10-12T14:02:55-07:00 Add safe haskell indication to haddock output - - - - - 42c91a47 by David Terei at 2011-10-12T14:06:03-07:00 Fix CSS issue with info table not being contained in module header - - - - - 0eddab6c by David Terei at 2011-10-12T14:06:58-07:00 Add safe haskell indication to haddock output - - - - - 3df058eb by David Terei at 2011-10-12T14:07:07-07:00 Fix CSS issue with info table not being contained in module header - - - - - a40a6c3f by David Waern at 2011-10-22T11:29:06+02:00 Bump .haddock file version since the format has changed recently - - - - - 8a6254be by David Waern at 2011-10-22T11:30:42+02:00 Merge branch 'development' - - - - - 642e3e02 by David Waern at 2011-10-23T21:23:39+02:00 Sort import list - - - - - 36371cf8 by David Waern at 2011-10-23T22:48:18+02:00 Remove NEW_GHC_LAYOUT conditional. - - - - - 5604b499 by David Waern at 2011-10-27T00:15:03+02:00 Add --print-ghc-path. - - - - - 463499fa by David Waern at 2011-10-27T00:16:22+02:00 Make testsuite able to find its dependencies automatically. - - - - - a3506172 by Ryan Newton at 2011-11-05T05:59:58-04:00 Improved declNames internal error. Added a case to handle DocD. - - - - - 001b8baf by David Waern at 2011-11-05T20:37:29+01:00 Rename copy.hs -> accept.hs. - - - - - 55d808d3 by David Waern at 2011-11-05T23:30:02+01:00 Fix build. - - - - - deb5c3be by David Waern at 2011-11-06T00:01:47+01:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9b663554 by David Waern at 2011-11-06T00:03:45+01:00 Merge https://github.com/rrnewton/haddock - - - - - 1abb0ff6 by David Waern at 2011-11-06T01:20:37+01:00 Use getDeclMainBinder instead of declNames. - - - - - 4b005c01 by David Waern at 2011-11-06T19:09:53+01:00 Fix build. - - - - - c2c51bc7 by Ian Lynagh at 2011-11-06T23:01:33+00:00 Remove -DNEW_GHC_LAYOUT in ghc.mk - - - - - f847d703 by Jose Pedro Magalhaes at 2011-11-11T09:07:39+00:00 New kind-polymorphic core This big patch implements a kind-polymorphic core for GHC. The current implementation focuses on making sure that all kind-monomorphic programs still work in the new core; it is not yet guaranteed that kind-polymorphic programs (using the new -XPolyKinds flag) will work. For more information, see http://haskell.org/haskellwiki/GHC/Kinds - - - - - 7d7c3b09 by Jose Pedro Magalhaes at 2011-11-16T21:42:22+01:00 Follow changes to tuple sorts in master - - - - - 8430e03e by Simon Peyton Jones at 2011-11-17T10:20:27+00:00 Remove redundant imports - - - - - d1b06832 by Ian Lynagh at 2011-11-19T01:33:21+00:00 Follow GHC build system change to the way we call rm - - - - - 9e2230ed by David Waern at 2011-11-24T15:00:24+01:00 Fix a bug in test runner and get rid of regex-compat dependency. - - - - - 52039b21 by David Waern at 2011-11-24T23:55:36+01:00 Avoid haskell98 dependency in test - - - - - 92e1220d by David Waern at 2011-11-25T00:03:33+01:00 Avoid depency on regex-compat also in accept.hs. - - - - - ddac6b6f by David Waern at 2011-11-25T02:13:38+01:00 Accept test output. - - - - - 5a720455 by David Waern at 2011-11-25T02:16:20+01:00 Some more changes to test scripts. - - - - - 170a9004 by David Waern at 2011-11-25T02:30:41+01:00 Add flag --interface-version. - - - - - d225576c by David Waern at 2011-11-25T02:39:26+01:00 Remove #ifs for older compiler versions. - - - - - f0d0a4f5 by David Waern at 2011-11-26T04:20:12+01:00 Give preference to type over data constructors for doc comment links at renaming time. Previously this was done in the backends. Also, warn when a doc comment refers to something that is in scope but which we don't have the .haddock file for. These changes mean we can make DocIdentifier [a] into DocIdentifier a. - - - - - eef0e776 by David Waern at 2011-11-26T17:01:06+01:00 Allow doc comments to link to out-of-scope things (#78). (A bug that should have been fixed long ago.) - - - - - 565ad529 by David Waern at 2011-11-26T19:56:21+01:00 Update tests. - - - - - fb3ce7b9 by David Waern at 2011-11-26T21:44:28+01:00 Cleanup. - - - - - d0328126 by David Waern at 2011-11-26T22:10:28+01:00 Fix module reference bug. - - - - - c03765f8 by David Waern at 2011-12-03T05:20:20+01:00 Slightly better behaviour on top-levels without type signatures. - Docs don't get attached to the next top-level with signature by mistake. - If there's an export list and the top-level is part of it, its doc comment shows up in the documentation. - - - - - 48461d31 by David Waern at 2011-12-03T05:38:10+01:00 Add a test for Unicode doc comments. - - - - - 549c4b4e by David Waern at 2011-12-03T19:07:55+01:00 Cleanup. - - - - - 7bfecf91 by David Waern at 2011-12-03T20:13:08+01:00 More cleanup. - - - - - 14fab722 by Ian Lynagh at 2011-12-12T21:21:35+00:00 Update dependencies and binaryInterfaceVersion - - - - - 469e6568 by Ian Lynagh at 2011-12-18T12:56:16+00:00 Fix (untested) building from source tarball without alex/happy haddock's .cabal file was declaring that it needed alex and happy to build, but in the GHC source tarballs it doesn't. - - - - - 895c9a8c by David Waern at 2011-12-27T12:57:43+01:00 Go back to having a doc, sub and decl map instead of one big decl map. This setup makes more sense since when we add value bindings to the processed declarations (for type inference), we will have multiple declarations which should share documentation. Also, we already have a separate doc map for instances which we can now merge into the main doc map. Another benefit is that we don't need the DeclInfo type any longer. - - - - - 736767d9 by David Waern at 2011-12-27T13:33:41+01:00 Merge ../../../haddock Conflicts: src/Haddock/InterfaceFile.hs - - - - - 20016f79 by David Waern at 2011-12-27T13:57:23+01:00 Bump version. - - - - - 31f276fb by David Waern at 2011-12-27T13:57:32+01:00 Merge ../ghc/utils/haddock - - - - - 95b367cd by David Waern at 2011-12-27T14:57:29+01:00 Update tests following version bump. - - - - - fa3c94cd by David Waern at 2011-12-27T14:57:51+01:00 Get rid of quite unnecessary use of different lists. - - - - - 9c4d3c54 by David Waern at 2011-12-27T15:26:42+01:00 Cleanup. - - - - - 2caf9f90 by David Waern at 2011-12-27T16:18:05+01:00 Wibbles. - - - - - 3757d09b by David Waern at 2011-12-27T20:50:26+01:00 Complete support for inferring types for top-level bindings. - - - - - 53418734 by David Waern at 2011-12-28T15:02:13+01:00 Minor fixes and cleanup. - - - - - 0c9d0385 by Ian Lynagh at 2012-01-03T18:31:29+00:00 Follow rename of Instance to ClsInst in GHC - - - - - c9bc969a by Simon Hengel at 2012-01-12T21:28:14+01:00 Make sure that generated xhtml is valid (close haskell/haddock#186) Thanks to Phyx. - - - - - 836a0b9a by David Waern at 2012-02-01T02:30:05+01:00 Fix bug introduced in my recent refactoring. - - - - - c7d733eb by David Waern at 2012-02-01T02:30:26+01:00 Cleanup mkMaps and avoid quadratic behaviour. - - - - - da3cda8f by David Waern at 2012-02-01T02:56:56+01:00 Require ghc >= 7.4. - - - - - 83a3287e by David Waern at 2012-02-01T02:57:36+01:00 Update CHANGES. - - - - - 93408f0b by Simon Hengel at 2012-02-04T00:48:04+01:00 Add reference renderings - - - - - 49d00d2c by Simon Hengel at 2012-02-04T00:48:25+01:00 Set unit tests for parser back to work - - - - - eb450980 by Simon Hengel at 2012-02-04T00:49:07+01:00 Add .gitignore - - - - - a841602c by Simon Hengel at 2012-02-04T00:49:16+01:00 Add .ghci file - - - - - 8861199d by Simon Hengel at 2012-02-04T00:49:29+01:00 tests/html-tests/copy.hs: Use mapM_ instead of mapM So we do net get a list of () on stdout when running with runhaskell. - - - - - b477d9b5 by Simon Hengel at 2012-02-04T00:49:46+01:00 Remove index files from golden tests - - - - - 9dbda34e by Simon Hengel at 2012-02-04T00:49:57+01:00 Add /tests/html-tests/tests/*index*.ref to .gitignore - - - - - a9434817 by Simon Hengel at 2012-02-04T00:50:04+01:00 Add DocWarning to Doc The Xhtml backend has special markup for that, Hoogle and LaTeX reuse what we have for DocEmphasis. - - - - - de2fb6fa by Simon Hengel at 2012-02-04T00:50:13+01:00 Add support for module warnings - - - - - 0640920e by Simon Hengel at 2012-02-04T00:50:21+01:00 Add tests for module warnings - - - - - 30ce0d77 by Simon Hengel at 2012-02-04T00:50:29+01:00 Add support for warnings - - - - - bb367960 by Simon Hengel at 2012-02-04T00:50:37+01:00 Add tests for warnings - - - - - 6af1dc2d by Simon Hengel at 2012-02-04T00:50:50+01:00 Expand type signatures in export list (fixes haskell/haddock#192) - - - - - a06cbf25 by Simon Hengel at 2012-02-04T00:51:04+01:00 Expand type signatures for modules without explicit export list - - - - - 57dda796 by Simon Hengel at 2012-02-04T00:51:15+01:00 Remove obsolete TODO - - - - - 270c3253 by David Waern at 2012-02-04T00:51:24+01:00 Fix issues in support for warnings. * Match against local names only. * Simplify (it's OK to map over the warnings). - - - - - 683634bd by David Waern at 2012-02-04T00:55:11+01:00 Some cleanup and make sure we filter warnings through exports. - - - - - 210cb4ca by David Waern at 2012-02-04T03:01:30+01:00 Merge branch 'fix-for-186' of https://github.com/sol/haddock into ghc-7.4 - - - - - e8db9031 by David Waern at 2012-02-04T03:07:51+01:00 Style police. - - - - - 261f9462 by David Waern at 2012-02-04T03:20:16+01:00 Update tests. - - - - - 823cfc7c by David Waern at 2012-02-04T03:21:12+01:00 Use mapM_ in accept.hs as well. - - - - - 873dd619 by David Waern at 2012-02-04T03:21:33+01:00 Remove copy.hs - use accept.hs instead. - - - - - 0e31a14a by David Waern at 2012-02-04T03:47:33+01:00 Use <> instead of mappend. - - - - - 2ff7544f by David Waern at 2012-02-04T03:48:55+01:00 Remove code for older ghc versions. - - - - - dacf2786 by David Waern at 2012-02-04T15:52:51+01:00 Clean up some code from last SoC project. - - - - - 00cbb117 by David Waern at 2012-02-04T21:43:49+01:00 Mostly hlint-inspired cleanup. - - - - - 7dc86cc2 by Simon Peyton Jones at 2012-02-06T09:14:41+00:00 Track changes in HsDecls - - - - - f91f82fe by Ian Lynagh at 2012-02-16T13:40:11+00:00 Follow changes in GHC caused by the CAPI CTYPE pragma - - - - - a0ea6b0b by Ian Lynagh at 2012-02-22T02:26:12+00:00 Follow changes in GHC - - - - - b23b07d1 by Simon Peyton Jones at 2012-03-02T16:36:41+00:00 Follow changes in data representation from the big PolyKinds commit - - - - - 43406022 by Simon Hengel at 2012-03-05T11:18:34+01:00 Save/restore global state for static flags when running GHC actions This is necessary if we want to run createInterfaces (from Documentation.Haddock) multiple times in the same process. - - - - - 9fba16fe by Paolo Capriotti at 2012-03-06T10:57:33+00:00 Update .gitignore. - - - - - a9325044 by Simon Peyton Jones at 2012-03-14T17:35:42+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - fd48065a by Iavor Diatchki at 2012-03-15T22:43:35-07:00 Add support for type-level literals. - - - - - 2e8206dd by Simon Peyton Jones at 2012-03-16T14:18:22+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - 93e13319 by Simon Peyton Jones at 2012-03-17T01:04:05+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock Conflicts: src/Haddock/Convert.hs - - - - - d253fa71 by Iavor Diatchki at 2012-03-19T20:12:18-07:00 Merge remote-tracking branch 'origin/master' into type-nats - - - - - fc40acc8 by Iavor Diatchki at 2012-03-19T20:31:27-07:00 Add a missing case for type literals. - - - - - fd2ad699 by Iavor Diatchki at 2012-03-24T13:28:29-07:00 Rename variable to avoid shadowing warning. - - - - - 9369dd3c by Simon Peyton Jones at 2012-03-26T09:14:23+01:00 Follow refactoring of TyClDecl/HsTyDefn - - - - - 38825ca5 by Simon Peyton Jones at 2012-03-26T09:14:37+01:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - 4324ac0f by David Waern at 2012-04-01T01:51:19+02:00 Disable unicode test. - - - - - 3165b750 by David Waern at 2012-04-01T01:51:34+02:00 Take reader environment directly from TypecheckedSource. - - - - - 213b644c by David Waern at 2012-04-01T01:55:20+02:00 Cleanup. - - - - - 3118b4ba by David Waern at 2012-04-01T02:16:15+02:00 Don't filter out unexported names from the four maps - fixes a regression. - - - - - d6524e17 by David Waern at 2012-04-01T02:40:34+02:00 Fix crash when using --qual. Naughty GHC API! - - - - - ea3c43d8 by Henning Thielemann at 2012-04-01T13:03:07+02:00 add QualOption type for distinction between qualification argument given by the user and the actual qualification for a concrete module - - - - - 5422ff05 by Henning Thielemann at 2012-04-01T16:25:02+02:00 emit an error message when the --qual option is used incorrectly - - - - - 026e3404 by David Waern at 2012-04-01T18:10:30+02:00 Don't crash on unicode strings in doc comments. - - - - - ce006632 by David Waern at 2012-04-01T20:13:35+02:00 Add test for --ignore-all-exports flag/ignore-exports pragma. - - - - - 6e4dd33c by David Waern at 2012-04-01T20:21:03+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.4 - - - - - 734ae124 by Henning Thielemann at 2012-04-01T20:22:10+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - 622f9ba5 by David Waern at 2012-04-01T21:26:13+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 55ce17cb by Henning Thielemann at 2012-04-01T22:03:25+02:00 'abbreviate' qualification style - basic support Currently we ignore the package a module is imported from. This means that a module import would shadow another one with the same module name from a different package. - - - - - c85314ef by David Waern at 2012-04-01T22:05:12+02:00 Check qualification option before processing modules. - - - - - ae4b626c by Henning Thielemann at 2012-04-02T00:19:36+02:00 abbreviated qualification: use Packages.lookupModuleInAllPackages for finding the package that a module belongs to - - - - - 60bdbcf5 by Henning Thielemann at 2012-04-02T00:25:31+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - df44301d by Henning Thielemann at 2012-04-02T00:29:05+02:00 qualification style 'abbreviated' -> 'aliased' - - - - - f4192a64 by David Waern at 2012-04-02T01:05:47+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 7ba09067 by David Terei at 2012-04-04T15:08:21-07:00 Fix reporting of modules safe haskell mode (#5989) - - - - - d0cc33d0 by David Terei at 2012-04-06T15:50:41+01:00 Fix reporting of modules safe haskell mode (#5989) - - - - - 6e3434c5 by Simon Peyton Jones at 2012-04-20T18:37:46+01:00 Track changes in HsSyn - - - - - 22014ed0 by Simon Peyton Jones at 2012-05-11T22:45:15+01:00 Follow changes to LHsTyVarBndrs - - - - - d9a07b24 by David Waern at 2012-05-15T01:46:35+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - a6c4ebc6 by David Waern at 2012-05-16T02:18:32+02:00 Update CHANGES. - - - - - 8e181d29 by David Waern at 2012-05-16T02:27:56+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - e358210d by David Waern at 2012-05-16T02:35:33+02:00 Mention the new aliased --qual mode in CHANGES. - - - - - efd36a28 by David Waern at 2012-05-16T21:33:13+02:00 Bump version number. - - - - - d6b3af14 by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for deprecated record field - - - - - 927f800e by Simon Hengel at 2012-05-17T19:08:20+02:00 Use >>= instead of fmap and join - - - - - 048b41d5 by Simon Hengel at 2012-05-17T19:08:20+02:00 newtype-wrap Doc nodes for things that may have warnings attached - - - - - e3a89fc3 by Simon Hengel at 2012-05-17T19:08:20+02:00 Attach warnings to `Documentation` type - - - - - 5d4cc43d by Simon Hengel at 2012-05-17T19:08:20+02:00 Simplify lookupWarning - - - - - cf8ae69d by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for haskell/haddock#205 - - - - - cb409b19 by Simon Peyton Jones at 2012-05-25T08:30:11+01:00 Follow changes in LHsTyVarBndrs - - - - - 2d5f4179 by Simon Hengel at 2012-05-26T19:21:29+02:00 Add Applicative instance for (GenRnM a) - - - - - e4373060 by Simon Hengel at 2012-05-26T19:21:33+02:00 Use a map for warnings, as suggested by @waern - - - - - 597a68c7 by Simon Hengel at 2012-05-27T08:48:24+02:00 Add an optional label to URLs - - - - - ef1ac7fe by Simon Hengel at 2012-05-27T08:48:24+02:00 Add support for hyperlink labels to parser - - - - - 41f2adce by Simon Hengel at 2012-05-27T08:48:24+02:00 Add golden test for hyperlinks - - - - - 83d5e764 by Simon Hengel at 2012-05-27T08:50:02+02:00 Use LANGUAGE pragmas instead of default-extensions in cabal file - - - - - ddb755e5 by Simon Hengel at 2012-05-27T08:50:02+02:00 Fix typo in comment - - - - - 110676b4 by Simon Hengel at 2012-05-27T08:50:02+02:00 Add a type signature for a where-binding - - - - - 7d9ba2a0 by Ian Lynagh at 2012-06-12T14:38:01+01:00 Follow changes in GHC - - - - - 47c704f2 by Ian Lynagh at 2012-06-12T18:52:16+01:00 Follow changes in GHC - - - - - e1efe1ab by Simon Peyton Jones at 2012-06-13T17:25:29+01:00 Follow changes for the implementation of implicit parameters - - - - - 69abc81c by Ian Lynagh at 2012-06-19T22:52:58+01:00 Follow changes in base - - - - - 9d074a21 by Paolo Capriotti at 2012-06-22T18:26:47+01:00 Use right docMap to get decl documentation. - - - - - e3292ef6 by Ian Lynagh at 2012-07-15T01:31:19+01:00 Follow changes in GHC - - - - - ceae56b0 by Ian Lynagh at 2012-07-16T21:22:48+01:00 Fix haddock following some GHC changes Passing _|_ as the Settings for defaultDynFlags no longer works well enough - - - - - 9df72735 by Paolo Capriotti at 2012-07-19T16:49:32+01:00 Forward port changes from stable. - - - - - 572f5fcf by Ian Lynagh at 2012-07-19T20:38:26+01:00 Merge branch 'master' of darcs.haskell.org:/srv/darcs//haddock - - - - - 9195aca4 by Paolo Capriotti at 2012-07-20T10:27:28+01:00 Update dependencies. - - - - - 33db3923 by Ian Lynagh at 2012-07-20T17:54:43+01:00 Build with GHC 7.7 - - - - - 925a2cea by David Waern at 2012-07-23T16:50:40+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.6 Conflicts: src/Haddock/InterfaceFile.hs - - - - - d710ef97 by David Waern at 2012-07-23T16:52:07+02:00 Bump version number. - - - - - eb0c2f83 by David Waern at 2012-07-23T16:57:58+02:00 Update CHANGES. - - - - - b3f56943 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Hide "internal" instances This fixes haskell/haddock#37 (http://trac.haskell.org/haddock/ticket/37) Precisely, we show an instance iff its class and all the types are exported by non-hidden modules. - - - - - a70aa412 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Tests for hiding instances (#37) - - - - - c0f4aa58 by Simon Hengel at 2012-07-27T13:00:13+03:00 Add an other test for hiding instances (#37) - - - - - a7ed6268 by Ian Lynagh at 2012-08-07T14:48:13+01:00 Follow changes in GHC - - - - - 0ab30d38 by Ian Lynagh at 2012-08-13T22:12:27+01:00 Improve haddock memory usage - - - - - 0eaa4e30 by Ian Lynagh at 2012-08-13T23:58:46+01:00 Improve haddock memory usage - - - - - 659d26cf by Ian Lynagh at 2012-08-14T13:16:48+01:00 Remove some temporary pragmas I accidentally recorded - - - - - d97fceb6 by Simon Hengel at 2012-08-25T13:19:34+02:00 Add missing dependency to library - - - - - 4c910697 by Simon Hengel at 2012-08-28T07:39:14+02:00 Move .ghci to project root - - - - - fc3c601a by Simon Hengel at 2012-08-28T07:39:14+02:00 accept.hs: Ignore some files - - - - - 1af9b984 by Simon Hengel at 2012-08-28T07:40:04+02:00 Update reference renderings (bump version) - - - - - 980dc253 by Simon Hengel at 2012-08-28T07:40:32+02:00 Update reference renderings (remove links for ()) - - - - - 33651dbf by Simon Hengel at 2012-08-28T07:41:50+02:00 Update documentation of `runInteractiveProcess` in reference rendering - - - - - 7ab25078 by David Waern at 2012-09-07T10:38:50+02:00 Merge branch 'hiddenInstances2' of http://github.com/feuerbach/haddock into ghc-7.6 - - - - - c3de3a4b by David Waern at 2012-09-07T14:29:27+02:00 Follow changes in GHC. - - - - - 298c43ac by David Waern at 2012-09-07T14:59:24+02:00 Update CHANGES. - - - - - e797993a by David Waern at 2012-09-07T15:21:30+02:00 Update ANNOUNCE. - - - - - d0b44790 by David Waern at 2012-09-07T15:22:43+02:00 Merge branch 'hidden-instances' into ghc-7.6 - - - - - 41a4adc8 by Simon Hengel at 2012-09-08T12:08:37+02:00 Update doc/README - - - - - 71ad1040 by Simon Hengel at 2012-09-08T12:17:17+02:00 Add documentation for URL labels - - - - - 9bb41afd by Simon Peyton Jones at 2012-09-20T18:14:26+01:00 Follow data type changes in the tc-untouchables branch Relating entirely to SynTyConRhs - - - - - b8139bfa by Simon Hengel at 2012-09-21T14:24:16+02:00 Disable Unicode test for now - - - - - a5fafdd7 by Simon Hengel at 2012-09-21T14:35:45+02:00 Update TypeOperators test for GHC 7.6.1 Type operators can't be used as type variables anymore! - - - - - 6ccf0025 by Simon Hengel at 2012-09-21T16:02:24+02:00 Remove (Monad (Either e)) instance from ref. rendering of CrossPackageDocs I do not really understand why the behavior changed, so I'll open a ticket, so that we can further investigate. - - - - - b5c6c138 by Ian Lynagh at 2012-09-27T02:00:57+01:00 Follow changes in GHC build system - - - - - b98eded0 by David Waern at 2012-09-27T15:37:02+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 76cc2051 by David Waern at 2012-09-27T15:48:19+02:00 Update hidden instances tests. - - - - - aeaa1c59 by David Waern at 2012-09-28T10:21:32+02:00 Make API buildable with GHC 7.6. - - - - - d76be1b0 by Simon Peyton Jones at 2012-09-28T15:57:05+01:00 Merge remote-tracking branch 'origin/master' into tc-untouchables - - - - - a1922af8 by David Waern at 2012-09-28T19:50:20+02:00 Fix spurious superclass constraints bug. - - - - - bc41bdbb by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove old examples - - - - - bed7d3dd by Simon Hengel at 2012-10-01T11:30:51+02:00 Adapt parsetests for GHC 7.6.1 - - - - - dcdb22bb by Simon Hengel at 2012-10-01T11:30:51+02:00 Add test-suite section for parsetests to cabal file + get rid of HUnit dependency - - - - - 1e5263c9 by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove test flag from cabal file This was not really used. - - - - - 4beee98b by David Waern at 2012-09-28T23:42:28+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 11dd2256 by Ian Lynagh at 2012-10-03T16:17:35+01:00 Follow change in GHC build system - - - - - fbd77962 by Simon Hengel at 2012-10-03T18:49:40+02:00 Remove redundant dependency from cabal file - - - - - 09218989 by Simon Hengel at 2012-10-04T16:03:05+02:00 Fix typo - - - - - 93a2d5f9 by Simon Hengel at 2012-10-04T16:11:41+02:00 Remove trailing whitespace from cabal file - - - - - c8b46cd3 by Simon Hengel at 2012-10-04T16:12:17+02:00 Export Haddock's main entry point from library - - - - - b411e77b by Simon Hengel at 2012-10-04T16:29:46+02:00 Depend on library for executable The main motivation for this is to increase build speed. In GHC's source tree the library is not build, but all modules are now required for the executable, so that GHC's validate will now detect build failures for the library. - - - - - f8f0979f by Simon Hengel at 2012-10-05T00:32:57+02:00 Set executable flag for Setup.lhs - - - - - dd045998 by Simon Hengel at 2012-10-07T16:44:06+02:00 Extend rather than set environment when running HTML tests On some platforms (e.g. ppc64) GHC requires gcc in the path. - - - - - 7b39c3ae by Simon Hengel at 2012-10-07T17:05:45+02:00 cross-package test: re-export IsString instead of Monad There is a monad instance for Q, which is not available on platforms that do not have GHCi support. This caused CrossPackageDocs to fail on those platforms. Re-exporting IsString should test the same thing, but it works on all platforms. - - - - - 0700c605 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Fix some warnings - - - - - f78eca79 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Make -Wall proof - - - - - 6beec041 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Use listToMaybe/fromMaybe instead of safeHead/maybe - - - - - 44b8ce86 by Ian Lynagh at 2012-10-08T21:59:46+01:00 Follow changes in GHC - - - - - 6da5f702 by Simon Hengel at 2012-10-09T11:16:19+02:00 Update .ghci - - - - - 9ac1a1b9 by Kazu Yamamoto at 2012-10-09T12:45:31+02:00 Add markup support for properties - - - - - 1944cb42 by Simon Hengel at 2012-10-09T12:45:31+02:00 Simplify lexing/parsing of properties In contrast to what we do for examples, we do not really need to capture the "prompt" here. - - - - - bffd8e62 by Simon Hengel at 2012-10-09T13:40:14+02:00 Add HTML test for properties - - - - - 2fe9c5cb by Simon Hengel at 2012-10-09T13:40:21+02:00 Add unit tests for properties - - - - - 874e361b by Simon Hengel at 2012-10-09T13:40:33+02:00 Bump interface version - - - - - 2506cc37 by Simon Hengel at 2012-10-09T15:15:04+02:00 Fix parser bug - - - - - 743d2b7d by Simon Hengel at 2012-10-09T15:31:06+02:00 Allow to load interface files with compatible versions - - - - - 981a1660 by Simon Hengel at 2012-10-10T10:32:05+02:00 Export more types from Documentation.Haddock (fixes haskell/haddock#216) - - - - - dff7dc76 by Simon Hengel at 2012-10-10T11:15:19+02:00 Update ANNOUNCE and CHANGES - - - - - edd2bb01 by Simon Hengel at 2012-10-10T11:22:50+02:00 Bump version - - - - - 5039163b by Simon Hengel at 2012-10-10T13:56:04+02:00 Fix typo in documentation - - - - - e4ce34da by Simon Hengel at 2012-10-10T14:28:35+02:00 Add documentation for properties - - - - - 9555ebca by Simon Hengel at 2012-10-11T10:49:04+02:00 Remove redundant if-defs, more source documentation - - - - - 87aa67e1 by Simon Hengel at 2012-10-11T12:32:51+02:00 Adapt cabal file - - - - - c44c1dee by Simon Hengel at 2012-10-11T12:41:58+02:00 Require ghc 7.6 - - - - - 8383bc34 by Simon Hengel at 2012-10-11T12:50:24+02:00 Bump version - - - - - 1030eb38 by Simon Hengel at 2012-10-11T12:55:44+02:00 Update ANNOUNCE and CHANGES - - - - - 74955088 by Simon Hengel at 2012-10-12T09:49:31+02:00 Improve note about `binaryInterfaceVersion` (thanks David) - - - - - ee30f6b7 by Simon Hengel at 2012-10-13T13:40:59+02:00 Update version in html tests, rpm spec file, and user manual - - - - - f2861f18 by Simon Hengel at 2012-10-13T14:40:33+02:00 Remove unused MonadFix constraint - - - - - dfdf1a74 by Simon Hengel at 2012-10-13T15:15:38+02:00 Minor code simplification - - - - - 4ecd1e70 by Simon Hengel at 2012-10-13T15:33:43+02:00 Increase code locality - - - - - f7df5cc9 by Simon Hengel at 2012-10-13T16:03:12+02:00 Minor code simplification - - - - - e737eb6e by Simon Hengel at 2012-10-13T19:03:04+02:00 Handle HsExplicitListTy in renameer (fixes haskell/haddock#213) - - - - - c2dc8f17 by Simon Hengel at 2012-10-13T20:46:31+02:00 Better error messages - - - - - 14d48b4c by Simon Hengel at 2012-10-14T00:21:07+02:00 Simplify RnM type - - - - - 6c2cc547 by Simon Hengel at 2012-10-14T00:23:35+02:00 Simplify lookupRn - - - - - bc77ce85 by Simon Hengel at 2012-10-14T01:51:32+02:00 Organize unite tests hierarchically - - - - - 2306d117 by Simon Hengel at 2012-10-14T10:34:58+02:00 Handle more cases in renameType - - - - - 8a864203 by Simon Hengel at 2012-10-14T11:47:59+02:00 Add mini_HiddenInstances.html.ref and mini_HiddenInstancesB.html.ref - - - - - 3a978eca by Simon Hengel at 2012-10-14T11:49:28+02:00 Add /tests/html-tests/output/ to .gitignore - - - - - db18888a by Simon Hengel at 2012-10-14T13:38:21+02:00 Allow haddock markup in deprecation messages - - - - - e7cfee9f by Simon Hengel at 2012-10-14T14:00:23+02:00 If parsing of deprecation message fails, include it verbatim - - - - - 242a85be by Simon Hengel at 2012-10-14T14:13:24+02:00 Add description for PruneWithWarning test - - - - - 43d33df1 by Simon Hengel at 2012-10-14T15:40:53+02:00 Minor formatting change - - - - - 22768c44 by Simon Hengel at 2012-10-14T16:03:43+02:00 Properly handle deprecation messages for re-exported things (fixes haskell/haddock#220) - - - - - cb4b9111 by Simon Hengel at 2012-10-14T17:30:28+02:00 Add build artifacts for documentation to .gitignore - - - - - 854cd8de by Simon Hengel at 2012-10-14T23:34:51+02:00 unit-tests: Improve readability Add IsString instance for (Doc RdrName) + use <> instead of DocAppend. - - - - - c4446d54 by Simon Hengel at 2012-10-14T23:37:21+02:00 unit-tests: Minor refactoring Rename parse to parseParas. - - - - - 04f2703c by Simon Hengel at 2012-10-15T00:36:42+02:00 Fix typo - - - - - 3d109e44 by Simon Hengel at 2012-10-15T10:30:07+02:00 Add description for DeprecatedReExport test - - - - - 84f0985c by Simon Hengel at 2012-10-15T14:54:19+02:00 Move resources to /resources directory - - - - - a5de7ca6 by Simon Hengel at 2012-10-15T15:46:18+02:00 Move HTML tests to directory /html-test/ - - - - - e21f727d by Simon Hengel at 2012-10-15T19:32:42+02:00 Move HTML reference renderings to /html-test/ref/ - - - - - 3a3c6c75 by Simon Hengel at 2012-10-15T19:32:42+02:00 Copy css, images, etc. on accept - - - - - 40ead6dc by Simon Hengel at 2012-10-15T19:32:42+02:00 Move unit tests to /test directory - - - - - 99a28231 by Simon Hengel at 2012-10-15T19:32:42+02:00 Fix Setup.lhs /usr/bin/runhaskell is not installed on all systems. - - - - - 95faf45e by Simon Hengel at 2012-10-15T19:32:42+02:00 Make test management scripts more robust * They are now independent from the current directory, and hence can be called from everywhere * On UNIX/Linux they can now be run as scripts - - - - - 027aaa2d by Simon Hengel at 2012-10-15T19:53:40+02:00 Add 'dev' flag to cabal file, that builds without -O2 That way --disable-optimization can be used, which decreases build time considerably. - - - - - e0266ede by Simon Hengel at 2012-10-15T20:03:43+02:00 Add test case for "spurious superclass constraints bug" - - - - - 52a2aa92 by Simon Hengel at 2012-10-15T20:28:55+02:00 Adapt accept.lhs, so that it ignores more index files - - - - - 53530781 by Simon Hengel at 2012-10-15T20:49:39+02:00 Rename html-test/runtests.lhs to html-test/run.lhs - - - - - 84518797 by Simon Hengel at 2012-10-15T20:49:39+02:00 Move source files for HTML tests to html-test/src - - - - - a911dc6c by Simon Hengel at 2012-10-15T20:49:39+02:00 Adapt output directory for HTML tests - - - - - d3c15857 by Ian Lynagh at 2012-10-16T16:54:43+01:00 Follow dopt->gopt rename - - - - - 956665a5 by Simon Hengel at 2012-10-18T08:42:48+02:00 Update html-test/README - - - - - 903b1029 by Simon Hengel at 2012-10-18T08:50:26+02:00 Use markdown for html-test/README - - - - - 150b4d63 by Ian Lynagh at 2012-10-18T16:36:00+01:00 Follow changes in GHC: 'flags' has been renamed 'generalFlags' - - - - - 41e04ff9 by Simon Hengel at 2012-11-28T09:54:35+01:00 Export missing types from Documentation.Haddock - - - - - 9be59237 by Ian Lynagh at 2012-11-30T23:20:47+00:00 Update dependencies - - - - - e06842f5 by Simon Hengel at 2012-12-07T20:58:05+01:00 Bump version - - - - - e3dbede0 by Simon Hengel at 2012-12-07T20:58:05+01:00 Add missing test files to cabal file (fixes haskell/haddock#230) - - - - - ee0dcca7 by Simon Hengel at 2012-12-07T20:58:05+01:00 Update CHANGES - - - - - 51601bdb by Simon Peyton Jones at 2012-12-19T17:28:35+00:00 Track changes in UNPACK pragma stuff - - - - - f2573bc1 by Richard Eisenberg at 2012-12-21T20:56:25-05:00 Implement overlapping type family instances. An ordered, overlapping type family instance is introduced by 'type instance where', followed by equations. See the new section in the user manual (7.7.2.2) for details. The canonical example is Boolean equality at the type level: type family Equals (a :: k) (b :: k) :: Bool type instance where Equals a a = True Equals a b = False A branched family instance, such as this one, checks its equations in order and applies only the first the matches. As explained in the note [Instance checking within groups] in FamInstEnv.lhs, we must be careful not to simplify, say, (Equals Int b) to False, because b might later unify with Int. This commit includes all of the commits on the overlapping-tyfams branch. SPJ requested that I combine all my commits over the past several months into one monolithic commit. The following GHC repos are affected: ghc, testsuite, utils/haddock, libraries/template-haskell, and libraries/dph. Here are some details for the interested: - The definition of CoAxiom has been moved from TyCon.lhs to a new file CoAxiom.lhs. I made this decision because of the number of definitions necessary to support BranchList. - BranchList is a GADT whose type tracks whether it is a singleton list or not-necessarily-a-singleton-list. The reason I introduced this type is to increase static checking of places where GHC code assumes that a FamInst or CoAxiom is indeed a singleton. This assumption takes place roughly 10 times throughout the code. I was worried that a future change to GHC would invalidate the assumption, and GHC might subtly fail to do the right thing. By explicitly labeling CoAxioms and FamInsts as being Unbranched (singleton) or Branched (not-necessarily-singleton), we make this assumption explicit and checkable. Furthermore, to enforce the accuracy of this label, the list of branches of a CoAxiom or FamInst is stored using a BranchList, whose constructors constrain its type index appropriately. I think that the decision to use BranchList is probably the most controversial decision I made from a code design point of view. Although I provide conversions to/from ordinary lists, it is more efficient to use the brList... functions provided in CoAxiom than always to convert. The use of these functions does not wander far from the core CoAxiom/FamInst logic. BranchLists are motivated and explained in the note [Branched axioms] in CoAxiom.lhs. - The CoAxiom type has changed significantly. You can see the new type in CoAxiom.lhs. It uses a CoAxBranch type to track branches of the CoAxiom. Correspondingly various functions producing and consuming CoAxioms had to change, including the binary layout of interface files. - To get branched axioms to work correctly, it is important to have a notion of type "apartness": two types are apart if they cannot unify, and no substitution of variables can ever get them to unify, even after type family simplification. (This is different than the normal failure to unify because of the type family bit.) This notion in encoded in tcApartTys, in Unify.lhs. Because apartness is finer-grained than unification, the tcUnifyTys now calls tcApartTys. - CoreLinting axioms has been updated, both to reflect the new form of CoAxiom and to enforce the apartness rules of branch application. The formalization of the new rules is in docs/core-spec/core-spec.pdf. - The FamInst type (in types/FamInstEnv.lhs) has changed significantly, paralleling the changes to CoAxiom. Of course, this forced minor changes in many files. - There are several new Notes in FamInstEnv.lhs, including one discussing confluent overlap and why we're not doing it. - lookupFamInstEnv, lookupFamInstEnvConflicts, and lookup_fam_inst_env' (the function that actually does the work) have all been more-or-less completely rewritten. There is a Note [lookup_fam_inst_env' implementation] describing the implementation. One of the changes that affects other files is to change the type of matches from a pair of (FamInst, [Type]) to a new datatype (which now includes the index of the matching branch). This seemed a better design. - The TySynInstD constructor in Template Haskell was updated to use the new datatype TySynEqn. I also bumped the TH version number, requiring changes to DPH cabal files. (That's why the DPH repo has an overlapping-tyfams branch.) - As SPJ requested, I refactored some of the code in HsDecls: * splitting up TyDecl into SynDecl and DataDecl, correspondingly changing HsTyDefn to HsDataDefn (with only one constructor) * splitting FamInstD into TyFamInstD and DataFamInstD and splitting FamInstDecl into DataFamInstDecl and TyFamInstDecl * making the ClsInstD take a ClsInstDecl, for parallelism with InstDecl's other constructors * changing constructor TyFamily into FamDecl * creating a FamilyDecl type that stores the details for a family declaration; this is useful because FamilyDecls can appear in classes but other decls cannot * restricting the associated types and associated type defaults for a * class to be the new, more restrictive types * splitting cid_fam_insts into cid_tyfam_insts and cid_datafam_insts, according to the new types * perhaps one or two more that I'm overlooking None of these changes has far-reaching implications. - The user manual, section 7.7.2.2, is updated to describe the new type family instances. - - - - - f788d0fb by Simon Peyton Jones at 2012-12-23T15:49:58+00:00 Track changes in HsBang - - - - - ca460a0c by Simon Peyton Jones at 2012-12-23T15:50:28+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - f078fea6 by Simon Peyton Jones at 2013-01-02T08:33:13+00:00 Use InstEnv.instanceSig rather than instanceHead (name change) - - - - - 88e41305 by Simon Peyton Jones at 2013-01-14T17:10:27+00:00 Track change to HsBang type - - - - - e1ad4e19 by Kazu Yamamoto at 2013-02-01T11:59:24+09:00 Merge branch 'ghc-7.6' into ghc-7.6-merge-2 Conflicts: haddock.cabal src/Haddock/Interface/AttachInstances.hs src/Haddock/Interface/Create.hs src/Haddock/Interface/LexParseRn.hs src/Haddock/InterfaceFile.hs src/Haddock/Types.hs Only GHC HEAD can compile this. GHC 7.6.x cannot compile this. Some test fail. - - - - - 62bec012 by Kazu Yamamoto at 2013-02-06T11:12:28+09:00 Using tcSplitSigmaTy in instanceHead' (FIXME is resolved.) - - - - - 013fd2e4 by Kazu Yamamoto at 2013-02-06T17:56:21+09:00 Refactoring instanceHead'. - - - - - 3148ce0e by Kazu Yamamoto at 2013-02-07T17:45:10+09:00 Using new syntax in html-test/src/GADTRecords.hs. - - - - - 626dabe7 by Gabor Greif at 2013-02-15T22:42:01+01:00 Typo - - - - - 1eb667ae by Ian Lynagh at 2013-02-16T17:02:07+00:00 Follow changes in base - - - - - 3ef8253a by Ian Lynagh at 2013-03-01T23:23:57+00:00 Follow changes in GHC's build system - - - - - 1a265a3c by Ian Lynagh at 2013-03-03T23:12:07+00:00 Follow changes in GHC build system - - - - - 69941c79 by Max Bolingbroke at 2013-03-10T09:38:28-07:00 Use Alex 3's Unicode support to properly lex source files as UTF-8 Signed-off-by: David Waern <david.waern at gmail.com> - - - - - ea687dad by Simon Peyton Jones at 2013-03-15T14:16:10+00:00 Adapt to tcRnGetInfo returning family instances too This API change was part of the fix to Trac haskell/haddock#4175. But it offers new information to Haddock: the type-family instances, as well as the class instances, of this type. This patch just drops the new information on the floor, but there's an open opportunity to use it in the information that Haddock displays. - - - - - 971a30b0 by Andreas Voellmy at 2013-05-19T20:47:39+01:00 Fix for haskell/haddock#7879. Changed copy of utils/haddock/html/resources/html to use "cp -RL" rather than "cp -R". This allows users to run validate in a build tree, where the build tree was setup using lndir with a relative path to the source directory. - - - - - 31fb7694 by Ian Lynagh at 2013-05-19T20:47:49+01:00 Use "cp -L" when making $(INPLACE_LIB)/latex too - - - - - e9952233 by Simon Hengel at 2013-06-01T18:06:50+02:00 Add -itest to .ghci - - - - - b06873b3 by Mateusz Kowalczyk at 2013-06-01T18:06:50+02:00 Workaround for a failing build with --enable-tests. - - - - - e7858d16 by Simon Hengel at 2013-06-01T19:29:28+02:00 Fix broken test - - - - - 0690acb1 by Richard Eisenberg at 2013-06-21T14:08:25+01:00 Updates to reflect changes in HsDecls to support closed type families. - - - - - 7fd347ec by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 53ed81b6 by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 931c4f4f by Richard Eisenberg at 2013-07-24T13:15:59+01:00 Remove (error "synifyKind") to use WithinType, to allow haddock to process base. - - - - - 55a9c804 by Richard Eisenberg at 2013-08-02T15:54:55+01:00 Changes to reflect changes in GHC's type HsTyVarBndr - - - - - b6e9226c by Mathieu Boespflug at 2013-08-04T10:39:43-07:00 Output Copright and License keys in Xhtml backend. This information is as relevant in the documentation as it is in the source files themselves. Signed-off-by: David Waern <david.waern at gmail.com> - - - - - 4c66028a by David Waern at 2013-08-04T15:27:36-07:00 Bump interface file version. - - - - - 67340163 by David Waern at 2013-08-09T16:12:51-07:00 Update tests. - - - - - 2087569b by Mateusz Kowalczyk at 2013-08-25T09:24:13+02:00 Add spec tests. This adds tests for all elements we can create during regular parsing. This also adds tests for text with unicode in it. - - - - - 97f36a11 by Mateusz Kowalczyk at 2013-08-27T06:59:12+01:00 Fix ticket haskell/haddock#247. I do the same thing that the XHTML backend does: give these no special treatment and just act as if they are regular functions. - - - - - 60681b4f by Mateusz Kowalczyk at 2013-08-27T21:22:48+02:00 LaTeX tests setup - - - - - fa4c27b2 by Mateusz Kowalczyk at 2013-09-02T23:21:43+01:00 Fixes haskell/haddock#253 - - - - - 1a202490 by Mateusz Kowalczyk at 2013-09-03T01:12:50+01:00 Use Hspec instead of nanospec This is motivated by the fact that Haddock tests are not ran by the GHC's ‘validate’ script so we're pretty liberal on dependencies in that area. Full Hspec gives us some nice features such as Quickcheck integration. - - - - - 8cde3b20 by David Luposchainsky at 2013-09-08T07:27:28-05:00 Fix AMP warnings Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - d10661f2 by Herbert Valerio Riedel at 2013-09-11T15:15:01+02:00 Update Git repo URL in `.cabal` file - - - - - 16a44eb5 by Richard Eisenberg at 2013-09-17T09:34:26-04:00 Revision to reflect new role annotation syntax in GHC. - - - - - 4b9833b9 by Herbert Valerio Riedel at 2013-09-18T10:15:28+02:00 Add missing `traverse` method for `GenLocated` As `Traversable` needs at least one of `traverse` or `sequenceA` to be overridden. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - b71fed5d by Simon Hengel at 2013-09-18T22:43:34+02:00 Add test helper - - - - - 4fc1ea86 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#231 - - - - - 435872f6 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#256 We inject -dynamic-too into flags before we run all our actions in the GHC monad. - - - - - b8b24abb by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Add new field to DynFlags - - - - - 49558795 by Simon Hengel at 2013-09-18T22:43:35+02:00 Fallback to ./resources when Cabal data is not found (so that themes are found during development) - - - - - bf79d05c by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Fixes haskell/haddock#5 - - - - - e1baebc2 by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Print missing documentation. Fixes haskell/haddock#258. - - - - - 02ea74de by Austin Seipp at 2013-10-09T10:52:22-05:00 Don't consider StaticFlags when parsing arguments. Instead, discard any static flags before parsing the command line using GHC's DynFlags parser. See http://ghc.haskell.org/trac/ghc/ticket/8276 Based off a patch from Simon Hengel. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 704fd5bb by Simon Hengel at 2013-11-09T00:15:13+01:00 Update HTML tests - - - - - f9fed49e by Simon Hengel at 2013-11-10T18:43:58+01:00 Bump version - - - - - 97ae1999 by Simon Peyton Jones at 2013-11-25T17:25:14+00:00 Track changes in HsSpliceTy data constructor - - - - - 59ad8268 by Simon Peyton Jones at 2014-01-10T18:17:43+00:00 Adapt to small change in Pretty's exports - - - - - 8b12e6aa by Simon Hengel at 2014-01-12T14:48:35-06:00 Some code simplification by using traverse - - - - - fc5ea9a2 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix warnings in test helper - - - - - 6dbb3ba5 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Add ByteString version of Attoparsec - - - - - 968d7774 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 One pass parser and tests. We remove the HTML test as it is no longer necessary. We cover the test case in spec tests and other HTML tests but keeping this around fails: this is because the new parser has different semantics there. In fact, I suspect the original behaviour was a bug that wasn't caught/fixed but simply included as-is during the testing. - - - - - 37a07c9c by Simon Hengel at 2014-01-12T14:48:35-06:00 Rename Haddock.ParseSpec to Haddock.ParserSpec - - - - - f0f68fe9 by Simon Hengel at 2014-01-12T14:48:35-06:00 Don't append newline to parseString input We also check that we have parsed everything with endOfInput. - - - - - 95d60093 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix totality, unicode, examples, paragraph parsing Also simplify specs and parsers while we're at it. Some parsers were made more generic. This commit is a part of GHC pre-merge squash, email fuuzetsu at fuuzetsu.co.uk if you need the full commit history. - - - - - 7d99108c by Simon Hengel at 2014-01-12T14:48:35-06:00 Update acceptance tests - - - - - d1b59640 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Support for bold. Conflicts: src/Haddock/Backends/Hoogle.hs src/Haddock/Interface/Rename.hs src/Haddock/Parser.hs - - - - - 4b412b39 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Allow for headings inside function documentation. LaTeX will treat the h3-h6 headings the same as we'd have to hack the style file heavily otherwise and it would make the headings tiny anyway. Hoogle upstream said they will put in the functionality on their end. Conflicts: src/Haddock/Interface/Rename.hs src/Haddock/Types.hs test/Haddock/ParserSpec.hs - - - - - fdcca428 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Per-module extension flags and language listing. Any extensions that are not enabled by a used language (Haskell2010 &c) will be shown. Furthermore, any implicitly enabled are also going to be shown. While we could eliminate this either by using the GHC API or a dirty hack, I opted not to: if a user doesn't want the implied flags to show, they are recommended to use enable extensions more carefully or individually. Perhaps this will encourage users to not enable the most powerful flags needlessly. Enabled with show-extensions. Conflicts: src/Haddock/InterfaceFile.hs - - - - - 368942a2 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Bump interface version There were some breaking changes over the last few patches so we bump the interface version. This causes a big problem with testing: 1. To generate cross package docs, we first need to generate docs for the package used. 2. To generate package docs with new interface version, we need to use Haddock which has the version bumped. 3. To get Haddock with the version bump, we first need to test cross package docs 4. GOTO 1 So the problem is the chicken and the egg problem. It seems that the only solution would be to generate some interface files on the fly but it is non-trivial. To run this test, you'll have to: * build Haddock without the test (make sure everything else passes) * rebuild the packages used in the test with your shiny new binary making sure they are visible to Haddock * remove the ‘_hidden’ suffix and re-run the tests Note: because the packages currently used for this test are those provided by GHC, it's probably non-trivial to just re-build them. Preferably something less tedious to rebuild should be used and something that is not subject to change. - - - - - 124ae7a9 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow for nesting of paragraphs under lists. The nesting rules are similar to Markdown's with the exception that we can not simply indent the first line of a hard wrapped indented paragraph and have it treated as if it was fully indented. The reason is differences in markup as some of our constructs care about whitespace while others just swallow everything up so it's just a lot easier to not bother with it rather than making arbitrary rules. Note that we now drop trailing for string entities inside of lists. They weren't needed and it makes the output look uniform whether we use a single or double newline between list elements. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - c7913535 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow escaping in URLs and pictures. Some tests were moved under parseString as they weren't about paragraph level markup. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - 32326680 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update documentation. - - - - - fbef6406 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update maintainer - - - - - b40e82f4 by Mateusz Kowalczyk at 2014-01-13T02:39:25-06:00 Fixes haskell/haddock#271 Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - f4eafbf8 by Gergő Érdi at 2014-01-19T15:35:16-06:00 Support for -XPatternSynonyms Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - a8939591 by Austin Seipp at 2014-01-29T08:09:04-06:00 Update CPP check for __GLASGOW_HASKELL__ Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 30d7e9d5 by Gergő Érdi at 2014-01-31T00:15:01+08:00 <+>: Don't insert a space when concatenating empty nodes - - - - - a25ccd4d by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Fix @ code blocks In cases where we had some horizontal space before the closing ‘@’, the parser would not accept the block as a code block and we'd get ugly output. - - - - - 0f67305a by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Update tests This updates tests due to Haddock Trac haskell/haddock#271 fix and due to removal of TypeHoles as an extension from GHC. - - - - - 157322a7 by Gergő Érdi at 2014-01-31T01:03:17+08:00 Handle infix vs prefix names correctly everywhere, by explicitly specifying the context The basic idea is that "a" and "+" are either pretty-printed as "a" and "(+)" or "`a`" and "+" - - - - - aa6d9685 by Mateusz Kowalczyk at 2014-01-30T17:21:50+00:00 Correct whitespace in ‘hidden’ test for <+> change - - - - - 121872f0 by Mateusz Kowalczyk at 2014-02-09T17:59:12+00:00 Document module header. Fixes Haddock Trac haskell/haddock#270. - - - - - e3253746 by Mateusz Kowalczyk at 2014-02-10T21:37:48+00:00 Insert a space between module link and description Fixes Haddock Trac haskell/haddock#277. - - - - - 771d2384 by Mateusz Kowalczyk at 2014-02-10T23:27:21+00:00 Ensure a space between type signature and ‘Source’ This is briefly related to Haddock Trac haskell/haddock#249 and employs effectively the suggested fix _but_ it doesn't actually fix the reported issue. This commit simply makes copying the full line a bit less of a pain. - - - - - 8cda9eff by nand at 2014-02-11T15:48:30+00:00 Add support for type/data families This adds support for type/data families with their respective instances, as well as closed type families and associated type/data families. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 3f22c510 by nand at 2014-02-11T15:53:50+00:00 Improve display of poly-kinded type operators This now displays them as (==) k a b c ... to mirror GHC's behavior, instead of the old (k == a) b c ... which was just wrong. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - effb2d6b by nand at 2014-02-11T15:56:50+00:00 Add test case for PatternSynonyms This just tests various stuff including poly-kinded patterns and operator patterns to make sure the rendering isn't broken. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - b38faf0d by Niklas Haas at 2014-02-13T21:53:32+00:00 Get rid of re-implementation of sortBy I have no idea what this was doing lying around here, and due to the usage of tuples it's actually slower, too. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - ac1e0413 by Mateusz Kowalczyk at 2014-02-13T23:57:16+00:00 Only warn about missing docs when docs are missing This fixes the ‘Missing documentation for…’ message for modules with 100% coverage. - - - - - cae2e36a by Niklas Haas at 2014-02-15T21:56:18+00:00 Add test case for inter-module type/data family instances These should show up in every place where the class is visible, and indeed they do right now. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 8bea5c3a by Mateusz Kowalczyk at 2014-02-19T05:11:34+00:00 Use a bespoke data type to indicate fixity This deals with what I imagine was an ancient TODO and makes it much clearer what the argument actually does rather than having the user chase down the comment. - - - - - 5b52d57c by Niklas Haas at 2014-02-22T21:31:03+01:00 Strip a single leading space from bird tracks (#201) This makes bird tracks in the form > foo > bar > bat parse as if they had been written as >foo >bar >bat ie. without the leading whitespace in front of every line. Ideally we also want to look into how leading whitespace affects code blocks written using the @ @ syntax, which are currently unaffected by this patch. - - - - - 5a1315a5 by Simon Hengel at 2014-02-22T21:55:35+01:00 Turn a source code comment into specs - - - - - 784cfe58 by Mateusz Kowalczyk at 2014-02-23T05:02:22+00:00 Update test case for lifted GADT type rendering The parsing of these seems to have been fixed by GHC folk and it now renders differently. IMHO it now renders in a better way so I'm updating the test to reflect this. - - - - - c3c88c2f by Mateusz Kowalczyk at 2014-02-23T06:37:14+00:00 Don't shadow ‘strip’. -Wall complains - - - - - 293031d8 by Niklas Haas at 2014-02-23T15:21:52+01:00 Make ImplicitParams render correctly (#260) This introduces a new precedence level for single contexts (because implicit param contexts always need parens around them, but other types of contexts don't necessarily, even when alone) - - - - - 4200842d by Niklas Haas at 2014-02-23T15:37:13+01:00 Lower precedence of equality constraints This drops them to the new precedence pREC_CTX, which makes single eqaulity constraints show up as (a ~ b) => ty, in line with GHC's rendering. Additional tests added to make sure other type operators render as intended. Current behavior matches GHC - - - - - b59e3227 by Niklas Haas at 2014-02-23T16:11:22+01:00 Add RankNTypes test case to ImplicitParams.hs This test actually tests what haskell/haddock#260 originally reported - I omitted the RankNTypes scenario from the original fix because I realized it's not relevant to the underlying issue and indeed, this renders as intended now. Still good to have more tests. - - - - - c373dbf7 by Mateusz Kowalczyk at 2014-02-24T06:09:54+00:00 Fix rendering of Contents when links are present Fixes Haddock Trac haskell/haddock#267. - - - - - 9ecb0e56 by Mateusz Kowalczyk at 2014-02-24T06:26:50+00:00 Fix wording in the docs - - - - - 4f4dcd8e by Mateusz Kowalczyk at 2014-02-27T03:00:33+00:00 Change rendering of duplicate record field docs See Haddock Trac haskell/haddock#195. We now change this behaviour to only rendering the documentation attached to the first instance of a duplicate field. Perhaps we could improve this by rendering the first instance that has documentation attached to it but for now, we'll stick with this. - - - - - ad8aa609 by Niklas Haas at 2014-03-08T09:43:26+01:00 Render fixity information Affects functions, type synonyms, type families, class names, data type names, constructors, data families, associated TFs/DFs, type synonyms, pattern synonyms and everything else I could think of. - - - - - 6a39c917 by Niklas Haas at 2014-03-09T07:43:39+01:00 Reorder topDeclElem to move the source/wiki links to the top They appear in the same position due to the float: right attribute but now they're always at the top of the box instead of at the bottom. - - - - - 2d34b3b4 by Niklas Haas at 2014-03-09T07:53:46+01:00 Use optLast instead of listToMaybe for sourceUrls/wikiUrls This lets you override them using eg. cabal haddock --haddock-options, which can come in handy if you want to use a different layout or URL for your source code links than cabal-install generates. - - - - - 0eff4624 by Niklas Haas at 2014-03-09T07:53:46+01:00 Differentiate between TH splices (line-links) and regular names This adds a new type of source code link, to a specific line rather than a specific declaration/name - this is used to link to the location of a TH splice that defines a certain name. Rather hefty changes throughout and still one unresolved issue (the line URLs aren't parsed from the third form of --read-interface which means they're currently restricted to same-interface links). Not sure if this issue is really worth all the hassle, especially since we could just use line links in general. This commit also contains some cleanup/clarification of the types in Haddock.Backends.Xhtml.Decl and shortens some overlong lines in the process. Notably, the Bool parameter was replaced by a Unicode type synonym to help clarify its presence in type signatures. - - - - - 66d6f77b by Niklas Haas at 2014-03-09T20:02:43+01:00 Group similar fixities together Identical fixities declared for the same line should now render using syntax like: infix 4 <, >=, >, <= - - - - - 6587f9f5 by Mateusz Kowalczyk at 2014-03-10T04:24:18+00:00 Update changelog - - - - - 7387ddad by Niklas Haas at 2014-03-11T10:26:04+01:00 Include fixity information in the Interface file This resolves fixity information not appearing across package borders. The binary file version has been increased accordingly. - - - - - ab46ef44 by Niklas Haas at 2014-03-11T10:26:04+01:00 Update changelog - - - - - 565cab6f by Niklas Haas at 2014-03-11T10:26:04+01:00 Update appearance of fixity annotations This moves them in-line with their corresponding lines, similar to a presentation envision by @hvr and described in #ghc. Redundant operator names are also omitted when no ambiguity is present. - - - - - 5d7afd67 by Niklas Haas at 2014-03-11T10:26:05+01:00 Filter family instances of hidden types Currently, this check does not extend to hidden right hand sides, although it probably should hide them in that case. - - - - - ec291b0c by Niklas Haas at 2014-03-11T10:26:05+01:00 Add documentation for --source-entity-line - - - - - 0922e581 by Niklas Haas at 2014-03-11T10:37:32+01:00 Revert "Reorder topDeclElem to move the source/wiki links to the top" This reverts commit 843c42c4179526a2ad3526e4c7d38cbf4d50001d. This change is no longer needed with the new rendering style, and it messes with copy/pasting lines. - - - - - 30618e8b by Mateusz Kowalczyk at 2014-03-11T09:41:07+00:00 Bump version to 2.15.0 - - - - - adf3f1bb by Mateusz Kowalczyk at 2014-03-11T09:41:09+00:00 Fix up some whitespace - - - - - 8905f57d by Niklas Haas at 2014-03-13T19:18:06+00:00 Hide RHS of TFs with non-exported right hand sides Not sure what to do about data families yet, since technically it would not make a lot of sense to display constructors that cannot be used by the user. - - - - - 5c44d5c2 by Niklas Haas at 2014-03-13T19:18:08+00:00 Add UnicodeSyntax alternatives for * and -> I could not find a cleaner way to do this other than checking for string equality with the given built-in types. But seeing as it's actually equivalent to string rewriting in GHC's implementation of UnicodeSyntax, it's probably fitting. - - - - - b04a63e6 by Niklas Haas at 2014-03-13T19:18:10+00:00 Display minimal complete definitions for type classes This corresponds to the new {-# MINIMAL #-} pragma present in GHC 7.8+. I also cleaned up some of the places in which ExportDecl is used to make adding fields easier in the future. Lots of test cases have been updated since they now render with minimality information. - - - - - a4a20b16 by Niklas Haas at 2014-03-13T19:18:12+00:00 Strip links from recently added html tests These were accidentally left there when the tests were originally added - - - - - d624f315 by Mateusz Kowalczyk at 2014-03-13T19:19:31+00:00 Update changelog - - - - - d27a21ac by Mateusz Kowalczyk at 2014-03-13T21:19:07+00:00 Always read in prologue files as UTF8 (#286). - - - - - 54b2fd78 by Mateusz Kowalczyk at 2014-03-13T21:28:09+00:00 Style only - - - - - fa4fe650 by Simon Hengel at 2014-03-15T09:04:18+01:00 Add Fuuzetsu maintainers field in cabal file - - - - - f83484b7 by Niklas Haas at 2014-03-15T18:20:24+00:00 Hide minimal definition for only-method classes Previously this was not covered by the All xs check since here it is not actually an All, rather a single Var n. This also adds the previously missing html-test/src/Minimal.hs. - - - - - 0099d276 by Niklas Haas at 2014-03-15T18:20:26+00:00 Fix issue haskell/haddock#281 This is a regression from the data family instances change. Data instances are now distinguished from regular lists by usage of the new class "inst", and the style has been updated to only apply to those. I've also updated the appropriate test case to test this a bit better, including GADT instances with GADT-style records. - - - - - 1f9687bd by Mateusz Kowalczyk at 2014-03-21T17:48:37+00:00 Please cabal sdist - - - - - 75542693 by Mateusz Kowalczyk at 2014-03-22T16:36:16+00:00 Drop needless --split-objs which slows us down. Involves tiny cleanup of all the dynflag bindings. Fixes haskell/haddock#292. - - - - - 31214dc3 by Herbert Valerio Riedel at 2014-03-23T18:01:01+01:00 Fix a few typos Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 0b73e638 by Mateusz Kowalczyk at 2014-03-31T05:34:36+01:00 Print kind signatures on GADTs - - - - - 2bab42f3 by Mateusz Kowalczyk at 2014-03-31T16:53:25+01:00 Add default for new PlatformConstraints field - - - - - 42647c5f by Mateusz Kowalczyk at 2014-03-31T18:29:04+01:00 Drop leading whitespace in @-style blocks. Fixes haskell/haddock#201. - - - - - 98208294 by Niklas Haas at 2014-03-31T20:09:58+02:00 Crash when exporting record selectors of data family instances This fixes bug haskell/haddock#294. This also fixes a related but never-before-mentioned bug about the display of GADT record selectors with non-polymorphic type signatures. Note: Associated data type constructors fail to show up if nothing is exported that they could be attached to. Exporting any of the data types in the instance head, or the class + data family itself, causes them to show up, but in the absence of either of these, exporting just the associated data type with the constructor itself will result in it being hidden. The only scenario I can come up that would involve this kind of situation involved OverlappingInstances, and even then it can be mitigated by just exporting the class itself, so I'm not going to solve it since the logic would most likely be very complicated. - - - - - 3832d171 by Mateusz Kowalczyk at 2014-04-01T19:07:33+01:00 Make CHANGES consistent with what's now in 2.14.2 - - - - - c386ae89 by Mateusz Kowalczyk at 2014-04-01T19:18:36+01:00 Actually bundle extra spec tests in sdist - - - - - bd57a6d3 by Mateusz Kowalczyk at 2014-04-03T21:13:48+01:00 Update test cases for GHC bug haskell/haddock#8945, Haddock haskell/haddock#188 The order of signature groups has been corrected upstream. Here we add a test case and update some existing test-cases to reflect this change. We remove grouped signature in test cases that we can (Minimal, BugDeprecated &c) so that the test is as self-contained as possible. - - - - - 708b88b1 by Mateusz Kowalczyk at 2014-04-03T21:16:07+01:00 Enforce strict GHC version in cabal file This stops people with 7.6.3 trying to install 2.15.x which clearly won't work. Unfortunately we shipped 2.14.x without realising this. - - - - - 60334f7c by Mateusz Kowalczyk at 2014-04-03T21:19:24+01:00 Initialise some new PlatformConstants fields - - - - - ea77f668 by Mateusz Kowalczyk at 2014-04-11T16:52:23+01:00 We don't actually want unicode here - - - - - 0b651cae by Mateusz Kowalczyk at 2014-04-11T18:13:30+01:00 Parse identifiers with ^ and ⋆ in them. Fixes haskell/haddock#298. - - - - - e8ad0f5f by Mateusz Kowalczyk at 2014-04-11T18:47:41+01:00 Ignore version string during HTML tests. - - - - - de489089 by Mateusz Kowalczyk at 2014-04-11T18:59:30+01:00 Update CHANGES to follow 2.14.3 - - - - - beb464a9 by Gergő Érdi at 2014-04-13T16:31:10+08:00 remove Origin flag from LHsBindsLR - - - - - cb16f07c by Herbert Valerio Riedel at 2014-04-21T17:16:50+02:00 Replace local `die` by new `System.Exit.die` Starting with GHC 7.10, System.Exit exports the new `die` which is essentially the same as Haddock.Util.die, so this commit changes Haddock.Util.die to be a simple re-export of System.Exit.die. See also https://ghc.haskell.org/trac/ghc/ticket/9016 for more details. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 9b9b23c7 by Mateusz Kowalczyk at 2014-05-03T15:40:11+02:00 Disambiguate ‘die’ in test runners. - - - - - 5d28a2b8 by Mateusz Kowalczyk at 2014-05-05T09:19:49+02:00 Prepare modules for parser split. We have to generalise the Doc (now DocH) slightly to remove the dependency on GHC-supplied type. - - - - - d3967ff3 by Mateusz Kowalczyk at 2014-05-05T11:00:41+02:00 Move parser + parser tests out to own package. We move some types out that are necessary as well and then re-export and specialise them in the core Haddock. Reason for moving out spec tests is that if we're working on the parser, we can simply work on that and we can ignore the rest of Haddock. The downside is that it's a little inconvenient if at the end of the day we want to see that everything passes. - - - - - 522a448d by Mateusz Kowalczyk at 2014-05-05T11:14:47+02:00 Move out Show and Eq instances to Types They are much more useful to the users here. - - - - - 11a6f0f2 by Mateusz Kowalczyk at 2014-05-06T13:50:31+02:00 Remove no longer necessary parser error handling. We can now drop some Maybe tests and even lets us strip an error handling monad away in a few places. - - - - - 6992c924 by Mateusz Kowalczyk at 2014-05-14T02:23:55+02:00 Please the GHC build-system. As I can not figure out how to do this properly, if we're in GHC tree, we treat the library as being the same package. If we're not in the tree, we require that the library be installed separately. - - - - - 7a8ad763 by Mateusz Kowalczyk at 2014-05-14T14:50:25+02:00 Update issue tracker URL - - - - - f616c521 by Mateusz Kowalczyk at 2014-05-14T14:53:32+02:00 Update issue tracker URL for haddock-library - - - - - 66580ded by Gergő Érdi at 2014-05-25T14:24:16+08:00 Accomodate change in PatSyn representation - - - - - 0e43b988 by Mateusz Kowalczyk at 2014-05-29T03:15:29+02:00 Revert "Accomodate change in PatSyn representation" This reverts commit 57aa591362d7c8ba21285fccd6a958629a422091. I am reverting this because I pushed it to master when it was meant to stay on a wip-branch. Sorry Gergo and everyone who had trouble due to this. - - - - - e10d7ec8 by Mateusz Kowalczyk at 2014-05-29T03:24:11+02:00 Revert "Revert "Accomodate change in PatSyn representation"" This reverts commit e110e6e70e40eed06c06676fd2e62578da01d295. Apparently as per GHC commit ac2796e6ddbd54c5762c53e2fcf29f20ea162fd5 this was actually intended. Embarrasing for me. - - - - - 5861aca9 by Mateusz Kowalczyk at 2014-06-05T19:49:27+02:00 Clear up highlighting of identifiers with ‘'’s. - - - - - d7cc420f by Simon Peyton Jones at 2014-06-06T12:41:09+01:00 Follow change in patSynSig - - - - - 938b4fd8 by Mateusz Kowalczyk at 2014-06-12T07:24:29+02:00 Slightly update the readme. Style-sheets are no longer a recent thing, dead links, old maintainers, different formats. - - - - - c7799dea by Mateusz Kowalczyk at 2014-06-18T00:05:56+02:00 Update cabal files Update repository urls, use subdir property for haddock-library and use a separate versioning scheme for haddock-library in preparation for release. - - - - - a2750b6a by Simon Hengel at 2014-06-18T11:01:18+08:00 Compatibility with older versions of base and bytestring - - - - - 009b4b03 by Simon Hengel at 2014-06-18T11:14:01+08:00 Enable travis-ci for haddock-library - - - - - 9b5862eb by Simon Hengel at 2014-06-18T11:14:01+08:00 haddock-library: Do not depend on haddock-library in test suite I think you either add src to hs-source-dirs or the library to build-depends. But doing both does not make sense (AFAICT). - - - - - fb1f3279 by Simon Hengel at 2014-06-18T11:49:05+08:00 haddock-library: Use -Wall for specs - - - - - 649340e1 by Mateusz Kowalczyk at 2014-06-18T06:58:54+02:00 Use Travis with multiple GHC versions When using HEAD, we build haddock-library directly from repository as a dependency (and thanks to --enable-tests, the tests get ran anyway). In all other cases, we manually run the tests on haddock-library only and don't test the main project. - - - - - d7eeeec2 by Mateusz Kowalczyk at 2014-06-18T07:49:04+02:00 Comment improvements + few words in cabal file - - - - - 0f8db914 by Simon Hengel at 2014-06-18T13:52:23+08:00 Use doctest to check examples in documentation - - - - - 2888a8dc by Simon Hengel at 2014-06-18T14:16:48+08:00 Remove doctest dependency (so that we can use haddock-library with doctest) - - - - - 626d5e85 by Mateusz Kowalczyk at 2014-06-18T08:41:25+02:00 Travis tweaks - - - - - 41d4f9cc by Mateusz Kowalczyk at 2014-06-18T08:58:43+02:00 Don't actually forget to install specified GHC. - - - - - c6aa512a by John MacFarlane at 2014-06-18T10:43:57-07:00 Removed reliance on LambdaCase (which breaks build with ghc 7.4). - - - - - b9b93b6f by John MacFarlane at 2014-06-18T10:54:56-07:00 Fixed haddock warnings. - - - - - a41b0ab5 by Mateusz Kowalczyk at 2014-06-19T01:20:10+02:00 Update Travis, bump version - - - - - 864bf62a by Mateusz Kowalczyk at 2014-06-25T10:36:54+02:00 Fix anchors. Closes haskell/haddock#308. - - - - - 53df91bb by Mateusz Kowalczyk at 2014-06-25T15:04:49+02:00 Drop DocParagraph from front of headers I can not remember why they were wrapped in paragraphs to begin with and it seems unnecessary now that I test it. Closes haskell/haddock#307. - - - - - 29b5f2fa by Mateusz Kowalczyk at 2014-06-25T15:17:20+02:00 Don't mangle append order for nested lists. The benefit of this is that the ‘top-level’ element of such lists is properly wrapped in <p> tags so any CSS working with these will be applied properly. It also just makes more sense. Pointed out at jgm/pandoc#1346. - - - - - 05cb6e9c by Mateusz Kowalczyk at 2014-06-25T15:19:45+02:00 Bump haddock-library to 1.1.0 for release - - - - - 70feab15 by Iavor Diatchki at 2014-07-01T03:37:07-07:00 Propagate overloading-mode for instance declarations in haddock (#9242) - - - - - d4ca34a7 by Simon Peyton Jones at 2014-07-14T16:23:15+01:00 Adapt to new definition of HsDecls.TyFamEqn This is a knock-on from the refactoring from Trac haskell/haddock#9063. I'll push the corresponding changes to GHC shortly. - - - - - f91e2276 by Edward Z. Yang at 2014-07-21T08:14:19-07:00 Track GHC PackageId to PackageKey renaming. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - b010f9ef by Edward Z. Yang at 2014-07-25T16:28:46-07:00 Track changes for module reexports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - 8b85f9f9 by Mateusz Kowalczyk at 2014-07-28T13:25:43+02:00 Catch mid-line URLs. Fixes haskell/haddock#314. - - - - - 4c613a78 by Edward Z. Yang at 2014-08-05T03:11:00-07:00 Track type signature change of lookupModuleInAllPackages Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - e80b051c by Edward Z. Yang at 2014-08-05T17:34:26+01:00 If GhcProfiled, also build Haddock profiled. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f9cccd29 by Edward Z. Yang at 2014-08-07T14:23:35+01:00 Ignore TAGS files. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 00b3af52 by Mateusz Kowalczyk at 2014-08-08T04:58:19+02:00 Update to attoparsec-0.12.1.1 There seems to be memory and speed improvement. - - - - - 5457dc71 by Mateusz Kowalczyk at 2014-08-08T18:24:02+02:00 Fix forgotten src - - - - - 3520cb04 by Mateusz Kowalczyk at 2014-08-14T20:19:07+01:00 Bump down the version for master to 2.14.4 - - - - - dc98c21b by Mateusz Kowalczyk at 2014-08-14T20:23:27+01:00 Revert "Track type signature change of lookupModuleInAllPackages" This reverts commit d59fec2c9551b5662a3507c0011e32a09a9c118f. - - - - - 3f2038c0 by Mateusz Kowalczyk at 2014-08-14T20:23:31+01:00 Revert "Track changes for module reexports." This reverts commit b99b57c0df072d12b67816b45eca2a03cb1da96d. - - - - - 56d4e49e by Mateusz Kowalczyk at 2014-08-14T20:23:42+01:00 Revert "Track GHC PackageId to PackageKey renaming." This reverts commit 8ac42d3327473939c013551750425cac191ff0fd. - - - - - 726ea3cb by Mateusz Kowalczyk at 2014-08-14T20:23:47+01:00 Revert "Adapt to new definition of HsDecls.TyFamEqn" This reverts commit cb96b4f1ed0462b4a394b9fda6612c3bea9886bd. - - - - - 61a88ff0 by Mateusz Kowalczyk at 2014-08-14T20:23:52+01:00 Revert "Propagate overloading-mode for instance declarations in haddock (#9242)" This reverts commit 8d20ca8d5a9bee73252ff2035ec45f9c03d0820c. - - - - - a32ba674 by Mateusz Kowalczyk at 2014-08-14T20:26:03+01:00 Revert "Disambiguate ‘die’ in test runners." This reverts commit dba02d6df32534aac5d257f2d28596238d248942. - - - - - f335820f by Mateusz Kowalczyk at 2014-08-14T20:26:09+01:00 Revert "Replace local `die` by new `System.Exit.die`" This reverts commit 08aa509ebac58bfb202ea79c7c41291ec280a1c5. - - - - - 107078e4 by Mateusz Kowalczyk at 2014-08-14T20:27:34+01:00 Merge branch 'reverts' This reverts any changes that were made to have Haddock compile with 7.9. When 7.10 release comes, we can simply re-apply all the patches and any patches that occur on ghc-head branch from now on. This allows us to build master with 7.8.3 - - - - - b44b3871 by Mateusz Kowalczyk at 2014-08-15T02:47:40+01:00 Fix haskell/haddock#313 by doing some list munging. I get rid of the Monoid instance because we weren't satisfying the laws. Convenience of having <> didn't outweigh the shock-factor of having it behave badly. - - - - - e1a62cde by Mateusz Kowalczyk at 2014-08-15T02:52:56+01:00 Stop testing haskell/haddock#188. Because the change is in GHC 7.9 and we now work against 7.8.3, this test no longer makes sense. We revert it until 7.10 becomes the standard version. If anything, there should be a test for this in GHC itself. - - - - - 54e8286d by Mateusz Kowalczyk at 2014-08-15T05:31:57+01:00 Add haskell/haddock#313 to CHANGES - - - - - 9df7ad5d by Simon Hengel at 2014-08-20T11:25:32+08:00 Fix warning - - - - - ee2574d6 by Simon Hengel at 2014-08-20T12:07:01+08:00 Fix travis builds - - - - - 384cf2e6 by Simon Hengel at 2014-08-20T12:14:31+08:00 Require GHC 7.8.3 - - - - - d4779863 by Simon Hengel at 2014-08-22T12:14:16+08:00 Move Haddock API to a separate package - - - - - 80f3e0e1 by Simon Hengel at 2014-08-22T14:57:38+08:00 Bump version to 2.15.0 and add version constraints - - - - - 309a94ce by Simon Hengel at 2014-08-22T15:18:06+08:00 Add deprecated compatibility module - - - - - 4d1e4e3f by Luite Stegeman at 2014-08-22T20:46:45+02:00 export things to allow customizing how the Ghc session is run - - - - - 47884591 by Luite Stegeman at 2014-08-22T20:46:51+02:00 ghc 7.8.2 compatibility - - - - - 5ea94e2c by Luite Stegeman at 2014-08-22T22:08:58+02:00 install dependencies for haddock-api on travis - - - - - 9fb845b2 by Mateusz Kowalczyk at 2014-08-23T10:09:34+01:00 Move sources under haddock-api/src - - - - - 85817dc4 by Mateusz Kowalczyk at 2014-08-23T10:10:48+01:00 Remove compat stuff - - - - - 151c6169 by Niklas Haas at 2014-08-24T08:14:10+02:00 Fix extra whitespace on signatures and update all test cases This was long overdue, now running ./accept.lhs on a clean test from master will not generate a bunch of changes. - - - - - d320e0d2 by Niklas Haas at 2014-08-24T08:14:35+02:00 Omit unnecessary foralls and fix haskell/haddock#315 This also fixes haskell/haddock#86. - - - - - bdafe108 by Mateusz Kowalczyk at 2014-08-24T15:06:46+01:00 Update CHANGES - - - - - fafa6d6e by Mateusz Kowalczyk at 2014-08-24T15:14:23+01:00 Delete few unused/irrelevant/badly-place files. - - - - - 3634923d by Duncan Coutts at 2014-08-27T13:49:31+01:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. - - - - - 539a7e70 by Herbert Valerio Riedel at 2014-08-31T11:36:32+02:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 9e3a0e5b by Mateusz Kowalczyk at 2014-08-31T12:54:43+01:00 Bump version in doc - - - - - 4a177525 by Mateusz Kowalczyk at 2014-08-31T13:01:23+01:00 Bump haddock-library version - - - - - f99c1384 by Mateusz Kowalczyk at 2014-08-31T13:05:25+01:00 Remove references to deleted files - - - - - 5e51a247 by Mateusz Kowalczyk at 2014-08-31T14:18:44+01:00 Make the doc parser not complain - - - - - 2cedb49a by Mateusz Kowalczyk at 2014-09-03T03:33:15+01:00 CONTRIBUTING file for issues - - - - - 88027143 by Mateusz Kowalczyk at 2014-09-04T00:46:59+01:00 Mention --print-missing-docs - - - - - 42f6754f by Alan Zimmerman at 2014-09-05T18:13:24-05:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e712719e by Austin Seipp at 2014-09-09T01:03:27-05:00 Fix import of 'empty' due to AMP. Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 71c29755 by Herbert Valerio Riedel at 2014-09-09T17:35:20+02:00 Bump `base` constraint for AMP - - - - - 0bf9f3ed by Mateusz Kowalczyk at 2014-09-12T19:18:32+01:00 Delete stale ANNOUNCE - - - - - cac89ee6 by Krzysztof Gogolewski at 2014-09-14T17:17:09+02:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 4d683426 by Edward Z. Yang at 2014-09-18T13:38:11-07:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 80697fd5 by Herbert Valerio Riedel at 2014-09-19T00:07:52+02:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. - - - - - c015eb70 by Herbert Valerio Riedel at 2014-09-19T00:10:36+02:00 Revert "Followup changes to addition of -fwarn-context-quantification" This reverts commit 4023817d7c0e46db012ba2eea28022626841ca9b temporarily as the respective feature hasn't landed in GHC HEAD yet, but this commit blocks later commits from being referenced in GHC HEAD. - - - - - 38ded784 by Edward Z. Yang at 2014-09-18T15:32:15-07:00 Revert "Revert "Followup changes to addition of -fwarn-context-quantification"" This reverts commit db14fd8ab4fab43694139bc203808b814eafb2dc. It's in HEAD now. - - - - - f55d59c9 by Herbert Valerio Riedel at 2014-09-26T19:18:28+02:00 Revert "Fix import of 'empty' due to AMP." This reverts commit 0cc5bc85e9fca92ab712b68a2ba2c0dd9d3d79f4 since it turns out we don't need to re-export `empty` from Control.Monad after all. - - - - - 467050f1 by David Feuer at 2014-10-09T20:07:36-04:00 Fix improper lazy IO use Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. - - - - - cc47b699 by Edward Z. Yang at 2014-10-09T21:38:19-07:00 Fix use-after-close lazy IO bug Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. Signed-off-by: David Feuer <David.Feuer at gmail.com> Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 87babcbe by Austin Seipp at 2014-10-20T20:05:27-05:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - ab259516 by Austin Seipp at 2014-10-20T20:07:01-05:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - b918093c by Mateusz Kowalczyk at 2014-10-29T03:59:39+00:00 Experimental support for collapsable headers Closes haskell/haddock#335 - - - - - 849db129 by Mateusz Kowalczyk at 2014-10-29T10:07:26+01:00 Experimental support for collapsable headers (cherry picked from commit e2ed3b9d8dfab09f1b1861dbc8e74f08e137ebcc) - - - - - a4cc4789 by Herbert Valerio Riedel at 2014-10-31T11:08:26+01:00 Collapse user-defined section by default (re haskell/haddock#335) - - - - - 9da1b33e by Yuras Shumovich at 2014-10-31T16:11:04-05:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - c625aefc by Austin Seipp at 2014-10-31T19:34:10-05:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - c7738e5e by Simon Hengel at 2014-11-02T07:25:30+08:00 Remove -fobject-code from .ghci (this slows down reloads on modifications) - - - - - d4a86e95 by Simon Hengel at 2014-11-03T09:26:11+08:00 Get rid of StandaloneDeriving - - - - - a974e311 by Simon Hengel at 2014-11-03T09:26:11+08:00 Derive more instances - - - - - 8aa0c4d7 by Simon Hengel at 2014-11-03T09:27:08+08:00 Remove unused language extensions - - - - - 3052d46a by Simon Hengel at 2014-11-03T09:30:46+08:00 Minor refactoring - - - - - 4281d3cb by Simon Hengel at 2014-11-03T09:30:46+08:00 parser: Try to parse definition lists right before text paragraphs - - - - - 8ba12bf9 by Simon Hengel at 2014-11-03T09:34:19+08:00 Add support for markdown links (closes haskell/haddock#336) - - - - - a2f8d747 by Simon Hengel at 2014-11-03T09:34:19+08:00 Allow markdown links at the beginning of a paragraph - - - - - 53b11207 by Simon Hengel at 2014-11-03T09:34:20+08:00 Update documentation - - - - - 652267c6 by Simon Hengel at 2014-11-03T09:34:20+08:00 Add support for markdown images - - - - - 9d667502 by Simon Hengel at 2014-11-03T09:34:20+08:00 Allow an optional colon after the closing bracket of definition lists This is to disambiguate them from markdown links and will be require with a future release. - - - - - 8167fc32 by Mateusz Kowalczyk at 2014-11-04T01:16:51+00:00 whitespace only - - - - - 3da62981 by Mateusz Kowalczyk at 2014-11-04T01:17:31+00:00 Fix re-exports of built-in type families Fixes haskell/haddock#310 - - - - - edc76b34 by Mateusz Kowalczyk at 2014-11-04T02:54:28+00:00 Turn some uses of error into recoverable warnings This should at the very least not abort when something weird happens. It does feel like we should have a type that carries these errors until the end however as the user might not see them unless they are printed at the end. - - - - - 0a137400 by Mateusz Kowalczyk at 2014-11-04T04:09:44+00:00 Fix warnings - - - - - d068fc21 by Mateusz Kowalczyk at 2014-11-04T21:04:07+00:00 Fix parsing of identifiers written in infix way - - - - - 1a9f2f3d by Simon Hengel at 2014-11-08T11:32:42+08:00 Minor code simplification - - - - - 6475e9b1 by Simon Hengel at 2014-11-08T17:28:33+08:00 newtype-wrap parser monad - - - - - dc1ea105 by Herbert Valerio Riedel at 2014-11-15T11:55:43+01:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - fbb1aca4 by Simon Hengel at 2014-11-16T08:51:38+08:00 State intention rather than implementation details in Haddock comment - - - - - 97851ab2 by Simon Hengel at 2014-11-16T10:20:19+08:00 (wip) Add support for @since (closes haskell/haddock#26) - - - - - 34bcd18e by Gergő Érdi at 2014-11-20T22:35:38+08:00 Update Haddock to new pattern synonym type signature syntax - - - - - 304b7dc3 by Jan Stolarek at 2014-11-20T17:48:43+01:00 Follow changes from haskell/haddock#9812 - - - - - 920f9b03 by Richard Eisenberg at 2014-11-20T16:52:50-05:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 0bfe4e78 by Alan Zimmerman at 2014-11-21T11:23:09-06:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 356ed45a by Thomas Winant at 2014-11-28T16:11:22-06:00 Support for PartialTypeSignatures - - - - - 5dc8f3b1 by Gergő Érdi at 2014-11-29T15:39:09+08:00 For pattern synonyms, render "pattern" as a keyword - - - - - fe704480 by Mateusz Kowalczyk at 2014-12-09T03:38:32+00:00 List new module in cabal file - - - - - b9ad5a29 by Mateusz Kowalczyk at 2014-12-10T00:58:24+00:00 Allow the parser to spit out meta-info Currently we only use it only for ‘since’ annotations but with these patches it should be fairly simple to add new attributes if we wish to. Closes haskell/haddock#26. It seems to work fine but due to 7.10 rush I don't have the chance to do more exhaustive testing right now. The way the meta is output (emphasis at the end of the whole comment) is fairly arbitrary and subject to bikeshedding. Note that this makes test for Bug310 fail due to interface version bump: it can't find the docs for base with this interface version so it fails. There is not much we can do to help this because it tests for ’built-in’ identifier, not something we can provide ourselves. - - - - - 765af0e3 by Mateusz Kowalczyk at 2014-12-10T01:17:19+00:00 Update doctest parts of comments - - - - - 8670272b by jpmoresmau at 2014-12-10T01:35:31+00:00 header could contain several lines Closes haskell/haddock#348 - - - - - 4f9ae4f3 by Mateusz Kowalczyk at 2014-12-12T06:22:31+00:00 Revert "Merge branch 'reverts'" This reverts commit 5c93cc347773c7634321edd5f808d5b55b46301f, reversing changes made to 5b81a9e53894d2ae591ca0c6c96199632d39eb06. Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - e974ac94 by Duncan Coutts at 2014-12-12T06:26:11+00:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. Conflicts: haddock-api/src/Haddock.hs - - - - - 2f3a2365 by Herbert Valerio Riedel at 2014-12-12T06:26:51+00:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 1dbd6390 by Alan Zimmerman at 2014-12-12T06:32:07+00:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - bb6ff1f4 by Mateusz Kowalczyk at 2014-12-12T06:35:07+00:00 Bump ‘base’ constraint Follows the similar commit made on ghc-head branch - - - - - 466fe4ab by Krzysztof Gogolewski at 2014-12-12T06:37:42+00:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 97e080c9 by Edward Z. Yang at 2014-12-12T06:39:35+00:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: haddock-api/src/Haddock/ModuleTree.hs - - - - - 20b2af56 by Herbert Valerio Riedel at 2014-12-12T06:42:50+00:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. Conflicts: haddock-library/src/Documentation/Haddock/Parser.hs - - - - - b3ad269d by Austin Seipp at 2014-12-12T06:44:14+00:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 072df0dd by Austin Seipp at 2014-12-12T06:45:01+00:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - dbb9294a by Herbert Valerio Riedel at 2014-12-12T06:46:17+00:00 Collapse user-defined section by default (re haskell/haddock#335) Conflicts: haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs - - - - - f23ab545 by Yuras Shumovich at 2014-12-12T06:46:41+00:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - 753a4b67 by Austin Seipp at 2014-12-12T06:46:51+00:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8954e8f5 by Herbert Valerio Riedel at 2014-12-12T06:50:53+00:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - d2b06d61 by Gergő Érdi at 2014-12-12T07:07:30+00:00 Update Haddock to new pattern synonym type signature syntax Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 1ff02426 by Jan Stolarek at 2014-12-12T07:13:24+00:00 Follow changes from haskell/haddock#9812 Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - 06ad7600 by Richard Eisenberg at 2014-12-12T07:13:43+00:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 8fd2aa8b by Alan Zimmerman at 2014-12-12T07:22:25+00:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Backends/LaTeX.hs haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 95c3db98 by Thomas Winant at 2014-12-12T07:35:49+00:00 Support for PartialTypeSignatures Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs haddock-api/src/Haddock/Interface/Create.hs - - - - - 45494428 by Gergő Érdi at 2014-12-12T07:36:18+00:00 For pattern synonyms, render "pattern" as a keyword - - - - - a237e3eb by Mateusz Kowalczyk at 2014-12-12T12:27:13+00:00 Various fixups and bumps for next release - - - - - 22918bcd by Herbert Valerio Riedel at 2014-12-14T10:11:47+01:00 Remove redundant wild-card pattern match (this would otherwise cause a build-failure with `-Werror`) - - - - - 1d6ce947 by Herbert Valerio Riedel at 2014-12-14T10:17:06+01:00 Treat GHC 7.10 the same as GHC 7.9 ...since the current GHC 7.9 is going to become GHC 7.10 real-soon-now anyway - - - - - f434ea89 by Herbert Valerio Riedel at 2014-12-14T18:26:50+01:00 Fixup ghc.mk (follow-up to 1739375eb23342) This makes the GHC build-system aware of the data-files to be copied into the bindist (as haddock.cabal doesn't list those anymore) - - - - - 6fb839eb by Mateusz Kowalczyk at 2014-12-17T09:28:59+00:00 Only keep one Version instead of blindly appending - - - - - 40645489 by Mateusz Kowalczyk at 2014-12-18T07:09:44+00:00 Fix dependency version - - - - - 8b3b927b by Mateusz Kowalczyk at 2014-12-18T07:14:23+00:00 Print missing docs by default Adds --no-print-missing-docs - - - - - 59666694 by Mateusz Kowalczyk at 2014-12-18T07:21:37+00:00 update changelog - - - - - aa6d168e by Mateusz Kowalczyk at 2014-12-18T07:30:58+00:00 Update docs for @since - - - - - 2d7043ee by Luite Stegeman at 2014-12-19T18:29:35-06:00 hide projectVersion from DynFlags since it clashes with Haddock.Version.projectVersion - - - - - aaa70fc0 by Luite Stegeman at 2014-12-22T15:58:43+01:00 Add missing import for standalone haddock-api package - - - - - 9ce01269 by Herbert Valerio Riedel at 2014-12-22T17:48:45+01:00 Reset ghc-head with master's tree (this is an overwriting git merge of master into ghc-head) - - - - - fcd6fec1 by Herbert Valerio Riedel at 2014-12-22T17:51:52+01:00 Bump versions for ghc-7.11 - - - - - 525ec900 by Mateusz Kowalczyk at 2014-12-23T13:36:24+00:00 travis-ci: test with HEAD - - - - - cbf494b5 by Simon Peyton Jones at 2014-12-23T15:22:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 50e01c99 by Mateusz Kowalczyk at 2014-12-29T15:28:47+00:00 Make travis use 7.10.x - - - - - 475e60b0 by Njagi Mwaniki at 2014-12-29T15:30:44+00:00 Turn the README into GitHub Markdown format. Closes haskell/haddock#354 - - - - - 8cacf48e by Luite Stegeman at 2015-01-05T16:25:37+01:00 bump haddock-api ghc dependency to allow release candidate and first release - - - - - 6ed6cf1f by Simon Peyton Jones at 2015-01-06T16:37:47+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 8b484f33 by Simon Peyton Jones at 2015-01-08T15:50:22+00:00 Track naming change in DataCon - - - - - 23c5c0b5 by Alan Zimmerman at 2015-01-16T10:15:11-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e7a5532c by JP Moresmau at 2015-01-22T17:19:03+00:00 Ignore warnings, install Cabal 1.22 - - - - - 86942c84 by jpmoresmau at 2015-01-22T17:19:04+00:00 solve dataDir ambiguity - - - - - 5ceb743e by jpmoresmau at 2015-01-22T19:17:32+00:00 support GHC 7.10: no Safe-Inferred, Foldable instance - - - - - 6a3b3fb5 by Mateusz Kowalczyk at 2015-01-22T19:32:10+00:00 Update test files Test: a correct behaviour for fields comma-separating values. I'm surprised we had no bug open for this. Maybe it affects how haskell/haddock#301 renders now but I doubt. Operators: Seems GHC is giving us a new order for operators, something must have changed on their side again. cc @haasn , this makes the fixity to the side not match the order on the LHS which is a bit unpleasant. Maybe the fixity can be made to match the GHC order? Bug335: We expand examples by default now. Bug310: Now inferred safe. - - - - - 708f8b2f by jpmoresmau at 2015-01-22T19:36:59+00:00 Links to source location of class instance definitions - - - - - 5cf8a6da by Vincent Berthoux at 2015-01-22T19:59:58+00:00 Filter '\r' from comments due to Windows problems. On Windows this was causing newline to be rendered twice in code blocks. Closes haskell/haddock#359, fixes haskell/haddock#356. - - - - - 1749e6f0 by Mateusz Kowalczyk at 2015-01-22T20:31:27+00:00 Changelog only - - - - - c8145f90 by Mateusz Kowalczyk at 2015-01-22T23:34:05+00:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. - - - - - 14248254 by Mateusz Kowalczyk at 2015-01-22T23:43:18+00:00 Sort out some module import warnings - - - - - d8a38989 by Simon Peyton Jones at 2015-01-23T07:10:16-06:00 Track naming change in DataCon (cherry picked from commit 04cf63d0195837ed52075ed7d2676e71831e8a0b) - - - - - d3ac6ae4 by Alan Zimmerman at 2015-01-23T07:17:19-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit d61bbc75890e4eb0ad508b9c2a27b91f691213e6) - - - - - 4c1ffeb0 by Simon Peyton Jones at 2015-02-10T12:10:33+00:00 Track changes in HsSyn for quasi-quotes - - - - - 775d20f7 by Mateusz Kowalczyk at 2015-03-15T08:11:48+01:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. (cherry picked from commit 8e06728afb0784128ab2df0be7a5d7a191d30ff4) - - - - - f9245e72 by Phil Ruffwind at 2015-03-16T04:32:01-04:00 Prevent Synopsis from using up too much horizontal space When long type signatures occur in the Synopsis, the element is stretched beyond the width of the window. Scrollbars don't appear, so it's impossible to read anything when this happens. - - - - - cd8fa415 by Mateusz Kowalczyk at 2015-03-17T21:59:39+00:00 Update changelog Closes haskell/haddock#151 due to 71170fc77962f10d7d001e3b8bc8b92bfeda99bc - - - - - b5248b47 by Ben Gamari at 2015-03-25T17:12:17+00:00 Make the error encountered when a package can't be found more user-friendly Closes haskell/haddock#369 - - - - - b756b772 by Mateusz Kowalczyk at 2015-03-26T16:31:40+00:00 Remove now redundant imports - - - - - 5ea5e8dd by Mateusz Kowalczyk at 2015-03-26T16:45:52+00:00 Update test to account for \r filtering - - - - - 6539bfb3 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Test for anchor defaulting I delete the old tests because it turns out that: * test runner would never put them in scope of each other even with imports so just one would suffice * test runner actually needed some hacking to keep links so in the end we would end up with no anchors making them useless - - - - - 1a01d950 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Clearly default to variables in out of scope case - - - - - 7943abe8 by Mateusz Kowalczyk at 2015-03-27T01:14:11+00:00 Fix Hoogle display of constructors Fixes haskell/haddock#361 - - - - - 6d6e587e by Mateusz Kowalczyk at 2015-03-27T01:45:18+00:00 Fully qualify names in Hoogle instances output Closes haskell/haddock#263 - - - - - 52dac365 by Mateusz Kowalczyk at 2015-03-27T01:55:01+00:00 Update changelog - - - - - ca5af9a8 by Mateusz Kowalczyk at 2015-03-27T02:43:55+00:00 Output method documentation in Hoogle backend One thing of note is that we no longer preserve grouping of methods and print each method on its own line. We could preserve it if no documentation is present for any methods in the group if someone asks for it though. Fixes haskell/haddock#259 - - - - - a33f0c10 by Mateusz Kowalczyk at 2015-03-27T03:04:21+00:00 Don't print instance safety information in Hoogle Fixes haskell/haddock#168 - - - - - df6c935a by Mateusz Kowalczyk at 2015-03-28T00:11:47+00:00 Post-release version bumps and changelog - - - - - dde8f7c0 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Loosen bounds on haddock-* - - - - - de93bf89 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Expand response files in arguments Closes haskell/haddock#285 - - - - - 1f0b0856 by Zejun Wu at 2015-04-26T16:35:35-07:00 Do not insert anchor for section headings in contents box - - - - - 860439d7 by Simon Peyton Jones at 2015-05-01T09:36:47+01:00 Track change in API of TyCon - - - - - a32f3e5f by Adam Gundry at 2015-05-04T15:32:59+01:00 Track API changes to support empty closed type familes - - - - - 77e98bee by Ben Gamari at 2015-05-06T20:17:08+01:00 Ignore doc/haddock.{ps,pdf} - - - - - 663d0204 by Murray Campbell at 2015-05-11T04:47:37-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8bb0dcf5 by Murray Campbell at 2015-05-11T06:35:06-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit 2380f07c430c525b205ce2eae6dab23c8388d899) - - - - - bad900ea by Adam Bergmark at 2015-05-11T15:29:39+01:00 haddock-library: require GHC >= 7.4 `Data.Monoid.<>` was added in base-4.5/GHC-7.4 Closes haskell/haddock#394 Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - daceff85 by Simon Peyton Jones at 2015-05-13T12:04:21+01:00 Track the new location of setRdrNameSpace - - - - - 1937d1c4 by Alan Zimmerman at 2015-05-25T21:27:15+02:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - ee0fb6c2 by Łukasz Hanuszczak at 2015-05-27T11:51:31+02:00 Create simple method for indentation parsing. - - - - - 7d6fcad5 by Łukasz Hanuszczak at 2015-05-27T21:36:13+02:00 Make nested lists count indentation according to first item. - - - - - d6819398 by Łukasz Hanuszczak at 2015-05-27T22:46:13+02:00 Add simple test case for arbitrary-depth list nesting. - - - - - 2929c54d by Łukasz Hanuszczak at 2015-06-03T02:11:31+02:00 Add arbitrary-indent spec test for parser. - - - - - 9a0a9bb0 by Mateusz Kowalczyk at 2015-06-03T05:25:29+01:00 Update docs with info on new list nesting rule Fixes haskell/haddock#278 through commits from PR haskell/haddock#401 - - - - - 12efc92c by Mateusz Kowalczyk at 2015-06-03T05:29:26+01:00 Update some meta data at the top of the docs - - - - - 765ee49f by Bartosz Nitka at 2015-06-07T08:40:59-07:00 Add some Hacking docs for getting started - - - - - 19aaf851 by Bartosz Nitka at 2015-06-07T08:44:30-07:00 Fix markdown - - - - - 2a90cb70 by Mateusz Kowalczyk at 2015-06-08T15:08:36+01:00 Refine hacking instructions slightly - - - - - 0894da6e by Thomas Winant at 2015-06-08T23:47:28-05:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 10a9bb76 by Emanuel Borsboom at 2015-06-12T02:46:23+01:00 Build executable with '-threaded' (fixes haskell/haddock#399) - - - - - 7696b94f by Mateusz Kowalczyk at 2015-06-12T02:59:19+01:00 Update changelog for -threaded Closes haskell/haddock#400 - - - - - d3c118ec by Bartosz Nitka at 2015-06-12T03:00:58+01:00 Fix haddock: internal error: spliceURL UnhelpfulSpan (#207) Inferred type signatures don't have SrcSpans, so let's use the one from the declaration. I've tested this manually on the test-case from haskell/haddock#207, but I got stuck at trying to run the test-suite. - - - - - b67e843b by Mateusz Kowalczyk at 2015-06-12T03:01:50+01:00 Changelog for haskell/haddock#207 Fixes haskell/haddock#207, closes haskell/haddock#402 - - - - - 841d785e by jpmoresmau at 2015-06-12T16:03:16+01:00 Attach to instance location the name that has the same location file Fixes haskell/haddock#383 - - - - - 98791cae by Mateusz Kowalczyk at 2015-06-12T16:08:27+01:00 Update changelog Closes haskell/haddock#398 - - - - - 7c0b5a87 by Phil Ruffwind at 2015-06-12T13:07:25-04:00 Fix alignment of Source links in instance table in Firefox Due to a Firefox bug [1], a combination of 'whitespace: nowrap' on the parent element with 'float: right' on the inner element can cause the floated element to be displaced downwards for no apparent reason. To work around this, the left side is wrapped in its own <span> and set to 'float: left'. As a precautionary measure to prevent the parent element from collapsing entirely, we also add the classic "clearfix" hack. The latter is not strictly needed but it helps prevent bugs if the layout is altered again in the future. Fixes haskell/haddock#384. Remark: line 159 of src/Haddock/Backends/Xhtml/Layout.hs was indented to prevent confusion over the operator precedence of (<+>) vs (<<). [1]: https://bugzilla.mozilla.org/show_bug.cgi?id=488725 - - - - - cfe86e73 by Mateusz Kowalczyk at 2015-06-14T10:49:01+01:00 Update tests for the CSS changes - - - - - 2d4983c1 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding for Haskell source parser module. - - - - - 29548785 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement function for tagging parsed chunks with source spans. - - - - - 6a5e4074 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement simple string chunking based on HsColour library. - - - - - 6e52291f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create basic token classification method. - - - - - da971a27 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Adapt source span tagging to work with current whitespace handling. - - - - - 4feb5a22 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add record accessors to exports of hyperlinker parser module. - - - - - a8cc4e39 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Make parser module export all types and associated accessors. - - - - - fb8d468f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple HTML renderer for parsed source file. - - - - - 80747822 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for specifying the CSS file path in HTML source renderer. - - - - - 994dc1f5 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix identifier recognition in Haskell source parser. - - - - - b1bd0430 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix comment recognition in Haskell source parser. - - - - - 11db85ae by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for recognizing compiler pragmas in source parser. - - - - - 736c7bd3 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding of module for associating tokens with AST names. - - - - - 7e149bc2 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement utility method for extracting variable identifiers from AST. - - - - - 32eb640a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple mechanism for associating tokens with AST names. - - - - - d4eba5bc by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add dummy support for hyperlinking named tokens. - - - - - 2b76141f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matcher bug causing wrong items being hyperlinked. - - - - - 2d48002e by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Constrain elements exported by hyperlinker modules. - - - - - 9715eec6 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for type token recognition. - - - - - 8fa401cb by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for binding token recognition. - - - - - d062400b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement go-to-definition mechanism for local bindings. - - - - - f4dc229b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement module export- and import-list item hyperlinking. - - - - - c9a46d58 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matching to allow parenthesized operators hyperlinking. - - - - - 03aad95a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix weird hyperlinking of parenthesized operators. - - - - - b4694a7d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for type declaration anchors. - - - - - 7358d2d2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for top-level function declaration anchors. - - - - - dfc24b24 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix external anchors to contain HTML file extension. - - - - - a045926c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Refactor the way AST names are handled within detailed tokens. - - - - - c76049b4 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement hyperlinking of imported module names. - - - - - 2d2a1572 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix parsing of single line comments with broken up newlines. - - - - - 11afdcf2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix bug with improper newline handling. - - - - - 8137f104 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issues with escaped newlines in comments. - - - - - 34759b19 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for parsing C preprocessor macros. - - - - - 09f0f847 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for parser module of source hyperlinker. - - - - - 709a8389 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for AST module of source hyperlinker. - - - - - 4df5c227 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add command line option for generating hyperlinked source. - - - - - 7a755ea2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Extend module interface with rich source token stream field. - - - - - 494f4ab1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement source tokenization during interface creation process. - - - - - 5f21c953 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create hyperlinker module and plug it into the Haddock pipeline. - - - - - 0cc8a216 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for providing custom CSS files for hyperlinked source. - - - - - a32bbdc1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for fancy highlighting upon hovering over identifier. - - - - - d16d642a by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make source hyperlinker generate output in apropriate directory. - - - - - ae12953d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create module with hyperlinker utility functions. - - - - - 6d4952c5 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make external hyperlinks point to locations specified by source URLs. - - - - - 8417555d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Rewrite source generation to fixed links and directory structure. - - - - - ce9cec01 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add basic support for cross-package hyperlink generation. - - - - - 7eaf025c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Disable generating hyperlinks for module references. - - - - - a50bf92e by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make Haddock generate source for all interfaces (also hidden ones). - - - - - f5ae2838 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Prevent source parser from throwing exception when lexing fails. - - - - - db9ffbe0 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement workaround for Chrome highlighting issues. - - - - - 0b6b453b by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate correct anchors for data constructors. - - - - - c86d38bc by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate anchors for record field declarations. - - - - - 063abf7f by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issue with hyperlink highlight styling in Chrome browser. - - - - - 880fc611 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking constructor names in patters. - - - - - c9e89b95 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record patterns. - - - - - 17a11996 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record expressions. - - - - - 0eef932d by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Make hyperlinker respect pretty-printer flag and add documentation. - - - - - f87c1776 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Unexpose hyperlinker modules in Cabal configuration. - - - - - 4c9e2b06 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Setup HSpec framework for Haddock API package. - - - - - 4b20cb30 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add basic tests related to comment parsing. - - - - - 6842e919 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add tests related to parsing basic language constructs. - - - - - 87bffb35 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add simple tests for do-notation parsing. - - - - - e7af1841 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add very simple QuickCheck properties for source parser spec. - - - - - c84efcf1 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Create simple test runner for hyperlinker tests. - - - - - 76b90447 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for basic identifier hyperlinking. - - - - - 0fbf4df6 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for operator hyperlinking. - - - - - 731aa039 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for constructor hyperlinking. - - - - - 995a78a2 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for record expressions and patterns hyperlinking. - - - - - 3566875a by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for literal syntax highlighting. - - - - - 68469a35 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add hyperlinker test runner to .cabal and .gitignore files. - - - - - aa946c93 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Adapt hyperlinker test runner to have the same interface as HTML one. - - - - - ce34da16 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Fix hyperlinker test runner file paths and add pretty-printing option. - - - - - 0d7dd65e by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add reference files for hyperlinker test cases. - - - - - efa4a1e0 by Łukasz Hanuszczak at 2015-07-01T00:47:32+02:00 Make hyperlinker test runner strip local links from generated source. - - - - - 3e96e584 by Łukasz Hanuszczak at 2015-07-01T01:14:59+02:00 Create simple script for accepting hyperlinker test case references. - - - - - 526fe610 by Łukasz Hanuszczak at 2015-07-01T01:16:41+02:00 Re-accept hyperlinker test cases with local references stripped out. - - - - - 892e2cb3 by Łukasz Hanuszczak at 2015-07-01T01:22:09+02:00 Fix bug with diffing wrong files in hyperlinker test runner. - - - - - 9ff46039 by Łukasz Hanuszczak at 2015-07-01T18:04:46+02:00 Remove unused dependencies in Haddock API spec configuration. - - - - - 47969c07 by Łukasz Hanuszczak at 2015-07-01T18:32:19+02:00 Add support for hyperlinking synonyms in patterns. - - - - - a73449e0 by Łukasz Hanuszczak at 2015-07-01T18:33:44+02:00 Create test case for hyperlinking @-patterns. - - - - - c2077ed8 by Łukasz Hanuszczak at 2015-07-01T19:06:04+02:00 Add support for hyperlinking universally quantified type variables. - - - - - 68017342 by Łukasz Hanuszczak at 2015-07-01T19:28:32+02:00 Create hyperlinker test case with quantified type variables. - - - - - 51c01a78 by Łukasz Hanuszczak at 2015-07-01T19:34:22+02:00 Add scoped type variables test for polymorphism test case. - - - - - 13181ae2 by Łukasz Hanuszczak at 2015-07-01T19:56:27+02:00 Add record wildcards test for records hyperlinking test case. - - - - - 991b81dd by Łukasz Hanuszczak at 2015-07-01T21:01:42+02:00 Document some functions in XHTML utlity module. - - - - - 98c8dfe5 by Łukasz Hanuszczak at 2015-07-01T22:25:21+02:00 Make hyperlinker render qualified names as one entity. - - - - - 75e13b9b by Łukasz Hanuszczak at 2015-07-01T22:27:38+02:00 Add qualified name test for identifiers hyperlinking test case. - - - - - de1e143f by Łukasz Hanuszczak at 2015-07-02T12:32:59+02:00 Fix crash happening when hyperlinking type family declarations. - - - - - 7a8fb175 by Łukasz Hanuszczak at 2015-07-02T12:47:03+02:00 Add support for anchoring data family constructor declarations. - - - - - 3b404e49 by Łukasz Hanuszczak at 2015-07-02T13:31:05+02:00 Improve support for hyperlinking type families. - - - - - 59eb7143 by Łukasz Hanuszczak at 2015-07-02T13:33:34+02:00 Add hyperlinker test case for checking type and type family declarations. - - - - - d1cda0c0 by Łukasz Hanuszczak at 2015-07-02T13:41:38+02:00 Fix issue with operators being recognized as preprocessor directives. - - - - - da206c9d by Łukasz Hanuszczak at 2015-07-02T17:18:12+02:00 Fix broken tests for parsing and hyperlinking hash operators. - - - - - 53750d1b by Łukasz Hanuszczak at 2015-07-02T18:53:28+02:00 Add support for anchoring signatures in type class declarations. - - - - - 1fa5bb10 by Łukasz Hanuszczak at 2015-07-02T19:04:47+02:00 Make hyperlinker generate anchors only to top-level value bindings. - - - - - a542305c by Łukasz Hanuszczak at 2015-07-02T19:05:58+02:00 Create hyperlinker test case for type classes. - - - - - b0dd4581 by Łukasz Hanuszczak at 2015-07-04T16:28:26+02:00 Update docs with information about source hyperlinking. - - - - - 9795302a by Łukasz Hanuszczak at 2015-07-04T16:52:15+02:00 Update docs on using `--read-interface` option. - - - - - 9acdc002 by Łukasz Hanuszczak at 2015-07-04T17:15:26+02:00 Remove potentially dangerous record access in hyperlinker AST module. - - - - - fb3ab7be by Łukasz Hanuszczak at 2015-07-04T17:40:10+02:00 Make Haddock generate warnings about potential misuse of hyperlinker. - - - - - a324c504 by Łukasz Hanuszczak at 2015-07-04T17:43:22+02:00 Fix incorrect specification of source style option in doc file. - - - - - 3f01a8e4 by Łukasz Hanuszczak at 2015-07-05T17:06:36+02:00 Refactor source path mapping to use modules as indices. - - - - - ac70f5b1 by Łukasz Hanuszczak at 2015-07-05T17:47:34+02:00 Fix bug where not all module interfaces were added to source mapping. - - - - - f5e57da9 by Łukasz Hanuszczak at 2015-07-06T16:39:57+02:00 Extract main hyperlinker types to separate module. - - - - - 43974905 by Łukasz Hanuszczak at 2015-07-06T16:52:13+02:00 Move source paths types to hyperlinker types module. - - - - - 3e236055 by Łukasz Hanuszczak at 2015-07-06T17:06:19+02:00 Add support for hyperlinking modules in import lists. - - - - - 58233d9f by Łukasz Hanuszczak at 2015-07-06T17:26:49+02:00 Add short documentation for hyperlinker source map type. - - - - - 14da016d by Łukasz Hanuszczak at 2015-07-06T18:07:20+02:00 Fix bug with module name being hyperlinked to `Prelude`. - - - - - 8f79db52 by Łukasz Hanuszczak at 2015-07-06T18:23:47+02:00 Fix problem with spec build in Haddock API configuration. - - - - - e7cc056c by Adam Sandberg Eriksson at 2015-07-07T23:22:21+01:00 StrictData: print correct strictness marks - - - - - e8253ca8 by Mateusz Kowalczyk at 2015-07-07T23:58:28+01:00 Update changelog - - - - - 0aba676b by Mateusz Kowalczyk at 2015-07-07T23:58:33+01:00 Relax upper bound on GHC a bit - - - - - 7a595381 by Mateusz Kowalczyk at 2015-07-07T23:58:52+01:00 Delete trailing whitespace - - - - - 50976d5e by Adam Sandberg Eriksson at 2015-07-08T15:03:04+02:00 StrictData: changes in HsBang type - - - - - 83b045fa by Mateusz Kowalczyk at 2015-07-11T14:35:18+01:00 Fix expansion icon for user-collapsible sections Closes haskell/haddock#412 - - - - - b2a3b0d1 by Mateusz Kowalczyk at 2015-07-22T22:03:21+01:00 Make some version changes after 2.16.1 release - - - - - a8294423 by Ben Gamari at 2015-07-27T13:16:07+02:00 Merge pull request haskell/haddock#422 from adamse/adamse-D1033 Merge for GHC D1033 - - - - - c0173f17 by randen at 2015-07-30T14:49:08-07:00 Break the response file by line termination rather than spaces, since spaces may be within the parameters. This simple approach avoids having the need for any quoting and/or escaping (although a newline char will not be possible in a parameter and has no escape mechanism to allow it). - - - - - 47c0ca14 by Alan Zimmerman at 2015-07-31T10:41:52+02:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - 45a9d770 by Mateusz Kowalczyk at 2015-07-31T09:47:43+01:00 Update changelog - - - - - 347a20a3 by Phil Ruffwind at 2015-08-02T23:15:26+01:00 Avoid JavaScript error during page load in non-frame mode In non-frame mode, parent.window.synopsis refers to the synopsis div rather than the nonexistent frame. Unfortunately, the script wrongly assumes that if it exists it must be a frame, leading to an error where it tries to access the nonexistent attribute 'replace' of an undefined value (synopsis.location). Closes haskell/haddock#406 - - - - - 54ebd519 by Phil Ruffwind at 2015-08-02T23:27:10+01:00 Link to the definitions to themselves Currently, the definitions already have an anchor tag that allows URLs with fragment identifiers to locate them, but it is rather inconvenient to obtain such a URL (so-called "permalink") as it would require finding the a link to the corresponding item in the Synopsis or elsewhere. This commit adds hyperlinks to the definitions themselves, allowing users to obtain links to them easily. To preserve the original aesthetics of the definitions, we alter the color of the link so as to be identical to what it was, except it now has a hover effect indicating that it is clickable. Additionally, the anchor now uses the 'id' attribute instead of the (obsolete) 'name' attribute. Closes haskell/haddock#407 - - - - - 02cc8bb7 by Phil Ruffwind at 2015-08-02T23:28:02+01:00 Fix typo in Haddock.Backends.Xhtml.Layout: divSynposis -> divSynopsis Closes haskell/haddock#408 - - - - - 2eb0a458 by Phil Ruffwind at 2015-08-02T23:30:07+01:00 Fix record field alignment when name is too long Change <dl> to <ul> and use display:table rather than floats to layout the record fields. This avoids bug haskell/haddock#301 that occurs whenever the field name gets too long. Slight aesthetic change: the entire cell of the field's source code is now shaded gray rather than just the area where text exists. Fixes haskell/haddock#301. Closes haskell/haddock#421 - - - - - 7abb3402 by Łukasz Hanuszczak at 2015-08-02T23:32:14+01:00 Add some utility definitions for generating line anchors. - - - - - e0b1d79b by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Make hyperlinked source renderer generate line anchors. - - - - - 24dd4c9f by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Re-accept test cases after adding line anchors for each of them. - - - - - 0372cfcb by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Override source line flags when source hyperlinker is enabled. - - - - - a81bcd07 by Mateusz Kowalczyk at 2015-08-02T23:58:25+01:00 Update tests to follow HTML changes - - - - - d2d7426f by Łukasz Hanuszczak at 2015-08-06T20:54:59+02:00 Fix quote syntax for promoted types. - - - - - 668cf029 by Łukasz Hanuszczak at 2015-08-06T21:12:00+02:00 Apply promoted type quoting to type-level consing. - - - - - 89f8e7c6 by Łukasz Hanuszczak at 2015-08-06T21:17:10+02:00 Extend advanced types test case with other examples. - - - - - 86494bca by Łukasz Hanuszczak at 2015-08-06T21:22:06+02:00 Rename advanced types test case and accept new output. - - - - - dbb7c7c0 by Adam Sandberg Eriksson at 2015-08-09T23:01:05+02:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 2a7704fa by Ben Gamari at 2015-08-10T13:18:05+02:00 Merge pull request haskell/haddock#433 from adamse/split-hsbang HsBang is split into HsSrcBang and HsImplBang - - - - - 891954bc by Thomas Miedema at 2015-08-15T14:51:18+02:00 Follow changes in GHC build system - - - - - b55d32ab by Mateusz Kowalczyk at 2015-08-21T18:06:09+01:00 Make Travis use 7.10.2 - - - - - 97348b51 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Move SYB utilities to standalone module. - - - - - 748ec081 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement `everywhere` transformation in SYB module. - - - - - 011cc543 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement generic transformation constructor. - - - - - b9510db2 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Create simple utility module for type specialization. - - - - - 43229fa6 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Make type of type specialization function more general. - - - - - fd844e90 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Add basic HTML test case for checking instance specialization. - - - - - 6ea0ad04 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Make HTML class instance printer take optional signature argument. - - - - - 65aa41b6 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Refactor instance head type to record instead of a meaningless tuple. - - - - - 3fc3bede by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add expandable method section for each class instance declaration. - - - - - 99ceb107 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Move dummy post-family instances for `DocName` to `Types` module. - - - - - e98f4708 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create convenience functions for type specialization module. - - - - - b947552f by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Hook type specialization logic with HTML pretty-printer. - - - - - dcaa8030 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create stub functions for sugaring specialized types. - - - - - fa84bc65 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement list syntax sugaring logic for specialized types. - - - - - e8b05b07 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement tuple syntax sugaring logic for specialized types. - - - - - 68a2e5bc by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Get rid of code duplication in type specialization module. - - - - - 4721c336 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create scaffolding of a framework for renaming specialized types. - - - - - 271b488d by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in missing cases in specialized type renaming function. - - - - - bfa5f2a4 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Remove code duplication in specialized type renamer. - - - - - ea6bd0e8 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Change state of the type renaming monad. - - - - - 77c5496e by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement simple mechanism for generating new type names. - - - - - 91bfb48b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in stub behaviour with actual environment renaming. - - - - - d244517b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix logic behind binder type renaming. - - - - - f3c5e360 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add SYB-like utility function for performing stateful queries. - - - - - eb3f9154 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create function for retrieving free variables from given type. - - - - - a94561d3 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix compilation error caused by incorrect type signature. - - - - - 8bb707cf by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Move `SetName` class definition to types module. - - - - - 5800b13b by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Hook type renamer with instance method HTML pretty-printer. - - - - - 6a480164 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some test cases for type renamer. - - - - - 839842f7 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized signatures refer to original signature declaration. - - - - - 4880f7c9 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized methods be nicely formatted again. - - - - - ab5a6a2e by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Attach source locations to the specialized class methods. - - - - - 43f8a559 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Extend instances test case to also test multi-name type signatures. - - - - - 59bc751c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix tab-based indentation in instances test case. - - - - - c2126815 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Improve placement of instance methods expander button. - - - - - 0a32e287 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add new data type declaration to instance specialization test case. - - - - - 5281af1f by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make type renamer first try single-letter names as alternatives. - - - - - 7d509475 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix type renamer bug with incorrect names being generated. - - - - - 0f35bf7c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some documentation and refactor type specialization module. - - - - - da1d0803 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix another bug where type renamer was generating incorrect names. - - - - - cd39b5cb by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Refactor type renamer to rebinding and pure renaming phases. - - - - - 850251f4 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix unwitting compilation bug. - - - - - e5e9fc01 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Integrate instance specification type into class instance definition. - - - - - 825b0ea0 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer neccessary instance specification type. - - - - - cdba44eb by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix declaration converter to use more appropriate mode for methods. - - - - - bc45c309 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug with types not being specialized at all. - - - - - 5d8e5d89 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug where instance expander was opening wrong section. - - - - - 6001ee41 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix another type renamer bug where not all names were rebound. - - - - - 5f58ce2a by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix yet another renamer bug where some names were not unique. - - - - - 8265e521 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split instance subsection layout method to top-level declarations. - - - - - e5e66298 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Rearrange layout of instance methods in generated documentation. - - - - - a50b4eea by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer used layout method. - - - - - 2ff36ec2 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach section title to the instance methods block. - - - - - 7ac15300 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Add basic tests for associated types in instances test case. - - - - - db0ea2f9 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach associated types information to instance header. - - - - - 71cad4d5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details section contain associated types information. - - - - - deee2809 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Improve look of rendered associated families in instance details. - - - - - 839d13a5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Introduce alternative type for family declarations. - - - - - d397f03f by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details record use new type for family declarations. - - - - - 2b23fe97 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split printer of type family header to separate functions. - - - - - c3498cdc by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Implement HTML renderer for pseudo-family declarations. - - - - - c12bbb04 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Apply type specializer to associated type family declarations. - - - - - 2fd69ff2 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Create helper method for specializing type signatures. - - - - - 475826e7 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Refactor specializer module to be independent from XHTML backend. - - - - - f00b431c by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add some documentation for instance head specializer. - - - - - a9fef2dc by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix bug with missing space in documentation for associated types. - - - - - 50e29056 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with incorrect instance details sections being expanded. - - - - - e6dfdd03 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by adding instance details section. - - - - - 75565b2a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make section identifier of instance details more GHC-independent. - - - - - add0c23e by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Re-accept tests after applying deterministic section identifiers. - - - - - 878f2534 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make identifier generation also architecture-independent. - - - - - 48be69f8 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with instance expander hijacking type hyperlink click. - - - - - 47830c1f by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Get rid of dreadful hashing function for generating identifiers. - - - - - 956cd5af by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Move `InstOrigin` type declaration to more appropriate module. - - - - - bf672ed3 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by changes related to instance expander. - - - - - 8f2a949a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add examples with type operators to the instances test case. - - - - - 64600a84 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add basic support for sugaring infix type operators. - - - - - 747d71b8 by Łukasz Hanuszczak at 2015-08-21T18:22:34+01:00 Add support for sugaring built-in function syntax. - - - - - d4696ffb by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Remove default methods from Hoogle class output. - - - - - bf0e09d7 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add fixity declarations in Hoogle backend output. - - - - - 90e91a51 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix bug with incorrect fixities being generated in Hoogle backend. - - - - - 48f11d35 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve class type family declarations output in Hoogle backend. - - - - - 661e8e8f by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add missing default family equations in Hoogle output. - - - - - e2d64103 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve formatting of class details output in Hoogle backend. - - - - - 490fc377 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix weird-looking Hoogle output for familyless classes. - - - - - ea115b64 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create script file for new HTML test runner. - - - - - 609913d3 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Set default behaviour if no arguments given. - - - - - dc115f67 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for providing optional arguments for test runner. - - - - - d93ec867 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve output of test runner error messages. - - - - - 0be9fe12 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for executing Haddock process in test runner. - - - - - 4e4d00d9 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add GHC path to test runner configuration. - - - - - d67a2086 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make GHC path a test runner command-line argument. - - - - - c810079a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Extend test runner configuration with Haddock arguments. - - - - - fee18845 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor test runner and create stub functions. - - - - - ff7c161f by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make test runner actually run Haddock executable. - - - - - 391f73e6 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with test runner not producing any output files. - - - - - 81a74e2d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Setup skeleton of framework for running tests. - - - - - f8a79ec4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with modules not being found in global search mode. - - - - - 7e700b4d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make Haddock standard output redirection be more configurable. - - - - - 53b4c17a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Incorporate old, ugly functions for comparing output files. - - - - - 8277c8aa by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor architecture of test runner output checking functions. - - - - - 587bb414 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement actual diffing mechanism. - - - - - 9ed2b5e4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve code style to match popular guidelines. - - - - - 14bffaf8 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make it possible to choose alternative diff tool. - - - - - 5cdfb005 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create stub methods for processing test output as XML documents. - - - - - 7ef8e12e by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement link-stripping logic as simple SYB transformation. - - - - - 8a1fcd4f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Incorporate link stripping to output diffing mechanism. - - - - - 37dba2bc by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement footer-stripping logic. - - - - - 9cd52120 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Add missing dependencies in Cabal configuration file. - - - - - e0f83c6e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix issue with output being printed in incorrect order. - - - - - 0a94fbb0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to run tests without generating diff. - - - - - 76a58c6f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor HTML test suite boilerplate to external package. - - - - - af41e6b0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utilities for storing directory configuration. - - - - - d8f0698f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move IO-dependent config of HTML test suite to test package. - - - - - 17369fa0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Enable all compiler warnings in Haddock test package configuration. - - - - - 9d03b47a by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move Haddock runner of HTML test suite to Haddock test package. - - - - - 4b3483c5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 03754194 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience wrappers to simplify in test entry points. - - - - - 27476ab7 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adjust module visibility and items they export. - - - - - c40002ba by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Remove no longer useful test option. - - - - - 55ab2541 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Change extension of test files used for diffing. - - - - - 136bf4e4 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor and simplify XHTML helper module of test package. - - - - - 69f7e3df by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix typo in link stripper of HTML test suite runner. - - - - - 0c3c1c6b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience script for running specific HTML tests. - - - - - 489e1b05 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement utility functions for conditional link stripping. - - - - - 0f985dc3 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt `hypsrc-test` module to work with new testing framework. - - - - - 927406f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement output accepting mechanism in test package. - - - - - 8545715e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utility function for recursive obtaining directory contents. - - - - - cb70381f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 019599b5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix path handling in test runner. - - - - - 399b985b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to specify ignored files for test output. - - - - - 41b3d93d by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt HTML test runner to use new ignoring functionality. - - - - - e2091c8b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix bug with not all test output files being checked. - - - - - b22134f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Specify ignored files for hyperlinker source test runner. - - - - - 3301dfa1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Copy test runner script for hyperlinked source case. - - - - - d39a6dfa by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner invoking Haddock in incorrect mode. - - - - - f32c8ff3 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix path handling in test module loader. - - - - - 10f94ee9 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make test runner ignore test packages with no modules. - - - - - 5dc4239c by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create test runner entry points for LaTeX test suite. - - - - - 58d1f7cf by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with unnecessary checking old test output. - - - - - c7ce76e1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Re-implement test acceptance functionality. - - - - - 13bbabe8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix warning about no longer needed definition. - - - - - 958a99b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Adapt Cabal configuration to execute LaTeX suite with new runner. - - - - - 550ff663 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Setup test suite for Hoogle backend. - - - - - 3aa969c4 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make Hoogle backend create output directory if needed. - - - - - eb085b02 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Add appropriate .gitignore entry and configure Hoogle test suite. - - - - - a50bf915 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner failing when run on multiple test packages. - - - - - bf5368b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create simple test cases for Hoogle backend. - - - - - 6121ba4b by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create helper function for conversion between XML and XHTML. - - - - - cb516061 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Refactor existing code to use XHTML printer instead of XML one. - - - - - e2de8c82 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Improve portability of test runner scripts. - - - - - 9563e774 by Łukasz Hanuszczak at 2015-08-22T23:43:16+02:00 Remove redundant import statement. - - - - - 55353df1 by Łukasz Hanuszczak at 2015-08-24T23:09:20+02:00 Fix bug with accepting to non-existing directory. - - - - - 00a334ca by Łukasz Hanuszczak at 2015-08-24T23:09:47+02:00 Accept output for Hoogle and LaTeX backends. - - - - - 29191d8b by Łukasz Hanuszczak at 2015-08-24T23:14:18+02:00 Get rid of obsolete testing utilities. - - - - - bbb25db3 by Łukasz Hanuszczak at 2015-08-24T23:18:50+02:00 Update sandbox setup guide to work with Haddock test package. - - - - - cfd45248 by Łukasz Hanuszczak at 2015-08-24T23:51:30+02:00 Make Travis aware of Haddock test package. - - - - - 74185b7a by Łukasz Hanuszczak at 2015-08-25T17:41:59+02:00 Fix test suite failure when used with Stack. - - - - - 18769697 by Łukasz Hanuszczak at 2015-08-25T18:02:09+02:00 Add sample Stack setup to the hacking guide. - - - - - 22715eeb by Łukasz Hanuszczak at 2015-08-25T18:04:47+02:00 Fix Markdown formatting of README file. - - - - - b49ec386 by Łukasz Hanuszczak at 2015-08-25T18:13:36+02:00 Setup Haddock executable path in Travis configuration. - - - - - 5d29eb03 by Eric Seidel at 2015-08-30T09:55:58-07:00 account for changes to ipClass - - - - - f111740a by Ben Gamari at 2015-09-02T13:20:37+02:00 Merge pull request haskell/haddock#443 from bgamari/ghc-head account for changes to ipClass - - - - - a2654bf6 by Jan Stolarek at 2015-09-03T01:32:57+02:00 Follow changes from haskell/haddock#6018 - - - - - 2678bafe by Richard Eisenberg at 2015-09-21T12:00:47-04:00 React to refactoring CoAxiom branch lists. - - - - - ebc56e24 by Edward Z. Yang at 2015-09-21T11:53:46-07:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4a8c4198 by Tamar Christina at 2015-09-27T13:59:08+02:00 Create Process: removed PhaseFailed - - - - - 7e99b790 by Oleg Grenrus at 2015-09-27T20:52:10+03:00 Generate docs for orphan instances - - - - - 32e932e2 by Oleg Grenrus at 2015-09-28T07:21:11+03:00 Have source links for orphan instances - - - - - c2eb9f4f by Oleg Grenrus at 2015-09-28T07:24:58+03:00 Print orphan instances header only if required - - - - - ff96f978 by Oleg Grenrus at 2015-09-28T07:40:54+03:00 Add orphan instances link to contents box - - - - - d72490a6 by Oleg Grenrus at 2015-09-28T16:37:44+03:00 Fix orphan instance collapsing - - - - - 25d3dfe5 by Ben Gamari at 2015-10-03T12:38:09+02:00 Merge pull request haskell/haddock#448 from Mistuke/fix-silent-death-of-runInteractive Remove PhaseFailed - - - - - 1e45e43b by Edward Z. Yang at 2015-10-11T13:10:10-07:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b1370ac1 by Adam Gundry at 2015-10-16T16:26:42+01:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 60bef421 by Simon Peyton Jones at 2015-10-26T12:52:36+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 4c1898ca by Simon Peyton Jones at 2015-10-27T14:24:56+00:00 Track change to PatSyn.patSynSig - - - - - 25108e85 by Simon Peyton Jones at 2015-10-27T17:34:18+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - 693643ac by Ben Gamari at 2015-10-28T14:33:06+01:00 Account for Typeable changes The treatment of type families changed. - - - - - cd7c2221 by Simon Peyton Jones at 2015-10-30T13:03:51+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - 712032cb by Herbert Valerio Riedel at 2015-10-31T11:01:45+01:00 Relax upper bound on `base` to allow base-4.9 - - - - - 0bfa0475 by Simon Peyton Jones at 2015-10-31T19:08:13+00:00 More adaption to wildcard-refactor - - - - - 0a3c0cb7 by Simon Peyton Jones at 2015-10-31T22:14:43+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - c4fd4ec9 by Alan Zimmerman at 2015-11-01T11:16:34+01:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 42cdd882 by Matthew Pickering at 2015-11-06T20:02:16+00:00 Change for IEThingWith - - - - - f368b7be by Ben Gamari at 2015-11-11T11:35:51+01:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - e32965b8 by Simon Peyton Jones at 2015-11-13T12:18:17+00:00 Merge with origin/head - - - - - ebcf795a by Edward Z. Yang at 2015-11-13T21:56:27-08:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4e23989f by Simon Peyton Jones at 2015-11-18T11:32:54+00:00 Wibbles to Haddock - - - - - 2289cd4a by Simon Peyton Jones at 2015-11-20T23:12:49+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor - - - - - 695975a6 by Alan Zimmerman at 2015-11-21T21:16:12+02:00 Update to match GHC wip/T11019 - - - - - bbba21e7 by Simon Peyton Jones at 2015-11-23T13:54:31+00:00 merge with origin/ghc-head - - - - - 3d664258 by Simon Peyton Jones at 2015-11-23T17:17:18+00:00 Wibble - - - - - e64cf586 by Herbert Valerio Riedel at 2015-12-05T00:29:55+01:00 Canonicalise Monad instances - - - - - a2de15a7 by Alan Zimmerman at 2015-12-05T17:33:52+02:00 Matching changes for haskell/haddock#11028 - - - - - cc29a3e4 by Alan Zimmerman at 2015-12-05T19:45:33+02:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 95dd15d1 by Richard Eisenberg at 2015-12-11T17:33:39-06:00 Update for type=kinds - - - - - cb5fd9ed by Herbert Valerio Riedel at 2015-12-14T15:07:30+00:00 Bump versions for ghc-7.11 - - - - - 4f286d96 by Simon Peyton Jones at 2015-12-14T15:10:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 13ea2733 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 098df8b8 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track changes in HsSyn for quasi-quotes - - - - - 716a64de by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track change in API of TyCon - - - - - 77a66bca by Adam Gundry at 2015-12-14T15:10:58+00:00 Track API changes to support empty closed type familes - - - - - f2808305 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track the new location of setRdrNameSpace - - - - - ba8b08a4 by Alan Zimmerman at 2015-12-14T15:10:59+00:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - a4ded87e by Thomas Winant at 2015-12-14T15:14:05+00:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 25c78107 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: print correct strictness marks - - - - - 6cbc41c4 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: changes in HsBang type - - - - - ad46821a by Alan Zimmerman at 2015-12-14T15:14:06+00:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - abc0ae5b by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 3308d06c by Thomas Miedema at 2015-12-14T15:14:07+00:00 Follow changes in GHC build system - - - - - 6c763deb by Eric Seidel at 2015-12-14T15:14:07+00:00 account for changes to ipClass - - - - - ae5b4eac by Jan Stolarek at 2015-12-14T15:17:00+00:00 Follow changes from haskell/haddock#6018 - - - - - ffbc40e0 by Richard Eisenberg at 2015-12-14T15:17:02+00:00 React to refactoring CoAxiom branch lists. - - - - - d1f531e9 by Edward Z. Yang at 2015-12-14T15:17:02+00:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 79f73754 by Tamar Christina at 2015-12-14T15:17:02+00:00 Create Process: removed PhaseFailed - - - - - 3d37bebb by Edward Z. Yang at 2015-12-14T15:20:46+00:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 5f8a9e44 by Adam Gundry at 2015-12-14T15:20:48+00:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 79dda70f by Simon Peyton Jones at 2015-12-14T15:26:02+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 959930fb by Simon Peyton Jones at 2015-12-14T15:37:50+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - e18a8df5 by Simon Peyton Jones at 2015-12-14T15:37:52+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - aa35ab52 by Simon Peyton Jones at 2015-12-14T15:40:18+00:00 More adaption to wildcard-refactor - - - - - 8ceef94b by Simon Peyton Jones at 2015-12-14T15:46:04+00:00 Track change to PatSyn.patSynSig - - - - - cd81e83d by Ben Gamari at 2015-12-14T15:46:06+00:00 Account for Typeable changes The treatment of type families changed. - - - - - 63c9117c by Herbert Valerio Riedel at 2015-12-14T15:46:34+00:00 Relax upper bound on `base` to allow base-4.9 - - - - - a484c613 by Alan Zimmerman at 2015-12-14T15:47:46+00:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 2c26fa51 by Matthew Pickering at 2015-12-14T15:47:47+00:00 Change for IEThingWith - - - - - 593baa0f by Ben Gamari at 2015-12-14T15:49:21+00:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - b6b5ca78 by Edward Z. Yang at 2015-12-14T15:49:54+00:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b5b0e072 by Alan Zimmerman at 2015-12-14T15:54:20+00:00 Update to match GHC wip/T11019 - - - - - 14ddeb68 by Simon Peyton Jones at 2015-12-14T15:54:22+00:00 Wibble - - - - - 10a90ad8 by Herbert Valerio Riedel at 2015-12-14T15:54:22+00:00 Canonicalise Monad instances - - - - - ed68ac50 by Alan Zimmerman at 2015-12-14T15:55:48+00:00 Matching changes for haskell/haddock#11028 - - - - - 3f7e5a2d by Alan Zimmerman at 2015-12-14T15:55:49+00:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 6543a73f by Richard Eisenberg at 2015-12-14T15:59:55+00:00 Update for type=kinds - - - - - 193a5c48 by Matthew Pickering at 2015-12-14T18:17:00+00:00 Changes to compile with 8.0 - - - - - add669ec by Matthew Pickering at 2015-12-14T18:47:12+00:00 Warnings - - - - - 223f3fb4 by Ben Gamari at 2015-12-15T23:45:05+01:00 Update for D1200 - - - - - d058388f by Ben Gamari at 2015-12-16T05:40:17-05:00 Types: Add Outputable[Bndr] DocName instances - - - - - 62ecd7fb by Ben Gamari at 2015-12-16T09:23:09-05:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ddbc187a by Ben Gamari at 2015-12-16T17:54:55+01:00 Update for D1200 - - - - - cec83b52 by Ben Gamari at 2015-12-16T17:54:55+01:00 Types: Add Outputable[Bndr] DocName instances - - - - - d12ecc98 by Ben Gamari at 2015-12-16T17:54:55+01:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ada1616f by Ben Gamari at 2015-12-16T17:54:58+01:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a4f0383d by Ben Gamari at 2015-12-16T23:32:38+01:00 Fix Hyperlinker GHC.con_names is now GHC.getConNames - - - - - a10e6849 by Ben Gamari at 2015-12-20T00:54:11+01:00 Merge remote-tracking branch 'mrhania/testing-framework-improvements' into ghc-head - - - - - f078b4fd by Ben Gamari at 2015-12-20T00:59:51+01:00 test: Compatibility with Cabal 1.23 - - - - - 88a511a9 by Ben Gamari at 2015-12-20T01:14:35+01:00 Merge remote-tracking branch 'phadej/orphans' into ghc-head - - - - - 4e250f36 by Ben Gamari at 2015-12-20T01:14:52+01:00 Add html-test for orphan instances output - - - - - 87fffbad by Alan Zimmerman at 2015-12-20T09:50:42+02:00 Update for GHC trac#11258 Adding locations to RdrName in FieldOcc and AmbiguousFieldOcc - - - - - 6b7e51c9 by idontgetoutmuch at 2015-12-20T21:01:47+00:00 Merge pull request haskell/haddock#1 from haskell/ghc-head Ghc head - - - - - 229c1fb5 by Dominic Steinitz at 2015-12-21T07:19:16+00:00 Handle inline math with mathjax. - - - - - 57902d66 by Dominic Steinitz at 2015-12-21T08:07:11+00:00 Fix the documentation for haddock itself. Change notation and add support for inline math. Allow newlines in display math. Add a command line option for the mathjax url (you might want to use a locally installed version). Rebase tests because of extra url and version change. Respond to (some of the) comments. Fix warnings in InterfaceFile.hs - - - - - 0e69f236 by Herbert Valerio Riedel at 2015-12-21T18:30:43+01:00 Fix-up left-over assumptions of GHC 7.12 into GHC 8.0 - - - - - c67f8444 by Simon Peyton Jones at 2015-12-22T16:26:56+00:00 Follow removal of NamedWildCard from HsType - - - - - da40327a by Ben Gamari at 2015-12-23T14:15:28+01:00 html-test/Operators: Clear up ambiguous types For reasons that aren't entirely clear a class with ambiguous types was accepted by GHC <8.0. I've added a functional dependency to clear up this ambiguity. - - - - - 541b7fa4 by Ben Gamari at 2015-12-23T14:18:51+01:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 0febc947 by Ben Gamari at 2015-12-24T00:30:20+01:00 hoogle-test/AssocTypes: Allow AmbiguousTypes GHC 8.0 complains otherwise - - - - - 25810841 by Ben Gamari at 2015-12-24T00:33:18+01:00 OrphanInstances: Accept test output - - - - - 841987f3 by Ben Gamari at 2015-12-25T11:03:11+01:00 Merge remote-tracking branch 'idontgetoutmuch/ghc-head' into ghc-head - - - - - 358391f0 by Ben Gamari at 2015-12-26T10:44:50+01:00 Add missing import - - - - - a8896885 by Ben Gamari at 2015-12-26T10:45:27+01:00 travis: Use Travis containers - - - - - 85e82134 by Herbert Valerio Riedel at 2015-12-30T17:25:39+01:00 tweak version bounds for GHC-8.1 - - - - - 672a5f75 by randen at 2016-01-01T23:45:25-08:00 The Haddock part for fully gcc-like response files " driver/Main.hs * Moved the response file handling into ResponseFile.hs, updating import section as appropriate. * driver/ResponseFile.hs * New file. In anticipation that maybe some day this could be provided by another library, and to make it possible to unit test, this functionality is pulled out of the Main.hs module, and expanded to support the style/format of response files which gcc uses. * The specification for the format of response files which gcc generates and consumes, seems to be best derived from the gcc code itself (libiberty/argv.c), so that is what has been done here. * This is intended to fix haskell/haddock#379 * driver-test/Main.hs * New file for testing code in the driver source tree * driver-test/ResponseFileSpec.hs * Tests, adapted/adopted from the same gcc code where the escaping/unescaping is from, in the hspec style of unit tests * haddock.cabal * Add the driver-test test-suite. Introduces a new library dependency (upon hspec) for the haddock driver target in the haddock.cabal file, but practically, this should not be a problem as the haddock-api tests already depend on hspec. - - - - - 498781df by Ben Gamari at 2016-01-06T13:41:04+01:00 Version bumps and changelog - - - - - 8451e46a by Ben Gamari at 2016-01-06T13:47:17+01:00 Merge remote-tracking branch 'randen/bug468' - - - - - fb2d9181 by Ben Gamari at 2016-01-06T08:14:42-05:00 Add ResponseFile to OtherModules - - - - - 2cb2d2e3 by Ben Gamari at 2016-01-06T14:35:00+01:00 Merge branch 'master' into ghc-head - - - - - 913477d4 by Eric Seidel at 2016-01-11T14:57:57-08:00 deal with un-wiring of IP class - - - - - c557a4b3 by Alan Zimmerman at 2016-01-15T11:14:35+02:00 Update to match wip/T11430 in GHC - - - - - 3e135093 by Alan Zimmerman at 2016-01-16T18:21:59+01:00 Update to match wip/T11430 in GHC - - - - - c48ef2f9 by Ben Gamari at 2016-01-18T09:50:06+01:00 Merge remote-tracking branch 'gridaphobe/ghc-head' into ghc-head - - - - - 9138a1b0 by Eric Seidel at 2016-01-18T12:50:15+01:00 deal with un-wiring of IP class (cherry picked from commit 17388b0f0029d969d79353be7737eb01c7b8dc5f) - - - - - b48c172e by Joachim Breitner at 2016-01-19T00:11:38+01:00 Make sure --mathjax affects all written HTML files This fixes haskell/haddock#475. - - - - - af61fe63 by Ryan Scott at 2016-02-07T23:25:57+01:00 Render */# instead of TYPE 'Lifted/TYPE 'Unlifted (fixes haskell/haddock#473) - - - - - b6458693 by Ben Gamari at 2016-02-07T23:29:27+01:00 Merge pull request haskell/haddock#477 from haskell/issue-475 Make sure --mathjax affects all written HTML files - - - - - adcc0071 by Ben Gamari at 2016-02-07T23:34:52+01:00 Merge branch 'master' into ghc-head - - - - - d0404e61 by Ben Gamari at 2016-02-08T12:46:49+01:00 doc: Switch to Sphinx - - - - - acb153b3 by Ben Gamari at 2016-02-08T12:46:56+01:00 Document --use-unicode flag - - - - - c20bdf1d by Ben Gamari at 2016-02-08T13:41:24+01:00 Fix GHC and haddock-library dependency bounds - - - - - 8d946801 by Ben Gamari at 2016-02-08T14:54:56+01:00 testsuite: Rework handling of output sanitization Previously un-cleaned artifacts were kept as reference output, making it difficult to tell what has changed and causing spurious changes in the version control history. Here we rework this, cleaning the output during acceptance. To accomplish this it was necessary to move to strict I/O to ensure the reference handle was closed before accept attempts to open the reference file. - - - - - c465705d by Ben Gamari at 2016-02-08T15:36:05+01:00 test: Compare on dump For reasons I don't understand the Xml representations differ despite their textual representations being identical. - - - - - 1ec0227a by Ben Gamari at 2016-02-08T15:36:05+01:00 html-test: Accept test output - - - - - eefbd63a by Ben Gamari at 2016-02-08T15:36:08+01:00 hypsrc-test: Accept test output And fix impredicative Polymorphism testcase. - - - - - d1df4372 by Ben Gamari at 2016-02-08T15:40:44+01:00 Merge branch 'fix-up-testsuite' - - - - - 206a3859 by Phil Ruffwind at 2016-02-08T17:51:21+01:00 Move the permalinks to "#" on the right side Since pull request haskell/haddock#407, the identifiers have been permalinked to themselves, but this makes it difficult to copy the identifier by double-clicking. To work around this usability problem, the permalinks are now placed on the far right adjacent to "Source", indicated by "#". Also, 'namedAnchor' now uses 'id' instead of 'name' (which is obsolete). - - - - - 6c89fa03 by Phil Ruffwind at 2016-02-08T17:54:44+01:00 Update tests for previous commit - - - - - effaa832 by Ben Gamari at 2016-02-08T17:56:17+01:00 Merge branch 'anchors-redux' - - - - - 9a2bec90 by Ben Gamari at 2016-02-08T17:58:40+01:00 Use -fprint-unicode-syntax when --use-unicode is enabled This allows GHC to render `*` as its Unicode representation, among other things. - - - - - 28ecac5b by Ben Gamari at 2016-02-11T18:53:03+01:00 Merge pull request haskell/haddock#480 from bgamari/sphinx Move documentation to ReStructuredText - - - - - 222e5920 by Ryan Scott at 2016-02-11T15:42:42-05:00 Collapse type/data family instances by default - - - - - a80ac03b by Ryan Scott at 2016-02-11T20:17:09-05:00 Ensure expanded family instances render correctly - - - - - 7f985231 by Ben Gamari at 2016-02-12T10:04:22+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - d4eda086 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Various cleanups - - - - - 79bee48d by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show kind signatures for type family variables Addresses GHC haskell/haddock#11588. - - - - - b2981d98 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show 'where ...' after closed type family Seems like we should ideally show the actual equations as well but that seems like it would be a fair amount of work - - - - - cfc0e621 by Ben Gamari at 2016-02-18T22:48:12+01:00 Merge pull request haskell/haddock#483 from bgamari/T11588 Fix GHC haskell/haddock#11588 This fixes GHC haskell/haddock#11588: * Show where ... after closed type families * Show kind signatures on type family type variables - - - - - 256e8a0d by Ben Gamari at 2016-02-18T23:15:39+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 32402036 by Richard Eisenberg at 2016-02-24T13:21:44-05:00 Follow-on changes to support RuntimeRep - - - - - 2b1c572d by Matthew Pickering at 2016-03-04T21:04:02+00:00 Remove unused functions - - - - - eb906f50 by Richard Eisenberg at 2016-03-13T21:17:20+01:00 Follow-on changes to support RuntimeRep (cherry picked from commit ab954263a793d8ced734459d6194a5d89214b66c) - - - - - 8c34ef34 by Richard Eisenberg at 2016-03-14T23:47:23-04:00 Changes due to fix for GHC#11648. - - - - - 0e022014 by Richard Eisenberg at 2016-03-15T14:06:45+01:00 Changes due to fix for GHC#11648. (cherry picked from commit bb994de1ab0c76d1aaf1e39c54158db2526d31f1) - - - - - ed3f78ab by Rik Steenkamp at 2016-04-02T22:20:36+01:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 - - - - - d3210042 by Rik Steenkamp at 2016-04-04T15:43:32+02:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 (cherry picked from commit 3ddcbd6b8e6884bd95028381176eb33bee6896fb) - - - - - 236eec90 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 692ee7e0 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. - - - - - 79619f57 by Ben Gamari at 2016-04-10T23:46:22+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. (cherry picked from commit c6d6a18d85e5e2d9bb5904e6919e8a8d7e31c4c5) - - - - - 3358ccb4 by Ben Gamari at 2016-04-10T23:47:27+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 264949b1 by Ben Gamari at 2016-04-16T17:50:23+02:00 Merge pull request haskell/haddock#482 from RyanGlScott/ghc-head Collapse type/data family instances by default - - - - - 478c483a by Ben Gamari at 2016-04-16T17:51:09+02:00 Merge pull request haskell/haddock#489 from mpickering/unused-functions Remove some unused functions - - - - - c94e55f0 by Ryan Scott at 2016-04-16T17:57:54+02:00 Collapse type/data family instances by default (cherry picked from commit 2da130a8db8f995c119b544fad807533236cf088) - - - - - 31e633d3 by Ryan Scott at 2016-04-16T17:58:06+02:00 Ensure expanded family instances render correctly (cherry picked from commit 1338b5d7c32939de6bbc31af0049477e4f847103) - - - - - 03e4d197 by Matthew Pickering at 2016-04-16T17:58:21+02:00 Remove unused functions (cherry picked from commit b89d1c2456bdb2d4208d94ded56155f7088a37d0) - - - - - ed4116f6 by Ben Gamari at 2016-04-20T10:46:57+02:00 ghc: Install files for needed --hyperlinked-source - - - - - 0be999c4 by Ben Gamari at 2016-04-20T11:37:54+02:00 ghc: Install files for needed --hyperlinked-source (cherry picked from commit 5c82c9fc2d21ddaae4a2470f1c375426968f19c6) - - - - - 4d17544c by Simon Peyton Jones at 2016-04-20T12:42:28+01:00 Track change to HsGroup This relates to a big GHC patch for Trac haskell/haddock#11348 - - - - - 1700a50d by Ben Gamari at 2016-05-01T13:19:27+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. - - - - - 0b7c8125 by Ben Gamari at 2016-05-01T13:21:43+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. (cherry picked from commit 609018dd09c4ffe27f9248b2d8b50f6196cd42b9) - - - - - af115ce0 by Ryan Scott at 2016-05-04T22:15:50-04:00 Render Haddocks for derived instances Currently, one can document top-level instance declarations, but derived instances (both those in `deriving` clauses and standalone `deriving` instances) do not enjoy the same privilege. This makes the necessary changes to the Haddock API to enable rendering Haddock comments for derived instances. This is part of a fix for Trac haskell/haddock#11768. - - - - - 76fa1edc by Ben Gamari at 2016-05-10T18:13:25+02:00 haddock-test: A bit of refactoring for debuggability - - - - - 7d4c4b20 by Ben Gamari at 2016-05-10T18:13:25+02:00 Create: Mark a comment as TODO - - - - - 2a6d0c90 by Ben Gamari at 2016-05-10T18:13:25+02:00 html-test: Update reference output - - - - - bd60913d by Ben Gamari at 2016-05-10T18:13:25+02:00 hypsrc-test: Fix reference file path in cabal file It appears the haddock insists on prefixing --hyperlinked-sourcer output with directory which the source appeared in. - - - - - c1548057 by Ben Gamari at 2016-05-10T18:22:12+02:00 doc: Update extra-source-files in Cabal file - - - - - 41d5bae3 by Ben Gamari at 2016-05-10T18:29:21+02:00 Bump versions - - - - - ca75b779 by Ben Gamari at 2016-05-11T16:03:44+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 4e3cfd62 by Ben Gamari at 2016-05-11T16:06:45+02:00 Merge remote-tracking branch 'RyanGlScott/ghc-head' into ghc-head - - - - - a2379970 by Ben Gamari at 2016-05-11T23:15:11+02:00 doc: Add clean targets - - - - - f275212e by Ben Gamari at 2016-05-11T23:15:14+02:00 doc: Add html as an all-target for ghc Otherwise the html documentation won't be installed for binary-dist. - - - - - 388fc0af by Ben Gamari at 2016-05-12T09:49:12+02:00 Update CHANGES - - - - - bad81ad5 by Ben Gamari at 2016-05-12T09:49:38+02:00 Version bump - - - - - c01688a7 by Ben Gamari at 2016-05-12T10:04:58+02:00 Revert "Version bump" This bump was a bit premature. This reverts commit 7b238d9c5be9b07aa2d10df323b5c7b8d1634dc8. - - - - - 7ed05724 by Ben Gamari at 2016-05-12T10:05:33+02:00 doc: Fix GHC clean rule Apparently GHC's build system doesn't permit wildcards in clean paths. - - - - - 5d9611f4 by Ben Gamari at 2016-05-12T17:43:50+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 653566b2 by Ben Gamari at 2016-05-14T09:57:31+02:00 Version bump to 2.17.2 - - - - - b355c439 by Ben Gamari at 2016-05-14T09:57:51+02:00 doc: Use `$(MAKE)` instead of `make` This is necessary to ensure we use gmake. - - - - - 8a18537d by Ben Gamari at 2016-05-14T10:15:45+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - b3290ef1 by Sebastian Meric de Bellefon at 2016-05-14T11:29:47-04:00 Fix haskell/haddock#303. Hide footer when printing The "Produced by Haddock" footer was overlapping the page's body when printing. This patch hides the footer with a css media rule. - - - - - b4a76f89 by Sebastian Meric de Bellefon at 2016-05-15T02:12:46-04:00 Fix haskell/haddock#280. Parsing of module header The initial newlines were counted as indentation spaces, thus disturbing the parsing of next lines - - - - - ba797c9e by Ben Gamari at 2016-05-16T14:53:46+02:00 doc: Vendorize alabaster Sphinx theme Alabaster is now the default sphinx theme and is a significant improvement over the previous default that it's worthproviding it when unavailable (e.g. Sphinx <1.3). - - - - - c9283e44 by Ben Gamari at 2016-05-16T14:55:17+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 1c9ea198 by Sebastian Méric de Bellefon at 2016-05-16T12:30:40-04:00 Merge pull request haskell/haddock#502 from Helkafen/master Fix haskell/haddock#303. Hide footer when printing - - - - - 33631016 by Ben Gamari at 2016-05-16T19:56:11+02:00 Revert "doc: Vendorize alabaster Sphinx theme" This ended up causes far too many issues to be worthwhile. We'll just have to live with inconsistent haddock documentation. This reverts commit cec21957001143794e71bcd9420283df18e7de40. - - - - - 93317d26 by Ben Gamari at 2016-05-16T19:56:11+02:00 cabal: Fix README path - - - - - c8695b22 by Ben Gamari at 2016-05-16T19:58:51+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 0b50eaaa by Ben Gamari at 2016-05-16T21:02:08+02:00 doc: Use whichever theme sphinx deems appropriate - - - - - 857c1c9c by Ben Gamari at 2016-05-16T21:07:08+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 15fc5637 by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Remove redundant imports - - - - - 132ddc6a by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Better debug output For tracking down haskell/haddock#505 - - - - - 2252a149 by Ben Gamari at 2016-05-22T12:43:59+02:00 Don't consider default class ops when looking for decls When we are looking for an operation within a class we don't care about `default`-type declarations. This was the cause of haskell/haddock#505. - - - - - 4886b2ec by Oleg Grenrus at 2016-05-24T16:19:48+03:00 UnfelpfulSpan line number omitted Kind of resolves https://github.com/haskell/haddock/issues/508 - - - - - a4befd36 by Oleg Grenrus at 2016-05-24T16:53:35+03:00 Change Hyperlinked lexer to know about DataKinds ticks - - - - - f45cb52e by David Feuer at 2016-05-24T18:48:53-04:00 Make parser state a newtype Previously, it was `data` wrapping a `Maybe`, which seems a bit silly. Obviously, this can be changed back if anyone wants to add more fields some day. - - - - - 05013dd7 by Sebastian Meric de Bellefon at 2016-05-24T22:03:55-04:00 remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) Frames are a bit broken, ignored by Hackage, and considered obsolete in general. This patch disables frames generation. The mini_*.html files are still used in the synopsis. - - - - - b8163a88 by Ben Gamari at 2016-05-25T14:44:15+02:00 Merge pull request haskell/haddock#507 from bgamari/T505 Fix haskell/haddock#505 - - - - - ea1b30c6 by Sebastian Meric de Bellefon at 2016-05-25T14:17:00-04:00 Update CHANGES - - - - - eddfc258 by Sebastian Méric de Bellefon at 2016-05-25T15:17:40-04:00 Merge pull request haskell/haddock#514 from Helkafen/frames remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) - - - - - 0e506818 by Alex Biehl at 2016-05-26T12:43:09+02:00 Remove misplaced haddock comment - - - - - a07d28c0 by Ben Gamari at 2016-05-27T11:34:59+02:00 Merge pull request haskell/haddock#515 from alexbiehl/master Remove misplaced haddock comment - - - - - 9001d267 by Ben Gamari at 2016-05-27T11:35:46+02:00 Merge pull request haskell/haddock#513 from treeowl/newtype-since Make parser state a newtype - - - - - 74e1a018 by Sebastian Méric de Bellefon at 2016-05-28T17:28:15-04:00 Merge pull request haskell/haddock#504 from Helkafen/issue-280 Fix haskell/haddock#280. Parsing of module header - - - - - 37557f4f by Alan Zimmerman at 2016-05-29T23:36:50+02:00 Matching changes for haskell/haddock#12105 - - - - - 7d09e5d6 by Sebastian Meric de Bellefon at 2016-06-03T18:07:48-04:00 Version bumps (2.17.3, 1.4.2) - - - - - 85b4bc15 by Sebastian Méric de Bellefon at 2016-06-06T18:35:13-04:00 Merge pull request haskell/haddock#521 from Helkafen/master Version bumps (2.17.3, 1.4.2) - - - - - e95f0dee by Sebastian Meric de Bellefon at 2016-06-06T19:11:35-04:00 publish haddock-test library - - - - - 4de40586 by Sebastian Méric de Bellefon at 2016-06-06T20:26:30-04:00 Merge pull request haskell/haddock#512 from phadej/oleg-fixes Fixes for haskell/haddock#508 and haskell/haddock#510 - - - - - ddfd0789 by Dominic Steinitz at 2016-06-09T09:27:28+01:00 Documentation for LaTeX markup. - - - - - 697a503a by Dominic Steinitz at 2016-06-09T09:33:59+01:00 Fix spelling mistake. - - - - - 246f6fff by Dominic Steinitz at 2016-06-09T09:37:15+01:00 Camel case MathJax. - - - - - 4684bd23 by Dominic Steinitz at 2016-06-09T09:44:53+01:00 Fix math typo and add link. - - - - - f20c037c by Simon Peyton Jones at 2016-06-13T18:26:03+01:00 Follow changes to LHsSigWcType - - - - - 0c58996d by Simon Peyton Jones at 2016-06-15T12:56:01+01:00 Follow GHC re-adding FunTy - - - - - 401b5ca7 by Sebastian Méric de Bellefon at 2016-06-15T12:16:47-04:00 Merge pull request haskell/haddock#525 from idontgetoutmuch/master Documentation for LaTeX markup. - - - - - 92d263b7 by Sebastian Méric de Bellefon at 2016-06-15T12:17:29-04:00 Merge pull request haskell/haddock#522 from Helkafen/master publish haddock-test library - - - - - 0953a2ca by Sebastian Meric de Bellefon at 2016-06-16T00:46:46-04:00 Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 65453e14 by Ben Gamari at 2016-06-16T11:16:32+02:00 ocean: Ensure that synopsis fully covers other content Previously MathJax content was being rendered on top of the synopsis due to ambiguous z-ordering. Here we explicitly give the synopsis block a higher z-index to ensure it is rendered on top. Fixes haskell/haddock#531. - - - - - 68e411a1 by Sebastian Méric de Bellefon at 2016-06-16T23:34:39-04:00 Merge pull request haskell/haddock#534 from bgamari/T531 ocean: Ensure that synopsis fully covers other content - - - - - fad6491b by Sebastian Méric de Bellefon at 2016-06-18T23:57:20-04:00 Merge pull request haskell/haddock#533 from Helkafen/master Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 6108e21b by Sebastian Meric de Bellefon at 2016-06-22T23:08:28-04:00 do not create empty src directory Fix haskell/haddock#536. - - - - - 1ef23823 by Sebastian Méric de Bellefon at 2016-06-24T00:04:48-04:00 Merge pull request haskell/haddock#537 from Helkafen/master do not create empty src directory - - - - - 966baa96 by Omari Norman at 2016-06-29T21:59:34-04:00 Add $ as a special character If this character is not escaped, documentation built with Haddock 2.17.2 will fail. This was not an issue with 2.16 series, which causes builds to fail and there is nothing in the docs or error message giving a clue about why builds that used to succeed now don't. - - - - - 324adb60 by Ben Gamari at 2016-07-01T12:18:51+02:00 GhcUtils: Changes for multi-pattern signatures - - - - - d7571675 by Ömer Sinan Ağacan at 2016-07-21T13:30:47+02:00 Add support for unboxed sums - - - - - 29d0907b by Simon Marlow at 2016-07-22T13:55:48+01:00 Disable NFData instances for GHC types when GHC >= 8.2 - - - - - 702d95f3 by Simon Marlow at 2016-08-02T15:57:30+02:00 Disable NFData instances for GHC types when GHC >= 8.0.2 (cherry picked from commit a3309e797c42dae9bccdeb17ce52fcababbaff8a) - - - - - f4fa79c3 by Ben Gamari at 2016-08-07T13:51:18+02:00 ghc.mk: Don't attempt to install html/frames.html The frames business has been removed. - - - - - 9cd63daf by Ben Gamari at 2016-08-07T13:51:40+02:00 Haddock.Types: More precise version guard This allows haddock to be built with GHC 8.0.2 pre-releases. - - - - - f3d7e03f by Mateusz Kowalczyk at 2016-08-29T20:47:45+01:00 Merge pull request haskell/haddock#538 from massysett/master Add $ as a special character - - - - - 16dbf7fd by Bartosz Nitka at 2016-09-20T19:44:04+01:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 - - - - - 7c31c1ff by Bartosz Nitka at 2016-09-27T17:32:22-04:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 (cherry picked from commit 073d899a8f94ddec698f617a38d3420160a7fd0b) - - - - - 33a90dce by Ryan Scott at 2016-09-30T20:53:41-04:00 Haddock changes for T10598 See https://ghc.haskell.org/trac/ghc/ticket/10598 - - - - - 1f32f7cb by Ben Gamari at 2016-10-13T20:01:26-04:00 Update for refactoring of NameCache - - - - - 1678ff2e by Ben Gamari at 2016-11-15T17:42:48-05:00 Bump upper bound on base - - - - - 9262a7c5 by Alan Zimmerman at 2016-12-07T21:14:28+02:00 Match changes in GHC wip/T3384 branch - - - - - ac0eaf1a by Ben Gamari at 2016-12-09T09:48:41-05:00 haddock-api: Don't use stdcall calling convention on 64-bit Windows See GHC haskell/haddock#12890. - - - - - 04afe4f7 by Alan Zimmerman at 2016-12-12T20:07:21+02:00 Matching changes for GHC wip/T12942 - - - - - e1d1701d by Ben Gamari at 2016-12-13T16:50:41-05:00 Bump base upper bound - - - - - 3d3eacd1 by Alan Zimmerman at 2017-01-10T16:59:38+02:00 HsIParamTy now has a Located name - - - - - 7dbceefd by Kyrill Briantsev at 2017-01-12T13:23:50+03:00 Prevent GHC API from doing optimization passes. - - - - - d48d1e33 by Richard Eisenberg at 2017-01-19T08:41:41-05:00 Upstream changes re levity polymorphism - - - - - 40c25ed6 by Alan Zimmerman at 2017-01-26T15:16:18+02:00 Changes to match haskell/haddock#13163 in GHC - - - - - 504f586d by Ben Gamari at 2017-02-02T17:19:37-05:00 Kill remaining static flags - - - - - 49147ea0 by Justus Adam at 2017-03-02T15:33:34+01:00 Adding MDoc to exports of Documentation.Haddock - - - - - 1cfba9b4 by Justus Adam at 2017-03-09T11:41:44+01:00 Also exposing toInstalledIface - - - - - 53f0c0dd by Ben Gamari at 2017-03-09T13:10:08-05:00 Bump for GHC 8.3 - - - - - c7902d2e by Ben Gamari at 2017-03-09T23:46:02-05:00 Bump for GHC 8.2 - - - - - 4f3a74f8 by Ben Gamari at 2017-03-10T10:21:55-05:00 Merge branch 'ghc-head' - - - - - e273b72f by Richard Eisenberg at 2017-03-14T13:34:04-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - 6ec3d436 by Richard Eisenberg at 2017-03-14T15:15:52-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - eee3cda1 by Ben Gamari at 2017-03-15T15:19:59-04:00 Adapt to EnumSet - - - - - 017cf58e by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 736d6773 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 475f84a0 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 13240b53 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - cd16d529 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 3bea97ae by Edward Z. Yang at 2017-03-15T22:50:46-07:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b2b051ce by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 0f082795 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 20ef63c9 by Edward Z. Yang at 2017-03-22T13:48:12-07:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 45692dcb by Edward Z. Yang at 2017-03-22T14:11:25-07:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4eae8caf by Ben Gamari at 2017-03-23T09:25:33-04:00 Merge commit '240bc38b94ed2d0af27333b23392d03eeb615e82' into HEAD - - - - - 0bbe03f5 by Ben Gamari at 2017-03-23T09:27:28-04:00 haddock-api: Bump bound on GHC - - - - - 65f3ac9d by Alex Biehl at 2017-03-23T17:36:11+01:00 Merge pull request haskell/haddock#581 from JustusAdam/master Adding more exports to Documentation.Haddock - - - - - 37d49a47 by Alex Biehl at 2017-03-23T17:39:14+01:00 Merge pull request haskell/haddock#568 from awson/ghc-head Prevent GHC API from doing optimization passes. - - - - - 1ed047e4 by Brian Huffman at 2017-03-23T17:45:58+01:00 Print any user-supplied kind signatures on type parameters. This applies to type parameters on data, newtype, type, and class declarations, and also to forall-bound type vars in type signatures. - - - - - 1b78ca5c by Brian Huffman at 2017-03-23T17:45:58+01:00 Update test suite to expect kind annotations on type parameters. - - - - - a856b162 by Alex Biehl at 2017-03-23T17:49:32+01:00 Include travis build indication badge - - - - - 8e2e2c56 by Ben Gamari at 2017-03-23T17:20:08-04:00 haddock-api: Bump bound on GHC - - - - - 4d2d9995 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 26d6c150b31bc4580ab17cfd07b6e7f9afe10737) - - - - - a650e20f by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 930cfbe58e2e87f5a4d431d89a3c204934e6e858) - - - - - caa282c2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 2067a2d0afa9cef381d26fb7140b67c62f433fc0) - - - - - 49684884 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 0671abfe7e8ceae2269467a30b77ed9d9656e2cc) - - - - - 4dcfeb1a by Edward Z. Yang at 2017-03-23T17:20:08-04:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 3d77b373dd5807d5d956719dd7c849a11534fa6a) - - - - - 74dd19d2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 94610e9b446324f4231fa6ad4c6ac51e4eba8c0e) - - - - - a9b19a23 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 6cc832dfb1de6088a4abcaae62b25a7e944d55c3) - - - - - d3631064 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit bf3c4d72a0fda38561376eac7eda216158783267) - - - - - ef2148fc by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 07b88c5d4e79b87a319fbb08f8ea01dbb41063c1) - - - - - 2f29518b by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 4eb765ca4205c79539d60b7afa9b7e261a4a49fe) - - - - - 37de047d by Phil Ruffwind at 2017-04-03T11:57:14+02:00 Update MathJax URL MathJax is shutting down their CDN: https://www.mathjax.org/cdn-shutting-down/ They recommend migrating to cdnjs. - - - - - e9d24ba8 by David C. Turner at 2017-04-03T14:58:01+02:00 Add highlight for :target to ocean.css - - - - - 4819a202 by Alex Biehl at 2017-04-11T19:36:48+02:00 Allow base-4.10 for haddock-test - - - - - 44cec69c by Alex Biehl at 2017-04-11T19:39:22+02:00 cabal.project for haddock-api, haddock-library and haddock-test - - - - - 935d0f6a by Alex Biehl at 2017-04-11T19:46:29+02:00 Move dist scripts to scripts/ - - - - - 128e150c by Alex Biehl at 2017-04-11T20:34:46+02:00 Add haddock to cabal.project - - - - - cc8e08ea by Alex Biehl at 2017-04-11T20:35:08+02:00 Read files for hyperlinker eagerly This also exposes Documentation.Haddock.Utf8 - - - - - 152dda78 by Alex Biehl at 2017-04-11T20:37:06+02:00 Explicit import list ofr Control.DeepSeq in Haddock.Interface.Create - - - - - 501b33c4 by Kyrill Briantsev at 2017-04-11T21:01:42+02:00 Prevent GHC API from doing optimization passes. - - - - - c9f3f5ff by Alexander Biehl at 2017-04-12T16:36:53+02:00 Add @alexbiehl as maintaner - - - - - 76f214cc by Alex Biehl at 2017-04-13T07:27:18+02:00 Disable doctest with ghc-8.3 Currently doctest doesn't support ghc-head - - - - - 46b4f5fc by Edward Z. Yang at 2017-04-22T20:38:26-07:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f0555235 by Alex Biehl at 2017-04-25T10:08:48+02:00 Travis: Use ghc-8.2.1 on master - - - - - 966ea348 by Alex Biehl at 2017-04-25T10:32:01+02:00 Travis: Verbose cabal output cf. https://travis-ci.org/haskell/haddock/jobs/225512194#L377 - - - - - 36972bcd by Alex Biehl at 2017-04-25T10:40:43+02:00 Use travis_retry for cabal invocations - - - - - b3a09d2c by Alex Biehl at 2017-04-25T17:02:20+02:00 Use new MathJax URL in html-test 18ed871afb82560d5433b2f53e31b4db9353a74e switched to a new MathJax URL but didn't update the tests. - - - - - ae331e5f by Alexander Biehl at 2017-04-25T17:02:20+02:00 Expand signatures for class declarations - - - - - e573c65a by Alexander Biehl at 2017-04-25T17:02:20+02:00 Hoogle: Correctly print classes with associated data types - - - - - 3fc6be9b by Edward Z. Yang at 2017-04-25T17:02:20+02:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit a0c4790e15a2d3fab8d830eee8fcd639fe6d39c9) - - - - - 6725c060 by Herbert Valerio Riedel at 2017-04-25T17:02:20+02:00 `html-test --accept` deltas to reference samples - - - - - 7d444d61 by Alex Biehl at 2017-04-26T07:13:50+02:00 Remove anything related to obsolete frames mode - - - - - b888972c by Alex Biehl at 2017-04-26T07:49:10+02:00 Cherry-picked remaining commits from haddock-2.17.4-release (#603) * Release haddock/haddock-api 2.17.4 and haddock-library 1.4.3 * Set version bounds for haddock-library NB: This allows GHC 8.2.1's base * Set version bounds for haddock & haddock-api The version bounds support GHC 8.2 * Merge (temporary) v2.17.3 branch into v2.17 This allows us to delete the v2.17.3 branch * Fixup changelog * Pin down haddock-api to a single version as otherwise `haddock`'s package version has no proper meaning * fix source-repo spec for haddock-api - - - - - 4161099b by Alex Biehl at 2017-04-26T11:11:20+02:00 Update changelog to reflect news in HEAD - - - - - eed72cb8 by Alex Biehl at 2017-04-26T11:11:20+02:00 Markdownify changelog - - - - - 5815cea1 by Alex Biehl at 2017-04-26T11:32:33+02:00 Bump to 2.18.0 (#605) - - - - - a551d558 by Alex Biehl at 2017-04-29T22:00:25+02:00 Update attoparsec-0.12.1.1 to attoparsec-0.13.1.0 - - - - - ea164a8d by Sergey Vinokurov at 2017-04-29T22:42:36+02:00 Improve error message - - - - - 2e10122f by Alex Biehl at 2017-04-30T10:07:46+02:00 Correctly remember collapsed sections (#608) Now the "collapsed" cookie stores which sections have changed state instead of which are collapsed. - - - - - f9b24d99 by Alex Biehl at 2017-05-01T17:40:36+02:00 Lazily decode docMap and argMap (#610) These are only used in case of a doc reexport so most of the time decoding these is wasted work. - - - - - 2372af62 by Alex Biehl at 2017-05-01T21:59:23+02:00 Fix Binary instance for InstalledInterface (#611) (#610) introduced lazy decoding for docs from InstalledInterface but forgot to remove the original calls to get and put_ - - - - - 6c633c13 by Nathan Collins at 2017-05-11T11:47:55+02:00 Improve documenation of Haddock markup (#614) * Improve documentation of Haddock markup. - document that Haddock supports inferring types top-level functions with without type signatures, but also explain why using this feature is discouraged. Looks like this feature has been around since version 2.0.0.0 in 2008! - rework the "Module description" section: - move the general discussion of field formatting to the section intro and add examples illustrating the prose for multiline fields. - mention that newlines are preserved in some multiline fields, but not in others (I also noticed that commas in the `Copyright` field are not preserved; I'll look into this bug later). - add a subsection for the module description fields documentation, and put the field keywords in code formatting (double back ticks) instead of double quotes, to be consistent with the typesetting of keywords in other parts of the documentation. - mention that "Named chunks" are not supported in the long-form "Module description" documentation. - fix formatting of keywords in the "Module attributes" section. Perhaps these errors were left over from an automatic translation to ReST from some other format as part of the transition to using Sphinx for Haddock documentation? Also, add a missing reference here; it just said "See ?"! - update footnote about special treatment for re-exporting partially imported modules not being implemented. In my tests it's not implemented at all -- I tried re-exporting both `import B hiding (f)` and `import B (a, b)` style partial imports, and in both cases got the same result as with full imports `import B`: I only get a module reference. * Rework the `Controlling the documentation structure` section. My main goal was to better explain how to use Haddock without an export list, since that's my most common use case, but I hope I improved the section overall: - remove the incomplete `Omitting the export list` section and fold it into the other sections. In particular, summarize the differences between using and not using an export list -- i.e. control over what and in what order is documented -- in the section lead. - add "realistic" examples that use the structure markup, both with and without an export list. I wanted a realistic example here to capture how it can be useful to explain the relationship between a group of functions in a section, in addition to documenting their individual APIs. - make it clear that you can associate documentation chunks with documentation sections when you aren't using an export list, and that doing it in the most obvious way -- i.e. with `-- |`, as you can in the export list -- doesn't work without an export list. It took me a while to figure this out the first time, since the docs didn't explain it at all before. - add a "no export list" example to the section header section. - add more cross references. * Add examples of gotchas for markup in `@...@`. I'm not sure this will help anyone, since I think most people first learn about `@...@` by reading other people's Haddocks, but I've documented the mistakes which I've made and then gotten confused by. * Use consistent Capitalization of Titles. Some titles were in usual title caps, and others only had the first word capitalized. I chose making them all use title caps because that seems to make the cross references look better. - - - - - d4734f45 by Ben Gamari at 2017-05-12T20:36:08+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 93883f37 by Alex Biehl at 2017-05-12T21:02:33+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 5b8f179c by Alex Biehl at 2017-05-13T12:48:10+02:00 Consequently use inClass and notInClass in haddock-library (#617) These allow attoparsec to do some clever lookup optimization - - - - - 77984b82 by Doug Wilson at 2017-05-27T17:37:38+02:00 Don't enable compilation for template haskell (#624) This is no longer necessary after ghc commit 53c78be0aab76a3107c4dacbb1d177afacdd37fa - - - - - 5a3de2b4 by Doug Wilson at 2017-05-27T19:54:53+02:00 Improve Syb code (#621) Specialize.hs and Ast.hs are modified to have their Syb code not recurse into Name or Id in HsSyn types. Specialize.hs is refactored to have fewer calls to Syb functions. Syb.hs has some foldl calls replaced with foldl' calls. There is still a lot of performance on the floor of Ast.hs. The RenamedSource is traversed many times, and lookupBySpan is very inefficient. everywhereBut and lookupBySpan dominate the runtime whenever --hyperlinked-source is passed. - - - - - 3d35a949 by Alex Biehl at 2017-05-30T19:01:37+02:00 Clear fixme comment (#625) - - - - - 2a44bd0c by Alex Biehl at 2017-05-30T19:02:12+02:00 Make haddock-library and haddock-api warning free (#626) - - - - - bd1a0e42 by Alex Biehl at 2017-06-01T10:40:33+02:00 Include `driver-test/*.hs` sdist (#630) This lead to haskell/haddock#629. - - - - - 184a3ab6 by Doug Wilson at 2017-06-03T12:02:08+02:00 Disable pattern match warnings (#628) This disables the pattern match checker which can be very expensive in some cases. The disabled warnings include: * Opt_WarnIncompletePatterns * Opt_WarnIncompleteUniPatterns * Opt_WarnIncompletePatternsRecUpd * Opt_WarnOverlappingPatterns - - - - - 0cf68004 by Alex Biehl at 2017-06-03T20:37:28+02:00 Allow user defined signatures for pattern synonyms (#631) - - - - - 7f51a58a by Alex Biehl at 2017-06-04T11:56:38+02:00 Use NameSet for isExported check (#632) - - - - - d8f044a9 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Match new AST as per GHC wip/new-tree-one-param See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow - - - - - da1254e3 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Rename extension index tags - - - - - 538c7514 by Christiaan Baaij at 2017-06-09T08:26:43+02:00 Haddock support for bundled pattern synonyms (#627) * Haddock support for bundled pattern synonyms * Add fixities to bundled pattern synonyms * Add bundled pattern synonyms to the synopsis * Store bundled pattern fixities in expItemFixities * Add test for bundled pattern synonyms * Stop threading fixities * Include bundled pattern synonyms for re-exported data types Sadly, fixity information isn't found for re-exported data types * Support for pattern synonyms * Modify tests after haskell/haddock#631 * Test some reexport variations * Also lookup bundled pattern synonyms from `InstalledInterface`s * Check isExported for bundled pattern synonyms * Pattern synonym is exported check * Always look for pattern synonyms in the current module Another overlooked cornercase * Account for types named twice in export lists Also introduce a fast function for nubbing on a `Name` and use it throughout the code base. * correct fixities for reexported pattern synonyms * Fuse concatMap and map * Remove obsolete import * Add pattern synonyms to visible exports * Fix test * Remove corner case - - - - - a050bffd by Doug Wilson at 2017-06-21T09:27:33+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#636) There is some performance improvement. GHC compiler: | version | bytes allocated | cpu_seconds --------------------------------- | before | 56057108648 | 41.0 | after | 51592019560 | 35.1 base: | version | bytes allocated | cpu_seconds --------------------------------- | before | 25174011784 | 14.6 | after | 23712637272 | 13.1 Cabal: | version | bytes allocated | cpu_seconds --------------------------------- | before | 18754966920 | 12.6 | after | 18198208864 | 11.6 - - - - - 5d06b871 by Doug Wilson at 2017-06-22T20:23:29+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#639) * Use new function getNameToInstancesIndex instead of tcRnGetInfo There is some significant performance improvement in the ghc testsuite. haddock.base: -23.3% haddock.Cabal: -16.7% haddock.compiler: -19.8% * Remove unused imports - - - - - b11bb73a by Alex Biehl at 2017-06-23T14:44:41+02:00 Lookup fixities for reexports without subordinates (#642) So we agree that reexported declarations which do not have subordinates (for example top-level functions) shouldn't have gotten fixities reexported according to the current logic. I wondered why for example Prelude.($) which is obviously reexported from GHC.Base has fixities attached (c.f. http://hackage.haskell.org/package/base-4.9.1.0/docs/Prelude.html#v:-36-). The reason is this: In mkMaps we lookup all the subordinates of top-level declarations, of course top-level functions don't have subordinates so for them the resulting list is empty. In haskell/haddock#644 I established the invariant that there won't be any empty lists in the subordinate map. Without the patch from haskell/haddock#642 top-level functions now started to fail reexporting their fixities. - - - - - d2a6dad6 by Alex Biehl at 2017-06-23T18:30:45+02:00 Don't include names with empty subordinates in maps (#644) These are unecessary anyway and just blow up interface size - - - - - 69c2aac4 by Alex Biehl at 2017-06-29T19:54:49+02:00 Make per-argument docs for class methods work again (#648) * Make per-argument docs for class methods work again * Test case - - - - - c9448d54 by Bartosz Nitka at 2017-07-02T12:12:01+02:00 Fix haddock: internal error: links: UnhelpfulSpan (#561) * Fix haddock: internal error: links: UnhelpfulSpan This fixes haskell/haddock#554 for me. I believe this is another fall out of `wildcard-refactor`, like haskell/haddock#549. * Comment to clarify why we take the methods name location - - - - - d4f29eb7 by Alex Biehl at 2017-07-03T19:43:04+02:00 Document record fields when DuplicateRecordFields is enabled (#649) - - - - - 9d6e3423 by Yuji Yamamoto at 2017-07-03T22:37:58+02:00 Fix test failures on Windows (#564) * Ignore .stack-work * Fix for windows: use nul instead of /dev/null * Fix for windows: canonicalize line separator * Also normalize osx line endings - - - - - 7d81e8b3 by Yuji Yamamoto at 2017-07-04T16:13:12+02:00 Avoid errors on non UTF-8 Windows (#566) * Avoid errors on non UTF-8 Windows Problem ==== haddock exits with errors like below: `(1)` ``` haddock: internal error: <stderr>: hPutChar: invalid argument (invalid character) ``` `(2)` ``` haddock: internal error: Language\Haskell\HsColour\Anchors.hs: hGetContents: invalid argument (invalid byte sequence) ``` `(1)` is caused by printing [the "bullet" character](http://www.fileformat.info/info/unicode/char/2022/index.htm) onto stderr. For example, this warning contains it: ``` Language\Haskell\HsColour\ANSI.hs:62:10: warning: [-Wmissing-methods] • No explicit implementation for ‘toEnum’ • In the instance declaration for ‘Enum Highlight’ ``` `(2)` is caused when the input file of `readFile` contains some Unicode characters. In the case above, '⇒' is the cause. Environment ---- OS: Windows 10 haddock: 2.17.3 GHC: 8.0.1 Solution ==== Add `hSetEncoding handle utf8` to avoid the errors. Note ==== - I found the detailed causes by these changes for debugging: - https://github.com/haskell/haddock/commit/8f29edb6b02691c1cf4c479f6c6f3f922b35a55b - https://github.com/haskell/haddock/commit/1dd23bf2065a1e1f2c14d0f4abd847c906b4ecb4 - These errors happen even after executing `chcp 65001` on the console. According to the debug code, `hGetEncoding stderr` returns `CP932` regardless of the console encoding. * Avoid 'internal error: <stderr>: hPutChar: invalid argument (invalid character)' non UTF-8 Windows Better solution for 59411754a6db41d17820733c076e6a72bcdbd82b's (1) - - - - - eded67d2 by Alex Biehl at 2017-07-07T19:17:15+02:00 Remove redudant import warning (#651) - - - - - 05114757 by Alex Biehl at 2017-07-08T00:33:12+02:00 Avoid missing home module warning (#652) * Avoid missing home module warning * Update haddock-library.cabal - - - - - e9cfc902 by Bryn Edwards at 2017-07-17T07:51:20+02:00 Fix haskell/haddock#249 (#655) - - - - - eb02792b by Herbert Valerio Riedel at 2017-07-20T09:09:15+02:00 Fix compilation of lib:haddock-library w/ GHC < 8 - - - - - 9200bfbc by Alex Biehl at 2017-07-20T09:20:38+02:00 Prepare 2.18.1 release (#657) - - - - - 46ddd22c by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Tweak haddock-api.cabal for pending release - - - - - 85e33d29 by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Avoid trivial use of LambdaCase otherwise we can't test w/ e.g. GHC 7.4.2 - - - - - 3afb4bfe by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Refactor .cabal to use sub-lib for vendored lib A practical benefit is that we can control the build-depends and also avoid some recompilation between library and test-suite. - - - - - e56a552e by Herbert Valerio Riedel at 2017-07-20T10:17:48+02:00 haddock-api: add changelog pointing to haddock's changelog This addresses https://github.com/haskell/haddock/issues/638#issuecomment-309283297 - - - - - 2222ff0d by Herbert Valerio Riedel at 2017-07-20T10:19:56+02:00 Drop obsolete/misleading `stability: experimental` This .cabal property has long been considered obsolete - - - - - 9b882905 by Alex Biehl at 2017-07-20T11:25:54+02:00 Beef up haddock description (#658) * Beef up haddock description * Handle empty lines - - - - - bb60e95c by Herbert Valerio Riedel at 2017-07-20T12:08:53+02:00 Import @aisamanra's Haddock cheatsheet from https://github.com/aisamanra/haddock-cheatsheet - - - - - 0761e456 by Herbert Valerio Riedel at 2017-07-20T12:12:55+02:00 Add cheatsheet to haddock.cabal - - - - - 2ece0f0f by Herbert Valerio Riedel at 2017-07-20T12:18:38+02:00 Mention new-build in README - - - - - 947b7865 by Herbert Valerio Riedel at 2017-07-20T12:32:16+02:00 Update README Also improves markup and removes/fixes redundant/obsolete parts [skip ci] - - - - - 785e09ad by Alex Biehl at 2017-07-27T07:28:57+02:00 Bump haddock to 2.18.2, haddock-library to 1.4.5 - - - - - e3ff1ca3 by Alex Biehl at 2017-07-31T20:15:32+02:00 Move `DocMarkup` from haddock-api to haddock-library (#659) * Move `DocMarkup` from haddock-api to haddock-library * Move more markup related functions * Markup module * CHANGELOG - - - - - cda7c20c by Alex Biehl at 2017-07-31T20:35:49+02:00 Fixup haddock - - - - - 583b6812 by Alex Biehl at 2017-07-31T21:20:45+02:00 Changelog for haddock-library - - - - - bac6a0eb by Alex Biehl at 2017-07-31T21:50:24+02:00 Prepare haddock-library-1.4.5 release - - - - - 58ce6877 by Moritz Drexl at 2017-08-05T16:44:40+02:00 Fix renaming after instance signature specializing (#660) * rework rename * Add regression test for Bug 613 * update tests * update changelog - - - - - b8137ec8 by Tim Baumann at 2017-08-06T11:33:38+02:00 Fix: Generate pattern signatures for constructors exported as patterns (#663) * Fix pretty-printing of pattern signatures Pattern synonyms can have up to two contexts, both having a different semantic meaning: The first holds the constraints required to perform the matching, the second contains the constraints provided by a successful pattern match. When the first context is empty but the second is not it is necessary to render the first, empty context. * Generate pattern synonym signatures for ctors exported as patterns This fixes haskell/haddock#653. * Simplify extractPatternSyn It is not necessary to generate the simplest type signature since it will be simplified when pretty-printed. * Add changelog entries for PR haskell/haddock#663 * Fix extractPatternSyn error message - - - - - d037086b by Alex Biehl at 2017-08-06T12:43:25+02:00 Bump haddock-library - - - - - 99d7e792 by Alex Biehl at 2017-08-06T12:44:07+02:00 Bump haddock-library in haddock-api - - - - - 94802a5b by Alex Biehl at 2017-08-06T13:18:02+02:00 Provide --show-interface option to dump interfaces (#645) * WIP: Provide --show-interface option to dump interfaces Like ghcs own --show-iface this flag dumps a binary interface file to stdout in a human (and machine) readable fashion. Currently it uses json as output format. * Fill all the jsonNull stubs * Rework Bifunctor instance of DocH, update changelog and documentation * replace changelog, bring DocMarkupH doc back * Update CHANGES.md * Update CHANGES.md * Move Control.Arrow up It would result in unused import if the Bifunctor instance is not generated. - - - - - c662e476 by Ryan Scott at 2017-08-14T21:00:21-04:00 Adapt to haskell/haddock#14060 - - - - - b891eb73 by Alex Biehl at 2017-08-16T08:24:48+02:00 Bifoldable and Bitraversable for DocH and MetaDoc - - - - - 021bb56c by Alex Biehl at 2017-08-16T09:06:40+02:00 Refactoring: Make doc renaming monadic This allows us to later throw warnings if can't find an identifier - - - - - 39fbf022 by Alex Biehl at 2017-08-19T20:35:27+02:00 Hyperlinker: Avoid linear lookup in enrichToken (#669) * Make Span strict in Position * Hyperlinker: Use a proper map to enrich tokens - - - - - e13baedd by Alex Biehl at 2017-08-21T20:05:42+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 27dd6e87 by Alex Biehl at 2017-08-21T22:06:35+02:00 Drop Avails from export list - - - - - 86b247e2 by Alex Biehl at 2017-08-22T08:44:22+02:00 Bump ghc version for haddock-api tests - - - - - d4607ca0 by Alex Biehl at 2017-08-22T08:45:17+02:00 Revert "Drop Avails from export list" This reverts commit a850ba86d88a4fb9c0bd175453a2580e544e3def. - - - - - c9c54c30 by Alex Biehl at 2017-08-22T09:26:01+02:00 IntefaceFile version - - - - - a85b7c02 by Ben Gamari at 2017-08-22T09:29:52-04:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 34e976f5 by Ben Gamari at 2017-08-22T17:40:06+02:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 577abf06 by Ryan Scott at 2017-08-23T14:47:29-04:00 Update for haskell/haddock#14131 - - - - - da68fc55 by Florian Eggenhofer at 2017-08-27T18:21:56+02:00 Generate an index for package content search (#662) Generate an index for package content search - - - - - 39e62302 by Alex Biehl at 2017-08-27T18:50:16+02:00 Content search for haddock html doc - - - - - 91fd6fb2 by Alex Biehl at 2017-08-28T18:39:58+02:00 Fix tests for content search - - - - - b4a3798a by Alex Biehl at 2017-08-28T18:44:08+02:00 Add search button to #page-menu - - - - - 25a7ca65 by Alex Biehl at 2017-08-28T18:47:43+02:00 Load javascript below the fold - - - - - 8d323c1a by Alex Biehl at 2017-08-28T18:49:22+02:00 Accept tests - - - - - c5dac557 by Alex Biehl at 2017-08-28T19:14:55+02:00 Content search css - - - - - 89a5af57 by Paolo Veronelli at 2017-08-29T07:42:13+02:00 Removed `nowrap` for interface method sigs (#674) with nowrap the interfaces method sigs would expand at libitum - - - - - a505f6f7 by Alex Biehl at 2017-08-29T08:05:33+02:00 Include subordinates in content index - - - - - 4bb698c4 by Alexander Biehl at 2017-08-29T11:40:19+02:00 QuickNav: Make docbase configurable - - - - - c783bf44 by Alexander Biehl at 2017-08-29T11:48:36+02:00 QuickNav: Also use baseUrl for doc-index.json request - - - - - 47017510 by Alex Biehl at 2017-08-29T17:56:47+02:00 Fix test fallout (again) - - - - - 924fc318 by Alex Biehl at 2017-08-30T09:24:56+02:00 Write meta.json when generating html output (#676) - - - - - 717dea52 by Alex Biehl at 2017-09-01T09:20:34+02:00 Use relative URL when no docBaseUrl given - - - - - e5d85f3b by Alex Biehl at 2017-09-01T09:35:19+02:00 Add missing js files to data-files (#677) - - - - - 95b9231a by Alex Biehl at 2017-09-01T11:01:36+02:00 Rename "Search" tab to "Quick Jump" - - - - - da0ead0b by Alex Biehl at 2017-09-01T13:03:49+02:00 Make trigger link configurable (#678) QuickNav: Configurable show/hide trigger - - - - - de7da594 by Ben Gamari at 2017-09-05T06:49:55-04:00 Account for "Remember the AvailInfo for each IE" As of GHC commit f609374a55bdcf3b79f3a299104767aae2ffbf21 GHC retains the AvailInfo associated with each IE. @alexbiehl has a patch making proper use of this change, but this is just to keep things building. - - - - - b05cd3b3 by Ben Gamari at 2017-09-14T07:55:07-04:00 Bump upper bound on base - - - - - 79db899e by Herbert Valerio Riedel at 2017-09-21T23:27:52+02:00 Make compatible with Prelude.<> export in GHC 8.4/base-4.11 - - - - - 3405dd52 by Tim Baumann at 2017-09-23T22:02:01+02:00 Add compile step that bundles and compresses JS files (#684) * Add compile step that bundles and compresses JS files Also, manage dependencies on third-party JS libraries using NPM. * Compile JS from TypeScript * Enable 'noImplicitAny' in TypeScript * QuickJump: use JSX syntax * Generate source maps from TypeScript for easier debugging * TypeScript: more accurate type * Separate quick jump css file from ocean theme - - - - - df0b5742 by Alex Biehl at 2017-09-29T21:15:40+02:00 Bump base for haddock-library and haddock-test - - - - - 62b12ea0 by Merijn Verstraaten at 2017-10-04T16:03:13+02:00 Inhibit output of coverage information for hidden modules. (#687) * Inhibit output of coverage information for hidden modules. * Add changelog entry. - - - - - 8daf8bc1 by Alexander Biehl at 2017-10-05T11:27:05+02:00 Don't use subMap in attachInstances - - - - - ad75114e by Alexander Biehl at 2017-10-05T11:27:58+02:00 Revert "Don't use subMap in attachInstances" This reverts commit 3adf5bcb1a6c5326ab33dc77b4aa229a91d91ce9. - - - - - 7d4aa02f by Alex Biehl at 2017-10-08T15:32:28+02:00 Precise Haddock: Use Avails for export resolution (#688) * Use Avails for export resolution * Support reexported modules * Factor out availExportItem * Use avails for fullModuleExports * Don't use subMap in attachInstances * lookupDocs without subMap * Completely remove subMap * Only calculate unqualified modules when explicit export list is given * Refactor * Refine comment * return * Fix * Refactoring * Split avail if declaration is not exported itself * Move avail splitting - - - - - b9b4faa8 by Alex Biehl at 2017-10-08T19:38:21+02:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 43325295 by Alex Biehl at 2017-10-08T20:18:46+02:00 Fix merge fallout - - - - - c6423cc0 by Alex Biehl at 2017-10-08T20:36:12+02:00 Copy QuickJump files over - - - - - 1db587c3 by Tim Baumann at 2017-10-09T18:33:09+02:00 Use <details> element for collapsibles (#690) * Remove unnecessary call to 'collapseSection' The call is unnecessary since there is no corresponding toggle for hiding the section of orphan instances. * Use <details> for collapsibles This makes them work even when JS is disabled. Closes haskell/haddock#560. - - - - - 1b54c64b by Tim Baumann at 2017-10-10T09:50:59+02:00 Quick Jump: Show error when loading 'doc-index.json' failed (#691) - - - - - 910f716d by Veronika Romashkina at 2017-10-24T07:36:20+02:00 Fix tiny typo in docs (#693) - - - - - b21de7e5 by Ryan Scott at 2017-10-24T13:07:15+02:00 Overhaul Haddock's rendering of kind signatures (#681) * Overhaul Haddock's rendering of kind signatures * Strip off kind signatures when specializing As an added bonus, this lets us remove an ugly hack specifically for `(->)`. Yay! * Update due to 0390e4a0f61e37bd1dcc24a36d499e92f2561b67 * @alexbiehl's suggestions * Import injectiveVarsOfBinder from GHC - - - - - 6704405c by Ryan Scott at 2017-10-28T07:10:27+02:00 Fix Haddock rendering of kind-indexed data family instances (#694) - - - - - 470f6b9c by Alex Biehl at 2017-10-30T08:45:51+01:00 Add QuickJump version to meta.json (#696) - - - - - b89eccdf by Alex Biehl at 2017-10-30T10:15:49+01:00 Put Quickjump behind --quickjump flag (#697) - - - - - 3095fb58 by Alex Biehl at 2017-10-30T19:09:06+01:00 Add build command to package.json - - - - - f223fda9 by Alex Biehl at 2017-10-30T19:10:39+01:00 Decrease threshold for fuzzy matching - - - - - 80245dda by Edward Z. Yang at 2017-10-31T20:35:05+01:00 Supported reexported-modules via --reexport flag. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 7e389742 by Alex Biehl at 2017-10-31T20:37:56+01:00 Correct missing title in changelog - - - - - 1a2a1c03 by Alex Biehl at 2017-10-31T20:59:07+01:00 Copy quickjump.css for nicer error messages - - - - - db234bb9 by Alex Biehl at 2017-10-31T21:31:18+01:00 Reexported modules: Report warnings if argument cannot be parsed or ... module cannot be found - - - - - eea8a205 by Carlo Hamalainen at 2017-10-31T21:43:14+01:00 More general type for nameCacheFromGhc. (#539) - - - - - 580eb42a by Alex Biehl at 2017-10-31T21:46:52+01:00 Remote tab - - - - - 0e599498 by Alex Biehl at 2017-10-31T21:48:55+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 7b8539bb by Alex Biehl at 2017-10-31T22:28:34+01:00 fullModuleContents traverses exports in declaration order - - - - - 0c91fbf2 by Alex Biehl at 2017-10-31T22:32:31+01:00 Remove excessive use of list comprehensions - - - - - f7356e02 by Alex Biehl at 2017-11-01T19:11:03+01:00 Make better use of AvailInfo - - - - - f3e512d5 by Alex Biehl at 2017-11-02T12:16:22+01:00 Always return documentation for exported subordinates ... event if they have no documentation (e.g. noDocForDecl) By using the information in the AvailInfo we don't need additional export checks. - - - - - 7cf58898 by Alan Zimmerman at 2017-11-07T08:28:03+02:00 Match changes for Trees that Grow in GHC - - - - - e5105a41 by Alan Zimmerman at 2017-11-08T17:21:58+02:00 Match Trees That Grow - - - - - 55178266 by Alan Zimmerman at 2017-11-11T22:20:31+02:00 Match Trees that Grow in GHC for HsExpr - - - - - 2082ab02 by Ryan Scott at 2017-11-14T15:27:03+01:00 Actually render infix type operators as infix (#703) * Actually render infix type operators as infix * Account for things like `(f :*: g) p`, too - - - - - c52ab7d0 by Alan Zimmerman at 2017-11-14T23:14:26+02:00 Clean up use of PlaceHolder, to match TTG - - - - - 81cc9851 by Moritz Angermann at 2017-11-20T07:52:49+01:00 Declare use of `Paths_haddock` module in other-modules (#705) This was detected by `-Wmissing-home-modules` - - - - - f9d27598 by Moritz Angermann at 2017-11-20T12:47:34+01:00 Drop Paths_haddock from ghc.mk (#707) With haskell/haddock#705 and haskell/haddock#706, the custom addition should not be necessary any more. # Conflicts: # ghc.mk - - - - - f34818dc by Moritz Angermann at 2017-11-20T12:47:59+01:00 Add autogen-modules (#706) > Packages using 'cabal-version: >= 1.25' and the autogenerated module Paths_* must include it also on the 'autogen-modules' field besides 'exposed-modules' and 'other-modules'. This specifies that the module does not come with the package and is generated on setup. Modules built with a custom Setup.hs script also go here to ensure that commands like sdist don't fail. # Conflicts: # haddock.cabal - - - - - bb43a0aa by Ben Gamari at 2017-11-21T15:50:12-05:00 Revert "Clean up use of PlaceHolder, to match TTG" This reverts commit 134a7bb054ea730b13c8629a76232d73e3ace049. - - - - - af9ebb2b by Ben Gamari at 2017-11-21T15:50:14-05:00 Revert "Match Trees that Grow in GHC for HsExpr" This reverts commit 9f054dc365379c66668de6719840918190ae6e44. - - - - - 5d35c3af by Ben Gamari at 2017-11-21T15:50:15-05:00 Revert "Match Trees That Grow" This reverts commit 73a26af844ac50b8bec39de11d64452a6286b00c. - - - - - 99a8e43b by Ben Gamari at 2017-11-21T16:36:06-05:00 Revert "Match changes for Trees that Grow in GHC" This reverts commit 01eeeb048acd2dd05ff6471ae148a97cf0720547. - - - - - c4d650c2 by Ben Gamari at 2017-12-04T15:06:07-05:00 Bump GHC version - - - - - 027b2274 by Ben Gamari at 2017-12-04T17:06:31-05:00 Bump GHC bound to 8.4.* - - - - - 58eaf755 by Alex Biehl at 2017-12-06T15:44:24+01:00 Update changelog - - - - - d68f5584 by Simon Peyton Jones at 2017-12-07T14:39:56+00:00 Track changes to follow Trac haskell/haddock#14529 This tracks the refactoring of HsDecl.ConDecl. - - - - - dc519d6b by Alec Theriault at 2018-01-06T08:20:43-08:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - 8285118c by Alec Theriault at 2018-01-13T12:12:37+01:00 Constructor and pattern synonym argument docs (#709) * Support Haddocks on constructor arguments This is in conjunction with https://phabricator.haskell.org/D4094. Adds support for rendering Haddock's on (non-record) constructor arguments, both for regular and GADT constructors. * Support haddocks on pattern synonym arguments It appears that GHC already parsed these - we just weren't using them. In the process of doing this, I tried to deduplicate some code around handling patterns. * Update the markup guide Add some information about the new support for commenting constructor arguments, and mention pattern synonyms and GADT-style constructors. * Overhaul LaTeX support for data/pattern decls This includes at least * fixing several bugs that resulted in invalid LaTeX * fixing GADT data declaration headers * overhaul handling of record fields * overhaul handling of GADT constructors * overhaul handling of bundled patterns * add support for constructor argument docs * Support GADT record constructors This means changes what existing HTML docs look like. As for LaTeX, looks like GADT records were never even supported. Now they are. * Clean up code/comments Made code/comments consistent between the LaTeX and XHTML backend when possible. * Update changelog * Patch post-rebase regressions * Another post-rebase change We want return values to be documentable on record GADT constructors. - - - - - ca4fabb4 by Alec Theriault at 2018-01-15T17:12:18-08:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 4c472fea by Ryan Scott at 2018-01-19T10:44:02+01:00 Fix haskell/haddock#732 (#733) - - - - - bff14dbd by Alex Biehl at 2018-01-19T15:33:30+01:00 extractDecl: Extract associated types correctly (#736) - - - - - a2a94a73 by Alex Biehl at 2018-01-19T15:34:40+01:00 extractDecl: Extract associated types correctly (#736) - - - - - 26df93dc by Alex Biehl at 2018-01-20T10:18:22+01:00 haddock-api: bump ghc to ^>= 8.4 - - - - - f65aeb1d by Alex Biehl at 2018-01-20T19:18:20+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - 0e721b97 by Alex Biehl at 2018-01-20T19:20:19+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - cb6234f6 by Ben Gamari at 2018-01-26T13:40:55-05:00 Merge remote-tracking branch 'harpocrates/fix/missing-orphan-instances' into ghc-head - - - - - 0fc28554 by Alec Theriault at 2018-02-01T14:58:18+01:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - b9123772 by Alec Theriault at 2018-02-01T14:58:18+01:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 0c12e274 by Ryan Scott at 2018-02-01T14:58:18+01:00 Fix haskell/haddock#548 by rendering datatype kinds more carefully (#702) - - - - - 8876d20b by Alec Theriault at 2018-02-01T14:58:18+01:00 Use the GHC lexer for the Hyperlinker backend (#714) * Start changing to use GHC lexer * better cpp * Change SrcSpan to RealSrcSpan * Remove error * Try to stop too many open files * wip * wip * Revert "wip" This reverts commit b605510a195f26315e3d8ca90e6d95a6737553e1. Conflicts: haddock-api/haddock-api.cabal haddock-api/src/Haddock/Interface.hs * Remove pointless 'caching' * Use dlist rather than lists when finding vars * Use a map rather than list * Delete bogus comment * Rebase followup Things now run using the GHC lexer. There are still - stray debug statements - unnecessary changes w.r.t. master * Cleaned up differences w.r.t. current Haddock HEAD Things are looking good. quasiquotes in particular look beautiful: the TH ones (with Haskell source inside) colour/link their contents too! Haven't yet begun to check for possible performance problems. * Support CPP and top-level pragmas The support for these is hackier - but no more hacky than the existing support. * Tests pass, CPP is better recognized The tests were in some cases altered: I consider the new output to be more correct than the old one.... * Fix shrinking of source without tabs in test * Replace 'Position'/'Span' with GHC counterparts Replaces 'Position' -> 'GHC.RealSrcLoc' and 'Span' -> 'GHC.RealSrcSpan'. * Nits * Forgot entry in .cabal * Update changelog - - - - - 95c6a771 by Alec Theriault at 2018-02-01T14:58:18+01:00 Clickable anchors for headings (#716) See haskell/haddock#579. This just adds an <a> tag around the heading, pointing to the heading itself. - - - - - 21463d28 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump: Matches on function names weight more than matches in ... module names. - - - - - 8023af39 by Alex Biehl at 2018-02-01T14:58:18+01:00 Treat escaped \] better in definition lists (#717) This fixes haskell/haddock#546. - - - - - e4866dc1 by Alex Biehl at 2018-02-01T14:58:18+01:00 Remove scanner, takeWhile1_ already takes care of escaping - - - - - 9bcaa49d by Alex Biehl at 2018-02-01T14:58:18+01:00 Take until line feed - - - - - 01d2af93 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Add simple framework for running parser fixtures (#668) * Add simple framework for running parser fixtures * Compatible with tree-diff-0.0.0.1 * Use parseParas to parse fixtures This allows to test all syntactic constructs available in haddock markup. - - - - - 31128417 by Alec Theriault at 2018-02-01T14:58:18+01:00 Patch flaky parser test (#720) * Patch flaky parser test This test was a great idea, but it doesn't port over too well to using the GHC lexer. GHC rewrites its input a bit - nothing surprising, but we need to guard against those cases for the test. * Change instance head * Change use site - - - - - 9704f214 by Herbert Valerio Riedel at 2018-02-01T14:58:18+01:00 Include secondary LICENSE file in source dist - - - - - 51f25074 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Grid Tables (#718) * Add table examples * Add table types and adopt simple parser Simple parser is done by Giovanni Cappellotto (@potomak) in https://github.com/haskell/haddock/pull/577 It seems to support single fine full tables, so far from full RST-grid tables, but it's good start. Table type support row- and colspans, but obviously parser is lacking. Still TODO: - Latex backend. Should we use multirow package https://ctan.org/pkg/multirow?lang=en? - Hoogle backend: ? * Implement grid-tables * Refactor table parser * Add two ill-examples * Update CHANGES.md * Basic documentation for tables * Fix documentation example - - - - - 670d6200 by Alex Biehl at 2018-02-01T14:58:18+01:00 Add grid table example to cheatsheet (pdf and svg need to be regenerated thought) - - - - - 4262dec9 by Alec Theriault at 2018-02-01T14:58:18+01:00 Fix infinite loop when specializing instance heads (#723) * Fix infinite loop when specializing instance heads The bug can only be triggered from TH, hence why it went un-noticed for so long. * Add test for haskell/haddock#679 and haskell/haddock#710 - - - - - 67ecd803 by Alec Theriault at 2018-02-01T14:58:18+01:00 Filter RTS arguments from 'ghc-options' arguments (#725) This fixes haskell/haddock#666. - - - - - 7db26992 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump Scrollable overlay - - - - - da9ff634 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Hyperlinker: Adjust parser to new PFailed constructor - - - - - 7b7cf8cb by Alexander Biehl at 2018-02-01T14:58:18+01:00 Specialize: Add missing IdP annotations - - - - - 78cd7231 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Convert: Correct pass type - - - - - a2d0f590 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Warning free compilation - - - - - cd861cf3 by Alexander Biehl at 2018-02-01T14:58:18+01:00 hadock-2.19.0 / haddock-api-2.19.0 / haddock-library-1.5.0 - - - - - c6651b72 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Adjust changelogs - - - - - 1e93da0b by Alexander Biehl at 2018-02-01T14:58:18+01:00 haddock-library: Info about breaking changes - - - - - f9b11db8 by Alec Theriault at 2018-02-02T12:36:02+01:00 Properly color pragma contents in hyperlinker The hyperlinker backend now classifies the content of pragmas as 'TkPragma'. That means that in something like '{-# INLINE foo #-}', 'foo' still gets classified as a pragma token. - - - - - c40b0043 by Alec Theriault at 2018-02-02T12:36:02+01:00 Support the new 'ITcolumn_prag' token - - - - - 4a2a4d39 by Alex Biehl at 2018-02-03T12:11:55+01:00 QuickJump: Mitigate encoding problems on Windows - - - - - bb34503a by Alex Biehl at 2018-02-04T18:39:31+01:00 Use withBinaryFile - - - - - 637605bf by Herbert Valerio Riedel at 2018-02-05T09:48:32+01:00 Try GHC 8.4.1 for Travis CI job - - - - - 7abb67e4 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 try harder to build w/ GHC 8.4.1 - - - - - 8255cc98 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 Add `SPDX-License-Identifier` as alised for "license" module header tokens C.f. SPDX 2.1 - Appendix V https://spdx.org/spdx-specification-21-web-version#h.twlc0ztnng3b The tag should appear on its own line in the source file, generally as part of a comment. SPDX-License-Identifier: <SPDX License Expression> Cherry-picked from haskell/haddock#743 - - - - - 267cd23d by Herbert Valerio Riedel at 2018-02-05T10:24:34+01:00 Make test-suite SMP compatible - - - - - 95d4bf40 by Alec Theriault at 2018-02-05T22:01:04+01:00 Hyperlink pattern synonyms and 'module' imports (#744) Links to pattern synonyms are now generated, as well as links from modules in import lists. Fixes haskell/haddock#731. - - - - - 67838dcd by Alec Theriault at 2018-02-06T08:23:36+01:00 Don't warn about missing '~' (#746) This manually filters out '~' from the list of things to warn about. It truly makes no sense to warn on this since '~' has nothing it could link to - it is magical. This fixes haskell/haddock#532. - - - - - ab6c3f9f by Alec Theriault at 2018-02-06T08:24:47+01:00 Don't barf on 'HsSpliceTy' (#745) This handles 'HsSpliceTy's by replacing them with what they expand to. IIUC everything that is happening, 'renameHsSpliceTy' should not be able to fail for the inputs we feed it from GHC. This fixes haskell/haddock#574. - - - - - 92bf95ad by Alex Biehl at 2018-02-06T08:28:23+01:00 Rename: renameHsSpliceTy ttg - - - - - 3130b1e1 by Alex Biehl at 2018-02-06T09:02:14+01:00 Expand SigDs - - - - - c72adae5 by Alex Biehl at 2018-02-06T09:20:51+01:00 fullModuleContents: support named docs - - - - - de2e4dbf by Alex Biehl at 2018-02-06T13:56:17+01:00 Hyperlinker: Also link pattern synonym arguments - - - - - b7c98237 by Alex Biehl at 2018-02-09T18:44:23+01:00 Expand SigD in a better place In https://github.com/haskell/haddock/issues/287 we found that haddock-2.19.0 would miss documentation on class methods with multiples names. This patch uses expandSigDecls in a more sensible place. - - - - - 8f598b27 by Alec Theriault at 2018-02-11T12:29:56+01:00 Add module tooltips to linked identifiers (#753) No more clicking to figure out whether your bytestring is strict or lazy! - - - - - d812e65d by Alec Theriault at 2018-02-11T12:31:44+01:00 Add 'show' option to complement 'hide' (#752) * Add 'show' option to complement 'hide' The behaviour is for flags passed in the command line to override flags in file headers. In the command line, later flags override earlier ones. Fixes haskell/haddock#751 and haskell/haddock#266. * Add a '--show-all' option - - - - - 6676cecb by Alex Biehl at 2018-02-18T11:07:15-05:00 QuickJump: Mitigate encoding problems on Windows (cherry picked from commit 86292c54bfee2343aee84559ec01f1fc68f52231) - - - - - e753dd88 by Alex Biehl at 2018-02-18T17:59:54+01:00 Use withBinaryFile - - - - - 724dc881 by Tamar Christina at 2018-02-19T05:34:49+01:00 Haddock: support splitted include paths. (#689) - - - - - 9b6d6f50 by Alex Biehl at 2018-02-19T05:57:02+01:00 Teach the HTML backend how to render methods with multiple names - - - - - a74aa754 by Alexander Biehl at 2018-02-19T10:04:34+01:00 Hoogle/Latex: Remove use of partial function - - - - - 66d8bb0e by Alec Theriault at 2018-02-25T16:04:01+01:00 Fix file handle leak (#763) (#764) Brought back some mistakenly deleted code for handling encoding and eager reading of files from e0ada1743cb722d2f82498a95b201f3ffb303137. - - - - - bb92d03d by Alex Biehl at 2018-03-02T14:21:23+01:00 Enable running test suite with stock haddock and ghc using ``` $ cabal new-run -- html-test --haddock-path=$(which haddock) --ghc-path=$(which ghc) ``` - - - - - dddb3cb2 by Alex Biehl at 2018-03-02T15:43:21+01:00 Make testsuite work with haddock-1.19.0 release (#766) - - - - - f38636ed by Alec Theriault at 2018-03-02T15:48:36+01:00 Support unicode operators, proper modules Unicode operators are a pretty big thing in Haskell, so supporting linking them seems like it outweighs the cost of the extra machinery to force Attoparsec to look for unicode. Fixes haskell/haddock#458. - - - - - 09d89f7c by Alec Theriault at 2018-03-02T15:48:43+01:00 Remove bang pattern - - - - - d150a687 by Alex Biehl at 2018-03-02T15:48:48+01:00 fix test - - - - - d6fd71a5 by Alex Biehl at 2018-03-02T16:22:38+01:00 haddock-test: Be more explicit which packages to pass We now pass `-hide-all-packages` to haddock when invoking the testsuite. This ensures we don't accidentally pick up any dependencies up through ghc.env files. - - - - - 0932c78c by Alex Biehl at 2018-03-02T17:50:38+01:00 Revert "fix test" This reverts commit 1ac2f9569242f6cb074ba6e577285a4c33ae1197. - - - - - 52516029 by Alex Biehl at 2018-03-02T18:16:50+01:00 Fix Bug548 for real - - - - - 89df9eb5 by Alex Biehl at 2018-03-05T18:28:19+01:00 Hyperlinker: Links for TyOps, class methods and associated types - - - - - d019a4cb by Ryan Scott at 2018-03-06T13:43:56-05:00 Updates for haskell/haddock#13324 - - - - - 6d5a42ce by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump haddock-2.19.0.1, haddock-api-2.19.0.1, haddock-library-1.5.0.1 - - - - - c0e6f380 by Alex Biehl at 2018-03-10T18:25:57+01:00 Update changelogs for haddock-2.19.0.1 and haddock-library-1.5.0.1 - - - - - 500da489 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Update to QC 2.11 - - - - - ce8362e9 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Restore backward-compat with base-4.5 through base-4.8 - - - - - baae4435 by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump lower bound for haddock-library - - - - - 10b7a73e by Alex Biehl at 2018-03-10T18:25:57+01:00 Haddock: Straighten out base bound - - - - - a6096f7b by Alex Biehl at 2018-03-13T08:45:06+01:00 extractDecl: Extract constructor patterns from data family instances (#776) * extractDecl: Allow extraction of data family instance constructors * extractDecl: extract data family instance constructors - - - - - ba4a0744 by Simon Jakobi at 2018-03-14T08:26:42+01:00 Readme: Update GHC version (#778) - - - - - 8de157d4 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for definition lists - - - - - 425b46f9 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for links - - - - - d53945d8 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for inline links - - - - - f1dc7c99 by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Slightly unmangle output - - - - - 0879d31c by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Prevent stdout buffering - - - - - 1f9e5f1b by Simon Jakobi at 2018-03-14T20:39:29+01:00 haddock-library.cabal: Clean up GHC options - - - - - 066b891a by Simon Jakobi at 2018-03-14T20:39:29+01:00 Make a proper definition for the <link> parser - - - - - 573d6ba7 by Alec Theriault at 2018-03-21T09:16:57+01:00 Show where instances are defined (#748) * Indicate source module of instances Above instance, we now also display a link to the module where the instance was defined. This is sometimes helpful in figuring out what to import. * Source module for type/data families too * Remove parens * Accept tests - - - - - 99b5d28b by Alex Biehl at 2018-03-21T09:20:36+01:00 Prepare changelog for next release - - - - - 482d3a93 by Alex Biehl at 2018-03-23T15:57:36+01:00 Useful cost centres, timers and allocation counters (#785) * Add some useful cost-centres for profiling * Add withTiming for each haddock phase Invoking haddock with `--optghc=-ddump-timings` now shows the amount of time spent and the number of allocated bytes for each phase. - - - - - 773b41bb by Alec Theriault at 2018-03-27T08:35:59+02:00 @since includes package name (#749) * Metadoc stores a package name This means that '@since' annotations can be package aware. * Get the package name the right way This should extract the package name for `@since` annotations the right way. I had to move `modulePackageInfo` around to do this and, in the process, I took the liberty to update it. Since it appears that finding the package name is something that can fail, I added a warning for this case. * Silence warnings * Hide package for local 'since' annotations As discussed, this is still the usual case (and we should avoid being noisy for it). Although this commit is large, it is basically only about threading a 'Maybe Package' from 'Haddock.render' all the way to 'Haddock.Backends.Xhtml.DocMarkup.renderMeta'. * Bump binary interface version * Add a '--since-qual' option This controls when to qualify since annotations with the package they come from. The default is always, but I've left an 'external' variant where only those annotations coming from outside of the current package are qualified. * Make ParserSpec work * Make Fixtures work * Use package name even if package version is not available The @since stuff needs only the package name passed in, so it makes sense to not be forced to pass in a version too. - - - - - e42c57bc by Alex Biehl at 2018-03-27T08:42:50+02:00 haddock-2.19.1, haddock-api-2.19.1, haddock-library-1.6.0 - - - - - 8373a529 by Alex Biehl at 2018-03-28T10:17:11+02:00 Bump haddock and haddock-api to 2.20.0 - - - - - 5038eddd by Jack Henahan at 2018-04-03T13:28:12+02:00 Clear search string on hide for haskell/haddock#781 (#789) - - - - - 920ca1eb by Alex Biehl at 2018-04-03T16:35:50+02:00 Travis: Build with ghc-8.4.2 (#793) - - - - - a232f0eb by Alan Zimmerman at 2018-04-07T14:14:32+02:00 Match changes in GHC for D4199 Removing HasSourceText and SourceTextX classes. - - - - - ab85060b by Alan Zimmerman at 2018-04-09T21:20:24+02:00 Match GHC changes for TTG - - - - - 739302b6 by Alan Zimmerman at 2018-04-13T13:31:44+02:00 Match GHC for TTG implemented on HsBinds, D4581 - - - - - 2f56d3cb by Ryan Scott at 2018-04-19T11:42:58-04:00 Bump upper bound on base to < 4.13 See https://ghc.haskell.org/trac/ghc/ticket/15018. - - - - - a49df92a by Alex Biehl at 2018-04-20T07:31:44+02:00 Don't treat fixity signatures like declarations - - - - - d02c103b by Ryan Scott at 2018-04-24T11:20:11-04:00 Add regression test for haskell/haddock#413 Fixes haskell/haddock#413. - - - - - c7577f52 by Ryan Scott at 2018-04-24T13:51:06-07:00 Improve the Hoogle backend's treatment of type families (#808) Fixes parts 1 and 2 of haskell/haddock#806. - - - - - d88f85b1 by Alec Theriault at 2018-04-25T11:24:07-07:00 Replace 'attoparsec' with 'parsec' (#799) * Remove attoparsec with parsec and start fixing failed parses * Make tests pass * Fix encoding issues The Haddock parser no longer needs to worry about bytestrings. All the internal parsing work in haddock-library happens over 'Text'. * Remove attoparsec vendor * Fix stuff broken in 'attoparsec' -> 'parsec' * hyperlinks * codeblocks * examples Pretty much all issues are due to attoparsec's backtracking failure behaviour vs. parsec's non-backtracking failure behaviour. * Fix small TODOs * Missing quote + Haddocks * Better handle spaces before/after paragraphs * Address review comments - - - - - fc25e2fe by Alan Zimmerman at 2018-04-27T15:36:53+02:00 Match changes in GHC for TTG - - - - - 06175f91 by Herbert Valerio Riedel at 2018-05-01T18:11:09+02:00 Merge branch 'ghc-head' with 'ghc-8.4' - - - - - 879caaa8 by Alec Theriault at 2018-05-07T18:53:15-07:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 3e0120cb by Simon Jakobi at 2018-05-07T19:00:18-07:00 Add docs for some DocH constructors (#814) - - - - - 0a32c6db by Alec Theriault at 2018-05-08T02:15:45-07:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 8816e783 by Simon Jakobi at 2018-05-08T10:48:11-07:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - ad60366f by Ryan Scott at 2018-05-10T11:19:47-04:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - 03b7cc3b by Ryan Scott at 2018-05-10T11:24:38-04:00 Wibbles - - - - - b03dd563 by Chaitanya Koparkar at 2018-05-10T11:44:58-04:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 9f298a40 by Ben Gamari at 2018-05-13T17:36:04-04:00 Account for refactoring of LitString - - - - - ea3dabe7 by Ryan Scott at 2018-05-16T09:21:43-04:00 Merge pull request haskell/haddock#826 from haskell/T825 Remove Hoogle backend hack that butchers infix datatype names - - - - - 0d234f7c by Alec Theriault at 2018-05-23T11:29:05+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 15fc9712 by Simon Jakobi at 2018-05-31T04:17:47+02:00 Adjust to new HsDocString internals - - - - - 6f1e19a8 by Ben Gamari at 2018-06-02T16:18:58-04:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 0d0355d9 by Ryan Scott at 2018-06-04T21:26:59-04:00 DerivingVia changes - - - - - 0d93475a by Simon Jakobi at 2018-06-05T19:47:05+02:00 Bump a few dependency bounds (#845) - - - - - 5cbef804 by Alec Theriault at 2018-06-05T19:47:16+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 9094c56f by Alec Theriault at 2018-06-05T22:53:25+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 70188719 by Simon Jakobi at 2018-06-08T22:20:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - 495cd1fc by Chaitanya Koparkar at 2018-06-13T23:01:34+02:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 81088732 by Ben Gamari at 2018-06-13T23:01:34+02:00 Account for refactoring of LitString - - - - - 7baf6587 by Simon Jakobi at 2018-06-13T23:05:08+02:00 Adjust to new HsDocString internals - - - - - bb61464d by Ben Gamari at 2018-06-13T23:05:22+02:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 5d8cb87f by Ryan Scott at 2018-06-13T23:39:30+02:00 DerivingVia changes - - - - - 73d373a3 by Alec Theriault at 2018-06-13T23:39:30+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 4865e254 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Remove `ITtildehsh` token - - - - - b867db54 by Alec Theriault at 2018-06-13T23:39:30+02:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 9598e392 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Add docs for some DocH constructors (#814) - - - - - 8a59035b by Alec Theriault at 2018-06-13T23:39:30+02:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 29350fc8 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - 2590bbd9 by Ryan Scott at 2018-06-13T23:39:30+02:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - a9939fdc by Ryan Scott at 2018-06-13T23:39:30+02:00 Wibbles - - - - - a22f7df4 by Alec Theriault at 2018-06-13T23:39:30+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 8741015d by Simon Jakobi at 2018-06-13T23:39:30+02:00 Bump a few dependency bounds (#845) - - - - - 4791e1cc by Alec Theriault at 2018-06-13T23:39:30+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 311d3216 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - d0577817 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Complete FixitySig and FamilyDecl pattern matches - - - - - 055b3aa7 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Fix redundant import warnings - - - - - f9ce19b1 by Simon Jakobi at 2018-06-13T23:49:52+02:00 html-test: Accept output - - - - - 04604ea7 by Simon Jakobi at 2018-06-13T23:54:37+02:00 Bump bounds on Cabal - - - - - 0713b692 by Simon Jakobi at 2018-06-14T00:00:12+02:00 Merge branch 'ghc-head' into ghc-head-update-3 - - - - - c6a56bfd by Simon Jakobi at 2018-06-14T02:33:27+02:00 Bump ghc bound for haddock-api spec test-suite - - - - - 119d04b2 by Simon Jakobi at 2018-06-14T12:37:48+02:00 Travis: `--allow-newer` for all packages - - - - - 0e876e2c by Alex Biehl at 2018-06-14T15:28:52+02:00 Merge pull request haskell/haddock#857 from sjakobi/ghc-head-update-3 Update ghc-head - - - - - 5be46454 by Alec Theriault at 2018-06-14T21:42:45+02:00 Improved handling of interfaces in 'haddock-test' (#851) This should now work with an inplace GHC where (for instance) HTML directories may not be properly recorded in the package DB. - - - - - 96ab1387 by Vladislav Zavialov at 2018-06-14T17:06:21-04:00 Handle -XStarIsType - - - - - e518f8c4 by Ben Gamari at 2018-06-14T17:48:00-04:00 Revert unintentional reversion of fix of haskell/haddock#548 - - - - - 01b9f96d by Alan Zimmerman at 2018-06-19T11:52:22+02:00 Match changes in GHC for haskell/haddock#14259 - - - - - 7f8c8298 by Ben Gamari at 2018-06-19T18:14:27-04:00 Bump GHC version to 8.6 - - - - - 11c6b5d2 by Ryan Scott at 2018-06-19T23:17:31-04:00 Remove HsEqTy and XEqTy - - - - - b33347c2 by Herbert Valerio Riedel at 2018-06-20T23:14:52+02:00 Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. - - - - - f0d2460e by Herbert Valerio Riedel at 2018-06-20T23:28:46+02:00 Update Travis CI job - - - - - ef239223 by Herbert Valerio Riedel at 2018-06-20T23:32:41+02:00 Drop GHC HEAD from CI and update GHC to 8.4.3 It's a waste of resource to even try to build this branch w/ ghc-head; so let's not do that... - - - - - 41c4a9fa by Ben Gamari at 2018-06-20T18:26:20-04:00 Bump GHC version to 8.7 - - - - - 8be593dc by Herbert Valerio Riedel at 2018-06-21T22:32:15+02:00 Update CI job to use GHC 8.7.* - - - - - b91d334a by Simon Jakobi at 2018-06-30T13:41:38+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section - - - - - f707d848 by Alec Theriault at 2018-07-05T10:43:35-04:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. - - - - - a6d2b8dc by Alec Theriault at 2018-07-06T10:06:32-04:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case - - - - - 13819f71 by Alan Zimmerman at 2018-07-15T19:33:51+02:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 - - - - - c346aa78 by Simon Jakobi at 2018-07-19T12:29:32+02:00 haddock-library: Bump bounds for containers - - - - - 722e733c by Simon Jakobi at 2018-07-19T13:36:45+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] - - - - - f0bd83fd by Alec Theriault at 2018-07-19T14:39:57+02:00 Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. - - - - - 394053a8 by Simon Jakobi at 2018-07-19T14:58:07+02:00 haddock-library: Bump bounds for containers - - - - - 1bda11a2 by Alec Theriault at 2018-07-20T09:04:03+02:00 Add HEAD.hackage overlay (#887) * Add HEAD.hackage overlay * Add HCPKG variable - - - - - c7b4ab45 by Alec Theriault at 2018-07-20T12:01:16+02:00 Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test - - - - - c05d32ad by Alec Theriault at 2018-07-20T12:01:49+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output - - - - - 24b39ee4 by Alec Theriault at 2018-07-20T12:02:16+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. - - - - - cb9d2099 by Simon Jakobi at 2018-07-20T13:39:29+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) - - - - - 133f24f5 by Alec Theriault at 2018-07-20T13:39:29+02:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) - - - - - 11024149 by Alec Theriault at 2018-07-20T13:39:29+02:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) - - - - - de0c139e by Simon Jakobi at 2018-07-20T13:39:29+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) - - - - - 6435e952 by Alec Theriault at 2018-07-20T13:39:29+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) - - - - - 1461af39 by Alec Theriault at 2018-07-20T13:39:29+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) - - - - - 69d3bde1 by Alec Theriault at 2018-07-20T13:49:47+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) - - - - - 6a5c73c7 by Alec Theriault at 2018-07-20T13:50:00+02:00 Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests - - - - - 92ca94c6 by Alec Theriault at 2018-07-20T13:55:36+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) - - - - - 981bc7fa by Simon Jakobi at 2018-07-20T15:06:06+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers - - - - - 27e7c0c5 by Simon Jakobi at 2018-07-20T15:09:05+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 49e1a415 by Simon Jakobi at 2018-07-20T16:02:02+02:00 Update the ghc-8.6 branch (#889) * Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. * README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) * Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) * Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) * tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) * Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. * Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test * Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) * Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) * Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) * Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests * Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 5ca14bed by Simon Jakobi at 2018-07-20T16:05:47+02:00 Revert "Revert "Bump GHC version to 8.6"" That commit didn't belong onto the ghc-8.6 branch. This reverts commit acbaef3b9daf1d2dea10017964bf886e77a8e967. - - - - - 2dd600dd by Simon Jakobi at 2018-07-20T16:18:21+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. - - - - - fceb2422 by Simon Jakobi at 2018-07-20T16:18:21+02:00 outOfScope: Recommend qualifying the identifier - - - - - acea5d23 by Simon Jakobi at 2018-07-20T16:19:35+02:00 outOfScope: Recommend qualifying the identifier (cherry picked from commit 73707ed58d879cc04cb644c5dab88c39ca1465b7) - - - - - 1a83ca55 by Simon Jakobi at 2018-07-20T16:19:35+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. (cherry picked from commit d504a2864a4e1982e142cf88c023e7caeea3b76f) - - - - - 48374451 by Masahiro Sakai at 2018-07-20T17:06:42+02:00 Add # as a special character (#884) '#' has special meaning used for anchors and can be escaped using backslash. Therefore it would be nice to be listed as special characters. - - - - - 5e1a5275 by Alec Theriault at 2018-07-20T23:37:24+02:00 Let `haddock-test` bypass interface version check (#890) This means `haddock-test` might * crash during deserialization * deserialize incorrectly Still - it means things _might_ work where they were previously sure not to. - - - - - 27286754 by Yuji Yamamoto at 2018-07-23T08:16:01+02:00 Avoid "invalid argument (invalid character)" on non-unicode Windows (#892) Steps to reproduce and the error message ==== ``` > stack haddock basement ... snip ... Warning: 'A' is out of scope. Warning: 'haddock: internal error: <stdout>: commitBuffer: invalid argument (invalid character) ``` Environment ==== OS: Windows 10 ver. 1709 haddock: [HEAD of ghc-8.4 when I reproduce the error](https://github.com/haskell/haddock/commit/532b209d127e4cecdbf7e9e3dcf4f653a5605b5a). (I had to use this version to avoid another probrem already fixed in HEAD) GHC: 8.4.3 stack: Version 1.7.1, Git revision 681c800873816c022739ca7ed14755e85a579565 (5807 commits) x86_64 hpack-0.28.2 Related pull request ==== https://github.com/haskell/haddock/pull/566 - - - - - 6729d361 by Alec Theriault at 2018-07-23T13:52:56-07:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). - - - - - 8cf4e6b5 by Ryan Scott at 2018-07-27T11:28:03-04:00 eqTyCon_RDR now lives in TysWiredIn After GHC commit http://git.haskell.org/ghc.git/commit/f265008fb6f70830e7e92ce563f6d83833cef071 - - - - - 1ad251a6 by Alan Zimmerman at 2018-07-30T13:28:09-04:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 (cherry picked from commit e3926b50ab8a7269fd6904b06e881745f08bc5d6) - - - - - 8aea2492 by Richard Eisenberg at 2018-08-02T10:54:17-04:00 Update against new HsImplicitBndrs - - - - - e42cada9 by Alec Theriault at 2018-08-04T17:51:30+02:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 0e852512 by Alex Biehl at 2018-08-06T13:04:02+02:00 Make --package-version optional for --hoogle generation (#899) * Make --package-version optional for --hoogle generation * Import mkVersion * It's makeVersion not mkVersion - - - - - d2abd684 by Noel Bourke at 2018-08-21T09:34:18+02:00 Remove unnecessary backslashes from docs (#908) On https://haskell-haddock.readthedocs.io/en/latest/markup.html#special-characters the backslash and backtick special characters showed up with an extra backslash before them – I think the escaping is not (or no longer) needed for those characters in rst. - - - - - 7a578a9e by Matthew Pickering at 2018-08-21T09:34:50+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - aa3d4db3 by Matthew Pickering at 2018-08-21T09:37:34+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - ede91744 by Alec Theriault at 2018-08-21T09:42:52+02:00 Better test output when Haddock crashes on a test (#902) In particular: we report the tests that crashed seperately from the tests that produced incorrect output. In order for tests to pass (and exit 0), they must not crash and must produce the right output. - - - - - 4a872b84 by Guillaume Bouchard at 2018-08-21T09:45:57+02:00 Fix a typo (#878) - - - - - 4dbf7595 by Ben Sklaroff at 2018-08-21T12:04:09-04:00 Add ITcomment_line_prag token to Hyperlinker Parser This token is necessary for parsing #line pragmas inside nested comments. Reviewers: bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D4935 - - - - - 9170b2a9 by Ben Gamari at 2018-08-21T17:55:15-04:00 Merge pull request haskell/haddock#893 from harpocrates/get-name-to-instances Accumulate explicitly which modules to load for 'attachInstances' - - - - - d57b57cc by Ben Gamari at 2018-08-21T17:59:13-04:00 Merge branch 'ghc-head' of github.com:haskell/haddock into ghc-head - - - - - 14601ca2 by Alec Theriault at 2018-08-21T19:09:37-04:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). (cherry picked from commit 5c7c596c51d69b92164e9ba920157b36ce2b2ec1) - - - - - 438c645e by Matthew Pickering at 2018-08-21T19:12:39-04:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 (cherry picked from commit e6aa8fb47b9477cc5ef5e46097524fe83e080f6d) - - - - - a80c5161 by Alec Theriault at 2018-08-21T22:06:40-07:00 Better rendering of unboxed sums/tuples * adds space after/before the '#' marks * properly reify 'HsSumTy' in 'synifyType' - - - - - 88456cc1 by Alec Theriault at 2018-08-21T22:06:40-07:00 Handle promoted tuples in 'synifyType' When we have a fully applied promoted tuple, we can expand it out properly. - - - - - fd1c1094 by Alec Theriault at 2018-08-21T22:19:34-07:00 Accept test cases - - - - - 6e80d9e0 by Alec Theriault at 2018-08-21T22:24:03-07:00 Merge pull request haskell/haddock#914 from harpocrates/feature/unboxed-stuff Better rendering of unboxed sums, unboxed tuples, promoted tuples. - - - - - 181a23f1 by Ben Gamari at 2018-08-23T15:53:48-04:00 Merge remote-tracking branch 'origin/ghc-8.6' into ghc-8.6 - - - - - 3a18c1d8 by Alec Theriault at 2018-08-27T14:15:25-07:00 Properly synify promoted list types We reconstruct promoted list literals whenever possible. That means that 'synifyType' produces '[Int, Bool, ()] instead of (Int ': (() ': (Bool ': ([] :: [Type])))) - - - - - b4794946 by Alec Theriault at 2018-09-03T07:19:55-07:00 Only look at visible types when synifying a 'HsListTy' The other types are still looked at when considering whether to make a kind signature or not. - - - - - a231fce2 by Alec Theriault at 2018-09-03T07:38:10-07:00 Merge pull request haskell/haddock#922 from harpocrates/promoted-lists Properly synify promoted list types - - - - - 0fdf044e by Ningning Xie at 2018-09-15T10:25:58-04:00 Update according to GHC Core changes - - - - - 7379b115 by Ningning Xie at 2018-09-15T15:40:18-04:00 update dataFullSig to work with Co Quantification This should have been in the previous patch, but wasn't. - - - - - cf84a046 by Alec Theriault at 2018-09-17T20:12:18-07:00 Fix/add to various docs * Add documentation for a bunch of previously undocumented options (fixes haskell/haddock#870) * Extend the documentation of `--hoogle` considerably (see haskell/haddock#807) * Describe how to add docs to `deriving` clauses (fixes haskell/haddock#912) * Fix inaccurate docs about hyperlinking infix identifiers (fixes haskell/haddock#780) - - - - - ae017935 by Alec Theriault at 2018-09-22T08:32:16-07:00 Update Travis - - - - - d95ae753 by Alec Theriault at 2018-09-22T09:34:10-07:00 Accept failing tests Also silence orphan warnings. - - - - - f3e67024 by Alec Theriault at 2018-09-22T09:41:23-07:00 Bump haddock-api-2.21.0, haddock-library-1.7.0 * Update CHANGELOGS * Update new versions in Cabal files * Purge references to ghc-8.4/master branches in README - - - - - 3f136d4a by Alec Theriault at 2018-09-22T10:53:31-07:00 Turn haddock-library into a minor release Fix some version bounds in haddock-library too. - - - - - b9def006 by Alec Theriault at 2018-09-22T13:07:35-07:00 keep cabal.project file - - - - - 4909aca7 by Alec Theriault at 2018-10-16T09:36:30-07:00 Build on 7.4 and 7.8 - - - - - 99d20a28 by Herbert Valerio Riedel at 2018-10-16T18:45:52+02:00 Minor tweak to package description - - - - - a8059618 by Herbert Valerio Riedel at 2018-10-16T18:47:24+02:00 Merge pull request haskell/haddock#945 haddock-api 2.21.0 and haddock-library 1.6.1 release - - - - - 2d9bdfc1 by Alec Theriault at 2018-10-16T10:54:21-07:00 Bump haddock-library to 1.7.0 The 1.6.1 release should've been a major bump, since types in the `Documentation.Haddock.Parser.Monad` module changed. This version makes that module internal (as it morally should be). - - - - - ed340cef by Alec Theriault at 2018-10-16T14:59:13-07:00 Merge branch 'ghc-8.4' into ghc-8.6 - - - - - 2821a8df by Alec Theriault at 2018-10-16T15:14:48-07:00 Merge branch 'ghc-8.6' into ghc-head - - - - - a722dc84 by Alec Theriault at 2018-10-16T16:28:55-07:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 63377496 by Alec Theriault at 2018-10-16T16:39:07-07:00 Update changelog - - - - - 099a0110 by Alec Theriault at 2018-10-16T16:49:28-07:00 Merge pull request haskell/haddock#942 from harpocrates/update-docs Fix & add to documentation - - - - - 0927416f by Alec Theriault at 2018-10-16T16:50:14-07:00 Set UTF-8 encoding before writing files (#934) This should fix haskell/haddock#929, as well as guard against future problems of this sort in other places. Basically replaces 'writeFile' (which selects the users default locale) with 'writeUtf8File' (which always uses utf8). - - - - - 83b7b017 by Alec Theriault at 2018-10-16T17:42:05-07:00 Output pattern synonyms in Hoogle backend (#947) * Output pattern synonyms in Hoogle backend We were previously weren't outputting _any_ pattern synonyms, bundled or not. Now, we output both. Fixes haskell/haddock#946. * Update changelog - - - - - 81e5033d by Alec Theriault at 2018-10-16T18:04:40-07:00 Release `haddock{,-api}-2.22.0` This version will accompany ghc-8.6.2 - - - - - 9661744e by Alex Biehl at 2018-10-18T08:14:32-07:00 Add NewOcean theme And make it the default theme. - - - - - 7ae6d722 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Improve appearance and readability These changes include: - use latest Haskell's logo colors - decrease #content width to improve readability - use nicer font - improve sizes and distances - - - - - 37f8703d by NunoAlexandre at 2018-10-18T08:14:32-07:00 Include custom font in the html head - - - - - 1d5e1d79 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Update html test reference files - - - - - 53b7651f by NunoAlexandre at 2018-10-18T08:14:32-07:00 Make it responsive - It makes small screens taking more space than larger ones - fixes a few issues present in small screens currently - make it look good across different screen sizes. - - - - - 6aa1aeb1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make the style consistent with hackage Several things are addressed here: - better responsive behaviour on the header - better space usage - consistent colors overall - other nit PR comments - - - - - 3a250c5c by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Place the package name before the menu links This supports the expected responsive menu design, where the package name appears above the menu links. - - - - - cae699b3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update html-test reference files The package name element in the package-header is now a div instead of a paragraph, and it is now above the menu ul.links instead of below. - - - - - 2ec7fd2d by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve synopsis style and code - Use CSS3 instead of loading pictures to show "+" and "-" symbols - Drop redundant code - - - - - 0c874c01 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Decrease space between code blocks There was too much space between code blocks as pointed out by reviewers. - - - - - 85568ce2 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Add an initial-scale property to all haddock pages This solves an issue reported about the content looking incredibly small on mobile devices. - - - - - c1538926 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Address several PR comments - Darken text color like done for hackage - Move synopsis to left side - Make table of contents stick to the left on wide screens - Wrap links to avoid page overflow - Improve expand/collapse buttons - Fix issue with content size on mobile devices - Fix issue with font-size on landscape mode - Increase width of the content - Change colors of table of contents and synopsis - Etc - - - - - e6639e5f by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make synopsis scrollable on wide screens When the synopsis is longer than the screen, you can’t see its end and you can't scroll down either, making the content unreachable. - - - - - 1f0591ff by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve information density - Reduce font size - Improve space between and within code blocks - Improve alignments - Improve spacing within sub-blocks - - - - - bf083097 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Minor adjustments Bring in some adjustments made to hackage: - link colors - page header show everything when package title is too long - - - - - 10375fc7 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix responsive triggers overlap issue The min and max width triggers have the same values, which caused the style resolution to take an intersection of both style declarations when the screen resolution had the size of the limts (say 1280px), causing an odd behaviour and look. - - - - - 95ff2f95 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix issue with menu alignment on firefox Reported and described here: https://github.com/haskell/haddock/pull/721#issuecomment-374668869 - - - - - dc86587e by Alex Biehl at 2018-10-18T08:14:32-07:00 Changelog entry for NewOcean - - - - - 27195e47 by Herbert Valerio Riedel at 2018-10-18T08:14:32-07:00 html-test --accept - - - - - 83f4f9c0 by Alex Biehl at 2018-10-18T08:14:32-07:00 Avoid name shadowing - - - - - 231487f1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font to PT Sans Also migrate some general text related changes from hackage. - - - - - 313db81a by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Use 'flex' to fix header alignment - - - - - 5087367b by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Misc of tweaks - Update link colors to hackage scheme - Tune spacing between content elements - Update footer style - Fix and improve code blocks identation - - - - - b08020df by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font in Xhtml.hs to PT Sans - - - - - 78ce06e3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve code blocks styling - Fix and improve spacing - Improve colors and borders - - - - - 81262d20 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make package-header caption backward-compatible The current html generator of this branch wraps the package-header caption as a div, which does not work (without style adjustments) with the old themes. Changing it from div to span does the trick, without needing to adjust the old stylesheets. - - - - - dc4475cb by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update test-suite reference html pages - - - - - 393d35d8 by Alec Theriault at 2018-10-18T08:25:36-07:00 Accept tests - - - - - a94484ba by Alec Theriault at 2018-10-21T10:29:29-07:00 Fix CHANGELOG - - - - - 8797eca3 by Alec Theriault at 2018-10-21T10:36:19-07:00 Update 'data-files' to include NewOcean stuff - - - - - 1ae51e4a by Simon Jakobi at 2018-10-23T11:29:14+02:00 Fix typo in a warning - - - - - 009ad8e8 by Alec Theriault at 2018-10-24T12:47:47-07:00 Update JS dependencies This was done via `npm audit fix`. I think this fixes haskell/haddock#903 along with some more serious vulnerabilities that nobody seems to have noticed. - - - - - 051994db by Alec Theriault at 2018-10-24T17:31:09-07:00 Resurrect the style-switcher This fixes haskell/haddock#810. Looks like things were broken during the quickjump refactor of the JS. For the (git) record: I do not think the style switcher is a good idea. I'm fixing it for the same reason @mzero added it; as an answer to "rumblings from some that they didn't want their pixels changed on bit" - - - - - 2a1d620f by Alec Theriault at 2018-10-24T17:38:07-07:00 Fix copy-pasta error in data-files - - - - - ed5bfb7f by Alec Theriault at 2018-10-24T20:42:14-07:00 Fix the synopsis button Here's these changes are supposed to do: * put the synopsis back on the right side * properly have it on the edge of the screen on wide screens * adjust the background of the synopsis to match the button (otherwise the grey blends in with what is underneath) * get rid of the dotted purple line * the synopsis contents are now scrollable even when in wide screens (this has been a long-standing bug) - - - - - 883fd74b by Alec Theriault at 2018-10-25T20:16:46-07:00 Avoid more conflicts in generated ids (#954) This fixes haskell/haddock#953 by passing more names into the generated ids. - - - - - ea54e331 by Alec Theriault at 2018-10-25T21:07:12-07:00 Don't hide bullets in method docs I think thst CSS was meant only to deal with fields and the effect on bullets was accidental. Fixes haskell/haddock#926. - - - - - 9a14ef4a by Alec Theriault at 2018-10-25T22:02:07-07:00 Indent more things + slightly smaller font - - - - - b9f17e29 by Alec Theriault at 2018-10-25T22:10:01-07:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 096a3cfa by Alec Theriault at 2018-10-25T22:24:38-07:00 Accept HTML output - - - - - 2669517d by Alec Theriault at 2018-10-26T09:02:35-07:00 User manual + stuff for building GHC docs - - - - - 46b27687 by Alec Theriault at 2018-10-26T09:10:59-07:00 Make 'Contents' in NewOcean scrollable This only happens if the contents block on the left is so big that it doesn't fit (vertically) on the page. If that happens, we want it to be scrollable. - - - - - 3443dd94 by Alec Theriault at 2018-10-26T09:36:46-07:00 Revert "Make 'Contents' in NewOcean scrollable" This reverts commit f909ffd8353d6463fd5dd184998a32aa98d5c922. I missed the fact this also forces the 'Contents' to always go down to the bottom of the page. - - - - - ed081424 by Alec Theriault at 2018-10-26T14:22:23-07:00 Avoid some partiality AFAICT this wasn't causing any crashes, but that's mostly because we happen not to be forcing `pkgStr` when it would diverge. We come dangerously close to doing that in `ppHtmlIndex`. Fixes haskell/haddock#569. - - - - - 6a5bec41 by Alec Theriault at 2018-10-27T10:05:04-07:00 Fix documentation in `haddock-api` (#957) * Fix misplaced Haddocks in Haddock itself Haddock should be able to generate documentation for 'haddock-api' again. * Make CI check that documentation can be built. * Add back a doc that is OK - - - - - 5100450a by Matthew Yacavone at 2018-10-27T14:51:38-04:00 More explicit foralls (GHC Proposal 0007) - - - - - 8771a6b0 by Alec Theriault at 2018-11-05T13:58:11-08:00 Only run MathJax on entities with "mathjax" class (#960) Correspondingly, we wrap all inline/diplay math in <span class="mathjax"> ... the math .... </span> This fixes haskell/haddock#959. - - - - - bd7ff5c5 by Alec Theriault at 2018-11-05T15:54:22-08:00 Deduplicate some work in 'AttachInstances' Perf only change: * avoid needlessly union-ing maps * avoid synify-ing instances twice Took this opportunity to add some docs too - - - - - cf99fd8f by Alec Theriault at 2018-11-05T15:54:22-08:00 Specialize some SYB functions Perf only change: * Add a 'SPECIALIZE' pragma to help GHC optimize a 'Data a =>' constraint * Manually specialize the needlessly general type of 'specializeTyVarBndrs' - - - - - 4f91c473 by Alec Theriault at 2018-11-05T15:54:22-08:00 Improve perf of renaming Perf only change: * don't look up type variable names (they're never in the environment) * use a difference list for accumulating missing names * more efficient 'Functor'/'Applicative' instances for 'RnM' - - - - - 4bbab0d4 by Alec Theriault at 2018-11-05T15:54:22-08:00 Faster 'Text' driven parser combinators Perf only change: * use 'getParserState'/'setParserState' to make 'Text'-optimized parser combinators * minimize uses of 'Data.Text.{pack,unpack,cons,snoc}' - - - - - fa430c02 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support hyperlink labels with inline markup The parser for pictures hasn't been properly adjusted yet. - - - - - c1431035 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support (and flatten) inline markup in image links Inline markup is supported in image links but, as per the [commonmark recommendation][0], it is stripped back to a plain text representation. [0]: https://spec.commonmark.org/0.28/#example-547 - - - - - d4ee1ba5 by Alec Theriault at 2018-11-06T12:03:24-08:00 Accept test case - - - - - 8088aeb1 by Alec Theriault at 2018-11-06T12:03:24-08:00 Fix/add to haddock-library test suite - - - - - e78f644d by Alec Theriault at 2018-11-06T13:26:31-08:00 Bump version bounds - - - - - 644335eb by Alec Theriault at 2018-11-06T13:53:30-08:00 Merge pull request haskell/haddock#875 from harpocrates/feature/markup-in-hyperlinks Inline markup in markdown-style links and images - - - - - e173ed0d by Alec Theriault at 2018-11-07T12:37:18-08:00 Fix issues around plus/minus * swap the minimize unicode to something more intuitive * use new unicode expander/collapser for instance lists * address some alignment issues in the "index" page - - - - - b2d92df7 by Alec Theriault at 2018-11-07T13:41:57-08:00 Allow "Contents" summary to scroll in a fixed div In the unfortunate event that the "Contents" summary doesn't fit vertically (like in the "Prelude"), it will be scrollable. - - - - - ca704c23 by Alec Theriault at 2018-11-07T13:45:15-08:00 Accept HTML output changes - - - - - 82c0ec6d by Alec Theriault at 2018-11-07T18:12:54-08:00 overflow-y 'scroll' -> 'auto' - - - - - 571d7657 by Alec Theriault at 2018-11-08T19:44:12-08:00 Clicking on "Contents" navigates to top of page - - - - - 8065a012 by Alec Theriault at 2018-11-08T19:44:17-08:00 Space out functions more Also, functions and data decls now have the same space before and after them. - - - - - cc650ede by Alec Theriault at 2018-11-09T08:13:35-08:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 65f8c17f by Alec Theriault at 2018-11-10T14:04:06-08:00 Update changelog - - - - - 20473847 by Alec Theriault at 2018-11-10T14:21:40-08:00 Replace oplus/ominus expander/collapser icons with triangles - - - - - 16592957 by Alec Theriault at 2018-11-10T14:35:10-08:00 Merge pull request haskell/haddock#949 from haskell/wip/new-ocean Introduce NewOcean theme. - - - - - 357cefe1 by Alec Theriault at 2018-11-10T16:02:13-08:00 Merge branch 'ghc-8.6' into ghc-head - - - - - de612267 by Alec Theriault at 2018-11-11T20:01:21-08:00 Rename 'NewOcean' theme to 'Linuwial' - - - - - 954b5baa by Alec Theriault at 2018-11-12T08:33:18-08:00 Add blockquote styling Matches b71da1feabf33efbbc517ac376bb690b5a604c2f from hackage-server. Fixes haskell/haddock#967. - - - - - d32c0b0b by Fangyi Zhou at 2018-11-12T10:24:13-08:00 Fix some broken links (#15733) Summary: For links in subpackages as well. https://phabricator.haskell.org/D5257 Test Plan: Manually verify links Reviewers: mpickering, bgamari, osa1 Reviewed By: osa1 GHC Trac Issues: haskell/haddock#15733 Differential Revision: https://phabricator.haskell.org/D5262 - - - - - 41098b1f by Alp Mestanogullari at 2018-11-15T22:40:09+01:00 Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change It got introduced in ghc/ghc at ae2c9b40f5b6bf272251d1f4107c60003f541b62. - - - - - c5c1c7e0 by Alec Theriault at 2018-11-15T13:48:13-08:00 Merge pull request haskell/haddock#970 from alpmestan/alp/fix-promotionflag Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change - - - - - 6473d3a4 by Shayan-Najd at 2018-11-23T01:38:49+01:00 [TTG: Handling Source Locations] Foundation and Pat Trac Issues haskell/haddock#15495 This patch removes the ping-pong style from HsPat (only, for now), using the plan laid out at https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/HandlingSourceLocations (solution A). - the class `HasSrcSpan`, and its functions (e.g., `cL` and `dL`), are introduced - some instances of `HasSrcSpan` are introduced - some constructors `L` are replaced with `cL` - some patterns `L` are replaced with `dL->L` view pattern - some type annotation are necessarily updated (e.g., `Pat p` --> `Pat (GhcPass p)`) - - - - - 7a088dfe by Alec Theriault at 2018-11-26T11:11:28-08:00 More uniform handling of `forall`'s in HTML/LaTeX * don't forget to print explicit `forall`'s when there are arg docs * when printing an explicit `forall`, print all tyvars Fixes haskell/haddock#973 - - - - - d735e570 by Alec Theriault at 2018-12-12T08:42:09-08:00 Fix warnings, accept output * remove redundant imports (only brought to light due to recent work for improving redundant import detection) * fix a bug that was casuing exports to appear in reverse order * fix something in haddock-library that prevented compilation on old GHC's - - - - - a3852f8a by Zejun Wu at 2018-12-14T09:37:47-05:00 Output better debug infromation on internal error in extractDecl This will make investigation of haskell/haddock#979 easier - - - - - 2eccb5b9 by Alec Theriault at 2018-12-17T09:25:10-05:00 Refactor names + unused functions (#982) This commit should not introduce any change in functionality! * consistently use `getOccString` to convert `Name`s to strings * compare names directly when possible (instead of comparing strings) * get rid of unused utility functions - - - - - e82e4df8 by Alec Theriault at 2018-12-20T16:16:30-05:00 Load plugins when compiling each module (#983) * WIP: Load (typechecker) plugins from language pragmas * Revert "Load plugins when starting a GHC session (#905)" This reverts commit 72d82e52f2a6225686d9668790ac33c1d1743193. * Simplify plugin initialization code - - - - - 96e86f38 by Alec Theriault at 2018-12-23T10:23:20-05:00 Properly synify and render promoted type variables (#985) * Synify and render properly promoted type variables Fixes haskell/haddock#923. * Accept output - - - - - 23343345 by Alec Theriault at 2018-12-27T16:39:38-05:00 Remove `haddock-test`'s dep. on `syb` (#987) The functionality is easily inlined into one short function: `gmapEverywhere`. This doesn't warrant pulling in another package. - - - - - d0734f21 by Alec Theriault at 2018-12-27T16:39:52-05:00 Address deprecation warnings in `haddock-test` (#988) Fixes haskell/haddock#885. - - - - - 4d9f144e by mynguyen at 2018-12-30T23:42:26-05:00 Visible kind application haddock update - - - - - ffe0e9ed by Alec Theriault at 2019-01-07T13:55:22-08:00 Print kinded tyvars in constructors for Hoogle (#993) Fixes haskell/haddock#992 - - - - - 2e18b55d by Alec Theriault at 2019-01-10T16:42:45-08:00 Accept new output `GHC.Maybe` -> `Data.Maybe` (#996) Since 53874834b779ad0dfbcde6650069c37926da1b79 in GHC, "GHC.Maybe" is marked as `not-home`. That changes around some test output. - - - - - 055da666 by Gabor Greif at 2019-01-22T14:41:51+01:00 Lone typofix - - - - - 01bb71c9 by Alec Theriault at 2019-01-23T11:46:46-08:00 Keep forall on H98 existential data constructors (#1003) The information about whether or not there is a source-level `forall` is already available on a `ConDecl` (as `con_forall`), so we should use it instead of always assuming `False`! Fixes haskell/haddock#1002. - - - - - f9b9bc0e by Ryan Scott at 2019-01-27T09:28:12-08:00 Fix haskell/haddock#1004 with a pinch of dropForAlls - - - - - 5cfcdd0a by Alec Theriault at 2019-01-28T16:49:57-08:00 Loosen 'QuickCheck' and 'hspec' bounds It looks like the new versions don't cause any breakage and loosening the bounds helps deps fit in one stack resolver. - - - - - 3545d3dd by Alec Theriault at 2019-01-31T01:37:25-08:00 Use `.hie` files for the Hyperlinker backend (#977) # Summary This is a large architectural change to the Hyperlinker. * extract link (and now also type) information from `.hie` instead of doing ad-hoc SYB traversals of the `RenamedSource`. Also adds a superb type-on-hover feature (#715). * re-engineer the lexer to avoid needless string conversions. By going directly through GHC's `P` monad and taking bytestring slices, we avoid a ton of allocation and have better handling of position pragmas and CPP. In terms of performance, the Haddock side of things has gotten _much_ more efficient. Unfortunately, much of this is cancelled out by the increased GHC workload for generating `.hie` files. For the full set of boot libs (including `ghc`-the-library) * the sum of total time went down by 9-10% overall * the sum of total allocations went down by 6-7% # Motivation Haddock is moving towards working entirely over `.hi` and `.hie` files. This change means we no longer need the `RenamedSource` from `TypecheckedModule` (something which is _not_ in `.hi` files). # Details Along the way a bunch of things were fixed: * Cross package (and other) links are now more reliable (#496) * The lexer tries to recover from errors on every line (instead of at CPP boundaries) * `LINE`/`COLUMN` pragmas are taken into account * filter out zero length tokens before rendering * avoid recomputing the `ModuleName`-based `SrcMap` * remove the last use of `Documentation.Haddock.Utf8` (see haskell/haddock#998) * restructure temporary folder logic for `.hi`/`.hie` model - - - - - 2ded3359 by Herbert Valerio Riedel at 2019-02-02T12:06:12+01:00 Update/modernise haddock-library.cabal file - - - - - 62b93451 by Herbert Valerio Riedel at 2019-02-02T12:19:31+01:00 Tentatively declare support for unreleased base-4.13/ghc-8.8 - - - - - 6041e767 by Herbert Valerio Riedel at 2019-02-02T16:04:32+01:00 Normalise LICENSE text w/ cabal's BSD2 template Also, correct the `.cabal` files to advertise `BSD2` instead of the incorrect `BSD3` license. - - - - - 0b459d7f by Alec Theriault at 2019-02-02T18:06:12-08:00 CI: fetch GHC from validate artifact Should help make CI be less broken - - - - - 6b5c07cf by Alec Theriault at 2019-02-02T18:06:12-08:00 Fix some Hyperlinker test suite fallout * Amend `ParserSpec` to match new Hyperlinker API - pass in compiler info - strip out null tokens * Make `hypsrc-test` pass reliably - strip out `local-*` ids - strip out `line-*` ids from the `ClangCppBug` test - re-accept output - - - - - ded34791 by Nathan Collins at 2019-02-02T18:31:23-08:00 Update README instructions for Stack No need to `stack install` Haddock to test it. Indeed, `stack install` changes the `haddock` on user's `PATH` if `~/.local/bin` is on user's `PATH` which may not be desirable when hacking on Haddock. - - - - - 723298c9 by Alec Theriault at 2019-02-03T09:11:05-08:00 Remove `Documentation.Haddock.Utf8` The circumstances under which this module appeared are completely gone. The Hyperlinker backend no longer needs this module (it uses the more efficient `Encoding` module from `ghc`). Why no deprecation? Because this module really shouldn't exist! - It isn't used in `haddock-library`/`haddock-api` anymore - It was copy pasted directly from `utf8-string` - Folks seeking a boot-lib only solution can use `ghc`'s `Encoding` - - - - - 51050006 by Alec Theriault at 2019-02-03T22:58:58-08:00 Miscellaneous improvements to `Convert` (#1020) Now that Haddock is moving towards working entirely over `.hi` and `.hie` files, all declarations and types are going to be synthesized via the `Convert` module. In preparation for this change, here are a bunch of fixes to this module: * Add kind annotations to type variables in `forall`'s whose kind is not `Type`, unless the kind can be inferred from some later use of the variable. See `implicitForAll` and `noKindTyVars` in particular if you wish to dive into this. * Properly detect `HsQualTy` in `synifyType`. This is done by following suit with what GHC's `toIfaceTypeX` does and checking the first argument of `FunTy{} :: Type` to see if it classified as a given/wanted in the typechecker (see `isPredTy`). * Beef up the logic around figuring out when an explicit `forall` is needed. This includes: observing if any of the type variables will need kind signatures, if the inferred type variable order _without_ a forall will still match the one GHC claims, and some other small things. * Add some (not yet used) functionality for default levity polymorphic type signatures. This functionality similar to `fprint-explicit-runtime-reps`. Couple other smaller fixes only worth mentioning: * Show the family result signature only when it isn't `Type` * Fix rendering of implicit parameters in the LaTeX and Hoogle backends * Better handling of the return kind of polykinded H98 data declarations * Class decls produced by `tyThingToLHsDecl` now contain associated type defaults and default method signatures when appropriate * Filter out more `forall`'s in pattern synonyms - - - - - 841980c4 by Oleg Grenrus at 2019-02-04T08:44:25-08:00 Make a fixture of weird parsing of lists (#997) The second example is interesting. If there's a list directly after the header, and that list has deeper structure, the parser is confused: It finds two lists: - One with the first nested element, - everything after it I'm not trying to fix this, as I'm not even sure this is a bug, and not a feature. - - - - - 7315c0c8 by Ryan Scott at 2019-02-04T12:17:56-08:00 Fix haskell/haddock#1015 with dataConUserTyVars (#1022) The central trick in this patch is to use `dataConUserTyVars` instead of `univ_tvs ++ ex_tvs`, which displays the foralls in a GADT constructor in a way that's more faithful to how the user originally wrote it. Fixes haskell/haddock#1015. - - - - - ee0b49a3 by Ryan Scott at 2019-02-04T15:25:17-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. - - - - - 1c850dc8 by Alan Zimmerman at 2019-02-05T21:54:18+02:00 Matching changes in GHC for haskell/haddock#16236 - - - - - ab03c38e by Simon Marlow at 2019-02-06T08:07:33+00:00 Merge pull request haskell/haddock#1014 from hvr/pr/bsd2-normalise Normalise LICENSE text w/ cabal's BSD2 template - - - - - 5a92ccae by Alec Theriault at 2019-02-10T06:21:55-05:00 Merge remote-tracking branch 'gitlab/wip/T16236-2' into ghc-head - - - - - c0485a1d by Alec Theriault at 2019-02-10T03:32:52-08:00 Removes `haddock-test`s dependency on `xml`/`xhtml` (#1027) This means that `html-test`, `latex-test`, `hoogle-test`, and `hypsrc-test` now only depend on GHC boot libs. So we should now be able to build and run these as part of GHC's testsuite. \o/ The reference output has changed very slightly, in three ways: * we don't convert quotes back into `&quot;` as the `xml` lib did * we don't add extra `&nbsp;` as the `xml` lib did * we now remove the entire footer `div` (instead of just emptying it) - - - - - 65a448e3 by Alec Theriault at 2019-02-11T12:27:41-05:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - 360ca937 by Alec Theriault at 2019-02-13T11:36:11-05:00 Clean up logic for guessing `-B` and `--lib` (#1026) Haddock built with the `in-ghc-tree` flag tries harder to find the GHC lib folder and its own resources. This should make it possible to use `in-ghc-tree`-built Haddock without having to specify the `-B` and `--lib` options (just how you can use in-tree GHC without always specifying the `-B` option). The logic to do this relies on `getExecutablePath`, so we only get this auto-detection on platforms where this function works. - - - - - d583e364 by Alec Theriault at 2019-02-16T10:41:22-05:00 Fix tests broken by GHC Changes in 19626218566ea709b5f6f287d3c296b0c4021de2 affected some of the hyperlinker output. Accepted the new output (hovering over a `..` now shows you what that wildcard binds). Also fixed some stray deprecation warnings. - - - - - da0c42cc by Vladislav Zavialov at 2019-02-17T11:39:19+03:00 Parser changes to match !380 - - - - - ab96bed7 by Ryan Scott at 2019-02-18T04:44:08-05:00 Bump ghc version to 8.9 - - - - - 44b7c714 by Alec Theriault at 2019-02-22T05:49:43-08:00 Match GHC changes for T16185 `FunTy` now has an `AnonArgFlag` that indicates whether the arrow is a `t1 => t2` or `t1 -> t2`. This commit shouldn't change any functionality in Haddock. - - - - - 2ee653b1 by Alec Theriault at 2019-02-24T18:53:33-08:00 Update .travis.yml Points to the new GHC CI artifact. - - - - - 90939d71 by Alec Theriault at 2019-02-25T00:42:41-08:00 Support value/type namespaces on identifier links Identifier links can be prefixed with a 'v' or 't' to indicate the value or type namespace of the desired identifier. For example: -- | Some link to a value: v'Data.Functor.Identity' -- -- Some link to a type: t'Data.Functor.Identity' The default is still the type (with a warning about the ambiguity) - - - - - d6ed496c by Alec Theriault at 2019-02-25T00:42:46-08:00 Better identifier parsing * '(<|>)' and '`elem`' now get parsed and rendered properly as links * 'DbModule'/'DbUnitId' now properly get split apart into two links * tuple names now get parsed properly * some more small niceties... The identifier parsing code is more precise and more efficient (although to be fair: it is also longer and in its own module). On the rendering side, we need to pipe through information about backticks/parens/neither all the way through from renaming to the backends. In terms of impact: a total of 35 modules in the entirety of the bootlib + ghc lib docs change. The only "regression" is things like '\0'. These should be changed to @\\0@ (the path by which this previously worked seems accidental). - - - - - 3c3b404c by Alec Theriault at 2019-02-25T22:12:11-08:00 Fix standalone deriving docs Docs on standalone deriving decls for classes with associated types should be associated with the class instance, not the associated type instance. Fixes haskell/haddock#1033 - - - - - d51ef69e by Alec Theriault at 2019-02-26T19:14:59-08:00 Fix bogus identifier defaulting This avoids a situation in which an identifier would get defaulted to a completely different identifier. Prior to this commit, the 'Bug1035' test case would hyperlink 'Foo' into 'Bar'! Fixes haskell/haddock#1035. - - - - - 88cbbdc7 by Ryan Scott at 2019-02-27T10:14:03-05:00 Visible dependent quantification (#16326) changes - - - - - 0dcf6cee by Xia Li-yao at 2019-02-27T21:53:27-05:00 Menu item controlling which instances are expanded/collapsed (#1007) Adds a menu item (like "Quick Jump") for options related to displaying instances. This provides functionality for: * expanding/collapsing all instances on the currently opened page * controlling whether instances are expanded/collapsed by default * controlling whether the state of instances should be "remembered" This new functionality is implemented in Typescript in `details-helper`. The built-in-themes style switcher also got a revamp so that all three of QuickJump, the style switcher, and instance preferences now have the same style and implementation structure. See also: https://mail.haskell.org/pipermail/haskell-cafe/2019-January/130495.html Fixes haskell/haddock#698. Co-authored-by: Lysxia <lysxia at gmail.com> Co-authored-by: Nathan Collins <conathan at galois.com> - - - - - 3828c0fb by Alec Theriault at 2019-02-28T12:42:49-05:00 `--show-interface` should output to stdout. (#1040) Fixes haskell/haddock#864. - - - - - a50f4cda by gbaz at 2019-03-01T07:43:16-08:00 Increase contrast of Linuwal theme (#1037) This is to address the concern that, on less nice and older screens, some of the shades of grey blend in too easily with the white background. * darken the font slightly * darken slightly the grey behind type signatures and such * add a border and round the corners on code blocks * knock the font down by one point - - - - - ab4d41de by Alec Theriault at 2019-03-03T09:23:26-08:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 12f509eb by Ben Gamari at 2019-03-04T22:13:20-05:00 Remove reference to Opt_SplitObjs flag Split-objects has been removed. - - - - - 5b3e4c9a by Ryan Scott at 2019-03-06T19:16:24-05:00 Update html-test output to reflect haskell/haddock#16391 changes - - - - - fc228af1 by Alec Theriault at 2019-03-09T08:29:23-08:00 Match changes for "Stop inferring over-polymorphic kinds" The `hsq_ext` field of `HsQTvs` is now just the implicit variables (instead of also including information about which of these variables are dependent). This commit shouldn't change any functionality in Haddock. - - - - - 6ac109eb by Alec Theriault at 2019-03-09T11:22:55-08:00 Add .hi, .dyn_hi, etc files to .gitignore Fixes haskell/haddock#1030. - - - - - b55f0c05 by Alec Theriault at 2019-03-09T11:22:55-08:00 Better support for default methods in classes * default methods now get rendered differently * default associated types get rendered * fix a forgotten `s/TypeSig/ClassOpSig/` refactor in LaTeX backend * LaTeX backend now renders default method signatures NB: there is still no way to document default class members and the NB: LaTeX backend still crashes on associated types - - - - - 10aea0cf by Alec Theriault at 2019-03-09T11:22:55-08:00 Avoid multi-line `emph` in LaTeX backend `markupWarning` often processes inputs which span across paragraphs. Unfortunately, LaTeX's `emph` is not made to handle this (and will crash). Fixes haskell/haddock#936. - - - - - d22dc2c9 by Alec Theriault at 2019-03-09T11:22:55-08:00 Many LaTeX backend fixes After this commit, we can run with `--latex` on all boot libraries without crashing (although the generated LaTeX still fails to compile in a handful of larger packages like `ghc` and `base`). * Add newlines after all block elements in LaTeX. This is important to prevent the final output from being more an more indented. See the `latext-test/src/Example` test case for a sample of this. * Support associated types in class declarations (but not yet defaults) * Several small issues for producing compiling LaTeX; - avoid empy `\haddockbeginargs` lists (ex: `type family Any`) - properly escape identifiers depending on context (ex: `Int#`) - add `vbox` around `itemize`/`enumerate` (so they can be in tables) * Several spacing fixes: - limit the width of `Pretty`-arranged monospaced code - cut out extra space characters in export lists - only escape spaces if there are _multiple_ spaces - allow type signatures to be multiline (even without docs) * Remove uninteresting and repetitive `main.tex`/`haddock.sty` files from `latex-test` test reference output. Fixes haskell/haddock#935, haskell/haddock#929 (LaTeX docs for `text` build & compile) Fixes haskell/haddock#727, haskell/haddock#930 (I think both are really about type families...) - - - - - 0e6cee00 by Alec Theriault at 2019-03-29T12:11:56-07:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - ce05434d by Alan Zimmerman at 2019-03-29T12:12:11-07:00 Matching changes in GHC for haskell/haddock#16236 (cherry picked from commit 3ee6526d4ae7bf4deb7cd1caf24b3d7355573576) - - - - - d85766b2 by Ben Gamari at 2019-03-29T12:14:04-07:00 Bump GHC to 8.8 - - - - - 5a82cbaf by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Redo ParseModuleHeader - - - - - b9033348 by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - bb55c8f4 by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove outdated `.ghci` files and `scripts` The `.ghci` files are actively annoying when trying to `cabal v2-repl`. As for the `scripts`, the distribution workflow is completely different. - - - - - 5ee244dc by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove obsolete arcanist files + STYLE Now that GHC is hosted on Gitlab, the arcanist files don't make sense anymore. The STYLE file contains nothing more than a dead link too. - - - - - d07c1928 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Redo ParseModuleHeader - - - - - 492762d2 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - af2ac773 by Ryan Scott at 2019-05-14T17:22:13-04:00 Changes for haskell/haddock#16110/#16356 - - - - - 6820ed0d by Alec Theriault at 2019-05-17T08:51:27-07:00 Unbreak haskell/haddock#1004 test case `fail` is no longer part of `Monad`. - - - - - 6bf7be98 by Alec Theriault at 2019-05-17T08:51:27-07:00 Fix haskell/haddock#1063 with better parenthesization logic for contexts The only other change in html/hoogle/hyperlinker output for the boot libraries that this caused is a fix to some Hoogle output for implicit params. ``` $ diff -r _build/docs/ old_docs diff -r _build/docs/html/libraries/base/base.txt old_docs/html/libraries/base/base.txt 13296c13296 < assertError :: (?callStack :: CallStack) => Bool -> a -> a --- > assertError :: ?callStack :: CallStack => Bool -> a -> a ``` - - - - - b5716b61 by Ryan Scott at 2019-05-22T17:24:32-04:00 Match changes with haskell/haddock#14332 - - - - - c115abf6 by Alec Theriault at 2019-05-26T16:01:58-04:00 Remove Haddock's dependency on `Cabal` At this point, Haddock depended on Cabal-the-library solely for a verbosity parser (which misleadingly accepts all sorts of verbosity options that Haddock never uses). Now, the only dependency on Cabal is for `haddock-test` (which uses Cabal to locate the Haddock interface files of a couple boot libraries). - - - - - e5b2d4a3 by Alec Theriault at 2019-05-26T16:16:25-04:00 Regression test: promoted lists in associated types When possible, associated types with promoted lists should use the promoted list literal syntax (instead of repeated applications of ': and '[]). This was fixed in 2122de5473fd5b434af690ff9ccb1a2e58491f8c. Closes haskell/haddock#466, - - - - - cc5ad5d3 by Alec Theriault at 2019-05-26T17:55:54-04:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 4b3301a6 by Alec Theriault at 2019-05-26T17:57:52-04:00 Release haddock-2.23, haddock-library-1.8.0 Tentatively adjust bounds and changelogs for the release to be bundled with GHC 8.8.1. - - - - - 69c7cfce by Matthew Pickering at 2019-05-30T10:54:27+01:00 Update hyperlinker tests for new types in .hie files - - - - - 29b7e738 by Zubin Duggal at 2019-05-30T10:57:51+01:00 update for new way to store hiefile headers - - - - - aeca5d5f by Zubin Duggal at 2019-06-04T18:57:42-04:00 update for new way to store hiefile headers - - - - - ba2ca518 by Ben Gamari at 2019-06-07T23:11:14+00:00 Update test output for introduction of Safe-Inferred - - - - - 3a975a6c by Ryan Scott at 2019-07-03T12:06:27-04:00 Changes for haskell/haddock#15247 - - - - - 0df46555 by Zubin Duggal at 2019-07-22T10:52:50+01:00 Fix haddockHypsrcTest - - - - - 2688686b by Sylvain Henry at 2019-09-12T23:19:39+02:00 Fix for GHC module renaming - - - - - 9ec0f3fc by Alec Theriault at 2019-09-20T03:21:00-04:00 Fix Travis CI, loosen .cabal bounds (#1089) Tentatively for the 2.23 release: * updated Travis CI to work again * tweaked bounds in the `.cabal` files * adjusted `extra-source-files` to properly identify test files - - - - - ca559beb by Matthías Páll Gissurarson at 2019-09-28T12:14:40-04:00 Small change in to facilitate extended typed-holes (#1090) This change has no functional effect on haddock itself, it just changes one pattern to use `_ (` rather than `_(`, so that we may use `_(` as a token for extended typed-holes later. - - - - - 02e28976 by Vladislav Zavialov at 2019-09-28T12:17:45-04:00 Remove spaces around @-patterns (#1093) This is needed to compile `haddock` when [GHC Proposal haskell/haddock#229](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0229-whitespace-bang-patterns.rst) is implemented. - - - - - 83cbbf55 by Alexis King at 2019-09-30T21:12:42-04:00 Fix the ignore-exports option (#1082) The `ignore-exports` option has been broken since haskell/haddock#688, as mentioned in https://github.com/haskell/haddock/pull/766#issue-172505043. This PR fixes it. - - - - - e127e0ab by Ben Gamari at 2019-10-06T15:12:06-04:00 Fix a few haddock issues - - - - - 3a0f5c89 by Zubin Duggal at 2019-10-07T17:56:13-04:00 Fix crash when there are no srcspans in the file due to CPP - - - - - 339c5ff8 by Alec Theriault at 2019-10-07T17:56:13-04:00 Prefer un-hyperlinked sources to no sources It is possible to fail to extract an HIE ast. This is however not a reason to produce _no_ output - we should still make a colorized HTML page. - - - - - d47ef478 by Alec Theriault at 2019-10-07T17:56:13-04:00 Add a regression test for haskell/haddock#1091 Previously, this input would crash Haddock. - - - - - ed7c8b0f by Alec Theriault at 2019-10-07T20:56:48-04:00 Add Hyperlinker test cases for TH-related stuff Hopefully this will guard against regressions around quasiquotes, TH quotes, and TH splices. - - - - - d00436ab by Andreas Klebinger at 2019-10-21T15:53:03+02:00 Refactor for withTiming changes. - - - - - 4230e712 by Ben Gamari at 2019-10-22T09:36:37-04:00 Merge pull request haskell/haddock#1101 from AndreasPK/withTimingRefactor Refactor for withTiming changes. - - - - - d155c5f4 by Ryan Scott at 2019-10-23T10:37:17-04:00 Reify oversaturated data family instances correctly (#1103) This fixes haskell/haddock#1103 by adapting the corresponding patch for GHC (see https://gitlab.haskell.org/ghc/ghc/issues/17296 and https://gitlab.haskell.org/ghc/ghc/merge_requests/1877). - - - - - 331a5adf by Sebastian Graf at 2019-10-25T17:14:40+02:00 Refactor for OutputableBndrId changes - - - - - 48a490e0 by Ben Gamari at 2019-10-27T10:16:16-04:00 Merge pull request haskell/haddock#1105 from sgraf812/wip/flexible-outputable Refactor for OutputableBndrId changes - - - - - f62a7dfc by Sebastian Graf at 2019-11-01T11:54:16+00:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - d9b242ed by Ryan Scott at 2019-11-03T13:20:03-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. (cherry picked from commit cfd682c5fd03b099a3d78c44f9279faf56a0ac70) - - - - - dfd42406 by Sebastian Graf at 2019-11-04T07:02:14-05:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - 0b15be7c by Ben Gamari at 2019-11-09T13:21:33-05:00 Import isRuntimeRepVar from Type rather than TyCoRep isRuntimeRepVar is not longer exported from TyCoRep due to ghc#17441. - - - - - 091f7283 by Ben Gamari at 2019-11-10T12:47:06-05:00 Bump to GHC 8.10 - - - - - e88c71f2 by Ben Gamari at 2019-11-14T00:22:24-05:00 Merge pull request haskell/haddock#1110 from haskell/wip/T17441 Import isRuntimeRepVar from Type rather than TyCoRep - - - - - 4e0bbc17 by Ben Gamari at 2019-11-14T00:22:45-05:00 Version bumps for GHC 8.11 - - - - - 0e85ceb4 by Ben Gamari at 2019-11-15T11:59:45-05:00 Bump to GHC 8.10 - - - - - 00d6d68b by Ben Gamari at 2019-11-16T18:35:58-05:00 Bump ghc version to 8.11 - - - - - dde1fc3f by Ben Gamari at 2019-11-16T20:40:37-05:00 Drop support for base 4.13 - - - - - f52e331d by Vladislav Zavialov at 2019-11-24T13:02:28+03:00 Update Hyperlinker.Parser.classify to use ITdollar - - - - - 1ad96198 by Vladislav Zavialov at 2019-11-28T16:12:33+03:00 Remove HasSrcSpan (#17494) - - - - - 651afd70 by Herbert Valerio Riedel at 2019-12-08T12:08:16+01:00 Document error-prone conditional definition of instances This can easily trip up people if one isn't aware of it. Usually it's better to avoid this kind of conditionality especially for typeclasses for which there's an compat-package as conditional instances like these tend to fragment the ecosystem into those packages that go the extra mile to provide backward compat via those compat-packages and those that fail to do so. - - - - - b521af56 by Herbert Valerio Riedel at 2019-12-08T12:09:54+01:00 Fix build-failure regression for base < 4.7 The `$>` operator definition is available only since base-4.7 which unfortunately wasn't caught before release to Hackage (but has been fixed up by a metadata-revision) This commit introduces a `CompatPrelude` module which allows to reduce the amount of CPP by ousting it to a central location, i.e. the new `CompatPrelude` module. This pattern also tends to reduce the tricks needed to silence unused import warnings. Addresses haskell/haddock#1119 - - - - - 556c375d by Sylvain Henry at 2020-01-02T19:01:55+01:00 Fix after Iface modules renaming - - - - - bd6c53e5 by Sylvain Henry at 2020-01-07T00:48:48+01:00 hsyl20-modules-renamer - - - - - fb23713b by Ryan Scott at 2020-01-08T07:41:13-05:00 Changes for GHC#17608 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2372 - - - - - 4a4dd382 by Ryan Scott at 2020-01-25T08:08:26-05:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - e782a44d by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename PackageConfig into UnitInfo - - - - - ba3c9f05 by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename lookupPackage - - - - - ab37f9b3 by Ben Gamari at 2020-01-29T13:00:44-05:00 Merge pull request haskell/haddock#1125 from haskell/wip/T17566-take-two Changes for GHC#17566 - - - - - 3ebd5ae0 by Ryan Scott at 2020-01-31T05:56:50-05:00 Merge branch 'wip-hsyl20-package-refactor' into ghc-head - - - - - 602a747e by Richard Eisenberg at 2020-02-04T09:05:43+00:00 Echo GHC's removal of PlaceHolder module This goes with GHC's !2083. - - - - - ccfe5679 by Sylvain Henry at 2020-02-10T10:13:56+01:00 Module hierarchy: runtime (cf haskell/haddock#13009) - - - - - 554914ce by Cale Gibbard at 2020-02-10T16:10:39-05:00 Fix build of haddock in stage1 We have to use the correct version of the GHC API, but the version of the compiler itself doesn't matter. - - - - - 5b6fa2a7 by John Ericson at 2020-02-10T16:18:07-05:00 Noramlize `tested-with` fields in cabal files - - - - - e6eb3ebe by Vladislav Zavialov at 2020-02-16T13:25:26+03:00 No MonadFail/Alternative for P - - - - - 90e181f7 by Ben Gamari at 2020-02-18T14:13:47-05:00 Merge pull request haskell/haddock#1129 from obsidiansystems/wip/fix-stage1-build Fix build of haddock in stage1 - - - - - 93b64636 by Sylvain Henry at 2020-02-19T11:20:27+01:00 Modules: Driver (#13009) - - - - - da4f6c7b by Vladislav Zavialov at 2020-02-22T15:33:02+03:00 Use RealSrcSpan in InstMap - - - - - 479b1b50 by Ben Gamari at 2020-02-23T10:28:13-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 55ecacf0 by Sylvain Henry at 2020-02-25T15:18:27+01:00 Modules: Core (#13009) - - - - - 60867b3b by Vladislav Zavialov at 2020-02-28T15:53:52+03:00 Ignore the BufLoc/BufSpan added in GHC's !2516 - - - - - 1e5506d3 by Sylvain Henry at 2020-03-02T12:32:43+01:00 Modules: Core (#13009) - - - - - 6fb53177 by Richard Eisenberg at 2020-03-09T14:49:40+00:00 Changes in GHC's !1913. - - - - - 30b792ea by Ben Gamari at 2020-03-16T12:45:02-04:00 Merge pull request haskell/haddock#1130 from hsyl20/wip/hsyl20-modules-core2 Modules: Core (#13009) - - - - - cd761ffa by Sylvain Henry at 2020-03-18T15:24:00+01:00 Modules: Types - - - - - b6646486 by Ben Gamari at 2020-03-18T14:42:43-04:00 Merge pull request haskell/haddock#1133 from hsyl20/wip/hsyl20/modules/types Modules: Types - - - - - 9325d734 by Kleidukos at 2020-03-19T12:38:31-04:00 Replace the 'caption' class so that the collapsible sections are shown - - - - - 5e2bb555 by Kleidukos at 2020-03-19T12:38:31-04:00 Force ghc-8.8.3 - - - - - c6fcd0aa by Kleidukos at 2020-03-19T12:38:31-04:00 Update test fixtures - - - - - 5c849cb1 by Sylvain Henry at 2020-03-20T09:34:39+01:00 Modules: Types - - - - - 7f439155 by Alec Theriault at 2020-03-20T20:17:01-04:00 Merge branch 'ghc-8.8' into ghc-8.10 - - - - - b7904e5c by Alina Banerjee at 2020-03-20T20:24:17-04:00 Update parsing to strip whitespace from table cells (#1074) * Update parsing to strip leading & trailing whitespace from table cells * Update fixture data to disallow whitespaces at both ends in table cells * Add test case for whitespaces stripped from both ends of table cells * Update table reference test data for html tests - - - - - b9d60a59 by Alec Theriault at 2020-03-22T11:46:42-04:00 Clean up warnings * unused imports * imports of `Data.List` without import lists * missing `CompatPrelude` file in `.cabal` - - - - - 0c317dbe by Alec Theriault at 2020-03-22T18:46:54-04:00 Fix NPM security warnings This was done by calling `npm audit fix`. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. - - - - - 6e306242 by Alec Theriault at 2020-03-22T20:10:52-04:00 Tentative 2.24 release Adjusted changelogs and versions in `.cabal` files in preparation for the upcoming release bundled with GHC 8.10. - - - - - 1bfb4645 by Ben Gamari at 2020-03-23T16:40:54-04:00 Merge commit '3c2944c037263b426c4fe60a3424c27b852ea71c' into HEAD More changes from the GHC types module refactoring. - - - - - be8c6f3d by Alec Theriault at 2020-03-26T20:10:53-04:00 Update `.travis.yml` to work with GHC 8.10.1 * Regenerated the Travis file with `haskell-ci` * Beef up `.cabal` files with more `tested-with` information - - - - - b025a9c6 by Alec Theriault at 2020-03-26T20:10:53-04:00 Update README Removed some out of date links/info, added some more useful links. * badge to Hackage * update old trac link * `ghc-head` => `ghc-8.10` * `cabal new-*` is now `cabal v2-*` and it should Just Work * `--test-option='--accept'` is the way to accept testsuite output - - - - - 564d889a by Alec Theriault at 2020-03-27T20:34:33-04:00 Fix crash in `haddock-library` on unicode space Our quickcheck tests for `haddock-library` stumbled across an edge case input that was causing Haddock to crash: it was a unicode space character. The root cause of the crash is that we were implicitly assuming that if a space character was not " \t\f\v\r", it would have to be "\n". We fix this by instead defining horizontal space as: any space character that is not '\n'. Fixes haskell/haddock#1142 - - - - - 2d360ba1 by Alec Theriault at 2020-03-27T21:57:32-04:00 Disallow qualified uses of reserved identifiers This a GHC bug (https://gitlab.haskell.org/ghc/ghc/issues/14109) too, but it is a relatively easy fix in Haddock. Note that the fix must live in `haddock-api` instead of `haddock-library` because we can only really decide if an identifier is a reserved one by asking the GHC lexer. Fixes haskell/haddock#952 - - - - - 47ae22ed by Alec Theriault at 2020-03-28T13:36:25-04:00 Remove unused `Haddock.Utils` functions * removed functions in `Haddock.Utils` that were not used anywhere (or exported from the `haddock-api` package) * moved GHC-specific utils from `Haddock.Utils` to `Haddock.GhcUtils` - - - - - c0291245 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use TTG empty extensions to remove some `error`'s None of these error cases should ever have been reachable, so this is just a matter of leveraging the type system to assert this. * Use the `NoExtCon` and `noExtCon` to handle case matches for no extension constructors, instead of throwing an `error`. * Use the extension field of `HsSpliceTy` to ensure that this variant of `HsType` cannot exist in an `HsType DocNameI`. - - - - - 0aff8dc4 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use `unLoc`/`noLoc` from GHC instead of `unL`/`reL` * `unL` is already defined by GHC as `unLoc` * `reL` is already defined by GHC as `noLoc` (in a safer way too!) * Condense `setOutputDir` and add a about exporting from GHC Fixes haskell/haddock#978 - - - - - bf6f2fb7 by Alec Theriault at 2020-03-28T13:36:25-04:00 Cleanup up GHC flags in `.cabal` files * enable more useful warning flags in `haddock-api`, handle the new warnings generated * remove `-fwarn-tabs` (now we'd use `-Wtabs`, but this has been in `-Wall` for a while now) - - - - - c576fbf1 by Alec Theriault at 2020-03-28T13:36:25-04:00 `haddock-library` document header level Document the fact the header level is going to always be between 1 and 6 inclusive. Along the way, I also optimized the parsing code a bit. - - - - - 71bce0ee by Alec Theriault at 2020-03-28T14:26:27-04:00 Disallow links in section headers This is quite straightforward to implement, since we already had a function `docToHtmlNoAnchors` (which we used to generate the link in the sidebar "Contents"). This breaks test `Bug387`, but that test case has aged badly: we now automatically generate anchors for all headings, so manually adding an anchor in a section makes no sense. Nested anchors are, as pointed out in haskell/haddock#1054, disallowed by the HTML standard. Fixes haskell/haddock#1054 - - - - - b461b0ed by Sylvain Henry at 2020-03-30T10:34:23+02:00 Modules: type checker - - - - - cd8cd1ee by Ben Gamari at 2020-03-31T12:45:02-04:00 Merge pull request haskell/haddock#1152 from hsyl20/wip/hsyl20/modules/tc Module renaming - - - - - 5e8f8ea7 by Felix Yan at 2020-04-01T17:58:06-07:00 Allow QuickCheck 2.14 Builds fine and all tests pass. - - - - - dc6b1633 by Sylvain Henry at 2020-04-05T16:43:44+02:00 Module renaming: amend previous patch - - - - - eee2f4ae by Ryan Scott at 2020-04-05T09:04:43-07:00 Fix haskell/haddock#1050 by filtering out invisible AppTy arguments This makes the `synifyType` case for `AppTy` more intelligent by taking into consideration the visibilities of each `AppTy` argument and filtering out any invisible arguments, as they aren't intended to be displayed in the source code. (See haskell/haddock#1050 for an example of what can happen if you fail to filter these out.) Along the way, I noticed that a special `synifyType` case for `AppTy t1 (CoercionTy {})` could be consolidated with the case below it, so I took the opportunity to tidy this up. - - - - - 23eb99e8 by Ben Gamari at 2020-04-07T11:19:58-04:00 Merge pull request haskell/haddock#1154 from hsyl20/wip/hsyl20/modules/tc Module renaming: amend previous patch - - - - - 072d994d by Ryan Scott at 2020-04-07T19:32:47-04:00 Make NoExtCon fields strict These changes are a part of a fix for [GHC#17992](https://gitlab.haskell.org/ghc/ghc/issues/17992). - - - - - d8ebf6c8 by Ignat Insarov at 2020-04-09T21:15:01-04:00 Recode Doc to Json. (#1159) * Recode Doc to Json. * More descriptive field labels. - - - - - 52df4b4e by Sylvain Henry at 2020-04-10T12:39:18+02:00 Module renaming - - - - - d9ab8ec8 by Cale Gibbard at 2020-04-14T11:43:34-04:00 Add instance of XCollectPat for DocNameI - - - - - 323d221d by Cale Gibbard at 2020-04-14T11:43:34-04:00 Rename XCollectPat -> CollectPass - - - - - 2df80867 by Alec Theriault at 2020-04-15T07:30:51-07:00 Prune docstrings that are never rendered When first creating a Haddock interface, trim `ifaceDocMap` and `ifaceArgMap` to not include docstrings that can never appear in the final output. Besides checking with GHC which names are exported, we also need to keep all the docs attached to instance declarations (it is much tougher to detect when an instance is fully private). This change means: * slightly smaller interface files (7% reduction on boot libs) * slightly less work to do processing docstrings that aren't used * no warnings in Haddock's output about private docstrings (see haskell/haddock#1070) I've tested manually that this does not affect any of the boot library generated docs (the only change in output was some small re-ordering in a handful of instance lists). This should mean no docstrings have been incorrectly dropped. - - - - - f49c90cc by Alec Theriault at 2020-04-15T07:30:51-07:00 Don't warn about missing links in miminal sigs When renaming the Haddock interface, never emit warnings when renaming a minimal signature. Also added some documention around `renameInterface`. Minimal signatures intentionally include references to potentially un-exported methods (see the discussion in haskell/haddock#330), so it is expected that they will not always have a link destination. On the principle that warnings should always be resolvable, this shouldn't produce a warning. See haskell/haddock#1070. - - - - - a9eda64d by Ben Gamari at 2020-04-17T09:27:35-04:00 Merge pull request haskell/haddock#1160 from hsyl20/wip/hsyl20/modules/systools Module renaming - - - - - f40d7879 by Cale Gibbard at 2020-04-20T11:30:38-04:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ttg-con-pat - - - - - a50e7753 by Ben Gamari at 2020-04-20T11:36:10-04:00 Merge pull request haskell/haddock#1165 from obsidiansystems/wip/ttg-con-pat Trees that Grow refactor (GHC !2553) - - - - - 6a24795c by Alec Theriault at 2020-04-21T08:06:45-07:00 Fallback to `hiDecl` when `extractDecl` fails Sometimes, the declaration being exported is a subdecl (for instance, a record accessor getting exported at the top-level). For these cases, Haddock has to find a way to produce some synthetic sensible top-level declaration. This is done with `extractDecl`. As is shown by haskell/haddock#1067, this is sometimes impossible to do just at a syntactic level (for instance when the subdecl is re-exported). In these cases, the only sensible thing to do is to try to reify a declaration based on a GHC `TyThing` via `hiDecl`. - - - - - eee1a8b7 by Sylvain Henry at 2020-04-24T15:46:05+02:00 Module structure - - - - - 50b9259c by Iñaki at 2020-04-25T18:38:11-04:00 Add support for custom section anchors (#1179) This allows to have stable anchors for groups, even if the set of groups in the documentation is altered. The syntax for setting the anchor of a group is -- * Group name #desiredAnchor# Which will produce an html anchor of the form '#g:desiredAnchor' Co-authored-by: Iñaki García Etxebarria <git at inaki.blueleaf.cc> - - - - - 4003c97a by Ben Gamari at 2020-04-26T09:35:15-04:00 Merge pull request haskell/haddock#1166 from hsyl20/wip/hsyl20/modules/utils Module structure - - - - - 5206ab60 by Sylvain Henry at 2020-04-27T16:47:39+02:00 Renamed UnitInfo fields - - - - - c32c333b by Sylvain Henry at 2020-04-27T17:32:58+02:00 UnitId has been renamed into Unit - - - - - 3e87db64 by Sylvain Henry at 2020-04-27T17:36:00+02:00 Fix for GHC.Unit.* modules - - - - - ae3323a7 by Ben Gamari at 2020-04-29T12:36:37-04:00 Merge pull request haskell/haddock#1183 from hsyl20/wip/hsyl20/unitid Refactoring of Unit code - - - - - b105564a by Artem Pelenitsyn at 2020-05-03T08:14:10+01:00 add dependency on exceptions because GHC.Exception was boiled down (ghc haskell/haddock#18075) - - - - - 9857eff3 by Zubin Duggal at 2020-05-04T18:48:25+01:00 Atomic update of NameCache in readHieFile - - - - - 86bbb226 by Sylvain Henry at 2020-05-14T16:36:27+02:00 Fix after Config module renaming - - - - - a4bbdbc2 by Gert-Jan Bottu at 2020-05-15T22:09:44+02:00 Explicit Specificity Support for Haddock - - - - - 46199daf by Ben Gamari at 2020-05-19T09:59:56-04:00 Merge pull request haskell/haddock#1192 from hsyl20/hsyl20/modules-config Fix after Config module renaming - - - - - f9a9d2ba by Gert-Jan Bottu at 2020-05-20T16:48:38-04:00 Explicit Specificity Support for Haddock - - - - - 55c5b7ea by Ben Gamari at 2020-05-21T00:32:02-04:00 Merge commit 'a8d7e66da4dcc3b242103271875261604be42d6e' into ghc-head - - - - - a566557f by Cale Gibbard at 2020-05-21T16:02:06-04:00 isBootSummary now produces a result of type IsBootInterface - - - - - ea52f905 by Zubin Duggal at 2020-05-24T17:55:48+01:00 update for hiefile-typeclass-info - - - - - 49ba7a67 by Willem Van Onsem at 2020-05-25T12:23:01-04:00 Use floor over round to calculate the percentage (#1195) If we compile documentation where only a small fraction is undocumented, it is misleading to see 100% coverage - 99% is more intuitive. Fixes haskell/haddock#1194 - - - - - c025ebf1 by Ben Gamari at 2020-05-29T14:32:42-04:00 Merge pull request haskell/haddock#1185 from obsidiansystems/boot-disambig isBootSummary now produces a result of type IsBootInterface - - - - - 74ab9415 by Ben Gamari at 2020-05-29T20:23:39-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - b40be944 by Ben Gamari at 2020-06-03T17:02:31-04:00 testsuite: Update expected output for simplified subsumption - - - - - 624be71c by Ryan Scott at 2020-06-05T12:43:23-04:00 Changes for GHC#18191 See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3337. - - - - - fbd8f7ce by Sylvain Henry at 2020-06-08T15:31:47+02:00 Fix after unit refactoring - - - - - 743fda4d by Ben Gamari at 2020-06-09T12:09:58-04:00 Merge pull request haskell/haddock#1202 from hsyl20/wip/hsyl20/unitid-ii Fix after unit refactoring - - - - - d07a06a9 by Ryan Scott at 2020-06-13T07:16:55-04:00 Use HsForAllTelescope (GHC#18235) - - - - - 389bb60d by Ben Gamari at 2020-06-13T15:30:52-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - 7a377f5f by Ben Gamari at 2020-06-17T14:53:16-04:00 Merge pull request haskell/haddock#1199 from bgamari/wip/ghc-8.12 haddock: Bounds bumps for GHC 8.12 - - - - - 9fd9e586 by Krzysztof Gogolewski at 2020-06-17T16:09:07-04:00 Adapt Haddock to LinearTypes See ghc/ghc!852. - - - - - 46fe7636 by Ben Gamari at 2020-06-18T14:20:02-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 35a3c9e2 by Zubin Duggal at 2020-06-21T21:19:18+05:30 Use functions exported from HsToCore - - - - - 8abe3928 by Ben Gamari at 2020-06-24T13:53:39-04:00 Merge pull request haskell/haddock#1204 from wz1000/wip/haddock-hstocore Use functions exported from GHC.HsToCore.Docs - - - - - 22f2c937 by Matthías Páll Gissurarson at 2020-06-26T19:07:03+02:00 Adapt Haddock for QualifiedDo - - - - - 3f6208d7 by Vladislav Zavialov at 2020-06-28T14:28:16+03:00 Handle LexicalNegation's ITprefixminus - - - - - 03a19f41 by Sylvain Henry at 2020-07-02T09:37:38+02:00 Rename hsctarget into backend - - - - - ea17ff23 by Andreas Klebinger at 2020-07-02T17:44:18+02:00 Update for UniqFM changes. - - - - - 9872f2f3 by Ben Gamari at 2020-07-09T10:39:19-04:00 Merge pull request haskell/haddock#1209 from AndreasPK/wip/typed_uniqfm Update for UniqFM changes. - - - - - 68f7b668 by Krzysztof Gogolewski at 2020-07-12T18:16:57+02:00 Sync with GHC removing {-# CORE #-} pragma See ghc ticket haskell/haddock#18048 - - - - - eb372681 by Sylvain Henry at 2020-07-20T11:41:30+02:00 Rename hscTarget into backend - - - - - fb7f78bf by Ben Gamari at 2020-07-21T12:15:25-04:00 Merge pull request haskell/haddock#1214 from hsyl20/wip/hsyl20/hadrian/ncg Rename hscTarget into backend - - - - - 1e8f5b56 by Ben Gamari at 2020-07-23T09:11:50-04:00 Merge commit '904dce0cafe0a241dd3ef355775db47fc12f434d' into ghc-head - - - - - d8fd1775 by Zubin Duggal at 2020-07-23T18:46:40+05:30 Update for modular ping pong - - - - - 8416f872 by Ben Gamari at 2020-07-23T09:35:03-04:00 Merge pull request haskell/haddock#1200 from wz1000/wip/wz1000-modular-ping-pong Modular ping pong - - - - - a24a8577 by Ben Gamari at 2020-07-28T15:23:36-04:00 Bump GHC version to 9.0 - - - - - 6a51c9dd by Sylvain Henry at 2020-08-05T18:47:05+02:00 Fix after Outputable refactoring - - - - - c05e1c99 by Ben Gamari at 2020-08-10T14:41:41-04:00 Merge pull request haskell/haddock#1223 from hsyl20/wip/hsyl20/dynflags/exception Fix after Outputable refactoring - - - - - d964f15b by Sylvain Henry at 2020-08-12T11:58:49+02:00 Fix after HomeUnit - - - - - 8e6d5b23 by Ben Gamari at 2020-08-12T14:25:30-04:00 Merge pull request haskell/haddock#1225 from hsyl20/wip/hsyl20/plugins/homeunit Fix after HomeUnit - - - - - 8c7880fe by Sylvain Henry at 2020-08-17T14:13:29+02:00 Remove Ord FastString instance - - - - - 8ea410db by Alex Biehl at 2020-08-19T10:56:32+02:00 Another round of `npm audit fix` (#1228) This should shut down the warnings on Github. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. Last NPM dependency audit happend in d576b2327e2bc117f912fe0a9d595e9ae62614e0 Co-authored-by: Alex Biehl <alex.biehl at target.com> - - - - - 7af6e2a8 by Ben Gamari at 2020-08-31T13:59:34-04:00 Merge pull request haskell/haddock#1226 from hsyl20/wip/hsyl20/fs_ord Remove Ord FastString instance - - - - - ffbc8702 by Alan Zimmerman at 2020-09-07T21:47:41+01:00 Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - a93f1268 by Alan Zimmerman at 2020-09-07T23:11:38+01:00 Merge pull request haskell/haddock#1232 from haskell/wip/T18639-remove-generated-pragma, Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - 1f605d50 by Ben Gamari at 2020-09-14T18:30:01-04:00 Bump GHC version to 9.1 - - - - - 6599df62 by Vladislav Zavialov at 2020-09-18T14:05:15+03:00 Bump base upper bound to 4.16 - - - - - a01b3c43 by Ben Gamari at 2020-09-22T15:41:48-04:00 Update hypsrc-test for QuickLook This appears to be a spurious change. - - - - - e9cc6cac by Vladislav Zavialov at 2020-09-26T21:00:12+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 30e3ca7c by Sylvain Henry at 2020-09-29T11:18:32-04:00 Update for parser (#1234) - - - - - b172f3e3 by Vladislav Zavialov at 2020-09-30T01:01:30+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 0b9c08d3 by Sylvain Henry at 2020-09-30T11:02:33+02:00 Adapt to GHC parser changes - - - - - b9540b7a by Sylvain Henry at 2020-10-12T09:13:38-04:00 Don't pass the HomeUnitId (#1239) - - - - - 34762e80 by HaskellMouse at 2020-10-13T12:58:04+03:00 Changed tests due to unification of `Nat` and `Natural` in the follwing merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3583 - - - - - 256f86b6 by Vladislav Zavialov at 2020-10-15T10:48:03+03:00 Add whitespace in: map ($ v) - - - - - 4a3f711b by Alan Zimmerman at 2020-10-19T08:57:27+01:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled - - - - - 072cdd21 by Alan Zimmerman at 2020-10-21T14:48:28-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 9e09a445 by Alan Zimmerman at 2020-10-21T23:53:34-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 636d7de3 by Sylvain Henry at 2020-10-26T14:31:54-04:00 GHC.Driver.Types refactoring (#1242) - - - - - a597f000 by Ryan Scott at 2020-10-29T04:18:05-04:00 Adapt to the removal of Hs{Boxed,Constraint}Tuple See ghc/ghc!4097 and GHC#18723. - - - - - b96660fb by Ryan Scott at 2020-10-30T04:53:05-04:00 Adapt to HsConDecl{H98,GADT}Details split Needed for GHC#18844. - - - - - c287d82c by Ryan Scott at 2020-10-30T19:35:59-04:00 Adapt to HsOuterTyVarBndrs These changes accompany ghc/ghc!4107, which aims to be a fix for haskell/haddock#16762. - - - - - a34c31a1 by Ryan Scott at 2020-11-13T13:38:34-05:00 Adapt to splitPiTysInvisible being renamed to splitInvisPiTys This is a part of !4434, a fix for GHC#18939. - - - - - 66ea459d by Sylvain Henry at 2020-11-16T10:59:30+01:00 Fix after Plugins moved into HscEnv - - - - - 508556d8 by Ben Gamari at 2020-11-18T15:47:40-05:00 Merge pull request haskell/haddock#1253 from hsyl20/wip/hsyl20/plugins/hscenv Fix after Plugins moved into HscEnv - - - - - 620fec1a by Andreas Klebinger at 2020-11-24T20:51:59+01:00 Update for changes in GHC's Pretty - - - - - 01cc13ab by Richard Eisenberg at 2020-11-25T23:18:35-05:00 Avoid GHC#18932. - - - - - 8d29ba21 by Cale Gibbard at 2020-11-25T23:18:35-05:00 Add type arguments to PrefixCon - - - - - 414d5f87 by Sylvain Henry at 2020-11-30T17:06:04+01:00 DynFlags's unit fields moved to HscEnv - - - - - e356668c by Ben Gamari at 2020-11-30T11:11:37-05:00 Merge pull request haskell/haddock#1258 from hsyl20/wip/hsyl20/hscenv/unitstate Unit fields moved from DynFlags to HscEnv - - - - - 7cf552f1 by Ben Gamari at 2020-12-03T10:31:27-05:00 Merge pull request haskell/haddock#1257 from AndreasPK/wip/andreask/opt_dumps Update for changes in GHC's Pretty - - - - - fc0871c3 by Veronika Romashkina at 2020-12-08T16:35:33+01:00 Fix docs links from Darcs to GitHub in intro (#1262) - - - - - 7059e808 by Veronika Romashkina at 2020-12-08T16:36:16+01:00 Use gender neutral word in docs (#1260) - - - - - 1b16e5ee by Maximilian Tagher at 2020-12-08T16:40:03+01:00 Allow scrolling search results (#1235) Closes https://github.com/haskell/haddock/issues/1231 - - - - - 8a118c01 by dependabot[bot] at 2020-12-08T16:40:25+01:00 Bump bl from 1.2.2 to 1.2.3 in /haddock-api/resources/html (#1255) Bumps [bl](https://github.com/rvagg/bl) from 1.2.2 to 1.2.3. - [Release notes](https://github.com/rvagg/bl/releases) - [Commits](https://github.com/rvagg/bl/compare/v1.2.2...v1.2.3) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - c89ff587 by Xia Li-yao at 2020-12-08T16:42:17+01:00 Allow more characters in anchor following module reference (#1220) - - - - - 14af7d64 by Xia Li-yao at 2020-12-08T16:43:05+01:00 Add dangling changes from branches ghc-8.6 and ghc-8.8 (#1243) * Fix multiple typos and inconsistencies in doc/markup.rst Note: I noticed some overlap with haskell/haddock#1112 from @wygulmage and haskell/haddock#1081 from @parsonsmatt after creating these proposed changes - mea culpa for not looking at the open PRs sooner. * Fix haskell/haddock#1113 If no Signatures, no section of index.html * Change the formatting of missing link destinations The current formatting of the missing link destination does not really help user to understand the reasons of the missing link. To address this, I've changed the formatting in two ways: - the missing link symbol name is now fully qualified. This way you immediately know which haskell module cannot be linked. It is then easier to understand why this module does not have documentation (hidden module or broken documentation). - one line per missing link, that's more readable now that symbol name can be longer due to qualification. For example, before haddock was listing missing symbol such as: ``` could not find link destinations for: Word8 Word16 mapMaybe ``` Now it is listed as: ``` could not find link destinations for: - Data.Word.Word8 - Data.Word.Word16 - Data.Maybe.mapMaybe ``` * Add `--ignore-link-symbol` command line argument This argument can be used multiples time. A missing link to a symbol listed by `--ignore-link-symbol` won't trigger "missing link" warning. * Forbid spaces in anchors (#1148) * Improve error messages with context information (#1060) Co-authored-by: Matt Audesse <matt at mattaudesse.com> Co-authored-by: Mike Pilgrem <mpilgrem at users.noreply.github.com> Co-authored-by: Guillaume Bouchard <guillaume.bouchard at tweag.io> Co-authored-by: Pepe Iborra <pepeiborra at gmail.com> - - - - - 89e3af13 by tomjaguarpaw at 2020-12-08T18:00:04+01:00 Enable two warnings (#1245) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - c3320f8d by Willem Van Onsem at 2020-12-08T18:26:55+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 685df308 by Alex Biehl at 2020-12-08T20:06:26+01:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - be3ec3c0 by Alex Biehl at 2020-12-08T20:06:26+01:00 Import intercalate - - - - - 32c33912 by Matthías Páll Gissurarson at 2020-12-08T21:15:30+01:00 Adapt Haddock for QualifiedDo - - - - - 31696088 by Alex Biehl at 2020-12-08T22:06:02+01:00 Fix haddock-library tests - - - - - fbc0998a by Alex Biehl at 2020-12-08T23:08:23+01:00 Move to GitHub CI (#1266) * Initial version of ci.yml This is a straight copy from Dmitrii Kovanikov's blog post at https://kodimensional.dev/github-actions. Will adapt to haddock in successive commits. * Delete .travis.yml * Modify to only test on ghc-8.10.{1,2} * Use actions/setup-haskell at v1.1.4 * Relax QuickCheck bound on haddock-api * Remove stack matrix for now * Nail down to ghc-8.10 branch for now * Pin index state to 2020-12-08T20:13:44Z for now * Disable macOS and Windows tests for now for speed up - - - - - 5b946b9a by tomjaguarpaw at 2020-12-10T19:01:41+01:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - bc5a408f by dependabot[bot] at 2020-12-10T19:02:16+01:00 Bump ini from 1.3.5 to 1.3.7 in /haddock-api/resources/html (#1269) Bumps [ini](https://github.com/isaacs/ini) from 1.3.5 to 1.3.7. - [Release notes](https://github.com/isaacs/ini/releases) - [Commits](https://github.com/isaacs/ini/compare/v1.3.5...v1.3.7) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - d02995f1 by Andrew Martin at 2020-12-14T16:48:40-05:00 Update for boxed rep - - - - - a381aeff by Ben Gamari at 2020-12-15T15:13:30-05:00 Revert "Enable two warnings (#1245) (#1268)" As this does not build on GHC `master`. This reverts commit 7936692badfe38f23ae95b51fb7bd7c2ff7e9bce. - - - - - a63c0a9e by Ben Gamari at 2020-12-15T15:17:59-05:00 Revert "Update for boxed rep" This reverts commit 4ffb30d8b637ccebecc81ce610f0af451ac8088d. - - - - - 53bfbb29 by Ben Gamari at 2020-12-15T15:37:24-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - bae76a30 by Ben Gamari at 2020-12-16T02:44:42+00:00 Update output for nullary TyConApp optimisation (ghc/ghc!2952) - - - - - 4b733b57 by Krzysztof Gogolewski at 2020-12-16T20:03:14+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. - - - - - ee463bd3 by Ryan Scott at 2020-12-16T16:55:23-05:00 Adapt to HsCoreTy (formerly NewHsTypeX) becoming a type synonym Needed for !4417, the fix for GHC#15706 and GHC#18914. - - - - - ed0b02f8 by tomjaguarpaw at 2020-12-19T10:17:19+00:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - d80bf8f5 by Sylvain Henry at 2020-12-21T10:09:25+01:00 Fix after binder collect changes - - - - - bf4c9d32 by Adam Gundry at 2020-12-23T21:35:01+00:00 Adapt to changes to GlobalRdrElt and AvailInfo Needed for ghc/ghc!4467 - - - - - 37736c4c by John Ericson at 2020-12-28T12:27:02-05:00 Support a new ghc --make node type for parallel backpack upsweep - - - - - 717bdeac by Vladislav Zavialov at 2020-12-29T10:50:02+03:00 Inline and fix getGADTConTypeG The getGADTConTypeG used HsRecTy, which is at odds with GHC issue haskell/haddock#18782. I noticed that getGADTConTypeG was only used in the Hoogle backend. Interestingly, when handling H98 constructors, Hoogle converts RecCon to PrefixCon (see Haddock.Backends.Hoogle.ppCtor). So I changed getGADTConTypeG to handle RecConGADT in the same manner as PrefixConGADT, and after this simplification moved it into the 'where' clause of ppCtor, to the only place where it is used. The practical effect of this change is as follows. Consider this example: data TestH98 = T98 { bar::Int } data TestGADT where TG :: { foo :: Int } -> TestGADT Before this patch, haddock --hoogle used to produce: T98 :: Int -> TestH98 [TG] :: {foo :: Int} -> TestGADT Notice how the record syntax was discarded in T98 but not TG. With this patch, we always produce signatures without record syntax: T98 :: Int -> TestH98 [TG] :: Int -> TestGADT I suspect this might also be a bugfix, as currently Hoogle doesn't seem to render GADT record constructors properly. - - - - - cb1b8c56 by Andreas Abel at 2020-12-30T21:12:37+01:00 Build instructions: haddock-library and -api first! - - - - - b947f6ad by Ben Gamari at 2020-12-31T13:04:19-05:00 Merge pull request haskell/haddock#1281 from obsidiansystems/wip/backpack-j Changes to support -j with backpack - - - - - 120e1cfd by Hécate Moonlight at 2021-01-04T19:54:58+01:00 Merge pull request haskell/haddock#1282 from andreasabel/master Build instructions: haddock-library and -api first! - - - - - fd45e41a by Ben Gamari at 2021-01-05T16:14:31-05:00 Merge remote-tracking branch 'origin/ghc-8.10' into ghc-9.0 - - - - - b471bdec by Ben Gamari at 2021-01-05T16:23:02-05:00 Merge commit '1e56f63c3197e7ca1c1e506e083c2bad25d08793' into ghc-9.0 - - - - - 81cdbc41 by Alex Biehl at 2021-01-09T12:14:41+01:00 Prepare Haddock for being a GHC Plugin - - - - - b646d952 by Alex Biehl at 2021-01-09T12:14:41+01:00 Make Haddock a GHC Plugin - - - - - cc044674 by Alex Biehl at 2021-01-09T12:14:41+01:00 Add -j[n] CLI param to Haddock executable It translates to `--ghcopt=-j[n]` - - - - - 84a04073 by Alex Biehl at 2021-01-09T12:14:41+01:00 Abstract Monad for interface creation I found that when running as a plugin the lookupName function (which runs in Ghc monad) does not work correctly from the typeCheckResultAction hook. Instead, we abstracted the monad used when creating interfaces, so that access to GHC session specific parts is explicit and so that the TcM can provide their (correct) implementation of lookupName. - - - - - 5be2c4f7 by Alex Biehl at 2021-01-09T12:14:41+01:00 Accept tests - - - - - 8cefee9d by Alex Biehl at 2021-01-09T16:10:47+01:00 Add missing dependency for mtl - - - - - 3681f919 by Ben Gamari at 2021-01-13T18:39:25-05:00 Merge remote-tracking branch 'origin/ghc-9.0' into ghc-head - - - - - 33c6b152 by Hécate Moonlight at 2021-01-14T16:04:20+01:00 Merge pull request haskell/haddock#1273 from hsyl20/wip/hsyl20/arrows Fix after binder collect changes - - - - - 70d13e8e by Joachim Breitner at 2021-01-22T19:03:45+01:00 Make haddock more robust to changes to the `Language` data type With the introduction of GHC2021, the `Languages` data type in GHC will grow. In preparation of that (and to avoid changing haddock with each new language), this change makes the code handle extensions to that data type gracefully. (cherry picked from commit c341dd7c9c3fc5ebc83a2d577c5a726f3eb152a5) - - - - - 7d6dd57a by John Ericson at 2021-01-22T22:02:02+00:00 Add `NoGhcTc` instance now that it's not closed - - - - - e5fdaf0a by Alan Zimmerman at 2021-01-23T22:57:44+00:00 Merge pull request haskell/haddock#1293 from obsidiansystems/wip/fix-18936 Add `NoGhcTc` instance now that it's not closed - - - - - 989a1e05 by Oleg Grenrus at 2021-01-24T16:11:46+03:00 Add import list to Data.List - - - - - 368e144a by Ben Gamari at 2021-01-28T22:15:48+01:00 Adapt to "Make PatSyn immutable" - - - - - abe66c21 by Alfredo Di Napoli at 2021-02-01T08:05:35+01:00 Rename pprLogErrMsg to new name - - - - - e600e75c by Hécate Moonlight at 2021-02-05T14:53:00+01:00 Move CI to ghc-9.0 - - - - - dd492961 by Vladislav Zavialov at 2021-02-05T14:53:00+01:00 Update cabal.project and README build instructions - - - - - 31bd292a by Hécate Moonlight at 2021-02-05T15:03:56+01:00 Merge pull request haskell/haddock#1296 from Kleidukos/ghc-9.0 Merge the late additions to ghc-8.10 into ghc-9.0 - - - - - 6388989e by Vladislav Zavialov at 2021-02-05T17:41:57+03:00 Cleanup: fix build warnings - - - - - f99407ef by Daniel Rogozin at 2021-02-05T18:11:48+03:00 type level characters support for haddock (required for haskell/haddock#11342) - - - - - d8c6b26f by Hécate Moonlight at 2021-02-05T17:44:50+01:00 Add a CONTRIBUTING.md file - - - - - 6a01ad98 by Hécate Moonlight at 2021-02-05T17:58:16+01:00 Merge pull request haskell/haddock#1312 from Kleidukos/proper-branch-etiquette Add a CONTRIBUTING.md file - - - - - 955eecc4 by Vladislav Zavialov at 2021-02-05T20:29:00+03:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into ghc-head - - - - - 47b3d6ab by Hécate Moonlight at 2021-02-05T19:09:38+01:00 Amend the CONTRIBUTING.md file - - - - - 23de6137 by Hécate Moonlight at 2021-02-05T19:16:49+01:00 Merge pull request haskell/haddock#1313 from Kleidukos/amend-contributing Amend the CONTRIBUTING.md file - - - - - 69026b59 by Krzysztof Gogolewski at 2021-02-05T23:05:56+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. (cherry picked from commit b4b4d896d2d68d6c48e7db7bfe95c185ca0709cb) - - - - - ea026b78 by Oleg Grenrus at 2021-02-06T17:14:45+01:00 Add import list to Data.List - - - - - 5204326f by Hécate Moonlight at 2021-02-06T17:15:44+01:00 Merge pull request haskell/haddock#1316 from Kleidukos/explicit-imports-to-data-list Add import list to Data.List - - - - - 1f4d2136 by Ben Gamari at 2021-02-06T11:53:31-05:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ghc-head-merge - - - - - 13f0d09a by Ben Gamari at 2021-02-06T11:53:45-05:00 Fix partial record selector warning - - - - - 5c115f7e by Ben Gamari at 2021-02-06T11:55:52-05:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into wip/ghc-head-merge - - - - - b6fd8b75 by Ben Gamari at 2021-02-06T12:01:31-05:00 Merge commit '41964cb2fd54b5a10f8c0f28147015b7d5ad2c02' into wip/ghc-head-merge - - - - - a967194c by Ben Gamari at 2021-02-06T18:30:35-05:00 Merge branch 'wip/ghc-head-merge' into ghc-head - - - - - 1f4c3a91 by MorrowM at 2021-02-07T01:52:33+02:00 Fix search div not scrolling - - - - - 684b1287 by Iñaki García Etxebarria at 2021-02-07T16:13:04+01:00 Add support for labeled module references Support a markdown-style way of annotating module references. For instance -- | [label]("Module.Name#anchor") will create a link that points to the same place as the module reference "Module.Name#anchor" but the text displayed on the link will be "label". - - - - - bdb55a5d by Hécate Moonlight at 2021-02-07T16:18:10+01:00 Merge pull request haskell/haddock#1319 from alexbiehl/alex/compat Backward compat: Add support for labeled module references - - - - - 6ca70991 by Hécate Moonlight at 2021-02-07T16:21:29+01:00 Merge pull request haskell/haddock#1314 from tweag/show-linear-backport Backport haskell/haddock#1238 (linear types) to ghc-9.0 - - - - - d9d73298 by Alex Biehl at 2021-02-07T17:46:25+01:00 Remove dubious parseModLink Instead construct the ModLink value directly when parsing. - - - - - 33b4d020 by Hécate Moonlight at 2021-02-07T17:52:05+01:00 Merge pull request haskell/haddock#1320 from haskell/alex/fix Remove dubious parseModLink - - - - - 54211316 by Hécate Moonlight at 2021-02-07T18:12:07+01:00 Merge pull request haskell/haddock#1318 from MorrowM/ghc-9.0 Fix search div not scrolling - - - - - 19db679e by alexbiehl-gc at 2021-02-07T18:14:46+01:00 Merge pull request haskell/haddock#1317 from bgamari/wip/ghc-head-merge Merge ghc-8.10 into ghc-head - - - - - 6bc1e9e4 by Willem Van Onsem at 2021-02-07T18:25:30+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - c8537cf8 by alexbiehl-gc at 2021-02-07T18:30:40+01:00 Merge pull request haskell/haddock#1322 from haskell/alex/forward-port simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 2d47ae4e by alexbiehl-gc at 2021-02-07T18:39:59+01:00 Merge branch 'ghc-head' into ghc-9.0 - - - - - 849e4733 by Hécate Moonlight at 2021-02-07T18:43:19+01:00 Merge pull request haskell/haddock#1321 from Kleidukos/ghc-9.0 Merge ghc-9.0 into ghc-head - - - - - ee6095d7 by Sylvain Henry at 2021-02-08T11:36:38+01:00 Update for Logger - - - - - 4ad688c9 by Alex Biehl at 2021-02-08T18:11:24+01:00 Merge pull request haskell/haddock#1310 from hsyl20/wip/hsyl20/logger2 Logger refactoring - - - - - 922a9e0e by Ben Gamari at 2021-02-08T12:54:33-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - 991649d2 by Sylvain Henry at 2021-02-09T10:55:17+01:00 Fix to build with HEAD - - - - - a8348dc2 by Hécate Moonlight at 2021-02-09T10:58:51+01:00 Merge pull request haskell/haddock#1327 from hsyl20/wip/hsyl20/logger2 Fix to build with HEAD - - - - - 0abdbca6 by Fendor at 2021-02-09T20:06:15+01:00 Add UnitId to Target record - - - - - d5790a0e by Alex Biehl at 2021-02-11T10:32:32+01:00 Stable sort for (data/newtype) instances - - - - - 8e6036f5 by Alex Biehl at 2021-02-11T10:32:32+01:00 Also make TyLit deterministic - - - - - f76d2945 by Hécate Moonlight at 2021-02-11T11:00:31+01:00 Merge pull request haskell/haddock#1329 from hsyl20/hsyl20/stabe_iface Stable sort for instances - - - - - 5e0469ea by Oleg Grenrus at 2021-02-14T15:28:15+02:00 Add import list to Data.List in Haddock.Interface.Create - - - - - fa57cd24 by Hécate Moonlight at 2021-02-14T17:19:27+01:00 Merge pull request haskell/haddock#1331 from phadej/more-explicit-data-list-imports Add import list to Data.List in Haddock.Interface.Create - - - - - f0cd629c by Hécate Moonlight at 2021-02-21T00:22:01+01:00 Merge pull request haskell/haddock#1311 from fendor/wip/add-targetUnitId-to-target Add UnitId to Target record - - - - - 674ef723 by Joachim Breitner at 2021-02-22T10:39:18+01:00 html-test: Always set language from ghc-9.2 on, the “default” langauge of GHC is expected to change more wildly. To prepare for that (and unblock https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4853), this sets the language for all the test files to `Haskell2010`. This should insolate this test suite against changes to the default. Cherry-picked from https://github.com/haskell/haddock/pull/1341 - - - - - f072d623 by Hécate Moonlight at 2021-02-22T10:56:51+01:00 Merge pull request haskell/haddock#1342 from nomeata/joachim/haskell2010-in-tests-ghc-head html-test: Always set language - - - - - caebbfca by Hécate Moonlight at 2021-02-22T11:53:07+01:00 Clean-up of Interface and Interface.Create's imports and pragmata - - - - - f6caa89d by Hécate Moonlight at 2021-02-22T11:54:58+01:00 Merge pull request haskell/haddock#1345 from Kleidukos/head/fix-interface-imports [ghc-head] Clean-up of Interface and Interface.Create's imports and pragmata - - - - - 7395c9cb by Hécate Moonlight at 2021-02-22T18:44:57+01:00 Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 6e9fb5d5 by Hécate Moonlight at 2021-02-22T18:45:28+01:00 Merge pull request haskell/haddock#1348 from Kleidukos/head/explicit-imports-interface Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 9198b118 by Alan Zimmerman at 2021-02-22T20:04:24+00:00 Context becomes a Maybe in the GHC AST This prevents noLoc's appearing in the ParsedSource. Match the change in GHC. - - - - - 0af20f64 by Hécate Moonlight at 2021-02-23T12:36:12+01:00 Fix the call-site of guessTarget in Interface.hs Explicit the imports from GHC.HsToCore.Docs - - - - - b7886885 by Hécate Moonlight at 2021-02-23T12:37:54+01:00 Merge pull request haskell/haddock#1349 from Kleidukos/fix-interface-guesstarget-call Fix the call-site of guessTarget in Interface.hs - - - - - 9cf041ba by Sylvain Henry at 2021-02-24T11:08:20+01:00 Fix haddockHypsrcTest output in ghc-head - - - - - b194182a by Hécate Moonlight at 2021-02-24T11:12:36+01:00 Merge pull request haskell/haddock#1351 from hsyl20/wip/hsyl20/fix-head Fix haddockHypsrcTest output in ghc-head - - - - - 3ce8b375 by Shayne Fletcher at 2021-03-06T09:55:03-05:00 Add ITproj to parser - - - - - d2abf762 by Ben Gamari at 2021-03-06T19:26:49-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a0f6047d by Andrew Martin at 2021-03-07T11:25:23-05:00 Update for boxed rep - - - - - 6f63c99e by Ben Gamari at 2021-03-10T13:20:21-05:00 Update for "FastString: Use FastMutInt instead of IORef Int" - - - - - e13f01df by Luke Lau at 2021-03-10T15:38:40-05:00 Implement template-haskell's putDoc This catches up to GHC using the new extractTHDocs function, which returns documentation added via the putDoc function (provided it was compiled with Opt_Haddock). Since it's already a map from names -> docs, there's no need to do traversal etc. It also matches the change from the argument map being made an IntMap rather than a Map Int - - - - - 89263d94 by Alan Zimmerman at 2021-03-15T17:15:26+00:00 Match changes in GHC AST for in-tree API Annotations As landed via https://gitlab.haskell.org/ghc/ghc/-/merge_requests/2418 - - - - - 28db1934 by Alan Zimmerman at 2021-03-15T20:40:09+00:00 Change some type family test results. It is not clear to me whether the original was printing incorrectly (since we did not have the TopLevel flag before now), or if this behaviour is expected. For the time being I am assuming the former. - - - - - 7c11c989 by Sylvain Henry at 2021-03-22T10:05:19+01:00 Fix after NameCache changes - - - - - addbde15 by Sylvain Henry at 2021-03-22T10:05:19+01:00 NameCache doesn't store a UniqSupply anymore - - - - - 15ec6cec by Ben Gamari at 2021-03-22T17:53:44-04:00 Bump GHC version to 9.2 - - - - - dbd6aa63 by Hécate Moonlight at 2021-03-24T14:28:36+01:00 Merge pull request haskell/haddock#1365 from hsyl20/wip/hsyl20/iface1 NameCache refactoring - - - - - 2d32da7e by Oleg Grenrus at 2021-03-27T01:12:00+02:00 Specialization of Data.List - - - - - 32b84fa6 by Fendor at 2021-03-27T10:50:17+01:00 Add UnitId to Target record This way we always know to which home-unit a given target belongs to. So far, there only exists a single home-unit at a time, but it enables having multiple home-units at the same time. - - - - - 54bf9f0e by Hécate Moonlight at 2021-03-28T14:08:35+02:00 Merge pull request haskell/haddock#1368 from fendor/target-unit-id-revert Add UnitId to Target record - - - - - 7dea168a by Alan Zimmerman at 2021-03-29T08:45:52+01:00 EPA : Rename ApiAnn to EpAnn - - - - - 72967f65 by Alfredo Di Napoli at 2021-03-29T09:47:01+02:00 pprError changed name in GHC - - - - - 4bc61035 by Alan Zimmerman at 2021-03-29T16:16:27-04:00 EPA : Rename ApiAnn to EpAnn - - - - - 108d031d by Ben Gamari at 2021-03-29T18:49:36-04:00 Merge commit '36418c4f70d7d2b179a77925b3ad5caedb08c9b5' into HEAD - - - - - 1444f700 by Ben Gamari at 2021-03-31T09:18:39-04:00 Merge pull request haskell/haddock#1370 from adinapoli/wip/adinapoli-diag-reason-severity Rename pprError to mkParserErr - - - - - d3087b79 by Ben Gamari at 2021-03-31T11:34:17-04:00 Merge commit 'd8d8024ad6796549a8d3b5512dabf3288d14e30f' into ghc-head - - - - - 170b79e9 by Ben Gamari at 2021-03-31T12:24:56-04:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - db0d6bae by Ben Gamari at 2021-04-10T09:34:35-04:00 Bump GHC version to 9.3 - - - - - a9f2c421 by Alan Zimmerman at 2021-04-19T18:26:46-04:00 Update for EPA changes in GHC (cherry picked from commit cafb48118f7c111020663776845897e225607b41) - - - - - 1ee4b7c7 by Sylvain Henry at 2021-05-11T10:00:06+02:00 Removal of HsVersions.h (#1388) * Update for EPA changes in GHC * Account for HsVersions.h removal Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 79e819e9 by Hécate Moonlight at 2021-05-11T10:14:47+02:00 Revert "Removal of HsVersions.h (#1388)" This reverts commit 72118896464f94d81f10c52f5d9261efcacc57a6. - - - - - 3dbd3f8b by Alan Zimmerman at 2021-05-11T10:15:17+02:00 Update for EPA changes in GHC - - - - - 2ce80c17 by Sylvain Henry at 2021-05-11T10:15:19+02:00 Account for HsVersions.h removal - - - - - 00e4c918 by Christiaan Baaij at 2021-05-13T08:21:56+02:00 Add Haddock support for the OPAQUE pragma (#1380) - - - - - 8f9049b2 by Hécate Moonlight at 2021-05-13T08:40:22+02:00 fixup! Use GHC 9.2 in CI runner - - - - - 27ddec38 by Alan Zimmerman at 2021-05-13T22:51:20+01:00 EPA: match changes from GHC T19834 - - - - - f8a1d714 by Felix Yan at 2021-05-14T17:10:04+02:00 Allow hspec 2.8 (#1389) All tests are passing. - - - - - df44453b by Divam Narula at 2021-05-20T15:42:42+02:00 Update ref, the variables got renamed. (#1391) This is due to ghc/ghc!5555 which caused a change in ModDetails in case of NoBackend. Now the initModDetails is used to recreate the ModDetails from interface and in-memory ModDetails is not used. - - - - - e46bfc87 by Alan Zimmerman at 2021-05-20T19:05:09+01:00 Remove Maybe from HsQualTy Match changes in GHC for haskell/haddock#19845 - - - - - 79bd7b62 by Shayne Fletcher at 2021-05-22T08:20:39+10:00 FieldOcc: rename extFieldOcc to foExt - - - - - 6ed68c74 by Ben Gamari at 2021-05-21T22:29:30-04:00 Merge commit '3b6a8774bdb543dad59b2618458b07feab8a55e9' into ghc-head - - - - - f9a02d34 by Alfredo Di Napoli at 2021-05-24T13:53:00+02:00 New Parser diagnostics interface - - - - - 392807d0 by Ben Gamari at 2021-05-24T09:57:40-04:00 Merge pull request haskell/haddock#1394 from adinapoli/wip/adinapoli-align-ps-messages Align Haddock to use the new Parser diagnostics interface - - - - - 33023cd8 by Ben Gamari at 2021-05-24T11:19:16-04:00 Revert "Add Haddock support for the OPAQUE pragma (#1380)" This reverts commit a1337c599ef7720b0482a25c55f11794112496dc. The GHC patch associated with this change is not yet ready to be merged. - - - - - 8c005af7 by Ben Simms at 2021-05-28T07:56:20+02:00 CI configuration for ghc-head (#1395) - - - - - 1e947612 by Hécate Moonlight at 2021-05-28T12:27:35+02:00 Use GHC 9.2 in CI runner (#1378) - - - - - e6fa10ab by CGenie at 2021-05-31T09:02:13+02:00 Add page about common errors (#1396) * Update index.rst Common errors page * Create common-errors.rst * Update common-errors.rst * Use GHC 9.2 in CI runner (#1378) * [haddock-api] remove .hspec-failures Co-authored-by: Hécate Moonlight <Kleidukos at users.noreply.github.com> - - - - - abc72a8d by Sylvain Henry at 2021-06-01T10:02:06+02:00 Adapt Haddock to Logger and Parser changes (#1399) - - - - - 91373656 by Zubin Duggal at 2021-06-01T20:45:10+02:00 Update haddockHypSrc tests since we now compute slighly more type info (#1397) - - - - - ed712822 by Marcin Szamotulski at 2021-06-02T08:54:33+02:00 Added myself to contributors - - - - - 49fdbcb7 by Marcin Szamotulski at 2021-06-02T08:57:24+02:00 Document multi component support - - - - - 9ddc8d7d by Hécate Moonlight at 2021-06-02T09:35:55+02:00 Merge pull request haskell/haddock#1379 from coot/coot/document-multi-component-support Document multi component support - - - - - 585b5c5e by Ben Simms at 2021-06-02T19:46:54+02:00 Update CONTRIBUTING.md (#1402) - - - - - 1df4a605 by Ben Simms at 2021-06-02T19:47:14+02:00 Update CONTRIBUTING.md (#1403) - - - - - 58ea43d2 by sheaf at 2021-06-02T22:09:06+02:00 Update Haddock Bug873 to account for renaming - - - - - c5d0ab23 by Vladislav Zavialov at 2021-06-10T13:35:42+03:00 HsToken in FunTy, RecConGADT - - - - - 1ae2f40c by Hécate Moonlight at 2021-06-11T11:19:09+02:00 Update the CI badges - - - - - 6fdc4de2 by Sylvain Henry at 2021-06-28T19:21:17+02:00 Fix mkParserOpts (#1411) - - - - - 18201670 by Alfredo Di Napoli at 2021-07-05T07:55:12+02:00 Rename getErrorMessages Lexer import This commit renames the Lexer import in `Hyperlinker.Parser` from `getErrorMessages` to `getPsErrorMessages` to eliminate the ambiguity with the `getErrorMessages` function defined in `GHC.Types.Error`. - - - - - 23173ca3 by Ben Gamari at 2021-07-07T11:31:44-04:00 Merge pull request haskell/haddock#1413 from adinapoli/wip/adinapoli-issue-19920 Rename getErrorMessages Lexer import - - - - - b3dc4ed8 by Alan Zimmerman at 2021-07-28T22:30:59+01:00 EPA: match changes from GHC T19834 (cherry picked from commit 2fec1b44e0ee7e263286709aa528b4ecb99ac6c2) - - - - - 5f177278 by Ben Gamari at 2021-08-06T01:17:37-04:00 Merge commit '2a966c8ca37' into HEAD - - - - - cdd81d08 by Marcin Szamotulski at 2021-08-08T17:19:06+02:00 coot/multiple packages (ghc-9.2) (#1418) - - - - - be0d71f1 by Marcin Szamotulski at 2021-08-16T08:46:03+02:00 coot/multiple package (ghc-head) (#1419) * FromJSON class Aeson style FromJSON class with Parsec based json parser. * doc-index.json file for multiple packages When creating haddock summary page for multiple packages render doc-index.json file using contents of all found 'doc-index.json' files. * Render doc-index.json When rendering html, render doc-index.json file independently of maybe_index_url option. doc-index.json file is useful now even if maybe_index_url is not `Nothing`. * base url option New `Flag_BaseURL` which configures from where static files are loaded (--base-url). If given and not equal "." static files are not coppied, as this indicates that they are not read from the the directory where we'd copy them. The default value is ".". - - - - - 3b09dbdf by Hécate Moonlight at 2021-10-07T23:26:03+02:00 Update GHC 9.2 to latest pre-release in CI - - - - - 7ac55417 by Zubin Duggal at 2021-10-11T12:10:19+02:00 Enable Haddock tests in GHC windows CI (#1428) * testsuite: strip windows line endings for haddock * hyperlinker: Work around double escaping (#19236) * deterministic SCC - - - - - 1cb81f25 by Andrew Lelechenko at 2021-10-12T15:23:19+02:00 haddock-library does not depend on bytestring or transformers (#1426) - - - - - a890b9aa by sheaf at 2021-10-15T22:19:42+02:00 update haddockHypsrcTest for GHC MR !6705 (#1430) - - - - - 42a55c6c by Sylvain Henry at 2021-10-15T22:20:10+02:00 Fix after PkgQual refactoring (#1429) - - - - - 91659238 by Alan Zimmerman at 2021-10-28T18:57:10+01:00 Update for changes in GHC for branch wip/az/no-srcspan-anno-instances - - - - - acf23e60 by Vladislav Zavialov at 2021-11-05T02:09:47+03:00 Do not use forall as an identifier See GHC ticket haskell/haddock#20609 - - - - - c565db0e by Krzysztof Gogolewski at 2021-11-27T02:42:35+01:00 Update after NoExtCon -> DataConCantHappen rename - - - - - b5f55590 by Artem Pelenitsyn at 2021-11-27T11:14:17+01:00 fix CI for 9.2 (#1436) - - - - - 25cd621e by Matthew Pickering at 2021-12-02T11:46:54+00:00 Update html-test for Data.List revert - - - - - 1d5ff85f by malteneuss at 2021-12-15T07:56:55+01:00 Add hint about inline link issue (#1444) - - - - - 791fde81 by Sylvain Henry at 2021-12-16T09:29:51+01:00 Bump ghc-head (#1445) * Update after NoExtCon -> DataConCantHappen rename * Update html-test for Data.List revert * Fix for new Plugins datatype Co-authored-by: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 44236317 by Sylvain Henry at 2021-12-17T09:39:00+01:00 Fix for new Plugins datatype - - - - - 80ada0fa by Hécate Moonlight at 2021-12-17T17:28:48+01:00 Remove ghc-head workflow (#1446) Contributions of GHC glue code are now done on the GHC gitlab, not in the GitHub repo anymore. - - - - - 49e171cd by Matthew Pickering at 2021-12-28T09:47:09+00:00 Remove use of ExtendedModSummary - - - - - 0e91b5ea by askeblad at 2022-01-04T09:18:35+01:00 update URLs - - - - - 9f13c212 by Hécate Moonlight at 2022-02-25T10:19:46+01:00 Fix solver for GHC 9.2 - - - - - 386751a1 by Meng Weng Wong at 2022-02-25T19:19:11+01:00 IDoc link has bitrotted; replaced with web.archive.org cache. (#1454) - - - - - d877cbe6 by Hécate Moonlight at 2022-02-25T19:21:58+01:00 Fix haddock user guide (#1456) - - - - - cc47f036 by Andrew Lelechenko at 2022-03-04T17:29:36+01:00 Allow text-2.0 in haddock-library (#1459) - - - - - 7b3685a3 by malteneuss at 2022-03-07T19:27:24+01:00 Add multi-line style hint to style section (#1460) - - - - - c51088b8 by John Ericson at 2022-03-11T16:46:26+01:00 Fix CollectPass instance to match TTG refactor Companion to GHC !7614 (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7614) - - - - - b882195b by Vladislav Zavialov at 2022-03-14T20:32:30+01:00 Link to (~) - - - - - 877349b8 by Christiaan Baaij at 2022-03-16T09:20:43+01:00 Add Haddock support for the OPAQUE pragma - - - - - 0ea22721 by askeblad at 2022-03-16T09:44:27+01:00 typos (#1464) - - - - - a6d13da1 by Matthew Pickering at 2022-03-22T13:41:17+00:00 Minimum changes needed for compilation with hi-haddock With hi-haddock, of course there is a much large refactoring of haddock which could be achieved but that is left for a future patch which can implemented at any time independently of GHC. - - - - - e7ac9129 by Matthew Pickering at 2022-03-22T21:17:50+00:00 Update test output - - - - - 6d916214 by Matthew Pickering at 2022-03-24T15:06:26+00:00 Merge branch 'wip/opaque_pragma' into 'ghc-head' Add Haddock support for the OPAQUE pragma See merge request ghc/haddock!2 - - - - - 42208183 by Steve Hart at 2022-03-25T20:43:50+01:00 Fix CI (#1467) * CI: Reinstall GHC with docs CI tests were failing because the GHC preinstalled to the CI environment does not include documentation, which is required for running the Haddock tests. This commit causes the CI workflow to reinstall GHC with docs so that tests can succeed. - - - - - 9676fd79 by Steve Hart at 2022-03-25T21:33:34+01:00 Make links in Synopsis functional again (#1458) Commit e41c1cbe9f0476997eac7b4a3f17cbc6b2262faf added a call to e.preventDefault() when handling click events that reach a toggle element. This prevents the browser from following hyperlinks within the Synopsis section when they are clicked by a user. This commit restores functioning hyperlinks within the Synopsis section by removing the call to e.preventDefault(), as it does not appear to be necessary, and removing it increases the flexibility of the details-helper code. - - - - - d1edd637 by sheaf at 2022-04-01T12:02:02+02:00 Keep track of promotion ticks in HsOpTy Keeping track of promotion ticks in HsOpTy allows us to properly pretty-print promoted constructors such as lists. - - - - - 9dcb2dfc by Jakob Brünker at 2022-04-01T15:46:22+00:00 Add support for \cases See merge request ghc/ghc!7873 - - - - - b0412ee5 by askeblad at 2022-04-06T17:47:57+02:00 spelling errors (#1471) - - - - - 6b18829b by Vladislav Zavialov at 2022-04-06T18:53:58+02:00 Rename [] to List - - - - - 2d046691 by Vladislav Zavialov at 2022-04-07T20:25:54+03:00 HsToken ConDeclGADT con_dcolon - - - - - 90b43da4 by Steve Hart at 2022-04-12T13:29:46+02:00 Parse Markdown links at beginning of line within a paragraph (#1470) * Catch Markdown links at beginning of line within paragraph Per Issue haskell/haddock#774, Markdown links were being parsed as ordinary text when they occurred at the beginning of a line other than the first line of the paragraph. This occurred because the parser was not interpreting a left square bracket as a special character that could delimit special markup. A space character was considered a special character, so, if a space occurred at the beginning of the new line, then the parser would interpret the space by itself and then continue parsing, thereby catching the Markdown link. '\n' was not treated as a special character, so the parser did not catch a Markdown link that may have followed. Note that this will allow for Markdown links that are not surrounded by spaces. For example, the following text includes a Markdown link that will be parsed: Hello, world[label](url) This is consistent with how the parser handles other types of markup. * Remove obsolete documentation hint Commit 6b9aeafddf20efc65d3725c16e3fc43a20aac343 should eliminate the need for the workaround suggested in the documentation. - - - - - 5b08312d by Hécate Moonlight at 2022-04-12T13:36:38+02:00 Force ghc-9.2 in the cabal.project - - - - - 0d0ea349 by dependabot[bot] at 2022-04-12T13:57:41+02:00 Bump path-parse from 1.0.5 to 1.0.7 in /haddock-api/resources/html (#1469) Bumps [path-parse](https://github.com/jbgutierrez/path-parse) from 1.0.5 to 1.0.7. - [Release notes](https://github.com/jbgutierrez/path-parse/releases) - [Commits](https://github.com/jbgutierrez/path-parse/commits/v1.0.7) --- updated-dependencies: - dependency-name: path-parse dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 2b9fc65e by dependabot[bot] at 2022-04-12T13:57:54+02:00 Bump copy-props from 2.0.4 to 2.0.5 in /haddock-api/resources/html (#1468) Bumps [copy-props](https://github.com/gulpjs/copy-props) from 2.0.4 to 2.0.5. - [Release notes](https://github.com/gulpjs/copy-props/releases) - [Changelog](https://github.com/gulpjs/copy-props/blob/master/CHANGELOG.md) - [Commits](https://github.com/gulpjs/copy-props/compare/2.0.4...2.0.5) --- updated-dependencies: - dependency-name: copy-props dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - ea98a6fb by Ben Gamari at 2022-04-23T22:54:37-04:00 Update for GHC 9.4 - - - - - 9e11864f by Ben Gamari at 2022-04-25T16:24:31-04:00 Merge remote-tracking branch 'upstream/ghc-9.2' into ghc-head - - - - - f83cc506 by Ben Gamari at 2022-04-25T17:00:25-04:00 Bump ghc version to 9.5 - - - - - e01c2e7d by Ben Gamari at 2022-04-28T16:19:04-04:00 Revert "Bump ghc-head (#1445)" This reverts commit b29a78ef6926101338f62e84f456dac8659dc9d2. This should not have been merged. - - - - - a2b5ee8c by Ben Gamari at 2022-04-28T16:19:24-04:00 Merge commit '2627a86c' into ghc-head - - - - - 0c6fe4f9 by Ben Gamari at 2022-04-29T10:05:54-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-9.4 - - - - - b6e5cb0a by Ben Gamari at 2022-04-29T11:46:06-04:00 Revert "HsToken ConDeclGADT con_dcolon" This reverts commit 24208496649a02d5f87373052c430ea4a97842c5. - - - - - 15a62888 by Ben Gamari at 2022-04-29T15:12:55-04:00 Bump base upper bound - - - - - 165b9031 by Ben Gamari at 2022-04-29T23:58:38-04:00 Update test output - - - - - e0c3e5da by Phil de Joux at 2022-05-02T14:46:38+02:00 Add hlint action .hlint.yaml with ignores & CPP. (#1475) - - - - - ead1158d by Raphael Das Gupta at 2022-05-02T14:46:48+02:00 fix grammar in docs: "can the" → "can be" (#1477) - - - - - cff97944 by Ben Gamari at 2022-05-02T18:38:56-04:00 Allow base-4.17 - - - - - e4ecb201 by Phil de Joux at 2022-05-03T13:14:55+02:00 Remove unused imports that GHC warned about. (#1480) - - - - - 222890b1 by Phil de Joux at 2022-05-03T13:15:46+02:00 Follow hlint suggestion to remove redundant bang. (#1479) - - - - - 058b671f by Phil de Joux at 2022-05-03T13:34:04+02:00 Follow hlint, remove language pragmas in libs. (#1478) - - - - - 0a645049 by Ben Simms at 2022-05-03T14:19:24+02:00 Keep track of ordered list indexes and render them (#1407) * Keep track of ordered list indexes and render them * Rename some identifiers to clarify - - - - - f0433304 by Norman Ramsey at 2022-05-04T15:13:34-04:00 update for changes in GHC API - - - - - 3740cf71 by Emily Martins at 2022-05-06T18:23:48+02:00 Add link to the readthedocs in cabal description to show on hackage. (cherry picked from commit 52e2d40d47295c02d3181aac0c53028e730f1e3b) - - - - - 5d754f1e by Hécate Moonlight at 2022-05-06T18:44:57+02:00 remove Bug873 - - - - - 968fc267 by Hécate Moonlight at 2022-05-06T18:48:28+02:00 Ignore "Use second" HLint suggestion. It increases laziness. - - - - - 02d14e97 by Jade Lovelace at 2022-05-07T17:42:08+02:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` - - - - - b22b87ed by Artem Pelenitsyn at 2022-05-08T16:19:47+02:00 fix parsing trailing quotes in backticked identifiers (#1408) (#1483) - - - - - 80ae107b by Alex Biehl at 2022-05-08T16:37:16+02:00 Fix "Defined by not used" error (cherry picked from commit 6e02a620a26c3a44f98675dd1b93b08070c36c0a) - - - - - 4c838e84 by Hécate Moonlight at 2022-05-08T16:37:16+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - fc9827b4 by Hécate Moonlight at 2022-05-08T16:40:40+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - b153b555 by Xia Li-yao at 2022-05-20T17:52:42+02:00 Hide synopsis from search when hidden (#1486) Fix haskell/haddock#1451 - - - - - f3e38b85 by Marcin Szamotulski at 2022-05-21T23:32:31+02:00 Allow to hide interfaces when rendering multiple components (#1487) This is useful when one wishes to `--gen-contents` when rendering multiple components, but one does not want to render all modules. This is in particular useful when adding base package. - - - - - f942863b by Marcin Szamotulski at 2022-05-24T08:29:59+02:00 Check if doc-index.json exists before reading it (#1488) - - - - - 31e92982 by Marcin Szamotulski at 2022-05-25T16:22:13+02:00 Version bump 2.26.1 (#1489) * Version bump 2.26.1 We extended format accepted by `--read-interface` option, which requires updating the minor version. * Update documentation of --read-interface option - - - - - 7cc873e0 by sheaf at 2022-05-25T16:42:31+02:00 Updated HaddockHypsrcTest output for record update changes (MR !7981) - - - - - cd196942 by Marcin Szamotulski at 2022-05-25T20:28:47+02:00 Use visibility to decide which interfaces are included in quickjump (#1490) This is also consistent with how html index is build. See haskell/cabal#7669 for rationale behind this decision. - - - - - 00c713c5 by Hécate Moonlight at 2022-05-26T17:09:15+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 2f3039f1 by Hécate Moonlight at 2022-05-26T17:10:59+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 63a5650c by romes at 2022-05-31T12:43:22+01:00 TTG: Match new GHC AST - - - - - dd7d1617 by romes at 2022-06-02T16:11:00+01:00 Update for IE changes in !8228 - - - - - c23aaab7 by cydparser at 2022-06-06T08:48:14+02:00 Fix and improve CI (#1495) * Pin GHC version before creating the freeze file * Use newest action versions * Improve caching * Avoid unnecessarily reinstalling GHC * Use GHC 9.2.2 for CI Co-authored-by: Cyd Wise <cwise at tripshot.com> - - - - - c156fa77 by Hécate Moonlight at 2022-06-06T11:59:35+02:00 Add Mergify configuration (#1496) - - - - - 2dba4188 by Hécate Moonlight at 2022-06-06T16:12:50+02:00 Bump haddock's version in cabal file to 2.26.1 (#1497) - - - - - d7d4b8b9 by Marcin Szamotulski at 2022-06-07T06:09:40+00:00 Render module tree per package in the content page (#1492) * Render module tree per package in the content page When rendering content page for multiple packages it is useful to split the module tree per package. Package names in this patch are inferred from haddock's interface file names. * Write PackageInfo into interface file To keep interface file format backward compatible, instead of using `Binary` instance for `InterfaceFile` we introduce functions to serialise and deserialise, which depends on the interface file version. - - - - - 77765665 by Mike Pilgrem at 2022-06-12T21:57:19+01:00 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - b0e079b0 by mergify[bot] at 2022-06-13T11:49:37+00:00 Merge pull request haskell/haddock#1108 from mpilgrem/fix783 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - 6c0292b1 by Hécate Moonlight at 2022-06-21T17:21:08+02:00 Update the contribution guide - - - - - e413b9fa by dependabot[bot] at 2022-06-21T23:38:19+02:00 Bump shell-quote from 1.6.1 to 1.7.3 in /haddock-api/resources/html (#1500) Bumps [shell-quote](https://github.com/substack/node-shell-quote) from 1.6.1 to 1.7.3. - [Release notes](https://github.com/substack/node-shell-quote/releases) - [Changelog](https://github.com/substack/node-shell-quote/blob/master/CHANGELOG.md) - [Commits](https://github.com/substack/node-shell-quote/compare/1.6.1...1.7.3) --- updated-dependencies: - dependency-name: shell-quote dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 29d0ef70 by romes at 2022-07-06T11:29:39+02:00 TTG: AST Updates for !8308 - - - - - 1bae7c87 by Alan Zimmerman at 2022-07-06T22:50:43+01:00 Match GHC changes for T21805 This brings in a newtype for FieldLabelString - - - - - 6fe8b988 by Phil de Joux at 2022-07-16T20:54:26+00:00 Bump hlint version to 3.4.1, the version with counts. (#1503) Redo the counts available with the --default option. - - - - - 48fb43af by Phil de Joux at 2022-07-19T09:32:55+02:00 Follow hlint suggestion: unused LANGUAGE pragma. (#1504) * Follow hlint suggestion: unused LANGUAGE pragma. * Ignore within modules to pass linting and pass tests. - - - - - c1cf1fa7 by Phil de Joux at 2022-07-24T13:45:59+02:00 Follow hlint suggestion: redundant $. (#1505) * Follow hlint suggestion: redundant $. * Remove $ and surplus blank lines in Operators. - - - - - 74777eb2 by Jade Lovelace at 2022-07-29T11:02:41+01:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` (cherry picked from commit ab53ccf089ea703b767581ac14be0f6c78a7678a) - - - - - faa4cfcf by Hécate Moonlight at 2022-07-29T20:31:20+02:00 Merge pull request haskell/haddock#1516 from duog/9-4-backport-fix-hyperlinks Backport 9-4: Fix hyperlinks to external items and modules (#1482) - - - - - 5d2450f3 by Ben Gamari at 2022-08-05T17:41:15-04:00 Merge remote-tracking branch 'origin/ghc-9.4' - - - - - 63954f73 by Ben Gamari at 2022-08-05T19:08:36-04:00 Clean up build and testsuite for GHC 9.4 - - - - - d4568cb8 by Hécate Moonlight at 2022-08-05T19:10:49-04:00 Bump the versions - - - - - 505583a4 by Ben Gamari at 2022-08-06T13:58:27-04:00 Merge pull request haskell/haddock#1518 from bgamari/wip/ghc-9.4-merge Merge GHC 9.4 into `main` - - - - - 5706f6a4 by Ben Gamari at 2022-08-06T22:57:21-04:00 html-test: Testsuite changes for GHC 9.4.1 - - - - - 5f2a45a2 by Ben Gamari at 2022-08-15T14:33:05-04:00 doc: Fix a few minor ReST issues Sphinx was complaining about too-short title underlines. - - - - - 220e6410 by Ben Gamari at 2022-08-15T14:41:24-04:00 Merge branch 'main' into ghc-head - - - - - fbeb1b02 by Ben Gamari at 2022-08-15T14:45:16-04:00 Updates for GHC 9.5 - - - - - eee562eb by Vladislav Zavialov at 2022-08-15T14:46:13-04:00 HsToken ConDeclGADT con_dcolon - - - - - c5f073db by Ben Gamari at 2022-08-15T16:55:35-04:00 Updates for GHC 9.5 - - - - - 3f7ab242 by Vladislav Zavialov at 2022-08-15T16:55:35-04:00 HsToken ConDeclGADT con_dcolon - - - - - a18e473d by Ben Gamari at 2022-08-16T08:35:19-04:00 Merge branch 'wip/ghc-head-bump' into ghc-head - - - - - af0ff3a4 by M Farkas-Dyck at 2022-09-15T21:16:05+00:00 Disuse `mapLoc`. - - - - - a748fc38 by Matthew Farkas-Dyck at 2022-09-17T10:44:18+00:00 Scrub partiality about `NewOrData`. - - - - - 2758fb6c by John Ericson at 2022-09-18T03:27:37+02:00 Test output changed because of change to `base` Spooky, but I guess that is intended? - - - - - a7eec128 by Torsten Schmits at 2022-09-21T11:06:55+02:00 update tests for the move of tuples to GHC.Tuple.Prim - - - - - 461e7b9d by Ross Paterson at 2022-09-24T22:01:25+00:00 match implementation of GHC proposal haskell/haddock#106 (Define Kinds Without Promotion) - - - - - f7fd77ef by sheaf at 2022-10-17T14:53:01+02:00 Update Haddock for GHC MR !8563 (configuration of diagnostics) - - - - - 3d3e85ab by Vladislav Zavialov at 2022-10-22T23:04:06+03:00 Class layout info - - - - - cbde4cb0 by Simon Peyton Jones at 2022-10-25T23:19:18+01:00 Adapt to Constraint-vs-Type See haskell/haddock#21623 and !8750 - - - - - 7108ba96 by Tom Smeding at 2022-11-01T22:33:23+01:00 Remove outdated footnote about module re-exports The footnote is invalid with GHC 9.2.4 (and possibly earlier): the described behaviour in the main text works fine. - - - - - 206c6bc7 by Hécate Moonlight at 2022-11-01T23:00:46+01:00 Merge pull request haskell/haddock#1534 from tomsmeding/patch-1 - - - - - a57b4c4b by Andrew Lelechenko at 2022-11-21T00:39:52+00:00 Support mtl-2.3 - - - - - e9d62453 by Simon Peyton Jones at 2022-11-25T13:49:12+01:00 Track small API change in TyCon.hs - - - - - eb1c73f7 by Ben Gamari at 2022-12-07T08:46:21-05:00 Update for GhC 9.6 - - - - - 063268dd by Ben Gamari at 2022-12-07T11:26:32-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 4ca722fe by Ben Gamari at 2022-12-08T14:43:26-05:00 Bump bounds to accomodate base-4.18 - - - - - 340b7511 by Vladislav Zavialov at 2022-12-10T12:31:28+00:00 HsToken in HsAppKindTy - - - - - 946226ec by Ben Gamari at 2022-12-13T20:12:56-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - fd8faa66 by Ben Gamari at 2022-12-22T13:44:28-05:00 Bump GHC version to 9.7 - - - - - 2958aa9c by Ben Gamari at 2022-12-22T14:49:16-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 9e0fefd8 by Andrei Borzenkov at 2023-01-30T14:02:04+04:00 Rename () to Unit, Rename (,,...,,) to Tuple<n> - - - - - eb3968b5 by Ben Gamari at 2023-03-10T02:32:43-05:00 Bump versions for ghc-9.6 release - - - - - 4aeead36 by Adam Gundry at 2023-03-23T13:53:47+01:00 Adapt to warning categories changes - - - - - 642d8d60 by sheaf at 2023-03-29T13:35:56+02:00 Adapt to record field refactor This commit adapts to the changes in GHC MR !8686, which overhauls the treatment of record fields in the renamer, adding separate record field namespaces and entirely removing the GreName datatype. - - - - - ac8d4333 by doyougnu at 2023-03-29T11:11:44-04:00 Update UniqMap API - - - - - 7866fc86 by Ben Orchard at 2023-04-20T11:29:33+02:00 update classify with new tokens - - - - - ffcdd683 by Finley McIlwaine at 2023-04-24T09:36:18-06:00 Remove index-state - - - - - 05b70982 by Finley McIlwaine at 2023-04-26T08:16:31-06:00 `renameInterface` space leak fixes - Change logic for accumulation of names for which link warnings will be generated - Change handling of `--ignore-link-symbol` to allow qualified and unqualified names. Added to CHANGES.md - Some formatting changes and comments here and there - - - - - e5697d7c by Finley McIlwaine at 2023-04-27T18:46:36-06:00 Messy things - ghc-debug dependency and instrumentation - cabal.project custom with-compiler - hie.yaml files - traces and such - - - - - 0b8ef80b by Finley McIlwaine at 2023-05-02T18:08:52-06:00 Stop retaining GRE closures GRE closures should never be necessary to Haddock, so we never want to keep them on the heap. Despite that, they are retained by a lot of the data structures that Haddock makes use of. - Attempt to fix that situation by adding strictness to various computations and pruning the `ifaceInstances` field of `Interface` to a much thinner data type. - Removes the `ifaceFamInstances` field, as it was never used. - Move some of the attach instances types (e.g. `SimpleType`) to the types module - - - - - 8bda991b by Finley McIlwaine at 2023-05-08T16:07:51-06:00 Memory usage fixes - Refactor `ifaceDeclMap` to drastically reduce memory footprint. We no longer store all declarations associated with a given name, since we only cared to determine if the only declaration associated with a name was a value declaration. Change the `DeclMap` type to better reflect this. - Drop pre-renaming export items after the renaming step. Since the Hoogle backend used the pre-renamed export items, this isn't trivial. We now generate Hoogle output for exported declarations during the renaming step (if Hoogle output /should/ be generated), and store that with the renamed export item. - Slightly refactor Hoogle backend to handle the above change and allow for early generation of Hoogle output. - Remove the `ifaceRnDocMap` and `ifaceRnArgMap` fields of the `Interface` type, as they were never used. - Remove some unnecessary strictness - Remove a lot of dead code from `Syb` module - - - - - 1611ac0c by Finley McIlwaine at 2023-05-09T11:51:57-06:00 Unify ErrMsgM and IfM - Delete ErrMsgM, stop accumulating warnings in a writer - Make IfM a state monad, print warnings directly to stdout, move IfM type into types module - Drop ErrMsg = String synonym - Unset IORefs from plugin after they are read, preventing unnecessary retention of interfaces - - - - - 42d696ab by Finley McIlwaine at 2023-05-11T15:52:07-06:00 Thunk leak fixes The strictness introduced in this commit was motivated by observing thunk leaks in the eventlog2html output. - Refactor attach instances list comprehension to avoid large intermediate thunks - Refactor some HTML backend list comprehensions to avoid large intermediate thunks - Avoid thunks accumulating in documentation types or documentation parser - A lot of orphan NFData instances to allow us to force documentation values - - - - - 68561cf6 by Finley McIlwaine at 2023-05-11T17:02:10-06:00 Remove GHC debug dep - - - - - 10519e3d by Finley McIlwaine at 2023-05-15T12:40:48-06:00 Force HIE file path Removes a potential retainer of `ModSummary`s - - - - - 1e4a6ec6 by Finley McIlwaine at 2023-05-15T14:20:34-06:00 Re-add index-state, with-compiler, delete hie.yamls - - - - - a2363fe9 by Hécate Moonlight at 2023-05-15T22:45:16+02:00 Merge pull request haskell/haddock#1594 from FinleyMcIlwaine/finley/ghc-9.6-mem-fixes Reduce memory usage - - - - - e8a78383 by Finley McIlwaine at 2023-05-17T12:19:16-06:00 Merge branch ghc-9.6 into ghc-head - - - - - 22e25581 by Finley McIlwaine at 2023-05-17T12:20:23-06:00 Merge branch 'ghc-head' of gitlab.haskell.org:ghc/haddock into ghc-head - - - - - 41bbf0df by Bartłomiej Cieślar at 2023-05-24T08:57:58+02:00 changes to the WarningTxt cases Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - c686ba9b by Hécate Moonlight at 2023-06-01T14:03:02-06:00 Port the remains of Hi-Haddock - - - - - 9d8a85fd by Hécate Moonlight at 2023-06-01T14:03:06-06:00 Stdout for tests - - - - - 36331d07 by Finley McIlwaine at 2023-06-01T14:06:02-06:00 Formatting, organize imports - - - - - a06059b1 by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix empty context confusion in Convert module - - - - - 379346ae by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix associated type families in Hoogle output - - - - - fc6ea7ed by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix test refs Accept several changes in Hoogle tests: Pretty printing logic no longer prints the `(Proxy (Proxy (...))` chain in Bug806 with parentheses. Since this test was only meant to verify that line breaks do not occur, accept the change. `tyThingToLHsDecl` is called for class and data declarations, which ends up "synifying" the type variables and giving unlifted types kind signatures. As a result, type variables of kind `Type -> Type` are now printed with kind signatures in Hoogle output. This could be changed by manually drop kind signatures from class variables in the Hoogle backend if the behavior is deemed unacceptable. Sometimes subordinate declarations are exported separate from their parent declarations (e.g. record selectors). In this case, a type signature is cobbled together for the export item in `extractDecl`. Since this type signature is very manually constructed, it may lack kind signatures of decls constructed from `tyThingToLHsDecl`. An example of this is the `type-sigs` Hoogle test. Change `*` to `Type` in Hoogle test refs. I don't think this will break Hoogle behavior, since it appears to not consider type signatures in search. I have not fully verified this. - - - - - e14b7e58 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix LaTeX backend test refs Changes to GHC pretty printing code have resulted in some differences to Haddock's LaTeX output. - Type variables are printed explicitly quantified in the LinearTypes test - Wildcard types in type family equations are now printed numbered, e.g. _1 _2, in the TypeFamilies3 test - Combined signatures in DefaultSignatures test are now documented as separate signatures - - - - - 41b5b296 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and test source updates - Stop using kind `*` in html test sources - Add TypeOperators where necessary to avoid warnings and future errors - Rename some test modules to match their module names - - - - - c640e2a2 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix missing deprecation warnings on record fields `lookupOccEnv` was used to resolve `OccNames` with warnings attached, but it doesn't look in the record field namespace. Thus, if a record field had a warning attached, it would not resolve and the warning map would not include it. This commit fixes by using `lookupOccEnv_WithFields` instead. - - - - - fad0c462 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and some comments - - - - - 751fd023 by Finley McIlwaine at 2023-06-01T14:11:41-06:00 Accept HTML test diffs All diffs now boil down to the expected differences resulting from declarations being reified from TyThings in hi-haddock. Surface syntax now has much less control over the syntax used in the documentation. - - - - - d835c845 by Finley McIlwaine at 2023-06-01T14:11:45-06:00 Adapt to new load' type - - - - - dcf776c4 by Finley McIlwaine at 2023-06-01T14:13:13-06:00 Update mkWarningMap and moduleWarning - - - - - 8e8432fd by Finley McIlwaine at 2023-06-01T14:28:54-06:00 Revert load' changes - - - - - aeb2982c by Finley McIlwaine at 2023-06-01T14:40:24-06:00 Accept change to Instances test in html-test Link to Data.Tuple instead of GHC.Tuple.Prim - - - - - 8adfdbac by Finley McIlwaine at 2023-06-01T15:53:17-06:00 Reset ghc dep to ^>= 9.6 - - - - - 2b1ce93d by Finley McIlwaine at 2023-06-06T07:50:04-06:00 Update CHANGES.md, user guide, recomp avoidance * Add --trace-args flag for tracing arguments received to standard output * Avoid recompiling due to changes in optimization flags * Update users guide and changes.md - - - - - f3da6676 by Finley McIlwaine at 2023-06-06T14:12:56-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - bf36c467 by Matthew Pickering at 2023-06-07T10:16:09+01:00 Revert back to e16e20d592a6f5d9ed1af17b77fafd6495242345 Neither of these MRs are ready to land yet which causes issues with other MRs which are ready to land and need haddock changes. - - - - - 421510a9 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 atSign has no unicode variant Prior to this change, atSign was defined as follows: atSign unicode = text (if unicode then "@" else "@") Yes, this is the same symbol '\64' and not your font playing tricks on you. Now we define: atSign = char '@' Both the LaTeX and the Xhtml backend are updated accordingly. - - - - - 3785c276 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 LaTeX: fix printing of type variable bindings Consider this type signature: kindOf :: forall {k} (a :: k). Proxy a -> Proxy k Prior to this fix, the LaTeX backend rendered it like this: kindOf :: forall k a. Proxy a -> Proxy k Now we preserve explicit specificity and kind annotations. - - - - - 0febf3a8 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 Add support for invisible binders in type declarations - - - - - 13e33bb3 by Finley McIlwaine at 2023-06-08T07:51:59-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - 3e5340ce by Finley McIlwaine at 2023-06-08T07:54:27-06:00 Add note about stubdir to recompilation docs - - - - - db7e84dc by Finley at 2023-06-08T08:11:03-06:00 Merge pull request haskell/haddock#1597 from haskell/finley/hi-haddock-9.6 hi-haddock for ghc 9.6 - - - - - 4e085d17 by Finley McIlwaine at 2023-06-14T13:41:06-06:00 Replace SYB traversals - - - - - 7b39aec5 by Finley McIlwaine at 2023-06-14T14:20:17-06:00 Test ref accepts, remove unused HaddockClsInst - - - - - df9c2090 by Finley McIlwaine at 2023-06-15T08:02:51-06:00 Use batchMsg for progress reporting during load With hi-haddock as is, there is an awkward silence during the load operation. This commit makes haddock use the default `batchMsg` Messager for progress reporting, and makes the default GHC verbosity level 1, so the user can see what GHC is doing. - - - - - f23679a8 by Hécate Moonlight at 2023-06-15T20:31:53+02:00 Merge pull request haskell/haddock#1600 from haskell/finley/hi-haddock-optim - - - - - a7982192 by Finley McIlwaine at 2023-06-15T15:02:16-06:00 hi-haddock squashed - - - - - c34f0c8d by Finley McIlwaine at 2023-06-15T16:22:03-06:00 Merge remote-tracking branch 'origin/ghc-9.6' into finley/hi-haddock-squashed - - - - - 40452797 by Bartłomiej Cieślar at 2023-06-16T12:26:04+02:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - e58673bf by Ben Gamari at 2023-06-16T09:33:35-04:00 Bump GHC version to 9.8 - - - - - 74bdf972 by Ben Gamari at 2023-06-16T09:36:18-04:00 Merge commit 'fcaaad06770a26d35d4aafd65772dedadf17669c' into ghc-head - - - - - 418ee3dc by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Remove NFData SourceText, IfaceWarnings updates The NFData SourceText instance is now available in GHC Handle mod_iface mi_warns now being IfaceWarnings - - - - - 62f31380 by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Accept Instances.hs test output Due to ghc!10469. - - - - - a8f2fc0e by Ben Gamari at 2023-06-20T15:48:08-04:00 Test fixes for "Fix associated data family doc structure items" Associated data families were being given their own export DocStructureItems, which resulted in them being documented separately from their classes in haddocks. This commit fixes it. - - - - - cb1ac33e by Bartłomiej Cieślar at 2023-06-21T12:56:02-04:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - 9933e10b by Ben Gamari at 2023-06-21T12:56:02-04:00 Bump GHC version to 9.8 - - - - - fe8c18b6 by Ben Gamari at 2023-06-21T15:36:29-04:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - c61a0d5b by Ben Gamari at 2023-06-21T16:10:51-04:00 Bump GHC version to 9.9 - - - - - 0c2a756e by sheaf at 2023-07-07T13:45:12+02:00 Avoid incomplete record update in Haddock Hoogle This commit avoids running into an incomplete record update warning in the Hoogle backend of Haddock. This was only noticed now, because incomplete record updates were broken in GHC 9.6. Now that they are fixed, we have to avoid running into them! - - - - - f9b952a7 by Ben Gamari at 2023-07-21T11:58:05-04:00 Bump base bound to <4.20 For GHC 9.8. - - - - - 1b27e151 by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Check for puns (see ghc#23368) - - - - - 457341fd by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Remove fake exports for (~), List, and Tuple<n> The old reasoning no longer applies, nowadays those names can be mentioned in export lists. - - - - - bf3dcddf by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Fix pretty-printing of Solo and MkSolo - - - - - 495b2241 by Matthew Pickering at 2023-09-01T13:02:07+02:00 Fix issue with duplicate reexported definitions (T23616) When a class method was reexported, it's default methods were also showing up in the generated html page. The simplest and most non-invasive fix is to not look for the default method if we are just exporting the class method.. because the backends are just showing default methods when the whole class is exported. In general it would be worthwhile to rewrite this bit of code I think as the logic and what gets included is split over `lookupDocs` and `availExportDecl` it would be clearer to combine the two. The result of lookupDocs is always just passed to availExportDecl so it seems simpler and more obvious to just write the function directly. - - - - - 6551824d by Finley McIlwaine at 2023-09-05T13:06:57-07:00 Remove fake export of `FUN` from Prelude This prevents `data FUN` from being shown at the top of the Prelude docs. Fixes \#23920 on GHC. - - - - - 9ab5a448 by Alan Zimmerman at 2023-09-08T18:26:53+01:00 Match changes in wip/az/T23885-unicode-funtycon - - - - - 4d08364e by Alan Zimmerman at 2023-10-31T19:46:45+00:00 EPA: match changes in GHC - EPA: Comments in AnchorOperation - EPA: Remove EpaEofComment - - - - - e7da0d25 by Alan Zimmerman at 2023-11-05T11:20:31+00:00 EPA: match changes in GHC, l2l cleanup - - - - - 4ceac14d by Alan Zimmerman at 2023-11-11T15:16:41+00:00 EPA: Replace Anchor with EpaLocation Match GHC - - - - - 94fb8d47 by Alan Zimmerman at 2023-11-29T18:10:26+00:00 Match GHC, No comments in EpaDelta for comments - - - - - 32d208e1 by Vladislav Zavialov at 2023-12-12T20:41:36+03:00 EPA: Match changes to LHsToken removal - - - - - eebdd316 by Apoorv Ingle at 2024-01-23T13:49:12+00:00 Changes for haskell/haddock#18324 - - - - - ae856a82 by Matthew Pickering at 2024-02-05T12:22:39+00:00 ghc-internals fallout - - - - - f8429266 by Jade at 2024-02-08T14:56:50+01:00 Adjust test for ghc MR !10993 - - - - - 6d1e2386 by Alan Zimmerman at 2024-02-13T22:00:28+03:00 EPA: Match changes to HsParTy and HsFunTy - - - - - 9c588f19 by Fendor at 2024-02-14T11:05:36+01:00 Adapt to GHC giving better Name's for linking - - - - - 778e1db3 by Andrei Borzenkov at 2024-02-16T16:12:07+03:00 Namespace specifiers for fixity signatures - - - - - 826c5b47 by Torsten Schmits at 2024-02-21T13:17:05+01:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 2cff14d5 by Ben Gamari at 2024-02-22T09:35:56-05:00 Bump bounds - - - - - f49376b3 by Ben Gamari at 2024-02-22T09:35:56-05:00 Allow `@since` annotations in export lists Here we extend Haddock to admit `@since` annotations in export lists. These can be attached to most export list items (although not subordinate lists). These annotations supercede the declaration's `@since` annotation in produced Haddocks. - - - - - b5aa93df by Ben Gamari at 2024-02-22T12:09:06-05:00 Allow package-qualified @since declarations - - - - - 8f5957f2 by Ben Gamari at 2024-02-22T13:55:19-05:00 Documentation changes from ghc-internal restructuring Previously many declarations (e.g. `Int`) were declared to have a "home" in `Prelude`. However, now Haddock instead chooses to put these in more specific homes (e.g. `Data.Int`). Given that the "home" decision is driven by heuristics and in general these changes seem quite reasonable I am accepting them: * `Int` moved from `Prelude` to `Data.Int` * `(~)` moved from `Prelude` to `Data.Type.Equality` * `Type` moved from `GHC.Types` to `Data.Kind` * `Maybe` moved from `Prelude` to `Data.Maybe` * `Bool` moved from `Prelude` to `Data.Bool` * `Ordering` moved from `Prelude` to `Data.Ord` As well, more identifiers are now hyperlinked; it's not immediately clear *why*, but it is an improvement nevertheless. - - - - - ec33fec3 by Ben Gamari at 2024-02-22T20:36:24-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 30cfd251 by Torsten Schmits at 2024-02-24T13:00:42-05:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 732db81d by Ben Gamari at 2024-02-24T19:12:18-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 86bf7010 by Ben Gamari at 2024-02-27T19:28:10-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 4b6e76b5 by Patrick at 2024-03-07T22:09:30+08:00 fix haskell/haddock#24493, with module name introduced in hieAst The accompanies haddoc PR with GHC PR https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12153 Two things have been done: 1. Link is introduced to every `X` in `module X where`, since we introduce the module name to HieAst, 2. `{-# LINE 4 "hypsrc-test/src/PositionPragmas.hs" #-}` is added before the `module PositionPragmas where` in ` hypsrc-test/ref/src/PositionPragmas.html `.It ensures only a single hieAst for file `hypsrc-test/src/PositionPragmas.hs` is generated. - - - - - 635abccc by Ben Gamari at 2024-03-08T17:09:06-05:00 Bump ghc version to 9.10 - - - - - 5b934048 by Ben Gamari at 2024-03-08T18:50:12-05:00 Bump base upper bound - - - - - b30d134e by Ben Gamari at 2024-03-08T18:50:44-05:00 Testsuite output update - - - - - 9bdf3586 by Ben Gamari at 2024-03-09T21:37:44-05:00 Merge branch 'ghc-9.10' into ghc-head - - - - - cec76981 by Ben Gamari at 2024-03-09T21:54:00-05:00 Bump GHC version to 9.11 - - - - - 4c59feb7 by Ben Gamari at 2024-03-09T22:15:01-05:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - bee54c24 by Krzysztof Gogolewski at 2024-04-19T11:13:00+02:00 Update quantification order following GHC haskell/haddock#23764 - - - - - 2814eb89 by Ben Gamari at 2024-04-19T18:57:05+02:00 hypsrc-test: Fix output of PositionPragmas.html - - - - - a27c6a49 by Fendor at 2024-04-22T10:13:03+02:00 Adapt to UserData split - - - - - 1efc5a7a by Fendor at 2024-04-22T10:13:03+02:00 Adapt to BinHandle split - - - - - c62239b7 by Sylvain Henry at 2024-04-29T10:35:00+02:00 Fix tests for T22229 - - - - - 649c24b9 by Oleg Grenrus at 2024-05-03T20:45:42-04:00 Expose constructors of SNat, SChar and SSymbol in ghc-internal - - - - - d603f199 by Mikolaj Konarski at 2024-05-03T20:46:19-04:00 Add DCoVarSet to PluginProv (!12037) - - - - - ba480026 by Serge S. Gulin at 2024-05-03T20:47:01-04:00 JS: Enable more efficient packing of string data (fixes #24706) - - - - - be1e60ee by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Track in-scope variables in ruleCheckProgram This small patch fixes #24726, by tracking in-scope variables properly in -drule-check. Not hard to do! - - - - - 58408c77 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Add a couple more HasCallStack constraints in SimpleOpt Just for debugging, no effect on normal code - - - - - 70e245e8 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Add comments to Prep.hs This documentation patch fixes a TODO left over from !12364 - - - - - e5687186 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Use HasDebugCallStack, rather than HasCallStack - - - - - 631cefec by Cheng Shao at 2024-05-03T20:48:17-04:00 driver: always merge objects when possible This patch makes the driver always merge objects with `ld -r` when possible, and only fall back to calling `ar -L` when merge objects command is unavailable. This completely reverts !8887 and !12313, given more fixes in Cabal seems to be needed to avoid breaking certain configurations and the maintainence cost is exceeding the behefits in this case :/ - - - - - 1dacb506 by Ben Gamari at 2024-05-03T20:48:53-04:00 Bump time submodule to 1.14 As requested in #24528. ------------------------- Metric Decrease: ghc_bignum_so rts_so Metric Increase: cabal_syntax_dir rts_so time_dir time_so ------------------------- - - - - - 4941b90e by Ben Gamari at 2024-05-03T20:48:53-04:00 Bump terminfo submodule to current master - - - - - 43d48b44 by Cheng Shao at 2024-05-03T20:49:30-04:00 wasm: use scheduler.postTask() for context switch when available This patch makes use of scheduler.postTask() for JSFFI context switch when it's available. It's a more principled approach than our MessageChannel based setImmediate() implementation, and it's available in latest version of Chromium based browsers. - - - - - 08207501 by Cheng Shao at 2024-05-03T20:50:08-04:00 testsuite: give pre_cmd for mhu-perf 5x time - - - - - bf3d4db0 by Alan Zimmerman at 2024-05-03T20:50:43-04:00 EPA: Preserve comments for pattern synonym sig Closes #24749 - - - - - c49493f2 by Matthew Pickering at 2024-05-04T06:02:57-04:00 tests: Widen acceptance window for dir and so size tests These are testing things which are sometimes out the control of a GHC developer. Therefore we shouldn't fail CI if something about these dependencies change because we can't do anything about it. It is still useful to have these statistics for visualisation in grafana though. Ticket #24759 - - - - - 9562808d by Matthew Pickering at 2024-05-04T06:02:57-04:00 Disable rts_so test It has already manifested large fluctuations and destabilising CI Fixes #24762 - - - - - fc24c5cf by Ryan Scott at 2024-05-04T06:03:33-04:00 unboxedSum{Type,Data}Name: Use GHC.Types as the module Unboxed sum constructors are now defined in the `GHC.Types` module, so if you manually quote an unboxed sum (e.g., `''Sum2#`), you will get a `Name` like: ```hs GHC.Types.Sum2# ``` The `unboxedSumTypeName` function in `template-haskell`, however, mistakenly believes that unboxed sum constructors are defined in `GHC.Prim`, so `unboxedSumTypeName 2` would return an entirely different `Name`: ```hs GHC.Prim.(#|#) ``` This is a problem for Template Haskell users, as it means that they can't be sure which `Name` is the correct one. (Similarly for `unboxedSumDataName`.) This patch fixes the implementations of `unboxedSum{Type,Data}Name` to use `GHC.Types` as the module. For consistency with `unboxedTupleTypeName`, the `unboxedSumTypeName` function now uses the non-punned syntax for unboxed sums (`Sum<N>#`) as the `OccName`. Fixes #24750. - - - - - 7eab4e01 by Alan Zimmerman at 2024-05-04T16:14:55+01:00 EPA: Widen stmtslist to include last semicolon Closes #24754 - - - - - 06f7db40 by Teo Camarasu at 2024-05-05T00:19:38-04:00 doc: Fix type error in hs_try_putmvar example - - - - - af000532 by Moritz Schuler at 2024-05-05T06:30:58-04:00 Fix parsing of module names in CLI arguments closes issue #24732 - - - - - da74e9c9 by Ben Gamari at 2024-05-05T06:31:34-04:00 ghc-platform: Add Setup.hs The Hadrian bootstrapping script relies upon `Setup.hs` to drive its build. Addresses #24761. - - - - - 35d34fde by Alan Zimmerman at 2024-05-05T12:52:40-04:00 EPA: preserve comments in class and data decls Fix checkTyClHdr which was discarding comments. Closes #24755 - - - - - 03c5dfbf by Simon Peyton Jones at 2024-05-05T12:53:15-04:00 Fix a float-out error Ticket #24768 showed that the Simplifier was accidentally destroying a join point. It turned out to be that we were sending a bottoming join point to the top, accidentally abstracting over /other/ join points. Easily fixed. - - - - - adba68e7 by John Ericson at 2024-05-05T19:35:56-04:00 Substitute bindist files with Hadrian not configure The `ghc-toolchain` overhaul will eventually replace all this stuff with something much more cleaned up, but I think it is still worth making this sort of cleanup in the meantime so other untanglings and dead code cleaning can procede. I was able to delete a fair amount of dead code doing this too. `LLVMTarget_CPP` is renamed to / merged with `LLVMTarget` because it wasn't actually turned into a valid CPP identifier. (Original to 1345c7cc42c45e63ab1726a8fd24a7e4d4222467, actually.) Progress on #23966 Co-Authored-By: Sylvain Henry <hsyl20 at gmail.com> - - - - - 18f4ff84 by Alan Zimmerman at 2024-05-05T19:36:32-04:00 EPA: fix mkHsOpTyPV duplicating comments Closes #24753 - - - - - a19201d4 by Matthew Craven at 2024-05-06T19:54:29-04:00 Add test cases for #24664 ...since none are present in the original MR !12463 fixing this issue. - - - - - 46328a49 by Alan Zimmerman at 2024-05-06T19:55:05-04:00 EPA: preserve comments in data decls Closes #24771 - - - - - 3b51995c by Andrei Borzenkov at 2024-05-07T14:39:40-04:00 Rename Solo# data constructor to MkSolo# (#24673) - data Solo# a = (# a #) + data Solo# a = MkSolo# a And `(# foo #)` syntax now becomes just a syntactic sugar for `MkSolo# a`. - - - - - 4d59abf2 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Add the cmm_cpp_is_gcc predicate to the testsuite A future C-- test called T24474-cmm-override-g0 relies on the GCC-specific behaviour of -g3 implying -dD, which, in turn, leads to it emitting #defines past the preprocessing stage. Clang, at least, does not do this, so the test would fail if ran on Clang. As the behaviour here being tested is ``-optCmmP-g3'' undoing effects of the workaround we apply as a fix for bug #24474, and the workaround was for GCC-specific behaviour, the test needs to be marked as fragile on other compilers. - - - - - 25b0b404 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Split out the C-- preprocessor, and make it pass -g0 Previously, C-- was processed with the C preprocessor program. This means that it inherited flags passed via -optc. A flag that is somewhat often passed through -optc is -g. At certain -g levels (>=2), GCC starts emitting defines *after* preprocessing, for the purposes of debug info generation. This is not useful for the C-- compiler, and, in fact, causes lexer errors. We can suppress this effect (safely, if supported) via -g0. As a workaround, in older versions of GCC (<=10), GCC only emitted defines if a certain set of -g*3 flags was passed. Newer versions check the debug level. For the former, we filter out those -g*3 flags and, for the latter, we specify -g0 on top of that. As a compatible and effective solution, this change adds a C-- preprocessor distinct from the C compiler and preprocessor, but that keeps its flags. The command line produced for C-- preprocessing now looks like: $pgmCmmP $optCs_without_g3 $g0_if_supported $optCmmP Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/24474 - - - - - 9b4129a5 by Andreas Klebinger at 2024-05-08T13:24:20-04:00 -fprof-late: Only insert cost centres on functions/non-workfree cafs. They are usually useless and doing so for data values comes with a large compile time/code size overhead. Fixes #24103 - - - - - 259b63d3 by Sebastian Graf at 2024-05-08T13:24:57-04:00 Simplifier: Preserve OccInfo on DataAlt fields when case binder is dead (#24770) See the adjusted `Note [DataAlt occ info]`. This change also has a positive repercussion on `Note [Combine case alts: awkward corner]`. Fixes #24770. We now try not to call `dataConRepStrictness` in `adjustFieldsIdInfo` when all fields are lazy anyway, leading to a 2% ghc/alloc decrease in T9675. Metric Decrease: T9675 - - - - - 31b28cdb by Sebastian Graf at 2024-05-08T13:24:57-04:00 Kill seqRule, discard dead seq# in Prep (#24334) Discarding seq#s in Core land via `seqRule` was problematic; see #24334. So instead we discard certain dead, discardable seq#s in Prep now. See the updated `Note [seq# magic]`. This fixes the symptoms of #24334. - - - - - b2682534 by Rodrigo Mesquita at 2024-05-10T01:47:51-04:00 Document NcgImpl methods Fixes #19914 - - - - - 4d3acbcf by Zejun Wu at 2024-05-10T01:48:28-04:00 Make renamer to be more flexible with parens in the LHS of the rules We used to reject LHS like `(f a) b` in RULES and requires it to be written as `f a b`. It will be handy to allow both as the expression may be more readable with extra parens in some cases when infix operator is involved. Espceially when TemplateHaskell is used, extra parens may be added out of user's control and result in "valid" rules being rejected and there are not always ways to workaround it. Fixes #24621 - - - - - ab840ce6 by Ben Gamari at 2024-05-10T01:49:04-04:00 IPE: Eliminate dependency on Read Instead of encoding the closure type as decimal string we now simply represent it as an integer, eliminating the need for `Read` in `GHC.Internal.InfoProv.Types.peekInfoProv`. Closes #24504. ------------------------- Metric Decrease: T24602_perf_size size_hello_artifact ------------------------- - - - - - a9979f55 by Cheng Shao at 2024-05-10T01:49:43-04:00 testsuite: fix testwsdeque with recent clang This patch fixes compilation of testwsdeque.c with recent versions of clang, which will fail with the error below: ``` testwsdeque.c:95:33: error: warning: format specifies type 'long' but the argument has type 'void *' [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~~ ^ testwsdeque.c:95:39: error: warning: format specifies type 'int' but the argument has type 'StgWord' (aka 'unsigned long') [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~ ^~~ | %lu testwsdeque.c:133:42: error: error: incompatible function pointer types passing 'void (void *)' to parameter of type 'OSThreadProc *' (aka 'void *(*)(void *)') [-Wincompatible-function-pointer-types] 133 | createOSThread(&ids[n], "thief", thief, (void*)(StgWord)n); | ^~~~~ /workspace/ghc/_build/stage1/lib/../lib/x86_64-linux-ghc-9.11.20240502/rts-1.0.2/include/rts/OSThreads.h:193:51: error: note: passing argument to parameter 'startProc' here 193 | OSThreadProc *startProc, void *param); | ^ 2 warnings and 1 error generated. ``` - - - - - c2b33fc9 by Rodrigo Mesquita at 2024-05-10T01:50:20-04:00 Rename pre-processor invocation args Small clean up. Uses proper names for the various groups of arguments that make up the pre-processor invocation. - - - - - 2b1af08b by Cheng Shao at 2024-05-10T01:50:55-04:00 ghc-heap: fix typo in ghc-heap cbits - - - - - fc2d6de1 by Jade at 2024-05-10T21:07:16-04:00 Improve performance of Data.List.sort(By) This patch improves the algorithm to sort lists in base. It does so using two strategies: 1) Use a four-way-merge instead of the 'default' two-way-merge. This is able to save comparisons and allocations. 2) Use `(>) a b` over `compare a b == GT` and allow inlining and specialization. This mainly benefits types with a fast (>). Note that this *may* break instances with a *malformed* Ord instance where `a > b` is *not* equal to `compare a b == GT`. CLC proposal: https://github.com/haskell/core-libraries-committee/issues/236 Fixes #24280 ------------------------- Metric Decrease: MultiLayerModulesTH_Make T10421 T13719 T15164 T18698a T18698b T1969 T9872a T9961 T18730 WWRec T12425 T15703 ------------------------- - - - - - 1012e8aa by Matthew Pickering at 2024-05-10T21:07:52-04:00 Revert "ghcup-metadata: Drop output_name field" This reverts commit ecbf22a6ac397a791204590f94c0afa82e29e79f. This breaks the ghcup metadata generation on the nightly jobs. - - - - - daff1e30 by Jannis at 2024-05-12T13:38:35-04:00 Division by constants optimization - - - - - 413217ba by Andreas Klebinger at 2024-05-12T13:39:11-04:00 Tidy: Add flag to expose unfoldings if they take dictionary arguments. Add the flag `-fexpose-overloaded-unfoldings` to be able to control this behaviour. For ghc's boot libraries file size grew by less than 1% when it was enabled. However I refrained from enabling it by default for now. I've also added a section on specialization more broadly to the users guide. ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot Metric Increase: T12425 T13386 hard_hole_fits ------------------------- - - - - - c5d89412 by Zubin Duggal at 2024-05-13T22:19:53-04:00 Don't store a GlobalRdrEnv in `mi_globals` for GHCi. GHCi only needs the `mi_globals` field for modules imported with :module +*SomeModule. It uses this field to make the top level environment in `SomeModule` available to the repl. By default, only the first target in the command line parameters is "star" loaded into GHCi. Other modules have to be manually "star" loaded into the repl. Storing the top level GlobalRdrEnv for each module is very wasteful, especially given that we will most likely never need most of these environments. Instead we store only the information needed to reconstruct the top level environment in a module, which is the `IfaceTopEnv` data structure, consisting of all import statements as well as all top level symbols defined in the module (not taking export lists into account) When a particular module is "star-loaded" into GHCi (as the first commandline target, or via an explicit `:module +*SomeModule`, we reconstruct the top level environment on demand using the `IfaceTopEnv`. - - - - - d65bf4a2 by Fendor at 2024-05-13T22:20:30-04:00 Add perf regression test for `-fwrite-if-simplified-core` - - - - - 2c0f8ddb by Andrei Borzenkov at 2024-05-13T22:21:07-04:00 Improve pattern to type pattern transformation (23739) `pat_to_type_pat` function now can handle more patterns: - TuplePat - ListPat - LitPat - NPat - ConPat Allowing these new constructors in type patterns significantly increases possible shapes of type patterns without `type` keyword. This patch also changes how lookups in `lookupOccRnConstr` are performed, because we need to fall back into types when we didn't find a constructor on data level to perform `ConPat` to type transformation properly. - - - - - be514bb4 by Cheng Shao at 2024-05-13T22:21:43-04:00 hadrian: fix hadrian building with ghc-9.10.1 - - - - - ad38e954 by Cheng Shao at 2024-05-13T22:21:43-04:00 linters: fix lint-whitespace compilation with ghc-9.10.1 - - - - - a593f284 by Andreas Klebinger at 2024-05-15T07:32:10-04:00 Expand the `inline` rule to look through casts/ticks. Fixes #24808 - - - - - b1e0c313 by Cheng Shao at 2024-05-15T07:32:46-04:00 testsuite: bump PartialDownSweep timeout to 5x on wasm32 - - - - - b2227487 by Fendor at 2024-05-15T17:14:06-04:00 Add Eq and Ord instance to `IfaceType` We add an `Ord` instance so that we can store `IfaceType` in a `Data.Map` container. This is required to deduplicate `IfaceType` while writing `.hi` files to disk. Deduplication has many beneficial consequences to both file size and memory usage, as the deduplication enables implicit sharing of values. See issue #24540 for more motivation. The `Ord` instance would be unnecessary if we used a `TrieMap` instead of `Data.Map` for the deduplication process. While in theory this is clerarly the better option, experiments on the agda code base showed that a `TrieMap` implementation has worse run-time performance characteristics. To the change itself, we mostly derive `Eq` and `Ord`. This requires us to change occurrences of `FastString` with `LexicalFastString`, since `FastString` has no `Ord` instance. We change the definition of `IfLclName` to a newtype of `LexicalFastString`, to make such changes in the future easier. Bump haddock submodule for IfLclName changes - - - - - d368f9a6 by Fendor at 2024-05-15T17:14:06-04:00 Move out LiteralMap to avoid cyclic module dependencies - - - - - 2fcc09fd by Fendor at 2024-05-15T17:14:06-04:00 Add deduplication table for `IfaceType` The type `IfaceType` is a highly redundant, tree-like data structure. While benchmarking, we realised that the high redundancy of `IfaceType` causes high memory consumption in GHCi sessions when byte code is embedded into the `.hi` file via `-fwrite-if-simplified-core` or `-fbyte-code-and-object-code`. Loading such `.hi` files from disk introduces many duplicates of memory expensive values in `IfaceType`, such as `IfaceTyCon`, `IfaceTyConApp`, `IA_Arg` and many more. We improve the memory behaviour of GHCi by adding an additional deduplication table for `IfaceType` to the serialisation of `ModIface`, similar to how we deduplicate `Name`s and `FastString`s. When reading the interface file back, the table allows us to automatically share identical values of `IfaceType`. To provide some numbers, we evaluated this patch on the agda code base. We loaded the full library from the `.hi` files, which contained the embedded core expressions (`-fwrite-if-simplified-core`). Before this patch: * Load time: 11.7 s, 2.5 GB maximum residency. After this patch: * Load time: 7.3 s, 1.7 GB maximum residency. This deduplication has the beneficial side effect to additionally reduce the size of the on-disk interface files tremendously. For example, on agda, we reduce the size of `.hi` files (with `-fwrite-if-simplified-core`): * Before: 101 MB on disk * Now: 24 MB on disk This has even a beneficial side effect on the cabal store. We reduce the size of the store on disk: * Before: 341 MB on disk * Now: 310 MB on disk Note, none of the dependencies have been compiled with `-fwrite-if-simplified-core`, but `IfaceType` occurs in multiple locations in a `ModIface`. We also add IfaceType deduplication table to .hie serialisation and refactor .hie file serialisation to use the same infrastrucutre as `putWithTables`. Bump haddock submodule to accomodate for changes to the deduplication table layout and binary interface. - - - - - 36aa7cf1 by Fendor at 2024-05-15T17:14:06-04:00 Add run-time configurability of `.hi` file compression Introduce the flag `-fwrite-if-compression=<n>` which allows to configure the compression level of writing .hi files. The motivation is that some deduplication operations are too expensive for the average use case. Hence, we introduce multiple compression levels with variable impact on performance, but still reduce the memory residency and `.hi` file size on disk considerably. We introduce three compression levels: * `1`: `Normal` mode. This is the least amount of compression. It deduplicates only `Name` and `FastString`s, and is naturally the fastest compression mode. * `2`: `Safe` mode. It has a noticeable impact on .hi file size and is marginally slower than `Normal` mode. In general, it should be safe to always use `Safe` mode. * `3`: `Full` deduplication mode. Deduplicate as much as we can, resulting in minimal .hi files, but at the cost of additional compilation time. Reading .hi files doesn't need to know the initial compression level, and can always deserialise a `ModIface`, as we write out a byte that indicates the next value has been deduplicated. This allows users to experiment with different compression levels for packages, without recompilation of dependencies. Note, the deduplication also has an additional side effect of reduced memory consumption to implicit sharing of deduplicated elements. See https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for example where that matters. ------------------------- Metric Decrease: MultiLayerModulesDefsGhciWithCore T16875 T21839c T24471 hard_hole_fits libdir ------------------------- - - - - - 1e63a6fb by Matthew Pickering at 2024-05-15T17:14:07-04:00 Introduce regression tests for `.hi` file sizes Add regression tests to track how `-fwrite-if-compression` levels affect the size of `.hi` files. - - - - - 639d742b by M Farkas-Dyck at 2024-05-15T17:14:49-04:00 TTG: ApplicativeStatement exist only in Rn and Tc Co-Authored-By: romes <rodrigo.m.mesquita at gmail.com> - - - - - aa7b336b by Jade at 2024-05-15T23:06:17-04:00 Documentation: Improve documentation for symbols exported from System.IO - - - - - c561de8f by Jade at 2024-05-15T23:06:54-04:00 Improve suggestions for language extensions - When suggesting Language extensions, also suggest Extensions which imply them - Suggest ExplicitForAll and GADTSyntax instead of more specific extensions - Rephrase suggestion to include the term 'Extension' - Also moves some flag specific definitions out of Session.hs into Flags.hs (#24478) Fixes: #24477 Fixes: #24448 Fixes: #10893 - - - - - 4c7ae2a1 by Andreas Klebinger at 2024-05-15T23:07:30-04:00 Testsuite: Check if llvm assembler is available for have_llvm - - - - - bc672166 by Torsten Schmits at 2024-05-15T23:08:06-04:00 refactor quadratic search in warnMissingHomeModules - - - - - 7875e8cb by Torsten Schmits at 2024-05-15T23:08:06-04:00 add test that runs MakeDepend on thousands of modules - - - - - b84b91f5 by Adam Gundry at 2024-05-16T15:32:06-04:00 Representation-polymorphic HasField (fixes #22156) This generalises the HasField class to support representation polymorphism, so that instead of type HasField :: forall {k} . k -> Type -> Type -> Constraint we have type HasField :: forall {k} {r_rep} {a_rep} . k -> TYPE r_rep -> TYPE a_rep -> Constraint - - - - - 05285090 by Matthew Pickering at 2024-05-16T15:32:43-04:00 Bump os-string submodule to 2.0.2.2 Closes #24786 - - - - - 886ab43a by Cheng Shao at 2024-05-17T01:34:50-04:00 rts: do not prefetch mark_closure bdescr in non-moving gc when ASSERTS_ENABLED This commit fixes a small an oversight in !12148: the prefetch logic in non-moving GC may trap in debug RTS because it calls Bdescr() for mark_closure which may be a static one. It's fine in non-debug RTS because even invalid bdescr addresses are prefetched, they will not cause segfaults, so this commit implements the most straightforward fix: don't prefetch mark_closure bdescr when assertions are enabled. - - - - - b38dcf39 by Teo Camarasu at 2024-05-17T01:34:50-04:00 rts: Allocate non-moving segments with megablocks Non-moving segments are 8 blocks long and need to be aligned. Previously we serviced allocations by grabbing 15 blocks, finding an aligned 8 block group in it and returning the rest. This proved to lead to high levels of fragmentation as a de-allocating a segment caused an 8 block gap to form, and this could not be reused for allocation. This patch introduces a segment allocator based around using entire megablocks to service segment allocations in bulk. When there are no free segments, we grab an entire megablock and fill it with aligned segments. As the megablock is free, we can easily guarantee alignment. Any unused segments are placed on a free list. It only makes sense to free segments in bulk when all of the segments in a megablock are freeable. After sweeping, we grab the free list, sort it, and find all groups of segments where they cover the megablock and free them. This introduces a period of time when free segments are not available to the mutator, but the risk that this would lead to excessive allocation is low. Right after sweep, we should have an abundance of partially full segments, and this pruning step is relatively quick. In implementing this we drop the logic that kept NONMOVING_MAX_FREE segments on the free list. We also introduce an eventlog event to log the amount of pruned/retained free segments. See Note [Segment allocation strategy] Resolves #24150 ------------------------- Metric Decrease: T13253 T19695 ------------------------- - - - - - 710665bd by Cheng Shao at 2024-05-17T01:35:30-04:00 rts: fix I/O manager compilation errors for win32 target This patch fixes I/O manager compilation errors for win32 target discovered when cross-compiling to win32 using recent clang: ``` rts/win32/ThrIOManager.c:117:7: error: error: call to undeclared function 'is_io_mng_native_p'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 117 | if (is_io_mng_native_p ()) { | ^ | 117 | if (is_io_mng_native_p ()) { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/fs.c:143:28: error: error: a function declaration without a prototype is deprecated in all versions of C [-Werror,-Wstrict-prototypes] 143 | int setErrNoFromWin32Error () { | ^ | void | 143 | int setErrNoFromWin32Error () { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:227:9: error: error: call to undeclared function 'interruptIOManagerEvent'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 227 | interruptIOManagerEvent (); | ^ | 227 | interruptIOManagerEvent (); | ^ rts/win32/ConsoleHandler.c:227:9: error: note: did you mean 'getIOManagerEvent'? | 227 | interruptIOManagerEvent (); | ^ rts/include/rts/IOInterface.h:27:10: error: note: 'getIOManagerEvent' declared here 27 | void * getIOManagerEvent (void); | ^ | 27 | void * getIOManagerEvent (void); | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:196:9: error: error: call to undeclared function 'setThreadLabel'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/win32/ConsoleHandler.c:196:9: error: note: did you mean 'postThreadLabel'? | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/eventlog/EventLog.h:118:6: error: note: 'postThreadLabel' declared here 118 | void postThreadLabel(Capability *cap, | ^ | 118 | void postThreadLabel(Capability *cap, | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) ``` - - - - - 28b9cee0 by Rodrigo Mesquita at 2024-05-17T01:36:05-04:00 configure: Check C99-compat for Cmm preprocessor Fixes #24815 - - - - - 8927e0c3 by Andreas Klebinger at 2024-05-17T01:36:41-04:00 Ensure `tcHasFixedRuntimeRep (# #)` returns True. - - - - - 04179044 by doyougnu at 2024-05-17T09:00:32-04:00 testsuite: make find_so regex less general Closes #24759 Background. In MR !12372 we began tracking shared object files and directories sizes for dependencies. However, this broke release builds because release builds alter the filenames swapping "in-place" for a hash. This was not considered in the MR and thus broke release pipelines. Furthermore, the rts_so test was found to be wildly varying and was therefore disabled in !12561. This commit fixes both of these issues: - fix the rts_so test by making the regex less general, now the rts_so test and all other foo.so tests must match "libHS<some-lib>-<version>-<hash|'in-place>-<ghc>". This prevents the rts_so test from accidentally matching different rts variants such as rts_threaded, which was the cause of the wild swings after !12372. - add logic to match either a hash or the string in-place. This should make the find_so function build agnostic. - - - - - 0962b50d by Andreas Klebinger at 2024-05-17T09:01:08-04:00 TagAnalysis: Treat all bottom ids as tagged during analysis. Ticket #24806 showed that we also need to treat dead end thunks as tagged during the analysis. - - - - - 7eb9f184 by Ben Gamari at 2024-05-17T11:23:37-04:00 Remove haddock submodule In preparation for merge into the GHC, as proposed in #23178. - - - - - 47b14dcc by Fendor at 2024-05-17T11:28:17-04:00 Adapt to `IfLclName` newtype changes (cherry picked from commit a711607e29b925f3d69e27c5fde4ba655c711ff1) - - - - - 6cc6681d by Fendor at 2024-05-17T11:28:17-04:00 Add IfaceType deduplication table to interface file serialisation Although we do not really need it in the interface file serialisation, as the deserialisation uses `getWithUserData`, we need to mirror the structure `getWithUserData` expects. Thus, we write essentially an empty `IfaceType` table at the end of the file, as the interface file doesn't reference `IfaceType`. (cherry picked from commit c9bc29c6a708483d2abc3d8ec9262510ce87ca61) - - - - - b9721206 by Ben Gamari at 2024-05-17T11:30:22-04:00 ghc-tags.yaml: Initial commit - - - - - 074e7d8f by Ben Gamari at 2024-05-17T11:31:29-04:00 fourmolu: Add configuration - - - - - 151b1736 by Ben Gamari at 2024-05-17T11:32:52-04:00 Makefile: Rework for use by haddock developers Previously the Makefile was present only for GHC's old make-based build system. Now since the make-based build system is gone we can use it for more useful ends. - - - - - a7dcf13b by Ben Gamari at 2024-05-17T11:36:14-04:00 Reformat with fourmolu Using previously-added configuration and `fourmolu -i .` Note that we exclude the test-cases (`./{hoogle,html-hypsrc,latex}-test`) as they are sensitive to formatting. - - - - - 0ea6017b by Ben Gamari at 2024-05-17T11:40:04-04:00 Add 'utils/haddock/' from commit 'a7dcf13bfbb97b20e75cc8ce650e2bb628db4660' git-subtree-dir: utils/haddock git-subtree-mainline: 7eb9f1849b1c72a1c61dee88462b4244550406f3 git-subtree-split: a7dcf13bfbb97b20e75cc8ce650e2bb628db4660 - - - - - aba1d304 by Hécate Moonlight at 2024-05-17T11:40:48-04:00 Add exceptions to the dangling notes list - - - - - 527bfbfb by Hécate Moonlight at 2024-05-17T11:40:52-04:00 Add haddock to the whitespace lint ignore list - - - - - 43274677 by Ben Gamari at 2024-05-17T11:41:20-04:00 git-blame-ignore-revs: Ignore haddock reformatting - - - - - 0e679e37 by Fendor at 2024-05-18T00:27:24-04:00 Pass cpp options to the CC builder in hadrian - - - - - bb40244e by Sylvain Henry at 2024-05-18T00:28:06-04:00 JS: fix allocation constant (fix #24746) - - - - - 646d30ab by Jade at 2024-05-18T19:23:31+02:00 Add highlighting for inline-code snippets in haddock - - - - - 64459a3e by Hécate Moonlight at 2024-05-19T08:42:27-04:00 haddock: Add a .readthedocs.yml file for online documentation - - - - - 7d3d9bbf by Serge S. Gulin at 2024-05-19T18:47:05+00:00 Unicode: General Category size test (related #24789) Added trivial size performance test which involves unicode general category usage via `read`. The `read` itself uses general category to detect spaces. The purpose for this test is to measure outcome of applying improvements at General Category representation in code discussed at #24789. - - - - - 8e04efcf by Alan Zimmerman at 2024-05-19T21:29:34-04:00 EPA: Remove redundant code Remove unused epAnnAnns function various cases for showAstData that no longer exist - - - - - 071d7a1e by Rodrigo Mesquita at 2024-05-20T10:55:16-04:00 Improve docs on closed type families in hs-boots Fixes #24776 - - - - - d9e2c119 by Torsten Schmits at 2024-05-20T10:55:52-04:00 Use default deviation for large-project test This new performance test has the purpose of detecting regressions in complexity in relation to the number of modules in a project, so 1% deviation is way too small to avoid false positives. - - - - - 20b0136a by Ben Gamari at 2024-05-22T00:31:39-04:00 ghcup-metadata: Various fixes from 9.10.1 Use Debian 12/x86-64, Debian 10/aarch64, and Debian 11/aarch64 bindists where possible. - - - - - 6838a7c3 by Sylvain Henry at 2024-05-22T00:32:23-04:00 Reverse arguments to stgCallocBytes (fix #24828) - - - - - f50f46c3 by Fendor at 2024-05-22T00:32:59-04:00 Add log messages for Iface serialisation compression level Fix the label of the number of 'IfaceType' entries in the log message. Add log message for the compression level that is used to serialise a an interface file. Adds `Outputable` instance for 'CompressionIFace'. - - - - - 3bad5d55 by Hécate Moonlight at 2024-05-22T00:33:40-04:00 base: Update doctests outputs ghc-internal: Update doctests outputs - - - - - 9317c6fb by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix the testsuites of the haddock-library - Apply all the metadata revisions from Hackage to the cabal file. - Fix the `ParserSpec.hs` file in the `spec` testsuite of haddock-library. - Make `CHANGES.md` an extra-doc-file instead of an extra-source-file. - - - - - 54073b02 by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix parser of @since pragma The testsuite contained tests for annotations of the form `@since foo-bar-0.5.0`, but the parser was written incorrectly. - - - - - ede6ede3 by Matthew Pickering at 2024-05-22T00:34:57-04:00 Fix nightly pages job It seems likely broken by 9f99126a which moved `index.html` from the root folder into `docs/` folder. Fixes #24840 - - - - - b7bcf729 by Cheng Shao at 2024-05-22T00:35:32-04:00 autoconf: remove unused context diff check This patch removes redundant autoconf check for the context diff program given it isn't actually been used anywhere, especially since make removal. - - - - - ea2fe66e by Hécate Moonlight at 2024-05-22T00:36:13-04:00 haddock: Rework the contributing guide - - - - - 0f302a94 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 haddock: Add module relationships diagrams of haddock-api and haddock-library - - - - - d1a9f34f by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add instructions - - - - - b880ee80 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add SVG outputs - - - - - 6d7e6ad8 by Ben Gamari at 2024-05-22T13:40:05-04:00 rts: Fix size of StgOrigThunkInfo frames Previously the entry code of the `stg_orig_thunk` frame failed to account for the size of the profiling header as it hard-coded the frame size. Fix this. Fixes #24809. - - - - - c645fe40 by Fendor at 2024-05-22T13:40:05-04:00 Add regression test T24809 for stg_orig_thunk_info_frame size - - - - - 4181aa40 by Andreas Klebinger at 2024-05-22T13:40:42-04:00 bindists: Check for existence of share folder before trying to copy it. This folder isn't distributed in windows bindists A lack of doing so resulted us copying loads of files twice. - - - - - d216510e by Matthew Pickering at 2024-05-22T13:40:42-04:00 Remove ad-hoc installation of mingw toolchain in relocatable bindists This reverts 616ac30026e8dd7d2ebb98d92dde071eedf5d951 The choice about whether to install mingw is taken in the installation makefile. This is also broken on non-windows systems. The actual issue was the EnableDistroToolchain variable wasn't declared in mk/config.mk and therefore the check to install mingw was failing. - - - - - 7b4c1998 by Cheng Shao at 2024-05-22T21:52:52-04:00 testsuite: fix T17920 for wasm backend T17920 was marked as fragile on wasm before; it can be trivially fixed by avoiding calling variadic printf() in cmm. - - - - - c739383b by Cheng Shao at 2024-05-22T21:53:29-04:00 testsuite: bump T22744 timeout to 5x - - - - - c4c6d714 by Cheng Shao at 2024-05-22T21:54:06-04:00 testsuite: don't attempt to detect host cpu features when testing cross ghc The testsuite driver CPU feature detection logic only detects host CPU and only makes sense when we are not testing a cross GHC. - - - - - 3d9e4ce6 by Simon Peyton Jones at 2024-05-22T21:54:43-04:00 Better skolemisation As #24810 showed, it is (a little) better to skolemise en-bloc, so that Note [Let-bound skolems] fires more often. See Note [Skolemisation en bloc] in GHC.Tc.Utils.Instantiate. - - - - - a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00 Add missing parenthesizePat in cvtp We need to ensure that the output of `cvtp` is parenthesized (at precedence `sigPrec`) so that any pattern signatures with a surrounding pattern signature can parse correctly. Fixes #24837. - - - - - 4bb2a7cc by Hécate Moonlight at 2024-05-22T21:55:59-04:00 [base] Document the memory overhead of ByteArray Add a diagram that shows the constituent parts of a ByteArray and their memory overhead. - - - - - 8b2a016a by Hécate Moonlight at 2024-05-22T21:56:38-04:00 Haddock: Add MR template for Haddock - - - - - ead75532 by Peter Trommler at 2024-05-23T02:28:05-04:00 PPC: Support ELF v2 on powerpc64 big-endian Detect ELF v2 on PowerPC 64-bit systems. Check for `_CALL_ELF` preprocessor macro. Fixes #21191 - - - - - 9d4c10f2 by Hécate Kleidukos at 2024-05-23T02:28:44-04:00 gitlab: Add @Kleidukos to CODEOWNERS for utils/haddock - - - - - 28e64170 by Preetham Gujjula at 2024-05-23T07:20:48-04:00 haddock: Add cabal-fmt to tools for `make style` - - - - - 00126a89 by Andrei Borzenkov at 2024-05-23T07:21:24-04:00 haddock: fix verbosity option parsing - - - - - a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00 base: specify tie-breaking behavior of min, max, and related list/Foldable functions - - - - - bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00 cmm: add word <-> double/float bitcast - closes: #25331 This is the last step in the project plan described in #25331. This commit: - adds bitcast operands for x86_64, LLVM, aarch64 - For PPC and i386 we resort to using the cmm implementations - renames conversion MachOps from Conv to Round|Truncate - - - - - f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor Some functions in StgToByteCode were filtering out void arguments. However, StgToByteCode is called after unarisation: the void arguments should have been removed earlier. Instead of filtering out, we assert that the args are non-void. - - - - - 03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor `layoutNativeCall` was always called with a `primRepCmmType platform` callback. Hence we can put it inside of `layoutNativeCall` rather than repeat it. - - - - - 27c430f3 by David Binder at 2024-05-24T07:52:38-04:00 haddock: Remove compatibility shims for GHC < 8.4 from haddock-library - - - - - 8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00 compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs This patch makes the STG->Cmm backend avoid saving foreign call target to local when there are no caller-save GlobalRegs. Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a foreign call, we unconditionally save the foreign call target to a temporary local first, then rely on cmmSink to clean it up later, which only happens with -fcmm-sink (implied by -O) and not in unoptimized code. And this is troublesome for the wasm backend NCG, which needs to infer a foreign call target symbol's type signature from the Cmm call site. Previously, the NCG has been emitting incorrect type signatures for unoptimized code, which happens to work with `wasm-ld` most of the time, but this is never future-proof against upstream toolchain updates, and it causes horrible breakages when LTO objects are included in linker input. Hence this patch. - - - - - 986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00 testsuite: add callee-no-local regression test - - - - - 52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00 Fix HasCallStack leftovers from !12514 / #24726 - - - - - c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00 user_guide: Fix typo in MultiWayIf chapter Close #24829 - - - - - bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - 1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Fix changelog reference to setBacktraceMechanismState (cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d) - - - - - 43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00 Float/double unboxed literal support for HexFloatLiterals (fix #22155) - - - - - 4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00 Improve test labels for binary interface file size tests Test labels for binary interface file sizes are hard to read and overly verbose at the same time. Extend the name for the metric title, but shorten it in the actual comparison table. - - - - - 14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00 Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present" This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa. - - - - - f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00 Fix default hyperlinked sources pattern Previously this didn't include the `%M` token which manifested as broken links to the hyperlinked sources of reexports of declarations defined in other packages. Fixes haddock#1628. (cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36) - - - - - 42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00 Make DocPaths a proper data type (cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c) - - - - - 53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00 haddock: Bump version to 2.30 (cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602) - - - - - e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00 haddock-api: allow base 4.20 and ghc 9.11 - - - - - e294f7a2 by PHO at 2024-05-24T12:17:55-04:00 Add a flag "threaded" for building haddock with the threaded RTS GHC isn't guaranteed to have a threaded RTS. There should be a way to build it with the vanilla one. (cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d) - - - - - 51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00 Update ticky counter event docs. Add the info about the info table address and json fields. Fixes #23200 - - - - - 98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00 Export extractPromotedList (#24866) This can be useful in plugins. - - - - - 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - d70abb49 by sheaf at 2024-06-18T18:47:20-04:00 Clarify -XGADTs enables existential quantification Even though -XGADTs does not turn on -XExistentialQuantification, it does allow the user of existential quantification syntax, without needing to use GADT-style syntax. Fixes #20865 - - - - - 13fdf788 by David Binder at 2024-06-18T18:48:02-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 1bab7dde by Fendor at 2024-06-18T18:48:38-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18698b T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The tests T16875 and T18698b fail on i386-linux for the same reason. - - - - - 099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - 5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00 Update user guide to indicate support for 64-tuples - - - - - 4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00 Remove duplicate Anno instances - - - - - 8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00 AArch64: Delete unused RegNos This has the additional benefit of getting rid of the -1 encoding (real registers start at 0.) - - - - - 325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00 Bump stm submodule to current master - - - - - 64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00 testsuite: bump T17572 timeout on wasm32 - - - - - eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00 AArch64: Simplify BL instruction The BL constructor carried unused data in its third argument. - - - - - b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00 TTG: Move SourceText from `Fixity` to `FixitySig` It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Precedes !12842, to simplify it - - - - - 842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00 base: Deprecate some .Internal modules Deprecates the following modules according to clc-proposal #217: https://github.com/haskell/core-libraries-committee/issues/217 * GHC.TypeNats.Internal * GHC.TypeLits.Internal * GHC.ExecutionStack.Internal Closes #24998 - - - - - 1cedfa11 by Andreas Klebinger at 2024-06-19T23:07:01+02:00 Allow profiling of time spent on safe calls. Done: Profile all safe calls via a runtime flag. Todo: Profile individual calls/modules via keyword/compilation flag. - - - - - f30fee93 by Andreas Klebinger at 2024-06-19T23:18:22+02:00 Fix rebase issues - - - - - 30 changed files: - + .git-blame-ignore-revs - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - + .gitlab/merge_request_templates/Haddock.md - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitmodules - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/CommonBlockElim.hs - compiler/GHC/Cmm/Config.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/LayoutStack.hs - compiler/GHC/Cmm/Lint.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/Sink.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/528a823c0e363ed9f41e23cc2e14b7f150145de8...f30fee9304fb9eeabb6b1db08d82c22dbaf6af51 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/528a823c0e363ed9f41e23cc2e14b7f150145de8...f30fee9304fb9eeabb6b1db08d82c22dbaf6af51 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 22:21:25 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Wed, 19 Jun 2024 18:21:25 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <667359e594013_1334da47a99101150ca@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 1f6b54e0 by Jacco Krijnen at 2024-06-19T18:19:57-04:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - ebd1d165 by Simon Peyton Jones at 2024-06-19T18:19:58-04:00 Fix demand signatures for join points This MR tackles #24623 and #23113 The main change is to give a clearer notion of "worker/wrapper arity", esp for join points. See GHC.Core.Opt.DmdAnal Note [Worker/wrapper arity and join points] This Note is a good summary of what this MR does: (1) The "worker/wrapper arity" of an Id is * For non-join-points: idArity * The join points: the join arity (Id part only of course) This is the number of args we will use in worker/wrapper. See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`. (2) A join point's demand-signature arity may exceed the Id's worker/wrapper arity. See the `arity_ok` assertion in `mkWwBodies`. (3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond the worker/wrapper arity. (4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper arity (re)-computed by workWrapArity. - - - - - 188becbe by Jan Hrček at 2024-06-19T18:20:04-04:00 Update haddocks of Import/Export AST types - - - - - 51ba766c by Hécate Kleidukos at 2024-06-19T18:20:09-04:00 haddock: Update bounds in cabal files and remove allow-newer stanza in cabal.project - - - - - fd924003 by Rodrigo Mesquita at 2024-06-19T18:20:10-04:00 cmm: Don't parse MO_BSwap for W8 Don't support parsing bswap8, since bswap8 is not really an operation and would have to be implemented as a no-op (and currently is not implemented at all). Fixes #25002 - - - - - 13ee16f9 by sheaf at 2024-06-19T18:20:11-04:00 Delete unused testsuite files These files were committed by mistake in !11902. This commit simply removes them. - - - - - 30 changed files: - compiler/GHC/Cmm/Parser.y - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/WorkWrap.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d2462c9c1f627029178ec2300e9131b01ccda34c...13ee16f99dd41f09e1b9431e15b797f769e894e1 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d2462c9c1f627029178ec2300e9131b01ccda34c...13ee16f99dd41f09e1b9431e15b797f769e894e1 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Wed Jun 19 22:49:01 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Wed, 19 Jun 2024 18:49:01 -0400 Subject: [Git][ghc/ghc][wip/T24978] More WIP Message-ID: <6673605dee156_1334da4c36f641156d2@gitlab.mail> Simon Peyton Jones pushed to branch wip/T24978 at Glasgow Haskell Compiler / GHC Commits: e39fd1ef by Simon Peyton Jones at 2024-06-19T23:48:32+01:00 More WIP does not compile - - - - - 2 changed files: - compiler/GHC/Tc/Instance/FunDeps.hs - compiler/GHC/Tc/Solver/Equality.hs Changes: ===================================== compiler/GHC/Tc/Instance/FunDeps.hs ===================================== @@ -68,8 +68,6 @@ The constraints ([Wanted] C Int Bool) and [Wanted] C Int alpha will generate the following FunDepEqn FDEqn { fd_qtvs = [] , fd_eqs = [Pair Bool alpha] - , fd_pred1 = C Int Bool - , fd_pred2 = C Int alpha , fd_loc = ... } However notice that a functional dependency may have more than one variable in the RHS which will create more than one pair of types in fd_eqs. Example: @@ -79,8 +77,6 @@ in the RHS which will create more than one pair of types in fd_eqs. Example: Will generate: FDEqn { fd_qtvs = [] , fd_eqs = [Pair Bool alpha, Pair alpha beta] - , fd_pred1 = C Int Bool - , fd_pred2 = C Int alpha , fd_loc = ... } INVARIANT: Corresponding types aren't already equal @@ -148,8 +144,6 @@ data FunDepEqn loc -- free in ty1 but not in ty2. See Wrinkle (1) of -- Note [Improving against instances] - , fd_pred1 :: PredType -- The FunDepEqn arose from - , fd_pred2 :: PredType -- combining these two constraints , fd_loc :: loc } deriving Functor @@ -221,7 +215,7 @@ improveFromAnother loc pred1 pred2 | Just (cls1, tys1) <- getClassPredTys_maybe pred1 , Just (cls2, tys2) <- getClassPredTys_maybe pred2 , cls1 == cls2 - = [ FDEqn { fd_qtvs = [], fd_eqs = eqs, fd_pred1 = pred1, fd_pred2 = pred2, fd_loc = loc } + = [ FDEqn { fd_qtvs = [], fd_eqs = eqs, fd_loc = loc } | let (cls_tvs, cls_fds) = classTvsFds cls1 , fd <- cls_fds , let (ltys1, rs1) = instFD fd cls_tvs tys1 @@ -245,7 +239,6 @@ improveFromInstEnv :: InstEnvs -- Post: Equations oriented from the template (matching instance) to the workitem! improveFromInstEnv inst_env mk_loc cls tys = [ FDEqn { fd_qtvs = meta_tvs, fd_eqs = eqs - , fd_pred1 = p_inst, fd_pred2 = pred , fd_loc = mk_loc p_inst (getSrcSpan (is_dfun ispec)) } | fd <- cls_fds -- Iterate through the fundeps first, -- because there often are none! @@ -257,13 +250,11 @@ improveFromInstEnv inst_env mk_loc cls tys , ispec <- instances , (meta_tvs, eqs) <- improveClsFD cls_tvs fd ispec tys trimmed_tcs -- NB: orientation - , let p_inst = mkClassPred cls (is_tys ispec) ] where (cls_tvs, cls_fds) = classTvsFds cls instances = classInstances inst_env cls rough_tcs = RM_KnownTc (className cls) : roughMatchTcs tys - pred = mkClassPred cls tys improveClsFD :: [TyVar] -> FunDep TyVar -- One functional dependency from the class -> ClsInst -- An instance template ===================================== compiler/GHC/Tc/Solver/Equality.hs ===================================== @@ -2993,10 +2993,8 @@ tryFunDeps eq_rel work_item@(EqCt { eq_lhs = lhs, eq_ev = ev }) improveTopFunEqs :: TyCon -> [TcType] -> EqCt -> TcS Bool -- See Note [FunDep and implicit parameter reactions] improveTopFunEqs fam_tc args (EqCt { eq_ev = ev, eq_rhs = rhs_ty }) - | isGiven ev - = improveGivenTopFunEqs fam_tc args ev rhs_ty - | otherwise - = improveWantedTopFunEqs fam_tc args ev rhs_ty + | isGiven ev = improveGivenTopFunEqs fam_tc args ev rhs_ty + | otherwise = improveWantedTopFunEqs fam_tc args ev rhs_ty improveGivenTopFunEqs :: TyCon -> [TcType] -> CtEvidence -> Xi -> TcS Bool improveGivenTopFunEqs fam_tc args ev rhs_ty @@ -3104,12 +3102,52 @@ improve_top_fun_eqs fam_envs fam_tc args rhs_ty improveLocalFunEqs :: InertCans -> TyCon -> [TcType] -> EqCt -> TcS Bool --- Generate improvement equalities, by comparing +improveLocalFunEqs inerts fam_tc args (EqCt { eq_ev = work_ev, eq_rhs = rhs }) + | isGiven work_ev = improveGivenLocalFunEqs funeqs_for_tc fam_tc args work_ev rhs + | otherwise = improveWantedLocalFunEqs funeqs_for_tc fam_tc args work_ev rhs + where + funeqs = inert_funeqs inerts + funeqs_for_tc :: [EqCt] + funeqs_for_tc = [ funeq_ct | equal_ct_list <- findFunEqsByTyCon funeqs fam_tc + , funeq_ct <- equal_ct_list + , NomEq == eq_eq_rel funeq_ct ] + -- Representational equalities don't interact + -- with type family dependencies + + +improveGivenLocalFunEqs :: TyCon -> [TcType] -> CtEvidence -> Xi -- Work item + -> [EqCt] -- Inert items + -> TcS Bool -- True <=> Something was emitted +improveGivenLocalFunEqs funeqs_for_tc fam_tc work_args work_ev work_rhs + | Just ops <- isBuiltInSynFamTyCon_maybe fam_tc + = foldlM (do_one ops) False fun_eqs_for_tc + | otherwise + = return False + where + do_one ops so_far (EqCt { eq_ev = inert_ev + , eq_lhs = TyFamLHS _ inert_args + , eq_rhs = inert_rhs }) + | isGiven inert_ev, not (null quads) + = do { emitNewGivens (ctEvLoc ev) quads; return True } + + | otherwise + = return so_far + where + given_co :: Coercion = ctEvCoercion work_ev + + quads = [ (Nominal, s, t, new_co) + | (ax, Pair s t) <- tryInteractInertFam ops fam_tc + work_args work_rhs inert_args inert_rhs + , let new_co = mkAxiomRuleCo ax [given_co] ] + +improveWantedLocalFunEqs :: [EqCt] -> TyCon -> [TcType] + -> CtEvidence -> Xi -> TcS Bool +-- Generate improvement equalities for a Watend constraint, by comparing -- the current work item with inert CFunEqs -- E.g. x + y ~ z, x + y' ~ z => [W] y ~ y' -- -- See Note [FunDep and implicit parameter reactions] -improveLocalFunEqs inerts fam_tc args (EqCt { eq_ev = work_ev, eq_rhs = rhs }) +improveWantedLocalFunEqs fun_eqs_for_tc fam_tc args work_ev rhs | null improvement_eqns = return False | otherwise @@ -3119,13 +3157,6 @@ improveLocalFunEqs inerts fam_tc args (EqCt { eq_ev = work_ev, eq_rhs = rhs }) , text "Inert eqs:" <+> ppr (inert_eqs inerts) ] ; emitFunDepWanteds work_ev improvement_eqns } where - funeqs = inert_funeqs inerts - funeqs_for_tc :: [EqCt] - funeqs_for_tc = [ funeq_ct | equal_ct_list <- findFunEqsByTyCon funeqs fam_tc - , funeq_ct <- equal_ct_list - , NomEq == eq_eq_rel funeq_ct ] - -- representational equalities don't interact - -- with type family dependencies work_loc = ctEvLoc work_ev work_pred = ctEvPred work_ev fam_inj_info = tyConInjectivityInfo fam_tc @@ -3146,11 +3177,7 @@ improveLocalFunEqs inerts fam_tc args (EqCt { eq_ev = work_ev, eq_rhs = rhs }) -------------------- do_one_built_in ops rhs (EqCt { eq_lhs = TyFamLHS _ iargs, eq_rhs = irhs, eq_ev = inert_ev }) - | isGiven inert_ev && isGiven work_ev - = [] -- ToDo: fill in - | otherwise = mk_fd_eqns inert_ev (map snd $ tryInteractInertFam ops fam_tc args rhs iargs irhs) - do_one_built_in _ _ _ = pprPanic "interactFunEq 1" (ppr fam_tc) -- TyVarLHS -------------------- @@ -3171,14 +3198,12 @@ improveLocalFunEqs inerts fam_tc args (EqCt { eq_ev = work_ev, eq_rhs = rhs }) mk_fd_eqns inert_ev eqns | null eqns = [] | otherwise = [ FDEqn { fd_qtvs = [], fd_eqs = eqns - , fd_pred1 = work_pred - , fd_pred2 = inert_pred , fd_loc = (loc, inert_rewriters) } ] where initial_loc -- start with the location of the Wanted involved | isGiven work_ev = inert_loc | otherwise = work_loc - eqn_orig = InjTFOrigin1 work_pred (ctLocOrigin work_loc) (ctLocSpan work_loc) + eqn_orig = InjTFOrigin1 work_pred (ctLocOrigin work_loc) (ctLocSpan work_loc) inert_pred (ctLocOrigin inert_loc) (ctLocSpan inert_loc) eqn_loc = setCtLocOrigin initial_loc eqn_orig inert_pred = ctEvPred inert_ev View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e39fd1ef1d32c256bf124b496940399c29bd8d34 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e39fd1ef1d32c256bf124b496940399c29bd8d34 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 06:31:32 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 20 Jun 2024 02:31:32 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 8 commits: ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <6673ccc45a0e9_1579de23ebdc010389@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: ebc14d42 by Jacco Krijnen at 2024-06-20T02:31:09-04:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 768749a1 by Simon Peyton Jones at 2024-06-20T02:31:10-04:00 Fix untouchability test This MR fixes #24938. The underlying problem was tha the test for "does this implication bring in scope any equalities" was plain wrong. See Note [Tracking Given equalities] and Note [Let-bound skolems] both in GHC.Tc.Solver.InertSet. Then * Test LocalGivenEqs succeeds for a different reason than before; see (LBS2) in Note [Let-bound skolems] * New test T24938a succeeds because of (LBS2), whereas it failed before. * Test LocalGivenEqs2 now fails, as it should. * Test T224938, the repro from the ticket, fails, as it should. - - - - - b4bcff12 by Simon Peyton Jones at 2024-06-20T02:31:10-04:00 Fix demand signatures for join points This MR tackles #24623 and #23113 The main change is to give a clearer notion of "worker/wrapper arity", esp for join points. See GHC.Core.Opt.DmdAnal Note [Worker/wrapper arity and join points] This Note is a good summary of what this MR does: (1) The "worker/wrapper arity" of an Id is * For non-join-points: idArity * The join points: the join arity (Id part only of course) This is the number of args we will use in worker/wrapper. See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`. (2) A join point's demand-signature arity may exceed the Id's worker/wrapper arity. See the `arity_ok` assertion in `mkWwBodies`. (3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond the worker/wrapper arity. (4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper arity (re)-computed by workWrapArity. - - - - - 69922698 by Jan Hrček at 2024-06-20T02:31:13-04:00 Update haddocks of Import/Export AST types - - - - - 74c92f39 by Hécate Kleidukos at 2024-06-20T02:31:15-04:00 haddock: Update bounds in cabal files and remove allow-newer stanza in cabal.project - - - - - 25767fc3 by Rodrigo Mesquita at 2024-06-20T02:31:16-04:00 cmm: Don't parse MO_BSwap for W8 Don't support parsing bswap8, since bswap8 is not really an operation and would have to be implemented as a no-op (and currently is not implemented at all). Fixes #25002 - - - - - cd7f2208 by sheaf at 2024-06-20T02:31:17-04:00 Delete unused testsuite files These files were committed by mistake in !11902. This commit simply removes them. - - - - - dab07419 by Matthew Pickering at 2024-06-20T02:31:17-04:00 Remove left over debugging pragma from 2016 This pragma was accidentally introduced in 648fd73a7b8fbb7955edc83330e2910428e76147 The top-level cost centres lead to a lack of optimisation when compiling with profiling. - - - - - 30 changed files: - compiler/GHC/Cmm/Parser.y - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/WorkWrap.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/StgToByteCode.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/13ee16f99dd41f09e1b9431e15b797f769e894e1...dab074193aad20d251b9601fbfedc4af4b73508f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/13ee16f99dd41f09e1b9431e15b797f769e894e1...dab074193aad20d251b9601fbfedc4af4b73508f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 06:44:03 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Thu, 20 Jun 2024 02:44:03 -0400 Subject: [Git][ghc/ghc][wip/romes/12935] 3 commits: Do uniq-renaming pass right at `codeGen` Message-ID: <6673cfb3da569_1579de26928bc12303f@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/12935 at Glasgow Haskell Compiler / GHC Commits: 74e9068a by Rodrigo Mesquita at 2024-06-19T16:34:07+01:00 Do uniq-renaming pass right at `codeGen` not better - - - - - 268439c3 by Rodrigo Mesquita at 2024-06-19T16:34:14+01:00 Revert "Do uniq-renaming pass right at `codeGen`" This reverts commit 74e9068aaaf736bf815a36bf74a0dde19a074a7a. - - - - - 70ff49b7 by Rodrigo Mesquita at 2024-06-19T16:40:09+01:00 Reapply "Do uniq renaming before SRTs" This reverts commit 682f89732fc2a95fa011f530c0c6922bf576d229. - - - - - 4 changed files: - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/GenerateCgIPEStub.hs - compiler/GHC/Driver/Main.hs Changes: ===================================== compiler/GHC/Cmm/Pipeline.hs ===================================== @@ -19,6 +19,7 @@ import GHC.Cmm.ProcPoint import GHC.Cmm.Sink import GHC.Cmm.Switch.Implement import GHC.Cmm.ThreadSanitizer +import GHC.Cmm.UniqueRenamer import GHC.Types.Unique.Supply @@ -42,18 +43,27 @@ cmmPipeline :: Logger -> CmmConfig -> ModuleSRTInfo -- Info about SRTs generated so far + -> DetUniqFM -> CmmGroup -- Input C-- with Procedures - -> IO (ModuleSRTInfo, CmmGroupSRTs) -- Output CPS transformed C-- + -> IO (ModuleSRTInfo, (DetUniqFM, CmmGroupSRTs)) -- Output CPS transformed C-- -cmmPipeline logger cmm_config srtInfo prog = do +cmmPipeline logger cmm_config srtInfo detRnEnv prog = do let forceRes (info, group) = info `seq` foldr seq () group let platform = cmmPlatform cmm_config withTimingSilent logger (text "Cmm pipeline") forceRes $ do - (procs, data_) <- {-# SCC "tops" #-} partitionWithM (cpsTop logger platform cmm_config) prog + + -- To produce deterministic object code, we alpha-rename all Uniques to deterministic uniques before Cmm linting. + -- From here on out, the backend code generation can't use (non-deterministic) Uniques, or risk producing non-deterministic code. + -- For example, the fix-up action in the ASM NCG should use determinist names for potential new blocks it has to create. + -- Therefore, in the ASM NCG `NatM` Monad we use a deterministic `UniqSuply` (which won't be shared about multiple threads) + -- TODO: Put these all into notes carefully organized + let (rn_mapping, renamed_prog) = detRenameUniques detRnEnv prog -- TODO: if gopt Opt_DeterministicObjects dflags + + (procs, data_) <- {-# SCC "tops" #-} partitionWithM (cpsTop logger platform cmm_config) renamed_prog (srtInfo, cmms) <- {-# SCC "doSRTs" #-} doSRTs cmm_config srtInfo procs data_ dumpWith logger Opt_D_dump_cmm_cps "Post CPS Cmm" FormatCMM (pdoc platform cmms) - return (srtInfo, cmms) + return (srtInfo, (rn_mapping, cmms)) -- | The Cmm pipeline for a single 'CmmDecl'. Returns: ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -39,7 +39,6 @@ import GHC.Data.OsPath import qualified GHC.Data.ShortText as ST import GHC.Data.Stream ( Stream ) import qualified GHC.Data.Stream as Stream -import GHC.Cmm.UniqueRenamer import GHC.Utils.TmpFs @@ -96,23 +95,12 @@ codeOutput logger tmpfs llvm_config dflags unit_state this_mod filenm location g cmm_stream = do { - -- To produce deterministic object code, we alpha-rename all Uniques to deterministic uniques before Cmm linting. - -- From here on out, the backend code generation can't use (non-deterministic) Uniques, or risk producing non-deterministic code. - -- For example, the fix-up action in the ASM NCG should use determinist names for potential new blocks it has to create. - -- Therefore, in the ASM NCG `NatM` Monad we use a deterministic `UniqSuply` (which won't be shared about multiple threads) - -- TODO: Put these all into notes carefully organized - ; let renamed_cmm_stream = do - -- if gopt Opt_DeterministicObjects dflags - - (rn_mapping, stream) <- Stream.mapAccumL_ (fmap pure . detRenameUniques) emptyDetUFM cmm_stream - Stream.liftIO $ debugTraceMsg logger 3 (text "DetRnM mapping:" <+> ppr rn_mapping) - return stream -- Lint each CmmGroup as it goes past ; let linted_cmm_stream = if gopt Opt_DoCmmLinting dflags - then Stream.mapM do_lint renamed_cmm_stream - else renamed_cmm_stream + then Stream.mapM do_lint cmm_stream + else cmm_stream do_lint cmm = withTimingSilent logger (text "CmmLint"<+>brackets (ppr this_mod)) ===================================== compiler/GHC/Driver/GenerateCgIPEStub.hs ===================================== @@ -35,6 +35,7 @@ import GHC.Unit.Types (Module, moduleName) import GHC.Unit.Module (moduleNameString) import qualified GHC.Utils.Logger as Logger import GHC.Utils.Outputable (ppr) +import GHC.Cmm.UniqueRenamer (emptyDetUFM) {- Note [Stacktraces from Info Table Provenance Entries (IPE based stack unwinding)] @@ -211,7 +212,7 @@ generateCgIPEStub hsc_env this_mod denv (nonCaffySet, moduleLFInfos, infoTablesW let denv' = denv {provInfoTables = Map.mapKeys cit_lbl infoTablesWithTickishes} ((mIpeStub, ipeCmmGroup), _) = runC (initStgToCmmConfig dflags this_mod) fstate cgState $ getCmm (initInfoTableProv initStats (Map.keys infoTablesWithTickishes) denv') - (_, ipeCmmGroupSRTs) <- liftIO $ cmmPipeline logger cmm_cfg (emptySRT this_mod) ipeCmmGroup + (_, (_, ipeCmmGroupSRTs)) <- liftIO $ cmmPipeline logger cmm_cfg (emptySRT this_mod) emptyDetUFM ipeCmmGroup Stream.yield ipeCmmGroupSRTs ipeStub <- ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -300,6 +300,8 @@ import GHC.StgToCmm.Utils (IPEStats) import GHC.Types.Unique.FM import GHC.Types.Unique.DFM import GHC.Cmm.Config (CmmConfig) +import GHC.Cmm.UniqueRenamer +import Data.Bifunctor {- ********************************************************************** @@ -2085,6 +2087,7 @@ hscCompileCmmFile hsc_env original_filename filename output_filename = runHsc hs $ parseCmmFile cmmpConfig cmm_mod home_unit filename let msgs = warns `unionMessages` errs return (GhcPsMessage <$> msgs, cmm) + liftIO $ do putDumpFileMaybe logger Opt_D_dump_cmm_verbose_by_proc "Parsed Cmm" FormatCMM (pdoc platform cmm) @@ -2094,8 +2097,10 @@ hscCompileCmmFile hsc_env original_filename filename output_filename = runHsc hs -- Re-ordering here causes breakage when booting with C backend because -- in C we must declare before use, but SRT algorithm is free to -- re-order [A, B] (B refers to A) when A is not CAFFY and return [B, A] - cmmgroup <- - concatMapM (\cmm -> snd <$> cmmPipeline logger cmm_config (emptySRT cmm_mod) [cmm]) cmm + (rn_mapping, cmmgroup) <- + second concat <$> mapAccumLM (\rn_mapping cmm -> snd <$> cmmPipeline logger cmm_config (emptySRT cmm_mod) rn_mapping [cmm]) emptyDetUFM cmm + + debugTraceMsg logger 3 (text "DetRnM mapping:" <+> ppr rn_mapping) unless (null cmmgroup) $ putDumpFileMaybe logger Opt_D_dump_cmm "Output Cmm" @@ -2193,9 +2198,10 @@ doCodeGen hsc_env this_mod denv data_tycons pipeline_stream :: Stream IO CmmGroupSRTs CmmCgInfos pipeline_stream = do - ((mod_srt_info, ipes, ipe_stats), lf_infos) <- + ((mod_srt_info, ipes, ipe_stats, rn_mapping), lf_infos) <- {-# SCC "cmmPipeline" #-} - Stream.mapAccumL_ (pipeline_action logger cmm_config) (emptySRT this_mod, M.empty, mempty) ppr_stream1 + Stream.mapAccumL_ (pipeline_action logger cmm_config) (emptySRT this_mod, M.empty, mempty, emptyDetUFM) ppr_stream1 + liftIO $ debugTraceMsg logger 3 (text "DetRnM mapping:" <+> ppr rn_mapping) let nonCaffySet = srtMapNonCAFs (moduleSRTMap mod_srt_info) cmmCgInfos <- generateCgIPEStub hsc_env this_mod denv (nonCaffySet, lf_infos, ipes, ipe_stats) return cmmCgInfos @@ -2203,11 +2209,11 @@ doCodeGen hsc_env this_mod denv data_tycons pipeline_action :: Logger -> CmmConfig - -> (ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats) + -> (ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats, DetUniqFM) -> CmmGroup - -> IO ((ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats), CmmGroupSRTs) - pipeline_action logger cmm_config (mod_srt_info, ipes, stats) cmm_group = do - (mod_srt_info', cmm_srts) <- cmmPipeline logger cmm_config mod_srt_info cmm_group + -> IO ((ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats, DetUniqFM), CmmGroupSRTs) + pipeline_action logger cmm_config (mod_srt_info, ipes, stats, detRnEnv) cmm_group = do + (mod_srt_info', (rn_mapping, cmm_srts)) <- cmmPipeline logger cmm_config mod_srt_info detRnEnv cmm_group -- If -finfo-table-map is enabled, we precompute a map from info -- tables to source locations. See Note [Mapping Info Tables to Source @@ -2218,7 +2224,7 @@ doCodeGen hsc_env this_mod denv data_tycons else return (ipes, stats) - return ((mod_srt_info', ipes', stats'), cmm_srts) + return ((mod_srt_info', ipes', stats', rn_mapping), cmm_srts) dump2 a = do unless (null a) $ View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/51fd4fe4b24520251cbfc2787e244a83b497730e...70ff49b7efc8c1fca46cba6eff630c5d39a99213 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/51fd4fe4b24520251cbfc2787e244a83b497730e...70ff49b7efc8c1fca46cba6eff630c5d39a99213 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 08:07:56 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 20 Jun 2024 04:07:56 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] 36 commits: SIMD NCG WIP: fix stack spilling Message-ID: <6673e35cc9e00_1862ad933104964be@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 4e136666 by sheaf at 2024-06-20T10:02:33+02:00 SIMD NCG WIP: fix stack spilling - - - - - 00963e9c by sheaf at 2024-06-20T10:02:36+02:00 SIMD NCG: accept simd006 - - - - - ec40fd99 by sheaf at 2024-06-20T10:02:36+02:00 WIP: fix mkSpillInstr/mkLoadInstr panics - - - - - 82b8ba93 by sheaf at 2024-06-20T10:02:36+02:00 improve RegClass - - - - - 6c16e39e by sheaf at 2024-06-20T10:02:36+02:00 set up basics for AArch64 SIMD - - - - - 4e5cc43f by sheaf at 2024-06-20T10:02:36+02:00 use MOVU instructions for spill/unspill - - - - - 372c958b by sheaf at 2024-06-20T10:02:36+02:00 WIP: start adding vector shuffle primops - - - - - 88baf78b by sheaf at 2024-06-20T10:02:36+02:00 remove redundant code in CmmToAsm/PPC/Instr - - - - - 420aa987 by sheaf at 2024-06-20T10:02:36+02:00 emit ymm/zmm when appropriate - - - - - 5ba5c324 by sheaf at 2024-06-20T10:02:37+02:00 fix reg2reg for vectors - - - - - d5784142 by sheaf at 2024-06-20T10:02:37+02:00 WIP: lower vector shuffle instruction on X86 - - - - - e36db160 by sheaf at 2024-06-20T10:02:37+02:00 NCG SIMD: fix shuffle lowering - - - - - 1d34282c by sheaf at 2024-06-20T10:02:37+02:00 slight improvement to vector unpack - - - - - d5b2d878 by sheaf at 2024-06-20T10:02:37+02:00 fix whitespace - - - - - 6fca446a by sheaf at 2024-06-20T10:02:37+02:00 fix regUsageOfInstr INSERTPS - - - - - 0184373c by Jaro Reinders at 2024-06-20T10:02:57+02:00 Add Int64X2 SIMD operations - - - - - 8077cb22 by sheaf at 2024-06-20T10:03:00+02:00 SIMD: need LLVM for Aarch64/PPC (for now) - - - - - 4cb02286 by sheaf at 2024-06-20T10:03:00+02:00 fixup Jaro - - - - - a5c8ac41 by sheaf at 2024-06-20T10:03:00+02:00 fixup: shuffle base exports - - - - - 5c0a0e87 by sheaf at 2024-06-20T10:03:00+02:00 improve cgrun083 - - - - - ac2b9b93 by sheaf at 2024-06-20T10:03:00+02:00 move SIMD tests - - - - - cdce59a3 by sheaf at 2024-06-20T10:03:27+02:00 TODO: MOV stuff - - - - - 2651caa3 by sheaf at 2024-06-20T10:03:31+02:00 X86 NCG SIMD: refactoring - - - - - b6a254cf by sheaf at 2024-06-20T10:03:31+02:00 SIMD tests: fixup - - - - - 63435fa1 by sheaf at 2024-06-20T10:04:44+02:00 fix X86 takeRegRegMove - - - - - e5f49360 by sheaf at 2024-06-20T10:04:47+02:00 SIMD: add vector FMA primops - - - - - 6f6a4bae by sheaf at 2024-06-20T10:05:34+02:00 SIMD: cleanup - - - - - 5c5cf23e by sheaf at 2024-06-20T10:05:37+02:00 WIP: improve broadcast, especially on LLVM - - - - - 88df70a6 by sheaf at 2024-06-20T10:05:38+02:00 more tidying - - - - - e9c588dd by sheaf at 2024-06-20T10:05:51+02:00 SIMD: refactor Format datatype - - - - - 650b3531 by sheaf at 2024-06-20T10:05:54+02:00 Revert "SIMD: refactor Format datatype" This reverts commit 84c46f16be09760b64a8b926f1f92ceb853b2da8. - - - - - 6bf593c3 by sheaf at 2024-06-20T10:05:54+02:00 SIMD cleanups, remove virtual Float reg - - - - - ce7accb8 by sheaf at 2024-06-20T10:05:54+02:00 add simd012 test - - - - - f155e901 by sheaf at 2024-06-20T10:05:55+02:00 fix getStackSlotFor FF32 - - - - - 7569cd81 by sheaf at 2024-06-20T10:05:55+02:00 X86 NCG: use FF64 format for Float MOV instructions - - - - - 00989fd2 by sheaf at 2024-06-20T10:05:55+02:00 don't print type of CmmReg - - - - - 30 changed files: - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/Cmm/CallConv.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/Reg.hs - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/AArch64.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/AArch64/Regs.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/PPC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/PPC/Regs.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Graph/Coalesce.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillCost.hs - compiler/GHC/CmmToAsm/Reg/Graph/Stats.hs - compiler/GHC/CmmToAsm/Reg/Graph/TrivColorable.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/AArch64.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/95d3ef7b4fc000185338aae2757bf8752e3cec92...00989fd206e4ff258992dd5481bc0ede5da876ad -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/95d3ef7b4fc000185338aae2757bf8752e3cec92...00989fd206e4ff258992dd5481bc0ede5da876ad You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 08:22:50 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 20 Jun 2024 04:22:50 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] fixup Reg.Liveness.equalBlockMaps Message-ID: <6673e6daab269_1862adbc29b01011c1@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 97dfd614 by sheaf at 2024-06-20T10:22:43+02:00 fixup Reg.Liveness.equalBlockMaps - - - - - 1 changed file: - compiler/GHC/CmmToAsm/Reg/Liveness.hs Changes: ===================================== compiler/GHC/CmmToAsm/Reg/Liveness.hs ===================================== @@ -925,8 +925,9 @@ livenessSCCs platform blockmap done -- BlockMaps for equality. equalBlockMaps a b = a' == b' - where a' = mapToList a - b' = mapToList b + where a' = map f $ mapToList a + b' = map f $ mapToList b + f (key,elt) = (key, nonDetEltsUniqSet elt) -- See Note [Unique Determinism and code generation] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/97dfd614413d06bc9ae87b2ba50bb5a9f25c0f0b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/97dfd614413d06bc9ae87b2ba50bb5a9f25c0f0b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 09:02:13 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 20 Jun 2024 05:02:13 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] fixup Reg.Liveness.equalBlockMaps Message-ID: <6673f0157dc66_1a98db432ab010388@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: bdfd1672 by sheaf at 2024-06-20T11:02:03+02:00 fixup Reg.Liveness.equalBlockMaps - - - - - 1 changed file: - compiler/GHC/CmmToAsm/Reg/Liveness.hs Changes: ===================================== compiler/GHC/CmmToAsm/Reg/Liveness.hs ===================================== @@ -923,10 +923,15 @@ livenessSCCs platform blockmap done -- probably the least efficient way to compare two -- BlockMaps for equality. + equalBlockMaps + :: BlockMap (UniqSet RegFormat) + -> BlockMap (UniqSet RegFormat) + -> Bool equalBlockMaps a b = a' == b' - where a' = mapToList a - b' = mapToList b + where a' = map f $ mapToList a + b' = map f $ mapToList b + f (key,elt) = (key, map regFormatReg $ nonDetEltsUniqSet elt) -- See Note [Unique Determinism and code generation] View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bdfd16720337a004f1ea37737b5e6d69aef7a7a5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bdfd16720337a004f1ea37737b5e6d69aef7a7a5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 11:21:55 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 20 Jun 2024 07:21:55 -0400 Subject: [Git][ghc/ghc][master] ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <667410d3e1d56_6081d246647781e@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 24e89c40 by Jacco Krijnen at 2024-06-20T07:21:27-04:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 30 changed files: - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs - compiler/GHC/Runtime/Eval.hs - compiler/GHC/Tc/Deriv.hs - compiler/GHC/Tc/Deriv/Functor.hs - compiler/GHC/Tc/Deriv/Generate.hs - compiler/GHC/Tc/Deriv/Generics.hs - compiler/GHC/Tc/Errors/Ppr.hs - compiler/GHC/Tc/Gen/Bind.hs - compiler/GHC/Tc/Gen/Expr.hs - compiler/GHC/Tc/Gen/Foreign.hs - compiler/GHC/Tc/Instance/Typeable.hs - compiler/GHC/Tc/Module.hs - compiler/GHC/Tc/TyCl/Class.hs - compiler/GHC/Tc/TyCl/Instance.hs - compiler/GHC/Tc/TyCl/PatSyn.hs - compiler/GHC/Tc/TyCl/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/24e89c40b7725123f03b98c7d934acc6256ff086 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/24e89c40b7725123f03b98c7d934acc6256ff086 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 11:22:46 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 20 Jun 2024 07:22:46 -0400 Subject: [Git][ghc/ghc][master] Fix untouchability test Message-ID: <66741106cac11_6081edc5748591f@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 04f5bb85 by Simon Peyton Jones at 2024-06-20T07:22:03-04:00 Fix untouchability test This MR fixes #24938. The underlying problem was tha the test for "does this implication bring in scope any equalities" was plain wrong. See Note [Tracking Given equalities] and Note [Let-bound skolems] both in GHC.Tc.Solver.InertSet. Then * Test LocalGivenEqs succeeds for a different reason than before; see (LBS2) in Note [Let-bound skolems] * New test T24938a succeeds because of (LBS2), whereas it failed before. * Test LocalGivenEqs2 now fails, as it should. * Test T224938, the repro from the ticket, fails, as it should. - - - - - 13 changed files: - compiler/GHC/Tc/Solver/InertSet.hs - testsuite/tests/indexed-types/should_fail/T13784.stderr - testsuite/tests/linters/notes.stdout - testsuite/tests/patsyn/should_fail/T11010.stderr - testsuite/tests/typecheck/should_compile/LocalGivenEqs.hs - testsuite/tests/typecheck/should_compile/LocalGivenEqs2.hs - + testsuite/tests/typecheck/should_compile/LocalGivenEqs2.stderr - + testsuite/tests/typecheck/should_compile/T24938a.hs - testsuite/tests/typecheck/should_compile/all.T - testsuite/tests/typecheck/should_fail/T22645.stderr - + testsuite/tests/typecheck/should_fail/T24938.hs - + testsuite/tests/typecheck/should_fail/T24938.stderr - testsuite/tests/typecheck/should_fail/all.T Changes: ===================================== compiler/GHC/Tc/Solver/InertSet.hs ===================================== @@ -647,11 +647,16 @@ enclosing Given equality. Exactly which constraints should trigger (UNTOUCHABLE), and hence should update inert_given_eq_lvl? -* We do /not/ need to worry about let-bound skolems, such ast +(TGE1) We do /not/ need to worry about let-bound skolems, such as forall[2] a. a ~ [b] => blah - See Note [Let-bound skolems] + See Note [Let-bound skolems] and the isOuterTyVar tests in `updGivenEqs` -* Consider an implication +(TGE2) However, solely to support better error messages (see Note [HasGivenEqs] in + GHC.Tc.Types.Constraint) we also track these "local" equalities in the + boolean inert_given_eqs field. This field is used only subsequntly (see + `getHasGivenEqs`), to set the ic_given_eqs field to LocalGivenEqs. + +(TGE3) Consider an implication forall[2]. beta[1] => alpha[1] ~ Int where beta is a unification variable that has already been unified to () in an outer scope. Then alpha[1] is perfectly touchable and @@ -659,64 +664,66 @@ should update inert_given_eq_lvl? an equality, we should canonicalise first, rather than just looking at the /original/ givens (#8644). - * However, we must take account of *potential* equalities. Consider the +(TGE4) However, we must take account of *potential* equalities. Consider the same example again, but this time we have /not/ yet unified beta: forall[2] beta[1] => ...blah... Because beta might turn into an equality, updGivenEqs conservatively treats it as a potential equality, and updates inert_give_eq_lvl - * What about something like forall[2] a b. a ~ F b => [W] alpha[1] ~ X y z? - - That Given cannot affect the Wanted, because the Given is entirely - *local*: it mentions only skolems bound in the very same - implication. Such equalities need not make alpha untouchable. (Test - case typecheck/should_compile/LocalGivenEqs has a real-life - motivating example, with some detailed commentary.) - Hence the 'mentionsOuterVar' test in updGivenEqs. - - However, solely to support better error messages - (see Note [HasGivenEqs] in GHC.Tc.Types.Constraint) we also track - these "local" equalities in the boolean inert_given_eqs field. - This field is used only to set the ic_given_eqs field to LocalGivenEqs; - see the function getHasGivenEqs. - - Here is a simpler case that triggers this behaviour: - - data T where - MkT :: F a ~ G b => a -> b -> T - - f (MkT _ _) = True - - Because of this behaviour around local equality givens, we can infer the - type of f. This is typecheck/should_compile/LocalGivenEqs2. - - * We need not look at the equality relation involved (nominal vs +(TGE5) We should not look at the equality relation involved (nominal vs representational), because representational equalities can still imply nominal ones. For example, if (G a ~R G b) and G's argument's role is nominal, then we can deduce a ~N b. +Historical note: prior to #24938 we also ignored Given equalities that +did not mention an "outer" type variable. But that is wrong, as #24938 +showed. Another example is immortalised in test LocalGivenEqs2 + data T where + MkT :: F a ~ G b => a -> b -> T + f (MkT _ _) = True +We should not infer the type for `f`; let-bound-skolems does not apply. + Note [Let-bound skolems] ~~~~~~~~~~~~~~~~~~~~~~~~ If * the inert set contains a canonical Given CEqCan (a ~ ty) and * 'a' is a skolem bound in this very implication, then: -a) The Given is pretty much a let-binding, like - f :: (a ~ b->c) => a -> a - Here the equality constraint is like saying - let a = b->c in ... - It is not adding any new, local equality information, - and hence can be ignored by has_given_eqs + a) The Given is pretty much a let-binding, like + f :: (a ~ b->c) => a -> a + Here the equality constraint is like saying + let a = b->c in ... + It is not adding any new, local equality information, + and hence can be ignored by has_given_eqs -b) 'a' will have been completely substituted out in the inert set, - so we can safely discard it. + b) 'a' will have been completely substituted out in the inert set, + so we can safely discard it. For an example, see #9211. -See also GHC.Tc.Utils.Unify Note [Deeper level on the left] for how we ensure -that the right variable is on the left of the equality when both are -tyvars. +The actual test is in `isLetBoundSkolemCt` + +Wrinkles: + +(LBS1) See GHC.Tc.Utils.Unify Note [Deeper level on the left] for how we ensure + that the correct variable is on the left of the equality when both are + tyvars. + +(LBS2) We also want this to work for + forall a. [G] F b ~ a (CEqCt with TyFamLHS) + Here the Given will have a TyFamLHS, with the skolem-bound tyvar on the RHS. + See tests T24938a, and LocalGivenEqs. + +(LBS3) Happily (LBS2) also makes cycle-breakers work. Suppose we have + forall a. [G] (F a) Int ~ a + where F has arity 1, and `a` is the locally-bound skolem. Then, as + Note [Type equality cycles] explains, we split into + [G] F a ~ cbv, [G] cbv Int ~ a + where `cbv` is the cycle breaker variable. But cbv has the same level + as `a`, so `isOuterTyVar` (called in `isLetBoundSkolemCt`) will return False. + + This actually matters occasionally: see test LocalGivenEqs. You might wonder whether the skolem really needs to be bound "in the very same implication" as the equality constraint. @@ -741,6 +748,18 @@ body of the lambda we'll get Now, unify alpha := a. Now we are stuck with an unsolved alpha~Int! So we must treat alpha as untouchable under the forall[2] implication. +Possible future improvements. The current test just looks to see whether one +side of an equality is a locally-bound skolem. But actually we could, in +theory, do better: if one side (or both sides, actually) of an equality +ineluctably mentions a local skolem, then the equality cannot possibly impact +types outside of the implication (because doing to would cause those types to be +ill-scoped). The problem is the "ineluctably": this means that no expansion, +other solving, etc., could possibly get rid of the variable. This is hard, +perhaps impossible, to know for sure, especially when we think about type family +interactions. (And it's a user-visible property so we don't want it to be hard +to predict.) So we keep the existing check, looking for one lone variable, +because we're sure that variable isn't going anywhere. + Note [Detailed InertCans Invariants] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ The InertCans represents a collection of constraints with the following properties: @@ -1467,27 +1486,28 @@ updGivenEqs :: TcLevel -> Ct -> InertCans -> InertCans -- if the constraint is a given equality that should prevent -- filling in an outer unification variable. -- See Note [Tracking Given equalities] -updGivenEqs tclvl ct inerts@(IC { inert_given_eq_lvl = ge_lvl }) +-- +-- Precondition: Ct is either CEqCan or CIrredCan +updGivenEqs tclvl ct inerts | not (isGivenCt ct) = inerts - | not_equality ct = inerts -- See Note [Let-bound skolems] - | otherwise = inerts { inert_given_eq_lvl = ge_lvl' - , inert_given_eqs = True } - where - ge_lvl' | mentionsOuterVar tclvl (ctEvidence ct) - -- Includes things like (c a), which *might* be an equality - = tclvl - | otherwise - = ge_lvl - - not_equality :: Ct -> Bool - -- True <=> definitely not an equality of any kind - -- except for a let-bound skolem, which doesn't count - -- See Note [Let-bound skolems] - -- NB: no need to spot the boxed CDictCan (a ~ b) because its - -- superclass (a ~# b) will be a CEqCan - not_equality (CEqCan (EqCt { eq_lhs = TyVarLHS tv })) = not (isOuterTyVar tclvl tv) - not_equality (CDictCan {}) = True - not_equality _ = False + + -- See Note [Let-bound skolems] + | isLetBoundSkolemCt tclvl ct = inerts { inert_given_eqs = True } + + -- At this point we are left with a constraint that either + -- is an equality (F a ~ ty), or /might/ be, like (c a) + | otherwise = inerts { inert_given_eq_lvl = tclvl + , inert_given_eqs = True } + +isLetBoundSkolemCt :: TcLevel -> Ct -> Bool +-- See Note [Let-bound skolems] +isLetBoundSkolemCt tclvl (CEqCan (EqCt { eq_lhs = lhs, eq_rhs = rhs })) + = case lhs of + TyVarLHS tv -> not (isOuterTyVar tclvl tv) + TyFamLHS {} -> case getTyVar_maybe rhs of + Just tv -> not (isOuterTyVar tclvl tv) + Nothing -> False +isLetBoundSkolemCt _ _ = False data KickOutSpec -- See Note [KickOutSpec] = KOAfterUnify TcTyVarSet -- We have unified these tyvars @@ -1732,11 +1752,6 @@ Hence: * * ********************************************************************* -} -mentionsOuterVar :: TcLevel -> CtEvidence -> Bool -mentionsOuterVar tclvl ev - = anyFreeVarsOfType (isOuterTyVar tclvl) $ - ctEvPred ev - isOuterTyVar :: TcLevel -> TyCoVar -> Bool -- True of a type variable that comes from a -- shallower level than the ambient level (tclvl) ===================================== testsuite/tests/indexed-types/should_fail/T13784.stderr ===================================== @@ -1,6 +1,10 @@ - T13784.hs:29:28: error: [GHC-25897] - • Couldn't match type ‘as’ with ‘a : Divide a as’ + • Could not deduce ‘as ~ (a : Divide a as)’ + from the context: (a : as) ~ (a1 : as1) + bound by a pattern with constructor: + :* :: forall a (as :: [*]). a -> Product as -> Product (a : as), + in an equation for ‘divide’ + at T13784.hs:29:13-19 Expected: Product (Divide a (a : as)) Actual: Product as1 ‘as’ is a rigid type variable bound by @@ -36,3 +40,4 @@ T13784.hs:33:29: error: [GHC-83865] • Relevant bindings include divide :: Product (a : as) -> (b, Product (Divide b (a : as))) (bound at T13784.hs:33:5) + ===================================== testsuite/tests/linters/notes.stdout ===================================== @@ -44,8 +44,6 @@ ref testsuite/tests/perf/should_run/all.T:8:6: Note [Solving from instanc ref testsuite/tests/polykinds/CuskFam.hs:16:11: Note [Unifying implicit CUSK variables] ref testsuite/tests/simplCore/should_compile/T5776.hs:16:7: Note [Simplifying RULE lhs constraints] ref testsuite/tests/simplCore/should_compile/simpl018.hs:3:7: Note [Float coercions] -ref testsuite/tests/typecheck/should_compile/LocalGivenEqs.hs:7:7: Note [When does an implication have given equalities?] -ref testsuite/tests/typecheck/should_compile/LocalGivenEqs2.hs:4:6: Note [When does an implication have given equalities?] ref testsuite/tests/typecheck/should_compile/T9117.hs:3:12: Note [Order of Coercible Instances] ref testsuite/tests/typecheck/should_compile/tc200.hs:5:7: Note [Multiple instantiation] ref testsuite/tests/typecheck/should_compile/tc228.hs:9:7: Note [Inference and implication constraints] ===================================== testsuite/tests/patsyn/should_fail/T11010.stderr ===================================== @@ -1,6 +1,8 @@ - T11010.hs:9:34: error: [GHC-25897] - • Couldn't match type ‘a1’ with ‘Int’ + • Could not deduce ‘a1 ~ Int’ + from the context: a ~ Int + bound by the signature for pattern synonym ‘IntFun’ + at T11010.hs:9:1-36 Expected: a -> b Actual: a1 -> b ‘a1’ is a rigid type variable bound by @@ -15,3 +17,4 @@ T11010.hs:9:34: error: [GHC-25897] | 9 | pattern IntFun str f x = Fun str f x | ^ + ===================================== testsuite/tests/typecheck/should_compile/LocalGivenEqs.hs ===================================== @@ -4,7 +4,7 @@ module LocalGivenEqs where --- See Note [When does an implication have given equalities?] in GHC.Tc.Solver.Monad; +-- See Note [Tracking Given equalities] in GHC.Tc.Solver.InertSet; -- this tests custom treatment for LocalGivenEqs {- ===================================== testsuite/tests/typecheck/should_compile/LocalGivenEqs2.hs ===================================== @@ -1,9 +1,7 @@ {-# LANGUAGE TypeFamilies, GADTSyntax, ExistentialQuantification #-} --- This is a simple case that exercises the LocalGivenEqs bullet --- of Note [When does an implication have given equalities?] in GHC.Tc.Solver.Monad --- If a future change rejects this, that's not the end of the world, but it's nice --- to be able to infer `f`. +-- This one should be rejected. +-- See Note [Tracking Given equalities] in GHC.Tc.Solver.InertSet module LocalGivenEqs2 where ===================================== testsuite/tests/typecheck/should_compile/LocalGivenEqs2.stderr ===================================== @@ -0,0 +1,16 @@ +LocalGivenEqs2.hs:14:15: error: [GHC-25897] + • Could not deduce ‘p ~ Bool’ + from the context: F a ~ G b + bound by a pattern with constructor: + MkT :: forall a b. (F a ~ G b) => a -> b -> T, + in an equation for ‘f’ + at LocalGivenEqs2.hs:14:4-10 + ‘p’ is a rigid type variable bound by + the inferred type of f :: T -> p + at LocalGivenEqs2.hs:14:1-18 + • In the expression: True + In an equation for ‘f’: f (MkT _ _) = True + • Relevant bindings include + f :: T -> p (bound at LocalGivenEqs2.hs:14:1) + Suggested fix: Consider giving ‘f’ a type signature + ===================================== testsuite/tests/typecheck/should_compile/T24938a.hs ===================================== @@ -0,0 +1,11 @@ +{-# LANGUAGE TypeFamilies, GADTs #-} + +module T24938a where + +type family F a + +data T b where + MkT :: forall a b. F b ~ a => a -> T b + -- This equality is a let-bound skolem + +f (MkT x) = True ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -762,7 +762,7 @@ test('InstanceGivenOverlap2', expect_broken(20076), compile_fail, ['']) test('T19044', normal, compile, ['']) test('T19052', normal, compile, ['']) test('LocalGivenEqs', normal, compile, ['']) -test('LocalGivenEqs2', normal, compile, ['']) +test('LocalGivenEqs2', normal, compile_fail, ['']) test('T18891', normal, compile, ['']) test('TyAppPat_Existential', normal, compile, ['']) @@ -918,3 +918,5 @@ test('T23764', normal, compile, ['']) test('T23739a', normal, compile, ['']) test('T24810', normal, compile, ['']) test('T24887', normal, compile, ['']) +test('T24938a', normal, compile, ['']) + ===================================== testsuite/tests/typecheck/should_fail/T22645.stderr ===================================== @@ -1,6 +1,9 @@ - T22645.hs:9:5: error: [GHC-25897] - • Couldn't match type ‘a’ with ‘b’ arising from a use of ‘coerce’ + • Could not deduce ‘a ~ b’ arising from a use of ‘coerce’ + from the context: Coercible a b + bound by the type signature for: + p :: forall a b. Coercible a b => T Maybe a -> T Maybe b + at T22645.hs:8:1-44 ‘a’ is a rigid type variable bound by the type signature for: p :: forall a b. Coercible a b => T Maybe a -> T Maybe b @@ -13,3 +16,4 @@ T22645.hs:9:5: error: [GHC-25897] In an equation for ‘p’: p = coerce • Relevant bindings include p :: T Maybe a -> T Maybe b (bound at T22645.hs:9:1) + ===================================== testsuite/tests/typecheck/should_fail/T24938.hs ===================================== @@ -0,0 +1,33 @@ +{-# LANGUAGE TypeFamilyDependencies, PartialTypeSignatures #-} + +module T24938 where + +import Prelude (Int, String, undefined) + +data Eq a b where + Refl :: Eq a a + +type family Mt a = r | r -> a + +anyM :: Mt a +anyM = undefined + +useIntAndRaise :: Mt Int -> a +useIntAndRaise = undefined + +type family Nt a = r | r -> a + +use :: Nt a -> a +use = undefined + +anyN :: Nt a +anyN = undefined + +foo p (e :: Eq (Mt Int) (Nt String)) = + (case e of + Refl -> + let bar x = + if p then useIntAndRaise x + else use x + in + bar) anyM ===================================== testsuite/tests/typecheck/should_fail/T24938.stderr ===================================== @@ -0,0 +1,19 @@ +T24938.hs:30:16: error: [GHC-25897] + • Could not deduce ‘p ~ GHC.Types.Bool’ + from the context: Nt String ~ Mt Int + bound by a pattern with constructor: + Refl :: forall {k} (a :: k). Eq a a, + in a case alternative + at T24938.hs:28:5-8 + ‘p’ is a rigid type variable bound by + the inferred type of foo :: p -> Eq (Mt Int) (Nt String) -> t + at T24938.hs:(26,1)-(33,17) + • In the expression: p + In the expression: if p then useIntAndRaise x else use x + In an equation for ‘bar’: + bar x = if p then useIntAndRaise x else use x + • Relevant bindings include + p :: p (bound at T24938.hs:26:5) + foo :: p -> Eq (Mt Int) (Nt String) -> t (bound at T24938.hs:26:1) + Suggested fix: Consider giving ‘foo’ a type signature + ===================================== testsuite/tests/typecheck/should_fail/all.T ===================================== @@ -728,3 +728,4 @@ test('T24470a', normal, compile_fail, ['']) test('T24553', normal, compile_fail, ['']) test('T23739b', normal, compile_fail, ['']) test('T24868', normal, compile_fail, ['']) +test('T24938', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/04f5bb85c8109843b9ac2af2a3e26544d05e02f4 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/04f5bb85c8109843b9ac2af2a3e26544d05e02f4 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 11:23:53 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 20 Jun 2024 07:23:53 -0400 Subject: [Git][ghc/ghc][master] Fix demand signatures for join points Message-ID: <66741149c8c0_6081f2bad4921f1@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 9a757a27 by Simon Peyton Jones at 2024-06-20T07:22:40-04:00 Fix demand signatures for join points This MR tackles #24623 and #23113 The main change is to give a clearer notion of "worker/wrapper arity", esp for join points. See GHC.Core.Opt.DmdAnal Note [Worker/wrapper arity and join points] This Note is a good summary of what this MR does: (1) The "worker/wrapper arity" of an Id is * For non-join-points: idArity * The join points: the join arity (Id part only of course) This is the number of args we will use in worker/wrapper. See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`. (2) A join point's demand-signature arity may exceed the Id's worker/wrapper arity. See the `arity_ok` assertion in `mkWwBodies`. (3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond the worker/wrapper arity. (4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper arity (re)-computed by workWrapArity. - - - - - 6 changed files: - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/WorkWrap.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Types/Demand.hs - + testsuite/tests/dmdanal/should_compile/T24623.hs - testsuite/tests/dmdanal/should_compile/all.T Changes: ===================================== compiler/GHC/Core/Opt/DmdAnal.hs ===================================== @@ -1008,7 +1008,7 @@ dmdTransform :: AnalEnv -- ^ The analysis environment -> DmdType -- ^ The demand type unleashed by the variable in this -- context. The returned DmdEnv includes the demand on -- this function plus demand on its free variables --- See Note [What are demand signatures?] in "GHC.Types.Demand" +-- See Note [DmdSig: demand signatures, and demand-sig arity] in "GHC.Types.Demand" dmdTransform env var sd -- Data constructors | Just con <- isDataConWorkId_maybe var @@ -1081,31 +1081,33 @@ dmdAnalRhsSig -- Process the RHS of the binding, add the strictness signature -- to the Id, and augment the environment with the signature as well. -- See Note [NOINLINE and strictness] -dmdAnalRhsSig top_lvl rec_flag env let_dmd id rhs +dmdAnalRhsSig top_lvl rec_flag env let_sd id rhs = -- pprTrace "dmdAnalRhsSig" (ppr id $$ ppr let_dmd $$ ppr rhs_dmds $$ ppr sig $$ ppr weak_fvs) $ (final_env, weak_fvs, final_id, final_rhs) where - threshold_arity = thresholdArity id rhs + ww_arity = workWrapArity id rhs + -- See Note [Worker/wrapper arity and join points] point (1) - rhs_dmd = mkCalledOnceDmds threshold_arity body_dmd - - body_dmd - | isJoinId id + body_sd | isJoinId id = let_sd + | otherwise = topSubDmd -- See Note [Demand analysis for join points] -- See Note [Invariants on join points] invariant 2b, in GHC.Core - -- threshold_arity matches the join arity of the join point - -- See Note [Unboxed demand on function bodies returning small products] - = unboxedWhenSmall env rec_flag (resultType_maybe id) let_dmd - | otherwise + -- ww_arity matches the join arity of the join point + + adjusted_body_sd = unboxedWhenSmall env rec_flag (resultType_maybe id) body_sd -- See Note [Unboxed demand on function bodies returning small products] - = unboxedWhenSmall env rec_flag (resultType_maybe id) topSubDmd - WithDmdType rhs_dmd_ty rhs' = dmdAnal env rhs_dmd rhs + rhs_sd = mkCalledOnceDmds ww_arity adjusted_body_sd + + WithDmdType rhs_dmd_ty rhs' = dmdAnal env rhs_sd rhs DmdType rhs_env rhs_dmds = rhs_dmd_ty - (final_rhs_dmds, final_rhs) = finaliseArgBoxities env id threshold_arity + (final_rhs_dmds, final_rhs) = finaliseArgBoxities env id ww_arity rhs_dmds (de_div rhs_env) rhs' - sig = mkDmdSigForArity threshold_arity (DmdType sig_env final_rhs_dmds) + dmd_sig_arity = ww_arity + strictCallArity body_sd + sig = mkDmdSigForArity dmd_sig_arity (DmdType sig_env final_rhs_dmds) + -- strictCallArity is > 0 only for join points + -- See Note [mkDmdSigForArity] opts = ae_opts env final_id = setIdDmdAndBoxSig opts id sig @@ -1137,13 +1139,6 @@ splitWeakDmds :: DmdEnv -> (DmdEnv, WeakDmds) splitWeakDmds (DE fvs div) = (DE sig_fvs div, weak_fvs) where (!weak_fvs, !sig_fvs) = partitionVarEnv isWeakDmd fvs -thresholdArity :: Id -> CoreExpr -> Arity --- See Note [Demand signatures are computed for a threshold arity based on idArity] -thresholdArity fn rhs - = case idJoinPointHood fn of - JoinPoint join_arity -> count isId $ fst $ collectNBinders join_arity rhs - NotJoinPoint -> idArity fn - -- | The result type after applying 'idArity' many arguments. Returns 'Nothing' -- when the type doesn't have exactly 'idArity' many arrows. resultType_maybe :: Id -> Maybe Type @@ -1243,47 +1238,97 @@ Consider B -> j 4 C -> (p,7)) -If j was a vanilla function definition, we'd analyse its body with -evalDmd, and think that it was lazy in p. But for join points we can -do better! We know that j's body will (if called at all) be evaluated -with the demand that consumes the entire join-binding, in this case -the argument demand from g. Whizzo! g evaluates both components of -its argument pair, so p will certainly be evaluated if j is called. +If j was a vanilla function definition, we'd analyse its body with evalDmd, and +think that it was lazy in p. But for join points we can do better! We know +that j's body will (if called at all) be evaluated with the demand that consumes +the entire join-binding, in this case the argument demand from g. Whizzo! g +evaluates both components of its argument pair, so p will certainly be evaluated +if j is called. -For f to be strict in p, we need /all/ paths to evaluate p; in this -case the C branch does so too, so we are fine. So, as usual, we need -to transport demands on free variables to the call site(s). Compare -Note [Lazy and unleashable free variables]. +For f to be strict in p, we need /all/ paths to evaluate p; in this case the C +branch does so too, so we are fine. So, as usual, we need to transport demands +on free variables to the call site(s). Compare Note [Lazy and unleashable free +variables]. -The implementation is easy. When analysing a join point, we can -analyse its body with the demand from the entire join-binding (written -let_dmd here). +The implementation is easy: see `body_sd` in`dmdAnalRhsSig`. When analysing +a join point, we can analyse its body (after stripping off the join binders, +here just 'y') with the demand from the entire join-binding (written `let_sd` +here). Another win for join points! #13543. -However, note that the strictness signature for a join point can -look a little puzzling. E.g. +BUT see Note [Worker/wrapper arity and join points]. + +Note we may analyse the rhs of a join point with a demand that is either +bigger than, or smaller than, the number of lambdas syntactically visible. +* More lambdas than call demands: + join j x = \p q r -> blah in ... + in a context with demand Top. + +* More call demands than lambdas: + (join j x = h in ..(j 2)..(j 3)) a b c +Note [Worker/wrapper arity and join points] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider (join j x = \y. error "urk") (in case v of ) ( A -> j 3 ) x ( B -> j 4 ) ( C -> \y. blah ) -The entire thing is in a C(1,L) context, so j's strictness signature -will be [A]b -meaning one absent argument, returns bottom. That seems odd because -there's a \y inside. But it's right because when consumed in a C(1,L) -context the RHS of the join point is indeed bottom. +The entire thing is in a C(1,L) context, so we will analyse j's body, namely + \y. error "urk" +with demand C(C(1,L)). See `rhs_sd` in `dmdAnalRhsSig`. That will produce +a demand signature of b: and indeed `j` diverges when given two arguments. + +BUT we do /not/ want to worker/wrapper `j` with two arguments. Suppose we have + join j2 :: Int -> Int -> blah + j2 x = rhs + in ...(j2 3)...(j2 4)... + +where j2's join-arity is 1, so calls to `j` will all have /one/ argument. +Suppose the entire expression is in a called context (like `j` above) and `j2` +gets the demand signature <1!P(L)><1!P(L)>, that is, strict in both arguments. + +we worker/wrapper'd `j2` with two args we'd get + join $wj2 x# y# = let x = I# x#; y = I# y# in rhs + j2 x = \y. case x of I# x# -> case y of I# y# -> $wj2 x# y# + in ...(j2 3)...(j2 4)... +But now `$wj2`is no longer a join point. Boo. + +Instead if we w/w at all, we want to do so only with /one/ argument: + join $wj2 x# = let x = I# x# in rhs + j2 x = case x of I# x# -> $wj2 x# + in ...(j2 3)...(j2 4)... +Now all is fine. BUT in `finaliseArgBoxities` we should trim y's boxity, +to reflect the fact tta we aren't going to unbox `y` at all. + +Conclusion: + +(1) The "worker/wrapper arity" of an Id is + * For non-join-points: idArity + * The join points: the join arity (Id part only of course) + This is the number of args we will use in worker/wrapper. + See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`. -Note [Demand signatures are computed for a threshold arity based on idArity] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Given a binding { f = rhs }, we compute a "theshold arity", and do demand -analysis based on a call with that many value arguments. +(2) A join point's demand-signature arity may exceed the Id's worker/wrapper + arity. See the `arity_ok` assertion in `mkWwBodies`. -The threshold we use is +(3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond + the worker/wrapper arity. -* Ordinary bindings: idArity f. +(4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper + arity (re)-computed by workWrapArity. + +Note [The demand for the RHS of a binding] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Given a binding { f = rhs }, in `dmdAnalRhsSig` we compute a `rhs_sd` in +which to analyse `rhs`. + +The demand we use is: + +* Ordinary bindings: a call-demand of depth (idArity f). Why idArity arguments? Because that's a conservative estimate of how many arguments we must feed a function before it does anything interesting with them. Also it elegantly subsumes the trivial RHS and PAP case. E.g. for @@ -1293,22 +1338,17 @@ The threshold we use is idArity is /at least/ the number of manifest lambdas, but might be higher for PAPs and trivial RHS (see Note [Demand analysis for trivial right-hand sides]). -* Join points: the value-binder subset of the JoinArity. This can - be less than the number of visible lambdas; e.g. - join j x = \y. blah - in ...(jump j 2)....(jump j 3).... - We know that j will never be applied to more than 1 arg (its join - arity, and we don't eta-expand join points, so here a threshold - of 1 is the best we can do. +* Join points: a call-demand of depth (value-binder subset of JoinArity), + wrapped around the incoming demand for the entire expression; see + Note [Demand analysis for join points] Note that the idArity of a function varies independently of its cardinality properties (cf. Note [idArity varies independently of dmdTypeDepth]), so we -implicitly encode the arity for when a demand signature is sound to unleash -in its 'dmdTypeDepth', not in its idArity (cf. Note [Understanding DmdType -and DmdSig] in GHC.Types.Demand). It is unsound to unleash a demand -signature when the incoming number of arguments is less than that. See -GHC.Types.Demand Note [What are demand signatures?] for more details on -soundness. +implicitly encode the arity for when a demand signature is sound to unleash in +its 'dmdTypeDepth', not in its idArity (cf. Note [Understanding DmdType and +DmdSig] in GHC.Types.Demand). It is unsound to unleash a demand signature when +the incoming number of arguments is less than that. See GHC.Types.Demand +Note [DmdSig: demand signatures, and demand-sig arity]. Note that there might, in principle, be functions for which we might want to analyse for more incoming arguments than idArity. Example: @@ -1339,6 +1379,30 @@ signatures for different arities (i.e., polyvariance) would be entirely possible, if it weren't for the additional runtime and implementation complexity. +Note [mkDmdSigForArity] +~~~~~~~~~~~~~~~~~~~~~~~ +Consider + f x = if expensive x + then \y. blah1 + else \y. blah2 +We will analyse the body with demand C(1L), reflecting the single visible +argument x. But dmdAnal will return a DmdType looking like + DmdType fvs [x-dmd, y-dmd] +because it has seen two lambdas, \x and \y. Since the length of the argument +demands in a DmdSig gives the "threshold" for applying the signature +(see Note [DmdSig: demand signatures, and demand-sig arity] in GHC.Types.Demand) +we must trim that DmdType to just + DmdSig (DmdTypte fvs [x-dmd]) +when making that DmdType into the DmdSig for f. This trimming is the job of +`mkDmdSigForArity`. + +Alternative. An alternative would be be to ensure that if + (dmd_ty, e') = dmdAnal env subdmd e +then the length dmds in dmd_ty is always less than (or maybe equal to?) the +call-depth of subdmd. To do that we'd need to adjust the Lam case of dmdAnal. +Probably not hard, but a job for another day; see discussion on !12873, #23113, +and #21392. + Note [idArity varies independently of dmdTypeDepth] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ In general, an Id `f` has two independently varying attributes: @@ -1932,30 +1996,35 @@ positiveTopBudget (MkB n _) = n >= 0 finaliseArgBoxities :: AnalEnv -> Id -> Arity -> [Demand] -> Divergence -> CoreExpr -> ([Demand], CoreExpr) -finaliseArgBoxities env fn threshold_arity rhs_dmds div rhs +-- POSTCONDITION: +-- If: (dmds', rhs') = finaliseArgBoxitities ... dmds .. rhs +-- Then: +-- dmds' is the same as dmds (including length), except for boxity info +-- rhs' is the same as rhs, except for dmd info on lambda binders +-- NB: For join points, length dmds might be greater than ww_arity +finaliseArgBoxities env fn ww_arity arg_dmds div rhs -- Check for an OPAQUE function: see Note [OPAQUE pragma] -- In that case, trim off all boxity info from argument demands -- and demand info on lambda binders -- See Note [The OPAQUE pragma and avoiding the reboxing of arguments] | isOpaquePragma (idInlinePragma fn) - , let trimmed_rhs_dmds = map trimBoxity rhs_dmds - = (trimmed_rhs_dmds, set_lam_dmds trimmed_rhs_dmds rhs) + , let trimmed_arg_dmds = map trimBoxity arg_dmds + = (trimmed_arg_dmds, set_lam_dmds trimmed_arg_dmds rhs) -- Check that we have enough visible binders to match the - -- threshold arity; if not, we won't do worker/wrapper + -- ww arity; if not, we won't do worker/wrapper -- This happens if we have simply {f = g} or a PAP {f = h 13} -- we simply want to give f the same demand signature as g -- How can such bindings arise? Perhaps from {-# NOLINE[2] f #-}, -- or if the call to `f` is currently not-applied (map f xs). -- It's a bit of a corner case. Anyway for now we pass on the -- unadulterated demands from the RHS, without any boxity trimming. - | threshold_arity > count isId bndrs - = (rhs_dmds, rhs) + | ww_arity > count isId bndrs + = (arg_dmds, rhs) -- The normal case - | otherwise -- NB: threshold_arity might be less than - -- manifest arity for join points + | otherwise = -- pprTrace "finaliseArgBoxities" ( -- vcat [text "function:" <+> ppr fn -- , text "max" <+> ppr max_wkr_args @@ -1966,23 +2035,29 @@ finaliseArgBoxities env fn threshold_arity rhs_dmds div rhs -- of the function, both because that's kosher, and because CPR analysis -- uses the info on the binders directly. where - opts = ae_opts env - (bndrs, _body) = collectBinders rhs - unarise_arity = sum [ unariseArity (idType b) | b <- bndrs, isId b ] - max_wkr_args = dmd_max_worker_args opts `max` unarise_arity - -- This is the budget initialisation step of - -- Note [Worker argument budget] - - -- This is the key line, which uses almost-circular programming - -- The remaining budget from one layer becomes the initial - -- budget for the next layer down. See Note [Worker argument budget] - (remaining_budget, arg_dmds') = go_args (MkB max_wkr_args remaining_budget) arg_triples + opts = ae_opts env + (bndrs, _body) = collectBinders rhs + -- NB: in the interesting code path, count isId bndrs >= ww_arity arg_triples :: [(Type, StrictnessMark, Demand)] - arg_triples = take threshold_arity $ + arg_triples = take ww_arity $ [ (idType bndr, NotMarkedStrict, get_dmd bndr) | bndr <- bndrs, isRuntimeVar bndr ] + arg_dmds' = ww_arg_dmds ++ map trimBoxity (drop ww_arity arg_dmds) + -- If ww_arity < length arg_dmds, the leftover ones + -- will not be w/w'd, so trimBoxity them + -- See Note [Worker/wrapper arity and join points] point (3) + + -- This is the key line, which uses almost-circular programming + -- The remaining budget from one layer becomes the initial + -- budget for the next layer down. See Note [Worker argument budget] + (remaining_budget, ww_arg_dmds) = go_args (MkB max_wkr_args remaining_budget) arg_triples + unarise_arity = sum [ unariseArity (idType b) | b <- bndrs, isId b ] + max_wkr_args = dmd_max_worker_args opts `max` unarise_arity + -- This is the budget initialisation step of + -- Note [Worker argument budget] + get_dmd :: Id -> Demand get_dmd bndr | is_bot_fn = unboxDeeplyDmd dmd -- See Note [Boxity for bottoming functions], ===================================== compiler/GHC/Core/Opt/WorkWrap.hs ===================================== @@ -758,11 +758,11 @@ by LitRubbish (see Note [Drop absent bindings]) so there is no great harm. --------------------- splitFun :: WwOpts -> Id -> CoreExpr -> UniqSM [(Id, CoreExpr)] splitFun ww_opts fn_id rhs - | Just (arg_vars, body) <- collectNValBinders_maybe (length wrap_dmds) rhs + | Just (arg_vars, body) <- collectNValBinders_maybe ww_arity rhs = warnPprTrace (not (wrap_dmds `lengthIs` (arityInfo fn_info))) "splitFun" (ppr fn_id <+> (ppr wrap_dmds $$ ppr cpr)) $ - do { mb_stuff <- mkWwBodies ww_opts fn_id arg_vars (exprType body) wrap_dmds cpr + do { mb_stuff <- mkWwBodies ww_opts fn_id ww_arity arg_vars (exprType body) wrap_dmds cpr ; case mb_stuff of Nothing -> -- No useful wrapper; leave the binding alone return [(fn_id, rhs)] @@ -794,8 +794,10 @@ splitFun ww_opts fn_id rhs = return [(fn_id, rhs)] where - uf_opts = so_uf_opts (wo_simple_opts ww_opts) - fn_info = idInfo fn_id + uf_opts = so_uf_opts (wo_simple_opts ww_opts) + fn_info = idInfo fn_id + ww_arity = workWrapArity fn_id rhs + -- workWrapArity: see (4) in Note [Worker/wrapper arity and join points] in DmdAnal (wrap_dmds, div) = splitDmdSig (dmdSigInfo fn_info) ===================================== compiler/GHC/Core/Opt/WorkWrap/Utils.hs ===================================== @@ -15,7 +15,7 @@ module GHC.Core.Opt.WorkWrap.Utils , findTypeShape, IsRecDataConResult(..), isRecDataCon , mkAbsentFiller , isWorkerSmallEnough, dubiousDataConInstArgTys - , boringSplit , usefulSplit + , boringSplit, usefulSplit, workWrapArity ) where @@ -159,6 +159,7 @@ nop_fn body = body mkWwBodies :: WwOpts -> Id -- ^ The original function + -> Arity -- ^ Worker/wrapper arity -> [Var] -- ^ Manifest args of original function -> Type -- ^ Result type of the original function, -- after being stripped of args @@ -205,8 +206,8 @@ mkWwBodies :: WwOpts -- and beta-redexes]), which allows us to apply the same split to function body -- and its unfolding(s) alike. -- -mkWwBodies opts fun_id arg_vars res_ty demands res_cpr - = do { massertPpr (filter isId arg_vars `equalLength` demands) +mkWwBodies opts fun_id ww_arity arg_vars res_ty demands res_cpr + = do { massertPpr arity_ok (text "wrong wrapper arity" $$ ppr fun_id $$ ppr arg_vars $$ ppr res_ty $$ ppr demands) -- Clone and prepare arg_vars of the original fun RHS @@ -271,6 +272,10 @@ mkWwBodies opts fun_id arg_vars res_ty demands res_cpr | otherwise = False + n_dmds = length demands + arity_ok | isJoinId fun_id = ww_arity <= n_dmds + | otherwise = ww_arity == n_dmds + -- | Version of 'GHC.Core.mkApps' that does beta reduction on-the-fly. -- PRECONDITION: The arg expressions are not free in any of the lambdas binders. mkAppsBeta :: CoreExpr -> [CoreArg] -> CoreExpr @@ -288,6 +293,13 @@ isWorkerSmallEnough max_worker_args old_n_args vars -- Also if the function took 82 arguments before (old_n_args), it's fine if -- it takes <= 82 arguments afterwards. +workWrapArity :: Id -> CoreExpr -> Arity +-- See Note [Worker/wrapper arity and join points] in DmdAnal +workWrapArity fn rhs + = case idJoinPointHood fn of + JoinPoint join_arity -> count isId $ fst $ collectNBinders join_arity rhs + NotJoinPoint -> idArity fn + {- Note [Always do CPR w/w] ~~~~~~~~~~~~~~~~~~~~~~~~ ===================================== compiler/GHC/Types/Demand.hs ===================================== @@ -1,3 +1,4 @@ + {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE BinaryLiterals #-} {-# LANGUAGE PatternSynonyms #-} @@ -38,7 +39,7 @@ module GHC.Types.Demand ( lazyApply1Dmd, lazyApply2Dmd, strictOnceApply1Dmd, strictManyApply1Dmd, -- ** Other @Demand@ operations oneifyCard, oneifyDmd, strictifyDmd, strictifyDictDmd, lazifyDmd, - peelCallDmd, peelManyCalls, mkCalledOnceDmd, mkCalledOnceDmds, + peelCallDmd, peelManyCalls, mkCalledOnceDmd, mkCalledOnceDmds, strictCallArity, mkWorkerDemand, subDemandIfEvaluated, -- ** Extracting one-shot information callCards, argOneShots, argsOneShots, saturatedByOneShots, @@ -1037,6 +1038,12 @@ peelManyCalls k sd = go k C_11 sd go _ _ _ = (topCard, topSubDmd) {-# INLINE peelManyCalls #-} -- so that the pair cancels away in a `fst _` context +strictCallArity :: SubDemand -> Arity +strictCallArity sd = go 0 sd + where + go n (Call card sd) | isStrict card = go (n+1) sd + go n _ = n + -- | Extract the 'SubDemand' of a 'Demand'. -- PRECONDITION: The SubDemand must be used in a context where the expression -- denoted by the Demand is under evaluation. @@ -2073,6 +2080,12 @@ body of the function. * * ************************************************************************ +Note [DmdSig: demand signatures, and demand-sig arity] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +See also + * Note [Demand signatures semantically] + * Note [Understanding DmdType and DmdSig] + In a let-bound Id we record its demand signature. In principle, this demand signature is a demand transformer, mapping a demand on the Id into a DmdType, which gives @@ -2083,20 +2096,22 @@ a demand on the Id into a DmdType, which gives However, in fact we store in the Id an extremely emasculated demand transformer, namely - - a single DmdType + a single DmdType (Nevertheless we dignify DmdSig as a distinct type.) -This DmdType gives the demands unleashed by the Id when it is applied -to as many arguments as are given in by the arg demands in the DmdType. +The DmdSig for an Id is a semantic thing. Suppose a function `f` has a DmdSig of + DmdSig (DmdType (fv_dmds,res) [d1..dn]) +Here `n` is called the "demand-sig arity" of the DmdSig. The signature means: + * If you apply `f` to n arguments (the demand-sig-arity) + * then you can unleash demands d1..dn on the arguments + * and demands fv_dmds on the free variables. Also see Note [Demand type Divergence] for the meaning of a Divergence in a -strictness signature. +demand signature. -If an Id is applied to less arguments than its arity, it means that -the demand on the function at a call site is weaker than the vanilla -call demand, used for signature inference. Therefore we place a top -demand on all arguments. Otherwise, the demand is specified by Id's -signature. +If `f` is applied to fewer value arguments than its demand-sig arity, it means +that the demand on the function at a call site is weaker than the vanilla call +demand, used for signature inference. Therefore we place a top demand on all +arguments. For example, the demand transformer described by the demand signature DmdSig (DmdType {x -> <1L>} <1P(L,L)>) @@ -2107,6 +2122,61 @@ and 1P(L,L) on the second. If this same function is applied to one arg, all we can say is that it uses x with 1L, and its arg with demand 1P(L,L). +Note [Demand signatures semantically] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Demand analysis interprets expressions in the abstract domain of demand +transformers. Given a (sub-)demand that denotes the evaluation context, the +abstract transformer of an expression gives us back a demand type denoting +how other things (like arguments and free vars) were used when the expression +was evaluated. Here's an example: + + f x y = + if x + expensive + then \z -> z + y * ... + else \z -> z * ... + +The abstract transformer (let's call it F_e) of the if expression (let's +call it e) would transform an incoming (undersaturated!) head sub-demand A +into a demand type like {x-><1L>,y->}. In pictures: + + SubDemand ---F_e---> DmdType + {x-><1L>,y->} + +Let's assume that the demand transformers we compute for an expression are +correct wrt. to some concrete semantics for Core. How do demand signatures fit +in? They are strange beasts, given that they come with strict rules when to +it's sound to unleash them. + +Fortunately, we can formalise the rules with Galois connections. Consider +f's strictness signature, {}<1L>. It's a single-point approximation of +the actual abstract transformer of f's RHS for arity 2. So, what happens is that +we abstract *once more* from the abstract domain we already are in, replacing +the incoming Demand by a simple lattice with two elements denoting incoming +arity: A_2 = {<2, >=2} (where '<2' is the top element and >=2 the bottom +element). Here's the diagram: + + A_2 -----f_f----> DmdType + ^ | + | α γ | + | v + SubDemand --F_f----> DmdType + +With + α(C(1,C(1,_))) = >=2 + α(_) = <2 + γ(ty) = ty +and F_f being the abstract transformer of f's RHS and f_f being the abstracted +abstract transformer computable from our demand signature simply by + + f_f(>=2) = {}<1L> + f_f(<2) = multDmdType C_0N {}<1L> + +where multDmdType makes a proper top element out of the given demand type. + +In practice, the A_n domain is not just a simple Bool, but a Card, which is +exactly the Card with which we have to multDmdType. The Card for arity n +is computed by calling @peelManyCalls n@, which corresponds to α above. + Note [Understanding DmdType and DmdSig] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Demand types are sound approximations of an expression's semantics relative to @@ -2119,10 +2189,10 @@ Here is a table with demand types resulting from different incoming demands we put that expression under. Note the monotonicity; a stronger incoming demand yields a more precise demand type: - incoming demand | demand type + incoming sub-demand | demand type -------------------------------- - 1A | {} - C(1,C(1,L)) | <1P(L)>{} + P(A) | {} + C(1,C(1,P(L))) | <1P(L)>{} C(1,C(1,1P(1P(L),A))) | <1P(A)>{} Note that in the first example, the depth of the demand type was *higher* than @@ -2143,11 +2213,11 @@ being a newtype wrapper around DmdType, it actually encodes two things: * A demand type that is sound to unleash when the minimum arity requirement is met. -Here comes the subtle part: The threshold is encoded in the wrapped demand -type's depth! So in mkDmdSigForArity we make sure to trim the list of -argument demands to the given threshold arity. Call sites will make sure that -this corresponds to the arity of the call demand that elicited the wrapped -demand type. See also Note [What are demand signatures?]. +Here comes the subtle part: The threshold is encoded in the demand-sig arity! +So in mkDmdSigForArity we make sure to trim the list of argument demands to the +given threshold arity. Call sites will make sure that this corresponds to the +arity of the call demand that elicited the wrapped demand type. See also +Note [DmdSig: demand signatures, and demand-sig arity] -} -- | The depth of the wrapped 'DmdType' encodes the arity at which it is safe @@ -2160,9 +2230,11 @@ newtype DmdSig -- | Turns a 'DmdType' computed for the particular 'Arity' into a 'DmdSig' -- unleashable at that arity. See Note [Understanding DmdType and DmdSig]. mkDmdSigForArity :: Arity -> DmdType -> DmdSig -mkDmdSigForArity arity dmd_ty@(DmdType fvs args) - | arity < dmdTypeDepth dmd_ty = DmdSig $ DmdType fvs (take arity args) - | otherwise = DmdSig (etaExpandDmdType arity dmd_ty) +mkDmdSigForArity threshold_arity dmd_ty@(DmdType fvs args) + | threshold_arity < dmdTypeDepth dmd_ty + = DmdSig $ DmdType (fvs { de_div = topDiv }) (take threshold_arity args) + | otherwise + = DmdSig (etaExpandDmdType threshold_arity dmd_ty) mkClosedDmdSig :: [Demand] -> Divergence -> DmdSig mkClosedDmdSig ds div = mkDmdSigForArity (length ds) (DmdType (mkEmptyDmdEnv div) ds) @@ -2307,7 +2379,7 @@ etaConvertDmdSig arity (DmdSig dmd_ty) -- whether it diverges. -- -- See Note [Understanding DmdType and DmdSig] --- and Note [What are demand signatures?]. +-- and Note [DmdSig: demand signatures, and demand-sig arity] type DmdTransformer = SubDemand -> DmdType -- | Extrapolate a demand signature ('DmdSig') into a 'DmdTransformer'. @@ -2318,7 +2390,7 @@ dmdTransformSig :: DmdSig -> DmdTransformer dmdTransformSig (DmdSig dmd_ty@(DmdType _ arg_ds)) sd = multDmdType (fst $ peelManyCalls (length arg_ds) sd) dmd_ty -- see Note [Demands from unsaturated function calls] - -- and Note [What are demand signatures?] + -- and Note [DmdSig: demand signatures, and demand-sig arity] -- | A special 'DmdTransformer' for data constructors that feeds product -- demands into the constructor arguments. @@ -2356,61 +2428,6 @@ dmdTransformDictSelSig (DmdSig (DmdType _ [_ :* prod])) call_sd dmdTransformDictSelSig sig sd = pprPanic "dmdTransformDictSelSig: no args" (ppr sig $$ ppr sd) {- -Note [What are demand signatures?] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Demand analysis interprets expressions in the abstract domain of demand -transformers. Given a (sub-)demand that denotes the evaluation context, the -abstract transformer of an expression gives us back a demand type denoting -how other things (like arguments and free vars) were used when the expression -was evaluated. Here's an example: - - f x y = - if x + expensive - then \z -> z + y * ... - else \z -> z * ... - -The abstract transformer (let's call it F_e) of the if expression (let's -call it e) would transform an incoming (undersaturated!) head demand 1A into -a demand type like {x-><1L>,y->}. In pictures: - - Demand ---F_e---> DmdType - <1A> {x-><1L>,y->} - -Let's assume that the demand transformers we compute for an expression are -correct wrt. to some concrete semantics for Core. How do demand signatures fit -in? They are strange beasts, given that they come with strict rules when to -it's sound to unleash them. - -Fortunately, we can formalise the rules with Galois connections. Consider -f's strictness signature, {}<1L>. It's a single-point approximation of -the actual abstract transformer of f's RHS for arity 2. So, what happens is that -we abstract *once more* from the abstract domain we already are in, replacing -the incoming Demand by a simple lattice with two elements denoting incoming -arity: A_2 = {<2, >=2} (where '<2' is the top element and >=2 the bottom -element). Here's the diagram: - - A_2 -----f_f----> DmdType - ^ | - | α γ | - | v - SubDemand --F_f----> DmdType - -With - α(C(1,C(1,_))) = >=2 - α(_) = <2 - γ(ty) = ty -and F_f being the abstract transformer of f's RHS and f_f being the abstracted -abstract transformer computable from our demand signature simply by - - f_f(>=2) = {}<1L> - f_f(<2) = multDmdType C_0N {}<1L> - -where multDmdType makes a proper top element out of the given demand type. - -In practice, the A_n domain is not just a simple Bool, but a Card, which is -exactly the Card with which we have to multDmdType. The Card for arity n -is computed by calling @peelManyCalls n@, which corresponds to α above. - Note [Demand transformer for a dictionary selector] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Suppose we have a superclass selector 'sc_sel' and a class method ===================================== testsuite/tests/dmdanal/should_compile/T24623.hs ===================================== @@ -0,0 +1,16 @@ +-- This gave a Lint error in HEAD (Jun 24) +module T24623 where + +{-# NOINLINE app #-} +app :: Int -> (Int -> (Int,Int)) -> (Int,Int) +app x f = if x>0 then f x else (0,0) + +foo :: String -> Bool -> Bool -> Int -> (Int,Int) +foo s b b2 y = app y (let {-# NOINLINE j #-} + j :: Int -> (Int,Int) + j = \z -> error s + in case b of + True -> j + False -> case b2 of + True -> \x -> (x-1, x+1) + False -> j) ===================================== testsuite/tests/dmdanal/should_compile/all.T ===================================== @@ -97,3 +97,4 @@ test('T22388', [ grep_errmsg(r'^\S+\$w\S+') ], compile, ['-dsuppress-uniques -dd # T22997: Just a panic that should not happen test('T22997', normal, compile, ['']) test('T23398', normal, compile, ['-dsuppress-uniques -ddump-simpl -dno-typeable-binds']) +test('T24623', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9a757a27ee95afa092899b404cb95881c7578202 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9a757a27ee95afa092899b404cb95881c7578202 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 11:24:49 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 20 Jun 2024 07:24:49 -0400 Subject: [Git][ghc/ghc][master] Update haddocks of Import/Export AST types Message-ID: <667411818428d_6081122e80897290@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 5e8faaf1 by Jan Hrček at 2024-06-20T07:23:20-04:00 Update haddocks of Import/Export AST types - - - - - 11 changed files: - compiler/GHC/Core/DataCon.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/ThToHs.hs - compiler/GHC/Types/Basic.hs - compiler/GHC/Types/ForeignCall.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/Language/Haskell/Syntax/ImpExp.hs Changes: ===================================== compiler/GHC/Core/DataCon.hs ===================================== @@ -849,7 +849,7 @@ type DataConEnv a = UniqFM DataCon a -- Keyed by DataCon -- emit a warning (in checkValidDataCon) and treat it like -- @(HsSrcBang _ NoSrcUnpack SrcLazy)@ data HsSrcBang = - HsSrcBang SourceText -- Note [Pragma source text] in "GHC.Types.SourceText" + HsSrcBang SourceText -- See Note [Pragma source text] in "GHC.Types.SourceText" SrcUnpackedness SrcStrictness deriving Data.Data ===================================== compiler/GHC/Hs/Binds.hs ===================================== @@ -714,7 +714,7 @@ type instance XSpecInstSig (GhcPass p) = ([AddEpAnn], SourceText) type instance XMinimalSig (GhcPass p) = ([AddEpAnn], SourceText) type instance XSCCFunSig (GhcPass p) = ([AddEpAnn], SourceText) type instance XCompleteMatchSig (GhcPass p) = ([AddEpAnn], SourceText) - -- SourceText: Note [Pragma source text] in "GHC.Types.SourceText" + -- SourceText: See Note [Pragma source text] in "GHC.Types.SourceText" type instance XXSig GhcPs = DataConCantHappen type instance XXSig GhcRn = IdSig type instance XXSig GhcTc = IdSig ===================================== compiler/GHC/Hs/Extension.hs ===================================== @@ -172,11 +172,15 @@ type GhcTc = GhcPass 'Typechecked -- Output of typechecker -- | Allows us to check what phase we're in at GHC's runtime. -- For example, this class allows us to write --- > f :: forall p. IsPass p => HsExpr (GhcPass p) -> blah --- > f e = case ghcPass @p of --- > GhcPs -> ... in this RHS we have HsExpr GhcPs... --- > GhcRn -> ... in this RHS we have HsExpr GhcRn... --- > GhcTc -> ... in this RHS we have HsExpr GhcTc... +-- +-- @ +-- f :: forall p. IsPass p => HsExpr (GhcPass p) -> blah +-- f e = case ghcPass @p of +-- GhcPs -> ... in this RHS we have HsExpr GhcPs... +-- GhcRn -> ... in this RHS we have HsExpr GhcRn... +-- GhcTc -> ... in this RHS we have HsExpr GhcTc... +-- @ +-- -- which is very useful, for example, when pretty-printing. -- See Note [IsPass]. class ( NoGhcTcPass (NoGhcTcPass p) ~ NoGhcTcPass p ===================================== compiler/GHC/Hs/ImpExp.hs ===================================== @@ -81,11 +81,10 @@ type instance ImportDeclPkgQual GhcTc = PkgQual type instance XCImportDecl GhcPs = XImportDeclPass type instance XCImportDecl GhcRn = XImportDeclPass type instance XCImportDecl GhcTc = DataConCantHappen - -- Note [Pragma source text] in "GHC.Types.SourceText" data XImportDeclPass = XImportDeclPass { ideclAnn :: EpAnn EpAnnImportDecl - , ideclSourceText :: SourceText + , ideclSourceText :: SourceText -- Note [Pragma source text] in "GHC.Types.SourceText" , ideclImplicit :: Bool -- ^ GHC generates an `ImportDecl` to represent the invisible `import Prelude` -- that appears in any file that omits `import Prelude`, setting @@ -112,12 +111,12 @@ deriving instance Eq (IEWrappedName GhcTc) -- API Annotations types data EpAnnImportDecl = EpAnnImportDecl - { importDeclAnnImport :: EpaLocation - , importDeclAnnPragma :: Maybe (EpaLocation, EpaLocation) - , importDeclAnnSafe :: Maybe EpaLocation - , importDeclAnnQualified :: Maybe EpaLocation - , importDeclAnnPackage :: Maybe EpaLocation - , importDeclAnnAs :: Maybe EpaLocation + { importDeclAnnImport :: EpaLocation -- ^ The location of the @import@ keyword + , importDeclAnnPragma :: Maybe (EpaLocation, EpaLocation) -- ^ The locations of @{-# SOURCE@ and @#-}@ respectively + , importDeclAnnSafe :: Maybe EpaLocation -- ^ The location of the @safe@ keyword + , importDeclAnnQualified :: Maybe EpaLocation -- ^ The location of the @qualified@ keyword + , importDeclAnnPackage :: Maybe EpaLocation -- ^ The location of the package name (when using @-XPackageImports@) + , importDeclAnnAs :: Maybe EpaLocation -- ^ The location of the @as@ keyword } deriving (Data) instance NoAnn EpAnnImportDecl where ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -863,7 +863,7 @@ data Token | ITdependency | ITrequires - -- Pragmas, see Note [Pragma source text] in "GHC.Types.SourceText" + -- Pragmas, see Note [Pragma source text] in "GHC.Types.SourceText" | ITinline_prag SourceText InlineSpec RuleMatchInfo | ITopaque_prag SourceText | ITspec_prag SourceText -- SPECIALISE ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -2721,7 +2721,7 @@ mkInlinePragma :: SourceText -> (InlineSpec, RuleMatchInfo) -> Maybe Activation -- The (Maybe Activation) is because the user can omit -- the activation spec (and usually does) mkInlinePragma src (inl, match_info) mb_act - = InlinePragma { inl_src = src -- Note [Pragma source text] in "GHC.Types.SourceText" + = InlinePragma { inl_src = src -- See Note [Pragma source text] in "GHC.Types.SourceText" , inl_inline = inl , inl_sat = Nothing , inl_act = act ===================================== compiler/GHC/ThToHs.hs ===================================== @@ -1883,7 +1883,7 @@ In the process, all parens are stripped out, as they are not needed. This Convert module then converts the TH AST back to hsSyn AST. -In order to pretty-print this hsSyn AST, parens need to be adde back at certain +In order to pretty-print this hsSyn AST, parens need to be added back at certain points so that the code is readable with its original meaning. So scattered through "GHC.ThToHs" are various points where parens are added. ===================================== compiler/GHC/Types/Basic.hs ===================================== @@ -1571,7 +1571,7 @@ no harm. data InlinePragma -- Note [InlinePragma] = InlinePragma - { inl_src :: SourceText -- Note [Pragma source text] + { inl_src :: SourceText -- See Note [Pragma source text] , inl_inline :: InlineSpec -- See Note [inl_inline and inl_act] , inl_sat :: Maybe Arity -- Just n <=> Inline only when applied to n ===================================== compiler/GHC/Types/ForeignCall.hs ===================================== @@ -222,7 +222,7 @@ instance Outputable CCallSpec where = text "__ffi_dyn_ccall" <> gc_suf <+> text "\"\"" -- The filename for a C header file --- Note [Pragma source text] in "GHC.Types.SourceText" +-- See Note [Pragma source text] in "GHC.Types.SourceText" data Header = Header SourceText FastString deriving (Eq, Data) @@ -236,7 +236,7 @@ instance Outputable Header where -- 'GHC.Parser.Annotation.AnnClose' @'\#-}'@, -- For details on above see Note [exact print annotations] in "GHC.Parser.Annotation" -data CType = CType SourceText -- Note [Pragma source text] in "GHC.Types.SourceText" +data CType = CType SourceText -- See Note [Pragma source text] in "GHC.Types.SourceText" (Maybe Header) -- header to include for this type (SourceText,FastString) -- the type itself deriving (Eq, Data) ===================================== compiler/Language/Haskell/Syntax/Expr.hs ===================================== @@ -285,7 +285,8 @@ data HsExpr p | HsOverLabel (XOverLabel p) SourceText FastString -- ^ Overloaded label (Note [Overloaded labels] in GHC.OverloadedLabels) - -- Note [Pragma source text] in GHC.Types.SourceText + + -- See Note [Pragma source text] in "GHC.Types.SourceText" | HsIPVar (XIPVar p) HsIPName -- ^ Implicit parameter (not in use after typechecking) ===================================== compiler/Language/Haskell/Syntax/ImpExp.hs ===================================== @@ -30,11 +30,6 @@ One per import declaration in a module. -- | Located Import Declaration type LImportDecl pass = XRec pass (ImportDecl pass) - -- ^ When in a list this may have - -- - -- - 'GHC.Parser.Annotation.AnnKeywordId' : 'GHC.Parser.Annotation.AnnSemi' - - -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation -- | If/how an import is 'qualified'. data ImportDeclQualifiedStyle @@ -58,10 +53,10 @@ instance NFData IsBootInterface where -- A single Haskell @import@ declaration. data ImportDecl pass = ImportDecl { - ideclExt :: XCImportDecl pass, + ideclExt :: XCImportDecl pass, -- ^ Locations of keywords like @import@, @qualified@, etc. are captured here. ideclName :: XRec pass ModuleName, -- ^ Module name. ideclPkgQual :: ImportDeclPkgQual pass, -- ^ Package qualifier. - ideclSource :: IsBootInterface, -- ^ IsBoot <=> {-\# SOURCE \#-} import + ideclSource :: IsBootInterface, -- ^ IsBoot \<=> {-\# SOURCE \#-} import ideclSafe :: Bool, -- ^ True => safe import ideclQualified :: ImportDeclQualifiedStyle, -- ^ If/how the import is qualified. ideclAs :: Maybe (XRec pass ModuleName), -- ^ as Module @@ -69,24 +64,8 @@ data ImportDecl pass -- ^ Explicit import list (EverythingBut => hiding, names) } | XImportDecl !(XXImportDecl pass) - -- ^ - -- 'GHC.Parser.Annotation.AnnKeywordId's - -- - -- - 'GHC.Parser.Annotation.AnnImport' - -- - -- - 'GHC.Parser.Annotation.AnnOpen', 'GHC.Parser.Annotation.AnnClose' for ideclSource - -- - -- - 'GHC.Parser.Annotation.AnnSafe','GHC.Parser.Annotation.AnnQualified', - -- 'GHC.Parser.Annotation.AnnPackageName','GHC.Parser.Annotation.AnnAs', - -- 'GHC.Parser.Annotation.AnnVal' - -- - -- - 'GHC.Parser.Annotation.AnnHiding','GHC.Parser.Annotation.AnnOpen', - -- 'GHC.Parser.Annotation.AnnClose' attached - -- to location in ideclImportList - - -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation - --- | Whether the import list is exactly what to import, or whether `hiding` was + +-- | Whether the import list is exactly what to import, or whether @hiding@ was -- used, and therefore everything but what was listed should be imported data ImportListInterpretation = Exactly | EverythingBut deriving (Eq, Data) @@ -107,7 +86,7 @@ type ExportDoc pass = LHsDoc pass -- | Imported or exported entity. data IE pass - = IEVar (XIEVar pass) (LIEWrappedName pass) (Maybe (ExportDoc pass)) + = IEVar (XIEVar pass) (LIEWrappedName pass) (Maybe (ExportDoc pass)) -- ^ Imported or exported variable -- -- @ @@ -115,36 +94,34 @@ data IE pass -- import Mod ( test ) -- @ - | IEThingAbs (XIEThingAbs pass) (LIEWrappedName pass) (Maybe (ExportDoc pass)) + | IEThingAbs (XIEThingAbs pass) (LIEWrappedName pass) (Maybe (ExportDoc pass)) -- ^ Imported or exported Thing with absent subordinate list -- - -- The thing is a typeclass or type (can't tell) - -- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnPattern', - -- 'GHC.Parser.Annotation.AnnType','GHC.Parser.Annotation.AnnVal' + -- The thing is a Class\/Type (can't tell) -- -- @ -- module Mod ( Test ) -- import Mod ( Test ) -- @ - -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation -- See Note [Located RdrNames] in GHC.Hs.Expr | IEThingAll (XIEThingAll pass) (LIEWrappedName pass) (Maybe (ExportDoc pass)) - -- ^ Imported or exported thing with wildcard subordinate list (e..g @(..)@) + -- ^ Imported or exported thing with wildcard subordinate list (e.g. @(..)@) -- - -- The thing is a Class/Type and the All refers to methods/constructors + -- The thing is a Class\/Type and the All refers to methods\/constructors -- - -- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnOpen', - -- 'GHC.Parser.Annotation.AnnDotdot','GHC.Parser.Annotation.AnnClose', - -- 'GHC.Parser.Annotation.AnnType' -- @ -- module Mod ( Test(..) ) -- import Mod ( Test(..) ) -- @ + -- + -- exactprint: the location of parens and @..@ is captured via 'GHC.Parser.Annotation.AnnKeywordId's : + -- 'GHC.Parser.Annotation.AnnOpenP', + -- 'GHC.Parser.Annotation.AnnDotdot', + -- 'GHC.Parser.Annotation.AnnCloseP' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation -- See Note [Located RdrNames] in GHC.Hs.Expr - | IEThingWith (XIEThingWith pass) (LIEWrappedName pass) IEWildcard @@ -152,31 +129,30 @@ data IE pass (Maybe (ExportDoc pass)) -- ^ Imported or exported thing with explicit subordinate list. -- - -- The thing is a Class/Type and the imported or exported things are + -- The thing is a Class\/Type (can't tell) and the imported or exported things are -- its children. - -- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnOpen', - -- 'GHC.Parser.Annotation.AnnClose', - -- 'GHC.Parser.Annotation.AnnComma', - -- 'GHC.Parser.Annotation.AnnType' + -- -- @ - -- module Mod ( Test(..) ) - -- import Mod ( Test(..) ) + -- module Mod ( Test(f, g) ) + -- import Mod ( Test(f, g) ) -- @ + -- + -- exactprint: the location of parens is captured via 'GHC.Parser.Annotation.AnnKeywordId's : + -- 'GHC.Parser.Annotation.AnnOpenP', 'GHC.Parser.Annotation.AnnCloseP' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation | IEModuleContents (XIEModuleContents pass) (XRec pass ModuleName) - -- ^ Imported or exported module contents - -- - -- (Export Only) - -- - -- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnModule' + -- ^ Export of entire module. Can only occur in export list. -- -- @ -- module Mod ( module Mod2 ) -- @ + -- + -- exactprint: the location of @module@ keyword is capture via 'GHC.Parser.Annotation.AnnKeywordId' : + -- 'GHC.Parser.Annotation.AnnModule' -- For details on above see Note [exact print annotations] in GHC.Parser.Annotation - | IEGroup (XIEGroup pass) Int (LHsDoc pass) -- ^ Doc section heading + | IEGroup (XIEGroup pass) Int (LHsDoc pass) -- ^ A Haddock section in an export list. -- -- @ @@ -185,7 +161,7 @@ data IE pass -- ... -- ) -- @ - | IEDoc (XIEDoc pass) (LHsDoc pass) -- ^ Some documentation + | IEDoc (XIEDoc pass) (LHsDoc pass) -- ^ A bit of unnamed documentation. -- -- @ @@ -194,7 +170,7 @@ data IE pass -- ... -- ) -- @ - | IEDocNamed (XIEDocNamed pass) String -- ^ Reference to named doc + | IEDocNamed (XIEDocNamed pass) String -- ^ A reference to a named documentation chunk. -- -- @ @@ -216,17 +192,16 @@ data IEWildcard -- | A name in an import or export specification which may have -- adornments. Used primarily for accurate pretty printing of --- ParsedSource, and API Annotation placement. The --- 'GHC.Parser.Annotation' is the location of the adornment in --- the original source. +-- ParsedSource, and API Annotation placement. data IEWrappedName p - = IEName (XIEName p) (LIdP p) -- ^ no extra - | IEPattern (XIEPattern p) (LIdP p) -- ^ pattern X - | IEType (XIEType p) (LIdP p) -- ^ type (:+:) + = IEName (XIEName p) (LIdP p) -- ^ unadorned name, e.g @myFun@ + | IEPattern (XIEPattern p) (LIdP p) -- ^ @pattern X@ + -- + -- exactprint: the location of @pattern@ keyword is captured via 'GHC.Parser.Annotation.EpaLocation' + | IEType (XIEType p) (LIdP p) -- ^ @type (:+:)@ + -- + -- exactprint: the location of @type@ keyword is captured via 'GHC.Parser.Annotation.EpaLocation' | XIEWrappedName !(XXIEWrappedName p) -- | Located name with possible adornment --- - 'GHC.Parser.Annotation.AnnKeywordId's : 'GHC.Parser.Annotation.AnnType', --- 'GHC.Parser.Annotation.AnnPattern' type LIEWrappedName p = XRec p (IEWrappedName p) --- For details on above see Note [exact print annotations] in GHC.Parser.Annotation View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5e8faaf143d50c4ac88dafb7e440e85fbcedf1fc -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5e8faaf143d50c4ac88dafb7e440e85fbcedf1fc You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 11:25:46 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 20 Jun 2024 07:25:46 -0400 Subject: [Git][ghc/ghc][master] haddock: Update bounds in cabal files and remove allow-newer stanza in cabal.project Message-ID: <667411babd8f5_608112325d41004bb@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: cd512234 by Hécate Kleidukos at 2024-06-20T07:24:02-04:00 haddock: Update bounds in cabal files and remove allow-newer stanza in cabal.project - - - - - 4 changed files: - utils/haddock/cabal.project - utils/haddock/haddock-library/haddock-library.cabal - utils/haddock/haddock-test/haddock-test.cabal - utils/haddock/haddock.cabal Changes: ===================================== utils/haddock/cabal.project ===================================== @@ -5,12 +5,6 @@ packages: ./ test-show-details: direct -allow-newer: - ghc-paths:Cabal, - *:base, - *:ghc-prim, - tree-diff:time - package haddock-library tests: False @@ -18,4 +12,4 @@ package haddock-api tests: False -- Pinning the index-state helps to make reasonably CI deterministic -index-state: 2023-05-22T15:14:29Z +index-state: 2024-06-18T11:54:44Z ===================================== utils/haddock/haddock-library/haddock-library.cabal ===================================== @@ -33,7 +33,7 @@ common lib-defaults default-language: Haskell2010 build-depends: - , base >= 4.10 && < 4.20 + , base >= 4.10 && < 4.21 , containers ^>= 0.4.2.1 || ^>= 0.5.0.0 || ^>= 0.6.0.1 || ^>= 0.7 , text ^>= 1.2.3.0 || ^>= 2.0 || ^>= 2.1 , parsec ^>= 3.1.13.0 @@ -79,9 +79,9 @@ test-suite spec Documentation.Haddock.Parser.Identifier build-depends: - , base-compat ^>= 0.12.0 || ^>= 0.13.0 - , QuickCheck ^>= 2.11 || ^>= 2.13.2 || ^>= 2.14 - , deepseq ^>= 1.3.0.0 || ^>= 1.4.0.0 || ^>=1.5.0.0 + , base-compat >= 0.12.0 && <0.15.0 + , QuickCheck >= 2.11 && <2.16 + , deepseq >= 1.3.0.0 && <1.6.0.0 -- NB: build-depends & build-tool-depends have independent -- install-plans, so it's best to limit to a single major @@ -106,8 +106,8 @@ test-suite fixtures , base -- extra dependencies - , base-compat ^>= 0.12.0 || ^>=0.13.0 + , base-compat , directory ^>= 1.3.0.2 - , filepath ^>= 1.4.1.2 + , filepath >= 1.4 && <1.6 , optparse-applicative >= 0.15 && < 0.19 , tree-diff ^>= 0.2 || ^>= 0.3 ===================================== utils/haddock/haddock-test/haddock-test.cabal ===================================== @@ -16,7 +16,7 @@ library default-language: Haskell2010 ghc-options: -Wall hs-source-dirs: src - build-depends: base >= 4.3 && < 4.20, bytestring, directory, process, filepath, Cabal + build-depends: base >= 4.3 && < 4.21, bytestring, directory, process, filepath, Cabal exposed-modules: Test.Haddock ===================================== utils/haddock/haddock.cabal ===================================== @@ -79,7 +79,7 @@ executable haddock -- haddock typically only supports a single GHC major version build-depends: - base ^>= 4.13.0.0 || ^>= 4.14.0.0 || ^>= 4.15.0.0 || ^>= 4.16.0.0 || ^>= 4.17.0.0 || ^>= 4.18.0.0 || ^>= 4.19.0.0 || ^>= 4.20.0.0 + base >= 4.13.0.0 && <4.21 if flag(in-ghc-tree) hs-source-dirs: haddock-api/src, haddock-library/src View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cd51223492e567edb39aa65fff5a37ffac2db327 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cd51223492e567edb39aa65fff5a37ffac2db327 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 11:26:36 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 20 Jun 2024 07:26:36 -0400 Subject: [Git][ghc/ghc][master] cmm: Don't parse MO_BSwap for W8 Message-ID: <667411ec82d40_608118a1668108160@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 8a8ff8f2 by Rodrigo Mesquita at 2024-06-20T07:24:38-04:00 cmm: Don't parse MO_BSwap for W8 Don't support parsing bswap8, since bswap8 is not really an operation and would have to be implemented as a no-op (and currently is not implemented at all). Fixes #25002 - - - - - 1 changed file: - compiler/GHC/Cmm/Parser.y Changes: ===================================== compiler/GHC/Cmm/Parser.y ===================================== @@ -1146,12 +1146,15 @@ callishMachOps platform = listToUFM $ ( "prefetch0", (MO_Prefetch_Data 0,)), ( "prefetch1", (MO_Prefetch_Data 1,)), ( "prefetch2", (MO_Prefetch_Data 2,)), - ( "prefetch3", (MO_Prefetch_Data 3,)) + ( "prefetch3", (MO_Prefetch_Data 3,)), + + ( "bswap16", (MO_BSwap W16,) ), + ( "bswap32", (MO_BSwap W32,) ), + ( "bswap64", (MO_BSwap W64,) ) ] ++ concat [ allWidths "popcnt" MO_PopCnt , allWidths "pdep" MO_Pdep , allWidths "pext" MO_Pext - , allWidths "bswap" MO_BSwap , allWidths "cmpxchg" MO_Cmpxchg , allWidths "xchg" MO_Xchg , allWidths "load_relaxed" (\w -> MO_AtomicRead w MemOrderAcquire) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8a8ff8f2bc115f00adfa4a1ed823e8375cb72132 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8a8ff8f2bc115f00adfa4a1ed823e8375cb72132 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 11:27:16 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 20 Jun 2024 07:27:16 -0400 Subject: [Git][ghc/ghc][master] Delete unused testsuite files Message-ID: <667412142161b_6081191a8601118a4@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 5cc472f5 by sheaf at 2024-06-20T07:25:14-04:00 Delete unused testsuite files These files were committed by mistake in !11902. This commit simply removes them. - - - - - 7 changed files: - − testsuite/tests/primops/Ben.dump-ds - − testsuite/tests/primops/Ben.dump-ds-preopt - − testsuite/tests/primops/Ben.dump-stg-final - − testsuite/tests/primops/Ben.hs - − testsuite/tests/primops/should_run/UnliftedWeakPtr.dump-ds - − testsuite/tests/primops/should_run/UnliftedWeakPtr.dump-ds-preopt - − testsuite/tests/primops/should_run/UnliftedWeakPtr.dump-stg-final Changes: ===================================== testsuite/tests/primops/Ben.dump-ds deleted ===================================== @@ -1,31 +0,0 @@ - -==================== Desugar (after optimization) ==================== -2023-09-19 16:22:12.539709 UTC - -Result size of Desugar (after optimization) - = {terms: 12, types: 41, coercions: 21, joins: 0/0} - --- RHS size: {terms: 11, types: 30, coercions: 21, joins: 0/0} -foo :: forall {s} a. a -> State# s -> (# Int#, State# s #) -[LclIdX, - Unf=Unf{Src=, TopLvl=True, - Value=True, ConLike=True, WorkFree=True, Expandable=True, - Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=True)}] -foo - = \ (@s_al6) (@a_al7) (x_akF :: a_al7) (s0_akG :: State# s_al6) -> - keepAlive# - @(TupleRep [IntRep, ZeroBitRep]) - @Lifted - @a_al7 - @s_al6 - @(# Int#, State# s_al6 #) - ((CO: _N) - `cast` (Sub (Sym (AxSmallRep# (_N))) - :: (TupleRep [IntRep, ZeroBitRep] - GHC.Prim.~# TupleRep [IntRep, ZeroBitRep]) - ~R# GHC.Prim.SmallRep# (TupleRep [IntRep, ZeroBitRep]))) - x_akF - s0_akG - (\ (s1_akH [OS=OneShot] :: State# s_al6) -> (# 42#, s1_akH #)) - - ===================================== testsuite/tests/primops/Ben.dump-ds-preopt deleted ===================================== @@ -1,36 +0,0 @@ - -==================== Desugar (before optimization) ==================== -2023-09-19 16:22:12.5377082 UTC - -Result size of Desugar (before optimization) - = {terms: 14, types: 51, coercions: 21, joins: 0/1} - -Rec { --- RHS size: {terms: 13, types: 40, coercions: 21, joins: 0/1} -foo :: forall {s} a. a -> State# s -> (# Int#, State# s #) -[LclIdX] -foo - = \ (@s_al6) (@a_al7) -> - let { - irred_ale :: GHC.Prim.SmallRep# (TupleRep [IntRep, ZeroBitRep]) - [LclId] - irred_ale - = (CO: _N) - `cast` (Sub (Sym (AxSmallRep# (_N))) - :: (TupleRep [IntRep, ZeroBitRep] - GHC.Prim.~# TupleRep [IntRep, ZeroBitRep]) - ~R# GHC.Prim.SmallRep# (TupleRep [IntRep, ZeroBitRep])) } in - \ (x_akF :: a_al7) (s0_akG :: State# s_al6) -> - keepAlive# - @(TupleRep [IntRep, ZeroBitRep]) - @Lifted - @a_al7 - @s_al6 - @(# Int#, State# s_al6 #) - irred_ale - x_akF - s0_akG - (\ (s1_akH :: State# s_al6) -> (# 42#, s1_akH #)) -end Rec } - - ===================================== testsuite/tests/primops/Ben.dump-stg-final deleted ===================================== @@ -1,17 +0,0 @@ - -==================== Final STG: ==================== -2023-09-19 16:22:12.5502122 UTC - -Ben.foo1 - :: forall s. - GHC.Prim.State# s -> (# GHC.Prim.Int#, GHC.Prim.State# s #) -[GblId, Arity=1, Str=, Cpr=1, Unf=OtherCon []] = - {} \r [void_0E] Solo# [42#]; - -Ben.foo - :: forall {s} a. - a -> GHC.Prim.State# s -> (# GHC.Prim.Int#, GHC.Prim.State# s #) -[GblId, Arity=2, Str=, Unf=OtherCon []] = - {} \r [x_sFm void_0E] - keepAlive# [GHC.Prim.coercionToken# x_sFm GHC.Prim.void# Ben.foo1]; - ===================================== testsuite/tests/primops/Ben.hs deleted ===================================== @@ -1,17 +0,0 @@ - -{-# LANGUAGE DataKinds, PolyKinds #-} -{-# LANGUAGE MagicHash, UnboxedTuples #-} -{-# LANGUAGE TypeFamilies #-} - -{-# LANGUAGE PartialTypeSignatures #-} -{-# OPTIONS_GHC -Wno-partial-type-signatures #-} - -module Ben where - -import Data.Kind -import GHC.Exts -import GHC.IO - -foo :: forall {s} a. a -> State# s -> (# Int#, State# s #) -foo x s0 = keepAlive# x s0 (\s1 -> (# 42#, s1 #)) - --keepAlive# ===================================== testsuite/tests/primops/should_run/UnliftedWeakPtr.dump-ds deleted ===================================== @@ -1,191 +0,0 @@ - -==================== Desugar (after optimization) ==================== -2023-09-19 16:23:01.4184099 UTC - -Result size of Desugar (after optimization) - = {terms: 150, types: 341, coercions: 25, joins: 0/0} - --- RHS size: {terms: 12, types: 16, coercions: 0, joins: 0/0} -finalise - :: MVar# RealWorld String - -> State# RealWorld -> (# State# RealWorld, () #) -[LclIdX, - Unf=Unf{Src=, TopLvl=True, - Value=True, ConLike=True, WorkFree=True, Expandable=True, - Guidance=IF_ARGS [0 0] 74 10}] -finalise - = \ (mvar_aKR :: MVar# RealWorld String) - (s0_aKS :: State# RealWorld) -> - case putMVar# - @Lifted - @RealWorld - @String - mvar_aKR - (unpackCString# "finalised!"#) - s0_aKS - of s1_aKT - { __DEFAULT -> - (# s1_aKT, GHC.Tuple.Prim.() #) - } - --- RHS size: {terms: 2, types: 1, coercions: 0, joins: 0/0} -$dShow_aUH :: Show [Char] -[LclId, - Unf=Unf{Src=, TopLvl=True, - Value=False, ConLike=True, WorkFree=False, Expandable=True, - Guidance=IF_ARGS [] 20 0}] -$dShow_aUH = GHC.Show.$fShowList @Char GHC.Show.$fShowChar - --- RHS size: {terms: 2, types: 2, coercions: 0, joins: 0/0} -$dShow_aUy :: Show [String] -[LclId, - Unf=Unf{Src=, TopLvl=True, - Value=False, ConLike=True, WorkFree=False, Expandable=True, - Guidance=IF_ARGS [] 20 0}] -$dShow_aUy = GHC.Show.$fShowList @[Char] $dShow_aUH - --- RHS size: {terms: 50, types: 102, coercions: 0, joins: 0/0} -inner - :: MVar# RealWorld String - -> MutVar# RealWorld Bool - -> State# RealWorld - -> (# State# RealWorld, Res #) -[LclIdX, - Unf=Unf{Src=, TopLvl=True, - Value=True, ConLike=True, WorkFree=True, Expandable=True, - Guidance=IF_ARGS [0 0 0] 232 10}] -inner - = \ (mvar_aKH :: MVar# RealWorld String) - (u_aKI :: MutVar# RealWorld Bool) - (s0_aKJ :: State# RealWorld) -> - case newByteArray# @RealWorld 42# s0_aKJ of ds_dVZ { __DEFAULT -> - case ds_dVZ of { (# s1_aKK, ba#_aKL #) -> - case mkWeak# - @Unlifted - @Unlifted - @(MutVar# RealWorld Bool) - @(MutableByteArray# RealWorld) - @() - u_aKI - ba#_aKL - (finalise mvar_aKH) - s1_aKK - of ds_dW1 - { __DEFAULT -> - case ds_dW1 of { (# s2_aKM, wk_aKN #) -> - case deRefWeak# - @Unlifted @(MutableByteArray# RealWorld) wk_aKN s2_aKM - of ds_dW3 - { __DEFAULT -> - case ds_dW3 of { (# s3_aKO, i_aKP, ba'#_aKQ #) -> - (# s3_aKO, - Main.Res - wk_aKN - (build - @String - (\ (@a_dW9) - (c_dWa [OS=OneShot] :: String -> a_dW9 -> a_dW9) - (n_dWb [OS=OneShot] :: a_dW9) -> - c_dWa - (show @Int GHC.Show.$fShowInt (GHC.Types.I# i_aKP)) - (c_dWa - (show - @Int - GHC.Show.$fShowInt - (GHC.Types.I# (sizeofMutableByteArray# @RealWorld ba'#_aKQ))) - n_dWb))) #) - } - } - } - } - } - } - --- RHS size: {terms: 76, types: 181, coercions: 25, joins: 0/0} -main :: IO () -[LclIdX, - Unf=Unf{Src=, TopLvl=True, - Value=False, ConLike=False, WorkFree=False, Expandable=False, - Guidance=IF_ARGS [] 366 0}] -main - = >>= - @IO - GHC.Base.$fMonadIO - @[String] - @() - ((\ (s0_aAn :: State# RealWorld) -> - case newMVar# @Lifted @RealWorld @String s0_aAn of ds_dWd - { __DEFAULT -> - case ds_dWd of { (# s1_aAo, mvar_aAp #) -> - case newMutVar# @Lifted @Bool @RealWorld GHC.Types.False s1_aAo - of ds_dWf - { __DEFAULT -> - case ds_dWf of { (# s2_aAq, val_var_aAr #) -> - case keepAlive# - @(TupleRep [ZeroBitRep, LiftedRep]) - @Unlifted - @(MutVar# RealWorld Bool) - @RealWorld - @(# State# RealWorld, Res #) - ((CO: _N) - `cast` (Sub (Sym (AxSmallRep# (_N))) - :: (TupleRep [ZeroBitRep, LiftedRep] - GHC.Prim.~# TupleRep [ZeroBitRep, LiftedRep]) - ~R# GHC.Prim.SmallRep# (TupleRep [ZeroBitRep, LiftedRep]))) - val_var_aAr - s2_aAq - (inner mvar_aAp val_var_aAr) - of ds_dWh - { __DEFAULT -> - case ds_dWh of { (# s3_aAs, ds_dWy #) -> - case ds_dWy of { Res wk_aAt strs_aAu -> - case unIO @() performGC s3_aAs of ds_dWk { __DEFAULT -> - case ds_dWk of { (# s4_aAw, _ [Occ=Dead] #) -> - case deRefWeak# - @Unlifted @(MutableByteArray# RealWorld) wk_aAt s4_aAw - of ds_dWn - { __DEFAULT -> - case ds_dWn of { (# s5_aAx, j_aAy, _ [Occ=Dead] #) -> - case takeMVar# @Lifted @RealWorld @String mvar_aAp s5_aAx of ds_dWq - { __DEFAULT -> - case ds_dWq of { (# s6_aAz, r_aAA #) -> - (# s6_aAz, - ++ - @String - strs_aAu - (build - @String - (\ (@a_dWt) - (c_dWu [OS=OneShot] :: String -> a_dWt -> a_dWt) - (n_dWv [OS=OneShot] :: a_dWt) -> - c_dWu - (show @Int GHC.Show.$fShowInt (GHC.Types.I# j_aAy)) - (c_dWu r_aAA n_dWv))) #) - } - } - } - } - } - } - } - } - } - } - } - } - }) - `cast` (Sym (GHC.Types.N:IO[0] <[String]>_R) - :: (State# RealWorld -> (# State# RealWorld, [String] #)) - ~R# IO [String])) - (\ (res_aHG :: [String]) -> print @[String] $dShow_aUy res_aHG) - --- RHS size: {terms: 2, types: 1, coercions: 0, joins: 0/0} -:Main.main :: IO () -[LclIdX, - Unf=Unf{Src=, TopLvl=True, - Value=True, ConLike=True, WorkFree=True, Expandable=True, - Guidance=IF_ARGS [] 20 60}] -:Main.main = GHC.TopHandler.runMainIO @() main - - ===================================== testsuite/tests/primops/should_run/UnliftedWeakPtr.dump-ds-preopt deleted ===================================== @@ -1,212 +0,0 @@ - -==================== Desugar (before optimization) ==================== -2023-09-19 16:23:01.4144104 UTC - -Result size of Desugar (before optimization) - = {terms: 176, types: 382, coercions: 21, joins: 0/0} - -Rec { --- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} -$dShow_aUr :: Show Int -[LclId] -$dShow_aUr = $dShow_aT6 - --- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} -$dShow_aTc :: Show Int -[LclId] -$dShow_aTc = $dShow_aT6 - --- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} -$dShow_aT6 :: Show Int -[LclId] -$dShow_aT6 = GHC.Show.$fShowInt - --- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} -$dMonad_aTr :: Monad IO -[LclId] -$dMonad_aTr = GHC.Base.$fMonadIO - --- RHS size: {terms: 0, types: 0, coercions: 21, joins: 0/0} -irred_aTT :: GHC.Prim.SmallRep# (TupleRep [ZeroBitRep, LiftedRep]) -[LclId] -irred_aTT - = (CO: _N) - `cast` (Sub (Sym (AxSmallRep# (_N))) - :: (TupleRep [ZeroBitRep, LiftedRep] - GHC.Prim.~# TupleRep [ZeroBitRep, LiftedRep]) - ~R# GHC.Prim.SmallRep# (TupleRep [ZeroBitRep, LiftedRep])) - --- RHS size: {terms: 2, types: 2, coercions: 0, joins: 0/0} -$dShow_aUy :: Show [String] -[LclId] -$dShow_aUy = GHC.Show.$fShowList @[Char] $dShow_aUH - --- RHS size: {terms: 2, types: 1, coercions: 0, joins: 0/0} -$dShow_aUH :: Show [Char] -[LclId] -$dShow_aUH = GHC.Show.$fShowList @Char $dShow_aUI - --- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} -$dShow_aUI :: Show Char -[LclId] -$dShow_aUI = GHC.Show.$fShowChar - --- RHS size: {terms: 12, types: 16, coercions: 0, joins: 0/0} -finalise - :: MVar# RealWorld String - -> State# RealWorld -> (# State# RealWorld, () #) -[LclIdX] -finalise - = \ (mvar_aKR :: MVar# RealWorld String) - (s0_aKS :: State# RealWorld) -> - case putMVar# - @Lifted - @RealWorld - @String - mvar_aKR - (unpackCString# "finalised!"#) - s0_aKS - of s1_aKT - { __DEFAULT -> - (# s1_aKT, GHC.Tuple.Prim.() #) - } - --- RHS size: {terms: 58, types: 110, coercions: 0, joins: 0/0} -inner - :: MVar# RealWorld String - -> MutVar# RealWorld Bool - -> State# RealWorld - -> (# State# RealWorld, Res #) -[LclIdX] -inner - = \ (mvar_aKH :: MVar# RealWorld String) - (u_aKI :: MutVar# RealWorld Bool) - (s0_aKJ :: State# RealWorld) -> - case newByteArray# @RealWorld 42# s0_aKJ of ds_dVZ { __DEFAULT -> - case ds_dVZ of wild_00 { (# s1_aKK, ba#_aKL #) -> - case mkWeak# - @Unlifted - @Unlifted - @(MutVar# RealWorld Bool) - @(MutableByteArray# RealWorld) - @() - u_aKI - ba#_aKL - (finalise mvar_aKH) - s1_aKK - of ds_dW1 - { __DEFAULT -> - case ds_dW1 of wild_00 { (# s2_aKM, wk_aKN #) -> - case deRefWeak# - @Unlifted @(MutableByteArray# RealWorld) wk_aKN s2_aKM - of ds_dW3 - { __DEFAULT -> - case ds_dW3 of wild_00 { (# s3_aKO, i_aKP, ba'#_aKQ #) -> - (# s3_aKO, - (\ (ds_dW5 :: Weak# (MutableByteArray# RealWorld)) - (ds_dW6 :: [String]) -> - Main.Res ds_dW5 ds_dW6) - wk_aKN - (build - @String - (\ (@a_dW9) (c_dWa :: String -> a_dW9 -> a_dW9) (n_dWb :: a_dW9) -> - c_dWa - (show - @Int - $dShow_aT6 - ((\ (ds_dW7 :: Int#) -> GHC.Types.I# ds_dW7) i_aKP)) - (c_dWa - (show - @Int - $dShow_aTc - ((\ (ds_dW8 :: Int#) -> GHC.Types.I# ds_dW8) - (sizeofMutableByteArray# @RealWorld ba'#_aKQ))) - n_dWb))) #) - } - } - } - } - } - } - --- RHS size: {terms: 83, types: 194, coercions: 0, joins: 0/0} -main :: IO () -[LclIdX] -main - = >>= - @IO - $dMonad_aTr - @[String] - @() - ((\ (@a_aAl) - (ds_dWc :: State# RealWorld -> (# State# RealWorld, a_aAl #)) -> - GHC.Types.IO @a_aAl ds_dWc) - @[String] - (\ (s0_aAn :: State# RealWorld) -> - case newMVar# @Lifted @RealWorld @String s0_aAn of ds_dWd - { __DEFAULT -> - case ds_dWd of wild_00 { (# s1_aAo, mvar_aAp #) -> - case newMutVar# @Lifted @Bool @RealWorld GHC.Types.False s1_aAo - of ds_dWf - { __DEFAULT -> - case ds_dWf of wild_00 { (# s2_aAq, val_var_aAr #) -> - case keepAlive# - @(TupleRep [ZeroBitRep, LiftedRep]) - @Unlifted - @(MutVar# RealWorld Bool) - @RealWorld - @(# State# RealWorld, Res #) - irred_aTT - val_var_aAr - s2_aAq - (inner mvar_aAp val_var_aAr) - of ds_dWh - { __DEFAULT -> - case ds_dWh of wild_00 { (# s3_aAs, ds_dWy #) -> - case ds_dWy of wild_00 { Res wk_aAt strs_aAu -> - case unIO @() performGC s3_aAs of ds_dWk { __DEFAULT -> - case ds_dWk of wild_00 { (# s4_aAw, ds_dWx #) -> - case deRefWeak# - @Unlifted @(MutableByteArray# RealWorld) wk_aAt s4_aAw - of ds_dWn - { __DEFAULT -> - case ds_dWn of wild_00 { (# s5_aAx, j_aAy, ds_dWw #) -> - case takeMVar# @Lifted @RealWorld @String mvar_aAp s5_aAx of ds_dWq - { __DEFAULT -> - case ds_dWq of wild_00 { (# s6_aAz, r_aAA #) -> - (# s6_aAz, - ++ - @String - strs_aAu - (build - @String - (\ (@a_dWt) (c_dWu :: String -> a_dWt -> a_dWt) (n_dWv :: a_dWt) -> - c_dWu - (show - @Int - $dShow_aUr - ((\ (ds_dWs :: Int#) -> GHC.Types.I# ds_dWs) j_aAy)) - (c_dWu r_aAA n_dWv))) #) - } - } - } - } - } - } - } - } - } - } - } - } - })) - (\ (res_aHG :: [String]) -> print @[String] $dShow_aUy res_aHG) - --- RHS size: {terms: 2, types: 1, coercions: 0, joins: 0/0} -:Main.main :: IO () -[LclIdX] -:Main.main = GHC.TopHandler.runMainIO @() main -end Rec } - - ===================================== testsuite/tests/primops/should_run/UnliftedWeakPtr.dump-stg-final deleted ===================================== @@ -1,175 +0,0 @@ - -==================== Final STG: ==================== -2023-09-19 16:23:01.5732892 UTC - -Main.finalise2 :: GHC.Prim.Addr# -[GblId, Unf=OtherCon []] = - "finalised!"#; - -Main.finalise1 :: [GHC.Types.Char] -[GblId] = - {} \u [] GHC.CString.unpackCString# Main.finalise2; - -Main.finalise - :: GHC.Prim.MVar# GHC.Prim.RealWorld GHC.Base.String - -> GHC.Prim.State# GHC.Prim.RealWorld - -> (# GHC.Prim.State# GHC.Prim.RealWorld, () #) -[GblId, Arity=2, Str=, Cpr=1(, 1), Unf=OtherCon []] = - {} \r [mvar_s1xt void_0E] - case - putMVar# [mvar_s1xt Main.finalise1 GHC.Prim.void#] - of - s1_s1xv [Occ=Once1] - { - (##) -> Solo# [GHC.Tuple.Prim.()]; - }; - -Main.inner [InlPrag=[2]] - :: GHC.Prim.MVar# GHC.Prim.RealWorld GHC.Base.String - -> GHC.Prim.MutVar# GHC.Prim.RealWorld GHC.Types.Bool - -> GHC.Prim.State# GHC.Prim.RealWorld - -> (# GHC.Prim.State# GHC.Prim.RealWorld, Main.Res #) -[GblId, Arity=3, Str=, Cpr=1(, 1), Unf=OtherCon []] = - {} \r [mvar_s1xw u_s1xx void_0E] - case newByteArray# [42# GHC.Prim.void#] of { - Solo# ipv1_s1xB [Occ=Once1] -> - let { - sat_s1xE [Occ=Once1] - :: GHC.Prim.State# GHC.Prim.RealWorld - -> (# GHC.Prim.State# GHC.Prim.RealWorld, () #) - [LclId] = - {mvar_s1xw} \r [void_XF] - case - putMVar# [mvar_s1xw Main.finalise1 GHC.Prim.void#] - of - s2_s1xD [Occ=Once1] - { - (##) -> Solo# [GHC.Tuple.Prim.()]; - }; - } in - case mkWeak# [u_s1xx ipv1_s1xB sat_s1xE GHC.Prim.void#] of { - Solo# ipv3_s1xH -> - case deRefWeak# [ipv3_s1xH GHC.Prim.void#] of { - (#,#) ipv5_s1xK [Occ=Once1] ipv6_s1xL [Occ=Once1] -> - let { - sat_s1xO [Occ=Once1] :: GHC.Base.String - [LclId] = - {ipv6_s1xL} \u [] - case sizeofMutableByteArray# [ipv6_s1xL] of sat_s1xN [Occ=Once1] { - __DEFAULT -> GHC.Show.itos sat_s1xN GHC.Types.[]; - }; } in - let { - sat_s1xP [Occ=Once1] :: [GHC.Base.String] - [LclId] = - :! [sat_s1xO GHC.Types.[]]; } in - let { - sat_s1xM [Occ=Once1] :: GHC.Base.String - [LclId] = - {ipv5_s1xK} \u [] GHC.Show.itos ipv5_s1xK GHC.Types.[]; } in - let { - sat_s1xQ [Occ=Once1] :: [GHC.Base.String] - [LclId] = - :! [sat_s1xM sat_s1xP]; } in - let { - sat_s1xR [Occ=Once1] :: Main.Res - [LclId] = - Main.Res! [ipv3_s1xH sat_s1xQ]; - } in Solo# [sat_s1xR]; - }; - }; - }; - -Main.main1 - :: GHC.Prim.State# GHC.Prim.RealWorld - -> (# GHC.Prim.State# GHC.Prim.RealWorld, () #) -[GblId, Arity=1, Str=, Unf=OtherCon []] = - {} \r [void_0E] - case newMVar# [GHC.Prim.void#] of { - Solo# ipv1_s1xV -> - case newMutVar# [GHC.Types.False GHC.Prim.void#] of { - Solo# ipv3_s1xY -> - let { - sat_s1xZ [Occ=Once1] - :: GHC.Prim.State# GHC.Prim.RealWorld - -> (# GHC.Prim.State# GHC.Prim.RealWorld, Main.Res #) - [LclId] = - {ipv1_s1xV, ipv3_s1xY} \r [void_XF] - Main.inner ipv1_s1xV ipv3_s1xY GHC.Prim.void#; - } in - case - keepAlive# [GHC.Prim.coercionToken# - ipv3_s1xY - GHC.Prim.void# - sat_s1xZ] - of - { - Solo# ipv5_s1y2 [Occ=Once1!] -> - case ipv5_s1y2 of { - Main.Res wk_s1y4 [Occ=Once1] strs_s1y5 [Occ=Once1] -> - case - __ffi_static_ccall_safe base:performMajorGC :: [GHC.Prim.void#] - of - { - (##) -> - case deRefWeak# [wk_s1y4 GHC.Prim.void#] of { - (#,#) ipv7_s1yb [Occ=Once1] _ [Occ=Dead] -> - case takeMVar# [ipv1_s1xV GHC.Prim.void#] of { - Solo# ipv10_s1yf [Occ=Once1] -> - let { - sat_s1yk [Occ=Once1] :: GHC.Base.String - [LclId] = - {strs_s1y5, ipv7_s1yb, ipv10_s1yf} \u [] - let { - sat_s1yh [Occ=Once1] :: [[GHC.Types.Char]] - [LclId] = - :! [ipv10_s1yf GHC.Types.[]]; } in - let { - sat_s1yg [Occ=Once1] :: GHC.Base.String - [LclId] = - {ipv7_s1yb} \u [] GHC.Show.itos ipv7_s1yb GHC.Types.[]; } in - let { - sat_s1yi [Occ=Once1] :: [[GHC.Types.Char]] - [LclId] = - :! [sat_s1yg sat_s1yh]; - } in - case GHC.Base.++ strs_s1y5 sat_s1yi of sat_s1yj [Occ=Once1] { - __DEFAULT -> - GHC.Show.showList__ - GHC.Show.$fShowCallStack_$cshowList1 sat_s1yj GHC.Types.[]; - }; - } in - GHC.IO.Handle.Text.hPutStr2 - GHC.IO.StdHandles.stdout sat_s1yk GHC.Types.True GHC.Prim.void#; - }; - }; - }; - }; - }; - }; - }; - -Main.main :: GHC.Types.IO () -[GblId, Arity=1, Str=, Unf=OtherCon []] = - {} \r [void_0E] Main.main1 GHC.Prim.void#; - -Main.main2 - :: GHC.Prim.State# GHC.Prim.RealWorld - -> (# GHC.Prim.State# GHC.Prim.RealWorld, () #) -[GblId, Arity=1, Str=, Unf=OtherCon []] = - {} \r [void_0E] - GHC.TopHandler.runMainIO1 Main.main1 GHC.Prim.void#; - -:Main.main :: GHC.Types.IO () -[GblId, Arity=1, Str=, Unf=OtherCon []] = - {} \r [void_0E] Main.main2 GHC.Prim.void#; - -Main.Res [InlPrag=CONLIKE] - :: GHC.Prim.Weak# (GHC.Prim.MutableByteArray# GHC.Prim.RealWorld) - %1 -> [GHC.Base.String] %1 -> Main.Res -[GblId[DataCon], Arity=2, Caf=NoCafRefs, Unf=OtherCon []] = - {} \r [eta_B0 eta_B1] Main.Res [eta_B0 eta_B1]; - -Main.U [InlPrag=CONLIKE] :: GHC.Prim.Int# %1 -> Main.U -[GblId[DataCon], Arity=1, Caf=NoCafRefs, Unf=OtherCon []] = - {} \r [eta_B0] Main.U [eta_B0]; - View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5cc472f5f5dd73ac9c35345907d6392c43be21ba -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5cc472f5f5dd73ac9c35345907d6392c43be21ba You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 11:27:32 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 20 Jun 2024 07:27:32 -0400 Subject: [Git][ghc/ghc][master] Remove left over debugging pragma from 2016 Message-ID: <6674122460f03_6081199914c1120a@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 7b079378 by Matthew Pickering at 2024-06-20T07:25:50-04:00 Remove left over debugging pragma from 2016 This pragma was accidentally introduced in 648fd73a7b8fbb7955edc83330e2910428e76147 The top-level cost centres lead to a lack of optimisation when compiling with profiling. - - - - - 1 changed file: - compiler/GHC/StgToByteCode.hs Changes: ===================================== compiler/GHC/StgToByteCode.hs ===================================== @@ -4,8 +4,6 @@ {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE FlexibleContexts #-} -{-# OPTIONS_GHC -fprof-auto-top #-} - -- -- (c) The University of Glasgow 2002-2006 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7b079378c516e75286768312d7a8da9001cf30fe -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7b079378c516e75286768312d7a8da9001cf30fe You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 11:30:02 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 20 Jun 2024 07:30:02 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] simd fixups Message-ID: <667412ba2cfe5_60811b786341122a7@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 09894485 by sheaf at 2024-06-20T13:29:52+02:00 simd fixups - - - - - 3 changed files: - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/X86/Instr.hs Changes: ===================================== compiler/GHC/CmmToAsm/Format.hs ===================================== @@ -25,6 +25,7 @@ module GHC.CmmToAsm.Format ( formatToWidth, formatInBytes, isIntScalarFormat, + VirtualRegFormat(..), RegFormat(..), takeVirtualRegs, takeRealRegs, @@ -197,6 +198,12 @@ formatInBytes = widthInBytes . formatToWidth -------------------------------------------------------------------------------- +data VirtualRegFormat + = VirtualRegFormat + { virtualRegFormatReg :: {-# UNPACK #-} !VirtualReg + , virtualRegFormatFormat :: !Format + } + -- | A typed register: a register, together with the specific format we -- are using it at. data RegFormat ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -135,8 +135,9 @@ import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Platform +import Data.Containers.ListUtils import Data.Maybe -import Data.List (partition, nub) +import Data.List (partition) import Control.Monad -- ----------------------------------------------------------------------------- @@ -501,13 +502,14 @@ genRaInsn block_live new_instrs block_id instr r_dying w_dying = do platform <- getPlatform case regUsageOfInstr platform instr of { RU read written -> do - let real_written = [ rr | RegFormat { regFormatReg = RegReal rr } <- written ] :: [RealReg] - let virt_written = [ vr | RegFormat { regFormatReg = RegVirtual vr } <- written ] + let real_written = [ rr | RegFormat {regFormatReg = RegReal rr} <- written ] + let virt_written = [ VirtualRegFormat vr fmt | RegFormat (RegVirtual vr) fmt <- written ] -- we don't need to do anything with real registers that are -- only read by this instr. (the list is typically ~2 elements, -- so using nub isn't a problem). - let virt_read = nub [ vr | RegFormat { regFormatReg = RegVirtual vr }<- read ] :: [VirtualReg] + let virt_read :: [VirtualRegFormat] + virt_read = nubOrdOn virtualRegFormatReg [ VirtualRegFormat vr fmt | RegFormat (RegVirtual vr) fmt <- read ] -- do -- let real_read = nub [ rr | (RegReal rr) <- read] @@ -567,9 +569,9 @@ genRaInsn block_live new_instrs block_id instr r_dying w_dying = do = toRegMap $ -- Cast key from VirtualReg to Reg -- See Note [UniqFM and the register allocator] listToUFM - [ (t, RegReal r) - | (t, r) <- zip virt_read r_allocd - ++ zip virt_written w_allocd ] + [ (virtualRegFormatReg vr, RegReal rr) + | (vr, rr) <- zip virt_read r_allocd + ++ zip virt_written w_allocd ] patched_instr :: instr patched_instr @@ -800,21 +802,21 @@ data SpillLoc = ReadMem StackSlot -- reading from register only in memory allocateRegsAndSpill :: forall freeRegs instr. (FR freeRegs, Instruction instr) - => Bool -- True <=> reading (load up spilled regs) - -> [VirtualReg] -- don't push these out - -> [instr] -- spill insns - -> [RealReg] -- real registers allocated (accum.) - -> [VirtualReg] -- temps to allocate + => Bool -- True <=> reading (load up spilled regs) + -> [VirtualRegFormat] -- don't push these out + -> [instr] -- spill insns + -> [RealReg] -- real registers allocated (accum.) + -> [VirtualRegFormat] -- temps to allocate -> RegM freeRegs ( [instr] , [RealReg]) allocateRegsAndSpill _ _ spills alloc [] = return (spills, reverse alloc) -allocateRegsAndSpill reading keep spills alloc (r:rs) +allocateRegsAndSpill reading keep spills alloc (VirtualRegFormat r fmt:rs) = do assig <- toVRegMap <$> getAssigR -- pprTraceM "allocateRegsAndSpill:assig" (ppr (r:rs) $$ ppr assig) -- See Note [UniqFM and the register allocator] - let doSpill = allocRegsAndSpill_spill reading keep spills alloc r rs assig + let doSpill = allocRegsAndSpill_spill reading keep spills alloc (VirtualRegFormat r fmt) rs assig case lookupUFM assig r of -- case (1a): already in a register Just (InReg my_reg) -> @@ -859,29 +861,19 @@ findPrefRealReg vreg = do -- convenient and it maintains the recursive structure of the allocator. -- EZY allocRegsAndSpill_spill :: (FR freeRegs, Instruction instr) => Bool - -> [VirtualReg] + -> [VirtualRegFormat] -> [instr] -> [RealReg] - -> VirtualReg - -> [VirtualReg] + -> VirtualRegFormat + -> [VirtualRegFormat] -> UniqFM VirtualReg Loc -> SpillLoc -> RegM freeRegs ([instr], [RealReg]) -allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc +allocRegsAndSpill_spill reading keep spills alloc (VirtualRegFormat r fmt) rs assig spill_loc = do platform <- getPlatform freeRegs <- getFreeRegsR let regclass = classOfVirtualReg r freeRegs_thisClass = frGetFreeRegs platform regclass freeRegs :: [RealReg] - vr_fmt = case r of - VirtualRegV128 {} -> VecFormat 2 FmtDouble - -- It doesn't really matter whether we use e.g. v2f64 or v4f32 - -- or v4i32 etc here. This is perhaps a sign that 'Format' - -- is not the right type to use here, but that is a battle - -- for another day. - VirtualRegD {} -> FF64 - VirtualRegI {} -> II64 - VirtualRegHi {} -> II64 - -- Can we put the variable into a register it already was? pref_reg <- findPrefRealReg r @@ -895,10 +887,10 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc = reg | otherwise = first_free - spills' <- loadTemp r vr_fmt spill_loc final_reg spills + spills' <- loadTemp r fmt spill_loc final_reg spills setAssigR $ toRegMap - $ (addToUFM assig r $! newLocation spill_loc $ RealRegUsage final_reg vr_fmt) + $ (addToUFM assig r $! newLocation spill_loc $ RealRegUsage final_reg fmt) setFreeRegsR $ frAllocateReg platform final_reg freeRegs allocateRegsAndSpill reading keep spills' (final_reg : alloc) rs @@ -911,7 +903,7 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc inRegOrBoth _ = False let candidates' :: UniqFM VirtualReg Loc candidates' = - flip delListFromUFM keep $ + flip delListFromUFM (fmap virtualRegFormatReg keep) $ filterUFM inRegOrBoth $ assig -- This is non-deterministic but we do not ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -973,10 +973,8 @@ scalarMoveFormat platform fmt = FF64 | II64 <- fmt = II64 - | PW4 <- platformWordSize platform - = II32 | otherwise - = II64 + = archWordFormat (target32Bit platform) -- | Check whether an instruction represents a reg-reg move. -- The register allocator attempts to eliminate reg->reg moves whenever it can, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/09894485b74b5266355e1f153096ea331d3742c9 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/09894485b74b5266355e1f153096ea331d3742c9 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 11:57:02 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 20 Jun 2024 07:57:02 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 12 commits: ttg: Use List instead of Bag in AST for LHsBindsLR Message-ID: <6674190e829cf_60812056034114178@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 24e89c40 by Jacco Krijnen at 2024-06-20T07:21:27-04:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 04f5bb85 by Simon Peyton Jones at 2024-06-20T07:22:03-04:00 Fix untouchability test This MR fixes #24938. The underlying problem was tha the test for "does this implication bring in scope any equalities" was plain wrong. See Note [Tracking Given equalities] and Note [Let-bound skolems] both in GHC.Tc.Solver.InertSet. Then * Test LocalGivenEqs succeeds for a different reason than before; see (LBS2) in Note [Let-bound skolems] * New test T24938a succeeds because of (LBS2), whereas it failed before. * Test LocalGivenEqs2 now fails, as it should. * Test T224938, the repro from the ticket, fails, as it should. - - - - - 9a757a27 by Simon Peyton Jones at 2024-06-20T07:22:40-04:00 Fix demand signatures for join points This MR tackles #24623 and #23113 The main change is to give a clearer notion of "worker/wrapper arity", esp for join points. See GHC.Core.Opt.DmdAnal Note [Worker/wrapper arity and join points] This Note is a good summary of what this MR does: (1) The "worker/wrapper arity" of an Id is * For non-join-points: idArity * The join points: the join arity (Id part only of course) This is the number of args we will use in worker/wrapper. See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`. (2) A join point's demand-signature arity may exceed the Id's worker/wrapper arity. See the `arity_ok` assertion in `mkWwBodies`. (3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond the worker/wrapper arity. (4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper arity (re)-computed by workWrapArity. - - - - - 5e8faaf1 by Jan Hrček at 2024-06-20T07:23:20-04:00 Update haddocks of Import/Export AST types - - - - - cd512234 by Hécate Kleidukos at 2024-06-20T07:24:02-04:00 haddock: Update bounds in cabal files and remove allow-newer stanza in cabal.project - - - - - 8a8ff8f2 by Rodrigo Mesquita at 2024-06-20T07:24:38-04:00 cmm: Don't parse MO_BSwap for W8 Don't support parsing bswap8, since bswap8 is not really an operation and would have to be implemented as a no-op (and currently is not implemented at all). Fixes #25002 - - - - - 5cc472f5 by sheaf at 2024-06-20T07:25:14-04:00 Delete unused testsuite files These files were committed by mistake in !11902. This commit simply removes them. - - - - - 7b079378 by Matthew Pickering at 2024-06-20T07:25:50-04:00 Remove left over debugging pragma from 2016 This pragma was accidentally introduced in 648fd73a7b8fbb7955edc83330e2910428e76147 The top-level cost centres lead to a lack of optimisation when compiling with profiling. - - - - - 8cf3e998 by Hécate Kleidukos at 2024-06-20T07:56:53-04:00 haddock: Remove unused pragmata, qualify usages of Data.List functions, add more sanity checking flags by default This commit enables some extensions and GHC flags in the cabal file in a way that allows us to reduce the amount of prologuing on top of each file. We also prefix the usage of some List functions that removes ambiguity when they are also exported from the Prelude, like foldl'. In general, this has the effect of pointing out more explicitly that a linked list is used. Metric Increase: haddock.Cabal haddock.base haddock.compiler - - - - - 93a7a1be by Arnaud Spiwack at 2024-06-20T07:56:53-04:00 Add test case for #23586 - - - - - f6fe7d39 by Arnaud Spiwack at 2024-06-20T07:56:53-04:00 When matching functions in rewrite rules: ignore multiplicity When matching a template variable to an expression, we check that it has the same type as the matched expression. But if the variable `f` has type `A -> B` while the expression `e` has type `A %1 -> B`, the match was previously rejected. A principled solution would have `f` substituted by `\(%Many x) -> e x` or some other appropriate coercion. But since linearity is not properly checked in Core, we can be cheeky and simply ignore multiplicity while matching. Much easier. This has forced a change in the linter which, when `-dlinear-core-lint` is off, must consider that `a -> b` and `a %1 -> b` are equal. This is achieved by adding an argument to configure the behaviour of `nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour which ignores multiplicities when comparing two `FunTy`. Fixes #24725. - - - - - 3becee50 by Simon Peyton Jones at 2024-06-20T07:56:53-04:00 Faster type equality This MR speeds up type equality, triggered by perf regressions that showed up when fixing #24725 by parameterising type equality over whether to ignore multiplicity. The changes are: * Do not use `nonDetCmpType` for type /equality/. Instead use a specialised type-equality function, which we have always had! `nonDetCmpType` remains, but I did not invest effort in refactoring or optimising it. * Type equality is parameterised by - whether to expand synonyms - whether to respect multiplicities - whether it has a RnEnv2 environment In this MR I systematically specialise it for static values of these parameters. Much more direct and predictable than before. See Note [Specialising type equality] * We want to avoid comparing kinds if possible. I refactored how this happens, at least for `eqType`. See Note [Casts and coercions in type comparison] * To make Lint fast, we want to avoid allocating a thunk for <msg> in ensureEqTypes ty1 ty2 <msg> because the test almost always succeeds, and <msg> isn't needed. See Note [INLINE ensureEqTys] Metric Decrease: T13386 T5030 - - - - - 30 changed files: - compiler/GHC/Cmm/Parser.y - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Multiplicity.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/WorkWrap.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/TyCo/Compare.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs - compiler/GHC/HsToCore/Docs.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Pmc/Desugar.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Parser/PostProcess/Haddock.hs - compiler/GHC/Rename/Bind.hs - compiler/GHC/Rename/Module.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dab074193aad20d251b9601fbfedc4af4b73508f...3becee5061a4f8ab153231bb42bfc24a596b6b17 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/dab074193aad20d251b9601fbfedc4af4b73508f...3becee5061a4f8ab153231bb42bfc24a596b6b17 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 12:22:59 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 20 Jun 2024 08:22:59 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] simd fixups Message-ID: <66741f2317d72_6081242a9441196c3@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: a012d5e4 by sheaf at 2024-06-20T14:22:41+02:00 simd fixups - - - - - 13 changed files: - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/PPC.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs - compiler/GHC/CmmToAsm/Reg/Linear/State.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/RegInfo.hs Changes: ===================================== compiler/GHC/CmmToAsm/AArch64/Instr.hs ===================================== @@ -369,13 +369,12 @@ patchJumpInstr instr patchF mkSpillInstr :: HasCallStack => NCGConfig - -> Reg -- register to spill - -> Format + -> RegFormat -- register to spill -> Int -- current stack delta -> Int -- spill slot to use -> [Instr] -mkSpillInstr config reg fmt delta slot = +mkSpillInstr config (RegFormat reg fmt) delta slot = case off - delta of imm | -256 <= imm && imm <= 255 -> [ mkStrSp imm ] imm | imm > 0 && imm .&. 0x7 == 0x0 && imm <= 0xfff -> [ mkStrSp imm ] @@ -396,12 +395,11 @@ mkSpillInstr config reg fmt delta slot = mkLoadInstr :: NCGConfig - -> Reg -- register to load - -> Format + -> RegFormat -> Int -- current stack delta -> Int -- spill slot to use -> [Instr] -mkLoadInstr config reg fmt delta slot = +mkLoadInstr config (RegFormat reg fmt) delta slot = case off - delta of imm | -256 <= imm && imm <= 255 -> [ mkLdrSp imm ] imm | imm > 0 && imm .&. 0x7 == 0x0 && imm <= 0xfff -> [ mkLdrSp imm ] ===================================== compiler/GHC/CmmToAsm/Format.hs ===================================== @@ -25,6 +25,7 @@ module GHC.CmmToAsm.Format ( formatToWidth, formatInBytes, isIntScalarFormat, + VirtualRegFormat(..), RegFormat(..), takeVirtualRegs, takeRealRegs, @@ -120,10 +121,15 @@ intFormat width "produce code for Format.intFormat " ++ show other ++ "\n\tConsider using the llvm backend with -fllvm" --- | Check if a format represents a vector -isVecFormat :: Format -> Bool -isVecFormat (VecFormat {}) = True -isVecFormat _ = False +-- | Check if a format represent an integer value. +isIntFormat :: Format -> Bool +isIntFormat format = + case format of + II8 -> True + II16 -> True + II32 -> True + II64 -> True + _ -> False -- | Get the float format of this width. floatFormat :: Width -> Format @@ -131,13 +137,8 @@ floatFormat width = case width of W32 -> FF32 W64 -> FF64 - other -> pprPanic "Format.floatFormat" (ppr other) --- | Check if a format represent an integer value. -isIntFormat :: Format -> Bool -isIntFormat = not . isFloatFormat - -- | Check if a format represents a floating point value. isFloatFormat :: Format -> Bool isFloatFormat format @@ -146,14 +147,6 @@ isFloatFormat format FF64 -> True _ -> False - --- | Convert a Cmm type to a Format. -cmmTypeFormat :: CmmType -> Format -cmmTypeFormat ty - | isFloatType ty = floatFormat (typeWidth ty) - | isVecType ty = vecFormat ty - | otherwise = intFormat (typeWidth ty) - vecFormat :: CmmType -> Format vecFormat ty = let l = vecLength ty @@ -170,6 +163,20 @@ vecFormat ty = W64 -> VecFormat l FmtInt64 _ -> pprPanic "Incorrect vector element width" (ppr elemTy) +-- | Check if a format represents a vector +isVecFormat :: Format -> Bool +isVecFormat (VecFormat {}) = True +isVecFormat _ = False + + +-- | Convert a Cmm type to a Format. +cmmTypeFormat :: CmmType -> Format +cmmTypeFormat ty + | isFloatType ty = floatFormat (typeWidth ty) + | isVecType ty = vecFormat ty + | otherwise = intFormat (typeWidth ty) + + -- | Get the Width of a Format. formatToWidth :: Format -> Width formatToWidth format @@ -197,6 +204,12 @@ formatInBytes = widthInBytes . formatToWidth -------------------------------------------------------------------------------- +data VirtualRegFormat + = VirtualRegFormat + { virtualRegFormatReg :: {-# UNPACK #-} !VirtualReg + , virtualRegFormatFormat :: !Format + } + -- | A typed register: a register, together with the specific format we -- are using it at. data RegFormat ===================================== compiler/GHC/CmmToAsm/Instr.hs ===================================== @@ -96,8 +96,7 @@ class Instruction instr where -- | An instruction to spill a register into a spill slot. mkSpillInstr :: NCGConfig - -> Reg -- ^ the reg to spill - -> Format + -> RegFormat -- ^ the reg to spill -> Int -- ^ the current stack delta -> Int -- ^ spill slots to use -> [instr] -- ^ instructions @@ -106,11 +105,10 @@ class Instruction instr where -- | An instruction to reload a register from a spill slot. mkLoadInstr :: NCGConfig - -> Reg -- ^ the reg to reload. - -> Format + -> RegFormat -- ^ the reg to reload. -> Int -- ^ the current stack delta -> Int -- ^ the spill slot to use - -> [instr] -- ^ instructions + -> [instr] -- ^ instructions -- | See if this instruction is telling us the current C stack delta takeDeltaInstr @@ -135,8 +133,8 @@ class Instruction instr where mkRegRegMoveInstr :: Platform -> Format - -> Reg -- ^ source register - -> Reg -- ^ destination register + -> Reg -- ^ source register + -> Reg -- ^ destination register -> instr -- | Take the source and destination from this reg -> reg move instruction ===================================== compiler/GHC/CmmToAsm/PPC.hs ===================================== @@ -48,8 +48,8 @@ instance Instruction PPC.Instr where jumpDestsOfInstr = PPC.jumpDestsOfInstr canFallthroughTo = PPC.canFallthroughTo patchJumpInstr = PPC.patchJumpInstr - mkSpillInstr cfg reg _ i j = PPC.mkSpillInstr cfg reg i j - mkLoadInstr cfg reg _ i j = PPC.mkLoadInstr cfg reg i j + mkSpillInstr = PPC.mkSpillInstr + mkLoadInstr = PPC.mkLoadInstr takeDeltaInstr = PPC.takeDeltaInstr isMetaInstr = PPC.isMetaInstr mkRegRegMoveInstr _ = PPC.mkRegRegMoveInstr ===================================== compiler/GHC/CmmToAsm/PPC/Instr.hs ===================================== @@ -550,12 +550,12 @@ patchJumpInstr insn patchF -- | An instruction to spill a register into a spill slot. mkSpillInstr :: NCGConfig - -> Reg -- register to spill + -> RegFormat -- register to spill -> Int -- current stack delta -> Int -- spill slot to use -> [Instr] -mkSpillInstr config reg delta slot +mkSpillInstr config (RegFormat reg _fmt) delta slot = let platform = ncgPlatform config off = spillSlotToOffset platform slot arch = platformArch platform @@ -574,12 +574,12 @@ mkSpillInstr config reg delta slot mkLoadInstr :: NCGConfig - -> Reg -- register to load + -> RegFormat -- register to load -> Int -- current stack delta -> Int -- spill slot to use -> [Instr] -mkLoadInstr config reg delta slot +mkLoadInstr config (RegFormat reg _fmt) delta slot = let platform = ncgPlatform config off = spillSlotToOffset platform slot arch = platformArch platform ===================================== compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs ===================================== @@ -243,7 +243,7 @@ spillRead regSlotMap instr (RegFormat reg fmt) { stateSpillSL = addToUFM_C accSpillSL (stateSpillSL s) reg (reg, 0, 1) } return ( instr' - , ( [LiveInstr (RELOAD slot nReg fmt) Nothing] + , ( [LiveInstr (RELOAD slot (RegFormat nReg fmt)) Nothing] , []) ) | otherwise = panic "RegSpill.spillRead: no slot defined for spilled reg" @@ -267,7 +267,7 @@ spillWrite regSlotMap instr (RegFormat reg fmt) return ( instr' , ( [] - , [LiveInstr (SPILL nReg fmt slot) Nothing])) + , [LiveInstr (SPILL (RegFormat nReg fmt) slot) Nothing])) | otherwise = panic "RegSpill.spillWrite: no slot defined for spilled reg" @@ -289,8 +289,8 @@ spillModify regSlotMap instr (RegFormat reg fmt) { stateSpillSL = addToUFM_C accSpillSL (stateSpillSL s) reg (reg, 1, 1) } return ( instr' - , ( [LiveInstr (RELOAD slot nReg fmt) Nothing] - , [LiveInstr (SPILL nReg fmt slot) Nothing])) + , ( [LiveInstr (RELOAD slot (RegFormat nReg fmt)) Nothing] + , [LiveInstr (SPILL (RegFormat nReg fmt) slot) Nothing])) | otherwise = panic "RegSpill.spillModify: no slot defined for spilled reg" ===================================== compiler/GHC/CmmToAsm/Reg/Graph/SpillClean.hs ===================================== @@ -161,13 +161,13 @@ cleanForward _ _ _ acc [] -- hopefully the spill will be also be cleaned in the next pass cleanForward platform blockId assoc acc (li1 : li2 : instrs) - | LiveInstr (SPILL reg1 _ slot1) _ <- li1 - , LiveInstr (RELOAD slot2 reg2 fmt) _ <- li2 + | LiveInstr (SPILL reg1 slot1) _ <- li1 + , LiveInstr (RELOAD slot2 reg2) _ <- li2 , slot1 == slot2 = do modify $ \s -> s { sCleanedReloadsAcc = sCleanedReloadsAcc s + 1 } cleanForward platform blockId assoc acc - $ li1 : LiveInstr (mkRegRegMoveInstr platform fmt reg1 reg2) Nothing + $ li1 : LiveInstr (mkRegRegMoveInstr platform (regFormatFormat reg2) (regFormatReg reg1) (regFormatReg reg2)) Nothing : instrs cleanForward platform blockId assoc acc (li@(LiveInstr i1 _) : instrs) @@ -190,8 +190,8 @@ cleanForward platform blockId assoc acc (li@(LiveInstr i1 _) : instrs) cleanForward platform blockId assoc acc (li : instrs) -- Update association due to the spill. - | LiveInstr (SPILL reg _ slot) _ <- li - = let assoc' = addAssoc (SReg reg) (SSlot slot) + | LiveInstr (SPILL reg slot) _ <- li + = let assoc' = addAssoc (SReg $ regFormatReg reg) (SSlot slot) $ delAssoc (SSlot slot) $ assoc in cleanForward platform blockId assoc' (li : acc) instrs @@ -230,7 +230,7 @@ cleanReload -> LiveInstr instr -> CleanM (Assoc Store, Maybe (LiveInstr instr)) -cleanReload platform blockId assoc li@(LiveInstr (RELOAD slot reg fmt) _) +cleanReload platform blockId assoc li@(LiveInstr (RELOAD slot (RegFormat reg fmt)) _) -- If the reg we're reloading already has the same value as the slot -- then we can erase the instruction outright. @@ -248,7 +248,7 @@ cleanReload platform blockId assoc li@(LiveInstr (RELOAD slot reg fmt) _) $ assoc return ( assoc' - , Just $ LiveInstr (mkRegRegMoveInstr platform fmt reg2 reg) Nothing) + , Just $ LiveInstr (mkRegRegMoveInstr platform fmt reg2 reg) Nothing ) -- Gotta keep this instr. | otherwise @@ -356,12 +356,12 @@ cleanBackward' _ _ _ acc [] cleanBackward' liveSlotsOnEntry reloadedBy noReloads acc (li : instrs) -- If nothing ever reloads from this slot then we don't need the spill. - | LiveInstr (SPILL _ _ slot) _ <- li + | LiveInstr (SPILL _ slot) _ <- li , Nothing <- lookupUFM reloadedBy (SSlot slot) = do modify $ \s -> s { sCleanedSpillsAcc = sCleanedSpillsAcc s + 1 } cleanBackward liveSlotsOnEntry noReloads acc instrs - | LiveInstr (SPILL _ _ slot) _ <- li + | LiveInstr (SPILL _ slot) _ <- li = if elementOfUniqSet slot noReloads -- We can erase this spill because the slot won't be read until @@ -376,7 +376,7 @@ cleanBackward' liveSlotsOnEntry reloadedBy noReloads acc (li : instrs) cleanBackward liveSlotsOnEntry noReloads' (li : acc) instrs -- if we reload from a slot then it's no longer unused - | LiveInstr (RELOAD slot _ _) _ <- li + | LiveInstr (RELOAD slot _) _ <- li , noReloads' <- delOneFromUniqSet noReloads slot = cleanBackward liveSlotsOnEntry noReloads' (li : acc) instrs ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -135,8 +135,9 @@ import GHC.Utils.Outputable import GHC.Utils.Panic import GHC.Platform +import Data.Containers.ListUtils import Data.Maybe -import Data.List (partition, nub) +import Data.List (partition) import Control.Monad -- ----------------------------------------------------------------------------- @@ -501,13 +502,14 @@ genRaInsn block_live new_instrs block_id instr r_dying w_dying = do platform <- getPlatform case regUsageOfInstr platform instr of { RU read written -> do - let real_written = [ rr | RegFormat { regFormatReg = RegReal rr } <- written ] :: [RealReg] - let virt_written = [ vr | RegFormat { regFormatReg = RegVirtual vr } <- written ] + let real_written = [ rr | RegFormat {regFormatReg = RegReal rr} <- written ] + let virt_written = [ VirtualRegFormat vr fmt | RegFormat (RegVirtual vr) fmt <- written ] -- we don't need to do anything with real registers that are -- only read by this instr. (the list is typically ~2 elements, -- so using nub isn't a problem). - let virt_read = nub [ vr | RegFormat { regFormatReg = RegVirtual vr }<- read ] :: [VirtualReg] + let virt_read :: [VirtualRegFormat] + virt_read = nubOrdOn virtualRegFormatReg [ VirtualRegFormat vr fmt | RegFormat (RegVirtual vr) fmt <- read ] -- do -- let real_read = nub [ rr | (RegReal rr) <- read] @@ -567,9 +569,9 @@ genRaInsn block_live new_instrs block_id instr r_dying w_dying = do = toRegMap $ -- Cast key from VirtualReg to Reg -- See Note [UniqFM and the register allocator] listToUFM - [ (t, RegReal r) - | (t, r) <- zip virt_read r_allocd - ++ zip virt_written w_allocd ] + [ (virtualRegFormatReg vr, RegReal rr) + | (vr, rr) <- zip virt_read r_allocd + ++ zip virt_written w_allocd ] patched_instr :: instr patched_instr @@ -721,7 +723,7 @@ saveClobberedTemps clobbered dying -- (2) no free registers: spill the value [] -> do - (spill, slot) <- spillR (RegReal reg) fmt temp + (spill, slot) <- spillR (RegFormat (RegReal reg) fmt) temp -- record why this reg was spilled for profiling recordSpill (SpillClobber temp) @@ -800,21 +802,21 @@ data SpillLoc = ReadMem StackSlot -- reading from register only in memory allocateRegsAndSpill :: forall freeRegs instr. (FR freeRegs, Instruction instr) - => Bool -- True <=> reading (load up spilled regs) - -> [VirtualReg] -- don't push these out - -> [instr] -- spill insns - -> [RealReg] -- real registers allocated (accum.) - -> [VirtualReg] -- temps to allocate + => Bool -- True <=> reading (load up spilled regs) + -> [VirtualRegFormat] -- don't push these out + -> [instr] -- spill insns + -> [RealReg] -- real registers allocated (accum.) + -> [VirtualRegFormat] -- temps to allocate -> RegM freeRegs ( [instr] , [RealReg]) allocateRegsAndSpill _ _ spills alloc [] = return (spills, reverse alloc) -allocateRegsAndSpill reading keep spills alloc (r:rs) +allocateRegsAndSpill reading keep spills alloc (VirtualRegFormat r fmt:rs) = do assig <- toVRegMap <$> getAssigR -- pprTraceM "allocateRegsAndSpill:assig" (ppr (r:rs) $$ ppr assig) -- See Note [UniqFM and the register allocator] - let doSpill = allocRegsAndSpill_spill reading keep spills alloc r rs assig + let doSpill = allocRegsAndSpill_spill reading keep spills alloc (VirtualRegFormat r fmt) rs assig case lookupUFM assig r of -- case (1a): already in a register Just (InReg my_reg) -> @@ -859,29 +861,19 @@ findPrefRealReg vreg = do -- convenient and it maintains the recursive structure of the allocator. -- EZY allocRegsAndSpill_spill :: (FR freeRegs, Instruction instr) => Bool - -> [VirtualReg] + -> [VirtualRegFormat] -> [instr] -> [RealReg] - -> VirtualReg - -> [VirtualReg] + -> VirtualRegFormat + -> [VirtualRegFormat] -> UniqFM VirtualReg Loc -> SpillLoc -> RegM freeRegs ([instr], [RealReg]) -allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc +allocRegsAndSpill_spill reading keep spills alloc (VirtualRegFormat r fmt) rs assig spill_loc = do platform <- getPlatform freeRegs <- getFreeRegsR let regclass = classOfVirtualReg r freeRegs_thisClass = frGetFreeRegs platform regclass freeRegs :: [RealReg] - vr_fmt = case r of - VirtualRegV128 {} -> VecFormat 2 FmtDouble - -- It doesn't really matter whether we use e.g. v2f64 or v4f32 - -- or v4i32 etc here. This is perhaps a sign that 'Format' - -- is not the right type to use here, but that is a battle - -- for another day. - VirtualRegD {} -> FF64 - VirtualRegI {} -> II64 - VirtualRegHi {} -> II64 - -- Can we put the variable into a register it already was? pref_reg <- findPrefRealReg r @@ -895,10 +887,10 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc = reg | otherwise = first_free - spills' <- loadTemp r vr_fmt spill_loc final_reg spills + spills' <- loadTemp (VirtualRegFormat r fmt) spill_loc final_reg spills setAssigR $ toRegMap - $ (addToUFM assig r $! newLocation spill_loc $ RealRegUsage final_reg vr_fmt) + $ (addToUFM assig r $! newLocation spill_loc $ RealRegUsage final_reg fmt) setFreeRegsR $ frAllocateReg platform final_reg freeRegs allocateRegsAndSpill reading keep spills' (final_reg : alloc) rs @@ -911,7 +903,7 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc inRegOrBoth _ = False let candidates' :: UniqFM VirtualReg Loc candidates' = - flip delListFromUFM keep $ + flip delListFromUFM (fmap virtualRegFormatReg keep) $ filterUFM inRegOrBoth $ assig -- This is non-deterministic but we do not @@ -941,7 +933,7 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc -- we have a temporary that is in both register and mem, -- just free up its register for use. | (temp, myRegUse@(RealRegUsage my_reg fmt), slot) : _ <- candidates_inBoth - = do spills' <- loadTemp r fmt spill_loc my_reg spills + = do spills' <- loadTemp (VirtualRegFormat r fmt) spill_loc my_reg spills let assig1 = addToUFM_Directly assig temp (InMem slot) let assig2 = addToUFM assig1 r $! newLocation spill_loc myRegUse @@ -953,7 +945,7 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc | (temp_to_push_out, RealRegUsage my_reg fmt) : _ <- candidates_inReg = do - (spill_store, slot) <- spillR (RegReal my_reg) fmt temp_to_push_out + (spill_store, slot) <- spillR (RegFormat (RegReal my_reg) fmt) temp_to_push_out -- record that this temp was spilled recordSpill (SpillAlloc temp_to_push_out) @@ -964,7 +956,7 @@ allocRegsAndSpill_spill reading keep spills alloc r rs assig spill_loc setAssigR $ toRegMap assig2 -- if need be, load up a spilled temp into the reg we've just freed up. - spills' <- loadTemp r fmt spill_loc my_reg spills + spills' <- loadTemp (VirtualRegFormat r fmt) spill_loc my_reg spills allocateRegsAndSpill reading keep (spill_store ++ spills') @@ -994,18 +986,17 @@ newLocation _ my_reg = InReg my_reg -- | Load up a spilled temporary if we need to (read from memory). loadTemp :: (Instruction instr) - => VirtualReg -- the temp being loaded - -> Format + => VirtualRegFormat -- the temp being loaded -> SpillLoc -- the current location of this temp -> RealReg -- the hreg to load the temp into -> [instr] -> RegM freeRegs [instr] -loadTemp vreg fmt (ReadMem slot) hreg spills +loadTemp (VirtualRegFormat vreg fmt) (ReadMem slot) hreg spills = do - insn <- loadR (RegReal hreg) fmt slot + insn <- loadR (RegFormat (RegReal hreg) fmt) slot recordSpill (SpillLoad $ getUnique vreg) return $ {- mkComment (text "spill load") : -} insn ++ spills -loadTemp _ _ _ _ spills = +loadTemp _ _ _ spills = return spills ===================================== compiler/GHC/CmmToAsm/Reg/Linear/JoinToTargets.hs ===================================== @@ -333,10 +333,10 @@ handleComponent delta instr = do -- spill the source into its slot (instrSpill, slot) - <- spillR (RegReal sreg) scls vreg + <- spillR (RegFormat (RegReal sreg) scls) vreg -- reload into destination reg - instrLoad <- loadR (RegReal dreg) dcls slot + instrLoad <- loadR (RegFormat (RegReal dreg) dcls) slot remainingFixUps <- mapM (handleComponent delta instr) (stronglyConnCompFromEdgedVerticesOrdR rest) @@ -369,10 +369,10 @@ makeMove delta vreg src dst return $ [mkRegRegMoveInstr platform fmt (RegReal s) (RegReal d)] (InMem s, InReg (RealRegUsage d cls)) -> do recordSpill (SpillJoinRM vreg) - return $ mkLoadInstr config (RegReal d) cls delta s + return $ mkLoadInstr config (RegFormat (RegReal d) cls) delta s (InReg (RealRegUsage s cls), InMem d) -> do recordSpill (SpillJoinRM vreg) - return $ mkSpillInstr config (RegReal s) cls delta d + return $ mkSpillInstr config (RegFormat (RegReal s) cls) delta d _ -> -- we don't handle memory to memory moves. -- they shouldn't happen because we don't share ===================================== compiler/GHC/CmmToAsm/Reg/Linear/State.hs ===================================== @@ -44,7 +44,6 @@ import GHC.CmmToAsm.Reg.Linear.Base import GHC.CmmToAsm.Reg.Liveness import GHC.CmmToAsm.Instr import GHC.CmmToAsm.Config -import GHC.Platform.Reg import GHC.Cmm.BlockId import GHC.Platform @@ -122,20 +121,20 @@ makeRAStats state spillR :: Instruction instr - => Reg -> Format -> Unique -> RegM freeRegs ([instr], Int) + => RegFormat -> Unique -> RegM freeRegs ([instr], Int) -spillR reg fmt temp = mkRegM $ \s -> - let (stack1,slots) = getStackSlotFor (ra_stack s) fmt temp - instr = mkSpillInstr (ra_config s) reg fmt (ra_delta s) slots +spillR reg temp = mkRegM $ \s -> + let (stack1,slots) = getStackSlotFor (ra_stack s) (regFormatFormat reg) temp + instr = mkSpillInstr (ra_config s) reg (ra_delta s) slots in RA_Result s{ra_stack=stack1} (instr,slots) loadR :: Instruction instr - => Reg -> Format -> Int -> RegM freeRegs [instr] + => RegFormat -> Int -> RegM freeRegs [instr] -loadR reg fmt slot = mkRegM $ \s -> - RA_Result s (mkLoadInstr (ra_config s) reg fmt (ra_delta s) slot) +loadR reg slot = mkRegM $ \s -> + RA_Result s (mkLoadInstr (ra_config s) reg (ra_delta s) slot) getFreeRegsR :: RegM freeRegs freeRegs getFreeRegsR = mkRegM $ \ s at RA_State{ra_freeregs = freeregs} -> ===================================== compiler/GHC/CmmToAsm/Reg/Liveness.hs ===================================== @@ -97,29 +97,32 @@ type LiveCmmDecl statics instr -- so we'll keep those here. data InstrSR instr -- | A real machine instruction - = Instr instr + = Instr !instr -- | spill this reg to a stack slot - | SPILL Reg Format Int + | SPILL !RegFormat !Int -- | reload this reg from a stack slot - | RELOAD Int Reg Format + | RELOAD !Int !RegFormat deriving (Functor) instance Instruction instr => Instruction (InstrSR instr) where regUsageOfInstr platform i = case i of - Instr instr -> regUsageOfInstr platform instr - SPILL reg fmt _ -> RU [RegFormat reg fmt] [] - RELOAD _ reg fmt -> RU [] [RegFormat reg fmt] + Instr instr -> regUsageOfInstr platform instr + SPILL reg _ -> RU [reg] [] + RELOAD _ reg -> RU [] [reg] patchRegsOfInstr i f = case i of Instr instr -> Instr (patchRegsOfInstr instr f) - SPILL reg cls slot -> SPILL (f reg) cls slot - RELOAD slot reg cls -> RELOAD slot (f reg) cls + SPILL reg slot -> SPILL (updReg f reg) slot + RELOAD slot reg -> RELOAD slot (updReg f reg) + where + updReg g (RegFormat reg fmt) = RegFormat (g reg) fmt + isJumpishInstr :: Instruction instr => InstrSR instr -> Bool isJumpishInstr i = case i of Instr instr -> isJumpishInstr instr @@ -214,7 +217,7 @@ instance Outputable instr ppr (Instr realInstr) = ppr realInstr - ppr (SPILL reg _cls slot) + ppr (SPILL (RegFormat reg _fmt) slot) = hcat [ text "\tSPILL", char ' ', @@ -222,7 +225,7 @@ instance Outputable instr comma, text "SLOT" <> parens (int slot)] - ppr (RELOAD slot reg _cls) + ppr (RELOAD slot (RegFormat reg _fmt)) = hcat [ text "\tRELOAD", char ' ', @@ -458,12 +461,12 @@ slurpReloadCoalesce live slurpLI slotMap li -- remember what reg was stored into the slot - | LiveInstr (SPILL reg _cls slot) _ <- li - , slotMap' <- addToUFM slotMap slot reg + | LiveInstr (SPILL (RegFormat reg _fmt) slot) _ <- li + , slotMap' <- addToUFM slotMap slot reg = return (slotMap', Nothing) -- add an edge between the this reg and the last one stored into the slot - | LiveInstr (RELOAD slot reg _cls) _ <- li + | LiveInstr (RELOAD slot (RegFormat reg _fmt)) _ <- li = case lookupUFM slotMap slot of Just reg2 | reg /= reg2 -> return (slotMap, Just (reg, reg2)) @@ -572,13 +575,13 @@ stripLiveBlock config (BasicBlock i lis) -- The SPILL/RELOAD cases do not appear to be exercised by our codegens -- - spillNat acc (LiveInstr (SPILL reg cls slot) _ : instrs) + spillNat acc (LiveInstr (SPILL reg slot) _ : instrs) = do delta <- get - spillNat (mkSpillInstr config reg cls delta slot ++ acc) instrs + spillNat (mkSpillInstr config reg delta slot ++ acc) instrs - spillNat acc (LiveInstr (RELOAD slot reg cls) _ : instrs) + spillNat acc (LiveInstr (RELOAD slot reg) _ : instrs) = do delta <- get - spillNat (mkLoadInstr config reg cls delta slot ++ acc) instrs + spillNat (mkLoadInstr config reg delta slot ++ acc) instrs spillNat acc (LiveInstr (Instr instr) _ : instrs) | Just i <- takeDeltaInstr instr ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -859,13 +859,12 @@ patchJumpInstr insn patchF -- | Make a spill instruction. mkSpillInstr :: NCGConfig - -> Reg -- register to spill - -> Format - -> Int -- current stack delta - -> Int -- spill slot to use + -> RegFormat -- register to spill + -> Int -- current stack delta + -> Int -- spill slot to use -> [Instr] -mkSpillInstr config reg fmt delta slot +mkSpillInstr config (RegFormat reg fmt) delta slot = let off = spillSlotToOffset platform slot - delta in case fmt of VecFormat {} @@ -881,13 +880,12 @@ mkSpillInstr config reg fmt delta slot -- | Make a spill reload instruction. mkLoadInstr :: NCGConfig - -> Reg -- register to load - -> Format + -> RegFormat -- register to load -> Int -- current stack delta -> Int -- spill slot to use -> [Instr] -mkLoadInstr config reg fmt delta slot +mkLoadInstr config (RegFormat reg fmt) delta slot = let off = spillSlotToOffset platform slot - delta in case fmt of VecFormat {} @@ -955,17 +953,19 @@ mkRegRegMoveInstr -> Reg -> Reg -> Instr -mkRegRegMoveInstr _platform fmt@(VecFormat _ s) src dst - | isIntScalarFormat s - = if widthInBytes (formatToWidth fmt) <= 128 - then MOVDQU fmt (OpReg src) (OpReg dst) - else VMOVDQU fmt (OpReg src) (OpReg dst) - | otherwise - = if widthInBytes (formatToWidth fmt) <= 128 - then MOVU fmt (OpReg src) (OpReg dst) - else VMOVU fmt (OpReg src) (OpReg dst) -mkRegRegMoveInstr platform fmt src dst - = MOV (scalarMoveFormat platform fmt) (OpReg src) (OpReg dst) +mkRegRegMoveInstr platform fmt src dst = + case fmt of + VecFormat _ s + | isIntScalarFormat s -> + if widthInBytes (formatToWidth fmt) <= 128 + then MOVDQU fmt (OpReg src) (OpReg dst) + else VMOVDQU fmt (OpReg src) (OpReg dst) + | otherwise -> + if widthInBytes (formatToWidth fmt) <= 128 + then MOVU fmt (OpReg src) (OpReg dst) + else VMOVU fmt (OpReg src) (OpReg dst) + _ -> + MOV (scalarMoveFormat platform fmt) (OpReg src) (OpReg dst) scalarMoveFormat :: Platform -> Format -> Format scalarMoveFormat platform fmt @@ -973,10 +973,8 @@ scalarMoveFormat platform fmt = FF64 | II64 <- fmt = II64 - | PW4 <- platformWordSize platform - = II32 | otherwise - = II64 + = archWordFormat (target32Bit platform) -- | Check whether an instruction represents a reg-reg move. -- The register allocator attempts to eliminate reg->reg moves whenever it can, ===================================== compiler/GHC/CmmToAsm/X86/RegInfo.hs ===================================== @@ -24,10 +24,7 @@ mkVirtualReg :: Unique -> Format -> VirtualReg mkVirtualReg u format = case format of FF32 -> VirtualRegD u - -- for scalar F32, we use the same xmm as F64! - -- this is a hack that needs some improvement. - -- For now we map both to being allocated as "Double" Registers - -- on X86/X86_64 + -- On X86, we pass 32-bit floats in the same registers as 64-bit floats. FF64 -> VirtualRegD u -- SIMD NCG TODO: add support for 256 and 512-wide vectors. VecFormat {} -> VirtualRegV128 u View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a012d5e443058641c7b579ea1799d1f7e51617da -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/a012d5e443058641c7b579ea1799d1f7e51617da You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 12:54:27 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Thu, 20 Jun 2024 08:54:27 -0400 Subject: [Git][ghc/ghc][wip/spj-unf-size] 4315 commits: [haddock @ 2002-04-04 16:23:43 by simonmar] Message-ID: <66742683b2e0a_608128b1a1c1302e2@gitlab.mail> Simon Peyton Jones pushed to branch wip/spj-unf-size at Glasgow Haskell Compiler / GHC Commits: 2b39cd94 by Simon Marlow at 2002-04-04T16:23:43+00:00 [haddock @ 2002-04-04 16:23:43 by simonmar] This is Haddock, my stab at a Haskell documentation tool. It's not quite ready for release yet, but I'm putting it in the repository so others can take a look. It uses a locally modified version of the hssource parser, extended with support for GHC extensions and documentation annotations. - - - - - 99ede94f by Simon Marlow at 2002-04-04T16:24:10+00:00 [haddock @ 2002-04-04 16:24:10 by simonmar] forgot one file - - - - - 8363294c by Simon Marlow at 2002-04-05T13:58:15+00:00 [haddock @ 2002-04-05 13:58:15 by simonmar] Remap names in the exported declarations to be "closer" to the current module. eg. if an exported declaration mentions a type 'T' which is imported from module A then re-exported from the current module, then links from the type or indeed the documentation will point to the current module rather than module A. This is to support better hiding: module A won't be referred to in the generated output. - - - - - 1570cbc1 by Simon Marlow at 2002-04-05T13:58:23+00:00 [haddock @ 2002-04-05 13:58:23 by simonmar] update the TODO list - - - - - 3a62f96b by Simon Marlow at 2002-04-05T14:11:51+00:00 [haddock @ 2002-04-05 14:11:51 by simonmar] Fix the anchor for a class declaration - - - - - c5d9a471 by Simon Marlow at 2002-04-05T14:18:41+00:00 [haddock @ 2002-04-05 14:18:41 by simonmar] remove underlines on visited links - - - - - 97280525 by Simon Marlow at 2002-04-05T16:11:47+00:00 [haddock @ 2002-04-05 16:11:47 by simonmar] - Update to generate more correct HTML. - Use our own non-overloaded table combinators, as the overloaded versions were giving me a headache. The improved type safety caught several errors in the HTML generation. - - - - - 9acd3a4d by Simon Marlow at 2002-04-05T16:32:19+00:00 [haddock @ 2002-04-05 16:32:19 by simonmar] Add width property to the title, and add TD.children for the module contents page. - - - - - ec9a0847 by Simon Marlow at 2002-04-08T16:39:56+00:00 [haddock @ 2002-04-08 16:39:56 by simonmar] Fix a problem with exports of the form T(..). - - - - - e4627dc8 by Simon Marlow at 2002-04-08T16:41:38+00:00 [haddock @ 2002-04-08 16:41:37 by simonmar] - Add our own versions of Html & BlockTable for the time being. - Add support for generating an index to the HTML backend - - - - - 2d73fd75 by Simon Marlow at 2002-04-09T11:23:24+00:00 [haddock @ 2002-04-09 11:23:24 by simonmar] Add '-- /' as a synonym for '-- |', for compatibility with IDoc. - - - - - 3675464e by Simon Marlow at 2002-04-09T11:33:55+00:00 [haddock @ 2002-04-09 11:33:54 by simonmar] - add the <...> syntax for marking up URLs in documentation - Make the output for data & class declarations more compact when there aren't any documentation annotations on the individual methods or constructors respectively. - - - - - 5077f5b1 by Simon Marlow at 2002-04-09T11:36:04+00:00 [haddock @ 2002-04-09 11:36:04 by simonmar] Update the TODO list - - - - - 9e83c54d by Simon Marlow at 2002-04-10T10:50:06+00:00 [haddock @ 2002-04-10 10:50:06 by simonmar] Use explicit 'px' suffix on pixel sizes; IE seems to prefer them - - - - - 052de51c by Simon Marlow at 2002-04-10T13:23:13+00:00 [haddock @ 2002-04-10 13:23:13 by simonmar] Lex URLs as a single token to avoid having to escape special characters inside the URL string. - - - - - 47187edb by Simon Marlow at 2002-04-10T13:23:55+00:00 [haddock @ 2002-04-10 13:23:55 by simonmar] Not sure why I made the constructor name for a record declaration into a TyCls name, but change it back into a Var name anyhow. - - - - - 3dc6aa81 by Simon Marlow at 2002-04-10T13:26:10+00:00 [haddock @ 2002-04-10 13:26:09 by simonmar] Lots of changes, including: - add index support to the HTML backend - clean up the renamer, put it into a monad - propogate unresolved names to the top level and report them in a nicer way - various bugfixes - - - - - c2a70a72 by Simon Marlow at 2002-04-10T13:32:39+00:00 [haddock @ 2002-04-10 13:32:39 by simonmar] Skeleton documentation - - - - - 50c98d17 by Simon Marlow at 2002-04-10T13:37:23+00:00 [haddock @ 2002-04-10 13:37:23 by simonmar] Update the TODO list, separate into pre-1.0 and post-1.0 items - - - - - f3778be6 by Simon Marlow at 2002-04-10T14:30:58+00:00 [haddock @ 2002-04-10 14:30:58 by simonmar] Add an introduction - - - - - cfbaf9f7 by Simon Marlow at 2002-04-10T14:59:51+00:00 [haddock @ 2002-04-10 14:59:51 by simonmar] Sort the module tree - - - - - 76bd7b34 by Simon Marlow at 2002-04-10T15:50:11+00:00 [haddock @ 2002-04-10 15:50:10 by simonmar] Generate a little table of contents at the top of the module doc (only if the module actually contains some section headings, though). - - - - - bb8560a1 by Simon Marlow at 2002-04-10T16:10:26+00:00 [haddock @ 2002-04-10 16:10:26 by simonmar] Now we understand (or at least don't barf on) type signatures in patterns such as you might find when scoped type variables are in use. - - - - - 86c2a026 by Simon Marlow at 2002-04-10T16:10:49+00:00 [haddock @ 2002-04-10 16:10:49 by simonmar] more updates - - - - - 1c052b0e by Simon Marlow at 2002-04-10T16:28:05+00:00 [haddock @ 2002-04-10 16:28:05 by simonmar] Parse errors in doc strings are now reported as warnings rather that causing the whole thing to fall over. It still needs cleaning up (the warning is emitted with trace) but this will do for the time being. - - - - - ace03e8f by Simon Marlow at 2002-04-10T16:38:03+00:00 [haddock @ 2002-04-10 16:38:03 by simonmar] update again - - - - - 69006c3e by Simon Marlow at 2002-04-11T13:38:02+00:00 [haddock @ 2002-04-11 13:38:02 by simonmar] mention Opera - - - - - fe9b10f8 by Simon Marlow at 2002-04-11T13:40:31+00:00 [haddock @ 2002-04-11 13:40:30 by simonmar] - copy haddock.css into the same place as the generated HTML - new option: --css <file> specifies the style sheet to use - new option: -o <dir> specifies the directory in which to generate the output. - because Haddock now needs to know where to find its default stylesheet, we have to have a wrapper script and do the haddock-inplace thing (Makefile code copied largely from fptools/happy). - - - - - 106adbbe by Simon Marlow at 2002-04-24T15:12:41+00:00 [haddock @ 2002-04-24 15:12:41 by simonmar] Stop slurping comment lines when we see a row of dashes longer than length 2: these are useful as separators. - - - - - 995d3f9e by Simon Marlow at 2002-04-24T15:14:12+00:00 [haddock @ 2002-04-24 15:14:11 by simonmar] Grok the kind of module headers we use in fptools/libraries, and pass the "portability", "stability", and "maintainer" strings through into the generated HTML. If the module header doesn't match the pattern, then we don't include the info in the HTML. - - - - - e14da136 by Simon Marlow at 2002-04-24T15:16:57+00:00 [haddock @ 2002-04-24 15:16:57 by simonmar] Done module headers now. - - - - - 2ca8dfd4 by Simon Marlow at 2002-04-24T15:57:48+00:00 [haddock @ 2002-04-24 15:57:47 by simonmar] Handle gcons in export lists (a common extension). - - - - - 044cea81 by Simon Marlow at 2002-04-25T14:20:12+00:00 [haddock @ 2002-04-25 14:20:12 by simonmar] Add the little lambda icon - - - - - 63955027 by Simon Marlow at 2002-04-25T14:40:05+00:00 [haddock @ 2002-04-25 14:40:05 by simonmar] - Add support for named chunks of documentation which can be referenced from the export list. - Copy the icon from $libdir to the destination in HTML mode. - - - - - 36e3f913 by Simon Marlow at 2002-04-25T16:48:36+00:00 [haddock @ 2002-04-25 16:48:36 by simonmar] More keyboard bashing - - - - - 7ae18dd0 by Simon Marlow at 2002-04-26T08:43:33+00:00 [haddock @ 2002-04-26 08:43:33 by simonmar] Package util reqd. to compile with 4.08.2 - - - - - bbd5fbab by Simon Marlow at 2002-04-26T10:13:00+00:00 [haddock @ 2002-04-26 10:13:00 by simonmar] Include $(GHC_HAPPY_OPTS) when compiling HsParser - - - - - 31c53d79 by Simon Marlow at 2002-04-26T11:18:57+00:00 [haddock @ 2002-04-26 11:18:56 by simonmar] - support for fundeps (partially contributed by Brett Letner - thanks Brett). - make it build with GHC 4.08.2 - - - - - c415ce76 by Simon Marlow at 2002-04-26T13:15:02+00:00 [haddock @ 2002-04-26 13:15:02 by simonmar] Move the explicit formatting of the little table for the stability/portability/maintainer info from the HTML into the CSS, and remove the explicit table size (just right-align it). - - - - - 520ee21a by Simon Marlow at 2002-04-26T16:01:44+00:00 [haddock @ 2002-04-26 16:01:44 by simonmar] Yet more keyboard bashing - this is pretty much complete now. - - - - - 2ae37179 by Simon Marlow at 2002-04-26T16:02:14+00:00 [haddock @ 2002-04-26 16:02:14 by simonmar] Add a couple of things I forgot about - - - - - b7211e04 by Simon Marlow at 2002-04-29T15:28:12+00:00 [haddock @ 2002-04-29 15:28:12 by simonmar] bugfix for declBinders on a NewTypeDecl - - - - - 640c154a by Simon Marlow at 2002-04-29T15:28:54+00:00 [haddock @ 2002-04-29 15:28:54 by simonmar] Allow '-- |' style annotations on constructors and record fields. - - - - - 393f258a by Simon Marlow at 2002-04-29T15:37:32+00:00 [haddock @ 2002-04-29 15:37:32 by simonmar] syntax fix - - - - - 8a2c2549 by Simon Marlow at 2002-04-29T15:37:48+00:00 [haddock @ 2002-04-29 15:37:48 by simonmar] Add an example - - - - - db88f8a2 by Simon Marlow at 2002-04-29T15:55:46+00:00 [haddock @ 2002-04-29 15:55:46 by simonmar] remove a trace - - - - - 2b0248e0 by Simon Marlow at 2002-04-29T15:56:19+00:00 [haddock @ 2002-04-29 15:56:19 by simonmar] Fix for 'make install' - - - - - 120453a0 by Simon Marlow at 2002-04-29T15:56:39+00:00 [haddock @ 2002-04-29 15:56:39 by simonmar] Install the auxilliary bits - - - - - 950e6dbb by Simon Marlow at 2002-04-29T15:57:30+00:00 [haddock @ 2002-04-29 15:57:30 by simonmar] Add BinDist bits - - - - - 154b9d71 by Simon Marlow at 2002-05-01T11:02:52+00:00 [haddock @ 2002-05-01 11:02:52 by simonmar] update - - - - - ba6c39fa by Simon Marlow at 2002-05-01T11:03:26+00:00 [haddock @ 2002-05-01 11:03:26 by simonmar] Add another item - - - - - bacb5e33 by Simon Marlow at 2002-05-03T08:50:00+00:00 [haddock @ 2002-05-03 08:50:00 by simonmar] Fix some typos. - - - - - 54c87895 by Sven Panne at 2002-05-05T19:40:51+00:00 [haddock @ 2002-05-05 19:40:51 by panne] As a temporary hack/workaround for a bug in GHC's simplifier, don't pass Happy the -c option for generating the parsers in this subdir. Furthermore, disable -O for HaddocParse, too. - - - - - e6c08703 by Simon Marlow at 2002-05-06T09:51:10+00:00 [haddock @ 2002-05-06 09:51:10 by simonmar] Add RPM spec file (thanks to Tom Moertel <tom-rpms at moertel.com>) - - - - - 7b8fa8e7 by Simon Marlow at 2002-05-06T12:29:26+00:00 [haddock @ 2002-05-06 12:29:26 by simonmar] Add missing type signature (a different workaround for the bug in GHC's simplifier). - - - - - cd0e300d by Simon Marlow at 2002-05-06T12:30:09+00:00 [haddock @ 2002-05-06 12:30:09 by simonmar] Remove workaround for simplifier bug in previous revision. - - - - - 687e68fa by Simon Marlow at 2002-05-06T12:32:32+00:00 [haddock @ 2002-05-06 12:32:32 by simonmar] Allow empty data declarations (another GHC extension). - - - - - 8f29f696 by Simon Marlow at 2002-05-06T12:49:21+00:00 [haddock @ 2002-05-06 12:49:21 by simonmar] Fix silly bug in named documentation block lookup. - - - - - 8e0059af by Simon Marlow at 2002-05-06T13:02:42+00:00 [haddock @ 2002-05-06 13:02:42 by simonmar] Add another named chunk with a different name - - - - - 68f8a896 by Simon Marlow at 2002-05-06T13:32:32+00:00 [haddock @ 2002-05-06 13:32:32 by simonmar] Be more lenient about extra paragraph breaks - - - - - 65fc31db by Simon Marlow at 2002-05-07T15:36:36+00:00 [haddock @ 2002-05-07 15:36:36 by simonmar] DocEmpty is a right and left-unit of DocAppend (remove it in the smart constructor). - - - - - adc81078 by Simon Marlow at 2002-05-07T15:37:15+00:00 [haddock @ 2002-05-07 15:37:15 by simonmar] Allow code blocks to be denoted with bird-tracks in addition to [...]. - - - - - 1283a3c1 by Simon Marlow at 2002-05-08T11:21:56+00:00 [haddock @ 2002-05-08 11:21:56 by simonmar] Add a facility for specifying options that affect Haddock's treatment of the module. Options are given at the top of the module in a comma-separated list, beginning with '-- #'. eg. -- # prune, hide, ignore-exports Options currently available, with their meanings: prune: ignore declarations which have no documentation annotations ignore-exports: act as if the export list were not specified (i.e. export everything local to the module). hide: do not include this module in the generated documentation, but propagate any exported definitions to modules which re-export them. There's a slight change in the semantics for re-exporting a full module by giving 'module M' in the export list: if module M does not have the 'hide' option, then the documentation will now just contain a reference to module M rather than the full inlined contents of that module. These features, and some other changes in the pipeline, are the result of discussions between myself and Manuel Chakravarty <chak at cse.unsw.edu.au> (author of IDoc) yesterday. Also: some cleanups, use a Writer monad to collect error messages in some places instead of just printing them with trace. - - - - - a2239cf5 by Simon Marlow at 2002-05-08T11:22:30+00:00 [haddock @ 2002-05-08 11:22:30 by simonmar] Update to test new features. - - - - - 6add955f by Simon Marlow at 2002-05-08T13:37:25+00:00 [haddock @ 2002-05-08 13:37:25 by simonmar] Change the markup for typewriter-font from [...] to @... at . The reasoning is that the '@' symbol is much less likely to be needed than square brackets, and we don't want to have to escape square brackets in code fragments. This will be mildly painful in the short term, but it's better to get the change out of the way as early as possible. - - - - - cda06447 by Simon Marlow at 2002-05-08T13:39:56+00:00 [haddock @ 2002-05-08 13:39:56 by simonmar] Allow nested-style comments to be used as documentation annotations too. eg. {-| ... -} is equivalent to -- | ... An extra space can also be left after the comment opener: {- | ... -}. The only version that isn't allowed is {-# ... -}, because this syntax overlaps with Haskell pragmas; use {- # ... -} instead. - - - - - db23f65e by Simon Marlow at 2002-05-08T14:48:41+00:00 [haddock @ 2002-05-08 14:48:39 by simonmar] Add support for existential quantifiers on constructors. - - - - - adce3794 by Simon Marlow at 2002-05-08T15:43:25+00:00 [haddock @ 2002-05-08 15:43:25 by simonmar] update - - - - - 62a1f436 by Simon Marlow at 2002-05-08T15:44:10+00:00 [haddock @ 2002-05-08 15:44:10 by simonmar] Update to version 0.2 - - - - - f6a24ba3 by Simon Marlow at 2002-05-09T08:48:29+00:00 [haddock @ 2002-05-09 08:48:29 by simonmar] typo - - - - - 9f9522a4 by Simon Marlow at 2002-05-09T10:33:14+00:00 [haddock @ 2002-05-09 10:33:14 by simonmar] oops, left out '/' from the special characters in the last change. - - - - - 14abcb39 by Simon Marlow at 2002-05-09T10:34:44+00:00 [haddock @ 2002-05-09 10:34:44 by simonmar] Fix buglet - - - - - b8d878be by Simon Marlow at 2002-05-09T10:35:00+00:00 [haddock @ 2002-05-09 10:35:00 by simonmar] Give a more useful instance of Show for Module. - - - - - f7bfd626 by Simon Marlow at 2002-05-09T10:37:07+00:00 [haddock @ 2002-05-09 10:37:07 by simonmar] The last commit to Main.lhs broke the delicate balance of laziness which was being used to avoid computing the dependency graph of modules. So I finally bit the bullet and did a proper topological sort of the module graph, which turned out to be easy (stealing the Digraph module from GHC - this really ought to be in the libraries somewhere). - - - - - b481c1d0 by Simon Marlow at 2002-05-09T10:37:25+00:00 [haddock @ 2002-05-09 10:37:25 by simonmar] another item done - - - - - 032e2b42 by Simon Marlow at 2002-05-09T10:44:15+00:00 [haddock @ 2002-05-09 10:44:15 by simonmar] Don't consider a module re-export as having documentation, for the purposes of deciding whether we need a Synopsis section or not. - - - - - 5fb45e92 by Simon Marlow at 2002-05-09T11:10:55+00:00 [haddock @ 2002-05-09 11:10:55 by simonmar] Add a special case for list types in ppHsAType - - - - - 1937e428 by Simon Marlow at 2002-05-09T12:43:06+00:00 [haddock @ 2002-05-09 12:43:06 by simonmar] Type synonyms can accept a ctype on the RHS, to match GHC. - - - - - 0f16ce56 by Simon Marlow at 2002-05-09T12:45:19+00:00 [haddock @ 2002-05-09 12:45:19 by simonmar] Add 'stdcall' keyword - - - - - 29b0d7d2 by Simon Marlow at 2002-05-09T13:35:45+00:00 [haddock @ 2002-05-09 13:35:45 by simonmar] Add System Requirements section - - - - - bf14dddd by Simon Marlow at 2002-05-09T13:36:11+00:00 [haddock @ 2002-05-09 13:36:11 by simonmar] Test existential types, amongst other things - - - - - 502f8f6f by Simon Marlow at 2002-05-09T13:37:35+00:00 [haddock @ 2002-05-09 13:37:35 by simonmar] Print the module name in a doc-string parse error - - - - - ca1f8d49 by Simon Marlow at 2002-05-09T13:38:04+00:00 [haddock @ 2002-05-09 13:38:04 by simonmar] Add dependency - - - - - 8d3d91ff by Simon Marlow at 2002-05-09T15:37:57+00:00 [haddock @ 2002-05-09 15:37:57 by simonmar] Add the changelog/release notes - - - - - f3960959 by Simon Marlow at 2002-05-09T15:47:47+00:00 [haddock @ 2002-05-09 15:47:47 by simonmar] mention the backquote-style of markup - - - - - 089fb6e6 by Simon Marlow at 2002-05-09T15:59:45+00:00 [haddock @ 2002-05-09 15:59:45 by simonmar] update - - - - - bdd3be0b by Simon Marlow at 2002-05-09T15:59:56+00:00 [haddock @ 2002-05-09 15:59:56 by simonmar] Document changes since 0.1 - - - - - 00fc4af8 by Simon Marlow at 2002-05-10T08:22:48+00:00 [haddock @ 2002-05-10 08:22:48 by simonmar] oops, update to version 0.2 - - - - - a8a79041 by Simon Marlow at 2002-05-10T16:05:08+00:00 [haddock @ 2002-05-10 16:05:08 by simonmar] Only include a mini-contents if there are 2 or more sections - - - - - 06653319 by Simon Marlow at 2002-05-13T09:13:12+00:00 [haddock @ 2002-05-13 09:13:12 by simonmar] fix typos - - - - - 1402b19b by Simon Marlow at 2002-05-13T10:14:22+00:00 [haddock @ 2002-05-13 10:14:22 by simonmar] Allow backquote as the right-hand quote as well as the left-hand quote, as suggested by Dean Herrington. Clean up the grammar a litte. - - - - - dcd5320d by Simon Marlow at 2002-05-13T10:44:10+00:00 [haddock @ 2002-05-13 10:44:10 by simonmar] a couple more things, prioritise a bit - - - - - a90130c4 by Simon Marlow at 2002-05-13T15:19:03+00:00 [haddock @ 2002-05-13 15:19:03 by simonmar] Cope with datatypes which have documentation on the constructor but not the type itself, and records which have documentation on the fields but not the constructor. (Thanks to Ross Paterson for pointing out the bugs). - - - - - a774d432 by Simon Marlow at 2002-05-13T15:20:54+00:00 [haddock @ 2002-05-13 15:20:54 by simonmar] Fix one of the record examples - - - - - 2d1d5218 by Simon Marlow at 2002-05-15T12:44:35+00:00 [haddock @ 2002-05-15 12:44:35 by simonmar] Preserve the newline before a bird-track, but only within a paragraph. - - - - - 1554c09a by Simon Marlow at 2002-05-15T13:03:02+00:00 [haddock @ 2002-05-15 13:03:01 by simonmar] Reworking of the internals to support documenting function arguments (the Most Wanted new feature by the punters). The old method of keeping parsed documentation in a Name -> Doc mapping wasn't going to cut it for anntations on type components, where there's no name to attach the documentation to, so I've moved to storing all the documentation in the abstract syntax. Previously some of the documentation was left in the abstract syntax by the parser, but was later extracted into the mapping. In order to avoid having to parameterise the abstract syntax over the type of documentation stored in it, we have to parse the documentation at the same time as we parse the Haskell source (well, I suppose we could store 'Either String Doc' in the HsSyn, but that's clunky). One upshot is that documentation is now parsed eagerly, and documentation parse errors are fatal (but have better line numbers in the error message). The new story simplifies matters for the code that processes the source modules, because we don't have to maintain the extra Name->Doc mapping, and it should improve efficiency a little too. New features: - Function arguments and return values can now have doc annotations. - If you refer to a qualified name in a doc string, eg. 'IO.putStr', then Haddock will emit a hyperlink even if the identifier is not in scope, so you don't have to make sure everything referred to from the documentation is imported. - several bugs & minor infelicities fixed. - - - - - 57344dc3 by Simon Marlow at 2002-05-15T13:03:19+00:00 [haddock @ 2002-05-15 13:03:19 by simonmar] Bump to version 0.3 - - - - - b2791812 by Simon Marlow at 2002-05-15T13:03:41+00:00 [haddock @ 2002-05-15 13:03:41 by simonmar] update - - - - - fead183e by Simon Marlow at 2002-05-15T13:10:15+00:00 [haddock @ 2002-05-15 13:10:15 by simonmar] Rename Foo.hs to Test.hs, and add a Makefile - - - - - b0b1f89f by Simon Marlow at 2002-05-15T13:16:07+00:00 [haddock @ 2002-05-15 13:16:07 by simonmar] - Remove the note about function argument docs not being implemented - Note that qualified identifiers can be used to point to entities that aren't in scope. - - - - - 5665f31a by Simon Marlow at 2002-05-15T13:28:46+00:00 [haddock @ 2002-05-15 13:28:46 by simonmar] Patch to add support for GHC-style primitive strings ".."#, from Ross Paterson. - - - - - 0564505d by Simon Marlow at 2002-05-17T10:51:57+00:00 [haddock @ 2002-05-17 10:51:57 by simonmar] Fix bugs in qualified name handling (A.B.f was returned as B.f) - - - - - 10e7311c by Simon Marlow at 2002-05-21T10:24:52+00:00 [haddock @ 2002-05-21 10:24:52 by simonmar] - Use an alternate tabular layout for datatypes, which is more compact - Fix some problems with the function argument documentation - - - - - 2f91c2a6 by Simon Marlow at 2002-05-21T10:27:40+00:00 [haddock @ 2002-05-21 10:27:40 by simonmar] add a few more test cases - - - - - 01c2ddd2 by Simon Marlow at 2002-05-21T10:28:33+00:00 [haddock @ 2002-05-21 10:28:33 by simonmar] Rearrange a bit, and add support for tabular datatype rendering - - - - - a4e4c5f8 by Simon Marlow at 2002-05-27T09:03:52+00:00 [haddock @ 2002-05-27 09:03:51 by simonmar] Lots of changes: - instances of a class are listed with the class, and instances involving a datatype are listed with that type. Derived instances aren't included at the moment: the calculation to find the instance head for a derived instance is non-trivial. - some formatting changes; use rows with specified height rather than cellspacing in some places. - various fixes (source file links were wrong, amongst others) - - - - - 48722e68 by Simon Marlow at 2002-05-27T12:30:38+00:00 [haddock @ 2002-05-27 12:30:37 by simonmar] - Put function arguments *before* the doc for the function, as suggested by Sven Panne. This looks nicer when the function documentation is long. - Switch to using bold for binders at the definition site, and use underline for keywords. This makes the binder stand out more. - - - - - 657204d2 by Simon Marlow at 2002-05-27T13:19:49+00:00 [haddock @ 2002-05-27 13:19:49 by simonmar] Fix bug: we weren't renaming HsDocCommentNamed in renameDecl - - - - - 592aae66 by Simon Marlow at 2002-05-27T14:10:27+00:00 [haddock @ 2002-05-27 14:10:27 by simonmar] Fix some bugs in the rendering of qualified type signatures. - - - - - 69c8f763 by Simon Marlow at 2002-05-27T14:36:45+00:00 [haddock @ 2002-05-27 14:36:45 by simonmar] warning message tweak - - - - - 16e64e21 by Simon Marlow at 2002-05-27T14:53:53+00:00 [haddock @ 2002-05-27 14:53:53 by simonmar] hyperlinked identifiers should be in <tt> - - - - - 8d5e4783 by Simon Marlow at 2002-05-27T15:56:45+00:00 [haddock @ 2002-05-27 15:56:45 by simonmar] Do something sensible for modules which don't export anything (except instances). - - - - - 9d3ef811 by Simon Marlow at 2002-05-28T10:12:50+00:00 [haddock @ 2002-05-28 10:12:50 by simonmar] Rename the module documentation properly (bug reported by Sven Panne). - - - - - ef03a1cc by Simon Marlow at 2002-05-28T10:13:04+00:00 [haddock @ 2002-05-28 10:13:04 by simonmar] Add some more test cases - - - - - 92baa0e8 by Simon Marlow at 2002-05-28T11:17:55+00:00 [haddock @ 2002-05-28 11:17:55 by simonmar] If an identifier doesn't lex, then just replace it by a DocString. - - - - - a3156213 by Simon Marlow at 2002-05-28T16:16:19+00:00 [haddock @ 2002-05-28 16:16:19 by simonmar] Only link to names in the current module which are actually listed in the documentation. A name may be exported but not present in the documentation if it is exported as part of a 'module M' export specifier. - - - - - 31acf941 by Simon Marlow at 2002-05-28T16:17:11+00:00 [haddock @ 2002-05-28 16:17:11 by simonmar] update - - - - - 7e474ebf by Sigbjorn Finne at 2002-05-28T22:42:08+00:00 [haddock @ 2002-05-28 22:42:08 by sof] Handle lone occurrences of '/', e.g., -- | This/that. [did this in the lexer rather than in the parser, as I couldn't see a way not to introduce an S/R conflict that way.] - - - - - 093f7e53 by Simon Marlow at 2002-05-29T09:09:49+00:00 [haddock @ 2002-05-29 09:09:49 by simonmar] Back out previous change until we can find a better way to do this. - - - - - 9234389c by Simon Marlow at 2002-05-29T13:19:06+00:00 [haddock @ 2002-05-29 13:19:06 by simonmar] Make the markup syntax a little more friendly: - single quotes are now interpreted literally unless they surround a valid Haskell identifier. So for example now there's no need to escape a single quote used as an apostrophe. - text to the right of a bird track is now literal (if you want marked-up text in a code block, use @...@). - - - - - b3333526 by Simon Marlow at 2002-05-29T13:38:51+00:00 [haddock @ 2002-05-29 13:38:51 by simonmar] Document recent changes to markup syntax - - - - - f93641d6 by Simon Marlow at 2002-05-29T15:27:18+00:00 [haddock @ 2002-05-29 15:27:18 by simonmar] Include the instances in abstract data types too - - - - - 613f21e3 by Simon Marlow at 2002-06-03T13:05:58+00:00 [haddock @ 2002-06-03 13:05:57 by simonmar] Allow exporting of individual class methods and record selectors. For these we have to invent the correct type signature, which we do in the simplest possible way (i.e. no context reduction nonsense in the class case). - - - - - 14b36807 by Simon Marlow at 2002-06-03T13:20:00+00:00 [haddock @ 2002-06-03 13:20:00 by simonmar] Fix linking to qualified names again (thanks to Sven Panne for pointing out the bug). - - - - - 95b10eac by Simon Marlow at 2002-06-03T13:46:48+00:00 [haddock @ 2002-06-03 13:46:48 by simonmar] Fix for exporting record selectors from a newtype declaration - - - - - 272f932e by Simon Marlow at 2002-06-03T13:56:38+00:00 [haddock @ 2002-06-03 13:56:38 by simonmar] update to version 0.3 - - - - - 1c0a3bed by Simon Marlow at 2002-06-03T14:05:07+00:00 [haddock @ 2002-06-03 14:05:07 by simonmar] Add changes in version 0.3 - - - - - 145b4626 by Simon Marlow at 2002-06-03T14:12:38+00:00 [haddock @ 2002-06-03 14:12:38 by simonmar] Render class names as proper binders - - - - - 052106b3 by Simon Marlow at 2002-06-03T14:15:10+00:00 [haddock @ 2002-06-03 14:15:10 by simonmar] update, and separate into bugs, features, and cosmetic items. - - - - - 854f4914 by Simon Marlow at 2002-06-03T14:16:13+00:00 [haddock @ 2002-06-03 14:16:13 by simonmar] More test cases - - - - - 466922c8 by Simon Marlow at 2002-06-03T14:16:56+00:00 [haddock @ 2002-06-03 14:16:56 by simonmar] Example from the paper - - - - - 9962a045 by Simon Marlow at 2002-06-03T14:17:49+00:00 [haddock @ 2002-06-03 14:17:49 by simonmar] A debugging version of the style-sheet, which gives some tables coloured backgrounds so we can see what's going on. - - - - - f16b79db by Simon Marlow at 2002-06-03T14:19:46+00:00 [haddock @ 2002-06-03 14:19:46 by simonmar] typo - - - - - 620db27b by Simon Marlow at 2002-06-03T14:48:32+00:00 [haddock @ 2002-06-03 14:48:32 by simonmar] oops, fix markup bugs - - - - - 53fd105c by Simon Marlow at 2002-06-05T09:05:07+00:00 [haddock @ 2002-06-05 09:05:07 by simonmar] Keep foreign imports when there is no export list (bug reported by Sven Panne). - - - - - 6d98989c by Simon Marlow at 2002-06-05T09:12:02+00:00 [haddock @ 2002-06-05 09:12:02 by simonmar] Identifiers in single quotes can be symbol names too (bug reported by Hal Daume). - - - - - 001811e5 by Sven Panne at 2002-06-08T14:03:36+00:00 [haddock @ 2002-06-08 14:03:36 by panne] Tiny workaround for the fact that Haddock currently ignores HsImportSpecs: Let the local_orig_env take precedence. This is no real solution at all, but improves things sometimes, e.g. in my GLUT documentation. :-) - - - - - 504d19c9 by Simon Marlow at 2002-06-11T09:23:25+00:00 [haddock @ 2002-06-11 09:23:25 by simonmar] portability nit - - - - - e13b5af4 by Simon Marlow at 2002-06-20T12:38:07+00:00 [haddock @ 2002-06-20 12:38:07 by simonmar] Empty declaration fixes. - - - - - f467a9b6 by Simon Marlow at 2002-06-20T12:39:02+00:00 [haddock @ 2002-06-20 12:39:01 by simonmar] Add support for a "prologue" - a description for the whole library, placed on the contents page before the module list. - - - - - b8dbfe20 by Simon Marlow at 2002-06-21T12:43:06+00:00 [haddock @ 2002-06-21 12:43:06 by simonmar] When we have a single code block paragraph, don't place it in <pre>..</pre>, just use <tt>..</tt> to avoid generating extra vertical white space in some browsers. - - - - - 4831dbbd by Simon Marlow at 2002-06-21T15:50:42+00:00 [haddock @ 2002-06-21 15:50:42 by simonmar] Add support for reading and writing interface files(!) This turned out to be quite easy, and necessary to get decent hyperlinks between the documentation for separate packages in the libraries. The functionality isn't quite complete yet: for a given package of modules, you'd like to say "the HTML for these modules lives in directory <dir>" (currently they are assumed to be all in the same place). Two new flags: --dump-interface=FILE dump an interface file in FILE --read-interface=FILE read interface from FILE an interface file describes *all* the modules being processed. Only the exported names are kept in the interface: if you re-export a name from a module in another interface the signature won't be copied. This is a compromise to keep the size of the interfaces sensible. Also, I added another useful option: --no-implicit-prelude avoids trying to import the Prelude. Previously this was the default, but now importing the Prelude from elsewhere makes sense if you also read in an interface containing the Prelude module, so Haddock imports the Prelude implicitly according to the Haskell spec. - - - - - d3640a19 by Sven Panne at 2002-06-23T14:54:00+00:00 [haddock @ 2002-06-23 14:54:00 by panne] Make it compile with newer GHCs - - - - - 780c506b by Sven Panne at 2002-06-23T15:44:31+00:00 [haddock @ 2002-06-23 15:44:31 by panne] Cleaned up build root handling and added more docs - - - - - 45290d2e by Simon Marlow at 2002-06-24T14:37:43+00:00 [haddock @ 2002-06-24 14:37:42 by simonmar] When reading an interface, allow a file path offset to be specified which represents the path to the HTML files for the modules specified by that interface. The path may be either relative (to the location of the HTML for this package), or absolute. The syntax is --read-interface=PATH,FILE where PATH is the path to the HTML, and FILE is the filename containing the interface. - - - - - 4e2b9ae6 by Simon Marlow at 2002-07-03T16:01:08+00:00 [haddock @ 2002-07-03 16:01:07 by simonmar] Handle import specs properly, include 'hiding'. Haddock now has a complete implementation of the Haskell module system (more or less; I won't claim it's 100% correct). - - - - - 9a9aa1a8 by Simon Marlow at 2002-07-03T16:18:16+00:00 [haddock @ 2002-07-03 16:18:16 by simonmar] Update - - - - - 560c3026 by Simon Marlow at 2002-07-04T14:56:10+00:00 [haddock @ 2002-07-04 14:56:10 by simonmar] Clean up the code that constructs the exported declarations, and fix a couple of bugs along the way. Now if you import a class hiding one of the methods, then re-export the class, the version in the documentation will correctly have the appropriate method removed. - - - - - 2c26e77d by Simon Marlow at 2002-07-04T15:26:13+00:00 [haddock @ 2002-07-04 15:26:13 by simonmar] More bugfixes to the export handling - - - - - 03e0710d by Simon Marlow at 2002-07-09T10:12:10+00:00 [haddock @ 2002-07-09 10:12:10 by simonmar] Don't require that the list type comes from "Prelude" for it to be treated as special syntax (sometimes it comes from Data.List or maybe even GHC.Base). - - - - - 44f3891a by Simon Marlow at 2002-07-09T10:12:51+00:00 [haddock @ 2002-07-09 10:12:51 by simonmar] commented-out debugging code - - - - - 97280873 by Krasimir Angelov at 2002-07-09T16:33:33+00:00 [haddock @ 2002-07-09 16:33:31 by krasimir] 'Microsoft HTML Help' support - - - - - 3dc04655 by Simon Marlow at 2002-07-10T09:40:56+00:00 [haddock @ 2002-07-10 09:40:56 by simonmar] Fix for rendering of the (->) type constructor, from Ross Paterson. - - - - - c9f149c6 by Simon Marlow at 2002-07-10T10:26:11+00:00 [haddock @ 2002-07-10 10:26:11 by simonmar] Tweaks to the MS Help support: the extra files are now only generated if you ask for them (--ms-help). - - - - - e8acc1e6 by Simon Marlow at 2002-07-10T10:57:10+00:00 [haddock @ 2002-07-10 10:57:10 by simonmar] Document all the new options since 0.3 - - - - - 8bb85544 by Simon Marlow at 2002-07-10T10:58:31+00:00 [haddock @ 2002-07-10 10:58:31 by simonmar] Sort the options a bit - - - - - abc0dd59 by Simon Marlow at 2002-07-15T09:19:38+00:00 [haddock @ 2002-07-15 09:19:38 by simonmar] Fix a bug in mkExportItems when processing a module without an explicit export list. We were placing one copy of a declaration for each binder in the declaration, which for a data type would mean one copy of the whole declaration per constructor or record selector. - - - - - dde65bb9 by Simon Marlow at 2002-07-15T09:54:16+00:00 [haddock @ 2002-07-15 09:54:16 by simonmar] merge rev. 1.35 - - - - - bd7eb8c4 by Simon Marlow at 2002-07-15T10:14:31+00:00 [haddock @ 2002-07-15 10:14:30 by simonmar] Be a bit more liberal in the kind of commenting styles we allow, as suggested by Malcolm Wallace. Mostly this consists of allowing doc comments either side of a separator token. In an export list, a section heading is now allowed before the comma, as well as after it. eg. module M where ( T(..) -- * a section heading , f -- * another section heading , g ) In record fields, doc comments are allowed anywhere (previously a doc-next was allowed only after the comma, and a doc-before was allowed only before the comma). eg. data R = C { -- | describes 'f' f :: Int -- | describes 'g' , g :: Int } - - - - - 8f6dfe34 by Simon Marlow at 2002-07-15T10:21:56+00:00 [haddock @ 2002-07-15 10:21:56 by simonmar] Mention alternative commenting styles. - - - - - fc515bb7 by Simon Marlow at 2002-07-15T16:16:50+00:00 [haddock @ 2002-07-15 16:16:50 by simonmar] Allow multiple sections/subsections before and after a comma in the export list. Also at the same time I made the syntax a little stricter (multiple commas now aren't allowed between export specs). - - - - - 80a97e74 by Simon Marlow at 2002-07-19T09:13:10+00:00 [haddock @ 2002-07-19 09:13:10 by simonmar] Allow special id's ([], (), etc.) to be used in an import declaration. - - - - - a69d7378 by Simon Marlow at 2002-07-19T09:59:02+00:00 [haddock @ 2002-07-19 09:59:02 by simonmar] Allow special id's ([], (), etc.) to be used in an import declarations. - - - - - d205fa60 by Simon Marlow at 2002-07-19T10:00:16+00:00 [haddock @ 2002-07-19 10:00:16 by simonmar] Relax the restrictions which require doc comments to be followed by semi colons - in some cases this isn't necessary. Now you can write module M where { -- | some doc class C where {} } without needing to put a semicolon before the class declaration. - - - - - e9301e14 by Simon Marlow at 2002-07-23T08:24:09+00:00 [haddock @ 2002-07-23 08:24:09 by simonmar] A new TODO list item - - - - - e5d77586 by Simon Marlow at 2002-07-23T08:40:56+00:00 [haddock @ 2002-07-23 08:40:56 by simonmar] - update the acknowledgements - remove the paragraph that described how to use explicit layout with doc comments; it isn't relevant any more. - - - - - 78a94137 by Simon Marlow at 2002-07-23T08:43:02+00:00 [haddock @ 2002-07-23 08:43:02 by simonmar] more tests - - - - - 5c320927 by Simon Marlow at 2002-07-23T08:43:26+00:00 [haddock @ 2002-07-23 08:43:26 by simonmar] Updates for version 0.4 - - - - - 488e99ae by Simon Marlow at 2002-07-23T09:10:46+00:00 [haddock @ 2002-07-23 09:10:46 by simonmar] Fix the %changelog (rpm complained that it wasn't in the right order) - - - - - a77bb373 by Simon Marlow at 2002-07-23T09:12:38+00:00 [haddock @ 2002-07-23 09:12:38 by simonmar] Another item for the TODO list - - - - - f1ec1813 by Simon Marlow at 2002-07-23T10:18:46+00:00 [haddock @ 2002-07-23 10:18:46 by simonmar] Add a version banner when invoked with -v - - - - - 1d44cadf by Simon Marlow at 2002-07-24T09:28:19+00:00 [haddock @ 2002-07-24 09:28:19 by simonmar] Remove ^Ms - - - - - 4d8d5e94 by Simon Marlow at 2002-07-24T09:42:18+00:00 [haddock @ 2002-07-24 09:42:17 by simonmar] Patches to quieten ghc -Wall, from those nice folks at Galois. - - - - - d6edc43e by Simon Marlow at 2002-07-25T14:37:29+00:00 [haddock @ 2002-07-25 14:37:28 by simonmar] Patch to allow simple hyperlinking to an arbitrary location in another module's documentation, from Volker Stolz. Now in a doc comment: #foo# creates <a name="foo"></a> And you can use the form "M\#foo" to hyperlink to the label 'foo' in module 'M'. Note that the backslash is necessary for now. - - - - - b34d18fa by Simon Marlow at 2002-08-02T09:08:22+00:00 [haddock @ 2002-08-02 09:08:22 by simonmar] The <TT> and <PRE> environments seem to use a font that is a little too small in IE. Compensate. (suggestion from Daan Leijen). - - - - - 8106b086 by Simon Marlow at 2002-08-02T09:25:23+00:00 [haddock @ 2002-08-02 09:25:20 by simonmar] Remove <P>..</P> from around list items, to reduce excess whitespace between the items of bulleted and ordered lists. (Suggestion from Daan Leijen). - - - - - c1acff8f by Simon Marlow at 2002-08-05T09:03:49+00:00 [haddock @ 2002-08-05 09:03:49 by simonmar] update - - - - - f968661c by Simon Marlow at 2002-11-11T09:32:57+00:00 [haddock @ 2002-11-11 09:32:57 by simonmar] Fix cut-n-pasto - - - - - 12d02619 by Simon Marlow at 2002-11-13T09:49:46+00:00 [haddock @ 2002-11-13 09:49:46 by simonmar] Small bugfix in the --read-interface option parsing from Brett Letner. - - - - - 30e32d5e by Ross Paterson at 2003-01-16T15:07:57+00:00 [haddock @ 2003-01-16 15:07:57 by ross] Adjust for the new exception libraries (as well as the old ones). - - - - - 871f65df by Sven Panne at 2003-02-20T21:31:40+00:00 [haddock @ 2003-02-20 21:31:40 by panne] * Add varsyms and consyms to index * Exclude empty entries from index - - - - - bc42cc87 by Sven Panne at 2003-02-24T21:26:29+00:00 [haddock @ 2003-02-24 21:26:29 by panne] Don't convert a "newtype" to a single-constructor "data" for non-abstractly exported types, they are quite different regarding strictness/pattern matching. Now a "data" without any constructors is only emitted for an abstractly exported type, regardless if it is actually a "newtype" or a "data". - - - - - 0c2a1d99 by Sven Panne at 2003-03-08T19:02:38+00:00 [haddock @ 2003-03-08 19:02:38 by panne] Fixed some broken/redirected/canonicalized links found by a very picky link checker. - - - - - 25459269 by Sven Panne at 2003-03-09T21:13:43+00:00 [haddock @ 2003-03-09 21:13:43 by panne] Don't append a fragment to non-defining index entries, only documents with a defining occurrence have a name anchor. - - - - - 6be4db86 by Sven Panne at 2003-03-10T21:34:25+00:00 [haddock @ 2003-03-10 21:34:24 by panne] Escape fragments. This fixes e.g. links to operators. - - - - - eb12972c by Ross Paterson at 2003-04-25T10:50:06+00:00 [haddock @ 2003-04-25 10:50:05 by ross] An 80% solution to generating derived instances. A complete solution would duplicate the instance inference logic, but if a type variable occurs as a constructor argument, then we can just propagate the derived class to the variable. But we know nothing of the constraints on any type variables that occur elsewhere. For example, the declarations data Either a b = Left a | Right b deriving (Eq, Ord) data Ptr a = Ptr Addr# deriving (Eq, Ord) newtype IORef a = IORef (STRef RealWorld a) deriving Eq yield the instances (Eq a, Eq b) => Eq (Either a b) (Ord a, Ord b) => Ord (Either a b) Eq (Ptr a) Ord (Ptr a) (??? a) => Eq (IORef a) The last example shows the limits of this local analysis. Note that a type variable may be in both categories: then we know a constraint, but there may be more, or a stronger constraint, e.g. data Tree a = Node a [Tree a] deriving Eq yields (Eq a, ??? a) => Eq (Tree a) - - - - - de886f78 by Simon Marlow at 2003-04-25T11:17:55+00:00 [haddock @ 2003-04-25 11:17:55 by simonmar] Some updates, including moving the derived instance item down to the bottom of the list now that Ross has contributed some code that does the job for common cases. - - - - - 1b52cffd by Simon Marlow at 2003-04-30T14:02:32+00:00 [haddock @ 2003-04-30 14:02:32 by simonmar] When installing on Windows, run cygpath over $(HADDOCKLIB) so that haddock (a mingw program, built by GHC) can understand it. You still need to be in a cygwin environment to run Haddock, because of the shell script wrapper. - - - - - d4f638de by Simon Marlow at 2003-05-06T10:04:47+00:00 [haddock @ 2003-05-06 10:04:47 by simonmar] Catch another case of a paragraph containing just a DocMonospaced that should turn into a DocCodeBlock. - - - - - 4162b2b9 by Simon Marlow at 2003-05-06T10:11:44+00:00 [haddock @ 2003-05-06 10:11:44 by simonmar] Add some more code-block tests. - - - - - 4f5802c8 by Simon Marlow at 2003-05-06T10:14:52+00:00 [haddock @ 2003-05-06 10:14:52 by simonmar] Don't turn a single DocCodeBlock into a DocMonospaced, because that tends to remove the line breaks in the code. - - - - - ef8c45f7 by Simon Marlow at 2003-05-21T15:07:21+00:00 [haddock @ 2003-05-21 15:07:21 by simonmar] Only omit the module contents when there are no section headings at all. - - - - - bcee1e75 by Sigbjorn Finne at 2003-05-30T16:50:45+00:00 [haddock @ 2003-05-30 16:50:45 by sof] cygpath: for now, steer clear of --mixed - - - - - 30567af3 by Sigbjorn Finne at 2003-05-30T17:59:28+00:00 [haddock @ 2003-05-30 17:59:28 by sof] oops, drop test defn from prev commit - - - - - b0856e7d by Simon Marlow at 2003-06-03T09:55:26+00:00 [haddock @ 2003-06-03 09:55:26 by simonmar] Two small fixes to make the output valid HTML 4.01 (transitional). Thanks to Malcolm Wallace for pointing out the problems. - - - - - 70e137ea by Simon Marlow at 2003-07-28T13:30:35+00:00 [haddock @ 2003-07-28 13:30:35 by simonmar] Add tests for a couple of bugs. - - - - - 122bd578 by Simon Marlow at 2003-07-28T13:31:25+00:00 [haddock @ 2003-07-28 13:31:25 by simonmar] Add documentation for anchors. - - - - - 0bd27cb2 by Simon Marlow at 2003-07-28T13:31:46+00:00 [haddock @ 2003-07-28 13:31:46 by simonmar] Update - - - - - 08052d42 by Simon Marlow at 2003-07-28T13:32:12+00:00 [haddock @ 2003-07-28 13:32:12 by simonmar] layout tweak. - - - - - 13942749 by Simon Marlow at 2003-07-28T13:33:03+00:00 [haddock @ 2003-07-28 13:33:03 by simonmar] Differentiate links to types/classes from links to variables/constructors with a prefix ("t:" and "v:" respectively). - - - - - d7f493b9 by Simon Marlow at 2003-07-28T13:35:17+00:00 [haddock @ 2003-07-28 13:35:16 by simonmar] When a module A exports another module's contents via 'module B', then modules which import entities from B re-exported by A should link to B.foo rather than A.foo. See examples/Bug2.hs. - - - - - d94cf705 by Simon Marlow at 2003-07-28T13:36:14+00:00 [haddock @ 2003-07-28 13:36:14 by simonmar] Update to version 0.5 - - - - - dbb776cd by Sven Panne at 2003-07-28T14:02:43+00:00 [haddock @ 2003-07-28 14:02:43 by panne] * Updated to version 0.5 * Automagically generate configure if it is not there - - - - - 6cfeee53 by Simon Marlow at 2003-07-28T14:32:43+00:00 [haddock @ 2003-07-28 14:32:42 by simonmar] Update to avoid using hslibs with GHC >= 5.04 - - - - - a1ce838f by Simon Marlow at 2003-07-28T14:33:37+00:00 [haddock @ 2003-07-28 14:33:37 by simonmar] Update for 0.5 - - - - - c0fe6493 by Simon Marlow at 2003-07-28T14:53:22+00:00 [haddock @ 2003-07-28 14:53:22 by simonmar] Markup fix - - - - - 6ea31596 by Sven Panne at 2003-07-28T16:40:45+00:00 [haddock @ 2003-07-28 16:40:45 by panne] Make it compile with GHC >= 6.01 - - - - - afcd30fc by Simon Marlow at 2003-07-30T15:04:52+00:00 [haddock @ 2003-07-30 15:04:52 by simonmar] Pay attention to import specs when building the the import env, as well as the orig env. This may fix some wrong links in documentation when import specs are being used. - - - - - 17c3137f by Simon Marlow at 2003-07-30T16:05:41+00:00 [haddock @ 2003-07-30 16:05:40 by simonmar] Rename instances based on the import_env for the module in which they are to be displayed. This should give, in many cases, better links for the types and classes mentioned in the instance head. This involves keeping around the import_env in the iface until the end, because instances are not collected up until all the modules have been processed. Fortunately it doesn't seem to affect performance much. Instance heads are now attached to ExportDecls, rather than the HTML backend passing around a separate mapping for instances. This is a cleanup. - - - - - 3d3b5c87 by Sven Panne at 2003-08-04T10:18:24+00:00 [haddock @ 2003-08-04 10:18:24 by panne] Don't print parentheses around one-element contexts - - - - - 9e3f3f2d by Simon Marlow at 2003-08-04T12:59:47+00:00 [haddock @ 2003-08-04 12:59:47 by simonmar] A couple of TODOs. - - - - - e9d8085c by Simon Marlow at 2003-08-05T14:10:31+00:00 [haddock @ 2003-08-05 14:10:31 by simonmar] I'm not sure why, but it seems that the index entries for non-defining occurrences of entities did not have an anchor - the link just pointed to the module. This fixes it. - - - - - ff5c7d6d by Simon Marlow at 2003-08-15T14:42:59+00:00 [haddock @ 2003-08-15 14:42:59 by simonmar] Convert the lexer to Alex, and fix a bug in the process. - - - - - 1aa077bf by Simon Marlow at 2003-08-15T15:00:18+00:00 [haddock @ 2003-08-15 15:00:18 by simonmar] Update - - - - - d3de1e38 by Simon Marlow at 2003-08-15T15:01:03+00:00 [haddock @ 2003-08-15 15:01:03 by simonmar] wibbles - - - - - b40ece3b by Simon Marlow at 2003-08-18T10:04:47+00:00 [haddock @ 2003-08-18 10:04:47 by simonmar] Lex the 'mdo' keyword as 'do'. - - - - - 8f9a1146 by Simon Marlow at 2003-08-18T11:48:24+00:00 [haddock @ 2003-08-18 11:48:24 by simonmar] Two bugs from Sven. - - - - - ea54ebc0 by Simon Marlow at 2003-08-18T11:48:46+00:00 [haddock @ 2003-08-18 11:48:46 by simonmar] Fixes to the new lexer. - - - - - d5f6a4b5 by Simon Marlow at 2003-08-19T09:09:03+00:00 [haddock @ 2003-08-19 09:09:03 by simonmar] Further wibbles to the syntax. - - - - - 6bbdadb7 by Sven Panne at 2003-08-26T18:45:35+00:00 [haddock @ 2003-08-26 18:45:35 by panne] Use autoreconf instead of autoconf - - - - - 32e889cb by Sven Panne at 2003-08-26T19:01:19+00:00 [haddock @ 2003-08-26 19:01:18 by panne] Made option handling a bit more consistent with other tools, in particular: Every program in fptools should output * version info on stdout and terminate successfully when -V or --version * usage info on stdout and terminate successfully when -? or --help * usage info on stderr and terminate unsuccessfully when an unknown option is given. - - - - - 5d156a91 by Sven Panne at 2003-08-26T19:20:55+00:00 [haddock @ 2003-08-26 19:20:55 by panne] Make it *very* clear that we terminate when given a -V/--version flag - - - - - e6577265 by Sven Panne at 2003-08-27T07:50:03+00:00 [haddock @ 2003-08-27 07:50:02 by panne] * Made -D a short option for --dump-interface. * Made -m a short option for --ms-help. * Made -n a short option for --no-implicit-prelude. * Made -c a short option for --css. * Removed DocBook options from executable (they didn't do anything), but mark them as reserved in the docs. Note that the short option for DocBook output is now -S (from SGML) instead of -d. The latter is now a short option for --debug. * The order of the Options in the documentation now matches the order printed by Haddock itself. Note: Although changing the names of options is often a bad idea, I'd really like to make the options for the programs in fptools more consistent and compatible to the ones used in common GNU programs. - - - - - d303ff98 by Simon Marlow at 2003-09-10T08:23:48+00:00 [haddock @ 2003-09-10 08:23:48 by simonmar] Add doc subdir. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 9a70e46a by Simon Marlow at 2003-09-10T08:24:32+00:00 [haddock @ 2003-09-10 08:24:32 by simonmar] Install these files in $(datadir), not $(libdir), since they're architecture independent. Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - bbb87e7a by Simon Marlow at 2003-09-10T08:25:31+00:00 [haddock @ 2003-09-10 08:25:31 by simonmar] Haddock's supplementary HTML bits now live in $(datadir), not $(libdir). Patch contributed by: Ian Lynagh <igloo at earth.li>. - - - - - 3587c24b by Simon Marlow at 2003-09-22T10:34:38+00:00 [haddock @ 2003-09-22 10:34:38 by simonmar] Allow installing of docs. - - - - - d510b517 by Sven Panne at 2003-10-11T08:10:44+00:00 [haddock @ 2003-10-11 08:10:44 by panne] Include architecture-independent files in file list - - - - - 187d7618 by Sigbjorn Finne at 2003-10-20T17:19:24+00:00 [haddock @ 2003-10-20 17:19:22 by sof] support for i-parameters + zip comprehensions - - - - - b6c7a273 by Simon Marlow at 2003-11-03T14:24:24+00:00 [haddock @ 2003-11-03 14:24:24 by simonmar] Update TODO file. - - - - - 58513e33 by Simon Marlow at 2003-11-05T11:22:04+00:00 [haddock @ 2003-11-05 11:22:04 by simonmar] Remove the last of the uses of 'trace' to emit warnings, and tidy up a couple of places where duplicate warnings were being emitted. - - - - - 33a78846 by Simon Marlow at 2003-11-05T11:30:53+00:00 [haddock @ 2003-11-05 11:30:52 by simonmar] - Suppress warnings about unknown imported modules by default. - Add a -v/--verbose flag to re-enable these warnings. The general idea is to suppress the "Warning: unknown module: Prelude" warnings which most Haddock users will see every time, and which aren't terribly useful. - - - - - a969de7f by Simon Marlow at 2003-11-05T12:30:28+00:00 [haddock @ 2003-11-05 12:30:28 by simonmar] - Remove the emboldening of index entries for defining locations. This isn't useful, and breaks abstractions. - If an entity is re-exported by a module but the module doesn't include documentation for that entity (perhaps because it is re-exported by 'module M'), then don't attempt to hyperlink to the documentation from the index. Instead, just list that module in the index, to indicate that the entity is exported from there. - - - - - f14ea82a by Simon Marlow at 2003-11-05T15:15:59+00:00 [haddock @ 2003-11-05 15:15:59 by simonmar] Index overhaul: - no more separate type/class and variable/function indices - the index now makes a distinction between different entities with the same name. One example is a type constructor with the same name as a data constructor, but another example is simply a function with the same name exported by two different modules. For example, the index entry for 'catch' now looks like this: catch 1 (Function) Control.Exception 2 (Function) GHC.Exception, Prelude, System.IO, System.IO.Error making it clear that there are two different 'catch'es, but one of them is exported by several modules. - Each index page now has the index contents (A B C ...) at the top. Please let me know if you really hate any of this. - - - - - 01a25ca6 by Simon Marlow at 2003-11-05T15:16:38+00:00 [haddock @ 2003-11-05 15:16:38 by simonmar] Update - - - - - 1a7ccb86 by Simon Marlow at 2003-11-05T17:16:05+00:00 [haddock @ 2003-11-05 17:16:04 by simonmar] Support for generating a single unified index for several packages. --use-index=URL turns off normal index generation, causes Index links to point to URL. --gen-index generates an combined index from the specified interfaces. Currently doesn't work exactly right, because the interfaces don't contain the iface_reexported info. I'll need to fix that up. - - - - - a2bca16d by Simon Marlow at 2003-11-06T10:44:52+00:00 [haddock @ 2003-11-06 10:44:52 by simonmar] Include iface_reexported in the .haddock file. This unfortunately bloats the file (40% for base). If this gets to be a problem we can always apply the dictionary trick that GHC uses for squashing .hi files. - - - - - 0a09c293 by Simon Marlow at 2003-11-06T12:39:47+00:00 [haddock @ 2003-11-06 12:39:46 by simonmar] - Add definition lists, marked up like this: -- | This is a definition list: -- -- [@foo@] The description of @foo at . -- -- [@bar@] The description of @bar at . Cunningly, the [] characters are not treated specially unless a [ is found at the beginning of a paragraph, in which case the ] becomes special in the following text. - Add --use-contents and --gen-contents, along the lines of --use-index and --gen-index added yesterday. Now we can generate a combined index and contents for the whole of the hierarchical libraries, and in theory the index/contents on the system could be updated as new packages are added. - - - - - fe1b3460 by Simon Marlow at 2003-11-06T14:47:36+00:00 [haddock @ 2003-11-06 14:47:36 by simonmar] Remove the 'Parent' button - it is of dubious use, and often points into thin air. - - - - - db6d762f by Simon Marlow at 2003-11-06T16:48:14+00:00 [haddock @ 2003-11-06 16:48:11 by simonmar] - Include the OptHide setting in the interface, so we don't include hidden modules in the combined index/contents. - Add a -k/--package flag to set the package name for the current set of modules. The package name for each module is now shown in the right-hand column of the contents, in a combined contents page. - - - - - 7d71718b by Simon Marlow at 2003-11-06T16:50:28+00:00 [haddock @ 2003-11-06 16:50:28 by simonmar] Add -k/--package docs - - - - - ef43949d by Simon Marlow at 2003-11-06T16:51:23+00:00 [haddock @ 2003-11-06 16:51:23 by simonmar] Bump to 0.6 - - - - - 1c419e06 by Simon Marlow at 2003-11-06T16:51:50+00:00 [haddock @ 2003-11-06 16:51:50 by simonmar] update - - - - - 69422327 by Simon Marlow at 2003-11-10T14:41:06+00:00 [haddock @ 2003-11-10 14:41:05 by simonmar] Re-exporting names from a different package is problematic, because we don't have access to the full documentation for the entity. Currently Haddock just ignores entities with no documentation, but this results in bogus-looking empty documentation for many of the modules in the haskell98 package. So: - the documentation will now just list the name, as a link pointing to the location of the actual documentation. - now we don't attempt to link to these re-exported entities if they are referred to by the current module. Additionally: - If there is no documentation in the current module, include just the Synopsis section (rather than just the documentation section, as it was before). This just looks nicer and was on the TODO list. - - - - - 3c3fc433 by Simon Marlow at 2003-11-10T14:51:59+00:00 [haddock @ 2003-11-10 14:51:59 by simonmar] Fix for getReExports: take into account names which are not visible because they are re-exported from a different package. - - - - - 31c8437b by Simon Marlow at 2003-11-10T15:10:53+00:00 [haddock @ 2003-11-10 15:10:53 by simonmar] Version 0.6 changes - - - - - a7c2430b by Simon Marlow at 2003-11-10T15:15:58+00:00 [haddock @ 2003-11-10 15:15:58 by simonmar] getReExports: one error case that isn't - - - - - 00cc459c by Simon Marlow at 2003-11-10T16:15:19+00:00 [haddock @ 2003-11-10 16:15:18 by simonmar] copyright update - - - - - ca62408d by Simon Marlow at 2003-11-11T09:57:25+00:00 [haddock @ 2003-11-11 09:57:25 by simonmar] Version 0.6 - - - - - 3acbf818 by Simon Marlow at 2003-11-11T12:10:44+00:00 [haddock @ 2003-11-11 12:10:44 by simonmar] Go back to producing just the documentation section, rather than just the synopsis section, for a module with no documentation annotations. One reason is that the synopsis section tries to link each entity to its documentation on the same page. Also, the doc section anchors each entity, and it lists instances which the synopsis doesn't. - - - - - 6c90abc2 by Simon Marlow at 2003-11-12T10:03:39+00:00 [haddock @ 2003-11-12 10:03:39 by simonmar] 2002 -> 2003 - - - - - 090bbc4c by Simon Marlow at 2003-11-28T12:08:00+00:00 [haddock @ 2003-11-28 12:08:00 by simonmar] update - - - - - 8096a832 by Simon Marlow at 2003-11-28T12:09:58+00:00 [haddock @ 2003-11-28 12:09:58 by simonmar] Fix some of the problems with Haddock generating pages that are too wide. Now we only specify 'nowrap' when it is necessary to avoid a code box getting squashed up by the text to the right of it. - - - - - 35294929 by Sven Panne at 2003-12-29T17:16:31+00:00 [haddock @ 2003-12-29 17:16:31 by panne] Updated my email address - - - - - cdb697bf by Simon Marlow at 2004-01-08T10:14:24+00:00 [haddock @ 2004-01-08 10:14:24 by simonmar] Add instructions for using GHC to pre-process source for feeding to Haddock. - - - - - 8dfc491f by Simon Marlow at 2004-01-09T12:45:46+00:00 [haddock @ 2004-01-09 12:45:46 by simonmar] Add -optP-P to example ghc command line. - - - - - ac41b820 by Simon Marlow at 2004-02-03T11:02:03+00:00 [haddock @ 2004-02-03 11:02:03 by simonmar] Fix bug in index generation - - - - - f4e7edcb by Simon Marlow at 2004-02-10T11:51:16+00:00 [haddock @ 2004-02-10 11:51:16 by simonmar] Don't throw away whitespace at the beginning of a line (experimental fix). - - - - - 68e212d2 by Simon Marlow at 2004-02-10T12:10:08+00:00 [haddock @ 2004-02-10 12:10:08 by simonmar] Fix for previous commit: I now realise why the whitespace was stripped from the beginning of the line. Work around it. - - - - - e7d7f2df by Sven Panne at 2004-02-10T18:38:45+00:00 [haddock @ 2004-02-10 18:38:45 by panne] Make Haddock link with the latest relocated monad transformer package - - - - - 992d4225 by Simon Marlow at 2004-02-16T10:21:35+00:00 [haddock @ 2004-02-16 10:21:35 by simonmar] Add a TODO - - - - - 1ac55326 by Simon Marlow at 2004-03-12T11:33:39+00:00 [haddock @ 2004-03-12 11:33:39 by simonmar] Add an item. - - - - - 0478e903 by Simon Marlow at 2004-03-15T12:24:05+00:00 [haddock @ 2004-03-15 12:24:05 by simonmar] Add an item. - - - - - 6f26d21a by Simon Marlow at 2004-03-18T14:21:29+00:00 [haddock @ 2004-03-18 14:21:29 by simonmar] Fix URL - - - - - 19b6bb99 by Simon Marlow at 2004-03-22T14:09:03+00:00 [haddock @ 2004-03-22 14:09:03 by simonmar] getReExports was bogus: we should really look in the import_env to find the documentation for an entity which we are re-exporting without documentation. Suggested by: Ross Paterson (patch modified by me). - - - - - 5c756031 by Simon Marlow at 2004-03-24T09:42:11+00:00 [haddock @ 2004-03-24 09:42:10 by simonmar] hiding bug from Ross Paterson (fixed in rev 1.59 of Main.hs) - - - - - 1b692e6c by Simon Marlow at 2004-03-24T10:10:50+00:00 [haddock @ 2004-03-24 10:10:50 by simonmar] mkExportItems fix & simplification: we should be looking at the actual exported names (calculated earlier) to figure out which subordinates of a declaration are exported. This means that if you export a record, and name its fields separately in the export list, the fields will still be visible in the documentation for the constructor. - - - - - 90e5e294 by Simon Marlow at 2004-03-24T10:12:08+00:00 [haddock @ 2004-03-24 10:12:08 by simonmar] Make restrictCons take into account record field names too (removing a ToDo). - - - - - 2600efa4 by Simon Marlow at 2004-03-24T10:16:17+00:00 [haddock @ 2004-03-24 10:16:17 by simonmar] Record export tests. - - - - - 6a8575c7 by Simon Marlow at 2004-03-25T09:35:14+00:00 [haddock @ 2004-03-25 09:35:14 by simonmar] restrictTo: fix for restricting a newtype with a record field. - - - - - dcf55a8d by Simon Marlow at 2004-03-25T10:01:42+00:00 [haddock @ 2004-03-25 10:01:42 by simonmar] Fix duplicate instance bug - - - - - f49aa758 by Simon Marlow at 2004-03-25T10:02:41+00:00 [haddock @ 2004-03-25 10:02:41 by simonmar] Duplicate instance bug. - - - - - 7b87344c by Simon Marlow at 2004-03-25T10:29:56+00:00 [haddock @ 2004-03-25 10:29:56 by simonmar] If a name is imported from two places, one hidden and one not, choose the unhidden one to link to. Also, when there's only a hidden module to link to, don't try linking to it. - - - - - 40f44d7b by Simon Marlow at 2004-03-25T15:17:24+00:00 [haddock @ 2004-03-25 15:17:23 by simonmar] Add support for collaspible parts of the page, with a +/- button and a bit of JavaScript. Make the instances collapsible, and collapse them by default. This makes documentation with long lists of instances (eg. the Prelude) much easier to read. Maybe we should give other documentation sections the same treatment. - - - - - 9b64dc0f by Simon Marlow at 2004-03-25T15:20:55+00:00 [haddock @ 2004-03-25 15:20:55 by simonmar] Update - - - - - c2fff7f2 by Simon Marlow at 2004-03-25T15:45:10+00:00 [haddock @ 2004-03-25 15:45:10 by simonmar] Eliminate some unnecessary spaces in the HTML rendering - - - - - b7948ff0 by Simon Marlow at 2004-03-25T16:00:37+00:00 [haddock @ 2004-03-25 16:00:36 by simonmar] Remove all that indentation in the generated HTML to keep the file sizes down. - - - - - da2bb4ca by Sven Panne at 2004-03-27T09:57:58+00:00 [haddock @ 2004-03-27 09:57:57 by panne] Added the new-born haddock.js to the build process and the documentation. - - - - - b99e6f8c by Sven Panne at 2004-03-27T10:32:20+00:00 [haddock @ 2004-03-27 10:32:20 by panne] "type" is a required attribute of the "script" element - - - - - 562b185a by Sven Panne at 2004-03-27T12:52:34+00:00 [haddock @ 2004-03-27 12:52:34 by panne] Add a doctype for the contents page, too. - - - - - f6a99c2d by Simon Marlow at 2004-04-14T10:03:25+00:00 [haddock @ 2004-04-14 10:03:25 by simonmar] fix for single-line comment syntax - - - - - de366303 by Simon Marlow at 2004-04-20T13:08:04+00:00 [haddock @ 2004-04-20 13:08:04 by simonmar] Allow a 'type' declaration to include documentation comments. These will be ignored by Haddock, but at least one user (Johannes Waldmann) finds this feature useful, and it's easy to add. - - - - - fd78f51e by Simon Marlow at 2004-05-07T15:14:56+00:00 [haddock @ 2004-05-07 15:14:56 by simonmar] - update copyright - add version to abstract - - - - - 59f53e32 by Sven Panne at 2004-05-09T14:39:53+00:00 [haddock @ 2004-05-09 14:39:53 by panne] Fix the fix for single-line comment syntax, ------------------------------------------- is now a valid comment line again. - - - - - 8b18f2fe by Simon Marlow at 2004-05-10T10:11:51+00:00 [haddock @ 2004-05-10 10:11:51 by simonmar] Update - - - - - 225a491d by Ross Paterson at 2004-05-19T13:10:23+00:00 [haddock @ 2004-05-19 13:10:23 by ross] Make the handling of "deriving" slightly smarter, by ignoring data constructor arguments that are identical to the lhs. Now handles things like data Tree a = Leaf a | Branch (Tree a) (Tree a) deriving ... - - - - - 37588686 by Mike Thomas at 2004-05-21T06:38:14+00:00 [haddock @ 2004-05-21 06:38:14 by mthomas] Windows exe extensions (bin remains for Unix). - - - - - cf2b9152 by Simon Marlow at 2004-05-25T09:34:54+00:00 [haddock @ 2004-05-25 09:34:54 by simonmar] Add some TODO items - - - - - 4d29cdfc by Simon Marlow at 2004-05-25T10:41:46+00:00 [haddock @ 2004-05-25 10:41:46 by simonmar] Complain if -h is used with --gen-index or --gen-contents, because it'll overwrite the new index/contents. - - - - - 2e0771e0 by Mike Thomas at 2004-05-28T20:17:55+00:00 [haddock @ 2004-05-28 20:17:55 by mthomas] Windows: search for templates in executable directory. Unix: Haddock tries cwd first rather than error if no -l arg. - - - - - 8d10bde1 by Sven Panne at 2004-06-05T16:53:34+00:00 [haddock @ 2004-06-05 16:53:34 by panne] Misc. rpm spec file cleanup, including: * make BuildRoot handling more consistent * added default file attributes * consistent defines and tags - - - - - 59974349 by Sven Panne at 2004-06-05T18:01:00+00:00 [haddock @ 2004-06-05 18:01:00 by panne] More rpm spec file cleanup, including: * added some BuildRequires * changed packager to me, so people can complain at the right place :-] * consistently refer to haskell.org instead of www.haskell.org - - - - - b94d4903 by Simon Marlow at 2004-07-01T11:08:58+00:00 [haddock @ 2004-07-01 11:08:57 by simonmar] Update to the +/- buttons: use a resized image rather than a <button>. Still seeing some strange effects in Konqueror, so might need to use a fixed-size image instead. - - - - - d5278f67 by Sven Panne at 2004-07-04T15:15:55+00:00 [haddock @ 2004-07-04 15:15:55 by panne] Install pictures for +/- pictures, too (JPEG is a strange format for graphics like this, I would have expected GIF or PNG here.) Things look fine with Konqueror and Netscape on Linux now, the only downside is that the cursor doesn't change when positioned above the "button". - - - - - 46dec6c5 by Sven Panne at 2004-07-13T17:59:28+00:00 [haddock @ 2004-07-13 17:59:28 by panne] A quote is a valid part of a Haskell identifier, but it would interfere with an ECMA script string delimiter, so escape it there. - - - - - 1d7bc432 by Simon Marlow at 2004-07-22T08:54:06+00:00 [haddock @ 2004-07-22 08:54:06 by simonmar] Add single quote to $ident, so you can say eg. 'foldl'' to refer to foldl' (the longest match rule is our friend). Bug reported by Adrian Hey <ahey at iee.org> - - - - - f183618b by Krasimir Angelov at 2004-07-27T22:59:35+00:00 [haddock @ 2004-07-27 22:58:23 by krasimir] Add basic support for Microsoft HTML Help 2.0 - - - - - d515d0c2 by Krasimir Angelov at 2004-07-27T23:02:36+00:00 [haddock @ 2004-07-27 23:02:36 by krasimir] escape names in the index - - - - - a5f1be23 by Krasimir Angelov at 2004-07-27T23:05:21+00:00 [haddock @ 2004-07-27 23:05:21 by krasimir] Add jsFile, plusFile and minusFile to the file list - - - - - c4fb4881 by Krasimir Angelov at 2004-07-28T22:12:10+00:00 [haddock @ 2004-07-28 22:12:09 by krasimir] bugfix. Move contentsHtmlFile, indexHtmlFile and subIndexHtmlFile functions to HaddockUtil.hs module to make them accessible from HaddockHH2.hs - - - - - 64d30b1d by Krasimir Angelov at 2004-07-30T22:15:47+00:00 [haddock @ 2004-07-30 22:15:45 by krasimir] more stuffs - support for separated compilation of packages - the contents page now uses DHTML TreeView - fixed copyFile bug - - - - - 133c8c5c by Krasimir Angelov at 2004-07-31T12:04:38+00:00 [haddock @ 2004-07-31 12:04:37 by krasimir] make the DHtmlTree in contents page more portable. The +/- buttons are replaced with new images which looks more beatiful. - - - - - 79040963 by Krasimir Angelov at 2004-07-31T13:10:20+00:00 [haddock @ 2004-07-31 13:10:20 by krasimir] Make DHtmlTree compatible with Mozila browser - - - - - 1a55dc90 by Krasimir Angelov at 2004-07-31T14:52:55+00:00 [haddock @ 2004-07-31 14:52:55 by krasimir] fix - - - - - 85ce0237 by Krasimir Angelov at 2004-07-31T14:53:28+00:00 [haddock @ 2004-07-31 14:53:28 by krasimir] HtmlHelp 1.x - - - - - 3c0c53ba by Krasimir Angelov at 2004-07-31T20:35:21+00:00 [haddock @ 2004-07-31 20:35:21 by krasimir] Added support for DevHelp - - - - - d42b5af1 by Krasimir Angelov at 2004-07-31T21:17:51+00:00 [haddock @ 2004-07-31 21:17:51 by krasimir] Document new features in HtmlHelp - - - - - 790fe21e by Krasimir Angelov at 2004-08-01T15:14:02+00:00 [haddock @ 2004-08-01 15:14:02 by krasimir] add missing imports - - - - - fd7cc6bc by Krasimir Angelov at 2004-08-01T19:52:08+00:00 [haddock @ 2004-08-01 19:52:06 by krasimir] fix some bugs. Now I have got the entire libraries documentation in HtmlHelp 2.0 format. - - - - - 94ad7ac8 by Krasimir Angelov at 2004-08-01T19:53:50+00:00 [haddock @ 2004-08-01 19:53:50 by krasimir] I forgot to add the new +/- images - - - - - f0c65388 by Krasimir Angelov at 2004-08-02T16:25:53+00:00 [haddock @ 2004-08-02 16:25:53 by krasimir] Add root node to the table of contents. All modules in tree are not children of the root - - - - - f50bd85d by Sven Panne at 2004-08-02T18:17:46+00:00 [haddock @ 2004-08-02 18:17:46 by panne] Mainly DocBook fixes - - - - - 09527ce3 by Sven Panne at 2004-08-02T20:02:29+00:00 [haddock @ 2004-08-02 20:02:29 by panne] Fixed -o/--odir handling. Generating the output, especially the directory handling, is getting a bit convoluted nowadays... - - - - - c8fbacfa by Sven Panne at 2004-08-02T20:31:13+00:00 [haddock @ 2004-08-02 20:31:13 by panne] Warning police - - - - - 37830bff by Sven Panne at 2004-08-02T20:32:29+00:00 [haddock @ 2004-08-02 20:32:28 by panne] Nuked dead code - - - - - 13847171 by Sven Panne at 2004-08-02T21:12:27+00:00 [haddock @ 2004-08-02 21:12:25 by panne] Use pathJoin instead of low-level list-based manipulation for FilePaths - - - - - c711d61e by Sven Panne at 2004-08-02T21:16:02+00:00 [haddock @ 2004-08-02 21:16:02 by panne] Removed WinDoze CRs - - - - - b1f7dc88 by Sven Panne at 2004-08-03T19:35:59+00:00 [haddock @ 2004-08-03 19:35:59 by panne] Fixed spelling of "http-equiv" attribute - - - - - dd5f394e by Sven Panne at 2004-08-03T19:44:03+00:00 [haddock @ 2004-08-03 19:44:03 by panne] Pacify W3C validator: * Added document encoding (currently UTF-8, not sure if this is completely correct) * Fixed syntax of `id' attributes * Added necessary `alt' attribute for +/- images Small layout improvement: * Added space after +/- images (still not perfect, but better than before) - - - - - 919c47c6 by Sigbjorn Finne at 2004-08-03T19:45:11+00:00 [haddock @ 2004-08-03 19:45:11 by sof] make it compile with <= ghc-6.1 - - - - - 4d6f01d8 by Sigbjorn Finne at 2004-08-03T19:45:30+00:00 [haddock @ 2004-08-03 19:45:30 by sof] ffi wibble - - - - - 4770643a by Sven Panne at 2004-08-03T20:47:46+00:00 [haddock @ 2004-08-03 20:47:46 by panne] Fixed CSS for button style. Note that only "0" is a valid measure without a unit! - - - - - 14aaf2e5 by Sven Panne at 2004-08-03T21:07:59+00:00 [haddock @ 2004-08-03 21:07:58 by panne] Improved spacing of dynamic module tree - - - - - 97c3579a by Simon Marlow at 2004-08-09T11:03:04+00:00 [haddock @ 2004-08-09 11:03:04 by simonmar] Add FormatVersion Patch submitted by: George Russell <ger at informatik.uni-bremen.de> - - - - - af7f8c03 by Simon Marlow at 2004-08-09T11:55:07+00:00 [haddock @ 2004-08-09 11:55:05 by simonmar] Add support for a short description for each module, which is included in the contents. The short description should be given in a "Description: " field of the header. Included in this patch are changes that make the format of the header a little more flexible. From the comments: -- all fields in the header are optional and have the form -- -- [spaces1][field name][spaces] ":" -- [text]"\n" ([spaces2][space][text]"\n" | [spaces]"\n")* -- where each [spaces2] should have [spaces1] as a prefix. -- -- Thus for the key "Description", -- -- > Description : this is a -- > rather long -- > -- > description -- > -- > The module comment starts here -- -- the value will be "this is a .. description" and the rest will begin -- at "The module comment". The header fields must be in the following order: Module, Description, Copyright, License, Maintainer, Stability, Portability. Patches submitted by: George Russell <ger at informatik.uni-bremen.de>, with a few small changes be me, mostly to merge with other recent changes. ToDo: document the module header. - - - - - 7b865ad3 by Simon Marlow at 2004-08-10T14:09:57+00:00 [haddock @ 2004-08-10 14:09:57 by simonmar] Fixes for DevHelp/HtmlHelp following introduction of short module description. - - - - - 814766cd by Simon Marlow at 2004-08-10T14:33:46+00:00 [haddock @ 2004-08-10 14:33:45 by simonmar] Fixes to installation under Windows. - - - - - 39cf9ede by Simon Marlow at 2004-08-12T12:08:23+00:00 [haddock @ 2004-08-12 12:08:23 by simonmar] Avoid using string-gap tricks. - - - - - b6d78551 by Simon Marlow at 2004-08-13T10:53:21+00:00 [haddock @ 2004-08-13 10:53:21 by simonmar] Update - - - - - eaae7417 by Simon Marlow at 2004-08-13T10:53:50+00:00 [haddock @ 2004-08-13 10:53:50 by simonmar] Test for primes in quoted links - - - - - 68c34f06 by Sven Panne at 2004-08-16T19:59:38+00:00 [haddock @ 2004-08-16 19:59:36 by panne] XMLification - - - - - 7f45a6f9 by Sven Panne at 2004-08-18T16:42:54+00:00 [haddock @ 2004-08-18 16:42:54 by panne] Re-added indices + minor fixes - - - - - 8a5dd97c by Sigbjorn Finne at 2004-08-25T17:15:42+00:00 [haddock @ 2004-08-25 17:15:42 by sof] backquote HADDOCK_VERSION defn for <= ghc-6.0.x; believe this is only needed under mingw - - - - - 4b1b42ea by Sven Panne at 2004-08-26T20:08:50+00:00 [haddock @ 2004-08-26 20:08:49 by panne] SGML is dead, long live DocBook XML! Note: The BuildRequires tags in the spec files are still incomplete and the documentation about the DocBook tools needs to be updated, too. Stay tuned... - - - - - 8d52cedb by Sven Panne at 2004-08-26T21:03:19+00:00 [haddock @ 2004-08-26 21:03:19 by panne] Updated BuildRequires tags. Alas, there seems to be no real standard here, so your mileage may vary... At least the current specs should work on SuSE Linux. - - - - - e6982912 by Sigbjorn Finne at 2004-08-30T15:44:59+00:00 [haddock @ 2004-08-30 15:44:59 by sof] escape HADDOCK_VERSION double quotes on all platforms when compiling with <=6.0.x - - - - - b3fbc867 by Simon Marlow at 2004-08-31T13:09:42+00:00 [haddock @ 2004-08-31 13:09:42 by simonmar] Avoid GHC/shell versionitis and create Version.hs - - - - - c359e16a by Sven Panne at 2004-09-05T19:12:33+00:00 [haddock @ 2004-09-05 19:12:32 by panne] * HTML documentation for "foo.xml" goes into directory "foo" again, not "foo-html". This is nicer and consistent with the behaviour for building the docs from SGML. * Disabled building PostScript documentation in the spec files for now, there are some strange issues with the FO->PS conversion for some files which have to be clarified first. - - - - - c68b1eba by Sven Panne at 2004-09-24T07:04:38+00:00 [haddock @ 2004-09-24 07:04:38 by panne] Switched the default state for instances and the module hierarchy to non-collapsed. This can be reversed when we finally use cookies from JavaScript to have a more persistent state. Previously going back and forth in the documentation was simply too annoying because everything was collapsed again and therefore the documentation was not easily navigatable. - - - - - dfb32615 by Simon Marlow at 2004-09-30T08:21:29+00:00 [haddock @ 2004-09-30 08:21:29 by simonmar] Add a feature request - - - - - 45ff783c by Sven Panne at 2004-10-23T19:54:00+00:00 [haddock @ 2004-10-23 19:54:00 by panne] Improved the Cygwin/MinGW chaos a little bit. There is still confusion about host platform vs. target platform... - - - - - 5f644714 by Krasimir Angelov at 2004-10-28T16:01:51+00:00 [haddock @ 2004-10-28 16:01:51 by krasimir] update for ghc-6.3+ - - - - - 92d9753e by Sven Panne at 2004-11-01T16:39:01+00:00 [haddock @ 2004-11-01 16:39:01 by panne] Revert previous commit: It's Network.URI which should be changed, not Haddock. - - - - - 05f70f6e by Simon Marlow at 2005-01-04T16:15:51+00:00 [haddock @ 2005-01-04 16:15:51 by simonmar] parser fix: allow qualified specialids. - - - - - 47870837 by Simon Marlow at 2005-01-04T16:16:54+00:00 [haddock @ 2005-01-04 16:16:54 by simonmar] Add a test - - - - - ff11fc2c by Ross Paterson at 2005-01-10T19:18:22+00:00 [haddock @ 2005-01-10 19:18:22 by ross] Render non-ASCII characters using numeric character references, to simplify charset issues. There's a META tag saying the charset is UTF-8, but GHC outputs characters as raw bytes. Ideally we need an encoding on the input side too, primarily in comments, because source files containing non-ASCII characters aren't portable between locales. - - - - - eba2fc4e by Simon Marlow at 2005-01-11T10:44:37+00:00 [haddock @ 2005-01-11 10:44:37 by simonmar] Remove string gap - - - - - b899a381 by Ross Paterson at 2005-01-13T11:41:33+00:00 [haddock @ 2005-01-13 11:41:33 by ross] recognize SGML-style numeric character references &#ddd; or &#xhhhh; and translate them into Chars. - - - - - 106e3cf0 by Ross Paterson at 2005-01-13T14:43:41+00:00 [haddock @ 2005-01-13 14:43:41 by ross] also allow uppercase X in hexadecimal character references (like SGML) - - - - - e8f54f25 by Ross Paterson at 2005-01-13T14:44:24+00:00 [haddock @ 2005-01-13 14:44:24 by ross] Describe numeric character references. - - - - - 914ccdce by Sven Panne at 2005-01-15T18:44:48+00:00 [haddock @ 2005-01-15 18:44:45 by panne] Make Haddock compile again after the recent base package changed. The Map/Set legacy hell has been factored out, so that all modules can simply use the new non-deprecated interfaces. Probably a lot of things can be improved by a little bit of Map/Set/List algebra, this can be done later if needed. Small note: Currently the list of instances in HTML code is reversed. This will hopefully be fixed later. - - - - - 6ab20e84 by Sven Panne at 2005-01-16T12:18:26+00:00 [haddock @ 2005-01-16 12:18:26 by panne] Trim imports - - - - - efb81da9 by Sven Panne at 2005-01-16T12:58:08+00:00 [haddock @ 2005-01-16 12:58:03 by panne] Correctly handle the new order of arguments for the combining function given to fromListWith. - - - - - e27b5834 by Sven Panne at 2005-01-16T14:14:41+00:00 [haddock @ 2005-01-16 14:14:39 by panne] Data.Map.unions is left-biased. - - - - - dae3cc3e by Sven Panne at 2005-01-16T14:22:44+00:00 [haddock @ 2005-01-16 14:22:44 by panne] Added the last missing "flip" to get identical HTML output as previous versions. - - - - - 951d8408 by Sven Panne at 2005-01-16T14:37:10+00:00 [haddock @ 2005-01-16 14:37:10 by panne] Refactored Text.PrettyPrint legacy hell into a separate module. - - - - - f1c4b892 by Sven Panne at 2005-01-16T15:41:25+00:00 [haddock @ 2005-01-16 15:41:21 by panne] Cleaned up imports and dropped support for GHC < 5.03, it never worked, anyway. - - - - - 60824c6e by Simon Marlow at 2005-01-18T10:02:48+00:00 [haddock @ 2005-01-18 10:02:48 by simonmar] Add a TODO - - - - - a8c82f23 by Krasimir Angelov at 2005-01-28T23:19:39+00:00 [haddock @ 2005-01-28 23:19:39 by krasimir] import Foreign/Foreign.C are required for Windows - - - - - d8450a23 by Simon Marlow at 2005-02-02T16:23:04+00:00 [haddock @ 2005-02-02 16:23:00 by simonmar] Revamp the linking strategy in Haddock. Now name resolution is done in two phases: - first resolve everything to original names, like a Haskell compiler would. - then, figure out the "home" location for every entity, and point all the links to there. The home location is the lowest non-hidden module in the import hierarchy that documents the entity. If there are multiple candidates, one is chosen at random. Also: - Haddock should not generate any HTML with dangling links any more. Unlinked references are just rendered as plain text. - Error reporting is better: if we can't find a link destination for an entity reference, we now emit a warning. - - - - - 1cce71d0 by Simon Marlow at 2005-02-03T13:42:19+00:00 [haddock @ 2005-02-03 13:42:19 by simonmar] - add --ignore-all-exports flag, which behaves as if every module has the ignore-exports attribute (requested by Chris Ryder). - add --hide option to hide a module on the command line. - add --use-package option to get Haddock info for a package from ghc-pkg (largely untested). - remove reexports from the .haddock file, they aren't used any more. - - - - - 767123ef by Ross Paterson at 2005-02-03T16:17:37+00:00 [haddock @ 2005-02-03 16:17:37 by ross] fix typo for < 6.3 - - - - - 0c680c04 by Simon Marlow at 2005-02-04T12:03:31+00:00 [haddock @ 2005-02-04 12:03:31 by simonmar] Fix bug in renameExportItems that meant links in instances weren't being renamed properly. - - - - - ff7abe5f by Simon Marlow at 2005-02-04T12:15:53+00:00 [haddock @ 2005-02-04 12:15:52 by simonmar] Add attribute #not-home, to indicate that the current module should not be considered to be a home module for the each entity it exports, unless there is no other module that exports the entity. - - - - - fc2cfd27 by Simon Marlow at 2005-02-04T12:40:02+00:00 [haddock @ 2005-02-04 12:40:02 by simonmar] Update the documentation w.r.t. home modules and the not-home attribute. - - - - - 26b8ddf7 by Ross Paterson at 2005-02-04T13:36:06+00:00 [haddock @ 2005-02-04 13:36:05 by ross] sort lists of instances by - arity of the type constructors (so higher-kinded instances come first) - name of the class - argument types - - - - - 26bfb19c by Simon Marlow at 2005-02-23T15:57:12+00:00 [haddock @ 2005-02-23 15:57:12 by simonmar] Fix documentation regarding the module attributes. - - - - - 9c3afd02 by Simon Marlow at 2005-02-28T16:18:17+00:00 [haddock @ 2005-02-28 16:18:17 by simonmar] version 0.7 - - - - - a95fd63f by Simon Marlow at 2005-02-28T16:22:08+00:00 [haddock @ 2005-02-28 16:22:08 by simonmar] Attempt to fix the layout of the package names in the contents. Having tried just about everything, the only thing I can get to work reliably is to make the package names line up on a fixed offset from the left margin. This obviously isn't ideal, so anyone else that would like to have a go at improving it is welcome. One option is to remove the +/- buttons from the contents list and go back to a plain table. The contents page now uses CSS for layout rather than tables. It seems that most browsers have different interpretations of CSS layout, so only the simplest things lead to consistent results. - - - - - 905d42f7 by Simon Marlow at 2005-03-01T17:16:42+00:00 [haddock @ 2005-03-01 17:16:40 by simonmar] Another attempt at lining up the package names on the contents page. Now, they line up with Konqueror, and almost line up with Firefox & IE (different layout in each case). - - - - - a0e1d178 by Wolfgang Thaller at 2005-03-09T08:28:39+00:00 [haddock @ 2005-03-09 08:28:39 by wolfgang] Hack haddock's lexer to accept the output from Apple's broken version of cpp (Apple's cpp leaves #pragma set_debug_pwd directives in it's output). - - - - - 9e1eb784 by Simon Marlow at 2005-04-22T14:27:15+00:00 [haddock @ 2005-04-22 14:27:15 by simonmar] Add a TODO item - - - - - 23281f78 by Ross Paterson at 2005-05-18T12:41:59+00:00 [haddock @ 2005-05-18 12:41:59 by ross] fix 3 bugs in --use-package, and document it. - - - - - 00074a68 by Sven Panne at 2005-05-21T12:35:29+00:00 [haddock @ 2005-05-21 12:35:29 by panne] Warning/versionitis police - - - - - 341fa822 by Simon Marlow at 2005-06-15T15:43:21+00:00 [haddock @ 2005-06-15 15:43:21 by simonmar] Allow "licence" as an alternate spelling of "license" - - - - - 3b953f8b by Simon Marlow at 2005-06-16T08:14:12+00:00 [haddock @ 2005-06-16 08:14:12 by simonmar] wibble - - - - - abfd9826 by Simon Marlow at 2005-06-27T14:46:40+00:00 [haddock @ 2005-06-27 14:46:40 by simonmar] name hierarchical HTML files as A-B-C.html instead of A.B.C.html. The old way confused Apache because the extensions are sometimes interpreted as having special meanings. - - - - - a01eea00 by Simon Marlow at 2005-08-04T13:59:40+00:00 [haddock @ 2005-08-04 13:59:40 by simonmar] 0.7 changes - - - - - 170ef87e by Simon Marlow at 2005-08-04T15:08:03+00:00 [haddock @ 2005-08-04 15:08:03 by simonmar] spec file from Jens Peterson - - - - - 7621fde4 by Simon Marlow at 2005-08-04T15:59:30+00:00 [haddock @ 2005-08-04 15:59:30 by simonmar] replace mingw tests with $(Windows) - - - - - a20739bb by Sven Panne at 2005-08-05T07:01:12+00:00 [haddock @ 2005-08-05 07:01:12 by panne] Reverted to previous version (but with bumped version number), the last commit broke RPM building on SuSE systems due to differently named dependencies. As a clarification: All .spec files in the repository have to work at least on SuSE, because that's the system I'm using. And as "Mr. Building Police", I reserve me the right to keep them that way... >:-) It might very well be the case that we need different .spec files for different platforms, so packagers which are unhappy with the current .spec files should contact me, stating the actual problems. - - - - - 4afb15cf by Simon Marlow at 2005-10-05T10:51:45+00:00 [haddock @ 2005-10-05 10:51:45 by simonmar] Add a bug - - - - - 60f69f82 by Simon Marlow at 2005-10-05T12:52:03+00:00 [haddock @ 2005-10-05 12:52:03 by simonmar] Document new behaviour of -s option - - - - - f7e520ca by Simon Marlow at 2005-10-10T15:02:55+00:00 [haddock @ 2005-10-10 15:02:55 by simonmar] extractRecSel: ignore non-record constructors (fixes a crash when using datatypes with a mixture of record and non-record style constructors). - - - - - b2edbedb by Simon Marlow at 2005-10-14T09:44:21+00:00 Start CHANGES for 0.8 - - - - - 21c7ac8d by Simon Marlow at 2005-10-14T23:11:19+00:00 First cut of Cabal build system - - - - - 766cecdd by Simon Marlow at 2005-10-29T08:14:43+00:00 Add configure script and Makefile for the docs Add a separate configure script and build system for building the documentation. The configure and Makefile code is stolen from fptools. This is left as a separate build system so that the main Cabal setup doesn't require a Unix build environment or DocBook XML tools. - - - - - aa36c783 by Duncan Coutts at 2006-01-17T19:29:55+00:00 Add a --wiki=URL flag to add a per-module link to a correspondng wiki page. So each html page gets an extra link (placed next to the source code and contents links) to a corresponding wiki page. The idea is to let readers contribute their own notes, examples etc to the documentation. Also slightly tidy up the code for the --source option. - - - - - e06e2da2 by Simon Marlow at 2006-01-18T09:28:15+00:00 TODO: documnet --wiki - - - - - 17adfda9 by Duncan Coutts at 2006-01-19T20:17:59+00:00 Add an optional wiki link for each top level exported name. In each module, for each "top level" exported entity we add a hyper link to a corresponding wiki page. The link url gets the name of the exported entity as a '#'-style anchor, so if there is an anchor in the page with that name then the users browser should jump directly to it. By "top level" we mean functions, classes, class members and data types (data, type, newtype), but not data constructors, class instances or data type class membership. The link is added at the right of the page and in a small font. Hopefully this is the right balance of visibility/distraction. We also include a link to the wiki base url in the contents and index pages. - - - - - f52324bb by Duncan Coutts at 2006-01-19T20:28:27+00:00 Rewrite pathJoin to only add a path separator when necessary. When the path ends in a file seperator there is no need to add another. Now using "--wiki=http://blah.com/foo/" should do the right thing. (Code snippet adapted from Isaac's FilePath package.) - - - - - 43bb89fa by Duncan Coutts at 2006-01-21T17:15:27+00:00 Teach haddock about line pragmas and add accurate source code links Teach haddock about C and Haskell style line pragmas. Extend the lexer/parser's source location tracking to include the file name as well as line/column. This way each AST item that is tagged with a SrcLoc gets the original file name too. Use this original file name to add source links to each exported item, in the same visual style as the wiki links. Note that the per-export source links are to the defining module rather than whichever module haddock pretends it is exported from. This is what we want for source code links. The source code link URL can also contain the name of the export so one could implement jumping to the actual location of the function in the file if it were linked to an html version of the source rather than just plain text. The name can be selected with the %N wild card. So for linking to the raw source code one might use: --source=http://darcs/haskell.org/foo/%F Or for linking to html syntax highlighted code: --source=http://darcs/haskell.org/foo/%M.html#%N - - - - - edd9f229 by Duncan Coutts at 2006-01-22T00:02:00+00:00 Extend URL variable expansion syntax and add source links to the contents page Like the wiki link on the contents and index page, add a source code link too. Extend the wiki & source URL variable expansion syntax. The original syntax was: %F for the source file name (the .hs version only, not the .lhs or .hs.pp one) %M for the module name (with '.' replaced by '/') The new syntax is: %F or %{FILE} for the original source file name %M or %{MODULE} for the module name (no replacements) %N or %{NAME} for the function/type export name %K or %{KIND} for a type/value flag "t" or "v" with these extensions: %{MODULE/./c} to replace the '.' module seperator with any other char c %{VAR|some text with the % char in it} which means if the VAR is not in use in this URL context then "" else replace the given text with the '%' char replaced by the string value of the VAR. This extension allows us to construct URLs wit optional parts, since the module/file name is not available for the URL in the contents/index pages and the value/type name is not available for the URL at the top level of each module. - - - - - eb3c6ada by Duncan Coutts at 2006-01-23T13:42:34+00:00 Remove the complex substitutions and add more command line flags instead. Instead of incomprehensable URL substitutions like ${MODULE/./-|?m=%} we now use three seperate command line flags for the top level, per-module and per-entity source and wiki links. They are: --source-base, --source-module, --source-entity --comments-base, --comments-module, --comments-entity We leave -s, --source as an alias for --source-module which is how that option behaved previously. The long forms of the substitutions are still available, ${FILE} ${MODULE} etc and the only non-trivial substitution is ${MODULE/./c} to replace the '.' characters in the module name with any other character c. eg ${MODULE/./-} Seperating the source and wiki url flags has the added bonus that they can be turned on or off individually. So users can have per-module links for example without having to also have per-entity links.` - - - - - a2f0f2af by Duncan Coutts at 2006-01-23T13:54:52+00:00 Make the --help output fit in 80 columns. This is a purely cosmetic patch, feel free to ignore it. The only trickery going on is that we don't display the deprecated -s, --source flags in the help message, but we do still accept them. - - - - - 2d3a4b0c by Duncan Coutts at 2006-01-23T14:12:16+00:00 Add documentation for the new --source-* and --comments-* command line options - - - - - 1a82a297 by Simon Marlow at 2006-01-23T17:03:27+00:00 fix markup - - - - - 100d464a by Duncan Coutts at 2006-01-23T18:31:13+00:00 remove a couple TODO items that have been done The --wiki, or rather the --comment-* options are now documented. There is probably no need to have haddock invoke unlit or cpp itself since it can now pick up the line pragmas to get the source locations right. Tools like Cabal will arrange for preprocessors to be run so there is less of a need for tools like haddock to do it themselves. - - - - - 3162fa91 by Simon Marlow at 2006-01-24T14:21:56+00:00 add a test I had lying around - - - - - 98947063 by Simon Marlow at 2006-01-31T13:52:54+00:00 add scabal-version field - - - - - c41876e6 by Neil Mitchell at 2006-02-26T17:48:21+00:00 Add Hoogle output option - - - - - f86fb9c0 by Simon Marlow at 2006-03-08T09:15:20+00:00 add haskell.vim Contributed by Brad Bowman <bsb at bereft.net>, thanks! - - - - - 35d3c511 by benjamin.franksen at 2006-03-03T22:39:54+00:00 fixed libdir (/html was missing) - - - - - 4d08fd7d by Simon Marlow at 2006-03-10T11:13:31+00:00 add PatternGuards extension - - - - - 3f095e70 by Simon Marlow at 2006-03-13T11:40:42+00:00 bug fixes from Brad Bowman - - - - - 8610849d by Sven Panne at 2006-03-19T17:02:56+00:00 Fixed Cabal/RPM build - - - - - 34a994d6 by sven.panne at 2006-04-20T12:39:23+00:00 Avoid pattern guards Due to the use of pattern guards in Haddock, GHC was called with -fglasgow-exts. This in turn enables bang patterns, too, which broke the Haddock build. Removing some unnecessary pattern guards seemed to be the better way of fixing this instead of using a pragma to disable pattern guards. - - - - - bb523f51 by Ross Paterson at 2006-04-24T09:03:25+00:00 extend 'deriving' heuristic a little If an argument of a data constructor has a type variable head, it is irreducible and the same type class can be copied into the constraint. (Formerly we just did this for type variable arguments.) - - - - - dab9fe7a by Simon Marlow at 2006-04-26T10:02:31+00:00 record an idea - - - - - 748b7078 by Simon Marlow at 2006-05-08T08:28:53+00:00 add section about deriving - - - - - 11252ea1 by Simon Marlow at 2006-05-24T15:43:10+00:00 replace a fatal error in lexChar with a parseError - - - - - 382c9411 by Simon Marlow at 2006-05-24T15:45:47+00:00 add a bug - - - - - b79272f5 by Simon Marlow at 2006-05-24T15:46:29+00:00 add a bug report - - - - - 912edf65 by David Waern at 2006-07-10T19:09:23+00:00 Initial modifications -- doesn't compile - - - - - a3c7ba99 by David Waern at 2006-07-11T00:54:19+00:00 More porting work -- doesn't compile - - - - - 0a173d19 by David Waern at 2006-07-11T11:30:03+00:00 Make the repos temporarily compile and illustrate a problem - - - - - bad316de by David Waern at 2006-07-11T15:43:47+00:00 Progress on the porting process - - - - - bbf12d02 by David Waern at 2006-07-11T23:07:44+00:00 More progress on the porting -- first pass starting to shape up - - - - - de580ba2 by David Waern at 2006-07-20T17:48:30+00:00 More progress -- still on phase1 - - - - - 75a917a2 by David Waern at 2006-07-23T18:22:43+00:00 More work on pass1 -- mostly done - - - - - 6697b3f7 by David Waern at 2006-07-23T22:17:40+00:00 More work, started working on the renaming phase -- this code will need a cleanup soon :) - - - - - 82a5bcbb by David Waern at 2006-07-29T16:16:43+00:00 Add instances, build renaming environment, start on the renamer - - - - - c3f8f4f1 by David Waern at 2006-07-29T21:37:48+00:00 Complete the renamer - - - - - 7e00d464 by David Waern at 2006-07-30T21:01:57+00:00 Start porting the Html renderer - - - - - f04ce121 by David Waern at 2006-08-09T20:04:56+00:00 More Html rendering progress - - - - - 20c21b53 by David Waern at 2006-08-10T17:37:47+00:00 More progress - - - - - d7097e0d by David Waern at 2006-08-11T20:31:51+00:00 Cleanup - - - - - a7351e86 by David Waern at 2006-08-12T11:44:47+00:00 Render H98 Data declarations - - - - - 3fb2208e by David Waern at 2006-08-12T17:15:34+00:00 Perfect rendering of Test.hs - - - - - 454fd062 by David Waern at 2006-08-13T21:57:08+00:00 Misc fixes and interface load/save - - - - - 7ef7e7be by David Waern at 2006-08-14T00:56:07+00:00 Some refactoring - - - - - a7d3efef by David Waern at 2006-08-19T20:07:55+00:00 Adapt to latest GHC - - - - - 5fc3c0d7 by David Waern at 2006-08-20T21:28:11+00:00 Move interface read/write to its own module + some cleanup - - - - - 037e011c by David Waern at 2006-08-20T21:38:24+00:00 Small cleanup - - - - - da3a1023 by David Waern at 2006-09-03T16:05:22+00:00 Change mode to BatchCompile to avoid GHC API bug - - - - - 3cc9be3b by David Waern at 2006-09-03T16:06:59+00:00 Starting work on GADT rendering - - - - - 94506037 by David Waern at 2006-09-03T20:02:48+00:00 Compensate for change of export list order in GHC - - - - - c2cec4eb by David Waern at 2006-09-04T20:53:01+00:00 Rename a function - - - - - 9a9735ba by David Waern at 2006-09-05T15:51:21+00:00 Change version number to 2.0 - - - - - 3758a714 by David Waern at 2006-09-05T15:51:49+00:00 Align comment properly - - - - - 68478d9e by David Waern at 2006-09-15T18:03:00+00:00 Remove interface reading/writing code and use the GHC api for creating package environments instead - - - - - d2eedd95 by David Waern at 2006-09-15T18:05:29+00:00 Change the executable name to haddock-ghc-nolib - - - - - fcfbcf66 by David Waern at 2006-09-15T18:05:45+00:00 Small source code cleanup - - - - - d08eb017 by David Waern at 2006-09-15T18:06:21+00:00 Remove handling of --package flag - - - - - b8a4cf53 by David Waern at 2006-09-15T18:07:16+00:00 Remove commented-out code - - - - - bef0a684 by David Waern at 2006-09-15T18:37:57+00:00 Don't warn about missing links to () - - - - - e7d25fd7 by David Waern at 2006-09-15T19:50:49+00:00 Remove Interface and Binary2 modules - - - - - 9894f2a1 by David Waern at 2006-09-15T19:53:43+00:00 Remove debug printing from HaddockHtml - - - - - a0e7455d by David Waern at 2006-09-16T00:16:29+00:00 Comments only - - - - - d5b26fa7 by David Waern at 2006-09-16T00:16:57+00:00 Refactor PackageData creation code and start on building the doc env propery (unfinished) - - - - - 06aaa779 by David Waern at 2006-09-16T00:19:25+00:00 Better comments in Main.hs - - - - - 1a52d1b4 by David Waern at 2006-09-18T22:17:11+00:00 Comments and spacing change - - - - - e5a97767 by David Waern at 2006-09-21T17:02:45+00:00 Remove unnecessary fmapM import in Main - - - - - 9d0f9d3a by David Waern at 2006-09-22T18:07:07+00:00 Make import list in HaddockHtml prettier - - - - - 3452f662 by David Waern at 2006-09-22T18:08:47+00:00 Refactor context rendering - - - - - 12d0a6d0 by David Waern at 2006-09-22T18:09:52+00:00 Do proper HsType rendering (inser parentheses correctly) - - - - - 2c20c2f9 by David Waern at 2006-09-22T18:10:45+00:00 Fix a bug in Main.toHsType - - - - - c5396443 by David Waern at 2006-09-22T18:11:16+00:00 Skip external package modules sort for now - - - - - 3fb95547 by David Waern at 2006-09-22T20:35:40+00:00 Take away trailin "2" on all previously clashing type names - - - - - 2174755f by David Waern at 2006-09-22T20:51:43+00:00 Remove unused imports in Main - - - - - 1e9f7a39 by David Waern at 2006-09-22T20:52:11+00:00 Fix a comment in Main - - - - - 32d9e028 by David Waern at 2006-10-05T16:40:11+00:00 Merge with changes to ghc HEAD - - - - - 3058c8f5 by David Waern at 2006-10-05T16:41:02+00:00 Comment fixes - - - - - b9c217ec by David Waern at 2006-10-05T16:49:59+00:00 Filter out more builtin type constructors from warning messages - - - - - 67e7d252 by David Waern at 2006-10-05T19:38:22+00:00 Refactoring -- better structured pass1 - - - - - cd21c0c1 by David Waern at 2006-10-05T19:44:42+00:00 Remove read/dump interface flags - - - - - 313f9e69 by David Waern at 2006-10-05T19:49:26+00:00 Remove unused pretty printing - - - - - 480f09d1 by David Waern at 2006-12-28T13:22:24+00:00 Update to build with latest GHC HEAD - - - - - 63dccfcb by David Waern at 2007-01-05T01:38:45+00:00 Fixed a bug so that --ghc-flag works correctly - - - - - 3117dadc by David Waern at 2006-12-29T18:53:39+00:00 Automatically get the GHC lib dir - - - - - 9dc84a5c by David Waern at 2006-12-29T19:58:53+00:00 Comments - - - - - 0b0237cc by David Waern at 2007-01-05T16:48:30+00:00 Collect docs based on SrcLoc, syncing with removal of DeclEntity from GHC - - - - - a962c256 by David Waern at 2007-01-05T17:02:47+00:00 Add tabs in haddock.cabal - - - - - 0ca30c97 by David Waern at 2007-01-05T17:04:11+00:00 Add GHCUtils.hs - - - - - c0ab9abe by David Waern at 2007-01-10T11:43:08+00:00 Change package name to haddock-ghc, version 0.1 - - - - - 38e18b27 by David Waern at 2007-01-12T12:03:52+00:00 No binder name for foreign exports - - - - - d18587ab by David Waern at 2007-01-12T12:08:15+00:00 Temp record - - - - - ba6251a0 by David Waern at 2007-01-12T18:27:55+00:00 Remove read/dump-interface (again) - - - - - f4ba2b39 by David Waern at 2007-01-12T18:31:36+00:00 Remove DocOption, use the GHC type - - - - - 511be8bd by David Waern at 2007-01-12T18:32:41+00:00 Use exceptions instead of Either when loading package info - - - - - 0f2144d8 by David Waern at 2007-01-12T18:33:23+00:00 Small type change - - - - - 77507eb7 by David Waern at 2007-01-12T18:33:59+00:00 Remove interface file read/write - - - - - 0ea1e14f by David Waern at 2007-01-17T21:40:26+00:00 Add trace_ppr to GHCUtils - - - - - 3878b493 by David Waern at 2007-01-17T21:40:53+00:00 Sort external package modules and build a doc env - - - - - 8dc323fc by David Waern at 2007-01-17T21:42:41+00:00 Remove comment - - - - - f4c5b097 by David Waern at 2007-01-18T23:22:18+00:00 Add haddock-ghc.cabal and remove ghc option pragma in source file - - - - - da242b2c by David Waern at 2007-01-18T23:22:46+00:00 Remove some tabs - - - - - 288ed096 by David Waern at 2007-01-18T23:39:28+00:00 Moved the defaultErrorHandler to scope only over sortAndCheckModules for now - - - - - 4dd150fe by David Waern at 2007-02-03T21:23:56+00:00 Let restrictCons handle infix constructors - - - - - 97893442 by David Waern at 2007-02-04T16:26:00+00:00 Render infix data constructors - - - - - da89db72 by David Waern at 2007-02-04T16:26:33+00:00 CHange project name to Haddock-GHC - - - - - e93d48af by David Waern at 2007-02-04T16:59:08+00:00 Render infix type constructors properly - - - - - 357bc99b by David Waern at 2007-02-04T17:37:08+00:00 Insert spaces around infix function names - - - - - ab6cfc49 by David Waern at 2007-02-04T17:59:54+00:00 Do not list entities without documentation - - - - - 04249c7e by David Waern at 2007-02-04T19:16:25+00:00 Add GADT support (quite untested) - - - - - 2c223f8d by David Waern at 2007-02-04T19:25:10+00:00 Add package file write/save again! - - - - - b07ed218 by David Waern at 2007-02-04T19:33:02+00:00 Comment out minf_iface based stuff - - - - - 953d1fa7 by David Waern at 2007-02-05T00:12:23+00:00 Solve conflicts - - - - - 593247fc by David Waern at 2007-02-06T19:48:48+00:00 Remove -package flag, GHC's can be used instead - - - - - f658ded2 by David Waern at 2007-02-06T20:50:44+00:00 Start for support of ATs - - - - - 97f9e913 by David Waern at 2007-02-06T20:52:27+00:00 Wibble - - - - - 2ce8e4cf by David Waern at 2007-02-16T12:09:49+00:00 Add the DocOptions change - - - - - dee4a9b5 by David Waern at 2007-03-06T01:24:48+00:00 Wibble - - - - - 7cb99d18 by David Waern at 2007-03-06T01:24:58+00:00 Change version to 2.0 and executable name to haddock - - - - - c5aa02bc by David Waern at 2007-03-08T15:59:49+00:00 Go back to -B flag - - - - - 3a349201 by David Waern at 2007-03-09T13:31:59+00:00 Better exception handling and parsing of GHC flags - - - - - 05a69b71 by David Waern at 2007-03-09T17:45:44+00:00 Remove commented-out DocEntity printing - - - - - 755032cb by davve at dtek.chalmers.se at 2007-03-23T23:30:20+00:00 Remove a file that shouldn't be here - - - - - a7077e5f by davve at dtek.chalmers.se at 2007-03-24T03:58:48+00:00 Remove an import - - - - - 6f55aa8b by davve at dtek.chalmers.se at 2007-03-25T00:46:48+00:00 Start work on Haddock API - - - - - f0199480 by davve at dtek.chalmers.se at 2007-03-25T00:56:36+00:00 Prettify some comments - - - - - f952f9d1 by davve at dtek.chalmers.se at 2007-03-25T00:56:53+00:00 Remove ppr in HaddockTypes - - - - - bc594904 by davve at dtek.chalmers.se at 2007-03-25T00:57:53+00:00 Remove commented out doc env inference - - - - - 11ebf08d by davve at dtek.chalmers.se at 2007-03-25T01:23:25+00:00 De-flatten the namespace - - - - - f696b4bc by davve at dtek.chalmers.se at 2007-03-25T03:21:48+00:00 Add missing stuff to API - - - - - 9a2a04c3 by davve at dtek.chalmers.se at 2007-03-25T03:22:02+00:00 Wibble - - - - - 7d04a6d5 by davve at dtek.chalmers.se at 2007-03-25T03:22:08+00:00 Avoid a GHC bug with parseStaticFlags [] - - - - - 4d2820ba by davve at dtek.chalmers.se at 2007-03-26T04:57:01+00:00 Add fall-through case to mkExportItem - - - - - 6ebc8950 by Stefan O'Rear at 2007-03-26T04:14:53+00:00 Add shebang line to Setup.lhs - - - - - 80966ec5 by davve at dtek.chalmers.se at 2007-03-26T05:24:26+00:00 Fix stupid compile error - - - - - 1ea1385d by davve at dtek.chalmers.se at 2007-04-05T17:19:56+00:00 Do save/read of interface files properly - - - - - 0e4f6541 by David Waern at 2007-04-10T21:08:36+00:00 Add version to ghc dependency - - - - - b0499b63 by David Waern at 2007-04-10T21:37:08+00:00 Change package name to haddock - - - - - 9d50d27e by David Waern at 2007-04-24T00:22:14+00:00 Use filepath package instead of FilePath - - - - - 87c7fcdf by David Waern at 2007-07-10T21:03:04+00:00 Add new package dependencies - - - - - 4768709c by David Waern at 2007-07-11T20:37:11+00:00 Follow changes to record constructor representation - - - - - b9a02fee by Simon Marlow at 2007-05-30T14:00:48+00:00 update to compile with the latest GHC & Cabal - - - - - c0ebdc01 by David Waern at 2007-07-11T21:35:45+00:00 Fix conflicts - - - - - 97f7afd4 by David Waern at 2007-07-11T21:52:38+00:00 Follow changes to the GHC API - - - - - a5b7b58f by David Waern at 2007-07-12T20:36:48+00:00 Call parseStaticFlags before newSession - - - - - f7f50dbc by David Waern at 2007-08-01T21:52:58+00:00 Better indentation in haddock.cabal - - - - - d84e52ad by David Waern at 2007-08-02T00:08:18+00:00 Wibble - - - - - a23f494a by David Waern at 2007-08-02T00:08:24+00:00 Be better at trying to load all module dependencies (debugging) - - - - - ee917f13 by David Waern at 2007-08-03T18:48:08+00:00 Load all targets explicitly (checkModule doesn't chase dependencies anymore) - - - - - 5182d631 by David Waern at 2007-08-16T16:48:55+00:00 Finalize support for links to other packages - - - - - dfd1e3da by David Waern at 2007-08-16T16:51:11+00:00 Fix haddock comment errors in Haddock.Types - - - - - 50c0d83e by David Waern at 2007-08-16T16:51:37+00:00 Remove a debug import - - - - - d84b7c2b by David Waern at 2007-08-16T17:06:30+00:00 Rename PackageData to HaddockPackage - - - - - 3b52cb9f by David Waern at 2007-08-16T17:09:42+00:00 Simplify some comments - - - - - 66fa68d9 by David Waern at 2007-08-16T17:11:38+00:00 Comment the HaddockPackage definition - - - - - 8674c761 by David Waern at 2007-08-16T17:25:54+00:00 Improve code layout in Main - - - - - 571a3a0b by David Waern at 2007-08-16T17:32:13+00:00 Remove explict module imports in Main - - - - - d31b3cb0 by David Waern at 2007-08-16T17:36:23+00:00 Correct comments - - - - - 7f8a9f2b by David Waern at 2007-08-16T17:39:50+00:00 Fix layout problems in Haddock.Types - - - - - 9f421d7f by David Waern at 2007-08-17T11:16:48+00:00 Move options out of Main into Haddock.Options - - - - - 80042b63 by David Waern at 2007-08-17T11:26:59+00:00 Small comment/layout fixes - - - - - b141b982 by David Waern at 2007-08-17T11:28:28+00:00 Change project name from Haddock-GHC to Haddock - - - - - dbeb4a81 by David Waern at 2007-08-17T11:41:05+00:00 Add top module comment to all files - - - - - ce99cc9e by David Waern at 2007-08-17T14:53:04+00:00 Factor out typechecking phase into Haddock.Typecheck - - - - - 6bf75d9e by David Waern at 2007-08-17T16:55:35+00:00 Factor out package code to Haddock.Packages - - - - - b396db37 by David Waern at 2007-08-29T22:40:23+00:00 Major refactoring - - - - - 3d4f95ee by David Waern at 2007-08-29T23:26:24+00:00 Rename HaddockModule to Interface and a few more refactorings - - - - - c55326db by David Waern at 2007-08-29T23:48:03+00:00 Some comment cleanup - - - - - 9a84fc46 by David Waern at 2007-08-29T23:49:29+00:00 Add some modules that I forgot to add earlier - - - - - 4536dce2 by David Waern at 2007-08-29T23:55:24+00:00 Wibble - - - - - 9b7f0206 by David Waern at 2007-08-30T16:03:29+00:00 Wibble - - - - - c52c050a by David Waern at 2007-08-30T16:30:37+00:00 Rename HaddockModule to Interface - - - - - eae2995f by David Waern at 2007-08-30T16:42:59+00:00 Simplify createInterfaces - - - - - 53f99caa by David Waern at 2007-09-29T00:04:31+00:00 Add build-type: Simple to the cabal file - - - - - 0d3103a8 by David Waern at 2007-09-29T00:04:58+00:00 Add containers and array dependency - - - - - 6acf5f30 by David Waern at 2007-09-29T00:13:36+00:00 Prettify the cabal file - - - - - 87c1e378 by David Waern at 2007-09-29T13:16:39+00:00 FIX: consym data headers with more than two variables - - - - - b67fc16a by David Waern at 2007-09-29T14:01:32+00:00 FIX: prefix types used as operators should be quoted - - - - - a8f925bc by David Waern at 2007-09-29T14:02:26+00:00 Use isSymOcc from OccName instead of isConSym - - - - - fc330701 by David Waern at 2007-09-29T14:15:37+00:00 Use isLexConSym/isLexVarSym from OccName - - - - - e4f3dbad by David Waern at 2007-09-29T15:01:08+00:00 FIX: do not quote varsym type operators - - - - - 402207d2 by David Waern at 2007-09-29T15:01:50+00:00 Wibble - - - - - f9d89ef0 by David Waern at 2007-09-29T15:17:40+00:00 Take care when pp tyvars - add parens on syms - - - - - 849e2a77 by David Waern at 2007-10-01T21:56:39+00:00 Go back to using a ModuleMap instead of LookupMod - fixes a bug - - - - - 549dbac6 by David Waern at 2007-10-02T01:05:19+00:00 Improve parsing of doc options - - - - - a36021b8 by David Waern at 2007-10-02T23:05:00+00:00 FIX: double arrows in constructor contexts - - - - - d03bf347 by David Waern at 2007-10-09T16:14:05+00:00 Add a simple test suite - - - - - c252c140 by David Waern at 2007-10-17T16:02:28+00:00 Add --optghc=.. style flag passing to GHC - - - - - cce6c1b3 by David Waern at 2007-10-18T22:03:20+00:00 Add support for --read-interface again - - - - - 33d059c0 by David Waern at 2007-10-18T22:30:18+00:00 Refactoring -- get rid of Haddock.Packages - - - - - f9ed0a4c by David Waern at 2007-10-18T22:34:36+00:00 Name changes - - - - - 8a1c816f by David Waern at 2007-10-20T14:24:23+00:00 Add --ghc-version option - - - - - 4925aaa1 by David Waern at 2007-10-21T14:34:26+00:00 Add some Outputable utils - - - - - 69e7e47f by David Waern at 2007-10-21T14:35:49+00:00 FIX: Ord for OrdName was not comparing modules - - - - - 5a4ae535 by David Waern at 2007-10-21T21:18:48+00:00 Wibble - - - - - 03d48e20 by David Waern at 2007-10-24T15:52:56+00:00 Remove Main from "other modules" - - - - - c66f6d82 by David Waern at 2007-10-24T16:37:18+00:00 Make it possible to run haddock on itself - - - - - 21d156d8 by David Waern at 2007-10-25T14:02:14+00:00 Don't set boot modules as targets - - - - - f8bcf91c by David Waern at 2007-10-31T22:11:17+00:00 Add optimisation flags - - - - - 7ac758f2 by David Waern at 2007-11-04T09:48:28+00:00 Go back to loading only targets (seems to work now) - - - - - 4862aae1 by David Waern at 2007-11-05T22:24:57+00:00 Do full compilation of modules -- temporary fix for GHC API problem - - - - - 697e1517 by David Waern at 2007-11-05T22:25:50+00:00 Don't warn about not being able to link to wired/system/builtin-names - - - - - 892186da by David Waern at 2007-11-06T00:49:21+00:00 Filter out instances with TyCons that are not exported - - - - - 9548314c by David Waern at 2007-11-06T09:37:14+00:00 Wibble - - - - - 5cafd627 by David Waern at 2007-11-08T01:43:07+00:00 Filter out all non-vanilla type sigs - - - - - 04621830 by David Waern at 2007-11-08T01:45:13+00:00 Synch loading of names from .haddock files with GHC's name cache - - - - - 88d37f77 by David Waern at 2007-11-08T01:46:21+00:00 Remove commented-out code - - - - - 6409c911 by David Waern at 2007-11-08T01:56:00+00:00 Small bugfix and cleanup in getDeclFromTyCls - - - - - af59d9c2 by David Waern at 2007-11-08T02:08:44+00:00 Remove OrdName stuff - - - - - 3a615e2e by David Waern at 2007-11-08T02:13:41+00:00 Update runtests.hs following changes to haddock - - - - - 01f3314e by David Waern at 2007-11-08T02:33:01+00:00 Complain if we can't link to wired-in names - - - - - fcafb5d1 by David Waern at 2007-11-09T02:40:16+00:00 Don't exit when there are no file arguments - - - - - 194bc332 by David Waern at 2007-11-09T02:55:37+00:00 Wibble - - - - - dbe4cb55 by David Waern at 2007-11-09T02:56:14+00:00 Wibble - - - - - 82869fda by David Waern at 2007-11-10T17:01:43+00:00 Introduce InstalledInterface structure and add more stuff to the .haddock files We introduce InstalledInterface capturing the part of Interface that is stored in the interface files. We change the ppHtmlContents and ppHtmllIndex to take this structure instead of a partial Interface. We add stuff like the doc map and exported names to the .haddock file (via InstalledInterface). - - - - - d6bb57bf by David Waern at 2007-11-10T17:19:48+00:00 FIX: contents and index should include external package modules when --gen-contents/--gen-index - - - - - e8814716 by David Waern at 2007-11-11T00:29:27+00:00 Remove lDocLinkName and its use in Html backend - - - - - 6f9bd702 by David Waern at 2007-11-11T00:50:57+00:00 Do some refactoring in the html backend This also merges an old patch by Augustsson: Wed Jul 12 19:54:36 CEST 2006 lennart.augustsson at credit-suisse.com * Print type definitions like signatures if given arrows. - - - - - 09d0ce24 by Malcolm.Wallace at 2006-07-20T13:13:57+00:00 mention HsColour in the docs, next to option flags for linking to source code - - - - - 24da6c34 by Malcolm.Wallace at 2006-07-20T13:14:50+00:00 change doc references to CVS to give darcs repository location instead - - - - - 74d52cd6 by David Waern at 2007-11-11T00:55:33+00:00 Update copyright - - - - - fcaa3b4f by Duncan Coutts at 2006-09-08T13:41:00+00:00 Eliminate dep on network by doing a little cut'n'paste haddock depending on the network causes a circular dependency at least if you want to build the network lib with haddock docs. - - - - - 10cc9bda by David Waern at 2007-11-11T02:09:41+00:00 Fix conflicts - - - - - 4e3acd39 by David Waern at 2007-11-11T02:21:19+00:00 Manual merge of a patch from Duncan Coutts that removes the dependency on mtl - - - - - fa9070da by Neil Mitchell at 2006-09-29T15:52:03+00:00 Do not generate an empty table if there are no exports, this fixes a <table></table> tag being generated, which is not valid HTML 4.01 - - - - - d7431c85 by David Waern at 2007-11-11T02:28:50+00:00 Fix conflicts - - - - - f87e8f98 by Simon Marlow at 2006-10-10T11:37:16+00:00 changes for 0.8 - - - - - db929565 by Simon Marlow at 2006-10-10T12:07:12+00:00 fix the name of the source file - - - - - 8220aa4b by Simon Marlow at 2006-10-11T14:17:37+00:00 Rename haddock.js to haddock-util.js haddock.js will be run automatically by Windows when you type 'haddock' if it is found on the PATH, so rename to avoid confusion. Spotted by Adrian Hey. - - - - - 6bccdaa1 by sven.panne at 2006-10-12T15:28:23+00:00 Cabal's sdist does not generate "-src.tar.gz" files, but ".tar.gz" ones - - - - - d3f3fc19 by Simon Marlow at 2006-12-06T16:05:07+00:00 add todo item for --maintainer - - - - - 2da7e269 by Simon Marlow at 2006-12-15T15:52:00+00:00 TODO: do something better about re-exported symbols from another package - - - - - 42d85549 by David Waern at 2007-11-11T02:30:59+00:00 Fix conflicts - - - - - 5e7ef6e5 by Neil Mitchell at 2007-01-11T15:41:15+00:00 Never do spliting index files into many - - - - - f3d4aebe by Neil Mitchell at 2007-01-11T17:07:09+00:00 Add searching on the index page - - - - - bad3ab66 by Neil Mitchell at 2007-01-11T18:17:46+00:00 Delete dead code, now there is only one index page - - - - - cd09eedb by Neil Mitchell at 2007-01-11T18:21:19+00:00 Delete more stuff that is no longer required - - - - - e2806646 by David Waern at 2007-11-11T02:41:53+00:00 Fix conflicts - - - - - a872a823 by Neil Mitchell at 2007-01-11T18:51:43+00:00 Make the index be in case-insensitive alphabetic order - - - - - 8bddd9d7 by Neil Mitchell at 2007-02-06T17:49:12+00:00 Do not create empty tables for data declarations which don't have any constructors, instances or comments. Gets better HTML 4.01 compliance - - - - - 036b8120 by David Waern at 2007-11-11T02:56:58+00:00 Fix conflicts - - - - - f50c1639 by Conal Elliott at 2007-02-14T21:54:00+00:00 added substitution %{FILE///c} - - - - - 402e166a by David Waern at 2007-11-11T03:35:46+00:00 Manual merge of old patch: Sat Apr 21 04:36:43 CEST 2007 Roberto Zunino <zunrob at users.sf.net> * URL expansion for %%, %L, %{LINE} - - - - - 2f264fbd by David Waern at 2007-11-11T03:40:33+00:00 Manual merge of an old patch: Thu Apr 19 20:23:40 CEST 2007 Wolfgang Jeltsch <g9ks157k at acme.softbase.org> * bug fix When Haddock was invoked with the --ignore-all-exports flag but the ignore-exports module attribute wasn't used, hyperlinks weren't created for non-exported names. This fix might not be as clean as one would wish (since --ignore-all-exports now results in ignore_all_exports = True *and* an additional OptIgnoreExports option for every module) but at least the bug seems to be resolved now. - - - - - 7d7ae106 by sven.panne at 2007-09-02T12:18:02+00:00 Install LICENSE in the correct place - - - - - 66eaa924 by David Waern at 2007-11-11T19:02:46+00:00 Fix a bug that made haddock loop - - - - - 4ed47b58 by David Waern at 2007-11-11T19:03:09+00:00 Rename java-script file (this wasn't merge correctly) - - - - - d569534a by David Waern at 2007-11-11T19:06:44+00:00 Don't require -B <ghc-libdir> when no argument files Change readInterfaceFile to take a Maybe Session, to avoid having to pass -B <ghc-libdir> to Haddock when there're no source files to process. This is nice when computing contents/index for external packages. - - - - - 373368bc by Neil Mitchell at 2007-01-11T18:22:44+00:00 Change from tabs to spaces in the ppHtmlIndex function - - - - - 6b063a77 by Neil Mitchell at 2007-01-12T12:17:46+00:00 Rewrite much of the index searching code, previously was too slow to execute on the base library with IE, the new version guarantees less than O(log n) operations be performed, where n is the number in the list (before was always O(n)) - - - - - bfad00b7 by David Waern at 2007-11-11T23:33:53+00:00 Fix conflicts - - - - - cd2dcc09 by Neil Mitchell at 2007-01-12T12:25:01+00:00 Make the max number of results 75 instead of 50, to allow map searching in the base library to work - - - - - 3ae74764 by Neil Mitchell at 2007-01-12T12:58:17+00:00 Make the search box in a form so that enter does the default search - - - - - 142103e5 by David Waern at 2007-11-12T00:03:18+00:00 Merge patch from the old branch: Fri Aug 31 13:21:45 CEST 2007 Duncan Coutts <duncan at haskell.org> * Add category: Development to .cabal file Otherwise it appears on the hackage website in the "Unclassified" category. - - - - - 22ec2ddb by David Waern at 2007-11-25T01:55:29+00:00 A a list of small improvements to the TODO file - - - - - eb0129f4 by Wolfgang Jeltsch at 2007-12-03T23:47:55+00:00 addition of type equality support (at least for HTML generation) - - - - - 816a7e22 by David Waern at 2007-12-08T15:46:26+00:00 Handle class operators correctly when rendering predicates - - - - - 68baaad2 by David Waern at 2007-12-08T16:15:54+00:00 Code layout changes - - - - - 09b77fb4 by David Waern at 2007-12-08T16:16:03+00:00 Handle infix operators correctly in the Type -> HsType translation - - - - - 31c36da2 by David Waern at 2007-12-08T16:24:27+00:00 Add ppLParendTypes/ppLParendType - - - - - b17cc818 by David Waern at 2007-12-08T16:26:12+00:00 Use ppParendType when printing types args in predicates - - - - - ffd1f2cf by David Waern at 2007-12-08T16:45:06+00:00 Fix rendering of instance heads to handle infix operators This is also a refactoring to share this code for rendering predicates. - - - - - ff886d45 by David Waern at 2007-12-08T17:27:46+00:00 Fix rendering of class operators - - - - - e2fcbb9e by David Waern at 2007-12-08T17:59:28+00:00 Fix a bug (use ppTyName instead of ppName to print names in type apps) - - - - - 79a1056e by David Waern at 2007-12-08T21:25:18+00:00 Update tests - - - - - 867741ac by David Waern at 2007-12-08T21:25:49+00:00 Give a diff on test failure - - - - - 7e5eb274 by David Waern at 2008-01-05T14:33:45+00:00 Add DrIFT commands - - - - - 3656454d by David Waern at 2008-01-05T20:26:00+00:00 Add "cabal-version: >= 1.2" to the cabal file - - - - - 77974efc by Simon Marlow at 2007-12-20T09:52:44+00:00 add an item - - - - - f6ac1708 by Simon Marlow at 2007-12-06T14:00:10+00:00 Source links must point to the original module, not the referring module - - - - - eda1d5c9 by David Waern at 2008-01-06T14:40:52+00:00 Manual merge of a patch to the 0.8 branch Thu Dec 6 15:00:10 CET 2007 Simon Marlow <simonmar at microsoft.com> * Source links must point to the original module, not the referring module - - - - - 378f4085 by David Waern at 2008-01-06T16:03:45+00:00 Change stability from stable to experimental - - - - - 8bdafe44 by David Waern at 2008-01-06T16:14:22+00:00 Add haskell.vim (it had been removed somehow) - - - - - ea34d02e by David Waern at 2008-01-06T16:36:57+00:00 Change version to 2.0.0.0 - - - - - 34631ac0 by David Waern at 2008-01-06T16:44:57+00:00 Add missing modules to the cabal file - - - - - 9e142935 by David Waern at 2008-01-06T17:25:42+00:00 Depend on ghc >= 6.8.2 && < 6.9 - - - - - 59f9eeaa by Simon Marlow at 2007-12-20T10:43:04+00:00 add build scripts - - - - - 1c29ae30 by Simon Marlow at 2007-12-20T10:47:07+00:00 update version number - - - - - fe16a3e4 by Simon Marlow at 2007-12-20T10:48:03+00:00 update version - - - - - f688530f by Simon Marlow at 2007-12-20T10:48:29+00:00 doc updates - - - - - ce71b611 by David Waern at 2008-01-07T13:46:32+00:00 Change version in docs and spec - - - - - 03ab8d6f by David Waern at 2008-01-07T13:47:38+00:00 Manually merge over changes to CHANGES for 0.9 - - - - - 39f1b042 by David Waern at 2008-01-07T15:17:41+00:00 Remove the -use-package flag, we don't support it anyway - - - - - 7274a544 by David Waern at 2008-01-07T15:33:05+00:00 Update CHANGES for 2.0.0.0 - - - - - 96594f5d by David Waern at 2008-01-07T15:46:49+00:00 Wibble - - - - - f4c5a4c4 by David Waern at 2008-01-07T15:55:36+00:00 Change url to repo in documentation - - - - - 8a4c77f0 by David Waern at 2008-01-07T16:00:54+00:00 Update CHANGES - - - - - cb3a9288 by David Waern at 2008-01-07T16:02:55+00:00 Documentation fix - - - - - d8e45539 by David Waern at 2008-01-07T16:12:00+00:00 Update docs to say that Haddock accets .lhs files and module names - - - - - 4b5ce824 by David Waern at 2008-01-07T16:12:25+00:00 Document -B option - - - - - 47274262 by David Waern at 2008-01-07T16:23:07+00:00 Update CHANGES - - - - - 7ff314a9 by David Waern at 2008-01-07T16:23:20+00:00 Remove --use-package, --package & --no-implicit.. flags from docs - - - - - 6c3819c0 by David Waern at 2008-01-07T16:23:52+00:00 Remove --no-implicit-prelide flag - - - - - 1b14ae40 by David Waern at 2008-01-07T16:32:26+00:00 Update the "Using literate or pre-processed source" section - - - - - 0117f620 by David Waern at 2008-01-07T16:41:55+00:00 Document the --optghc flag - - - - - 087ab1cf by David Waern at 2008-01-07T16:42:10+00:00 Remove the documenation section on derived instances The problem mentioned there doesn't exist in Haddock 2.0.0.0 - - - - - 7253951e by David Waern at 2008-01-07T16:48:40+00:00 Document OPTIONS_HADDOCK - - - - - 3b6bdcf6 by David Waern at 2008-01-07T16:56:54+00:00 Wibble - - - - - 3025adf9 by David Waern at 2008-01-07T17:08:14+00:00 Wibble - - - - - 5f30f1a0 by David Waern at 2008-01-07T17:15:44+00:00 Change synopsis field to description - - - - - 1673f54b by David Waern at 2008-01-07T17:18:21+00:00 Change my email address in the cabal file - - - - - 55aa9808 by David Waern at 2008-01-07T18:18:02+00:00 Add documentation for readInterfaceFile - - - - - eaea417f by David Waern at 2008-01-07T18:21:30+00:00 Export necessary stuff from Distribution.Haddock - - - - - 7ea18759 by David Waern at 2008-01-07T18:31:49+00:00 Remove dep on Cabal - - - - - 7b79c74e by David Waern at 2008-01-07T18:33:49+00:00 Remove dep on process - - - - - ce3054e6 by David Waern at 2008-01-16T23:01:21+00:00 Add feature-requsts from Henning Thielemann to TODO - - - - - 0c08f1ec by David Waern at 2008-01-16T23:03:02+00:00 Record a bug in TODO - - - - - b04605f3 by David Waern at 2008-01-23T16:59:06+00:00 Add a bug reported by Ross to TODO - - - - - 5b17c030 by David Waern at 2008-01-23T18:05:53+00:00 A a bug report to TODO - - - - - 1c993b0d by David Waern at 2008-01-25T16:30:25+00:00 Accept test output - - - - - c22fc0d0 by David Waern at 2008-01-25T16:34:49+00:00 Accept test output - - - - - 4b795811 by David Waern at 2008-01-25T16:38:37+00:00 Change Hidden.hs (test) to use OPTIONS_HADDOCK - - - - - c124dbd9 by David Waern at 2008-01-25T16:39:23+00:00 Accept test output - - - - - ec6f6eea by David Waern at 2008-01-25T16:42:08+00:00 Add Hidden.html.ref to tests - - - - - 1dc9610c by David Waern at 2008-02-02T20:50:51+00:00 Add a comment about UNPACK bug in TODO - - - - - 2d3f7081 by David Waern at 2008-02-09T22:33:24+00:00 Change the representation of DocNames Ross Paterson reported a bug where links would point to the defining module instead of the "best" module for an identifier (e.g Int pointing to GHC.Base instead of Data.Int). This patch fixes this problem by refactoring the way renamed names are represented. Instead of representing them by: > data DocName = Link Name | NoLink Name they are now represented as such: > data DocName = Documented Name Module | Undocumented Name and the the link-env looks like this: > type LinkEnv = Map Name Module There are several reasons for this. First of all, the bug was caused by changing the module part of Names during the renaming process, without changing the Unique field. This caused names to be overwritten during the loading of .haddock files (which caches names using the NameCache of the GHC session). So we might create new Uniques during renaming to fix this (but I'm not sure that would be problem-free). Instead, we just keep the Name and add the Module where the name is best documented, since it can be useful to keep the original Name around (for e.g. source-code location info and for users of the Haddock API). Also, the names Link/NoLink don't really make sense, since wether to use links or not is entirely up to the users of DocName. In the process of following this change into H.Backends.Html I removed the assumption that binder names are Undocumented (which was just an unnecessary assumption, the OccName is the only thing needed to render these). This will probably make it possible to get rid of the renamer and replace it with a traversal from SYB or Uniplate. Since DocName has changed, InterfaceFile has changed so this patch also increments the file-format version. No backwards-compatibility is implemented. - - - - - 0f28c921 by David Waern at 2008-02-09T23:00:36+00:00 H.GHC.Utils: remove unused imports/exports - - - - - 0c44cad5 by David Waern at 2008-02-10T00:28:13+00:00 H.GHC.Utils: add some functions that were removed by mistake - - - - - e3452f49 by David Waern at 2008-02-10T00:28:48+00:00 Fix some trivial warnings in H.InterfaceFile - - - - - a6d74644 by David Waern at 2008-02-10T00:48:06+00:00 Update the version message to fit in small terminals - - - - - 76c9cd3e by David Waern at 2008-02-10T14:47:39+00:00 Remove bugs from TODO that don't apply anymore since the port - - - - - 5e10e090 by David Waern at 2008-02-10T15:22:47+00:00 Remove bugs from TODO that weren't actual bugs - - - - - fef70878 by David Waern at 2008-02-10T15:23:44+00:00 Remove yet another item from TODO that was not an actual bug - - - - - e1af47b8 by David Waern at 2008-02-11T10:25:57+00:00 Bump the version number to 2.1.0 Since the exported datatype DocName has changed, we need to bump the major version number. Let's also drop the fourth version component, it's not that useful. - - - - - e3be7825 by David Waern at 2008-04-11T14:29:04+00:00 Add a bug to TODO - - - - - cb6574be by David Waern at 2008-04-11T16:00:45+00:00 Use the in-place haddock when running tests - - - - - c6d7af0d by David Waern at 2008-04-11T16:09:16+00:00 Turn off GHC warnings when running tests - - - - - 7f61b546 by David Waern at 2008-04-11T17:24:00+00:00 Add a flag for turning off all warnings - - - - - 883b8422 by David Waern at 2008-04-12T14:02:18+00:00 Fix printing of data binders - - - - - 2a0db8fc by David Waern at 2008-04-12T18:52:46+00:00 Fix missing parenthesis in constructor args bug - - - - - 1b3ac3f9 by David Waern at 2008-04-12T18:57:23+00:00 Simplify test suite and add tests I move all tests into one single directory to simplify things, and add a test for the last bug that was fixed. - - - - - 8f178376 by David Waern at 2008-04-12T19:00:15+00:00 Add a script for copying test output to "expected" output - - - - - 193e3a03 by David Waern at 2008-04-12T19:16:37+00:00 Remove two fixed bugs from TODO - - - - - ddc9130c by David Waern at 2008-04-12T19:37:06+00:00 Update test README - - - - - 956069c0 by David Waern at 2008-05-01T12:16:14+00:00 Update version number in spec and docs - - - - - 5478621c by David Waern at 2008-05-01T12:28:12+00:00 Remove claim of backwards compatibility from docs for readInterfaceFile - - - - - 4a16dea9 by David Waern at 2008-05-01T12:33:04+00:00 Update CHANGES - - - - - 804216fb by David Waern at 2008-05-01T12:43:16+00:00 Add a synopsis - - - - - fd0c84d5 by David Waern at 2008-05-01T12:44:44+00:00 Add Haddock.DocName to the cabal file - - - - - 9f4a7439 by David Waern at 2008-05-01T12:45:53+00:00 Remove -fglasgow-exts and -fasm - - - - - aee7c145 by David Waern at 2008-05-01T12:54:01+00:00 Add LANGUAGE pragmas to source files - - - - - 9a58428b by David Waern at 2008-05-01T12:54:19+00:00 Add extensions to cabal file - - - - - 494f1bee by David Waern at 2008-05-01T13:12:09+00:00 Export DocName in the API - - - - - c938196b by David Waern at 2008-05-01T13:12:19+00:00 Add hide options to some source files - - - - - 236e86af by Neil Mitchell at 2008-06-07T20:45:10+00:00 Rewrite the --hoogle flag support - - - - - 6d910950 by Neil Mitchell at 2008-06-14T10:56:50+00:00 Simplify the newtype/data outputting in Hoogle, as haddock does it automatically - - - - - f87a95a8 by Neil Mitchell at 2008-06-14T12:10:18+00:00 Add initial structure for outputting documentation as well, but does not yet output anything - - - - - 7c3bce54 by Neil Mitchell at 2008-06-14T12:27:07+00:00 Remove <document comment> from the Hoogle output - - - - - 9504a325 by Neil Mitchell at 2008-06-16T06:33:21+00:00 Default to "main" if there is no package, otherwise will clobber hoogle's hoogle info - - - - - 4a794a79 by Neil Mitchell at 2008-06-16T06:53:29+00:00 Change packageName to packageStr, as it better reflects the information stored in it - - - - - 7abc9baf by Neil Mitchell at 2008-06-16T07:09:49+00:00 Add modulePkgInfo to Haddock.GHC.Utils, which gives back package name and version info - - - - - 8ca11514 by Neil Mitchell at 2008-06-16T07:13:48+00:00 Change Hoogle to take the package name and package version separately - - - - - a6da452d by Neil Mitchell at 2008-06-18T11:29:46+00:00 In Hoogle do not list things that are not local to this module - - - - - 974b76b7 by David Waern at 2008-06-19T18:40:13+00:00 Be more consistent with GHC API naming in H.GHC.Utils - - - - - 2facb4eb by David Waern at 2008-06-19T19:03:03+00:00 Update test output - - - - - c501de72 by David Waern at 2008-06-26T20:26:49+00:00 Use ghc-paths to get the lib dir The path can still be overridden using the -B flag. It's not longer required to pass the lib dir to the program that runs the test suite. - - - - - ac4c6836 by David Waern at 2008-06-26T20:33:08+00:00 Update CHANGES - - - - - 9d21c60a by David Waern at 2008-06-26T20:34:53+00:00 Update README - - - - - 741448f0 by David Waern at 2008-06-26T21:12:57+00:00 Improve wording in the help message - - - - - b1b42b11 by David Waern at 2008-06-30T10:16:17+00:00 Rename ForeignType - - - - - 6d6c2b34 by David Waern at 2008-06-30T10:25:09+00:00 Rename TyFamily - - - - - 8d1125ed by David Waern at 2008-06-30T10:37:21+00:00 Rename type patterns - - - - - 7610a4cb by David Waern at 2008-06-30T10:45:07+00:00 Rename associated types - - - - - 8eeba14c by David Waern at 2008-06-30T10:47:41+00:00 Remove the TODO file now that we have a trac - - - - - 1af5b25b by David Waern at 2008-07-02T18:19:28+00:00 Render type family declarations (untested) - - - - - ceb99797 by David Waern at 2008-07-02T18:24:06+00:00 Remove redundant check for summary when rendering data types - - - - - b36a58e0 by David Waern at 2008-07-02T22:01:38+00:00 More support for type families and associated types Now we just need to render the instances - - - - - 78784879 by David Waern at 2008-07-07T22:13:58+00:00 Remove filtering of instances We were filtering out all instances for types with unknown names. This was probably an attempt to filter out instances for internal types. I am removing the filtering for the moment, and will try to fix this properly later. - - - - - 3e758dad by David Waern at 2008-06-30T18:50:30+00:00 Run haddock in-place during testing - - - - - d9dab0ce by David Waern at 2008-07-08T21:04:32+00:00 Remove index.html and doc-index.html from output, they should not be versioned - - - - - 3e6c4681 by David Waern at 2008-07-08T21:06:42+00:00 Update test output following change to instance filtering - - - - - e34a3f14 by David Waern at 2008-07-12T16:48:28+00:00 Stop using the map from exported names to declarations During creation of the interface, we were using two maps: one from exported names to declarations, and one from all defined names in the module to declarations. The first contained subordinate names while the second one didn't. The first map was never used to look up names not defined in the associated module, so if we add subordinate names to the second map, we could use it everywhere. That's that this patch does. This simplifies code because we don't have to pass around two maps everywhere. We now store the map from locally defined things in the interface structure instead of the one from exported names. - - - - - 2e1d2766 by David Waern at 2008-07-12T16:55:21+00:00 Get the all locally defined names from GHC API We previously had some code to compute all locally defined names in a module including subordinate names. We don't need it since we can get the names from modInfoTyThings in the GHC API. - - - - - bf637994 by David Waern at 2008-07-13T13:09:16+00:00 Refactoring in H.Interface.Create We were creating a doc map, a declaration map and a list of entities separately by going through the HsGroup. These structures were all used to build the interface of a module. Instead of doing this, we can start by creating a list of declarations from the HsGroup, then collect the docs directly from this list (instead of using the list of entities), creating a documentation map. We no longer need the Entity data type, and we can store a single map from names to declarations and docs in the interface, instead of the declaration map and the doc map. This way, there is only one place where we filter out the declarations that we don't want, and we can remove a lot of code. Another advantage of this is that we can create the exports directly out of the list of declarations when we export the full module contents. (Previously we did a look up for each name to find the declarations). This is faster and removes another point where we depend on names to identify exported declarations, which is good because it eliminates problems with instances (which don't have names). - - - - - 547e410e by David Waern at 2008-07-13T13:34:51+00:00 Remove FastString import and FSLIT macro in H.I.Create -- they were unused - - - - - 693759d1 by David Waern at 2008-07-13T13:36:23+00:00 Remove unused import from H.I.Create - - - - - cde6e7fb by David Waern at 2008-07-13T13:51:54+00:00 Small touches - - - - - 96de8f1d by David Waern at 2008-07-20T11:21:46+00:00 Preparation for rendering instances as separate declarations We want to be able to render instances as separate declarations. So we remove the Name argument of ExportDecl, since instances are nameless. This patch also contains the first steps needed to gather type family instances and display them in the backend, but the implementation is far from complete. Because of this, we don't actually show the instances yet. - - - - - b0f824fb by David Waern at 2008-07-20T15:53:08+00:00 Follow changes to ExportDecl in Hoogle - - - - - 1192eff3 by Neil Mitchell at 2008-06-26T00:28:10+00:00 Change how the Hoogle backend outputs classes, adding the context in - - - - - 7a0d1464 by Neil Mitchell at 2008-06-26T00:28:46+00:00 Remove the indent utility function from Hoogle backend - - - - - 3361241b by Neil Mitchell at 2008-06-26T09:45:09+00:00 Add support for Hoogle writing ForeignImport/ForeignExport properly - - - - - 795ad3bf by Neil Mitchell at 2008-06-26T12:15:25+00:00 Flesh out the Hoogle code to render documentation - - - - - 23277995 by Neil Mitchell at 2008-06-26T14:56:41+00:00 Fix a bug in the Hoogle backend, unordered lists were being written out <ul>...</u> - - - - - db739b27 by Neil Mitchell at 2008-06-26T15:09:54+00:00 Remove any white space around a <li> element - - - - - f2e6bb8c by Neil Mitchell at 2008-07-10T15:30:47+00:00 Remove the TODO in the Hoogle HTML generation, was already done - - - - - 693ec9a3 by Neil Mitchell at 2008-07-10T15:53:00+00:00 Put brackets round operators in more places in the Hoogle output - - - - - 842313aa by Neil Mitchell at 2008-07-10T16:01:25+00:00 Print type signatures with brackets around the name - - - - - cf93deb0 by David Waern at 2008-07-20T17:04:22+00:00 Bump version number to 2.2.0 - - - - - 30e6a8d1 by David Waern at 2008-07-20T17:04:41+00:00 Resolve conflicts in H.B.Hoogle - - - - - 1f0071c9 by David Waern at 2008-07-23T23:05:01+00:00 Add "all" command to runtests.hs that runs all tests despite failures - - - - - f2723023 by David Waern at 2008-07-23T23:08:39+00:00 Update tests/README - - - - - c0304a11 by David Waern at 2008-07-23T23:21:15+00:00 Be compatible with GHC 6.8.3 The cabal file is converted to use the "new" syntax with explicit Library and Executable sections. We define the __GHC_PATCHLEVEL__ symbol using a conditinal cpp-options field in the cabal file. (Ideally, Cabal would define the symbol for us, like it does for __GLASGOW_HASKELL__). We use these symbols to #ifdef around a small difference between 6.8.2 and 6.8.3. Previously, we only supported GHC 6.8.2 officially but the dependencies field said "ghc <= 6.9". This was just for convenience when testing against the (then compatible) HEAD version of GHC, and was left in the release by mistake. Now, we support both GHC 6.8.2 and 6.8.3 and the dependencies field correctly reflects this. - - - - - 88a5fe71 by David Waern at 2008-07-23T23:54:16+00:00 Depend on the currently available ghc-paths versions only - - - - - 8738d97b by David Waern at 2008-07-24T10:50:44+00:00 FIX haskell/haddock#44: Propagate parenthesis level when printing documented types - - - - - 05339119 by David Waern at 2008-07-24T16:06:18+00:00 Drop unnecessary parenthesis in types, put in by the user We were putting in parenthesis were the user did. Let's remove this since it just clutters up the types. The types are readable anyway since we print parens around infix operators and do not rely on fixity levels. When doing this I discovered that we were relying on user parenthesis when printin types like (a `O` b) c. This patchs fixes this problem so that parenthesis are always inserted around an infix op application in case it is applied to further arguments, or if it's an arguments to a type constructor. Tests are updated. - - - - - b3a99828 by David Waern at 2008-07-24T10:19:43+00:00 Print parenthesis around non-atomic banged types Fixes half of haskell/haddock#44 - - - - - ab5238e0 by David Waern at 2008-07-24T22:07:49+00:00 Add a reference file for the TypeFamilies test - - - - - 1941cc11 by David Waern at 2008-07-25T17:15:53+00:00 Simplify definition of pretty and trace_ppr - - - - - e3bfa33c by David Waern at 2008-07-25T17:18:27+00:00 Warning messages Output a warning when filtering out data/type instances and associated types in instances. We don't show these in the documentation yet, and we need to let the user know. - - - - - 9b85fc89 by David Waern at 2008-07-25T17:45:40+00:00 Doc: Mention Hoogle in the Introduction - - - - - afb2dd60 by David Waern at 2008-07-25T17:49:00+00:00 Doc: update -B description - - - - - 584c0c91 by David Waern at 2008-07-25T18:11:38+00:00 Doc: describe -w flag - - - - - 77619c24 by David Waern at 2008-07-28T12:29:07+00:00 Remove TODO from cabal file - - - - - 96717d5f by David Waern at 2008-07-28T12:29:27+00:00 Support type equality predicates - - - - - c2fd2330 by David Waern at 2008-07-29T19:45:14+00:00 Move unL from H.B.Hoogle to H.GHC.Utils I like Neil's shorter unL better than unLoc from the GHC API. - - - - - c4c3bf6a by David Waern at 2008-07-29T19:47:36+00:00 Do not export ATs when not in list of subitems - - - - - bf9a7b85 by David Waern at 2008-08-03T11:42:59+00:00 Filter out ForeignExports - - - - - df59fcb0 by David Waern at 2008-08-03T14:02:51+00:00 Filter out more declarations The previous refactorings in H.I.Create introduced a few bugs. Filtering of some types of declarations that we don't handle was removed. This patch fixes this. - - - - - 2f8a958b by David Waern at 2008-08-03T15:24:07+00:00 Move reL to H.GHC.Utils so we can use it everywhere - - - - - 8ec15efd by David Waern at 2008-08-03T15:25:00+00:00 Use isVanillaLSig from GHC API instead of home brewn function - - - - - 300f93a2 by David Waern at 2008-08-03T15:25:27+00:00 Filter out separately exported ATs This is a quick and dirty hack to get rid of separately exported ATs. We haven't decided how to handle them yet. No warning message is given. - - - - - 8776d1ec by David Waern at 2008-08-03T16:21:21+00:00 Filter out more declarations and keep only vanilla type sigs in classes - - - - - ea07eada by David Waern at 2008-08-03T16:48:00+00:00 Fix layout - - - - - dd5e8199 by David Waern at 2008-08-03T16:50:52+00:00 Move some utility functions from H.I.Create to H.GHC.Utils - - - - - 4a1dbd72 by David Waern at 2008-08-03T17:39:55+00:00 Do not filter out doc declarations - - - - - 0bc8dca4 by David Waern at 2008-08-03T17:47:26+00:00 Filter out separately exported ATs (take two) - - - - - af970fe8 by David Waern at 2008-08-03T22:39:17+00:00 Update CHANGES - - - - - 5436ad24 by David Waern at 2008-08-03T22:40:20+00:00 Bump version number to 2.2.1 - - - - - d66de448 by David Waern at 2008-08-05T19:00:32+00:00 Remove version restriction on ghc-paths - - - - - 534b1364 by David Waern at 2008-08-05T19:04:35+00:00 Bump version to 2.2.2 and update CHANGES - - - - - 549188ff by David Waern at 2008-08-05T19:16:49+00:00 Fix CHANGES - - - - - 0d156bb4 by Luke Plant at 2008-08-11T15:20:59+00:00 invoking haddock clarification and help - - - - - 748295cc by David Waern at 2008-08-11T18:56:37+00:00 Doc: say that the --hoogle option is functional - - - - - 43301db4 by David Waern at 2008-08-05T19:26:08+00:00 Change ghc version dependency to >= 6.8.2 - - - - - 3e5a53b6 by David Waern at 2008-08-10T22:42:05+00:00 Make H.GHC.Utils build with GHC HEAD - - - - - 7568ace0 by David Waern at 2008-08-11T19:41:54+00:00 Import Control.OldException instead of C.Exception when using ghc >= 6.9 We should really test for base version instead, but I don't currently know which version to test for. - - - - - b71ae991 by David Waern at 2008-08-12T22:40:39+00:00 Make our .haddock file version number depend on the GHC version We need to do this, since our .haddock format can potentially change whenever GHC's version changes (even when only the patchlevel changes). - - - - - 6307ce3f by David Waern at 2008-08-12T22:49:57+00:00 Remove matching on NoteTy in AttachInstances, it has been removed - - - - - 2dbcfd5f by David Waern at 2008-08-12T23:02:02+00:00 Comment out H.GHC.loadPackages - it is unused and doesn't build with ghc >= 6.9 - - - - - c74db5c2 by David Waern at 2008-08-12T23:03:58+00:00 Hide <.> from GHC import in Hoogle only for ghc <= 6.8.3 - - - - - 69a44ebb by David Waern at 2008-08-12T23:11:12+00:00 Follow changes to parseDynamic/StaticFlags - - - - - 5881f3f0 by David Waern at 2008-08-13T21:43:58+00:00 Add __GHC_PATCHLEVEL__ symbol also when building the library - - - - - 8574dc11 by David Waern at 2008-08-13T21:44:17+00:00 Follow move of package string functions from PackageConfig to Module - - - - - c9baa77f by David Waern at 2008-08-13T21:45:29+00:00 Follow extensible exceptions changes - - - - - 9092de15 by David Waern at 2008-08-13T21:46:20+00:00 Update test following Haddock version change - - - - - ebe569a4 by David Waern at 2008-08-13T21:46:54+00:00 Follow changes to parseDynamic- parseStaticFlags in GHC - - - - - b8a5ffd3 by David Waern at 2008-08-13T21:47:36+00:00 Follow changes to Binary in GHC 6.9 - - - - - edfda1cc by David Waern at 2008-08-13T21:50:17+00:00 Change ghc version dependency to >= 6.8.2 && <= 6.9 - - - - - d59be1cf by Neil Mitchell at 2008-08-12T16:02:53+00:00 Output all items, even if they are not defined in this module - ensures map comes from Prelude, not just GHC.Base - - - - - dda93b9f by Neil Mitchell at 2008-08-12T21:37:32+00:00 Add support for type synonyms to Hoogle, was accidentally missing before (woops!) - - - - - b6ee795c by Neil Mitchell at 2008-08-13T14:03:24+00:00 Generalise Hoogle.doc and add a docWith - - - - - 415e1bb2 by Neil Mitchell at 2008-08-13T14:03:46+00:00 Make Hoogle add documentation to a package - - - - - 790a1202 by Neil Mitchell at 2008-08-18T12:52:43+00:00 Use the same method to put out signatures as class methods in the Hoogle backend - - - - - ded37eba by Neil Mitchell at 2008-08-18T12:53:04+00:00 Remove Explicit top-level forall's when pretty-printing signatures - - - - - 6468c722 by Neil Mitchell at 2008-08-20T07:59:13+00:00 Simplify the code by removing not-to-important use of <.> in the Hoogle back end - - - - - 788c3a8b by Neil Mitchell at 2008-08-21T18:20:24+00:00 In the hoogle back end, markup definition lists using <i>, not <b> - - - - - 77d4b000 by Ian Lynagh at 2008-08-14T10:49:14+00:00 Add a Makefile for GHC's build system. Still won't work yet, but we're closer - - - - - 920440d7 by Ian Lynagh at 2008-08-27T18:06:46+00:00 Add haddock.wrapper - - - - - bcda925f by Ian Lynagh at 2008-08-27T18:07:02+00:00 Add a manual Cabal flag to control the ghc-paths dependency - - - - - 04d194e2 by Ian Lynagh at 2008-08-27T20:41:27+00:00 Update extensions in Cabal file Use ScopedTypeVariables instead of PatternSignatures - - - - - 12480043 by Ian Lynagh at 2008-08-27T20:41:55+00:00 Increase the upper bound on the GHC version number - - - - - b1f809a5 by Ian Lynagh at 2008-08-27T21:32:22+00:00 Fix some warnings - - - - - aea0453d by Ian Lynagh at 2008-08-28T14:22:29+00:00 Fixes for using haddock in a GHC build tree - - - - - ad23bf86 by Ian Lynagh at 2008-08-28T21:14:27+00:00 Don't use Cabal wrappers on Windows - - - - - 35858e4c by Ian Lynagh at 2008-08-29T00:07:42+00:00 Fix in-tree haddock on Windows - - - - - c2642066 by Ian Lynagh at 2008-09-03T22:35:53+00:00 follow library changes - - - - - 2eb55d50 by Ian Lynagh at 2008-09-07T18:52:51+00:00 bindist fixes - - - - - 3daa5b59 by Ian Lynagh at 2008-09-10T16:58:18+00:00 We need to tell haddock that its datasubdir is . or it can't find package.conf - - - - - 388fd8c2 by Ian Lynagh at 2008-09-10T19:47:44+00:00 Fix haddock inplace on Windows - - - - - 70a641c1 by Ian Lynagh at 2008-09-10T22:15:44+00:00 Fix installed haddock on Windows - - - - - 83c1e997 by Neil Mitchell at 2008-09-11T10:48:55+00:00 Import GHC.Paths if not IN_GHC_TREE, seems to match the use of GHC.Paths functions much better - - - - - b452519b by Ian Lynagh at 2008-09-12T12:58:24+00:00 Add a LANGUAGE ForeignFunctionInterface pragma - - - - - afbd592c by Ian Lynagh at 2008-09-12T12:59:13+00:00 Wibble imports - - - - - 547ac4ad by Ian Lynagh at 2008-09-14T15:34:22+00:00 Add a "#!/bin/sh" to haddock.wrapper - - - - - f207a807 by Ian Lynagh at 2008-09-15T10:02:32+00:00 Use "exec" when calling haddock in the wrapper - - - - - 2ee68509 by Thomas Schilling at 2008-09-15T09:09:16+00:00 Port Haddock.Interface to new GHC API. This required one bigger change: 'readInterfaceFile' used to take an optional 'Session' argument. This was used to optionally update the name cache of an existing GHC session. This does not work with the new GHC API, because an active session requires the function to return a 'GhcMonad' action, but this is not possible if no session is provided. The solution is to use an argument of functions for reading and updating the name cache and to make the function work for any monad that embeds IO, so it's result type can adapt to the calling context. While refactoring, I tried to make the code a little more self-documenting, mostly turning comments into function names. - - - - - 3bb96431 by Thomas Schilling at 2008-09-15T09:09:37+00:00 Reflect GHC API changes. - - - - - 2e60f714 by Thomas Schilling at 2008-09-15T09:10:37+00:00 Port Haddock.GHC.Typecheck to new GHC API. - - - - - 9cfd4cff by Thomas Schilling at 2008-09-15T09:11:00+00:00 Port Haddock.GHC to new GHC API. - - - - - caffa003 by Thomas Schilling at 2008-09-15T09:11:25+00:00 Port Main to new GHC API. - - - - - 069a4608 by Ian Lynagh at 2008-09-21T11:19:00+00:00 Fix paths used on Windows frmo a GHC tree: There is no whare directory - - - - - 7ceee1f7 by Ian Lynagh at 2008-09-21T12:20:16+00:00 Fix the in-tree haddock on Windows - - - - - 0d486514 by Ian Lynagh at 2008-09-23T18:06:58+00:00 Increase the GHC upper bound from 6.11 to 6.13 - - - - - f092c414 by Neil Mitchell at 2008-09-11T14:56:07+00:00 Do not wrap __ in brackets - - - - - 036bdd13 by Ian Lynagh at 2008-09-28T01:42:35+00:00 Fix building haddock when GhcProfiled=YES - - - - - 01434a89 by David Waern at 2008-09-24T20:24:21+00:00 Add PatternSignatures LANGUAGE pragma to Main and Utils - - - - - 1671a750 by David Waern at 2008-10-02T22:57:25+00:00 For source links, get original module from declaration name instead of environment. Getting it from the environment must have been a remnant from the times when we were using unqualified names (versions 0.x). - - - - - a25dde99 by David Waern at 2008-10-02T22:59:57+00:00 Remove ifaceEnv from Interface - it's no longer used - - - - - 610993da by David Waern at 2008-10-02T23:04:58+00:00 Write a comment about source links for type instance declarations - - - - - 5a96b5d5 by Thomas Schilling at 2008-10-03T10:45:08+00:00 Follow GHC API change of parseModule. - - - - - 5a943ae5 by Ian Lynagh at 2008-10-03T15:56:58+00:00 TAG 2008-10-03 - - - - - 76cdd6ae by Thomas Schilling at 2008-10-08T12:29:50+00:00 Only load modules once when typechecking with GHC. This still doesn't fix the memory leak since the typechecked source is retained and then processed separately. To fix the leak, modules must be processed directly after typechecking. - - - - - 7074d251 by David Waern at 2008-10-09T23:53:54+00:00 Interleave typechecking with interface creation At the same time, we fix a bug where the list of interfaces were processed in the wrong order, when building the links and renaming the interfaces. - - - - - 4b9b2b2d by David Waern at 2008-10-09T23:54:49+00:00 Add some strictness annotations in Interface We add some strictness annotations to the fields of Interface, so that less GHC data is hold on to during processing. - - - - - 22035628 by David Waern at 2008-10-10T20:02:31+00:00 Remove typecheckFiles and MonadUtils import from H.GHC.Typeccheck - - - - - be637ad3 by David Waern at 2008-10-10T20:33:38+00:00 Make Haddock build with GHC 6.8.2 - - - - - 523b3404 by David Waern at 2008-10-10T21:08:09+00:00 Fix documentation for createInterfaces - - - - - e1556702 by David Waern at 2008-10-10T21:26:19+00:00 Hide H.Utils in library - - - - - a8e751c3 by David Waern at 2008-10-10T21:34:59+00:00 Add back .haddock file versioning based on GHC version It was accidentally removed in the patch for GHC 6.8.2 compatibility - - - - - 06fb3c01 by David Waern at 2008-10-10T21:47:15+00:00 Bump version number to 2.3.0 - - - - - ff087fce by David Waern at 2008-10-10T22:35:49+00:00 Add support for DocPic The support for DocPic was merged into the GHC source long ago, but the support in Haddock was forgotten. Thanks Peter Gavin for submitting this fix! - - - - - 3af85bf6 by David Waern at 2008-10-10T23:34:05+00:00 Update tests - - - - - 0966873c by Simon Marlow at 2008-10-10T14:43:04+00:00 no need for handleErrMsg now, we don't throw any ErrMsgs - - - - - f1870de3 by Clemens Fruhwirth at 2008-10-10T13:29:36+00:00 Compile with wrapper but remove it for dist-install - - - - - 7b440dc2 by David Waern at 2008-10-11T14:02:25+00:00 Remove interface from LinksInfo It was there to know the documentation home module when creating a wiki link, but we already know this since we have the DocName. - - - - - e5729e6a by David Waern at 2008-10-15T20:49:18+00:00 Wibble - - - - - b2a8e01a by David Waern at 2008-10-15T21:03:36+00:00 Use type synonyms for declarations and docs in H.I.Create - - - - - be71a15b by David Waern at 2008-10-15T21:12:17+00:00 Comment out unused type family stuff completely - - - - - 91aaf075 by David Waern at 2008-10-15T21:49:04+00:00 Wibble - - - - - 42ba4eb4 by David Waern at 2008-10-15T21:53:53+00:00 Move convenient type synonym to H.Types - - - - - db11b723 by David Waern at 2008-10-15T22:14:07+00:00 Add DeclInfo to H.Types - - - - - 193552b6 by David Waern at 2008-10-15T22:15:01+00:00 Add subordinates with docs to the declaration map The only place in the code where we want the subordinates for a declaration is right after having looked up the declaration in the map. And since we include subordinates in the map, we might as well take the opportunity to store those subordinates that belong to a particular declaration together with that declaration. We also store the documentation for each subordinate. - - - - - 31e6eebc by David Waern at 2008-10-16T17:18:47+00:00 Wibble - - - - - 0dcbd79f by David Waern at 2008-10-16T20:58:42+00:00 Fix haskell/haddock#61 We were not getting docs for re-exported class methods. This was because we were looking up the docs in a map made from the declarations in the current module being rendered. Obviously, re-exported class methods come from another module. Class methods and ATs were the only thing we were looking up using the doc map, everything else we found in the ExporItems. So now I've put subordinate docs in the ExportItem's directly, to make things a bit more consistent. To do this, I added subordinates to the the declarations in the declaration map. This was easy since we were computing subordinates anyway, to store stand-alone in the map. I added a new type synonym 'DeclInfo', which is what we call what is now stored in the map. This little refactoring removes duplicate code to retrieve subordinates and documentation from the HsGroup. - - - - - de47f20a by David Waern at 2008-10-16T22:06:35+00:00 Document function and improve its layout - - - - - e74e625a by Thomas Schilling at 2008-10-20T11:12:57+00:00 Force interface more aggressively. For running Haddock on GHC this reduces memory usage by about 50 MB on a 32 bit system. A heap profile shows total memory usage peak at about 100 MB, but actual usage is at around 300 MB even with compacting GC (+RTS -c). - - - - - b63ac9a1 by David Waern at 2008-10-20T20:25:50+00:00 Make renamer consistent Instead of explicitly making some binders Undocumented, treat all names the same way (that is, try to find a Documented name). - - - - - f6de0bb0 by Ian Lynagh at 2008-09-19T00:54:43+00:00 TAG GHC 6.10 fork - - - - - 74599cd0 by David Waern at 2008-10-20T21:13:24+00:00 Do not save hidden modules in the .haddock file We were saving interfaces of all processed modules including those hidden using {-# OPTIONS_HADDOCK hide #-} in the .haddock file. This caused broken links when generating the index for the libraries that come with GHC. This patch excludes modules with hidden documentation when writing .haddock files. It should fix the above problem. - - - - - 7b6742e9 by David Waern at 2008-10-21T19:54:52+00:00 Do not save hidden modules in the .haddock file (also for ghc >= 6.9) When writing the first patch, I forgot to do the fix in both branches of an #if macro. - - - - - b99b1951 by David Waern at 2008-10-22T20:04:18+00:00 Remove subordinate map and its usage It is not needed now that we store subordinate names in the DeclInfo map. - - - - - da97cddc by David Waern at 2008-10-22T20:11:46+00:00 Tidy up code in H.I.Create a little Remove commented out half-done type instance support, and remove DeclWithDoc synonym. - - - - - 6afa76f3 by David Waern at 2008-10-22T21:17:29+00:00 Fix warnings in H.GHC.Utils - - - - - 171ea1e8 by David Waern at 2008-10-22T21:35:04+00:00 Fix warnings in H.Utils - - - - - c8cb3b91 by David Waern at 2008-10-22T21:36:49+00:00 Wibble - - - - - 767fa06a by David Waern at 2008-10-27T19:59:04+00:00 Make named doc comments into ExportDoc instead of ExportDecl Fixes a crash when processing modules without export lists containing named docs. - - - - - e638bbc6 by David Waern at 2008-11-02T22:21:10+00:00 Add HCAR entry - - - - - 92b4ffcf by David Waern at 2008-11-02T22:44:19+00:00 Update CHANGES - - - - - 84d4da6e by David Waern at 2008-11-03T11:25:04+00:00 Add failing test for template haskell crash - - - - - 2a9cd2b1 by David Waern at 2008-11-04T21:13:44+00:00 Add tests/TH.hs - - - - - 8a59348e by David Waern at 2008-11-04T21:30:26+00:00 TAG 2.3.0 - - - - - 54f70d31 by Thomas Schilling at 2008-10-24T17:04:08+00:00 Enable framed view of the HTML documentation. This patch introduces: - A page that displays the documentation in a framed view. The left side will show a full module index. Clicking a module name will show it in the right frame. If Javascript is enabled, the left side is split again to show the modules at the top and a very short synopsis for the module currently displayed on the right. - Code to generate the mini-synopsis for each module and the mini module index ("index-frames.html"). - CSS rules for the mini-synopsis. - A very small amount of javascript to update the mini-synopsis (but only if inside a frame.) Some perhaps controversial things: - Sharing code was very difficult, so there is a small amount of code duplication. - The amount of generated pages has been doubled, since every module now also gets a mini-synopsis. The overhead should not be too much, but I haven't checked. Alternatively, the mini-synopsis could also be generated using Javascript if we properly annotate the actual synopsis. - - - - - 5d7ea5a6 by David Waern at 2008-11-04T23:20:17+00:00 Follow change to ExportDecl in frames code - - - - - 60e16308 by David Waern at 2008-11-04T23:35:26+00:00 Update CHANGES - - - - - d63fd26d by David Waern at 2008-11-04T23:37:43+00:00 Bump version number - - - - - c1660c39 by David Waern at 2008-11-04T23:44:46+00:00 Update CHANGES - - - - - 995ab384 by David Waern at 2008-11-04T23:55:21+00:00 Remove .ref files from tests/output/ - - - - - 1abbbe75 by David Waern at 2008-11-04T23:57:41+00:00 Output version info before running tests - - - - - 649b182f by David Waern at 2008-11-05T22:45:37+00:00 Add ANNOUNCE message - - - - - c36ae0bb by David Waern at 2008-11-05T23:15:35+00:00 Update ANNOUNCE - - - - - 9c4f3d40 by David Waern at 2008-11-05T23:18:30+00:00 Wibble - - - - - 5aac87ce by David Waern at 2008-11-06T21:07:48+00:00 Depend on base 4.* when using GHC >= 6.9, otherwise 3.* - - - - - b9796a74 by David Waern at 2008-11-06T21:13:40+00:00 Bump version to 2.4.1 and update CHANGES - - - - - d4b26baa by David Waern at 2008-11-06T21:26:33+00:00 Depend on base 4.0.* instead of 4.* - - - - - 2cb0903c by David Waern at 2008-11-06T21:46:53+00:00 Fix warnings in H.B.HH and H.B.HH2 - - - - - e568e89a by David Waern at 2008-11-06T21:47:12+00:00 Fix warnings in Haddock.ModuleTree - - - - - 9dc14fbd by David Waern at 2008-11-06T21:47:52+00:00 Fix warnings in Haddock.Version - - - - - 02ac197c by David Waern at 2008-11-06T21:51:31+00:00 Fix warnings in H.InterfaceFile and H.Options - - - - - 63e7439a by David Waern at 2008-11-06T21:59:45+00:00 Fix warnings in H.GHC.Typecheck - - - - - 4bca5b68 by David Waern at 2008-11-08T13:43:42+00:00 Set HscTarget to HscNothing instead of HscAsm There used to be a bug in the GHC API that prevented us from setting this value. - - - - - 07357aec by David Waern at 2008-11-09T22:27:00+00:00 Re-export NameCache and friends from Distribution.Haddock - - - - - ea554b5a by David Waern at 2008-11-09T23:14:10+00:00 Add Haddock.GHC.Utils to other-modules in library - - - - - 74aecfd7 by David Waern at 2008-11-10T01:18:57+00:00 Export DocName in the library - - - - - 241a58b3 by David Waern at 2008-11-10T01:19:18+00:00 Document the functions in H.DocName - - - - - edc2ef1b by David Waern at 2008-11-10T01:20:52+00:00 Export H.DocName in the library - - - - - 4f588d55 by David Waern at 2008-11-10T01:29:14+00:00 Make DocName an instance of NamedThing - - - - - b4647244 by David Waern at 2008-11-15T22:58:18+00:00 Reflect version bump in test suite - - - - - 4bee8ce2 by David Waern at 2008-11-15T22:58:45+00:00 Update tests For unknown reasons, test output for Bug1 and Test has changed for the better. - - - - - 1690e2f9 by David Waern at 2008-11-15T22:59:33+00:00 Store hidden modules in .haddock files We store documentation for an entity in the 'InstalledInterface' of the definition site module, and never in the same structure for a module which re-exports the entity. So when a client of the Haddock library wants to look up some documentation, he/she might need to access a hidden module. But we currently don't store hidden modules in the .haddock files. So we add the hidden modules and the Haddock options to the .haddock files. The options will be used to filter the module list to obtain the visible modules only, which is necessary for generating the contents and index for installed packages. - - - - - 8add6435 by David Waern at 2008-11-16T14:35:50+00:00 Bump major version number due to .haddock file format change - - - - - 48bfcf82 by David Waern at 2008-11-23T14:32:52+00:00 Update tests to account for version number bump - - - - - 0bbd1738 by David Waern at 2008-11-23T14:33:31+00:00 HADDOCK_DATA_DIR changed to haddock_datadir - - - - - 5088b78c by David Waern at 2008-11-23T17:13:21+00:00 FIX haskell/haddock#45: generate two anchors for each name We generate two anchor tags for each name, one where we don't escape the name and one where we URI-encode it. This is for compatibility between IE and Opera. Test output is updated. - - - - - 5ee5ca3b by Neil Mitchell at 2008-11-27T14:38:11+00:00 Drop HsDocTy annotations, they mess up pretty printing and also have a bracketing bug (#2584) - - - - - 51c014e9 by Roman Cheplyaka at 2008-11-27T22:27:36+00:00 Allow referring to a specific section within a module in a module link Fixes haskell/haddock#65 - - - - - 4094bdc5 by David Waern at 2008-11-28T21:13:33+00:00 Update tests following anchor change - - - - - f89552dd by Thomas Schilling at 2008-11-29T16:16:20+00:00 Haddock really shouldn't try to overwrite files. - - - - - 98127499 by David Waern at 2008-12-07T14:09:15+00:00 Solve conflict - - - - - 319356c5 by David Waern at 2008-10-22T21:16:55+00:00 Add -Wall -Werror to ghc-options - - - - - 3c4968c9 by David Waern at 2008-11-04T23:38:56+00:00 TAG 2.4.0 - - - - - 4b21e003 by David Waern at 2008-11-06T21:14:04+00:00 TAG 2.4.1 - - - - - 8e0cad5c by David Waern at 2008-12-07T14:12:54+00:00 Remove -Werror - - - - - 299d6deb by David Waern at 2008-12-07T14:25:18+00:00 Remove -Wall, we'll focus on warnings after 6.10.2 is out - - - - - 5f4216b6 by David Waern at 2008-12-07T20:58:05+00:00 Resolve conflict properly - - - - - 67d774e7 by Neil Mitchell at 2008-12-15T11:44:26+00:00 Make forall's in constructors explicit, i.e. data Foo = Foo {foo :: Eq a => a} - - - - - 61851792 by Neil Mitchell at 2008-12-18T15:39:39+00:00 Try and find a better package name than "main" for Hoogle, goes wrong when working on an executable rather than a library - - - - - 2fab8554 by David Waern at 2008-12-08T23:19:48+00:00 Make visible names from ExportItems Instead of a complicated calculation of visible names out of GHC's export items, we can get them straight out of the already calculated ExportItems. The ExportItems should represent exactly those items that are visible in an interface. If store all the exported sub-names in ExportDecl instead of only those with documentation, the calculation becomes very simple. So we do this change as well (should perhaps have been a separate patch). This should fix the problem with names from ghc-prim not appearing in the link environment. - - - - - 7caadd8c by Ian Lynagh at 2008-12-11T17:01:04+00:00 Wrap the GHC usage with defaultCleanupHandler This fixes a bug where haddock leaves /tmp/ghc* directories uncleaned. - - - - - 7c9fc9a5 by David Waern at 2009-01-02T21:38:27+00:00 Show re-exported names from external packages again This fixes GHC ticket 2746. In order to also link to the exported subordinate names of a declaration, we need to re-introduce the sub map in the .haddock files. - - - - - 119e4e05 by David Waern at 2009-01-06T23:34:17+00:00 Do not process boot modules We should of course not try to produce documentation for boot modules! The reason this has worked in the past is that the output of "real" modules overwrites the output of boot modules later in the process. However, this causes a subtle link environment problem. So let's get rid of this stupid behaviour. We avoid processing boot modules, but we continue to typecheck them. - - - - - c285b9d2 by David Waern at 2009-01-08T18:03:36+00:00 Export modules also when coming from external packages This seems to have regressed since a refactoring that was part of the 2.3.0 release. - - - - - 24031c17 by David Waern at 2009-01-10T15:26:26+00:00 Change version to 2.4.2 - no need to go to 2.5.0 - - - - - 864d1c3f by David Waern at 2009-01-10T15:35:20+00:00 Update tests to account for version number change - - - - - 524ba886 by David Waern at 2009-01-10T18:29:17+00:00 Add test for Template Haskell splicing - - - - - 05e6e003 by David Waern at 2009-01-10T19:35:42+00:00 Fix Trac haskell/haddock#68: Turn on compilation via C for Template Haskell packages We can't use HscNothing if we need to run code coming from modules inside the processed package during typechecking, which is the case for some packages using Template Haskell. This could be improved, to e.g. use HscInterpreted and HscNothing where possible, instead of using HscC for all modules in the package. - - - - - 2b2bafa1 by David Waern at 2009-01-10T20:22:25+00:00 Only use needsTemplateHaskell when compiling with GHC 6.10.2 or above - - - - - bedc3a93 by Ian Lynagh at 2009-01-11T14:58:41+00:00 Fix the location of INPLACE_PKG_CONF; fixes the build Spotted by Conal Elliott - - - - - 943107c8 by David Waern at 2009-01-20T19:27:39+00:00 Document H.I.Create.collectDocs better - - - - - c6252e37 by David Waern at 2009-01-20T19:29:51+00:00 Fix Trac haskell/haddock#59: TH-generated declarations disappearing This patch was contributed by Joachim Breitner (nomeata). - - - - - 3568a6af by David Waern at 2009-01-21T21:41:48+00:00 Do not indicate that a constructor argument is unboxed We only show the strictness annotation for an unboxed constructor argument. The fact that it is unboxed is an implementation detail and should not be part of the module interface. - - - - - 562a4523 by David Waern at 2009-01-22T18:53:49+00:00 Fix Trac haskell/haddock#50: do not attach docs to pragmas or other kinds of non-declarations We now filter out everything that is not a proper Haskell declaration before collecting the docs and attaching them to declarations. - - - - - 6fdf21c2 by David Waern at 2009-01-22T19:48:09+00:00 Add test for quasi quotation. No reference output yet. - - - - - dc4100fd by David Waern at 2009-01-22T19:57:47+00:00 Improve quasi-quotation test and add reference output - - - - - 908b74bb by David Waern at 2009-01-23T23:22:03+00:00 Filter out separately exported associated types in a smarter way - - - - - f6b42ecb by David Waern at 2009-01-24T16:54:39+00:00 Correct spelling mistake in error message - - - - - 24e4245d by David Waern at 2009-01-24T17:48:03+00:00 Correct comment - - - - - b5e8462f by David Waern at 2009-02-07T13:22:29+00:00 Do not show a subordinate at the top level if its parent is also exported See note in the source code for more info. - - - - - 4b09de57 by David Waern at 2009-02-07T13:53:53+00:00 Update test following change to top level subordinates - - - - - 76379896 by David Waern at 2009-02-07T13:58:04+00:00 Remove html files in the tests/output/ directory which have been accidentally added - - - - - 1a6d8b10 by Joachim Breitner at 2009-02-20T10:29:43+00:00 Typo in comment - - - - - fec367d0 by David Waern at 2009-02-24T20:21:17+00:00 Fix small bug The rule is to prefer type constructors to other things when an identifier in a doc string can refer to multiple things. This stopped working with newer GHC versions (due to a tiny change in the GHC renamer). We implement this rule in the HTML backend for now, instead of fixing it in GHC, since we will move renaming of doc strings to Haddock in the future anyway. - - - - - 9b4172eb by David Waern at 2009-02-25T20:04:38+00:00 Fix bad error handling with newer GHCs When support for GHC 6.10 was added, an error handler was installed only around the typechecking phase. This had the effect that errors thrown during dependency chasing were caught in the top-level exception handler and not printed with enough detail. With this patch we wrap the error handler around all our usage of the Ghc monad. - - - - - de2df363 by Simon Peyton Jones at 2009-02-02T16:47:42+00:00 Hide funTyConName, now exported by TypeRep - - - - - 4d40a29f by Ian Lynagh at 2009-02-12T18:57:49+00:00 Don't build the library when building in the GHC tree - - - - - 1cd0abe4 by Ian Lynagh at 2009-02-13T13:58:53+00:00 Add a ghc.mk - - - - - 3d814eeb by Ian Lynagh at 2009-02-13T18:50:28+00:00 do .depend generation for haddock with the stage1 compiler This is a bit of a hack. We mkdepend with stage1 as if .depend depends on the stage2 compiler then make goes wrong: haddock's .depend gets included, which means that make won't reload until it's built, but we can't build it without the stage2 compiler. We therefore build the stage2 compiler before its .depend file is available, and so compilation fails. - - - - - b55036a4 by Ian Lynagh at 2009-02-25T01:38:13+00:00 Give haddock a wrapper on unix in the new GHC build system - - - - - 9eabfe68 by Ian Lynagh at 2009-02-25T19:21:32+00:00 Create inplace/lib/html in the new GHC build system - - - - - 93af30c7 by Ian Lynagh at 2008-11-07T19:18:23+00:00 TAG GHC 6.10.1 release - - - - - 06e6e34a by Thomas Schilling at 2009-02-24T18:11:00+00:00 Define __GHC_PATCHLEVEL__ for recent version of GHC (stable). - - - - - 680e6ed8 by Thomas Schilling at 2009-02-24T18:12:26+00:00 'needsTemplateHaskell' is not defined in current stable GHC. - - - - - 6c5619df by David Waern at 2009-02-25T22:15:23+00:00 Hide fynTyConName only for recent GHC versions - - - - - 6b2344f1 by Ian Lynagh at 2009-02-26T00:49:56+00:00 Add the module to one of haddocks warnings - - - - - e5d11c70 by David Waern at 2009-02-27T21:37:20+00:00 Bug fix We tried to filter out subordinates that were already exported through their parent. This didn't work properly since we were in some cases looking at the grand-parent and not the parent. We now properly compute all the parent-child relations of a declaration, and use this information to get the parent of a subordinate. We also didn't consider record fields with multiple parents. This is now handled correctly. We don't currently support separately exported associated types. But when we do, they should be handled correctly by this process too. Also slightly improved the warning message that we give when filtering out subordinates. - - - - - 10a79a60 by David Waern at 2009-02-27T22:08:08+00:00 Fix error message conflict The module name is already written in the beginning of the message, as seems to be the convention in Haddock. Perhaps not so clear, but we should change it everywhere in that case. Leaving it as it is for now. - - - - - c5055c7f by David Waern at 2009-02-27T22:15:17+00:00 Shorten warning message - - - - - a72fed3a by David Waern at 2009-02-28T00:53:55+00:00 Do not show package name in warning message - - - - - a5daccb2 by Ian Lynagh at 2009-03-01T14:59:35+00:00 Install haddock in the new GHC build system - - - - - dfdb025c by Ian Lynagh at 2009-03-07T23:56:29+00:00 Relax base dependency to < 4.2, not < 4.1 - - - - - 5769c8b4 by David Waern at 2009-03-21T14:58:52+00:00 Bump .haddock file version number (due to change of format) - - - - - f1b8f67b by David Waern at 2009-03-21T14:59:26+00:00 Define __GHC_PATCHLEVEL__=1 when using ghc-6.10.1 - - - - - 23f78831 by David Waern at 2009-03-21T16:40:52+00:00 Update CHANGES - - - - - 7d2735e9 by David Waern at 2009-03-21T16:50:33+00:00 Update ANNOUNCE - - - - - 0771e00a by David Waern at 2009-03-21T16:54:40+00:00 Update ANNOUNCE, again - - - - - 81a6942a by David Waern at 2009-03-21T17:50:06+00:00 Don't be too verbose in CHANGES - - - - - 29861dcf by David Waern at 2009-03-21T18:03:31+00:00 TAG 2.4.2 - - - - - a585f285 by David Waern at 2009-03-21T19:20:29+00:00 Require Cabal >= 1.2.3 - - - - - 7c611662 by David Waern at 2009-03-21T19:21:48+00:00 TAG 2.4.2 with cabal-version >= 1.2.3 - - - - - 23b7deff by Simon Marlow at 2009-03-20T15:43:42+00:00 new GHC build system: use shell-wrappers macro - - - - - 25f8afe7 by Ian Lynagh at 2009-03-21T19:13:53+00:00 Fix (with a hack?) haddock in teh new build system - - - - - 6a29a37e by David Waern at 2009-03-24T22:10:15+00:00 Remove unnecessary LANGUAGE pragma - - - - - 954da57d by David Waern at 2009-03-24T22:21:23+00:00 Fix warnings in H.B.DevHelp - - - - - 1619f1df by David Waern at 2009-03-26T23:20:44+00:00 -Wall police in H.B.Html - - - - - b211e13b by Simon Marlow at 2009-03-24T13:00:56+00:00 install Haddock's html stuff - - - - - 78e0b107 by David Waern at 2008-12-07T19:58:53+00:00 Add verbosity flag and utils, remove "verbose" flag - - - - - 913dae06 by David Waern at 2008-12-07T20:01:05+00:00 Add some basic "verbose" mode logging in H.Interface - - - - - 1cbff3bf by David Waern at 2009-03-27T00:07:26+00:00 Fix conflicts - - - - - 22f82032 by David Waern at 2009-03-27T21:15:11+00:00 Remove H.GHC.Typecheck - - - - - 81557804 by David Waern at 2009-03-27T21:19:22+00:00 Remove docNameOrig and use getName everywhere instead - - - - - d8267213 by David Waern at 2009-03-27T21:21:46+00:00 Use docNameOcc instead of nameOccName . getName - - - - - 5d55deab by David Waern at 2009-03-27T21:33:04+00:00 Remove H.DocName and put DocName in H.Types - - - - - 8ba72611 by David Waern at 2009-03-27T22:06:26+00:00 Document DocName - - - - - 605f8ca5 by David Waern at 2009-03-27T22:45:21+00:00 -Wall police - - - - - e4da93ae by David Waern at 2009-03-27T23:12:53+00:00 -Wall police in H.B.Hoogle - - - - - bb255519 by David Waern at 2009-03-27T23:41:28+00:00 Define Foldable and Traversable instances for Located - - - - - f1195cfe by David Waern at 2009-03-27T23:51:34+00:00 Wibble - - - - - 23818d7c by David Waern at 2009-03-28T00:03:55+00:00 -Wall police in H.I.Rename - - - - - 0f050d67 by David Waern at 2009-03-28T00:15:15+00:00 -Wall police in H.I.AttachInstances - - - - - 0f3fe038 by David Waern at 2009-03-28T21:09:41+00:00 Wibble - - - - - 275d4865 by David Waern at 2009-03-28T21:27:06+00:00 Layout fix - - - - - 54ff0ef8 by David Waern at 2009-03-28T21:59:07+00:00 -Wall police in H.I.Create - - - - - 7f58b117 by David Waern at 2009-03-28T22:10:19+00:00 -Wall police in H.Interface - - - - - f0c03b44 by David Waern at 2009-03-28T22:22:59+00:00 -Wall police in Main - - - - - 29da355c by David Waern at 2009-03-28T22:23:39+00:00 Turn on -Wall -Werror - - - - - 446d3060 by David Waern at 2009-04-01T20:40:30+00:00 hlint police - - - - - 3867c9fc by David Waern at 2009-04-01T20:48:42+00:00 hlint police - - - - - bd1f1600 by David Waern at 2009-04-01T20:58:02+00:00 hlint police - - - - - e0e90866 by David Waern at 2009-04-05T12:42:53+00:00 Move H.GHC.Utils to H.GhcUtils - - - - - 9cbd426b by David Waern at 2009-04-05T12:57:21+00:00 Remove Haddock.GHC and move its (small) contents to Main - - - - - b5c2cbfd by David Waern at 2009-04-05T13:07:04+00:00 Fix whitespace and stylistic issues in Main - - - - - 3c04aa56 by porges at 2008-12-07T08:22:19+00:00 add unicode output - - - - - 607918da by David Waern at 2009-04-26T15:09:43+00:00 Resolve conflict - - - - - 4bec6b6b by Simon Marlow at 2009-05-13T10:00:31+00:00 fix markup - - - - - 436ad6f4 by Simon Marlow at 2009-03-23T11:54:45+00:00 clean up - - - - - bdcd1398 by Simon Marlow at 2009-03-24T10:36:45+00:00 new GHC build system: add $(exeext) - - - - - 9c0972f3 by Simon Marlow at 2009-03-24T11:04:31+00:00 update for new GHC build system layout - - - - - d0f3f83a by Ian Lynagh at 2009-03-29T15:31:43+00:00 GHC new build system fixes - - - - - 5a8245c2 by Ian Lynagh at 2009-04-04T20:44:23+00:00 Tweak new build system - - - - - 9c6f2d7b by Simon Marlow at 2009-05-13T10:01:27+00:00 add build instructions for GHC - - - - - 66d07c76 by Ian Lynagh at 2009-05-31T00:37:53+00:00 Quote program paths in ghc.mk - - - - - bb7de2cd by Ian Lynagh at 2009-06-03T22:57:55+00:00 Use a bang pattern on an unlifted binding - - - - - 3ad283fc by Ian Lynagh at 2009-06-13T16:17:50+00:00 Include haddock in GHC bindists - - - - - ac447ff4 by David Waern at 2009-06-24T21:07:50+00:00 Delete Haddock.Exception and move contents to Haddock.Types Only a few lines of code that mainly declares a type - why not just put it in Haddock.Types. - - - - - 4464fb9b by David Waern at 2009-06-24T22:23:23+00:00 Add Haddock module headers Add a proper Haddock module header to each module, with a more finegrained copyright. If you feel mis-accreditted, please correct any copyright notice! The maintainer field is set to haddock at projects.haskell.org. Next step is to add a brief description to each module. - - - - - 5f4c95dd by David Waern at 2009-06-24T22:39:44+00:00 Fix spelling error - - - - - 6d074cdb by David Waern at 2009-06-25T21:53:56+00:00 Document Interface and InstalledInterface better - - - - - d0cbd183 by David Waern at 2009-06-27T12:46:46+00:00 Remove misplaced whitespace in H.I.Rename - - - - - fa381c49 by David Waern at 2009-06-27T13:26:03+00:00 Fix haskell/haddock#104 - create output directory if missing - - - - - 91fb77ae by Ian Lynagh at 2009-06-25T15:59:50+00:00 TAG 2009-06-25 - - - - - 0d853f40 by Simon Peyton Jones at 2009-07-02T15:35:22+00:00 Follow extra field in ConDecl - - - - - b201735d by Ian Lynagh at 2009-07-05T16:50:35+00:00 Update Makefile for the new GHC build system - - - - - df6c0092 by Ian Lynagh at 2009-07-05T17:01:13+00:00 Resolve conflicts - - - - - 1066870a by Ian Lynagh at 2009-07-05T17:01:48+00:00 Remove the -Wwarn hack in the GHC build system - - - - - 7e856076 by Ian Lynagh at 2009-07-05T17:17:59+00:00 Fix warnings - - - - - 5d4cd958 by Ian Lynagh at 2009-07-05T19:35:40+00:00 Bump version number Cabal needs to distinguish between haddocks having a --verbose and --verbosity flag - - - - - 6ee07c99 by David Waern at 2009-07-06T20:14:57+00:00 Wibble - - - - - 2308b66f by David Waern at 2009-07-06T20:24:20+00:00 Clearer printing of versions by runtests.hs - - - - - d4b5d9ab by David Waern at 2009-07-06T21:22:42+00:00 Fix (invisible) bug introduced by unicode patch - - - - - 2caca8d8 by David Waern at 2009-07-06T21:44:10+00:00 Use HscAsm instead of HscC when using TH - - - - - 18f3b755 by David Waern at 2009-07-06T22:10:22+00:00 Update HCAR entry (by Janis) - - - - - a72ac9db by David Waern at 2009-07-06T23:01:35+00:00 Follow HsRecTy change with an #if __GLASGOW_HASKEL__ >= 611 - - - - - 549135d2 by David Waern at 2009-07-06T23:11:41+00:00 Remove unused functions from Haddock.Utils - - - - - b450134a by Isaac Dupree at 2009-07-11T14:59:00+00:00 revert to split-index for large indices - remove the search-box, because browsers have search-for-text abilities anyway. - pick 150 items in index as the arbitrary time at which to split it - notice the bug that identifiers starting with non-ASCII characters won't be listed in split-index, but don't bother to fix it yet (see ticket haskell/haddock#116, http://trac.haskell.org/haddock/ticket/116 ) - - - - - 78a5661e by Isaac Dupree at 2009-07-20T15:37:18+00:00 Implement GADT records in HTML backend - - - - - 4e163555 by Isaac Dupree at 2009-07-21T22:03:25+00:00 add test for GADT records - - - - - 79aa4d6e by David Waern at 2009-07-23T20:40:37+00:00 Update test suite following version bump - - - - - 5932c011 by David Waern at 2009-08-02T10:25:39+00:00 Fix documentation bug - - - - - a6970fca by David Waern at 2009-08-12T23:08:53+00:00 Remove support for ghc 6.8.* from .cabal file - - - - - c1695902 by Ian Lynagh at 2009-07-07T13:35:45+00:00 Fix unused import warnings - - - - - fb6df7f9 by Ian Lynagh at 2009-07-16T00:20:31+00:00 Use cProjectVersion directly rather than going through compilerInfo Fixes the build after changes in GHC - - - - - 548cdd66 by Simon Marlow at 2009-07-28T14:27:04+00:00 follow changes in GHC's ForeignType - - - - - 9395aaa0 by David Waern at 2009-08-13T22:17:33+00:00 Switch from PatternSignatures to ScopedTypeVariables in Main - - - - - eebf39bd by David Waern at 2009-08-14T17:14:28+00:00 Version .haddock files made with GHC 6.10.3/4 correclty - - - - - 58f3e735 by David Waern at 2009-08-14T17:19:37+00:00 Support GHC 6.10.* and 6.11.* only - - - - - 5f63cecc by David Waern at 2009-08-14T22:03:20+00:00 Do not version .haddock file based on GHC patchlevel version We require that the instances of Binary that we use from GHC will not change between patchlevel versions. - - - - - d519de9f by David Waern at 2009-08-14T23:50:00+00:00 Update CHANGES - - - - - 35dccf5c by David Waern at 2009-08-14T23:51:38+00:00 Update version number everywhere - - - - - 6d363fea by David Waern at 2009-08-15T09:46:49+00:00 Update ANNOUNCE - - - - - c7ee6bc2 by David Waern at 2009-08-15T09:47:13+00:00 Remove -Werror Forgot that Hackage doesn't like it. - - - - - a125c12b by David Waern at 2009-08-15T09:49:50+00:00 Require Cabal >= 1.6 - - - - - adb2f560 by Isaac Dupree at 2009-08-12T03:47:14+00:00 Cross-Package Documentation version 4 - - - - - 3d6dc04d by David Waern at 2009-08-15T23:42:57+00:00 Put all the IN_GHC_TREE stuff inside getGhcLibDir - - - - - 56624097 by David Waern at 2009-08-15T23:52:03+00:00 Add --print-ghc-libdir - - - - - f15d3ccb by David Waern at 2009-08-16T00:37:52+00:00 Read base.haddock when running tests We can now test cross-package docs. - - - - - 283f0fb9 by David Waern at 2009-08-16T00:50:59+00:00 Update test output - we now have more links - - - - - 673d1004 by David Waern at 2009-08-16T01:26:08+00:00 Read process.haddock when running tests - - - - - 0d127f82 by David Waern at 2009-08-16T01:43:04+00:00 Add a test for cross-package documentation - - - - - f94db967 by Ian Lynagh at 2009-08-16T18:42:44+00:00 Follow GHC build system changes - - - - - 5151278a by Isaac Dupree at 2009-08-16T19:58:05+00:00 make cross-package list types look nicer - - - - - c41e8228 by Isaac Dupree at 2009-08-18T01:47:47+00:00 Haddock.Convert: export more functions This lets us remove some code in Haddock.Interface.AttachInstances - - - - - 2e5fa398 by Isaac Dupree at 2009-08-18T02:11:05+00:00 switch AttachInstances to use synify code It changed an instance from showing ((,) a b) to (a, b) because my synify code is more sophisticated; I hope the latter is a good thing rather than a bad thing aesthetically, here. But this definitely reduces code duplication! - - - - - b8b07123 by Isaac Dupree at 2009-08-18T02:23:31+00:00 Find instances using GHC, which is more complete. In particular, it works cross-package. An intermediate patch also moved the instance-finding into createInterface, but that move turned out not to be necessary, so if we want to do that, it'd go in a separate patch. (Is that possible? Or will we need GHC to have loaded all the modules first, before we can go searching for the instances (e.g. if the modules are recursive or something)?) - - - - - 6959b451 by Isaac Dupree at 2009-08-17T00:37:18+00:00 fix preprocessor conditional sense - - - - - 942823af by Isaac Dupree at 2009-08-16T22:46:48+00:00 remove ghc 6.8 conditionals from Haddock.Interface - - - - - 4b3ad888 by Isaac Dupree at 2009-08-18T20:24:38+00:00 Fix GHC 6.11 build in Haddock.Convert - - - - - 0a89c5ab by Isaac Dupree at 2009-08-23T00:08:58+00:00 hacks to make it compile without fnArgDocsn - - - - - 7b3bed43 by Isaac Dupree at 2009-08-23T03:01:28+00:00 less big-Map-based proper extraction of constructor subdocs - - - - - b21c279a by Isaac Dupree at 2009-08-23T03:02:06+00:00 Html: remove unnecessary+troublesome GHC. qualifications - - - - - 96c97115 by Isaac Dupree at 2009-08-23T03:08:03+00:00 Move doc parsing/lexing into Haddock for ghc>=6.11 - - - - - e1cec02d by Isaac Dupree at 2009-08-23T05:08:14+00:00 get rid of unused DocMap parameter in Html - - - - - 66960c59 by Isaac Dupree at 2009-08-23T05:54:20+00:00 fix horrible named-docs-disappearing bug :-) - - - - - a9d7eff3 by Isaac Dupree at 2009-08-23T06:26:36+00:00 re-implement function-argument docs ..on top of the lexParseRn work. This patch doesn't change the InstalledInterface format, and thus, it does not work cross-package, but that will be easy to add subsequently. - - - - - 8bf6852c by Isaac Dupree at 2009-08-23T07:26:05+00:00 cross-package fnArgDocs. WARNING: changes .haddock binary format While breaking the format, I took the opportunity to unrename the DocMap that's saved to disk, because there's really no reason that we want to know what *another* package's favorite place to link a Name to was. (Is that true? Or might we want to know, someday?) Also, I added instance Binary Map in InterfaceFile. It makes the code a little simpler without changing anything of substance. Also it lets us add another Map hidden inside another Map (fnArgsDocs in instDocMap) without having really-convoluted serialization code. Instances are neat! I don't understand why this change to InterfaceFile seemed to subtly break binary compatibility all by itself, but no matter, I'll just roll it into the greater format-changing patch. Done! - - - - - 30115a64 by Isaac Dupree at 2009-08-23T18:22:47+00:00 Improve behavior for unfindable .haddock - - - - - aa364bda by Isaac Dupree at 2009-08-23T18:28:16+00:00 add comment for FnArgsDoc type - - - - - 49b23a99 by Isaac Dupree at 2009-08-23T21:52:48+00:00 bugfix: restore fnArgDocs for type-synonyms - - - - - f65f9467 by Isaac Dupree at 2009-08-23T22:06:55+00:00 Backends.Hoogle: eliminate warnings - - - - - a292d216 by Isaac Dupree at 2009-08-23T22:10:24+00:00 Haddock.Convert: eliminate warnings - - - - - 5546cd20 by Isaac Dupree at 2009-08-23T22:12:31+00:00 Haddock.Interface.Rename: eliminate warnings - - - - - 0a9798b6 by Isaac Dupree at 2009-08-23T22:18:47+00:00 Main.hs: remove ghc<6.9 conditionals - - - - - e8f9867f by Isaac Dupree at 2009-08-23T22:27:46+00:00 Main.hs: eliminate warnings (except for OldException) - - - - - 61c64247 by Isaac Dupree at 2009-08-23T22:41:01+00:00 move get*LibDir code in Main.hs, to +consistent code, -duplication - - - - - 948f1e69 by Isaac Dupree at 2009-08-23T23:14:26+00:00 Main.hs: OldException->Exception: which eliminates warnings - - - - - 3d5d5e03 by Isaac Dupree at 2009-08-23T23:20:11+00:00 GhcUtils: ghc >= 6.10 - - - - - 2771d657 by Isaac Dupree at 2009-08-23T23:21:55+00:00 InterfaceFile: ghc >= 6.10 - - - - - d9f2b9d1 by Isaac Dupree at 2009-08-23T23:22:58+00:00 Types: ghc >= 6.10 - - - - - ca39210e by Isaac Dupree at 2009-08-23T23:23:26+00:00 ModuleTree: ghc >= 6.10 - - - - - 883c4e59 by Isaac Dupree at 2009-08-23T23:24:04+00:00 Backends.DevHelp: ghc >= 6.10 - - - - - 04667df5 by Isaac Dupree at 2009-08-23T23:24:37+00:00 Backends.Html: ghc >= 6.10 - - - - - a9f7f25f by Isaac Dupree at 2009-08-23T23:25:24+00:00 Utils: ghc >= 6.10 - - - - - b7105022 by Isaac Dupree at 2009-08-23T23:37:47+00:00 eliminate haskell98 dependency, following GHC's example It turns out I/we already had, and it was only a matter of deleting it from the cabal file. - - - - - 292e0911 by Isaac Dupree at 2009-08-24T01:22:44+00:00 refactor out subordinatesWithNoDocs dep of inferenced-decls fix - - - - - c2ed46a2 by Isaac Dupree at 2009-08-24T01:24:03+00:00 Eradicate wrong runtime warning for type-inferenced exported-functions see the long comment in the patch for why I did it this way :-) - - - - - 4ac0b57c by David Waern at 2009-09-04T22:56:20+00:00 Clean up tyThingToHsSynSig a little Factor out noLoc and use the case construct. Also rename the function to tyThingToLHsDecl, since it doesn't just create type signatures. - - - - - 28ab9201 by David Waern at 2009-09-04T22:58:50+00:00 Wibble - - - - - 0d9fe6d0 by David Waern at 2009-09-06T18:39:30+00:00 Add more copyright owners to H.I.AttachInstances - - - - - 122441b1 by David Waern at 2009-09-06T18:44:12+00:00 Style police - - - - - 1fa79463 by David Waern at 2009-09-06T18:57:45+00:00 Move toHsInstHead to Haddock.Convert and call it synifyInstHead - - - - - 0d42a8aa by David Waern at 2009-09-06T21:11:38+00:00 Use colordiff to display test results if available - - - - - ea9d8e03 by Simon Marlow at 2009-08-24T08:46:14+00:00 Follow changes in GHC's interface file format Word32 instead of Int for FastString and Name offsets - - - - - 537e051e by Simon Marlow at 2009-07-29T14:16:53+00:00 define unpackPackageId (it was removed from GHC) - - - - - 50c63aa7 by David Waern at 2009-09-09T23:18:03+00:00 Remove commented-out code - - - - - 511631fe by David Waern at 2009-09-09T23:19:05+00:00 Correct copyright in H.I.ParseModuleHeader - - - - - 898ec768 by David Waern at 2009-09-11T11:22:29+00:00 Use Map.fromList/toList intead of fromAscList/toAscList when serializing Maps This fixes the missing docs problem. The Eq and Ord instances for Name uses the unique number in Name. This number is created at deserialization time by GHC's magic Binary instance for Name, and it is random. Thus, fromAscList can't be used at deserialization time, even though toAscList was used at serialization time. - - - - - 37bec0d5 by Simon Peyton Jones at 2009-09-11T08:28:04+00:00 Track change in HsType - - - - - eb3a97c3 by Ian Lynagh at 2009-09-11T16:07:09+00:00 Allow building with base 4.2 - - - - - bb4205ed by Ian Lynagh at 2009-09-22T13:50:02+00:00 Loosen the GHC dependency - - - - - 5c75deb2 by Ian Lynagh at 2009-09-22T14:08:39+00:00 Fix building with GHC >= 6.12 - - - - - fb131481 by David Waern at 2009-09-11T11:24:48+00:00 Update runtests.hs to work with GHC 6.11 - - - - - ac3a419d by David Waern at 2009-09-11T11:25:14+00:00 Update CrossPackageDocs test - - - - - ec65c3c6 by David Waern at 2009-09-11T11:25:40+00:00 Add reference output for CrossPackageDocs - - - - - 520c2758 by Ian Lynagh at 2009-10-25T17:26:40+00:00 Fix installation in the GHC build system - - - - - 28b3d7df by Ian Lynagh at 2009-11-05T15:57:27+00:00 GHC build system: Make *nix installation work in paths containing spaces - - - - - 5c9bb541 by David Waern at 2009-11-14T11:56:39+00:00 Track change in HsType for the right compiler version - - - - - 905097ce by David Waern at 2009-11-14T12:10:47+00:00 hlint police - - - - - 04920630 by Ian Lynagh at 2009-11-20T13:46:30+00:00 Use defaultObjectTarget rather than HscAsm This fixes haddock when we don't have a native code generator - - - - - 966eb079 by David Waern at 2009-11-15T12:32:21+00:00 Remove commented-out code - - - - - 37f00fc4 by David Waern at 2009-11-22T13:58:48+00:00 Make runtests.hs strip links before diffing Generates easier to read diffs when tests fail. The content of the links is not important anyway since it is not taken into account by the tests. - - - - - 3a9bb8ef by David Waern at 2009-11-22T14:05:06+00:00 Follow findProgramOnPath signature change in runtests.hs - - - - - b26b9e5a by David Waern at 2009-11-22T14:08:40+00:00 Follow removal of GHC.MVar from base in CrossPackageDocs - - - - - f4d90ae4 by David Waern at 2009-11-22T14:48:47+00:00 Make copy.hs strip link contents before copying No more updating of reference files when URLs in links changes. - - - - - 4c9c420d by David Waern at 2009-11-22T15:26:41+00:00 Update test reference output * More links (Int, Float etc) * Stripped link contents - - - - - a62b80e3 by David Waern at 2009-11-23T23:19:39+00:00 Update CrossPackageDocs reference output - Remove GHC.MVar import (removed from base) - Strip link contents - - - - - 43491394 by David Waern at 2009-11-23T23:20:00+00:00 Update test reference files with comments on instances - - - - - 0d370a0b by David Waern at 2009-11-23T23:25:16+00:00 Bump version number - - - - - 2293113e by David Waern at 2009-11-24T20:55:49+00:00 Comments on instances Implementing this was a little trickier than I thought, since we need to match up instances from the renamed syntax with instances represented by InstEnv.Instance. This is due to the current design of Haddock, which matches comments with declarations from the renamed syntax, while getting the list of instances of a class/family directly using the GHC API. - Works for class instances only (Haddock has no support for type family instances yet) - The comments are rendered to the right of the instance head in the HTML output - No change to the .haddock file format - Works for normal user-written instances only. No comments are added on derived or TH-generated instances - - - - - bf586f29 by David Waern at 2009-11-27T22:05:15+00:00 Whitespace police - - - - - b8f03afa by David Waern at 2009-11-27T22:11:46+00:00 Remove bad whitespace and commented-out pieces - - - - - 90b8ee90 by David Waern at 2009-11-27T22:15:04+00:00 Whitespace police - - - - - b5ede900 by David Waern at 2009-11-27T22:15:50+00:00 Whitespace police - - - - - e3fddbfe by David Waern at 2009-11-28T13:37:59+00:00 Remove Name from DocInstance It's not used. - - - - - 9502786c by David Waern at 2009-11-28T13:56:54+00:00 Require at least GHC 6.12 While regression testing Haddock, I found a bug that happens with GHC 6.10.3, but not with GHC 6.12-rc2 (haven't tried 6.10.4). I don't have time to track it down. I think we should just always require the latest major GHC version. The time spent on making Haddock work with older versions is too high compared to the time spent on bugfixing, refactoring and features. - - - - - 8fa688d8 by David Waern at 2009-11-28T15:05:03+00:00 Remove cruft due to compatibility with older GHCs - - - - - 46fbbe9d by David Waern at 2009-11-28T15:07:50+00:00 Add a documentation header to Haddock.Convert - - - - - c3d2cc4a by David Waern at 2009-11-28T15:10:14+00:00 Remove unused H.Utils.FastMutInt2 - - - - - 490aba80 by David Waern at 2009-11-28T15:36:36+00:00 Rename Distribution.Haddock into Documentation.Haddock - - - - - 33ee2397 by David Waern at 2009-11-28T15:36:47+00:00 Fix error message - - - - - a5a3b950 by David Waern at 2009-11-28T16:58:39+00:00 Add a test flag that brings in QuickCheck - - - - - fa049e13 by David Waern at 2009-11-28T19:32:18+00:00 Say that we want quickcheck 2 - - - - - f32b0d9b by David Waern at 2009-11-28T19:32:40+00:00 Add an Arbitrary instance for HsDoc - - - - - da9a8bd7 by David Waern at 2009-11-28T20:15:30+00:00 Rename HsDoc back into Doc - - - - - edb60101 by David Waern at 2009-11-28T22:16:16+00:00 Move H.Interface.Parse/Lex to H.Parse/Lex These are not just used to build Interfaces. - - - - - 0656a9b8 by David Waern at 2009-11-28T23:12:14+00:00 Update version number in test suite - - - - - 5e8c6f4a by David Waern at 2009-12-21T14:12:41+00:00 Improve doc of DocName - - - - - 7868e551 by Ian Lynagh at 2009-09-22T10:43:03+00:00 TAG GHC 6.12-branch created - - - - - 0452a3ea by Ian Lynagh at 2009-12-15T12:46:07+00:00 TAG GHC 6.12.1 release - - - - - 65e9be62 by David Waern at 2009-12-21T16:58:58+00:00 Update CHANGES - - - - - 145cee32 by David Waern at 2009-12-21T16:59:09+00:00 TAG 2.6.0 - - - - - 3c552008 by David Waern at 2009-12-22T17:11:14+00:00 Update ANNOUNCE - - - - - 931f9db4 by David Waern at 2010-01-22T19:57:17+00:00 Convert haddock.vim to use unix newlines - - - - - 4e56588f by David Waern at 2010-01-22T22:11:17+00:00 Remove unnecessary (and inexplicable) uses of nub - - - - - 744bb4d1 by David Waern at 2010-01-22T22:12:14+00:00 Follow move of parser and lexer - - - - - e34bab14 by David Waern at 2010-01-22T22:49:13+00:00 Use findProgramLocation instead of findProgramOnPath in runtests.hs - - - - - 8d39891b by Isaac Dupree at 2010-01-14T18:53:18+00:00 fix html arg-doc off-by-one and silliness - - - - - 9401f2e9 by David Waern at 2010-01-22T22:57:03+00:00 Create a test for function argument docs - - - - - 507a82d7 by David Waern at 2010-01-22T23:24:47+00:00 Put parenthesis around type signature arguments of function type - - - - - 8a305c28 by David Waern at 2010-01-23T17:26:59+00:00 Add reference file for the FunArgs test - - - - - 1309d5e1 by David Waern at 2010-01-24T16:05:08+00:00 Improve FunArg test and update Test.html.ref - - - - - 2990f055 by Yitzchak Gale at 2010-02-14T16:03:46+00:00 Do not generate illegal character in HTML ID attribute. - - - - - c5bcab7a by David Waern at 2010-02-22T22:10:30+00:00 Fix Haddock markup error in comment - - - - - c6416a73 by David Waern at 2010-02-24T22:55:08+00:00 Large additions to the Haddock API Also improved and added more doc comments. - - - - - 57d289d7 by David Waern at 2010-02-24T22:58:02+00:00 Remove unused ifaceLocals - - - - - 80528d93 by David Waern at 2010-02-25T21:05:09+00:00 Add HaddockModInfo to the API - - - - - 82806848 by David Waern at 2010-02-25T21:05:27+00:00 Wibble - - - - - 744cad4c by David Waern at 2010-02-25T23:30:59+00:00 Make it possible to run a single test - - - - - 6a806e4c by David Waern at 2010-03-14T14:19:39+00:00 Bump version number - - - - - a5a8e4a7 by David Waern at 2010-03-14T14:36:35+00:00 Update ANNOUNCE - - - - - 6f05435e by Simon Hengel at 2010-03-15T20:52:42+00:00 Add missing dependencies for 'library' in haddock.cabal - - - - - faefe2bd by David Waern at 2010-03-15T22:29:37+00:00 Solve conflicts - - - - - 9808ad52 by David Waern at 2010-03-15T22:51:21+00:00 Bump version number - - - - - eb0bf60b by David Waern at 2010-03-15T22:52:32+00:00 Update CHANGES - - - - - f95cd891 by David Waern at 2010-03-15T23:01:06+00:00 Add Paths_haddock to other-modules of library - - - - - 65997b0a by David Waern at 2010-03-15T23:14:59+00:00 Update CHANGES - - - - - 7e251731 by David Waern at 2010-03-15T23:15:30+00:00 Bump version number - - - - - c9cd0ddc by David Waern at 2010-03-16T00:28:34+00:00 Fix warning - - - - - 1cac2d93 by Simon Peyton Jones at 2010-01-04T15:22:16+00:00 Fix imports for new location of splitKindFunTys - - - - - 474f26f6 by Simon Peyton Jones at 2010-02-10T14:36:06+00:00 Update Haddock for quasiquotes - - - - - 0dcc06c0 by Simon Peyton Jones at 2010-02-10T10:59:45+00:00 Track changes in HsTyVarBndr - - - - - 2d84733a by Simon Peyton Jones at 2010-02-10T14:52:44+00:00 Track HsSyn chnages - - - - - 9e3adb8b by Ian Lynagh at 2010-02-20T17:09:42+00:00 Resolve conflicts - - - - - a3e72ff8 by Simon Peyton Jones at 2010-03-04T13:05:16+00:00 Track change in HsUtils; and use a nicer function not an internal one - - - - - 27994854 by David Waern at 2010-03-18T22:22:27+00:00 Fix build with GHC 6.12.1 - - - - - 11f6e488 by David Waern at 2010-03-18T22:24:09+00:00 Bump version in test reference files - - - - - 0ef2f11b by David Waern at 2010-03-20T00:56:30+00:00 Fix library part of cabal file when in ghc tree - - - - - 3f6146ff by Mark Lentczner at 2010-03-20T22:30:11+00:00 First, experimental XHTML rendering switch to using the xhtml package copied Html.hs to Xhtml.hs and split into sub-modules under Haddock/Backends/Xhtml and detabify moved footer into div, got ready for iface change headers converted to semantic markup contents in semantic markup summary as semantic markup description in semantic markup, info block in header fixed factored out rendering so during debug it can be readable (see renderToString) - - - - - b8ab329b by Mark Lentczner at 2010-03-20T22:54:01+00:00 apply changes to Html.hs to Xhtml/*.hs incorporate changes that were made between the time Html.hs was copied and split into Xhtml.hs and Xhtml/*.hs includes patchs after "Wibble" (!) through "Fix build with GHC 6.12.1" - - - - - 73df2433 by Ian Lynagh at 2010-03-20T21:56:37+00:00 Follow LazyUniqFM->UniqFM in GHC - - - - - db4f602b by David Waern at 2010-03-29T22:00:01+00:00 Fix build with GHC 6.12 - - - - - d8dca088 by Simon Hengel at 2010-04-02T16:39:55+00:00 Add missing dependencies to cabal file - - - - - e2adc437 by Simon Hengel at 2010-04-02T14:08:40+00:00 Add markup support for interactive examples - - - - - e882ac05 by Simon Hengel at 2010-04-02T14:11:53+00:00 Add tests for interactive examples - - - - - 5a07a6d3 by David Waern at 2010-04-07T17:05:20+00:00 Propagate source positions from Lex.x to Parse.y - - - - - 6493b46f by David Waern at 2010-04-07T21:48:57+00:00 Let runtests.hs die when haddock has not been built - - - - - 5e34423e by David Waern at 2010-04-07T22:01:13+00:00 Make runtests.hs slightly more readable - - - - - 321d59b3 by David Waern at 2010-04-07T22:13:27+00:00 Fix haskell/haddock#75 Add colons to the $ident character set. - - - - - 37b08b8d by David Waern at 2010-04-08T00:32:52+00:00 Fix haskell/haddock#118 Avoid being too greedy when lexing URL markup (<..>), in order to allow multiple URLs on the same line. Do the same thing with <<..>> and #..#. - - - - - df8feac9 by David Waern at 2010-04-08T00:57:33+00:00 Make it easier to add new package deps to test suite This is a hack - we should use Cabal to get the package details instead. - - - - - 1ca6f84b by David Waern at 2010-04-08T01:03:06+00:00 Add ghc-prim to test suite deps - - - - - 27371e3a by Simon Hengel at 2010-04-08T19:26:34+00:00 Let parsing fails on paragraphs that are immediately followed by an example This is more consistent with the way we treat code blocks. - - - - - 83096e4a by David Waern at 2010-04-08T21:20:00+00:00 Improve function name - - - - - 439983ce by David Waern at 2010-04-10T10:46:14+00:00 Fix haskell/haddock#112 No link was generated for 'Addr#' in a doc comment. The reason was simply that the identifier didn't parse. We were using parseIdentifier from the GHC API, with a parser state built from 'defaultDynFlags'. If we pass the dynflags of the module instead, the right options are turned on on while parsing the identifer (in this case -XMagicHash), and the parse succeeds. - - - - - 5c0d35d7 by David Waern at 2010-04-10T10:54:06+00:00 Rename startGhc into withGhc - - - - - dca081fa by Simon Hengel at 2010-04-12T19:09:16+00:00 Add documentation for interactive examples - - - - - c7f26bfa by David Waern at 2010-04-13T00:51:51+00:00 Slight fix to the documentation of examples - - - - - 06eb7c4c by David Waern at 2010-04-13T00:57:05+00:00 Rename Interactive Examples into Examples (and simplify explanation) - - - - - 264830cb by David Waern at 2010-05-10T20:07:27+00:00 Update CHANGES with info about 2.6.1 - - - - - 8e5d4514 by Simon Hengel at 2010-04-18T18:16:54+00:00 Add unit tests for parser - - - - - 68297f40 by David Waern at 2010-05-10T21:53:37+00:00 Improve testsuite README - - - - - f04eb6e4 by David Waern at 2010-05-11T19:14:31+00:00 Re-organise the testsuite structure - - - - - a360f710 by David Waern at 2010-05-11T19:18:03+00:00 Shorten function name - - - - - 1d5dd359 by David Waern at 2010-05-11T21:40:02+00:00 Update runtests.hs following testsuite re-organisation - - - - - ffebe217 by David Waern at 2010-05-11T21:40:10+00:00 Update runtests.hs to use base-4.2.0.1 - - - - - 635de402 by David Waern at 2010-05-11T21:41:11+00:00 Update runparsetests.hs following testsuite reorganisation - - - - - 72137910 by Ian Lynagh at 2010-05-06T20:43:06+00:00 Fix build - - - - - 1a80b76e by Ian Lynagh at 2010-05-06T22:25:29+00:00 Remove redundant import - - - - - 1031a80c by Simon Peyton Jones at 2010-05-07T13:21:09+00:00 Minor wibbles to HsBang stuff - - - - - dd8e7fe5 by Ian Lynagh at 2010-05-08T15:22:00+00:00 GHC build system: Follow "rm" variable changes - - - - - 7f5e6748 by David Waern at 2010-05-13T11:53:02+00:00 Fix build with GHC 6.12.2 - - - - - 7953d4d8 by David Waern at 2010-05-13T18:45:01+00:00 Fixes to comments only - - - - - 8ae8eb64 by David Waern at 2010-05-13T18:57:26+00:00 ModuleMap -> IfaceMap - - - - - 1c3eadc6 by David Waern at 2010-05-13T19:03:13+00:00 Fix whitespace style issues - - - - - e96783c0 by David Waern at 2010-05-13T19:08:53+00:00 Fix comment - - - - - c998a78b by David Waern at 2010-05-13T19:39:00+00:00 Position the module header the same way everywhere Silly, but nice with some consistency :-) - - - - - b48a714e by David Waern at 2010-05-13T19:41:32+00:00 Position of module header, this time in the HTML backends - - - - - f9bfb12e by David Waern at 2010-05-13T19:43:05+00:00 Two newlines between declarations in Main - - - - - 071d44c7 by David Waern at 2010-05-13T19:44:21+00:00 Newlines in Convert - - - - - 036346db by David Waern at 2010-05-13T19:46:47+00:00 Fix a few stylistic issues in H.InterfaceFile - - - - - f0b8379e by David Waern at 2010-05-13T19:47:53+00:00 Add newlines to H.ModuleTree - - - - - 27409f8e by David Waern at 2010-05-13T19:51:10+00:00 Fix stylistic issues in H.Utils - - - - - 24774a11 by David Waern at 2010-05-13T20:00:43+00:00 Structure H.Types better - - - - - 7b6f5e40 by David Waern at 2010-05-13T20:01:04+00:00 Remove bad Arbitrary instance - - - - - fac9f1f6 by David Waern at 2010-05-13T20:05:50+00:00 Get rid of H.Utils.pathJoin and use System.FilePath.joinPath instead - - - - - fe6d00c4 by David Waern at 2010-05-13T20:51:55+00:00 Export a couple of more types from the API - - - - - b2e33a5f by David Waern at 2010-05-13T21:27:51+00:00 Improve doc comment for Interface - - - - - c585f2ce by David Waern at 2010-05-13T21:30:14+00:00 Improve documentation of Haddock.Interface - - - - - e6791db2 by David Waern at 2010-05-13T22:07:35+00:00 Remove meaningless comments - - - - - 7801b390 by David Waern at 2010-05-14T17:53:33+00:00 Remove unused modules - - - - - f813e937 by David Waern at 2010-05-14T17:55:17+00:00 Re-direct compilation output to a temporary directory Also add a flag --no-tmp-comp-dir that can be used to get the old behaviour of writing compilation files to GHC's output directory (default "."). - - - - - e56737ec by David Waern at 2010-05-14T18:06:11+00:00 Wibble - - - - - e40b0447 by David Waern at 2010-05-14T19:01:52+00:00 Move flag evaluation code from Main to Haddock.Options Determining the value of "singular" flags (by e.g. taking the last occurrence of the flag) and other flag evaluation should done in Haddock.Options which is the module that is supposed to define the command line interface. This makes Main a bit easier on the eyes as well. - - - - - 27091f57 by David Waern at 2010-05-14T19:05:10+00:00 Wibble - - - - - c658cf61 by David Waern at 2010-05-14T19:06:49+00:00 Re-order things in Haddock.Options a bit - - - - - 8cfdd342 by David Waern at 2010-05-14T19:20:29+00:00 De-tabify Haddock.Options and fix other whitespace issues - - - - - 0df16b62 by David Waern at 2010-05-14T19:25:07+00:00 Improve comments - - - - - 80b38e2b by David Waern at 2010-05-14T19:26:42+00:00 Whitespace police - - - - - fe580255 by David Waern at 2010-05-14T19:31:23+00:00 Wibbles to comments - - - - - a2b43fad by David Waern at 2010-05-14T20:24:32+00:00 Move some more flag functions to Haddock.Options - - - - - 3f895547 by David Waern at 2010-05-14T20:37:12+00:00 Make renderStep a top-level function in Main - - - - - 5cdca11d by David Waern at 2010-05-14T20:39:27+00:00 Spelling in comment - - - - - ad98d14c by David Waern at 2010-05-14T20:40:26+00:00 Comment fixes - - - - - 0bb9218f by David Waern at 2010-05-14T20:49:01+00:00 Whitespace police - - - - - 0f0a533f by David Waern at 2010-05-15T16:42:29+00:00 Improve description of --dump-interface - - - - - 5b2833ac by David Waern at 2010-05-15T17:16:53+00:00 Document --no-tmp-comp-dir - - - - - 8160b170 by David Waern at 2010-05-15T17:18:59+00:00 Wibble - - - - - 570dbe33 by David Waern at 2010-05-18T21:15:38+00:00 HLint police - - - - - 204e425f by David Waern at 2010-05-18T21:16:30+00:00 HLint police - - - - - 6db657ac by David Waern at 2010-05-18T21:16:37+00:00 Wibble - - - - - b942ccd7 by Simon Marlow at 2010-06-02T08:27:30+00:00 Interrupted disappeared in GHC 6.13 (GHC ticket haskell/haddock#4100) - - - - - 3b94a819 by Simon Marlow at 2010-06-02T08:45:08+00:00 Allow base-4.3 - - - - - c5a1fb7c by Simon Marlow at 2010-06-02T09:03:04+00:00 Fix compilation with GHC 6.13 - - - - - 6181296c by David Waern at 2010-06-08T21:09:05+00:00 Display name of prologue file when parsing it fails - - - - - 7cbc6f60 by Ian Lynagh at 2010-06-13T16:20:25+00:00 Remove redundant imports - - - - - 980c804b by Simon Marlow at 2010-06-22T08:41:50+00:00 isLocalAndTypeInferenced: fix for local module names overlapping package modules - - - - - d74d4a12 by Simon Marlow at 2010-06-23T12:03:27+00:00 Unresolved identifiers in Doc get replaced with DocMonospaced rather than plain strings - - - - - d8546783 by Simon Marlow at 2010-06-30T12:45:17+00:00 LaTeX backend (new options: --latex, --latex-style=<style>) - - - - - 437afa9e by David Waern at 2010-07-01T12:02:44+00:00 Fix a few stylistic whitespace issues in LaTeX backend - - - - - 85bc1fae by David Waern at 2010-07-01T15:42:45+00:00 Make runtest.hs work with GHC 6.12.3 (we should really stop hard coding this) - - - - - 7d2eb86f by David Waern at 2010-07-01T15:43:33+00:00 Update test following Simon's patch to render unresolved names in monospaced font - - - - - 08fcbcd2 by David Waern at 2010-07-01T16:12:18+00:00 Warning police - - - - - d04a8d7a by David Waern at 2010-07-04T14:53:39+00:00 Fix a bug in attachInstances We didn't look for instance docs in all the interfaces of the package. This had the effect of instance docs not always showing up under a declaration. I took the opportunity to clean up the code in H.I.AttachInstances a bit as well. More cleanup is needed, however. - - - - - d10344eb by Simon Hengel at 2010-07-10T09:19:04+00:00 Add missing dependencies to cabal file - - - - - 24090531 by Mark Lentczner at 2010-03-21T04:51:16+00:00 add exports to Xhtml modules - - - - - 84f9a333 by Mark Lentczner at 2010-04-03T19:14:22+00:00 clean up Doc formatting code - add CSS for lists - renderToString now uses showHtml since prettyHtml messes up <pre> sections - - - - - bebccf52 by Mark Lentczner at 2010-04-04T04:51:08+00:00 tweak list css - - - - - 0c2aeb5e by Mark Lentczner at 2010-04-04T06:24:14+00:00 all decls now generate Html not HtmlTable - ppDecl return Html, and so now do all of the functions it calls - added some internal tables to some decls, which is wrong, and will have to be fixed - decl "Box" functions became "Elem" functions to make clear they aren't in a table anymore (see Layout.hs) - docBox went away, as only used in one place (and its days are numbered) - cleaned up logic in a number of places, removed dead code - added maybeDocToHtml which simplified a number of places in the code - - - - - dbf73e6e by Mark Lentczner at 2010-04-05T05:02:43+00:00 clean up processExport and place a div around each decl - - - - - e25b7e9f by Mark Lentczner at 2010-04-10T21:23:21+00:00 data decls are now a sequence of paragraphs, not a table - - - - - 89ee0294 by Mark Lentczner at 2010-04-10T21:29:16+00:00 removed commented out code that can't be maintained - - - - - d466f536 by Mark Lentczner at 2010-04-12T04:56:27+00:00 removed declWithDoc and cleaned up data decls in summary - - - - - ed755832 by Mark Lentczner at 2010-04-12T05:07:53+00:00 merge in markupExample changes - - - - - c36f51fd by Mark Lentczner at 2010-04-25T04:56:37+00:00 made record fields be an unordList, not a table - - - - - ed3a28d6 by Mark Lentczner at 2010-04-25T05:23:28+00:00 fixed surround of instance and constructor tables - - - - - 0e35bbc4 by Mark Lentczner at 2010-04-25T05:36:59+00:00 fix class member boxes in summary - - - - - 5041749b by Mark Lentczner at 2010-04-25T05:38:35+00:00 remove unused bodyBox - - - - - e91724db by Mark Lentczner at 2010-04-25T06:26:10+00:00 fixed javascript quoting/escpaing issue - - - - - f4abbb73 by Mark Lentczner at 2010-05-03T23:04:31+00:00 adjust css for current markup - - - - - e75fec4c by Mark Lentczner at 2010-05-04T06:14:34+00:00 added assoicated types and methods back into class decls - - - - - 84169323 by Mark Lentczner at 2010-05-24T13:13:42+00:00 merge in changes from the big-whitespace cleanup - - - - - 3c1c872e by Mark Lentczner at 2010-06-11T21:03:58+00:00 adjust synopsis and bottom bar spacing - - - - - 3c1f9ef7 by Mark Lentczner at 2010-06-11T21:14:44+00:00 fix missing space in "module" lines in synoposis - - - - - 9a137e6d by Mark Lentczner at 2010-06-11T21:34:08+00:00 changed tt elements to code elements - - - - - 50f71ef1 by Mark Lentczner at 2010-06-11T23:27:46+00:00 factored out ppInstances - - - - - 3b9a9de5 by Mark Lentczner at 2010-06-17T17:36:01+00:00 push single constructors (newtype) onto line with decl - - - - - e0f8f2ec by Mark Lentczner at 2010-06-17T22:20:56+00:00 remove <++> connector - - - - - 56c075dd by Mark Lentczner at 2010-07-13T05:26:21+00:00 change to new page structure - - - - - 04be6ca7 by Mark Lentczner at 2010-07-14T04:21:55+00:00 constructors and args as dl lists, built in Layout.hs - - - - - 65aeafc2 by Mark Lentczner at 2010-07-14T05:38:32+00:00 better interface to subDecls - - - - - 72032189 by Mark Lentczner at 2010-07-14T07:04:10+00:00 made subDecl tables looks just so - - - - - b782eca2 by Mark Lentczner at 2010-07-14T16:00:54+00:00 convert args to SubDecl format - - - - - cc75e98f by Mark Lentczner at 2010-07-14T16:28:53+00:00 convert instances to SubDecl - - - - - 34e2aa5a by Mark Lentczner at 2010-07-14T21:07:32+00:00 removing old table cruft from Layout.hs - - - - - d5810d95 by Mark Lentczner at 2010-07-14T21:54:58+00:00 methods and associated types in new layout scheme - - - - - 65ef9579 by Mark Lentczner at 2010-07-14T23:43:42+00:00 clean up synopsis lists - - - - - e523318f by Mark Lentczner at 2010-07-15T05:02:26+00:00 clean up of anchors - - - - - 1215dfc5 by Mark Lentczner at 2010-07-15T23:53:01+00:00 added two new themes and rough css switcher - - - - - 7f0fd36f by Mark Lentczner at 2010-07-16T04:57:38+00:00 fixed package catpion, added style menu - - - - - 0dd4999c by Mark Lentczner at 2010-07-16T20:12:39+00:00 new output for mini_ pages - - - - - 64b2810b by Mark Lentczner at 2010-07-16T20:58:41+00:00 reformat index-frames - - - - - 3173f555 by Mark Lentczner at 2010-07-16T22:41:53+00:00 convert index to new markup - - - - - b0a4b7c9 by Mark Lentczner at 2010-07-17T04:07:22+00:00 convert index.html to new markup, adjust module markup - - - - - 8261ae1e by Mark Lentczner at 2010-07-17T05:07:29+00:00 classing styling of ancillary pages - - - - - 2a4fb025 by Mark Lentczner at 2010-07-17T05:11:45+00:00 clean up Layout.hs: no more vanillaTable - - - - - 87eec685 by Mark Lentczner at 2010-07-17T05:35:16+00:00 clean up Util.hs - - - - - d304e9b0 by Mark Lentczner at 2010-07-17T05:38:50+00:00 qualify import of XHtml as XHtml - - - - - 7dc05807 by Mark Lentczner at 2010-07-17T06:17:53+00:00 factored out head element generation - - - - - 9cdaec9e by Mark Lentczner at 2010-07-17T06:44:54+00:00 refactored out main page body generation - - - - - 8a51019e by Mark Lentczner at 2010-07-17T06:48:20+00:00 moved footer into only place that used it - - - - - efa479da by Mark Lentczner at 2010-07-17T18:48:30+00:00 styling auxillary pages for tibbe and snappy themes - - - - - 81de5509 by Mark Lentczner at 2010-07-18T04:41:38+00:00 fixed alphabet on index page, and styling of it and packages in module lists - - - - - 20718c1a by Mark Lentczner at 2010-07-18T05:34:29+00:00 cleaned up div functions in Layout.hs - - - - - 60d50453 by Mark Lentczner at 2010-07-18T05:48:39+00:00 added content div to main pages - - - - - ed16561c by Mark Lentczner at 2010-07-18T06:12:22+00:00 add .doc class to documentation blocks - - - - - f5c781b0 by Mark Lentczner at 2010-07-19T05:20:53+00:00 refactoring of anchor ID and fragment handling - - - - - a69a93bf by Mark Lentczner at 2010-07-19T05:35:55+00:00 remove an explicit bold tag - replace with .def class - - - - - d76c7225 by Mark Lentczner at 2010-07-19T06:56:15+00:00 rename Haddock.Backends.Xhtml.Util to Utils - - - - - 5a58c0da by David Waern at 2010-07-21T13:30:54+00:00 Remove trailing whitespace in Haddock.Backends.Xhtml - - - - - 0652aa17 by David Waern at 2010-07-21T13:33:21+00:00 Align a few comments - - - - - 785776c3 by David Waern at 2010-07-21T13:39:04+00:00 Remove trailing whitespace in H.B.X.Decl - - - - - 71a30710 by David Waern at 2010-07-21T13:44:27+00:00 Remove more trailing whitespace - - - - - 38750394 by David Waern at 2010-07-21T13:50:43+00:00 Style police - - - - - 3023d940 by David Waern at 2010-07-21T14:01:22+00:00 Style police in H.B.X.Decl - - - - - df16e9e6 by David Waern at 2010-07-21T14:14:45+00:00 Style police in H.B.X.DocMarkup - - - - - 6020e321 by David Waern at 2010-07-21T14:17:32+00:00 More style police - - - - - 86ad8bf5 by David Waern at 2010-07-21T14:21:02+00:00 Style police in H.B.Xhtml - - - - - aea27d03 by David Waern at 2010-07-21T14:42:03+00:00 Fix warnings in LaTeX backend - - - - - 2aff34a9 by David Waern at 2010-07-21T14:50:46+00:00 Style police in LaTeX backend (mainly more newlines) - - - - - e517162d by David Waern at 2010-07-21T15:05:47+00:00 Doc sections in Main - - - - - b971aa0c by David Waern at 2010-07-21T15:06:17+00:00 Trailing whitespace in Documentation.Haddock - - - - - f11628fb by David Waern at 2010-07-21T15:07:06+00:00 Trailing whitespace in Haddock.Convert - - - - - cbaf284c by David Waern at 2010-07-21T15:08:11+00:00 Style police in Haddock.GhcUtils - - - - - 71feb77b by David Waern at 2010-07-21T15:09:06+00:00 Style police in Haddock.InterfaceFile - - - - - 0a9c80e6 by David Waern at 2010-07-21T15:11:33+00:00 Whitespace police - - - - - 6168376c by David Waern at 2010-07-21T15:16:35+00:00 Style police in Haddock.Utils - - - - - 9fe4dd90 by David Waern at 2010-07-21T15:19:31+00:00 Add -fwarn-tabs - - - - - a000d752 by Mark Lentczner at 2010-07-20T17:25:52+00:00 move CSS Theme functions into Themes.hs - - - - - b52b440f by Mark Lentczner at 2010-07-20T17:29:35+00:00 add Thomas Schilling's theme - - - - - e43fa7e8 by Mark Lentczner at 2010-07-21T04:49:34+00:00 correct icon used with Snappy theme - - - - - ba5092d3 by Mark Lentczner at 2010-07-21T04:56:47+00:00 apply Tibbe's updates to his theme - - - - - 7804eef6 by Mark Lentczner at 2010-07-21T05:15:49+00:00 space between "Style" and the downward triangle - - - - - 7131d4c6 by Mark Lentczner at 2010-07-21T17:43:35+00:00 merge with David's source cleanups - - - - - ee65f1cb by David Waern at 2010-07-22T16:50:46+00:00 Fix a bug where we allowed --hoogle, --latex, etc without input files - - - - - e413ff7a by David Waern at 2010-07-22T17:21:58+00:00 Improve function name - - - - - a0fd14f3 by Simon Marlow at 2010-06-30T15:34:32+00:00 fix warnings - - - - - 31f73d2a by David Waern at 2010-07-22T19:29:41+00:00 Solve conflicts - - - - - d563b4a5 by Simon Marlow at 2010-06-30T15:34:37+00:00 fix warning - - - - - 412b6469 by David Waern at 2010-07-22T19:31:28+00:00 Solve conflict - - - - - 35174b94 by Ian Lynagh at 2010-07-06T17:27:16+00:00 Follow mkPState argument order change - - - - - b5c3585c by Simon Marlow at 2010-07-14T08:49:21+00:00 common up code for instance rendering - - - - - d8009560 by Simon Marlow at 2010-07-14T12:37:11+00:00 fix warnings - - - - - a6d88695 by David Waern at 2010-07-24T15:33:33+00:00 Fix build with ghc < 6.13 - - - - - 94cf9de1 by David Waern at 2010-07-24T15:34:37+00:00 Remove conflict left-over - - - - - 313b15c0 by Mark Lentczner at 2010-07-21T22:09:04+00:00 reorganization of nhaddock.css with tibbe - - - - - 9defed80 by Mark Lentczner at 2010-07-21T22:42:14+00:00 further cleanup of nhaddock.css, float TOC, support aux. pages - - - - - 6d944c1b by Mark Lentczner at 2010-07-22T06:22:23+00:00 remove old HTML backend - - - - - b3e8cba5 by Mark Lentczner at 2010-07-22T06:43:32+00:00 remove --html-help support - it was old, out-of-date, and mostly missing - - - - - d2654a08 by Mark Lentczner at 2010-07-22T21:45:34+00:00 tweaks to nhaddock.css - - - - - f73b285c by Mark Lentczner at 2010-07-23T06:19:35+00:00 command like processing for theme selection The bulk of the change is threadnig the selected theme set through functions in Xhtml.hs so that the selected themes can be used when generating the page output. There isn't much going on in most of these changes, just passing it along. The real work is all done in Themes.hs. - - - - - 8bddc90d by Mark Lentczner at 2010-07-23T06:58:31+00:00 drop --themes support, add named theme support decided that --themes was silly - no one would do that, just use multiple --theme arguments made --theme a synonym for --css and -c made those arguments, if no file is found, look up the argument as the name of a built in theme all of this let's haddock be invoked with "--theme=classic" for example. - - - - - 20cafd4f by Mark Lentczner at 2010-07-23T17:44:29+00:00 rename --default-themes to --built-in-themes - - - - - 0fe41307 by Mark Lentczner at 2010-07-23T18:33:02+00:00 tweaks to theme for info table, headings, and tables - - - - - cba4fee0 by Mark Lentczner at 2010-07-23T19:13:59+00:00 tweaks for dl layout, though still not used - - - - - 463fa294 by Mark Lentczner at 2010-07-23T21:07:19+00:00 tweak look of mini pages, keywords, and preblocks - - - - - 5472fc02 by Mark Lentczner at 2010-07-24T05:36:15+00:00 slide out Synopsis drawer - - - - - 9d5d5de5 by Mark Lentczner at 2010-07-24T06:02:42+00:00 extend package header and footer to edges of page - - - - - a47c91a2 by Mark Lentczner at 2010-07-24T06:28:44+00:00 fields are def lists, tweak css for style menu, mini pages, arguments - - - - - ca20f23b by Mark Lentczner at 2010-07-24T16:55:22+00:00 excisting last vestiges of the --xhtml flag - - - - - 71fb012e by Mark Lentczner at 2010-07-25T18:47:49+00:00 change how collapsing sections are done make whole .caption be the target improve javascript for class toggling have plus/minus images come from .css, not img tags - - - - - c168c8d3 by Mark Lentczner at 2010-07-26T00:32:05+00:00 reorganize files in the html lib data dir - - - - - 93324301 by Mark Lentczner at 2010-07-26T01:27:42+00:00 cleaned up Themes.hs - - - - - ad3b5dd4 by Mark Lentczner at 2010-07-26T02:39:15+00:00 make module list use new collapsers - - - - - 1df9bfc6 by Mark Lentczner at 2010-07-27T19:09:25+00:00 remove Tibbe theme - - - - - 8b9b01b3 by Mark Lentczner at 2010-07-27T20:04:03+00:00 move themes into html dir with .theme and .std-theme extensions - - - - - a7beb965 by Mark Lentczner at 2010-07-27T21:06:34+00:00 give a class to empty dd elements so they can be hidden - - - - - a258c117 by Mark Lentczner at 2010-07-27T21:23:58+00:00 remove custom version of copyFile in Xhtml.hs - - - - - b70dba6e by Mark Lentczner at 2010-07-27T22:12:45+00:00 apply margin changes to pre and headings as per group decision, and small cleanups - - - - - e6f722a2 by Mark Lentczner at 2010-07-28T00:03:12+00:00 make info block and package bar links be floatable by placing them first in the dom tree - - - - - c8278867 by Mark Lentczner at 2010-07-28T19:01:18+00:00 styling source links on declarations - - - - - 88fdc399 by Mark Lentczner at 2010-07-29T01:12:46+00:00 styling tweaks don't generate an empty li for absent style menu in links area update css for Classic and Snappy to handle: dl lists links in package header and in declarations floating of links and info block in package and module headers - - - - - 8a75b213 by Ian Lynagh at 2010-07-30T20:21:46+00:00 Fix build in GHC tree - - - - - ce8e18b3 by Simon Hengel at 2010-08-03T18:37:26+00:00 Adapt paths to data files in cabal file - - - - - 9701a455 by Simon Hengel at 2010-08-07T13:20:27+00:00 Add missing dependency to cabal file - - - - - 01b838d1 by Mark Lentczner at 2010-07-30T20:19:40+00:00 improved synopsis drawer: on click, not hover - - - - - 7b6f3e59 by Mark Lentczner at 2010-07-30T23:38:55+00:00 put the synopsis back in the other themes - - - - - 7b2904c9 by Mark Lentczner at 2010-08-11T11:11:26+00:00 close arrows on expanded synopsis drawer - - - - - ea19e177 by Mark Lentczner at 2010-08-12T21:16:45+00:00 width and font changes removed the max width restrictions on the page as a whole and the synopsis made the main font size smaller (nominally 14pt) and then tweaked most font sizes (relative) to be more consistent - - - - - 5ced00c0 by Mark Lentczner at 2010-08-13T15:09:55+00:00 implemented YUI's CSS font approach - - - - - 2799c548 by Mark Lentczner at 2010-08-13T15:11:59+00:00 adjusted margin to 2em, 1 wasn't enough - - - - - 58f06893 by Mark Lentczner at 2010-08-13T15:48:44+00:00 removed underlining on hover for named anchors headings in interface lost thier a element, no need, just put id on heading css for a elements now only applies to those with href attribute - - - - - 7aced4c4 by Mark Lentczner at 2010-08-13T15:50:22+00:00 more space between elements - - - - - 5a3c1cce by Mark Lentczner at 2010-08-13T16:43:43+00:00 adjusted font sizes of auxilary pages per new scheme - - - - - 487539ef by Mark Lentczner at 2010-08-13T21:43:41+00:00 add Frames button and clean up frames.html - - - - - c1a140b6 by Mark Lentczner at 2010-08-13T22:17:48+00:00 move frames button to js - - - - - b0bdb68e by Mark Lentczner at 2010-08-14T03:44:46+00:00 build style menu in javascript moved to javascript, so as to not polute the content with the style menu removed menu building code in Themes.hs removed onclick in Utils.hs changed text of button in header from "Source code" to "Source" more consistent with links in rest of page - - - - - 43ab7120 by Mark Lentczner at 2010-08-16T15:15:37+00:00 font size and margin tweaks - - - - - c0b68652 by Mark Lentczner at 2010-08-17T18:19:52+00:00 clean up collapser logics javascript code for collapasble sections cleaned up rewrote class utilities in javascript to be more robust refactored utilities for generating collapsable sections made toc be same color as synopsis module list has needed clear attribute in CSS - - - - - 5d573427 by Mark Lentczner at 2010-08-17T23:06:02+00:00 don't collapse entries in module list when clicking on links - - - - - 8c307c4a by Mark Lentczner at 2010-08-17T23:21:43+00:00 add missing data file to .cabal - - - - - 414bcfcf by Mark Lentczner at 2010-08-17T23:28:47+00:00 remove synopsis when in frames - - - - - ba0fa98a by Mark Lentczner at 2010-08-18T16:16:11+00:00 layout tweeks - mini page font size, toc color, etc. - - - - - 63c1bed1 by Mark Lentczner at 2010-08-18T19:50:02+00:00 margin fiddling - - - - - c311c094 by Mark Lentczner at 2010-08-20T01:37:55+00:00 better synopsis handling logic - no flashing - - - - - f1fe5fa8 by Mark Lentczner at 2010-08-20T01:41:06+00:00 fix small layout issues mini frames should have same size top heading give info block dts some padding so they don't collide in some browsers - - - - - 0de84d77 by Mark Lentczner at 2010-08-20T02:13:09+00:00 made style changing and cookies storage robust - - - - - 1ef064f9 by Thomas Schilling at 2010-08-04T13:12:22+00:00 Make synopsis frame behave properly in Firefox. In Firefox, pressing the back button first reverted the synopsis frame, and only clicking the back button a second time would update the main frame. - - - - - dd1c9a94 by Mark Lentczner at 2010-08-21T01:46:19+00:00 remove Snappy theme - - - - - 2353a90d by Mark Lentczner at 2010-08-25T05:16:19+00:00 fix occasional v.scroll bars on pre blocks (I think) - - - - - 459b8bf1 by Simon Hengel at 2010-08-08T10:12:45+00:00 Add createInterfaces' (a more high-level alternative to createInterfaces) to Haddock API - - - - - b1b68675 by David Waern at 2010-08-26T20:31:58+00:00 Follow recent API additions with some refactorings Simon Hegel's patch prompted me to do some refactorings in Main, Haddock.Documentation and Haddock.Interface. - - - - - 264d4d67 by David Waern at 2010-08-26T21:40:59+00:00 Get rid of GhcModule and related cruft We can get everything we need directly from TypecheckedModule. - - - - - 0feacec2 by Mark Lentczner at 2010-08-26T23:44:13+00:00 fixed CSS for ordered lists and def lists in doc blocks - - - - - 2997e0c2 by Mark Lentczner at 2010-08-26T23:45:03+00:00 support both kinds of enumerated lists in doc markup The documentation for Haddock says enumerated lists can use either of (1) first item 2. second item The second form wasn't actually supported - - - - - 5d4ddeec by Mark Lentczner at 2010-08-27T21:29:48+00:00 fix broken header link margins - - - - - 614456ba by Mark Lentczner at 2010-08-27T22:16:19+00:00 fix table of contents CSS - - - - - 03f329a2 by David Waern at 2010-08-28T16:36:09+00:00 Update tests following switch to the Xhtml backend - - - - - ca689fa2 by Mark Lentczner at 2010-08-28T18:25:16+00:00 fix def lists - - - - - 18e1d3d2 by Mark Lentczner at 2010-08-28T18:26:18+00:00 push footer to bottom of window - - - - - b0ab8d82 by David Waern at 2010-08-28T22:04:32+00:00 Whitespace police - - - - - 2d217977 by David Waern at 2010-08-29T12:44:45+00:00 Remove Snappy data files - - - - - 01e27d5f by David Waern at 2010-08-29T13:03:28+00:00 Add source entity path to --read-interface You can now use this flag like this: --read-interface=<html path>,<source entity path>,<.haddock file> By "source entity path" I mean the same thing that is specified with the --source-entity flag. The purpose of this is to be able to specify the source entity path per package, to allow source links to work in the presence of cross-package documentation. When given two arguments or less the --read-interface flag behaves as before. - - - - - 20bf4aaa by David Waern at 2010-08-29T13:11:03+00:00 Naming wibbles - - - - - ad22463f by Mark Lentczner at 2010-08-29T15:14:54+00:00 make portability block be a table - solves layout issues - - - - - 97bd1ae6 by Mark Lentczner at 2010-08-29T15:17:42+00:00 update golden test for Test due to portability box change - - - - - d37e139e by Mark Lentczner at 2010-08-29T17:07:17+00:00 move TOC and Info blocks down 0.5em to improve layout issue w/Test.hs - - - - - acf52501 by David Waern at 2010-08-29T17:32:36+00:00 Allow building with ghc < 6.16 - - - - - 1cb34ed8 by Ian Lynagh at 2010-07-24T23:18:49+00:00 Flatten the dynflags before parsing - - - - - b36845b4 by Ian Lynagh at 2010-07-24T23:26:49+00:00 Follow flattenLanguageFlags -> flattenExtensionFlags rename - - - - - 7f7fcc7e by David Waern at 2010-08-29T17:46:23+00:00 Use flattenExtensionFlags with ghc >= 6.13 only - - - - - 13cf9411 by Ian Lynagh at 2010-08-01T18:09:54+00:00 Make the main haddock script versioned, and make plain "haddock" a symlink - - - - - 495cbff2 by Ian Lynagh at 2010-08-18T18:57:24+00:00 Fix installation in the GHC build system Data-files are now in subdirectories, so we need to handle that - - - - - 88ebab0a by Ian Lynagh at 2010-08-18T19:43:53+00:00 GHC build system: Add all the data files to BINDIST_EXTRAS - - - - - 65837172 by David Waern at 2010-08-29T20:12:34+00:00 Update Test - - - - - 094bbaa2 by David Waern at 2010-08-29T20:55:14+00:00 Revert update to Test - - - - - a881cfb3 by David Waern at 2010-08-31T18:24:15+00:00 Bump version number - - - - - 1fc8a3eb by David Waern at 2010-08-31T22:32:27+00:00 Update ANNOUNCE - - - - - ee1df9d0 by David Waern at 2010-08-31T22:33:11+00:00 Update CHANGES - - - - - 394cc854 by David Waern at 2010-08-31T22:33:23+00:00 Update interface file versioning to work with ghc 6.14/15 - - - - - 7d03b79b by David Waern at 2010-08-31T22:36:00+00:00 Update test output following version change - - - - - a48d82d1 by Mark Lentczner at 2010-09-01T04:29:35+00:00 sort options in doc to match --help output removed --html-help option, as it is no longer supported - - - - - 06561aeb by Mark Lentczner at 2010-09-01T05:29:32+00:00 update options documentation rewrote doc for --html added doc for --theme and --built-in-themes added --use-contents and --gen-contents - - - - - 57dea832 by Mark Lentczner at 2010-09-01T05:31:27+00:00 slight wording change about Frames mode - - - - - fa1f6da3 by David Waern at 2010-09-01T10:57:44+00:00 Update doc configure script to find docbook stylesheets on arch linux - - - - - addff770 by David Waern at 2010-09-01T11:02:29+00:00 Wibble - - - - - 8399006d by David Waern at 2010-09-01T11:19:21+00:00 Replace ghci> with >>> in example syntax - - - - - 35074cf8 by David Waern at 2010-09-01T19:03:27+00:00 Improve docs for --no-tmp-comp-dir - - - - - 0f8f8cfd by David Waern at 2010-09-02T11:22:27+00:00 Add a list of contributors to the user guide Break out everyone thanked in the `Acknowledgements` chapter into a separate contributor list and add everyone from `darcs show authors`. We consider everyone who is thanked to be a contributor as a conservative estimation :-) I have added some more contributors that I know about, who were not in the darcs history, but others may be missing. So please add anyone that you think is missing from the list. - - - - - 42ccf099 by David Waern at 2010-09-02T11:29:22+00:00 Update copyright years in license - - - - - 0d560479 by David Waern at 2010-09-02T11:38:52+00:00 Update release instructions - - - - - 72ab7796 by David Waern at 2010-09-02T19:27:08+00:00 Add a note to ANNOUNCE - - - - - bf9d9c5d by David Waern at 2010-09-02T19:27:48+00:00 H.Utils needs FFI on Win+MinGW - - - - - 048ae44a by Mark Lentczner at 2010-09-04T23:19:47+00:00 make TOC group header identifiers validate - - - - - 8c6faf36 by Simon Michael at 2010-09-22T07:12:34+00:00 add hints for cleaner darcs show authors output - - - - - 9909bd17 by Simon Michael at 2010-09-22T17:58:06+00:00 print haddock coverage info on stdout when generating docs A module's haddockable items are its exports and the module itself. The output is lightly formatted so you can align the :'s and sort for readability. - - - - - 6da72171 by David Waern at 2010-10-03T21:31:24+00:00 Style wibble - - - - - 2f8d8e4d by Tobias Brandt at 2010-08-27T07:01:21+00:00 adding the option to fully qualify identifiers - - - - - 833be6c6 by Tobias Brandt at 2010-08-27T15:50:28+00:00 adding support for local and relative name qualification - - - - - df15c4e9 by Tobias Brandt at 2010-08-27T15:56:37+00:00 corrected qualification help message - - - - - 449e9ce1 by David Waern at 2010-10-16T17:34:30+00:00 Solve conflicts - - - - - 3469bda5 by David Waern at 2010-10-16T18:42:40+00:00 Use "qual" as an abbreviation for qualification instead of "quali" for consistency - - - - - 97c2d728 by David Waern at 2010-10-16T18:47:07+00:00 Style police - - - - - ce14fbea by David Waern at 2010-10-16T21:15:25+00:00 Style police - - - - - fdf29e9d by David Waern at 2010-10-17T00:30:44+00:00 Add a pointer to the style guide - - - - - 8e6b44e8 by rrnewton at 2010-10-24T03:19:28+00:00 Change to index pages: include an 'All' option even when subdividing A-Z. - - - - - 755b131c by David Waern at 2010-11-14T19:39:36+00:00 Bump version - - - - - d0345a04 by David Waern at 2010-11-14T19:41:59+00:00 TAG 2.8.1 - - - - - f6221508 by Simon Peyton Jones at 2010-09-13T09:53:00+00:00 Adapt to minor changes in internal GHC functions - - - - - 1290713d by Ian Lynagh at 2010-09-15T10:37:18+00:00 Remove duplicate Outputable instance for Data.Map.Map - - - - - 87f69eef by Ian Lynagh at 2010-09-21T15:01:10+00:00 Bump GHC dep upper bound - - - - - af36e087 by Ian Lynagh at 2010-09-21T15:12:02+00:00 Fix up __GLASGOW_HASKELL__ tests - - - - - ad67716c by Ian Lynagh at 2010-09-21T20:31:35+00:00 Don't build haddock is HADDOCK_DOCS is NO - - - - - 63b3f1f5 by Ian Lynagh at 2010-09-21T21:39:51+00:00 Fixes for when HADDOCK_DOCS=NO - - - - - e92bfa42 by Ian Lynagh at 2010-09-29T21:15:38+00:00 Fix URL creation on Windows: Use / not \ in URLs. Fixes haskell/haddock#4353 - - - - - 66c55e05 by Ian Lynagh at 2010-09-30T17:03:34+00:00 Tidy up haddock symlink installation In particular, it now doesn't get created if we aren't installing haddock. - - - - - 549b5556 by Ian Lynagh at 2010-10-23T21:17:14+00:00 Follow extension-flattening change in GHC - - - - - d7c2f72b by David Waern at 2010-11-14T20:17:55+00:00 Bump version to 2.8.2 - - - - - 6989a3a9 by David Waern at 2010-11-14T20:26:01+00:00 Solve conflict - - - - - 055c6910 by Ian Lynagh at 2010-09-22T15:36:20+00:00 Bump GHC dep - - - - - c96c0763 by Simon Marlow at 2010-10-27T11:09:44+00:00 follow changes in the GHC API - - - - - 45907129 by David Waern at 2010-11-07T14:00:58+00:00 Update the HCAR entry - - - - - 61940b95 by David Waern at 2010-11-07T14:07:34+00:00 Make the HCAR entry smaller - - - - - aa590b7d by David Waern at 2010-11-14T21:30:59+00:00 Update HCAR entry with November 2010 version - - - - - 587f9847 by David Waern at 2010-11-14T23:48:17+00:00 Require ghc >= 7.0 - - - - - ff5c647c by David Waern at 2010-11-14T23:49:09+00:00 TAG 2.8.2 - - - - - 937fcb4f by David Waern at 2010-11-14T23:49:45+00:00 Solve conflict - - - - - 8e5d0c1a by David Waern at 2010-11-15T21:09:50+00:00 Remove code for ghc < 7 - - - - - 3d47b70a by David Waern at 2010-11-15T21:11:06+00:00 Fix bad merge - - - - - 7f4a0d8a by David Waern at 2010-11-15T21:13:57+00:00 Remove more ghc < 7 code - - - - - 9ee34b50 by David Waern at 2010-11-15T21:31:25+00:00 Match all AsyncExceptions in exception handler - - - - - 42849c70 by David Waern at 2010-11-15T21:35:31+00:00 Just say "internal error" instead of "internal Haddock or GHC error" - - - - - c88c809b by David Waern at 2010-11-15T21:44:19+00:00 Remove docNameOcc under the motto "don't name compositions" - - - - - b798fc7c by David Waern at 2010-11-15T23:27:13+00:00 Wibble - - - - - 2228197e by David Waern at 2010-11-15T23:28:24+00:00 Rename the HCAR entry file - - - - - 8a3f9090 by David Waern at 2010-11-16T00:05:29+00:00 Remove Haskell 2010 extensions from .cabal file - - - - - c7a0c597 by David Waern at 2010-11-16T00:10:28+00:00 Style wibbles - - - - - cde707a5 by David Waern at 2010-11-16T00:12:00+00:00 Remove LANGUAGE ForeignFunctionInterface pragmas - - - - - 1dbda8ed by David Waern at 2010-11-16T00:17:21+00:00 Make a little more use of DoAndIfThenElse - - - - - 4c45ff6e by David Waern at 2010-11-16T00:59:41+00:00 hlint police - - - - - d2feaf09 by David Waern at 2010-11-16T01:14:15+00:00 hlint police - - - - - 99876e97 by David Waern at 2010-11-20T19:06:00+00:00 Haddock documentation updates - - - - - 65ce6987 by David Waern at 2010-11-20T19:42:51+00:00 Follow the style guide closer in Haddock.Types and improve docs - - - - - 28ca304a by tob.brandt at 2010-11-20T17:04:40+00:00 add full qualification for undocumented names - - - - - d61341e3 by David Waern at 2010-11-20T20:04:15+00:00 Re-structure qualification code a little - - - - - 0057e4d6 by David Waern at 2010-11-20T20:07:55+00:00 Re-order functions - - - - - d7279afd by David Waern at 2010-11-21T03:39:54+00:00 Add BangPatterns to alex and happy source files - - - - - 629fe60e by tob.brandt at 2010-11-23T23:35:11+00:00 documentation for qualification - - - - - 37031cee by David Waern at 2010-11-23T21:06:44+00:00 Update CHANGES - don't mention 2.8.2, we won't release it - - - - - f2489e19 by David Waern at 2010-12-01T21:57:11+00:00 Update deps of runtests.hs to work with ghc 7.0.1 - - - - - d3657e9a by David Waern at 2010-12-01T22:04:57+00:00 Make tests compile with ghc 7.0.1 - - - - - a2f09d9b by David Waern at 2010-12-01T22:06:59+00:00 Update tests following version bump - - - - - 50883ebb by David Waern at 2010-12-06T14:09:18+00:00 Update tests following recent changes - - - - - fc2fadeb by David Waern at 2010-12-06T14:17:29+00:00 Add a flag --pretty-html for rendering indented html with newlines - - - - - 30832ef2 by David Waern at 2010-12-06T14:17:35+00:00 Use --pretty-html when running the test suite. Makes it easier to compare output - - - - - a0b81b31 by David Waern at 2010-12-06T14:18:27+00:00 Wibble - - - - - 3aaa23fe by David Waern at 2010-12-06T14:19:29+00:00 Haddockify ppHtml comments - - - - - 24bb24f0 by David Waern at 2010-12-06T14:23:15+00:00 Remove --debug. It was't used, and --verbosity should take its place - - - - - 6bc076e5 by David Waern at 2010-12-06T14:25:37+00:00 Rename golden-tests into html-tests. "golden tests" sounds strange - - - - - 53301e55 by David Waern at 2010-12-06T14:26:26+00:00 QUALI -> QUAL in the description --qual for consistency - - - - - 98b6affb by David Waern at 2010-12-06T21:54:02+00:00 Bump version - - - - - 371bf1b3 by David Waern at 2010-12-06T22:08:55+00:00 Update tests following version bump - - - - - 25be762d by David Waern at 2010-12-06T22:21:03+00:00 Update CHANGES - - - - - 7c7dac71 by David Waern at 2010-12-06T22:33:43+00:00 Update ANNOUNCE - - - - - 30d7a5f2 by Simon Peyton Jones at 2010-11-15T08:38:38+00:00 Alex generates BangPatterns, so make Lex.x accept them (It'd be better for Alex to generate this pragma.) - - - - - 605e8018 by Simon Marlow at 2010-11-17T11:37:24+00:00 Add {-# LANGUAGE BangPatterns #-} to mollify GHC - - - - - a46607ba by David Waern at 2010-12-07T14:08:10+00:00 Solve conflicts - - - - - b28cda66 by David Waern at 2010-12-09T20:41:35+00:00 Docs: Mention that \ is a special character in markup - - - - - a435bfdd by Ian Lynagh at 2010-11-17T14:01:19+00:00 TAG GHC 7.0.1 release - - - - - 5a15a05a by David Waern at 2010-12-11T17:51:19+00:00 Fix indentation problem - - - - - 4232289a by Lennart Kolmodin at 2010-12-17T18:32:03+00:00 Revise haddock.cabal given that we now require ghc-7 default-language should be Haskell2010, slight new semantics for extensions. Rewrite into clearer dependencies of base and Cabal. - - - - - a36302dc by David Waern at 2010-12-19T17:12:37+00:00 Update CHANGES - - - - - 7c8b85b3 by David Waern at 2010-12-19T17:14:24+00:00 Bump version - - - - - cff22813 by Ian Lynagh at 2011-01-05T18:24:27+00:00 Write hoogle output in utf8; fixes GHC build on Windows - - - - - c7e762ea by David Waern at 2011-01-22T00:00:35+00:00 Put title outside doc div when HTML:fying title+prologue Avoids indenting the title, and makes more sense since the title is not a doc string anyway. - - - - - 5f639054 by David Waern at 2011-01-22T16:09:44+00:00 Fix spelling error - contributed by Marco Silva - - - - - c11dce78 by Ian Lynagh at 2011-01-07T02:33:11+00:00 Follow GHC build system changes - - - - - 101cfaf5 by David Waern at 2011-01-08T14:06:44+00:00 Bump version - - - - - af62348b by David Waern at 2011-01-08T14:07:07+00:00 TAG 2.9.2 - - - - - 4d1f6461 by Ian Lynagh at 2011-01-07T23:06:57+00:00 Name the haddock script haddock-ghc-7.0.2 instead of haddock-7.0.2; haskell/haddock#4882 "7.0.2" looked like a haddock version number before - - - - - 8ee4d5d3 by Simon Peyton Jones at 2011-01-10T17:31:12+00:00 Update Haddock to reflect change in hs_tyclds field of HsGroup - - - - - 06f3e3db by Ian Lynagh at 2011-03-03T15:02:37+00:00 TAG GHC 7.0.2 release - - - - - 7de0667d by David Waern at 2011-03-10T22:47:13+00:00 Update CHANGES - - - - - 33a9f1c8 by David Waern at 2011-03-10T22:47:31+00:00 Fix build with ghc 7.0.1 - - - - - 4616f861 by David Waern at 2011-03-10T22:47:50+00:00 TAG 2.9.2-actual - - - - - 0dab5e3c by Simon Hengel at 2011-04-08T15:53:01+00:00 Set shell script for unit tests back to work - - - - - 85c54dee by Simon Hengel at 2011-04-08T16:01:24+00:00 Set unit tests back to work Here "ghci>" was still used instead of ">>>". - - - - - 1cea9b78 by Simon Hengel at 2011-04-08T16:25:36+00:00 Update runtests.hs for GHC 7.0.2 - - - - - 8e5b3bbb by Simon Hengel at 2011-04-08T16:28:49+00:00 Update Haddock version in *.html.ref - - - - - 2545e955 by Simon Hengel at 2011-04-08T17:09:28+00:00 Add support for blank lines in the result of examples Result lines that only contain the string "<BLANKLINE>" are treated as a blank line. - - - - - adf64d2e by Simon Hengel at 2011-04-08T17:36:50+00:00 Add documentation for "support for blank lines in the result of examples" - - - - - c51352ca by David Waern at 2011-05-21T23:57:56+00:00 Improve a haddock comment - - - - - 7419cf2c by David Waern at 2011-05-22T15:41:52+00:00 Use cabal's test suite support to run the test suite This gives up proper dependency tracking of the test script. - - - - - 7770070c by David Waern at 2011-05-22T01:45:44+00:00 We don't need to send DocOptions nor a flag to mkExportItems - - - - - 9d95b7b6 by David Waern at 2011-05-22T21:39:03+00:00 Fix a bug - - - - - 1f93699b by David Waern at 2011-05-22T21:40:21+00:00 Break out fullContentsOf, give it a better name and some documentation The documentation describes how we want this function to eventually behave, once we have fixed a few problems with the current implementation. - - - - - 9a86432f by David Waern at 2011-05-22T21:53:52+00:00 Fix some stylistic issues in mkExportItems - - - - - c271ff0c by David Waern at 2011-05-22T22:09:11+00:00 Indentation - - - - - 93e602b1 by David Waern at 2011-06-10T01:35:31+00:00 Add git commits since switchover: darcs format (followed by a conflict resolution): commit 6f92cdd12d1354dfbd80f8323ca333bea700896a Merge: f420cc4 28df3a1 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Thu May 19 17:54:34 2011 +0100 Merge remote branch 'origin/master' into ghc-generics commit 28df3a119f770fdfe85c687dd73d5f6712b8e7d0 Author: Max Bolingbroke <batterseapower at hotmail.com> Date: Sat May 14 22:37:02 2011 +0100 Unicode fix for getExecDir on Windows commit 89813e729be8bce26765b95419a171a7826f6d70 Merge: 6df3a04 797ab27 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 9 11:55:17 2011 +0100 Merge branch 'ghc-new-co' commit 6df3a040da3dbddee67c6e30a892f87e6b164383 Author: Ian Lynagh <igloo at earth.li> Date: Sun May 8 17:05:50 2011 +0100 Follow changes in SDoc commit f420cc48b9259f0b1afd2438b12f9a2bde57053d Author: Jose Pedro Magalhaes <jpm at cs.uu.nl> Date: Wed May 4 17:31:52 2011 +0200 Adapt haddock to the removal of HsNumTy and TypePat. commit 797ab27bdccf39c73ccad374fea265f124cb52ea Merge: 1d81436 5a91450 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:05:03 2011 +0100 Merge remote branch 'origin/master' into ghc-new-co commit 1d8143659a81cf9611668348e33fd0775c7ab1d2 Author: Simon Peyton Jones <simonpj at microsoft.com> Date: Mon May 2 12:03:46 2011 +0100 Wibbles for ghc-new-co branch commit 5a91450e2ea5a93c70bd3904b022445c9cc82488 Author: Ian Lynagh <igloo at earth.li> Date: Fri Apr 22 00:51:56 2011 +0100 Follow defaultDynFlags change in GHC - - - - - 498da5ae by David Waern at 2011-06-11T00:33:33+00:00 * Merge in git patch from Michal Terepeta >From 6fc71d067738ef4b7de159327bb6dc3d0596be29 Mon Sep 17 00:00:00 2001 From: Michal Terepeta <michal.terepeta at gmail.com> Date: Sat, 14 May 2011 19:18:22 +0200 Subject: [PATCH] Follow the change of TypeSig in GHC. This follows the change in GHC to make TypeSig take a list of names (instead of just one); GHC ticket haskell/haddock#1595. This should also improve the Haddock output in case the user writes a type signature that refers to many names: -- | Some comment.. foo, bar :: ... will now generate the expected output with one signature for both names. - - - - - 094607fe by Ian Lynagh at 2011-06-17T19:10:29+01:00 Fix build - - - - - 8fa35740 by Ian Lynagh at 2011-06-26T21:06:40+01:00 Bump GHC dep to allow 7.2 - - - - - e4d2ca3c by Ian Lynagh at 2011-07-07T23:06:28+01:00 Relax base dep - - - - - b948fde9 by Ian Lynagh at 2011-07-28T16:39:45+01:00 GHC build system: Don't install the datafiles twice - - - - - f82f6d70 by Simon Marlow at 2011-08-11T12:08:15+01:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - b341cc12 by Max Bolingbroke at 2011-08-22T20:25:27+01:00 Fix compilation with no-pred-ty GHC - - - - - 30494581 by Max Bolingbroke at 2011-08-23T10:20:54+01:00 Remaining fixes for PredTy removal - - - - - 0b197138 by Max Bolingbroke at 2011-08-26T08:27:45+01:00 Rename factKind to constraintKind - - - - - a379bec5 by Max Bolingbroke at 2011-09-04T12:54:47+01:00 Deal with change to IParam handling in GHC - - - - - f94e421b by Max Bolingbroke at 2011-09-06T17:34:31+01:00 Adapt Haddock for the ConstraintKind extension changes - - - - - 8821e5cc by Max Bolingbroke at 2011-09-09T08:24:59+01:00 Ignore associated type defaults (just as we ignore default methods) - - - - - 31a0afd4 by Max Bolingbroke at 2011-09-09T09:06:00+01:00 Merge branch 'no-pred-ty' of ssh://darcs.haskell.org/srv/darcs/haddock into no-pred-ty - - - - - dd3b530a by Max Bolingbroke at 2011-09-09T14:10:25+01:00 Merge branch 'no-pred-ty' Conflicts: src/Haddock/Convert.hs - - - - - 5f25ec96 by Max Bolingbroke at 2011-09-09T14:10:40+01:00 Replace FactTuple with ConstraintTuple - - - - - cd30b9cc by David Waern at 2011-09-26T02:17:55+02:00 Bump to version 2.9.3 - - - - - 4fbfd397 by Max Bolingbroke at 2011-09-27T14:55:21+01:00 Follow changes to BinIface Name serialization - - - - - 92257d90 by David Waern at 2011-09-30T23:45:07+02:00 Fix problem with test files not added to distribution tarball - - - - - 00255bda by David Waern at 2011-09-30T23:48:24+02:00 Merge branch 'development' - - - - - 5421264f by David Waern at 2011-10-01T01:25:39+02:00 Merge in darcs patch from Simon Meier: Wed Jun 1 19:41:16 CEST 2011 iridcode at gmail.com * prettier haddock coverage info The new coverage info rendering uses less horizontal space. This reduces the number of unnecessary line-wrappings. Moreover, the most important information, how much has been documented already, is now put up front. Hopefully, this makes it more likely that a library author is bothered by the low coverage of his modules and fixes that issue ;-) - - - - - 07d318ef by David Waern at 2011-10-01T01:34:10+02:00 Use printException instead of deprecated printExceptionAndWarnings - - - - - 40d52ee4 by David Waern at 2011-10-01T01:41:13+02:00 Merge in darcs pach: Mon Apr 11 18:09:54 JST 2011 Liyang HU <haddock at liyang.hu> * Remember collapsed sections in index.html / haddock-util.js - - - - - 279d6dd4 by David Waern at 2011-10-01T01:55:45+02:00 Merge in darcs patch: Joachim Breitner <mail at joachim-breitner.de>**20110619201645 Ignore-this: f6c51228205b0902ad5bfad5040b989a As reported on http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=578301, generating the global index takes much too long if type-level (with lots of auto-generated types) is installed. The patch avoids a quadratic runtime in the subfunction getIfaceIndex of ppHtmlIndex by using a temporary set. Runtime improvement observed here from 25.36s to 2.86s. - - - - - d1612383 by David Waern at 2011-10-01T01:56:48+02:00 Merge branch 'development' - - - - - 347520c1 by David Waern at 2011-10-01T01:56:54+02:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9a0c95e8 by David Waern at 2011-10-01T02:19:10+02:00 Improve .cabal file - - - - - 6967dc64 by Ian Lynagh at 2011-10-01T01:34:06+01:00 Follow changes to ForeignImport/ForeignExport in GHC - - - - - 565cb26b by Simon Marlow at 2011-10-04T00:15:04+02:00 Hack this to make it work with both Alex 2.x and Alex 3.x. Unicode in documentation strings is (still) mangled. I don't think it's possible to make it so that we get the current behaviour with Alex 2.x but magic Unicode support if you use Alex 3.x. At some point we have to decide that Alex 3.x is a requirement, then we can do Unicode. - - - - - 8b74f512 by David Waern at 2011-10-04T00:18:17+02:00 Requre ghc >= 7.2 - - - - - 271d360c by David Waern at 2011-10-04T00:22:50+02:00 Bump version to 2.9.4 - - - - - 37f3edb0 by David Waern at 2011-10-06T02:30:21+02:00 Add alex and happy to build-tools. - - - - - 7ac2bb6e by David Terei at 2011-10-12T14:02:55-07:00 Add safe haskell indication to haddock output - - - - - 42c91a47 by David Terei at 2011-10-12T14:06:03-07:00 Fix CSS issue with info table not being contained in module header - - - - - 0eddab6c by David Terei at 2011-10-12T14:06:58-07:00 Add safe haskell indication to haddock output - - - - - 3df058eb by David Terei at 2011-10-12T14:07:07-07:00 Fix CSS issue with info table not being contained in module header - - - - - a40a6c3f by David Waern at 2011-10-22T11:29:06+02:00 Bump .haddock file version since the format has changed recently - - - - - 8a6254be by David Waern at 2011-10-22T11:30:42+02:00 Merge branch 'development' - - - - - 642e3e02 by David Waern at 2011-10-23T21:23:39+02:00 Sort import list - - - - - 36371cf8 by David Waern at 2011-10-23T22:48:18+02:00 Remove NEW_GHC_LAYOUT conditional. - - - - - 5604b499 by David Waern at 2011-10-27T00:15:03+02:00 Add --print-ghc-path. - - - - - 463499fa by David Waern at 2011-10-27T00:16:22+02:00 Make testsuite able to find its dependencies automatically. - - - - - a3506172 by Ryan Newton at 2011-11-05T05:59:58-04:00 Improved declNames internal error. Added a case to handle DocD. - - - - - 001b8baf by David Waern at 2011-11-05T20:37:29+01:00 Rename copy.hs -> accept.hs. - - - - - 55d808d3 by David Waern at 2011-11-05T23:30:02+01:00 Fix build. - - - - - deb5c3be by David Waern at 2011-11-06T00:01:47+01:00 Merge branch 'master' of http://darcs.haskell.org/haddock - - - - - 9b663554 by David Waern at 2011-11-06T00:03:45+01:00 Merge https://github.com/rrnewton/haddock - - - - - 1abb0ff6 by David Waern at 2011-11-06T01:20:37+01:00 Use getDeclMainBinder instead of declNames. - - - - - 4b005c01 by David Waern at 2011-11-06T19:09:53+01:00 Fix build. - - - - - c2c51bc7 by Ian Lynagh at 2011-11-06T23:01:33+00:00 Remove -DNEW_GHC_LAYOUT in ghc.mk - - - - - f847d703 by Jose Pedro Magalhaes at 2011-11-11T09:07:39+00:00 New kind-polymorphic core This big patch implements a kind-polymorphic core for GHC. The current implementation focuses on making sure that all kind-monomorphic programs still work in the new core; it is not yet guaranteed that kind-polymorphic programs (using the new -XPolyKinds flag) will work. For more information, see http://haskell.org/haskellwiki/GHC/Kinds - - - - - 7d7c3b09 by Jose Pedro Magalhaes at 2011-11-16T21:42:22+01:00 Follow changes to tuple sorts in master - - - - - 8430e03e by Simon Peyton Jones at 2011-11-17T10:20:27+00:00 Remove redundant imports - - - - - d1b06832 by Ian Lynagh at 2011-11-19T01:33:21+00:00 Follow GHC build system change to the way we call rm - - - - - 9e2230ed by David Waern at 2011-11-24T15:00:24+01:00 Fix a bug in test runner and get rid of regex-compat dependency. - - - - - 52039b21 by David Waern at 2011-11-24T23:55:36+01:00 Avoid haskell98 dependency in test - - - - - 92e1220d by David Waern at 2011-11-25T00:03:33+01:00 Avoid depency on regex-compat also in accept.hs. - - - - - ddac6b6f by David Waern at 2011-11-25T02:13:38+01:00 Accept test output. - - - - - 5a720455 by David Waern at 2011-11-25T02:16:20+01:00 Some more changes to test scripts. - - - - - 170a9004 by David Waern at 2011-11-25T02:30:41+01:00 Add flag --interface-version. - - - - - d225576c by David Waern at 2011-11-25T02:39:26+01:00 Remove #ifs for older compiler versions. - - - - - f0d0a4f5 by David Waern at 2011-11-26T04:20:12+01:00 Give preference to type over data constructors for doc comment links at renaming time. Previously this was done in the backends. Also, warn when a doc comment refers to something that is in scope but which we don't have the .haddock file for. These changes mean we can make DocIdentifier [a] into DocIdentifier a. - - - - - eef0e776 by David Waern at 2011-11-26T17:01:06+01:00 Allow doc comments to link to out-of-scope things (#78). (A bug that should have been fixed long ago.) - - - - - 565ad529 by David Waern at 2011-11-26T19:56:21+01:00 Update tests. - - - - - fb3ce7b9 by David Waern at 2011-11-26T21:44:28+01:00 Cleanup. - - - - - d0328126 by David Waern at 2011-11-26T22:10:28+01:00 Fix module reference bug. - - - - - c03765f8 by David Waern at 2011-12-03T05:20:20+01:00 Slightly better behaviour on top-levels without type signatures. - Docs don't get attached to the next top-level with signature by mistake. - If there's an export list and the top-level is part of it, its doc comment shows up in the documentation. - - - - - 48461d31 by David Waern at 2011-12-03T05:38:10+01:00 Add a test for Unicode doc comments. - - - - - 549c4b4e by David Waern at 2011-12-03T19:07:55+01:00 Cleanup. - - - - - 7bfecf91 by David Waern at 2011-12-03T20:13:08+01:00 More cleanup. - - - - - 14fab722 by Ian Lynagh at 2011-12-12T21:21:35+00:00 Update dependencies and binaryInterfaceVersion - - - - - 469e6568 by Ian Lynagh at 2011-12-18T12:56:16+00:00 Fix (untested) building from source tarball without alex/happy haddock's .cabal file was declaring that it needed alex and happy to build, but in the GHC source tarballs it doesn't. - - - - - 895c9a8c by David Waern at 2011-12-27T12:57:43+01:00 Go back to having a doc, sub and decl map instead of one big decl map. This setup makes more sense since when we add value bindings to the processed declarations (for type inference), we will have multiple declarations which should share documentation. Also, we already have a separate doc map for instances which we can now merge into the main doc map. Another benefit is that we don't need the DeclInfo type any longer. - - - - - 736767d9 by David Waern at 2011-12-27T13:33:41+01:00 Merge ../../../haddock Conflicts: src/Haddock/InterfaceFile.hs - - - - - 20016f79 by David Waern at 2011-12-27T13:57:23+01:00 Bump version. - - - - - 31f276fb by David Waern at 2011-12-27T13:57:32+01:00 Merge ../ghc/utils/haddock - - - - - 95b367cd by David Waern at 2011-12-27T14:57:29+01:00 Update tests following version bump. - - - - - fa3c94cd by David Waern at 2011-12-27T14:57:51+01:00 Get rid of quite unnecessary use of different lists. - - - - - 9c4d3c54 by David Waern at 2011-12-27T15:26:42+01:00 Cleanup. - - - - - 2caf9f90 by David Waern at 2011-12-27T16:18:05+01:00 Wibbles. - - - - - 3757d09b by David Waern at 2011-12-27T20:50:26+01:00 Complete support for inferring types for top-level bindings. - - - - - 53418734 by David Waern at 2011-12-28T15:02:13+01:00 Minor fixes and cleanup. - - - - - 0c9d0385 by Ian Lynagh at 2012-01-03T18:31:29+00:00 Follow rename of Instance to ClsInst in GHC - - - - - c9bc969a by Simon Hengel at 2012-01-12T21:28:14+01:00 Make sure that generated xhtml is valid (close haskell/haddock#186) Thanks to Phyx. - - - - - 836a0b9a by David Waern at 2012-02-01T02:30:05+01:00 Fix bug introduced in my recent refactoring. - - - - - c7d733eb by David Waern at 2012-02-01T02:30:26+01:00 Cleanup mkMaps and avoid quadratic behaviour. - - - - - da3cda8f by David Waern at 2012-02-01T02:56:56+01:00 Require ghc >= 7.4. - - - - - 83a3287e by David Waern at 2012-02-01T02:57:36+01:00 Update CHANGES. - - - - - 93408f0b by Simon Hengel at 2012-02-04T00:48:04+01:00 Add reference renderings - - - - - 49d00d2c by Simon Hengel at 2012-02-04T00:48:25+01:00 Set unit tests for parser back to work - - - - - eb450980 by Simon Hengel at 2012-02-04T00:49:07+01:00 Add .gitignore - - - - - a841602c by Simon Hengel at 2012-02-04T00:49:16+01:00 Add .ghci file - - - - - 8861199d by Simon Hengel at 2012-02-04T00:49:29+01:00 tests/html-tests/copy.hs: Use mapM_ instead of mapM So we do net get a list of () on stdout when running with runhaskell. - - - - - b477d9b5 by Simon Hengel at 2012-02-04T00:49:46+01:00 Remove index files from golden tests - - - - - 9dbda34e by Simon Hengel at 2012-02-04T00:49:57+01:00 Add /tests/html-tests/tests/*index*.ref to .gitignore - - - - - a9434817 by Simon Hengel at 2012-02-04T00:50:04+01:00 Add DocWarning to Doc The Xhtml backend has special markup for that, Hoogle and LaTeX reuse what we have for DocEmphasis. - - - - - de2fb6fa by Simon Hengel at 2012-02-04T00:50:13+01:00 Add support for module warnings - - - - - 0640920e by Simon Hengel at 2012-02-04T00:50:21+01:00 Add tests for module warnings - - - - - 30ce0d77 by Simon Hengel at 2012-02-04T00:50:29+01:00 Add support for warnings - - - - - bb367960 by Simon Hengel at 2012-02-04T00:50:37+01:00 Add tests for warnings - - - - - 6af1dc2d by Simon Hengel at 2012-02-04T00:50:50+01:00 Expand type signatures in export list (fixes haskell/haddock#192) - - - - - a06cbf25 by Simon Hengel at 2012-02-04T00:51:04+01:00 Expand type signatures for modules without explicit export list - - - - - 57dda796 by Simon Hengel at 2012-02-04T00:51:15+01:00 Remove obsolete TODO - - - - - 270c3253 by David Waern at 2012-02-04T00:51:24+01:00 Fix issues in support for warnings. * Match against local names only. * Simplify (it's OK to map over the warnings). - - - - - 683634bd by David Waern at 2012-02-04T00:55:11+01:00 Some cleanup and make sure we filter warnings through exports. - - - - - 210cb4ca by David Waern at 2012-02-04T03:01:30+01:00 Merge branch 'fix-for-186' of https://github.com/sol/haddock into ghc-7.4 - - - - - e8db9031 by David Waern at 2012-02-04T03:07:51+01:00 Style police. - - - - - 261f9462 by David Waern at 2012-02-04T03:20:16+01:00 Update tests. - - - - - 823cfc7c by David Waern at 2012-02-04T03:21:12+01:00 Use mapM_ in accept.hs as well. - - - - - 873dd619 by David Waern at 2012-02-04T03:21:33+01:00 Remove copy.hs - use accept.hs instead. - - - - - 0e31a14a by David Waern at 2012-02-04T03:47:33+01:00 Use <> instead of mappend. - - - - - 2ff7544f by David Waern at 2012-02-04T03:48:55+01:00 Remove code for older ghc versions. - - - - - dacf2786 by David Waern at 2012-02-04T15:52:51+01:00 Clean up some code from last SoC project. - - - - - 00cbb117 by David Waern at 2012-02-04T21:43:49+01:00 Mostly hlint-inspired cleanup. - - - - - 7dc86cc2 by Simon Peyton Jones at 2012-02-06T09:14:41+00:00 Track changes in HsDecls - - - - - f91f82fe by Ian Lynagh at 2012-02-16T13:40:11+00:00 Follow changes in GHC caused by the CAPI CTYPE pragma - - - - - a0ea6b0b by Ian Lynagh at 2012-02-22T02:26:12+00:00 Follow changes in GHC - - - - - b23b07d1 by Simon Peyton Jones at 2012-03-02T16:36:41+00:00 Follow changes in data representation from the big PolyKinds commit - - - - - 43406022 by Simon Hengel at 2012-03-05T11:18:34+01:00 Save/restore global state for static flags when running GHC actions This is necessary if we want to run createInterfaces (from Documentation.Haddock) multiple times in the same process. - - - - - 9fba16fe by Paolo Capriotti at 2012-03-06T10:57:33+00:00 Update .gitignore. - - - - - a9325044 by Simon Peyton Jones at 2012-03-14T17:35:42+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - fd48065a by Iavor Diatchki at 2012-03-15T22:43:35-07:00 Add support for type-level literals. - - - - - 2e8206dd by Simon Peyton Jones at 2012-03-16T14:18:22+00:00 Follow changes to tcdKindSig (Trac haskell/haddock#5937) - - - - - 93e13319 by Simon Peyton Jones at 2012-03-17T01:04:05+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock Conflicts: src/Haddock/Convert.hs - - - - - d253fa71 by Iavor Diatchki at 2012-03-19T20:12:18-07:00 Merge remote-tracking branch 'origin/master' into type-nats - - - - - fc40acc8 by Iavor Diatchki at 2012-03-19T20:31:27-07:00 Add a missing case for type literals. - - - - - fd2ad699 by Iavor Diatchki at 2012-03-24T13:28:29-07:00 Rename variable to avoid shadowing warning. - - - - - 9369dd3c by Simon Peyton Jones at 2012-03-26T09:14:23+01:00 Follow refactoring of TyClDecl/HsTyDefn - - - - - 38825ca5 by Simon Peyton Jones at 2012-03-26T09:14:37+01:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - 4324ac0f by David Waern at 2012-04-01T01:51:19+02:00 Disable unicode test. - - - - - 3165b750 by David Waern at 2012-04-01T01:51:34+02:00 Take reader environment directly from TypecheckedSource. - - - - - 213b644c by David Waern at 2012-04-01T01:55:20+02:00 Cleanup. - - - - - 3118b4ba by David Waern at 2012-04-01T02:16:15+02:00 Don't filter out unexported names from the four maps - fixes a regression. - - - - - d6524e17 by David Waern at 2012-04-01T02:40:34+02:00 Fix crash when using --qual. Naughty GHC API! - - - - - ea3c43d8 by Henning Thielemann at 2012-04-01T13:03:07+02:00 add QualOption type for distinction between qualification argument given by the user and the actual qualification for a concrete module - - - - - 5422ff05 by Henning Thielemann at 2012-04-01T16:25:02+02:00 emit an error message when the --qual option is used incorrectly - - - - - 026e3404 by David Waern at 2012-04-01T18:10:30+02:00 Don't crash on unicode strings in doc comments. - - - - - ce006632 by David Waern at 2012-04-01T20:13:35+02:00 Add test for --ignore-all-exports flag/ignore-exports pragma. - - - - - 6e4dd33c by David Waern at 2012-04-01T20:21:03+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.4 - - - - - 734ae124 by Henning Thielemann at 2012-04-01T20:22:10+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - 622f9ba5 by David Waern at 2012-04-01T21:26:13+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 55ce17cb by Henning Thielemann at 2012-04-01T22:03:25+02:00 'abbreviate' qualification style - basic support Currently we ignore the package a module is imported from. This means that a module import would shadow another one with the same module name from a different package. - - - - - c85314ef by David Waern at 2012-04-01T22:05:12+02:00 Check qualification option before processing modules. - - - - - ae4b626c by Henning Thielemann at 2012-04-02T00:19:36+02:00 abbreviated qualification: use Packages.lookupModuleInAllPackages for finding the package that a module belongs to - - - - - 60bdbcf5 by Henning Thielemann at 2012-04-02T00:25:31+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - df44301d by Henning Thielemann at 2012-04-02T00:29:05+02:00 qualification style 'abbreviated' -> 'aliased' - - - - - f4192a64 by David Waern at 2012-04-02T01:05:47+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - 7ba09067 by David Terei at 2012-04-04T15:08:21-07:00 Fix reporting of modules safe haskell mode (#5989) - - - - - d0cc33d0 by David Terei at 2012-04-06T15:50:41+01:00 Fix reporting of modules safe haskell mode (#5989) - - - - - 6e3434c5 by Simon Peyton Jones at 2012-04-20T18:37:46+01:00 Track changes in HsSyn - - - - - 22014ed0 by Simon Peyton Jones at 2012-05-11T22:45:15+01:00 Follow changes to LHsTyVarBndrs - - - - - d9a07b24 by David Waern at 2012-05-15T01:46:35+02:00 Merge branch 'ghc-7.4' of http://darcs.haskell.org/haddock into ghc-7.4 - - - - - a6c4ebc6 by David Waern at 2012-05-16T02:18:32+02:00 Update CHANGES. - - - - - 8e181d29 by David Waern at 2012-05-16T02:27:56+02:00 Merge http://code.haskell.org/~thielema/haddock/ into ghc-7.4 - - - - - e358210d by David Waern at 2012-05-16T02:35:33+02:00 Mention the new aliased --qual mode in CHANGES. - - - - - efd36a28 by David Waern at 2012-05-16T21:33:13+02:00 Bump version number. - - - - - d6b3af14 by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for deprecated record field - - - - - 927f800e by Simon Hengel at 2012-05-17T19:08:20+02:00 Use >>= instead of fmap and join - - - - - 048b41d5 by Simon Hengel at 2012-05-17T19:08:20+02:00 newtype-wrap Doc nodes for things that may have warnings attached - - - - - e3a89fc3 by Simon Hengel at 2012-05-17T19:08:20+02:00 Attach warnings to `Documentation` type - - - - - 5d4cc43d by Simon Hengel at 2012-05-17T19:08:20+02:00 Simplify lookupWarning - - - - - cf8ae69d by Simon Hengel at 2012-05-17T19:08:20+02:00 Add test for haskell/haddock#205 - - - - - cb409b19 by Simon Peyton Jones at 2012-05-25T08:30:11+01:00 Follow changes in LHsTyVarBndrs - - - - - 2d5f4179 by Simon Hengel at 2012-05-26T19:21:29+02:00 Add Applicative instance for (GenRnM a) - - - - - e4373060 by Simon Hengel at 2012-05-26T19:21:33+02:00 Use a map for warnings, as suggested by @waern - - - - - 597a68c7 by Simon Hengel at 2012-05-27T08:48:24+02:00 Add an optional label to URLs - - - - - ef1ac7fe by Simon Hengel at 2012-05-27T08:48:24+02:00 Add support for hyperlink labels to parser - - - - - 41f2adce by Simon Hengel at 2012-05-27T08:48:24+02:00 Add golden test for hyperlinks - - - - - 83d5e764 by Simon Hengel at 2012-05-27T08:50:02+02:00 Use LANGUAGE pragmas instead of default-extensions in cabal file - - - - - ddb755e5 by Simon Hengel at 2012-05-27T08:50:02+02:00 Fix typo in comment - - - - - 110676b4 by Simon Hengel at 2012-05-27T08:50:02+02:00 Add a type signature for a where-binding - - - - - 7d9ba2a0 by Ian Lynagh at 2012-06-12T14:38:01+01:00 Follow changes in GHC - - - - - 47c704f2 by Ian Lynagh at 2012-06-12T18:52:16+01:00 Follow changes in GHC - - - - - e1efe1ab by Simon Peyton Jones at 2012-06-13T17:25:29+01:00 Follow changes for the implementation of implicit parameters - - - - - 69abc81c by Ian Lynagh at 2012-06-19T22:52:58+01:00 Follow changes in base - - - - - 9d074a21 by Paolo Capriotti at 2012-06-22T18:26:47+01:00 Use right docMap to get decl documentation. - - - - - e3292ef6 by Ian Lynagh at 2012-07-15T01:31:19+01:00 Follow changes in GHC - - - - - ceae56b0 by Ian Lynagh at 2012-07-16T21:22:48+01:00 Fix haddock following some GHC changes Passing _|_ as the Settings for defaultDynFlags no longer works well enough - - - - - 9df72735 by Paolo Capriotti at 2012-07-19T16:49:32+01:00 Forward port changes from stable. - - - - - 572f5fcf by Ian Lynagh at 2012-07-19T20:38:26+01:00 Merge branch 'master' of darcs.haskell.org:/srv/darcs//haddock - - - - - 9195aca4 by Paolo Capriotti at 2012-07-20T10:27:28+01:00 Update dependencies. - - - - - 33db3923 by Ian Lynagh at 2012-07-20T17:54:43+01:00 Build with GHC 7.7 - - - - - 925a2cea by David Waern at 2012-07-23T16:50:40+02:00 Merge branch 'dev' of https://github.com/sol/haddock into ghc-7.6 Conflicts: src/Haddock/InterfaceFile.hs - - - - - d710ef97 by David Waern at 2012-07-23T16:52:07+02:00 Bump version number. - - - - - eb0c2f83 by David Waern at 2012-07-23T16:57:58+02:00 Update CHANGES. - - - - - b3f56943 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Hide "internal" instances This fixes haskell/haddock#37 (http://trac.haskell.org/haddock/ticket/37) Precisely, we show an instance iff its class and all the types are exported by non-hidden modules. - - - - - a70aa412 by Roman Cheplyaka at 2012-07-27T13:00:13+03:00 Tests for hiding instances (#37) - - - - - c0f4aa58 by Simon Hengel at 2012-07-27T13:00:13+03:00 Add an other test for hiding instances (#37) - - - - - a7ed6268 by Ian Lynagh at 2012-08-07T14:48:13+01:00 Follow changes in GHC - - - - - 0ab30d38 by Ian Lynagh at 2012-08-13T22:12:27+01:00 Improve haddock memory usage - - - - - 0eaa4e30 by Ian Lynagh at 2012-08-13T23:58:46+01:00 Improve haddock memory usage - - - - - 659d26cf by Ian Lynagh at 2012-08-14T13:16:48+01:00 Remove some temporary pragmas I accidentally recorded - - - - - d97fceb6 by Simon Hengel at 2012-08-25T13:19:34+02:00 Add missing dependency to library - - - - - 4c910697 by Simon Hengel at 2012-08-28T07:39:14+02:00 Move .ghci to project root - - - - - fc3c601a by Simon Hengel at 2012-08-28T07:39:14+02:00 accept.hs: Ignore some files - - - - - 1af9b984 by Simon Hengel at 2012-08-28T07:40:04+02:00 Update reference renderings (bump version) - - - - - 980dc253 by Simon Hengel at 2012-08-28T07:40:32+02:00 Update reference renderings (remove links for ()) - - - - - 33651dbf by Simon Hengel at 2012-08-28T07:41:50+02:00 Update documentation of `runInteractiveProcess` in reference rendering - - - - - 7ab25078 by David Waern at 2012-09-07T10:38:50+02:00 Merge branch 'hiddenInstances2' of http://github.com/feuerbach/haddock into ghc-7.6 - - - - - c3de3a4b by David Waern at 2012-09-07T14:29:27+02:00 Follow changes in GHC. - - - - - 298c43ac by David Waern at 2012-09-07T14:59:24+02:00 Update CHANGES. - - - - - e797993a by David Waern at 2012-09-07T15:21:30+02:00 Update ANNOUNCE. - - - - - d0b44790 by David Waern at 2012-09-07T15:22:43+02:00 Merge branch 'hidden-instances' into ghc-7.6 - - - - - 41a4adc8 by Simon Hengel at 2012-09-08T12:08:37+02:00 Update doc/README - - - - - 71ad1040 by Simon Hengel at 2012-09-08T12:17:17+02:00 Add documentation for URL labels - - - - - 9bb41afd by Simon Peyton Jones at 2012-09-20T18:14:26+01:00 Follow data type changes in the tc-untouchables branch Relating entirely to SynTyConRhs - - - - - b8139bfa by Simon Hengel at 2012-09-21T14:24:16+02:00 Disable Unicode test for now - - - - - a5fafdd7 by Simon Hengel at 2012-09-21T14:35:45+02:00 Update TypeOperators test for GHC 7.6.1 Type operators can't be used as type variables anymore! - - - - - 6ccf0025 by Simon Hengel at 2012-09-21T16:02:24+02:00 Remove (Monad (Either e)) instance from ref. rendering of CrossPackageDocs I do not really understand why the behavior changed, so I'll open a ticket, so that we can further investigate. - - - - - b5c6c138 by Ian Lynagh at 2012-09-27T02:00:57+01:00 Follow changes in GHC build system - - - - - b98eded0 by David Waern at 2012-09-27T15:37:02+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 76cc2051 by David Waern at 2012-09-27T15:48:19+02:00 Update hidden instances tests. - - - - - aeaa1c59 by David Waern at 2012-09-28T10:21:32+02:00 Make API buildable with GHC 7.6. - - - - - d76be1b0 by Simon Peyton Jones at 2012-09-28T15:57:05+01:00 Merge remote-tracking branch 'origin/master' into tc-untouchables - - - - - a1922af8 by David Waern at 2012-09-28T19:50:20+02:00 Fix spurious superclass constraints bug. - - - - - bc41bdbb by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove old examples - - - - - bed7d3dd by Simon Hengel at 2012-10-01T11:30:51+02:00 Adapt parsetests for GHC 7.6.1 - - - - - dcdb22bb by Simon Hengel at 2012-10-01T11:30:51+02:00 Add test-suite section for parsetests to cabal file + get rid of HUnit dependency - - - - - 1e5263c9 by Simon Hengel at 2012-10-01T11:30:51+02:00 Remove test flag from cabal file This was not really used. - - - - - 4beee98b by David Waern at 2012-09-28T23:42:28+02:00 Merge branch 'ghc-7.6' of http://darcs.haskell.org/haddock into ghc-7.6 - - - - - 11dd2256 by Ian Lynagh at 2012-10-03T16:17:35+01:00 Follow change in GHC build system - - - - - fbd77962 by Simon Hengel at 2012-10-03T18:49:40+02:00 Remove redundant dependency from cabal file - - - - - 09218989 by Simon Hengel at 2012-10-04T16:03:05+02:00 Fix typo - - - - - 93a2d5f9 by Simon Hengel at 2012-10-04T16:11:41+02:00 Remove trailing whitespace from cabal file - - - - - c8b46cd3 by Simon Hengel at 2012-10-04T16:12:17+02:00 Export Haddock's main entry point from library - - - - - b411e77b by Simon Hengel at 2012-10-04T16:29:46+02:00 Depend on library for executable The main motivation for this is to increase build speed. In GHC's source tree the library is not build, but all modules are now required for the executable, so that GHC's validate will now detect build failures for the library. - - - - - f8f0979f by Simon Hengel at 2012-10-05T00:32:57+02:00 Set executable flag for Setup.lhs - - - - - dd045998 by Simon Hengel at 2012-10-07T16:44:06+02:00 Extend rather than set environment when running HTML tests On some platforms (e.g. ppc64) GHC requires gcc in the path. - - - - - 7b39c3ae by Simon Hengel at 2012-10-07T17:05:45+02:00 cross-package test: re-export IsString instead of Monad There is a monad instance for Q, which is not available on platforms that do not have GHCi support. This caused CrossPackageDocs to fail on those platforms. Re-exporting IsString should test the same thing, but it works on all platforms. - - - - - 0700c605 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Fix some warnings - - - - - f78eca79 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Make -Wall proof - - - - - 6beec041 by Simon Hengel at 2012-10-07T19:06:34+02:00 runtests.hs: Use listToMaybe/fromMaybe instead of safeHead/maybe - - - - - 44b8ce86 by Ian Lynagh at 2012-10-08T21:59:46+01:00 Follow changes in GHC - - - - - 6da5f702 by Simon Hengel at 2012-10-09T11:16:19+02:00 Update .ghci - - - - - 9ac1a1b9 by Kazu Yamamoto at 2012-10-09T12:45:31+02:00 Add markup support for properties - - - - - 1944cb42 by Simon Hengel at 2012-10-09T12:45:31+02:00 Simplify lexing/parsing of properties In contrast to what we do for examples, we do not really need to capture the "prompt" here. - - - - - bffd8e62 by Simon Hengel at 2012-10-09T13:40:14+02:00 Add HTML test for properties - - - - - 2fe9c5cb by Simon Hengel at 2012-10-09T13:40:21+02:00 Add unit tests for properties - - - - - 874e361b by Simon Hengel at 2012-10-09T13:40:33+02:00 Bump interface version - - - - - 2506cc37 by Simon Hengel at 2012-10-09T15:15:04+02:00 Fix parser bug - - - - - 743d2b7d by Simon Hengel at 2012-10-09T15:31:06+02:00 Allow to load interface files with compatible versions - - - - - 981a1660 by Simon Hengel at 2012-10-10T10:32:05+02:00 Export more types from Documentation.Haddock (fixes haskell/haddock#216) - - - - - dff7dc76 by Simon Hengel at 2012-10-10T11:15:19+02:00 Update ANNOUNCE and CHANGES - - - - - edd2bb01 by Simon Hengel at 2012-10-10T11:22:50+02:00 Bump version - - - - - 5039163b by Simon Hengel at 2012-10-10T13:56:04+02:00 Fix typo in documentation - - - - - e4ce34da by Simon Hengel at 2012-10-10T14:28:35+02:00 Add documentation for properties - - - - - 9555ebca by Simon Hengel at 2012-10-11T10:49:04+02:00 Remove redundant if-defs, more source documentation - - - - - 87aa67e1 by Simon Hengel at 2012-10-11T12:32:51+02:00 Adapt cabal file - - - - - c44c1dee by Simon Hengel at 2012-10-11T12:41:58+02:00 Require ghc 7.6 - - - - - 8383bc34 by Simon Hengel at 2012-10-11T12:50:24+02:00 Bump version - - - - - 1030eb38 by Simon Hengel at 2012-10-11T12:55:44+02:00 Update ANNOUNCE and CHANGES - - - - - 74955088 by Simon Hengel at 2012-10-12T09:49:31+02:00 Improve note about `binaryInterfaceVersion` (thanks David) - - - - - ee30f6b7 by Simon Hengel at 2012-10-13T13:40:59+02:00 Update version in html tests, rpm spec file, and user manual - - - - - f2861f18 by Simon Hengel at 2012-10-13T14:40:33+02:00 Remove unused MonadFix constraint - - - - - dfdf1a74 by Simon Hengel at 2012-10-13T15:15:38+02:00 Minor code simplification - - - - - 4ecd1e70 by Simon Hengel at 2012-10-13T15:33:43+02:00 Increase code locality - - - - - f7df5cc9 by Simon Hengel at 2012-10-13T16:03:12+02:00 Minor code simplification - - - - - e737eb6e by Simon Hengel at 2012-10-13T19:03:04+02:00 Handle HsExplicitListTy in renameer (fixes haskell/haddock#213) - - - - - c2dc8f17 by Simon Hengel at 2012-10-13T20:46:31+02:00 Better error messages - - - - - 14d48b4c by Simon Hengel at 2012-10-14T00:21:07+02:00 Simplify RnM type - - - - - 6c2cc547 by Simon Hengel at 2012-10-14T00:23:35+02:00 Simplify lookupRn - - - - - bc77ce85 by Simon Hengel at 2012-10-14T01:51:32+02:00 Organize unite tests hierarchically - - - - - 2306d117 by Simon Hengel at 2012-10-14T10:34:58+02:00 Handle more cases in renameType - - - - - 8a864203 by Simon Hengel at 2012-10-14T11:47:59+02:00 Add mini_HiddenInstances.html.ref and mini_HiddenInstancesB.html.ref - - - - - 3a978eca by Simon Hengel at 2012-10-14T11:49:28+02:00 Add /tests/html-tests/output/ to .gitignore - - - - - db18888a by Simon Hengel at 2012-10-14T13:38:21+02:00 Allow haddock markup in deprecation messages - - - - - e7cfee9f by Simon Hengel at 2012-10-14T14:00:23+02:00 If parsing of deprecation message fails, include it verbatim - - - - - 242a85be by Simon Hengel at 2012-10-14T14:13:24+02:00 Add description for PruneWithWarning test - - - - - 43d33df1 by Simon Hengel at 2012-10-14T15:40:53+02:00 Minor formatting change - - - - - 22768c44 by Simon Hengel at 2012-10-14T16:03:43+02:00 Properly handle deprecation messages for re-exported things (fixes haskell/haddock#220) - - - - - cb4b9111 by Simon Hengel at 2012-10-14T17:30:28+02:00 Add build artifacts for documentation to .gitignore - - - - - 854cd8de by Simon Hengel at 2012-10-14T23:34:51+02:00 unit-tests: Improve readability Add IsString instance for (Doc RdrName) + use <> instead of DocAppend. - - - - - c4446d54 by Simon Hengel at 2012-10-14T23:37:21+02:00 unit-tests: Minor refactoring Rename parse to parseParas. - - - - - 04f2703c by Simon Hengel at 2012-10-15T00:36:42+02:00 Fix typo - - - - - 3d109e44 by Simon Hengel at 2012-10-15T10:30:07+02:00 Add description for DeprecatedReExport test - - - - - 84f0985c by Simon Hengel at 2012-10-15T14:54:19+02:00 Move resources to /resources directory - - - - - a5de7ca6 by Simon Hengel at 2012-10-15T15:46:18+02:00 Move HTML tests to directory /html-test/ - - - - - e21f727d by Simon Hengel at 2012-10-15T19:32:42+02:00 Move HTML reference renderings to /html-test/ref/ - - - - - 3a3c6c75 by Simon Hengel at 2012-10-15T19:32:42+02:00 Copy css, images, etc. on accept - - - - - 40ead6dc by Simon Hengel at 2012-10-15T19:32:42+02:00 Move unit tests to /test directory - - - - - 99a28231 by Simon Hengel at 2012-10-15T19:32:42+02:00 Fix Setup.lhs /usr/bin/runhaskell is not installed on all systems. - - - - - 95faf45e by Simon Hengel at 2012-10-15T19:32:42+02:00 Make test management scripts more robust * They are now independent from the current directory, and hence can be called from everywhere * On UNIX/Linux they can now be run as scripts - - - - - 027aaa2d by Simon Hengel at 2012-10-15T19:53:40+02:00 Add 'dev' flag to cabal file, that builds without -O2 That way --disable-optimization can be used, which decreases build time considerably. - - - - - e0266ede by Simon Hengel at 2012-10-15T20:03:43+02:00 Add test case for "spurious superclass constraints bug" - - - - - 52a2aa92 by Simon Hengel at 2012-10-15T20:28:55+02:00 Adapt accept.lhs, so that it ignores more index files - - - - - 53530781 by Simon Hengel at 2012-10-15T20:49:39+02:00 Rename html-test/runtests.lhs to html-test/run.lhs - - - - - 84518797 by Simon Hengel at 2012-10-15T20:49:39+02:00 Move source files for HTML tests to html-test/src - - - - - a911dc6c by Simon Hengel at 2012-10-15T20:49:39+02:00 Adapt output directory for HTML tests - - - - - d3c15857 by Ian Lynagh at 2012-10-16T16:54:43+01:00 Follow dopt->gopt rename - - - - - 956665a5 by Simon Hengel at 2012-10-18T08:42:48+02:00 Update html-test/README - - - - - 903b1029 by Simon Hengel at 2012-10-18T08:50:26+02:00 Use markdown for html-test/README - - - - - 150b4d63 by Ian Lynagh at 2012-10-18T16:36:00+01:00 Follow changes in GHC: 'flags' has been renamed 'generalFlags' - - - - - 41e04ff9 by Simon Hengel at 2012-11-28T09:54:35+01:00 Export missing types from Documentation.Haddock - - - - - 9be59237 by Ian Lynagh at 2012-11-30T23:20:47+00:00 Update dependencies - - - - - e06842f5 by Simon Hengel at 2012-12-07T20:58:05+01:00 Bump version - - - - - e3dbede0 by Simon Hengel at 2012-12-07T20:58:05+01:00 Add missing test files to cabal file (fixes haskell/haddock#230) - - - - - ee0dcca7 by Simon Hengel at 2012-12-07T20:58:05+01:00 Update CHANGES - - - - - 51601bdb by Simon Peyton Jones at 2012-12-19T17:28:35+00:00 Track changes in UNPACK pragma stuff - - - - - f2573bc1 by Richard Eisenberg at 2012-12-21T20:56:25-05:00 Implement overlapping type family instances. An ordered, overlapping type family instance is introduced by 'type instance where', followed by equations. See the new section in the user manual (7.7.2.2) for details. The canonical example is Boolean equality at the type level: type family Equals (a :: k) (b :: k) :: Bool type instance where Equals a a = True Equals a b = False A branched family instance, such as this one, checks its equations in order and applies only the first the matches. As explained in the note [Instance checking within groups] in FamInstEnv.lhs, we must be careful not to simplify, say, (Equals Int b) to False, because b might later unify with Int. This commit includes all of the commits on the overlapping-tyfams branch. SPJ requested that I combine all my commits over the past several months into one monolithic commit. The following GHC repos are affected: ghc, testsuite, utils/haddock, libraries/template-haskell, and libraries/dph. Here are some details for the interested: - The definition of CoAxiom has been moved from TyCon.lhs to a new file CoAxiom.lhs. I made this decision because of the number of definitions necessary to support BranchList. - BranchList is a GADT whose type tracks whether it is a singleton list or not-necessarily-a-singleton-list. The reason I introduced this type is to increase static checking of places where GHC code assumes that a FamInst or CoAxiom is indeed a singleton. This assumption takes place roughly 10 times throughout the code. I was worried that a future change to GHC would invalidate the assumption, and GHC might subtly fail to do the right thing. By explicitly labeling CoAxioms and FamInsts as being Unbranched (singleton) or Branched (not-necessarily-singleton), we make this assumption explicit and checkable. Furthermore, to enforce the accuracy of this label, the list of branches of a CoAxiom or FamInst is stored using a BranchList, whose constructors constrain its type index appropriately. I think that the decision to use BranchList is probably the most controversial decision I made from a code design point of view. Although I provide conversions to/from ordinary lists, it is more efficient to use the brList... functions provided in CoAxiom than always to convert. The use of these functions does not wander far from the core CoAxiom/FamInst logic. BranchLists are motivated and explained in the note [Branched axioms] in CoAxiom.lhs. - The CoAxiom type has changed significantly. You can see the new type in CoAxiom.lhs. It uses a CoAxBranch type to track branches of the CoAxiom. Correspondingly various functions producing and consuming CoAxioms had to change, including the binary layout of interface files. - To get branched axioms to work correctly, it is important to have a notion of type "apartness": two types are apart if they cannot unify, and no substitution of variables can ever get them to unify, even after type family simplification. (This is different than the normal failure to unify because of the type family bit.) This notion in encoded in tcApartTys, in Unify.lhs. Because apartness is finer-grained than unification, the tcUnifyTys now calls tcApartTys. - CoreLinting axioms has been updated, both to reflect the new form of CoAxiom and to enforce the apartness rules of branch application. The formalization of the new rules is in docs/core-spec/core-spec.pdf. - The FamInst type (in types/FamInstEnv.lhs) has changed significantly, paralleling the changes to CoAxiom. Of course, this forced minor changes in many files. - There are several new Notes in FamInstEnv.lhs, including one discussing confluent overlap and why we're not doing it. - lookupFamInstEnv, lookupFamInstEnvConflicts, and lookup_fam_inst_env' (the function that actually does the work) have all been more-or-less completely rewritten. There is a Note [lookup_fam_inst_env' implementation] describing the implementation. One of the changes that affects other files is to change the type of matches from a pair of (FamInst, [Type]) to a new datatype (which now includes the index of the matching branch). This seemed a better design. - The TySynInstD constructor in Template Haskell was updated to use the new datatype TySynEqn. I also bumped the TH version number, requiring changes to DPH cabal files. (That's why the DPH repo has an overlapping-tyfams branch.) - As SPJ requested, I refactored some of the code in HsDecls: * splitting up TyDecl into SynDecl and DataDecl, correspondingly changing HsTyDefn to HsDataDefn (with only one constructor) * splitting FamInstD into TyFamInstD and DataFamInstD and splitting FamInstDecl into DataFamInstDecl and TyFamInstDecl * making the ClsInstD take a ClsInstDecl, for parallelism with InstDecl's other constructors * changing constructor TyFamily into FamDecl * creating a FamilyDecl type that stores the details for a family declaration; this is useful because FamilyDecls can appear in classes but other decls cannot * restricting the associated types and associated type defaults for a * class to be the new, more restrictive types * splitting cid_fam_insts into cid_tyfam_insts and cid_datafam_insts, according to the new types * perhaps one or two more that I'm overlooking None of these changes has far-reaching implications. - The user manual, section 7.7.2.2, is updated to describe the new type family instances. - - - - - f788d0fb by Simon Peyton Jones at 2012-12-23T15:49:58+00:00 Track changes in HsBang - - - - - ca460a0c by Simon Peyton Jones at 2012-12-23T15:50:28+00:00 Merge branch 'master' of http://darcs.haskell.org//haddock - - - - - f078fea6 by Simon Peyton Jones at 2013-01-02T08:33:13+00:00 Use InstEnv.instanceSig rather than instanceHead (name change) - - - - - 88e41305 by Simon Peyton Jones at 2013-01-14T17:10:27+00:00 Track change to HsBang type - - - - - e1ad4e19 by Kazu Yamamoto at 2013-02-01T11:59:24+09:00 Merge branch 'ghc-7.6' into ghc-7.6-merge-2 Conflicts: haddock.cabal src/Haddock/Interface/AttachInstances.hs src/Haddock/Interface/Create.hs src/Haddock/Interface/LexParseRn.hs src/Haddock/InterfaceFile.hs src/Haddock/Types.hs Only GHC HEAD can compile this. GHC 7.6.x cannot compile this. Some test fail. - - - - - 62bec012 by Kazu Yamamoto at 2013-02-06T11:12:28+09:00 Using tcSplitSigmaTy in instanceHead' (FIXME is resolved.) - - - - - 013fd2e4 by Kazu Yamamoto at 2013-02-06T17:56:21+09:00 Refactoring instanceHead'. - - - - - 3148ce0e by Kazu Yamamoto at 2013-02-07T17:45:10+09:00 Using new syntax in html-test/src/GADTRecords.hs. - - - - - 626dabe7 by Gabor Greif at 2013-02-15T22:42:01+01:00 Typo - - - - - 1eb667ae by Ian Lynagh at 2013-02-16T17:02:07+00:00 Follow changes in base - - - - - 3ef8253a by Ian Lynagh at 2013-03-01T23:23:57+00:00 Follow changes in GHC's build system - - - - - 1a265a3c by Ian Lynagh at 2013-03-03T23:12:07+00:00 Follow changes in GHC build system - - - - - 69941c79 by Max Bolingbroke at 2013-03-10T09:38:28-07:00 Use Alex 3's Unicode support to properly lex source files as UTF-8 Signed-off-by: David Waern <david.waern at gmail.com> - - - - - ea687dad by Simon Peyton Jones at 2013-03-15T14:16:10+00:00 Adapt to tcRnGetInfo returning family instances too This API change was part of the fix to Trac haskell/haddock#4175. But it offers new information to Haddock: the type-family instances, as well as the class instances, of this type. This patch just drops the new information on the floor, but there's an open opportunity to use it in the information that Haddock displays. - - - - - 971a30b0 by Andreas Voellmy at 2013-05-19T20:47:39+01:00 Fix for haskell/haddock#7879. Changed copy of utils/haddock/html/resources/html to use "cp -RL" rather than "cp -R". This allows users to run validate in a build tree, where the build tree was setup using lndir with a relative path to the source directory. - - - - - 31fb7694 by Ian Lynagh at 2013-05-19T20:47:49+01:00 Use "cp -L" when making $(INPLACE_LIB)/latex too - - - - - e9952233 by Simon Hengel at 2013-06-01T18:06:50+02:00 Add -itest to .ghci - - - - - b06873b3 by Mateusz Kowalczyk at 2013-06-01T18:06:50+02:00 Workaround for a failing build with --enable-tests. - - - - - e7858d16 by Simon Hengel at 2013-06-01T19:29:28+02:00 Fix broken test - - - - - 0690acb1 by Richard Eisenberg at 2013-06-21T14:08:25+01:00 Updates to reflect changes in HsDecls to support closed type families. - - - - - 7fd347ec by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 53ed81b6 by Simon Hengel at 2013-07-08T10:28:48+02:00 Fix failing test - - - - - 931c4f4f by Richard Eisenberg at 2013-07-24T13:15:59+01:00 Remove (error "synifyKind") to use WithinType, to allow haddock to process base. - - - - - 55a9c804 by Richard Eisenberg at 2013-08-02T15:54:55+01:00 Changes to reflect changes in GHC's type HsTyVarBndr - - - - - b6e9226c by Mathieu Boespflug at 2013-08-04T10:39:43-07:00 Output Copright and License keys in Xhtml backend. This information is as relevant in the documentation as it is in the source files themselves. Signed-off-by: David Waern <david.waern at gmail.com> - - - - - 4c66028a by David Waern at 2013-08-04T15:27:36-07:00 Bump interface file version. - - - - - 67340163 by David Waern at 2013-08-09T16:12:51-07:00 Update tests. - - - - - 2087569b by Mateusz Kowalczyk at 2013-08-25T09:24:13+02:00 Add spec tests. This adds tests for all elements we can create during regular parsing. This also adds tests for text with unicode in it. - - - - - 97f36a11 by Mateusz Kowalczyk at 2013-08-27T06:59:12+01:00 Fix ticket haskell/haddock#247. I do the same thing that the XHTML backend does: give these no special treatment and just act as if they are regular functions. - - - - - 60681b4f by Mateusz Kowalczyk at 2013-08-27T21:22:48+02:00 LaTeX tests setup - - - - - fa4c27b2 by Mateusz Kowalczyk at 2013-09-02T23:21:43+01:00 Fixes haskell/haddock#253 - - - - - 1a202490 by Mateusz Kowalczyk at 2013-09-03T01:12:50+01:00 Use Hspec instead of nanospec This is motivated by the fact that Haddock tests are not ran by the GHC's ‘validate’ script so we're pretty liberal on dependencies in that area. Full Hspec gives us some nice features such as Quickcheck integration. - - - - - 8cde3b20 by David Luposchainsky at 2013-09-08T07:27:28-05:00 Fix AMP warnings Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - d10661f2 by Herbert Valerio Riedel at 2013-09-11T15:15:01+02:00 Update Git repo URL in `.cabal` file - - - - - 16a44eb5 by Richard Eisenberg at 2013-09-17T09:34:26-04:00 Revision to reflect new role annotation syntax in GHC. - - - - - 4b9833b9 by Herbert Valerio Riedel at 2013-09-18T10:15:28+02:00 Add missing `traverse` method for `GenLocated` As `Traversable` needs at least one of `traverse` or `sequenceA` to be overridden. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - b71fed5d by Simon Hengel at 2013-09-18T22:43:34+02:00 Add test helper - - - - - 4fc1ea86 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#231 - - - - - 435872f6 by Mateusz Kowalczyk at 2013-09-18T22:43:34+02:00 Fixes haskell/haddock#256 We inject -dynamic-too into flags before we run all our actions in the GHC monad. - - - - - b8b24abb by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Add new field to DynFlags - - - - - 49558795 by Simon Hengel at 2013-09-18T22:43:35+02:00 Fallback to ./resources when Cabal data is not found (so that themes are found during development) - - - - - bf79d05c by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Fixes haskell/haddock#5 - - - - - e1baebc2 by Mateusz Kowalczyk at 2013-09-18T22:43:35+02:00 Print missing documentation. Fixes haskell/haddock#258. - - - - - 02ea74de by Austin Seipp at 2013-10-09T10:52:22-05:00 Don't consider StaticFlags when parsing arguments. Instead, discard any static flags before parsing the command line using GHC's DynFlags parser. See http://ghc.haskell.org/trac/ghc/ticket/8276 Based off a patch from Simon Hengel. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 704fd5bb by Simon Hengel at 2013-11-09T00:15:13+01:00 Update HTML tests - - - - - f9fed49e by Simon Hengel at 2013-11-10T18:43:58+01:00 Bump version - - - - - 97ae1999 by Simon Peyton Jones at 2013-11-25T17:25:14+00:00 Track changes in HsSpliceTy data constructor - - - - - 59ad8268 by Simon Peyton Jones at 2014-01-10T18:17:43+00:00 Adapt to small change in Pretty's exports - - - - - 8b12e6aa by Simon Hengel at 2014-01-12T14:48:35-06:00 Some code simplification by using traverse - - - - - fc5ea9a2 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix warnings in test helper - - - - - 6dbb3ba5 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Add ByteString version of Attoparsec - - - - - 968d7774 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 One pass parser and tests. We remove the HTML test as it is no longer necessary. We cover the test case in spec tests and other HTML tests but keeping this around fails: this is because the new parser has different semantics there. In fact, I suspect the original behaviour was a bug that wasn't caught/fixed but simply included as-is during the testing. - - - - - 37a07c9c by Simon Hengel at 2014-01-12T14:48:35-06:00 Rename Haddock.ParseSpec to Haddock.ParserSpec - - - - - f0f68fe9 by Simon Hengel at 2014-01-12T14:48:35-06:00 Don't append newline to parseString input We also check that we have parsed everything with endOfInput. - - - - - 95d60093 by Simon Hengel at 2014-01-12T14:48:35-06:00 Fix totality, unicode, examples, paragraph parsing Also simplify specs and parsers while we're at it. Some parsers were made more generic. This commit is a part of GHC pre-merge squash, email fuuzetsu at fuuzetsu.co.uk if you need the full commit history. - - - - - 7d99108c by Simon Hengel at 2014-01-12T14:48:35-06:00 Update acceptance tests - - - - - d1b59640 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Support for bold. Conflicts: src/Haddock/Backends/Hoogle.hs src/Haddock/Interface/Rename.hs src/Haddock/Parser.hs - - - - - 4b412b39 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Allow for headings inside function documentation. LaTeX will treat the h3-h6 headings the same as we'd have to hack the style file heavily otherwise and it would make the headings tiny anyway. Hoogle upstream said they will put in the functionality on their end. Conflicts: src/Haddock/Interface/Rename.hs src/Haddock/Types.hs test/Haddock/ParserSpec.hs - - - - - fdcca428 by Mateusz Kowalczyk at 2014-01-12T14:48:35-06:00 Per-module extension flags and language listing. Any extensions that are not enabled by a used language (Haskell2010 &c) will be shown. Furthermore, any implicitly enabled are also going to be shown. While we could eliminate this either by using the GHC API or a dirty hack, I opted not to: if a user doesn't want the implied flags to show, they are recommended to use enable extensions more carefully or individually. Perhaps this will encourage users to not enable the most powerful flags needlessly. Enabled with show-extensions. Conflicts: src/Haddock/InterfaceFile.hs - - - - - 368942a2 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Bump interface version There were some breaking changes over the last few patches so we bump the interface version. This causes a big problem with testing: 1. To generate cross package docs, we first need to generate docs for the package used. 2. To generate package docs with new interface version, we need to use Haddock which has the version bumped. 3. To get Haddock with the version bump, we first need to test cross package docs 4. GOTO 1 So the problem is the chicken and the egg problem. It seems that the only solution would be to generate some interface files on the fly but it is non-trivial. To run this test, you'll have to: * build Haddock without the test (make sure everything else passes) * rebuild the packages used in the test with your shiny new binary making sure they are visible to Haddock * remove the ‘_hidden’ suffix and re-run the tests Note: because the packages currently used for this test are those provided by GHC, it's probably non-trivial to just re-build them. Preferably something less tedious to rebuild should be used and something that is not subject to change. - - - - - 124ae7a9 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow for nesting of paragraphs under lists. The nesting rules are similar to Markdown's with the exception that we can not simply indent the first line of a hard wrapped indented paragraph and have it treated as if it was fully indented. The reason is differences in markup as some of our constructs care about whitespace while others just swallow everything up so it's just a lot easier to not bother with it rather than making arbitrary rules. Note that we now drop trailing for string entities inside of lists. They weren't needed and it makes the output look uniform whether we use a single or double newline between list elements. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - c7913535 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Allow escaping in URLs and pictures. Some tests were moved under parseString as they weren't about paragraph level markup. Conflicts: src/Haddock/Parser.hs test/Haddock/ParserSpec.hs - - - - - 32326680 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update documentation. - - - - - fbef6406 by Mateusz Kowalczyk at 2014-01-12T14:48:36-06:00 Update maintainer - - - - - b40e82f4 by Mateusz Kowalczyk at 2014-01-13T02:39:25-06:00 Fixes haskell/haddock#271 Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - f4eafbf8 by Gergő Érdi at 2014-01-19T15:35:16-06:00 Support for -XPatternSynonyms Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - a8939591 by Austin Seipp at 2014-01-29T08:09:04-06:00 Update CPP check for __GLASGOW_HASKELL__ Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 30d7e9d5 by Gergő Érdi at 2014-01-31T00:15:01+08:00 <+>: Don't insert a space when concatenating empty nodes - - - - - a25ccd4d by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Fix @ code blocks In cases where we had some horizontal space before the closing ‘@’, the parser would not accept the block as a code block and we'd get ugly output. - - - - - 0f67305a by Mateusz Kowalczyk at 2014-01-30T17:22:34+01:00 Update tests This updates tests due to Haddock Trac haskell/haddock#271 fix and due to removal of TypeHoles as an extension from GHC. - - - - - 157322a7 by Gergő Érdi at 2014-01-31T01:03:17+08:00 Handle infix vs prefix names correctly everywhere, by explicitly specifying the context The basic idea is that "a" and "+" are either pretty-printed as "a" and "(+)" or "`a`" and "+" - - - - - aa6d9685 by Mateusz Kowalczyk at 2014-01-30T17:21:50+00:00 Correct whitespace in ‘hidden’ test for <+> change - - - - - 121872f0 by Mateusz Kowalczyk at 2014-02-09T17:59:12+00:00 Document module header. Fixes Haddock Trac haskell/haddock#270. - - - - - e3253746 by Mateusz Kowalczyk at 2014-02-10T21:37:48+00:00 Insert a space between module link and description Fixes Haddock Trac haskell/haddock#277. - - - - - 771d2384 by Mateusz Kowalczyk at 2014-02-10T23:27:21+00:00 Ensure a space between type signature and ‘Source’ This is briefly related to Haddock Trac haskell/haddock#249 and employs effectively the suggested fix _but_ it doesn't actually fix the reported issue. This commit simply makes copying the full line a bit less of a pain. - - - - - 8cda9eff by nand at 2014-02-11T15:48:30+00:00 Add support for type/data families This adds support for type/data families with their respective instances, as well as closed type families and associated type/data families. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 3f22c510 by nand at 2014-02-11T15:53:50+00:00 Improve display of poly-kinded type operators This now displays them as (==) k a b c ... to mirror GHC's behavior, instead of the old (k == a) b c ... which was just wrong. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - effb2d6b by nand at 2014-02-11T15:56:50+00:00 Add test case for PatternSynonyms This just tests various stuff including poly-kinded patterns and operator patterns to make sure the rendering isn't broken. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - b38faf0d by Niklas Haas at 2014-02-13T21:53:32+00:00 Get rid of re-implementation of sortBy I have no idea what this was doing lying around here, and due to the usage of tuples it's actually slower, too. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - ac1e0413 by Mateusz Kowalczyk at 2014-02-13T23:57:16+00:00 Only warn about missing docs when docs are missing This fixes the ‘Missing documentation for…’ message for modules with 100% coverage. - - - - - cae2e36a by Niklas Haas at 2014-02-15T21:56:18+00:00 Add test case for inter-module type/data family instances These should show up in every place where the class is visible, and indeed they do right now. Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - 8bea5c3a by Mateusz Kowalczyk at 2014-02-19T05:11:34+00:00 Use a bespoke data type to indicate fixity This deals with what I imagine was an ancient TODO and makes it much clearer what the argument actually does rather than having the user chase down the comment. - - - - - 5b52d57c by Niklas Haas at 2014-02-22T21:31:03+01:00 Strip a single leading space from bird tracks (#201) This makes bird tracks in the form > foo > bar > bat parse as if they had been written as >foo >bar >bat ie. without the leading whitespace in front of every line. Ideally we also want to look into how leading whitespace affects code blocks written using the @ @ syntax, which are currently unaffected by this patch. - - - - - 5a1315a5 by Simon Hengel at 2014-02-22T21:55:35+01:00 Turn a source code comment into specs - - - - - 784cfe58 by Mateusz Kowalczyk at 2014-02-23T05:02:22+00:00 Update test case for lifted GADT type rendering The parsing of these seems to have been fixed by GHC folk and it now renders differently. IMHO it now renders in a better way so I'm updating the test to reflect this. - - - - - c3c88c2f by Mateusz Kowalczyk at 2014-02-23T06:37:14+00:00 Don't shadow ‘strip’. -Wall complains - - - - - 293031d8 by Niklas Haas at 2014-02-23T15:21:52+01:00 Make ImplicitParams render correctly (#260) This introduces a new precedence level for single contexts (because implicit param contexts always need parens around them, but other types of contexts don't necessarily, even when alone) - - - - - 4200842d by Niklas Haas at 2014-02-23T15:37:13+01:00 Lower precedence of equality constraints This drops them to the new precedence pREC_CTX, which makes single eqaulity constraints show up as (a ~ b) => ty, in line with GHC's rendering. Additional tests added to make sure other type operators render as intended. Current behavior matches GHC - - - - - b59e3227 by Niklas Haas at 2014-02-23T16:11:22+01:00 Add RankNTypes test case to ImplicitParams.hs This test actually tests what haskell/haddock#260 originally reported - I omitted the RankNTypes scenario from the original fix because I realized it's not relevant to the underlying issue and indeed, this renders as intended now. Still good to have more tests. - - - - - c373dbf7 by Mateusz Kowalczyk at 2014-02-24T06:09:54+00:00 Fix rendering of Contents when links are present Fixes Haddock Trac haskell/haddock#267. - - - - - 9ecb0e56 by Mateusz Kowalczyk at 2014-02-24T06:26:50+00:00 Fix wording in the docs - - - - - 4f4dcd8e by Mateusz Kowalczyk at 2014-02-27T03:00:33+00:00 Change rendering of duplicate record field docs See Haddock Trac haskell/haddock#195. We now change this behaviour to only rendering the documentation attached to the first instance of a duplicate field. Perhaps we could improve this by rendering the first instance that has documentation attached to it but for now, we'll stick with this. - - - - - ad8aa609 by Niklas Haas at 2014-03-08T09:43:26+01:00 Render fixity information Affects functions, type synonyms, type families, class names, data type names, constructors, data families, associated TFs/DFs, type synonyms, pattern synonyms and everything else I could think of. - - - - - 6a39c917 by Niklas Haas at 2014-03-09T07:43:39+01:00 Reorder topDeclElem to move the source/wiki links to the top They appear in the same position due to the float: right attribute but now they're always at the top of the box instead of at the bottom. - - - - - 2d34b3b4 by Niklas Haas at 2014-03-09T07:53:46+01:00 Use optLast instead of listToMaybe for sourceUrls/wikiUrls This lets you override them using eg. cabal haddock --haddock-options, which can come in handy if you want to use a different layout or URL for your source code links than cabal-install generates. - - - - - 0eff4624 by Niklas Haas at 2014-03-09T07:53:46+01:00 Differentiate between TH splices (line-links) and regular names This adds a new type of source code link, to a specific line rather than a specific declaration/name - this is used to link to the location of a TH splice that defines a certain name. Rather hefty changes throughout and still one unresolved issue (the line URLs aren't parsed from the third form of --read-interface which means they're currently restricted to same-interface links). Not sure if this issue is really worth all the hassle, especially since we could just use line links in general. This commit also contains some cleanup/clarification of the types in Haddock.Backends.Xhtml.Decl and shortens some overlong lines in the process. Notably, the Bool parameter was replaced by a Unicode type synonym to help clarify its presence in type signatures. - - - - - 66d6f77b by Niklas Haas at 2014-03-09T20:02:43+01:00 Group similar fixities together Identical fixities declared for the same line should now render using syntax like: infix 4 <, >=, >, <= - - - - - 6587f9f5 by Mateusz Kowalczyk at 2014-03-10T04:24:18+00:00 Update changelog - - - - - 7387ddad by Niklas Haas at 2014-03-11T10:26:04+01:00 Include fixity information in the Interface file This resolves fixity information not appearing across package borders. The binary file version has been increased accordingly. - - - - - ab46ef44 by Niklas Haas at 2014-03-11T10:26:04+01:00 Update changelog - - - - - 565cab6f by Niklas Haas at 2014-03-11T10:26:04+01:00 Update appearance of fixity annotations This moves them in-line with their corresponding lines, similar to a presentation envision by @hvr and described in #ghc. Redundant operator names are also omitted when no ambiguity is present. - - - - - 5d7afd67 by Niklas Haas at 2014-03-11T10:26:05+01:00 Filter family instances of hidden types Currently, this check does not extend to hidden right hand sides, although it probably should hide them in that case. - - - - - ec291b0c by Niklas Haas at 2014-03-11T10:26:05+01:00 Add documentation for --source-entity-line - - - - - 0922e581 by Niklas Haas at 2014-03-11T10:37:32+01:00 Revert "Reorder topDeclElem to move the source/wiki links to the top" This reverts commit 843c42c4179526a2ad3526e4c7d38cbf4d50001d. This change is no longer needed with the new rendering style, and it messes with copy/pasting lines. - - - - - 30618e8b by Mateusz Kowalczyk at 2014-03-11T09:41:07+00:00 Bump version to 2.15.0 - - - - - adf3f1bb by Mateusz Kowalczyk at 2014-03-11T09:41:09+00:00 Fix up some whitespace - - - - - 8905f57d by Niklas Haas at 2014-03-13T19:18:06+00:00 Hide RHS of TFs with non-exported right hand sides Not sure what to do about data families yet, since technically it would not make a lot of sense to display constructors that cannot be used by the user. - - - - - 5c44d5c2 by Niklas Haas at 2014-03-13T19:18:08+00:00 Add UnicodeSyntax alternatives for * and -> I could not find a cleaner way to do this other than checking for string equality with the given built-in types. But seeing as it's actually equivalent to string rewriting in GHC's implementation of UnicodeSyntax, it's probably fitting. - - - - - b04a63e6 by Niklas Haas at 2014-03-13T19:18:10+00:00 Display minimal complete definitions for type classes This corresponds to the new {-# MINIMAL #-} pragma present in GHC 7.8+. I also cleaned up some of the places in which ExportDecl is used to make adding fields easier in the future. Lots of test cases have been updated since they now render with minimality information. - - - - - a4a20b16 by Niklas Haas at 2014-03-13T19:18:12+00:00 Strip links from recently added html tests These were accidentally left there when the tests were originally added - - - - - d624f315 by Mateusz Kowalczyk at 2014-03-13T19:19:31+00:00 Update changelog - - - - - d27a21ac by Mateusz Kowalczyk at 2014-03-13T21:19:07+00:00 Always read in prologue files as UTF8 (#286). - - - - - 54b2fd78 by Mateusz Kowalczyk at 2014-03-13T21:28:09+00:00 Style only - - - - - fa4fe650 by Simon Hengel at 2014-03-15T09:04:18+01:00 Add Fuuzetsu maintainers field in cabal file - - - - - f83484b7 by Niklas Haas at 2014-03-15T18:20:24+00:00 Hide minimal definition for only-method classes Previously this was not covered by the All xs check since here it is not actually an All, rather a single Var n. This also adds the previously missing html-test/src/Minimal.hs. - - - - - 0099d276 by Niklas Haas at 2014-03-15T18:20:26+00:00 Fix issue haskell/haddock#281 This is a regression from the data family instances change. Data instances are now distinguished from regular lists by usage of the new class "inst", and the style has been updated to only apply to those. I've also updated the appropriate test case to test this a bit better, including GADT instances with GADT-style records. - - - - - 1f9687bd by Mateusz Kowalczyk at 2014-03-21T17:48:37+00:00 Please cabal sdist - - - - - 75542693 by Mateusz Kowalczyk at 2014-03-22T16:36:16+00:00 Drop needless --split-objs which slows us down. Involves tiny cleanup of all the dynflag bindings. Fixes haskell/haddock#292. - - - - - 31214dc3 by Herbert Valerio Riedel at 2014-03-23T18:01:01+01:00 Fix a few typos Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 0b73e638 by Mateusz Kowalczyk at 2014-03-31T05:34:36+01:00 Print kind signatures on GADTs - - - - - 2bab42f3 by Mateusz Kowalczyk at 2014-03-31T16:53:25+01:00 Add default for new PlatformConstraints field - - - - - 42647c5f by Mateusz Kowalczyk at 2014-03-31T18:29:04+01:00 Drop leading whitespace in @-style blocks. Fixes haskell/haddock#201. - - - - - 98208294 by Niklas Haas at 2014-03-31T20:09:58+02:00 Crash when exporting record selectors of data family instances This fixes bug haskell/haddock#294. This also fixes a related but never-before-mentioned bug about the display of GADT record selectors with non-polymorphic type signatures. Note: Associated data type constructors fail to show up if nothing is exported that they could be attached to. Exporting any of the data types in the instance head, or the class + data family itself, causes them to show up, but in the absence of either of these, exporting just the associated data type with the constructor itself will result in it being hidden. The only scenario I can come up that would involve this kind of situation involved OverlappingInstances, and even then it can be mitigated by just exporting the class itself, so I'm not going to solve it since the logic would most likely be very complicated. - - - - - 3832d171 by Mateusz Kowalczyk at 2014-04-01T19:07:33+01:00 Make CHANGES consistent with what's now in 2.14.2 - - - - - c386ae89 by Mateusz Kowalczyk at 2014-04-01T19:18:36+01:00 Actually bundle extra spec tests in sdist - - - - - bd57a6d3 by Mateusz Kowalczyk at 2014-04-03T21:13:48+01:00 Update test cases for GHC bug haskell/haddock#8945, Haddock haskell/haddock#188 The order of signature groups has been corrected upstream. Here we add a test case and update some existing test-cases to reflect this change. We remove grouped signature in test cases that we can (Minimal, BugDeprecated &c) so that the test is as self-contained as possible. - - - - - 708b88b1 by Mateusz Kowalczyk at 2014-04-03T21:16:07+01:00 Enforce strict GHC version in cabal file This stops people with 7.6.3 trying to install 2.15.x which clearly won't work. Unfortunately we shipped 2.14.x without realising this. - - - - - 60334f7c by Mateusz Kowalczyk at 2014-04-03T21:19:24+01:00 Initialise some new PlatformConstants fields - - - - - ea77f668 by Mateusz Kowalczyk at 2014-04-11T16:52:23+01:00 We don't actually want unicode here - - - - - 0b651cae by Mateusz Kowalczyk at 2014-04-11T18:13:30+01:00 Parse identifiers with ^ and ⋆ in them. Fixes haskell/haddock#298. - - - - - e8ad0f5f by Mateusz Kowalczyk at 2014-04-11T18:47:41+01:00 Ignore version string during HTML tests. - - - - - de489089 by Mateusz Kowalczyk at 2014-04-11T18:59:30+01:00 Update CHANGES to follow 2.14.3 - - - - - beb464a9 by Gergő Érdi at 2014-04-13T16:31:10+08:00 remove Origin flag from LHsBindsLR - - - - - cb16f07c by Herbert Valerio Riedel at 2014-04-21T17:16:50+02:00 Replace local `die` by new `System.Exit.die` Starting with GHC 7.10, System.Exit exports the new `die` which is essentially the same as Haddock.Util.die, so this commit changes Haddock.Util.die to be a simple re-export of System.Exit.die. See also https://ghc.haskell.org/trac/ghc/ticket/9016 for more details. Signed-off-by: Herbert Valerio Riedel <hvr at gnu.org> - - - - - 9b9b23c7 by Mateusz Kowalczyk at 2014-05-03T15:40:11+02:00 Disambiguate ‘die’ in test runners. - - - - - 5d28a2b8 by Mateusz Kowalczyk at 2014-05-05T09:19:49+02:00 Prepare modules for parser split. We have to generalise the Doc (now DocH) slightly to remove the dependency on GHC-supplied type. - - - - - d3967ff3 by Mateusz Kowalczyk at 2014-05-05T11:00:41+02:00 Move parser + parser tests out to own package. We move some types out that are necessary as well and then re-export and specialise them in the core Haddock. Reason for moving out spec tests is that if we're working on the parser, we can simply work on that and we can ignore the rest of Haddock. The downside is that it's a little inconvenient if at the end of the day we want to see that everything passes. - - - - - 522a448d by Mateusz Kowalczyk at 2014-05-05T11:14:47+02:00 Move out Show and Eq instances to Types They are much more useful to the users here. - - - - - 11a6f0f2 by Mateusz Kowalczyk at 2014-05-06T13:50:31+02:00 Remove no longer necessary parser error handling. We can now drop some Maybe tests and even lets us strip an error handling monad away in a few places. - - - - - 6992c924 by Mateusz Kowalczyk at 2014-05-14T02:23:55+02:00 Please the GHC build-system. As I can not figure out how to do this properly, if we're in GHC tree, we treat the library as being the same package. If we're not in the tree, we require that the library be installed separately. - - - - - 7a8ad763 by Mateusz Kowalczyk at 2014-05-14T14:50:25+02:00 Update issue tracker URL - - - - - f616c521 by Mateusz Kowalczyk at 2014-05-14T14:53:32+02:00 Update issue tracker URL for haddock-library - - - - - 66580ded by Gergő Érdi at 2014-05-25T14:24:16+08:00 Accomodate change in PatSyn representation - - - - - 0e43b988 by Mateusz Kowalczyk at 2014-05-29T03:15:29+02:00 Revert "Accomodate change in PatSyn representation" This reverts commit 57aa591362d7c8ba21285fccd6a958629a422091. I am reverting this because I pushed it to master when it was meant to stay on a wip-branch. Sorry Gergo and everyone who had trouble due to this. - - - - - e10d7ec8 by Mateusz Kowalczyk at 2014-05-29T03:24:11+02:00 Revert "Revert "Accomodate change in PatSyn representation"" This reverts commit e110e6e70e40eed06c06676fd2e62578da01d295. Apparently as per GHC commit ac2796e6ddbd54c5762c53e2fcf29f20ea162fd5 this was actually intended. Embarrasing for me. - - - - - 5861aca9 by Mateusz Kowalczyk at 2014-06-05T19:49:27+02:00 Clear up highlighting of identifiers with ‘'’s. - - - - - d7cc420f by Simon Peyton Jones at 2014-06-06T12:41:09+01:00 Follow change in patSynSig - - - - - 938b4fd8 by Mateusz Kowalczyk at 2014-06-12T07:24:29+02:00 Slightly update the readme. Style-sheets are no longer a recent thing, dead links, old maintainers, different formats. - - - - - c7799dea by Mateusz Kowalczyk at 2014-06-18T00:05:56+02:00 Update cabal files Update repository urls, use subdir property for haddock-library and use a separate versioning scheme for haddock-library in preparation for release. - - - - - a2750b6a by Simon Hengel at 2014-06-18T11:01:18+08:00 Compatibility with older versions of base and bytestring - - - - - 009b4b03 by Simon Hengel at 2014-06-18T11:14:01+08:00 Enable travis-ci for haddock-library - - - - - 9b5862eb by Simon Hengel at 2014-06-18T11:14:01+08:00 haddock-library: Do not depend on haddock-library in test suite I think you either add src to hs-source-dirs or the library to build-depends. But doing both does not make sense (AFAICT). - - - - - fb1f3279 by Simon Hengel at 2014-06-18T11:49:05+08:00 haddock-library: Use -Wall for specs - - - - - 649340e1 by Mateusz Kowalczyk at 2014-06-18T06:58:54+02:00 Use Travis with multiple GHC versions When using HEAD, we build haddock-library directly from repository as a dependency (and thanks to --enable-tests, the tests get ran anyway). In all other cases, we manually run the tests on haddock-library only and don't test the main project. - - - - - d7eeeec2 by Mateusz Kowalczyk at 2014-06-18T07:49:04+02:00 Comment improvements + few words in cabal file - - - - - 0f8db914 by Simon Hengel at 2014-06-18T13:52:23+08:00 Use doctest to check examples in documentation - - - - - 2888a8dc by Simon Hengel at 2014-06-18T14:16:48+08:00 Remove doctest dependency (so that we can use haddock-library with doctest) - - - - - 626d5e85 by Mateusz Kowalczyk at 2014-06-18T08:41:25+02:00 Travis tweaks - - - - - 41d4f9cc by Mateusz Kowalczyk at 2014-06-18T08:58:43+02:00 Don't actually forget to install specified GHC. - - - - - c6aa512a by John MacFarlane at 2014-06-18T10:43:57-07:00 Removed reliance on LambdaCase (which breaks build with ghc 7.4). - - - - - b9b93b6f by John MacFarlane at 2014-06-18T10:54:56-07:00 Fixed haddock warnings. - - - - - a41b0ab5 by Mateusz Kowalczyk at 2014-06-19T01:20:10+02:00 Update Travis, bump version - - - - - 864bf62a by Mateusz Kowalczyk at 2014-06-25T10:36:54+02:00 Fix anchors. Closes haskell/haddock#308. - - - - - 53df91bb by Mateusz Kowalczyk at 2014-06-25T15:04:49+02:00 Drop DocParagraph from front of headers I can not remember why they were wrapped in paragraphs to begin with and it seems unnecessary now that I test it. Closes haskell/haddock#307. - - - - - 29b5f2fa by Mateusz Kowalczyk at 2014-06-25T15:17:20+02:00 Don't mangle append order for nested lists. The benefit of this is that the ‘top-level’ element of such lists is properly wrapped in <p> tags so any CSS working with these will be applied properly. It also just makes more sense. Pointed out at jgm/pandoc#1346. - - - - - 05cb6e9c by Mateusz Kowalczyk at 2014-06-25T15:19:45+02:00 Bump haddock-library to 1.1.0 for release - - - - - 70feab15 by Iavor Diatchki at 2014-07-01T03:37:07-07:00 Propagate overloading-mode for instance declarations in haddock (#9242) - - - - - d4ca34a7 by Simon Peyton Jones at 2014-07-14T16:23:15+01:00 Adapt to new definition of HsDecls.TyFamEqn This is a knock-on from the refactoring from Trac haskell/haddock#9063. I'll push the corresponding changes to GHC shortly. - - - - - f91e2276 by Edward Z. Yang at 2014-07-21T08:14:19-07:00 Track GHC PackageId to PackageKey renaming. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - b010f9ef by Edward Z. Yang at 2014-07-25T16:28:46-07:00 Track changes for module reexports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: src/Haddock/Interface/Create.hs - - - - - 8b85f9f9 by Mateusz Kowalczyk at 2014-07-28T13:25:43+02:00 Catch mid-line URLs. Fixes haskell/haddock#314. - - - - - 4c613a78 by Edward Z. Yang at 2014-08-05T03:11:00-07:00 Track type signature change of lookupModuleInAllPackages Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - e80b051c by Edward Z. Yang at 2014-08-05T17:34:26+01:00 If GhcProfiled, also build Haddock profiled. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f9cccd29 by Edward Z. Yang at 2014-08-07T14:23:35+01:00 Ignore TAGS files. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 00b3af52 by Mateusz Kowalczyk at 2014-08-08T04:58:19+02:00 Update to attoparsec-0.12.1.1 There seems to be memory and speed improvement. - - - - - 5457dc71 by Mateusz Kowalczyk at 2014-08-08T18:24:02+02:00 Fix forgotten src - - - - - 3520cb04 by Mateusz Kowalczyk at 2014-08-14T20:19:07+01:00 Bump down the version for master to 2.14.4 - - - - - dc98c21b by Mateusz Kowalczyk at 2014-08-14T20:23:27+01:00 Revert "Track type signature change of lookupModuleInAllPackages" This reverts commit d59fec2c9551b5662a3507c0011e32a09a9c118f. - - - - - 3f2038c0 by Mateusz Kowalczyk at 2014-08-14T20:23:31+01:00 Revert "Track changes for module reexports." This reverts commit b99b57c0df072d12b67816b45eca2a03cb1da96d. - - - - - 56d4e49e by Mateusz Kowalczyk at 2014-08-14T20:23:42+01:00 Revert "Track GHC PackageId to PackageKey renaming." This reverts commit 8ac42d3327473939c013551750425cac191ff0fd. - - - - - 726ea3cb by Mateusz Kowalczyk at 2014-08-14T20:23:47+01:00 Revert "Adapt to new definition of HsDecls.TyFamEqn" This reverts commit cb96b4f1ed0462b4a394b9fda6612c3bea9886bd. - - - - - 61a88ff0 by Mateusz Kowalczyk at 2014-08-14T20:23:52+01:00 Revert "Propagate overloading-mode for instance declarations in haddock (#9242)" This reverts commit 8d20ca8d5a9bee73252ff2035ec45f9c03d0820c. - - - - - a32ba674 by Mateusz Kowalczyk at 2014-08-14T20:26:03+01:00 Revert "Disambiguate ‘die’ in test runners." This reverts commit dba02d6df32534aac5d257f2d28596238d248942. - - - - - f335820f by Mateusz Kowalczyk at 2014-08-14T20:26:09+01:00 Revert "Replace local `die` by new `System.Exit.die`" This reverts commit 08aa509ebac58bfb202ea79c7c41291ec280a1c5. - - - - - 107078e4 by Mateusz Kowalczyk at 2014-08-14T20:27:34+01:00 Merge branch 'reverts' This reverts any changes that were made to have Haddock compile with 7.9. When 7.10 release comes, we can simply re-apply all the patches and any patches that occur on ghc-head branch from now on. This allows us to build master with 7.8.3 - - - - - b44b3871 by Mateusz Kowalczyk at 2014-08-15T02:47:40+01:00 Fix haskell/haddock#313 by doing some list munging. I get rid of the Monoid instance because we weren't satisfying the laws. Convenience of having <> didn't outweigh the shock-factor of having it behave badly. - - - - - e1a62cde by Mateusz Kowalczyk at 2014-08-15T02:52:56+01:00 Stop testing haskell/haddock#188. Because the change is in GHC 7.9 and we now work against 7.8.3, this test no longer makes sense. We revert it until 7.10 becomes the standard version. If anything, there should be a test for this in GHC itself. - - - - - 54e8286d by Mateusz Kowalczyk at 2014-08-15T05:31:57+01:00 Add haskell/haddock#313 to CHANGES - - - - - 9df7ad5d by Simon Hengel at 2014-08-20T11:25:32+08:00 Fix warning - - - - - ee2574d6 by Simon Hengel at 2014-08-20T12:07:01+08:00 Fix travis builds - - - - - 384cf2e6 by Simon Hengel at 2014-08-20T12:14:31+08:00 Require GHC 7.8.3 - - - - - d4779863 by Simon Hengel at 2014-08-22T12:14:16+08:00 Move Haddock API to a separate package - - - - - 80f3e0e1 by Simon Hengel at 2014-08-22T14:57:38+08:00 Bump version to 2.15.0 and add version constraints - - - - - 309a94ce by Simon Hengel at 2014-08-22T15:18:06+08:00 Add deprecated compatibility module - - - - - 4d1e4e3f by Luite Stegeman at 2014-08-22T20:46:45+02:00 export things to allow customizing how the Ghc session is run - - - - - 47884591 by Luite Stegeman at 2014-08-22T20:46:51+02:00 ghc 7.8.2 compatibility - - - - - 5ea94e2c by Luite Stegeman at 2014-08-22T22:08:58+02:00 install dependencies for haddock-api on travis - - - - - 9fb845b2 by Mateusz Kowalczyk at 2014-08-23T10:09:34+01:00 Move sources under haddock-api/src - - - - - 85817dc4 by Mateusz Kowalczyk at 2014-08-23T10:10:48+01:00 Remove compat stuff - - - - - 151c6169 by Niklas Haas at 2014-08-24T08:14:10+02:00 Fix extra whitespace on signatures and update all test cases This was long overdue, now running ./accept.lhs on a clean test from master will not generate a bunch of changes. - - - - - d320e0d2 by Niklas Haas at 2014-08-24T08:14:35+02:00 Omit unnecessary foralls and fix haskell/haddock#315 This also fixes haskell/haddock#86. - - - - - bdafe108 by Mateusz Kowalczyk at 2014-08-24T15:06:46+01:00 Update CHANGES - - - - - fafa6d6e by Mateusz Kowalczyk at 2014-08-24T15:14:23+01:00 Delete few unused/irrelevant/badly-place files. - - - - - 3634923d by Duncan Coutts at 2014-08-27T13:49:31+01:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. - - - - - 539a7e70 by Herbert Valerio Riedel at 2014-08-31T11:36:32+02:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 9e3a0e5b by Mateusz Kowalczyk at 2014-08-31T12:54:43+01:00 Bump version in doc - - - - - 4a177525 by Mateusz Kowalczyk at 2014-08-31T13:01:23+01:00 Bump haddock-library version - - - - - f99c1384 by Mateusz Kowalczyk at 2014-08-31T13:05:25+01:00 Remove references to deleted files - - - - - 5e51a247 by Mateusz Kowalczyk at 2014-08-31T14:18:44+01:00 Make the doc parser not complain - - - - - 2cedb49a by Mateusz Kowalczyk at 2014-09-03T03:33:15+01:00 CONTRIBUTING file for issues - - - - - 88027143 by Mateusz Kowalczyk at 2014-09-04T00:46:59+01:00 Mention --print-missing-docs - - - - - 42f6754f by Alan Zimmerman at 2014-09-05T18:13:24-05:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e712719e by Austin Seipp at 2014-09-09T01:03:27-05:00 Fix import of 'empty' due to AMP. Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 71c29755 by Herbert Valerio Riedel at 2014-09-09T17:35:20+02:00 Bump `base` constraint for AMP - - - - - 0bf9f3ed by Mateusz Kowalczyk at 2014-09-12T19:18:32+01:00 Delete stale ANNOUNCE - - - - - cac89ee6 by Krzysztof Gogolewski at 2014-09-14T17:17:09+02:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 4d683426 by Edward Z. Yang at 2014-09-18T13:38:11-07:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 80697fd5 by Herbert Valerio Riedel at 2014-09-19T00:07:52+02:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. - - - - - c015eb70 by Herbert Valerio Riedel at 2014-09-19T00:10:36+02:00 Revert "Followup changes to addition of -fwarn-context-quantification" This reverts commit 4023817d7c0e46db012ba2eea28022626841ca9b temporarily as the respective feature hasn't landed in GHC HEAD yet, but this commit blocks later commits from being referenced in GHC HEAD. - - - - - 38ded784 by Edward Z. Yang at 2014-09-18T15:32:15-07:00 Revert "Revert "Followup changes to addition of -fwarn-context-quantification"" This reverts commit db14fd8ab4fab43694139bc203808b814eafb2dc. It's in HEAD now. - - - - - f55d59c9 by Herbert Valerio Riedel at 2014-09-26T19:18:28+02:00 Revert "Fix import of 'empty' due to AMP." This reverts commit 0cc5bc85e9fca92ab712b68a2ba2c0dd9d3d79f4 since it turns out we don't need to re-export `empty` from Control.Monad after all. - - - - - 467050f1 by David Feuer at 2014-10-09T20:07:36-04:00 Fix improper lazy IO use Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. - - - - - cc47b699 by Edward Z. Yang at 2014-10-09T21:38:19-07:00 Fix use-after-close lazy IO bug Make `getPrologue` force `parseParas dflags str` before returning. Without this, it will attempt to read from the file after it is closed, with unspecified and generally bad results. Signed-off-by: David Feuer <David.Feuer at gmail.com> Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 87babcbe by Austin Seipp at 2014-10-20T20:05:27-05:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - ab259516 by Austin Seipp at 2014-10-20T20:07:01-05:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - b918093c by Mateusz Kowalczyk at 2014-10-29T03:59:39+00:00 Experimental support for collapsable headers Closes haskell/haddock#335 - - - - - 849db129 by Mateusz Kowalczyk at 2014-10-29T10:07:26+01:00 Experimental support for collapsable headers (cherry picked from commit e2ed3b9d8dfab09f1b1861dbc8e74f08e137ebcc) - - - - - a4cc4789 by Herbert Valerio Riedel at 2014-10-31T11:08:26+01:00 Collapse user-defined section by default (re haskell/haddock#335) - - - - - 9da1b33e by Yuras Shumovich at 2014-10-31T16:11:04-05:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - c625aefc by Austin Seipp at 2014-10-31T19:34:10-05:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - c7738e5e by Simon Hengel at 2014-11-02T07:25:30+08:00 Remove -fobject-code from .ghci (this slows down reloads on modifications) - - - - - d4a86e95 by Simon Hengel at 2014-11-03T09:26:11+08:00 Get rid of StandaloneDeriving - - - - - a974e311 by Simon Hengel at 2014-11-03T09:26:11+08:00 Derive more instances - - - - - 8aa0c4d7 by Simon Hengel at 2014-11-03T09:27:08+08:00 Remove unused language extensions - - - - - 3052d46a by Simon Hengel at 2014-11-03T09:30:46+08:00 Minor refactoring - - - - - 4281d3cb by Simon Hengel at 2014-11-03T09:30:46+08:00 parser: Try to parse definition lists right before text paragraphs - - - - - 8ba12bf9 by Simon Hengel at 2014-11-03T09:34:19+08:00 Add support for markdown links (closes haskell/haddock#336) - - - - - a2f8d747 by Simon Hengel at 2014-11-03T09:34:19+08:00 Allow markdown links at the beginning of a paragraph - - - - - 53b11207 by Simon Hengel at 2014-11-03T09:34:20+08:00 Update documentation - - - - - 652267c6 by Simon Hengel at 2014-11-03T09:34:20+08:00 Add support for markdown images - - - - - 9d667502 by Simon Hengel at 2014-11-03T09:34:20+08:00 Allow an optional colon after the closing bracket of definition lists This is to disambiguate them from markdown links and will be require with a future release. - - - - - 8167fc32 by Mateusz Kowalczyk at 2014-11-04T01:16:51+00:00 whitespace only - - - - - 3da62981 by Mateusz Kowalczyk at 2014-11-04T01:17:31+00:00 Fix re-exports of built-in type families Fixes haskell/haddock#310 - - - - - edc76b34 by Mateusz Kowalczyk at 2014-11-04T02:54:28+00:00 Turn some uses of error into recoverable warnings This should at the very least not abort when something weird happens. It does feel like we should have a type that carries these errors until the end however as the user might not see them unless they are printed at the end. - - - - - 0a137400 by Mateusz Kowalczyk at 2014-11-04T04:09:44+00:00 Fix warnings - - - - - d068fc21 by Mateusz Kowalczyk at 2014-11-04T21:04:07+00:00 Fix parsing of identifiers written in infix way - - - - - 1a9f2f3d by Simon Hengel at 2014-11-08T11:32:42+08:00 Minor code simplification - - - - - 6475e9b1 by Simon Hengel at 2014-11-08T17:28:33+08:00 newtype-wrap parser monad - - - - - dc1ea105 by Herbert Valerio Riedel at 2014-11-15T11:55:43+01:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - fbb1aca4 by Simon Hengel at 2014-11-16T08:51:38+08:00 State intention rather than implementation details in Haddock comment - - - - - 97851ab2 by Simon Hengel at 2014-11-16T10:20:19+08:00 (wip) Add support for @since (closes haskell/haddock#26) - - - - - 34bcd18e by Gergő Érdi at 2014-11-20T22:35:38+08:00 Update Haddock to new pattern synonym type signature syntax - - - - - 304b7dc3 by Jan Stolarek at 2014-11-20T17:48:43+01:00 Follow changes from haskell/haddock#9812 - - - - - 920f9b03 by Richard Eisenberg at 2014-11-20T16:52:50-05:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 0bfe4e78 by Alan Zimmerman at 2014-11-21T11:23:09-06:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 356ed45a by Thomas Winant at 2014-11-28T16:11:22-06:00 Support for PartialTypeSignatures - - - - - 5dc8f3b1 by Gergő Érdi at 2014-11-29T15:39:09+08:00 For pattern synonyms, render "pattern" as a keyword - - - - - fe704480 by Mateusz Kowalczyk at 2014-12-09T03:38:32+00:00 List new module in cabal file - - - - - b9ad5a29 by Mateusz Kowalczyk at 2014-12-10T00:58:24+00:00 Allow the parser to spit out meta-info Currently we only use it only for ‘since’ annotations but with these patches it should be fairly simple to add new attributes if we wish to. Closes haskell/haddock#26. It seems to work fine but due to 7.10 rush I don't have the chance to do more exhaustive testing right now. The way the meta is output (emphasis at the end of the whole comment) is fairly arbitrary and subject to bikeshedding. Note that this makes test for Bug310 fail due to interface version bump: it can't find the docs for base with this interface version so it fails. There is not much we can do to help this because it tests for ’built-in’ identifier, not something we can provide ourselves. - - - - - 765af0e3 by Mateusz Kowalczyk at 2014-12-10T01:17:19+00:00 Update doctest parts of comments - - - - - 8670272b by jpmoresmau at 2014-12-10T01:35:31+00:00 header could contain several lines Closes haskell/haddock#348 - - - - - 4f9ae4f3 by Mateusz Kowalczyk at 2014-12-12T06:22:31+00:00 Revert "Merge branch 'reverts'" This reverts commit 5c93cc347773c7634321edd5f808d5b55b46301f, reversing changes made to 5b81a9e53894d2ae591ca0c6c96199632d39eb06. Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - e974ac94 by Duncan Coutts at 2014-12-12T06:26:11+00:00 Changes due to ghc api changes in package representation Also fix a bug with finding the package name and version given a module. This had become wrong due to the package key changes (it was very hacky in the first place). We now look up the package key in the package db to get the package info properly. Conflicts: haddock-api/src/Haddock.hs - - - - - 2f3a2365 by Herbert Valerio Riedel at 2014-12-12T06:26:51+00:00 Import Data.Word w/o import-list This is needed to keep the compilation warning free (and thus pass GHC's ./validate) regardless of whether Word is re-exported from Prelude or not See https://ghc.haskell.org/trac/ghc/ticket/9531 for more details - - - - - 1dbd6390 by Alan Zimmerman at 2014-12-12T06:32:07+00:00 Follow changes to TypeAnnot in GHC HEAD Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - bb6ff1f4 by Mateusz Kowalczyk at 2014-12-12T06:35:07+00:00 Bump ‘base’ constraint Follows the similar commit made on ghc-head branch - - - - - 466fe4ab by Krzysztof Gogolewski at 2014-12-12T06:37:42+00:00 Followup changes to addition of -fwarn-context-quantification (GHC Trac haskell/haddock#4426) - - - - - 97e080c9 by Edward Z. Yang at 2014-12-12T06:39:35+00:00 Properly render package ID (not package key) in index, fixes haskell/haddock#329. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> Conflicts: haddock-api/src/Haddock/ModuleTree.hs - - - - - 20b2af56 by Herbert Valerio Riedel at 2014-12-12T06:42:50+00:00 Disambiguate string-literals GHC fails type-inference with `OverloadedStrings` + `Data.Foldable.elem` otherwise. Conflicts: haddock-library/src/Documentation/Haddock/Parser.hs - - - - - b3ad269d by Austin Seipp at 2014-12-12T06:44:14+00:00 Add an .arcconfig file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - 072df0dd by Austin Seipp at 2014-12-12T06:45:01+00:00 Add .arclint file. Signed-off-by: Austin Seipp <austin at well-typed.com> - - - - - dbb9294a by Herbert Valerio Riedel at 2014-12-12T06:46:17+00:00 Collapse user-defined section by default (re haskell/haddock#335) Conflicts: haddock-api/src/Haddock/Backends/Xhtml/DocMarkup.hs - - - - - f23ab545 by Yuras Shumovich at 2014-12-12T06:46:41+00:00 reflect ForeignType constructore removal Reviewers: austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D358 - - - - - 753a4b67 by Austin Seipp at 2014-12-12T06:46:51+00:00 Remove overlapping pattern match Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8954e8f5 by Herbert Valerio Riedel at 2014-12-12T06:50:53+00:00 Make compatible with `deepseq-1.4.0.0` ...by not relying on the default method implementation of `rnf` - - - - - d2b06d61 by Gergő Érdi at 2014-12-12T07:07:30+00:00 Update Haddock to new pattern synonym type signature syntax Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 1ff02426 by Jan Stolarek at 2014-12-12T07:13:24+00:00 Follow changes from haskell/haddock#9812 Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - 06ad7600 by Richard Eisenberg at 2014-12-12T07:13:43+00:00 Changes to reflect refactoring in GHC as part of haskell/haddock#7484 - - - - - 8fd2aa8b by Alan Zimmerman at 2014-12-12T07:22:25+00:00 Follow API changes in D426 Signed-off-by: Austin Seipp <aseipp at pobox.com> Conflicts: haddock-api/src/Haddock/Backends/LaTeX.hs haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs - - - - - 95c3db98 by Thomas Winant at 2014-12-12T07:35:49+00:00 Support for PartialTypeSignatures Conflicts: haddock-api/src/Haddock/Backends/Xhtml/Decl.hs haddock-api/src/Haddock/Convert.hs haddock-api/src/Haddock/Interface/Create.hs - - - - - 45494428 by Gergő Érdi at 2014-12-12T07:36:18+00:00 For pattern synonyms, render "pattern" as a keyword - - - - - a237e3eb by Mateusz Kowalczyk at 2014-12-12T12:27:13+00:00 Various fixups and bumps for next release - - - - - 22918bcd by Herbert Valerio Riedel at 2014-12-14T10:11:47+01:00 Remove redundant wild-card pattern match (this would otherwise cause a build-failure with `-Werror`) - - - - - 1d6ce947 by Herbert Valerio Riedel at 2014-12-14T10:17:06+01:00 Treat GHC 7.10 the same as GHC 7.9 ...since the current GHC 7.9 is going to become GHC 7.10 real-soon-now anyway - - - - - f434ea89 by Herbert Valerio Riedel at 2014-12-14T18:26:50+01:00 Fixup ghc.mk (follow-up to 1739375eb23342) This makes the GHC build-system aware of the data-files to be copied into the bindist (as haddock.cabal doesn't list those anymore) - - - - - 6fb839eb by Mateusz Kowalczyk at 2014-12-17T09:28:59+00:00 Only keep one Version instead of blindly appending - - - - - 40645489 by Mateusz Kowalczyk at 2014-12-18T07:09:44+00:00 Fix dependency version - - - - - 8b3b927b by Mateusz Kowalczyk at 2014-12-18T07:14:23+00:00 Print missing docs by default Adds --no-print-missing-docs - - - - - 59666694 by Mateusz Kowalczyk at 2014-12-18T07:21:37+00:00 update changelog - - - - - aa6d168e by Mateusz Kowalczyk at 2014-12-18T07:30:58+00:00 Update docs for @since - - - - - 2d7043ee by Luite Stegeman at 2014-12-19T18:29:35-06:00 hide projectVersion from DynFlags since it clashes with Haddock.Version.projectVersion - - - - - aaa70fc0 by Luite Stegeman at 2014-12-22T15:58:43+01:00 Add missing import for standalone haddock-api package - - - - - 9ce01269 by Herbert Valerio Riedel at 2014-12-22T17:48:45+01:00 Reset ghc-head with master's tree (this is an overwriting git merge of master into ghc-head) - - - - - fcd6fec1 by Herbert Valerio Riedel at 2014-12-22T17:51:52+01:00 Bump versions for ghc-7.11 - - - - - 525ec900 by Mateusz Kowalczyk at 2014-12-23T13:36:24+00:00 travis-ci: test with HEAD - - - - - cbf494b5 by Simon Peyton Jones at 2014-12-23T15:22:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 50e01c99 by Mateusz Kowalczyk at 2014-12-29T15:28:47+00:00 Make travis use 7.10.x - - - - - 475e60b0 by Njagi Mwaniki at 2014-12-29T15:30:44+00:00 Turn the README into GitHub Markdown format. Closes haskell/haddock#354 - - - - - 8cacf48e by Luite Stegeman at 2015-01-05T16:25:37+01:00 bump haddock-api ghc dependency to allow release candidate and first release - - - - - 6ed6cf1f by Simon Peyton Jones at 2015-01-06T16:37:47+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 8b484f33 by Simon Peyton Jones at 2015-01-08T15:50:22+00:00 Track naming change in DataCon - - - - - 23c5c0b5 by Alan Zimmerman at 2015-01-16T10:15:11-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - e7a5532c by JP Moresmau at 2015-01-22T17:19:03+00:00 Ignore warnings, install Cabal 1.22 - - - - - 86942c84 by jpmoresmau at 2015-01-22T17:19:04+00:00 solve dataDir ambiguity - - - - - 5ceb743e by jpmoresmau at 2015-01-22T19:17:32+00:00 support GHC 7.10: no Safe-Inferred, Foldable instance - - - - - 6a3b3fb5 by Mateusz Kowalczyk at 2015-01-22T19:32:10+00:00 Update test files Test: a correct behaviour for fields comma-separating values. I'm surprised we had no bug open for this. Maybe it affects how haskell/haddock#301 renders now but I doubt. Operators: Seems GHC is giving us a new order for operators, something must have changed on their side again. cc @haasn , this makes the fixity to the side not match the order on the LHS which is a bit unpleasant. Maybe the fixity can be made to match the GHC order? Bug335: We expand examples by default now. Bug310: Now inferred safe. - - - - - 708f8b2f by jpmoresmau at 2015-01-22T19:36:59+00:00 Links to source location of class instance definitions - - - - - 5cf8a6da by Vincent Berthoux at 2015-01-22T19:59:58+00:00 Filter '\r' from comments due to Windows problems. On Windows this was causing newline to be rendered twice in code blocks. Closes haskell/haddock#359, fixes haskell/haddock#356. - - - - - 1749e6f0 by Mateusz Kowalczyk at 2015-01-22T20:31:27+00:00 Changelog only - - - - - c8145f90 by Mateusz Kowalczyk at 2015-01-22T23:34:05+00:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. - - - - - 14248254 by Mateusz Kowalczyk at 2015-01-22T23:43:18+00:00 Sort out some module import warnings - - - - - d8a38989 by Simon Peyton Jones at 2015-01-23T07:10:16-06:00 Track naming change in DataCon (cherry picked from commit 04cf63d0195837ed52075ed7d2676e71831e8a0b) - - - - - d3ac6ae4 by Alan Zimmerman at 2015-01-23T07:17:19-06:00 Follow API changes in D538 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit d61bbc75890e4eb0ad508b9c2a27b91f691213e6) - - - - - 4c1ffeb0 by Simon Peyton Jones at 2015-02-10T12:10:33+00:00 Track changes in HsSyn for quasi-quotes - - - - - 775d20f7 by Mateusz Kowalczyk at 2015-03-15T08:11:48+01:00 --package-name and --package-version flags Used for --hoogle amongst other things. Now we need to teach cabal to use it. The situation is still a bit sub-par because if the flags aren't passed in, the crash will occur. Closes haskell/haddock#353. (cherry picked from commit 8e06728afb0784128ab2df0be7a5d7a191d30ff4) - - - - - f9245e72 by Phil Ruffwind at 2015-03-16T04:32:01-04:00 Prevent Synopsis from using up too much horizontal space When long type signatures occur in the Synopsis, the element is stretched beyond the width of the window. Scrollbars don't appear, so it's impossible to read anything when this happens. - - - - - cd8fa415 by Mateusz Kowalczyk at 2015-03-17T21:59:39+00:00 Update changelog Closes haskell/haddock#151 due to 71170fc77962f10d7d001e3b8bc8b92bfeda99bc - - - - - b5248b47 by Ben Gamari at 2015-03-25T17:12:17+00:00 Make the error encountered when a package can't be found more user-friendly Closes haskell/haddock#369 - - - - - b756b772 by Mateusz Kowalczyk at 2015-03-26T16:31:40+00:00 Remove now redundant imports - - - - - 5ea5e8dd by Mateusz Kowalczyk at 2015-03-26T16:45:52+00:00 Update test to account for \r filtering - - - - - 6539bfb3 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Test for anchor defaulting I delete the old tests because it turns out that: * test runner would never put them in scope of each other even with imports so just one would suffice * test runner actually needed some hacking to keep links so in the end we would end up with no anchors making them useless - - - - - 1a01d950 by Mateusz Kowalczyk at 2015-03-27T00:20:09+00:00 Clearly default to variables in out of scope case - - - - - 7943abe8 by Mateusz Kowalczyk at 2015-03-27T01:14:11+00:00 Fix Hoogle display of constructors Fixes haskell/haddock#361 - - - - - 6d6e587e by Mateusz Kowalczyk at 2015-03-27T01:45:18+00:00 Fully qualify names in Hoogle instances output Closes haskell/haddock#263 - - - - - 52dac365 by Mateusz Kowalczyk at 2015-03-27T01:55:01+00:00 Update changelog - - - - - ca5af9a8 by Mateusz Kowalczyk at 2015-03-27T02:43:55+00:00 Output method documentation in Hoogle backend One thing of note is that we no longer preserve grouping of methods and print each method on its own line. We could preserve it if no documentation is present for any methods in the group if someone asks for it though. Fixes haskell/haddock#259 - - - - - a33f0c10 by Mateusz Kowalczyk at 2015-03-27T03:04:21+00:00 Don't print instance safety information in Hoogle Fixes haskell/haddock#168 - - - - - df6c935a by Mateusz Kowalczyk at 2015-03-28T00:11:47+00:00 Post-release version bumps and changelog - - - - - dde8f7c0 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Loosen bounds on haddock-* - - - - - de93bf89 by Mateusz Kowalczyk at 2015-03-28T20:39:10+00:00 Expand response files in arguments Closes haskell/haddock#285 - - - - - 1f0b0856 by Zejun Wu at 2015-04-26T16:35:35-07:00 Do not insert anchor for section headings in contents box - - - - - 860439d7 by Simon Peyton Jones at 2015-05-01T09:36:47+01:00 Track change in API of TyCon - - - - - a32f3e5f by Adam Gundry at 2015-05-04T15:32:59+01:00 Track API changes to support empty closed type familes - - - - - 77e98bee by Ben Gamari at 2015-05-06T20:17:08+01:00 Ignore doc/haddock.{ps,pdf} - - - - - 663d0204 by Murray Campbell at 2015-05-11T04:47:37-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> - - - - - 8bb0dcf5 by Murray Campbell at 2015-05-11T06:35:06-05:00 Change ModuleTree Node to carry PackageKey and SourcePackageId to resolve haskell/haddock#385 Signed-off-by: Austin Seipp <aseipp at pobox.com> (cherry picked from commit 2380f07c430c525b205ce2eae6dab23c8388d899) - - - - - bad900ea by Adam Bergmark at 2015-05-11T15:29:39+01:00 haddock-library: require GHC >= 7.4 `Data.Monoid.<>` was added in base-4.5/GHC-7.4 Closes haskell/haddock#394 Signed-off-by: Mateusz Kowalczyk <fuuzetsu at fuuzetsu.co.uk> - - - - - daceff85 by Simon Peyton Jones at 2015-05-13T12:04:21+01:00 Track the new location of setRdrNameSpace - - - - - 1937d1c4 by Alan Zimmerman at 2015-05-25T21:27:15+02:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - ee0fb6c2 by Łukasz Hanuszczak at 2015-05-27T11:51:31+02:00 Create simple method for indentation parsing. - - - - - 7d6fcad5 by Łukasz Hanuszczak at 2015-05-27T21:36:13+02:00 Make nested lists count indentation according to first item. - - - - - d6819398 by Łukasz Hanuszczak at 2015-05-27T22:46:13+02:00 Add simple test case for arbitrary-depth list nesting. - - - - - 2929c54d by Łukasz Hanuszczak at 2015-06-03T02:11:31+02:00 Add arbitrary-indent spec test for parser. - - - - - 9a0a9bb0 by Mateusz Kowalczyk at 2015-06-03T05:25:29+01:00 Update docs with info on new list nesting rule Fixes haskell/haddock#278 through commits from PR haskell/haddock#401 - - - - - 12efc92c by Mateusz Kowalczyk at 2015-06-03T05:29:26+01:00 Update some meta data at the top of the docs - - - - - 765ee49f by Bartosz Nitka at 2015-06-07T08:40:59-07:00 Add some Hacking docs for getting started - - - - - 19aaf851 by Bartosz Nitka at 2015-06-07T08:44:30-07:00 Fix markdown - - - - - 2a90cb70 by Mateusz Kowalczyk at 2015-06-08T15:08:36+01:00 Refine hacking instructions slightly - - - - - 0894da6e by Thomas Winant at 2015-06-08T23:47:28-05:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 10a9bb76 by Emanuel Borsboom at 2015-06-12T02:46:23+01:00 Build executable with '-threaded' (fixes haskell/haddock#399) - - - - - 7696b94f by Mateusz Kowalczyk at 2015-06-12T02:59:19+01:00 Update changelog for -threaded Closes haskell/haddock#400 - - - - - d3c118ec by Bartosz Nitka at 2015-06-12T03:00:58+01:00 Fix haddock: internal error: spliceURL UnhelpfulSpan (#207) Inferred type signatures don't have SrcSpans, so let's use the one from the declaration. I've tested this manually on the test-case from haskell/haddock#207, but I got stuck at trying to run the test-suite. - - - - - b67e843b by Mateusz Kowalczyk at 2015-06-12T03:01:50+01:00 Changelog for haskell/haddock#207 Fixes haskell/haddock#207, closes haskell/haddock#402 - - - - - 841d785e by jpmoresmau at 2015-06-12T16:03:16+01:00 Attach to instance location the name that has the same location file Fixes haskell/haddock#383 - - - - - 98791cae by Mateusz Kowalczyk at 2015-06-12T16:08:27+01:00 Update changelog Closes haskell/haddock#398 - - - - - 7c0b5a87 by Phil Ruffwind at 2015-06-12T13:07:25-04:00 Fix alignment of Source links in instance table in Firefox Due to a Firefox bug [1], a combination of 'whitespace: nowrap' on the parent element with 'float: right' on the inner element can cause the floated element to be displaced downwards for no apparent reason. To work around this, the left side is wrapped in its own <span> and set to 'float: left'. As a precautionary measure to prevent the parent element from collapsing entirely, we also add the classic "clearfix" hack. The latter is not strictly needed but it helps prevent bugs if the layout is altered again in the future. Fixes haskell/haddock#384. Remark: line 159 of src/Haddock/Backends/Xhtml/Layout.hs was indented to prevent confusion over the operator precedence of (<+>) vs (<<). [1]: https://bugzilla.mozilla.org/show_bug.cgi?id=488725 - - - - - cfe86e73 by Mateusz Kowalczyk at 2015-06-14T10:49:01+01:00 Update tests for the CSS changes - - - - - 2d4983c1 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding for Haskell source parser module. - - - - - 29548785 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement function for tagging parsed chunks with source spans. - - - - - 6a5e4074 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement simple string chunking based on HsColour library. - - - - - 6e52291f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create basic token classification method. - - - - - da971a27 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Adapt source span tagging to work with current whitespace handling. - - - - - 4feb5a22 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add record accessors to exports of hyperlinker parser module. - - - - - a8cc4e39 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Make parser module export all types and associated accessors. - - - - - fb8d468f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple HTML renderer for parsed source file. - - - - - 80747822 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for specifying the CSS file path in HTML source renderer. - - - - - 994dc1f5 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix identifier recognition in Haskell source parser. - - - - - b1bd0430 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix comment recognition in Haskell source parser. - - - - - 11db85ae by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for recognizing compiler pragmas in source parser. - - - - - 736c7bd3 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create scaffolding of module for associating tokens with AST names. - - - - - 7e149bc2 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement utility method for extracting variable identifiers from AST. - - - - - 32eb640a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Create simple mechanism for associating tokens with AST names. - - - - - d4eba5bc by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add dummy support for hyperlinking named tokens. - - - - - 2b76141f by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matcher bug causing wrong items being hyperlinked. - - - - - 2d48002e by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Constrain elements exported by hyperlinker modules. - - - - - 9715eec6 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for type token recognition. - - - - - 8fa401cb by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Add support for binding token recognition. - - - - - d062400b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement go-to-definition mechanism for local bindings. - - - - - f4dc229b by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Implement module export- and import-list item hyperlinking. - - - - - c9a46d58 by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix span matching to allow parenthesized operators hyperlinking. - - - - - 03aad95a by Łukasz Hanuszczak at 2015-06-30T22:37:48+02:00 Fix weird hyperlinking of parenthesized operators. - - - - - b4694a7d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for type declaration anchors. - - - - - 7358d2d2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for top-level function declaration anchors. - - - - - dfc24b24 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix external anchors to contain HTML file extension. - - - - - a045926c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Refactor the way AST names are handled within detailed tokens. - - - - - c76049b4 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement hyperlinking of imported module names. - - - - - 2d2a1572 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix parsing of single line comments with broken up newlines. - - - - - 11afdcf2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix bug with improper newline handling. - - - - - 8137f104 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issues with escaped newlines in comments. - - - - - 34759b19 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for parsing C preprocessor macros. - - - - - 09f0f847 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for parser module of source hyperlinker. - - - - - 709a8389 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add some documentation for AST module of source hyperlinker. - - - - - 4df5c227 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add command line option for generating hyperlinked source. - - - - - 7a755ea2 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Extend module interface with rich source token stream field. - - - - - 494f4ab1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement source tokenization during interface creation process. - - - - - 5f21c953 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create hyperlinker module and plug it into the Haddock pipeline. - - - - - 0cc8a216 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for providing custom CSS files for hyperlinked source. - - - - - a32bbdc1 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add support for fancy highlighting upon hovering over identifier. - - - - - d16d642a by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make source hyperlinker generate output in apropriate directory. - - - - - ae12953d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Create module with hyperlinker utility functions. - - - - - 6d4952c5 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make external hyperlinks point to locations specified by source URLs. - - - - - 8417555d by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Rewrite source generation to fixed links and directory structure. - - - - - ce9cec01 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Add basic support for cross-package hyperlink generation. - - - - - 7eaf025c by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Disable generating hyperlinks for module references. - - - - - a50bf92e by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make Haddock generate source for all interfaces (also hidden ones). - - - - - f5ae2838 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Prevent source parser from throwing exception when lexing fails. - - - - - db9ffbe0 by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Implement workaround for Chrome highlighting issues. - - - - - 0b6b453b by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate correct anchors for data constructors. - - - - - c86d38bc by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Make hyperlinker generate anchors for record field declarations. - - - - - 063abf7f by Łukasz Hanuszczak at 2015-06-30T22:37:49+02:00 Fix issue with hyperlink highlight styling in Chrome browser. - - - - - 880fc611 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking constructor names in patters. - - - - - c9e89b95 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record patterns. - - - - - 17a11996 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add support for hyperlinking field names in record expressions. - - - - - 0eef932d by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Make hyperlinker respect pretty-printer flag and add documentation. - - - - - f87c1776 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Unexpose hyperlinker modules in Cabal configuration. - - - - - 4c9e2b06 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Setup HSpec framework for Haddock API package. - - - - - 4b20cb30 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add basic tests related to comment parsing. - - - - - 6842e919 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add tests related to parsing basic language constructs. - - - - - 87bffb35 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add simple tests for do-notation parsing. - - - - - e7af1841 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add very simple QuickCheck properties for source parser spec. - - - - - c84efcf1 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Create simple test runner for hyperlinker tests. - - - - - 76b90447 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for basic identifier hyperlinking. - - - - - 0fbf4df6 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for operator hyperlinking. - - - - - 731aa039 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for constructor hyperlinking. - - - - - 995a78a2 by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for record expressions and patterns hyperlinking. - - - - - 3566875a by Łukasz Hanuszczak at 2015-06-30T22:37:50+02:00 Add test case for literal syntax highlighting. - - - - - 68469a35 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add hyperlinker test runner to .cabal and .gitignore files. - - - - - aa946c93 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Adapt hyperlinker test runner to have the same interface as HTML one. - - - - - ce34da16 by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Fix hyperlinker test runner file paths and add pretty-printing option. - - - - - 0d7dd65e by Łukasz Hanuszczak at 2015-06-30T22:38:33+02:00 Add reference files for hyperlinker test cases. - - - - - efa4a1e0 by Łukasz Hanuszczak at 2015-07-01T00:47:32+02:00 Make hyperlinker test runner strip local links from generated source. - - - - - 3e96e584 by Łukasz Hanuszczak at 2015-07-01T01:14:59+02:00 Create simple script for accepting hyperlinker test case references. - - - - - 526fe610 by Łukasz Hanuszczak at 2015-07-01T01:16:41+02:00 Re-accept hyperlinker test cases with local references stripped out. - - - - - 892e2cb3 by Łukasz Hanuszczak at 2015-07-01T01:22:09+02:00 Fix bug with diffing wrong files in hyperlinker test runner. - - - - - 9ff46039 by Łukasz Hanuszczak at 2015-07-01T18:04:46+02:00 Remove unused dependencies in Haddock API spec configuration. - - - - - 47969c07 by Łukasz Hanuszczak at 2015-07-01T18:32:19+02:00 Add support for hyperlinking synonyms in patterns. - - - - - a73449e0 by Łukasz Hanuszczak at 2015-07-01T18:33:44+02:00 Create test case for hyperlinking @-patterns. - - - - - c2077ed8 by Łukasz Hanuszczak at 2015-07-01T19:06:04+02:00 Add support for hyperlinking universally quantified type variables. - - - - - 68017342 by Łukasz Hanuszczak at 2015-07-01T19:28:32+02:00 Create hyperlinker test case with quantified type variables. - - - - - 51c01a78 by Łukasz Hanuszczak at 2015-07-01T19:34:22+02:00 Add scoped type variables test for polymorphism test case. - - - - - 13181ae2 by Łukasz Hanuszczak at 2015-07-01T19:56:27+02:00 Add record wildcards test for records hyperlinking test case. - - - - - 991b81dd by Łukasz Hanuszczak at 2015-07-01T21:01:42+02:00 Document some functions in XHTML utlity module. - - - - - 98c8dfe5 by Łukasz Hanuszczak at 2015-07-01T22:25:21+02:00 Make hyperlinker render qualified names as one entity. - - - - - 75e13b9b by Łukasz Hanuszczak at 2015-07-01T22:27:38+02:00 Add qualified name test for identifiers hyperlinking test case. - - - - - de1e143f by Łukasz Hanuszczak at 2015-07-02T12:32:59+02:00 Fix crash happening when hyperlinking type family declarations. - - - - - 7a8fb175 by Łukasz Hanuszczak at 2015-07-02T12:47:03+02:00 Add support for anchoring data family constructor declarations. - - - - - 3b404e49 by Łukasz Hanuszczak at 2015-07-02T13:31:05+02:00 Improve support for hyperlinking type families. - - - - - 59eb7143 by Łukasz Hanuszczak at 2015-07-02T13:33:34+02:00 Add hyperlinker test case for checking type and type family declarations. - - - - - d1cda0c0 by Łukasz Hanuszczak at 2015-07-02T13:41:38+02:00 Fix issue with operators being recognized as preprocessor directives. - - - - - da206c9d by Łukasz Hanuszczak at 2015-07-02T17:18:12+02:00 Fix broken tests for parsing and hyperlinking hash operators. - - - - - 53750d1b by Łukasz Hanuszczak at 2015-07-02T18:53:28+02:00 Add support for anchoring signatures in type class declarations. - - - - - 1fa5bb10 by Łukasz Hanuszczak at 2015-07-02T19:04:47+02:00 Make hyperlinker generate anchors only to top-level value bindings. - - - - - a542305c by Łukasz Hanuszczak at 2015-07-02T19:05:58+02:00 Create hyperlinker test case for type classes. - - - - - b0dd4581 by Łukasz Hanuszczak at 2015-07-04T16:28:26+02:00 Update docs with information about source hyperlinking. - - - - - 9795302a by Łukasz Hanuszczak at 2015-07-04T16:52:15+02:00 Update docs on using `--read-interface` option. - - - - - 9acdc002 by Łukasz Hanuszczak at 2015-07-04T17:15:26+02:00 Remove potentially dangerous record access in hyperlinker AST module. - - - - - fb3ab7be by Łukasz Hanuszczak at 2015-07-04T17:40:10+02:00 Make Haddock generate warnings about potential misuse of hyperlinker. - - - - - a324c504 by Łukasz Hanuszczak at 2015-07-04T17:43:22+02:00 Fix incorrect specification of source style option in doc file. - - - - - 3f01a8e4 by Łukasz Hanuszczak at 2015-07-05T17:06:36+02:00 Refactor source path mapping to use modules as indices. - - - - - ac70f5b1 by Łukasz Hanuszczak at 2015-07-05T17:47:34+02:00 Fix bug where not all module interfaces were added to source mapping. - - - - - f5e57da9 by Łukasz Hanuszczak at 2015-07-06T16:39:57+02:00 Extract main hyperlinker types to separate module. - - - - - 43974905 by Łukasz Hanuszczak at 2015-07-06T16:52:13+02:00 Move source paths types to hyperlinker types module. - - - - - 3e236055 by Łukasz Hanuszczak at 2015-07-06T17:06:19+02:00 Add support for hyperlinking modules in import lists. - - - - - 58233d9f by Łukasz Hanuszczak at 2015-07-06T17:26:49+02:00 Add short documentation for hyperlinker source map type. - - - - - 14da016d by Łukasz Hanuszczak at 2015-07-06T18:07:20+02:00 Fix bug with module name being hyperlinked to `Prelude`. - - - - - 8f79db52 by Łukasz Hanuszczak at 2015-07-06T18:23:47+02:00 Fix problem with spec build in Haddock API configuration. - - - - - e7cc056c by Adam Sandberg Eriksson at 2015-07-07T23:22:21+01:00 StrictData: print correct strictness marks - - - - - e8253ca8 by Mateusz Kowalczyk at 2015-07-07T23:58:28+01:00 Update changelog - - - - - 0aba676b by Mateusz Kowalczyk at 2015-07-07T23:58:33+01:00 Relax upper bound on GHC a bit - - - - - 7a595381 by Mateusz Kowalczyk at 2015-07-07T23:58:52+01:00 Delete trailing whitespace - - - - - 50976d5e by Adam Sandberg Eriksson at 2015-07-08T15:03:04+02:00 StrictData: changes in HsBang type - - - - - 83b045fa by Mateusz Kowalczyk at 2015-07-11T14:35:18+01:00 Fix expansion icon for user-collapsible sections Closes haskell/haddock#412 - - - - - b2a3b0d1 by Mateusz Kowalczyk at 2015-07-22T22:03:21+01:00 Make some version changes after 2.16.1 release - - - - - a8294423 by Ben Gamari at 2015-07-27T13:16:07+02:00 Merge pull request haskell/haddock#422 from adamse/adamse-D1033 Merge for GHC D1033 - - - - - c0173f17 by randen at 2015-07-30T14:49:08-07:00 Break the response file by line termination rather than spaces, since spaces may be within the parameters. This simple approach avoids having the need for any quoting and/or escaping (although a newline char will not be possible in a parameter and has no escape mechanism to allow it). - - - - - 47c0ca14 by Alan Zimmerman at 2015-07-31T10:41:52+02:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - 45a9d770 by Mateusz Kowalczyk at 2015-07-31T09:47:43+01:00 Update changelog - - - - - 347a20a3 by Phil Ruffwind at 2015-08-02T23:15:26+01:00 Avoid JavaScript error during page load in non-frame mode In non-frame mode, parent.window.synopsis refers to the synopsis div rather than the nonexistent frame. Unfortunately, the script wrongly assumes that if it exists it must be a frame, leading to an error where it tries to access the nonexistent attribute 'replace' of an undefined value (synopsis.location). Closes haskell/haddock#406 - - - - - 54ebd519 by Phil Ruffwind at 2015-08-02T23:27:10+01:00 Link to the definitions to themselves Currently, the definitions already have an anchor tag that allows URLs with fragment identifiers to locate them, but it is rather inconvenient to obtain such a URL (so-called "permalink") as it would require finding the a link to the corresponding item in the Synopsis or elsewhere. This commit adds hyperlinks to the definitions themselves, allowing users to obtain links to them easily. To preserve the original aesthetics of the definitions, we alter the color of the link so as to be identical to what it was, except it now has a hover effect indicating that it is clickable. Additionally, the anchor now uses the 'id' attribute instead of the (obsolete) 'name' attribute. Closes haskell/haddock#407 - - - - - 02cc8bb7 by Phil Ruffwind at 2015-08-02T23:28:02+01:00 Fix typo in Haddock.Backends.Xhtml.Layout: divSynposis -> divSynopsis Closes haskell/haddock#408 - - - - - 2eb0a458 by Phil Ruffwind at 2015-08-02T23:30:07+01:00 Fix record field alignment when name is too long Change <dl> to <ul> and use display:table rather than floats to layout the record fields. This avoids bug haskell/haddock#301 that occurs whenever the field name gets too long. Slight aesthetic change: the entire cell of the field's source code is now shaded gray rather than just the area where text exists. Fixes haskell/haddock#301. Closes haskell/haddock#421 - - - - - 7abb3402 by Łukasz Hanuszczak at 2015-08-02T23:32:14+01:00 Add some utility definitions for generating line anchors. - - - - - e0b1d79b by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Make hyperlinked source renderer generate line anchors. - - - - - 24dd4c9f by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Re-accept test cases after adding line anchors for each of them. - - - - - 0372cfcb by Łukasz Hanuszczak at 2015-08-02T23:32:15+01:00 Override source line flags when source hyperlinker is enabled. - - - - - a81bcd07 by Mateusz Kowalczyk at 2015-08-02T23:58:25+01:00 Update tests to follow HTML changes - - - - - d2d7426f by Łukasz Hanuszczak at 2015-08-06T20:54:59+02:00 Fix quote syntax for promoted types. - - - - - 668cf029 by Łukasz Hanuszczak at 2015-08-06T21:12:00+02:00 Apply promoted type quoting to type-level consing. - - - - - 89f8e7c6 by Łukasz Hanuszczak at 2015-08-06T21:17:10+02:00 Extend advanced types test case with other examples. - - - - - 86494bca by Łukasz Hanuszczak at 2015-08-06T21:22:06+02:00 Rename advanced types test case and accept new output. - - - - - dbb7c7c0 by Adam Sandberg Eriksson at 2015-08-09T23:01:05+02:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 2a7704fa by Ben Gamari at 2015-08-10T13:18:05+02:00 Merge pull request haskell/haddock#433 from adamse/split-hsbang HsBang is split into HsSrcBang and HsImplBang - - - - - 891954bc by Thomas Miedema at 2015-08-15T14:51:18+02:00 Follow changes in GHC build system - - - - - b55d32ab by Mateusz Kowalczyk at 2015-08-21T18:06:09+01:00 Make Travis use 7.10.2 - - - - - 97348b51 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Move SYB utilities to standalone module. - - - - - 748ec081 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement `everywhere` transformation in SYB module. - - - - - 011cc543 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Implement generic transformation constructor. - - - - - b9510db2 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Create simple utility module for type specialization. - - - - - 43229fa6 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Make type of type specialization function more general. - - - - - fd844e90 by Łukasz Hanuszczak at 2015-08-21T18:22:29+01:00 Add basic HTML test case for checking instance specialization. - - - - - 6ea0ad04 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Make HTML class instance printer take optional signature argument. - - - - - 65aa41b6 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Refactor instance head type to record instead of a meaningless tuple. - - - - - 3fc3bede by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add expandable method section for each class instance declaration. - - - - - 99ceb107 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Move dummy post-family instances for `DocName` to `Types` module. - - - - - e98f4708 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create convenience functions for type specialization module. - - - - - b947552f by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Hook type specialization logic with HTML pretty-printer. - - - - - dcaa8030 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create stub functions for sugaring specialized types. - - - - - fa84bc65 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement list syntax sugaring logic for specialized types. - - - - - e8b05b07 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement tuple syntax sugaring logic for specialized types. - - - - - 68a2e5bc by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Get rid of code duplication in type specialization module. - - - - - 4721c336 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create scaffolding of a framework for renaming specialized types. - - - - - 271b488d by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in missing cases in specialized type renaming function. - - - - - bfa5f2a4 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Remove code duplication in specialized type renamer. - - - - - ea6bd0e8 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Change state of the type renaming monad. - - - - - 77c5496e by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Implement simple mechanism for generating new type names. - - - - - 91bfb48b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fill in stub behaviour with actual environment renaming. - - - - - d244517b by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix logic behind binder type renaming. - - - - - f3c5e360 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Add SYB-like utility function for performing stateful queries. - - - - - eb3f9154 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Create function for retrieving free variables from given type. - - - - - a94561d3 by Łukasz Hanuszczak at 2015-08-21T18:22:30+01:00 Fix compilation error caused by incorrect type signature. - - - - - 8bb707cf by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Move `SetName` class definition to types module. - - - - - 5800b13b by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Hook type renamer with instance method HTML pretty-printer. - - - - - 6a480164 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some test cases for type renamer. - - - - - 839842f7 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized signatures refer to original signature declaration. - - - - - 4880f7c9 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make specialized methods be nicely formatted again. - - - - - ab5a6a2e by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Attach source locations to the specialized class methods. - - - - - 43f8a559 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Extend instances test case to also test multi-name type signatures. - - - - - 59bc751c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix tab-based indentation in instances test case. - - - - - c2126815 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Improve placement of instance methods expander button. - - - - - 0a32e287 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add new data type declaration to instance specialization test case. - - - - - 5281af1f by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Make type renamer first try single-letter names as alternatives. - - - - - 7d509475 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix type renamer bug with incorrect names being generated. - - - - - 0f35bf7c by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Add some documentation and refactor type specialization module. - - - - - da1d0803 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix another bug where type renamer was generating incorrect names. - - - - - cd39b5cb by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Refactor type renamer to rebinding and pure renaming phases. - - - - - 850251f4 by Łukasz Hanuszczak at 2015-08-21T18:22:31+01:00 Fix unwitting compilation bug. - - - - - e5e9fc01 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Integrate instance specification type into class instance definition. - - - - - 825b0ea0 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer neccessary instance specification type. - - - - - cdba44eb by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix declaration converter to use more appropriate mode for methods. - - - - - bc45c309 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug with types not being specialized at all. - - - - - 5d8e5d89 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix bug where instance expander was opening wrong section. - - - - - 6001ee41 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix another type renamer bug where not all names were rebound. - - - - - 5f58ce2a by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Fix yet another renamer bug where some names were not unique. - - - - - 8265e521 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split instance subsection layout method to top-level declarations. - - - - - e5e66298 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Rearrange layout of instance methods in generated documentation. - - - - - a50b4eea by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Get rid of no longer used layout method. - - - - - 2ff36ec2 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach section title to the instance methods block. - - - - - 7ac15300 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Add basic tests for associated types in instances test case. - - - - - db0ea2f9 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Attach associated types information to instance header. - - - - - 71cad4d5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details section contain associated types information. - - - - - deee2809 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Improve look of rendered associated families in instance details. - - - - - 839d13a5 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Introduce alternative type for family declarations. - - - - - d397f03f by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Make instance details record use new type for family declarations. - - - - - 2b23fe97 by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Split printer of type family header to separate functions. - - - - - c3498cdc by Łukasz Hanuszczak at 2015-08-21T18:22:32+01:00 Implement HTML renderer for pseudo-family declarations. - - - - - c12bbb04 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Apply type specializer to associated type family declarations. - - - - - 2fd69ff2 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Create helper method for specializing type signatures. - - - - - 475826e7 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Refactor specializer module to be independent from XHTML backend. - - - - - f00b431c by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add some documentation for instance head specializer. - - - - - a9fef2dc by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix bug with missing space in documentation for associated types. - - - - - 50e29056 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with incorrect instance details sections being expanded. - - - - - e6dfdd03 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by adding instance details section. - - - - - 75565b2a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make section identifier of instance details more GHC-independent. - - - - - add0c23e by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Re-accept tests after applying deterministic section identifiers. - - - - - 878f2534 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Make identifier generation also architecture-independent. - - - - - 48be69f8 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Fix issue with instance expander hijacking type hyperlink click. - - - - - 47830c1f by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Get rid of dreadful hashing function for generating identifiers. - - - - - 956cd5af by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Move `InstOrigin` type declaration to more appropriate module. - - - - - bf672ed3 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Accept tests affected by changes related to instance expander. - - - - - 8f2a949a by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add examples with type operators to the instances test case. - - - - - 64600a84 by Łukasz Hanuszczak at 2015-08-21T18:22:33+01:00 Add basic support for sugaring infix type operators. - - - - - 747d71b8 by Łukasz Hanuszczak at 2015-08-21T18:22:34+01:00 Add support for sugaring built-in function syntax. - - - - - d4696ffb by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Remove default methods from Hoogle class output. - - - - - bf0e09d7 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add fixity declarations in Hoogle backend output. - - - - - 90e91a51 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix bug with incorrect fixities being generated in Hoogle backend. - - - - - 48f11d35 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve class type family declarations output in Hoogle backend. - - - - - 661e8e8f by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Add missing default family equations in Hoogle output. - - - - - e2d64103 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Improve formatting of class details output in Hoogle backend. - - - - - 490fc377 by Łukasz Hanuszczak at 2015-08-21T18:31:31+01:00 Fix weird-looking Hoogle output for familyless classes. - - - - - ea115b64 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create script file for new HTML test runner. - - - - - 609913d3 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Set default behaviour if no arguments given. - - - - - dc115f67 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for providing optional arguments for test runner. - - - - - d93ec867 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve output of test runner error messages. - - - - - 0be9fe12 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add support for executing Haddock process in test runner. - - - - - 4e4d00d9 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Add GHC path to test runner configuration. - - - - - d67a2086 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make GHC path a test runner command-line argument. - - - - - c810079a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Extend test runner configuration with Haddock arguments. - - - - - fee18845 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor test runner and create stub functions. - - - - - ff7c161f by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make test runner actually run Haddock executable. - - - - - 391f73e6 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with test runner not producing any output files. - - - - - 81a74e2d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Setup skeleton of framework for running tests. - - - - - f8a79ec4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Fix bug with modules not being found in global search mode. - - - - - 7e700b4d by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make Haddock standard output redirection be more configurable. - - - - - 53b4c17a by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Incorporate old, ugly functions for comparing output files. - - - - - 8277c8aa by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Refactor architecture of test runner output checking functions. - - - - - 587bb414 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement actual diffing mechanism. - - - - - 9ed2b5e4 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Improve code style to match popular guidelines. - - - - - 14bffaf8 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Make it possible to choose alternative diff tool. - - - - - 5cdfb005 by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Create stub methods for processing test output as XML documents. - - - - - 7ef8e12e by Łukasz Hanuszczak at 2015-08-22T23:40:26+02:00 Implement link-stripping logic as simple SYB transformation. - - - - - 8a1fcd4f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Incorporate link stripping to output diffing mechanism. - - - - - 37dba2bc by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement footer-stripping logic. - - - - - 9cd52120 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Add missing dependencies in Cabal configuration file. - - - - - e0f83c6e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix issue with output being printed in incorrect order. - - - - - 0a94fbb0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to run tests without generating diff. - - - - - 76a58c6f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor HTML test suite boilerplate to external package. - - - - - af41e6b0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utilities for storing directory configuration. - - - - - d8f0698f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move IO-dependent config of HTML test suite to test package. - - - - - 17369fa0 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Enable all compiler warnings in Haddock test package configuration. - - - - - 9d03b47a by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Move Haddock runner of HTML test suite to Haddock test package. - - - - - 4b3483c5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 03754194 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience wrappers to simplify in test entry points. - - - - - 27476ab7 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adjust module visibility and items they export. - - - - - c40002ba by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Remove no longer useful test option. - - - - - 55ab2541 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Change extension of test files used for diffing. - - - - - 136bf4e4 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Refactor and simplify XHTML helper module of test package. - - - - - 69f7e3df by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix typo in link stripper of HTML test suite runner. - - - - - 0c3c1c6b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create convenience script for running specific HTML tests. - - - - - 489e1b05 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement utility functions for conditional link stripping. - - - - - 0f985dc3 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt `hypsrc-test` module to work with new testing framework. - - - - - 927406f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Implement output accepting mechanism in test package. - - - - - 8545715e by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Create utility function for recursive obtaining directory contents. - - - - - cb70381f by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make Haddock test package more generic. - - - - - 019599b5 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix path handling in test runner. - - - - - 399b985b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Make it possible to specify ignored files for test output. - - - - - 41b3d93d by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Adapt HTML test runner to use new ignoring functionality. - - - - - e2091c8b by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Fix bug with not all test output files being checked. - - - - - b22134f9 by Łukasz Hanuszczak at 2015-08-22T23:40:27+02:00 Specify ignored files for hyperlinker source test runner. - - - - - 3301dfa1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Copy test runner script for hyperlinked source case. - - - - - d39a6dfa by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner invoking Haddock in incorrect mode. - - - - - f32c8ff3 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix path handling in test module loader. - - - - - 10f94ee9 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make test runner ignore test packages with no modules. - - - - - 5dc4239c by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create test runner entry points for LaTeX test suite. - - - - - 58d1f7cf by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with unnecessary checking old test output. - - - - - c7ce76e1 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Re-implement test acceptance functionality. - - - - - 13bbabe8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix warning about no longer needed definition. - - - - - 958a99b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Adapt Cabal configuration to execute LaTeX suite with new runner. - - - - - 550ff663 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Setup test suite for Hoogle backend. - - - - - 3aa969c4 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Make Hoogle backend create output directory if needed. - - - - - eb085b02 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Add appropriate .gitignore entry and configure Hoogle test suite. - - - - - a50bf915 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Fix bug with test runner failing when run on multiple test packages. - - - - - bf5368b8 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create simple test cases for Hoogle backend. - - - - - 6121ba4b by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Create helper function for conversion between XML and XHTML. - - - - - cb516061 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Refactor existing code to use XHTML printer instead of XML one. - - - - - e2de8c82 by Łukasz Hanuszczak at 2015-08-22T23:40:28+02:00 Improve portability of test runner scripts. - - - - - 9563e774 by Łukasz Hanuszczak at 2015-08-22T23:43:16+02:00 Remove redundant import statement. - - - - - 55353df1 by Łukasz Hanuszczak at 2015-08-24T23:09:20+02:00 Fix bug with accepting to non-existing directory. - - - - - 00a334ca by Łukasz Hanuszczak at 2015-08-24T23:09:47+02:00 Accept output for Hoogle and LaTeX backends. - - - - - 29191d8b by Łukasz Hanuszczak at 2015-08-24T23:14:18+02:00 Get rid of obsolete testing utilities. - - - - - bbb25db3 by Łukasz Hanuszczak at 2015-08-24T23:18:50+02:00 Update sandbox setup guide to work with Haddock test package. - - - - - cfd45248 by Łukasz Hanuszczak at 2015-08-24T23:51:30+02:00 Make Travis aware of Haddock test package. - - - - - 74185b7a by Łukasz Hanuszczak at 2015-08-25T17:41:59+02:00 Fix test suite failure when used with Stack. - - - - - 18769697 by Łukasz Hanuszczak at 2015-08-25T18:02:09+02:00 Add sample Stack setup to the hacking guide. - - - - - 22715eeb by Łukasz Hanuszczak at 2015-08-25T18:04:47+02:00 Fix Markdown formatting of README file. - - - - - b49ec386 by Łukasz Hanuszczak at 2015-08-25T18:13:36+02:00 Setup Haddock executable path in Travis configuration. - - - - - 5d29eb03 by Eric Seidel at 2015-08-30T09:55:58-07:00 account for changes to ipClass - - - - - f111740a by Ben Gamari at 2015-09-02T13:20:37+02:00 Merge pull request haskell/haddock#443 from bgamari/ghc-head account for changes to ipClass - - - - - a2654bf6 by Jan Stolarek at 2015-09-03T01:32:57+02:00 Follow changes from haskell/haddock#6018 - - - - - 2678bafe by Richard Eisenberg at 2015-09-21T12:00:47-04:00 React to refactoring CoAxiom branch lists. - - - - - ebc56e24 by Edward Z. Yang at 2015-09-21T11:53:46-07:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4a8c4198 by Tamar Christina at 2015-09-27T13:59:08+02:00 Create Process: removed PhaseFailed - - - - - 7e99b790 by Oleg Grenrus at 2015-09-27T20:52:10+03:00 Generate docs for orphan instances - - - - - 32e932e2 by Oleg Grenrus at 2015-09-28T07:21:11+03:00 Have source links for orphan instances - - - - - c2eb9f4f by Oleg Grenrus at 2015-09-28T07:24:58+03:00 Print orphan instances header only if required - - - - - ff96f978 by Oleg Grenrus at 2015-09-28T07:40:54+03:00 Add orphan instances link to contents box - - - - - d72490a6 by Oleg Grenrus at 2015-09-28T16:37:44+03:00 Fix orphan instance collapsing - - - - - 25d3dfe5 by Ben Gamari at 2015-10-03T12:38:09+02:00 Merge pull request haskell/haddock#448 from Mistuke/fix-silent-death-of-runInteractive Remove PhaseFailed - - - - - 1e45e43b by Edward Z. Yang at 2015-10-11T13:10:10-07:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b1370ac1 by Adam Gundry at 2015-10-16T16:26:42+01:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 60bef421 by Simon Peyton Jones at 2015-10-26T12:52:36+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 4c1898ca by Simon Peyton Jones at 2015-10-27T14:24:56+00:00 Track change to PatSyn.patSynSig - - - - - 25108e85 by Simon Peyton Jones at 2015-10-27T17:34:18+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - 693643ac by Ben Gamari at 2015-10-28T14:33:06+01:00 Account for Typeable changes The treatment of type families changed. - - - - - cd7c2221 by Simon Peyton Jones at 2015-10-30T13:03:51+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - 712032cb by Herbert Valerio Riedel at 2015-10-31T11:01:45+01:00 Relax upper bound on `base` to allow base-4.9 - - - - - 0bfa0475 by Simon Peyton Jones at 2015-10-31T19:08:13+00:00 More adaption to wildcard-refactor - - - - - 0a3c0cb7 by Simon Peyton Jones at 2015-10-31T22:14:43+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor Conflicts: haddock-api/src/Haddock/Convert.hs - - - - - c4fd4ec9 by Alan Zimmerman at 2015-11-01T11:16:34+01:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 42cdd882 by Matthew Pickering at 2015-11-06T20:02:16+00:00 Change for IEThingWith - - - - - f368b7be by Ben Gamari at 2015-11-11T11:35:51+01:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - e32965b8 by Simon Peyton Jones at 2015-11-13T12:18:17+00:00 Merge with origin/head - - - - - ebcf795a by Edward Z. Yang at 2015-11-13T21:56:27-08:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4e23989f by Simon Peyton Jones at 2015-11-18T11:32:54+00:00 Wibbles to Haddock - - - - - 2289cd4a by Simon Peyton Jones at 2015-11-20T23:12:49+00:00 Merge remote-tracking branch 'origin/ghc-head' into wip/spj-wildcard-refactor - - - - - 695975a6 by Alan Zimmerman at 2015-11-21T21:16:12+02:00 Update to match GHC wip/T11019 - - - - - bbba21e7 by Simon Peyton Jones at 2015-11-23T13:54:31+00:00 merge with origin/ghc-head - - - - - 3d664258 by Simon Peyton Jones at 2015-11-23T17:17:18+00:00 Wibble - - - - - e64cf586 by Herbert Valerio Riedel at 2015-12-05T00:29:55+01:00 Canonicalise Monad instances - - - - - a2de15a7 by Alan Zimmerman at 2015-12-05T17:33:52+02:00 Matching changes for haskell/haddock#11028 - - - - - cc29a3e4 by Alan Zimmerman at 2015-12-05T19:45:33+02:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 95dd15d1 by Richard Eisenberg at 2015-12-11T17:33:39-06:00 Update for type=kinds - - - - - cb5fd9ed by Herbert Valerio Riedel at 2015-12-14T15:07:30+00:00 Bump versions for ghc-7.11 - - - - - 4f286d96 by Simon Peyton Jones at 2015-12-14T15:10:56+00:00 Eliminate instanceHead' in favour of GHC's instanceSig This is made possible by the elimination of "silent superclass parameters" in GHC - - - - - 13ea2733 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Remove redundant constraints from haddock, discovered by -fwarn-redundant-constraints - - - - - 098df8b8 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track changes in HsSyn for quasi-quotes - - - - - 716a64de by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track change in API of TyCon - - - - - 77a66bca by Adam Gundry at 2015-12-14T15:10:58+00:00 Track API changes to support empty closed type familes - - - - - f2808305 by Simon Peyton Jones at 2015-12-14T15:10:58+00:00 Track the new location of setRdrNameSpace - - - - - ba8b08a4 by Alan Zimmerman at 2015-12-14T15:10:59+00:00 ApiAnnotations : strings in warnings do not return SourceText The strings used in a WARNING pragma are captured via strings :: { Located ([AddAnn],[Located FastString]) } : STRING { sL1 $1 ([],[L (gl $1) (getSTRING $1)]) } .. The STRING token has a method getSTRINGs that returns the original source text for a string. A warning of the form {-# WARNING Logic , mkSolver , mkSimpleSolver , mkSolverForLogic , solverSetParams , solverPush , solverPop , solverReset , solverGetNumScopes , solverAssertCnstr , solverAssertAndTrack , solverCheck , solverCheckAndGetModel , solverGetReasonUnknown "New Z3 API support is still incomplete and fragile: \ \you may experience segmentation faults!" #-} returns the concatenated warning string rather than the original source. - - - - - a4ded87e by Thomas Winant at 2015-12-14T15:14:05+00:00 Update after wild card renaming refactoring in D613 Summary: * Move `Post*` type instances to `Haddock.Types` as other modules than `Haddock.Interface.Rename` will rely on these type instances. * Update after wild card renaming refactoring in D613. Reviewers: simonpj, austin Reviewed By: austin Differential Revision: https://phabricator.haskell.org/D954 GHC Trac Issues: haskell/haddock#10098 - - - - - 25c78107 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: print correct strictness marks - - - - - 6cbc41c4 by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 StrictData: changes in HsBang type - - - - - ad46821a by Alan Zimmerman at 2015-12-14T15:14:06+00:00 Replace (SourceText,FastString) with WithSourceText data type Phab:D907 introduced SourceText for a number of data types, by replacing FastString with (SourceText,FastString). Since this has an Outputable instance, no warnings are generated when ppr is called on it, but unexpected output is generated. See Phab:D1096 for an example of this. Replace the (SourceText,FastString) tuples with a new data type data WithSourceText = WithSourceText SourceText FastString Trac ticket: haskell/haddock#10692 - - - - - abc0ae5b by Adam Sandberg Eriksson at 2015-12-14T15:14:06+00:00 HsBang is split into HsSrcBang and HsImplBang With recent changes in GHC handling of strictness annotations in Haddock is simplified. - - - - - 3308d06c by Thomas Miedema at 2015-12-14T15:14:07+00:00 Follow changes in GHC build system - - - - - 6c763deb by Eric Seidel at 2015-12-14T15:14:07+00:00 account for changes to ipClass - - - - - ae5b4eac by Jan Stolarek at 2015-12-14T15:17:00+00:00 Follow changes from haskell/haddock#6018 - - - - - ffbc40e0 by Richard Eisenberg at 2015-12-14T15:17:02+00:00 React to refactoring CoAxiom branch lists. - - - - - d1f531e9 by Edward Z. Yang at 2015-12-14T15:17:02+00:00 Track msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 79f73754 by Tamar Christina at 2015-12-14T15:17:02+00:00 Create Process: removed PhaseFailed - - - - - 3d37bebb by Edward Z. Yang at 2015-12-14T15:20:46+00:00 s/PackageKey/UnitId/g and s/packageKey/unitId/g Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 5f8a9e44 by Adam Gundry at 2015-12-14T15:20:48+00:00 Roughly fix up haddock for DuplicateRecordFields changes This compiles, but will probably need more work to produce good documentation when the DuplicateRecordFields extension is used. - - - - - 79dda70f by Simon Peyton Jones at 2015-12-14T15:26:02+00:00 Track wip/spj-wildcard-refactor on main repo - - - - - 959930fb by Simon Peyton Jones at 2015-12-14T15:37:50+00:00 Follow changes to HsTYpe Not yet complete (but on a wip/ branch) - - - - - e18a8df5 by Simon Peyton Jones at 2015-12-14T15:37:52+00:00 Work on updating Haddock to wip/spj-wildard-recactor Still incomplete - - - - - aa35ab52 by Simon Peyton Jones at 2015-12-14T15:40:18+00:00 More adaption to wildcard-refactor - - - - - 8ceef94b by Simon Peyton Jones at 2015-12-14T15:46:04+00:00 Track change to PatSyn.patSynSig - - - - - cd81e83d by Ben Gamari at 2015-12-14T15:46:06+00:00 Account for Typeable changes The treatment of type families changed. - - - - - 63c9117c by Herbert Valerio Riedel at 2015-12-14T15:46:34+00:00 Relax upper bound on `base` to allow base-4.9 - - - - - a484c613 by Alan Zimmerman at 2015-12-14T15:47:46+00:00 Matching change GHC haskell/haddock#11017 BooleanFormula located - - - - - 2c26fa51 by Matthew Pickering at 2015-12-14T15:47:47+00:00 Change for IEThingWith - - - - - 593baa0f by Ben Gamari at 2015-12-14T15:49:21+00:00 Eliminate support for deprecated GADT syntax Follows from GHC D1460. - - - - - b6b5ca78 by Edward Z. Yang at 2015-12-14T15:49:54+00:00 Undo msHsFilePath change. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b5b0e072 by Alan Zimmerman at 2015-12-14T15:54:20+00:00 Update to match GHC wip/T11019 - - - - - 14ddeb68 by Simon Peyton Jones at 2015-12-14T15:54:22+00:00 Wibble - - - - - 10a90ad8 by Herbert Valerio Riedel at 2015-12-14T15:54:22+00:00 Canonicalise Monad instances - - - - - ed68ac50 by Alan Zimmerman at 2015-12-14T15:55:48+00:00 Matching changes for haskell/haddock#11028 - - - - - 3f7e5a2d by Alan Zimmerman at 2015-12-14T15:55:49+00:00 Placeholder for record style GADT declaration A GADT Declaration is now presented as CmmCondBranch :: {..} -> CmmNode O C cml_pred :: CmmExpr cml_true, cml_false :: !Label cml_likely :: Maybe Bool for CmmCondBranch :: { -- conditional branch cml_pred :: CmmExpr, cml_true, cml_false :: ULabel, cml_likely :: Maybe Bool -- likely result of the conditional, -- if known } -> CmmNode O C - - - - - 6543a73f by Richard Eisenberg at 2015-12-14T15:59:55+00:00 Update for type=kinds - - - - - 193a5c48 by Matthew Pickering at 2015-12-14T18:17:00+00:00 Changes to compile with 8.0 - - - - - add669ec by Matthew Pickering at 2015-12-14T18:47:12+00:00 Warnings - - - - - 223f3fb4 by Ben Gamari at 2015-12-15T23:45:05+01:00 Update for D1200 - - - - - d058388f by Ben Gamari at 2015-12-16T05:40:17-05:00 Types: Add Outputable[Bndr] DocName instances - - - - - 62ecd7fb by Ben Gamari at 2015-12-16T09:23:09-05:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ddbc187a by Ben Gamari at 2015-12-16T17:54:55+01:00 Update for D1200 - - - - - cec83b52 by Ben Gamari at 2015-12-16T17:54:55+01:00 Types: Add Outputable[Bndr] DocName instances - - - - - d12ecc98 by Ben Gamari at 2015-12-16T17:54:55+01:00 Fix fallout from wildcards refactoring The wildcard refactoring was introduced a new type of signature, `ClassOpSig`, which is carried by typeclasses. The original patch adapting Haddock for this change missed a few places where this constructor needed to be handled, resulting in no class methods in documentation produced by Haddock. Additionally, this moves and renames the `isVanillaLSig` helper from GHC's HsBinds module into GhcUtils, since it is only used by Haddock. - - - - - ada1616f by Ben Gamari at 2015-12-16T17:54:58+01:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a4f0383d by Ben Gamari at 2015-12-16T23:32:38+01:00 Fix Hyperlinker GHC.con_names is now GHC.getConNames - - - - - a10e6849 by Ben Gamari at 2015-12-20T00:54:11+01:00 Merge remote-tracking branch 'mrhania/testing-framework-improvements' into ghc-head - - - - - f078b4fd by Ben Gamari at 2015-12-20T00:59:51+01:00 test: Compatibility with Cabal 1.23 - - - - - 88a511a9 by Ben Gamari at 2015-12-20T01:14:35+01:00 Merge remote-tracking branch 'phadej/orphans' into ghc-head - - - - - 4e250f36 by Ben Gamari at 2015-12-20T01:14:52+01:00 Add html-test for orphan instances output - - - - - 87fffbad by Alan Zimmerman at 2015-12-20T09:50:42+02:00 Update for GHC trac#11258 Adding locations to RdrName in FieldOcc and AmbiguousFieldOcc - - - - - 6b7e51c9 by idontgetoutmuch at 2015-12-20T21:01:47+00:00 Merge pull request haskell/haddock#1 from haskell/ghc-head Ghc head - - - - - 229c1fb5 by Dominic Steinitz at 2015-12-21T07:19:16+00:00 Handle inline math with mathjax. - - - - - 57902d66 by Dominic Steinitz at 2015-12-21T08:07:11+00:00 Fix the documentation for haddock itself. Change notation and add support for inline math. Allow newlines in display math. Add a command line option for the mathjax url (you might want to use a locally installed version). Rebase tests because of extra url and version change. Respond to (some of the) comments. Fix warnings in InterfaceFile.hs - - - - - 0e69f236 by Herbert Valerio Riedel at 2015-12-21T18:30:43+01:00 Fix-up left-over assumptions of GHC 7.12 into GHC 8.0 - - - - - c67f8444 by Simon Peyton Jones at 2015-12-22T16:26:56+00:00 Follow removal of NamedWildCard from HsType - - - - - da40327a by Ben Gamari at 2015-12-23T14:15:28+01:00 html-test/Operators: Clear up ambiguous types For reasons that aren't entirely clear a class with ambiguous types was accepted by GHC <8.0. I've added a functional dependency to clear up this ambiguity. - - - - - 541b7fa4 by Ben Gamari at 2015-12-23T14:18:51+01:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 0febc947 by Ben Gamari at 2015-12-24T00:30:20+01:00 hoogle-test/AssocTypes: Allow AmbiguousTypes GHC 8.0 complains otherwise - - - - - 25810841 by Ben Gamari at 2015-12-24T00:33:18+01:00 OrphanInstances: Accept test output - - - - - 841987f3 by Ben Gamari at 2015-12-25T11:03:11+01:00 Merge remote-tracking branch 'idontgetoutmuch/ghc-head' into ghc-head - - - - - 358391f0 by Ben Gamari at 2015-12-26T10:44:50+01:00 Add missing import - - - - - a8896885 by Ben Gamari at 2015-12-26T10:45:27+01:00 travis: Use Travis containers - - - - - 85e82134 by Herbert Valerio Riedel at 2015-12-30T17:25:39+01:00 tweak version bounds for GHC-8.1 - - - - - 672a5f75 by randen at 2016-01-01T23:45:25-08:00 The Haddock part for fully gcc-like response files " driver/Main.hs * Moved the response file handling into ResponseFile.hs, updating import section as appropriate. * driver/ResponseFile.hs * New file. In anticipation that maybe some day this could be provided by another library, and to make it possible to unit test, this functionality is pulled out of the Main.hs module, and expanded to support the style/format of response files which gcc uses. * The specification for the format of response files which gcc generates and consumes, seems to be best derived from the gcc code itself (libiberty/argv.c), so that is what has been done here. * This is intended to fix haskell/haddock#379 * driver-test/Main.hs * New file for testing code in the driver source tree * driver-test/ResponseFileSpec.hs * Tests, adapted/adopted from the same gcc code where the escaping/unescaping is from, in the hspec style of unit tests * haddock.cabal * Add the driver-test test-suite. Introduces a new library dependency (upon hspec) for the haddock driver target in the haddock.cabal file, but practically, this should not be a problem as the haddock-api tests already depend on hspec. - - - - - 498781df by Ben Gamari at 2016-01-06T13:41:04+01:00 Version bumps and changelog - - - - - 8451e46a by Ben Gamari at 2016-01-06T13:47:17+01:00 Merge remote-tracking branch 'randen/bug468' - - - - - fb2d9181 by Ben Gamari at 2016-01-06T08:14:42-05:00 Add ResponseFile to OtherModules - - - - - 2cb2d2e3 by Ben Gamari at 2016-01-06T14:35:00+01:00 Merge branch 'master' into ghc-head - - - - - 913477d4 by Eric Seidel at 2016-01-11T14:57:57-08:00 deal with un-wiring of IP class - - - - - c557a4b3 by Alan Zimmerman at 2016-01-15T11:14:35+02:00 Update to match wip/T11430 in GHC - - - - - 3e135093 by Alan Zimmerman at 2016-01-16T18:21:59+01:00 Update to match wip/T11430 in GHC - - - - - c48ef2f9 by Ben Gamari at 2016-01-18T09:50:06+01:00 Merge remote-tracking branch 'gridaphobe/ghc-head' into ghc-head - - - - - 9138a1b0 by Eric Seidel at 2016-01-18T12:50:15+01:00 deal with un-wiring of IP class (cherry picked from commit 17388b0f0029d969d79353be7737eb01c7b8dc5f) - - - - - b48c172e by Joachim Breitner at 2016-01-19T00:11:38+01:00 Make sure --mathjax affects all written HTML files This fixes haskell/haddock#475. - - - - - af61fe63 by Ryan Scott at 2016-02-07T23:25:57+01:00 Render */# instead of TYPE 'Lifted/TYPE 'Unlifted (fixes haskell/haddock#473) - - - - - b6458693 by Ben Gamari at 2016-02-07T23:29:27+01:00 Merge pull request haskell/haddock#477 from haskell/issue-475 Make sure --mathjax affects all written HTML files - - - - - adcc0071 by Ben Gamari at 2016-02-07T23:34:52+01:00 Merge branch 'master' into ghc-head - - - - - d0404e61 by Ben Gamari at 2016-02-08T12:46:49+01:00 doc: Switch to Sphinx - - - - - acb153b3 by Ben Gamari at 2016-02-08T12:46:56+01:00 Document --use-unicode flag - - - - - c20bdf1d by Ben Gamari at 2016-02-08T13:41:24+01:00 Fix GHC and haddock-library dependency bounds - - - - - 8d946801 by Ben Gamari at 2016-02-08T14:54:56+01:00 testsuite: Rework handling of output sanitization Previously un-cleaned artifacts were kept as reference output, making it difficult to tell what has changed and causing spurious changes in the version control history. Here we rework this, cleaning the output during acceptance. To accomplish this it was necessary to move to strict I/O to ensure the reference handle was closed before accept attempts to open the reference file. - - - - - c465705d by Ben Gamari at 2016-02-08T15:36:05+01:00 test: Compare on dump For reasons I don't understand the Xml representations differ despite their textual representations being identical. - - - - - 1ec0227a by Ben Gamari at 2016-02-08T15:36:05+01:00 html-test: Accept test output - - - - - eefbd63a by Ben Gamari at 2016-02-08T15:36:08+01:00 hypsrc-test: Accept test output And fix impredicative Polymorphism testcase. - - - - - d1df4372 by Ben Gamari at 2016-02-08T15:40:44+01:00 Merge branch 'fix-up-testsuite' - - - - - 206a3859 by Phil Ruffwind at 2016-02-08T17:51:21+01:00 Move the permalinks to "#" on the right side Since pull request haskell/haddock#407, the identifiers have been permalinked to themselves, but this makes it difficult to copy the identifier by double-clicking. To work around this usability problem, the permalinks are now placed on the far right adjacent to "Source", indicated by "#". Also, 'namedAnchor' now uses 'id' instead of 'name' (which is obsolete). - - - - - 6c89fa03 by Phil Ruffwind at 2016-02-08T17:54:44+01:00 Update tests for previous commit - - - - - effaa832 by Ben Gamari at 2016-02-08T17:56:17+01:00 Merge branch 'anchors-redux' - - - - - 9a2bec90 by Ben Gamari at 2016-02-08T17:58:40+01:00 Use -fprint-unicode-syntax when --use-unicode is enabled This allows GHC to render `*` as its Unicode representation, among other things. - - - - - 28ecac5b by Ben Gamari at 2016-02-11T18:53:03+01:00 Merge pull request haskell/haddock#480 from bgamari/sphinx Move documentation to ReStructuredText - - - - - 222e5920 by Ryan Scott at 2016-02-11T15:42:42-05:00 Collapse type/data family instances by default - - - - - a80ac03b by Ryan Scott at 2016-02-11T20:17:09-05:00 Ensure expanded family instances render correctly - - - - - 7f985231 by Ben Gamari at 2016-02-12T10:04:22+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - d4eda086 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Various cleanups - - - - - 79bee48d by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show kind signatures for type family variables Addresses GHC haskell/haddock#11588. - - - - - b2981d98 by Ben Gamari at 2016-02-18T00:05:56+01:00 Xhtml.Decl: Show 'where ...' after closed type family Seems like we should ideally show the actual equations as well but that seems like it would be a fair amount of work - - - - - cfc0e621 by Ben Gamari at 2016-02-18T22:48:12+01:00 Merge pull request haskell/haddock#483 from bgamari/T11588 Fix GHC haskell/haddock#11588 This fixes GHC haskell/haddock#11588: * Show where ... after closed type families * Show kind signatures on type family type variables - - - - - 256e8a0d by Ben Gamari at 2016-02-18T23:15:39+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 32402036 by Richard Eisenberg at 2016-02-24T13:21:44-05:00 Follow-on changes to support RuntimeRep - - - - - 2b1c572d by Matthew Pickering at 2016-03-04T21:04:02+00:00 Remove unused functions - - - - - eb906f50 by Richard Eisenberg at 2016-03-13T21:17:20+01:00 Follow-on changes to support RuntimeRep (cherry picked from commit ab954263a793d8ced734459d6194a5d89214b66c) - - - - - 8c34ef34 by Richard Eisenberg at 2016-03-14T23:47:23-04:00 Changes due to fix for GHC#11648. - - - - - 0e022014 by Richard Eisenberg at 2016-03-15T14:06:45+01:00 Changes due to fix for GHC#11648. (cherry picked from commit bb994de1ab0c76d1aaf1e39c54158db2526d31f1) - - - - - ed3f78ab by Rik Steenkamp at 2016-04-02T22:20:36+01:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 - - - - - d3210042 by Rik Steenkamp at 2016-04-04T15:43:32+02:00 Fix printing of pattern synonym types Removes the call to `patSynType :: PatSyn -> Type` in `Convert.hs` as this function will be removed from GHC. Instead, we use the function `patSynSig` and build the `HsDecl` manually. This also fixes the printing of the two contexts and the quantified type variables in a pattern synonym type. Reviewers: goldfire, bgamari, mpickering Differential Revision: https://phabricator.haskell.org/D2048 (cherry picked from commit 3ddcbd6b8e6884bd95028381176eb33bee6896fb) - - - - - 236eec90 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 692ee7e0 by Ben Gamari at 2016-04-10T23:40:15+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. - - - - - 79619f57 by Ben Gamari at 2016-04-10T23:46:22+02:00 doc: Only install if BUILD_SPHINX_HTML==YES Fixes GHC haskell/haddock#11818. (cherry picked from commit c6d6a18d85e5e2d9bb5904e6919e8a8d7e31c4c5) - - - - - 3358ccb4 by Ben Gamari at 2016-04-10T23:47:27+02:00 doc: Fix option references (cherry picked from commit f915fb3c74328fb994235bbbd42092a691539197) - - - - - 264949b1 by Ben Gamari at 2016-04-16T17:50:23+02:00 Merge pull request haskell/haddock#482 from RyanGlScott/ghc-head Collapse type/data family instances by default - - - - - 478c483a by Ben Gamari at 2016-04-16T17:51:09+02:00 Merge pull request haskell/haddock#489 from mpickering/unused-functions Remove some unused functions - - - - - c94e55f0 by Ryan Scott at 2016-04-16T17:57:54+02:00 Collapse type/data family instances by default (cherry picked from commit 2da130a8db8f995c119b544fad807533236cf088) - - - - - 31e633d3 by Ryan Scott at 2016-04-16T17:58:06+02:00 Ensure expanded family instances render correctly (cherry picked from commit 1338b5d7c32939de6bbc31af0049477e4f847103) - - - - - 03e4d197 by Matthew Pickering at 2016-04-16T17:58:21+02:00 Remove unused functions (cherry picked from commit b89d1c2456bdb2d4208d94ded56155f7088a37d0) - - - - - ed4116f6 by Ben Gamari at 2016-04-20T10:46:57+02:00 ghc: Install files for needed --hyperlinked-source - - - - - 0be999c4 by Ben Gamari at 2016-04-20T11:37:54+02:00 ghc: Install files for needed --hyperlinked-source (cherry picked from commit 5c82c9fc2d21ddaae4a2470f1c375426968f19c6) - - - - - 4d17544c by Simon Peyton Jones at 2016-04-20T12:42:28+01:00 Track change to HsGroup This relates to a big GHC patch for Trac haskell/haddock#11348 - - - - - 1700a50d by Ben Gamari at 2016-05-01T13:19:27+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. - - - - - 0b7c8125 by Ben Gamari at 2016-05-01T13:21:43+02:00 doc: At long last fix ghc.mk The variable reference was incorrectly escaped, meaning that Sphinx documentation was never installed. (cherry picked from commit 609018dd09c4ffe27f9248b2d8b50f6196cd42b9) - - - - - af115ce0 by Ryan Scott at 2016-05-04T22:15:50-04:00 Render Haddocks for derived instances Currently, one can document top-level instance declarations, but derived instances (both those in `deriving` clauses and standalone `deriving` instances) do not enjoy the same privilege. This makes the necessary changes to the Haddock API to enable rendering Haddock comments for derived instances. This is part of a fix for Trac haskell/haddock#11768. - - - - - 76fa1edc by Ben Gamari at 2016-05-10T18:13:25+02:00 haddock-test: A bit of refactoring for debuggability - - - - - 7d4c4b20 by Ben Gamari at 2016-05-10T18:13:25+02:00 Create: Mark a comment as TODO - - - - - 2a6d0c90 by Ben Gamari at 2016-05-10T18:13:25+02:00 html-test: Update reference output - - - - - bd60913d by Ben Gamari at 2016-05-10T18:13:25+02:00 hypsrc-test: Fix reference file path in cabal file It appears the haddock insists on prefixing --hyperlinked-sourcer output with directory which the source appeared in. - - - - - c1548057 by Ben Gamari at 2016-05-10T18:22:12+02:00 doc: Update extra-source-files in Cabal file - - - - - 41d5bae3 by Ben Gamari at 2016-05-10T18:29:21+02:00 Bump versions - - - - - ca75b779 by Ben Gamari at 2016-05-11T16:03:44+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 4e3cfd62 by Ben Gamari at 2016-05-11T16:06:45+02:00 Merge remote-tracking branch 'RyanGlScott/ghc-head' into ghc-head - - - - - a2379970 by Ben Gamari at 2016-05-11T23:15:11+02:00 doc: Add clean targets - - - - - f275212e by Ben Gamari at 2016-05-11T23:15:14+02:00 doc: Add html as an all-target for ghc Otherwise the html documentation won't be installed for binary-dist. - - - - - 388fc0af by Ben Gamari at 2016-05-12T09:49:12+02:00 Update CHANGES - - - - - bad81ad5 by Ben Gamari at 2016-05-12T09:49:38+02:00 Version bump - - - - - c01688a7 by Ben Gamari at 2016-05-12T10:04:58+02:00 Revert "Version bump" This bump was a bit premature. This reverts commit 7b238d9c5be9b07aa2d10df323b5c7b8d1634dc8. - - - - - 7ed05724 by Ben Gamari at 2016-05-12T10:05:33+02:00 doc: Fix GHC clean rule Apparently GHC's build system doesn't permit wildcards in clean paths. - - - - - 5d9611f4 by Ben Gamari at 2016-05-12T17:43:50+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 653566b2 by Ben Gamari at 2016-05-14T09:57:31+02:00 Version bump to 2.17.2 - - - - - b355c439 by Ben Gamari at 2016-05-14T09:57:51+02:00 doc: Use `$(MAKE)` instead of `make` This is necessary to ensure we use gmake. - - - - - 8a18537d by Ben Gamari at 2016-05-14T10:15:45+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - b3290ef1 by Sebastian Meric de Bellefon at 2016-05-14T11:29:47-04:00 Fix haskell/haddock#303. Hide footer when printing The "Produced by Haddock" footer was overlapping the page's body when printing. This patch hides the footer with a css media rule. - - - - - b4a76f89 by Sebastian Meric de Bellefon at 2016-05-15T02:12:46-04:00 Fix haskell/haddock#280. Parsing of module header The initial newlines were counted as indentation spaces, thus disturbing the parsing of next lines - - - - - ba797c9e by Ben Gamari at 2016-05-16T14:53:46+02:00 doc: Vendorize alabaster Sphinx theme Alabaster is now the default sphinx theme and is a significant improvement over the previous default that it's worthproviding it when unavailable (e.g. Sphinx <1.3). - - - - - c9283e44 by Ben Gamari at 2016-05-16T14:55:17+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 1c9ea198 by Sebastian Méric de Bellefon at 2016-05-16T12:30:40-04:00 Merge pull request haskell/haddock#502 from Helkafen/master Fix haskell/haddock#303. Hide footer when printing - - - - - 33631016 by Ben Gamari at 2016-05-16T19:56:11+02:00 Revert "doc: Vendorize alabaster Sphinx theme" This ended up causes far too many issues to be worthwhile. We'll just have to live with inconsistent haddock documentation. This reverts commit cec21957001143794e71bcd9420283df18e7de40. - - - - - 93317d26 by Ben Gamari at 2016-05-16T19:56:11+02:00 cabal: Fix README path - - - - - c8695b22 by Ben Gamari at 2016-05-16T19:58:51+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 0b50eaaa by Ben Gamari at 2016-05-16T21:02:08+02:00 doc: Use whichever theme sphinx deems appropriate - - - - - 857c1c9c by Ben Gamari at 2016-05-16T21:07:08+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 15fc5637 by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Remove redundant imports - - - - - 132ddc6a by Ben Gamari at 2016-05-22T12:43:59+02:00 Create: Better debug output For tracking down haskell/haddock#505 - - - - - 2252a149 by Ben Gamari at 2016-05-22T12:43:59+02:00 Don't consider default class ops when looking for decls When we are looking for an operation within a class we don't care about `default`-type declarations. This was the cause of haskell/haddock#505. - - - - - 4886b2ec by Oleg Grenrus at 2016-05-24T16:19:48+03:00 UnfelpfulSpan line number omitted Kind of resolves https://github.com/haskell/haddock/issues/508 - - - - - a4befd36 by Oleg Grenrus at 2016-05-24T16:53:35+03:00 Change Hyperlinked lexer to know about DataKinds ticks - - - - - f45cb52e by David Feuer at 2016-05-24T18:48:53-04:00 Make parser state a newtype Previously, it was `data` wrapping a `Maybe`, which seems a bit silly. Obviously, this can be changed back if anyone wants to add more fields some day. - - - - - 05013dd7 by Sebastian Meric de Bellefon at 2016-05-24T22:03:55-04:00 remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) Frames are a bit broken, ignored by Hackage, and considered obsolete in general. This patch disables frames generation. The mini_*.html files are still used in the synopsis. - - - - - b8163a88 by Ben Gamari at 2016-05-25T14:44:15+02:00 Merge pull request haskell/haddock#507 from bgamari/T505 Fix haskell/haddock#505 - - - - - ea1b30c6 by Sebastian Meric de Bellefon at 2016-05-25T14:17:00-04:00 Update CHANGES - - - - - eddfc258 by Sebastian Méric de Bellefon at 2016-05-25T15:17:40-04:00 Merge pull request haskell/haddock#514 from Helkafen/frames remove framed view of the HTML documentation (see haskell/haddock#114 and haskell/haddock#274) - - - - - 0e506818 by Alex Biehl at 2016-05-26T12:43:09+02:00 Remove misplaced haddock comment - - - - - a07d28c0 by Ben Gamari at 2016-05-27T11:34:59+02:00 Merge pull request haskell/haddock#515 from alexbiehl/master Remove misplaced haddock comment - - - - - 9001d267 by Ben Gamari at 2016-05-27T11:35:46+02:00 Merge pull request haskell/haddock#513 from treeowl/newtype-since Make parser state a newtype - - - - - 74e1a018 by Sebastian Méric de Bellefon at 2016-05-28T17:28:15-04:00 Merge pull request haskell/haddock#504 from Helkafen/issue-280 Fix haskell/haddock#280. Parsing of module header - - - - - 37557f4f by Alan Zimmerman at 2016-05-29T23:36:50+02:00 Matching changes for haskell/haddock#12105 - - - - - 7d09e5d6 by Sebastian Meric de Bellefon at 2016-06-03T18:07:48-04:00 Version bumps (2.17.3, 1.4.2) - - - - - 85b4bc15 by Sebastian Méric de Bellefon at 2016-06-06T18:35:13-04:00 Merge pull request haskell/haddock#521 from Helkafen/master Version bumps (2.17.3, 1.4.2) - - - - - e95f0dee by Sebastian Meric de Bellefon at 2016-06-06T19:11:35-04:00 publish haddock-test library - - - - - 4de40586 by Sebastian Méric de Bellefon at 2016-06-06T20:26:30-04:00 Merge pull request haskell/haddock#512 from phadej/oleg-fixes Fixes for haskell/haddock#508 and haskell/haddock#510 - - - - - ddfd0789 by Dominic Steinitz at 2016-06-09T09:27:28+01:00 Documentation for LaTeX markup. - - - - - 697a503a by Dominic Steinitz at 2016-06-09T09:33:59+01:00 Fix spelling mistake. - - - - - 246f6fff by Dominic Steinitz at 2016-06-09T09:37:15+01:00 Camel case MathJax. - - - - - 4684bd23 by Dominic Steinitz at 2016-06-09T09:44:53+01:00 Fix math typo and add link. - - - - - f20c037c by Simon Peyton Jones at 2016-06-13T18:26:03+01:00 Follow changes to LHsSigWcType - - - - - 0c58996d by Simon Peyton Jones at 2016-06-15T12:56:01+01:00 Follow GHC re-adding FunTy - - - - - 401b5ca7 by Sebastian Méric de Bellefon at 2016-06-15T12:16:47-04:00 Merge pull request haskell/haddock#525 from idontgetoutmuch/master Documentation for LaTeX markup. - - - - - 92d263b7 by Sebastian Méric de Bellefon at 2016-06-15T12:17:29-04:00 Merge pull request haskell/haddock#522 from Helkafen/master publish haddock-test library - - - - - 0953a2ca by Sebastian Meric de Bellefon at 2016-06-16T00:46:46-04:00 Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 65453e14 by Ben Gamari at 2016-06-16T11:16:32+02:00 ocean: Ensure that synopsis fully covers other content Previously MathJax content was being rendered on top of the synopsis due to ambiguous z-ordering. Here we explicitly give the synopsis block a higher z-index to ensure it is rendered on top. Fixes haskell/haddock#531. - - - - - 68e411a1 by Sebastian Méric de Bellefon at 2016-06-16T23:34:39-04:00 Merge pull request haskell/haddock#534 from bgamari/T531 ocean: Ensure that synopsis fully covers other content - - - - - fad6491b by Sebastian Méric de Bellefon at 2016-06-18T23:57:20-04:00 Merge pull request haskell/haddock#533 from Helkafen/master Copyright holders shown on several lines. Fix haskell/haddock#279 - - - - - 6108e21b by Sebastian Meric de Bellefon at 2016-06-22T23:08:28-04:00 do not create empty src directory Fix haskell/haddock#536. - - - - - 1ef23823 by Sebastian Méric de Bellefon at 2016-06-24T00:04:48-04:00 Merge pull request haskell/haddock#537 from Helkafen/master do not create empty src directory - - - - - 966baa96 by Omari Norman at 2016-06-29T21:59:34-04:00 Add $ as a special character If this character is not escaped, documentation built with Haddock 2.17.2 will fail. This was not an issue with 2.16 series, which causes builds to fail and there is nothing in the docs or error message giving a clue about why builds that used to succeed now don't. - - - - - 324adb60 by Ben Gamari at 2016-07-01T12:18:51+02:00 GhcUtils: Changes for multi-pattern signatures - - - - - d7571675 by Ömer Sinan Ağacan at 2016-07-21T13:30:47+02:00 Add support for unboxed sums - - - - - 29d0907b by Simon Marlow at 2016-07-22T13:55:48+01:00 Disable NFData instances for GHC types when GHC >= 8.2 - - - - - 702d95f3 by Simon Marlow at 2016-08-02T15:57:30+02:00 Disable NFData instances for GHC types when GHC >= 8.0.2 (cherry picked from commit a3309e797c42dae9bccdeb17ce52fcababbaff8a) - - - - - f4fa79c3 by Ben Gamari at 2016-08-07T13:51:18+02:00 ghc.mk: Don't attempt to install html/frames.html The frames business has been removed. - - - - - 9cd63daf by Ben Gamari at 2016-08-07T13:51:40+02:00 Haddock.Types: More precise version guard This allows haddock to be built with GHC 8.0.2 pre-releases. - - - - - f3d7e03f by Mateusz Kowalczyk at 2016-08-29T20:47:45+01:00 Merge pull request haskell/haddock#538 from massysett/master Add $ as a special character - - - - - 16dbf7fd by Bartosz Nitka at 2016-09-20T19:44:04+01:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 - - - - - 7c31c1ff by Bartosz Nitka at 2016-09-27T17:32:22-04:00 Fix rendering of class methods for Eq and Ord See haskell/haddock#549 and GHC issue haskell/haddock#12519 (cherry picked from commit 073d899a8f94ddec698f617a38d3420160a7fd0b) - - - - - 33a90dce by Ryan Scott at 2016-09-30T20:53:41-04:00 Haddock changes for T10598 See https://ghc.haskell.org/trac/ghc/ticket/10598 - - - - - 1f32f7cb by Ben Gamari at 2016-10-13T20:01:26-04:00 Update for refactoring of NameCache - - - - - 1678ff2e by Ben Gamari at 2016-11-15T17:42:48-05:00 Bump upper bound on base - - - - - 9262a7c5 by Alan Zimmerman at 2016-12-07T21:14:28+02:00 Match changes in GHC wip/T3384 branch - - - - - ac0eaf1a by Ben Gamari at 2016-12-09T09:48:41-05:00 haddock-api: Don't use stdcall calling convention on 64-bit Windows See GHC haskell/haddock#12890. - - - - - 04afe4f7 by Alan Zimmerman at 2016-12-12T20:07:21+02:00 Matching changes for GHC wip/T12942 - - - - - e1d1701d by Ben Gamari at 2016-12-13T16:50:41-05:00 Bump base upper bound - - - - - 3d3eacd1 by Alan Zimmerman at 2017-01-10T16:59:38+02:00 HsIParamTy now has a Located name - - - - - 7dbceefd by Kyrill Briantsev at 2017-01-12T13:23:50+03:00 Prevent GHC API from doing optimization passes. - - - - - d48d1e33 by Richard Eisenberg at 2017-01-19T08:41:41-05:00 Upstream changes re levity polymorphism - - - - - 40c25ed6 by Alan Zimmerman at 2017-01-26T15:16:18+02:00 Changes to match haskell/haddock#13163 in GHC - - - - - 504f586d by Ben Gamari at 2017-02-02T17:19:37-05:00 Kill remaining static flags - - - - - 49147ea0 by Justus Adam at 2017-03-02T15:33:34+01:00 Adding MDoc to exports of Documentation.Haddock - - - - - 1cfba9b4 by Justus Adam at 2017-03-09T11:41:44+01:00 Also exposing toInstalledIface - - - - - 53f0c0dd by Ben Gamari at 2017-03-09T13:10:08-05:00 Bump for GHC 8.3 - - - - - c7902d2e by Ben Gamari at 2017-03-09T23:46:02-05:00 Bump for GHC 8.2 - - - - - 4f3a74f8 by Ben Gamari at 2017-03-10T10:21:55-05:00 Merge branch 'ghc-head' - - - - - e273b72f by Richard Eisenberg at 2017-03-14T13:34:04-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - 6ec3d436 by Richard Eisenberg at 2017-03-14T15:15:52-04:00 Update Haddock w.r.t. new HsImplicitBndrs - - - - - eee3cda1 by Ben Gamari at 2017-03-15T15:19:59-04:00 Adapt to EnumSet - - - - - 017cf58e by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 736d6773 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 475f84a0 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 13240b53 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - cd16d529 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 3bea97ae by Edward Z. Yang at 2017-03-15T22:50:46-07:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - b2b051ce by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 0f082795 by Edward Z. Yang at 2017-03-15T22:50:46-07:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 20ef63c9 by Edward Z. Yang at 2017-03-22T13:48:12-07:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 45692dcb by Edward Z. Yang at 2017-03-22T14:11:25-07:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 4eae8caf by Ben Gamari at 2017-03-23T09:25:33-04:00 Merge commit '240bc38b94ed2d0af27333b23392d03eeb615e82' into HEAD - - - - - 0bbe03f5 by Ben Gamari at 2017-03-23T09:27:28-04:00 haddock-api: Bump bound on GHC - - - - - 65f3ac9d by Alex Biehl at 2017-03-23T17:36:11+01:00 Merge pull request haskell/haddock#581 from JustusAdam/master Adding more exports to Documentation.Haddock - - - - - 37d49a47 by Alex Biehl at 2017-03-23T17:39:14+01:00 Merge pull request haskell/haddock#568 from awson/ghc-head Prevent GHC API from doing optimization passes. - - - - - 1ed047e4 by Brian Huffman at 2017-03-23T17:45:58+01:00 Print any user-supplied kind signatures on type parameters. This applies to type parameters on data, newtype, type, and class declarations, and also to forall-bound type vars in type signatures. - - - - - 1b78ca5c by Brian Huffman at 2017-03-23T17:45:58+01:00 Update test suite to expect kind annotations on type parameters. - - - - - a856b162 by Alex Biehl at 2017-03-23T17:49:32+01:00 Include travis build indication badge - - - - - 8e2e2c56 by Ben Gamari at 2017-03-23T17:20:08-04:00 haddock-api: Bump bound on GHC - - - - - 4d2d9995 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Correctly handle Backpack identity/semantic modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 26d6c150b31bc4580ab17cfd07b6e7f9afe10737) - - - - - a650e20f by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Add a field marking if interface is a signature or not. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 930cfbe58e2e87f5a4d431d89a3c204934e6e858) - - - - - caa282c2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render signature module tree separately from modules. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 2067a2d0afa9cef381d26fb7140b67c62f433fc0) - - - - - 49684884 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Documentation. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 0671abfe7e8ceae2269467a30b77ed9d9656e2cc) - - - - - 4dcfeb1a by Edward Z. Yang at 2017-03-23T17:20:08-04:00 More docs. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 3d77b373dd5807d5d956719dd7c849a11534fa6a) - - - - - 74dd19d2 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 TODO on moduleExports. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 94610e9b446324f4231fa6ad4c6ac51e4eba8c0e) - - - - - a9b19a23 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Better Backpack support with signature merging. When we merge signatures, we gain exports that don't necessarily have a source-level declaration corresponding to them. This meant Haddock dropped them. There are two big limitations: * If there's no export list, we won't report inherited signatures. * If the type has a subordinate, the current hiDecl implementation doesn't reconstitute them. These are probably worth fixing eventually, but this gets us to minimum viable functionality. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 6cc832dfb1de6088a4abcaae62b25a7e944d55c3) - - - - - d3631064 by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Fix haddock-test to work with latest version of Cabal. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit bf3c4d72a0fda38561376eac7eda216158783267) - - - - - ef2148fc by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Annotate signature docs with (signature) Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 07b88c5d4e79b87a319fbb08f8ea01dbb41063c1) - - - - - 2f29518b by Edward Z. Yang at 2017-03-23T17:20:08-04:00 Render help documentation link next to (signature) in title. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit 4eb765ca4205c79539d60b7afa9b7e261a4a49fe) - - - - - 37de047d by Phil Ruffwind at 2017-04-03T11:57:14+02:00 Update MathJax URL MathJax is shutting down their CDN: https://www.mathjax.org/cdn-shutting-down/ They recommend migrating to cdnjs. - - - - - e9d24ba8 by David C. Turner at 2017-04-03T14:58:01+02:00 Add highlight for :target to ocean.css - - - - - 4819a202 by Alex Biehl at 2017-04-11T19:36:48+02:00 Allow base-4.10 for haddock-test - - - - - 44cec69c by Alex Biehl at 2017-04-11T19:39:22+02:00 cabal.project for haddock-api, haddock-library and haddock-test - - - - - 935d0f6a by Alex Biehl at 2017-04-11T19:46:29+02:00 Move dist scripts to scripts/ - - - - - 128e150c by Alex Biehl at 2017-04-11T20:34:46+02:00 Add haddock to cabal.project - - - - - cc8e08ea by Alex Biehl at 2017-04-11T20:35:08+02:00 Read files for hyperlinker eagerly This also exposes Documentation.Haddock.Utf8 - - - - - 152dda78 by Alex Biehl at 2017-04-11T20:37:06+02:00 Explicit import list ofr Control.DeepSeq in Haddock.Interface.Create - - - - - 501b33c4 by Kyrill Briantsev at 2017-04-11T21:01:42+02:00 Prevent GHC API from doing optimization passes. - - - - - c9f3f5ff by Alexander Biehl at 2017-04-12T16:36:53+02:00 Add @alexbiehl as maintaner - - - - - 76f214cc by Alex Biehl at 2017-04-13T07:27:18+02:00 Disable doctest with ghc-8.3 Currently doctest doesn't support ghc-head - - - - - 46b4f5fc by Edward Z. Yang at 2017-04-22T20:38:26-07:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - f0555235 by Alex Biehl at 2017-04-25T10:08:48+02:00 Travis: Use ghc-8.2.1 on master - - - - - 966ea348 by Alex Biehl at 2017-04-25T10:32:01+02:00 Travis: Verbose cabal output cf. https://travis-ci.org/haskell/haddock/jobs/225512194#L377 - - - - - 36972bcd by Alex Biehl at 2017-04-25T10:40:43+02:00 Use travis_retry for cabal invocations - - - - - b3a09d2c by Alex Biehl at 2017-04-25T17:02:20+02:00 Use new MathJax URL in html-test 18ed871afb82560d5433b2f53e31b4db9353a74e switched to a new MathJax URL but didn't update the tests. - - - - - ae331e5f by Alexander Biehl at 2017-04-25T17:02:20+02:00 Expand signatures for class declarations - - - - - e573c65a by Alexander Biehl at 2017-04-25T17:02:20+02:00 Hoogle: Correctly print classes with associated data types - - - - - 3fc6be9b by Edward Z. Yang at 2017-04-25T17:02:20+02:00 Render (signature) only if it actually is a signature! I forgot a conditional, oops! Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> (cherry picked from commit a0c4790e15a2d3fab8d830eee8fcd639fe6d39c9) - - - - - 6725c060 by Herbert Valerio Riedel at 2017-04-25T17:02:20+02:00 `html-test --accept` deltas to reference samples - - - - - 7d444d61 by Alex Biehl at 2017-04-26T07:13:50+02:00 Remove anything related to obsolete frames mode - - - - - b888972c by Alex Biehl at 2017-04-26T07:49:10+02:00 Cherry-picked remaining commits from haddock-2.17.4-release (#603) * Release haddock/haddock-api 2.17.4 and haddock-library 1.4.3 * Set version bounds for haddock-library NB: This allows GHC 8.2.1's base * Set version bounds for haddock & haddock-api The version bounds support GHC 8.2 * Merge (temporary) v2.17.3 branch into v2.17 This allows us to delete the v2.17.3 branch * Fixup changelog * Pin down haddock-api to a single version as otherwise `haddock`'s package version has no proper meaning * fix source-repo spec for haddock-api - - - - - 4161099b by Alex Biehl at 2017-04-26T11:11:20+02:00 Update changelog to reflect news in HEAD - - - - - eed72cb8 by Alex Biehl at 2017-04-26T11:11:20+02:00 Markdownify changelog - - - - - 5815cea1 by Alex Biehl at 2017-04-26T11:32:33+02:00 Bump to 2.18.0 (#605) - - - - - a551d558 by Alex Biehl at 2017-04-29T22:00:25+02:00 Update attoparsec-0.12.1.1 to attoparsec-0.13.1.0 - - - - - ea164a8d by Sergey Vinokurov at 2017-04-29T22:42:36+02:00 Improve error message - - - - - 2e10122f by Alex Biehl at 2017-04-30T10:07:46+02:00 Correctly remember collapsed sections (#608) Now the "collapsed" cookie stores which sections have changed state instead of which are collapsed. - - - - - f9b24d99 by Alex Biehl at 2017-05-01T17:40:36+02:00 Lazily decode docMap and argMap (#610) These are only used in case of a doc reexport so most of the time decoding these is wasted work. - - - - - 2372af62 by Alex Biehl at 2017-05-01T21:59:23+02:00 Fix Binary instance for InstalledInterface (#611) (#610) introduced lazy decoding for docs from InstalledInterface but forgot to remove the original calls to get and put_ - - - - - 6c633c13 by Nathan Collins at 2017-05-11T11:47:55+02:00 Improve documenation of Haddock markup (#614) * Improve documentation of Haddock markup. - document that Haddock supports inferring types top-level functions with without type signatures, but also explain why using this feature is discouraged. Looks like this feature has been around since version 2.0.0.0 in 2008! - rework the "Module description" section: - move the general discussion of field formatting to the section intro and add examples illustrating the prose for multiline fields. - mention that newlines are preserved in some multiline fields, but not in others (I also noticed that commas in the `Copyright` field are not preserved; I'll look into this bug later). - add a subsection for the module description fields documentation, and put the field keywords in code formatting (double back ticks) instead of double quotes, to be consistent with the typesetting of keywords in other parts of the documentation. - mention that "Named chunks" are not supported in the long-form "Module description" documentation. - fix formatting of keywords in the "Module attributes" section. Perhaps these errors were left over from an automatic translation to ReST from some other format as part of the transition to using Sphinx for Haddock documentation? Also, add a missing reference here; it just said "See ?"! - update footnote about special treatment for re-exporting partially imported modules not being implemented. In my tests it's not implemented at all -- I tried re-exporting both `import B hiding (f)` and `import B (a, b)` style partial imports, and in both cases got the same result as with full imports `import B`: I only get a module reference. * Rework the `Controlling the documentation structure` section. My main goal was to better explain how to use Haddock without an export list, since that's my most common use case, but I hope I improved the section overall: - remove the incomplete `Omitting the export list` section and fold it into the other sections. In particular, summarize the differences between using and not using an export list -- i.e. control over what and in what order is documented -- in the section lead. - add "realistic" examples that use the structure markup, both with and without an export list. I wanted a realistic example here to capture how it can be useful to explain the relationship between a group of functions in a section, in addition to documenting their individual APIs. - make it clear that you can associate documentation chunks with documentation sections when you aren't using an export list, and that doing it in the most obvious way -- i.e. with `-- |`, as you can in the export list -- doesn't work without an export list. It took me a while to figure this out the first time, since the docs didn't explain it at all before. - add a "no export list" example to the section header section. - add more cross references. * Add examples of gotchas for markup in `@...@`. I'm not sure this will help anyone, since I think most people first learn about `@...@` by reading other people's Haddocks, but I've documented the mistakes which I've made and then gotten confused by. * Use consistent Capitalization of Titles. Some titles were in usual title caps, and others only had the first word capitalized. I chose making them all use title caps because that seems to make the cross references look better. - - - - - d4734f45 by Ben Gamari at 2017-05-12T20:36:08+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 93883f37 by Alex Biehl at 2017-05-12T21:02:33+02:00 Haddock: Fix broken lazy IO in prologue reading (#615) We previously used withFile in conjunction with hGetContents. The list returned by the latter wasn't completely forced by the time we left the withFile block, meaning that we would try to read from a closed handle. - - - - - 5b8f179c by Alex Biehl at 2017-05-13T12:48:10+02:00 Consequently use inClass and notInClass in haddock-library (#617) These allow attoparsec to do some clever lookup optimization - - - - - 77984b82 by Doug Wilson at 2017-05-27T17:37:38+02:00 Don't enable compilation for template haskell (#624) This is no longer necessary after ghc commit 53c78be0aab76a3107c4dacbb1d177afacdd37fa - - - - - 5a3de2b4 by Doug Wilson at 2017-05-27T19:54:53+02:00 Improve Syb code (#621) Specialize.hs and Ast.hs are modified to have their Syb code not recurse into Name or Id in HsSyn types. Specialize.hs is refactored to have fewer calls to Syb functions. Syb.hs has some foldl calls replaced with foldl' calls. There is still a lot of performance on the floor of Ast.hs. The RenamedSource is traversed many times, and lookupBySpan is very inefficient. everywhereBut and lookupBySpan dominate the runtime whenever --hyperlinked-source is passed. - - - - - 3d35a949 by Alex Biehl at 2017-05-30T19:01:37+02:00 Clear fixme comment (#625) - - - - - 2a44bd0c by Alex Biehl at 2017-05-30T19:02:12+02:00 Make haddock-library and haddock-api warning free (#626) - - - - - bd1a0e42 by Alex Biehl at 2017-06-01T10:40:33+02:00 Include `driver-test/*.hs` sdist (#630) This lead to haskell/haddock#629. - - - - - 184a3ab6 by Doug Wilson at 2017-06-03T12:02:08+02:00 Disable pattern match warnings (#628) This disables the pattern match checker which can be very expensive in some cases. The disabled warnings include: * Opt_WarnIncompletePatterns * Opt_WarnIncompleteUniPatterns * Opt_WarnIncompletePatternsRecUpd * Opt_WarnOverlappingPatterns - - - - - 0cf68004 by Alex Biehl at 2017-06-03T20:37:28+02:00 Allow user defined signatures for pattern synonyms (#631) - - - - - 7f51a58a by Alex Biehl at 2017-06-04T11:56:38+02:00 Use NameSet for isExported check (#632) - - - - - d8f044a9 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Match new AST as per GHC wip/new-tree-one-param See https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow - - - - - da1254e3 by Alan Zimmerman at 2017-06-05T22:26:55+02:00 Rename extension index tags - - - - - 538c7514 by Christiaan Baaij at 2017-06-09T08:26:43+02:00 Haddock support for bundled pattern synonyms (#627) * Haddock support for bundled pattern synonyms * Add fixities to bundled pattern synonyms * Add bundled pattern synonyms to the synopsis * Store bundled pattern fixities in expItemFixities * Add test for bundled pattern synonyms * Stop threading fixities * Include bundled pattern synonyms for re-exported data types Sadly, fixity information isn't found for re-exported data types * Support for pattern synonyms * Modify tests after haskell/haddock#631 * Test some reexport variations * Also lookup bundled pattern synonyms from `InstalledInterface`s * Check isExported for bundled pattern synonyms * Pattern synonym is exported check * Always look for pattern synonyms in the current module Another overlooked cornercase * Account for types named twice in export lists Also introduce a fast function for nubbing on a `Name` and use it throughout the code base. * correct fixities for reexported pattern synonyms * Fuse concatMap and map * Remove obsolete import * Add pattern synonyms to visible exports * Fix test * Remove corner case - - - - - a050bffd by Doug Wilson at 2017-06-21T09:27:33+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#636) There is some performance improvement. GHC compiler: | version | bytes allocated | cpu_seconds --------------------------------- | before | 56057108648 | 41.0 | after | 51592019560 | 35.1 base: | version | bytes allocated | cpu_seconds --------------------------------- | before | 25174011784 | 14.6 | after | 23712637272 | 13.1 Cabal: | version | bytes allocated | cpu_seconds --------------------------------- | before | 18754966920 | 12.6 | after | 18198208864 | 11.6 - - - - - 5d06b871 by Doug Wilson at 2017-06-22T20:23:29+02:00 Use new function getNameToInstancesIndex instead of tcRnGetInfo (#639) * Use new function getNameToInstancesIndex instead of tcRnGetInfo There is some significant performance improvement in the ghc testsuite. haddock.base: -23.3% haddock.Cabal: -16.7% haddock.compiler: -19.8% * Remove unused imports - - - - - b11bb73a by Alex Biehl at 2017-06-23T14:44:41+02:00 Lookup fixities for reexports without subordinates (#642) So we agree that reexported declarations which do not have subordinates (for example top-level functions) shouldn't have gotten fixities reexported according to the current logic. I wondered why for example Prelude.($) which is obviously reexported from GHC.Base has fixities attached (c.f. http://hackage.haskell.org/package/base-4.9.1.0/docs/Prelude.html#v:-36-). The reason is this: In mkMaps we lookup all the subordinates of top-level declarations, of course top-level functions don't have subordinates so for them the resulting list is empty. In haskell/haddock#644 I established the invariant that there won't be any empty lists in the subordinate map. Without the patch from haskell/haddock#642 top-level functions now started to fail reexporting their fixities. - - - - - d2a6dad6 by Alex Biehl at 2017-06-23T18:30:45+02:00 Don't include names with empty subordinates in maps (#644) These are unecessary anyway and just blow up interface size - - - - - 69c2aac4 by Alex Biehl at 2017-06-29T19:54:49+02:00 Make per-argument docs for class methods work again (#648) * Make per-argument docs for class methods work again * Test case - - - - - c9448d54 by Bartosz Nitka at 2017-07-02T12:12:01+02:00 Fix haddock: internal error: links: UnhelpfulSpan (#561) * Fix haddock: internal error: links: UnhelpfulSpan This fixes haskell/haddock#554 for me. I believe this is another fall out of `wildcard-refactor`, like haskell/haddock#549. * Comment to clarify why we take the methods name location - - - - - d4f29eb7 by Alex Biehl at 2017-07-03T19:43:04+02:00 Document record fields when DuplicateRecordFields is enabled (#649) - - - - - 9d6e3423 by Yuji Yamamoto at 2017-07-03T22:37:58+02:00 Fix test failures on Windows (#564) * Ignore .stack-work * Fix for windows: use nul instead of /dev/null * Fix for windows: canonicalize line separator * Also normalize osx line endings - - - - - 7d81e8b3 by Yuji Yamamoto at 2017-07-04T16:13:12+02:00 Avoid errors on non UTF-8 Windows (#566) * Avoid errors on non UTF-8 Windows Problem ==== haddock exits with errors like below: `(1)` ``` haddock: internal error: <stderr>: hPutChar: invalid argument (invalid character) ``` `(2)` ``` haddock: internal error: Language\Haskell\HsColour\Anchors.hs: hGetContents: invalid argument (invalid byte sequence) ``` `(1)` is caused by printing [the "bullet" character](http://www.fileformat.info/info/unicode/char/2022/index.htm) onto stderr. For example, this warning contains it: ``` Language\Haskell\HsColour\ANSI.hs:62:10: warning: [-Wmissing-methods] • No explicit implementation for ‘toEnum’ • In the instance declaration for ‘Enum Highlight’ ``` `(2)` is caused when the input file of `readFile` contains some Unicode characters. In the case above, '⇒' is the cause. Environment ---- OS: Windows 10 haddock: 2.17.3 GHC: 8.0.1 Solution ==== Add `hSetEncoding handle utf8` to avoid the errors. Note ==== - I found the detailed causes by these changes for debugging: - https://github.com/haskell/haddock/commit/8f29edb6b02691c1cf4c479f6c6f3f922b35a55b - https://github.com/haskell/haddock/commit/1dd23bf2065a1e1f2c14d0f4abd847c906b4ecb4 - These errors happen even after executing `chcp 65001` on the console. According to the debug code, `hGetEncoding stderr` returns `CP932` regardless of the console encoding. * Avoid 'internal error: <stderr>: hPutChar: invalid argument (invalid character)' non UTF-8 Windows Better solution for 59411754a6db41d17820733c076e6a72bcdbd82b's (1) - - - - - eded67d2 by Alex Biehl at 2017-07-07T19:17:15+02:00 Remove redudant import warning (#651) - - - - - 05114757 by Alex Biehl at 2017-07-08T00:33:12+02:00 Avoid missing home module warning (#652) * Avoid missing home module warning * Update haddock-library.cabal - - - - - e9cfc902 by Bryn Edwards at 2017-07-17T07:51:20+02:00 Fix haskell/haddock#249 (#655) - - - - - eb02792b by Herbert Valerio Riedel at 2017-07-20T09:09:15+02:00 Fix compilation of lib:haddock-library w/ GHC < 8 - - - - - 9200bfbc by Alex Biehl at 2017-07-20T09:20:38+02:00 Prepare 2.18.1 release (#657) - - - - - 46ddd22c by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Tweak haddock-api.cabal for pending release - - - - - 85e33d29 by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Avoid trivial use of LambdaCase otherwise we can't test w/ e.g. GHC 7.4.2 - - - - - 3afb4bfe by Herbert Valerio Riedel at 2017-07-20T10:05:14+02:00 Refactor .cabal to use sub-lib for vendored lib A practical benefit is that we can control the build-depends and also avoid some recompilation between library and test-suite. - - - - - e56a552e by Herbert Valerio Riedel at 2017-07-20T10:17:48+02:00 haddock-api: add changelog pointing to haddock's changelog This addresses https://github.com/haskell/haddock/issues/638#issuecomment-309283297 - - - - - 2222ff0d by Herbert Valerio Riedel at 2017-07-20T10:19:56+02:00 Drop obsolete/misleading `stability: experimental` This .cabal property has long been considered obsolete - - - - - 9b882905 by Alex Biehl at 2017-07-20T11:25:54+02:00 Beef up haddock description (#658) * Beef up haddock description * Handle empty lines - - - - - bb60e95c by Herbert Valerio Riedel at 2017-07-20T12:08:53+02:00 Import @aisamanra's Haddock cheatsheet from https://github.com/aisamanra/haddock-cheatsheet - - - - - 0761e456 by Herbert Valerio Riedel at 2017-07-20T12:12:55+02:00 Add cheatsheet to haddock.cabal - - - - - 2ece0f0f by Herbert Valerio Riedel at 2017-07-20T12:18:38+02:00 Mention new-build in README - - - - - 947b7865 by Herbert Valerio Riedel at 2017-07-20T12:32:16+02:00 Update README Also improves markup and removes/fixes redundant/obsolete parts [skip ci] - - - - - 785e09ad by Alex Biehl at 2017-07-27T07:28:57+02:00 Bump haddock to 2.18.2, haddock-library to 1.4.5 - - - - - e3ff1ca3 by Alex Biehl at 2017-07-31T20:15:32+02:00 Move `DocMarkup` from haddock-api to haddock-library (#659) * Move `DocMarkup` from haddock-api to haddock-library * Move more markup related functions * Markup module * CHANGELOG - - - - - cda7c20c by Alex Biehl at 2017-07-31T20:35:49+02:00 Fixup haddock - - - - - 583b6812 by Alex Biehl at 2017-07-31T21:20:45+02:00 Changelog for haddock-library - - - - - bac6a0eb by Alex Biehl at 2017-07-31T21:50:24+02:00 Prepare haddock-library-1.4.5 release - - - - - 58ce6877 by Moritz Drexl at 2017-08-05T16:44:40+02:00 Fix renaming after instance signature specializing (#660) * rework rename * Add regression test for Bug 613 * update tests * update changelog - - - - - b8137ec8 by Tim Baumann at 2017-08-06T11:33:38+02:00 Fix: Generate pattern signatures for constructors exported as patterns (#663) * Fix pretty-printing of pattern signatures Pattern synonyms can have up to two contexts, both having a different semantic meaning: The first holds the constraints required to perform the matching, the second contains the constraints provided by a successful pattern match. When the first context is empty but the second is not it is necessary to render the first, empty context. * Generate pattern synonym signatures for ctors exported as patterns This fixes haskell/haddock#653. * Simplify extractPatternSyn It is not necessary to generate the simplest type signature since it will be simplified when pretty-printed. * Add changelog entries for PR haskell/haddock#663 * Fix extractPatternSyn error message - - - - - d037086b by Alex Biehl at 2017-08-06T12:43:25+02:00 Bump haddock-library - - - - - 99d7e792 by Alex Biehl at 2017-08-06T12:44:07+02:00 Bump haddock-library in haddock-api - - - - - 94802a5b by Alex Biehl at 2017-08-06T13:18:02+02:00 Provide --show-interface option to dump interfaces (#645) * WIP: Provide --show-interface option to dump interfaces Like ghcs own --show-iface this flag dumps a binary interface file to stdout in a human (and machine) readable fashion. Currently it uses json as output format. * Fill all the jsonNull stubs * Rework Bifunctor instance of DocH, update changelog and documentation * replace changelog, bring DocMarkupH doc back * Update CHANGES.md * Update CHANGES.md * Move Control.Arrow up It would result in unused import if the Bifunctor instance is not generated. - - - - - c662e476 by Ryan Scott at 2017-08-14T21:00:21-04:00 Adapt to haskell/haddock#14060 - - - - - b891eb73 by Alex Biehl at 2017-08-16T08:24:48+02:00 Bifoldable and Bitraversable for DocH and MetaDoc - - - - - 021bb56c by Alex Biehl at 2017-08-16T09:06:40+02:00 Refactoring: Make doc renaming monadic This allows us to later throw warnings if can't find an identifier - - - - - 39fbf022 by Alex Biehl at 2017-08-19T20:35:27+02:00 Hyperlinker: Avoid linear lookup in enrichToken (#669) * Make Span strict in Position * Hyperlinker: Use a proper map to enrich tokens - - - - - e13baedd by Alex Biehl at 2017-08-21T20:05:42+02:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 27dd6e87 by Alex Biehl at 2017-08-21T22:06:35+02:00 Drop Avails from export list - - - - - 86b247e2 by Alex Biehl at 2017-08-22T08:44:22+02:00 Bump ghc version for haddock-api tests - - - - - d4607ca0 by Alex Biehl at 2017-08-22T08:45:17+02:00 Revert "Drop Avails from export list" This reverts commit a850ba86d88a4fb9c0bd175453a2580e544e3def. - - - - - c9c54c30 by Alex Biehl at 2017-08-22T09:26:01+02:00 IntefaceFile version - - - - - a85b7c02 by Ben Gamari at 2017-08-22T09:29:52-04:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 34e976f5 by Ben Gamari at 2017-08-22T17:40:06+02:00 haddock: Add Documentation.Haddock.Markup to other-modules - - - - - 577abf06 by Ryan Scott at 2017-08-23T14:47:29-04:00 Update for haskell/haddock#14131 - - - - - da68fc55 by Florian Eggenhofer at 2017-08-27T18:21:56+02:00 Generate an index for package content search (#662) Generate an index for package content search - - - - - 39e62302 by Alex Biehl at 2017-08-27T18:50:16+02:00 Content search for haddock html doc - - - - - 91fd6fb2 by Alex Biehl at 2017-08-28T18:39:58+02:00 Fix tests for content search - - - - - b4a3798a by Alex Biehl at 2017-08-28T18:44:08+02:00 Add search button to #page-menu - - - - - 25a7ca65 by Alex Biehl at 2017-08-28T18:47:43+02:00 Load javascript below the fold - - - - - 8d323c1a by Alex Biehl at 2017-08-28T18:49:22+02:00 Accept tests - - - - - c5dac557 by Alex Biehl at 2017-08-28T19:14:55+02:00 Content search css - - - - - 89a5af57 by Paolo Veronelli at 2017-08-29T07:42:13+02:00 Removed `nowrap` for interface method sigs (#674) with nowrap the interfaces method sigs would expand at libitum - - - - - a505f6f7 by Alex Biehl at 2017-08-29T08:05:33+02:00 Include subordinates in content index - - - - - 4bb698c4 by Alexander Biehl at 2017-08-29T11:40:19+02:00 QuickNav: Make docbase configurable - - - - - c783bf44 by Alexander Biehl at 2017-08-29T11:48:36+02:00 QuickNav: Also use baseUrl for doc-index.json request - - - - - 47017510 by Alex Biehl at 2017-08-29T17:56:47+02:00 Fix test fallout (again) - - - - - 924fc318 by Alex Biehl at 2017-08-30T09:24:56+02:00 Write meta.json when generating html output (#676) - - - - - 717dea52 by Alex Biehl at 2017-09-01T09:20:34+02:00 Use relative URL when no docBaseUrl given - - - - - e5d85f3b by Alex Biehl at 2017-09-01T09:35:19+02:00 Add missing js files to data-files (#677) - - - - - 95b9231a by Alex Biehl at 2017-09-01T11:01:36+02:00 Rename "Search" tab to "Quick Jump" - - - - - da0ead0b by Alex Biehl at 2017-09-01T13:03:49+02:00 Make trigger link configurable (#678) QuickNav: Configurable show/hide trigger - - - - - de7da594 by Ben Gamari at 2017-09-05T06:49:55-04:00 Account for "Remember the AvailInfo for each IE" As of GHC commit f609374a55bdcf3b79f3a299104767aae2ffbf21 GHC retains the AvailInfo associated with each IE. @alexbiehl has a patch making proper use of this change, but this is just to keep things building. - - - - - b05cd3b3 by Ben Gamari at 2017-09-14T07:55:07-04:00 Bump upper bound on base - - - - - 79db899e by Herbert Valerio Riedel at 2017-09-21T23:27:52+02:00 Make compatible with Prelude.<> export in GHC 8.4/base-4.11 - - - - - 3405dd52 by Tim Baumann at 2017-09-23T22:02:01+02:00 Add compile step that bundles and compresses JS files (#684) * Add compile step that bundles and compresses JS files Also, manage dependencies on third-party JS libraries using NPM. * Compile JS from TypeScript * Enable 'noImplicitAny' in TypeScript * QuickJump: use JSX syntax * Generate source maps from TypeScript for easier debugging * TypeScript: more accurate type * Separate quick jump css file from ocean theme - - - - - df0b5742 by Alex Biehl at 2017-09-29T21:15:40+02:00 Bump base for haddock-library and haddock-test - - - - - 62b12ea0 by Merijn Verstraaten at 2017-10-04T16:03:13+02:00 Inhibit output of coverage information for hidden modules. (#687) * Inhibit output of coverage information for hidden modules. * Add changelog entry. - - - - - 8daf8bc1 by Alexander Biehl at 2017-10-05T11:27:05+02:00 Don't use subMap in attachInstances - - - - - ad75114e by Alexander Biehl at 2017-10-05T11:27:58+02:00 Revert "Don't use subMap in attachInstances" This reverts commit 3adf5bcb1a6c5326ab33dc77b4aa229a91d91ce9. - - - - - 7d4aa02f by Alex Biehl at 2017-10-08T15:32:28+02:00 Precise Haddock: Use Avails for export resolution (#688) * Use Avails for export resolution * Support reexported modules * Factor out availExportItem * Use avails for fullModuleExports * Don't use subMap in attachInstances * lookupDocs without subMap * Completely remove subMap * Only calculate unqualified modules when explicit export list is given * Refactor * Refine comment * return * Fix * Refactoring * Split avail if declaration is not exported itself * Move avail splitting - - - - - b9b4faa8 by Alex Biehl at 2017-10-08T19:38:21+02:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 43325295 by Alex Biehl at 2017-10-08T20:18:46+02:00 Fix merge fallout - - - - - c6423cc0 by Alex Biehl at 2017-10-08T20:36:12+02:00 Copy QuickJump files over - - - - - 1db587c3 by Tim Baumann at 2017-10-09T18:33:09+02:00 Use <details> element for collapsibles (#690) * Remove unnecessary call to 'collapseSection' The call is unnecessary since there is no corresponding toggle for hiding the section of orphan instances. * Use <details> for collapsibles This makes them work even when JS is disabled. Closes haskell/haddock#560. - - - - - 1b54c64b by Tim Baumann at 2017-10-10T09:50:59+02:00 Quick Jump: Show error when loading 'doc-index.json' failed (#691) - - - - - 910f716d by Veronika Romashkina at 2017-10-24T07:36:20+02:00 Fix tiny typo in docs (#693) - - - - - b21de7e5 by Ryan Scott at 2017-10-24T13:07:15+02:00 Overhaul Haddock's rendering of kind signatures (#681) * Overhaul Haddock's rendering of kind signatures * Strip off kind signatures when specializing As an added bonus, this lets us remove an ugly hack specifically for `(->)`. Yay! * Update due to 0390e4a0f61e37bd1dcc24a36d499e92f2561b67 * @alexbiehl's suggestions * Import injectiveVarsOfBinder from GHC - - - - - 6704405c by Ryan Scott at 2017-10-28T07:10:27+02:00 Fix Haddock rendering of kind-indexed data family instances (#694) - - - - - 470f6b9c by Alex Biehl at 2017-10-30T08:45:51+01:00 Add QuickJump version to meta.json (#696) - - - - - b89eccdf by Alex Biehl at 2017-10-30T10:15:49+01:00 Put Quickjump behind --quickjump flag (#697) - - - - - 3095fb58 by Alex Biehl at 2017-10-30T19:09:06+01:00 Add build command to package.json - - - - - f223fda9 by Alex Biehl at 2017-10-30T19:10:39+01:00 Decrease threshold for fuzzy matching - - - - - 80245dda by Edward Z. Yang at 2017-10-31T20:35:05+01:00 Supported reexported-modules via --reexport flag. Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu> - - - - - 7e389742 by Alex Biehl at 2017-10-31T20:37:56+01:00 Correct missing title in changelog - - - - - 1a2a1c03 by Alex Biehl at 2017-10-31T20:59:07+01:00 Copy quickjump.css for nicer error messages - - - - - db234bb9 by Alex Biehl at 2017-10-31T21:31:18+01:00 Reexported modules: Report warnings if argument cannot be parsed or ... module cannot be found - - - - - eea8a205 by Carlo Hamalainen at 2017-10-31T21:43:14+01:00 More general type for nameCacheFromGhc. (#539) - - - - - 580eb42a by Alex Biehl at 2017-10-31T21:46:52+01:00 Remote tab - - - - - 0e599498 by Alex Biehl at 2017-10-31T21:48:55+01:00 Merge remote-tracking branch 'origin/master' into ghc-head - - - - - 7b8539bb by Alex Biehl at 2017-10-31T22:28:34+01:00 fullModuleContents traverses exports in declaration order - - - - - 0c91fbf2 by Alex Biehl at 2017-10-31T22:32:31+01:00 Remove excessive use of list comprehensions - - - - - f7356e02 by Alex Biehl at 2017-11-01T19:11:03+01:00 Make better use of AvailInfo - - - - - f3e512d5 by Alex Biehl at 2017-11-02T12:16:22+01:00 Always return documentation for exported subordinates ... event if they have no documentation (e.g. noDocForDecl) By using the information in the AvailInfo we don't need additional export checks. - - - - - 7cf58898 by Alan Zimmerman at 2017-11-07T08:28:03+02:00 Match changes for Trees that Grow in GHC - - - - - e5105a41 by Alan Zimmerman at 2017-11-08T17:21:58+02:00 Match Trees That Grow - - - - - 55178266 by Alan Zimmerman at 2017-11-11T22:20:31+02:00 Match Trees that Grow in GHC for HsExpr - - - - - 2082ab02 by Ryan Scott at 2017-11-14T15:27:03+01:00 Actually render infix type operators as infix (#703) * Actually render infix type operators as infix * Account for things like `(f :*: g) p`, too - - - - - c52ab7d0 by Alan Zimmerman at 2017-11-14T23:14:26+02:00 Clean up use of PlaceHolder, to match TTG - - - - - 81cc9851 by Moritz Angermann at 2017-11-20T07:52:49+01:00 Declare use of `Paths_haddock` module in other-modules (#705) This was detected by `-Wmissing-home-modules` - - - - - f9d27598 by Moritz Angermann at 2017-11-20T12:47:34+01:00 Drop Paths_haddock from ghc.mk (#707) With haskell/haddock#705 and haskell/haddock#706, the custom addition should not be necessary any more. # Conflicts: # ghc.mk - - - - - f34818dc by Moritz Angermann at 2017-11-20T12:47:59+01:00 Add autogen-modules (#706) > Packages using 'cabal-version: >= 1.25' and the autogenerated module Paths_* must include it also on the 'autogen-modules' field besides 'exposed-modules' and 'other-modules'. This specifies that the module does not come with the package and is generated on setup. Modules built with a custom Setup.hs script also go here to ensure that commands like sdist don't fail. # Conflicts: # haddock.cabal - - - - - bb43a0aa by Ben Gamari at 2017-11-21T15:50:12-05:00 Revert "Clean up use of PlaceHolder, to match TTG" This reverts commit 134a7bb054ea730b13c8629a76232d73e3ace049. - - - - - af9ebb2b by Ben Gamari at 2017-11-21T15:50:14-05:00 Revert "Match Trees that Grow in GHC for HsExpr" This reverts commit 9f054dc365379c66668de6719840918190ae6e44. - - - - - 5d35c3af by Ben Gamari at 2017-11-21T15:50:15-05:00 Revert "Match Trees That Grow" This reverts commit 73a26af844ac50b8bec39de11d64452a6286b00c. - - - - - 99a8e43b by Ben Gamari at 2017-11-21T16:36:06-05:00 Revert "Match changes for Trees that Grow in GHC" This reverts commit 01eeeb048acd2dd05ff6471ae148a97cf0720547. - - - - - c4d650c2 by Ben Gamari at 2017-12-04T15:06:07-05:00 Bump GHC version - - - - - 027b2274 by Ben Gamari at 2017-12-04T17:06:31-05:00 Bump GHC bound to 8.4.* - - - - - 58eaf755 by Alex Biehl at 2017-12-06T15:44:24+01:00 Update changelog - - - - - d68f5584 by Simon Peyton Jones at 2017-12-07T14:39:56+00:00 Track changes to follow Trac haskell/haddock#14529 This tracks the refactoring of HsDecl.ConDecl. - - - - - dc519d6b by Alec Theriault at 2018-01-06T08:20:43-08:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - 8285118c by Alec Theriault at 2018-01-13T12:12:37+01:00 Constructor and pattern synonym argument docs (#709) * Support Haddocks on constructor arguments This is in conjunction with https://phabricator.haskell.org/D4094. Adds support for rendering Haddock's on (non-record) constructor arguments, both for regular and GADT constructors. * Support haddocks on pattern synonym arguments It appears that GHC already parsed these - we just weren't using them. In the process of doing this, I tried to deduplicate some code around handling patterns. * Update the markup guide Add some information about the new support for commenting constructor arguments, and mention pattern synonyms and GADT-style constructors. * Overhaul LaTeX support for data/pattern decls This includes at least * fixing several bugs that resulted in invalid LaTeX * fixing GADT data declaration headers * overhaul handling of record fields * overhaul handling of GADT constructors * overhaul handling of bundled patterns * add support for constructor argument docs * Support GADT record constructors This means changes what existing HTML docs look like. As for LaTeX, looks like GADT records were never even supported. Now they are. * Clean up code/comments Made code/comments consistent between the LaTeX and XHTML backend when possible. * Update changelog * Patch post-rebase regressions * Another post-rebase change We want return values to be documentable on record GADT constructors. - - - - - ca4fabb4 by Alec Theriault at 2018-01-15T17:12:18-08:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 4c472fea by Ryan Scott at 2018-01-19T10:44:02+01:00 Fix haskell/haddock#732 (#733) - - - - - bff14dbd by Alex Biehl at 2018-01-19T15:33:30+01:00 extractDecl: Extract associated types correctly (#736) - - - - - a2a94a73 by Alex Biehl at 2018-01-19T15:34:40+01:00 extractDecl: Extract associated types correctly (#736) - - - - - 26df93dc by Alex Biehl at 2018-01-20T10:18:22+01:00 haddock-api: bump ghc to ^>= 8.4 - - - - - f65aeb1d by Alex Biehl at 2018-01-20T19:18:20+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - 0e721b97 by Alex Biehl at 2018-01-20T19:20:19+01:00 Fix duplicate declarations and TypeFamilies specifics - - - - - cb6234f6 by Ben Gamari at 2018-01-26T13:40:55-05:00 Merge remote-tracking branch 'harpocrates/fix/missing-orphan-instances' into ghc-head - - - - - 0fc28554 by Alec Theriault at 2018-02-01T14:58:18+01:00 Pass to GHC visible modules for instance filtering The GHC-side `getNameToInstancesIndex` filters out incorrectly some instances because it is not aware of what modules are visible. On the Haddock side, we need to pass in the modules we are processing. On the GHC side, we need to check against _those_ modules when checking if an instance is visible. - - - - - b9123772 by Alec Theriault at 2018-02-01T14:58:18+01:00 Update the GblRdrEnv when processing modules Without a complete environment, we will miss some instances that were encountered during typechecking. - - - - - 0c12e274 by Ryan Scott at 2018-02-01T14:58:18+01:00 Fix haskell/haddock#548 by rendering datatype kinds more carefully (#702) - - - - - 8876d20b by Alec Theriault at 2018-02-01T14:58:18+01:00 Use the GHC lexer for the Hyperlinker backend (#714) * Start changing to use GHC lexer * better cpp * Change SrcSpan to RealSrcSpan * Remove error * Try to stop too many open files * wip * wip * Revert "wip" This reverts commit b605510a195f26315e3d8ca90e6d95a6737553e1. Conflicts: haddock-api/haddock-api.cabal haddock-api/src/Haddock/Interface.hs * Remove pointless 'caching' * Use dlist rather than lists when finding vars * Use a map rather than list * Delete bogus comment * Rebase followup Things now run using the GHC lexer. There are still - stray debug statements - unnecessary changes w.r.t. master * Cleaned up differences w.r.t. current Haddock HEAD Things are looking good. quasiquotes in particular look beautiful: the TH ones (with Haskell source inside) colour/link their contents too! Haven't yet begun to check for possible performance problems. * Support CPP and top-level pragmas The support for these is hackier - but no more hacky than the existing support. * Tests pass, CPP is better recognized The tests were in some cases altered: I consider the new output to be more correct than the old one.... * Fix shrinking of source without tabs in test * Replace 'Position'/'Span' with GHC counterparts Replaces 'Position' -> 'GHC.RealSrcLoc' and 'Span' -> 'GHC.RealSrcSpan'. * Nits * Forgot entry in .cabal * Update changelog - - - - - 95c6a771 by Alec Theriault at 2018-02-01T14:58:18+01:00 Clickable anchors for headings (#716) See haskell/haddock#579. This just adds an <a> tag around the heading, pointing to the heading itself. - - - - - 21463d28 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump: Matches on function names weight more than matches in ... module names. - - - - - 8023af39 by Alex Biehl at 2018-02-01T14:58:18+01:00 Treat escaped \] better in definition lists (#717) This fixes haskell/haddock#546. - - - - - e4866dc1 by Alex Biehl at 2018-02-01T14:58:18+01:00 Remove scanner, takeWhile1_ already takes care of escaping - - - - - 9bcaa49d by Alex Biehl at 2018-02-01T14:58:18+01:00 Take until line feed - - - - - 01d2af93 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Add simple framework for running parser fixtures (#668) * Add simple framework for running parser fixtures * Compatible with tree-diff-0.0.0.1 * Use parseParas to parse fixtures This allows to test all syntactic constructs available in haddock markup. - - - - - 31128417 by Alec Theriault at 2018-02-01T14:58:18+01:00 Patch flaky parser test (#720) * Patch flaky parser test This test was a great idea, but it doesn't port over too well to using the GHC lexer. GHC rewrites its input a bit - nothing surprising, but we need to guard against those cases for the test. * Change instance head * Change use site - - - - - 9704f214 by Herbert Valerio Riedel at 2018-02-01T14:58:18+01:00 Include secondary LICENSE file in source dist - - - - - 51f25074 by Oleg Grenrus at 2018-02-01T14:58:18+01:00 Grid Tables (#718) * Add table examples * Add table types and adopt simple parser Simple parser is done by Giovanni Cappellotto (@potomak) in https://github.com/haskell/haddock/pull/577 It seems to support single fine full tables, so far from full RST-grid tables, but it's good start. Table type support row- and colspans, but obviously parser is lacking. Still TODO: - Latex backend. Should we use multirow package https://ctan.org/pkg/multirow?lang=en? - Hoogle backend: ? * Implement grid-tables * Refactor table parser * Add two ill-examples * Update CHANGES.md * Basic documentation for tables * Fix documentation example - - - - - 670d6200 by Alex Biehl at 2018-02-01T14:58:18+01:00 Add grid table example to cheatsheet (pdf and svg need to be regenerated thought) - - - - - 4262dec9 by Alec Theriault at 2018-02-01T14:58:18+01:00 Fix infinite loop when specializing instance heads (#723) * Fix infinite loop when specializing instance heads The bug can only be triggered from TH, hence why it went un-noticed for so long. * Add test for haskell/haddock#679 and haskell/haddock#710 - - - - - 67ecd803 by Alec Theriault at 2018-02-01T14:58:18+01:00 Filter RTS arguments from 'ghc-options' arguments (#725) This fixes haskell/haddock#666. - - - - - 7db26992 by Alex Biehl at 2018-02-01T14:58:18+01:00 Quickjump Scrollable overlay - - - - - da9ff634 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Hyperlinker: Adjust parser to new PFailed constructor - - - - - 7b7cf8cb by Alexander Biehl at 2018-02-01T14:58:18+01:00 Specialize: Add missing IdP annotations - - - - - 78cd7231 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Convert: Correct pass type - - - - - a2d0f590 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Warning free compilation - - - - - cd861cf3 by Alexander Biehl at 2018-02-01T14:58:18+01:00 hadock-2.19.0 / haddock-api-2.19.0 / haddock-library-1.5.0 - - - - - c6651b72 by Alexander Biehl at 2018-02-01T14:58:18+01:00 Adjust changelogs - - - - - 1e93da0b by Alexander Biehl at 2018-02-01T14:58:18+01:00 haddock-library: Info about breaking changes - - - - - f9b11db8 by Alec Theriault at 2018-02-02T12:36:02+01:00 Properly color pragma contents in hyperlinker The hyperlinker backend now classifies the content of pragmas as 'TkPragma'. That means that in something like '{-# INLINE foo #-}', 'foo' still gets classified as a pragma token. - - - - - c40b0043 by Alec Theriault at 2018-02-02T12:36:02+01:00 Support the new 'ITcolumn_prag' token - - - - - 4a2a4d39 by Alex Biehl at 2018-02-03T12:11:55+01:00 QuickJump: Mitigate encoding problems on Windows - - - - - bb34503a by Alex Biehl at 2018-02-04T18:39:31+01:00 Use withBinaryFile - - - - - 637605bf by Herbert Valerio Riedel at 2018-02-05T09:48:32+01:00 Try GHC 8.4.1 for Travis CI job - - - - - 7abb67e4 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 try harder to build w/ GHC 8.4.1 - - - - - 8255cc98 by Herbert Valerio Riedel at 2018-02-05T10:05:42+01:00 Add `SPDX-License-Identifier` as alised for "license" module header tokens C.f. SPDX 2.1 - Appendix V https://spdx.org/spdx-specification-21-web-version#h.twlc0ztnng3b The tag should appear on its own line in the source file, generally as part of a comment. SPDX-License-Identifier: <SPDX License Expression> Cherry-picked from haskell/haddock#743 - - - - - 267cd23d by Herbert Valerio Riedel at 2018-02-05T10:24:34+01:00 Make test-suite SMP compatible - - - - - 95d4bf40 by Alec Theriault at 2018-02-05T22:01:04+01:00 Hyperlink pattern synonyms and 'module' imports (#744) Links to pattern synonyms are now generated, as well as links from modules in import lists. Fixes haskell/haddock#731. - - - - - 67838dcd by Alec Theriault at 2018-02-06T08:23:36+01:00 Don't warn about missing '~' (#746) This manually filters out '~' from the list of things to warn about. It truly makes no sense to warn on this since '~' has nothing it could link to - it is magical. This fixes haskell/haddock#532. - - - - - ab6c3f9f by Alec Theriault at 2018-02-06T08:24:47+01:00 Don't barf on 'HsSpliceTy' (#745) This handles 'HsSpliceTy's by replacing them with what they expand to. IIUC everything that is happening, 'renameHsSpliceTy' should not be able to fail for the inputs we feed it from GHC. This fixes haskell/haddock#574. - - - - - 92bf95ad by Alex Biehl at 2018-02-06T08:28:23+01:00 Rename: renameHsSpliceTy ttg - - - - - 3130b1e1 by Alex Biehl at 2018-02-06T09:02:14+01:00 Expand SigDs - - - - - c72adae5 by Alex Biehl at 2018-02-06T09:20:51+01:00 fullModuleContents: support named docs - - - - - de2e4dbf by Alex Biehl at 2018-02-06T13:56:17+01:00 Hyperlinker: Also link pattern synonym arguments - - - - - b7c98237 by Alex Biehl at 2018-02-09T18:44:23+01:00 Expand SigD in a better place In https://github.com/haskell/haddock/issues/287 we found that haddock-2.19.0 would miss documentation on class methods with multiples names. This patch uses expandSigDecls in a more sensible place. - - - - - 8f598b27 by Alec Theriault at 2018-02-11T12:29:56+01:00 Add module tooltips to linked identifiers (#753) No more clicking to figure out whether your bytestring is strict or lazy! - - - - - d812e65d by Alec Theriault at 2018-02-11T12:31:44+01:00 Add 'show' option to complement 'hide' (#752) * Add 'show' option to complement 'hide' The behaviour is for flags passed in the command line to override flags in file headers. In the command line, later flags override earlier ones. Fixes haskell/haddock#751 and haskell/haddock#266. * Add a '--show-all' option - - - - - 6676cecb by Alex Biehl at 2018-02-18T11:07:15-05:00 QuickJump: Mitigate encoding problems on Windows (cherry picked from commit 86292c54bfee2343aee84559ec01f1fc68f52231) - - - - - e753dd88 by Alex Biehl at 2018-02-18T17:59:54+01:00 Use withBinaryFile - - - - - 724dc881 by Tamar Christina at 2018-02-19T05:34:49+01:00 Haddock: support splitted include paths. (#689) - - - - - 9b6d6f50 by Alex Biehl at 2018-02-19T05:57:02+01:00 Teach the HTML backend how to render methods with multiple names - - - - - a74aa754 by Alexander Biehl at 2018-02-19T10:04:34+01:00 Hoogle/Latex: Remove use of partial function - - - - - 66d8bb0e by Alec Theriault at 2018-02-25T16:04:01+01:00 Fix file handle leak (#763) (#764) Brought back some mistakenly deleted code for handling encoding and eager reading of files from e0ada1743cb722d2f82498a95b201f3ffb303137. - - - - - bb92d03d by Alex Biehl at 2018-03-02T14:21:23+01:00 Enable running test suite with stock haddock and ghc using ``` $ cabal new-run -- html-test --haddock-path=$(which haddock) --ghc-path=$(which ghc) ``` - - - - - dddb3cb2 by Alex Biehl at 2018-03-02T15:43:21+01:00 Make testsuite work with haddock-1.19.0 release (#766) - - - - - f38636ed by Alec Theriault at 2018-03-02T15:48:36+01:00 Support unicode operators, proper modules Unicode operators are a pretty big thing in Haskell, so supporting linking them seems like it outweighs the cost of the extra machinery to force Attoparsec to look for unicode. Fixes haskell/haddock#458. - - - - - 09d89f7c by Alec Theriault at 2018-03-02T15:48:43+01:00 Remove bang pattern - - - - - d150a687 by Alex Biehl at 2018-03-02T15:48:48+01:00 fix test - - - - - d6fd71a5 by Alex Biehl at 2018-03-02T16:22:38+01:00 haddock-test: Be more explicit which packages to pass We now pass `-hide-all-packages` to haddock when invoking the testsuite. This ensures we don't accidentally pick up any dependencies up through ghc.env files. - - - - - 0932c78c by Alex Biehl at 2018-03-02T17:50:38+01:00 Revert "fix test" This reverts commit 1ac2f9569242f6cb074ba6e577285a4c33ae1197. - - - - - 52516029 by Alex Biehl at 2018-03-02T18:16:50+01:00 Fix Bug548 for real - - - - - 89df9eb5 by Alex Biehl at 2018-03-05T18:28:19+01:00 Hyperlinker: Links for TyOps, class methods and associated types - - - - - d019a4cb by Ryan Scott at 2018-03-06T13:43:56-05:00 Updates for haskell/haddock#13324 - - - - - 6d5a42ce by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump haddock-2.19.0.1, haddock-api-2.19.0.1, haddock-library-1.5.0.1 - - - - - c0e6f380 by Alex Biehl at 2018-03-10T18:25:57+01:00 Update changelogs for haddock-2.19.0.1 and haddock-library-1.5.0.1 - - - - - 500da489 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Update to QC 2.11 - - - - - ce8362e9 by Herbert Valerio Riedel at 2018-03-10T18:25:57+01:00 Restore backward-compat with base-4.5 through base-4.8 - - - - - baae4435 by Alex Biehl at 2018-03-10T18:25:57+01:00 Bump lower bound for haddock-library - - - - - 10b7a73e by Alex Biehl at 2018-03-10T18:25:57+01:00 Haddock: Straighten out base bound - - - - - a6096f7b by Alex Biehl at 2018-03-13T08:45:06+01:00 extractDecl: Extract constructor patterns from data family instances (#776) * extractDecl: Allow extraction of data family instance constructors * extractDecl: extract data family instance constructors - - - - - ba4a0744 by Simon Jakobi at 2018-03-14T08:26:42+01:00 Readme: Update GHC version (#778) - - - - - 8de157d4 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for definition lists - - - - - 425b46f9 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for links - - - - - d53945d8 by Simon Jakobi at 2018-03-14T20:39:29+01:00 Add fixture test for inline links - - - - - f1dc7c99 by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Slightly unmangle output - - - - - 0879d31c by Simon Jakobi at 2018-03-14T20:39:29+01:00 fixtures: Prevent stdout buffering - - - - - 1f9e5f1b by Simon Jakobi at 2018-03-14T20:39:29+01:00 haddock-library.cabal: Clean up GHC options - - - - - 066b891a by Simon Jakobi at 2018-03-14T20:39:29+01:00 Make a proper definition for the <link> parser - - - - - 573d6ba7 by Alec Theriault at 2018-03-21T09:16:57+01:00 Show where instances are defined (#748) * Indicate source module of instances Above instance, we now also display a link to the module where the instance was defined. This is sometimes helpful in figuring out what to import. * Source module for type/data families too * Remove parens * Accept tests - - - - - 99b5d28b by Alex Biehl at 2018-03-21T09:20:36+01:00 Prepare changelog for next release - - - - - 482d3a93 by Alex Biehl at 2018-03-23T15:57:36+01:00 Useful cost centres, timers and allocation counters (#785) * Add some useful cost-centres for profiling * Add withTiming for each haddock phase Invoking haddock with `--optghc=-ddump-timings` now shows the amount of time spent and the number of allocated bytes for each phase. - - - - - 773b41bb by Alec Theriault at 2018-03-27T08:35:59+02:00 @since includes package name (#749) * Metadoc stores a package name This means that '@since' annotations can be package aware. * Get the package name the right way This should extract the package name for `@since` annotations the right way. I had to move `modulePackageInfo` around to do this and, in the process, I took the liberty to update it. Since it appears that finding the package name is something that can fail, I added a warning for this case. * Silence warnings * Hide package for local 'since' annotations As discussed, this is still the usual case (and we should avoid being noisy for it). Although this commit is large, it is basically only about threading a 'Maybe Package' from 'Haddock.render' all the way to 'Haddock.Backends.Xhtml.DocMarkup.renderMeta'. * Bump binary interface version * Add a '--since-qual' option This controls when to qualify since annotations with the package they come from. The default is always, but I've left an 'external' variant where only those annotations coming from outside of the current package are qualified. * Make ParserSpec work * Make Fixtures work * Use package name even if package version is not available The @since stuff needs only the package name passed in, so it makes sense to not be forced to pass in a version too. - - - - - e42c57bc by Alex Biehl at 2018-03-27T08:42:50+02:00 haddock-2.19.1, haddock-api-2.19.1, haddock-library-1.6.0 - - - - - 8373a529 by Alex Biehl at 2018-03-28T10:17:11+02:00 Bump haddock and haddock-api to 2.20.0 - - - - - 5038eddd by Jack Henahan at 2018-04-03T13:28:12+02:00 Clear search string on hide for haskell/haddock#781 (#789) - - - - - 920ca1eb by Alex Biehl at 2018-04-03T16:35:50+02:00 Travis: Build with ghc-8.4.2 (#793) - - - - - a232f0eb by Alan Zimmerman at 2018-04-07T14:14:32+02:00 Match changes in GHC for D4199 Removing HasSourceText and SourceTextX classes. - - - - - ab85060b by Alan Zimmerman at 2018-04-09T21:20:24+02:00 Match GHC changes for TTG - - - - - 739302b6 by Alan Zimmerman at 2018-04-13T13:31:44+02:00 Match GHC for TTG implemented on HsBinds, D4581 - - - - - 2f56d3cb by Ryan Scott at 2018-04-19T11:42:58-04:00 Bump upper bound on base to < 4.13 See https://ghc.haskell.org/trac/ghc/ticket/15018. - - - - - a49df92a by Alex Biehl at 2018-04-20T07:31:44+02:00 Don't treat fixity signatures like declarations - - - - - d02c103b by Ryan Scott at 2018-04-24T11:20:11-04:00 Add regression test for haskell/haddock#413 Fixes haskell/haddock#413. - - - - - c7577f52 by Ryan Scott at 2018-04-24T13:51:06-07:00 Improve the Hoogle backend's treatment of type families (#808) Fixes parts 1 and 2 of haskell/haddock#806. - - - - - d88f85b1 by Alec Theriault at 2018-04-25T11:24:07-07:00 Replace 'attoparsec' with 'parsec' (#799) * Remove attoparsec with parsec and start fixing failed parses * Make tests pass * Fix encoding issues The Haddock parser no longer needs to worry about bytestrings. All the internal parsing work in haddock-library happens over 'Text'. * Remove attoparsec vendor * Fix stuff broken in 'attoparsec' -> 'parsec' * hyperlinks * codeblocks * examples Pretty much all issues are due to attoparsec's backtracking failure behaviour vs. parsec's non-backtracking failure behaviour. * Fix small TODOs * Missing quote + Haddocks * Better handle spaces before/after paragraphs * Address review comments - - - - - fc25e2fe by Alan Zimmerman at 2018-04-27T15:36:53+02:00 Match changes in GHC for TTG - - - - - 06175f91 by Herbert Valerio Riedel at 2018-05-01T18:11:09+02:00 Merge branch 'ghc-head' with 'ghc-8.4' - - - - - 879caaa8 by Alec Theriault at 2018-05-07T18:53:15-07:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 3e0120cb by Simon Jakobi at 2018-05-07T19:00:18-07:00 Add docs for some DocH constructors (#814) - - - - - 0a32c6db by Alec Theriault at 2018-05-08T02:15:45-07:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 8816e783 by Simon Jakobi at 2018-05-08T10:48:11-07:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - ad60366f by Ryan Scott at 2018-05-10T11:19:47-04:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - 03b7cc3b by Ryan Scott at 2018-05-10T11:24:38-04:00 Wibbles - - - - - b03dd563 by Chaitanya Koparkar at 2018-05-10T11:44:58-04:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 9f298a40 by Ben Gamari at 2018-05-13T17:36:04-04:00 Account for refactoring of LitString - - - - - ea3dabe7 by Ryan Scott at 2018-05-16T09:21:43-04:00 Merge pull request haskell/haddock#826 from haskell/T825 Remove Hoogle backend hack that butchers infix datatype names - - - - - 0d234f7c by Alec Theriault at 2018-05-23T11:29:05+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 15fc9712 by Simon Jakobi at 2018-05-31T04:17:47+02:00 Adjust to new HsDocString internals - - - - - 6f1e19a8 by Ben Gamari at 2018-06-02T16:18:58-04:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 0d0355d9 by Ryan Scott at 2018-06-04T21:26:59-04:00 DerivingVia changes - - - - - 0d93475a by Simon Jakobi at 2018-06-05T19:47:05+02:00 Bump a few dependency bounds (#845) - - - - - 5cbef804 by Alec Theriault at 2018-06-05T19:47:16+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 9094c56f by Alec Theriault at 2018-06-05T22:53:25+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 70188719 by Simon Jakobi at 2018-06-08T22:20:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - 495cd1fc by Chaitanya Koparkar at 2018-06-13T23:01:34+02:00 Use the response file utilities defined in `base` (#821) Summary: The response file related modules were recently copied from `haddock` into `base`. This patch removes them from `haddock`. GHC Trac Issues: haskell/haddock#13896 - - - - - 81088732 by Ben Gamari at 2018-06-13T23:01:34+02:00 Account for refactoring of LitString - - - - - 7baf6587 by Simon Jakobi at 2018-06-13T23:05:08+02:00 Adjust to new HsDocString internals - - - - - bb61464d by Ben Gamari at 2018-06-13T23:05:22+02:00 Remove ParallelArrays and Data Parallel Haskell - - - - - 5d8cb87f by Ryan Scott at 2018-06-13T23:39:30+02:00 DerivingVia changes - - - - - 73d373a3 by Alec Theriault at 2018-06-13T23:39:30+02:00 Extract docs from strict/unpacked constructor args (#839) This fixes haskell/haddock#836. - - - - - 4865e254 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Remove `ITtildehsh` token - - - - - b867db54 by Alec Theriault at 2018-06-13T23:39:30+02:00 Filter out CRLFs in hyperlinker backend (#813) This prevents spurious lines from appearing in the final output. - - - - - 9598e392 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Add docs for some DocH constructors (#814) - - - - - 8a59035b by Alec Theriault at 2018-06-13T23:39:30+02:00 Remove 'TokenGroup' from Hyperlinker (#818) Since the hyperlinker backend now relies on the GHC tokenizer, something like 'Bar.Baz.foo' already gets bunched together into one token (as opposed to being spread across 'Bar', '.', 'Baz', '.', and 'foo'). - - - - - 29350fc8 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about out of scope identifiers. (#819) - - - - - 2590bbd9 by Ryan Scott at 2018-06-13T23:39:30+02:00 Remove Hoogle backend hack that butchers infix datatype names - - - - - a9939fdc by Ryan Scott at 2018-06-13T23:39:30+02:00 Wibbles - - - - - a22f7df4 by Alec Theriault at 2018-06-13T23:39:30+02:00 Use `ClassOpSig` instead of `TypeSig` for class methods (#835) * Fix minimal pragma handling Class declarations contain 'ClassOpSig' not 'Typesig'. This should fix haskell/haddock#834. * Accept html-test output - - - - - 8741015d by Simon Jakobi at 2018-06-13T23:39:30+02:00 Bump a few dependency bounds (#845) - - - - - 4791e1cc by Alec Theriault at 2018-06-13T23:39:30+02:00 Improve hyperlinker's 'spanToNewline' (#846) 'spanToNewline' is used to help break apart the source into lines which can then be partioned into CPP and non-CPP chunks. It is important that 'spanToNewline' not break apart tokens, so it needs to properly handle things like * block comments, possibly nested * string literals, possibly multi-line * CPP macros, possibly multi-line String literals in particular were not being properly handled. The fix is to to fall back in 'Text.Read.lex' to help lex things that are not comments. Fixes haskell/haddock#837. - - - - - 311d3216 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Renamer: Warn about ambiguous identifiers (#831) * Renamer: Warn about ambiguous identifiers Example: Warning: 'elem' is ambiguous. It is defined * in ‘Data.Foldable’ * at /home/simon/tmp/hdk/src/Lib.hs:7:1 You may be able to disambiguate the identifier by qualifying it or by hiding some imports. Defaulting to 'elem' defined at /home/simon/tmp/hdk/src/Lib.hs:7:1 Fixes haskell/haddock#830. * Deduplicate warnings Fixes haskell/haddock#832. - - - - - d0577817 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Complete FixitySig and FamilyDecl pattern matches - - - - - 055b3aa7 by Simon Jakobi at 2018-06-13T23:39:30+02:00 Fix redundant import warnings - - - - - f9ce19b1 by Simon Jakobi at 2018-06-13T23:49:52+02:00 html-test: Accept output - - - - - 04604ea7 by Simon Jakobi at 2018-06-13T23:54:37+02:00 Bump bounds on Cabal - - - - - 0713b692 by Simon Jakobi at 2018-06-14T00:00:12+02:00 Merge branch 'ghc-head' into ghc-head-update-3 - - - - - c6a56bfd by Simon Jakobi at 2018-06-14T02:33:27+02:00 Bump ghc bound for haddock-api spec test-suite - - - - - 119d04b2 by Simon Jakobi at 2018-06-14T12:37:48+02:00 Travis: `--allow-newer` for all packages - - - - - 0e876e2c by Alex Biehl at 2018-06-14T15:28:52+02:00 Merge pull request haskell/haddock#857 from sjakobi/ghc-head-update-3 Update ghc-head - - - - - 5be46454 by Alec Theriault at 2018-06-14T21:42:45+02:00 Improved handling of interfaces in 'haddock-test' (#851) This should now work with an inplace GHC where (for instance) HTML directories may not be properly recorded in the package DB. - - - - - 96ab1387 by Vladislav Zavialov at 2018-06-14T17:06:21-04:00 Handle -XStarIsType - - - - - e518f8c4 by Ben Gamari at 2018-06-14T17:48:00-04:00 Revert unintentional reversion of fix of haskell/haddock#548 - - - - - 01b9f96d by Alan Zimmerman at 2018-06-19T11:52:22+02:00 Match changes in GHC for haskell/haddock#14259 - - - - - 7f8c8298 by Ben Gamari at 2018-06-19T18:14:27-04:00 Bump GHC version to 8.6 - - - - - 11c6b5d2 by Ryan Scott at 2018-06-19T23:17:31-04:00 Remove HsEqTy and XEqTy - - - - - b33347c2 by Herbert Valerio Riedel at 2018-06-20T23:14:52+02:00 Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. - - - - - f0d2460e by Herbert Valerio Riedel at 2018-06-20T23:28:46+02:00 Update Travis CI job - - - - - ef239223 by Herbert Valerio Riedel at 2018-06-20T23:32:41+02:00 Drop GHC HEAD from CI and update GHC to 8.4.3 It's a waste of resource to even try to build this branch w/ ghc-head; so let's not do that... - - - - - 41c4a9fa by Ben Gamari at 2018-06-20T18:26:20-04:00 Bump GHC version to 8.7 - - - - - 8be593dc by Herbert Valerio Riedel at 2018-06-21T22:32:15+02:00 Update CI job to use GHC 8.7.* - - - - - b91d334a by Simon Jakobi at 2018-06-30T13:41:38+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section - - - - - f707d848 by Alec Theriault at 2018-07-05T10:43:35-04:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. - - - - - a6d2b8dc by Alec Theriault at 2018-07-06T10:06:32-04:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case - - - - - 13819f71 by Alan Zimmerman at 2018-07-15T19:33:51+02:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 - - - - - c346aa78 by Simon Jakobi at 2018-07-19T12:29:32+02:00 haddock-library: Bump bounds for containers - - - - - 722e733c by Simon Jakobi at 2018-07-19T13:36:45+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] - - - - - f0bd83fd by Alec Theriault at 2018-07-19T14:39:57+02:00 Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. - - - - - 394053a8 by Simon Jakobi at 2018-07-19T14:58:07+02:00 haddock-library: Bump bounds for containers - - - - - 1bda11a2 by Alec Theriault at 2018-07-20T09:04:03+02:00 Add HEAD.hackage overlay (#887) * Add HEAD.hackage overlay * Add HCPKG variable - - - - - c7b4ab45 by Alec Theriault at 2018-07-20T12:01:16+02:00 Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test - - - - - c05d32ad by Alec Theriault at 2018-07-20T12:01:49+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output - - - - - 24b39ee4 by Alec Theriault at 2018-07-20T12:02:16+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. - - - - - cb9d2099 by Simon Jakobi at 2018-07-20T13:39:29+02:00 README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) - - - - - 133f24f5 by Alec Theriault at 2018-07-20T13:39:29+02:00 Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) - - - - - 11024149 by Alec Theriault at 2018-07-20T13:39:29+02:00 Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) - - - - - de0c139e by Simon Jakobi at 2018-07-20T13:39:29+02:00 tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) - - - - - 6435e952 by Alec Theriault at 2018-07-20T13:39:29+02:00 Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) - - - - - 1461af39 by Alec Theriault at 2018-07-20T13:39:29+02:00 Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) - - - - - 69d3bde1 by Alec Theriault at 2018-07-20T13:49:47+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) - - - - - 6a5c73c7 by Alec Theriault at 2018-07-20T13:50:00+02:00 Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests - - - - - 92ca94c6 by Alec Theriault at 2018-07-20T13:55:36+02:00 Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) - - - - - 981bc7fa by Simon Jakobi at 2018-07-20T15:06:06+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers - - - - - 27e7c0c5 by Simon Jakobi at 2018-07-20T15:09:05+02:00 Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 49e1a415 by Simon Jakobi at 2018-07-20T16:02:02+02:00 Update the ghc-8.6 branch (#889) * Revert "Bump GHC version to 8.6" This was applied to the wrong branch; there's now a `ghc-8.6` branch; ghc-head is always supposed to point to GHC HEAD, i.e. an odd major version. The next version bump to `ghc-head` is supposed to go from e.g. 8.5 to 8.7 This reverts commit 5e3cf5d8868323079ff5494a8225b0467404a5d1. * README updates (#856) * README: Remove mentions of master branch * README: Add instructions for using html-test * README: Change command to run _all_ the testsuites * README: Add project overview section (cherry picked from commit 61d6f935da97eb96685f07bf385102c2dbc2a33c) * Export more fixities for Hoogle (#871) This exports fixities for more things, including class methods and type-level operators. (cherry picked from commit 88316b972e3d47197b1019111bae0f7f87275fce) * Avoid line breaks due to line length in Hoogle (#868) * Avoid line breaks due to line length in Hoogle Hoogle operates in a line-oriented fashion, so we should avoid ever breaking due to long lines. One way of doing this non-intrusively is to modify the 'DynFlags' that are threaded through the 'Hoogle' module (note this is anyways only passed through for use in the various 'showSDoc' functions). * Amend test case (cherry picked from commit 657b1b3d519545f8d4ca048c06210d6cbf0f0da0) * tyThingToLHsDecl: Preserve type synonyms that contain a forall (#880) * tyThingToLHsDecls: Preserve type synonyms that contain a forall Fixes haskell/haddock#879. * Add Note [Invariant: Never expand type synonyms] * Clarify Note [Invariant: Never expand type synonyms] (cherry picked from commit c3eb3f0581f69e816f9453b1747a9f2a3ba02bb9) * Fix HEAD html-test (#860) * Update tests for 'StarIsType' * Accept tests * Revert "Update tests for 'StarIsType'" This reverts commit 7f0c01383bbba6dc5af554ee82988d2cf44e407a. * Refactor handling of parens in types (#874) * Fix type parenthesization in Hoogle backend Ported the logic in the HTML and LaTeX backends for adding in parens into something top-level in 'GhcUtil'. Calling that from the Hoogle backend fixes haskell/haddock#873. * Remove parenthesizing logic from LaTeX and XHTML backends Now, the only times that parenthesis in types are added in any backend is through the explicit 'HsParTy' constructor. Precedence is also represented as its own datatype. * List out cases explicitly vs. catch-all * Fix printing of parens for QuantifiedConstraints The priority of printing 'forall' types was just one too high. Fixes haskell/haddock#877. * Accept HTML output for quantified contexts test * Preserve docs on type family instances (#867) * Preserve docs on type family instances The only problem was that the instance location was slightly off for type family instances. * Accept output (cherry picked from commit 133e9c2c168db19c1135479f7ab144c4e33af2a4) * Fix broken instance source links (#869) The problem manifests itself in instances that are defined in modules other than the module where the class is defined. The fix is just to thread through the 'Module' of the instance further along. Since orphan instances appear to already have been working, I didn't do anything there. (cherry picked from commit 2de7c2acf9b1ec85b09027a8bb58bf8512e91c05) * Add some more unicode related tests (#872) This has been fixed for sure ever since we switched from attoparsec to parsec. Parts of it may have been working before that, but there was a point where this would have failed (see haskell/haddock#191). A regression test never hurt anyone. :) (cherry picked from commit 5ec7715d418bfac0f26aec6039792a99a6e89370) * Misc tests (#858) * More tests * spliced types * constructor/pattern argument docs * strictness marks on fields with argument docs * latex test cases need seperate directory * Accept tests * Additional tests for the identifier parser (#816) * Add tests for the identifier parser * docs: Clarify how to delimit identifiers (cherry picked from commit 0861affeca4d72938f05a2eceddfae2c19199071) - - - - - 5ca14bed by Simon Jakobi at 2018-07-20T16:05:47+02:00 Revert "Revert "Bump GHC version to 8.6"" That commit didn't belong onto the ghc-8.6 branch. This reverts commit acbaef3b9daf1d2dea10017964bf886e77a8e967. - - - - - 2dd600dd by Simon Jakobi at 2018-07-20T16:18:21+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. - - - - - fceb2422 by Simon Jakobi at 2018-07-20T16:18:21+02:00 outOfScope: Recommend qualifying the identifier - - - - - acea5d23 by Simon Jakobi at 2018-07-20T16:19:35+02:00 outOfScope: Recommend qualifying the identifier (cherry picked from commit 73707ed58d879cc04cb644c5dab88c39ca1465b7) - - - - - 1a83ca55 by Simon Jakobi at 2018-07-20T16:19:35+02:00 Don't warn about ambiguous identifiers when the candidate names belong to the same type This also changes the defaulting heuristic for ambiguous identifiers. We now prefer local names primarily, and type constructors or class names secondarily. Partially fixes haskell/haddock#854. (cherry picked from commit d504a2864a4e1982e142cf88c023e7caeea3b76f) - - - - - 48374451 by Masahiro Sakai at 2018-07-20T17:06:42+02:00 Add # as a special character (#884) '#' has special meaning used for anchors and can be escaped using backslash. Therefore it would be nice to be listed as special characters. - - - - - 5e1a5275 by Alec Theriault at 2018-07-20T23:37:24+02:00 Let `haddock-test` bypass interface version check (#890) This means `haddock-test` might * crash during deserialization * deserialize incorrectly Still - it means things _might_ work where they were previously sure not to. - - - - - 27286754 by Yuji Yamamoto at 2018-07-23T08:16:01+02:00 Avoid "invalid argument (invalid character)" on non-unicode Windows (#892) Steps to reproduce and the error message ==== ``` > stack haddock basement ... snip ... Warning: 'A' is out of scope. Warning: 'haddock: internal error: <stdout>: commitBuffer: invalid argument (invalid character) ``` Environment ==== OS: Windows 10 ver. 1709 haddock: [HEAD of ghc-8.4 when I reproduce the error](https://github.com/haskell/haddock/commit/532b209d127e4cecdbf7e9e3dcf4f653a5605b5a). (I had to use this version to avoid another probrem already fixed in HEAD) GHC: 8.4.3 stack: Version 1.7.1, Git revision 681c800873816c022739ca7ed14755e85a579565 (5807 commits) x86_64 hpack-0.28.2 Related pull request ==== https://github.com/haskell/haddock/pull/566 - - - - - 6729d361 by Alec Theriault at 2018-07-23T13:52:56-07:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). - - - - - 8cf4e6b5 by Ryan Scott at 2018-07-27T11:28:03-04:00 eqTyCon_RDR now lives in TysWiredIn After GHC commit http://git.haskell.org/ghc.git/commit/f265008fb6f70830e7e92ce563f6d83833cef071 - - - - - 1ad251a6 by Alan Zimmerman at 2018-07-30T13:28:09-04:00 Match XFieldOcc rename in GHC Trac haskell/haddock#15386 (cherry picked from commit e3926b50ab8a7269fd6904b06e881745f08bc5d6) - - - - - 8aea2492 by Richard Eisenberg at 2018-08-02T10:54:17-04:00 Update against new HsImplicitBndrs - - - - - e42cada9 by Alec Theriault at 2018-08-04T17:51:30+02:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 0e852512 by Alex Biehl at 2018-08-06T13:04:02+02:00 Make --package-version optional for --hoogle generation (#899) * Make --package-version optional for --hoogle generation * Import mkVersion * It's makeVersion not mkVersion - - - - - d2abd684 by Noel Bourke at 2018-08-21T09:34:18+02:00 Remove unnecessary backslashes from docs (#908) On https://haskell-haddock.readthedocs.io/en/latest/markup.html#special-characters the backslash and backtick special characters showed up with an extra backslash before them – I think the escaping is not (or no longer) needed for those characters in rst. - - - - - 7a578a9e by Matthew Pickering at 2018-08-21T09:34:50+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - aa3d4db3 by Matthew Pickering at 2018-08-21T09:37:34+02:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 - - - - - ede91744 by Alec Theriault at 2018-08-21T09:42:52+02:00 Better test output when Haddock crashes on a test (#902) In particular: we report the tests that crashed seperately from the tests that produced incorrect output. In order for tests to pass (and exit 0), they must not crash and must produce the right output. - - - - - 4a872b84 by Guillaume Bouchard at 2018-08-21T09:45:57+02:00 Fix a typo (#878) - - - - - 4dbf7595 by Ben Sklaroff at 2018-08-21T12:04:09-04:00 Add ITcomment_line_prag token to Hyperlinker Parser This token is necessary for parsing #line pragmas inside nested comments. Reviewers: bgamari Reviewed By: bgamari Differential Revision: https://phabricator.haskell.org/D4935 - - - - - 9170b2a9 by Ben Gamari at 2018-08-21T17:55:15-04:00 Merge pull request haskell/haddock#893 from harpocrates/get-name-to-instances Accumulate explicitly which modules to load for 'attachInstances' - - - - - d57b57cc by Ben Gamari at 2018-08-21T17:59:13-04:00 Merge branch 'ghc-head' of github.com:haskell/haddock into ghc-head - - - - - 14601ca2 by Alec Theriault at 2018-08-21T19:09:37-04:00 Accumulate explicitly which modules to load for 'attachInstances' The old approach to fixing haskell/haddock#469, while correct, consumes a lot of memory. We ended up with a HUGE 'GblRdrEnv' in 'ic_rn_gbl_env'. However, 'getNameToInstancesIndex' takes that environment and compresses it down to a much smaller 'ModuleSet'. Now, we compute that 'ModuleSet' explicitly as we process modules. That way we can just tell 'getNameToInstancesIndex' what modules to load (instead of it trying to compute that information from the interactive context). (cherry picked from commit 5c7c596c51d69b92164e9ba920157b36ce2b2ec1) - - - - - 438c645e by Matthew Pickering at 2018-08-21T19:12:39-04:00 Load plugins when starting a GHC session (#905) Fixes haskell/haddock#900 (cherry picked from commit e6aa8fb47b9477cc5ef5e46097524fe83e080f6d) - - - - - a80c5161 by Alec Theriault at 2018-08-21T22:06:40-07:00 Better rendering of unboxed sums/tuples * adds space after/before the '#' marks * properly reify 'HsSumTy' in 'synifyType' - - - - - 88456cc1 by Alec Theriault at 2018-08-21T22:06:40-07:00 Handle promoted tuples in 'synifyType' When we have a fully applied promoted tuple, we can expand it out properly. - - - - - fd1c1094 by Alec Theriault at 2018-08-21T22:19:34-07:00 Accept test cases - - - - - 6e80d9e0 by Alec Theriault at 2018-08-21T22:24:03-07:00 Merge pull request haskell/haddock#914 from harpocrates/feature/unboxed-stuff Better rendering of unboxed sums, unboxed tuples, promoted tuples. - - - - - 181a23f1 by Ben Gamari at 2018-08-23T15:53:48-04:00 Merge remote-tracking branch 'origin/ghc-8.6' into ghc-8.6 - - - - - 3a18c1d8 by Alec Theriault at 2018-08-27T14:15:25-07:00 Properly synify promoted list types We reconstruct promoted list literals whenever possible. That means that 'synifyType' produces '[Int, Bool, ()] instead of (Int ': (() ': (Bool ': ([] :: [Type])))) - - - - - b4794946 by Alec Theriault at 2018-09-03T07:19:55-07:00 Only look at visible types when synifying a 'HsListTy' The other types are still looked at when considering whether to make a kind signature or not. - - - - - a231fce2 by Alec Theriault at 2018-09-03T07:38:10-07:00 Merge pull request haskell/haddock#922 from harpocrates/promoted-lists Properly synify promoted list types - - - - - 0fdf044e by Ningning Xie at 2018-09-15T10:25:58-04:00 Update according to GHC Core changes - - - - - 7379b115 by Ningning Xie at 2018-09-15T15:40:18-04:00 update dataFullSig to work with Co Quantification This should have been in the previous patch, but wasn't. - - - - - cf84a046 by Alec Theriault at 2018-09-17T20:12:18-07:00 Fix/add to various docs * Add documentation for a bunch of previously undocumented options (fixes haskell/haddock#870) * Extend the documentation of `--hoogle` considerably (see haskell/haddock#807) * Describe how to add docs to `deriving` clauses (fixes haskell/haddock#912) * Fix inaccurate docs about hyperlinking infix identifiers (fixes haskell/haddock#780) - - - - - ae017935 by Alec Theriault at 2018-09-22T08:32:16-07:00 Update Travis - - - - - d95ae753 by Alec Theriault at 2018-09-22T09:34:10-07:00 Accept failing tests Also silence orphan warnings. - - - - - f3e67024 by Alec Theriault at 2018-09-22T09:41:23-07:00 Bump haddock-api-2.21.0, haddock-library-1.7.0 * Update CHANGELOGS * Update new versions in Cabal files * Purge references to ghc-8.4/master branches in README - - - - - 3f136d4a by Alec Theriault at 2018-09-22T10:53:31-07:00 Turn haddock-library into a minor release Fix some version bounds in haddock-library too. - - - - - b9def006 by Alec Theriault at 2018-09-22T13:07:35-07:00 keep cabal.project file - - - - - 4909aca7 by Alec Theriault at 2018-10-16T09:36:30-07:00 Build on 7.4 and 7.8 - - - - - 99d20a28 by Herbert Valerio Riedel at 2018-10-16T18:45:52+02:00 Minor tweak to package description - - - - - a8059618 by Herbert Valerio Riedel at 2018-10-16T18:47:24+02:00 Merge pull request haskell/haddock#945 haddock-api 2.21.0 and haddock-library 1.6.1 release - - - - - 2d9bdfc1 by Alec Theriault at 2018-10-16T10:54:21-07:00 Bump haddock-library to 1.7.0 The 1.6.1 release should've been a major bump, since types in the `Documentation.Haddock.Parser.Monad` module changed. This version makes that module internal (as it morally should be). - - - - - ed340cef by Alec Theriault at 2018-10-16T14:59:13-07:00 Merge branch 'ghc-8.4' into ghc-8.6 - - - - - 2821a8df by Alec Theriault at 2018-10-16T15:14:48-07:00 Merge branch 'ghc-8.6' into ghc-head - - - - - a722dc84 by Alec Theriault at 2018-10-16T16:28:55-07:00 Latex type families (#734) * Support for type families in LaTeX The code is ported over from the XHTML backend. * Refactor XHTML and LaTeX family handling This is mostly a consolidation effort: stripping extra exports, inlining some short definitions, and trying to make the backends match. The LaTeX backend now has preliminary support for data families, although the only the data instance head is printed (not the actual constructors). Both backends also now use "newtype" for newtype data family instances. * Add some tests - - - - - 63377496 by Alec Theriault at 2018-10-16T16:39:07-07:00 Update changelog - - - - - 099a0110 by Alec Theriault at 2018-10-16T16:49:28-07:00 Merge pull request haskell/haddock#942 from harpocrates/update-docs Fix & add to documentation - - - - - 0927416f by Alec Theriault at 2018-10-16T16:50:14-07:00 Set UTF-8 encoding before writing files (#934) This should fix haskell/haddock#929, as well as guard against future problems of this sort in other places. Basically replaces 'writeFile' (which selects the users default locale) with 'writeUtf8File' (which always uses utf8). - - - - - 83b7b017 by Alec Theriault at 2018-10-16T17:42:05-07:00 Output pattern synonyms in Hoogle backend (#947) * Output pattern synonyms in Hoogle backend We were previously weren't outputting _any_ pattern synonyms, bundled or not. Now, we output both. Fixes haskell/haddock#946. * Update changelog - - - - - 81e5033d by Alec Theriault at 2018-10-16T18:04:40-07:00 Release `haddock{,-api}-2.22.0` This version will accompany ghc-8.6.2 - - - - - 9661744e by Alex Biehl at 2018-10-18T08:14:32-07:00 Add NewOcean theme And make it the default theme. - - - - - 7ae6d722 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Improve appearance and readability These changes include: - use latest Haskell's logo colors - decrease #content width to improve readability - use nicer font - improve sizes and distances - - - - - 37f8703d by NunoAlexandre at 2018-10-18T08:14:32-07:00 Include custom font in the html head - - - - - 1d5e1d79 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Update html test reference files - - - - - 53b7651f by NunoAlexandre at 2018-10-18T08:14:32-07:00 Make it responsive - It makes small screens taking more space than larger ones - fixes a few issues present in small screens currently - make it look good across different screen sizes. - - - - - 6aa1aeb1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make the style consistent with hackage Several things are addressed here: - better responsive behaviour on the header - better space usage - consistent colors overall - other nit PR comments - - - - - 3a250c5c by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Place the package name before the menu links This supports the expected responsive menu design, where the package name appears above the menu links. - - - - - cae699b3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update html-test reference files The package name element in the package-header is now a div instead of a paragraph, and it is now above the menu ul.links instead of below. - - - - - 2ec7fd2d by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve synopsis style and code - Use CSS3 instead of loading pictures to show "+" and "-" symbols - Drop redundant code - - - - - 0c874c01 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Decrease space between code blocks There was too much space between code blocks as pointed out by reviewers. - - - - - 85568ce2 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Add an initial-scale property to all haddock pages This solves an issue reported about the content looking incredibly small on mobile devices. - - - - - c1538926 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Address several PR comments - Darken text color like done for hackage - Move synopsis to left side - Make table of contents stick to the left on wide screens - Wrap links to avoid page overflow - Improve expand/collapse buttons - Fix issue with content size on mobile devices - Fix issue with font-size on landscape mode - Increase width of the content - Change colors of table of contents and synopsis - Etc - - - - - e6639e5f by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make synopsis scrollable on wide screens When the synopsis is longer than the screen, you can’t see its end and you can't scroll down either, making the content unreachable. - - - - - 1f0591ff by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve information density - Reduce font size - Improve space between and within code blocks - Improve alignments - Improve spacing within sub-blocks - - - - - bf083097 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Minor adjustments Bring in some adjustments made to hackage: - link colors - page header show everything when package title is too long - - - - - 10375fc7 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix responsive triggers overlap issue The min and max width triggers have the same values, which caused the style resolution to take an intersection of both style declarations when the screen resolution had the size of the limts (say 1280px), causing an odd behaviour and look. - - - - - 95ff2f95 by NunoAlexandre at 2018-10-18T08:14:32-07:00 Fix issue with menu alignment on firefox Reported and described here: https://github.com/haskell/haddock/pull/721#issuecomment-374668869 - - - - - dc86587e by Alex Biehl at 2018-10-18T08:14:32-07:00 Changelog entry for NewOcean - - - - - 27195e47 by Herbert Valerio Riedel at 2018-10-18T08:14:32-07:00 html-test --accept - - - - - 83f4f9c0 by Alex Biehl at 2018-10-18T08:14:32-07:00 Avoid name shadowing - - - - - 231487f1 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font to PT Sans Also migrate some general text related changes from hackage. - - - - - 313db81a by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Use 'flex' to fix header alignment - - - - - 5087367b by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Misc of tweaks - Update link colors to hackage scheme - Tune spacing between content elements - Update footer style - Fix and improve code blocks identation - - - - - b08020df by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update font in Xhtml.hs to PT Sans - - - - - 78ce06e3 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Improve code blocks styling - Fix and improve spacing - Improve colors and borders - - - - - 81262d20 by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Make package-header caption backward-compatible The current html generator of this branch wraps the package-header caption as a div, which does not work (without style adjustments) with the old themes. Changing it from div to span does the trick, without needing to adjust the old stylesheets. - - - - - dc4475cb by Nuno Alexandre at 2018-10-18T08:14:32-07:00 Update test-suite reference html pages - - - - - 393d35d8 by Alec Theriault at 2018-10-18T08:25:36-07:00 Accept tests - - - - - a94484ba by Alec Theriault at 2018-10-21T10:29:29-07:00 Fix CHANGELOG - - - - - 8797eca3 by Alec Theriault at 2018-10-21T10:36:19-07:00 Update 'data-files' to include NewOcean stuff - - - - - 1ae51e4a by Simon Jakobi at 2018-10-23T11:29:14+02:00 Fix typo in a warning - - - - - 009ad8e8 by Alec Theriault at 2018-10-24T12:47:47-07:00 Update JS dependencies This was done via `npm audit fix`. I think this fixes haskell/haddock#903 along with some more serious vulnerabilities that nobody seems to have noticed. - - - - - 051994db by Alec Theriault at 2018-10-24T17:31:09-07:00 Resurrect the style-switcher This fixes haskell/haddock#810. Looks like things were broken during the quickjump refactor of the JS. For the (git) record: I do not think the style switcher is a good idea. I'm fixing it for the same reason @mzero added it; as an answer to "rumblings from some that they didn't want their pixels changed on bit" - - - - - 2a1d620f by Alec Theriault at 2018-10-24T17:38:07-07:00 Fix copy-pasta error in data-files - - - - - ed5bfb7f by Alec Theriault at 2018-10-24T20:42:14-07:00 Fix the synopsis button Here's these changes are supposed to do: * put the synopsis back on the right side * properly have it on the edge of the screen on wide screens * adjust the background of the synopsis to match the button (otherwise the grey blends in with what is underneath) * get rid of the dotted purple line * the synopsis contents are now scrollable even when in wide screens (this has been a long-standing bug) - - - - - 883fd74b by Alec Theriault at 2018-10-25T20:16:46-07:00 Avoid more conflicts in generated ids (#954) This fixes haskell/haddock#953 by passing more names into the generated ids. - - - - - ea54e331 by Alec Theriault at 2018-10-25T21:07:12-07:00 Don't hide bullets in method docs I think thst CSS was meant only to deal with fields and the effect on bullets was accidental. Fixes haskell/haddock#926. - - - - - 9a14ef4a by Alec Theriault at 2018-10-25T22:02:07-07:00 Indent more things + slightly smaller font - - - - - b9f17e29 by Alec Theriault at 2018-10-25T22:10:01-07:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 096a3cfa by Alec Theriault at 2018-10-25T22:24:38-07:00 Accept HTML output - - - - - 2669517d by Alec Theriault at 2018-10-26T09:02:35-07:00 User manual + stuff for building GHC docs - - - - - 46b27687 by Alec Theriault at 2018-10-26T09:10:59-07:00 Make 'Contents' in NewOcean scrollable This only happens if the contents block on the left is so big that it doesn't fit (vertically) on the page. If that happens, we want it to be scrollable. - - - - - 3443dd94 by Alec Theriault at 2018-10-26T09:36:46-07:00 Revert "Make 'Contents' in NewOcean scrollable" This reverts commit f909ffd8353d6463fd5dd184998a32aa98d5c922. I missed the fact this also forces the 'Contents' to always go down to the bottom of the page. - - - - - ed081424 by Alec Theriault at 2018-10-26T14:22:23-07:00 Avoid some partiality AFAICT this wasn't causing any crashes, but that's mostly because we happen not to be forcing `pkgStr` when it would diverge. We come dangerously close to doing that in `ppHtmlIndex`. Fixes haskell/haddock#569. - - - - - 6a5bec41 by Alec Theriault at 2018-10-27T10:05:04-07:00 Fix documentation in `haddock-api` (#957) * Fix misplaced Haddocks in Haddock itself Haddock should be able to generate documentation for 'haddock-api' again. * Make CI check that documentation can be built. * Add back a doc that is OK - - - - - 5100450a by Matthew Yacavone at 2018-10-27T14:51:38-04:00 More explicit foralls (GHC Proposal 0007) - - - - - 8771a6b0 by Alec Theriault at 2018-11-05T13:58:11-08:00 Only run MathJax on entities with "mathjax" class (#960) Correspondingly, we wrap all inline/diplay math in <span class="mathjax"> ... the math .... </span> This fixes haskell/haddock#959. - - - - - bd7ff5c5 by Alec Theriault at 2018-11-05T15:54:22-08:00 Deduplicate some work in 'AttachInstances' Perf only change: * avoid needlessly union-ing maps * avoid synify-ing instances twice Took this opportunity to add some docs too - - - - - cf99fd8f by Alec Theriault at 2018-11-05T15:54:22-08:00 Specialize some SYB functions Perf only change: * Add a 'SPECIALIZE' pragma to help GHC optimize a 'Data a =>' constraint * Manually specialize the needlessly general type of 'specializeTyVarBndrs' - - - - - 4f91c473 by Alec Theriault at 2018-11-05T15:54:22-08:00 Improve perf of renaming Perf only change: * don't look up type variable names (they're never in the environment) * use a difference list for accumulating missing names * more efficient 'Functor'/'Applicative' instances for 'RnM' - - - - - 4bbab0d4 by Alec Theriault at 2018-11-05T15:54:22-08:00 Faster 'Text' driven parser combinators Perf only change: * use 'getParserState'/'setParserState' to make 'Text'-optimized parser combinators * minimize uses of 'Data.Text.{pack,unpack,cons,snoc}' - - - - - fa430c02 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support hyperlink labels with inline markup The parser for pictures hasn't been properly adjusted yet. - - - - - c1431035 by Alec Theriault at 2018-11-06T12:03:24-08:00 Support (and flatten) inline markup in image links Inline markup is supported in image links but, as per the [commonmark recommendation][0], it is stripped back to a plain text representation. [0]: https://spec.commonmark.org/0.28/#example-547 - - - - - d4ee1ba5 by Alec Theriault at 2018-11-06T12:03:24-08:00 Accept test case - - - - - 8088aeb1 by Alec Theriault at 2018-11-06T12:03:24-08:00 Fix/add to haddock-library test suite - - - - - e78f644d by Alec Theriault at 2018-11-06T13:26:31-08:00 Bump version bounds - - - - - 644335eb by Alec Theriault at 2018-11-06T13:53:30-08:00 Merge pull request haskell/haddock#875 from harpocrates/feature/markup-in-hyperlinks Inline markup in markdown-style links and images - - - - - e173ed0d by Alec Theriault at 2018-11-07T12:37:18-08:00 Fix issues around plus/minus * swap the minimize unicode to something more intuitive * use new unicode expander/collapser for instance lists * address some alignment issues in the "index" page - - - - - b2d92df7 by Alec Theriault at 2018-11-07T13:41:57-08:00 Allow "Contents" summary to scroll in a fixed div In the unfortunate event that the "Contents" summary doesn't fit vertically (like in the "Prelude"), it will be scrollable. - - - - - ca704c23 by Alec Theriault at 2018-11-07T13:45:15-08:00 Accept HTML output changes - - - - - 82c0ec6d by Alec Theriault at 2018-11-07T18:12:54-08:00 overflow-y 'scroll' -> 'auto' - - - - - 571d7657 by Alec Theriault at 2018-11-08T19:44:12-08:00 Clicking on "Contents" navigates to top of page - - - - - 8065a012 by Alec Theriault at 2018-11-08T19:44:17-08:00 Space out functions more Also, functions and data decls now have the same space before and after them. - - - - - cc650ede by Alec Theriault at 2018-11-09T08:13:35-08:00 Merge branch 'ghc-8.6' into wip/new-ocean - - - - - 65f8c17f by Alec Theriault at 2018-11-10T14:04:06-08:00 Update changelog - - - - - 20473847 by Alec Theriault at 2018-11-10T14:21:40-08:00 Replace oplus/ominus expander/collapser icons with triangles - - - - - 16592957 by Alec Theriault at 2018-11-10T14:35:10-08:00 Merge pull request haskell/haddock#949 from haskell/wip/new-ocean Introduce NewOcean theme. - - - - - 357cefe1 by Alec Theriault at 2018-11-10T16:02:13-08:00 Merge branch 'ghc-8.6' into ghc-head - - - - - de612267 by Alec Theriault at 2018-11-11T20:01:21-08:00 Rename 'NewOcean' theme to 'Linuwial' - - - - - 954b5baa by Alec Theriault at 2018-11-12T08:33:18-08:00 Add blockquote styling Matches b71da1feabf33efbbc517ac376bb690b5a604c2f from hackage-server. Fixes haskell/haddock#967. - - - - - d32c0b0b by Fangyi Zhou at 2018-11-12T10:24:13-08:00 Fix some broken links (#15733) Summary: For links in subpackages as well. https://phabricator.haskell.org/D5257 Test Plan: Manually verify links Reviewers: mpickering, bgamari, osa1 Reviewed By: osa1 GHC Trac Issues: haskell/haddock#15733 Differential Revision: https://phabricator.haskell.org/D5262 - - - - - 41098b1f by Alp Mestanogullari at 2018-11-15T22:40:09+01:00 Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change It got introduced in ghc/ghc at ae2c9b40f5b6bf272251d1f4107c60003f541b62. - - - - - c5c1c7e0 by Alec Theriault at 2018-11-15T13:48:13-08:00 Merge pull request haskell/haddock#970 from alpmestan/alp/fix-promotionflag Follow GHC HEAD's HsTypes.Promoted -> BasicTypes.PromotionFlag change - - - - - 6473d3a4 by Shayan-Najd at 2018-11-23T01:38:49+01:00 [TTG: Handling Source Locations] Foundation and Pat Trac Issues haskell/haddock#15495 This patch removes the ping-pong style from HsPat (only, for now), using the plan laid out at https://ghc.haskell.org/trac/ghc/wiki/ImplementingTreesThatGrow/HandlingSourceLocations (solution A). - the class `HasSrcSpan`, and its functions (e.g., `cL` and `dL`), are introduced - some instances of `HasSrcSpan` are introduced - some constructors `L` are replaced with `cL` - some patterns `L` are replaced with `dL->L` view pattern - some type annotation are necessarily updated (e.g., `Pat p` --> `Pat (GhcPass p)`) - - - - - 7a088dfe by Alec Theriault at 2018-11-26T11:11:28-08:00 More uniform handling of `forall`'s in HTML/LaTeX * don't forget to print explicit `forall`'s when there are arg docs * when printing an explicit `forall`, print all tyvars Fixes haskell/haddock#973 - - - - - d735e570 by Alec Theriault at 2018-12-12T08:42:09-08:00 Fix warnings, accept output * remove redundant imports (only brought to light due to recent work for improving redundant import detection) * fix a bug that was casuing exports to appear in reverse order * fix something in haddock-library that prevented compilation on old GHC's - - - - - a3852f8a by Zejun Wu at 2018-12-14T09:37:47-05:00 Output better debug infromation on internal error in extractDecl This will make investigation of haskell/haddock#979 easier - - - - - 2eccb5b9 by Alec Theriault at 2018-12-17T09:25:10-05:00 Refactor names + unused functions (#982) This commit should not introduce any change in functionality! * consistently use `getOccString` to convert `Name`s to strings * compare names directly when possible (instead of comparing strings) * get rid of unused utility functions - - - - - e82e4df8 by Alec Theriault at 2018-12-20T16:16:30-05:00 Load plugins when compiling each module (#983) * WIP: Load (typechecker) plugins from language pragmas * Revert "Load plugins when starting a GHC session (#905)" This reverts commit 72d82e52f2a6225686d9668790ac33c1d1743193. * Simplify plugin initialization code - - - - - 96e86f38 by Alec Theriault at 2018-12-23T10:23:20-05:00 Properly synify and render promoted type variables (#985) * Synify and render properly promoted type variables Fixes haskell/haddock#923. * Accept output - - - - - 23343345 by Alec Theriault at 2018-12-27T16:39:38-05:00 Remove `haddock-test`'s dep. on `syb` (#987) The functionality is easily inlined into one short function: `gmapEverywhere`. This doesn't warrant pulling in another package. - - - - - d0734f21 by Alec Theriault at 2018-12-27T16:39:52-05:00 Address deprecation warnings in `haddock-test` (#988) Fixes haskell/haddock#885. - - - - - 4d9f144e by mynguyen at 2018-12-30T23:42:26-05:00 Visible kind application haddock update - - - - - ffe0e9ed by Alec Theriault at 2019-01-07T13:55:22-08:00 Print kinded tyvars in constructors for Hoogle (#993) Fixes haskell/haddock#992 - - - - - 2e18b55d by Alec Theriault at 2019-01-10T16:42:45-08:00 Accept new output `GHC.Maybe` -> `Data.Maybe` (#996) Since 53874834b779ad0dfbcde6650069c37926da1b79 in GHC, "GHC.Maybe" is marked as `not-home`. That changes around some test output. - - - - - 055da666 by Gabor Greif at 2019-01-22T14:41:51+01:00 Lone typofix - - - - - 01bb71c9 by Alec Theriault at 2019-01-23T11:46:46-08:00 Keep forall on H98 existential data constructors (#1003) The information about whether or not there is a source-level `forall` is already available on a `ConDecl` (as `con_forall`), so we should use it instead of always assuming `False`! Fixes haskell/haddock#1002. - - - - - f9b9bc0e by Ryan Scott at 2019-01-27T09:28:12-08:00 Fix haskell/haddock#1004 with a pinch of dropForAlls - - - - - 5cfcdd0a by Alec Theriault at 2019-01-28T16:49:57-08:00 Loosen 'QuickCheck' and 'hspec' bounds It looks like the new versions don't cause any breakage and loosening the bounds helps deps fit in one stack resolver. - - - - - 3545d3dd by Alec Theriault at 2019-01-31T01:37:25-08:00 Use `.hie` files for the Hyperlinker backend (#977) # Summary This is a large architectural change to the Hyperlinker. * extract link (and now also type) information from `.hie` instead of doing ad-hoc SYB traversals of the `RenamedSource`. Also adds a superb type-on-hover feature (#715). * re-engineer the lexer to avoid needless string conversions. By going directly through GHC's `P` monad and taking bytestring slices, we avoid a ton of allocation and have better handling of position pragmas and CPP. In terms of performance, the Haddock side of things has gotten _much_ more efficient. Unfortunately, much of this is cancelled out by the increased GHC workload for generating `.hie` files. For the full set of boot libs (including `ghc`-the-library) * the sum of total time went down by 9-10% overall * the sum of total allocations went down by 6-7% # Motivation Haddock is moving towards working entirely over `.hi` and `.hie` files. This change means we no longer need the `RenamedSource` from `TypecheckedModule` (something which is _not_ in `.hi` files). # Details Along the way a bunch of things were fixed: * Cross package (and other) links are now more reliable (#496) * The lexer tries to recover from errors on every line (instead of at CPP boundaries) * `LINE`/`COLUMN` pragmas are taken into account * filter out zero length tokens before rendering * avoid recomputing the `ModuleName`-based `SrcMap` * remove the last use of `Documentation.Haddock.Utf8` (see haskell/haddock#998) * restructure temporary folder logic for `.hi`/`.hie` model - - - - - 2ded3359 by Herbert Valerio Riedel at 2019-02-02T12:06:12+01:00 Update/modernise haddock-library.cabal file - - - - - 62b93451 by Herbert Valerio Riedel at 2019-02-02T12:19:31+01:00 Tentatively declare support for unreleased base-4.13/ghc-8.8 - - - - - 6041e767 by Herbert Valerio Riedel at 2019-02-02T16:04:32+01:00 Normalise LICENSE text w/ cabal's BSD2 template Also, correct the `.cabal` files to advertise `BSD2` instead of the incorrect `BSD3` license. - - - - - 0b459d7f by Alec Theriault at 2019-02-02T18:06:12-08:00 CI: fetch GHC from validate artifact Should help make CI be less broken - - - - - 6b5c07cf by Alec Theriault at 2019-02-02T18:06:12-08:00 Fix some Hyperlinker test suite fallout * Amend `ParserSpec` to match new Hyperlinker API - pass in compiler info - strip out null tokens * Make `hypsrc-test` pass reliably - strip out `local-*` ids - strip out `line-*` ids from the `ClangCppBug` test - re-accept output - - - - - ded34791 by Nathan Collins at 2019-02-02T18:31:23-08:00 Update README instructions for Stack No need to `stack install` Haddock to test it. Indeed, `stack install` changes the `haddock` on user's `PATH` if `~/.local/bin` is on user's `PATH` which may not be desirable when hacking on Haddock. - - - - - 723298c9 by Alec Theriault at 2019-02-03T09:11:05-08:00 Remove `Documentation.Haddock.Utf8` The circumstances under which this module appeared are completely gone. The Hyperlinker backend no longer needs this module (it uses the more efficient `Encoding` module from `ghc`). Why no deprecation? Because this module really shouldn't exist! - It isn't used in `haddock-library`/`haddock-api` anymore - It was copy pasted directly from `utf8-string` - Folks seeking a boot-lib only solution can use `ghc`'s `Encoding` - - - - - 51050006 by Alec Theriault at 2019-02-03T22:58:58-08:00 Miscellaneous improvements to `Convert` (#1020) Now that Haddock is moving towards working entirely over `.hi` and `.hie` files, all declarations and types are going to be synthesized via the `Convert` module. In preparation for this change, here are a bunch of fixes to this module: * Add kind annotations to type variables in `forall`'s whose kind is not `Type`, unless the kind can be inferred from some later use of the variable. See `implicitForAll` and `noKindTyVars` in particular if you wish to dive into this. * Properly detect `HsQualTy` in `synifyType`. This is done by following suit with what GHC's `toIfaceTypeX` does and checking the first argument of `FunTy{} :: Type` to see if it classified as a given/wanted in the typechecker (see `isPredTy`). * Beef up the logic around figuring out when an explicit `forall` is needed. This includes: observing if any of the type variables will need kind signatures, if the inferred type variable order _without_ a forall will still match the one GHC claims, and some other small things. * Add some (not yet used) functionality for default levity polymorphic type signatures. This functionality similar to `fprint-explicit-runtime-reps`. Couple other smaller fixes only worth mentioning: * Show the family result signature only when it isn't `Type` * Fix rendering of implicit parameters in the LaTeX and Hoogle backends * Better handling of the return kind of polykinded H98 data declarations * Class decls produced by `tyThingToLHsDecl` now contain associated type defaults and default method signatures when appropriate * Filter out more `forall`'s in pattern synonyms - - - - - 841980c4 by Oleg Grenrus at 2019-02-04T08:44:25-08:00 Make a fixture of weird parsing of lists (#997) The second example is interesting. If there's a list directly after the header, and that list has deeper structure, the parser is confused: It finds two lists: - One with the first nested element, - everything after it I'm not trying to fix this, as I'm not even sure this is a bug, and not a feature. - - - - - 7315c0c8 by Ryan Scott at 2019-02-04T12:17:56-08:00 Fix haskell/haddock#1015 with dataConUserTyVars (#1022) The central trick in this patch is to use `dataConUserTyVars` instead of `univ_tvs ++ ex_tvs`, which displays the foralls in a GADT constructor in a way that's more faithful to how the user originally wrote it. Fixes haskell/haddock#1015. - - - - - ee0b49a3 by Ryan Scott at 2019-02-04T15:25:17-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. - - - - - 1c850dc8 by Alan Zimmerman at 2019-02-05T21:54:18+02:00 Matching changes in GHC for haskell/haddock#16236 - - - - - ab03c38e by Simon Marlow at 2019-02-06T08:07:33+00:00 Merge pull request haskell/haddock#1014 from hvr/pr/bsd2-normalise Normalise LICENSE text w/ cabal's BSD2 template - - - - - 5a92ccae by Alec Theriault at 2019-02-10T06:21:55-05:00 Merge remote-tracking branch 'gitlab/wip/T16236-2' into ghc-head - - - - - c0485a1d by Alec Theriault at 2019-02-10T03:32:52-08:00 Removes `haddock-test`s dependency on `xml`/`xhtml` (#1027) This means that `html-test`, `latex-test`, `hoogle-test`, and `hypsrc-test` now only depend on GHC boot libs. So we should now be able to build and run these as part of GHC's testsuite. \o/ The reference output has changed very slightly, in three ways: * we don't convert quotes back into `&quot;` as the `xml` lib did * we don't add extra `&nbsp;` as the `xml` lib did * we now remove the entire footer `div` (instead of just emptying it) - - - - - 65a448e3 by Alec Theriault at 2019-02-11T12:27:41-05:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - 360ca937 by Alec Theriault at 2019-02-13T11:36:11-05:00 Clean up logic for guessing `-B` and `--lib` (#1026) Haddock built with the `in-ghc-tree` flag tries harder to find the GHC lib folder and its own resources. This should make it possible to use `in-ghc-tree`-built Haddock without having to specify the `-B` and `--lib` options (just how you can use in-tree GHC without always specifying the `-B` option). The logic to do this relies on `getExecutablePath`, so we only get this auto-detection on platforms where this function works. - - - - - d583e364 by Alec Theriault at 2019-02-16T10:41:22-05:00 Fix tests broken by GHC Changes in 19626218566ea709b5f6f287d3c296b0c4021de2 affected some of the hyperlinker output. Accepted the new output (hovering over a `..` now shows you what that wildcard binds). Also fixed some stray deprecation warnings. - - - - - da0c42cc by Vladislav Zavialov at 2019-02-17T11:39:19+03:00 Parser changes to match !380 - - - - - ab96bed7 by Ryan Scott at 2019-02-18T04:44:08-05:00 Bump ghc version to 8.9 - - - - - 44b7c714 by Alec Theriault at 2019-02-22T05:49:43-08:00 Match GHC changes for T16185 `FunTy` now has an `AnonArgFlag` that indicates whether the arrow is a `t1 => t2` or `t1 -> t2`. This commit shouldn't change any functionality in Haddock. - - - - - 2ee653b1 by Alec Theriault at 2019-02-24T18:53:33-08:00 Update .travis.yml Points to the new GHC CI artifact. - - - - - 90939d71 by Alec Theriault at 2019-02-25T00:42:41-08:00 Support value/type namespaces on identifier links Identifier links can be prefixed with a 'v' or 't' to indicate the value or type namespace of the desired identifier. For example: -- | Some link to a value: v'Data.Functor.Identity' -- -- Some link to a type: t'Data.Functor.Identity' The default is still the type (with a warning about the ambiguity) - - - - - d6ed496c by Alec Theriault at 2019-02-25T00:42:46-08:00 Better identifier parsing * '(<|>)' and '`elem`' now get parsed and rendered properly as links * 'DbModule'/'DbUnitId' now properly get split apart into two links * tuple names now get parsed properly * some more small niceties... The identifier parsing code is more precise and more efficient (although to be fair: it is also longer and in its own module). On the rendering side, we need to pipe through information about backticks/parens/neither all the way through from renaming to the backends. In terms of impact: a total of 35 modules in the entirety of the bootlib + ghc lib docs change. The only "regression" is things like '\0'. These should be changed to @\\0@ (the path by which this previously worked seems accidental). - - - - - 3c3b404c by Alec Theriault at 2019-02-25T22:12:11-08:00 Fix standalone deriving docs Docs on standalone deriving decls for classes with associated types should be associated with the class instance, not the associated type instance. Fixes haskell/haddock#1033 - - - - - d51ef69e by Alec Theriault at 2019-02-26T19:14:59-08:00 Fix bogus identifier defaulting This avoids a situation in which an identifier would get defaulted to a completely different identifier. Prior to this commit, the 'Bug1035' test case would hyperlink 'Foo' into 'Bar'! Fixes haskell/haddock#1035. - - - - - 88cbbdc7 by Ryan Scott at 2019-02-27T10:14:03-05:00 Visible dependent quantification (#16326) changes - - - - - 0dcf6cee by Xia Li-yao at 2019-02-27T21:53:27-05:00 Menu item controlling which instances are expanded/collapsed (#1007) Adds a menu item (like "Quick Jump") for options related to displaying instances. This provides functionality for: * expanding/collapsing all instances on the currently opened page * controlling whether instances are expanded/collapsed by default * controlling whether the state of instances should be "remembered" This new functionality is implemented in Typescript in `details-helper`. The built-in-themes style switcher also got a revamp so that all three of QuickJump, the style switcher, and instance preferences now have the same style and implementation structure. See also: https://mail.haskell.org/pipermail/haskell-cafe/2019-January/130495.html Fixes haskell/haddock#698. Co-authored-by: Lysxia <lysxia at gmail.com> Co-authored-by: Nathan Collins <conathan at galois.com> - - - - - 3828c0fb by Alec Theriault at 2019-02-28T12:42:49-05:00 `--show-interface` should output to stdout. (#1040) Fixes haskell/haddock#864. - - - - - a50f4cda by gbaz at 2019-03-01T07:43:16-08:00 Increase contrast of Linuwal theme (#1037) This is to address the concern that, on less nice and older screens, some of the shades of grey blend in too easily with the white background. * darken the font slightly * darken slightly the grey behind type signatures and such * add a border and round the corners on code blocks * knock the font down by one point - - - - - ab4d41de by Alec Theriault at 2019-03-03T09:23:26-08:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 12f509eb by Ben Gamari at 2019-03-04T22:13:20-05:00 Remove reference to Opt_SplitObjs flag Split-objects has been removed. - - - - - 5b3e4c9a by Ryan Scott at 2019-03-06T19:16:24-05:00 Update html-test output to reflect haskell/haddock#16391 changes - - - - - fc228af1 by Alec Theriault at 2019-03-09T08:29:23-08:00 Match changes for "Stop inferring over-polymorphic kinds" The `hsq_ext` field of `HsQTvs` is now just the implicit variables (instead of also including information about which of these variables are dependent). This commit shouldn't change any functionality in Haddock. - - - - - 6ac109eb by Alec Theriault at 2019-03-09T11:22:55-08:00 Add .hi, .dyn_hi, etc files to .gitignore Fixes haskell/haddock#1030. - - - - - b55f0c05 by Alec Theriault at 2019-03-09T11:22:55-08:00 Better support for default methods in classes * default methods now get rendered differently * default associated types get rendered * fix a forgotten `s/TypeSig/ClassOpSig/` refactor in LaTeX backend * LaTeX backend now renders default method signatures NB: there is still no way to document default class members and the NB: LaTeX backend still crashes on associated types - - - - - 10aea0cf by Alec Theriault at 2019-03-09T11:22:55-08:00 Avoid multi-line `emph` in LaTeX backend `markupWarning` often processes inputs which span across paragraphs. Unfortunately, LaTeX's `emph` is not made to handle this (and will crash). Fixes haskell/haddock#936. - - - - - d22dc2c9 by Alec Theriault at 2019-03-09T11:22:55-08:00 Many LaTeX backend fixes After this commit, we can run with `--latex` on all boot libraries without crashing (although the generated LaTeX still fails to compile in a handful of larger packages like `ghc` and `base`). * Add newlines after all block elements in LaTeX. This is important to prevent the final output from being more an more indented. See the `latext-test/src/Example` test case for a sample of this. * Support associated types in class declarations (but not yet defaults) * Several small issues for producing compiling LaTeX; - avoid empy `\haddockbeginargs` lists (ex: `type family Any`) - properly escape identifiers depending on context (ex: `Int#`) - add `vbox` around `itemize`/`enumerate` (so they can be in tables) * Several spacing fixes: - limit the width of `Pretty`-arranged monospaced code - cut out extra space characters in export lists - only escape spaces if there are _multiple_ spaces - allow type signatures to be multiline (even without docs) * Remove uninteresting and repetitive `main.tex`/`haddock.sty` files from `latex-test` test reference output. Fixes haskell/haddock#935, haskell/haddock#929 (LaTeX docs for `text` build & compile) Fixes haskell/haddock#727, haskell/haddock#930 (I think both are really about type families...) - - - - - 0e6cee00 by Alec Theriault at 2019-03-29T12:11:56-07:00 Remove workaround for now-fixed Clang CPP bug (#1028) Before LLVM 6.0.1 (or 10.0 on Apple LLVM), there was a bug where lines that started with an octothorpe but turned out not to lex like pragmas would have an extra line added after them. Since this bug has been fixed upstream and that it doesn't have dire consequences anyways, the workaround is not really worth it anymore - we can just tell people to update their clang version (or re-structure their pragma code). - - - - - ce05434d by Alan Zimmerman at 2019-03-29T12:12:11-07:00 Matching changes in GHC for haskell/haddock#16236 (cherry picked from commit 3ee6526d4ae7bf4deb7cd1caf24b3d7355573576) - - - - - d85766b2 by Ben Gamari at 2019-03-29T12:14:04-07:00 Bump GHC to 8.8 - - - - - 5a82cbaf by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Redo ParseModuleHeader - - - - - b9033348 by Oleg Grenrus at 2019-05-05T13:02:00-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - bb55c8f4 by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove outdated `.ghci` files and `scripts` The `.ghci` files are actively annoying when trying to `cabal v2-repl`. As for the `scripts`, the distribution workflow is completely different. - - - - - 5ee244dc by Alec Theriault at 2019-05-13T16:10:07-07:00 Remove obsolete arcanist files + STYLE Now that GHC is hosted on Gitlab, the arcanist files don't make sense anymore. The STYLE file contains nothing more than a dead link too. - - - - - d07c1928 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Redo ParseModuleHeader - - - - - 492762d2 by Oleg Grenrus at 2019-05-13T16:41:43-07:00 Comment C, which clarifies why e.g. ReadP is not enough - - - - - af2ac773 by Ryan Scott at 2019-05-14T17:22:13-04:00 Changes for haskell/haddock#16110/#16356 - - - - - 6820ed0d by Alec Theriault at 2019-05-17T08:51:27-07:00 Unbreak haskell/haddock#1004 test case `fail` is no longer part of `Monad`. - - - - - 6bf7be98 by Alec Theriault at 2019-05-17T08:51:27-07:00 Fix haskell/haddock#1063 with better parenthesization logic for contexts The only other change in html/hoogle/hyperlinker output for the boot libraries that this caused is a fix to some Hoogle output for implicit params. ``` $ diff -r _build/docs/ old_docs diff -r _build/docs/html/libraries/base/base.txt old_docs/html/libraries/base/base.txt 13296c13296 < assertError :: (?callStack :: CallStack) => Bool -> a -> a --- > assertError :: ?callStack :: CallStack => Bool -> a -> a ``` - - - - - b5716b61 by Ryan Scott at 2019-05-22T17:24:32-04:00 Match changes with haskell/haddock#14332 - - - - - c115abf6 by Alec Theriault at 2019-05-26T16:01:58-04:00 Remove Haddock's dependency on `Cabal` At this point, Haddock depended on Cabal-the-library solely for a verbosity parser (which misleadingly accepts all sorts of verbosity options that Haddock never uses). Now, the only dependency on Cabal is for `haddock-test` (which uses Cabal to locate the Haddock interface files of a couple boot libraries). - - - - - e5b2d4a3 by Alec Theriault at 2019-05-26T16:16:25-04:00 Regression test: promoted lists in associated types When possible, associated types with promoted lists should use the promoted list literal syntax (instead of repeated applications of ': and '[]). This was fixed in 2122de5473fd5b434af690ff9ccb1a2e58491f8c. Closes haskell/haddock#466, - - - - - cc5ad5d3 by Alec Theriault at 2019-05-26T17:55:54-04:00 Merge branch 'ghc-8.6' into ghc-8.8 - - - - - 4b3301a6 by Alec Theriault at 2019-05-26T17:57:52-04:00 Release haddock-2.23, haddock-library-1.8.0 Tentatively adjust bounds and changelogs for the release to be bundled with GHC 8.8.1. - - - - - 69c7cfce by Matthew Pickering at 2019-05-30T10:54:27+01:00 Update hyperlinker tests for new types in .hie files - - - - - 29b7e738 by Zubin Duggal at 2019-05-30T10:57:51+01:00 update for new way to store hiefile headers - - - - - aeca5d5f by Zubin Duggal at 2019-06-04T18:57:42-04:00 update for new way to store hiefile headers - - - - - ba2ca518 by Ben Gamari at 2019-06-07T23:11:14+00:00 Update test output for introduction of Safe-Inferred - - - - - 3a975a6c by Ryan Scott at 2019-07-03T12:06:27-04:00 Changes for haskell/haddock#15247 - - - - - 0df46555 by Zubin Duggal at 2019-07-22T10:52:50+01:00 Fix haddockHypsrcTest - - - - - 2688686b by Sylvain Henry at 2019-09-12T23:19:39+02:00 Fix for GHC module renaming - - - - - 9ec0f3fc by Alec Theriault at 2019-09-20T03:21:00-04:00 Fix Travis CI, loosen .cabal bounds (#1089) Tentatively for the 2.23 release: * updated Travis CI to work again * tweaked bounds in the `.cabal` files * adjusted `extra-source-files` to properly identify test files - - - - - ca559beb by Matthías Páll Gissurarson at 2019-09-28T12:14:40-04:00 Small change in to facilitate extended typed-holes (#1090) This change has no functional effect on haddock itself, it just changes one pattern to use `_ (` rather than `_(`, so that we may use `_(` as a token for extended typed-holes later. - - - - - 02e28976 by Vladislav Zavialov at 2019-09-28T12:17:45-04:00 Remove spaces around @-patterns (#1093) This is needed to compile `haddock` when [GHC Proposal haskell/haddock#229](https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0229-whitespace-bang-patterns.rst) is implemented. - - - - - 83cbbf55 by Alexis King at 2019-09-30T21:12:42-04:00 Fix the ignore-exports option (#1082) The `ignore-exports` option has been broken since haskell/haddock#688, as mentioned in https://github.com/haskell/haddock/pull/766#issue-172505043. This PR fixes it. - - - - - e127e0ab by Ben Gamari at 2019-10-06T15:12:06-04:00 Fix a few haddock issues - - - - - 3a0f5c89 by Zubin Duggal at 2019-10-07T17:56:13-04:00 Fix crash when there are no srcspans in the file due to CPP - - - - - 339c5ff8 by Alec Theriault at 2019-10-07T17:56:13-04:00 Prefer un-hyperlinked sources to no sources It is possible to fail to extract an HIE ast. This is however not a reason to produce _no_ output - we should still make a colorized HTML page. - - - - - d47ef478 by Alec Theriault at 2019-10-07T17:56:13-04:00 Add a regression test for haskell/haddock#1091 Previously, this input would crash Haddock. - - - - - ed7c8b0f by Alec Theriault at 2019-10-07T20:56:48-04:00 Add Hyperlinker test cases for TH-related stuff Hopefully this will guard against regressions around quasiquotes, TH quotes, and TH splices. - - - - - d00436ab by Andreas Klebinger at 2019-10-21T15:53:03+02:00 Refactor for withTiming changes. - - - - - 4230e712 by Ben Gamari at 2019-10-22T09:36:37-04:00 Merge pull request haskell/haddock#1101 from AndreasPK/withTimingRefactor Refactor for withTiming changes. - - - - - d155c5f4 by Ryan Scott at 2019-10-23T10:37:17-04:00 Reify oversaturated data family instances correctly (#1103) This fixes haskell/haddock#1103 by adapting the corresponding patch for GHC (see https://gitlab.haskell.org/ghc/ghc/issues/17296 and https://gitlab.haskell.org/ghc/ghc/merge_requests/1877). - - - - - 331a5adf by Sebastian Graf at 2019-10-25T17:14:40+02:00 Refactor for OutputableBndrId changes - - - - - 48a490e0 by Ben Gamari at 2019-10-27T10:16:16-04:00 Merge pull request haskell/haddock#1105 from sgraf812/wip/flexible-outputable Refactor for OutputableBndrId changes - - - - - f62a7dfc by Sebastian Graf at 2019-11-01T11:54:16+00:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - d9b242ed by Ryan Scott at 2019-11-03T13:20:03-05:00 Changes from haskell/haddock#14579 We now have a top-level `tyConAppNeedsKindSig` function, which means that we can delete lots of code in `Convert`. (cherry picked from commit cfd682c5fd03b099a3d78c44f9279faf56a0ac70) - - - - - dfd42406 by Sebastian Graf at 2019-11-04T07:02:14-05:00 Define `XRec` for location information and get rid of `HasSrcSpan` In https://gitlab.haskell.org/ghc/ghc/merge_requests/1970 I propose a simpler way to encode location information into the GHC and Haddock AST while incurring no cost for e.g. TH which doesn't need location information. These are just changes that have to happen in lock step. - - - - - 0b15be7c by Ben Gamari at 2019-11-09T13:21:33-05:00 Import isRuntimeRepVar from Type rather than TyCoRep isRuntimeRepVar is not longer exported from TyCoRep due to ghc#17441. - - - - - 091f7283 by Ben Gamari at 2019-11-10T12:47:06-05:00 Bump to GHC 8.10 - - - - - e88c71f2 by Ben Gamari at 2019-11-14T00:22:24-05:00 Merge pull request haskell/haddock#1110 from haskell/wip/T17441 Import isRuntimeRepVar from Type rather than TyCoRep - - - - - 4e0bbc17 by Ben Gamari at 2019-11-14T00:22:45-05:00 Version bumps for GHC 8.11 - - - - - 0e85ceb4 by Ben Gamari at 2019-11-15T11:59:45-05:00 Bump to GHC 8.10 - - - - - 00d6d68b by Ben Gamari at 2019-11-16T18:35:58-05:00 Bump ghc version to 8.11 - - - - - dde1fc3f by Ben Gamari at 2019-11-16T20:40:37-05:00 Drop support for base 4.13 - - - - - f52e331d by Vladislav Zavialov at 2019-11-24T13:02:28+03:00 Update Hyperlinker.Parser.classify to use ITdollar - - - - - 1ad96198 by Vladislav Zavialov at 2019-11-28T16:12:33+03:00 Remove HasSrcSpan (#17494) - - - - - 651afd70 by Herbert Valerio Riedel at 2019-12-08T12:08:16+01:00 Document error-prone conditional definition of instances This can easily trip up people if one isn't aware of it. Usually it's better to avoid this kind of conditionality especially for typeclasses for which there's an compat-package as conditional instances like these tend to fragment the ecosystem into those packages that go the extra mile to provide backward compat via those compat-packages and those that fail to do so. - - - - - b521af56 by Herbert Valerio Riedel at 2019-12-08T12:09:54+01:00 Fix build-failure regression for base < 4.7 The `$>` operator definition is available only since base-4.7 which unfortunately wasn't caught before release to Hackage (but has been fixed up by a metadata-revision) This commit introduces a `CompatPrelude` module which allows to reduce the amount of CPP by ousting it to a central location, i.e. the new `CompatPrelude` module. This pattern also tends to reduce the tricks needed to silence unused import warnings. Addresses haskell/haddock#1119 - - - - - 556c375d by Sylvain Henry at 2020-01-02T19:01:55+01:00 Fix after Iface modules renaming - - - - - bd6c53e5 by Sylvain Henry at 2020-01-07T00:48:48+01:00 hsyl20-modules-renamer - - - - - fb23713b by Ryan Scott at 2020-01-08T07:41:13-05:00 Changes for GHC#17608 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2372 - - - - - 4a4dd382 by Ryan Scott at 2020-01-25T08:08:26-05:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - e782a44d by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename PackageConfig into UnitInfo - - - - - ba3c9f05 by Sylvain Henry at 2020-01-26T02:12:37+01:00 Rename lookupPackage - - - - - ab37f9b3 by Ben Gamari at 2020-01-29T13:00:44-05:00 Merge pull request haskell/haddock#1125 from haskell/wip/T17566-take-two Changes for GHC#17566 - - - - - 3ebd5ae0 by Ryan Scott at 2020-01-31T05:56:50-05:00 Merge branch 'wip-hsyl20-package-refactor' into ghc-head - - - - - 602a747e by Richard Eisenberg at 2020-02-04T09:05:43+00:00 Echo GHC's removal of PlaceHolder module This goes with GHC's !2083. - - - - - ccfe5679 by Sylvain Henry at 2020-02-10T10:13:56+01:00 Module hierarchy: runtime (cf haskell/haddock#13009) - - - - - 554914ce by Cale Gibbard at 2020-02-10T16:10:39-05:00 Fix build of haddock in stage1 We have to use the correct version of the GHC API, but the version of the compiler itself doesn't matter. - - - - - 5b6fa2a7 by John Ericson at 2020-02-10T16:18:07-05:00 Noramlize `tested-with` fields in cabal files - - - - - e6eb3ebe by Vladislav Zavialov at 2020-02-16T13:25:26+03:00 No MonadFail/Alternative for P - - - - - 90e181f7 by Ben Gamari at 2020-02-18T14:13:47-05:00 Merge pull request haskell/haddock#1129 from obsidiansystems/wip/fix-stage1-build Fix build of haddock in stage1 - - - - - 93b64636 by Sylvain Henry at 2020-02-19T11:20:27+01:00 Modules: Driver (#13009) - - - - - da4f6c7b by Vladislav Zavialov at 2020-02-22T15:33:02+03:00 Use RealSrcSpan in InstMap - - - - - 479b1b50 by Ben Gamari at 2020-02-23T10:28:13-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 55ecacf0 by Sylvain Henry at 2020-02-25T15:18:27+01:00 Modules: Core (#13009) - - - - - 60867b3b by Vladislav Zavialov at 2020-02-28T15:53:52+03:00 Ignore the BufLoc/BufSpan added in GHC's !2516 - - - - - 1e5506d3 by Sylvain Henry at 2020-03-02T12:32:43+01:00 Modules: Core (#13009) - - - - - 6fb53177 by Richard Eisenberg at 2020-03-09T14:49:40+00:00 Changes in GHC's !1913. - - - - - 30b792ea by Ben Gamari at 2020-03-16T12:45:02-04:00 Merge pull request haskell/haddock#1130 from hsyl20/wip/hsyl20-modules-core2 Modules: Core (#13009) - - - - - cd761ffa by Sylvain Henry at 2020-03-18T15:24:00+01:00 Modules: Types - - - - - b6646486 by Ben Gamari at 2020-03-18T14:42:43-04:00 Merge pull request haskell/haddock#1133 from hsyl20/wip/hsyl20/modules/types Modules: Types - - - - - 9325d734 by Kleidukos at 2020-03-19T12:38:31-04:00 Replace the 'caption' class so that the collapsible sections are shown - - - - - 5e2bb555 by Kleidukos at 2020-03-19T12:38:31-04:00 Force ghc-8.8.3 - - - - - c6fcd0aa by Kleidukos at 2020-03-19T12:38:31-04:00 Update test fixtures - - - - - 5c849cb1 by Sylvain Henry at 2020-03-20T09:34:39+01:00 Modules: Types - - - - - 7f439155 by Alec Theriault at 2020-03-20T20:17:01-04:00 Merge branch 'ghc-8.8' into ghc-8.10 - - - - - b7904e5c by Alina Banerjee at 2020-03-20T20:24:17-04:00 Update parsing to strip whitespace from table cells (#1074) * Update parsing to strip leading & trailing whitespace from table cells * Update fixture data to disallow whitespaces at both ends in table cells * Add test case for whitespaces stripped from both ends of table cells * Update table reference test data for html tests - - - - - b9d60a59 by Alec Theriault at 2020-03-22T11:46:42-04:00 Clean up warnings * unused imports * imports of `Data.List` without import lists * missing `CompatPrelude` file in `.cabal` - - - - - 0c317dbe by Alec Theriault at 2020-03-22T18:46:54-04:00 Fix NPM security warnings This was done by calling `npm audit fix`. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. - - - - - 6e306242 by Alec Theriault at 2020-03-22T20:10:52-04:00 Tentative 2.24 release Adjusted changelogs and versions in `.cabal` files in preparation for the upcoming release bundled with GHC 8.10. - - - - - 1bfb4645 by Ben Gamari at 2020-03-23T16:40:54-04:00 Merge commit '3c2944c037263b426c4fe60a3424c27b852ea71c' into HEAD More changes from the GHC types module refactoring. - - - - - be8c6f3d by Alec Theriault at 2020-03-26T20:10:53-04:00 Update `.travis.yml` to work with GHC 8.10.1 * Regenerated the Travis file with `haskell-ci` * Beef up `.cabal` files with more `tested-with` information - - - - - b025a9c6 by Alec Theriault at 2020-03-26T20:10:53-04:00 Update README Removed some out of date links/info, added some more useful links. * badge to Hackage * update old trac link * `ghc-head` => `ghc-8.10` * `cabal new-*` is now `cabal v2-*` and it should Just Work * `--test-option='--accept'` is the way to accept testsuite output - - - - - 564d889a by Alec Theriault at 2020-03-27T20:34:33-04:00 Fix crash in `haddock-library` on unicode space Our quickcheck tests for `haddock-library` stumbled across an edge case input that was causing Haddock to crash: it was a unicode space character. The root cause of the crash is that we were implicitly assuming that if a space character was not " \t\f\v\r", it would have to be "\n". We fix this by instead defining horizontal space as: any space character that is not '\n'. Fixes haskell/haddock#1142 - - - - - 2d360ba1 by Alec Theriault at 2020-03-27T21:57:32-04:00 Disallow qualified uses of reserved identifiers This a GHC bug (https://gitlab.haskell.org/ghc/ghc/issues/14109) too, but it is a relatively easy fix in Haddock. Note that the fix must live in `haddock-api` instead of `haddock-library` because we can only really decide if an identifier is a reserved one by asking the GHC lexer. Fixes haskell/haddock#952 - - - - - 47ae22ed by Alec Theriault at 2020-03-28T13:36:25-04:00 Remove unused `Haddock.Utils` functions * removed functions in `Haddock.Utils` that were not used anywhere (or exported from the `haddock-api` package) * moved GHC-specific utils from `Haddock.Utils` to `Haddock.GhcUtils` - - - - - c0291245 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use TTG empty extensions to remove some `error`'s None of these error cases should ever have been reachable, so this is just a matter of leveraging the type system to assert this. * Use the `NoExtCon` and `noExtCon` to handle case matches for no extension constructors, instead of throwing an `error`. * Use the extension field of `HsSpliceTy` to ensure that this variant of `HsType` cannot exist in an `HsType DocNameI`. - - - - - 0aff8dc4 by Alec Theriault at 2020-03-28T13:36:25-04:00 Use `unLoc`/`noLoc` from GHC instead of `unL`/`reL` * `unL` is already defined by GHC as `unLoc` * `reL` is already defined by GHC as `noLoc` (in a safer way too!) * Condense `setOutputDir` and add a about exporting from GHC Fixes haskell/haddock#978 - - - - - bf6f2fb7 by Alec Theriault at 2020-03-28T13:36:25-04:00 Cleanup up GHC flags in `.cabal` files * enable more useful warning flags in `haddock-api`, handle the new warnings generated * remove `-fwarn-tabs` (now we'd use `-Wtabs`, but this has been in `-Wall` for a while now) - - - - - c576fbf1 by Alec Theriault at 2020-03-28T13:36:25-04:00 `haddock-library` document header level Document the fact the header level is going to always be between 1 and 6 inclusive. Along the way, I also optimized the parsing code a bit. - - - - - 71bce0ee by Alec Theriault at 2020-03-28T14:26:27-04:00 Disallow links in section headers This is quite straightforward to implement, since we already had a function `docToHtmlNoAnchors` (which we used to generate the link in the sidebar "Contents"). This breaks test `Bug387`, but that test case has aged badly: we now automatically generate anchors for all headings, so manually adding an anchor in a section makes no sense. Nested anchors are, as pointed out in haskell/haddock#1054, disallowed by the HTML standard. Fixes haskell/haddock#1054 - - - - - b461b0ed by Sylvain Henry at 2020-03-30T10:34:23+02:00 Modules: type checker - - - - - cd8cd1ee by Ben Gamari at 2020-03-31T12:45:02-04:00 Merge pull request haskell/haddock#1152 from hsyl20/wip/hsyl20/modules/tc Module renaming - - - - - 5e8f8ea7 by Felix Yan at 2020-04-01T17:58:06-07:00 Allow QuickCheck 2.14 Builds fine and all tests pass. - - - - - dc6b1633 by Sylvain Henry at 2020-04-05T16:43:44+02:00 Module renaming: amend previous patch - - - - - eee2f4ae by Ryan Scott at 2020-04-05T09:04:43-07:00 Fix haskell/haddock#1050 by filtering out invisible AppTy arguments This makes the `synifyType` case for `AppTy` more intelligent by taking into consideration the visibilities of each `AppTy` argument and filtering out any invisible arguments, as they aren't intended to be displayed in the source code. (See haskell/haddock#1050 for an example of what can happen if you fail to filter these out.) Along the way, I noticed that a special `synifyType` case for `AppTy t1 (CoercionTy {})` could be consolidated with the case below it, so I took the opportunity to tidy this up. - - - - - 23eb99e8 by Ben Gamari at 2020-04-07T11:19:58-04:00 Merge pull request haskell/haddock#1154 from hsyl20/wip/hsyl20/modules/tc Module renaming: amend previous patch - - - - - 072d994d by Ryan Scott at 2020-04-07T19:32:47-04:00 Make NoExtCon fields strict These changes are a part of a fix for [GHC#17992](https://gitlab.haskell.org/ghc/ghc/issues/17992). - - - - - d8ebf6c8 by Ignat Insarov at 2020-04-09T21:15:01-04:00 Recode Doc to Json. (#1159) * Recode Doc to Json. * More descriptive field labels. - - - - - 52df4b4e by Sylvain Henry at 2020-04-10T12:39:18+02:00 Module renaming - - - - - d9ab8ec8 by Cale Gibbard at 2020-04-14T11:43:34-04:00 Add instance of XCollectPat for DocNameI - - - - - 323d221d by Cale Gibbard at 2020-04-14T11:43:34-04:00 Rename XCollectPat -> CollectPass - - - - - 2df80867 by Alec Theriault at 2020-04-15T07:30:51-07:00 Prune docstrings that are never rendered When first creating a Haddock interface, trim `ifaceDocMap` and `ifaceArgMap` to not include docstrings that can never appear in the final output. Besides checking with GHC which names are exported, we also need to keep all the docs attached to instance declarations (it is much tougher to detect when an instance is fully private). This change means: * slightly smaller interface files (7% reduction on boot libs) * slightly less work to do processing docstrings that aren't used * no warnings in Haddock's output about private docstrings (see haskell/haddock#1070) I've tested manually that this does not affect any of the boot library generated docs (the only change in output was some small re-ordering in a handful of instance lists). This should mean no docstrings have been incorrectly dropped. - - - - - f49c90cc by Alec Theriault at 2020-04-15T07:30:51-07:00 Don't warn about missing links in miminal sigs When renaming the Haddock interface, never emit warnings when renaming a minimal signature. Also added some documention around `renameInterface`. Minimal signatures intentionally include references to potentially un-exported methods (see the discussion in haskell/haddock#330), so it is expected that they will not always have a link destination. On the principle that warnings should always be resolvable, this shouldn't produce a warning. See haskell/haddock#1070. - - - - - a9eda64d by Ben Gamari at 2020-04-17T09:27:35-04:00 Merge pull request haskell/haddock#1160 from hsyl20/wip/hsyl20/modules/systools Module renaming - - - - - f40d7879 by Cale Gibbard at 2020-04-20T11:30:38-04:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ttg-con-pat - - - - - a50e7753 by Ben Gamari at 2020-04-20T11:36:10-04:00 Merge pull request haskell/haddock#1165 from obsidiansystems/wip/ttg-con-pat Trees that Grow refactor (GHC !2553) - - - - - 6a24795c by Alec Theriault at 2020-04-21T08:06:45-07:00 Fallback to `hiDecl` when `extractDecl` fails Sometimes, the declaration being exported is a subdecl (for instance, a record accessor getting exported at the top-level). For these cases, Haddock has to find a way to produce some synthetic sensible top-level declaration. This is done with `extractDecl`. As is shown by haskell/haddock#1067, this is sometimes impossible to do just at a syntactic level (for instance when the subdecl is re-exported). In these cases, the only sensible thing to do is to try to reify a declaration based on a GHC `TyThing` via `hiDecl`. - - - - - eee1a8b7 by Sylvain Henry at 2020-04-24T15:46:05+02:00 Module structure - - - - - 50b9259c by Iñaki at 2020-04-25T18:38:11-04:00 Add support for custom section anchors (#1179) This allows to have stable anchors for groups, even if the set of groups in the documentation is altered. The syntax for setting the anchor of a group is -- * Group name #desiredAnchor# Which will produce an html anchor of the form '#g:desiredAnchor' Co-authored-by: Iñaki García Etxebarria <git at inaki.blueleaf.cc> - - - - - 4003c97a by Ben Gamari at 2020-04-26T09:35:15-04:00 Merge pull request haskell/haddock#1166 from hsyl20/wip/hsyl20/modules/utils Module structure - - - - - 5206ab60 by Sylvain Henry at 2020-04-27T16:47:39+02:00 Renamed UnitInfo fields - - - - - c32c333b by Sylvain Henry at 2020-04-27T17:32:58+02:00 UnitId has been renamed into Unit - - - - - 3e87db64 by Sylvain Henry at 2020-04-27T17:36:00+02:00 Fix for GHC.Unit.* modules - - - - - ae3323a7 by Ben Gamari at 2020-04-29T12:36:37-04:00 Merge pull request haskell/haddock#1183 from hsyl20/wip/hsyl20/unitid Refactoring of Unit code - - - - - b105564a by Artem Pelenitsyn at 2020-05-03T08:14:10+01:00 add dependency on exceptions because GHC.Exception was boiled down (ghc haskell/haddock#18075) - - - - - 9857eff3 by Zubin Duggal at 2020-05-04T18:48:25+01:00 Atomic update of NameCache in readHieFile - - - - - 86bbb226 by Sylvain Henry at 2020-05-14T16:36:27+02:00 Fix after Config module renaming - - - - - a4bbdbc2 by Gert-Jan Bottu at 2020-05-15T22:09:44+02:00 Explicit Specificity Support for Haddock - - - - - 46199daf by Ben Gamari at 2020-05-19T09:59:56-04:00 Merge pull request haskell/haddock#1192 from hsyl20/hsyl20/modules-config Fix after Config module renaming - - - - - f9a9d2ba by Gert-Jan Bottu at 2020-05-20T16:48:38-04:00 Explicit Specificity Support for Haddock - - - - - 55c5b7ea by Ben Gamari at 2020-05-21T00:32:02-04:00 Merge commit 'a8d7e66da4dcc3b242103271875261604be42d6e' into ghc-head - - - - - a566557f by Cale Gibbard at 2020-05-21T16:02:06-04:00 isBootSummary now produces a result of type IsBootInterface - - - - - ea52f905 by Zubin Duggal at 2020-05-24T17:55:48+01:00 update for hiefile-typeclass-info - - - - - 49ba7a67 by Willem Van Onsem at 2020-05-25T12:23:01-04:00 Use floor over round to calculate the percentage (#1195) If we compile documentation where only a small fraction is undocumented, it is misleading to see 100% coverage - 99% is more intuitive. Fixes haskell/haddock#1194 - - - - - c025ebf1 by Ben Gamari at 2020-05-29T14:32:42-04:00 Merge pull request haskell/haddock#1185 from obsidiansystems/boot-disambig isBootSummary now produces a result of type IsBootInterface - - - - - 74ab9415 by Ben Gamari at 2020-05-29T20:23:39-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - b40be944 by Ben Gamari at 2020-06-03T17:02:31-04:00 testsuite: Update expected output for simplified subsumption - - - - - 624be71c by Ryan Scott at 2020-06-05T12:43:23-04:00 Changes for GHC#18191 See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3337. - - - - - fbd8f7ce by Sylvain Henry at 2020-06-08T15:31:47+02:00 Fix after unit refactoring - - - - - 743fda4d by Ben Gamari at 2020-06-09T12:09:58-04:00 Merge pull request haskell/haddock#1202 from hsyl20/wip/hsyl20/unitid-ii Fix after unit refactoring - - - - - d07a06a9 by Ryan Scott at 2020-06-13T07:16:55-04:00 Use HsForAllTelescope (GHC#18235) - - - - - 389bb60d by Ben Gamari at 2020-06-13T15:30:52-04:00 haddock: Bounds bumps for GHC 8.12 - - - - - 7a377f5f by Ben Gamari at 2020-06-17T14:53:16-04:00 Merge pull request haskell/haddock#1199 from bgamari/wip/ghc-8.12 haddock: Bounds bumps for GHC 8.12 - - - - - 9fd9e586 by Krzysztof Gogolewski at 2020-06-17T16:09:07-04:00 Adapt Haddock to LinearTypes See ghc/ghc!852. - - - - - 46fe7636 by Ben Gamari at 2020-06-18T14:20:02-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 35a3c9e2 by Zubin Duggal at 2020-06-21T21:19:18+05:30 Use functions exported from HsToCore - - - - - 8abe3928 by Ben Gamari at 2020-06-24T13:53:39-04:00 Merge pull request haskell/haddock#1204 from wz1000/wip/haddock-hstocore Use functions exported from GHC.HsToCore.Docs - - - - - 22f2c937 by Matthías Páll Gissurarson at 2020-06-26T19:07:03+02:00 Adapt Haddock for QualifiedDo - - - - - 3f6208d7 by Vladislav Zavialov at 2020-06-28T14:28:16+03:00 Handle LexicalNegation's ITprefixminus - - - - - 03a19f41 by Sylvain Henry at 2020-07-02T09:37:38+02:00 Rename hsctarget into backend - - - - - ea17ff23 by Andreas Klebinger at 2020-07-02T17:44:18+02:00 Update for UniqFM changes. - - - - - 9872f2f3 by Ben Gamari at 2020-07-09T10:39:19-04:00 Merge pull request haskell/haddock#1209 from AndreasPK/wip/typed_uniqfm Update for UniqFM changes. - - - - - 68f7b668 by Krzysztof Gogolewski at 2020-07-12T18:16:57+02:00 Sync with GHC removing {-# CORE #-} pragma See ghc ticket haskell/haddock#18048 - - - - - eb372681 by Sylvain Henry at 2020-07-20T11:41:30+02:00 Rename hscTarget into backend - - - - - fb7f78bf by Ben Gamari at 2020-07-21T12:15:25-04:00 Merge pull request haskell/haddock#1214 from hsyl20/wip/hsyl20/hadrian/ncg Rename hscTarget into backend - - - - - 1e8f5b56 by Ben Gamari at 2020-07-23T09:11:50-04:00 Merge commit '904dce0cafe0a241dd3ef355775db47fc12f434d' into ghc-head - - - - - d8fd1775 by Zubin Duggal at 2020-07-23T18:46:40+05:30 Update for modular ping pong - - - - - 8416f872 by Ben Gamari at 2020-07-23T09:35:03-04:00 Merge pull request haskell/haddock#1200 from wz1000/wip/wz1000-modular-ping-pong Modular ping pong - - - - - a24a8577 by Ben Gamari at 2020-07-28T15:23:36-04:00 Bump GHC version to 9.0 - - - - - 6a51c9dd by Sylvain Henry at 2020-08-05T18:47:05+02:00 Fix after Outputable refactoring - - - - - c05e1c99 by Ben Gamari at 2020-08-10T14:41:41-04:00 Merge pull request haskell/haddock#1223 from hsyl20/wip/hsyl20/dynflags/exception Fix after Outputable refactoring - - - - - d964f15b by Sylvain Henry at 2020-08-12T11:58:49+02:00 Fix after HomeUnit - - - - - 8e6d5b23 by Ben Gamari at 2020-08-12T14:25:30-04:00 Merge pull request haskell/haddock#1225 from hsyl20/wip/hsyl20/plugins/homeunit Fix after HomeUnit - - - - - 8c7880fe by Sylvain Henry at 2020-08-17T14:13:29+02:00 Remove Ord FastString instance - - - - - 8ea410db by Alex Biehl at 2020-08-19T10:56:32+02:00 Another round of `npm audit fix` (#1228) This should shut down the warnings on Github. Note that the security issues seem to have been entirely in the build dependencies, since the output JS has not changed. Last NPM dependency audit happend in d576b2327e2bc117f912fe0a9d595e9ae62614e0 Co-authored-by: Alex Biehl <alex.biehl at target.com> - - - - - 7af6e2a8 by Ben Gamari at 2020-08-31T13:59:34-04:00 Merge pull request haskell/haddock#1226 from hsyl20/wip/hsyl20/fs_ord Remove Ord FastString instance - - - - - ffbc8702 by Alan Zimmerman at 2020-09-07T21:47:41+01:00 Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - a93f1268 by Alan Zimmerman at 2020-09-07T23:11:38+01:00 Merge pull request haskell/haddock#1232 from haskell/wip/T18639-remove-generated-pragma, Match GHC for haskell/haddock#18639, remove GENERATED pragma - - - - - 1f605d50 by Ben Gamari at 2020-09-14T18:30:01-04:00 Bump GHC version to 9.1 - - - - - 6599df62 by Vladislav Zavialov at 2020-09-18T14:05:15+03:00 Bump base upper bound to 4.16 - - - - - a01b3c43 by Ben Gamari at 2020-09-22T15:41:48-04:00 Update hypsrc-test for QuickLook This appears to be a spurious change. - - - - - e9cc6cac by Vladislav Zavialov at 2020-09-26T21:00:12+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 30e3ca7c by Sylvain Henry at 2020-09-29T11:18:32-04:00 Update for parser (#1234) - - - - - b172f3e3 by Vladislav Zavialov at 2020-09-30T01:01:30+03:00 Updates for the new linear types syntax: a %p -> b - - - - - 0b9c08d3 by Sylvain Henry at 2020-09-30T11:02:33+02:00 Adapt to GHC parser changes - - - - - b9540b7a by Sylvain Henry at 2020-10-12T09:13:38-04:00 Don't pass the HomeUnitId (#1239) - - - - - 34762e80 by HaskellMouse at 2020-10-13T12:58:04+03:00 Changed tests due to unification of `Nat` and `Natural` in the follwing merge request: https://gitlab.haskell.org/ghc/ghc/-/merge_requests/3583 - - - - - 256f86b6 by Vladislav Zavialov at 2020-10-15T10:48:03+03:00 Add whitespace in: map ($ v) - - - - - 4a3f711b by Alan Zimmerman at 2020-10-19T08:57:27+01:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled - - - - - 072cdd21 by Alan Zimmerman at 2020-10-21T14:48:28-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 9e09a445 by Alan Zimmerman at 2020-10-21T23:53:34-04:00 Match GHC, adding IsUnicodeSyntax field to HsFunTy and HsScaled (cherry picked from commit a7d1d8e034d25612d5d08ed8fdbf6f472aded4a1) - - - - - 636d7de3 by Sylvain Henry at 2020-10-26T14:31:54-04:00 GHC.Driver.Types refactoring (#1242) - - - - - a597f000 by Ryan Scott at 2020-10-29T04:18:05-04:00 Adapt to the removal of Hs{Boxed,Constraint}Tuple See ghc/ghc!4097 and GHC#18723. - - - - - b96660fb by Ryan Scott at 2020-10-30T04:53:05-04:00 Adapt to HsConDecl{H98,GADT}Details split Needed for GHC#18844. - - - - - c287d82c by Ryan Scott at 2020-10-30T19:35:59-04:00 Adapt to HsOuterTyVarBndrs These changes accompany ghc/ghc!4107, which aims to be a fix for haskell/haddock#16762. - - - - - a34c31a1 by Ryan Scott at 2020-11-13T13:38:34-05:00 Adapt to splitPiTysInvisible being renamed to splitInvisPiTys This is a part of !4434, a fix for GHC#18939. - - - - - 66ea459d by Sylvain Henry at 2020-11-16T10:59:30+01:00 Fix after Plugins moved into HscEnv - - - - - 508556d8 by Ben Gamari at 2020-11-18T15:47:40-05:00 Merge pull request haskell/haddock#1253 from hsyl20/wip/hsyl20/plugins/hscenv Fix after Plugins moved into HscEnv - - - - - 620fec1a by Andreas Klebinger at 2020-11-24T20:51:59+01:00 Update for changes in GHC's Pretty - - - - - 01cc13ab by Richard Eisenberg at 2020-11-25T23:18:35-05:00 Avoid GHC#18932. - - - - - 8d29ba21 by Cale Gibbard at 2020-11-25T23:18:35-05:00 Add type arguments to PrefixCon - - - - - 414d5f87 by Sylvain Henry at 2020-11-30T17:06:04+01:00 DynFlags's unit fields moved to HscEnv - - - - - e356668c by Ben Gamari at 2020-11-30T11:11:37-05:00 Merge pull request haskell/haddock#1258 from hsyl20/wip/hsyl20/hscenv/unitstate Unit fields moved from DynFlags to HscEnv - - - - - 7cf552f1 by Ben Gamari at 2020-12-03T10:31:27-05:00 Merge pull request haskell/haddock#1257 from AndreasPK/wip/andreask/opt_dumps Update for changes in GHC's Pretty - - - - - fc0871c3 by Veronika Romashkina at 2020-12-08T16:35:33+01:00 Fix docs links from Darcs to GitHub in intro (#1262) - - - - - 7059e808 by Veronika Romashkina at 2020-12-08T16:36:16+01:00 Use gender neutral word in docs (#1260) - - - - - 1b16e5ee by Maximilian Tagher at 2020-12-08T16:40:03+01:00 Allow scrolling search results (#1235) Closes https://github.com/haskell/haddock/issues/1231 - - - - - 8a118c01 by dependabot[bot] at 2020-12-08T16:40:25+01:00 Bump bl from 1.2.2 to 1.2.3 in /haddock-api/resources/html (#1255) Bumps [bl](https://github.com/rvagg/bl) from 1.2.2 to 1.2.3. - [Release notes](https://github.com/rvagg/bl/releases) - [Commits](https://github.com/rvagg/bl/compare/v1.2.2...v1.2.3) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - c89ff587 by Xia Li-yao at 2020-12-08T16:42:17+01:00 Allow more characters in anchor following module reference (#1220) - - - - - 14af7d64 by Xia Li-yao at 2020-12-08T16:43:05+01:00 Add dangling changes from branches ghc-8.6 and ghc-8.8 (#1243) * Fix multiple typos and inconsistencies in doc/markup.rst Note: I noticed some overlap with haskell/haddock#1112 from @wygulmage and haskell/haddock#1081 from @parsonsmatt after creating these proposed changes - mea culpa for not looking at the open PRs sooner. * Fix haskell/haddock#1113 If no Signatures, no section of index.html * Change the formatting of missing link destinations The current formatting of the missing link destination does not really help user to understand the reasons of the missing link. To address this, I've changed the formatting in two ways: - the missing link symbol name is now fully qualified. This way you immediately know which haskell module cannot be linked. It is then easier to understand why this module does not have documentation (hidden module or broken documentation). - one line per missing link, that's more readable now that symbol name can be longer due to qualification. For example, before haddock was listing missing symbol such as: ``` could not find link destinations for: Word8 Word16 mapMaybe ``` Now it is listed as: ``` could not find link destinations for: - Data.Word.Word8 - Data.Word.Word16 - Data.Maybe.mapMaybe ``` * Add `--ignore-link-symbol` command line argument This argument can be used multiples time. A missing link to a symbol listed by `--ignore-link-symbol` won't trigger "missing link" warning. * Forbid spaces in anchors (#1148) * Improve error messages with context information (#1060) Co-authored-by: Matt Audesse <matt at mattaudesse.com> Co-authored-by: Mike Pilgrem <mpilgrem at users.noreply.github.com> Co-authored-by: Guillaume Bouchard <guillaume.bouchard at tweag.io> Co-authored-by: Pepe Iborra <pepeiborra at gmail.com> - - - - - 89e3af13 by tomjaguarpaw at 2020-12-08T18:00:04+01:00 Enable two warnings (#1245) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - c3320f8d by Willem Van Onsem at 2020-12-08T18:26:55+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 685df308 by Alex Biehl at 2020-12-08T20:06:26+01:00 Changes for GHC#17566 See https://gitlab.haskell.org/ghc/ghc/merge_requests/2469 - - - - - be3ec3c0 by Alex Biehl at 2020-12-08T20:06:26+01:00 Import intercalate - - - - - 32c33912 by Matthías Páll Gissurarson at 2020-12-08T21:15:30+01:00 Adapt Haddock for QualifiedDo - - - - - 31696088 by Alex Biehl at 2020-12-08T22:06:02+01:00 Fix haddock-library tests - - - - - fbc0998a by Alex Biehl at 2020-12-08T23:08:23+01:00 Move to GitHub CI (#1266) * Initial version of ci.yml This is a straight copy from Dmitrii Kovanikov's blog post at https://kodimensional.dev/github-actions. Will adapt to haddock in successive commits. * Delete .travis.yml * Modify to only test on ghc-8.10.{1,2} * Use actions/setup-haskell at v1.1.4 * Relax QuickCheck bound on haddock-api * Remove stack matrix for now * Nail down to ghc-8.10 branch for now * Pin index state to 2020-12-08T20:13:44Z for now * Disable macOS and Windows tests for now for speed up - - - - - 5b946b9a by tomjaguarpaw at 2020-12-10T19:01:41+01:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - bc5a408f by dependabot[bot] at 2020-12-10T19:02:16+01:00 Bump ini from 1.3.5 to 1.3.7 in /haddock-api/resources/html (#1269) Bumps [ini](https://github.com/isaacs/ini) from 1.3.5 to 1.3.7. - [Release notes](https://github.com/isaacs/ini/releases) - [Commits](https://github.com/isaacs/ini/compare/v1.3.5...v1.3.7) Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - d02995f1 by Andrew Martin at 2020-12-14T16:48:40-05:00 Update for boxed rep - - - - - a381aeff by Ben Gamari at 2020-12-15T15:13:30-05:00 Revert "Enable two warnings (#1245) (#1268)" As this does not build on GHC `master`. This reverts commit 7936692badfe38f23ae95b51fb7bd7c2ff7e9bce. - - - - - a63c0a9e by Ben Gamari at 2020-12-15T15:17:59-05:00 Revert "Update for boxed rep" This reverts commit 4ffb30d8b637ccebecc81ce610f0af451ac8088d. - - - - - 53bfbb29 by Ben Gamari at 2020-12-15T15:37:24-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - bae76a30 by Ben Gamari at 2020-12-16T02:44:42+00:00 Update output for nullary TyConApp optimisation (ghc/ghc!2952) - - - - - 4b733b57 by Krzysztof Gogolewski at 2020-12-16T20:03:14+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. - - - - - ee463bd3 by Ryan Scott at 2020-12-16T16:55:23-05:00 Adapt to HsCoreTy (formerly NewHsTypeX) becoming a type synonym Needed for !4417, the fix for GHC#15706 and GHC#18914. - - - - - ed0b02f8 by tomjaguarpaw at 2020-12-19T10:17:19+00:00 Enable two warnings (#1245) (#1268) because they will be soon be added to -Wall. See https://gitlab.haskell.org/ghc/ghc/-/issues/15656 - - - - - d80bf8f5 by Sylvain Henry at 2020-12-21T10:09:25+01:00 Fix after binder collect changes - - - - - bf4c9d32 by Adam Gundry at 2020-12-23T21:35:01+00:00 Adapt to changes to GlobalRdrElt and AvailInfo Needed for ghc/ghc!4467 - - - - - 37736c4c by John Ericson at 2020-12-28T12:27:02-05:00 Support a new ghc --make node type for parallel backpack upsweep - - - - - 717bdeac by Vladislav Zavialov at 2020-12-29T10:50:02+03:00 Inline and fix getGADTConTypeG The getGADTConTypeG used HsRecTy, which is at odds with GHC issue haskell/haddock#18782. I noticed that getGADTConTypeG was only used in the Hoogle backend. Interestingly, when handling H98 constructors, Hoogle converts RecCon to PrefixCon (see Haddock.Backends.Hoogle.ppCtor). So I changed getGADTConTypeG to handle RecConGADT in the same manner as PrefixConGADT, and after this simplification moved it into the 'where' clause of ppCtor, to the only place where it is used. The practical effect of this change is as follows. Consider this example: data TestH98 = T98 { bar::Int } data TestGADT where TG :: { foo :: Int } -> TestGADT Before this patch, haddock --hoogle used to produce: T98 :: Int -> TestH98 [TG] :: {foo :: Int} -> TestGADT Notice how the record syntax was discarded in T98 but not TG. With this patch, we always produce signatures without record syntax: T98 :: Int -> TestH98 [TG] :: Int -> TestGADT I suspect this might also be a bugfix, as currently Hoogle doesn't seem to render GADT record constructors properly. - - - - - cb1b8c56 by Andreas Abel at 2020-12-30T21:12:37+01:00 Build instructions: haddock-library and -api first! - - - - - b947f6ad by Ben Gamari at 2020-12-31T13:04:19-05:00 Merge pull request haskell/haddock#1281 from obsidiansystems/wip/backpack-j Changes to support -j with backpack - - - - - 120e1cfd by Hécate Moonlight at 2021-01-04T19:54:58+01:00 Merge pull request haskell/haddock#1282 from andreasabel/master Build instructions: haddock-library and -api first! - - - - - fd45e41a by Ben Gamari at 2021-01-05T16:14:31-05:00 Merge remote-tracking branch 'origin/ghc-8.10' into ghc-9.0 - - - - - b471bdec by Ben Gamari at 2021-01-05T16:23:02-05:00 Merge commit '1e56f63c3197e7ca1c1e506e083c2bad25d08793' into ghc-9.0 - - - - - 81cdbc41 by Alex Biehl at 2021-01-09T12:14:41+01:00 Prepare Haddock for being a GHC Plugin - - - - - b646d952 by Alex Biehl at 2021-01-09T12:14:41+01:00 Make Haddock a GHC Plugin - - - - - cc044674 by Alex Biehl at 2021-01-09T12:14:41+01:00 Add -j[n] CLI param to Haddock executable It translates to `--ghcopt=-j[n]` - - - - - 84a04073 by Alex Biehl at 2021-01-09T12:14:41+01:00 Abstract Monad for interface creation I found that when running as a plugin the lookupName function (which runs in Ghc monad) does not work correctly from the typeCheckResultAction hook. Instead, we abstracted the monad used when creating interfaces, so that access to GHC session specific parts is explicit and so that the TcM can provide their (correct) implementation of lookupName. - - - - - 5be2c4f7 by Alex Biehl at 2021-01-09T12:14:41+01:00 Accept tests - - - - - 8cefee9d by Alex Biehl at 2021-01-09T16:10:47+01:00 Add missing dependency for mtl - - - - - 3681f919 by Ben Gamari at 2021-01-13T18:39:25-05:00 Merge remote-tracking branch 'origin/ghc-9.0' into ghc-head - - - - - 33c6b152 by Hécate Moonlight at 2021-01-14T16:04:20+01:00 Merge pull request haskell/haddock#1273 from hsyl20/wip/hsyl20/arrows Fix after binder collect changes - - - - - 70d13e8e by Joachim Breitner at 2021-01-22T19:03:45+01:00 Make haddock more robust to changes to the `Language` data type With the introduction of GHC2021, the `Languages` data type in GHC will grow. In preparation of that (and to avoid changing haddock with each new language), this change makes the code handle extensions to that data type gracefully. (cherry picked from commit c341dd7c9c3fc5ebc83a2d577c5a726f3eb152a5) - - - - - 7d6dd57a by John Ericson at 2021-01-22T22:02:02+00:00 Add `NoGhcTc` instance now that it's not closed - - - - - e5fdaf0a by Alan Zimmerman at 2021-01-23T22:57:44+00:00 Merge pull request haskell/haddock#1293 from obsidiansystems/wip/fix-18936 Add `NoGhcTc` instance now that it's not closed - - - - - 989a1e05 by Oleg Grenrus at 2021-01-24T16:11:46+03:00 Add import list to Data.List - - - - - 368e144a by Ben Gamari at 2021-01-28T22:15:48+01:00 Adapt to "Make PatSyn immutable" - - - - - abe66c21 by Alfredo Di Napoli at 2021-02-01T08:05:35+01:00 Rename pprLogErrMsg to new name - - - - - e600e75c by Hécate Moonlight at 2021-02-05T14:53:00+01:00 Move CI to ghc-9.0 - - - - - dd492961 by Vladislav Zavialov at 2021-02-05T14:53:00+01:00 Update cabal.project and README build instructions - - - - - 31bd292a by Hécate Moonlight at 2021-02-05T15:03:56+01:00 Merge pull request haskell/haddock#1296 from Kleidukos/ghc-9.0 Merge the late additions to ghc-8.10 into ghc-9.0 - - - - - 6388989e by Vladislav Zavialov at 2021-02-05T17:41:57+03:00 Cleanup: fix build warnings - - - - - f99407ef by Daniel Rogozin at 2021-02-05T18:11:48+03:00 type level characters support for haddock (required for haskell/haddock#11342) - - - - - d8c6b26f by Hécate Moonlight at 2021-02-05T17:44:50+01:00 Add a CONTRIBUTING.md file - - - - - 6a01ad98 by Hécate Moonlight at 2021-02-05T17:58:16+01:00 Merge pull request haskell/haddock#1312 from Kleidukos/proper-branch-etiquette Add a CONTRIBUTING.md file - - - - - 955eecc4 by Vladislav Zavialov at 2021-02-05T20:29:00+03:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into ghc-head - - - - - 47b3d6ab by Hécate Moonlight at 2021-02-05T19:09:38+01:00 Amend the CONTRIBUTING.md file - - - - - 23de6137 by Hécate Moonlight at 2021-02-05T19:16:49+01:00 Merge pull request haskell/haddock#1313 from Kleidukos/amend-contributing Amend the CONTRIBUTING.md file - - - - - 69026b59 by Krzysztof Gogolewski at 2021-02-05T23:05:56+01:00 Display linear/multiplicity arrows correctly (#1238) Previously we were ignoring multiplicity and displayed a %1 -> b as a -> b. (cherry picked from commit b4b4d896d2d68d6c48e7db7bfe95c185ca0709cb) - - - - - ea026b78 by Oleg Grenrus at 2021-02-06T17:14:45+01:00 Add import list to Data.List - - - - - 5204326f by Hécate Moonlight at 2021-02-06T17:15:44+01:00 Merge pull request haskell/haddock#1316 from Kleidukos/explicit-imports-to-data-list Add import list to Data.List - - - - - 1f4d2136 by Ben Gamari at 2021-02-06T11:53:31-05:00 Merge remote-tracking branch 'origin/ghc-head' into wip/ghc-head-merge - - - - - 13f0d09a by Ben Gamari at 2021-02-06T11:53:45-05:00 Fix partial record selector warning - - - - - 5c115f7e by Ben Gamari at 2021-02-06T11:55:52-05:00 Merge commit 'a917dfd29f3103b69378138477514cbfa38558a9' into wip/ghc-head-merge - - - - - b6fd8b75 by Ben Gamari at 2021-02-06T12:01:31-05:00 Merge commit '41964cb2fd54b5a10f8c0f28147015b7d5ad2c02' into wip/ghc-head-merge - - - - - a967194c by Ben Gamari at 2021-02-06T18:30:35-05:00 Merge branch 'wip/ghc-head-merge' into ghc-head - - - - - 1f4c3a91 by MorrowM at 2021-02-07T01:52:33+02:00 Fix search div not scrolling - - - - - 684b1287 by Iñaki García Etxebarria at 2021-02-07T16:13:04+01:00 Add support for labeled module references Support a markdown-style way of annotating module references. For instance -- | [label]("Module.Name#anchor") will create a link that points to the same place as the module reference "Module.Name#anchor" but the text displayed on the link will be "label". - - - - - bdb55a5d by Hécate Moonlight at 2021-02-07T16:18:10+01:00 Merge pull request haskell/haddock#1319 from alexbiehl/alex/compat Backward compat: Add support for labeled module references - - - - - 6ca70991 by Hécate Moonlight at 2021-02-07T16:21:29+01:00 Merge pull request haskell/haddock#1314 from tweag/show-linear-backport Backport haskell/haddock#1238 (linear types) to ghc-9.0 - - - - - d9d73298 by Alex Biehl at 2021-02-07T17:46:25+01:00 Remove dubious parseModLink Instead construct the ModLink value directly when parsing. - - - - - 33b4d020 by Hécate Moonlight at 2021-02-07T17:52:05+01:00 Merge pull request haskell/haddock#1320 from haskell/alex/fix Remove dubious parseModLink - - - - - 54211316 by Hécate Moonlight at 2021-02-07T18:12:07+01:00 Merge pull request haskell/haddock#1318 from MorrowM/ghc-9.0 Fix search div not scrolling - - - - - 19db679e by alexbiehl-gc at 2021-02-07T18:14:46+01:00 Merge pull request haskell/haddock#1317 from bgamari/wip/ghc-head-merge Merge ghc-8.10 into ghc-head - - - - - 6bc1e9e4 by Willem Van Onsem at 2021-02-07T18:25:30+01:00 simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - c8537cf8 by alexbiehl-gc at 2021-02-07T18:30:40+01:00 Merge pull request haskell/haddock#1322 from haskell/alex/forward-port simplify calculating percentages fixing haskell/haddock#1194 (#1236) - - - - - 2d47ae4e by alexbiehl-gc at 2021-02-07T18:39:59+01:00 Merge branch 'ghc-head' into ghc-9.0 - - - - - 849e4733 by Hécate Moonlight at 2021-02-07T18:43:19+01:00 Merge pull request haskell/haddock#1321 from Kleidukos/ghc-9.0 Merge ghc-9.0 into ghc-head - - - - - ee6095d7 by Sylvain Henry at 2021-02-08T11:36:38+01:00 Update for Logger - - - - - 4ad688c9 by Alex Biehl at 2021-02-08T18:11:24+01:00 Merge pull request haskell/haddock#1310 from hsyl20/wip/hsyl20/logger2 Logger refactoring - - - - - 922a9e0e by Ben Gamari at 2021-02-08T12:54:33-05:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - 991649d2 by Sylvain Henry at 2021-02-09T10:55:17+01:00 Fix to build with HEAD - - - - - a8348dc2 by Hécate Moonlight at 2021-02-09T10:58:51+01:00 Merge pull request haskell/haddock#1327 from hsyl20/wip/hsyl20/logger2 Fix to build with HEAD - - - - - 0abdbca6 by Fendor at 2021-02-09T20:06:15+01:00 Add UnitId to Target record - - - - - d5790a0e by Alex Biehl at 2021-02-11T10:32:32+01:00 Stable sort for (data/newtype) instances - - - - - 8e6036f5 by Alex Biehl at 2021-02-11T10:32:32+01:00 Also make TyLit deterministic - - - - - f76d2945 by Hécate Moonlight at 2021-02-11T11:00:31+01:00 Merge pull request haskell/haddock#1329 from hsyl20/hsyl20/stabe_iface Stable sort for instances - - - - - 5e0469ea by Oleg Grenrus at 2021-02-14T15:28:15+02:00 Add import list to Data.List in Haddock.Interface.Create - - - - - fa57cd24 by Hécate Moonlight at 2021-02-14T17:19:27+01:00 Merge pull request haskell/haddock#1331 from phadej/more-explicit-data-list-imports Add import list to Data.List in Haddock.Interface.Create - - - - - f0cd629c by Hécate Moonlight at 2021-02-21T00:22:01+01:00 Merge pull request haskell/haddock#1311 from fendor/wip/add-targetUnitId-to-target Add UnitId to Target record - - - - - 674ef723 by Joachim Breitner at 2021-02-22T10:39:18+01:00 html-test: Always set language from ghc-9.2 on, the “default” langauge of GHC is expected to change more wildly. To prepare for that (and unblock https://gitlab.haskell.org/ghc/ghc/-/merge_requests/4853), this sets the language for all the test files to `Haskell2010`. This should insolate this test suite against changes to the default. Cherry-picked from https://github.com/haskell/haddock/pull/1341 - - - - - f072d623 by Hécate Moonlight at 2021-02-22T10:56:51+01:00 Merge pull request haskell/haddock#1342 from nomeata/joachim/haskell2010-in-tests-ghc-head html-test: Always set language - - - - - caebbfca by Hécate Moonlight at 2021-02-22T11:53:07+01:00 Clean-up of Interface and Interface.Create's imports and pragmata - - - - - f6caa89d by Hécate Moonlight at 2021-02-22T11:54:58+01:00 Merge pull request haskell/haddock#1345 from Kleidukos/head/fix-interface-imports [ghc-head] Clean-up of Interface and Interface.Create's imports and pragmata - - - - - 7395c9cb by Hécate Moonlight at 2021-02-22T18:44:57+01:00 Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 6e9fb5d5 by Hécate Moonlight at 2021-02-22T18:45:28+01:00 Merge pull request haskell/haddock#1348 from Kleidukos/head/explicit-imports-interface Explicit imports for Haddock.Interface and Haddock.Interface.Create - - - - - 9198b118 by Alan Zimmerman at 2021-02-22T20:04:24+00:00 Context becomes a Maybe in the GHC AST This prevents noLoc's appearing in the ParsedSource. Match the change in GHC. - - - - - 0af20f64 by Hécate Moonlight at 2021-02-23T12:36:12+01:00 Fix the call-site of guessTarget in Interface.hs Explicit the imports from GHC.HsToCore.Docs - - - - - b7886885 by Hécate Moonlight at 2021-02-23T12:37:54+01:00 Merge pull request haskell/haddock#1349 from Kleidukos/fix-interface-guesstarget-call Fix the call-site of guessTarget in Interface.hs - - - - - 9cf041ba by Sylvain Henry at 2021-02-24T11:08:20+01:00 Fix haddockHypsrcTest output in ghc-head - - - - - b194182a by Hécate Moonlight at 2021-02-24T11:12:36+01:00 Merge pull request haskell/haddock#1351 from hsyl20/wip/hsyl20/fix-head Fix haddockHypsrcTest output in ghc-head - - - - - 3ce8b375 by Shayne Fletcher at 2021-03-06T09:55:03-05:00 Add ITproj to parser - - - - - d2abf762 by Ben Gamari at 2021-03-06T19:26:49-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - a0f6047d by Andrew Martin at 2021-03-07T11:25:23-05:00 Update for boxed rep - - - - - 6f63c99e by Ben Gamari at 2021-03-10T13:20:21-05:00 Update for "FastString: Use FastMutInt instead of IORef Int" - - - - - e13f01df by Luke Lau at 2021-03-10T15:38:40-05:00 Implement template-haskell's putDoc This catches up to GHC using the new extractTHDocs function, which returns documentation added via the putDoc function (provided it was compiled with Opt_Haddock). Since it's already a map from names -> docs, there's no need to do traversal etc. It also matches the change from the argument map being made an IntMap rather than a Map Int - - - - - 89263d94 by Alan Zimmerman at 2021-03-15T17:15:26+00:00 Match changes in GHC AST for in-tree API Annotations As landed via https://gitlab.haskell.org/ghc/ghc/-/merge_requests/2418 - - - - - 28db1934 by Alan Zimmerman at 2021-03-15T20:40:09+00:00 Change some type family test results. It is not clear to me whether the original was printing incorrectly (since we did not have the TopLevel flag before now), or if this behaviour is expected. For the time being I am assuming the former. - - - - - 7c11c989 by Sylvain Henry at 2021-03-22T10:05:19+01:00 Fix after NameCache changes - - - - - addbde15 by Sylvain Henry at 2021-03-22T10:05:19+01:00 NameCache doesn't store a UniqSupply anymore - - - - - 15ec6cec by Ben Gamari at 2021-03-22T17:53:44-04:00 Bump GHC version to 9.2 - - - - - dbd6aa63 by Hécate Moonlight at 2021-03-24T14:28:36+01:00 Merge pull request haskell/haddock#1365 from hsyl20/wip/hsyl20/iface1 NameCache refactoring - - - - - 2d32da7e by Oleg Grenrus at 2021-03-27T01:12:00+02:00 Specialization of Data.List - - - - - 32b84fa6 by Fendor at 2021-03-27T10:50:17+01:00 Add UnitId to Target record This way we always know to which home-unit a given target belongs to. So far, there only exists a single home-unit at a time, but it enables having multiple home-units at the same time. - - - - - 54bf9f0e by Hécate Moonlight at 2021-03-28T14:08:35+02:00 Merge pull request haskell/haddock#1368 from fendor/target-unit-id-revert Add UnitId to Target record - - - - - 7dea168a by Alan Zimmerman at 2021-03-29T08:45:52+01:00 EPA : Rename ApiAnn to EpAnn - - - - - 72967f65 by Alfredo Di Napoli at 2021-03-29T09:47:01+02:00 pprError changed name in GHC - - - - - 4bc61035 by Alan Zimmerman at 2021-03-29T16:16:27-04:00 EPA : Rename ApiAnn to EpAnn - - - - - 108d031d by Ben Gamari at 2021-03-29T18:49:36-04:00 Merge commit '36418c4f70d7d2b179a77925b3ad5caedb08c9b5' into HEAD - - - - - 1444f700 by Ben Gamari at 2021-03-31T09:18:39-04:00 Merge pull request haskell/haddock#1370 from adinapoli/wip/adinapoli-diag-reason-severity Rename pprError to mkParserErr - - - - - d3087b79 by Ben Gamari at 2021-03-31T11:34:17-04:00 Merge commit 'd8d8024ad6796549a8d3b5512dabf3288d14e30f' into ghc-head - - - - - 170b79e9 by Ben Gamari at 2021-03-31T12:24:56-04:00 Merge remote-tracking branch 'upstream/ghc-head' into ghc-head - - - - - db0d6bae by Ben Gamari at 2021-04-10T09:34:35-04:00 Bump GHC version to 9.3 - - - - - a9f2c421 by Alan Zimmerman at 2021-04-19T18:26:46-04:00 Update for EPA changes in GHC (cherry picked from commit cafb48118f7c111020663776845897e225607b41) - - - - - 1ee4b7c7 by Sylvain Henry at 2021-05-11T10:00:06+02:00 Removal of HsVersions.h (#1388) * Update for EPA changes in GHC * Account for HsVersions.h removal Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 79e819e9 by Hécate Moonlight at 2021-05-11T10:14:47+02:00 Revert "Removal of HsVersions.h (#1388)" This reverts commit 72118896464f94d81f10c52f5d9261efcacc57a6. - - - - - 3dbd3f8b by Alan Zimmerman at 2021-05-11T10:15:17+02:00 Update for EPA changes in GHC - - - - - 2ce80c17 by Sylvain Henry at 2021-05-11T10:15:19+02:00 Account for HsVersions.h removal - - - - - 00e4c918 by Christiaan Baaij at 2021-05-13T08:21:56+02:00 Add Haddock support for the OPAQUE pragma (#1380) - - - - - 8f9049b2 by Hécate Moonlight at 2021-05-13T08:40:22+02:00 fixup! Use GHC 9.2 in CI runner - - - - - 27ddec38 by Alan Zimmerman at 2021-05-13T22:51:20+01:00 EPA: match changes from GHC T19834 - - - - - f8a1d714 by Felix Yan at 2021-05-14T17:10:04+02:00 Allow hspec 2.8 (#1389) All tests are passing. - - - - - df44453b by Divam Narula at 2021-05-20T15:42:42+02:00 Update ref, the variables got renamed. (#1391) This is due to ghc/ghc!5555 which caused a change in ModDetails in case of NoBackend. Now the initModDetails is used to recreate the ModDetails from interface and in-memory ModDetails is not used. - - - - - e46bfc87 by Alan Zimmerman at 2021-05-20T19:05:09+01:00 Remove Maybe from HsQualTy Match changes in GHC for haskell/haddock#19845 - - - - - 79bd7b62 by Shayne Fletcher at 2021-05-22T08:20:39+10:00 FieldOcc: rename extFieldOcc to foExt - - - - - 6ed68c74 by Ben Gamari at 2021-05-21T22:29:30-04:00 Merge commit '3b6a8774bdb543dad59b2618458b07feab8a55e9' into ghc-head - - - - - f9a02d34 by Alfredo Di Napoli at 2021-05-24T13:53:00+02:00 New Parser diagnostics interface - - - - - 392807d0 by Ben Gamari at 2021-05-24T09:57:40-04:00 Merge pull request haskell/haddock#1394 from adinapoli/wip/adinapoli-align-ps-messages Align Haddock to use the new Parser diagnostics interface - - - - - 33023cd8 by Ben Gamari at 2021-05-24T11:19:16-04:00 Revert "Add Haddock support for the OPAQUE pragma (#1380)" This reverts commit a1337c599ef7720b0482a25c55f11794112496dc. The GHC patch associated with this change is not yet ready to be merged. - - - - - 8c005af7 by Ben Simms at 2021-05-28T07:56:20+02:00 CI configuration for ghc-head (#1395) - - - - - 1e947612 by Hécate Moonlight at 2021-05-28T12:27:35+02:00 Use GHC 9.2 in CI runner (#1378) - - - - - e6fa10ab by CGenie at 2021-05-31T09:02:13+02:00 Add page about common errors (#1396) * Update index.rst Common errors page * Create common-errors.rst * Update common-errors.rst * Use GHC 9.2 in CI runner (#1378) * [haddock-api] remove .hspec-failures Co-authored-by: Hécate Moonlight <Kleidukos at users.noreply.github.com> - - - - - abc72a8d by Sylvain Henry at 2021-06-01T10:02:06+02:00 Adapt Haddock to Logger and Parser changes (#1399) - - - - - 91373656 by Zubin Duggal at 2021-06-01T20:45:10+02:00 Update haddockHypSrc tests since we now compute slighly more type info (#1397) - - - - - ed712822 by Marcin Szamotulski at 2021-06-02T08:54:33+02:00 Added myself to contributors - - - - - 49fdbcb7 by Marcin Szamotulski at 2021-06-02T08:57:24+02:00 Document multi component support - - - - - 9ddc8d7d by Hécate Moonlight at 2021-06-02T09:35:55+02:00 Merge pull request haskell/haddock#1379 from coot/coot/document-multi-component-support Document multi component support - - - - - 585b5c5e by Ben Simms at 2021-06-02T19:46:54+02:00 Update CONTRIBUTING.md (#1402) - - - - - 1df4a605 by Ben Simms at 2021-06-02T19:47:14+02:00 Update CONTRIBUTING.md (#1403) - - - - - 58ea43d2 by sheaf at 2021-06-02T22:09:06+02:00 Update Haddock Bug873 to account for renaming - - - - - c5d0ab23 by Vladislav Zavialov at 2021-06-10T13:35:42+03:00 HsToken in FunTy, RecConGADT - - - - - 1ae2f40c by Hécate Moonlight at 2021-06-11T11:19:09+02:00 Update the CI badges - - - - - 6fdc4de2 by Sylvain Henry at 2021-06-28T19:21:17+02:00 Fix mkParserOpts (#1411) - - - - - 18201670 by Alfredo Di Napoli at 2021-07-05T07:55:12+02:00 Rename getErrorMessages Lexer import This commit renames the Lexer import in `Hyperlinker.Parser` from `getErrorMessages` to `getPsErrorMessages` to eliminate the ambiguity with the `getErrorMessages` function defined in `GHC.Types.Error`. - - - - - 23173ca3 by Ben Gamari at 2021-07-07T11:31:44-04:00 Merge pull request haskell/haddock#1413 from adinapoli/wip/adinapoli-issue-19920 Rename getErrorMessages Lexer import - - - - - b3dc4ed8 by Alan Zimmerman at 2021-07-28T22:30:59+01:00 EPA: match changes from GHC T19834 (cherry picked from commit 2fec1b44e0ee7e263286709aa528b4ecb99ac6c2) - - - - - 5f177278 by Ben Gamari at 2021-08-06T01:17:37-04:00 Merge commit '2a966c8ca37' into HEAD - - - - - cdd81d08 by Marcin Szamotulski at 2021-08-08T17:19:06+02:00 coot/multiple packages (ghc-9.2) (#1418) - - - - - be0d71f1 by Marcin Szamotulski at 2021-08-16T08:46:03+02:00 coot/multiple package (ghc-head) (#1419) * FromJSON class Aeson style FromJSON class with Parsec based json parser. * doc-index.json file for multiple packages When creating haddock summary page for multiple packages render doc-index.json file using contents of all found 'doc-index.json' files. * Render doc-index.json When rendering html, render doc-index.json file independently of maybe_index_url option. doc-index.json file is useful now even if maybe_index_url is not `Nothing`. * base url option New `Flag_BaseURL` which configures from where static files are loaded (--base-url). If given and not equal "." static files are not coppied, as this indicates that they are not read from the the directory where we'd copy them. The default value is ".". - - - - - 3b09dbdf by Hécate Moonlight at 2021-10-07T23:26:03+02:00 Update GHC 9.2 to latest pre-release in CI - - - - - 7ac55417 by Zubin Duggal at 2021-10-11T12:10:19+02:00 Enable Haddock tests in GHC windows CI (#1428) * testsuite: strip windows line endings for haddock * hyperlinker: Work around double escaping (#19236) * deterministic SCC - - - - - 1cb81f25 by Andrew Lelechenko at 2021-10-12T15:23:19+02:00 haddock-library does not depend on bytestring or transformers (#1426) - - - - - a890b9aa by sheaf at 2021-10-15T22:19:42+02:00 update haddockHypsrcTest for GHC MR !6705 (#1430) - - - - - 42a55c6c by Sylvain Henry at 2021-10-15T22:20:10+02:00 Fix after PkgQual refactoring (#1429) - - - - - 91659238 by Alan Zimmerman at 2021-10-28T18:57:10+01:00 Update for changes in GHC for branch wip/az/no-srcspan-anno-instances - - - - - acf23e60 by Vladislav Zavialov at 2021-11-05T02:09:47+03:00 Do not use forall as an identifier See GHC ticket haskell/haddock#20609 - - - - - c565db0e by Krzysztof Gogolewski at 2021-11-27T02:42:35+01:00 Update after NoExtCon -> DataConCantHappen rename - - - - - b5f55590 by Artem Pelenitsyn at 2021-11-27T11:14:17+01:00 fix CI for 9.2 (#1436) - - - - - 25cd621e by Matthew Pickering at 2021-12-02T11:46:54+00:00 Update html-test for Data.List revert - - - - - 1d5ff85f by malteneuss at 2021-12-15T07:56:55+01:00 Add hint about inline link issue (#1444) - - - - - 791fde81 by Sylvain Henry at 2021-12-16T09:29:51+01:00 Bump ghc-head (#1445) * Update after NoExtCon -> DataConCantHappen rename * Update html-test for Data.List revert * Fix for new Plugins datatype Co-authored-by: Krzysztof Gogolewski <krzysztof.gogolewski at tweag.io> Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com> - - - - - 44236317 by Sylvain Henry at 2021-12-17T09:39:00+01:00 Fix for new Plugins datatype - - - - - 80ada0fa by Hécate Moonlight at 2021-12-17T17:28:48+01:00 Remove ghc-head workflow (#1446) Contributions of GHC glue code are now done on the GHC gitlab, not in the GitHub repo anymore. - - - - - 49e171cd by Matthew Pickering at 2021-12-28T09:47:09+00:00 Remove use of ExtendedModSummary - - - - - 0e91b5ea by askeblad at 2022-01-04T09:18:35+01:00 update URLs - - - - - 9f13c212 by Hécate Moonlight at 2022-02-25T10:19:46+01:00 Fix solver for GHC 9.2 - - - - - 386751a1 by Meng Weng Wong at 2022-02-25T19:19:11+01:00 IDoc link has bitrotted; replaced with web.archive.org cache. (#1454) - - - - - d877cbe6 by Hécate Moonlight at 2022-02-25T19:21:58+01:00 Fix haddock user guide (#1456) - - - - - cc47f036 by Andrew Lelechenko at 2022-03-04T17:29:36+01:00 Allow text-2.0 in haddock-library (#1459) - - - - - 7b3685a3 by malteneuss at 2022-03-07T19:27:24+01:00 Add multi-line style hint to style section (#1460) - - - - - c51088b8 by John Ericson at 2022-03-11T16:46:26+01:00 Fix CollectPass instance to match TTG refactor Companion to GHC !7614 (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/7614) - - - - - b882195b by Vladislav Zavialov at 2022-03-14T20:32:30+01:00 Link to (~) - - - - - 877349b8 by Christiaan Baaij at 2022-03-16T09:20:43+01:00 Add Haddock support for the OPAQUE pragma - - - - - 0ea22721 by askeblad at 2022-03-16T09:44:27+01:00 typos (#1464) - - - - - a6d13da1 by Matthew Pickering at 2022-03-22T13:41:17+00:00 Minimum changes needed for compilation with hi-haddock With hi-haddock, of course there is a much large refactoring of haddock which could be achieved but that is left for a future patch which can implemented at any time independently of GHC. - - - - - e7ac9129 by Matthew Pickering at 2022-03-22T21:17:50+00:00 Update test output - - - - - 6d916214 by Matthew Pickering at 2022-03-24T15:06:26+00:00 Merge branch 'wip/opaque_pragma' into 'ghc-head' Add Haddock support for the OPAQUE pragma See merge request ghc/haddock!2 - - - - - 42208183 by Steve Hart at 2022-03-25T20:43:50+01:00 Fix CI (#1467) * CI: Reinstall GHC with docs CI tests were failing because the GHC preinstalled to the CI environment does not include documentation, which is required for running the Haddock tests. This commit causes the CI workflow to reinstall GHC with docs so that tests can succeed. - - - - - 9676fd79 by Steve Hart at 2022-03-25T21:33:34+01:00 Make links in Synopsis functional again (#1458) Commit e41c1cbe9f0476997eac7b4a3f17cbc6b2262faf added a call to e.preventDefault() when handling click events that reach a toggle element. This prevents the browser from following hyperlinks within the Synopsis section when they are clicked by a user. This commit restores functioning hyperlinks within the Synopsis section by removing the call to e.preventDefault(), as it does not appear to be necessary, and removing it increases the flexibility of the details-helper code. - - - - - d1edd637 by sheaf at 2022-04-01T12:02:02+02:00 Keep track of promotion ticks in HsOpTy Keeping track of promotion ticks in HsOpTy allows us to properly pretty-print promoted constructors such as lists. - - - - - 9dcb2dfc by Jakob Brünker at 2022-04-01T15:46:22+00:00 Add support for \cases See merge request ghc/ghc!7873 - - - - - b0412ee5 by askeblad at 2022-04-06T17:47:57+02:00 spelling errors (#1471) - - - - - 6b18829b by Vladislav Zavialov at 2022-04-06T18:53:58+02:00 Rename [] to List - - - - - 2d046691 by Vladislav Zavialov at 2022-04-07T20:25:54+03:00 HsToken ConDeclGADT con_dcolon - - - - - 90b43da4 by Steve Hart at 2022-04-12T13:29:46+02:00 Parse Markdown links at beginning of line within a paragraph (#1470) * Catch Markdown links at beginning of line within paragraph Per Issue haskell/haddock#774, Markdown links were being parsed as ordinary text when they occurred at the beginning of a line other than the first line of the paragraph. This occurred because the parser was not interpreting a left square bracket as a special character that could delimit special markup. A space character was considered a special character, so, if a space occurred at the beginning of the new line, then the parser would interpret the space by itself and then continue parsing, thereby catching the Markdown link. '\n' was not treated as a special character, so the parser did not catch a Markdown link that may have followed. Note that this will allow for Markdown links that are not surrounded by spaces. For example, the following text includes a Markdown link that will be parsed: Hello, world[label](url) This is consistent with how the parser handles other types of markup. * Remove obsolete documentation hint Commit 6b9aeafddf20efc65d3725c16e3fc43a20aac343 should eliminate the need for the workaround suggested in the documentation. - - - - - 5b08312d by Hécate Moonlight at 2022-04-12T13:36:38+02:00 Force ghc-9.2 in the cabal.project - - - - - 0d0ea349 by dependabot[bot] at 2022-04-12T13:57:41+02:00 Bump path-parse from 1.0.5 to 1.0.7 in /haddock-api/resources/html (#1469) Bumps [path-parse](https://github.com/jbgutierrez/path-parse) from 1.0.5 to 1.0.7. - [Release notes](https://github.com/jbgutierrez/path-parse/releases) - [Commits](https://github.com/jbgutierrez/path-parse/commits/v1.0.7) --- updated-dependencies: - dependency-name: path-parse dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 2b9fc65e by dependabot[bot] at 2022-04-12T13:57:54+02:00 Bump copy-props from 2.0.4 to 2.0.5 in /haddock-api/resources/html (#1468) Bumps [copy-props](https://github.com/gulpjs/copy-props) from 2.0.4 to 2.0.5. - [Release notes](https://github.com/gulpjs/copy-props/releases) - [Changelog](https://github.com/gulpjs/copy-props/blob/master/CHANGELOG.md) - [Commits](https://github.com/gulpjs/copy-props/compare/2.0.4...2.0.5) --- updated-dependencies: - dependency-name: copy-props dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - ea98a6fb by Ben Gamari at 2022-04-23T22:54:37-04:00 Update for GHC 9.4 - - - - - 9e11864f by Ben Gamari at 2022-04-25T16:24:31-04:00 Merge remote-tracking branch 'upstream/ghc-9.2' into ghc-head - - - - - f83cc506 by Ben Gamari at 2022-04-25T17:00:25-04:00 Bump ghc version to 9.5 - - - - - e01c2e7d by Ben Gamari at 2022-04-28T16:19:04-04:00 Revert "Bump ghc-head (#1445)" This reverts commit b29a78ef6926101338f62e84f456dac8659dc9d2. This should not have been merged. - - - - - a2b5ee8c by Ben Gamari at 2022-04-28T16:19:24-04:00 Merge commit '2627a86c' into ghc-head - - - - - 0c6fe4f9 by Ben Gamari at 2022-04-29T10:05:54-04:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-9.4 - - - - - b6e5cb0a by Ben Gamari at 2022-04-29T11:46:06-04:00 Revert "HsToken ConDeclGADT con_dcolon" This reverts commit 24208496649a02d5f87373052c430ea4a97842c5. - - - - - 15a62888 by Ben Gamari at 2022-04-29T15:12:55-04:00 Bump base upper bound - - - - - 165b9031 by Ben Gamari at 2022-04-29T23:58:38-04:00 Update test output - - - - - e0c3e5da by Phil de Joux at 2022-05-02T14:46:38+02:00 Add hlint action .hlint.yaml with ignores & CPP. (#1475) - - - - - ead1158d by Raphael Das Gupta at 2022-05-02T14:46:48+02:00 fix grammar in docs: "can the" → "can be" (#1477) - - - - - cff97944 by Ben Gamari at 2022-05-02T18:38:56-04:00 Allow base-4.17 - - - - - e4ecb201 by Phil de Joux at 2022-05-03T13:14:55+02:00 Remove unused imports that GHC warned about. (#1480) - - - - - 222890b1 by Phil de Joux at 2022-05-03T13:15:46+02:00 Follow hlint suggestion to remove redundant bang. (#1479) - - - - - 058b671f by Phil de Joux at 2022-05-03T13:34:04+02:00 Follow hlint, remove language pragmas in libs. (#1478) - - - - - 0a645049 by Ben Simms at 2022-05-03T14:19:24+02:00 Keep track of ordered list indexes and render them (#1407) * Keep track of ordered list indexes and render them * Rename some identifiers to clarify - - - - - f0433304 by Norman Ramsey at 2022-05-04T15:13:34-04:00 update for changes in GHC API - - - - - 3740cf71 by Emily Martins at 2022-05-06T18:23:48+02:00 Add link to the readthedocs in cabal description to show on hackage. (cherry picked from commit 52e2d40d47295c02d3181aac0c53028e730f1e3b) - - - - - 5d754f1e by Hécate Moonlight at 2022-05-06T18:44:57+02:00 remove Bug873 - - - - - 968fc267 by Hécate Moonlight at 2022-05-06T18:48:28+02:00 Ignore "Use second" HLint suggestion. It increases laziness. - - - - - 02d14e97 by Jade Lovelace at 2022-05-07T17:42:08+02:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` - - - - - b22b87ed by Artem Pelenitsyn at 2022-05-08T16:19:47+02:00 fix parsing trailing quotes in backticked identifiers (#1408) (#1483) - - - - - 80ae107b by Alex Biehl at 2022-05-08T16:37:16+02:00 Fix "Defined by not used" error (cherry picked from commit 6e02a620a26c3a44f98675dd1b93b08070c36c0a) - - - - - 4c838e84 by Hécate Moonlight at 2022-05-08T16:37:16+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - fc9827b4 by Hécate Moonlight at 2022-05-08T16:40:40+02:00 Fix the changelog and bump the version of haddock-library on ghc-9.2 - - - - - b153b555 by Xia Li-yao at 2022-05-20T17:52:42+02:00 Hide synopsis from search when hidden (#1486) Fix haskell/haddock#1451 - - - - - f3e38b85 by Marcin Szamotulski at 2022-05-21T23:32:31+02:00 Allow to hide interfaces when rendering multiple components (#1487) This is useful when one wishes to `--gen-contents` when rendering multiple components, but one does not want to render all modules. This is in particular useful when adding base package. - - - - - f942863b by Marcin Szamotulski at 2022-05-24T08:29:59+02:00 Check if doc-index.json exists before reading it (#1488) - - - - - 31e92982 by Marcin Szamotulski at 2022-05-25T16:22:13+02:00 Version bump 2.26.1 (#1489) * Version bump 2.26.1 We extended format accepted by `--read-interface` option, which requires updating the minor version. * Update documentation of --read-interface option - - - - - 7cc873e0 by sheaf at 2022-05-25T16:42:31+02:00 Updated HaddockHypsrcTest output for record update changes (MR !7981) - - - - - cd196942 by Marcin Szamotulski at 2022-05-25T20:28:47+02:00 Use visibility to decide which interfaces are included in quickjump (#1490) This is also consistent with how html index is build. See haskell/cabal#7669 for rationale behind this decision. - - - - - 00c713c5 by Hécate Moonlight at 2022-05-26T17:09:15+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 2f3039f1 by Hécate Moonlight at 2022-05-26T17:10:59+02:00 Add code of conduct and hspec failure files in .gitignore - - - - - 63a5650c by romes at 2022-05-31T12:43:22+01:00 TTG: Match new GHC AST - - - - - dd7d1617 by romes at 2022-06-02T16:11:00+01:00 Update for IE changes in !8228 - - - - - c23aaab7 by cydparser at 2022-06-06T08:48:14+02:00 Fix and improve CI (#1495) * Pin GHC version before creating the freeze file * Use newest action versions * Improve caching * Avoid unnecessarily reinstalling GHC * Use GHC 9.2.2 for CI Co-authored-by: Cyd Wise <cwise at tripshot.com> - - - - - c156fa77 by Hécate Moonlight at 2022-06-06T11:59:35+02:00 Add Mergify configuration (#1496) - - - - - 2dba4188 by Hécate Moonlight at 2022-06-06T16:12:50+02:00 Bump haddock's version in cabal file to 2.26.1 (#1497) - - - - - d7d4b8b9 by Marcin Szamotulski at 2022-06-07T06:09:40+00:00 Render module tree per package in the content page (#1492) * Render module tree per package in the content page When rendering content page for multiple packages it is useful to split the module tree per package. Package names in this patch are inferred from haddock's interface file names. * Write PackageInfo into interface file To keep interface file format backward compatible, instead of using `Binary` instance for `InterfaceFile` we introduce functions to serialise and deserialise, which depends on the interface file version. - - - - - 77765665 by Mike Pilgrem at 2022-06-12T21:57:19+01:00 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - b0e079b0 by mergify[bot] at 2022-06-13T11:49:37+00:00 Merge pull request haskell/haddock#1108 from mpilgrem/fix783 Fix haskell/haddock#783 Don't show button if --quickjump not present - - - - - 6c0292b1 by Hécate Moonlight at 2022-06-21T17:21:08+02:00 Update the contribution guide - - - - - e413b9fa by dependabot[bot] at 2022-06-21T23:38:19+02:00 Bump shell-quote from 1.6.1 to 1.7.3 in /haddock-api/resources/html (#1500) Bumps [shell-quote](https://github.com/substack/node-shell-quote) from 1.6.1 to 1.7.3. - [Release notes](https://github.com/substack/node-shell-quote/releases) - [Changelog](https://github.com/substack/node-shell-quote/blob/master/CHANGELOG.md) - [Commits](https://github.com/substack/node-shell-quote/compare/1.6.1...1.7.3) --- updated-dependencies: - dependency-name: shell-quote dependency-type: indirect ... Signed-off-by: dependabot[bot] <support at github.com> Co-authored-by: dependabot[bot] <49699333+dependabot[bot]@users.noreply.github.com> - - - - - 29d0ef70 by romes at 2022-07-06T11:29:39+02:00 TTG: AST Updates for !8308 - - - - - 1bae7c87 by Alan Zimmerman at 2022-07-06T22:50:43+01:00 Match GHC changes for T21805 This brings in a newtype for FieldLabelString - - - - - 6fe8b988 by Phil de Joux at 2022-07-16T20:54:26+00:00 Bump hlint version to 3.4.1, the version with counts. (#1503) Redo the counts available with the --default option. - - - - - 48fb43af by Phil de Joux at 2022-07-19T09:32:55+02:00 Follow hlint suggestion: unused LANGUAGE pragma. (#1504) * Follow hlint suggestion: unused LANGUAGE pragma. * Ignore within modules to pass linting and pass tests. - - - - - c1cf1fa7 by Phil de Joux at 2022-07-24T13:45:59+02:00 Follow hlint suggestion: redundant $. (#1505) * Follow hlint suggestion: redundant $. * Remove $ and surplus blank lines in Operators. - - - - - 74777eb2 by Jade Lovelace at 2022-07-29T11:02:41+01:00 Fix hyperlinks to external items and modules (#1482) Fixes haskell/haddock#1481. There were two bugs in this: * We were assuming that we were always getting a relative path to the module in question, while Nix gives us file:// URLs sometimes. This change checks for those and stops prepending `..` to them. * We were not linking to the file under the module. This seems to have been a regression introduced by haskell/haddock#977. That is, the URLs were going to something like file:///nix/store/3bwbsy0llxxn1pixx3ll02alln56ivxy-ghc-9.0.2-doc/share/doc/ghc/html/libraries/base-4.15.1.0/src which does not have the appropriate HTML file or fragment for the item in question at the end. There is a remaining instance of the latter bug, but not in the hyperlinker: the source links to items reexported from other modules are also not including the correct file name. e.g. the reexport of Entity in esqueleto, from persistent. NOTE: This needs to get tested with relative-path located modules. It seems correct for Nix based on my testing. Testing strategy: ``` nix-shell '<nixpkgs>' --pure -A haskell.packages.ghc922.aeson mkdir /tmp/aesonbuild && cd /tmp/aesonbuild export out=/tmp/aesonbuild/out genericBuild ln -sf $HOME/co/haddock/haddock-api/resources . ./Setup haddock --with-haddock=$HOME/path/to/haddock/exec --hyperlink-source ``` (cherry picked from commit ab53ccf089ea703b767581ac14be0f6c78a7678a) - - - - - faa4cfcf by Hécate Moonlight at 2022-07-29T20:31:20+02:00 Merge pull request haskell/haddock#1516 from duog/9-4-backport-fix-hyperlinks Backport 9-4: Fix hyperlinks to external items and modules (#1482) - - - - - 5d2450f3 by Ben Gamari at 2022-08-05T17:41:15-04:00 Merge remote-tracking branch 'origin/ghc-9.4' - - - - - 63954f73 by Ben Gamari at 2022-08-05T19:08:36-04:00 Clean up build and testsuite for GHC 9.4 - - - - - d4568cb8 by Hécate Moonlight at 2022-08-05T19:10:49-04:00 Bump the versions - - - - - 505583a4 by Ben Gamari at 2022-08-06T13:58:27-04:00 Merge pull request haskell/haddock#1518 from bgamari/wip/ghc-9.4-merge Merge GHC 9.4 into `main` - - - - - 5706f6a4 by Ben Gamari at 2022-08-06T22:57:21-04:00 html-test: Testsuite changes for GHC 9.4.1 - - - - - 5f2a45a2 by Ben Gamari at 2022-08-15T14:33:05-04:00 doc: Fix a few minor ReST issues Sphinx was complaining about too-short title underlines. - - - - - 220e6410 by Ben Gamari at 2022-08-15T14:41:24-04:00 Merge branch 'main' into ghc-head - - - - - fbeb1b02 by Ben Gamari at 2022-08-15T14:45:16-04:00 Updates for GHC 9.5 - - - - - eee562eb by Vladislav Zavialov at 2022-08-15T14:46:13-04:00 HsToken ConDeclGADT con_dcolon - - - - - c5f073db by Ben Gamari at 2022-08-15T16:55:35-04:00 Updates for GHC 9.5 - - - - - 3f7ab242 by Vladislav Zavialov at 2022-08-15T16:55:35-04:00 HsToken ConDeclGADT con_dcolon - - - - - a18e473d by Ben Gamari at 2022-08-16T08:35:19-04:00 Merge branch 'wip/ghc-head-bump' into ghc-head - - - - - af0ff3a4 by M Farkas-Dyck at 2022-09-15T21:16:05+00:00 Disuse `mapLoc`. - - - - - a748fc38 by Matthew Farkas-Dyck at 2022-09-17T10:44:18+00:00 Scrub partiality about `NewOrData`. - - - - - 2758fb6c by John Ericson at 2022-09-18T03:27:37+02:00 Test output changed because of change to `base` Spooky, but I guess that is intended? - - - - - a7eec128 by Torsten Schmits at 2022-09-21T11:06:55+02:00 update tests for the move of tuples to GHC.Tuple.Prim - - - - - 461e7b9d by Ross Paterson at 2022-09-24T22:01:25+00:00 match implementation of GHC proposal haskell/haddock#106 (Define Kinds Without Promotion) - - - - - f7fd77ef by sheaf at 2022-10-17T14:53:01+02:00 Update Haddock for GHC MR !8563 (configuration of diagnostics) - - - - - 3d3e85ab by Vladislav Zavialov at 2022-10-22T23:04:06+03:00 Class layout info - - - - - cbde4cb0 by Simon Peyton Jones at 2022-10-25T23:19:18+01:00 Adapt to Constraint-vs-Type See haskell/haddock#21623 and !8750 - - - - - 7108ba96 by Tom Smeding at 2022-11-01T22:33:23+01:00 Remove outdated footnote about module re-exports The footnote is invalid with GHC 9.2.4 (and possibly earlier): the described behaviour in the main text works fine. - - - - - 206c6bc7 by Hécate Moonlight at 2022-11-01T23:00:46+01:00 Merge pull request haskell/haddock#1534 from tomsmeding/patch-1 - - - - - a57b4c4b by Andrew Lelechenko at 2022-11-21T00:39:52+00:00 Support mtl-2.3 - - - - - e9d62453 by Simon Peyton Jones at 2022-11-25T13:49:12+01:00 Track small API change in TyCon.hs - - - - - eb1c73f7 by Ben Gamari at 2022-12-07T08:46:21-05:00 Update for GhC 9.6 - - - - - 063268dd by Ben Gamari at 2022-12-07T11:26:32-05:00 Merge remote-tracking branch 'upstream/ghc-head' into HEAD - - - - - 4ca722fe by Ben Gamari at 2022-12-08T14:43:26-05:00 Bump bounds to accomodate base-4.18 - - - - - 340b7511 by Vladislav Zavialov at 2022-12-10T12:31:28+00:00 HsToken in HsAppKindTy - - - - - 946226ec by Ben Gamari at 2022-12-13T20:12:56-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - fd8faa66 by Ben Gamari at 2022-12-22T13:44:28-05:00 Bump GHC version to 9.7 - - - - - 2958aa9c by Ben Gamari at 2022-12-22T14:49:16-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 9e0fefd8 by Andrei Borzenkov at 2023-01-30T14:02:04+04:00 Rename () to Unit, Rename (,,...,,) to Tuple<n> - - - - - eb3968b5 by Ben Gamari at 2023-03-10T02:32:43-05:00 Bump versions for ghc-9.6 release - - - - - 4aeead36 by Adam Gundry at 2023-03-23T13:53:47+01:00 Adapt to warning categories changes - - - - - 642d8d60 by sheaf at 2023-03-29T13:35:56+02:00 Adapt to record field refactor This commit adapts to the changes in GHC MR !8686, which overhauls the treatment of record fields in the renamer, adding separate record field namespaces and entirely removing the GreName datatype. - - - - - ac8d4333 by doyougnu at 2023-03-29T11:11:44-04:00 Update UniqMap API - - - - - 7866fc86 by Ben Orchard at 2023-04-20T11:29:33+02:00 update classify with new tokens - - - - - ffcdd683 by Finley McIlwaine at 2023-04-24T09:36:18-06:00 Remove index-state - - - - - 05b70982 by Finley McIlwaine at 2023-04-26T08:16:31-06:00 `renameInterface` space leak fixes - Change logic for accumulation of names for which link warnings will be generated - Change handling of `--ignore-link-symbol` to allow qualified and unqualified names. Added to CHANGES.md - Some formatting changes and comments here and there - - - - - e5697d7c by Finley McIlwaine at 2023-04-27T18:46:36-06:00 Messy things - ghc-debug dependency and instrumentation - cabal.project custom with-compiler - hie.yaml files - traces and such - - - - - 0b8ef80b by Finley McIlwaine at 2023-05-02T18:08:52-06:00 Stop retaining GRE closures GRE closures should never be necessary to Haddock, so we never want to keep them on the heap. Despite that, they are retained by a lot of the data structures that Haddock makes use of. - Attempt to fix that situation by adding strictness to various computations and pruning the `ifaceInstances` field of `Interface` to a much thinner data type. - Removes the `ifaceFamInstances` field, as it was never used. - Move some of the attach instances types (e.g. `SimpleType`) to the types module - - - - - 8bda991b by Finley McIlwaine at 2023-05-08T16:07:51-06:00 Memory usage fixes - Refactor `ifaceDeclMap` to drastically reduce memory footprint. We no longer store all declarations associated with a given name, since we only cared to determine if the only declaration associated with a name was a value declaration. Change the `DeclMap` type to better reflect this. - Drop pre-renaming export items after the renaming step. Since the Hoogle backend used the pre-renamed export items, this isn't trivial. We now generate Hoogle output for exported declarations during the renaming step (if Hoogle output /should/ be generated), and store that with the renamed export item. - Slightly refactor Hoogle backend to handle the above change and allow for early generation of Hoogle output. - Remove the `ifaceRnDocMap` and `ifaceRnArgMap` fields of the `Interface` type, as they were never used. - Remove some unnecessary strictness - Remove a lot of dead code from `Syb` module - - - - - 1611ac0c by Finley McIlwaine at 2023-05-09T11:51:57-06:00 Unify ErrMsgM and IfM - Delete ErrMsgM, stop accumulating warnings in a writer - Make IfM a state monad, print warnings directly to stdout, move IfM type into types module - Drop ErrMsg = String synonym - Unset IORefs from plugin after they are read, preventing unnecessary retention of interfaces - - - - - 42d696ab by Finley McIlwaine at 2023-05-11T15:52:07-06:00 Thunk leak fixes The strictness introduced in this commit was motivated by observing thunk leaks in the eventlog2html output. - Refactor attach instances list comprehension to avoid large intermediate thunks - Refactor some HTML backend list comprehensions to avoid large intermediate thunks - Avoid thunks accumulating in documentation types or documentation parser - A lot of orphan NFData instances to allow us to force documentation values - - - - - 68561cf6 by Finley McIlwaine at 2023-05-11T17:02:10-06:00 Remove GHC debug dep - - - - - 10519e3d by Finley McIlwaine at 2023-05-15T12:40:48-06:00 Force HIE file path Removes a potential retainer of `ModSummary`s - - - - - 1e4a6ec6 by Finley McIlwaine at 2023-05-15T14:20:34-06:00 Re-add index-state, with-compiler, delete hie.yamls - - - - - a2363fe9 by Hécate Moonlight at 2023-05-15T22:45:16+02:00 Merge pull request haskell/haddock#1594 from FinleyMcIlwaine/finley/ghc-9.6-mem-fixes Reduce memory usage - - - - - e8a78383 by Finley McIlwaine at 2023-05-17T12:19:16-06:00 Merge branch ghc-9.6 into ghc-head - - - - - 22e25581 by Finley McIlwaine at 2023-05-17T12:20:23-06:00 Merge branch 'ghc-head' of gitlab.haskell.org:ghc/haddock into ghc-head - - - - - 41bbf0df by Bartłomiej Cieślar at 2023-05-24T08:57:58+02:00 changes to the WarningTxt cases Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - c686ba9b by Hécate Moonlight at 2023-06-01T14:03:02-06:00 Port the remains of Hi-Haddock - - - - - 9d8a85fd by Hécate Moonlight at 2023-06-01T14:03:06-06:00 Stdout for tests - - - - - 36331d07 by Finley McIlwaine at 2023-06-01T14:06:02-06:00 Formatting, organize imports - - - - - a06059b1 by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix empty context confusion in Convert module - - - - - 379346ae by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix associated type families in Hoogle output - - - - - fc6ea7ed by Finley McIlwaine at 2023-06-01T14:06:04-06:00 Fix test refs Accept several changes in Hoogle tests: Pretty printing logic no longer prints the `(Proxy (Proxy (...))` chain in Bug806 with parentheses. Since this test was only meant to verify that line breaks do not occur, accept the change. `tyThingToLHsDecl` is called for class and data declarations, which ends up "synifying" the type variables and giving unlifted types kind signatures. As a result, type variables of kind `Type -> Type` are now printed with kind signatures in Hoogle output. This could be changed by manually drop kind signatures from class variables in the Hoogle backend if the behavior is deemed unacceptable. Sometimes subordinate declarations are exported separate from their parent declarations (e.g. record selectors). In this case, a type signature is cobbled together for the export item in `extractDecl`. Since this type signature is very manually constructed, it may lack kind signatures of decls constructed from `tyThingToLHsDecl`. An example of this is the `type-sigs` Hoogle test. Change `*` to `Type` in Hoogle test refs. I don't think this will break Hoogle behavior, since it appears to not consider type signatures in search. I have not fully verified this. - - - - - e14b7e58 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix LaTeX backend test refs Changes to GHC pretty printing code have resulted in some differences to Haddock's LaTeX output. - Type variables are printed explicitly quantified in the LinearTypes test - Wildcard types in type family equations are now printed numbered, e.g. _1 _2, in the TypeFamilies3 test - Combined signatures in DefaultSignatures test are now documented as separate signatures - - - - - 41b5b296 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and test source updates - Stop using kind `*` in html test sources - Add TypeOperators where necessary to avoid warnings and future errors - Rename some test modules to match their module names - - - - - c640e2a2 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Fix missing deprecation warnings on record fields `lookupOccEnv` was used to resolve `OccNames` with warnings attached, but it doesn't look in the record field namespace. Thus, if a record field had a warning attached, it would not resolve and the warning map would not include it. This commit fixes by using `lookupOccEnv_WithFields` instead. - - - - - fad0c462 by Finley McIlwaine at 2023-06-01T14:06:05-06:00 Formatting and some comments - - - - - 751fd023 by Finley McIlwaine at 2023-06-01T14:11:41-06:00 Accept HTML test diffs All diffs now boil down to the expected differences resulting from declarations being reified from TyThings in hi-haddock. Surface syntax now has much less control over the syntax used in the documentation. - - - - - d835c845 by Finley McIlwaine at 2023-06-01T14:11:45-06:00 Adapt to new load' type - - - - - dcf776c4 by Finley McIlwaine at 2023-06-01T14:13:13-06:00 Update mkWarningMap and moduleWarning - - - - - 8e8432fd by Finley McIlwaine at 2023-06-01T14:28:54-06:00 Revert load' changes - - - - - aeb2982c by Finley McIlwaine at 2023-06-01T14:40:24-06:00 Accept change to Instances test in html-test Link to Data.Tuple instead of GHC.Tuple.Prim - - - - - 8adfdbac by Finley McIlwaine at 2023-06-01T15:53:17-06:00 Reset ghc dep to ^>= 9.6 - - - - - 2b1ce93d by Finley McIlwaine at 2023-06-06T07:50:04-06:00 Update CHANGES.md, user guide, recomp avoidance * Add --trace-args flag for tracing arguments received to standard output * Avoid recompiling due to changes in optimization flags * Update users guide and changes.md - - - - - f3da6676 by Finley McIlwaine at 2023-06-06T14:12:56-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - bf36c467 by Matthew Pickering at 2023-06-07T10:16:09+01:00 Revert back to e16e20d592a6f5d9ed1af17b77fafd6495242345 Neither of these MRs are ready to land yet which causes issues with other MRs which are ready to land and need haddock changes. - - - - - 421510a9 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 atSign has no unicode variant Prior to this change, atSign was defined as follows: atSign unicode = text (if unicode then "@" else "@") Yes, this is the same symbol '\64' and not your font playing tricks on you. Now we define: atSign = char '@' Both the LaTeX and the Xhtml backend are updated accordingly. - - - - - 3785c276 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 LaTeX: fix printing of type variable bindings Consider this type signature: kindOf :: forall {k} (a :: k). Proxy a -> Proxy k Prior to this fix, the LaTeX backend rendered it like this: kindOf :: forall k a. Proxy a -> Proxy k Now we preserve explicit specificity and kind annotations. - - - - - 0febf3a8 by Vladislav Zavialov at 2023-06-07T09:36:30+00:00 Add support for invisible binders in type declarations - - - - - 13e33bb3 by Finley McIlwaine at 2023-06-08T07:51:59-06:00 Add "Avoiding Recompilation" section to docs This section is a bit of a WIP due to the unstable nature of hi-haddock and the lack of tooling supporting it, but its a good start. - - - - - 3e5340ce by Finley McIlwaine at 2023-06-08T07:54:27-06:00 Add note about stubdir to recompilation docs - - - - - db7e84dc by Finley at 2023-06-08T08:11:03-06:00 Merge pull request haskell/haddock#1597 from haskell/finley/hi-haddock-9.6 hi-haddock for ghc 9.6 - - - - - 4e085d17 by Finley McIlwaine at 2023-06-14T13:41:06-06:00 Replace SYB traversals - - - - - 7b39aec5 by Finley McIlwaine at 2023-06-14T14:20:17-06:00 Test ref accepts, remove unused HaddockClsInst - - - - - df9c2090 by Finley McIlwaine at 2023-06-15T08:02:51-06:00 Use batchMsg for progress reporting during load With hi-haddock as is, there is an awkward silence during the load operation. This commit makes haddock use the default `batchMsg` Messager for progress reporting, and makes the default GHC verbosity level 1, so the user can see what GHC is doing. - - - - - f23679a8 by Hécate Moonlight at 2023-06-15T20:31:53+02:00 Merge pull request haskell/haddock#1600 from haskell/finley/hi-haddock-optim - - - - - a7982192 by Finley McIlwaine at 2023-06-15T15:02:16-06:00 hi-haddock squashed - - - - - c34f0c8d by Finley McIlwaine at 2023-06-15T16:22:03-06:00 Merge remote-tracking branch 'origin/ghc-9.6' into finley/hi-haddock-squashed - - - - - 40452797 by Bartłomiej Cieślar at 2023-06-16T12:26:04+02:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - e58673bf by Ben Gamari at 2023-06-16T09:33:35-04:00 Bump GHC version to 9.8 - - - - - 74bdf972 by Ben Gamari at 2023-06-16T09:36:18-04:00 Merge commit 'fcaaad06770a26d35d4aafd65772dedadf17669c' into ghc-head - - - - - 418ee3dc by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Remove NFData SourceText, IfaceWarnings updates The NFData SourceText instance is now available in GHC Handle mod_iface mi_warns now being IfaceWarnings - - - - - 62f31380 by Finley McIlwaine at 2023-06-20T15:39:05-04:00 Accept Instances.hs test output Due to ghc!10469. - - - - - a8f2fc0e by Ben Gamari at 2023-06-20T15:48:08-04:00 Test fixes for "Fix associated data family doc structure items" Associated data families were being given their own export DocStructureItems, which resulted in them being documented separately from their classes in haddocks. This commit fixes it. - - - - - cb1ac33e by Bartłomiej Cieślar at 2023-06-21T12:56:02-04:00 Changes related to MR !10283 MR !10283 changes the alternatives for WarningTxt pass. This MR reflects those changes in the haddock codebase. Signed-off-by: Bartłomiej Cieślar <bcieslar2001 at gmail.com> - - - - - 9933e10b by Ben Gamari at 2023-06-21T12:56:02-04:00 Bump GHC version to 9.8 - - - - - fe8c18b6 by Ben Gamari at 2023-06-21T15:36:29-04:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - c61a0d5b by Ben Gamari at 2023-06-21T16:10:51-04:00 Bump GHC version to 9.9 - - - - - 0c2a756e by sheaf at 2023-07-07T13:45:12+02:00 Avoid incomplete record update in Haddock Hoogle This commit avoids running into an incomplete record update warning in the Hoogle backend of Haddock. This was only noticed now, because incomplete record updates were broken in GHC 9.6. Now that they are fixed, we have to avoid running into them! - - - - - f9b952a7 by Ben Gamari at 2023-07-21T11:58:05-04:00 Bump base bound to <4.20 For GHC 9.8. - - - - - 1b27e151 by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Check for puns (see ghc#23368) - - - - - 457341fd by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Remove fake exports for (~), List, and Tuple<n> The old reasoning no longer applies, nowadays those names can be mentioned in export lists. - - - - - bf3dcddf by Vladislav Zavialov at 2023-08-02T10:42:11+00:00 Fix pretty-printing of Solo and MkSolo - - - - - 495b2241 by Matthew Pickering at 2023-09-01T13:02:07+02:00 Fix issue with duplicate reexported definitions (T23616) When a class method was reexported, it's default methods were also showing up in the generated html page. The simplest and most non-invasive fix is to not look for the default method if we are just exporting the class method.. because the backends are just showing default methods when the whole class is exported. In general it would be worthwhile to rewrite this bit of code I think as the logic and what gets included is split over `lookupDocs` and `availExportDecl` it would be clearer to combine the two. The result of lookupDocs is always just passed to availExportDecl so it seems simpler and more obvious to just write the function directly. - - - - - 6551824d by Finley McIlwaine at 2023-09-05T13:06:57-07:00 Remove fake export of `FUN` from Prelude This prevents `data FUN` from being shown at the top of the Prelude docs. Fixes \#23920 on GHC. - - - - - 9ab5a448 by Alan Zimmerman at 2023-09-08T18:26:53+01:00 Match changes in wip/az/T23885-unicode-funtycon - - - - - 4d08364e by Alan Zimmerman at 2023-10-31T19:46:45+00:00 EPA: match changes in GHC - EPA: Comments in AnchorOperation - EPA: Remove EpaEofComment - - - - - e7da0d25 by Alan Zimmerman at 2023-11-05T11:20:31+00:00 EPA: match changes in GHC, l2l cleanup - - - - - 4ceac14d by Alan Zimmerman at 2023-11-11T15:16:41+00:00 EPA: Replace Anchor with EpaLocation Match GHC - - - - - 94fb8d47 by Alan Zimmerman at 2023-11-29T18:10:26+00:00 Match GHC, No comments in EpaDelta for comments - - - - - 32d208e1 by Vladislav Zavialov at 2023-12-12T20:41:36+03:00 EPA: Match changes to LHsToken removal - - - - - eebdd316 by Apoorv Ingle at 2024-01-23T13:49:12+00:00 Changes for haskell/haddock#18324 - - - - - ae856a82 by Matthew Pickering at 2024-02-05T12:22:39+00:00 ghc-internals fallout - - - - - f8429266 by Jade at 2024-02-08T14:56:50+01:00 Adjust test for ghc MR !10993 - - - - - 6d1e2386 by Alan Zimmerman at 2024-02-13T22:00:28+03:00 EPA: Match changes to HsParTy and HsFunTy - - - - - 9c588f19 by Fendor at 2024-02-14T11:05:36+01:00 Adapt to GHC giving better Name's for linking - - - - - 778e1db3 by Andrei Borzenkov at 2024-02-16T16:12:07+03:00 Namespace specifiers for fixity signatures - - - - - 826c5b47 by Torsten Schmits at 2024-02-21T13:17:05+01:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 2cff14d5 by Ben Gamari at 2024-02-22T09:35:56-05:00 Bump bounds - - - - - f49376b3 by Ben Gamari at 2024-02-22T09:35:56-05:00 Allow `@since` annotations in export lists Here we extend Haddock to admit `@since` annotations in export lists. These can be attached to most export list items (although not subordinate lists). These annotations supercede the declaration's `@since` annotation in produced Haddocks. - - - - - b5aa93df by Ben Gamari at 2024-02-22T12:09:06-05:00 Allow package-qualified @since declarations - - - - - 8f5957f2 by Ben Gamari at 2024-02-22T13:55:19-05:00 Documentation changes from ghc-internal restructuring Previously many declarations (e.g. `Int`) were declared to have a "home" in `Prelude`. However, now Haddock instead chooses to put these in more specific homes (e.g. `Data.Int`). Given that the "home" decision is driven by heuristics and in general these changes seem quite reasonable I am accepting them: * `Int` moved from `Prelude` to `Data.Int` * `(~)` moved from `Prelude` to `Data.Type.Equality` * `Type` moved from `GHC.Types` to `Data.Kind` * `Maybe` moved from `Prelude` to `Data.Maybe` * `Bool` moved from `Prelude` to `Data.Bool` * `Ordering` moved from `Prelude` to `Data.Ord` As well, more identifiers are now hyperlinked; it's not immediately clear *why*, but it is an improvement nevertheless. - - - - - ec33fec3 by Ben Gamari at 2024-02-22T20:36:24-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 30cfd251 by Torsten Schmits at 2024-02-24T13:00:42-05:00 rename GHC.Tuple.Prim to GHC.Tuple - - - - - 732db81d by Ben Gamari at 2024-02-24T19:12:18-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 86bf7010 by Ben Gamari at 2024-02-27T19:28:10-05:00 Merge remote-tracking branch 'origin/ghc-head' into HEAD - - - - - 4b6e76b5 by Patrick at 2024-03-07T22:09:30+08:00 fix haskell/haddock#24493, with module name introduced in hieAst The accompanies haddoc PR with GHC PR https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12153 Two things have been done: 1. Link is introduced to every `X` in `module X where`, since we introduce the module name to HieAst, 2. `{-# LINE 4 "hypsrc-test/src/PositionPragmas.hs" #-}` is added before the `module PositionPragmas where` in ` hypsrc-test/ref/src/PositionPragmas.html `.It ensures only a single hieAst for file `hypsrc-test/src/PositionPragmas.hs` is generated. - - - - - 635abccc by Ben Gamari at 2024-03-08T17:09:06-05:00 Bump ghc version to 9.10 - - - - - 5b934048 by Ben Gamari at 2024-03-08T18:50:12-05:00 Bump base upper bound - - - - - b30d134e by Ben Gamari at 2024-03-08T18:50:44-05:00 Testsuite output update - - - - - 9bdf3586 by Ben Gamari at 2024-03-09T21:37:44-05:00 Merge branch 'ghc-9.10' into ghc-head - - - - - cec76981 by Ben Gamari at 2024-03-09T21:54:00-05:00 Bump GHC version to 9.11 - - - - - 4c59feb7 by Ben Gamari at 2024-03-09T22:15:01-05:00 Merge remote-tracking branch 'origin/ghc-head' into ghc-head - - - - - 0fde229f by Ben Gamari at 2024-04-04T07:04:58-04:00 testsuite: Introduce template-haskell-exports test - - - - - 0c4a9686 by Luite Stegeman at 2024-04-04T07:05:39-04:00 Update correct counter in bumpTickyAllocd - - - - - 5f085d3a by Fendor at 2024-04-04T14:47:33-04:00 Replace `SizedSeq` with `FlatBag` for flattened structure LinkedLists are notoriously memory ineffiecient when all we do is traversing a structure. As 'UnlinkedBCO' has been identified as a data structure that impacts the overall memory usage of GHCi sessions, we avoid linked lists and prefer flattened structure for storing. We introduce a new memory efficient representation of sequential elements that has special support for the cases: * Empty * Singleton * Tuple Elements This improves sharing in the 'Empty' case and avoids the overhead of 'Array' until its constant overhead is justified. - - - - - 82cfe10c by Fendor at 2024-04-04T14:47:33-04:00 Compact FlatBag array representation `Array` contains three additional `Word`'s we do not need in `FlatBag`. Move `FlatBag` to `SmallArray`. Expand the API of SmallArray by `sizeofSmallArray` and add common traversal functions, such as `mapSmallArray` and `foldMapSmallArray`. Additionally, allow users to force the elements of a `SmallArray` via `rnfSmallArray`. - - - - - 36a75b80 by Andrei Borzenkov at 2024-04-04T14:48:10-04:00 Change how invisible patterns represented in haskell syntax and TH AST (#24557) Before this patch: data ArgPat p = InvisPat (LHsType p) | VisPat (LPat p) With this patch: data Pat p = ... | InvisPat (LHsType p) ... And the same transformation in the TH land. The rest of the changes is just updating code to handle new AST and writing tests to check if it is possible to create invalid states using TH. Metric Increase: MultiLayerModulesTH_OneShot - - - - - 28009fbc by Matthew Pickering at 2024-04-04T14:48:46-04:00 Fix off by one error in seekBinNoExpand and seekBin - - - - - 9b9e031b by Ben Gamari at 2024-04-04T21:30:08-04:00 compiler: Allow more types in GHCForeignImportPrim For many, many years `GHCForeignImportPrim` has suffered from the rather restrictive limitation of not allowing any non-trivial types in arguments or results. This limitation was justified by the code generator allegely barfing in the presence of such types. However, this restriction appears to originate well before the NCG rewrite and the new NCG does not appear to have any trouble with such types (see the added `T24598` test). Lift this restriction. Fixes #24598. - - - - - 1324b862 by Alan Zimmerman at 2024-04-04T21:30:44-04:00 EPA: Use EpaLocation not SrcSpan in ForeignDecls This allows us to update them for makeDeltaAst in ghc-exactprint - - - - - 19883a23 by Alan Zimmerman at 2024-04-05T16:58:17-04:00 EPA: Use EpaLocation for RecFieldsDotDot So we can update it to a delta position in makeDeltaAst if needed. - - - - - e8724327 by Matthew Pickering at 2024-04-05T16:58:53-04:00 Remove accidentally committed test.hs - - - - - 88cb3e10 by Fendor at 2024-04-08T09:03:34-04:00 Avoid UArray when indexing is not required `UnlinkedBCO`'s can occur many times in the heap. Each `UnlinkedBCO` references two `UArray`'s but never indexes them. They are only needed to encode the elements into a `ByteArray#`. The three words for the lower bound, upper bound and number of elements are essentially unused, thus we replace `UArray` with a wrapper around `ByteArray#`. This saves us up to three words for each `UnlinkedBCO`. Further, to avoid re-allocating these words for `ResolvedBCO`, we repeat the procedure for `ResolvedBCO` and add custom `Binary` and `Show` instances. For example, agda's repl session has around 360_000 UnlinkedBCO's, so avoiding these three words is already saving us around 8MB residency. - - - - - f2cc1107 by Fendor at 2024-04-08T09:04:11-04:00 Never UNPACK `FastMutInt` for counting z-encoded `FastString`s In `FastStringTable`, we count the number of z-encoded FastStrings that exist in a GHC session. We used to UNPACK the counters to not waste memory, but live retainer analysis showed that we allocate a lot of `FastMutInt`s, retained by `mkFastZString`. We lazily compute the `FastZString`, only incrementing the counter when the `FastZString` is forced. The function `mkFastStringWith` calls `mkZFastString` and boxes the `FastMutInt`, leading to the following core: mkFastStringWith = \ mk_fs _ -> = case stringTable of { FastStringTable _ n_zencs segments# _ -> ... case ((mk_fs (I# ...) (FastMutInt n_zencs)) `cast` <Co:2> :: ...) ... Marking this field as `NOUNPACK` avoids this reboxing, eliminating the allocation of a fresh `FastMutInt` on every `FastString` allocation. - - - - - c6def949 by Matthew Pickering at 2024-04-08T16:06:51-04:00 Force in_multi to avoid retaining entire hsc_env - - - - - fbb91a63 by Fendor at 2024-04-08T16:06:51-04:00 Eliminate name thunk in declaration fingerprinting Thunk analysis showed that we have about 100_000 thunks (in agda and `-fwrite-simplified-core`) pointing to the name of the name decl. Forcing this thunk fixes this issue. The thunk created here is retained by the thunk created by forkM, it is better to eagerly force this because the result (a `Name`) is already retained indirectly via the `IfaceDecl`. - - - - - 3b7b0c1c by Alan Zimmerman at 2024-04-08T16:07:27-04:00 EPA: Use EpaLocation in WarningTxt This allows us to use an EpDelta if needed when using makeDeltaAst. - - - - - 12b997df by Alan Zimmerman at 2024-04-08T16:07:27-04:00 EPA: Move DeltaPos and EpaLocation' into GHC.Types.SrcLoc This allows us to use a NoCommentsLocation for the possibly trailing comma location in a StringLiteral. This in turn allows us to correctly roundtrip via makeDeltaAst. - - - - - 868c8a78 by Fendor at 2024-04-09T08:51:50-04:00 Prefer packed representation for CompiledByteCode As there are many 'CompiledByteCode' objects alive during a GHCi session, representing its element in a more packed manner improves space behaviour at a minimal cost. When running GHCi on the agda codebase, we find around 380 live 'CompiledByteCode' objects. Packing their respective 'UnlinkedByteCode' can save quite some pointers. - - - - - be3bddde by Alan Zimmerman at 2024-04-09T08:52:26-04:00 EPA: Capture all comments in a ClassDecl Hopefully the final fix needed for #24533 - - - - - 3d0806fc by Jade at 2024-04-10T05:39:53-04:00 Validate -main-is flag using parseIdentifier Fixes #24368 - - - - - dd530bb7 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 rts: free error message before returning Fixes a memory leak in rts/linker/PEi386.c - - - - - e008a19a by Alexis King at 2024-04-10T05:40:29-04:00 linker: Avoid linear search when looking up Haskell symbols via dlsym See the primary Note [Looking up symbols in the relevant objects] for a more in-depth explanation. When dynamically loading a Haskell symbol (typical when running a splice or GHCi expression), before this commit we would search for the symbol in all dynamic libraries that were loaded. However, this could be very inefficient when too many packages are loaded (which can happen if there are many package dependencies) because the time to lookup the would be linear in the number of packages loaded. This commit drastically improves symbol loading performance by introducing a mapping from units to the handles of corresponding loaded dlls. These handles are returned by dlopen when we load a dll, and can then be used to look up in a specific dynamic library. Looking up a given Name is now much more precise because we can get lookup its unit in the mapping and lookup the symbol solely in the handles of the dynamic libraries loaded for that unit. In one measurement, the wait time before the expression was executed went from +-38 seconds down to +-2s. This commit also includes Note [Symbols may not be found in pkgs_loaded], explaining the fallback to the old behaviour in case no dll can be found in the unit mapping for a given Name. Fixes #23415 Co-authored-by: Rodrigo Mesquita (@alt-romes) - - - - - dcfaa190 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 rts: Make addDLL a wrapper around loadNativeObj Rewrite the implementation of `addDLL` as a wrapper around the more principled `loadNativeObj` rts linker function. The latter should be preferred while the former is preserved for backwards compatibility. `loadNativeObj` was previously only available on ELF platforms, so this commit further refactors the rts linker to transform loadNativeObj_ELF into loadNativeObj_POSIX, which is available in ELF and MachO platforms. The refactor made it possible to remove the `dl_mutex` mutex in favour of always using `linker_mutex` (rather than a combination of both). Lastly, we implement `loadNativeObj` for Windows too. - - - - - 12931698 by Rodrigo Mesquita at 2024-04-10T05:40:29-04:00 Use symbol cache in internal interpreter too This commit makes the symbol cache that was used by the external interpreter available for the internal interpreter too. This follows from the analysis in #23415 that suggests the internal interpreter could benefit from this cache too, and that there is no good reason not to have the cache for it too. It also makes it a bit more uniform to have the symbol cache range over both the internal and external interpreter. This commit also refactors the cache into a function which is used by both `lookupSymbol` and also by `lookupSymbolInDLL`, extending the caching logic to `lookupSymbolInDLL` too. - - - - - dccd3ea1 by Ben Gamari at 2024-04-10T05:40:29-04:00 testsuite: Add test for lookupSymbolInNativeObj - - - - - 1b1a92bd by Alan Zimmerman at 2024-04-10T05:41:05-04:00 EPA: Remove unnecessary XRec in CompleteMatchSig The XRec for [LIdP pass] is not needed for exact printing, remove it. - - - - - 6e18ce2b by Ben Gamari at 2024-04-12T08:16:09-04:00 users-guide: Clarify language extension documentation Over the years the users guide's language extension documentation has gone through quite a few refactorings. In the process some of the descriptions have been rendered non-sensical. For instance, the description of `NoImplicitPrelude` actually describes the semantics of `ImplicitPrelude`. To fix this we: * ensure that all extensions are named in their "positive" sense (e.g. `ImplicitPrelude` rather than `NoImplicitPrelude`). * rework the documentation to avoid flag-oriented wording like "enable" and "disable" * ensure that the polarity of the documentation is consistent with reality. Fixes #23895. - - - - - a933aff3 by Zubin Duggal at 2024-04-12T08:16:45-04:00 driver: Make `checkHomeUnitsClosed` faster The implementation of `checkHomeUnitsClosed` was traversing every single path in the unit dependency graph - this grows exponentially and quickly grows to be infeasible on larger unit dependency graphs. Instead we replace this with a faster implementation which follows from the specificiation of the closure property - there is a closure error if there are units which are both are both (transitively) depended upon by home units and (transitively) depend on home units, but are not themselves home units. To compute the set of units required for closure, we first compute the closure of the unit dependency graph, then the transpose of this closure, and find all units that are reachable from the home units in the transpose of the closure. - - - - - 23c3e624 by Andreas Klebinger at 2024-04-12T08:17:21-04:00 RTS: Emit warning when -M < -H Fixes #24487 - - - - - d23afb8c by Ben Gamari at 2024-04-12T08:17:56-04:00 testsuite: Add broken test for CApiFFI with -fprefer-bytecode See #24634. - - - - - a4bb3a51 by Ben Gamari at 2024-04-12T08:18:32-04:00 base: Deprecate GHC.Pack As proposed in #21461. Closes #21540. - - - - - 55eb8c98 by Ben Gamari at 2024-04-12T08:19:08-04:00 ghc-internal: Fix mentions of ghc-internal in deprecation warnings Closes #24609. - - - - - b0fbd181 by Ben Gamari at 2024-04-12T08:19:44-04:00 rts: Implement set_initial_registers for AArch64 Fixes #23680. - - - - - 14c9ec62 by Ben Gamari at 2024-04-12T08:20:20-04:00 ghcup-metadata: Use Debian 9 binaries on Ubuntu 16, 17 Closes #24646. - - - - - 35a1621e by Ben Gamari at 2024-04-12T08:20:55-04:00 Bump unix submodule to 2.8.5.1 Closes #24640. - - - - - a1c24df0 by Finley McIlwaine at 2024-04-12T08:21:31-04:00 Correct default -funfolding-use-threshold in docs - - - - - 0255d03c by Oleg Grenrus at 2024-04-12T08:22:07-04:00 FastString is a __Modified__ UTF-8 - - - - - c3489547 by Matthew Pickering at 2024-04-12T13:13:44-04:00 rts: Improve tracing message when nursery is resized It is sometimes more useful to know how much bigger or smaller the nursery got when it is resized. In particular I am trying to investigate situations where we end up with fragmentation due to the nursery (#24577) - - - - - 5e4f4ba8 by Simon Peyton Jones at 2024-04-12T13:14:20-04:00 Don't generate wrappers for `type data` constructors with StrictData Previously, the logic for checking if a data constructor needs a wrapper or not would take into account whether the constructor's fields have explicit strictness (e.g., `data T = MkT !Int`), but the logic would _not_ take into account whether `StrictData` was enabled. This meant that something like `type data T = MkT Int` would incorrectly generate a wrapper for `MkT` if `StrictData` was enabled, leading to the horrible errors seen in #24620. To fix this, we disable generating wrappers for `type data` constructors altogether. Fixes #24620. Co-authored-by: Ryan Scott <ryan.gl.scott at gmail.com> - - - - - dbdf1995 by Alex Mason at 2024-04-15T15:28:26+10:00 Implements MO_S_Mul2 and MO_U_Mul2 using the UMULH, UMULL and SMULH instructions for AArch64 Also adds a test for MO_S_Mul2 - - - - - 42bd0407 by Teo Camarasu at 2024-04-16T20:06:39-04:00 Make template-haskell a stage1 package Promoting template-haskell from a stage0 to a stage1 package means that we can much more easily refactor template-haskell. We implement this by duplicating the in-tree `template-haskell`. A new `template-haskell-next` library is autogenerated to mirror `template-haskell` `stage1:ghc` to depend on the new interface of the library including the `Binary` instances without adding an explicit dependency on `template-haskell`. This is controlled by the `bootstrap-th` cabal flag When building `template-haskell` modules as part of this vendoring we do not have access to quote syntax, so we cannot use variable quote notation (`'Just`). So we either replace these with hand-written `Name`s or hide the code behind CPP. We can remove the `th_hack` from hadrian, which was required when building stage0 packages using the in-tree `template-haskell` library. For more details see Note [Bootstrapping Template Haskell]. Resolves #23536 Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> Co-Authored-By: Matthew Craven <5086-clyring at users.noreply.gitlab.haskell.org> - - - - - 3d973e47 by Ben Gamari at 2024-04-16T20:07:15-04:00 Bump parsec submodule to 3.1.17.0 - - - - - 9d38bfa0 by Simon Peyton Jones at 2024-04-16T20:07:51-04:00 Clone CoVars in CorePrep This MR addresses #24463. It's all explained in the new Note [Cloning CoVars and TyVars] - - - - - 0fe2b410 by Andreas Klebinger at 2024-04-16T20:08:27-04:00 NCG: Fix a bug where we errounously removed a required jump instruction. Add a new method to the Instruction class to check if we can eliminate a jump in favour of fallthrough control flow. Fixes #24507 - - - - - 9f99126a by Teo Camarasu at 2024-04-16T20:09:04-04:00 Fix documentation preview from doc-tarball job - Include all the .html files and assets in the job artefacts - Include all the .pdf files in the job artefacts - Mark the artefact as an "exposed" artefact meaning it turns up in the UI. Resolves #24651 - - - - - 3a0642ea by Ben Gamari at 2024-04-16T20:09:39-04:00 rts: Ignore EINTR while polling in timerfd itimer implementation While the RTS does attempt to mask signals, it may be that a foreign library unmasks them. This previously caused benign warnings which we now ignore. See #24610. - - - - - 9a53cd3f by Alan Zimmerman at 2024-04-16T20:10:15-04:00 EPA: Add additional comments field to AnnsModule This is used in exact printing to store comments coming after the `where` keyword but before any comments allocated to imports or decls. It is used in ghc-exactprint, see https://github.com/alanz/ghc-exactprint/commit/44bbed311fd8f0d053053fef195bf47c17d34fa7 - - - - - e5c43259 by Bryan Richter at 2024-04-16T20:10:51-04:00 Remove unrunnable FreeBSD CI jobs FreeBSD runner supply is inelastic. Currently there is only one, and it's unavailable because of a hardware issue. - - - - - 914eb49a by Ben Gamari at 2024-04-16T20:11:27-04:00 rel-eng: Fix mktemp usage in recompress-all We need a temporary directory, not a file. - - - - - f30e4984 by Teo Camarasu at 2024-04-16T20:12:03-04:00 Fix ghc API link in docs/index.html This was missing part of the unit ID meaning it would 404. Resolves #24674 - - - - - d7a3d6b5 by Ben Gamari at 2024-04-16T20:12:39-04:00 template-haskell: Declare TH.Lib.Internal as not-home Rather than `hide`. Closes #24659. - - - - - 5eaa46e7 by Matthew Pickering at 2024-04-19T02:14:55-04:00 testsuite: Rename isCross() predicate to needsTargetWrapper() isCross() was a misnamed because it assumed that all cross targets would provide a target wrapper, but the two most common cross targets (javascript, wasm) don't need a target wrapper. Therefore we rename this predicate to `needsTargetWrapper()` so situations in the testsuite where we can check whether running executables requires a target wrapper or not. - - - - - 55a9d699 by Simon Peyton Jones at 2024-04-19T02:15:32-04:00 Do not float HNFs out of lambdas This MR adjusts SetLevels so that it is less eager to float a HNF (lambda or constructor application) out of a lambda, unless it gets to top level. Data suggests that this change is a small net win: * nofib bytes-allocated falls by -0.09% (but a couple go up) * perf/should_compile bytes-allocated falls by -0.5% * perf/should_run bytes-allocated falls by -0.1% See !12410 for more detail. When fiddling elsewhere, I also found that this patch had a huge positive effect on the (very delicate) test perf/should_run/T21839r But that improvement doesn't show up in this MR by itself. Metric Decrease: MultiLayerModulesRecomp T15703 parsing001 - - - - - f0701585 by Alan Zimmerman at 2024-04-19T02:16:08-04:00 EPA: Fix comments in mkListSyntaxTy0 Also extend the test to confirm. Addresses #24669, 1 of 4 - - - - - b01c01d4 by Serge S. Gulin at 2024-04-19T02:16:51-04:00 JS: set image `x86_64-linux-deb11-emsdk-closure` for build - - - - - c90c6039 by Alan Zimmerman at 2024-04-19T02:17:27-04:00 EPA: Provide correct span for PatBind And remove unused parameter in checkPatBind Contributes to #24669 - - - - - bee54c24 by Krzysztof Gogolewski at 2024-04-19T11:13:00+02:00 Update quantification order following GHC haskell/haddock#23764 - - - - - 2814eb89 by Ben Gamari at 2024-04-19T18:57:05+02:00 hypsrc-test: Fix output of PositionPragmas.html - - - - - 26036f96 by Alan Zimmerman at 2024-04-19T13:11:08-04:00 EPA: Fix span for PatBuilderAppType Include the location of the prefix @ in the span for InVisPat. Also removes unnecessary annotations from HsTP. Contributes to #24669 - - - - - dba03aab by Matthew Craven at 2024-04-19T13:11:44-04:00 testsuite: Give the pre_cmd for mhu-perf more time - - - - - d31fbf6c by Krzysztof Gogolewski at 2024-04-19T21:04:09-04:00 Fix quantification order for a `op` b and a %m -> b Fixes #23764 Implements https://github.com/ghc-proposals/ghc-proposals/blob/master/proposals/0640-tyop-quantification-order.rst Updates haddock submodule. - - - - - 385cd1c4 by Sebastian Graf at 2024-04-19T21:04:45-04:00 Make `seq#` a magic Id and inline it in CorePrep (#24124) We can save much code and explanation in Tag Inference and StgToCmm by making `seq#` a known-key Magic Id in `GHC.Internal.IO` and inline this definition in CorePrep. See the updated `Note [seq# magic]`. I also implemented a new `Note [Flatten case-bind]` to get better code for otherwise nested case scrutinees. I renamed the contructors of `ArgInfo` to use an `AI` prefix in order to resolve the clash between `type CpeApp = CoreExpr` and the data constructor of `ArgInfo`, as well as fixed typos in `Note [CorePrep invariants]`. Fixes #24252 and #24124. - - - - - 275e41a9 by Jade at 2024-04-20T11:10:40-04:00 Put the newline after errors instead of before them This mainly has consequences for GHCi but also slightly alters how the output of GHC on the commandline looks. Fixes: #22499 - - - - - dd339c7a by Teo Camarasu at 2024-04-20T11:11:16-04:00 Remove unecessary stage0 packages Historically quite a few packages had to be stage0 as they depended on `template-haskell` and that was stage0. In #23536 we made it so that was no longer the case. This allows us to remove a bunch of packages from this list. A few still remain. A new version of `Win32` is required by `semaphore-compat`. Including `Win32` in the stage0 set requires also including `filepath` because otherwise Hadrian's dependency logic gets confused. Once our boot compiler has a newer version of `Win32` all of these will be able to be dropped. Resolves #24652 - - - - - 2f8e3a25 by Alan Zimmerman at 2024-04-20T11:11:52-04:00 EPA: Avoid duplicated comments in splice decls Contributes to #24669 - - - - - c70b9ddb by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: fix typos and namings (fixes #24602) You may noted that I've also changed term of ``` , global "h$vt_double" ||= toJExpr IntV ``` See "IntV" and ``` WaitReadOp -> \[] [fd] -> pure $ PRPrimCall $ returnS (app "h$waidRead" [fd]) ``` See "h$waidRead" - - - - - 3db54f9b by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: trivial checks for variable presence (fixes #24602) - - - - - 777f108f by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: fs module imported twice (by emscripten and by ghc-internal). ghc-internal import wrapped in a closure to prevent conflict with emscripten (fixes #24602) Better solution is to use some JavaScript module system like AMD, CommonJS or even UMD. It will be investigated at other issues. At first glance we should try UMD (See https://github.com/umdjs/umd) - - - - - a45a5712 by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: thread.js requires h$fds and h$fdReady to be declared for static code analysis, minimal code copied from GHCJS (fixes #24602) I've just copied some old pieces of GHCJS from publicly available sources (See https://github.com/Taneb/shims/blob/a6dd0202dcdb86ad63201495b8b5d9763483eb35/src/io.js#L607). Also I didn't put details to h$fds. I took minimal and left only its object initialization: `var h$fds = {};` - - - - - ad90bf12 by Serge S. Gulin at 2024-04-21T16:33:43+03:00 JS: heap and stack overflows reporting defined as js hard failure (fixes #24602) These errors were treated as a hard failure for browser application. The fix is trivial: just throw error. - - - - - 5962fa52 by Serge S. Gulin at 2024-04-21T16:33:44+03:00 JS: Stubs for code without actual implementation detected by Google Closure Compiler (fixes #24602) These errors were fixed just by introducing stubbed functions with throw for further implementation. - - - - - a0694298 by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Add externs to linker (fixes #24602) After enabling jsdoc and built-in google closure compiler types I was needed to deal with the following: 1. Define NodeJS-environment types. I've just copied minimal set of externs from semi-official repo (see https://github.com/externs/nodejs/blob/6c6882c73efcdceecf42e7ba11f1e3e5c9c041f0/v8/nodejs.js#L8). 2. Define Emscripten-environment types: `HEAP8`. Emscripten already provides some externs in our code but it supposed to be run in some module system. And its definitions do not work well in plain bundle. 3. We have some functions which purpose is to add to functions some contextual information via function properties. These functions should be marked as `modifies` to let google closure compiler remove calls if these functions are not used actually by call graph. Such functions are: `h$o`, `h$sti`, `h$init_closure`, `h$setObjInfo`. 4. STG primitives such as registries and stuff from `GHC.StgToJS`. `dXX` properties were already present at externs generator function but they are started from `7`, not from `1`. This message is related: `// fixme does closure compiler bite us here?` - - - - - e58bb29f by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: added both tests: for size and for correctness (fixes #24602) By some reason MacOS builds add to stderr messages like: Ignoring unexpected archive entry: __.SYMDEF ... However I left stderr to `/dev/null` for compatibility with linux CI builds. - - - - - 909f3a9c by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Disable js linker warning for empty symbol table to make js tests running consistent across environments - - - - - 83eb10da by Serge S. Gulin at 2024-04-21T16:34:07+03:00 JS: Add special preprocessor for js files due of needing to keep jsdoc comments (fixes #24602) Our js files have defined google closure compiler types at jsdoc entries but these jsdoc entries are removed by cpp preprocessor. I considered that reusing them in javascript-backend would be a nice thing. Right now haskell processor uses `-traditional` option to deal with comments and `//` operators. But now there are following compiler options: `-C` and `-CC`. You can read about them at GCC (see https://gcc.gnu.org/onlinedocs/gcc/Preprocessor-Options.html#index-CC) and CLang (see https://clang.llvm.org/docs/ClangCommandLineReference.html#cmdoption-clang-CC). It seems that `-CC` works better for javascript jsdoc than `-traditional`. At least it leaves `/* ... */` comments w/o changes. - - - - - e1cf8dc2 by brandon s allbery kf8nh at 2024-04-22T03:48:26-04:00 fix link in CODEOWNERS It seems that our local Gitlab no longer has documentation for the `CODEOWNERS` file, but the master documentation still does. Use that instead. - - - - - a27c6a49 by Fendor at 2024-04-22T10:13:03+02:00 Adapt to UserData split - - - - - 1efc5a7a by Fendor at 2024-04-22T10:13:03+02:00 Adapt to BinHandle split - - - - - 593f4e04 by Fendor at 2024-04-23T10:19:14-04:00 Add performance regression test for '-fwrite-simplified-core' - - - - - 1ba39b05 by Fendor at 2024-04-23T10:19:14-04:00 Typecheck corebindings lazily during bytecode generation This delays typechecking the corebindings until the bytecode generation happens. We also avoid allocating a thunk that is retained by `unsafeInterleaveIO`. In general, we shouldn't retain values of the hydrated `Type`, as not evaluating the bytecode object keeps it alive. It is better if we retain the unhydrated `IfaceType`. See Note [Hydrating Modules] - - - - - e916fc92 by Alan Zimmerman at 2024-04-23T10:19:50-04:00 EPA: Keep comments in a CaseAlt match The comments now live in the surrounding location, not inside the Match. Make sure we keep them. Closes #24707 - - - - - d2b17f32 by Cheng Shao at 2024-04-23T15:01:22-04:00 driver: force merge objects when building dynamic objects This patch forces the driver to always merge objects when building dynamic objects even when ar -L is supported. It is an oversight of !8887: original rationale of that patch is favoring the relatively cheap ar -L operation over object merging when ar -L is supported, which makes sense but only if we are building static objects! Omitting check for whether we are building dynamic objects will result in broken .so files with undefined reference errors at executable link time when building GHC with llvm-ar. Fixes #22210. - - - - - 209d09f5 by Julian Ospald at 2024-04-23T15:02:03-04:00 Allow non-absolute values for bootstrap GHC variable Fixes #24682 - - - - - 3fff0977 by Matthew Pickering at 2024-04-23T15:02:38-04:00 Don't depend on registerPackage function in Cabal More recent versions of Cabal modify the behaviour of libAbiHash which breaks our usage of registerPackage. It is simpler to inline the part of registerPackage that we need and avoid any additional dependency and complication using the higher-level function introduces. - - - - - c62dc317 by Cheng Shao at 2024-04-25T01:32:02-04:00 ghc-bignum: remove obsolete ln script This commit removes an obsolete ln script in ghc-bignum/gmp. See 060251c24ad160264ae8553efecbb8bed2f06360 for its original intention, but it's been obsolete for a long time, especially since the removal of the make build system. Hence the house cleaning. - - - - - 6399d52b by Cheng Shao at 2024-04-25T01:32:02-04:00 ghc-bignum: update gmp to 6.3.0 This patch bumps the gmp-tarballs submodule and updates gmp to 6.3.0. The tarball format is now xz, and gmpsrc.patch has been patched into the tarball so hadrian no longer needs to deal with patching logic when building in-tree GMP. - - - - - 65b4b92f by Cheng Shao at 2024-04-25T01:32:02-04:00 hadrian: remove obsolete Patch logic This commit removes obsolete Patch logic from hadrian, given we no longer need to patch the gmp tarball when building in-tree GMP. - - - - - 71f28958 by Cheng Shao at 2024-04-25T01:32:02-04:00 autoconf: remove obsolete patch detection This commit removes obsolete deletection logic of the patch command from autoconf scripts, given we no longer need to patch anything in the GHC build process. - - - - - daeda834 by Sylvain Henry at 2024-04-25T01:32:43-04:00 JS: correctly handle RUBBISH literals (#24664) - - - - - 8a06ddf6 by Matthew Pickering at 2024-04-25T11:16:16-04:00 Linearise ghc-internal and base build This is achieved by requesting the final package database for ghc-internal, which mandates it is fully built as a dependency of configuring the `base` package. This is at the expense of cross-package parrallelism between ghc-internal and the base package. Fixes #24436 - - - - - 94da9365 by Andrei Borzenkov at 2024-04-25T11:16:54-04:00 Fix tuple puns renaming (24702) Move tuple renaming short cutter from `isBuiltInOcc_maybe` to `isPunOcc_maybe`, so we consider incoming module. I also fixed some hidden bugs that raised after the change was done. - - - - - fa03b1fb by Fendor at 2024-04-26T18:03:13-04:00 Refactor the Binary serialisation interface The goal is simplifiy adding deduplication tables to `ModIface` interface serialisation. We identify two main points of interest that make this difficult: 1. UserData hardcodes what `Binary` instances can have deduplication tables. Moreover, it heavily uses partial functions. 2. GHC.Iface.Binary hardcodes the deduplication tables for 'Name' and 'FastString', making it difficult to add more deduplication. Instead of having a single `UserData` record with fields for all the types that can have deduplication tables, we allow to provide custom serialisers for any `Typeable`. These are wrapped in existentials and stored in a `Map` indexed by their respective `TypeRep`. The `Binary` instance of the type to deduplicate still needs to explicitly look up the decoder via `findUserDataReader` and `findUserDataWriter`, which is no worse than the status-quo. `Map` was chosen as microbenchmarks indicate it is the fastest for a small number of keys (< 10). To generalise the deduplication table serialisation mechanism, we introduce the types `ReaderTable` and `WriterTable` which provide a simple interface that is sufficient to implement a general purpose deduplication mechanism for `writeBinIface` and `readBinIface`. This allows us to provide a list of deduplication tables for serialisation that can be extended more easily, for example for `IfaceTyCon`, see the issue https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for more motivation. In addition to this refactoring, we split `UserData` into `ReaderUserData` and `WriterUserData`, to avoid partial functions and reduce overall memory usage, as we need fewer mutable variables. Bump haddock submodule to accomodate for `UserData` split. ------------------------- Metric Increase: MultiLayerModulesTH_Make MultiLayerModulesRecomp T21839c ------------------------- - - - - - bac57298 by Fendor at 2024-04-26T18:03:13-04:00 Split `BinHandle` into `ReadBinHandle` and `WriteBinHandle` A `BinHandle` contains too much information for reading data. For example, it needs to keep a `FastMutInt` and a `IORef BinData`, when the non-mutable variants would suffice. Additionally, this change has the benefit that anyone can immediately tell whether the `BinHandle` is used for reading or writing. Bump haddock submodule BinHandle split. - - - - - 4d6394dd by Simon Peyton Jones at 2024-04-26T18:03:49-04:00 Fix missing escaping-kind check in tcPatSynSig Note [Escaping kind in type signatures] explains how we deal with escaping kinds in type signatures, e.g. f :: forall r (a :: TYPE r). a where the kind of the body is (TYPE r), but `r` is not in scope outside the forall-type. I had missed this subtlety in tcPatSynSig, leading to #24686. This MR fixes it; and a similar bug in tc_top_lhs_type. (The latter is tested by T24686a.) - - - - - 981c2c2c by Alan Zimmerman at 2024-04-26T18:04:25-04:00 EPA: check-exact: check that the roundtrip reproduces the source Closes #24670 - - - - - a8616747 by Andrew Lelechenko at 2024-04-26T18:05:01-04:00 Document that setEnv is not thread-safe - - - - - 1e41de83 by Bryan Richter at 2024-04-26T18:05:37-04:00 CI: Work around frequent Signal 9 errors - - - - - a6d5f9da by Naïm Favier at 2024-04-27T17:52:40-04:00 ghc-internal: add MonadFix instance for (,) Closes https://gitlab.haskell.org/ghc/ghc/-/issues/24288, implements CLC proposal https://github.com/haskell/core-libraries-committee/issues/238. Adds a MonadFix instance for tuples, permitting value recursion in the "native" writer monad and bringing consistency with the existing instance for transformers's WriterT (and, to a lesser extent, for Solo). - - - - - 64feadcd by Rodrigo Mesquita at 2024-04-27T17:53:16-04:00 bindist: Fix xattr cleaning The original fix (725343aa) was incorrect because it used the shell bracket syntax which is the quoting syntax in autoconf, making the test for existence be incorrect and therefore `xattr` was never run. Fixes #24554 - - - - - e2094df3 by damhiya at 2024-04-28T23:52:00+09:00 Make read accepts binary integer formats CLC proposal : https://github.com/haskell/core-libraries-committee/issues/177 - - - - - c62239b7 by Sylvain Henry at 2024-04-29T10:35:00+02:00 Fix tests for T22229 - - - - - 1c2fd963 by Alan Zimmerman at 2024-04-29T23:17:00-04:00 EPA: Preserve comments in Match Pats Closes #24708 Closes #24715 Closes #24734 - - - - - 4189d17e by Sylvain Henry at 2024-04-29T23:17:42-04:00 LLVM: better unreachable default destination in Switch (#24717) See added note. Co-authored-by: Siddharth Bhat <siddu.druid at gmail.com> - - - - - a3725c88 by Cheng Shao at 2024-04-29T23:18:20-04:00 ci: enable wasm jobs for MRs with wasm label This patch enables wasm jobs for MRs with wasm label. Previously the wasm label didn't actually have any effect on the CI pipeline, and full-ci needed to be applied to run wasm jobs which was a waste of runners when working on the wasm backend, hence the fix here. - - - - - 702f7964 by Matthew Pickering at 2024-04-29T23:18:56-04:00 Make interface files and object files depend on inplace .conf file A potential fix for #24737 - - - - - 728af21e by Cheng Shao at 2024-04-30T05:30:23-04:00 utils: remove obsolete vagrant scripts Vagrantfile has long been removed in !5288. This commit further removes the obsolete vagrant scripts in the tree. - - - - - 36f2c342 by Cheng Shao at 2024-04-30T05:31:00-04:00 Update autoconf scripts Scripts taken from autoconf 948ae97ca5703224bd3eada06b7a69f40dd15a02 - - - - - ecbf22a6 by Ben Gamari at 2024-04-30T05:31:36-04:00 ghcup-metadata: Drop output_name field This is entirely redundant to the filename of the URL. There is no compelling reason to name the downloaded file differently from its source. - - - - - c56d728e by Zubin Duggal at 2024-04-30T22:45:09-04:00 testsuite: Handle exceptions in framework_fail when testdir is not initialised When `framework_fail` is called before initialising testdir, it would fail with an exception reporting the testdir not being initialised instead of the actual failure. Ensure we report the actual reason for the failure instead of failing in this way. One way this can manifest is when trying to run a test that doesn't exist using `--only` - - - - - d5bea4d6 by Alan Zimmerman at 2024-04-30T22:45:45-04:00 EPA: Fix range for GADT decl with sig only Closes #24714 - - - - - 4d78c53c by Sylvain Henry at 2024-05-01T17:23:06-04:00 Fix TH dependencies (#22229) Add a dependency between Syntax and Internal (via module reexport). - - - - - 37e38db4 by Sylvain Henry at 2024-05-01T17:23:06-04:00 Bump haddock submodule - - - - - ca13075c by Sylvain Henry at 2024-05-01T17:23:47-04:00 JS: cleanup to prepare for #24743 - - - - - 40026ac3 by Alan Zimmerman at 2024-05-01T22:45:07-04:00 EPA: Preserve comments for PrefixCon Preserve comments in fun (Con {- c1 -} a b) = undefined Closes #24736 - - - - - 92134789 by Hécate Moonlight at 2024-05-01T22:45:42-04:00 Correct `@since` metadata in HpcFlags It was introduced in base-4.20, not 4.22. Fix #24721 - - - - - a580722e by Cheng Shao at 2024-05-02T08:18:45-04:00 testsuite: fix req_target_smp predicate - - - - - ac9c5f84 by Andreas Klebinger at 2024-05-02T08:18:45-04:00 STM: Remove (unused)coarse grained locking. The STM code had a coarse grained locking mode guarded by #defines that was unused. This commit removes the code. - - - - - 917ef81b by Andreas Klebinger at 2024-05-02T08:18:45-04:00 STM: Be more optimistic when validating in-flight transactions. * Don't lock tvars when performing non-committal validation. * If we encounter a locked tvar don't consider it a failure. This means in-flight validation will only fail if committing at the moment of validation is *guaranteed* to fail. This prevents in-flight validation from failing spuriously if it happens in parallel on multiple threads or parallel to thread comitting. - - - - - 167a56a0 by Alan Zimmerman at 2024-05-02T08:19:22-04:00 EPA: fix span for empty \case(s) In instance SDecide Nat where SZero %~ (SSucc _) = Disproved (\case) Ensure the span for the HsLam covers the full construct. Closes #24748 - - - - - 9bae34d8 by doyougnu at 2024-05-02T15:41:08-04:00 testsuite: expand size testing infrastructure - closes #24191 - adds windows_skip, wasm_skip, wasm_arch, find_so, _find_so - path_from_ghcPkg, collect_size_ghc_pkg, collect_object_size, find_non_inplace functions to testsuite - adds on_windows and req_dynamic_ghc predicate to testsuite The design is to not make the testsuite too smart and simply offload to ghc-pkg for locations of object files and directories. - - - - - b85b1199 by Sylvain Henry at 2024-05-02T15:41:49-04:00 GHCi: support inlining breakpoints (#24712) When a breakpoint is inlined, its context may change (e.g. tyvars in scope). We must take this into account and not used the breakpoint tick index as its sole identifier. Each instance of a breakpoint (even with the same tick index) now gets a different "info" index. We also need to distinguish modules: - tick module: module with the break array (tick counters, status, etc.) - info module: module having the CgBreakInfo (info at occurrence site) - - - - - 649c24b9 by Oleg Grenrus at 2024-05-03T20:45:42-04:00 Expose constructors of SNat, SChar and SSymbol in ghc-internal - - - - - d603f199 by Mikolaj Konarski at 2024-05-03T20:46:19-04:00 Add DCoVarSet to PluginProv (!12037) - - - - - ba480026 by Serge S. Gulin at 2024-05-03T20:47:01-04:00 JS: Enable more efficient packing of string data (fixes #24706) - - - - - be1e60ee by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Track in-scope variables in ruleCheckProgram This small patch fixes #24726, by tracking in-scope variables properly in -drule-check. Not hard to do! - - - - - 58408c77 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Add a couple more HasCallStack constraints in SimpleOpt Just for debugging, no effect on normal code - - - - - 70e245e8 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Add comments to Prep.hs This documentation patch fixes a TODO left over from !12364 - - - - - e5687186 by Simon Peyton Jones at 2024-05-03T20:47:37-04:00 Use HasDebugCallStack, rather than HasCallStack - - - - - 631cefec by Cheng Shao at 2024-05-03T20:48:17-04:00 driver: always merge objects when possible This patch makes the driver always merge objects with `ld -r` when possible, and only fall back to calling `ar -L` when merge objects command is unavailable. This completely reverts !8887 and !12313, given more fixes in Cabal seems to be needed to avoid breaking certain configurations and the maintainence cost is exceeding the behefits in this case :/ - - - - - 1dacb506 by Ben Gamari at 2024-05-03T20:48:53-04:00 Bump time submodule to 1.14 As requested in #24528. ------------------------- Metric Decrease: ghc_bignum_so rts_so Metric Increase: cabal_syntax_dir rts_so time_dir time_so ------------------------- - - - - - 4941b90e by Ben Gamari at 2024-05-03T20:48:53-04:00 Bump terminfo submodule to current master - - - - - 43d48b44 by Cheng Shao at 2024-05-03T20:49:30-04:00 wasm: use scheduler.postTask() for context switch when available This patch makes use of scheduler.postTask() for JSFFI context switch when it's available. It's a more principled approach than our MessageChannel based setImmediate() implementation, and it's available in latest version of Chromium based browsers. - - - - - 08207501 by Cheng Shao at 2024-05-03T20:50:08-04:00 testsuite: give pre_cmd for mhu-perf 5x time - - - - - bf3d4db0 by Alan Zimmerman at 2024-05-03T20:50:43-04:00 EPA: Preserve comments for pattern synonym sig Closes #24749 - - - - - c49493f2 by Matthew Pickering at 2024-05-04T06:02:57-04:00 tests: Widen acceptance window for dir and so size tests These are testing things which are sometimes out the control of a GHC developer. Therefore we shouldn't fail CI if something about these dependencies change because we can't do anything about it. It is still useful to have these statistics for visualisation in grafana though. Ticket #24759 - - - - - 9562808d by Matthew Pickering at 2024-05-04T06:02:57-04:00 Disable rts_so test It has already manifested large fluctuations and destabilising CI Fixes #24762 - - - - - fc24c5cf by Ryan Scott at 2024-05-04T06:03:33-04:00 unboxedSum{Type,Data}Name: Use GHC.Types as the module Unboxed sum constructors are now defined in the `GHC.Types` module, so if you manually quote an unboxed sum (e.g., `''Sum2#`), you will get a `Name` like: ```hs GHC.Types.Sum2# ``` The `unboxedSumTypeName` function in `template-haskell`, however, mistakenly believes that unboxed sum constructors are defined in `GHC.Prim`, so `unboxedSumTypeName 2` would return an entirely different `Name`: ```hs GHC.Prim.(#|#) ``` This is a problem for Template Haskell users, as it means that they can't be sure which `Name` is the correct one. (Similarly for `unboxedSumDataName`.) This patch fixes the implementations of `unboxedSum{Type,Data}Name` to use `GHC.Types` as the module. For consistency with `unboxedTupleTypeName`, the `unboxedSumTypeName` function now uses the non-punned syntax for unboxed sums (`Sum<N>#`) as the `OccName`. Fixes #24750. - - - - - 7eab4e01 by Alan Zimmerman at 2024-05-04T16:14:55+01:00 EPA: Widen stmtslist to include last semicolon Closes #24754 - - - - - 06f7db40 by Teo Camarasu at 2024-05-05T00:19:38-04:00 doc: Fix type error in hs_try_putmvar example - - - - - af000532 by Moritz Schuler at 2024-05-05T06:30:58-04:00 Fix parsing of module names in CLI arguments closes issue #24732 - - - - - da74e9c9 by Ben Gamari at 2024-05-05T06:31:34-04:00 ghc-platform: Add Setup.hs The Hadrian bootstrapping script relies upon `Setup.hs` to drive its build. Addresses #24761. - - - - - 35d34fde by Alan Zimmerman at 2024-05-05T12:52:40-04:00 EPA: preserve comments in class and data decls Fix checkTyClHdr which was discarding comments. Closes #24755 - - - - - 03c5dfbf by Simon Peyton Jones at 2024-05-05T12:53:15-04:00 Fix a float-out error Ticket #24768 showed that the Simplifier was accidentally destroying a join point. It turned out to be that we were sending a bottoming join point to the top, accidentally abstracting over /other/ join points. Easily fixed. - - - - - adba68e7 by John Ericson at 2024-05-05T19:35:56-04:00 Substitute bindist files with Hadrian not configure The `ghc-toolchain` overhaul will eventually replace all this stuff with something much more cleaned up, but I think it is still worth making this sort of cleanup in the meantime so other untanglings and dead code cleaning can procede. I was able to delete a fair amount of dead code doing this too. `LLVMTarget_CPP` is renamed to / merged with `LLVMTarget` because it wasn't actually turned into a valid CPP identifier. (Original to 1345c7cc42c45e63ab1726a8fd24a7e4d4222467, actually.) Progress on #23966 Co-Authored-By: Sylvain Henry <hsyl20 at gmail.com> - - - - - 18f4ff84 by Alan Zimmerman at 2024-05-05T19:36:32-04:00 EPA: fix mkHsOpTyPV duplicating comments Closes #24753 - - - - - a19201d4 by Matthew Craven at 2024-05-06T19:54:29-04:00 Add test cases for #24664 ...since none are present in the original MR !12463 fixing this issue. - - - - - 46328a49 by Alan Zimmerman at 2024-05-06T19:55:05-04:00 EPA: preserve comments in data decls Closes #24771 - - - - - 3b51995c by Andrei Borzenkov at 2024-05-07T14:39:40-04:00 Rename Solo# data constructor to MkSolo# (#24673) - data Solo# a = (# a #) + data Solo# a = MkSolo# a And `(# foo #)` syntax now becomes just a syntactic sugar for `MkSolo# a`. - - - - - 4d59abf2 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Add the cmm_cpp_is_gcc predicate to the testsuite A future C-- test called T24474-cmm-override-g0 relies on the GCC-specific behaviour of -g3 implying -dD, which, in turn, leads to it emitting #defines past the preprocessing stage. Clang, at least, does not do this, so the test would fail if ran on Clang. As the behaviour here being tested is ``-optCmmP-g3'' undoing effects of the workaround we apply as a fix for bug #24474, and the workaround was for GCC-specific behaviour, the test needs to be marked as fragile on other compilers. - - - - - 25b0b404 by Arsen Arsenović at 2024-05-07T14:40:24-04:00 Split out the C-- preprocessor, and make it pass -g0 Previously, C-- was processed with the C preprocessor program. This means that it inherited flags passed via -optc. A flag that is somewhat often passed through -optc is -g. At certain -g levels (>=2), GCC starts emitting defines *after* preprocessing, for the purposes of debug info generation. This is not useful for the C-- compiler, and, in fact, causes lexer errors. We can suppress this effect (safely, if supported) via -g0. As a workaround, in older versions of GCC (<=10), GCC only emitted defines if a certain set of -g*3 flags was passed. Newer versions check the debug level. For the former, we filter out those -g*3 flags and, for the latter, we specify -g0 on top of that. As a compatible and effective solution, this change adds a C-- preprocessor distinct from the C compiler and preprocessor, but that keeps its flags. The command line produced for C-- preprocessing now looks like: $pgmCmmP $optCs_without_g3 $g0_if_supported $optCmmP Closes: https://gitlab.haskell.org/ghc/ghc/-/issues/24474 - - - - - 9b4129a5 by Andreas Klebinger at 2024-05-08T13:24:20-04:00 -fprof-late: Only insert cost centres on functions/non-workfree cafs. They are usually useless and doing so for data values comes with a large compile time/code size overhead. Fixes #24103 - - - - - 259b63d3 by Sebastian Graf at 2024-05-08T13:24:57-04:00 Simplifier: Preserve OccInfo on DataAlt fields when case binder is dead (#24770) See the adjusted `Note [DataAlt occ info]`. This change also has a positive repercussion on `Note [Combine case alts: awkward corner]`. Fixes #24770. We now try not to call `dataConRepStrictness` in `adjustFieldsIdInfo` when all fields are lazy anyway, leading to a 2% ghc/alloc decrease in T9675. Metric Decrease: T9675 - - - - - 31b28cdb by Sebastian Graf at 2024-05-08T13:24:57-04:00 Kill seqRule, discard dead seq# in Prep (#24334) Discarding seq#s in Core land via `seqRule` was problematic; see #24334. So instead we discard certain dead, discardable seq#s in Prep now. See the updated `Note [seq# magic]`. This fixes the symptoms of #24334. - - - - - b2682534 by Rodrigo Mesquita at 2024-05-10T01:47:51-04:00 Document NcgImpl methods Fixes #19914 - - - - - 4d3acbcf by Zejun Wu at 2024-05-10T01:48:28-04:00 Make renamer to be more flexible with parens in the LHS of the rules We used to reject LHS like `(f a) b` in RULES and requires it to be written as `f a b`. It will be handy to allow both as the expression may be more readable with extra parens in some cases when infix operator is involved. Espceially when TemplateHaskell is used, extra parens may be added out of user's control and result in "valid" rules being rejected and there are not always ways to workaround it. Fixes #24621 - - - - - ab840ce6 by Ben Gamari at 2024-05-10T01:49:04-04:00 IPE: Eliminate dependency on Read Instead of encoding the closure type as decimal string we now simply represent it as an integer, eliminating the need for `Read` in `GHC.Internal.InfoProv.Types.peekInfoProv`. Closes #24504. ------------------------- Metric Decrease: T24602_perf_size size_hello_artifact ------------------------- - - - - - a9979f55 by Cheng Shao at 2024-05-10T01:49:43-04:00 testsuite: fix testwsdeque with recent clang This patch fixes compilation of testwsdeque.c with recent versions of clang, which will fail with the error below: ``` testwsdeque.c:95:33: error: warning: format specifies type 'long' but the argument has type 'void *' [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~~ ^ testwsdeque.c:95:39: error: warning: format specifies type 'int' but the argument has type 'StgWord' (aka 'unsigned long') [-Wformat] 95 | barf("FAIL: %ld %d %d", p, n, val); | ~~ ^~~ | %lu testwsdeque.c:133:42: error: error: incompatible function pointer types passing 'void (void *)' to parameter of type 'OSThreadProc *' (aka 'void *(*)(void *)') [-Wincompatible-function-pointer-types] 133 | createOSThread(&ids[n], "thief", thief, (void*)(StgWord)n); | ^~~~~ /workspace/ghc/_build/stage1/lib/../lib/x86_64-linux-ghc-9.11.20240502/rts-1.0.2/include/rts/OSThreads.h:193:51: error: note: passing argument to parameter 'startProc' here 193 | OSThreadProc *startProc, void *param); | ^ 2 warnings and 1 error generated. ``` - - - - - c2b33fc9 by Rodrigo Mesquita at 2024-05-10T01:50:20-04:00 Rename pre-processor invocation args Small clean up. Uses proper names for the various groups of arguments that make up the pre-processor invocation. - - - - - 2b1af08b by Cheng Shao at 2024-05-10T01:50:55-04:00 ghc-heap: fix typo in ghc-heap cbits - - - - - fc2d6de1 by Jade at 2024-05-10T21:07:16-04:00 Improve performance of Data.List.sort(By) This patch improves the algorithm to sort lists in base. It does so using two strategies: 1) Use a four-way-merge instead of the 'default' two-way-merge. This is able to save comparisons and allocations. 2) Use `(>) a b` over `compare a b == GT` and allow inlining and specialization. This mainly benefits types with a fast (>). Note that this *may* break instances with a *malformed* Ord instance where `a > b` is *not* equal to `compare a b == GT`. CLC proposal: https://github.com/haskell/core-libraries-committee/issues/236 Fixes #24280 ------------------------- Metric Decrease: MultiLayerModulesTH_Make T10421 T13719 T15164 T18698a T18698b T1969 T9872a T9961 T18730 WWRec T12425 T15703 ------------------------- - - - - - 1012e8aa by Matthew Pickering at 2024-05-10T21:07:52-04:00 Revert "ghcup-metadata: Drop output_name field" This reverts commit ecbf22a6ac397a791204590f94c0afa82e29e79f. This breaks the ghcup metadata generation on the nightly jobs. - - - - - daff1e30 by Jannis at 2024-05-12T13:38:35-04:00 Division by constants optimization - - - - - 413217ba by Andreas Klebinger at 2024-05-12T13:39:11-04:00 Tidy: Add flag to expose unfoldings if they take dictionary arguments. Add the flag `-fexpose-overloaded-unfoldings` to be able to control this behaviour. For ghc's boot libraries file size grew by less than 1% when it was enabled. However I refrained from enabling it by default for now. I've also added a section on specialization more broadly to the users guide. ------------------------- Metric Decrease: MultiLayerModulesTH_OneShot Metric Increase: T12425 T13386 hard_hole_fits ------------------------- - - - - - c5d89412 by Zubin Duggal at 2024-05-13T22:19:53-04:00 Don't store a GlobalRdrEnv in `mi_globals` for GHCi. GHCi only needs the `mi_globals` field for modules imported with :module +*SomeModule. It uses this field to make the top level environment in `SomeModule` available to the repl. By default, only the first target in the command line parameters is "star" loaded into GHCi. Other modules have to be manually "star" loaded into the repl. Storing the top level GlobalRdrEnv for each module is very wasteful, especially given that we will most likely never need most of these environments. Instead we store only the information needed to reconstruct the top level environment in a module, which is the `IfaceTopEnv` data structure, consisting of all import statements as well as all top level symbols defined in the module (not taking export lists into account) When a particular module is "star-loaded" into GHCi (as the first commandline target, or via an explicit `:module +*SomeModule`, we reconstruct the top level environment on demand using the `IfaceTopEnv`. - - - - - d65bf4a2 by Fendor at 2024-05-13T22:20:30-04:00 Add perf regression test for `-fwrite-if-simplified-core` - - - - - 2c0f8ddb by Andrei Borzenkov at 2024-05-13T22:21:07-04:00 Improve pattern to type pattern transformation (23739) `pat_to_type_pat` function now can handle more patterns: - TuplePat - ListPat - LitPat - NPat - ConPat Allowing these new constructors in type patterns significantly increases possible shapes of type patterns without `type` keyword. This patch also changes how lookups in `lookupOccRnConstr` are performed, because we need to fall back into types when we didn't find a constructor on data level to perform `ConPat` to type transformation properly. - - - - - be514bb4 by Cheng Shao at 2024-05-13T22:21:43-04:00 hadrian: fix hadrian building with ghc-9.10.1 - - - - - ad38e954 by Cheng Shao at 2024-05-13T22:21:43-04:00 linters: fix lint-whitespace compilation with ghc-9.10.1 - - - - - a593f284 by Andreas Klebinger at 2024-05-15T07:32:10-04:00 Expand the `inline` rule to look through casts/ticks. Fixes #24808 - - - - - b1e0c313 by Cheng Shao at 2024-05-15T07:32:46-04:00 testsuite: bump PartialDownSweep timeout to 5x on wasm32 - - - - - b2227487 by Fendor at 2024-05-15T17:14:06-04:00 Add Eq and Ord instance to `IfaceType` We add an `Ord` instance so that we can store `IfaceType` in a `Data.Map` container. This is required to deduplicate `IfaceType` while writing `.hi` files to disk. Deduplication has many beneficial consequences to both file size and memory usage, as the deduplication enables implicit sharing of values. See issue #24540 for more motivation. The `Ord` instance would be unnecessary if we used a `TrieMap` instead of `Data.Map` for the deduplication process. While in theory this is clerarly the better option, experiments on the agda code base showed that a `TrieMap` implementation has worse run-time performance characteristics. To the change itself, we mostly derive `Eq` and `Ord`. This requires us to change occurrences of `FastString` with `LexicalFastString`, since `FastString` has no `Ord` instance. We change the definition of `IfLclName` to a newtype of `LexicalFastString`, to make such changes in the future easier. Bump haddock submodule for IfLclName changes - - - - - d368f9a6 by Fendor at 2024-05-15T17:14:06-04:00 Move out LiteralMap to avoid cyclic module dependencies - - - - - 2fcc09fd by Fendor at 2024-05-15T17:14:06-04:00 Add deduplication table for `IfaceType` The type `IfaceType` is a highly redundant, tree-like data structure. While benchmarking, we realised that the high redundancy of `IfaceType` causes high memory consumption in GHCi sessions when byte code is embedded into the `.hi` file via `-fwrite-if-simplified-core` or `-fbyte-code-and-object-code`. Loading such `.hi` files from disk introduces many duplicates of memory expensive values in `IfaceType`, such as `IfaceTyCon`, `IfaceTyConApp`, `IA_Arg` and many more. We improve the memory behaviour of GHCi by adding an additional deduplication table for `IfaceType` to the serialisation of `ModIface`, similar to how we deduplicate `Name`s and `FastString`s. When reading the interface file back, the table allows us to automatically share identical values of `IfaceType`. To provide some numbers, we evaluated this patch on the agda code base. We loaded the full library from the `.hi` files, which contained the embedded core expressions (`-fwrite-if-simplified-core`). Before this patch: * Load time: 11.7 s, 2.5 GB maximum residency. After this patch: * Load time: 7.3 s, 1.7 GB maximum residency. This deduplication has the beneficial side effect to additionally reduce the size of the on-disk interface files tremendously. For example, on agda, we reduce the size of `.hi` files (with `-fwrite-if-simplified-core`): * Before: 101 MB on disk * Now: 24 MB on disk This has even a beneficial side effect on the cabal store. We reduce the size of the store on disk: * Before: 341 MB on disk * Now: 310 MB on disk Note, none of the dependencies have been compiled with `-fwrite-if-simplified-core`, but `IfaceType` occurs in multiple locations in a `ModIface`. We also add IfaceType deduplication table to .hie serialisation and refactor .hie file serialisation to use the same infrastrucutre as `putWithTables`. Bump haddock submodule to accomodate for changes to the deduplication table layout and binary interface. - - - - - 36aa7cf1 by Fendor at 2024-05-15T17:14:06-04:00 Add run-time configurability of `.hi` file compression Introduce the flag `-fwrite-if-compression=<n>` which allows to configure the compression level of writing .hi files. The motivation is that some deduplication operations are too expensive for the average use case. Hence, we introduce multiple compression levels with variable impact on performance, but still reduce the memory residency and `.hi` file size on disk considerably. We introduce three compression levels: * `1`: `Normal` mode. This is the least amount of compression. It deduplicates only `Name` and `FastString`s, and is naturally the fastest compression mode. * `2`: `Safe` mode. It has a noticeable impact on .hi file size and is marginally slower than `Normal` mode. In general, it should be safe to always use `Safe` mode. * `3`: `Full` deduplication mode. Deduplicate as much as we can, resulting in minimal .hi files, but at the cost of additional compilation time. Reading .hi files doesn't need to know the initial compression level, and can always deserialise a `ModIface`, as we write out a byte that indicates the next value has been deduplicated. This allows users to experiment with different compression levels for packages, without recompilation of dependencies. Note, the deduplication also has an additional side effect of reduced memory consumption to implicit sharing of deduplicated elements. See https://gitlab.haskell.org/ghc/ghc/-/issues/24540 for example where that matters. ------------------------- Metric Decrease: MultiLayerModulesDefsGhciWithCore T16875 T21839c T24471 hard_hole_fits libdir ------------------------- - - - - - 1e63a6fb by Matthew Pickering at 2024-05-15T17:14:07-04:00 Introduce regression tests for `.hi` file sizes Add regression tests to track how `-fwrite-if-compression` levels affect the size of `.hi` files. - - - - - 639d742b by M Farkas-Dyck at 2024-05-15T17:14:49-04:00 TTG: ApplicativeStatement exist only in Rn and Tc Co-Authored-By: romes <rodrigo.m.mesquita at gmail.com> - - - - - aa7b336b by Jade at 2024-05-15T23:06:17-04:00 Documentation: Improve documentation for symbols exported from System.IO - - - - - c561de8f by Jade at 2024-05-15T23:06:54-04:00 Improve suggestions for language extensions - When suggesting Language extensions, also suggest Extensions which imply them - Suggest ExplicitForAll and GADTSyntax instead of more specific extensions - Rephrase suggestion to include the term 'Extension' - Also moves some flag specific definitions out of Session.hs into Flags.hs (#24478) Fixes: #24477 Fixes: #24448 Fixes: #10893 - - - - - 4c7ae2a1 by Andreas Klebinger at 2024-05-15T23:07:30-04:00 Testsuite: Check if llvm assembler is available for have_llvm - - - - - bc672166 by Torsten Schmits at 2024-05-15T23:08:06-04:00 refactor quadratic search in warnMissingHomeModules - - - - - 7875e8cb by Torsten Schmits at 2024-05-15T23:08:06-04:00 add test that runs MakeDepend on thousands of modules - - - - - b84b91f5 by Adam Gundry at 2024-05-16T15:32:06-04:00 Representation-polymorphic HasField (fixes #22156) This generalises the HasField class to support representation polymorphism, so that instead of type HasField :: forall {k} . k -> Type -> Type -> Constraint we have type HasField :: forall {k} {r_rep} {a_rep} . k -> TYPE r_rep -> TYPE a_rep -> Constraint - - - - - 05285090 by Matthew Pickering at 2024-05-16T15:32:43-04:00 Bump os-string submodule to 2.0.2.2 Closes #24786 - - - - - 886ab43a by Cheng Shao at 2024-05-17T01:34:50-04:00 rts: do not prefetch mark_closure bdescr in non-moving gc when ASSERTS_ENABLED This commit fixes a small an oversight in !12148: the prefetch logic in non-moving GC may trap in debug RTS because it calls Bdescr() for mark_closure which may be a static one. It's fine in non-debug RTS because even invalid bdescr addresses are prefetched, they will not cause segfaults, so this commit implements the most straightforward fix: don't prefetch mark_closure bdescr when assertions are enabled. - - - - - b38dcf39 by Teo Camarasu at 2024-05-17T01:34:50-04:00 rts: Allocate non-moving segments with megablocks Non-moving segments are 8 blocks long and need to be aligned. Previously we serviced allocations by grabbing 15 blocks, finding an aligned 8 block group in it and returning the rest. This proved to lead to high levels of fragmentation as a de-allocating a segment caused an 8 block gap to form, and this could not be reused for allocation. This patch introduces a segment allocator based around using entire megablocks to service segment allocations in bulk. When there are no free segments, we grab an entire megablock and fill it with aligned segments. As the megablock is free, we can easily guarantee alignment. Any unused segments are placed on a free list. It only makes sense to free segments in bulk when all of the segments in a megablock are freeable. After sweeping, we grab the free list, sort it, and find all groups of segments where they cover the megablock and free them. This introduces a period of time when free segments are not available to the mutator, but the risk that this would lead to excessive allocation is low. Right after sweep, we should have an abundance of partially full segments, and this pruning step is relatively quick. In implementing this we drop the logic that kept NONMOVING_MAX_FREE segments on the free list. We also introduce an eventlog event to log the amount of pruned/retained free segments. See Note [Segment allocation strategy] Resolves #24150 ------------------------- Metric Decrease: T13253 T19695 ------------------------- - - - - - 710665bd by Cheng Shao at 2024-05-17T01:35:30-04:00 rts: fix I/O manager compilation errors for win32 target This patch fixes I/O manager compilation errors for win32 target discovered when cross-compiling to win32 using recent clang: ``` rts/win32/ThrIOManager.c:117:7: error: error: call to undeclared function 'is_io_mng_native_p'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 117 | if (is_io_mng_native_p ()) { | ^ | 117 | if (is_io_mng_native_p ()) { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/fs.c:143:28: error: error: a function declaration without a prototype is deprecated in all versions of C [-Werror,-Wstrict-prototypes] 143 | int setErrNoFromWin32Error () { | ^ | void | 143 | int setErrNoFromWin32Error () { | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:227:9: error: error: call to undeclared function 'interruptIOManagerEvent'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 227 | interruptIOManagerEvent (); | ^ | 227 | interruptIOManagerEvent (); | ^ rts/win32/ConsoleHandler.c:227:9: error: note: did you mean 'getIOManagerEvent'? | 227 | interruptIOManagerEvent (); | ^ rts/include/rts/IOInterface.h:27:10: error: note: 'getIOManagerEvent' declared here 27 | void * getIOManagerEvent (void); | ^ | 27 | void * getIOManagerEvent (void); | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) rts/win32/ConsoleHandler.c:196:9: error: error: call to undeclared function 'setThreadLabel'; ISO C99 and later do not support implicit function declarations [-Wimplicit-function-declaration] 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/win32/ConsoleHandler.c:196:9: error: note: did you mean 'postThreadLabel'? | 196 | setThreadLabel(cap, t, "signal handler thread"); | ^ rts/eventlog/EventLog.h:118:6: error: note: 'postThreadLabel' declared here 118 | void postThreadLabel(Capability *cap, | ^ | 118 | void postThreadLabel(Capability *cap, | ^ 1 error generated. `x86_64-w64-mingw32-clang' failed in phase `C Compiler'. (Exit code: 1) ``` - - - - - 28b9cee0 by Rodrigo Mesquita at 2024-05-17T01:36:05-04:00 configure: Check C99-compat for Cmm preprocessor Fixes #24815 - - - - - 8927e0c3 by Andreas Klebinger at 2024-05-17T01:36:41-04:00 Ensure `tcHasFixedRuntimeRep (# #)` returns True. - - - - - 04179044 by doyougnu at 2024-05-17T09:00:32-04:00 testsuite: make find_so regex less general Closes #24759 Background. In MR !12372 we began tracking shared object files and directories sizes for dependencies. However, this broke release builds because release builds alter the filenames swapping "in-place" for a hash. This was not considered in the MR and thus broke release pipelines. Furthermore, the rts_so test was found to be wildly varying and was therefore disabled in !12561. This commit fixes both of these issues: - fix the rts_so test by making the regex less general, now the rts_so test and all other foo.so tests must match "libHS<some-lib>-<version>-<hash|'in-place>-<ghc>". This prevents the rts_so test from accidentally matching different rts variants such as rts_threaded, which was the cause of the wild swings after !12372. - add logic to match either a hash or the string in-place. This should make the find_so function build agnostic. - - - - - 0962b50d by Andreas Klebinger at 2024-05-17T09:01:08-04:00 TagAnalysis: Treat all bottom ids as tagged during analysis. Ticket #24806 showed that we also need to treat dead end thunks as tagged during the analysis. - - - - - 7eb9f184 by Ben Gamari at 2024-05-17T11:23:37-04:00 Remove haddock submodule In preparation for merge into the GHC, as proposed in #23178. - - - - - 47b14dcc by Fendor at 2024-05-17T11:28:17-04:00 Adapt to `IfLclName` newtype changes (cherry picked from commit a711607e29b925f3d69e27c5fde4ba655c711ff1) - - - - - 6cc6681d by Fendor at 2024-05-17T11:28:17-04:00 Add IfaceType deduplication table to interface file serialisation Although we do not really need it in the interface file serialisation, as the deserialisation uses `getWithUserData`, we need to mirror the structure `getWithUserData` expects. Thus, we write essentially an empty `IfaceType` table at the end of the file, as the interface file doesn't reference `IfaceType`. (cherry picked from commit c9bc29c6a708483d2abc3d8ec9262510ce87ca61) - - - - - b9721206 by Ben Gamari at 2024-05-17T11:30:22-04:00 ghc-tags.yaml: Initial commit - - - - - 074e7d8f by Ben Gamari at 2024-05-17T11:31:29-04:00 fourmolu: Add configuration - - - - - 151b1736 by Ben Gamari at 2024-05-17T11:32:52-04:00 Makefile: Rework for use by haddock developers Previously the Makefile was present only for GHC's old make-based build system. Now since the make-based build system is gone we can use it for more useful ends. - - - - - a7dcf13b by Ben Gamari at 2024-05-17T11:36:14-04:00 Reformat with fourmolu Using previously-added configuration and `fourmolu -i .` Note that we exclude the test-cases (`./{hoogle,html-hypsrc,latex}-test`) as they are sensitive to formatting. - - - - - 0ea6017b by Ben Gamari at 2024-05-17T11:40:04-04:00 Add 'utils/haddock/' from commit 'a7dcf13bfbb97b20e75cc8ce650e2bb628db4660' git-subtree-dir: utils/haddock git-subtree-mainline: 7eb9f1849b1c72a1c61dee88462b4244550406f3 git-subtree-split: a7dcf13bfbb97b20e75cc8ce650e2bb628db4660 - - - - - aba1d304 by Hécate Moonlight at 2024-05-17T11:40:48-04:00 Add exceptions to the dangling notes list - - - - - 527bfbfb by Hécate Moonlight at 2024-05-17T11:40:52-04:00 Add haddock to the whitespace lint ignore list - - - - - 43274677 by Ben Gamari at 2024-05-17T11:41:20-04:00 git-blame-ignore-revs: Ignore haddock reformatting - - - - - 0e679e37 by Fendor at 2024-05-18T00:27:24-04:00 Pass cpp options to the CC builder in hadrian - - - - - bb40244e by Sylvain Henry at 2024-05-18T00:28:06-04:00 JS: fix allocation constant (fix #24746) - - - - - 646d30ab by Jade at 2024-05-18T19:23:31+02:00 Add highlighting for inline-code snippets in haddock - - - - - 64459a3e by Hécate Moonlight at 2024-05-19T08:42:27-04:00 haddock: Add a .readthedocs.yml file for online documentation - - - - - 7d3d9bbf by Serge S. Gulin at 2024-05-19T18:47:05+00:00 Unicode: General Category size test (related #24789) Added trivial size performance test which involves unicode general category usage via `read`. The `read` itself uses general category to detect spaces. The purpose for this test is to measure outcome of applying improvements at General Category representation in code discussed at #24789. - - - - - 8e04efcf by Alan Zimmerman at 2024-05-19T21:29:34-04:00 EPA: Remove redundant code Remove unused epAnnAnns function various cases for showAstData that no longer exist - - - - - 071d7a1e by Rodrigo Mesquita at 2024-05-20T10:55:16-04:00 Improve docs on closed type families in hs-boots Fixes #24776 - - - - - d9e2c119 by Torsten Schmits at 2024-05-20T10:55:52-04:00 Use default deviation for large-project test This new performance test has the purpose of detecting regressions in complexity in relation to the number of modules in a project, so 1% deviation is way too small to avoid false positives. - - - - - 20b0136a by Ben Gamari at 2024-05-22T00:31:39-04:00 ghcup-metadata: Various fixes from 9.10.1 Use Debian 12/x86-64, Debian 10/aarch64, and Debian 11/aarch64 bindists where possible. - - - - - 6838a7c3 by Sylvain Henry at 2024-05-22T00:32:23-04:00 Reverse arguments to stgCallocBytes (fix #24828) - - - - - f50f46c3 by Fendor at 2024-05-22T00:32:59-04:00 Add log messages for Iface serialisation compression level Fix the label of the number of 'IfaceType' entries in the log message. Add log message for the compression level that is used to serialise a an interface file. Adds `Outputable` instance for 'CompressionIFace'. - - - - - 3bad5d55 by Hécate Moonlight at 2024-05-22T00:33:40-04:00 base: Update doctests outputs ghc-internal: Update doctests outputs - - - - - 9317c6fb by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix the testsuites of the haddock-library - Apply all the metadata revisions from Hackage to the cabal file. - Fix the `ParserSpec.hs` file in the `spec` testsuite of haddock-library. - Make `CHANGES.md` an extra-doc-file instead of an extra-source-file. - - - - - 54073b02 by David Binder at 2024-05-22T00:34:21-04:00 haddock: Fix parser of @since pragma The testsuite contained tests for annotations of the form `@since foo-bar-0.5.0`, but the parser was written incorrectly. - - - - - ede6ede3 by Matthew Pickering at 2024-05-22T00:34:57-04:00 Fix nightly pages job It seems likely broken by 9f99126a which moved `index.html` from the root folder into `docs/` folder. Fixes #24840 - - - - - b7bcf729 by Cheng Shao at 2024-05-22T00:35:32-04:00 autoconf: remove unused context diff check This patch removes redundant autoconf check for the context diff program given it isn't actually been used anywhere, especially since make removal. - - - - - ea2fe66e by Hécate Moonlight at 2024-05-22T00:36:13-04:00 haddock: Rework the contributing guide - - - - - 0f302a94 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 haddock: Add module relationships diagrams of haddock-api and haddock-library - - - - - d1a9f34f by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add instructions - - - - - b880ee80 by Hécate Moonlight at 2024-05-22T00:36:52-04:00 Add SVG outputs - - - - - 6d7e6ad8 by Ben Gamari at 2024-05-22T13:40:05-04:00 rts: Fix size of StgOrigThunkInfo frames Previously the entry code of the `stg_orig_thunk` frame failed to account for the size of the profiling header as it hard-coded the frame size. Fix this. Fixes #24809. - - - - - c645fe40 by Fendor at 2024-05-22T13:40:05-04:00 Add regression test T24809 for stg_orig_thunk_info_frame size - - - - - 4181aa40 by Andreas Klebinger at 2024-05-22T13:40:42-04:00 bindists: Check for existence of share folder before trying to copy it. This folder isn't distributed in windows bindists A lack of doing so resulted us copying loads of files twice. - - - - - d216510e by Matthew Pickering at 2024-05-22T13:40:42-04:00 Remove ad-hoc installation of mingw toolchain in relocatable bindists This reverts 616ac30026e8dd7d2ebb98d92dde071eedf5d951 The choice about whether to install mingw is taken in the installation makefile. This is also broken on non-windows systems. The actual issue was the EnableDistroToolchain variable wasn't declared in mk/config.mk and therefore the check to install mingw was failing. - - - - - 7b4c1998 by Cheng Shao at 2024-05-22T21:52:52-04:00 testsuite: fix T17920 for wasm backend T17920 was marked as fragile on wasm before; it can be trivially fixed by avoiding calling variadic printf() in cmm. - - - - - c739383b by Cheng Shao at 2024-05-22T21:53:29-04:00 testsuite: bump T22744 timeout to 5x - - - - - c4c6d714 by Cheng Shao at 2024-05-22T21:54:06-04:00 testsuite: don't attempt to detect host cpu features when testing cross ghc The testsuite driver CPU feature detection logic only detects host CPU and only makes sense when we are not testing a cross GHC. - - - - - 3d9e4ce6 by Simon Peyton Jones at 2024-05-22T21:54:43-04:00 Better skolemisation As #24810 showed, it is (a little) better to skolemise en-bloc, so that Note [Let-bound skolems] fires more often. See Note [Skolemisation en bloc] in GHC.Tc.Utils.Instantiate. - - - - - a3cd3a1d by Ryan Scott at 2024-05-22T21:55:19-04:00 Add missing parenthesizePat in cvtp We need to ensure that the output of `cvtp` is parenthesized (at precedence `sigPrec`) so that any pattern signatures with a surrounding pattern signature can parse correctly. Fixes #24837. - - - - - 4bb2a7cc by Hécate Moonlight at 2024-05-22T21:55:59-04:00 [base] Document the memory overhead of ByteArray Add a diagram that shows the constituent parts of a ByteArray and their memory overhead. - - - - - 8b2a016a by Hécate Moonlight at 2024-05-22T21:56:38-04:00 Haddock: Add MR template for Haddock - - - - - ead75532 by Peter Trommler at 2024-05-23T02:28:05-04:00 PPC: Support ELF v2 on powerpc64 big-endian Detect ELF v2 on PowerPC 64-bit systems. Check for `_CALL_ELF` preprocessor macro. Fixes #21191 - - - - - 9d4c10f2 by Hécate Kleidukos at 2024-05-23T02:28:44-04:00 gitlab: Add @Kleidukos to CODEOWNERS for utils/haddock - - - - - 28e64170 by Preetham Gujjula at 2024-05-23T07:20:48-04:00 haddock: Add cabal-fmt to tools for `make style` - - - - - 00126a89 by Andrei Borzenkov at 2024-05-23T07:21:24-04:00 haddock: fix verbosity option parsing - - - - - a3e0b68b by Ryan Hendrickson at 2024-05-23T15:52:03-04:00 base: specify tie-breaking behavior of min, max, and related list/Foldable functions - - - - - bdcc0f37 by doyougnu at 2024-05-24T07:51:18-04:00 cmm: add word <-> double/float bitcast - closes: #25331 This is the last step in the project plan described in #25331. This commit: - adds bitcast operands for x86_64, LLVM, aarch64 - For PPC and i386 we resort to using the cmm implementations - renames conversion MachOps from Conv to Round|Truncate - - - - - f0d257f7 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor Some functions in StgToByteCode were filtering out void arguments. However, StgToByteCode is called after unarisation: the void arguments should have been removed earlier. Instead of filtering out, we assert that the args are non-void. - - - - - 03137fd2 by Krzysztof Gogolewski at 2024-05-24T07:51:55-04:00 StgToByteCode: minor refactor `layoutNativeCall` was always called with a `primRepCmmType platform` callback. Hence we can put it inside of `layoutNativeCall` rather than repeat it. - - - - - 27c430f3 by David Binder at 2024-05-24T07:52:38-04:00 haddock: Remove compatibility shims for GHC < 8.4 from haddock-library - - - - - 8dd8a076 by Cheng Shao at 2024-05-24T07:53:14-04:00 compiler: avoid saving foreign call target to local when there are no caller-save GlobalRegs This patch makes the STG->Cmm backend avoid saving foreign call target to local when there are no caller-save GlobalRegs. Since 321941a8ebe25192cdeece723e1058f2f47809ea, when we lower a foreign call, we unconditionally save the foreign call target to a temporary local first, then rely on cmmSink to clean it up later, which only happens with -fcmm-sink (implied by -O) and not in unoptimized code. And this is troublesome for the wasm backend NCG, which needs to infer a foreign call target symbol's type signature from the Cmm call site. Previously, the NCG has been emitting incorrect type signatures for unoptimized code, which happens to work with `wasm-ld` most of the time, but this is never future-proof against upstream toolchain updates, and it causes horrible breakages when LTO objects are included in linker input. Hence this patch. - - - - - 986df1ab by Cheng Shao at 2024-05-24T07:53:14-04:00 testsuite: add callee-no-local regression test - - - - - 52d62e2a by Sylvain Henry at 2024-05-24T07:53:57-04:00 Fix HasCallStack leftovers from !12514 / #24726 - - - - - c5e00c35 by crumbtoo at 2024-05-24T07:54:38-04:00 user_guide: Fix typo in MultiWayIf chapter Close #24829 - - - - - bd323b0e by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Ensure that CHANGELOG is included in extra-source-files This was missed in the `ghc-internal` split. Closes #24831. - - - - - 1bfd32e8 by Ben Gamari at 2024-05-24T07:55:15-04:00 base: Fix changelog reference to setBacktraceMechanismState (cherry picked from commit b63f7ba01fdfd98a01d2f0dec8d9262b3e595c5d) - - - - - 43e8e4f3 by Sylvain Henry at 2024-05-24T12:16:43-04:00 Float/double unboxed literal support for HexFloatLiterals (fix #22155) - - - - - 4a7f4713 by Fendor at 2024-05-24T12:17:19-04:00 Improve test labels for binary interface file size tests Test labels for binary interface file sizes are hard to read and overly verbose at the same time. Extend the name for the metric title, but shorten it in the actual comparison table. - - - - - 14e554cf by Zubin Duggal at 2024-05-24T12:17:55-04:00 Revert "Fix haskell/haddock#783 Don't show button if --quickjump not present" This reverts commit 7776566531e72c415f66dd3b13da9041c52076aa. - - - - - f56838c3 by Ben Gamari at 2024-05-24T12:17:55-04:00 Fix default hyperlinked sources pattern Previously this didn't include the `%M` token which manifested as broken links to the hyperlinked sources of reexports of declarations defined in other packages. Fixes haddock#1628. (cherry picked from commit 1432bcc943d41736eca491ecec4eb9a6304dab36) - - - - - 42efa62c by Ben Gamari at 2024-05-24T12:17:55-04:00 Make DocPaths a proper data type (cherry picked from commit 7f3a5c4da0023ae47b4c376c9b1ea2d706c94d8c) - - - - - 53d9ceb3 by Ben Gamari at 2024-05-24T12:17:55-04:00 haddock: Bump version to 2.30 (cherry picked from commit 994989ed3d535177e57b778629726aeabe8c7602) - - - - - e4db1112 by Zubin Duggal at 2024-05-24T12:17:55-04:00 haddock-api: allow base 4.20 and ghc 9.11 - - - - - e294f7a2 by PHO at 2024-05-24T12:17:55-04:00 Add a flag "threaded" for building haddock with the threaded RTS GHC isn't guaranteed to have a threaded RTS. There should be a way to build it with the vanilla one. (cherry picked from commit 75a94e010fb5b0236c670d22b04f5472397dc15d) - - - - - 51165bc9 by Andreas Klebinger at 2024-05-25T10:58:03-04:00 Update ticky counter event docs. Add the info about the info table address and json fields. Fixes #23200 - - - - - 98597ad5 by Sylvain Henry at 2024-05-25T10:58:45-04:00 Export extractPromotedList (#24866) This can be useful in plugins. - - - - - 228dcae6 by Teo Camarasu at 2024-05-28T13:12:24+00:00 template-haskell: Move wired-ins to ghc-internal Thus we make `template-haskell` reinstallable and keep it as the public API for Template Haskell. All of the wired-in identifiers are moved to `ghc-internal`. This necessitates also moving much of `ghc-boot-th` into `ghc-internal`. These modules are then re-exported from `ghc-boot-th` and `template-haskell`. To avoid a dependency on `template-haskell` from `lib:ghc`, we instead depend on the TH ASTs via `ghc-boot-th`. As `template-haskell` no longer has special status, we can drop the logic adding an implicit dependency on `template-haskell` when using TH. We can also drop the `template-haskell-next` package, which was previously used when bootstrapping. When bootstrapping, we need to vendor the TH AST modules from `ghc-internal` into `ghc-boot-th`. This is controlled by the `bootstrap` cabal flag as before. See Note [Bootstrapping Template Haskell]. We split out a GHC.Internal.TH.Lift module resolving #24752. This module is only built when not bootstrapping. Resolves #24703 ------------------------- Metric Increase: ghc_boot_th_dir ghc_boot_th_so ------------------------- - - - - - 62dded28 by Teo Camarasu at 2024-05-28T13:12:24+00:00 testsuite: mark tests broken by #24886 Now that `template-haskell` is no longer wired-in. These tests are triggering #24886, and so need to be marked broken. - - - - - 3ca72ad9 by Cheng Shao at 2024-05-30T02:57:06-04:00 rts: fix missing function prototypes in ClosureMacros.h - - - - - e0029e3d by Andreas Klebinger at 2024-05-30T02:57:43-04:00 UnliftedFFITypes: Allow `(# #)` as argument when it's the only argument. This allows representing functions like: int foo(void); to be imported like this: foreign import ccall "a_number_c" c_number :: (# #) -> Int64# Which can be useful when the imported function isn't implicitly stateful. - - - - - d0401335 by Matthew Pickering at 2024-05-30T02:58:19-04:00 ci: Update ci-images commit for fedora38 image The fedora38 nightly job has been failing for quite a while because `diff` was no longer installed. The ci-images bump explicitly installs `diffutils` into these images so hopefully they now pass again. - - - - - 3c97c74a by Jan Hrček at 2024-05-30T02:58:58-04:00 Update exactprint docs - - - - - 77760cd7 by Jan Hrček at 2024-05-30T02:58:58-04:00 Incorporate review feedback - - - - - 87591368 by Jan Hrček at 2024-05-30T02:58:58-04:00 Remove no longer relevant reference to comments - - - - - 05f4f142 by Jan Hrček at 2024-05-30T02:58:59-04:00 Replace outdated code example - - - - - 45a4a5f3 by Andreas Klebinger at 2024-05-30T02:59:34-04:00 Reword error resulting from missing -XBangPatterns. It can be the result of either a bang pattern or strict binding, so now we say so instead of claiming it must be a bang pattern. Fixes #21032 - - - - - e17f2df9 by Cheng Shao at 2024-05-30T03:00:10-04:00 testsuite: bump MultiLayerModulesDefsGhciReload timeout to 10x - - - - - 7a660042 by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: ensure gc_thread/gen_workspace is allocated with proper alignment gc_thread/gen_workspace are required to be aligned by 64 bytes. However, this property has not been properly enforced before, and numerous alignment violations at runtime has been caught by UndefinedBehaviorSanitizer that look like: ``` rts/sm/GC.c:1167:8: runtime error: member access within misaligned address 0x0000027a3390 for type 'gc_thread' (aka 'struct gc_thread_'), which requires 64 byte alignment 0x0000027a3390: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1167:8 rts/sm/GC.c:1184:13: runtime error: member access within misaligned address 0x0000027a3450 for type 'gen_workspace' (aka 'struct gen_workspace_'), which requires 64 byte alignment 0x0000027a3450: note: pointer points here 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/GC.c:1184:13 ``` This patch fixes the gc_thread/gen_workspace misalignment issue by explicitly allocating them with alignment constraint. - - - - - c77a48af by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: fix an unaligned load in nonmoving gc This patch fixes an unaligned load in nonmoving gc by ensuring the closure address is properly untagged first before attempting to prefetch its header. The unaligned load is reported by UndefinedBehaviorSanitizer: ``` rts/sm/NonMovingMark.c:921:9: runtime error: member access within misaligned address 0x0042005f3a71 for type 'StgClosure' (aka 'struct StgClosure_'), which requires 8 byte alignment 0x0042005f3a71: note: pointer points here 00 00 00 98 43 13 8e 12 7f 00 00 50 3c 5f 00 42 00 00 00 58 17 b7 92 12 7f 00 00 89 cb 5e 00 42 ^ SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/sm/NonMovingMark.c:921:9 ``` This issue had previously gone unnoticed since it didn't really harm runtime correctness, the invalid header address directly loaded from a tagged pointer is only used as prefetch address and will not cause segfaults. However, it still should be corrected because the prefetch would be rendered useless by this issue, and untagging only involves a single bitwise operation without memory access so it's cheap enough to add. - - - - - 05c4fafb by Cheng Shao at 2024-05-30T14:42:29-04:00 rts: use __builtin_offsetof to implement STG_FIELD_OFFSET This patch fixes the STG_FIELD_OFFSET macro definition by using __builtin_offsetof, which is what gcc/clang uses to implement offsetof in standard C. The previous definition that uses NULL pointer involves subtle undefined behavior in C and thus reported by UndefinedBehaviorSanitizer as well: ``` rts/Capability.h:243:58: runtime error: member access within null pointer of type 'Capability' (aka 'struct Capability_') SUMMARY: UndefinedBehaviorSanitizer: undefined-behavior rts/Capability.h:243:58 ``` - - - - - 5ff83bfc by Sylvain Henry at 2024-05-30T14:43:10-04:00 JS: remove useless h$CLOCK_REALTIME (#23202) - - - - - 95ef2d58 by Matthew Pickering at 2024-05-30T14:43:47-04:00 ghcup-metadata: Fix metadata generation There were some syntax errors in the generation script which were preventing it from running. I have tested this with: ``` nix shell --extra-experimental-features nix-command -f .gitlab/rel_eng -c ghcup-metadata --metadata ghcup-0.0.7.yaml --date="2024-05-27" --pipeline-id=95534 --version=9.11.20240525 ``` which completed successfully. - - - - - 1bc66ee4 by Jakob Bruenker at 2024-05-30T14:44:22-04:00 Add diagrams to Arrows documentation This adds diagrams to the documentation of Arrows, similar to the ones found on https://www.haskell.org/arrows/. It does not add diagrams for ArrowChoice for the time being, mainly because it's not clear to me how to visually distinguish them from the ones for Arrow. Ideally, you might want to do something like highlight the arrows belonging to the same tuple or same Either in common colors, but that's not really possible with unicode. - - - - - d10a1c65 by Matthew Craven at 2024-05-30T23:35:48-04:00 Make UnsafeSNat et al. into pattern synonyms ...so that they do not cause coerce to bypass the nominal role on the corresponding singleton types when they are imported. See Note [Preventing unsafe coercions for singleton types] and the discussion at #23478. This also introduces unsafeWithSNatCo (and analogues for Char and Symbol) so that users can still access the dangerous coercions that importing the real constructors would allow, but only in a very localized way. - - - - - 0958937e by Cheng Shao at 2024-05-30T23:36:25-04:00 hadrian: build C/C++ with split sections when enabled When split sections is enabled, ensure -fsplit-sections is passed to GHC as well when invoking GHC to compile C/C++; and pass -ffunction-sections -fdata-sections to gcc/clang when compiling C/C++ with the hadrian Cc builder. Fixes #23381. - - - - - 02b1f91e by Cheng Shao at 2024-05-30T23:36:25-04:00 driver: build C/C++ with -ffunction-sections -fdata-sections when split sections is enabled When -fsplit-sections is passed to GHC, pass -ffunction-sections -fdata-sections to gcc/clang when building C/C++. Previously, -fsplit-sections was only respected by the NCG/LLVM backends, but not the unregisterised backend; the GHC driver did not pass -fdata-sections and -ffunction-sections to the C compiler, which resulted in excessive executable sizes. Fixes #23381. ------------------------- Metric Decrease: size_hello_artifact size_hello_unicode ------------------------- - - - - - fd47e2e3 by Cheng Shao at 2024-05-30T23:37:00-04:00 testsuite: mark process005 as fragile on JS - - - - - 34a04ea1 by Matthew Pickering at 2024-05-31T06:08:36-04:00 Add -Wderiving-typeable to -Wall Deriving `Typeable` does nothing, and it hasn't done for a long while. There has also been a warning for a long while which warns you about uselessly deriving it but it wasn't enabled in -Wall. Fixes #24784 - - - - - 75fa7b0b by Matthew Pickering at 2024-05-31T06:08:36-04:00 docs: Fix formatting of changelog entries - - - - - 303c4b33 by Preetham Gujjula at 2024-05-31T06:09:21-04:00 docs: Fix link to injective type families paper Closes #24863 - - - - - df97e9a6 by Ben Gamari at 2024-05-31T06:09:57-04:00 ghc-internal: Fix package description The previous description was inherited from `base` and was inappropriate for `ghc-internal`. Also fix the maintainer and bug reporting fields. Closes #24906. - - - - - bf0737c0 by Cheng Shao at 2024-05-31T06:10:33-04:00 compiler: remove ArchWasm32 special case in cmmDoCmmSwitchPlans This patch removes special consideration for ArchWasm32 in cmmDoCmmSwitchPlans, which means the compiler will now disable cmmImplementSwitchPlans for wasm unreg backend, just like unreg backend of other targets. We enabled it in the past to workaround some compile-time panic in older versions of LLVM, but those panics are no longer present, hence no need to keep this workaround. - - - - - 7eda4bd2 by Cheng Shao at 2024-05-31T15:52:04-04:00 utils: add hie.yaml config file for ghc-config Add hie.yaml to ghc-config project directory so it can be edited using HLS. - - - - - 1e5752f6 by Cheng Shao at 2024-05-31T15:52:05-04:00 hadrian: handle findExecutable "" gracefully hadrian may invoke findExecutable "" at run-time due to a certain program is not found by configure script. Which is fine and findExecutable is supposed to return Nothing in this case. However, on Windows there's a directory bug that throws an exception (see https://github.com/haskell/directory/issues/180), so we might as well use a wrapper for findExecutable and handle exceptions gracefully. - - - - - 4eb5ad09 by Cheng Shao at 2024-05-31T15:52:05-04:00 configure: do not set LLC/OPT/LLVMAS fallback values when FIND_LLVM_PROG fails When configure fails to find LLC/OPT/LLVMAS within supported version range, it used to set "llc"/"opt"/"clang" as fallback values. This behavior is particularly troublesome when the user has llc/opt/clang with other versions in their PATH and run the testsuite, since hadrian will incorrectly assume have_llvm=True and pass that to the testsuite driver, resulting in annoying optllvm test failures (#23186). If configure determines llc/opt/clang wouldn't work, then we shouldn't pretend it'll work at all, and the bindist configure will invoke FIND_LLVM_PROG check again at install time anyway. - - - - - 5f1afdf7 by Sylvain Henry at 2024-05-31T15:52:52-04:00 Introduce UniqueSet and use it to replace 'UniqSet Unique' 'UniqSet Unique' represents a set of uniques as a 'Map Unique Unique', which is wasting space (associated key/value are always the same). Fix #23572 and #23605 - - - - - e0aa42b9 by crumbtoo at 2024-05-31T15:53:33-04:00 Improve template-haskell haddocks Closes #15822 - - - - - ae170155 by Olivier Benz at 2024-06-01T09:35:17-04:00 Bump max LLVM version to 19 (not inclusive) - - - - - 92aa65ea by Matthew Pickering at 2024-06-01T09:35:17-04:00 ci: Update CI images to test LLVM 18 The debian12 image in this commit has llvm 18 installed. - - - - - adb1fe42 by Serge S. Gulin at 2024-06-01T09:35:53-04:00 Unicode: make ucd2haskell build-able again ucd2haskell tool used streamly library which version in cabal was out of date. It is updated to the latest version at hackage with deprecated parts rewritten. Also following fixes were applied to existing code in suppose that from its last run the code structure was changed and now it was required to be up to date with actual folder structures: 1. Ghc module path environment got a suffix with `src`. 2. Generated code got 2.1 `GHC.Internal` prefix for `Data.*`. 2.2 `GHC.Unicode.Internal` swapped on `GHC.Internal.Unicode` according to actual structure. - - - - - ad56fd84 by Jade at 2024-06-01T09:36:29-04:00 Replace 'NB' with 'Note' in error messages - - - - - 6346c669 by Cheng Shao at 2024-06-01T09:37:04-04:00 compiler: fix -ddump-cmm-raw when compiling .cmm This patch fixes missing -ddump-cmm-raw output when compiling .cmm, which is useful for debugging cmm related codegen issues. - - - - - 1c834ad4 by Ryan Scott at 2024-06-01T09:37:40-04:00 Print namespace specifiers in FixitySig's Outputable instance For whatever reason, the `Outputable` instance for `FixitySig` simply did not print out namespace specifiers, leading to the confusing `-ddump-splices` output seen in #24911. This patch corrects this oversight. Fixes #24911. - - - - - cf49fb5f by Sylvain Henry at 2024-06-01T09:38:19-04:00 Configure: display C++ compiler path - - - - - f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - d70abb49 by sheaf at 2024-06-18T18:47:20-04:00 Clarify -XGADTs enables existential quantification Even though -XGADTs does not turn on -XExistentialQuantification, it does allow the user of existential quantification syntax, without needing to use GADT-style syntax. Fixes #20865 - - - - - 13fdf788 by David Binder at 2024-06-18T18:48:02-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 1bab7dde by Fendor at 2024-06-18T18:48:38-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18698b T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The tests T16875 and T18698b fail on i386-linux for the same reason. - - - - - 099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - 5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00 Update user guide to indicate support for 64-tuples - - - - - 4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00 Remove duplicate Anno instances - - - - - 8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00 AArch64: Delete unused RegNos This has the additional benefit of getting rid of the -1 encoding (real registers start at 0.) - - - - - 325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00 Bump stm submodule to current master - - - - - 64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00 testsuite: bump T17572 timeout on wasm32 - - - - - eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00 AArch64: Simplify BL instruction The BL constructor carried unused data in its third argument. - - - - - b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00 TTG: Move SourceText from `Fixity` to `FixitySig` It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Precedes !12842, to simplify it - - - - - 842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00 base: Deprecate some .Internal modules Deprecates the following modules according to clc-proposal #217: https://github.com/haskell/core-libraries-committee/issues/217 * GHC.TypeNats.Internal * GHC.TypeLits.Internal * GHC.ExecutionStack.Internal Closes #24998 - - - - - 24e89c40 by Jacco Krijnen at 2024-06-20T07:21:27-04:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 04f5bb85 by Simon Peyton Jones at 2024-06-20T07:22:03-04:00 Fix untouchability test This MR fixes #24938. The underlying problem was tha the test for "does this implication bring in scope any equalities" was plain wrong. See Note [Tracking Given equalities] and Note [Let-bound skolems] both in GHC.Tc.Solver.InertSet. Then * Test LocalGivenEqs succeeds for a different reason than before; see (LBS2) in Note [Let-bound skolems] * New test T24938a succeeds because of (LBS2), whereas it failed before. * Test LocalGivenEqs2 now fails, as it should. * Test T224938, the repro from the ticket, fails, as it should. - - - - - 9a757a27 by Simon Peyton Jones at 2024-06-20T07:22:40-04:00 Fix demand signatures for join points This MR tackles #24623 and #23113 The main change is to give a clearer notion of "worker/wrapper arity", esp for join points. See GHC.Core.Opt.DmdAnal Note [Worker/wrapper arity and join points] This Note is a good summary of what this MR does: (1) The "worker/wrapper arity" of an Id is * For non-join-points: idArity * The join points: the join arity (Id part only of course) This is the number of args we will use in worker/wrapper. See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`. (2) A join point's demand-signature arity may exceed the Id's worker/wrapper arity. See the `arity_ok` assertion in `mkWwBodies`. (3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond the worker/wrapper arity. (4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper arity (re)-computed by workWrapArity. - - - - - 5e8faaf1 by Jan Hrček at 2024-06-20T07:23:20-04:00 Update haddocks of Import/Export AST types - - - - - cd512234 by Hécate Kleidukos at 2024-06-20T07:24:02-04:00 haddock: Update bounds in cabal files and remove allow-newer stanza in cabal.project - - - - - 8a8ff8f2 by Rodrigo Mesquita at 2024-06-20T07:24:38-04:00 cmm: Don't parse MO_BSwap for W8 Don't support parsing bswap8, since bswap8 is not really an operation and would have to be implemented as a no-op (and currently is not implemented at all). Fixes #25002 - - - - - 5cc472f5 by sheaf at 2024-06-20T07:25:14-04:00 Delete unused testsuite files These files were committed by mistake in !11902. This commit simply removes them. - - - - - 7b079378 by Matthew Pickering at 2024-06-20T07:25:50-04:00 Remove left over debugging pragma from 2016 This pragma was accidentally introduced in 648fd73a7b8fbb7955edc83330e2910428e76147 The top-level cost centres lead to a lack of optimisation when compiling with profiling. - - - - - 0f3d44eb by Simon Peyton Jones at 2024-06-20T13:53:20+01:00 Work in progress on unfoldings re-engineering - - - - - c62a00c2 by Simon Peyton Jones at 2024-06-20T13:53:20+01:00 Fix a bad, subtle bug in exprIsConApp_maybe In extend_in_scope We were simply overwriting useful bindings in the in-scope set, notably ones that had unfoldings. That could lead to repeated simplifier iterations. - - - - - 0b2e013e by Simon Peyton Jones at 2024-06-20T13:53:20+01:00 Minor refactoring... Plus: don't be so eager to inline when argument is a non-value, but has some struture. We want *some* incentive though. - - - - - 0df6faf3 by Simon Peyton Jones at 2024-06-20T13:53:20+01:00 Adjust * Reduce caseElimDiscount to 10 Example: f_nand in spectral/hartel/event is quite big but was still getting inlined; that make f_simulate too big for SpecConstr * Increase jumpSize. Not so much cheaper than tail calls. I'm trying making them the same size. - - - - - 72d4821d by Simon Peyton Jones at 2024-06-20T13:53:20+01:00 Typo - - - - - 30 changed files: - + .git-blame-ignore-revs - .gitignore - .gitlab-ci.yml - .gitlab/ci.sh - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - + .gitlab/merge_request_templates/Haddock.md - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - .gitlab/rel_eng/recompress-all - .gitmodules - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Builtin/primops.txt.pp - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/ByteCode/Instr.hs - compiler/GHC/ByteCode/Linker.hs - compiler/GHC/ByteCode/Types.hs - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Config.hs - compiler/GHC/Cmm/LRegSet.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/MachOp.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Opt.hs - compiler/GHC/Cmm/Parser.y The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1a2c37f050c7bd8258fc37c1d4b8997f8cb81708...72d4821d36ba2730427aca15c045b3b430ae7f04 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/1a2c37f050c7bd8258fc37c1d4b8997f8cb81708...72d4821d36ba2730427aca15c045b3b430ae7f04 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 13:26:22 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 20 Jun 2024 09:26:22 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] debugging mkRegRegMove Message-ID: <66742dfe17416_3003343474ac434a2@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 1c5e1428 by sheaf at 2024-06-20T15:26:10+02:00 debugging mkRegRegMove - - - - - 8 changed files: - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs - compiler/GHC/CmmToAsm/Reg/Linear/State.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs Changes: ===================================== compiler/GHC/CmmToAsm.hs ===================================== @@ -500,7 +500,7 @@ cmmNativeGen logger ncgImpl us fileIds dbgMap cmm count if ( ncgRegsGraph config || ncgRegsIterative config ) then do -- the regs usable for allocation - let (alloc_regs :: UniqFM RegClass (UniqSet RealReg)) + let alloc_regs :: UniqFM RegClass (UniqSet RealReg) = foldr (\r -> plusUFM_C unionUniqSets $ unitUFM (targetClassOfRealReg platform r) (unitUniqSet r)) emptyUFM ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -704,7 +704,11 @@ saveClobberedTemps clobbered dying = do platform <- getPlatform freeRegs <- getFreeRegsR - let regclass = targetClassOfRealReg platform reg + let regclass + | isIntFormat fmt + = RcInteger + | otherwise + = RcFloatOrVector freeRegs_thisClass = frGetFreeRegs platform regclass freeRegs case filter (`notElem` clobbered) freeRegs_thisClass of ===================================== compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs ===================================== @@ -55,7 +55,7 @@ getStackSlotFor fs@(StackMap _ reserved) _fmt regUnique getStackSlotFor (StackMap freeSlot reserved) fmt regUnique = let - nbSlots = max 1 (formatInBytes fmt `div` 8) + nbSlots = ( formatInBytes fmt + 7 ) `div` 8 in (StackMap (freeSlot+nbSlots) (addToUFM reserved regUnique freeSlot), freeSlot) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/State.hs ===================================== @@ -42,6 +42,7 @@ import GHC.CmmToAsm.Reg.Linear.Stats import GHC.CmmToAsm.Reg.Linear.StackMap import GHC.CmmToAsm.Reg.Linear.Base import GHC.CmmToAsm.Reg.Liveness +import GHC.CmmToAsm.Format import GHC.CmmToAsm.Instr import GHC.CmmToAsm.Config import GHC.Cmm.BlockId @@ -52,7 +53,7 @@ import GHC.Types.Unique.Supply import GHC.Exts (oneShot) import Control.Monad (ap) -import GHC.CmmToAsm.Format + type RA_Result freeRegs a = (# RA_State freeRegs, a #) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/X86.hs ===================================== @@ -21,29 +21,27 @@ noFreeRegs = FreeRegs 0 releaseReg :: RealReg -> FreeRegs -> FreeRegs releaseReg (RealRegSingle n) (FreeRegs f) - = FreeRegs (f .|. (1 `shiftL` n)) + = FreeRegs (setBit f n) initFreeRegs :: Platform -> FreeRegs initFreeRegs platform = foldl' (flip releaseReg) noFreeRegs (allocatableRegs platform) getFreeRegs :: Platform -> RegClass -> FreeRegs -> [RealReg] -- lazily -getFreeRegs platform cls (FreeRegs f) = go f 0 - - where go 0 _ = [] - go n m - | n .&. 1 /= 0 && compatibleClass m - = RealRegSingle m : (go (n `shiftR` 1) $! (m+1)) - - | otherwise - = go (n `shiftR` 1) $! (m+1) - -- ToDo: there's no point looking through all the integer registers - -- in order to find a floating-point one. - compatibleClass i = - cls == classOfRealReg platform (RealRegSingle i) - +getFreeRegs platform cls (FreeRegs f) = + case cls of + RcInteger -> + [ RealRegSingle i + | i <- [ 0 .. lastint platform ] + , testBit f i + ] + RcFloatOrVector -> + [ RealRegSingle i + | i <- [ lastint platform + 1 .. lastxmm platform ] + , testBit f i + ] allocateReg :: RealReg -> FreeRegs -> FreeRegs allocateReg (RealRegSingle r) (FreeRegs f) - = FreeRegs (f .&. complement (1 `shiftL` r)) + = FreeRegs (clearBit f r) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs ===================================== @@ -21,28 +21,27 @@ noFreeRegs = FreeRegs 0 releaseReg :: RealReg -> FreeRegs -> FreeRegs releaseReg (RealRegSingle n) (FreeRegs f) - = FreeRegs (f .|. (1 `shiftL` n)) + = FreeRegs (setBit f n) initFreeRegs :: Platform -> FreeRegs initFreeRegs platform = foldl' (flip releaseReg) noFreeRegs (allocatableRegs platform) getFreeRegs :: Platform -> RegClass -> FreeRegs -> [RealReg] -- lazily -getFreeRegs platform cls (FreeRegs f) = go f 0 - - where go 0 _ = [] - go n m - | n .&. 1 /= 0 && compatibleClass m - = RealRegSingle m : (go (n `shiftR` 1) $! (m+1)) - - | otherwise - = go (n `shiftR` 1) $! (m+1) - -- ToDo: there's no point looking through all the integer registers - -- in order to find a floating-point one. - compatibleClass i = - cls == classOfRealReg platform (RealRegSingle i) +getFreeRegs platform cls (FreeRegs f) = + case cls of + RcInteger -> + [ RealRegSingle i + | i <- [ 0 .. lastint platform ] + , testBit f i + ] + RcFloatOrVector -> + [ RealRegSingle i + | i <- [ lastint platform + 1 .. lastxmm platform ] + , testBit f i + ] allocateReg :: RealReg -> FreeRegs -> FreeRegs allocateReg (RealRegSingle r) (FreeRegs f) - = FreeRegs (f .&. complement (1 `shiftL` r)) + = FreeRegs (clearBit f r) ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -2086,12 +2086,12 @@ intLoadCode instr mem = do -- Compute an expression into *any* register, adding the appropriate -- move instruction if necessary. -getAnyReg :: CmmExpr -> NatM (Reg -> InstrBlock) +getAnyReg :: HasDebugCallStack => CmmExpr -> NatM (Reg -> InstrBlock) getAnyReg expr = do r <- getRegister expr anyReg r -anyReg :: Register -> NatM (Reg -> InstrBlock) +anyReg :: HasDebugCallStack => Register -> NatM (Reg -> InstrBlock) anyReg (Any _ code) = return code anyReg (Fixed rep reg fcode) = do platform <- getPlatform @@ -2100,7 +2100,7 @@ anyReg (Fixed rep reg fcode) = do -- A bit like getSomeReg, but we want a reg that can be byte-addressed. -- Fixed registers might not be byte-addressable, so we make sure we've -- got a temporary, inserting an extra reg copy if necessary. -getByteReg :: CmmExpr -> NatM (Reg, InstrBlock) +getByteReg :: HasDebugCallStack => CmmExpr -> NatM (Reg, InstrBlock) getByteReg expr = do platform <- getPlatform is32Bit <- is32BitPlatform @@ -2122,7 +2122,7 @@ getByteReg expr = do -- Another variant: this time we want the result in a register that cannot -- be modified by code to evaluate an arbitrary expression. -getNonClobberedReg :: CmmExpr -> NatM (Reg, InstrBlock) +getNonClobberedReg :: HasDebugCallStack => CmmExpr -> NatM (Reg, InstrBlock) getNonClobberedReg expr = do r <- getRegister expr platform <- ncgPlatform <$> getConfig ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -46,10 +46,13 @@ import GHC.Data.FastString import GHC.CmmToAsm.X86.Cond import GHC.CmmToAsm.X86.Regs import GHC.CmmToAsm.Format +import GHC.CmmToAsm.Reg.Target (targetClassOfReg) import GHC.CmmToAsm.Types import GHC.CmmToAsm.Utils import GHC.CmmToAsm.Instr (RegUsage(..), noUsage) import GHC.Platform.Reg +import GHC.Platform.Reg.Class + import GHC.CmmToAsm.Config import GHC.Cmm.BlockId @@ -66,9 +69,9 @@ import GHC.Types.Unique import GHC.Types.Unique.Supply import GHC.Types.Basic (Alignment) import GHC.Cmm.DebugBlock (UnwindTable) +import GHC.Utils.Misc ( HasDebugCallStack ) import Data.Maybe (fromMaybe) -import GHC.CmmToAsm.Reg.Target (targetClassOfReg) -- Format of an x86/x86_64 memory address, in bytes. -- @@ -948,7 +951,8 @@ isMetaInstr instr -- | Make a reg-reg move instruction. mkRegRegMoveInstr - :: Platform + :: HasDebugCallStack + => Platform -> Format -> Reg -> Reg @@ -965,7 +969,18 @@ mkRegRegMoveInstr platform fmt src dst = then MOVU fmt (OpReg src) (OpReg dst) else VMOVU fmt (OpReg src) (OpReg dst) _ -> - MOV (scalarMoveFormat platform fmt) (OpReg src) (OpReg dst) + let fmt' = scalarMoveFormat platform fmt + cls_f = if isIntFormat fmt' then RcInteger else RcFloatOrVector + cls1 = targetClassOfReg platform src + cls2 = targetClassOfReg platform dst + in + assertPpr (all (== cls_f) [cls1, cls2]) + (vcat [ text "mkRegRegMoveInstr: incompatible formats" + , text "format:" <+> ppr fmt <+> parens (ppr cls_f) + , text "src:" <+> ppr src <+> parens (ppr cls1) + , text "dst:" <+> ppr dst <+> parens (ppr cls2) + , callStackDoc ]) + $ MOV (scalarMoveFormat platform fmt) (OpReg src) (OpReg dst) scalarMoveFormat :: Platform -> Format -> Format scalarMoveFormat platform fmt View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1c5e1428042ebde5f7c73e53d0860a78deea44b5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/1c5e1428042ebde5f7c73e53d0860a78deea44b5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 14:39:05 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 20 Jun 2024 10:39:05 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] debugging mkRegRegMove Message-ID: <66743f0922822_300334cf8730562d2@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 342cc709 by sheaf at 2024-06-20T16:38:53+02:00 debugging mkRegRegMove - - - - - 11 changed files: - compiler/GHC/CmmToAsm.hs - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs - compiler/GHC/CmmToAsm/Reg/Linear/State.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs Changes: ===================================== compiler/GHC/CmmToAsm.hs ===================================== @@ -500,7 +500,7 @@ cmmNativeGen logger ncgImpl us fileIds dbgMap cmm count if ( ncgRegsGraph config || ncgRegsIterative config ) then do -- the regs usable for allocation - let (alloc_regs :: UniqFM RegClass (UniqSet RealReg)) + let alloc_regs :: UniqFM RegClass (UniqSet RealReg) = foldr (\r -> plusUFM_C unionUniqSets $ unitUFM (targetClassOfRealReg platform r) (unitUniqSet r)) emptyUFM ===================================== compiler/GHC/CmmToAsm/Instr.hs ===================================== @@ -18,6 +18,8 @@ import GHC.CmmToAsm.Config import GHC.Data.FastString import GHC.CmmToAsm.Format +import GHC.Utils.Misc (HasDebugCallStack) + -- | Holds a list of source and destination registers used by a -- particular instruction. -- @@ -131,7 +133,8 @@ class Instruction instr where -- | Copy the value in a register to another one. -- Must work for all register classes. mkRegRegMoveInstr - :: Platform + :: HasDebugCallStack + => Platform -> Format -> Reg -- ^ source register -> Reg -- ^ destination register ===================================== compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs ===================================== @@ -9,11 +9,12 @@ module GHC.CmmToAsm.Reg.Graph.Spill ( import GHC.Prelude +import GHC.CmmToAsm.Format ( RegFormat(..) ) import GHC.CmmToAsm.Reg.Liveness import GHC.CmmToAsm.Reg.Utils import GHC.CmmToAsm.Instr import GHC.Platform.Reg -import GHC.Cmm hiding (RegSet) +import GHC.Cmm import GHC.Cmm.BlockId import GHC.Cmm.Dataflow.Label @@ -34,9 +35,6 @@ import Data.List (intersectBy) import Data.Maybe import Data.IntSet (IntSet) import qualified Data.IntSet as IntSet -import GHC.CmmToAsm.Format ( RegFormat(RegFormat, regFormatReg) ) - - -- | Spill all these virtual regs to stack slots. ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -124,7 +124,7 @@ import GHC.Platform.Reg.Class (RegClass(..)) import GHC.Cmm.BlockId import GHC.Cmm.Dataflow.Label -import GHC.Cmm hiding (RegSet) +import GHC.Cmm import GHC.Data.Graph.Directed import GHC.Types.Unique @@ -704,7 +704,11 @@ saveClobberedTemps clobbered dying = do platform <- getPlatform freeRegs <- getFreeRegsR - let regclass = targetClassOfRealReg platform reg + let regclass + | isIntFormat fmt + = RcInteger + | otherwise + = RcFloatOrVector freeRegs_thisClass = frGetFreeRegs platform regclass freeRegs case filter (`notElem` clobbered) freeRegs_thisClass of ===================================== compiler/GHC/CmmToAsm/Reg/Linear/StackMap.hs ===================================== @@ -55,7 +55,7 @@ getStackSlotFor fs@(StackMap _ reserved) _fmt regUnique getStackSlotFor (StackMap freeSlot reserved) fmt regUnique = let - nbSlots = max 1 (formatInBytes fmt `div` 8) + nbSlots = (formatInBytes fmt + 7) `div` 8 in (StackMap (freeSlot+nbSlots) (addToUFM reserved regUnique freeSlot), freeSlot) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/State.hs ===================================== @@ -42,6 +42,7 @@ import GHC.CmmToAsm.Reg.Linear.Stats import GHC.CmmToAsm.Reg.Linear.StackMap import GHC.CmmToAsm.Reg.Linear.Base import GHC.CmmToAsm.Reg.Liveness +import GHC.CmmToAsm.Format import GHC.CmmToAsm.Instr import GHC.CmmToAsm.Config import GHC.Cmm.BlockId @@ -52,7 +53,7 @@ import GHC.Types.Unique.Supply import GHC.Exts (oneShot) import Control.Monad (ap) -import GHC.CmmToAsm.Format + type RA_Result freeRegs a = (# RA_State freeRegs, a #) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/X86.hs ===================================== @@ -21,29 +21,27 @@ noFreeRegs = FreeRegs 0 releaseReg :: RealReg -> FreeRegs -> FreeRegs releaseReg (RealRegSingle n) (FreeRegs f) - = FreeRegs (f .|. (1 `shiftL` n)) + = FreeRegs (setBit f n) initFreeRegs :: Platform -> FreeRegs initFreeRegs platform = foldl' (flip releaseReg) noFreeRegs (allocatableRegs platform) getFreeRegs :: Platform -> RegClass -> FreeRegs -> [RealReg] -- lazily -getFreeRegs platform cls (FreeRegs f) = go f 0 - - where go 0 _ = [] - go n m - | n .&. 1 /= 0 && compatibleClass m - = RealRegSingle m : (go (n `shiftR` 1) $! (m+1)) - - | otherwise - = go (n `shiftR` 1) $! (m+1) - -- ToDo: there's no point looking through all the integer registers - -- in order to find a floating-point one. - compatibleClass i = - cls == classOfRealReg platform (RealRegSingle i) - +getFreeRegs platform cls (FreeRegs f) = + case cls of + RcInteger -> + [ RealRegSingle i + | i <- [ 0 .. lastint platform ] + , testBit f i + ] + RcFloatOrVector -> + [ RealRegSingle i + | i <- [ lastint platform + 1 .. lastxmm platform ] + , testBit f i + ] allocateReg :: RealReg -> FreeRegs -> FreeRegs allocateReg (RealRegSingle r) (FreeRegs f) - = FreeRegs (f .&. complement (1 `shiftL` r)) + = FreeRegs (clearBit f r) ===================================== compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs ===================================== @@ -21,28 +21,27 @@ noFreeRegs = FreeRegs 0 releaseReg :: RealReg -> FreeRegs -> FreeRegs releaseReg (RealRegSingle n) (FreeRegs f) - = FreeRegs (f .|. (1 `shiftL` n)) + = FreeRegs (setBit f n) initFreeRegs :: Platform -> FreeRegs initFreeRegs platform = foldl' (flip releaseReg) noFreeRegs (allocatableRegs platform) getFreeRegs :: Platform -> RegClass -> FreeRegs -> [RealReg] -- lazily -getFreeRegs platform cls (FreeRegs f) = go f 0 - - where go 0 _ = [] - go n m - | n .&. 1 /= 0 && compatibleClass m - = RealRegSingle m : (go (n `shiftR` 1) $! (m+1)) - - | otherwise - = go (n `shiftR` 1) $! (m+1) - -- ToDo: there's no point looking through all the integer registers - -- in order to find a floating-point one. - compatibleClass i = - cls == classOfRealReg platform (RealRegSingle i) +getFreeRegs platform cls (FreeRegs f) = + case cls of + RcInteger -> + [ RealRegSingle i + | i <- [ 0 .. lastint platform ] + , testBit f i + ] + RcFloatOrVector -> + [ RealRegSingle i + | i <- [ lastint platform + 1 .. lastxmm platform ] + , testBit f i + ] allocateReg :: RealReg -> FreeRegs -> FreeRegs allocateReg (RealRegSingle r) (FreeRegs f) - = FreeRegs (f .&. complement (1 `shiftL` r)) + = FreeRegs (clearBit f r) ===================================== compiler/GHC/CmmToAsm/Reg/Liveness.hs ===================================== @@ -12,7 +12,6 @@ ----------------------------------------------------------------------------- module GHC.CmmToAsm.Reg.Liveness ( - RegSet, RegMap, emptyRegMap, BlockMap, mapEmpty, LiveCmmDecl, @@ -48,7 +47,7 @@ import GHC.CmmToAsm.Utils import GHC.Cmm.BlockId import GHC.Cmm.Dataflow.Label -import GHC.Cmm hiding (RegSet, emptyRegSet) +import GHC.Cmm import GHC.Data.Graph.Directed import GHC.Utils.Monad @@ -67,7 +66,6 @@ import Data.Maybe import Data.IntSet (IntSet) ----------------------------------------------------------------------------- -type RegSet = UniqSet Reg -- | Map from some kind of register to a. -- ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -2086,12 +2086,12 @@ intLoadCode instr mem = do -- Compute an expression into *any* register, adding the appropriate -- move instruction if necessary. -getAnyReg :: CmmExpr -> NatM (Reg -> InstrBlock) +getAnyReg :: HasDebugCallStack => CmmExpr -> NatM (Reg -> InstrBlock) getAnyReg expr = do r <- getRegister expr anyReg r -anyReg :: Register -> NatM (Reg -> InstrBlock) +anyReg :: HasDebugCallStack => Register -> NatM (Reg -> InstrBlock) anyReg (Any _ code) = return code anyReg (Fixed rep reg fcode) = do platform <- getPlatform @@ -2100,7 +2100,7 @@ anyReg (Fixed rep reg fcode) = do -- A bit like getSomeReg, but we want a reg that can be byte-addressed. -- Fixed registers might not be byte-addressable, so we make sure we've -- got a temporary, inserting an extra reg copy if necessary. -getByteReg :: CmmExpr -> NatM (Reg, InstrBlock) +getByteReg :: HasDebugCallStack => CmmExpr -> NatM (Reg, InstrBlock) getByteReg expr = do platform <- getPlatform is32Bit <- is32BitPlatform @@ -2122,7 +2122,7 @@ getByteReg expr = do -- Another variant: this time we want the result in a register that cannot -- be modified by code to evaluate an arbitrary expression. -getNonClobberedReg :: CmmExpr -> NatM (Reg, InstrBlock) +getNonClobberedReg :: HasDebugCallStack => CmmExpr -> NatM (Reg, InstrBlock) getNonClobberedReg expr = do r <- getRegister expr platform <- ncgPlatform <$> getConfig ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -46,10 +46,13 @@ import GHC.Data.FastString import GHC.CmmToAsm.X86.Cond import GHC.CmmToAsm.X86.Regs import GHC.CmmToAsm.Format +import GHC.CmmToAsm.Reg.Target (targetClassOfReg) import GHC.CmmToAsm.Types import GHC.CmmToAsm.Utils import GHC.CmmToAsm.Instr (RegUsage(..), noUsage) import GHC.Platform.Reg +import GHC.Platform.Reg.Class + import GHC.CmmToAsm.Config import GHC.Cmm.BlockId @@ -66,9 +69,9 @@ import GHC.Types.Unique import GHC.Types.Unique.Supply import GHC.Types.Basic (Alignment) import GHC.Cmm.DebugBlock (UnwindTable) +import GHC.Utils.Misc ( HasDebugCallStack ) import Data.Maybe (fromMaybe) -import GHC.CmmToAsm.Reg.Target (targetClassOfReg) -- Format of an x86/x86_64 memory address, in bytes. -- @@ -948,7 +951,8 @@ isMetaInstr instr -- | Make a reg-reg move instruction. mkRegRegMoveInstr - :: Platform + :: HasDebugCallStack + => Platform -> Format -> Reg -> Reg @@ -965,7 +969,18 @@ mkRegRegMoveInstr platform fmt src dst = then MOVU fmt (OpReg src) (OpReg dst) else VMOVU fmt (OpReg src) (OpReg dst) _ -> - MOV (scalarMoveFormat platform fmt) (OpReg src) (OpReg dst) + let fmt' = scalarMoveFormat platform fmt + cls_f = if isIntFormat fmt' then RcInteger else RcFloatOrVector + cls1 = targetClassOfReg platform src + cls2 = targetClassOfReg platform dst + in + assertPpr (all (== cls_f) [cls1, cls2]) + (vcat [ text "mkRegRegMoveInstr: incompatible formats" + , text "format:" <+> ppr fmt <+> parens (ppr cls_f) + , text "src:" <+> ppr src <+> parens (ppr cls1) + , text "dst:" <+> ppr dst <+> parens (ppr cls2) + , callStackDoc ]) + $ MOV (scalarMoveFormat platform fmt) (OpReg src) (OpReg dst) scalarMoveFormat :: Platform -> Format -> Format scalarMoveFormat platform fmt View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/342cc709600e2eee3eff1ceef93b6f4923d2899b -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/342cc709600e2eee3eff1ceef93b6f4923d2899b You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 15:17:38 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 20 Jun 2024 11:17:38 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: Derive previously hand-written `Lift` instances (#14030) Message-ID: <66744812cfb6a_3003341305d0868066@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 216a282d by Sebastian Graf at 2024-06-20T11:17:30-04:00 Derive previously hand-written `Lift` instances (#14030) This is possible now that #22229 is fixed. - - - - - a82770d7 by Sebastian Graf at 2024-06-20T11:17:30-04:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. - - - - - 02ec5a0a by Hécate Kleidukos at 2024-06-20T11:17:33-04:00 haddock: Remove unused pragmata, qualify usages of Data.List functions, add more sanity checking flags by default This commit enables some extensions and GHC flags in the cabal file in a way that allows us to reduce the amount of prologuing on top of each file. We also prefix the usage of some List functions that removes ambiguity when they are also exported from the Prelude, like foldl'. In general, this has the effect of pointing out more explicitly that a linked list is used. Metric Increase: haddock.Cabal haddock.base haddock.compiler - - - - - 9f86ba72 by Arnaud Spiwack at 2024-06-20T11:17:33-04:00 Add test case for #23586 - - - - - 3d4e11d2 by Arnaud Spiwack at 2024-06-20T11:17:33-04:00 When matching functions in rewrite rules: ignore multiplicity When matching a template variable to an expression, we check that it has the same type as the matched expression. But if the variable `f` has type `A -> B` while the expression `e` has type `A %1 -> B`, the match was previously rejected. A principled solution would have `f` substituted by `\(%Many x) -> e x` or some other appropriate coercion. But since linearity is not properly checked in Core, we can be cheeky and simply ignore multiplicity while matching. Much easier. This has forced a change in the linter which, when `-dlinear-core-lint` is off, must consider that `a -> b` and `a %1 -> b` are equal. This is achieved by adding an argument to configure the behaviour of `nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour which ignores multiplicities when comparing two `FunTy`. Fixes #24725. - - - - - 34ad82c7 by Simon Peyton Jones at 2024-06-20T11:17:34-04:00 Faster type equality This MR speeds up type equality, triggered by perf regressions that showed up when fixing #24725 by parameterising type equality over whether to ignore multiplicity. The changes are: * Do not use `nonDetCmpType` for type /equality/. Instead use a specialised type-equality function, which we have always had! `nonDetCmpType` remains, but I did not invest effort in refactoring or optimising it. * Type equality is parameterised by - whether to expand synonyms - whether to respect multiplicities - whether it has a RnEnv2 environment In this MR I systematically specialise it for static values of these parameters. Much more direct and predictable than before. See Note [Specialising type equality] * We want to avoid comparing kinds if possible. I refactored how this happens, at least for `eqType`. See Note [Casts and coercions in type comparison] * To make Lint fast, we want to avoid allocating a thunk for <msg> in ensureEqTypes ty1 ty2 <msg> because the test almost always succeeds, and <msg> isn't needed. See Note [INLINE ensureEqTys] Metric Decrease: T13386 T5030 - - - - - 30 changed files: - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Multiplicity.hs - compiler/GHC/Core/TyCo/Compare.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Utils/TcType.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - testsuite/tests/ghci/scripts/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - + testsuite/tests/simplCore/should_run/T23586.hs - + testsuite/tests/simplCore/should_run/T23586.stdout - testsuite/tests/simplCore/should_run/all.T - testsuite/tests/th/TH_Lift.hs - + testsuite/tests/th/TH_Lift.stderr - testsuite/tests/th/all.T - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/src/Haddock.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface.hs - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Options.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/haddock-library/fixtures/Fixtures.hs - utils/haddock/haddock-library/haddock-library.cabal The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3becee5061a4f8ab153231bb42bfc24a596b6b17...34ad82c7feb1ee8cb807fb335852edd08b008706 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/3becee5061a4f8ab153231bb42bfc24a596b6b17...34ad82c7feb1ee8cb807fb335852edd08b008706 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 15:31:29 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 20 Jun 2024 11:31:29 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] test: Eq/Ord RealRegUsage Message-ID: <66744b518343c_30033416a09547612f@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 71c19ee0 by sheaf at 2024-06-20T17:31:22+02:00 test: Eq/Ord RealRegUsage - - - - - 1 changed file: - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs Changes: ===================================== compiler/GHC/CmmToAsm/Reg/Linear/Base.hs ===================================== @@ -39,6 +39,8 @@ import GHC.Cmm.Dataflow.Label import GHC.CmmToAsm.Reg.Utils import GHC.CmmToAsm.Format +import Data.Function ( on ) + data ReadingOrWriting = Reading | Writing deriving (Eq,Ord) -- | Used to store the register assignment on entry to a basic block. @@ -105,13 +107,18 @@ data Loc -- | vreg is held in both a register and stack slots | InBoth {-# UNPACK #-} !RealRegUsage {-# UNPACK #-} !StackSlot - deriving (Eq, Show, Ord) + deriving (Eq, Ord, Show) data RealRegUsage = RealRegUsage { realReg :: !RealReg , realRegFormat :: !Format - } deriving (Eq, Show, Ord) + } deriving Show + +instance Eq RealRegUsage where + (==) = (==) `on` realReg +instance Ord RealRegUsage where + compare = compare `on` realReg instance Outputable Loc where ppr l = text (show l) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/71c19ee0400a1a3a63c05fa3909e2039ac71bc86 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/71c19ee0400a1a3a63c05fa3909e2039ac71bc86 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 16:20:44 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 20 Jun 2024 12:20:44 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/llvm-version-bsd Message-ID: <667456dc99900_3003341faa6bc84998@gitlab.mail> Matthew Pickering pushed new branch wip/llvm-version-bsd at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/llvm-version-bsd You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 16:28:06 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 20 Jun 2024 12:28:06 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] WIP: more SIMD debugging Message-ID: <6674589682306_3003342105868869c0@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 9c1487b5 by sheaf at 2024-06-20T18:27:54+02:00 WIP: more SIMD debugging - - - - - 6 changed files: - compiler/GHC/CmmToAsm/Format.hs - compiler/GHC/CmmToAsm/Reg/Graph.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/Base.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/Reg/Target.hs Changes: ===================================== compiler/GHC/CmmToAsm/Format.hs ===================================== @@ -29,7 +29,6 @@ module GHC.CmmToAsm.Format ( RegFormat(..), takeVirtualRegs, takeRealRegs, - mapRegFormatSet, ) where @@ -43,6 +42,7 @@ import GHC.Types.Unique.Set import GHC.Utils.Outputable import GHC.Utils.Panic + {- Note [GHC's data format representations] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ GHC has severals types that represent various aspects of data format. @@ -239,5 +239,3 @@ takeRealRegs = mapMaybeUniqSet_sameUnique $ \ case { RegFormat { regFormatReg = RegReal rr } -> Just rr; _ -> Nothing } -- See Note [Unique Determinism and code generation] -mapRegFormatSet :: (Reg -> Reg) -> UniqSet RegFormat -> UniqSet RegFormat -mapRegFormatSet f = mapUniqSet (\ ( RegFormat r fmt ) -> RegFormat ( f r ) fmt) ===================================== compiler/GHC/CmmToAsm/Reg/Graph.hs ===================================== @@ -33,7 +33,7 @@ import GHC.Platform import GHC.Types.Unique.FM import GHC.Types.Unique.Set import GHC.Types.Unique.Supply -import GHC.Utils.Misc (seqList) +import GHC.Utils.Misc (seqList, HasDebugCallStack) import GHC.CmmToAsm.CFG import Data.Maybe @@ -96,7 +96,8 @@ regAlloc config regsFree slotsFree slotsCount code cfg regAlloc_spin :: forall instr statics. (Instruction instr, - OutputableP Platform statics) + OutputableP Platform statics, + HasDebugCallStack) => NCGConfig -> Int -- ^ Number of solver iterations we've already performed. -> Color.Triv VirtualReg RegClass RealReg ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -727,7 +727,7 @@ saveClobberedTemps clobbered dying -- (2) no free registers: spill the value [] -> do - (spill, slot) <- spillR (RegFormat (RegReal reg) fmt) temp + (spill, slot) <- spillR (mkRegFormat platform (RegReal reg) fmt) temp -- record why this reg was spilled for profiling recordSpill (SpillClobber temp) @@ -891,7 +891,7 @@ allocRegsAndSpill_spill reading keep spills alloc (VirtualRegFormat r fmt) rs as = reg | otherwise = first_free - spills' <- loadTemp (VirtualRegFormat r fmt) spill_loc final_reg spills + spills' <- loadTemp platform (VirtualRegFormat r fmt) spill_loc final_reg spills setAssigR $ toRegMap $ (addToUFM assig r $! newLocation spill_loc $ RealRegUsage final_reg fmt) @@ -937,7 +937,7 @@ allocRegsAndSpill_spill reading keep spills alloc (VirtualRegFormat r fmt) rs as -- we have a temporary that is in both register and mem, -- just free up its register for use. | (temp, myRegUse@(RealRegUsage my_reg fmt), slot) : _ <- candidates_inBoth - = do spills' <- loadTemp (VirtualRegFormat r fmt) spill_loc my_reg spills + = do spills' <- loadTemp platform (VirtualRegFormat r fmt) spill_loc my_reg spills let assig1 = addToUFM_Directly assig temp (InMem slot) let assig2 = addToUFM assig1 r $! newLocation spill_loc myRegUse @@ -949,7 +949,7 @@ allocRegsAndSpill_spill reading keep spills alloc (VirtualRegFormat r fmt) rs as | (temp_to_push_out, RealRegUsage my_reg fmt) : _ <- candidates_inReg = do - (spill_store, slot) <- spillR (RegFormat (RegReal my_reg) fmt) temp_to_push_out + (spill_store, slot) <- spillR (mkRegFormat platform (RegReal my_reg) fmt) temp_to_push_out -- record that this temp was spilled recordSpill (SpillAlloc temp_to_push_out) @@ -960,7 +960,7 @@ allocRegsAndSpill_spill reading keep spills alloc (VirtualRegFormat r fmt) rs as setAssigR $ toRegMap assig2 -- if need be, load up a spilled temp into the reg we've just freed up. - spills' <- loadTemp (VirtualRegFormat r fmt) spill_loc my_reg spills + spills' <- loadTemp platform (VirtualRegFormat r fmt) spill_loc my_reg spills allocateRegsAndSpill reading keep (spill_store ++ spills') @@ -990,17 +990,18 @@ newLocation _ my_reg = InReg my_reg -- | Load up a spilled temporary if we need to (read from memory). loadTemp :: (Instruction instr) - => VirtualRegFormat -- the temp being loaded + => Platform + -> VirtualRegFormat -- the temp being loaded -> SpillLoc -- the current location of this temp -> RealReg -- the hreg to load the temp into -> [instr] -> RegM freeRegs [instr] -loadTemp (VirtualRegFormat vreg fmt) (ReadMem slot) hreg spills +loadTemp platform (VirtualRegFormat vreg fmt) (ReadMem slot) hreg spills = do - insn <- loadR (RegFormat (RegReal hreg) fmt) slot + insn <- loadR (mkRegFormat platform (RegReal hreg) fmt) slot recordSpill (SpillLoad $ getUnique vreg) return $ {- mkComment (text "spill load") : -} insn ++ spills -loadTemp _ _ _ spills = +loadTemp _ _ _ _ spills = return spills ===================================== compiler/GHC/CmmToAsm/Reg/Linear/Base.hs ===================================== @@ -12,6 +12,7 @@ module GHC.CmmToAsm.Reg.Linear.Base ( Loc(..), regsOfLoc, RealRegUsage(..), + mkRealRegUsage, -- for stats SpillReason(..), @@ -28,6 +29,7 @@ import GHC.Prelude import GHC.CmmToAsm.Reg.Linear.StackMap import GHC.CmmToAsm.Reg.Liveness import GHC.CmmToAsm.Config +import GHC.Platform import GHC.Platform.Reg import GHC.Utils.Outputable @@ -38,6 +40,9 @@ import GHC.Cmm.BlockId import GHC.Cmm.Dataflow.Label import GHC.CmmToAsm.Reg.Utils import GHC.CmmToAsm.Format +import GHC.Platform.Reg.Class +import GHC.Utils.Panic +import GHC.CmmToAsm.Reg.Target (targetClassOfRealReg) import Data.Function ( on ) @@ -120,6 +125,25 @@ instance Eq RealRegUsage where instance Ord RealRegUsage where compare = compare `on` realReg +mkRealRegUsage :: Platform -> RealReg -> Format -> RealRegUsage +mkRealRegUsage platform reg fmt + = assertPpr (regCls == fmtCls) + (vcat [ text "mkRealRegUsage: incompatible register & format" + , text "reg:" <+> ppr reg <+> dcolon <+> ppr regCls + , text "fmt:" <+> ppr fmt <+> parens (ppr fmtCls) ]) + $ RealRegUsage reg fmt + where + regCls = targetClassOfRealReg platform reg + fmtCls = formatRegClass fmt + +-- TODO: SIMD debugging +formatRegClass :: Format -> RegClass +formatRegClass fmt + | isIntFormat fmt + = RcInteger + | otherwise + = RcFloatOrVector + instance Outputable Loc where ppr l = text (show l) ===================================== compiler/GHC/CmmToAsm/Reg/Liveness.hs ===================================== @@ -48,6 +48,7 @@ import GHC.CmmToAsm.Utils import GHC.Cmm.BlockId import GHC.Cmm.Dataflow.Label import GHC.Cmm +import GHC.CmmToAsm.Reg.Target import GHC.Data.Graph.Directed import GHC.Utils.Monad @@ -64,6 +65,7 @@ import GHC.Utils.Monad.State.Strict import Data.List (mapAccumL, partition) import Data.Maybe import Data.IntSet (IntSet) +import GHC.Utils.Misc ----------------------------------------------------------------------------- @@ -610,7 +612,7 @@ eraseDeltasLive cmm -- also erase reg -> reg moves when the reg is the same. -- also erase reg -> reg moves when the destination dies in this instr. patchEraseLive - :: Instruction instr + :: (Instruction instr, HasDebugCallStack) => Platform -> (Reg -> Reg) -> LiveCmmDecl statics instr -> LiveCmmDecl statics instr @@ -663,7 +665,7 @@ patchEraseLive platform patchF cmm -- | Patch registers in this LiveInstr, including the liveness information. -- patchRegsLiveInstr - :: Instruction instr + :: (Instruction instr, HasDebugCallStack) => (Reg -> Reg) -> LiveInstr instr -> LiveInstr instr ===================================== compiler/GHC/CmmToAsm/Reg/Target.hs ===================================== @@ -14,7 +14,8 @@ module GHC.CmmToAsm.Reg.Target ( targetClassOfRealReg, targetMkVirtualReg, targetRegDotColor, - targetClassOfReg + targetClassOfReg, + mkRegFormat, mapRegFormatSet, ) where @@ -26,8 +27,10 @@ import GHC.Platform.Reg.Class import GHC.CmmToAsm.Format import GHC.Utils.Outputable +import GHC.Utils.Misc import GHC.Utils.Panic import GHC.Types.Unique +import GHC.Types.Unique.Set import GHC.Platform import qualified GHC.CmmToAsm.X86.Regs as X86 @@ -138,3 +141,25 @@ targetClassOfReg platform reg = case reg of RegVirtual vr -> classOfVirtualReg vr RegReal rr -> targetClassOfRealReg platform rr + +mkRegFormat :: HasDebugCallStack => Platform -> Reg -> Format -> RegFormat +mkRegFormat platform reg fmt + = assertPpr (regCls == fmtCls) + (vcat [ text "mkRegFormat: incompatible register & format" + , text "reg:" <+> ppr reg <+> dcolon <+> ppr regCls + , text "fmt:" <+> ppr fmt <+> parens (ppr fmtCls) ]) + $ RegFormat reg fmt + where + regCls = targetClassOfReg platform reg + fmtCls = formatRegClass fmt + +-- TODO: SIMD debugging +formatRegClass :: Format -> RegClass +formatRegClass fmt + | isIntFormat fmt + = RcInteger + | otherwise + = RcFloatOrVector + +mapRegFormatSet :: HasDebugCallStack => (Reg -> Reg) -> UniqSet RegFormat -> UniqSet RegFormat +mapRegFormatSet f = mapUniqSet (\ ( RegFormat r fmt ) -> RegFormat ( f r ) fmt) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9c1487b5bdc322a665e9ab7771f3bbf7c4bf0a13 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9c1487b5bdc322a665e9ab7771f3bbf7c4bf0a13 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 16:44:42 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Thu, 20 Jun 2024 12:44:42 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/bindist-rel Message-ID: <66745c7a4c212_30033425a740c9027c@gitlab.mail> Matthew Pickering pushed new branch wip/bindist-rel at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/bindist-rel You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 17:43:36 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Thu, 20 Jun 2024 13:43:36 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] more SIMD debugging Message-ID: <66746a482b10a_3003342d8563897959@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 85a0b5b0 by sheaf at 2024-06-20T19:43:04+02:00 more SIMD debugging - - - - - 6 changed files: - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Target.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Regs.hs Changes: ===================================== compiler/GHC/CmmToAsm/Instr.hs ===================================== @@ -97,7 +97,8 @@ class Instruction instr where -- | An instruction to spill a register into a spill slot. mkSpillInstr - :: NCGConfig + :: HasDebugCallStack + => NCGConfig -> RegFormat -- ^ the reg to spill -> Int -- ^ the current stack delta -> Int -- ^ spill slots to use @@ -106,7 +107,8 @@ class Instruction instr where -- | An instruction to reload a register from a spill slot. mkLoadInstr - :: NCGConfig + :: HasDebugCallStack + => NCGConfig -> RegFormat -- ^ the reg to reload. -> Int -- ^ the current stack delta -> Int -- ^ the spill slot to use ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -440,7 +440,7 @@ raInsn block_live new_instrs id (LiveInstr (Instr instr) (Just live)) not (dst `elemUFM` assig), isRealReg src || isInReg src assig -> do case src of - RegReal rr -> setAssigR (addToUFM assig dst (InReg $ RealRegUsage rr fmt)) + RegReal rr -> setAssigR (addToUFM assig dst (InReg $ mkRealRegUsage platform rr fmt)) -- if src is a fixed reg, then we just map dest to this -- reg in the assignment. src must be an allocatable reg, -- otherwise it wouldn't be in r_dying. @@ -509,7 +509,7 @@ genRaInsn block_live new_instrs block_id instr r_dying w_dying = do -- only read by this instr. (the list is typically ~2 elements, -- so using nub isn't a problem). let virt_read :: [VirtualRegFormat] - virt_read = nubOrdOn virtualRegFormatReg [ VirtualRegFormat vr fmt | RegFormat (RegVirtual vr) fmt <- read ] + virt_read = nubOrdOn virtualRegFormatReg [ mkVirtualRegFormat vr fmt | RegFormat (RegVirtual vr) fmt <- read ] -- do -- let real_read = nub [ rr | (RegReal rr) <- read] @@ -719,7 +719,7 @@ saveClobberedTemps clobbered dying (my_reg : _) -> do setFreeRegsR (frAllocateReg platform my_reg freeRegs) - let new_assign = addToUFM_Directly assig temp (InReg (RealRegUsage my_reg fmt)) + let new_assign = addToUFM_Directly assig temp (InReg (mkRealRegUsage platform my_reg fmt)) let instr = mkRegRegMoveInstr platform fmt (RegReal reg) (RegReal my_reg) @@ -732,7 +732,7 @@ saveClobberedTemps clobbered dying -- record why this reg was spilled for profiling recordSpill (SpillClobber temp) - let new_assign = addToUFM_Directly assig temp (InBoth (RealRegUsage reg fmt) slot) + let new_assign = addToUFM_Directly assig temp (InBoth (mkRealRegUsage platform reg fmt) slot) return (new_assign, (spill ++ instrs)) @@ -816,12 +816,12 @@ allocateRegsAndSpill allocateRegsAndSpill _ _ spills alloc [] = return (spills, reverse alloc) -allocateRegsAndSpill reading keep spills alloc (VirtualRegFormat r fmt:rs) +allocateRegsAndSpill reading keep spills alloc (r@(VirtualRegFormat vr _fmt):rs) = do assig <- toVRegMap <$> getAssigR -- pprTraceM "allocateRegsAndSpill:assig" (ppr (r:rs) $$ ppr assig) -- See Note [UniqFM and the register allocator] - let doSpill = allocRegsAndSpill_spill reading keep spills alloc (VirtualRegFormat r fmt) rs assig - case lookupUFM assig r of + let doSpill = allocRegsAndSpill_spill reading keep spills alloc r rs assig + case lookupUFM assig vr of -- case (1a): already in a register Just (InReg my_reg) -> allocateRegsAndSpill reading keep spills (realReg my_reg:alloc) rs @@ -832,14 +832,14 @@ allocateRegsAndSpill reading keep spills alloc (VirtualRegFormat r fmt:rs) -- NB2. This is why we must process written registers here, even if they -- are also read by the same instruction. Just (InBoth my_reg _) - -> do when (not reading) (setAssigR $ toRegMap (addToUFM assig r (InReg my_reg))) + -> do when (not reading) (setAssigR $ toRegMap (addToUFM assig vr (InReg my_reg))) allocateRegsAndSpill reading keep spills (realReg my_reg:alloc) rs -- Not already in a register, so we need to find a free one... Just (InMem slot) | reading -> doSpill (ReadMem slot) | otherwise -> doSpill WriteMem Nothing | reading -> - pprPanic "allocateRegsAndSpill: Cannot read from uninitialized register" (ppr r) + pprPanic "allocateRegsAndSpill: Cannot read from uninitialized register" (ppr vr) -- NOTE: if the input to the NCG contains some -- unreachable blocks with junk code, this panic -- might be triggered. Make sure you only feed @@ -873,14 +873,14 @@ allocRegsAndSpill_spill :: (FR freeRegs, Instruction instr) -> UniqFM VirtualReg Loc -> SpillLoc -> RegM freeRegs ([instr], [RealReg]) -allocRegsAndSpill_spill reading keep spills alloc (VirtualRegFormat r fmt) rs assig spill_loc +allocRegsAndSpill_spill reading keep spills alloc r@(VirtualRegFormat vr fmt) rs assig spill_loc = do platform <- getPlatform freeRegs <- getFreeRegsR - let regclass = classOfVirtualReg r - freeRegs_thisClass = frGetFreeRegs platform regclass freeRegs :: [RealReg] + let regclass = if isIntFormat fmt then RcInteger else RcFloatOrVector + freeRegs_thisClass = frGetFreeRegs platform regclass freeRegs :: [RealReg] -- Can we put the variable into a register it already was? - pref_reg <- findPrefRealReg r + pref_reg <- findPrefRealReg vr case freeRegs_thisClass of -- case (2): we have a free register @@ -891,10 +891,10 @@ allocRegsAndSpill_spill reading keep spills alloc (VirtualRegFormat r fmt) rs as = reg | otherwise = first_free - spills' <- loadTemp platform (VirtualRegFormat r fmt) spill_loc final_reg spills + spills' <- loadTemp platform r spill_loc final_reg spills setAssigR $ toRegMap - $ (addToUFM assig r $! newLocation spill_loc $ RealRegUsage final_reg fmt) + $ (addToUFM assig vr $! newLocation spill_loc $ mkRealRegUsage platform final_reg fmt) setFreeRegsR $ frAllocateReg platform final_reg freeRegs allocateRegsAndSpill reading keep spills' (final_reg : alloc) rs @@ -916,30 +916,30 @@ allocRegsAndSpill_spill reading keep spills alloc (VirtualRegFormat r fmt) rs as let candidates = nonDetUFMToList candidates' -- the vregs we could kick out that are already in a slot - let compat reg' r' + let compat reg' = targetClassOfRealReg platform reg' - == classOfVirtualReg r' + == regclass candidates_inBoth :: [(Unique, RealRegUsage, StackSlot)] candidates_inBoth = [ (temp, reg, mem) | (temp, InBoth reg mem) <- candidates - , compat (realReg reg) r ] + , compat (realReg reg) ] -- the vregs we could kick out that are only in a reg -- this would require writing the reg to a new slot before using it. let candidates_inReg = [ (temp, reg) | (temp, InReg reg) <- candidates - , compat (realReg reg) r ] + , compat (realReg reg) ] let result -- we have a temporary that is in both register and mem, -- just free up its register for use. - | (temp, myRegUse@(RealRegUsage my_reg fmt), slot) : _ <- candidates_inBoth - = do spills' <- loadTemp platform (VirtualRegFormat r fmt) spill_loc my_reg spills + | (temp, (RealRegUsage my_reg _old_fmt), slot) : _ <- candidates_inBoth + = do spills' <- loadTemp platform r spill_loc my_reg spills let assig1 = addToUFM_Directly assig temp (InMem slot) - let assig2 = addToUFM assig1 r $! newLocation spill_loc myRegUse + let assig2 = addToUFM assig1 vr $! newLocation spill_loc (mkRealRegUsage platform my_reg fmt) setAssigR $ toRegMap assig2 allocateRegsAndSpill reading keep spills' (my_reg:alloc) rs @@ -955,12 +955,12 @@ allocRegsAndSpill_spill reading keep spills alloc (VirtualRegFormat r fmt) rs as recordSpill (SpillAlloc temp_to_push_out) -- update the register assignment - let assig1 = addToUFM_Directly assig temp_to_push_out (InMem slot) - let assig2 = addToUFM assig1 r $! newLocation spill_loc (RealRegUsage my_reg fmt) + let assig1 = addToUFM_Directly assig temp_to_push_out (InMem slot) + let assig2 = addToUFM assig1 vr $! newLocation spill_loc (mkRealRegUsage platform my_reg fmt) setAssigR $ toRegMap assig2 -- if need be, load up a spilled temp into the reg we've just freed up. - spills' <- loadTemp platform (VirtualRegFormat r fmt) spill_loc my_reg spills + spills' <- loadTemp platform r spill_loc my_reg spills allocateRegsAndSpill reading keep (spill_store ++ spills') @@ -971,8 +971,9 @@ allocRegsAndSpill_spill reading keep spills alloc (VirtualRegFormat r fmt) rs as | otherwise = pprPanic ("RegAllocLinear.allocRegsAndSpill: no spill candidates\n") $ vcat - [ text "allocating vreg: " <> text (show r) + [ text "allocating vreg: " <> text (show vr) , text "assignment: " <> ppr assig + , text "format: " <> ppr fmt , text "freeRegs: " <> text (showRegs freeRegs) , text "initFreeRegs: " <> text (showRegs (frInitFreeRegs platform `asTypeOf` freeRegs)) ] ===================================== compiler/GHC/CmmToAsm/Reg/Target.hs ===================================== @@ -15,7 +15,7 @@ module GHC.CmmToAsm.Reg.Target ( targetMkVirtualReg, targetRegDotColor, targetClassOfReg, - mkRegFormat, mapRegFormatSet, + mkVirtualRegFormat, mkRegFormat, mapRegFormatSet, ) where @@ -142,6 +142,17 @@ targetClassOfReg platform reg RegVirtual vr -> classOfVirtualReg vr RegReal rr -> targetClassOfRealReg platform rr +mkVirtualRegFormat :: HasDebugCallStack => VirtualReg -> Format -> VirtualRegFormat +mkVirtualRegFormat reg fmt + = assertPpr (regCls == fmtCls) + (vcat [ text "mkVirtualRegFormat: incompatible register & format" + , text "reg:" <+> ppr reg <+> dcolon <+> ppr regCls + , text "fmt:" <+> ppr fmt <+> parens (ppr fmtCls) ]) + $ VirtualRegFormat reg fmt + where + regCls = classOfVirtualReg reg + fmtCls = formatRegClass fmt + mkRegFormat :: HasDebugCallStack => Platform -> Reg -> Format -> RegFormat mkRegFormat platform reg fmt = assertPpr (regCls == fmtCls) ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -35,6 +35,7 @@ import GHC.CmmToAsm.X86.Cond import GHC.CmmToAsm.X86.Regs import GHC.CmmToAsm.X86.Ppr import GHC.CmmToAsm.X86.RegInfo +import GHC.CmmToAsm.Reg.Target import GHC.Platform.Regs import GHC.CmmToAsm.CPrim @@ -89,6 +90,7 @@ import Data.Maybe import Data.Word import qualified Data.Map as M +import GHC.Platform.Reg.Class (RegClass(..)) is32BitPlatform :: NatM Bool is32BitPlatform = do @@ -518,24 +520,41 @@ getSomeReg expr = do return (reg, code) +mkMOV :: HasDebugCallStack => Platform -> Format -> Operand -> Operand -> Instr +mkMOV platform fmt op1 op2 = + assertPpr (all (== fmtCls) $ catMaybes [cls1, cls2]) + (vcat [ text "invalid mkMOV instruction" + , text "fmt:" <+> ppr fmt + , case op1 of { OpReg r1 -> ppr r1 <+> dcolon <+> ppr (fromJust cls1); _ -> empty } + , case op2 of { OpReg r2 -> ppr r2 <+> dcolon <+> ppr (fromJust cls2); _ -> empty } + ]) + $ MOV fmt op1 op2 + + where + fmtCls = if isIntFormat fmt then RcInteger else RcFloatOrVector + cls1 = case op1 of { OpReg r1 -> Just (targetClassOfReg platform r1); _ -> Nothing } + cls2 = case op2 of { OpReg r2 -> Just (targetClassOfReg platform r2); _ -> Nothing } + assignMem_I64Code :: CmmExpr -> CmmExpr -> NatM InstrBlock assignMem_I64Code addrTree valueTree = do + platform <- getPlatform Amode addr addr_code <- getAmode addrTree RegCode64 vcode rhi rlo <- iselExpr64 valueTree let -- Little-endian store - mov_lo = MOV II32 (OpReg rlo) (OpAddr addr) - mov_hi = MOV II32 (OpReg rhi) (OpAddr (fromJust (addrOffset addr 4))) + mov_lo = mkMOV platform II32 (OpReg rlo) (OpAddr addr) + mov_hi = mkMOV platform II32 (OpReg rhi) (OpAddr (fromJust (addrOffset addr 4))) return (vcode `appOL` addr_code `snocOL` mov_lo `snocOL` mov_hi) assignReg_I64Code :: CmmReg -> CmmExpr -> NatM InstrBlock assignReg_I64Code (CmmLocal dst) valueTree = do + platform <- getPlatform RegCode64 vcode r_src_hi r_src_lo <- iselExpr64 valueTree let Reg64 r_dst_hi r_dst_lo = localReg64 dst - mov_lo = MOV II32 (OpReg r_src_lo) (OpReg r_dst_lo) - mov_hi = MOV II32 (OpReg r_src_hi) (OpReg r_dst_hi) + mov_lo = mkMOV platform II32 (OpReg r_src_lo) (OpReg r_dst_lo) + mov_hi = mkMOV platform II32 (OpReg r_src_hi) (OpReg r_dst_hi) return ( vcode `snocOL` mov_lo `snocOL` mov_hi ) @@ -545,22 +564,24 @@ assignReg_I64Code _ _ iselExpr64 :: HasDebugCallStack => CmmExpr -> NatM (RegCode64 InstrBlock) iselExpr64 (CmmLit (CmmInt i _)) = do + platform <- getPlatform Reg64 rhi rlo <- getNewReg64 let r = fromIntegral (fromIntegral i :: Word32) q = fromIntegral (fromIntegral (i `shiftR` 32) :: Word32) code = toOL [ - MOV II32 (OpImm (ImmInteger r)) (OpReg rlo), - MOV II32 (OpImm (ImmInteger q)) (OpReg rhi) + mkMOV platform II32 (OpImm (ImmInteger r)) (OpReg rlo), + mkMOV platform II32 (OpImm (ImmInteger q)) (OpReg rhi) ] return (RegCode64 code rhi rlo) iselExpr64 (CmmLoad addrTree ty _) | isWord64 ty = do + platform <- getPlatform Amode addr addr_code <- getAmode addrTree Reg64 rhi rlo <- getNewReg64 let - mov_lo = MOV II32 (OpAddr addr) (OpReg rlo) - mov_hi = MOV II32 (OpAddr (fromJust (addrOffset addr 4))) (OpReg rhi) + mov_lo = mkMOV platform II32 (OpAddr addr) (OpReg rlo) + mov_hi = mkMOV platform II32 (OpAddr (fromJust (addrOffset addr 4))) (OpReg rhi) return ( RegCode64 (addr_code `snocOL` mov_lo `snocOL` mov_hi) rhi rlo ) @@ -570,41 +591,44 @@ iselExpr64 (CmmReg (CmmLocal local_reg)) = do return (RegCode64 nilOL hi lo) iselExpr64 (CmmMachOp (MO_Add _) [e1, CmmLit (CmmInt i _)]) = do + platform <- getPlatform RegCode64 code1 r1hi r1lo <- iselExpr64 e1 Reg64 rhi rlo <- getNewReg64 let r = fromIntegral (fromIntegral i :: Word32) q = fromIntegral (fromIntegral (i `shiftR` 32) :: Word32) code = code1 `appOL` - toOL [ MOV II32 (OpReg r1lo) (OpReg rlo), + toOL [ mkMOV platform II32 (OpReg r1lo) (OpReg rlo), ADD II32 (OpImm (ImmInteger r)) (OpReg rlo), - MOV II32 (OpReg r1hi) (OpReg rhi), + mkMOV platform II32 (OpReg r1hi) (OpReg rhi), ADC II32 (OpImm (ImmInteger q)) (OpReg rhi) ] return (RegCode64 code rhi rlo) iselExpr64 (CmmMachOp (MO_Add _) [e1,e2]) = do + platform <- getPlatform RegCode64 code1 r1hi r1lo <- iselExpr64 e1 RegCode64 code2 r2hi r2lo <- iselExpr64 e2 Reg64 rhi rlo <- getNewReg64 let code = code1 `appOL` code2 `appOL` - toOL [ MOV II32 (OpReg r1lo) (OpReg rlo), + toOL [ mkMOV platform II32 (OpReg r1lo) (OpReg rlo), ADD II32 (OpReg r2lo) (OpReg rlo), - MOV II32 (OpReg r1hi) (OpReg rhi), + mkMOV platform II32 (OpReg r1hi) (OpReg rhi), ADC II32 (OpReg r2hi) (OpReg rhi) ] return (RegCode64 code rhi rlo) iselExpr64 (CmmMachOp (MO_Sub _) [e1,e2]) = do + platform <- getPlatform RegCode64 code1 r1hi r1lo <- iselExpr64 e1 RegCode64 code2 r2hi r2lo <- iselExpr64 e2 Reg64 rhi rlo <- getNewReg64 let code = code1 `appOL` code2 `appOL` - toOL [ MOV II32 (OpReg r1lo) (OpReg rlo), + toOL [ mkMOV platform II32 (OpReg r1lo) (OpReg rlo), SUB II32 (OpReg r2lo) (OpReg rlo), - MOV II32 (OpReg r1hi) (OpReg rhi), + mkMOV platform II32 (OpReg r1hi) (OpReg rhi), SBB II32 (OpReg r2hi) (OpReg rhi) ] return (RegCode64 code rhi rlo) @@ -637,44 +661,48 @@ iselExpr64 (CmmMachOp (MO_UU_Conv W8 W64) [expr]) = do r_dst_lo iselExpr64 (CmmMachOp (MO_SS_Conv W32 W64) [expr]) = do + platform <- getPlatform code <- getAnyReg expr Reg64 r_dst_hi r_dst_lo <- getNewReg64 return $ RegCode64 (code r_dst_lo `snocOL` - MOV II32 (OpReg r_dst_lo) (OpReg eax) `snocOL` + mkMOV platform II32 (OpReg r_dst_lo) (OpReg eax) `snocOL` CLTD II32 `snocOL` - MOV II32 (OpReg eax) (OpReg r_dst_lo) `snocOL` - MOV II32 (OpReg edx) (OpReg r_dst_hi)) + mkMOV platform II32 (OpReg eax) (OpReg r_dst_lo) `snocOL` + mkMOV platform II32 (OpReg edx) (OpReg r_dst_hi)) r_dst_hi r_dst_lo iselExpr64 (CmmMachOp (MO_SS_Conv W16 W64) [expr]) = do + platform <- getPlatform (r, code) <- getByteReg expr Reg64 r_dst_hi r_dst_lo <- getNewReg64 return $ RegCode64 (code `appOL` toOL [ MOVSxL II16 (OpReg r) (OpReg eax), CLTD II32, - MOV II32 (OpReg eax) (OpReg r_dst_lo), - MOV II32 (OpReg edx) (OpReg r_dst_hi)]) + mkMOV platform II32 (OpReg eax) (OpReg r_dst_lo), + mkMOV platform II32 (OpReg edx) (OpReg r_dst_hi)]) r_dst_hi r_dst_lo iselExpr64 (CmmMachOp (MO_SS_Conv W8 W64) [expr]) = do + platform <- getPlatform (r, code) <- getByteReg expr Reg64 r_dst_hi r_dst_lo <- getNewReg64 return $ RegCode64 (code `appOL` toOL [ MOVSxL II8 (OpReg r) (OpReg eax), CLTD II32, - MOV II32 (OpReg eax) (OpReg r_dst_lo), - MOV II32 (OpReg edx) (OpReg r_dst_hi)]) + mkMOV platform II32 (OpReg eax) (OpReg r_dst_lo), + mkMOV platform II32 (OpReg edx) (OpReg r_dst_hi)]) r_dst_hi r_dst_lo iselExpr64 (CmmMachOp (MO_S_Neg _) [expr]) = do + platform <- getPlatform RegCode64 code rhi rlo <- iselExpr64 expr Reg64 rohi rolo <- getNewReg64 let ocode = code `appOL` - toOL [ MOV II32 (OpReg rlo) (OpReg rolo), + toOL [ mkMOV platform II32 (OpReg rlo) (OpReg rolo), XOR II32 (OpReg rohi) (OpReg rohi), NEGI II32 (OpReg rolo), SBB II32 (OpReg rhi) (OpReg rohi) ] @@ -690,6 +718,7 @@ iselExpr64 (CmmMachOp (MO_S_Neg _) [expr]) = do -- Note that @(r1hi * r2hi) << 64@ can be dropped because it overflows completely. iselExpr64 (CmmMachOp (MO_Mul _) [e1,e2]) = do + platform <- getPlatform RegCode64 code1 r1hi r1lo <- iselExpr64 e1 RegCode64 code2 r2hi r2lo <- iselExpr64 e2 Reg64 rhi rlo <- getNewReg64 @@ -697,26 +726,27 @@ iselExpr64 (CmmMachOp (MO_Mul _) [e1,e2]) = do let code = code1 `appOL` code2 `appOL` - toOL [ MOV II32 (OpReg r1lo) (OpReg eax), - MOV II32 (OpReg r2lo) (OpReg tmp), - MOV II32 (OpReg r1hi) (OpReg rhi), + toOL [ mkMOV platform II32 (OpReg r1lo) (OpReg eax), + mkMOV platform II32 (OpReg r2lo) (OpReg tmp), + mkMOV platform II32 (OpReg r1hi) (OpReg rhi), IMUL II32 (OpReg tmp) (OpReg rhi), - MOV II32 (OpReg r2hi) (OpReg rlo), + mkMOV platform II32 (OpReg r2hi) (OpReg rlo), IMUL II32 (OpReg eax) (OpReg rlo), ADD II32 (OpReg rlo) (OpReg rhi), MUL2 II32 (OpReg tmp), ADD II32 (OpReg edx) (OpReg rhi), - MOV II32 (OpReg eax) (OpReg rlo) + mkMOV platform II32 (OpReg eax) (OpReg rlo) ] return (RegCode64 code rhi rlo) iselExpr64 (CmmMachOp (MO_S_MulMayOflo W64) _) = do + platform <- getPlatform -- Performance sensitive users won't use 32 bit so let's keep it simple: -- We always return a (usually false) positive. Reg64 rhi rlo <- getNewReg64 let code = toOL [ - MOV II32 (OpImm (ImmInt 1)) (OpReg rhi), - MOV II32 (OpImm (ImmInt 1)) (OpReg rlo) + mkMOV platform II32 (OpImm (ImmInt 1)) (OpReg rhi), + mkMOV platform II32 (OpImm (ImmInt 1)) (OpReg rlo) ] return (RegCode64 code rhi rlo) @@ -730,6 +760,7 @@ iselExpr64 (CmmMachOp (MO_S_MulMayOflo W64) _) = do -- the contents of @rlo@ to @rhi@ and clear @rlo at . iselExpr64 (CmmMachOp (MO_Shl _) [e1,e2]) = do + platform <- getPlatform RegCode64 code1 r1hi r1lo <- iselExpr64 e1 code2 <- getAnyReg e2 Reg64 rhi rlo <- getNewReg64 @@ -738,15 +769,15 @@ iselExpr64 (CmmMachOp (MO_Shl _) [e1,e2]) = do let code = code1 `appOL` code2 ecx `appOL` - toOL [ MOV II32 (OpReg r1lo) (OpReg rlo), - MOV II32 (OpReg r1hi) (OpReg rhi), + toOL [ mkMOV platform II32 (OpReg r1lo) (OpReg rlo), + mkMOV platform II32 (OpReg r1hi) (OpReg rhi), SHLD II32 (OpReg ecx) (OpReg rlo) (OpReg rhi), SHL II32 (OpReg ecx) (OpReg rlo), TEST II32 (OpImm (ImmInt 32)) (OpReg ecx), JXX EQQ lbl2, JXX ALWAYS lbl1, NEWBLOCK lbl1, - MOV II32 (OpReg rlo) (OpReg rhi), + mkMOV platform II32 (OpReg rlo) (OpReg rhi), XOR II32 (OpReg rlo) (OpReg rlo), JXX ALWAYS lbl2, NEWBLOCK lbl2 @@ -760,6 +791,7 @@ iselExpr64 (CmmMachOp (MO_Shl _) [e1,e2]) = do -- To accomplish that we shift @rhi@ by 31. iselExpr64 (CmmMachOp (MO_S_Shr _) [e1,e2]) = do + platform <- getPlatform RegCode64 code1 r1hi r1lo <- iselExpr64 e1 (r2, code2) <- getSomeReg e2 Reg64 rhi rlo <- getNewReg64 @@ -768,16 +800,16 @@ iselExpr64 (CmmMachOp (MO_S_Shr _) [e1,e2]) = do let code = code1 `appOL` code2 `appOL` - toOL [ MOV II32 (OpReg r1lo) (OpReg rlo), - MOV II32 (OpReg r1hi) (OpReg rhi), - MOV II32 (OpReg r2) (OpReg ecx), + toOL [ mkMOV platform II32 (OpReg r1lo) (OpReg rlo), + mkMOV platform II32 (OpReg r1hi) (OpReg rhi), + mkMOV platform II32 (OpReg r2) (OpReg ecx), SHRD II32 (OpReg ecx) (OpReg rhi) (OpReg rlo), SAR II32 (OpReg ecx) (OpReg rhi), TEST II32 (OpImm (ImmInt 32)) (OpReg ecx), JXX EQQ lbl2, JXX ALWAYS lbl1, NEWBLOCK lbl1, - MOV II32 (OpReg rhi) (OpReg rlo), + mkMOV platform II32 (OpReg rhi) (OpReg rlo), SAR II32 (OpImm (ImmInt 31)) (OpReg rhi), JXX ALWAYS lbl2, NEWBLOCK lbl2 @@ -787,6 +819,7 @@ iselExpr64 (CmmMachOp (MO_S_Shr _) [e1,e2]) = do -- Similar to the above. iselExpr64 (CmmMachOp (MO_U_Shr _) [e1,e2]) = do + platform <- getPlatform RegCode64 code1 r1hi r1lo <- iselExpr64 e1 (r2, code2) <- getSomeReg e2 Reg64 rhi rlo <- getNewReg64 @@ -795,16 +828,16 @@ iselExpr64 (CmmMachOp (MO_U_Shr _) [e1,e2]) = do let code = code1 `appOL` code2 `appOL` - toOL [ MOV II32 (OpReg r1lo) (OpReg rlo), - MOV II32 (OpReg r1hi) (OpReg rhi), - MOV II32 (OpReg r2) (OpReg ecx), + toOL [ mkMOV platform II32 (OpReg r1lo) (OpReg rlo), + mkMOV platform II32 (OpReg r1hi) (OpReg rhi), + mkMOV platform II32 (OpReg r2) (OpReg ecx), SHRD II32 (OpReg ecx) (OpReg rhi) (OpReg rlo), SHR II32 (OpReg ecx) (OpReg rhi), TEST II32 (OpImm (ImmInt 32)) (OpReg ecx), JXX EQQ lbl2, JXX ALWAYS lbl1, NEWBLOCK lbl1, - MOV II32 (OpReg rhi) (OpReg rlo), + mkMOV platform II32 (OpReg rhi) (OpReg rlo), XOR II32 (OpReg rhi) (OpReg rhi), JXX ALWAYS lbl2, NEWBLOCK lbl2 @@ -816,12 +849,13 @@ iselExpr64 (CmmMachOp (MO_Or _) [e1,e2]) = iselExpr64ParallelBin OR e1 e2 iselExpr64 (CmmMachOp (MO_Xor _) [e1,e2]) = iselExpr64ParallelBin XOR e1 e2 iselExpr64 (CmmMachOp (MO_Not _) [e1]) = do + platform <- getPlatform RegCode64 code1 r1hi r1lo <- iselExpr64 e1 Reg64 rhi rlo <- getNewReg64 let code = code1 `appOL` - toOL [ MOV II32 (OpReg r1lo) (OpReg rlo), - MOV II32 (OpReg r1hi) (OpReg rhi), + toOL [ mkMOV platform II32 (OpReg r1lo) (OpReg rlo), + mkMOV platform II32 (OpReg r1hi) (OpReg rhi), NOT II32 (OpReg rlo), NOT II32 (OpReg rhi) ] @@ -837,14 +871,15 @@ iselExpr64 expr iselExpr64ParallelBin :: (Format -> Operand -> Operand -> Instr) -> CmmExpr -> CmmExpr -> NatM (RegCode64 (OrdList Instr)) iselExpr64ParallelBin op e1 e2 = do + platform <- getPlatform RegCode64 code1 r1hi r1lo <- iselExpr64 e1 RegCode64 code2 r2hi r2lo <- iselExpr64 e2 Reg64 rhi rlo <- getNewReg64 let code = code1 `appOL` code2 `appOL` - toOL [ MOV II32 (OpReg r1lo) (OpReg rlo), - MOV II32 (OpReg r1hi) (OpReg rhi), + toOL [ mkMOV platform II32 (OpReg r1lo) (OpReg rlo), + mkMOV platform II32 (OpReg r1hi) (OpReg rhi), op II32 (OpReg r2lo) (OpReg rlo), op II32 (OpReg r2hi) (OpReg rhi) ] @@ -993,7 +1028,8 @@ getRegister' _ is32Bit (CmmMachOp (MO_SS_Conv W16 W64) [CmmLoad addr _ _]) getRegister' _ is32Bit (CmmMachOp (MO_UU_Conv W32 W64) [CmmLoad addr _ _]) | not is32Bit = do - code <- intLoadCode (MOV II32) addr -- 32-bit loads zero-extend + platform <- getPlatform + code <- intLoadCode (mkMOV platform II32) addr -- 32-bit loads zero-extend return (Any II64 code) getRegister' _ is32Bit (CmmMachOp (MO_SS_Conv W32 W64) [CmmLoad addr _ _]) @@ -1060,16 +1096,16 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps MO_SS_Conv W16 W32 -> integerExtend W16 W32 MOVSxL x MO_SS_Conv W8 W16 -> integerExtend W8 W16 MOVSxL x - -- We don't care about the upper bits for MO_XX_Conv, so MOV is enough. However, on 32-bit we + -- We don't care about the upper bits for MO_XX_Conv, so mkMOV platform is enough. However, on 32-bit we -- have 8-bit registers only for a few registers (as opposed to x86-64 where every register -- has 8-bit version). So for 32-bit code, we'll just zero-extend. MO_XX_Conv W8 W32 | is32Bit -> integerExtend W8 W32 MOVZxL x - | otherwise -> integerExtend W8 W32 MOV x + | otherwise -> integerExtend W8 W32 (mkMOV platform) x MO_XX_Conv W8 W16 | is32Bit -> integerExtend W8 W16 MOVZxL x - | otherwise -> integerExtend W8 W16 MOV x - MO_XX_Conv W16 W32 -> integerExtend W16 W32 MOV x + | otherwise -> integerExtend W8 W16 (mkMOV platform) x + MO_XX_Conv W16 W32 -> integerExtend W16 W32 (mkMOV platform) x MO_UU_Conv W8 W64 | not is32Bit -> integerExtend W8 W64 MOVZxL x MO_UU_Conv W16 W64 | not is32Bit -> integerExtend W16 W64 MOVZxL x @@ -1082,10 +1118,10 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps -- away as an unnecessary reg-to-reg move, so we keep it in -- the form of a movzl and print it as a movl later. -- This doesn't apply to MO_XX_Conv since in this case we don't care about - -- the upper bits. So we can just use MOV. - MO_XX_Conv W8 W64 | not is32Bit -> integerExtend W8 W64 MOV x - MO_XX_Conv W16 W64 | not is32Bit -> integerExtend W16 W64 MOV x - MO_XX_Conv W32 W64 | not is32Bit -> integerExtend W32 W64 MOV x + -- the upper bits. So we can just use mkMOV platform. + MO_XX_Conv W8 W64 | not is32Bit -> integerExtend W8 W64 (mkMOV platform) x + MO_XX_Conv W16 W64 | not is32Bit -> integerExtend W16 W64 (mkMOV platform) x + MO_XX_Conv W32 W64 | not is32Bit -> integerExtend W32 W64 (mkMOV platform) x MO_FF_Conv W32 W64 -> coerceFP2FP W64 x MO_FF_Conv W64 W32 -> coerceFP2FP W32 x @@ -1309,7 +1345,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x]) = do -- unary MachOps (reg, exp) <- getSomeReg expr let fmt = VecFormat len FmtInt64 return $ Any fmt (\dst -> exp `snocOL` - (MOV II64 (OpReg reg) (OpReg dst)) `snocOL` + (mkMOV platform II64 (OpReg reg) (OpReg dst)) `snocOL` (PUNPCKLQDQ fmt (OpReg dst) dst) `snocOL` (PUNPCKLQDQ fmt (OpReg dst) dst) `snocOL` (PUNPCKLQDQ fmt (OpReg dst) dst) `snocOL` @@ -1704,7 +1740,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps imm = litToImm lit code dst = case lit of - CmmInt 0 _ -> exp `snocOL` (MOV FF32 (OpReg r) (OpReg dst)) + CmmInt 0 _ -> exp `snocOL` (mkMOV platform FF32 (OpReg r) (OpReg dst)) CmmInt _ _ -> exp `snocOL` (VPSHUFD format imm (OpReg r) dst) _ -> panic "Error in offset while unpacking" return (Any format code) @@ -1715,7 +1751,7 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps code dst = case lit of CmmInt 0 _ -> exp `snocOL` - (MOV FF64 (OpReg r) (OpReg dst)) + (mkMOV platform FF64 (OpReg r) (OpReg dst)) CmmInt 1 _ -> exp `snocOL` (MOVHLPS format (OpReg r) dst) _ -> panic "Error in offset while unpacking" @@ -1757,10 +1793,10 @@ getRegister' platform is32Bit (CmmMachOp mop [x, y]) = do -- dyadic MachOps let code dst = case lit of CmmInt 0 _ -> exp `snocOL` - (MOV II64 (OpReg r) (OpReg dst)) + (mkMOV platform II64 (OpReg r) (OpReg dst)) CmmInt 1 _ -> exp `snocOL` (MOVHLPS fmt (OpReg r) tmp) `snocOL` - (MOV II64 (OpReg tmp) (OpReg dst)) + (mkMOV platform II64 (OpReg tmp) (OpReg dst)) _ -> panic "Error in offset while unpacking" return (Any fmt code) vector_int_unpack_sse _ w c e @@ -1901,11 +1937,11 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps = case offset of CmmInt 0 _ -> valExp `appOL` vecExp `snocOL` - (MOV FF64 (OpReg valReg) (OpReg dst)) `snocOL` + (mkMOV platform FF64 (OpReg valReg) (OpReg dst)) `snocOL` (SHUFPD fmt (ImmInt 0b00) (OpReg vecReg) dst) CmmInt 1 _ -> valExp `appOL` vecExp `snocOL` - (MOV FF64 (OpReg vecReg) (OpReg dst)) `snocOL` + (mkMOV platform FF64 (OpReg vecReg) (OpReg dst)) `snocOL` (SHUFPD fmt (ImmInt 0b00) (OpReg valReg) dst) _ -> pprPanic "MO_VF_Insert DoubleX2: unsupported offset" (ppr offset) in return $ Any fmt code @@ -1942,12 +1978,12 @@ getRegister' platform _is32Bit (CmmMachOp mop [x, y, z]) = do -- ternary MachOps CmmInt 0 _ -> valExp `appOL` vecExp `snocOL` (MOVHLPS fmt (OpReg vecReg) tmp) `snocOL` - (MOV II64 (OpReg valReg) (OpReg dst)) `snocOL` + (mkMOV platform II64 (OpReg valReg) (OpReg dst)) `snocOL` (PUNPCKLQDQ fmt (OpReg tmp) dst) CmmInt 1 _ -> valExp `appOL` vecExp `snocOL` - (MOV fmt (OpReg vecReg) (OpReg dst)) `snocOL` - (MOV II64 (OpReg valReg) (OpReg tmp)) `snocOL` + (mkMOV platform fmt (OpReg vecReg) (OpReg dst)) `snocOL` + (mkMOV platform II64 (OpReg valReg) (OpReg tmp)) `snocOL` (PUNPCKLQDQ fmt (OpReg tmp) dst) _ -> pprPanic "MO_V_Insert Int64X2: unsupported offset" (ppr offset) in return $ Any fmt code @@ -1983,14 +2019,16 @@ getRegister' _ _ (CmmLoad mem pk _) getRegister' _ is32Bit (CmmLoad mem pk _) | is32Bit && not (isWord64 pk) = do + platform <- getPlatform + let + instr = case width of + W8 -> MOVZxL II8 + _other -> mkMOV platform format code <- intLoadCode instr mem return (Any format code) where width = typeWidth pk format = intFormat width - instr = case width of - W8 -> MOVZxL II8 - _other -> MOV format -- We always zero-extend 8-bit loads, if we -- can't think of anything better. This is because -- we can't guarantee access to an 8-bit variant of every register @@ -2001,7 +2039,8 @@ getRegister' _ is32Bit (CmmLoad mem pk _) getRegister' _ is32Bit (CmmLoad mem pk _) | not is32Bit = do - code <- intLoadCode (MOV format) mem + platform <- getPlatform + code <- intLoadCode (mkMOV platform format) mem return (Any format code) where format = intFormat $ typeWidth pk @@ -2042,7 +2081,7 @@ getRegister' platform is32Bit (CmmLit lit) | not is32Bit, isWord64 (cmmLitType platform lit), not (isBigLit lit) = let imm = litToImm lit - code dst = unitOL (MOV II32 (OpImm imm) (OpReg dst)) + code dst = unitOL (mkMOV platform II32 (OpImm imm) (OpReg dst)) in return (Any II64 code) where @@ -2071,7 +2110,7 @@ getRegister' platform _ (CmmLit lit) = do let format = cmmTypeFormat ctype imm = litToImm lit - code dst = unitOL (MOV format (OpImm imm) (OpReg dst)) + code dst = unitOL (mkMOV platform format (OpImm imm) (OpReg dst)) return (Any format code) getRegister' platform _ other @@ -2409,9 +2448,10 @@ memConstant align lit = do loadFloatAmode :: Width -> AddrMode -> InstrBlock -> NatM Register loadFloatAmode w addr addr_code = do + platform <- getPlatform let format = floatFormat w code dst = addr_code `snocOL` - MOV format (OpAddr addr) (OpReg dst) + mkMOV platform format (OpAddr addr) (OpReg dst) return (Any format code) @@ -2584,19 +2624,19 @@ condIntCode' platform cond x y cmpExact :: OrdList Instr cmpExact = toOL - [ MOV II32 (OpReg r1_hi) (OpReg tmp1) - , MOV II32 (OpReg r1_lo) (OpReg tmp2) + [ mkMOV platform II32 (OpReg r1_hi) (OpReg tmp1) + , mkMOV platform II32 (OpReg r1_lo) (OpReg tmp2) , XOR II32 (OpReg r2_hi) (OpReg tmp1) , XOR II32 (OpReg r2_lo) (OpReg tmp2) , OR II32 (OpReg tmp1) (OpReg tmp2) ] cmpGE = toOL - [ MOV II32 (OpReg r1_hi) (OpReg tmp1) + [ mkMOV platform II32 (OpReg r1_hi) (OpReg tmp1) , CMP II32 (OpReg r2_lo) (OpReg r1_lo) , SBB II32 (OpReg r2_hi) (OpReg tmp1) ] cmpLE = toOL - [ MOV II32 (OpReg r2_hi) (OpReg tmp1) + [ mkMOV platform II32 (OpReg r2_hi) (OpReg tmp1) , CMP II32 (OpReg r1_lo) (OpReg r2_lo) , SBB II32 (OpReg r1_hi) (OpReg tmp1) ] @@ -2736,10 +2776,10 @@ assignMem_IntCode pk addr src = do let code = code_src `appOL` code_addr `snocOL` - MOV pk op_src (OpAddr addr) + mkMOV platform pk op_src (OpAddr addr) -- NOTE: op_src is stable, so it will still be valid -- after code_addr. This may involve the introduction - -- of an extra MOV to a temporary register, but we hope + -- of an extra mkMOV platform to a temporary register, but we hope -- the register allocator will get rid of it. -- return code @@ -2754,7 +2794,8 @@ assignMem_IntCode pk addr src = do -- Assign; dst is a reg, rhs is mem assignReg_IntCode pk reg (CmmLoad src _ _) = do - load_code <- intLoadCode (MOV pk) src + platform <- getPlatform + load_code <- intLoadCode (mkMOV platform pk) src platform <- ncgPlatform <$> getConfig return (load_code (getRegisterReg platform reg)) @@ -2767,12 +2808,13 @@ assignReg_IntCode _ reg src = do -- Floating point assignment to memory assignMem_FltCode pk addr src = do + platform <- getPlatform (src_reg, src_code) <- getNonClobberedReg src Amode addr addr_code <- getAmode addr let code = src_code `appOL` addr_code `snocOL` - MOV pk (OpReg src_reg) (OpAddr addr) + mkMOV platform pk (OpReg src_reg) (OpAddr addr) return code @@ -3324,7 +3366,7 @@ genCCall32 addr _ dest_regs args = do in -- assume SSE2 - MOV format (OpReg reg) (OpAddr addr) + mkMOV platform format (OpReg reg) (OpAddr addr) ] ) @@ -3406,12 +3448,12 @@ genCCall32 addr _ dest_regs args = do -- NB: This code will need to be -- revisited once GHC does more work around -- SIGFPE f - MOV fmt (OpAddr tmp_amode) (OpReg r_dest), + mkMOV platform fmt (OpAddr tmp_amode) (OpReg r_dest), ADD II32 (OpImm (ImmInt b)) (OpReg esp), DELTA delta0] - | isWord64 ty = toOL [MOV II32 (OpReg eax) (OpReg r_dest), - MOV II32 (OpReg edx) (OpReg r_dest_hi)] - | otherwise = unitOL (MOV (intFormat w) + | isWord64 ty = toOL [mkMOV platform II32 (OpReg eax) (OpReg r_dest), + mkMOV platform II32 (OpReg edx) (OpReg r_dest_hi)] + | otherwise = unitOL (mkMOV platform (intFormat w) (OpReg eax) (OpReg r_dest)) where @@ -3519,7 +3561,7 @@ genCCall64 addr conv dest_regs args = do -- If we are calling a varargs function -- then we need to define ireg as well -- as freg - MOV II64 (OpReg freg) (OpReg ireg)) + mkMOV platform II64 (OpReg freg) (OpReg ireg)) | otherwise = do arg_code <- getAnyReg arg load_args_win rest (ireg : usedInt) usedFP regs @@ -3538,7 +3580,7 @@ genCCall64 addr conv dest_regs args = do let code' = code `appOL` arg_code `appOL` toOL [ SUB (intFormat (wordWidth platform)) (OpImm (ImmInt arg_size)) (OpReg rsp), DELTA (delta-arg_size), - MOV (floatFormat width) (OpReg arg_reg) (OpAddr (spRel platform 0))] + mkMOV platform (floatFormat width) (OpReg arg_reg) (OpAddr (spRel platform 0))] push_args rest code' | otherwise = do @@ -3630,7 +3672,7 @@ genCCall64 addr conv dest_regs args = do -- It's not safe to omit this assignment, even if the number -- of SSE2 regs in use is zero. If %al is larger than 8 -- on entry to a varargs function, seg faults ensue. - assign_eax n = unitOL (MOV II32 (OpImm (ImmInt n)) (OpReg eax)) + assign_eax n = unitOL (mkMOV platform II32 (OpImm (ImmInt n)) (OpReg eax)) let call = callinsns `appOL` toOL ( @@ -3647,13 +3689,13 @@ genCCall64 addr conv dest_regs args = do assign_code [] = nilOL assign_code [dest] = case typeWidth rep of - W32 | isFloatType rep -> unitOL (MOV (floatFormat W32) + W32 | isFloatType rep -> unitOL (mkMOV platform (floatFormat W32) (OpReg xmm0) (OpReg r_dest)) - W64 | isFloatType rep -> unitOL (MOV (floatFormat W64) + W64 | isFloatType rep -> unitOL (mkMOV platform (floatFormat W64) (OpReg xmm0) (OpReg r_dest)) - _ -> unitOL (MOV (cmmTypeFormat rep) (OpReg rax) (OpReg r_dest)) + _ -> unitOL (mkMOV platform (cmmTypeFormat rep) (OpReg rax) (OpReg r_dest)) where rep = localRegType dest r_dest = getRegisterReg platform (CmmLocal dest) @@ -3767,7 +3809,7 @@ genSwitch expr targets = do let op = OpAddr (AddrBaseIndex (EABaseReg tableReg) (EAIndex reg (platformWordSizeInBytes platform)) (ImmInt 0)) code = e_code `appOL` toOL [ LEA (archWordFormat is32bit) (OpAddr (AddrBaseIndex EABaseRip EAIndexNone (ImmCLbl lbl))) (OpReg tableReg) - , MOV (archWordFormat is32bit) op (OpReg targetReg) + , mkMOV platform (archWordFormat is32bit) op (OpReg targetReg) , JMP_TBL (OpReg targetReg) ids (Section ReadOnlyData lbl) lbl ] return code @@ -4002,6 +4044,7 @@ trivialCode' _ width instr _ a b genTrivialCode :: Format -> (Operand -> Operand -> Instr) -> CmmExpr -> CmmExpr -> NatM Register genTrivialCode rep instr a b = do + platform <- getPlatform (b_op, b_code) <- getNonClobberedOperand b a_code <- getAnyReg a tmp <- getNewRegNat rep @@ -4015,7 +4058,7 @@ genTrivialCode rep instr a b = do code dst | dst `regClashesWithOp` b_op = b_code `appOL` - unitOL (MOV rep b_op (OpReg tmp)) `appOL` + unitOL (mkMOV platform rep b_op (OpReg tmp)) `appOL` a_code dst `snocOL` instr (OpReg tmp) (OpReg dst) | otherwise = @@ -4169,6 +4212,7 @@ coerceFP2FP to x = do sse2NegCode :: Width -> CmmExpr -> NatM Register sse2NegCode w x = do + platform <- getPlatform let fmt = floatFormat w x_code <- getAnyReg x -- This is how gcc does it, so it can't be that bad: @@ -4188,7 +4232,7 @@ sse2NegCode w x = do tmp <- getNewRegNat fmt let code dst = x_code dst `appOL` amode_code `appOL` toOL [ - MOV fmt (OpAddr amode) (OpReg tmp), + mkMOV platform fmt (OpAddr amode) (OpReg tmp), XOR fmt (OpReg tmp) (OpReg dst) ] -- @@ -4285,31 +4329,34 @@ genAtomicRMW bid width amop dst addr n = do -> Reg -- Register containing argument -> AddrMode -- Address of location to mutate -> NatM (OrdList Instr,BlockId) -- TODO: Return Maybe BlockId - op_code dst_r arg amode = case amop of - -- In the common case where dst_r is a virtual register the - -- final move should go away, because it's the last use of arg - -- and the first use of dst_r. - AMO_Add -> return $ (toOL [ LOCK (XADD format (OpReg arg) (OpAddr amode)) - , MOV format (OpReg arg) (OpReg dst_r) - ], bid) - AMO_Sub -> return $ (toOL [ NEGI format (OpReg arg) - , LOCK (XADD format (OpReg arg) (OpAddr amode)) - , MOV format (OpReg arg) (OpReg dst_r) - ], bid) - -- In these cases we need a new block id, and have to return it so - -- that later instruction selection can reference it. - AMO_And -> cmpxchg_code (\ src dst -> unitOL $ AND format src dst) - AMO_Nand -> cmpxchg_code (\ src dst -> toOL [ AND format src dst - , NOT format dst - ]) - AMO_Or -> cmpxchg_code (\ src dst -> unitOL $ OR format src dst) - AMO_Xor -> cmpxchg_code (\ src dst -> unitOL $ XOR format src dst) + op_code dst_r arg amode = do + platform <- getPlatform + case amop of + -- In the common case where dst_r is a virtual register the + -- final move should go away, because it's the last use of arg + -- and the first use of dst_r. + AMO_Add -> return $ (toOL [ LOCK (XADD format (OpReg arg) (OpAddr amode)) + , mkMOV platform format (OpReg arg) (OpReg dst_r) + ], bid) + AMO_Sub -> return $ (toOL [ NEGI format (OpReg arg) + , LOCK (XADD format (OpReg arg) (OpAddr amode)) + , mkMOV platform format (OpReg arg) (OpReg dst_r) + ], bid) + -- In these cases we need a new block id, and have to return it so + -- that later instruction selection can reference it. + AMO_And -> cmpxchg_code (\ src dst -> unitOL $ AND format src dst) + AMO_Nand -> cmpxchg_code (\ src dst -> toOL [ AND format src dst + , NOT format dst + ]) + AMO_Or -> cmpxchg_code (\ src dst -> unitOL $ OR format src dst) + AMO_Xor -> cmpxchg_code (\ src dst -> unitOL $ XOR format src dst) where -- Simulate operation that lacks a dedicated instruction using -- cmpxchg. cmpxchg_code :: (Operand -> Operand -> OrdList Instr) -> NatM (OrdList Instr, BlockId) cmpxchg_code instrs = do + platform <- getPlatform lbl1 <- getBlockIdNat lbl2 <- getBlockIdNat tmp <- getNewRegNat format @@ -4322,12 +4369,12 @@ genAtomicRMW bid width amop dst addr n = do updateCfgNat (addWeightEdge lbl1 lbl1 0) return $ (toOL - [ MOV format (OpAddr amode) (OpReg eax) + [ mkMOV platform format (OpAddr amode) (OpReg eax) , JXX ALWAYS lbl1 , NEWBLOCK lbl1 -- Keep old value so we can return it: - , MOV format (OpReg eax) (OpReg dst_r) - , MOV format (OpReg eax) (OpReg tmp) + , mkMOV platform format (OpReg eax) (OpReg dst_r) + , mkMOV platform format (OpReg eax) (OpReg tmp) ] `appOL` instrs (OpReg arg) (OpReg tmp) `appOL` toOL [ LOCK (CMPXCHG format (OpReg tmp) (OpAddr amode)) @@ -4357,6 +4404,7 @@ genCtz64_32 -> CmmExpr -> NatM (InstrBlock, Maybe BlockId) genCtz64_32 bid dst src = do + platform <- getPlatform RegCode64 vcode rhi rlo <- iselExpr64 src let dst_r = getLocalRegReg dst lbl1 <- getBlockIdNat @@ -4380,9 +4428,9 @@ genCtz64_32 bid dst src = do -- dst = 64; -- } let instrs = vcode `appOL` toOL - ([ MOV II32 (OpReg rhi) (OpReg tmp_r) + ([ mkMOV platform II32 (OpReg rhi) (OpReg tmp_r) , OR II32 (OpReg rlo) (OpReg tmp_r) - , MOV II32 (OpImm (ImmInt 64)) (OpReg dst_r) + , mkMOV platform II32 (OpImm (ImmInt 64)) (OpReg dst_r) , JXX EQQ lbl2 , JXX ALWAYS lbl1 @@ -4402,6 +4450,7 @@ genCtz64_32 bid dst src = do -- Generic case (width <= word size) genCtzGeneric :: Width -> LocalReg -> CmmExpr -> NatM InstrBlock genCtzGeneric width dst src = do + platform <- getPlatform code_src <- getAnyReg src config <- getConfig let bw = widthInBits width @@ -4429,10 +4478,10 @@ genCtzGeneric width dst src = do let instrs = code_src src_r `appOL` toOL ([ MOVZxL II8 (OpReg src_r) (OpReg src_r) | width == W8 ] ++ [ BSF format (OpReg src_r) tmp_r - , MOV II32 (OpImm (ImmInt bw)) (OpReg dst_r) + , mkMOV platform II32 (OpImm (ImmInt bw)) (OpReg dst_r) , CMOV NE format (OpReg tmp_r) dst_r ]) -- NB: We don't need to zero-extend the result for the - -- W8/W16 cases because the 'MOV' insn already + -- W8/W16 cases because the 'mkMOV platform' insn already -- took care of implicitly clearing the upper bits return instrs @@ -4494,21 +4543,21 @@ genMemCpyInlineMaybe align dst src n = do go :: Reg -> Reg -> Reg -> Integer -> OrdList Instr go dst src tmp i | i >= sizeBytes = - unitOL (MOV format (OpAddr src_addr) (OpReg tmp)) `appOL` - unitOL (MOV format (OpReg tmp) (OpAddr dst_addr)) `appOL` + unitOL (mkMOV platform format (OpAddr src_addr) (OpReg tmp)) `appOL` + unitOL (mkMOV platform format (OpReg tmp) (OpAddr dst_addr)) `appOL` go dst src tmp (i - sizeBytes) -- Deal with remaining bytes. | i >= 4 = -- Will never happen on 32-bit - unitOL (MOV II32 (OpAddr src_addr) (OpReg tmp)) `appOL` - unitOL (MOV II32 (OpReg tmp) (OpAddr dst_addr)) `appOL` + unitOL (mkMOV platform II32 (OpAddr src_addr) (OpReg tmp)) `appOL` + unitOL (mkMOV platform II32 (OpReg tmp) (OpAddr dst_addr)) `appOL` go dst src tmp (i - 4) | i >= 2 = unitOL (MOVZxL II16 (OpAddr src_addr) (OpReg tmp)) `appOL` - unitOL (MOV II16 (OpReg tmp) (OpAddr dst_addr)) `appOL` + unitOL (mkMOV platform II16 (OpReg tmp) (OpAddr dst_addr)) `appOL` go dst src tmp (i - 2) | i >= 1 = unitOL (MOVZxL II8 (OpAddr src_addr) (OpReg tmp)) `appOL` - unitOL (MOV II8 (OpReg tmp) (OpAddr dst_addr)) `appOL` + unitOL (mkMOV platform II8 (OpReg tmp) (OpAddr dst_addr)) `appOL` go dst src tmp (i - 1) | otherwise = nilOL where @@ -4581,24 +4630,24 @@ genMemSetInlineMaybe align dst c n = do sizeBytes :: Integer sizeBytes = fromIntegral (formatInBytes format) - -- Depending on size returns the widest MOV instruction and its + -- Depending on size returns the widest mkMOV platform instruction and its -- width. gen4 :: AddrMode -> Integer -> (InstrBlock, Integer) gen4 addr size | size >= 4 = - (unitOL (MOV II32 (OpImm (ImmInteger c4)) (OpAddr addr)), 4) + (unitOL (mkMOV platform II32 (OpImm (ImmInteger c4)) (OpAddr addr)), 4) | size >= 2 = - (unitOL (MOV II16 (OpImm (ImmInteger c2)) (OpAddr addr)), 2) + (unitOL (mkMOV platform II16 (OpImm (ImmInteger c2)) (OpAddr addr)), 2) | size >= 1 = - (unitOL (MOV II8 (OpImm (ImmInteger c)) (OpAddr addr)), 1) + (unitOL (mkMOV platform II8 (OpImm (ImmInteger c)) (OpAddr addr)), 1) | otherwise = (nilOL, 0) - -- Generates a 64-bit wide MOV instruction from REG to MEM. + -- Generates a 64-bit wide mkMOV platform instruction from REG to MEM. gen8 :: AddrMode -> Reg -> InstrBlock gen8 addr reg8byte = - unitOL (MOV format (OpReg reg8byte) (OpAddr addr)) + unitOL (mkMOV platform format (OpReg reg8byte) (OpAddr addr)) - -- Unrolls memset when the widest MOV is <= 4 bytes. + -- Unrolls memset when the widest mkMOV platform is <= 4 bytes. go4 :: Reg -> Integer -> InstrBlock go4 dst left = if left <= 0 then nilOL @@ -4608,7 +4657,7 @@ genMemSetInlineMaybe align dst c n = do dst_addr = AddrBaseIndex (EABaseReg dst) EAIndexNone (ImmInteger (n - left)) (curMov, curWidth) = gen4 dst_addr possibleWidth - -- Unrolls memset when the widest MOV is 8 bytes (thus another Reg + -- Unrolls memset when the widest mkMOV platform is 8 bytes (thus another Reg -- argument). Falls back to go4 when all 8 byte moves are -- exhausted. go8 :: Reg -> Reg -> Integer -> InstrBlock @@ -4675,6 +4724,7 @@ genPrefetchData n src = do genByteSwap :: Width -> LocalReg -> CmmExpr -> NatM InstrBlock genByteSwap width dst src = do + platform <- getPlatform is32Bit <- is32BitPlatform let format = intFormat width case width of @@ -4682,8 +4732,8 @@ genByteSwap width dst src = do let Reg64 dst_hi dst_lo = localReg64 dst RegCode64 vcode rhi rlo <- iselExpr64 src return $ vcode `appOL` - toOL [ MOV II32 (OpReg rlo) (OpReg dst_hi), - MOV II32 (OpReg rhi) (OpReg dst_lo), + toOL [ mkMOV platform II32 (OpReg rlo) (OpReg dst_hi), + mkMOV platform II32 (OpReg rhi) (OpReg dst_lo), BSWAP II32 dst_hi, BSWAP II32 dst_lo ] W16 -> do @@ -4796,6 +4846,7 @@ genPext bid width dst src mask = do genClz :: BlockId -> Width -> CmmFormal -> CmmActual -> NatM InstrBlock genClz bid width dst src = do + platform <- getPlatform is32Bit <- is32BitPlatform config <- getConfig if is32Bit && width == W64 @@ -4829,11 +4880,11 @@ genClz bid width dst src = do return $ code_src src_r `appOL` toOL ([ MOVZxL II8 (OpReg src_r) (OpReg src_r) | width == W8 ] ++ [ BSR format (OpReg src_r) tmp_r - , MOV II32 (OpImm (ImmInt (2*bw-1))) (OpReg dst_r) + , mkMOV platform II32 (OpImm (ImmInt (2*bw-1))) (OpReg dst_r) , CMOV NE format (OpReg tmp_r) dst_r , XOR format (OpImm (ImmInt (bw-1))) (OpReg dst_r) ]) -- NB: We don't need to zero-extend the result for the - -- W8/W16 cases because the 'MOV' insn already + -- W8/W16 cases because the 'mkMOV platform' insn already -- took care of implicitly clearing the upper bits genWordToFloat :: BlockId -> Width -> CmmFormal -> CmmActual -> NatM InstrBlock @@ -4843,7 +4894,8 @@ genWordToFloat bid width dst src = genAtomicRead :: Width -> MemoryOrdering -> LocalReg -> CmmExpr -> NatM InstrBlock genAtomicRead width _mord dst addr = do - load_code <- intLoadCode (MOV (intFormat width)) addr + platform <- getPlatform + load_code <- intLoadCode (mkMOV platform (intFormat width)) addr return (load_code (getLocalRegReg dst)) genAtomicWrite :: Width -> MemoryOrdering -> CmmExpr -> CmmExpr -> NatM InstrBlock @@ -4880,9 +4932,9 @@ genCmpXchg bid width dst addr old new = do platform <- getPlatform let dst_r = getRegisterReg platform (CmmLocal dst) code = toOL - [ MOV format (OpReg oldval) (OpReg eax) + [ mkMOV platform format (OpReg oldval) (OpReg eax) , LOCK (CMPXCHG format (OpReg newval) (OpAddr amode)) - , MOV format (OpReg eax) (OpReg dst_r) + , mkMOV platform format (OpReg eax) (OpReg dst_r) ] return $ addr_code `appOL` newval_code newval `appOL` oldval_code oldval `appOL` code @@ -4893,6 +4945,7 @@ genCmpXchg bid width dst addr old new = do genXchg :: Width -> LocalReg -> CmmExpr -> CmmExpr -> NatM InstrBlock genXchg width dst addr value = do + platform <- getPlatform is32Bit <- is32BitPlatform when (is32Bit && width == W64) $ @@ -4904,7 +4957,7 @@ genXchg width dst addr value = do let dst_r = getLocalRegReg dst -- Copy the value into the target register, perform the exchange. let code = toOL - [ MOV format (OpReg newval) (OpReg dst_r) + [ mkMOV platform format (OpReg newval) (OpReg dst_r) -- On X86 xchg implies a lock prefix if we use a memory argument. -- so this is atomic. , XCHG format (OpAddr amode) dst_r @@ -4914,6 +4967,7 @@ genXchg width dst addr value = do genFloatAbs :: Width -> LocalReg -> CmmExpr -> NatM InstrBlock genFloatAbs width dst src = do + platform <- getPlatform let format = floatFormat width const = case width of @@ -4925,7 +4979,7 @@ genFloatAbs width dst src = do tmp <- getNewRegNat format let dst_r = getLocalRegReg dst pure $ src_code dst_r `appOL` amode_code `appOL` toOL - [ MOV format (OpAddr amode) (OpReg tmp) + [ mkMOV platform format (OpAddr amode) (OpReg tmp) , AND format (OpReg tmp) (OpReg dst_r) ] @@ -4990,6 +5044,7 @@ genSignedLargeMul -> CmmExpr -> NatM (OrdList Instr) genSignedLargeMul width res_c res_h res_l arg_x arg_y = do + platform <- getPlatform (y_reg, y_code) <- getRegOrMem arg_y x_code <- getAnyReg arg_x reg_tmp <- getNewRegNat II8 @@ -5000,8 +5055,8 @@ genSignedLargeMul width res_c res_h res_l arg_x arg_y = do code = y_code `appOL` x_code rax `appOL` toOL [ IMUL2 format y_reg - , MOV format (OpReg rdx) (OpReg reg_h) - , MOV format (OpReg rax) (OpReg reg_l) + , mkMOV platform format (OpReg rdx) (OpReg reg_h) + , mkMOV platform format (OpReg rax) (OpReg reg_l) , SETCC CARRY (OpReg reg_tmp) , MOVZxL II8 (OpReg reg_tmp) (OpReg reg_c) ] @@ -5015,6 +5070,7 @@ genUnsignedLargeMul -> CmmExpr -> NatM (OrdList Instr) genUnsignedLargeMul width res_h res_l arg_x arg_y = do + platform <- getPlatform (y_reg, y_code) <- getRegOrMem arg_y x_code <- getAnyReg arg_x let format = intFormat width @@ -5023,8 +5079,8 @@ genUnsignedLargeMul width res_h res_l arg_x arg_y = do code = y_code `appOL` x_code rax `appOL` toOL [MUL2 format y_reg, - MOV format (OpReg rdx) (OpReg reg_h), - MOV format (OpReg rax) (OpReg reg_l)] + mkMOV platform format (OpReg rdx) (OpReg reg_h), + mkMOV platform format (OpReg rax) (OpReg reg_l)] return code @@ -5038,6 +5094,7 @@ genQuotRem -> CmmExpr -> NatM InstrBlock genQuotRem width signed res_q res_r m_arg_x_high arg_x_low arg_y = do + platform <- getPlatform case width of W8 -> do -- See Note [DIV/IDIV for bytes] @@ -5067,5 +5124,5 @@ genQuotRem width signed res_q res_r m_arg_x_high arg_x_low arg_y = do x_low_code rax `appOL` x_high_code rdx `appOL` toOL [instr format y_reg, - MOV format (OpReg rax) (OpReg reg_q), - MOV format (OpReg rdx) (OpReg reg_r)] + mkMOV platform format (OpReg rax) (OpReg reg_q), + mkMOV platform format (OpReg rdx) (OpReg reg_r)] ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -46,7 +46,7 @@ import GHC.Data.FastString import GHC.CmmToAsm.X86.Cond import GHC.CmmToAsm.X86.Regs import GHC.CmmToAsm.Format -import GHC.CmmToAsm.Reg.Target (targetClassOfReg) +import GHC.CmmToAsm.Reg.Target (targetClassOfReg, mkRegFormat) import GHC.CmmToAsm.Types import GHC.CmmToAsm.Utils import GHC.CmmToAsm.Instr (RegUsage(..), noUsage) @@ -463,24 +463,24 @@ regUsageOfInstr platform instr POP fmt op -> mkRU fmt [] (def_W op) TEST fmt src dst -> mkRUR fmt (use_R src $! use_R dst []) CMP fmt src dst -> mkRUR fmt (use_R src $! use_R dst []) - SETCC _ op -> mkRU II64 [] (def_W op) - JXX _ _ -> mkRU II64 [] [] - JXX_GBL _ _ -> mkRU II64 [] [] - JMP op regs -> mkRUR II64 (use_R op regs) - JMP_TBL op _ _ _ -> mkRUR II64 (use_R op []) - CALL (Left _) params -> mkRU II64 params (callClobberedRegs platform) - CALL (Right reg) params -> mkRU II64 (reg:params) (callClobberedRegs platform) - CLTD _ -> mkRU II64 [eax] [edx] - NOP -> mkRU II64 [] [] + SETCC _ op -> mkRUFormat [] (def_W op) + JXX _ _ -> mkRUFormat [] [] + JXX_GBL _ _ -> mkRUFormat [] [] + JMP op regs -> mkRUFormat (use_R op regs) [] + JMP_TBL op _ _ _ -> mkRUFormat (use_R op []) [] + CALL (Left _) params -> mkRUFormat params (callClobberedRegs platform) + CALL (Right reg) params -> mkRUFormat (reg:params) (callClobberedRegs platform) + CLTD fmt -> mkRU fmt [eax] [edx] + NOP -> mkRUFormat [] [] X87Store fmt dst -> mkRUR fmt ( use_EA dst []) - CVTSS2SD src dst -> mkRU FF64 [src] [dst] - CVTSD2SS src dst -> mkRU FF32 [src] [dst] - CVTTSS2SIQ _ src dst -> mkRU FF32 (use_R src []) [dst] - CVTTSD2SIQ _ src dst -> mkRU FF64 (use_R src []) [dst] - CVTSI2SS _ src dst -> mkRU FF32 (use_R src []) [dst] - CVTSI2SD _ src dst -> mkRU FF64 (use_R src []) [dst] + CVTSS2SD src dst -> mkRUFormat [src] [dst] + CVTSD2SS src dst -> mkRUFormat [src] [dst] + CVTTSS2SIQ _ src dst -> mkRUFormat (use_R src []) [dst] + CVTTSD2SIQ _ src dst -> mkRUFormat (use_R src []) [dst] + CVTSI2SS _ src dst -> mkRUFormat (use_R src []) [dst] + CVTSI2SD _ src dst -> mkRUFormat (use_R src []) [dst] FDIV fmt src dst -> usageRM fmt src dst SQRT fmt src dst -> mkRU fmt (use_R src []) [dst] @@ -573,32 +573,32 @@ regUsageOfInstr platform instr -- are read. -- 2 operand form; first operand Read; second Written - usageRW :: Format -> Operand -> Operand -> RegUsage + usageRW :: HasDebugCallStack => Format -> Operand -> Operand -> RegUsage usageRW fmt op (OpReg reg) = mkRU fmt (use_R op []) [reg] usageRW fmt op (OpAddr ea) = mkRUR fmt (use_R op $! use_EA ea []) usageRW _ _ _ = panic "X86.RegInfo.usageRW: no match" -- 2 operand form; first operand Read; second Modified - usageRM :: Format -> Operand -> Operand -> RegUsage + usageRM :: HasDebugCallStack => Format -> Operand -> Operand -> RegUsage usageRM fmt op (OpReg reg) = mkRU fmt (use_R op [reg]) [reg] usageRM fmt op (OpAddr ea) = mkRUR fmt (use_R op $! use_EA ea []) usageRM _ _ _ = panic "X86.RegInfo.usageRM: no match" -- 2 operand form; first operand Modified; second Modified - usageMM :: Format -> Operand -> Operand -> RegUsage + usageMM :: HasDebugCallStack => Format -> Operand -> Operand -> RegUsage usageMM fmt (OpReg src) (OpReg dst) = mkRU fmt [src, dst] [src, dst] usageMM fmt (OpReg src) (OpAddr ea) = mkRU fmt (use_EA ea [src]) [src] usageMM fmt (OpAddr ea) (OpReg dst) = mkRU fmt (use_EA ea [dst]) [dst] usageMM _ _ _ = panic "X86.RegInfo.usageMM: no match" -- 3 operand form; first operand Read; second Modified; third Modified - usageRMM :: Format -> Operand -> Operand -> Operand -> RegUsage + usageRMM :: HasDebugCallStack => Format -> Operand -> Operand -> Operand -> RegUsage usageRMM fmt (OpReg src) (OpReg dst) (OpReg reg) = mkRU fmt [src, dst, reg] [dst, reg] usageRMM fmt (OpReg src) (OpAddr ea) (OpReg reg) = mkRU fmt (use_EA ea [src, reg]) [reg] usageRMM _ _ _ _ = panic "X86.RegInfo.usageRMM: no match" -- 3 operand form of FMA instructions. - usageFMA :: Format -> Operand -> Reg -> Reg -> RegUsage + usageFMA :: HasDebugCallStack => Format -> Operand -> Reg -> Reg -> RegUsage usageFMA fmt (OpReg src1) src2 dst = mkRU fmt [src1, src2, dst] [dst] usageFMA fmt (OpAddr ea1) src2 dst @@ -607,7 +607,7 @@ regUsageOfInstr platform instr = panic "X86.RegInfo.usageFMA: no match" -- 1 operand form; operand Modified - usageM :: Format -> Operand -> RegUsage + usageM :: HasDebugCallStack => Format -> Operand -> RegUsage usageM fmt (OpReg reg) = mkRU fmt [reg] [reg] usageM fmt (OpAddr ea) = mkRUR fmt (use_EA ea []) usageM _ _ = panic "X86.RegInfo.usageM: no match" @@ -631,13 +631,25 @@ regUsageOfInstr platform instr use_index EAIndexNone tl = tl use_index (EAIndex i _) tl = i : tl - mkRUR fmt src = src' `seq` RU (map (\ r -> RegFormat r fmt) src') [] + mkRUR :: HasDebugCallStack => Format -> [Reg] -> RegUsage + mkRUR fmt src = src' `seq` RU (map (\ r -> mkRegFormat platform r fmt) src') [] where src' = filter (interesting platform) src - mkRU fmt src dst = src' `seq` dst' `seq` RU (map (\ r -> RegFormat r fmt) src') (map (\ r -> RegFormat r fmt) dst') + mkRU :: HasDebugCallStack => Format -> [Reg] -> [Reg] -> RegUsage + mkRU fmt src dst = src' `seq` dst' `seq` RU (map (\ r -> mkRegFormat platform r fmt) src') (map (\ r -> mkRegFormat platform r fmt) dst') where src' = filter (interesting platform) src dst' = filter (interesting platform) dst + mkRUFormat :: HasDebugCallStack => [Reg] -> [Reg] -> RegUsage + mkRUFormat src dst = src' `seq` dst' `seq` RU (map mkFormat src') (map mkFormat dst') + where src' = filter (interesting platform) src + dst' = filter (interesting platform) dst + mkFormat reg = + mkRegFormat platform reg $ + case targetClassOfReg platform reg of + RcInteger -> archWordFormat (target32Bit platform) + RcFloatOrVector -> FF64 + -- | Is this register interesting for the register allocator? interesting :: Platform -> Reg -> Bool interesting _ (RegVirtual _) = True @@ -861,7 +873,8 @@ patchJumpInstr insn patchF -- ----------------------------------------------------------------------------- -- | Make a spill instruction. mkSpillInstr - :: NCGConfig + :: HasDebugCallStack + => NCGConfig -> RegFormat -- register to spill -> Int -- current stack delta -> Int -- spill slot to use @@ -877,12 +890,23 @@ mkSpillInstr config (RegFormat reg fmt) delta slot -> [MOVU fmt (OpReg reg) (OpAddr (spRel platform off))] -- NB: not using MOVA, because we have no guarantees about the stack -- being sufficiently aligned, including even numbered stack slots. - _ -> [MOV (scalarMoveFormat platform fmt) (OpReg reg) (OpAddr (spRel platform off))] + _ -> + let fmt' = scalarMoveFormat platform fmt + cls_f = if isIntFormat fmt' then RcInteger else RcFloatOrVector + cls1 = targetClassOfReg platform reg + in + assertPpr (all (== cls_f) [cls1]) + (vcat [ text "mkSpillInstr: incompatible formats" + , text "format:" <+> ppr fmt <+> parens (ppr cls_f) + , text "src:" <+> ppr reg <+> parens (ppr cls1) + , callStackDoc ]) + $ [MOV fmt' (OpReg reg) (OpAddr (spRel platform off))] where platform = ncgPlatform config -- | Make a spill reload instruction. mkLoadInstr - :: NCGConfig + :: HasDebugCallStack + => NCGConfig -> RegFormat -- register to load -> Int -- current stack delta -> Int -- spill slot to use @@ -898,7 +922,17 @@ mkLoadInstr config (RegFormat reg fmt) delta slot -> [MOVU fmt (OpAddr (spRel platform off)) (OpReg reg)] -- NB: not using MOVA, because we have no guarantees about the stack -- being sufficiently aligned, including even numbered stack slots. - _ -> [MOV (scalarMoveFormat platform fmt) (OpAddr (spRel platform off)) (OpReg reg)] + _ -> + let fmt' = scalarMoveFormat platform fmt + cls_f = if isIntFormat fmt' then RcInteger else RcFloatOrVector + cls2 = targetClassOfReg platform reg + in + assertPpr (all (== cls_f) [cls2]) + (vcat [ text "mkLoadInstr: incompatible formats" + , text "format:" <+> ppr fmt <+> parens (ppr cls_f) + , text "dst:" <+> ppr reg <+> parens (ppr cls2) + , callStackDoc ]) + $ [MOV fmt' (OpAddr (spRel platform off)) (OpReg reg)] where platform = ncgPlatform config spillSlotSize :: Platform -> Int @@ -980,7 +1014,7 @@ mkRegRegMoveInstr platform fmt src dst = , text "src:" <+> ppr src <+> parens (ppr cls1) , text "dst:" <+> ppr dst <+> parens (ppr cls2) , callStackDoc ]) - $ MOV (scalarMoveFormat platform fmt) (OpReg src) (OpReg dst) + $ MOV fmt' (OpReg src) (OpReg dst) scalarMoveFormat :: Platform -> Format -> Format scalarMoveFormat platform fmt ===================================== compiler/GHC/CmmToAsm/X86/Regs.hs ===================================== @@ -378,7 +378,7 @@ callClobberedRegs platform -- Only xmm0-5 are caller-saves registers on 64-bit windows. -- For details check the Win64 ABI: -- https://docs.microsoft.com/en-us/cpp/build/x64-software-conventions - ++ map xmm [0 .. 5] + ++ map xmm [0 .. 5] | otherwise -- all xmm regs are caller-saves -- caller-saves registers View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/85a0b5b00d73758142c936a0d4584f02b409f62e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/85a0b5b00d73758142c936a0d4584f02b409f62e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 18:18:06 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 20 Jun 2024 14:18:06 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 6 commits: Derive previously hand-written `Lift` instances (#14030) Message-ID: <6674725ec4b2f_30033433c639411458b@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 41b15f9a by Sebastian Graf at 2024-06-20T14:17:55-04:00 Derive previously hand-written `Lift` instances (#14030) This is possible now that #22229 is fixed. - - - - - 7eeae9e0 by Sebastian Graf at 2024-06-20T14:17:55-04:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. - - - - - ad279551 by Hécate Kleidukos at 2024-06-20T14:17:57-04:00 haddock: Remove unused pragmata, qualify usages of Data.List functions, add more sanity checking flags by default This commit enables some extensions and GHC flags in the cabal file in a way that allows us to reduce the amount of prologuing on top of each file. We also prefix the usage of some List functions that removes ambiguity when they are also exported from the Prelude, like foldl'. In general, this has the effect of pointing out more explicitly that a linked list is used. Metric Increase: haddock.Cabal haddock.base haddock.compiler - - - - - 512f6d19 by Arnaud Spiwack at 2024-06-20T14:17:58-04:00 Add test case for #23586 - - - - - 649809f5 by Arnaud Spiwack at 2024-06-20T14:17:58-04:00 When matching functions in rewrite rules: ignore multiplicity When matching a template variable to an expression, we check that it has the same type as the matched expression. But if the variable `f` has type `A -> B` while the expression `e` has type `A %1 -> B`, the match was previously rejected. A principled solution would have `f` substituted by `\(%Many x) -> e x` or some other appropriate coercion. But since linearity is not properly checked in Core, we can be cheeky and simply ignore multiplicity while matching. Much easier. This has forced a change in the linter which, when `-dlinear-core-lint` is off, must consider that `a -> b` and `a %1 -> b` are equal. This is achieved by adding an argument to configure the behaviour of `nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour which ignores multiplicities when comparing two `FunTy`. Fixes #24725. - - - - - d6e5be07 by Simon Peyton Jones at 2024-06-20T14:17:58-04:00 Faster type equality This MR speeds up type equality, triggered by perf regressions that showed up when fixing #24725 by parameterising type equality over whether to ignore multiplicity. The changes are: * Do not use `nonDetCmpType` for type /equality/. Instead use a specialised type-equality function, which we have always had! `nonDetCmpType` remains, but I did not invest effort in refactoring or optimising it. * Type equality is parameterised by - whether to expand synonyms - whether to respect multiplicities - whether it has a RnEnv2 environment In this MR I systematically specialise it for static values of these parameters. Much more direct and predictable than before. See Note [Specialising type equality] * We want to avoid comparing kinds if possible. I refactored how this happens, at least for `eqType`. See Note [Casts and coercions in type comparison] * To make Lint fast, we want to avoid allocating a thunk for <msg> in ensureEqTypes ty1 ty2 <msg> because the test almost always succeeds, and <msg> isn't needed. See Note [INLINE ensureEqTys] Metric Decrease: T13386 T5030 - - - - - 30 changed files: - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Multiplicity.hs - compiler/GHC/Core/TyCo/Compare.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Utils/TcType.hs - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - testsuite/tests/ghci/scripts/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - + testsuite/tests/simplCore/should_run/T23586.hs - + testsuite/tests/simplCore/should_run/T23586.stdout - testsuite/tests/simplCore/should_run/all.T - testsuite/tests/th/TH_Lift.hs - + testsuite/tests/th/TH_Lift.stderr - testsuite/tests/th/all.T - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/src/Haddock.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface.hs - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Options.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/haddock-library/fixtures/Fixtures.hs - utils/haddock/haddock-library/haddock-library.cabal The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/34ad82c7feb1ee8cb807fb335852edd08b008706...d6e5be07f5a6da39d4b749fd51c479fb4dbde176 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/34ad82c7feb1ee8cb807fb335852edd08b008706...d6e5be07f5a6da39d4b749fd51c479fb4dbde176 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 19:13:01 2024 From: gitlab at gitlab.haskell.org (Alan Zimmerman (@alanz)) Date: Thu, 20 Jun 2024 15:13:01 -0400 Subject: [Git][ghc/ghc][wip/kirchner/ttg-zurich] TTG HsCmdArrForm: use Fixity via extension point Message-ID: <66747f3d5ecfa_43ba4737b0c10469e@gitlab.mail> Alan Zimmerman pushed to branch wip/kirchner/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: 04578d90 by romes at 2024-06-20T20:11:49+01:00 TTG HsCmdArrForm: use Fixity via extension point Also migrate Fixity from GHC.Hs to Language.Haskell.Syntax since it no longer uses any GHC-specific data types. Fixed arrow desugaring bug. (This was dead code before.) Remove mkOpFormRn, it is also dead code, only used in the arrow desugaring now removed. Co-authored-by: Fabian Kirchner <kirchner at posteo.de> Co-authored-by: Alan Zimmerman <alan.zimm at gmail.com> - - - - - 20 changed files: - + compiler/GHC/Hs/Basic.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Instances.hs - compiler/GHC/HsToCore/Arrows.hs - compiler/GHC/HsToCore/Ticks.hs - compiler/GHC/Iface/Ext/Ast.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/PostProcess.hs - compiler/GHC/Rename/Expr.hs - compiler/GHC/Rename/HsType.hs - compiler/GHC/Tc/Gen/Arrow.hs - compiler/GHC/Tc/Zonk/Type.hs - compiler/GHC/Types/Fixity.hs - compiler/GHC/Types/Fixity/Env.hs - compiler/Language/Haskell/Syntax/Basic.hs - compiler/Language/Haskell/Syntax/Expr.hs - compiler/ghc.cabal.in - testsuite/tests/count-deps/CountDepsAst.stdout - testsuite/tests/count-deps/CountDepsParser.stdout - utils/check-exact/ExactPrint.hs Changes: ===================================== compiler/GHC/Hs/Basic.hs ===================================== @@ -0,0 +1,58 @@ +{-# OPTIONS_GHC -Wno-orphans #-} -- Outputable, Binary, Eq +{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE DeriveDataTypeable #-} + +-- | Fixity +module GHC.Hs.Basic + ( module Language.Haskell.Syntax.Basic + ) where + +import GHC.Prelude + +import GHC.Utils.Outputable +import GHC.Utils.Binary + +import Data.Data () + +import Language.Haskell.Syntax.Basic + +instance Outputable LexicalFixity where + ppr Prefix = text "Prefix" + ppr Infix = text "Infix" + +instance Outputable FixityDirection where + ppr InfixL = text "infixl" + ppr InfixR = text "infixr" + ppr InfixN = text "infix" + +instance Outputable Fixity where + ppr (Fixity prec dir) = hcat [ppr dir, space, int prec] + +instance Eq Fixity where -- Used to determine if two fixities conflict + (Fixity p1 dir1) == (Fixity p2 dir2) = p1==p2 && dir1 == dir2 + +instance Binary Fixity where + put_ bh (Fixity aa ab) = do + put_ bh aa + put_ bh ab + get bh = do + aa <- get bh + ab <- get bh + return (Fixity aa ab) + +------------------------ + +instance Binary FixityDirection where + put_ bh InfixL = + putByte bh 0 + put_ bh InfixR = + putByte bh 1 + put_ bh InfixN = + putByte bh 2 + get bh = do + h <- getByte bh + case h of + 0 -> return InfixL + 1 -> return InfixR + _ -> return InfixN ===================================== compiler/GHC/Hs/Expr.hs ===================================== @@ -32,6 +32,7 @@ import Language.Haskell.Syntax.Expr -- friends: import GHC.Prelude +import GHC.Hs.Basic() -- import instances import GHC.Hs.Decls() -- import instances import GHC.Hs.Pat import GHC.Hs.Lit @@ -1245,8 +1246,10 @@ type instance XCmdArrApp GhcRn = NoExtField type instance XCmdArrApp GhcTc = Type type instance XCmdArrForm GhcPs = AnnList -type instance XCmdArrForm GhcRn = NoExtField -type instance XCmdArrForm GhcTc = NoExtField +-- | fixity (filled in by the renamer), for forms that were converted from +-- OpApp's by the renamer +type instance XCmdArrForm GhcRn = Maybe Fixity +type instance XCmdArrForm GhcTc = Maybe Fixity type instance XCmdApp (GhcPass _) = NoExtField type instance XCmdLam (GhcPass _) = NoExtField @@ -1407,7 +1410,7 @@ ppr_cmd (HsCmdArrApp _ arrow arg HsHigherOrderApp True) ppr_cmd (HsCmdArrApp _ arrow arg HsHigherOrderApp False) = hsep [ppr_lexpr arg, arrowtt, ppr_lexpr arrow] -ppr_cmd (HsCmdArrForm _ (L _ op) ps_fix rn_fix args) +ppr_cmd (HsCmdArrForm rn_fix (L _ op) ps_fix args) | HsVar _ (L _ v) <- op = ppr_cmd_infix v | GhcTc <- ghcPass @p @@ -1422,7 +1425,10 @@ ppr_cmd (HsCmdArrForm _ (L _ op) ps_fix rn_fix args) ppr_cmd_infix :: OutputableBndr v => v -> SDoc ppr_cmd_infix v | [arg1, arg2] <- args - , isJust rn_fix || ps_fix == Infix + , case ghcPass @p of + GhcPs -> ps_fix == Infix + GhcRn -> isJust rn_fix || ps_fix == Infix + GhcTc -> isJust rn_fix || ps_fix == Infix = hang (pprCmdArg (unLoc arg1)) 4 (sep [ pprInfixOcc v, pprCmdArg (unLoc arg2)]) | otherwise ===================================== compiler/GHC/Hs/Instances.hs ===================================== @@ -570,6 +570,9 @@ deriving instance Eq (IE GhcTc) deriving instance Data HsThingRn deriving instance Data XXExprGhcRn + +-- --------------------------------------------------------------------- + deriving instance Data XXExprGhcTc deriving instance Data XXPatGhcTc ===================================== compiler/GHC/HsToCore/Arrows.hs ===================================== @@ -634,7 +634,7 @@ dsCmd ids local_vars stack_ty res_ty (HsCmdDo _ (L _ stmts)) env_ids = do -- ----------------------------------- -- D; xs |-a (|e c1 ... cn|) :: stk --> t ---> e [t_xs] c1 ... cn -dsCmd _ local_vars _stack_ty _res_ty (HsCmdArrForm _ op _ _ args) env_ids = do +dsCmd _ local_vars _stack_ty _res_ty (HsCmdArrForm _ op _ args) env_ids = do let env_ty = mkBigCoreVarTupTy env_ids core_op <- dsLExpr op (core_args, fv_sets) <- mapAndUnzipM (dsTrimCmdArg local_vars env_ids) args ===================================== compiler/GHC/HsToCore/Ticks.hs ===================================== @@ -883,11 +883,10 @@ addTickHsCmd (HsCmdArrApp arr_ty e1 e2 ty1 lr) = (addTickLHsExpr e2) (return ty1) (return lr) -addTickHsCmd (HsCmdArrForm x e f fix cmdtop) = - liftM4 (HsCmdArrForm x) +addTickHsCmd (HsCmdArrForm x e f cmdtop) = + liftM3 (HsCmdArrForm x) (addTickLHsExpr e) (return f) - (return fix) (mapM (traverse (addTickHsCmdTop)) cmdtop) addTickHsCmd (XCmd (HsWrap w cmd)) = ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -1510,7 +1510,7 @@ instance HiePass p => ToHie (LocatedA (HsCmd (GhcPass p))) where [ toHie a , toHie b ] - HsCmdArrForm _ a _ _ cmdtops -> + HsCmdArrForm _ a _ cmdtops -> [ toHie a , toHie cmdtops ] ===================================== compiler/GHC/Parser.y ===================================== @@ -3081,7 +3081,7 @@ aexp2 :: { ECP } | '(|' aexp cmdargs '|)' {% runPV (unECP $2) >>= \ $2 -> fmap ecpFromCmd $ amsA' (sLL $1 $> $ HsCmdArrForm (AnnList (glRM $1) (Just $ mu AnnOpenB $1) (Just $ mu AnnCloseB $4) [] []) $2 Prefix - Nothing (reverse $3)) } + (reverse $3)) } projection :: { Located (NonEmpty (LocatedAn NoEpAnns (DotFieldOcc GhcPs))) } projection ===================================== compiler/GHC/Parser/PostProcess.hs ===================================== @@ -1765,7 +1765,7 @@ instance DisambECP (HsCmd GhcPs) where mkHsOpAppPV l c1 op c2 = do let cmdArg c = L (l2l $ getLoc c) $ HsCmdTop noExtField c !cs <- getCommentsFor l - return $ L (EpAnn (spanAsAnchor l) noAnn cs) $ HsCmdArrForm (AnnList Nothing Nothing Nothing [] []) (reLoc op) Infix Nothing [cmdArg c1, cmdArg c2] + return $ L (EpAnn (spanAsAnchor l) noAnn cs) $ HsCmdArrForm (AnnList Nothing Nothing Nothing [] []) (reLoc op) Infix [cmdArg c1, cmdArg c2] mkHsCasePV l c (L lm m) anns = do !cs <- getCommentsFor l ===================================== compiler/GHC/Rename/Expr.hs ===================================== @@ -905,21 +905,10 @@ rnCmd (HsCmdArrApp _ arrow arg ho rtl) -- Local bindings, inside the enclosing proc, are not in scope -- inside 'arrow'. In the higher-order case (-<<), they are. --- infix form -rnCmd (HsCmdArrForm _ op _ (Just _) [arg1, arg2]) - = do { (op',fv_op) <- escapeArrowScope (rnLExpr op) - ; let L _ (HsVar _ (L _ op_name)) = op' - ; (arg1',fv_arg1) <- rnCmdTop arg1 - ; (arg2',fv_arg2) <- rnCmdTop arg2 - -- Deal with fixity - ; fixity <- lookupFixityRn op_name - ; final_e <- mkOpFormRn arg1' op' fixity arg2' - ; return (final_e, fv_arg1 `plusFV` fv_op `plusFV` fv_arg2) } - -rnCmd (HsCmdArrForm _ op f fixity cmds) +rnCmd (HsCmdArrForm _ op f cmds) = do { (op',fvOp) <- escapeArrowScope (rnLExpr op) ; (cmds',fvCmds) <- rnCmdArgs cmds - ; return ( HsCmdArrForm noExtField op' f fixity cmds' + ; return ( HsCmdArrForm Nothing op' f cmds' , fvOp `plusFV` fvCmds) } rnCmd (HsCmdApp x fun arg) ===================================== compiler/GHC/Rename/HsType.hs ===================================== @@ -25,7 +25,7 @@ module GHC.Rename.HsType ( -- Precence related stuff NegationHandling(..), - mkOpAppRn, mkNegAppRn, mkOpFormRn, mkConOpPatRn, + mkOpAppRn, mkNegAppRn, mkConOpPatRn, checkPrecMatch, checkSectionPrec, -- Binding related stuff @@ -1455,35 +1455,6 @@ not_op_app :: HsExpr id -> Bool not_op_app (OpApp {}) = False not_op_app _ = True ---------------------------- -mkOpFormRn :: LHsCmdTop GhcRn -- Left operand; already rearranged - -> LHsExpr GhcRn -> Fixity -- Operator and fixity - -> LHsCmdTop GhcRn -- Right operand (not an infix) - -> RnM (HsCmd GhcRn) - --- (e1a `op1` e1b) `op2` e2 -mkOpFormRn e1@(L loc - (HsCmdTop _ - (L _ (HsCmdArrForm x op1 f (Just fix1) - [e1a,e1b])))) - op2 fix2 e2 - | nofix_error - = do precParseErr (get_op op1,fix1) (get_op op2,fix2) - return (HsCmdArrForm x op2 f (Just fix2) [e1, e2]) - - | associate_right - = do new_c <- mkOpFormRn e1a op2 fix2 e2 - return (HsCmdArrForm noExtField op1 f (Just fix1) - [e1b, L loc (HsCmdTop [] (L (l2l loc) new_c))]) - -- TODO: locs are wrong - where - (nofix_error, associate_right) = compareFixity fix1 fix2 - --- Default case -mkOpFormRn arg1 op fix arg2 -- Default case, no rearrangement - = return (HsCmdArrForm noExtField op Infix (Just fix) [arg1, arg2]) - - -------------------------------------- mkConOpPatRn :: LocatedN Name -> Fixity -> LPat GhcRn -> LPat GhcRn -> RnM (Pat GhcRn) ===================================== compiler/GHC/Tc/Gen/Arrow.hs ===================================== @@ -290,7 +290,7 @@ tc_cmd env (HsCmdDo _ (L l stmts) ) (cmd_stk, res_ty) -- ---------------------------------------------- -- D; G |-a (| e c1 ... cn |) : stk --> t -tc_cmd env cmd@(HsCmdArrForm x expr f fixity cmd_args) (cmd_stk, res_ty) +tc_cmd env cmd@(HsCmdArrForm fixity expr f cmd_args) (cmd_stk, res_ty) = addErrCtxt (cmdCtxt cmd) do { (cmd_args', cmd_tys) <- mapAndUnzipM tc_cmd_arg cmd_args -- We use alphaTyVar for 'w' @@ -298,7 +298,7 @@ tc_cmd env cmd@(HsCmdArrForm x expr f fixity cmd_args) (cmd_stk, res_ty) mkVisFunTysMany cmd_tys $ mkCmdArrTy env (mkPairTy alphaTy cmd_stk) res_ty ; expr' <- tcCheckPolyExpr expr e_ty - ; return (HsCmdArrForm x expr' f fixity cmd_args') } + ; return (HsCmdArrForm fixity expr' f cmd_args') } where tc_cmd_arg :: LHsCmdTop GhcRn -> TcM (LHsCmdTop GhcTc, TcType) ===================================== compiler/GHC/Tc/Zonk/Type.hs ===================================== @@ -1152,10 +1152,10 @@ zonkCmd (HsCmdArrApp ty e1 e2 ho rl) new_ty <- zonkTcTypeToTypeX ty return (HsCmdArrApp new_ty new_e1 new_e2 ho rl) -zonkCmd (HsCmdArrForm x op f fixity args) +zonkCmd (HsCmdArrForm x op fixity args) = do new_op <- zonkLExpr op new_args <- mapM zonkCmdTop args - return (HsCmdArrForm x new_op f fixity new_args) + return (HsCmdArrForm x new_op fixity new_args) zonkCmd (HsCmdApp x c e) = do new_c <- zonkLCmd c ===================================== compiler/GHC/Types/Fixity.hs ===================================== @@ -1,4 +1,5 @@ {-# LANGUAGE DeriveDataTypeable #-} +{-# OPTIONS_GHC -Wno-dodgy-exports #-} -- For re-export of GHC.Hs.Basic instances -- | Fixity module GHC.Types.Fixity @@ -11,61 +12,17 @@ module GHC.Types.Fixity , negateFixity , funTyFixity , compareFixity + , module GHC.Hs.Basic ) where import GHC.Prelude -import GHC.Utils.Outputable -import GHC.Utils.Binary - -import Data.Data hiding (Fixity, Prefix, Infix) - -data Fixity = Fixity Int FixityDirection - deriving Data - -instance Outputable Fixity where - ppr (Fixity prec dir) = hcat [ppr dir, space, int prec] - -instance Eq Fixity where -- Used to determine if two fixities conflict - (Fixity p1 dir1) == (Fixity p2 dir2) = p1==p2 && dir1 == dir2 - -instance Binary Fixity where - put_ bh (Fixity aa ab) = do - put_ bh aa - put_ bh ab - get bh = do - aa <- get bh - ab <- get bh - return (Fixity aa ab) +import Language.Haskell.Syntax.Basic (LexicalFixity(..), FixityDirection(..), Fixity(..) ) +import GHC.Hs.Basic () -- For instances only ------------------------ -data FixityDirection - = InfixL - | InfixR - | InfixN - deriving (Eq, Data) -instance Outputable FixityDirection where - ppr InfixL = text "infixl" - ppr InfixR = text "infixr" - ppr InfixN = text "infix" - -instance Binary FixityDirection where - put_ bh InfixL = - putByte bh 0 - put_ bh InfixR = - putByte bh 1 - put_ bh InfixN = - putByte bh 2 - get bh = do - h <- getByte bh - case h of - 0 -> return InfixL - 1 -> return InfixR - _ -> return InfixN - ------------------------- maxPrecedence, minPrecedence :: Int maxPrecedence = 9 minPrecedence = 0 @@ -103,12 +60,3 @@ compareFixity (Fixity prec1 dir1) (Fixity prec2 dir2) right = (False, True) left = (False, False) error_please = (True, False) - --- |Captures the fixity of declarations as they are parsed. This is not --- necessarily the same as the fixity declaration, as the normal fixity may be --- overridden using parens or backticks. -data LexicalFixity = Prefix | Infix deriving (Data,Eq) - -instance Outputable LexicalFixity where - ppr Prefix = text "Prefix" - ppr Infix = text "Infix" ===================================== compiler/GHC/Types/Fixity/Env.hs ===================================== @@ -43,4 +43,3 @@ mkIfaceFixCache pairs emptyIfaceFixCache :: OccName -> Maybe Fixity emptyIfaceFixCache _ = Nothing - ===================================== compiler/Language/Haskell/Syntax/Basic.hs ===================================== @@ -96,3 +96,25 @@ data SrcUnpackedness = SrcUnpack -- ^ {-# UNPACK #-} specified | SrcNoUnpack -- ^ {-# NOUNPACK #-} specified | NoSrcUnpack -- ^ no unpack pragma deriving (Eq, Data) + +{- +************************************************************************ +* * +Fixity +* * +************************************************************************ +-} + +-- | Captures the fixity of declarations as they are parsed. This is not +-- necessarily the same as the fixity declaration, as the normal fixity may be +-- overridden using parens or backticks. +data LexicalFixity = Prefix | Infix deriving (Eq, Data) + +data FixityDirection + = InfixL + | InfixR + | InfixN + deriving (Eq, Data) + +data Fixity = Fixity Int FixityDirection + deriving Data ===================================== compiler/Language/Haskell/Syntax/Expr.hs ===================================== @@ -30,7 +30,6 @@ import Language.Haskell.Syntax.Type import Language.Haskell.Syntax.Binds -- others: -import GHC.Types.Fixity (LexicalFixity(Infix), Fixity) import GHC.Types.SourceText (StringLiteral, SourceText) import GHC.Unit.Module (ModuleName) @@ -832,8 +831,6 @@ data HsCmd id -- applied to the type of the local environment tuple LexicalFixity -- Whether the operator appeared prefix or infix when -- parsed. - (Maybe Fixity) -- fixity (filled in by the renamer), for forms that - -- were converted from OpApp's by the renamer [LHsCmdTop id] -- argument commands | HsCmdApp (XCmdApp id) ===================================== compiler/ghc.cabal.in ===================================== @@ -523,6 +523,7 @@ Library GHC.Driver.Ppr GHC.Driver.Session GHC.Hs + GHC.Hs.Basic GHC.Hs.Binds GHC.Hs.Decls GHC.Hs.Doc ===================================== testsuite/tests/count-deps/CountDepsAst.stdout ===================================== @@ -91,6 +91,7 @@ GHC.Driver.Phases GHC.Driver.Pipeline.Monad GHC.Driver.Plugins.External GHC.Hs +GHC.Hs.Basic GHC.Hs.Binds GHC.Hs.Decls GHC.Hs.Doc ===================================== testsuite/tests/count-deps/CountDepsParser.stdout ===================================== @@ -94,6 +94,7 @@ GHC.Driver.Phases GHC.Driver.Pipeline.Monad GHC.Driver.Plugins.External GHC.Hs +GHC.Hs.Basic GHC.Hs.Binds GHC.Hs.Decls GHC.Hs.Doc ===================================== utils/check-exact/ExactPrint.hs ===================================== @@ -3470,7 +3470,7 @@ instance ExactPrint (HsCmd GhcPs) where arr' <- markAnnotated arr return (HsCmdArrApp an0 arr' arg' o isRightToLeft) - exact (HsCmdArrForm an e fixity mf cs) = do + exact (HsCmdArrForm an e fixity cs) = do an0 <- markLensMAA' an lal_open (e',cs') <- case (fixity, cs) of (Infix, (arg1:argrest)) -> do @@ -3484,7 +3484,7 @@ instance ExactPrint (HsCmd GhcPs) where return (e', cs') (Infix, []) -> error "Not possible" an1 <- markLensMAA' an0 lal_close - return (HsCmdArrForm an1 e' fixity mf cs') + return (HsCmdArrForm an1 e' fixity cs') exact (HsCmdApp an e1 e2) = do e1' <- markAnnotated e1 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/04578d903c7769038e43f501adb7dae1b49ae489 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/04578d903c7769038e43f501adb7dae1b49ae489 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 21:18:56 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 20 Jun 2024 17:18:56 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 4 commits: haddock: Remove unused pragmata, qualify usages of Data.List functions, add... Message-ID: <66749cc0e75fe_43ba4180be601375c7@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: b007b87d by Hécate Kleidukos at 2024-06-20T17:18:27-04:00 haddock: Remove unused pragmata, qualify usages of Data.List functions, add more sanity checking flags by default This commit enables some extensions and GHC flags in the cabal file in a way that allows us to reduce the amount of prologuing on top of each file. We also prefix the usage of some List functions that removes ambiguity when they are also exported from the Prelude, like foldl'. In general, this has the effect of pointing out more explicitly that a linked list is used. Metric Increase: haddock.Cabal haddock.base haddock.compiler - - - - - 3cc2ccd0 by Arnaud Spiwack at 2024-06-20T17:18:27-04:00 Add test case for #23586 - - - - - fcb838e2 by Arnaud Spiwack at 2024-06-20T17:18:27-04:00 When matching functions in rewrite rules: ignore multiplicity When matching a template variable to an expression, we check that it has the same type as the matched expression. But if the variable `f` has type `A -> B` while the expression `e` has type `A %1 -> B`, the match was previously rejected. A principled solution would have `f` substituted by `\(%Many x) -> e x` or some other appropriate coercion. But since linearity is not properly checked in Core, we can be cheeky and simply ignore multiplicity while matching. Much easier. This has forced a change in the linter which, when `-dlinear-core-lint` is off, must consider that `a -> b` and `a %1 -> b` are equal. This is achieved by adding an argument to configure the behaviour of `nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour which ignores multiplicities when comparing two `FunTy`. Fixes #24725. - - - - - 7392a012 by Simon Peyton Jones at 2024-06-20T17:18:27-04:00 Faster type equality This MR speeds up type equality, triggered by perf regressions that showed up when fixing #24725 by parameterising type equality over whether to ignore multiplicity. The changes are: * Do not use `nonDetCmpType` for type /equality/. Instead use a specialised type-equality function, which we have always had! `nonDetCmpType` remains, but I did not invest effort in refactoring or optimising it. * Type equality is parameterised by - whether to expand synonyms - whether to respect multiplicities - whether it has a RnEnv2 environment In this MR I systematically specialise it for static values of these parameters. Much more direct and predictable than before. See Note [Specialising type equality] * We want to avoid comparing kinds if possible. I refactored how this happens, at least for `eqType`. See Note [Casts and coercions in type comparison] * To make Lint fast, we want to avoid allocating a thunk for <msg> in ensureEqTypes ty1 ty2 <msg> because the test almost always succeeds, and <msg> isn't needed. See Note [INLINE ensureEqTys] Metric Decrease: T13386 T5030 - - - - - 25 changed files: - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Multiplicity.hs - compiler/GHC/Core/TyCo/Compare.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Utils/TcType.hs - + testsuite/tests/simplCore/should_run/T23586.hs - + testsuite/tests/simplCore/should_run/T23586.stdout - testsuite/tests/simplCore/should_run/all.T - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/src/Haddock.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface.hs - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Options.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/haddock-library/fixtures/Fixtures.hs - utils/haddock/haddock-library/haddock-library.cabal - utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs - utils/haddock/haddock-library/src/Documentation/Haddock/Parser/Monad.hs - utils/haddock/haddock.cabal Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -53,7 +53,7 @@ import GHC.Core.Predicate( isCoVarType ) import GHC.Core.Multiplicity import GHC.Core.UsageEnv import GHC.Core.TyCo.Rep -- checks validity of types/coercions -import GHC.Core.TyCo.Compare ( eqType, eqForAllVis ) +import GHC.Core.TyCo.Compare ( eqType, eqTypes, eqTypeIgnoringMultiplicity, eqForAllVis ) import GHC.Core.TyCo.Subst import GHC.Core.TyCo.FVs import GHC.Core.TyCo.Ppr @@ -2807,7 +2807,7 @@ lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches extra_checks | isNewTyCon tc - = do { CoAxBranch { cab_tvs = tvs + = do { CoAxBranch { cab_tvs = ax_tvs , cab_eta_tvs = eta_tvs , cab_cvs = cvs , cab_roles = roles @@ -2815,14 +2815,10 @@ lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches <- case branch_list of [branch] -> return branch _ -> failWithL (text "multi-branch axiom with newtype") - ; let ax_lhs = mkInfForAllTys tvs $ - mkTyConApp tc lhs_tys - nt_tvs = takeList tvs (tyConTyVars tc) - -- axiom may be eta-reduced: Note [Newtype eta] in GHC.Core.TyCon - nt_lhs = mkInfForAllTys nt_tvs $ - mkTyConApp tc (mkTyVarTys nt_tvs) - -- See Note [Newtype eta] in GHC.Core.TyCon - ; lintL (ax_lhs `eqType` nt_lhs) + + -- The LHS of the axiom is (N lhs_tys) + -- We expect it to be (N ax_tvs) + ; lintL (mkTyVarTys ax_tvs `eqTypes` lhs_tys) (text "Newtype axiom LHS does not match newtype definition") ; lintL (null cvs) (text "Newtype axiom binds coercion variables") @@ -2831,7 +2827,7 @@ lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches (text "Newtype axiom has eta-tvs") ; lintL (ax_role == Representational) (text "Newtype axiom role not representational") - ; lintL (roles `equalLength` tvs) + ; lintL (roles `equalLength` ax_tvs) (text "Newtype axiom roles list is the wrong length." $$ text "roles:" <+> sep (map ppr roles)) ; lintL (roles == takeList roles (tyConRoles tc)) @@ -3098,84 +3094,93 @@ we behave as follows (#15057, #T15664): Note [Linting linearity] ~~~~~~~~~~~~~~~~~~~~~~~~ -Core understands linear types: linearity is checked with the flag -`-dlinear-core-lint`. Why not make `-dcore-lint` check linearity? Because -optimisation passes are not (yet) guaranteed to maintain linearity. They should -do so semantically (GHC is careful not to duplicate computation) but it is much -harder to ensure that the statically-checkable constraints of Linear Core are -maintained. The current Linear Core is described in the wiki at: +Lint ignores linearity unless `-dlinear-core-lint` is set. For why, see below. + +But first, "ignore linearity" specifically means two things. When ignoring linearity: +* In `ensureEqTypes`, use `eqTypeIgnoringMultiplicity` +* In `ensureSubMult`, do nothing + +But why make `-dcore-lint` ignore linearity? Because optimisation passes are +not (yet) guaranteed to maintain linearity. They should do so semantically (GHC +is careful not to duplicate computation) but it is much harder to ensure that +the statically-checkable constraints of Linear Core are maintained. The current +Linear Core is described in the wiki at: https://gitlab.haskell.org/ghc/ghc/-/wikis/linear-types/implementation. -Why don't the optimisation passes maintain the static types of Linear Core? -Because doing so would cripple some important optimisations. Here is an -example: +Here are some examples of how the optimiser can break linearity checking. Other +examples are documented in the linear-type implementation wiki page +[https://gitlab.haskell.org/ghc/ghc/-/wikis/linear-types/implementation#core-to-core-passes] - data T = MkT {-# UNPACK #-} !Int +* EXAMPLE 1: the binder swap transformation + Consider -The wrapper for MkT is + data T = MkT {-# UNPACK #-} !Int - $wMkT :: Int %1 -> T - $wMkT n = case %1 n of - I# n' -> MkT n' + The wrapper for MkT is -This introduces, in particular, a `case %1` (this is not actual Haskell or Core -syntax), where the `%1` means that the `case` expression consumes its scrutinee -linearly. + $wMkT :: Int %1 -> T + $wMkT n = case %1 n of + I# n' -> MkT n' -Now, `case %1` interacts with the binder swap optimisation in a non-trivial -way. Take a slightly modified version of the code for $wMkT: + This introduces, in particular, a `case %1` (this is not actual Haskell or + Core syntax), where the `%1` means that the `case` expression consumes its + scrutinee linearly. - case %1 x of z { - I# n' -> (x, n') - } + Now, `case %1` interacts with the binder swap optimisation in a non-trivial + way. Take a slightly modified version of the code for $wMkT: -Binder-swap wants to change this to + case %1 x of z { + I# n' -> (x, n') + } - case %1 x of z { - I# n' -> let x = z in (x, n') - } + Binder-swap changes this to -Now, this is not something that a linear type checker usually considers -well-typed. It is not something that `-dlinear-core-lint` considers to be -well-typed either. But it's only because `-dlinear-core-lint` is not good -enough. However, making `-dlinear-core-lint` recognise this expression as valid -is not obvious. There are many such interactions between a linear type system -and GHC optimisations documented in the linear-type implementation wiki page -[https://gitlab.haskell.org/ghc/ghc/-/wikis/linear-types/implementation#core-to-core-passes]. + case %1 x of z { + I# n' -> let x = z in (x, n') + } -PRINCIPLE: The type system bends to the optimisation, not the other way around. + This is rejected by `-dlinear-core-lint` because 1/ n' must be used linearly + 2/ `-dlinear-core-lint` recognises a use of `z` as a use of `n'`. So it sees + two uses of n' where there should be a single one. + +* EXAMPLE 2: letrec + Some optimisations can create a letrec which uses a variable + linearly, e.g. + + letrec f True = f False + f False = x + in f True + + uses 'x' linearly, but this is not seen by the linter, which considers, + conservatively, that a letrec always has multiplicity Many (in particular + that every captured free variable must have multiplicity Many). This issue + is discussed in ticket #18694. -In the original linear-types implementation, we had tried to make every -optimisation pass produce code that passes `-dlinear-core-lint`. It had proved -very difficult. And we kept finding corner case after corner case. Plus, we -used to restrict transformations when `-dlinear-core-lint` couldn't typecheck -the result. There are still occurrences of such restrictions in the code. But -our current stance is that such restrictions can be removed. +* EXAMPLE 3: rewrite rules + Ignoring linearity means in particular that `a -> b` and `a %1 -> b` must be + treated the same by rewrite rules (see also Note [Rewrite rules ignore + multiplicities in FunTy] in GHC.Core.Unify). Consider -For instance, some optimisations can create a letrec which uses a variable -linearly, e.g. + m :: Bool -> A + m' :: (Bool -> Bool) -> A + {- RULES "ex" forall f. m (f True) = m' f -} - letrec f True = f False - f False = x - in f True + f :: Bool %1 -> A + x = m (f True) -uses 'x' linearly, but this is not seen by the linter. This issue is discussed -in ticket #18694. + The rule "ex" must match . So the linter must accept `m' f`. -Plus in many cases, in order to make a transformation compatible with linear -linting, we ended up restricting to avoid producing patterns that were not -recognised as linear by the linter. This violates the above principle. +Historical note: In the original linear-types implementation, we had tried to +make every optimisation pass produce code that passes `-dlinear-core-lint`. It +had proved very difficult. We kept finding corner case after corner +case. Furthermore, to attempt to achieve that goal we ended up restricting +transformations when `-dlinear-core-lint` couldn't typecheck the result. In the future, we may be able to lint the linearity of the output of -Core-to-Core passes (#19165). But right now, we can't. Therefore, in virtue of -the principle above, after the desguarer, the optimiser should take no special -pains to preserve linearity (in the type system sense). +Core-to-Core passes (#19165). But this shouldn't be done at the expense of +producing efficient code. Therefore we lay the following principle. -In general the optimiser tries hard not to lose sharing, so it probably doesn't -actually make linear things non-linear. We postulate that any program -transformation which breaks linearity would negatively impact performance, and -therefore wouldn't be suitable for an optimiser. An alternative to linting -linearity after each pass is to prove this statement. +PRINCIPLE: The type system bends to the optimisation, not the other way around. There is a useful discussion at https://gitlab.haskell.org/ghc/ghc/-/issues/22123 @@ -3483,7 +3488,25 @@ ensureEqTys :: LintedType -> LintedType -> SDoc -> LintM () -- check ty2 is subtype of ty1 (ie, has same structure but usage -- annotations need only be consistent, not equal) -- Assumes ty1,ty2 are have already had the substitution applied -ensureEqTys ty1 ty2 msg = lintL (ty1 `eqType` ty2) msg +{-# INLINE ensureEqTys #-} -- See Note [INLINE ensureEqTys] +ensureEqTys ty1 ty2 msg + = do { flags <- getLintFlags + ; lintL (eq_type flags ty1 ty2) msg } + +eq_type :: LintFlags -> Type -> Type -> Bool +-- When `-dlinear-core-lint` is off, then consider `a -> b` and `a %1 -> b` to +-- be equal. See Note [Linting linearity]. +eq_type flags ty1 ty2 | lf_check_linearity flags = eqType ty1 ty2 + | otherwise = eqTypeIgnoringMultiplicity ty1 ty2 + +{- Note [INLINE ensureEqTys] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +To make Lint fast, we want to avoid allocating a thunk for in + ensureEqTypes ty1 ty2 +because the test almost always succeeds, and isn't needed. +So we INLINE `ensureEqTys`. This actually make a difference of +1-2% when compiling programs with -dcore-lint. +-} ensureSubUsage :: Usage -> Mult -> SDoc -> LintM () ensureSubUsage Bottom _ _ = return () ===================================== compiler/GHC/Core/Multiplicity.hs ===================================== @@ -30,7 +30,9 @@ module GHC.Core.Multiplicity , IsSubmult(..) , submult , mapScaledType - , pprArrowWithMultiplicity ) where + , pprArrowWithMultiplicity + , MultiplicityFlag(..) + ) where import GHC.Prelude @@ -395,3 +397,8 @@ pprArrowWithMultiplicity af pp_mult | otherwise = ppr (funTyFlagTyCon af) +-- | In Core, without `-dlinear-core-lint`, some function must ignore +-- multiplicities. See Note [Linting linearity] in GHC.Core.Lint. +data MultiplicityFlag + = RespectMultiplicities + | IgnoreMultiplicities ===================================== compiler/GHC/Core/TyCo/Compare.hs ===================================== @@ -7,15 +7,17 @@ -- | Type equality and comparison module GHC.Core.TyCo.Compare ( - -- * Type comparison - eqType, eqTypeX, eqTypes, nonDetCmpType, nonDetCmpTypes, nonDetCmpTypeX, - nonDetCmpTypesX, nonDetCmpTc, + -- * Type equality + eqType, eqTypeIgnoringMultiplicity, eqTypeX, eqTypes, eqVarBndrs, pickyEqType, tcEqType, tcEqKind, tcEqTypeNoKindCheck, tcEqTyConApps, mayLookIdentical, + -- * Type comparison + nonDetCmpType, + -- * Visiblity comparision eqForAllVis, cmpForAllVis @@ -29,10 +31,12 @@ import GHC.Core.Type( typeKind, coreView, tcSplitAppTyNoView_maybe, splitAppTyNo import GHC.Core.TyCo.Rep import GHC.Core.TyCo.FVs import GHC.Core.TyCon +import GHC.Core.Multiplicity( MultiplicityFlag(..) ) import GHC.Types.Var import GHC.Types.Unique import GHC.Types.Var.Env +import GHC.Types.Var.Set import GHC.Utils.Outputable import GHC.Utils.Misc @@ -52,7 +56,11 @@ so it currently sits "on top of" GHC.Core.Type. {- ********************************************************************* * * - Type equality + Type equality + + We don't use (==) from class Eq, partly so that we know where + type equality is called, and partly because there are multiple + variants. * * ********************************************************************* -} @@ -72,6 +80,93 @@ that needs to be updated. * See Historical Note [Typechecker equality vs definitional equality] below +Note [Casts and coercions in type comparision] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +As (EQTYPE) in Note [Non-trivial definitional equality] says, our +general plan, implemented by `fullEq`, is: + (1) ignore both casts and coercions when comparing types, + (2) instead, compare the /kinds/ of the two types, + as well as the types themselves + +If possible we want to avoid step (2), comparing the kinds; doing so involves +calling `typeKind` and doing another comparision. + +When can we avoid doing so? Answer: we can certainly avoid doing so if the +types we are comparing have no casts or coercions. But we can do better. +Consider + eqType (TyConApp T [s1, ..., sn]) (TyConApp T [t1, .., tn]) +We are going to call (eqType s1 t1), (eqType s2 t2) etc. + +The kinds of `s1` and `t1` must be equal, because these TyConApps are well-kinded, +and both TyConApps are headed by the same T. So the first recursive call to `eqType` +certainly doesn't need to check kinds. If that call returns False, we stop. Otherwise, +we know that `s1` and `t1` are themselves equal (not just their kinds). This +makes the kinds of `s2` and `t2` to be equal, because those kinds come from the +kind of T instantiated with `s1` and `t1` -- which are the same. Thus we do not +need to check the kinds of `s2` and `t2`. By induction, we don't need to check +the kinds of *any* of the types in a TyConApp, and we also do not need to check +the kinds of the TyConApps themselves. + +Conclusion: + +* casts and coercions under a TyConApp don't matter -- even including type synonyms + +* In step (2), use `hasCasts` to tell if there are any casts to worry about. It + does not look very deep, because TyConApps and FunTys are so common, and it + doesn't allocate. The only recursive cases are AppTy and ForAllTy. + +Alternative implementation. Instead of `hasCasts`, we could make the +generic_eq_type function return + data EqResult = NotEq | EqWithNoCasts | EqWithCasts +Practically free; but stylistically I prefer useing `hasCasts`: + * `generic_eq_type` can just uses familiar booleans + * There is a lot more branching with the three-value variant. + * It separates concerns. No need to think about cast-tracking when doing the + equality comparison. + * Indeed sometimes we omit the kind check unconditionally, so tracking it is just wasted + work. +I did try both; there was no perceptible perf difference so I chose `hasCasts` version. + +Note [Equality on AppTys] +~~~~~~~~~~~~~~~~~~~~~~~~~ +In our cast-ignoring equality, we want to say that the following two +are equal: + + (Maybe |> co) (Int |> co') ~? Maybe Int + +But the left is an AppTy while the right is a TyConApp. The solution is +to use splitAppTyNoView_maybe to break up the TyConApp into its pieces and +then continue. Easy to do, but also easy to forget to do. + +Note [Comparing nullary type synonyms] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider the task of testing equality between two 'Type's of the form + + TyConApp tc [] + +where @tc@ is a type synonym. A naive way to perform this comparison these +would first expand the synonym and then compare the resulting expansions. + +However, this is obviously wasteful and the RHS of @tc@ may be large; it is +much better to rather compare the TyCons directly. Consequently, before +expanding type synonyms in type comparisons we first look for a nullary +TyConApp and simply compare the TyCons if we find one. Of course, if we find +that the TyCons are *not* equal then we still need to perform the expansion as +their RHSs may still be equal. + +We perform this optimisation in a number of places: + + * GHC.Core.Types.eqType + * GHC.Core.Types.nonDetCmpType + * GHC.Core.Unify.unify_ty + * GHC.Tc.Solver.Equality.can_eq_nc' + * TcUnify.uType + +This optimisation is especially helpful for the ubiquitous GHC.Types.Type, +since GHC prefers to use the type synonym over @TYPE 'LiftedRep@ applications +whenever possible. See Note [Using synonyms to compress types] in +GHC.Core.Type for details. + Note [Type comparisons using object pointer comparisons] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Quite often we substitute the type from a definition site into @@ -81,6 +176,21 @@ The type of every `x` will often be represented by a single object in the heap. We can take advantage of this by shortcutting the equality check if two types are represented by the same pointer under the hood. In some cases this reduces compiler allocations by ~2%. + +See Note [Pointer comparison operations] in GHC.Builtin.primops.txt.pp + +Note [Respecting multiplicity when comparing types] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Generally speaking, we respect multiplicities (i.e. the linear part of the type +system) when comparing types. Doing so is of course crucial during typechecking. + +But for reasons described in Note [Linting linearity] in GHC.Core.Lint, it is hard +to ensure that Core is always type-correct when it comes to linearity. So +* `eqTypeIgnoringMultiplicity` provides a way to compare types that /ignores/ multiplicities +* We use this multiplicity-blind comparison very occasionally, notably + - in Core Lint: see Note [Linting linearity] in GHC.Core.Lint + - in rule matching: see Note [Rewrite rules ignore multiplicities in FunTy] + in GHC.Core.Unify -} @@ -88,21 +198,12 @@ tcEqKind :: HasDebugCallStack => Kind -> Kind -> Bool tcEqKind = tcEqType tcEqType :: HasDebugCallStack => Type -> Type -> Bool --- ^ tcEqType implements typechecker equality --- It behaves just like eqType, but is implemented --- differently (for now) -tcEqType ty1 ty2 - = tcEqTypeNoSyns ki1 ki2 - && tcEqTypeNoSyns ty1 ty2 - where - ki1 = typeKind ty1 - ki2 = typeKind ty2 +tcEqType = eqType -- | Just like 'tcEqType', but will return True for types of different kinds -- as long as their non-coercion structure is identical. tcEqTypeNoKindCheck :: Type -> Type -> Bool -tcEqTypeNoKindCheck ty1 ty2 - = tcEqTypeNoSyns ty1 ty2 +tcEqTypeNoKindCheck = eqTypeNoKindCheck -- | Check whether two TyConApps are the same; if the number of arguments -- are different, just checks the common prefix of arguments. @@ -114,175 +215,220 @@ tcEqTyConApps tc1 args1 tc2 args2 -- any difference in the kinds of later arguments would show up -- as differences in earlier (dependent) arguments -{- -Note [Specialising tc_eq_type] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -The type equality predicates in Type are hit pretty hard during typechecking. -Consequently we take pains to ensure that these paths are compiled to -efficient, minimally-allocating code. - -To this end we place an INLINE on tc_eq_type, ensuring that it is inlined into -its publicly-visible interfaces (e.g. tcEqType). In addition to eliminating -some dynamic branches, this allows the simplifier to eliminate the closure -allocations that would otherwise be necessary to capture the two boolean "mode" -flags. This reduces allocations by a good fraction of a percent when compiling -Cabal. -See #19226. --} - -mayLookIdentical :: Type -> Type -> Bool --- | Returns True if the /visible/ part of the types --- might look equal, even if they are really unequal (in the invisible bits) --- --- This function is very similar to tc_eq_type but it is much more --- heuristic. Notably, it is always safe to return True, even with types --- that might (in truth) be unequal -- this affects error messages only --- (Originally there were one function with an extra flag, but the result --- was hard to understand.) -mayLookIdentical orig_ty1 orig_ty2 - = go orig_env orig_ty1 orig_ty2 - where - orig_env = mkRnEnv2 $ mkInScopeSet $ tyCoVarsOfTypes [orig_ty1, orig_ty2] - - go :: RnEnv2 -> Type -> Type -> Bool - -- See Note [Comparing nullary type synonyms] - go _ (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = True - - go env t1 t2 | Just t1' <- coreView t1 = go env t1' t2 - go env t1 t2 | Just t2' <- coreView t2 = go env t1 t2' - - go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 - go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 - go env (CastTy t1 _) t2 = go env t1 t2 - go env t1 (CastTy t2 _) = go env t1 t2 - go _ (CoercionTy {}) (CoercionTy {}) = True - - go env (ForAllTy (Bndr tv1 vis1) ty1) - (ForAllTy (Bndr tv2 vis2) ty2) - = vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] - && go (rnBndr2 env tv1 tv2) ty1 ty2 - -- Visible stuff only: ignore kinds of binders - - -- If we have (forall (r::RunTimeRep). ty1 ~ blah) then respond - -- with True. Reason: the type pretty-printer defaults RuntimeRep - -- foralls (see Ghc.Iface.Type.hideNonStandardTypes). That can make, - -- say (forall r. TYPE r -> Type) into (Type -> Type), so it looks the - -- same as a very different type (#24553). By responding True, we - -- tell GHC (see calls of mayLookIdentical) to display without defaulting. - -- See Note [Showing invisible bits of types in error messages] - -- in GHC.Tc.Errors.Ppr - go _ (ForAllTy b _) _ | isDefaultableBndr b = True - go _ _ (ForAllTy b _) | isDefaultableBndr b = True +-- | Type equality on lists of types, looking through type synonyms +eqTypes :: [Type] -> [Type] -> Bool +eqTypes [] [] = True +eqTypes (t1:ts1) (t2:ts2) = eqType t1 t2 && eqTypes ts1 ts2 +eqTypes _ _ = False - go env (FunTy _ w1 arg1 res1) (FunTy _ w2 arg2 res2) - = go env arg1 arg2 && go env res1 res2 && go env w1 w2 - -- Visible stuff only: ignore agg kinds +eqVarBndrs :: HasCallStack => RnEnv2 -> [Var] -> [Var] -> Maybe RnEnv2 +-- Check that the var lists are the same length +-- and have matching kinds; if so, extend the RnEnv2 +-- Returns Nothing if they don't match +eqVarBndrs env [] [] + = Just env +eqVarBndrs env (tv1:tvs1) (tv2:tvs2) + | eqTypeX env (varType tv1) (varType tv2) + = eqVarBndrs (rnBndr2 env tv1 tv2) tvs1 tvs2 +eqVarBndrs _ _ _= Nothing - -- See Note [Equality on AppTys] in GHC.Core.Type - go env (AppTy s1 t1) ty2 - | Just (s2, t2) <- tcSplitAppTyNoView_maybe ty2 - = go env s1 s2 && go env t1 t2 - go env ty1 (AppTy s2 t2) - | Just (s1, t1) <- tcSplitAppTyNoView_maybe ty1 - = go env s1 s2 && go env t1 t2 +initRnEnv :: Type -> Type -> RnEnv2 +initRnEnv ta tb = mkRnEnv2 $ mkInScopeSet $ + tyCoVarsOfType ta `unionVarSet` tyCoVarsOfType tb - go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) - = tc1 == tc2 && gos env (tyConBinders tc1) ts1 ts2 +eqTypeNoKindCheck :: Type -> Type -> Bool +eqTypeNoKindCheck ty1 ty2 = eq_type_expand_respect ty1 ty2 - go _ _ _ = False - - gos :: RnEnv2 -> [TyConBinder] -> [Type] -> [Type] -> Bool - gos _ _ [] [] = True - gos env bs (t1:ts1) (t2:ts2) - | (invisible, bs') <- case bs of - [] -> (False, []) - (b:bs) -> (isInvisibleTyConBinder b, bs) - = (invisible || go env t1 t2) && gos env bs' ts1 ts2 - - gos _ _ _ _ = False +-- | Type equality comparing both visible and invisible arguments, +-- expanding synonyms and respecting multiplicities. +eqType :: HasCallStack => Type -> Type -> Bool +eqType ta tb = fullEq eq_type_expand_respect ta tb +-- | Compare types with respect to a (presumably) non-empty 'RnEnv2'. +eqTypeX :: HasCallStack => RnEnv2 -> Type -> Type -> Bool +eqTypeX env ta tb = fullEq (eq_type_expand_respect_x env) ta tb --- | Type equality comparing both visible and invisible arguments and expanding --- type synonyms. -tcEqTypeNoSyns :: Type -> Type -> Bool -tcEqTypeNoSyns ta tb = tc_eq_type False ta tb +eqTypeIgnoringMultiplicity :: Type -> Type -> Bool +-- See Note [Respecting multiplicity when comparing types] +eqTypeIgnoringMultiplicity ta tb = fullEq eq_type_expand_ignore ta tb -- | Like 'pickyEqTypeVis', but returns a Bool for convenience pickyEqType :: Type -> Type -> Bool -- Check when two types _look_ the same, _including_ synonyms. -- So (pickyEqType String [Char]) returns False -- This ignores kinds and coercions, because this is used only for printing. -pickyEqType ty1 ty2 = tc_eq_type True ty1 ty2 +pickyEqType ta tb = eq_type_keep_respect ta tb --- | Real worker for 'tcEqType'. No kind check! -tc_eq_type :: Bool -- ^ True <=> do not expand type synonyms - -> Type -> Type - -> Bool --- Flags False, False is the usual setting for tc_eq_type --- See Note [Computing equality on types] in Type -{-# INLINE tc_eq_type #-} -- See Note [Specialising tc_eq_type]. -tc_eq_type keep_syns orig_ty1 orig_ty2 - = go orig_env orig_ty1 orig_ty2 - where - orig_env = mkRnEnv2 $ mkInScopeSet $ tyCoVarsOfTypes [orig_ty1, orig_ty2] +{- Note [Specialising type equality] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The type equality predicates in Type are hit pretty hard by GHC. Consequently +we take pains to ensure that these paths are compiled to efficient, +minimally-allocating code. Plan: - go :: RnEnv2 -> Type -> Type -> Bool - -- See Note [Comparing nullary type synonyms] - go _ (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = True +* The main workhorse is `inline_generic_eq_type_x`. It is /non-recursive/ + and is marked INLINE. - go env t1 t2 | not keep_syns, Just t1' <- coreView t1 = go env t1' t2 - go env t1 t2 | not keep_syns, Just t2' <- coreView t2 = go env t1 t2' +* `inline_generic_eq_type_x` has various parameters that control what it does: + * syn_flag::SynFlag whether type synonyms are expanded or kept. + * mult_flag::MultiplicityFlag whether multiplicities are ignored or respected + * mb_env::Maybe RnEnv2 an optional RnEnv2. - go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 - go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 - go env (CastTy t1 _) t2 = go env t1 t2 - go env t1 (CastTy t2 _) = go env t1 t2 - go _ (CoercionTy {}) (CoercionTy {}) = True +* `inline_generic_eq_type_x` has a handful of call sites, namely the ones + in `eq_type_expand_respect`, `eq_type_expand_repect_x` etc. It inlines + at all these sites, specialising to the data values passed for the + control parameters. - go env (ForAllTy (Bndr tv1 vis1) ty1) - (ForAllTy (Bndr tv2 vis2) ty2) - = vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] - && go env (varType tv1) (varType tv2) - && go (rnBndr2 env tv1 tv2) ty1 ty2 +* All /other/ calls to `inline_generic_eq_type_x` go via + generic_eq_type_x = inline_generic_eq_type_x + {-# NOINLNE generic_eq_type_x #-} + The idea is that all calls to `generic_eq_type_x` are specialised by the + RULES, so this NOINLINE version is seldom, if ever, actually called. + +* For each of specialised copy of `inline_generic_eq_type_x, there is a + corresponding rewrite RULE that rewrites a call to (generic_eq_type_x args) + into the appropriate specialied version. + +See #19226. +-} + +-- | This flag controls whether we expand synonyms during comparison +data SynFlag = ExpandSynonyms | KeepSynonyms + +eq_type_expand_respect, eq_type_expand_ignore, eq_type_keep_respect + :: Type -> Type -> Bool +eq_type_expand_respect_x, eq_type_expand_ignore_x, eq_type_keep_respect_x + :: RnEnv2 -> Type -> Type -> Bool + +eq_type_expand_respect = inline_generic_eq_type_x ExpandSynonyms RespectMultiplicities Nothing +eq_type_expand_respect_x env = inline_generic_eq_type_x ExpandSynonyms RespectMultiplicities (Just env) +eq_type_expand_ignore = inline_generic_eq_type_x ExpandSynonyms IgnoreMultiplicities Nothing +eq_type_expand_ignore_x env = inline_generic_eq_type_x ExpandSynonyms IgnoreMultiplicities (Just env) +eq_type_keep_respect = inline_generic_eq_type_x KeepSynonyms RespectMultiplicities Nothing +eq_type_keep_respect_x env = inline_generic_eq_type_x KeepSynonyms RespectMultiplicities (Just env) + +{-# RULES +"eqType1" generic_eq_type_x ExpandSynonyms RespectMultiplicities Nothing + = eq_type_expand_respect +"eqType2" forall env. generic_eq_type_x ExpandSynonyms RespectMultiplicities (Just env) + = eq_type_expand_respect_x env +"eqType3" generic_eq_type_x ExpandSynonyms IgnoreMultiplicities Nothing + = eq_type_expand_ignore +"eqType4" forall env. generic_eq_type_x ExpandSynonyms IgnoreMultiplicities (Just env) + = eq_type_expand_ignore_x env +"eqType5" generic_eq_type_x KeepSynonyms RespectMultiplicities Nothing + = eq_type_keep_respect +"eqType6" forall env. generic_eq_type_x KeepSynonyms RespectMultiplicities (Just env) + = eq_type_keep_respect_x env + #-} + +-- --------------------------------------------------------------- +-- | Real worker for 'eqType'. No kind check! +-- Inline it at the (handful of local) call sites +-- The "generic" bit refers to the flag paramerisation +-- See Note [Specialising type equality]. +generic_eq_type_x, inline_generic_eq_type_x + :: SynFlag -> MultiplicityFlag -> Maybe RnEnv2 -> Type -> Type -> Bool + +{-# NOINLINE generic_eq_type_x #-} +generic_eq_type_x = inline_generic_eq_type_x +-- See Note [Computing equality on types] in Type + +{-# INLINE inline_generic_eq_type_x #-} +-- This non-recursive function can inline at its (few) call sites. The +-- recursion goes via generic_eq_type_x, which is the loop-breaker. +inline_generic_eq_type_x syn_flag mult_flag mb_env + = \ t1 t2 -> t1 `seq` t2 `seq` + let go = generic_eq_type_x syn_flag mult_flag mb_env + -- Abbreviation for recursive calls + in case (t1,t2) of + _ | 1# <- reallyUnsafePtrEquality# t1 t2 -> True + -- See Note [Type comparisons using object pointer comparisons] + + (TyConApp tc1 [], TyConApp tc2 []) | tc1 == tc2 -> True + -- See Note [Comparing nullary type synonyms] + + _ | ExpandSynonyms <- syn_flag, Just t1' <- coreView t1 -> go t1' t2 + | ExpandSynonyms <- syn_flag, Just t2' <- coreView t2 -> go t1 t2' + + (TyVarTy tv1, TyVarTy tv2) + -> case mb_env of + Nothing -> tv1 == tv2 + Just env -> rnOccL env tv1 == rnOccR env tv2 + + (LitTy lit1, LitTy lit2) -> lit1 == lit2 + (CastTy t1' _, _) -> go t1' t2 -- Ignore casts + (_, CastTy t2' _) -> go t1 t2' -- Ignore casts + (CoercionTy {}, CoercionTy {}) -> True -- Ignore coercions -- Make sure we handle all FunTy cases since falling through to the -- AppTy case means that tcSplitAppTyNoView_maybe may see an unzonked -- kind variable, which causes things to blow up. -- See Note [Equality on FunTys] in GHC.Core.TyCo.Rep: we must check -- kinds here - go env (FunTy _ w1 arg1 res1) (FunTy _ w2 arg2 res2) - = go env (typeKind arg1) (typeKind arg2) && - go env (typeKind res1) (typeKind res2) && - go env arg1 arg2 && go env res1 res2 && go env w1 w2 + (FunTy _ w1 arg1 res1, FunTy _ w2 arg2 res2) + -> fullEq go arg1 arg2 + && fullEq go res1 res2 + && (case mult_flag of + RespectMultiplicities -> go w1 w2 + IgnoreMultiplicities -> True) -- See Note [Equality on AppTys] in GHC.Core.Type - go env (AppTy s1 t1) ty2 - | Just (s2, t2) <- tcSplitAppTyNoView_maybe ty2 - = go env s1 s2 && go env t1 t2 - go env ty1 (AppTy s2 t2) - | Just (s1, t1) <- tcSplitAppTyNoView_maybe ty1 - = go env s1 s2 && go env t1 t2 - - go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) - = tc1 == tc2 && gos env ts1 ts2 - - go _ _ _ = False - - gos _ [] [] = True - gos env (t1:ts1) (t2:ts2) = go env t1 t2 && gos env ts1 ts2 - gos _ _ _ = False + (AppTy s1 t1', _) + | Just (s2, t2') <- tcSplitAppTyNoView_maybe t2 + -> go s1 s2 && go t1' t2' + (_, AppTy s2 t2') + | Just (s1, t1') <- tcSplitAppTyNoView_maybe t1 + -> go s1 s2 && go t1' t2' + + (TyConApp tc1 ts1, TyConApp tc2 ts2) + | tc1 == tc2 -> gos ts1 ts2 + | otherwise -> False + where + gos [] [] = True + gos (t1:ts1) (t2:ts2) = go t1 t2 && gos ts1 ts2 + gos _ _ = False + + (ForAllTy (Bndr tv1 vis1) body1, ForAllTy (Bndr tv2 vis2) body2) + -> case mb_env of + Nothing -> generic_eq_type_x syn_flag mult_flag + (Just (initRnEnv t1 t2)) t1 t2 + Just env + | vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] + -> go (varType tv1) (varType tv2) -- Always do kind-check + && generic_eq_type_x syn_flag mult_flag + (Just (rnBndr2 env tv1 tv2)) body1 body2 + | otherwise + -> False + + _ -> False + +fullEq :: (Type -> Type -> Bool) -> Type -> Type -> Bool +-- Do "full equality" including the kind check +-- See Note [Casts and coercions in type comparision] +{-# INLINE fullEq #-} +fullEq eq ty1 ty2 + = case eq ty1 ty2 of + False -> False + True | hasCasts ty1 || hasCasts ty2 + -> eq (typeKind ty1) (typeKind ty2) + | otherwise + -> True + +hasCasts :: Type -> Bool +-- Fast, does not look deep, does not allocate +hasCasts (CastTy {}) = True +hasCasts (CoercionTy {}) = True +hasCasts (AppTy t1 t2) = hasCasts t1 || hasCasts t2 +hasCasts (ForAllTy _ ty) = hasCasts ty +hasCasts _ = False -- TyVarTy, TyConApp, FunTy, LitTy -isDefaultableBndr :: ForAllTyBinder -> Bool --- This function should line up with the defaulting done --- by GHC.Iface.Type.defaultIfaceTyVarsOfKind --- See Note [Showing invisible bits of types in error messages] --- in GHC.Tc.Errors.Ppr -isDefaultableBndr (Bndr tv vis) - = isInvisibleForAllTyFlag vis && is_defaultable (tyVarKind tv) - where - is_defaultable ki = isLevityTy ki || isRuntimeRepTy ki || isMultiplicityTy ki +{- ********************************************************************* +* * + Comparing ForAllTyFlags +* * +********************************************************************* -} -- | Do these denote the same level of visibility? 'Required' -- arguments are visible, others are not. So this function @@ -442,91 +588,13 @@ is more finer-grained than definitional equality in two places: ************************************************************************ * * Comparison for types - (We don't use instances so that we know where it happens) + + Not so heavily used, less carefully optimised * * ************************************************************************ -Note [Equality on AppTys] -~~~~~~~~~~~~~~~~~~~~~~~~~ -In our cast-ignoring equality, we want to say that the following two -are equal: - - (Maybe |> co) (Int |> co') ~? Maybe Int - -But the left is an AppTy while the right is a TyConApp. The solution is -to use splitAppTyNoView_maybe to break up the TyConApp into its pieces and -then continue. Easy to do, but also easy to forget to do. - -Note [Comparing nullary type synonyms] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Consider the task of testing equality between two 'Type's of the form - - TyConApp tc [] - -where @tc@ is a type synonym. A naive way to perform this comparison these -would first expand the synonym and then compare the resulting expansions. - -However, this is obviously wasteful and the RHS of @tc@ may be large; it is -much better to rather compare the TyCons directly. Consequently, before -expanding type synonyms in type comparisons we first look for a nullary -TyConApp and simply compare the TyCons if we find one. Of course, if we find -that the TyCons are *not* equal then we still need to perform the expansion as -their RHSs may still be equal. - -We perform this optimisation in a number of places: - - * GHC.Core.Types.eqType - * GHC.Core.Types.nonDetCmpType - * GHC.Core.Unify.unify_ty - * GHC.Tc.Solver.Equality.can_eq_nc' - * TcUnify.uType - -This optimisation is especially helpful for the ubiquitous GHC.Types.Type, -since GHC prefers to use the type synonym over @TYPE 'LiftedRep@ applications -whenever possible. See Note [Using synonyms to compress types] in -GHC.Core.Type for details. - --} - -eqType :: Type -> Type -> Bool --- ^ Type equality on source types. Does not look through @newtypes@, --- 'PredType's or type families, but it does look through type synonyms. --- This first checks that the kinds of the types are equal and then --- checks whether the types are equal, ignoring casts and coercions. --- (The kind check is a recursive call, but since all kinds have type --- @Type@, there is no need to check the types of kinds.) --- See also Note [Non-trivial definitional equality] in "GHC.Core.TyCo.Rep". -eqType t1 t2 = isEqual $ nonDetCmpType t1 t2 - -- It's OK to use nonDetCmpType here and eqType is deterministic, - -- nonDetCmpType does equality deterministically - --- | Compare types with respect to a (presumably) non-empty 'RnEnv2'. -eqTypeX :: RnEnv2 -> Type -> Type -> Bool -eqTypeX env t1 t2 = isEqual $ nonDetCmpTypeX env t1 t2 - -- It's OK to use nonDetCmpType here and eqTypeX is deterministic, - -- nonDetCmpTypeX does equality deterministically - --- | Type equality on lists of types, looking through type synonyms --- but not newtypes. -eqTypes :: [Type] -> [Type] -> Bool -eqTypes tys1 tys2 = isEqual $ nonDetCmpTypes tys1 tys2 - -- It's OK to use nonDetCmpType here and eqTypes is deterministic, - -- nonDetCmpTypes does equality deterministically - -eqVarBndrs :: RnEnv2 -> [Var] -> [Var] -> Maybe RnEnv2 --- Check that the var lists are the same length --- and have matching kinds; if so, extend the RnEnv2 --- Returns Nothing if they don't match -eqVarBndrs env [] [] - = Just env -eqVarBndrs env (tv1:tvs1) (tv2:tvs2) - | eqTypeX env (varType tv1) (varType tv2) - = eqVarBndrs (rnBndr2 env tv1 tv2) tvs1 tvs2 -eqVarBndrs _ _ _= Nothing - -- Now here comes the real worker -{- Note [nonDetCmpType nondeterminism] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ nonDetCmpType is implemented in terms of nonDetCmpTypeX. nonDetCmpTypeX @@ -538,6 +606,7 @@ See Note [Unique Determinism] for more details. -} nonDetCmpType :: Type -> Type -> Ordering +{-# INLINE nonDetCmpType #-} nonDetCmpType !t1 !t2 -- See Note [Type comparisons using object pointer comparisons] | 1# <- reallyUnsafePtrEquality# t1 t2 @@ -549,12 +618,6 @@ nonDetCmpType t1 t2 = nonDetCmpTypeX rn_env t1 t2 where rn_env = mkRnEnv2 (mkInScopeSet (tyCoVarsOfTypes [t1, t2])) -{-# INLINE nonDetCmpType #-} - -nonDetCmpTypes :: [Type] -> [Type] -> Ordering -nonDetCmpTypes ts1 ts2 = nonDetCmpTypesX rn_env ts1 ts2 - where - rn_env = mkRnEnv2 (mkInScopeSet (tyCoVarsOfTypes (ts1 ++ ts2))) -- | An ordering relation between two 'Type's (known below as @t1 :: k1@ -- and @t2 :: k2@) @@ -569,6 +632,7 @@ data TypeOrdering = TLT -- ^ @t1 < t2@ nonDetCmpTypeX :: RnEnv2 -> Type -> Type -> Ordering -- Main workhorse -- See Note [Non-trivial definitional equality] in GHC.Core.TyCo.Rep -- See Note [Computing equality on types] + -- Always respects multiplicities, unlike eqType nonDetCmpTypeX env orig_t1 orig_t2 = case go env orig_t1 orig_t2 of -- If there are casts then we also need to do a comparison of @@ -661,13 +725,6 @@ nonDetCmpTypeX env orig_t1 orig_t2 = gos _ _ [] = TGT gos env (ty1:tys1) (ty2:tys2) = go env ty1 ty2 `thenCmpTy` gos env tys1 tys2 -------------- -nonDetCmpTypesX :: RnEnv2 -> [Type] -> [Type] -> Ordering -nonDetCmpTypesX _ [] [] = EQ -nonDetCmpTypesX env (t1:tys1) (t2:tys2) = nonDetCmpTypeX env t1 t2 S.<> - nonDetCmpTypesX env tys1 tys2 -nonDetCmpTypesX _ [] _ = LT -nonDetCmpTypesX _ _ [] = GT ------------- -- | Compare two 'TyCon's. @@ -680,4 +737,91 @@ nonDetCmpTc tc1 tc2 u2 = tyConUnique tc2 +{- ********************************************************************* +* * + mayLookIdentical +* * +********************************************************************* -} + +mayLookIdentical :: Type -> Type -> Bool +-- | Returns True if the /visible/ part of the types +-- might look equal, even if they are really unequal (in the invisible bits) +-- +-- This function is very similar to tc_eq_type but it is much more +-- heuristic. Notably, it is always safe to return True, even with types +-- that might (in truth) be unequal -- this affects error messages only +-- (Originally this test was done by eqType with an extra flag, but the result +-- was hard to understand.) +mayLookIdentical orig_ty1 orig_ty2 + = go orig_env orig_ty1 orig_ty2 + where + orig_env = mkRnEnv2 $ mkInScopeSet $ tyCoVarsOfTypes [orig_ty1, orig_ty2] + + go :: RnEnv2 -> Type -> Type -> Bool + -- See Note [Comparing nullary type synonyms] + go _ (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = True + + go env t1 t2 | Just t1' <- coreView t1 = go env t1' t2 + go env t1 t2 | Just t2' <- coreView t2 = go env t1 t2' + + go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 + go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 + go env (CastTy t1 _) t2 = go env t1 t2 + go env t1 (CastTy t2 _) = go env t1 t2 + go _ (CoercionTy {}) (CoercionTy {}) = True + + go env (ForAllTy (Bndr tv1 vis1) ty1) + (ForAllTy (Bndr tv2 vis2) ty2) + = vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] + && go (rnBndr2 env tv1 tv2) ty1 ty2 + -- Visible stuff only: ignore kinds of binders + + -- If we have (forall (r::RunTimeRep). ty1 ~ blah) then respond + -- with True. Reason: the type pretty-printer defaults RuntimeRep + -- foralls (see Ghc.Iface.Type.hideNonStandardTypes). That can make, + -- say (forall r. TYPE r -> Type) into (Type -> Type), so it looks the + -- same as a very different type (#24553). By responding True, we + -- tell GHC (see calls of mayLookIdentical) to display without defaulting. + -- See Note [Showing invisible bits of types in error messages] + -- in GHC.Tc.Errors.Ppr + go _ (ForAllTy b _) _ | isDefaultableBndr b = True + go _ _ (ForAllTy b _) | isDefaultableBndr b = True + + go env (FunTy _ w1 arg1 res1) (FunTy _ w2 arg2 res2) + = go env arg1 arg2 && go env res1 res2 && go env w1 w2 + -- Visible stuff only: ignore agg kinds + + -- See Note [Equality on AppTys] in GHC.Core.Type + go env (AppTy s1 t1) ty2 + | Just (s2, t2) <- tcSplitAppTyNoView_maybe ty2 + = go env s1 s2 && go env t1 t2 + go env ty1 (AppTy s2 t2) + | Just (s1, t1) <- tcSplitAppTyNoView_maybe ty1 + = go env s1 s2 && go env t1 t2 + + go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) + = tc1 == tc2 && gos env (tyConBinders tc1) ts1 ts2 + + go _ _ _ = False + + gos :: RnEnv2 -> [TyConBinder] -> [Type] -> [Type] -> Bool + gos _ _ [] [] = True + gos env bs (t1:ts1) (t2:ts2) + | (invisible, bs') <- case bs of + [] -> (False, []) + (b:bs) -> (isInvisibleTyConBinder b, bs) + = (invisible || go env t1 t2) && gos env bs' ts1 ts2 + + gos _ _ _ _ = False + + +isDefaultableBndr :: ForAllTyBinder -> Bool +-- This function should line up with the defaulting done +-- by GHC.Iface.Type.defaultIfaceTyVarsOfKind +-- See Note [Showing invisible bits of types in error messages] +-- in GHC.Tc.Errors.Ppr +isDefaultableBndr (Bndr tv vis) + = isInvisibleForAllTyFlag vis && is_defaultable (tyVarKind tv) + where + is_defaultable ki = isLevityTy ki || isRuntimeRepTy ki || isMultiplicityTy ki ===================================== compiler/GHC/Core/TyCo/Rep.hs ===================================== @@ -350,14 +350,24 @@ This kind instantiation only happens in TyConApp currently. Note [Non-trivial definitional equality] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Is Int |> <*> the same as Int? YES! In order to reduce headaches, -we decide that any reflexive casts in types are just ignored. -(Indeed they must be. See Note [Respecting definitional equality].) -More generally, the `eqType` function, which defines Core's type equality -relation, ignores casts and coercion arguments, as long as the -two types have the same kind. This allows us to be a little sloppier -in keeping track of coercions, which is a good thing. It also means -that eqType does not depend on eqCoercion, which is also a good thing. +Is ((IO |> co1) Int |> co2) equal to (IO Int)? +Assume + co1 :: (Type->Type) ~ (Type->Wombat) + co2 :: Wombat ~ Type +Well, yes. The casts are just getting in the way. +See also Note [Respecting definitional equality]. + +So we do this: + +(EQTYPE) + The `eqType` function, which defines Core's type equality relation, + - /ignores/ casts, and + - /ignores/ coercion arguments + - /provided/ two types have the same kind + +This allows us to be a little sloppier in keeping track of coercions, which is a +good thing. It also means that eqType does not depend on eqCoercion, which is +also a good thing. Why is this sensible? That is, why is something different than α-equivalence appropriate for the implementation of eqType? ===================================== compiler/GHC/Core/Type.hs ===================================== @@ -1366,6 +1366,8 @@ funTyConAppTy_maybe :: FunTyFlag -> Type -> Type -> Type funTyConAppTy_maybe af mult arg res | Just arg_rep <- getRuntimeRep_maybe arg , Just res_rep <- getRuntimeRep_maybe res + -- If you're changing the lines below, you'll probably want to adapt the + -- `fUNTyCon` case of GHC.Core.Unify.unify_ty correspondingly. , let args | isFUNArg af = [mult, arg_rep, res_rep, arg, res] | otherwise = [ arg_rep, res_rep, arg, res] = Just $ (funTyFlagTyCon af, args) ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -54,6 +54,8 @@ import GHC.Data.FastString import Data.List ( mapAccumL ) import Control.Monad import qualified Data.Semigroup as S +import GHC.Builtin.Types.Prim (fUNTyCon) +import GHC.Core.Multiplicity {- @@ -211,6 +213,7 @@ tc_match_tys_x bind_me match_kis (Subst in_scope id_env tv_env cv_env) tys1 tys2 False -- Matching, not unifying False -- Not an injectivity check match_kis + RespectMultiplicities (mkRnEnv2 in_scope) tv_env cv_env tys1 tys2 of Unifiable (tv_env', cv_env') -> Just $ Subst in_scope id_env tv_env' cv_env' @@ -229,6 +232,8 @@ ruleMatchTyKiX tmpl_tvs rn_env tenv tmpl target -- See Note [Kind coercions in Unify] = case tc_unify_tys (matchBindFun tmpl_tvs) False False True -- <-- this means to match the kinds + IgnoreMultiplicities + -- See Note [Rewrite rules ignore multiplicities in FunTy] rn_env tenv emptyCvSubstEnv [tmpl] [target] of Unifiable (tenv', _) -> Just tenv' _ -> Nothing @@ -394,6 +399,40 @@ types are apart. This has practical consequences for the ability for closed type family applications to reduce. See test case indexed-types/should_compile/Overlap14. +Note [Rewrite rules ignore multiplicities in FunTy] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider the following (higher-order) rule: + +m :: Bool -> Bool -> Bool +{-# RULES "m" forall f. m (f True) = f #-} + +let x = m ((,) @Bool @Bool True True) + +The rewrite rule expects an `f :: Bool -> Bool`, but `(,) @Bool @Bool True :: +Bool %1 -> Bool` is linear (see Note [Data constructors are linear by default] +in GHC.Core.Multiplicity) Should the rule match? Yes! According to the +principles laid out in Note [Linting linearity] in GHC.Core.Lint, optimisation +shouldn't be constrained by linearity. + +However, when matching the template variable `f` to `(,) True`, we do check that +their types unify (see Note [Matching variable types] in GHC.Core.Rules). So +when unifying types for the sake of rule-matching, the unification algorithm +must be able to ignore multiplicities altogether. + +How is this done? + (1) The `um_arr_mult` field of `UMEnv` recordsw when we are doing rule-matching, + and hence want to ignore multiplicities. + (2) The field is set to True in by `ruleMatchTyKiX`. + (3) It is consulted when matching `FunTy` in `unify_ty`. + +Wrinkle in (3). In `unify_tc_app`, in `unify_ty`, `FunTy` is handled as if it +was a regular type constructor. In this case, and when the types being unified +are *function* arrows, but not constraint arrows, then the first argument is a +multiplicity. + +We select this situation by comparing the type constructor with fUNTyCon. In +this case, and this case only, we can safely drop the first argument (using the +tail function) and unify the rest. -} -- | Simple unification of two types; all type variables are bindable @@ -421,7 +460,7 @@ tcUnifyTyWithTFs :: Bool -- ^ True <=> do two-way unification; -- The code is incorporated with the standard unifier for convenience, but -- its operation should match the specification in the paper. tcUnifyTyWithTFs twoWay in_scope t1 t2 - = case tc_unify_tys alwaysBindFun twoWay True False + = case tc_unify_tys alwaysBindFun twoWay True False RespectMultiplicities rn_env emptyTvSubstEnv emptyCvSubstEnv [t1] [t2] of Unifiable (tv_subst, _cv_subst) -> Just $ maybe_fix tv_subst @@ -530,7 +569,7 @@ tc_unify_tys_fg :: Bool -> [Type] -> [Type] -> UnifyResult tc_unify_tys_fg match_kis bind_fn tys1 tys2 - = do { (env, _) <- tc_unify_tys bind_fn True False match_kis rn_env + = do { (env, _) <- tc_unify_tys bind_fn True False match_kis RespectMultiplicities rn_env emptyTvSubstEnv emptyCvSubstEnv tys1 tys2 ; return $ niFixSubst in_scope env } @@ -544,6 +583,7 @@ tc_unify_tys :: BindFun -> AmIUnifying -- ^ True <=> unify; False <=> match -> Bool -- ^ True <=> doing an injectivity check -> Bool -- ^ True <=> treat the kinds as well + -> MultiplicityFlag -- ^ see Note [Rewrite rules ignore multiplicities in FunTy] in GHC.Core.Unify -> RnEnv2 -> TvSubstEnv -- ^ substitution to extend -> CvSubstEnv @@ -560,7 +600,7 @@ tc_unify_tys :: BindFun -- pair equal. Yet, we still don't need a separate pass to unify the kinds -- of these types, so it's appropriate to use the Ty variant of unification. -- See also Note [tcMatchTy vs tcMatchTyKi]. -tc_unify_tys bind_fn unif inj_check match_kis rn_env tv_env cv_env tys1 tys2 +tc_unify_tys bind_fn unif inj_check match_kis match_mults rn_env tv_env cv_env tys1 tys2 = initUM tv_env cv_env $ do { when match_kis $ unify_tys env kis1 kis2 @@ -571,6 +611,7 @@ tc_unify_tys bind_fn unif inj_check match_kis rn_env tv_env cv_env tys1 tys2 , um_skols = emptyVarSet , um_unif = unif , um_inj_tf = inj_check + , um_arr_mult = match_mults , um_rn_env = rn_env } kis1 = map typeKind tys1 @@ -1144,7 +1185,7 @@ unify_ty env ty1 ty2 _kco , Just (tc2, tys2) <- mb_tc_app2 , tc1 == tc2 = do { massertPpr (isInjectiveTyCon tc1 Nominal) (ppr tc1) - ; unify_tys env tys1 tys2 + ; unify_tc_app tc1 tys1 tys2 } -- TYPE and CONSTRAINT are not Apart @@ -1175,6 +1216,21 @@ unify_ty env ty1 ty2 _kco mb_tc_app1 = splitTyConApp_maybe ty1 mb_tc_app2 = splitTyConApp_maybe ty2 + unify_tc_app tc tys1 tys2 + | tc == fUNTyCon + , IgnoreMultiplicities <- um_arr_mult env + , (_mult1 : no_mult_tys1) <- tys1 + , (_mult2 : no_mult_tys2) <- tys2 + = -- We're comparing function arrow types here (not constraint arrow + -- types!), and they have at least one argument, which is the arrow's + -- multiplicity annotation. The flag `um_arr_mult` instructs us to + -- ignore multiplicities in this very case. This is a little tricky: see + -- point (3) in Note [Rewrite rules ignore multiplicities in FunTy]. + unify_tys env no_mult_tys1 no_mult_tys2 + + | otherwise + = unify_tys env tys1 tys2 + -- Applications need a bit of care! -- They can match FunTy and TyConApp, so use splitAppTy_maybe -- NB: we've already dealt with type variables, @@ -1410,6 +1466,10 @@ data UMEnv -- Checking for injectivity? -- See (end of) Note [Specification of unification] + , um_arr_mult :: MultiplicityFlag + -- Whether to unify multiplicity arguments when unifying arrows. + -- See Note [Rewrite rules ignore multiplicities in FunTy] + , um_rn_env :: RnEnv2 -- Renaming InTyVars to OutTyVars; this eliminates -- shadowing, and lines up matching foralls on the left ===================================== compiler/GHC/Tc/Utils/TcType.hs ===================================== @@ -96,7 +96,7 @@ module GHC.Tc.Utils.TcType ( -- Re-exported from GHC.Core.TyCo.Compare -- mainly just for back-compat reasons - eqType, eqTypes, nonDetCmpType, nonDetCmpTypes, eqTypeX, + eqType, eqTypes, nonDetCmpType, eqTypeX, pickyEqType, tcEqType, tcEqKind, tcEqTypeNoKindCheck, mayLookIdentical, tcEqTyConApps, eqForAllVis, eqVarBndrs, ===================================== testsuite/tests/simplCore/should_run/T23586.hs ===================================== @@ -0,0 +1,45 @@ +{-# LANGUAGE LinearTypes #-} + +module Main where + +-- These rules are clearly nonsensical, so that we can observe the result of +-- their firing. +{-# RULES "test/match" forall f. mark (f True) = (False, False) #-} +{-# RULES "test/core" forall f. mark (f False) = ensure_many f #-} + +-- Tests that constructors are matched by higher-order rules (as originally +-- reported) +g = mark (True, True) + +-- Tests that linear functions are matched by higher-order rules (as was +-- understood to be the root cause of the issue) +h = mark (d True) + +-- Tests that a matched linear function can be used where a non-linear function +-- is expected, and that the result passes the linter. This wasn't part of the +-- original report, but a first fix to #23586 was incorrect because this rule +-- produced Core which was rejected by the linter. +-- See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12648#note_565803 . +i = mark (d False) + +main :: IO () +main = do + print g + print h + print i + + +-- Helpers below + +mark :: a -> a +mark x = x +{-# NOINLINE mark #-} + +d :: Bool %1 -> (Bool, Bool) +d True = (True, True) +d False = (False, False) +{-# NOINLINE d #-} + +ensure_many :: (Bool -> (Bool, Bool)) -> (Bool, Bool) +ensure_many f = (False, True) +{-# NOINLINE ensure_many #-} ===================================== testsuite/tests/simplCore/should_run/T23586.stdout ===================================== @@ -0,0 +1,3 @@ +(False,False) +(False,False) +(False,True) ===================================== testsuite/tests/simplCore/should_run/all.T ===================================== @@ -114,3 +114,4 @@ test('T23184', normal, compile_and_run, ['-O']) test('T23134', normal, compile_and_run, ['-O0 -fcatch-nonexhaustive-cases']) test('T23289', normal, compile_and_run, ['']) test('T23056', [only_ways(['ghci-opt'])], ghci_script, ['T23056.script']) +test('T23586', normal, compile_and_run, ['-O -dcore-lint']) ===================================== utils/haddock/haddock-api/haddock-api.cabal ===================================== @@ -43,8 +43,29 @@ source-repository head location: https://gitlab.haskell.org/ghc/ghc.git subdir: utils/haddock/haddock-api +common extensions + default-extensions: + LambdaCase + NoStarIsType + OverloadedRecordDot + StrictData + TypeApplications + TypeOperators + + default-language: Haskell2010 + +common ghc-options + ghc-options: + -Wall -Wcompat -Widentities -Wincomplete-record-updates + -Wincomplete-uni-patterns -Wredundant-constraints + -fhide-source-paths -Wno-unused-do-bind -fshow-hole-constraints + -Wno-unticked-promoted-constructors -Werror=unused-imports + -fdicts-strict -Wunused-packages -funbox-strict-fields + -Wnoncanonical-monad-instances -Wmissing-home-modules + library - default-language: Haskell2010 + import: extensions + import: ghc-options -- this package typically supports only single major versions build-depends: base >= 4.16 && < 4.21 @@ -69,19 +90,6 @@ library , transformers hs-source-dirs: src - - ghc-options: -funbox-strict-fields -O2 - -Wall - -Wcompat - -Wcompat-unqualified-imports - -Widentities - -Wredundant-constraints - -Wnoncanonical-monad-instances - -Wmissing-home-modules - -Wincomplete-uni-patterns - -Wincomplete-record-updates - - exposed-modules: Documentation.Haddock @@ -131,10 +139,10 @@ library Paths_haddock_api test-suite spec + import: extensions + import: ghc-options type: exitcode-stdio-1.0 - default-language: Haskell2010 main-is: Spec.hs - ghc-options: -Wall hs-source-dirs: test @@ -201,7 +209,6 @@ test-suite spec , exceptions , filepath , ghc-boot - , ghc-boot-th , mtl , transformers ===================================== utils/haddock/haddock-api/src/Haddock.hs ===================================== @@ -5,7 +5,6 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# OPTIONS_GHC -Wwarn #-} ----------------------------------------------------------------------------- -- | -- Module : Haddock @@ -50,9 +49,9 @@ import Control.DeepSeq (force) import Control.Monad hiding (forM_) import Control.Monad.IO.Class (MonadIO(..)) import Data.Bifunctor (second) -import Data.Foldable (forM_, foldl') +import Data.Foldable (forM_) import Data.Traversable (for) -import Data.List (find, isPrefixOf, nub) +import qualified Data.List as List import Control.Exception import Data.Maybe import Data.IORef @@ -256,7 +255,7 @@ withTempOutputDir action = do -- | Create warnings about potential misuse of -optghc optGhcWarnings :: [String] -> [String] -optGhcWarnings = map format . filter (isPrefixOf "-optghc") +optGhcWarnings = map format . filter (List.isPrefixOf "-optghc") where format arg = concat ["Warning: `", arg, "' means `-o ", drop 2 arg, "', did you mean `-", arg, "'?"] @@ -449,7 +448,7 @@ render log' dflags unit_state flags sinceQual qual ifaces packages extSrcMap = d let withQuickjump = Flag_QuickJumpIndex `elem` flags withBaseURL = isJust - . find (\flag -> case flag of + . List.find (\flag -> case flag of Flag_BaseURL base_url -> base_url /= "." && base_url /= "./" _ -> False @@ -481,7 +480,7 @@ render log' dflags unit_state flags sinceQual qual ifaces packages extSrcMap = d ppJsonIndex odir sourceUrls' opt_wiki_urls unicode Nothing qual ifaces - ( nub + ( List.nub . map fst . filter ((== Visible) . piVisibility . snd) $ packages) @@ -612,7 +611,7 @@ withGhc' libDir needHieFiles flags ghcActs = runGhc (Just libDir) $ do ++ if needHieFiles then [Opt_WriteHie] -- Generate .hie-files else [] - dynflags' = (foldl' gopt_set dynflags extra_opts) + dynflags' = (List.foldl' gopt_set dynflags extra_opts) { backend = noBackend , ghcMode = CompManager , ghcLink = NoLink @@ -626,7 +625,7 @@ withGhc' libDir needHieFiles flags ghcActs = runGhc (Just libDir) $ do unsetPatternMatchWarnings :: DynFlags -> DynFlags unsetPatternMatchWarnings dflags = - foldl' wopt_unset dflags pattern_match_warnings + List.foldl' wopt_unset dflags pattern_match_warnings where pattern_match_warnings = [ Opt_WarnIncompletePatterns ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs ===================================== @@ -50,9 +50,10 @@ import Control.DeepSeq (force) import Control.Monad (unless, when) import Data.Bifunctor (bimap) import qualified Data.ByteString.Builder as Builder +import qualified Data.List as List import Data.Char (isSpace, toUpper) import Data.Either (partitionEithers) -import Data.Foldable (foldl', traverse_) +import Data.Foldable (traverse_) import Data.List (intersperse, isPrefixOf, sortBy) import Data.Map.Strict (Map) import qualified Data.Map.Strict as Map @@ -305,12 +306,15 @@ bodyHtml body << [ divPackageHeader << [ nonEmptySectionName << doctitle - , unordList (catMaybes [ - srcButton maybe_source_url iface, - wikiButton maybe_wiki_url (ifaceMod <$> iface), - contentsButton maybe_contents_url, - indexButton maybe_index_url]) - ! [theclass "links", identifier "page-menu"] + , unordList + ( catMaybes + [ srcButton maybe_source_url iface + , wikiButton maybe_wiki_url (ifaceMod <$> iface) + , contentsButton maybe_contents_url + , indexButton maybe_index_url + ] + ) + ! [theclass "links", identifier "page-menu"] ] , divContent << pageContent , divFooter @@ -777,7 +781,7 @@ ppHtmlIndex -- that export that entity. Each of the modules exports the entity -- in a visible or invisible way (hence the Bool). full_index :: Map String (Map GHC.Name [(Module, Bool)]) - full_index = foldl' f Map.empty ifaces + full_index = List.foldl' f Map.empty ifaces where f :: Map String (Map Name [(Module, Bool)]) @@ -791,7 +795,7 @@ ppHtmlIndex getIfaceIndex :: InstalledInterface -> Map String (Map Name [(Module, Bool)]) getIfaceIndex iface = - foldl' f Map.empty (instExports iface) + List.foldl' f Map.empty (instExports iface) where f :: Map String (Map Name [(Module, Bool)]) ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs ===================================== @@ -54,6 +54,8 @@ module Haddock.Backends.Xhtml.Layout import qualified Data.Map as Map import Data.Maybe (fromMaybe) +import GHC hiding (anchor) +import GHC.Types.Name (nameOccName) import Haddock.Backends.Xhtml.DocMarkup import Haddock.Backends.Xhtml.Types import Haddock.Backends.Xhtml.Utils @@ -61,9 +63,6 @@ import Haddock.Types import Haddock.Utils (makeAnchorId, nameAnchorId) import Text.XHtml hiding (name, quote, title) -import GHC hiding (anchor) -import GHC.Types.Name (nameOccName) - -------------------------------------------------------------------------------- -- * Sections of the document ===================================== utils/haddock/haddock-api/src/Haddock/GhcUtils.hs ===================================== @@ -31,10 +31,11 @@ module Haddock.GhcUtils where import Control.Arrow import Data.Char (isSpace) -import Data.Foldable (foldl', toList) +import Data.Foldable (toList) import Data.List.NonEmpty (NonEmpty) import Data.Maybe (fromMaybe, mapMaybe) import qualified Data.Set as Set +import qualified Data.List as List import Haddock.Types (DocName, DocNameI, XRecCond) @@ -771,7 +772,7 @@ typeNames ty = go ty Set.empty TyVarTy{} -> acc AppTy t1 t2 -> go t2 $ go t1 acc FunTy _ _ t1 t2 -> go t2 $ go t1 acc - TyConApp tcon args -> foldl' (\s t' -> go t' s) (Set.insert (getName tcon) acc) args + TyConApp tcon args -> List.foldl' (\s t' -> go t' s) (Set.insert (getName tcon) acc) args ForAllTy bndr t' -> go t' $ go (tyVarKind (binderVar bndr)) acc LitTy _ -> acc CastTy t' _ -> go t' acc ===================================== utils/haddock/haddock-api/src/Haddock/Interface.hs ===================================== @@ -1,8 +1,6 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE BangPatterns #-} -{-# LANGUAGE NamedFieldPuns #-} -{-# LANGUAGE TupleSections #-} ----------------------------------------------------------------------------- -- | -- Module : Haddock.Interface @@ -47,7 +45,7 @@ import Haddock.Types import Haddock.Utils (Verbosity (..), normal, out, verbose) import Control.Monad -import Data.List (foldl', isPrefixOf) +import Data.List (isPrefixOf) import Data.Traversable (for) import qualified Data.Map.Strict as Map import qualified Data.Set as Set @@ -71,11 +69,11 @@ import GHC.Types.Name.Occurrence (emptyOccEnv) import GHC.Unit.Module.Graph (ModuleGraphNode (..)) import GHC.Unit.Module.ModDetails import GHC.Unit.Module.ModSummary (isBootSummary) -import GHC.Utils.Outputable ((<+>), pprModuleName) +import GHC.Utils.Outputable (Outputable, (<+>), pprModuleName) import GHC.Utils.Error (withTiming) import GHC.Unit.Home.ModInfo import GHC.Tc.Utils.Env (lookupGlobal_maybe) -import GHC.Utils.Outputable (Outputable) +import qualified Data.List as List #if defined(mingw32_HOST_OS) import System.IO @@ -327,15 +325,15 @@ processModule verbosity modSummary flags ifaceMap instIfaceMap = do -- The interfaces are passed in in topologically sorted order, but we start -- by reversing the list so we can do a foldl. buildHomeLinks :: [Interface] -> LinkEnv -buildHomeLinks ifaces = foldl' upd Map.empty (reverse ifaces) +buildHomeLinks ifaces = List.foldl' upd Map.empty (reverse ifaces) where upd old_env iface | OptHide `elem` ifaceOptions iface = old_env | OptNotHome `elem` ifaceOptions iface = - foldl' keep_old old_env exported_names + List.foldl' keep_old old_env exported_names | otherwise = - foldl' keep_new old_env exported_names + List.foldl' keep_new old_env exported_names where exported_names = ifaceVisibleExports iface ++ map getName (ifaceInstances iface) mdl = ifaceMod iface ===================================== utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs ===================================== @@ -1,8 +1,5 @@ {-# LANGUAGE BangPatterns #-} -{-# LANGUAGE LambdaCase #-} -{-# LANGUAGE MagicHash #-} {-# LANGUAGE NamedFieldPuns #-} -{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -Wno-incomplete-record-updates #-} @@ -31,13 +28,13 @@ import Haddock.Types import Control.Applicative ((<|>)) import Control.Arrow hiding ((<+>)) import Control.DeepSeq (force) -import Data.Foldable (foldl', toList) -import Data.List (sortBy) +import Data.Foldable (toList) import qualified Data.Map.Strict as Map import Data.Maybe (fromMaybe, mapMaybe, maybeToList) import Data.Ord (comparing) import qualified Data.Sequence as Seq import qualified Data.Set as Set +import qualified Data.List as List import GHC import GHC.Builtin.Types (unrestrictedFunTyConName) @@ -168,7 +165,7 @@ attachOrphanInstances attachOrphanInstances expInfo getInstDoc cls_instances fam_index = [ (synifyInstHead i famInsts, getInstDoc n, (L (getSrcSpan n) n), nameModule_maybe n) | let is = [(instanceSig i, getName i) | i <- cls_instances, isOrphan (is_orphan i)] - , (i@(_, _, cls, tys), n) <- sortBy (comparing $ first instHead) is + , (i@(_, _, cls, tys), n) <- List.sortBy (comparing $ first instHead) is , not $ isInstanceHidden expInfo (getName cls) tys , let famInsts = getFamInsts expInfo fam_index getInstDoc cls tys ] @@ -205,7 +202,7 @@ attachToExportItem cls_index fam_index index expInfo getInstDoc getFixity export , spanNameE n synFamInst (L (locA eSpan) (tcdName d)) , mb_mdl ) - | i <- sortBy (comparing instFam) fam_instances + | i <- List.sortBy (comparing instFam) fam_instances , let n = getName i , not $ isNameHidden expInfo (fi_fam i) , not $ any (isTypeHidden expInfo) (fi_tys i) @@ -220,7 +217,7 @@ attachToExportItem cls_index fam_index index expInfo getInstDoc getFixity export , mb_mdl ) | let is = [(instanceSig i, getName i) | i <- cls_instances] - , (i@(_, _, cls, tys), n) <- sortBy (comparing $ first instHead) is + , (i@(_, _, cls, tys), n) <- List.sortBy (comparing $ first instHead) is , not $ isInstanceHidden expInfo (getName cls) tys , let synClsInst = synifyInstHead i famInsts famInsts = getFamInsts expInfo fam_index getInstDoc cls tys @@ -251,7 +248,7 @@ attachToExportItem cls_index fam_index index expInfo getInstDoc getFixity export } where fixities :: [(Name, Fixity)] - !fixities = force . Map.toList $ foldl' f Map.empty all_names + !fixities = force . Map.toList $ List.foldl' f Map.empty all_names f :: Map.Map Name Fixity -> Name -> Map.Map Name Fixity f !fs n = Map.alter (<|> getFixity n) n fs ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Create.hs ===================================== @@ -2,17 +2,13 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedRecordDot #-} -{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE ViewPatterns #-} {-# OPTIONS_GHC -Wwarn #-} ----------------------------------------------------------------------------- ===================================== utils/haddock/haddock-api/src/Haddock/Options.hs ===================================== @@ -563,10 +563,12 @@ readIfaceArgs flags = [parseIfaceOption s | Flag_ReadInterface s <- flags] (src, ',' : rest') -> let src' = case src of "" -> Nothing - _ -> Just src - docPaths = DocPaths { docPathsHtml = fpath - , docPathsSources = src' - } + _ -> Just src + docPaths = + DocPaths + { docPathsHtml = fpath + , docPathsSources = src' + } in case break (== ',') rest' of (visibility, ',' : file) | visibility == "hidden" -> ===================================== utils/haddock/haddock-api/src/Haddock/Types.hs ===================================== @@ -1,4 +1,3 @@ -{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DeriveDataTypeable #-} @@ -78,9 +77,12 @@ type SubMap = Map Name [Name] type DeclMap = Map Name DeclMapEntry type InstMap = Map RealSrcSpan Name type FixMap = Map Name Fixity -data DocPaths = DocPaths { docPathsHtml :: FilePath -- ^ path to HTML Haddocks - , docPathsSources :: Maybe FilePath -- ^ path to hyperlinked sources - } +data DocPaths = DocPaths + { docPathsHtml :: FilePath + -- ^ path to HTML Haddocks + , docPathsSources :: Maybe FilePath + -- ^ path to hyperlinked sources + } type WarningMap = Map Name (Doc Name) ----------------------------------------------------------------------------- ===================================== utils/haddock/haddock-library/fixtures/Fixtures.hs ===================================== @@ -8,7 +8,7 @@ import Control.Applicative ((<|>)) import Control.Exception (IOException, catch) import Control.Monad (when) import Data.Foldable (traverse_) -import Data.List (foldl') +import qualified Data.List as List import Data.Traversable (for) import GHC.Generics (Generic) import System.Directory (getDirectoryContents) @@ -86,7 +86,7 @@ runFixtures fixtures = do input <- readFile i return (parseString input) ediffGolden goldenFixture name o readDoc - case foldl' combineResults (Result 0 0) results of + case List.foldl' combineResults (Result 0 0) results of Result s t -> do putStrLn $ "Fixtures: success " ++ show s ++ "; total " ++ show t when (s /= t) exitFailure ===================================== utils/haddock/haddock-library/haddock-library.cabal ===================================== @@ -29,8 +29,21 @@ source-repository head location: https://gitlab.haskell.org/ghc/ghc.git subdir: utils/haddock/haddock-library -common lib-defaults - default-language: Haskell2010 +common extensions + default-extensions: + NoStarIsType + StrictData + + default-language: Haskell2010 + +common ghc-options + ghc-options: + -Wall -Wcompat -Widentities -Wincomplete-record-updates + -Wincomplete-uni-patterns -Wredundant-constraints + -fhide-source-paths -Wno-unused-do-bind -fshow-hole-constraints + -Wno-unticked-promoted-constructors -Werror=unused-imports + -fdicts-strict -Wunused-packages -funbox-strict-fields + -Wnoncanonical-monad-instances -Wmissing-home-modules build-depends: , base >= 4.10 && < 4.21 @@ -38,13 +51,9 @@ common lib-defaults , text ^>= 1.2.3.0 || ^>= 2.0 || ^>= 2.1 , parsec ^>= 3.1.13.0 - ghc-options: -funbox-strict-fields - -Wall - -Wcompat - -Wnoncanonical-monad-instances - library - import: lib-defaults + import: extensions + import: ghc-options hs-source-dirs: src @@ -60,7 +69,8 @@ library Documentation.Haddock.Parser.Identifier test-suite spec - import: lib-defaults + import: extensions + import: ghc-options type: exitcode-stdio-1.0 main-is: Spec.hs hs-source-dirs: @@ -94,10 +104,10 @@ test-suite spec , hspec-discover:hspec-discover >= 2.4.4 && < 2.12 test-suite fixtures + import: extensions + import: ghc-options type: exitcode-stdio-1.0 - default-language: Haskell2010 main-is: Fixtures.hs - ghc-options: -Wall hs-source-dirs: fixtures build-depends: -- intra-package dependency ===================================== utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs ===================================== @@ -28,7 +28,7 @@ import Control.Applicative import Control.Arrow (first) import Control.Monad import Data.Char (chr, isAlpha, isSpace, isUpper) -import Data.List (elemIndex, intercalate, unfoldr, intersperse) +import Data.List (elemIndex, intercalate, intersperse, unfoldr) import Data.Maybe (fromMaybe, mapMaybe) import Data.Monoid import qualified Data.Set as Set ===================================== utils/haddock/haddock-library/src/Documentation/Haddock/Parser/Monad.hs ===================================== @@ -34,7 +34,7 @@ import Control.Applicative as App import Control.Monad (mfilter) import Data.Bits (Bits (..)) import Data.Char (ord) -import Data.List (foldl') +import qualified Data.List as List import Data.String (IsString (..)) import Documentation.Haddock.Types (MetaSince (..)) @@ -146,13 +146,13 @@ scan f st = do -- | Parse a decimal number. decimal :: Integral a => Parser a -decimal = foldl' step 0 `fmap` Parsec.many1 Parsec.digit +decimal = List.foldl' step 0 `fmap` Parsec.many1 Parsec.digit where step a c = a * 10 + fromIntegral (ord c - 48) -- | Parse a hexadecimal number. hexadecimal :: (Integral a, Bits a) => Parser a -hexadecimal = foldl' step 0 `fmap` Parsec.many1 Parsec.hexDigit +hexadecimal = List.foldl' step 0 `fmap` Parsec.many1 Parsec.hexDigit where step a c | w >= 48 && w <= 57 = (a `shiftL` 4) .|. fromIntegral (w - 48) ===================================== utils/haddock/haddock.cabal ===================================== @@ -69,11 +69,28 @@ source-repository head location: https://gitlab.haskell.org/ghc/ghc.git subdir: utils/haddock +common extensions + default-extensions: + NoStarIsType + OverloadedRecordDot + StrictData + + default-language: Haskell2010 + +common ghc-options + ghc-options: + -Wall -Wcompat -Widentities -Wincomplete-record-updates + -Wincomplete-uni-patterns -Wredundant-constraints + -fhide-source-paths -Wno-unused-do-bind -fshow-hole-constraints + -Wno-unticked-promoted-constructors -Werror=unused-imports + -fdicts-strict -Wunused-packages -funbox-strict-fields + -Wnoncanonical-monad-instances -Wmissing-home-modules + executable haddock - default-language: Haskell2010 + import: extensions + import: ghc-options main-is: Main.hs hs-source-dirs: driver - ghc-options: -funbox-strict-fields -Wall -Wincomplete-uni-patterns -Wincomplete-record-updates -O2 if flag(threaded) ghc-options: -threaded @@ -93,7 +110,6 @@ executable haddock array, xhtml >= 3000.2 && < 3000.3, ghc-boot, - ghc-boot-th, ghc == 9.11.*, bytestring, parsec, @@ -162,38 +178,41 @@ executable haddock build-depends: haddock-api == 2.30.0 test-suite html-test + import: extensions + import: ghc-options type: exitcode-stdio-1.0 -- This tells cabal that this test depends on the executable -- component 'haddock' from this very same package, as well -- as adding the build-folder where the `haddock` -- executable can be found in front of $PATH build-tool-depends: haddock:haddock - default-language: Haskell2010 main-is: Main.hs hs-source-dirs: html-test build-depends: base, filepath, haddock-test == 0.0.1 test-suite hypsrc-test + import: extensions + import: ghc-options type: exitcode-stdio-1.0 build-tool-depends: haddock:haddock - default-language: Haskell2010 main-is: Main.hs hs-source-dirs: hypsrc-test build-depends: base, filepath, haddock-test == 0.0.1 - ghc-options: -Wall -fwarn-tabs test-suite latex-test + import: extensions + import: ghc-options type: exitcode-stdio-1.0 build-tool-depends: haddock:haddock - default-language: Haskell2010 main-is: Main.hs hs-source-dirs: latex-test build-depends: base, filepath, haddock-test == 0.0.1 test-suite hoogle-test + import: extensions + import: ghc-options type: exitcode-stdio-1.0 build-tool-depends: haddock:haddock - default-language: Haskell2010 main-is: Main.hs hs-source-dirs: hoogle-test build-depends: base, filepath, haddock-test == 0.0.1 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d6e5be07f5a6da39d4b749fd51c479fb4dbde176...7392a0120b1d38e022108eb47e55f19f2d4e1ad3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d6e5be07f5a6da39d4b749fd51c479fb4dbde176...7392a0120b1d38e022108eb47e55f19f2d4e1ad3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 23:29:07 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 20 Jun 2024 19:29:07 -0400 Subject: [Git][ghc/ghc][master] haddock: Remove unused pragmata, qualify usages of Data.List functions, add... Message-ID: <6674bb4350f23_43ba429f240814817@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: c872e09b by Hécate Kleidukos at 2024-06-20T19:28:36-04:00 haddock: Remove unused pragmata, qualify usages of Data.List functions, add more sanity checking flags by default This commit enables some extensions and GHC flags in the cabal file in a way that allows us to reduce the amount of prologuing on top of each file. We also prefix the usage of some List functions that removes ambiguity when they are also exported from the Prelude, like foldl'. In general, this has the effect of pointing out more explicitly that a linked list is used. Metric Increase: haddock.Cabal haddock.base haddock.compiler - - - - - 15 changed files: - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/src/Haddock.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface.hs - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Options.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/haddock-library/fixtures/Fixtures.hs - utils/haddock/haddock-library/haddock-library.cabal - utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs - utils/haddock/haddock-library/src/Documentation/Haddock/Parser/Monad.hs - utils/haddock/haddock.cabal Changes: ===================================== utils/haddock/haddock-api/haddock-api.cabal ===================================== @@ -43,8 +43,29 @@ source-repository head location: https://gitlab.haskell.org/ghc/ghc.git subdir: utils/haddock/haddock-api +common extensions + default-extensions: + LambdaCase + NoStarIsType + OverloadedRecordDot + StrictData + TypeApplications + TypeOperators + + default-language: Haskell2010 + +common ghc-options + ghc-options: + -Wall -Wcompat -Widentities -Wincomplete-record-updates + -Wincomplete-uni-patterns -Wredundant-constraints + -fhide-source-paths -Wno-unused-do-bind -fshow-hole-constraints + -Wno-unticked-promoted-constructors -Werror=unused-imports + -fdicts-strict -Wunused-packages -funbox-strict-fields + -Wnoncanonical-monad-instances -Wmissing-home-modules + library - default-language: Haskell2010 + import: extensions + import: ghc-options -- this package typically supports only single major versions build-depends: base >= 4.16 && < 4.21 @@ -69,19 +90,6 @@ library , transformers hs-source-dirs: src - - ghc-options: -funbox-strict-fields -O2 - -Wall - -Wcompat - -Wcompat-unqualified-imports - -Widentities - -Wredundant-constraints - -Wnoncanonical-monad-instances - -Wmissing-home-modules - -Wincomplete-uni-patterns - -Wincomplete-record-updates - - exposed-modules: Documentation.Haddock @@ -131,10 +139,10 @@ library Paths_haddock_api test-suite spec + import: extensions + import: ghc-options type: exitcode-stdio-1.0 - default-language: Haskell2010 main-is: Spec.hs - ghc-options: -Wall hs-source-dirs: test @@ -201,7 +209,6 @@ test-suite spec , exceptions , filepath , ghc-boot - , ghc-boot-th , mtl , transformers ===================================== utils/haddock/haddock-api/src/Haddock.hs ===================================== @@ -5,7 +5,6 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE Rank2Types #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# OPTIONS_GHC -Wwarn #-} ----------------------------------------------------------------------------- -- | -- Module : Haddock @@ -50,9 +49,9 @@ import Control.DeepSeq (force) import Control.Monad hiding (forM_) import Control.Monad.IO.Class (MonadIO(..)) import Data.Bifunctor (second) -import Data.Foldable (forM_, foldl') +import Data.Foldable (forM_) import Data.Traversable (for) -import Data.List (find, isPrefixOf, nub) +import qualified Data.List as List import Control.Exception import Data.Maybe import Data.IORef @@ -256,7 +255,7 @@ withTempOutputDir action = do -- | Create warnings about potential misuse of -optghc optGhcWarnings :: [String] -> [String] -optGhcWarnings = map format . filter (isPrefixOf "-optghc") +optGhcWarnings = map format . filter (List.isPrefixOf "-optghc") where format arg = concat ["Warning: `", arg, "' means `-o ", drop 2 arg, "', did you mean `-", arg, "'?"] @@ -449,7 +448,7 @@ render log' dflags unit_state flags sinceQual qual ifaces packages extSrcMap = d let withQuickjump = Flag_QuickJumpIndex `elem` flags withBaseURL = isJust - . find (\flag -> case flag of + . List.find (\flag -> case flag of Flag_BaseURL base_url -> base_url /= "." && base_url /= "./" _ -> False @@ -481,7 +480,7 @@ render log' dflags unit_state flags sinceQual qual ifaces packages extSrcMap = d ppJsonIndex odir sourceUrls' opt_wiki_urls unicode Nothing qual ifaces - ( nub + ( List.nub . map fst . filter ((== Visible) . piVisibility . snd) $ packages) @@ -612,7 +611,7 @@ withGhc' libDir needHieFiles flags ghcActs = runGhc (Just libDir) $ do ++ if needHieFiles then [Opt_WriteHie] -- Generate .hie-files else [] - dynflags' = (foldl' gopt_set dynflags extra_opts) + dynflags' = (List.foldl' gopt_set dynflags extra_opts) { backend = noBackend , ghcMode = CompManager , ghcLink = NoLink @@ -626,7 +625,7 @@ withGhc' libDir needHieFiles flags ghcActs = runGhc (Just libDir) $ do unsetPatternMatchWarnings :: DynFlags -> DynFlags unsetPatternMatchWarnings dflags = - foldl' wopt_unset dflags pattern_match_warnings + List.foldl' wopt_unset dflags pattern_match_warnings where pattern_match_warnings = [ Opt_WarnIncompletePatterns ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs ===================================== @@ -50,9 +50,10 @@ import Control.DeepSeq (force) import Control.Monad (unless, when) import Data.Bifunctor (bimap) import qualified Data.ByteString.Builder as Builder +import qualified Data.List as List import Data.Char (isSpace, toUpper) import Data.Either (partitionEithers) -import Data.Foldable (foldl', traverse_) +import Data.Foldable (traverse_) import Data.List (intersperse, isPrefixOf, sortBy) import Data.Map.Strict (Map) import qualified Data.Map.Strict as Map @@ -305,12 +306,15 @@ bodyHtml body << [ divPackageHeader << [ nonEmptySectionName << doctitle - , unordList (catMaybes [ - srcButton maybe_source_url iface, - wikiButton maybe_wiki_url (ifaceMod <$> iface), - contentsButton maybe_contents_url, - indexButton maybe_index_url]) - ! [theclass "links", identifier "page-menu"] + , unordList + ( catMaybes + [ srcButton maybe_source_url iface + , wikiButton maybe_wiki_url (ifaceMod <$> iface) + , contentsButton maybe_contents_url + , indexButton maybe_index_url + ] + ) + ! [theclass "links", identifier "page-menu"] ] , divContent << pageContent , divFooter @@ -777,7 +781,7 @@ ppHtmlIndex -- that export that entity. Each of the modules exports the entity -- in a visible or invisible way (hence the Bool). full_index :: Map String (Map GHC.Name [(Module, Bool)]) - full_index = foldl' f Map.empty ifaces + full_index = List.foldl' f Map.empty ifaces where f :: Map String (Map Name [(Module, Bool)]) @@ -791,7 +795,7 @@ ppHtmlIndex getIfaceIndex :: InstalledInterface -> Map String (Map Name [(Module, Bool)]) getIfaceIndex iface = - foldl' f Map.empty (instExports iface) + List.foldl' f Map.empty (instExports iface) where f :: Map String (Map Name [(Module, Bool)]) ===================================== utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs ===================================== @@ -54,6 +54,8 @@ module Haddock.Backends.Xhtml.Layout import qualified Data.Map as Map import Data.Maybe (fromMaybe) +import GHC hiding (anchor) +import GHC.Types.Name (nameOccName) import Haddock.Backends.Xhtml.DocMarkup import Haddock.Backends.Xhtml.Types import Haddock.Backends.Xhtml.Utils @@ -61,9 +63,6 @@ import Haddock.Types import Haddock.Utils (makeAnchorId, nameAnchorId) import Text.XHtml hiding (name, quote, title) -import GHC hiding (anchor) -import GHC.Types.Name (nameOccName) - -------------------------------------------------------------------------------- -- * Sections of the document ===================================== utils/haddock/haddock-api/src/Haddock/GhcUtils.hs ===================================== @@ -31,10 +31,11 @@ module Haddock.GhcUtils where import Control.Arrow import Data.Char (isSpace) -import Data.Foldable (foldl', toList) +import Data.Foldable (toList) import Data.List.NonEmpty (NonEmpty) import Data.Maybe (fromMaybe, mapMaybe) import qualified Data.Set as Set +import qualified Data.List as List import Haddock.Types (DocName, DocNameI, XRecCond) @@ -771,7 +772,7 @@ typeNames ty = go ty Set.empty TyVarTy{} -> acc AppTy t1 t2 -> go t2 $ go t1 acc FunTy _ _ t1 t2 -> go t2 $ go t1 acc - TyConApp tcon args -> foldl' (\s t' -> go t' s) (Set.insert (getName tcon) acc) args + TyConApp tcon args -> List.foldl' (\s t' -> go t' s) (Set.insert (getName tcon) acc) args ForAllTy bndr t' -> go t' $ go (tyVarKind (binderVar bndr)) acc LitTy _ -> acc CastTy t' _ -> go t' acc ===================================== utils/haddock/haddock-api/src/Haddock/Interface.hs ===================================== @@ -1,8 +1,6 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE BangPatterns #-} -{-# LANGUAGE NamedFieldPuns #-} -{-# LANGUAGE TupleSections #-} ----------------------------------------------------------------------------- -- | -- Module : Haddock.Interface @@ -47,7 +45,7 @@ import Haddock.Types import Haddock.Utils (Verbosity (..), normal, out, verbose) import Control.Monad -import Data.List (foldl', isPrefixOf) +import Data.List (isPrefixOf) import Data.Traversable (for) import qualified Data.Map.Strict as Map import qualified Data.Set as Set @@ -71,11 +69,11 @@ import GHC.Types.Name.Occurrence (emptyOccEnv) import GHC.Unit.Module.Graph (ModuleGraphNode (..)) import GHC.Unit.Module.ModDetails import GHC.Unit.Module.ModSummary (isBootSummary) -import GHC.Utils.Outputable ((<+>), pprModuleName) +import GHC.Utils.Outputable (Outputable, (<+>), pprModuleName) import GHC.Utils.Error (withTiming) import GHC.Unit.Home.ModInfo import GHC.Tc.Utils.Env (lookupGlobal_maybe) -import GHC.Utils.Outputable (Outputable) +import qualified Data.List as List #if defined(mingw32_HOST_OS) import System.IO @@ -327,15 +325,15 @@ processModule verbosity modSummary flags ifaceMap instIfaceMap = do -- The interfaces are passed in in topologically sorted order, but we start -- by reversing the list so we can do a foldl. buildHomeLinks :: [Interface] -> LinkEnv -buildHomeLinks ifaces = foldl' upd Map.empty (reverse ifaces) +buildHomeLinks ifaces = List.foldl' upd Map.empty (reverse ifaces) where upd old_env iface | OptHide `elem` ifaceOptions iface = old_env | OptNotHome `elem` ifaceOptions iface = - foldl' keep_old old_env exported_names + List.foldl' keep_old old_env exported_names | otherwise = - foldl' keep_new old_env exported_names + List.foldl' keep_new old_env exported_names where exported_names = ifaceVisibleExports iface ++ map getName (ifaceInstances iface) mdl = ifaceMod iface ===================================== utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs ===================================== @@ -1,8 +1,5 @@ {-# LANGUAGE BangPatterns #-} -{-# LANGUAGE LambdaCase #-} -{-# LANGUAGE MagicHash #-} {-# LANGUAGE NamedFieldPuns #-} -{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -Wno-incomplete-record-updates #-} @@ -31,13 +28,13 @@ import Haddock.Types import Control.Applicative ((<|>)) import Control.Arrow hiding ((<+>)) import Control.DeepSeq (force) -import Data.Foldable (foldl', toList) -import Data.List (sortBy) +import Data.Foldable (toList) import qualified Data.Map.Strict as Map import Data.Maybe (fromMaybe, mapMaybe, maybeToList) import Data.Ord (comparing) import qualified Data.Sequence as Seq import qualified Data.Set as Set +import qualified Data.List as List import GHC import GHC.Builtin.Types (unrestrictedFunTyConName) @@ -168,7 +165,7 @@ attachOrphanInstances attachOrphanInstances expInfo getInstDoc cls_instances fam_index = [ (synifyInstHead i famInsts, getInstDoc n, (L (getSrcSpan n) n), nameModule_maybe n) | let is = [(instanceSig i, getName i) | i <- cls_instances, isOrphan (is_orphan i)] - , (i@(_, _, cls, tys), n) <- sortBy (comparing $ first instHead) is + , (i@(_, _, cls, tys), n) <- List.sortBy (comparing $ first instHead) is , not $ isInstanceHidden expInfo (getName cls) tys , let famInsts = getFamInsts expInfo fam_index getInstDoc cls tys ] @@ -205,7 +202,7 @@ attachToExportItem cls_index fam_index index expInfo getInstDoc getFixity export , spanNameE n synFamInst (L (locA eSpan) (tcdName d)) , mb_mdl ) - | i <- sortBy (comparing instFam) fam_instances + | i <- List.sortBy (comparing instFam) fam_instances , let n = getName i , not $ isNameHidden expInfo (fi_fam i) , not $ any (isTypeHidden expInfo) (fi_tys i) @@ -220,7 +217,7 @@ attachToExportItem cls_index fam_index index expInfo getInstDoc getFixity export , mb_mdl ) | let is = [(instanceSig i, getName i) | i <- cls_instances] - , (i@(_, _, cls, tys), n) <- sortBy (comparing $ first instHead) is + , (i@(_, _, cls, tys), n) <- List.sortBy (comparing $ first instHead) is , not $ isInstanceHidden expInfo (getName cls) tys , let synClsInst = synifyInstHead i famInsts famInsts = getFamInsts expInfo fam_index getInstDoc cls tys @@ -251,7 +248,7 @@ attachToExportItem cls_index fam_index index expInfo getInstDoc getFixity export } where fixities :: [(Name, Fixity)] - !fixities = force . Map.toList $ foldl' f Map.empty all_names + !fixities = force . Map.toList $ List.foldl' f Map.empty all_names f :: Map.Map Name Fixity -> Name -> Map.Map Name Fixity f !fs n = Map.alter (<|> getFixity n) n fs ===================================== utils/haddock/haddock-api/src/Haddock/Interface/Create.hs ===================================== @@ -2,17 +2,13 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE FlexibleInstances #-} -{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE OverloadedRecordDot #-} -{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE ScopedTypeVariables #-} -{-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE ViewPatterns #-} {-# OPTIONS_GHC -Wwarn #-} ----------------------------------------------------------------------------- ===================================== utils/haddock/haddock-api/src/Haddock/Options.hs ===================================== @@ -563,10 +563,12 @@ readIfaceArgs flags = [parseIfaceOption s | Flag_ReadInterface s <- flags] (src, ',' : rest') -> let src' = case src of "" -> Nothing - _ -> Just src - docPaths = DocPaths { docPathsHtml = fpath - , docPathsSources = src' - } + _ -> Just src + docPaths = + DocPaths + { docPathsHtml = fpath + , docPathsSources = src' + } in case break (== ',') rest' of (visibility, ',' : file) | visibility == "hidden" -> ===================================== utils/haddock/haddock-api/src/Haddock/Types.hs ===================================== @@ -1,4 +1,3 @@ -{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DeriveDataTypeable #-} @@ -78,9 +77,12 @@ type SubMap = Map Name [Name] type DeclMap = Map Name DeclMapEntry type InstMap = Map RealSrcSpan Name type FixMap = Map Name Fixity -data DocPaths = DocPaths { docPathsHtml :: FilePath -- ^ path to HTML Haddocks - , docPathsSources :: Maybe FilePath -- ^ path to hyperlinked sources - } +data DocPaths = DocPaths + { docPathsHtml :: FilePath + -- ^ path to HTML Haddocks + , docPathsSources :: Maybe FilePath + -- ^ path to hyperlinked sources + } type WarningMap = Map Name (Doc Name) ----------------------------------------------------------------------------- ===================================== utils/haddock/haddock-library/fixtures/Fixtures.hs ===================================== @@ -8,7 +8,7 @@ import Control.Applicative ((<|>)) import Control.Exception (IOException, catch) import Control.Monad (when) import Data.Foldable (traverse_) -import Data.List (foldl') +import qualified Data.List as List import Data.Traversable (for) import GHC.Generics (Generic) import System.Directory (getDirectoryContents) @@ -86,7 +86,7 @@ runFixtures fixtures = do input <- readFile i return (parseString input) ediffGolden goldenFixture name o readDoc - case foldl' combineResults (Result 0 0) results of + case List.foldl' combineResults (Result 0 0) results of Result s t -> do putStrLn $ "Fixtures: success " ++ show s ++ "; total " ++ show t when (s /= t) exitFailure ===================================== utils/haddock/haddock-library/haddock-library.cabal ===================================== @@ -29,8 +29,21 @@ source-repository head location: https://gitlab.haskell.org/ghc/ghc.git subdir: utils/haddock/haddock-library -common lib-defaults - default-language: Haskell2010 +common extensions + default-extensions: + NoStarIsType + StrictData + + default-language: Haskell2010 + +common ghc-options + ghc-options: + -Wall -Wcompat -Widentities -Wincomplete-record-updates + -Wincomplete-uni-patterns -Wredundant-constraints + -fhide-source-paths -Wno-unused-do-bind -fshow-hole-constraints + -Wno-unticked-promoted-constructors -Werror=unused-imports + -fdicts-strict -Wunused-packages -funbox-strict-fields + -Wnoncanonical-monad-instances -Wmissing-home-modules build-depends: , base >= 4.10 && < 4.21 @@ -38,13 +51,9 @@ common lib-defaults , text ^>= 1.2.3.0 || ^>= 2.0 || ^>= 2.1 , parsec ^>= 3.1.13.0 - ghc-options: -funbox-strict-fields - -Wall - -Wcompat - -Wnoncanonical-monad-instances - library - import: lib-defaults + import: extensions + import: ghc-options hs-source-dirs: src @@ -60,7 +69,8 @@ library Documentation.Haddock.Parser.Identifier test-suite spec - import: lib-defaults + import: extensions + import: ghc-options type: exitcode-stdio-1.0 main-is: Spec.hs hs-source-dirs: @@ -94,10 +104,10 @@ test-suite spec , hspec-discover:hspec-discover >= 2.4.4 && < 2.12 test-suite fixtures + import: extensions + import: ghc-options type: exitcode-stdio-1.0 - default-language: Haskell2010 main-is: Fixtures.hs - ghc-options: -Wall hs-source-dirs: fixtures build-depends: -- intra-package dependency ===================================== utils/haddock/haddock-library/src/Documentation/Haddock/Parser.hs ===================================== @@ -28,7 +28,7 @@ import Control.Applicative import Control.Arrow (first) import Control.Monad import Data.Char (chr, isAlpha, isSpace, isUpper) -import Data.List (elemIndex, intercalate, unfoldr, intersperse) +import Data.List (elemIndex, intercalate, intersperse, unfoldr) import Data.Maybe (fromMaybe, mapMaybe) import Data.Monoid import qualified Data.Set as Set ===================================== utils/haddock/haddock-library/src/Documentation/Haddock/Parser/Monad.hs ===================================== @@ -34,7 +34,7 @@ import Control.Applicative as App import Control.Monad (mfilter) import Data.Bits (Bits (..)) import Data.Char (ord) -import Data.List (foldl') +import qualified Data.List as List import Data.String (IsString (..)) import Documentation.Haddock.Types (MetaSince (..)) @@ -146,13 +146,13 @@ scan f st = do -- | Parse a decimal number. decimal :: Integral a => Parser a -decimal = foldl' step 0 `fmap` Parsec.many1 Parsec.digit +decimal = List.foldl' step 0 `fmap` Parsec.many1 Parsec.digit where step a c = a * 10 + fromIntegral (ord c - 48) -- | Parse a hexadecimal number. hexadecimal :: (Integral a, Bits a) => Parser a -hexadecimal = foldl' step 0 `fmap` Parsec.many1 Parsec.hexDigit +hexadecimal = List.foldl' step 0 `fmap` Parsec.many1 Parsec.hexDigit where step a c | w >= 48 && w <= 57 = (a `shiftL` 4) .|. fromIntegral (w - 48) ===================================== utils/haddock/haddock.cabal ===================================== @@ -69,11 +69,28 @@ source-repository head location: https://gitlab.haskell.org/ghc/ghc.git subdir: utils/haddock +common extensions + default-extensions: + NoStarIsType + OverloadedRecordDot + StrictData + + default-language: Haskell2010 + +common ghc-options + ghc-options: + -Wall -Wcompat -Widentities -Wincomplete-record-updates + -Wincomplete-uni-patterns -Wredundant-constraints + -fhide-source-paths -Wno-unused-do-bind -fshow-hole-constraints + -Wno-unticked-promoted-constructors -Werror=unused-imports + -fdicts-strict -Wunused-packages -funbox-strict-fields + -Wnoncanonical-monad-instances -Wmissing-home-modules + executable haddock - default-language: Haskell2010 + import: extensions + import: ghc-options main-is: Main.hs hs-source-dirs: driver - ghc-options: -funbox-strict-fields -Wall -Wincomplete-uni-patterns -Wincomplete-record-updates -O2 if flag(threaded) ghc-options: -threaded @@ -93,7 +110,6 @@ executable haddock array, xhtml >= 3000.2 && < 3000.3, ghc-boot, - ghc-boot-th, ghc == 9.11.*, bytestring, parsec, @@ -162,38 +178,41 @@ executable haddock build-depends: haddock-api == 2.30.0 test-suite html-test + import: extensions + import: ghc-options type: exitcode-stdio-1.0 -- This tells cabal that this test depends on the executable -- component 'haddock' from this very same package, as well -- as adding the build-folder where the `haddock` -- executable can be found in front of $PATH build-tool-depends: haddock:haddock - default-language: Haskell2010 main-is: Main.hs hs-source-dirs: html-test build-depends: base, filepath, haddock-test == 0.0.1 test-suite hypsrc-test + import: extensions + import: ghc-options type: exitcode-stdio-1.0 build-tool-depends: haddock:haddock - default-language: Haskell2010 main-is: Main.hs hs-source-dirs: hypsrc-test build-depends: base, filepath, haddock-test == 0.0.1 - ghc-options: -Wall -fwarn-tabs test-suite latex-test + import: extensions + import: ghc-options type: exitcode-stdio-1.0 build-tool-depends: haddock:haddock - default-language: Haskell2010 main-is: Main.hs hs-source-dirs: latex-test build-depends: base, filepath, haddock-test == 0.0.1 test-suite hoogle-test + import: extensions + import: ghc-options type: exitcode-stdio-1.0 build-tool-depends: haddock:haddock - default-language: Haskell2010 main-is: Main.hs hs-source-dirs: hoogle-test build-depends: base, filepath, haddock-test == 0.0.1 View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c872e09b41629b442ed7a0c0a52835068fa205a3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/c872e09b41629b442ed7a0c0a52835068fa205a3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Thu Jun 20 23:30:09 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Thu, 20 Jun 2024 19:30:09 -0400 Subject: [Git][ghc/ghc][master] 3 commits: Add test case for #23586 Message-ID: <6674bb816fdab_43ba42b877b415527d@gitlab.mail> Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 8c87d4e1 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00 Add test case for #23586 - - - - - 568de8a5 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00 When matching functions in rewrite rules: ignore multiplicity When matching a template variable to an expression, we check that it has the same type as the matched expression. But if the variable `f` has type `A -> B` while the expression `e` has type `A %1 -> B`, the match was previously rejected. A principled solution would have `f` substituted by `\(%Many x) -> e x` or some other appropriate coercion. But since linearity is not properly checked in Core, we can be cheeky and simply ignore multiplicity while matching. Much easier. This has forced a change in the linter which, when `-dlinear-core-lint` is off, must consider that `a -> b` and `a %1 -> b` are equal. This is achieved by adding an argument to configure the behaviour of `nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour which ignores multiplicities when comparing two `FunTy`. Fixes #24725. - - - - - c8a8727e by Simon Peyton Jones at 2024-06-20T19:29:12-04:00 Faster type equality This MR speeds up type equality, triggered by perf regressions that showed up when fixing #24725 by parameterising type equality over whether to ignore multiplicity. The changes are: * Do not use `nonDetCmpType` for type /equality/. Instead use a specialised type-equality function, which we have always had! `nonDetCmpType` remains, but I did not invest effort in refactoring or optimising it. * Type equality is parameterised by - whether to expand synonyms - whether to respect multiplicities - whether it has a RnEnv2 environment In this MR I systematically specialise it for static values of these parameters. Much more direct and predictable than before. See Note [Specialising type equality] * We want to avoid comparing kinds if possible. I refactored how this happens, at least for `eqType`. See Note [Casts and coercions in type comparison] * To make Lint fast, we want to avoid allocating a thunk for <msg> in ensureEqTypes ty1 ty2 <msg> because the test almost always succeeds, and <msg> isn't needed. See Note [INLINE ensureEqTys] Metric Decrease: T13386 T5030 - - - - - 10 changed files: - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Multiplicity.hs - compiler/GHC/Core/TyCo/Compare.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Utils/TcType.hs - + testsuite/tests/simplCore/should_run/T23586.hs - + testsuite/tests/simplCore/should_run/T23586.stdout - testsuite/tests/simplCore/should_run/all.T Changes: ===================================== compiler/GHC/Core/Lint.hs ===================================== @@ -53,7 +53,7 @@ import GHC.Core.Predicate( isCoVarType ) import GHC.Core.Multiplicity import GHC.Core.UsageEnv import GHC.Core.TyCo.Rep -- checks validity of types/coercions -import GHC.Core.TyCo.Compare ( eqType, eqForAllVis ) +import GHC.Core.TyCo.Compare ( eqType, eqTypes, eqTypeIgnoringMultiplicity, eqForAllVis ) import GHC.Core.TyCo.Subst import GHC.Core.TyCo.FVs import GHC.Core.TyCo.Ppr @@ -2807,7 +2807,7 @@ lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches extra_checks | isNewTyCon tc - = do { CoAxBranch { cab_tvs = tvs + = do { CoAxBranch { cab_tvs = ax_tvs , cab_eta_tvs = eta_tvs , cab_cvs = cvs , cab_roles = roles @@ -2815,14 +2815,10 @@ lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches <- case branch_list of [branch] -> return branch _ -> failWithL (text "multi-branch axiom with newtype") - ; let ax_lhs = mkInfForAllTys tvs $ - mkTyConApp tc lhs_tys - nt_tvs = takeList tvs (tyConTyVars tc) - -- axiom may be eta-reduced: Note [Newtype eta] in GHC.Core.TyCon - nt_lhs = mkInfForAllTys nt_tvs $ - mkTyConApp tc (mkTyVarTys nt_tvs) - -- See Note [Newtype eta] in GHC.Core.TyCon - ; lintL (ax_lhs `eqType` nt_lhs) + + -- The LHS of the axiom is (N lhs_tys) + -- We expect it to be (N ax_tvs) + ; lintL (mkTyVarTys ax_tvs `eqTypes` lhs_tys) (text "Newtype axiom LHS does not match newtype definition") ; lintL (null cvs) (text "Newtype axiom binds coercion variables") @@ -2831,7 +2827,7 @@ lint_axiom ax@(CoAxiom { co_ax_tc = tc, co_ax_branches = branches (text "Newtype axiom has eta-tvs") ; lintL (ax_role == Representational) (text "Newtype axiom role not representational") - ; lintL (roles `equalLength` tvs) + ; lintL (roles `equalLength` ax_tvs) (text "Newtype axiom roles list is the wrong length." $$ text "roles:" <+> sep (map ppr roles)) ; lintL (roles == takeList roles (tyConRoles tc)) @@ -3098,84 +3094,93 @@ we behave as follows (#15057, #T15664): Note [Linting linearity] ~~~~~~~~~~~~~~~~~~~~~~~~ -Core understands linear types: linearity is checked with the flag -`-dlinear-core-lint`. Why not make `-dcore-lint` check linearity? Because -optimisation passes are not (yet) guaranteed to maintain linearity. They should -do so semantically (GHC is careful not to duplicate computation) but it is much -harder to ensure that the statically-checkable constraints of Linear Core are -maintained. The current Linear Core is described in the wiki at: +Lint ignores linearity unless `-dlinear-core-lint` is set. For why, see below. + +But first, "ignore linearity" specifically means two things. When ignoring linearity: +* In `ensureEqTypes`, use `eqTypeIgnoringMultiplicity` +* In `ensureSubMult`, do nothing + +But why make `-dcore-lint` ignore linearity? Because optimisation passes are +not (yet) guaranteed to maintain linearity. They should do so semantically (GHC +is careful not to duplicate computation) but it is much harder to ensure that +the statically-checkable constraints of Linear Core are maintained. The current +Linear Core is described in the wiki at: https://gitlab.haskell.org/ghc/ghc/-/wikis/linear-types/implementation. -Why don't the optimisation passes maintain the static types of Linear Core? -Because doing so would cripple some important optimisations. Here is an -example: +Here are some examples of how the optimiser can break linearity checking. Other +examples are documented in the linear-type implementation wiki page +[https://gitlab.haskell.org/ghc/ghc/-/wikis/linear-types/implementation#core-to-core-passes] - data T = MkT {-# UNPACK #-} !Int +* EXAMPLE 1: the binder swap transformation + Consider -The wrapper for MkT is + data T = MkT {-# UNPACK #-} !Int - $wMkT :: Int %1 -> T - $wMkT n = case %1 n of - I# n' -> MkT n' + The wrapper for MkT is -This introduces, in particular, a `case %1` (this is not actual Haskell or Core -syntax), where the `%1` means that the `case` expression consumes its scrutinee -linearly. + $wMkT :: Int %1 -> T + $wMkT n = case %1 n of + I# n' -> MkT n' -Now, `case %1` interacts with the binder swap optimisation in a non-trivial -way. Take a slightly modified version of the code for $wMkT: + This introduces, in particular, a `case %1` (this is not actual Haskell or + Core syntax), where the `%1` means that the `case` expression consumes its + scrutinee linearly. - case %1 x of z { - I# n' -> (x, n') - } + Now, `case %1` interacts with the binder swap optimisation in a non-trivial + way. Take a slightly modified version of the code for $wMkT: -Binder-swap wants to change this to + case %1 x of z { + I# n' -> (x, n') + } - case %1 x of z { - I# n' -> let x = z in (x, n') - } + Binder-swap changes this to -Now, this is not something that a linear type checker usually considers -well-typed. It is not something that `-dlinear-core-lint` considers to be -well-typed either. But it's only because `-dlinear-core-lint` is not good -enough. However, making `-dlinear-core-lint` recognise this expression as valid -is not obvious. There are many such interactions between a linear type system -and GHC optimisations documented in the linear-type implementation wiki page -[https://gitlab.haskell.org/ghc/ghc/-/wikis/linear-types/implementation#core-to-core-passes]. + case %1 x of z { + I# n' -> let x = z in (x, n') + } -PRINCIPLE: The type system bends to the optimisation, not the other way around. + This is rejected by `-dlinear-core-lint` because 1/ n' must be used linearly + 2/ `-dlinear-core-lint` recognises a use of `z` as a use of `n'`. So it sees + two uses of n' where there should be a single one. + +* EXAMPLE 2: letrec + Some optimisations can create a letrec which uses a variable + linearly, e.g. + + letrec f True = f False + f False = x + in f True + + uses 'x' linearly, but this is not seen by the linter, which considers, + conservatively, that a letrec always has multiplicity Many (in particular + that every captured free variable must have multiplicity Many). This issue + is discussed in ticket #18694. -In the original linear-types implementation, we had tried to make every -optimisation pass produce code that passes `-dlinear-core-lint`. It had proved -very difficult. And we kept finding corner case after corner case. Plus, we -used to restrict transformations when `-dlinear-core-lint` couldn't typecheck -the result. There are still occurrences of such restrictions in the code. But -our current stance is that such restrictions can be removed. +* EXAMPLE 3: rewrite rules + Ignoring linearity means in particular that `a -> b` and `a %1 -> b` must be + treated the same by rewrite rules (see also Note [Rewrite rules ignore + multiplicities in FunTy] in GHC.Core.Unify). Consider -For instance, some optimisations can create a letrec which uses a variable -linearly, e.g. + m :: Bool -> A + m' :: (Bool -> Bool) -> A + {- RULES "ex" forall f. m (f True) = m' f -} - letrec f True = f False - f False = x - in f True + f :: Bool %1 -> A + x = m (f True) -uses 'x' linearly, but this is not seen by the linter. This issue is discussed -in ticket #18694. + The rule "ex" must match . So the linter must accept `m' f`. -Plus in many cases, in order to make a transformation compatible with linear -linting, we ended up restricting to avoid producing patterns that were not -recognised as linear by the linter. This violates the above principle. +Historical note: In the original linear-types implementation, we had tried to +make every optimisation pass produce code that passes `-dlinear-core-lint`. It +had proved very difficult. We kept finding corner case after corner +case. Furthermore, to attempt to achieve that goal we ended up restricting +transformations when `-dlinear-core-lint` couldn't typecheck the result. In the future, we may be able to lint the linearity of the output of -Core-to-Core passes (#19165). But right now, we can't. Therefore, in virtue of -the principle above, after the desguarer, the optimiser should take no special -pains to preserve linearity (in the type system sense). +Core-to-Core passes (#19165). But this shouldn't be done at the expense of +producing efficient code. Therefore we lay the following principle. -In general the optimiser tries hard not to lose sharing, so it probably doesn't -actually make linear things non-linear. We postulate that any program -transformation which breaks linearity would negatively impact performance, and -therefore wouldn't be suitable for an optimiser. An alternative to linting -linearity after each pass is to prove this statement. +PRINCIPLE: The type system bends to the optimisation, not the other way around. There is a useful discussion at https://gitlab.haskell.org/ghc/ghc/-/issues/22123 @@ -3483,7 +3488,25 @@ ensureEqTys :: LintedType -> LintedType -> SDoc -> LintM () -- check ty2 is subtype of ty1 (ie, has same structure but usage -- annotations need only be consistent, not equal) -- Assumes ty1,ty2 are have already had the substitution applied -ensureEqTys ty1 ty2 msg = lintL (ty1 `eqType` ty2) msg +{-# INLINE ensureEqTys #-} -- See Note [INLINE ensureEqTys] +ensureEqTys ty1 ty2 msg + = do { flags <- getLintFlags + ; lintL (eq_type flags ty1 ty2) msg } + +eq_type :: LintFlags -> Type -> Type -> Bool +-- When `-dlinear-core-lint` is off, then consider `a -> b` and `a %1 -> b` to +-- be equal. See Note [Linting linearity]. +eq_type flags ty1 ty2 | lf_check_linearity flags = eqType ty1 ty2 + | otherwise = eqTypeIgnoringMultiplicity ty1 ty2 + +{- Note [INLINE ensureEqTys] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +To make Lint fast, we want to avoid allocating a thunk for in + ensureEqTypes ty1 ty2 +because the test almost always succeeds, and isn't needed. +So we INLINE `ensureEqTys`. This actually make a difference of +1-2% when compiling programs with -dcore-lint. +-} ensureSubUsage :: Usage -> Mult -> SDoc -> LintM () ensureSubUsage Bottom _ _ = return () ===================================== compiler/GHC/Core/Multiplicity.hs ===================================== @@ -30,7 +30,9 @@ module GHC.Core.Multiplicity , IsSubmult(..) , submult , mapScaledType - , pprArrowWithMultiplicity ) where + , pprArrowWithMultiplicity + , MultiplicityFlag(..) + ) where import GHC.Prelude @@ -395,3 +397,8 @@ pprArrowWithMultiplicity af pp_mult | otherwise = ppr (funTyFlagTyCon af) +-- | In Core, without `-dlinear-core-lint`, some function must ignore +-- multiplicities. See Note [Linting linearity] in GHC.Core.Lint. +data MultiplicityFlag + = RespectMultiplicities + | IgnoreMultiplicities ===================================== compiler/GHC/Core/TyCo/Compare.hs ===================================== @@ -7,15 +7,17 @@ -- | Type equality and comparison module GHC.Core.TyCo.Compare ( - -- * Type comparison - eqType, eqTypeX, eqTypes, nonDetCmpType, nonDetCmpTypes, nonDetCmpTypeX, - nonDetCmpTypesX, nonDetCmpTc, + -- * Type equality + eqType, eqTypeIgnoringMultiplicity, eqTypeX, eqTypes, eqVarBndrs, pickyEqType, tcEqType, tcEqKind, tcEqTypeNoKindCheck, tcEqTyConApps, mayLookIdentical, + -- * Type comparison + nonDetCmpType, + -- * Visiblity comparision eqForAllVis, cmpForAllVis @@ -29,10 +31,12 @@ import GHC.Core.Type( typeKind, coreView, tcSplitAppTyNoView_maybe, splitAppTyNo import GHC.Core.TyCo.Rep import GHC.Core.TyCo.FVs import GHC.Core.TyCon +import GHC.Core.Multiplicity( MultiplicityFlag(..) ) import GHC.Types.Var import GHC.Types.Unique import GHC.Types.Var.Env +import GHC.Types.Var.Set import GHC.Utils.Outputable import GHC.Utils.Misc @@ -52,7 +56,11 @@ so it currently sits "on top of" GHC.Core.Type. {- ********************************************************************* * * - Type equality + Type equality + + We don't use (==) from class Eq, partly so that we know where + type equality is called, and partly because there are multiple + variants. * * ********************************************************************* -} @@ -72,6 +80,93 @@ that needs to be updated. * See Historical Note [Typechecker equality vs definitional equality] below +Note [Casts and coercions in type comparision] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +As (EQTYPE) in Note [Non-trivial definitional equality] says, our +general plan, implemented by `fullEq`, is: + (1) ignore both casts and coercions when comparing types, + (2) instead, compare the /kinds/ of the two types, + as well as the types themselves + +If possible we want to avoid step (2), comparing the kinds; doing so involves +calling `typeKind` and doing another comparision. + +When can we avoid doing so? Answer: we can certainly avoid doing so if the +types we are comparing have no casts or coercions. But we can do better. +Consider + eqType (TyConApp T [s1, ..., sn]) (TyConApp T [t1, .., tn]) +We are going to call (eqType s1 t1), (eqType s2 t2) etc. + +The kinds of `s1` and `t1` must be equal, because these TyConApps are well-kinded, +and both TyConApps are headed by the same T. So the first recursive call to `eqType` +certainly doesn't need to check kinds. If that call returns False, we stop. Otherwise, +we know that `s1` and `t1` are themselves equal (not just their kinds). This +makes the kinds of `s2` and `t2` to be equal, because those kinds come from the +kind of T instantiated with `s1` and `t1` -- which are the same. Thus we do not +need to check the kinds of `s2` and `t2`. By induction, we don't need to check +the kinds of *any* of the types in a TyConApp, and we also do not need to check +the kinds of the TyConApps themselves. + +Conclusion: + +* casts and coercions under a TyConApp don't matter -- even including type synonyms + +* In step (2), use `hasCasts` to tell if there are any casts to worry about. It + does not look very deep, because TyConApps and FunTys are so common, and it + doesn't allocate. The only recursive cases are AppTy and ForAllTy. + +Alternative implementation. Instead of `hasCasts`, we could make the +generic_eq_type function return + data EqResult = NotEq | EqWithNoCasts | EqWithCasts +Practically free; but stylistically I prefer useing `hasCasts`: + * `generic_eq_type` can just uses familiar booleans + * There is a lot more branching with the three-value variant. + * It separates concerns. No need to think about cast-tracking when doing the + equality comparison. + * Indeed sometimes we omit the kind check unconditionally, so tracking it is just wasted + work. +I did try both; there was no perceptible perf difference so I chose `hasCasts` version. + +Note [Equality on AppTys] +~~~~~~~~~~~~~~~~~~~~~~~~~ +In our cast-ignoring equality, we want to say that the following two +are equal: + + (Maybe |> co) (Int |> co') ~? Maybe Int + +But the left is an AppTy while the right is a TyConApp. The solution is +to use splitAppTyNoView_maybe to break up the TyConApp into its pieces and +then continue. Easy to do, but also easy to forget to do. + +Note [Comparing nullary type synonyms] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider the task of testing equality between two 'Type's of the form + + TyConApp tc [] + +where @tc@ is a type synonym. A naive way to perform this comparison these +would first expand the synonym and then compare the resulting expansions. + +However, this is obviously wasteful and the RHS of @tc@ may be large; it is +much better to rather compare the TyCons directly. Consequently, before +expanding type synonyms in type comparisons we first look for a nullary +TyConApp and simply compare the TyCons if we find one. Of course, if we find +that the TyCons are *not* equal then we still need to perform the expansion as +their RHSs may still be equal. + +We perform this optimisation in a number of places: + + * GHC.Core.Types.eqType + * GHC.Core.Types.nonDetCmpType + * GHC.Core.Unify.unify_ty + * GHC.Tc.Solver.Equality.can_eq_nc' + * TcUnify.uType + +This optimisation is especially helpful for the ubiquitous GHC.Types.Type, +since GHC prefers to use the type synonym over @TYPE 'LiftedRep@ applications +whenever possible. See Note [Using synonyms to compress types] in +GHC.Core.Type for details. + Note [Type comparisons using object pointer comparisons] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Quite often we substitute the type from a definition site into @@ -81,6 +176,21 @@ The type of every `x` will often be represented by a single object in the heap. We can take advantage of this by shortcutting the equality check if two types are represented by the same pointer under the hood. In some cases this reduces compiler allocations by ~2%. + +See Note [Pointer comparison operations] in GHC.Builtin.primops.txt.pp + +Note [Respecting multiplicity when comparing types] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Generally speaking, we respect multiplicities (i.e. the linear part of the type +system) when comparing types. Doing so is of course crucial during typechecking. + +But for reasons described in Note [Linting linearity] in GHC.Core.Lint, it is hard +to ensure that Core is always type-correct when it comes to linearity. So +* `eqTypeIgnoringMultiplicity` provides a way to compare types that /ignores/ multiplicities +* We use this multiplicity-blind comparison very occasionally, notably + - in Core Lint: see Note [Linting linearity] in GHC.Core.Lint + - in rule matching: see Note [Rewrite rules ignore multiplicities in FunTy] + in GHC.Core.Unify -} @@ -88,21 +198,12 @@ tcEqKind :: HasDebugCallStack => Kind -> Kind -> Bool tcEqKind = tcEqType tcEqType :: HasDebugCallStack => Type -> Type -> Bool --- ^ tcEqType implements typechecker equality --- It behaves just like eqType, but is implemented --- differently (for now) -tcEqType ty1 ty2 - = tcEqTypeNoSyns ki1 ki2 - && tcEqTypeNoSyns ty1 ty2 - where - ki1 = typeKind ty1 - ki2 = typeKind ty2 +tcEqType = eqType -- | Just like 'tcEqType', but will return True for types of different kinds -- as long as their non-coercion structure is identical. tcEqTypeNoKindCheck :: Type -> Type -> Bool -tcEqTypeNoKindCheck ty1 ty2 - = tcEqTypeNoSyns ty1 ty2 +tcEqTypeNoKindCheck = eqTypeNoKindCheck -- | Check whether two TyConApps are the same; if the number of arguments -- are different, just checks the common prefix of arguments. @@ -114,175 +215,220 @@ tcEqTyConApps tc1 args1 tc2 args2 -- any difference in the kinds of later arguments would show up -- as differences in earlier (dependent) arguments -{- -Note [Specialising tc_eq_type] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -The type equality predicates in Type are hit pretty hard during typechecking. -Consequently we take pains to ensure that these paths are compiled to -efficient, minimally-allocating code. - -To this end we place an INLINE on tc_eq_type, ensuring that it is inlined into -its publicly-visible interfaces (e.g. tcEqType). In addition to eliminating -some dynamic branches, this allows the simplifier to eliminate the closure -allocations that would otherwise be necessary to capture the two boolean "mode" -flags. This reduces allocations by a good fraction of a percent when compiling -Cabal. -See #19226. --} - -mayLookIdentical :: Type -> Type -> Bool --- | Returns True if the /visible/ part of the types --- might look equal, even if they are really unequal (in the invisible bits) --- --- This function is very similar to tc_eq_type but it is much more --- heuristic. Notably, it is always safe to return True, even with types --- that might (in truth) be unequal -- this affects error messages only --- (Originally there were one function with an extra flag, but the result --- was hard to understand.) -mayLookIdentical orig_ty1 orig_ty2 - = go orig_env orig_ty1 orig_ty2 - where - orig_env = mkRnEnv2 $ mkInScopeSet $ tyCoVarsOfTypes [orig_ty1, orig_ty2] - - go :: RnEnv2 -> Type -> Type -> Bool - -- See Note [Comparing nullary type synonyms] - go _ (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = True - - go env t1 t2 | Just t1' <- coreView t1 = go env t1' t2 - go env t1 t2 | Just t2' <- coreView t2 = go env t1 t2' - - go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 - go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 - go env (CastTy t1 _) t2 = go env t1 t2 - go env t1 (CastTy t2 _) = go env t1 t2 - go _ (CoercionTy {}) (CoercionTy {}) = True - - go env (ForAllTy (Bndr tv1 vis1) ty1) - (ForAllTy (Bndr tv2 vis2) ty2) - = vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] - && go (rnBndr2 env tv1 tv2) ty1 ty2 - -- Visible stuff only: ignore kinds of binders - - -- If we have (forall (r::RunTimeRep). ty1 ~ blah) then respond - -- with True. Reason: the type pretty-printer defaults RuntimeRep - -- foralls (see Ghc.Iface.Type.hideNonStandardTypes). That can make, - -- say (forall r. TYPE r -> Type) into (Type -> Type), so it looks the - -- same as a very different type (#24553). By responding True, we - -- tell GHC (see calls of mayLookIdentical) to display without defaulting. - -- See Note [Showing invisible bits of types in error messages] - -- in GHC.Tc.Errors.Ppr - go _ (ForAllTy b _) _ | isDefaultableBndr b = True - go _ _ (ForAllTy b _) | isDefaultableBndr b = True +-- | Type equality on lists of types, looking through type synonyms +eqTypes :: [Type] -> [Type] -> Bool +eqTypes [] [] = True +eqTypes (t1:ts1) (t2:ts2) = eqType t1 t2 && eqTypes ts1 ts2 +eqTypes _ _ = False - go env (FunTy _ w1 arg1 res1) (FunTy _ w2 arg2 res2) - = go env arg1 arg2 && go env res1 res2 && go env w1 w2 - -- Visible stuff only: ignore agg kinds +eqVarBndrs :: HasCallStack => RnEnv2 -> [Var] -> [Var] -> Maybe RnEnv2 +-- Check that the var lists are the same length +-- and have matching kinds; if so, extend the RnEnv2 +-- Returns Nothing if they don't match +eqVarBndrs env [] [] + = Just env +eqVarBndrs env (tv1:tvs1) (tv2:tvs2) + | eqTypeX env (varType tv1) (varType tv2) + = eqVarBndrs (rnBndr2 env tv1 tv2) tvs1 tvs2 +eqVarBndrs _ _ _= Nothing - -- See Note [Equality on AppTys] in GHC.Core.Type - go env (AppTy s1 t1) ty2 - | Just (s2, t2) <- tcSplitAppTyNoView_maybe ty2 - = go env s1 s2 && go env t1 t2 - go env ty1 (AppTy s2 t2) - | Just (s1, t1) <- tcSplitAppTyNoView_maybe ty1 - = go env s1 s2 && go env t1 t2 +initRnEnv :: Type -> Type -> RnEnv2 +initRnEnv ta tb = mkRnEnv2 $ mkInScopeSet $ + tyCoVarsOfType ta `unionVarSet` tyCoVarsOfType tb - go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) - = tc1 == tc2 && gos env (tyConBinders tc1) ts1 ts2 +eqTypeNoKindCheck :: Type -> Type -> Bool +eqTypeNoKindCheck ty1 ty2 = eq_type_expand_respect ty1 ty2 - go _ _ _ = False - - gos :: RnEnv2 -> [TyConBinder] -> [Type] -> [Type] -> Bool - gos _ _ [] [] = True - gos env bs (t1:ts1) (t2:ts2) - | (invisible, bs') <- case bs of - [] -> (False, []) - (b:bs) -> (isInvisibleTyConBinder b, bs) - = (invisible || go env t1 t2) && gos env bs' ts1 ts2 - - gos _ _ _ _ = False +-- | Type equality comparing both visible and invisible arguments, +-- expanding synonyms and respecting multiplicities. +eqType :: HasCallStack => Type -> Type -> Bool +eqType ta tb = fullEq eq_type_expand_respect ta tb +-- | Compare types with respect to a (presumably) non-empty 'RnEnv2'. +eqTypeX :: HasCallStack => RnEnv2 -> Type -> Type -> Bool +eqTypeX env ta tb = fullEq (eq_type_expand_respect_x env) ta tb --- | Type equality comparing both visible and invisible arguments and expanding --- type synonyms. -tcEqTypeNoSyns :: Type -> Type -> Bool -tcEqTypeNoSyns ta tb = tc_eq_type False ta tb +eqTypeIgnoringMultiplicity :: Type -> Type -> Bool +-- See Note [Respecting multiplicity when comparing types] +eqTypeIgnoringMultiplicity ta tb = fullEq eq_type_expand_ignore ta tb -- | Like 'pickyEqTypeVis', but returns a Bool for convenience pickyEqType :: Type -> Type -> Bool -- Check when two types _look_ the same, _including_ synonyms. -- So (pickyEqType String [Char]) returns False -- This ignores kinds and coercions, because this is used only for printing. -pickyEqType ty1 ty2 = tc_eq_type True ty1 ty2 +pickyEqType ta tb = eq_type_keep_respect ta tb --- | Real worker for 'tcEqType'. No kind check! -tc_eq_type :: Bool -- ^ True <=> do not expand type synonyms - -> Type -> Type - -> Bool --- Flags False, False is the usual setting for tc_eq_type --- See Note [Computing equality on types] in Type -{-# INLINE tc_eq_type #-} -- See Note [Specialising tc_eq_type]. -tc_eq_type keep_syns orig_ty1 orig_ty2 - = go orig_env orig_ty1 orig_ty2 - where - orig_env = mkRnEnv2 $ mkInScopeSet $ tyCoVarsOfTypes [orig_ty1, orig_ty2] +{- Note [Specialising type equality] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +The type equality predicates in Type are hit pretty hard by GHC. Consequently +we take pains to ensure that these paths are compiled to efficient, +minimally-allocating code. Plan: - go :: RnEnv2 -> Type -> Type -> Bool - -- See Note [Comparing nullary type synonyms] - go _ (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = True +* The main workhorse is `inline_generic_eq_type_x`. It is /non-recursive/ + and is marked INLINE. - go env t1 t2 | not keep_syns, Just t1' <- coreView t1 = go env t1' t2 - go env t1 t2 | not keep_syns, Just t2' <- coreView t2 = go env t1 t2' +* `inline_generic_eq_type_x` has various parameters that control what it does: + * syn_flag::SynFlag whether type synonyms are expanded or kept. + * mult_flag::MultiplicityFlag whether multiplicities are ignored or respected + * mb_env::Maybe RnEnv2 an optional RnEnv2. - go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 - go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 - go env (CastTy t1 _) t2 = go env t1 t2 - go env t1 (CastTy t2 _) = go env t1 t2 - go _ (CoercionTy {}) (CoercionTy {}) = True +* `inline_generic_eq_type_x` has a handful of call sites, namely the ones + in `eq_type_expand_respect`, `eq_type_expand_repect_x` etc. It inlines + at all these sites, specialising to the data values passed for the + control parameters. - go env (ForAllTy (Bndr tv1 vis1) ty1) - (ForAllTy (Bndr tv2 vis2) ty2) - = vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] - && go env (varType tv1) (varType tv2) - && go (rnBndr2 env tv1 tv2) ty1 ty2 +* All /other/ calls to `inline_generic_eq_type_x` go via + generic_eq_type_x = inline_generic_eq_type_x + {-# NOINLNE generic_eq_type_x #-} + The idea is that all calls to `generic_eq_type_x` are specialised by the + RULES, so this NOINLINE version is seldom, if ever, actually called. + +* For each of specialised copy of `inline_generic_eq_type_x, there is a + corresponding rewrite RULE that rewrites a call to (generic_eq_type_x args) + into the appropriate specialied version. + +See #19226. +-} + +-- | This flag controls whether we expand synonyms during comparison +data SynFlag = ExpandSynonyms | KeepSynonyms + +eq_type_expand_respect, eq_type_expand_ignore, eq_type_keep_respect + :: Type -> Type -> Bool +eq_type_expand_respect_x, eq_type_expand_ignore_x, eq_type_keep_respect_x + :: RnEnv2 -> Type -> Type -> Bool + +eq_type_expand_respect = inline_generic_eq_type_x ExpandSynonyms RespectMultiplicities Nothing +eq_type_expand_respect_x env = inline_generic_eq_type_x ExpandSynonyms RespectMultiplicities (Just env) +eq_type_expand_ignore = inline_generic_eq_type_x ExpandSynonyms IgnoreMultiplicities Nothing +eq_type_expand_ignore_x env = inline_generic_eq_type_x ExpandSynonyms IgnoreMultiplicities (Just env) +eq_type_keep_respect = inline_generic_eq_type_x KeepSynonyms RespectMultiplicities Nothing +eq_type_keep_respect_x env = inline_generic_eq_type_x KeepSynonyms RespectMultiplicities (Just env) + +{-# RULES +"eqType1" generic_eq_type_x ExpandSynonyms RespectMultiplicities Nothing + = eq_type_expand_respect +"eqType2" forall env. generic_eq_type_x ExpandSynonyms RespectMultiplicities (Just env) + = eq_type_expand_respect_x env +"eqType3" generic_eq_type_x ExpandSynonyms IgnoreMultiplicities Nothing + = eq_type_expand_ignore +"eqType4" forall env. generic_eq_type_x ExpandSynonyms IgnoreMultiplicities (Just env) + = eq_type_expand_ignore_x env +"eqType5" generic_eq_type_x KeepSynonyms RespectMultiplicities Nothing + = eq_type_keep_respect +"eqType6" forall env. generic_eq_type_x KeepSynonyms RespectMultiplicities (Just env) + = eq_type_keep_respect_x env + #-} + +-- --------------------------------------------------------------- +-- | Real worker for 'eqType'. No kind check! +-- Inline it at the (handful of local) call sites +-- The "generic" bit refers to the flag paramerisation +-- See Note [Specialising type equality]. +generic_eq_type_x, inline_generic_eq_type_x + :: SynFlag -> MultiplicityFlag -> Maybe RnEnv2 -> Type -> Type -> Bool + +{-# NOINLINE generic_eq_type_x #-} +generic_eq_type_x = inline_generic_eq_type_x +-- See Note [Computing equality on types] in Type + +{-# INLINE inline_generic_eq_type_x #-} +-- This non-recursive function can inline at its (few) call sites. The +-- recursion goes via generic_eq_type_x, which is the loop-breaker. +inline_generic_eq_type_x syn_flag mult_flag mb_env + = \ t1 t2 -> t1 `seq` t2 `seq` + let go = generic_eq_type_x syn_flag mult_flag mb_env + -- Abbreviation for recursive calls + in case (t1,t2) of + _ | 1# <- reallyUnsafePtrEquality# t1 t2 -> True + -- See Note [Type comparisons using object pointer comparisons] + + (TyConApp tc1 [], TyConApp tc2 []) | tc1 == tc2 -> True + -- See Note [Comparing nullary type synonyms] + + _ | ExpandSynonyms <- syn_flag, Just t1' <- coreView t1 -> go t1' t2 + | ExpandSynonyms <- syn_flag, Just t2' <- coreView t2 -> go t1 t2' + + (TyVarTy tv1, TyVarTy tv2) + -> case mb_env of + Nothing -> tv1 == tv2 + Just env -> rnOccL env tv1 == rnOccR env tv2 + + (LitTy lit1, LitTy lit2) -> lit1 == lit2 + (CastTy t1' _, _) -> go t1' t2 -- Ignore casts + (_, CastTy t2' _) -> go t1 t2' -- Ignore casts + (CoercionTy {}, CoercionTy {}) -> True -- Ignore coercions -- Make sure we handle all FunTy cases since falling through to the -- AppTy case means that tcSplitAppTyNoView_maybe may see an unzonked -- kind variable, which causes things to blow up. -- See Note [Equality on FunTys] in GHC.Core.TyCo.Rep: we must check -- kinds here - go env (FunTy _ w1 arg1 res1) (FunTy _ w2 arg2 res2) - = go env (typeKind arg1) (typeKind arg2) && - go env (typeKind res1) (typeKind res2) && - go env arg1 arg2 && go env res1 res2 && go env w1 w2 + (FunTy _ w1 arg1 res1, FunTy _ w2 arg2 res2) + -> fullEq go arg1 arg2 + && fullEq go res1 res2 + && (case mult_flag of + RespectMultiplicities -> go w1 w2 + IgnoreMultiplicities -> True) -- See Note [Equality on AppTys] in GHC.Core.Type - go env (AppTy s1 t1) ty2 - | Just (s2, t2) <- tcSplitAppTyNoView_maybe ty2 - = go env s1 s2 && go env t1 t2 - go env ty1 (AppTy s2 t2) - | Just (s1, t1) <- tcSplitAppTyNoView_maybe ty1 - = go env s1 s2 && go env t1 t2 - - go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) - = tc1 == tc2 && gos env ts1 ts2 - - go _ _ _ = False - - gos _ [] [] = True - gos env (t1:ts1) (t2:ts2) = go env t1 t2 && gos env ts1 ts2 - gos _ _ _ = False + (AppTy s1 t1', _) + | Just (s2, t2') <- tcSplitAppTyNoView_maybe t2 + -> go s1 s2 && go t1' t2' + (_, AppTy s2 t2') + | Just (s1, t1') <- tcSplitAppTyNoView_maybe t1 + -> go s1 s2 && go t1' t2' + + (TyConApp tc1 ts1, TyConApp tc2 ts2) + | tc1 == tc2 -> gos ts1 ts2 + | otherwise -> False + where + gos [] [] = True + gos (t1:ts1) (t2:ts2) = go t1 t2 && gos ts1 ts2 + gos _ _ = False + + (ForAllTy (Bndr tv1 vis1) body1, ForAllTy (Bndr tv2 vis2) body2) + -> case mb_env of + Nothing -> generic_eq_type_x syn_flag mult_flag + (Just (initRnEnv t1 t2)) t1 t2 + Just env + | vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] + -> go (varType tv1) (varType tv2) -- Always do kind-check + && generic_eq_type_x syn_flag mult_flag + (Just (rnBndr2 env tv1 tv2)) body1 body2 + | otherwise + -> False + + _ -> False + +fullEq :: (Type -> Type -> Bool) -> Type -> Type -> Bool +-- Do "full equality" including the kind check +-- See Note [Casts and coercions in type comparision] +{-# INLINE fullEq #-} +fullEq eq ty1 ty2 + = case eq ty1 ty2 of + False -> False + True | hasCasts ty1 || hasCasts ty2 + -> eq (typeKind ty1) (typeKind ty2) + | otherwise + -> True + +hasCasts :: Type -> Bool +-- Fast, does not look deep, does not allocate +hasCasts (CastTy {}) = True +hasCasts (CoercionTy {}) = True +hasCasts (AppTy t1 t2) = hasCasts t1 || hasCasts t2 +hasCasts (ForAllTy _ ty) = hasCasts ty +hasCasts _ = False -- TyVarTy, TyConApp, FunTy, LitTy -isDefaultableBndr :: ForAllTyBinder -> Bool --- This function should line up with the defaulting done --- by GHC.Iface.Type.defaultIfaceTyVarsOfKind --- See Note [Showing invisible bits of types in error messages] --- in GHC.Tc.Errors.Ppr -isDefaultableBndr (Bndr tv vis) - = isInvisibleForAllTyFlag vis && is_defaultable (tyVarKind tv) - where - is_defaultable ki = isLevityTy ki || isRuntimeRepTy ki || isMultiplicityTy ki +{- ********************************************************************* +* * + Comparing ForAllTyFlags +* * +********************************************************************* -} -- | Do these denote the same level of visibility? 'Required' -- arguments are visible, others are not. So this function @@ -442,91 +588,13 @@ is more finer-grained than definitional equality in two places: ************************************************************************ * * Comparison for types - (We don't use instances so that we know where it happens) + + Not so heavily used, less carefully optimised * * ************************************************************************ -Note [Equality on AppTys] -~~~~~~~~~~~~~~~~~~~~~~~~~ -In our cast-ignoring equality, we want to say that the following two -are equal: - - (Maybe |> co) (Int |> co') ~? Maybe Int - -But the left is an AppTy while the right is a TyConApp. The solution is -to use splitAppTyNoView_maybe to break up the TyConApp into its pieces and -then continue. Easy to do, but also easy to forget to do. - -Note [Comparing nullary type synonyms] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Consider the task of testing equality between two 'Type's of the form - - TyConApp tc [] - -where @tc@ is a type synonym. A naive way to perform this comparison these -would first expand the synonym and then compare the resulting expansions. - -However, this is obviously wasteful and the RHS of @tc@ may be large; it is -much better to rather compare the TyCons directly. Consequently, before -expanding type synonyms in type comparisons we first look for a nullary -TyConApp and simply compare the TyCons if we find one. Of course, if we find -that the TyCons are *not* equal then we still need to perform the expansion as -their RHSs may still be equal. - -We perform this optimisation in a number of places: - - * GHC.Core.Types.eqType - * GHC.Core.Types.nonDetCmpType - * GHC.Core.Unify.unify_ty - * GHC.Tc.Solver.Equality.can_eq_nc' - * TcUnify.uType - -This optimisation is especially helpful for the ubiquitous GHC.Types.Type, -since GHC prefers to use the type synonym over @TYPE 'LiftedRep@ applications -whenever possible. See Note [Using synonyms to compress types] in -GHC.Core.Type for details. - --} - -eqType :: Type -> Type -> Bool --- ^ Type equality on source types. Does not look through @newtypes@, --- 'PredType's or type families, but it does look through type synonyms. --- This first checks that the kinds of the types are equal and then --- checks whether the types are equal, ignoring casts and coercions. --- (The kind check is a recursive call, but since all kinds have type --- @Type@, there is no need to check the types of kinds.) --- See also Note [Non-trivial definitional equality] in "GHC.Core.TyCo.Rep". -eqType t1 t2 = isEqual $ nonDetCmpType t1 t2 - -- It's OK to use nonDetCmpType here and eqType is deterministic, - -- nonDetCmpType does equality deterministically - --- | Compare types with respect to a (presumably) non-empty 'RnEnv2'. -eqTypeX :: RnEnv2 -> Type -> Type -> Bool -eqTypeX env t1 t2 = isEqual $ nonDetCmpTypeX env t1 t2 - -- It's OK to use nonDetCmpType here and eqTypeX is deterministic, - -- nonDetCmpTypeX does equality deterministically - --- | Type equality on lists of types, looking through type synonyms --- but not newtypes. -eqTypes :: [Type] -> [Type] -> Bool -eqTypes tys1 tys2 = isEqual $ nonDetCmpTypes tys1 tys2 - -- It's OK to use nonDetCmpType here and eqTypes is deterministic, - -- nonDetCmpTypes does equality deterministically - -eqVarBndrs :: RnEnv2 -> [Var] -> [Var] -> Maybe RnEnv2 --- Check that the var lists are the same length --- and have matching kinds; if so, extend the RnEnv2 --- Returns Nothing if they don't match -eqVarBndrs env [] [] - = Just env -eqVarBndrs env (tv1:tvs1) (tv2:tvs2) - | eqTypeX env (varType tv1) (varType tv2) - = eqVarBndrs (rnBndr2 env tv1 tv2) tvs1 tvs2 -eqVarBndrs _ _ _= Nothing - -- Now here comes the real worker -{- Note [nonDetCmpType nondeterminism] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ nonDetCmpType is implemented in terms of nonDetCmpTypeX. nonDetCmpTypeX @@ -538,6 +606,7 @@ See Note [Unique Determinism] for more details. -} nonDetCmpType :: Type -> Type -> Ordering +{-# INLINE nonDetCmpType #-} nonDetCmpType !t1 !t2 -- See Note [Type comparisons using object pointer comparisons] | 1# <- reallyUnsafePtrEquality# t1 t2 @@ -549,12 +618,6 @@ nonDetCmpType t1 t2 = nonDetCmpTypeX rn_env t1 t2 where rn_env = mkRnEnv2 (mkInScopeSet (tyCoVarsOfTypes [t1, t2])) -{-# INLINE nonDetCmpType #-} - -nonDetCmpTypes :: [Type] -> [Type] -> Ordering -nonDetCmpTypes ts1 ts2 = nonDetCmpTypesX rn_env ts1 ts2 - where - rn_env = mkRnEnv2 (mkInScopeSet (tyCoVarsOfTypes (ts1 ++ ts2))) -- | An ordering relation between two 'Type's (known below as @t1 :: k1@ -- and @t2 :: k2@) @@ -569,6 +632,7 @@ data TypeOrdering = TLT -- ^ @t1 < t2@ nonDetCmpTypeX :: RnEnv2 -> Type -> Type -> Ordering -- Main workhorse -- See Note [Non-trivial definitional equality] in GHC.Core.TyCo.Rep -- See Note [Computing equality on types] + -- Always respects multiplicities, unlike eqType nonDetCmpTypeX env orig_t1 orig_t2 = case go env orig_t1 orig_t2 of -- If there are casts then we also need to do a comparison of @@ -661,13 +725,6 @@ nonDetCmpTypeX env orig_t1 orig_t2 = gos _ _ [] = TGT gos env (ty1:tys1) (ty2:tys2) = go env ty1 ty2 `thenCmpTy` gos env tys1 tys2 -------------- -nonDetCmpTypesX :: RnEnv2 -> [Type] -> [Type] -> Ordering -nonDetCmpTypesX _ [] [] = EQ -nonDetCmpTypesX env (t1:tys1) (t2:tys2) = nonDetCmpTypeX env t1 t2 S.<> - nonDetCmpTypesX env tys1 tys2 -nonDetCmpTypesX _ [] _ = LT -nonDetCmpTypesX _ _ [] = GT ------------- -- | Compare two 'TyCon's. @@ -680,4 +737,91 @@ nonDetCmpTc tc1 tc2 u2 = tyConUnique tc2 +{- ********************************************************************* +* * + mayLookIdentical +* * +********************************************************************* -} + +mayLookIdentical :: Type -> Type -> Bool +-- | Returns True if the /visible/ part of the types +-- might look equal, even if they are really unequal (in the invisible bits) +-- +-- This function is very similar to tc_eq_type but it is much more +-- heuristic. Notably, it is always safe to return True, even with types +-- that might (in truth) be unequal -- this affects error messages only +-- (Originally this test was done by eqType with an extra flag, but the result +-- was hard to understand.) +mayLookIdentical orig_ty1 orig_ty2 + = go orig_env orig_ty1 orig_ty2 + where + orig_env = mkRnEnv2 $ mkInScopeSet $ tyCoVarsOfTypes [orig_ty1, orig_ty2] + + go :: RnEnv2 -> Type -> Type -> Bool + -- See Note [Comparing nullary type synonyms] + go _ (TyConApp tc1 []) (TyConApp tc2 []) | tc1 == tc2 = True + + go env t1 t2 | Just t1' <- coreView t1 = go env t1' t2 + go env t1 t2 | Just t2' <- coreView t2 = go env t1 t2' + + go env (TyVarTy tv1) (TyVarTy tv2) = rnOccL env tv1 == rnOccR env tv2 + go _ (LitTy lit1) (LitTy lit2) = lit1 == lit2 + go env (CastTy t1 _) t2 = go env t1 t2 + go env t1 (CastTy t2 _) = go env t1 t2 + go _ (CoercionTy {}) (CoercionTy {}) = True + + go env (ForAllTy (Bndr tv1 vis1) ty1) + (ForAllTy (Bndr tv2 vis2) ty2) + = vis1 `eqForAllVis` vis2 -- See Note [ForAllTy and type equality] + && go (rnBndr2 env tv1 tv2) ty1 ty2 + -- Visible stuff only: ignore kinds of binders + + -- If we have (forall (r::RunTimeRep). ty1 ~ blah) then respond + -- with True. Reason: the type pretty-printer defaults RuntimeRep + -- foralls (see Ghc.Iface.Type.hideNonStandardTypes). That can make, + -- say (forall r. TYPE r -> Type) into (Type -> Type), so it looks the + -- same as a very different type (#24553). By responding True, we + -- tell GHC (see calls of mayLookIdentical) to display without defaulting. + -- See Note [Showing invisible bits of types in error messages] + -- in GHC.Tc.Errors.Ppr + go _ (ForAllTy b _) _ | isDefaultableBndr b = True + go _ _ (ForAllTy b _) | isDefaultableBndr b = True + + go env (FunTy _ w1 arg1 res1) (FunTy _ w2 arg2 res2) + = go env arg1 arg2 && go env res1 res2 && go env w1 w2 + -- Visible stuff only: ignore agg kinds + + -- See Note [Equality on AppTys] in GHC.Core.Type + go env (AppTy s1 t1) ty2 + | Just (s2, t2) <- tcSplitAppTyNoView_maybe ty2 + = go env s1 s2 && go env t1 t2 + go env ty1 (AppTy s2 t2) + | Just (s1, t1) <- tcSplitAppTyNoView_maybe ty1 + = go env s1 s2 && go env t1 t2 + + go env (TyConApp tc1 ts1) (TyConApp tc2 ts2) + = tc1 == tc2 && gos env (tyConBinders tc1) ts1 ts2 + + go _ _ _ = False + + gos :: RnEnv2 -> [TyConBinder] -> [Type] -> [Type] -> Bool + gos _ _ [] [] = True + gos env bs (t1:ts1) (t2:ts2) + | (invisible, bs') <- case bs of + [] -> (False, []) + (b:bs) -> (isInvisibleTyConBinder b, bs) + = (invisible || go env t1 t2) && gos env bs' ts1 ts2 + + gos _ _ _ _ = False + + +isDefaultableBndr :: ForAllTyBinder -> Bool +-- This function should line up with the defaulting done +-- by GHC.Iface.Type.defaultIfaceTyVarsOfKind +-- See Note [Showing invisible bits of types in error messages] +-- in GHC.Tc.Errors.Ppr +isDefaultableBndr (Bndr tv vis) + = isInvisibleForAllTyFlag vis && is_defaultable (tyVarKind tv) + where + is_defaultable ki = isLevityTy ki || isRuntimeRepTy ki || isMultiplicityTy ki ===================================== compiler/GHC/Core/TyCo/Rep.hs ===================================== @@ -350,14 +350,24 @@ This kind instantiation only happens in TyConApp currently. Note [Non-trivial definitional equality] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Is Int |> <*> the same as Int? YES! In order to reduce headaches, -we decide that any reflexive casts in types are just ignored. -(Indeed they must be. See Note [Respecting definitional equality].) -More generally, the `eqType` function, which defines Core's type equality -relation, ignores casts and coercion arguments, as long as the -two types have the same kind. This allows us to be a little sloppier -in keeping track of coercions, which is a good thing. It also means -that eqType does not depend on eqCoercion, which is also a good thing. +Is ((IO |> co1) Int |> co2) equal to (IO Int)? +Assume + co1 :: (Type->Type) ~ (Type->Wombat) + co2 :: Wombat ~ Type +Well, yes. The casts are just getting in the way. +See also Note [Respecting definitional equality]. + +So we do this: + +(EQTYPE) + The `eqType` function, which defines Core's type equality relation, + - /ignores/ casts, and + - /ignores/ coercion arguments + - /provided/ two types have the same kind + +This allows us to be a little sloppier in keeping track of coercions, which is a +good thing. It also means that eqType does not depend on eqCoercion, which is +also a good thing. Why is this sensible? That is, why is something different than α-equivalence appropriate for the implementation of eqType? ===================================== compiler/GHC/Core/Type.hs ===================================== @@ -1366,6 +1366,8 @@ funTyConAppTy_maybe :: FunTyFlag -> Type -> Type -> Type funTyConAppTy_maybe af mult arg res | Just arg_rep <- getRuntimeRep_maybe arg , Just res_rep <- getRuntimeRep_maybe res + -- If you're changing the lines below, you'll probably want to adapt the + -- `fUNTyCon` case of GHC.Core.Unify.unify_ty correspondingly. , let args | isFUNArg af = [mult, arg_rep, res_rep, arg, res] | otherwise = [ arg_rep, res_rep, arg, res] = Just $ (funTyFlagTyCon af, args) ===================================== compiler/GHC/Core/Unify.hs ===================================== @@ -54,6 +54,8 @@ import GHC.Data.FastString import Data.List ( mapAccumL ) import Control.Monad import qualified Data.Semigroup as S +import GHC.Builtin.Types.Prim (fUNTyCon) +import GHC.Core.Multiplicity {- @@ -211,6 +213,7 @@ tc_match_tys_x bind_me match_kis (Subst in_scope id_env tv_env cv_env) tys1 tys2 False -- Matching, not unifying False -- Not an injectivity check match_kis + RespectMultiplicities (mkRnEnv2 in_scope) tv_env cv_env tys1 tys2 of Unifiable (tv_env', cv_env') -> Just $ Subst in_scope id_env tv_env' cv_env' @@ -229,6 +232,8 @@ ruleMatchTyKiX tmpl_tvs rn_env tenv tmpl target -- See Note [Kind coercions in Unify] = case tc_unify_tys (matchBindFun tmpl_tvs) False False True -- <-- this means to match the kinds + IgnoreMultiplicities + -- See Note [Rewrite rules ignore multiplicities in FunTy] rn_env tenv emptyCvSubstEnv [tmpl] [target] of Unifiable (tenv', _) -> Just tenv' _ -> Nothing @@ -394,6 +399,40 @@ types are apart. This has practical consequences for the ability for closed type family applications to reduce. See test case indexed-types/should_compile/Overlap14. +Note [Rewrite rules ignore multiplicities in FunTy] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider the following (higher-order) rule: + +m :: Bool -> Bool -> Bool +{-# RULES "m" forall f. m (f True) = f #-} + +let x = m ((,) @Bool @Bool True True) + +The rewrite rule expects an `f :: Bool -> Bool`, but `(,) @Bool @Bool True :: +Bool %1 -> Bool` is linear (see Note [Data constructors are linear by default] +in GHC.Core.Multiplicity) Should the rule match? Yes! According to the +principles laid out in Note [Linting linearity] in GHC.Core.Lint, optimisation +shouldn't be constrained by linearity. + +However, when matching the template variable `f` to `(,) True`, we do check that +their types unify (see Note [Matching variable types] in GHC.Core.Rules). So +when unifying types for the sake of rule-matching, the unification algorithm +must be able to ignore multiplicities altogether. + +How is this done? + (1) The `um_arr_mult` field of `UMEnv` recordsw when we are doing rule-matching, + and hence want to ignore multiplicities. + (2) The field is set to True in by `ruleMatchTyKiX`. + (3) It is consulted when matching `FunTy` in `unify_ty`. + +Wrinkle in (3). In `unify_tc_app`, in `unify_ty`, `FunTy` is handled as if it +was a regular type constructor. In this case, and when the types being unified +are *function* arrows, but not constraint arrows, then the first argument is a +multiplicity. + +We select this situation by comparing the type constructor with fUNTyCon. In +this case, and this case only, we can safely drop the first argument (using the +tail function) and unify the rest. -} -- | Simple unification of two types; all type variables are bindable @@ -421,7 +460,7 @@ tcUnifyTyWithTFs :: Bool -- ^ True <=> do two-way unification; -- The code is incorporated with the standard unifier for convenience, but -- its operation should match the specification in the paper. tcUnifyTyWithTFs twoWay in_scope t1 t2 - = case tc_unify_tys alwaysBindFun twoWay True False + = case tc_unify_tys alwaysBindFun twoWay True False RespectMultiplicities rn_env emptyTvSubstEnv emptyCvSubstEnv [t1] [t2] of Unifiable (tv_subst, _cv_subst) -> Just $ maybe_fix tv_subst @@ -530,7 +569,7 @@ tc_unify_tys_fg :: Bool -> [Type] -> [Type] -> UnifyResult tc_unify_tys_fg match_kis bind_fn tys1 tys2 - = do { (env, _) <- tc_unify_tys bind_fn True False match_kis rn_env + = do { (env, _) <- tc_unify_tys bind_fn True False match_kis RespectMultiplicities rn_env emptyTvSubstEnv emptyCvSubstEnv tys1 tys2 ; return $ niFixSubst in_scope env } @@ -544,6 +583,7 @@ tc_unify_tys :: BindFun -> AmIUnifying -- ^ True <=> unify; False <=> match -> Bool -- ^ True <=> doing an injectivity check -> Bool -- ^ True <=> treat the kinds as well + -> MultiplicityFlag -- ^ see Note [Rewrite rules ignore multiplicities in FunTy] in GHC.Core.Unify -> RnEnv2 -> TvSubstEnv -- ^ substitution to extend -> CvSubstEnv @@ -560,7 +600,7 @@ tc_unify_tys :: BindFun -- pair equal. Yet, we still don't need a separate pass to unify the kinds -- of these types, so it's appropriate to use the Ty variant of unification. -- See also Note [tcMatchTy vs tcMatchTyKi]. -tc_unify_tys bind_fn unif inj_check match_kis rn_env tv_env cv_env tys1 tys2 +tc_unify_tys bind_fn unif inj_check match_kis match_mults rn_env tv_env cv_env tys1 tys2 = initUM tv_env cv_env $ do { when match_kis $ unify_tys env kis1 kis2 @@ -571,6 +611,7 @@ tc_unify_tys bind_fn unif inj_check match_kis rn_env tv_env cv_env tys1 tys2 , um_skols = emptyVarSet , um_unif = unif , um_inj_tf = inj_check + , um_arr_mult = match_mults , um_rn_env = rn_env } kis1 = map typeKind tys1 @@ -1144,7 +1185,7 @@ unify_ty env ty1 ty2 _kco , Just (tc2, tys2) <- mb_tc_app2 , tc1 == tc2 = do { massertPpr (isInjectiveTyCon tc1 Nominal) (ppr tc1) - ; unify_tys env tys1 tys2 + ; unify_tc_app tc1 tys1 tys2 } -- TYPE and CONSTRAINT are not Apart @@ -1175,6 +1216,21 @@ unify_ty env ty1 ty2 _kco mb_tc_app1 = splitTyConApp_maybe ty1 mb_tc_app2 = splitTyConApp_maybe ty2 + unify_tc_app tc tys1 tys2 + | tc == fUNTyCon + , IgnoreMultiplicities <- um_arr_mult env + , (_mult1 : no_mult_tys1) <- tys1 + , (_mult2 : no_mult_tys2) <- tys2 + = -- We're comparing function arrow types here (not constraint arrow + -- types!), and they have at least one argument, which is the arrow's + -- multiplicity annotation. The flag `um_arr_mult` instructs us to + -- ignore multiplicities in this very case. This is a little tricky: see + -- point (3) in Note [Rewrite rules ignore multiplicities in FunTy]. + unify_tys env no_mult_tys1 no_mult_tys2 + + | otherwise + = unify_tys env tys1 tys2 + -- Applications need a bit of care! -- They can match FunTy and TyConApp, so use splitAppTy_maybe -- NB: we've already dealt with type variables, @@ -1410,6 +1466,10 @@ data UMEnv -- Checking for injectivity? -- See (end of) Note [Specification of unification] + , um_arr_mult :: MultiplicityFlag + -- Whether to unify multiplicity arguments when unifying arrows. + -- See Note [Rewrite rules ignore multiplicities in FunTy] + , um_rn_env :: RnEnv2 -- Renaming InTyVars to OutTyVars; this eliminates -- shadowing, and lines up matching foralls on the left ===================================== compiler/GHC/Tc/Utils/TcType.hs ===================================== @@ -96,7 +96,7 @@ module GHC.Tc.Utils.TcType ( -- Re-exported from GHC.Core.TyCo.Compare -- mainly just for back-compat reasons - eqType, eqTypes, nonDetCmpType, nonDetCmpTypes, eqTypeX, + eqType, eqTypes, nonDetCmpType, eqTypeX, pickyEqType, tcEqType, tcEqKind, tcEqTypeNoKindCheck, mayLookIdentical, tcEqTyConApps, eqForAllVis, eqVarBndrs, ===================================== testsuite/tests/simplCore/should_run/T23586.hs ===================================== @@ -0,0 +1,45 @@ +{-# LANGUAGE LinearTypes #-} + +module Main where + +-- These rules are clearly nonsensical, so that we can observe the result of +-- their firing. +{-# RULES "test/match" forall f. mark (f True) = (False, False) #-} +{-# RULES "test/core" forall f. mark (f False) = ensure_many f #-} + +-- Tests that constructors are matched by higher-order rules (as originally +-- reported) +g = mark (True, True) + +-- Tests that linear functions are matched by higher-order rules (as was +-- understood to be the root cause of the issue) +h = mark (d True) + +-- Tests that a matched linear function can be used where a non-linear function +-- is expected, and that the result passes the linter. This wasn't part of the +-- original report, but a first fix to #23586 was incorrect because this rule +-- produced Core which was rejected by the linter. +-- See https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12648#note_565803 . +i = mark (d False) + +main :: IO () +main = do + print g + print h + print i + + +-- Helpers below + +mark :: a -> a +mark x = x +{-# NOINLINE mark #-} + +d :: Bool %1 -> (Bool, Bool) +d True = (True, True) +d False = (False, False) +{-# NOINLINE d #-} + +ensure_many :: (Bool -> (Bool, Bool)) -> (Bool, Bool) +ensure_many f = (False, True) +{-# NOINLINE ensure_many #-} ===================================== testsuite/tests/simplCore/should_run/T23586.stdout ===================================== @@ -0,0 +1,3 @@ +(False,False) +(False,False) +(False,True) ===================================== testsuite/tests/simplCore/should_run/all.T ===================================== @@ -114,3 +114,4 @@ test('T23184', normal, compile_and_run, ['-O']) test('T23134', normal, compile_and_run, ['-O0 -fcatch-nonexhaustive-cases']) test('T23289', normal, compile_and_run, ['']) test('T23056', [only_ways(['ghci-opt'])], ghci_script, ['T23056.script']) +test('T23586', normal, compile_and_run, ['-O -dcore-lint']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c872e09b41629b442ed7a0c0a52835068fa205a3...c8a8727ef67a3212abbf9f928bef67dfef276adf -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/c872e09b41629b442ed7a0c0a52835068fa205a3...c8a8727ef67a3212abbf9f928bef67dfef276adf You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 10:18:28 2024 From: gitlab at gitlab.haskell.org (Peter Trommler (@trommler)) Date: Fri, 21 Jun 2024 06:18:28 -0400 Subject: [Git][ghc/ghc][wip/T23034] 32 commits: Make flip representation polymorphic, similar to ($) and (&) Message-ID: <667553747e5d5_2f9c286c8ae070038@gitlab.mail> Peter Trommler pushed to branch wip/T23034 at Glasgow Haskell Compiler / GHC Commits: e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - d70abb49 by sheaf at 2024-06-18T18:47:20-04:00 Clarify -XGADTs enables existential quantification Even though -XGADTs does not turn on -XExistentialQuantification, it does allow the user of existential quantification syntax, without needing to use GADT-style syntax. Fixes #20865 - - - - - 13fdf788 by David Binder at 2024-06-18T18:48:02-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 1bab7dde by Fendor at 2024-06-18T18:48:38-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18698b T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The tests T16875 and T18698b fail on i386-linux for the same reason. - - - - - 099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - 5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00 Update user guide to indicate support for 64-tuples - - - - - 4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00 Remove duplicate Anno instances - - - - - 8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00 AArch64: Delete unused RegNos This has the additional benefit of getting rid of the -1 encoding (real registers start at 0.) - - - - - 325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00 Bump stm submodule to current master - - - - - 64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00 testsuite: bump T17572 timeout on wasm32 - - - - - eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00 AArch64: Simplify BL instruction The BL constructor carried unused data in its third argument. - - - - - b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00 TTG: Move SourceText from `Fixity` to `FixitySig` It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Precedes !12842, to simplify it - - - - - 842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00 base: Deprecate some .Internal modules Deprecates the following modules according to clc-proposal #217: https://github.com/haskell/core-libraries-committee/issues/217 * GHC.TypeNats.Internal * GHC.TypeLits.Internal * GHC.ExecutionStack.Internal Closes #24998 - - - - - 24e89c40 by Jacco Krijnen at 2024-06-20T07:21:27-04:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 04f5bb85 by Simon Peyton Jones at 2024-06-20T07:22:03-04:00 Fix untouchability test This MR fixes #24938. The underlying problem was tha the test for "does this implication bring in scope any equalities" was plain wrong. See Note [Tracking Given equalities] and Note [Let-bound skolems] both in GHC.Tc.Solver.InertSet. Then * Test LocalGivenEqs succeeds for a different reason than before; see (LBS2) in Note [Let-bound skolems] * New test T24938a succeeds because of (LBS2), whereas it failed before. * Test LocalGivenEqs2 now fails, as it should. * Test T224938, the repro from the ticket, fails, as it should. - - - - - 9a757a27 by Simon Peyton Jones at 2024-06-20T07:22:40-04:00 Fix demand signatures for join points This MR tackles #24623 and #23113 The main change is to give a clearer notion of "worker/wrapper arity", esp for join points. See GHC.Core.Opt.DmdAnal Note [Worker/wrapper arity and join points] This Note is a good summary of what this MR does: (1) The "worker/wrapper arity" of an Id is * For non-join-points: idArity * The join points: the join arity (Id part only of course) This is the number of args we will use in worker/wrapper. See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`. (2) A join point's demand-signature arity may exceed the Id's worker/wrapper arity. See the `arity_ok` assertion in `mkWwBodies`. (3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond the worker/wrapper arity. (4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper arity (re)-computed by workWrapArity. - - - - - 5e8faaf1 by Jan Hrček at 2024-06-20T07:23:20-04:00 Update haddocks of Import/Export AST types - - - - - cd512234 by Hécate Kleidukos at 2024-06-20T07:24:02-04:00 haddock: Update bounds in cabal files and remove allow-newer stanza in cabal.project - - - - - 8a8ff8f2 by Rodrigo Mesquita at 2024-06-20T07:24:38-04:00 cmm: Don't parse MO_BSwap for W8 Don't support parsing bswap8, since bswap8 is not really an operation and would have to be implemented as a no-op (and currently is not implemented at all). Fixes #25002 - - - - - 5cc472f5 by sheaf at 2024-06-20T07:25:14-04:00 Delete unused testsuite files These files were committed by mistake in !11902. This commit simply removes them. - - - - - 7b079378 by Matthew Pickering at 2024-06-20T07:25:50-04:00 Remove left over debugging pragma from 2016 This pragma was accidentally introduced in 648fd73a7b8fbb7955edc83330e2910428e76147 The top-level cost centres lead to a lack of optimisation when compiling with profiling. - - - - - c872e09b by Hécate Kleidukos at 2024-06-20T19:28:36-04:00 haddock: Remove unused pragmata, qualify usages of Data.List functions, add more sanity checking flags by default This commit enables some extensions and GHC flags in the cabal file in a way that allows us to reduce the amount of prologuing on top of each file. We also prefix the usage of some List functions that removes ambiguity when they are also exported from the Prelude, like foldl'. In general, this has the effect of pointing out more explicitly that a linked list is used. Metric Increase: haddock.Cabal haddock.base haddock.compiler - - - - - 8c87d4e1 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00 Add test case for #23586 - - - - - 568de8a5 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00 When matching functions in rewrite rules: ignore multiplicity When matching a template variable to an expression, we check that it has the same type as the matched expression. But if the variable `f` has type `A -> B` while the expression `e` has type `A %1 -> B`, the match was previously rejected. A principled solution would have `f` substituted by `\(%Many x) -> e x` or some other appropriate coercion. But since linearity is not properly checked in Core, we can be cheeky and simply ignore multiplicity while matching. Much easier. This has forced a change in the linter which, when `-dlinear-core-lint` is off, must consider that `a -> b` and `a %1 -> b` are equal. This is achieved by adding an argument to configure the behaviour of `nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour which ignores multiplicities when comparing two `FunTy`. Fixes #24725. - - - - - c8a8727e by Simon Peyton Jones at 2024-06-20T19:29:12-04:00 Faster type equality This MR speeds up type equality, triggered by perf regressions that showed up when fixing #24725 by parameterising type equality over whether to ignore multiplicity. The changes are: * Do not use `nonDetCmpType` for type /equality/. Instead use a specialised type-equality function, which we have always had! `nonDetCmpType` remains, but I did not invest effort in refactoring or optimising it. * Type equality is parameterised by - whether to expand synonyms - whether to respect multiplicities - whether it has a RnEnv2 environment In this MR I systematically specialise it for static values of these parameters. Much more direct and predictable than before. See Note [Specialising type equality] * We want to avoid comparing kinds if possible. I refactored how this happens, at least for `eqType`. See Note [Casts and coercions in type comparison] * To make Lint fast, we want to avoid allocating a thunk for <msg> in ensureEqTypes ty1 ty2 <msg> because the test almost always succeeds, and <msg> isn't needed. See Note [INLINE ensureEqTys] Metric Decrease: T13386 T5030 - - - - - 9dfa0846 by Peter Trommler at 2024-06-21T12:17:32+02:00 PPC NCG: Fix sign hints in C calls Sign hints for parameters are in the second component of the pair. Fixes #23034 - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Multiplicity.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/WorkWrap.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/TyCo/Compare.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Hs.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Utils.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6d3d8a7a7045813d8d9583851738ccb44a6b6e3c...9dfa08465d28755afe77d2edf57457ed6366aef5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/6d3d8a7a7045813d8d9583851738ccb44a6b6e3c...9dfa08465d28755afe77d2edf57457ed6366aef5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 10:34:12 2024 From: gitlab at gitlab.haskell.org (Peter Trommler (@trommler)) Date: Fri, 21 Jun 2024 06:34:12 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T23034-ghc-9.10 Message-ID: <66755724adc86_2f9c28a434b891328@gitlab.mail> Peter Trommler pushed new branch wip/T23034-ghc-9.10 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T23034-ghc-9.10 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 10:38:30 2024 From: gitlab at gitlab.haskell.org (Peter Trommler (@trommler)) Date: Fri, 21 Jun 2024 06:38:30 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T23034-ghc-9.8 Message-ID: <66755826720c3_2f9c28ba6e40985b@gitlab.mail> Peter Trommler pushed new branch wip/T23034-ghc-9.8 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T23034-ghc-9.8 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 10:41:51 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 21 Jun 2024 06:41:51 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] fixup! ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Message-ID: <667558efb666e_2f9c28c4419010225c@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: d63c4930 by Rodrigo Mesquita at 2024-06-20T15:58:19+01:00 fixup! ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var - - - - - 4 changed files: - + compiler/GHC/Hs/Specificity.hs - compiler/GHC/Types/Var.hs - compiler/GHC/Types/Var.hs-boot - compiler/ghc.cabal.in Changes: ===================================== compiler/GHC/Hs/Specificity.hs ===================================== @@ -0,0 +1,52 @@ +{-# OPTIONS_GHC -Wno-orphans #-} +module GHC.Hs.Specificity where + +import Prelude +import Control.DeepSeq (NFData(..)) + +import GHC.Utils.Outputable +import GHC.Utils.Binary + +import Language.Haskell.Syntax.Specificity + +{- ********************************************************************* +* * +* ForAllTyFlag +* * +********************************************************************* -} + +instance Outputable ForAllTyFlag where + ppr Required = text "[req]" + ppr Specified = text "[spec]" + ppr Inferred = text "[infrd]" + +instance Binary Specificity where + put_ bh SpecifiedSpec = putByte bh 0 + put_ bh InferredSpec = putByte bh 1 + + get bh = do + h <- getByte bh + case h of + 0 -> return SpecifiedSpec + _ -> return InferredSpec + +instance Binary ForAllTyFlag where + put_ bh Required = putByte bh 0 + put_ bh Specified = putByte bh 1 + put_ bh Inferred = putByte bh 2 + + get bh = do + h <- getByte bh + case h of + 0 -> return Required + 1 -> return Specified + _ -> return Inferred + +instance NFData Specificity where + rnf SpecifiedSpec = () + rnf InferredSpec = () +instance NFData ForAllTyFlag where + rnf (Invisible spec) = rnf spec + rnf Required = () + + ===================================== compiler/GHC/Types/Var.hs ===================================== @@ -129,6 +129,7 @@ import GHC.Utils.Binary import GHC.Utils.Outputable import GHC.Utils.Panic +import GHC.Hs.Specificity () import Language.Haskell.Syntax.Specificity import Data.Data @@ -451,46 +452,6 @@ updateVarTypeM upd var result = do { ty' <- upd (varType var) ; return (var { varType = ty' }) } -{- ********************************************************************* -* * -* ForAllTyFlag -* * -********************************************************************* -} - -instance Outputable ForAllTyFlag where - ppr Required = text "[req]" - ppr Specified = text "[spec]" - ppr Inferred = text "[infrd]" - -instance Binary Specificity where - put_ bh SpecifiedSpec = putByte bh 0 - put_ bh InferredSpec = putByte bh 1 - - get bh = do - h <- getByte bh - case h of - 0 -> return SpecifiedSpec - _ -> return InferredSpec - -instance Binary ForAllTyFlag where - put_ bh Required = putByte bh 0 - put_ bh Specified = putByte bh 1 - put_ bh Inferred = putByte bh 2 - - get bh = do - h <- getByte bh - case h of - 0 -> return Required - 1 -> return Specified - _ -> return Inferred - -instance NFData Specificity where - rnf SpecifiedSpec = () - rnf InferredSpec = () -instance NFData ForAllTyFlag where - rnf (Invisible spec) = rnf spec - rnf Required = () - {- ********************************************************************* * * * FunTyFlag ===================================== compiler/GHC/Types/Var.hs-boot ===================================== @@ -2,7 +2,7 @@ module GHC.Types.Var where import {-# SOURCE #-} GHC.Types.Name -import Language.Haskell.Syntax.Specificity (Specificity, ForAllTyFlag) +import Language.Haskell.Syntax.Specificity (Specificity) data FunTyFlag data Var ===================================== compiler/ghc.cabal.in ===================================== @@ -535,6 +535,7 @@ Library GHC.Hs.Instances GHC.Hs.Lit GHC.Hs.Pat + GHC.Hs.Specificity GHC.Hs.Stats GHC.HsToCore GHC.HsToCore.Arrows View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d63c49305b66917063d30ddd300efc10c1841752 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d63c49305b66917063d30ddd300efc10c1841752 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 11:28:13 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 21 Jun 2024 07:28:13 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] keep track of GlobalRegUse for register allocation Message-ID: <667563cd38e61_2f9c281261028112852@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: eecb6387 by sheaf at 2024-06-21T13:27:44+02:00 keep track of GlobalRegUse for register allocation - - - - - 24 changed files: - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/AArch64.hs - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/PPC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Regs.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/CmmToLlvm/Ppr.hs - compiler/GHC/StgToCmm/Monad.hs Changes: ===================================== compiler/GHC/Cmm.hs ===================================== @@ -100,7 +100,7 @@ data GenCmmDecl d h g = CmmProc -- A procedure h -- Extra header such as the info table CLabel -- Entry label - [GlobalReg] -- Registers live on entry. Note that the set of live + [GlobalRegUse] -- Registers live on entry. Note that the set of live -- registers will be correct in generated C-- code, but -- not in hand-written C-- code. However, -- splitAtProcPoints calculates correct liveness ===================================== compiler/GHC/Cmm/Graph.hs ===================================== @@ -208,7 +208,7 @@ mkJump profile conv e actuals updfr_off = -- | A jump where the caller says what the live GlobalRegs are. Used -- for low-level hand-written Cmm. -mkRawJump :: Profile -> CmmExpr -> UpdFrameOffset -> [GlobalReg] +mkRawJump :: Profile -> CmmExpr -> UpdFrameOffset -> [GlobalRegUse] -> CmmAGraph mkRawJump profile e updfr_off vols = lastWithArgs profile Jump Old NativeNodeCall [] updfr_off $ @@ -297,7 +297,7 @@ stackStubExpr w = CmmLit (CmmInt 0 w) copyInOflow :: Profile -> Convention -> Area -> [CmmFormal] -> [CmmFormal] - -> (Int, [GlobalReg], CmmAGraph) + -> (Int, [GlobalRegUse], CmmAGraph) copyInOflow profile conv area formals extra_stk = (offset, gregs, catAGraphs $ map mkMiddle nodes) @@ -308,9 +308,9 @@ copyInOflow profile conv area formals extra_stk copyIn :: Profile -> Convention -> Area -> [CmmFormal] -> [CmmFormal] - -> (ByteOff, [GlobalReg], [CmmNode O O]) + -> (ByteOff, [GlobalRegUse], [CmmNode O O]) copyIn profile conv area formals extra_stk - = (stk_size, [r | (_, RegisterParam r) <- args], map ci (stk_args ++ args)) + = (stk_size, [GlobalRegUse r (localRegType lr)| (lr, RegisterParam r) <- args], map ci (stk_args ++ args)) where platform = profilePlatform profile @@ -365,7 +365,7 @@ data Transfer = Call | JumpRet | Jump | Ret deriving Eq copyOutOflow :: Profile -> Convention -> Transfer -> Area -> [CmmExpr] -> UpdFrameOffset -> [CmmExpr] -- extra stack args - -> (Int, [GlobalReg], CmmAGraph) + -> (Int, [GlobalRegUse], CmmAGraph) -- Generate code to move the actual parameters into the locations -- required by the calling convention. This includes a store for the @@ -383,8 +383,8 @@ copyOutOflow profile conv transfer area actuals updfr_off extra_stack_stuff (regs, graph) = foldr co ([], mkNop) (setRA ++ args ++ stack_params) co :: (CmmExpr, ParamLocation) - -> ([GlobalReg], CmmAGraph) - -> ([GlobalReg], CmmAGraph) + -> ([GlobalRegUse], CmmAGraph) + -> ([GlobalRegUse], CmmAGraph) co (v, RegisterParam r@(VanillaReg {})) (rs, ms) = let width = cmmExprWidth platform v value @@ -393,12 +393,14 @@ copyOutOflow profile conv transfer area actuals updfr_off extra_stack_stuff | width < wordWidth platform = CmmMachOp (MO_XX_Conv width (wordWidth platform)) [v] | otherwise = panic "Parameter width greater than word width" + ru = GlobalRegUse r (cmmExprType platform value) - in (r:rs, mkAssign (CmmGlobal $ GlobalRegUse r (cmmExprType platform value)) value <*> ms) + in (ru:rs, mkAssign (CmmGlobal ru) value <*> ms) -- Non VanillaRegs co (v, RegisterParam r) (rs, ms) = - (r:rs, mkAssign (CmmGlobal $ GlobalRegUse r (cmmExprType platform v)) v <*> ms) + let ru = GlobalRegUse r (cmmExprType platform v) + in (ru:rs, mkAssign (CmmGlobal ru) v <*> ms) co (v, StackParam off) (rs, ms) = (rs, mkStore (CmmStackSlot area off) (value v) <*> ms) @@ -461,13 +463,13 @@ copyOutOflow profile conv transfer area actuals updfr_off extra_stack_stuff mkCallEntry :: Profile -> Convention -> [CmmFormal] -> [CmmFormal] - -> (Int, [GlobalReg], CmmAGraph) + -> (Int, [GlobalRegUse], CmmAGraph) mkCallEntry profile conv formals extra_stk = copyInOflow profile conv Old formals extra_stk lastWithArgs :: Profile -> Transfer -> Area -> Convention -> [CmmExpr] -> UpdFrameOffset - -> (ByteOff -> [GlobalReg] -> CmmAGraph) + -> (ByteOff -> [GlobalRegUse] -> CmmAGraph) -> CmmAGraph lastWithArgs profile transfer area conv actuals updfr_off last = lastWithArgsAndExtraStack profile transfer area conv actuals @@ -476,7 +478,7 @@ lastWithArgs profile transfer area conv actuals updfr_off last = lastWithArgsAndExtraStack :: Profile -> Transfer -> Area -> Convention -> [CmmExpr] -> UpdFrameOffset -> [CmmExpr] - -> (ByteOff -> [GlobalReg] -> CmmAGraph) + -> (ByteOff -> [GlobalRegUse] -> CmmAGraph) -> CmmAGraph lastWithArgsAndExtraStack profile transfer area conv actuals updfr_off extra_stack last = @@ -490,7 +492,7 @@ noExtraStack :: [CmmExpr] noExtraStack = [] toCall :: CmmExpr -> Maybe BlockId -> UpdFrameOffset -> ByteOff - -> ByteOff -> [GlobalReg] + -> ByteOff -> [GlobalRegUse] -> CmmAGraph toCall e cont updfr_off res_space arg_space regs = mkLast $ CmmCall e cont regs arg_space res_space updfr_off ===================================== compiler/GHC/Cmm/Liveness.hs ===================================== @@ -59,7 +59,7 @@ cmmLocalLiveness platform graph = check facts = noLiveOnEntry entry (expectJust "check" $ mapLookup entry facts) facts -cmmGlobalLiveness :: Platform -> CmmGraph -> BlockEntryLiveness GlobalReg +cmmGlobalLiveness :: Platform -> CmmGraph -> BlockEntryLiveness GlobalRegUse cmmGlobalLiveness platform graph = analyzeCmmBwd liveLattice (xferLive platform) graph mapEmpty @@ -92,7 +92,7 @@ xferLive platform (BlockCC eNode middle xNode) fBase = !result = foldNodesBwdOO (gen_kill platform) middle joined in mapSingleton (entryLabel eNode) result {-# SPECIALIZE xferLive :: Platform -> TransferFun (CmmLive LocalReg) #-} -{-# SPECIALIZE xferLive :: Platform -> TransferFun (CmmLive GlobalReg) #-} +{-# SPECIALIZE xferLive :: Platform -> TransferFun (CmmLive GlobalRegUse) #-} ----------------------------------------------------------------------------- -- | Specialization that only retains the keys for local variables. ===================================== compiler/GHC/Cmm/Node.hs ===================================== @@ -118,7 +118,7 @@ data CmmNode e x where -- occur in CmmExprs, namely as (CmmLit (CmmBlock b)) or -- (CmmStackSlot (Young b) _). - cml_args_regs :: [GlobalReg], + cml_args_regs :: [GlobalRegUse], -- The argument GlobalRegs (Rx, Fx, Dx, Lx) that are passed -- to the call. This is essential information for the -- native code generator's register allocator; without @@ -544,7 +544,7 @@ instance UserOfRegs LocalReg (CmmNode e x) where => (b -> LocalReg -> b) -> b -> a -> b fold f z n = foldRegsUsed platform f z n -instance UserOfRegs GlobalReg (CmmNode e x) where +instance UserOfRegs GlobalRegUse (CmmNode e x) where {-# INLINEABLE foldRegsUsed #-} foldRegsUsed platform f !z n = case n of CmmAssign _ expr -> fold f z expr @@ -555,8 +555,8 @@ instance UserOfRegs GlobalReg (CmmNode e x) where CmmCall {cml_target=tgt, cml_args_regs=args} -> fold f (fold f z args) tgt CmmForeignCall {tgt=tgt, args=args} -> fold f (fold f z tgt) args _ -> z - where fold :: forall a b. UserOfRegs GlobalReg a - => (b -> GlobalReg -> b) -> b -> a -> b + where fold :: forall a b. UserOfRegs GlobalRegUse a + => (b -> GlobalRegUse -> b) -> b -> a -> b fold f z n = foldRegsUsed platform f z n instance (Ord r, UserOfRegs r CmmReg) => UserOfRegs r ForeignTarget where -- The (Ord r) in the context is necessary here @@ -576,7 +576,7 @@ instance DefinerOfRegs LocalReg (CmmNode e x) where => (b -> LocalReg -> b) -> b -> a -> b fold f z n = foldRegsDefd platform f z n -instance DefinerOfRegs GlobalReg (CmmNode e x) where +instance DefinerOfRegs GlobalRegUse (CmmNode e x) where {-# INLINEABLE foldRegsDefd #-} foldRegsDefd platform f !z n = case n of CmmAssign lhs _ -> fold f z lhs @@ -585,12 +585,13 @@ instance DefinerOfRegs GlobalReg (CmmNode e x) where CmmForeignCall {} -> fold f z activeRegs -- See Note [Safe foreign calls clobber STG registers] _ -> z - where fold :: forall a b. DefinerOfRegs GlobalReg a - => (b -> GlobalReg -> b) -> b -> a -> b + where fold :: forall a b. DefinerOfRegs GlobalRegUse a + => (b -> GlobalRegUse -> b) -> b -> a -> b fold f z n = foldRegsDefd platform f z n - activeRegs = activeStgRegs platform - activeCallerSavesRegs = filter (callerSaves platform) activeRegs + activeRegs :: [GlobalRegUse] + activeRegs = map (\ r -> GlobalRegUse r (globalRegSpillType platform r)) $ activeStgRegs platform + activeCallerSavesRegs = filter (callerSaves platform . globalRegUseGlobalReg) activeRegs foreignTargetRegs (ForeignTarget _ (ForeignConvention _ _ _ CmmNeverReturns)) = [] foreignTargetRegs _ = activeCallerSavesRegs ===================================== compiler/GHC/Cmm/Parser.y ===================================== @@ -770,13 +770,15 @@ safety :: { Safety } : {- empty -} { PlayRisky } | STRING {% parseSafety $1 } -vols :: { [GlobalReg] } +vols :: { [GlobalRegUse] } : '[' ']' { [] } - | '[' '*' ']' {% do platform <- PD.getPlatform - ; return (realArgRegsCover platform) } - -- All of them. See comment attached - -- to realArgRegsCover - | '[' globals ']' { map globalRegUseGlobalReg $2 } + | '[' '*' ']' {% do platform <- PD.getPlatform; + let { gregs = realArgRegsCover platform + ; uses = map (\gr -> GlobalRegUse gr (globalRegSpillType platform gr)) gregs }; + return uses } + -- All of them. See comment attached + -- to realArgRegsCover + | '[' globals ']' { $2 } globals :: { [GlobalRegUse] } : GLOBALREG { [$1] } @@ -1374,7 +1376,7 @@ mkReturnSimple profile actuals updfr_off = where e = entryCode platform (cmmLoadGCWord platform (CmmStackSlot Old updfr_off)) platform = profilePlatform profile -doRawJump :: CmmParse CmmExpr -> [GlobalReg] -> CmmParse () +doRawJump :: CmmParse CmmExpr -> [GlobalRegUse] -> CmmParse () doRawJump expr_code vols = do profile <- getProfile expr <- expr_code ===================================== compiler/GHC/Cmm/ProcPoint.hs ===================================== @@ -262,7 +262,7 @@ splitAtProcPoints platform entry_label callPPs procPoints procMap cmmProc = do let liveness = cmmGlobalLiveness platform g - let ppLiveness pp = filter isArgReg $ regSetToList $ + let ppLiveness pp = filter (isArgReg . globalRegUseGlobalReg) $ regSetToList $ expectJust "ppLiveness" $ mapLookup pp liveness graphEnv <- return $ foldlGraphBlocks add_block mapEmpty g ===================================== compiler/GHC/Cmm/Sink.hs ===================================== @@ -709,7 +709,7 @@ conflicts platform (r, rhs, addr) node globalRegistersConflict :: Platform -> CmmExpr -> CmmNode e x -> Bool globalRegistersConflict platform expr node = -- See Note [Inlining foldRegsDefd] - inline foldRegsDefd platform (\b r -> b || globalRegUsedIn platform r expr) + inline foldRegsDefd platform (\b r -> b || globalRegUsedIn platform (globalRegUseGlobalReg r) expr) False node -- Returns True if node defines any local registers that are used in the ===================================== compiler/GHC/CmmToAsm/AArch64.hs ===================================== @@ -44,7 +44,7 @@ ncgAArch64 config -- | Instruction instance for aarch64 instance Instruction AArch64.Instr where regUsageOfInstr = AArch64.regUsageOfInstr - patchRegsOfInstr = AArch64.patchRegsOfInstr + patchRegsOfInstr _ = AArch64.patchRegsOfInstr isJumpishInstr = AArch64.isJumpishInstr jumpDestsOfInstr = AArch64.jumpDestsOfInstr canFallthroughTo = AArch64.canFallthroughTo ===================================== compiler/GHC/CmmToAsm/Instr.hs ===================================== @@ -62,7 +62,9 @@ class Instruction instr where -- | Apply a given mapping to all the register references in this -- instruction. patchRegsOfInstr - :: instr + :: HasDebugCallStack + => Platform + -> instr -> (Reg -> Reg) -> instr ===================================== compiler/GHC/CmmToAsm/PPC.hs ===================================== @@ -43,7 +43,7 @@ ncgPPC config = NcgImpl -- | Instruction instance for powerpc instance Instruction PPC.Instr where regUsageOfInstr = PPC.regUsageOfInstr - patchRegsOfInstr = PPC.patchRegsOfInstr + patchRegsOfInstr _ = PPC.patchRegsOfInstr isJumpishInstr = PPC.isJumpishInstr jumpDestsOfInstr = PPC.jumpDestsOfInstr canFallthroughTo = PPC.canFallthroughTo ===================================== compiler/GHC/CmmToAsm/PPC/CodeGen.hs ===================================== @@ -195,8 +195,11 @@ stmtToInstrs stmt = do _ -> panic "stmtToInstrs: statement should have been cps'd away" -jumpRegs :: Platform -> [GlobalReg] -> [Reg] -jumpRegs platform gregs = [ RegReal r | Just r <- map (globalRegMaybe platform) gregs ] +jumpRegs :: Platform -> [GlobalRegUse] -> [RegFormat] +jumpRegs platform gregs = + [ RegFormat (RegReal r) (cmmTypeFormat ty) + | GlobalRegUse gr ty <- gregs + , Just r <- [globalRegMaybe platform gr] ] -------------------------------------------------------------------------------- -- | 'InstrBlock's are the insn sequences generated by the insn selectors. @@ -1091,7 +1094,7 @@ assignReg_FltCode = assignReg_IntCode -genJump :: CmmExpr{-the branch target-} -> [Reg] -> NatM InstrBlock +genJump :: CmmExpr{-the branch target-} -> [RegFormat] -> NatM InstrBlock genJump (CmmLit (CmmLabel lbl)) regs = return (unitOL $ JMP lbl regs) @@ -1101,7 +1104,7 @@ genJump tree gregs platform <- getPlatform genJump' tree (platformToGCP platform) gregs -genJump' :: CmmExpr -> GenCCallPlatform -> [Reg] -> NatM InstrBlock +genJump' :: CmmExpr -> GenCCallPlatform -> [RegFormat] -> NatM InstrBlock genJump' tree (GCP64ELF 1) regs = do ===================================== compiler/GHC/CmmToAsm/PPC/Instr.hs ===================================== @@ -221,11 +221,11 @@ data Instr -- Just True: branch likely taken -- Just False: branch likely not taken -- Nothing: no hint - | JMP CLabel [Reg] -- same as branch, + | JMP CLabel [RegFormat] -- same as branch, -- but with CLabel instead of block ID -- and live global registers | MTCTR Reg - | BCTR [Maybe BlockId] (Maybe CLabel) [Reg] + | BCTR [Maybe BlockId] (Maybe CLabel) [RegFormat] -- with list of local destinations, and -- jump table location if necessary | BL CLabel [Reg] -- with list of argument regs @@ -333,9 +333,9 @@ regUsageOfInstr platform instr CMPL _ reg ri -> usage (reg : regRI ri,[]) BCC _ _ _ -> noUsage BCCFAR _ _ _ -> noUsage - JMP _ regs -> usage (regs, []) + JMP _ regs -> usage (map regFormatReg regs, []) MTCTR reg -> usage ([reg],[]) - BCTR _ _ regs -> usage (regs, []) + BCTR _ _ regs -> usage (map regFormatReg regs, []) BL _ params -> usage (params, callClobberedRegs platform) BCTRL params -> usage (params, callClobberedRegs platform) ===================================== compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs ===================================== @@ -208,9 +208,9 @@ regSpill_instr platform regSlotMap (LiveInstr instr (Just _)) = do let rsSpillModify = filter (\r -> elemUFM (regFormatReg r) regSlotMap) rsModify -- rewrite the instr and work out spill code. - (instr1, prepost1) <- mapAccumLM (spillRead regSlotMap) instr rsSpillRead - (instr2, prepost2) <- mapAccumLM (spillWrite regSlotMap) instr1 rsSpillWritten - (instr3, prepost3) <- mapAccumLM (spillModify regSlotMap) instr2 rsSpillModify + (instr1, prepost1) <- mapAccumLM (spillRead platform regSlotMap) instr rsSpillRead + (instr2, prepost2) <- mapAccumLM (spillWrite platform regSlotMap) instr1 rsSpillWritten + (instr3, prepost3) <- mapAccumLM (spillModify platform regSlotMap) instr2 rsSpillModify let (mPrefixes, mPostfixes) = unzip (prepost1 ++ prepost2 ++ prepost3) let prefixes = concat mPrefixes @@ -228,14 +228,15 @@ regSpill_instr platform regSlotMap (LiveInstr instr (Just _)) = do -- writes to a vreg that is being spilled. spillRead :: Instruction instr - => UniqFM Reg Int + => Platform + -> UniqFM Reg Int -> instr -> RegFormat -> SpillM (instr, ([LiveInstr instr'], [LiveInstr instr'])) -spillRead regSlotMap instr (RegFormat reg fmt) +spillRead platform regSlotMap instr (RegFormat reg fmt) | Just slot <- lookupUFM regSlotMap reg - = do (instr', nReg) <- patchInstr reg instr + = do (instr', nReg) <- patchInstr platform reg instr modify $ \s -> s { stateSpillSL = addToUFM_C accSpillSL (stateSpillSL s) reg (reg, 0, 1) } @@ -251,14 +252,15 @@ spillRead regSlotMap instr (RegFormat reg fmt) -- writes to a vreg that is being spilled. spillWrite :: Instruction instr - => UniqFM Reg Int + => Platform + -> UniqFM Reg Int -> instr -> RegFormat -> SpillM (instr, ([LiveInstr instr'], [LiveInstr instr'])) -spillWrite regSlotMap instr (RegFormat reg fmt) +spillWrite platform regSlotMap instr (RegFormat reg fmt) | Just slot <- lookupUFM regSlotMap reg - = do (instr', nReg) <- patchInstr reg instr + = do (instr', nReg) <- patchInstr platform reg instr modify $ \s -> s { stateSpillSL = addToUFM_C accSpillSL (stateSpillSL s) reg (reg, 1, 0) } @@ -274,14 +276,15 @@ spillWrite regSlotMap instr (RegFormat reg fmt) -- both reads and writes to a vreg that is being spilled. spillModify :: Instruction instr - => UniqFM Reg Int + => Platform + -> UniqFM Reg Int -> instr -> RegFormat -> SpillM (instr, ([LiveInstr instr'], [LiveInstr instr'])) -spillModify regSlotMap instr (RegFormat reg fmt) +spillModify platform regSlotMap instr (RegFormat reg fmt) | Just slot <- lookupUFM regSlotMap reg - = do (instr', nReg) <- patchInstr reg instr + = do (instr', nReg) <- patchInstr platform reg instr modify $ \s -> s { stateSpillSL = addToUFM_C accSpillSL (stateSpillSL s) reg (reg, 1, 1) } @@ -297,9 +300,9 @@ spillModify regSlotMap instr (RegFormat reg fmt) -- virtual reg. patchInstr :: Instruction instr - => Reg -> instr -> SpillM (instr, Reg) + => Platform -> Reg -> instr -> SpillM (instr, Reg) -patchInstr reg instr +patchInstr platform reg instr = do nUnique <- newUnique -- The register we're rewriting is supposed to be virtual. @@ -312,19 +315,19 @@ patchInstr reg instr RegReal{} -> panic "RegAlloc.Graph.Spill.patchIntr: not patching real reg" - let instr' = patchReg1 reg nReg instr + let instr' = patchReg1 platform reg nReg instr return (instr', nReg) patchReg1 :: Instruction instr - => Reg -> Reg -> instr -> instr + => Platform -> Reg -> Reg -> instr -> instr -patchReg1 old new instr +patchReg1 platform old new instr = let patchF r | r == old = new | otherwise = r - in patchRegsOfInstr instr patchF + in patchRegsOfInstr platform instr patchF -- Spiller monad -------------------------------------------------------------- ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -575,7 +575,7 @@ genRaInsn block_live new_instrs block_id instr r_dying w_dying = do patched_instr :: instr patched_instr - = patchRegsOfInstr adjusted_instr patchLookup + = patchRegsOfInstr platform adjusted_instr patchLookup patchLookup :: Reg -> Reg patchLookup x ===================================== compiler/GHC/CmmToAsm/Reg/Linear/X86.hs ===================================== @@ -32,12 +32,12 @@ getFreeRegs platform cls (FreeRegs f) = case cls of RcInteger -> [ RealRegSingle i - | i <- [ 0 .. lastint platform ] + | i <- intregnos platform , testBit f i ] RcFloatOrVector -> [ RealRegSingle i - | i <- [ lastint platform + 1 .. lastxmm platform ] + | i <- xmmregnos platform , testBit f i ] ===================================== compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs ===================================== @@ -32,12 +32,12 @@ getFreeRegs platform cls (FreeRegs f) = case cls of RcInteger -> [ RealRegSingle i - | i <- [ 0 .. lastint platform ] + | i <- intregnos platform , testBit f i ] RcFloatOrVector -> [ RealRegSingle i - | i <- [ lastint platform + 1 .. lastxmm platform ] + | i <- xmmregnos platform , testBit f i ] ===================================== compiler/GHC/CmmToAsm/Reg/Liveness.hs ===================================== @@ -114,9 +114,9 @@ instance Instruction instr => Instruction (InstrSR instr) where SPILL reg _ -> RU [reg] [] RELOAD _ reg -> RU [] [reg] - patchRegsOfInstr i f + patchRegsOfInstr platform i f = case i of - Instr instr -> Instr (patchRegsOfInstr instr f) + Instr instr -> Instr (patchRegsOfInstr platform instr f) SPILL reg slot -> SPILL (updReg f reg) slot RELOAD slot reg -> RELOAD slot (updReg f reg) where @@ -648,7 +648,7 @@ patchEraseLive platform patchF cmm | otherwise = li' : patchInstrs lis - where li' = patchRegsLiveInstr patchF li + where li' = patchRegsLiveInstr platform patchF li eatMe r1 r2 live -- source and destination regs are the same @@ -666,17 +666,18 @@ patchEraseLive platform patchF cmm -- patchRegsLiveInstr :: (Instruction instr, HasDebugCallStack) - => (Reg -> Reg) + => Platform + -> (Reg -> Reg) -> LiveInstr instr -> LiveInstr instr -patchRegsLiveInstr patchF li +patchRegsLiveInstr platform patchF li = case li of LiveInstr instr Nothing - -> LiveInstr (patchRegsOfInstr instr patchF) Nothing + -> LiveInstr (patchRegsOfInstr platform instr patchF) Nothing LiveInstr instr (Just live) -> LiveInstr - (patchRegsOfInstr instr patchF) + (patchRegsOfInstr platform instr patchF) (Just live { -- WARNING: have to go via lists here because patchF changes the uniq in the Reg liveBorn = mapRegFormatSet patchF $ liveBorn live ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -378,8 +378,11 @@ stmtToInstrs bid stmt = do panic "stmtToInstrs: statement should have been cps'd away" -jumpRegs :: Platform -> [GlobalReg] -> [Reg] -jumpRegs platform gregs = [ RegReal r | Just r <- map (globalRegMaybe platform) gregs ] +jumpRegs :: Platform -> [GlobalRegUse] -> [RegFormat] +jumpRegs platform gregs = + [ RegFormat (RegReal r) (cmmTypeFormat ty) + | GlobalRegUse gr ty <- gregs + , Just r <- [globalRegMaybe platform gr] ] -------------------------------------------------------------------------------- -- | 'InstrBlock's are the insn sequences generated by the insn selectors. @@ -535,6 +538,8 @@ mkMOV platform fmt op1 op2 = cls1 = case op1 of { OpReg r1 -> Just (targetClassOfReg platform r1); _ -> Nothing } cls2 = case op2 of { OpReg r2 -> Just (targetClassOfReg platform r2); _ -> Nothing } + + assignMem_I64Code :: CmmExpr -> CmmExpr -> NatM InstrBlock assignMem_I64Code addrTree valueTree = do platform <- getPlatform @@ -2848,7 +2853,7 @@ assignReg_VecCode format reg src = do let flag = use_avx || use_sse return (src_code (getVecRegisterReg platform flag format reg)) -genJump :: CmmExpr{-the branch target-} -> [Reg] -> NatM InstrBlock +genJump :: CmmExpr{-the branch target-} -> [RegFormat] -> NatM InstrBlock genJump (CmmLoad mem _ _) regs = do Amode target code <- getAmode mem @@ -3479,11 +3484,11 @@ genCCall64 addr conv dest_regs args = do let prom_args = map (maybePromoteCArg platform W32) args let load_args :: [CmmExpr] - -> [Reg] -- int regs avail for args - -> [Reg] -- FP regs avail for args + -> [RegFormat] -- int regs avail for args + -> [RegFormat] -- FP regs avail for args -> InstrBlock -- code computing args -> InstrBlock -- code assigning args to ABI regs - -> NatM ([CmmExpr],[Reg],[Reg],InstrBlock,InstrBlock) + -> NatM ([CmmExpr],[RegFormat],[RegFormat],InstrBlock,InstrBlock) -- no more regs to use load_args args [] [] code acode = return (args, [], [], code, acode) @@ -3495,12 +3500,12 @@ genCCall64 addr conv dest_regs args = do load_args (arg : rest) aregs fregs code acode | isFloatType arg_rep = case fregs of [] -> push_this_arg - (r:rs) -> do + (RegFormat r _fmt:rs) -> do (code',acode') <- reg_this_arg r load_args rest aregs rs code' acode' | otherwise = case aregs of [] -> push_this_arg - (r:rs) -> do + (RegFormat r _fmt:rs) -> do (code',acode') <- reg_this_arg r load_args rest rs fregs code' acode' where @@ -3540,11 +3545,11 @@ genCCall64 addr conv dest_regs args = do arg_fmt = cmmTypeFormat arg_rep load_args_win :: [CmmExpr] - -> [Reg] -- used int regs - -> [Reg] -- used FP regs + -> [RegFormat] -- used int regs + -> [RegFormat] -- used FP regs -> [(Reg, Reg)] -- (int, FP) regs avail for args -> InstrBlock - -> NatM ([CmmExpr],[Reg],[Reg],InstrBlock,InstrBlock) + -> NatM ([CmmExpr],[RegFormat],[RegFormat],InstrBlock,InstrBlock) load_args_win args usedInt usedFP [] code = return (args, usedInt, usedFP, code, nilOL) -- no more regs to use @@ -3555,16 +3560,19 @@ genCCall64 addr conv dest_regs args = do ((ireg, freg) : regs) code | isFloatType arg_rep = do arg_code <- getAnyReg arg - load_args_win rest (ireg : usedInt) (freg : usedFP) regs + load_args_win rest (mkRegFormat platform ireg II64: usedInt) (mkRegFormat platform freg FF64 : usedFP) regs (code `appOL` arg_code freg `snocOL` -- If we are calling a varargs function -- then we need to define ireg as well -- as freg - mkMOV platform II64 (OpReg freg) (OpReg ireg)) + CVTTSD2SIQ II64 (OpReg freg) ireg) + -- SLD TODO: I changed this from MOV FF64 (OpReg freg) (OpReg ireg) + -- to CVTTSD2SIQ ... + -- because it is going between two different types of register | otherwise = do arg_code <- getAnyReg arg - load_args_win rest (ireg : usedInt) usedFP regs + load_args_win rest (mkRegFormat platform ireg II64: usedInt) usedFP regs (code `appOL` arg_code ireg) where arg_rep = cmmExprType platform arg @@ -3611,19 +3619,20 @@ genCCall64 addr conv dest_regs args = do if platformOS platform == OSMinGW32 then load_args_win prom_args [] [] (allArgRegs platform) nilOL else do + let intArgRegs = map (\r -> mkRegFormat platform r II64) $ allIntArgRegs platform + fpArgRegs = map (\r -> mkRegFormat platform r FF64) $ allFPArgRegs platform (stack_args, aregs, fregs, load_args_code, assign_args_code) - <- load_args prom_args (allIntArgRegs platform) - (allFPArgRegs platform) - nilOL nilOL + <- load_args prom_args intArgRegs fpArgRegs nilOL nilOL let used_regs rs as = dropTail (length rs) as - fregs_used = used_regs fregs (allFPArgRegs platform) - aregs_used = used_regs aregs (allIntArgRegs platform) + fregs_used = used_regs fregs fpArgRegs + aregs_used = used_regs aregs intArgRegs return (stack_args, aregs_used, fregs_used, load_args_code , assign_args_code) let + wordFmt = archWordFormat (target32Bit platform) arg_regs_used = int_regs_used ++ fp_regs_used - arg_regs = [eax] ++ arg_regs_used + arg_regs = [mkRegFormat platform eax wordFmt] ++ arg_regs_used -- for annotating the call instruction with sse_regs = length fp_regs_used arg_stack_slots = if platformOS platform == OSMinGW32 ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -71,7 +71,7 @@ import GHC.Types.Basic (Alignment) import GHC.Cmm.DebugBlock (UnwindTable) import GHC.Utils.Misc ( HasDebugCallStack ) -import Data.Maybe (fromMaybe) +import GHC.Data.Maybe -- Format of an x86/x86_64 memory address, in bytes. -- @@ -316,7 +316,7 @@ data Instr -- | POPA -- Jumping around. - | JMP Operand [Reg] -- including live Regs at the call + | JMP Operand [RegFormat] -- including live Regs at the call | JXX Cond BlockId -- includes unconditional branches | JXX_GBL Cond Imm -- non-local version of JXX -- Table jump @@ -326,7 +326,7 @@ data Instr CLabel -- Label of jump table -- | X86 call instruction | CALL (Either Imm Reg) -- ^ Jump target - [Reg] -- ^ Arguments (required for register allocation) + [RegFormat] -- ^ Arguments (required for register allocation) -- Other things. | CLTD Format -- sign extend %eax into %edx:%eax @@ -420,7 +420,7 @@ regUsageOfInstr platform instr = case instr of MOV fmt src dst -> usageRW fmt src dst MOVD fmt src dst -> usageRW fmt src dst - CMOV _ fmt src dst -> mkRU fmt (use_R src [dst]) [dst] + CMOV _ fmt src dst -> mkRU (use_R fmt src [mk fmt dst]) [mk fmt dst] MOVZxL fmt src dst -> usageRW fmt src dst MOVSxL fmt src dst -> usageRW fmt src dst LEA fmt src dst -> usageRW fmt src dst @@ -431,80 +431,80 @@ regUsageOfInstr platform instr IMUL fmt src dst -> usageRM fmt src dst -- Result of IMULB will be in just in %ax - IMUL2 II8 src -> mkRU II8 (eax:use_R src []) [eax] + IMUL2 II8 src -> mkRU (mk II8 eax:use_R II8 src []) [mk II8 eax] -- Result of IMUL for wider values, will be split between %dx/%edx/%rdx and -- %ax/%eax/%rax. - IMUL2 fmt src -> mkRU fmt (eax:use_R src []) [eax,edx] + IMUL2 fmt src -> mkRU (mk fmt eax:use_R fmt src []) [mk fmt eax,mk fmt edx] MUL fmt src dst -> usageRM fmt src dst - MUL2 fmt src -> mkRU fmt (eax:use_R src []) [eax,edx] - DIV fmt op -> mkRU fmt (eax:edx:use_R op []) [eax,edx] - IDIV fmt op -> mkRU fmt (eax:edx:use_R op []) [eax,edx] + MUL2 fmt src -> mkRU (mk fmt eax:use_R fmt src []) [mk fmt eax,mk fmt edx] + DIV fmt op -> mkRU (mk fmt eax:mk fmt edx:use_R fmt op []) [mk fmt eax, mk fmt edx] + IDIV fmt op -> mkRU (mk fmt eax:mk fmt edx:use_R fmt op []) [mk fmt eax, mk fmt edx] ADD_CC fmt src dst -> usageRM fmt src dst SUB_CC fmt src dst -> usageRM fmt src dst AND fmt src dst -> usageRM fmt src dst OR fmt src dst -> usageRM fmt src dst XOR fmt (OpReg src) (OpReg dst) - | src == dst -> mkRU fmt [] [dst] + | src == dst -> mkRU [] [mk fmt dst] XOR fmt src dst -> usageRM fmt src dst NOT fmt op -> usageM fmt op - BSWAP fmt reg -> mkRU fmt [reg] [reg] + BSWAP fmt reg -> mkRU [mk fmt reg] [mk fmt reg] NEGI fmt op -> usageM fmt op SHL fmt imm dst -> usageRM fmt imm dst SAR fmt imm dst -> usageRM fmt imm dst SHR fmt imm dst -> usageRM fmt imm dst SHLD fmt imm dst1 dst2 -> usageRMM fmt imm dst1 dst2 SHRD fmt imm dst1 dst2 -> usageRMM fmt imm dst1 dst2 - BT fmt _ src -> mkRUR fmt (use_R src []) - - PUSH fmt op -> mkRUR fmt (use_R op []) - POP fmt op -> mkRU fmt [] (def_W op) - TEST fmt src dst -> mkRUR fmt (use_R src $! use_R dst []) - CMP fmt src dst -> mkRUR fmt (use_R src $! use_R dst []) - SETCC _ op -> mkRUFormat [] (def_W op) - JXX _ _ -> mkRUFormat [] [] - JXX_GBL _ _ -> mkRUFormat [] [] - JMP op regs -> mkRUFormat (use_R op regs) [] - JMP_TBL op _ _ _ -> mkRUFormat (use_R op []) [] - CALL (Left _) params -> mkRUFormat params (callClobberedRegs platform) - CALL (Right reg) params -> mkRUFormat (reg:params) (callClobberedRegs platform) - CLTD fmt -> mkRU fmt [eax] [edx] - NOP -> mkRUFormat [] [] - - X87Store fmt dst -> mkRUR fmt ( use_EA dst []) - - CVTSS2SD src dst -> mkRUFormat [src] [dst] - CVTSD2SS src dst -> mkRUFormat [src] [dst] - CVTTSS2SIQ _ src dst -> mkRUFormat (use_R src []) [dst] - CVTTSD2SIQ _ src dst -> mkRUFormat (use_R src []) [dst] - CVTSI2SS _ src dst -> mkRUFormat (use_R src []) [dst] - CVTSI2SD _ src dst -> mkRUFormat (use_R src []) [dst] + BT fmt _ src -> mkRUR (use_R fmt src []) + + PUSH fmt op -> mkRUR (use_R fmt op []) + POP fmt op -> mkRU [] (def_W fmt op) + TEST fmt src dst -> mkRUR (use_R fmt src $! use_R fmt dst []) + CMP fmt src dst -> mkRUR (use_R fmt src $! use_R fmt dst []) + SETCC _ op -> mkRU [] (def_W II8 op) + JXX _ _ -> mkRU [] [] + JXX_GBL _ _ -> mkRU [] [] + JMP op regs -> mkRU (use_R addrFmt op regs) [] + JMP_TBL op _ _ _ -> mkRU (use_R addrFmt op []) [] + CALL (Left _) params -> mkRU params (map mkFmt $ callClobberedRegs platform) + CALL (Right reg) params -> mkRU (mk addrFmt reg:params) (map mkFmt $ callClobberedRegs platform) + CLTD fmt -> mkRU [mk fmt eax] [mk fmt edx] + NOP -> mkRU [] [] + + X87Store _fmt dst -> mkRUR ( use_EA dst []) + + CVTSS2SD src dst -> mkRU [mk FF32 src] [mk FF64 dst] + CVTSD2SS src dst -> mkRU [mk FF64 src] [mk FF32 dst] + CVTTSS2SIQ fmt src dst -> mkRU (use_R FF32 src []) [mk fmt dst] + CVTTSD2SIQ fmt src dst -> mkRU (use_R FF64 src []) [mk fmt dst] + CVTSI2SS fmt src dst -> mkRU (use_R fmt src []) [mk FF32 dst] + CVTSI2SD fmt src dst -> mkRU (use_R fmt src []) [mk FF64 dst] FDIV fmt src dst -> usageRM fmt src dst - SQRT fmt src dst -> mkRU fmt (use_R src []) [dst] + SQRT fmt src dst -> mkRU (use_R fmt src []) [mk fmt dst] - FETCHGOT reg -> mkRU II64 [] [reg] - FETCHPC reg -> mkRU II64 [] [reg] + FETCHGOT reg -> mkRU [] [mk addrFmt reg] + FETCHPC reg -> mkRU [] [mk addrFmt reg] COMMENT _ -> noUsage LOCATION{} -> noUsage UNWIND{} -> noUsage DELTA _ -> noUsage - POPCNT fmt src dst -> mkRU fmt (use_R src []) [dst] - LZCNT fmt src dst -> mkRU fmt (use_R src []) [dst] - TZCNT fmt src dst -> mkRU fmt (use_R src []) [dst] - BSF fmt src dst -> mkRU fmt (use_R src []) [dst] - BSR fmt src dst -> mkRU fmt (use_R src []) [dst] + POPCNT fmt src dst -> mkRU (use_R fmt src []) [mk fmt dst] + LZCNT fmt src dst -> mkRU (use_R fmt src []) [mk fmt dst] + TZCNT fmt src dst -> mkRU (use_R fmt src []) [mk fmt dst] + BSF fmt src dst -> mkRU (use_R fmt src []) [mk fmt dst] + BSR fmt src dst -> mkRU (use_R fmt src []) [mk fmt dst] - PDEP fmt src mask dst -> mkRU fmt (use_R src $ use_R mask []) [dst] - PEXT fmt src mask dst -> mkRU fmt (use_R src $ use_R mask []) [dst] + PDEP fmt src mask dst -> mkRU (use_R fmt src $ use_R fmt mask []) [mk fmt dst] + PEXT fmt src mask dst -> mkRU (use_R fmt src $ use_R fmt mask []) [mk fmt dst] FMA3 fmt _ _ src3 src2 dst -> usageFMA fmt src3 src2 dst -- note: might be a better way to do this - PREFETCH _ fmt src -> mkRU fmt (use_R src []) [] + PREFETCH _ fmt src -> mkRU (use_R fmt src []) [] LOCK i -> regUsageOfInstr platform i XADD fmt src dst -> usageMM fmt src dst CMPXCHG fmt src dst -> usageRMM fmt src dst (OpReg eax) @@ -512,10 +512,10 @@ regUsageOfInstr platform instr MFENCE -> noUsage -- vector instructions - VBROADCAST fmt src dst -> mkRU fmt (use_EA src []) [dst] - VEXTRACT fmt _off src dst -> mkRU fmt [src] (use_R dst []) + VBROADCAST fmt src dst -> mkRU (use_EA src []) [mk fmt dst] + VEXTRACT fmt _off src dst -> mkRU [mk fmt src] (use_R fmt dst []) INSERTPS fmt (ImmInt off) src dst - -> mkRU fmt ((use_R src []) ++ [dst | not doesNotReadDst]) [dst] + -> mkRU ((use_R fmt src []) ++ [mk fmt dst | not doesNotReadDst]) [mk fmt dst] where -- Compute whether the instruction reads the destination register or not. -- Immediate bits: ss_dd_zzzz s = src pos, d = dst pos, z = zeroed components. @@ -524,42 +524,42 @@ regUsageOfInstr platform instr -- are being zeroed. where pos = ( off `shiftR` 4 ) .&. 0b11 INSERTPS fmt _off src dst - -> mkRU fmt ((use_R src []) ++ [dst]) [dst] - - VMOVU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) - MOVU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) - MOVA fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) - MOVL fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) - MOVH fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) - MOVDQU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) - VMOVDQU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) - - VPXOR fmt s1 s2 dst -> mkRU fmt [s1,s2] [dst] - - VADD fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] - VSUB fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] - VMUL fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] - VDIV fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] - - VPSHUFD fmt _off src dst - -> mkRU fmt (use_R src []) [dst] - PSHUFD fmt _off src dst - -> mkRU fmt (use_R src []) [dst] - SHUFPD fmt _off src dst - -> mkRU fmt (use_R src [dst]) [dst] - SHUFPS fmt _off src dst - -> mkRU fmt (use_R src [dst]) [dst] - VSHUFPD fmt _off src1 src2 dst - -> mkRU fmt (use_R src1 [src2]) [dst] - VSHUFPS fmt _off src1 src2 dst - -> mkRU fmt (use_R src1 [src2]) [dst] - - PSLLDQ fmt off dst -> mkRU fmt (use_R off []) [dst] + -> mkRU ((use_R fmt src []) ++ [mk fmt dst]) [mk fmt dst] + + VMOVU fmt src dst -> mkRU (use_R fmt src []) (use_R fmt dst []) + MOVU fmt src dst -> mkRU (use_R fmt src []) (use_R fmt dst []) + MOVA fmt src dst -> mkRU (use_R fmt src []) (use_R fmt dst []) + MOVL fmt src dst -> mkRU (use_R fmt src []) (use_R fmt dst []) + MOVH fmt src dst -> mkRU (use_R fmt src []) (use_R fmt dst []) + MOVDQU fmt src dst -> mkRU (use_R fmt src []) (use_R fmt dst []) + VMOVDQU fmt src dst -> mkRU (use_R fmt src []) (use_R fmt dst []) + + VPXOR fmt s1 s2 dst -> mkRU (map (mk fmt) [s1,s2]) [mk fmt dst] + + VADD fmt s1 s2 dst -> mkRU ((use_R fmt s1 []) ++ [mk fmt s2]) [mk fmt dst] + VSUB fmt s1 s2 dst -> mkRU ((use_R fmt s1 []) ++ [mk fmt s2]) [mk fmt dst] + VMUL fmt s1 s2 dst -> mkRU ((use_R fmt s1 []) ++ [mk fmt s2]) [mk fmt dst] + VDIV fmt s1 s2 dst -> mkRU ((use_R fmt s1 []) ++ [mk fmt s2]) [mk fmt dst] + + VPSHUFD fmt _off src dst + -> mkRU (use_R fmt src []) [mk fmt dst] + PSHUFD fmt _off src dst + -> mkRU (use_R fmt src []) [mk fmt dst] + SHUFPD fmt _off src dst + -> mkRU (use_R fmt src [mk fmt dst]) [mk fmt dst] + SHUFPS fmt _off src dst + -> mkRU (use_R fmt src [mk fmt dst]) [mk fmt dst] + VSHUFPD fmt _off src1 src2 dst + -> mkRU (use_R fmt src1 [mk fmt src2]) [mk fmt dst] + VSHUFPS fmt _off src1 src2 dst + -> mkRU (use_R fmt src1 [mk fmt src2]) [mk fmt dst] + + PSLLDQ fmt off dst -> mkRU (use_R fmt off []) [mk fmt dst] MOVHLPS fmt src dst - -> mkRU fmt (use_R src []) [dst] + -> mkRU (use_R fmt src []) [mk fmt dst] PUNPCKLQDQ fmt src dst - -> mkRU fmt (use_R src [dst]) [dst] + -> mkRU (use_R fmt src [mk fmt dst]) [mk fmt dst] _other -> panic "regUsage: unrecognised instr" where @@ -574,81 +574,91 @@ regUsageOfInstr platform instr -- 2 operand form; first operand Read; second Written usageRW :: HasDebugCallStack => Format -> Operand -> Operand -> RegUsage - usageRW fmt op (OpReg reg) = mkRU fmt (use_R op []) [reg] - usageRW fmt op (OpAddr ea) = mkRUR fmt (use_R op $! use_EA ea []) + usageRW fmt op (OpReg reg) = mkRU (use_R fmt op []) [mk fmt reg] + usageRW fmt op (OpAddr ea) = mkRUR (use_R fmt op $! use_EA ea []) usageRW _ _ _ = panic "X86.RegInfo.usageRW: no match" -- 2 operand form; first operand Read; second Modified usageRM :: HasDebugCallStack => Format -> Operand -> Operand -> RegUsage - usageRM fmt op (OpReg reg) = mkRU fmt (use_R op [reg]) [reg] - usageRM fmt op (OpAddr ea) = mkRUR fmt (use_R op $! use_EA ea []) + usageRM fmt op (OpReg reg) = mkRU (use_R fmt op [mk fmt reg]) [mk fmt reg] + usageRM fmt op (OpAddr ea) = mkRUR (use_R fmt op $! use_EA ea []) usageRM _ _ _ = panic "X86.RegInfo.usageRM: no match" -- 2 operand form; first operand Modified; second Modified usageMM :: HasDebugCallStack => Format -> Operand -> Operand -> RegUsage - usageMM fmt (OpReg src) (OpReg dst) = mkRU fmt [src, dst] [src, dst] - usageMM fmt (OpReg src) (OpAddr ea) = mkRU fmt (use_EA ea [src]) [src] - usageMM fmt (OpAddr ea) (OpReg dst) = mkRU fmt (use_EA ea [dst]) [dst] + usageMM fmt (OpReg src) (OpReg dst) = mkRU (map (mk fmt) [src, dst]) (map (mk fmt) [src, dst]) + usageMM fmt (OpReg src) (OpAddr ea) = mkRU (use_EA ea [mk fmt src]) [mk fmt src] + usageMM fmt (OpAddr ea) (OpReg dst) = mkRU (use_EA ea [mk fmt dst]) [mk fmt dst] usageMM _ _ _ = panic "X86.RegInfo.usageMM: no match" -- 3 operand form; first operand Read; second Modified; third Modified usageRMM :: HasDebugCallStack => Format -> Operand -> Operand -> Operand -> RegUsage - usageRMM fmt (OpReg src) (OpReg dst) (OpReg reg) = mkRU fmt [src, dst, reg] [dst, reg] - usageRMM fmt (OpReg src) (OpAddr ea) (OpReg reg) = mkRU fmt (use_EA ea [src, reg]) [reg] + usageRMM fmt (OpReg src) (OpReg dst) (OpReg reg) = mkRU (map (mk fmt) [src, dst, reg]) (map (mk fmt) [dst, reg]) + usageRMM fmt (OpReg src) (OpAddr ea) (OpReg reg) = mkRU (use_EA ea (map (mk fmt) [src, reg])) [mk fmt reg] usageRMM _ _ _ _ = panic "X86.RegInfo.usageRMM: no match" -- 3 operand form of FMA instructions. usageFMA :: HasDebugCallStack => Format -> Operand -> Reg -> Reg -> RegUsage - usageFMA fmt (OpReg src1) src2 dst - = mkRU fmt [src1, src2, dst] [dst] + usageFMA fmt (OpReg src1) src2 dst = + mkRU (map (\r -> mkRegFormat platform r fmt) [src1, src2, dst]) [ mkRegFormat platform dst fmt ] usageFMA fmt (OpAddr ea1) src2 dst - = mkRU fmt (use_EA ea1 [src2, dst]) [dst] + = mkRU (use_EA ea1 (map (\r -> mkRegFormat platform r fmt) [src2, dst])) [ mkRegFormat platform dst fmt ] usageFMA _ _ _ _ = panic "X86.RegInfo.usageFMA: no match" -- 1 operand form; operand Modified usageM :: HasDebugCallStack => Format -> Operand -> RegUsage - usageM fmt (OpReg reg) = mkRU fmt [reg] [reg] - usageM fmt (OpAddr ea) = mkRUR fmt (use_EA ea []) - usageM _ _ = panic "X86.RegInfo.usageM: no match" + usageM fmt (OpReg reg) = + let r' = mk fmt reg + in mkRU [r'] [r'] + usageM _ (OpAddr ea) = mkRUR (use_EA ea []) + usageM _ _ = panic "X86.RegInfo.usageM: no match" -- Registers defd when an operand is written. - def_W (OpReg reg) = [reg] - def_W (OpAddr _ ) = [] - def_W _ = panic "X86.RegInfo.def_W: no match" + def_W fmt (OpReg reg) = [mk fmt reg] + def_W _ (OpAddr _ ) = [] + def_W _ _ = panic "X86.RegInfo.def_W: no match" -- Registers used when an operand is read. - use_R (OpReg reg) tl = reg : tl - use_R (OpImm _) tl = tl - use_R (OpAddr ea) tl = use_EA ea tl + use_R fmt (OpReg reg) tl = mk fmt reg : tl + use_R _ (OpImm _) tl = tl + use_R _ (OpAddr ea) tl = use_EA ea tl -- Registers used to compute an effective address. use_EA (ImmAddr _ _) tl = tl use_EA (AddrBaseIndex base index _) tl = use_base base $! use_index index tl - where use_base (EABaseReg r) tl = r : tl + where use_base (EABaseReg r) tl = mk addrFmt r : tl use_base _ tl = tl use_index EAIndexNone tl = tl - use_index (EAIndex i _) tl = i : tl - - mkRUR :: HasDebugCallStack => Format -> [Reg] -> RegUsage - mkRUR fmt src = src' `seq` RU (map (\ r -> mkRegFormat platform r fmt) src') [] - where src' = filter (interesting platform) src - - mkRU :: HasDebugCallStack => Format -> [Reg] -> [Reg] -> RegUsage - mkRU fmt src dst = src' `seq` dst' `seq` RU (map (\ r -> mkRegFormat platform r fmt) src') (map (\ r -> mkRegFormat platform r fmt) dst') - where src' = filter (interesting platform) src - dst' = filter (interesting platform) dst - - mkRUFormat :: HasDebugCallStack => [Reg] -> [Reg] -> RegUsage - mkRUFormat src dst = src' `seq` dst' `seq` RU (map mkFormat src') (map mkFormat dst') - where src' = filter (interesting platform) src - dst' = filter (interesting platform) dst - mkFormat reg = - mkRegFormat platform reg $ - case targetClassOfReg platform reg of - RcInteger -> archWordFormat (target32Bit platform) - RcFloatOrVector -> FF64 + use_index (EAIndex i _) tl = mk addrFmt i : tl + + mkRUR :: [RegFormat] -> RegUsage + mkRUR src = mkRU src [] + + mkRU :: [RegFormat] -> [RegFormat] -> RegUsage + mkRU src dst = src' `seq` dst' `seq` RU src' dst' + where src' = filter (interesting platform . regFormatReg) src + dst' = filter (interesting platform . regFormatReg) dst + + addrFmt = archWordFormat (target32Bit platform) + mk :: HasDebugCallStack => Format -> Reg -> RegFormat + mk fmt r = mkRegFormat platform r fmt + + mkFmt :: HasDebugCallStack => Reg -> RegFormat + mkFmt r = RegFormat r $ case targetClassOfReg platform r of + RcInteger -> addrFmt + RcFloatOrVector -> FF64 + + --mkRUFormat :: HasDebugCallStack => [Reg] -> [Reg] -> RegUsage + --mkRUFormat src dst = src' `seq` dst' `seq` RU (map mkFormat src') (map mkFormat dst') + -- where src' = filter (interesting platform) src + -- dst' = filter (interesting platform) dst + -- mkFormat reg = + -- mkRegFormat platform reg $ + -- case targetClassOfReg platform reg of + -- RcInteger -> archWordFormat (target32Bit platform) + -- RcFloatOrVector -> FF64 -- | Is this register interesting for the register allocator? interesting :: Platform -> Reg -> Bool @@ -659,10 +669,26 @@ interesting platform (RegReal (RealRegSingle i)) = freeReg platform i -- | Applies the supplied function to all registers in instructions. -- Typically used to change virtual registers to real registers. -patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr -patchRegsOfInstr instr env - = case instr of - MOV fmt src dst -> patch2 (MOV fmt) src dst +patchRegsOfInstr :: HasDebugCallStack => Platform -> Instr -> (Reg -> Reg) -> Instr +patchRegsOfInstr platform instr env + = case instr of + MOV fmt src dst -> + mkMOV fmt (patchOp src) (patchOp dst) + where + fmtCls = if isIntFormat fmt then RcInteger else RcFloatOrVector + mkMOV :: HasDebugCallStack => Format -> Operand -> Operand -> Instr + mkMOV fmt op1 op2 = + assertPpr (all (== fmtCls) $ catMaybes [cls1, cls2]) + (vcat [ text "patchRegsOfInstr produced invalid MOV instruction" + , text "fmt:" <+> ppr fmt + , case op1 of { OpReg r1 -> ppr r1 <+> dcolon <+> ppr (fromJust cls1); _ -> empty } + , case op2 of { OpReg r2 -> ppr r2 <+> dcolon <+> ppr (fromJust cls2); _ -> empty } + ]) + $ MOV fmt op1 op2 + where + cls1 = case op1 of { OpReg r1 -> Just (targetClassOfReg platform r1); _ -> Nothing } + cls2 = case op2 of { OpReg r2 -> Just (targetClassOfReg platform r2); _ -> Nothing } + MOVD fmt src dst -> patch2 (MOVD fmt) src dst CMOV cc fmt src dst -> CMOV cc fmt (patchOp src) (env dst) MOVZxL fmt src dst -> patch2 (MOVZxL fmt) src dst @@ -740,7 +766,7 @@ patchRegsOfInstr instr env PREFETCH lvl format src -> PREFETCH lvl format (patchOp src) - LOCK i -> LOCK (patchRegsOfInstr i env) + LOCK i -> LOCK (patchRegsOfInstr platform i env) XADD fmt src dst -> patch2 (XADD fmt) src dst CMPXCHG fmt src dst -> patch2 (CMPXCHG fmt) src dst XCHG fmt src dst -> XCHG fmt (patchOp src) (env dst) @@ -1138,7 +1164,7 @@ mkStackAllocInstr platform amount case platformArch platform of ArchX86_64 | needs_probe_call platform amount -> [ MOV II64 (OpImm (ImmInt amount)) (OpReg rax) - , CALL (Left $ strImmLit (fsLit "___chkstk_ms")) [rax] + , CALL (Left $ strImmLit (fsLit "___chkstk_ms")) [mkRegFormat platform rax II64] , SUB II64 (OpReg rax) (OpReg rsp) ] | otherwise -> ===================================== compiler/GHC/CmmToAsm/X86/Regs.hs ===================================== @@ -38,6 +38,7 @@ module GHC.CmmToAsm.X86.Regs ( xmm8, xmm9, xmm10, xmm11, xmm12, xmm13, xmm14, xmm15, xmm, firstxmm, lastxmm, + intregnos, xmmregnos, ripRel, allFPArgRegs, ===================================== compiler/GHC/CmmToLlvm.hs ===================================== @@ -139,7 +139,7 @@ llvmGroupLlvmGens cmm = do Nothing -> l Just (CmmStaticsRaw info_lbl _) -> info_lbl lml <- strCLabel_llvm l' - funInsert lml =<< llvmFunTy live + funInsert lml =<< llvmFunTy (map globalRegUseGlobalReg live) return Nothing cdata <- fmap catMaybes $ mapM split cmm ===================================== compiler/GHC/CmmToLlvm/CodeGen.hs ===================================== @@ -57,7 +57,7 @@ genLlvmProc :: RawCmmDecl -> LlvmM [LlvmCmmDecl] genLlvmProc (CmmProc infos lbl live graph) = do let blocks = toBlockListEntryFirstFalseFallthrough graph - (lmblocks, lmdata) <- basicBlocksCodeGen live blocks + (lmblocks, lmdata) <- basicBlocksCodeGen (map globalRegUseGlobalReg live) blocks let info = mapLookup (g_entry graph) infos proc = CmmProc info lbl live (ListGraph lmblocks) return (proc:lmdata) @@ -152,7 +152,7 @@ stmtToInstrs ubid stmt = case stmt of -- Tail call CmmCall { cml_target = arg, - cml_args_regs = live } -> genJump arg live + cml_args_regs = live } -> genJump arg $ map globalRegUseGlobalReg live _ -> panic "Llvm.CodeGen.stmtToInstrs" ===================================== compiler/GHC/CmmToLlvm/Ppr.hs ===================================== @@ -49,8 +49,9 @@ pprLlvmCmmDecl (CmmData _ lmdata) = do return ( vcat $ map (pprLlvmData opts) lmdata , vcat $ map (pprLlvmData opts) lmdata) -pprLlvmCmmDecl (CmmProc mb_info entry_lbl live (ListGraph blks)) - = do let lbl = case mb_info of +pprLlvmCmmDecl (CmmProc mb_info entry_lbl liveWithUses (ListGraph blks)) + = do let live = map globalRegUseGlobalReg liveWithUses + lbl = case mb_info of Nothing -> entry_lbl Just (CmmStaticsRaw info_lbl _) -> info_lbl link = if externallyVisibleCLabel lbl ===================================== compiler/GHC/StgToCmm/Monad.hs ===================================== @@ -778,7 +778,7 @@ emitProcWithConvention :: Convention -> Maybe CmmInfoTable -> CLabel emitProcWithConvention conv mb_info lbl args blocks = emitProcWithStackFrame conv mb_info lbl [] args blocks True -emitProc :: Maybe CmmInfoTable -> CLabel -> [GlobalReg] -> CmmAGraphScoped +emitProc :: Maybe CmmInfoTable -> CLabel -> [GlobalRegUse] -> CmmAGraphScoped -> Int -> Bool -> FCode () emitProc mb_info lbl live blocks offset do_layout = do { l <- newBlockId View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eecb6387a44def336413eb1e592f27bb14a13195 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/eecb6387a44def336413eb1e592f27bb14a13195 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 12:05:44 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 21 Jun 2024 08:05:44 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 7 commits: haddock: Remove unused pragmata, qualify usages of Data.List functions, add... Message-ID: <66756c98310be_2f9c28179ff081185e@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: c872e09b by Hécate Kleidukos at 2024-06-20T19:28:36-04:00 haddock: Remove unused pragmata, qualify usages of Data.List functions, add more sanity checking flags by default This commit enables some extensions and GHC flags in the cabal file in a way that allows us to reduce the amount of prologuing on top of each file. We also prefix the usage of some List functions that removes ambiguity when they are also exported from the Prelude, like foldl'. In general, this has the effect of pointing out more explicitly that a linked list is used. Metric Increase: haddock.Cabal haddock.base haddock.compiler - - - - - 8c87d4e1 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00 Add test case for #23586 - - - - - 568de8a5 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00 When matching functions in rewrite rules: ignore multiplicity When matching a template variable to an expression, we check that it has the same type as the matched expression. But if the variable `f` has type `A -> B` while the expression `e` has type `A %1 -> B`, the match was previously rejected. A principled solution would have `f` substituted by `\(%Many x) -> e x` or some other appropriate coercion. But since linearity is not properly checked in Core, we can be cheeky and simply ignore multiplicity while matching. Much easier. This has forced a change in the linter which, when `-dlinear-core-lint` is off, must consider that `a -> b` and `a %1 -> b` are equal. This is achieved by adding an argument to configure the behaviour of `nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour which ignores multiplicities when comparing two `FunTy`. Fixes #24725. - - - - - c8a8727e by Simon Peyton Jones at 2024-06-20T19:29:12-04:00 Faster type equality This MR speeds up type equality, triggered by perf regressions that showed up when fixing #24725 by parameterising type equality over whether to ignore multiplicity. The changes are: * Do not use `nonDetCmpType` for type /equality/. Instead use a specialised type-equality function, which we have always had! `nonDetCmpType` remains, but I did not invest effort in refactoring or optimising it. * Type equality is parameterised by - whether to expand synonyms - whether to respect multiplicities - whether it has a RnEnv2 environment In this MR I systematically specialise it for static values of these parameters. Much more direct and predictable than before. See Note [Specialising type equality] * We want to avoid comparing kinds if possible. I refactored how this happens, at least for `eqType`. See Note [Casts and coercions in type comparison] * To make Lint fast, we want to avoid allocating a thunk for <msg> in ensureEqTypes ty1 ty2 <msg> because the test almost always succeeds, and <msg> isn't needed. See Note [INLINE ensureEqTys] Metric Decrease: T13386 T5030 - - - - - 032b6b2d by Sebastian Graf at 2024-06-21T08:05:33-04:00 Derive previously hand-written `Lift` instances (#14030) This is possible now that #22229 is fixed. - - - - - bff20301 by Sebastian Graf at 2024-06-21T08:05:33-04:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. - - - - - d48159c5 by Matthew Pickering at 2024-06-21T08:05:34-04:00 bindist: Use complete relative paths when cding to directories If a user has configured CDPATH on their system then `cd lib` may change into an unexpected directory during the installation process. If you write `cd ./lib` then it will not consult `CDPATH` to determine what you mean. I have added a check on ghcup-ci to verify that the bindist installation works in this situation. Fixes #24951 - - - - - 30 changed files: - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Multiplicity.hs - compiler/GHC/Core/TyCo/Compare.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Tc/Utils/TcType.hs - hadrian/bindist/Makefile - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - testsuite/tests/ghci/scripts/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - + testsuite/tests/simplCore/should_run/T23586.hs - + testsuite/tests/simplCore/should_run/T23586.stdout - testsuite/tests/simplCore/should_run/all.T - testsuite/tests/th/TH_Lift.hs - + testsuite/tests/th/TH_Lift.stderr - testsuite/tests/th/all.T - utils/haddock/haddock-api/haddock-api.cabal - utils/haddock/haddock-api/src/Haddock.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml.hs - utils/haddock/haddock-api/src/Haddock/Backends/Xhtml/Layout.hs - utils/haddock/haddock-api/src/Haddock/GhcUtils.hs - utils/haddock/haddock-api/src/Haddock/Interface.hs - utils/haddock/haddock-api/src/Haddock/Interface/AttachInstances.hs - utils/haddock/haddock-api/src/Haddock/Interface/Create.hs - utils/haddock/haddock-api/src/Haddock/Options.hs - utils/haddock/haddock-api/src/Haddock/Types.hs - utils/haddock/haddock-library/fixtures/Fixtures.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7392a0120b1d38e022108eb47e55f19f2d4e1ad3...d48159c5dca07c172e2126926c66e420e92fdf41 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7392a0120b1d38e022108eb47e55f19f2d4e1ad3...d48159c5dca07c172e2126926c66e420e92fdf41 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 12:11:26 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Fri, 21 Jun 2024 08:11:26 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/9_10_ci_job Message-ID: <66756deebc3c3_2f9c2819844681243c8@gitlab.mail> Matthew Pickering pushed new branch wip/9_10_ci_job at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/9_10_ci_job You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 12:12:45 2024 From: gitlab at gitlab.haskell.org (Matthew Pickering (@mpickering)) Date: Fri, 21 Jun 2024 08:12:45 -0400 Subject: [Git][ghc/ghc][wip/9_10_ci_job] 2 commits: Update bootstrap plans for recent GHC versions (9.6.5, 9.8.2, 9.10.10) Message-ID: <66756e3d47fcd_2f9c281a33ecc1263d2@gitlab.mail> Matthew Pickering pushed to branch wip/9_10_ci_job at Glasgow Haskell Compiler / GHC Commits: 216a222b by Matthew Pickering at 2024-06-21T13:12:33+01:00 Update bootstrap plans for recent GHC versions (9.6.5, 9.8.2, 9.10.10) - - - - - 5028e740 by Matthew Pickering at 2024-06-21T13:12:33+01:00 ci: Add 9_10 bootstrap testing job - - - - - 8 changed files: - .gitlab-ci.yml - hadrian/bootstrap/generate_bootstrap_plans - + hadrian/bootstrap/plan-9_10_1.json - hadrian/bootstrap/plan-9_4_1.json - hadrian/bootstrap/plan-9_4_2.json - hadrian/bootstrap/plan-9_4_3.json - hadrian/bootstrap/plan-9_4_4.json - hadrian/bootstrap/plan-9_4_5.json The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7f782ffc10bb286aa0f500122cb9c16189692cc0...5028e74094820502801346050d29f163f17412c3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/7f782ffc10bb286aa0f500122cb9c16189692cc0...5028e74094820502801346050d29f163f17412c3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 12:18:37 2024 From: gitlab at gitlab.haskell.org (sheaf (@sheaf)) Date: Fri, 21 Jun 2024 08:18:37 -0400 Subject: [Git][ghc/ghc][wip/ncg-simd] keep track of GlobalRegUse for register allocation Message-ID: <66756f9dce73e_2f9c281becafc1306e@gitlab.mail> sheaf pushed to branch wip/ncg-simd at Glasgow Haskell Compiler / GHC Commits: 7d901da2 by sheaf at 2024-06-21T14:18:14+02:00 keep track of GlobalRegUse for register allocation - - - - - 24 changed files: - compiler/GHC/Cmm.hs - compiler/GHC/Cmm/Graph.hs - compiler/GHC/Cmm/Liveness.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ProcPoint.hs - compiler/GHC/Cmm/Sink.hs - compiler/GHC/CmmToAsm/AArch64.hs - compiler/GHC/CmmToAsm/Instr.hs - compiler/GHC/CmmToAsm/PPC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/Instr.hs - compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs - compiler/GHC/CmmToAsm/Reg/Linear.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86.hs - compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs - compiler/GHC/CmmToAsm/Reg/Liveness.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToAsm/X86/Regs.hs - compiler/GHC/CmmToLlvm.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/CmmToLlvm/Ppr.hs - compiler/GHC/StgToCmm/Monad.hs Changes: ===================================== compiler/GHC/Cmm.hs ===================================== @@ -100,7 +100,7 @@ data GenCmmDecl d h g = CmmProc -- A procedure h -- Extra header such as the info table CLabel -- Entry label - [GlobalReg] -- Registers live on entry. Note that the set of live + [GlobalRegUse] -- Registers live on entry. Note that the set of live -- registers will be correct in generated C-- code, but -- not in hand-written C-- code. However, -- splitAtProcPoints calculates correct liveness ===================================== compiler/GHC/Cmm/Graph.hs ===================================== @@ -208,7 +208,7 @@ mkJump profile conv e actuals updfr_off = -- | A jump where the caller says what the live GlobalRegs are. Used -- for low-level hand-written Cmm. -mkRawJump :: Profile -> CmmExpr -> UpdFrameOffset -> [GlobalReg] +mkRawJump :: Profile -> CmmExpr -> UpdFrameOffset -> [GlobalRegUse] -> CmmAGraph mkRawJump profile e updfr_off vols = lastWithArgs profile Jump Old NativeNodeCall [] updfr_off $ @@ -297,7 +297,7 @@ stackStubExpr w = CmmLit (CmmInt 0 w) copyInOflow :: Profile -> Convention -> Area -> [CmmFormal] -> [CmmFormal] - -> (Int, [GlobalReg], CmmAGraph) + -> (Int, [GlobalRegUse], CmmAGraph) copyInOflow profile conv area formals extra_stk = (offset, gregs, catAGraphs $ map mkMiddle nodes) @@ -308,9 +308,9 @@ copyInOflow profile conv area formals extra_stk copyIn :: Profile -> Convention -> Area -> [CmmFormal] -> [CmmFormal] - -> (ByteOff, [GlobalReg], [CmmNode O O]) + -> (ByteOff, [GlobalRegUse], [CmmNode O O]) copyIn profile conv area formals extra_stk - = (stk_size, [r | (_, RegisterParam r) <- args], map ci (stk_args ++ args)) + = (stk_size, [GlobalRegUse r (localRegType lr)| (lr, RegisterParam r) <- args], map ci (stk_args ++ args)) where platform = profilePlatform profile @@ -365,7 +365,7 @@ data Transfer = Call | JumpRet | Jump | Ret deriving Eq copyOutOflow :: Profile -> Convention -> Transfer -> Area -> [CmmExpr] -> UpdFrameOffset -> [CmmExpr] -- extra stack args - -> (Int, [GlobalReg], CmmAGraph) + -> (Int, [GlobalRegUse], CmmAGraph) -- Generate code to move the actual parameters into the locations -- required by the calling convention. This includes a store for the @@ -383,8 +383,8 @@ copyOutOflow profile conv transfer area actuals updfr_off extra_stack_stuff (regs, graph) = foldr co ([], mkNop) (setRA ++ args ++ stack_params) co :: (CmmExpr, ParamLocation) - -> ([GlobalReg], CmmAGraph) - -> ([GlobalReg], CmmAGraph) + -> ([GlobalRegUse], CmmAGraph) + -> ([GlobalRegUse], CmmAGraph) co (v, RegisterParam r@(VanillaReg {})) (rs, ms) = let width = cmmExprWidth platform v value @@ -393,12 +393,14 @@ copyOutOflow profile conv transfer area actuals updfr_off extra_stack_stuff | width < wordWidth platform = CmmMachOp (MO_XX_Conv width (wordWidth platform)) [v] | otherwise = panic "Parameter width greater than word width" + ru = GlobalRegUse r (cmmExprType platform value) - in (r:rs, mkAssign (CmmGlobal $ GlobalRegUse r (cmmExprType platform value)) value <*> ms) + in (ru:rs, mkAssign (CmmGlobal ru) value <*> ms) -- Non VanillaRegs co (v, RegisterParam r) (rs, ms) = - (r:rs, mkAssign (CmmGlobal $ GlobalRegUse r (cmmExprType platform v)) v <*> ms) + let ru = GlobalRegUse r (cmmExprType platform v) + in (ru:rs, mkAssign (CmmGlobal ru) v <*> ms) co (v, StackParam off) (rs, ms) = (rs, mkStore (CmmStackSlot area off) (value v) <*> ms) @@ -461,13 +463,13 @@ copyOutOflow profile conv transfer area actuals updfr_off extra_stack_stuff mkCallEntry :: Profile -> Convention -> [CmmFormal] -> [CmmFormal] - -> (Int, [GlobalReg], CmmAGraph) + -> (Int, [GlobalRegUse], CmmAGraph) mkCallEntry profile conv formals extra_stk = copyInOflow profile conv Old formals extra_stk lastWithArgs :: Profile -> Transfer -> Area -> Convention -> [CmmExpr] -> UpdFrameOffset - -> (ByteOff -> [GlobalReg] -> CmmAGraph) + -> (ByteOff -> [GlobalRegUse] -> CmmAGraph) -> CmmAGraph lastWithArgs profile transfer area conv actuals updfr_off last = lastWithArgsAndExtraStack profile transfer area conv actuals @@ -476,7 +478,7 @@ lastWithArgs profile transfer area conv actuals updfr_off last = lastWithArgsAndExtraStack :: Profile -> Transfer -> Area -> Convention -> [CmmExpr] -> UpdFrameOffset -> [CmmExpr] - -> (ByteOff -> [GlobalReg] -> CmmAGraph) + -> (ByteOff -> [GlobalRegUse] -> CmmAGraph) -> CmmAGraph lastWithArgsAndExtraStack profile transfer area conv actuals updfr_off extra_stack last = @@ -490,7 +492,7 @@ noExtraStack :: [CmmExpr] noExtraStack = [] toCall :: CmmExpr -> Maybe BlockId -> UpdFrameOffset -> ByteOff - -> ByteOff -> [GlobalReg] + -> ByteOff -> [GlobalRegUse] -> CmmAGraph toCall e cont updfr_off res_space arg_space regs = mkLast $ CmmCall e cont regs arg_space res_space updfr_off ===================================== compiler/GHC/Cmm/Liveness.hs ===================================== @@ -59,7 +59,7 @@ cmmLocalLiveness platform graph = check facts = noLiveOnEntry entry (expectJust "check" $ mapLookup entry facts) facts -cmmGlobalLiveness :: Platform -> CmmGraph -> BlockEntryLiveness GlobalReg +cmmGlobalLiveness :: Platform -> CmmGraph -> BlockEntryLiveness GlobalRegUse cmmGlobalLiveness platform graph = analyzeCmmBwd liveLattice (xferLive platform) graph mapEmpty @@ -92,7 +92,7 @@ xferLive platform (BlockCC eNode middle xNode) fBase = !result = foldNodesBwdOO (gen_kill platform) middle joined in mapSingleton (entryLabel eNode) result {-# SPECIALIZE xferLive :: Platform -> TransferFun (CmmLive LocalReg) #-} -{-# SPECIALIZE xferLive :: Platform -> TransferFun (CmmLive GlobalReg) #-} +{-# SPECIALIZE xferLive :: Platform -> TransferFun (CmmLive GlobalRegUse) #-} ----------------------------------------------------------------------------- -- | Specialization that only retains the keys for local variables. ===================================== compiler/GHC/Cmm/Node.hs ===================================== @@ -118,7 +118,7 @@ data CmmNode e x where -- occur in CmmExprs, namely as (CmmLit (CmmBlock b)) or -- (CmmStackSlot (Young b) _). - cml_args_regs :: [GlobalReg], + cml_args_regs :: [GlobalRegUse], -- The argument GlobalRegs (Rx, Fx, Dx, Lx) that are passed -- to the call. This is essential information for the -- native code generator's register allocator; without @@ -544,7 +544,7 @@ instance UserOfRegs LocalReg (CmmNode e x) where => (b -> LocalReg -> b) -> b -> a -> b fold f z n = foldRegsUsed platform f z n -instance UserOfRegs GlobalReg (CmmNode e x) where +instance UserOfRegs GlobalRegUse (CmmNode e x) where {-# INLINEABLE foldRegsUsed #-} foldRegsUsed platform f !z n = case n of CmmAssign _ expr -> fold f z expr @@ -555,8 +555,8 @@ instance UserOfRegs GlobalReg (CmmNode e x) where CmmCall {cml_target=tgt, cml_args_regs=args} -> fold f (fold f z args) tgt CmmForeignCall {tgt=tgt, args=args} -> fold f (fold f z tgt) args _ -> z - where fold :: forall a b. UserOfRegs GlobalReg a - => (b -> GlobalReg -> b) -> b -> a -> b + where fold :: forall a b. UserOfRegs GlobalRegUse a + => (b -> GlobalRegUse -> b) -> b -> a -> b fold f z n = foldRegsUsed platform f z n instance (Ord r, UserOfRegs r CmmReg) => UserOfRegs r ForeignTarget where -- The (Ord r) in the context is necessary here @@ -576,7 +576,7 @@ instance DefinerOfRegs LocalReg (CmmNode e x) where => (b -> LocalReg -> b) -> b -> a -> b fold f z n = foldRegsDefd platform f z n -instance DefinerOfRegs GlobalReg (CmmNode e x) where +instance DefinerOfRegs GlobalRegUse (CmmNode e x) where {-# INLINEABLE foldRegsDefd #-} foldRegsDefd platform f !z n = case n of CmmAssign lhs _ -> fold f z lhs @@ -585,12 +585,13 @@ instance DefinerOfRegs GlobalReg (CmmNode e x) where CmmForeignCall {} -> fold f z activeRegs -- See Note [Safe foreign calls clobber STG registers] _ -> z - where fold :: forall a b. DefinerOfRegs GlobalReg a - => (b -> GlobalReg -> b) -> b -> a -> b + where fold :: forall a b. DefinerOfRegs GlobalRegUse a + => (b -> GlobalRegUse -> b) -> b -> a -> b fold f z n = foldRegsDefd platform f z n - activeRegs = activeStgRegs platform - activeCallerSavesRegs = filter (callerSaves platform) activeRegs + activeRegs :: [GlobalRegUse] + activeRegs = map (\ r -> GlobalRegUse r (globalRegSpillType platform r)) $ activeStgRegs platform + activeCallerSavesRegs = filter (callerSaves platform . globalRegUseGlobalReg) activeRegs foreignTargetRegs (ForeignTarget _ (ForeignConvention _ _ _ CmmNeverReturns)) = [] foreignTargetRegs _ = activeCallerSavesRegs ===================================== compiler/GHC/Cmm/Parser.y ===================================== @@ -770,13 +770,15 @@ safety :: { Safety } : {- empty -} { PlayRisky } | STRING {% parseSafety $1 } -vols :: { [GlobalReg] } +vols :: { [GlobalRegUse] } : '[' ']' { [] } - | '[' '*' ']' {% do platform <- PD.getPlatform - ; return (realArgRegsCover platform) } - -- All of them. See comment attached - -- to realArgRegsCover - | '[' globals ']' { map globalRegUseGlobalReg $2 } + | '[' '*' ']' {% do platform <- PD.getPlatform; + let { gregs = realArgRegsCover platform + ; uses = map (\gr -> GlobalRegUse gr (globalRegSpillType platform gr)) gregs }; + return uses } + -- All of them. See comment attached + -- to realArgRegsCover + | '[' globals ']' { $2 } globals :: { [GlobalRegUse] } : GLOBALREG { [$1] } @@ -1374,7 +1376,7 @@ mkReturnSimple profile actuals updfr_off = where e = entryCode platform (cmmLoadGCWord platform (CmmStackSlot Old updfr_off)) platform = profilePlatform profile -doRawJump :: CmmParse CmmExpr -> [GlobalReg] -> CmmParse () +doRawJump :: CmmParse CmmExpr -> [GlobalRegUse] -> CmmParse () doRawJump expr_code vols = do profile <- getProfile expr <- expr_code ===================================== compiler/GHC/Cmm/ProcPoint.hs ===================================== @@ -262,7 +262,7 @@ splitAtProcPoints platform entry_label callPPs procPoints procMap cmmProc = do let liveness = cmmGlobalLiveness platform g - let ppLiveness pp = filter isArgReg $ regSetToList $ + let ppLiveness pp = filter (isArgReg . globalRegUseGlobalReg) $ regSetToList $ expectJust "ppLiveness" $ mapLookup pp liveness graphEnv <- return $ foldlGraphBlocks add_block mapEmpty g ===================================== compiler/GHC/Cmm/Sink.hs ===================================== @@ -709,7 +709,7 @@ conflicts platform (r, rhs, addr) node globalRegistersConflict :: Platform -> CmmExpr -> CmmNode e x -> Bool globalRegistersConflict platform expr node = -- See Note [Inlining foldRegsDefd] - inline foldRegsDefd platform (\b r -> b || globalRegUsedIn platform r expr) + inline foldRegsDefd platform (\b r -> b || globalRegUsedIn platform (globalRegUseGlobalReg r) expr) False node -- Returns True if node defines any local registers that are used in the ===================================== compiler/GHC/CmmToAsm/AArch64.hs ===================================== @@ -44,7 +44,7 @@ ncgAArch64 config -- | Instruction instance for aarch64 instance Instruction AArch64.Instr where regUsageOfInstr = AArch64.regUsageOfInstr - patchRegsOfInstr = AArch64.patchRegsOfInstr + patchRegsOfInstr _ = AArch64.patchRegsOfInstr isJumpishInstr = AArch64.isJumpishInstr jumpDestsOfInstr = AArch64.jumpDestsOfInstr canFallthroughTo = AArch64.canFallthroughTo ===================================== compiler/GHC/CmmToAsm/Instr.hs ===================================== @@ -62,7 +62,9 @@ class Instruction instr where -- | Apply a given mapping to all the register references in this -- instruction. patchRegsOfInstr - :: instr + :: HasDebugCallStack + => Platform + -> instr -> (Reg -> Reg) -> instr ===================================== compiler/GHC/CmmToAsm/PPC.hs ===================================== @@ -43,7 +43,7 @@ ncgPPC config = NcgImpl -- | Instruction instance for powerpc instance Instruction PPC.Instr where regUsageOfInstr = PPC.regUsageOfInstr - patchRegsOfInstr = PPC.patchRegsOfInstr + patchRegsOfInstr _ = PPC.patchRegsOfInstr isJumpishInstr = PPC.isJumpishInstr jumpDestsOfInstr = PPC.jumpDestsOfInstr canFallthroughTo = PPC.canFallthroughTo ===================================== compiler/GHC/CmmToAsm/PPC/CodeGen.hs ===================================== @@ -195,8 +195,11 @@ stmtToInstrs stmt = do _ -> panic "stmtToInstrs: statement should have been cps'd away" -jumpRegs :: Platform -> [GlobalReg] -> [Reg] -jumpRegs platform gregs = [ RegReal r | Just r <- map (globalRegMaybe platform) gregs ] +jumpRegs :: Platform -> [GlobalRegUse] -> [RegFormat] +jumpRegs platform gregs = + [ RegFormat (RegReal r) (cmmTypeFormat ty) + | GlobalRegUse gr ty <- gregs + , Just r <- [globalRegMaybe platform gr] ] -------------------------------------------------------------------------------- -- | 'InstrBlock's are the insn sequences generated by the insn selectors. @@ -1091,7 +1094,7 @@ assignReg_FltCode = assignReg_IntCode -genJump :: CmmExpr{-the branch target-} -> [Reg] -> NatM InstrBlock +genJump :: CmmExpr{-the branch target-} -> [RegFormat] -> NatM InstrBlock genJump (CmmLit (CmmLabel lbl)) regs = return (unitOL $ JMP lbl regs) @@ -1101,7 +1104,7 @@ genJump tree gregs platform <- getPlatform genJump' tree (platformToGCP platform) gregs -genJump' :: CmmExpr -> GenCCallPlatform -> [Reg] -> NatM InstrBlock +genJump' :: CmmExpr -> GenCCallPlatform -> [RegFormat] -> NatM InstrBlock genJump' tree (GCP64ELF 1) regs = do ===================================== compiler/GHC/CmmToAsm/PPC/Instr.hs ===================================== @@ -221,11 +221,11 @@ data Instr -- Just True: branch likely taken -- Just False: branch likely not taken -- Nothing: no hint - | JMP CLabel [Reg] -- same as branch, + | JMP CLabel [RegFormat] -- same as branch, -- but with CLabel instead of block ID -- and live global registers | MTCTR Reg - | BCTR [Maybe BlockId] (Maybe CLabel) [Reg] + | BCTR [Maybe BlockId] (Maybe CLabel) [RegFormat] -- with list of local destinations, and -- jump table location if necessary | BL CLabel [Reg] -- with list of argument regs @@ -333,9 +333,9 @@ regUsageOfInstr platform instr CMPL _ reg ri -> usage (reg : regRI ri,[]) BCC _ _ _ -> noUsage BCCFAR _ _ _ -> noUsage - JMP _ regs -> usage (regs, []) + JMP _ regs -> usage (map regFormatReg regs, []) MTCTR reg -> usage ([reg],[]) - BCTR _ _ regs -> usage (regs, []) + BCTR _ _ regs -> usage (map regFormatReg regs, []) BL _ params -> usage (params, callClobberedRegs platform) BCTRL params -> usage (params, callClobberedRegs platform) ===================================== compiler/GHC/CmmToAsm/Reg/Graph/Spill.hs ===================================== @@ -208,9 +208,9 @@ regSpill_instr platform regSlotMap (LiveInstr instr (Just _)) = do let rsSpillModify = filter (\r -> elemUFM (regFormatReg r) regSlotMap) rsModify -- rewrite the instr and work out spill code. - (instr1, prepost1) <- mapAccumLM (spillRead regSlotMap) instr rsSpillRead - (instr2, prepost2) <- mapAccumLM (spillWrite regSlotMap) instr1 rsSpillWritten - (instr3, prepost3) <- mapAccumLM (spillModify regSlotMap) instr2 rsSpillModify + (instr1, prepost1) <- mapAccumLM (spillRead platform regSlotMap) instr rsSpillRead + (instr2, prepost2) <- mapAccumLM (spillWrite platform regSlotMap) instr1 rsSpillWritten + (instr3, prepost3) <- mapAccumLM (spillModify platform regSlotMap) instr2 rsSpillModify let (mPrefixes, mPostfixes) = unzip (prepost1 ++ prepost2 ++ prepost3) let prefixes = concat mPrefixes @@ -228,14 +228,15 @@ regSpill_instr platform regSlotMap (LiveInstr instr (Just _)) = do -- writes to a vreg that is being spilled. spillRead :: Instruction instr - => UniqFM Reg Int + => Platform + -> UniqFM Reg Int -> instr -> RegFormat -> SpillM (instr, ([LiveInstr instr'], [LiveInstr instr'])) -spillRead regSlotMap instr (RegFormat reg fmt) +spillRead platform regSlotMap instr (RegFormat reg fmt) | Just slot <- lookupUFM regSlotMap reg - = do (instr', nReg) <- patchInstr reg instr + = do (instr', nReg) <- patchInstr platform reg instr modify $ \s -> s { stateSpillSL = addToUFM_C accSpillSL (stateSpillSL s) reg (reg, 0, 1) } @@ -251,14 +252,15 @@ spillRead regSlotMap instr (RegFormat reg fmt) -- writes to a vreg that is being spilled. spillWrite :: Instruction instr - => UniqFM Reg Int + => Platform + -> UniqFM Reg Int -> instr -> RegFormat -> SpillM (instr, ([LiveInstr instr'], [LiveInstr instr'])) -spillWrite regSlotMap instr (RegFormat reg fmt) +spillWrite platform regSlotMap instr (RegFormat reg fmt) | Just slot <- lookupUFM regSlotMap reg - = do (instr', nReg) <- patchInstr reg instr + = do (instr', nReg) <- patchInstr platform reg instr modify $ \s -> s { stateSpillSL = addToUFM_C accSpillSL (stateSpillSL s) reg (reg, 1, 0) } @@ -274,14 +276,15 @@ spillWrite regSlotMap instr (RegFormat reg fmt) -- both reads and writes to a vreg that is being spilled. spillModify :: Instruction instr - => UniqFM Reg Int + => Platform + -> UniqFM Reg Int -> instr -> RegFormat -> SpillM (instr, ([LiveInstr instr'], [LiveInstr instr'])) -spillModify regSlotMap instr (RegFormat reg fmt) +spillModify platform regSlotMap instr (RegFormat reg fmt) | Just slot <- lookupUFM regSlotMap reg - = do (instr', nReg) <- patchInstr reg instr + = do (instr', nReg) <- patchInstr platform reg instr modify $ \s -> s { stateSpillSL = addToUFM_C accSpillSL (stateSpillSL s) reg (reg, 1, 1) } @@ -297,9 +300,9 @@ spillModify regSlotMap instr (RegFormat reg fmt) -- virtual reg. patchInstr :: Instruction instr - => Reg -> instr -> SpillM (instr, Reg) + => Platform -> Reg -> instr -> SpillM (instr, Reg) -patchInstr reg instr +patchInstr platform reg instr = do nUnique <- newUnique -- The register we're rewriting is supposed to be virtual. @@ -312,19 +315,19 @@ patchInstr reg instr RegReal{} -> panic "RegAlloc.Graph.Spill.patchIntr: not patching real reg" - let instr' = patchReg1 reg nReg instr + let instr' = patchReg1 platform reg nReg instr return (instr', nReg) patchReg1 :: Instruction instr - => Reg -> Reg -> instr -> instr + => Platform -> Reg -> Reg -> instr -> instr -patchReg1 old new instr +patchReg1 platform old new instr = let patchF r | r == old = new | otherwise = r - in patchRegsOfInstr instr patchF + in patchRegsOfInstr platform instr patchF -- Spiller monad -------------------------------------------------------------- ===================================== compiler/GHC/CmmToAsm/Reg/Linear.hs ===================================== @@ -575,7 +575,7 @@ genRaInsn block_live new_instrs block_id instr r_dying w_dying = do patched_instr :: instr patched_instr - = patchRegsOfInstr adjusted_instr patchLookup + = patchRegsOfInstr platform adjusted_instr patchLookup patchLookup :: Reg -> Reg patchLookup x ===================================== compiler/GHC/CmmToAsm/Reg/Linear/X86.hs ===================================== @@ -32,12 +32,12 @@ getFreeRegs platform cls (FreeRegs f) = case cls of RcInteger -> [ RealRegSingle i - | i <- [ 0 .. lastint platform ] + | i <- intregnos platform , testBit f i ] RcFloatOrVector -> [ RealRegSingle i - | i <- [ lastint platform + 1 .. lastxmm platform ] + | i <- xmmregnos platform , testBit f i ] ===================================== compiler/GHC/CmmToAsm/Reg/Linear/X86_64.hs ===================================== @@ -32,12 +32,12 @@ getFreeRegs platform cls (FreeRegs f) = case cls of RcInteger -> [ RealRegSingle i - | i <- [ 0 .. lastint platform ] + | i <- intregnos platform , testBit f i ] RcFloatOrVector -> [ RealRegSingle i - | i <- [ lastint platform + 1 .. lastxmm platform ] + | i <- xmmregnos platform , testBit f i ] ===================================== compiler/GHC/CmmToAsm/Reg/Liveness.hs ===================================== @@ -114,9 +114,9 @@ instance Instruction instr => Instruction (InstrSR instr) where SPILL reg _ -> RU [reg] [] RELOAD _ reg -> RU [] [reg] - patchRegsOfInstr i f + patchRegsOfInstr platform i f = case i of - Instr instr -> Instr (patchRegsOfInstr instr f) + Instr instr -> Instr (patchRegsOfInstr platform instr f) SPILL reg slot -> SPILL (updReg f reg) slot RELOAD slot reg -> RELOAD slot (updReg f reg) where @@ -648,7 +648,7 @@ patchEraseLive platform patchF cmm | otherwise = li' : patchInstrs lis - where li' = patchRegsLiveInstr patchF li + where li' = patchRegsLiveInstr platform patchF li eatMe r1 r2 live -- source and destination regs are the same @@ -666,17 +666,18 @@ patchEraseLive platform patchF cmm -- patchRegsLiveInstr :: (Instruction instr, HasDebugCallStack) - => (Reg -> Reg) + => Platform + -> (Reg -> Reg) -> LiveInstr instr -> LiveInstr instr -patchRegsLiveInstr patchF li +patchRegsLiveInstr platform patchF li = case li of LiveInstr instr Nothing - -> LiveInstr (patchRegsOfInstr instr patchF) Nothing + -> LiveInstr (patchRegsOfInstr platform instr patchF) Nothing LiveInstr instr (Just live) -> LiveInstr - (patchRegsOfInstr instr patchF) + (patchRegsOfInstr platform instr patchF) (Just live { -- WARNING: have to go via lists here because patchF changes the uniq in the Reg liveBorn = mapRegFormatSet patchF $ liveBorn live ===================================== compiler/GHC/CmmToAsm/X86/CodeGen.hs ===================================== @@ -378,8 +378,11 @@ stmtToInstrs bid stmt = do panic "stmtToInstrs: statement should have been cps'd away" -jumpRegs :: Platform -> [GlobalReg] -> [Reg] -jumpRegs platform gregs = [ RegReal r | Just r <- map (globalRegMaybe platform) gregs ] +jumpRegs :: Platform -> [GlobalRegUse] -> [RegFormat] +jumpRegs platform gregs = + [ RegFormat (RegReal r) (cmmTypeFormat ty) + | GlobalRegUse gr ty <- gregs + , Just r <- [globalRegMaybe platform gr] ] -------------------------------------------------------------------------------- -- | 'InstrBlock's are the insn sequences generated by the insn selectors. @@ -535,6 +538,8 @@ mkMOV platform fmt op1 op2 = cls1 = case op1 of { OpReg r1 -> Just (targetClassOfReg platform r1); _ -> Nothing } cls2 = case op2 of { OpReg r2 -> Just (targetClassOfReg platform r2); _ -> Nothing } + + assignMem_I64Code :: CmmExpr -> CmmExpr -> NatM InstrBlock assignMem_I64Code addrTree valueTree = do platform <- getPlatform @@ -2848,7 +2853,7 @@ assignReg_VecCode format reg src = do let flag = use_avx || use_sse return (src_code (getVecRegisterReg platform flag format reg)) -genJump :: CmmExpr{-the branch target-} -> [Reg] -> NatM InstrBlock +genJump :: CmmExpr{-the branch target-} -> [RegFormat] -> NatM InstrBlock genJump (CmmLoad mem _ _) regs = do Amode target code <- getAmode mem @@ -3479,11 +3484,11 @@ genCCall64 addr conv dest_regs args = do let prom_args = map (maybePromoteCArg platform W32) args let load_args :: [CmmExpr] - -> [Reg] -- int regs avail for args - -> [Reg] -- FP regs avail for args + -> [RegFormat] -- int regs avail for args + -> [RegFormat] -- FP regs avail for args -> InstrBlock -- code computing args -> InstrBlock -- code assigning args to ABI regs - -> NatM ([CmmExpr],[Reg],[Reg],InstrBlock,InstrBlock) + -> NatM ([CmmExpr],[RegFormat],[RegFormat],InstrBlock,InstrBlock) -- no more regs to use load_args args [] [] code acode = return (args, [], [], code, acode) @@ -3495,12 +3500,12 @@ genCCall64 addr conv dest_regs args = do load_args (arg : rest) aregs fregs code acode | isFloatType arg_rep = case fregs of [] -> push_this_arg - (r:rs) -> do + (RegFormat r _fmt:rs) -> do (code',acode') <- reg_this_arg r load_args rest aregs rs code' acode' | otherwise = case aregs of [] -> push_this_arg - (r:rs) -> do + (RegFormat r _fmt:rs) -> do (code',acode') <- reg_this_arg r load_args rest rs fregs code' acode' where @@ -3540,11 +3545,11 @@ genCCall64 addr conv dest_regs args = do arg_fmt = cmmTypeFormat arg_rep load_args_win :: [CmmExpr] - -> [Reg] -- used int regs - -> [Reg] -- used FP regs + -> [RegFormat] -- used int regs + -> [RegFormat] -- used FP regs -> [(Reg, Reg)] -- (int, FP) regs avail for args -> InstrBlock - -> NatM ([CmmExpr],[Reg],[Reg],InstrBlock,InstrBlock) + -> NatM ([CmmExpr],[RegFormat],[RegFormat],InstrBlock,InstrBlock) load_args_win args usedInt usedFP [] code = return (args, usedInt, usedFP, code, nilOL) -- no more regs to use @@ -3555,16 +3560,19 @@ genCCall64 addr conv dest_regs args = do ((ireg, freg) : regs) code | isFloatType arg_rep = do arg_code <- getAnyReg arg - load_args_win rest (ireg : usedInt) (freg : usedFP) regs + load_args_win rest (mkRegFormat platform ireg II64: usedInt) (mkRegFormat platform freg FF64 : usedFP) regs (code `appOL` arg_code freg `snocOL` -- If we are calling a varargs function -- then we need to define ireg as well -- as freg - mkMOV platform II64 (OpReg freg) (OpReg ireg)) + CVTTSD2SIQ II64 (OpReg freg) ireg) + -- SLD TODO: I changed this from MOV FF64 (OpReg freg) (OpReg ireg) + -- to CVTTSD2SIQ ... + -- because it is going between two different types of register | otherwise = do arg_code <- getAnyReg arg - load_args_win rest (ireg : usedInt) usedFP regs + load_args_win rest (mkRegFormat platform ireg II64: usedInt) usedFP regs (code `appOL` arg_code ireg) where arg_rep = cmmExprType platform arg @@ -3611,19 +3619,20 @@ genCCall64 addr conv dest_regs args = do if platformOS platform == OSMinGW32 then load_args_win prom_args [] [] (allArgRegs platform) nilOL else do + let intArgRegs = map (\r -> mkRegFormat platform r II64) $ allIntArgRegs platform + fpArgRegs = map (\r -> mkRegFormat platform r FF64) $ allFPArgRegs platform (stack_args, aregs, fregs, load_args_code, assign_args_code) - <- load_args prom_args (allIntArgRegs platform) - (allFPArgRegs platform) - nilOL nilOL + <- load_args prom_args intArgRegs fpArgRegs nilOL nilOL let used_regs rs as = dropTail (length rs) as - fregs_used = used_regs fregs (allFPArgRegs platform) - aregs_used = used_regs aregs (allIntArgRegs platform) + fregs_used = used_regs fregs fpArgRegs + aregs_used = used_regs aregs intArgRegs return (stack_args, aregs_used, fregs_used, load_args_code , assign_args_code) let + wordFmt = archWordFormat (target32Bit platform) arg_regs_used = int_regs_used ++ fp_regs_used - arg_regs = [eax] ++ arg_regs_used + arg_regs = [mkRegFormat platform eax wordFmt] ++ arg_regs_used -- for annotating the call instruction with sse_regs = length fp_regs_used arg_stack_slots = if platformOS platform == OSMinGW32 ===================================== compiler/GHC/CmmToAsm/X86/Instr.hs ===================================== @@ -71,7 +71,7 @@ import GHC.Types.Basic (Alignment) import GHC.Cmm.DebugBlock (UnwindTable) import GHC.Utils.Misc ( HasDebugCallStack ) -import Data.Maybe (fromMaybe) +import GHC.Data.Maybe -- Format of an x86/x86_64 memory address, in bytes. -- @@ -316,7 +316,7 @@ data Instr -- | POPA -- Jumping around. - | JMP Operand [Reg] -- including live Regs at the call + | JMP Operand [RegFormat] -- including live Regs at the call | JXX Cond BlockId -- includes unconditional branches | JXX_GBL Cond Imm -- non-local version of JXX -- Table jump @@ -326,7 +326,7 @@ data Instr CLabel -- Label of jump table -- | X86 call instruction | CALL (Either Imm Reg) -- ^ Jump target - [Reg] -- ^ Arguments (required for register allocation) + [RegFormat] -- ^ Arguments (required for register allocation) -- Other things. | CLTD Format -- sign extend %eax into %edx:%eax @@ -419,8 +419,16 @@ regUsageOfInstr :: Platform -> Instr -> RegUsage regUsageOfInstr platform instr = case instr of MOV fmt src dst -> usageRW fmt src dst - MOVD fmt src dst -> usageRW fmt src dst - CMOV _ fmt src dst -> mkRU fmt (use_R src [dst]) [dst] + MOVD fmt src dst -> + mkRU (use_R fmt src []) (use_R out_fmt dst []) + where + out_fmt = case fmt of + II32 -> FF32 + II64 -> FF64 + FF32 -> II32 + FF64 -> II64 + _ -> panic "MOVD: not a scalar 32/64 bit format" + CMOV _ fmt src dst -> mkRU (use_R fmt src [mk fmt dst]) [mk fmt dst] MOVZxL fmt src dst -> usageRW fmt src dst MOVSxL fmt src dst -> usageRW fmt src dst LEA fmt src dst -> usageRW fmt src dst @@ -431,80 +439,80 @@ regUsageOfInstr platform instr IMUL fmt src dst -> usageRM fmt src dst -- Result of IMULB will be in just in %ax - IMUL2 II8 src -> mkRU II8 (eax:use_R src []) [eax] + IMUL2 II8 src -> mkRU (mk II8 eax:use_R II8 src []) [mk II8 eax] -- Result of IMUL for wider values, will be split between %dx/%edx/%rdx and -- %ax/%eax/%rax. - IMUL2 fmt src -> mkRU fmt (eax:use_R src []) [eax,edx] + IMUL2 fmt src -> mkRU (mk fmt eax:use_R fmt src []) [mk fmt eax,mk fmt edx] MUL fmt src dst -> usageRM fmt src dst - MUL2 fmt src -> mkRU fmt (eax:use_R src []) [eax,edx] - DIV fmt op -> mkRU fmt (eax:edx:use_R op []) [eax,edx] - IDIV fmt op -> mkRU fmt (eax:edx:use_R op []) [eax,edx] + MUL2 fmt src -> mkRU (mk fmt eax:use_R fmt src []) [mk fmt eax,mk fmt edx] + DIV fmt op -> mkRU (mk fmt eax:mk fmt edx:use_R fmt op []) [mk fmt eax, mk fmt edx] + IDIV fmt op -> mkRU (mk fmt eax:mk fmt edx:use_R fmt op []) [mk fmt eax, mk fmt edx] ADD_CC fmt src dst -> usageRM fmt src dst SUB_CC fmt src dst -> usageRM fmt src dst AND fmt src dst -> usageRM fmt src dst OR fmt src dst -> usageRM fmt src dst XOR fmt (OpReg src) (OpReg dst) - | src == dst -> mkRU fmt [] [dst] + | src == dst -> mkRU [] [mk fmt dst] XOR fmt src dst -> usageRM fmt src dst NOT fmt op -> usageM fmt op - BSWAP fmt reg -> mkRU fmt [reg] [reg] + BSWAP fmt reg -> mkRU [mk fmt reg] [mk fmt reg] NEGI fmt op -> usageM fmt op SHL fmt imm dst -> usageRM fmt imm dst SAR fmt imm dst -> usageRM fmt imm dst SHR fmt imm dst -> usageRM fmt imm dst SHLD fmt imm dst1 dst2 -> usageRMM fmt imm dst1 dst2 SHRD fmt imm dst1 dst2 -> usageRMM fmt imm dst1 dst2 - BT fmt _ src -> mkRUR fmt (use_R src []) - - PUSH fmt op -> mkRUR fmt (use_R op []) - POP fmt op -> mkRU fmt [] (def_W op) - TEST fmt src dst -> mkRUR fmt (use_R src $! use_R dst []) - CMP fmt src dst -> mkRUR fmt (use_R src $! use_R dst []) - SETCC _ op -> mkRUFormat [] (def_W op) - JXX _ _ -> mkRUFormat [] [] - JXX_GBL _ _ -> mkRUFormat [] [] - JMP op regs -> mkRUFormat (use_R op regs) [] - JMP_TBL op _ _ _ -> mkRUFormat (use_R op []) [] - CALL (Left _) params -> mkRUFormat params (callClobberedRegs platform) - CALL (Right reg) params -> mkRUFormat (reg:params) (callClobberedRegs platform) - CLTD fmt -> mkRU fmt [eax] [edx] - NOP -> mkRUFormat [] [] - - X87Store fmt dst -> mkRUR fmt ( use_EA dst []) - - CVTSS2SD src dst -> mkRUFormat [src] [dst] - CVTSD2SS src dst -> mkRUFormat [src] [dst] - CVTTSS2SIQ _ src dst -> mkRUFormat (use_R src []) [dst] - CVTTSD2SIQ _ src dst -> mkRUFormat (use_R src []) [dst] - CVTSI2SS _ src dst -> mkRUFormat (use_R src []) [dst] - CVTSI2SD _ src dst -> mkRUFormat (use_R src []) [dst] + BT fmt _ src -> mkRUR (use_R fmt src []) + + PUSH fmt op -> mkRUR (use_R fmt op []) + POP fmt op -> mkRU [] (def_W fmt op) + TEST fmt src dst -> mkRUR (use_R fmt src $! use_R fmt dst []) + CMP fmt src dst -> mkRUR (use_R fmt src $! use_R fmt dst []) + SETCC _ op -> mkRU [] (def_W II8 op) + JXX _ _ -> mkRU [] [] + JXX_GBL _ _ -> mkRU [] [] + JMP op regs -> mkRU (use_R addrFmt op regs) [] + JMP_TBL op _ _ _ -> mkRU (use_R addrFmt op []) [] + CALL (Left _) params -> mkRU params (map mkFmt $ callClobberedRegs platform) + CALL (Right reg) params -> mkRU (mk addrFmt reg:params) (map mkFmt $ callClobberedRegs platform) + CLTD fmt -> mkRU [mk fmt eax] [mk fmt edx] + NOP -> mkRU [] [] + + X87Store _fmt dst -> mkRUR ( use_EA dst []) + + CVTSS2SD src dst -> mkRU [mk FF32 src] [mk FF64 dst] + CVTSD2SS src dst -> mkRU [mk FF64 src] [mk FF32 dst] + CVTTSS2SIQ fmt src dst -> mkRU (use_R FF32 src []) [mk fmt dst] + CVTTSD2SIQ fmt src dst -> mkRU (use_R FF64 src []) [mk fmt dst] + CVTSI2SS fmt src dst -> mkRU (use_R fmt src []) [mk FF32 dst] + CVTSI2SD fmt src dst -> mkRU (use_R fmt src []) [mk FF64 dst] FDIV fmt src dst -> usageRM fmt src dst - SQRT fmt src dst -> mkRU fmt (use_R src []) [dst] + SQRT fmt src dst -> mkRU (use_R fmt src []) [mk fmt dst] - FETCHGOT reg -> mkRU II64 [] [reg] - FETCHPC reg -> mkRU II64 [] [reg] + FETCHGOT reg -> mkRU [] [mk addrFmt reg] + FETCHPC reg -> mkRU [] [mk addrFmt reg] COMMENT _ -> noUsage LOCATION{} -> noUsage UNWIND{} -> noUsage DELTA _ -> noUsage - POPCNT fmt src dst -> mkRU fmt (use_R src []) [dst] - LZCNT fmt src dst -> mkRU fmt (use_R src []) [dst] - TZCNT fmt src dst -> mkRU fmt (use_R src []) [dst] - BSF fmt src dst -> mkRU fmt (use_R src []) [dst] - BSR fmt src dst -> mkRU fmt (use_R src []) [dst] + POPCNT fmt src dst -> mkRU (use_R fmt src []) [mk fmt dst] + LZCNT fmt src dst -> mkRU (use_R fmt src []) [mk fmt dst] + TZCNT fmt src dst -> mkRU (use_R fmt src []) [mk fmt dst] + BSF fmt src dst -> mkRU (use_R fmt src []) [mk fmt dst] + BSR fmt src dst -> mkRU (use_R fmt src []) [mk fmt dst] - PDEP fmt src mask dst -> mkRU fmt (use_R src $ use_R mask []) [dst] - PEXT fmt src mask dst -> mkRU fmt (use_R src $ use_R mask []) [dst] + PDEP fmt src mask dst -> mkRU (use_R fmt src $ use_R fmt mask []) [mk fmt dst] + PEXT fmt src mask dst -> mkRU (use_R fmt src $ use_R fmt mask []) [mk fmt dst] FMA3 fmt _ _ src3 src2 dst -> usageFMA fmt src3 src2 dst -- note: might be a better way to do this - PREFETCH _ fmt src -> mkRU fmt (use_R src []) [] + PREFETCH _ fmt src -> mkRU (use_R fmt src []) [] LOCK i -> regUsageOfInstr platform i XADD fmt src dst -> usageMM fmt src dst CMPXCHG fmt src dst -> usageRMM fmt src dst (OpReg eax) @@ -512,10 +520,10 @@ regUsageOfInstr platform instr MFENCE -> noUsage -- vector instructions - VBROADCAST fmt src dst -> mkRU fmt (use_EA src []) [dst] - VEXTRACT fmt _off src dst -> mkRU fmt [src] (use_R dst []) + VBROADCAST fmt src dst -> mkRU (use_EA src []) [mk fmt dst] + VEXTRACT fmt _off src dst -> mkRU [mk fmt src] (use_R fmt dst []) INSERTPS fmt (ImmInt off) src dst - -> mkRU fmt ((use_R src []) ++ [dst | not doesNotReadDst]) [dst] + -> mkRU ((use_R fmt src []) ++ [mk fmt dst | not doesNotReadDst]) [mk fmt dst] where -- Compute whether the instruction reads the destination register or not. -- Immediate bits: ss_dd_zzzz s = src pos, d = dst pos, z = zeroed components. @@ -524,42 +532,42 @@ regUsageOfInstr platform instr -- are being zeroed. where pos = ( off `shiftR` 4 ) .&. 0b11 INSERTPS fmt _off src dst - -> mkRU fmt ((use_R src []) ++ [dst]) [dst] - - VMOVU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) - MOVU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) - MOVA fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) - MOVL fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) - MOVH fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) - MOVDQU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) - VMOVDQU fmt src dst -> mkRU fmt (use_R src []) (use_R dst []) - - VPXOR fmt s1 s2 dst -> mkRU fmt [s1,s2] [dst] - - VADD fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] - VSUB fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] - VMUL fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] - VDIV fmt s1 s2 dst -> mkRU fmt ((use_R s1 []) ++ [s2]) [dst] - - VPSHUFD fmt _off src dst - -> mkRU fmt (use_R src []) [dst] - PSHUFD fmt _off src dst - -> mkRU fmt (use_R src []) [dst] - SHUFPD fmt _off src dst - -> mkRU fmt (use_R src [dst]) [dst] - SHUFPS fmt _off src dst - -> mkRU fmt (use_R src [dst]) [dst] - VSHUFPD fmt _off src1 src2 dst - -> mkRU fmt (use_R src1 [src2]) [dst] - VSHUFPS fmt _off src1 src2 dst - -> mkRU fmt (use_R src1 [src2]) [dst] - - PSLLDQ fmt off dst -> mkRU fmt (use_R off []) [dst] + -> mkRU ((use_R fmt src []) ++ [mk fmt dst]) [mk fmt dst] + + VMOVU fmt src dst -> mkRU (use_R fmt src []) (use_R fmt dst []) + MOVU fmt src dst -> mkRU (use_R fmt src []) (use_R fmt dst []) + MOVA fmt src dst -> mkRU (use_R fmt src []) (use_R fmt dst []) + MOVL fmt src dst -> mkRU (use_R fmt src []) (use_R fmt dst []) + MOVH fmt src dst -> mkRU (use_R fmt src []) (use_R fmt dst []) + MOVDQU fmt src dst -> mkRU (use_R fmt src []) (use_R fmt dst []) + VMOVDQU fmt src dst -> mkRU (use_R fmt src []) (use_R fmt dst []) + + VPXOR fmt s1 s2 dst -> mkRU (map (mk fmt) [s1,s2]) [mk fmt dst] + + VADD fmt s1 s2 dst -> mkRU ((use_R fmt s1 []) ++ [mk fmt s2]) [mk fmt dst] + VSUB fmt s1 s2 dst -> mkRU ((use_R fmt s1 []) ++ [mk fmt s2]) [mk fmt dst] + VMUL fmt s1 s2 dst -> mkRU ((use_R fmt s1 []) ++ [mk fmt s2]) [mk fmt dst] + VDIV fmt s1 s2 dst -> mkRU ((use_R fmt s1 []) ++ [mk fmt s2]) [mk fmt dst] + + VPSHUFD fmt _off src dst + -> mkRU (use_R fmt src []) [mk fmt dst] + PSHUFD fmt _off src dst + -> mkRU (use_R fmt src []) [mk fmt dst] + SHUFPD fmt _off src dst + -> mkRU (use_R fmt src [mk fmt dst]) [mk fmt dst] + SHUFPS fmt _off src dst + -> mkRU (use_R fmt src [mk fmt dst]) [mk fmt dst] + VSHUFPD fmt _off src1 src2 dst + -> mkRU (use_R fmt src1 [mk fmt src2]) [mk fmt dst] + VSHUFPS fmt _off src1 src2 dst + -> mkRU (use_R fmt src1 [mk fmt src2]) [mk fmt dst] + + PSLLDQ fmt off dst -> mkRU (use_R fmt off []) [mk fmt dst] MOVHLPS fmt src dst - -> mkRU fmt (use_R src []) [dst] + -> mkRU (use_R fmt src []) [mk fmt dst] PUNPCKLQDQ fmt src dst - -> mkRU fmt (use_R src [dst]) [dst] + -> mkRU (use_R fmt src [mk fmt dst]) [mk fmt dst] _other -> panic "regUsage: unrecognised instr" where @@ -574,81 +582,91 @@ regUsageOfInstr platform instr -- 2 operand form; first operand Read; second Written usageRW :: HasDebugCallStack => Format -> Operand -> Operand -> RegUsage - usageRW fmt op (OpReg reg) = mkRU fmt (use_R op []) [reg] - usageRW fmt op (OpAddr ea) = mkRUR fmt (use_R op $! use_EA ea []) + usageRW fmt op (OpReg reg) = mkRU (use_R fmt op []) [mk fmt reg] + usageRW fmt op (OpAddr ea) = mkRUR (use_R fmt op $! use_EA ea []) usageRW _ _ _ = panic "X86.RegInfo.usageRW: no match" -- 2 operand form; first operand Read; second Modified usageRM :: HasDebugCallStack => Format -> Operand -> Operand -> RegUsage - usageRM fmt op (OpReg reg) = mkRU fmt (use_R op [reg]) [reg] - usageRM fmt op (OpAddr ea) = mkRUR fmt (use_R op $! use_EA ea []) + usageRM fmt op (OpReg reg) = mkRU (use_R fmt op [mk fmt reg]) [mk fmt reg] + usageRM fmt op (OpAddr ea) = mkRUR (use_R fmt op $! use_EA ea []) usageRM _ _ _ = panic "X86.RegInfo.usageRM: no match" -- 2 operand form; first operand Modified; second Modified usageMM :: HasDebugCallStack => Format -> Operand -> Operand -> RegUsage - usageMM fmt (OpReg src) (OpReg dst) = mkRU fmt [src, dst] [src, dst] - usageMM fmt (OpReg src) (OpAddr ea) = mkRU fmt (use_EA ea [src]) [src] - usageMM fmt (OpAddr ea) (OpReg dst) = mkRU fmt (use_EA ea [dst]) [dst] + usageMM fmt (OpReg src) (OpReg dst) = mkRU (map (mk fmt) [src, dst]) (map (mk fmt) [src, dst]) + usageMM fmt (OpReg src) (OpAddr ea) = mkRU (use_EA ea [mk fmt src]) [mk fmt src] + usageMM fmt (OpAddr ea) (OpReg dst) = mkRU (use_EA ea [mk fmt dst]) [mk fmt dst] usageMM _ _ _ = panic "X86.RegInfo.usageMM: no match" -- 3 operand form; first operand Read; second Modified; third Modified usageRMM :: HasDebugCallStack => Format -> Operand -> Operand -> Operand -> RegUsage - usageRMM fmt (OpReg src) (OpReg dst) (OpReg reg) = mkRU fmt [src, dst, reg] [dst, reg] - usageRMM fmt (OpReg src) (OpAddr ea) (OpReg reg) = mkRU fmt (use_EA ea [src, reg]) [reg] + usageRMM fmt (OpReg src) (OpReg dst) (OpReg reg) = mkRU (map (mk fmt) [src, dst, reg]) (map (mk fmt) [dst, reg]) + usageRMM fmt (OpReg src) (OpAddr ea) (OpReg reg) = mkRU (use_EA ea (map (mk fmt) [src, reg])) [mk fmt reg] usageRMM _ _ _ _ = panic "X86.RegInfo.usageRMM: no match" -- 3 operand form of FMA instructions. usageFMA :: HasDebugCallStack => Format -> Operand -> Reg -> Reg -> RegUsage - usageFMA fmt (OpReg src1) src2 dst - = mkRU fmt [src1, src2, dst] [dst] + usageFMA fmt (OpReg src1) src2 dst = + mkRU (map (\r -> mkRegFormat platform r fmt) [src1, src2, dst]) [ mkRegFormat platform dst fmt ] usageFMA fmt (OpAddr ea1) src2 dst - = mkRU fmt (use_EA ea1 [src2, dst]) [dst] + = mkRU (use_EA ea1 (map (\r -> mkRegFormat platform r fmt) [src2, dst])) [ mkRegFormat platform dst fmt ] usageFMA _ _ _ _ = panic "X86.RegInfo.usageFMA: no match" -- 1 operand form; operand Modified usageM :: HasDebugCallStack => Format -> Operand -> RegUsage - usageM fmt (OpReg reg) = mkRU fmt [reg] [reg] - usageM fmt (OpAddr ea) = mkRUR fmt (use_EA ea []) - usageM _ _ = panic "X86.RegInfo.usageM: no match" + usageM fmt (OpReg reg) = + let r' = mk fmt reg + in mkRU [r'] [r'] + usageM _ (OpAddr ea) = mkRUR (use_EA ea []) + usageM _ _ = panic "X86.RegInfo.usageM: no match" -- Registers defd when an operand is written. - def_W (OpReg reg) = [reg] - def_W (OpAddr _ ) = [] - def_W _ = panic "X86.RegInfo.def_W: no match" + def_W fmt (OpReg reg) = [mk fmt reg] + def_W _ (OpAddr _ ) = [] + def_W _ _ = panic "X86.RegInfo.def_W: no match" -- Registers used when an operand is read. - use_R (OpReg reg) tl = reg : tl - use_R (OpImm _) tl = tl - use_R (OpAddr ea) tl = use_EA ea tl + use_R fmt (OpReg reg) tl = mk fmt reg : tl + use_R _ (OpImm _) tl = tl + use_R _ (OpAddr ea) tl = use_EA ea tl -- Registers used to compute an effective address. use_EA (ImmAddr _ _) tl = tl use_EA (AddrBaseIndex base index _) tl = use_base base $! use_index index tl - where use_base (EABaseReg r) tl = r : tl + where use_base (EABaseReg r) tl = mk addrFmt r : tl use_base _ tl = tl use_index EAIndexNone tl = tl - use_index (EAIndex i _) tl = i : tl - - mkRUR :: HasDebugCallStack => Format -> [Reg] -> RegUsage - mkRUR fmt src = src' `seq` RU (map (\ r -> mkRegFormat platform r fmt) src') [] - where src' = filter (interesting platform) src - - mkRU :: HasDebugCallStack => Format -> [Reg] -> [Reg] -> RegUsage - mkRU fmt src dst = src' `seq` dst' `seq` RU (map (\ r -> mkRegFormat platform r fmt) src') (map (\ r -> mkRegFormat platform r fmt) dst') - where src' = filter (interesting platform) src - dst' = filter (interesting platform) dst - - mkRUFormat :: HasDebugCallStack => [Reg] -> [Reg] -> RegUsage - mkRUFormat src dst = src' `seq` dst' `seq` RU (map mkFormat src') (map mkFormat dst') - where src' = filter (interesting platform) src - dst' = filter (interesting platform) dst - mkFormat reg = - mkRegFormat platform reg $ - case targetClassOfReg platform reg of - RcInteger -> archWordFormat (target32Bit platform) - RcFloatOrVector -> FF64 + use_index (EAIndex i _) tl = mk addrFmt i : tl + + mkRUR :: [RegFormat] -> RegUsage + mkRUR src = mkRU src [] + + mkRU :: [RegFormat] -> [RegFormat] -> RegUsage + mkRU src dst = src' `seq` dst' `seq` RU src' dst' + where src' = filter (interesting platform . regFormatReg) src + dst' = filter (interesting platform . regFormatReg) dst + + addrFmt = archWordFormat (target32Bit platform) + mk :: HasDebugCallStack => Format -> Reg -> RegFormat + mk fmt r = mkRegFormat platform r fmt + + mkFmt :: HasDebugCallStack => Reg -> RegFormat + mkFmt r = RegFormat r $ case targetClassOfReg platform r of + RcInteger -> addrFmt + RcFloatOrVector -> FF64 + + --mkRUFormat :: HasDebugCallStack => [Reg] -> [Reg] -> RegUsage + --mkRUFormat src dst = src' `seq` dst' `seq` RU (map mkFormat src') (map mkFormat dst') + -- where src' = filter (interesting platform) src + -- dst' = filter (interesting platform) dst + -- mkFormat reg = + -- mkRegFormat platform reg $ + -- case targetClassOfReg platform reg of + -- RcInteger -> archWordFormat (target32Bit platform) + -- RcFloatOrVector -> FF64 -- | Is this register interesting for the register allocator? interesting :: Platform -> Reg -> Bool @@ -659,10 +677,26 @@ interesting platform (RegReal (RealRegSingle i)) = freeReg platform i -- | Applies the supplied function to all registers in instructions. -- Typically used to change virtual registers to real registers. -patchRegsOfInstr :: Instr -> (Reg -> Reg) -> Instr -patchRegsOfInstr instr env - = case instr of - MOV fmt src dst -> patch2 (MOV fmt) src dst +patchRegsOfInstr :: HasDebugCallStack => Platform -> Instr -> (Reg -> Reg) -> Instr +patchRegsOfInstr platform instr env + = case instr of + MOV fmt src dst -> + mkMOV fmt (patchOp src) (patchOp dst) + where + fmtCls = if isIntFormat fmt then RcInteger else RcFloatOrVector + mkMOV :: HasDebugCallStack => Format -> Operand -> Operand -> Instr + mkMOV fmt op1 op2 = + assertPpr (all (== fmtCls) $ catMaybes [cls1, cls2]) + (vcat [ text "patchRegsOfInstr produced invalid MOV instruction" + , text "fmt:" <+> ppr fmt + , case op1 of { OpReg r1 -> ppr r1 <+> dcolon <+> ppr (fromJust cls1); _ -> empty } + , case op2 of { OpReg r2 -> ppr r2 <+> dcolon <+> ppr (fromJust cls2); _ -> empty } + ]) + $ MOV fmt op1 op2 + where + cls1 = case op1 of { OpReg r1 -> Just (targetClassOfReg platform r1); _ -> Nothing } + cls2 = case op2 of { OpReg r2 -> Just (targetClassOfReg platform r2); _ -> Nothing } + MOVD fmt src dst -> patch2 (MOVD fmt) src dst CMOV cc fmt src dst -> CMOV cc fmt (patchOp src) (env dst) MOVZxL fmt src dst -> patch2 (MOVZxL fmt) src dst @@ -740,7 +774,7 @@ patchRegsOfInstr instr env PREFETCH lvl format src -> PREFETCH lvl format (patchOp src) - LOCK i -> LOCK (patchRegsOfInstr i env) + LOCK i -> LOCK (patchRegsOfInstr platform i env) XADD fmt src dst -> patch2 (XADD fmt) src dst CMPXCHG fmt src dst -> patch2 (CMPXCHG fmt) src dst XCHG fmt src dst -> XCHG fmt (patchOp src) (env dst) @@ -1138,7 +1172,7 @@ mkStackAllocInstr platform amount case platformArch platform of ArchX86_64 | needs_probe_call platform amount -> [ MOV II64 (OpImm (ImmInt amount)) (OpReg rax) - , CALL (Left $ strImmLit (fsLit "___chkstk_ms")) [rax] + , CALL (Left $ strImmLit (fsLit "___chkstk_ms")) [mkRegFormat platform rax II64] , SUB II64 (OpReg rax) (OpReg rsp) ] | otherwise -> ===================================== compiler/GHC/CmmToAsm/X86/Regs.hs ===================================== @@ -38,6 +38,7 @@ module GHC.CmmToAsm.X86.Regs ( xmm8, xmm9, xmm10, xmm11, xmm12, xmm13, xmm14, xmm15, xmm, firstxmm, lastxmm, + intregnos, xmmregnos, ripRel, allFPArgRegs, ===================================== compiler/GHC/CmmToLlvm.hs ===================================== @@ -139,7 +139,7 @@ llvmGroupLlvmGens cmm = do Nothing -> l Just (CmmStaticsRaw info_lbl _) -> info_lbl lml <- strCLabel_llvm l' - funInsert lml =<< llvmFunTy live + funInsert lml =<< llvmFunTy (map globalRegUseGlobalReg live) return Nothing cdata <- fmap catMaybes $ mapM split cmm ===================================== compiler/GHC/CmmToLlvm/CodeGen.hs ===================================== @@ -57,7 +57,7 @@ genLlvmProc :: RawCmmDecl -> LlvmM [LlvmCmmDecl] genLlvmProc (CmmProc infos lbl live graph) = do let blocks = toBlockListEntryFirstFalseFallthrough graph - (lmblocks, lmdata) <- basicBlocksCodeGen live blocks + (lmblocks, lmdata) <- basicBlocksCodeGen (map globalRegUseGlobalReg live) blocks let info = mapLookup (g_entry graph) infos proc = CmmProc info lbl live (ListGraph lmblocks) return (proc:lmdata) @@ -152,7 +152,7 @@ stmtToInstrs ubid stmt = case stmt of -- Tail call CmmCall { cml_target = arg, - cml_args_regs = live } -> genJump arg live + cml_args_regs = live } -> genJump arg $ map globalRegUseGlobalReg live _ -> panic "Llvm.CodeGen.stmtToInstrs" ===================================== compiler/GHC/CmmToLlvm/Ppr.hs ===================================== @@ -49,8 +49,9 @@ pprLlvmCmmDecl (CmmData _ lmdata) = do return ( vcat $ map (pprLlvmData opts) lmdata , vcat $ map (pprLlvmData opts) lmdata) -pprLlvmCmmDecl (CmmProc mb_info entry_lbl live (ListGraph blks)) - = do let lbl = case mb_info of +pprLlvmCmmDecl (CmmProc mb_info entry_lbl liveWithUses (ListGraph blks)) + = do let live = map globalRegUseGlobalReg liveWithUses + lbl = case mb_info of Nothing -> entry_lbl Just (CmmStaticsRaw info_lbl _) -> info_lbl link = if externallyVisibleCLabel lbl ===================================== compiler/GHC/StgToCmm/Monad.hs ===================================== @@ -778,7 +778,7 @@ emitProcWithConvention :: Convention -> Maybe CmmInfoTable -> CLabel emitProcWithConvention conv mb_info lbl args blocks = emitProcWithStackFrame conv mb_info lbl [] args blocks True -emitProc :: Maybe CmmInfoTable -> CLabel -> [GlobalReg] -> CmmAGraphScoped +emitProc :: Maybe CmmInfoTable -> CLabel -> [GlobalRegUse] -> CmmAGraphScoped -> Int -> Bool -> FCode () emitProc mb_info lbl live blocks offset do_layout = do { l <- newBlockId View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7d901da2e8b1c972a92a9988757d0a57439b3ec3 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/7d901da2e8b1c972a92a9988757d0a57439b3ec3 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 13:11:28 2024 From: gitlab at gitlab.haskell.org (Peter Trommler (@trommler)) Date: Fri, 21 Jun 2024 09:11:28 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T23034-9.6 Message-ID: <66757c00d64ea_2f9c2825b8bbc154367@gitlab.mail> Peter Trommler pushed new branch wip/T23034-9.6 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T23034-9.6 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 13:37:56 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 21 Jun 2024 09:37:56 -0400 Subject: [Git][ghc/ghc][wip/romes/12935] 3 commits: Try ALSO after SRT Message-ID: <6675823481e6a_2f9c2828cff941545e8@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/12935 at Glasgow Haskell Compiler / GHC Commits: c5dd7b42 by Rodrigo Mesquita at 2024-06-20T11:58:26+01:00 Try ALSO after SRT - - - - - 1d77a6f6 by Rodrigo Mesquita at 2024-06-20T11:58:36+01:00 Revert "Try ALSO after SRT" This reverts commit c5dd7b426cde768126402aac3f39617ccb99f5c5. - - - - - 82b39d63 by Rodrigo Mesquita at 2024-06-21T14:37:45+01:00 Renaming before and after SRTs bc of procs and srts and ... - - - - - 3 changed files: - compiler/GHC/Cmm/Info/Build.hs - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/UniqueRenamer.hs Changes: ===================================== compiler/GHC/Cmm/Info/Build.hs ===================================== @@ -9,6 +9,10 @@ module GHC.Cmm.Info.Build ( CAFSet, CAFEnv, cafAnal, cafAnalData , doSRTs, ModuleSRTInfo (..), emptySRT , SRTMap, srtMapNonCAFs + + -- * Some internal bits + , SRTEntry(..) + , CAFfyLabel(..) ) where import GHC.Prelude hiding (succ) ===================================== compiler/GHC/Cmm/Pipeline.hs ===================================== @@ -47,7 +47,7 @@ cmmPipeline -> CmmGroup -- Input C-- with Procedures -> IO (ModuleSRTInfo, (DetUniqFM, CmmGroupSRTs)) -- Output CPS transformed C-- -cmmPipeline logger cmm_config srtInfo detRnEnv prog = do +cmmPipeline logger cmm_config srtInfo detRnEnv0 prog = do let forceRes (info, group) = info `seq` foldr seq () group let platform = cmmPlatform cmm_config withTimingSilent logger (text "Cmm pipeline") forceRes $ do @@ -57,13 +57,21 @@ cmmPipeline logger cmm_config srtInfo detRnEnv prog = do -- For example, the fix-up action in the ASM NCG should use determinist names for potential new blocks it has to create. -- Therefore, in the ASM NCG `NatM` Monad we use a deterministic `UniqSuply` (which won't be shared about multiple threads) -- TODO: Put these all into notes carefully organized - let (rn_mapping, renamed_prog) = detRenameUniques detRnEnv prog -- TODO: if gopt Opt_DeterministicObjects dflags + let (detRnEnv1, renamed_prog) = detRenameUniques detRnEnv0 prog -- TODO: if gopt Opt_DeterministicObjects dflags (procs, data_) <- {-# SCC "tops" #-} partitionWithM (cpsTop logger platform cmm_config) renamed_prog + -- We also have to rename `data_` since it is not fully determined from + -- the renamed CLabels in renamed_prog. + -- We may also generate new names in procs, so rename that too. + -- We need to do this before SRT generation because otherwise we may look + -- at the "old names" within the body of the function we are generating SRTs for. + -- Easy easy: rename before and after. (srtInfo, cmms) <- {-# SCC "doSRTs" #-} doSRTs cmm_config srtInfo procs data_ - dumpWith logger Opt_D_dump_cmm_cps "Post CPS Cmm" FormatCMM (pdoc platform cmms) + -- Easy easy: here we go. + let (detRnEnv2, (srtInfo_renamed, cmms_renamed)) = detRenameUniques detRnEnv1 (srtInfo, cmms) + dumpWith logger Opt_D_dump_cmm_cps "Post CPS Cmm (uniq-renamed)" FormatCMM (pdoc platform cmms_renamed) - return (srtInfo, (rn_mapping, cmms)) + return (srtInfo_renamed, (detRnEnv2, cmms_renamed)) -- | The Cmm pipeline for a single 'CmmDecl'. Returns: ===================================== compiler/GHC/Cmm/UniqueRenamer.hs ===================================== @@ -15,10 +15,13 @@ import GHC.Cmm.Dataflow.Block import GHC.Cmm.Dataflow.Graph import GHC.Cmm.Dataflow.Label import GHC.Cmm.Switch +import GHC.Cmm.Info.Build import GHC.Types.Unique import GHC.Types.Unique.FM import GHC.Utils.Outputable as Outputable import Data.Tuple (swap) +import qualified Data.Map as M +import qualified Data.Set as S {- -------------------------------------------------------------------------------- @@ -76,8 +79,8 @@ renameDetUniq uq = do return det_uniq -- Rename local symbols deterministically (in order of appearance) -detRenameUniques :: DetUniqFM -> CmmGroup -> (DetUniqFM, CmmGroup) -detRenameUniques dufm group = swap $ runState (mapM uniqRename group) dufm +detRenameUniques :: UniqRenamable a => DetUniqFM -> a -> (DetUniqFM, a) +detRenameUniques dufm x = swap $ runState (uniqRename x) dufm -- The most important function here, which does the actual renaming. -- Arguably, maybe we should rename this to CLabelRenamer @@ -110,20 +113,24 @@ instance UniqRenamable CmmTickScope where -- ROMES:TODO: We may have to change this to get deterministic objects with ticks. uniqRename = pure --- * Traversals from here on out - --- ROMES:TODO: Delete RawCmmStatics instanceS? -instance UniqRenamable (GenCmmDecl RawCmmStatics (LabelMap RawCmmStatics) CmmGraph) where +instance (UniqRenamable a, UniqRenamable b) => UniqRenamable (GenCmmDecl a b CmmGraph) where uniqRename (CmmProc h lbl regs g) - = CmmProc <$> uniqRename h <*> uniqRename lbl <*> mapM uniqRename regs <*> uniqRename g + = CmmProc <$> uniqRename h <*> uniqRename lbl <*> uniqRename regs <*> uniqRename g uniqRename (CmmData sec d) = CmmData <$> uniqRename sec <*> uniqRename d -instance UniqRenamable (GenCmmDecl CmmStatics CmmTopInfo CmmGraph) where - uniqRename (CmmProc h lbl regs g) - = CmmProc <$> uniqRename h <*> uniqRename lbl <*> mapM uniqRename regs <*> uniqRename g - uniqRename (CmmData sec d) - = CmmData <$> uniqRename sec <*> uniqRename d +instance UniqRenamable ModuleSRTInfo where + uniqRename + ModuleSRTInfo{thisModule, dedupSRTs, flatSRTs, moduleSRTMap} + -- ROMES:TODO: I feel like we don't really need to do this for all of these maps, and can shortcut some of this + -- Nonetheless, in order to produce a working prototype, I'm just always renaming them all. We can optimise later. + = ModuleSRTInfo thisModule <$> uniqRename dedupSRTs <*> uniqRename flatSRTs <*> uniqRename moduleSRTMap + +instance UniqRenamable SRTEntry where + uniqRename (SRTEntry cl) = SRTEntry <$> uniqRename cl + +instance UniqRenamable CAFfyLabel where + uniqRename (CAFfyLabel cl) = CAFfyLabel <$> uniqRename cl instance UniqRenamable CmmTopInfo where uniqRename TopInfo{info_tbls, stack_info} @@ -167,8 +174,7 @@ instance UniqRenamable CmmLit where instance UniqRenamable a {- for 'Body' and on 'RawCmmStatics' -} => UniqRenamable (LabelMap a) where - -- ROMES:TODO: Can a rename of the map have collisions and we lose values? Think harder... - uniqRename lm = mapFromListWith (\_ _ -> error "very bad") <$> traverse (\(l,x) -> (,) <$> uniqRename l <*> uniqRename x) (mapToList lm) + uniqRename lm = mapFromListWith panicMapKeysNotInjective <$> traverse (\(l,x) -> (,) <$> uniqRename l <*> uniqRename x) (mapToList lm) instance UniqRenamable CmmGraph where uniqRename (CmmGraph e g) = CmmGraph <$> uniqRename e <*> uniqRename g @@ -241,9 +247,25 @@ instance UniqRenamable CmmReg where CmmLocal l -> CmmLocal <$> uniqRename l CmmGlobal x -> pure $ CmmGlobal x +instance UniqRenamable a => UniqRenamable [a] where + uniqRename = mapM uniqRename + instance (UniqRenamable a, UniqRenamable b) => UniqRenamable (a, b) where uniqRename (a, b) = (,) <$> uniqRename a <*> uniqRename b instance (UniqRenamable a) => UniqRenamable (Maybe a) where uniqRename Nothing = pure Nothing uniqRename (Just x) = Just <$> uniqRename x + +instance (Ord a, UniqRenamable a, UniqRenamable b) => UniqRenamable (M.Map a b) where + uniqRename m = M.fromListWith panicMapKeysNotInjective <$> traverse (\(l,x) -> (,) <$> uniqRename l <*> uniqRename x) (M.toList m) + +instance (Ord a, UniqRenamable a) => UniqRenamable (S.Set a) where + -- Because of renaming being injective the resulting set should have the same + -- size as the intermediate list. + uniqRename s = S.fromList <$> mapM uniqRename (S.toList s) + +-- | Utility panic used by UniqRenamable instances for Map-like datatypes +panicMapKeysNotInjective :: a -> b -> c +panicMapKeysNotInjective _ _ = error "this should be impossible because the function which maps keys should be injective" + View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/70ff49b7efc8c1fca46cba6eff630c5d39a99213...82b39d632877ba5fedf8b5cc5a926c96deeb02c5 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/70ff49b7efc8c1fca46cba6eff630c5d39a99213...82b39d632877ba5fedf8b5cc5a926c96deeb02c5 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 13:45:04 2024 From: gitlab at gitlab.haskell.org (Peter Trommler (@trommler)) Date: Fri, 21 Jun 2024 09:45:04 -0400 Subject: [Git][ghc/ghc][wip/T23034] PPC NCG: Fix sign hints in C calls Message-ID: <667583e069382_2f9c282a603b815518@gitlab.mail> Peter Trommler pushed to branch wip/T23034 at Glasgow Haskell Compiler / GHC Commits: 2ebb4737 by Peter Trommler at 2024-06-21T15:44:22+02:00 PPC NCG: Fix sign hints in C calls Sign hints for parameters are in the second component of the pair. Fixes #23034 - - - - - 6 changed files: - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - + testsuite/tests/codeGen/should_run/T23034.h - + testsuite/tests/codeGen/should_run/T23034.hs - + testsuite/tests/codeGen/should_run/T23034.stdout - + testsuite/tests/codeGen/should_run/T23034_c.c - testsuite/tests/codeGen/should_run/all.T Changes: ===================================== compiler/GHC/CmmToAsm/PPC/CodeGen.hs ===================================== @@ -1770,7 +1770,7 @@ genCCall' config gcp target dest_regs args _ -> panic "genCall': unknown calling conv." argReps = map (cmmExprType platform) args - (argHints, _) = foreignTargetHints target + (_, argHints) = foreignTargetHints target roundTo a x | x `mod` a == 0 = x | otherwise = x + a - (x `mod` a) ===================================== testsuite/tests/codeGen/should_run/T23034.h ===================================== @@ -0,0 +1 @@ +void t_printf(signed long a, signed int b, signed short c, signed char d); ===================================== testsuite/tests/codeGen/should_run/T23034.hs ===================================== @@ -0,0 +1,8 @@ +module Main where + +import Foreign.C + +foreign import ccall unsafe "T23034.h t_printf" + t_printf :: CLong -> CInt -> CShort -> CSChar -> IO () + +main = t_printf (-1) (-2) (-3) (-4) ===================================== testsuite/tests/codeGen/should_run/T23034.stdout ===================================== @@ -0,0 +1 @@ +-1 -2 -3 -4 ===================================== testsuite/tests/codeGen/should_run/T23034_c.c ===================================== @@ -0,0 +1,6 @@ +#include "T23034.h" +#include + +void t_printf(signed long a, signed int b, signed short c, signed char d) { + printf("%d %d %d %d\n", a, b, c, d); +} ===================================== testsuite/tests/codeGen/should_run/all.T ===================================== @@ -247,3 +247,4 @@ test('T24295b', normal, compile_and_run, ['-O -floopification -fpedantic-bottoms test('T24664a', normal, compile_and_run, ['-O']) test('T24664b', normal, compile_and_run, ['-O']) test('CtzClz0', normal, compile_and_run, ['']) +test('T23034', normal, compile_and_run, ['-O2 T23034_c.c']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2ebb4737ecdb9da84e4f622beda7c06fd6dd4c0e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/2ebb4737ecdb9da84e4f622beda7c06fd6dd4c0e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 13:58:12 2024 From: gitlab at gitlab.haskell.org (Simon Peyton Jones (@simonpj)) Date: Fri, 21 Jun 2024 09:58:12 -0400 Subject: [Git][ghc/ghc] Pushed new branch wip/T25009 Message-ID: <667586f4acb4_2f9c282c7f7201576bb@gitlab.mail> Simon Peyton Jones pushed new branch wip/T25009 at Glasgow Haskell Compiler / GHC -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/tree/wip/T25009 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 14:03:10 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Fri, 21 Jun 2024 10:03:10 -0400 Subject: [Git][ghc/ghc][wip/fabu/T24452-confusing-error] compiler: Fix emitting a confusing error for non visible class method Message-ID: <6675881e9cf25_2f9c282dff3c01596e9@gitlab.mail> Fabricio Nascimento pushed to branch wip/fabu/T24452-confusing-error at Glasgow Haskell Compiler / GHC Commits: 5fe709ef by Fabricio de Sousa Nascimento at 2024-06-21T22:57:22+09:00 compiler: Fix emitting a confusing error for non visible class method While solving for class methods on the GRE, if the method with the right parent is not visible, but more than one other class methods with the same name are, GHC would report ambiguous names, when in fact the correct error message would be that the expected class method is not visible. Fixes #24452 - - - - - 11 changed files: - compiler/GHC/Rename/Env.hs - + testsuite/tests/rename/T24452/T24452a.hs - + testsuite/tests/rename/T24452/T24452b.hs - + testsuite/tests/rename/T24452/T24452b.stderr - + testsuite/tests/rename/T24452/T24452c.hs - + testsuite/tests/rename/T24452/T24452c.stderr - + testsuite/tests/rename/T24452/T24452d.hs - + testsuite/tests/rename/T24452/T24452d.stderr - + testsuite/tests/rename/T24452/T24452e.hs - + testsuite/tests/rename/T24452/T24452e.stderr - + testsuite/tests/rename/T24452/all.T Changes: ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -708,8 +708,8 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name how_lkup else checkFld g DisambiguatedOccurrence g -> checkFld g - AmbiguousOccurrence gres -> - mkNameClashErr gres + AmbiguousOccurrence _ -> + noMatchingParentErr original_gres where checkFld :: GlobalRdrElt -> RnM ChildLookupResult checkFld g = do @@ -721,21 +721,25 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name how_lkup -- 1. There were none to begin with. -- 2. None of the matching ones were the parent but -- a. They were from an overloaded record field so we can report - -- a better error + -- a better error. -- b. The original lookup was actually ambiguous. -- For example, the case where overloading is off and two -- record fields are in scope from different record - -- constructors, neither of which is the parent. + -- constructors, neither of which is the parent. Or two or more + -- class methods with the same name are in scope, in which case + -- we want to report we did not find the method for the expected + -- parent, instead of a clashing name error, which would be confusing + -- and point the user the wrong direction (#24452). noMatchingParentErr :: [GlobalRdrElt] -> RnM ChildLookupResult noMatchingParentErr original_gres = do - traceRn "npe" (ppr original_gres) + traceRn "noMatchingParentErr" (ppr original_gres) dup_fields_ok <- xoptM LangExt.DuplicateRecordFields case original_gres of [] -> return NameNotFound [g] -> return $ IncorrectParent parent g [p | ParentIs p <- [greParent g]] gss@(g:gss'@(_:_)) -> - if all isRecFldGRE gss && dup_fields_ok + if must_have_parent || dup_fields_ok && all isRecFldGRE gss then return $ IncorrectParent parent g [p | x <- gss, ParentIs p <- [greParent x]] ===================================== testsuite/tests/rename/T24452/T24452a.hs ===================================== @@ -0,0 +1,13 @@ +-- A program with empty (Alternative.empty, Map.empty, Set.empty) builds +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative (empty, (<|>))) +import qualified Data.Map as Map +import qualified Data.Set as Set + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined + p <|> q = undefined ===================================== testsuite/tests/rename/T24452/T24452b.hs ===================================== @@ -0,0 +1,10 @@ +-- Alternative.empty is not visible +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452b.stderr ===================================== @@ -0,0 +1,2 @@ +T24452b.hs:10:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452c.hs ===================================== @@ -0,0 +1,11 @@ +-- Having Map.empty present, does not change the fact that Alternative.empty is not visible +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) +import qualified Data.Map as Map + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452c.stderr ===================================== @@ -0,0 +1,2 @@ +T24452c.hs:11:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452d.hs ===================================== @@ -0,0 +1,12 @@ +-- Multiple other empty (Map.empty, Data.empty), but the issue still Alternative.empty not visible. +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) +import qualified Data.Map as Map +import qualified Data.Set as Set + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452d.stderr ===================================== @@ -0,0 +1,2 @@ +T24452d.hs:12:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452e.hs ===================================== @@ -0,0 +1,24 @@ +-- Multiple unrelated errors related to empty. +{-# LANGUAGE DuplicateRecordFields #-} +{-# LANGUAGE OverloadedRecordDot #-} +{-# LANGUAGE OverloadedRecordUpdate #-} + +module BugReproduce where + +import Control.Applicative (Alternative) +import qualified Data.Map as Map +import qualified Data.Set as Set + +data A = A { + empty :: () +} +data B = B { + empty :: () +} + +foo = empty + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452e.stderr ===================================== @@ -0,0 +1,10 @@ +T24452e.hs:19:7: error: [GHC-87543] + Ambiguous occurrence ‘empty’. + It could refer to + either the field ‘empty’ of record ‘A’, + defined at T24452e.hs:13:5, + or the field ‘empty’ of record ‘B’, + defined at T24452e.hs:16:5. + +T24452e.hs:24:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/all.T ===================================== @@ -0,0 +1,5 @@ +test('T24452a', normal, compile, ['']) +test('T24452b', normal, compile_fail, ['']) +test('T24452c', normal, compile_fail, ['']) +test('T24452d', normal, compile_fail, ['']) +test('T24452e', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5fe709efbb988fd6e2b87fef3e92f6d738143f1e -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/5fe709efbb988fd6e2b87fef3e92f6d738143f1e You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 14:05:37 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 21 Jun 2024 10:05:37 -0400 Subject: [Git][ghc/ghc][wip/romes/ttg-zurich] 25 commits: Clarify -XGADTs enables existential quantification Message-ID: <667588b1de2f3_2f9c282f265dc160453@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/ttg-zurich at Glasgow Haskell Compiler / GHC Commits: d70abb49 by sheaf at 2024-06-18T18:47:20-04:00 Clarify -XGADTs enables existential quantification Even though -XGADTs does not turn on -XExistentialQuantification, it does allow the user of existential quantification syntax, without needing to use GADT-style syntax. Fixes #20865 - - - - - 13fdf788 by David Binder at 2024-06-18T18:48:02-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 1bab7dde by Fendor at 2024-06-18T18:48:38-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18698b T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The tests T16875 and T18698b fail on i386-linux for the same reason. - - - - - 099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - 5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00 Update user guide to indicate support for 64-tuples - - - - - 4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00 Remove duplicate Anno instances - - - - - 8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00 AArch64: Delete unused RegNos This has the additional benefit of getting rid of the -1 encoding (real registers start at 0.) - - - - - 325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00 Bump stm submodule to current master - - - - - 64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00 testsuite: bump T17572 timeout on wasm32 - - - - - eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00 AArch64: Simplify BL instruction The BL constructor carried unused data in its third argument. - - - - - b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00 TTG: Move SourceText from `Fixity` to `FixitySig` It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Precedes !12842, to simplify it - - - - - 842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00 base: Deprecate some .Internal modules Deprecates the following modules according to clc-proposal #217: https://github.com/haskell/core-libraries-committee/issues/217 * GHC.TypeNats.Internal * GHC.TypeLits.Internal * GHC.ExecutionStack.Internal Closes #24998 - - - - - e965aae6 by Adriaan Leijnse at 2024-06-21T15:05:27+01:00 ttg: Remove SourceText from OverloadedLabel Progress towards #21592 - - - - - 1b01990c by Alexander Foremny at 2024-06-21T15:05:27+01:00 AST: GHC.Prelude -> Prelude Refactor occurrences to GHC.Prelude with Prelude within Language/Haskell. Progress towards #21592 - - - - - 75583e0e by Alexander Foremny at 2024-06-21T15:05:27+01:00 AST: remove occurrences of GHC.Unit.Module.ModuleName `GHC.Unit.Module` re-exports `ModuleName` from `Language.Haskell.Syntax.Module.Name`. Progress towards #21592 - - - - - 10e85e12 by Fabian Kirchner at 2024-06-21T15:05:27+01:00 AST: move Data instance definition for ModuleName to GHC.Unit.Types To remove the dependency on GHC.Utils.Misc inside Language.Haskell.Syntax.Module.Name, the instance definition is moved from there into GHC.Unit.Types. Progress towards #21592 - - - - - b8a5c13c by Fabian Kirchner at 2024-06-21T15:05:27+01:00 AST: move negateOverLitVal into GHC.Hs.Lit The function negateOverLitVal is not used within Language.Haskell and therefore can be moved to the respective module inside GHC.Hs. Progress towards #21592 - - - - - 45129ebb by Fabian Kirchner at 2024-06-21T15:05:27+01:00 AST: move conDetailsArity into GHC.Rename.Module The function conDetailsArity is only used inside GHC.Rename.Module. We therefore move it there from Language.Haskell.Syntax.Lit. Progress towards #21592 - - - - - 891ad15f by Mauricio at 2024-06-21T15:05:27+01:00 AST: Remove GHC.Utils.Assert from GHC Simple cleanup. Progress towards #21592 - - - - - a8e55a33 by Fabian Kirchner at 2024-06-21T15:05:27+01:00 ttg: extract Specificity, ForAllTyFlag and helper functions from GHC.Types.Var Progress towards #21592 Specificity, ForAllTyFlag and its' helper functions are extracted from GHC.Types.Var and moved into a new module Language.Haskell.Syntax.Specificity. Note: Eventually (i.e. after Language.Haskell.Syntax.Decls does not depend on GHC.* anymore) these should be moved into Language.Haskell.Syntax.Decls. At this point, this would cause cyclic dependencies. - - - - - 3246e0e5 by Adowrath at 2024-06-21T15:05:27+01:00 ttg: Split HsSrcBang, remove ref to DataCon from Syntax.Type Progress towards #21592 This splits HsSrcBang up, creating the new HsBang within `Language.Haskell.Syntax.Basic`. `HsBang` holds the unpackedness and strictness information, while `HsSrcBang` only adds the SourceText for usage within the compiler directly. Inside the AST, to preserve the SourceText, it is hidden behind the pre-existing extension point `XBindTy`. All other occurrences of `HsSrcBang` were adapted to deconstruct the inner `HsBang`, and when interacting with the `BindTy` constructor, the hidden `SourceText` is extracted/inserted into the `XBindTy` extension point. `GHC.Core.DataCon` exports both `HsSrcBang` and `HsBang` for convenience. A constructor function `mkHsSrcBang` that takes all individual components has been added. Two exceptions has been made though: - The `Outputable HsSrcBang` instance is replaced by `Outputable HsBang`. While being only GHC-internal, the only place it's used is in outputting `HsBangTy` constructors -- which already have `HsBang`. It wouldn't make sense to reconstruct a `HsSrcBang` just to ignore the `SourceText` anyway. - The error `TcRnUnexpectedAnnotation` did not use the `SourceText`, so it too now only holds a `HsBang`. - - - - - 93af4f54 by Mauricio at 2024-06-21T15:05:28+01:00 AST: Moved definitions that use GHC.Utils.Panic to GHC namespace Progress towards #21592 - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/TyCo/Rep.hs-boot - compiler/GHC/CoreToIface.hs - compiler/GHC/Hs.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Lit.hs - + compiler/GHC/Hs/Specificity.hs - compiler/GHC/Hs/Syn/Type.hs - compiler/GHC/Hs/Type.hs - compiler/GHC/HsToCore/Expr.hs - compiler/GHC/HsToCore/Quote.hs - compiler/GHC/Iface/Binary.hs - compiler/GHC/Iface/Ext/Binary.hs - compiler/GHC/Iface/Ext/Fields.hs - compiler/GHC/Iface/Load.hs - compiler/GHC/Iface/Make.hs - compiler/GHC/Iface/Recomp.hs - compiler/GHC/Iface/Rename.hs - compiler/GHC/IfaceToCore.hs - compiler/GHC/Parser.y - compiler/GHC/Parser/Annotation.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d63c49305b66917063d30ddd300efc10c1841752...93af4f548acbe4d9679567b77e66817a68226f61 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/d63c49305b66917063d30ddd300efc10c1841752...93af4f548acbe4d9679567b77e66817a68226f61 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 14:06:12 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 21 Jun 2024 10:06:12 -0400 Subject: [Git][ghc/ghc][wip/romes/12935] Wait no that was way too slow... Message-ID: <667588d421f21_2f9c2830124c81616f4@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/12935 at Glasgow Haskell Compiler / GHC Commits: cf0a17ad by Rodrigo Mesquita at 2024-06-21T15:06:03+01:00 Wait no that was way too slow... - - - - - 2 changed files: - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/UniqueRenamer.hs Changes: ===================================== compiler/GHC/Cmm/Pipeline.hs ===================================== @@ -31,6 +31,8 @@ import GHC.Utils.Misc ( partitionWithM ) import GHC.Platform import Control.Monad +import Data.List (mapAccumL) +import Data.Bifunctor ----------------------------------------------------------------------------- -- | Top level driver for C-- pipeline @@ -47,7 +49,7 @@ cmmPipeline -> CmmGroup -- Input C-- with Procedures -> IO (ModuleSRTInfo, (DetUniqFM, CmmGroupSRTs)) -- Output CPS transformed C-- -cmmPipeline logger cmm_config srtInfo detRnEnv0 prog = do +cmmPipeline logger cmm_config srtInfo0 detRnEnv0 prog = do let forceRes (info, group) = info `seq` foldr seq () group let platform = cmmPlatform cmm_config withTimingSilent logger (text "Cmm pipeline") forceRes $ do @@ -66,12 +68,14 @@ cmmPipeline logger cmm_config srtInfo detRnEnv0 prog = do -- We need to do this before SRT generation because otherwise we may look -- at the "old names" within the body of the function we are generating SRTs for. -- Easy easy: rename before and after. - (srtInfo, cmms) <- {-# SCC "doSRTs" #-} doSRTs cmm_config srtInfo procs data_ - -- Easy easy: here we go. - let (detRnEnv2, (srtInfo_renamed, cmms_renamed)) = detRenameUniques detRnEnv1 (srtInfo, cmms) - dumpWith logger Opt_D_dump_cmm_cps "Post CPS Cmm (uniq-renamed)" FormatCMM (pdoc platform cmms_renamed) - - return (srtInfo_renamed, (detRnEnv2, cmms_renamed)) + -- Easy easy: but that turns out to be really slow, so let's try renaming + -- procs and data instead and hope srts are generated using names found there. + -- And don't rename procs just yet, ehhh + let (detRnEnv2, data_renamed) = mapAccumL (\rne (a,b) -> second (a,) $ detRenameUniques rne b) detRnEnv1 data_ + (srtInfo1, cmms) <- {-# SCC "doSRTs" #-} doSRTs cmm_config srtInfo0 procs data_renamed + dumpWith logger Opt_D_dump_cmm_cps "Post CPS Cmm (uniq-renamed)" FormatCMM (pdoc platform cmms) + + return (srtInfo1, (detRnEnv2, cmms)) -- | The Cmm pipeline for a single 'CmmDecl'. Returns: ===================================== compiler/GHC/Cmm/UniqueRenamer.hs ===================================== @@ -132,6 +132,11 @@ instance UniqRenamable SRTEntry where instance UniqRenamable CAFfyLabel where uniqRename (CAFfyLabel cl) = CAFfyLabel <$> uniqRename cl +instance UniqRenamable CmmDataDecl where + uniqRename (CmmData sec d) + = CmmData <$> uniqRename sec <*> uniqRename d + uniqRename _ = error "impossible" + instance UniqRenamable CmmTopInfo where uniqRename TopInfo{info_tbls, stack_info} = TopInfo <$> uniqRename info_tbls <*> pure stack_info View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cf0a17ad26a9ba46b0169a0b97cfa7696c02286c -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cf0a17ad26a9ba46b0169a0b97cfa7696c02286c You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 14:09:27 2024 From: gitlab at gitlab.haskell.org (Fabricio Nascimento (@fabu)) Date: Fri, 21 Jun 2024 10:09:27 -0400 Subject: [Git][ghc/ghc][wip/fabu/T24452-confusing-error] compiler: Fix emitting a confusing error for non visible class method Message-ID: <667589974dabc_2f9c283110f6416242f@gitlab.mail> Fabricio Nascimento pushed to branch wip/fabu/T24452-confusing-error at Glasgow Haskell Compiler / GHC Commits: fa6b8287 by Fabricio de Sousa Nascimento at 2024-06-21T23:06:31+09:00 compiler: Fix emitting a confusing error for non visible class method Changes the error message when trying to lookup names on GRE that `must_have_parent` but we get an `AmbiguousOccurrence`. The new behavior now points the user to the missing name, instead of the name clash which would be unhelpful in solving their compiling issue. Fixes #24452 - - - - - 11 changed files: - compiler/GHC/Rename/Env.hs - + testsuite/tests/rename/T24452/T24452a.hs - + testsuite/tests/rename/T24452/T24452b.hs - + testsuite/tests/rename/T24452/T24452b.stderr - + testsuite/tests/rename/T24452/T24452c.hs - + testsuite/tests/rename/T24452/T24452c.stderr - + testsuite/tests/rename/T24452/T24452d.hs - + testsuite/tests/rename/T24452/T24452d.stderr - + testsuite/tests/rename/T24452/T24452e.hs - + testsuite/tests/rename/T24452/T24452e.stderr - + testsuite/tests/rename/T24452/all.T Changes: ===================================== compiler/GHC/Rename/Env.hs ===================================== @@ -708,8 +708,8 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name how_lkup else checkFld g DisambiguatedOccurrence g -> checkFld g - AmbiguousOccurrence gres -> - mkNameClashErr gres + AmbiguousOccurrence _ -> + noMatchingParentErr original_gres where checkFld :: GlobalRdrElt -> RnM ChildLookupResult checkFld g = do @@ -721,21 +721,25 @@ lookupSubBndrOcc_helper must_have_parent warn_if_deprec parent rdr_name how_lkup -- 1. There were none to begin with. -- 2. None of the matching ones were the parent but -- a. They were from an overloaded record field so we can report - -- a better error + -- a better error. -- b. The original lookup was actually ambiguous. -- For example, the case where overloading is off and two -- record fields are in scope from different record - -- constructors, neither of which is the parent. + -- constructors, neither of which is the parent. Or two or more + -- class methods with the same name are in scope, in which case + -- we want to report we did not find the method for the expected + -- parent, instead of a clashing name error, which would be confusing + -- and point the user the wrong direction (#24452). noMatchingParentErr :: [GlobalRdrElt] -> RnM ChildLookupResult noMatchingParentErr original_gres = do - traceRn "npe" (ppr original_gres) + traceRn "noMatchingParentErr" (ppr original_gres) dup_fields_ok <- xoptM LangExt.DuplicateRecordFields case original_gres of [] -> return NameNotFound [g] -> return $ IncorrectParent parent g [p | ParentIs p <- [greParent g]] gss@(g:gss'@(_:_)) -> - if all isRecFldGRE gss && dup_fields_ok + if must_have_parent || dup_fields_ok && all isRecFldGRE gss then return $ IncorrectParent parent g [p | x <- gss, ParentIs p <- [greParent x]] ===================================== testsuite/tests/rename/T24452/T24452a.hs ===================================== @@ -0,0 +1,13 @@ +-- A program with empty (Alternative.empty, Map.empty, Set.empty) builds +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative (empty, (<|>))) +import qualified Data.Map as Map +import qualified Data.Set as Set + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined + p <|> q = undefined ===================================== testsuite/tests/rename/T24452/T24452b.hs ===================================== @@ -0,0 +1,10 @@ +-- Alternative.empty is not visible +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452b.stderr ===================================== @@ -0,0 +1,2 @@ +T24452b.hs:10:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452c.hs ===================================== @@ -0,0 +1,11 @@ +-- Having Map.empty present, does not change the fact that Alternative.empty is not visible +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) +import qualified Data.Map as Map + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452c.stderr ===================================== @@ -0,0 +1,2 @@ +T24452c.hs:11:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452d.hs ===================================== @@ -0,0 +1,12 @@ +-- Multiple other empty (Map.empty, Data.empty), but the issue still Alternative.empty not visible. +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +module BugReproduce where + +import Control.Applicative (Alternative) +import qualified Data.Map as Map +import qualified Data.Set as Set + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined ===================================== testsuite/tests/rename/T24452/T24452d.stderr ===================================== @@ -0,0 +1,2 @@ +T24452d.hs:12:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452e.hs ===================================== @@ -0,0 +1,24 @@ +-- Multiple unrelated errors related to empty. +{-# LANGUAGE DuplicateRecordFields #-} +{-# LANGUAGE OverloadedRecordDot #-} +{-# LANGUAGE OverloadedRecordUpdate #-} + +module BugReproduce where + +import Control.Applicative (Alternative) +import qualified Data.Map as Map +import qualified Data.Set as Set + +data A = A { + empty :: () +} +data B = B { + empty :: () +} + +foo = empty + +newtype Foo a = MkFoo [a] deriving (Functor, Applicative) + +instance Alternative Foo where + empty = undefined \ No newline at end of file ===================================== testsuite/tests/rename/T24452/T24452e.stderr ===================================== @@ -0,0 +1,10 @@ +T24452e.hs:19:7: error: [GHC-87543] + Ambiguous occurrence ‘empty’. + It could refer to + either the field ‘empty’ of record ‘A’, + defined at T24452e.hs:13:5, + or the field ‘empty’ of record ‘B’, + defined at T24452e.hs:16:5. + +T24452e.hs:24:3: error: [GHC-54721] + ‘empty’ is not a (visible) method of class ‘Alternative’ \ No newline at end of file ===================================== testsuite/tests/rename/T24452/all.T ===================================== @@ -0,0 +1,5 @@ +test('T24452a', normal, compile, ['']) +test('T24452b', normal, compile_fail, ['']) +test('T24452c', normal, compile_fail, ['']) +test('T24452d', normal, compile_fail, ['']) +test('T24452e', normal, compile_fail, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fa6b82877f19f033dc249378b8d3f1f170658fab -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/fa6b82877f19f033dc249378b8d3f1f170658fab You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 14:51:11 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Fri, 21 Jun 2024 10:51:11 -0400 Subject: [Git][ghc/ghc][wip/T14030] 31 commits: compiler: Rejects RULES whose LHS immediately fails to type-check Message-ID: <6675935f14e89_2f9c283772038168862@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - d70abb49 by sheaf at 2024-06-18T18:47:20-04:00 Clarify -XGADTs enables existential quantification Even though -XGADTs does not turn on -XExistentialQuantification, it does allow the user of existential quantification syntax, without needing to use GADT-style syntax. Fixes #20865 - - - - - 13fdf788 by David Binder at 2024-06-18T18:48:02-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 1bab7dde by Fendor at 2024-06-18T18:48:38-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18698b T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The tests T16875 and T18698b fail on i386-linux for the same reason. - - - - - 099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - 5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00 Update user guide to indicate support for 64-tuples - - - - - 4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00 Remove duplicate Anno instances - - - - - 8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00 AArch64: Delete unused RegNos This has the additional benefit of getting rid of the -1 encoding (real registers start at 0.) - - - - - 325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00 Bump stm submodule to current master - - - - - 64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00 testsuite: bump T17572 timeout on wasm32 - - - - - eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00 AArch64: Simplify BL instruction The BL constructor carried unused data in its third argument. - - - - - b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00 TTG: Move SourceText from `Fixity` to `FixitySig` It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Precedes !12842, to simplify it - - - - - 842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00 base: Deprecate some .Internal modules Deprecates the following modules according to clc-proposal #217: https://github.com/haskell/core-libraries-committee/issues/217 * GHC.TypeNats.Internal * GHC.TypeLits.Internal * GHC.ExecutionStack.Internal Closes #24998 - - - - - 24e89c40 by Jacco Krijnen at 2024-06-20T07:21:27-04:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 04f5bb85 by Simon Peyton Jones at 2024-06-20T07:22:03-04:00 Fix untouchability test This MR fixes #24938. The underlying problem was tha the test for "does this implication bring in scope any equalities" was plain wrong. See Note [Tracking Given equalities] and Note [Let-bound skolems] both in GHC.Tc.Solver.InertSet. Then * Test LocalGivenEqs succeeds for a different reason than before; see (LBS2) in Note [Let-bound skolems] * New test T24938a succeeds because of (LBS2), whereas it failed before. * Test LocalGivenEqs2 now fails, as it should. * Test T224938, the repro from the ticket, fails, as it should. - - - - - 9a757a27 by Simon Peyton Jones at 2024-06-20T07:22:40-04:00 Fix demand signatures for join points This MR tackles #24623 and #23113 The main change is to give a clearer notion of "worker/wrapper arity", esp for join points. See GHC.Core.Opt.DmdAnal Note [Worker/wrapper arity and join points] This Note is a good summary of what this MR does: (1) The "worker/wrapper arity" of an Id is * For non-join-points: idArity * The join points: the join arity (Id part only of course) This is the number of args we will use in worker/wrapper. See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`. (2) A join point's demand-signature arity may exceed the Id's worker/wrapper arity. See the `arity_ok` assertion in `mkWwBodies`. (3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond the worker/wrapper arity. (4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper arity (re)-computed by workWrapArity. - - - - - 5e8faaf1 by Jan Hrček at 2024-06-20T07:23:20-04:00 Update haddocks of Import/Export AST types - - - - - cd512234 by Hécate Kleidukos at 2024-06-20T07:24:02-04:00 haddock: Update bounds in cabal files and remove allow-newer stanza in cabal.project - - - - - 8a8ff8f2 by Rodrigo Mesquita at 2024-06-20T07:24:38-04:00 cmm: Don't parse MO_BSwap for W8 Don't support parsing bswap8, since bswap8 is not really an operation and would have to be implemented as a no-op (and currently is not implemented at all). Fixes #25002 - - - - - 5cc472f5 by sheaf at 2024-06-20T07:25:14-04:00 Delete unused testsuite files These files were committed by mistake in !11902. This commit simply removes them. - - - - - 7b079378 by Matthew Pickering at 2024-06-20T07:25:50-04:00 Remove left over debugging pragma from 2016 This pragma was accidentally introduced in 648fd73a7b8fbb7955edc83330e2910428e76147 The top-level cost centres lead to a lack of optimisation when compiling with profiling. - - - - - c872e09b by Hécate Kleidukos at 2024-06-20T19:28:36-04:00 haddock: Remove unused pragmata, qualify usages of Data.List functions, add more sanity checking flags by default This commit enables some extensions and GHC flags in the cabal file in a way that allows us to reduce the amount of prologuing on top of each file. We also prefix the usage of some List functions that removes ambiguity when they are also exported from the Prelude, like foldl'. In general, this has the effect of pointing out more explicitly that a linked list is used. Metric Increase: haddock.Cabal haddock.base haddock.compiler - - - - - 8c87d4e1 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00 Add test case for #23586 - - - - - 568de8a5 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00 When matching functions in rewrite rules: ignore multiplicity When matching a template variable to an expression, we check that it has the same type as the matched expression. But if the variable `f` has type `A -> B` while the expression `e` has type `A %1 -> B`, the match was previously rejected. A principled solution would have `f` substituted by `\(%Many x) -> e x` or some other appropriate coercion. But since linearity is not properly checked in Core, we can be cheeky and simply ignore multiplicity while matching. Much easier. This has forced a change in the linter which, when `-dlinear-core-lint` is off, must consider that `a -> b` and `a %1 -> b` are equal. This is achieved by adding an argument to configure the behaviour of `nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour which ignores multiplicities when comparing two `FunTy`. Fixes #24725. - - - - - c8a8727e by Simon Peyton Jones at 2024-06-20T19:29:12-04:00 Faster type equality This MR speeds up type equality, triggered by perf regressions that showed up when fixing #24725 by parameterising type equality over whether to ignore multiplicity. The changes are: * Do not use `nonDetCmpType` for type /equality/. Instead use a specialised type-equality function, which we have always had! `nonDetCmpType` remains, but I did not invest effort in refactoring or optimising it. * Type equality is parameterised by - whether to expand synonyms - whether to respect multiplicities - whether it has a RnEnv2 environment In this MR I systematically specialise it for static values of these parameters. Much more direct and predictable than before. See Note [Specialising type equality] * We want to avoid comparing kinds if possible. I refactored how this happens, at least for `eqType`. See Note [Casts and coercions in type comparison] * To make Lint fast, we want to avoid allocating a thunk for <msg> in ensureEqTypes ty1 ty2 <msg> because the test almost always succeeds, and <msg> isn't needed. See Note [INLINE ensureEqTys] Metric Decrease: T13386 T5030 - - - - - 0b70496d by Sebastian Graf at 2024-06-21T14:51:01+00:00 Derive previously hand-written `Lift` instances (#14030) This is possible now that #22229 is fixed. - - - - - e9d6b306 by Sebastian Graf at 2024-06-21T14:51:01+00:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. - - - - - 30 changed files: - compiler/GHC.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Multiplicity.hs - compiler/GHC/Core/Opt/DmdAnal.hs - compiler/GHC/Core/Opt/WorkWrap.hs - compiler/GHC/Core/Opt/WorkWrap/Utils.hs - compiler/GHC/Core/TyCo/Compare.hs - compiler/GHC/Core/TyCo/Rep.hs - compiler/GHC/Core/Type.hs - compiler/GHC/Core/Unify.hs - compiler/GHC/Driver/Env.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/Hs.hs - compiler/GHC/Hs/Binds.hs - compiler/GHC/Hs/Decls.hs - compiler/GHC/Hs/Dump.hs - compiler/GHC/Hs/Expr.hs - compiler/GHC/Hs/Extension.hs - compiler/GHC/Hs/ImpExp.hs - compiler/GHC/Hs/Pat.hs - compiler/GHC/Hs/Stats.hs - compiler/GHC/Hs/Utils.hs - compiler/GHC/HsToCore/Binds.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4e1b3ea5a403151c75c7ece23db8c96a8fa469f8...e9d6b306708d7c9cda5370156eafe9157c179195 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/4e1b3ea5a403151c75c7ece23db8c96a8fa469f8...e9d6b306708d7c9cda5370156eafe9157c179195 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 15:18:15 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 21 Jun 2024 11:18:15 -0400 Subject: [Git][ghc/ghc][wip/romes/12935] 3 commits: cleaner approach, same idea Message-ID: <667599b77b399_2f9c283b9741017800@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/12935 at Glasgow Haskell Compiler / GHC Commits: 8da04b1b by Rodrigo Mesquita at 2024-06-21T15:58:33+01:00 cleaner approach, same idea - - - - - ab410ec4 by Rodrigo Mesquita at 2024-06-21T15:58:42+01:00 Revert "Reapply "Do uniq renaming before SRTs"" This reverts commit 70ff49b7efc8c1fca46cba6eff630c5d39a99213. - - - - - ffd9d859 by Rodrigo Mesquita at 2024-06-21T16:18:04+01:00 Finfixes - - - - - 6 changed files: - compiler/GHC/Cmm/Pipeline.hs - compiler/GHC/Cmm/UniqueRenamer.hs - compiler/GHC/Driver/CodeOutput.hs - compiler/GHC/Driver/GenerateCgIPEStub.hs - compiler/GHC/Driver/Main.hs - compiler/GHC/StgToCmm.hs Changes: ===================================== compiler/GHC/Cmm/Pipeline.hs ===================================== @@ -19,7 +19,6 @@ import GHC.Cmm.ProcPoint import GHC.Cmm.Sink import GHC.Cmm.Switch.Implement import GHC.Cmm.ThreadSanitizer -import GHC.Cmm.UniqueRenamer import GHC.Types.Unique.Supply @@ -31,8 +30,6 @@ import GHC.Utils.Misc ( partitionWithM ) import GHC.Platform import Control.Monad -import Data.List (mapAccumL) -import Data.Bifunctor ----------------------------------------------------------------------------- -- | Top level driver for C-- pipeline @@ -45,38 +42,18 @@ cmmPipeline :: Logger -> CmmConfig -> ModuleSRTInfo -- Info about SRTs generated so far - -> DetUniqFM -> CmmGroup -- Input C-- with Procedures - -> IO (ModuleSRTInfo, (DetUniqFM, CmmGroupSRTs)) -- Output CPS transformed C-- + -> IO (ModuleSRTInfo, CmmGroupSRTs) -- Output CPS transformed C-- -cmmPipeline logger cmm_config srtInfo0 detRnEnv0 prog = do +cmmPipeline logger cmm_config srtInfo prog = do let forceRes (info, group) = info `seq` foldr seq () group let platform = cmmPlatform cmm_config withTimingSilent logger (text "Cmm pipeline") forceRes $ do + (procs, data_) <- {-# SCC "tops" #-} partitionWithM (cpsTop logger platform cmm_config) prog + (srtInfo, cmms) <- {-# SCC "doSRTs" #-} doSRTs cmm_config srtInfo procs data_ + dumpWith logger Opt_D_dump_cmm_cps "Post CPS Cmm" FormatCMM (pdoc platform cmms) - -- To produce deterministic object code, we alpha-rename all Uniques to deterministic uniques before Cmm linting. - -- From here on out, the backend code generation can't use (non-deterministic) Uniques, or risk producing non-deterministic code. - -- For example, the fix-up action in the ASM NCG should use determinist names for potential new blocks it has to create. - -- Therefore, in the ASM NCG `NatM` Monad we use a deterministic `UniqSuply` (which won't be shared about multiple threads) - -- TODO: Put these all into notes carefully organized - let (detRnEnv1, renamed_prog) = detRenameUniques detRnEnv0 prog -- TODO: if gopt Opt_DeterministicObjects dflags - - (procs, data_) <- {-# SCC "tops" #-} partitionWithM (cpsTop logger platform cmm_config) renamed_prog - -- We also have to rename `data_` since it is not fully determined from - -- the renamed CLabels in renamed_prog. - -- We may also generate new names in procs, so rename that too. - -- We need to do this before SRT generation because otherwise we may look - -- at the "old names" within the body of the function we are generating SRTs for. - -- Easy easy: rename before and after. - -- Easy easy: but that turns out to be really slow, so let's try renaming - -- procs and data instead and hope srts are generated using names found there. - -- And don't rename procs just yet, ehhh - let (detRnEnv2, data_renamed) = mapAccumL (\rne (a,b) -> second (a,) $ detRenameUniques rne b) detRnEnv1 data_ - (srtInfo1, cmms) <- {-# SCC "doSRTs" #-} doSRTs cmm_config srtInfo0 procs data_renamed - dumpWith logger Opt_D_dump_cmm_cps "Post CPS Cmm (uniq-renamed)" FormatCMM (pdoc platform cmms) - - return (srtInfo1, (detRnEnv2, cmms)) - + return (srtInfo, cmms) -- | The Cmm pipeline for a single 'CmmDecl'. Returns: -- ===================================== compiler/GHC/Cmm/UniqueRenamer.hs ===================================== @@ -15,7 +15,7 @@ import GHC.Cmm.Dataflow.Block import GHC.Cmm.Dataflow.Graph import GHC.Cmm.Dataflow.Label import GHC.Cmm.Switch -import GHC.Cmm.Info.Build +-- import GHC.Cmm.Info.Build import GHC.Types.Unique import GHC.Types.Unique.FM import GHC.Utils.Outputable as Outputable @@ -119,18 +119,18 @@ instance (UniqRenamable a, UniqRenamable b) => UniqRenamable (GenCmmDecl a b Cmm uniqRename (CmmData sec d) = CmmData <$> uniqRename sec <*> uniqRename d -instance UniqRenamable ModuleSRTInfo where - uniqRename - ModuleSRTInfo{thisModule, dedupSRTs, flatSRTs, moduleSRTMap} - -- ROMES:TODO: I feel like we don't really need to do this for all of these maps, and can shortcut some of this - -- Nonetheless, in order to produce a working prototype, I'm just always renaming them all. We can optimise later. - = ModuleSRTInfo thisModule <$> uniqRename dedupSRTs <*> uniqRename flatSRTs <*> uniqRename moduleSRTMap +-- instance UniqRenamable ModuleSRTInfo where +-- uniqRename +-- ModuleSRTInfo{thisModule, dedupSRTs, flatSRTs, moduleSRTMap} +-- -- ROMES:TODO: I feel like we don't really need to do this for all of these maps, and can shortcut some of this +-- -- Nonetheless, in order to produce a working prototype, I'm just always renaming them all. We can optimise later. +-- = ModuleSRTInfo thisModule <$> uniqRename dedupSRTs <*> uniqRename flatSRTs <*> uniqRename moduleSRTMap -instance UniqRenamable SRTEntry where - uniqRename (SRTEntry cl) = SRTEntry <$> uniqRename cl +-- instance UniqRenamable SRTEntry where +-- uniqRename (SRTEntry cl) = SRTEntry <$> uniqRename cl -instance UniqRenamable CAFfyLabel where - uniqRename (CAFfyLabel cl) = CAFfyLabel <$> uniqRename cl +-- instance UniqRenamable CAFfyLabel where +-- uniqRename (CAFfyLabel cl) = CAFfyLabel <$> uniqRename cl instance UniqRenamable CmmDataDecl where uniqRename (CmmData sec d) ===================================== compiler/GHC/Driver/CodeOutput.hs ===================================== @@ -39,6 +39,7 @@ import GHC.Data.OsPath import qualified GHC.Data.ShortText as ST import GHC.Data.Stream ( Stream ) import qualified GHC.Data.Stream as Stream +import GHC.Cmm.UniqueRenamer import GHC.Utils.TmpFs @@ -95,12 +96,23 @@ codeOutput logger tmpfs llvm_config dflags unit_state this_mod filenm location g cmm_stream = do { + -- To produce deterministic object code, we alpha-rename all Uniques to deterministic uniques before Cmm linting. + -- From here on out, the backend code generation can't use (non-deterministic) Uniques, or risk producing non-deterministic code. + -- For example, the fix-up action in the ASM NCG should use determinist names for potential new blocks it has to create. + -- Therefore, in the ASM NCG `NatM` Monad we use a deterministic `UniqSuply` (which won't be shared about multiple threads) + -- TODO: Put these all into notes carefully organized + ; let renamed_cmm_stream = do + -- if gopt Opt_DeterministicObjects dflags + + (rn_mapping, stream) <- Stream.mapAccumL_ (fmap pure . detRenameUniques) emptyDetUFM cmm_stream + Stream.liftIO $ debugTraceMsg logger 3 (text "DetRnM mapping:" <+> ppr rn_mapping) + return stream -- Lint each CmmGroup as it goes past ; let linted_cmm_stream = if gopt Opt_DoCmmLinting dflags - then Stream.mapM do_lint cmm_stream - else cmm_stream + then Stream.mapM do_lint renamed_cmm_stream + else renamed_cmm_stream do_lint cmm = withTimingSilent logger (text "CmmLint"<+>brackets (ppr this_mod)) ===================================== compiler/GHC/Driver/GenerateCgIPEStub.hs ===================================== @@ -35,7 +35,6 @@ import GHC.Unit.Types (Module, moduleName) import GHC.Unit.Module (moduleNameString) import qualified GHC.Utils.Logger as Logger import GHC.Utils.Outputable (ppr) -import GHC.Cmm.UniqueRenamer (emptyDetUFM) {- Note [Stacktraces from Info Table Provenance Entries (IPE based stack unwinding)] @@ -212,7 +211,7 @@ generateCgIPEStub hsc_env this_mod denv (nonCaffySet, moduleLFInfos, infoTablesW let denv' = denv {provInfoTables = Map.mapKeys cit_lbl infoTablesWithTickishes} ((mIpeStub, ipeCmmGroup), _) = runC (initStgToCmmConfig dflags this_mod) fstate cgState $ getCmm (initInfoTableProv initStats (Map.keys infoTablesWithTickishes) denv') - (_, (_, ipeCmmGroupSRTs)) <- liftIO $ cmmPipeline logger cmm_cfg (emptySRT this_mod) emptyDetUFM ipeCmmGroup + (_, ipeCmmGroupSRTs) <- liftIO $ cmmPipeline logger cmm_cfg (emptySRT this_mod) ipeCmmGroup Stream.yield ipeCmmGroupSRTs ipeStub <- ===================================== compiler/GHC/Driver/Main.hs ===================================== @@ -300,8 +300,6 @@ import GHC.StgToCmm.Utils (IPEStats) import GHC.Types.Unique.FM import GHC.Types.Unique.DFM import GHC.Cmm.Config (CmmConfig) -import GHC.Cmm.UniqueRenamer -import Data.Bifunctor {- ********************************************************************** @@ -2087,7 +2085,6 @@ hscCompileCmmFile hsc_env original_filename filename output_filename = runHsc hs $ parseCmmFile cmmpConfig cmm_mod home_unit filename let msgs = warns `unionMessages` errs return (GhcPsMessage <$> msgs, cmm) - liftIO $ do putDumpFileMaybe logger Opt_D_dump_cmm_verbose_by_proc "Parsed Cmm" FormatCMM (pdoc platform cmm) @@ -2097,10 +2094,8 @@ hscCompileCmmFile hsc_env original_filename filename output_filename = runHsc hs -- Re-ordering here causes breakage when booting with C backend because -- in C we must declare before use, but SRT algorithm is free to -- re-order [A, B] (B refers to A) when A is not CAFFY and return [B, A] - (rn_mapping, cmmgroup) <- - second concat <$> mapAccumLM (\rn_mapping cmm -> snd <$> cmmPipeline logger cmm_config (emptySRT cmm_mod) rn_mapping [cmm]) emptyDetUFM cmm - - debugTraceMsg logger 3 (text "DetRnM mapping:" <+> ppr rn_mapping) + cmmgroup <- + concatMapM (\cmm -> snd <$> cmmPipeline logger cmm_config (emptySRT cmm_mod) [cmm]) cmm unless (null cmmgroup) $ putDumpFileMaybe logger Opt_D_dump_cmm "Output Cmm" @@ -2198,10 +2193,9 @@ doCodeGen hsc_env this_mod denv data_tycons pipeline_stream :: Stream IO CmmGroupSRTs CmmCgInfos pipeline_stream = do - ((mod_srt_info, ipes, ipe_stats, rn_mapping), lf_infos) <- + ((mod_srt_info, ipes, ipe_stats), lf_infos) <- {-# SCC "cmmPipeline" #-} - Stream.mapAccumL_ (pipeline_action logger cmm_config) (emptySRT this_mod, M.empty, mempty, emptyDetUFM) ppr_stream1 - liftIO $ debugTraceMsg logger 3 (text "DetRnM mapping:" <+> ppr rn_mapping) + Stream.mapAccumL_ (pipeline_action logger cmm_config) (emptySRT this_mod, M.empty, mempty) ppr_stream1 let nonCaffySet = srtMapNonCAFs (moduleSRTMap mod_srt_info) cmmCgInfos <- generateCgIPEStub hsc_env this_mod denv (nonCaffySet, lf_infos, ipes, ipe_stats) return cmmCgInfos @@ -2209,11 +2203,11 @@ doCodeGen hsc_env this_mod denv data_tycons pipeline_action :: Logger -> CmmConfig - -> (ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats, DetUniqFM) + -> (ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats) -> CmmGroup - -> IO ((ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats, DetUniqFM), CmmGroupSRTs) - pipeline_action logger cmm_config (mod_srt_info, ipes, stats, detRnEnv) cmm_group = do - (mod_srt_info', (rn_mapping, cmm_srts)) <- cmmPipeline logger cmm_config mod_srt_info detRnEnv cmm_group + -> IO ((ModuleSRTInfo, Map CmmInfoTable (Maybe IpeSourceLocation), IPEStats), CmmGroupSRTs) + pipeline_action logger cmm_config (mod_srt_info, ipes, stats) cmm_group = do + (mod_srt_info', cmm_srts) <- cmmPipeline logger cmm_config mod_srt_info cmm_group -- If -finfo-table-map is enabled, we precompute a map from info -- tables to source locations. See Note [Mapping Info Tables to Source @@ -2224,7 +2218,7 @@ doCodeGen hsc_env this_mod denv data_tycons else return (ipes, stats) - return ((mod_srt_info', ipes', stats', rn_mapping), cmm_srts) + return ((mod_srt_info', ipes', stats'), cmm_srts) dump2 a = do unless (null a) $ ===================================== compiler/GHC/StgToCmm.hs ===================================== @@ -14,6 +14,7 @@ module GHC.StgToCmm ( codeGen ) where import GHC.Prelude as Prelude +import GHC.Cmm.UniqueRenamer import GHC.StgToCmm.Prof (initCostCentres, ldvEnter) import GHC.StgToCmm.Monad import GHC.StgToCmm.Env @@ -86,18 +87,31 @@ codeGen logger tmpfs cfg (InfoTableProvMap (UniqMap denv) _ _) data_tycons -- we would need to add a state monad layer which regresses -- allocations by 0.5-2%. ; cgref <- liftIO $ initC >>= \s -> newIORef s + ; uniqRnRef <- liftIO $ newIORef emptyDetUFM + ; let fstate = initFCodeState $ stgToCmmPlatform cfg ; let cg :: FCode a -> Stream IO CmmGroup a cg fcode = do (a, cmm) <- liftIO . withTimingSilent logger (text "STG -> Cmm") (`seq` ()) $ do st <- readIORef cgref - let fstate = initFCodeState $ stgToCmmPlatform cfg - let (a,st') = runC cfg fstate st (getCmm fcode) + + -- To produce deterministic object code, we alpha-rename all Uniques to deterministic uniques before Cmm linting. + -- From here on out, the backend code generation can't use (non-deterministic) Uniques, or risk producing non-deterministic code. + -- For example, the fix-up action in the ASM NCG should use determinist names for potential new blocks it has to create. + -- Therefore, in the ASM NCG `NatM` Monad we use a deterministic `UniqSuply` (which won't be shared about multiple threads) + -- TODO: Put these all into notes carefully organized + rnm0 <- readIORef uniqRnRef + + let + ((a, cmm), st') = runC cfg fstate st (getCmm fcode) + (rnm1, cmm_renamed) = detRenameUniques rnm0 cmm -- The yielded cmm will already be renamed. -- NB. stub-out cgs_tops and cgs_stmts. This fixes -- a big space leak. DO NOT REMOVE! -- This is observed by the #3294 test writeIORef cgref $! (st'{ cgs_tops = nilOL, cgs_stmts = mkNop }) - return a + writeIORef uniqRnRef $! rnm1 + + return (a, cmm_renamed) yield cmm return a View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cf0a17ad26a9ba46b0169a0b97cfa7696c02286c...ffd9d8591c745115d68c994fcd0daff30489d422 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/cf0a17ad26a9ba46b0169a0b97cfa7696c02286c...ffd9d8591c745115d68c994fcd0daff30489d422 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 15:21:32 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Fri, 21 Jun 2024 11:21:32 -0400 Subject: [Git][ghc/ghc][wip/T14030] Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) Message-ID: <66759a7cbf977_2f9c283c7006c178813@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: b426344a by Sebastian Graf at 2024-06-21T17:19:58+02:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. The residency of T24471 increases by 13% because we now load `AnnLookup` from its interface file, which transitively loads the whole TH AST. Unavoidable and not terrible, I think. Metric Increase: T24471 - - - - - 8 changed files: - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - testsuite/tests/ghci/scripts/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/th/TH_Lift.hs - + testsuite/tests/th/TH_Lift.stderr - testsuite/tests/th/all.T Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs ===================================== @@ -42,7 +42,7 @@ module GHC.Internal.TH.Lift where import GHC.Internal.TH.Syntax -import GHC.Internal.TH.Lib () -- See wrinkle (W4) of Note [Tracking dependencies on primitives] +import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives] import GHC.Internal.Lexeme ( startsVarSym, startsVarId ) import GHC.Internal.Data.Either @@ -54,8 +54,9 @@ import GHC.Internal.Integer import GHC.Internal.Real import GHC.Internal.Word import GHC.Internal.Int -import GHC.Internal.Data.Data +import GHC.Internal.Data.Data hiding (Fixity) import GHC.Internal.Natural +import GHC.Internal.ForeignPtr -- | A 'Lift' instance can have any of its values turned into a Template -- Haskell expression. This is needed when a value used within a Template @@ -305,6 +306,141 @@ rightName = 'Right nonemptyName :: Name nonemptyName = '(:|) +----------------------------------------------------- +-- +-- Lifting the TH AST +-- +----------------------------------------------------- + +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Loc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DocLoc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ModName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift GHC.Internal.TH.Syntax.Module +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameSpace +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NamespaceSpecifier +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PkgName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameFlavour +-- | @since template-haskell-2.22.1.0 +deriving instance Lift OccName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Name +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameIs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Specificity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift BndrVis +-- | @since template-haskell-2.22.1.0 +deriving instance Lift a => Lift (TyVarBndr a) +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TyLit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Type +-- | @since template-haskell-2.22.1.0 +instance Lift Bytes where + liftTyped x = unsafeCodeCoerce (lift x) + lift bytes at Bytes{} = -- See Note [Why FinalPtr] + [| Bytes + { bytesPtr = ForeignPtr $(Lib.litE (BytesPrimL bytes)) FinalPtr + , bytesOffset = 0 + , bytesSize = $(lift (bytesSize bytes)) + } + |] +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Lit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pat +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Clause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivClause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivStrategy +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Overlap +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FunDep +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Safety +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Callconv +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Foreign +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ForeignSrcLang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FixityDirection +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Fixity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Inline +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleMatch +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Phases +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleBndr +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnTarget +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pragma +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceUnpackedness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DecidedStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Bang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Con +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TySynEqn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FamilyResultSig +-- | @since template-haskell-2.22.1.0 +deriving instance Lift InjectivityAnn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TypeFamilyHead +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Role +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynArgs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynDir +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Dec +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Range +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Exp +-- | @since template-haskell-2.22.1.0 +instance Lift (TExp a) where + lift (TExp e) = [| TExp $(lift e) |] + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Match +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Guard +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Stmt +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Body +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Info +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnLookup +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Extension + ----------------------------------------------------- -- -- Generic Lift implementations ===================================== libraries/template-haskell/changelog.md ===================================== @@ -1,5 +1,9 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) +## 2.22.1.0 + + * `Lift` instances were added for the `template-haskell` AST. + ## 2.22.0.0 * The kind of `Code` was changed from `forall r. (Type -> Type) -> TYPE r -> Type` ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -3,7 +3,7 @@ -- template-haskell.cabal. name: template-haskell -version: 2.22.0.0 +version: 2.22.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE ===================================== testsuite/tests/ghci/scripts/all.T ===================================== @@ -369,8 +369,8 @@ test('T20909', normal, ghci_script, ['T20909.script']) test('T20150', normal, ghci_script, ['T20150.script']) test('T20974', normal, ghci_script, ['T20974.script']) test('T21088', normal, ghci_script, ['T21088.script']) -test('T21110', [extra_files(['T21110A.hs'])], ghci_script, - ['T21110.script']) +test('T21110', [extra_files(['T21110A.hs']), normalise_version('template-haskell')], + ghci_script, ['T21110.script']) test('T17830', [filter_stdout_lines(r'======.*')], ghci_script, ['T17830.script']) test('T21294a', normal, ghci_script, ['T21294a.script']) test('T21507', normal, ghci_script, ['T21507.script']) ===================================== testsuite/tests/interface-stability/template-haskell-exports.stdout ===================================== @@ -2420,11 +2420,37 @@ instance GHC.Internal.Show.Show GHC.Internal.LanguageExtensions.Extension -- Def instance GHC.Internal.Show.Show GHC.Internal.TH.Ppr.ForallVisFlag -- Defined in ‘GHC.Internal.TH.Ppr’ instance [safe] GHC.Internal.Show.Show GHC.Internal.TH.PprLib.Doc -- Defined in ‘GHC.Internal.TH.PprLib’ instance GHC.Internal.Show.Show GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.ForeignSrcLang’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnLookup -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnTarget -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.BndrVis -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Body -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Bool -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bytes -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Callconv -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Char -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Clause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Con -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Dec -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DecidedStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivClause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivStrategy -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DocLoc -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Double -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (GHC.Internal.Data.Either.Either a b) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Exp -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.LanguageExtensions.Extension -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FamilyResultSig -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Fixity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FixityDirection -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Float -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Foreign -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FunDep -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Guard -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Info -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.InjectivityAnn -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Inline -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Int -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int16 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int32 -- Defined in ‘GHC.Internal.TH.Lift’ @@ -2432,16 +2458,49 @@ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int64 -- Defined in ‘GHC.I instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int8 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Integer.Integer -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift [a] -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Lit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Loc -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Match -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Maybe.Maybe a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.ModName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Module -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Name -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameFlavour -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameIs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameSpace -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NamespaceSpecifier -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Natural.Natural -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.OccName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Overlap -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pat -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynArgs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynDir -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Phases -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PkgName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pragma -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Range -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.Real.Integral a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Real.Ratio a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Role -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleBndr -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleMatch -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Safety -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceUnpackedness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Specificity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Stmt -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TExp a) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (a, b) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c) => GHC.Internal.TH.Lift.Lift (a, b, c) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d) => GHC.Internal.TH.Lift.Lift (a, b, c, d) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f g. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f, GHC.Internal.TH.Lift.Lift g) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f, g) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TyLit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TySynEqn -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TyVarBndr a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Type -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TypeFamilyHead -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift () -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Word -- Defined in ‘GHC.Internal.TH.Lift’ ===================================== testsuite/tests/th/TH_Lift.hs ===================================== @@ -1,6 +1,7 @@ -- test Lifting instances {-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE MagicHash #-} module TH_Lift where @@ -10,6 +11,8 @@ import Data.Word import Data.Int import Numeric.Natural import Data.List.NonEmpty +import qualified Data.ByteString as B +import qualified Data.ByteString.Internal as B a :: Integer a = $( (\x -> [| x |]) (5 :: Integer) ) @@ -80,3 +83,17 @@ o = $( (\x -> [| x |]) (True, 'x', 4 :: Int) ) p :: NonEmpty Char p = $( (\x -> [| x |]) ('a' :| "bcde") ) +exp :: Exp +exp = $( [| 3 + 4 |] >>= lift ) + +texp :: TExp Int +texp = $$( examineCode [|| 3 + 4 ||] `bindCode` liftTyped ) + +bytes :: Bytes +bytes = $(do + let (fp, offset, size) = B.toForeignPtr (B.pack [72, 101, 108, 108, 111]) -- "hello"# + let bytes = Bytes { bytesPtr = fp + , bytesOffset = fromIntegral offset + , bytesSize = fromIntegral size + } + lift bytes) ===================================== testsuite/tests/th/TH_Lift.stderr ===================================== @@ -0,0 +1,197 @@ +TH_Lift.hs:18:6-39: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Integer) + ======> + 5 +TH_Lift.hs:21:6-35: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int) + ======> + 5 +TH_Lift.hs:24:7-37: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int8) + ======> + 5 +TH_Lift.hs:27:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int16) + ======> + 5 +TH_Lift.hs:30:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int32) + ======> + 5 +TH_Lift.hs:33:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int64) + ======> + 5 +TH_Lift.hs:36:6-36: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word) + ======> + 5 +TH_Lift.hs:39:6-37: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word8) + ======> + 5 +TH_Lift.hs:42:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word16) + ======> + 5 +TH_Lift.hs:45:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word32) + ======> + 5 +TH_Lift.hs:48:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word64) + ======> + 5 +TH_Lift.hs:51:7-40: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Natural) + ======> + 5 +TH_Lift.hs:54:6-44: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 % 3 :: Rational) + ======> + 1.6666666666666667 +TH_Lift.hs:57:7-39: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (pi :: Float) + ======> + 3.1415927410125732 +TH_Lift.hs:60:7-40: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (pi :: Double) + ======> + 3.141592653589793 +TH_Lift.hs:63:6-28: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + 'x' + ======> + 'x' +TH_Lift.hs:66:6-29: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + True + ======> + True +TH_Lift.hs:69:6-35: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (Just 'x') + ======> + Just 'x' +TH_Lift.hs:72:6-58: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (Right False :: Either Char Bool) + ======> + Right False +TH_Lift.hs:75:6-29: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + "hi!" + ======> + "hi!" +TH_Lift.hs:78:6-27: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + () + ======> + () +TH_Lift.hs:81:6-46: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (True, 'x', 4 :: Int) + ======> + (,,) True 'x' 4 +TH_Lift.hs:84:6-41: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + ('a' :| "bcde") + ======> + (:|) 'a' "bcde" +TH_Lift.hs:87:8-31: Splicing expression + [| 3 + 4 |] >>= lift + ======> + InfixE + (Just (LitE (IntegerL 3))) + (VarE + (Name + (OccName "+") + (NameG + VarName (PkgName "ghc-internal") (ModName "GHC.Internal.Num")))) + (Just (LitE (IntegerL 4))) +TH_Lift.hs:(93,10)-(99,13): Splicing expression + do let (fp, offset, size) + = B.toForeignPtr (B.pack [72, 101, 108, 108, 111]) + let bytes + = Bytes + {bytesPtr = fp, bytesOffset = fromIntegral offset, + bytesSize = fromIntegral size} + lift bytes + ======> + Bytes + {bytesPtr = GHC.Internal.ForeignPtr.ForeignPtr + "Hello"# GHC.Internal.ForeignPtr.FinalPtr, + bytesOffset = 0, bytesSize = 5} +TH_Lift.hs:90:10-59: Splicing expression + examineCode [|| 3 + 4 ||] `bindCode` liftTyped + ======> + TExp + (InfixE + (Just (LitE (IntegerL 3))) + (VarE + (Name + (OccName "+") + (NameG + VarName (PkgName "ghc-internal") (ModName "GHC.Internal.Num")))) + (Just (LitE (IntegerL 4)))) ===================================== testsuite/tests/th/all.T ===================================== @@ -318,7 +318,7 @@ test('T1476', normal, compile, ['-v0']) test('T1476b', normal, compile, ['-v0']) test('T8031', normal, compile, ['-v0']) test('T8624', only_ways(['normal']), makefile_test, ['T8624']) -test('TH_Lift', normal, compile, ['-v0']) +test('TH_Lift', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques']) test('T10047', only_ways(['ghci']), ghci_script, ['T10047.script']) test('T10019', only_ways(['ghci']), ghci_script, ['T10019.script']) test('T10267', [], multimod_compile_fail, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b426344a0c6bd481721cd619d67c494160d37e7f -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/b426344a0c6bd481721cd619d67c494160d37e7f You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 16:21:57 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Fri, 21 Jun 2024 12:21:57 -0400 Subject: [Git][ghc/ghc][wip/T14030] Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) Message-ID: <6675a8a5b2102_33d7554d0fa8378de@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: d0e3f1d9 by Sebastian Graf at 2024-06-21T18:21:46+02:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. The residency of T24471 increases by 13% because we now load `AnnLookup` from its interface file, which transitively loads the whole TH AST. Unavoidable and not terrible, I think. Metric Increase: T24471 - - - - - 8 changed files: - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - testsuite/tests/ghci/scripts/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/th/TH_Lift.hs - + testsuite/tests/th/TH_Lift.stderr - testsuite/tests/th/all.T Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs ===================================== @@ -42,7 +42,7 @@ module GHC.Internal.TH.Lift where import GHC.Internal.TH.Syntax -import GHC.Internal.TH.Lib () -- See wrinkle (W4) of Note [Tracking dependencies on primitives] +import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives] import GHC.Internal.Lexeme ( startsVarSym, startsVarId ) import GHC.Internal.Data.Either @@ -54,8 +54,9 @@ import GHC.Internal.Integer import GHC.Internal.Real import GHC.Internal.Word import GHC.Internal.Int -import GHC.Internal.Data.Data +import GHC.Internal.Data.Data hiding (Fixity) import GHC.Internal.Natural +import GHC.Internal.ForeignPtr -- | A 'Lift' instance can have any of its values turned into a Template -- Haskell expression. This is needed when a value used within a Template @@ -305,6 +306,141 @@ rightName = 'Right nonemptyName :: Name nonemptyName = '(:|) +----------------------------------------------------- +-- +-- Lifting the TH AST +-- +----------------------------------------------------- + +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Loc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DocLoc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ModName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift GHC.Internal.TH.Syntax.Module +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameSpace +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NamespaceSpecifier +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PkgName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameFlavour +-- | @since template-haskell-2.22.1.0 +deriving instance Lift OccName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Name +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameIs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Specificity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift BndrVis +-- | @since template-haskell-2.22.1.0 +deriving instance Lift a => Lift (TyVarBndr a) +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TyLit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Type +-- | @since template-haskell-2.22.1.0 +instance Lift Bytes where + liftTyped x = unsafeCodeCoerce (lift x) + lift bytes at Bytes{} = -- See Note [Why FinalPtr] + [| Bytes + { bytesPtr = ForeignPtr $(Lib.litE (BytesPrimL bytes)) FinalPtr + , bytesOffset = 0 + , bytesSize = $(lift (bytesSize bytes)) + } + |] +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Lit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pat +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Clause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivClause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivStrategy +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Overlap +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FunDep +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Safety +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Callconv +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Foreign +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ForeignSrcLang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FixityDirection +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Fixity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Inline +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleMatch +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Phases +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleBndr +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnTarget +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pragma +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceUnpackedness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DecidedStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Bang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Con +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TySynEqn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FamilyResultSig +-- | @since template-haskell-2.22.1.0 +deriving instance Lift InjectivityAnn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TypeFamilyHead +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Role +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynArgs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynDir +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Dec +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Range +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Exp +-- | @since template-haskell-2.22.1.0 +instance Lift (TExp a) where + lift (TExp e) = [| TExp $(lift e) |] + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Match +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Guard +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Stmt +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Body +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Info +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnLookup +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Extension + ----------------------------------------------------- -- -- Generic Lift implementations ===================================== libraries/template-haskell/changelog.md ===================================== @@ -1,5 +1,9 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) +## 2.22.1.0 + + * `Lift` instances were added for the `template-haskell` AST. + ## 2.22.0.0 * The kind of `Code` was changed from `forall r. (Type -> Type) -> TYPE r -> Type` ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -3,7 +3,7 @@ -- template-haskell.cabal. name: template-haskell -version: 2.22.0.0 +version: 2.22.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE ===================================== testsuite/tests/ghci/scripts/all.T ===================================== @@ -369,8 +369,8 @@ test('T20909', normal, ghci_script, ['T20909.script']) test('T20150', normal, ghci_script, ['T20150.script']) test('T20974', normal, ghci_script, ['T20974.script']) test('T21088', normal, ghci_script, ['T21088.script']) -test('T21110', [extra_files(['T21110A.hs'])], ghci_script, - ['T21110.script']) +test('T21110', [extra_files(['T21110A.hs']), normalise_version('template-haskell')], + ghci_script, ['T21110.script']) test('T17830', [filter_stdout_lines(r'======.*')], ghci_script, ['T17830.script']) test('T21294a', normal, ghci_script, ['T21294a.script']) test('T21507', normal, ghci_script, ['T21507.script']) ===================================== testsuite/tests/interface-stability/template-haskell-exports.stdout ===================================== @@ -2420,11 +2420,37 @@ instance GHC.Internal.Show.Show GHC.Internal.LanguageExtensions.Extension -- Def instance GHC.Internal.Show.Show GHC.Internal.TH.Ppr.ForallVisFlag -- Defined in ‘GHC.Internal.TH.Ppr’ instance [safe] GHC.Internal.Show.Show GHC.Internal.TH.PprLib.Doc -- Defined in ‘GHC.Internal.TH.PprLib’ instance GHC.Internal.Show.Show GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.ForeignSrcLang’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnLookup -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnTarget -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.BndrVis -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Body -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Bool -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bytes -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Callconv -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Char -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Clause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Con -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Dec -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DecidedStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivClause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivStrategy -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DocLoc -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Double -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (GHC.Internal.Data.Either.Either a b) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Exp -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.LanguageExtensions.Extension -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FamilyResultSig -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Fixity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FixityDirection -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Float -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Foreign -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FunDep -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Guard -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Info -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.InjectivityAnn -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Inline -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Int -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int16 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int32 -- Defined in ‘GHC.Internal.TH.Lift’ @@ -2432,16 +2458,49 @@ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int64 -- Defined in ‘GHC.I instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int8 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Integer.Integer -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift [a] -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Lit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Loc -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Match -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Maybe.Maybe a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.ModName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Module -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Name -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameFlavour -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameIs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameSpace -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NamespaceSpecifier -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Natural.Natural -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.OccName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Overlap -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pat -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynArgs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynDir -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Phases -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PkgName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pragma -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Range -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.Real.Integral a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Real.Ratio a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Role -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleBndr -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleMatch -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Safety -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceUnpackedness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Specificity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Stmt -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TExp a) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (a, b) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c) => GHC.Internal.TH.Lift.Lift (a, b, c) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d) => GHC.Internal.TH.Lift.Lift (a, b, c, d) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f g. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f, GHC.Internal.TH.Lift.Lift g) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f, g) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TyLit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TySynEqn -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TyVarBndr a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Type -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TypeFamilyHead -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift () -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Word -- Defined in ‘GHC.Internal.TH.Lift’ ===================================== testsuite/tests/th/TH_Lift.hs ===================================== @@ -1,6 +1,7 @@ -- test Lifting instances {-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE MagicHash #-} module TH_Lift where @@ -10,6 +11,8 @@ import Data.Word import Data.Int import Numeric.Natural import Data.List.NonEmpty +import qualified Data.ByteString as B +import qualified Data.ByteString.Internal as B a :: Integer a = $( (\x -> [| x |]) (5 :: Integer) ) @@ -80,3 +83,17 @@ o = $( (\x -> [| x |]) (True, 'x', 4 :: Int) ) p :: NonEmpty Char p = $( (\x -> [| x |]) ('a' :| "bcde") ) +exp :: Exp +exp = $( [| 3 + 4 |] >>= lift ) + +texp :: TExp Int +texp = $$( examineCode [|| 3 + 4 ||] `bindCode` liftTyped ) + +bytes :: Bytes +bytes = $(do + let (fp, offset, size) = B.toForeignPtr (B.pack [72, 101, 108, 108, 111]) -- "hello"# + let bytes = Bytes { bytesPtr = fp + , bytesOffset = fromIntegral offset + , bytesSize = fromIntegral size + } + lift bytes) ===================================== testsuite/tests/th/TH_Lift.stderr ===================================== @@ -0,0 +1,197 @@ +TH_Lift.hs:18:6-39: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Integer) + ======> + 5 +TH_Lift.hs:21:6-35: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int) + ======> + 5 +TH_Lift.hs:24:7-37: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int8) + ======> + 5 +TH_Lift.hs:27:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int16) + ======> + 5 +TH_Lift.hs:30:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int32) + ======> + 5 +TH_Lift.hs:33:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int64) + ======> + 5 +TH_Lift.hs:36:6-36: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word) + ======> + 5 +TH_Lift.hs:39:6-37: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word8) + ======> + 5 +TH_Lift.hs:42:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word16) + ======> + 5 +TH_Lift.hs:45:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word32) + ======> + 5 +TH_Lift.hs:48:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word64) + ======> + 5 +TH_Lift.hs:51:7-40: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Natural) + ======> + 5 +TH_Lift.hs:54:6-44: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 % 3 :: Rational) + ======> + 1.6666666666666667 +TH_Lift.hs:57:7-39: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (pi :: Float) + ======> + 3.1415927410125732 +TH_Lift.hs:60:7-40: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (pi :: Double) + ======> + 3.141592653589793 +TH_Lift.hs:63:6-28: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + 'x' + ======> + 'x' +TH_Lift.hs:66:6-29: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + True + ======> + True +TH_Lift.hs:69:6-35: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (Just 'x') + ======> + Just 'x' +TH_Lift.hs:72:6-58: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (Right False :: Either Char Bool) + ======> + Right False +TH_Lift.hs:75:6-29: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + "hi!" + ======> + "hi!" +TH_Lift.hs:78:6-27: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + () + ======> + () +TH_Lift.hs:81:6-46: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (True, 'x', 4 :: Int) + ======> + (,,) True 'x' 4 +TH_Lift.hs:84:6-41: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + ('a' :| "bcde") + ======> + (:|) 'a' "bcde" +TH_Lift.hs:87:8-31: Splicing expression + [| 3 + 4 |] >>= lift + ======> + InfixE + (Just (LitE (IntegerL 3))) + (VarE + (Name + (OccName "+") + (NameG + VarName (PkgName "ghc-internal") (ModName "GHC.Internal.Num")))) + (Just (LitE (IntegerL 4))) +TH_Lift.hs:(93,10)-(99,13): Splicing expression + do let (fp, offset, size) + = B.toForeignPtr (B.pack [72, 101, 108, 108, 111]) + let bytes + = Bytes + {bytesPtr = fp, bytesOffset = fromIntegral offset, + bytesSize = fromIntegral size} + lift bytes + ======> + Bytes + {bytesPtr = GHC.Internal.ForeignPtr.ForeignPtr + "Hello"# GHC.Internal.ForeignPtr.FinalPtr, + bytesOffset = 0, bytesSize = 5} +TH_Lift.hs:90:10-59: Splicing expression + examineCode [|| 3 + 4 ||] `bindCode` liftTyped + ======> + TExp + (InfixE + (Just (LitE (IntegerL 3))) + (VarE + (Name + (OccName "+") + (NameG + VarName (PkgName "ghc-internal") (ModName "GHC.Internal.Num")))) + (Just (LitE (IntegerL 4)))) ===================================== testsuite/tests/th/all.T ===================================== @@ -318,7 +318,7 @@ test('T1476', normal, compile, ['-v0']) test('T1476b', normal, compile, ['-v0']) test('T8031', normal, compile, ['-v0']) test('T8624', only_ways(['normal']), makefile_test, ['T8624']) -test('TH_Lift', normal, compile, ['-v0']) +test('TH_Lift', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques -package bytestring']) test('T10047', only_ways(['ghci']), ghci_script, ['T10047.script']) test('T10019', only_ways(['ghci']), ghci_script, ['T10019.script']) test('T10267', [], multimod_compile_fail, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d0e3f1d976a1bdc9b5e469f8bf9d00584771c670 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d0e3f1d976a1bdc9b5e469f8bf9d00584771c670 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 16:44:29 2024 From: gitlab at gitlab.haskell.org (Rodrigo Mesquita (@alt-romes)) Date: Fri, 21 Jun 2024 12:44:29 -0400 Subject: [Git][ghc/ghc][wip/romes/12935] Add traces Message-ID: <6675aded5bcc7_33d755911f6841496@gitlab.mail> Rodrigo Mesquita pushed to branch wip/romes/12935 at Glasgow Haskell Compiler / GHC Commits: 6d989e10 by Rodrigo Mesquita at 2024-06-21T17:44:23+01:00 Add traces - - - - - 1 changed file: - compiler/GHC/Cmm/Pipeline.hs Changes: ===================================== compiler/GHC/Cmm/Pipeline.hs ===================================== @@ -64,7 +64,10 @@ cmmPipeline logger cmm_config srtInfo prog = do -- -- - in the case of a `CmmData`, the unmodified 'CmmDecl' and a 'CAFSet' containing cpsTop :: Logger -> Platform -> CmmConfig -> CmmDecl -> IO (Either (CAFEnv, [CmmDecl]) (CAFSet, CmmDataDecl)) -cpsTop _logger platform _ (CmmData section statics) = return (Right (cafAnalData platform statics, CmmData section statics)) +cpsTop logger platform _ (CmmData section statics) = do + dumpWith logger Opt_D_dump_cmm_verbose "Pre CPS Data" FormatCMM (pdoc platform (CmmData section statics :: CmmDataDecl)) + dumpWith logger Opt_D_dump_cmm_verbose "Post CPS Data" FormatCMM (pdoc platform (cafAnalData platform statics)) + return (Right (cafAnalData platform statics, CmmData section statics)) cpsTop logger platform cfg proc = do ----------- Control-flow optimisations ---------------------------------- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6d989e102a8bde6b9c714ba30f4b8416ba15b748 -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/6d989e102a8bde6b9c714ba30f4b8416ba15b748 You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 16:53:09 2024 From: gitlab at gitlab.haskell.org (Sebastian Graf (@sgraf812)) Date: Fri, 21 Jun 2024 12:53:09 -0400 Subject: [Git][ghc/ghc][wip/T14030] Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) Message-ID: <6675aff5751b8_33d755ac97fc43957@gitlab.mail> Sebastian Graf pushed to branch wip/T14030 at Glasgow Haskell Compiler / GHC Commits: 59ea726a by Sebastian Graf at 2024-06-21T18:52:58+02:00 Implement the "Derive Lift instances for data types in template-haskell" proposal (#14030) After #22229 had been fixed, we can finally derive the `Lift` instance for the TH AST, as proposed by Ryan Scott in https://mail.haskell.org/pipermail/libraries/2015-September/026117.html. Fixes #14030, #14296, #21759 and #24560. The residency of T24471 increases by 13% because we now load `AnnLookup` from its interface file, which transitively loads the whole TH AST. Unavoidable and not terrible, I think. Metric Increase: T24471 - - - - - 8 changed files: - libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs - libraries/template-haskell/changelog.md - libraries/template-haskell/template-haskell.cabal.in - testsuite/tests/ghci/scripts/all.T - testsuite/tests/interface-stability/template-haskell-exports.stdout - testsuite/tests/th/TH_Lift.hs - + testsuite/tests/th/TH_Lift.stderr - testsuite/tests/th/all.T Changes: ===================================== libraries/ghc-internal/src/GHC/Internal/TH/Lift.hs ===================================== @@ -42,7 +42,7 @@ module GHC.Internal.TH.Lift where import GHC.Internal.TH.Syntax -import GHC.Internal.TH.Lib () -- See wrinkle (W4) of Note [Tracking dependencies on primitives] +import qualified GHC.Internal.TH.Lib as Lib (litE) -- See wrinkle (W4) of Note [Tracking dependencies on primitives] import GHC.Internal.Lexeme ( startsVarSym, startsVarId ) import GHC.Internal.Data.Either @@ -54,8 +54,9 @@ import GHC.Internal.Integer import GHC.Internal.Real import GHC.Internal.Word import GHC.Internal.Int -import GHC.Internal.Data.Data +import GHC.Internal.Data.Data hiding (Fixity) import GHC.Internal.Natural +import GHC.Internal.ForeignPtr -- | A 'Lift' instance can have any of its values turned into a Template -- Haskell expression. This is needed when a value used within a Template @@ -305,6 +306,141 @@ rightName = 'Right nonemptyName :: Name nonemptyName = '(:|) +----------------------------------------------------- +-- +-- Lifting the TH AST +-- +----------------------------------------------------- + +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Loc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DocLoc +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ModName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift GHC.Internal.TH.Syntax.Module +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameSpace +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NamespaceSpecifier +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PkgName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameFlavour +-- | @since template-haskell-2.22.1.0 +deriving instance Lift OccName +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Name +-- | @since template-haskell-2.22.1.0 +deriving instance Lift NameIs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Specificity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift BndrVis +-- | @since template-haskell-2.22.1.0 +deriving instance Lift a => Lift (TyVarBndr a) +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TyLit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Type +-- | @since template-haskell-2.22.1.0 +instance Lift Bytes where + liftTyped x = unsafeCodeCoerce (lift x) + lift bytes at Bytes{} = -- See Note [Why FinalPtr] + [| Bytes + { bytesPtr = ForeignPtr $(Lib.litE (BytesPrimL bytes)) FinalPtr + , bytesOffset = 0 + , bytesSize = $(lift (bytesSize bytes)) + } + |] +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Lit +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pat +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Clause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivClause +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DerivStrategy +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Overlap +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FunDep +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Safety +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Callconv +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Foreign +-- | @since template-haskell-2.22.1.0 +deriving instance Lift ForeignSrcLang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FixityDirection +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Fixity +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Inline +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleMatch +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Phases +-- | @since template-haskell-2.22.1.0 +deriving instance Lift RuleBndr +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnTarget +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Pragma +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift SourceUnpackedness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift DecidedStrictness +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Bang +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Con +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TySynEqn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift FamilyResultSig +-- | @since template-haskell-2.22.1.0 +deriving instance Lift InjectivityAnn +-- | @since template-haskell-2.22.1.0 +deriving instance Lift TypeFamilyHead +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Role +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynArgs +-- | @since template-haskell-2.22.1.0 +deriving instance Lift PatSynDir +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Dec +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Range +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Exp +-- | @since template-haskell-2.22.1.0 +instance Lift (TExp a) where + lift (TExp e) = [| TExp $(lift e) |] + liftTyped = unsafeCodeCoerce . lift +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Match +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Guard +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Stmt +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Body +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Info +-- | @since template-haskell-2.22.1.0 +deriving instance Lift AnnLookup +-- | @since template-haskell-2.22.1.0 +deriving instance Lift Extension + ----------------------------------------------------- -- -- Generic Lift implementations ===================================== libraries/template-haskell/changelog.md ===================================== @@ -1,5 +1,9 @@ # Changelog for [`template-haskell` package](http://hackage.haskell.org/package/template-haskell) +## 2.22.1.0 + + * `Lift` instances were added for the `template-haskell` AST. + ## 2.22.0.0 * The kind of `Code` was changed from `forall r. (Type -> Type) -> TYPE r -> Type` ===================================== libraries/template-haskell/template-haskell.cabal.in ===================================== @@ -3,7 +3,7 @@ -- template-haskell.cabal. name: template-haskell -version: 2.22.0.0 +version: 2.22.1.0 -- NOTE: Don't forget to update ./changelog.md license: BSD3 license-file: LICENSE ===================================== testsuite/tests/ghci/scripts/all.T ===================================== @@ -369,8 +369,8 @@ test('T20909', normal, ghci_script, ['T20909.script']) test('T20150', normal, ghci_script, ['T20150.script']) test('T20974', normal, ghci_script, ['T20974.script']) test('T21088', normal, ghci_script, ['T21088.script']) -test('T21110', [extra_files(['T21110A.hs'])], ghci_script, - ['T21110.script']) +test('T21110', [extra_files(['T21110A.hs']), normalise_version('template-haskell')], + ghci_script, ['T21110.script']) test('T17830', [filter_stdout_lines(r'======.*')], ghci_script, ['T17830.script']) test('T21294a', normal, ghci_script, ['T21294a.script']) test('T21507', normal, ghci_script, ['T21507.script']) ===================================== testsuite/tests/interface-stability/template-haskell-exports.stdout ===================================== @@ -2420,11 +2420,37 @@ instance GHC.Internal.Show.Show GHC.Internal.LanguageExtensions.Extension -- Def instance GHC.Internal.Show.Show GHC.Internal.TH.Ppr.ForallVisFlag -- Defined in ‘GHC.Internal.TH.Ppr’ instance [safe] GHC.Internal.Show.Show GHC.Internal.TH.PprLib.Doc -- Defined in ‘GHC.Internal.TH.PprLib’ instance GHC.Internal.Show.Show GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.ForeignSrcLang’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnLookup -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.AnnTarget -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.BndrVis -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Body -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Bool -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Bytes -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Callconv -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Char -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Clause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Con -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Dec -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DecidedStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivClause -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DerivStrategy -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.DocLoc -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Double -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (GHC.Internal.Data.Either.Either a b) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Exp -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.LanguageExtensions.Extension -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FamilyResultSig -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Fixity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FixityDirection -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Float -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Foreign -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.ForeignSrcLang.ForeignSrcLang -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.FunDep -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Guard -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Info -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.InjectivityAnn -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Inline -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Int -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int16 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int32 -- Defined in ‘GHC.Internal.TH.Lift’ @@ -2432,16 +2458,49 @@ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int64 -- Defined in ‘GHC.I instance GHC.Internal.TH.Lift.Lift GHC.Internal.Int.Int8 -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Integer.Integer -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift [a] -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Lit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Loc -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Match -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Maybe.Maybe a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.ModName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Module -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Name -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameFlavour -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameIs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NameSpace -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.NamespaceSpecifier -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Num.Natural.Natural -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Base.NonEmpty a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.OccName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Overlap -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pat -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynArgs -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PatSynDir -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Phases -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.PkgName -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Pragma -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Range -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a. GHC.Internal.Real.Integral a => GHC.Internal.TH.Lift.Lift (GHC.Internal.Real.Ratio a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Role -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleBndr -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.RuleMatch -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Safety -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceStrictness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.SourceUnpackedness -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Specificity -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Stmt -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TExp a) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b) => GHC.Internal.TH.Lift.Lift (a, b) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c) => GHC.Internal.TH.Lift.Lift (a, b, c) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d) => GHC.Internal.TH.Lift.Lift (a, b, c, d) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f) -- Defined in ‘GHC.Internal.TH.Lift’ instance forall a b c d e f g. (GHC.Internal.TH.Lift.Lift a, GHC.Internal.TH.Lift.Lift b, GHC.Internal.TH.Lift.Lift c, GHC.Internal.TH.Lift.Lift d, GHC.Internal.TH.Lift.Lift e, GHC.Internal.TH.Lift.Lift f, GHC.Internal.TH.Lift.Lift g) => GHC.Internal.TH.Lift.Lift (a, b, c, d, e, f, g) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TyLit -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TySynEqn -- Defined in ‘GHC.Internal.TH.Lift’ +instance forall a. GHC.Internal.TH.Lift.Lift a => GHC.Internal.TH.Lift.Lift (GHC.Internal.TH.Syntax.TyVarBndr a) -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.Type -- Defined in ‘GHC.Internal.TH.Lift’ +instance GHC.Internal.TH.Lift.Lift GHC.Internal.TH.Syntax.TypeFamilyHead -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift () -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Internal.Base.Void -- Defined in ‘GHC.Internal.TH.Lift’ instance GHC.Internal.TH.Lift.Lift GHC.Types.Word -- Defined in ‘GHC.Internal.TH.Lift’ ===================================== testsuite/tests/th/TH_Lift.hs ===================================== @@ -1,6 +1,7 @@ -- test Lifting instances {-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE MagicHash #-} module TH_Lift where @@ -10,6 +11,8 @@ import Data.Word import Data.Int import Numeric.Natural import Data.List.NonEmpty +import qualified Data.ByteString as B +import qualified Data.ByteString.Internal as B a :: Integer a = $( (\x -> [| x |]) (5 :: Integer) ) @@ -80,3 +83,17 @@ o = $( (\x -> [| x |]) (True, 'x', 4 :: Int) ) p :: NonEmpty Char p = $( (\x -> [| x |]) ('a' :| "bcde") ) +exp :: Exp +exp = $( [| 3 + 4 |] >>= lift ) + +texp :: TExp Int +texp = $$( examineCode [|| 3 + 4 ||] `bindCode` liftTyped ) + +bytes :: Bytes +bytes = $(do + let (fp, offset, size) = B.toForeignPtr (B.pack [72, 101, 108, 108, 111]) -- "hello"# + let bytes = Bytes { bytesPtr = fp + , bytesOffset = fromIntegral offset + , bytesSize = fromIntegral size + } + lift bytes) ===================================== testsuite/tests/th/TH_Lift.stderr ===================================== @@ -0,0 +1,197 @@ +TH_Lift.hs:18:6-39: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Integer) + ======> + 5 +TH_Lift.hs:21:6-35: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int) + ======> + 5 +TH_Lift.hs:24:7-37: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int8) + ======> + 5 +TH_Lift.hs:27:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int16) + ======> + 5 +TH_Lift.hs:30:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int32) + ======> + 5 +TH_Lift.hs:33:7-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Int64) + ======> + 5 +TH_Lift.hs:36:6-36: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word) + ======> + 5 +TH_Lift.hs:39:6-37: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word8) + ======> + 5 +TH_Lift.hs:42:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word16) + ======> + 5 +TH_Lift.hs:45:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word32) + ======> + 5 +TH_Lift.hs:48:6-38: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Word64) + ======> + 5 +TH_Lift.hs:51:7-40: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 :: Natural) + ======> + 5 +TH_Lift.hs:54:6-44: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (5 % 3 :: Rational) + ======> + 1.6666666666666667 +TH_Lift.hs:57:7-39: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (pi :: Float) + ======> + 3.1415927410125732 +TH_Lift.hs:60:7-40: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (pi :: Double) + ======> + 3.141592653589793 +TH_Lift.hs:63:6-28: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + 'x' + ======> + 'x' +TH_Lift.hs:66:6-29: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + True + ======> + True +TH_Lift.hs:69:6-35: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (Just 'x') + ======> + Just 'x' +TH_Lift.hs:72:6-58: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (Right False :: Either Char Bool) + ======> + Right False +TH_Lift.hs:75:6-29: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + "hi!" + ======> + "hi!" +TH_Lift.hs:78:6-27: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + () + ======> + () +TH_Lift.hs:81:6-46: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + (True, 'x', 4 :: Int) + ======> + (,,) True 'x' 4 +TH_Lift.hs:84:6-41: Splicing expression + (\ x + -> [| x |] + pending(rn) []) + ('a' :| "bcde") + ======> + (:|) 'a' "bcde" +TH_Lift.hs:87:8-31: Splicing expression + [| 3 + 4 |] >>= lift + ======> + InfixE + (Just (LitE (IntegerL 3))) + (VarE + (Name + (OccName "+") + (NameG + VarName (PkgName "ghc-internal") (ModName "GHC.Internal.Num")))) + (Just (LitE (IntegerL 4))) +TH_Lift.hs:(93,10)-(99,13): Splicing expression + do let (fp, offset, size) + = B.toForeignPtr (B.pack [72, 101, 108, 108, 111]) + let bytes + = Bytes + {bytesPtr = fp, bytesOffset = fromIntegral offset, + bytesSize = fromIntegral size} + lift bytes + ======> + Bytes + {bytesPtr = GHC.Internal.ForeignPtr.ForeignPtr + "Hello"# GHC.Internal.ForeignPtr.FinalPtr, + bytesOffset = 0, bytesSize = 5} +TH_Lift.hs:90:10-59: Splicing expression + examineCode [|| 3 + 4 ||] `bindCode` liftTyped + ======> + TExp + (InfixE + (Just (LitE (IntegerL 3))) + (VarE + (Name + (OccName "+") + (NameG + VarName (PkgName "ghc-internal") (ModName "GHC.Internal.Num")))) + (Just (LitE (IntegerL 4)))) ===================================== testsuite/tests/th/all.T ===================================== @@ -318,7 +318,7 @@ test('T1476', normal, compile, ['-v0']) test('T1476b', normal, compile, ['-v0']) test('T8031', normal, compile, ['-v0']) test('T8624', only_ways(['normal']), makefile_test, ['T8624']) -test('TH_Lift', normal, compile, ['-v0']) +test('TH_Lift', js_broken(24886), compile, ['-v0 -ddump-splices -dsuppress-uniques']) test('T10047', only_ways(['ghci']), ghci_script, ['T10047.script']) test('T10019', only_ways(['ghci']), ghci_script, ['T10019.script']) test('T10267', [], multimod_compile_fail, View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/59ea726a7ddd505b600053969aea31349678ac4d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/59ea726a7ddd505b600053969aea31349678ac4d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 17:05:08 2024 From: gitlab at gitlab.haskell.org (Brandon Chinn (@brandonchinn178)) Date: Fri, 21 Jun 2024 13:05:08 -0400 Subject: [Git][ghc/ghc][wip/multiline-strings] 118 commits: hadrian: disable PIC for in-tree GMP on wasm32 Message-ID: <6675b2c3f2f75_33d755d28214467f8@gitlab.mail> Brandon Chinn pushed to branch wip/multiline-strings at Glasgow Haskell Compiler / GHC Commits: f9c1ae12 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable PIC for in-tree GMP on wasm32 This patch disables PIC for in-tree GMP on wasm32 target. Enabling PIC unconditionally adds undesired code size and runtime overhead for wasm32. - - - - - 1a32f828 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: disable in-tree gmp fft code path for wasm32 This patch disables in-tree GMP FFT code paths for wasm32 target in order to give up some performance of multiplying very large operands in exchange for reduced code size. - - - - - 06277d56 by Cheng Shao at 2024-06-02T14:01:55-04:00 hadrian: build in-tree GMP with malloc-notreentrant on wasm32 This patch makes hadrian build in-tree GMP with the --enable-alloca=malloc-notreentrant configure option. We will only need malloc-reentrant when we have threaded RTS and SMP support on wasm32, which will take some time to happen, before which we should use malloc-notreentrant to avoid undesired runtime overhead. - - - - - 9f614270 by ARATA Mizuki at 2024-06-02T14:02:35-04:00 Set package include paths when assembling .S files Fixes #24839. Co-authored-by: Sylvain Henry <hsyl20 at gmail.com> - - - - - 4998a6ed by Alex Mason at 2024-06-03T02:09:29-04:00 Improve performance of genericWordQuotRem2Op (#22966) Implements the algorithm from compiler-rt's udiv128by64to64default. This rewrite results in a roughly 24x improvement in runtime on AArch64 (and likely any other arch that uses it). - - - - - ae50a8eb by Cheng Shao at 2024-06-03T02:10:05-04:00 testsuite: mark T7773 as fragile on wasm - - - - - c8ece0df by Fendor at 2024-06-03T19:43:22-04:00 Migrate `Finder` component to `OsPath`, fixed #24616 For each module in a GHCi session, we keep alive one `ModLocation`. A `ModLocation` is fairly inefficiently packed, as `String`s are expensive in memory usage. While benchmarking the agda codebase, we concluded that we keep alive around 11MB of `FilePath`'s, solely retained by `ModLocation`. We provide a more densely packed encoding of `ModLocation`, by moving from `FilePath` to `OsPath`. Further, we migrate the full `Finder` component to `OsPath` to avoid unnecessary transformations. As the `Finder` component is well-encapsulated, this requires only a minimal amount of changes in other modules. We introduce pattern synonym for 'ModLocation' which maintains backwards compatibility and avoids breaking consumers of 'ModLocation'. - - - - - 0cff083a by Cheng Shao at 2024-06-03T19:43:58-04:00 compiler: emit NaturallyAligned when element type & index type are the same width This commit fixes a subtle mistake in alignmentFromTypes that used to generate Unaligned when element type & index type are the same width. Fixes #24930. - - - - - 18f63970 by Sebastian Graf at 2024-06-04T05:05:27-04:00 Parser: Remove unused `apats` rule - - - - - 38757c30 by David Knothe at 2024-06-04T05:05:27-04:00 Implement Or Patterns (#22596) This commit introduces a new language extension, `-XOrPatterns`, as described in GHC Proposal 522. An or-pattern `pat1; ...; patk` succeeds iff one of the patterns `pat1`, ..., `patk` succeed, in this order. See also the summary `Note [Implmentation of OrPatterns]`. Co-Authored-By: Sebastian Graf <sgraf1337 at gmail.com> - - - - - 395412e8 by Cheng Shao at 2024-06-04T05:06:04-04:00 compiler/ghci/rts: remove stdcall support completely We have formally dropped i386 windows support (#18487) a long time ago. The stdcall foreign call convention is only used by i386 windows, and the legacy logic around it is a significant maintenance burden for future work that adds arm64 windows support (#24603). Therefore, this patch removes stdcall support completely from the compiler as well as the RTS (#24883): - stdcall is still recognized as a FFI calling convention in Haskell syntax. GHC will now unconditionally emit a warning (-Wunsupported-calling-conventions) and treat it as ccall. - Apart from minimum logic to support the parsing and warning logic, all other code paths related to stdcall has been completely stripped from the compiler. - ghci only supports FFI_DEFAULT_ABI and ccall convention from now on. - FFI foreign export adjustor code on all platforms no longer handles the stdcall case and only handles ccall from now on. - The Win32 specific parts of RTS no longer has special code paths for stdcall. This commit is the final nail on the coffin for i386 windows support. Further commits will perform more housecleaning to strip the legacy code paths and pave way for future arm64 windows support. - - - - - d1fe9ab6 by Cheng Shao at 2024-06-04T05:06:04-04:00 rts: remove legacy i386 windows code paths This commit removes some legacy i386 windows related code paths in the RTS, given this target is no longer supported. - - - - - a605e4b2 by Cheng Shao at 2024-06-04T05:06:04-04:00 autoconf: remove i386 windows related logic This commit removes legacy i386 windows logic in autoconf scripts. - - - - - 91e5ac5e by Cheng Shao at 2024-06-04T05:06:04-04:00 llvm-targets: remove i386 windows support This commit removes i386 windows from llvm-targets and the script to generate it. - - - - - 65fe75a4 by Cheng Shao at 2024-06-04T05:06:04-04:00 libraries/utils: remove stdcall related legacy logic This commit removes stdcall related legacy logic in libraries and utils. ccall should be used uniformly for all supported windows hosts from now on. - - - - - d2a83302 by Cheng Shao at 2024-06-04T05:06:04-04:00 testsuite: adapt the testsuite for stdcall removal This patch adjusts test cases to handle the stdcall removal: - Some stdcall usages are replaced with ccall since stdcall doesn't make sense anymore. - We also preserve some stdcall usages, and check in the expected warning messages to ensure GHC always warn about stdcall usages (-Wunsupported-calling-conventions) as expected. - Error code testsuite coverage is slightly improved, -Wunsupported-calling-conventions is now tested. - Obsolete code paths related to i386 windows are also removed. - - - - - cef8f47a by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: minor adjustments for stdcall removal This commit include minor adjustments of documentation related to stdcall removal. - - - - - 54332437 by Cheng Shao at 2024-06-04T05:06:04-04:00 docs: mention i386 Windows removal in 9.12 changelog This commit mentions removal of i386 Windows support and stdcall related change in the 9.12 changelog. - - - - - 2aaea8a1 by Cheng Shao at 2024-06-04T05:06:40-04:00 hadrian: improve user settings documentation This patch adds minor improvements to hadrian user settings documentation: - Add missing `ghc.cpp.opts` case - Remove non-existent `cxx` case - Clarify `cc.c.opts` also works for C++, while `cc.deps.opts` doesn't - Add example of passing configure argument to autoconf packages - - - - - 71010381 by Alex Mason at 2024-06-04T12:09:07-04:00 Add AArch64 CLZ, CTZ, RBIT primop implementations. Adds support for emitting the clz and rbit instructions, which are used by GHC.Prim.clz*#, GHC.Prim.ctz*# and GHC.Prim.bitReverse*#. - - - - - 44e2abfb by Cheng Shao at 2024-06-04T12:09:43-04:00 hadrian: add +text_simdutf flavour transformer to allow building text with simdutf This patch adds a +text_simdutf flavour transformer to hadrian to allow downstream packagers and users that build from source to opt-in simdutf support for text, in order to benefit from SIMD speedup at run-time. It's still disabled by default for the time being. - - - - - 077cb2e1 by Cheng Shao at 2024-06-04T12:09:43-04:00 ci: enable +text_simdutf flavour transformer for wasm jobs This commit enables +text_simdutf flavour transformer for wasm jobs, so text is now built with simdutf support for wasm. - - - - - b23746ad by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Use TemplateHaskellQuotes in instance Lift ByteArray Resolves #24852 - - - - - 3fd25743 by Teo Camarasu at 2024-06-04T22:50:50-04:00 base: Mark addrToByteArray as NOINLINE This function should never be inlined in order to keep code size small. - - - - - 98ad1ea5 by Cheng Shao at 2024-06-04T22:51:26-04:00 compiler: remove unused CompilerInfo/LinkerInfo types This patch removes CompilerInfo/LinkerInfo types from the compiler since they aren't actually used anywhere. - - - - - 11795244 by Cheng Shao at 2024-06-05T06:33:17-04:00 rts: remove unused PowerPC/IA64 native adjustor code This commit removes unused PowerPC/IA64 native adjustor code which is never actually enabled by autoconf/hadrian. Fixes #24920. - - - - - 5132754b by Sylvain Henry at 2024-06-05T06:33:57-04:00 RTS: fix warnings with doing*Profiling (#24918) - - - - - accc8c33 by Cheng Shao at 2024-06-05T11:35:36-04:00 hadrian: don't depend on inplace/mingw when --enable-distro-toolchain on Windows - - - - - 6ffbd678 by Cheng Shao at 2024-06-05T11:35:37-04:00 autoconf: normalize paths of some build-time dependencies on Windows This commit applies path normalization via cygpath -m to some build-time dependencies on Windows. Without this logic, the /clang64/bin prefixed msys2-style paths cause the build to fail with --enable-distro-toolchain. - - - - - 075dc6d4 by Cheng Shao at 2024-06-05T11:36:12-04:00 hadrian: remove OSDarwin mention from speedHack This commit removes mentioning of OSDarwin from speedHack, since speedHack is purely for i386 and we no longer support i386 darwin (#24921). - - - - - 83235c4c by Cheng Shao at 2024-06-05T11:36:12-04:00 compiler: remove 32-bit darwin logic This commit removes all 32-bit darwin logic from the compiler, given we no longer support 32-bit apple systems (#24921). Also contains a bit more cleanup of obsolete i386 windows logic. - - - - - 1eb99bc3 by Cheng Shao at 2024-06-05T11:36:12-04:00 rts: remove 32-bit darwin/ios logic This commit removes 32-bit darwin/ios related logic from the rts, given we no longer support them (#24921). - - - - - 24f65892 by Cheng Shao at 2024-06-05T11:36:12-04:00 llvm-targets: remove 32-bit darwin/ios targets This commit removes 32-bit darwin/ios targets from llvm-targets given we no longer support them (#24921). - - - - - ccdbd689 by Cheng Shao at 2024-06-05T11:36:12-04:00 testsuite: remove 32-bit darwin logic This commit removes 32-bit darwin logic from the testsuite given it's no longer supported (#24921). Also contains more cleanup of obsolete i386 windows logic. - - - - - 11d661c4 by Cheng Shao at 2024-06-05T11:36:13-04:00 docs: mention 32-bit darwin/ios removal in 9.12 changelog This commit mentions removal of 32-bit darwin/ios support (#24921) in the 9.12 changelog. - - - - - 7c173310 by Georgi Lyubenov at 2024-06-05T15:17:22-04:00 Add firstA and secondA to Data.Bitraversable Please see https://github.com/haskell/core-libraries-committee/issues/172 for related discussion - - - - - 3b6f9fd1 by Ben Gamari at 2024-06-05T15:17:59-04:00 base: Fix name of changelog Fixes #24899. Also place it under `extra-doc-files` to better reflect its nature and avoid triggering unnecessary recompilation if it changes. - - - - - 1f4d2ef7 by Sebastian Graf at 2024-06-05T15:18:34-04:00 Announce Or-patterns in the release notes for GHC 9.12 (#22596) Leftover from !9229. - - - - - 8650338d by Jan Hrček at 2024-06-06T10:39:24-04:00 Improve haddocks of Language.Haskell.Syntax.Pat.Pat - - - - - 2eee65e1 by Cheng Shao at 2024-06-06T10:40:00-04:00 testsuite: bump T7653 timeout for wasm - - - - - 990fed60 by Sylvain Henry at 2024-06-07T14:45:23-04:00 StgToCmm: refactor opTranslate and friends - Change arguments order to avoid `\args -> ...` lambdas - Fix documentation - Rename StgToCmm options ("big" doesn't mean anything) - - - - - 1afad514 by Sylvain Henry at 2024-06-07T14:45:23-04:00 NCG x86: remove dead code (#5444) Since 6755d833af8c21bbad6585144b10e20ac4a0a1ab this code is dead. - - - - - 595c0894 by Cheng Shao at 2024-06-07T14:45:58-04:00 testsuite: skip objc-hi/objcxx-hi when cross compiling objc-hi/objcxx-hi should be skipped when cross compiling. The existing opsys('darwin') predicate only asserts the host system is darwin but tells us nothing about the target, hence the oversight. - - - - - edfe6140 by qqwy at 2024-06-08T11:23:54-04:00 Replace '?callStack' implicit param with HasCallStack in GHC.Internal.Exception.throw - - - - - 35a64220 by Cheng Shao at 2024-06-08T11:24:30-04:00 rts: cleanup inlining logic This patch removes pre-C11 legacy code paths related to INLINE_HEADER/STATIC_INLINE/EXTERN_INLINE macros, ensure EXTERN_INLINE is treated as static inline in most cases (fixes #24945), and also corrects the comments accordingly. - - - - - 9ea90ed2 by Andrew Lelechenko at 2024-06-08T11:25:06-04:00 CODEOWNERS: add @core-libraries to track base interface changes A low-tech tactical solution for #24919 - - - - - 580fef7b by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update CHANGELOG to reflect current version - - - - - 391ecff5 by Ben Gamari at 2024-06-09T01:27:21-04:00 ghc-internal: Update prologue.txt to reflect package description - - - - - 3dca3b7d by Ben Gamari at 2024-06-09T01:27:57-04:00 compiler: Clarify comment regarding need for MOVABS The comment wasn't clear in stating that it was only applicable to immediate source and memory target operands. - - - - - 6bd850e8 by doyougnu at 2024-06-09T21:02:14-04:00 JS: establish single source of truth for symbols In pursuit of: #22736. This MR moves ad-hoc symbols used throughout the js backend into a single symbols file. Why? First, this cleans up the code by removing ad-hoc strings created on the fly and therefore makes the code more maintainable. Second, it makes it much easier to eventually type these identifiers. - - - - - f3017dd3 by Cheng Shao at 2024-06-09T21:02:49-04:00 rts: replace ad-hoc MYTASK_USE_TLV with proper CC_SUPPORTS_TLS This patch replaces the ad-hoc `MYTASK_USE_TLV` with the `CC_SUPPORTS_TLS` macro. If TLS support is detected by autoconf, then we should use that for managing `myTask` in the threaded RTS. - - - - - e17d7e8c by Ben Gamari at 2024-06-11T05:25:21-04:00 users-guide: Fix stylistic issues in 9.12 release notes - - - - - 8a8a982a by Hugo Peters at 2024-06-11T05:25:57-04:00 fix typo in the simplifier debug output: baling -> bailing - - - - - 16475bb8 by Hécate Moonlight at 2024-06-12T03:07:55-04:00 haddock: Correct the Makefile to take into account Darwin systems - - - - - a2f60da5 by Hécate Kleidukos at 2024-06-12T03:08:35-04:00 haddock: Remove obsolete links to github.com/haskell/haddock in the docs - - - - - de4395cd by qqwy at 2024-06-12T03:09:12-04:00 Add `__GLASGOW_HASKELL_ASSERTS_IGNORED__` as CPP macro name if `-fasserts-ignored is set. This allows users to create their own Control.Exception.assert-like functionality that does something other than raising an `AssertFailed` exception. Fixes #24967 - - - - - 0e9c4dee by Ryan Hendrickson at 2024-06-12T03:09:53-04:00 compiler: add hint to TcRnBadlyStaged message - - - - - 2747cd34 by Simon Peyton Jones at 2024-06-12T12:51:37-04:00 Fix a QuickLook bug This MR fixes the bug exposed by #24676. The problem was that quickLookArg was trying to avoid calling tcInstFun unnecessarily; but it was in fact necessary. But that in turn forced me into a significant refactoring, putting more fields into EValArgQL. Highlights: see Note [Quick Look overview] in GHC.Tc.Gen.App * Instantiation variables are now distinguishable from ordinary unification variables, by level number = QLInstVar. This is treated like "level infinity". See Note [The QLInstVar TcLevel] in GHC.Tc.Utils.TcType. * In `tcApp`, we don't track the instantiation variables in a set Delta any more; instead, we just tell them apart by their level number. * EValArgQL now much more clearly captures the "half-done" state of typechecking an argument, ready for later resumption. See Note [Quick Look at value arguments] in GHC.Tc.Gen.App * Elminated a bogus (never used) fast-path in GHC.Tc.Utils.Instantiate.instCallConstraints See Note [Possible fast path for equality constraints] Many other small refactorings. - - - - - 1b1523b1 by George Thomas at 2024-06-12T12:52:18-04:00 Fix non-compiling extensible record `HasField` example - - - - - 97b141a3 by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Fix hyperlinker source urls (#24907) This fixes a bug introduced by f56838c36235febb224107fa62334ebfe9941aba Links to external modules in the hyperlinker are uniformly generated using splicing the template given to us instead of attempting to construct the url in an ad-hoc manner. - - - - - 954f864c by Zubin Duggal at 2024-06-12T12:52:55-04:00 haddock: Add name anchor to external source urls from documentation page URLs for external source links from documentation pages were missing a splice location for the name. Fixes #24912 - - - - - b0b64177 by Simon Peyton Jones at 2024-06-12T12:53:31-04:00 Prioritise nominal equalities The main payload of this patch is * Prioritise nominal equalities in the constraint solver. This ameliorates the incompleteness of solving for representational constraints over newtypes: see #24887. See (EX2) in Note [Decomposing newtype equalities] in GHC.Tc.Solver.Equality In doing this patch I tripped over some other things that I refactored: * Move `isCoVarType` from `GHC.Core.Type` to `GHC.Core.Predicate` where it seems more at home. * Clarify the "rewrite role" of a constraint. I was very puzzled about what the role of, say `(Eq a)` might be, but see the new Note [The rewrite-role of a constraint]. In doing so I made predTypeEqRel crash when given a non-equality. Usually it expects an equality; but it was being mis-used for the above rewrite-role stuff. - - - - - cb7c1b83 by Liam Goodacre at 2024-06-12T12:54:09-04:00 compiler: missing-deriving-strategies suggested fix Extends the missing-deriving-strategies warning with a suggested fix that includes which deriving strategies were assumed. For info about the warning, see comments for `TcRnNoDerivStratSpecified`, `TcRnNoDerivingClauseStrategySpecified`, & `TcRnNoStandaloneDerivingStrategySpecified`. For info about the suggested fix, see `SuggestExplicitDerivingClauseStrategies` & `SuggestExplicitStandalanoDerivingStrategy`. docs: Rewords missing-deriving-strategies to mention the suggested fix. Resolves #24955 - - - - - 4e36d3a3 by Jan Hrček at 2024-06-12T12:54:48-04:00 Further haddocks improvements in Language.Haskell.Syntax.Pat.Pat - - - - - 558353f4 by Cheng Shao at 2024-06-12T12:55:24-04:00 rts: use page sized mblocks on wasm This patch changes mblock size to page size on wasm. It allows us to simplify our wasi-libc fork, makes it much easier to test third party libc allocators like emmalloc/mimalloc, as well as experimenting with threaded RTS in wasm. - - - - - b3cc5366 by Matthew Pickering at 2024-06-12T23:06:57-04:00 compiler: Make ghc-experimental not wired in If you need to wire in definitions, then place them in ghc-internal and reexport them from ghc-experimental. Ticket #24903 - - - - - 700eeab9 by Hécate Kleidukos at 2024-06-12T23:07:37-04:00 base: Use a more appropriate unicode arrow for the ByteArray diagram This commit rectifies the usage of a unicode arrow in favour of one that doesn't provoke mis-alignment. - - - - - cca7de25 by Matthew Pickering at 2024-06-12T23:08:14-04:00 ghcup-metadata: Fix debian version ranges This was caught by `ghcup-ci` failing and attempting to install a deb12 bindist on deb11. ``` configure: WARNING: m4/prep_target_file.m4: Expecting YES/NO but got in ArSupportsDashL_STAGE0. Defaulting to False. bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by bin/ghc-toolchain-bin) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.34' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) bin/ghc-toolchain-bin: /lib/x86_64-linux-gnu/libc.so.6: version `GLIBC_2.33' not found (required by /tmp/tmp.LBhwvFbVoy/foobarbaz/.ghcup/tmp/ghcup-708d9668d5d82287/ghc-9.11.20240609-x86_64-unknown-linux/bin/../lib/x86_64-linux-ghc-9.11.20240609/libHSunix-2.8.5.1-inplace-ghc9.11.20240609.so) ``` Fixes #24974 - - - - - 7b23ce8b by Pierre Le Marre at 2024-06-13T15:35:04-04:00 ucd2haskell: remove Streamly dependency + misc - Remove dead code. - Remove `streamly` dependency. - Process files with `bytestring`. - Replace Unicode files parsers with the corresponding ones from the package `unicode-data-parser`. - Simplify cabal file and rename module - Regenerate `ghc-internal` Unicode files with new header - - - - - 4570319f by Jacco Krijnen at 2024-06-13T15:35:41-04:00 Document how to run haddocks tests (#24976) Also remove ghc 9.7 requirement - - - - - fb629e24 by amesgen at 2024-06-14T00:28:20-04:00 compiler: refactor lower_CmmExpr_Ptr - - - - - def46c8c by amesgen at 2024-06-14T00:28:20-04:00 compiler: handle CmmRegOff in lower_CmmExpr_Ptr - - - - - ce76bf78 by Simon Peyton Jones at 2024-06-14T00:28:56-04:00 Small documentation update in Quick Look - - - - - 19bcfc9b by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Add hack for #24623 ..Th bug in #24623 is randomly triggered by this MR!.. - - - - - 7a08a025 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Various fixes to type-tidying This MR was triggered by #24868, but I found a number of bugs and infelicities in type-tidying as I went along. Highlights: * Fix to #24868 is in GHC.Tc.Errors.report_unsolved: avoid using the OccNames of /bound/ variables when tidying /free/ variables; see the call to `tidyAvoiding`. That avoid the gratuitous renaming which was the cause of #24868. See Note [tidyAvoiding] in GHC.Core.TyCo.Tidy * Refactor and document the tidying of open types. See GHC.Core.TyCo.Tidy Note [Tidying open types] Note [Tidying is idempotent] * Tidy the coercion variable in HoleCo. That's important so that tidied types have tidied kinds. * Some small renaming to make things consistent. In particular the "X" forms return a new TidyEnv. E.g. tidyOpenType :: TidyEnv -> Type -> Type tidyOpenTypeX :: TidyEnv -> Type -> (TidyEnv, Type) - - - - - 2eac0288 by Simon Peyton Jones at 2024-06-14T14:44:19-04:00 Wibble - - - - - e5d24cc2 by Simon Peyton Jones at 2024-06-14T14:44:20-04:00 Wibbles - - - - - 246bc3a4 by Simon Peyton Jones at 2024-06-14T14:44:56-04:00 Localise a case-binder in SpecConstr.mkSeqs This small change fixes #24944 See (SCF1) in Note [SpecConstr and strict fields] - - - - - a5994380 by Sylvain Henry at 2024-06-15T03:20:29-04:00 PPC: display foreign label in panic message (cf #23969) - - - - - bd95553a by Rodrigo Mesquita at 2024-06-15T03:21:06-04:00 cmm: Parse MO_BSwap primitive operation Parsing this operation allows it to be tested using `test-primops` in a subsequent MR. - - - - - e0099721 by Andrew Lelechenko at 2024-06-16T17:57:38-04:00 Make flip representation polymorphic, similar to ($) and (&) CLC proposal: https://github.com/haskell/core-libraries-committee/issues/245 - - - - - 118a1292 by Alan Zimmerman at 2024-06-16T17:58:15-04:00 EPA: Add location to Match Pats list So we can freely modify the pats and the following item spacing will still be valid when exact printing. Closes #24862 - - - - - db343324 by Fabricio de Sousa Nascimento at 2024-06-17T10:01:51-04:00 compiler: Rejects RULES whose LHS immediately fails to type-check Fixes GHC crashing on `decomposeRuleLhs` due to ignoring coercion values. This happens when we have a RULE that does not type check, and enable `-fdefer-type-errors`. We prevent this to happen by rejecting RULES with an immediately LHS type error. Fixes #24026 - - - - - e7a95662 by Dylan Thinnes at 2024-06-17T10:02:35-04:00 Add hscTypecheckRenameWithDiagnostics, for HLS (#24996) Use runHsc' in runHsc so that both functions can't fall out of sync We're currently copying parts of GHC code to get structured warnings in HLS, so that we can recreate `hscTypecheckRenameWithDiagnostics` locally. Once we get this function into GHC we can drop the copied code in future versions of HLS. - - - - - d70abb49 by sheaf at 2024-06-18T18:47:20-04:00 Clarify -XGADTs enables existential quantification Even though -XGADTs does not turn on -XExistentialQuantification, it does allow the user of existential quantification syntax, without needing to use GADT-style syntax. Fixes #20865 - - - - - 13fdf788 by David Binder at 2024-06-18T18:48:02-04:00 Add RTS flag --read-tix-file (GHC Proposal 612) This commit introduces the RTS flag `--read-tix-file=<yes|no>` which controls whether a preexisting .tix file is read in at the beginning of a program run. The default is currently `--read-tix-file=yes` but will change to `--read-tix-file=no` in a future release of GHC. For this reason, whenever a .tix file is read in a warning is emitted to stderr. This warning can be silenced by explicitly passing the `--read-tix-file=yes` option. Details can be found in the GHC proposal cited below. Users can query whether this flag has been used with the help of the module `GHC.RTS.Flags`. A new field `readTixFile` was added to the record `HpcFlags`. These changes have been discussed and approved in - GHC proposal 612: https://github.com/ghc-proposals/ghc-proposals/pull/612 - CLC proposal 276: https://github.com/haskell/core-libraries-committee/issues/276 - - - - - f0e3cb6a by Fendor at 2024-06-18T18:48:38-04:00 Improve sharing of duplicated values in `ModIface`, fixes #24723 As a `ModIface` often contains duplicated values that are not necessarily shared, we improve sharing by serialising the `ModIface` to an in-memory byte array. Serialisation uses deduplication tables, and deserialisation implicitly shares duplicated values. This helps reducing the peak memory usage while compiling in `--make` mode. The peak memory usage is especially smaller when generating interface files with core expressions (`-fwrite-if-simplified-core`). On agda, this reduces the peak memory usage: * `2.2 GB` to `1.9 GB` for a ghci session. On `lib:Cabal`, we report: * `570 MB` to `500 MB` for a ghci session * `790 MB` to `667 MB` for compiling `lib:Cabal` with ghc There is a small impact on execution time, around 2% on the agda code base. - - - - - 1bab7dde by Fendor at 2024-06-18T18:48:38-04:00 Avoid unneccessarily re-serialising the `ModIface` To reduce memory usage of `ModIface`, we serialise `ModIface` to an in-memory byte array, which implicitly shares duplicated values. This serialised byte array can be reused to avoid work when we actually write the `ModIface` to disk. We introduce a new field to `ModIface` which allows us to save the byte array, and write it direclty to disk if the `ModIface` wasn't changed after the initial serialisation. This requires us to change absolute offsets, for example to jump to the deduplication table for `Name` or `FastString` with relative offsets, as the deduplication byte array doesn't contain header information, such as fingerprints. To allow us to dump the binary blob to disk, we need to replace all absolute offsets with relative ones. We introduce additional helpers for `ModIface` binary serialisation, which construct relocatable binary blobs. We say the binary blob is relocatable, if the binary representation can be moved and does not contain any absolute offsets. Further, we introduce new primitives for `Binary` that allow to create relocatable binaries, such as `forwardGetRel` and `forwardPutRel`. ------------------------- Metric Decrease: MultiLayerModulesDefsGhcWithCore Metric Increase: MultiComponentModules MultiLayerModules T10421 T12150 T12234 T12425 T13035 T13253-spj T13701 T13719 T14697 T15703 T16875 T18698b T18140 T18304 T18698a T18730 T18923 T20049 T24582 T5837 T6048 T9198 T9961 mhu-perf ------------------------- These metric increases may look bad, but they are all completely benign, we simply allocate 1 MB per module for `shareIface`. As this allocation is quite quick, it has a negligible impact on run-time performance. In fact, the performance difference wasn't measurable on my local machine. Reducing the size of the pre-allocated 1 MB buffer avoids these test failures, but also requires us to reallocate the buffer if the interface file is too big. These reallocations *did* have an impact on performance, which is why I have opted to accept all these metric increases, as the number of allocated bytes is merely a guidance. This 1MB allocation increase causes a lot of tests to fail that generally have a low allocation number. E.g., increasing from 40MB to 41MB is a 2.5% increase. In particular, the tests T12150, T13253-spj, T18140, T18304, T18698a, T18923, T20049, T24582, T5837, T6048, and T9961 only fail on i386-darwin job, where the number of allocated bytes seems to be lower than in other jobs. The tests T16875 and T18698b fail on i386-linux for the same reason. - - - - - 099992df by Andreas Klebinger at 2024-06-18T18:49:14-04:00 Improve documentation of @Any@ type. In particular mention possible uses for non-lifted types. Fixes #23100. - - - - - 5e75412b by Jakob Bruenker at 2024-06-18T18:49:51-04:00 Update user guide to indicate support for 64-tuples - - - - - 4f5da595 by Andreas Klebinger at 2024-06-18T18:50:28-04:00 lint notes: Add more info to notes.stdout When fixing a note reference CI fails with a somewhat confusing diff. See #21123. This commit adds a line to the output file being compared which hopefully makes it clear this is the list of broken refs, not all refs. Fixes #21123 - - - - - 1eb15c61 by Jakob Bruenker at 2024-06-18T18:51:04-04:00 docs: Update mention of ($) type in user guide Fixes #24909 - - - - - 1d66c9e3 by Jan Hrček at 2024-06-18T18:51:47-04:00 Remove duplicate Anno instances - - - - - 8ea0ba95 by Sven Tennie at 2024-06-18T18:52:23-04:00 AArch64: Delete unused RegNos This has the additional benefit of getting rid of the -1 encoding (real registers start at 0.) - - - - - 325422e0 by Sjoerd Visscher at 2024-06-18T18:53:04-04:00 Bump stm submodule to current master - - - - - 64fba310 by Cheng Shao at 2024-06-18T18:53:40-04:00 testsuite: bump T17572 timeout on wasm32 - - - - - eb612fbc by Sven Tennie at 2024-06-19T06:46:00-04:00 AArch64: Simplify BL instruction The BL constructor carried unused data in its third argument. - - - - - b0300503 by Alan Zimmerman at 2024-06-19T06:46:36-04:00 TTG: Move SourceText from `Fixity` to `FixitySig` It is only used there, simplifies the use of `Fixity` in the rest of the code, and is moved into a TTG extension point. Precedes !12842, to simplify it - - - - - 842e119b by Rodrigo Mesquita at 2024-06-19T06:47:13-04:00 base: Deprecate some .Internal modules Deprecates the following modules according to clc-proposal #217: https://github.com/haskell/core-libraries-committee/issues/217 * GHC.TypeNats.Internal * GHC.TypeLits.Internal * GHC.ExecutionStack.Internal Closes #24998 - - - - - 24e89c40 by Jacco Krijnen at 2024-06-20T07:21:27-04:00 ttg: Use List instead of Bag in AST for LHsBindsLR Considering that the parser used to create a Bag of binds using a cons-based approach, it can be also done using lists. The operations in the compiler don't really require Bag. By using lists, there is no dependency on GHC.Data.Bag anymore from the AST. Progress towards #21592 - - - - - 04f5bb85 by Simon Peyton Jones at 2024-06-20T07:22:03-04:00 Fix untouchability test This MR fixes #24938. The underlying problem was tha the test for "does this implication bring in scope any equalities" was plain wrong. See Note [Tracking Given equalities] and Note [Let-bound skolems] both in GHC.Tc.Solver.InertSet. Then * Test LocalGivenEqs succeeds for a different reason than before; see (LBS2) in Note [Let-bound skolems] * New test T24938a succeeds because of (LBS2), whereas it failed before. * Test LocalGivenEqs2 now fails, as it should. * Test T224938, the repro from the ticket, fails, as it should. - - - - - 9a757a27 by Simon Peyton Jones at 2024-06-20T07:22:40-04:00 Fix demand signatures for join points This MR tackles #24623 and #23113 The main change is to give a clearer notion of "worker/wrapper arity", esp for join points. See GHC.Core.Opt.DmdAnal Note [Worker/wrapper arity and join points] This Note is a good summary of what this MR does: (1) The "worker/wrapper arity" of an Id is * For non-join-points: idArity * The join points: the join arity (Id part only of course) This is the number of args we will use in worker/wrapper. See `ww_arity` in `dmdAnalRhsSig`, and the function `workWrapArity`. (2) A join point's demand-signature arity may exceed the Id's worker/wrapper arity. See the `arity_ok` assertion in `mkWwBodies`. (3) In `finaliseArgBoxities`, do trimBoxity on any argument demands beyond the worker/wrapper arity. (4) In WorkWrap.splitFun, make sure we split based on the worker/wrapper arity (re)-computed by workWrapArity. - - - - - 5e8faaf1 by Jan Hrček at 2024-06-20T07:23:20-04:00 Update haddocks of Import/Export AST types - - - - - cd512234 by Hécate Kleidukos at 2024-06-20T07:24:02-04:00 haddock: Update bounds in cabal files and remove allow-newer stanza in cabal.project - - - - - 8a8ff8f2 by Rodrigo Mesquita at 2024-06-20T07:24:38-04:00 cmm: Don't parse MO_BSwap for W8 Don't support parsing bswap8, since bswap8 is not really an operation and would have to be implemented as a no-op (and currently is not implemented at all). Fixes #25002 - - - - - 5cc472f5 by sheaf at 2024-06-20T07:25:14-04:00 Delete unused testsuite files These files were committed by mistake in !11902. This commit simply removes them. - - - - - 7b079378 by Matthew Pickering at 2024-06-20T07:25:50-04:00 Remove left over debugging pragma from 2016 This pragma was accidentally introduced in 648fd73a7b8fbb7955edc83330e2910428e76147 The top-level cost centres lead to a lack of optimisation when compiling with profiling. - - - - - c872e09b by Hécate Kleidukos at 2024-06-20T19:28:36-04:00 haddock: Remove unused pragmata, qualify usages of Data.List functions, add more sanity checking flags by default This commit enables some extensions and GHC flags in the cabal file in a way that allows us to reduce the amount of prologuing on top of each file. We also prefix the usage of some List functions that removes ambiguity when they are also exported from the Prelude, like foldl'. In general, this has the effect of pointing out more explicitly that a linked list is used. Metric Increase: haddock.Cabal haddock.base haddock.compiler - - - - - 8c87d4e1 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00 Add test case for #23586 - - - - - 568de8a5 by Arnaud Spiwack at 2024-06-20T19:29:12-04:00 When matching functions in rewrite rules: ignore multiplicity When matching a template variable to an expression, we check that it has the same type as the matched expression. But if the variable `f` has type `A -> B` while the expression `e` has type `A %1 -> B`, the match was previously rejected. A principled solution would have `f` substituted by `\(%Many x) -> e x` or some other appropriate coercion. But since linearity is not properly checked in Core, we can be cheeky and simply ignore multiplicity while matching. Much easier. This has forced a change in the linter which, when `-dlinear-core-lint` is off, must consider that `a -> b` and `a %1 -> b` are equal. This is achieved by adding an argument to configure the behaviour of `nonDetCmpTypeX` and modify `ensureEqTys` to call to the new behaviour which ignores multiplicities when comparing two `FunTy`. Fixes #24725. - - - - - c8a8727e by Simon Peyton Jones at 2024-06-20T19:29:12-04:00 Faster type equality This MR speeds up type equality, triggered by perf regressions that showed up when fixing #24725 by parameterising type equality over whether to ignore multiplicity. The changes are: * Do not use `nonDetCmpType` for type /equality/. Instead use a specialised type-equality function, which we have always had! `nonDetCmpType` remains, but I did not invest effort in refactoring or optimising it. * Type equality is parameterised by - whether to expand synonyms - whether to respect multiplicities - whether it has a RnEnv2 environment In this MR I systematically specialise it for static values of these parameters. Much more direct and predictable than before. See Note [Specialising type equality] * We want to avoid comparing kinds if possible. I refactored how this happens, at least for `eqType`. See Note [Casts and coercions in type comparison] * To make Lint fast, we want to avoid allocating a thunk for <msg> in ensureEqTypes ty1 ty2 <msg> because the test almost always succeeds, and <msg> isn't needed. See Note [INLINE ensureEqTys] Metric Decrease: T13386 T5030 - - - - - 29f59c51 by Brandon Chinn at 2024-06-21T10:04:11-07:00 Add MultilineStrings extension - - - - - 36f3b3cc by Brandon Chinn at 2024-06-21T10:04:38-07:00 Add test cases for MultilineStrings - - - - - 30abcd9c by Brandon Chinn at 2024-06-21T10:04:39-07:00 Break out common lex_magic_hash logic for strings and chars - - - - - 9437e768 by Brandon Chinn at 2024-06-21T10:04:39-07:00 Factor out string processing functions - - - - - d2990425 by Brandon Chinn at 2024-06-21T10:04:39-07:00 Implement MultilineStrings (#24390) Updates haddock submodule for new ITmultiline constructor - - - - - efb79a21 by Brandon Chinn at 2024-06-21T10:04:54-07:00 Add docs for MultilineStrings - - - - - b1f8004e by Brandon Chinn at 2024-06-21T10:04:55-07:00 Address feedback - - - - - 30 changed files: - .gitlab/generate-ci/gen_ci.hs - .gitlab/jobs.yaml - .gitlab/rel_eng/mk-ghcup-metadata/mk_ghcup_metadata.py - CODEOWNERS - compiler/GHC.hs - compiler/GHC/Builtin/Names.hs - compiler/GHC/Builtin/Names/TH.hs - compiler/GHC/Builtin/PrimOps.hs - compiler/GHC/Builtin/Types.hs - compiler/GHC/ByteCode/Asm.hs - compiler/GHC/Cmm/CLabel.hs - compiler/GHC/Cmm/Node.hs - compiler/GHC/Cmm/Parser.y - compiler/GHC/Cmm/ThreadSanitizer.hs - compiler/GHC/CmmToAsm/AArch64/CodeGen.hs - compiler/GHC/CmmToAsm/AArch64/Instr.hs - compiler/GHC/CmmToAsm/AArch64/Ppr.hs - compiler/GHC/CmmToAsm/PIC.hs - compiler/GHC/CmmToAsm/PPC/CodeGen.hs - compiler/GHC/CmmToAsm/PPC/Ppr.hs - compiler/GHC/CmmToAsm/Wasm/FromCmm.hs - compiler/GHC/CmmToAsm/X86/CodeGen.hs - compiler/GHC/CmmToAsm/X86/Instr.hs - compiler/GHC/CmmToC.hs - compiler/GHC/CmmToLlvm/CodeGen.hs - compiler/GHC/Core.hs - compiler/GHC/Core/DataCon.hs - compiler/GHC/Core/Lint.hs - compiler/GHC/Core/Make.hs - compiler/GHC/Core/Multiplicity.hs The diff was not included because it is too large. View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5209d145f7f04def92091adb311a33cdbf7cf29a...b1f8004e71f7f83bb2b523e37991ca3f3341c50d -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/5209d145f7f04def92091adb311a33cdbf7cf29a...b1f8004e71f7f83bb2b523e37991ca3f3341c50d You're receiving this email because of your account on gitlab.haskell.org. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gitlab at gitlab.haskell.org Fri Jun 21 19:28:41 2024 From: gitlab at gitlab.haskell.org (Marge Bot (@marge-bot)) Date: Fri, 21 Jun 2024 15:28:41 -0400 Subject: [Git][ghc/ghc][wip/marge_bot_batch_merge_job] 2 commits: base: Add inits1 and tails1 to Data.List Message-ID: <6675d4696b39d_1f29d6119b08108e8@gitlab.mail> Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC Commits: 0f5f19f0 by Ryan Hendrickson at 2024-06-21T15:28:27-04:00 base: Add inits1 and tails1 to Data.List - - - - - 74c9ce12 by Matthew Pickering at 2024-06-21T15:28:29-04:00 bindist: Use complete relative paths when cding to directories If a user has configured CDPATH on their system then `cd lib` may change into an unexpected directory during the installation process. If you write `cd ./lib` then it will not consult `CDPATH` to determine what you mean. I have added a check on ghcup-ci to verify that the bindist installation works in this situation. Fixes #24951 - - - - - 15 changed files: - hadrian/bindist/Makefile - libraries/base/changelog.md - libraries/base/src/Data/List.hs - libraries/base/src/Data/List/NonEmpty.hs - libraries/ghc-internal/ghc-internal.cabal - + libraries/ghc-internal/src/GHC/Internal/Data/List/NonEmpty.hs - testsuite/tests/interface-stability/base-exports.stdout - testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs - testsuite/tests/interface-stability/base-exports.stdout-mingw32 - testsuite/tests/interface-stability/base-exports.stdout-ws-32 - + testsuite/tests/lib/base/InitsTails.hs - + testsuite/tests/lib/base/InitsTails.stdout - testsuite/tests/lib/base/all.T - utils/haddock/html-test/ref/Identifiers.html - utils/haddock/html-test/ref/Instances.html Changes: ===================================== hadrian/bindist/Makefile ===================================== @@ -169,7 +169,7 @@ install_lib: lib/settings $(INSTALL_DIR) "$(DESTDIR)$(ActualLibsDir)" @dest="$(DESTDIR)$(ActualLibsDir)"; \ - cd lib; \ + cd ./lib; \ for i in `$(FIND) . -type f`; do \ dir="`dirname $$i`" ; \ $(INSTALL_DIR) "$$dest/$$dir" ; \ @@ -197,7 +197,7 @@ install_docs: $(INSTALL_DIR) "$(DESTDIR)$(docdir)" if [ -d doc ]; then \ - cd doc; $(FIND) . -type f -exec sh -c \ + cd ./doc; $(FIND) . -type f -exec sh -c \ '$(INSTALL_DIR) "$(DESTDIR)$(docdir)/`dirname $$1`" && $(INSTALL_DATA) "$$1" "$(DESTDIR)$(docdir)/`dirname $$1`"' \ sh '{}' ';'; \ fi @@ -213,7 +213,7 @@ install_data: @echo "Copying data to $(DESTDIR)share" $(INSTALL_DIR) "$(DESTDIR)$(datadir)" if [ -d share ]; then \ - cd share; $(FIND) . -type f -exec sh -c \ + cd ./share; $(FIND) . -type f -exec sh -c \ '$(INSTALL_DIR) "$(DESTDIR)$(datadir)/`dirname $$1`" && \ $(INSTALL_DATA) "$$1" "$(DESTDIR)$(datadir)/`dirname $$1`"' \ sh '{}' ';'; \ @@ -235,7 +235,7 @@ export SHELL install_wrappers: install_bin_libdir install_hsc2hs_wrapper @echo "Installing wrapper scripts" $(INSTALL_DIR) "$(DESTDIR)$(WrapperBinsDir)" - for p in `cd wrappers; $(FIND) . ! -type d`; do \ + for p in `cd ./wrappers; $(FIND) . ! -type d`; do \ mk/install_script.sh "$$p" "$(DESTDIR)/$(WrapperBinsDir)/$$p" "$(WrapperBinsDir)" "$(ActualBinsDir)" "$(ActualBinsDir)/$$p" "$(ActualLibsDir)" "$(docdir)" "$(includedir)"; \ done ===================================== libraries/base/changelog.md ===================================== @@ -8,6 +8,7 @@ * The `HasField` class now supports representation polymorphism ([CLC proposal #194](https://github.com/haskell/core-libraries-committee/issues/194)) * Make `read` accept binary integer notation ([CLC proposal #177](https://github.com/haskell/core-libraries-committee/issues/177)) * Improve the performance of `Data.List.sort` using an improved merging strategy. Instead of `compare`, `sort` now uses `(>)` which may break *malformed* `Ord` instances ([CLC proposal #236](https://github.com/haskell/core-libraries-committee/issues/236)) + * Add `inits1` and `tails1` to `Data.List`, factored from the corresponding functions in `Data.List.NonEmpty` ([CLC proposal #252](https://github.com/haskell/core-libraries-committee/issues/252)) * Add `firstA` and `secondA` to `Data.Bitraversable`. ([CLC proposal #172](https://github.com/haskell/core-libraries-committee/issues/172)) ## 4.20.0.0 *TBA* ===================================== libraries/base/src/Data/List.hs ===================================== @@ -83,7 +83,9 @@ module Data.List stripPrefix, group, inits, + inits1, tails, + tails1, -- ** Predicates isPrefixOf, isSuffixOf, @@ -177,3 +179,67 @@ module Data.List ) where import GHC.Internal.Data.List +import GHC.Internal.Data.List.NonEmpty (NonEmpty(..)) +import GHC.List (build) + +inits1, tails1 :: [a] -> [NonEmpty a] + +-- | The 'inits1' function returns all non-empty initial segments of the +-- argument, shortest first. +-- +-- @since 4.21.0.0 +-- +-- ==== __Laziness__ +-- +-- Note that 'inits1' has the following strictness property: +-- @inits1 (xs ++ _|_) = inits1 xs ++ _|_@ +-- +-- In particular, +-- @inits1 _|_ = _|_@ +-- +-- ==== __Examples__ +-- +-- >>> inits1 "abc" +-- ['a' :| "",'a' :| "b",'a' :| "bc"] +-- +-- >>> inits1 [] +-- [] +-- +-- inits1 is productive on infinite lists: +-- +-- >>> take 3 $ inits1 [1..] +-- [1 :| [],1 :| [2],1 :| [2,3]] +inits1 [] = [] +inits1 (x : xs) = map (x :|) (inits xs) + +-- | \(\mathcal{O}(n)\). The 'tails1' function returns all non-empty final +-- segments of the argument, longest first. +-- +-- @since 4.21.0.0 +-- +-- ==== __Laziness__ +-- +-- Note that 'tails1' has the following strictness property: +-- @tails1 _|_ = _|_@ +-- +-- >>> tails1 undefined +-- *** Exception: Prelude.undefined +-- +-- >>> drop 1 (tails1 [undefined, 1, 2]) +-- [1 :| [2],2 :| []] +-- +-- ==== __Examples__ +-- +-- >>> tails1 "abc" +-- ['a' :| "bc",'b' :| "c",'c' :| ""] +-- +-- >>> tails1 [1, 2, 3] +-- [1 :| [2,3],2 :| [3],3 :| []] +-- +-- >>> tails1 [] +-- [] +{-# INLINABLE tails1 #-} +tails1 lst = build (\c n -> + let tails1Go [] = n + tails1Go (x : xs) = (x :| xs) `c` tails1Go xs + in tails1Go lst) ===================================== libraries/base/src/Data/List/NonEmpty.hs ===================================== @@ -109,10 +109,10 @@ import Prelude hiding (break, cycle, drop, dropWhile, import qualified Prelude import Control.Applicative (Applicative (..), Alternative (many)) +import qualified Data.List as List import GHC.Internal.Data.Foldable hiding (length, toList) import qualified GHC.Internal.Data.Foldable as Foldable import GHC.Internal.Data.Function (on) -import qualified GHC.Internal.Data.List as List import GHC.Internal.Data.Ord (comparing) import GHC.Internal.Base (NonEmpty(..)) import GHC.Internal.Stack.Types (HasCallStack) @@ -273,15 +273,7 @@ inits = fromList . List.inits . Foldable.toList -- -- @since 4.18 inits1 :: NonEmpty a -> NonEmpty (NonEmpty a) -inits1 = - -- fromList is an unsafe function, but this usage should be safe, since: - -- * `inits xs = [[], ..., init (init xs), init xs, xs]` - -- * If `xs` is nonempty, it follows that `inits xs` contains at least one nonempty - -- list, since `last (inits xs) = xs`. - -- * The only empty element of `inits xs` is the first one (by the definition of `inits`) - -- * Therefore, if we take all but the first element of `inits xs` i.e. - -- `tail (inits xs)`, we have a nonempty list of nonempty lists - fromList . Prelude.map fromList . List.drop 1 . List.inits . Foldable.toList +inits1 = fromList . List.inits1 . Foldable.toList -- | The 'tails' function takes a stream @xs@ and returns all the -- suffixes of @xs@, starting with the longest. The result is 'NonEmpty' @@ -301,15 +293,7 @@ tails = fromList . List.tails . Foldable.toList -- -- @since 4.18 tails1 :: NonEmpty a -> NonEmpty (NonEmpty a) -tails1 = - -- fromList is an unsafe function, but this usage should be safe, since: - -- * `tails xs = [xs, tail xs, tail (tail xs), ..., []]` - -- * If `xs` is nonempty, it follows that `tails xs` contains at least one nonempty - -- list, since `head (tails xs) = xs`. - -- * The only empty element of `tails xs` is the last one (by the definition of `tails`) - -- * Therefore, if we take all but the last element of `tails xs` i.e. - -- `init (tails xs)`, we have a nonempty list of nonempty lists - fromList . Prelude.map fromList . List.init . List.tails . Foldable.toList +tails1 = fromList . List.tails1 . Foldable.toList -- | @'insert' x xs@ inserts @x@ into the last position in @xs@ where it -- is still less than or equal to the next element. In particular, if the ===================================== libraries/ghc-internal/ghc-internal.cabal ===================================== @@ -122,6 +122,7 @@ Library GHC.Internal.Data.IORef GHC.Internal.Data.Ix GHC.Internal.Data.List + GHC.Internal.Data.List.NonEmpty GHC.Internal.Data.Maybe GHC.Internal.Data.Monoid GHC.Internal.Data.OldList ===================================== libraries/ghc-internal/src/GHC/Internal/Data/List/NonEmpty.hs ===================================== @@ -0,0 +1,7 @@ +{-# LANGUAGE Trustworthy #-} + +module GHC.Internal.Data.List.NonEmpty + ( NonEmpty(..) + ) where + +import GHC.Internal.Base ===================================== testsuite/tests/interface-stability/base-exports.stdout ===================================== @@ -1332,6 +1332,7 @@ module Data.List where head :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> a init :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] inits :: forall a. [a] -> [[a]] + inits1 :: forall a. [a] -> [GHC.Internal.Base.NonEmpty a] insert :: forall a. GHC.Classes.Ord a => a -> [a] -> [a] insertBy :: forall a. (a -> a -> GHC.Types.Ordering) -> a -> [a] -> [a] intercalate :: forall a. [a] -> [[a]] -> [a] @@ -1382,6 +1383,7 @@ module Data.List where sum :: forall (t :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, GHC.Internal.Num.Num a) => t a -> a tail :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] tails :: forall a. [a] -> [[a]] + tails1 :: forall a. [a] -> [GHC.Internal.Base.NonEmpty a] take :: forall a. GHC.Types.Int -> [a] -> [a] takeWhile :: forall a. (a -> GHC.Types.Bool) -> [a] -> [a] transpose :: forall a. [[a]] -> [[a]] ===================================== testsuite/tests/interface-stability/base-exports.stdout-javascript-unknown-ghcjs ===================================== @@ -1332,6 +1332,7 @@ module Data.List where head :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> a init :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] inits :: forall a. [a] -> [[a]] + inits1 :: forall a. [a] -> [GHC.Internal.Base.NonEmpty a] insert :: forall a. GHC.Classes.Ord a => a -> [a] -> [a] insertBy :: forall a. (a -> a -> GHC.Types.Ordering) -> a -> [a] -> [a] intercalate :: forall a. [a] -> [[a]] -> [a] @@ -1382,6 +1383,7 @@ module Data.List where sum :: forall (t :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, GHC.Internal.Num.Num a) => t a -> a tail :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] tails :: forall a. [a] -> [[a]] + tails1 :: forall a. [a] -> [GHC.Internal.Base.NonEmpty a] take :: forall a. GHC.Types.Int -> [a] -> [a] takeWhile :: forall a. (a -> GHC.Types.Bool) -> [a] -> [a] transpose :: forall a. [[a]] -> [[a]] ===================================== testsuite/tests/interface-stability/base-exports.stdout-mingw32 ===================================== @@ -1332,6 +1332,7 @@ module Data.List where head :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> a init :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] inits :: forall a. [a] -> [[a]] + inits1 :: forall a. [a] -> [GHC.Internal.Base.NonEmpty a] insert :: forall a. GHC.Classes.Ord a => a -> [a] -> [a] insertBy :: forall a. (a -> a -> GHC.Types.Ordering) -> a -> [a] -> [a] intercalate :: forall a. [a] -> [[a]] -> [a] @@ -1382,6 +1383,7 @@ module Data.List where sum :: forall (t :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, GHC.Internal.Num.Num a) => t a -> a tail :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] tails :: forall a. [a] -> [[a]] + tails1 :: forall a. [a] -> [GHC.Internal.Base.NonEmpty a] take :: forall a. GHC.Types.Int -> [a] -> [a] takeWhile :: forall a. (a -> GHC.Types.Bool) -> [a] -> [a] transpose :: forall a. [[a]] -> [[a]] ===================================== testsuite/tests/interface-stability/base-exports.stdout-ws-32 ===================================== @@ -1332,6 +1332,7 @@ module Data.List where head :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> a init :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] inits :: forall a. [a] -> [[a]] + inits1 :: forall a. [a] -> [GHC.Internal.Base.NonEmpty a] insert :: forall a. GHC.Classes.Ord a => a -> [a] -> [a] insertBy :: forall a. (a -> a -> GHC.Types.Ordering) -> a -> [a] -> [a] intercalate :: forall a. [a] -> [[a]] -> [a] @@ -1382,6 +1383,7 @@ module Data.List where sum :: forall (t :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, GHC.Internal.Num.Num a) => t a -> a tail :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a] tails :: forall a. [a] -> [[a]] + tails1 :: forall a. [a] -> [GHC.Internal.Base.NonEmpty a] take :: forall a. GHC.Types.Int -> [a] -> [a] takeWhile :: forall a. (a -> GHC.Types.Bool) -> [a] -> [a] transpose :: forall a. [[a]] -> [[a]] ===================================== testsuite/tests/lib/base/InitsTails.hs ===================================== @@ -0,0 +1,23 @@ +module Main (main) where + +import Data.List (inits, inits1, tails, tails1) + +main :: IO () +main = do + print $ inits "abc" + print $ inits ([] :: [Int]) + print $ take 5 $ inits [1..] + print $ take 3 $ inits ([1, 2] ++ undefined) + + print $ inits1 "abc" + print $ inits1 ([] :: [Int]) + print $ take 3 $ inits1 [1..] + print $ take 2 $ inits1 ([1, 2] ++ undefined) + + print $ tails "abc" + print $ tails ([] :: [Int]) + print $ drop 1 (tails [undefined, 1, 2]) + + print $ tails1 "abc" + print $ tails1 ([] :: [Int]) + print $ drop 1 (tails1 [undefined, 1, 2]) ===================================== testsuite/tests/lib/base/InitsTails.stdout ===================================== @@ -0,0 +1,14 @@ +["","a","ab","abc"] +[[]] +[[],[1],[1,2],[1,2,3],[1,2,3,4]] +[[],[1],[1,2]] +['a' :| "",'a' :| "b",'a' :| "bc"] +[] +[1 :| [],1 :| [2],1 :| [2,3]] +[1 :| [],1 :| [2]] +["abc","bc","c",""] +[[]] +[[1,2],[2],[]] +['a' :| "bc",'b' :| "c",'c' :| ""] +[] +[1 :| [2],2 :| []] ===================================== testsuite/tests/lib/base/all.T ===================================== @@ -12,3 +12,4 @@ test('Unsnoc', normal, compile_and_run, ['']) test('First-Semigroup-sconcat', normal, compile_and_run, ['']) test('First-Monoid-sconcat', normal, compile_and_run, ['']) test('Sort', normal, compile_and_run, ['']) +test('InitsTails', normal, compile_and_run, ['']) ===================================== utils/haddock/html-test/ref/Identifiers.html ===================================== @@ -142,7 +142,7 @@ >